./CBFlib-0.9.2.2/0000755000076500007650000000000011603751102011576 5ustar yayayaya./CBFlib-0.9.2.2/m4/0000755000076500007650000000000011603703065012123 5ustar yayayaya./CBFlib-0.9.2.2/m4/fcb_exit_binary.m40000644000076500007650000000476211603702103015515 0ustar yayayayam4_include(`fcblib_defines.m4')m4_dnl ` INTEGER FUNCTION FCB_EXIT_BINARY(TAPIN,LAST_CHAR,FCB_BYTES_IN_REC,& BYTE_IN_FILE,REC_IN_FILE,BUFFER, & PADDING ) !----------------------------------------------------------------------- ! Skip to end of binary section that was just read !----------------------------------------------------------------------- IMPLICIT NONE INTEGER, INTENT(IN) :: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: BYTE_IN_FILE,REC_IN_FILE INTEGER(1),INTENT(INOUT):: LAST_CHAR,BUFFER(FCB_BYTES_IN_REC) INTEGER(8),INTENT(IN) :: PADDING !External functions called' fcb_interface_FCB_READ_BYTE fcb_interface_FCB_READ_LINE fcb_interface_FCB_CI_STRNCMPARR `!----------------------------------------------------------------------- INTEGER,PARAMETER :: LINESIZE=2048 INTEGER(1) LINE(LINESIZE) ! BUFFER FOR THE NEXT LINE INTEGER LINELEN ! VALID CHARACTERS IN LINE INTEGER ITEM ! 1 FOR MIME ITEM FOUND, 0 OTHERWISE INTEGER QUOTE INTEGER TEXT_BITS INTEGER COUNT INTEGER BOUND_FOUND CHARACTER*31 BOUNDARY DATA BOUNDARY/"--CIF-BINARY-FORMAT-SECTION----"/ !----------------------------------------------------------------------- ! -- Skip the trailing pad BYTE_IN_FILE = BYTE_IN_FILE+PADDING ! -- Skip to MIME boundary BOUND_FOUND = 0 DO FCB_EXIT_BINARY = & FCB_READ_LINE(TAPIN,LAST_CHAR,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER,LINE,LINESIZE,LINELEN) IF(FCB_EXIT_BINARY.NE.0 ) RETURN ! *** DEBUG *** PRINT *," LINELEN, LINE: ", LINELEN, LINE(1:LINELEN) IF (BOUND_FOUND .EQ. 0) THEN IF (FCB_CI_STRNCMPARR(BOUNDARY,LINE,LINELEN,31).EQ.0) THEN BOUND_FOUND = 1 ! *** DEBUG *** PRINT *, & ! "MIME BOUNDARY --CIF-BINARY-FORMAT-SECTION---- FOUND" END IF END IF IF (LINE(1).EQ.IACHAR(''`;''`)) THEN IF (LINELEN.EQ.1.OR.LINE(2).EQ.32.OR.LINE(2).EQ.9) THEN IF (BOUND_FOUND.EQ.0) THEN PRINT *, " END OF TEXT FOUND BEFORE MIME BOUNDARY" ELSE EXIT END IF END IF END IF END DO FCB_EXIT_BINARY = 0 RETURN END FUNCTION FCB_EXIT_BINARY' ./CBFlib-0.9.2.2/m4/fcb_open_cifin.m40000644000076500007650000000311411603702103015277 0ustar yayayayam4_include(`fcblib_defines.m4')m4_dnl ` INTEGER FUNCTION FCB_OPEN_CIFIN(FILNAM,TAPIN,LAST_CHAR, & FCB_BYTES_IN_REC,BYTE_IN_FILE,REC_IN_FILE,BUFFER) !----------------------------------------------------------------------- ! FILNAM - Name of the file countaining the image (GIVEN) ! TAPIN - Fortran device unit number assigned to image file (GIVEN) ! LAST_CHAR - ! Last character read (RESULT) ! FCB_BYTES_IN_REC - ! Number of bytes in a record (GIVEN) ! BYTE_IN_FILE - ! Byte (counting from 1) of the byte to read (RESULT) ! REC_IN_FILE - ! Record (counting from 1) of next record to read (RESULT) ! BUFFER - Array of length FCB_BYTES_IN_REC (GIVEN) !----------------------------------------------------------------------- IMPLICIT NONE CHARACTER(len=*),INTENT(IN) :: FILNAM INTEGER, INTENT(IN) :: TAPIN,FCB_BYTES_IN_REC INTEGER(1), INTENT(OUT):: LAST_CHAR INTEGER, INTENT(OUT):: BYTE_IN_FILE,REC_IN_FILE INTEGER(1), INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) INTEGER FCB_RECORD_SIZE ' fcb_errcode_CBF_FORMAT fcb_errcode_CBF_FILEOPEN fcb_errcode_CBF_FILEREAD fcb_interface_FCB_CI_STRNCMPARR fcb_macro_FCB_OPEN_CIFIN(`IOSTAT=FCB_OPEN_CIFIN', `IOSTAT=FCB_OPEN_CIFIN', `THEN FCB_OPEN_CIFIN = CBF_FILEREAD ENDIF')` RETURN END FUNCTION FCB_OPEN_CIFIN' ./CBFlib-0.9.2.2/m4/setup_py.m40000644000076500007650000000117511603702103014231 0ustar yayayaya# # pycbf/setup.py generated from m4/setup_py.m4 # `# Import the things to build python binary extensions from distutils.core import setup, Extension # Make our extension module e = Extension(''`_pycbf''`, sources = ["pycbf_wrap.c","../src/cbf_simple.c"], extra_compile_args=["-g"], 'm4_ifelse(regexlibdir,`NOREGEXLIBDIR',`library_dirs=["../lib/"],',`library_dirs=["../lib/","'regexlibdir`"],')` 'm4_ifelse(regexlib,`NOREGEXLIB',`libraries=["cbf"],',`libraries=["cbf","'regexlib`"],')` include_dirs = ["../include"] ) # Build it setup(name="_pycbf",ext_modules=[e],)' ./CBFlib-0.9.2.2/m4/fcb_next_binary.m40000644000076500007650000005723611603702103015526 0ustar yayayayam4_include(`fcblib_defines.m4')m4_dnl ` INTEGER FUNCTION FCB_NEXT_BINARY(TAPIN,LAST_CHAR,FCB_BYTES_IN_REC,& BYTE_IN_FILE,REC_IN_FILE,BUFFER, & ENCODING,SIZE,ID,DIGEST, & COMPRESSION,BITS,VORZEICHEN,REELL,& BYTEORDER,DIMOVER,DIM1,DIM2,DIM3, & PADDING ) !----------------------------------------------------------------------- ! Skip to the next binary and parse MIME header. !----------------------------------------------------------------------- IMPLICIT NONE INTEGER, INTENT(IN) :: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: BYTE_IN_FILE,REC_IN_FILE INTEGER(1),INTENT(INOUT):: LAST_CHAR,BUFFER(FCB_BYTES_IN_REC) INTEGER, INTENT(OUT) :: ENCODING INTEGER, INTENT(OUT) :: SIZE !Binary size INTEGER, INTENT(OUT) :: ID !Binary ID CHARACTER(len=*),INTENT(OUT):: DIGEST !Message digest INTEGER, INTENT(OUT):: COMPRESSION INTEGER, INTENT(OUT):: BITS,VORZEICHEN,REELL CHARACTER(len=*),INTENT(OUT):: BYTEORDER ! Possible parameter values for BYTEORDER are: ! "LITTLE_ENDIAN" supported ! "BIG_ENDIAN" not supported INTEGER(8), INTENT(OUT):: DIMOVER INTEGER(8), INTENT(OUT):: DIM1 INTEGER(8), INTENT(OUT):: DIM2 INTEGER(8), INTENT(OUT):: DIM3 INTEGER(8), INTENT(OUT):: PADDING ' fcb_param_ENC_LIST_ALL fcb_param_CBF_LIST_ALL ` !External functions called' fcb_interface_FCB_SKIP_WHITESPACE fcb_interface_FCB_CI_STRNCMPARR fcb_interface_FCB_NBLEN_ARRAY fcb_interface_FCB_READ_LINE fcb_interface_FCB_ATOL_WCNT `!----------------------------------------------------------------------- ' fcb_errcode_CBF_FORMAT ` INTEGER,PARAMETER :: LINESIZE=2048 INTEGER CONTINUATION INTEGER(1) LINE(LINESIZE) ! BUFFER FOR THE NEXT LINE INTEGER LINELEN ! VALID CHARACTERS IN LINE INTEGER IC ! CHARACTER WITHIN LINE INTEGER STATE ! SELECTION FROM VALUE (0, ...) INTEGER ITEM ! 1 FOR MIME ITEM FOUND, 0 OTHERWISE INTEGER LINE_COUNT ! NUMBER OF LINES INTO HEADER INTEGER FRESH_LINE INTEGER QUOTE INTEGER TEXT_BITS INTEGER COUNT INTEGER FAILURE INTEGER I,INTEXT,J INTEGER VALUELEN(12) CHARACTER*29 BOUNDARY CHARACTER*32 VALUE(12) DATA BOUNDARY/"--CIF-BINARY-FORMAT-SECTION--"/ DATA VALUE/ & "Content-Type:", & ! /* State 0 */ "Content-Transfer-Encoding:", & ! /* State 1 */ "Content-MD5:", & ! /* State 2 */ "X-Binary-Size:", & ! /* State 3 */ "X-Binary-ID:", & ! /* State 4 */ "X-Binary-Element-Type:", & ! /* State 5 */ "X-Binary-Element-Byte-Order:", & ! /* State 6 */ "X-Binary-Size-Fastest-Dimension:", & ! /* State 7 */ "X-Binary-Size-Second-Dimension:", & ! /* State 8 */ "X-Binary-Size-Third-Dimension:", & ! /* State 9 */ "X-Binary-Size-Padding:", & ! /* State 10 */ "X-Binary-Number-of-Elements:" & ! /* State 11 */ / !----------------------------------------------------------------------- DO I = 1,12 VALUELEN(I)=LEN(TRIM(VALUE(I))) END DO FAILURE = 0 ! -- Repeat : Skip lines until the start of a text field is reached and ! -- then loop until a mime boundary or end of the text field is reached INTEXT=0 DO IF (FCB_READ_LINE(TAPIN,LAST_CHAR,FCB_BYTES_IN_REC,BYTE_IN_FILE,& REC_IN_FILE,BUFFER,LINE,LINESIZE,LINELEN).NE.0 ) THEN FCB_NEXT_BINARY=1 RETURN END IF ! *** DEBUG *** PRINT *," LINELEN, LINE: ", LINELEN, LINE(1:LINELEN) IF (LINELEN.GT.0)THEN IF (INTEXT.EQ.0)THEN IF (LINE(1).EQ.IACHAR(''`;''`))INTEXT=1 !start of a text field ! *** DEBUG *** PRINT *, "FOUND START OF TEXT FIELD" ELSE IF (LINE(1).EQ.IACHAR(''`;''`))THEN IF (LINELEN.EQ.1.OR.LINE(2).EQ.32.OR.LINE(2).EQ.9) & INTEXT=0 !end of the text field is reached ENDIF IF (FCB_CI_STRNCMPARR(BOUNDARY,LINE,LINELEN,29).EQ.0)EXIT ENDIF ENDIF ENDDO ! *** DEBUG *** PRINT *, "MIME BOUNDARY --CIF-BINARY-FORMAT-SECTION-- FOUND" !----------------------------------------------------------------------- STATE = -1 LINE_COUNT = 0 FRESH_LINE = 0 ENCODING = 0 SIZE = 0 ID = 0 DIGEST = "" COMPRESSION = CBF_NONE BITS = 0 VORZEICHEN = -1 REELL = -1 BYTEORDER="LITTLE_ENDIAN" DIMOVER = 0 DIM1 = 0 DIM2 = 0 DIM3 = 0 PADDING = 0 DO IF (FRESH_LINE.EQ.0) THEN IF (FCB_READ_LINE(TAPIN,LAST_CHAR,FCB_BYTES_IN_REC, & BYTE_IN_FILE,REC_IN_FILE,BUFFER,LINE,LINESIZE,LINELEN).NE.0)& THEN FCB_NEXT_BINARY=1 RETURN ENDIF IF (LINELEN.GT.0 .AND. LINE(1).EQ.IACHAR(''`;''`) .AND. & (LINELEN.EQ.1 .OR. LINE(2).EQ.IACHAR(''` ''`) .OR. & LINE(2).EQ.Z''`09''`) ) GO TO 100 IF (FCB_CI_STRNCMPARR(BOUNDARY,LINE,LINELEN,29).EQ.0) & GO TO 100 END IF FRESH_LINE = 0 LINE_COUNT = LINE_COUNT+1 CONTINUATION = 0 IF (LINELEN.GT.0.AND. & (LINE(1).EQ.IACHAR(''` ''`).OR.LINE(1).EQ.Z''`09''`))CONTINUATION=1 ITEM = 0 IF (CONTINUATION .EQ. 0 ) THEN DO IC = 1, LINELEN IF ((LINE(IC).EQ.IACHAR(''`:''`)).AND.(IC.GT.1))ITEM=1 IF ((ITEM.NE.0).OR.(LINE(IC).LE.32.OR.LINE(IC).GE.127)) EXIT END DO END IF ! Check for the end of the header IF (LINE_COUNT.GT.1.AND.FCB_NBLEN_ARRAY(LINE,LINELEN).EQ.0) THEN FCB_NEXT_BINARY = 0 RETURN END IF ! Check for valid header-ness of line IF (ITEM.EQ.0.AND.(LINE_COUNT.EQ.1.OR.CONTINUATION.EQ.0)) GO TO 110 ! Look for the entries we are interested in IC = 1 IF (ITEM.NE.0) THEN DO STATE = 11,0,-1 J=STATE+1 I=VALUELEN(J) IF (FCB_CI_STRNCMPARR(VALUE(J)(1:I),LINE,LINELEN,I).EQ.0)THEN IC = I+1 EXIT END IF END DO END IF ! Skip past comments and whitespace IF (FCB_SKIP_WHITESPACE(TAPIN,LAST_CHAR,FCB_BYTES_IN_REC, & BYTE_IN_FILE,REC_IN_FILE,BUFFER,LINE,LINESIZE,LINELEN,IC, & FRESH_LINE).NE.0) GO TO 100 SELECT CASE (STATE) ! Get the value CASE (0) !"Content-Type:" I=LINELEN-IC+1 IF (FCB_CI_STRNCMPARR("application/",LINE(IC:LINELEN),I,12).NE.0.AND.& FCB_CI_STRNCMPARR("image/", LINE(IC:LINELEN),I, 6).NE.0.AND.& FCB_CI_STRNCMPARR("text/", LINE(IC:LINELEN),I, 5).NE.0.AND.& FCB_CI_STRNCMPARR("audio/", LINE(IC:LINELEN),I, 6).NE.0.AND.& FCB_CI_STRNCMPARR("video/", LINE(IC:LINELEN),I, 6).NE.0) & GO TO 110 DO IF (IC.GT.LINELEN)EXIT ! Skip to the end of the section (a semicolon) DO IF (IC.GT.LINELEN)EXIT IF (LINE(IC).EQ.Z''`22''`) THEN ! double quote IC = IC+1 DO IF (IC.GT.LINELEN)EXIT IF (LINE(IC).EQ.Z''`22''`) THEN !double quote IC = IC+1 EXIT ELSE IF (LINE(IC).EQ.Z''`5C''`) THEN !backslash IC = IC+1 END IF IF (IC .LE. LINELEN) IC = IC+1 END IF END DO ELSE IF (LINE(IC).EQ.IACHAR(''`(''`)) THEN FCB_NEXT_BINARY = FCB_SKIP_WHITESPACE(TAPIN, & LAST_CHAR,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER,LINE,LINESIZE,LINELEN,IC, & FRESH_LINE) IF (FCB_NEXT_BINARY.NE.0) RETURN ELSE IF (LINE(IC).EQ.IACHAR(''`;''`)) THEN IC = IC+1 EXIT ELSE IC = IC+1 END IF END IF END IF END DO FCB_NEXT_BINARY = FCB_SKIP_WHITESPACE(TAPIN,LAST_CHAR, & FCB_BYTES_IN_REC,BYTE_IN_FILE,REC_IN_FILE,BUFFER, & LINE,LINESIZE,LINELEN,IC,FRESH_LINE) IF (FCB_NEXT_BINARY.NE.0) RETURN IF (FCB_CI_STRNCMPARR("conversions", & LINE(IC:LINELEN), LINELEN-IC+1, 11) .EQ.0 ) THEN IC = IC+11 FCB_NEXT_BINARY = FCB_SKIP_WHITESPACE(TAPIN,LAST_CHAR, & FCB_BYTES_IN_REC,BYTE_IN_FILE,REC_IN_FILE,BUFFER, & LINE,LINESIZE,LINELEN,IC,FRESH_LINE) IF (FCB_NEXT_BINARY.NE.0) RETURN IF (LINE(IC).EQ.IACHAR(''`=''`)) THEN IC = IC+1 FCB_NEXT_BINARY = FCB_SKIP_WHITESPACE(TAPIN,LAST_CHAR, & FCB_BYTES_IN_REC,BYTE_IN_FILE,REC_IN_FILE,BUFFER, & LINE,LINESIZE,LINELEN,IC,FRESH_LINE) IF (FCB_NEXT_BINARY.NE.0) RETURN QUOTE = 0 IF (LINE(IC).EQ.Z''`22''`) QUOTE=1 ! double quote COMPRESSION = CBF_NONE IF (FCB_CI_STRNCMPARR("x-CBF_PACKED", & LINE(IC+QUOTE:LINELEN),LINELEN-IC-QUOTE+1,12).EQ.0) & COMPRESSION=CBF_PACKED IF (FCB_CI_STRNCMPARR("x-CBF_PACKED_V2", & LINE(IC+QUOTE:LINELEN),LINELEN-IC-QUOTE+1,15).EQ.0) & COMPRESSION=CBF_PACKED_V2 IF (FCB_CI_STRNCMPARR("x-CBF_CANONICAL", & LINE(IC+QUOTE:LINELEN),LINELEN-IC-QUOTE+1,15).EQ.0) & COMPRESSION=CBF_CANONICAL IF (FCB_CI_STRNCMPARR("x-cbf_byte_offset", & LINE(IC+QUOTE:LINELEN),LINELEN-IC-QUOTE+1,17).EQ.0) & COMPRESSION=CBF_BYTE_OFFSET IF (FCB_CI_STRNCMPARR("x-cbf_predictor", & LINE(IC+QUOTE:LINELEN),LINELEN-IC-QUOTE+1,15).EQ.0) & COMPRESSION=CBF_PREDICTOR IF ( (COMPRESSION .EQ. CBF_PACKED) .OR. & (COMPRESSION .EQ. CBF_PACKED_V2) ) THEN DO IF (IC.GT.LINELEN)EXIT ! Skip to the end of the section (a semicolon) DO IF (IC.GT.LINELEN)EXIT IF (LINE(IC).EQ.Z''`22''`) THEN ! double quote IC = IC+1 DO IF (IC.GT.LINELEN)EXIT IF (LINE(IC).EQ.Z''`22''`) THEN !double quote IC = IC+1 EXIT ELSE IF (LINE(IC).EQ.Z''`5C''`) THEN !backslash IC = IC+1 END IF IF (IC .LE. LINELEN) IC = IC+1 END IF END DO ELSE IF (LINE(IC).EQ.IACHAR(''`(''`)) THEN FCB_NEXT_BINARY = FCB_SKIP_WHITESPACE(TAPIN, & LAST_CHAR,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER,LINE,LINESIZE,LINELEN,IC, & FRESH_LINE) IF (FCB_NEXT_BINARY.NE.0) RETURN ELSE IF (LINE(IC).EQ.IACHAR(''`;''`)) THEN IC = IC+1 EXIT ELSE IC = IC+1 END IF END IF END IF FCB_NEXT_BINARY = FCB_SKIP_WHITESPACE(TAPIN, & LAST_CHAR,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER,LINE,LINESIZE,LINELEN,IC, & FRESH_LINE) IF (FCB_NEXT_BINARY.NE.0) RETURN QUOTE = 0 IF (LINE(IC).EQ.Z''`22''`) QUOTE=1 ! double quote IF (FCB_CI_STRNCMPARR("uncorrelated_sections", & LINE(IC+QUOTE:LINELEN),LINELEN-IC-QUOTE+1,21).EQ.0) & COMPRESSION = IOR(COMPRESSION,CBF_UNCORRELATED_SECTIONS) IF (FCB_CI_STRNCMPARR("flat", & LINE(IC+QUOTE:LINELEN),LINELEN-IC-QUOTE+1,4).EQ.0) & COMPRESSION = IOR(COMPRESSION,CBF_FLAT_IMAGE) END DO END DO END IF END IF END IF END DO STATE = -1 ! *** DEBUG *** PRINT *, "COMPRESSION: ", COMPRESSION CASE (1) ! Binary encoding FAILURE = 1 QUOTE = 0; IF (LINE(IC) .EQ. Z''`22''`) QUOTE = 1 !double quote IF (FCB_CI_STRNCMPARR("Quoted-Printable", & LINE(IC+QUOTE:LINELEN), LINELEN-IC-QUOTE+1, 16) .EQ. 0)THEN IF (IC+16.EQ.LINELEN+1 .OR. & FCB_NBLEN_ARRAY(LINE(IC+16),1).EQ.0 .OR. & LINE(IC+16).EQ.IACHAR(''`(''`).OR. & (QUOTE.EQ.1.AND.LINE(IC+16).EQ.Z''`22''`)) THEN !double quote FAILURE = 0 ENCODING = ENC_QP END IF END IF IF (FCB_CI_STRNCMPARR("Base64", & LINE(IC+QUOTE:LINELEN), LINELEN-IC-QUOTE+1, 6) .EQ. 0)THEN IF (IC+6.EQ.LINELEN+1 .OR. & FCB_NBLEN_ARRAY(LINE(IC+6),1).EQ.0 .OR. & LINE(IC+6).EQ.IACHAR(''`(''`).OR. & (QUOTE.EQ.1.AND.LINE(IC+6).EQ.Z''`22''`)) THEN ! double quote FAILURE = 0 ENCODING = ENC_BASE64 END IF END IF IF (FCB_CI_STRNCMPARR("X-Base32k", & LINE(IC+QUOTE:LINELEN), LINELEN-IC-QUOTE+1, 9) .EQ. 0)THEN IF (IC+9.EQ.LINELEN+1 .OR. & FCB_NBLEN_ARRAY(LINE(IC+9),1).EQ.0 .OR. & LINE(IC+9).EQ.IACHAR(''`(''`).OR. & (QUOTE.EQ.1.AND.LINE(IC+9).EQ.Z''`22''`)) THEN ! double quote FAILURE = 0 ENCODING = ENC_BASE32K END IF END IF IF (FCB_CI_STRNCMPARR("X-Base8", & LINE(IC+QUOTE:LINELEN), LINELEN-IC-QUOTE+1, 7) .EQ. 0)THEN IF (IC+7.EQ.LINELEN+1 .OR. & FCB_NBLEN_ARRAY(LINE(IC+7),1).EQ.0 .OR. & LINE(IC+7).EQ.IACHAR(''`(''`).OR. & (QUOTE.EQ.1.AND.LINE(IC+7).EQ.Z''`22''`)) THEN ! double quote FAILURE = 0 ENCODING = ENC_BASE8 END IF END IF IF (FCB_CI_STRNCMPARR("X-Base10", & LINE(IC+QUOTE:LINELEN), LINELEN-IC-QUOTE+1, 8) .EQ. 0)THEN IF (IC+8.EQ.LINELEN+1 .OR. & FCB_NBLEN_ARRAY(LINE(IC+8),1).EQ.0 .OR. & LINE(IC+8).EQ.IACHAR(''`(''`).OR. & (QUOTE.EQ.1.AND.LINE(IC+8).EQ.Z''`22''`)) THEN ! double quote FAILURE = 0 ENCODING = ENC_BASE10 END IF END IF IF (FCB_CI_STRNCMPARR("X-Base16", & LINE(IC+QUOTE:LINELEN), LINELEN-IC-QUOTE+1, 8) .EQ. 0)THEN IF (IC+8.EQ.LINELEN+1 .OR. & FCB_NBLEN_ARRAY(LINE(IC+8),1).EQ.0 .OR. & LINE(IC+8).EQ.IACHAR(''`(''`).OR. & (QUOTE.EQ.1.AND.LINE(IC+8).EQ.Z''`22''`)) THEN !double quote FAILURE = 0 ENCODING = ENC_BASE16 END IF END IF IF (FCB_CI_STRNCMPARR("7bit", & LINE(IC+QUOTE:LINELEN), LINELEN-IC-QUOTE+1, 4) .EQ. 0 .OR. & FCB_CI_STRNCMPARR("8bit", & LINE(IC+QUOTE:LINELEN), LINELEN-IC-QUOTE+1, 4) .EQ. 0 ) THEN IF (IC+4.EQ.LINELEN+1 .OR. & FCB_NBLEN_ARRAY(LINE(IC+4),1).EQ.0 .OR. & LINE(IC+4).EQ.IACHAR(''`(''`).OR. & (QUOTE.EQ.1.AND.LINE(IC+4).EQ.Z''`22''`)) THEN !double quote FAILURE = 0 ENCODING = ENC_NONE END IF END IF IF (FCB_CI_STRNCMPARR("Binary", & LINE(IC+QUOTE:LINELEN), LINELEN-IC-QUOTE+1, 6) .EQ. 0) THEN IF (IC+6.EQ.LINELEN+1 .OR. & FCB_NBLEN_ARRAY(LINE(IC+6),1).EQ.0 .OR. & LINE(IC+6).EQ.IACHAR(''`(''`).OR. & (QUOTE.EQ.1.AND.LINE(IC+6).EQ.Z''`22''`)) THEN ! double quote FAILURE = 0 ENCODING = ENC_NONE END IF END IF IF (FAILURE.NE.0)GO TO 110 ! *** DEBUG *** PRINT *, "ENCODING: ", ENCODING CASE (2) ! Message digest IF (LINELEN.GE.IC+23) THEN DO I = IC,IC+23 DIGEST(I-IC+1:I-IC+1)=ACHAR(LINE(I)) END DO ELSE DO I = IC,LINELEN DIGEST(I-IC+1:I-IC+1)=ACHAR(LINE(I)) END DO DIGEST(LINELEN-IC+1:24)=''` ''` END IF ! *** DEBUG *** PRINT *, "DIGEST: ", DIGEST CASE (3) ! Binary size SIZE = FCB_ATOL_WCNT(LINE(IC:LINELEN),LINELEN-IC+1,COUNT) ! *** DEBUG *** PRINT *, "SIZE: ", SIZE CASE (4) ! Binary ID */ ID = FCB_ATOL_WCNT(LINE(IC:LINELEN),LINELEN-IC+1,COUNT) ! *** DEBUG *** PRINT *, "ID: ", ID CASE (5) ! Binary element type (signed/unsigned ?-bit integer) ! or (signed ?-bit real/complex IEEE) FAILURE = 3 QUOTE = 0 DO IF (IC.GT.LINELEN)EXIT FCB_NEXT_BINARY = FCB_SKIP_WHITESPACE(TAPIN,LAST_CHAR, & FCB_BYTES_IN_REC,BYTE_IN_FILE,REC_IN_FILE,BUFFER, & LINE,LINESIZE,LINELEN,IC,FRESH_LINE) IF (FCB_NEXT_BINARY.NE.0) RETURN IF (LINE(IC) .EQ. Z''`22''`) THEN ! double quote IF (QUOTE.NE.0) EXIT IC = IC+1 QUOTE = QUOTE+1 END IF IF (FAILURE .EQ. 3) THEN IF (FCB_CI_STRNCMPARR("signed", & LINE(IC:LINELEN),LINELEN-IC+1, 6) .EQ. 0) THEN IC = IC+6 VORZEICHEN = 1 FAILURE = FAILURE-1 END IF IF (FCB_CI_STRNCMPARR("unsigned", & LINE(IC:LINELEN),LINELEN-IC+1, 8) .EQ. 0) THEN IC = IC+8 VORZEICHEN = 0 FAILURE = FAILURE-1 END IF END IF IF (FAILURE .EQ. 2) THEN COUNT = 0 TEXT_BITS = FCB_ATOL_WCNT(LINE(IC:LINELEN),LINELEN-IC+1,COUNT) IF (FCB_CI_STRNCMPARR("-bit", & LINE(IC+COUNT:LINELEN),LINELEN-IC-COUNT+1,3).EQ.0)THEN IF (COUNT.NE.0.AND.TEXT_BITS.GT.0.AND.TEXT_BITS.LE.64)THEN IC = IC+COUNT+1 BITS = TEXT_BITS IF (LINE(IC) .EQ. IACHAR(''` ''`)) IC = IC+1 FAILURE = FAILURE-1 END IF END IF END IF IF (FAILURE .EQ. 1) THEN IF (FCB_CI_STRNCMPARR("integer", & LINE(IC:LINELEN),LINELEN-IC+1, 7 ) .EQ. 0) THEN FAILURE=FAILURE-1 REELL=0 ELSE IF (FCB_CI_STRNCMPARR("real", & LINE(IC:LINELEN), LINELEN-IC+1, 4 ) .EQ. 0 ) THEN IC = IC+4 IF (LINE(IC).EQ.IACHAR(''` ''`)) IC = IC+1 IF (FCB_CI_STRNCMPARR("ieee", & LINE(IC:LINELEN),LINELEN-IC+1,4).EQ.0) THEN FAILURE=FAILURE-1 REELL = 1 END IF ELSE IF (FCB_CI_STRNCMPARR("complex", & LINE(IC:LINELEN),LINELEN-IC+1,7).EQ.0) THEN IC = IC+7 IF (LINE(IC).EQ.IACHAR(''` ''`)) IC = IC+1 IF (FCB_CI_STRNCMPARR("ieee", & LINE(IC:LINELEN),LINELEN-IC+1,4).EQ.0) THEN FAILURE=FAILURE-1 REELL = 1 END IF END IF END IF END IF END IF IF (IC .LE. LINELEN) IC = IC+1 END DO IF (FAILURE .NE. 0)GO TO 110 ! *** DEBUG *** PRINT *, "VORZEICHEN, BITS, REELL",VORZEICHEN,BITS,REELL CASE (6) ! Byte order of elements (only endian-ness is supported) IF (0.EQ.FCB_CI_STRNCMPARR("big_endian", & LINE(IC:LINELEN),LINELEN-IC+1,10) ) THEN BYTEORDER="BIG_ENDIAN" ELSE IF (0.EQ.FCB_CI_STRNCMPARR("little_endian", & LINE(IC:LINELEN),LINELEN-IC+1,13)) THEN BYTEORDER="LITTLE_ENDIAN" ELSE GO TO 110 END IF END IF ! *** DEBUG *** PRINT *, "BYTEORDER: ", BYTEORDER CASE(7) ! Size of fastest dimension (Number of "fast" pixels) DIM1 = FCB_ATOL_WCNT(LINE(IC:LINELEN),LINELEN-IC+1,COUNT) ! *** DEBUG *** PRINT *,"DIM1: ",DIM1 CASE(8) ! Size of second fastest dimension (Number of "slow" pixels) DIM2 = FCB_ATOL_WCNT(LINE(IC:LINELEN),LINELEN-IC+1,COUNT) ! *** DEBUG *** PRINT *,"DIM2: ",DIM2 CASE(9) ! Size of third dimension DIM3 = FCB_ATOL_WCNT(LINE(IC:LINELEN),LINELEN-IC+1,COUNT) ! *** DEBUG *** PRINT *,"DIM3: ",DIM3 CASE(10) ! Size of padding after the data PADDING = FCB_ATOL_WCNT(LINE(IC:LINELEN),LINELEN-IC+1,COUNT) ! *** DEBUG *** PRINT *,"PADDING: ",PADDING CASE (11) ! Overall number of elements DIMOVER = FCB_ATOL_WCNT(LINE(IC:LINELEN),LINELEN-IC+1,COUNT) ! *** DEBUG *** PRINT *,"DIMOVER: ",DIMOVER END SELECT ENDDO 100 FCB_NEXT_BINARY = -1 RETURN 110 FCB_NEXT_BINARY = CBF_FORMAT RETURN END FUNCTION FCB_NEXT_BINARY' ./CBFlib-0.9.2.2/m4/Makefile.m40000644000076500007650000022005511603702103014076 0ustar yayayayam4_define(`cbf_version',`0.9.2')m4_dnl m4_define(`cbf_date',`12 Feb 2011')m4_dnl m4_ifelse(cbf_system,`',`m4_define(`cbf_system',`LINUX')') `###################################################################### # Makefile - command file for make to create CBFlib # # # # Version 'cbf_version cbf_date` # # # # Paul Ellis and # # Herbert J. Bernstein (yaya@bernstein-plus-sons.com) # # # # (C) Copyright 2006 - 2011 Herbert J. Bernstein # # # ###################################################################### ###################################################################### # # # YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL # # # # ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS # # OF THE LGPL # # # ###################################################################### ########################### GPL NOTICES ############################## # # # This program is free software; you can redistribute it and/or # # modify it under the terms of the GNU General Public License as # # published by the Free Software Foundation; either version 2 of # # (the License, or (at your option) any later version. # # # # This program is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # # GNU General Public License for more details. # # # # You should have received a copy of the GNU General Public License # # along with this program; if not, write to the Free Software # # Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA # # 02111-1307 USA # # # ###################################################################### ######################### LGPL NOTICES ############################### # # # This library is free software; you can redistribute it and/or # # modify it under the terms of the GNU Lesser General Public # # License as published by the Free Software Foundation; either # # version 2.1 of the License, or (at your option) any later version. # # # # This library is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # # Lesser General Public License for more details. # # # # You should have received a copy of the GNU Lesser General Public # # License along with this library; if not, write to the Free # # Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, # # MA 02110-1301 USA # # # ###################################################################### ###################################################################### # # # Stanford University Notices # # for the CBFlib software package that incorporates SLAC software # # on which copyright is disclaimed # # # # This software # # ------------- # # The term "this software", as used in these Notices, refers to # # those portions of the software package CBFlib that were created by # # employees of the Stanford Linear Accelerator Center, Stanford # # University. # # # # Stanford disclaimer of copyright # # -------------------------------- # # Stanford University, owner of the copyright, hereby disclaims its # # copyright and all other rights in this software. Hence, anyone # # may freely use it for any purpose without restriction. # # # # Acknowledgement of sponsorship # # ------------------------------ # # This software was produced by the Stanford Linear Accelerator # # Center, Stanford University, under Contract DE-AC03-76SFO0515 with # # the Department of Energy. # # # # Government disclaimer of liability # # ---------------------------------- # # Neither the United States nor the United States Department of # # Energy, nor any of their employees, makes any warranty, express or # # implied, or assumes any legal liability or responsibility for the # # accuracy, completeness, or usefulness of any data, apparatus, # # product, or process disclosed, or represents that its use would # # not infringe privately owned rights. # # # # Stanford disclaimer of liability # # -------------------------------- # # Stanford University makes no representations or warranties, # # express or implied, nor assumes any liability for the use of this # # software. # # # # Maintenance of notices # # ---------------------- # # In the interest of clarity regarding the origin and status of this # # software, this and all the preceding Stanford University notices # # are to remain affixed to any copy or derivative of this software # # made or distributed by the recipient and are to be affixed to any # # copy of software made or distributed by the recipient that # # contains a copy or derivative of this software. # # # # Based on SLAC Software Notices, Set 4 # # OTT.002a, 2004 FEB 03 # ###################################################################### ###################################################################### # NOTICE # # Creative endeavors depend on the lively exchange of ideas. There # # are laws and customs which establish rights and responsibilities # # for authors and the users of what authors create. This notice # # is not intended to prevent you from using the software and # # documents in this package, but to ensure that there are no # # misunderstandings about terms and conditions of such use. # # # # Please read the following notice carefully. If you do not # # understand any portion of this notice, please seek appropriate # # professional legal advice before making use of the software and # # documents included in this software package. In addition to # # whatever other steps you may be obliged to take to respect the # # intellectual property rights of the various parties involved, if # # you do make use of the software and documents in this package, # # please give credit where credit is due by citing this package, # # its authors and the URL or other source from which you obtained # # it, or equivalent primary references in the literature with the # # same authors. # # # # Some of the software and documents included within this software # # package are the intellectual property of various parties, and # # placement in this package does not in any way imply that any # # such rights have in any way been waived or diminished. # # # # With respect to any software or documents for which a copyright # # exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. # # # # Even though the authors of the various documents and software # # found here have made a good faith effort to ensure that the # # documents are correct and that the software performs according # # to its documentation, and we would greatly appreciate hearing of # # any problems you may encounter, the programs and documents any # # files created by the programs are provided **AS IS** without any * # warranty as to correctness, merchantability or fitness for any # # particular or general use. # # # # THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF # # PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE # # PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS # # OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE # # PROGRAMS OR DOCUMENTS. # ###################################################################### ###################################################################### # # # The IUCr Policy # # for the Protection and the Promotion of the STAR File and # # CIF Standards for Exchanging and Archiving Electronic Data # # # # Overview # # # # The Crystallographic Information File (CIF)[1] is a standard for # # information interchange promulgated by the International Union of # # Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the # # recommended method for submitting publications to Acta # # Crystallographica Section C and reports of crystal structure # # determinations to other sections of Acta Crystallographica # # and many other journals. The syntax of a CIF is a subset of the # # more general STAR File[2] format. The CIF and STAR File approaches # # are used increasingly in the structural sciences for data exchange # # and archiving, and are having a significant influence on these # # activities in other fields. # # # # Statement of intent # # # # The IUCr''`s interest in the STAR File is as a general data # # interchange standard for science, and its interest in the CIF, # # a conformant derivative of the STAR File, is as a concise data # # exchange and archival standard for crystallography and structural # # science. # # # # Protection of the standards # # # # To protect the STAR File and the CIF as standards for # # interchanging and archiving electronic data, the IUCr, on behalf # # of the scientific community, # # # # # holds the copyrights on the standards themselves, * # # # # owns the associated trademarks and service marks, and * # # # # holds a patent on the STAR File. * # # # These intellectual property rights relate solely to the # # interchange formats, not to the data contained therein, nor to # # the software used in the generation, access or manipulation of # # the data. # # # # Promotion of the standards # # # # The sole requirement that the IUCr, in its protective role, # # imposes on software purporting to process STAR File or CIF data # # is that the following conditions be met prior to sale or # # distribution. # # # # # Software claiming to read files written to either the STAR * # File or the CIF standard must be able to extract the pertinent # # data from a file conformant to the STAR File syntax, or the CIF # # syntax, respectively. # # # # # Software claiming to write files in either the STAR File, or * # the CIF, standard must produce files that are conformant to the # # STAR File syntax, or the CIF syntax, respectively. # # # # # Software claiming to read definitions from a specific data * # dictionary approved by the IUCr must be able to extract any # # pertinent definition which is conformant to the dictionary # # definition language (DDL)[3] associated with that dictionary. # # # # The IUCr, through its Committee on CIF Standards, will assist # # any developer to verify that software meets these conformance # # conditions. # # # # Glossary of terms # # # # [1] CIF: is a data file conformant to the file syntax defined # # at http://www.iucr.org/iucr-top/cif/spec/index.html # # # # [2] STAR File: is a data file conformant to the file syntax # # defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html # # # # [3] DDL: is a language used in a data dictionary to define data # # items in terms of "attributes". Dictionaries currently approved # # by the IUCr, and the DDL versions used to construct these # # dictionaries, are listed at # # http://www.iucr.org/iucr-top/cif/spec/ddl/index.html # # # # Last modified: 30 September 2000 # # # # IUCr Policy Copyright (C) 2000 International Union of # # Crystallography # ###################################################################### # Version string VERSION = 'cbf_version` # # Comment out the next line if scratch test files sould be retain # CLEANTESTS = yes 'm4_ifelse(cbf_use_pycifrw,`yes',` # # Definitions to get versions of PyCifRW and PLY # PYCIFRW = PyCifRW-3.3_6Dec09 PLY = ply-3.2 PYCIFRWFLAG = -DCBF_USE_PYCIFRW ')m4_dnl ` # # Definition to get a version of tifflib to support tiff2cbf # TIFF = tiff-3.9.4-rev-6Feb11 TIFFPREFIX = $(PWD) # # Definitions to get a stable version of regex # REGEX = regex-20090805 REGEXDIR = /usr/lib REGEXDEP = # Program to use to retrieve a URL DOWNLOAD = wget # Flag to control symlinks versus copying SLFLAGS = --use_ln # # Program to use to pack shars # SHAR = /usr/bin/shar #SHAR = /usr/local/bin/gshar # # Program to use to create archives # AR = /usr/bin/ar # # Program to use to add an index to an archive # RANLIB = /usr/bin/ranlib # # Program to use to decompress a data file # DECOMPRESS = /usr/bin/bunzip2 # # Program to use to compress a data file # COMPRESS = /usr/bin/bzip2 # # Program to use to generate a signature # SIGNATURE = /usr/bin/openssl dgst -md5 # # Extension for compressed data file (with period) # CEXT = .bz2 # # Extension for signatures of files # SEXT = .md5 # call to time a command #TIME = #TIME = time # # Program to display differences between files # DIFF = diff -u -b # # Program to generate wrapper classes for Python # PYSWIG = swig -python # # Program to generate wrapper classes for Java # JSWIG = swig -java # # Program to generate LaTex and HTML program documentation # NUWEB = nuweb # # Compiler for Java # JAVAC = javac # # Java archiver for compiled classes # JAR = jar # # Java SDK root directory # ifeq ($(JDKDIR),) JDKDIR = /usr/lib/java endif ifneq ($(CBF_DONT_USE_LONG_LONG),) NOLLFLAG = -DCBF_DONT_USE_LONG_LONG else NOLLFLAG = endif # # PYCBF definitions # PYCBFEXT = so PYCBFBOPT = SETUP_PY = setup.py # # Set the compiler and flags # 'm4_ifelse(cbf_system,`OSX',` ######################################################### # # Appropriate compiler definitions for MAC OS X # Also change defintion of DOWNLOAD # ######################################################### CC = gcc C++ = g++ CFLAGS = -g -O2 -Wall -ansi -pedantic F90C = gfortran F90FLAGS = -g -fno-range-check F90LDFLAGS = -bind_at_load EXTRALIBS = -lm M4FLAGS = -Dfcb_bytes_in_rec=131072 TIME = time DOWNLOAD = /sw/bin/wget', cbf_system,`OSX_gcc42',` ######################################################### # # Appropriate compiler definitions for MAC OS X # with gcc 4.2 # Also change defintion of DOWNLOAD # ######################################################### CC = gcc C++ = g++ CFLAGS = -g -O2 -Wall -ansi -pedantic F90C = gfortran F90FLAGS = -g -fno-range-check F90LDFLAGS = -bind_at_load SOCFLAGS = -fPIC SOLDFLAGS = -shared -Wl,-rpath,$(INSTALLDIR)/lib JAVAINCLUDES = -I$(JDKDIR)/include -I$(JDKDIR)/include/linux LDPREFIX = LD_LIBRARY_PATH=$(SOLIB) EXTRALIBS = -lm M4FLAGS = -Dfcb_bytes_in_rec=131072 TIME = time DOWNLOAD = /sw/bin/wget', cbf_system,`OSX_gcc42_DMALLOC',` ######################################################### # # Appropriate compiler definitions for MAC OS X # with gcc 4.2 and DMALLOC # Also change defintion of DOWNLOAD # ######################################################### CC = gcc C++ = g++ CFLAGS = -g -O2 -Wall -ansi -pedantic -DDMALLOC -DDMALLOC_FUNC_CHECK -I$(HOME)/include F90C = gfortran F90FLAGS = -g -fno-range-check F90LDFLAGS = -bind_at_load SOCFLAGS = -fPIC SOLDFLAGS = -shared -Wl,-rpath,$(INSTALLDIR)/lib JAVAINCLUDES = -I$(JDKDIR)/include -I$(JDKDIR)/include/linux LDPREFIX = LD_LIBRARY_PATH=$(SOLIB) EXTRALIBS = -lm -L$(HOME)/lib -ldmalloc M4FLAGS = -Dfcb_bytes_in_rec=131072 TIME = time DOWNLOAD = /sw/bin/wget', cbf_system,`LINUX_64',` ######################################################### # # Appropriate compiler definitions for Linux x86_64 # with gcc version 4.2 # ######################################################### CC = gcc -m64 C++ = g++ -m64 CFLAGS = -g -O2 -Wall -D_USE_XOPEN_EXTENDED -fno-strict-aliasing F90C = gfortran -m64 F90FLAGS = -g -fno-range-check F90LDFLAGS = SOCFLAGS = -fPIC SOLDFLAGS = -shared -Wl,-rpath,$(INSTALLDIR)/lib JAVAINCLUDES = -I$(JDKDIR)/include -I$(JDKDIR)/include/linux LDPREFIX = LD_LIBRARY_PATH=$(SOLIB) EXTRALIBS = -lm M4FLAGS = -Dfcb_bytes_in_rec=131072 TIME = time DOWNLOAD = /sw/bin/wget', cbf_system,`LINUX_gcc42',` ######################################################### # # Appropriate compiler definitions for Linux # with gcc version 4.2 # ######################################################### CC = gcc C++ = g++ CFLAGS = -g -O2 -Wall -D_USE_XOPEN_EXTENDED -fno-strict-aliasing F90C = gfortran F90FLAGS = -g -fno-range-check F90LDFLAGS = SOCFLAGS = -fPIC SOLDFLAGS = -shared -Wl,-rpath,$(INSTALLDIR)/lib JAVAINCLUDES = -I$(JDKDIR)/include -I$(JDKDIR)/include/linux LDPREFIX = LD_LIBRARY_PATH=$(SOLIB) EXTRALIBS = -lm M4FLAGS = -Dfcb_bytes_in_rec=131072 TIME = time', cbf_system,`LINUX',` ######################################################### # # Appropriate compiler definitions for Linux # ######################################################### CC = gcc C++ = g++ CFLAGS = -g -O2 -Wall -D_USE_XOPEN_EXTENDED -fno-strict-aliasing F90C = gfortran F90FLAGS = -g F90LDFLAGS = SOCFLAGS = -fPIC SOLDFLAGS = -shared -Wl,-rpath,$(INSTALLDIR)/lib JAVAINCLUDES = -I$(JDKDIR)/include -I$(JDKDIR)/include/linux LDPREFIX = LD_LIBRARY_PATH=$(SOLIB) EXTRALIBS = -lm M4FLAGS = -Dfcb_bytes_in_rec=131072 TIME = time', cbf_system,`LINUX_gcc42_DMALLOC',` ######################################################### # # Appropriate compiler definitions for Linux # with gcc version 4.2 and DMALLOC # ######################################################### CC = gcc C++ = g++ CFLAGS = -g -O2 -Wall -D_USE_XOPEN_EXTENDED -fno-strict-aliasing -DDMALLOC -DDMALLOC_FUNC_CHECK -I$(HOME)/include F90C = gfortran F90FLAGS = -g -fno-range-check F90LDFLAGS = SOCFLAGS = -fPIC SOLDFLAGS = -shared -Wl,-rpath,$(INSTALLDIR)/lib JAVAINCLUDES = -I$(JDKDIR)/include -I$(JDKDIR)/include/linux LDPREFIX = LD_LIBRARY_PATH=$(SOLIB) EXTRALIBS = -lm -L$(HOME)/lib -ldmalloc M4FLAGS = -Dfcb_bytes_in_rec=131072 TIME = time', cbf_system,`LINUX_DMALLOC',` ######################################################### # # Appropriate compiler definitions for Linux and DMALLOC # ######################################################### CC = gcc C++ = g++ CFLAGS = -g -O2 -Wall -D_USE_XOPEN_EXTENDED -fno-strict-aliasing -DDMALLOC -DDMALLOC_FUNC_CHECK -I$(HOME)/include F90C = gfortran F90FLAGS = -g F90LDFLAGS = SOCFLAGS = -fPIC SOLDFLAGS = -shared -Wl,-rpath,$(INSTALLDIR)/lib JAVAINCLUDES = -I$(JDKDIR)/include -I$(JDKDIR)/include/linux LDPREFIX = LD_LIBRARY_PATH=$(SOLIB) EXTRALIBS = -lm -L$(HOME)/lib -ldmalloc M4FLAGS = -Dfcb_bytes_in_rec=131072 TIME = time', cbf_system,`AIX',` ######################################################### # # Appropriate compiler definitions for AIX # ######################################################### CC = xlc C++ = xlC CFLAGS = -g -O2 -Wall F90C = xlf90 F90FLAGS = -g -qsuffix=f=f90 F90LDFLAGS = M4FLAGS = -Dfcb_bytes_in_rec=131072 EXTRALIBS = -lm TIME = time', cbf_system,`MINGW',` ######################################################### # # Appropriate compiler definitions for Mingw # Also change from symlinks to copies and # use default paths for utilities # ######################################################### CC = gcc C++ = g++ CFLAGS = -g -O2 -Wall -static -I/usr/include -fno-strict-aliasing F90C = g95 F90FLAGS = -g F90LDFLAGS = M4FLAGS = -Dfcb_bytes_in_rec=4096 SOCFLAGS = -D_JNI_IMPLEMENTATION_ SOLDFLAGS = -shared -Wl,--kill-at JAVAINCLUDES = -I$(JDKDIR)/include -I$(JDKDIR)/include/win32 EXTRALIBS = -L$(REGEXDIR) -lregex -lm REGEXDEP = $(REGEXDIR)/libregex.a TIME = PYCBFEXT = pyd PYCBFBOPT = --compiler=mingw32 SETUP_PY = setup_MINGW.py JDKDIR = /java JSWIG = /swig/swig -java PYSWIG = /swig/swig -python SLFLAGS = --use_cp SHAR = shar AR = ar RANLIB = ranlib DECOMPRESS = bunzip2', cbf_system,`IRIX_gcc',` ######################################################### # # Appropriate compiler definitions for IRIX w. gcc # No f90 # use default paths for utilities # ######################################################### CC = gcc C++ = g++ CFLAGS = -g -O2 -Wall F90C = F90FLAGS = M4FLAGS = -Dfcb_bytes_in_rec=4096 EXTRALIBS = -lm TIME = SHAR = shar AR = ar RANLIB = DECOMPRESS = bunzip2', ` ######################################################### # # Appropriate compiler definitions for default (Linux) # ######################################################### CC = gcc C++ = g++ CFLAGS = -g -O2 -Wall -D_USE_XOPEN_EXTENDED -fno-strict-aliasing F90C = gfortran F90FLAGS = -g -fno-range-check F90LDFLAGS = SOCFLAGS = -fPIC SOLDFLAGS = -shared -Wl,-rpath,$(INSTALLDIR)/lib JAVAINCLUDES = -I$(JDKDIR)/include -I$(JDKDIR)/include/linux LDPREFIX = LD_LIBRARY_PATH=$(SOLIB) EXTRALIBS = -lm M4FLAGS = -Dfcb_bytes_in_rec=131072 TIME = time')` ifneq ($(NOFORTRAN),) F90C = endif # # Directories # ROOT = . LIB = $(ROOT)/lib SOLIB = $(ROOT)/solib JCBF = $(ROOT)/jcbf JAVADIR = $(ROOT)/java BIN = $(ROOT)/bin SRC = $(ROOT)/src INCLUDE = $(ROOT)/include M4 = $(ROOT)/m4 PYCBF = $(ROOT)/pycbf EXAMPLES = $(ROOT)/examples DECTRIS_EXAMPLES = $(EXAMPLES)/dectris_cbf_template_test DOC = $(ROOT)/doc GRAPHICS = $(ROOT)/html_graphics DATADIRI = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Input DATADIRO = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Output DATADIRS = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only INSTALLDIR = $(HOME) # # URLs from which to retrieve the data directories # DATAURLBASE = http://downloads.sf.net/cbflib/ DATAURLI = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Input.tar.gz DATAURLO = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Output.tar.gz DATAURLS = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz # # URLs from which to retrieve needed external package snapshots # 'm4_ifelse(cbf_use_pycifrw,`yes',` PYCIFRWURL = http://downloads.sf.net/cbflib/$(PYCIFRW).tar.gz PLYURL = http://www.dabeaz.com/ply/$(PLY).tar.gz ')m4_dnl `REGEXURL = http://downloads.sf.net/cbflib/$(REGEX).tar.gz TIFFURL = http://downloads.sf.net/cbflib/$(TIFF).tar.gz # # Include directories # INCLUDES = -I$(INCLUDE) -I$(SRC) ###################################################################### # You should not need to make modifications below this line # ###################################################################### # # Suffixes of files to be used or built # .SUFFIXES: .c .o .f90 .m4 .m4.f90: m4 -P $(M4FLAGS) $< > $@ ifneq ($(F90C),) .f90.o: $(F90C) $(F90FLAGS) -c $< -o $@ endif # # Common dependencies # COMMONDEP = Makefile # # Source files # SOURCE = $(SRC)/cbf.c \ $(SRC)/cbf_alloc.c \ $(SRC)/cbf_ascii.c \ $(SRC)/cbf_binary.c \ $(SRC)/cbf_byte_offset.c \ $(SRC)/cbf_canonical.c \ $(SRC)/cbf_codes.c \ $(SRC)/cbf_compress.c \ $(SRC)/cbf_context.c \ $(SRC)/cbf_copy.c \ $(SRC)/cbf_file.c \ $(SRC)/cbf_getopt.c \ $(SRC)/cbf_lex.c \ $(SRC)/cbf_packed.c \ $(SRC)/cbf_predictor.c \ $(SRC)/cbf_read_binary.c \ $(SRC)/cbf_read_mime.c \ $(SRC)/cbf_simple.c \ $(SRC)/cbf_string.c \ $(SRC)/cbf_stx.c \ $(SRC)/cbf_tree.c \ $(SRC)/cbf_uncompressed.c \ $(SRC)/cbf_write.c \ $(SRC)/cbf_write_binary.c \ $(SRC)/cbf_ws.c \ $(SRC)/md5c.c 'm4_ifelse(cbf_use_pycifrw,`yes',` PYSOURCE = $(SRC)/drel_lex.py \ $(SRC)/drel_yacc.py \ $(SRC)/drelc.py \ $(SRC)/drel_prep.py ')m4_dnl ` F90SOURCE = $(SRC)/fcb_atol_wcnt.f90 \ $(SRC)/fcb_ci_strncmparr.f90 \ $(SRC)/fcb_exit_binary.f90 \ $(SRC)/fcb_nblen_array.f90 \ $(SRC)/fcb_next_binary.f90 \ $(SRC)/fcb_open_cifin.f90 \ $(SRC)/fcb_packed.f90 \ $(SRC)/fcb_read_bits.f90 \ $(SRC)/fcb_read_byte.f90 \ $(SRC)/fcb_read_image.f90 \ $(SRC)/fcb_read_line.f90 \ $(SRC)/fcb_read_xds_i2.f90 \ $(SRC)/fcb_skip_whitespace.f90 \ $(EXAMPLES)/test_fcb_read_image.f90 \ $(EXAMPLES)/test_xds_binary.f90 # # Header files # HEADERS = $(INCLUDE)/cbf.h \ $(INCLUDE)/cbf_alloc.h \ $(INCLUDE)/cbf_ascii.h \ $(INCLUDE)/cbf_binary.h \ $(INCLUDE)/cbf_byte_offset.h \ $(INCLUDE)/cbf_canonical.h \ $(INCLUDE)/cbf_codes.h \ $(INCLUDE)/cbf_compress.h \ $(INCLUDE)/cbf_context.h \ $(INCLUDE)/cbf_copy.h \ $(INCLUDE)/cbf_file.h \ $(INCLUDE)/cbf_getopt.h \ $(INCLUDE)/cbf_lex.h \ $(INCLUDE)/cbf_packed.h \ $(INCLUDE)/cbf_predictor.h \ $(INCLUDE)/cbf_read_binary.h \ $(INCLUDE)/cbf_read_mime.h \ $(INCLUDE)/cbf_simple.h \ $(INCLUDE)/cbf_string.h \ $(INCLUDE)/cbf_stx.h \ $(INCLUDE)/cbf_tree.h \ $(INCLUDE)/cbf_uncompressed.h \ $(INCLUDE)/cbf_write.h \ $(INCLUDE)/cbf_write_binary.h \ $(INCLUDE)/cbf_ws.h \ $(INCLUDE)/global.h \ $(INCLUDE)/cbff.h \ $(INCLUDE)/md5.h # # m4 macro files # M4FILES = $(M4)/fcblib_defines.m4 \ $(M4)/fcb_exit_binary.m4 \ $(M4)/fcb_next_binary.m4 \ $(M4)/fcb_open_cifin.m4 \ $(M4)/fcb_packed.m4 \ $(M4)/fcb_read_bits.m4 \ $(M4)/fcb_read_image.m4 \ $(M4)/fcb_read_xds_i2.m4 \ $(M4)/test_fcb_read_image.m4 \ $(M4)/test_xds_binary.m4 # # Documentation files # DOCUMENTS = $(DOC)/CBFlib.html \ $(DOC)/CBFlib.txt \ $(DOC)/CBFlib_NOTICES.html \ $(DOC)/CBFlib_NOTICES.txt \ $(DOC)/ChangeLog \ $(DOC)/ChangeLog.html \ $(DOC)/MANIFEST \ $(DOC)/gpl.txt $(DOC)/lgpl.txt # # HTML Graphics files # JPEGS = $(GRAPHICS)/CBFbackground.jpg \ $(GRAPHICS)/CBFbig.jpg \ $(GRAPHICS)/CBFbutton.jpg \ $(GRAPHICS)/cbflibbackground.jpg \ $(GRAPHICS)/cbflibbig.jpg \ $(GRAPHICS)/cbflibbutton.jpg \ $(GRAPHICS)/cifhome.jpg \ $(GRAPHICS)/iucrhome.jpg \ $(GRAPHICS)/noticeButton.jpg # # Default: instructions # default: @echo ''` ''` @echo ''`***************************************************************''` @echo ''` ''` @echo ''` PLEASE READ README and doc/CBFlib_NOTICES.txt''` @echo ''` ''` @echo ''` Before making the CBF library and example programs, check''` @echo ''` that the C compiler name and flags are correct:''` @echo ''` ''` @echo ''` The current values are:''` @echo ''` ''` @echo ''` $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG)''` @echo ''` ''` @echo ''` Before installing the CBF library and example programs, check''` @echo ''` that the install directory is correct:''` @echo ''` ''` @echo ''` The current value :''` @echo ''` ''` @echo ''` $(INSTALLDIR) ''` @echo ''` ''` @echo ''` To compile the CBF library and example programs type:''` @echo ''` ''` @echo ''` make clean''` @echo ''` make all''` @echo ''` ''` @echo ''` To compile the CBF library as a shared object library, type:''` @echo ''` ''` @echo ''` make shared''` @echo ''` ''` @echo ''` To compile the Java wrapper classes for CBF library, type:''` @echo ''` ''` @echo ''` make javawrapper''` @echo ''` ''` @echo ''` To run a set of tests type:''` @echo ''` ''` @echo ''` make tests''` @echo ''` ''` @echo ''` To run some java tests type:''` @echo ''` ''` @echo ''` make javatests''` @echo ''` ''` @echo ''` The tests assume that several data files are in the directories''` @echo ''` $(DATADIRI) and $(DATADIRO)''` @echo ''` ''` @echo ''` Alternatively tests can be run comparing MD5 signatures only by''` @echo ''` ''` @echo ''` make tests_sigs_only''` @echo ''` ''` @echo ''` These signature only tests save space and download time by''` @echo ''` assuming that input data files and the output signatures''` @echo ''` are in the directories''` @echo ''` $(DATADIRI) and $(DATADIRS)''` @echo ''` ''` @echo ''` These directory can be obtained from''` @echo ''` ''` @echo ''` $(DATAURLI) ''` @echo ''` $(DATAURLO) ''` @echo ''` $(DATAURLS) ''` @echo ''` ''` @echo ''` To clean up the directories type:''` @echo ''` ''` @echo ''` make clean''` @echo ''` ''` @echo ''` To install the library and binaries type:''` @echo ''` ''` @echo ''` make install''` @echo ''` ''` @echo ''`***************************************************************''` @echo ''` ''` # # Compile the library and examples # all:: $(BIN) $(SOURCE) $(F90SOURCE) $(HEADERS) \ 'm4_ifelse(cbf_use_pycifrw,`yes',` $(PYCIFRW) $(PLY) \ ')m4_dnl ` symlinksdone $(REGEXDEP) \ $(LIB)/libcbf.a \ $(LIB)/libfcb.a \ $(LIB)/libimg.a \ $(BIN)/adscimg2cbf \ $(BIN)/cbf2adscimg \ $(BIN)/convert_image \ $(BIN)/convert_minicbf \ $(BIN)/sequence_match \ $(BIN)/arvai_test \ $(BIN)/makecbf \ $(BIN)/img2cif \ $(BIN)/adscimg2cbf \ $(BIN)/cif2cbf \ $(BIN)/testcell \ $(BIN)/cif2c \ $(BIN)/testreals \ $(BIN)/testflat \ $(BIN)/testflatpacked ifneq ($(F90C),) all:: $(BIN)/test_xds_binary \ $(BIN)/test_fcb_read_image endif shared: $(SOLIB)/libcbf.so $(SOLIB)/libfcb.so $(SOLIB)/libimg.so javawrapper: shared $(JCBF) $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf_wrap.so ifneq ($(CBFLIB_USE_PYCIFRW),) PYCIFRWDEF = -Dcbf_use_pycifrw=yes else PYCIFRWDEF = endif Makefiles: Makefile \ Makefile_LINUX \ Makefile_LINUX_64 \ Makefile_LINUX_gcc42 \ Makefile_LINUX_DMALLOC \ Makefile_LINUX_gcc42_DMALLOC \ Makefile_OSX \ Makefile_OSX_gcc42 \ Makefile_OSX_gcc42_DMALLOC \ Makefile_AIX \ Makefile_MINGW \ Makefile_IRIX_gcc Makefile_LINUX: $(M4)/Makefile.m4 -cp Makefile_LINUX Makefile_LINUX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX $(M4)/Makefile.m4 > Makefile_LINUX Makefile_LINUX_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_LINUX Makefile_LINUX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_DMALLOC $(M4)/Makefile.m4 > Makefile_LINUX_DMALLOC Makefile_LINUX_64: $(M4)/Makefile.m4 -cp Makefile_LINUX_64 Makefile_LINUX_64_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_64 $(M4)/Makefile.m4 > Makefile_LINUX_64 Makefile_LINUX_gcc42: $(M4)/Makefile.m4 -cp Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_gcc42 $(M4)/Makefile.m4 > Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_gcc42_DMALLOC $(M4)/Makefile.m4 > Makefile_LINUX_gcc42_DMALLOC Makefile_OSX: $(M4)/Makefile.m4 -cp Makefile_OSX Makefile_OSX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX $(M4)/Makefile.m4 > Makefile_OSX Makefile_OSX_gcc42: $(M4)/Makefile.m4 -cp Makefile_OSX_gcc42 Makefile_OSX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX_gcc42 $(M4)/Makefile.m4 > Makefile_OSX_gcc42 Makefile_OSX_gcc42_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_OSX_gcc42 Makefile_OSX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX_gcc42_DMALLOC $(M4)/Makefile.m4 > Makefile_OSX_gcc42_DMALLOC Makefile_AIX: $(M4)/Makefile.m4 -cp Makefile_AIX Makefile_AIX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=AIX $(M4)/Makefile.m4 > Makefile_AIX Makefile_MINGW: $(M4)/Makefile.m4 -cp Makefile_MINGW Makefile_MINGW_old m4 -P $(PYCIFRWDEF) -Dcbf_system=MINGW $(M4)/Makefile.m4 > Makefile_MINGW Makefile_IRIX_gcc: $(M4)/Makefile.m4 -cp Makefile_IRIX_gcc Makefile_IRIX_gcc_old m4 -P $(PYCIFREDEF) -Dcbf_system=IRIX_gcc $(M4)/Makefile.m4 > Makefile_IRIX_gcc Makefile: $(M4)/Makefile.m4 -cp Makefile Makefile_old m4 -P $(PYCIFRWDEF) -Dcbf_system=default $(M4)/Makefile.m4 > Makefile symlinksdone: chmod a+x .symlinks chmod a+x .undosymlinks chmod a+x doc/.symlinks chmod a+x doc/.undosymlinks chmod a+x libtool/.symlinks chmod a+x libtool/.undosymlinks ./.symlinks $(SLFLAGS) touch symlinksdone install: all $(INSTALLDIR) $(INSTALLDIR)/lib $(INSTALLDIR)/bin \ $(INSTALLDIR)/include $(INSTALLDIR)/include/cbflib \ $(PYSOURCE) -chmod -R 755 $(INSTALLDIR)/include/cbflib -chmod 755 $(INSTALLDIR)/lib/libcbf.a -cp $(INSTALLDIR)/lib/libcbf.a $(INSTALLDIR)/lib/libcbf_old.a cp $(LIB)/libcbf.a $(INSTALLDIR)/lib/libcbf.a -cp $(INSTALLDIR)/lib/libimg.a $(INSTALLDIR)/lib/libimg_old.a cp $(LIB)/libimg.a $(INSTALLDIR)/lib/libimg.a -cp $(INSTALLDIR)/bin/adscimg2cbf $(INSTALLDIR)/bin/adscimg2cbf_old cp $(BIN)/adscimg2cbf $(INSTALLDIR)/bin/adscimg2cbf -cp $(INSTALLDIR)/bin/cbf2adscimg $(INSTALLDIR)/bin/cbf2adscimg_old cp $(BIN)/cbf2adscimg $(INSTALLDIR)/bin/cbf2adscimg -cp $(INSTALLDIR)/bin/convert_image $(INSTALLDIR)/bin/convert_image_old cp $(BIN)/convert_image $(INSTALLDIR)/bin/convert_image -cp $(INSTALLDIR)/bin/convert_minicbf $(INSTALLDIR)/bin/convert_minicbf_old cp $(BIN)/convert_minicbf $(INSTALLDIR)/bin/convert_minicbf -cp $(INSTALLDIR)/bin/makecbf $(INSTALLDIR)/bin/makecbf_old cp $(BIN)/makecbf $(INSTALLDIR)/bin/makecbf -cp $(INSTALLDIR)/bin/img2cif $(INSTALLDIR)/bin/img2cif_old cp $(BIN)/img2cif $(INSTALLDIR)/bin/img2cif -cp $(INSTALLDIR)/bin/cif2cbf $(INSTALLDIR)/bin/cif2cbf_old cp $(BIN)/cif2cbf $(INSTALLDIR)/bin/cif2cbf -cp $(INSTALLDIR)/bin/sequence_match $(INSTALLDIR)/bin/sequence_match_old cp $(BIN)/sequence_match $(INSTALLDIR)/bin/sequence_match -cp $(INSTALLDIR)/bin/arvai_test $(INSTALLDIR)/bin/arvai_test_old cp $(BIN)/arvai_test $(INSTALLDIR)/bin/arvai_test -cp $(INSTALLDIR)/bin/cif2c $(INSTALLDIR)/bin/cif2c_old cp $(BIN)/cif2c $(INSTALLDIR)/bin/cif2c -cp $(INSTALLDIR)/bin/testreals $(INSTALLDIR)/bin/testreals_old cp $(BIN)/testreals $(INSTALLDIR)/bin/testreals -cp $(INSTALLDIR)/bin/testflat $(INSTALLDIR)/bin/testflat_old cp $(BIN)/testflat $(INSTALLDIR)/bin/testflat -cp $(INSTALLDIR)/bin/testflatpacked $(INSTALLDIR)/bin/testflatpacked_old cp $(BIN)/testflatpacked $(INSTALLDIR)/bin/testflatpacked 'm4_ifelse(cbf_use_pycifrw,`yes',` cp $(SRC)/drel_lex.py $(INSTALLDIR)/bin/drel_lex.py cp $(SRC)/drel_yacc.py $(INSTALLDIR)/bin/drel_yacc.py cp $(SRC)/drelc.py $(INSTALLDIR)/bin/drelc.py cp $(SRC)/drel_prep.py $(INSTALLDIR)/bin/drel_prep.py ')m4_dnl ` chmod -R 755 $(INSTALLDIR)/include/cbflib -rm -rf $(INSTALLDIR)/include/cbflib_old -cp -r $(INSTALLDIR)/include/cbflib $(INSTALLDIR)/include/cbflib_old -rm -rf $(INSTALLDIR)/include/cbflib cp -r $(INCLUDE) $(INSTALLDIR)/include/cbflib chmod 644 $(INSTALLDIR)/lib/libcbf.a chmod 755 $(INSTALLDIR)/bin/convert_image chmod 755 $(INSTALLDIR)/bin/convert_minicbf chmod 755 $(INSTALLDIR)/bin/makecbf chmod 755 $(INSTALLDIR)/bin/img2cif chmod 755 $(INSTALLDIR)/bin/cif2cbf chmod 755 $(INSTALLDIR)/bin/sequence_match chmod 755 $(INSTALLDIR)/bin/arvai_test chmod 755 $(INSTALLDIR)/bin/cif2c chmod 755 $(INSTALLDIR)/bin/testreals chmod 755 $(INSTALLDIR)/bin/testflat chmod 755 $(INSTALLDIR)/bin/testflatpacked chmod 644 $(INSTALLDIR)/include/cbflib/*.h 'm4_ifelse(cbf_use_pycifrw,`yes',` # # PyCifRW # $(PYCIFRW): $(DOWNLOAD) $(PYCIFRWURL) tar -xvf $(PYCIFRW).tar.gz -rm $(PYCIFRW).tar.gz (cd $(PYCIFRW); python setup.py install ) # # PLY # $(PLY): $(DOWNLOAD) $(PLYURL) tar -xvf $(PLY).tar.gz -rm $(PLY).tar.gz (cd $(PLY); python setup.py install ) ')m4_dnl ` # # REGEX # ifneq ($(REGEXDEP),) $(REGEXDEP): $(REGEX) (cd $(REGEX); ./configure; make install) endif $(REGEX): $(DOWNLOAD) $(REGEXURL) tar -xvf $(REGEX).tar.gz -rm $(REGEX).tar.gz # # TIFF # $(TIFF): $(DOWNLOAD) $(TIFFURL) tar -xvf $(TIFF).tar.gz -rm $(TIFF).tar.gz (cd $(TIFF); ./configure --prefix=$(TIFFPREFIX); make install) # # Directories # $(INSTALLDIR): mkdir -p $(INSTALLDIR) $(INSTALLDIR)/lib: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/lib $(INSTALLDIR)/bin: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/bin $(INSTALLDIR)/include: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/include $(INSTALLDIR)/include/cbflib: $(INSTALLDIR)/include mkdir -p $(INSTALLDIR)/include/cbflib $(LIB): mkdir $@ $(BIN): mkdir $@ $(SOLIB): mkdir $@ $(JCBF): mkdir $@ # # Parser # $(SRC)/cbf_stx.c: $(SRC)/cbf.stx.y bison $(SRC)/cbf.stx.y -o $(SRC)/cbf.stx.tab.c -d mv $(SRC)/cbf.stx.tab.c $(SRC)/cbf_stx.c mv $(SRC)/cbf.stx.tab.h $(INCLUDE)/cbf_stx.h # # CBF library # $(LIB)/libcbf.a: $(SOURCE) $(HEADERS) $(COMMONDEP) $(LIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG) $(INCLUDES) $(WARNINGS) -c $(SOURCE) $(AR) cr $@ *.o mv *.o $(LIB) ifneq ($(RANLIB),) $(RANLIB) $@ endif $(SOLIB)/libcbf.so: $(SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(SOURCE) $(CC) -o $@ *.o $(SOLDFLAGS) $(EXTRALIBS) rm *.o # # IMG library # $(LIB)/libimg.a: $(EXAMPLES)/img.c $(HEADERS) $(COMMONDEP) $(LIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) -c $(EXAMPLES)/img.c $(AR) cr $@ img.o ifneq ($(RANLIB),) $(RANLIB) $@ endif rm img.o $(SOLIB)/libimg.so: $(SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(EXAMPLES)/img.c $(CC) -o $@ img.o $(SOLDFLAGS) rm img.o # # CBF and IMG libraries # CBF_IMG_LIBS: $(LIB)/libcbf.a $(LIB)/libimg.a # # FCB library # $(LIB)/libfcb.a: $(F90SOURCE) $(COMMONDEP) $(LIB) ifneq ($(F90C),) $(F90C) $(F90FLAGS) -c $(F90SOURCE) $(AR) cr $@ *.o ifneq ($(RANLIB),) $(RANLIB) $@ endif rm *.o else echo "Define F90C to build $(LIB)/libfcb.a" endif $(SOLIB)/libfcb.so: $(F90SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) ifneq ($(F90C),) $(F90C) $(F90FLAGS) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(F90SOURCE) $(F90C) $(F90FLAGS) -o $@ *.o $(SOLDFLAGS) rm *.o else echo "Define F90C to build $(SOLIB)/libfcb.so" endif # # Python bindings # $(PYCBF)/_pycbf.$(PYCBFEXT): $(PYCBF) $(LIB)/libcbf.a \ $(PYCBF)/$(SETUP_PY) \ $(LIB)/libfcb.a \ $(LIB)/libimg.a \ $(PYCBF)/pycbf.i \ $(PYCBF)/cbfhandlewrappers.i \ $(PYCBF)/cbfdetectorwrappers.i \ $(PYCBF)/cbfgenericwrappers.i \ $(PYCBF)/cbfgoniometerwrappers.i (cd $(PYCBF); python $(SETUP_PY) build $(PYCBFBOPT); cp build/lib.*/_pycbf.$(PYCBFEXT) .) $(PYCBF)/setup.py: $(M4)/setup_py.m4 (m4 -P -Dregexlib=NOREGEXLIB -Dregexlibdir=NOREGEXLIBDIR $(M4)/setup_py.m4 > $@) $(PYCBF)/setup_MINGW.py: m4/setup_py.m4 (m4 -P -Dregexlib=regex -Dregexlibdir=$(REGEXDIR) $(M4)/setup_py.m4 > $@) $(LIB)/_pycbf.$(PYCBFEXT): $(PYCBF)/_pycbf.$(PYCBFEXT) cp $(PYCBF)/_pycbf.$(PYCBFEXT) $(LIB)/_pycbf.$(PYCBFEXT) $(PYCBF)/pycbf.pdf: $(PYCBF)/pycbf.w (cd $(PYCBF); \ $(NUWEB) pycbf; \ latex pycbf; \ $(NUWEB) pycbf; \ latex pycbf; \ dvipdfm pycbf ) $(PYCBF)/CBFlib.txt: $(DOC)/CBFlib.html links -dump $(DOC)/CBFlib.html > $(PYCBF)/CBFlib.txt $(PYCBF)/cbfhandlewrappers.i \ $(PYCBF)/cbfdetectorwrappers.i \ $(PYCBF)/cbfgenericwrappers.i \ $(PYCBF)/cbfgoniometerwrappers.i: $(PYCBF)/CBFlib.txt $(PYCBF)/make_pycbf.py (cd $(PYCBF); python make_pycbf.py; $(PYSWIG) pycbf.i; python setup.py build) # # Java bindings # $(JCBF)/cbflib-$(VERSION).jar: $(JCBF) $(JCBF)/jcbf.i $(JSWIG) -I$(INCLUDE) -package org.iucr.cbflib -outdir $(JCBF) $(JCBF)/jcbf.i $(JAVAC) -d . $(JCBF)/*.java $(JAR) cf $@ org $(SOLIB)/libcbf_wrap.so: $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf.so $(CC) $(CFLAGS) $(NOLLFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) $(JAVAINCLUDES) -c $(JCBF)/jcbf_wrap.c $(CC) -o $@ jcbf_wrap.o $(SOLDFLAGS) -L$(SOLIB) -lcbf rm jcbf_wrap.o # # F90SOURCE # $(SRC)/fcb_exit_binary.f90: $(M4)/fcb_exit_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_exit_binary.m4) > $(SRC)/fcb_exit_binary.f90 $(SRC)/fcb_next_binary.f90: $(M4)/fcb_next_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_next_binary.m4) > $(SRC)/fcb_next_binary.f90 $(SRC)/fcb_open_cifin.f90: $(M4)/fcb_open_cifin.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_open_cifin.m4) > $(SRC)/fcb_open_cifin.f90 $(SRC)/fcb_packed.f90: $(M4)/fcb_packed.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_packed.m4) > $(SRC)/fcb_packed.f90 $(SRC)/fcb_read_bits.f90: $(M4)/fcb_read_bits.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_bits.m4) > $(SRC)/fcb_read_bits.f90 $(SRC)/fcb_read_image.f90: $(M4)/fcb_read_image.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_image.m4) > $(SRC)/fcb_read_image.f90 $(SRC)/fcb_read_xds_i2.f90: $(M4)/fcb_read_xds_i2.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_xds_i2.m4) > $(SRC)/fcb_read_xds_i2.f90 $(EXAMPLES)/test_fcb_read_image.f90: $(M4)/test_fcb_read_image.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) test_fcb_read_image.m4) > $(EXAMPLES)/test_fcb_read_image.f90 $(EXAMPLES)/test_xds_binary.f90: $(M4)/test_xds_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) test_xds_binary.m4) > $(EXAMPLES)/test_xds_binary.f90 # # convert_image example program # $(BIN)/convert_image: $(LIB)/libcbf.a $(EXAMPLES)/convert_image.c $(EXAMPLES)/img.c \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/convert_image.c $(EXAMPLES)/img.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # convert_minicbf example program # $(BIN)/convert_minicbf: $(LIB)/libcbf.a $(EXAMPLES)/convert_minicbf.c \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/convert_minicbf.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # makecbf example program # $(BIN)/makecbf: $(LIB)/libcbf.a $(EXAMPLES)/makecbf.c $(LIB)/libimg.a $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/makecbf.c -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # adscimg2cbf example program # $(BIN)/adscimg2cbf: $(LIB)/libcbf.a $(EXAMPLES)/adscimg2cbf.c $(EXAMPLES)/adscimg2cbf_sub.c $(CC) $(CFLAGS) $(NOLLFLAG) -D_SVID_SOURCE $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/adscimg2cbf.c $(EXAMPLES)/adscimg2cbf_sub.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # cbf2adscimg example program # $(BIN)/cbf2adscimg: $(LIB)/libcbf.a $(EXAMPLES)/cbf2adscimg.c $(EXAMPLES)/cbf2adscimg_sub.c $(CC) $(CFLAGS) $(NOLLFLAG) -D_SVID_SOURCE $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cbf2adscimg.c $(EXAMPLES)/cbf2adscimg_sub.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # changtestcompression example program # $(BIN)/changtestcompression: $(LIB)/libcbf.a $(EXAMPLES)/changtestcompression.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/changtestcompression.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # img2cif example program # $(BIN)/img2cif: $(LIB)/libcbf.a $(EXAMPLES)/img2cif.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOTPINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/img2cif.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # cif2cbf example program # $(BIN)/cif2cbf: $(LIB)/libcbf.a $(EXAMPLES)/cif2cbf.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cif2cbf.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # dectris cbf_template_t program # $(BIN)/cbf_template_t: $(DECTRIS_EXAMPLES)/cbf_template_t.c \ $(DECTRIS_EXAMPLES)/mx_cbf_t_extras.h \ $(DECTRIS_EXAMPLES)/mx_parms.h $(CC) $(CFLAGS) $(NOLLFLAG) -I $(DECTRIS_EXAMPLES) $(WARNINGS) \ $(DECTRIS_EXAMPLES)/cbf_template_t.c -o $@ # # testcell example program # $(BIN)/testcell: $(LIB)/libcbf.a $(EXAMPLES)/testcell.C $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testcell.C -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # cif2c example program # $(BIN)/cif2c: $(LIB)/libcbf.a $(EXAMPLES)/cif2c.c $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cif2c.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # sauter_test example program # $(BIN)/sauter_test: $(LIB)/libcbf.a $(EXAMPLES)/sauter_test.C $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/sauter_test.C -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # sequence_match example program # $(BIN)/sequence_match: $(LIB)/libcbf.a $(EXAMPLES)/sequence_match.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/sequence_match.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # tiff2cbf example program # $(BIN)/tiff2cbf: $(LIB)/libcbf.a $(EXAMPLES)/tiff2cbf.c \ $(GOPTLIB) $(GOPTINC) $(TIFF) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ -I$(TIFFPREFIX)/include $(EXAMPLES)/tiff2cbf.c $(GOPTLIB) -L$(LIB) \ -lcbf -L$(TIFFPREFIX)/lib -ltiff $(EXTRALIBS) -limg -o $@ # # Andy Arvai''`s buffered read test program # $(BIN)/arvai_test: $(LIB)/libcbf.a $(EXAMPLES)/arvai_test.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/arvai_test.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # testreals example program # $(BIN)/testreals: $(LIB)/libcbf.a $(EXAMPLES)/testreals.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testreals.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testflat example program # $(BIN)/testflat: $(LIB)/libcbf.a $(EXAMPLES)/testflat.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testflat.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testflatpacked example program # $(BIN)/testflatpacked: $(LIB)/libcbf.a $(EXAMPLES)/testflatpacked.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testflatpacked.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ ifneq ($(F90C),) # # test_xds_binary example program # $(BIN)/test_xds_binary: $(LIB)/libfcb.a $(EXAMPLES)/test_xds_binary.f90 $(F90C) $(F90FLAGS) $(F90LDFLAGS) $(EXAMPLES)/test_xds_binary.f90 \ -L$(LIB) -lfcb -o $@ # # test_fcb_read_image example program # $(BIN)/test_fcb_read_image: $(LIB)/libfcb.a $(EXAMPLES)/test_fcb_read_image.f90 $(F90C) $(F90FLAGS) $(F90LDFLAGS) $(EXAMPLES)/test_fcb_read_image.f90 \ -L$(LIB) -lfcb -o $@ endif # # testcbf (C) # $(BIN)/ctestcbf: $(EXAMPLES)/testcbf.c $(LIB)/libcbf.a $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testcbf.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testcbf (Java) # $(BIN)/testcbf.class: $(EXAMPLES)/testcbf.java $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf_wrap.so $(JAVAC) -cp $(JCBF)/cbflib-$(VERSION).jar -d $(BIN) $(EXAMPLES)/testcbf.java # # Data files for tests # $(DATADIRI): (cd ..; $(DOWNLOAD) $(DATAURLI)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Input.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Input.tar.gz) $(DATADIRO): (cd ..; $(DOWNLOAD) $(DATAURLO)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Output.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Output.tar.gz) $(DATADIRS): (cd ..; $(DOWNLOAD) $(DATAURLS)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz) # Input Data Files TESTINPUT_BASIC = example.mar2300 DATADIRI_INPUT_BASIC = $(DATADIRI)/example.mar2300$(CEXT) TESTINPUT_EXTRA = 9ins.cif mb_LP_1_001.img insulin_pilatus6m.cbf testrealin.cbf \ testflatin.cbf testflatpackedin.cbf XRD1621.tif DATADIRI_INPUT_EXTRA = $(DATADIRI)/9ins.cif$(CEXT) $(DATADIRI)/mb_LP_1_001.img$(CEXT) \ $(DATADIRI)/insulin_pilatus6m.cbf$(CEXT) $(DATADIRI)/testrealin.cbf$(CEXT) \ $(DATADIRI)/testflatin.cbf$(CEXT) $(DATADIRI)/testflatpackedin.cbf$(CEXT) \ $(DATADIRI)/XRD1621.tif$(CEXT) # Output Data Files TESTOUTPUT = adscconverted_flat_orig.cbf \ adscconverted_orig.cbf converted_flat_orig.cbf converted_orig.cbf \ insulin_pilatus6mconverted_orig.cbf \ mb_LP_1_001_orig.cbf testcell_orig.prt \ test_xds_bin_testflatout_orig.out \ test_xds_bin_testflatpackedout_orig.out test_fcb_read_testflatout_orig.out \ test_fcb_read_testflatpackedout_orig.out \ XRD1621_orig.cbf XRD1621_I4encbC100_orig.cbf NEWTESTOUTPUT = adscconverted_flat.cbf \ adscconverted.cbf converted_flat.cbf converted.cbf \ insulin_pilatus6mconverted.cbf \ mb_LP_1_001.cbf testcell.prt \ test_xds_bin_testflatout.out \ test_xds_bin_testflatpackedout.out test_fcb_read_testflatout.out \ test_fcb_read_testflatpackedout.out \ XRD1621.cbf XRD1621_I4encbC100.cbf DATADIRO_OUTPUT = $(DATADIRO)/adscconverted_flat_orig.cbf$(CEXT) \ $(DATADIRO)/adscconverted_orig.cbf$(CEXT) \ $(DATADIRO)/converted_flat_orig.cbf$(CEXT) \ $(DATADIRO)/converted_orig.cbf$(CEXT) \ $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(CEXT) \ $(DATADIRO)/mb_LP_1_001_orig.cbf$(CEXT) \ $(DATADIRO)/testcell_orig.prt$(CEXT) \ $(DATADIRO)/test_xds_bin_testflatout_orig.out$(CEXT) \ $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(CEXT) \ $(DATADIRO)/test_fcb_read_testflatout_orig.out$(CEXT) \ $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(CEXT) \ $(DATADIRO)/XRD1621_orig.cbf$(CEXT) \ $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(CEXT) DATADIRO_OUTPUT_SIGNATURES = $(DATADIRO)/adscconverted_flat_orig.cbf$(SEXT) \ $(DATADIRO)/adscconverted_orig.cbf$(SEXT) \ $(DATADIRO)/converted_flat_orig.cbf$(SEXT) \ $(DATADIRO)/converted_orig.cbf$(SEXT) \ $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(SEXT) \ $(DATADIRO)/mb_LP_1_001_orig.cbf$(SEXT) \ $(DATADIRO)/testcell_orig.prt$(SEXT) \ $(DATADIRO)/test_xds_bin_testflatout_orig.out$(SEXT) \ $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(SEXT) \ $(DATADIRO)/test_fcb_read_testflatout_orig.out$(SEXT) \ $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(SEXT) \ $(DATADIRO)/XRD1621_orig.cbf$(SEXT) \ $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(SEXT) # Output Data File Signatures TESTOUTPUTSIGS = adscconverted_flat_orig.cbf$(SEXT) \ adscconverted_orig.cbf$(SEXT) converted_flat_orig.cbf$(SEXT) converted_orig.cbf$(SEXT) \ insulin_pilatus6mconverted_orig.cbf$(SEXT) \ mb_LP_1_001_orig.cbf$(SEXT) testcell_orig.prt$(SEXT) \ test_xds_bin_testflatout_orig.out$(SEXT) \ test_xds_bin_testflatpackedout_orig.out$(SEXT) test_fcb_read_testflatout_orig.out$(SEXT) \ test_fcb_read_testflatpackedout_orig.out$(SEXT) \ XRD1621_orig.cbf$(SEXT) DATADIRS_OUTPUT_SIGNATURES = $(DATADIRS)/adscconverted_flat_orig.cbf$(SEXT) \ $(DATADIRS)/adscconverted_orig.cbf$(SEXT) \ $(DATADIRS)/converted_flat_orig.cbf$(SEXT) \ $(DATADIRS)/converted_orig.cbf$(SEXT) \ $(DATADIRS)/insulin_pilatus6mconverted_orig.cbf$(SEXT) \ $(DATADIRS)/mb_LP_1_001_orig.cbf$(SEXT) \ $(DATADIRS)/testcell_orig.prt$(SEXT) \ $(DATADIRS)/test_xds_bin_testflatout_orig.out$(SEXT) \ $(DATADIRS)/test_xds_bin_testflatpackedout_orig.out$(SEXT) \ $(DATADIRS)/test_fcb_read_testflatout_orig.out$(SEXT) \ $(DATADIRS)/test_fcb_read_testflatpackedout_orig.out$(SEXT) \ $(DATADIRS)/XRD1621_orig.cbf$(SEXT) \ $(DATADIRS)/XRD1621_I4encbC100_orig.cbf$(SEXT) # Fetch Input Data Files $(TESTINPUT_BASIC): $(DATADIRI) $(DATADIRI_INPUT_BASIC) $(DECOMPRESS) < $(DATADIRI)/$@$(CEXT) > $@ cp $(DATADIRI)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) $(TESTINPUT_EXTRA): $(DATADIRI) $(DATADIRI_INPUT_EXTRA) $(DECOMPRESS) < $(DATADIRI)/$@$(CEXT) > $@ cp $(DATADIRI)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) # Fetch Output Data Files and Signatures $(TESTOUTPUT): $(DATADIRO) $(DATADIRO_OUTPUT) $(DATADIRO_OUTPUT_SIGNATURES) $(DECOMPRESS) < $(DATADIRO)/$@$(CEXT) > $@ cp $(DATADIRO)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) # Fetch Output Data File Signatures $(TESTOUTPUTSIGS): $(DATADIRS) $(DATADIRS_OUTPUT_SIGNATURES) cp $(DATADIRS)/$@ $@ # # Tests # tests: $(LIB) $(BIN) symlinksdone basic extra dectristests pycbftests tests_sigs_only: $(LIB) $(BIN) symlinksdone basic extra_sigs_only restore_output: $(NEWTESTOUTPUT) $(DATADIRO) $(SIGNATURE) < adscconverted_flat.cbf > $(DATADIRO)/adscconverted_flat_orig.cbf$(SEXT) $(SIGNATURE) < adscconverted.cbf > $(DATADIRO)/adscconverted_orig.cbf$(SEXT) $(SIGNATURE) < converted_flat.cbf > $(DATADIRO)/converted_flat_orig.cbf$(SEXT) $(SIGNATURE) < converted.cbf > $(DATADIRO)/converted_orig.cbf$(SEXT) $(SIGNATURE) < insulin_pilatus6mconverted.cbf > $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(SEXT) $(SIGNATURE) < mb_LP_1_001.cbf$ > $(DATADIRO)/mb_LP_1_001_orig.cbf$(SEXT) $(SIGNATURE) < testcell.prt > $(DATADIRO)/testcell_orig.prt$(SEXT) $(SIGNATURE) < test_xds_bin_testflatout.out > $(DATADIRO)/test_xds_bin_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_xds_bin_testflatpackedout.out > $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatout.out > $(DATADIRO)/test_fcb_read_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatpackedout.out > $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < XRD1621.cbf > $(DATADIRO)/XRD1621_orig.cbf$(SEXT) $(SIGNATURE) < XRD1621_I4encbC100.cbf > $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(SEXT) $(COMPRESS) < adscconverted_flat.cbf > $(DATADIRO)/adscconverted_flat_orig.cbf$(CEXT) $(COMPRESS) < adscconverted.cbf > $(DATADIRO)/adscconverted_orig.cbf$(CEXT) $(COMPRESS) < converted_flat.cbf > $(DATADIRO)/converted_flat_orig.cbf$(CEXT) $(COMPRESS) < converted.cbf > $(DATADIRO)/converted_orig.cbf$(CEXT) $(COMPRESS) < insulin_pilatus6mconverted.cbf > $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(CEXT) $(COMPRESS) < mb_LP_1_001.cbf$ > $(DATADIRO)/mb_LP_1_001_orig.cbf$(CEXT) $(COMPRESS) < testcell.prt > $(DATADIRO)/testcell_orig.prt$(CEXT) $(COMPRESS) < test_xds_bin_testflatout.out > $(DATADIRO)/test_xds_bin_testflatout_orig.out$(CEXT) $(COMPRESS) < test_xds_bin_testflatpackedout.out > $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(CEXT) $(COMPRESS) < test_fcb_read_testflatout.out > $(DATADIRO)/test_fcb_read_testflatout_orig.out$(CEXT) $(COMPRESS) < test_fcb_read_testflatpackedout.out > $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(CEXT) $(COMPRESS) < XRD1621.cbf > $(DATADIRO)/XRD1621_orig.cbf$(CEXT) $(COMPRESS) < XRD1621_I4encbC100.cbf > $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(CEXT) restore_sigs_only: $(NEWTESTOUTPUT) $(DATADIRS) $(SIGNATURE) < adscconverted_flat.cbf > $(DATADIRS)/adscconverted_flat_orig.cbf$(SEXT) $(SIGNATURE) < adscconverted.cbf > $(DATADIRS)/adscconverted_orig.cbf$(SEXT) $(SIGNATURE) < converted_flat.cbf > $(DATADIRS)/converted_flat_orig.cbf$(SEXT) $(SIGNATURE) < converted.cbf > $(DATADIRS)/converted_orig.cbf$(SEXT) $(SIGNATURE) < insulin_pilatus6mconverted.cbf > $(DATADIRS)/insulin_pilatus6mconverted_orig.cbf$(SEXT) $(SIGNATURE) < mb_LP_1_001.cbf$ > $(DATADIRS)/mb_LP_1_001_orig.cbf$(SEXT) $(SIGNATURE) < testcell.prt > $(DATADIRS)/testcell_orig.prt$(SEXT) $(SIGNATURE) < test_xds_bin_testflatout.out > $(DATADIRS)/test_xds_bin_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_xds_bin_testflatpackedout.out > $(DATADIRS)/test_xds_bin_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatout.out > $(DATADIRS)/test_fcb_read_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatpackedout.out > $(DATADIRS)/test_fcb_read_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < XRD1621.cbf > $(DATADIRS)/XRD1621_orig.cbf$(SEXT) $(SIGNATURE) < XRD1621_I4encbC100.cbf > $(DATADIRS)/XRD1621_I4encbC100_orig.cbf$(SEXT) restore_signatures: restore_output restore_sigs_only # # Basic Tests # basic: $(BIN)/makecbf $(BIN)/img2cif $(BIN)/cif2cbf $(TESTINPUT_BASIC) $(BIN)/makecbf example.mar2300 makecbf.cbf $(BIN)/img2cif -c flatpacked -m headers -d digest \ -e base64 example.mar2300 img2cif_packed.cif $(BIN)/img2cif -c canonical -m headers -d digest \ -e base64 example.mar2300 img2cif_canonical.cif $(BIN)/img2cif -c flatpacked -m headers -d digest \ -e none example.mar2300 img2cif_packed.cbf $(BIN)/img2cif -c canonical -m headers -d digest \ -e none example.mar2300 img2cif_canonical.cbf $(BIN)/cif2cbf -e none -c flatpacked \ img2cif_canonical.cif cif2cbf_packed.cbf $(BIN)/cif2cbf -e none -c canonical \ img2cif_packed.cif cif2cbf_canonical.cbf -cmp cif2cbf_packed.cbf makecbf.cbf -cmp cif2cbf_packed.cbf img2cif_packed.cbf -cmp cif2cbf_canonical.cbf img2cif_canonical.cbf # # Extra Tests # ifneq ($(F90C),) extra: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/test_xds_binary $(BIN)/test_fcb_read_image $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg \ $(BIN)/changtestcompression $(BIN)/tiff2cbf \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUT) else extra: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUT) endif $(TIME) $(BIN)/cif2cbf -e hex -c none \ makecbf.cbf cif2cbf_ehcn.cif $(TIME) $(BIN)/cif2cbf -e none -c flatpacked \ cif2cbf_ehcn.cif cif2cbf_encp.cbf; rm cif2cbf_ehcn.cif -cmp makecbf.cbf cif2cbf_encp.cbf $(TIME) $(BIN)/cif2cbf -i 9ins.cif -o 9ins.cbf -cmp 9ins.cif 9ins.cbf $(TIME) $(BIN)/convert_image -F example.mar2300 converted_flat.cbf -cmp converted_flat.cbf converted_flat_orig.cbf $(TIME) $(BIN)/convert_image example.mar2300 converted.cbf -cmp converted.cbf converted_orig.cbf -$(TIME) $(BIN)/testcell < testcell.dat > testcell.prt -cmp testcell.prt testcell_orig.prt $(TIME) $(BIN)/convert_image -F -d adscquantum315 mb_LP_1_001.img adscconverted_flat.cbf -cmp adscconverted_flat.cbf adscconverted_flat_orig.cbf $(TIME) $(BIN)/convert_image -d adscquantum315 mb_LP_1_001.img adscconverted.cbf -cmp adscconverted.cbf adscconverted_orig.cbf $(TIME) $(BIN)/adscimg2cbf --no_pad --cbf_packed,flat mb_LP_1_001.img -cmp mb_LP_1_001.cbf mb_LP_1_001_orig.cbf ifneq ($(CLEANTESTS),) mv mb_LP_1_001.cbf nmb_LP_1_001.cbf else cp mb_LP_1_001.cbf nmb_LP_1_001.cbf endif $(TIME) $(BIN)/cbf2adscimg nmb_LP_1_001.cbf -cmp nmb_LP_1_001.img mb_LP_1_001.img rm nmb_LP_1_001.cbf ifneq ($(CLEANTESTS),) rm nmb_LP_1_001.img endif $(TIME) $(BIN)/convert_minicbf -d pilatus6m insulin_pilatus6m.cbf insulin_pilatus6mconverted.cbf -cmp insulin_pilatus6mconverted.cbf insulin_pilatus6mconverted_orig.cbf $(TIME) $(BIN)/testreals -cmp testrealin.cbf testrealout.cbf $(TIME) $(BIN)/testflat -cmp testflatin.cbf testflatout.cbf $(TIME) $(BIN)/testflatpacked -cmp testflatpackedin.cbf testflatpackedout.cbf ifneq ($(F90C),) echo testflatout.cbf | $(TIME) $(BIN)/test_xds_binary > test_xds_bin_testflatout.out -$(DIFF) test_xds_bin_testflatout.out test_xds_bin_testflatout_orig.out echo testflatpackedout.cbf | $(TIME) $(BIN)/test_xds_binary > test_xds_bin_testflatpackedout.out -$(DIFF) test_xds_bin_testflatpackedout.out test_xds_bin_testflatpackedout_orig.out echo testflatout.cbf | $(TIME) $(BIN)/test_fcb_read_image > test_fcb_read_testflatout.out -$(DIFF) test_fcb_read_testflatout.out test_fcb_read_testflatout_orig.out echo testflatpackedout.cbf | $(TIME) $(BIN)/test_fcb_read_image > test_fcb_read_testflatpackedout.out -$(DIFF) test_fcb_read_testflatpackedout.out test_fcb_read_testflatpackedout_orig.out endif $(TIME) $(BIN)/sauter_test $(TIME) $(BIN)/changtestcompression $(TIME) (export LD_LIBRARY_PATH=$(LIB);$(BIN)/tiff2cbf XRD1621.tif XRD1621.cbf) -$(DIFF) XRD1621.cbf XRD1621_orig.cbf $(TIME) $(BIN)/cif2cbf -I 4 -C 100. -L 0. -e n -c b -i XRD1621.cbf -o XRD1621_I4encbC100.cbf -$(DIFF) XRD1621_I4encbC100.cbf XRD1621_I4encbC100_orig.cbf ifneq ($(F90C),) extra_sigs_only: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/test_xds_binary $(BIN)/test_fcb_read_image $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg $(BIN)/tiff2cbf \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) else extra_sigs_only: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf\ basic $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) endif $(TIME) $(BIN)/cif2cbf -e hex -c none \ makecbf.cbf cif2cbf_ehcn.cif $(TIME) $(BIN)/cif2cbf -e none -c packed \ cif2cbf_ehcn.cif cif2cbf_encp.cbf; rm cif2cbf_ehcn.cif -cmp makecbf.cbf cif2cbf_encp.cbf $(TIME) $(BIN)/cif2cbf -i 9ins.cif -o 9ins.cbf -cmp 9ins.cif 9ins.cbf $(TIME) $(BIN)/convert_image -F example.mar2300 converted_flat.cbf -$(SIGNATURE) < converted_flat.cbf | $(DIFF) - converted_flat_orig.cbf$(SEXT); rm converted_flat.cbf $(TIME) $(BIN)/convert_image example.mar2300 converted.cbf -$(SIGNATURE) < converted.cbf | $(DIFF) - converted_orig.cbf$(SEXT); rm converted.cbf -$(TIME) $(BIN)/testcell < testcell.dat | \ $(SIGNATURE) | $(DIFF) - testcell_orig.prt$(SEXT) $(TIME) $(BIN)/convert_image -F -d adscquantum315 mb_LP_1_001.img adscconverted_flat.cbf -$(SIGNATURE) < adscconverted_flat.cbf | $(DIFF) - adscconverted_flat_orig.cbf$(SEXT) $(TIME) $(BIN)/convert_image -d adscquantum315 mb_LP_1_001.img adscconverted.cbf -$(SIGNATURE) < adscconverted.cbf | $(DIFF) - adscconverted_orig.cbf$(SEXT); rm adscconverted.cbf $(TIME) $(BIN)/adscimg2cbf --cbf_packed,flat mb_LP_1_001.img -$(SIGNATURE) < mb_LP_1_001.cbf | $(DIFF) - mb_LP_1_001_orig.cbf$(SEXT) mv mb_LP_1_001.cbf nmb_LP_1_001.cbf $(TIME) $(BIN)/cbf2adscimg nmb_LP_1_001.cbf -cmp nmb_LP_1_001.img mb_LP_1_001.img rm nmb_LP_1_001.cbf rm nmb_LP_1_001.img $(TIME) $(BIN)/convert_minicbf -d pilatus6m insulin_pilatus6m.cbf insulin_pilatus6mconverted.cbf -$(SIGNATURE) < insulin_pilatus6mconverted.cbf | $(DIFF) - insulin_pilatus6mconverted_orig.cbf$(SEXT); rm insulin_pilatus6mconverted.cbf $(TIME) $(BIN)/testreals -cmp testrealin.cbf testrealout.cbf $(TIME) $(BIN)/testflat -cmp testflatin.cbf testflatout.cbf $(TIME) $(BIN)/testflatpacked -cmp testflatpackedin.cbf testflatpackedout.cbf ifneq ($(F90C),) echo testflatout.cbf | $(TIME) $(BIN)/test_xds_binary | \ $(SIGNATURE) | $(DIFF) - test_xds_bin_testflatout_orig.out$(SEXT) echo testflatpackedout.cbf | $(TIME) $(BIN)/test_xds_binary | \ $(SIGNATURE) | $(DIFF) - test_xds_bin_testflatpackedout_orig.out$(SEXT) echo testflatout.cbf | $(TIME) $(BIN)/test_fcb_read_image | \ $(SIGNATURE) | $(DIFF) - test_fcb_read_testflatout_orig.out$(SEXT) echo testflatpackedout.cbf | $(TIME) $(BIN)/test_fcb_read_image | \ $(SIGNATURE) | $(DIFF) - test_fcb_read_testflatpackedout_orig.out$(SEXT) endif $(TIME) $(BIN)/sauter_test $(TIME) $(BIN)/tiff2cbf XRD1621.tif XRD1621.cbf $(TIME) $(BIN)/cif2cbf -I 4 -C 100. -L 0. -e n -c b -i XRD1621.cbf -o XRD1621_I4encbC100.cbf -$(SIGNATURE) < XRD1621.cbf | $(DIFF) - XRD1621_orig.cbf$(SEXT); rm XRD1621.cbf -$(SIGNATURE) < XRD1621_I4encbC100.cbf | $(DIFF) - XRD1621_I4encbC100_orig.cbf$(SEXT); rm XRD1621_I4encbC100.cbf @-rm -f adscconverted_flat.cbf @-rm -f $(TESTINPUT_BASIC) $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) @-rm -f cif2cbf_packed.cbf makecbf.cbf \ cif2cbf_packed.cbf img2cif_packed.cbf \ cif2cbf_canonical.cbf img2cif_canonical.cbf @-rm -f testrealout.cbf testflatout.cbf testflatpackedout.cbf \ cif2cbf_encp.cbf img2cif_canonical.cif img2cif_packed.cif 9ins.cbf pycbftests: $(PYCBF)/_pycbf.$(PYCBFEXT) (cd $(PYCBF); python pycbf_test1.py) (cd $(PYCBF); python pycbf_test2.py) (cd $(PYCBF); python pycbf_test3.py) javatests: $(BIN)/ctestcbf $(BIN)/testcbf.class $(SOLIB)/libcbf_wrap.so $(BIN)/ctestcbf > testcbfc.txt $(LDPREFIX) java -cp $(JCBF)/cbflib-$(VERSION).jar:$(BIN) testcbf > testcbfj.txt $(DIFF) testcbfc.txt testcbfj.txt dectristests: $(BIN)/cbf_template_t $(DECTRIS_EXAMPLES)/cbf_test_orig.out (cd $(DECTRIS_EXAMPLES); ../../bin/cbf_template_t; diff -a -u cbf_test_orig.out cbf_template_t.out) # # Remove all non-source files # empty: @-rm -f $(LIB)/*.o @-rm -f $(LIB)/libcbf.a @-rm -f $(LIB)/libfcb.a @-rm -f $(LIB)/libimg.a @-rm -f $(LIB)/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/build/*/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/build/src/cbf_simple.o @-rm -f $(PYCBF)/build/*/pycbf_wrap.o @-rm -rf $(BIN)/adscimg2cbf* @-rm -rf $(BIN)/cbf2adscimg* @-rm -rf $(BIN)/makecbf* @-rm -rf $(BIN)/img2cif* @-rm -rf $(BIN)/cif2cbf* @-rm -rf $(BIN)/convert_image* @-rm -rf $(BIN)/convert_minicbf* @-rm -rf $(BIN)/test_fcb_read_image* @-rm -rf $(BIN)/test_xds_binary* @-rm -rf $(BIN)/testcell* @-rm -rf $(BIN)/cif2c* @-rm -rf $(BIN)/testreals* @-rm -rf $(BIN)/testflat* @-rm -rf $(BIN)/testflatpacked* @-rm -rf $(BIN)/cbf_template_t* @-rm -rf $(BIN)/sauter_test* @-rm -rf $(BIN)/arvai_test* @-rm -rf $(BIN)/changtestcompression* @-rm -rf $(BIN)/tiff2cbf* @-rm -f makecbf.cbf @-rm -f img2cif_packed.cif @-rm -f img2cif_canonical.cif @-rm -f img2cif_packed.cbf @-rm -f img2cif_canonical.cbf @-rm -f img2cif_raw.cbf @-rm -f cif2cbf_packed.cbf @-rm -f cif2cbf_canonical.cbf @-rm -f converted.cbf @-rm -f adscconverted.cbf @-rm -f converted_flat.cbf @-rm -f adscconverted_flat.cbf @-rm -f adscconverted_flat_rev.cbf @-rm -f mb_LP_1_001.cbf @-rm -f cif2cbf_ehcn.cif @-rm -f cif2cbf_encp.cbf @-rm -f 9ins.cbf @-rm -f 9ins.cif @-rm -f testcell.prt @-rm -f example.mar2300 @-rm -f converted_orig.cbf @-rm -f adscconverted_orig.cbf @-rm -f converted_flat_orig.cbf @-rm -f adscconverted_flat_orig.cbf @-rm -f adscconverted_flat_rev_orig.cbf @-rm -f mb_LP_1_001_orig.cbf @-rm -f insulin_pilatus6mconverted_orig.cbf @-rm -f insulin_pilatus6mconverted.cbf @-rm -f insulin_pilatus6m.cbf @-rm -f testrealin.cbf @-rm -f testrealout.cbf @-rm -f testflatin.cbf @-rm -f testflatout.cbf @-rm -f testflatpackedin.cbf @-rm -f testflatpackedout.cbf @-rm -f CTC.cbf @-rm -f test_fcb_read_testflatout.out @-rm -f test_fcb_read_testflatpackedout.out @-rm -f test_xds_bin_testflatpackedout.out @-rm -f test_xds_bin_testflatout.out @-rm -f test_fcb_read_testflatout_orig.out @-rm -f test_fcb_read_testflatpackedout_orig.out @-rm -f test_xds_bin_testflatpackedout_orig.out @-rm -f test_xds_bin_testflatout_orig.out @-rm -f mb_LP_1_001.img @-rm -f 9ins.cif @-rm -f testcell_orig.prt @-rm -f $(DECTRIS_EXAMPLES)/cbf_template_t.out @-rm -f XRD1621.cbf @-rm -f XRD1621_orig.cbf @-rm -f XRD1621_orig.cbf @-rm -f XRD1621_I4encbC100.cbf @-rm -f $(SRC)/fcb_exit_binary.f90 @-rm -f $(SRC)/fcb_next_binary.f90 @-rm -f $(SRC)/fcb_open_cifin.f90 @-rm -f $(SRC)/fcb_packed.f90 @-rm -f $(SRC)/fcb_read_bits.f90 @-rm -f $(SRC)/fcb_read_image.f90 @-rm -f $(SRC)/fcb_read_xds_i2.f90 @-rm -f $(EXAMPLES)/test_fcb_read_image.f90 @-rm -f $(EXAMPLES)/test_xds_binary.f90 @-rm -f symlinksdone @-rm -f $(TESTOUTPUT) *$(SEXT) @-rm -f $(SOLIB)/*.o @-rm -f $(SOLIB)/libcbf_wrap.so @-rm -f $(SOLIB)/libjcbf.so @-rm -f $(SOLIB)/libimg.so @-rm -f $(SOLIB)/libfcb.so @-rm -rf $(JCBF)/org @-rm -f $(JCBF)/*.java @-rm -f $(JCBF)/jcbf_wrap.c @-rm -f $(SRC)/cbf_wrap.c @-rm -f $(BIN)/ctestcbf $(BIN)/testcbf.class testcbfc.txt testcbfj.txt @-rm -rf $(REGEX) @-rm -rf $(TIFF) ./.undosymlinks # # Remove temporary files # clean: @-rm -f core @-rm -f *.o @-rm -f *.u # # Restore to distribution state # distclean: clean empty # # Create a Tape Archive for distribution # tar: $(DOCUMENTS) $(SOURCE) $(SRC)/cbf.stx $(HEADERS) $(M4FILES)\ $(EXAMPLES) \ README.html README Makefile \ $(JPEGS) -/bin/rm -f CBFlib.tar* tar cvBf CBFlib.tar \ $(DOCUMENTS) $(SOURCE) $(SRC)/cbf.stx $(HEADERS) $(M4FILES)\ $(EXAMPLES) \ README.html README Makefile \ $(JPEGS) gzip --best CBFlib.tar ' ./CBFlib-0.9.2.2/m4/test_xds_binary.m40000644000076500007650000000126011603702103015555 0ustar yayayayam4_include(`fcblib_defines.m4')` PROGRAM TEST IMPLICIT NONE CHARACTER(LEN=100) LINE INTEGER(2) IFRAME(1000,1000), DPREV INTEGER(4) JFRAME(1000,1000) INTEGER IER, I, J, K' fcb_interface_FCB_READ_XDS_I2 ` PRINT *,''` NAME OF TEST CBF ''` READ *, LINE IER = FCB_READ_XDS_I2(LINE,9,1000,1000,IFRAME,JFRAME) IF (IER.NE.0) THEN PRINT *," ERROR: ", IER ELSE DPREV = 0 DO I = 1,1000 DO J = 1,1000 IF (IFRAME(I,J).NE.DPREV) THEN PRINT *,"ROW ", I, ":" PRINT *,(IFRAME(I,K),K=1,1000) DPREV = IFRAME(I,1000) GO TO 1000 ENDIF END DO 1000 CONTINUE END DO END IF STOP END './CBFlib-0.9.2.2/m4/fcb_read_xds_i2.m40000644000076500007650000002303511603702103015355 0ustar yayayayam4_include(`fcblib_defines.m4') ` INTEGER FUNCTION FCB_READ_XDS_I2(FILNAM,TAPIN,NX,NY,IFRAME,JFRAME) !----------------------------------------------------------------------- ! Reads a 32 bit integer two''`s complement image compressed by a ! BYTE-OFFSET algorithm. W. Kabsch, Version 9-2006 ! ! REVISED 1-2007, H. J. Bernstein to conform to CBFlib_0.7.7 ! (http://www.bernstein-plus-sons.com/software/CBF) ! ! The BYTE-OFFSET algorithm is a slightly simplified version of ! that described in Andy Hammersley''`s web page ! (http://www.esrf.fr/computing/Forum/imgCIF/cbf_definition.html) ! !----------------------------------------------------------------------- ! FILNAM - Name of the file countaining the image (GIVEN) ! TAPIN - Fortran device unit number assigned to image file (GIVEN) ! NX - Number of "fast" pixels of the image (GIVEN) ! NY - Number of "slow" pixels of the image (GIVEN) ! IFRAME - 16 bit coded image as needed by XDS (RESULT) ! Returns (as function value) (RESULT) ! CBF_FORMAT (=1): ! cannot handle this CBF format (not implemented) ! 0: No error ! -1: Cannot determine endian architecture of this machine ! -2: Cannot open image file ! -3: Wrong image format ! -4: Cannot read image !----------------------------------------------------------------------- IMPLICIT NONE CHARACTER(len=*),INTENT(IN) :: FILNAM INTEGER, INTENT(IN) :: TAPIN,NX,NY INTEGER(2), INTENT(OUT):: IFRAME(NX*NY) INTEGER(4), INTENT(OUT):: JFRAME(NX,NY) INTEGER(8) NELEM,NELEM_READ ! -- Definition of CBF_FORMAT' fcb_errcode_CBF_FORMAT `! -- External functions called' fcb_interface_FCB_READ_BYTE fcb_interface_FCB_NEXT_BINARY fcb_interface_FCB_CI_STRNCMPARR fcb_interface_FCB_DECOMPRESS_PACKED_I4 INTEGER(2) CNT2PIX `! -- Local variables INTEGER,PARAMETER:: FCB_BYTES_IN_REC='m4_ifelse(`fcb_bytes_in_rec',`',4096,`fcb_bytes_in_rec')` INTEGER FCB_RECORD_SIZE,BYTE_IN_FILE,REC_IN_FILE, & STEP,FIRST2,LAST2,FIRST4,LAST4,I,J,IOS INTEGER(4) DIFF,PIXVALUE,MARKER,IADR INTEGER(2) SHORTINT INTEGER(1) BUFFER(FCB_BYTES_IN_REC),LAST_CHAR,ONEBYTE, & TWOBYTES(2),FOURBYTES(4),ENDIANORDER(4), & MARKBYTES(4) INTEGER ENCODING ' fcb_param_ENC_LIST_ALL ` INTEGER SIZE INTEGER ID INTEGER COMPRESSION ' fcb_param_CBF_LIST_ALL ` INTEGER BITS,VORZEICHEN,REELL CHARACTER(len=24) DIGEST CHARACTER(len=14) BYTEORDER !Possible parameter values for BYTEORDER are: !"LITTLE_ENDIAN" supported !"BIG_ENDIAN" not supported INTEGER(8) DIMOVER INTEGER(8) DIM1 !Number of "fast" pixels of the image INTEGER(8) DIM2 !Number of "slow" pixels of the image INTEGER(8) DIM3 INTEGER(8) PADDING INTEGER(4) PREV_ELEMENT DATA ENDIANORDER/Z''`12''`,Z''`34''`,Z''`56''`,Z''`78''`/ DATA MARKBYTES/Z''`0C''`,Z''`1A''`,Z''`04''`,Z''`D5''`/ !----------------------------------------------------------------------- ! -- Determine endian architecture of this machine !----------------------------------------------------------------------- ! Definition: If the lowest memory address of multi-byte data is ! considered the starting address of the data, the least ! significant byte (LSB) is at the lowest memory address ! for a ''`little_endian''` cpu architecture. ! ! Example: The 32 bit hex value Z''`12345678''` is stored as follows: ! ENDIAN ORDER BYTE0 BYTE1 BYTE2 BYTE3 ! Big Endian 12 34 56 78(LSB) ! Little Endian 78(LSB) 56 34 12 !----------------------------------------------------------------------- PIXVALUE=TRANSFER(ENDIANORDER,PIXVALUE) STEP=0 IF (PIXVALUE .EQ. Z''`78563412''`) THEN !Little Endian machine STEP=1 FIRST2=1;LAST2=2 FIRST4=1;LAST4=4 ENDIF IF (PIXVALUE .EQ. Z''`12345678''`) THEN ! Big Endian machine STEP=-1 FIRST2=2;LAST2=1 FIRST4=4;LAST4=1 ENDIF IF (STEP.EQ.0)GO TO 110 'fcb_macro_FCB_OPEN_CIFIN(`ERR=120',`IOSTAT=IOS',`GO TO 130') m4_dnl ` IF (IOS.GT.0) GO TO 140 !----------------------------------------------------------------------- ! -- Skip to the next binary and parse the MIME header !----------------------------------------------------------------------- IF (FCB_NEXT_BINARY(TAPIN,LAST_CHAR,FCB_BYTES_IN_REC,BYTE_IN_FILE,& REC_IN_FILE,BUFFER,ENCODING,SIZE,ID,DIGEST,COMPRESSION,BITS, & VORZEICHEN,REELL,BYTEORDER,DIMOVER,DIM1,DIM2,DIM3,PADDING).NE.0)& GO TO 130 IF ((DIM1.NE.NX).OR.(DIM2.NE.NY))GO TO 130 !----------------------------------------------------------------------- ! -- Advance to start of binary image data !----------------------------------------------------------------------- ! In CBF the binary data begins immediately after the first occurence ! of the following 4 bytes (MARKBYTES) in the image file ! Octet Hex Decimal Purpose ! 1 0C 12 (ctrl-L) End the current page ! 2 1A 26 (ctrl-Z) Stop listings in MS-DOS ! 3 04 04 (Ctrl-D) Stop listings in UNIX ! 4 D5 213 Binary section begins ! 5..5+n-1 Binary data (n octets) !----------------------------------------------------------------------- MARKER=TRANSFER(MARKBYTES,MARKER) FOURBYTES=0 DO DO I=1,3 FOURBYTES(I)=FOURBYTES(I+1) ENDDO BYTE_IN_FILE=BYTE_IN_FILE+1 IF (FCB_READ_BYTE(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,FOURBYTES(4)).NE.0) GO TO 140 PIXVALUE=TRANSFER(FOURBYTES,PIXVALUE) IF (PIXVALUE.EQ.MARKER)EXIT ENDDO ! *** DEBUG *** PRINT *, "fwa-1 address of IMAGE at: " ! *** DEBUG *** PRINT *, "BYTE_IN_FILE: ", BYTE_IN_FILE ! *** DEBUG *** PRINT *, "REC_IN_FILE: ", REC_IN_FILE !----------------------------------------------------------------------- ! -- Read data image of 32 bit two''`s complement integers, compressed ! -- by the BYTE-OFFSET algorithm. ! -- After the expansion the original pixel values are coded by 16 bit ! -- in a special way suitable for XDS (see INTEGER*2 FUNCTION CNT2PIX). !----------------------------------------------------------------------- FCB_READ_XDS_I2=CBF_FORMAT !Cannot handle this CBF format IF ((BYTEORDER.EQ."LITTLE_ENDIAN").AND.(ENCODING.EQ.ENC_NONE).AND.& (IAND(COMPRESSION,CBF_COMPRESSION_MASK).EQ.CBF_BYTE_OFFSET))THEN PIXVALUE=0 DO IADR=1,NX*NY BYTE_IN_FILE=BYTE_IN_FILE+1 IF (FCB_READ_BYTE(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,ONEBYTE).NE.0) GO TO 140 DIFF=ONEBYTE IF (DIFF.EQ.-128)THEN DO I=FIRST2,LAST2,STEP BYTE_IN_FILE=BYTE_IN_FILE+1 IF (FCB_READ_BYTE(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,TWOBYTES(I)).NE.0)GO TO 140 ENDDO SHORTINT=TRANSFER(TWOBYTES,SHORTINT) DIFF=SHORTINT IF (DIFF.EQ.-32768)THEN DO I=FIRST4,LAST4,STEP BYTE_IN_FILE=BYTE_IN_FILE+1 IF (FCB_READ_BYTE(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,FOURBYTES(I)).NE.0) & GO TO 140 ENDDO DIFF=TRANSFER(FOURBYTES,DIFF) ENDIF ENDIF PIXVALUE=PIXVALUE+DIFF IFRAME(IADR)=CNT2PIX(PIXVALUE) ! xds-specific 16 bit coding ENDDO FCB_READ_XDS_I2=0 !No error ELSE IF ((BYTEORDER.EQ."LITTLE_ENDIAN").AND.(ENCODING.EQ.ENC_NONE).AND.& ((IAND(COMPRESSION,CBF_COMPRESSION_MASK).EQ.CBF_PACKED) .OR. & (IAND(COMPRESSION,CBF_COMPRESSION_MASK).EQ.CBF_PACKED_V2)))THEN NELEM = NX*NY FCB_READ_XDS_I2=FCB_DECOMPRESS_PACKED_I4 (JFRAME,NELEM,NELEM_READ, & VORZEICHEN, COMPRESSION, DIM1, DIM2, & TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) IF (NELEM_READ.NE.NELEM) PRINT *, "EARLY TERMINATION AT ",NELEM_READ PREV_ELEMENT = 0 DO J = 1,NY DO I = 1,NX IF (JFRAME(I,J).NE.PREV_ELEMENT) THEN PREV_ELEMENT = JFRAME(I,J) PRINT *,"ARRAY(",I+(J-1)*NX,") =",JFRAME(I,J) ENDIF IFRAME(I+(J-1)*NX) = CNT2PIX(JFRAME(I,J)) END DO END DO END IF END IF !----------------------------------------------------------------------- 100 CLOSE(TAPIN) RETURN 110 FCB_READ_XDS_I2=-1 !Cannot determine endian architecture of this machine RETURN 120 FCB_READ_XDS_I2=-2 !Cannot open image file RETURN 130 FCB_READ_XDS_I2=-3 !Wrong image format GO TO 100 140 FCB_READ_XDS_I2=-4 !Cannot read image GO TO 100 END FUNCTION FCB_READ_XDS_I2 INTEGER(2) FUNCTION CNT2PIX(I32) IMPLICIT NONE INTEGER(4),INTENT(IN)::I32 INTEGER(4),PARAMETER ::RATIO=32 !compression ratio INTEGER(4),PARAMETER ::OFLOW=RATIO*32768 !largest 32 bit INTEGER INTEGER(4),PARAMETER ::UFLOW=1-32768/RATIO !smallest 32 bit INTEGER REAL(4) R ! I16=CNT2PIX(I32) codes an integer I32 in the range UFLOW<=I32<=OFLOW ! by a 16 bit number I16. ! J32=PIX2CNT(I16) retrieves an approximation to the original value ! with a maximum absolute error of RATIO/2. R=MIN(I32,OFLOW) R=MAX(I32,UFLOW) IF (I32.GT.32767)R=-R/RATIO CNT2PIX=NINT(R) RETURN END FUNCTION CNT2PIX' ./CBFlib-0.9.2.2/m4/fcblib_defines.m40000644000076500007650000012676011603702103015307 0ustar yayayayam4_define(`fcb_not_first',`')m4_dnl m4_define(`fcb_is_last',`is_last')m4_dnl m4_dnl Error codes: m4_define(`fcb_errcode_CBF_FORMAT', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_FORMAT = Z''`00000001''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` ! 1')m4_dnl m4_define(`fcb_errcode_CBF_ALLOC', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_ALLOC = Z''`00000002''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` ! 2')m4_dnl m4_define(`fcb_errcode_CBF_ARGUMENT', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_ARGUMENT = Z''`00000004''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` ! 4')m4_dnl m4_define(`fcb_errcode_CBF_ASCII', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_ASCII = Z''`00000008''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` ! 8')m4_dnl m4_define(`fcb_errcode_CBF_BINARY', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_BINARY = Z''`00000010''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` ! 16')m4_dnl m4_define(`fcb_errcode_CBF_BITCOUNT', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_BITCOUNT = Z''`00000020''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` ! 32')m4_dnl m4_define(`fcb_errcode_CBF_ENDOFDATA', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_ENDOFDATA = Z''`00000040''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` ! 64')m4_dnl m4_define(`fcb_errcode_CBF_FILECLOSE', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_FILECLOSE = Z''`00000080''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` ! 128')m4_dnl m4_define(`fcb_errcode_CBF_FILEOPEN', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_FILEOPEN = Z''`00000100''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` ! 256')m4_dnl m4_define(`fcb_errcode_CBF_FILEREAD', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_FILEREAD = Z''`00000200''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` ! 512')m4_dnl m4_define(`fcb_errcode_CBF_FILESEEK', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_FILESEEK = Z''`00000400''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` ! 1024')m4_dnl m4_define(`fcb_errcode_CBF_FILETELL', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_FILETELL = Z''`00000800''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` ! 2048')m4_dnl m4_define(`fcb_errcode_CBF_FILEWRITE', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_FILEWRITE = Z''`00001000''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` ! 4096')m4_dnl m4_define(`fcb_errcode_CBF_IDENTICAL', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_IDENTICAL = Z''`00002000''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` ! 8192')m4_dnl m4_define(`fcb_errcode_CBF_NOTFOUND', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_NOTFOUND = Z''`00004000''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` ! 16384')m4_dnl m4_define(`fcb_errcode_CBF_OVERFLOW', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_OVERFLOW = Z''`00008000''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` ! 32768')m4_dnl m4_define(`fcb_errcode_CBF_UNDEFINED', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_UNDEFINED = Z''`00010000''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` ! 65536')m4_dnl m4_define(`fcb_errcode_CBF_NOTIMPLEMENTED', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_NOTIMPLEMENTED = Z''`00020000''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` ! 131072')m4_dnl m4_define(`fcb_errcode_LIST_ALL', m4_define(`fcb_is_last',`')m4_dnl ! ! Definitions of CBF error code parameters ! fcb_errcode_CBF_FORMAT m4_define(`fcb_not_first',`not_first')m4_dnl fcb_errcode_CBF_ALLOC fcb_errcode_CBF_ARGUMENT fcb_errcode_CBF_ASCII fcb_errcode_CBF_BINARY fcb_errcode_CBF_BITCOUNT fcb_errcode_CBF_ENDOFDATA fcb_errcode_CBF_FILECLOSE fcb_errcode_CBF_FILEOPEN fcb_errcode_CBF_FILEREAD fcb_errcode_CBF_FILESEEK fcb_errcode_CBF_FILETELL fcb_errcode_CBF_FILEWRITE fcb_errcode_CBF_IDENTICAL fcb_errcode_CBF_NOTFOUND fcb_errcode_CBF_OVERFLOW fcb_errcode_CBF_UNDEFINED m4_define(`fcb_is_last',`is_last')m4_dnl fcb_errcode_CBF_NOTIMPLEMENTED m4_define(`fcb_not_first',`')m4_dnl )m4_dnl m4_dnl m4_dnl Possible parameter values for ENCODING are: m4_define(`fcb_param_ENC_NONE', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')ENC_NONE = Z''`0001''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` !Use BINARY encoding')m4_dnl m4_define(`fcb_param_ENC_BASE64', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')ENC_BASE64 = Z''`0002''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` !Use BASE64 encoding')m4_dnl m4_define(`fcb_param_ENC_BASE32k', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')ENC_BASE32K = Z''`0004''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` !Use X-BASE32K encoding')m4_dnl m4_define(`fcb_param_ENC_QP', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')ENC_QP = Z''`0008''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` !Use QUOTED-PRINTABLE encoding')m4_dnl m4_define(`fcb_param_ENC_BASE10', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')ENC_BASE10 = Z''`0010''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` !Use BASE10 encoding')m4_dnl m4_define(`fcb_param_ENC_BASE16', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')ENC_BASE16 = Z''`0020''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` !Use BASE16 encoding')m4_dnl m4_define(`fcb_param_ENC_BASE8', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')ENC_BASE8 = Z''`0040''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` !Use BASE8 encoding')m4_dnl m4_define(`fcb_param_ENC_LIST_ALL', m4_define(`fcb_is_last',`')m4_dnl ! ! Definitions of CBF encodings parameters ! fcb_param_ENC_NONE m4_define(`fcb_not_first',`not_first')m4_dnl fcb_param_ENC_BASE64 fcb_param_ENC_BASE32k fcb_param_ENC_QP fcb_param_ENC_BASE10 fcb_param_ENC_BASE16 m4_define(`fcb_is_last',`is_last')m4_dnl fcb_param_ENC_BASE8 m4_define(`fcb_not_first',`')m4_dnl )m4_dnl m4_dnl m4_dnl Possible parameter values for COMPRESSION are: m4_dnl m4_define(`fcb_param_CBF_INTEGER', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_INTEGER = Z''`0010''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` !Uncompressed integer')m4_dnl m4_define(`fcb_param_CBF_FLOAT', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_FLOAT = Z''`0020''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` !Uncompressed IEEE floating point')m4_dnl m4_define(`fcb_param_CBF_CANONICAL', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_CANONICAL = Z''`0050''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` !Canonical compression')m4_dnl m4_define(`fcb_param_CBF_PACKED', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_PACKED = Z''`0060''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` !Packed compression')m4_dnl m4_define(`fcb_param_CBF_PACKED_V2', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_PACKED_V2 = Z''`0090''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` !Packed compression')m4_dnl m4_define(`fcb_param_CBF_BYTE_OFFSET', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_BYTE_OFFSET = Z''`0070''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` !Byte Offset Compression')m4_dnl m4_define(`fcb_param_CBF_PREDICTOR', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_PREDICTOR = Z''`0080''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` !Predictor_Huffman Compression')m4_dnl m4_define(`fcb_param_CBF_NONE', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_NONE = Z''`0040''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` !No compression flag')m4_dnl m4_define(`fcb_param_CBF_COMPRESSION_MASK', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_COMPRESSION_MASK = & Z''`00FF''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` !Mask to sep compressiontype from flags')m4_dnl m4_define(`fcb_param_CBF_FLAG_MASK', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_FLAG_MASK = Z''`0F00''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` !Mask to sep flags from compression type')m4_dnl m4_define(`fcb_param_CBF_UNCORRELATED_SECTIONS', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_UNCORRELATED_SECTIONS =& Z''`0100''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` !Flag for uncorrelated sections')m4_dnl m4_define(`fcb_param_CBF_FLAT_IMAGE', `m4_ifelse(fcb_not_first,`',``INTEGER,PARAMETER:: & '',``'')CBF_FLAT_IMAGE = Z''`0200''`m4_ifelse(fcb_is_last,`is_last',` ',``, &'')'` !Flag for flat (linear) images')m4_dnl m4_define(`fcb_param_CBF_LIST_ALL', m4_define(`fcb_is_last',`')m4_dnl ! ! Definitions of CBF compression parameters ! fcb_param_CBF_INTEGER m4_define(`fcb_not_first',`not_first')m4_dnl fcb_param_CBF_FLOAT fcb_param_CBF_CANONICAL fcb_param_CBF_PACKED fcb_param_CBF_PACKED_V2 fcb_param_CBF_BYTE_OFFSET fcb_param_CBF_PREDICTOR fcb_param_CBF_NONE fcb_param_CBF_COMPRESSION_MASK fcb_param_CBF_FLAG_MASK fcb_param_CBF_UNCORRELATED_SECTIONS m4_define(`fcb_is_last',`is_last')m4_dnl fcb_param_CBF_FLAT_IMAGE m4_define(`fcb_not_first',`')m4_dnl )m4_dnl m4_dnl m4_dnl fcblib function interfaces m4_dnl m4_define(`fcb_interface_FCB_ATOL_WCNT', `INTERFACE INTEGER(8) FUNCTION FCB_ATOL_WCNT(ARRAY,N,CNT) !----------------------------------------------------------------------- ! Converts bytes in ARRAY to an INTEGER(8), consuming CNT bytes !----------------------------------------------------------------------- INTEGER, INTENT(OUT):: CNT INTEGER, INTENT(IN):: N INTEGER(1),INTENT(IN):: ARRAY(N) END FUNCTION !----------------------------------------------------------------------- END INTERFACE')m4_dnl m4_dnl m4_define(`fcb_interface_FCB_CI_STRNCMPARR', `INTERFACE INTEGER FUNCTION FCB_CI_STRNCMPARR(STRING, ARRAY, N, LIMIT) !----------------------------------------------------------------------- ! Compares up to LIMIT characters of STRING and ARRAY case insensitive !----------------------------------------------------------------------- CHARACTER(LEN=*),INTENT(IN):: STRING INTEGER, INTENT(IN):: N,LIMIT INTEGER(1), INTENT(IN):: ARRAY(N) END FUNCTION !----------------------------------------------------------------------- END INTERFACE')m4_dnl m4_dnl m4_define(`fcb_interface_FCB_DECOMPRESS_PACKED_I2', `INTERFACE INTEGER FUNCTION FCB_DECOMPRESS_PACKED_I2 (ARRAY,NELEM,NELEM_READ, & ELSIGN, COMPRESSION, DIM1, DIM2, & TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) INTEGER(8), INTENT(IN):: DIM1,DIM2 INTEGER(2), INTENT(OUT):: ARRAY(DIM1,DIM2) INTEGER(8), INTENT(OUT):: NELEM_READ INTEGER(8), INTENT(IN):: NELEM INTEGER, INTENT(IN):: ELSIGN, COMPRESSION INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) END FUNCTION !----------------------------------------------------------------------- END INTERFACE')m4_dnl m4_dnl m4_define(`fcb_interface_FCB_DECOMPRESS_PACKED_I4', `INTERFACE INTEGER FUNCTION FCB_DECOMPRESS_PACKED_I4 (ARRAY,NELEM,NELEM_READ, & ELSIGN, COMPRESSION, DIM1, DIM2, & TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) INTEGER(8), INTENT(IN):: DIM1,DIM2 INTEGER(4), INTENT(OUT):: ARRAY(DIM1,DIM2) INTEGER(8), INTENT(OUT):: NELEM_READ INTEGER(8), INTENT(IN):: NELEM INTEGER, INTENT(IN):: ELSIGN, COMPRESSION INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) END FUNCTION !----------------------------------------------------------------------- END INTERFACE')m4_dnl m4_dnl m4_define(`fcb_interface_FCB_DECOMPRESS_PACKED_3D_I2', `INTERFACE INTEGER FUNCTION FCB_DECOMPRESS_PACKED_3D_I2 (ARRAY,NELEM,NELEM_READ, & ELSIGN, COMPRESSION, DIM1, DIM2, DIM3, & TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) INTEGER(8), INTENT(IN):: DIM1,DIM2,DIM3 INTEGER(2), INTENT(OUT):: ARRAY(DIM1,DIM2,DIM3) INTEGER(8), INTENT(OUT):: NELEM_READ INTEGER(8), INTENT(IN):: NELEM INTEGER, INTENT(IN):: ELSIGN, COMPRESSION INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) END FUNCTION !----------------------------------------------------------------------- END INTERFACE')m4_dnl m4_dnl m4_define(`fcb_interface_FCB_DECOMPRESS_PACKED_3D_I4', `INTERFACE INTEGER FUNCTION FCB_DECOMPRESS_PACKED_3D_I4 (ARRAY,NELEM,NELEM_READ, & ELSIGN, COMPRESSION, DIM1, DIM2, DIM3, & TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) INTEGER(8), INTENT(IN):: DIM1,DIM2,DIM3 INTEGER(4), INTENT(OUT):: ARRAY(DIM1,DIM2,DIM3) INTEGER(8), INTENT(OUT):: NELEM_READ INTEGER(8), INTENT(IN):: NELEM INTEGER, INTENT(IN):: ELSIGN, COMPRESSION INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) END FUNCTION !----------------------------------------------------------------------- END INTERFACE')m4_dnl m4_dnl m4_define(`fcb_interface_FCB_EXIT_BINARY', `INTERFACE INTEGER FUNCTION FCB_EXIT_BINARY(TAPIN,LAST_CHAR,FCB_BYTES_IN_REC,& BYTE_IN_FILE,REC_IN_FILE,BUFFER, & PADDING ) !----------------------------------------------------------------------- ! Skip to end of binary section that was just read !----------------------------------------------------------------------- INTEGER, INTENT(IN) :: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: BYTE_IN_FILE,REC_IN_FILE INTEGER(1),INTENT(INOUT):: LAST_CHAR,BUFFER(FCB_BYTES_IN_REC) INTEGER(8),INTENT(IN) :: PADDING END FUNCTION !----------------------------------------------------------------------- END INTERFACE')m4_dnl m4_dnl m4_define(`fcb_interface_FCB_NBLEN_ARRAY', `INTERFACE INTEGER FUNCTION FCB_NBLEN_ARRAY(ARRAY, ARRAYLEN) !----------------------------------------------------------------------- ! Returns the non-blank length of an array !----------------------------------------------------------------------- INTEGER, INTENT(IN):: ARRAYLEN INTEGER(1), INTENT(IN):: ARRAY(ARRAYLEN) END FUNCTION !----------------------------------------------------------------------- END INTERFACE')m4_dnl m4_dnl m4_define(`fcb_interface_FCB_NEXT_BINARY', `INTERFACE INTEGER FUNCTION FCB_NEXT_BINARY(TAPIN,LAST_CHAR,FCB_BYTES_IN_REC,& BYTE_IN_FILE,REC_IN_FILE,BUFFER, & ENCODING,SIZE,ID,DIGEST, & COMPRESSION,BITS,VORZEICHEN,REELL,& BYTEORDER,DIMOVER,DIM1,DIM2,DIM3, & PADDING ) !----------------------------------------------------------------------- ! Skip to the next binary and parse MIME header. !----------------------------------------------------------------------- INTEGER, INTENT(IN) :: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: BYTE_IN_FILE,REC_IN_FILE INTEGER(1),INTENT(INOUT):: LAST_CHAR,BUFFER(FCB_BYTES_IN_REC) INTEGER, INTENT(OUT) :: ENCODING,SIZE,ID,COMPRESSION,BITS, & VORZEICHEN,REELL CHARACTER(*), INTENT(OUT):: BYTEORDER,DIGEST INTEGER(8), INTENT(OUT):: DIMOVER INTEGER(8), INTENT(OUT):: DIM1 INTEGER(8), INTENT(OUT):: DIM2 INTEGER(8), INTENT(OUT):: DIM3 INTEGER(8), INTENT(OUT):: PADDING END FUNCTION !----------------------------------------------------------------------- END INTERFACE')m4_dnl m4_dnl m4_define(`fcb_interface_FCB_OPEN_CIFIN', `INTERFACE INTEGER FUNCTION FCB_OPEN_CIFIN(FILNAM,TAPIN,LAST_CHAR, & FCB_BYTES_IN_REC,BYTE_IN_FILE,REC_IN_FILE,BUFFER) !----------------------------------------------------------------------- ! -- Open CBF file named FILNAM and connect to unit number TAPIN !----------------------------------------------------------------------- ! We have chosen to use the direct access method to read the file ! with explicit buffer handling. This approach is general but ! clumpsy. Rather than putting the buffer and its control variables ! into COMMON these are passed as local arguments to make the routines ! inherently ''`threadsafe''` in a parallel programming environment. ! Note also, that a reading error could occur for the last record ! if it did not fill a full block. This could be avoided if the ! images were padded with a sufficient number of additional bytes ! (arbitrary values) after the end of the valid binary data. ! ! The more natural method would use byte stream I/O which is, ! unfortunately, only an extension of Fortran 90 that has been ! implemented in some compilers (like the Intel ifort) but ! not in all (like the SGI IRIX f90). ! For BSD style opens, there is a special variant on the direct ! access open with a recl of 1 to give byte-by-byte access. !----------------------------------------------------------------------- ! FILNAM - Name of the file countaining the image (GIVEN) ! TAPIN - Fortran device unit number assigned to image file (GIVEN) ! LAST_CHAR - ! Last character read (RESULT) ! FCB_BYTES_IN_REC - ! Number of bytes in a record (GIVEN) ! BYTE_IN_FILE - ! Byte (counting from 1) of the byte to read (RESULT) ! REC_IN_FILE - ! Record (counting from 1) of next record to read (RESULT) ! BUFFER - Array of length FCB_BYTES_IN_REC (GIVEN) !----------------------------------------------------------------------- IMPLICIT NONE CHARACTER(len=*),INTENT(IN) :: FILNAM INTEGER, INTENT(IN) :: TAPIN,FCB_BYTES_IN_REC INTEGER(1), INTENT(OUT):: LAST_CHAR INTEGER, INTENT(OUT):: BYTE_IN_FILE,REC_IN_FILE INTEGER(1), INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) END FUNCTION !----------------------------------------------------------------------- END INTERFACE')m4_dnl m4_dnl m4_define(`fcb_interface_FCB_READ_BITS', `INTERFACE INTEGER FUNCTION FCB_READ_BITS(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,BCOUNT,BBYTE, & BITCOUNT,IINT,LINT) !----------------------------------------------------------------------- ! Get integer value starting at BYTE_IN_FILE from file TAPIN ! continuing through BITCOUNT bits, with sign extension. ! (first byte is BYTE_IN_FILE=1) !----------------------------------------------------------------------- INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) INTEGER, INTENT(INOUT):: BCOUNT INTEGER(1),INTENT(INOUT):: BBYTE INTEGER, INTENT(IN):: BITCOUNT INTEGER, INTENT(IN):: LINT INTEGER(4), INTENT(OUT):: IINT(LINT) END FUNCTION !----------------------------------------------------------------------- END INTERFACE')m4_dnl m4_dnl m4_define(`fcb_interface_FCB_READ_BYTE', `INTERFACE INTEGER FUNCTION FCB_READ_BYTE(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,IBYTE) !----------------------------------------------------------------------- ! Get byte number BYTE_IN_FILE from file (first byte is BYTE_IN_FILE=1) !----------------------------------------------------------------------- INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) INTEGER(1), INTENT(OUT):: IBYTE END FUNCTION !----------------------------------------------------------------------- END INTERFACE')m4_dnl m4_dnl m4_define(`fcb_interface_FCB_READ_LINE', `INTERFACE INTEGER FUNCTION FCB_READ_LINE(TAPIN,LAST_CHAR,FCB_BYTES_IN_REC, & BYTE_IN_FILE,REC_IN_FILE,BUFFER,LINE,N,LINELEN) !----------------------------------------------------------------------- ! Reads successive bytes into byte array LINE(N), stopping at N, ! error or first CR(Z''`0D''`) or LF(Z''`0A''`), discarding a LF after a CR. !----------------------------------------------------------------------- INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC,N INTEGER, INTENT(INOUT):: BYTE_IN_FILE,REC_IN_FILE INTEGER, INTENT(OUT):: LINELEN INTEGER(1),INTENT(INOUT):: LAST_CHAR,BUFFER(FCB_BYTES_IN_REC) INTEGER(1), INTENT(OUT):: LINE(N) END FUNCTION !----------------------------------------------------------------------- END INTERFACE')m4_dnl m4_dnl m4_define(`fcb_interface_FCB_READ_IMAGE_I2', `INTERFACE INTEGER FUNCTION FCB_READ_IMAGE_I2(ARRAY,NELEM,NELEM_READ, & ELSIGN, COMPRESSION, DIM1, DIM2, PADDING, & TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) !----------------------------------------------------------------------- ! Reads a 16-bit integer twos complement 2D image ! ! compressed by a BYTE_OFFSET algorithm by W. Kabsch based ! on a proposal by A. Hammersley or ! compressed by a PACKED algorithm by J. P. Abrahams as ! used in CCP4, with modifications by P. Ellis and ! H. J. Bernstein. ! ! The BYTE-OFFSET algorithm is a slightly simplified version of ! that described in Andy Hammersley''`s web page ! (http://www.esrf.fr/computing/Forum/imgCIF/cbf_definition.html) ! !----------------------------------------------------------------------- ! ARRAY - Image (RESULT) ! NELEM - The number of elements to be read (GIVEN) ! NELEM_READ ! - The number of elements actually read (RESULT) ! ELSIGN - Flag for signed (1) OR unsigned (0) data (GIVEN) ! COMPRESSION ! - The actual compression of the image (RESULT) ! DIM1 - The fastest dimension of ARRAY (GIVEN) ! DIM2 - The slowest dimension (GIVEN) ! TAPIN - Fortran device unit number assigned to image file (GIVEN) ! FCB_BYTES_IN_REC ! - The number of bytes in each bufferload to read (GIVEN) ! BYTE_IN_FILE ! - The position in the file of the next byte to read (GIVEN, ! RESULT) ! REC_IN_FILE ! - The record number from 1 of the block in BUFFER (GIVEN, ! RESULT) ! BUFFER - Buffer of bytes read from the file (GIVEN, ! RESULT) ! PADDING - Pad bytes after the binary (RESULT) ! ! Returns (as function value) (RESULT) ! CBF_FORMAT (=1): ! cannot handle this CBF format (not implemented) ! 0: No error !----------------------------------------------------------------------- INTEGER(8), INTENT(IN):: DIM1,DIM2 INTEGER(2), INTENT(OUT):: ARRAY(DIM1,DIM2) INTEGER(8), INTENT(OUT):: NELEM_READ INTEGER(8), INTENT(IN):: NELEM INTEGER, INTENT(IN):: ELSIGN INTEGER, INTENT(OUT):: COMPRESSION INTEGER(8), INTENT(OUT):: PADDING INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) END FUNCTION !----------------------------------------------------------------------- END INTERFACE')m4_dnl m4_dnl m4_define(`fcb_interface_FCB_READ_IMAGE_I4', `INTERFACE INTEGER FUNCTION FCB_READ_IMAGE_I4(ARRAY,NELEM,NELEM_READ, & ELSIGN, COMPRESSION, DIM1, DIM2, PADDING, & TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) !----------------------------------------------------------------------- ! Reads a 32-bit integer twos complement 2D image ! ! compressed by a BYTE_OFFSET algorithm by W. Kabsch based ! on a proposal by A. Hammersley or ! compressed by a PACKED algorithm by J. P. Abrahams as ! used in CCP4, with modifications by P. Ellis and ! H. J. Bernstein. ! ! The BYTE-OFFSET algorithm is a slightly simplified version of ! that described in Andy Hammersley''`s web page ! (http://www.esrf.fr/computing/Forum/imgCIF/cbf_definition.html) ! !----------------------------------------------------------------------- ! ARRAY - Image (RESULT) ! NELEM - The number of elements to be read (GIVEN) ! NELEM_READ ! - The number of elements actually read (RESULT) ! ELSIGN - Flag for signed (1) OR unsigned (0) data (GIVEN) ! COMPRESSION ! - The actual compression of the image (RESULT) ! DIM1 - The fastest dimension of ARRAY (GIVEN) ! DIM2 - The slowest dimension (GIVEN) ! TAPIN - Fortran device unit number assigned to image file (GIVEN) ! FCB_BYTES_IN_REC ! - The number of bytes in each bufferload to read (GIVEN) ! BYTE_IN_FILE ! - The position in the file of the next byte to read (GIVEN, ! RESULT) ! REC_IN_FILE ! - The record number from 1 of the block in BUFFER (GIVEN, ! RESULT) ! BUFFER - Buffer of bytes read from the file (GIVEN, ! RESULT) ! PADDING - Pad bytes after the binary (RESULT) ! ! Returns (as function value) (RESULT) ! CBF_FORMAT (=1): ! cannot handle this CBF format (not implemented) ! 0: No error !----------------------------------------------------------------------- INTEGER(8), INTENT(IN):: DIM1,DIM2 INTEGER(4), INTENT(OUT):: ARRAY(DIM1,DIM2) INTEGER(8), INTENT(OUT):: NELEM_READ INTEGER(8), INTENT(IN):: NELEM INTEGER, INTENT(IN):: ELSIGN INTEGER, INTENT(OUT):: COMPRESSION INTEGER(8), INTENT(OUT):: PADDING INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) END FUNCTION !----------------------------------------------------------------------- END INTERFACE')m4_dnl m4_dnl m4_define(`fcb_interface_FCB_READ_IMAGE_3D_I2', `INTERFACE INTEGER FUNCTION FCB_READ_IMAGE_3D_I2(ARRAY,NELEM,NELEM_READ, & ELSIGN, COMPRESSION, DIM1, DIM2, DIM3, PADDING, & TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) !----------------------------------------------------------------------- ! Reads a 16-bit integer twos complement 3D image ! ! compressed by a BYTE_OFFSET algorithm by W. Kabsch based ! on a proposal by A. Hammersley or ! compressed by a PACKED algorithm by J. P. Abrahams as ! used in CCP4, with modifications by P. Ellis and ! H. J. Bernstein. ! ! The BYTE-OFFSET algorithm is a slightly simplified version of ! that described in Andy Hammersley''`s web page ! (http://www.esrf.fr/computing/Forum/imgCIF/cbf_definition.html) ! !----------------------------------------------------------------------- ! ARRAY - Image (RESULT) ! NELEM - The number of elements to be read (GIVEN) ! NELEM_READ ! - The number of elements actually read (RESULT) ! ELSIGN - Flag for signed (1) OR unsigned (0) data (GIVEN) ! COMPRESSION ! - The actual compression of the image (RESULT) ! DIM1 - The fastest dimension of ARRAY (GIVEN) ! DIM2 - The slowest dimension (GIVEN) ! TAPIN - Fortran device unit number assigned to image file (GIVEN) ! FCB_BYTES_IN_REC ! - The number of bytes in each bufferload to read (GIVEN) ! BYTE_IN_FILE ! - The position in the file of the next byte to read (GIVEN, ! RESULT) ! REC_IN_FILE ! - The record number from 1 of the block in BUFFER (GIVEN, ! RESULT) ! BUFFER - Buffer of bytes read from the file (GIVEN, ! RESULT) ! PADDING - Pad bytes after the binary (RESULT) ! ! Returns (as function value) (RESULT) ! CBF_FORMAT (=1): ! cannot handle this CBF format (not implemented) ! 0: No error !----------------------------------------------------------------------- INTEGER(8), INTENT(IN):: DIM1,DIM2,DIM3 INTEGER(2), INTENT(OUT):: ARRAY(DIM1,DIM2,DIM3) INTEGER(8), INTENT(OUT):: NELEM_READ INTEGER(8), INTENT(IN):: NELEM INTEGER, INTENT(IN):: ELSIGN INTEGER, INTENT(OUT):: COMPRESSION INTEGER(8), INTENT(OUT):: PADDING INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) END FUNCTION !----------------------------------------------------------------------- END INTERFACE')m4_dnl m4_dnl m4_define(`fcb_interface_FCB_READ_IMAGE_3D_I4', `INTERFACE INTEGER FUNCTION FCB_READ_IMAGE_3D_I4(ARRAY,NELEM,NELEM_READ, & ELSIGN, COMPRESSION, DIM1, DIM2, DIM3, PADDING, & TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) !----------------------------------------------------------------------- ! Reads a 32-bit integer twos complement 3D image ! ! compressed by a BYTE_OFFSET algorithm by W. Kabsch based ! on a proposal by A. Hammersley or ! compressed by a PACKED algorithm by J. P. Abrahams as ! used in CCP4, with modifications by P. Ellis and ! H. J. Bernstein. ! ! The BYTE-OFFSET algorithm is a slightly simplified version of ! that described in Andy Hammersley''`s web page ! (http://www.esrf.fr/computing/Forum/imgCIF/cbf_definition.html) ! !----------------------------------------------------------------------- ! ARRAY - Image (RESULT) ! NELEM - The number of elements to be read (GIVEN) ! NELEM_READ ! - The number of elements actually read (RESULT) ! ELSIGN - Flag for signed (1) OR unsigned (0) data (GIVEN) ! COMPRESSION ! - The actual compression of the image (RESULT) ! DIM1 - The fastest dimension of ARRAY (GIVEN) ! DIM2 - The slowest dimension (GIVEN) ! TAPIN - Fortran device unit number assigned to image file (GIVEN) ! FCB_BYTES_IN_REC ! - The number of bytes in each bufferload to read (GIVEN) ! BYTE_IN_FILE ! - The position in the file of the next byte to read (GIVEN, ! RESULT) ! REC_IN_FILE ! - The record number from 1 of the block in BUFFER (GIVEN, ! RESULT) ! BUFFER - Buffer of bytes read from the file (GIVEN, ! RESULT) ! PADDING - Pad bytes after the binary (RESULT) ! ! Returns (as function value) (RESULT) ! CBF_FORMAT (=1): ! cannot handle this CBF format (not implemented) ! 0: No error !----------------------------------------------------------------------- INTEGER(8), INTENT(IN):: DIM1,DIM2,DIM3 INTEGER(4), INTENT(OUT):: ARRAY(DIM1,DIM2,DIM3) INTEGER(8), INTENT(OUT):: NELEM_READ INTEGER(8), INTENT(IN):: NELEM INTEGER, INTENT(IN):: ELSIGN INTEGER, INTENT(OUT):: COMPRESSION INTEGER(8), INTENT(OUT):: PADDING INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) END FUNCTION !----------------------------------------------------------------------- END INTERFACE')m4_dnl m4_dnl m4_define(`fcb_interface_FCB_READ_INTEGER', `INTERFACE INTEGER FUNCTION FCB_READ_INTEGER(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,BCOUNT,BBYTE, & VALSIGN,BITCOUNT,IINT,LINT) !----------------------------------------------------------------------- ! Get integer value starting at BYTE_IN_FILE from file TAPIN ! continuing through BITCOUNT bits, with optional sign extension. ! (first byte is BYTE_IN_FILE=1) !----------------------------------------------------------------------- INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) INTEGER, INTENT(INOUT):: BCOUNT INTEGER(1),INTENT(INOUT):: BBYTE INTEGER, INTENT(IN):: VALSIGN,BITCOUNT INTEGER, INTENT(IN):: LINT INTEGER(4), INTENT(OUT):: IINT(LINT) END FUNCTION !----------------------------------------------------------------------- END INTERFACE')m4_dnl m4_dnl m4_define(`fcb_interface_FCB_READ_XDS_I2', `INTERFACE INTEGER FUNCTION FCB_READ_XDS_I2(FILNAM,TAPIN,NX,NY,IFRAME,JFRAME) !----------------------------------------------------------------------- ! Reads a 32 bit integer two''`s complement image compressed by a ! BYTE-OFFSET algorithm. W. Kabsch, Version 9-2006 ! ! REVISED 1-2007, H. J. Bernstein to conform to CBFlib_0.7.7 ! (http://www.bernstein-plus-sons.com/software/CBF) ! ! The BYTE-OFFSET algorithm is a slightly simplified version of ! that described in Andy Hammersley''`s web page ! (http://www.esrf.fr/computing/Forum/imgCIF/cbf_definition.html) ! !----------------------------------------------------------------------- ! FILNAM - Name of the file countaining the image (GIVEN) ! TAPIN - Fortran device unit number assigned to image file (GIVEN) ! NX - Number of "fast" pixels of the image (GIVEN) ! NY - Number of "slow" pixels of the image (GIVEN) ! IFRAME - 16 bit coded image as needed by XDS (RESULT) ! JFRAME - 32 bit scratch array (RESULT) ! Returns (as function value) (RESULT) ! 1: cannot handle this CBF format (not implemented) ! 0: No error ! -1: Cannot determine endian architecture of this machine ! -2: Cannot open image file ! -3: Wrong image format ! -4: Cannot read image !----------------------------------------------------------------------- IMPLICIT NONE CHARACTER(len=*),INTENT(IN) :: FILNAM INTEGER, INTENT(IN) :: TAPIN,NX,NY INTEGER(2), INTENT(OUT):: IFRAME(NX*NY) INTEGER(4), INTENT(OUT):: JFRAME(NX,NY) END FUNCTION !----------------------------------------------------------------------- END INTERFACE')m4_dnl m4_dnl m4_define(`fcb_interface_FCB_SKIP_WHITESPACE', `INTERFACE INTEGER FUNCTION FCB_SKIP_WHITESPACE(TAPIN,LAST_CHAR, & FCB_BYTES_IN_REC,BYTE_IN_FILE,REC_IN_FILE,BUFFER,& LINE,N,LINELEN,ICUR,FRESH_LINE) !----------------------------------------------------------------------- ! Skips forward on the current LINE of size N with data in ! LINE(1:LINELEN) from the current position ICUR moving over ! whitespace and comments, reading new lines into LINE if ! needed. The flag FRESH_LINE indicates that a fresh line ! should be read on entry. !----------------------------------------------------------------------- INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC,N INTEGER, INTENT(INOUT):: BYTE_IN_FILE,REC_IN_FILE,LINELEN,ICUR, & FRESH_LINE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC),LINE(N), & LAST_CHAR END FUNCTION !----------------------------------------------------------------------- END INTERFACE')m4_dnl m4_dnl m4_define(`fcb_interface_FCB_UPDATE_JPA_POINTERS_I2', `INTERFACE INTEGER FUNCTION FCB_UPDATE_JPA_POINTERS_I2(TRAIL_INDEX_ARRAY,& NDIM1, NDIM2, ARRAY, DIM1, DIM2, AVERAGE, COMPRESSION) INTEGER(8),INTENT(INOUT):: TRAIL_INDEX_ARRAY(4), NDIM1, NDIM2 INTEGER(8), INTENT(IN):: DIM1,DIM2 INTEGER(2), INTENT(IN):: ARRAY(DIM1,DIM2) INTEGER(4), INTENT(OUT):: AVERAGE INTEGER, INTENT(IN):: COMPRESSION END FUNCTION !----------------------------------------------------------------------- END INTERFACE')m4_dnl m4_dnl m4_define(`fcb_interface_FCB_UPDATE_JPA_POINTERS_I4', `INTERFACE INTEGER FUNCTION FCB_UPDATE_JPA_POINTERS_I4(TRAIL_INDEX_ARRAY,& NDIM1, NDIM2, ARRAY, DIM1, DIM2, AVERAGE, COMPRESSION) INTEGER(8),INTENT(INOUT):: TRAIL_INDEX_ARRAY(4), NDIM1, NDIM2 INTEGER(8), INTENT(IN):: DIM1,DIM2 INTEGER(4), INTENT(IN):: ARRAY(DIM1,DIM2) INTEGER(4), INTENT(OUT):: AVERAGE INTEGER, INTENT(IN):: COMPRESSION END FUNCTION !----------------------------------------------------------------------- END INTERFACE')m4_dnl m4_dnl m4_define(`fcb_interface_FCB_UPDATE_JPA_POINTERS_3D_I2', `INTERFACE INTEGER FUNCTION FCB_UPDATE_JPA_POINTERS_3D_I2(TRAIL_INDEX_ARRAY,& NDIM1, NDIM2, NDIM3, ARRAY, DIM1, DIM2, DIM3, AVERAGE, COMPRESSION) INTEGER(8),INTENT(INOUT):: TRAIL_INDEX_ARRAY(8), NDIM1, NDIM2, NDIM3 INTEGER(8), INTENT(IN):: DIM1,DIM2,DIM3 INTEGER(2), INTENT(IN):: ARRAY(DIM1,DIM2,DIM3) INTEGER(4), INTENT(OUT):: AVERAGE INTEGER, INTENT(IN):: COMPRESSION END FUNCTION !----------------------------------------------------------------------- END INTERFACE')m4_dnl m4_dnl m4_define(`fcb_interface_FCB_UPDATE_JPA_POINTERS_3D_I4', `INTERFACE INTEGER FUNCTION FCB_UPDATE_JPA_POINTERS_3D_I4(TRAIL_INDEX_ARRAY,& NDIM1, NDIM2, NDIM3, ARRAY, DIM1, DIM2, DIM3, AVERAGE, COMPRESSION) IMPLICIT NONE INTEGER(8),INTENT(INOUT):: TRAIL_INDEX_ARRAY(8), NDIM1, NDIM2, NDIM3 INTEGER(8), INTENT(IN):: DIM1,DIM2,DIM3 INTEGER(4), INTENT(IN):: ARRAY(DIM1,DIM2,DIM3) INTEGER(4), INTENT(OUT):: AVERAGE INTEGER, INTENT(IN):: COMPRESSION END FUNCTION !----------------------------------------------------------------------- END INTERFACE')m4_dnl m4_dnl m4_dnl macro version of cbf file open to be used both in the library m4_dnl and in applications that wish to avoid the long argument list m4_dnl m4_dnl The macro should be called with 3 arguments m4_dnl $1 should give any additional parameters to OPEN m4_dnl such as ERR=120 or IOSTAT=IOS m4_dnl $2 should give any additional parameters for the m4_dnl first read such as ERR=140 or IOSTAT=IOS m4_dnl $3 should give any the action to take if the file m4_dnl does not begin with "###CBF: " m4_define(`fcb_macro_FCB_OPEN_CIFIN', ``!----------------------------------------------------------------------- ! -- Open CBF file named FILNAM and connect to unit number TAPIN !----------------------------------------------------------------------- ! We have chosen to use the direct access method to read the file ! with explicit buffer handling. This approach is general but ! clumpsy. Rather than putting the buffer and its control variables ! into COMMON these are passed as local arguments to make the routines ! inherently '''``threadsafe'''`` in a parallel programming environment. ! Note also, that a reading error could occur for the last record ! if it did not fill a full block. This could be avoided if the ! images were padded with a sufficient number of additional bytes ! (arbitrary values) after the end of the valid binary data. ! ! The more natural method would use byte stream I/O which is, ! unfortunately, only an extension of Fortran 90 that has been ! implemented in some compilers (like the Intel ifort) but ! not in all (like the SGI IRIX f90). ! For BSD style opens, there is a special variant on the direct ! access open with a recl of 1 to give byte-by-byte access. !----------------------------------------------------------------------- INQUIRE(IOLENGTH=FCB_RECORD_SIZE)BUFFER OPEN(UNIT=TAPIN,FILE=TRIM(FILNAM),STATUS='''``OLD'''``,ACTION='''``READ'''``, & ACCESS='''``DIRECT'''``,FORM='''``UNFORMATTED'''``,RECL=FCB_RECORD_SIZE, & $1) ! *** DEBUG *** PRINT *, "RECL: ", FCB_RECORD_SIZE DO BYTE_IN_FILE = 1, FCB_BYTES_IN_REC BUFFER(BYTE_IN_FILE) = 0 END DO READ(TAPIN,REC=1,$2)BUFFER !Read the first record' m4_ifelse($3,`',`',` IF (FCB_CI_STRNCMPARR("###CBF: ",BUFFER,FCB_BYTES_IN_REC,8).NE.0) & '$3` !Check for presence of the CBF-format keyword')` REC_IN_FILE=1 BYTE_IN_FILE=0 LAST_CHAR=0 '')m4_dnl m4_define(`fcb_interface_LIST_ALL',` ! ! Definitions of fcblib interfaces ! fcb_interface_FCB_ATOL_WCNT fcb_interface_FCB_CI_STRNCMPARR fcb_interface_FCB_DECOMPRESS_PACKED_I2 fcb_interface_FCB_DECOMPRESS_PACKED_I4 fcb_interface_FCB_DECOMPRESS_PACKED_3D_I2 fcb_interface_FCB_DECOMPRESS_PACKED_3D_I4 fcb_interface_FCB_EXIT_BINARY fcb_interface_FCB_NBLEN_ARRAY fcb_interface_FCB_NEXT_BINARY fcb_interface_FCB_OPEN_CIFIN fcb_interface_FCB_READ_BITS fcb_interface_FCB_READ_BYTE fcb_interface_FCB_READ_INTEGER fcb_interface_FCB_READ_LINE fcb_interface_FCB_READ_XDS_I2 fcb_interface_FCB_SKIP_WHITESPACE fcb_interface_FCB_UPDATE_JPA_POINTERS_I2 fcb_interface_FCB_UPDATE_JPA_POINTERS_I4 fcb_interface_FCB_UPDATE_JPA_POINTERS_3D_I2 fcb_interface_FCB_UPDATE_JPA_POINTERS_3D_I4 ')./CBFlib-0.9.2.2/m4/fcb_read_image.m40000644000076500007650000002633211603702103015252 0ustar yayayayam4_dnl fcb_read_image.m4 -- m4 macro file to generate I2, I4, m4_dnl and 3D_I2 and 3D_I4 versions m4_dnl of FCB_READ_IMAGE m4_include(`fcblib_defines.m4') m4_define(`fcb_macro_FCB_READ_IMAGE', `! FCB_READ_IMAGE_$1.F90 ! ! Derived from f90 test code by W. Kabsch ! H. J. Bernstein, 24 March 2007 ! ! Reads the next binary image from a CIF files that ! has already been opened. Leaves the file open and ! positioned just after the binary and still within ! the text field ! ! This version is for ! ! m4_ifelse($1,`I2',`2-D INTEGER*2 arrays', $1,`I4',`2-D INTEGER*4 arrays', $1,`3D_I2',`3-D INTEGER*2 arrays', $1,`3D_I4',`3-D INTEGER*4 arrays',`2-D INTEGER*2 arrays') m4_define(`fcb_3d_flag',`2D')m4_dnl m4_ifelse($1,`3D_I2',`m4_define(`fcb_3d_flag',`3D')', $1,`3D_I4',`m4_define(`fcb_3d_flag',`3D')')m4_dnl ! ! with function ! ! FCB_READ_IMAGE_$1 INTEGER FUNCTION FCB_READ_IMAGE_$1(ARRAY,NELEM,NELEM_READ, & ELSIGN, COMPRESSION, DIM1, DIM2, m4_ifelse(fcb_3d_flag,`3D', `DIM3, ') & PADDING,TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) !----------------------------------------------------------------------- m4_ifelse($1,`I2', `! Reads a 16-bit integer twos complement 2D image', $1,`I4', `! Reads a 32-bit integer twos complement 2D image', $1,`3D_I2', `! Reads a 16-bit integer twos complement 3D image', $1,`3D_I4', `! Reads a 32-bit integer twos complement 3D image') ! ! compressed by a BYTE_OFFSET algorithm by W. Kabsch based ! on a proposal by A. Hammersley or ! compressed by a PACKED algorithm by J. P. Abrahams as ! used in CCP4, with modifications by P. Ellis and ! H. J. Bernstein. ! ! The BYTE-OFFSET algorithm is a slightly simplified version of ! that described in Andy Hammersley''`s web page ! (http://www.esrf.fr/computing/Forum/imgCIF/cbf_definition.html) ! !----------------------------------------------------------------------- ! ARRAY - Image (RESULT) ! NELEM - The number of elements to be read (GIVEN) ! NELEM_READ ! - The number of elements actually read (RESULT) ! ELSIGN - Flag for signed (1) OR unsigned (0) data (GIVEN) ! COMPRESSION ! - The actual compression of the image (RESULT) ! DIM1 - The fastest dimension of ARRAY (GIVEN) m4_ifelse(`fcb_3d_flag',`3D', `! DIM2 - The next slower dimension (GIVEN) ! DIM3 - The slowest dimension (GIVEN)', `! DIM2 - The slowest dimension (GIVEN)') ! TAPIN - Fortran device unit number assigned to image file (GIVEN) ! FCB_BYTES_IN_REC ! - The number of bytes in each bufferload to read (GIVEN) ! BYTE_IN_FILE ! - The position in the file of the next byte to read (GIVEN, ! RESULT) ! REC_IN_FILE ! - The record number from 1 of the block in BUFFER (GIVEN, ! RESULT) ! BUFFER - Buffer of bytes read from the file (GIVEN, ! RESULT) ! PADDING - Pad bytes after the binary (RESULT) ! ! Returns (as function value) (RESULT) ! CBF_FORMAT (=1): ! cannot handle this CBF format (not implemented) ! 0: No error !----------------------------------------------------------------------- IMPLICIT NONE INTEGER(8), INTENT(IN):: DIM1,DIM2`'m4_ifelse(fcb_3d_flag,`3D', `,DIM3') INTEGER(m4_ifelse($1,`I2',2,$1,`3D_I2',2,4)), INTENT(OUT):: ARRAY(DIM1,DIM2`'m4_ifelse(fcb_3d_flag,`3D', `,DIM3')) INTEGER(8), INTENT(OUT):: NELEM_READ INTEGER(8), INTENT(IN):: NELEM INTEGER, INTENT(IN):: ELSIGN INTEGER, INTENT(OUT):: COMPRESSION INTEGER(8), INTENT(OUT):: PADDING INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) ! -- Definition of CBF_FORMAT fcb_errcode_CBF_FORMAT ! -- External functions called fcb_interface_FCB_READ_BYTE fcb_interface_FCB_NEXT_BINARY fcb_interface_FCB_CI_STRNCMPARR fcb_interface_FCB_DECOMPRESS_PACKED_$1 ! -- Local variables INTEGER STEP,FIRST2,LAST2,FIRST4,LAST4,II,I,J`'m4_ifelse(fcb_3d_flag, `3D',`,K') INTEGER(4) DIFF,PIXVALUE,MARKER,IADR INTEGER(2) SHORTINT INTEGER(1) LAST_CHAR,ONEBYTE, & TWOBYTES(2),FOURBYTES(4),ENDIANORDER(4), & MARKBYTES(4) INTEGER ENCODING fcb_param_ENC_LIST_ALL INTEGER SIZE INTEGER ID fcb_param_CBF_LIST_ALL INTEGER BITS,VORZEICHEN,REELL CHARACTER(len=24) DIGEST CHARACTER(len=14) BYTEORDER !Possible parameter values for BYTEORDER are: !"LITTLE_ENDIAN" supported !"BIG_ENDIAN" not supported INTEGER(8) DIMOVER INTEGER(8) LDIM1 !Number of "fast" pixels of the image INTEGER(8) LDIM2 !Number of "slow" pixels of the image INTEGER(8) LDIM3 INTEGER(4) PREV_ELEMENT DATA ENDIANORDER/Z''`12''`,Z''`34''`,Z''`56''`,Z''`78''`/ DATA MARKBYTES/Z''`0C''`,Z''`1A''`,Z''`04''`,Z''`D5''`/ !----------------------------------------------------------------------- ! -- Determine endian architecture of this machine !----------------------------------------------------------------------- ! Definition: If the lowest memory address of multi-byte data is ! considered the starting address of the data, the least ! significant byte (LSB) is at the lowest memory address ! for a ''`little_endian''` cpu architecture. ! ! Example: The 32 bit hex value Z''`12345678''` is stored as follows: ! ENDIAN ORDER BYTE0 BYTE1 BYTE2 BYTE3 ! Big Endian 12 34 56 78(LSB) ! Little Endian 78(LSB) 56 34 12 !----------------------------------------------------------------------- PIXVALUE=TRANSFER(ENDIANORDER,PIXVALUE) STEP=0 IF (PIXVALUE .EQ. Z''`78563412''`) THEN !Little Endian machine STEP=1 FIRST2=1;LAST2=2 FIRST4=1;LAST4=4 ENDIF IF (PIXVALUE .EQ. Z''`12345678''`) THEN ! Big Endian machine STEP=-1 FIRST2=2;LAST2=1 FIRST4=4;LAST4=1 ENDIF IF (STEP.EQ.0)GO TO 110 !----------------------------------------------------------------------- ! -- Skip to the next binary and parse the MIME header !----------------------------------------------------------------------- IF (FCB_NEXT_BINARY(TAPIN,LAST_CHAR,FCB_BYTES_IN_REC,BYTE_IN_FILE,& REC_IN_FILE,BUFFER,ENCODING,SIZE,ID,DIGEST,COMPRESSION,BITS, & VORZEICHEN,REELL,BYTEORDER,DIMOVER,LDIM1,LDIM2,LDIM3,PADDING).NE.0) & GO TO 130 IF ((DIM1.NE.LDIM1).OR.(DIM2.NE.LDIM2)`'m4_ifelse(`fcb_3d_flag', `3D',`.OR.(DIM3.NE.LDIM3)'))GO TO 130 !----------------------------------------------------------------------- ! -- Advance to start of binary image data !----------------------------------------------------------------------- ! In CBF the binary data begins immediately after the first occurence ! of the following 4 bytes (MARKBYTES) in the image file ! Octet Hex Decimal Purpose ! 1 0C 12 (ctrl-L) End the current page ! 2 1A 26 (ctrl-Z) Stop listings in MS-DOS ! 3 04 04 (Ctrl-D) Stop listings in UNIX ! 4 D5 213 Binary section begins ! 5..5+n-1 Binary data (n octets) !----------------------------------------------------------------------- MARKER=TRANSFER(MARKBYTES,MARKER) FOURBYTES=0 DO DO I=1,3 FOURBYTES(I)=FOURBYTES(I+1) ENDDO BYTE_IN_FILE=BYTE_IN_FILE+1 IF (FCB_READ_BYTE(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,FOURBYTES(4)).NE.0) GO TO 140 PIXVALUE=TRANSFER(FOURBYTES,PIXVALUE) IF (PIXVALUE.EQ.MARKER)EXIT ENDDO ! *** DEBUG *** PRINT *, "fwa-1 address of IMAGE at: " ! *** DEBUG *** PRINT *, "BYTE_IN_FILE: ", BYTE_IN_FILE ! *** DEBUG *** PRINT *, "REC_IN_FILE: ", REC_IN_FILE !----------------------------------------------------------------------- ! -- Read data image of 32 bit two''`s complement integers, compressed ! -- by the BYTE-OFFSET algorithm. ! -- After the expansion the original pixel values are coded by 16 bit ! -- in a special way suitable for XDS (see INTEGER*2 FUNCTION CNT2PIX). !----------------------------------------------------------------------- FCB_READ_IMAGE_$1=CBF_FORMAT !Cannot handle this CBF format IF ((BYTEORDER.EQ."LITTLE_ENDIAN").AND.(ENCODING.EQ.ENC_NONE).AND.& (IAND(COMPRESSION,CBF_COMPRESSION_MASK).EQ.CBF_BYTE_OFFSET))THEN PIXVALUE=0 NELEM_READ=0 m4_ifelse(fcb_3d_flag, `3D',`DO K = 1, DIM3') DO J = 1, DIM2 DO I = 1, DIM1 BYTE_IN_FILE=BYTE_IN_FILE+1 IF (FCB_READ_BYTE(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,ONEBYTE).NE.0) GO TO 140 DIFF=ONEBYTE IF (DIFF.EQ.-128)THEN DO II=FIRST2,LAST2,STEP BYTE_IN_FILE=BYTE_IN_FILE+1 IF (FCB_READ_BYTE(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,TWOBYTES(II)).NE.0)GO TO 140 ENDDO SHORTINT=TRANSFER(TWOBYTES,SHORTINT) DIFF=SHORTINT IF (DIFF.EQ.-32768)THEN DO II=FIRST4,LAST4,STEP BYTE_IN_FILE=BYTE_IN_FILE+1 IF (FCB_READ_BYTE(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,FOURBYTES(II)).NE.0) & GO TO 140 ENDDO DIFF=TRANSFER(FOURBYTES,DIFF) ENDIF ENDIF PIXVALUE=PIXVALUE+DIFF ARRAY(I,J`'m4_ifelse(fcb_3d_flag,`3D',`,K')) = PIXVALUE NELEM_READ=NELEM_READ+1 ENDDO ENDDO`'m4_ifelse(fcb_3d_flag,`3D',` ENDDO') FCB_READ_IMAGE_$1=0 !No error ELSE IF ((BYTEORDER.EQ."LITTLE_ENDIAN").AND.(ENCODING.EQ.ENC_NONE).AND. & ((IAND(COMPRESSION,CBF_COMPRESSION_MASK).EQ.CBF_PACKED) .OR. & (IAND(COMPRESSION,CBF_COMPRESSION_MASK).EQ.CBF_PACKED_V2)))THEN FCB_READ_IMAGE_$1=FCB_DECOMPRESS_PACKED_$1 (ARRAY,NELEM,NELEM_READ, & VORZEICHEN, COMPRESSION, DIM1, DIM2,`'m4_ifelse(fcb_3d_flag,`3D',`DIM3,') & TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) IF (NELEM_READ.NE.NELEM) PRINT *, "EARLY TERMINATION AT ",NELEM_READ PREV_ELEMENT = 0 END IF END IF !----------------------------------------------------------------------- 100 RETURN 110 FCB_READ_IMAGE_$1=-1 !Cannot determine endian architecture of this machine RETURN 130 FCB_READ_IMAGE_$1=-3 !Wrong image format GO TO 100 140 FCB_READ_IMAGE_$1=-4 !Cannot read image GO TO 100 END FUNCTION FCB_READ_IMAGE_$1') fcb_macro_FCB_READ_IMAGE(`I2') fcb_macro_FCB_READ_IMAGE(`I4') fcb_macro_FCB_READ_IMAGE(`3D_I2') fcb_macro_FCB_READ_IMAGE(`3D_I4') ./CBFlib-0.9.2.2/m4/test_fcb_read_image.m40000644000076500007650000001510111603702103016301 0ustar yayayayam4_include(`fcblib_defines.m4')` PROGRAM TEST IMPLICIT NONE CHARACTER(LEN=100) LINE INTEGER(2) IFRAME(1000,1000), DPREV INTEGER(4) JFRAME(1000,1000) INTEGER(4) KFRAME(50,60,70) INTEGER,PARAMETER:: FCB_BYTES_IN_REC='m4_ifelse(`fcb_bytes_in_rec',`',4096,`fcb_bytes_in_rec')` INTEGER IER, I, J, K, TAPIN, SIZE INTEGER BYTE_IN_FILE, REC_IN_FILE, DTARG, ID INTEGER(1) LAST_CHAR, BUFFER(FCB_BYTES_IN_REC) INTEGER COMPRESSION, BITS, VORZEICHEN, REELL, ENCODING INTEGER(8) DIM1, DIM2, DIM3, DIMOVER, PADDING INTEGER(8) NELEM, NELEM_READ CHARACTER(len=24) DIGEST CHARACTER(len=14) BYTEORDER ' fcb_interface_FCB_EXIT_BINARY fcb_interface_FCB_OPEN_CIFIN fcb_interface_FCB_NEXT_BINARY fcb_interface_FCB_READ_IMAGE_I2 fcb_interface_FCB_READ_IMAGE_I4 fcb_interface_FCB_READ_IMAGE_3D_I2 fcb_interface_FCB_READ_IMAGE_3D_I4 TAPIN=9 ` PRINT *,''` NAME OF TEST CBF ''` READ *, LINE IER = FCB_OPEN_CIFIN(LINE,TAPIN,LAST_CHAR, & FCB_BYTES_IN_REC,BYTE_IN_FILE,REC_IN_FILE,BUFFER) IF (IER.NE.0) THEN PRINT *,"FILE OPEN ERROR: ", IER STOP END IF ! Read an array 1000 x 1000 INTEGER(4) in a flat field of 1000 PRINT *, " 1000 x 1000 I4 TEST " NELEM = 1000*1000 DIM1 = 1000 DIM2 = 1000 IER = FCB_READ_IMAGE_I4(JFRAME,NELEM,NELEM_READ, & 1, COMPRESSION, DIM1, DIM2, PADDING, & TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) IF (IER.NE.0) THEN PRINT *," FCB_READ_IMAGE_I4 ERROR: ", IER STOP ELSE DPREV = 0 DO J = 1,1000 DO I = 1,1000 DTARG = 1000 IF (JFRAME(I,J).NE.DTARG) THEN PRINT *, "IFRAME(",I,",",J,") = ", & JFRAME(I,J), ", SHOULD BE ",DTARG END IF END DO END DO END IF IER = FCB_EXIT_BINARY(TAPIN,LAST_CHAR,FCB_BYTES_IN_REC,& BYTE_IN_FILE,REC_IN_FILE,BUFFER, PADDING ) IF (IER.NE.0) THEN PRINT *," FCB_EXIT_BINARY ERROR: ", IER STOP END IF ! Read an array 1000 x 1000 INTEGER(2) in a flat field of 1000 PRINT *, " 1000 x 1000 I2 TEST " IER = FCB_READ_IMAGE_I2(IFRAME,NELEM,NELEM_READ, & 1, COMPRESSION, DIM1, DIM2, PADDING, & TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) IF (IER.NE.0) THEN PRINT *," FCB_READ_IMAGE_I2 ERROR: ", IER STOP ELSE DPREV = 0 DO J = 1,1000 DO I = 1,1000 DTARG = 1000 IF (IFRAME(I,J).NE.DTARG) THEN PRINT *, "IFRAME(",I,",",J,") = ", & IFRAME(I,J), ", SHOULD BE ",DTARG END IF END DO END DO END IF IER = FCB_EXIT_BINARY(TAPIN,LAST_CHAR,FCB_BYTES_IN_REC,& BYTE_IN_FILE,REC_IN_FILE,BUFFER, PADDING ) IF (IER.NE.0) THEN PRINT *," FCB_EXIT_BINARY ERROR: ", IER STOP END IF ! Read an array 1000 x 1000 INTEGER(4) in a flat field of 1000 ! except for -3 along the main diagonal and its transpose PRINT *, " 1000 x 1000 I4 TEST, WITH -3 on diag and transpose " IER = FCB_READ_IMAGE_I4(JFRAME,NELEM,NELEM_READ, & 1, COMPRESSION, DIM1, DIM2, PADDING, & TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) IF (IER.NE.0) THEN PRINT *," FCB_READ_IMAGE_I4 ERROR: ", IER STOP ELSE DPREV = 0 DO J = 1,1000 DO I = 1,1000 DTARG = 1000 IF (I .EQ. J .OR. 1001-I .EQ. J) THEN DTARG = -3 END IF IF (JFRAME(I,J).NE.DTARG) THEN PRINT *, "IFRAME(",I,",",J,") = ", & JFRAME(I,J), ", SHOULD BE ",DTARG END IF END DO END DO END IF IER = FCB_EXIT_BINARY(TAPIN,LAST_CHAR,FCB_BYTES_IN_REC,& BYTE_IN_FILE,REC_IN_FILE,BUFFER, PADDING ) IF (IER.NE.0) THEN PRINT *," FCB_EXIT_BINARY ERROR: ", IER STOP END IF ! Read an array 1000 x 1000 INTEGER(2) in a flat field of 1000 ! except for -3 along the main diagonal and its transpose PRINT *, " 1000 x 1000 I2 TEST, WITH -3 on diag and transpose " IER = FCB_READ_IMAGE_I2(IFRAME,NELEM,NELEM_READ, & 1, COMPRESSION, DIM1, DIM2, PADDING, & TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) IF (IER.NE.0) THEN PRINT *," FCB_READ_IMAGE_I2 ERROR: ", IER STOP ELSE DPREV = 0 DO J = 1,1000 DO I = 1,1000 DTARG = 1000 IF (I .EQ. J .OR. 1001-I .EQ. J) THEN DTARG = -3 END IF IF (IFRAME(I,J).NE.DTARG) THEN PRINT *, "IFRAME(",I,",",J,") = ", & IFRAME(I,J), ", SHOULD BE ",DTARG END IF END DO END DO END IF IER = FCB_EXIT_BINARY(TAPIN,LAST_CHAR,FCB_BYTES_IN_REC,& BYTE_IN_FILE,REC_IN_FILE,BUFFER, PADDING ) IF (IER.NE.0) THEN PRINT *," FCB_EXIT_BINARY ERROR: ", IER STOP END IF ! Read an array 50 x 60 x 70 INTEGER(4) in a flat field of 1000, ! except for -3 along the main diagonal and the values i+j+k-3 ! every 1000th pixel PRINT *, " 50 x 60 x 70 3D_I4 TEST " DIM1 = 50 DIM2 = 60 DIM3 = 70 NELEM = DIM1*DIM2*DIM3 IER = FCB_READ_IMAGE_3D_I4(KFRAME,NELEM,NELEM_READ, & 1, COMPRESSION, DIM1, DIM2, DIM3, PADDING, & TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) IF (IER.NE.0) THEN PRINT *," FCB_READ_IMAGE_3D_I4 ERROR: ", IER STOP ELSE DPREV = 0 DO K = 1,70 DO J = 1,60 DO I = 1,50 DTARG = 1000 IF (I .EQ. J .OR. J .EQ. K) THEN DTARG = -3 END IF IF (MOD(I-1+(J-1)*50+(K-1)*50*60,1000).EQ.0) THEN DTARG = I+J+K-3 END IF IF (KFRAME(I,J,K).NE.DTARG) THEN PRINT *, "KFRAME(",I,",",J,",",K,") = ", & KFRAME(I,J,K), ", SHOULD BE ",DTARG END IF END DO END DO END DO END IF PRINT *, "TESTS COMPLETED" STOP END './CBFlib-0.9.2.2/m4/fcb_read_bits.m40000644000076500007650000001334511603702103015131 0ustar yayayayam4_include(`fcblib_defines.m4')m4_dnl ` INTEGER FUNCTION FCB_READ_BITS(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,BCOUNT,BBYTE, & BITCOUNT,IINT,LINT) !----------------------------------------------------------------------- ! Get integer value starting at BYTE_IN_FILE from file TAPIN ! continuing through BITCOUNT bits, with sign extension. ! (first byte is BYTE_IN_FILE=1) !----------------------------------------------------------------------- IMPLICIT NONE INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) INTEGER, INTENT(INOUT):: BCOUNT INTEGER(1),INTENT(INOUT):: BBYTE INTEGER, INTENT(IN):: BITCOUNT INTEGER, INTENT(IN):: LINT INTEGER(4), INTENT(OUT):: IINT(LINT) INTEGER I,J,LBITCOUNT,COUNT,KINTS INTEGER(8) BITCODE,TBITCODE, M, MASK8 !----------------------------------------------------------------------- INTEGER MAXBITS, NUMINTS ' fcb_interface_FCB_READ_BYTE ` MAXBITS = 32 NUMINTS = (BITCOUNT+MAXBITS-1)/MAXBITS MASK8 = Z''`000000FF''` DO KINTS = 1,NUMINTS LBITCOUNT = MAXBITS IF (KINTS.EQ.NUMINTS) LBITCOUNT = BITCOUNT-(NUMINTS-1)*32 COUNT = BCOUNT BITCODE = BBYTE BITCODE = IAND(BITCODE,MASK8) DO IF (COUNT .GE. LBITCOUNT) EXIT BYTE_IN_FILE=BYTE_IN_FILE+1 FCB_READ_BITS = & FCB_READ_BYTE(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,BBYTE) IF (FCB_READ_BITS.NE.0) RETURN BCOUNT=8 TBITCODE = BBYTE TBITCODE = IAND(TBITCODE,MASK8) CALL MVBITS(TBITCODE,0,MIN(8,32-COUNT),BITCODE,COUNT) COUNT = COUNT+8 END DO ! SIGN EXTEND IF (LBITCOUNT .LT. MAXBITS) THEN M = 1 M = ISHFT(M,LBITCOUNT-1) IF (IAND(BITCODE,M).NE.0) THEN IINT(KINTS) = IOR(BITCODE,-M) ELSE IINT(KINTS) = IAND(BITCODE,NOT(-M)) ENDIF ELSE IINT(KINTS) = BITCODE ENDIF ! SAVE THE REMAINING BITS FOR NEXT TIME TBITCODE = BBYTE TBITCODE = ISHFT(IAND(TBITCODE,MASK8),-(BCOUNT-(COUNT-LBITCOUNT)) ) BBYTE = TBITCODE BCOUNT = COUNT-LBITCOUNT END DO FCB_READ_BITS = 0 RETURN END FUNCTION FCB_READ_BITS INTEGER FUNCTION FCB_READ_INTEGER(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,BCOUNT,BBYTE, & VALSIGN,BITCOUNT,IINT,LINT) !----------------------------------------------------------------------- ! Get integer value starting at BYTE_IN_FILE from file TAPIN ! continuing through BITCOUNT bits, with optional sign extension. ! (first byte is BYTE_IN_FILE=1) !----------------------------------------------------------------------- IMPLICIT NONE INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) INTEGER, INTENT(INOUT):: BCOUNT INTEGER(1),INTENT(INOUT):: BBYTE INTEGER, INTENT(IN):: VALSIGN,BITCOUNT INTEGER, INTENT(IN):: LINT INTEGER(4), INTENT(OUT):: IINT(LINT) INTEGER SIGNBITS, VALBITS, NUMINTS, FRI INTEGER I,J,LBITCOUNT,COUNT INTEGER(4) TVAL(4), BITCODE,TBITCODE, M INTEGER(4) XSIGN(1) ' fcb_errcode_CBF_OVERFLOW fcb_interface_FCB_READ_BITS ` !----------------------------------------------------------------------- IF (BITCOUNT .LE. 0) THEN IINT(1) = 0 FCB_READ_INTEGER = 0 RETURN END IF SIGNBITS = BITCOUNT-32 IF (SIGNBITS .GT. 0) THEN VALBITS = BITCOUNT-SIGNBITS ELSE VALBITS = BITCOUNT END IF ! READ THE VALUE FRI = & FCB_READ_BITS(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,BCOUNT,BBYTE, & VALBITS,IINT,LINT) FCB_READ_INTEGER = FRI IF (FCB_READ_INTEGER .NE. 0) RETURN IF (VALBITS .LT. 32 .AND. VALSIGN .EQ. 0) THEN IINT(1) = IAND(IINT(1),NOT(-ISHFT(1,VALBITS)) ) ENDIF DO IF (SIGNBITS .LE. 0) EXIT IF (SIGNBITS .LT. 32) THEN FRI = & FCB_READ_BITS(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,BCOUNT,BBYTE, & SIGNBITS,XSIGN,1) FCB_READ_INTEGER = FRI IF (FCB_READ_INTEGER .NE. 0) RETURN ELSE FRI = & FCB_READ_BITS(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,BCOUNT,BBYTE, & 32,XSIGN,1) FCB_READ_INTEGER = FRI IF (FCB_READ_INTEGER .NE. 0) RETURN END IF SIGNBITS = SIGNBITS-32 IF ((IINT(1) .LT. 0 .AND. VALSIGN.NE.0 .AND. XSIGN(1).NE.-1) & .OR. ((IINT(1) .GE. 0 .OR. VALSIGN.EQ.0) .AND. XSIGN(1).NE.0)& ) THEN FCB_READ_INTEGER = CBF_OVERFLOW IINT(1) = -1 IF (VALSIGN.NE.0) THEN IF (XSIGN(1).GE. 0) THEN IINT(1) = Z''`7FFFFFFF''` ELSE IINT(1) = Z''`80000000''` END IF END IF RETURN END IF END DO FCB_READ_INTEGER = 0 RETURN END FUNCTION FCB_READ_INTEGER' ./CBFlib-0.9.2.2/m4/fcb_packed.m40000644000076500007650000004445011603702103014425 0ustar yayayayam4_dnl fcb_packed.m4 -- m4 macro file to generate I2, I4, m4_dnl and 3D_I2 and 3D_I4 versions m4_dnl of FCB_DECOMPRESS_PACKED m4_include(`fcblib_defines.m4')m4_dnl m4_define(`fcb_macro_FCB_PACKED', `! FCB_PACKED_$1.f90 ! ! Derived from CBFlib cbf_packed.c ! H. J. Bernstein, 25 February 2007 ! ! Based on J. P. Abrahams pack_c.c ! incorporated under GPL and LGPL in ! CBFlib with permission from CCP4 and ! from J. P. Abramhams ! ! Also based in part on test_pack.f90 ! translation of an earlier pack_c.c ! by W. Kabsch and K. Rohm ! Update pointers for averaging in J. P. Abrahams CCP4 compression ! algorithm. These f90 routines are derived from ! cbf_update_jpa_pointers, reworked as one routine ! for 2-dimensional arrays and one routine for 3-dimensional ! arrays, with I2 and I4 variants for each. ! ! This version is for ! ! m4_ifelse($1,`I2',`2-D INTEGER*2 arrays', $1,`I4',`2-D INTEGER*4 arrays', $1,`3D_I2',`3-D INTEGER*2 arrays', $1,`3D_I4',`3-D INTEGER*4 arrays',`2-D INTEGER*2 arrays') m4_define(`fcb_3d_flag',`2D')m4_dnl m4_ifelse($1,`3D_I2',`m4_define(`fcb_3d_flag',`3D')', $1,`3D_I4',`m4_define(`fcb_3d_flag',`3D')')m4_dnl m4_define(`fcb_i2_flag',`I2')m4_dnl m4_ifelse($1,`I4',`m4_define(`fcb_i2_flag',`I4')', $1,`3D_I4',`m4_define(`fcb_i2_flag',`I4')')m4_dnl ! ! with functions ! ! FCB_UPDATE_JPA_POINTERS_$1 ! FCB_DECOMPRESS_PACKED_$1 ! ! In the f90 implementation TRAIL_INDEX_ARRAY(1..8) has been ! replaced by TRAIL_INDEX_ARRAY(1..4) for 2-dimensional ! arrays and TRAIL_INDEX_ARRAY(1..8) for 3-dimensional arrays ! containing array indices or 0, for the array as if it ! were a linear array. ! ! On entry, TRAIL_INDEX_ARRAY(1) should point to the data element ! immediately prior to the next data element to be processed, either ! in the same row (fastest index) or, at the end of the prior row ! if the next data element to be processed is at the end of a row ! ! ndim1, ndim2, ndim3 should point to the indices of the same ! data element as TRAIL_INDEX_ARRAY(1) points to. These values ! will be incremented to be the indices of the next data element ! to be processed before populating TRAIL_INDEX_ARRAY. ! ! On exit, TRAIL_INDEX_ARRAY(1..8) will have been populated with ! pointers to the data elements to be used in forming the average. ! Elements that will not be used will be set to NULL. Note ! that TRAIL_INDEX_ARRAY(1) may be set to NULL. ! ! If we mark the next element to be processed with a "*" and the ! entries in TRAIL_INDEX_ARRAY with their array indices 1 .. 8, the ! possible patterns of settings in the general case are: ! ! current section: ! ! - - - - 1 * - - - - ! - - - - 4 3 2 - - - ! - - - - - - - - - - ! ! prior section: ! ! - - - - - 5 - - - - ! - - - - 8 7 6 - - - ! - - - - - - - - - - ! ! If there is no prior section (i.e. ndim3 is 0, or ! the CBF_UNCORRELATED_SECTIONS flag is set ! to indicate discontinuous sections), the values ! for TRAIL_INDEX_ARRAY (5..8) will all be NULL. When ! there is a prior section, TRAIL_INDEX_ARRAY(6..8) are ! pointers to the elements immediately below the ! elements pointed to by TRAIL_INDEX_ARRAY(2..4), but ! TRAIL_INDEX_ARRAY(5) is one element further along ! its row to be directly below the next element to ! be processed. ! ! The first element of the first row of the first section ! is a special case, with no averaging. This function ! should not be called for that case. ! ! In the first row of the first section (ndim2 == 1, ! and ndim3 == 1), after the first element (ndim1 > 1), ! only TRAIL_INDEX_ARRAY(1) is used ! ! current section: ! ! - - - - 1 * - - - - ! For subsequent rows of the first section (ndim2 > 1, ! and ndim3 == 1), for the first element (ndim1 == 1), ! two elements from the prior row are used: ! ! current section: ! ! * - - - - - - - - - ! 3 2 - - - - - - - - ! - - - - - - - - - - ! while for element after the first element, but before ! the last element of the row, a full set of 4 elements ! is used: ! ! current section: ! ! - - - - 1 * - - - - ! - - - - 4 3 2 - - - ! - - - - - - - - - - ! ! For the last element of a row (ndim1 == dim1-1), two ! elements are used ! ! current section: ! ! - - - - - - - - 1 * ! - - - - - - - - - 3 ! - - - - - - - - - - ! ! For sections after the first section, provided the ! CBF_UNCORRELATED_SECTIONS flag is not set in compression, ! for each non-NULL entry in TRAIL_INDEX_ARRAY (1..4) an entry ! is made in TRAIL_INDEX_ARRAY (5..8), except for the ! first element of the first row of a section. In that ! case an entry is made in TRAIL_INDEX_ARRAY(5). INTEGER FUNCTION FCB_UPDATE_JPA_POINTERS_$1(TRAIL_INDEX_ARRAY,& NDIM1, NDIM2, m4_ifelse(fcb_3d_flag,`3D', `NDIM3, ')ARRAY, DIM1, DIM2, m4_ifelse(fcb_3d_flag,`3D', `DIM3, ')AVERAGE, COMPRESSION) IMPLICIT NONE INTEGER(8), INTENT(IN):: DIM1,DIM2`'m4_ifelse(fcb_3d_flag,`3D',`,DIM3') INTEGER(8),INTENT(INOUT):: TRAIL_INDEX_ARRAY(`'m4_ifelse(fcb_3d_flag, `3D',`8',`4')), NDIM1, NDIM2`'m4_ifelse(fcb_3d_flag,`3D',`, NDIM3',` ') INTEGER(m4_ifelse($1,`I2',2,$1,`3D_I2',2,4)), INTENT(IN):: ARRAY(DIM1,DIM2`'m4_ifelse(fcb_3d_flag,`3D',`,DIM3')) INTEGER(4), INTENT(OUT):: AVERAGE INTEGER, INTENT(IN):: COMPRESSION INTEGER I, J, K, IFAST, m4_ifelse(fcb_3d_flag,`3D',`IMID, ')ISLOW INTEGER LOGTWO(4) m4_ifelse(fcb_i2_flag,`I2', ` INTEGER(4), PARAMETER:: SIGNMASK=Z'''``00008000'''`` INTEGER(4), PARAMETER:: LIMMASK=Z'''``0000FFFF'''``') fcb_param_CBF_LIST_ALL DATA LOGTWO / 1,2,0,3 / AVERAGE = 0 NDIM1 = NDIM1+1 IF (NDIM1 .EQ. DIM1+1) THEN NDIM1 = 1 NDIM2 = NDIM2+1 m4_ifelse(fcb_3d_flag,`3D', `` IF (NDIM2 .EQ. DIM2+1) THEN NDIM2 = 1 NDIM3 = NDIM3+1 END IF '') END IF DO I = 2,m4_ifelse(fcb_3d_flag,`3D',`8',`4') TRAIL_INDEX_ARRAY(I) = 0 END DO IF (NDIM2 > 1) THEN ! NOT IN THE FIRST ROW TRAIL_INDEX_ARRAY(2) = TRAIL_INDEX_ARRAY(1)-(DIM1-2) ! DOWN 1 RIGHT 2 TRAIL_INDEX_ARRAY(3) = TRAIL_INDEX_ARRAY(1)-(DIM1-1) ! DOWN 1 RIGHT 1 IF (NDIM1 > 1) THEN ! NOT IN THE FIRST COLUMN TRAIL_INDEX_ARRAY(4) = TRAIL_INDEX_ARRAY(1)-DIM1 ! DOWN 1 IF (NDIM1 .EQ. DIM1) THEN ! LAST COLUMN TRAIL_INDEX_ARRAY(2) = 0 TRAIL_INDEX_ARRAY(4) = 0 END IF ELSE ! FIRST COLUMN TRAIL_INDEX_ARRAY(1) = 0 END IF m4_ifelse(fcb_3d_flag,`3D', `` IF (NDIM3 .GT. 1 .AND. & IAND(COMPRESSION,CBF_UNCORRELATED_SECTIONS).EQ.0 ) THEN IF (TRAIL_INDEX_ARRAY(1).NE.0) THEN TRAIL_INDEX_ARRAY(5) = & TRAIL_INDEX_ARRAY(1) - DIM1*DIM2 + 1 END IF DO I = 2,4 IF (TRAIL_INDEX_ARRAY(I).NE.0) THEN TRAIL_INDEX_ARRAY(I+4) = & TRAIL_INDEX_ARRAY(I) - DIM1*DIM2 END IF END DO END IF '') ELSE ! FIRST ROW OF A SECTION IF (NDIM1 .EQ. 1 ) THEN m4_ifelse(fcb_3d_flag,`3D', `` TRAIL_INDEX_ARRAY(5) = TRAIL_INDEX_ARRAY(1) - (DIM1*DIM2-1) '') TRAIL_INDEX_ARRAY(1) = 0 END IF END IF J = 0 m4_ifelse(fcb_3d_flag,`3D', ` DO I = 1,8 IF (TRAIL_INDEX_ARRAY(I).NE.0) THEN J = J+1 ISLOW = 1+(TRAIL_INDEX_ARRAY(I)-1)/(DIM1*DIM2) IMID = 1+MOD(TRAIL_INDEX_ARRAY(I)-1,DIM1*DIM2) IMID = 1+(IMID-1)/DIM1 IFAST = 1+MOD(TRAIL_INDEX_ARRAY(I)-1,DIM1) AVERAGE = AVERAGE+ARRAY(IFAST,IMID,ISLOW) END IF END DO ', ` DO I = 1,4 IF (TRAIL_INDEX_ARRAY(I).NE.0) THEN J = J+1 ISLOW = 1+(TRAIL_INDEX_ARRAY(I)-1)/DIM1 IFAST = 1+MOD(TRAIL_INDEX_ARRAY(I)-1,DIM1) AVERAGE = AVERAGE+ARRAY(IFAST,ISLOW) END IF END DO ') K = ISHFT(J,-1) IF ( K .GT. 0 ) THEN m4_ifelse(fcb_i2_flag,`I2', ` AVERAGE = IAND(AVERAGE,LIMMASK) IF (IAND(AVERAGE+K,SIGNMASK).NE.0) AVERAGE = IOR(AVERAGE,NOT(LIMMASK))') IF (AVERAGE .GE.0) THEN AVERAGE = ISHFT(AVERAGE+K,-LOGTWO(K)) ELSE AVERAGE = NOT(ISHFT(NOT(AVERAGE+K),-LOGTWO(K))) ENDIF END IF FCB_UPDATE_JPA_POINTERS_$1 = 0 RETURN END FUNCTION FCB_UPDATE_JPA_POINTERS_$1 INTEGER FUNCTION FCB_DECOMPRESS_PACKED_$1 (ARRAY,NELEM,NELEM_READ, & ELSIGN, COMPRESSION, DIM1, DIM2, m4_ifelse(fcb_3d_flag,`3D', ``DIM3, '') & TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) IMPLICIT NONE INTEGER(8), INTENT(IN):: DIM1,DIM2`'m4_ifelse(fcb_3d_flag,`3D', `,DIM3') INTEGER(m4_ifelse($1,`I2',2,$1,`3D_I2',2,4)), INTENT(OUT):: ARRAY(DIM1,DIM2`'m4_ifelse(fcb_3d_flag,`3D', `,DIM3')) INTEGER(8), INTENT(OUT):: NELEM_READ INTEGER(8), INTENT(IN):: NELEM INTEGER, INTENT(IN):: ELSIGN, COMPRESSION INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) INTEGER(8) TRAIL_INDEX_ARRAY(m4_ifelse(fcb_3d_flag,`3D',8,4)) INTEGER I, V2FLAG, AVGFLAG, CLIPBITS, BITS INTEGER(8) NDIM1, NDIM2, m4_ifelse(fcb_3d_flag,`3D', `NDIM3,')LDIM1, LDIM2`'m4_ifelse(fcb_3d_flag,`3D', `, LDIM3') INTEGER COUNT, PIXEL, NEXT(1), IINT, IBITS INTEGER BCOUNT INTEGER(1) BBYTE INTEGER ERRORCODE, KBITS, KSIGN, PIXELCOUNT INTEGER(4) VORZEICHEN, UNSIGN, ELEMENT, LIMIT INTEGER(4) LAST_ELEMENT INTEGER(4) DISCARD(2), OFFSET(3) ! *** DEBUG *** INTEGER(4) PREV_ELEMENT, PREV_INDEX fcb_interface_FCB_READ_INTEGER fcb_interface_FCB_READ_BITS fcb_interface_FCB_UPDATE_JPA_POINTERS_$1 fcb_param_CBF_LIST_ALL fcb_errcode_LIST_ALL ! Version 1 bit lengths INTEGER(4),PARAMETER:: & CBF_PACKED_BITS1 = 4, & CBF_PACKED_BITS2 = 5, & CBF_PACKED_BITS3 = 6, & CBF_PACKED_BITS4 = 7, & CBF_PACKED_BITS5 = 8, & CBF_PACKED_BITS6 = 16 ! Version 2 bit lengths INTEGER(4),PARAMETER:: & CBF_PACKED_V2_BITS1 = 3, & CBF_PACKED_V2_BITS2 = 4, & CBF_PACKED_V2_BITS3 = 5, & CBF_PACKED_V2_BITS4 = 6, & CBF_PACKED_V2_BITS5 = 7, & CBF_PACKED_V2_BITS6 = 8, & CBF_PACKED_V2_BITS7 = 9, & CBF_PACKED_V2_BITS8 = 10, & CBF_PACKED_V2_BITS9 = 11, & CBF_PACKED_V2_BITS10 = 12, & CBF_PACKED_V2_BITS11 = 13, & CBF_PACKED_V2_BITS12 = 14, & CBF_PACKED_V2_BITS13 = 15, & CBF_PACKED_V2_BITS14 = 16 INTEGER(4) CBF_PACKED_BITS(8), CBF_PACKEDV2_BITS(16) DATA CBF_PACKED_BITS/ 0, CBF_PACKED_BITS1, & CBF_PACKED_BITS2, CBF_PACKED_BITS3, CBF_PACKED_BITS4, & CBF_PACKED_BITS5, CBF_PACKED_BITS6, 65 / DATA CBF_PACKEDV2_BITS/ 0, CBF_PACKED_V2_BITS1, & CBF_PACKED_V2_BITS2, CBF_PACKED_V2_BITS3, & CBF_PACKED_V2_BITS4, CBF_PACKED_V2_BITS5, & CBF_PACKED_V2_BITS6, CBF_PACKED_V2_BITS7, & CBF_PACKED_V2_BITS8, CBF_PACKED_V2_BITS9, & CBF_PACKED_V2_BITS10, CBF_PACKED_V2_BITS11, & CBF_PACKED_V2_BITS12, CBF_PACKED_V2_BITS13, & CBF_PACKED_V2_BITS14, 65 / BCOUNT = 0 BBYTE = 0 ! Discard the file_nelem entry (64 bits) */ FCB_DECOMPRESS_PACKED_$1 = & FCB_READ_INTEGER(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,BCOUNT,BBYTE, & 0,64,DISCARD,2) IF (FCB_DECOMPRESS_PACKED_$1 .NE. 0) RETURN ! Discard the minimum element entry (64 bits) */ FCB_DECOMPRESS_PACKED_$1 = & FCB_READ_INTEGER(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,BCOUNT,BBYTE, & 0,64,DISCARD,2) IF (FCB_DECOMPRESS_PACKED_$1 .NE. 0) RETURN ! Discard the maximum element entry (64 bits) */ FCB_DECOMPRESS_PACKED_$1 = & FCB_READ_INTEGER(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,BCOUNT,BBYTE, & 0,64,DISCARD,2) IF (FCB_DECOMPRESS_PACKED_$1 .NE. 0) RETURN ! Discard the reserved entry (64 bits) */ FCB_DECOMPRESS_PACKED_$1 = & FCB_READ_INTEGER(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,BCOUNT,BBYTE, & 0,64,DISCARD,2) IF (FCB_DECOMPRESS_PACKED_$1 .NE. 0) RETURN V2FLAG = 0 IF (IAND(COMPRESSION,CBF_COMPRESSION_MASK).EQ.CBF_PACKED_V2) & V2FLAG = 1 AVGFLAG = 1 IF (DIM1 .EQ. 0 .AND. DIM2 .EQ. 0 `'m4_ifelse(fcb_3d_flag,`3D',`.AND. DIM3 .EQ. 0')) AVGFLAG = 0 BITS = m4_ifelse($1,`I2',16,$1,`3D_I2',16,32) CLIPBITS = 0 IF (AVGFLAG .NE. 0) CLIPBITS=BITS DO I =1,m4_ifelse(fcb_3d_flag,`3D',8,4) TRAIL_INDEX_ARRAY(I) = 0 END DO VORZEICHEN = m4_ifelse($1,`I2',Z''`00008000''`,$1,`3D_I2',Z''`00008000''`,Z''`80000000''`) UNSIGN = 0 IF (ELSIGN.NE.0) UNSIGN=VORZEICHEN LIMIT = m4_ifelse($1,`I2',Z''`0000FFFF''`,$1,`3D_I2',Z''`0000FFFF''`,Z''`FFFFFFFF''`) ! Initialise the first element LAST_ELEMENT = UNSIGN ! *** DEBUG *** PREV_ELEMENT = 0 ! *** DEBUG *** PREV_INDEX = 0 m4_ifelse(fcb_3d_flag,`3D',` LDIM3 = DIM3 IF (DIM3.EQ.0) LDIM3 = 1') LDIM2 = DIM2 IF (DIM2.EQ.0) LDIM2 = 1 LDIM1 = DIM1 m4_ifelse(fcb_3d_flag,`3D',` IF (DIM1.EQ.0) LDIM1 = NELEM/(LDIM2*LDIM3) IF (LDIM1*LDIM2*LDIM3.NE.NELEM) THEN ', ` IF (DIM1.EQ.0) LDIM1 = NELEM/LDIM2 IF (LDIM1*LDIM2.NE.NELEM) THEN') FCB_DECOMPRESS_PACKED_$1 = CBF_ARGUMENT RETURN END IF ! Read the elements COUNT = 0 PIXEL = 0 NDIM1 = 1 NDIM2 = 1 m4_ifelse(fcb_3d_flag,`3D',` NDIM3 = 1') DO IF (COUNT .GE. NELEM) EXIT ! GET THE NEXT 6 BITS OF DATA FCB_DECOMPRESS_PACKED_$1 = & FCB_READ_INTEGER(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,BCOUNT,BBYTE, & 0,6+V2FLAG,NEXT,1) IF (FCB_DECOMPRESS_PACKED_$1 .NE. 0) THEN NELEM_READ=COUNT+PIXEL RETURN END IF PIXELCOUNT = ISHFT(1,IAND(NEXT(1),7)) IF (V2FLAG.NE.0) THEN BITS = CBF_PACKEDV2_BITS(1+IAND(ISHFT(NEXT(1),-3),15) ) ELSE BITS = CBF_PACKED_BITS(1+IAND(ISHFT(NEXT(1),-3),7) ) END IF IF (AVGFLAG.NE.0 .AND. BITS.EQ. 65) BITS = CLIPBITS ! READ THE OFFSETS IF ( PIXELCOUNT + COUNT .GT. NELEM ) & PIXELCOUNT = NELEM - COUNT DO PIXEL = 0, PIXELCOUNT-1 ELEMENT = LAST_ELEMENT OFFSET(1) = 0 OFFSET(2) = 0 OFFSET(3) = 0 ERRORCODE = 0 IF (BITS .NE. 0) THEN IF (BITS .GT. 32 ) THEN IINT = 1 DO IBITS=0,BITS-1,32 KSIGN = 1 IF (IBITS .LT. BITS-32) KSIGN = 0 KBITS = BITS-32*(IINT-1) IF (IBITS .LT. BITS-32) KBITS = 32 ERRORCODE=IOR(ERRORCODE, & FCB_READ_INTEGER(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,BCOUNT,BBYTE, & KSIGN,KBITS,OFFSET(IINT:IINT),1) ) IINT = IINT+1 END DO ELSE ERRORCODE = FCB_READ_BITS(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,BCOUNT,BBYTE, & BITS,OFFSET(1:1),1) END IF END IF IF (ERRORCODE.NE.0) THEN NELEM_READ = COUNT+PIXEL FCB_DECOMPRESS_PACKED_$1 = ERRORCODE RETURN END IF ELEMENT = ELEMENT+OFFSET(1) ELEMENT = IAND(ELEMENT,LIMIT) ELEMENT = ELEMENT-UNSIGN TRAIL_INDEX_ARRAY(1) = NDIM1+(NDIM2-1)*LDIM1`'m4_ifelse(fcb_3d_flag,`3D',` & +(NDIM3-1)*LDIM1*LDIM2') ARRAY(NDIM1,NDIM2`'m4_ifelse(fcb_3d_flag,`3D',`,NDIM3')) = ELEMENT ! *** DEBUG *** IF (PREV_ELEMENT.NE.ELEMENT.OR.PREV_INDEX.NE.TRAIL_INDEX_ARRAY(1)-1) THEN ! *** DEBUG *** PREV_ELEMENT = ELEMENT ! *** DEBUG *** PRINT *, "ARRAY(",TRAIL_INDEX_ARRAY(1),") = ", ELEMENT ! *** DEBUG *** END IF ! *** DEBUG *** PREV_INDEX= TRAIL_INDEX_ARRAY(1) IF (AVGFLAG.NE.0) THEN FCB_DECOMPRESS_PACKED_$1 = & FCB_UPDATE_JPA_POINTERS_$1(TRAIL_INDEX_ARRAY,& NDIM1, NDIM2, m4_ifelse(fcb_3d_flag,`3D', `NDIM3,')ARRAY, LDIM1, LDIM2, m4_ifelse(fcb_3d_flag,`3D', `LDIM3,')LAST_ELEMENT, COMPRESSION) LAST_ELEMENT = LAST_ELEMENT + UNSIGN LAST_ELEMENT = IAND(LAST_ELEMENT,LIMIT) ELSE LAST_ELEMENT = ELEMENT+UNSIGN NDIM1 = NDIM1+1 IF (NDIM1 .GT. LDIM1) THEN NDIM1 = 1 NDIM2 = NDIM2+1 m4_ifelse(fcb_3d_flag,`3D', ` IF(NDIM2 .GT. LDIM2) THEN NDIM2 = 1 NDIM3 = NDIM3+1 END IF') END IF ENDIF END DO COUNT = COUNT+PIXELCOUNT END DO NELEM_READ = COUNT FCB_DECOMPRESS_PACKED_$1 = 0 RETURN END FUNCTION FCB_DECOMPRESS_PACKED_$1') fcb_macro_FCB_PACKED(`I2') fcb_macro_FCB_PACKED(`I4') fcb_macro_FCB_PACKED(`3D_I2') fcb_macro_FCB_PACKED(`3D_I4') ./CBFlib-0.9.2.2/bin/0000755000076500007650000000000011603703065012353 5ustar yayayaya./CBFlib-0.9.2.2/bin/.keepme0000644000076500007650000000000011603702115013603 0ustar yayayaya./CBFlib-0.9.2.2/doc/0000755000076500007650000000000011603751102012343 5ustar yayayaya./CBFlib-0.9.2.2/doc/Iarray_intensities.gain.html0000644000076500007650000000540311603702115020015 0ustar yayayaya (IUCr) CIF Definition save__array_intensities.gain

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_array_intensities.gain

Name:
'_array_intensities.gain'

Definition:

        Detector 'gain'. The factor by which linearized
               intensity count values should be divided to produce
               true photon counts.

Type: float

Mandatory item: yes


The permitted range is [0.0, infinity)

Related item: _array_intensities.gain_esd (associated_value)

Category: array_intensities

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Iarray_structure_list_axis.axis_id.html0000644000076500007650000000566411603702115022311 0ustar yayayaya (IUCr) CIF Definition save__array_structure_list_axis.axis_id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_array_structure_list_axis.axis_id

Name:
'_array_structure_list_axis.axis_id'

Definition:

        The value of this data item is the identifier of one of
               the axes in the set of axes for which settings are being
               specified.

               Multiple axes may be specified for the same value of
               _array_structure_list_axis.axis_set_id.

               This item is a pointer to _axis.id in the
               AXIS category.

Type: code

Mandatory item: yes

Category: array_structure_list_axis

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Carray_data.html0000644000076500007650000002006111603702115015442 0ustar yayayaya (IUCr) CIF Definition save_array_data

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

Category ARRAY_DATA

Name:
'array_data'

Description:

    Data items in the ARRAY_DATA category are the containers for
     the array data items described in the category ARRAY_STRUCTURE.

     It is recognized that the data in this category needs to be used in
     two distinct ways.  During a data collection the lack of ancillary
     data and timing constraints in processing data may dictate the
     need to make a 'miniCBF' nothing more than an essential minimum
     of information to record the results of the data collection.  In that
     case it is proper to use the ARRAY_DATA category as a
     container for just a single image and a compacted, beam-line
     dependent list of data collection parameter values.  In such
     a case, only the tags '_array_data.header_convention',
     '_array_data.header_contents' and '_array_data.data' need be
     populated.

     For full processing and archiving, most of the tags in this
     dictionary will need to be populated.


Examples:

Example 1 - This example shows two binary data blocks. The first one was compressed by the CBF_CANONICAL compression algorithm and is presented as hexadecimal data. The first character 'H' on the data lines means hexadecimal. It could have been 'O' for octal or 'D' for decimal. The second character on the line shows the number of bytes in each word (in this case '4'), which then requires eight hexadecimal digits per word. The third character gives the order of octets within a word, in this case '<' for the ordering 4321 (i.e. 'big-endian'). Alternatively, the character '>' could have been used for the ordering 1234 (i.e. 'little-endian'). The block has a 'message digest' to check the integrity of the data. The second block is similar, but uses CBF_PACKED compression and BASE64 encoding. Note that the size and the digest are different.
 

        loop_
        _array_data.array_id
        _array_data.binary_id
        _array_data.data
        image_1 1
        ;
        --CIF-BINARY-FORMAT-SECTION--
        Content-Type: application/octet-stream;
             conversions="X-CBF_CANONICAL"
        Content-Transfer-Encoding: X-BASE16
        X-Binary-Size: 3927126
        X-Binary-ID: 1
        Content-MD5: u2sTJEovAHkmkDjPi+gWsg==

        # Hexadecimal encoding, byte 0, byte order ...21
        #
        H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ...
        ....
        --CIF-BINARY-FORMAT-SECTION----
        ;
        image_2 2
        ;
        --CIF-BINARY-FORMAT-SECTION--
        Content-Type: application/octet-stream;
             conversions="X-CBF-PACKED"
        Content-Transfer-Encoding: BASE64
        X-Binary-Size: 3745758
        X-Binary-ID: 2
        Content-MD5: 1zsJjWPfol2GYl2V+QSXrw==

        ELhQAAAAAAAA...
        ...
        --CIF-BINARY-FORMAT-SECTION----
        ;



Example 2 - This example shows a single image in a miniCBF, provided by E. Eikenberry. The entire CBF consists of one data block containing one category and three tags. The CBFlib program convert_miniCBF and a suitable template file can be used to convert this miniCBF to a full imgCIF file.
 
        ###CBF: VERSION 1.5
        # CBF file written by CBFlib v0.7.8

        data_insulin_pilatus6m

        _array_data.header_convention SLS_1.0
        _array_data.header_contents
        ;
        # Detector: PILATUS 6M SN: 60-0001
        # 2007/Jun/17 15:12:36.928
        # Pixel_size 172e-6 m x 172e-6 m
        # Silicon sensor, thickness 0.000320 m
        # Exposure_time 0.995000 s
        # Exposure_period 1.000000 s
        # Tau = 194.0e-09 s
        # Count_cutoff 1048575 counts
        # Threshold_setting 5000 eV
        # Wavelength 1.2398 A
        # Energy_range (0, 0) eV
        # Detector_distance 0.15500 m
        # Detector_Voffset -0.01003 m
        # Beam_xy (1231.00, 1277.00) pixels
        # Flux 22487563295 ph/s
        # Filter_transmission 0.0008
        # Start_angle 13.0000 deg.
        # Angle_increment 1.0000 deg.
        # Detector_2theta 0.0000 deg.
        # Polarization 0.990
        # Alpha 0.0000 deg.
        # Kappa 0.0000 deg.
        # Phi 0.0000 deg.
        # Chi 0.0000 deg.
        # Oscillation_axis  X, CW
        # N_oscillations 1
        ;

        _array_data.data
        ;
        --CIF-BINARY-FORMAT-SECTION--
        Content-Type: application/octet-stream;
             conversions="x-CBF_BYTE_OFFSET"
        Content-Transfer-Encoding: BINARY
        X-Binary-Size: 6247567
        X-Binary-ID: 1
        X-Binary-Element-Type: "signed 32-bit integer"
        X-Binary-Element-Byte-Order: LITTLE_ENDIAN
        Content-MD5: 8wO6i2+899lf5iO8QPdgrw==
        X-Binary-Number-of-Elements: 6224001
        X-Binary-Size-Fastest-Dimension: 2463
        X-Binary-Size-Second-Dimension: 2527
        X-Binary-Size-Padding: 4095

        ...

        --CIF-BINARY-FORMAT-SECTION----
        ;



Category groups:
    inclusive_group
    array_data_group
Category keys:
    _array_data.array_id
    _array_data.binary_id

Mandatory category: no

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/map_edit.html0000644000076500007650000002641611603702115015024 0ustar yayayaya####### # MAP # ####### save_MAP _category.description ; Data items in the MAP category record the details of a maps. Maps record values of parameters, such as density, that are functions of position within a cell or are functions of orthogonal coordinates in three space. A map may is composed of one or more map segments specified in the MAP_SEGMENT category. Maps are optionally keyed to a particular _diffrn.id or to a particular _entry.id, so that multiple maps for different data collections or entries may be collected in one data block. Examples are given in the MAP_SEGMENT category. ; _category.id map _category.mandatory_code no loop_ _category_key.name '_map.id' '_map.diffrn_id' '_map.entry_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Identifying an observed density map and a calculated density map ; ; loop_ _map.id _map.details rho_calc ; density calculated from F_calc derived from the ATOM_SITE list ; rho_obs ; density combining the observed structure factors with the calculated phases ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__map.details _item_description.description ; The value of _map.details should give a description of special aspects of each map. ; _item.name '_map.details' _item.category_id map _item.mandatory_code no _item_type.code text loop_ _item_examples.case _item_examples.detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Identifying an observed density map and a calculated density map ; ; loop_ _map.id _map.details rho_calc ; density calculated from F_calc derived from the ATOM_SITE list ; rho_obs ; density combining the observed structure factors with the calculated phases ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__map.diffrn_id _item_description.description ; This item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_map.diffrn_id' _item.category_id map _item.mandatory_code implicit _item_type.code code save_ save__map.entry_id _item_description.description ; This item is a pointer to _entry.id in the ENTRY category. ; _item.name '_map.entry_id' _item.category_id map _item.mandatory_code implicit _item_type.code code save_ save__map.id _item_description.description ; The value of _map.id must uniquely identify each map for the given diffrn.id or entry.id. ; loop_ _item.name _item.category_id _item.mandatory_code '_map.id' map yes '_map_segment.id' map_segment yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_map_segment.id' '_map.id' save_ ########################### # MAP_SEGMENT # ########################### save_MAP_SEGMENT _category.description ; Data items in the MAP_SEGMENT category record the details about each segment (section or brick) of a map. ; _category.id map_segment _category.mandatory_code no loop_ _category_key.name '_map_segment.id' '_map_segment.map_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Identifying an observed density map and a calculated density map, each consisting of one segment, both using the same array structure and mask. ; ; loop_ _map.id _map.details rho_calc ; density calculated from F_calc derived from the ATOM_SITE list ; rho_obs ; density combining the observed structure factors with the calculated phases ; loop_ _map_segment.map_id _map_segment.id _map_segment.array_id _map_segment.binary_id _map_segment.mask_array_id _map_segment.mask_binary_id rho_calc rho_calc map_structure 1 mask_structure 1 rho_obs rho_obs map_structure 2 mask_structure 1 # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__map_segment.array_id _item_description.description ; The value of _map_segment.array_id identifies the array structure into which the map is organized. This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_map_segment.array_id' _item.category_id map_segment _item.mandatory_code yes _item_type.code code save_ save__map_segment.binary_id _item_description.description ; The value of _map_segment.binary_id distinguishes the particular set of data organized according to _map_segment.array_id in which the data values of the map are stored. This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_map_segment.binary_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code int save_ save__map_segment.mask_array_id _item_description.description ; The value of _map_segment.mask_array_id, if given, the array structure into which the mask for the map is organized. If no value is given, then all elements of the map are valid. If a value is given, then only elements of the map for which the corresponding element of the mask is non-zero are valid. The value of _map_segment.mask_array_id differ from the value of _map_segment.array_id in order to permit the mask to be given as, say, unsigned 8-bit integers, while the map is given as a data type with more range. However, the two array structures must be aligned, using the same axes in the same order with the same displacements and increments This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_map_segment.mask_array_id' _item.category_id map_segment _item.mandatory_code no _item_type.code code save_ save__map_segment.mask_binary_id _item_description.description ; The value of _map_segment.mask_binary_id identifies the particular set of data organized according to _map_segment.mask_array_id specifying the mask for the map. This item is a pointer to _array_data.mask_binary_id in the ARRAY_DATA category. ; _item.name '_map_segment.mask_binary_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code int save_ save__map_segment.id _item_description.description ; The value of _map_segment.id must uniquely identify each segment of a map. ; loop_ _item.name _item.category_id _item.mandatory_code '_map_segment.id' map_segment yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_map_data_frame.map_segment_id' '_map_segment.id' save_ save__map_segment.map_id _item_description.description ; This item is a pointer to _map.id in the MAP category. ; _item.name '_map_segment.map_id' _item.category_id map_segment _item.mandatory_code yes _item_type.code code save_ save__map_segment.details _item_description.description ; The value of _map_segment.details should give a description of special aspects of each segment of a map. ; _item.name '_map_segment.details' _item.category_id map_segment _item.mandatory_code no _item_type.code text loop_ _item_examples.case _item_examples.detail ; Example to be provided ; ; ; save_ ./CBFlib-0.9.2.2/doc/Idiffrn_frame_data.details.html0000644000076500007650000000520511603702115020403 0ustar yayayaya (IUCr) CIF Definition save__diffrn_frame_data.details

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_frame_data.details

Name:
'_diffrn_frame_data.details'

Definition:

       The value of _diffrn_data_frame.details should give a
              description of special aspects of each frame of data.

              DEPRECATED -- DO NOT USE

Type: text

Mandatory item: no

Category: diffrn_frame_data

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_measurement.number_of_axes.html0000644000076500007650000000602611603702115022216 0ustar yayayaya (IUCr) CIF Definition save__diffrn_measurement.number_of_axes

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_measurement.number_of_axes

Name:
'_diffrn_measurement.number_of_axes'

Definition:

        The value of _diffrn_measurement.number_of_axes gives the
               number of axes of the positioner for the goniometer or
               other sample orientation or positioning device identified
               by _diffrn_measurement.id.

               The description of the axes should be provided by entries in
               DIFFRN_MEASUREMENT_AXIS.

Type: int

Mandatory item: no


The permitted range is [1, infinity)

Category: diffrn_measurement

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_radiation.polarisn_ratio.html0000644000076500007650000000612411603702115021673 0ustar yayayaya (IUCr) CIF Definition save__diffrn_radiation.polarisn_ratio

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_radiation.polarisn_ratio

Name:
'_diffrn_radiation.polarisn_ratio'

Definition:

        Polarization ratio of the diffraction beam incident on the
               crystal. This is the ratio of the perpendicularly polarized to
               the parallel polarized component of the radiation. The
               perpendicular component forms an angle of
               _diffrn_radiation.polarisn_norm to the normal to the
               diffraction plane of the sample (i.e. the plane containing
               the incident and reflected beams).

Type: float

Mandatory item: no

Alias:
_diffrn_radiation_polarisn_ratio (cif_core.dic version 2.0.1)
The permitted range is [0.0, infinity)

Category: diffrn_radiation

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/iz3004.cif0000644000076500007650000017704611603702115013776 0ustar yayayaya############################################################################## ### ### ### Full Paper (Acta Crystallographica Section C) ### ### ### ############################################################################## # # # This CIF contains the data in a paper accepted for publication in Acta # # Crystallographica Section C. It conforms to the editorial and technical # # requirements of Notes for Authors for Section C, and has been peer # # reviewed under the auspices of the IUCr Commission on Journals. # # # # Full details of the Crystallographic Information File format # # are given in the paper "The Crystallographic Information File (CIF): # # a New Standard Archive File for Crystallography" by S. R. Hall, F. H. # # Allen and I. D. Brown [Acta Cryst. (1991), A47, 655-685]. # # # # The current version of the core CIF dictionary is obtainable from # # ftp://ftp.iucr.org/pub/cif_core.dic. The current version number is 2.1. # # # # Software is freely available for graphical display of the structure(s) in # # this CIF. For information consult the CIF home page http://www.iucr.org/ # # cif/home.html # # # # Copyright International Union of Crystallography # # # ############################################################################## data_I _audit_creation_method SHELXL97 _chemical_name_systematic ; dirubidium heptaoxodimolybdate ; _chemical_name_common ? _chemical_formula_moiety 'Mo2 O7 , 2Rb' _chemical_formula_sum 'Mo2 O7 Rb2' _chemical_formula_iupac 'Rb2 Mo2 O7' _chemical_formula_weight 474.82 _chemical_melting_point ? _symmetry_cell_setting Orthorhombic _symmetry_space_group_name_H-M 'A m a 2' _symmetry_space_group_name_Hall 'A 2 -2a' loop_ _symmetry_equiv_pos_as_xyz 'x, y, z' '-x, -y, z' 'x+1/2, -y, z' '-x+1/2, y, z' 'x, y+1/2, z+1/2' '-x, -y+1/2, z+1/2' 'x+1/2, -y+1/2, z+1/2' '-x+1/2, y+1/2, z+1/2' _cell_length_a 11.8887(6) _cell_length_b 12.8303(6) _cell_length_c 10.2464(4) _cell_angle_alpha 90.00 _cell_angle_beta 90.00 _cell_angle_gamma 90.00 _cell_volume 1562.94(12) _cell_formula_units_Z 8 _cell_measurement_reflns_used 3812 _cell_measurement_theta_min 3.07 _cell_measurement_theta_max 27.46 _cell_measurement_temperature 293(2) _exptl_crystal_description fragment _exptl_crystal_colour colourless _exptl_crystal_size_max 0.06 _exptl_crystal_size_mid 0.06 _exptl_crystal_size_min 0.06 _exptl_crystal_density_diffrn 4.036 _exptl_crystal_density_meas ? _exptl_crystal_density_method 'not measured' _exptl_crystal_F_000 1712 _exptl_absorpt_coefficient_mu 15.574 _exptl_absorpt_correction_type multi-scan _exptl_absorpt_process_details '(SADABS; Bruker, 2004)' _exptl_absorpt_correction_T_min 0.4551 _exptl_absorpt_correction_T_max 0.4551 _exptl_special_details ; ? ; _diffrn_ambient_temperature 293(2) _diffrn_radiation_type MoK\a _diffrn_radiation_wavelength 0.71073 _diffrn_radiation_source 'fine-focus sealed X-ray tube' _diffrn_radiation_monochromator graphite _diffrn_measurement_device_type 'Bruker Nonius X8 APEX CCD area-detector' _diffrn_measurement_method '\f scans, frame data integration' _diffrn_detector_area_resol_mean ? _diffrn_reflns_number 4744 _diffrn_reflns_av_R_equivalents 0.0216 _diffrn_reflns_av_sigmaI/netI 0.0411 _diffrn_reflns_theta_min 2.54 _diffrn_reflns_theta_max 27.46 _diffrn_reflns_theta_full 27.46 _diffrn_measured_fraction_theta_max 1.000 _diffrn_measured_fraction_theta_full 1.000 _diffrn_reflns_limit_h_min -15 _diffrn_reflns_limit_h_max 15 _diffrn_reflns_limit_k_min -15 _diffrn_reflns_limit_k_max 16 _diffrn_reflns_limit_l_min -13 _diffrn_reflns_limit_l_max 7 _diffrn_standards_number 0 _diffrn_standards_interval_count ? _diffrn_standards_interval_time ? _diffrn_standards_decay_% 0 _refine_special_details ; Refinement of F^2^ against ALL reflections. The weighted R-factor wR and goodness of fit S are based on F^2^, conventional R-factors R are based on F, with F set to zero for negative F^2^. The threshold expression of F^2^ > 2sigma(F^2^) is used only for calculating R-factors(gt) etc. and is not relevant to the choice of reflections for refinement. R-factors based on F^2^ are statistically about twice as large as those based on F, and R- factors based on ALL data will be even larger. ; _reflns_number_total 1454 _reflns_number_gt 1416 _reflns_threshold_expression I>2\s(I) _refine_ls_structure_factor_coef Fsqd _refine_ls_matrix_type full _refine_ls_R_factor_all 0.0183 _refine_ls_R_factor_gt 0.0178 _refine_ls_wR_factor_gt 0.0493 _refine_ls_wR_factor_ref 0.0494 _refine_ls_goodness_of_fit_ref 1.152 _refine_ls_restrained_S_all 1.152 _refine_ls_number_reflns 1454 _refine_ls_number_parameters 110 _refine_ls_number_restraints 0 _refine_ls_hydrogen_treatment . _refine_ls_weighting_scheme calc _refine_ls_weighting_details 'calc w = 1/[\s^2^(Fo^2^)+(0.0203P)^2^] where P=(Fo^2^+2Fc^2^)/3' _atom_sites_solution_hydrogens . _atom_sites_solution_primary direct _atom_sites_solution_secondary difmap _refine_ls_shift/su_max 0.000 _refine_ls_shift/su_mean 0.000 _refine_diff_density_max 0.695 _refine_diff_density_min -0.599 _refine_ls_extinction_method 'Reference?' _refine_ls_extinction_coef 0.00047(5) _refine_ls_abs_structure_details 'Flack (1983), with how many Friedel pairs?' _refine_ls_abs_structure_Flack 0.019(6) loop_ _atom_type_symbol _atom_type_description _atom_type_scat_dispersion_real _atom_type_scat_dispersion_imag _atom_type_scat_source 'Li' 'Li' -0.0003 0.0001 'International Tables Vol C Tables 4.2.6.8 and 6.1.1.4' 'O' 'O' 0.0106 0.0060 'International Tables Vol C Tables 4.2.6.8 and 6.1.1.4' 'Co' 'Co' 0.3494 0.9721 'International Tables Vol C Tables 4.2.6.8 and 6.1.1.4' 'Mo' 'Mo' -1.6832 0.6857 'International Tables Vol C Tables 4.2.6.8 and 6.1.1.4' 'Cs' 'Cs' -0.3680 2.1192 'International Tables Vol C Tables 4.2.6.8 and 6.1.1.4' _computing_data_collection 'SMART (Bruker, 2004)' _computing_cell_refinement 'SMART' _computing_data_reduction 'SAINT (Bruker, 2004)' _computing_structure_solution 'SHELXS97 (Sheldrick, 1997)' _computing_structure_refinement 'SHELXL97 (Sheldrick, 1997)' _computing_molecular_graphics 'BS (Ozawa & Kang, 2004)' _computing_publication_material 'SHELXL97' loop_ _atom_site_type_symbol _atom_site_label _atom_site_fract_x _atom_site_fract_y _atom_site_fract_z _atom_site_U_iso_or_equiv _atom_site_adp_type _atom_site_calc_flag _atom_site_refinement_flags _atom_site_occupancy _atom_site_disorder_assembly _atom_site_disorder_group Rb Rb1 0.0000 0.5000 0.5000 0.0237(2) Uani d S 1 . . Rb Rb2 0.2500 0.48386(5) -0.26390(11) 0.01891(17) Uani d S 1 . . Rb Rb3 0.2500 0.21144(6) 0.49330(11) 0.02700(18) Uani d S 1 . . Rb Rb4 0.2500 0.25540(7) -0.02260(13) 0.0378(2) Uani d S 1 . . Mo Mo1 0.0000 0.5000 0.06117(13) 0.01268(15) Uani d S 1 . . Mo Mo2 0.2500 0.47105(5) 0.28712(12) 0.01558(14) Uani d S 1 . . Mo Mo3 0.01169(3) 0.25276(4) 0.22891(13) 0.01681(11) Uani d . 1 . . O O1 0.1103(3) 0.5171(3) -0.0426(4) 0.0277(9) Uani d . 1 . . O O2 0.0319(3) 0.3571(2) 0.1036(4) 0.0187(7) Uani d . 1 . . O O3 0.1236(3) 0.5306(3) 0.2280(4) 0.0243(8) Uani d . 1 . . O O4 0.2500 0.3413(4) 0.2440(6) 0.0275(11) Uani d S 1 . . O O5 0.2500 0.4846(5) 0.4559(6) 0.0326(14) Uani d S 1 . . O O6 -0.1241(3) 0.2050(3) 0.2201(4) 0.0340(10) Uani d . 1 . . O O7 0.1013(3) 0.1507(3) 0.1898(4) 0.0294(9) Uani d . 1 . . O O8 0.0325(3) 0.2957(3) 0.3879(4) 0.0292(9) Uani d . 1 . . loop_ _atom_site_aniso_label _atom_site_aniso_U_11 _atom_site_aniso_U_22 _atom_site_aniso_U_33 _atom_site_aniso_U_12 _atom_site_aniso_U_13 _atom_site_aniso_U_23 Rb1 0.0188(4) 0.0240(4) 0.0283(5) -0.0010(3) 0.000 0.000 Rb2 0.0217(4) 0.0170(3) 0.0181(4) 0.000 0.000 -0.0004(3) Rb3 0.0264(4) 0.0240(4) 0.0305(4) 0.000 0.000 -0.0003(4) Rb4 0.0406(7) 0.0475(6) 0.0252(5) 0.000 0.000 0.0026(4) Mo1 0.0134(3) 0.0112(3) 0.0135(4) -0.0008(2) 0.000 0.000 Mo2 0.0116(3) 0.0217(3) 0.0135(3) 0.000 0.000 -0.0006(3) Mo3 0.01570(19) 0.0145(2) 0.0202(2) -0.00137(15) -0.0004(2) 0.00216(17) O1 0.031(2) 0.027(2) 0.026(2) -0.0015(17) 0.0133(18) 0.0019(15) O2 0.0213(17) 0.0126(16) 0.0222(19) 0.0006(13) -0.0002(15) -0.0004(15) O3 0.0218(18) 0.0240(19) 0.027(2) 0.0031(15) -0.0071(17) -0.0037(17) O4 0.022(2) 0.020(3) 0.041(3) 0.000 0.000 0.003(2) O5 0.020(3) 0.059(4) 0.020(3) 0.000 0.000 -0.006(2) O6 0.0235(19) 0.032(2) 0.047(3) -0.0114(16) -0.003(2) 0.011(2) O7 0.034(2) 0.0166(19) 0.038(2) 0.0083(16) -0.0030(18) 0.0011(16) O8 0.036(2) 0.026(2) 0.026(2) 0.0013(18) 0.0023(18) 0.0022(18) _geom_special_details ; All esds (except the esd in the dihedral angle between two l.s. planes) are estimated using the full covariance matrix. The cell esds are taken into account individually in the estimation of esds in distances, angles and torsion angles; correlations between esds in cell parameters are only used when they are defined by crystal symmetry. An approximate (isotropic) treatment of cell esds is used for estimating esds involving l.s. planes. ; loop_ _geom_bond_atom_site_label_1 _geom_bond_atom_site_label_2 _geom_bond_site_symmetry_2 _geom_bond_distance _geom_bond_publ_flag Rb1 O8 2_565 2.888(4) yes Rb1 O8 . 2.888(4) yes Rb1 O7 5 2.995(4) yes Rb1 O7 6 2.995(4) yes Rb1 O5 2_565 3.0128(10) yes Rb1 O5 . 3.0128(10) yes Rb1 O3 2_565 3.176(4) yes Rb1 O3 . 3.176(4) yes Rb1 Mo2 2_565 3.7054(7) no Rb1 Mo2 . 3.7054(7) no Rb1 Rb2 1_556 3.8379(7) no Rb1 Rb2 2_566 3.8379(7) no Rb2 O7 8_554 2.816(4) yes Rb2 O7 5_554 2.816(4) yes Rb2 O1 4 2.843(4) yes Rb2 O1 . 2.843(4) yes Rb2 O6 6_554 2.853(4) yes Rb2 O6 7_554 2.853(4) yes Rb2 O5 1_554 2.871(6) yes Rb2 Rb4 . 3.8347(12) no Rb2 Rb1 1_554 3.8379(7) no Rb2 Rb1 3_564 3.8379(7) no Rb2 Rb3 5_554 3.9333(12) no Rb2 Rb3 1_554 4.2903(12) no Rb3 O6 7 2.964(4) yes Rb3 O6 6 2.964(4) yes Rb3 O8 . 3.003(4) yes Rb3 O8 4 3.003(4) yes Rb3 O1 5_545 3.018(4) yes Rb3 O1 8_545 3.018(4) yes Rb3 O4 . 3.050(6) yes Rb3 O5 . 3.525(6) yes Rb3 O2 7 3.644(3) yes Rb3 O2 6 3.644(3) yes Rb3 Rb2 5_545 3.9333(12) no Rb3 Mo2 . 3.9444(10) no Rb4 O4 . 2.945(6) yes Rb4 O6 6_554 3.074(4) yes Rb4 O6 7_554 3.074(4) yes Rb4 O7 4 3.109(4) yes Rb4 O7 . 3.109(4) yes Rb4 O2 4 3.178(3) yes Rb4 O2 . 3.178(3) yes Rb4 O5 5_544 3.482(6) yes Rb4 O8 6_554 3.543(4) yes Rb4 O8 7_554 3.543(4) yes Rb4 Mo3 4 3.8301(8) no Rb4 Mo3 . 3.8301(8) no Mo1 O1 2_565 1.702(4) yes Mo1 O1 . 1.702(4) yes Mo1 O2 2_565 1.922(3) yes Mo1 O2 . 1.922(3) yes Mo1 O3 . 2.288(4) yes Mo1 O3 2_565 2.288(4) yes Mo1 Rb3 5_554 4.0837(6) no Mo1 Rb3 6_554 4.0837(6) no Mo2 O4 . 1.723(5) yes Mo2 O5 . 1.738(6) yes Mo2 O3 . 1.791(4) yes Mo2 O3 4 1.791(4) yes Mo2 Rb1 3_565 3.7054(7) no Mo2 Rb4 5 4.1367(11) no Mo2 Rb3 5_554 4.3100(10) no Mo3 O6 . 1.729(4) yes Mo3 O7 . 1.736(4) yes Mo3 O8 . 1.738(4) yes Mo3 O2 . 1.870(3) yes Mo3 Rb3 6_554 3.9646(7) no Mo3 Rb1 5_544 4.0047(9) no Mo3 Rb4 6 4.0216(7) no Mo3 Rb2 6 4.3475(7) no O1 Rb3 5_554 3.018(4) no O2 Rb3 6_554 3.644(3) no O5 Rb2 1_556 2.871(6) no O5 Rb1 3_565 3.0128(9) no O5 Rb4 5 3.482(6) no O6 Rb2 6 2.853(4) no O6 Rb3 6_554 2.964(4) no O6 Rb4 6 3.074(4) no O7 Rb2 5_545 2.816(4) no O7 Rb1 5_544 2.995(4) no O8 Rb4 6 3.543(4) no loop_ _geom_angle_atom_site_label_1 _geom_angle_atom_site_label_2 _geom_angle_atom_site_label_3 _geom_angle_site_symmetry_1 _geom_angle_site_symmetry_3 _geom_angle _geom_angle_publ_flag O8 Rb1 O8 2_565 . 133.14(16) no O8 Rb1 O7 2_565 5 74.11(10) no O8 Rb1 O7 . 5 142.20(10) no O8 Rb1 O7 2_565 6 142.20(10) no O8 Rb1 O7 . 6 74.11(10) no O7 Rb1 O7 5 6 99.03(15) no O8 Rb1 O5 2_565 2_565 75.44(14) no O8 Rb1 O5 . 2_565 97.60(15) no O7 Rb1 O5 5 2_565 116.86(14) no O7 Rb1 O5 6 2_565 75.10(13) no O8 Rb1 O5 2_565 . 97.60(15) no O8 Rb1 O5 . . 75.44(14) no O7 Rb1 O5 5 . 75.10(13) no O7 Rb1 O5 6 . 116.86(14) no O5 Rb1 O5 2_565 . 162.7(2) no O8 Rb1 O3 2_565 2_565 72.62(10) no O8 Rb1 O3 . 2_565 66.46(10) no O7 Rb1 O3 5 2_565 146.72(10) no O7 Rb1 O3 6 2_565 107.68(10) no O5 Rb1 O3 2_565 2_565 54.54(13) no O5 Rb1 O3 . 2_565 108.47(13) no O8 Rb1 O3 2_565 . 66.46(10) no O8 Rb1 O3 . . 72.62(10) no O7 Rb1 O3 5 . 107.68(10) no O7 Rb1 O3 6 . 146.72(10) no O5 Rb1 O3 2_565 . 108.47(13) no O5 Rb1 O3 . . 54.54(13) no O3 Rb1 O3 2_565 . 57.26(13) no O8 Rb1 Mo2 2_565 2_565 64.37(8) no O8 Rb1 Mo2 . 2_565 87.96(8) no O7 Rb1 Mo2 5 2_565 129.81(7) no O7 Rb1 Mo2 6 2_565 97.13(8) no O5 Rb1 Mo2 2_565 2_565 27.60(11) no O5 Rb1 Mo2 . 2_565 135.20(12) no O3 Rb1 Mo2 2_565 2_565 28.88(7) no O3 Rb1 Mo2 . 2_565 80.92(7) no O8 Rb1 Mo2 2_565 . 87.96(8) no O8 Rb1 Mo2 . . 64.37(8) no O7 Rb1 Mo2 5 . 97.13(8) no O7 Rb1 Mo2 6 . 129.81(7) no O5 Rb1 Mo2 2_565 . 135.20(12) no O5 Rb1 Mo2 . . 27.60(11) no O3 Rb1 Mo2 2_565 . 80.92(7) no O3 Rb1 Mo2 . . 28.88(7) no Mo2 Rb1 Mo2 2_565 . 107.87(3) no O8 Rb1 Rb2 2_565 1_556 113.79(8) no O8 Rb1 Rb2 . 1_556 95.62(8) no O7 Rb1 Rb2 5 1_556 46.69(7) no O7 Rb1 Rb2 6 1_556 82.39(8) no O5 Rb1 Rb2 2_565 1_556 149.55(11) no O5 Rb1 Rb2 . 1_556 47.70(11) no O3 Rb1 Rb2 2_565 1_556 154.83(7) no O3 Rb1 Rb2 . 1_556 101.62(7) no Mo2 Rb1 Rb2 2_565 1_556 176.09(2) no Mo2 Rb1 Rb2 . 1_556 75.195(15) no O8 Rb1 Rb2 2_565 2_566 95.62(8) no O8 Rb1 Rb2 . 2_566 113.79(8) no O7 Rb1 Rb2 5 2_566 82.39(8) no O7 Rb1 Rb2 6 2_566 46.69(7) no O5 Rb1 Rb2 2_565 2_566 47.70(11) no O5 Rb1 Rb2 . 2_566 149.55(11) no O3 Rb1 Rb2 2_565 2_566 101.62(7) no O3 Rb1 Rb2 . 2_566 154.83(7) no Mo2 Rb1 Rb2 2_565 2_566 75.195(15) no Mo2 Rb1 Rb2 . 2_566 176.09(2) no Rb2 Rb1 Rb2 1_556 2_566 101.85(3) no O7 Rb2 O7 8_554 5_554 77.76(16) no O7 Rb2 O1 8_554 4 69.74(11) no O7 Rb2 O1 5_554 4 112.78(11) no O7 Rb2 O1 8_554 . 112.78(11) no O7 Rb2 O1 5_554 . 69.74(11) no O1 Rb2 O1 4 . 71.49(18) no O7 Rb2 O6 8_554 6_554 164.82(12) no O7 Rb2 O6 5_554 6_554 107.85(11) no O1 Rb2 O6 4 6_554 118.68(12) no O1 Rb2 O6 . 6_554 82.35(12) no O7 Rb2 O6 8_554 7_554 107.85(11) no O7 Rb2 O6 5_554 7_554 164.82(12) no O1 Rb2 O6 4 7_554 82.35(12) no O1 Rb2 O6 . 7_554 118.68(12) no O6 Rb2 O6 6_554 7_554 63.28(15) no O7 Rb2 O5 8_554 1_554 80.15(12) no O7 Rb2 O5 5_554 1_554 80.15(12) no O1 Rb2 O5 4 1_554 142.86(9) no O1 Rb2 O5 . 1_554 142.86(9) no O6 Rb2 O5 6_554 1_554 86.85(14) no O6 Rb2 O5 7_554 1_554 86.85(14) no O7 Rb2 Rb4 8_554 . 133.60(8) no O7 Rb2 Rb4 5_554 . 133.60(8) no O1 Rb2 Rb4 4 . 66.45(7) no O1 Rb2 Rb4 . . 66.45(7) no O6 Rb2 Rb4 6_554 . 52.26(9) no O6 Rb2 Rb4 7_554 . 52.26(9) no O5 Rb2 Rb4 1_554 . 130.33(13) no O7 Rb2 Rb1 8_554 1_554 109.80(8) no O7 Rb2 Rb1 5_554 1_554 50.70(8) no O1 Rb2 Rb1 4 1_554 161.28(9) no O1 Rb2 Rb1 . 1_554 92.42(9) no O6 Rb2 Rb1 6_554 1_554 66.62(8) no O6 Rb2 Rb1 7_554 1_554 114.57(8) no O5 Rb2 Rb1 1_554 1_554 50.912(16) no Rb4 Rb2 Rb1 . 1_554 116.594(16) no O7 Rb2 Rb1 8_554 3_564 50.70(8) no O7 Rb2 Rb1 5_554 3_564 109.80(8) no O1 Rb2 Rb1 4 3_564 92.42(9) no O1 Rb2 Rb1 . 3_564 161.28(9) no O6 Rb2 Rb1 6_554 3_564 114.57(8) no O6 Rb2 Rb1 7_554 3_564 66.62(8) no O5 Rb2 Rb1 1_554 3_564 50.912(16) no Rb4 Rb2 Rb1 . 3_564 116.594(16) no Rb1 Rb2 Rb1 1_554 3_564 101.51(3) no O7 Rb2 Rb3 8_554 5_554 63.18(8) no O7 Rb2 Rb3 5_554 5_554 63.18(8) no O1 Rb2 Rb3 4 5_554 49.77(8) no O1 Rb2 Rb3 . 5_554 49.77(8) no O6 Rb2 Rb3 6_554 5_554 132.00(8) no O6 Rb2 Rb3 7_554 5_554 132.00(8) no O5 Rb2 Rb3 1_554 5_554 131.89(13) no Rb4 Rb2 Rb3 . 5_554 97.78(3) no Rb1 Rb2 Rb3 1_554 5_554 112.476(14) no Rb1 Rb2 Rb3 3_564 5_554 112.476(14) no O7 Rb2 Rb3 8_554 1_554 121.42(8) no O7 Rb2 Rb3 5_554 1_554 121.42(8) no O1 Rb2 Rb3 4 1_554 125.79(8) no O1 Rb2 Rb3 . 1_554 125.79(8) no O6 Rb2 Rb3 6_554 1_554 43.50(8) no O6 Rb2 Rb3 7_554 1_554 43.50(8) no O5 Rb2 Rb3 1_554 1_554 54.74(12) no Rb4 Rb2 Rb3 . 1_554 75.59(2) no Rb1 Rb2 Rb3 1_554 1_554 71.242(14) no Rb1 Rb2 Rb3 3_564 1_554 71.242(14) no Rb3 Rb2 Rb3 5_554 1_554 173.37(3) no O6 Rb3 O6 7 6 60.65(14) no O6 Rb3 O8 7 . 125.89(10) no O6 Rb3 O8 6 . 73.56(11) no O6 Rb3 O8 7 4 73.56(11) no O6 Rb3 O8 6 4 125.89(11) no O8 Rb3 O8 . 4 118.83(15) no O6 Rb3 O1 7 5_545 132.22(11) no O6 Rb3 O1 6 5_545 96.67(10) no O8 Rb3 O1 . 5_545 77.28(11) no O8 Rb3 O1 4 5_545 136.67(11) no O6 Rb3 O1 7 8_545 96.67(10) no O6 Rb3 O1 6 8_545 132.22(11) no O8 Rb3 O1 . 8_545 136.67(11) no O8 Rb3 O1 4 8_545 77.28(11) no O1 Rb3 O1 5_545 8_545 66.78(15) no O6 Rb3 O4 7 . 117.32(12) no O6 Rb3 O4 6 . 117.32(12) no O8 Rb3 O4 . . 60.15(8) no O8 Rb3 O4 4 . 60.15(8) no O1 Rb3 O4 5_545 . 110.44(12) no O1 Rb3 O4 8_545 . 110.44(12) no O6 Rb3 O5 7 . 74.08(11) no O6 Rb3 O5 6 . 74.08(11) no O8 Rb3 O5 . . 66.61(8) no O8 Rb3 O5 4 . 66.61(8) no O1 Rb3 O5 5_545 . 143.89(9) no O1 Rb3 O5 8_545 . 143.89(9) no O4 Rb3 O5 . . 50.65(14) no O6 Rb3 O2 7 7 51.67(9) no O6 Rb3 O2 6 7 107.96(9) no O8 Rb3 O2 . 7 171.90(9) no O8 Rb3 O2 4 7 53.62(9) no O1 Rb3 O2 5_545 7 110.15(9) no O1 Rb3 O2 8_545 7 48.12(9) no O4 Rb3 O2 . 7 113.06(6) no O5 Rb3 O2 . 7 105.88(6) no O6 Rb3 O2 7 6 107.96(9) no O6 Rb3 O2 6 6 51.67(9) no O8 Rb3 O2 . 6 53.62(9) no O8 Rb3 O2 4 6 171.90(9) no O1 Rb3 O2 5_545 6 48.12(9) no O1 Rb3 O2 8_545 6 110.15(9) no O4 Rb3 O2 . 6 113.06(6) no O5 Rb3 O2 . 6 105.88(6) no O2 Rb3 O2 7 6 133.72(11) no O6 Rb3 Rb2 7 5_545 142.52(7) no O6 Rb3 Rb2 6 5_545 142.52(7) no O8 Rb3 Rb2 . 5_545 91.51(8) no O8 Rb3 Rb2 4 5_545 91.51(8) no O1 Rb3 Rb2 5_545 5_545 45.99(8) no O1 Rb3 Rb2 8_545 5_545 45.99(8) no O4 Rb3 Rb2 . 5_545 81.04(10) no O5 Rb3 Rb2 . 5_545 131.69(10) no O2 Rb3 Rb2 7 5_545 91.65(5) no O2 Rb3 Rb2 6 5_545 91.65(5) no O6 Rb3 Mo2 7 . 96.57(8) no O6 Rb3 Mo2 6 . 96.57(8) no O8 Rb3 Mo2 . . 60.23(8) no O8 Rb3 Mo2 4 . 60.23(8) no O1 Rb3 Mo2 5_545 . 129.22(8) no O1 Rb3 Mo2 8_545 . 129.22(8) no O4 Rb3 Mo2 . . 24.51(10) no O5 Rb3 Mo2 . . 26.15(9) no O2 Rb3 Mo2 7 . 111.71(5) no O2 Rb3 Mo2 6 . 111.71(5) no Rb2 Rb3 Mo2 5_545 . 105.55(2) no O4 Rb4 O6 . 6_554 137.20(10) no O4 Rb4 O6 . 7_554 137.20(10) no O6 Rb4 O6 6_554 7_554 58.27(14) no O4 Rb4 O7 . 4 60.83(10) no O6 Rb4 O7 6_554 4 161.54(10) no O6 Rb4 O7 7_554 4 113.26(10) no O4 Rb4 O7 . . 60.83(10) no O6 Rb4 O7 6_554 . 113.26(10) no O6 Rb4 O7 7_554 . 161.54(10) no O7 Rb4 O7 4 . 69.30(14) no O4 Rb4 O2 . 4 57.92(7) no O6 Rb4 O2 6_554 4 132.73(10) no O6 Rb4 O2 7_554 4 83.34(9) no O7 Rb4 O2 4 4 55.16(9) no O7 Rb4 O2 . 4 110.89(10) no O4 Rb4 O2 . . 57.92(7) no O6 Rb4 O2 6_554 . 83.34(9) no O6 Rb4 O2 7_554 . 132.73(10) no O7 Rb4 O2 4 . 110.89(10) no O7 Rb4 O2 . . 55.16(9) no O2 Rb4 O2 4 . 109.36(12) no O4 Rb4 O5 . 5_544 115.59(14) no O6 Rb4 O5 6_554 5_544 96.35(11) no O6 Rb4 O5 7_554 5_544 96.35(11) no O7 Rb4 O5 4 5_544 67.22(10) no O7 Rb4 O5 . 5_544 67.22(10) no O2 Rb4 O5 4 5_544 115.82(7) no O2 Rb4 O5 . 5_544 115.82(7) no O4 Rb4 O8 . 6_554 108.01(6) no O6 Rb4 O8 6_554 6_554 49.24(9) no O6 Rb4 O8 7_554 6_554 105.68(10) no O7 Rb4 O8 4 6_554 129.80(9) no O7 Rb4 O8 . 6_554 64.03(9) no O2 Rb4 O8 4 6_554 162.72(9) no O2 Rb4 O8 . 6_554 53.68(8) no O5 Rb4 O8 5_544 6_554 78.40(7) no O4 Rb4 O8 . 7_554 108.01(6) no O6 Rb4 O8 6_554 7_554 105.68(10) no O6 Rb4 O8 7_554 7_554 49.24(9) no O7 Rb4 O8 4 7_554 64.03(9) no O7 Rb4 O8 . 7_554 129.80(9) no O2 Rb4 O8 4 7_554 53.68(8) no O2 Rb4 O8 . 7_554 162.72(9) no O5 Rb4 O8 5_544 7_554 78.40(7) no O8 Rb4 O8 6_554 7_554 142.90(13) no O4 Rb4 Mo3 . 4 51.63(3) no O6 Rb4 Mo3 6_554 4 159.84(7) no O6 Rb4 Mo3 7_554 4 102.62(7) no O7 Rb4 Mo3 4 4 26.45(6) no O7 Rb4 Mo3 . 4 86.89(7) no O2 Rb4 Mo3 4 4 29.10(6) no O2 Rb4 Mo3 . 4 109.47(7) no O5 Rb4 Mo3 5_544 4 91.93(7) no O8 Rb4 Mo3 6_554 4 150.90(7) no O8 Rb4 Mo3 7_554 4 58.07(6) no O4 Rb4 Mo3 . . 51.63(3) no O6 Rb4 Mo3 6_554 . 102.62(7) no O6 Rb4 Mo3 7_554 . 159.84(7) no O7 Rb4 Mo3 4 . 86.89(7) no O7 Rb4 Mo3 . . 26.45(6) no O2 Rb4 Mo3 4 . 109.47(7) no O2 Rb4 Mo3 . . 29.10(6) no O5 Rb4 Mo3 5_544 . 91.93(7) no O8 Rb4 Mo3 6_554 . 58.07(6) no O8 Rb4 Mo3 7_554 . 150.90(7) no Mo3 Rb4 Mo3 4 . 95.42(2) no O1 Mo1 O1 2_565 . 102.7(3) no O1 Mo1 O2 2_565 2_565 96.46(16) no O1 Mo1 O2 . 2_565 99.80(16) no O1 Mo1 O2 2_565 . 99.80(16) no O1 Mo1 O2 . . 96.46(16) no O2 Mo1 O2 2_565 . 153.8(2) no O1 Mo1 O3 2_565 . 169.55(19) no O1 Mo1 O3 . . 87.10(17) no O2 Mo1 O3 2_565 . 78.09(14) no O2 Mo1 O3 . . 82.42(14) no O1 Mo1 O3 2_565 2_565 87.10(17) no O1 Mo1 O3 . 2_565 169.55(19) no O2 Mo1 O3 2_565 2_565 82.42(14) no O2 Mo1 O3 . 2_565 78.09(14) no O3 Mo1 O3 . 2_565 83.4(2) no O1 Mo1 Rb3 2_565 5_554 122.68(15) no O1 Mo1 Rb3 . 5_554 41.17(14) no O2 Mo1 Rb3 2_565 5_554 63.15(10) no O2 Mo1 Rb3 . 5_554 121.92(10) no O3 Mo1 Rb3 . 5_554 62.97(10) no O3 Mo1 Rb3 2_565 5_554 135.14(10) no O1 Mo1 Rb3 2_565 6_554 41.17(14) no O1 Mo1 Rb3 . 6_554 122.68(15) no O2 Mo1 Rb3 2_565 6_554 121.92(10) no O2 Mo1 Rb3 . 6_554 63.15(10) no O3 Mo1 Rb3 . 6_554 135.14(10) no O3 Mo1 Rb3 2_565 6_554 62.97(10) no Rb3 Mo1 Rb3 5_554 6_554 160.39(3) no O4 Mo2 O5 . . 110.6(3) no O4 Mo2 O3 . . 109.02(15) no O5 Mo2 O3 . . 107.10(17) no O4 Mo2 O3 . 4 109.02(15) no O5 Mo2 O3 . 4 107.10(17) no O3 Mo2 O3 . 4 114.0(3) no O4 Mo2 Rb1 . 3_565 104.35(11) no O5 Mo2 Rb1 . 3_565 53.434(19) no O3 Mo2 Rb1 . 3_565 146.00(12) no O3 Mo2 Rb1 4 3_565 58.91(14) no O4 Mo2 Rb1 . . 104.35(11) no O5 Mo2 Rb1 . . 53.434(19) no O3 Mo2 Rb1 . . 58.91(14) no O3 Mo2 Rb1 4 . 146.00(12) no Rb1 Mo2 Rb1 3_565 . 106.67(3) no O4 Mo2 Rb3 . . 47.2(2) no O5 Mo2 Rb3 . . 63.3(2) no O3 Mo2 Rb3 . . 122.80(12) no O3 Mo2 Rb3 4 . 122.80(12) no Rb1 Mo2 Rb3 3_565 . 76.665(15) no Rb1 Mo2 Rb3 . . 76.665(15) no O4 Mo2 Rb4 . 5 166.7(2) no O5 Mo2 Rb4 . 5 56.2(2) no O3 Mo2 Rb4 . 5 77.46(12) no O3 Mo2 Rb4 4 5 77.46(12) no Rb1 Mo2 Rb4 3_565 5 68.538(13) no Rb1 Mo2 Rb4 . 5 68.538(13) no Rb3 Mo2 Rb4 . 5 119.49(3) no O4 Mo2 Rb4 . . 34.05(19) no O5 Mo2 Rb4 . . 144.6(2) no O3 Mo2 Rb4 . . 91.46(13) no O3 Mo2 Rb4 4 . 91.46(13) no Rb1 Mo2 Rb4 3_565 . 120.637(13) no Rb1 Mo2 Rb4 . . 120.637(13) no Rb3 Mo2 Rb4 . . 81.30(2) no Rb4 Mo2 Rb4 5 . 159.21(3) no O4 Mo2 Rb3 . 5_554 120.83(19) no O5 Mo2 Rb3 . 5_554 128.6(2) no O3 Mo2 Rb3 . 5_554 57.20(13) no O3 Mo2 Rb3 4 5_554 57.20(13) no Rb1 Mo2 Rb3 3_565 5_554 109.844(16) no Rb1 Mo2 Rb3 . 5_554 109.844(16) no Rb3 Mo2 Rb3 . 5_554 168.08(3) no Rb4 Mo2 Rb3 5 5_554 72.428(18) no Rb4 Mo2 Rb3 . 5_554 86.78(2) no O6 Mo3 O7 . . 107.08(18) no O6 Mo3 O8 . . 107.1(2) no O7 Mo3 O8 . . 111.62(19) no O6 Mo3 O2 . . 109.72(16) no O7 Mo3 O2 . . 107.63(17) no O8 Mo3 O2 . . 113.47(16) no O6 Mo3 Rb4 . . 131.19(14) no O7 Mo3 Rb4 . . 52.91(13) no O8 Mo3 Rb4 . . 121.50(14) no O2 Mo3 Rb4 . . 55.73(10) no O6 Mo3 Rb3 . . 131.09(13) no O7 Mo3 Rb3 . . 67.50(13) no O8 Mo3 Rb3 . . 45.43(14) no O2 Mo3 Rb3 . . 118.30(10) no Rb4 Mo3 Rb3 . . 86.109(14) no O6 Mo3 Rb3 . 6_554 43.65(13) no O7 Mo3 Rb3 . 6_554 115.38(13) no O8 Mo3 Rb3 . 6_554 130.25(14) no O2 Mo3 Rb3 . 6_554 66.41(10) no Rb4 Mo3 Rb3 . 6_554 99.77(2) no Rb3 Mo3 Rb3 . 6_554 174.05(2) no O6 Mo3 Rb1 . 5_544 69.51(14) no O7 Mo3 Rb1 . 5_544 43.51(13) no O8 Mo3 Rb1 . 5_544 144.18(13) no O2 Mo3 Rb1 . 5_544 100.50(10) no Rb4 Mo3 Rb1 . 5_544 68.824(19) no Rb3 Mo3 Rb1 . 5_544 108.507(18) no Rb3 Mo3 Rb1 6_554 5_544 73.140(17) no O6 Mo3 Rb4 . 6 45.71(14) no O7 Mo3 Rb4 . 6 126.99(13) no O8 Mo3 Rb4 . 6 61.64(14) no O2 Mo3 Rb4 . 6 123.54(10) no Rb4 Mo3 Rb4 . 6 176.85(2) no Rb3 Mo3 Rb4 . 6 96.72(2) no Rb3 Mo3 Rb4 6_554 6 77.378(13) no Rb1 Mo3 Rb4 5_544 6 108.838(17) no O6 Mo3 Rb1 . . 105.68(14) no O7 Mo3 Rb1 . . 137.72(13) no O8 Mo3 Rb1 . . 31.67(13) no O2 Mo3 Rb1 . . 85.29(10) no Rb4 Mo3 Rb1 . . 117.433(19) no Rb3 Mo3 Rb1 . . 70.939(17) no Rb3 Mo3 Rb1 6_554 . 106.737(15) no Rb1 Mo3 Rb1 5_544 . 173.41(3) no Rb4 Mo3 Rb1 6 . 64.991(16) no O6 Mo3 Rb2 . 6 23.85(13) no O7 Mo3 Rb2 . 6 85.20(13) no O8 Mo3 Rb2 . 6 107.92(13) no O2 Mo3 Rb2 . 6 127.11(10) no Rb4 Mo3 Rb2 . 6 123.16(2) no Rb3 Mo3 Rb2 . 6 114.04(2) no Rb3 Mo3 Rb2 6_554 6 61.945(16) no Rb1 Mo3 Rb2 5_544 6 54.523(12) no Rb4 Mo3 Rb2 6 6 54.373(17) no Rb1 Mo3 Rb2 . 6 119.363(18) no Mo1 O1 Rb2 . . 158.2(2) no Mo1 O1 Rb3 . 5_554 117.03(19) no Rb2 O1 Rb3 . 5_554 84.23(10) no Mo3 O2 Mo1 . . 144.4(2) no Mo3 O2 Rb4 . . 95.18(12) no Mo1 O2 Rb4 . . 117.41(14) no Mo3 O2 Rb3 . 6_554 85.53(11) no Mo1 O2 Rb3 . 6_554 88.77(11) no Rb4 O2 Rb3 . 6_554 121.67(10) no Mo2 O3 Mo1 . . 135.9(2) no Mo2 O3 Rb1 . . 92.20(16) no Mo1 O3 Rb1 . . 109.69(13) no Mo2 O4 Rb4 . . 126.8(3) no Mo2 O4 Rb3 . . 108.2(3) no Rb4 O4 Rb3 . . 124.92(16) no Mo2 O5 Rb2 . 1_556 174.1(3) no Mo2 O5 Rb1 . 3_565 98.96(11) no Rb2 O5 Rb1 1_556 3_565 81.39(11) no Mo2 O5 Rb1 . . 98.96(11) no Rb2 O5 Rb1 1_556 . 81.39(11) no Rb1 O5 Rb1 3_565 . 161.2(2) no Mo2 O5 Rb4 . 5 99.4(3) no Rb2 O5 Rb4 1_556 5 86.55(14) no Rb1 O5 Rb4 3_565 5 85.70(11) no Rb1 O5 Rb4 . 5 85.70(11) no Mo2 O5 Rb3 . . 90.5(2) no Rb2 O5 Rb3 1_556 . 83.58(16) no Rb1 O5 Rb3 3_565 . 92.81(12) no Rb1 O5 Rb3 . . 92.81(12) no Rb4 O5 Rb3 5 . 170.13(19) no Mo3 O6 Rb2 . 6 142.0(2) no Mo3 O6 Rb3 . 6_554 112.61(17) no Rb2 O6 Rb3 6 6_554 95.02(11) no Mo3 O6 Rb4 . 6 110.55(19) no Rb2 O6 Rb4 6 6 80.53(9) no Rb3 O6 Rb4 6_554 6 111.51(12) no Mo3 O7 Rb2 . 5_545 156.9(2) no Mo3 O7 Rb1 . 5_544 112.96(17) no Rb2 O7 Rb1 5_545 5_544 82.62(9) no Mo3 O7 Rb4 . . 100.64(15) no Rb2 O7 Rb4 5_545 . 95.15(11) no Rb1 O7 Rb4 5_544 . 93.06(11) no Mo3 O8 Rb1 . . 129.91(19) no Mo3 O8 Rb3 . . 110.23(18) no Rb1 O8 Rb3 . . 107.41(13) no Mo3 O8 Rb4 . 6 92.79(15) no Rb1 O8 Rb4 . 6 86.45(10) no Rb3 O8 Rb4 . 6 131.03(12) no data_II _audit_creation_method SHELXL97 _chemical_name_systematic ; dicaesium heptaoxodimolybdate ; _chemical_name_common ? _chemical_formula_moiety 'Mo2 O7 , 2Cs' _chemical_formula_sum 'Cs2 Mo2 O7' _chemical_formula_iupac 'Cs2 Mo2 O7' _chemical_formula_weight 569.70 _chemical_melting_point ? _symmetry_cell_setting Monoclinic _symmetry_space_group_name_H-M 'P 21/c' _symmetry_space_group_name_Hall '-P 2ybc' loop_ _symmetry_equiv_pos_as_xyz 'x, y, z' '-x, y+1/2, -z+1/2' '-x, -y, -z' 'x, -y-1/2, z-1/2' _cell_length_a 15.5580(5) _cell_length_b 15.1794(5) _cell_length_c 7.2252(2) _cell_angle_alpha 90.00 _cell_angle_beta 90.0059(11) _cell_angle_gamma 90.00 _cell_volume 1706.31(9) _cell_formula_units_Z 8 _cell_measurement_reflns_used 5301 _cell_measurement_theta_min 2.42 _cell_measurement_theta_max 34.51 _cell_measurement_temperature 293(2) _exptl_crystal_description fragment _exptl_crystal_colour colourless _exptl_crystal_size_max 0.16 _exptl_crystal_size_mid 0.13 _exptl_crystal_size_min 0.10 _exptl_crystal_density_diffrn 4.435 _exptl_crystal_density_meas ? _exptl_crystal_density_method 'not measured' _exptl_crystal_F_000 2000 _exptl_absorpt_coefficient_mu 11.340 _exptl_absorpt_correction_type multi-scan _exptl_absorpt_process_details '(SADABS; Bruker, 2004)' _exptl_absorpt_correction_T_min 0.2641 _exptl_absorpt_correction_T_max 0.3968 _exptl_special_details ; ? ; _diffrn_ambient_temperature 293(2) _diffrn_radiation_type MoK\a _diffrn_radiation_wavelength 0.71073 _diffrn_radiation_source 'fine-focus sealed X-ray tube' _diffrn_radiation_monochromator graphite _diffrn_measurement_device_type 'Bruker Nonius X8 APEX CCD area-detector' _diffrn_measurement_method '\f scans, frame data integration' _diffrn_detector_area_resol_mean ? _diffrn_reflns_number 21380 _diffrn_reflns_av_R_equivalents 0.0280 _diffrn_reflns_av_sigmaI/netI 0.0353 _diffrn_reflns_theta_min 1.31 _diffrn_reflns_theta_max 36.31 _diffrn_reflns_theta_full 36.31 _diffrn_measured_fraction_theta_max 0.989 _diffrn_measured_fraction_theta_full 0.989 _diffrn_reflns_limit_h_min -25 _diffrn_reflns_limit_h_max 18 _diffrn_reflns_limit_k_min -19 _diffrn_reflns_limit_k_max 25 _diffrn_reflns_limit_l_min -12 _diffrn_reflns_limit_l_max 8 _diffrn_standards_number 0 _diffrn_standards_interval_count ? _diffrn_standards_interval_time ? _diffrn_standards_decay_% 0 _refine_special_details ; Refinement of F^2^ against ALL reflections. The weighted R-factor wR and goodness of fit S are based on F^2^, conventional R-factors R are based on F, with F set to zero for negative F^2^. The threshold expression of F^2^ > 2sigma(F^2^) is used only for calculating R-factors(gt) etc. and is not relevant to the choice of reflections for refinement. R-factors based on F^2^ are statistically about twice as large as those based on F, and R- factors based on ALL data will be even larger. ; _reflns_number_total 8167 _reflns_number_gt 7405 _reflns_threshold_expression I>2\s(I) _refine_ls_structure_factor_coef Fsqd _refine_ls_matrix_type full _refine_ls_R_factor_all 0.0330 _refine_ls_R_factor_gt 0.0282 _refine_ls_wR_factor_gt 0.0561 _refine_ls_wR_factor_ref 0.0582 _refine_ls_goodness_of_fit_ref 1.067 _refine_ls_restrained_S_all 1.067 _refine_ls_number_reflns 8167 _refine_ls_number_parameters 201 _refine_ls_number_restraints 0 _refine_ls_hydrogen_treatment . _refine_ls_weighting_scheme calc _refine_ls_weighting_details 'calc w = 1/[\s^2^(Fo^2^)+(0.009P)^2^] where P=(Fo^2^+2Fc^2^)/3' _atom_sites_solution_hydrogens . _atom_sites_solution_primary direct _atom_sites_solution_secondary difmap _refine_ls_shift/su_max 0.001 _refine_ls_shift/su_mean 0.000 _refine_diff_density_max 1.523 _refine_diff_density_min -1.475 _refine_ls_extinction_method 'SHELXL97 (Sheldrick, 1997)' _refine_ls_extinction_coef 0.00018(3) _refine_ls_extinction_expression 'Fc^*^=kFc[1+0.001xFc^2^\l^3^/sin(2\q)]^-1/4^' loop_ _atom_type_symbol _atom_type_description _atom_type_scat_dispersion_real _atom_type_scat_dispersion_imag _atom_type_scat_source 'Li' 'Li' -0.0003 0.0001 'International Tables Vol C Tables 4.2.6.8 and 6.1.1.4' 'O' 'O' 0.0106 0.0060 'International Tables Vol C Tables 4.2.6.8 and 6.1.1.4' 'Zn' 'Zn' 0.2839 1.4301 'International Tables Vol C Tables 4.2.6.8 and 6.1.1.4' 'Rb' 'Rb' -0.9393 2.9676 'International Tables Vol C Tables 4.2.6.8 and 6.1.1.4' 'Mo' 'Mo' -1.6832 0.6857 'International Tables Vol C Tables 4.2.6.8 and 6.1.1.4' _computing_data_collection 'SMART (Bruker, 2004)' _computing_cell_refinement 'SMART' _computing_data_reduction 'SAINT (Bruker, 2004)' _computing_structure_solution 'SHELXS97 (Sheldrick, 1997)' _computing_structure_refinement 'SHELXL97 (Sheldrick, 1997)' _computing_molecular_graphics 'BS (Ozawa & Kang, 2004)' _computing_publication_material 'SHELXL97' loop_ _atom_site_type_symbol _atom_site_label _atom_site_fract_x _atom_site_fract_y _atom_site_fract_z _atom_site_U_iso_or_equiv _atom_site_adp_type _atom_site_calc_flag _atom_site_refinement_flags _atom_site_occupancy _atom_site_disorder_assembly _atom_site_disorder_group Cs Cs1 0.305713(17) 0.488134(17) 0.71413(4) 0.02378(6) Uani d . 1 . . Cs Cs2 0.16855(2) 0.511854(17) 0.22599(4) 0.02549(6) Uani d . 1 . . Cs Cs3 0.05951(2) 0.317975(18) 0.71214(5) 0.03001(7) Uani d . 1 . . Cs Cs4 0.542116(19) 0.331208(18) 0.78093(5) 0.02846(6) Uani d . 1 . . Mo Mo1 0.28731(2) 0.25051(2) 0.48632(4) 0.01324(5) Uani d . 1 . . Mo Mo2 0.421384(19) 0.40626(2) 0.24720(4) 0.01540(6) Uani d . 1 . . Mo Mo3 0.226402(19) 0.75416(2) 0.50724(4) 0.01281(6) Uani d . 1 . . Mo Mo4 0.076127(19) 0.60920(2) 0.76033(4) 0.01473(6) Uani d . 1 . . O O1 0.2063(2) 0.1769(2) 0.5235(5) 0.0300(8) Uani d . 1 . . O O2 0.2317(2) 0.3463(2) 0.4408(4) 0.0248(7) Uani d . 1 . . O O3 0.31550(17) 0.21878(17) 0.2381(4) 0.0184(5) Uani d . 1 . . O O4 0.3834(2) 0.1480(2) 0.5429(4) 0.0277(8) Uani d . 1 . . O O5 0.4139(2) 0.3329(2) 0.4401(4) 0.0236(7) Uani d . 1 . . O O6 0.5267(2) 0.4371(3) 0.2068(6) 0.0511(11) Uani d . 1 . . O O7 0.3609(2) 0.5009(2) 0.2916(6) 0.0389(9) Uani d . 1 . . O O8 0.3192(2) 0.6964(2) 0.5405(5) 0.0264(7) Uani d . 1 . . O O9 0.2631(2) 0.8578(2) 0.4539(4) 0.0267(7) Uani d . 1 . . O O10 0.19872(17) 0.78356(17) 0.7593(4) 0.0178(5) Uani d . 1 . . O O11 0.1458(2) 0.6401(2) 0.5747(4) 0.0232(6) Uani d . 1 . . O O12 0.0861(2) 0.8208(2) 0.4564(4) 0.0226(6) Uani d . 1 . . O O13 -0.0284(2) 0.6175(2) 0.6776(5) 0.0321(8) Uani d . 1 . . O O14 0.0987(3) 0.50124(19) 0.8239(5) 0.0321(8) Uani d . 1 . . loop_ _atom_site_aniso_label _atom_site_aniso_U_11 _atom_site_aniso_U_22 _atom_site_aniso_U_33 _atom_site_aniso_U_12 _atom_site_aniso_U_13 _atom_site_aniso_U_23 Cs1 0.02287(11) 0.02133(11) 0.02713(13) 0.00009(9) 0.00106(11) -0.00772(10) Cs2 0.03514(13) 0.02007(11) 0.02125(12) -0.00143(10) -0.00264(12) 0.00327(10) Cs3 0.03963(15) 0.02490(13) 0.02551(14) -0.00782(11) 0.00071(13) -0.00070(11) Cs4 0.02705(12) 0.03026(13) 0.02806(13) -0.00301(10) 0.00353(12) 0.00190(12) Mo1 0.01830(12) 0.01333(12) 0.00811(12) -0.00066(14) -0.00024(11) 0.00040(10) Mo2 0.01524(12) 0.01767(13) 0.01330(15) -0.00410(10) 0.00006(12) -0.00122(11) Mo3 0.01669(12) 0.01299(12) 0.00874(13) -0.00161(13) 0.00128(12) 0.00047(10) Mo4 0.01627(12) 0.01514(13) 0.01277(14) -0.00185(10) 0.00015(12) 0.00165(11) O1 0.0359(19) 0.0309(18) 0.0232(16) -0.0178(16) 0.0004(14) -0.0006(13) O2 0.0280(17) 0.0256(16) 0.0208(15) 0.0079(13) -0.0018(13) -0.0010(12) O3 0.0313(14) 0.0162(12) 0.0076(11) 0.0009(10) -0.0004(11) 0.0005(9) O4 0.043(2) 0.0266(17) 0.0137(13) 0.0166(15) -0.0050(13) -0.0009(12) O5 0.0245(16) 0.0322(17) 0.0142(13) -0.0053(14) -0.0069(12) 0.0015(12) O6 0.0252(17) 0.087(3) 0.041(2) -0.0181(19) -0.0038(18) 0.015(2) O7 0.048(2) 0.0212(15) 0.047(2) 0.0039(14) 0.017(2) -0.0015(16) O8 0.0212(15) 0.0359(18) 0.0220(15) 0.0085(13) -0.0004(12) -0.0008(14) O9 0.039(2) 0.0215(15) 0.0193(14) -0.0109(14) 0.0072(14) -0.0003(12) O10 0.0260(13) 0.0165(12) 0.0108(12) 0.0015(10) -0.0007(11) 0.0006(10) O11 0.0326(17) 0.0208(14) 0.0162(14) -0.0089(13) 0.0061(12) -0.0016(11) O12 0.0242(15) 0.0284(16) 0.0152(13) 0.0041(13) 0.0020(11) 0.0028(11) O13 0.0212(15) 0.0427(19) 0.0323(18) -0.0049(14) -0.0093(14) -0.0029(15) O14 0.052(2) 0.0155(14) 0.0290(17) -0.0009(14) -0.0032(17) 0.0038(12) _geom_special_details ; All esds (except the esd in the dihedral angle between two l.s. planes) are estimated using the full covariance matrix. The cell esds are taken into account individually in the estimation of esds in distances, angles and torsion angles; correlations between esds in cell parameters are only used when they are defined by crystal symmetry. An approximate (isotropic) treatment of cell esds is used for estimating esds involving l.s. planes. ; loop_ _geom_bond_atom_site_label_1 _geom_bond_atom_site_label_2 _geom_bond_site_symmetry_2 _geom_bond_distance _geom_bond_publ_flag Cs1 O6 3_666 2.900(3) yes Cs1 O9 4_576 2.985(3) yes Cs1 O2 . 3.140(3) yes Cs1 O3 4_566 3.149(3) yes Cs1 O7 . 3.177(4) yes Cs1 O14 . 3.323(4) yes Cs1 O4 4_566 3.372(3) yes Cs1 O8 . 3.408(4) yes Cs1 O5 . 3.508(3) yes Cs1 O11 . 3.539(3) yes Cs1 O1 4_566 3.697(4) yes Cs1 Mo1 . 3.9751(5) no Cs2 O13 3_566 3.016(3) yes Cs2 O7 . 3.035(4) yes Cs2 O14 1_554 3.106(4) yes Cs2 O2 . 3.113(3) yes Cs2 O10 4_575 3.150(3) yes Cs2 O9 4_575 3.153(3) yes Cs2 O11 . 3.204(3) yes Cs2 O1 4_565 3.270(3) yes Cs2 O12 4_575 3.449(3) yes Cs2 Mo4 1_554 3.9458(4) no Cs2 Mo3 4_575 3.9904(4) no Cs3 O14 . 2.960(3) yes Cs3 O13 3_566 3.020(3) yes Cs3 O13 2_546 3.182(3) yes Cs3 O1 4_566 3.206(4) yes Cs3 O12 2_546 3.296(3) yes Cs3 O12 3_566 3.324(3) yes Cs3 O2 . 3.347(3) yes Cs3 O1 . 3.414(4) yes Cs3 Mo4 2_546 3.8126(4) no Cs3 Mo1 . 4.0340(5) no Cs3 Cs3 4_565 4.1605(3) no Cs3 Cs3 4_566 4.1605(3) no Cs4 O7 3_666 3.007(3) yes Cs4 O4 4_566 3.128(4) yes Cs4 O5 . 3.169(3) yes Cs4 O8 3_666 3.197(3) yes Cs4 O8 2_646 3.241(3) yes Cs4 O5 4_566 3.392(3) yes Cs4 O6 1_556 3.480(4) yes Cs4 O9 2_646 3.608(4) yes Cs4 O3 4_566 3.620(3) yes Cs4 O6 3_666 3.677(5) yes Cs4 Mo2 1_556 4.0221(5) no Cs4 Mo2 3_666 4.0305(4) no Mo1 O1 . 1.706(3) yes Mo1 O2 . 1.724(3) yes Mo1 O3 . 1.908(3) yes Mo1 O3 4_566 1.928(3) yes Mo1 O4 . 2.196(3) yes Mo1 O5 . 2.356(3) yes Mo1 Cs1 4_565 4.1318(5) no Mo1 Cs3 4_565 4.1911(5) no Mo1 Cs4 4_565 4.4110(5) no Mo2 O6 . 1.729(3) yes Mo2 O7 . 1.747(3) yes Mo2 O5 . 1.788(3) yes Mo2 O4 4_565 1.791(3) yes Mo2 Cs4 1_554 4.0221(5) no Mo2 Cs4 3_666 4.0305(4) no Mo2 Cs4 4_565 4.0719(4) no Mo2 Cs1 1_554 4.4290(4) no Mo3 O8 . 1.706(3) yes Mo3 O9 . 1.718(3) yes Mo3 O10 . 1.924(3) yes Mo3 O10 4_575 1.929(3) yes Mo3 O11 . 2.192(3) yes Mo3 O12 . 2.434(3) yes Mo3 Cs2 4_576 3.9904(4) no Mo3 Cs4 2_656 4.0840(4) no Mo3 Cs4 3_666 4.3573(4) no Mo4 O13 . 1.737(3) yes Mo4 O14 . 1.738(3) yes Mo4 O12 4_576 1.778(3) yes Mo4 O11 . 1.788(3) yes Mo4 Cs3 2_556 3.8126(4) no Mo4 Cs2 1_556 3.9458(4) no Mo4 Cs3 3_566 4.1626(5) no Mo4 Cs2 3_566 4.2281(4) no Mo4 Cs3 3_567 4.4949(5) no O1 Cs3 4_565 3.206(4) no O1 Cs2 4_566 3.270(3) no O1 Cs1 4_565 3.697(4) no O3 Mo1 4_565 1.928(3) no O3 Cs1 4_565 3.149(3) no O3 Cs4 4_565 3.620(3) no O4 Mo2 4_566 1.791(3) no O4 Cs4 4_565 3.128(4) no O4 Cs1 4_565 3.372(3) no O5 Cs4 4_565 3.392(3) no O6 Cs1 3_666 2.900(3) no O6 Cs4 1_554 3.480(4) no O6 Cs4 3_666 3.677(5) no O7 Cs4 3_666 3.007(3) no O8 Cs4 3_666 3.197(3) no O8 Cs4 2_656 3.241(3) no O9 Cs1 4_575 2.985(3) no O9 Cs2 4_576 3.153(3) no O9 Cs4 2_656 3.608(4) no O10 Mo3 4_576 1.929(3) no O10 Cs2 4_576 3.150(3) no O12 Mo4 4_575 1.778(3) no O12 Cs3 2_556 3.296(3) no O12 Cs3 3_566 3.324(3) no O12 Cs2 4_576 3.449(3) no O13 Cs2 3_566 3.016(3) no O13 Cs3 3_566 3.020(3) no O13 Cs3 2_556 3.182(3) no O14 Cs2 1_556 3.106(4) no loop_ _geom_angle_atom_site_label_1 _geom_angle_atom_site_label_2 _geom_angle_atom_site_label_3 _geom_angle_site_symmetry_1 _geom_angle_site_symmetry_3 _geom_angle _geom_angle_publ_flag O6 Cs1 O9 3_666 4_576 77.22(11) no O6 Cs1 O2 3_666 . 136.20(11) no O9 Cs1 O2 4_576 . 145.15(9) no O6 Cs1 O3 3_666 4_566 109.63(10) no O9 Cs1 O3 4_576 4_566 139.47(8) no O2 Cs1 O3 . 4_566 50.85(7) no O6 Cs1 O7 3_666 . 85.53(11) no O9 Cs1 O7 4_576 . 124.75(8) no O2 Cs1 O7 . . 62.41(9) no O3 Cs1 O7 4_566 . 95.78(7) no O6 Cs1 O14 3_666 . 143.22(10) no O9 Cs1 O14 4_576 . 66.38(9) no O2 Cs1 O14 . . 80.54(9) no O3 Cs1 O14 4_566 . 95.36(7) no O7 Cs1 O14 . . 119.19(9) no O6 Cs1 O4 3_666 4_566 77.23(10) no O9 Cs1 O4 4_576 4_566 98.66(8) no O2 Cs1 O4 . 4_566 98.88(8) no O3 Cs1 O4 4_566 4_566 48.15(7) no O7 Cs1 O4 . 4_566 128.12(9) no O14 Cs1 O4 . 4_566 102.47(9) no O6 Cs1 O8 3_666 . 69.75(10) no O9 Cs1 O8 4_576 . 60.05(9) no O2 Cs1 O8 . . 115.29(8) no O3 Cs1 O8 4_566 . 160.47(7) no O7 Cs1 O8 . . 64.72(8) no O14 Cs1 O8 . . 95.29(7) no O4 Cs1 O8 4_566 . 143.67(8) no O6 Cs1 O5 3_666 . 86.73(10) no O9 Cs1 O5 4_576 . 163.85(9) no O2 Cs1 O5 . . 50.23(8) no O3 Cs1 O5 4_566 . 48.53(7) no O7 Cs1 O5 . . 50.88(8) no O14 Cs1 O5 . . 129.78(7) no O4 Cs1 O5 4_566 . 79.28(8) no O8 Cs1 O5 . . 112.70(8) no O6 Cs1 O11 3_666 . 115.64(10) no O9 Cs1 O11 4_576 . 59.90(8) no O2 Cs1 O11 . . 90.58(7) no O3 Cs1 O11 4_566 . 134.41(7) no O7 Cs1 O11 . . 82.92(8) no O14 Cs1 O11 . . 49.28(7) no O4 Cs1 O11 4_566 . 148.40(8) no O8 Cs1 O11 . . 48.23(7) no O5 Cs1 O11 . . 127.92(7) no O6 Cs1 O1 3_666 4_566 121.49(10) no O9 Cs1 O1 4_576 4_566 94.98(8) no O2 Cs1 O1 . 4_566 76.25(9) no O3 Cs1 O1 4_566 4_566 46.46(7) no O7 Cs1 O1 . 4_566 137.36(8) no O14 Cs1 O1 . 4_566 59.38(7) no O4 Cs1 O1 4_566 4_566 46.28(8) no O8 Cs1 O1 . 4_566 151.29(7) no O5 Cs1 O1 . 4_566 94.98(7) no O11 Cs1 O1 . 4_566 108.64(7) no O6 Cs1 Mo1 3_666 . 120.09(9) no O9 Cs1 Mo1 4_576 . 159.26(7) no O2 Cs1 Mo1 . . 24.65(6) no O3 Cs1 Mo1 4_566 . 28.51(5) no O7 Cs1 Mo1 . . 71.16(6) no O14 Cs1 Mo1 . . 94.78(5) no O4 Cs1 Mo1 4_566 . 76.20(5) no O8 Cs1 Mo1 . . 133.93(6) no O5 Cs1 Mo1 . . 36.02(5) no O11 Cs1 Mo1 . . 115.03(5) no O1 Cs1 Mo1 4_566 . 66.76(6) no O13 Cs2 O7 3_566 . 129.89(9) no O13 Cs2 O14 3_566 1_554 85.94(9) no O7 Cs2 O14 . 1_554 119.24(11) no O13 Cs2 O2 3_566 . 65.62(9) no O7 Cs2 O2 . . 64.33(9) no O14 Cs2 O2 1_554 . 122.34(8) no O13 Cs2 O10 3_566 4_575 137.06(8) no O7 Cs2 O10 . 4_575 83.97(8) no O14 Cs2 O10 1_554 4_575 100.07(7) no O2 Cs2 O10 . 4_575 135.30(8) no O13 Cs2 O9 3_566 4_575 152.85(9) no O7 Cs2 O9 . 4_575 70.83(10) no O14 Cs2 O9 1_554 4_575 67.21(9) no O2 Cs2 O9 . 4_575 132.08(9) no O10 Cs2 O9 4_575 4_575 50.18(8) no O13 Cs2 O11 3_566 . 97.72(8) no O7 Cs2 O11 . . 91.10(10) no O14 Cs2 O11 1_554 . 136.76(9) no O2 Cs2 O11 . . 97.66(8) no O10 Cs2 O11 4_575 . 50.00(7) no O9 Cs2 O11 4_575 . 99.24(8) no O13 Cs2 O1 3_566 4_565 70.28(10) no O7 Cs2 O1 . 4_565 81.08(9) no O14 Cs2 O1 1_554 4_565 66.35(8) no O2 Cs2 O1 . 4_565 57.25(9) no O10 Cs2 O1 4_575 4_565 150.60(8) no O9 Cs2 O1 4_575 4_565 100.78(8) no O11 Cs2 O1 . 4_565 154.70(8) no O13 Cs2 O12 3_566 4_575 109.94(8) no O7 Cs2 O12 . 4_575 119.70(9) no O14 Cs2 O12 1_554 4_575 51.67(8) no O2 Cs2 O12 . 4_575 173.58(8) no O10 Cs2 O12 4_575 4_575 51.13(7) no O9 Cs2 O12 4_575 4_575 50.16(8) no O11 Cs2 O12 . 4_575 87.44(8) no O1 Cs2 O12 4_565 4_575 117.36(8) no O13 Cs2 Mo4 3_566 1_554 100.22(6) no O7 Cs2 Mo4 . 1_554 120.87(8) no O14 Cs2 Mo4 1_554 1_554 25.10(5) no O2 Cs2 Mo4 . 1_554 147.40(6) no O10 Cs2 Mo4 4_575 1_554 75.54(5) no O9 Cs2 Mo4 4_575 1_554 53.38(6) no O11 Cs2 Mo4 . 1_554 113.75(6) no O1 Cs2 Mo4 4_565 1_554 90.69(6) no O12 Cs2 Mo4 4_575 1_554 26.76(5) no O13 Cs2 Mo3 3_566 4_575 146.53(6) no O7 Cs2 Mo3 . 4_575 83.57(6) no O14 Cs2 Mo3 1_554 4_575 75.80(6) no O2 Cs2 Mo3 . 4_575 147.66(7) no O10 Cs2 Mo3 4_575 4_575 28.26(5) no O9 Cs2 Mo3 4_575 4_575 24.41(6) no O11 Cs2 Mo3 . 4_575 78.20(5) no O1 Cs2 Mo3 4_565 4_575 124.20(6) no O12 Cs2 Mo3 4_575 4_575 37.31(5) no Mo4 Cs2 Mo3 1_554 4_575 53.925(7) no O13 Cs2 Cs1 3_566 . 96.85(6) no O7 Cs2 Cs1 . . 49.72(8) no O14 Cs2 Cs1 1_554 . 166.70(7) no O2 Cs2 Cs1 . . 48.86(6) no O10 Cs2 Cs1 4_575 . 86.77(5) no O9 Cs2 Cs1 4_575 . 110.20(6) no O11 Cs2 Cs1 . . 55.90(6) no O1 Cs2 Cs1 4_565 . 102.27(6) no O12 Cs2 Cs1 4_575 . 137.50(5) no Mo4 Cs2 Cs1 1_554 . 161.304(9) no Mo3 Cs2 Cs1 4_575 . 107.381(9) no O14 Cs3 O13 . 3_566 89.00(9) no O14 Cs3 O13 . 2_546 149.50(9) no O13 Cs3 O13 3_566 2_546 121.26(9) no O14 Cs3 O1 . 4_566 68.85(9) no O13 Cs3 O1 3_566 4_566 139.50(9) no O13 Cs3 O1 2_546 4_566 87.47(9) no O14 Cs3 O12 . 2_546 86.06(9) no O13 Cs3 O12 3_566 2_546 124.28(8) no O13 Cs3 O12 2_546 2_546 74.09(8) no O1 Cs3 O12 4_566 2_546 88.81(8) no O14 Cs3 O12 . 3_566 146.68(9) no O13 Cs3 O12 3_566 3_566 75.80(8) no O13 Cs3 O12 2_546 3_566 51.85(8) no O1 Cs3 O12 4_566 3_566 139.26(9) no O12 Cs3 O12 2_546 3_566 78.83(8) no O14 Cs3 O2 . . 82.78(10) no O13 Cs3 O2 3_566 . 62.64(8) no O13 Cs3 O2 2_546 . 113.03(8) no O1 Cs3 O2 4_566 . 80.68(9) no O12 Cs3 O2 2_546 . 166.83(8) no O12 Cs3 O2 3_566 . 114.33(8) no O14 Cs3 O1 . . 124.11(10) no O13 Cs3 O1 3_566 . 86.46(9) no O13 Cs3 O1 2_546 . 66.54(8) no O1 Cs3 O1 4_566 . 79.58(8) no O12 Cs3 O1 2_546 . 139.25(8) no O12 Cs3 O1 3_566 . 84.95(8) no O2 Cs3 O1 . . 46.50(8) no O14 Cs3 Mo4 . 2_546 151.75(8) no O13 Cs3 Mo4 3_566 2_546 103.26(6) no O13 Cs3 Mo4 2_546 2_546 26.87(5) no O1 Cs3 Mo4 4_566 2_546 112.19(7) no O12 Cs3 Mo4 2_546 2_546 65.95(6) no O12 Cs3 Mo4 3_566 2_546 27.79(5) no O2 Cs3 Mo4 . 2_546 125.47(6) no O1 Cs3 Mo4 . 2_546 82.51(6) no O14 Cs3 Mo1 . . 99.68(8) no O13 Cs3 Mo1 3_566 . 81.13(6) no O13 Cs3 Mo1 2_546 . 89.55(6) no O1 Cs3 Mo1 4_566 . 70.39(6) no O12 Cs3 Mo1 2_546 . 154.26(6) no O12 Cs3 Mo1 3_566 . 106.83(5) no O2 Cs3 Mo1 . . 24.85(6) no O1 Cs3 Mo1 . . 24.73(6) no Mo4 Cs3 Mo1 2_546 . 107.241(10) no O14 Cs3 Cs3 . 4_565 134.66(7) no O13 Cs3 Cs3 3_566 4_565 49.55(6) no O13 Cs3 Cs3 2_546 4_565 75.11(6) no O1 Cs3 Cs3 4_566 4_565 128.41(6) no O12 Cs3 Cs3 2_546 4_565 129.59(5) no O12 Cs3 Cs3 3_566 4_565 50.77(5) no O2 Cs3 Cs3 . 4_565 63.58(6) no O1 Cs3 Cs3 . 4_565 48.87(6) no Mo4 Cs3 Cs3 2_546 4_565 68.473(9) no Mo1 Cs3 Cs3 . 4_565 61.498(7) no O14 Cs3 Cs3 . 4_566 103.26(7) no O13 Cs3 Cs3 3_566 4_566 166.01(6) no O13 Cs3 Cs3 2_546 4_566 46.24(6) no O1 Cs3 Cs3 4_566 4_566 53.33(7) no O12 Cs3 Cs3 2_546 4_566 51.35(6) no O12 Cs3 Cs3 3_566 4_566 90.22(5) no O2 Cs3 Cs3 . 4_566 124.92(5) no O1 Cs3 Cs3 . 4_566 92.04(6) no Mo4 Cs3 Cs3 2_546 4_566 62.765(9) no Mo1 Cs3 Cs3 . 4_566 103.023(8) no Cs3 Cs3 Cs3 4_565 4_566 120.527(13) no O7 Cs4 O4 3_666 4_566 114.58(9) no O7 Cs4 O5 3_666 . 100.00(10) no O4 Cs4 O5 4_566 . 88.41(9) no O7 Cs4 O8 3_666 3_666 69.28(10) no O4 Cs4 O8 4_566 3_666 170.27(8) no O5 Cs4 O8 . 3_666 82.04(8) no O7 Cs4 O8 3_666 2_646 105.69(9) no O4 Cs4 O8 4_566 2_646 110.39(9) no O5 Cs4 O8 . 2_646 137.17(9) no O8 Cs4 O8 3_666 2_646 75.95(7) no O7 Cs4 O5 3_666 4_566 167.49(9) no O4 Cs4 O5 4_566 4_566 53.45(8) no O5 Cs4 O5 . 4_566 84.20(8) no O8 Cs4 O5 3_666 4_566 123.15(8) no O8 Cs4 O5 2_646 4_566 78.06(8) no O7 Cs4 O6 3_666 1_556 78.31(10) no O4 Cs4 O6 4_566 1_556 50.49(8) no O5 Cs4 O6 . 1_556 129.79(9) no O8 Cs4 O6 3_666 1_556 138.53(8) no O8 Cs4 O6 2_646 1_556 89.16(9) no O5 Cs4 O6 4_566 1_556 89.93(8) no O7 Cs4 O9 3_666 2_646 64.93(10) no O4 Cs4 O9 4_566 2_646 109.31(8) no O5 Cs4 O9 . 2_646 160.12(8) no O8 Cs4 O9 3_666 2_646 80.42(8) no O8 Cs4 O9 2_646 2_646 45.60(8) no O5 Cs4 O9 4_566 2_646 113.35(7) no O6 Cs4 O9 1_556 2_646 62.39(7) no O7 Cs4 O3 3_666 4_566 130.64(8) no O4 Cs4 O3 4_566 4_566 45.87(7) no O5 Cs4 O3 . 4_566 47.32(7) no O8 Cs4 O3 3_666 4_566 124.58(7) no O8 Cs4 O3 2_646 4_566 123.36(7) no O5 Cs4 O3 4_566 4_566 45.74(7) no O6 Cs4 O3 1_556 4_566 96.05(7) no O9 Cs4 O3 2_646 4_566 152.50(7) no O7 Cs4 O6 3_666 3_666 48.69(9) no O4 Cs4 O6 4_566 3_666 70.05(8) no O5 Cs4 O6 . 3_666 80.08(9) no O8 Cs4 O6 3_666 3_666 109.85(9) no O8 Cs4 O6 2_646 3_666 141.99(8) no O5 Cs4 O6 4_566 3_666 121.51(8) no O6 Cs4 O6 1_556 3_666 61.11(11) no O9 Cs4 O6 2_646 3_666 97.16(8) no O3 Cs4 O6 4_566 3_666 85.35(7) no O7 Cs4 Mo2 3_666 1_556 98.07(8) no O4 Cs4 Mo2 4_566 1_556 25.26(6) no O5 Cs4 Mo2 . 1_556 110.76(6) no O8 Cs4 Mo2 3_666 1_556 163.88(6) no O8 Cs4 Mo2 2_646 1_556 98.98(6) no O5 Cs4 Mo2 4_566 1_556 69.46(5) no O6 Cs4 Mo2 1_556 1_556 25.36(6) no O9 Cs4 Mo2 2_646 1_556 85.17(5) no O3 Cs4 Mo2 4_566 1_556 71.09(4) no O6 Cs4 Mo2 3_666 1_556 64.72(6) no O7 Cs4 Mo2 3_666 3_666 23.47(7) no O4 Cs4 Mo2 4_566 3_666 92.40(6) no O5 Cs4 Mo2 . 3_666 92.39(6) no O8 Cs4 Mo2 3_666 3_666 89.89(7) no O8 Cs4 Mo2 2_646 3_666 123.40(6) no O5 Cs4 Mo2 4_566 3_666 145.68(6) no O6 Cs4 Mo2 1_556 3_666 66.27(7) no O9 Cs4 Mo2 2_646 3_666 78.32(5) no O3 Cs4 Mo2 4_566 3_666 109.89(4) no O6 Cs4 Mo2 3_666 3_666 25.40(5) no Mo2 Cs4 Mo2 1_556 3_666 80.096(9) no O1 Mo1 O2 . . 102.21(18) no O1 Mo1 O3 . . 98.78(14) no O2 Mo1 O3 . . 98.56(13) no O1 Mo1 O3 . 4_566 100.24(14) no O2 Mo1 O3 . 4_566 95.18(13) no O3 Mo1 O3 . 4_566 153.56(16) no O1 Mo1 O4 . . 90.54(17) no O2 Mo1 O4 . . 167.15(15) no O3 Mo1 O4 . . 80.77(11) no O3 Mo1 O4 4_566 . 80.85(11) no O1 Mo1 O5 . . 170.92(16) no O2 Mo1 O5 . . 86.84(14) no O3 Mo1 O5 . . 78.97(11) no O3 Mo1 O5 4_566 . 79.36(11) no O4 Mo1 O5 . . 80.43(13) no O1 Mo1 Cs1 . . 125.61(13) no O2 Mo1 Cs1 . . 49.44(11) no O3 Mo1 Cs1 . . 126.99(8) no O3 Mo1 Cs1 4_566 . 51.22(8) no O4 Mo1 Cs1 . . 121.13(9) no O5 Mo1 Cs1 . . 61.12(8) no O1 Mo1 Cs3 . . 56.85(13) no O2 Mo1 Cs3 . . 54.69(12) no O3 Mo1 Cs3 . . 130.26(8) no O3 Mo1 Cs3 4_566 . 75.92(8) no O4 Mo1 Cs3 . . 134.63(9) no O5 Mo1 Cs3 . . 131.06(8) no Cs1 Mo1 Cs3 . . 70.452(8) no O1 Mo1 Cs1 . 4_565 63.38(13) no O2 Mo1 Cs1 . 4_565 133.12(11) no O3 Mo1 Cs1 . 4_565 46.80(8) no O3 Mo1 Cs1 4_566 4_565 130.18(8) no O4 Mo1 Cs1 . 4_565 54.56(9) no O5 Mo1 Cs1 . 4_565 109.87(8) no Cs1 Mo1 Cs1 . 4_565 170.979(12) no Cs3 Mo1 Cs1 . 4_565 118.424(10) no O1 Mo1 Cs3 . 4_565 44.52(12) no O2 Mo1 Cs3 . 4_565 72.21(11) no O3 Mo1 Cs3 . 4_565 71.79(8) no O3 Mo1 Cs3 4_566 4_565 134.27(8) no O4 Mo1 Cs3 . 4_565 119.19(9) no O5 Mo1 Cs3 . 4_565 140.47(7) no Cs1 Mo1 Cs3 . 4_565 118.793(10) no Cs3 Mo1 Cs3 . 4_565 60.737(7) no Cs1 Mo1 Cs3 4_565 4_565 67.430(7) no O1 Mo1 Cs4 . 4_565 122.21(13) no O2 Mo1 Cs4 . 4_565 128.62(12) no O3 Mo1 Cs4 . 4_565 53.57(8) no O3 Mo1 Cs4 4_566 4_565 100.43(8) no O4 Mo1 Cs4 . 4_565 41.56(9) no O5 Mo1 Cs4 . 4_565 49.50(8) no Cs1 Mo1 Cs4 . 4_565 109.256(9) no Cs3 Mo1 Cs4 . 4_565 175.644(11) no Cs1 Mo1 Cs4 4_565 4_565 62.032(7) no Cs3 Mo1 Cs4 4_565 4_565 122.087(10) no O6 Mo2 O7 . . 108.57(18) no O6 Mo2 O5 . . 111.24(16) no O7 Mo2 O5 . . 109.50(17) no O6 Mo2 O4 . 4_565 107.35(19) no O7 Mo2 O4 . 4_565 110.61(19) no O5 Mo2 O4 . 4_565 109.54(14) no O6 Mo2 Cs1 . . 118.83(14) no O7 Mo2 Cs1 . . 49.50(14) no O5 Mo2 Cs1 . . 60.60(11) no O4 Mo2 Cs1 4_565 . 133.32(12) no O6 Mo2 Cs4 . 1_554 59.51(14) no O7 Mo2 Cs4 . 1_554 129.67(14) no O5 Mo2 Cs4 . 1_554 120.47(11) no O4 Mo2 Cs4 4_565 1_554 48.20(12) no Cs1 Mo2 Cs4 . 1_554 178.145(10) no O6 Mo2 Cs4 . 3_666 65.81(15) no O7 Mo2 Cs4 . 3_666 43.27(12) no O5 Mo2 Cs4 . 3_666 131.64(10) no O4 Mo2 Cs4 4_565 3_666 117.36(10) no Cs1 Mo2 Cs4 . 3_666 78.449(8) no Cs4 Mo2 Cs4 1_554 3_666 99.904(9) no O6 Mo2 Cs4 . 4_565 79.20(15) no O7 Mo2 Cs4 . 4_565 164.88(14) no O5 Mo2 Cs4 . 4_565 55.40(11) no O4 Mo2 Cs4 4_565 4_565 78.15(12) no Cs1 Mo2 Cs4 . 4_565 115.463(10) no Cs4 Mo2 Cs4 1_554 4_565 65.413(7) no Cs4 Mo2 Cs4 3_666 4_565 144.418(8) no O6 Mo2 Cs2 . . 140.26(14) no O7 Mo2 Cs2 . . 36.71(13) no O5 Mo2 Cs2 . . 101.68(11) no O4 Mo2 Cs2 4_565 . 80.69(13) no Cs1 Mo2 Cs2 . . 59.960(7) no Cs4 Mo2 Cs2 1_554 . 120.590(10) no Cs4 Mo2 Cs2 3_666 . 75.860(8) no Cs4 Mo2 Cs2 4_565 . 139.720(9) no O6 Mo2 Cs1 . 1_554 99.34(13) no O7 Mo2 Cs1 . 1_554 73.16(15) no O5 Mo2 Cs1 . 1_554 145.69(10) no O4 Mo2 Cs1 4_565 1_554 43.78(11) no Cs1 Mo2 Cs1 . 1_554 117.457(9) no Cs4 Mo2 Cs1 1_554 1_554 62.666(8) no Cs4 Mo2 Cs1 3_666 1_554 74.689(8) no Cs4 Mo2 Cs1 4_565 1_554 119.198(9) no Cs2 Mo2 Cs1 . 1_554 59.127(7) no O6 Mo2 Cs4 . . 79.34(13) no O7 Mo2 Cs4 . . 106.21(15) no O5 Mo2 Cs4 . . 35.95(10) no O4 Mo2 Cs4 4_565 . 137.56(11) no Cs1 Mo2 Cs4 . . 62.593(8) no Cs4 Mo2 Cs4 1_554 . 117.224(10) no Cs4 Mo2 Cs4 3_666 . 103.768(8) no Cs4 Mo2 Cs4 4_565 . 61.678(7) no Cs2 Mo2 Cs4 . . 121.316(9) no Cs1 Mo2 Cs4 1_554 . 178.321(9) no O8 Mo3 O9 . . 102.75(17) no O8 Mo3 O10 . . 100.10(13) no O9 Mo3 O10 . . 94.25(13) no O8 Mo3 O10 . 4_575 99.62(14) no O9 Mo3 O10 . 4_575 97.93(13) no O10 Mo3 O10 . 4_575 153.87(15) no O8 Mo3 O11 . . 92.71(15) no O9 Mo3 O11 . . 164.44(15) no O10 Mo3 O11 . . 81.06(11) no O10 Mo3 O11 4_575 . 81.05(11) no O8 Mo3 O12 . . 173.64(14) no O9 Mo3 O12 . . 83.33(14) no O10 Mo3 O12 . . 81.12(11) no O10 Mo3 O12 4_575 . 77.47(11) no O11 Mo3 O12 . . 81.29(12) no O8 Mo3 Cs2 . 4_576 126.32(12) no O9 Mo3 Cs2 . 4_576 49.33(11) no O10 Mo3 Cs2 . 4_576 50.81(8) no O10 Mo3 Cs2 4_575 4_576 125.56(8) no O11 Mo3 Cs2 . 4_576 119.07(8) no O12 Mo3 Cs2 . 4_576 59.18(8) no O8 Mo3 Cs4 . 2_656 49.30(12) no O9 Mo3 Cs4 . 2_656 61.87(12) no O10 Mo3 Cs4 . 2_656 77.07(8) no O10 Mo3 Cs4 4_575 2_656 129.03(8) no O11 Mo3 Cs4 . 2_656 130.31(9) no O12 Mo3 Cs4 . 2_656 136.77(8) no Cs2 Mo3 Cs4 4_576 2_656 78.206(8) no O8 Mo3 Cs2 . . 78.72(12) no O9 Mo3 Cs2 . . 138.39(10) no O10 Mo3 Cs2 . . 126.81(8) no O10 Mo3 Cs2 4_575 . 42.28(8) no O11 Mo3 Cs2 . . 46.33(8) no O12 Mo3 Cs2 . . 95.53(8) no Cs2 Mo3 Cs2 4_576 . 154.403(12) no Cs4 Mo3 Cs2 2_656 . 127.370(10) no O8 Mo3 Cs4 . 3_666 38.27(11) no O9 Mo3 Cs4 . 3_666 83.72(12) no O10 Mo3 Cs4 . 3_666 134.94(8) no O10 Mo3 Cs4 4_575 3_666 69.67(8) no O11 Mo3 Cs4 . 3_666 110.12(9) no O12 Mo3 Cs4 . 3_666 142.46(7) no Cs2 Mo3 Cs4 4_576 3_666 129.825(10) no Cs4 Mo3 Cs4 2_656 3_666 62.314(7) no Cs2 Mo3 Cs4 . 3_666 72.097(8) no O8 Mo3 Cs1 . . 42.01(12) no O9 Mo3 Cs1 . . 144.02(12) no O10 Mo3 Cs1 . . 87.41(8) no O10 Mo3 Cs1 4_575 . 95.96(8) no O11 Mo3 Cs1 . . 51.05(9) no O12 Mo3 Cs1 . . 132.21(8) no Cs2 Mo3 Cs1 4_576 . 137.086(10) no Cs4 Mo3 Cs1 2_656 . 83.697(8) no Cs2 Mo3 Cs1 . . 56.212(7) no Cs4 Mo3 Cs1 3_666 . 70.347(7) no O13 Mo4 O14 . . 110.39(17) no O13 Mo4 O12 . 4_576 108.17(15) no O14 Mo4 O12 . 4_576 109.63(16) no O13 Mo4 O11 . . 106.91(16) no O14 Mo4 O11 . . 108.87(17) no O12 Mo4 O11 4_576 . 112.84(14) no O13 Mo4 Cs3 . 2_556 55.89(11) no O14 Mo4 Cs3 . 2_556 151.86(13) no O12 Mo4 Cs3 4_576 2_556 60.62(11) no O11 Mo4 Cs3 . 2_556 99.02(11) no O13 Mo4 Cs2 . 1_556 131.43(12) no O14 Mo4 Cs2 . 1_556 49.31(12) no O12 Mo4 Cs2 4_576 1_556 60.85(11) no O11 Mo4 Cs2 . 1_556 121.13(11) no Cs3 Mo4 Cs2 2_556 1_556 117.933(11) no O13 Mo4 Cs1 . . 146.54(11) no O14 Mo4 Cs1 . . 54.06(13) no O12 Mo4 Cs1 4_576 . 105.17(10) no O11 Mo4 Cs1 . . 61.30(11) no Cs3 Mo4 Cs1 2_556 . 150.900(10) no Cs2 Mo4 Cs1 1_556 . 64.977(8) no O13 Mo4 Cs3 . 3_566 39.11(12) no O14 Mo4 Cs3 . 3_566 124.71(12) no O12 Mo4 Cs3 4_576 3_566 122.59(11) no O11 Mo4 Cs3 . 3_566 67.83(11) no Cs3 Mo4 Cs3 2_556 3_566 62.709(7) no Cs2 Mo4 Cs3 1_556 3_566 169.539(10) no Cs1 Mo4 Cs3 . 3_566 120.154(10) no O13 Mo4 Cs2 . 3_566 36.57(11) no O14 Mo4 Cs2 . 3_566 76.44(13) no O12 Mo4 Cs2 4_576 3_566 108.62(10) no O11 Mo4 Cs2 . 3_566 132.68(10) no Cs3 Mo4 Cs2 2_556 3_566 82.051(8) no Cs2 Mo4 Cs2 1_556 3_566 98.356(9) no Cs1 Mo4 Cs2 . 3_566 126.987(10) no Cs3 Mo4 Cs2 3_566 3_566 71.231(7) no O13 Mo4 Cs2 . . 91.65(12) no O14 Mo4 Cs2 . . 81.28(13) no O12 Mo4 Cs2 4_576 . 151.19(10) no O11 Mo4 Cs2 . . 39.42(10) no Cs3 Mo4 Cs2 2_556 . 120.565(10) no Cs2 Mo4 Cs2 1_556 . 120.395(10) no Cs1 Mo4 Cs2 . . 58.791(7) no Cs3 Mo4 Cs2 3_566 . 62.150(8) no Cs2 Mo4 Cs2 3_566 . 99.774(9) no O13 Mo4 Cs3 . . 89.49(11) no O14 Mo4 Cs3 . . 25.02(12) no O12 Mo4 Cs3 4_576 . 131.50(10) no O11 Mo4 Cs3 . . 103.75(10) no Cs3 Mo4 Cs3 2_556 . 143.046(8) no Cs2 Mo4 Cs3 1_556 . 73.462(8) no Cs1 Mo4 Cs3 . . 65.880(7) no Cs3 Mo4 Cs3 3_566 . 99.818(8) no Cs2 Mo4 Cs3 3_566 . 61.113(7) no Cs2 Mo4 Cs3 . . 67.294(7) no O13 Mo4 Cs3 . 3_567 80.46(12) no O14 Mo4 Cs3 . 3_567 95.89(13) no O12 Mo4 Cs3 4_576 3_567 38.56(10) no O11 Mo4 Cs3 . 3_567 148.93(10) no Cs3 Mo4 Cs3 2_556 3_567 59.432(7) no Cs2 Mo4 Cs3 1_556 3_567 62.622(8) no Cs1 Mo4 Cs3 . 3_567 126.759(10) no Cs3 Mo4 Cs3 3_566 3_567 113.085(10) no Cs2 Mo4 Cs3 3_566 3_567 70.385(7) no Cs2 Mo4 Cs3 . 3_567 170.159(9) no Cs3 Mo4 Cs3 . 3_567 106.493(8) no Mo1 O1 Cs3 . 4_565 113.57(16) no Mo1 O1 Cs2 . 4_566 140.98(19) no Cs3 O1 Cs2 4_565 4_566 101.97(9) no Mo1 O1 Cs3 . . 98.41(15) no Cs3 O1 Cs3 4_565 . 77.80(9) no Cs2 O1 Cs3 4_566 . 104.53(10) no Mo1 O1 Cs1 . 4_565 92.25(14) no Cs3 O1 Cs1 4_565 4_565 83.70(8) no Cs2 O1 Cs1 4_566 4_565 75.64(8) no Cs3 O1 Cs1 . 4_565 161.14(11) no Mo1 O2 Cs2 . . 159.16(17) no Mo1 O2 Cs1 . . 105.91(14) no Cs2 O2 Cs1 . . 82.87(8) no Mo1 O2 Cs3 . . 100.46(14) no Cs2 O2 Cs3 . . 98.24(9) no Cs1 O2 Cs3 . . 90.75(8) no Mo1 O3 Mo1 . 4_565 140.66(15) no Mo1 O3 Cs1 . 4_565 107.00(10) no Mo1 O3 Cs1 4_565 4_565 100.26(10) no Mo1 O3 Cs4 . 4_565 101.33(9) no Mo1 O3 Cs4 4_565 4_565 110.65(10) no Cs1 O3 Cs4 4_565 4_565 80.95(6) no Mo2 O4 Mo1 4_566 . 134.74(18) no Mo2 O4 Cs4 4_566 4_565 106.54(15) no Mo1 O4 Cs4 . 4_565 110.68(12) no Mo2 O4 Cs1 4_566 4_565 114.66(14) no Mo1 O4 Cs1 . 4_565 93.40(11) no Cs4 O4 Cs1 4_565 4_565 85.33(8) no Mo2 O5 Mo1 . . 119.72(15) no Mo2 O5 Cs4 . . 124.70(14) no Mo1 O5 Cs4 . . 114.32(11) no Mo2 O5 Cs4 . 4_565 98.89(13) no Mo1 O5 Cs4 . 4_565 98.63(10) no Cs4 O5 Cs4 . 4_565 83.53(7) no Mo2 O5 Cs1 . . 93.03(12) no Mo1 O5 Cs1 . . 82.86(9) no Cs4 O5 Cs1 . . 82.46(7) no Cs4 O5 Cs1 4_565 . 165.20(10) no Mo2 O6 Cs1 . 3_666 157.6(2) no Mo2 O6 Cs4 . 1_554 95.13(16) no Cs1 O6 Cs4 3_666 1_554 107.04(11) no Mo2 O6 Cs4 . 3_666 88.79(16) no Cs1 O6 Cs4 3_666 3_666 83.27(10) no Cs4 O6 Cs4 1_554 3_666 118.89(11) no Mo2 O7 Cs4 . 3_666 113.26(17) no Mo2 O7 Cs2 . . 123.17(17) no Cs4 O7 Cs2 3_666 . 114.90(11) no Mo2 O7 Cs1 . . 105.78(17) no Cs4 O7 Cs1 3_666 . 110.79(12) no Cs2 O7 Cs1 . . 83.50(9) no Mo3 O8 Cs4 . 3_666 122.43(15) no Mo3 O8 Cs4 . 2_656 107.17(15) no Cs4 O8 Cs4 3_666 2_656 85.58(8) no Mo3 O8 Cs1 . . 118.42(15) no Cs4 O8 Cs1 3_666 . 100.80(9) no Cs4 O8 Cs1 2_656 . 118.70(10) no Mo3 O9 Cs1 . 4_575 157.16(16) no Mo3 O9 Cs2 . 4_576 106.26(13) no Cs1 O9 Cs2 4_575 4_576 88.52(9) no Mo3 O9 Cs4 . 2_656 93.30(13) no Cs1 O9 Cs4 4_575 2_656 102.09(9) no Cs2 O9 Cs4 4_576 2_656 97.54(8) no Mo3 O10 Mo3 . 4_576 139.48(14) no Mo3 O10 Cs2 . 4_576 100.93(10) no Mo3 O10 Cs2 4_576 4_576 113.38(11) no Mo4 O11 Mo3 . . 136.14(16) no Mo4 O11 Cs2 . . 119.84(13) no Mo3 O11 Cs2 . . 104.00(10) no Mo4 O11 Cs1 . . 92.40(12) no Mo3 O11 Cs1 . . 100.15(11) no Cs2 O11 Cs1 . . 75.53(7) no Mo4 O12 Mo3 4_575 . 116.51(15) no Mo4 O12 Cs3 4_575 2_556 121.80(14) no Mo3 O12 Cs3 . 2_556 120.10(11) no Mo4 O12 Cs3 4_575 3_566 91.59(12) no Mo3 O12 Cs3 . 3_566 113.79(11) no Cs3 O12 Cs3 2_556 3_566 77.87(7) no Mo4 O12 Cs2 4_575 4_576 92.39(12) no Mo3 O12 Cs2 . 4_576 83.51(9) no Cs3 O12 Cs2 2_556 4_576 81.65(7) no Cs3 O12 Cs2 3_566 4_576 158.00(10) no Mo4 O13 Cs2 . 3_566 123.36(16) no Mo4 O13 Cs3 . 3_566 119.62(16) no Cs2 O13 Cs3 3_566 3_566 108.09(9) no Mo4 O13 Cs3 . 2_556 97.23(13) no Cs2 O13 Cs3 3_566 2_556 117.06(11) no Cs3 O13 Cs3 3_566 2_556 84.21(9) no Mo4 O14 Cs3 . . 140.61(18) no Mo4 O14 Cs2 . 1_556 105.59(14) no Cs3 O14 Cs2 . 1_556 112.08(10) no Mo4 O14 Cs1 . . 100.89(15) no Cs3 O14 Cs1 . . 94.48(10) no Cs2 O14 Cs1 1_556 . 83.51(9) no data_global _journal_date_recd_electronic 2006-03-31 _journal_date_accepted 2006-04-24 _journal_name_full 'Acta Crystallographica, Section C' _journal_year 2006 _journal_volume 62 _journal_issue 7 _journal_page_first i53 _journal_page_last i56 _journal_paper_category FI _journal_coeditor_code IZ3004 _publ_contact_author_name 'Professor Sergey F. Solodovnikov' _publ_contact_author_address ; Nikolaev Institute of Inorganic Chemistry SB Russian Academy of Sciences Academician Lavrentiev Avenue 3 Novosibirsk 630090 Russia ; _publ_contact_author_email solod@che.nsk.su _publ_contact_author_fax '+7 (383) 3309489' _publ_contact_author_phone '+7 (383) 3309466' _publ_section_title ; Rubidium dimolybdate, Rb~2~Mo~2~O~7~, and caesium dimolybdate, Cs~2~Mo~2~O~7~ ; loop_ _publ_author_name _publ_author_address 'Solodovnikova, Zoya A.' ; Nikolaev Institute of Inorganic Chemistry SB Russian Academy of Sciences Academician Lavrentiev Avenue 3 Novosibirsk 630090 Russian Federation ; 'Solodovnikov, Sergey F.' ; Nikolaev Institute of Inorganic Chemistry SB Russian Academy of Sciences Academician Lavrentiev Avenue 3 Novosibirsk 630090 Russian Federation ; _publ_section_synopsis ; Rb~2~Mo~2~O~7~ and Cs~2~Mo~2~O~7~ represent new structure types with infinite chains of linked MoO~4~ tetrahedra and MoO~6~ octahedra. The chains in Cs~2~Mo~2~O~7~ resemble those in the Na~2~Mo~2~O~7~ structure. The orthorhombic pseudosymmetry of Cs~2~Mo~2~O~7~ implies a possible high-temperature transition P2~1~/c \\rightarrow Pbca. ; ./CBFlib-0.9.2.2/doc/Cdiffrn_measurement_axis.html0000644000076500007650000000551311603702115020241 0ustar yayayaya (IUCr) CIF Definition save_diffrn_measurement_axis

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

Category DIFFRN_MEASUREMENT_AXIS

Name:
'diffrn_measurement_axis'

Description:

    Data items in the DIFFRN_MEASUREMENT_AXIS category associate
     axes with goniometers.

Category groups:
    inclusive_group
    diffrn_group
Category keys:
    _diffrn_measurement_axis.measurement_device
    _diffrn_measurement_axis.measurement_id
    _diffrn_measurement_axis.axis_id

Mandatory category: no

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/CBFlib_NOTICES.txt0000644000076500007650000017050711603702115015363 0ustar yayayaya CBFlib Notices COPYING All of the CBFlib 0.7.7 package may be distributed under the terms of the GNU General Public License (the GPL), see http://www.gnu.org/licenses/gpl.txt Alternatively most of the CBFlib 0.7.7 package may be distributed under the terms of the GNU Lesser General Public License (the LGPL), see http://www.gnu.org/licenses/lgpl.txt The portions that may be distributed under the LGPL indentified as such in the comments of the relevant files, and include the portions constituting the API, but do not include the documentation nor does it include the example programs. The documentation and examples may only be distributed under the GPL. ---------------------------------------------------------------------- ---------------------------------------------------------------------- THE FIRST ALTERNATIVE LICENSE FOR ALL OF CBFLIB (GPL) (Valid for versions of CBFlib starting with release 0.7.5) ========================== GPL STARTS HERE ================================= GNU GENERAL PUBLIC LICENSE Version 2, June 1991 Copyright (C) 1989, 1991 Free Software Foundation, Inc. 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA Everyone is permitted to copy and distribute verbatim copies of this license document, but changing it is not allowed. Preamble The licenses for most software are designed to take away your freedom to share and change it. By contrast, the GNU General Public License is intended to guarantee your freedom to share and change free software--to make sure the software is free for all its users. This General Public License applies to most of the Free Software Foundation's software and to any other program whose authors commit to using it. (Some other Free Software Foundation software is covered by the GNU Library General Public License instead.) You can apply it to your programs, too. When we speak of free software, we are referring to freedom, not price. Our General Public Licenses are designed to make sure that you have the freedom to distribute copies of free software (and charge for this service if you wish), that you receive source code or can get it if you want it, that you can change the software or use pieces of it in new free programs; and that you know you can do these things. To protect your rights, we need to make restrictions that forbid anyone to deny you these rights or to ask you to surrender the rights. These restrictions translate to certain responsibilities for you if you distribute copies of the software, or if you modify it. For example, if you distribute copies of such a program, whether gratis or for a fee, you must give the recipients all the rights that you have. You must make sure that they, too, receive or can get the source code. And you must show them these terms so they know their rights. We protect your rights with two steps: (1) copyright the software, and (2) offer you this license which gives you legal permission to copy, distribute and/or modify the software. Also, for each author's protection and ours, we want to make certain that everyone understands that there is no warranty for this free software. If the software is modified by someone else and passed on, we want its recipients to know that what they have is not the original, so that any problems introduced by others will not reflect on the original authors' reputations. Finally, any free program is threatened constantly by software patents. We wish to avoid the danger that redistributors of a free program will individually obtain patent licenses, in effect making the program proprietary. To prevent this, we have made it clear that any patent must be licensed for everyone's free use or not licensed at all. The precise terms and conditions for copying, distribution and modification follow. GNU GENERAL PUBLIC LICENSE TERMS AND CONDITIONS FOR COPYING, DISTRIBUTION AND MODIFICATION 0. This License applies to any program or other work which contains a notice placed by the copyright holder saying it may be distributed under the terms of this General Public License. The "Program", below, refers to any such program or work, and a "work based on the Program" means either the Program or any derivative work under copyright law: that is to say, a work containing the Program or a portion of it, either verbatim or with modifications and/or translated into another language. (Hereinafter, translation is included without limitation in the term "modification".) Each licensee is addressed as "you". Activities other than copying, distribution and modification are not covered by this License; they are outside its scope. The act of running the Program is not restricted, and the output from the Program is covered only if its contents constitute a work based on the Program (independent of having been made by running the Program). Whether that is true depends on what the Program does. 1. You may copy and distribute verbatim copies of the Program's source code as you receive it, in any medium, provided that you conspicuously and appropriately publish on each copy an appropriate copyright notice and disclaimer of warranty; keep intact all the notices that refer to this License and to the absence of any warranty; and give any other recipients of the Program a copy of this License along with the Program. You may charge a fee for the physical act of transferring a copy, and you may at your option offer warranty protection in exchange for a fee. 2. You may modify your copy or copies of the Program or any portion of it, thus forming a work based on the Program, and copy and distribute such modifications or work under the terms of Section 1 above, provided that you also meet all of these conditions: a) You must cause the modified files to carry prominent notices stating that you changed the files and the date of any change. b) You must cause any work that you distribute or publish, that in whole or in part contains or is derived from the Program or any part thereof, to be licensed as a whole at no charge to all third parties under the terms of this License. c) If the modified program normally reads commands interactively when run, you must cause it, when started running for such interactive use in the most ordinary way, to print or display an announcement including an appropriate copyright notice and a notice that there is no warranty (or else, saying that you provide a warranty) and that users may redistribute the program under these conditions, and telling the user how to view a copy of this License. (Exception: if the Program itself is interactive but does not normally print such an announcement, your work based on the Program is not required to print an announcement.) These requirements apply to the modified work as a whole. If identifiable sections of that work are not derived from the Program, and can be reasonably considered independent and separate works in themselves, then this License, and its terms, do not apply to those sections when you distribute them as separate works. But when you distribute the same sections as part of a whole which is a work based on the Program, the distribution of the whole must be on the terms of this License, whose permissions for other licensees extend to the entire whole, and thus to each and every part regardless of who wrote it. Thus, it is not the intent of this section to claim rights or contest your rights to work written entirely by you; rather, the intent is to exercise the right to control the distribution of derivative or collective works based on the Program. In addition, mere aggregation of another work not based on the Program with the Program (or with a work based on the Program) on a volume of a storage or distribution medium does not bring the other work under the scope of this License. 3. You may copy and distribute the Program (or a work based on it, under Section 2) in object code or executable form under the terms of Sections 1 and 2 above provided that you also do one of the following: a) Accompany it with the complete corresponding machine-readable source code, which must be distributed under the terms of Sections 1 and 2 above on a medium customarily used for software interchange; or, b) Accompany it with a written offer, valid for at least three years, to give any third party, for a charge no more than your cost of physically performing source distribution, a complete machine-readable copy of the corresponding source code, to be distributed under the terms of Sections 1 and 2 above on a medium customarily used for software interchange; or, c) Accompany it with the information you received as to the offer to distribute corresponding source code. (This alternative is allowed only for noncommercial distribution and only if you received the program in object code or executable form with such an offer, in accord with Subsection b above.) The source code for a work means the preferred form of the work for making modifications to it. For an executable work, complete source code means all the source code for all modules it contains, plus any associated interface definition files, plus the scripts used to control compilation and installation of the executable. However, as a special exception, the source code distributed need not include anything that is normally distributed (in either source or binary form) with the major components (compiler, kernel, and so on) of the operating system on which the executable runs, unless that component itself accompanies the executable. If distribution of executable or object code is made by offering access to copy from a designated place, then offering equivalent access to copy the source code from the same place counts as distribution of the source code, even though third parties are not compelled to copy the source along with the object code. 4. You may not copy, modify, sublicense, or distribute the Program except as expressly provided under this License. Any attempt otherwise to copy, modify, sublicense or distribute the Program is void, and will automatically terminate your rights under this License. However, parties who have received copies, or rights, from you under this License will not have their licenses terminated so long as such parties remain in full compliance. 5. You are not required to accept this License, since you have not signed it. However, nothing else grants you permission to modify or distribute the Program or its derivative works. These actions are prohibited by law if you do not accept this License. Therefore, by modifying or distributing the Program (or any work based on the Program), you indicate your acceptance of this License to do so, and all its terms and conditions for copying, distributing or modifying the Program or works based on it. 6. Each time you redistribute the Program (or any work based on the Program), the recipient automatically receives a license from the original licensor to copy, distribute or modify the Program subject to these terms and conditions. You may not impose any further restrictions on the recipients' exercise of the rights granted herein. You are not responsible for enforcing compliance by third parties to this License. 7. If, as a consequence of a court judgment or allegation of patent infringement or for any other reason (not limited to patent issues), conditions are imposed on you (whether by court order, agreement or otherwise) that contradict the conditions of this License, they do not excuse you from the conditions of this License. If you cannot distribute so as to satisfy simultaneously your obligations under this License and any other pertinent obligations, then as a consequence you may not distribute the Program at all. For example, if a patent license would not permit royalty-free redistribution of the Program by all those who receive copies directly or indirectly through you, then the only way you could satisfy both it and this License would be to refrain entirely from distribution of the Program. If any portion of this section is held invalid or unenforceable under any particular circumstance, the balance of the section is intended to apply and the section as a whole is intended to apply in other circumstances. It is not the purpose of this section to induce you to infringe any patents or other property right claims or to contest validity of any such claims; this section has the sole purpose of protecting the integrity of the free software distribution system, which is implemented by public license practices. Many people have made generous contributions to the wide range of software distributed through that system in reliance on consistent application of that system; it is up to the author/donor to decide if he or she is willing to distribute software through any other system and a licensee cannot impose that choice. This section is intended to make thoroughly clear what is believed to be a consequence of the rest of this License. 8. If the distribution and/or use of the Program is restricted in certain countries either by patents or by copyrighted interfaces, the original copyright holder who places the Program under this License may add an explicit geographical distribution limitation excluding those countries, so that distribution is permitted only in or among countries not thus excluded. In such case, this License incorporates the limitation as if written in the body of this License. 9. The Free Software Foundation may publish revised and/or new versions of the General Public License from time to time. Such new versions will be similar in spirit to the present version, but may differ in detail to address new problems or concerns. Each version is given a distinguishing version number. If the Program specifies a version number of this License which applies to it and "any later version", you have the option of following the terms and conditions either of that version or of any later version published by the Free Software Foundation. If the Program does not specify a version number of this License, you may choose any version ever published by the Free Software Foundation. 10. If you wish to incorporate parts of the Program into other free programs whose distribution conditions are different, write to the author to ask for permission. For software which is copyrighted by the Free Software Foundation, write to the Free Software Foundation; we sometimes make exceptions for this. Our decision will be guided by the two goals of preserving the free status of all derivatives of our free software and of promoting the sharing and reuse of software generally. NO WARRANTY 11. BECAUSE THE PROGRAM IS LICENSED FREE OF CHARGE, THERE IS NO WARRANTY FOR THE PROGRAM, TO THE EXTENT PERMITTED BY APPLICABLE LAW. EXCEPT WHEN OTHERWISE STATED IN WRITING THE COPYRIGHT HOLDERS AND/OR OTHER PARTIES PROVIDE THE PROGRAM "AS IS" WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESSED OR IMPLIED, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE. THE ENTIRE RISK AS TO THE QUALITY AND PERFORMANCE OF THE PROGRAM IS WITH YOU. SHOULD THE PROGRAM PROVE DEFECTIVE, YOU ASSUME THE COST OF ALL NECESSARY SERVICING, REPAIR OR CORRECTION. 12. IN NO EVENT UNLESS REQUIRED BY APPLICABLE LAW OR AGREED TO IN WRITING WILL ANY COPYRIGHT HOLDER, OR ANY OTHER PARTY WHO MAY MODIFY AND/OR REDISTRIBUTE THE PROGRAM AS PERMITTED ABOVE, BE LIABLE TO YOU FOR DAMAGES, INCLUDING ANY GENERAL, SPECIAL, INCIDENTAL OR CONSEQUENTIAL DAMAGES ARISING OUT OF THE USE OR INABILITY TO USE THE PROGRAM (INCLUDING BUT NOT LIMITED TO LOSS OF DATA OR DATA BEING RENDERED INACCURATE OR LOSSES SUSTAINED BY YOU OR THIRD PARTIES OR A FAILURE OF THE PROGRAM TO OPERATE WITH ANY OTHER PROGRAMS), EVEN IF SUCH HOLDER OR OTHER PARTY HAS BEEN ADVISED OF THE POSSIBILITY OF SUCH DAMAGES. END OF TERMS AND CONDITIONS How to Apply These Terms to Your New Programs If you develop a new program, and you want it to be of the greatest possible use to the public, the best way to achieve this is to make it free software which everyone can redistribute and change under these terms. To do so, attach the following notices to the program. It is safest to attach them to the start of each source file to most effectively convey the exclusion of warranty; and each file should have at least the "copyright" line and a pointer to where the full notice is found. Copyright (C) This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA Also add information on how to contact you by electronic and paper mail. If the program is interactive, make it output a short notice like this when it starts in an interactive mode: Gnomovision version 69, Copyright (C) year name of author Gnomovision comes with ABSOLUTELY NO WARRANTY; for details type `show w'. This is free software, and you are welcome to redistribute it under certain conditions; type `show c' for details. The hypothetical commands `show w' and `show c' should show the appropriate parts of the General Public License. Of course, the commands you use may be called something other than `show w' and `show c'; they could even be mouse-clicks or menu items--whatever suits your program. You should also get your employer (if you work as a programmer) or your school, if any, to sign a "copyright disclaimer" for the program, if necessary. Here is a sample; alter the names: Yoyodyne, Inc., hereby disclaims all copyright interest in the program `Gnomovision' (which makes passes at compilers) written by James Hacker. , 1 April 1989 Ty Coon, President of Vice This General Public License does not permit incorporating your program into proprietary programs. If your program is a subroutine library, you may consider it more useful to permit linking proprietary applications with the library. If this is what you want to do, use the GNU Library General Public License instead of this License. =========================== GPL ENDS HERE ================================== ---------------------------------------------------------------------- ---------------------------------------------------------------------- THE SECOND ALTERNATIVE LICENSE FOR CERTAIN PORTIONS OF CBFLIB INCLUDING THE API ITSELF, BUT NOT THE DOCUMENTATION AND NOT THE EXAMPLES (LGPL) (Valid for versions of CBFlib starting with release 0.7.5) ========================== LGPL STARTS HERE ================================ GNU LESSER GENERAL PUBLIC LICENSE Version 2.1, February 1999 Copyright (C) 1991, 1999 Free Software Foundation, Inc. 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA Everyone is permitted to copy and distribute verbatim copies of this license document, but changing it is not allowed. [This is the first released version of the Lesser GPL. It also counts as the successor of the GNU Library Public License, version 2, hence the version number 2.1.] Preamble The licenses for most software are designed to take away your freedom to share and change it. By contrast, the GNU General Public Licenses are intended to guarantee your freedom to share and change free software--to make sure the software is free for all its users. This license, the Lesser General Public License, applies to some specially designated software packages--typically libraries--of the Free Software Foundation and other authors who decide to use it. You can use it too, but we suggest you first think carefully about whether this license or the ordinary General Public License is the better strategy to use in any particular case, based on the explanations below. When we speak of free software, we are referring to freedom of use, not price. Our General Public Licenses are designed to make sure that you have the freedom to distribute copies of free software (and charge for this service if you wish); that you receive source code or can get it if you want it; that you can change the software and use pieces of it in new free programs; and that you are informed that you can do these things. To protect your rights, we need to make restrictions that forbid distributors to deny you these rights or to ask you to surrender these rights. These restrictions translate to certain responsibilities for you if you distribute copies of the library or if you modify it. For example, if you distribute copies of the library, whether gratis or for a fee, you must give the recipients all the rights that we gave you. You must make sure that they, too, receive or can get the source code. If you link other code with the library, you must provide complete object files to the recipients, so that they can relink them with the library after making changes to the library and recompiling it. And you must show them these terms so they know their rights. We protect your rights with a two-step method: (1) we copyright the library, and (2) we offer you this license, which gives you legal permission to copy, distribute and/or modify the library. To protect each distributor, we want to make it very clear that there is no warranty for the free library. Also, if the library is modified by someone else and passed on, the recipients should know that what they have is not the original version, so that the original author's reputation will not be affected by problems that might be introduced by others. Finally, software patents pose a constant threat to the existence of any free program. We wish to make sure that a company cannot effectively restrict the users of a free program by obtaining a restrictive license from a patent holder. Therefore, we insist that any patent license obtained for a version of the library must be consistent with the full freedom of use specified in this license. Most GNU software, including some libraries, is covered by the ordinary GNU General Public License. This license, the GNU Lesser General Public License, applies to certain designated libraries, and is quite different from the ordinary General Public License. We use this license for certain libraries in order to permit linking those libraries into non-free programs. When a program is linked with a library, whether statically or using a shared library, the combination of the two is legally speaking a combined work, a derivative of the original library. The ordinary General Public License therefore permits such linking only if the entire combination fits its criteria of freedom. The Lesser General Public License permits more lax criteria for linking other code with the library. We call this license the "Lesser" General Public License because it does Less to protect the user's freedom than the ordinary General Public License. It also provides other free software developers Less of an advantage over competing non-free programs. These disadvantages are the reason we use the ordinary General Public License for many libraries. However, the Lesser license provides advantages in certain special circumstances. For example, on rare occasions, there may be a special need to encourage the widest possible use of a certain library, so that it becomes a de-facto standard. To achieve this, non-free programs must be allowed to use the library. A more frequent case is that a free library does the same job as widely used non-free libraries. In this case, there is little to gain by limiting the free library to free software only, so we use the Lesser General Public License. In other cases, permission to use a particular library in non-free programs enables a greater number of people to use a large body of free software. For example, permission to use the GNU C Library in non-free programs enables many more people to use the whole GNU operating system, as well as its variant, the GNU/Linux operating system. Although the Lesser General Public License is Less protective of the users' freedom, it does ensure that the user of a program that is linked with the Library has the freedom and the wherewithal to run that program using a modified version of the Library. The precise terms and conditions for copying, distribution and modification follow. Pay close attention to the difference between a "work based on the library" and a "work that uses the library". The former contains code derived from the library, whereas the latter must be combined with the library in order to run. GNU LESSER GENERAL PUBLIC LICENSE TERMS AND CONDITIONS FOR COPYING, DISTRIBUTION AND MODIFICATION 0. This License Agreement applies to any software library or other program which contains a notice placed by the copyright holder or other authorized party saying it may be distributed under the terms of this Lesser General Public License (also called "this License"). Each licensee is addressed as "you". A "library" means a collection of software functions and/or data prepared so as to be conveniently linked with application programs (which use some of those functions and data) to form executables. The "Library", below, refers to any such software library or work which has been distributed under these terms. A "work based on the Library" means either the Library or any derivative work under copyright law: that is to say, a work containing the Library or a portion of it, either verbatim or with modifications and/or translated straightforwardly into another language. (Hereinafter, translation is included without limitation in the term "modification".) "Source code" for a work means the preferred form of the work for making modifications to it. For a library, complete source code means all the source code for all modules it contains, plus any associated interface definition files, plus the scripts used to control compilation and installation of the library. Activities other than copying, distribution and modification are not covered by this License; they are outside its scope. The act of running a program using the Library is not restricted, and output from such a program is covered only if its contents constitute a work based on the Library (independent of the use of the Library in a tool for writing it). Whether that is true depends on what the Library does and what the program that uses the Library does. 1. You may copy and distribute verbatim copies of the Library's complete source code as you receive it, in any medium, provided that you conspicuously and appropriately publish on each copy an appropriate copyright notice and disclaimer of warranty; keep intact all the notices that refer to this License and to the absence of any warranty; and distribute a copy of this License along with the Library. You may charge a fee for the physical act of transferring a copy, and you may at your option offer warranty protection in exchange for a fee. 2. You may modify your copy or copies of the Library or any portion of it, thus forming a work based on the Library, and copy and distribute such modifications or work under the terms of Section 1 above, provided that you also meet all of these conditions: a) The modified work must itself be a software library. b) You must cause the files modified to carry prominent notices stating that you changed the files and the date of any change. c) You must cause the whole of the work to be licensed at no charge to all third parties under the terms of this License. d) If a facility in the modified Library refers to a function or a table of data to be supplied by an application program that uses the facility, other than as an argument passed when the facility is invoked, then you must make a good faith effort to ensure that, in the event an application does not supply such function or table, the facility still operates, and performs whatever part of its purpose remains meaningful. (For example, a function in a library to compute square roots has a purpose that is entirely well-defined independent of the application. Therefore, Subsection 2d requires that any application-supplied function or table used by this function must be optional: if the application does not supply it, the square root function must still compute square roots.) These requirements apply to the modified work as a whole. If identifiable sections of that work are not derived from the Library, and can be reasonably considered independent and separate works in themselves, then this License, and its terms, do not apply to those sections when you distribute them as separate works. But when you distribute the same sections as part of a whole which is a work based on the Library, the distribution of the whole must be on the terms of this License, whose permissions for other licensees extend to the entire whole, and thus to each and every part regardless of who wrote it. Thus, it is not the intent of this section to claim rights or contest your rights to work written entirely by you; rather, the intent is to exercise the right to control the distribution of derivative or collective works based on the Library. In addition, mere aggregation of another work not based on the Library with the Library (or with a work based on the Library) on a volume of a storage or distribution medium does not bring the other work under the scope of this License. 3. You may opt to apply the terms of the ordinary GNU General Public License instead of this License to a given copy of the Library. To do this, you must alter all the notices that refer to this License, so that they refer to the ordinary GNU General Public License, version 2, instead of to this License. (If a newer version than version 2 of the ordinary GNU General Public License has appeared, then you can specify that version instead if you wish.) Do not make any other change in these notices. Once this change is made in a given copy, it is irreversible for that copy, so the ordinary GNU General Public License applies to all subsequent copies and derivative works made from that copy. This option is useful when you wish to copy part of the code of the Library into a program that is not a library. 4. You may copy and distribute the Library (or a portion or derivative of it, under Section 2) in object code or executable form under the terms of Sections 1 and 2 above provided that you accompany it with the complete corresponding machine-readable source code, which must be distributed under the terms of Sections 1 and 2 above on a medium customarily used for software interchange. If distribution of object code is made by offering access to copy from a designated place, then offering equivalent access to copy the source code from the same place satisfies the requirement to distribute the source code, even though third parties are not compelled to copy the source along with the object code. 5. A program that contains no derivative of any portion of the Library, but is designed to work with the Library by being compiled or linked with it, is called a "work that uses the Library". Such a work, in isolation, is not a derivative work of the Library, and therefore falls outside the scope of this License. However, linking a "work that uses the Library" with the Library creates an executable that is a derivative of the Library (because it contains portions of the Library), rather than a "work that uses the library". The executable is therefore covered by this License. Section 6 states terms for distribution of such executables. When a "work that uses the Library" uses material from a header file that is part of the Library, the object code for the work may be a derivative work of the Library even though the source code is not. Whether this is true is especially significant if the work can be linked without the Library, or if the work is itself a library. The threshold for this to be true is not precisely defined by law. If such an object file uses only numerical parameters, data structure layouts and accessors, and small macros and small inline functions (ten lines or less in length), then the use of the object file is unrestricted, regardless of whether it is legally a derivative work. (Executables containing this object code plus portions of the Library will still fall under Section 6.) Otherwise, if the work is a derivative of the Library, you may distribute the object code for the work under the terms of Section 6. Any executables containing that work also fall under Section 6, whether or not they are linked directly with the Library itself. 6. As an exception to the Sections above, you may also combine or link a "work that uses the Library" with the Library to produce a work containing portions of the Library, and distribute that work under terms of your choice, provided that the terms permit modification of the work for the customer's own use and reverse engineering for debugging such modifications. You must give prominent notice with each copy of the work that the Library is used in it and that the Library and its use are covered by this License. You must supply a copy of this License. If the work during execution displays copyright notices, you must include the copyright notice for the Library among them, as well as a reference directing the user to the copy of this License. Also, you must do one of these things: a) Accompany the work with the complete corresponding machine-readable source code for the Library including whatever changes were used in the work (which must be distributed under Sections 1 and 2 above); and, if the work is an executable linked with the Library, with the complete machine-readable "work that uses the Library", as object code and/or source code, so that the user can modify the Library and then relink to produce a modified executable containing the modified Library. (It is understood that the user who changes the contents of definitions files in the Library will not necessarily be able to recompile the application to use the modified definitions.) b) Use a suitable shared library mechanism for linking with the Library. A suitable mechanism is one that (1) uses at run time a copy of the library already present on the user's computer system, rather than copying library functions into the executable, and (2) will operate properly with a modified version of the library, if the user installs one, as long as the modified version is interface-compatible with the version that the work was made with. c) Accompany the work with a written offer, valid for at least three years, to give the same user the materials specified in Subsection 6a, above, for a charge no more than the cost of performing this distribution. d) If distribution of the work is made by offering access to copy from a designated place, offer equivalent access to copy the above specified materials from the same place. e) Verify that the user has already received a copy of these materials or that you have already sent this user a copy. For an executable, the required form of the "work that uses the Library" must include any data and utility programs needed for reproducing the executable from it. However, as a special exception, the materials to be distributed need not include anything that is normally distributed (in either source or binary form) with the major components (compiler, kernel, and so on) of the operating system on which the executable runs, unless that component itself accompanies the executable. It may happen that this requirement contradicts the license restrictions of other proprietary libraries that do not normally accompany the operating system. Such a contradiction means you cannot use both them and the Library together in an executable that you distribute. 7. You may place library facilities that are a work based on the Library side-by-side in a single library together with other library facilities not covered by this License, and distribute such a combined library, provided that the separate distribution of the work based on the Library and of the other library facilities is otherwise permitted, and provided that you do these two things: a) Accompany the combined library with a copy of the same work based on the Library, uncombined with any other library facilities. This must be distributed under the terms of the Sections above. b) Give prominent notice with the combined library of the fact that part of it is a work based on the Library, and explaining where to find the accompanying uncombined form of the same work. 8. You may not copy, modify, sublicense, link with, or distribute the Library except as expressly provided under this License. Any attempt otherwise to copy, modify, sublicense, link with, or distribute the Library is void, and will automatically terminate your rights under this License. However, parties who have received copies, or rights, from you under this License will not have their licenses terminated so long as such parties remain in full compliance. 9. You are not required to accept this License, since you have not signed it. However, nothing else grants you permission to modify or distribute the Library or its derivative works. These actions are prohibited by law if you do not accept this License. Therefore, by modifying or distributing the Library (or any work based on the Library), you indicate your acceptance of this License to do so, and all its terms and conditions for copying, distributing or modifying the Library or works based on it. 10. Each time you redistribute the Library (or any work based on the Library), the recipient automatically receives a license from the original licensor to copy, distribute, link with or modify the Library subject to these terms and conditions. You may not impose any further restrictions on the recipients' exercise of the rights granted herein. You are not responsible for enforcing compliance by third parties with this License. 11. If, as a consequence of a court judgment or allegation of patent infringement or for any other reason (not limited to patent issues), conditions are imposed on you (whether by court order, agreement or otherwise) that contradict the conditions of this License, they do not excuse you from the conditions of this License. If you cannot distribute so as to satisfy simultaneously your obligations under this License and any other pertinent obligations, then as a consequence you may not distribute the Library at all. For example, if a patent license would not permit royalty-free redistribution of the Library by all those who receive copies directly or indirectly through you, then the only way you could satisfy both it and this License would be to refrain entirely from distribution of the Library. If any portion of this section is held invalid or unenforceable under any particular circumstance, the balance of the section is intended to apply, and the section as a whole is intended to apply in other circumstances. It is not the purpose of this section to induce you to infringe any patents or other property right claims or to contest validity of any such claims; this section has the sole purpose of protecting the integrity of the free software distribution system which is implemented by public license practices. Many people have made generous contributions to the wide range of software distributed through that system in reliance on consistent application of that system; it is up to the author/donor to decide if he or she is willing to distribute software through any other system and a licensee cannot impose that choice. This section is intended to make thoroughly clear what is believed to be a consequence of the rest of this License. 12. If the distribution and/or use of the Library is restricted in certain countries either by patents or by copyrighted interfaces, the original copyright holder who places the Library under this License may add an explicit geographical distribution limitation excluding those countries, so that distribution is permitted only in or among countries not thus excluded. In such case, this License incorporates the limitation as if written in the body of this License. 13. The Free Software Foundation may publish revised and/or new versions of the Lesser General Public License from time to time. Such new versions will be similar in spirit to the present version, but may differ in detail to address new problems or concerns. Each version is given a distinguishing version number. If the Library specifies a version number of this License which applies to it and "any later version", you have the option of following the terms and conditions either of that version or of any later version published by the Free Software Foundation. If the Library does not specify a license version number, you may choose any version ever published by the Free Software Foundation. 14. If you wish to incorporate parts of the Library into other free programs whose distribution conditions are incompatible with these, write to the author to ask for permission. For software which is copyrighted by the Free Software Foundation, write to the Free Software Foundation; we sometimes make exceptions for this. Our decision will be guided by the two goals of preserving the free status of all derivatives of our free software and of promoting the sharing and reuse of software generally. NO WARRANTY 15. BECAUSE THE LIBRARY IS LICENSED FREE OF CHARGE, THERE IS NO WARRANTY FOR THE LIBRARY, TO THE EXTENT PERMITTED BY APPLICABLE LAW. EXCEPT WHEN OTHERWISE STATED IN WRITING THE COPYRIGHT HOLDERS AND/OR OTHER PARTIES PROVIDE THE LIBRARY "AS IS" WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESSED OR IMPLIED, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE. THE ENTIRE RISK AS TO THE QUALITY AND PERFORMANCE OF THE LIBRARY IS WITH YOU. SHOULD THE LIBRARY PROVE DEFECTIVE, YOU ASSUME THE COST OF ALL NECESSARY SERVICING, REPAIR OR CORRECTION. 16. IN NO EVENT UNLESS REQUIRED BY APPLICABLE LAW OR AGREED TO IN WRITING WILL ANY COPYRIGHT HOLDER, OR ANY OTHER PARTY WHO MAY MODIFY AND/OR REDISTRIBUTE THE LIBRARY AS PERMITTED ABOVE, BE LIABLE TO YOU FOR DAMAGES, INCLUDING ANY GENERAL, SPECIAL, INCIDENTAL OR CONSEQUENTIAL DAMAGES ARISING OUT OF THE USE OR INABILITY TO USE THE LIBRARY (INCLUDING BUT NOT LIMITED TO LOSS OF DATA OR DATA BEING RENDERED INACCURATE OR LOSSES SUSTAINED BY YOU OR THIRD PARTIES OR A FAILURE OF THE LIBRARY TO OPERATE WITH ANY OTHER SOFTWARE), EVEN IF SUCH HOLDER OR OTHER PARTY HAS BEEN ADVISED OF THE POSSIBILITY OF SUCH DAMAGES. END OF TERMS AND CONDITIONS How to Apply These Terms to Your New Libraries If you develop a new library, and you want it to be of the greatest possible use to the public, we recommend making it free software that everyone can redistribute and change. You can do so by permitting redistribution under these terms (or, alternatively, under the terms of the ordinary General Public License). To apply these terms, attach the following notices to the library. It is safest to attach them to the start of each source file to most effectively convey the exclusion of warranty; and each file should have at least the "copyright" line and a pointer to where the full notice is found. Copyright (C) This library is free software; you can redistribute it and/or modify it under the terms of the GNU Lesser General Public License as published by the Free Software Foundation; either version 2.1 of the License, or (at your option) any later version. This library is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public License for more details. You should have received a copy of the GNU Lesser General Public License along with this library; if not, write to the Free Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA Also add information on how to contact you by electronic and paper mail. You should also get your employer (if you work as a programmer) or your school, if any, to sign a "copyright disclaimer" for the library, if necessary. Here is a sample; alter the names: Yoyodyne, Inc., hereby disclaims all copyright interest in the library `Frob' (a library for tweaking knobs) written by James Random Hacker. , 1 April 1990 Ty Coon, President of Vice That's all there is to it! =========================== LGPL ENDS HERE ================================= The following notice applies to this work as a whole and to the works included within it: * Creative endeavors depend on the lively exchange of ideas. There are laws and customs which establish rights and responsibilities for authors and the users of what authors create. This notice is not intended to prevent you from using the software and documents in this package, but to ensure that there are no misunderstandings about terms and conditions of such use. * Please read the following notice carefully. If you do not understand any portion of this notice, please seek appropriate professional legal advice before making use of the software and documents included in this software package. In addition to whatever other steps you may be obliged to take to respect the intellectual property rights of the various parties involved, if you do make use of the software and documents in this package, please give credit where credit is due by citing this package, its authors and the URL or other source from which you obtained it, or equivalent primary references in the literature with the same authors. * Some of the software and documents included within this software package are the intellectual property of various parties, and placement in this package does not in any way imply that any such rights have in any way been waived or diminished. * With respect to any software or documents for which a copyright exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * Even though the authors of the various documents and software found here have made a good faith effort to ensure that the documents are correct and that the software performs according to its documentation, and we would greatly appreciate hearing of any problems you may encounter, the programs and documents any files created by the programs are provided **AS IS** without any warranty as to correctness, merchantability or fitness for any particular or general use. * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE PROGRAMS OR DOCUMENTS. ---------------------------------------------------------------------- ---------------------------------------------------------------------- Stanford University Notices for the CBFlib software package that incorporates SLAC software on which copyright is disclaimed This software The term 'this software', as used in these Notices, refers to those portions of the software package CBFlib that were created by employees of the Stanford Linear Accelerator Center, Stanford University. Stanford disclaimer of copyright Stanford University, owner of the copyright, hereby disclaims its copyright and all other rights in this software. Hence, anyone may freely use it for any purpose without restriction. Acknowledgement of sponsorship This software was produced by the Stanford Linear Accelerator Center, Stanford University, under Contract DE-AC03-76SFO0515 with the Department of Energy. Government disclaimer of liability Neither the United States nor the United States Department of Energy, nor any of their employees, makes any warranty, express or implied, or assumes any legal liability or responsibility for the accuracy, completeness, or usefulness of any data, apparatus, product, or process disclosed, or represents that its use would not infringe privately owned rights. Stanford disclaimer of liability Stanford University makes no representations or warranties, express or implied, nor assumes any liability for the use of this software. Maintenance of notices In the interest of clarity regarding the origin and status of this software, this and all the preceding Stanford University notices are to remain affixed to any copy or derivative of this software made or distributed by the recipient and are to be affixed to any copy of software made or distributed by the recipient that contains a copy or derivative of this software. Based on SLAC Software Notices, Set 4 OTT.002a, 2004 FEB 03 ---------------------------------------------------------------------- ---------------------------------------------------------------------- The IUCr Policy for the Protection and the Promotion of the STAR File and CIF Standards for Exchanging and Archiving Electronic Data Overview The Crystallographic Information File (CIF)[1] is a standard for information interchange promulgated by the International Union of Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the recommended method for submitting publications to Acta Crystallographica Section C and reports of crystal structure determinations to other sections of Acta Crystallographica and many other journals. The syntax of a CIF is a subset of the more general STAR File[2] format. The CIF and STAR File approaches are used increasingly in the structural sciences for data exchange and archiving, and are having a significant influence on these activities in other fields. Statement of intent The IUCr's interest in the STAR File is as a general data interchange standard for science, and its interest in the CIF, a conformant derivative of the STAR File, is as a concise data exchange and archival standard for crystallography and structural science. Protection of the standards To protect the STAR File and the CIF as standards for interchanging and archiving electronic data, the IUCr, on behalf of the scientific community, * holds the copyrights on the standards themselves, * owns the associated trademarks and service marks, and * holds a patent on the STAR File. These intellectual property rights relate solely to the interchange formats, not to the data contained therein, nor to the software used in the generation, access or manipulation of the data. Promotion of the standards The sole requirement that the IUCr, in its protective role, imposes on software purporting to process STAR File or CIF data is that the following conditions be met prior to sale or distribution. * Software claiming to read files written to either the STAR File or the CIF standard must be able to extract the pertinent data from a file conformant to the STAR File syntax, or the CIF syntax, respectively. * Software claiming to write files in either the STAR File, or the CIF, standard must produce files that are conformant to the STAR File syntax, or the CIF syntax, respectively. * Software claiming to read definitions from a specific data dictionary approved by the IUCr must be able to extract any pertinent definition which is conformant to the dictionary definition language (DDL)[3] associated with that dictionary. The IUCr, through its Committee on CIF Standards, will assist any developer to verify that software meets these conformance conditions. Glossary of terms [1] CIF: is a data file conformant to the file syntax defined at http://www.iucr.org/iucr-top/cif/spec/index.html [2] STAR File: is a data file conformant to the file syntax defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html [3] DDL: is a language used in a data dictionary to define data items in terms of "attributes". Dictionaries currently approved by the IUCr, and the DDL versions used to construct these dictionaries, are listed at http://www.iucr.org/iucr-top/cif/spec/ddl/index.html Last modified: 30 September 2000 IUCr Policy Copyright (C) 2000 International Union of Crystallography ---------------------------------------------------------------------- ---------------------------------------------------------------------- CBFlib V0.1 Notice The following Diclaimer Notice applies to CBFlib V0.1, from which this version is derived. * The items furnished herewith were developed under the sponsorship of the U.S. Government. Neither the U.S., nor the U.S. D.O.E., nor the Leland Stanford Junior University, nor their employees, makes any warranty, express or implied, or assumes any liability or responsibility for accuracy, completeness or usefulness of any information, apparatus, product or process disclosed, or represents that its use will not infringe privately-owned rights. Mention of any product, its manufacturer, or suppliers shall not, nor is it intended to, imply approval, disapproval, or fitness for any particular use. The U.S. and the University at all times retain the right to use and disseminate the furnished items for any purpose whatsoever. * Notice 91 02 01 ---------------------------------------------------------------------- ---------------------------------------------------------------------- CIFPARSE notice Portions of this software are loosely based on the CIFPARSE software package from the NDB at Rutgers university (see http://ndbserver.rutgers.edu/NDB/mmcif/software). CIFPARSE is part of the NDBQUERY application, a program component of the Nucleic Acid Database Project [ H. M. Berman, W. K. Olson, D. L. Beveridge, J. K. Westbrook, A. Gelbin, T. Demeny, S. H. Shieh, A. R. Srinivasan, and B. Schneider. (1992). The Nucleic Acid Database: A Comprehensive Relational Database of Three-Dimensional Structures of Nucleic Acids. Biophys J., 63, 751-759.], whose cooperation is gratefully acknowledged, especially in the form of design concepts created by J. Westbrook. Please be aware of the following notice in the CIFPARSE API: * This software is provided WITHOUT WARRANTY OF MERCHANTABILITY OR FITNESS FOR A PARTICULAR PURPOSE OR ANY OTHER WARRANTY, EXPRESS OR IMPLIED. RUTGERS MAKE NO REPRESENTATION OR WARRANTY THAT THE SOFTWARE WILL NOT INFRINGE ANY PATENT, COPYRIGHT OR OTHER PROPRIETARY RIGHT. ---------------------------------------------------------------------- ---------------------------------------------------------------------- MPACK notice Portions of this library are adapted from the "mpack/munpack version 1.5" routines, written by John G. Myers. Mpack and munpack are utilities for encoding and decoding (respectively) binary files in MIME (Multipurpose Internet Mail Extensions) format mail messages. The mpack software used is (C) Copyright 1993,1994 by Carnegie Mellon University, All Rights Reserved, and is subject to the following notice: * Permission to use, copy, modify, distribute, and sell this software and its documentation for any purpose is hereby granted without fee, provided that the above copyright notice appear in all copies and that both that copyright notice and this permission notice appear in supporting documentation, and that the name of Carnegie Mellon University not be used in advertising or publicity pertaining to distribution of the software without specific, written prior permission. Carnegie Mellon University makes no representations about the suitability of this software for any purpose. It is provided "as is" without express or implied warranty. * CARNEGIE MELLON UNIVERSITY DISCLAIMS ALL WARRANTIES WITH REGARD TO THIS SOFTWARE, INCLUDING ALL IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS, IN NO EVENT SHALL CARNEGIE MELLON UNIVERSITY BE LIABLE FOR ANY SPECIAL, INDIRECT OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. ---------------------------------------------------------------------- ---------------------------------------------------------------------- MD5 Notice The following notice applies to the message digest software in md5.h and md5.c which are optionally used by this library. To that extent, this library is a work "derived from the RSA Data Security, Inc. MD5 Message-Digest Algorithm". The software in md5.h and md5.c is Copyright (C) 1991-2, RSA Data Security, Inc. Created 1991. All rights reserved, and is subject to the following notice: * License to copy and use this software is granted provided that it is identified as the "RSA Data Security, Inc. MD5 Message-Digest Algorithm" in all material mentioning or referencing this software or this function. * License is also granted to make and use derivative works provided that such works are identified as "derived from the RSA Data Security, Inc. MD5 Message-Digest Algorithm" in all material mentioning or referencing the derived work. * RSA Data Security, Inc. makes no representations concerning either the merchantability of this software or the suitability of this software for any particular purpose. It is provided "as is" without express or implied warranty of any kind. * These notices must be retained in any copies of any part of this documentation and/or software. ---------------------------------------------------------------------- ---------------------------------------------------------------------- CCP4 Packed Compression Notice The CBF_PACKED and CBF_PACKED_V2 compression and decompression code incorporated in CBFlib is derived in large part from the J. P. Abrahams pack_c.c compression code in CCP4. This code is incorporated in CBFlib under the GPL and the LGPL with both the permission Jan Pieter Abrahams, the original author of pack_c.c (email from Jan Pieter Abrahams of 15 January 2007) and of the CCP4 project (email from Martyn Winn on 12 January 2007). The cooperation of J. P. Abrahams and of the CCP4 project is gratefully acknowledged. ---------------------------------------------------------------------- ---------------------------------------------------------------------- Updated 7 April 2007. yaya@bernstein-plus-sons.com ./CBFlib-0.9.2.2/doc/Carray_element_size.html0000644000076500007650000000626611603702115017227 0ustar yayayaya (IUCr) CIF Definition save_array_element_size

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

Category ARRAY_ELEMENT_SIZE

Name:
'array_element_size'

Description:

    Data items in the ARRAY_ELEMENT_SIZE category record the physical
     size of array elements along each array dimension.

Example:

Example 1 - A regular 2D array with a uniform element dimension of 1220 nanometres.
 
        loop_
       _array_element_size.array_id
       _array_element_size.index
       _array_element_size.size
        image_1   1    1.22e-6
        image_1   2    1.22e-6



Category groups:
    inclusive_group
    array_data_group
Category keys:
    _array_element_size.array_id
    _array_element_size.index

Mandatory category: no

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_scan_axis.reference_displacement.html0000644000076500007650000000660511603702115023336 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan_axis.reference_displacement

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_scan_axis.reference_displacement

Name:
'_diffrn_scan_axis.reference_displacement'

Definition:

        The setting of the specified axis in millimetres
               against which measurements of the reference beam center
               and reference detector distance should be made.

               In general, this will agree with
               _diffrn_scan_frame_axis.reference_displacement.

               If the individual frame values vary, then the value of
               _diffrn_scan_axis.reference_displacement will be
               representative of the ensemble of values of
               _diffrn_scan_frame_axis.reference_displacement (e.g.
               the mean).

               If not specified, the value defaults to to the value of
               _diffrn_scan_axis.displacement.

Type: float

Mandatory item: implicit

Category: diffrn_scan_axis

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Imap_segment.id.html0000644000076500007650000000500511603702115016234 0ustar yayayaya (IUCr) CIF Definition save__map_segment.id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_map_segment.id

Name:
'_map_segment.id'

Definition:

       The value of _map_segment.id must uniquely
              identify each segment of a map.

Type: code

Mandatory item: yes

Category: map_segment

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Cdiffrn_measurement.html0000644000076500007650000001006111603702115017207 0ustar yayayaya (IUCr) CIF Definition save_diffrn_measurement

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

Category DIFFRN_MEASUREMENT

Name:
'diffrn_measurement'

Description:

        Data items in the DIFFRN_MEASUREMENT category record details
               about the device used to orient and/or position the crystal
               during data measurement and the manner in which the
               diffraction data were measured.

Examples:

Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP
 
    _diffrn_measurement.diffrn_id          'd1'
    _diffrn_measurement.device             '3-circle camera'
    _diffrn_measurement.device_type        'Supper model X'
    _diffrn_measurement.device_details     'none'
    _diffrn_measurement.method             'omega scan'
    _diffrn_measurement.details
    ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector
      angle 22.5 degrees
    ;



Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277].
 
    _diffrn_measurement.diffrn_id       's1'
    _diffrn_measurement.device_type     'Philips PW1100/20 diffractometer'
    _diffrn_measurement.method          'theta/2theta (\q/2\q)'



Category groups:
    inclusive_group
    diffrn_group
Category keys:
    _diffrn_measurement.device
    _diffrn_measurement.diffrn_id
    _diffrn_measurement.id

Mandatory category: no

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Iarray_data.header_contents.html0000644000076500007650000000572011603702115020621 0ustar yayayaya (IUCr) CIF Definition save__array_data.header_contents

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_array_data.header_contents

Name:
'_array_data.header_contents'

Definition:

       This item is an text field for use in minimal CBF files to carry
              essential header information to be kept with image data
              in _array_data.data when the tags that normally carry the
              structured metadata for the image have not been populated.

              Normally this data item should not appear when the full set
              of tags have been populated and _diffrn_data_frame.details
              appears.

Type: text

Mandatory item: no

Category: array_data

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Iarray_data.header_convention.html0000644000076500007650000000575111603702115021152 0ustar yayayaya (IUCr) CIF Definition save__array_data.header_convention

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_array_data.header_convention

Name:
'_array_data.header_convention'

Definition:

       This item is an identifier for the convention followed in
              constructing the contents of _array_data.header_contents

              The permitted values are of the of an image creator identifier
              followed by an underscore and a version string.  To avoid
              confusion about conventions, all creator identifiers
              should be registered with the IUCr and the conventions
              for all identifiers and versions should be posted on
              the MEDSBIO.org web site.

Type: code

Mandatory item: no

Category: array_data

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_detector_element.reference_center_slow.html0000644000076500007650000000717111603702115024563 0ustar yayayaya (IUCr) CIF Definition save__diffrn_detector_element.reference_center_slow

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_detector_element.reference_center_slow

Name:
'_diffrn_detector_element.reference_center_slow'

Definition:

       The value of _diffrn_detector_element.reference_center_slow is
              the slow index axis beam center position relative to the detector
              element face in the units specified in the data item
              '_diffrn_detector_element.reference_center_units' along the slow
              axis of the detector from the center of the first pixel to
              the point at which the Z-axis (which should be colinear with the
              beam) intersects the face of the detector, if in fact is does.
              At the time of the measurement all settings of the detector
              positioner should be at their reference settings.  If more than
              one reference setting has been used the value givien whould be
              representive of the beam center as determined from the ensemble
              of settings.

              It is important to note that the sense of the axis is used,
              rather than the sign of the pixel-to-pixel increments.


Type: float

Mandatory item: no

Category: diffrn_detector_element

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Imap.entry_id.html0000644000076500007650000000466011603702115015741 0ustar yayayaya (IUCr) CIF Definition save__map.entry_id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_map.entry_id

Name:
'_map.entry_id'

Definition:

       This item is a pointer to _entry.id in the
              ENTRY category.

Type: code

Mandatory item: implicit

Category: map

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_scan_axis.angle_start.html0000644000076500007650000000501211603702115021142 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan_axis.angle_start

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_scan_axis.angle_start

Name:
'_diffrn_scan_axis.angle_start'

Definition:

        The starting position for the specified axis in degrees.

Type: float

Mandatory item: no


Enumeration default: 0.0

Category: diffrn_scan_axis

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_scan_axis.displacement_start.html0000644000076500007650000000504311603702115022530 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan_axis.displacement_start

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_scan_axis.displacement_start

Name:
'_diffrn_scan_axis.displacement_start'

Definition:

        The starting position for the specified axis in millimetres.

Type: float

Mandatory item: no


Enumeration default: 0.0

Category: diffrn_scan_axis

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/cif_img_1.4_4Jul06.pdf0000644000076500007650000120430411603702115016065 0ustar yayayaya%PDF-1.4 %âãÏÓ 1 0 obj 65 endobj 2 0 obj << /Length 1 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»år¹äÍB–È endstream endobj 3 0 obj << /Type /Page /Parent 4 0 R /Resources 5 0 R /Contents 2 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 4 0 obj << /Type /Pages /Parent 222 0 R /Count 6 /Kids [ 3 0 R 21 0 R 30 0 R 37 0 R 44 0 R 51 0 R ] >> endobj 5 0 obj << /ProcSet [ /PDF ] /XObject << /Fm1 6 0 R >> >> endobj 6 0 obj << /Length 7 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 8 0 R /Filter /FlateDecode >> stream xÚ­}kw·‘èwü Þì%+voÀ¹9çJ²´Qù%f³>ë{|FÃ&9ñpFžJÖþú­BÏèîÂtƒ´Ï±h±Q.Ôõøõâû‹_/^^]pQyË/jøwÿ£Pu%¿°ÒWÂê‹«û‹?¾áüþâêæâ™ªLõû‹«±×WÄzŠxù³Åýí«·opÕE¼ŠE«dí+éu²ìz3»ÙõVÅï’°W+%‹W}:³ÂVµóÉ{šÍv±^ýžå–9UqŸ.㕊_Uâý¤ðã·ºª¥½°ÜVRÛ‘âˆÈ—ÑbWq-ÃûÂOŒ;QI¥â¥Ï~ì½ì"~™—•“ÑöìEv¨ye¼K^Qe¿GÔðdnê»ü;8~†gùw¤+låuúŽ¿DäÖAÔ…ºrB$Ï¿È VHQ žÂG?!༽± ^³ÏyYdžþëîó,z^ËJÔé)üƒ¯=üy„Ïðù÷¹ç ЭKñó÷Ü~Œ¯ŒñùýÇðƹrÉ~ò„*¯:ü=ÎÙv½€¸ÑV6ž/n @[‚.û ^èÞѺ€ç”²‡ç/æ÷ø÷€qçˆî/Àsžÿbyñ|Ø!²ƒmJs³÷?¯…×µ:õÂKƒÇ”}Ýñº-à©ÕV$¯‹ÃÓ×bå"~ÿºèë<Èp.b¤þñ< 㯿~÷îÝ?ößÎ5xbÜ -ÿzV”¬mü¹A°öýA&Vw»ûe•£W®‚Óãì}³ºÎQ,øUâxÉ|}߬vÛ,Íntú&Yçi^g¸c{â²½\þ¿ÅÃ|“*µ©—‡µ­!<#PÀÂG-¸ÍhS¾®;(~~¾Ø-V·¹]™ìQG_´»k²º\Xd è5ŸrÛ xÎ&Ï·b®ÊŠ`0ê@fK`–ºÕ@¯f»æv½ù’[åyÅ%È hÙí&«TAΞ,X?|[¬KÅ‘ïFmf›ÍìKŸ¿À>P‡%l’(‰6 ˆ”¨Ï÷`‚>Ÿífý·9 fw|ßÑÅhY"€)Dü¥€LÀN9le/e²Ï-{ÒàÇ*8êø5ëÍ¢Étlx´£E»»Ù.ÇMð9hfÇK®›í|³ø38„@7;9ïô‡¨J×ÈTÉ'áIU#$K­+]óö5¿‘Êz¤f~ùþÁ1ÄĆԠ­ð÷ñûˆÃ nºfÔáºÃ6áp]òžp¸íF®L–P‡›˜ÈíöÖs'+m%ŒI¾§ÙŽ8W ’Ik¹7Âo2¾GˆàÁ×Ç+n6«>—ƒ%=÷Ï•K$àÌB¸8B¼ÅˆI6YrŽX •¢""ŠË…’ÉçäáÈå||žS³›-–ÛœöÐ`Áë뛽ôxu烲s´mz< ýôW ØÖ¼C?³ùeît F¯ö­ŽÞe}DÆA{á’%YI¦¨Eô<{öÛÇf³@­êS÷o€Êk£ûbÎÈÃíÐwo½ÁõÁåèœÕ5þ>ú-]eë®®/.kû5 X;HÐ`qjøSƒ‘fð{â°Ç‹~8F'fx-$Á:Nâ)?AåਃµxXS, Ð%å`¾àtÞýõÆó >öñPF=ïq;ÉóWz5è=eûð‰ý€]káà5¸òž̴½#òud7 ÉDSYðý¢ÅÏ»æ~›c!ØŸé’,ÿ€qæp¼ ¨ Ã‚ðÍS#‹ŸgÈ~¤W ¥ S ¨ãYþMw¯,=ÔˆàÅÕ‹œ¹híÒïšçÁ%¼×³xÉC_ÛªÎ[f›æŒ¬öl÷Du`Cž~Çz*auy–ì˜rçàëä( ®.¢çoÚ Á6¾»CÄÏgõY])éâç¬W¸5à —°ÄÍt A+¿$f—Á+ˆ t¸¢%5}“°7©Ó7e#™ZVÔG_2±°€óxÁ0õ²“†vI¤C¼){“óÍÖÆ¼s| Ó !¶ ú|̈uN†eºîÄÆï¯~øÇ««üð:'£e¦»ã/BÅ c4.VóåÃvñ©ù¹5~¹„ƒz®–•‘?ø32ÉϱéÌV<|zÿP†ðÅúøŠVÄ‹—ü’y>$–€­?ßd¾Ç”T`1ÄÏ9E÷-¬ý t¿3,D$}ÂgÕþ¸ˆdën€y¥ÁàÓ•ò­aCø°XÍ61ˆSˆ÷p…p'Ë0XM 2„ô§¿:ÚMÈ_¬ËÑ d¹±®ý}üš×¿Íî?.IÅÎàåàMêxù3N V'X&ñפ8l L&Ë[R½J/ÊÒ­®0/ -Ø‚U&¿ÿVjCÞ¢fáÉ’íÝúóЖXkŒ0—Mºb÷y1“€¤ÜqSA¼¶@/Ñ<¼"Rx¬¿LáÒ–ë9ýç*§Yüü/IÐ }<%èœ[Cl‚Ã~Tz?Ii6äA !Â{r;zC ”µÉãë}ÌBßîS}žÑt'ЦïœÀ|}ÿqCïÈÁŠ„RÙ³f»Ml‡t¦ð !”Z—(ú<­ëp|Î:È °G÷ϲ{õòÍ@ÐÆWì‘ÜžÈÝÄÁ `~nîÕ‹o¾ýæí«'¿ˆ [Y¶ñª<’ÑÅu’³xEÓ½;î²°«°ÉKfK ôìîîiz]jeºµÙꚦ—È“çi±’C^Ãééz3ÁŽK7Ûfµ .vX"”Yú™ @¬’ µdˆ ]Q§HýmvÝÌ÷³%)¥Œ)°^ Æ ;4ŒFW,^q•Ù–ÃKr—¾¡;¤øsÒ+‘¬ ÅOÄ JÏÙšW®æÉÓw3z3 A«ÓÍÌæ»fCë"Éád烅ú üGg¸H‰¤´æ8H«pË?¾ËnLÈ:èž3‰UÌVCX.V M®ª²;-`Ïî›Ù*Çp`Ò¢<¢!%“x×—~‘¾3j2|9Oû6£ÄÀ³ã2=½ùúayMëU iqÕ¡¨O´)w`9P— 7÷y }Ö`oi…Òò¸€‚ú6KPÝ1£’×ÜÄ™@¬Ãu!áÁ%ϯç»Ù’>pÌÄ“Ž%+2z‚ƒ“áeòüŒ¯ÃgüÜ严?£K·JTΥϟ¥n1÷çˆ+vN¦qp"0:¿dÛÌ×±2b]åÜ‘, e&¼{0>âí Œ¢IVOîfI(ャéO Á*ŸœsÎÊÁ »H¿%Í@¶õÐlæþ^³ƒÌéq1vGŽ/S:C¢ÖÃý‡†ûàŒOÆK’;›ŽwfAxƒ?þáË.'-1΀&ÞqKcT]æÑ ðf6Ï8C\]™<—q…Dð®÷ObûœccPTÚ¤ŸzM›“šW]<þ”ýPL¼B'"ÚÎ.ãïb %}Ã|¶mHâÇ!Sô R(‡~úýsšêj áÙdáç»E†…ªLr,s$7é¾€¨W´BÃ[¡ -È Y)b›_›¬æDC2¡»--TÀþôéö›Åí]FÕú¨b 6× ¸¸Cx¿]ž5lAIùº÷tŒá6ÊpV$‹®·‹]Ž%†ÂKZ?69-hBê[üŠ>»Åþ˜ ù`É–2šL™I•l'«É?eúÅÀn´ê@þZ¥ûÉp3Ø.N°øéŒmnÑ ä ì“Þˆ°¸ö219cÂ6?°0ÄÒÝß.>59#£,ñy±¼òCqšï€0=z„X˜éu“ãaÑòptº´VºÀ€‰µ)>Á¤kv&ÆD‚Ú¥ä ^yFbcv¤·&9ãÙYU\×AG¥äφ"&N¢s=ý<lôÖ‚I=žÙºƒ³ÕèäD”Í ©«Ô-H•M×åXÏ“.@eóH³¼?tç1Ñ.dgìÞVËΗÐÎTp7eº¯t86ŽJ6Ú jš4ÚefUqžîHIÁinÆœTg1ªž-ª&ÃÍ"\sÆ+rñRS#{Gñaq{™¦ w9Z†‹Î„¦è=a}›K¿b–‘¾u<¢§W­RÑÂJ‘žÝ‹%ˆ½Õl²lù…æn¤_“"ìyF?+›åiªÇÚX.†%o±¬PÏXñ©yòtÎÇ[¤öÚ³øù¬¬Ç;'‘€ßó]õ7½…o66ýŠƒÿ?lns t%:_ò)—£¡Uõa;À:#Lf‰ßðD±Y?¾ª;ÈÍ ‡9¼6An6ËKc"âç“|„.ç{-ÓÇóÒƒa0VÚô“¹Š&VhµŠO奰‘ É ñ+*ÚØÖ¾¿%¨åb·[6(@³#çž¹. dë}Ž{Î83><ÏÎÞ áµt*yÁ/änœB{:ÝÎ]&í1Î/Òí̲†±ã pÄ×}³ÝÎhÂÅB|¬¸ˆVeTŒ‡Ì8?g;á}Œ{Z)`ÓZ'Ï7Û]Nk3¼$ô`ÝÇkv™kHLôLžÓ0äižnÿ®™g¸¼C‘¥…X˜`n$¿£ïî0˸9‹Õ®!¥¤@CH¤{»Yì¾d,oâ½1¹åŒ]8^mDï rÞ3èÔ²7îE/E‹³®h,a±º}~LЇ­ðdIþʸVxÑÏâ¿d¶6ÝÐbKÓ?¦‚+™ìq¿XÎrÑW8ei’5ϳ¡$Ì'N>—&9å€ÛSä<ì2¬hÒ§·¹€¦t¹;løn–;¹?>8x9[Ÿ¿žÅ*¤ÎYG h\oÒ³{‘M Ð^&O¿úÛë¯i“R¨P5/ n}ÙQßjžâ÷Ì­/ÞgÖ§—°3÷·ÁM_ð’æf‡Ü–¢çýk£Î2³³Áµ{iVóõuÎ¥wÑ ¥‹ºë%Ö90Y“§¿YïšüÕ¤+,ZЩcèÇ’šyÉ‚Ì% HTïdòüvñ?ïUq éÅÏç Ë:u½ý°Œú3éöO y`7ÖV–›äù&“‚ù4ÚÄÛgÏ2²˜Ôé×6täëòîl>£žj,ر ÁÝäB=?Ö¦»‰J 2ÜŒ«”i[¦pË»érËõúãϹ¬Áýêp{­{ùqý »CºëBÀ¬!éÎgØe@p̦=ënjéa5(E¹D-îg·ÍÏ<“ʈ\ça»ûU¬›XG`»aå>þ§óhEù$÷¥Ã——¯Þ¾¹|ùö›?üxùæÛÞ½¸º|ÿúÕÕÛo¿¹¼<¾Øs)ƒP_ƒÍµÚ]^}ùØ|•Á+r>¶­‰×Î>~\.æ3,àùcˆ ^nw›fvŸû‡=T nåp7¾ú´oGðçßýv óçc’ÑïF| –ë[•~Ìf¶Úo\¾Þ ä¯2™¥ÁÌ¿,ô_—/Aøs“I-=¾åÝaU ÐË÷ ¿ÊQ ²ˆð,^,½°\˜t£°qOßøöë¯r©ÄÀPÎ$+ùy.À@´Þ÷˜;`öÝ×:ûaûµ+'<ˆíÕ__¯?½øË/÷¿|ý¯ïÿ~ûÏííŸÿ<âC9^~µ‚îßr©Ç¯pÝáù¶1W“$.Q©Ú¢ŽVtøó 㥄s>Y‡—µ9Ìá;ÎY¼¤~žY€¡IÝýwÐÇŒ·øÑ-YoÒë€î§„ž¡áÝiMUUâ¼c ä+c[)ùoç“{SÙº•wQÿ7s,wÃŽcñ 0ƒë—Ž×¹Si‰/]Õþ“;<(ØÔUØÿÂúá—eNc»²·ìòMîÀ³P¡¹â¤Mîk„Њ±rôªVB›‹xPDæ«l}e÷ªÂgµ4F$Ü^ÏfuÚ­Æ ¿jXö‰ËDÝ^Ú·*^ŒPññ*1#Øßg¯,ÿt^àbN¹ßËç‘*žÄ,fptd7¡â»8HÃxíhÁÙ«xŒj×{åÖ×ñ—ß½@òw#°R»7¥à¿k¯àc@/»¾q‚ÞWµÝ÷À˜ªÞ‹[õnhDwžf°U6†í©wšö‚/^)Îs£ ‹¦©÷ÓJöŒÿÏö¯ÿúçw7ë¥ø—â?ÿýû÷ÿµùç㜨9 L‚)ÎëŽé~Šï`‡M¯ëÕ„ë¸&\ïkÂÉŠr9ÂÆ%ÖÞŸ ÒOÕ+)o˾=üÏ¡ð[½¯œ…ŸBÃMºÔ_x>ì¨ T³aÈ'È ƒïØÝé9©·ZïH³îÄYðJ^É(‹KÙ~z6Xþ~¦ªt(DŠ6z*¥™ÒŒ†]΀ä3J§Ÿíô÷9˜ìÓUÞ˜}›DüIbÉZPPÿeH+.4`|¥¥‰€2Wo¡­\­1èÀúpÛêÇ]s?nÜ@Ë 9þ‚‚»…ÚÞn½ÛOPPgE¨Å,Ì Pûq·›"ì*lmU »§{¢ D«0ò†vx§ÝšQgÉ­“å„]H] µÓ&á‘’bÒðÒÜ(K+¯§ÓZPbŒ@B\«>‰‘•ol\n\e<‰••R•Ò†‚[båž…Yî[ʙʈ¸~8°òŸ”æÿ‰ŒD_²#¥a‰ò¹úäû|œR~É—R­ ¦äÔ'ÐÊx‘ê€æâê¨t~÷¥}¼RæÇP@Ÿýáwš˜ëÂ}¼^Öû¾kÃpËô²Â{,£)¨³“²`S$š@?PR¸“¦IJ‰åûŽÂííeKJlÐ&$‰ÚkpØXÙÏÆêÎ]"> Ÿ…º„»çeZĦpŠBÈl¹.BˆÖ*t9$Àž®]'ÑZp°‰å0Ô¨ç3› Ê|ŒÒÇÉSv¾óÄDuªÐKLßsÚýó2öÊ9ÐÑÐíÝú¡H¸a]±Ñ}¸{¤,¯ËØÏˆÊa+¤áÝ>¬¿>D)­9Øý‰5¸‚BÄbÀKdcøƒ«>qD„¼[Ü|¥’{€¥ -±÷€Y¡9ÜkŸŒÇi"û8ÛœWÌlÐ'ðx{Oawþ°LLžéÞ-)Îö\0Lˆú¥Pbíf}Àa˧ä²iJ»ö:sA@¥â1cü[ìk)(À×§ÌiŠ´¶a"LìžgU¡Ãи¤pûö¦Ä¹•uÛã0†™1°#9<ѽ•º2ÒR()´Ú4øûÜ( %«õ®L‘‚Ëo­§È¢)Ó£8š;¦ ý ï.ekl%Ìm·»q½Wi I°.܃ݶ(cf-+Ž(õS#kÌ»rÐfõ¼ˆ‘1ÙÍc> ³exÅÉZžSx½n ¥$3™F€=,w…Þ7a–8ŠªMó6̾Oé ny¡D _K ·Ww…QÐkµSOK´ØÉq’fˇ¦ÌŒtu¥ @ I¶¹-,PFqÛÇfÞ†/·…Ár´ ð³"Öª8 Ÿ å ‚"²È šÈÁa&1ßýü¨VwV¥ÂkZA@ò‘ž—écì8Š.Ï%ÌÀ2 É=lxÓ“í4} ûÁ¢$„yîÔXV’¡w86‘8l¬éªÁ®Sœª#ÉN¶\IŒhpl5ê·Á­cPxYfklØÅuð‡æq!@q¬~‰C€Í¯§.>C€OõOÉÁè‡eèGA½+#7i]%‚,û© µØ4Ç µ¥ „ƒ׿Äf ã18åW£’?‚)!*8  Íª8d yŸfÙx™>œQc7…Wê…1Ú¸`Š¢uEÒͼ8²/—á´“ puª Ìî¹Vñ »ÎïÁ²Ø›õr¹þ¼é w³ôѵ†÷Œwì¡a}B|†nÀC»Œ(,⨅‘Ùj<*¢”kä`°ï»Æ}š-›|B#÷¬Ú¦ôMQ®æÖa.`hjëeS‚‰À%Ö9FE¥µ“³©ï_•!§ø  èØÒMC€Å }ÂeýÚԅ1|Vt.°“ѨKß^ÖWƒPHâH}cã²É°!—!à²ý”º¯Šð±—,ÜW›½ eNáËëÅÍÍfÕN¹ÙÌîÒd#™Å„žÖÉûN~ÒóÇ|Ä…Â6^íÌÃä#ö‰X©°]ìWC±ÔGìß÷4)ƒÇp¼Jô«ËÄ*.g%ëƒm¯à›ÍýbuŽŸDð¼ÞÐrø&•>‰Ld˜"‡³±·¢}U(÷B @méÄ·ûßE b¾Öxb½Å• P—ÍÎa#4¶s ¾â{ ÿ§Ì À¤uì7ŒÓ|–dÆ _ å#µ*B*^×9AÁüç]³)#V¼ZÂXWë2M¥°U±Sƒ=¼*ªO ŒòÀØ  ªÐÍrn_G"Öàl(K!övQ†XìéÜ#ÖÚ0`øûãköIh1h§Àv{6Þ†êR¯³íöá~œF0UdeŒ§Ôͧ"«Uã¸ã¥TËè,}T_jÕ²)(@ë@öyao·b'º2Ô*Ì“±)jAúNÒ4}ÜbƒGšÄ°å\UˆÜ¶ ×½O* Øô ˆ“¹$C[–¹w{­Úi¢¤qzR<6.9[¨ÀÎ*`ÿ©S˜'a?¬ ¨b_«p‚ËÆ×*\µ ìP@H`àE™±ÇƒÂÂ.¬#Qبœ¬¶CöSYJ„!q|ôé®`°2Õ‘›qØï™'±ƒÊª!Y[*"©]ÏÁÑÇ®_•ƒ”QV)¡ëvT¹õ¡:9¢(ô¶LèxAlù¾Ô‰õuh@€-ôb±o(?" ¢]ý²LwqlÑ?¸½î‰eÚKsxMaW¡eþ¼8!GJ‘CÅ÷kpã.ÅÕ8ÅëÞeþw›Åj7û°l&~@’ÁÖæd ¾¡ý€3塳ÏWŒô‹÷eÁŠì².Ô=¼vŸ×ÙÖ VŽ òB‹Žd¤pñš×éÆ'Ý:×àeXKádÂÆŒ^ñZ²ÌÆÍXǶß\¯i@¤À,QÍU±1¹ÍSô£â¸Âº}Ï£}YÆ€8sqÐ@°;KÓ,׊›2àãŠr6ñú»XtÁ²IEÃC×`JYFlvÁV¤•ª¸t֛¦e¦â`Pƒ"|ûMÙmŒ5•P>Í:9ƒEN-Î&÷ûã(FN©‘`ɹ1T6©3waÚ Xö¬03‡œiNqñ˜[ÑA¿ünl H  *`~ Ã) ¥9öØäˆ&ƒõ|7[>œ„„Ô`Îö²Žó8'ç¤b!ýt?ðW)wÎP`Kœ¢u/“ɤәXŠÐDØòn?¯0¡3ŠH,—uâQ³råÐà9íý¦Âɘ±ÅE›²n¨ÇÜ9’*>nÖ…mMUsKý´¸.MÐÁ¦ÆPôVÚ7¦’¦(ìÎ׫ËGµaÄËu?O©°C²Äû4KmV‹f5/»”à´vŽ ÙST0€Š×’Úï¸ùsl¨ù«$j?åE`ë[“¨}¸½Å¸GQì^àüë#fÙ4©ž‘ØŸžÄ±0¹Cuì¶ÛMþpI —µ7qeö4^€ ͈ý¶·{…RUÆSˆ¸)´§q&6Õ"m~·(“Úqfz€ÙAð†í´ÅfÑ‚Bð$ò’ÊH3SÛ Ó"‹îG~À c çwØìãq‰Nô7½hñÛB9©jp…ÔêUz)[IôX†¾*““Z†núÐÂäPi„”V ã~ÆVÜ“H]¯Ê$¤t*T¡S`oÊ ^W‚‚¹»+Ì×À’{IëñJi[ÜO_Õ$)`h8m³mv~Ø^ζóÅ¢ ò”Mý•2œú”äe»›KwÞÏgg\ÀÔù€Ý„$ éCC*ëo¿ŒÚ,ÑwÞöÍåùffR©'aÇ77Ó:Abgê>ØÇ]ãã :S[Flö¡Ö± E+ …9lÈAÖ ’Ö s%«Œr^‹;Ì÷ÖbÃ=iáD¼¤·Š|±¿‹”$'G1„éyçèÉtâ-^”²Žâaþû´æ»è® F(†¡†ü–›/e¾#NØ11è'IO’ÎU–+jÇó»2õ™†µ§ ‚JœM²è 4Ø0šàÐì8ࣰµ­Ä)´ŒØñ´Šo–Âí†Á–:8ap!O­´.YyÔAšÂmaÊW回ÂìoX7<.‚ÙkK^YA²[Ò ¬^M†æý> ‡¾êÕDݶsxÌ ŽØÙSª½Û ´$b6n—äèÐC¦°^MUµ:îù‰r{±Ônǵßëß¼ ìêKÝÛ•eaÏ‹ÞÞh61ph(‡R‚"¶E™¥¦¹dh ùF|[$—õ˜Ç“Ó~(Û‰o8=¶®¸OÍÄ¡AºÓ4™¥ª³¤3÷"ôÔîÏÆ*‹+€ê´à«ïÁ>Ñð ˜]Om¶4ÿKò< „är½mÊ©)EZ›𽺘”sТ¬”aÄž¥Î@µ$&ö=«"BÃÞxŽ€ý¶¬)òàj(CÑYY®HhtmjNíµpÚ3ÇD* æ|¶mž—5å‘hÌž-n e™ÄD' ¯…UixÅA¢õea†É ôÛw…Y ظMQP’ÒÎnÇæÀÒôŠÃËfù2)(_~€Ú¿ðÛ5ó²¨"@aà´ˆpBX΂õŒ2·¶ Ë={óº°u N÷“ŒØî›Â ¯Z‡RÔbûÊ€+A€ý°¸½lV׋Y¡h4*Ô’„ö«7—Ü6{sþ”¥èl¹Øí–Íáô ç˜NU÷ÆT¶§W6ð‡A9׃ÌSšºžØïë7…5ƒíÀ\êË—…aul2B}SXÂaÁJ7PÙ£Æ+IlZ¢Y†ܸνlH@Ôqà4Ñ(;ÏÊŠ×$v[MTfêaŽ<f}MTv[ì2Gí·¸¦Lh0 HÊ]€d˜ÏvÅ)Y*”?,<x˜ˆâÚ‡®Æ½)ÁËea$ʶ®Û0ÜÂj!´N*¢a¨Q“zVÒNåwÄÖV»EaŠ%o³ˆ=Op•¢âšDEÓIa  á׃PYñˆkSW\¡>ÕØaÚà•¢Q@E;ÇØ&ueÑueÍLmá­ØÇébŒCyíÙ#(ŒŒCY½A²ï†jÖ'Å¡”«ú°ÎŠ|-é+‹ÑPöh'Y¨Êcý^”õ®U†³C½i6c§Ù ÓÄ®žÃ€_~û®*l¶äÁ¹0]°ìQ]§Úxº&P;Y«u¦Izaiê*ËgÇŽ^ŽZ|ßÖÞö˜ÅËþâ˜?ÖÚ o¶¼Îº½ëWèr6úªòé¦ÿQAl( ùaP>¶@ÏeðŽŽNk0Ó­ ÀŽïÓw±³‰Ë2· £{±Έ=³±•’žBE)Kpˆ•ƒàIŒ¬\ùÙËF[#¡´§Ð‹ÖÈó⌠…þ6àÕòKá-ž ÅvOŒb]X„¦Pü(f‡É‹Gp® Ç)V—bj\œB;cê˜ $)¨…íèÃëú@Y§–oZtG‚¥n±Õ 2¢ݱàcAaa ÏŸ”=`Sã=Þ0©VÕ„Æù\kŠÔ’¦U§@`_)IYiŸô‹¥§ nš¸oÕ£L®1}M»sÈ<€½†’¢Û£¸YivŸÁ"xCÁ½^lw‹Õ|WØ@ß¶›‘“sÆÙ(¦2Æ1bÇSªà;&Š÷–ÂC;9§¬°ˆŽ<¹ÇUÕp,²×îɪjdè]°‡úT±ÐÊ8 jèàPvéÀÜnío o"Ue0´3ŒY” ˦ìúMH£)Dwº•ؤ›‚Ú¬Êô¦­ŠÆí#l`Ë+WƒêÞî~Jb™,2§Q\!‡YgU±ãBK“}ŸxÙ!ínµ-îÊâ\ßL²«côº:'ŠÛ×ï%™x§ÞWl÷w_ ïKë0· ˜®zW…Æ5FæŒeĆwؤy55¦bø>@WÜO |aØ@agiÁ‡Á2°ƒg×¥1ƒ@šÂGU¦ŽÁZ•’SXx[Ø`µV•T$­¶ZÇTWìNÚÔEeîHÔNÐEýô«=7$³©×àƒ[,u$#VØÜ{qÍ©8âú!@‚׈Øt±âÀÒ$%‰ŒëmÙˆ')Â4Õ.\v¸ëÝÝyCBkFì·ôþ {›bN1–˜#ó(¹EJ€g8˜©°?$1¹ {b‘‚‚¤¶GM{:ðŸ מƒÝÇF‘\§.v‚­&PÕ©—àO«ì0žËË u˜)D‹.cpKîÃ}Üä*l€j¹bÄn‹/o±Ž‚FÂüaƒWŒá]6V¿P ›²»[mt¥ALï¡öâx×\8T†ú"b»e ‚´³•³žÄA™_ºgBí+'„ìùNIó˜ÞsÖ=9ñ€¥…˜%A@=§PX®GŽB'àßЫa³³.بµéŸ §©JH ¹Ófu°´¡Q-†Ù®Ðñ·!‹Š‚[èøc{hIï^Y—Í· Å$ʰô0­£µ ªšû¾°¾6ބŧ9 2ÄË Ú-˜ÐÝKT ÒŒ•ˆ ²ôŠ 7L@-m:d+®<4î·9)à º‡ã¬äXöˆ®8A8 %)´—ø:tg…‚M!bq'‰×Ïe¡¡¦¦”•:^ñ<5Gaöœß•)‡ó!1€€[:§ Œ%W+ j°›hŽb¿0')¢°Kì\"­ç® Ë…[[€Çë¦7z4íFñ:6}N½U~îçeÙÉaĆÁ!»CÕÊ‚€Xÿ¯qhï0ØâÜ¡P®†Á>*ˆ­G7ŒØpiÓ;´ôj\D€½)õ“±•’ÃñÛç<-w[WŠØcC“Â~&®²`ô›ýõ›˜~5* ÈC†qûÛöGÉm¥-³§ozÀù ì÷ÿ D}d endstream endobj 7 0 obj 11969 endobj 8 0 obj << /ProcSet [ /PDF /Text ] /Font << /F4.0 9 0 R /F2.0 10 0 R /F6.0 11 0 R /F5.0 12 0 R /F8.0 13 0 R /F7.0 14 0 R /F9.1 15 0 R /F10.0 16 0 R /F3.0 17 0 R /F1.0 18 0 R >> >> endobj 9 0 obj << /Type /Font /Subtype /Type1 /BaseFont /XOJFNR+NimbusMonL-Bold /FontDescriptor 136 0 R /Widths 137 0 R /FirstChar 34 /LastChar 213 /Encoding /MacRomanEncoding >> endobj 10 0 obj << /Type /Font /Subtype /Type1 /BaseFont /BLSXKR+NimbusRomNo9L-Regu /FontDescriptor 143 0 R /Widths 144 0 R /FirstChar 37 /LastChar 251 /Encoding /MacRomanEncoding >> endobj 11 0 obj << /Type /Font /Subtype /Type1 /BaseFont /VDXOZN+NimbusMonL-BoldObli /FontDescriptor 150 0 R /Widths 151 0 R /FirstChar 46 /LastChar 122 /Encoding /MacRomanEncoding >> endobj 12 0 obj << /Type /Font /Subtype /Type1 /BaseFont /VRKLZQ+NimbusRomNo9L-ReguItal /FontDescriptor 165 0 R /Widths 166 0 R /FirstChar 38 /LastChar 223 /Encoding /MacRomanEncoding >> endobj 13 0 obj << /Type /Font /Subtype /Type1 /BaseFont /RDODNJ+CMMI10 /FontDescriptor 172 0 R /Widths 173 0 R /FirstChar 44 /LastChar 62 /Encoding /MacRomanEncoding >> endobj 14 0 obj << /Type /Font /Subtype /Type1 /BaseFont /JXODNJ+CMR10 /FontDescriptor 181 0 R /Widths 182 0 R /FirstChar 40 /LastChar 93 /Encoding /MacRomanEncoding >> endobj 15 0 obj << /Type /Font /Subtype /Type1 /BaseFont /NLTDNJ+CMSY7 /FontDescriptor 197 0 R /Widths 199 0 R /FirstChar 33 /LastChar 34 /Encoding 200 0 R >> endobj 16 0 obj << /Type /Font /Subtype /Type1 /BaseFont /BFPMAG+NimbusMonL-Regu /FontDescriptor 206 0 R /Widths 207 0 R /FirstChar 37 /LastChar 247 /Encoding /MacRomanEncoding >> endobj 17 0 obj << /Type /Font /Subtype /Type1 /BaseFont /NLTDNJ+NimbusRomNo9L-MediItal /FontDescriptor 213 0 R /Widths 214 0 R /FirstChar 68 /LastChar 89 /Encoding /MacRomanEncoding >> endobj 18 0 obj << /Type /Font /Subtype /Type1 /BaseFont /BLKJPF+NimbusRomNo9L-Medi /FontDescriptor 220 0 R /Widths 221 0 R /FirstChar 45 /LastChar 121 /Encoding /MacRomanEncoding >> endobj 19 0 obj 65 endobj 20 0 obj << /Length 19 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»åq¹äÍBžÉ endstream endobj 21 0 obj << /Type /Page /Parent 4 0 R /Resources 22 0 R /Contents 20 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 22 0 obj << /ProcSet [ /PDF ] /XObject << /Fm2 23 0 R >> >> endobj 23 0 obj << /Length 24 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 25 0 R /Filter /FlateDecode >> stream xÚ­}k“Grà÷úã»ÇèŽlu½»÷¼Ž DÊ¢­‡WäÚ»k9 œÁjRÜð¿Ìj ‘ÙèÊj@Kņ°Tg=²²òY¿\ýáê—«/Þ^µUìU ÿt¿\SYÛ^Å6Tu0Wo®>ÿJWõ•¾zûþêúÅ?¼øìêí_¯^½U#À1TZ{}ýçý÷WueÛæê#L«ˆ¾jlÕÖ^¾ž?àßWºmÚ诮L¿Žqõ=2kª¦uŠNúò0éÈç­­¢m[¤´©þÕxǾ›_éÚÃntü±õ˜á{M¾WŸez”»J‚MeZsu²w•ù¾ñUÝÄ©kS¦Õ•Ž“÷~eà;k=Ý‹¸w[ÃwšÌË×_¾}ýýwG(uåBtÃwñÃëWo„x«:f {¾|>Ò§÷M¥ØR£Zë $êâ±§9…+^>Ü ˜ñ×ËOªºYδtW©1•Ó¶Û⑾Ÿï»áŒŠ\#]5Ñy ~ýõB¾HÖéVQ€_g7‹ùòav/Ài8>Ã&R×/s "˜Ê úÈLc“Ýh ÜÖqÚ<®·Ò–ö(T1êÊÁG¨Zø¾ÇýþKáö{'ÚHÜä°ðånsÿü›ßI÷ÐàÄî•èíqv+mÝ8 ˆâ+{·YÌ~XcOq¡®\ë»Ý›éÑE¿1…Tzum‚p@™!¡ë/¿nN.µÝ­%Îète´e ÷Ëín¹ºÝŠ ȱ°Ž¬$ ßˆ™Ìóí›ç/¿3å\\[y™r.äûÚM9—@çBfHçòR>[Àäc*6•EžD@&‹­BmÙLp,J8[5Î1€?~÷úO§s¨“C±MÜ=Ø)¼¥û>‘ÊK?åPÈ@¢~ûS!ï–«Ùæ“Dùº}Ë0 íb¾[®E:ö5`¸a»y'ò#ÓǦ¹]®¶S  •¯;žÿÝz%Ì¢à:šºv dý^:¸Ž¦s¨ëÝ(&]‡c2é ¢’ ôGo"_Ên‰€µ]ÆEf›…H-JæY®æ÷O7‹ð5  nÌllu 1ä­žÈ3 úØ£8‘Ê|v?ºŸ‰ÌPHrš9}8ØJ;=}qÊ€^æh{Xl·²pí)SÃÙºNo—“@hÒÀÿ Ý^6õôFnIDÑÒÄÊz4Cä“Ñ5>ŸŒ@5€c¾‰h<0~öµt'Áä¬êºaØ-lù=Ú5d~Šj”0áßh­¨›åíb»«„½ôg_ÛʃA›l(qu¡©¢·æ‘öó§ç_$ÆüüL6È"ÌBg»[€V¾‘Ž® †mA‘ÿÑÚ°X®©÷ú ,Ün j›KÞ“q5X‰|¸Ö‚tFòqMyUê¨Ô`Ìx±øåi)jf±2Èr ÈÑ6aÛ86Åì~±Ú 9ÐN&¬ ŸsÂXæf¶›I $F@ DÆ*€9F¾ïT%јµUkØV^¿—XØ#uˆôûùúáq·T¶Ó:MwóQ”60õtžÙVbºÓüÈ÷OÛÅÍ3IfX`ÍÀŸÈîn)ê£ÞÅ“E©âM¦ÖlŽÓ¥ÞγÃÖ$Nhmg>E€õ´ 3Ê ³ïw‹€ÜÐVÑ´ÁS&©MƬa >º¿è[A®Ø"EêŠ0ç+ü$üh(Dþý»õúçç?KÜHÃaÖu‹Å£¼´Hc­ÙVÿ¾¿ÙŠ>D7-ÇÛ Ùôq•±–ŸëÍ_Ÿ¶»çÂñôÔŒ6j³—¸«°0ÔÍC l‰€ˆ·TÓVבÏ¢OâJuò+0÷TÍ:9m\w™ DAÙñeš"Ý›Ðô|¶][ ã@ SíÙ¿p<Ýáv¸£‡ÙNd^ƒºé”ì—•ìv8ï–ó»‚t†#{±¼½›$AÇ¥¨ÃÁ§ÝBÚ ŽG¯8…‘:MMˆŠMR°ƒ¯@Ù®›£¬g%ïƒÉi½«à,ƒxÚ¸™kß'R“I,‚ê V6à½hfèšmDÉžkAÔ†Ýi¢tÒ*´tû`lz\ˆì¬éìZ:Ûë•Dúm¨ZÍÁMàGl†ÐvñLâf@óÖÞ â-O-°‘jÇ ºë"9`i.0˜ÑëÂ43°ÐmÃvó$~ê ßɶ£²œ}µ0Êd^ïV¶ 'ȺýÎk¡¦™k.r4#‘InïÓ-#¢³E¡yáG¹}z·ÛÌæ²èÙ༱¿øýfý Yè7;‚œâîäJ£@¯‘4 *wÏÄ(§«¬ç³l×"»ô•ä{ô›Ívºt1æ7rJýdŸ¶|Q³‘n]εj¸÷‚XÖx˜äãòþ^Ê€­òNbü(Å1J6‹ÇõF&ã¡ul7Ë÷/këìŽs´ZøNö÷ìùçw0!©ÃšÅ{ ’ ex è­ÌñËPÕx+ÉKÉwÑ:௑/ééññ~)¡Xi»¿ÊtšUAýÓˆ± ä1Ö`ýa¸“Nñíëo_I”*Œ ‘ç;. i/²·Ÿa%Q Zʆcê[‘MZ]~‚¢Þ†&g+*¡9w¬ÛsP‹öNSëj ¸ê5àz­ŽeÛ½& $òE-·­cà À¦X?€YusJŠ3V£9äG‘ÃÁk}ø>ÝÅ™¨òhUÑͬ¥a€ßp€t?bеöS” ‘…h4›æ $HÜÛ9Ìt``£¼K1¶ º$[ZQqqװݼõPÄAŸ`sÜ.VϧS ŽZßtåfv/ùUÈ%Y­å¸%hˆÀY ®‚×N'?]¼ÚÀî‘WÙÅ«1¨ƒ(y …ÄLñî'¤åX^ŠôU{© ëJâJ`jÃ`ndÝŒOÓ¶ŠÏRˆ¦Å0†a•Ïd ¨´!p7âò{ÝXäúp·4œ¼ßkùò•nߌº]5e%çÜÇx ÑØt½¢}´æÕý½\ÏߊܲFÍxŸ¸«¬èh¸“ÞZ¶FQÁ×1‚.Õ0™ˆ•n›ªñ b4"4bNÞf[¶’L6UÓ´l.®ê©±|Æ"k `L7md‡T¼ü=-D]Õ?†R”ä³Ô¡ D £-W†~_ŠÁ†îð;uŒ¾<+ˆp_ó­ý´Ýmžæ»§Í¢Z¬æk ü”®“$€"“ÈÇ=fŽVÒMÔt£–m@æ—ÍÅ´ q³T›¾¤³§{Éml0Lc,ù ÙÛ XuÞó)îŸâYƒM_÷ ª¨â÷g ¤ wk 1îiµ]ޮĬ›§@¦J@­yþn)úu¨œ h¹Ú•²ŒÖŠ‚Ü.6°J_MÙ™:Ú;öÅRÀÔadbàÛ±ä6E’Ut Ú.…(çÝ –c«(T—±QÇŽoæaöILŸ)/„B<“¼úÙ²üûµÌîgµý¢:®¿šÝ‹œdÕŽåYé.Ãwô{9GÏ€Tq¡ƒáUñ2óÍ¿ýà3’AfˆÏ¿ò=wúáT½‘bNœÐ^ŠÙª'f°÷Í>úÍbþ´Yî$d#±m{SY"8z÷mÔžMóz5—x­FéV2ùVN 5].ƒÀ[S0Þ È s+Q¿•Ž-û~ñüåòVbM±Ó‚o¾p)[,ðl'/îo×p*wï¾6ŽÌĪk¶wë§{Ñj 4Žów‹‚äiÃFï Aµ©<„Â|·žà^ò =™}VxÙÆŽ-,¤%Ù v|R³ @ÁÈSÖ¢1C ʳu• -Û(I17(À‡ `Jî*î§€‰¹«5ú ‹Ûg–|ˆýºÔU‘C× 'òqƒYåýÉæG)é³`d¹³ö²Ït=B¨32]=Ƈö‰ñ$GRÉPn¹m´¶ßè\`9°ï ~°ÒMm „+ÙПî[6Áf¶Ú¾?%äÆe|dP¯:\¤æ6éP¨ÛBº+¦ßÑï»ë’3ä"ºÉ @ÅóOÏ¿®2ºW¾™o^5¨ >•‚€ùëjÒlÄ*Uðv8›®qºB!FÛ:7Z>hú-†–Ý2&ð[×`K§FH»c3X$ò=î&tÈ8®®¢ ,q\Ðò£e…|OÔ 0±Š‚”Šྵ|Yè5_¬vŽ v0˜ l¦­Èq5°)°žïF\Ôƒ”'ã<ÛÏXPhlÒ^(D*(Tb‹%Ÿ­L$4¬ùt Àp»Èâ@M­§ì™'Â2~UÖgÙØˆ˜J…ÜÊÚpÓ€tü^]ÏVË¿ÉÉHu‹Å5l0X×’Jl°D×2ûåJrÒ(ä·mm&oì;8IöùGÑlÐT ?’ƒÉªU1;ˆ¼šÉ¹tÚ&Ó‹¯JâÊ5°¤v¸*IŰ˜LÁ!$­L! ·o|¾Y’±„=±ˆª+ ­ZÀUƒ,’N³~x>¡0Ìyô‚º½º¼óih ÝŸh=—ó¢Á;Ò¨ëRÙV5äÏñ^Ô0,èð Äí­©¢J! }ýñ ›Ýþ¿ŠF ͧe0ãÇ~`ôÁ'¿*¸Ý¬Å¼3ÔÉl¿®®¨YÄ.fxè3°k’õÂ̳‚÷Úè–áÖÊʘ£Ú²Ü3ñžÄKhRŸ ¶çMÉ£[FµhƒeôàZ â§®¥¦IÉ6Œ>ÀtcPýµ…Þù2åî#ƒÇï‹ÑA ìÏfXK~ƒQj€lܶ°‰Öƒêx„øü«fÌ·>Êî@UŸp“ý>Vƶ8Qê`=[ËvÏ:X£ÅD(à]MöcÒ¤ß-oŸ/V7ËÙ µÝ?+t7h¢.àP­cj~ÄÚX'^9›BlÒä.Ÿ[Á·2BùKm4S¿¿Â ȶϜS:ï—»Ýý‚a´*…%Œ¥ô&šÒGá‹ñM8˜ÉÉ¥E7…µ Ž>m•@¼/”Mטû½HÄÿQv#é®4™o„Vó¨1Ù˜®3ß»(#–+ q ŒËÕØÉ¥!s©ë•(ï°õ‹á({x': °¸ÒGË@ä¸8B‰;Q€R±¹ñÀg³€–®Ä#]sÄ×ý½˜w‡õ?gM²ìµc{¹Ÿ‰^åžöM¨‚!™p†€yß¾£ßƒ-{0S¡†{HA`+¹±Žº_Õ”zfLûGÅ…Lò°Ü WÒ2¶à»/~JÍ ßOÁyé=F¡ó AeðxÈ{_ƒÜ,$ètar¦Šë”7€ ÷÷¿O>'¹:3±&²¡÷²ØÂ;Žèň}Ǩ¿ÅüÜ“ä¥ÒX9røJfzÀZô£ˆDR%/¨r.Ôš½úu6ßÝë3uÐ%F v ±hoß«lË’áb"_Õâ—'ê9Qcuï颌ŋôíæG™Lÿ¦îJò*E„ ý›Ãö^TLS1êýtû‚Ǧ ŒZ8ϪØO(fBÚ©Km>÷f@ØÅcnôûrî´u¾ÿ¾«z[É%2Æ¡iO&«ÞÐôtƒ-$¿d¡ ©3[‰*‚1QÜC¨ë ýÔ0‹Œo½#Tš äû}¢P%êê.‹g`…Lì“Ñ6l;])ªæÊg‘mv”Éü( À+CQé!0ËíïYWW}ÖÕ~-ÆCYÚ•B5}ÃΔƒ‚°tX$M@¯MÈq]×I*K ƒYRU{%‚än¥Å8_>&@0S a~ÈÊP×¹N;`=Ápæ½Ù#Ʋ0  öžÂ&¡ýµäk;:Öq#F±´î’Nö0ê0Ï÷Ý 9¤[Ãæê8‹ÊË-gNöórl5¸ôÀ)œ¬ƒèTuí…(4Éi‘¸è÷}8BŠaa•d†‚1^Io1Pc0~mR{0gÙnúµÉ J›ÚœPížèWÅ|¿F Ú²´XN Ã„°V>Gß0ˆÕÓ˜ùǹ˜àEDó/õª#‹t€30œÐãBì™àBrbRQõCŸäákEBRB¼³l|&iOe`j„ÛRšSv#ÆÅ›¸†ƒ¹WÎAª GîEŠ·]Ô]r‘lP÷Õ?‰ò×$õv¸Ò=±—¬ ³ hv-5o1Àú¼7gl.9ÌP™f+À$`bK´YLæYÜkŠÛNO˜†q•âmž_*O°Uh( ¨‰^¡à’µC§zœÝ¤öS‚²Ô¶ØŽžAÉ ˆú‹„†RÛLpŒ[µtÜC¨ ŽÑ}'›ä£d7•±`JÑï 2‹ÁX§Ål\4tÔz ˜‹îúù²ÄŒÏ “Ï}:r5²ì–#wöø¸Y?n–³Ý¢ ¶(/)–b»*4Žùîwk‰ú=¦s€ùzƒ7Yn‰‚Ф1lO7…²'ôÊ ©²´Ö¦îÖ“h¸®°QöVµØ¤Õ}uVKLÓ¥2qE•ÃE! CªtÂJLæ´`,é†í«*{"0Îã`êúk÷OeOÄôú«ýŸ¼/Bc­–/ñ™jïI'@u”R°Ë7ýòÉýþÔðgŠdc¨F™â&ä8* ¨óûô%ÛQû´:¬^ŸRÔˆ.?¬SãÎzß‚áAn—«U†‘«c% (a êãrw'zð0§²ŸH˜_Cfç°‡:ƒr„ÿ-I °•ë8è¨b¯2ò»üÑÍÉýÄR° -…x\l–»]±Ý_9NvbT­ÅB‹–M´|íF,#´ÉcAa> ±Æ•ã÷%½ Ÿÿ¡ßo31‰ólØÉ^ßÌÞ-ïGJúïgá`SÊ`½ ›R%°ÿþP%œ¤h·©Í/9Ty‹ô‚¹è†½_ß߯ e)ÙÍÇRïI¬¨ “ðÞJ#Í$Û䆣 sY5âªcTB&®ˆfÆaX]%v«Æl8¾MPƒ&–Ÿ§Þ+Îl7b†cOb® ­Òf%‡-[b{w ´~/s[XØÝm‹ß‰ü6?) 4×Ï ~gÙ,só¬ðz6raV Z‚=‡÷(ÄÛB#IŒ¡Q…®§û]!0®» W:S/lFÝ¥˜,Xs€wËœaßv ‰€r0ÍZ;¶›w›õÏ¢gÐV:òu-äª[ÅÐïyÕF6Q3p‚=Äߟ6r—ƇpEA¶Ë_S %iœè/dP¿<Íàþ‹ >LØ0¨åBî¯âàÊ4‘íh»›m D£“‹Ø³™’Z#¨ØHRxÛ Æß–AÜ-oïž'O`!5¼iƒà¼ç„«)D¢i%:¢#êƒäG`†lš7…øü+%:¶õRÊ1Y¬Ë^¡zš‘’•¯¾B ®‡•ƒk{q¢Îzü^”@-ÿ€Y’›1O«ÿÓ–Í’<%ÆkAÇç+[š´õ{Á4A‡ºÍ@Ò6”ŽØ3¬¥ß,hzÝîT1¥ ½ÇÉ–$¸{¬¡{ÚÐÏex v+J"˜I‹!³ÉhM1%~e9äl Id ‡Ö&¹Â¦(Œ© J­¯(ÌG±<´Aµ,ñN2j[àd Ÿ¡àÕèûÕñ>ÑÝÐ¥)Ò)¬rÔ„ó c¡Äðõ$vX÷Àg*WÊ‹EŽBv#Ó0çy„dÑêÔ ŠBl “߈~f@šu (¬ð|@l)¾ÔµHHøÑsRù¯19ÁÓÝ.óºwQôZQ$ôâS<ûWe¢èI·ûè`IHU8$l̆ÎÒá´Øÿ˜¾|lvZ@©øR$ª&¿á#>]]snÃ?~ößrFÜ—x˜YMZhöûH[ ~íM*¦§ïÖ»Ôp]a]¢± *h³øl–|3%Ñ¢ÛÔÎBï¾+íÐÎåw?]ò-= âÝOýn£ëš‹½Ùš®LBŒß}E^h@ÝŸ!ø~B*|ò_5û7EáåAp£¥°è…—ðÞžCqç„X¸ŒïíY‡‰´G€RY n6QÜ•ø(†mØLÅwFBjNDßpì–D˜Õ!fx_x›Ô9Pîî\7¿…07æÙcD‚­ªR·É—Âü×ÛTü!T<)Ì?^ój½gÖb)eJЉœ'‹"4¨°D’Á³Hz‹ŒKßø“i§ˆ¢þ’FÌåô#¢ÈJ-€Ò艢x–mÁÊÌ ¢(uƆ´Ÿ$‹'ˆâãŒ%Y„é;dò1Ý0 ÙdÇ0°Àè¡Êw´Ê:°Iä®ÀÀCó›m]ª= ò]Žpý_Uñ.7Iq¥0ãd§¨æê-Çð?W6¥•`åÞ®i!'ÒDzòSa› •ŸÊ'Ï»a™ˆ/Mܯñ¹Ü=Œš é «÷)º‡iö¸åb[x+Ë·;á f ì±ý`Ë®{9 3a‘ŠÂÝz$º°½»S廼¹†/MzdP%±ä8Ò^¼ùòõëÂÛMÙÙÌïfé…!QÝÒ¹ºÎÐåtv|ž¬5qJ:{—¾Ã fƒ' G34vû‹]ÏnÍ&[ ×W{\^¨®u>ì _µ±%_3‰×­öy*:®ôk[L2áZÅØµ,©1Õƒ.ÔÊ¿²¹$ý Àðš}/ÿ)#ƒ}­JȘ2¶ê‘1i%ýºñy»oáùÅ—/_}õ/_¿þ×ûæÛï¾ÿ÷?üðæíÿã?ÿôç¿ÌÞÍoïoï–ýùþa•]ðaP”0V™ ñ«2è×¾HôëP\ êazÿuî„˃ÔH]¾€ÿÃv&}Ýo‡]Z h¢1Äéã/›íîéÃÇ_?ýí¸¡ÿûùVå:ÆžhZ$‡C¿„ÝFã)4&‰n=@aK‘ÔL•ÀìC¤²Û¯ñ=PÙ³†Ï£¶Agaµó*ӹѸȀ0EX~p ›&Z’°SÓÖ ø(’n’“”N±á ª±.îÁó“‘r6Ä侓E¡7¾€H·"¦ðà«Æ­n8µEÆï%!í»rdZ(ÆCGckù¹ŠÏ®¡ÁÕ:§(€dìK¨AHçË=?AÎ:ô—R€}¾¬”÷©È—€Òà@¹¥) QÊ̲uå±f—€¤cÍJ%¸lMj§Ù°cý½dF×sFsØÉ'‹I0Ær´‹lßñšï@í6©ŸcnÄÚµ6…§§ŸQz÷ tB6…-%34œzö‰Ù+›?ЛhLa—`>Ï” +|c¦Þ÷W–ûÊÐîVt‡+kþMâÓXÇ¢=’²¬Ô±ŸJ“ #`rkÐÙ}hÙv¶Ë‡åýlSp¥Ø4}º…Ê$ñ醯ë Qâ`KÙvˆ³à Ö·õŽm倲g¥ŒÀ×&¥¢g,ÚÀ¾ÿu¾x”4ô;¬Ü¥“ßµî}ã¯bƒ/ot¡ ­ÜÉ:˜ÅêHÙÃi=¬Ç ¥ #Z0U£b3”š5ÙÖUÞ[6ËLlîåR¾HË ÒQŠ :|$Ï4|1sØ; €±Ýlå tÀGœø’ tÝç>{"#Ù!ø_`ÈŽZ ¨³ …”$l§~O«%¢WÀ.>ÈâØí­{)3Iõ”ŒÄ&„)¬3éÙ˜#¦Œ-f?Ë©LÀp|ž£Ú©F)Œâ¦aÚÔÒù`4¿Ö|/²¯ÒaŽaèw£¦d§WÖ Êè,Ô]ûè4ïÃ=ÎÃHÍWÆs £_L’4Ív#‰yƘþìØ\â˸ÓRŽ’™âà3ŽÃˆhî Ñ·on¬E!ö§">‡$2â9LyG¦LW¶¹`ŒÁbkôÈ`ÄÍ8×=mÍ ¤bUÇæ˜‰Öb½:ýü¶±›½»¹Ø ø0…{Z±@FŰØv6³Õ­ø¨ªÇÔýš#í?1R£Êt ·Æ8®üI¦“`ƒ&Cáþ¶ØˆW3'D@%ÃÂ!a¹È %w±6LP€ñdŠ gãøÊqIÿÛ¨|‹GF>ØKбYÖO;)Ì–66ÿfëß$„Ó¯°×…(D’<æÉÕ|/¢bæ­OïkÒ9£9å°hñpôfò’éV"êå‘AIlÉc~Mg‘Ûø{ºY6þk)®×_’,éK5pdaÝ÷ªØåÇ: 6ÁÃz#…M->½DAE°ØÚÂZM@DߟÅçš«*Wúã-l+“{æb ߈À{ûL¼R¦ÒѳÍÌÄï±mbÃæ@£ý^²<¶ âûO­¥âoS2ù`"‘ßcÍŸf;¹»c× TsÀ×âÓr>tÉç$U¤>ŸBõ 7ÍññYqiÐ+H]Û—bF‡`;Ëç‘ø<rüÌÓsðâ›Ç #GË7ôêáÝBÖø÷¶Ö³M}¼[îÛÇÙ\”ä(Àø*WRš0Jþ6òõ­Ä’óY4øXê ˆÜR[ǶS¨Þ:‚ÙÚƒ‚µYß<Íżg jSëZ8.]Õádm§/€Çné€tLõª„gñe>¾4ñ8Ô25_ÙJÚŠKÏâÀYúˆ™ ò8šˆ:mì=¡ð ÍfijI lj=€£-ÒZìü͘ªDj¨f“ }¿šBiµÅ§I÷Íî˜J:jaƒ,Ô j&éc ɬEöUç™BŠï™î¡öoÏ—KÑ4Á~ªl"‚l)šˆmä5ÛÑJzfÄc0 ….(¬ ¹¾æJ¶3«ä­­îIŠÑ4]9x>Á“°‡„ßo&Kž½“Ña¯ÓšÀÕЀ™H§YÞ®àŠÞHŠya×À $µÜa²fË>/¸q̺w›èVäžmHf‘¯i&U2:Ð êÁ&D»Ÿ!4-[Ñn3[Þ ¸Vƒ~í8®:ýIò¢A3 Ô«º݆øziÀäòW°#ŸQ¢Øw²§L|¹¬5e¡am›ž1¢9Ä MlcظâÉ´uìÈÚ* Thò ¤†ÉT|CËÕÍr>“ß»Ãçmœç ”£\ªkiDß¾îš ð-èÔzeßJt0êÙ<ó´Ðq`ùL¢ÚñQãÃ÷厾ÉÞò5½[LP×CD{bï˜Ü,Då(&Pï7RîmR¿ÑÍÊ&º“#-.½6O!+Ñ/c4¾áË D· >p\SÇ3EõϦǜ‡{Ü’Mê&N!’n"Û v‹ ½øŽ™¨5ÕM[6Ó×Û…hàa/âÖ2˜Yˆýõ¼Ã‚Zq+ê  "+#~ ªÌÏ" ëŠÏ zK_¹]‰íð›6å Ð=›Â½ñm®}+åÿ.”ŧË-û~¶Ý.E;Ñ™ (Ì7ËÝ\”E6u!ä}í_¹Ø÷ÒÓ,è~-ÿþßDIìµý÷ûj»›ÉÏû¢Úb‚c³ü¥’T)L­ÎF¾]îDm ËÂS’âb+ÖÎñ{%’ˆÃD<Ã1õõbRJtr‚¦[¾ªo¸ÆÂþ–QÉ‹Íj»[,WÏÄ;ˆ:{dûÁÌžW¢P 1XÐÙÐe=_.V;Amïï ì[ç¾yz|MK<6-ÀzÔ ”ìeD'Á ØM°øD+`¹šm>I¡K´<y)¿&™‚`ñYD‰‚t,›C®qG‚uSúö‰üñ‘¥¦a¯ïû“ÌÒ°n×0÷/¯g}ýØQ×gÏq$˜Šo û1d ·øÓÓv ·±ï#ûÕRôâZ”Üx=)ˆÄ.Á:jþ}ê\—ÞR˜‰¤S$’B¾Û¢¹/z¯<NdÓý'XgâûÙ»Oúz!y£0O2´ìû/_ˆNOŸ0ìTwùA™õulÄ>XÕ·‹Å.¹oåÅ›ôÆûz½Zß?Ý?=›¢ñ¢ò·ïÈóõkQ;1FÐv Ä¿>Ý‹i"X#›ÄÔuÀʦrp5h˜ÐuºÌ$šÃö¨¨’ïÿø½¨hÔ¾l½HçóöÕËçÿþÃëïÞŠ!ü:õ £½øâ›WŸÂæõÆ1©Pa­Wò}©s[²1K÷ö®¨ó·`‚Õ–Íó~]ÓhJQ¹Õt NQ±7œ7M 1P€ÔNŠÍ€væÃ]+Is.ÕäPùÝ(üáv±z>…Ë‚ÜÄÀuâåØKNô‚rRãy ùúQòôº…’Ÿ|*e_á뎀¨rj ƒ}c8–΃©Û…<ˆ ãùvv›™¨b¶‹c©.O–´®[4ôËSÅäë¤oÖ|´Kéa/Œõcª/…)”Ú)äËulŒHg_RgŸÏîŸÄêÇ}0ŠÃˆÁâizÌ06kŒÇb”æ Îxlº. Cç’ÞÑEM£¬MêÚ‡L¼Iu2ý÷4g¿E°6*:•ßð¶1µ `‹s´|ÈÕy¾:qŠ'ü º1)y·i =£Â÷h¡ºâ|u'Ý=lCçÛg¢7*¢³˜A„Z4$I­<膂x<ÈfE€ nòá8 Ô€Žß«Â÷mêW—9m‚¤l´Ø4…/N,úPÑ4f»Ã`~¹g*5 ëBí|]K1î'6À¦«µ8EÄž†]éYÑCØ X^ôÿR­OY7EïvwÈ›¶åÔu–˜ƒvþ †r±µGƒù²G -ÞéÆ&÷xÑ…qU>? «Ê(ÄŸô– ¡Ôf½á{ãßý}Cwidû™Âùøz¸fSõ•úbÈê–J¹)ç(r€ßl{×>WƒwV¢[“m½¥SÑ·¶ŠÎ«È@Ùë‹*Cãøà3›NZêˆyècÒÎyÀÌÚ&ÕØSAí­‘#„’_ @Ø>›¢wPŒ@cÇI¶­)E[ÎaÊ3ŸNôË¡@²HTÀ„×¹S–tË‘ÆÃh§Ž¹T²ÅWµ…KÛéÂ5$/ÄäÛ$"Ÿ¢Ën ˜ã˜@adµåƒ šA 3þ¸ÁÌ´ùM¥>åÁû6=d3¡¸uG|ý}¢JÒÂz¬1l `ybŠiÀ>i d¹ší„f K´a0'•ÉY½ »yiÅ@i›$¶Mý€6(ŸXV‹BäÂ"O#û¬Ä W_9k¯2 •«*-?jÞ=~¤†F§r 2/˜” J4ô”l¹ÕuêIgØw—lJì Ðr(9QÓÁmíè_Ëùm©–žSíòáñ~9‹Ïúûä0óè˜(Ù•.Thê¼Hïrê6×40$XÐ ê.®H!Vb 8˜Ç;E>ˆåcmÇ‹È÷¢ß/zÈÝËírOP$äÀ·A9wvà’8N¿à;|ôxª)lÀþk¶ÙÌ>ý„Áñÿ>Œò ü7¾›#V“úP?àÉã{W'ï ~ÉÙFeôe–(# ?M¡ößc Øô{qI˜Ä ªÙÐõ§ Çe“–ÎBÙü©Ãèþêý„¬¡êþjySµ5)»Åï‹JdžZ®n¿ž*ýÙ–1'ÕkgéÍ)Ì´ÿ«^qàÒ¤;š84_ý:ü™¬0JQ­à÷2Û·)Õb:ö1üùW2±âÍ #!/òkA®Û6ìëM~-M›üPôëE~%éNþõíïË3ÔD°]º6/󟟲»è@ ƒïÕñ{,1FÒ§ß”•Z¥“c:Nø ƒ‹|üüjЛÓpô<­–øe~†¶æÔ(v'ò‹ÃxSù>…éY~ö¨=f7¹ôøYcáNø$ÚäÉôx‡L÷¾õj¶Z?,váæ˜TÊ|‚íÓâ uÊP[, BÂBv4 ÷ëõãO‚Y‰ìØŸì/Œ¥æøÍ)ëRcœ‡ê¢‘WS8—ʈ4 ÈïV»ì8eKåäLB :áÚý¾–³ÛÅOZÎXrƒí©”¸5"›Hî¿ïZÀêσ(»¥øÅº®ÁÒrû9,@™ü$ª_ù~°´£ØðøôÏÀ¸G»RŒûddæŒû£s %$­U”0Š{ˆÐ!VüÁ†¯{+Þ¿×éàWïàEE½1vœ&ÆLùãÈjtäÄ`ÑóIF¦×g@ù*;ü~ქœåƒ£=G—ìYcºÊ£è¡c%3íŽRõÈ©±;ë Wzp&©c6)hÿ±ûe p|W}|ÔÿCU-Œ;'­M‰=ΦpзwÇÈTÆNkÐy:n§^ïÓÇUܹ¡]{•w; µc¦¡7&7êì"Ô:]§ÎÔ>®—+Ò%ü,ìbü,Ô!‡Ýc|ö ¢Åf2uPñÑt7w»Û<ÍwO<}eêYKG=ËÛ†KW»ë"„tÅÝ6‹»K®q7t›ÒTƒ2——Hn¥Ä£åÉGñ…¥Õ$.†=·°„|t¡êúÍÛþøåÛ?þðê2ZþQ 4Æ‘@ÝZg]d,’kPnKíþ³®2z ¹q«IWy¨.ø‹°…0àÛSg"áªPý÷D¤ <>ÊÏÅ|¢9èÌÒjºøï…ôpÕ ifŸ/¡y,hzŽ,í$4_ít ¹ƒ [ég“È$'¡OGUC }u¶„Ƽô!ær\ê¥:å{¶¶÷" ­2¹V¾ÌŒ;\­š†…ô@rfµŠIè3PÛêô¬HµHh’¥‰þü,d !Z´•-¾ÜIÇÌKèŸî—ÛÝþ.«KdjzW8ä°s™¤V¤6YÄLÔêTîHìReŠ’z¢\í$5•Jju6‡®šì«ëhð}ònX5NÉÛËŒ|+;dQ1»ÐÒ…*2ƒ³AÏãjøHwÝœŒº§4Ô"V·ÇîCgÝ=|Ñ!º6·âõê²›W›{žˆÜiDæ¹k%²Íe4–:…ÕmŽÆX |ÚÀêX[ƒ=28¸Ý,o.Ó^{ýÁt!û§Ä4*;å骉ödØ=•=bôn7‘̆1GÛÚôo6j<ú/ÁAzþ£­ûsRZ}bEZ0aØJ›iöQ/&N‚Áµ®@õÍ!ul¥ª¸}ìý†™4™•>›daÚTº¶§í铨gáëOðíÖÓÓŸ`Kô<ñ4ÂÞt²w©Õ$ž˜µdé ÇÔ­©Îñž¥Ô)Wëü¸w®^gB6«^éAAo…¸yúQ;AÁ±UºmRÊîXr½x8ÇáGkrlLŒÌð;#LP3îÃpwÌpÏàNMô­`)tfU¯¿{ûê»7¯ß¾~õæ"_ã!»G7;s*!KþL'7öbíÇý;:¹ñÕ¹˜÷Bwl*2‹U—†FS‡Ìàr¨='4J+ëly™ýC£9#>º+6ïÄT¼=_ðMn¥¿•p±P ê˜ÃL…Úk¨³ËžäËT™rnŸ=7^>p–G kN±¤ótdu™!Ò*w/ó{ Ý¬c–-ºÁ³L/l £eF}~™§îÀA{m†,áµó9-ìQnÕȸH¿<-7ç˜sÔ©¤‹¬£#O |Vâu_í|}™Q ìÆcÝ`ÔD±.óÓaï4 8䉳`s™}Œ^ÕÆd:íb©±w1F=:(Æ=W[òþšè²?5’±R'Ù› Eyª¶ŒM;ŽYÚ%ú<>‹ýsh¸·øÂ¶íø ä¹MÑvKq :CWY]¬vaMHz ùRo~‹Úe4—­öÃeŽCßàûݹA»î^—yñEܸÛ]z…á"å@c®›>ŒüwŠ cæ”Íãá²:¾Ú€<2ƒ^AÇ×`í`ÔßAÇz­¤Ñ“ìËo_\¨pÙôXa“¹Q…K·¾œ÷D‘›Ìd-*žãêi>—‘ŠRP‹œÉÑë…QA…­u±T1ƒ‚›Å޼ýUÈ7Ïð/|Ù¯1§ÊÆæ2 ]¼a'Ã&ÍàaöéB• SʬönvYl4¢K:‡‚—EFñM"—Åëâ2¬bk°Ðä°z™V€nˆ׫ôÄþZÓʺ³|çÎbOØÃÁ¯gêôòzfÐÍ¢kй½[>^&qZl‘@†gÌñÝ¥¶(XåhÚenÙÇÅbuÑõÅÞw±ÎÒ.—dg˜¢®ë_œ!´Í…ú'vâŽ9Bûx!gô©“BI ÿœÑâcž#™D·WgÕuØ”ñ3W¡Ù¶ƒÒmT™Å^È`ãø #ÚâTÞ†“¹qIÈ3ÓF|ÕØ^/uŸàËÀ"s˜å™§Saafd9Í%Ï#Vèæ]®æË›KóF°õš«é¹1Þøx·Þ­ÉÃ^çÅYÁÞÁzÏ̺__–ŸäA_Àî%™QÖýƒÊê2«sSÂI,>Û.úÞÚçj8X~y0òÕTÌTœ˜™g†ÍR±š`¡™ÔÂ;3òo±ý0”ò¢ùïeû¡!E\ŽßÑ>YÙ6¹añ}–Õ±{Ëyl­Å6Œ>Gk¬ýÈ™×C™:Gj—Ç>Œç¹†±Ù&zÆÇ½»,)ÝLɲõÃ….w“°§ƒª¡–~ŽÃÝà‘²½Ìä}eqº]><¿, w`d,?­%jþj²ù‡YÍ㣪ԺovYÙ&¶GߨÌz™öÑ=6Må05>þ‰ï]Mädu1Ö7Ž‹U+æ`7ì ¥ÍwO³ûË,7ìum e¥'®j“™(=çðHl]‰•XÃQÕ©ÖsÁÕ««àšì¹[ÿÆ«WwÚŠ©ê¬ÂqªÔÉÀ‰©Ý./TL,ŒÖªÌr?\œ•Žï]g]\˜•Þå1ûnšÝ6(;Â&"ÈÕé˜ÇúÕ}È!ê³\l«ÛÙ¥¡ÕÚ¥÷ý2˯.»wp‚9 ヾ¾ðÞÁm^q2ª:$^§jáübŽÔ>^¨•ø* ãôÙ…J‰Ny3ƒ>­æëÍf1ß]¨XÐ^:ب ¯3‚çT?f14õ* öá*3îfqáU6I¯õq³Øö00,=7mYgPÓXfLd`—ñZßVÖÚã°jº3.§3¤m¢+=©¥*Cg “F¦"_·Óm›AL2ç/*bǶðÖdsi@ÄÅ*ƘY+¾´PÒr|¡ 9$ЇÎÓt°N øÐ`\uê²>ƒ>ºÛ¡"–M ’F)ÄÌ|¥½¾"eü> >> endobj 26 0 obj << /Type /Font /Subtype /Type1 /BaseFont /TKQDNJ+CMSY10 /FontDescriptor 188 0 R /Widths 189 0 R /FirstChar 124 /LastChar 124 /Encoding /MacRomanEncoding >> endobj 27 0 obj << /Type /Font /Subtype /Type1 /BaseFont /TKQDNJ+CMSY10 /FontDescriptor 188 0 R /Widths 190 0 R /FirstChar 33 /LastChar 35 /Encoding 191 0 R >> endobj 28 0 obj 65 endobj 29 0 obj << /Length 28 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»ås¹äÍB¦Ê endstream endobj 30 0 obj << /Type /Page /Parent 4 0 R /Resources 31 0 R /Contents 29 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 31 0 obj << /ProcSet [ /PDF ] /XObject << /Fm3 32 0 R >> >> endobj 32 0 obj << /Length 33 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 34 0 R /Filter /FlateDecode >> stream xÚ½}[s#¹‘î;~÷mì˜Á)Ü¿yíñ ?ìnìLïqlìlt°%ªÅ’Ø&)õ´ýf‚Ud]ETR³öƒzºÅ¨, oø2óï«_ý}õÏVI&oV üÿô'¥1i’—׫Ï«ÿó%›•Z}xX}w·}øÝêÃÿ_ýøaÕH“¢ø (*\­\’Ö†óGïžñï¥J1·z^i ºüÅÓêgXÃ?ãx-­ñý|·}þÜ}maÉ—Dÿò~{7ó mLÉ ŸRËFœžÒJ/ç>í­lôp…ý—ÿû§¿þ?$Ê2’&†Á‡þüÓÿò¡ôE­LŒñÒ™ágþß?ýü×›Y ZºÆ Äñ¯s¿µT£…)igŦF6ÁP{ä?ýôÇË÷M^¯SAF7øºÿì~½·—´“Þv¿%Š{©QÓÝ4Y¬ÓQzÏHùeýë‡ÿõç¿~øë?O¿¹;1É&Æé.öF6ÊŠÑ7O>ï}#=l1ü<üjjpµ«Þ(X˜IVŒ?ï” ¸¹àµU8EÎKm†çHä'2…Œ‘ÿÐÁ#uP§wäÎïèÇ_×Ï_ž6½×4ütTÒ7Îõ?þêm"¿dó¯Ÿþ䣴öœƒgÒáômöümO»Ý—W?½ 6IãU~E×ûýúÛÇíËqórØ·›ƒlÿ澨ɢ%€ž¶/›õ~{üVdà(èH!}^o_*@4h´vë@vo›ýÓn]ó\ÊH›ôúr¿y€g»ÿø¶~zÝT¼®ÆJ§ÓŠÀû²ýuóôña}8~ü´}ùxØþc‚)&kôÉI?g1O»¯Lqí¹}=˜ü<&À½l_>|Þw÷ !ÈvÛçõçÍG5ópJÁŽjBÿC§]4#de„S,zŸQRÏ}êÕÞ¼sθ™‡Ñ°°`Ÿiè¯Zi1· m­ÔMþúÌZ¼“JÖò¸Þß]ï7#5 vÖÀ“³=éúzÒuzr¬gEOÏêä(=½"õ4Ø0øŸJð–á³ÙrXïZËê¾^£³åCÒ>–(á®(\e¬Éö³²l‚¦›…(n¡Á6'ø‹¸>kâ_¾»Š)&¦D'#½SCÌ‹-¹ÛÝoF¨âúJÁ!Ü"¹Òßu;möé#yŸÿñô'‹Î÷@Eô÷U-»Äƒ-pÉŒúáq{¨‡=·ÕÊðt•q·ÇÍó® –«ÀÓÔ!q/« „ è`ðµÝµk–d•NàäJ´_vxÒö5Ð7Sy/ Ëm‘»¨¸²cU4 ßF/ìâå´ÊápÜ¿Þ_÷¹½¯Ú“ð=?´5§¯ã÷÷Â5(Ð:Èㆡ:©A‡;ÆÄ@à?š! ‡k‡¨=1W uâÎ6Ê÷Záç?ýÇŸ>üÇO?.l»å”Á_±”îÖÇ ïCŒÁ°¸Ÿwûo•æg|0@5ª l{Že• &–6UtJxÔé!_ÙM|¶ÿ®IÑ"ƒ+(ŠÄù»çºÃW6ÎíwˆÑw€q?s½_dEÏ’‚ûÁïà j­³ ì(¸8c©¸žº8ö@EåéŒsq¡óŠaœ Dþq$ÛþÓÿ¾w|»}-Ä‹ 4yÁwÁ ·g —ÀeTÊMpÅÄ@/:×JÛK‚Xíšå£(me2Žm E…5 z¹žWÁAPÑ_®(hˆûõq½à‹¢625ôÖx©2{ÔÖFQE•^Q6ÚÁn¶6º&Îhmt‹:µÑ5.[ÑF/ëüó?ü‘·ÍšœH$`³u,ÏÜ(£(±ö¬ó27-ÛKŠ¡Ê< Â<¯œWÒÚ*ó̱ÝN³˜9 ÄáÇÎ_! æùücóÜOÉ-ðíuR2˜!îØ0‹eO'8Åq´VwVó¿vë#ãD·ÆYP‹]`œÅ$r&@ϲ ÝŽÃ¯ŒžœéÍqswÜí«d;†šöÀ§ÿÅhû™u˜Qg µhØ^€í$ϧGH|è)øE±9„ ÎÙ l»Óxþ„12-(9ton¹Oáœ Ž’Á§o<Éú«%Q¿>nïyáœb¼#dûÄ ÇWº±§3\^/ÞOücsÏÊ|hã¤Ó–E§€¿U…ð Àñ)í`qʾ¾y @5‰Èk«al­"ÏòÓ7©5 KçïuÃ˰yØh Lþ¶Ýi‡ÇÝëÓ=K¶É v‚Xð§ ïƒgÕøH‰á~ËV‘.P oÛûó©XxŽq ¤DI·˜¬@µÐ[EIöË~wÿÊn€èõYøŽ™SŠ¡ …zÜŸo —*Iø™<%Ü/»ãŽ©'Á´)o)g}sàyÅÝ)VNjeçlqïÚêj* ¢Ú¤…úe³Þ›ºÌð;‚ŒÿÞ‚ƒŽýúåófYþ®Šj¼ôæ—W]™?™Üg*#›±,Â%ì¨2@SP þYéµeÔ°ò—JE8Æ~(ظ,êšÜµ*ÝH"%Ô†µi•7ÝÞÔe¥ßW…>SPÐnô¢ ÐjAÿ‰µY¸!MmÖ°4J™sˆ ¹SoЖ N™vn úÓæi}9c¢R Y_±Œ,r ñ¬ÁîxÌöõé`» Œ?n÷,­¦$‰EJB¿|·>vwÛ5W³i§Z…_°¼¿ ÙÁD© µf¤Èüò»+FÌÞw¬,:éß4¡ûÒFpº×.<ꢅ҅‡é¾ƒÈ¨ 6ŽXÉY•öEWWè¬Ê@&®÷/ϪˆÁ•Çt±úJÌò\¢PÏ ÂÎûÂÃ?–ë‡Ç Ë×ò^­•˜Â¶[á¸}ž(Âêûøt£Vøá¸~¹_ïïYò@¦•óMÈãž'å4¸[šÇ3ùÀ)°”@ƒnw/¼D7øöΓÞ¾ðòÜIƒ½ÕêX1ß÷RxµØâìÛƒÛ‘ryÅWSx‚¸³†î§ðÄRKu>{.A(ÆyÇÚ³7¶UmØpA%ÂŽÞ… x?lË\¼6l/»È$Â1@-‡ W@Å4l dÐ0œSØ0-‡ œ6l˜®ô–§ ZPQ6Ô8§°a°Ò~ØÀ pÚ°xû3,ª‚‘SØ@¼~ÉrZϪþи Ÿ¡6\£°¡E.1þÀS§°a|5làÅÑI‹>rY:ƒs¢5>EŠüÕ+ν¸Bf× “ûÍ{°DÁØßÖ¹?}GÁ¹×BˆE®ø‰k<@¿¨¦{Ÿ¹Æb€9Ë5®á]}ûÑJßÉ·/£ÞèÛ+¼~KïæÛ‡L´¢’wBK\{΋[à“r›Å¾=& yîÖ€ÿ™çà'•‰”PÚBŽ—¯a¿%e(‰¼*=¹©c«dã)ØÁÆ‚+={â¾ãfî8‡ÉQÒå…OÚ+銻á¤ÐöGž\‘7¦-û°ßñ˜~'B×t¹¢žt=£#D§2ê©?Ï­`‰Sô+K®™ƒß$s u@T.^Cßx§œŒ*‚]ôºú1?Rî !„DÏLm °àZyxó´yÞœ/ã—“lò„pßx²…³ 5µi1ûžJÐZ‚‘ ¤€IžJЭûZ„=Ù4Ì"°ö®†Ã–“aEù2 À¹ü.Z1·bž„!j0š …~ž±iæ­íX[×€ZO‡íÃ7)\“ 4ð“,îasì¶ÂbçÉ[ô¡ÕŠ€~Þ¬_,2qÂúqK#™xÍ#ê¨~šVÜ¢#û¼Wm¥KIˆáç˜ê„œ" týT•K˜2I|¾ô!P_™„b ‘ŠO”\ï7¿ã_6÷L6I’.K®äܸöˆÕŒö×l*a÷ð'…%.*2BÎF¥ÃáF‰KóQ‹¼ŒEª7‰ÂИ@]ß³iL˜r4i|£ßÅ› ˆånÖgòäÒÛïÍSbº(K¯;°ˆˆ”ðó¶â+Kn3tR$k—i\tÔjÑÞµ‘lÁT€¬#*æÒWˆ¢!©­GmdˆžÚË ‰˜G$î†OÎDU—?ÖÌY’úÙage  ¢Û,Ùb‰™uF‹]¤õ y/„HxAë‹ëVºÉåÃÌY­ßehX¥Ðð2csû;ª} N )› Ó«Õé‘~=ŽÏü¹(SœdZÛ/OÛ  öÏE§{ÝÅýÛ#Sõ7 Jq£”q¯™:èGQé@â^LÊòŒ‚org˜ ´`f¬ •%GÉw¡Ié TaQm¸gRJæDkláΟ>·OÉ=WúÍÚò_Œ›¯´«sôÉÅ×”,µ:îh}0ƒj´ÔöŒ:Ö×1G³ŽFQ+ž Ê­¼—ÊG õ8[ñ3#ˆÜŠÂQ án÷üiûÃ1Œ›¼VÓÒÜ ÅO!€ûíN˜ºöky÷À’oÂâw)T®|3³¡1ØNá~eÉ{¨XÔµ„XrUxûd5%/û K° É“ðµìÛv÷z˜±e3BÀî‰)Q¢½[6‡ïyâMX›DŠ÷Š)£%ŒÎ{Bçïú[¤L#M4,*ï K¨ɲV–ðK¸ÚìZ@ ÷Z9àŒt±&E+J ë/”o#*uÙʘ-åÄÇ{Øí7,;„ Ϊ‡ò²$˜£KO Â’ Þ]s‚èå½¢PsN†¦¶Ïi³$c0e\1ë.Í€‚ßàÑJ”%{Í]rt›rÁ>!…ì.ý§)]‹N ¹w%Ù³@ØžÊġjý¯ê—òL‰—“•ËýR_©w¿­¤‘|-×0£ vô”,¯äft­EBL q™n8÷6La»’Í¿¿òÄ Á©ACV^íz¿á 79„%7ênÇn§f±D¯ ³ZKTË[U`VhŠ*®^rÏ bsƒ3¨XpÉMkí¨0 ÕÔó÷r!<õ¢QSâ}~}êÂŽ%S"ª&Q™½pDoa©ÑŠ«rDœ3Øí>q¶M‹îRiPPéɹ(ƨç¶1Ow¯×ØsÙån²úúåžgÑvbF +Z¦Óµv%/›ýãúK•¨E©ÂÀjK c¿Ã¶Æ< 5i¬¥rÜñ´3ò¥üùí½—ó§qÏ)CÉáeÃÚjý€&’[m¿9Yú/ð›TÀÒ»-ÿÐ`þhÒôpË1|#Â,AU²ô²GF9nƒ"æ‡Ç×s»,z#ÝçǸb@¦üÇ ¦>#¶/®³O»Ï?°Q·["Æ0¥²ì·ÇÇçË´þ™ÁÉ2V?ùÞwLéûÔºz–™À*¼ËS‹Û2ý<”ï1‘âdg8Юh\æEHÂÜ·ŸÀvîÈî33„=’˜ÝTÌ RÊ DùÓúÀÌÖ{ð`—¸ªaÞ㩌FˆwÇÌÕ'ìÕï(é.Ɉ!³Ë= Ô¯·ä޲AVf.wÂ9ŰycJ±ƒtî„uóf›œç ?oš)V¥C¥f‡˜7òkæ¶Ÿ•^+J>¼ä‰ÀígU är7ßvŽe»½fÔ¸i+ßIB¦>˜ÈÎp -nðQr‰ v‡#V¼ !#JíìÆ2t)!SF ØZ)–¡&dxˆQÚx~}ã½6IòTï6ŠÙJIžbÞDGP¡$èãÜÄ›¹ÔQÑ*J´ÚoxßGˆ•gvój)¥š’j!ž-á#¹yûY±(RŠ2úér+F[\ÍGá’In.ͳ¸6øL–ëTùȼӆBîrG,¯Øœ*[hÁJ2R&·œ&üÆSpÔ¢O(¦hö«›ç:R¸L?E»”ël+Õ¹¬¸?–Übmº‡•?Q>sÍ ä¡z\S6yfÓUÔæ{fÔ£o”¸e‡Mµc0 ,%„5O5°ë–< ½,’àd‘&¸‚ÏwöÇ –¤x±üšoY|rëÚöÛæîÌ–Å·Èž›ÂŠÁEoÓimÄŠWµïp®$¼BW5¼ç¢T¦P{nÔ¢ø64¹{:!^fb/Cã)Ñ~Ù1ù·ø:÷t5ÂÍ“7ߋᒌºm¡6D'¹2ï½áÙF)A¬öåõùó ûÿiR ¼+¸Ræ3§P–C‹20?¯ˆ³ˆÐ5¡p¹yE$ÍJÀ8¢‰§T‚(ÓPòeS§Œ•t˼fÀI÷‘íó2éÜSãJ´Üœ¢Çv[¤`™9El¼¹»x9E´8C‰}còš¢FèUn 0q¾êt$àá¸_o??Y1nb×f»×ÖfYüé+ØV])0Öt°Œ^£tu1¼.,‹¢Îþòe†ó˦ù¸+Ôv©jœ´"·RCÐ&ˆå¾Õƒöºð!>çÀË W ciÑbk9o…ûüz8VöRËÒ|áRî§ K´Ø]4_g•W»{Ù°„‹ÔO« %„Ê’©i/L“ÛרGæ¶U8,Þ’}Ø==íxÂuï´)á~…8êÕÑë¥' XIÓ¤ºÔêsÕÔ÷Ë¡np’–*·¿´Ò›+ŠFTÅÙÝJƒ¹ ×=¯T|×¶ÕX¿#Ó ¬ƒòZNo¸?T*ñõÖñÉKäîÃàdáHÌ2"¡^Ä•Çyi&(ôRt/‹ypXrF·²©ód3Û¿¿Øš6+ËÅ‚.N“(Y·ÅöËe’ÀqD‘8¢™TUÚpdÁ¤‡(ê‚I¶WY¢”Æ6¡fEÀÎ_%QºÆËŽ9¨ƒ ö™0§*æûª\ÅE—±q”`ßd3T„6)JW+ºÄ¼R´A¯'ê{˜jK¶+ŽôPù½Ùf2ÊŠ¥a¿‚÷™¼ƒÞ"Vœ“õŠ€¬v¼Æí=àG¤@ÇíHÄ"Íh¤ó–’+S5‚E´#±²2Ðâêw•cY47kG +Mx_íxÆä²^Ä;ç,ÌŠÀ.ÔX‹ªÍÁ ójV’ cŒý}%Z¶’8 ûn«å¸9èÛêFQe%)ª=GLŠu¬Ð‚’,ˆv»µÚ}òLÝŒØÕ ©›&©Ë_<­~^¤bµôÎL—uÎPñÚ¨A€¶µA¯nðh{>R2ž4x37Ú šbˆŠmïÀ¥°+{¤ŒU¢ƒ³ßÇd1ñÇ)ÉÆJ°×zä¶wR£sT.󮮺±º‘Öº±ÖÐØÇ˜èÅM1QC_‰ Ê´qš’kuÊáŽÅB2¬Ë'PkÛUŒ– ÁgVôØ0üXl˜­-ÀŠúVcHÚ9u‚ݨb¨ô[;’tÍ‚&S.ÅØá¦‰nÛ¢¢&_=6ÓN&ç‹°‚«¸±[ªXÞœ¢.À™ÇšzúªSUpQ0'©úÆÉÄÜî€zùÙ8/WÕ­qÎ#òÒÄþ^îeêq)§OÍÛe1*©¸¶"ä¤5ž\Q®¨`ù£°¬àDî#¹º)ÏtŽ~´ÅEÄ\ú³ar¯S0eÔQw±Ät¿0ëÌä„et-¢à]ÃýY%œÂâså˜uÀZÚ2 Õ¡.ŠÜN«tza/„!²iLž»5D¾%øžêÇðŸ§ò•eZÏ Šôä·Pë¬s\DñÜ[›Û^¾o â8¯G‡v_õ¾€6ø#‰þò—5 ÜZ\Æå¦UÒDÔ=O`Ð@,-C'‘ÜÓîs±l¿ëMØ`@÷á~Õ¾Z=‹Kˆ™ÿbaˆ‰éÔÊy¼²+ÆìMx·½&ÀO¥ÕÂ(“x;ÏáÕ£¢dº Úºƒ=…K¨<-×7Æ%©sx)EAŽ#g±Ä©¡V*ntj ïüoìÔ4üÞî»æ„j¡€–il,ƒ^¼Vú¯’M°‚XqE4Qàñƒçßàåe“EÚ=¿Etñ·½Á8˜SnŠ¢¶byŒ˜»´bY½2¥‘Vj‰¯»¯eM¬6hR–ÅJå«§X'*´-Sfø›™‡Øƒ7&æs¯} ÁMÀQ´ÝEZ/á±_eyòFÂÉW˜©³ï•íÀØÎP Ys1BGÛœføMaʼnAŠðp<°2Ø5% bÁ n×{N–u™þM`î×' § zKa~å8Y8ú]ë2¤øŽåbŸ­1$8AŠ+F¶Z¡äRzxf¨Õ`›R ÛÑpÁJ/Ka8`(¡¾ìXNx„—w/&üÑý~s‡ÁUÂ'6DJkV]Îi#µ'"@«o›Hɕ廆ã²T?m6/œ›”Îê7ÁD‚äÇ)V±‡ÀØQÈ{ܲؓVƒjU%XÁ'ûZÛô×*&›êåþi™÷wn; û›R¨,gç}؆Âä¹j˜ÊÁÉlEPQ_=â"²})Án9ÚÕ)'ƒKÔã¶ÏÛ'V«ƒ]í !×'´Ài¾´X¯µ(!¯º0zS”X?o9bõ)G„ÄÓs*<\Ày¤ (*,q5€̆\æÃnK«i²\GNpu监n7ÀcpF-I®a“ÚÕæ«o{p\—(×F:ï ¨b19tKg¼ ÖºÀÇèû¬`²)[ž^ÅT®#1‘šý=G¨p°")S¦ÁÂ’Mè@K­Ú—f+ÚL–þø÷•«ƒ]•(ÄñóWºW´€õeP¾µÂ†)FQR½ß>°.Ö@îªÍžuñ ~E°äùßrJ³ð®Ô‹ZoP­>)L ¼Oq†í>Dqå¶liìñéû‹}­¢H•ÄܾÜmï/5™bQæFWÛ2^¾<îŽKb¬~JGÁQÒÝrÂ6Cž‹G½±‡üjSÊã)ÐÍÝæpXï·Oßåo3- · 鞬÷Ó7–÷¦ÁÊJ¾ûMõ úØßÊiaRżƒ¨=¿8¡lÖù ®‡)n8¾ýD.öKUÔZ+g O¯ÃÑgeÌ»ÝëË‘Sl`ÁÖèDà Ø_vûã•È›<¾`Æœßò’?<òNpÂv€äFxcß(½¶ä ŸÃÞŽ29C0Eܘ\•§*¶˜¢DbZFËç{>Ìë9J;V$ë!ò Âë“!@²Ú±X•g ƒ½¥§—²[VZ ÌM4¦Ã,Ôòl?í¯’H‹n¥õ$8ÇŸµ«ÇtR|÷ë—Í~‹XÖÜ;¨ƒòrw,G)8ø…D‰€ui!²xÆÊ˜ë~/µÑö:£äÊ£3b+jOm×V¥5æ´²&,?{M’LjOàÈÍúܯµ^ c½Íýô¦¨í×ó—'VŽ;bñµUeè׳vÁYVÓ«rŒÀ?ÇÂõ~ [ C†&( ýôy—ÙÍ,* 8øÊ¥ö(vZ¿°H@ k‚'W¼ß°X@IÒ¥6ˆüfpc ¸±êWV%¦k<œ4OÉ”u|Áå€ ömy¥ X5½‹.4 صŒy­Ý9©TNóÏŽ:ÀöË®„zr¹Ž›gÉꃉד¤âá$¤0«þ_jÑWvOÆš¤S^ü“Ñ \Øi ®—ÿT<~ FQÅîKÆ4©™&†W}È\¶†Ë說¿ãl°ðÈ~`º^J܄ݚ“µpg1»ÉbÛ¸ú—ßñ&ÆžÞ ðð3š ;æßxãÿL’]Þ2êµ×Evë6Øu•P—×­Ûøa*€Ššîx4.¨ví)Éys' 삦1”Ö÷÷¼Á;©·«‹]Ò]ÞâÀw3}]¢ÄZÔ'#$CÉvA»¶é[¬¢Ð©f‹ÕÙB·?zE¾µÌ—á ƒÂL€Ñ±~§![ùö9’Ë­-½ "Ñ[R´Ïë——A ¼`ĉÃÞ@Ô ¾ßîöÛOÌyPg ©ðFšé¢Lޱ=õÍ)ƒÖÖ‡NÕ#ö›´*z ÅðQ0ݵgÙHÊmíÂñëü!Q'•ŸAV?ÂZy¤ÖhWã q•ÎryN”¾Êç®”OÙj¿d5õ†Þ6û§ÝšU¹×úCìË9š÷‡VóþÐ@(”?´èƵõ‡¦‹­ð‡Ä•Óžé! ,óôqÛµËZ_÷õµ>c}ìQ^t·ã¾ñ\ÜpÞSàO~Ú¾ !æãóæø¸ãÔ£¬’5Ãï¹9Ķy ÇÓõ®ïY©ÙΞLV*Ä×1§wñO2èÆœ_Lÿ÷Kãv1²Sǰ«:JvÊ *Ã2lLÇ–!Å-áµÂEî»ô5QçzÔÁZg+òŠÇ„ÉáAÑ!Rsø²¹ûá¶‚SàÍ”•‚Iüͽ[¢ò4wÞŸ+†nư¢#éUë¢ rs ½ üzX#öí˜2˜Ç&±cz^F:úÍÝoö[ÖÀJk@'éHÉ—é{Y#=)Y¦ëåšÌÖ$@ùîÖ^›d)àœ?â‰6y©‚£D[{=QM‚}ë(é†óÕ Ø%ú·m`6¬éç΃(‰ Š“©'cΜ´°“òþ§ëÆDœÕ¤Ü`8­‡EÁgÄD6X'`'ž³¨ôE1® ±\±d@ß4J°?¨X8'†–-:Š’Ao>ßBÙFtò#…û©®‰Ê‰–”ì¢ù|ýù xV.Q²­tWÆ’µ ›ÁiJGæ®Åè‹ Øñ|¾ú M ¡,–Ïç›VNcë¦ØõÆëUN?®÷÷_+çùŠiú;p6§NÚUjá*74_ÐS˜Ýíƒ÷ °é|ì n˰BEž³y\±ê¯VõÜßÍ‘òíù8‹ÈKñÄŸ¢ f{W€û Î ØVk)líÈPeÖ %r6hrÊ¨ÌæR¦‘4&«eÅcc¨ÝÊâ˜Ylnkµ›–”·ˆ!+Ô'êáyµ=¹¾•èÐÊÔ7©qù&»*¾ÛÝÂ2EÏ6N¼Ï»=§û—I` 3U)£–œC— L¬mð(¸†,žZÌ…Èè§o=­cîŒxÁ¬0t¤MrOGòñy,~ê99 3ÛUm \.ÊïÖ{^möy±ÔNeñ¡s[ÏËîŸ&Ô®±Ò:´0»|IC&¼U!äú=G¥#„ˆ„T7ò3§½³A*ëfNC¬.ä¶¾æëe÷<¸TaîP1 _Àãï¨ãxÜ>ohI%ciJfÑSMÄ@@Q˜Ÿ·‡ã°³¾³qÈósŠÀ‚×Ó)ÅÊûs¾rοÓOËôOú3G©Zø…à)Ð#‹ó‹eQ‚<äTœa÷Ó ú@,5Ô%MÑöû)®vj¨ëê¬NEQ(?;Vß<°TŠÜ‡×/›=ç²Éœz#Oas€òO®Ø©5Z5#WÉi v ®sû”sá~öÝñ\‹ çÒåò0,õWÉ—¢kF‘$DjاôúN³\Q¿`ÿýòbÏÑ5' Æ»)QÐ¬Ž•˜<>”1ÅÕx,ŠÂŽéPÅ\¼¾¤ñW# µV^ô1À¢DÊ™j“Éü(3Çë w@)©&˜â–:dZ/ˆuîYA0ö¢åù•£[Ïé*’]S¡dhJ/Ipï…óõ½ŽÚõÌ ý@HíWU¦$è€×læ Õz —õS ³ö*gìâ(wÁii–˜þ‰ò2õè½Î>&8âÉ_¬œ§Á1aŠzC¬ªxðSµ& ³…fÕÑa'mM¼"0ùœÐïìN8-µžæê[_õžÕŠ·u'@Ú_IÖ‹¥îD Tð݉UçNœpÇ 6mçN”å°9°š<µîDsàNˆåîÄUð݉UëNb­o‘vî!Ò{V‡Ö(cÒÿb©;QÞ­·¸ÔNeÍ‘=»Ävâtqé܉2d1ù/ê݉2*/Ô¹gLñžîDy¥·º`´tJ×ý QÕÇFç‹/”ïPŒ©Ï ïãQ8Ey¡¬åÜ,|v®KaÐBS/‰ëR$ʘâ»O;^OCsI`‹*®^(Ôé9ñ Š`Öæƒå^‘ “ÁJ¢v<‡"Ï×U˽m¤6?à{ŽJ1޹Ø5oôŽŸ%÷ÿ×ÇI{SQÙ,è@¡žöC¬[ŽÙ±ò¯Tò;™Æ)'21'çãlXÀ¼é Xô€êªŒ™ï*97 èT÷W*n½«;;Jªµ¼­‘®ëß8E=ýý¶íÈΚB¨ ²$_jÎB+#ÎH-Ëõ¤]8mvôɵ"ÖÊR¯NÛÓÍ:±[Y­8΃šL^×=–ˆLVB¨;^ÿ.^`“<µVÉ!«u±µ yÅãØú¥6ýC•E¢†Ñš6¥¥Íaó"56¡ÃÌ™ñ“‚ÈМn­ÊË}cU&çA*˜](ƒر¢²(ŒlÐe\ÁKX"Væ-ô庼¥Æk¤¶ ÖZh;¹w`V âÎŽÚt¨“B*£nîêŽã“‚|ÓåEßP–>ÄHÁ2Ë©¢Å¼ÑS,›½2í‚täfË‘ƒEÃh3TìÇõማñãaû O³tÛÌìt<oZ¸±H0ÐâŒY÷0‡§Ý×ËÃpÊJðºØµêñ厨:›¶Í€H4x1‚]ÂË/V•àdCëVeØO¼£”ðYE€*ÉÉì¶ÖÒxÝ=¸ØÎGéõ«î¶[ÖX^4J-Ê}Ì9õ$¥ÉåIZCÊ˜× ã¨ìr¹ » ;¢#Vß?;•@Emû£)q/ÊNïu÷ìtž`_|vÖͳó§mUDdew¼ÊUìâàB,ä´7JqÅ-å—¯É}?Êk®óÄ”4ãÉWUn….j(3Šm>ÿ¹@ö^VY¡I1‘+dÁ@bºž¤ÎÁoÞ/,']©òC¼l6ˆ —ë±¹¶£PßX5?Xý… „¦ â–ª²ìá}by­•~橌ª_ý…ó÷H |Þòäš¼ôÊ¿³\XF4e¹n^¾çª¡ô‰’kmH6l¾H7¤`ׇÃës%)g²b{šêJJ—srqŠ4ºgLñ.¥ó”h»¶J-NÖê!‚l,zàIY)ä–…@ËòäŠþ¢jÄ^Šb©Ó5ÞgØùÑëv’u†»î/°‰%¼Åߺ‰˜ÁìXË ¿±‡Ø YL›¿œ¿cÔB¬ƒ1–¶ÝÄúßÒëWzC31чä÷“Þ/£¥.k%F´~!0_'°…ýhô¤ÅÀ‡Gf;›»[‹1ìjqS1ìü⛸"@¯iÑ™¼Š>ù)eÜ^ªbAŸÃhrÏ—æl£Cú˜, mÁër´”²>ü•78š ¹ôzë—™íâ¤V°]FÈœÄí`À† fEÀ’nDE–Uçù‡r%cš3;5iQ£Ž±”¿Îeý¨:Ë‹­)ņ2XxWäK)OQÝûÅ«àʸ"O5Øxj öù@î³Ú[½iã9pn¬¥L‘úDE®=¼DAoy%§zm¨Æ½(Áô‘Üôõæ’Vš:OàL%=UdÁëoA'%tûoµã1ÇmÈ0wg¦–{C/'o¤ûMßo¹­œ"òT µÑÀ ؽH^ÚÃZˆà%ݸƞÜß¾lïÖO<…fÑÙzç†ÀäF[~‹%ºË‡&÷.'÷ÿú!jOÁªïoòåu·ÇNb$ý=ó®4JÜ^#Ðv©–Ù°Üeœ¶Vœç<…%³ DèFQRý³ÝdÞ”T7/<¹&•,°ÇÇ sÃbK†~a½ôè¢ÃZÉ 4%ZÅóñÀ-EXê"'zи§y&Jfçfœ;¨ÉV[<µb8*ƒÜ³7ŒÊˆ/ )…K«Ã¥Gå†fð oÂK™ ¹m_XÒÅ›£ˆÖ¦,ÝÛ.ЩjÏþóá{V¼v6>JwøÔ…6à”ª2¬`öÿ4Ø·¶1(»wà„ÊåÁÍU†’Áç-O²ùrž”ìÈ…ãŸm äºyaö¬U¹U!؇/ÃÐà-¦°g²‘s6€üßiž|>(”Ý„ ù²Û?¯Ÿž¾ñÚ'ÃÓ`®ü =ÌÍ=î^Ÿx#—LŠ29OÚ°¸aVaÑFaµ¢»´éXr’·m@u$ŸˆEÿ•9rÉ™œÛ(ƒV²ÖKaaÔŽzo—‹}^øÒhEl¸õ—ŒQVzˆ%¯yãt´–ÞR˜¥QÁ™òV[Âï™TlkÛ Q3³J²~MHá+O²±‘>R˜¥y˜KˆÖÚzpÛUÂR’»Ãô1pu„Å%3*±îIj¹¾ºÏ]}Ü»ýf}dæw@ëÀ‰› ßîq‡ ›áLyÉmnùÀœŽåNÞPµ˜E¥ƒŒÝÛ}·¾!ßTG€;‹XT1¶jN³•!’{ = Þ|º€œ*Oá~Ý<-%ÄkƒïnÒê¬k²Î¼‡C÷ÄGQ¯&mOÓÖØ˜6®T6>Yið0—aû'‰š¾”GÊxþŽõc=µâ_yþŽUÒRº…Ä„¨ÒgJ*øI âí4“ÃØí_mqX±`2™'MáÛÎø-l!‘ò¼=++L9‡MnM€ï×/Ÿë¬F©ç¼CÝ3ËY‡*ŸÉ2 † ·ˆIet§Q–AÃd2&i’‚ÆkY¼~D½0Y©¸ºÒP›{¡¶íe¥ßóè{àæ¨f´i“T-è?ñè{ [Ìûñö ô#QÅãŒ28E½~ž.°8ÂÕDJðùÌØ²ÆaìS^-“ÏŒ:±§ºÞ‡w‹ðqü±[Ù|fë(rA¬•Ég¶'Ë“`ò™-úg¹F-SL”\Ù|fЭK”\¹|æÜÇA“‚½…ÏŒ]œ›hérN.ÒR@yS'—MhÆ–ûÁëÛ–8çHdö1glжaôÖz%_Š5<(wŸˆÖ z¹N2ÙÌ'Ò±ÆÔPR5¤ãºX¸L:Ö°©‘‰Ø}¸™uÜ›kÙ±ŽÇ_2¢/¯–,ÓŽ_óN¼ã&‹x,ÊC'Ç‹c‹Ú¡“h¦ß’fWIIÇ&W<6‚í7ì;Uë;#uò(¿Z?é#Ëj†MÖCP=LÁ®+^8£­:I<ÍièäM;%6à+M¦Yn—3ÅåÅBô km¡ß-7‘›° vÀ<^˜hl O,–§h7=8ó[ b½lÒ„QÒG‰á óxfÞ5¶§Ÿyië#O¶>b'yJ¶·0óÌEç(s™ÇèÜakRÀL~šU¹­[] \šâ¹y·¼;m¼;QÚ Þ¦Ó–Ö³ì Suk*͆/ À™&z©­íPß‹×:§¹ÀNûænw­† †Çb³O!˜ÒK PÆL`Å5¢tÍA†Í• VÌ«lÂ>IJ $Qº¦~\ÿdid¼—bÝY{›çÂ[ ‰Ò/·˜V.ù¦©ç+Lé~¨É¡ü9Žc¾*f™Ò5‡9æöðÄr™5tIË„z§ ºfÒñP(M¡öÙ׋N±BîÀŠeý§JSZ,&qm¨=ËlX†)!ëHá*vg%§ÉS{ÅéŸ)n€¥!ÕlïB’SÜ ,ŽšÐ|Ùì™DS,Ýs>‚]±x£Z­€Š¶ |KMà©Á’£ ™5Ö4r°ÞÁ7—Ô,¬s¹J”Xl%©™Þlà9ámß÷xQ¼±ß³Ôn㑚±K}¹×‘šûçØ)r«UÞÊL¸æZ–QyÝÑkTÖ@Û[v裦û°`Tm¯;Z§pÀƒ.þoó„„Ðûæ÷# ;ìLiÔð©Þ‡ÜÉ óïD@FV‡ %Hñôcìûàð—VÌdcCAƒ6µ„É$›ÛÛ…2æÅoBî”C/ey¶¥g63Kãë6"*-wÍc*bž bs­™IDð,m*Cï`–fƒÔ–-“ÉŒ,P¬(?ÿ""óÀ¹ÖÄñªÁVb²kgÊ•Sˆ§4U#.ŠZ`A{ûB–3áÝ%Ô% fAjCeqˆæ»Qkóí¦]J¸bÈ`^Z’ ¡£¼b¾'Œ|,V™&ÌU4E¬ÊŒiVÌ,gØc/ÛØá F‹ú¢jD27^#–—ûÂÓ|¤@ ´è*É‚…PÔFkiѼZ¼U&%û™Ç §½l yÞªhÑ3-•‚´Q‘æõi¯-&¨·ö9i¡#cÔóàh5,ƒòp”ËØ¥Œ¨T=ÖQ¨›'ö]ˆ2¶CE3«Yj«Ús&Õè…½˜i.lË`&` f±˜Ü2˜/à‚b0/ä]· fbÕLÂVË`¢Ò fQI‹>1˜‹KL^pÇ`nAÅ ƒy /øÄ`&„ÚðxÁ-ƒy:Ï`®hëÙ2˜ }3‹Ü2˜2 • i¡¶ fB¨’'Ô–ÁL€–Ì¢²aì‰ÁLlÖ—½Ú2˜’]z¥4lË`&dP•Ö$ƒ¹Z³Tʵe0rý¼åɵe0¿¯\[3!€³ Ìlmˆ iµe0‚¥Ì«Z³ VüÆã¶ f殥û¶ æëÛV,AË`£ ‚Á¼ZÆ`ж×?Y1‰Æ'3%„ÛÛ&ãÑðÍoÞ69`³ŒÎw¼±o²IÇ`n¿dÊ`>Ü­Ÿ†¹ ±µ<€î¥No`-eÂo—œêk¹¸Øê~ÉTÆ%œô4Aý—S@¸½[·¼ð"`›xÕá >;£Ÿ‘† µè 3%¹ÃHNwÙ‚V­àSiK™Ûû}*lWKH–Ýû' m%‡ŠÌ¬ eqnú‰Ç Ç~#ÁxJ°ë/°uyéy°ÿx{_ e ^ŽÃû5äÄKSdÞÀ½9ÜbqËH­§¸7RQqð‹¢…Ë¤¢"³ÛϰÏëyªÝU%i±ìßNp_˜í猵y°ÔVt)¨ÃÝ~û‰y½„õ ÊGjÍC´‹-¼(I÷]FÝ7Ïœ©× ç ê!ª=ãÂ2¨âÍz¿=~c3‚¦âÆIðŸM|7— œÌQHþ×Ó ÎÚi6%=Öûæ²úÿÅî endstream endobj 33 0 obj 13891 endobj 34 0 obj << /ProcSet [ /PDF /Text ] /Font << /F4.0 9 0 R /F2.0 10 0 R /F5.0 12 0 R /F8.0 13 0 R /F7.0 14 0 R /F10.0 16 0 R /F9.1 15 0 R /F1.0 18 0 R >> >> endobj 35 0 obj 65 endobj 36 0 obj << /Length 35 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»åšp¹äÍB®Ë endstream endobj 37 0 obj << /Type /Page /Parent 4 0 R /Resources 38 0 R /Contents 36 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 38 0 obj << /ProcSet [ /PDF ] /XObject << /Fm4 39 0 R >> >> endobj 39 0 obj << /Length 40 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 41 0 R /Filter /FlateDecode >> stream xÚ½}[“·‘õ;~Eû4Rˆå­è¦(ŒØÕÚäØkÅÊÁhÎÔÌÔj¦{ÜÝËýfÖ¥».ÈjT¹öƒH©ëp*‘Èÿ\ýeõÏÕ/W! …^åðÿæOÆgZ‡• E–juù°úÃÏ2ËWruy³ºxùöíËïV—ÿ³z})"»"“Òž¾øµýý*Ïtð«OðZY?"W^g!·¢ûõÕþûLœ]=¬T:ý‹ûÕ;tä­¾È|0¢ÿÒ7¿\¾þåÝ›Ë7¯ßu¯<¨ —9-{ÃøY'k²¹gÏTPƒ©þ„¿Äï½Írï¿Iã d&üþrn<ð;­m.sø+ÃïäðSýôæÕå›ÿüåô”˜{Ú\—7Õ¦¼~ÿq}ÿTö– Ë‚«Ÿ¯ÿ€Rãôp'þí¢7íæAq|ÐdÚ›á“öô¤Ön»>Loß+tî³V7õâïfønÈ®°ð¡ä¹…±ÉÈ.ÚÞï?Îè¤BeÎZ;ø}ØÄz™ycŠÁ#‡í̘LÕýÄŇ™7¬dªÏ«ÁöOö‡êðt(¯g¦#MÈ «OÞÌŒMH _È _µ›Z¡°ÁÏQú@ ¿ï­r›Ym£fðûV«(™gªð“³ŸÓrZgJ'Ó¬æÍÜFgÕhÿSÞ•3*N¡ê>p½>¬g·—)5”àzÅϪkP2#Ëzä°ªLýûæO ñ™· õÅXÃü÷HÔût`'¥ÚmíªÈ,ˆ‰N…ŸÃÌû:Uüeú¼u2³ÖÔÏÃOCŽzxÕû‹´&sðÏN'O(– þ‰ÚBÚÌäÅŒ‘q¤Nôžv(¡§§OFÆi´˜µ…9þìêA°¬ Yx˜®îpj‘{wùvny—(¤½þõÕå_ß¾žY×·*V DA^Çúó§ˆöq?Hè=|Qʇ¹…¿”N[Ñd3«°TÛÍ ¯¸Ðìè±õæzVŽmæ ûÞåæj{]mæ¦#ÁîUÒ^´½™™„]Ź?°ø– NjCeh¯ô9·ñ€‘Ûã[D##3m*»°¨áÀúÚî‡Fe>r|9”ïÁt*wg¶=Òf%WëÛò½œ[ÿaP«þSÿöîÔíÐa9ap&†)-ý¾šö`D…tbInç,IRôñlH@Ó,>},ùªpGùÀQ,9ز àÛÀ½"aÇÒ±A ¾ºV¶©ŠÓ˱Wê4Tð’”­Í¡ähÓô P§ëU$©j¬€&A3†Zé Sù—Ö«l Ó&Ua-]lþ¾„;=8°MÅØ6]-´M=ÖшӠVƒA¥›¦£º× ›M =¥ÓlÓ³&dîêšRô~ +žaBb±­×=T±Ä2£ôˆ¶ òH SÑx–¤¡0§j4EÐëÒK\“qP®]îàAQ¤ ÓE´†¦>‹m‚¦q¬í×¥UIßjŽÕ=ƒV,tò)«g*¨h½le6øXÃ4Á,°Ú²$@K޹BUТ f)ƒQŸƒYê(FYn¹ò¡>·N®ýÇÕÑyÓö@=c–ŠySÜ(cݼU*ÒV> 3 Gƒg­RÒ|ï!?¢Š9«4Y—(“Yé¨É§X¥"jê*̯ÄA#Viš’†íÓ+qÔ¡UÊÐÖð=ø¯±ªÜdEAš§«¥®Ïš˜+ ¯ÄøôàFl566!P?²bŠ˜Ø ÞP ý«Q;\^ Õç6±paÎÁà)(bo+^´6·™Ë¿2±uãÚ@a–›x±Zl¸QP¬¦OÏe<ÌKѺÞïAӤŦ1` :Ì/áV$–}fgEVpXp²U¶¸ÌZ›É12¼ÇJj´`2™$r2ZX¹ÖDƒ‹t‚«OkM,:ƒ/cIY[o!ð‰R:½Þb>‹­·¨ëeŒ;üKLwÆ{\¶ï˜ô¸\%Û\ÊÜ çÖæ’ÞFÞù⇘§b‹§ûjÃ)Àïª-¦C‰Õ3}.ü&õ¹œ)`èä"—õUsÙ%…!Xî[xMáŽûèŸ)š¶>ÇÜÑ[<§’£Ø‚Z"¼fÕ,H峜fÝÙĀߴ(Äd×Áï=8o‰¥Ó²&eÒB¥B…Š'œP Aõ)R°*œ£€‡µKÄ ; yŒÄÅì͆Wö:(1JÎö%¯8[¤Y’ݬÂ#,_ ¾ el—˜ ŒÝ'‘„®aàz_î`qÛ^†©U­5÷@é˜[ ÖY£Wì›×¯_³èÅöOÞ8 w©]XØ¥°*tмÌLj5zTà¼ãÝ•7àn®Ê댵c`#³ÜxŠŽwe™)ˆve„U…g¿ÞL‹Yø|ùwrÐa½¹žíe6ŧ^&ຆ¢¤ñ… Þ²6Žv¿—Fs&’B~àX‚=/}yÅÿö]ÆÚ;ð‚¼,¬põÏјßv‚÷#¯¼Dç…Þ…‹P£=¡&¸ÇHèsÁ›÷Š™1'¹¤Ó6E˜Nµjd¡ˆDs"$êq¡° ,Á¾ÒEè°¹)´‰­‚†väÓµ°¬6ëÓXq`¶IG!ÿ|¿]À(|‘µ£–66ë›þüy[m,M‡•t°b„ÛµÛU‡»žuŒ€Ô«8py¨®2ÞŠVXÜ—¿¼{ó‡nU/渎…¿;ðê¥ñ´4¿²ÏXKº¾ Ò9‚Š_x¾.0Ž ÐO,^ëŒmp³¿2MmðEìv÷û<[Û¡ooˆé¿Ù´7³²”e·„Áõ°¹Œ”Çr´$ÐŽèu¬%_ß—W‡]RÂ6FGØ·žólkйE,‹¬p–‚m½ÝT¼U Ò&§Cî<¦}\`…¤ ¼¹­6e¤­dZT³ }¼igþø¼XT˜…Ï.Ìïp¿0¿0î ó ’’Š™Â|wÒN,,Ì'È}^a>Eí¢Âü~4¾-Ì'HH<›Iæ¨c\,,Ì'˜}~a>1Þgæ×ç‹§ Lïc·äÔ;‰îëÛÅ8¥¦ª.û?›“´-*l9Cv„H]ßœc$ÊGJ1d€ñb2‚Àfó¡Àè±®‡û-ɸuj‰ˆ$Õ"w"BÀ·WÐq„u²îR‚Ì\®Â7‘ ›ÏFüuÐ߀‘¾•˜PðZ=SLNÀ߀”ìPo¾˜PØ|FZ19F¬ n¿ #ö³9Ù• Ë»s 2 †æçXóí»^c{Že±¸‘+²<Án=”Âôï ]β ½ˆe1¨ñC–)X’e‘Ú$Mƒ–»Y–§].²|Â1Yæ4’id™4îÞ—Ÿ9Å”EQ·;¡ûD fÊfʰHDœŠD´ àÚ•««öüÙShUbð}Tí¢eN¿¥;qΩzw(㺃‹ªOA±¹Ñ0¶ú˜Ñ[²ÂŒ(žmõ!ŠO´ÂŠE¡~Ï M¥¡°™Ñ“ZƒË%)Ûþ…X¢eް¬Æ“Xª¶ªŽ¥ Å™ñÓVÊH õ‰×yBãífZS¼r€ íñÒëb8Ò¹•{Í :Ÿ9é)Bêp + šËºY"AÉ/3™ãÅH¤ mª>•÷_XP«aEAW×åæPÝ|aÅ?QïäÆô°¹ÚrØ5p²îºåŒ7M³ËÕ¡|`Õhj=P°iikVžòhSÄZ{^×'¹Z`±´9Ëtn‹‡ìÙî@‰MU–dA¶6°0| `ëhÚ§¶Vo±M¡ÁÃÁó‚'pÑG‰øíbŸX9!$ÔEúÔÈïÖyŒ¬ÉIFzMå–”¨i2­Š jwéÃ?Ÿªëû21K;àb_b ÿóŽU¤nÀ ·JQ Ûû´,×/¿öäw«6¬2uƒ÷„YJÒweµã1ëx5þ+3ëù¹Êý#ž úÈ«T·9lIk«¯Ö^îÁ*L•‚ôí/Cü‘ÅÇQ·aY•m³ªÅظ¨ugóÇêš'$X;í|÷ž±rþ%!ÇÁ+Y›óñÁ-£÷÷Õþpšç‘ÁÓ#JßxÊ`²¦Ñ}áÀ¡,´'¦¡©Í¾:À§Ïa¡0ð p]õ_×ÿ‚?‡U` ¸6=Ö›Ãuus³ÛÔ‚ôþf·~(é9$ííÚ×Íõß\°|±~<®¨9.ß$?üÈ#AÊSx\Ý#¾ÐY.Íñ_MºÄwܽ š ºŽòùêAÿ‚–Á;¢Í¼–´`AXvvlèrªÓyûö%ýMƸ½‚£l}ˆÀÖ’­3]ØãXtÕ×=ÁŸrIÓuQùet‘ik¨Q½»|KËÊ ‰¨`ðØZVþúêò¯o£Õ€&øº!û™‹„Ï8\¹—ÝÄhÆÿþæÝeú÷í; º #ÇSÀÊ.;²ÒâF êô®¦mäöÕ¿xk а0n¿hN,Q ÖCOP»ƒq;ž¦jÁÄXoyÄz™°KHª­£Dʦˆ½×´¥ÀçÊ(çPAr£;Ôɽj³A³™ýÌÔňähÏœŒ›39°]§qàëê yÞ:Æ3FR‚ß-ã­b¥ë1âKæ*¶°“ ïÊûZÖöwÕ#o‡ï´îsù䊋¹†×s¨¯¶1êXÞyÒVg1”‹uuñe?_<#nÚy7E!¯?³ \‡el¼¢ ”0­'ŸÀ)1Ö‡s+Žr=¤¯»¯°x›…Ñ`„[ tÐÛcã€59VQ¼~dÑŠî0ò%D¶LT “øJ·¾À³SfRZýꌙC–§j¼ËÍJ ·gæÌëƒ ® ™w>Ž+.nwÛ§Ç:êý#‡ŽzIHÂÛ‡7½ðéÕýÓ¾úX¾¯_”$r±W˜VÄæI¯ØS4®}‡àL£ûª¹ãx’POúªQié¾jƒ{ö«&KK÷U㸿'y1ÓüHsMT\”<Á*ï(f¿,—=q lk«‡ã5©¡N–˜àƒZYPÙ°%Ф7V›ëx}M+t¬L7Ó°øJ‡žQãV¨­7õߣùëÏk,ýI2îGÀÌY›p­¯%Ã+ÅÛ#L8BŽ/šùM«œC@3 XC1ðr“´øF# ²nN`VkN!×õõ'è-'t«"ÿö9ÈA•œÐĆaA£éO=Õëe2© jêóÖ "2`\kò»’ô"uòËÆ!Å…ÔyÎaVÞ@ˆýgNÜ V’ÒÔÔ¥J§ˆ°Œ‹@m[¼ì3†2A?+„@)“KNð°.X1*P¼î¼Z´'ɺÞʃX[à$±‘0‰8?ylm(IÌÙ&ú4¨W™ËIu2WÅE+ýnÄà€ tIܸw%˜\x8†êç…¢±SŽVèm’i>ÞD%l¢Ä8K?k<ɯd9–újÏÚBmÝY™˜ù}ysàl¢}^K¡F¢çÅsxxW¹«nïœ}TÚ ÕÓu ÷¿¡‹ÃQ'XŒ}c‰Ñ–klÈ5W‹Do~ «x9µ6œÍ¬xk %¬¬ Ï ‹Y¤ò”¸â…+,f}Ñlþñùï¬ýÏÔ^ Ù„/û!â%û¸r!-ΞY§AÁX)Ií‡íá°}X„+Ú­%dØJ/}Ýž—W‹E¶JÒ˜ =ú>°Z¯Çû삜e[Wb_ÉW0–-qPJ;ød6>àÕ™Ì,µkÁží¦0‡«6™Y<©â,Åì¾¼Ú²D㕎âõ¸ÀíD?¸jÛ ¯óÔa(¸ßnßóBShk õ†ËÍéÿ‹D÷F]·C~f"}‚ªÈœI›ßI>k‚Òe®«X>÷ÊÇ]yU^cß-úaÊ;sŸùÔ@Òuµk¦?gš¦¾ZK¦Msý¹Ú¿ß—‡x…XÊ<ëe€Îœw“Ò°ŒoË÷’7 Š€în¡ÇÓ‘¬à©‘*“® Æ›ärGû—÷h(R¸¬à©qy欋ƒŠÚJl6Vµ©vÕ‚òëý¯¹|ÿ÷pA‰…—YÈ%¬äC'1hq¡X\ŢȚJŒÄĪÖk±ˆó XÜÅ"ŠVÈH,Är±˜ ‹¾Xüú>Z'eáÛ„qIefÎW§¿ª¤²_“iA‘ƒ×u!æ°¨ÿ•H¨Ùž›<¾ecõ¤öi¬"³„Ã# X é¥ï½dhDª£—8ùÝAÍ|Úì3˜ÍAÍsÙìtx«=¨é|—𞪥j¨ß'©Zê ¦©ObMòT—w3oÁ¦’®Ã‹NŒÍ•9€Ž=£ãM Ë¢dÏèkµëßëäy”ÚGlÜXî˜ùxl¼Qb¼‰…)£Ü&¢ÜHRŽ.,1§¸†.R|3ÕçxJŠ$„ýìÖ†ö±®Qg«fçâŸ~ˆJ•¡¦‡?C¡â½¢Y–¬+®R³ùÓjþuŠÜsÙ|º¨ÜGc 7KòÒ§¯òLSÚzsîäFíaüƒµ‡eN¢²—gݧÄrÒQ…n£½Dô7êYÿèll«Û«ûoHkª0Ûj÷ê>&±W/v{õd¤"q¯žiª ˆùÏ«­íd#WõÝc“*ÊùÝo¦h@4[íyõ}¨çëÔùUœ¹wc¶dY××äµ “#ØåþjW=–DªürYPDÜÌÃΔù° Ûß›–Ô„‹-€'¨â9U¤µmé<ì£ñ±b)Zðl¼"el¾2•f›55 jIj=Q¢\“ä~fZJ9ld$·%7 &%•7Ed ø «1X–"«*$ÅkJDí¼RÔ®îM8SU,fSÓ€J s Á†À#Xq<Ëo`Þ—ówÝÌy)ÒÕù-bÜ FNÔGQv)l,qQŒ’A²x–xÔÆS!±)MtÈkÞâ3Ô¥"…nÍ ab=’Ô’üh¬Ì™ÍM؃>£s¶¬vá8ÿIç Ýúþ~°8y•"à\õƒ ¯fÀ&(êsö ¼Á’Ëxûá@py½ÕºîÎZáQÍIYð›fƒDì8ˆ¥éQTXÀ;f‡DÐðx Ü‹‰,k_ÓÉ#ÔŽßÍ=/v–ü“âvöRÖ9¥™Ã|¶W·²ÐÞÁÆQ.Ünx†¤nmÞ8·Ì cÜɽ£¸Ý—‡xäâÎH.Ó–¹E‹àöú˜Z˜ ¸ÿ’Ý nóÊÄ…•!“äN‹_ˆX8¯v®(~'±m‘ÜCVaæ7†+Î.ŠYÕëÔQÆ;ÐþnûtÍÚ‚Ž%8…rzÓ ³+ ^Û"½¤PŸö%¯ð¾.G‹}„+–Û7£ ©œ«)>Zv^—‘Š„æ’¤ÈÊ "{C†1|v™ö‚/ЖnP¿ZzÆÊLc"%NhÊŒ×ø®“_0ü”,ÎÝ;”|Pï qT1¼vˆÑ¯¾vHCN¸vhîìf{í¹v(ñ8k{íÁÈzÃ<ºÙ\;Ô¢Nº'$\;4sÊ¿»vˆàbÇ:ß];D€nèQ×a»¢4½³V” mx¤67˜gn2šãµ½É(ác¥Ÿyén2š‚ ê&£‡m››Œ(z¯õ“›Œ(&蛌ü·ÚR…æÂø”Ë€Þ£Õ28JÃi€1ŠîÍbæHSú íîHÓ`:ô¥°‘#MbáÙc…­áÇ=ÄsΟ^"º#MÑ—´G𦅖5Ö1ðþ>q I$=‹TFÄØ^›ƒ§b¬=ÏÔ‚Šåg#ç™Dwö˜˜þ÷,Oâ(¸©KŸÒ>©¸É€„K uëjÂÃ6þ:¹dôáÃRMœ.‘1E FË ÎcØÂ“ ]‡IúâÇYËÙeÆôé$,÷‡í®¼fß—€õ2Ĩ+æAƒBg•g•‰vxÍ’ŽÃŠ”ËfB»…‚ïQMò|wlï–P,=wk-M1xî¬Ôx}"]S‹®Vç/žå¹+ ;« Óë_Î4Çgã÷÷ETšXÔáÏúé lwدÜ=T‡C⺛ôUwy¦§Æ¼[onˤpz¬Ù¼E¥NU˜e"™­ó7Ë€[YÃs§XøN°€9¡9í´À§Uè}â™+Ý„`Ïö®Íêµ…K+‰ ©W2(øëd'~³¹®0V½çôhÎÁòsNŒ¡ŸÕ² «ù0ÕD€žSéä0›¡P?3ª¾ñš: z! ):uμÆ[KÑz³[Ы½Ç+&CŒ¤R±2P’Ÿê°å\-ŠÌ‚J Xå]-€†ÑãjAÅäNÅÏÕë>V¨Šb ­Où­ áÃå2L´Â°Y,W+8¼í÷›(…!ò×Ñ QÌ窄(è³4B±S‚«N¸‚­ú÷b´ú€ýâ÷b`¸3Ž[f‰g蕯ÃPqÜeæÇ—#C(jt!Æ+œ÷ļ+ º˜‘WNGÓ1#±0œsô$$žwTÅ·í³|zÉ4f»¦@$ñßä9؃x纫&Ï9 ¥Ç3òœ‚è‚p‘˜öX&P¿V×/©M¦Ýl´ˆ×q!dN÷àÅWémãm}KO|Ðà ½ø°ÞÏgÄ\®ÜP„ v$±°EWnÕV,; ª”Mfr)nø%ÊŽâ–_¡,³B ;Þ™ƒ«,>Pqñ‰àT¦…œZç:cÏ~ŠÐ«íýÓÆw"¤¾YÞ’Êk´€wÑE°ÊîâÎéj@œ‰.Ï•J¥3#%™ÎžUU%¥:5µ·_%ôfBu°ã0kPÅ •rR *@nkP ð^ ªXÕikPǸ"¹‹ãL ª F» •º[kP ô/jÖÖ FAÅ uµ¸Uv°bÑ•cô5*MÁ(AÀÙ‚QšÙ¶`ôë2ÛŒÌ~‚QbÄÏ.%p¿FÁ¨Ìê¢x½h[‹õ~_ý«lvVª•>Š_÷.ñìLûñ`aP°`œL)ÏK»?®Éаt-KR&§­e!À›Zn¾kYZ`ÁkP:Í74µ,ƒážê.þ›yŒ¡©e!8> >> endobj 42 0 obj 65 endobj 43 0 obj << /Length 42 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»åšr¹äÍB¶Ì endstream endobj 44 0 obj << /Type /Page /Parent 4 0 R /Resources 45 0 R /Contents 43 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 45 0 obj << /ProcSet [ /PDF ] /XObject << /Fm5 46 0 R >> >> endobj 46 0 obj << /Length 47 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 48 0 R /Filter /FlateDecode >> stream xÚÅ}[³ÛÈ‘æ{ýŠó´!OHeÔ½ªßÚ=ö†"lϺ[Þíöj£ƒâ$Ìð2ɣˆüf‚T—ÄéõDŒ¤–·‡¬¬¼Uæ?ïþv÷Ï»?¼¹K2ysWÀÿ~g£4&Ý…äeáõÝ›‡»ßÿIÉâNݽy÷b]½ÿÝÝ›ÿ¼ûã›»BšÅ@Qõ«;—¤µáò£ëüïR¥˜‚»{¸Ó~÷ô6w?ÁþðFtW൴ƷWð¢zøÐ<6³ä€K¢ýò¾Zßø mLÉ\¿¥–…8½¥•^Þúioe¡¯Wøú/ÿý‡×Âù2…’&†«ú÷¿ÿӛ܃Μã¥3×?ó?ÿøãO¯ÿãÆêLÐÒ抎¿Þú÷QKÕY˜’öÆ«8¥M‘’‘ï~ýSó¼ŠF8¹ŠI1ö…ÃY(ÛZ¸Dëç½R2úÓÏÃ?MEhýA… µJíŸÇç |Zÿó 6óVª0R9X!ˆ“†'!ßÿøã÷Í«üM–‡iÀ¢ÙoAª_/ànoƒ BÆ5ÖP¨Çe Vk 2…úïêß( ÒDŠZT¿Œ¢ ௽fÖ^ÖúëtH¡‚•Qyêõa‹ÓÛ±ÇíõjµHÕa–^­A€Öp~$G­¶Þ b2­¾VÒ-PÁdƒ ðˆuövìh |-RX׫c™Å[Và Ká~Øí¿â•Ò0L?Øc5³O°÷åa½¯Þ•³”A*¤·Êµ°oìÛ ê ˆÒYöÓÇQÚ ‡ªÀþq1ƒ*õÛ¡Z¯6³”­I³Z b½‡òx¬¶FéÛžY­¢‘.yŠ‹]t„Ñ`)Ð÷³äL¥ =*'PÑgá0ËRÑðÝt$ïQ©óܤŒ­¾ŽÒŒ}E±**^”³¸ÓÎIÅìûÝ~±UîüÝK1 Z!*R¸ÖåöËR2 <2Û¥ö¸ŸI.ç¶þõ„+¦‹WŽ[ص*&•_-¨°êë,n““!hKÁ–›Ã,j¸g%àöãê8O1‚?åhn×»=|µO»íý¬ƒX…>£¡È8îæ> Ž_(Ôû+*ÆŸ>è69­3°õé3ÏÊ× ”˜¥èý´«¶ÇyV>ê±"’Ô6FÃýLCÇHï~ò!Äd.po¤¨¯Ìú&äI删Ár€íѵ 'yâ‚ bë5¨†6êhS7kåG+maîˆuvý1ÅÛÁˆHÑ_¬˜o—+㤗Պœÿ0+¢á‚ĸDžÒ,R¹ Ì}«…[›å³t.è™:™Ã/ä<…›À°Ó‘âöõv¦¦d´‘¢`¶¡ ÓÉ“Îê‡O›òpœÉÓ>HíûÒ i8”‡—ót.ꙃŒÜaÖX7 \ ïoº<ãÏ2ð$½A¯:zåòˆI,D/Stª‡,¾žEnJRÙ”±à}ùPŽ<ÒúŽð0l‘‡ÎØyb”ë†^"¿Ûjž'e“ êòÙzž8“›y»  {½Ü¯Õa¦Ñdd@‡2»¾òP¦M^Ú¨2°â$Ç+O­ ÏöüЇŒG*6_.‘4̇`æJcŠ. ›­µ1ÄÜøpíŠÐÝÉóüŸ»S^H‰.êe_Ìa]5åûKÚѧE…¼ÚïWó‚oJ`ë¶pÅõ—»/çÙ:&l ÖûUÎ3ul” =÷<ê_vûrž©4X|Äjh<èçíâ¢Î+RböuÞ&.’Œ:Q4 E[¨M ›7YõÃ,fµÖ2FŠØÕ¶ú¿«cµÛÎ5u|”ÁùkvÝS´avø}•<¦ü0ÜX€ÓN£Î#7:Zċçj?3`|ö+=˜’Φž[¯&}±¶†Lr³wòÃêÛÌ€<ü8€Ø}ùÏÇê¢ÄÄìà"õ C}÷ºaÞG…Œ)R4?ìê­1˘ԅ–ÎyŠÕf·ý0/€ ^…¶*,^<y£zy8×xžÍŠb$%ÆFðøØ³œ0¤½R ¬˜*”ógda µÚ1éPA„r<ŠY¶+£¿*V¼Ø¯î«¹eÑ"ÈÚ€HÈ™ÑYP¼1Qt¼ùXÍË5jL ›Hñq_½ŸiÜ€ »HÉÚûr?³ú< E-p÷»‡YôÌZEn¹YÖc£#<øÛ¡_™4¯|Èãß«´Kì·Mµ½ßO+iiµ&º‰ŽZrÇŸcT #:†ÂE1K£·‚~Ðõ*œóåcµþ83wI¤V;7Á‚©+SXöË,!Ê$å‰ÅŠ»™‰«â俥lž•#4ú­ž”®&iV3*U½¨«™Q2­ì…DñºÝgº±¶CSÌÎp°Å“±ãêADµY‚~tÜ×vƒ˜ìûᯪWÿw(ãr®^¦`ë¿<ý® æX-ƒíÅõ~“w¾ÀŠ'X9}Ô5yÜ^Þ™ÒŒÝ傚 Ú½îâí‹ÃÛß}7JCváU᥶-ô«:Þj»Þ<ªÏå¯õsfƒOp$c$I§|¢Õÿz¿:®z?é×X—ݫՙöIïzŸTôqoÒ!F.Ÿ4û_£6aw±K‹b¤@Ç鸨Ð"äAÅ‹ogÁ›CnJ2zÍm«ªæ$‡ãþq}|Ü—¿nªÃñWÌwJü¿ÂîÿµçŸgœ,(Aåê"‰n…ÌÀƒ«¬ê5ªÉYÑ¿7åÚ÷¦uoª}ï nʵ­ÓKׯ¬R_S[ïÎ*w~Œ3NÇ8DzV¡tŸt—’2 k›Gõ®]´h%³ãÄKu® €3Ìõ+=‰ýÛY›‰x‰.²­KÓ® ÝERÞvDr ¾0E6’KÿÝRˆ ¦.Â;Ó÷óG2ùq;Ùâ[GǺÈÐOa¦ñ+êÜ1µ~"Ë}v6L}^àh¾‹‰Kï^JTºAïUƒ|*×ÈŽŸ@O¿8¼¼DÓ“±Å„ @u\ Œƒ*ÁI…š!¿vâJÚH±×…“Ê üž%öZA 4%öf±ÒTðªS,±ð}Y8"å3xÝ›€§üë±Ä¸~›¥Džò‡Gê‚:c娥m¥AfBB³”âýTÏ(æGHp$1÷ÔuÑ‘Ì4Jã¡iëÉ9Ôtp=‰RÂs©Á¶m –æ˜ÑäÂOåAœÄ°Þ<_— qN6qA’óu†ží${H$5_ªãG3ðY&™am&0'ÁN -L%" O-üéêK×°5(³ bï9çÃõ3çdEUf"Å~Ã:Yëì…¥ÀY'+F× gZàb¼¹GYÙ¢þM£#±ß‰r£üÌ+“s,t\hžÝXÉÙǘöÊ\¿WëæË@ÖÚ€—j)p¦¬ñÊ·-d‘åØ ¶± ÔÚ¿²xñNEbW–­Çm2‘¢åâ7ÁßÌSÄ ¿Ð)Pý‚òÃw¹°2i<;à‡YÛºöy…•¿ð'÷’å)Uß&^åø±b½ ÖÇ`ó"âe¾T› Ë ²õµjõïJŽ®Æ«U],Š–²Fÿ0yŠ˜u¹=îKžƒˆ%DŠZýÈÀt1.¥Ÿ‰TœÞźsx¬Î7¾.6$Ö^nx¢;EòàµaÈQú :ƒ½ð¾¸Ò˜¿ õOë'øš™Ï‹8ˆyZV›Çr ½ÿÔ‹0*É¡´} ¾Ìƒ¿fy‡‹YÌ|aÿ0uÐÔÒ‡„qÐ * pœ-ÿ•å@{´13BsâºåŠ/ÈOúd‚°V‹×H]ï!çóãžut` *9êVÖ©Š ùPðóàhÞܗ׿ Ga¢ î½xŸ‚Øx™!ófPg:,‡öüɼ™o)+|z&å #È"?3i߈±Ëo”²NÒ™Þ•i¾nO)ƒu£cYðIÔäœðÎæN ô®y314Ño ¡‡.Ƙ7Cš¡n¢‰q—üÒ‡â^ƒºAiæÿ°úZ=<>dóÕ£ƒ‚é”Ù8=aiJ/:åù`PXæ IË€ÂÖXuŒ:O P“â,ÝZf³*4Hº+ÿ_Ëý$K¡Waç­š€ßî¦0Ó+ ÒD˜[äH¿›-.e!&® ±ì!£uˆ0‰ Ž}}Z¥_îTÔ6|ž”GTð¢N(±îÏJ°2¿ ¤°Ü¾dQ¢@±PŒLdÃYbôâ“ ²³„¼ bžˆwÒvÀ:!jßWS²÷}èúîCŸª&YŒ`/]§NÐþeqZÅ…kYQÅ~7Ÿè¡'ƒ–Q—–§Ð¤“ jꘕÁÅ¡nÕI3üo²ªìÿd¯EŽ,²:N698 S¯ k·œk’å—/çzzÔÍr®_/=.¦¸@Ù®óÅPa×dÑ)ìºz×®(*ì7WÞv]áw »æ<Í7KÅÍ®ÉV ^Š,BlÐǶAiÂ/’¢ÀËÍ«“oõê¸{…OâdЭ’I)Š¥ó£Xö²‡Y‘/³ç€)¬¯#Àgm®\|!Ù@Q4² ‹ò¡«ó¸Ä XÃÁ…SûK½¹µÉ!C$ågÇfcw ç–­oÄØ‹Šžg¦olÿР?Sž³{èbïÐ+BÓ‹41}Þ…³¥ÿ*·‡ÕàŽZû=3·WÀ×Uø¬”¬@Cðõ-4âû¾aUòÒáá˜_Å+s,\y'ÀñNKeªºžƒ`æ¡\mA+¼ÜpÒÚp÷H~¶œÒÞ¦Bˆû9‘Óvýh¤ÞÁ&Ž ”´[i(-,&ÇMEk³Þ*]XﶇãŠg5€—ðÚ$ñŸyY§Óœ»ÜìÖ˦ƒüÖ¿)ø†NK3˜€Ý$© [¨Œ¼+ÆæýˆK'–Þǹè¨Xmïy• xð*’ž»ÇÍ=GñkcÀ×ÓÔ¦.´ŽN8¡^#ÅóÏ 3-Äó’M^I[DŠ•…Ì8»ät{dˆy>#ØÍ°ÉúZŸw¡Ã;°ÆQn:ð-µ/9‚ƒ4ØzÀÿ©œT²Óin]À‘…žV{ÜmÀ“—ñë§ê¸þÈ+/qÒ)òõ$'¶Û|xlžzÁÝÁôÅàçsú⌟Ï_Ìy7ù ü3‡—&A3µì¦ËK“Á –>ÍÆ¥Rø)‡1??rÊaݲFu#&jáç4ÆlZNi ülÙΦåœÇ ä…LdŒÏ”œ·¤}65˜É YŸMÍ9•APS±$æœË –ÎÛF§d…]g3#WRg3Ü5-7ÒSÅåœÎ Wï$‹s>ÃêTßWŸÏ`\¯+Ô*à¼+1t?}’Q‘Kh˜æQ·­ƒžÎh¿ÚÂéŒö«ù@sóNZÌõœÑŸ!׃Fµ‹X?·™hå IrXÅuº¨;AÔ0/iS÷€'NV¦U› †Lì=eÁfXÌ>KîÇDüL"z¨6›ê¡ÄIŠ’×½ÁÊɯÌMøèàëÖŽE¼„Oôà “ücJ懛‹^ÃÖ”¹«:1ÝÓŸ¤Áž"çô•ÿæ÷*ŠFÕ“‡göý@݃}?vædM²¹`ð_ÃÓGò§éoê‚­.¶heMHm$p£\¤Þ€ŸÚÀ!ßmõÞ–ImhªÈ“/0Ò¸"ç%y}¸%¤œ;™ˆ] ýêNæãv½{|µˆíGM0ýYp›Û‘¡¡-ìá=¿@µ ÁM¡š'ˆÜ|ÞI“…-ù¬&5èO‹ÏZæ³íWÀÉ)bfd„Ev´·‹Ôò÷+V'¯º³\_2›«vÕ#O)€ú7ž¤þí‹5K+h ‚o(ôëFÖó³{8ÁÝý‘ø(ó¾Aò7¶/K9\tWïNå“Âï|/£Có€…“Â ìt}‰å¿ãpJ6~[‚›–ƒÁjÖ¤@¹yŠ fÜÃ2>zê†Jj†ã2`úkMRÄk×d¤Õ/ÌúR¬óJ–Z7ÝØ}¬[aìiÓæñ¹ p¦L EÍŠÕ#ÂÊZùP¯U1b^ŠrŽÞ°Ç/e¹]Äã³WõåsZh´Â…LØ]ýŒÞÙ¸ ó"ŠMý-ç :L[Í?–¢çøqÅm€wž‰`EñêSÁQØÜ®«´õ/—3ÇTƒ³0%jýèszá;ûÂ)8Ýcž¬5 G9-œ ú¼ŽÃÚâÀLRv®â<Ó8¸Úäwœ¸ Ú¹ˆ¡–_ÿu™ÑÄÚE©™$£KSºÏ¿NÕÿ@Iâµ€ó"Xí躙úË ê(Ó3]“Vyô%nIûô³\’Î.z©;ÒYðe®HgYæ†tvÕü Ò”ü-sA:ËÇB÷£ó22\U$F^¾I¸˜};ú‚+ØÕsWU?`»›²Í-úÉB7˜³ä§%(ËüP+_¦ÜÇÔC¯Õo\îcŠ:Lõ[”ûœu«Üç<åƒQè>F]6Óz«¥*}°½ º~ ׊GÞ—ü2Ÿ+ð¹e>±6¥ðßœ~ÖyĹÀ)ÿÆqy1ªë Œ½›VB4"ü|2:«yM°Ò`jž±—îþ‡Ñ5¬º!–έ;PRÃÎ"ÀëK¬)JzŠnß|l°®Œ§Ö^Ë5`T†IxfX­¨ƒî5ÜægúY–\ú=ø § )ëBJ=T4³eÅœ~ß=G×[é5ùu©1¶£û [8"Gî©©´$8¥B ha^ϼèÉhê@̸™#iqAºd=^²¼l8”n f,¹5y%:ˆ©•3{`nµðšB?”GÞLLq\Ö.æµJ&Ó¶NºèæÉËpÚÖÊ–æMy™Ÿ·Åªõ@ÑÂÍÉ_7!–ÎO>Xoˆ $x¡ °Ç‚¡Zíy‡Þ³U¤à¼+ê)Ç4d6†äçS¹^¤æKlÄßoU}ÊJN(9àÎBEzD÷þòÈÉúÇ„˜¶~>E6Çêӆנ]Á°–Z=ï Q< ºä5ý°J:k(bnd;œC-ÙÑ?–Š$/bÙÙÕÚÖ3^ÉçÖЃÒÑÉQïÀm JÇ)R(«^ζn¯(j>³r¶ç&ðÔ~š+&õÞdw7Æë:f€ˆ&] gŠë<‹dJ¹Ø{71ÄN«æ±¨›¥¼®‹¦ øÚx«€¿rBÅuÒFÛ‚ÌFñ-›Ã8ÉÔ¬W¤?¥ìT;^=$Y`0êü„ž ½›¡‹ØöÜvßÞ(ûÕ=oøü«)~NÎÐlËÙR£ÔÔLó@ë1·O½œ­ÄÄ¿ÿùõO¼¨‹—…1ü§€s\­N¨&™!‡¼àõ5’œE¢ûÚÄÚþùm£ûXš“þ-¢ûçG E÷§OvËGø¯ÞlÙÿÕ›,á¿_*Âo‚ŒÑ$š”ãÕÑ^ÄIé×Ñ2£üÁ`G¡ó¢ü ø/+_:Ê}¿žù¥3£üZÕ­û pv”ß‚‘‚ <5ì8PõÀfbõì8?*CŸ€€çPç4E 7Îo¼Tšff©8„Mï1ËÄù›h9%›ünƒ¸kq{eJ£Ë#'¢í¢Ûº`nÛm#Þh&–Î Ü&lD€!Î ÜbOÓënùbzë»~ÄÒÙ[…ÕÅŠޙʋõáØ&ȹą9ÍGqè”'…>Óœu ØvÑÅȸððüc¬6ä–} ’É%T,É)TêoÏVƧ_£Ð…m!æEXIƒ|!_b~ýÓN®P9ƒ-í(jê(7Ë…IÒhGÁ×Qn– ƒÖáµÀ̼Ô#ŽÞ`Ib^¿ç•äXé Î ƒ¡Õf ’—¡8ÕpâÝÌhjõÌLÎÃÚIpîÈÚ¥‹3-›ü%§ÃP£%ërýUGŽÁüŸT¼iÂQ²‚`ŽÛ¤ µô8£,+ K­ £(ü«ó\L÷ÒY×Üg[#€½€“rˆ¥¯wû}yø´Û²FJ8+mt™gˆÓµc^DCÔ;äÇýʳQejúÛ^YÚ-Jï.o±è½Ó&µ‰³C°ÿo˜Ú„Ò'V>fÓ6º‘Ù¼¯Ÿ6«õ2C¯ÞlÙ.ÅWoò ]Нðº¨TÝ,né&Åð©žþ'ô»Ñ HÇk©¾* ÷Ÿ Øi˜³[–±|æÈyìê C’Ó ÊÍœyfq*,ñ}g5 íŒ<Ó‰z^o\¬ t«C(Kƒñ,Å·*#sèëÍŸ1ÃUðx΃£àìGv±8|ÛBÃ&ÐK'°A5¸ x6XÃJåaË ZÔ²¯sªŠfþZi°»0ž›_újÏ«°^“¼ì¹9Œ$=j´<1Õöž™Åðþ’XûWn…F;ý¥:~äUØÁ ^¨g’ ÇÎÔ%ñz&ûÔxyÀžv½ÇN£‰—G%#ºÚ„Ð-$IŒ[ê`Þ˜­³–DãK4ÇLÙ"ó“H_í¼zöÌñZý]O‘=c‹I1§AÅ\¼²Ô¹#8Æ“èµbµ¸óà—QÄ|eÝ–ðNE~Pf4+8™L¤ÀêyÞÍ*kúÓ¤8bã¢LNÆ3x®ÉIÝMjuE‡C^² g¥¤)õ*Gî°` ê#êe¾€}Ë»„êdˆ‚Wò.¡0Q,MMÉ-m¤¿òiî »¶1)ê<Û•ô3QƒŠÓƒ7G,9ô+'µ%‰)yíˆQ µ§ˆ©-,ÖÅ\€·šZûé)F$Iƒ%‰ÿÊbæ|ÿŽ`f‘ûwĺ¹—êF2±?¢B±,Ðö1¤Ø€/kxP8tŠX9Ó‰FF4…ε@0·€£à fX&ˆ*€öhÉ¥3+èÐ "Y2A¸N(έ!ع票ÁJŽzévnË”Góæ¾¼6o˜‰YíE×¼Ñ4Ž&åˆkÞhlƒFÏ3o4 Áß †w†G!E~fÒ¾MpÔŸÚwð3"´+lr–gGÄO3QíÞ5o&†/"úm!ôÐEÛ¼™ÀH^Â_jé£ÍA×kOÂ?¬¾V,w?­»1ï=AÌ•öë–Ãb¦¬wOUrŒ9!ëS*ÀúØç1æl1bŒù¶¸Œ1ϯ»éi<öH%ǘ·á‰®ÆbÆ'mƘ_àŤ¾ÆÃ]“Ï}áEü­:š¨þo7܇S d!œVp~V÷ óõAóæ têmš—¬GÛ%K…ŒQ2Áy†^¾TÈ‚NÅþR¥B^@ê"-\+d°†.©}áØæiª¥Ð—hnÁ³v‰¤éò(ÎmVëu=mƒx؜۬6€Hê>Yg­~Þ_ oÉ ž…£–ÿž7tÓi N¢_[“+{Iudã ]tÆñ<+2¾ðe³Y ;zLåÜDwØ€Íalè>`‘þà1ÕCÙó‹g^ÕÄi§±03Ëô ´ô…Òç‡,]6g±•¥^W6g±Í)8s'kwÍ›‹xì|Ø«œt\‡Ì< ¼² ~ÞqëçÔ¢o4þ™ãüáAã­¥ˆ™5A¤Í ªfpÿˆ¥ófˆìiR¼œ×ÙÄD_Ï1'ˆaE ¦ÐŒ§~ž’3— þ¼*Hô‰ãÝzèàs˜ I•3cÂŽ8ÆÞ÷ÙÜÀiˆÃéìZÜ9ä8°sà%È©,^0‰P¼ 9˜ƒÔ€&pº³›:&‡š¾P 50ÛÁ´ïKÂ~ÕºV–¿­ƒé=ȬúmÌó³hs¿º¯V›_?UÇõÇùn¥ Zú®_m·ÒÁ©®åõ›,èVº§±u×øK»•G—ô‹c¹n%hð~Á3~Y–c‰×çm¤p™ÎÉr(µÄ.{Aï÷»ž1Š*1˜i/y·rζT~ñÌRê‹rÀqpÑ-ªÞŒÁ~•¡Á^º{¹q8~/PKçu/Gc ;àܶM&FœjKQÃmÛd•‚•¨ÕŒ«´¤ð»F’TÉKÊZ01=EÍû’§-a³*KÊû¡ú°­x76Šº;‰38oÖ=p§ÐN6$EÌ€…CKÙhZöK®AeÑñ|ã<^¿.…”Ë”Ò2 '_ã1Y¡ýÝø^­üâœ>‰FzôñNkY´éRóž.áâ°x=n“Ö$ðyõ¸MZó ¾l†íœÖ$έÇmÒš<¯·Ik¼ðêq›´&±rVr­IkØÌzÜ&­IÐÂ,ÈmÒš”Àð r›´fÿ ü‚ÜsZSÌ÷¡’Ü&­ySÜçÖä6iÍ.¸˜X7K”å6iÍ+x¢nvFYn“Ö$¨¹NkŠ9iÓSZÓ…k›ò­qiÍÌ[Ï át¬‹Áà™ðR¥˜àî´Ç®éöé?mî~ÊÜ9œ»eü§©(0QÙúƒ AjÕÿùÓÛšæ7VS3_ÀÃÄ ˜n0î\§òêÄ xÒ•Âܦ®CuV÷¢Òÿ~³Y /ž\)+ujÃ÷Ü‘Ã-|1´ü€ö‰cðànpr¢¿,~’ží£_´c=µðÛƒ‡yÁ€·w$ï·3cÏS‹ fn$àÅu‘¬WŽZý¾\ïö7N ë‡ó9†<¾˜úaûQo'£·‚”É÷»ýÃêXz™ÁÓ2™@1tù“_ã  °/ÿùXíoU6 áFíX Þ/w¿•$¡ÀÑÇ«ø}ÉR ÎÈàmÞÏÇì«w%‹0z]¡Hjn ç 7)ÀÖ"Ñ?s¨S]k(jVûj÷x`éSHo"µø»mµ{(½@Ž˜ôàÑ`_ÆîCÎVØK†jGsØ@Kæ±\oÕÐ`§°ç<õ„—œïë4X5Þ“¢¿{ܯY¢ïfRµøÕöžÅ ¶i0$ù;ØY{ΡxÑi`“À0e@Ö­`qÔolÀ§ È¡À«Q†ÂÞ–åý­Þbc )Ì0DŠ™ÛÚ~‚\hjõõµ‚÷ßXÖ–q…÷b`øÍì(“Â+¤ÙÕßO°¿³Cl¶¾»›…_ï6Ð8Õn+é\äs ‡ÄXêû¾ùÈÓ E¬ÇOï°Ù5[erýb‚fs ;:w1¢–kXé;Ø]¡öó[wukÂãS0h07)ôÎ…1[©ù¿ïÚ‚Õa3âI©E[à#§ÛMÚ¾&`ùRÈ<¥Þ¾ï¾qö¯IXd­ñ Ç/ÀEΠÂNûøŽ¥Ô°I7j†<+ŸYJ çÛH‘RÛ8‡ï8Bo­‘ÞSÄܼ(8bùŽÇ æy™¿}‡l8&bƒ¯§“‹¯Ž‡róþ%ËÒ)ð²2)7·®qoÁ|2—åOHV Sã@p´'­Z¬h/5š9yðÕÅŠ õ”`‚VÍ?[dXý¸­Ž<»Xcwhå:ïO¶Yž•AggÐ4ˆ^ZM-µ‡.ŸóuéhÆáXÄXºoð~ñË ÆJ„ä©•ß6fiÁòK‚¿Çä,OÁÉ„'^ž®§€—`ȵ3#+˜7Ã+þnuà…\ öå‹33LTqÏ51>3ÎŽ£óÎê(½¡VÎÖØ„½¤IÞ%ïœ>ùyVÀ';ð¼2ênˆÄÒ?³N$cd´î&íŽÈ8ÿ€™ÕžG Nî¡å}_¾µÈÉd1P{ììË횯Áyx‚œž°°¡“B,Å¢&Zø5RØûêÃG–¦»º‚—WÁ,˜”é»|&Ö%ÑÄlVïvûÕ±_›‘ôÅ0tR¶õqÚíï«íͱ­cD¬‹t‰79|;äkQÅø4U”Á˜ÌÄðý€a›nÉiuæNžžO‚©w"¹z j±äÞ:lSe2''ù»©e ­rQ,\sAX{K§n¹è¿¦¨¶.r:¥ÕòÈ¿L˜Î œÜ…üö|^‰Y„`|Þ ™sï¶5XïP')Ê/õ5kGò‚GVï\Sß *‡ºøò«Ú©“.>5˜WÎr–øðï'É#‘ðk”±°²˜-ë§+VuIù×ì]$.È¡…0o‰›kÆËjg1ƒ <7\oÖ¿~íüïg†*'_wgðòTÓ_åé%~ÏPØÁO ÚWÛuõiµ™rxä·ëù ]}@– L »àá ^"~£?s,ÀªAûÜ·«áÄbûä€UCJ`adáݤ¯: /¡ÀùQwûfAyAG±âRæˆHDÀ‹¥Š‚gæÒë>ηÐEÆ—çì^…׸¨Õ3Ãó:Ȩ~råË-K±yô/cóˆþÍÒÝ áiÓ“L}ï“úº¼ìlÛHrÿ±ä¥/p~ ÅË“%ψµ¢Úñ6RëϨ1-É€-@B~™¢²àëa£víìè¤vèí„Û…Ö³+éC¨+ÖΙpxĽ£ˆý°õCFæ äcôä(xͪ¢…îEËÛ¿ ‘ɲw`ñÖR‹ÃMöúº£åº»ŽóͦÆPf¤ÄpíA =ÅKê;° Mac)×ç^Ì.ühëœÔJØÝþøq[÷¶Ò›}Ä9&eSl—x%ËÂÙ!ÍSÄØäѳ¯Ü[ê5îK¬;Í™ýbJ¡’ºèSuþجÂSa½•¡ ¿óÀn#V…ktÊUS«Å +3«+¯z>Õ§nž—;$ƒÅÖkÑÕ8Ö§_¼ÃÎÿ…o¡‹6ëÿàÔZ;ÎO$~Å<ë*ô@óöÅ¡,‰á¸0ÓKÙ½+7¼¢›¤ ©ïM|û;É aT¤à¿gFG0ƒ…m9†eI‘o£–~«ùõ˜ÛˆI”š6xGàçßFt2‘"…kD)WÏk"háQÌ×B?/xu8%ж ˜Ç1L»´ŒUö}¹¯X¾8Øþé›.[H˜t=Ü…Xzɻ٢Ž÷ëð:BÄ©–Ó¡îÀAðrd^ï²Ü@O-ž¼U:¾N¨¾ •“H±„Áq9™À¢´½ƒïËÇŠw½Ë`SÊ,ü‡]É»Þ@ƒ«ÐAC‹”Zœ‘üÚ¹&ªÂÎÅ1Àâœ"9œÈׂÌÈ–-†>2ÞD™Å˰ŽÄKò-õn’,mPT~ÀÒw=U:…[«i¹þƒ=‘óÄpTè{+kV˜ù geñLÒÒ\ŠÏƒ¯w¯±Ú‹ îºù´ÛÞ¶7î®KÀxÊé ßu Ø€ÚSà7»1Ú½T¨ØóÜð»)`•£2ÔêW¼lo¬ûÿØÜd/É,É ¯tÕÖwŽÃ­Ê½ê’Hy¼¯ö§ëö,z0¥Eï&+ œÏE61 OK'l=¦ÆŽß7£B Cy£F«)p]fÉŽ44x³Y©¸˜ol·U¬î«‡P·ÐG–€ Zª8;4zŠ–+;[Ì rXíZð‚©Úꦅ–ü¤Ü«V(ôO›Õ–y7¯*\¨£ƒÙS.¦Ô‡!ÉP&˜=%RÁzòû˜90åŸCèëÆ=—Ðã-»ëý*æD³É‹åxo:>“Ôã½ò”Ñd‹)û‹éñý)'uk^)¡‘.ÚÿnêJ1Æù†³–À_}å5¯ÄêaC‘SòŠ,ñ2‡7äÊ÷lu©b¢Ðñ&õ=W]âv‚šϾtJº ¨ÅsO’óG½U˜Á1¢”’Šbç%¯¿˜Ç^SËßîx¾ÃVZ$ó¼öJî™D# &=“ÄàT„¤=…¾ÛWà‚¯ñòU°Øj¾®xô‡-×À/ÝÏB÷$8×Ç^àçÌŒé÷8Ü# \*pó‰xɪ[Æ!k>GN9ÿ°_±¢Ã°_k5Ÿ_ùçêøÛ"J¡qÓ†²úÊãZ²ÂÃ.Õ5ÝOð‚½ê;e×ä†u†`Áx"y_ »^´¤>Ø–ëòpXMj©ÝLõ jß²|pl¡¬ê‹¡–’ãýÍFeâH”Ø/=Ýðj´¬“OÂ<:¿Ó)]jðîtP¡‘‹gv:Ø/Þ’¼ïy~x×I^>T¼p.˜ (”ù¥óTØe1’sV}¬¢O¨ˆó¬¼ãµŠ·àÛ'’•Cyä¸(µòäNzÏ+gMu1AÌñã¾ä%’’!’Ü`Ak€áU¹[ìÕßÁ Ë]Z§yr»23ÈÎc"?îþ¾u—1[CaXº&ÂÛ?³œ)cñvŠoÁ_-ÿ^Gh˜–Â~Éë %à7ØbJ’woÁœWÔº¹e|Ük ýõ{^À¼n•®iY¬Ê|i5),ÜòO«0k)øŠy€2E1ëË'$< cOlxçªÁ*ó@¡Ÿ"òó ù¨/KÑÂ,ãƒM깑xÙc臘YÙïŽ8…UÈç¥väVbøR<¥ŠèÄkÞ‹%0–d§âű´¯»H>‹Ì8㤣¤l+›÷ꦯªOÐ:.G¶ÓÉ÷ *É»V¶’.….9¬ 5€ã䯰[×*x5ŽÃ=ìË~â±p’y Ð?WÌ È^šÂ´Ð¯Œ°/nÚ8\/6Æà!Áú»ÿ,׼Ʃà;ÅtyÀ²m-Æ $5ï˜i©(ðúaæˆ>!RܼçÕ‚ûº®Œ\ýïü°õ œ2ɪ2–âåªoáÌbGPˆ†ÔoÙùºœÜUÇUµY¦¿2Ž ]¶< «ƒÐc=a/Ýw‹ƒÐ Ì£sû4×_ Oó™wßNV©¥ó5Xgê)ü—¼‹JáTü’ç…éøáð¢Úίüdló¦ç`9» }¹¬1—{®à Ñ_v½Ù­ÿë óî"|\ìF ¯ ·ªo»÷5¯Xcgµð/›d $)Çýj{ج¸µ¬çáE;Ü»hU .UtË^EC[>bh2‹Ý]ô’W$ŽósÏY<$¿&ЧReŽfÀnÖ¸y»ì(µ‚ùåOãFäêllp7Ù‰+˱óIžÞè¥T`ĉ`eRµ ¦K¦A¡?°º9%ýs =Æü±= ñå–YÒ×hœ"Ö®Õ¢ù"œkë0Èzïߦ9TÇŠw›æYɯþ3/v®¤¶‰ÂæÍä ©âNÓ:«$«‰ Zó¯ð×ݱüŽ7w of»~§¤„;wì4rœXþúã®Zó\«•CxáÇÒAo õgÍ,èW•xRc¨7È´óœCœûbÔ¦r^×¹ Þ¬¾z¨6«=7á#O˜Öh=×öΗ¼W'Àó#ØQžZøã‘×Å"ÖýHÞ?lëcq½Ú7ßXQ)8•×E÷o HŠšz÷%³¬ýg)ø-+±a± ¸B3³n²‹k/â|œü7Öi’lݱ„XþÿرŠs [ÇÓð/åfó’U«}=¤ô ÿÊ”Òð£,SÊziœ&?-¯Ì”¤TÉPè¯yÅKÉŠ˜Ÿ_íWß–ˆÒá] Õoô®\=ð²pø9þÔÀl¶Íê P©_:B\ݤ’XúøÓ難?¼þ§€³, ÿìê!îr†üƒ¼7§Y Ä `|wäÔ!êA‡MòW÷c§;ä!J[¤úrý±Ù˜¶ŠZ9³/ùº¢•¢…טoÏmWî´ª«‰‰…sílãë¹oúžwC0ɘ> >> endobj 49 0 obj 65 endobj 50 0 obj << /Length 49 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»åšq¹äÍB¾Í endstream endobj 51 0 obj << /Type /Page /Parent 4 0 R /Resources 52 0 R /Contents 50 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 52 0 obj << /ProcSet [ /PDF ] /XObject << /Fm6 53 0 R >> >> endobj 53 0 obj << /Length 54 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 55 0 R /Filter /FlateDecode >> stream xÚµ}[#7’î;…žåƒîtòÎ4p¼ÏŽæ²c70>˜6 uUV•Ž«¤IUíž_"ò"‘™Œ“©Ý¶Û6ù)2 ?ƒÿZý}õ¯Õ~XUEe䪄ÿµS®²ZÙÊ¥«Ï«¯ÿÈ‹rÅWîW7ßþüÃO_­>ü¿Õ÷X¤³0¶°’‡½Å©·*º¾§f^_ë Q ¿ï͆íýßrº(íÛ3lÿíTûŠܪÿÔ<ÐNJ´ŸÂ—%´ãU Ï~øîÃûëT/e Ã]ø+?þð}£e-JKŽÑíæ¾ÿÁ²•cŸa¤yÓŸ¯´v?kmuûŒÿ¡à•«¬^=¯D+ùù_=­~Zý=6ÖÚ >M ùæùþV¦-ÊmƒÅÝæ¶ïr–²7BWÁ»PHB ªV!Çý¹ÐEbhZ•øa«ó?0@\U£þøk%üŸØ7òñ ½R`h´²jï<7æi^Xa˜…Êr4i¾ý=Ô3_ø2«AGj}˜FeqQ­nôE€>¯¿x¨,Y•;•1X†°Ÿê,µòÒ`”^ïê—z{Wo)àlƒVIR½»í•%™•*ªJÓ¨õW,GNÊy¨ÌG]owÇÇ 3QªÂ”Ž´±ýEÔè"Âyá@- ,I‚[°1e7ólLHð0öd¹¬Õ'YÎS+¬ ee)¬ßòktØî5Q³l–´ãcžÉŠª,„–¡bý™ðô%K·­¯?K£’CivÛÍî¹>^²\Fyœ²0bÄуcsæ¯e ñpÙYÇYR‚IÉqï6ûúö¸‰¸²$ KE‰M|wŸç )œ#5üùqsû˜go\¾°lrf$Îc*”°‡ã~s{¼dÇ„© m`~†|»Ûnaðê»>Œœ¥ v,¸¤ÔqÜ-šz²*$ aÄQä85Ä êìãzà²D8UXŽá —Ý|Κq®l–÷ C¯¶Þ×E–jyYÚqJ ß>=eéãg%IÝî†c–ª[®D¡qÕŒëvŸçÍl¸&uû{žfa¿$,¥úçMUØ×¨`™ÎVbCZÁ᥾Ý|”Ò€WÈr‘Bªr”‚?å-È!m¯í8‡û•8ìËî°Á•­>6;6©ôxø.Çæ@ Ëq\æ/YÛÀÞé W(¡GëeÖÚSÂqŒOã »×§»¬0öÒF¢ýp;½®‡×çÌH‡CS1J õ6K»\6»lJ-Š#•+Já(ØÀ•¥ï²¹¶…ÀØi„ÊÒ}Y” 1NSª}}ÙeªÖU°+Òr7yqnY©ÚÛÇ,Õ n ®5¥Ú\ ’uœÒmžGÀ-«0¤b[Z$‚Ì.‹k@ $0®jYËŽ+ Už¼Íh]?æ-;h^H23w“·ì.·…2fˆûïz¿Ë²0Ë‹Jð,k׳Íöx(2i2X*ÁÆâÿ#Û5‚b¦ôÐÄ"÷_6Û‡¼HÇÊ‚W$úìào»}ž½•H«ûJq$òOº¢®ïòÂÉÁzIØÜø (£D–¥P+‚€²ŠSªÍÝf[Ü¥Æð°ÉS­ƒhLZ õ-+sâ…ŠR윩Û®ÇÕºp»^B|î÷ZÛuƒ4¬¦`?Õëç,“…\Yt1\vs[o™›ka©¨ .‹<‹:bG°G*øiw›;ŸšS°ë€Ð›EBZQHëFÀŒ$ôÒŽ&À“ǘYT¹•-œ’ÉfÖ㲋¬ÃãÄq[3Ë[v æ·ê„Ì.(%ùFà QºkÏbt¹Î’j8­¿9vÖùSéB«jhf‡Ç`{9GÃG:e"Ÿl"ËÒ*Ñ„ êÃ&û$ArC¡¾åÑn%žÞº8höêÃaÕá¥ìQG‹zžárk¬„R וmþ[óä99Tøáüñ¯IšÀZX|œqÕI¯¿&)`ÙnÒ¥þáûß÷áo?ÎQ-;oV+ˆ—*J ·ëckK)ɉ°Ûç%àIW1\–o_Í^UiE9ƒ»Íü®•ï³dïĜ¨t8³ßŸgfûGp8{#èFÏ›§§Ís ‹P^,37qÁï÷»ç¼ƒü+!ØñdfÉi ° ¨o2s%À | G_å»òãW™¹º!H“Øf: ÙæŒÄaYúÝoÜX>Ÿ…II'Tv)j˜åÔ*t˜”…Yš•ÈŒXK`þpÌÒlï¬,ŒäCÍ. op¥ˆ/‰nÀpíŠ@Ýî|/6'æ"G´Ú8ðñq}Ì›¾R®ä=.e¨e†#º„= £Äý’™CæŠRq ôn“™#a\á {_ï1é-K¹•*¤2”rwûÍÃf{È›¿B°« „^ï7‡Ì¨DaTBZp>Ì JUE@—ñý¦*¬1Ô¾«ñôv»IÊÉ™ŠJŒ(ŒSrÒVaÓJ»8*»É›p+« e1þoQ‡¦–¥_fq‹Þ,®€ß_ê=OÛcÞrÁÁ„9þCž¥q\Þm µeþ×¥Þ¾>­÷y~ÍŠÂÒ2¿ËLý²`ÆŽ]2³\¡‰ KQ&ÝÏa§ÍIC»Ë¤ûe!$9ÕÖŸvy¼ ¤`3Ii) Yjj×ïò|™g£(µn2OíTU°ÉKư W†ªm}[ëÌÍkOͳ7š?ùqü“K?[ËZ†,”q¼‡¾VBCå Ã1ðÃ>ín}^šÍŽøL%FØ yi…¹T,W-mÊ‚—ŠÒC6-™_F w -Íy“SFØZ.- Ke…œa¾z£îQAe)ØE´4RÞ¼4”™åÒPNNXÒÎêýóaIÞ—X­²¯S¦1^»j6,qÔpØØœ¼/ˆ›\–·™¹ `gʱL5P³ö®‚VnvÖ—„HÄQ¨ãé#qä`ùb³a^tŸ©• ”ÛæâçÞáéif›KÉdê—-ª*mNÌIýª`ãª(ã½Ý½î¹!’ÊR ƈ7+¬¡¾+J·»Íöv¹ÇfÅ&ÍÇi{›cÞý Ì‚ñ–e¯ÇÞ:ä„2š’¶[7³&3l”°r¦±áSð*[vÈÎÁLŽ {X?¿³æ†Z[\ðo‹Ì³ØJC¡þW‘y¶>˜»8*»ùGžU`¾•íAÙ<–~ê`Å‘Zý¼M!æyEþ÷.‹ÂÀ6¯È¡ú\?=½Ë‹Ò ’ÿœRìŸ25 YÅ%îÇÑàǯŠ%y²¦E¯×fÿò·Ÿþøç¿ä]%¯ ‰Š8ÞöͰ›Éô(É"¸ îßeïKiVQÐ?¯?íöëcxj>ÃÔàK¹ °aõÉ»q¯:A~ñ/»§:ƒ†dç;ÄxS2*ínvO»‡/™Gxà,¡†wK—€Ôˆ£ÿÓæééá@ˆ®ë‡søÇÝúî]–r+Ó¥”Äß­Ÿ?í7wÑE%%¶šSèßožÖÛ»"ó,iN©äñx|ùæë¯?þœCPb¤¦$/¾ûî¿U±¾-^ûÓA¾þý}ÖÞ«· ÿèÄpëõy³½Ë#­Á[bŠ ûÅäðõ_v‡RÚç¯Ó<´)*Õð?¶; ®›±ÙÓvûCX£ …$Í—Eò„Vɸ¸XIn!ïÃ~÷úòñæðñ«o’¬!œ£@ë$;Å“æÒR _:›ÎQ.KÎø: îW´¸bs7O¿ìõ‘´Ô×Cck‘ë½n^žcxÀ™ôæ$ËÂZ9.S…åd5¬ååQ²æ/= „óRŠaœùý︳­½’UA&s°Ñ,µö»ßpªõÊÙBÃÄò¿ï‡eÔ¸Œ—…´²-Föx>Á‰b®Q"è@ ¾ÂT}Ø­»o¥ªðR¯pA—ÃãîsL¤V·>ÔºP$ç´6‰j¶oßÔÌò¯;h<š­B‘úKì݉õ9È!–a×3ç2Ò.Þ µÆ$ Þæªœ¯,¼UÓŸ‚¹±Fªiyع9&­ Ä_ÓàZÀ$ ûÛúåeýžîþOºÐ@¼ÒmlÐ-Cij,“sö½„}3]–…â¼Å×!ÌvØf­ünÿ<Ô´Õâªf,:ütܽß~ƒõ]„Ñ\Ð忊 «u7§_h”û§‰æ ³t€þä8ã•leEÐúÿÐØ°_t<¥Þêí;º‹“…Á¡ó~àÏ9мK’aó‰%^ÞQÁ(¼Aì±ã^w—áoüü~O1¸ù&SÐo¿þBOe…T£ šŽû×Ûãë~b:ÀüW"Ô,ÝÚaý‡ð ðxfÿ¼yOª¶sø /ª)×ôÙ6.ŒVDø¥ƒðÜïó-½üX!`Éõ[¿ì½bƒæ°@ãµ ¿ùúö¸¹]?‘ºm¸Qø~Ÿ‡×ÍÝ”Ïç…~v3a­x59_œ/£§2Œ5‡ðÛ×wÅä2°ÅîÚ7Ãü2Õ R¸1z:c¢° ;üuB9•„õMâ|ž˜l <ð>øÿ¥WXÑd¨ÉÝþ·o&V4œe(ÿ˜˜ÁæX(ÊfGyÂHäÔCi¾L¬•àt¨–¶SˆаK0¡]n7xðKáRÏHˆò”ëêÁ>Ò¿ÂðØÌt˜Á$>êÈk½¦½¸”o´'㹕mlÁk}|œXW5&ä ¯=»©' KÙ†²D¢Ïî±2Pé‚^µ¡‰ a¼ª ~)2áÏ×¢ "×áwowäã'™ˆ1ÃÐZZÝÜj¯°BdRºVœ¾ ëŒhbæŒ5Ñ ,»Ã‘ôÕ˜¢j ˆw>^-îö¿ó<µ¤UÐÎò°¦kjvCH?Õ`RènÁlJVÔôP[ÜM•–ù}ÖO»ímä¶9ô;t1|Ü8ʪ‰fýö?Ó–‡^*Šƒ»Ø‰Å dˆíü'BY…¥ ƒæ[ÚppyB© ùïlj¥ŒCt~ìf»íìnj…‰¼Ã~Gî aõ.´§Ùм›ÜUæ4n,jJ^s…™µ6”éH/=¸‡tá(Lí¤l³jz¢è’nm,ˆ¢컉UsÚÃ{˜XÓ`f ˆ2á±Ûr©ƒÏÜ>øk2Ýœ6³eGoçs†Éè·žpsভDwâµÿ™toX÷K ZO»7¼´)à3ý— ÒÊžú´ôÃgz'¶»èC½¹ßÓ‹ ìÙ… 5z¾.Yúl“ à‹3Éžà­¥øÃÎßÓ°ñâ‡1ü·ø°[C\L†®#u¯õyÝ‹¬`%8çª ÚŸý½—ƒåžWé†q^)O=ØÍËãf¢^€•´~Ú²VÁ–® %ûTC/…°µ)mØþ÷Rè ã…ÝÕÐëñ¿'bȲh'ì¹õÇ“aј“7þàÜþý-Ð\U"ça}®€‰"u!u“ˆ˜CèbÃ/h]lôGúM¦›øìøÔð>›õ~sâ;8Ãu8rÞ8’ODSUV Sg‡çÝO»Ý˯Þoµ)^’­øô·MÄŽ?6<|¥F4½˜*]ŸÆßõ:~y©/ö[É æ¿k)yâ@~ª3&Bx?ÚÖ=üœÉR½Žºöz¿5w[þÉñlw”³Iñ‰Þâ— £û•Fѽå/ôg³^pgçª>ÂÚQrìÄM¥ú>ÕíwÇ¡O%o¶þOy'§´nqK†u`üŽEì‡:ãÅ/*nƒö|B0sTìuKS±Å\GtŒšow½š½>ﱺª­.+;ø²)ewK¦„±ÒýXcJ•0ü£3þNŠ0™“I{=ÒõÍünÑdRß§Žì¢MœôíýŸŸÞ¬½öIfݶ§÷Î^7 ¸Ž”Þ3{UYó—ð_±QþR I‰íò—"g¼]þ’×ýF\È_b~ã÷—H ‰5/Ú‹=~þÒX°5g©~‡IþÐ(Åk<ª…ä¿Â'Eü.˜¾DoƹÁúÔ~û‰8–AüíTÐ~:yI)؆¯%/ÑQü!BáÚs+"ˆ2Íå¸Ôoe…·üß2•½a ^1ò¿ew?Éè+9Ðyˆ¡–|ìð¦vt¢´ ,dšäÃÇ’ãè¸Ó8¯àLÁƒÁ›âNY¿ë>x‚Ãê'OsX÷'äv¢ÝŠ» ùúmsüBÈ-Ïăi&6)ê„ñ ³͹™¾£iqˆ29fÙûÍï&(,Îë2æq=1Ï„nN:}üOµÏg²1?PÁ–Ôïp;1ñX04¯õãzâ¯<ò*”gŠD°H£ØppGÔxˆ1°…I?âÊÐÐö§}%Vé%Þlc£Å¼´‘£j¯OS»ö m}6x'ù¥!zL¶6\ÍñÂéÀÚ6ÖÔ2æáO97§`‡þÂDšUóê° Í¿>ÔÛ÷—(A‰™Ý>å8½\€ Á&{]&ݳƒanŽð½ØýF1X…Ô&¨ÞNLÈR‚Iœ¤¹tž‹Oó(\ˆ=xïf{$×D4OLû훇m·®zŻƓïÛqtrto¥ièµ¹>q, …£„Ûãõ ñ”áá9Œ õºŸäö19;ÚÑÛÇ×$´M Dt¾!MMe°ì¡! _êˆò‡Ö„c6±ÀR,ší~ûp9 Öb,ÔäÚ1>®£Oç0@ûíW7#ôàx®ÂW0ýæÇì3cußšµÂÓ¹©ª$pãè•ØÁFGÚ ù©^ðäùœ† JðÁÓYbäêçT¼…E£d‰»)_?SS| ¤¹Ûì'èJ~s÷¨)¹ bQŠDä ttd‰œgøÉ÷3³è¹ yê@àm0}ACa®%^ðÛ‡y£Ö6µ£|ynëÉ\ËÆ»Ÿá‹Ë¬Žhn1ñ$btL»a6›´z1ÚîÊ6t1Úä(ŸÛ<£ÉL?Ç ÇQb”æ6O½K˜lÕ1ÓqOŒ’½ÅµÙ£dï)b´'¡qéÐí3´]çÝ=¦NF0º]o6ê=%ø‰Ñ%¿<^¢¥úir[O);ô)¦>«2ˆ¾9£"ø(ð>°#~ctðД<áwLÒWÏB°[bûŽîòÛó Cî–SdáLi.ª#2,Еܾµ8þÔ¼mT·ÑåsŸ”Aÿ»<ÈI?ÁNc|n>=ÄtÈý=Ÿ’¦â$ø~‚§ßƦpØœ]ß4ô~}ÀÄm[ªî¤x½ý÷Ôxáò[Ú¾ëûž.ÒØíHû? _ÇÇ2®à¶ ºíwLjˆl8§ý. s:ø¤”9íãOQäýˆÃÆÑJyQœÓ·í/Šssÿ}ÇA&mØÎJŽŸñ5êãúòÈ3¿[ÊéE7ì^¯„a笠ßmò4®s¯=Oó¶}ú˜{øe˜㋠ՌiÞ¶g©~|?2âIuÞÝ—”Ñ»¤Ž¶×kÎ$÷ºQÉÆ‹·ß-i¢·íÙE#é} ?2èxÁ¤Ïó¦yú4?£§Íri WM9Îñ˜‡]RÇÜë5gÌÃû’âØ½.IãݶOŸä~ŠcUSì,yÀÛöé#îá{C~~4Er¼P«.¿‚­7ž–ög¥åÊûî‚«ª«öp®N¢ðÉÖª= P~±p-Ïͳ3Èûþ•×½­ÁÑÔ²àüC_k)ɶÖþ­Ç/yó|çTÖKP%cŒÖðép]U¸ff)K^Å{ŠÚÁ®ê„:Y#>ŠÉ"å7%X¹~z­£UÊ.}?ž8îX¢LÙtœÕgÁT|+Œ¶ä ž&/ñ6 !õùâã!ZHç’N0»­β4,=ˆS,njÛÀ é„ÊŤó›Ê€?Ä¡QaÉWK}ØhùdÌ7))ØQ}9–ê·°â5VêŽÀ²›$‡5ï– lîUýëkgãú'×/‰ªíÂ[„·~¦tÅÚ.M g›ê®>þÅw:/AV9š3$óó"_owwõüÙÛœdÌ݉ úUÖ¼•` xRf!jä‚§<Ÿ²ÌH|/¼’ì[ÖÔ• µœde)q~ÊÜ•V5/OÂïp §î ÌeLˆ9i¶lv`gDSnÿü,-ÒŸ„?=¶„õ£´"-ã8½ÿ#<Í >sGžAÙ,mh zçf„Ë’1ŠªKpjŒ–v;³¦ž©ÎéÓ^h~ðòÂfíѤÆÂ2.Ì. [w¼…ØÁަXô7ó€;•HðÀ–;J¥Pç„|¼ ö.k¥°¨­"?ÃúŸi‰µ,'¢pGdÉØOŸ2 ô#å´~öë,¢±FÞ¹›4xPxQlR#󲕜»=pöïÎó%†¥Ð´Î³öŠºIK)¥QwM¼¼~q©éç<ĶbL Ôûõj£HRÇ0;+,û4¹–³TøÐ´Ávú¸[×Y#^R3BÜ·tP惺æd‹½#кÅ+Øœ‚}~õ8ŸYº…©-¸£tû©ÎÓ,V Q¤fwÛ:K·ª´ÍõY ö>K³ª¹%(Ôc¦Õ*¼VkIÍÞïžžvYÊUXrÕZJ¹ŸaÕþ&9º?gÆIi›”P‹öóyéíõ†WÒ&c‚A4 »^Œ_,¸d)$ÇÌßë4|q_}‚faSßeìupô0{Š8ý‡ä ë<"¡ÇÜí7ÃHŽ¥i@ãö•ù«Ð ­,š¬{L6¢ªô;Ûqä>a¾©B©5¥…æ5­é#l¬7`ÞÝЀý[Slž6Næ[b½ý};+ ›/Bç˜ïy2ŸÌ7Ž:m¾„~OæÇ BW6G`¾¡Ü=>ënÛ¬äCkÑ™…Á +ÊŒýZ½Å¨'Çà:«0N4Õ!§6g,Ï© ¡Ù§Ö[#¾Ÿá)€ìcõœS…·Ä5¥ÕÏÛÏ9V azóØ`|¤öw9k˦àeón³ï®V,°X¬ÄùÈbü郅˜Òhqm‹£^ÇdãØËlö„ɦF. ™u^ ö˜ø.6¡ŠàÚþ[smy*J »$†j€Yá<ŽÉæA 0ƒ€ªÑÔøÇc½ÏÛÊfBà ªQàí.o¯­]óF ú–¤Û(¾Ëªb¢²Y‡cb@CKé6q‹7©KR›<Å:Œä•[uïDÆë½ÿ1o›Å"KCé5•ÄqÍ+1¤bׇÃës4¸c Ä^.T´vYÛPAØl{Ðì3¯áÝ…geµÊ7ÛØ…¥«†Ö$P‘:MÚ`p ožhpÛMK si즊©`´ÌºÈ25mlÁ+|º}¾%õDürÂgOô|tC 2‘cþJ¬m[‰ýŒÌ§á« L…ï²°@Zí½è>ã4Ü+Úgìj ƒÔãð“‡tEeLóÛ¿a‡~7Žú¿²žúáÒx%º½)ù!÷<SÕ5£Î Ï‡i}oÁã«iqÐdú|$+ÆæZR¸uÌÒƒg,!²ª“Zç¤3Ü&Ñ*J¹ß?G¿¸—R0¸¯ÛÍ¿^ë§/Y9ÊV…Ô–ÂÞÜÕÛ#ÄýY©š‹¦hR‡=\†êõmæ¡8M‰ü˜u®®¥hòà)oªXr.€£æ»Ù×OyóX›¦r2¥Û·<ÍbéuR™ _R¤…wy¹B½{´¶À WJô“˜–é)7Sµ•**©CÕžôâ!/!ªÄ²†..êê&ïV¦ 8Cju•gŽþ_Ê$@ŸónÏ5%ïe°áõÛYùr¸woÞ%”°þøUf¦8Ly"»,çˆd)ǰa€ÊæQ9cŸ‹/V1BÖ¤”ûXˆ®!ô—’´òM÷‹ÉjŠ7¸¿em-5ìu¥" ,?Êi]CºÚ/™‹î°õù)‡Ÿ,B-Èæ:%úíÏ?ü´l Óºpãc™'˜y!)x/|W½‡ ïImoŸ^ïêCf-æÆ+BâÜdm‰·È]E ž¢š"éˆJWÔX‹Øðá5‰yÌ&¦+ªÊC –&ïësìì+‰@7U¡ñeõ88^ ûxsh¹§ùúÀµ½r”>×o™T/VÎ)I¬·yT/ÇÚx†BEÛx[?C^6”Umm!zŸ”’ÇôÂôÓB0BäÝSæ‘‚¶ÍS”QäeEêªÀ§×ã˜Û¬“e ÎÓ<Ê:'±ÉT¬­pÁ »ÏS«M‚e`xŒ}ܼ¥ÝO+«ÂÐÖÛ9Ç5ºá O¸ÃPú“ oI ËsœÜ%캫²sÆ&¥vÀœ³<Óœ¼¿q'Þ-9}Ýàð].£/ø~¿þòëḽ=¾îë_Ÿ6‡cû5øÿ~0¸,É&ñ%×ÿêpíz—5¼§OἨœ}ÊÝæþ~¿ýµOuœþŠ47€ÕÒlÿƒã¯Èåþ+ÊöúÄù+˜ÿÏõúã |ò‡ÀØP¾G6«²ÿ“ñïH?ì¿OðJcÂÁNßq¸]og|厤*DøS”üsïk ûä¥]ÖÔÈ¿_?×áWd'ò"ËÓOCû¬›¿¬?è ¾cÞÕ_6}Љi<%·ñƒÎs-ÏœóN¬Èn½¸Æy§Æ $ „ÖÞ²´»4Æuø(rwä_8òdÉ{¥±2ºˆÝb™T¹æª‡ZšWzu&]‡ZJÚú©¾D³NlvÀ|µ¡ 3™až»}Æ4D]H~(sŽãÓ¥Qaûº~Ÿ  oê IØ5Ò,ÞòN"šËÄè±›àU•™ç“ ÔQQêHNØ‘A˜ÓÃIsKLä³6¶}¿/ŽÚ%hæ]èln*+šå¤MQ÷ñüš—2óŠühÆIäÈITtëYf†7 ñÂl—¥ÖN‰Ý¶ø,»åŽ)ZÜé©döyœcŸÌ>f)Éì« ÉìŒ7ó–{“ÌNê`Á-÷&™ÂM,¾7N;o“Ù ÅN'³¯.$³_Y±]2;z!™]Hf§`³ï¸wÉì„bédöUj2ûuµÛ'³_ÛlûdöëšmŸÌNhw”̾š—ֻ̪ ËÓ.>fI§_WäÄïøÀ¿ÃÒJ» ùÒ4OKõÈ,Âïˆ_2îøÿRù6É¿3çšá‰ßËæTx£‚†Y>\¥xKJïè8ê…Á¢žŽÝ‰£†t›™ãÔ’;äeÕÁ:n‡Pí1Sµµ³¢P)f'™„é˜>Ë ¬{b§Å¼b\Ýò:„..Ñ:4ÓÑ:„Šw™¹8-«3eRg•Iê\ÙÎzç‹©#Üå–ó¡8ÕãtfNàŽÓâ²Yõp N‡Òf«¶ãtØKœÍ;tœÎå!›GQ·œ¡ÚEœ¥Ù9œÎ8 ´ãt(5ì3ïÏ´ü e ÿ’w…¦å_:x6Ÿ¡|dË¿bÈ­ÓÙñ/ì[ž‹ìø—1(Ë\'VÿBYÛœä1‰/´ 1Å¿devüKžeò/«žéPY&ÿBo‘{¥À6‹¾Ï-&À.ñ/ðv—G>tņ¨löFvTLb긨óne³1ÿBà&ÒˆÿB zü ›Ï¿\Y±-ÿB)vV16æ_ØÔôXŠ¡ÌàÌ¿°LþŃf™ü˸˜ÀÕͶç_®k¶=ÿB zü Ëá_B\¯šÏ,þe5â_-ïÂBðU `b:·r2¿F.ɯ9ÿÀõòk¡¯™__-¿6EM©×+ç×t°£ü¹,¿†öù5ôÂüš!ê•òka¯—_CüÀ²üš(è5òkiç×Pj^–_C ^#¿æ }Õü¬?"tuåüuq~Mwq~M‡zíüB ‹ókR‡l^~ ¡Úeù5„f¯’_C©aŸyµãbâ¨Wãbâ YÎÅÄÅ^ÌÅÄar1#Ðkq1qi—r1\2‰I,AÒ311ðMžx˜“ýϰ0¥(¤ÿ,Lx) 3@½ u9 Ç]ÊÂÄQ—²0WUlÏÂÄE]ÌÂÄa³0„\ƒ…9A_“…¹²ÙžX˜«ší‰…‰£.ga|Ük²0¤¼KYøª,ŒpX]Šx+®y-ƒ€1X ÚyØ× `JX" äÍ}ßp\Ñ1€]Ñ‘¢_„5…×,K})F¿p>†e жµ·)ÇYç=pèÇNVÖ)J‰'ýÃꋪP0̨Ñf½mÛk|ûõŒ~Õ· ¾+9¥Ür ,×*RÏùo–`ðß&Œ-÷mCQ<%emóÞóóI…uá¥\2ú-gðôÛ¬‚k”9'?¸C: ƒäÆèj,Jím;/½YGs2þT¶ÿ™qFâ@üdN¦’…–.ë_­ë˜Ë«è%!‚Õ†ýóc½ÍcR´*ªª¢p‡³1™ Å÷û”¡4âÍÆ™¾ ×'CJæsçX—Ð9I)a»;fé `Ù<vT´”%;˜{FQÊͼž#K0Civ½=f¾D‰|°Ð”Öyþ•q9î3'2fT–4Ûî¥Ï VFQz}[ö–¥€é+íˆeÇ·C¿*²ŠEœ•j¸ÅÌ+eÔC–cXv•‡, q—=dI€.}È’€]üå÷:YÒ.}È’‚]ö%ºô!KB³Ë²$ä]ú¥²9‹^o!OXò;€BˆBU#³ß<<ß?®·wuÎÛxô‚Nòβßbò²„%ÍXA‰œõ¶<H²T¤Æ f3º5ÈjôÎÆÜ;Èñ×®¾,ï¦Ît2tÒ½ØÇÞäX̉¢Âp7.nÞKWÂƹ3æõ^ºÒUQrEH{ÉÎXü @Û2¤2KÅG ¬%0›I6_«½ÙrdDGrÍ{c’z½²ó8à€ cDvuè!wÒ>ÐF Žk¡&½ñ[!IPQ Ÿ7·Y[ÖW@V¾ÃÐãR‚¢&ïÌo "%§IlrµUÚÁ4 0Ã]YòCoÝ¼Š‚ÎxH"2³ª“Qå=#1X¼0›Þ’MyF‚M„÷>Ê‹ÏѱÙ7øÇÀì 7ø q—Ýà'@ßà'pÞà¢^çÿuÛÝà'@—Þà'`—Þà'{üWÕnƒÿÚfÛŸ]^×lû³KB»‹oð¸yñ#ž££4;¿di¥i»óK®Ua‡Æ±¤*Óç—Œ«ò¼L ‚Þš„¢ eÿØtyðÄ!&›—Ebj/OÎ"ßâg”°_-Jâ°ˆ˜EnfYŸENÀúÃ5ët´Ë"²ä,òKù!ñœ³06Î"'P³»«ü$¬ŸEžõÈH—EÞýÀuÞë³È ©2Ùd9d‘Ï: ì²È sËÌGî²È)K›q¡ŸQYä3ÌmÎKj ‹Â*G?žW- \nZp¶`âÙÙe“ïLˆ¼ÎR¯\âþ::‹ ‹åRW"&0»œï<‘ï€%_*FH<—» À’ŽÔò ß™Í{ƒGkJ¹O›j¹õ’RÇ[æÃ>ø®:9;.ºµ‰ôlÑÅqàÃãîõé./ñÆÍUcc›wªBU‚ýLa]5&5öÏë§Í¿öñØÕ­ìÜ'"a§è§P?e^¡«\óô]‡Êr|OäÙ3ݼLˆúºÝää£ßiƒ8î[Þm˜ÊÚ8è’ûbønƒ#!íz›w] ™3«I;È,³©,¦^X õŸô<€ë}ªà&—¼QéÂÉrTéb¶þ˜…ŒW<‘­?‹Dê²õ Ô·> >> endobj 56 0 obj 65 endobj 57 0 obj << /Length 56 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»åšs¹äÍBÆÎ endstream endobj 58 0 obj << /Type /Page /Parent 59 0 R /Resources 60 0 R /Contents 57 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 59 0 obj << /Type /Pages /Parent 222 0 R /Count 6 /Kids [ 58 0 R 66 0 R 73 0 R 81 0 R 89 0 R 97 0 R ] >> endobj 60 0 obj << /ProcSet [ /PDF ] /XObject << /Fm7 61 0 R >> >> endobj 61 0 obj << /Length 62 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 63 0 R /Filter /FlateDecode >> stream xÚ½}]“·­è;ÅÞ·uÊî4?»;®<ÈòêDUŽìH{òqã”j´Û«›ÝefV¶Î¯¿»{†lœîæúTª¢‘ÜAþsñ—‹ÿ\|w}Ñ‘%ü¯û¥êBÊæ¢jLQqqýxñûW¼(/øÅõÝÅåÍúî«‹ëÿwqu}Q²©Ù/€…[p~¡›B©êzóˆÿ^ð¦n*}ñx! øuú‡‡‹w@Ãw×lL…’Æ¥àrýøq6Br…$WÌ(n×7 ¡tÑ4ÒŸ¥(JÖÍR¦HAU”§ðõŸÿëåëWÄâ@²ä…¬+èû·/^]Çêy"¥)´ôaþzõöÝëÔÉJº”;Þ¤¾¯EÁG„ñB%¦¢]H-)ùþõ«Wo‡™#RºjÒòQò ¢‘/¦öyyu}õòšž'ÓUTûóüñ­ Œîð×°Î(߳߿RÇY¾_ýºÞŸÛ›Ãv÷Où/OU4•Ecˆ†•°°AÒz,?_&ŒrÆH}”ÑŸAä·« .˺0M탳˟¿JˆÄ0s£·œº¾oÇÌÙ²¬Ge<Ÿ)ã!@èYjæB´íc»9$ 8¯ Qú”mï¾b4€, ¡µp§;î¡LÁAìÚö›³ä1Q‚æ¨jösJ‘”M¡¹÷¹•§Ä„l"ŽòäÀ<íÛÛÄŒ`þâsØ&õ›)Œ9Neörÿ©Ýÿ%Õ40LE°š%ÄL+Ø!݆¼]ï€ëí&¡kh)=°í]‚0 «.qU:;UJÈ`çð²òØm+‡¬Øl¸‘> ÓѵKH ÇuÑÂ8ìV›ýÊâÀQn@Û6Ÿª£Œí[úä]'—GÀ„êÊçÃç”ô«ª¨J=;qNPUñB;ìr¿}z¸MW0ùFùd}pv4£ÄLÉ¢‚ƒßo¶»ÇÕÃúÚÄ@ N9£a0¹ox©‹ºÑó(‹¨3àlw„UBÍrS.µ÷ýÓfÔ˜°ˆ¦i˜ ò9ù=¨ré“‹˜°8˜}"-÷þ>Àj“Zr^ØÂ>c×û¬]£üYÜ®A{ïac=´ûn§ô2°m•î~ ò"Aü¹²°»owîBAX÷ËÔ¨0…³ÙÆú_h‹ÔhŒtl¼,ãïësé °zxrÅ~ æCiiˆÇ´1/ËBiÃ\€ë$€q¬¼>'Ëá¸+kŸ³íækzÆ9È–ñüÓ;B€í&\v¹Ú@¡&®ëp"k¹® X‹pPsµk“œ­@nå ±wTuø=ØEhI8ßÿ,…J±DJWÞ,Àˆ/–)üJØ€"jæA;f­ºH€ ØÐByâïÚÖÿÄÃìh=ž<ˆag‚¨¹ö„‘E ÄŒˆ^U FÁ²Fxø´)Ñé¸8ýN2‰6ûà„êE ä—`ŠC8@lL>¿Q¢×ÙƒwY|xƒÚC¸Ã_~ŸR¸0_!㨑¸˜1ý(÷OUà’¹Ã½zûâÏW 58a LSÂŸÍØ û~uH„¨9ËÝCw»÷Ð>îSŽG ^x3‚IYµœk뻾®óý;[§áLÉ÷¼# †ƒükwÏ£u¦3yç•è°ïŵ#Nl[£j¢Ç$ˆe¨aJ°¾ˆ1Ï-¸T Á\vÞ¬m2(Ä Ã¥··»/)o |^˜íî6aÅ 0NªF$V:.½ÌT X31ÓVë‡}ÚÁ–B€|œ€V¶O‡¤ÌÂù¬¤ Ò®nîSβ„s |ân·zLÚ¼`.šF»“IzoÃYð¡;yØ®EÊ"mðti\ë™à˜¥]€n§„EªqfΈí}tÂUQ£8Ÿ†8܇6¬+&`Ôœ»ç¸†/Ká²ÖÊïyµö+…¿ ¥ËRºKpY\O»T@Ýu§ ñy½}Ú?¤(ãÎSÞ0*É`Ô‡5®¡°r„d¤•`¯ËÒŸyZ{Z·Å¨Ú™¤É.ðøÅ]ÕÁ±3Šlg·®M0(;7¨(1†Óø€#•Š23µMß)ÊÆUå³ÿŒða˜Ií2æòëd¬N<_ò~¹_»ú‰Eƒî#¡H:Žƒ¦ÕÌ_„~\pWÁai`”ðKB5ÁJ N™ûým ¹{[$}GMíA&µÈ8Øð¼ö&sN­q8ÐJáÓw·Û>¦N ØàVO9 ‡û”¥矆]€¤Z+¥5›ûï­œl“!"n£VÒÁ_J¼†•THZ~™€O9÷GYíÚ3 gŸÁ@y&C±µ­Vyc|^ߺÞ,£”º2EÝôá•ÔšÞ¨Zàa½Ú·)¨†ã ÷†ù8“¥.¥÷ýÓ!%& Á4šIÀÙà —´SÞ\6Ûd€L— ãΣMYÀ¯ c>îD’᮪¨”öçѦÃ]V¤r Øå]2ŒŠ.‘>M›Ô… £Iÿ’ÜP¦P戟ýƒÍÚÇ¿Ýý»HÄT©•• "ÄKÿÄC€7­JU1d´eƒ°[]4’û£|ÜmŸ>ý|¹ÿù«?8âƮЦtÝý¹yxÚ¯?·ï-¶3x´€m#€Ó›)»ÝêË{´j{p:Ð3p :£S=Æ00Ì…žÈ0æ‚ü;§¯CÕµ7D›˜¨7©JŸ¤/ýbÐáV¼Ñ1#.8–Øíúîn·éjÝ‘b}› ”ÜŸ,NQ["(Àã²—ïûkÀ÷€3ˆð ˃»Ëè0¡Aˆd,Äão= »­—áæ·ŸßÕ¯«ÇO-éq×`óðڿ䤡§w >s¿þYŠ’h}+ý ÒÐ抆{ßíhS¹­+ß} *ýÍv¾ñf½ùHÇ3´.à,öÀnýÐÀzŒ/m&O£Âx‰>ï,–GúsX Ö¶‹]¾f§¯Y€é1™–¦.”öiI±Tp †¾ùãý" ¡ȧô€®V7ô `ÎÈRyë|Om0Ô¥ã3ŽÐÆ>É\rÆ5^©k™1 3ìPð¸¥îé_íIÍ«œ‡î÷+ÒÓ¬J8j›Î×7ÛÇGïNx´Í@OWB ¬?V C=þV_h™Ã¼ ps|Š6?Ki>>%FQ LXfw”ÑÝö8ÒާOÞcàTÈÍ\;Q3q‚ïhTÕüHK}– e›U#«½9q¼ïHì@‡œGàm»¿Ù­?´·ä¬„½Œ»ÜZ“|cBª¢©}.¼xûöÅ?[Dæ{‚`¿e&„3ð–ÅÔžtžN'vùîúí¿¼þï·Wç÷&Äéðúwtœ8KA¡zßÓ"gÀó’¹·è[§Î³RÚùœ@¬³È‡TƒópÀŒZ·^þEÃF†ò`®SÑ}Ø9ÔÃ÷,qB6WÂÀóX$(U{Ÿ· …R¯F|½OH¼(Ôh¶ƒý”xð(Qm{KWÃìxìÀùÏýV»„̃ýU*«mòØ©|íýl_I `i]û‚š;tí•21ô·é€f´ î¶O49Ã6«à<ç½”Ò¬Ñh%€cÓÞ™,OŸö$j]ÐÌ~/ïSÚ,bÿóëÍj÷%qFa a.HzX0´€Ž£ñ°Dƒßû:qáÆ0““uÜïÓ*¯Í žšGˆ‰*ÍMU{C¹*Ö¿o öÚo•£ÈíHj˲ñÅd›X!ÊBON¾N| †Oí¯ÈÃzóoš‰ïûÔRÀͲöˆù ]cà±:³â1xÏî Hʦ6©ÇgMÌÁ/›Þ˜%R6'/‘–ˆ·¡ªý¥^ßÒ&Bã1+’v?¦¶ºÜÙ°Û[uyçQÓjdX±˜BQ¥öÆ[ߦ’HÀÌW˜×­A Ëà>æa»ýôþ,ô…VpêÈ.ëLà€D!†BÙŒÀ–3à`du“Šáì"FqDÌ'ŽÃ±!5…¨[Ñ&N³ÔöFéxÉûž§„x xòÔ-ss›Ó`Æhî ÖM–§‚j`Šâ„ ÅÏóFÁލJ1sF.T?#1aF.Øô¹PbÂŒP%H3wFT?#9eFØŒ9PrÂŒªÚË,˜2¡ˆ9óQSæsjÆtN@*Tõj´baÆ™v3Îô…—qMXƒ“…«…ñÞì?áKÐøeÉá,Á¡‡7.,xã¢LIÆ>‡YÅð2¯óv†ËhR.bW9»*ŒÑèdMáÒ:`'ä,þ¦fNP¸š3àSÌõf{ÛNÆÊ‚G8V‡Ò¯&1o ŒýÝ/•L0é¤“HzVp˜–¦·8­©ÊÜz·mþÍøJq%L ÁÅ«o¸ä ² sÀËkS×>Ví½]ŒæÚ–' `Ù—îc‘©jš(̘©D@TŸÁá¼lœ‡ŒH-jFÌÕ}ÿx/s{1ÿŸä!?eÇÐ2Š\ô2¸Ô‚Ÿ6KK¼ìP².¼+³×NzU’AŽèêªlX€¶[°Cû8­›ÀQòB”ò‚@»ŸÄ×𠾄4ÒUBÐóÇXUÅ+‚­Ÿ¶ëÍ¡Ý-â¬uˆ ÁØÓÓš$ÎQ\­¶yè­îM«¤ö‡ÝÓÍáiçšó³8"j{çEp䴙Ōî½Éûv2;NçͰ!De-šN/Z‘³‘g†·–ÊÇI|³YrÙœ+Ê’ŠÎS™-2‰ŸÉçÛ¹Á9xWÝë.‚h7hBâ¾4˜íA¡-'!}:ÌËE¤ŸÆŒ—ìŸ#ø¯‰¬Ž¾V%>EðBzº!©IõhHÇ’ ;CœvªÖ>vç‘ôå •t²ùJL‘p²Ñ º>…³§#eGC2FèCò$zcCRV€L‘H/7ÂË&'½\ÈF ocÒr5bLÆ×p²Í‚Ïϵ?ÜDw€¶X0Ý·»Íêc…0\“…WU!Œ:B·&çq–WxéfâT± küãdY–5éD³0}¯¥ &ž±&r¨7p«áØ$W|¼Økëa4&È­²æä’ó¨ÂªZxY–=é>O¶)͆¢w‚ñ=8¾b'¹°ZÄY|·Œ·™Q¤,Ó¤,Á猠w†QɼŒ‚FÈ ¬Ê¨âbóL@°^›R||Ã<Ã’bIŽe‰ÅePq=¯eéa}Ë’ Ó}ö0OÌ0²ìʞǦÄ;oÉ)r—Û”h5)’ Ť]L•ãNú7¶)¥‚IêßÔ¦<1¶)GÏë’l ¯éñqƒ‡Û3FØl‹­TQŸ'§SôÐ.²REQ—œytžpþzX ##•šûW‹ ±A d3”rð.ÑCcrX<¶Ä¬(!‡ÑØ,[’4ƒðá­PÚŸCÜ–ôž‹;eu¤eª-9Ùl®º÷§UglIÚpF\““ulÉ™T|Ü„xÙ`KªE¦¯}aÇÁ€pÑÎò¬bÁ¾Ah¾ªC[²]í3øpX íçEÁ--Ð Úè–[ÙbÖ‘ .EYUàºÆ‰ÝÞ-Ð0`ÙlM&þÏѱ'äXhªm¬ ü·HÓ0³Óc`¬A°æTte–tÐ2xûý¬Ò41»‚Že¢ïàðÍÁÙÕ"[J€kl]ïøô»”ÛOß,bí°¹±Ïbǵ“Ñ<ëþx[*)¼lÖ 64¬˜V ÑâÔÚJn«‡)¨YhL¥±B܇ý$³=4Y+,(GÍ–òËY5åq寒æ–7˜g¸ÃÙ, ɯB1#n°ò)jfìâRèfHí&>ÖSX¦"ÑŠŒS;ï ŽùõYñ$wáeª] G>%½Ë61ÖijNmâÕ§O»í§Ýz©‹8¨p@ж7ÞsŠY’V+,]"â˜×‹âžÚQ¬ì¤'ƒýNaÜ6ƒ Ý´ß½Œ¡Ånìƒ µËMµ é9É‹ªâQ °o¯—É«Á¦ƒŠÄ¼T^Q1šk/¯yKtWQÙ¾´3—¨ƒbNÙ¤¦ò–ÈþÃìüÞa‰¢Þ¾xó_WyKD`Î\¢1Öc‚ïs¬¯ S†^Ñß^üõꇫ7ÿuý§e¥Aèr„s{'`eƒeØT¬yGÀú42ô޾»z Võqšìù…¶‹ÓPT½¼zs Ô0´Íî¦r!a‰%Æw|‚¤ìï‹—¯¬Yv4àJpF‘Ê5ì°‰{‰%| 8ãûj[iÉa#ÉéÀæ-›ᣨê%'Væ(9ÓcïæzƒäŒ(ë×ø Ír+9Œšï¸£•’‰´ä°9$l‰^Rႜ¸É1 2 ]óN¯Oâ1£Ô:4æïϾ ‚%² <@0D^ÿðËë×?¾YÈøSD°O³(èÀ²„M& …x™YŽýd£ãHÙ%ϱÆQ™uæÁŒv‘°)Yc†4ÿzØ­nÓ24ÛD©Îe pG^L;‹•éGDñ2÷éÍ,N€ZÇ'=ÖqZЋïãq—³Ò¦°hIJÅ_žV›ÃÓã²ûGk µäzÙí¹Äl1 eÃãǾù¢@h¯Š7¿ÁæÓödƇ/‹´¼ûCÔŽ&À¾v{ùÝ«‡õ‡½RcãúÖ1G°ä,l*A샡 ·ðáÐ,Å…¥Á·èÞ ._?®>¦š»IÌÖU•ã÷– FÛ…ƒ-àBŒzK†;NPYÕÞ(¾$¦¢„²™¢.ÀËûׄ58óVMÌ›uû°o7)Ò𬎠å5¤µLJ²Þ0Ve$f>[ÝøLvub$P®ËÊv£rAV ª`¥<~ëüêm¤ºCÜl`Ë; ¾1@­ £|F¯‰¢ÜûÝ 2ïÞ½ý!%eÃn4¸mL×£¡]=>¬7©æŽRcó#XWÒýí¶ýŽíY5È©|CL±qìè« ‡žÕ”Š6nËK¿¨Ìqžh R•ûÇð}â³­{‹ˆÏÖ]øsÍü&uºÂˆt1Äk—„­*Ì®˜/~iƒm±ófdýŒXýA|hS oοKéÅDz´Vñ¤Z0Tׯèöîðzøã -'¼Ï7܇Öx9Å45Þ’jy„!œ‹Ä3lÌRØ‚OÎènBÏ`¢va÷¥[ç/ªgTgd8ƒ8%übM]Á,¢&úU¢¡øq±9¸@µì[f%»wãÞHÍ\·¾^ ¤6ÔÊe½Oô1–]·@`•hc,Û`Äû~Tð.öª,?“Ö܄J P w“&;UÜ�IÐG[0 /Ð! nR°Ö¢“Þ¬ñíÕüë¸ØpZ‚É`¿ÿþõ«Woß½¿¤ÆÐCå‚D‹Ç…cÌ’m˜(Èt Ù¥²u÷{x6y`UbÉÆ‹p\k—^ýpõç«7×)¡P° És˜4<Ô šU£Q$kâLWsUsÛlÓ)Îè‘Ê6Þ¯Ô4ã‚mÑ‹ð5ø¤¯K°›vˆ^ø‡ho;gšøŒO¾îÌ<D4>Kœ™>dòÌdÁ™Iš83Ùpf:°§–‰3Ó`Y˜ŠMÈÂ3sv¬EÇNèh##ô8ö,HaŽH€©m,´ntB² 'ä08½¸pøÐ k@abíAÄOÈ£±¯´´î‘ â¯EتfOÒ'äÅø„4°É ?5•L^Ê`´ËøœÐR•ÒûÞ­=Oñþê¢m]\càÔ£è|+oz~ª°ÿGèNÜ||Úœ¶ÁÁ¡ŠcórgºO›õžÚ‡/‰[ˆaV° nôæ°¾û’:"+¬ëQ3Ì­G”ZpÝ]¿ô?=´‡äªc±"È«O³½<âü¼U %ÄùàèµS4–öh‚–;¾$ÀÀtÕ¸°—wàòn9½ŽFI°?,.±‡¢m9ŸŒ•”ø=sáîWŸS¬Â’±¥Oâ*å+ŽèŒÐþçiýyõà÷@ ã%Ú[.à.E™ª@‹áûn>$ç‚!À1ÛRi,và}~.tÓh0×É9TMQ›ššsèžf#µ¶\Ù:µŠà¢ÁQ=Z”Q?ÍÐM*í™íN§ëü‡)»ΩJ’EówíÝæèNëôA ‡­Q•ƒÏ»zøz )0‘ª¦(Ù߬N„¼ßV»CRæD!PIZœãcn5%>îçGr˜Døä´›$o¤*Ä€p -‹¯‘¢¥?®¦¬”êúGzHgÒSc™»ÞE »=ïW¿®÷I¢†‡Ñ˜éÞ ˆÉÒ´CÀ<ÐI‰ïæÅðŒÄçúA`Äi|ç˜}Xi,'ÐåÖFïá{uLÆ9ÚÁÉÓ‘8að­ððæÇÉÍwTÇnÅ®¤ØÉ¶ógÀ0´¿¢†k@€–6€0`²®±õQS†&“éy.m¦ ¬@ekU:Æ8N± E8ö±á÷ Ú«É` ¶Ë…o{˜°ÿuy8PÝA¼ö½lìnƒÔÞ”¨˜ÂSWÐú.&¹ö›†g,v&¦¬X…™$þìFmèc‹ ^¤ wîvvƒ­+ºÂ¨RF=¶Ø û$ç#±#ðŽ«Ñ8‡öæ›”™:ˆ 4C8þÒï·˜© sDÂ-NDÙÂUÃüA’bÚtûßxlWû§Ô€5\åÁìÚÄîÃk5Óøi[w9ÜAØÝjþphwÉù+|t G¤­n×6ÇáëÄœ4/m¥@p½¹yxºõ-îq>då­’‘C\wb_ÎD)1^å°zøÆÑ ¤¤ ]ˆª dÙ§²Ö®À~qAüîÙ1I3ØYýNö‡oöÇäj0ÆRûcá}ÞúquHIhwƒ‹Z$âGFpBÞµ~™¶n%8À 悌´N4% Id·}úd½®?¤¼‡–×Å>4Lu”ÈøÒ_Ûи+´$w› –¸ºúÓlGÓVÇéž¾o÷Ÿ¶kh°D «o;@ô})“Øœ\çë¤ô—¦kŠìPd¥Ÿ”6lxVzÔ¤¥_I8ß¼)'#§ƒÚÒèjŸÜ6E“¹Ÿg1'*(}Ëñÿ§ƒmÉ»+·€Qþ!=~fÐúñéá°þe½k§RŽ¢‰’qøò©B‚ƒ‡}·ÆÛò½KÁé(Ò (®!ÎpÑǬG?ĬÇïÇâ U‡™èÀbñw‹’_|süï«uŒK)‹žµt'5 /_ûÆB¼§–ó¶/2ÄøÊUª 0­[ëÜ5X ¤\ÜÓzlpÇ´%ã¬.Ü‘^[l:ÝýUrÈv®}Qwv?M‰mGÉ„«c^I¸Ælî˜Ö³µ§ÝqL6µýtC+A½éÏèl+.¼ \³*Z ¦æ%ê)¸ô)Ñö$ÀVã}^÷æÚÄdí3WOyB>ÄŒ5X’¤=ÝE8r–xÓ9o~X„‚ÓÏG§p§ÆBíŠyLëQÔí­Ä¦Óewô‚~XU¾ã¦‡4ræu?J7 ¡†an VÛ±ÄR¯{" L¢;K؇ÎElî¼Ä:S°/ˆ!°ƒQÖ"+¬­­âø“Ý‘¦¯«®ÉH|™Óü?‡,tðDEŸ,¾Ñmav†´yêúc’~j5CÝ1 ‚6`ç^„c°0.ŠZ‘rZ̲q¨;=Y›B)¤ ž­IlÉRÔ{L–°‹‰ì»EÇ0®¬‡b.èwZ&€RÊÍquIÚKë¿fé7nº<º›©`£)˜ŒlÞþc)7À4Ù7ÀÇ}j2zh—»lpƸ'´Ü=Ï“Þ  xòÕ,ž* 0­**íá¨Àß/ZåÐFsºòG%Öy%ŒY¼q°³‘#æjqÓðY'EôY%ý9œFqrC'ù~¡ÁZÚíc±ÙkÊûÃÓßHœñþòN=¼VÐÊËñc/³f¢°ž x.öó^_Y¥©(öz}pvqÃIúr½>ÞØzÝ'ôÏéõ a8´ç{}6Y‹À.º Ä{| ~ ¶Üã‹zKÃRÚVɘÓzŠ»¤ªB |ÆÑl7í.Ó]Âì‡ò8˜=7«ý>‹C¸1loŸB¦?©ðGØI‹}I¬úA ·ÇažÃ¤Œ}IÑŸì;v¦&»jT±‚/¿{O­”°¾&ôÔÖûLW­±- ü¶ÀO–Ÿ†µojÃünŒew—MIѾž—Òbn ­T;;Ó½wŠƒSš¢ÖÅ–QŽe>š¬ì%bˆÃvVäfœD‰)ä>ê ÍËy¯¿Ì‡–&–w“%øø~«fSì™é‚Ó(Aw¡jèU‚ÿØgs´F\Qäßœ1ϳ§Âà©wl¦xŽ^@•ŒqqÏ¢3E#p“ýÑ­²l(ôŸ³n‰ís%äcƸE–ñ¦êÒŸ âgƵƩ®Ü–ŒðpO1Ó‰=0âØs4>ƒq]„eºÓÔ¶à"1Æmû³”fÓî³–,˜»ØôöðSôCÙ=ï f°oyê;ÐèAŒ²”l`^ j‰o×wY6ƒVø¹î°LízÖé¾ýâ6;ö4‚_kx³Äx8=–Äê²´òÊ[,r&Ž ›’ þ¿s/O v{X?¶Y—ò˜]ùsy¶KyÌ+ä>níÄþdµ]ÝÌ3Ïq¡ˆÿ*Ï¥–ä©¡“hÃÛó÷Ý¢dE}me ż±9“ŒHÈ•ñg–¸CgËæÐ€ &‡AØ„+ô9Ôà¥Íáù×Þöá¥F*:Å…,8çÌñùVÜÖ—þ|è‹ô~Ÿ+)ì›ÞjÎE:›yKòÎë€>»H_rK€Bb¨é·™ù.ð§ª)äÞEú’À±Ò5_ øYü*}ñFBe`àOJð¾Ê󆤥â1g#+~Ά©+F ¿mWóÈXý .¨Œü칉Á6a<½1ö^ð×7»í¾½Ùnn3/ì5(<çã³È½°7˜M®rö…}øz•y¹ß H¾TõVû…ÆØB«Ýa±;ã–¿XæÑ`‘QÅÉ%Øæ94ºÁöVv[Xc—¹•ûûeùj±8‰Š„Ú#øG?g&°L€¹>S¦_ƒ°Ñ&1 ‰nöëúݳž¤¶Fx3žËõ}›—äו бÝv÷¸>Ò»á¼ýV•…Ä39>ÈnµùØfÞÅaâ˜kñÖû,sM¢FÂ3ÙÅ^.âòÖ·ÑES’ë[æ­.F¥á#¯çF.)K«ä…ŠZÕ2/QÅ–ÂäålTÎma"kmË«zÈA¥ö”ÿŸ<¶pÓ¹Bqiñ,¸%I¨uQiwEÙòXtPÿ¾¿qöHŸúž‚-|J-0óÕ©¶ÎÜ8Gòçâ7ÎãÁq›óx¸¿jöp/NºŽ÷”ðpO¿j>û¤ºØ”SΛsÕ ¢Z‡lâM—¿[’쓈—¶=¼›“óŽ˜p\‘è?g(»ÈÙâpºWe lÛ†S”O¾•¡Sí½ˆ£÷œ—¹wµ²V…·×ÃP 3nmQ.°BµŸŠSézÙ2klŠlµÌOYˬKS(I è„«¥óކöC|ˆc}î¬û[Á[1b ·˜wÖƒq¶0ÍŹôl¶(q+¬ÊaŒgw'1׬w‰˜C¦;‰¯†÷ö® VfŽ¿°]Å(úórãvG©(ò#Äf¾/­§7ÆÏæ_ðÅŸ‹s›~A?ÅY='+ÐS{ 7qJs¬ù#¨õÝ·‡"ïTJÛk•Àÿú.kµ’¶R$±À‡û6OOëXPÄÎ:Œµ‘öáÜKÁ`‹R_Å—™eFµÃ­\Ãæ=i;Ó@U„*¸6Þh§‰¬÷y ]ñùp oyÙºë¯ÇþqY+¸Q|ùœ©×dQ×5Ax»ù:-Uc ı¯óÌ6¬¤)Cžâ’Ç–Ü!N­ç>O`'¼’½~üô°¾Y¾ä•QÂéî›:ížVy¡s¬-m81‰Üȹí¨VQÈïŸ'hα(»æ 5=aæàK˜’éqä‘d»™µ´,xâmº Ñ>î©eo—?ÌÄ=Z ݨyy›Á–á3ƆX#}w²Bæ]gû©IOVÔ¼kãÈA‚Ž> kÀØž?ÔLÜö?ËîãûA=þñ}üj“wßw"¨ -Ë·è[Gé·^n¶E×§ˆ˜‚Ó²hY¸»ojD QÞ-@׉àË&/]»$‚n¯sÒ2Æô½•ˆvyŒé1œ z2-ªò8tm"f0;mŸjñDàº=e©¸áDÖ]ÆÕ¹Ì1ÛØçø7ÏëXpWÓçòœÿ îj¼™ýÖw5\8•ªÿ»šñ`ƒCõôø¡Ý½ßÞÁbµûYI a•*ÿ­çyŸâë‚1ô›ð /=ä‹_’ñR°7ÁÖgK¯U¨P¦Âjõ€~–̦\« oÇmMä¼:.ܶ½!ðoï2îâ$jtÎ}Ú&òhdE老E-ˆi}\g?`0œºàsCwÚÖ:#?žƒ™‘;Ø`ZS¤çVòÄ‹côEãØa¿Éz×qÜÈB‚™?Ú]^”ª‹²rÑ?k[l/.…}õköF6èùı·û¼'¬ €á£‰œ™yQ–…BE1ÂþLÑjeKIŠøO[LjÛnÒÂæÔLÒ†ån»ËLQ…Pµ¾¹Ù‹góž¢þY®±€‹‘õ0‹^½â˾6ï \ã¹# 5—_f ëèL4àH¨ßü6ü ®”?mo³ÙeÊ*àfV‘»ë°F÷â¤ÿ’y… ;G¾ÝÝf3ªÂf´ÆAÏÆ¥tNZÃmÿ±ìÐ]?yb2ë}Þ[H dYSsY˜—ÃKH‹8ÈX†ê¶Ý¯?nòÎO­ ùñîf<cÄ‹uU6ôò45VoÖšZçÏë›\·‹Ïq’üÃý*ïÊß«s´ãøW»6[ÇÕK>{Þ·/pÜ`Š2ÅžÌ<°KLµŠc¿¹Ÿý˜€ºÅkÊX]¯çxù¢qÇ>”û¼t4|¡å ÁF)¢nÞ_kšþOþ2ý†O8©!:ú—²U!kÕ#êX|ú´Ú­Oû¼Œ4Ð@؈8>_²J=arf>Èm¶ùÃzÓ®vyê Û0‚-JÈÿnµÙ?ôŽó62·EâÃì¶ýAù;sET˜¨œW’W‚5'@KÇ‘ßl?¬7«gØËÕЧažs3«ŽÊ†šÃþ)z;a#×…ƒ7Žþqk¹SäY*FÃn¨‰%~ñkö>®ÅžvŸ¹k \†Èí>þå~=#ï9¾ñEÄûFÄE–6£4Ž}dC,°Q0ë­cgS,ˆóŒ1€ Üá8éŸvÛÌ ®.¸¢Øþy}Û>KP{LÕÍóú§›¿ƒ sÄ=ÒhÛÝ-ª´Ì‚dØbì·ø û/{,²˜¥8/¸à,>@¶ë‚máŠG¡q8ÓuÁbOR±ï–3CLÎ+AP¾ºÉìJ†™¤ä²nóžsƒ_m_ØÅÙ²ÊsܱœASÖ_2{µÛO4Ž{×®ò”$¸@¥ª]€QÕÃÜÆ¡3'ÁU7wö÷Û§‡ÛL3le}Ÿ;½d—n4fŠcÏ~Ç‚é~ ÉX;æCæ=cAßS ‚5×¹g‡Ö6 â#æÎ¥ºà­ìϼòÕãFqÔÃ#®åª@ª¢2".ð˜õ•òÂeQÚŸCIZEFN§Ç²ó}”$IO6‡ÉtQ(nzì1s8WIVpjÿ‡/™Z²){qÖ´›&(æy˜%xÈšäG¯$¦öy·•"ê&Šš-©ê<®ª]_ùœ°;ÙJ³˜2B ®_~kœ%ß_]_½¼þñmÆ­4˜ÒÒÀ¹”Îá ¶ßãŠÅIñ÷×ïò®ê¹±–j}‘ÕñÔœÒñUaÿMŠ ÅÇx¾CqüóF•r‘Ó†æ6…ì* „Û@ÏYØ‹¾ÀÇ”S}¡¯óº~‚­aF"™.ÒÃf”Ñé®â~³gèø©À‘’’ögj ãà~®ž0À¬Ýj¿ê~J2 ¯µí64š‰Ó£ç/ÿ?F endstream endobj 62 0 obj 12948 endobj 63 0 obj << /ProcSet [ /PDF /Text ] /Font << /F4.0 9 0 R /F2.0 10 0 R /F6.0 11 0 R /F5.0 12 0 R /F8.0 13 0 R /F7.0 14 0 R /F10.0 16 0 R /F9.1 15 0 R /F1.0 18 0 R >> >> endobj 64 0 obj 65 endobj 65 0 obj << /Length 64 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»åZp¹äÍBÎÏ endstream endobj 66 0 obj << /Type /Page /Parent 59 0 R /Resources 67 0 R /Contents 65 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 67 0 obj << /ProcSet [ /PDF ] /XObject << /Fm8 68 0 R >> >> endobj 68 0 obj << /Length 69 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 70 0 R /Filter /FlateDecode >> stream xÚ½}m“#7Žæwþ EÜ—¶ÃÎK¾“ó­·]Ží¸±½Ó.ßÌìÚÑ¡®R»´®’j$UÛ}¿þ€”RÊ"3™w'b§ìQ‚àC@ø×âo‹-þív‹èô¢„ÿÿ2¡Ð:.|tEéÔâöiñ¿¿•E¹‹Û‹Wß¼ýöÛwß±¸ýïÅÍ­( Ãâw $+ r\a=}÷„ÿ¾1DoO UÀ_—ñ¸øQü-ÅDˆ…µ¦ÉÄ«onnoÞÜžFn}#ŽI ìÝúè‡w©N)ç ¯eý¨¦ªÎS5Åз>*ª6‡_ú÷Áeð­ß¿˜ŒŠ²¾Àí?ð;­ms.iú§¿t ¿“±ÍÿÛ7·o8/nê+ã 'C{ïÞÞüH$¬ñEéIº[¬?¾H‘µ¡´DRŒJÙ¤ER¬C] —õÓ¯ÈXü¶Wª¸_ß]>%2 ãÇOð¯ã–A‚OC8ÎМgøþ~ýñãnóþ~uXݶ;$$ê±Û„¤Ž0#Ó ôª8|~^5ØõEôÕø‡PÑÀFQ­‘/üó+êC_¨Ò><о=x GÁQE(›s}õÇ¡1¥î¯Cá@Eü}ÑÆÁïÀ/«¿. Â.Ò¿u$ªïkœDƒÜâBNj ÚÔ¤ºœHŠ¥Ôíoí°Kz­¨¿éKp Ú£/¿=¶M,|ð¢1ö«»£ -ˆ‰ÂÞ Ê6¹}5 ì¿kþ¾-ï—OÄé¯a×ú&TÈ!¶([Q ‰u$Y ÿxÒ…«më@*¥Z_<-ë!ÎŽ.´í1V_ 𬋩_é•§íýêqà©¢Ð檹”¢÷œhÑ·?Ø,ŸVÚVÂOK<›c|bÊYXËæâÕáa5ôE( ›¹9DS·g‡’À™ï|50¥L¡PÈ|Zß q¦ ¬¢´­EyٯT°¹„4vé»Êû¿:jæ—Zê.[½–N¥*ÞÛéNÃIkºFOï{ÌGÐwø=ü4–x¾-ÿ‡†kUÑ— *Z)ávƒ–ÛqxQi* O‚Ógã&[ë¤=ï JïàÙu~Àf«?бpA‹æG›í‚ B)bRŒ›J‚Ù&e‹É×ÿxûãÀ&´²ð †NZD·£·¾Y–Ýù‰ËÇÞ Á›¿ZVOû!HJYh«Dë›ÍÐR^¶8¬wpòLF­bKÓú}[8zfFµ¶Æ¶AhX8¤µ Aø õ‡]­”–‘Þ1SJXwã‹i+Y¥Šée5օҭù¾º[6­"Ñ×=`ºµåäÕ¯ÛÝç! ç!ØØÍO–ûýönÝjAI$œYþ¨ä– üÜÁ!dýûãɶ’Y ïÛ¿ÿ}}x: %@î¬h|QëËýî­'âMáÁÛÃïÞàÔù…3…)QŸtP>}"êO@mF-Û£üºÛ¾<ÿüjÿó2YÀGRF4>lÊÞzs÷ø²_Z½¯¨ÐÁ '­?™Ì§SeìË ëàŒ–Gé¿ìž7m1!±:}І÷ŒUã“ß Á Àã†)5?Ä8ÁÚ”g–*Ùý<ºpF×bê²¢ï,ÿXï‹ó?­ï‡)Gr Æz°¶b?Mÿ_ƒÔå`Ò g¢!éÞ¶yzÛöé<ümL8º ã¡õ=h9ø?O8‰$že=˜ >¤gZOîob€ü"M¾v\/ôÛz:âà4Žãˆ®Ó `Ã7f‘vâ¤5….i8¨¬l“¶g!»Û^lÕ |§½`AñýE$°Ea3àoŽäë(L¾Ì„ð»°t÷½}Xïs éK¡°6N‚8èdžY5F<ål€³é´–‹4u4ÁZÔEë²}¡C—º8QçÀ"¤ÅOC¥÷YÓ²sOÄú$oMjä$Ÿ¨*ꓼ5‰F´vä$SNò6ñîI>UO'9É—9t Z†¶v4–ÞP¨"oÄFº,‚Tõ¼îEä­.$øç­ù$#òMê©Û«Èš8Vu0M{u&UkºAÂþT‚âºÞ‚Jß3g8j ˜fè9—wܧ y‘alSä/7?ONrY –*ðåíJ¯s4HZŸc‚L©À™·hÒ¥¹ÿƒŒRhçR¤—{Ρ¡4ì|)Xžw+*îŠbýÓzû²ˆ[³ïM•œÕ@àŸÊÔ®)|Ô”6Àëùû©ô© µ… «ÆN³ÎÙà†Äê8dw©Xß=°¬„è‹R™ö”¦š ãQ›PôõÒÄ7[Ö&ËIâ#á¨L ÜHC2βžxñÚxŠöý ¶/ž(,±QÁÊG ÜGlê  9º¯öW„@ä• ¢¾}dAƒ©D.œyOAÃÚP óÚ8ŠyÞ†BoA÷çÝ–¥k´¬LÖ40ŸÖ÷ÓUg°WKܰiæ—:¤Æ=ÕS¿,`Ð#޶¦}U{¥Êé =w¡9ì•§ Ùî~+²c†"q#RÊ•qâHÖ|’7"àÒ¥UŒ;õFä4ÔÈÍ£È-Ô!—Ää09IZ´.BZ¼O¾±Ó.BZÄçFr‰‹ÖúN»Õúµè`ê]ô‹Ì0ñØ®ÃÄù*PÌÐlu øDþÚÑŠS¨˜`žiXž‚Åñ%Ëz:…‹ XÚ‰ ó9Œ î‡CÆÃ©·HYn%)A–Õ€qc¤†º©·-¾æÒ‹¹ÞcàøD\PÉÍù×ÇÀ1Éõ„Àñè¶R°ž^SCŒähLØY8Ó††8n9l±zHpÏ ;<ƒâà øNúšþuMYâ»4I1ϲeðÌÙ¡PgÚ2˜…FG –«X3øLrAç˜3Ö«‡ú¬Ïñ²QË™¦¤·¼ì+l%zJ–¤À´nðçœ×øˆ+’BÓ|Ö3Ï-Pà(j/íVwÛÝý54MÀ7¢Ž¹z‘³XXÌ ¨Ãa½\?òÒJ05”®GèÅç?l_,uæXpä öÏËÃzɺÇÜGƒÔ¡º\~ž3…æ»…*ENa¹¹ç$ÈàsÎ-E} ´ãdÈ`ÂCéCƒ~KAÜ=,wË»Ãj—•1×#ð­¹'·Áú®K^dMS»>H§ ¨íGÎúÖ;؃BÕ=ç~µœ˜%@¬¯_GÁØùÇÕÓjsÈ9R¯¤ b¡ÿÈÛ¿`æ[C±ÏK†Ô¡(•¥hŸ£Ü¬|H,uc(lØ9 ªt…F›$=…§ågž/‹±zR4–¼L¨P¹4ŸX7øè³$¥†g0€)5O/‡õó#+8„÷ ¥¦-ûõ5,‡Žy¯ìjƒ=+>ª;O ð–uŸ¾ xí²&ÞÅæi»gš º@k-ÍúÝr¿ÚÅR9ÌA/©~]³¢õ`‰”ÞPØ|Zo~ea°â-8Ûo_•˜»(òG[“™Ze|¡5…Ïzóq»{{p»ÉI3ì×CSDSóèyÏbº³Uï\ ‡Šêš¯ß½{ýÏÙ©ØÂƒ…£d‹v®o›LLX+A÷y®èþxûî§7·?½»É±0û5W°`]‡q~nºÔ¶* “æü¯o¼åHIUˆ‚¥oÒg –C%ðg‰Â<m¯/%hÇT6ä$1™§ÅeÁŒÝœ!±XŽÎ-˜b’FÅ›êNqÜ2¢ð!djWŠ ¯›Gu–ÈD?ðfj hlã÷³ç?®vË+–‰a e0By„÷Š©þ4Uz21ƒýúéùñ3+¡ÑÓ‰DgʉE‡µ%(ö?­ï§Ô{yiI|Úñ,‘·À¡ êí`ÄjÃò:ðî"x’w¦}$ ØGñ£—=ÛS¶Ð"ÿÀ»VÔ±Êh"X'³ÉDÆàЋº/6¢å(f¼ß=WdªU­{Y„o2ÃÐTI)‚|nš*?u"ßK7èWíšbÔ¤Ëzµç0XÖK̜αî×B+_HÕË+YîvËÏï1%¬]lΓózÕ«+jdÕ³ŸœŸWýLžõ|*ÐFpÿG`ëeígyëbf'Ú]iýœ'©©ÄÚSá³ó¯Ájý‘—"–®‰"f¾Z1uÐDÁµ¦ÅWK(œÛÞ…9Xa €É|‘åzªh«ËŽN¯›?–OÏ+ÖCà€;9IñJæÜ t({̶ ‚òÏZ•9O›8˜Š2(• .Ž©PyÒIïBb©^)îïå|çBjP>pd¤;vºÈrIïK‹¨ó£Ÿž·û¼Iíì*¬.Åûð•ÃXÖ(À"IÄ?n_v9ª­KSï¦o½yóM.&ŠU Ë -)´(NÔ LÿPJœ´ÕpxtÄ•†ó*xr «åÕËU¤®463(IYWe9Zébj±îòüô4 |᤼"(ø<¬èj´éS\4ßE”QPp|5ÿ¨¼ò` <Àžœ¿m$¸m Úiñj™’ï¦;9,ŒL’¥_E"öi(ùNQ¯øE“HÏða;‡ õ…p«xÓþ_/Ë#AËaxCpÍÉXó²zɘ&ü¬Ž'd޼¾ÎÙ‹¯°¥$XæåïEl±@‰ÝóòpXí6óøjuŠQU/ÃÆìˆ‡õ…/Q¨”»Œ«ùˆ`‘÷ )Â_Η gC“å–€hÆE¨í(–ÍüC«^>8¼\iº„¿ßv0Y«ÛIZÕ#.j©^æ#®²Ál‚sVݧˆê~DÐþ°Z>Í/û$¥È…ÊØ{,ß&Tu ÖW×F1€ó\›ÜlCA²\ÿúpxüÌP¯ìI’õûõþùqy—÷H¼«dCÕðƒá#ýÁbò,.]»}š¯a1øm$eeØ5ƒßÛóqé¨É­Êbº›:òY‡"Z?S§ŒbËK|S28#/®{ýˆÏa%(s\I‘>+ðrV÷fðß/É,¡‰½Ã|tO™õ!:Þ“*tTJ|Þn°Àöø2 Þ™œ¤¼ò5¾Gû¤·¿¯X'P'Ws‡*—sX„K8Ôï¶»M^t·O„Z5È_MH0âB$9—_qülà©Fdef Q_–³»ûgÉJ# Vb.RÊWœ£1ÆY™¯9žDidæÈŠhä¿XRTCTð¹0}UQ9öqŠ /ÏÏ,Q‰ØWn¶Z“œMƒ/®.)à\E|p"MI÷^ÚJ“œëù¬Ú„QÇ4åSÖÛL¥¦'¶% ÉÌ`hË †ð°'Á÷¨ŠÑ2¾,ªû¯4ï¬{ Ÿ }l!=÷‚Ýý*1Åœú¼5/b·Ûç÷œËåš:ø‰îf“îy·Ìõèø¶9x‘qµÍI_9 Ší{ºÄÅÂj÷_ò—+LýÚԳܑ±Õ/9×¿ÔØx»ÔêO-2®g©t0Á¬¢Oüt÷ûþîîþ½äd·`.ÂÓ}mŽéÛoج4 ú­´Û¯›ägä·œÑ/ ðšúq$ú„>M¼B_q÷‚~5DWrÀQCð“3â–ÇŒh]|Áýš¸HƒŸ¤$øiþ«L÷˜ý}q¡oÚAÔð»cEŒ,ÙS gø)âü&'0FÂ"!ûþ*²ŸžA[±%šNö«ÃtšN¶ªÃôªËȪ¤ƒ+/O“,ßbˉm'¥v…ÕvìÄ¥ÕTc¤‘”§¡zlÿ0_L,¥aÝu{R%ÅÐ4º”M¡ƒi“¾¨~ÖÚo‡îxF苺j#Åú9 uW1̆±ŠÝblu{Í"£U¦K\Œ¾Â%-<^^ŠïåãËŠ æÛH£ê×Cd¬eU_“¹{,ª$i‘{¤v‚ŒøÖ§Œ"ÍõpY•6m‘,˜g«6ÄÒ.¬8 ²²¥íRS^¢O0Á¼†c‰ZϧÕrÿ²1mÛºXøÐ ¿þþ°Úpt‚W…2¥:Qï7‘{äh„` +á|J³þ¼Ý¯1ÈÒ¯«"òŒ%Y8ßÃGL9¼Ç‹Â`N¼%&01$AÙ ––çcëÉw»­º7§Aá†Ï|<=´I0žå– º ŒŠ¡m×äœÔÑå&äåÀRbM0°¯y¸Øcj|šüÿ[µ* åã«§B0ûÕá;u¨€æ¸åT·ÙƒP½RÆoY±‹`“¦=˜«9AKJLþ 'âýRç{,:ôàu‚YPÆcÏã$ÿÿ`™2€¦ IÒâÕvÇøª ¹ Q4iÛY^Y)W”´`Ö V‘²O]̼4êh_‰¯Ü)YÜp¬%¬ãà`ƒ¦©ow‡‡í¯Û͹ô»˜å=a¯éà?lYŽ%ªUè¡:Û³´¦Ò^iâ󒺎¥ÇÒÐ|Ås,ÁåŽ2 «gäéúŸWp, ìW×+êœÜ¨ââ\B)OÔY·»£íf°Ø v[KÒ®ZÖ2$%ºÂ»¨\Öðˆ—÷¬à¾ò`åY‚}flLå)ÚÌó‹EcQ»42=6ïøgØFJnª&¬9nG7Íë$óþ©ì%—üýa•|KäÀ9T—ü¹ÕZŽÙ«˜–R°ž ý)ÇÕî•7+1UH¨L΋!@‰¦(8òiÆ×{(², cAûX½|.*4¯/=Ê'$•Õ ®W›¯XTÍÎ Ú‡¼Ü¬mì¿ %(ûýËSV”­WÓy‹øMò\\ॄ°'⹸ §áËš%*X=ˬ&çmð±PšôÏZ™¿´G´ŠõmY‘åø‹KÔXi“æÝh°ü·7mqè yºqþ…“Õªao)° ¼Ç>’nüÙH^H¢“¬«eaðÙÞq°î{/RÄÜ´õªÀ>Ö­YMkzN‘¾¹±UU€Öš…G3hGL†X¥>¶èOë{>nJW+Ä^ªßœËↅ©±öT 5õ,=:ꀫæö4íJ•2¬oí±…˰q<,/ë Ýf<ã]gVŸ=‚OALëŽûi±¬=½ mÈFWÕ^T|¦6¦Žì$g-E½•¨+æiLì?ëÄ`¦î Aå\è/ò¼¯Q ñFž"Î{ fŽ=J `[/OQ”®hå¤9ÿ'OQ‚_çIÈ ?óo²lÕŽ€eźÉ2ÑU Ù)Îw,a±Noå†v*ÇÁ«&Gn¤sÊîgΕõ`ßxr ‰ÔZ‘ç$‚q$¥*¿féÉZ +‰µZó³k)Ui1¨©Zùµb®›m=€H°å¸‹øŠÜy§N†í¬™€œV ˆ™Ìð±DÛN ÞQȼ¤o M´Õƒ`‚vf;W¹YY½e¦˜™þ >[á1†‘f~,ÏvT½O+ÑI“?'ÚrÜ«z˲Ñ "Õvv,Õê*§æD~‘—k;êybÆ'ü¯õf²-Ç€C;%Íȶmn-\Ú@NaµçÙRªêbBÿÈK 2ƨœÓ°xAxãÊ"JRpÆ» Nñm¡Qùw†óŸ5½«;XXRò,ç LpM®k;çvF8ÊêX½Å»ÐI·3bîÀ=½m‡²nE®^sØ£I‡®ûü–]ÆsÞ‡L¹K4Š\á¯XF2¾ˆ²¤äXÊ IKñÍ ـ馔6øÏkä8t }¼¶6И¢ Få‰üuµúÍÑ)Š87ÇWc9yIBs…$_S†ª›%1æ­OJ‘Ĺ·ZƒAï)p@U²€1¦êÅIðNkáɆúúVûÄ‚Ê!ÎÊ=;ï+ìÒ»®žDLäžaòŽ“† ßI"ÎLTÔóŸU—ö5rZÁ.œ¡ØÎ-®×cupé êC ”&€dQ=¦M‚ò++}SƒzwV|³Zu„hGngggoš²,déL2m.(¼&,@DˆJF1 †+¥6“Pϼ­6ÆÀpså 8N¡ŒÓÄ<ðYUIÂM÷5°ý­j¯éõÒ}7Eé-Í;/Ý×_e·5Éÿ¥û:¼ ðã龬l_…oÈB=Vw~YõþÇ~±Õ¶nÏëZ ¿¦JjM£Ù;â~ÅÏömŸ›í°Jõ›ã_°·`[+ ”/¯‘çgï¥ÕAó.›kˆƒ_(=E~×WC<(ðúcMþºU`uôG”æ}É3ÁËÂá;Ç4íçí³†yÁi»)hò^ó¶w’q'uÚdžV>Í^sb±Ø4ÖšÆh‚y±WENjÿ¹¬ZëÀºØ;o-tˆúuú¾yûí·ï¾Ÿ¯*5öyR¾&ß;©îNEIÆonoÞÜþðŽÆÄÔgrˆêZ’#üJaM šé·’ã>(ü@‘ [äCÚX­¸ôÿ³ÆDY^º*ýÙÆÄq,ʘXgU $lˆæt®lC4¹¿º Ñ$~u" ÊUlLµñe¼r> ¥ŒõO¬'V ³²¦-æ†( ëFI±žÅëhŒ:èæÓúbqÂ$8˜ÑPx=¥Ñfd“˜ÂIMáõ²Yÿëe•èFs RUõéËjýØö~µ¹JJ˜Åq?Qhýñ3+ÌØ*¸—¦¾ZÞ=pjAab®ÆjJmê‚®‹œimaX»É¤Ùçµe!E{ɽ-c½¦é’Ô<{dÒ{ Þ}1†ƒU h9°P¦ŠuX´×H‡6URŠŽÛFX0­,Wç>C!únŸ¡ê_uû ÕûN£ ‰FÐŽ°"ŽWD£"Wÿ¡ÉúØ%G¦zž€ží1TÕµê™ ö®¾|×›!6v*eo†‚`p0ɳz. Š&ƒß¾{ýÝMj 0 ¤%Í  \Ld°Qﶉ -îNŠ )M*hŠökZÞǵØeë¬èоâ{ô’¤Jù0È÷\L´VUÖ?Þ¾wÿüÍò°¤M‚qTªe¥OÔ{˜C6*MûÉáµ<ÅùêiÏ‚%èÂM_o8¢¢#–º¶(ƒQ…>ñvZ#uXz1›Úg*\d€‡6àý‚˜Êu“°/J×`»Ã!uÒ0ñs< ½²1¦‡é&Û·U¯óJrã¼¾}M_MQ'<±Ø¥.¦$fRV)8H Ö‡ }XROŽKKmÝên»ùM€ÆƒNÑ‘–ÌíÓóVkuXʪÙsßœ[®yšŒå5ÂòÃöåÀR¹˜»bM_ »ÙZÓ½%M³ÿq·|Z±Îh°ñœ‘ý£0Wó««&6÷pÚ,p<¶Öqó·Ѧ±ðX¤¶iÄ,PÐóÄb³-Pr-±´…‡Z=ZŠíQûQL(0S*MÑçêƒé¹ÒPÒÂÕ-VqÜ,­«Ðï'æö§t Ö6¡p9w`–úŽz©Ô?E½Ô§6](ÍµÕ &[b4íDþŠêEW±@צÜݨ,­«¬nÃrƒ%#°ÁwÏ×ËÕ/`wEç)òlý‚5pÀ4"Ä…«_09Ÿ"Ü3m´¨1_œ Î³]ªuUG<‰ Ëx1U­iŠïûÕ38°°÷}_5ECbNa1É߯€ã ­H±Ÿ®€Åpèk(Ecóª†M±Lm¡Ñš9“9ǨuêuQF’û;žq g6ZìiÚL… «· º¦~u…€ý}&™g*…Ñ%šçÝ–«+%ª›44ŸÖ÷CÉãS”¥)œ%…f¹çéJW(Iâëå~Å‹”®6Pð0#`¨*í)ö¼àIU‹B“à€ÉÃ3UAÛKIs¿¾ÃJ ˬ%H}i±»»›pœq”h¼[E¥Ð!.F›˜Œ$˜˜µ¦Ÿ(6Up¬1ñ¶Ødß—j/ ‹ΙºhÛf{^¸9ùH"3”ô0êË—X|Å·I÷s€ª€íû*òY·Y!D_`—åÓ ­p&Ü‚b¹+çIѨz0pš;5$EXl¨^<°€›ËRœ`‰tdÓ¼ƒòùú7ÄÕ-ê÷}9)6ŽAâÊíÌã"'B1¥¸«ÓŽbþößo~äņªkOÑ{{óÝ<ƒŒX2] CiŠ÷±”1¡L'v[&ÈWN-ËóñEÐä†qjGUÒ@Äæy¨ Ô×ë]ÐZ6[·yrOñ¼B_uŒ¦Ežwo|V” »EÄí¸q”ŽÇ'ã²D 6vο<Æ+<ÁÓSÀf«Ãj³Úï9IxPasêî0'ñÇAħéZj /Žƒhœ.¤!‰ï¶/÷9Ék}#GU© ÄòŽ˜PSúOXŒê¤ÙÿÀ‹Š(Y”¨xà÷LÍ&”FÍ“F†'÷Ž+¬CNÉý:]_40½Ã[A§sSz¥™tUó۫ĉÀ‘vÊËd1Ý®tE¨òLû¤ÅPÉ‘)( \"I®·ë{$à›H r·Ý||ÙƒšÿŠ)Âx‹¶º;†à¤%^¤Ä›*OL`ÅR§«iÒ4ëíϺ†1Ö*6è·hKÖ%ŒÁ¼,GðþaµÚðœW'%5»Õ몡z-çkyÓ«÷Lˆ”´øÒRÒrÏ3&± 8Ê©IÀlË w–ÄdÎ3•ÜC»ÕýËæ:q²ì~;³û冗׋6FùŽä»à<ƒ ²9|}÷°žî¦QÍ»"FYÓ³x\o~Û³Ô$>5îƒ$Æ OLÐ’Úƒ¸iÞ· @;–ª´¡(¥§è·\Ø9šÒëª#腼踰ë/ã©,ÁGÿK–b(á¿q黎âEúLუdŸuƒ&0¹¤Ü#¤ºV(ÉÝÄ>CÀµÑŠÄ…wˆ`g+K KÚ¶&é˜;)KMUx¶CýMfŠC¿Î¡cLÖä¹)ÇBaÍR‡Øñ!PÜÿºÛ¾<ÿüjÿó¡›“L˜DðU2Bksy¾¹{³õÓê}5k>[¹`Ý[(Û«°Üí–Ÿ«;ÂÎPbÆÊÔ É Qu•ܛ̗M'ò¢·ðgòY ?*¶õ§Éÿ–£äz´ñaP´5m–’ëÁ‚· (Ji¾?'…5™PVéÝ­¯›×÷¬ŽãEU=(&]o·žš¿_'»¬•ƒ<¿t®ˆ?-”… êxùW—Î"?‰[€8¥Ï÷nâ|1™Ÿ¯z¢-ª*¯Öõhç''_>bv6­j‘wd¢m(#i†eæKÐ,›¦óóTÅßéa‘ùp¬Z‹íèÓ ä¾í`bBaP1¤9Ï} ÚáÜÙ*ºH_gÅ£»¯o±1©§@ÁüZ(;ÂJŠïcâî|XÐRÖJQä»ö²pÁ›$U: —V°{2ø¶WÇ@±>5Ô†Åb)-@w*pHD¬e–FÃÜÅŒãõR‰¬´Ð°ó‰ó=ûéå€Ò79ðu“¡hßüãõwÿñ×›œû‹”YºXÐ=JßÝ|÷ÃÿÍK¥èÚ—F•UŽ^>°‹(N[§Š-Ui‘ºbKõTÅ–fɰªDïoÔŒéã¹Áq1R³îùKÝ)äÅp]Šü@¬p4§»âbbÝÚ¢]c—`¼®±;0‚˜Xc—á0ðtiLØë»'Ò=çç¨ö‡ÝËÝáe·*&*1\c—Zã gë»ÄÆüi˜D«Æ® pôÛl¿~÷îõ?sV¸_btq‹ø¤r8c«‹0±?Í…r ’oßýôæö§w7Ùâßy¤Id†}Š ¢¯\Œ¤È'cË ¶y1àßžÈg$ “´E³$žÑ®ÍzÕt,& ã"XB’"t-þÂKTà=t œË÷[ŽØ`Êm(=Åþ ý?Ö7+5EüåøÔBÌÅÅÀIuÙU]\²„¦^«JÁÎUïèU—ùŒú…¡Ž[gµf%œæ¨†,Î,ÝŸ¶8/cu,ÎkÌŽ{?T’yÜ.<¶³:‘S’™"}.É€d ªvbs˜¯ÿëŠÌ-ÚÓ*2÷ÙîYœ2AÓ|™eÐöskÂ÷Ž2æ5vßÈÚbÍ5I‘nì0Á.ô±zÚt"ŸÓØa4QQ“Ð,YÚÕ@‘íë0åd”UAW™ÃvþV2Ø5¯ì¬iÏæ¬"í-0Õê[às¡gA,ò†uŽUV§¢VbÄêœÖÙA©itÎÓ•µÑYÑÎ(q1¶ºg›3Éô$“sJW“HÁR[œsO÷³ÅÙfêµßk¹68“¼¨ÍÍ,}k“³‘jk3Éþ°±)&¼ïªŒÍ$í“­9Û<ÙšI`^ö+(µ©™d>p¦Ç®§4`ÂêÖ-ö§xbºÏïªÂ¹ýÄÌØuë9øB.‚ý‘ØõØ»‰³JÃê™!.F< ‘©Œªêht©‹ùÁësòJíRHðD±±uFðºWg*Ã¥P £›Q$1ߣh%Ew¨‹CA$„Š9ÎÅ1oâ<˜àúõ-f6ÑœÆÔ®‚ScØMÚ @Ì aŸ’&Ž´3z Ž[?g!’¶ŠÕ^=|]YC‘燯UaÙü•Ã×`µIOBÃ2 «je4.׈_+]¥{аâ×XI)¨6óÌžˆSN´P…÷¨µ¾J›X«D±eià]nâ)qlìO|"ÕHö±?1Åøhâ1dL‰åàC{€«$~T ê²A¸u†Üüõæ»›ïoyqlÌö&±a§}80ÎEõà„EÝЙke}´…:Ò~½¬¬TŠú5’>ôñiC ›«%}X >—£Øç&} Íï"E gÁ3ú}))`®’õÁáí7ºÿ“’>ÀÌôu׫?9ªc7·² Å<3¹Iûòü{ž™ÜÊ.MÊÓÍä®{—6“;\Óqr‘o&÷h‹¹fr×'øh1³U?':h’´?ñÌo03±³^’tgYß`4•úD]dxF,€ ŒÛŒ½€ÌÒÝóPÁ6m '¦wÛž`…‰©îéE ›mg…Þeÿkzìµ]5Äf)SEzÒK=Ü oúö5r†*»Æz΃NÒ3#-gÍX#ÒìgíÑÏs†Eû’´SmöDn²ÖåjP¿ÄÂfE9›ED@¯™h»Ôg¤LPUD<¬*Ö¡IÐ1Õ2ã„ØnÈ;I@“âLö)ÁÍ †`|jÎõÈ@b&–#ˆ9 P9X³ Ý2 S⛢_%5ÅãŽjl¸U]ˆ¦¼ p!þ·ÿsëWf endstream endobj 69 0 obj 12434 endobj 70 0 obj << /ProcSet [ /PDF /Text ] /Font << /F10.0 16 0 R /F6.0 11 0 R /F1.0 18 0 R /F4.0 9 0 R /F5.0 12 0 R /F2.0 10 0 R >> >> endobj 71 0 obj 65 endobj 72 0 obj << /Length 71 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»åZr¹äÍBÖÐ endstream endobj 73 0 obj << /Type /Page /Parent 59 0 R /Resources 74 0 R /Contents 72 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 74 0 obj << /ProcSet [ /PDF ] /XObject << /Fm9 75 0 R >> >> endobj 75 0 obj << /Length 76 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 77 0 R /Filter /FlateDecode >> stream xÚ½}[“#·ræ;~÷a7F ©T¸ò“Ž4ZëAò±4ö:Ö:¡ Øœi®ØÍ’=Òø×;³XEUȺ=kGœI¬@"‘7d&Þ¯þuõ~õ·7+_y#W5üÿåoÊURú•õ¦ªX½yX}õ=¯ê_½y»zµÙ½ýlõæÿ­^¿YÕ•ôŽý (¼ùœ¯´¯”²×O7øï+î·zõ°üíö/ö«_`{Ãú30¢RÒ„3xµ{x× ›˜²Å)[~PÝí6#_¥+ïe¼JQÕì²JU™jìk£ªZÄ3üáÇÿýíßãG,ý‘¬y%>úîço¾“¨¥‰”¦Ò2þæß_ÿüËÿ22;iE¥k‘ã§±ß;QñÞÄx¥F–¢”êŠG¾ûáûïîFd7öP0bœ?j>ƒC”Ó•à<šò¯¿ùåß~~ýã럮 8ÓèJs¶xäÁÒµq•¶Gþæ?~øe8dwŽœ¯jç†CYÕ\±Þƒïu]WFùæ{ø©¯qš«à„ƒIÏúßãh5üŸäømb)œ{`H·²p|ŒôæÅ[Áqm+ÃÕõ×㇛‘äÖSË`ÔˆwÂ]d$Ëj^Y<ŽT};½ÿ­ÏëŽûRÒBT0E~ýjwÞ>œè3Â`·r½oG¯ üɃØ«óý6øÂVÞ64᎜Ññf´Ÿ°Û'ÊWNʘ êJ…ßè±4È7®A¾ÄAJÉ@ü Mòj³>oÇ>‘²ÒÂFk|w8~ÙhSå:úâ¸ÝŽwýaXðã•×ñ0wÛóz·Ùá–¥˜Õ Ö”l>Zÿ~x>©SI¡€ ƒopéåøþ@澸ێ(§Ÿóxˆ»Í•ñXs8’í' ?y>mïÆ>‘ÀIÞÇ 9Ü>È_®qZ<úàpÜmGÈÅ`R•ã:úhýx÷Õá8Æ3µ¬¬äÑjž§ ÆÔ1ÅvçÝáqd9B‚,òr°‘#ƒhwÂGì²9~<×û±¯ÎŒÉv÷|Ü=¾›!ë$Jkuùæ&à‚/Ø•/ï­Œ¾xØ®OÏ#3Cùƈ„à›ãöatCAf¥¥Š‚ Y W PøAgvÓÜõÖ²~|ÜŽñ ÷¹3Z̨°F&óÈÎÁŽØ?`zTµ~¿ÛÜ,DH,æç,ýj¢‚í'®Ko8ÿîf}'™Ò[‰hŒ·Çõ¦ã~j5øÅÌá°ëj:ž`z}¡×ö8¶ ¢ß*×}®LyÜÞ…¦6hMPÍøÝåoÝH Ô”n¬…Wß¶Z†¥¿Û\Õè…Ÿ4Z&1»ü L/y<Ê»ãáùé×W§_?ûzdz¨æ…bÁ‡¡ Þ=nöϧ݇ío ÚŽÀ²¼3 • »·o“Ÿv÷Bß`h„ÊüÛX%“ĺ~=PÉýO®Ä >ùc„¸`ôK…ffðû±)i/U}RÃ)'7ƒ3ѤnÁ^ýÖÒ²å8”kÕݶ§H^é•ñàN]¦‘„¹ü«ÝÝ$3A»¹)¨Fà¸\v×X8›’³Õ­McE—Øäë` *zÖPG_yäõ_뇧=m›‚ÖÒÚÚöë‹0HïǶRdcðã_¥¨)p²ZÕž‡¿ÿ}›+=땃°Irý€½ •ûÀ®–À"„ÿûwüœ]mjÞXÁÏag"áÑ·¥=ØÒ!e_éþ÷¿Ó¿bÖ°aÁ¨2I߃Œ¾³ôHâ g߇ÓYŸ#󲮜Žès$gƒ¼Ñ# 1Nƒ+0@?³¹;Ñ¿^ÖZ‡èo#“1¶ruÄ8c–€¤®LÜÌåt>>oÎÏôüe âQÄܘ‘įu‡GÛhpl4…Ûï·§§ÃãZƒÔG(Hx<ØéÔQ䵫@±„¿Nñ~w¹Ð žDøó ÞÇ0ÆëºXŸ÷ ]eþ£x¬£â•ÖH‚Ã!á.„E™£ï8þo:l80ÿ‘H ŸT,1þ –_nvÇbUÃÏ- >ÛìÇ‹$ø`ý°=®›e²Iª _ÕJM¬ó·óǧíbh8þ/ÏOOÛã•0 åâi<î¶û±ƒÙ¨¼`á7¥65µZ .œ÷‰Õv9 ¾âÛx*Œš ¸ è-SSyØžïwAÄŠœB„C¶ïÖCR°ÉU%PDß6ëÇYd¦å—~L…ÒèY×ýÓ˜1Z£WåVáGl} n«*ú<ž‡í鋲p0²eSW‘2°ÏÑ}“ÝM¶}wÜ&º}e\å@q„q=¶ ðÁ+#lôÅi»ùbľè:¨xØšíæ|—>È"Úœ»Ýé¼~5Š1„á —$ÆŽX0ŠÇ[´yÛžöÔhŒñ׳×Ó0fÚ¢C&ZÃêÝ~ÂÓ€Óß0öGVƒ~GF>iaZÏh°X„Õñ9˜úÚ`|úrGÁòM}­Atj~ñØún-‚Ï&´±^ Æ3Ã_ÖþÅZòo€tôÁ”¹o+þDûEsôFí}§Gô‚ý(:Z=6úà´=ü¶’ÂGóyCÿL#tBôù¿ôd¬ªÀÕ‹~~x;âLH0l4—ÿ3òk°µ‹Àwûý.a=›eKo:ÛnFœ >ˆÇð÷ü¹;߸®²RE#ü¯@>ý Çcæ|3âOp¼ó‹hù_Ûo¤5ï¡ÿç7àŠýñêÍø˜¢ßb¸"Ìît×)טWÜ{þëg_3aãµgáGß*KÿD.ʨàçBXó%üýG5m(jð ñÖù¥Ìs°#¤Q!lc½œfšçZÀ>Z>Ën±¡ºYh8þßïwûÝÓiÔpÕ"â/ÿ>­Y»ß_N%ØõW£&F·Z>vkÝ7‹]ƒâ q{œgåkðYTSÆæŒí €php®Ïë¯ÄyÄÞm=šèSüŠ^5 ·}sÍŒöjŒºè8Gëýæ¯Lú믣ßúƤkœá·ï¿–5ñ·Ñ¸#$Kõ0·ùöý¯Ÿu'ECÕk•ÈÐa€îr.&Kæ€4¼ÝÙ7]snÿêšCÀÚ‚&ƒ€ûÕ—ƒ\etÞÇ¿µ)ðפvIæëèå(ÌÅÇJî )˜pGƇa—azâä¦Öb r ¥ßØr‰úØ`ûÕ&ÆÖׄ£[~yâÀ„‹‘°>v;ï¿Î4?©QqM>[D“þÁèØøPz}7W¢$Ä×o9»žvçËÉ&”ñgz¡mÝ…-’nݺõÚÂÜÆm¾Îp¬?„DǸ@`bvKù§Exà˜ÊÖÖ‘èÉeùÒ3H”Ò`ø½¸ožú¬MÁÉ5„QâÐΞ¯Â„O@v°þý ò,Y”²@48 Ô*Út6§rÌãVCø–UÃxu–Æt,nèù_¢ÁEÌ*„ƒ#Mo4˜A%¼z9 +…Ñd冻܋³gí28+ÒÓ 2Üe1€gK6¹9 Côv“ƒ~ž­%.©Ôìûÿ¬]Æè«äô — ‚’F“T ɨšë„"“±Æœ>=B§ðòe-¢S `jgØ"µ£g ñ6½ ÷=÷ÿúxÿX´"!}]9ß X:†¹Ð²I%º±ÒA‰.w`¶íšŽIDë!cs°Ù &ÍÿæïŒÆ$†‡¯7¸Ä$ìKL"“&]L‚¢Ég‹h>Ÿ1 Qš¿­$hh×ÛÔàŸã³™§M: |ÊkÌc5óh˜¨HNçkÁ¢Q³ØˆrV€E¡Ó!ÖµÅÛq¼ë¾D'GB‹4™­A»ÁìØÂQñ•U†Zü¶0ž"À­txòȲGA¼XpŸZ|–ò ÄsVõŠb¼ÏŠ‚ÝYNòvœ|s¿ìÐ rÖU¥,÷Œ€·]thúèS-§&ÿ¸=F! –ôÀìE ùÆ›ýút*ò‹±šCIA­àPRSÓ)ðÂx†àÌuæ} òîð¸»Ü¹í°ÀKK.a wزȇæçCtÖ†E!!¼jG¹žz˜™p¶™œÆëÕfɵa±õ啨àó¡ˆñ;±ƒQîû“?=?=Žç¢ˆŸÇ\C•]ü–»²x7•ÿ”X@\É—ôÓàyyCPõÃRBÅð^@7‡>ì²¥å5ûÍ̲ªHº¡W$“ÜŒðÃÛ"Å…Ý œÖlõ3ä¦Ã[rs?”‰5Lª‡‡«këýs™`CÉPkIòþ²`wì˜trdg=/»}¹e? ¯cv )Á AüTv«á/iðÇÃyQˆi¨UŅ裷;ýnW¦ÀfÞibêÊ´—0Í¥C{ûøEÙ•^%ÕÁÌã+s‘hÀö˜î˜Ã.ÓR ;xŠæ»‡§ýn³;ï?1|wȤ©xÍûš}ûþyÙMÞ@¹ƒü‘\èn€Õ"Óa’D/Ô(ø ôB—…£t†ðʤAm+«5÷„h^&ú1w× Ï–IædŠ Öõ©Õçf6.‹Fö+þÁ³Ve×’NYM²Òë0Óq‘šÖfBW\‰å%µY¶Zv£)á¨Ù>S?Ì^î+¢Ó‚’ÜÛ_tŸn@![;¥5N oÓiìjb ‡}á}zÓ1€dÔÝã"ù?¼­WG~CJ?@[îŽeû‹ ‚äβl9 Š­!¹ÓäÏ»e‰(˜xiÅþóý*Ý ©@$Ùçâx|½È¤#òw„ÅŽ.ÈßaTþÎú¯Ý©J$ô”Ìû6ÕÈÈá4n†eUrÛ%2¡±!ààŠ¤ME?}]t­ÇFmX¥äW)T‘ Å>@—<‹’›æ<›}·a«U]»x Á —îdI\-*«I#lËNoóu“,ÒÂfoÄütk%Dý½Žè4؈¬úy/bp6ˆ}†m6†Çð…þX?=­¿|·Å´—ãDz¬k.Ñ-%‡j7£(QºJËõ‰5² ¹ŽT+_• ÊÀnÈ?–N‡Óf·ß¯§Šê¦+A°¯/ªôñ­()ÊÄ{VïFضP>a¦ÖÎÛŠŒ{Y7]?(=·›íé´Ðͳ{ÀðäW†ú ß—JJ—¨u™üX§Œì_ŸŒdòÏ0&3ù±Ÿ·µrêÎn¡÷n/@Œ•è—ŸßeôGcõS±³«.ý-6[”Ñ?Q-ÐeôGóžÙe`ºZ³„=I“ÏŠÎ^ÇH5vj/açdÜ“›½È[ö¢’M+¥fô€|UX²®*+bðÉ^X3Ûˆ¼– Kï—”ˆá(rv½ËÜÅšì ìÁÖ‡g‹ï)µÃ±Û9÷ù½ØH¢’~œxŸãÿe*î|VP#Ó¿nO÷Mžaÿ¸~SkÕ®âN( <ì7PpÕp#†Ym’¼æø<¥Ñï8“âŒ6¤tº‚ Z,î 0Lø±Èyñ?·cÞÕ¹yÐ0dv/•ÖÁñálAíìcac']Iš6 »Öõ/„ÿ¬,ÙJ‚ï~øþûŸÊ£ ëº/aÇbbîS•UÓN¶3—rü$ü;|c¾Ä»Æ§Ö¥7, _-äøXÏJá+áôÊZW"™îþStY„O (PYÄhç%€ _wµ¼òJÆkmäÌfs¨¶ªé aë«E2_Ë&U¸v¾2J“3_V·ÛW³’ƒ‚!Kص;«¡hÇCÆ€Òæ7÷e2©yÅkÕÁ/êÛ5yt%6c‘†oúv]‹¾#gþÂTÊžmæñ±¬xê“"Jƒo4z¡¨Å<<ŸÎEÑn|ÕGmÆ¥•@;“ì($œ0³îî¶_–±kw€³¤6ݽýXȱ¼©Â§ðïKVTÚÀ§áƒçŸ³¶X6M85ûCYî ªÁ— ±ÎºÍýúq·)삈ԥFé̉û5æ(n»Óy·)뚢ˆn®‚¡X¦øH¶1ÃnšŠ±RQ¶:ö+PŠ‚¿+cTmaò6ËnÂ=uб»xñoR›&—†¿8,ÿ#Šœt°¦@­›ñéÙ¯ï¾Zø8ÑàKß´ÛIðtÀÜÜÂåÀ#¨#v 0EZ×5%±€Ss£T&€Bµ3·^¶›]šýïžØ°¦ètç /¸Í‹÷z•ʃëÐûG`sØï·Ë²ÈÓºÌ4OPk(Õe_–ô.Sg½¹/‹á«É¸Û•=m©t]iAÂ_Òø‹º*°ä´´Ô&ç”DÙ:à’‘Ä‰C|ª‘+ðÅ…VVU¦¥ÖtŒÀÿ¡¬‚Kãu†—c‡·$)EÛþtç({°÷b6¤g>¿ƒ>›kø$]-FEÂÒ ™kM¡«bÒ½J»JyE­¦°# OÃûœM5Ð_T† Î16'æ>ÞAúü‚~¯­¡Ð?ÙoÌ+ ôµàl´‡~†nº2šÞÕseÐ0Qz„gŠäš†]UœQè·6ú/rŠ9ÇÞ}«Ñ>úY3ðZ„öÝ/ü4—ÉÄôKÝ:‰Ù VPðe¼/±ðƒ}iÊä=qÂâñ†šü¸C=‘ïJ×ÞÛI¿èTFÆ0bQUÑ˜Ææ¡äYHvÒ_ÒxþzÖj°ž£Õ–´Ò'5ø7^Ä£Y»Kõ´‚ £–¬¨PO£MÃñâ#½šÒVúÝ4‰…yá^úRÕMjØ ý…C-¯,…_ØK_¢­ª:pVÒJ?)ÊAâÜôä‹Hã]ž2…~i¥_d@Z3b€E--“•èÒT¤9ÿ®ì¥¥=Až®™k¢<|¡ nð5#’þ?zàøF§ ‰Sú̞ÃVRRa[t_¯<øŠ<´ãúç· ×J¼L ÃRú3¼MÜaA®cI£þ [ÕXØc':õçEZ$F…ëÆxá ‰ÏÚ8E­àîØZÅ'«ôæ€"W˜—Æ^X~Å‹&¥W½ÙÚ;^,³¶ŠZÏ‚Góqà„"wc ì‡ŽŒjúó÷ñY¾cÕÕœš}ó À‹œe° mxYö®¬qŽT®òRtølÉ;3Ò4tSiDL¾} DZK§+0Ü#°‚‡‚ç+ýõEñ/{ `²~UâCkÎSð·—J²ü¥ñ¶Ïiae/Pý4}Ýd+‰^Èê›Sëæ¡Ó>>Ë Øf…å½h¥g?òÀ¢¢2NÚéQŽe¥ùÊVZj—…Í»•ÆÆ²äþîÊ£=öe$°ËZÉ*숣)²”?2 °1q£›ZP†(€/IŽy™Gt}ñT‰A»d|tù y¸ú¯ ä”é_Å4¦¯´91ã})¯ . å¸'ÖÝ&Ua/r°-¸Œ°?aÍ•–B[øÉ`UQ²±ºé™Ø¬;úgØ£óýá® ø†&šò½!^¨ÐFƒÙ‡éõöò.1É: nŠE‡7Ý볬ö¨Ë.¦hòÙËM\6b3ÚÄôv™e)@|<Öv£²é\ïEbÜÕ[Òdƒ¥°Ô^°î«kë`çíµupÍoÿ*Ý"F¢4¢4'û]‘ó [#,©4ëæBgË&"9£ ô€Š7hn3—)8àÃNiÄM`ŸEíLÁgÄlI»ð^¾{õc_ÜÑtÆd@YÎ’ÈSaó>.‹ã%=è4î˜-‘,T¤ÄZiÔ®é)iúB‰•–4ôòÌ¡0Ãó Þ5çtÐ49( Fƒe‡}»ÂÆ léÁ“h»›ô¬·RÆ`AHÔŽ³7z âðv·Ÿ%+î$ðœîÍ9ÀN¤[±yB<=†Z˜½z{<<äI7 fF;ltx¿=¯¿ÍóáY,‹,jn‚ cêm„í0'ƃQÁ&;W²%´ð®ª N¶e¹÷_‰,kÀ0\±éÙ.!-fÞaEÚ÷cæÐmµ°•PžÄ=mÖ': ?Ff§9кʣïÅÓ`ÚÕÍ+2EM)#ÙŸv1´vMuÏT ›vo#av-ÚAØÐµx|~ø}{üíð¼Áíi–œê»®Rð_£uL˜œl0ñ¾i޽?z´ ß\<Ï¢FÚÞ¿Î~ß`D^·ßg¾C2ma‘©-§`?Ì’ûÃü*Øz.Ó ìÕXýϨÉÅÁt7ê ïü6®˜¼Q“tËH ÈÚKªqðGÝ[ÿøµQïx° úh º÷’¢ÏXÊå}4ºÊë¹ ’>É©¤& î#ºy×fŒ I)®ÃöÇYDu¢r ¢ÞoË3Ø1–û 6Ì0Ë ¬“òXôØÑsøh‚J 6.êú¯¼íE¥}ʦ™`–ÛP_ºÏ!À|1©¾M¢Ž¦Ü9OÍ[~. ˰Ò*‹°˜8ÎÑ IS¶©Þšâ/2¯›WŽ&ïhëøU7ýíæ—-9¼ò ïòà]ƒ,c´σ˜ïÄ[ #î?Æ!½÷$÷æQ÷*n€‹mⱜ ‡”-;ÁÚÀ¶ Qh·D6€U,-£¦ÜTQN¼B9vžU ‘$EŽYvB l\•] 'G‹÷Ƹ®6XøLÑän›Çr\ƒ R)Æs}ÇŽ´t•äžÂÅJÿóîW)Íö.[3Ëïõ…ÜïgQ#¾b¸.›ÄÆyù>Y’_*0«x<ÒUª<¹}|L‡É2\„¤FE?FS_=Ëâ,·éÓ<©°‰~vPógŒ:ç¯Q"Ài±”žìC(<‚ “¾E‚qKˆ))AÒõtxΣ¬“õ »Ï §7f¶§Èú{žd»žf|B¦òÅò´)ÞNqCÁbšØ]ž6Ûk·úÀl‘D¦È7]À1]a˜åÆ]mí4t¢ã›Œž(îšpÙ6#[•Á”´0¯°,’ìË•Åå: а?¾þæ—ûùõ¯z“BÐ|# !øØ|§)ÛˆDM‡oþã‡_ò1;«ëޱùåO#÷ŒÝÙÅT7l:>7Ü•ÊtVR°OÛãÃî|žy~à¶n¼¹>xW°°~|—w™‹ñ$í8#f½;e…âes¡âéÚ[:ïjÍcñ,¹o<ë†\z_I/bPw ?|‘w‡ìjnÆÚû ÞÎôä]㥉°MgÄ~Yò Ã/$×VY—s]¦Sz뉹ôþax5Àâû§Ãòé`èLs:}ÿ„áýCó®-¬â·ÓóÓÓáxÎðºä¦h1óV’ómRS„9šÔ4CзÉLæ_%—7ÌœK RÊ›ºy%fFòÒ`YÎÙw¼2Fuã²å;™<ü—wzâÕLç-y^Ië®sI>yÞæ-v ‚Ù˜ÖÌ ÒP~`GÁn³$=:ƒ: ɲ“–ËG×>ÞîEIK}à6‡«u°$"šðÜS1®Sø`ªµ}–8n-`_=ØÖNqÁdš½Û¯O§,ÍѤÄó ö^?íöûõñc^žÃø^M ýE–ƒ‹²H7.MnTRVÆ3ŠïŸ×Çóe¥6*Ø@ïøB³E)\àíI?BýEfn˜©àp³1~Îʾç”,I·»‰´ƒ‘ô;ìë#^žå0¸¤kþâ,§Q¾ IòÜÃv®6ÐYNÐg{8<åÑØú&5~„ÆU»H>ÂsæF: ß\Ýšà…ÞΑ1²ª¹¢™+@-+)\Ðþˆrû|¡ ˜iGhvã 8±¼ ‰ãò—­éÇ–S>šP•3¶û0á£yçùhƒLØæ1bjt0¹ öàr­®_/›ß¬Ü*LÐP’š_vðXâ…š¦õn_õÝzf ÷`«5Ê Ûá»ìmNy VŽ£¿C?æ%Xa®y[§Ê–\Wö.(jlR¬HÚN¼ë’À½¤ä¢mˆm¢ÉξKaéÛQ‰ÚQTí±?[»Â‹ ãóeùw?ÀZÆ6Ó”mNCV²¥¬+qÃ]Ö°i$Ý¥ñC´¡p›'rr²´q ‰e—½šk§9Í­…¿Ì ¨Ñ%¹U›Ý$u)‘ eSGGI D¨KvÄ•å§G‚üÆÔlψ¹þ¹;ßçkü¥ó Û>s|Þ{%[l®'Ömž#BÛ>§};çd¤›‚èJjÞᲩ“1;²­}c¤%ç ¸ÇÃóSÓäë¼k60¸³1¼ ´Ðfÿ|Ú}ØþÖ ”çû¢•…6TøFy¿¤£5 /øYnG…n:Dõ(4µ£lrGÓ¸ÁŽ.¼Ýív´‡Ûj‘?2Ëúà{͈Énó(Û¼`) |$ùŽÍ`Šºr\ÆÐjYóìšÅ‘d‹Äµ.ƒ÷9r³Í;©¸$p]%Gé²–´»Ë8 !h^7ÐDlÖ §þÅC³iØìz¥.2Ûƒ}©Àlz¶…qÙ4hYX6_—²œ¨lš°EAÙò“Æd‰ÝËË£îB²PV‘]9žù‹%Qwlƒº0…:Ýt¶5_Àñf4l¡ñšg%¦kS…*Yr³/çø‹X’¨UÞñ5—˜L2’µ‹Hêd“I“$i¶LÔàŠ;íÒDý33¢[7ÓIÈufo2Á+í̧ã6ïðc¦ª6)PöêÃîð|ÚçµÐjž‘•Q×Û‹þöòzeŸv¸Ëë–ˆÇB1w-²;¿È;¾F4o•†+(e6ì/Rk·JcÞï6÷™I5¬XKÀF¦[ScÁ÷ÓCPv¹“È<Àø´ Q¢jÞýˆÕ¯3O°¬xÈP½æ pˆ›[¤¬«?´ „”}pv;qUQlS¹…X•4ÈŒ"ËÍX¥Aû»Ì°2¾VjT$Až)îts¾z°¥Ae¬ß6Y'ú,ŽXâ¦éQ‘F Û,.”ØzH‚”Bc‹L¡’˜lôÁÔQ™ V¬ì0x.x¿[/Ü®îuw+š´ó4~ϪRÌY«Ìçs^2(¦©sGPõtŸ+aq«(²>çu0eͽ·¥ˆ^P/*Ü“øÒ/u~ßf%à+à5>éÞ«SnCf0dÀlAcxš¬øÞ5ÕÇmÞëŸü DëŸY]o®íM\åLÚðfËk£M%­ïc²®Gùe™¥€îk÷²™¥è*hù¯—¿J콋àà–ÙA?ã´ýoXÀm endstream endobj 76 0 obj 11368 endobj 77 0 obj << /ProcSet [ /PDF /Text ] /Font << /F4.0 9 0 R /F2.0 10 0 R /F6.0 11 0 R /F5.0 12 0 R /F7.0 14 0 R /F8.0 13 0 R /F10.0 16 0 R /F9.0 78 0 R /F9.1 15 0 R /F1.0 18 0 R >> >> endobj 78 0 obj << /Type /Font /Subtype /Type1 /BaseFont /NLTDNJ+CMSY7 /FontDescriptor 197 0 R /Widths 198 0 R /FirstChar 92 /LastChar 92 /Encoding /MacRomanEncoding >> endobj 79 0 obj 66 endobj 80 0 obj << /Length 79 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»åp¹ä R?ø endstream endobj 81 0 obj << /Type /Page /Parent 59 0 R /Resources 82 0 R /Contents 80 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 82 0 obj << /ProcSet [ /PDF ] /XObject << /Fm10 83 0 R >> >> endobj 83 0 obj << /Length 84 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 85 0 R /Filter /FlateDecode >> stream xÚÅ}ë“Ç‘ß÷ú+Övø°R×»Jß(’g1u$ì£xP0»ìœvg ™Y€Ð_ïÌžî™~TN?²—–"ÚýuVVVVfV>þqóo7ÿ¸ùÛ›$“77ü÷ô7¥1é&$/ ¯oÞ<Þüî_•,nÔÍ›÷7/¾ùî_ÿõ‡?¿¼yóŸ7ß¾…4)Þ| U"¨›è¥óîüÛ·øï¥J1wóx£%üíò/n~ÿ–#"&éœmñâOß~õãÿùáÛ?}ûç7ÕçëÏ u£|’Ñé ß½iWœþ¦‚–Ѫև¿úé»ë/fHÕ>È`ο"J†é3ì¼ö»!Jtësß¼ôÏG'‹Úäåð«å褤 m>¾¹Füœ1®¹–<~õ7SÀϩԦÿ»¯ß|÷ýYDr¿e½ô*¶WñÃwß^á²p6È"by»yß ø_ç¢Tn‰¬PêšXTsùè[|Ù<~¸ÂÞöNÉ»Íí™JQSYŸ7ù"ƾäz,¶]"ËUŠÆï;«àœ~~4¸°›Æ?hà 6Í_ÇÏ üXÿñ 5³e éÈÊ*|è´ÇM-ЀƒƒeŒúüÓ£â…ÃÔXfPMj*9(?|õÍwgmÒ5¬ #]0¢\ XC¤GàŠ† (4HH)*¹½h‡oVÇÕuX‘'ô”Cq!p7Çõãá ,&ðå5(ÓðvwUádˆNäï×£`ƒL¡ä-þåF)74o›BÚÆÜ› .)g·‰kϸ¿ää>KjÒÁ)v‰âj)¶ÓD¬¡á€Ã-BòávuænNOkåNú3ûa·ÿÒÂcšqÒjÇ/îÖ‡ÛýæÝzÞ1…tIq­{Šu´pŒÅŠýên³zAV¯µ~p`KYÓ£w³ÛÖöÀ$>€=¤¼Ò5n×*y:¬ïfÉÜRÆyMÑû~·Ÿ%jª€‹¡ Ùð¸^žö›í‡QG¯ö†±®^¾»‹í0 Öà±+ö«ÛrûF`‹v‚ˆ$›7Ûãz{˜wø” Ôæ‘\›õáÕ¼£g,î!ÅÍñ0ïèÁîig)VÜî6« §Å8ªÞû‘âÇj;뜜µóm÷ø=î¶»Ûûýéþçj””dO‰ðç¯tYón DZ©ï&˜YàÔ”W`YLV£MØh$øK‚ ø°züø°–³NŒVAÆ"Q¼øËîp|}Ÿeá½bŒíÁW:ä¸_¯Žëíq–R­…EG¸]—ôÝûY ñZúà …šÛB1‚à×8ÐÖì»õêqÖ…¥ `‚mÀŠ–ò8̳ŒXð–älmiÜÍ2Á•S'MJpâËÌ“g¥E£«‡Zž¼»A‡áÊÑ ´sžÚ¶Ã0I?`áF’ÇCƒ ®)pkS'½b¤® ¨MÈ®¸æ0 à‚Uèüù¨ Âa˜)´¯l–üú¿ùöÍ·_¿ùþ‡Y¼­Õ hLëý€»0^ráÊð*d`EÖ[ øã 7Oî¨ÛâÆOm)´åßÎ,(¢ìñöëAI4@o. xr ò¨õ‹ë¤6PC'Wei/>ìwOß¾8¼}ùûñ|h€«Œ+0a/ضqrož›Oë_ʯÌb â;­ÀIÒÛý˜Þï÷Û _Ì ¿ÚGæ²ó¡{k|=ÆóÍÀŠz'/¸×=_Ê`£ö’Àýû( ¶ 5hŠó âÅ,à©3¶8s kÀ~™.s¢†Qˆ¾Ãƒ†²¬d¢t©Ñ2–Õ¿ØÜå$¤ °zÑFçË`Þ%Þ(~œ¢Økô€0'JÝÙæûö×¶996ÂuáBÜŠj¢¨A7†doòˆo.Fß6™àÙ")ôݪC{ +p@“YTñbœ¿Ü…ÔàÓz]AŠ¡ùæ3.`e•ßX*ü“ãèxö\4ëi†SYë9}0·žBšYv#>EK-åq–¢-ü8­£@ÅXà“|$˜.^ÜížÞ=̳ÊO»)¼sOõ¨ý¸ÙÞïÖ£dåšä«(­!ù(öÈ‘”–Ó'sÒòa¿úx¿™%ûÚZ© M-èHqJŒv; ¸×â0£Ž_>®yü©?$ºìùúi–ƒ«*“:ò+øß£Î=bñ|š6fºûv§Á{‚ÐU¹ƒœÀAN¨²]Îö·ðóêÓúa½ýp¼GM?KÕ¨$1p~ùdk)*§j**]òŽû°wÛÌícm½ô©{ÖÞíôÛ>ji,ôŒÛºíõ9Iã #ò”{·YCxª5ØãyЮw;Ö"S*š%PG¾Qv­§(Udù 0Ã$³h’b“Àä˜ã†» NÄ6½™ÖP^•îrñûŸçlP°Ò‡DmÐûYþ·‘ÁòßçìH|r‘Ø ˜h#ßè;îwá%¹ô?¬oG©ýŽkw+>Ÿç1ÿþys¼õÌØuÀ£ †:Eÿ‚ˆbº÷•î"Šé²yq¾èñ °ë)îþ¹žWFõ©¬@ÿã«Û™IŒ€FíÑ×û/‡£eèæ¯{¥úZù…JI½}ùj†øƒ7Ÿ\j ·Äÿkæ²" ¨Õ:ø×ð?áorÖå^óƒ&nØ"l›s ¸ò%X†—/ Úš˜è^8gËTŠqví˜üJŠøü‡*»–c0WÈbŽaÛ7–Ár+R‡ÜËvØÛÒÚ\áÁªç›ˆi–­³è-÷œÏ!/nŽá_ïfî‹M'îâpu•·Qœx›IbwÍ$v×Hbo¥6rà­K£sè/OåUê¿E[覆hü[ý­€ŠËJEþ€d™yíKâò%~B;²ó©Š©í@MNLˆïtnPŠÎéöW.YMo_LYBvªeÒ„nÄ&× E7ê«Ë5ýë1ëiŽ¢ÚÕUÙaHuzÞ¾œÂî99Ip °ƒ:a{Z½þ2”Ú8ò³X2­ïÎÝä®nTÁÀ¡mp—«ËiU‰DUz®Õo]*sÊCŽU"EÒ—Ñ©Y©‰sC* scI\Gß =‰ipKS½âë5wƒlM°IÊ›•DWá©XDž¹iÀ}©²¯1#9£áôÕÄo¥e\=EŽÌ­úD›Ò%>Á~s•ïb(‡Éƒ«5…>ZB‹§00ië¯t“+ˆkøx#Oi0’¥–ð~wûtÈ&å‰ÑäƒÉbàÇú_8ezÍÚÝsú#˜/1 ‚úÕÇ"0CÈ~?µÞHø<ñΛ™˜F=‘áSt\\=‡.J_ŽAúŤ›rò—üº^†R<ü~Šø÷² ÜG>ÔßèŠ?‰v²îl„ýán‰6¶Wöe O=?äغ.:OÂ?>rXƒ ËêÂ~ÑE?½½®^z8WVL©FKýçPÁÁ.‡¾`orã1P…»œ®ì²ãì2¦¿¸ži—5V;9wå¸Wœ ÁŠ Þ^Ù[ËaŽÆ¬ú+Ì©®˜, 6áq³ßïö‡ \ê¿W…( ã¯yÅî^‚ãÞÀ.Le·]oñ?ºöþߦ,†ðL­×ÒªÁÐM6€JÞBí/Õžiõ)ÑóL/ #ד‰X¦l˜Ð^Nck^dcÊĺИۥÚЗœ¡ÛÝݤ;:ë> Šî)†¯ˆpéûògN³h[xŠ'ÿƒcÑÕÒã ØbÛõzßÜo›Îãû8¾Yø+%-„¨ô ‚ôàªèXØÂ1é¸JÑļ¸Z˜4Ò¢Sª2ºò´¯Xv.&ÅÆHaÜaé>[P;ÁpéL½¸nJ:H—‡?‹¹>-Ú{êLfUÌh¡/ËÛÑXï1H\)\ —(}Jæ'xíˆIKŽÜÙLÓT7&2&JäÉ~cݘèÁÅSùdqÅH¹ÇœP“</§1&ˬыŒø¯ÿí~ªqË~úå×_»§ým¾\kämî¶iedhÐ ‡–±ò¹ÝLÚ0a·:NÙè|¤¶Kzþªxê}ÖZº~XüXãÊ8UCt=ø:È´ßœVCøÀz. Ÿ§ø•.h«ˆq%ŸâWN{Šú;V|OºGSàöëõÙs •É™«ýêáaý0ÍÒïÆ¯´4<Ì/!s늉¬ (Ég°N]ÚÒ˪º däk0¼êðç¢x~šæût/F'­£vwõë k°YIAEJþÛ‡õ$áo+ÌZ§óîBïZ¬›ÜÍåLÙoæŒ.ƶ Él{çI<š o_JVL×™/ˆÓ³ÓÐ7ø"©lXú^Y|)søŠåþX—Iº6ïWØåf½ŸÁÑìL`œ£ys¼þØ5¨ -uAâŸRþfk¸ ƒñ”àÏQ˜M ÃÉEÉ“þÓëýЧ+.;1ød3ÑêÒKkH­°âiËèKµFHÍ‘Å0^ƒU$øÃÃÓkcj]\À~×ë´Ù‚¾d1'jðý‹Pa¢û9Äž„FŽ6úΫuL! ÆEò zË}"ÅägŒéô\ßn×Û^¸NLZ¶ð2}&Uªsõ~žÚlSJF£©E€É¹SÊø…%Ñ› ¬xoáØr¶Œnæ·šê¿5r§«ƒfb’Þ]{Ηœ­Nà³cßîgêìb®ñ ‹2„XÓx€£†e8Õhg´ùà@UÄzëðp„ý]íY[¬@×¹HÑÿ´½]ï«Íöø…³ÃXcŽí‰~ûb-òNÎÊlÏEI­È¥}ÀÆ^iád¨\ÙgÎ)Ž˜¸~>hÝS|·Ù¯o_/qF}B®MæÃæ9ø<í[}¦½¸ß¨<˜÷AýõxÌ`ÈDß֓¬ç *ˆl›9o}¶cÖmH¶\°fq_á’¢¸òñaµåñ%t „fµß=ñnÆ2©Ý©kÛÊÑ6Æ–mÀ ôÇõŠg4xðxU¤¸Ó‹ŠÏp.ˆ%y¢Þ D€Å8ûß”£z±ëR[žŒ`›ÒUéòèÏ;^HcÀ˜ŸÄŽ÷«#/P ;ÿž(8Ÿ u M±æ°{dq¦,ZŒé¼øµOØë‚€>|Ù¢Q~Üã}Â9^ÚÈdÅŸã=3ÎiUYÐJ¬âKñ`·`¼OòØ«‡'žã½,"Å&[‚®“¤—^)¾ÝôÒ_ŌЃqø;²»ÿH?Å•uʪ‹}Žj€³U>n¯Xg L?óÄgNK˜kª)¬ûˆ±ÂîîïçûÍí=/ðôD~»:0•CždÌŠÅ—`¥ó[nYFöDÄ›%zÇ3]ceg±?±’ VPä²Þ6»-/ð ×_ ŽÒ†åëhwH °·ëõÝúNò”$ØÆÚÌyÃs‘A7*RZx²“ÊRl¹Ý±ô Ú“Ê8‚%ŸX,IØ‹¢{½g™a8à)éô*¥¾ˆ°jT«EY‚ÃVJ)9agN°@Kç…λ€¢Á¢7G±år‰²Rà–ÃÁ9Ä 2Á1%voàÒ=p1'+° µ ´ÈeEBØíÆQØŸXϨp~ŒS†$r- »¢s×Er6_¢—6‘ÒrÇ ''ƒkn¨è%ä¼âݤZ*g(꟎›¬NQðÚ't1IWq&yiRá(ÒϺ’•#tšÕý„˜­+[9Bª»w…õ¬,! ‘‚s®Ýà%—Z©ÐûÉo/ï*Ѿ¥„™ìV˜pl5)÷‡Õ#Ïí´Z(Î, 01J¤Hág*̲Ð?“RÐ œ© )Þüõç%Ô¥ÂY«öfª6¡. ŒÀæá«j7V  ïñé8Žò²ð¢~È“.…‚#eIÞW¹#æàÈgç(î¼›Óî¬Éž„å>${*ó’ÕÈÑ–Ç©ÿQÙ—’åÉUæûôŽPάÃÚcGÁÞ4ÂDbÎã^”)6ÐÛ¹fkNb‡Ž…´‘ÜÙ®÷¼Œü‚oHÎ0kk†£0Š^߉§mY³¾ã4§-#ìhŒœ>såW²,l ŠùÕ°‹==öœóÔ*ØÅž GŠ¯ÆØsl)ç=Å™Ãî‘W(Œ³…1Á#O|£"“©Æ²CÛûHe.¸ <8@ŽÜZ¦vÃ.8šÜ\VR}٥ɑlá&ÕW _‡]¸ëŠÃ¤5(ðN­ç\Ù/ÇÃU_Y¸O'ïŸXB³Ü“W9¾îe =ÙÿÇÓŠ[9a=¹ûõÝ+î°çHÚò†Í€—è)ÆÌ«Uí˜=&ò?T¬:Êì‰$kXM ±jÂÃmH°ævÇNyôÞS”â½liS¤°[…¥³1 +T ‡œD ÷š¨ÊR†¥1!e¾÷1·´´SKJ ‚ø'÷ xmC¡)ÆääQLKÿ´.öÐÅüJÊÆ€'5¹£Å¥Ã h˜H¡óú–šÅ^„)VK¥I÷X»CÐÏ1:y ¾uiL¯· Žm€ v}iÆ(ÆÉˆ¤`&¼ÙòÉ„¯“æ9q4b‰Õ;§/ðÆZô㋘ñlÆÉüä÷¬¥!Yó‰÷c¤ÕžbÊ,[[4¯%ËB’ù¹Ý–°‡…Õ1ÿ°<—/`:ìŽV‹lCyN#W%U E|%î¯x÷GE9R­ý Ѫe%b†ð•-x÷…÷|ídˆ$‹ ^ß“BŸÚÛ‰¢ÇÉOÀ7z ºûÕ·Ó&ØÅF‡.û«¶÷Ö ¹1•d#%ôÜ’ ll«y^7Ü÷)£^–ö²ôc5ž0Ë™¥½¢í2•:¸IûÈâÞÁ™~ È¬qÁ¾¦ÖŠ)’3²Ôí¨‡ûÉ÷r,ÿý~½_søâáJõQQøÛIõÁ½A¨]`_ƒ³z tÑÎ@­˜'|j”ÞT+ _8 þäGÎå Í-Í—ÎpLU¸“œ§üKé©ìïE`¯·¯xÃaSðÉseâ#f-:” !/‡ÃÓã´bÔùÎI¸•2_s¥½¥3e}pŒ|Peǃ«²>wJ(*\LBï‚ ÖœÜË yÐ.t¶µ5'·`M.³6IoÏP3I¾j qÁÍ 3Cˆ+ÓÝðôZ ÂÙÁÎbâx·^gS*ßb±¾­-Û¢ý }!(Òù}!p£ ÎHWCÌìïRÚ gøçi aÊ$1b^LQÛòé½ .f'¶†!Ò÷ ÊÇûÌ‚Âəζyð¾˜ú Ljp‚%E=»¢¼(CsyðF©7«žÜJŸÚ¼¹^é=¾Ù!ÎN äÉ*õÎ8Á lŽ‚?•a‹¹#1Ïj'öÜ YUØ¢3팾tv=-¾Dv5€-Ïn v=-O>Ohêñkyl^ÛÝÓôµOàØ5b)Ìj«jìÚ¼}£Æ®‘û\]ã&ÉÃIÆ8Raz ipîÚ{‚CŨÙâ]LYpÑQàõà5–ÓË)]{˜ ¶¨" ’|nÑw©"t½ã¥Ïv[ÀºµE‡-#¯ ¾š{ ~.½©ÜJ4¼f=)‘üR4¬ˆÎ’GŠ91Ú  M²‡[‹†­qjϯE;•}+Š;ÜZ´ZŸEì`Õ•Ék Ãá4yM÷>"Å8­œÌÓä5b CÅ8c¼œ¼FÀ¿o5v3'¯¬™3y­É™jòA:3+³œ¼F@·&¯q\àjòZõ™çš¼F¬b‘ÉköB“ׯ,3yÚÜ'¯îA ѩ瘽ÖÃ~®ÙkÄw–¾V?ÓôµH¿Ôø5~‰ùkgÀF½Ì6|‰lO–›ÁFÉú"CØð§°üYd %3KÌa£N)¯a=ˆàÊ"“ØÊÅö꥾šðá\ûçÆfjìgÆv!ý9¦±YŠ/ËNc#V°Ì4¶.ø¢Óب­]b½È46‚)KMc»*’ÜiløÓØTü™¦±Ô“µ&bòÈ4jsß}áÕþ–#Óòs#Óf=ËPj™gdô¡·»wN‰ÏifZ›™6³:ŽÙ àO›*•¿&ù"f M£»š¦àE¸äd›×ûià‹~ÿÅSí#ß¼®}¨ðE¶öan¾y]û@ÏJïkì©¡ˆ|탥ø2-Ñ/O8Õ>´ØðêNµט>¿hãTû@pk8l9Õ>„O| é‘^Õ>PòRÕ>pJ7ªÚ‚9¬JŸ²ö᪬sXSÕ>ðÌ:Ÿªöàʬڇ¦ÌTµ-ÚÇ×> ²¦ª} Xsª}`ÈÌy(f“;ÏUû`0¨el4í‡j¶’Sý`6Ôë®ìýæá¸Þÿ²¾û0©l§lë°KKí]©}¸jcv¡ÄGë´;§y±kÀ\G’þ’S±sÞè2ZYzzz£iîCšmù&¬êïŠáý˜pÒ­³åœ–Ö¢.η›lŧdåEý[€ ÿö¸“íæñ§vèB]þÕÃÍòŒâ¹õVê"’ä]{Rk Sœ Fj“ ºh¢_9CW°Eí¥6$åòîÚà'£†-X¸l àa¤¢…n˜5®Ðå^Jè^NáM¯gE}’ànýRò¯Þvû™D=1ø‘fÔ6À©÷‘Ê›½®#á…IØõˆZµHE_ê{îfËjü¿Óœa¶X¾ˆ%6‡ ¡_4 ‡+'¶ÙHîìöÃá¸g±g©ú@èûÓÎÒ™¶#¸cMÙóòBËÑß=fpç2òÌc²)÷×r¶ú¡GzÀ¤-üj‹ìŒÁ|9}–÷®>8_zØÓ ç:fµ|F~èæ O~gÃÉþÈë„§C¾ËÚX­)ΊÍ¾÷ý¼ÚõÙï <Š`(ôëýãæx¼ÖørXï›PHƒøôþ>o?L¿ö†Á¹Ä`òkØ8—¢)cF¶ .v?‹1É•cÛÆ3ÄF\°(5ݦ{T¯œ†ŽRÓ–bxÁá‰-¬ŒJµyr¡û‡'åXt„= -Žà ¶·ž’““q3›)˜Ùê4%(’ħîéåØŽº ÇÖÀ.× ï®8¶Ó®õŽ_ T±ñ­ÖÂäf{¿{Ü}Xo×›ã—)÷áÚž>3Å•¢ E×µm®À5o¯ë®m_j;¤×®m_/$³ç­ÖV&]µú¾æÚ¶÷ƒs½:Ùs§/çƒ ³¢7pÍ·W5ìÛ¾íù·Ú¾­˜ãÛR½Ï¶—Nù¶3D ¢¦Ð×,¾âT2c)Æù¶ƒ1 p­´5é'ß–Á§`‡)r“NRÏë¬O’ÒðϽö\=¼ýysw¼çÊ&à„ÚóG¦4°±‚lAUÜÌÇõq¿>pBÖè“É“_ÓÂYGhæÁ¹®¸ÎøcÄo¶·g@ÿ$OnîÝz{dñ&©“ÖÉÃ_Ÿ‹=ÂÃRp=¡M1‡Ã‡½U®í*ƒ/û:ý2ŒÃ¬.¿|Cô8wb<‡ù¼æpç¬Ö TýÚ¡õtþÓÃjÏa 1šúS:ÃŒ9‚VÃ_ƌ &Pè`>±N‘¤sbÌ{ìeÁ ½`Ü ‹¿©ý¥kûÇÄÔÀ%DÓçÎ9Ûõ"AŸÔÆg ºè‹]ªo<[Ð…XÃ2A—øÂA‚1‹]Zt/t!¾HХœ…ƒ.-ººr²LÐ…”E‚.-Ÿ;èâ±}y¿mã³].ßj]M3v{NÐÅ•“YªÏ,t9=”µVpñkN¼G4 ú×ãq͇r(†¼déúZ€Úùa8Kaö.çB9 üêê˼}îŰ)–é5—5"–S€EiDý[Ï—§tK Ècæ)DujTwF_0OÝ}GRÎÎS(ó²-ÏÏSP…LJ‘B·Hž‚wð§Ó-ËA§ë4¢¦Ð×ÇûÝËŸÂAþL~¯ÓÌáڀΠì€dHú¯ûkƒa õß½Ã9,§ û1`Mqž9͆Q£ƒ™¹F<dÈÑ\j¤’xƬ4†ÜéïÞóâ < ò¬–ˆ+xðuê O˜}7õt°A\ª¿Ó+Þ9W¬Ó€­÷œ¢V2ÍÇê «1e|:pBÖ-uÑR¼¹:Çq_0ZªI¾0/, Ú“ò³:®÷›Õ+h‡Õ£…§Øsud˘¦‘Q›gb5Ë"rB(1j·>°¸ƒÍ=)<;¦æë@ÛgbÎY÷àÀ;Ók”þ‡ýêÖÎq¨?ã÷¢:k|^O ݉¬jóe+±ŒU§WúätA°¯ ÝCC >¦) ë¥A+.¿V,æ¼ÍÚ—Óâ;ØßþZvÿ<üžc…0&, OߘVŽ1§óZ}«&þ¸{Xí7‡í/ÛÝþ‘Ÿ›×ZÒ²¹y­~^¯·KÇž‡GgU‰JÇ…LÚÓB9ØB¨¶þ\ïýîv÷ø\<^nö(I†ZÊ‘•ÛfÐq‰l13üÙIœ÷]P„¿®Dö[ RJîpiEþóì=ˆÙ Á¾L¼$6˜>7§ašóX4¨(\QŽÐ$ЙiK_”¥8³DZçùc{ï³-ÿ%':I‘”ŽÎ ªmWQæ!ðíè윇:,ïDóòŒ/˜é¶FÈ糤"¶îÔ¿t<ÒùÎ… …í}FÔækþ\Žï…“›­¥–12&@õ¿R¦¬þ!ÀÛ¯˜q(gk4I]‡—ÓþÊbÊ-ɘ+ïøxL™ë3ŸÃCÐFlmJeWë~DO?‡å"ô~çÐÁ5e´ÇØÌsk°'¸]ð¥4–JZEñ…«Ð”tn[¦'/ꀳŸò\i…°¾°ž+0¦€CvU$5“!9AðQ-àôì¼à9Û[fߨ"‰q{0µ©SR‰âÍj¿zxX?°b•NÀ¶1…î­ Ù?áê2>I—ùF療÷– ;¤Ì7–xKÐQú bÜ· .g‘(ö,SäR> ÂõR}dá×{Wœ3A-á¤-8Û‹&3N(!¶·~Kc¨iŒVcÇùkBúšu‡Õ'-‚‡ëMôZãÌh¾j,ʨiÀ‹ÎüÔGÖ{»ã°UD¿Ú²LA:¸¤$8f0›€k|^¡E;ƒ)ÿl’~­ƒý쌿~ÝZQ¶÷&Åkùrz WÔŽ,ô@nqè^ÑËùCÎðꎌÃѦþÀÂíp<Ž õ\Þàô·@ò†ùnZ¾à$G1f‘v8Ú˘ µ€Ü¨t1­…X3|zøbvÕTÓIõ…t`jÍÛÛA{”¨§åþÐr°§ RQÖó]ÐE›ñkŽçÊÖ)ä¶^™gÅr>f üzÛÈ5¯¯ZÞ§¶Ð»y#=¶h]¦h<2p˜"ã¯%c@Mz§)mp»Ûb¥øë%²(0cFY×ú|`…4ÀvvxvÐÅü˜L+¤‘@[šv~Ä õ16#&>>¬üËBzkjt²Šr¼—w`B9ÇŠXÆ o_JNèü,E>uWµMt_zY%UÞÇnS6÷Á©ÎûèCÌÏûh6r«ò>ˆ5L‹¿Qy-ðNÞÇØ•÷Ñ%\ÌOq¸0¥jSÖžš) ®·)#^pxR·)ëÒ-æ·)»<¢UmÊZØ#Û” ò¤jSFÈIë…KÌmSFèÉiäS§8´9ôLÌMqÀ¾‘¦¶Óž9Åáò­\ŠÃ?·¿vOûÛõBehÕמ#Ñ¡µgHthá/];ƒèŒM‹×Îé&ÕèÏP;§GŸ[;¥O–b /ð ×V­„3»Ö‚ØX ºYÍ1ݰÒV‘"Ã-žíHÆp‹gœÂü [<ƒÅ…^SŒaWÏ`ü7‘Äsý9eËáúá#ÏÓ`ˆSŒ©Êr81At‡è}¥ËrÄd=©ÁXNݬ,ž7jÒÉ`ÀÊ€ŸcŽœ^28VÖ˜›<~/ä8m_*¤ÆF{7;€`‚<á¯eMÒ ñô ˜ÿ 7”•»ÖÔZºR¦0ÍñüÎrUB*»häÁVïv{ìCñ…W-ceˆŠ`Î_Yñ/Õi)áYýÊëÝvV\X&3"›ezXœ!cjð~Ù.öfÚ²ðeAÿKYbÿ^k3Øbæ´ˆ–ÂQ.+A>ñÉ»mj—¯qK¾úé»9AlÙãŠÐƒ¯TåíêÈÓ•6•#—ê?àAå<€¼Šd«Ü¬ òf°+ÎüyÇã fϪR^®ûfC|q ]¼·4|C͈9I<Åéà /fψÌ\ç´Læ í¼ë›z(R ÙOçµÆ)`z/Û£50¾kTà£M©INØåO…Þg–y1ÄVKÆQkྂIH•AÞÈ^PgEjà‹ÑòÜ[ly[ÍwÉmîýî¸Û^ñæ1Eµ§>±Þ÷÷\ ŒþÓ`£IùÙ¿µ†Œ?;És¨²¿b½ÕºßT/Iäðe‹ý‡û39H—/'ÄWðyéaÃt´•Æéú=%·ç[NÓŸ ú‡bD3‘þ¿bu7®b-_¦y]¾A`+è öš&ÿÆ¡_ÒÅóŸþ/†Š=Eöè|zÊäñ\KÁ·ËIÄôä±´7ÑÛé‚ë=kXûY3€wèœ]Zæ3e)ÏœQhpˆ©©Á»Bÿ‰Å°ÁË•'|õðÄJ{¥(ø“¡3oîJY‰îb›+ãó9®·e\bQ¼ç‡ò8Gmöh¿¥Á3qæÙùx']r¿an(°Uîüå~âǬÞŠˆ»ál{iKͯp×F ¼å°ha/¬¥™ô°z½Äã¬ôý^Ç ë¨c©[ Á?±cø†áv³g½WƒÖ â´nÌièBWÛ°û­:ðK¬ªñÅ¿ä+¡¾@ÛÞSëè½ìNS ÊŸ¡^ÉþçûÍí=× ÌáŸólxF r†Â>lZ©ŽsÞC¢’…Òˆ¡Úµ‰n³CDS ¸þ%Ft‹UQQà‹¹ÍÞŸü ü)¸]1;3ë²9±ˆw‹Ô­àné…T×G¬ôØâÐ>VWfœgUdá61hñ8E­`P>‡'‡ÂáEc? ¸ß==ð’76´ˆoÞ±Xƒ-Ý|LíÇÕßy³Ñ±øšƒ´ ”Ž¥fuàf®iE2…Ÿº†¯¯YìŸ~fÅe òOøz¸êö'} [p-Usù«<ç–õQ(15ÙPÁ8# z='ü›IÒ8¨Ë A¼,ÎÇBž33Úi7"ù©«Õ´ Žä_êj&wÍ=TØh©Õ-ÒU[§ö­~¦®Úú¢]µ«o<[Wmb ËtÕn/ÜU»Å˜…»jLY¦«v |á®Ú„´,ÒU› {‘®ÚWÎíªÝbÊÂ]µ ÂéªMœžEºj‚Âã‰sUGŠ'ÿ~¿Þ³Ô®upò),Ûo•>8Š1ŸXŒñ¡Lˆ#Ÿš#‘gÜuM>|fk’lù°á Ó2%OQþ‰Å”„s=…=qžS¿±2ó6Ql9Þóf“*,_"wtu8<=òz78 ^kÈI¤˜+í l'CLb¦´ΟŚ=§G.bí˜8a{Ø‚1¸»Ñ¨Àˆ¾³¯¹¶ð7V·o Ó(Rÿ¶GÚÎêö}j) #à‡Ô­ò¿ÚR`r™ÿÙ‚ ~pØ?áŒÏ­[ TßC-ÆwÐ×z ´–FöÓÚœz ´ ]C€{ \ÂT÷ H¹D?I%Cu×çËôWac@m¨¸hv[øŽÓkÃÐ×pà4jׂú‘`°Ø>>´™Ö~íïü7V€ÁaMœ¯Á»mľc¹àø°Qîf–)¼z¬¼ ¤ ð:[`‡bãÚ<¹x ¿ãõ  ¡Ã( ŸÑÔBÁñÑmðÎfÎvºÃiÐCµ™bŠ„2®­ÒRË3åò*-P_=KÀx E¤X²åµùðÒ's]ÀçÈ-Êòì¸nûóó3Làþ¹hÙ®]üyÈ®µì½¦Ågó¥Œ:Š/^ïœS 5µ¡Ì'|„Ò)Rè›íq½=l޼jþB•SÄ ö¼}±züø°9>ݱڒ㸠Ó=U·À<­öë»óášÕ•Çïâ[b%ÌâÒÚ@rؾhñ¿Öž|Ú<úúa}{Üony Ç`(¹ó'–-D‰˜««Hòo׳·†Õ&°ƒy|^цUpÈŒ§Ã|bÇ€¢¥ç¿°;L¿‰>3eÑû2e‘`ÌØV.ƒª\[IO¬¡û|:59ÏX©Ug.^Ùw¬˜‚  @©¡¹ôÍ,3„JË€iy”ÈXõzXñ_À—LÓuØÑÜ]9­pk-’™§­“Jg·x7"•ஞПéBÄg:…oŒÄ–¸Q÷¸”¨•ð.D Î1vç$Àµ|Êâ›D¡ã…ÈkûfP+çùRÞ´Î`ŒN“´âUgXéáÿ¥øRÞ´ÌææA;Š5^6N¾Ñî™D ¨}¢øíÍ=Püóœ¦:ËçyXsV˜p*ŸžaB†+ëé OÈÀ ê(êÙ2°5¦¡Ðù­ä0ÅßLò¬a*a­±•E{ÃBã7{r}Í1¢zÞ!‚èk`Q8o{‡Ž’1Çsv¦yªÄ”r¤áYJzK2†™Ým01š\ÿÌz„qIø†”ç û­Á”µ”|¦ŸÍ˜À¤6c–{„Û#ÑCvë?0ßïðzê}@0Zþžc¡“4µ±¹ÁÝ“ew¹¹­øÍŒI’˜ØÙd΢¯ Ø;,Dê¸þ•W’ÚÀ™ÿus¬kÕ¤2{ÔIAP?qÜ@.)s5ôî=;kð® ¡/˜ãfûx €qCv×8›[v¬±–ÚÜÝ–Õ'È9ä?y¾˜-Ò±>fTèŸX¹ÁÉÐCÓk3®ET€;%Ø›yï Ù¤yc‹rŽD ú·­WÖQ&{¦`ÑË›`Û/Šqؤ‚sO:_$àß±ê÷14U‘â‹â™v_)Šrf_ƒ³¼btMõ2ßóÞ±1u?¤3ú²íÖ0½£°éKõ[+ ¨jÕûÊ̶bíb¬¡Å;¬‰ý›žèóö» ­óÏcÞ°—>ÑØÖQà÷+^„—¡ðW˜ÝÂñ¹2R„3‡z¦2]‡ÀæñŒ]ý<IJ&£Iª™ýÓшN4ÙəڔÕ`_ ÉKZŶ–¢ü;–㈱çÎŒT[_HÕaK'x7»í.˜†.ÒâœN‡vai½ÂšN‡EÓAGJ\ÞåGmNÊìJ–TŠ·÷»o–'†Â ‚õbN~QË,Çü¢(â6¼Ê‡ânIÕÈk¿x¾E­/Ÿ(—å‰U Ø;¡‹¾ØÃ$¨ÒŽÊã3&#h_•à‚Ý^3û2‰¥Kä޹¹-bZì×zKmp5Ursä鵨áT7«€§Öø?$úçÍÃ/aÕ–od|ÏÐÇÙÙ,͆!Zåhò¯§¼ˆz þ¾ájìcAÿ/¼/ØáÁQØÎìyyP pœ¡Xóö…J)¼})ÿÆkG‚åI,âÍ=sж Œæ.|ü°yÏŠ_Ø$‹˜(â߯÷^!FwIÞ¼Û5Ä|¥à°ŽÆ÷ŠêfЈˌpØ‹åÁ”# ô“Í븤¥VgòsEüàt‚aÏß”Oã>êzg&GFŠ3ë™y€6‘ìaö,©TšœÝ~³ÞÙiëƒe1ºz> >> endobj 86 0 obj << /Type /Font /Subtype /Type1 /BaseFont /RDODNJ+CMMI10 /FontDescriptor 172 0 R /Widths 174 0 R /FirstChar 33 /LastChar 33 /Encoding 175 0 R >> endobj 87 0 obj 66 endobj 88 0 obj << /Length 87 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»år¹ä RGù endstream endobj 89 0 obj << /Type /Page /Parent 59 0 R /Resources 90 0 R /Contents 88 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 90 0 obj << /ProcSet [ /PDF ] /XObject << /Fm11 91 0 R >> >> endobj 91 0 obj << /Length 92 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 93 0 R /Filter /FlateDecode >> stream xÚµ}m—ܶ‘îwüŠÞýpÏ8GBˆWú¦ØÖ®Žíd#ëîæÜUŽNk†£éõL÷¤»%Yùõ[E6Ù‰B“Ý$ÎŒdÖ P¨7€¬þºúÇêOoWž{«Vü·ûM;®”_ÕÞòÊÊÕÛ‡Õ_ ^­ÄêííêêzsûÝêíÿ¬~|»ª¸òŽ}Ñ’‹•ñ\ëz ½~À¿çÂ;_›ÕÃJrøíü÷«_¡zËÆ=°’keÃ\m>öÍ&º\c—kð›Íu†BjýWñ(%¯X7JÍ-ÏQ[Í+÷ðõ/ÿöýëWHÄÒDª\¹:"úáÍËWoS x¢”åFÅ4ÿùã›__ÿ%Ó;UKn*±ãϹïäbÔ1Áuf(F*øi)ùáõ«WoúY 0±Â˼|Tb†„k Ë"êò¯ß¿ÌŒ’ub $à¥füÔç7Ím³o¶×Í‹ †×\¶œ:c\ýåøe³ÝeØ+€YÎøžˆ!Ñ—Ão›g9]sç}ÔÐÿ $rÂKOVqÏþO®ë¹uŽ…ßÿãØçh`øÂÇm<ûŽe¾u \ôýe„úÏ}e£ï³«P(ø®Žûî Z­ß}—¥ÓšÁœ]ýGŽÒh®¥‰º¸»n‡Íöcfv¤‡õdcÎínsKt…×ñôüíy†`n˜WF‚}vú12ú~ý5#ú ñ´B…Ülrc¨5‡îû€‚]Ýæ˜ë—Öº¸O×ÇÍn›ü >Ö£~­ëÌP„ôÜ¡öH®w÷÷MÎ`£¸­†ÎµÂvln²KÌñzÄâMv(5¬—:&Ø®7÷÷k`Bná°FG„ÛœK ÂDcyØÝ4—ì¥2Q9}$ ;ÿKs¼ÛÝ23#ã×I@õãöŸ_gI¾q õi0÷9| ›/YÛŒVs h܈ølGže˜£ÎÛôJUõ;%+%#‡Ãr_ëv†»ß†AÂ/Rwúàí]“¢8ýf+îe=P´lylö›c,µc:2Xɨ¡ýzû± tɘDT–[”€fs Û`w…ŠûLðÇWõÀÂÿÎtOÐÝÆ³ˆ„åDú¯9R)€ý6äH8q"K a­â»Á[äYR`ÌuDznµ $mBª*^œ޶š´)©_“l51Vv&µÜÕd«<7¯Êq O<Ö ›´äÒæõ,Ï’‚W&5¯¹É‘0Ö*–Ü?¾Òüþ7¸Ûýöý~}³A¼ý{¤T´5§Å¿ K´’ +®]pïGr¡@нîÉ;Î÷»M "à Õ-Qû‹‡ ì™$ø»« 9üž„–×ZÇ”f ¼ßl›íÐ(SèhO·ú]†ß'1ë%¯…éhí@;f×ö}7~Z/ m¹Ò~,˜Ê ¤uƤÝs# Æjh/Š`F0Ä7“øeÚ6XÀ û .È>§ lÝÊGH‘åL]µÚ.ü~OšÀ8lö‰¤•`ÏjF$X»ä|—±¤§Dƒ·¶]”º~h2~Nm¸5ÀÖ€"ëE»šk§ìéûÎe»Ëy9¢RÎ ¿>69Ÿ ƒ;Xs»$”áueXðý í92p¦mÔ¯O‡æ†gƒ/ÇQ\ί9Ï V5ºÁ÷›C6öçVÚðûÃq¿Û~¼ÿšé†O^Èjß\ïšíÍÔ—fSQ¿ÐU‡q¼[s>ð¹Ö·D$Ù1ø[ 2’DÚwLê×ôµ‚›Œ‹ îèûÏYqS úäô}+ÀMVLpV\5pØeøŠ.ˆäÆbj ڌH²‘“áJȨ&𠮀Œ¹4¶ÆâR¯TD3g]IÙö-L^îÄÁÚE ]ß7ë}^î1_8¢:<6×›wJY\Ç´'×K¾Jåæ;þ,¤ÄcP.à{©¨‘χ¿®Á¥q§Ö÷ŸræÈC¯0ä I>Ž9ÓÒ/!>‘°ÓrÌÇÆÇÝÚ…ž K9çZÄÔwʯöÖFÌ=f§£õN•Œš¸ÝÝßïr¶ÞÔ@3ëËfûñÅÄ)c'‡Üž iq'—LTƒþýù>ÊíÄ]O«àO§TÓ¶ù„Êœ"šöù6ûÊ®šûæzªêBû뇇ufzz÷< iÝóéž³ îùÊ€[¤»È›pÎYÆ9¨·<ö FLm]s¶—uÍW#×\ÙÏ|ÕyænÜ&›í˜Ãe]_öËÛ±³l4'€o^zø,µ`´«cÚ¼[΄à…û?ÝX˜å–3LòùZ„m·nyfy[¢rŽ]eÕEQŽ[H¹å, ©!úŽ).{å‚{ãÅÿï.æÓV~)ÙÔàL<­%]÷ÝêX?í›hE\'7XÄ(ç8³ÖªdDpÁ™—àG€ö8S°³OÀ³‰[ÕæÀ¦ޞ\GÊgqš«:æAÎ`¸—"af¢á|}Ü\¯ïï¿fý }3Ñô¬³y[0.nç¦9\ï7½kD I‚Keåü ’tdíLP/i`xÌiào#K•ØS¨0Õx¦˘ño€0tð}Ž]ÜA'tÿ=»ä¡ƒ[#Ũ?` ·˜’Y¨6Ûœ´À¬·ÒüºÉ ?hQgEÄÜÖwù S€ýˆ™µÝÏë…åÇ)ÓÙ&í_?<Þ7‡½V{[Gtï”Ô¹ä4¨y jíLù9ßú)C +N£íˆÙ)s<èÄw9R&I®&ížLë:ëÅÊvK#¢ T±’æYÎ’‚M×*_fÒ9 =«Ñ ¹”KáJÅ•Q{?eÓÛ +(ÊÃ÷l6W…yu[•éÌpB‘Ž/¶ÎæÄAÌ]ÌJqÁsà“-$3ŠÊ˜É\³p®3ä´:9×ÔÖ xÕ:9×S†@4ZîOÏÎfDXrO&bb®Ëg*'ò°Ú”ô«Ë "/a‘¡ò‹ŒzL~))—h" L¶ÚÄÚ$`ü—»Í±yþ¡Y?ä@ sçb¸Ûsv/ „Gö›ì^¬4˜€ªMê³’Í‹39H_ÖŸO¶ðýæ&³‰Qq?Z2VS*nAWE”A¤ïhÇs+Q­†²kk°Ùö7¦±žÇFƒýÃe7GC0ÚõìM²ìþ´×1Iº¦©n¡F$ ÙìbÛ‹,"9d³‹Xç¢6Ö9§Ü ¡løýãn³=6ûÌH0"":îȘ}u°‘ýçl”"˜F®g¡ä››LF±Ÿ5ø‰:y$9omeÀvÀ×3éÈއP+…LØR_@G-Q§>ê\0hr߃(eÉQ½yùÃë—o_ÿåÏä²ÔžÒs[ºl ×Â2¢åÿzùŸ?þüãŸÿíí¿_¨÷²NFŒ½^³e+œÌZEÌý¸Ûgsµ–(å$WšÑka ?eåg$©Fz”M´°òh\ìjÙ2ëµpH¾å¿CDõþðõáÃî>“tê²U'J¶4]µÙê`¶ _Ñ{‡DÌ¡:u9ar!ãz€JײŽaçæ­`×zÔ¥Ky+ŒOÁr÷4CÞÊWUœ·jÿ‚Î[aQ,Ë íKy+/Ûäú™âBÞ 66náBÞ Ë9e­"’K‰+)—’QüŸ‘·RXu'Ýœ¼•Å},ÕSt{¤ÿ÷?rõ[÷nEDñ2—M€ØÍ{ÏÂï¿Ïejà'";5²¾uOB¢Û]ÖÀB\£d<î ™4,.VuÄÛK™ôû¥ˆyõ%·‘މÊ+ø~-F†é1os™‰Õ÷£¹ë35c (¹€»h>jp’æsWZp“¼Š¸KîwÉ9ׯFa+­²{žñÇúb ‡¶‹«Æ©ÐtÝáJa9zU/(;†™µû¶1o÷1¢˜³ûÌÛ} )æî>†4³vñ°ŠÓÓíÇŸžÿŒñ»ñ1,cÈëœkþŸH'Âã®%¨NÈ¡ ô_Â.zAÊî7¬ömj¬_Í„Žýo­ÃΞ"–ü\@  íjwAñæ!&·4ê΀"N÷ŽÐ¦Ýæ9?MöŽÃ&‹ç ¢úTo¸Nîà*,ÁUÔ,Ë`–§ý,WÝ>ÛŒYfÁ,ÇtËf™© +Ô&{aòò,²8îKÏò¹‹ÉY‚±~–ŠY³Ü}ßj¤™³´Î2ËìÓcr¥21Í¿D‹9‰qšfé€ÏF]šf6ZÌ1]0Íÿš™+ð´ H¶˜6pk´Éò«³K[ƒ\m%æ-˜g n£PÑ÷—æMAªÃÑŒW'=o˜•òÓdz¿<Ÿ¥ÕðxælW6Ê`:dijҼö"$½úr×D»À# °ÒD…ùç ê71Åͦa’òâtn0”Æ+H¶»=N{þ"³ÞÀù©}Ô½õö†žg+@—ŠÃÁ:Vp§û¯XÙp°0œ¿p8uæ Æ°h8ûŒØBÄWËxø „t& =½÷fßv÷Ÿi ž†­£&Â2P² ¨ËÑèùAgæŸÅ‚?XßZŸnêþÁzrl¬Âÿ´¤É[˜~caº`ÈFg“Øähí*였˜Ù85N‰wždêLÞw¬+jOt âeÙã³Ñ¡©7?¾ú9Ù/øÑVcÁ:r~¤ºß5»iX–îo-¹uMᆉÿ²|€È«ÆŠŠ1îIE¶ÙÅEl²ëWÚ1¢¿ûæ¦ÁjÑí&´‹8‚a¼ÅÝšt wëÑl~ÇkÛæ¦°­Ä~hšmC¼ƒ_P Yß%ã—Y\ô n?{ÞlXÄ\TMxÚ•@m"P6“\‡Ê©4(»úýØloŠx+1ùåIa ‚ÊeœÅ$¤€ýVÆX~5„°ß–±^€·d)Æ–­`¬€ Ö×8ž<‡öKPY¯añVÆ”ÌK'?ÁÉ0ìážÎz3KCŽý@Ùž"_0`—pU?,‹p[O3 YÕ`Ä &Ì0i”¦Å BOáF¦g™¦õXžF±¶Üôx0é~ÄÚÄ Ê,è8ý?ÈmÕn-0¿y@³v’`Ä*.]S¸Ø¥î†YEǽÓþöf}¿ûôøîêðî»ó¹îÐ`:QÇè:ˆO¯ï?6Ÿ›÷m;ÉØ…` FŠ6Üö¸¤ŠèõwKø1*¹ZJ®ÒÐXª¯„Qc­FŸyða3°ÆÙ¨3zœ• ê³æ0e²]ì Â…µO çJØ"„„9íù2ÖIë§0/ÓÀ«dÒ݈•ðEX¬D]|ljø9ãf@šˆ+S}Šûï[uÊóZ`hŒ }÷)>Ûdè3s‚»ãvŒÍòaÅ.±¾tÄsZé•ñÿ ®Œªå,Æî!v.`sgÖá]2ÙgvõÃË·/‹ÙÑn@oØÜ>ÓÀlºA¥êš`ô«7/ùq C¦W`U´™Â³D³TÁ0,v—àŸ¥;Oº}3Wr9%t¾dᤊ¶k, °mº›*ºF'ãï©!(é¹tx…[ÎM¯Á,8Ú£ÓŠS<ôX{;vÆÎ)^<Ñ+½˜¦zÛ*q)1«±,/»_Z*Ÿ½å1j@ƒSïŒd=áÌ{S=$æWÛš;¼Á+ݵð*È( p ™W /µÁ+Ø0?4¹ô‡ ’%Ý_ ×(¼Ž‚qOà0˜…w}Öí9 x›CedwñìŸsjhrÜÕ•®Úäà“ͱ 4¬ª¸ö2fí,ý:d¤ácÈôð#éZÂVmÐcón RÙ"éÒxÕ¢ „6¯Ks°]Í'%´xŒ´Hf ú–†”®ýæCSÄ^’PkùT©Àjƒ7þQì}\£§.ë¡„ÉlÐ8·&N‘4QSé]@jý uÛÐ&0§ÆÀ³nì,»ÚíË”c«ul<ìöMkÛëÑ4Å„Ãõz{x–G¦Ì„âyßàð 3˜ ÜÇc÷‡"/[Ëã9Ljoʬ®A¥ ’ûC»[y ÝÐܺ6¤À»dó"*LSж6l;ðYÜgÛ†¥¬Eë—ÏMyõÚØãT €°t™À ô;›Óß3.Æ~µ›àÎLy_€gèD´—e‡ðËrÞ9ƒ×>á}±x+‚Xœò¾È ~B%hS=Ùл4¡4gú íp—?Ö''4›Îy_d‚UE˜4(•ó¾ j!†©)Î~].vçUè` ÷wš¤Aí?NÏœÌà0íÂq£·ÉÛ©ð…ÍðX|¼ºº²ã“B§»fI씼A¹€£ô®(ð®ñ€‘ž}Å«‹g£žkËTP[Š7ÍôB*uÆ.ÆU{É|»§sL\­n‚yR“»‡’ ‹…}9¾åi½‘i÷Ê:jä‡Og©”ql Ç gÙõ1dÝ¥ÆÓÍ¡-oZ.û[yo)Ùÿðµd–Pø…¤„ÿ /} »B“•Æü…Ï2„£~‚ôž”ú_¿4Í‘ÏrÒŠÊzÇ…®Ç’ÿö®)Ñ(õ&cžúú¹¹>Î #Æ*Å@_Wl>Œ"ØÚzZR˜Íú:YÅqaøx»…3iPvuW"¦Xy«T9Ñ&¿ÏôîÇ ÅB¬g¨ÑÏÀdÉÅ/…¦0ƒòâæTÙ•4¥A?‚))R( Pµ%*R(w;dªœ…P×RÒß”$«œ‡x‘œ§g%úÄ×í±dòCs½>ŸX¢PŒÄ C)”ͱ€¥·),©PÈþY™í¹ÄûZÓ˜û¦ƒç‘ÈyÚÍJÈŒ!=^÷I©Ò È.|ã$¯ñ–â´àçSÊyKÂlûÆä®õãK¨|¼ÀÝáÕIЗ{ýk‰Ö¯!\mo¶N¢’uãàð”k •-ÊÑN‰6–b+/Q'•åµÔðÿôµDŸHÑž»!0Ö¿ÍM–5¿À[ob\;)øÁPï=ZAÞþ–Û“?75Úk55žz ¥b½-‰Vÿ w±¤¤n±8÷ÿ/¸Ki«°ÔÕME‹ú·[†·Í¢Þ?Ñ–a‹þAòë¡DøjÙÞ%A`Fž!›mÆ1ßdÒ˜l‘: ­.K@Çn\Á;]|¬²Y ð©wcHCíÍe*^*Ow”-ÚÈ;HŠkA±ô’… …½ýÞÜ”¸xR¯Ñq‡´æP¢R*‰7œÂz½`ᆦZJªfî†U4ž1¦x¼=QÅHFEðõvW‹™:JH*jiUYŠ˜þ/Q½–Æ'üü$æz½-I iÁ=>ÂdÑ«5‹5ØNa{Tö÷lxú <>|Ô‘üißb¹?+Ö4î³Çk_j òx·/±}Á 0#Û×9}¬S|*ÝÏ}Q縂¸€Ý#±DO+Å ÍÓH¡.°}àP`9ã•Í0)dæ^s§(Ù—¿ÌLˆ¶GŠH¾ÎðQ Q§»–`éöpÏÖ|¾¢QÑ•&ùZ”^……µš’×õ±(ÛVu¶*¹ÝmÿÙeÜ,èUëÉ…P’qÃ!­)Uýï!;”çÇÚ|”š<û²Þ—hkåÛ°fQ|ÎÆ– ïxÑdàV<+ɑն­æ˜¢·ûes¼+Ê‘x|À:Ùç%º€Ej[ÒŒ¸´¸(+<ú–${Íãca¦ ã@á&Èly¢0ÔÛxY:!²o‹6H˜¶à[Zý-…à ë-™œ©‹u5Þg(Ìí®¤ÎÀ᳞š£¢í&_µÏÒsÔ¬»mI_˜°‚ý—»¯¦#E/©‡IXÁf™+Üõ´8lh¼0,<#½ ,m“©dG¯wŸîoJ2u5Þ*i9=ÁÁXáÎ[=É~Þ­?Õèîhí •M¢à¦DTÛB³3ê…@xq6Èp‡™À4xt“ÌìÔr¥¸C#Í\´EÚZV\ã¶Nš»oÖ‹²Aƒ¶†å%¬¥P¤­ñŽ6Còt³½ÝíÆÌü¼=> diÉ=)YÍ­•ßXpÀ‡9‚[²ÃJ /±"Ð?”¸Æàbx|K3ÍÛOE{û’yе ¾š¢ü}Õ>0C-Û»QLÂ~A(§krµ l¾¦•b9ŸÊ6d1´íª;P6?ÝH&› ZddGï¯?A$ÛÜ”lŒ€Sã¾P;q‘›•É©Q¤1w%[¬–‹YН…›‚£)ÆŽv0x™,M (©—Ó+x^tÎD±eNŠ4&Û6ŠTvv«eËv1([èñ9 R¤æL?Kî6Ô4èf{]ä pµI­Ò<4ÛcÉÖ`[‰U‘ à°+±ºæÊHö®&Ní=W$n.œò¥ljm¸pä’Šnû`Ë3CµÚå¼+Έ‘íÇûæý~”œ®WÚÄÍåâ6ÓGsÒ)XVfspmà3•'Ìñ*¾)I?˜ Â0O~÷ø<Ö¾dƒ£ŸD4n’‰üÓ.Êl±ZZ„¢,ºèdçøKÓ<–„awMÅ€›9çêSž^¡`)Ô©ŸUN,@TÙUdko 5¯1 @Ùâñ'LŽÆ×6ÕÕ9;±,YNe-SKÎ|€ÞS‡ ª¬¢mß¾nApõ¶¬BÜxé5ü‡¢t1Þ J3`]´»QáŽ9‰Ù”„pBò ­´F bNþ„`ƒ÷úJ1îðŸ—sA•„ˆx z)˜#‹€A ð)d µ):ú!Ú’ ŒHmÌ¿%jŠ»»’º¬¯Å³*æÝîKQµÀËa¾-k5ÞÊ]Kе¥µ>¢âBØõ›ìÊᶬ¯,5ü’”™Á[% Ùn5%¦ýdaÈù?¿aº„§øÈ¸Ö&›žÖ)Ùìì<,ã«öìXª¾l®‹*S0)OT§a‹*SðÐFEöt·½.:ú‹/êõÚÀ÷è”aO›ýCÉá<©ê[ H3 (õ¡§Qä<*c¹µ> Ê®vEu)Ucg“ÓE{¦¸Á©H‰ZßßU¦`6K Ó®ÎÒ(˜@GÎýºD¡àñlO þÇ¢Àƒ@ReR·§ŠÌMI=æ[¼ðßVè©9¾qIýç𥽂Ce„à—9Ÿu>`'rÇg8^*úqß½{Ü<4EåÄøÀͨ¹ ž¸¨P­­Ò‚AŸ–ßÒ²­x @/W)‘.c„¢pãx“-LpZð‰Àß ‡™Œ %®ÃeËν›É†×Î¥»zù^8*‹/¥Ö&Fµs.5ÍXnøÀÔTGñÜKI‚W Ýß>ò'çÍÁt ¼S—}},ÚÝ͈Û;&„±‡æþkIÝ–Rp°ÕáÅr†bkéi2‹7 Rl]æg‡GÚ#ÇÔø÷…GªšÖ8ã2ÿ0Ö*J«ùÃÆàáýX¡ÉÓøòŠ%°Ùè%§pËŽ[à“ÉàÍÜ+’§›äD…\µ…PÛ¦§ ü”CéMµ×é)Zè§„¡ã~ÒÕ᎗¯E.ÓÞàœž¢ÍmQ™ªjïßKBÞ6%ñ›Ám2U§çˆ—æ¤C¾ÑÁ,zõ”^jÊJŒSxýY^<µ+ µ|Êo0ÄŒX­&÷íŠàùaÙrHä›}QÎÝÜÊNºÚsóxAk’wâY}M –îc{®UÄd…µ,íøluÊ JYRÇD{D-=øuÉéå¹WÔ$=®÷Ç :—9¤ÞUômib©öþ ÉJKYVQ) ÖÇâ,qk+´ìŠy‘i7 MÎ’»ýq½=–\aˆQ>꼤F9Õ¸ZÍ%!øŸeY%Ï…u³VýÒû‰ŒÂR¶oS…¯p–< òù|(9º.qq1qâÍ~RsÇ ¯o¼Â­QÌ… »ä†ñ¹Ûk°¬ŠlAÌRÚÓgúnCľŸ<)$æÀ›æýáêl>ƒ‚§ñ=Åã–ú;ì*ñ\ÀÿÜÛªh0Fzð¹$1õBÚZbKO›áJpçTv†[^53KM'óÜs*Õ˱jþ`V¥£^(à•¹Ä+vI¬´—à»ÕùÕ0Η¼Ê€UŸBÚ¾Áñ+ŒŠWOšs\zÞˆì8ú·rGk„•ŒbÔë㥛÷?Ë÷€ñ´Á |9=o0±³åC™4Æ‚¡È§Åâ}FîòPæ%XÈA¤›‘•({BÂGµã•3ca½ßíß/c -;|‰Xø[&wŸ²å£è« 0=ݪg\T:g¿‡lL .œ½<²îÄK·ËæèÔ ÀÊ÷ƒ›wÂæ²Æ¬ ’4jîñ°W{6ëIƒÄG±¤«ÙÅFo6‡ÇûõuÛbÒ`ËÚÅ@Tб…»ÐîŒcL¤/•ÁxÙxŸÊënÑ+ãðÐ=˸o ô ¾ æu:Ðî¡ù¸.ãÞAÁ‚ÖæeZ{‘AeÀ¬.³ÓÝQ@‰ƒ‚*óY5¾l)>ð27^{¬ º€±x÷T¥)Æò²™z‘Å‚gc¾±Èv ãáÿ¶~||’ȦaŸër‘íÞQ™³N´ž(±éþ.‚MIlö‰{´@bÓ|}ªÄVxê[Kl :þãݦìa¶“¼&A…¬¹™•0¤å5Ìž*¯g aÙY^“l˜%Œ–×Ù l¼ Or ”ি‹ü›Ék:îéü§–iX'¹s†æEòŠàÐáM‚²R=€g+ŒàkYŠkn”¥F/¹*RxjÕæ=“°ã…5[ ôk ÍÖR50xÐe,0tÕ~3^×`—òy]cß6á©* ¢rÏÓn½èØb,û©´K45JyÅPsRèìªË ª²~¡Ô“sžŸ¡0Ù<UÝY¢ Œ ÏpŸšýÖÙ<é,·^ÌMŸ+Êæ £5eóŠVáiî5J¸"‰T×`ìõlnzÒTwMN, {ÚLÏë)ƒfdØ.d$VÈIs™C]a£§di¤ÆCÒ3”îìtÛÅlÌ w^Îæzö dƒx´œbfƒAb¦È雚{›ÍE-‡™¡§IReð*â¹,þÿ‘ÎñþqTgu› ËV »uø²Ä‹vNXVânVÙ΋FK3…e‹ÓG!¨§Ð9–îlÙ{òx®·K\€É. BíÛʺh EbÖKB‡Î–'|ˆÝŽ^Ò½g|–¤;:YHㆨl¹0L`ÙB’^ÑW^èôâ‚/]FŠrÿƒ8$ÐÙ¬lJN/t¨ìb:e¶õÂäE±ˆ „-̨õªaú 2j ÿ°¹Â0SÔzaèЧ*h˪}“.dðI&˜OàoŸV"ø;'«ÌU´5$‚?!·}9—À‡!@Ïþ^ÓUUfõ^/Þ'äÏu¿ú50ø®ÂJh| Ða×ðKçkuþÃÊâ㵟+ˆkðÙÀÛ£ö´o!ôšnÂgš|÷oÛ_™ø tÒ£NTžE`éÿú¿XèµÝ endstream endobj 92 0 obj 9311 endobj 93 0 obj << /ProcSet [ /PDF /Text ] /Font << /F4.0 9 0 R /F2.0 10 0 R /F6.0 11 0 R /F12.1 94 0 R /F5.0 12 0 R /F8.0 13 0 R /F8.1 86 0 R /F7.0 14 0 R /F9.0 78 0 R /F9.1 15 0 R /F10.0 16 0 R /F1.0 18 0 R >> >> endobj 94 0 obj << /Type /Font /Subtype /Type1 /BaseFont /BNZDNJ+CMMI8 /FontDescriptor 157 0 R /Widths 158 0 R /FirstChar 33 /LastChar 34 /Encoding 159 0 R >> endobj 95 0 obj 66 endobj 96 0 obj << /Length 95 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»åq¹ä ROú endstream endobj 97 0 obj << /Type /Page /Parent 59 0 R /Resources 98 0 R /Contents 96 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 98 0 obj << /ProcSet [ /PDF ] /XObject << /Fm12 99 0 R >> >> endobj 99 0 obj << /Length 100 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 101 0 R /Filter /FlateDecode >> stream xÚµ]mo#7’þÎ_! À!2¼æ;™oÎÄIæ.3ÉÚÞ½LÀPlyF[š••ÍÌþú«êVK­«›]šÛ;¶%>,«ŠUÅ"ùÏÙßfÿœ}{3K2y3«à¿æ'¥1i’—•׳›§Ù~¯d5S³›‡Ù—ß½úþû«7_Ínþwvy#*iRœý@ªFP³è¥ónßúî ÿ.UŠ)¸ÙÓLKøéð‡ÇÙµø[Žˆ˜¤s¶KÄ—×//Ú~3-„öA£ŽéÖ{º­¤ÛÎtˆR'-ºÝ}7ôýèdÃy-OrßOJªp<œ›¡±À÷ŒqYü=¦‚ï©îœ ˜¨—7¯~~3ÔÊzéU<îåêÕåõÀHœ ² ¤tÜ-Úk‘øsQª·²2Q©#©˜¤Btz÷ÈGDñòéÝÀ]@zÃÑÌÊûåÝ•µà¶b’WÅxJd´Ò æ˜È“öF$…º9|3U8®Yç—à@L“è·®f/*Yáÿ,¶…‘ 0øaýƒS2hxHÒÛаdP4l¿ü8úð¸h58½¦J¢¼›P]Ž)˜^F‹‚•ÇüÝèjVäHMZZ p켇)J†Ÿ¢¬l 1ŸÖ›¯Ät¦*UI—tUtQY¥”“Á’µàL”RI*MNÔÇíbõ¼üWZŒ’ ÆÅf$¶K®˜Ê›d¬¥|%Û ¢E±ö÷/¯$‹»°J8´úyØ×’£*95 zý×b±ýz,Êy ¨‚!MÌ/¾j­d4-¤èÑ*BkSE ÿ¿Š EŸÊ(©y*ÅÈÀ–¸˜ä!/—Ï»¢a‘ñÆPvå?Xsä@Q¢„ÿG–èkRª2-¬@ØÇÅüþ™ejkë-„¯hÅûúµæ°ÕW`¾HBtÎa«‡0^§DaÞqŒ ξ%!߯—w‹o8æb8£îGFKÐ… Ër+6†dl‘ŠeL7x›Æ“|˜\<³L·¿8) výÀ²Ü®GŽâ,ÏÆåµt´ ºD$£d…ÞÁÛ ÇÒªÇ3*x‘·® ˜-ÛbŠünŒ_Ã1³:Dò`Ë2³&HïJ5¡t ƒØ;P‚ ¾\o–ï–«¯Yì Fº(;;_ñA’àŠÃ[²‚/µßbJ”n"z=ÈßXG”Ρ³Ç<2Ï‹ívyâupµÂÔVžÚõÇ̦ ”6& ôÅ©7_ff+L£çay18æáœ£8»Xm™ë—QMhŸ§uqÿ5/ô0(äl’*J΢@¹‡wÍ.Až±™¥¶Œ¯Q5v+Oì|Ãb+„ÊΠ W“•6’ÂzXe8y#•$î°¼ý ¼.V.Î@po‡ä€Á[Ìq©@òvµ¸[%6a¯ÄIˆi?É·–†€±’¢$xk§&/òwóÇÇ)6ä ôí*§ÕœúÝåÍåËW±V¢N†ä¾âp5)CÓïãê[Ž”&/½W-d?_ñ›<‡§*ÔäžÈ)Ë×)õÚ 5³1Pd›ANm¥ûÀ+ꀉòu©ÈõH\?¬Ÿ—Ûåz51®õÙÒ¬w¦•hT–äD/}'¦ÅkIjôþ{Ð;»\ñ 1` DgšË¢L¬vÞrë0 æ—Î.YéKÜÒ2è÷çPÅ—0Y a¼J ,1‚„‹Õ=ÏpFÆH27Kî¸;à ˜e¢å€³Ü'mð”OÚ;ßC‹}^БÒðGÂZ‹[ÁoÊçl£äì–yL ¢ûv‚+ =Ž¼Íµàp8'Èå¨nJRUäÏ;R•—V‘ =ÇCL ²`úã)oÅσH¹¤˜ânÏó(5‹>6y¼.¨ßƒÞ²X4Úеo%Ç*î4Áƒ_“\èÅÞî9ø.õCg l'?^IcÀ¥ÍÛøœ9DG<õÔ÷SsæÀŠÓ,¯¨b¥µ h>§R©èÉä%kÍAßCQbvF=M”à4@–œ_YŒM¸aHÆ.7Üjç5ü×CŒ»ÉÍH1h<Îrîp/ÎP¼e:JàyDçÅ€°ªi`ʪ8›® £b»ó<ä·œÌIko#@ÂÌõÌÓ2b™Šshz°û*kæNo4R¹Ú±Éâ”ä“»N†Ê: vqlÉ‹Ý/UE©mÊÀŠ3Ž,`ÞAŠ||ßL¦5\emœôÀI¦fô œ±ÞÔ n‚±¼ÂE,ƒªÅYÔ¬ æ„û’ÚH -;ïW9©•¦`{ª[^a‡Å¶ÖR¼åÙ βq†b.'ý'ö;ˆxD‚`?ÿ‡Ç;žüæ@ÓA{?KP'P^Oqö×s€>øú˜ÈtÍgƒÔX¢AÀžcªzâ'еÐ>Í?ñl-8øZ ‚à?Øç°| ˜À«®Ó"FMa®·ó-3ƵV* ,Ê *òµ‹1&Š«ë?y®F¸Þ’BËMªBŒ‡±Xô-o7ÑKKK@“ì¼ÒE…¦p+¦kmfWQ_ƒå l¾îC+X7$°ÇHùêe1÷(CÀõgµ¯¤MZ¦‹ŸRÅm1Ú(2Sª O­‡tÂɃs_sZt̪…ƃ¶G=v½y{M©®« 0·¬J8¬SIÑR óÕóc#µœÄA…»x†b-ÖÃIžcoeT$s_my~½ƒ`(ÐŒ‚•TÄ™ˆ $ tç ²J ±Ržd-;M+Ы ¸$M›1ŒU%}åA‡Ò´¢d]pÒÄHúË«›—?žsâÑ»€;»ŸçÄ#¬5:Šä±¬×¬tWÐ2Y4‡yØûå $Nº+M¨0ÄÍ?zÞ.žx…DZ>DFð–YÃ¥Ö°QÜp¶Ad:=ʼnÌ2&Êt×%”›¥q0žäíÃüŽwz&†ú8)ÅV±<¦“JCàœ„®-)RÚ@Œã„‡²¤àòò´†TÁR‚»]lžx‡J1ÿ‹3sÊu̼rÕ¦ªxác“„Ú±­$hà½MÒéÀ99øè¥Æó è‡åÇÅã3ÇÞâ9ŸˆûyàFº¦fÀSJ9}º ró;–±­"ˆA¤ûž—:€ ©áoÙÔ®H¡6›A’—>ˆÒá†Xž³ÌÍÜ:ùëÅÙËŸ.__¾¹am5&tBý1½c›ä¢à@¡'¹û+«ÚUî=ÅWv«øŽb,óà>.TÙ‚ÒqAí:(ØÞíÒô¬×2XŸ`^îygJ! 7…5°ýíGVV&j`+)VÜó8ànxŠx™—ñ¬R7Sié¦û¼å¯\€©¤5'Û5^6Ba)šÚžÄøŸ8L xëš÷æ2“íEW¹Yƒ)Ž,(Ë/ŽxÃnÞ·â\)ųžÚcª7K%ï¸Øh“à³<&7Í«*\­ ÐûùvÎ: ®½Tަ ïº9ΕòÄ,1÷9,¨½Ä41·ê•]·Ÿ{žP™%öý¥ÊiAÌÀ™tì÷Þ5ocVi»·%bb!2‘‹2`ê-?Qyûrx™³”Ñãåó´I@)¥Põª/x÷—Rø§ÜÒÒ]ô-`Ašgf¸ÿ¤}þÈry¢‘6ëSY&|EÉÓóâîÅ9yAc¤1ú´T‹uÎbJ…gO¨Ó×ûÌÚ ÆÔO¢~b­ÍšR¤@k‘âœII2z)¾~”¼05` S´~»¸›ÿYxWœ.TuÅ^9¿ˆ’kAµ&Qw©Á+ÿ÷–â.s«»)3¥¸Ë<àb¤ ¤"Ô‰ lÚf|×P1À½Ó<òGV¨ª›[œû˜âˆZÞ]2Éb’€äƒ4TÞ»Åj»aåÐzc)Å€(Lf.ÞœŽež¹Sü듽ãÏÌÖvMЂ!7X–ž›‰x<‰Û ,Eqñje+•a›1üâ.oƒ+ÎȯÖE¼NÇàªçÀœµÅ›ð &mˆé½­‚ûšUº© )½Ëcðï_ñ¢p؃<ÑS¶ޝ(0˜r̓n™µ›Êc&[Q°½N1éBO áóÌØè,8«¨”¦xÛlt–9 Ý[ÚüÔšÁuR ´ÝCñÅ/¿ýþ›2=îCG ¶Âpñ»æÇ?.¯®;Ï& 3¤­êº(XÛótò7WtØ;~3‡—'ºØGÅLÄíòiþnq«Êüýn7ðx z»‹Ôav™çÔÇôx0ÆUôPï@èÞ­7ŸxüP•’xv‹ ùè’w‡à…wÒºÔ¾½_>ùÏŸVwï7ëí¦´òóTsq¿‚ÿÝhw}}õÓ¦aþ ‚d‚',æOËÕ‚iè4%OQž^($þKoƒ“!¹¬µìUï€*Î\õ:BÒš‚ä½¹ºøîÕÅMß…ÓôÕB¼uê›´B“3€ëÀÇõFú¹™ß/ë‚ÙŽÕ)ò¤‰Þð Pò³ÑÞþšÿkñ¸X½Û¾?ÓÎY“d2”™;tø´^­Q¥ŸæÅ—'S6÷{ñÃúq¾Yþ»µð üù¬¡jÆÆÇÚïyµÞ<•¥P‰Ž•‘•Q³ú×íÇ]¯gªæ±ïðÓmÑ*68©&A•bé?5ÆÝ’f"DÊFö%m‡ÛËÿ\üãò§Ë7?Üü¨ÎZÒøzI[24 á­G”¢Ö[ì±=>’(²+yrƒOM¡+GâÖöqu…u±îwŸª­âË0˜ ÷.C.3P°l™4nu–^âã;ÆŒE&bš¯E\_á84É}_áö ç˜fã°¸Ãç#•3,°±Jޝª·‡e\žç8|¾Ë˜QÜíñðãY#Õ¦¾tÊXÿÚòÆÚZ~e%¦¶‡-´`$Ã*iªØÁÇʘx¶C´¦?O·’Õ9$>½j}Ï>ˆ):N îuü¬lÒ\äu¼9ÍTxC” ˜ƒ„к,1Á^`E„3ŽÒ³öÐÁçÉAàûqÎ'Jµö-ïÏb•ÇÓZztHüÄ®‡ïøÑѬþ|úc±¹]?ÜÜ ?l(´ÕÒŸ¤‹zâçbç!žÀÖÙÄ×Wƺ×o´?ËJä‰Fz`:[ŸHÓ4PÝñÅD•Oµô¡wî–=Ç×ÒÚÊ`/­zâhí [•t^Ä$Öï¶Û‹__]Ÿ¥Jø²n8Y øÉŽ]ÞëceÇLÁm}ºÿ[c~s,õûG&ö%'ß'þ;Ų3 x¿Y '«pO}ùÞÃÿhrö“ÿ+/k©ø0†¡ž!Á-õyü=õoÏŠÙ±>)™“m$žé9êk|’úߘώzZt?î9×ð·Ô‹,~‡úúó9QÞ„rªÞgFƒ9ÐÏ æ î›Ó¡ÃR¢Ð w8VþãÀºx¾ cNÏ-DFO‹ÕöÌ(P© Õ¸ùn;ëZð³´ºÂpl_«wÓÂLŒÀ²œõ-x¹Á›TB€g;l•>s Áõÿ§„€ ¹UŠ‹›‹Ûï¯.^_– ȳß À7¨z‹ò¹»)­W1‘Š…!›ùÓâLEð/e/駯çnc¡•£C¶CÇóÍfþéÜí"'AJ†ùÇr5ß|:WÑ „íVŸÈu-nŠçÖÄ$ >/»ƒž•Û’”»oÄ$À/®®.Þªó6‘ –r|-oêO럄ÁBvÌ^¼îeG°>œ·^,ß½ÏæÎŒÆWÖÝ,àÃ1¢ÔÀR¥˜‚›=Õ—T°4ìÿô8»Îà£nFEÌ8áwS¾`û_|!„]û c€)2â³Ë¢O³w6rMAž5^ ß4ÅÑŸ$œrÍð)޽Ólg __^\ÿýjï %ü/|)ŽL]f³hßBkÝ<«¹×»§ÅüùÏÍnío g,ûË9U†a` jJ² §Ù•1¦àƒÂMÍMði±}¿¾š«šKÛhL]Qsœ‚ɃŽ0>©ÕiòÃÏo^ýü\¾« ²¨?¸Îtš¡ï×ß;êgÓÞÛ60¢k|ŠÒ65y¹ÇrÝý~ß åZt›Êu“L˜+<Þߺ#)Üýâ»4MÝFn¼û‡å} Û‚’®±Æ4jé˕ǟ½’®ªDX|"Þþòã+š5bß+Ýo*5ÊDsßkÓPôzýï‹_~¹´»~!"jžWìv+ƻ͵»…~h{CSaŒO–ô=wv’Þù~¹¤·ÍDGÒ¯_^¼)‘Tì‘çL„‹õËn»&µ2©áxjo\G-N6K-¾¦ÒQ‹j° >4¡øÚÊÙ“> ægŽNšŸN›O¤??æXR2?M1Ήýüt:©Êæ‡jAÏOy‹v~z- æÇâS¹iÚütÚû§(ȤÌQãøR},™Ÿ¦Ñ”ùétS8?T z~Ê[´óÓkQ0?úªÌ´ùé´9ÝaÊÍ ˜1:ñáͺÝ/ðÙàÁnšÙåCÙÍæ asƒ6›êåsÓiÓÙ»,˜›Nùٷ(ž›á>rssÔÂ*fª/k˜0pÊ£7'T•LL…w¹ „ ât^öMN7ij šzZD§]é¬ôˆ±I)ëAædßàE%ÝMàæ™NbTUðñš8B’ÈLˆRÒ5û¥tw<#¢Û&¿Ó<Äå¦qɂѲ¹ÓÝÈ‚Ñò™jAË~y‹Vö{-hÙw ¾RãT‰¾gn’‘®©;)Ê‚ï¾/&æPºÝtãÑfOp<€0ÑÂ'Ì$M€É5™P«Ù|j“½G©ôM Ôä°KÆâ‚ •§Ð–+àꦩNÞ.ŸJÂ+cñ®ŽD!–ÇÞ¦¾ZÌP@÷xÅÁ¸6¦’± ‰”îlÕ—é£Fƒ"ÀXÛo×b¨‡µÉ¤$½>î k†Ä@v爨” ¥_TöFUßhó%¢£ð2Q[ª_¢ûý)úÕiv¢_G•}C³_¼°j’’éÔ¸Üy‰iâû®¦ìëèè$nÁ•§€t²ªâ0¦\J°êW~õ V7‘Q 'Ú%‰2OÒ“n£)ù ¼†Îû£æcù‹ÝR·kR°œVIUe2©ÙÜõ~`‡Fc×ÝìÐ|,ðo&ºM ÿªæ6¿v`ÓܬÓ(1g-1õÙÅn㱈yïvÌ4ºã óv`ûFýPS nlvÛxµ-:-F£Àý˜@ tã©”©nÓÐÄØVm§A›èMk·/Œ²R[;q4M£~`3>œN»ÂñtZŒÄûá›!LQÓ( Œª%²ÓxØ;¶6I|N‘hq(PqIÉÔ)OÙ—²ˆ¶<¥®k9*OÉ•·À«gûò˜º¤åItËcê?õÛ7u;m*wT%“KͧõOwEp ¾Žéû¥;JÊvþöOühî endstream endobj 100 0 obj 6505 endobj 101 0 obj << /ProcSet [ /PDF /Text ] /Font << /F6.0 11 0 R /F1.0 18 0 R /F4.0 9 0 R /F5.0 12 0 R /F2.0 10 0 R >> >> endobj 102 0 obj 66 endobj 103 0 obj << /Length 102 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»ås¹ä RWû endstream endobj 104 0 obj << /Type /Page /Parent 105 0 R /Resources 106 0 R /Contents 103 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 105 0 obj << /Type /Pages /Parent 222 0 R /Count 4 /Kids [ 104 0 R 112 0 R 119 0 R 126 0 R ] >> endobj 106 0 obj << /ProcSet [ /PDF ] /XObject << /Fm13 107 0 R >> >> endobj 107 0 obj << /Length 108 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 109 0 R /Filter /FlateDecode >> stream xÚµ]ms7’þŽ_ÁJª®¼u+ìàÈÖ~ %9Q6~YIÉÚ¾\±hr¤p"µ$åÄûë=œ¡È49ŒªX–ÄF¿£ü{ðÁ¿/oŽ:-™ÿoû•´T70NÓLóÁíÃà/¯Ílp{7x1™Ýýipû¯Áåí £ÂYò»GaÅÇÙ@9*¥Ù}tòß§ÌYgÔàaÀ©ÿêùóÁ§áå-©S 9•BïSðböp_  ÙɆì€Ng“#ŸàRQçÄá,9ÍÈv–’jzìÓZÒŒRxõúûó«Wð!þÈÖ|èâzøê64PÉ!4Uâð3¿\^ß\½=B0œªL°ãͱ߷œ²aŒÊ#SQ\ø¿5&#W¯^]W#’=ñð Ë?.k!!J+O2; ùæ|¸›åó˜•4[G3kIcH-hÆd}ÈÆçƒß+(ö¿é²Œ‘lðü6žc‡Á2øc᳞•š:#‹_ååÐÏÃHª¸Û2Rîùm5Ÿc¤9ðÂɵèd¼Éï—«/{ؤ-¹æ…؉6ìáû«›647p 6ã—Uùå­Q<_.GíaI v`”×"gê°£ñ³5MȤÁ# mÒ»Þ|yÌÿDby10ÂR­¥Ç&MìüßO³Ç‡|±Iá wT;&~š?æ‹éz´\D‰I5BF`‡#r„Ïùd³\ýûßy!Œsjux„Áá<<9%éÞbXÆZ !þ7e¡£^ðà ½¼»[ç›N\Ú[èŠK»è\ê`*.5† !DÜRkÿs§&ãÔ4Åõû·o®Þ¾¾¼½¼ù¿¾Æ­µ`” lˆÕr3Þ̼&Ĭ1Ó–Zõ”ؤ†}¿\Ì–ù&_E-0gÒ‹Å(§ÇAI˜dî½;‡x Ê@IK>pÏb-]”¼È¢¼—þ˜Á˜J8¸|К(ž">™{d”êzÚqˆ‚¸ÄAc¶T7íµ‚×­Òžºý}øîÝ0Î,mÕíyˆ°ºÅ°¤R7{OÝbxS©[‰N¶(NäJå@¨>ißNi´òÆÙ§+Ú*ïð™›WÅëQÒâÃ_ëô™$( '“J-,©ƒîÈ5Zg2J ·á« ÐqjȘτýOQÐ(¿Á|øgLJb¬æJµ6Ô5ƒ=Ý~÷ÃU” Uš ¦Ù$ʑֱI¼#Ý×ÀJ³qÖœÄ%GÜ‚[7¥¤³E²>ï”zŸà¾º5¨“T2/.a¢³(£/ÀIYT6²8ÃVDÐZÙ¢*pBGH;ëSfÏAP§x>‰ðR`tÚ¯6KG]3»½yûóõùe’‡ïóE¾Ï#•XR“5i.•x½|ZMò(3ï:·“Ñ4.¼ö2+4Êâ8™å JÑ´uxÍeƒ’X;À÷IJíGj¹ðA>ýÈðZz­Å¦ë×wúÅhÖ0.ß_¹ºýçÛ+ý* ®^«";õ ‘|¿žm¾Ä™g)¸Ç pœ¡å™¦ \c3K Ѓ¬=cq»Sƒ0¡Q»Ó‚6 m™î”Åì_(N•auL’`J½"ZpšÎ:/|Dt~ûözô1*àªt+ ¾YëyBj•² _òcêãO(F† ¥ “i+Ù ƒfq‚V /¥º•ônAÉѪSkžVâÛ~ú-xê¸H"{å©vÛ$²OžVŒ ÿ·©›Ã¦}èÂ[R×´ø M{F']4- ¿Ó´8/QjÚ›4-PZ'Lr+«FŽWúèȘÑ*ƒFÇŒ~ݬfo#K².;"j‘Zì#å\л‚e¡Ár…1I¬ûp‰iVw9;%~1–J\o¡Ä­¢ÆJ‰Ãð5wIâ”åKœün•˜ $w0˜Uâ04‹ó•‡A#}q¥Ä[Ð~•#4I‰Ûƒ¶Vb)c½*±²Žr.Q%~wu{þC7î’o\àôžJ{-F°{Ñbœ1 Zl Br‹‰j1%i1Ê’´¸íU‹;̾½÷ÊÒJ‹=¸’ýj±á”[[ÖËŸ.__¾¹MóÄuìž=1߇ْꉒ»L‚n(-¨àü´/&¶Ð8_\m” ýh±—†Œù,›¾Ü8A+6C †|vݱø"5–7 Ó6›·Å(¥$ªÑ"U©t\ÀW©t;¤Ò$¢U‡ï³…³%i7mXÏ® ‡J**¬ë§¹h§Í[Ð~ R;mQë?wÚÜô´ÿô¾XXÅqÐcæ 5jŸP’lËÊÖa…N¥£:¨û~»¥ƒ:¨;¶Êj{x}=ü0º¹½þùüöçëËÑOW7· Í¥ŠYXÖݱ¡ºÑ®®2Gô=¯Vã/£õfõ4Ù<­òÑ|¶ÞÐí7wmÖ$fYF•jl‡Ç›-¦ù !tÌG£¬Ý䦳‡|±Žm-´Þ(ð@§whÀÇU>ɧùâÔ6ùц éÓ ­lÛ)ú!7‰Sô¥ ž¶˜"ô ÖùflÍ?ÝÍ[FéÒm¸ *X\Bµ5‰¶BîÇ#lM¢ÆÈå"Ëâ6ÂÊ2—EíÙ2o´2‰ð–¼˜-&«|¼ž-îãz8¼Xfž%Éò+‚I…„F\‡HE OvRB&/x+vR±%1RÌ2+©³ÇŹ•T„ARAºKED„èˆ?“ÜRËu¿Ç¯Ð^Ž_5± <ŒºÉj’>°:âHÖqäÓDëÚEÛC$û^!Á¹iåˆöÆôDÛ1…ãÔiÖa®ÓÙúq>žäÅ ¯øÉ =q²Ãd÷z»wÈ,ª3\E3Þw­¬l㮃wsäX™A`àþÓFŲ²ƒaIF™Jªa ‡aYÏ5ŒŠÕíÁIÇŠŽ€“&«#šÅ1–tduÃ& i)ë|\—¯3  5ѱdVú‹:6ÙO6«5¼¹úx™Âá(kž.IõBÀ!kXÏ|¾µUëÙòçL3Ádò¢d¶˜ƒµH3Ï‹qʵh3/ø_JÿÈåÍþŸ`ÌÛ²~\ƼÏÈÝ3!‚ż¨Êò3ÕéRòÎ5ˆFG<ªÐŸ„€Ý"RçB3À„nbdžk;N™®ng%‚ ¯“u0]!xkº®ÞÜ^¾¹¹º½º¼Iá‰6T6x×-W×j4WpM5¿oÍÔb•£Í,_×Kd1Ö—KG¥sˆ9ÙìÓl1^%šI8x«š§C£Íg‹|¼Šm;/GŒ*­[Ìí~Õ˜‚û€FŸœä§/›|´\MOd>1Ã⊮Sunc}kÈ¥0³žÝ{¯g*Š{jAˆüìÓ,îª#¦¸7¶c8¾û|õMä…íÝ7öãxòù4é€B‰L~i“t@!x3ÏGùb:[Ì˨S°ƒP» M önBSèMh»‹Ô8ÕŒï_ÄæS½úElþ[õÏ î(·ªºÉ v½ºÝä¶P”K³?r0ã'h%k^åV0W°“Ý…¦V™nwº•ا+!=ñpñà‰«Ý>Ä)ÙƒÛ-°i; æ]ÃÛá±yœJõw…¯pûk’&VØá»ÕÎÎί^½¼z3¼þpöêíõëáíÙÍåùíÕÛ7gg½¬}qçSC=Ï—ÊmÎn}°ò]’Hû¨]Šêf±†¥?>Îg“¢yñ/ËÉ&ßœù&?ü5inJxm•ØõJ“åÂ'‹­ÿöÍgç/_Þ Ïÿ~yñM ©­ô1H£È°c(tkÞ嫳Ë2ý.e¦RnÃêrÐúL_o.µì,ú'¤½·³Íå{ö²0Dg7³ÿÈ é¼fÎë-ëÙ tÝ Ÿ”ÞÏT´ÿw³^²›ÊÕÅwÁü·õD¶êÃxC´ ¼vSPÛü›Âå¶êÐÞŽ“‘5ÚÆ€-bõS#”¾\z6)#°) Ù[ê¥tpY™ÄØFî):¨¼W(n›ÞP×ÁÕ7½­t˜Ey}¡¾ æ]V6žÍüã«Ï¯þ{üvòO«®Þ˜§õÜÿö·>B6퓈¬Y'_^[ýIZ3¦©1®"¢q# ¥½,“”5ãþáâõ…þ‘ÙÜ[ñöõê/›ûõú_¯¯~|ý~x{±þ¸üô“ˆ—ï'²ÁÜ’QŸäßg÷—}ÌR9 ©R§È¥ŸØEYCyÓ¿ÿµË¬¼Îš"Ô+¾ð$Õ†§½ ½¾@VÏ] Œçys´ÅTøšSU â‹.pÙú4‹í!“}ä_ÏØâs88nñ•¸"3I…ÁàyÁᜄÑcÊkÏÅàõ 1åæ÷<ßü9^T”XBµç]O„¡FZŒ'),‘ .òÃXòc—h«ŽìapwFãM¶ò‰gvÄ%Ìç³u_C׊jµC'5ôÿŠ÷d>Õ V¢òñC K¬ð™ ê~ŒwcÊú¸‡)ÌÅ‹ÙÅ;†QÅdæ—ùj±Þä³Å¯J`Ìn §¯T}aBÐ#Nísôèê‘È^Tå#L’îe<ž+‚‡A?&pž1:à÷Wæ âb=¢ÅHNððÂÊ¢ € Oj5†N^8S<UÇ. 7—YJÈŠ—ˆº‚îY’¡ÐãùòàtT×8Pú°G9Œ)›ßò¦@«C%ûcO|úä>”'(dW–À é–a,¹[%D‚pƒŠ°¡{ùïâ¥ÇÌHx!IÛ0nAE°É©«Ò[ÉŠ’¡¡&%%”PõÀeeoQ”‚-b‹IÊl‘ jF3Ž J‹Lû„­\±òøŽc©vDxìÑÞMä*ú´Lp;ÐÖÃ-Fõç†(ã¡ýç†À#uL` ù/#ÂGÇN8‚Ðü´‰·&E¡G ì˜-â ô8ÿKAhâ Õñ`ê”×>9KòûêSaÆQ *d)‘\Þ‹pg¯Có!¥$#!òFå>#Þ¸’t]É04üHLFçãMžP1† †3{Ýe‹¦=@ÍS(#u܃«Wd$Q¤‹Î·­?pˆ{P¦Œ’mÑ0àª$H"ë1•ÙÎR‘FäP~–Ú"‚Ëàx㣩E[¼ýæ ƒ¿[%Ô œÊÛ§œD‡°;hr”x¾W]O§"ضI6¤9™D —O›õlšÇש„vTòŠòº äÓû„ʃOµ­bå),±š ‹q{¶ ñг[HèÁ2¬ÎÛîÎlúvØ'R¿ÎÛrÌ›@‹—»"‘LW”Ęò¸„ó2>“ZÜ'8K`ô7U¨S„½Û4 l’Vc{V©à5F{K÷ƒìÙâÊ–lé¸oäü_ cˇ”m# ›–¡z:[¥ì©mØÆ.ïgŠOŒ3]œOAe¥x 8¡Z ¤'Fþr‘V.0âëÈŠRÚ» öõTHYYl Äì¡`À5™ ™]_rÅaSÓ@'•ÃHÈ ¤É¸Ž“žR°ö?†}Æ0ø,¡º$¬Ï$4ǘ2Ïç á>‘™-]A(ß^!ž`s… R_=Tx`r}ðìlMZôs3~Jj(¼Ýò&7LôšPQ©ȳÝTv§b¢¶%ˆ‰dš´p4$â-‡éîÐ(B‚!‘tãI3$ŠlýñôïA:d'"—?¡ô·±ç'¢àù9…°‰H¤¨ÛmKÀšt˶ŽÇè¦1²ß'0ÄÇDG$fš’îCL¤2…q$ub ÄDðš/*,XLÔv“F”›4a+°LÙŒð1‘Íf:È ÇDJtÐ!Òµi¢Œ‰j¤è¥I'^ ©±&:°ÛFi¼4BÛzü×ãEÊ^¸–”eºþ\nNØË^IµÂ(ÏÛº $Þr”9¦D[pXÓŸýF'BP“Qé#\¿–Ute‹Õ”Á-­a¶$]ú.ÃOÉWÀ rº–TΞÂ'žpl˜)rŠ0[”;F|-§èÆ(ãðš¹ÕÏG`úE \‡‚Ú•÷´dM±/~\À;; /)Ü3; žnXÀM0Ö(ó0þ’à‚à,“6ñŸRúò½njÜ"Ы„ k&¨“f<¹•”ðså}¾Å¯R’}V?E —O‹”£ > ÒSÒ6Æ5Üœ„.凔5C%(¯ÓÊe°œŒ%iÕ2 ço™k+Þ\§B3TH6øÓ5-}œåÛç9‰ ÇC¶¬8¾ŽZÓí¶ð\¯Å™“éowlw¤÷šéWU-èz°:Ðu¸JÙ³eÛbØyž°ç#O8ÃQB7X²J8"M¯RbT{u´¯ ëÌ…G€r_¾¦)¹Š¢Fy;¦ÿ*¡©LWõ8Œ5³„â\*×°#%T)*7¡<¸ÍfÞ†Iéä)¬§Ø4ÀIêµ>JܾE‹}ìuí–Žúà5Æ–´Rðþ ܘˆ°eœT)÷?ÖãË4¥_û@HbIÙ¤…Ç ¡øðz:Ïã[Káe&¸K¾D' —,­Tž)¬¥˜tå‹wm.CÁ7ËHÁ1¦Ü-W Lñù3(OâÕUÊÄfõ òN‹±$©YÉâ>F·Á”ãòBø¸ “²1&¶ƒßR. Æ”„4Úß±ƒx~ª_·bÐÌ´þl¸¨ÅÙF+rJ ’«Ìè úÄþRTƒ¶öì@àË—‡ù˜µ;ä ¾ Ô1ðPôñ#”_¿½M0,Ìï²!Øe§@¤©…›ÿ„Åd%-Ї¾­0º“§|Æ&Q1LõÉ>’¨úÄšÉAÁ†K‹Qžä­õvœŸÐÍøËZ ÓŽ9Œ-•nÆ7Pù`¥¡û-uó„±õÆ\rT¯‡ ‡aŠe‡²e˜r‡GT#{’®Ó]-pvޏ×/´˜MRŽÂÁ|N× ä›¤»Z¶ýÞé)G¦L¹ F^¥\Õ"©ÝÙ!“¦½ŠwÊ>ð”åÈãl3II”7†ÿ-¥u—y¹Æ™²˜¦´îjª9*ß)'¢½Ã„gäÚ”ßEq•pºê˜HÙà€ÛÒAˆž%äÝ ^F;& etNpØ ã'^g=’EíJdüYµÙÁÆŽËÙÖÿÀ^;Ô™ÃØ ªpEŒ–åH\šò|ªâ}Õr1;ŸëÖEgz+KÛ)JRpÈdÛÆœà}Škj¹@ Êf™p'-.`Æ8ò)å¿‚»-ð¤³Æn’õnáH—MSìÌš’=@[Ú'µÊ# DN=Ü.µ*žË S½ÎSš]¡ƒI„!ábx'OÌ)“‡üÖ;)¥ÜµYLHnÞ]]¢I/V6Ðrïwï£}ûí·ç/_}—ô ö–[šj„ú³0¿\^ß\½}“ôäMñH:FY/ȇtµ¬£ÃŒ£ÙÃø>±>^ÏÏÁ›Ï}›ôRbù®h‰}âìV!ö®hsˆB.®^½º~ÓÇ#kBÀÝïeMgww«M“ÖºšExwúõË^Ö˜Ã±ÏÆûVÕ&«/ëÍxÞöÕRD³!’º+4•Ñùõ‡›ÛáO¦—9Á£>Õá¾åv‹ýUå¶1Ğ܎nÞþ|}Þ˳\"+Î.´ɽ£•⎧¬Ã¢5Z/ŸV“œ–ÿêçZîC;Ù|å²6äö¯4WUŽOŸ˜ úš{Û¹•ãrxÁX2)Ò Yñ\ _ŸÌúËbòÛj¹Y52§NÏ$à ftc²{|LÝÜ\ÿ”ôN$J˱‰|ÊÇóÙ"Oz)ÒÀ† áÎX±¹Ñ‡ ÃûÎÙ×q½%ö×4aÍ!öMØõðâjx›i)C±OS ùõ¬ܘ×|…²Rò”¶ TÙ³!ƒ‡¤3NNŽúûøs>Ï÷›ßF‰ñF52<3-Ôéù>,K0 c8rÑÇœáhíNÏùq9¯fÿ©,¬ÿ‰ÿvÒ‹¼% žƒÎxã÷“,N¤Èm™Ïà•f¡ÛÛçÑåè}ðžÁ£Ê†´÷Ëè´m=áâè‡h;á/}L¹ô§ ^ãækùÓ¾>³ñ)þ›ïo`}øÓú(ûþt–’ãÀéÇÐi0Æ‚ûø]œiù292BFmÒ»çå«ÑÈ*ûO§,²ôq¦`8é™íE9à”‘aø´ô¾ðœ®‚°&ë#½`ðr²h8Îo“8S†0ö.„IáN”CÔ¹SaFÏ ÝË’Ã]ÚÍ%ßF3}Øyx•6S' ýè9® ýÄ,ƒ×–Ü ËÈÏ_ö1w§àV¡NSÿ}“&­[O'b3}̤̮|œ};HS™M2t¥Ÿ O…­¨ò$9â# Ÿn¯;£ü÷þa<´ÉóÁÍÁ§…¸¡MÒçZV xV~Èÿy®ái-ùü­ú籞ÁrnûKÛ/“Åã#pH¢zŽ“?ON<Ïíÿ…ºG endstream endobj 108 0 obj 7400 endobj 109 0 obj << /ProcSet [ /PDF /Text ] /Font << /F6.0 11 0 R /F1.0 18 0 R /F4.0 9 0 R /F5.0 12 0 R /F2.0 10 0 R >> >> endobj 110 0 obj 66 endobj 111 0 obj << /Length 110 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»åšp¹ä R_ü endstream endobj 112 0 obj << /Type /Page /Parent 105 0 R /Resources 113 0 R /Contents 111 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 113 0 obj << /ProcSet [ /PDF ] /XObject << /Fm14 114 0 R >> >> endobj 114 0 obj << /Length 115 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 116 0 R /Filter /FlateDecode >> stream xÚµ]Ys#7’~ǯ`„_¼Ââ>æMÓ–=Šu–è™ñÌ:´T’¹!Qm’êuï¯ß¬%² ¨B@w¸EªÉLd"óCf"úcñÓâÅ_— ‹­â êWÂ`ÎíB[…‰b‹åóâ?¿§˜,èbù°øö»ëï¿¿ùð‹åÿ,®–ˆ`nÍâ­(Ð…QX*Ù~ûî¹ü=¦ÖX-Ï †áÕÛ/ž·è'ß ŒÅRŠãA|{ûîÒñõ|1¥±æôtܬ·Àáï.˜6˜Y†ŽÙ}7ôy#11údx—N'¾Ï[Š©>g9$ |Žsé¥ï'ð9z]¦(×€x‚‡543 hh©‡€?\ñ@SMVB~Nó†H5ͳDH¾á¶Èt¼+=#ÛàB`*„?EKX`¨Ö!PØß­·x ÓmÎ —ï+å„A•¸Ô¬ö‡õî" Õ˜ 9(MˬØÞ'ä¶œ˜ÒžÆåJÚ´bÒ&ÚÃìÒ–æ¥J¦,A@ñFx(Á›ÿ@Š$,‹¢<±"8Ö†÷(#_6Í`„„\[4?ú9Ò­C˜†è¼mr4ýhaLjØÃ4ƒ“ç{ʶ!Ô¿ÔaGõª9Ó2k&ÁÍ8'à$èJH,©›†Õöñ©hàm>æ0¸Ð’Uìvð£H‘2ih¬t›í]>&d—ŒB¢NŸ„÷›ýç§õ]®¦.Œ@¾^Y šÀµVãJ°2l¢¬oZNXV¨…$žÊüËÊáØ0^k®àA&³táfÒ8ºÝµbÜyEI˱µááFõµÏ0ZöVðYÒ!‹œ¥¯—õe/Yôí,^Q\nÊ4;S± "árÃ+R±Šu®aÖýä¾kÄj¶u aÔO÷fÙšs ÿàÇ|–NZ×ðÓkl­køUBðLss®Q“E3 ÃkoÎ5J˜Õöغ†Ÿ¨g¨1©bëáùJY5t‡ç_5Z‹‰…4š:Ô­,TIlÒVšr.ck]Ã?`’ºjÄ‘¼jøÈ&¯~ͦ®yë\r?CÕV aÝ×´ê.EQO²]äq¶™dC©/ÓDÆ‘¯0RȤ…à²Õ–ã‰ëPnõ¶Î ;K¹­³ù‰ÎÔ­ó HtL/–œ½^8§@>º'ý‰³"Ô×~Úþ9‹ÈYœK©ÎZ{œG8ª(ËÒã"0V5/„´å™žhµ¢HA›ÌjuV+6g sZ‹9=ÁÃ'Äg££3ÜY”`cÎrQÔh'¬<Îtýd/–³ÂG0WrH¹hÖa1-c‘šl®ØÑÙ/‡©£z<‰uáÖ~ý„û}ÊÓwtµµò šÃIÿÀçÆ|­µÅ‘ÏŠk¤ôQMIЍ¬ÉfKŠ]ÜWµue”‚X#Æ{RЄ}ßÑvWfÖBÜìÊ4´ÑÀ®Lt‹. é¤l^2q-ºñÛÊC˜Èá"tÝWêöMêìÛ#ì`ý˜YÝ´–°ab¦ÔØé6[0ƒ]ÕLµ:lžS¶M´ÄTÒ)}[]O(€ #à=ØyJT$5†e«'Ŭq(,rÁ-åÞÚXgiø‰²¹'-7¦´öÓMÉišÍmÒ‚µú‚² "–”ü…ñ¿ãcÃ!å´R î¡ry|¨\ºCåÁ#éM+†ÚíÕAôöDûÛ¯º_çÌbqøÛ‘xä;¿‰w@L³ãñ£Îøe•¥öÅW:æí ˆ9‡€KêÐasÿ¶CùhM$‡±1PþØ!yf±ca`úJ=×,F—›ðéÒ.ÃÈ´úêœ÷.>h†@Ž~{ˆ~2ë Ñv)J™.ÇzðL}—óPËÀT™ëƒö(–s¹ÇžEàá“÷]¾Ç›ÏIb‹²Yºcç(¾ñ(Ö·5c¡#óÁ-èf+ÊGJ…®¨v¢“UÕ¶ Ygy<Ý/ ¦Žb'Jðë@ŸVÊL»‰¨ ±þÖ|j'Â/ËɾçœyvÑ’G&blšÛ‰ðßB0î(v"ü :Ûk 3.8¬ï¶½óùwÙ|»¿$™<"p™B>h i‡ÔýLz‘¯  s‚v”'Îp—zÓ‚9°Yǵsà¿ybÂò€FæÀÏàtóÍu„fjhš™Ž:›¿¡ýT'hïá8—Ô Ð´*øD'ð ‘Ë :ÔÑH•yª øo&Éè~:n†õ a”Û„ Þà’º4a²ç2‘o¼ÝëÑñoª~ýk°1<6úmRCϰǒÀxxoA Ÿ@™˜)ö¯zÑC† '{c°Ð²ð_ZR³8¹Ñ,!™}»Tõ™¼n>›¤=œÐ§À=#͵LŸ‹íý~õ²Í19Í-#þÉùRݪðoúkR,O ´ úè>“0'ök<ê(™R&IÂR¤µ ɳû7ÿÕ»M4ub:÷° c!^öÅ!vbBxë&ÆãË 'ö«w·yêÄ´œP€S ´ã—çÐW"žXè(/eª%D´ÂÇÏ eÕ-§]VÎÄB§Ã§Ä<Íbæñe»yy.]𨂇- Ï<$NY½$`$ƒ '@›¦„ûô¯H;Õ(ª#+R'’øvRˆ#YyÛT÷l•puH!8I!¢¼˜×žÅHZŸõ_ãu$;:El|¶f…b}vJä|Ö/ÇgçÔÆœÏ¶L¦1¸ÆšürŒãçxd þ«T™y2 %˜¶9ªÞRRÈKUV„à0Ío¤ûƒ× âÃ$õ49E€CNpK1“"¤˜$¤àÖbˆôÇŒ‚aqÆŠªC‰’ÍY1Â'‡wUG³â„JƇã5¡ÆŸ ã› £ËdY_°©¦)µ©eY¥r„Q*$€F†cͬÈ$ÇN°ä‹~'¥2Mi¤KÍÇ‚·¢šäX–í+1㞪‡L`Ñ¿/÷öãÏ7ï®Rì¤EšA‹m±[?¥ÕÒ$V2(Âþåuwç?ãÒ‰êÒ¡>”:· Ön;I‚GXžT™#ÆÓŽV‰$ðaB*¡)*‘Ä@L C:ÁÉysÄÓŽ× +›æÄY̤qS$©Ä²_üûáæòï×Ë_’JWÎOýNýt8?­9ô`·þ²9$…¶˜²  IASy«£¨nõÒ&I[n.Êðkæ"©§¤q§ÁÏ/œ; (|vîÜɯ”´<VRûY ¥]Q‰Â’ËÛÜsÄÖ5“®r»õvÿ4)ÀF½#QÜUÄ))x»´,Pê,¿E’ÎòýÃÏcù´“-ß?¹4‹åŸC'`ùæ\:‘rmÒI–&&a5–ý­¨3™hºÇv™ Ù;Ôd¥ç±3qäø)W³·1Ò€Ã=FãVZ×`Ä­B?Þê&¯çÂÔ–[XCãž­]>jNžG'”I!B:Ióܦø)Ê'(Ú¼:iQÁ¬úÍhG½>Öñ†É™×ñ€(9×ñ7ÞçÀ¤ÒTðK±ú% *ø‰Ó,¨àŸd’üã΃ ´“Qá :iQAÃOÅ΃ ŠceåûÏ2ÔŒÎR?w°à—Å, Ù°Ð²8,ø¥îÅŒ†?ñ<Á‚†ó ãN†…sèÄÁ‚_'y`AJ¬™<,€½èþYÖæÉ0«›Ë,˜Ps9w´à—%k´Ð²8,ø¥>.¾Üë\¬ÇÍß;u1|Ò¶@ëb~Ú4E'­‹qƒµÉ«WïÓN×IÓ†04šÚ=!˜Å†±®JZd¸ü.©ûÌ!CË(2 égɺ\ÐHuaRÍ®A¿ N]Ië—C?‹DŒv…ª†zÞ`_šª)$0rš£S @;qU¯z΢’¦[`hØ©­U‚Qld^•¸^„²1ÙÒÈËû£ë™u/BC{Âþhê)þ> Ô>­nu»¼ùùÝò盫Õ×·Ëg¸ØJs š3ÜHlî7¢W?Üv¯w‡×]±zÚìoODÌВµƾó>¾›í}ñgŽó\Ldÿô¾—ëýæ¹ØîGBËØc8\Ö—lDqþ¼+îŠûb{Wdð™2+4ð>ä"*eœÐÕ% ûâzQC}”PFM¯ø:ðTɉ74 ².I\C8¢l8)ïSÉ‘N”“”€ Fª(;0úê ëýfû˜•O³ä=&§Ï#]Ý~º¾¹ü1i– SÁ:Ë3Ú9ïœiXx½ ³Z­r8äÄëçÙN2«0g< ÏŽîi %Ãá-f4æ2nÍ(ßDí2€Ï3QxWWÐäл‚”‘‰ z?¹…&‡âÁbšâ·¯OëÝêóæp÷{õKŠ…¥ô¿[ßoÖOÍ2,lL0,Y¯P8úFŽt6Œ†*{)`HB'í*žª}•†$ÈÒ  ßÖ2)›®OÔ‚st}°² Í"Þ‚&úkkAFUzNy,È/NÚ,7uŸmªav’±¦S¹¡Ÿ·Õ¯9ßûd2G5)@?K‘€Q‰Sg)4´ÏY$è³8*´~vý¯«!*# +yžk´¿§EŠb«¸£Þå5,¡i$Ü9µÀð?oþ,žöI$ªdGzT½Þ)Ç_×A³Ððë5&e…¯Ð͆èÿö5í:€úìÈñÎõkT’´îîº^üósŽ0Z•å^ŸšmO5´»Vÿ"É⥮®G üqó¥H.L"ŸŠVV}Íܽ¬wûwÇ Ì`[=éÐ;þp©M¿£Ë£‰z~/vEÚ¡8g›梿~…õ:±2KµÅZ2œâ©yxçæÿŠ·zp†ì’–Ú³¡ìò„m]Îáå°•+Gð,ÿÊ‘½Q ‚¢ç+K6 ÎP– Q–¤¸PYL€ÃÊÁÌY‚¾†ö9ƒ¾>‹£ ïúÃòêÃíõòúê6GÌG™„ŠMÆ€hÏ åÞh¨r_^»pyØû¼@ &ý²=\Ûl×»¯™JjÖbâ¹LºÏõi³-Ö»òÈ^amyC¿Šõq½É²c(¦1R–üVÅ>ÏuÙ S%"„|ùRìž^ÖYæSqL­Žô’˜ÓûÕ—õÓk|—å½Eg„÷šþÐÝO¸¶ø¤JÑÍ} >ÅБZD\\Ç£'˜%Üñ]/q&Ê/§ÝhW—)ýªñ&I[ÛyàBõl÷À…ò =p¡}`,Xš/ÆžbØP=ÆÂÖª_–ûN†—ÊIco³~tÁÍOÿ‰%ƒ endstream endobj 115 0 obj 5025 endobj 116 0 obj << /ProcSet [ /PDF /Text ] /Font << /F2.0 10 0 R /F1.0 18 0 R /F4.0 9 0 R >> >> endobj 117 0 obj 66 endobj 118 0 obj << /Length 117 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»åšr¹ä Rgý endstream endobj 119 0 obj << /Type /Page /Parent 105 0 R /Resources 120 0 R /Contents 118 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 120 0 obj << /ProcSet [ /PDF ] /XObject << /Fm15 121 0 R >> >> endobj 121 0 obj << /Length 122 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 123 0 R /Filter /FlateDecode >> stream xÚÅ}[—·‘æ;~E¯çEš%1‰;`?P·=œYÙkŠÞ±g5‡§ÔlÖ¸»šªª¦¤ùõ‘UY•DV&€’<çŒh™õedd ˆ/ðãÍ_n~¼ùâíMàÁª› þïð'í¹RáÆË++oÞ>ÞüË7‚W7âæíû›Ïn×ï?¿yû_7_¿½©¸ žý(¢ù¹¸1kíN?½}ÄÏEðÁ™›ÇÉáOçñpóÈðÅ[6”ÀJ®•íJðÙúñ¾}lDd‡";Öý¿[ßNüBjÃCPý·”¼b‡·ÔÜò©_[Í+Ù—ðõ·ÿëË×ßàXüGª\y×ûÑWo^}ó6ö £N”²Ü¨þoþï×o¾{ýç 锓ÜTª§Ž?Mý}/¹&¸žx Ó8OÙÈW¯¿ùæMûDÖ1¥¹¯Ì´}Tb†…€N¸ º'òw_¾:½eç™Öp#Ú¿Èf?rôÎÆz®Ãé>òÕß^7~d»€|à•÷ã·´ŠWBŸþ;}¥ê˜Dó÷Yç—ð®VùîO?»]íëû§í/ßu(*Ë…ËëüìÕ›7¯þþî»·oþúåÛ¿¾ùzâ×­¸øÅ¬jüðôôñÝŒŸ°Çàšç½[m·«_ÞíöÛçÛýó¶æë»ÏÙEí8|ãèïëÍíÓÝzsÿnÿËÇz”òÜZǺ}zü¸­w»õÓf.œ Ü‚ÙEá~øe_¿{ÚÞÕÛ9@wJœ¿‰˜øþ`ºÊßûÑïvëûM}7õù¥äÞ Öý•’/Xï§~dÀûÙ{Ôz¦Vo7ñVDôBô~öquû±€×’"pQõŸõ°ÞO‰'•á^©Þ;=ÔïêÍÝzµ™øý¤«$ø©Ã×û§©o¤¹tà+ºŸZo¬»Þªÿ³ÃzûêÕÛW´tì Þíà=/­´ã/¼Þ:(õ7A(up/_Bôðò‹×zõæï/¿ùó›o_½}ùÝ×_¾}ýç?½|yY) vߣ„_>ÁêÙì_¾ÿòû³´l´‚„† Mö~»úøña †þé_žn÷õþ%8›zõø‡ ÍB´a5( ?ØãÁtŸ6Ÿê-z¹Ý÷óË/¿øæÝÿyõå¿}ýÕï.ëD(.”é¿ÉvµÙ½¯·/¿>ºâßO9Ø»<„™] /^}÷µÕ éøìJsøyó“¿½ü¢1É—ß­ÿ»«Æ‘‘þÞÙÞ•¯„’ú¢©˜`¸¬±Ä鯿úý”»vW®ýéÙ&'µj¼åRÙþ›}ýP?ö …Myè>¹°³ƒ6ÜBŒÜýÕÅÍ@‚MáX÷G§Íà¢6ãÒ†žé|û•™4–V›ŸVîá?¾ùôÍÿ\ýùöß½yý'÷¼{ð¯þøÇ‹‹Ð@úiÈÁ·¼úâÍ«Yÿ™€=ì=¡Ì9ŸPúQ Tû·ÿþÕ·_Ùþ/÷^ýùÛí¿ìïw»ÿúöõ¿~û·Wo¿ÚýÇÓÿ;T¯¾þÛ­þ·õý×—ßQ‚Ó8:‹I—5ÃiÞÑcüaF+ø6ÁÀ^5ŠƒM76Ý8˜Š£ØÔ¥8|ô{pÎð+>»I ´5ìÀŸN¨dCÇ=ínýþývónw»Úà–Ô¾V —õpoθBA˜ÙM¸¸7ÑGë'†mË5ÿ[ó ;§‡ £{Îy¿ÿlJX3p07ÖÃ4'Qÿ¼|||yww›°Uå›Ðw(ïûûÏG˜,úÑ¢å ¸'=}ûá“_0…AÉÂrÿû– `ÁêYÚà2p¢Æƒƒ"Ä]mæ)v(.ÁÜ@àHÀî×}qÙL54D”Q\öÙÓû%ÀzPB\J¹ûiº` X®"”P§êòW ~…€é€ÍÓƒÑkJ³‰:¸W)Òn7¶ øX«‘~ùŠÔŸž¦£Æ=ÑiEZÏe‹!‚`¼"X‹»Þ%)Xº "ÃyW¿Ì‡eXÈM‚“”~HS.–(ƒžð6'T¶@­Çõ·Ö 5[ïÀÛ$»GˆF„A彯7õ ï’”!¤åXf#Àïž·‰$Ùš0E{Ei$y-Ã^¤c„À¸–_$›’È àê÷OÛ˜Èìòꢉ¿ ä}ân ©Wæôé†^íã¶¾]ï)™KÿŽkIšÜhçœí×¼‡¿(Üή±déÉ‘¤s¥-í°¢™ƒs•MÙ8cfû¦ˆ‡HÅ:\ÅVR¨],Ñl…:áG°ì¼ØÒ1d=Þ:J·Kv¡î –øWHÕþcó”æ"•n"tö§Nì0¥ÛQÞkàŸÆÞh™Ÿ§üç¨Ûÿ×ɱþs¦:z kw$ ™¡²ÃüªhG<£~·Û¯¶û¶ê’Åõ€ eq=ÌÂYÜPÞ2YDƒÊ‹‚Yœ’R¶°%³8-„¢ÄÍÉâ ¤`³²8¶ÃÍÊâš &®Üô,ÌL“JØNêÖø+ž‚ÝîÓ²8ˆŒ·¥5‹ýÎ×lP¼Ò’ÔìåÜMùwˆJ¤‚Xjäûþ-÷ï'ï °Â‡‚3Ò¿¿ß®æo!,âßOÏè½Ãcýn}÷. ±ËÞb‹ÿìAw<æg³t2ÄTÜbDÜUÉÙÃß>ÝÕË÷ vò턤ŸÏZz¬Í6ÿãáOZq»ôŸ³ö Hp+c‹íŽÛ ú;\xŸ’–“(ª§d]=<×I ’8'p9ÇqSëR•æÎšeéu܃‚•”j;§½K· Õ„!„Öûú1±ê9½¤qw‰U?ȉ´§µ›^õg*w}WoöëïAMõ6­:¥ðèFÌ6µ™)2|ºŠVqj&' ¸Ì‘°Ç€úaµÛ'Vþ°)I0B\Øxë$íª |yEjw½IÒîÑCª€®”r-Ä|Aé,K®/ÿ„ÄbBÞ·R3åÊrç$¥‡Kþa¢šˆ'Ì–ÄÝ%©W( ° Ô»Jó¸M©öãžÈÏr lìÏ4meO á6è¡åŽ£=Ü1Þ5‹®Ó¸lA{ˆv´iÄ­;rC:”è윅7?én³l凘½þÜéÔ° Íú>jGÑ a©LË"ëÉÙib[• £—žj~‰a¼PFxÆ,™R’fe„hVF¨4ÄíB̵s'Øb¡§FÉš“jƒ&ÇÍȵ P!gI‹I*p ŽRkb’ÉšB§Ñ”f%™ÑdPKX¤q‚ÈÙ…Yä™@©65Õ† LÍ \ù°‚O&I%ÌL2étPîp›¿h½‹²A-š3§!j扩4Ž'!,ªa;/Ïd±<ÓIrÇòÌy ¹Í3)kÛdœß(…>½X/×)Ï<À¦×ª‰<“î噋2·6Ïà²u¨‰<“ò¦fÅmžG]¥¥Ä‡<“íä™,Å¥5yæ š]È3oææ™}Í^Ê3S[Aš<“ø„›ŒVKÜÜ…Ë3™Â¶Ï`fä™S°l˜gvQgæol:Ï$äìç™l®A´yfLN6/ϼ!òÌ$›•gÎiÇ<å™q Ü®Û1Oyf·“g.l‘kóÌ.[gR玬aè9i楰/žfV7ÒL¶•`š™r²yJ3Ï`£4s—´ÉY‹7}Á{éeJÛDCe˜Ž›w€ë% ¤ Ÿ'ålÇφn׸áVñ65 9¶’œP—ç£HÏa½_[3š²y­l°;âè¤|" ÈâZÝ'glÂqÁn\Öô„ â›@¡Fb±™™0ý JqØ]šbÁ² I!›˜¬yø\e›çÇ.Uü‰ø¹átí`ªÄ07–R7ýé1PvÈx»õq;“š_l“vj‘3G-Û _ŒŽ› ,å`º [´I¶ÞÐyìmn¼sÝa„~¤lÛÆúõöq½¿Ð©OÖ}8¯ðíjs?/ŽÍ³°ÊÄg×[ƤS<Çö-êawç8$”!›;R"I±ÈmÖ¸átAý ôŬžÿñ”Áò}P°å#èÿ˜åÇ cšNètFÝ9ªT%›‘=„RóN;z W8íÖC¨¨&O;Öw‹ÂEÖ;è=`n¸È¦O#z˜Äi›NµñâXR¶À*ˆÓˆ#(»x1gÿm¿™AÞ»F¤„5ÈJUÂS°Ÿ’¢ˆB…Õ2ÊæFa¨²ò¤¶¨iˆ<  «¯'+‘’%Vk°EËV’ÒñófýãsýðKR ƒ§Ê©6#Jèie=i$—iõêöCblr[ v~l2®aîÁà YV®ÖV±p&œóÌuñx ÙWVÜPøi­ Š 1ÁŒ¡²Ïžwõ]" K½¦Åe—[tæ´áÔGé`¿®ó¶ÀU U»ºOd@˜ÃÜ=B¹³o“ÚŒ¤t»zxHLÞŽ‘¡…ÄÝC‚ó´$êzóþiûØŒ J$\‹¦=„o[×~xzNí»4ÈÖ·ûõ§:Éj¥ôx¶·Ú۹ǡv%N²”»Ú®ëÝb­{”°Øì‘ d£ü»ÕÏëoþ4³Áw<èLqiTû°áöü"I5í Éu%'_àpjܾAÒr42>ßÚ9áÍ:6kAYÖ¹ÙÄ-4ûàÝt’¶ÙÏ%" ΰ‰Å©ÑCŽáÆý¶‰dÞ]šß@ž aM«¾èmÜr,,%¯û˜¦Û1äžV9‡h”°Y‡hØôUµŽå úêãÇíÓϋ缰ói’‚¯¨;ð%úO*®0P Ÿf­Àqú$!ÂÐÃŽ¸]Ý'r¶°ÇFH;ÛpG­=¸º¥¥´È&B¢³”ŽBÝÕ·O›»]ZQwG%(SKLP¥ÀdGÑjØ'&QÒ6™ÀE¿S'š„*MÚ…Ú ‹³< ¼§¾Ü¾þ˜8± <„ ‘Ê lºšHÔTÚZëÍ\hêoÅXkX; ñ8¥Ù £[TŒS9 XzÞ›ÑOXqìc  ·“tŒ £ ¶ÅÆZi¥sØæ q“—1ÎÖ²7¸Çð!­1›YŒ¦Œ-q&ú3#eiËÜCÚ+›ùW”©­¶ûõíóÃj›TÔı´:ŽÎ:Ÿž›ÇÔ2jmÏiß6¸Ç™ÓB,œÂG¶ùàYy(RI]>NãÕ $ì§õ]F‹¬CW,¡gbÐ)`I°ž¤z*ejFDÇ"øEëÐ9pc±%Ù߸—Wq+#´žXŠôŽ;oÈO™¸“JÔQ ušsS–K)®ßçœ×4íUÆÜäTÑYoÙ¹€²ÆaÑ÷ì’4 & ñîøÃ*mÄÑ—j„Ê2˜f7¢ví¥ÚÄ £™Œ/©÷Om€Âæ?ñ½Î´—…­ÇÈ ’R쬂’,Gгˆ°¨\‚׌xWï_ÎÇe#À®´Gá›û]’G°C(ŽÛ+:²Ù:ððêNÊ1hãV?')ÏAᓱ¸¤õ.I«ø•“®>O¸YÿŠ@í×FÙR=LqFØ#‰OÒ/&z^ B¿Ýì>&iX–ã­$tQß:j§æãN¬5å¹´”žÁÎXʆ8Ô@Dwe©vÖõÆsk<%é¶NóŽÙ”nW»Ýóc}—´‚Þv¡ÊÛ^Ÿ’ ÌBDgý“-©‘Ózu˜Ž)4°ŸÊ"…:£ëcóVl¾ s‰(î×Û§$ƒÅœ4tuÀFã3fº„Ñõ°+8 åýrN¬Àâ—Üê ¯‡ÂŽB6OX¼ü=(—–}v¿}zþØ4¤þ>EM‰FjÖ×hüöáy·þT¿k3ýF?F¬ijƒ'“à<[*ÿñSB®-F=Ö_Îúˆ/Éú¨Kb¾X‰©ýQÔÌÚG•;É•Æ+cu’¹AŒ£4^:†dŸý’ai!àÕÊ]ê}Ž)Z'ˆ­5¶èèËÂÿG´TïèQ7tž‹(l\â¨oq.)4…—QG´E…Ánfªã*Môþ)¸ôæÆ9ßÞ^=ùÆ´R;ÏbùRî…ï<«§]¾ÚÜ?ÔïÀql›ËwiÇ?~­~¦hðÞeçÚ±=‡4;A›¦Ãª÷—Z{ølZt°pÔÉd3E8¶ï £&ÞÉó½;{lVV'ôqy¦ý®dX;ã ‚àýáàlFrriÜo*O½ÁtcHÌþg³ X$|¯ƒƒ-ÿºx‹“9óى‰~j3ÕïH dßO›»$:–„$5óñœ±äÏÛÜv,Œ§Ì¶{£ªØ…*'ì?GC|7w†à xª_0Æ5³3 ÅÜoëz*Zž¡ˆÃC”ô¯³Tsòjxu¶‘ñ›.^äX޲xËcû„ñ`Æ<ÃÁÑÈ›#^à§õTׯ ý°KGêg…Ÿ7G9ZVͼkB;?­÷–î·çqwZŽþ¾+ûT¿Ó1,K$FºÄ$‡z9žãRO†«5XײŽ×ŸI¤è»çǬYŸ -ú’‰3„‡àG¢çn6•ƒˆœTû§OªO©@d¹ ­ Ôž’}ZíÓ‘§6ØŽúÐ3—Z–%µ«@ÁÃÔhêí䀗¼†¤ØuÄþ ܇Ñ×^Qo—qàŒ Ü8º¯Wlìë†B%=¿,òá%Nò ô÷I/ÌF –‡Ìùˆ9sÚÇYÞl¾ Í\¸ñX¢ ìmÚ° `„øûù©‹º)ÕÄaú(f ½ ²‡"éž].AÏHÒLÅmÐ7™š¡r44zE¢÷o-d‹·‡Pq绊a™»f§=ÂT8&Q/ÔÜaGo:?sÜ$„yæüQÙIНÄñ"ž6›IŽà‚$!lìÔ4ÇU"¡-ÈÍçxΈB±M¶"%¿_g©Å®Š%À³b-…]šÒIe-XgRŠþœ µ"góÀZ¨Ð!ò€fóxµy`ÒäaÒçnö0¾˜@_oîÖY›VXƒÁ³ç9kûÀ›{qŽz\úÕCÎîapF¹Ÿ´šœ zIWé>›In™±{@Øû6­— ™ËÅ Ä©I/oŸ¡ç¸SŠtSns W°’hÿõ¢È–Q‰óñfo•n²ö )¦¢x–îâ)ºhê2qÙ?eéÅ[®ÑZâØÍÅœr•Àɤ^–Å`ýÃ! ™’¢/ùäña¹D³µ&šFc¶°ˆxñ{دdhá—Ð9g|q‡ÌdKoëÛz—÷Ññ¾ž³øCílö_fÕe¤€]ESoµ0TÀ)vVå_몹¼†ÐK^O›A”¤Ï-ãòš´Èz³«È+MXS8Qÿ*Ú1Ók#®b2Æ(.ëŒPI¡§èjÅ”91Ê7×áõ/Wº0’{å)ôÇzµùþs¾Äb†MC'›µ`9£Õðïêí¢XkØü¥4bõ~tÅÓåŒD7þࣣ؋òó´M+K\+Ó³°g(ŸqÁ×»,¥àX¥”CE$Y+gU)B+Ÿ«¤3³¹&R¸¸ØõæEŽN4^ZTQàÇ%šª-—*)S5m/¶¬H ¥§Ì±¢y•¥H°Œ× ÈnxŽjŒ€zÑ>οmÂÿ\VÕ‰·`ZøÕ¯Ô‚y~V¬óÀÚÏn¿<>äí—=ù¯Ð~ÙÃ/Ý~i‘Õ}…öKÃՂϹègaŽû– þûíÓc^‚ŽC*¥›Ìj•ðu=©œæîùØið‚ÎTtÔθÑ#XK9Ù­“ް:%Zí±ŠþÓ žÃddsO¡š¸’³qL㟷ÎÊp$±0äÇý8ƒP7ã ¬jº!ˆï›Ô<Ú9–0^s£Ií¯79Ç'ǃQиð®Î9ÓV¼-:à,¯yté·Òã‘Ù¸çébzu1ÚoÓ«8þ!¿J÷Ûüê^6Þo¬¸à—2¬‹zi3¬8üz——S¬¸^î×YÓæXqɳÂýS’ÇÆ,+'¬m³¬¸Znƒ£€¿M³ƒ!ó,6[þ6Ï=¥šû0Ñb‰æ><Ö&3­)só[ç¤qÇTkÎæåZàÙ)×êÂ’­û™lÅUÓ϶Øò/{ʶNølfº•¶axðÏè–µD¶Õ<ŠÉÖn¿Ý7•ë%oEd\wšH¸Ø’\î˜puÏ—˜ÌÈ·&áÙ)ߊ þy‘¨§K=Ý^¿<ì]£ÊOèlÛmQÚ"›ÛP‰7X½ß×Y!¿Ö•»@á7|·œœl' íàÙ¢qé3ŽR*Ã-)|n6¤üK¡ãFœsÄd,÷žTÌDƲ O«µƒO¶x“/ö—@Â2Dg‹"RÎA â(Ñï²Z|›èBr¼—°°4B”ä2´ølÙí¢KÐ’;°(á[²[N%õõeóš·‘în%þ‡¥ÕÍq•òè½–Æåð]£dc]eRúiÝtaóä ¼„Ã-;Vï„(YÝ7Ö·"¥Ò ©°ê¿]1&Æ@6è¹LºöËàºp“‰2`S¸Þà…OÖNpGÅÄÑóº»=ÄW8%®–|&]Ó,á(Ùó˜t a[úW`ҵͪ„Ê^ä7ålýö¿MSŽƒ '´e bkK0>ííÊøÆ“‚5ö¨”e *ììáˆ]ÚXÃ¥–øjsŸÇðÀʬ'´òœÉlzB¥—A$ëú“øÃyHyü@m`Oò–%}Ô8'n–kAi&zÔ±ä$¥‚ÔJ¹1:Ë&6•$ÂuÔb”ㆴõæqI¡%vÂ$³,nàéx \¤±yz¹PhÁ6>éÄäÅR,…ü¾ØwÐYaj åààBþ\j N²ÚSð™Ô@ˆ‘YýôÁ¹v¼r¤ì›<ÅË•RøÏû¬Îv‡7²’zés±’ªOªÑO¿­â”6?]ÒˆÈX:Ù«ÓØ^ p qáó¼$Þ£-¹šž²öã`Kk¥aÏ>ÒUÍ}1„à3$©Ò„óÔ üSN%óR¥”:¯×:wéš]ÉëˆÑ£•Dc’QüUák}H„8£÷6݇§ç‡»¼4Rr…Áu\üúÇçÕCþL–ú¯8“Ã)e–Ý@9oP ºEw¥=²ÍLø²®…qBRÁwP”^6uî0c%ùÏû¼!`š{,ÆÁ„ö¬8Ä73äÕ¼~Ÿ[õÁÒ“‡XÁ½W¤É ¡=ëÌq¡,¥$´¯òB0m'¿mÞìÁŠË@ÚNV™ÏhÓœ¯ÊÉ.ó!í|JîôšðvN`#í¼D%/®•%¦Îáñ)x…(í<ÓÿúJMÀçÃëœC‹žÕN7RŒÇÑyÂ–Ç :à‰Ñqañ¼‰çCøYÄó‹Áç‘xN€·Äóœ³à#ñüø„«ω7(B<'° Ï%¥—2ÄsBðBÄsJ-‰çWÑNK<¿†É´Äs»ñ¼ˆbâg\¡ýmNÈUCE(Í<‡X}]÷ýJ1ϬfCAçÏ]s?_O)¥ˆçx½ÞÑм ñÜï§À òαÖiÄõˆçGüë0Ï ð"ÔsB1¥¸ç„èeÈçxö9¡˜"ôsBðBüs}a^AÐ)ƒ)Ç@Ÿ2÷\ :]ŠƒN(§ ½ ½_ž†N¨¦½'þ fK¡+œ¶«¸ª.§‘%ˆèÇgDôÙz6½÷Be‰è=ù¯@Dïá—&¢c£š7ŠeÑ—Ö·è× [7Azüˆ’dk¡¹4ÔKd² °X®Œ£Ð3‹dH먤¢>ï.ë Ì…@I^†k­=ÔçÍåZë€>HQïǵÆb¼«HÃÉãZãh2¼î ~%®5–gÔø>Îb\k¿ ×ú~®5!x)®5_†kMè¥ ×š¼ךÀ.ĵ&ÔRˆkML9®õø å¸Ö‰æ>—k=iî¹\ë!xa®u¾<ךPM1®õÿWàZk%¸¸PS-E¶>>k̶>^Õº µm˜M´ê¿Ì…l‚ÍMT47Íé´9µŠß>ÝÕÉë6•`”ÜŸ/Q ƶù;‡?Áb‚•,)¥üsÖ;­õø§öϧd)7ý,ÅyËbàËœ'c²nâЫ,•X½J*YXÖgU‡úq¹­°ULKMè$zƒ"[6=ÌË1x³Þ­öY}¡x¿¡–Ž}½¯³.ÒHÖ¢Àó®a2wa„ÍÒ;ûZ±þé)ÁïêÍþ f%Ó<u3e’,ƒ+"ñ´Á%æ5ó!§Ìj{“²–.÷cR4½–òî‚Eœô„VV?g)ň9(Á3ïAGÌtë5Ù³ÊsiK“,‚‹hÁGõ2Žòz` Ÿµ„”u;ì½d¶ ;d+JðŸ>¬o?äñr W4þ‘˜Õ®€ @,HÄÕ³Úæqs –ù,%ÿuœ¾¸àRnˆpk"ôs®õñÜqûÂiJIß>?ì×ò()Æ4ŒCâM"NmÑ`HX_alFlŽW»ÌIÁkÂ$%ùãê—Ä=W•šì­[N½€ÀF‡6KžqCõÌcç#ñ™ezlšGÖ$ž[¦¯¯ÂIC£2}&AM+Ù áó:•ã¢" 'ûŠ&ÈrL¥(Íd]Ñ;–­Ÿ4^‘àƒb[~Y^!H,žå´n«„þßæÎÑØoø#à{)OÊoš’ñžeN;èœÛ|š·«›%We^ôXqÅÇþø„Tç¼9ò{q’ž]&OÎïoDŠ(¦cùM7ãt}ìr‹;<©’”~k,ƒ`$´&Uó¡NŸ‚ü"¬G‚¿úÛëïòFª!hð·«¼Ës5n‚žÔÌýSÞˆ—)mõ<ç„§­Fc#¾òsú[2*Ä'׀døªý-¡}Ö¨¿ån½ûø°ºmæâ¤Mȉ·ºôÞ­l«KïU®ÐêÒÃ/Ýê¢ Y’"ou±Ü«|ì蘒lÙ,'Íè,ŠÛ­âU²!#oÐLÍ)nJ°Êà)øÞP–F"ñ•èÀ³\šr·ÕÅh® „Ï&úIÕ´ùQÖÆù‹;ëgtëÂ]ë‰ÖzKtÎ…ó˜ñ’k+S ›‹„b×ëÇz¿]ÐMâ.¹²¢S@ŸŒ)ˆ[¤‘C@—Ðî¬ä¸çG@×,¢Ý¡øø€0¸¼î,ì„#ݰœ)ƒÓ ¡há÷ÒÇxc×EÓ$u†¾L@Ê$†ÄËœh5XtNçÉp•€ÔOÔ‰Û±EGÏÔÙÄ'²E/<¨ƒ,«)ѳuBTª$…ž7¨‹dgÉËê„Á(ò£f ê” =ô¡—­¸SV¸¥UÑ™–8øµñ‚ìßΙŠ=šzÉÌÑ–­«ÃÁbáU£m£Ê8øjsßL Ì1Ñ·ñíØì” òdõyçÐX‘‘ÚOi?«‹Ýð %¥œ¼“hŸ y+%z^èŠ5fSIÒpòæÚùŠËÊPjÉ÷\ÓÞOˆ^o²êƒ8Ä×y;mé1ýáfíë(¦œéHÅôf\¦hÆb×§¦àÛ!—6ðT}T º4äòò q 6ZøÒq6p«,…¾Ê2Œc·ÅܯóF‹âüLA þ)ïtRðP) »Î«¶CvÝ´„VŽó²Ž'q^˜¤¤·3HÒ`ë&Àsw&‹NRPºiæ…åhÆ«¦¯Ÿ²™u–fBÕL¼!À›QdYͪ¹ rÊlòܰìz±²³KpÖ­ &v‰SðHÝdÍ®jÇ‘Q²OŸ±™ãÈô% ô<¥_}iÙ¬[‘U‹~…á÷UE¢ç¥Õ°å9Eêe•ÒëÍúd±¢geÕ8ß]Ø>ôÔ4²òIçɨ6’Œ®šIšIÖ v3ÉŽðËf’]¾hû0“Œog’e5f’Ú)6“Œxƒ3É…]d&¡—23ÉÁ Í$£ÔRp&ÙU´s˜I&¯b2íL2»ÀL2]F)ñyd63ÿ¡+TðÀÛ…ÐÊQx(® Œ,º/Yj(™…XÔK ;s*™« ù2}­”šJÖ\Ö1øòå‚–Ö®ðj°1Á´àX2©aŸQWšJÖÂ_g(Y»ÈL²¸VJ$‹ ^f"Y»Ä@2Mh¥È<²¸Ø…Æ‘ÅÁr°¨id„©”F6aæ¹³ÈâÐ¥F‘Å5SfY\òRƒÈºèåçÅõRl YWøY3Xz—¦Tška‡ ®Ò¥y~ÖD—ævµ¹¯ó;4ϺF‡fï5®Ð¡ÙÃ/Ý¡)¥„o"®0ŒÌá¾x@eÓÍ7ÍÊÖ%wVSøï·Oy='Á4×ÊÉ=í„·„ðy‡ Ö‘v;.ë€[Ô¥—›°¬/pa¾Üev¥‡èD‘†“y+\ܸp%»L—[OÊNsû–݇¨-hhlA…¦À!É©"í3s\sc4 þ¸~x™u#bë2…h }Ï‹{W§&ÁItVWšGâ—™w¿Ê$8BðR“àø2“པ˜§)É‹L‚#° M‚#ÔRhe0å&ÁŸPn\¢¹Ï7ià†à…'ÁõàËO‚#TSlÜÿW˜'‚àðç_a\hŸÅ¦³:ú¤ùùÑ1µë½Ü0µc‰Yã!µë½Ë¢ÔnºO¸Mí(Ñ?/Qjxk—Ó±nÿœÜè@¾;‚³Ùä»ESËä;âb]m‹¦–ÈwCt¶|G2U|(á{令ÁeòÝ,ݰå# ä»3:ËM`ºÔ¾#ùŽR͉|—ÁÑjÉwãg°DòÝ͈|LjX’1’|')ýŒ’#–B¾#Ì>…|MR½¦ä½)âÕ,^c;ê†:±ï²¨F ûîø–J¿›š#=%ÿ¥æ6“GÀxYÍx„rf3ð⃠ ¼žì ÏÜË\f-ø?ˆxË"$'‹Ýà”w)À^ÇXŒ\„ë¨ÅXÑ\WË%àå«êq5õEï·«—E|ŒÀæïøqfއ1D}¶…/N/t¢µÇ¥Ïžó)`))R7òB3dZJ3yuŒ*p¯,%ø&óÂzœO*)ðŸóhÌJr‡u͸V²‰bX›÷†ü¤Ûú!Nr˜_Þñ€µH–Êæê`ãHFÈž5  ÞR’52`rÉ(dQqoŜ͘½yñ¸^â#äytI×K¨YÄÁ?åÍU‡L>®”z“7‚€@ºÅÙ«ˆMe¤µô3–ÚÆ x´vÔÆ°ûðôü7ÚÂŽ*|çý…ô#²]“W™£Àh ‹þ+&®Ç Žg˶Ĺ“Upg¬”Y:ŒÍ Þ¡à7Yaš2¸+ÊœE7®œHDCHOHNãço,•ƒŒÄEÀ.ãçO­°Œü¬uα&SÖ“_u½¹Ë»ÎFr]5t¤ë¬³2£y’üÓúî‚«¸xZ[:Æ;Sf“5S[Xˆwº/ÀrÉå§‘Ú¸õš@Ê~±¸x9gó<®&«.ŠÜ?t’„+XåMFÆBgH_ð"K)ÍÍŠvÀu‘q0°‰8­MñmЇ½ìØä­9AaçÞ=ÐŒƒÑRL£3@8¢t_òÙÄø2UÒö»ãto̵˜ñGøë0ã ð‚ÌxB;…˜ñ†zƒ"Ìx»3žÐK f¼¢/ÄŒ§ÔRí´Ìøk˜LËŒ'°‹0ã‹(%~°f<¨Ýþ–§ôû̽h%)ÌÇFóú¯YŒÎÂ) ;—¯¸ ¶¯•ÂÜøžàÅâ´ãÞŽ¯"(ÈWð_+o®FŽ?â_‡O€¡ÇŠ)Å'D/C'ÀË0ä šȂâÈè §ðQ$yÊ`ʱä§Ì=—&O`—âÉÊ)C”'d/Å”ïÁ—§Êª)Æ•ï‰?ƒVÁæ< ÔL8ü¥Ã•ÐMª-<<}‚s~—¿ü‘ˆº_ endstream endobj 122 0 obj 11647 endobj 123 0 obj << /ProcSet [ /PDF /Text ] /Font << /F4.0 9 0 R /F2.0 10 0 R /F6.0 11 0 R /F5.0 12 0 R /F8.0 13 0 R /F8.1 86 0 R /F7.0 14 0 R /F9.0 78 0 R /F9.1 15 0 R /F10.0 16 0 R /F1.0 18 0 R >> >> endobj 124 0 obj 66 endobj 125 0 obj << /Length 124 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»åšq¹ä Roþ endstream endobj 126 0 obj << /Type /Page /Parent 105 0 R /Resources 127 0 R /Contents 125 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 127 0 obj << /ProcSet [ /PDF ] /XObject << /Fm16 128 0 R >> >> endobj 128 0 obj << /Length 129 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 130 0 R /Filter /FlateDecode >> stream xÚÅ}k“#Çà÷ü¼o#‡œ—ïÇ}ÓÚV„>Ø–gc7âìPPÝ w»Ùã&g,ݯ? XEVVê…ê9o¬Õ¶YH$‰ÄÿÜýu÷ÏÝ¿½ße™ƒÝ)ø¿ë_.Ikó.æ U0»÷Ï»ÿù½–j§wï?ìÞýñ‡ï¿ÿñ/ßìÞÿ×îOï…’6§Ý¿® è] Òûúáÿ{©sÊÑïžwFÂ_÷ÿâi÷7ñ×!$R–Þ»6ïþö‡ïšu[ëi¥‰bþz»Áõ´QÒø,Ú ~÷Ÿ?ü­YpࢌV—„2R‰+¡œû6&i²)ö÷ÇûïEï÷ÉK•bñûïÆàg-utÅvÞþ>À¡ûAøbà÷VÁït.ñÿáïøßZ¥ÞuAÊU~üáOcTö.Jo+‰;>?ôyÂû$u‹Z¦S(=ƒ-|@:†ããó/ß߈ø–'%ÅÜ%Tý×õÂ#Á§Á…+#¹Ûz<~øðzúéü°?ý´ÿõØ…$®‹#$m3lɵ!½;ÃêçOOû‡Ãóátùé|Ù¿^Z ¢Ì±Â¥úù&ÚsÃäïïzîn:i0\ûKÿÒÚø²¿Ÿ[•dIR.º 3Â!¼ @è+«<ŒQ^7Æ_Td9ž~é®#îŸå$£*¿úôr>^Ž/§ì´µÒ*+ÚŸ}xyû8Þi],tùˆâï¥ö%fz¡P6ÄrÿŸG8¥pxC-Ã?ñ:\¿Äczy“,:I¯ËÅŽ§1Qg€Î¾<ÏçãÓÓñùpy=œÛR52®bÞë_ 'xL|½zÿññðzè²k> Àw!Ñþæô2ò0¨M>‹|iN÷÷I!c»â÷û§Ïƒ8‰ë_p•TP¡ø¤ qw ­”tþöAu,¿G?ðÀË›hÿ^´Ÿ¥* {8};¶€AT"tù8vÚ€3åž÷çóçç?Š¡¯óSßÇý÷BÃÃàgE³@Ô2SÞ?ïF ­Œ¹<íóaQðºøýß­qcKGùÚ ¢ºÉJøkìël¥6©}2… µÆË‘Ï…WÍ$¬žªZçù?§êüþ³·+Ÿ½]t˜×U¤zêvOÝís|êª-áß}¦”ÌðÏÖWÔ'º_Zð¤Ú_Þ¸‡—ÇùªÞ^7bÕöë–@†jÙê/Ÿ$¼Ú­mþnÆchµt9Ï{ ³Éå_Ft8¸!Wü¾s‰ºK€Na]¶Í'•4xù0öÌ(#£‹Å—m(õwgŠO÷—ýØ3”;´:^Ff¬—Zˆw‡ç±‚‚}”HõË–Š¡#òä;£­à ¢ÝÒ^â½ëc>¦gãdºŸäô±àå7FÓØõßr¿,÷ƒWtäTL4Ò¤òìÇõ%øµTÊÇò¯Ç‡3® pM}©†Ô˜ÖÉ ­ñìï_œ—Ëqdqô ZÜ?9ýre{¸[`–´±º*/”⶯ö¶ýÁχ%¶u}µ3p‹·T?9ÊiþéÛÛùóç§ËñÓÓa”ÉP^ø’Ò#âÈXЦ Áá<²ƒûQŹ<ïµÚáôÍâJ³QK݃”pÁF§a1P|š¡÷ Ðʳråã—”UÝ•ÛâÝyÿ|˜à1‡¶Bk‘/c }êkë÷û1ø ‰x|ꮿ¯è;þ:hÐ8¢)1j‹¡Î;¬-j"ÅÏ)cYG\F¡=gK@÷GYŽÅh'µ+>…WvÜ ² lhm­OŽ—Ñ×Ãx|nJ~€5FîXLÊÏ8«æî€¨­tîÖï?½O—ÑgŒY”RÅN./¤e__Pd0¦<.A×0›éƒ.ݽmÇqÜñmûÛÎÃÕá1´ÀÁ@nÿ¾ð{ö·©AL$•Äà>-éQoÓG´¹°íóäaxcl‰èÃþ2¦ïT”ÀhòËËë€ÈwÞ2¹’|sŒ„Èþ(:´ „»¯áÐ6ò»‡gQzuAˆ+íº¼Þ÷>ƒLµ•ÿ~™°­ÚÝÿ Pw¿Æµü Ø >RAf¡@ÁóÞúÈ È: :¯›Å,wõbmq ê|B #Öf§­ì*tšÏ8h‰A¿Q„Ç“¤×÷?~÷ç?µðsbúe À: :·d¸¨Î¡e,9_°¶ÀŠWNôá^… îó|ÀÅsªdm‚|‡*†ÑÕ” hKÒÒ¶#—L– ·A b„ŧàz­*6p%(烬ü™ø“Ø?Åô=®í f°¸]‡cˆŠé½§²7Rˆ^¯XÁ¯F£)J¢ÞWOŠ{ Œ…WF¸ýn,’ƃ|Æeîãáüðz¼«åKh‘}å‚ëÂC·a·PÒˆ`Ñ~ê"üzxÚcàüñøé¼Š"è‘ÕžåAøw}¸*fá¬5Ø.†ú #ŸŸö¯«xNûŠK¼/—«ˆ¬}–•ܦ2˜6+Ån U@pî]{]&usõ9@Q»¹+F9¸«?5šήËÀ˜{™{¡‚×EÑ…»ä2ù°A‰ÊV÷ñm྾|þô÷wç¿ó¿f1q?V$ªZmè®õb><}>¿~ªÖ™ÅÉC+xJ˜uÑôôÕZ]½Â_C æ<1èz†æôyŠÑó¤à繄ýnçÙ[ó߯b¾d@à'°†‘=¬"lòT‘ømë´˜Ä7g™B‡DHþÊ¥näaq0ª š†+‹UÿþÓÝ^n¯fµ’Ù;ѳ}0zÒú„íÓ²œ¼5}eÊòºnUç¾ôŒþ`ºDÉTôúÇ‚ ê}tðç<ù>.âZâ}¼.5ð>Ž©C«2ï¢ØÎè)æ>`MbFÚß|€íČկ£ ð^ò:ŠNjÇ®Ní `ÿnPoyÝî±JçºÎ»÷+$ô®ˆ…ÿƒ†9½NœÇöÏkÎ%0/3M +r&êÀ+Æ£ÎÐ/VKèvTŒÐá)ÜÛ,ó4æî›—Ò& |;Û¥°÷æ>^ÎÉt ¼èú¼WG´#•@~œ2“è®Újšð¬§ ŸFëàÝ—k(ÙfŽ|ìˆa•h¨=À¹¯¯3VŠí/,y LЕ÷™@ýª;0ôdi´§à—ºÃ Îo„¥Îp|—ñב¦lÄYÅ™7Øê¿îŸƒjÉæGî4:SKTy î×Nfoðb ÆÒjm¨²ì™rÁ¡\0ð=K×Ç쌨)ºtò(V‘&Ex Iì ¯õ,¿æñÔÆÛ ûÚ%>)µÇéøÈa¢kÎÍD§-œ ˜ÏcÓ.*é„Î.å(Ðu tµë¥Ê‹õ ôy‘ÐQÀM¾qR›H¢ýÝûstÀ,`÷‘Ë©¡MmÞ ‹~p”s@g’M&\€“¢&$™PŽ ƒ¯œñ)œ@{Ê¡ä•dµ9°»U3]ëÐý{¾î1»V,·6ëÛêн–픯{™F5l×Þ—¶kOŸŸ>¼®¿Æ&Ç*i»^G,òÿŽ_d«<`¹Ü‚oÉÍËú‹|5m;°»¦íÚ×±9åh¥·I,süNÝdô·£X®¡/²?§îqÔöÈìÊþdÜc,ËUð„az•‘6$ ÷)ûsRÄÁã IöÊþäˆ8¸®&kŠ4lES "‰=“4§I™¦<ÏM×b+‚2µüâ8OáMÇäýq®œ¢ÁÊ>߈6Æaæ"Eš…ë!y’*SVí$]"Y ü¿Žp_O,Ò€’¯c¤hà Ó4>écò·Ë”ÃÆÀoʵ9× ŒLk®—À8ÆIƒäÞfýÚ:é»Õ¢ÝÝ|ËŠ$# Å~Z¾^–pHQ¢§tôgžÌD#þ×aŠ/,¾Wh¡iïV¹ã:õìšxLÐû —P¥2oxÓl™f`7û/`¥hÔ ô^zóáõùx¹91ÿ„º«Î½5D£ž~9¬ð½ÜR¨ ƒõÔ– ûM8,Ö‡–ÀãݱSÀËNö £XDsĹPÂN Å Eƒ Ž:4=¹†ý?X41¹Š vé-Ö¤ÒõˆbÁ¸O‘âÉ!ÊÍ؆=îdäc6BÁ*ÙX%#Ö²ÀaÇÆaж^ª»­ƒÄÍ/¯UåÆOUÆÃXõÍjïi`ÝW«ØÙV‹álHo™åÎ'Ò[n ÅTvËì¨jÃA('ŒÛ:­ƒÍÚSЗòIÏ×X£qu¿m( 3Pœ‹îçÃÃËéñÌI,Âþ–X@LÄ$ç„T½Ö‚Ào+'Û«X(â  .”œ­ú*Èy‡/V¥ÿPî(0:m"¹þ|9|bé6ȤIð¼Œaãh°‰bz®]Xý–¤ ö`‘3 m¢å /â‘f -ˆ^hïüñåó+Õ *í¬kè«ø¬ì“„1ÃHçz¾Ñ1(Ò|z=<ϼdso«Ž¤úÜ4ü˜ªn¸xf>ö Ì$ux/‰Qºj$@†çƒR,·ðZ%ㆬÓmxq6ãóU­Fÿ°øÈsEaYIúkÙîï786éUÏ,¯*‚äg6aïæü`: dé U6ÑÐbmt¹èíÙ3ö_X¼Ic)ØEróš ^喇¾^0™¾Ý8 ô⤅;;¸ ¶¥!ÀsƒËر -\‚å¹Áec¯ñ_{ò ŸÍò&Úª Áò?³òù1¿6h+ìïd×$ôcv šS ïU×2ƒ¹CPåpâPå*$…iì]šW°<“&MV0û×OOLJãåé7Ž5÷Ie°Fîk”ý^^Y^zx›rHÔ¸O ÆVŽ$tv1Z“ RÃߺ´3Âu2äér#œ³‚=ýxúpx}=°²u±WŽu Èóáõ噫>)©0 M  5 ú–›t•QHñM¿8iaš !ú²4œÁ.|6ºêmšÈpŠEÜðgõº›¦­6[ n[`:{½5êØý[«=ú·ØR½†èå­‰-‰²­ Æ–ˆ=,ÓרØR¼[Z5lbKa‡kšØRwšÇ‘“41JÚ˜(‚+MŒ•)ø’&i]ȽGƒm„c‰7[J륦¸dYŽqt‹ÄSl²IN|ø[çÄ[o±IÎdÿ—-Bb÷µ:1±¦Í‚ƒ.õ®WØ6v-õ.îÁ¿>V_›OÄšüŽ£Š7Ìã4(mvë`÷ha CgiS`Òª„oìöÖÚTvÒàÈ,uŽ6…Ö²®½º;Ôl­ÜË”-E®Vò™U‡ úsöš"[W;Ks’á»>·Š{¨†ã»kî‚U#ݯ—Óeޝ,Ê`–VÒüÿ{x}á\& —)8Š4•ÏŽ)ppnJ6þ?|ø–u£pŒ ¥€×Ùeëµ³PE (¾9±èâ¼Ì`•¨ó3ï«"ûšI¹š*ÁJ£ÈÛôeÅã-ŠKžçh&å4U’Á >¯àÛúíºªÕ`êô\u§—SuW,“pF:¾M×–ä„O'W%·‘‚½çpL 7iKQæéóø«:)ÁF3$UöŸ>=±.“v ¬›@ÁGÑ¿pU5ŠÇaÚðdŒFÃÌ‘‡Ê#KÄÉ<$ìÑš¢iªàoë)ª0í¾ªí¬Nê>71cÆvÎ!ÀO„ç½J&S´9³äo5¬¼KGžü­êBHàëf®rÁ º°}) Û°e {®/ÅbÉt5ÿí¦Á¡¯¡™^Î,ÊàÈéLÓg)H-OÀÞWoGü*:¦h3Yõ:-k¬­òXˆ ü|à=M¡¯Dçéy3Ê™d–ž§}’É$ qžž§Aà 8‹(ÀìÁ‘D¹–ÌðÞ&ŒX’È_xº :Ês&¹ñ*ßWÆÈ”h1s<óì%PÃàgêSâ}úq UWê*7Ξñ8EU¤ˆ3^ê3M›Œ0É4ã¥>“¤iž•eˆý¢Âãó§'möŸ¿ÁT%Çs‹=+"µƒÁB¢EÞìXÕŒvÁ‹õ‚ò^ìP©ÑêûÙ¶z !kòp …O, ù¨Ô¨ “edrûðÂ(Ì’³%ø¥!V1óSIšä)štB¬ ©‚m5½Ó=´ÅêÈð=ƒÍIk¬ Ð^’§0<+ݧ$Š*rd.Ÿ9iÚ(Ì9Õ³'Mσ.šÅ]ð35÷©®eÍœb |9wZ¬ÛD3~º^DLŒŸfl§™B•ð؉tl µX}(Í‘c›Í{•«Ž\ôgR×à¹Æuäøÿæt=¡š¢Ìš› ºƒª ¼éAÕ³)SÏ«.«Høiÿëñ|ïË`¨zxµŽSXÄÌ•ñß&X÷s;¬Û¹ƒ½ÔC}mÊﲘÎ]LŸójª–Ê“‚ïUÄì&‰NSÙ«É1Æ>¼õZ]27T=ýò4¨å2ý)§/ÂSlhÞ”Îþº á Àa ïS:'NÀ{X8O¢þÍ,Є²v;è,ßiÊ+1}´è.Êb ºH‡YBš^a9ÎG ‘Â,Æ«IZ‚û'€v›&ŽÃøôò=7Q+±a×÷e?F’>xµè¢§{ ;Ø>x1íÜ.:]àÙ"pÌú£MJHèân?c3É—cn‘i¶÷6€ªC²}]§Åà|œd­,Åùï'П.Xñ2xòdy´¹ÉKï«Ù‘ÛŠ뮞ݺNäÉKÔ,…ÿø;5-/ᑟž·!NŽ Iœ›Â!Ó~)ìyO‰3QƜ߈4ΙjhAšñö²3(ã£4$Ï7= ÉœÖø§XÕ’÷WM¯J¹d]sývk“¹_ùû¯‹“®¡`&l9 þée‰Õî¯îû;p13h2[Ô°ƒ®æˆª÷¹¾‡:¨ÆXjF€?ŽLd™A—ªxæF± ·\´‡ë#2ŒùU2üÀ öáôíYÐLƒU È2šç0M§U£†Ì ³ñíCÛ!–ëÙý;còŠXÉî]e»Þ™ðc÷a‡æ Ü=È0Õ§K3‚ÁÇ‘$–àá°o-~¤âHHÁ¢¤ì½\¢n÷àg-S ¥+ ­¼ ÿXfA>‹ñŽ­2XNlX•LW‹õ|QwÉOÇÓÃëáùpº,Ùá-ioô–ˆÞŒ»·¤ Ú·Øx+o ú6Þc@OI[{K<&5†ôNåã’s¥T9…ƒ¢µƒ ³tRËÅÊu<ÜaèãéX3ÔDP“¹‘°‹8U'‹øFÄñÚJƒö E– €F{´$m@4Œ7¿žaWG¸`šÄŒÓßobYWù$¹ß¯~l$æœËrG¥¼XdÝM[ÕNjIÜ?X”É8¿ÂQÐÏsJ æÙÑ9Š@=OáÒ»2N‡¡61î)3ìGÌ4'€?–Ø=àH~k)ÂTžBɺXØ;=Ø¿çq‡W%%’y>?shã1©:ç7ºUDPg’n|©°èݰ¿ÐUé3$M0 çÐbYzÍ ªà\Ô1_æ¥êtÒ5Vjô´ ÏwV9ÎËU½+$½NK•Aqo|XsP@‹;éE[jéќ͡£¤jX䌞Çr{›Ý¦Tˆ™‚Þhì“q¦4йò6!µ1ƒG‚8P¥c¢ÀU«ÌQWpðÓ 8Ó‹Ó×Wà­·ŽB}ê­ŸVX4P†$üþÂzŽ•ªZ(¿ eœö2õø4š¶Œôʼ Ë8œmž M^@WU”]XT§g]°«èG±Efw$]èðÅ|9\Eò-hžy‚ÞåHÚV Î1#Î9£Ù†ùFyxEhÚLLšh¤|HUk§Ž¿x~l‡ŠÕ±>ü~lgy਎íÀ¿,ñ³õ`×±.l±ÜÙ=H—:¶C >“kÄxl‡^Äv–ÔêØÎø†µ:¶C ޱF䨉íкzÐëØN }q¿Ñ£:¶3‹Ý—ÒæÛ¡`WìÎ!NÛ!ˆ³LHöèRÇvܧb;“¤©c;øNl‡Cš:¶C¦Œí¬¡NÛ)ПÛa„[n ªáÉM§þrIMl§^l7Ûy=_^/•eºdwÃÁboó¦P E'¸SìdÁLï)EÜ)àÏd0ÃäjÎÜá”Ä,–¹á&M.ï¥q¹ÞWr©àŽXbyé½é­Ñ¼øF{eÏHÈ´îj× ïa¶ªH¥dztgX |1D¬±ÐÌhƒ³M˜É±í^›HÔ¹‘#'³ 4Ý\ÀGCñ}åçáYYF ÷=0uHŠ^981£F"ट^);ÌÞjà'®c©€ÑìÚE"yë ]SƒTÙ*oÔ-^žÁ°ÓÖÁ¼P±GŸM²Ö½³+{s^Òº¯ê‡¨síD¢Ö$­»ïw wQ¾€éÑÔÍŽÀGì @ñJáZË*7`àíëW8¬ˆpµxÅz¶î_èˤ²U’²X úYR’ÎdYåj«X†Òq÷™dLnBW¦6©ý5â\é:fº^W µãY§vßx3Lús¾J˜+^cEW 6 âùªÝMZ·»u)”‘&Ûm£xÖ90ÿr|ë8wðU7"úž™Uƒu¢ÃM9BU£b«aäéz˜ù•6Uŧý[¼Wùj!±îd'U$¬Iâpu$Ôc”=ðbN¥Ðô„ŠP•Ã0)#F,ŒølST ­Q“°]©-ø‚™õÒÖ“’‚çɽ•8¨%™Ï4=·u¬ eÒOf³Hþ׉ôc”ÊÚøu"ýõbD¤¿îÆðë*ÐYli«?(?Ý øÖòÇ?º__ÝOUC üÍõ/¸Xp« E”ßqºñÜxÃ'Él\Àc]¨LÞaà_xYæºjxZÃŒzøá4søAvêÜæ\ð†ÑDçÖšbÑ"$H3>Ða^ž¹ $öÕ@V¢9\J|à ðgn¢9:†)ÃvcDx‰ùãD´˜‘iž¼†®ynœÈf#E^MœW×LêJ˜™æXŸÆ/ìjãÓ‚^õF\ãAFæ@ ɱù}ó*(±ðë2ù¤×¤œa:+g2)$·q&cÃ8c-~^Í6NelÀoLR["ÿ×ÇãÃG^Hx úm,GΘ$•Nyö¯<9\·#6ðóY=ç€ïºÑÝÓˆx­U”ÊyŠHþüt9~zZB)ÑOšÁè$# Èž)ÑÜ?1=;tF.X0K…ùóþ7V.!ê–æ V¯”Fô€Åé‚ëu–]ž…6t´(#ðdo‹t'òlc¸ÊŸp11VxNv°d‚Fœx¶»O;Š,箑¼49Ëݲï+œvý´"L[Šê³ *ƒÙ%ÐŒ ¾PýÄ2£#p!w@·†<ôü÷è¬;|ÍY"6$·È¬Ãìf¯|÷œWµmçÖ¹,1”Û>ÓÀšÌ­ ùʤø3K¸aú.FoÀEopæÚô0™« âÕtÞ¯ ”y4µÂu¨³XåÙr&TChkÐÃ]ÐŽ,‘ïB¼:—‰ƒ=± 4"öCOË/4‚ÊÆgX‚`½¡ŸÕ2'õt´j‡Á³²Ö¤Ô€0°&Q,?>]cF¿l´¥°—,Ÿ{ã´V8økú¬ñÈÝWrY_×öX?ÏŸžö‹³H‡ëÒÚ»Ú¶,­½‡7¨Jkƒè8(8™§Ø®Þk¿uQš‹RƒZCƒüJÔrµ×+l_‰áÝäµ ÐçæWb&èŠqz&†X—ì"uÀì¶kXd”µ fÛµ€ók5üùøôt|>\^g^n¹¯&5âzÈà‚…@î΃ãT=yÃ6˜¥€¹ähÁLNoäNòaãa ­1MçÎ ðVªèo1L!©ÁÆ ðgS@µÂÚ7"ŽS8æ7‘ÄaSM];’o˜Ãl¨¦¡¿i0(š5Eö0…$<\ò[LSÈðª+3°Â¶ÓœOU2À[MS ào3Má|ûi â[MS Ào3M¡þ6ÓÌ7™¦@ÀÞhšA–¦)P ³Ý4…þ ÛMSXÉîs§)Œ²;wšBøÆÓ ðÛOS H³Ù4…BH~i èB÷:}i õbbÒ«1o¨Â¼r,9ôÞUXçµ°ŸlsZ,÷pLôÑ+ÆxK¢þÍY•s—È Àà〰Åìž;KüÅ nºÃØÛ¦ó9ú„6C°ÅºÆŒE¬ÊIAz"¾d”UœªPE,ëÇn\Ÿ_ÄÚ<¢N]jB‡ØÞ…›sƒ®5ƒ‹4M¹]¬ªF¶Noß´ÆVýqkð[·­Q2¢/f8{~ –ŽZŠ2[5®…K™Lía‹«Ø2» ~£«±ŠŽ¸·üy’7_ÔIcµÌ{f;+ÔY¼#ùó3/¡î:ðàmø¿¹»êZ÷¹õpÑ,5Þ®+t±Ä›Ì€±²£0Ÿl3g²¨B7ê0üe‰©Ý)c§õ’*ÓEª#oX3ü »1±ºqÊ="ܰ“ÍVFcw+¶¶Qw°†llðØxB•áZîqóWd¿8.Ä€ÃBbÒÍ oá¤Î˜!S{`zbm³rpf£ìç(Ò0Ë ¦Sòd™œCÇŽ%Áóƒ ¬@V„á`àØìD)wB†Iqœ9“šP˜¾ a¼¨4¯OŦk/bÕŠßÄXšQ–Ö“²fªyÊIîl¹qÔ›(ŽZ&å7/÷¢Ñ4àÅÜæó]à þ À'·hBf³ ÉþW šX޳øu‚&õb3‚&­æ›ì¨‰:õçn5©A¿YÔ„B}“¨‰5 ¸-oìDkâ&5ô7œ;àF êØIº`Œµj»J¯Ñùåi׃ñ“Y´kì$Œ Ü¡ ®Ôε¯c(îÛzÎÈ^5<²]>ÔÜ/eÊ»µaAß/ £ Cïød–ÖUÕQ”lÁ9Ü;Yê Ê0â3c(sòû0†2¼Hå›áä÷Õ!”+t±(#zÒyRGP†1  ˆ¥}!1€2|Âï™!Ð:~Bœðçg^=á5|ò&|ßÜXú˜Õ[3~ÕË9ö /2ÉbBUur&`—ѱ&òé¥6ºŸÑ¯¸Ñ¡Äµ"¿#·´Q_>Ù §~½üôÔ7@»ÍÿÇàI!ªy“ùØðÿRi·j“ÛtØ÷€òQÉÆö›m¢èýæ“äuÕmœ€¾E]ìS¯ðA"¬‹×!Q{`‰Àòa‚ú«}þøGŠ6ìú©ìd&9‡Wá4²FÃlí²%™†[áAÝH³=eš¾EoCš›<Vª¼y…GÝ¿†þuüÁĺ8N¿ ¾ ð_Po'Fšàл²X,bü.t1§ þ¤Í_7Á'PŸÙ=[Œ7Á§¨Î3øë&øwàbAüiƒÿÚŸ@}Ï‹7Mð èu|–‚um‚OHƒÉ&ø3U,hgãWW\¶Y}ëÚYà.§roÖÎZW•ùà™­ðAHë¤)Ê0[á{x{¡0ß®¾qZê˜Þ¬~þ†­ð à›´ÂïÂÞ¸>ú6­ð à۴¿ß¾>øF­ð èµÂ¯¡¿a+üYì¾rè={«Vøq¶i…Oà¾U+üüö­ð ÒlÖ ¿@ÿë´2Vƒ"”&S¡Ym…p¾§NÍZÝíÕZЭ…»~±§m{á[غ~|ë^øQ6é…oôu˜ûÖ½ð±;[¢ 3›áƒ²v½}/|=†9·¾‘N“Àù½ðáÒ&G‘†ß ?ɈªÉ0öü^ø¹RÂ)ðÌ^øIº;î›çb[i2:6Ão:Ö3G}fçzËl2㽜Uü‚âMÞ¨OwHÎ/ó0Öô%Ä@}0-ø‚k@·='!Vó& ìù=Èa¬ˆ6·u$Ýb»[cðoQ¼ö–AÉ3¼vM™GÝ™ Î+³Ú R”™ìž>¯¶ÔäÁÝÓYÕ¦®Ê±é.#VwOï»U¦ÊÓ"Y”a%:GÌœÜg€‰ÄÏížNN´m8“¨ÿ|àN´Hi÷leÑ9Jc¶îÛg˜¦ö}ó˜.æ ú™;Ø"âªL‘†WŠ›\5ú‡@}i=E?:÷UY <§×i<Ò’(cžòYΧ4¢îCò‘äù˜ƒ´> >> endobj 131 0 obj 1635 endobj 132 0 obj 19248 endobj 133 0 obj 540 endobj 134 0 obj << /Length 135 0 R /Length1 131 0 R /Length2 132 0 R /Length3 133 0 R /Filter /FlateDecode >> stream xÚ¬·ctfm´%ÛN*xc۬ضmÛ¶mW*¶mÛ¶mUœ[ßwºûô8Ý¿úž{Œ½ðÌ…¹ž5ö&%µ³uVö°7a¤e¤cà¨ËIŠÊ*RËZغ8ÉØÙJÓ ÚYþZaHI…M œ-ìl… œM¸j&Æa#€‘““† dgïáhafî  PQT£¤¦¦ùOÍ?.Cÿiù{ÒÉÂÌ@ö÷ÅÕÄÚÎÞÆÄÖù/ÄÿóA%€³¹ ÀÔÂÚ $'¯!!+ “Uˆ™Øš8Xä] ­-ŒÒF&¶N&”S;G€õ#;[c‹Js¢û‹%à08Ù›Yü=fândbÿ‰`oâhcáäô÷`á0s4°uþÛg;€…­‘µ‹ñ? üÕ›Úý›½£Ý_›¿¶¿`òvNÎNFŽö΀¿Qå…Eÿ#Ogsçb;Yü5ìLÿzÛ¹üSÒ¿¶¿0­Î¶NgwçbšŒ-œì­ <þÆþ fïhño.N¶fÿ™ ÀÑÄÌÀÑØÚÄÉé/Ì_ìºóŸuþ·ê ìí­=þ=m÷¯×ÿÊÁÂÙÉÄÚ”†‘éoL#翱Í,laèÿ™ [S;#Ãè]ìÿ§ÍÕÄñßQüVÊ¿IÛÙZ{ŒMLaèeíœÿ†Pü¿±L÷ßGòÅÿ-ÿ·ÐûÿÜÿÊÑÿv‰ÿÿÞçÿ -êbm-k`ówþcÇþ.;€4àŸ5óøØXX{ü_¼ÿ«£šÉdø‘p6øÛ[³¿T0Ð1ü‡ÒÂIÔÂÝÄXÞÂÙÈ`j`ý·GÿêUlM­-lMþrùo´Œ ÿŦlnadeûOÓYÿÃdbkü_3ÿKÏ¿yÓK+ +ý õ_/ù¿¬ÿ»|ÿ#„šŒñÿþÁ´sxѲ0h™Ø9lŒvFŸÿK´aÿS–1pv´ph1ü³·ÿ-ü<ÿ)éü[#;ã¦DÉÙÀÖøï`ý/Åÿ¨ßÂÁÅDBøoÕL œ,lÿj\ÿ²üïøÛ†ÿ)ÿ;ø&&î&F0kËvFÜÁ–éYε˜yÓÂZý½Œ Ã!ö% Ê…þÕv=~éỜú5!tÓ\_mKçöŸ‡’TG£½Öä=©&׿p}ˆ)û ·È:Ø©éuKà3.Ô¢½n¥wÀ4ÙTö&u‹? ð¦;˜¡nþPú»ø£‘<Û#ø¥ÕÇ¡w"5¡Ôþ>¿ K:ýóL>862<ÔsÞwøƒ:7š”Û ž,Êß!÷ÇOM• ¯ª¥ãÌñIk þ ³ža ŽG ¶pÆpî­Ša7ŸkÌûS9<%Ø;…aB—K+GÏÀ¾¤¹^œÁÄŽý€FS².ÂûªŽO4±¤És=Üuf¤S^÷üt 8ÓåÚá ׈˜œ¾ü`g˜“çžÝ’=h$Añ‰PÆ` ®À›ÙÏìdÕ3{ k4¾yC¤»jW$î¾ ÎÊT:ØRTÖlôZo祳ÐXB³säŒyÜÒ@ï­»î 5² t_Åb*nCÏÁA"G1OBŠjTÇ ÜJú¾ÝÇ/†‹#ŠÕ‡<@S=óê#®Z¨ê:&× ²êèÛ“dƒ%}¯šb°4¤köÀNšU¹}±Ÿ¨¬ó0ܶ¹A*5lf<Ç<ä‹·{A_ëu@Œu×Ìmj\tØ-Ãí…Þ|'_¡øÛjªùð^Ü·?¼y‘’¦L/''‰•$P&âa¡ŽSœkýHŒÀ7;‰ÃüÉ#/¢sUx¡-“eGÊó,üX%±ïÄ—)û~õM,™Oddx!¸c@}r¤ ªÍDÔî¢Àþ´¼õ`M«Rá¹Öž\¼Í®m1ÂÆùsÆÁSÓ¯C¶^Û©ã5Ï;%¾À˜úO?Ò .õ€PÞ‰Êû»ÆMD½4ÆÏDûré”qD½4Y½ÔJG=u”oè‘8oÉ­o™eDI”4sǧ,£žB|ý¯Ûn¶óSi0#"$Ä™Æv¾¹ò”!IãÓJDNé“öP|iüÜ–Mäeµ<r©÷Ç` ¶ƒ¹Ü$d¥ð±ÚSÂáÁÂÆæêͨaä³Ó^@ªdD@4¼;ðZµsO‡ NŸAÄ=³÷4ÞO9U áˆd*;ïctk-:îÛ)œ¦ûx¬‰¯DÌ4þô²»Üû5€~í+x Š©Ñc™·Ü ½-À÷UlÑ’Ê y°:jÿ«ä€ Lƃà ?}¨ PÜ)–ø¸¥_QŠ|”„bµxŸyÃüeü–OÍò@…ûÙCóZ7 €TDuKn7õÉWT&u†éüÙEP'áw'¤éˆrGÙ"ŒcEG£¹ž-o%J¶ôSÈÇüÉw^–«ØÚTÆ›âÛo„¤Dð&¡bö} \U-ãñwM+2Z&´Cƒ”ByÏ~ ™ínæk”¥‚Mm}€Ï¹ ýµçY§sµþÛ ¬Ù[øv§²Î`¸ f;°¾ý•.ÖP„wQ«ÔüåœMfë:²Û‘ÿÒø{Ô×\²9)C8“›è¥OmvØÿÀaÓé“ÖS“Nò0åëRç«O <«ˆ6Ðô§­ÃÈzËbKY0ßÕdq_†1fÞ×Ì 뵘,óú»w–j5?Æñ­sNõÐú¾.VÚsp2%²+hÁ8äèÎ)Æ” ͽ´Ùuïõª;LgÃp™ot,摜ÀTÊ®±iûáß,`fR¿‰#Ò¦äB·Ìiãÿ‡´9A–FA}o0¥Ÿ[nš64UÊGÏÚJÇè[,L™·!æ¦vqÌú^˜À6L÷è»É-Yù^ÎÁucp§;8Âü$Šgò‹>bÖIî®Î9¸Pxq© rTŠ% -p¬Ô ï 0BBC\ Ó! Øî\o²×‘ø:d§tütÃç µìÂ>Êd$ þ…ëŒU³ ß½3!“Q¬ÑwAÉT-(±|Ú{ V:×!ÕäZ®õq?ûª¥ß輌yà :\®¿ûd¬b-‰l\ ò© ”ÒÜAál„òtZŽ{3lê`²Œi##d{Ý;ãoõ½™N,¦ž}ÌÚíøÑ mP‰g ê*Bu°–’+J@Lƒëâñü_¹UaÛ04Âé±UEåR“»¼(šׯ.Ã@DïNÁc·D/œ©|XL¹›âRü—˜%yäßfû¢@Ue›qàɰP~_õðtl¡¹øûàR¾¿íT¥#Œ§qK Ù‚zM`õŒ÷‡ñ»®O…Ñô^s« Øiêè“é r·åçp5V@¢)äqgÝ òÛYž=¾— ̃a9žý©:ƒØ¶ÉÄ8 ÒŸ7DOWÉÊ`‘„7<ˆ]ô$ä]¾˜WBÜÖ%æ(—Š#Ñ\<­H:vzõ{§ÐéòygNÎÝ’¾ûÉz2Ù<¥ª— Àx—‹)dÿÊEȆû(hÜ£Éá5 §Ì¯•@?–H'nIm5 ii“[NMª³$xâ«÷¦O]>/PS•EØZ¢êó kCÖ*ÀxÁ†æÈ$|®WeJo™¯QÛþä£|»ÉR{³¨=l/VRT#9óÕ¹ªë"nLoý+²+|æ×YóVuÕÕùég°¾HˆèË…“På4ø/é®?i/Žý:ý>_3RjäIvÄ¢ëƒïݰ‰<øHň·¦kƒÖK~BJëÃå)ÁÃæÜä ƒ¨ÒBËoÌáÚY™ÍDŸàÙâê¯Þ³Á‰•å|<¹÷—Aå`•YMeº¸>³¤"š€BÎeÃ3Á*ˆ.olüe£néËLH²‡xòÕÔJè\.ÿ™KÍyiïÖLì —™zœ­Iš q:¨@‘¸ìó(f̨Nñt·¡S?%Ëž F‰9~Îrwþú4Š‘pî@È Z‡G ^U(h€]¡€ç0c¾)SQÿ:q «´ lªŽfÂön>üÚsˆõËæaj?jk1÷\©C°Ú!ˆž<¹á:8"0p" ävO›ìþ×FÑ{Éc £u °‰µÎbo«Cš™årˆÝ/M¶ëb³:mK“‚úÎlµî,b´X 7®\†º­:ŠÑIkU 1ßuÞôf„×ÚÊÂz,%Ü5Q´Ý? 5 ›ß–:€@ÇtwY„;,Ѥª”^9ïbnÐ2Åø(Ó ¾K¶\6: =‡¥w?ž;™` Ÿï¢ÍŠÓ.ézÛüd“ò,ÀA烡aô­ú»±Ç8æ6})ç:ÒÚØ¾,qJ”ŠBj?×ò FÔ“­[Ô‚îy‡Ò_LoÕ(,Á}=„Î.»d&@ž);ËOÞß[ÎŽin-;ò KÇÃ<ßKÎ[¿2J¬œUK²–×ÎÎŽ£‚¾Äƒ²¤žHütpq·ÌhÍÊNté¾îøe¼™›Å‚F£Úr¶…ÊU=; ôÒòzƒ/oÀÓ1O;0Lð£Ÿëx<{èQÓg™4È ^B:å ±óŒñâÅ¿Pº‰ÿâ †ËaëóÇåCê…ßH‘Õº{UξÍO·ºUûoˆY±çðbfedÛER‘ǧ¾s“,”&€[¬6S©Þw¦n_Ì_Á _ë»WÂ'xÌÄ@mb¢ØSÂåäÖ_¡÷b.WrJ˜Ýn°&&£ú%*¸5þh2Kk¤hbå›FYÙ˜1ê‘Uò“–Ws¤G‰Œ+ŠM. u[&Ü,;`Ù÷< ²ƒ,6 ÔMЯ¹*RámOc‰ÝÁˆ;ý=3EŠ…G¹©7?Ä :è®æRš; õ·`å·,ÎÃÚߢ%o7€mo©)AïÓ‚ÛÛ†ä½Þ;™ëj³xQüTYH·ÖͰ­\ãVq?èà²réhLOŒHs/Êlt ogEsy@–¶¼z*¸sÈíMV’a·þ Ï_Mzž#6+)äÀM ™éQ›é胦—»ŸåÅ ïI*äk´æÃL‚h‘ûÁ­ÁHáÁ„iˆï‘sŒÁÍ_E©¯÷¾7S‚Ô$Ȇ+åµ Ð/ßê*Øå†õÈý 8ë5"ÀÉûÛ¢…pÅ9<¤­ðe#¯£qÂåfY¢©Hò4ÓúTg/øâbm¨*ÙéA­9`ûÝd¸1rÛ -éAí‚LÔMÜiäù«wäyp¶"mq8ØÞ'ã=•“±(¾q‘ø¹º³5´y:Ñò†˜Ï¾E$®7—y= ºRZ lZ Ä·õ+fé[ ¤n›°4B…o†K‚3P³d`Å‹M‚ìæ•õ*ÿÒä‚´aÀ•¿”…1l>ä·ãð¦EP™…&Ëü¹œ½í‹•ÓÀÈZÅ»»  c‡Y‘ÚVÛ@›IÛ!­¨¡QIÖ‡ÔÚ¸GÍï—x²FÚ ¶fÑbëÖÝ»H“Ù6ŽgnMÚ-#f‚³#ã GÈ-Å*Lлö”:9sbP°úÛkq.\Bc2Ä1–Ö3eV<)†pï²a°ž~@ÓOç!ûïÉÑew™¨©C¼F®€ßrNλó@$½âpƒÚ²[¿û“H¶†£tM¨÷c1N$¶®‹Ä²Ýœ„2þ&Óƒ«óôÝé1¹èJö%ï»t›ê“Žà"ˆI*&Úô€ ·ù›ð°ÕoøRÞÝŠ‡<‰ŽU=Ía±< ß“͵(ÒÐñ ¦ˆµ§+@BÚë ð þ’ûþŒ1λÚMšH¼ÛÃûƒ¦Ð;ᨇ꟒^+< ›?]geØdÔCô¶¦2x‚Háë€0é VóVP H<ý\wh%bƒ4€útiú™Bð7oz­¹ºÒ0äÑK#IH1ér7£/…€ de³ì…‡qZë{³o0…ẹ{ãA§Ë:|øy·Ê9³:õÄG£ '•Vè¹Ê,–ûZµfW0ÔB°Ýa¤TˆÀƒg¡qÔ?´D ‹9ê'í‚›?KŠhžêyc$u cwñïÇŠdÉ* ¨ÖÏZª½ßÑüÞ(6iÌ hvi¬UÓ||ê걯ù¾¤ ]ïØíRò'¨Nk-K£¾Š_ŠqÑ|Ô°¨¼ÂôeFàSE)ܘ=±ªþ¦»É¡®ø¥Ù“žP¤£ÜªFu{SWÈ·“Eƒ {Ú %áÏÖNQs5l5`“C n±¬…~X•ƒ‚3õ‹èq¥.ý° ÝX™Ï=ºg‡&.ܦ 9nØÈ$ÇɬdÁ‹ñgæz‡ûËÓ)ˆÇð·%ÉØŸÐZãy²™‹MäÉñütí¸ Þ2œ÷áöyœ=Â.<³ã©£uôA¨--Áã#ýcãŸiŒgûw‹ôïÑžå:¥ó2I¸€Ysrµ#“ÁùT¾/¬’TJQ­W£n*…rþC$S÷S‡-ìËè Ë óÑ ƒE–Œr°rzÝFÄœB¼õbÆnsGF3vò7ë£ì#á?lIÚæ.; 5Bn¥zoºµ!>ôÃa‚äÒ·_æçŸgAš‘ó?ŸþæCŸa»œÜgéû‰ùL1 ³›#䯸ïåòò“}U0Væ¾á¦Øs¾FXØ!’ÕéüDÝCqóqêP÷]´Ä zè0é®­ãäÐÙ#¸´}”|)ŒèÌ?cæ2ãðø@~ éÞ›¦æû¶Pƒ£ÊOϳ_/ÅŠ8‹ãï"‡XFnîðáj(6¿ Ë\ƒþ¸A–+'جG è6/ê3 ã‡kùÜ&WòT˜@g!r«¯3’KÓt^¯‡IðåØ;O0/ÛQÒÑY/H^ÉÓÖ˜ÁéJ å`…[#Åç<ÜW©[âJ,UNý»Æ©^Ö¿ò§´Ï.‡.0P[Ã'ÅÑ9ëCÛ}÷M¢'{w¡ßŒ>Ò×Zg7>ÏÁÇíõÁšqiüÙž¤³n=Še9wiÒgº×æZ=cF𖃆>,ÙD»9¸M©-•J·{v¼U¨Ph´ ë>´Ý€x‰~R‡mÒШ:Žî²‚É9‰„)^]zsÁ­#Üýj-{¼´ù±`@‘̇·¼¸^g–‘ý{†eeƒ>bk ’W§„»È±„M×þ—‚D‘x>$A]WÇ)>}ýÁC§no[K³¶Ñô¾çðÖd—Ú‰‡‚Á@4ätÅÛð¢3G!†TÂD)Ÿp”Ãëû…â‘§’B :¦Ú•­éá$Á`ã=%S´‚Lh¬ÍŒSë½¼8…ŽU03iÞG£R›$LŠgƒ|P"ýË,$l\›¤ X8ã ?ñЬ¨n~Ò;}æ)ë†*©)ÔQK/êƒ@SC0i RA³8wÀC…o,!ærj œúÛ^ÞMÒI`7œcÚ@©x¹j³O ÙÉœ§±^±}mä3d¸÷Ù+WI¥+½»ühzAâÕ#¿!©÷ZÝCüe’5RdY.&}Àwþvƒh!­ÿ$V ×Õê@}¼cìžà¬h™²yŸP£KU¶òOYë—qŸq¹ˆc„ «õ| 7:ûÏ/;âJ¨¶2ßN9,¨Fa¬‰¬¯¬˜Ä{:Þu€(œÊ€K! KÕêŸÄzƤ¢]Fî#håèW´&Be/.žY-=ƒ¢w½-"_ìY«ü˜Èz„T5 4Lý½P0¸Ø¹P½äú;˧À3ŸûÛk[E‘ÈÂÜõÞôßù1xSì3«àcòÝRF¹¤dFô^¶$¡^Pƒ£ß´UÉ#Kšêz1Ø—Ùy‹vËú?òÜ,Œ¶"Ûz“¬‹Ìñ´ÆJ㶦!Ìoizõò‰zË'] £õÅ:ŠÍdµÂâéÀöRŠ’“rµ ™|Q•ŒÓƒä? $”BËç.ïÙ—äÕK“4q÷¯"Gvø¨$î'Ij†ƒ—ÿ˜¿ö'¥”ù’æA+Æ,È!A¥w#¶NBíéñNö/¸QnbgÈÎñ¤¨˜ÔFƒ…ÏÁÝÇpš ,z<Ô$Õ³Lúé*Þ`ÔhãËNáAMŽøŒãüXŸºÏ;Ðî•õDƒ4ÄH\È §1é°ÃÖ¸ì”GG²LâH÷„Ðÿsªã/` e|L²QpéÏÒŠ6ðbm³4.†ƒ™ÝãAÙÚ`‰ÈÕ Û©ìÈo•‘˜ÉfJ&úFË÷FŸ@¿JTϵ§åÜyDKw!¡¹{«Ð±Q¢Î[f·â)Ñ‘Üdt0’›!ˆ†,S'ÖC>Ÿ-˜ÓíöÕê%?êÎDßÖD®åW!t !?ÖÜ*Öü¹Ÿ=7Y—èÛ€OtÚä|\²·%åƒÐj|ñC½Î‘6#xÏtnÞ:ݵž“‘d-ñ¸í«-IP®±(œ˜½‘—]](B•Rj OX’qÐŽõƒyÀ[Ò¹JoÿA‘1ñ,N â‚VÚÑZsŸ¿‘Å• |jÒÔ]YJ¸Nö€{;±(*<"Ù½»édõ«ñIHQýGí»"%–*xºÔÀ%y™:`1AœJ?¶C2ÝÃ-+‹oLûЇ­)ÉÊuš6|àO*²ò¸|²)ryû™RšÅHÖ»ËóO,kÿ9Nõ¥•ÂöÜ8*q·d Ùyµóæôˆ¨h+W„Ñ Mo¬ ¹G´ü< Fò]^òK—iD bëh{gàê"áMÇÕ®Æ,Y®ÝØO‘Èèì Âüfý,è?çäZ 5¥)“Ã:j¦‚§%îôRœÆÁàÇ8]¸jˆ‚ûì™/ªE6•¤j4ŒG¸KøÆú-Àõi8i*Ö0S±jŠ |×nJ‘ÈØœxqÒàÒzë0È©™¿~X‹ü1ßxï@‡^D·ÏqXb’'ŽZܾ1y`J_ú(@©_Ár§ë¥8–;}x‚‘§Ižò\•Ë9§»÷D Ý…¾wµV€ªùuÀ(d ¹3®R=jz³ˆ`˜‹> e| Á &Õ²ÄW±õí’ðxRË´Š^:è,>ª¡kþãqÈÓ` ½ Ëžªò9î½!z"ÃvcŸçabpM¤é‘C×—W÷½^Ï⹓¥„RZRÅö®­\Œ-ã;´_¥s„d€kІ¡õ1Ô˽‘uÏwß@3'%.:­z!Ã^±û(~ß«uc¤5Œøº¡T%…V8¯­ÝÞ¨$á7óLä~jÒ^óx¥ßC‡¬~«ð>“ÜŽ5¥îÒC7ãƒÞ@zqZ7åTϘ&h‰z†Ï…?ø’Xp›øûP£˜ê‹ªžŽÜ ç)Å»´ ¶1á38Áþrë‚­³%¸ ÅþzÏ ˜£Ï‰JYôóñ²ˆ,ê¨ÃDœ‹GãW›nAȘܯÞ;aQïyH¥»Ô_TÐîR½æâ^ ^®6ØFU|pûq:|µrðg8mDû\Tñ°c¹ß³·„$³7 o>¶íÞmT=oÌê›óké}‚ÑP7û­»]ßr±ì@’Œ±â²ÜÍF8+†\™çŠAÝgŒý\’ +³‚oe÷_óä8(i.ÝAg%b÷µÜ·uí#,E6|eV:Éžª.œ¯.šès2õø—Á=³¿õmod^ZŒJ;Oh¬•zÛâÓÕ†tM@Rzx˜Ó:a‚~ ZD›–ŽÝÊb¿}òBì*«9 d¨#KìE”“Súîú“dQ Ø©sE=ûKŒ@} 9ì¤òlOZaƒ£ÁZJ ê&@ÝR‡!Ô ”cÆ wû±8à„™Ö ]\×Âð˜£,~OB ŽÆÓ‘ ¼µ éØ8dÀßë„CxOÏl|¹<ј& ¦söb²—³¶íý¼h]0úŠ“ÔØvcÞ¢FCÞv3“Ewv9 ªµ!0ˆ,8XH 4ÉväzP¯&´*âÏ‹µÊÂà5”徨Í]2¡­,x‚·Œá>¾pÚ']›GHr…³Ø”çÙ?Y‹º v|†Ì*[ ms½ uò}úý’ÿ©ß_–EɱÈ6ÐhcŠíu“D¥k¼ˆ9Ü,\—çMëÆGáûeš.Â&·™t´EÏl¯W¶2Óæ;ùÛø´'Ë•à¨àI”„Q#`#Wƒ 3hsòzžœyð Gá^”jò€äGý-pw´:cÜ}Æsª—? YîÁó䇫á n†ÔãÇúöZ1£Ö ˆÁŠb”ŒQ›^ â~ɇ”NUNüÌîKj²Px=×Ü Z{ò¢‘üf6QèkI@œ#´Å§Jï8P!TÆboäìŠËt–üÎU9Ö%zfó-#äqâFŽúNU’Ù ]˜˜4T±F¡òìxQ~g£ýo0*6•¥ÅÖÉô9愤u¶«ú!‡Õˆ]j¦¥T²…&*‰x0°ØSÄеj6ä˜"¿0 «¦©àU¬rŽj® ð›^Aãhz-"«»œØÛIÔ‚m×øîÄÅ«Ó9/ÖÍì²Çüª¥GªLºãçÞgâÏmDî'MÉxMìÌXéëœÄîç?àþŒfö([£ÂK¨Ä*æJE]SÎǸÐ1œ\p»³¶MÙ+ô·µ$*m˜ß©…Z}IÒeëŸt0œê¦œ«{ƒQYëÞä€ßç0†Ì”éQ6™ uº§ª8Ì0¥5™}@ŽJçDu{½!ƒÜ:nÜ“Ö5½¢÷ŸÔÈC—¦ÅÙPü)ß{®P˜ê¡ÈÓŒê4ABþŽUúÝáŽXb4¥˜qöj†.ôG¤ŸïæÍÃXÌ"ÝB¿80û8×ÕáÉ €U"ÿB6…ù>ò)1àˆ\#ÙÜMaDkp„ІrQèêŠó¼ú±lyŽˆ‹®äohƒˆ‘ð0Ê”†°%ùÓ39±­žŸœhXLYÍ'•ÿö<þ%ÉÕc KĆD>g£¯½Û$îÀê`¥Uöj— öz¦ºDÂL‹^²T±A«=X삎¤lýÂX¼îó ÈVB ^ÙñÞùt­(C;¾õ£Rí¶á±êtvó%ᄞ½~ØûÜ„¼G1°”ìâ\ëϰiØL¼…†‡õ‚‹zÓ¦·Y¤áê Q3ÿùO/§]£#* „Þ·|0¡‹?Ë ›Qµ (<üžÌ¶¬UvöÅ<n§­TèBíI¾âõè&Ìœ7!óWýðÖvÀK…‚°UÏ¢¦€Þh–®›²>CøÝk›†ê c ©æµ"34ÙiRñØ|qf…š+ß®—âu”m2¢“ßgzQã9ð¼å:i…`!±Þ€l¯Þ\÷10m+ Fš³œh:‘E´°ô·2¨(A¡½+®sæY¼_Þk+6Vª†AèÃ.PÀó,¶ßà0-iÝ•j ²Â–c4_Ç›óÇ øåfÙ§Øòœu^³|è ºÄ="§Á¨~,SÙu³jœáû0ž·ZœžŸýå}88éwÓ@+6RPní.Ç×uUf;G«Ôe QÒR«Ù~P%y¢ÂFP%:³ï„úÝCõk×aé0”©ïBÚ«*í4P3 }N˜='*Œh?þÛÊJ^æÅ/È{s®”Hï.ìÃóO…DÒΗg;4Dåíü3cli%Ý]>Ô+ÊžEÉW~Ó¸og¥ H.ÏUn|"Å*:¯ÞÝF½Â*œüÍ"–üGî¥r}—ê ñ1!WISÛX¨ƒÞþþ:ô†ÂI"9²ŠÈÁt¸Ú‰ËíH9.·ÐiÝàº$-q’dLÙ¾õ‚\±~ZùW÷žJ¾Ýú{êæ^S¸d~‘°~OJ%2ç¿}Ú²30Y¨/ödÐs©«ÁPsè0ràE 2£Ía(|ÜýUܰóà*Ç‚j„êàð¨iQm Æ…Yܬ×ýPP(ç8–¥ÃÚúéJG…w5ßÏ„Ùýò½ fA\7Þáî-°Up`!?èqÌ–€ «^h÷îJ‡,{ëæH…øM’Ìp¥Î ß±9¸j4üA@•ÿ7ƒŽ4¦ÃÊçòÃÅË}Ìçü˜¨v Å>ü´çòXé®§ Ý%ЧcT}mû¸÷…ÿ”ɘÁNIÙÊ·h²»ðçŒ+áØ -,Œ–TÕÙíÎV+úAh,=Ä ½.Y–"ÉÊ1ØLìqŒ›k¡Ô¸ôóJxPxÝ`¥&Õ» ÎQÊám½U·±x©£-ü£ÿÆ Rìæ{`=ZþÍqÀ‚wüÎR`zuº+¹&?F)7jväp žiÙ×nÔé–n’õ¸$òÓÛ–PTÈæ'ÚSW§hîŠùˆAåèàñªÛc?¡ì˜:lÞÉ€8¥á»fÆVôHf3yì™Êyd'pŸµãõ¨‘ãl¿­¿ oTޱ]—“žâ‰/n(dدmL –­úÈN{ôyL*ûë™-{¡ëâ[rí.KÙ鳸z:B.i¹RHíÎVE¸…yÅXûê¦mŸ ¢ˆ§ÿÇ'µøŸI`ËŽ›ÒÕ·!:ÍÞd¸ž87±ŽÊ'î~«/öót€Í6¸Œÿ8äD=¢w™¢½vª‡ÓéU°Eª 7àó o»[5 Ô%<Ÿ³fEgiÿH¯ón»Œ@pÂJruoü‚A«bû™…Æ7ß"ŽRW "ê—qâ3X åpš¡J*ûKqÍ^Î8o¡>Ê|7¾Û¹;vŒ×*•½M°rðÏз瘈’h_G†Öu£EUJoÝ„²Ÿ¸UýŪeó?‹hHH!ñcžö¤T]¿Ñy º‰q\ ^Y!h§½¾nr­j‘®b ¹’éTwÍ9½•Ýq¡{¹>„6ê÷Äf˜¥#ôQêŽ å.j¡míµøM‡x[€v»öäJ"Ï.izûOD®G^×­;,ÝÍZ_d_kø€zd *qì`¬º§K·× lQ̨S»`F4=á ÆFTCêWÕ||çìªH·DbH¯ÕBy7ÏS›Ip‹å½U›Žßy — ¾™ñä®=åÚ.Fdö/°_¿w¾ßÝ3Ÿ…z>:Øí¬f㓎êÂ6ÖW‹J]>…Ψ-ûà“cH®´²qéS¨”Nê=ÿä+¿#ÊÌnñæô9îÒï }Ë»‘ïRÀhïóÿÂD°å»v'®ïì$Óå·ic´×¥¦uÖw¥ P6_WdÀ}‚¯'ê"†Œ,¼w¿%ávÔEl!å‘â ^^#ÁŽòÀdÔL!CÛÊ?ßÙ”†.|ÑÛrB›È‡p¸Ðw‘ZBM­`sÚ­69•Tq¾¬Myå~Ûñ²° 97À$£"ÙG³Ù™ïµ@sÇ–ñׯsrt»´kAòn@·ÒŽhË`Òì>>JøC·ôßCÚ΢Zçæÿ|=S%Þ†8+UÔDE,üPûÄ:SLß>ÑAíÆ­v~­ê¢ˆQÖ2¾2’MÍ1gAfè]ÍóP ã#ˆòÜã7ǧ«CCÄAaíÖÄ0¾ÖÅpr5ˆ9ÙA-¡Fipo¹µÏÄW‡é4^:ÊR4Žr|¹‹]KaKjRà-T!¿îq.È*ÞwÖ±°ìKÜ6ÁâõµâÇæðy‡‡*Šv¬ŽVèûˆJ’‚¤,Œa áw"­´õGoôöÿ³R4ªÐŠx©aÖÚ¯óÒž”çö½=Àòônúr 9Q5×?ëp7º+q<–Ò¢òzŠŽFû|.‹ðÙÁÝåcg²f2½M;¸0´…‹tû%ùµ×·Ý8Qaa\à÷ÒÁ5±ABa[6c(ŒÀ&WЉ0·Šëúœqk›XŸ–Ì\(÷΢êK¯¿—|yñ²ß®ø`ŒÖmÚÇàIŠgÄa­ääBæÀt^Ö1ä`vÈ' ’˜« ¤ÚE¿×Ls)à 4ˆÍ­‡Ie„û<ÃZû]Xã3AwÚ¶ | -ÀÍ´ž1}€§uÿ¤Cðv´¸l@à½Eìþ#y³¢¨%|11ú4dÃå;»í»M1²Cûua‘ò~$”ø‚8>0¢Zv|ÁqEe;„9yÆTÏ[J6ó\Bé#ôzË4¥˜íÙxÐ>³3†Z”H3xÅñûÆs%•Öüš<ºÎ^þÁè„•,,†½;Q´Dï5Æ„q?3Ò]±Ð]w·–i¯"N„Ú“A8 rÄB¡û{ï!–ð“Fp:‘![—…å<öhE‚ 1æÐ®R\*´± c©æ¥E„©¾'ÁÀ“·¿¯ßô“IçÐ "|¦}]÷³¯7<TÃùìÜ«š`4B¥ÎAþ¢’÷jYøÖö…²ÍFfQg'»Ï>äieýxÑá´É鵧ЄåÙA=’Ãë<LÝ98>åcE0»ß§¨£·s1B Ó-þ› vîµhfCºÙn/d… 'J{ó˜-CŽŽk@! èVÀ(qsmá—1¾8ë Ü1à¿LrÃ,’2’™ÏÌ@õ,Kë½i‹K¢EÆÚ ¢œˆ¾w¹•¨³]ÍK~B\q‡õ£ëݬ* ÷ÃjyÙÖZ{ ÇV.öÙ‘T‹éLš†|åFu'ìšâõà·\º‹ÏßÊ,ä™0?éæëÍÜumýáb&-¾T¼{®^–¦Ñ*bJ)RlÝE0ÙÊPƒè•Çüc—e ª¨š †)0­˰®²pb€Tú ùP¢³žo¥®×_m¼®*e£lÂlÆTøãó~Ýç‘Ñãu6”Í«µ«u…i /­ìÆÁ€,p_RW »ÏL@¬´bk^K‡÷wbØÔܹÄÜyXʸÂÑÞÖÛ›Dñëu—]6 "+CÜ]êë#,ë9ëãÔ[òî'ìY^½‡úBKD{­T1¶³ C¿=?|ðÜò†=#̸ØÐˆt»îûÌTj˜ “ :;¯ñÍ×5#—í‰cQÍmÄ–š1êãDóõ&ða1pq^Ýz×Måü1‰Ë,ü>´ÜD–Éз=“6$8v)BðÍ™üw&º¤ÄÅÌ%ê7CËÑ'Ið߈­£r¢êg>VÕéÞr­¤¯˜×5o|ò Òµ;kW-Ô;d6(ÅÀâ©i¤‚Ðè™æx£ÚãJ“ÞŠ˜'þ´š›lT I¸±Q7(?mztÆ£÷|ÍKòȾ¤YÆ_…¶™³ŽY>kAÃÿWºWQ"™ÚA8ïÆfÃáxÊùdl7$wÓ‚Ä{" Üͳ^ÙÅ×h8ælå}°1bp¶ûNë±-[Ú¸aƒWÿ±¾œ”ë¿”EɼtLcÿe°ò£3KÐÏò”ÑêþÞß gôàmÀfÅ™BL¾ÇеÎSOOðÔ!QÌá CÈÉø4œ]‘­µ#DUò tªïÒS®{'Lð3šÚ»ÞoŸóAu¯Ò|GZocɆÞWA8¬™œPh­cI¶7dø–kêJ•'¿Þo-.\Zr¤Iò[:tKÕÕ4ý›MàDþBŠÛU›ûcÔ¹J]i':¤Uc^ßtÿ‡b!¦JØ?_³¾Sþ#Œ ì=_P‡%jÈêD½®iüröñoá^ÄŸ~ûhÀ9³‘ÃùÆ~Ñ„Û}øS_¤4Òþw" êôqâž¿KØæZk²Ã• ÆbðÍö츟'.YhÆ÷ÆqYSFæScŽUPÓQ¸DÕÉÒÄ:#h?ŠXí3kG+Ž»åò™¤ò·ë F»ip„Ö­‰…Dù-… qT¹£•¶î+ƒÔÁà JliºÏ ôž*#=^fùDBöÈŸmNLŠZ~€^­Ñ{x`vRÕ`Sªß™tù²%<¸øBF´ð×4®G¥Ú­Ÿ¾dFJòüv &íûrN¾Gô¯dóÙd»küÔ‘²ƒvæ€{CçÓ7y<‹Ò¤GJ’D—ƒp4–ž?¯—ížéCÀéŽû%?žBkß;}-$üºb(Aœ3ùb—v›Fíé@3¬ÊD0ظýkzÁ¶†âF¦<6ò.Ç6ç×±Üpu“0ˆÊãÌâרzΰÕsÈ`…7Ù@;ôEô˜áxi`n^¡ô›U¶ŠNí çx¤³1ÆèUs˜Çêc„MÌÒ}©P—é?ê¤lÔ²ÙÓ©~ý˜P¯S¤òŒÌˆ–vG˜=¤è“³ð‡fqEŒùIÒ0Ë× g9Öuwq¹º”meÎx$>?LOX-g䣨۱JX@Êà òe7n cžMêY…ç"+ Ddgÿ˜ÎÑu¹çññâB*'ãñi´áM>+§¶ýš¥38v5u =”œÕ=™Ý€Ì͙ψĬlŽ‹7¾N†:ŒA«ÒFr©.‘ÚAý<~{0®h¸qxãÕ°v êºÐV̇ÊT}Ü•šP¯HÓˇˆ°¤Û¦`A¸‚fƒ@öbF~‡c Te9çÃGÅ«™h(_ %×ÊÕ´+ÞŒ(e]ËP‡¥ï¡{Ã+ÿ ÎõŒ7:Æ/­˜ÛU•çF¢{ežAt™UtI—†æ2jæùô-Øî2¾®˜#ø§Ú¡03Œ/OÙR‘€ç³²|„(-)Т>,Â3xÈìþNˆpB×\XzÓHÖ“û÷ä&<Èã/LÈk“DšÀ¹ |Â6MûÂØçàûïgâŽ&ÆpG­yíÃÂwy\¢Ÿ¼³¹.E”‰ôõ÷~¬z%Ä%;Ó™àÀ Ó]¹TzŒGéº)È-R—¼bÊ—Ý\¬ðUBÏØîâ®aÑF!CæõÚ½„ÎÝOL¼•‡Îì¸L+dyr¾á©[á˜J°/¨T&ª§TcyzÐöPÕ¶üOYÂïáA¥ocǯ(5Ë<3í6— r’`ö nΘ‘]U0Œ—–x Ÿ®^Ž.}!¼œþj4}¥1~ü`³Ñðï-Gƒ|äÄ|é?ãÑ4¢l¦_šê0RÝÂPœE¹‡lÅí"­Úè–~s‡^¿•ó„ªW›X¤‘fï‹ïSHïº(P‰wB_;å³(Ê~ðzÛ™."åÚf /³´óìjJëö O!žví4FxbÑŽöbe.bh9™¿9#òòW€·uA‘éö7’„æýnThy´ÏÖÌ}P(f$»…;Xõ¸è±/B¤âjøÝLæá>qìHë(‡:¿Ê™C®_’zãÂ¥¹ôŠÎ½VA‡yÙ|m›éïÝ¡p9ŠžnMoUšhcÆnC>Ç —R`^Ï£Þþ¡ƒt™«°µKÆ…!v@š"/z ¹Už.îÄ.Ð1‰ȉÛÑßG¨Àн·Ixè(Ó+AÞxØîSÄP%|7\ç­»¸æFÓú$³1?œ¦¯ªœ®<­{\¿F«ëÿ¯½¹lkP0LHHÃhÔÑÒÒÝÝ02@rtË£C:”†t‡Ò)àA çPRzÆyÿÁûÎy>ß×õHÜ>Sß"½×³­“Þ‰H¸ß#ij+¸.$Ëøá0™~'DÄŽ¾’Ÿ›ä ZöçoVš®ÅØŸ|åðºí ~¬ÜÿKM‰Ëì1]•q.¯V^fF*Ô1ö|;`o€•L.ptC›+܆«€Uɽ±Ý•6sºpK™; “단qCÞ¯E¿Dz ®Ïèo:ƒ/(¹7boÃ: ªÒºfñQz&/ª^?ha¤é^rÚ*d" %‹š‹»Ÿ“ï[YÒŸÄç²€¡zz¨v»zhO·çâcTZ¬ÿ†þ9vŒéóX"l5Іçß+e?¤ Ùß¼­¡•‰ÇÊw6(]CcvãÑä¼4¤ä‰”\pó×–DÀ>Y»ÛSüЉS™ªÂŒâ“iþ+2;b–̺<öD 7xï³SP±9hðFýZÑU˜ ‰°ŠÌ°¯;ZoâÐxy!•ñ‘»Õ¨-Ÿ¸Ô.Œ×RÊ^¾—X3¿¢’Š?þ3?fZKÍù#ɲga€¨á…r+þ¶;˜ì Ïs  e­¼Ü¨½Øµì|óý‡;œn•Nó HCÌ,ý…ߺÍ8º7ÂÅŠŸ4–ôs)´£Šõé®U„X†Bfú}4îgù>CΈѨ=ÍÄ΃aÓ3z~?ñ«ý-TU¾’ÒÐâó$ž~™ˆùîý©†QÕ§•!\ííàB›j+.HiÀ¹¦7Ï6¥<å9q ÄÉ7Š¥àn¨eoxð«¹eÑfŸ¦vþŠri{ÍËý F’™Ð \m:ÆÓ‰#¬ÕóD^—;šOIÒET¼šú~ÏPH]í¦ƒsö•P…¦ëßNh¶úêõ’yX:àmu]éØlÃ=åL5qå$‡}ò+Í£õP(Yû¶«Œ×jŸÓ“—HûdÓ$„óu5M9¼¨oÛÄØO(yTRÐËŽ{'ý’4'¾&è"Aä%…ýýR¹´…­ =–W…Ÿtcˆ Ý"WÂhC7¬}íƒc˜`+)¬ᛊ§0.ußü©3?G E.3ݼ3̸Ϳ2Î;³ÃNH!ŽéRÓtz²LôO> Oþfön/Q÷¯ïʦÖjɱbQv:¥bòåJÖ¬À4ñT®ì)ž\ëãM`¿çTLÑpæmw™«$O&O‰EæÙ‰xŽ_çËP?6eÑvñK¦a…)øÌ`Dud ;ÅiðZø\fÄ%•Ò ZŧZ(šNÊî÷OeIK4âîãLk¾€Q…I·»/”f€Ùä¯C?u¡d(Á‚L’oÚú¬¢(ŒÙ¿.pÄ=êÝÇCýL>–N·žE¡ê ûÙœ¦Þóõ´1~ 9ª^8BÄ=µoâ+uXEÖè÷.•È èÁcíÑY·Ãç$,HÛÕbƒñÏ4ó¶HNZbù@šÏâ<‚`ä¿TõÁù•nŸ0½ %‘ž<ª[¾I>†"i­K<Š*úêÓè~.ãÇ¡º>­¢Â¯Z²xî÷azûõv:FqÜ3„ÈéL<ótž­²^˜Òk×'гfËy²çõ¢Ñ»ƒå•˜Ä%îXô;¶ýd¨R1hÂD¤Î4p$Ô;ó&ÖPI3}?})e& #:I¥¤ÐuÇú†õc䳡ÃËâ°÷NêZ)åš“ ªÂŸ1ˆ&¶!>….B¬¸Q@nJÊ4ý¹<á[¡Ë¹è3AÿÀEèœpa#Š—Oýk!”±0‚,¹€ëb'.1U ¾z‰¯8-¡tIÚÛô“±”è'˜Ý ˆ yÇûSðÔ€ZPˆîƒšG-ûËïóH^†XŠÔHÿI††q¯õÓ0•\ª³ÓÇ÷Çár :’¢†ž×¼\ÿèù/D§ó<¨©öL뇄,!T=§ðóu¢ðÑÛ?¹aŒ¥õÚ*Ý?êŒíÒGÕtl»PCª]o¸LÁ-pÕŸï8›R ™örÛ>P­ûHžtHóÜÜè¥Y±†oyyÕó®´Ù8ki>è?ü„¾ ì&Sýꉌâ:Éû„ãœ` Çw¯¢ÑºVù©ò/ºÝsqeD˜jÃ6¿ÍüŒýw6þYØK\¹<©fQ#¹âHE©ûßødêÖº6ÛºªE·9GOÊ>Îó¯žeFJÇ@%’T+.•9»f»gƒá÷§„l¾ ½T|?€û\éÊiw‘µßO9k³ÉÖÓr³"¼q½SŠrX´nÖ0lM2wÇü¥¿ìîï\@%u?³ž¿ì7›ôâ¥ùö²d[ÍÒ–ZNGêFµ™\IÌõºËy%/ù2s6Uj|LŽ Ñ;ø}Æa]à Ö[}'{æ?)gD&¶Ïp>•ßlà€8ÁWsŠ+æŸmÌ‹ÑÑ–‘Z.Ü;;“Úí çn1Ê'QÏÉî¿2§@¡:¼4ðq¶l™ÆYe‚Ų ïkFîý¾«!t1aIS >·Ø—n…$ ðµX*ÕN½Ö¶2­¹¤ý–öƒJ„H›²Ã³à çÎíë>¿>"èHX±O2gÚ Ž¾]³I…XÍC:-Èâ(䉘J·I>'2Ô^:½VwNýrëäaÕF#VÀçT{ö·YX~;çíвոo@§íèþë6Ó¥mICBœÌ˜©¶öK5ì£Y‡@À>ÃZB§W†è§1}„’ÿ”õ+cˆ¢² ¬/Ÿ© “` é4™œïɾúøïY½…PÂ0(Ýñ¶~åÓÏŒ4øÃ©Ñ9ÒWiQÍ\Í5wzŒs1Ó· ôŸÝÏ]cu1ÅÇÑ/Ö–š­s¯+I‘d°NÊ_Z‰D‹UVW/ ñB¾)ý|¸ûú$¢À‰¶ÜÄv8»¶h–Õ~V[d>‡Ì¬?})pøúñTVõÀ”›ÿp€´fñž=7f§7A!ðÚø!äf ÄWµßG/2ÝþˆÛ;Ž¥:Þ(ÛZÖµT~û%Û=#‡E]Áƒ½¾Ô~6*ÿ·gâÜÓ³—š‹U¼H´]Fð­ä{Š6nÇ•Lœ”?¾­ bÍÚ¶û‘ŽÐé0…8òxù‘´Å2@XéÖA·0Œî.jþ^p<+‚íK2á`N¨LŸ;b§­s›9¼hš·í¸ßXN™{ñÉ=¦XÚuךl—‰Q Ñ¡=ãÜÚ£ÖÙH©+j;¥•RIÎ'ï‚àu- [¾Êÿ6‰UsiG OCÂ]ªaÿ,tm#Šõ¥Óê2ÍÊ bq Æû8&‘® ç¼ä›ž)i~ýjå,ÀÚâu}”ðm9ã¬rŽ\CU>/¡…r“æU˜ñ Zu´æŠÔèé[}+H`•Ïv¬Úæ«–‚u è‡ÌgÄzþõÛ”Ö4ÖI6niÀcoÈá«!Œ¿Wýë'¨I¿F$©1ÈÚ5£2„§&–Ëz怶18C ±Äj7ú…·-G -Çc-ïè\òjTµB ÖÜÍSÎMû6¢¼Å #% øbv_¨W˜#'VArsE€,éÚG³¶ÜÅÂûÙÓ7š½"kÖÎðRŒ€ÿa¦:ˆ(9,Ó°.gÀ8Q…p9Õcäž?±¢jÎ%òÆ)ëQjs9V@”²n,Úm–& 5Ð$ ù©òÎbl};òç²R?v‡€¨3æU$Ëå¬ÛÝ×AÌ~…Ës𣶼ð3ŸÅ©7=e\Õ¦2Q¢*¿ùÚÔyXïL¨î‡*f²*æ*ã±F•ìd‘­”‚Wýl·ÙùÆ…ÌébþѶK%üŠñ¬bÝKƒ#­œ²Xˆä>ç#lÂâcXîú«ò² þɆ蛳ׯ³sh¶»Ipaüs»¢3$2ÏËÐ’Tr<|hªŒ®ÏC´.GoƒUWVUê¦×å•Ý5†° ·­ÎMÀ;[|%¡ºü' ˆ>=à7aW±Ÿ?ÓÊŽ·ý|žqÖÿÒ¼@ѨÑé¡HH˜ûßk¡Â¶=_#ž„káÔpìá1Dl¨ä3µ?ü4‡mÎàVÉ5FíËD³‚øÿÅÿÀ€úº9ø9ùPüëòòn endstream endobj 135 0 obj 20173 endobj 136 0 obj << /Type /FontDescriptor /Ascent 871 /CapHeight 0 /Descent -278 /Flags 32 /FontBBox [ -74 -309 712 902 ] /FontName /XOJFNR+NimbusMonL-Bold /ItalicAngle 0 /StemV 101 /MaxWidth -786 /StemH 101 /FontFile 134 0 R >> endobj 137 0 obj [ 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 ] endobj 138 0 obj 1659 endobj 139 0 obj 19280 endobj 140 0 obj 540 endobj 141 0 obj << /Length 142 0 R /Length1 138 0 R /Length2 139 0 R /Length3 140 0 R /Filter /FlateDecode >> stream xÚ¬ºst¤o·&;éØêضmÛ®$£âtlÛFǶm³ã¤ƒŽÍîèëßûÎ9gÖùfþ™™?j­çÞ¸6®}ïUO­¢ü*åèÒðr°2²2±ð‘Š)¨ëÈ«Ñ+íÍÜ\Õí•yÕVn¤,, XX()Å]¦  £ƒ„)ÀGª ° •˜“²±‘²òòò"P’Š;:y¹­¬A¤4šjÚ´ôô ÿ%ùÇ„ÔÌë?4=]V¤TÜvŽNöÐ_ˆÿcGu€d µÚHÅ•Ute•¤Ii¤•4I¥S;R73; 9©Ðàà  %µtt!µû÷ÔÜÑÁøOi®L±D]IMI]æÀ¿nOs€Ó?*R'€‹=ÐÕõï3)ЕÔÊÅÔô· GR ƒ¹›Å? ü•[:þ+!'Ç¿öuÁT]A®æ.@'éߨ*RÿÎdm ú'¶+ð¯šÔÑò¯¥…£¹Û?%ýK÷æ¯d tp%ÿwh)7;;%Sû¿ðï5CúwϘ:þ]5¤ ¤ÿì;S—ÿŸ©=ÐÎëçõß­µÿN÷& 2ýÛQ«¿Ô°0±ü[t•z,T€ skRKS»¿=û—\ÓÁàbtüåö_m%edeaùo: k ¹­Ã?$pþ[p°øïü¥ë_ù3ëÈjɨèý¯vì¿ Uþ¿V2éÿˆ¢­èhñŸ‡`ÄÄ=I}Y¹xHÙxXÿÞ¿¿ ñ²q|û_„üëMA.@OR}––ù¿ªÿŸÿ:þ7IsG‹FGdê`ñwÚþSð?štvÈJü-…—ýß±ÌÝ\\þRÿ¯µð·ÿqþ×m<æ뫎æü!6Ù™ zœüÑi ýÁ~VÈÑP§²&’¢€ZÇ>ÿŒˆ=Þ*“·ºP¦æY¾¯•3§÷C9º£ñ~l;ê¾4ÀU!á7rÚ"´mª.nú£ f£2äÌsíŸëe…](=.­£ŸÓªjFßß`ˆf»Ø]டiÈÝ‹0)žœPüÌÓ㱺Q›ÁÐë‹ÏΩ’OžŸ¨‡'ÆFGún¡ èóâá)ùÝ¡©¢œó„õ4«|â°èDŽD“dï‡Lu_ŽäÕ)¬€€â0)Oüú¶§âÕwÔÉ’¬Ý#)æÅ S•-<5•'Ì`™RÓšX&ê¯×/¥NSìR ý$»ˆd¨þtõÁñõ“©[öGí#n Á&Ä~ù®»–0 ½5>lûŠÞÈ;æ³y*@ÚÇ–n¶¤8t–Aô£Õœ+Dv´B×(4÷¾9*{íÔ˜²Q_~´®žß«ªÃpC5Z´$Eˆ“½_ÜÌï·2›òY²±²}yttbmj“œHÇE\µ0 µVHˆ’"Ìït1Áú…XÜåAñªyµ÷Jñ·Vï4R›HšYã«ÛÏ%‚ilD7OcUtÎëí KHëƒà=— ñ$BÑ «Ï¸pÿÏåMðù6'¿ë¯~)e¿CQ/©×Nê៯í;£ÿ÷XÇ¡6meùîœHW*Ž_xRë R]x›MU‹jÕ)pæ÷Líµó“®.Èä­´¯¶,Ê44», èPŽ;²ïWãßb0~ÿ(üôÎ5~®çµòº%Ì‹a/‚”i%ˆ¨g…j3†·Ò×Ì)aa#>A¦wÍéG%ïS&ùÝOɤ;]6h‚־׺˜3˜?Fô^z¼²÷;>·3 )M]7G#̨*ìKÑÞêØ°¼¦P5hÅÈË ¤(ôùºõëUÐÓM èbÊÛXß;¿i%ÝÕ[J¬ ^C·Ô>V¤:áÕ“Œ ç†Ôsà•~Š@t:²áQ0[ñ É¥ Pèý¢"®‡‚¾5Ñ)*×åJÿZKîþ¨½SzêÒ ÇS<6qîV)\PJÛóÙ—€6d¢¥¼à 1aRgv½¼?@im—e„¦”:F2žex:ÙwT 0÷ŒÍ¡X7Úøåû&®ßç-³\½™¸g,•ƒ‰÷ƒÏ¶pºÁõÅÝa ¢A-Ñ4£x[äÁþEȈ¬‹sšç ÞD-*DQyWr¨“þ«V˜ÞzÒõD˜sн ¢_L?©~s˜c$ ¬ ÚúÚµ„ô„N“vbÖ,u Qn&¢+ Ì‘B¼Þ( #°f'¸-Òµ\¡„ds€©üƵ( š×”Ýdzt¹Mn —âlÒ9Iíèè\°55犹Áh§ûWo3•M°!'€x6¿ó-£¾9=rÊ–TcýÖw‘3¹õu ŠÈùð+‚)«æh½–îåëÔâ±fåÅ…¿©-¤æ<¡ËO¯Y ,þú àÍé^ŸøõEêõι±á" ˜¡_£³e2`Y‹¨ 8`ÅÞ iá$ Of&H©á¸Ú”úûfñÉ™È Âv$(×ãå|ßqõÌ0fö™<-°i]&ƒÜæ”ù>‘ á#¤ul/c@§U¤¹v²å®Œæ×7ö]ÖfÓ¢Çàux¯.2Ó8:œ‘ÝWÝ?ôË[¶/ºÞ ÜÉ´5MV¿éï²²ÒyãHop&sÛ:›:ÛèÃËZû”ÏçYÙ~ÃP“jÀ§í†@n%JaP>¡Ïa~½‡Ï™ñÊa€OI¾qf·Ï0@âBdÖÓñxkýͤ‹¶½ÛD„óœâ*öûÔF ž½ß2 ”)в+r3£^›Õé(¥ø>€ƒU¹º̶FŠ9„a÷4ž e´ŠsB3ß©11ù2ŽvˆV4^¿C;ãFéÜpÊÙæ=Xg{Œ«èqSaû!$<Å °Ø´"T‘†37XY ‹žœøß ‘hçô Öâ\<ÿ}*t`Î-ôæÍþÄ(|XœÐÊç~Ú¨Žël»’aúH E4¦šôýlAO g÷»­%ÒM\®Õq:¥¥ný§E—a|ÂДN1n âXVâÑÃËú&þ]yOÕú;³ü¦A‡¼ò¢¤S³H-¨}â0Ηñº^½0O_ñ>«OÙqÑxºNŒŽ%qò˜ªáŒˆ”_xXÔU Q*ã²7ð|‘°¥ÅyߌfÒ¨7ýÎQ'{‘nBå‚/C2@µDë»ÚwÌ:ÒŒ˜ ‰FBâpþªE3¡ùøVûÑb–“ÄãÐya"ˆ¨ÆÌÿN•UÚÃø7»áblh!Á­¦»[“_án8†üÚG’˜k¦êþÀh¢ú%™½thïCÀÓˆ]ëCS˜@‰šg.^Â\p±nÌÉLÏ¢±‡tùÉÅ õha¥q[…B= À!ž¤ ÍïŽû»Ýçé\VZùM"¼O6Ñ[î"³Ý9Ê{*"èfQBÜ™2¯VŠ B‚Ë~ÿ¯ ¢DÑq±@Ý›¯hìÜ䛞ƒƒáV†®XL£ìégfc°ZÜ{èâÑag öÎ¥ö`¿ªO×>-l¡×h·nbg™/ñq–‚Ë&ŽK'ÏyzÊ!~m«pJŽVGÌGÅVt¢h%I¢‘V¬aÔ±¼žûò{)•*PÕS ¶W“Û-{p…Ï´ë°\PÄFwÔ@ýÎ#Hhr# ’ÌW` |”®]IâQûZ9OñÏq ÕÕ›ë¸Å`ÐC$8žØì¶ ºèLÖÞþHê$ü$i¾·]wvÁÆ#ö—ª»ržÒÉíÑùY‘šk=}¶e®ó–’ûI³Të»ò=Ê‚¤_MCy¨ƒ}ƒýÙÅt£S£¶†j½Z¼Hn+Ù>4 *–¤`ní<Ìw<†²¦LŽ8õ¨¿‡O:|ù!'oðy¶k3ßÞÓŸþ ˜µ6C쫜îÕØˆ?…iy¤1ä½xŽG >,‡¥ØàS^έ´ìå€(’ApŒ°ààãÊ£”~7Ö)ºpŒ‰Yk|Ôæ1Z}ª—}¿Ï·v"·R]¿&Cýмö}£Ê-úÇŸoÖ0PG}¡ A–h q‘d…Ë6ãê=“ÜÏ‹‹žàLrñN=¡J%‘g@^x[-ì¨ótüÊ‚IKgî2+Ó©¢×ÏÙºƒÓXÍ„MÁn‰¦ßË×Px“û,a‘ÑzdLgxe&Î#¯+Chiv‹ºg:ñ Áj¬ÆúٽୟFüÊ;¾³³zElyU=K¨ILÛ¬e½IÏbÿ8£QÀp÷E~F¿ŽWøOGÉ*ˆ•”}Ñ׳åTФ>;›¡²Êi¶©®4ž=JÊ„6®¥õÄ»>NMëJݖļWÝ0$cY)`‚Û×>/ Øîó„ÅŒAÀ ßìbøZ$„‘[($–‰ùüèÌ–l®[0 8ʨSK`v6´k¶_D@׸[#˜†ê¡cHqòÚ²Wß{:¬’MÎE4o³MéîÉÞQæä‰ÈJbSë½½FëMåò•ùdÎ߸ÛÌóO'å<çŸïP HåƒPÎ(§ævO,ƒJfeâ•6I.ï§6bQLÌ,v¨m²é*ý`ÿ†ÌUÊÂì.1#m—x˜\K›S¡BF [•û€WF‚24Êuˆ*˜:é\£BȆºñð)aÅ{­û5—&nÔ¬Â[rÖêB²¨@Ù™>8÷ƒ¹?|*F¯‹ÁXíˆWãGèóhî$å hm-?‹e–›¬IŸ»ÈtŸ‚Ç,½0—\-‘®Ã!Dœ*H*:ˆž¸=³ïµïÜuØ`ß‚å&aß^‚j†½(ƒ+»¨S½v­DŸ¸g^tã[‚Üh<0%ê+ƒ¶ÀŽQvþ€  ×ʼ|®!ðÕ;­Ç>­&”1’@z ï¾.1¦èî6L_wo ò$KG,ã£á”Éflì^¡ín Êø Ђt9™>í­Ã} ¸WØÂî—+Ü!ú· ªÁj›çLH›µ4#y«Ò:~ÚP€%Ç’™h©õjÃÎ!„y¶(9ð¡ò3}"¶±Øûú «ñÓ]Py g’ÆÆMTQ¯ê :šІTé)~•¶ÝòП6µæÁÊ*DÖ_x‹f v¨5Zxµß¤ ä3+lËè+%€‰¶Žh³'co}EóRÆ6Ó˜âŸkU˰Ü<…ÿ5Ï™¥ý–jTbù%)¡6HújÀ2&Î+8cEH­ÔZ¡RwØ·)&¾¼½X®ËÜòD¬ˆ„D½ÿ†é¡zúL¥è`q[¯zÉAÝõ JBè®óüKÇÁíÀ€J×xMá@ Úßhñò¤3ªxˆ?FpþãkfºPEËÞÚúÙs©<™€²ÈoU$¾èØJ§:OßJ@™‹¯ðú|ÿW_h¯ðð"ØÙðTÜéí²c˜Špœ™r$Ãʺ{ÏÅ–5ÕÞ )W|;ÚËí©„ÈƒÁíÖ´¥¶~«K5ï}†Z³Ðmüe&8ø+@ ™õbœ3th’Ù)W_Ù;ìò·£3ÍÄ$#­à°¥ï$S'.)zÔ n<ò?Oô©*ᥡœñ´w¸‹Þ÷µ}ŠCÁaáÞcÕ¸6‚b.|ÛV)± άE ”ÍJão\žà |H_ÓdçýÁe”™‚iQØÄ•g±ªoœ¢¯„OSbù~Š‚²¥¡u~éRsŒ;¸õ‚0礨LÑ æÅ/LéÚSg÷rË"1+ÃC¢˜WŠþU Ü­Å„í´ÃÛP eðß.(FÅr0d¨¬Ðd¿•¶2w4 ¿'sÑ.zü¤¡í–rÀ˜ÏmY¯S‘?<Ó=”Ì;Óõ<øÃ2ó¦×®¹b‡¿Æ­œüÞâV¸sTYÙüŒ½u¾÷¥*Q“ŒVá[9DÊ*ÚûSÿ!Ál¶4ÞÀ?RïX="QÝÄòEÔññ@ûcšcµ5ª—¹qD¤ ¿/aÑŠ ªŸ6³ÐÀ‘Ö¥"P©0#°i@°eXÞ8”Û.‡ xšó­8¥z8Ý‚x½&ê›Yµqœí´Ç‡ÅJ '/w¡6R£>y›t#×ý‰ðÓaxY°Àú¸£ü”UÃPŒ"yh¿×êøÈå^ʨÙ`n’ôî÷ñ-{‹Æ¿âTê~Ì@éÃ@“ÙC¿d½|Ÿ<ÖV&r5d„’Wÿ:ËŽ¯òÅ7 ¹¦I‰tø…6dvdÅm*å¥1I¡¢¤®Ñ{.šÙ #lá3þcÕm݉žÒ@ߘ4=]þÜÜnŒW¸QWþ¡ Øãóœ¤$¤“ÜÜo)«ÄÐmt“ÑoÞÙo¡ìïƒ^jõQzPƒîáÂ8ŸºSÐ×=xÌa…#›;ÚÅÉ?àðL¸˜+B->,OË‘±G—ÛÛÞûE1·E_|\IxW‰äðÛ&RQ†RV{9ú‰Éqþ ÄŸ¯y¡EÞ->6¯®T â†Bã¨D¼À“Ê®8rìsš™¤Q­ø¤TÐ\JàÓÞ|~FÍ€³1àÀÕÃU~¡áÐ7lØ1Ñ8 º‚ã›CLí¸EGsGîxúcüZ9'ä!#Î|wx5?Œ ™„ ¾ª3:òàß¼¶©8æÇ3(˜È>µK‘š¿:#/RU»;ÞîÞ>b0¿ äy‰K#o¢{ÌIŦ€mYÕ.CzŽ|8ß}?&G¥·&¥²25$z”1Òð\Â{á…2N ò­ãGè‰yÏf$\«æ÷€”,ÍyÀ"‡*3h$UB¥.öûªÔÝN[‹ß3dÀWs¥3š}­Ö¨Â$˜ã™ý†3T$I½KV}Ú,*wìBÆ&˜ñ„鱎Õä°Ä~ü’;Àl¯2’wò1ñ·×Å8Xª•7ÖYÃmKRB+_šbÔÁ¾M@çwÝ-Ùò¼Ù¿Ñ¿ƒšJéÄbãYè»/5¹0`œ'(Ü ùë(nMøøÍD%uÔÔŽfõ:áÀQö˜­¡]¤[Ýí–Õ%I)óÆ@íû9 ;è¾?3Q» ‡¯ñ›è·îúNÁŒb|Z¨¾½_âo~²7Dcqƒsz¼¢Eæø½hLJ àgùcF–Wó}F7å^Š´XAîÃUÖÒVc«è–T©=Ã`rBη¶y")[Ô!fÓËæ£³š^ͯ(dQä}=šÎ‰Ž¬ãòé#|Ûkz¬li4YHŸXç;- ÑYG3MùX§f#¤µÔG}Ñ3³üúTA~=ªs»åæøÉv..ñšé4KvW\­ý'lÉ®þ½9¾`VçlÙcè—OД*=llÒ‘ß¼;¡/Oì{±¦C€â^î€äv´³w—©6)7„¼%Ì'Ëþ¬Ýó±vèažšÞ¨‘¸.ë‹È­HyÖïLjA; ¾Æyƒ‰ñv_–ÒZôû˜Ì£6ãcRÉž’DÆúÎýÜI…-u>.1/ ¸ÂW“÷9ë:oý+ΰ5°vÔDïCPtº”ðÞž _8‹³Z ‡öS--µÐ5‡Ÿh®€€VÎRýE óµ?ûÑ<‹˜u˜Ë“Û¼!Šp¬zN@iæX¥'%ºh³íÍÆ"ÇàgwÏV±Ÿ'äþZùA労¯.[^:…„N-f†Þ°”cñÎéz’¸üÅ4QËéLˆ~m‹¢,9èE¨r.»j`Ö–jjU k_ƺü-Îê™>§mð€Q4a{1:Oþ {4hsç·@=±ï»zÅ ÒÈ“ð4™ò4„:êá(Ì>!¶Û²(…”YjÌY¯?œ·h[`“ÆÅLØ$E~#¢­S-RfÌ­œý¶^AbîË+ÁìÃõÏàÓµ÷SY=êßaÛ§…& ëH;CýÄ”3ÊÔéDDÊí:¡2—zí R¤ç ÆátÞrÃOà³)«)\u!%(Žä Ö÷0“§üâŸ+kYnVëø“qaKŠ¡ˆå³õ áR†Y‘±½ÔS×ÊÞ’Û !D2–Á5વ"÷ÝÔ`ÛYÕÕÎmé 'y*kÚýzfqúj§œ‡bæ÷5ÇÙß¡½ócÄÄÝJ\-§a3+B¤blWØ·Êx¹±8 ‡™½ˆå ºÍ©’êý…W»X‘óÄ‚l‹ÞÉ­tê;Mîé!í¿˜u‚½‡cà¼ïöã3''9 wg=é)]Ì"\æ €¿ŒQPZcЬTž‰s¸ÐÚQ'Ùb^?#¯¿r‰$ï‚?«ž\1;›KGs‡¿„Ø^©˜–L‚Ø"›êéˆhëC¤µ"Ú&ÐEž‡Õ™7 ƒ&Ö[åGßH1Ip ‹©oJa©7y²õÚ_°IݧçÙªn¡èˆ¥oï¸OU‰ÿ7¦£Ù O¼à¶Ç|!¿€¥•S¾4‘Ûø_æúAL€‘¡¤Fs#}b~Ûâ•D¢´&¢{í×—RÁvÕ´"Û;¤q,<àBÓ÷ÃÔvá:\Bx .dnë_c|,1†$M>:‚È8Œ>™eÑ9úTm­…+1:”ÔÎZšs”é}dJWø¶t5ž3öÔ# Ù°…_úÇr+/8¯‰.2hê‰Äêb( Öݸ&l|ÁGò1‡á—·æRÓ¥B"¥š1W÷™/ð­`[a¦4ó åjƒ!§ô[çOˆ¨‚†#–·í­ù’“èã¾H{ާ¥¶Õ6è‚#¾xþTä}@úoçqJÅíÒÞ¶lm¢äÌb–:ç†ËRŽUpã€#vÔÑ€îþÁs¯cØêz?êÓn¤z$bV@÷¡Õrø4¯JÔˆ0‡½^ô T)WÙ,_Púöf8âUì7v}™&Pg$°ÿIý„Ê_Ç…¶-mŽS/ïþ†¦ óÓ,ç#p>£ðç:Ö£XoêXv-ëàÐå©´m:¸$Šòȹg› ÆHiwׯ»`#µòÊE}8[ýXáÖ¥ðWÇ#—·L=ú¾ Õ#αü(Æ—Äý [U5ë!;ϤéY%\ôš`=‡nDPô ™7â5Ûi³þ4Ú9ëŠƧó§ÈPïx”«‹úˆw–³iª¾¼d8T?~,ü×€&Õ´Q²zå™MàƒîFipò 1߇ü/ø¨—v£8eꂬr88ðßÝîh[N_Öú’àúœy­ü,d$¼Æø¶œ>‹~|Ò&7:OõTÝãÁ‚`.¯wÉ×§ŠØ{¯*_ÙpDgp£šT|”­*àe¼ïÕ²x£ë¤3šÆ•Bã?p<%uõÕ°üŠæQ÷Œ¤Ü5'om‡¼ëRá§¡íQ•wHD×8¦}”‘”‘ÈëGԖРauöè©»€×’@ï ®bK ‡Ë¥>û\;öQ_ɇ7Ί81Û"WbJÅ­iN8B÷ï,ŽXrGó^‹ï¯IXfÏ?[ô+!#Žá’s1rx‰{uZôµ;¹ÖM“’K’Zâ¹+ŒóÐmdÓðêˈª-=W •µ—¾ Š3ïÿËø\Òhdü5‡s¿~·žÆ n<}ûdÇíéCÀL$%¬GƒDDlùõmÚ‡oäÍJZ|Šå)9:] #íQÕ¢Ô{9/MSoFð)Ô@8¿Pe´è'€ŠŽÍÞ¥`_I˜aæór_d9˜%™…Ï o±£„®®þ«œ|jqoJ{“ ¤iZ0ö·Ôy&Yú ˆ'b‰ª]‰,ü†ì¯Ëjù ó~õà ½ÑNþó].À?R?sD›ÍbºFÛÕ(MÆÈž³›ÒŠz©|!oAÂGW4uXZí÷rp'&\à•Î6× ÈN¿íãò äw°Mû‰rõ„ßoª4Ü `;ÊVŠ¥þ#^Ÿ¬ÎñÏ"—È{„‘|+Ø ÓŒw…‡•‚Yǃٗ^>CBèDËUAdd¾Õ_!`<[~­`Š_jZÆ,ßu‰Z²7.úÃ{¸ùU'Ï¢—ï/¦fùxgÈfs˜õ! OÿàÜåö£¤WŠ †N»li"~l\Õˆ­e±ME%ñ]hGBÇ É9ê±cTsØ×Ewe¦g?Œ¦ Pôs¨§,V—ã±ßO$ñßÉÔ¤è¼îJUÃ{×ô=A}/tùK¯“೉ -!Ý{õíÂ÷ÅÆ÷/“úŽ@«Í“R5’ÕÖé3ôÉ”Õ@ž÷°F¯à½§hC17‚5œØ˜àA[Ëpwç%†²ÆW?¹ÝíÞº}„ë¨:¬¤Ë­¤è4b‡+oó÷}Hº¢ÎÂ5£¿HuïqHQ¡Z.kŽl»xSDVðO… N뻋n¤3XphUš¨£IyÌÄ‹µ7I'ÆÈ’Ž¥\> *y2’œ˜Wi6É,í ”4iÙ‡B¬©m‹ù¨i––’J ´ŸpI\ ›Ž%£š¦!ÀÄl {O"¿É‡@cù2“Òû|Á=;èÖìq°R\ü Mò$a‹4ÎÏÙØÊØìÜ =wwÔ‹  §ZaÝÕ³÷ÔhQtõµ¿O£Omn^ƒµ©/Ù$LbNŸòr²â¿ïVmÅUûºcio?ª‰@ >LHáÄ¡W÷v„+‚‚øPúŒä¯zɤoŠš‡–_y Ñ÷Gk–x³ ã™Í€mÒg`@b{@§¦Э$ Ž:aÞ“Åjd}×÷`G+E^¶‰$|øí}!¶R0ÍJ’Ñ#@ŒÛ;Vâœ:-ùöÉ`–*iJÍû§/Lýd”!6W$ÜŽxå6é|Åysç%´%<8[Ë/W>5~bãèýùಇ‘-së›YLƒŒ ^)ü+õÇÂãR0X¥5̬BHt´¡oÔÀi€uNi/ÖП´Ée7”£Ê†­*'Ÿ£Hk´Ûk´'ÁJ]|M T\·÷Géàû[rvêí/ ¶… ¶ˆ{´Âç7m1Ö_ôßî¸õ ú’Š:u «é«oÕîÊ?@†uÕ.†?%uœðs,në|Ó³ùý í1úÆBÝò¹‡o‘¿M¬ôO²ú¼’꽿³ñ;NÂEoÍ7].}›P®{š¢Ü£ëô‹o§ïu7X\‚Ó@AHEÜOƒX°räòhfÖwîWêÍ>{{ƒ'OïBqº¶p¢>ëwšeé¯6.ƒÜ\Äz¥¯±ƒ ô¦09‡µTðmbUfORÖàE[X¼êævj&9ñœØVذ`òÄÕEè=n+ð®P²œÌÓP²é‚LÑß´ ÝûONóé˜~®ÞÒAäjµn¿-ß%îuáçzÐþlU<%d± <Ï·¬µHª…Ð'ŒzCuy~…€ÙíOí—ŠÉ,÷ÀÓé‡Û ý’Ô‡É$Ü>œeþ:Â'¥¾€3›™½ô±åsf¯‘J[“f›3AQ=ûvº'F¥š§™ã†£¥æÿ\¬^ ¢UùH<Ä‚Z:Q-°Ôk?qÔÀ§^µª –K3µA–†-äñô<)ý°FIµ1/ûõõéçÙè']»ö½‰žTe¯Ãz‡OÌå2꾄`%0 +Ó–¨Áxßk™P^eV”EL-UeÏ@5½ˆqPJRf×w_5¶G‰Þùb 3£[Ïë­åU‘£Ÿè‡fpQ¡Øœí®–Ú¦ ˆªQ*‘ä^kcÞ]K±¿î5m)¬ c6&y ]ék¯F¬ð P§Õªs=NòØ’ž|û)´WÊ« zYu¼æBLÊg0þXûh´”¬ûV¼'@i3ðJa—ÀŽLJ‡ú¤ qÂa±.Yë>o(DJc#EXóYe c–\¸TjœÐyϵ«2Ô#'ÉKD¶o¶€w·þy(#n/‰¹géGßSƒQ’$`ëM9˜ xvÙè ™˜Åôˆhlä·™± EÒØÁª£%^u£ð“ L‹N­;]ÂøyºLÙ|èGør(ûò¿Í¾?^¹²§áÊqR¸á4ÆÀR9ဠ«!F=ýó­¨÷øTâÇjMw"¾¯Æ¾+ÊW™.A¿P\cÍXeÕºÍî‡@;‘uÞò®ÕÉøþ/,´f·~í× $B¬’Úaˆ2.ÜûÐty²!nr+ŸE…E¹×Þ÷±RjÒÓpè¾&r¸Dn¯˜ßRCV>4ýʹ¡¦Ùa-Ï b Þ%üa#eÄ–ñ‚ð”¡!Ú~¡n¹Nƒˆb)y|Íøü”îbðîs±dÓ*¸¹Í,äØîeo«µ65Ù!A»t-ÞçQ›9ŹþT kúþ¶@í\»‡ðºqà>*ŒCéÃÝ-10Qk3ìô²æ%›8§ähÏF{7øEÁçé2_Ñp`MÚ+â4ÌFŸZñ«ã–×€E¼ƒ€ËÖ-›“Ùæ±O¬ñˆB×çó ú]ƒ}‰|oW£©×]ef$3Ò¯c¹B Fò%;ÛÊ`žjÆŒ ~«ø±1ÓNSœÑRC½¥”ÅÂ*cDú¯Pá8Èp¶“+cƒ]9¸rÆÂ‰ag„䢉L·ÏHC‘Æ’¥]^û‚:úR}]¢â\lE‹³¨Û%Æ/ŠmÑçXuüEbÑAð+_,ê÷?²ÜΤŸÉVvºÕ^©­<{f¢ÍrÕiÒïM$žUSl$³”MðŽ]sè5î„Æ$ë‰hº±ZÑ&*´ ¯gÈ9|§kàÊ%M «g›®ÀuÜ}_Wà h±´ ÛYæU\´HbuŒÔ ìÌ x5¸Á„^q Þol’‹çwK„SÁEB`ì™UÌ„–¹D«Ek8»œ¨Ô´ë¬×ø¥˜û{P‰âUu•º{U\`”é&—½­àÍ×äÄ·Ôù´õÙ~Uð:$£¤#ª¬>øå£öv,—Aˆv‹Bn,ƒ]úMp7ï×Héâl²†/#1[Hu½§ZªEH·­f7åØÝ·Õ}nç7ÅBòw1•/!šöÅQ,T_¸¿Gû×~‚¹°Z>±„hÂöë(:ŽJ"Ò,qæýQ—P2ŠÇ‹Aè75šÜúÞó•cñÕºíÏÖÞ1CÛ—U?±‡*VÇ!;ßRv–k©u­k´[W†Vl9VO“¿Å’eˆ‡„6  Š^U<†ç«µ¦§ÚóO_ oÌÔÓÎwÊ@a˜¸Å«m³õÛÖdÍÞîTæâÛX¦_ö¸`OÀì.æå¡„¼%KAë“­¸yê’E×$Ùq„fᲬçE¾«fÚ‘ePZ&B‘`¬F·-Ðvyбcò‡²nlß#×àÃÕv ý®,'Ü0®áÇ’úÿ RÃy¸Åôÿ,¡G7A×ZP8Ëú%¼»åN–«àvêFzEåЪ݆÷ǘléìî=@œ6cÚ+5%¦mzŸ Ò‹þ…³¸±úê:˜Ð§¸µš¢L³\”ä%þ²Fƒ˜*Õ.–ÖM*Äp¥×goÚ``O/[æ?Þ=ªÖóJì"L†ÃáÖ@ ódž\/eìŠÑ¡DÂ'—p>2Yà©iá{6ár¨ø+½ù%“Uy`WáJ¼ 2Eç@Ux¢ãËÒ±•ý6ý”/”ÒÙõ,‹†5 ¼ÁoŽNL¤ßUy¹7´„=¡¨)ÅDè÷Î$¼Ú#î·ÌCŸAn!h—8Þf ›ìÜ­¼ÒïËRëİƂZ#€”°%ŒµØ_< hc.F3<ãpšKšäåŸñ(¹4Ü|¹Û‡÷yóWˆû«ª‰ ñÎ ÀÖ!é¿£ÞœªÆ¢EÄèªÚmºŠ„gò`R•t’GÊcl\ýØ%[Bcõ/˜+RAä ~i{]Cli[ÈÖ¼ÀÇÿY=P¹à kAnSÑ+rˆ=×[ªXÍÊEpÇÜê¥VT^ž(¤6 ×'唺Osᯅ¨Þ$Çóû¶Bê?xeŽÃå]ó<ÚJÓž NÛˆþƒb‰š’陀¤JBE/rv©#ò¾÷;ZD?uìd>XÕH[2ÜÜQ0´ÛyB×ä©Kä áy³R¤è Úô ÚŠ—7ôv¥U¹‹47é ÷&È3P]ÇH÷íJpµÂ¯¼nƒ†@9R”©wpXÛì]ÁE1—ñ?,x0š‡_8&y˶¾ñÀ* Ξš½á°~Pg.%5'^Z|•M3Zûxï¼4­føžv„r¾PoJ]v¼ªeÛŠr¾‰2(”^éq2¸{B'Ĺz§å¦7YZ‹eñö r™:¸úU™û[*”舂ʢùSïO²•VøxwÄH* ì8âÀùÞõf•¦¼ðÂíeì{žÂ‘ݨ†G@’oõ(q¢~… ›¿%3gœÈü¾ c*j‡¤n·@›«š©6^ïBŒ;w‚658}t²~‘ÃÅ¢ÎÇzv¬ÿÉ?žíEØFƒÍ,ÚZ:ÊïGàku2|ôN”ʱ²zŽ“Ìèð™ZTWµÃNk•°„ÆÄ¢ŸNl@V“|¿wRðè¾BövàÕÁd ©5a«<[˜¼Û‘éb‹vŠWüizj™YÌHLMZßÔ/ºì^ŸË®ÃhW2‡DÕbñÒ›zÁì¡’¥Œy7Sðk§ù2®Ã|µ=wØl)Øîð”x¥x<•Š6÷´Øh ÌF9Jûh0• L÷ð‹¦ùÓÖì«ß>^Cϲ^"ïBX™P—þÀKÙÝýh@éófô "äFZ5.‚œß‘ýÀî)'µx¡¾×E+¡´LG@À“1±>sžDMy¬EXµ/ž"sÙg01Êga[ÈàÝd£ùÌ:þ¥ºPYãr°Öš½alMéÊÿã‹òšøbYZrLÕ>n̬LiMöËÛ¡`®f–¾ëúdùqM¾Nü:i‰vÝ ÁaûÜÈTW‚|{ÕŸ2£3g:öõ)ŸôŽƒtz ÷´o Žù±ù1å…‚’Ô0/`ë%¾pÞ Yw`Ö…bªƒ;;rªé´O¢®Šá…·p«*ì'ï{2x|sSdù!½-DšÁr"¨5AwÈ^~7ÙðÒSjZ®òæÜƲ^â§ÿ²}Á·˜kM²û«;ã#*×jÆ>[iQe±Uw&¬ÀÄCMŠŽ·ákµR‘Bsž;Ü,Ï´úƒ°CfÇÇ'£LãƒÔÇœ«×Êêè0`Þe¾º‹é­q½ ÇAÜÂ2Ø-õÚÔ„¡¸­noØ'r¥Xµ4ÉFI³2ÙgMG %Zër·IjqPmTŽðÞËÅ„¦}ˆ}±„¼‹Ã7–‹ÏоÎlî BFÁ€t”>[qDЀŸ&ò6ò3¬yÊú7$yšÍª¶½b "æ+rs¶“h#LsÐBÜ;j-{òÃ}N.þ-ü‹CNÊZC;ø¾ÞÑ!"Yr!Nd§Š݆¦ôó¡ékRE%þ±—çRòQžu¹m¢î›@i G¢B[¿àË–s‹€×‚-œaH—— 12v ] )PëçMpå×÷øŒ‡ñÖ&}šß>¹@›g©HFu„ ­ðôÕf>ž‰§™à7àö»”Mµaû-÷ïsè„HD„³}½ ÔHxÉ%AfɇªŽ\®UÖ1ð°Üœnå&\2 ³Áé(ÀlU×k›«@ì/Ÿï“BCã_ÌЮÙ6túÀ11ÔS HaHi냓Ñ=´9 Äò=ÛN:ÛûJ6 ®môÅ™ÜJŒ8Ä3 –?ýŸ.?þíÖw#ãÀñ3³gœîŒ ™©3Î%[2NÙ²·³Ê8Žl‡CÂÙe“½EöÙ#+ÉuVÆó{¿ð<ß¿?/à{¯«9)¼dÝ KD%[àþÕˆ.cÿ°®Q=û¡9ü˜Ñ)‚GY]”Ö®§×§§F àèmñÔ|n^Ƀ£È&Qot§}âO^AuS[Ç׎™†B2õLËWéR:ãwbc`-Uxó@‰€Ð¥gk—adgðyGs*A`6àÈÙ AW·-Êõ4P_Š©ï[ްª$F5’S#r«tŠ(»}‘)h1°`ÖuLm¾†˜âËŸñÆ;Ï)îÆ^Ï;?b:] Z~kCi¸L¥‚~¤QNÔ ‰3Ž•7whžýQa!ž ˜iô”AÁR¶)l©›uÜXWŠû M¸…ü”]­MU©Î;&‚Ž¥D¾g PÀKôCâ}0³Oürc ƒŸ ™Hs«“+RèL)-‰÷úÑÇÈïŠ?³ä``3ÆB(½Ì§ú ¾úˆƒ«„ƒõäÂá8w§Ç×”Uœ4›T~6臿<# ¬¿6àéÁ‚7{$=B Ö“.O)>°¹Jß"8îŠÍu‘ÊÒ=zÑi©(#£ø.Š#OœáfH”iÙzÃ:|³'ɲDêÕ9H­V7ÃÌTG+ã™3¢TÙüh :Oê½sD•îI‡ù{¦ú¼Ê¥0‰*|é$J*BdB ÜéÔÞÎuí˜æ¼Õó\6UæñÝBŠž7Ǩø5ËŸ#y_¢!Ú.÷Su©ç¬Ñ1˜Ë¼š‰FÐuh2ãö¥3§Ü­1bË”·b¾&#óŸø6OïÍò–o²æî‹¯¿ŸO© »}¡ìm^ŒŠ×ÓÀîÔnÖþ¸ TĨŸŠðK×áPkÏ¢=½/¼¸¼*É›ä…ëu)¬œJÒkhÅ#ŒrG5ÝÐ|ïƒì(9rHU¯©í¼ö',£TsÏ ÷Ômbì½Rx“õTÂg‹ûdëqMS šÅqiÁàqýöKœæÙ žêh»‹(ÊGæKG!+4´tÍ“e-ÄR™¶Û¯Ï£›ËF‡Î¿þxLrÞô9)R¦\òùð˜Á"ËT®B*«U t4=¬ùm±lI˶hô°áöuÐ]·Y|‰GGõÆLªõšƒÕdB²–ja#¿qô'GíÝÚêþŒJn‹b ´$Ç©š>³ù ÷Ž"ùò°â47UNdë·/Nmœ°íb*ƒ÷ÊšI‡´k0 š…¸["=ÏÿÝk¹‡qçþ8pŸåUœb Ó~òÕÄ8X= xPvE)Ç]1ì`$¶ÁBYÐmRn¨[/ÍGø™Ž~Ö¨!Fó‰|$ͧ¶?ÜynzËåÊnSÈh³:OqÓ±áó>ÏòèèÆŠ•ú¹Ý Sv§ ¹w£PÁH\¼ÑMr`Ý(Ò³GCJsKµ’ÉýŸJïZÒ’]“jš.²ÛäÏŸÈýнÞLPik2‚âÑáÅêóstÍ(øjjyüM%tHi’¾ÝQ IÊR;§£YA{Zc@šécÓE-ÂÛfÏôj 3c‘Ûxz¡^ßl³!ÊåÈ%€Zƒóײ>о¡0ê,5 £íC©6C`“i*ºQ˜öb`øŠ!Ýå¼ÊV%Ï&É,öÞ¡¿uµ‹V¥{Sžßþçï–GF LZuk@1[LÁ/UY»ìDr¦·¦^?ØÂ O·­âà÷“¿©–:/2SêøªËcp‘ [FÇŸÚBÚ«X`*£=<ç³ÚÂÎôbjÍW´+Ì:ðo.¦ÐÌg#ÂVfïfÌ^mM.,èLM“[«¸WŠû8†·Ä™zuûx~"øò8Jo^J$™Ù¾î%(òºÕ±ƒ©)€Èàå«n®ðÛn…ÜnL%/}/Æ~‡UÖÔÏèb%2øÿ=LÈ'^c‡cËL$-m^îª}f*’¾«Ê~â“›vø7âMiÆë@f©Ýü‘YôãÑMHÑÊŽ7=cÚñû&_j$Òé›$G^ªÄ×pÎvç髼Ât{Fvó´³v‚¿«à(ƒCk¾¥:VŽQ¹¡yüM4ž›÷l͉bÛ§IíÄâ ¾ò† µ‘Ï þÓù–¦Û­‚£ðN)žà”àqµ˜Ä{ÅsFÆÎ†_ùÂh»¢ö¨P>=UÔî•\6·¤†ãkÙ§œ%LÓq³Eȸ±ÙãÐnMYƒ_Ù«À©G¤Æ N߯œIBý¸Ž£¬‘–^ðŸzhÏ"å˜æg¶ßê#YqêüÍ(×ü»5cýÜ×ûƒ'îYˆë…"b€úÑö|f íÈJæøäCÏä8O]ÈÅ] ÇÈ#ûãSA"’ì§Éj„‰:¿à¿pÃH‘\RBœ3&´;z§Ù¤/ ëiÔK »°!ST+›x¤XÁXÍoïlÜðÏujCøøŠQ'àµý •¨EQñ‡Š9ÃÖ/!zÜJѱ˜j•òì;+9óáV{§`E_ÛN…â¼µÛ~˜•þ@Á¯­èÚ*Òõž@w 5ªÐ9]±{ 1°Ã‰Ë§0¬äêÕl¶)Q È1 #G)¥Ë¼ºm7Ìõ›“‘˃p㜴«”6k’Ì[l>Z Äy~Ê­Æ$uÙ·HwÑfÐ÷û­}+ÛPàì·$‚ó=öîÎÏÐ ­7 —4W¢»S¼°g5»p™hOàúEÓ_*&ùÅ ½:ÅXÅİ“ŒR¨Ý›ÃܱùŠ||cn¿°nÂ/ÕgDyä8_Ê“çwÍi_|Cë’Hû´QFp¯$xògì˜z·nËhh¡a~ITI’¡ Ölš]bcû\íx'WcËœâ$ù&œVîàWñó>e¿þÍ¢WA'éQd¤[iýKûËïs•BÎVy=!™’å{—{ª5”Û¤@IÙE¸Ô¾~X³ír¹¿TÂRú”‹4±sx—÷½S2±àöf.VçÇQ¨±Ÿ²0Õk‰~1Éÿ'šÿÿ*ðÆÕÎáãáfp¡ùŒ ÿÀ endstream endobj 142 0 obj 20209 endobj 143 0 obj << /Type /FontDescriptor /Ascent 924 /CapHeight 0 /Descent -281 /Flags 32 /FontBBox [ -199 -312 1031 955 ] /FontName /BLSXKR+NimbusRomNo9L-Regu /ItalicAngle 0 /StemV 85 /MaxWidth -1230 /StemH 30 /FontFile 141 0 R >> endobj 144 0 obj [ 833 778 250 333 333 500 250 250 333 250 278 500 500 500 500 500 500 500 500 500 500 278 278 250 564 250 250 250 722 667 667 722 611 556 722 722 333 389 722 611 889 722 722 556 722 667 556 611 722 722 944 722 722 611 333 250 333 250 250 250 444 500 444 500 444 333 500 500 278 278 500 278 778 500 500 500 500 333 389 278 500 500 722 500 500 444 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 333 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 500 250 250 250 333 333 250 250 250 250 250 250 250 250 556 556 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 333 ] endobj 145 0 obj 1653 endobj 146 0 obj 7713 endobj 147 0 obj 540 endobj 148 0 obj << /Length 149 0 R /Length1 145 0 R /Length2 146 0 R /Length3 147 0 R /Filter /FlateDecode >> stream xÚíweP\í–.œ`Á%4ÖÁÝ%¸'Xðh¬¡»!8Ipw·àn N H€à‚‚[°!ùæœ3õÝ©ºU3çß½»ªwíwɳäYïªj&:¨BÇÃÌÃÁÃÉ- Г3Ð0TgS‡8Z¸ÂÕ Nª2P+ €›ûÁ‚››‰I! P'9, Ð[äÀ–^^ˆˆ6@êìƒØØ"̺Úú,llìÿ’ü6XxüCóà ‡Ø8€n`¨³#Ø ññ?v| ¶`€5Ä ÕÐ|¥¬®`VT×(‚À0@Óõ¡K€*Ä쳬¡0€Ã_€%ÔÉ ò»48ç–4ÀÁ–7°»%Øù·Šà †9Bàð‡o°œ=@@'KW«ß <È­¡r†A,t`šP8n ƒ8#Q5åþÊa BüŽ ‡<¨PëK+¨¥ëï’þè`´Ä @€Ý¿cY€V¸³Èã!ö˜3 ò' W8ÄÉæ_°``ÌÊ ‡?À<`ÿîοêü—êAÎμ¡¬þ™;Xsbóð>Ä´D<Ķ8asýže'k(€‡û/¹•«ó?tn`ØŸ1? ËC +¨“ƒÀ lÍ¥E<„0ÿÏXæü÷‘üo øßBð¿…Þÿ¹çè¿\âÿí}þ;´‚«ƒƒ:ÈñaþÚ3€‡E¨~¯Àï]ãâ þ?|@ŽÿÆëï†úà¿2ý öw2ôÐi'›J8xx9¹ÿCà w°•&ai °9ÌÀŸu øÏ0újP«~ãÈÈ@Ý^‚<^!a€0?7@XˆÇ翉ø†ç_g5qqÿÞ ÷?~ÿ:™ü FÞÉjõ{f^"@NVcöOÁöà7SÊr•ór‹ð ÿ‘ZºÂ`œÿÙ­øÇùÏ5ƒÝÁ–Øß¦¡–bAv)驈j²ìÞ!9£®NÔÞ`ç¢:‚<ÿJh‡_JÈŠH™ùMU0gý°è]“ÇÔ®óíú ÖþNR‡gIàŸ¹Ô> ,Ÿò-Bl\¦ES÷ô#¼&U— rëm¬ii›Þ Ó ·ðÁ0.XüÜòü‰Ïñ|-“k£IZ ꑈªów÷€ñÛçÏ>éëíé8Bû´NÅ–Å$æöè10Üß%‹JÒP·Ì+”ñ¹ü—ABãxéaúy¯Ç¾¡n"È´óüZ9g„c%O*“bÃVž`<'0Ð`nïW¢:Eb\!úOy˾ ™pÝÝ­¯J¯”äɤ"ÃëJ²Xü’ ¦˜Yó·úN~zUº¢à£âðþÉÍUýS›Ÿ½ÝJm÷óîYJÁn[ü™ü<ÜÓ@‚ ‹ïyOi•fL[ù˜ïck‚ èÝñ«O8¢&¨z”2”2õŽ QeønÅÔ‹ “nGüî òxKºU‚¾÷SvëUd”rð5ªÛ°_i5¨ÍU¹ÏAosŒq¢±:3XȨnØÈhªÎ@»%E]Ò©-c%sBþÅ‚’ô˜£Èò•|vߨ¤†ßÒÖ¶tÐ<ßÒ·ˆ$vãuE`Nüq~‹DÆZë­q”œú¤\péòuI¸r×±é ›ÌŸõBBõÍå å/uÊ0[ߦqPo5Ö]0=¥ž1Ð „ubŸ[§¢Þv×S$ÄF–L—(è­~bü Ov =ø¥ç­¥¸4è°$w¼]loR÷tÐF3µêãü„¹çØs$_C33Üiááæ–¶J5èÝÑJf"éÍÕɽœPºš§•šB!^0ÉÙ;Y8÷N€t ‘3SÐ:ž0¢eëu‹‘§lk_p =ev!Ÿ:ƾ­ž¸_»ðsxutiOàj E‡‰fi‰ZDnó¬y> —‚æ"‹m.Ðln€Kÿåã=¿‹ÈëÔÁŒ²gÉ"M• ¹ß4WÕ‰Çbsv±’ÑÆz=ûäè$JƒâЫ¬œÄ~Çá„=Oëñ¹EÛüeyOç½zm¢x¼æ†›~¼@öê§MÕ—êG/ ]¼E¥|b.oà!§Rß½2÷Êk‡†¶½ ó×›efæV´¶÷Ï’Fd­15VîИ"ü‡ïë6œ÷z²l–SQr‚¤L^à>{Áò“«“š)V쳤®ŠkíkCà\íÍz5í’t ®Ý®æ@½ž•huK¨LiõKœÜþÄàv¥6hÅ€4F¤©6&†nßL™øŽçÚé<$C‰uPñCØPÏKP k™#ìµ?¼sË >½„zш·fÁÔ›s¬hß¹ k 3’­›Ø`#ŒË›Ž õ ls÷©]ª±zãFÚìE‘lS¥eŽŠz6v¡Çå{q×°‰Òê2ÒôTc!ÇÙŒ»#ÖÐü¢óÙ§—Hxɦ®OFIìeBªï Œô¨&~îvo·$¶Qƒ“ZMC{äñl{ÈÏ–¾$I# êÏRßMõŒÏ…ùëJ¢q%§Dª<´æg÷1q˜©uoë7ðãF¨“Jaä)zv,&¯Ñ%Ä,\W‰d׊1–’ÔΔ|*UC%ãšÝ{¢}nU۱΅ØÈ0þA ·ýYÉ—öìÔ(M[ó}²FàÞ©jÓKÛ\cg‹¬orÎ^=åE“%hÂm3Š Ì7÷ºNÙXðbwÀPöy©­bÊš†òOÅ-7ŽÖ©o3ñçQ"ñ8ñE€¦»lwü-žH½vz¦bÎʘgL~toG\l_îôeŽõ|U2GdPDßÏ­Š¼}X©lB/ù”ÐëHßkœ¸Ï¡|?·LªS2 ™-ƒ#ÖƒwäF4‰Ùpƒ>°±8doq lÀžÙ¥ëÊR$hN.\ê~5ö~Êô%*.9^º8ØÛœWÆQô‰ý{„‰§c×›ÊÖ Q6“—äDµ(Ë3÷ù7t]Ê¿–¯!Ç,ŽÙ0YåyuÝZܧé3†gömkÒXµ5‚(qÕŸÅX¾Z0¿¬tÛ·½äðöø:0ƒµ;í͹uö>Â÷«íÉw_3þfÇQCñ#&%ú:£v{µ½>ÖNÇÆÉxæoPºØÊúÉ}g‘W uþ¤ì×êPJ/š KÕvó•¬ió÷p˯øñ©yþF‹oj•ÔÑ0Z¾-øóÅ DB›E-SBç.óËà™¶fuv•¹[Ybí;GÎâ7›ÁóÅ çÉ>÷¤asÛ¹.öCDè©SZ¡/Ãß`°¡ fæä ŒŠ¹«5í×þ˜IC§—­¨Ûó Ú)Ê^½~ŒGµˆSù!åãRE†€åH‰Yð=2i<·Ù2GÒÛÛ£C"ÖGÑiÉ‹Åa$¾;Éí4åèŒ 6¯Uº:ÍÿoænÆ]Ù¢o¸_ĵc„ôV÷ª9¡0w›½cvT„äÚ (vƒ4|U)žñ'k’ç±KÞYrÔßèd—öÔ„ú}´õ(·‰Û&’¡„ e­Ñ ël’Œ²Å[¨³–ÛcÆöÅmny¿À«Þ BêuvdY¾HMÔ›Y¿mŽRG[}œP "‹By2ÆçÃ]Fâ'þ™ëzjÑòq;õøè§0iJ·9PÌÆ?þ]ðZÿ2ª¢™ñÂ/ýóF0 #§O`Ø›×ÝLÏ4¤!iÒ•xÔÂ+H”,AQO•¿WK^«_×RXÄBšRnm<nôH–f:à ²qu–ê ŸÄ@­ø^±íæD©sÜ;mKž)ªd|Û=Šãzí!Cªå‘ç1ÑÛZè ®í&¦Ÿ)/0xðþKj:P‡V‚;­Wó®Jlñ½ „8›•*"§?om²(lØáÐÏŠ|¥ï,pÏŸ|ØaþyÔY©õDÉ£1°6Èœ‚ÙûKOoAÐÜì1v¨³ÄÎ@òÅt‡| þ*¬[{®ùÕ88Åq#m¹I´Ä %EoaióPá “¤˜Üs3‹ª˜–¤ëfr^JƒZG×6,ÍÐû¥ øÒø™[’’—Ôê$‹/}Œ)–ƒbTí,Y3}gç°ØC'£0óô'Z)«†‰þì/Jj,Ë¥/L¸æü"ŠßZÎϹæNÆvý}0ŽœbuQ÷fÅÈ$ì˜Å5 œÎø9Etˆ(?E«å•<¸ª½[D;‘R}UŽAŠlÉUÎ8/{¸¸hçæ©÷t7*ZÀ¯îrÈMkn®.f¥]ØççŽäp¯™ƒš{ÚWÕ2-EÛq2ôç½7´Aú‘½¡È=ô1”y‚‹Ê{'qèþgÆsÑ­ï¼–l¶Wäì”zs”òÎs½ekr> ÇG}Ù7ò!Æ"€5$œW@×ùõµ|:Tê\sÏ2ÉŒrì©z¡wW;Y C·êéªé©LÎJ®Ð/¶–¶ç­¥lÐ8Ã^äqH.ó-éé®ã|´A^i ®oŸª)Ͼ¾ Éñç0Îìüæ:o3w@Xz1ÉÄî»d˜ ËîëÒŒ¡{ JýAÉ1c˜Êü©ŠŸe¿ÌÇjѪžwYJæ«w+´G«¹Þ¤5y¡‹^4–pËÌdÏÕ$}Ún<ÜU?Ð!/²Œ¥ÁŸ—Çl—6±ç³pð­°÷Ú#¥_ÊJÁçND‰÷WäZÎO= 5Wl2rÛkKIBl׫lûò?¼-ÒùfƒTSÌŸ¦y·AäÄûH»%ÆN*ÞØÞŒ`èAQu ðÉ%Î[·Ô›è8'¯)HÖº+žQI’×4²ý”lÑÛÅ!{vþ¤L­7É çùm1Jõbsëòyaÿd¤7D+{*G<Š‹Ûýrñëýªéjv ŽnœB¤J‘BäÝcÌÇs¢¯·…eç*œëA6¢ %éuÜ×7júc/1ïŽR âz2I2 ^Oצ¹)i [L𫨤KY”ÊÊ´(Åß¼»Þ:gÙ#}lËáÿ• ®^¸>‘;ŸøUçOâfìLjÌÝr=W)S'¥2úYé„Åu…Q‹4Ua5>c8¢¥QYñçSÕ¶Â|xE*DWÓ6Ј,ØÇP퟾$Žz?LòQRöl•Ô•NdÑyuÛÖ’Â¥è´0‘£Tا…ë{(×^ÐÄØ™¿‚zŸŠs”ZtEãG‚J¡NåPræÖcßÌ}lTý%¼œc±5ø9^n|ßY‘gÜ=ºœN©©xãÙ—îè3žL³ìÂÃnŒ6 öP ÷Ò¿.31EFOÒ¬² g‘gX›”+2è³âö`l8¿v¬yêÃŒ"$¥Ú¾‚FË<¼jhvéâ¬lyFùâ Ro¯6ÿ´Â|fš•O4«j:M%ŒÊÚˆ m[Ñl#';1 rUäÇ D©õß“và¼Ô`(×aówÆB“2Gë~m1cÿ¡¦Œe² ¢/àó”*=Ba9¾ã‹N•1Ö#µ{¦’µ¯=Œ.­ÅäÉè+×ÍÐàïq¿AaåPâî¡/㘴‡Ú%¸ÚðZ {på%Ëb¬2z"Tµ]åã,™ÊVörOW@õô–Y-#›}v)3‘û(ÃZþéTõÝ]'¾¢l!l¦‚xoêt[gß"Ä6ΙéÉË÷Aï8Ãw\Aå•SgµJ+¤tÚ}ò¤èéÌ3£è;áÞájjÑ­ê0ð¸ÌøÚ¿ê¹ù <¢~]¹ýœF’k×”'õWÑ^.°Ș|¨ù¹Á€ð›ØyJSwå|Ó±L½cw%.3Š ž1̨_~¥Ö•4ÙB‰{ì¾åòýë·L ·á\ŒÕÅ»Ë{‡g¼v¤#-mv•öS^™ù‰}üdW)U(ZIQù´[¦hj¯(u¨ôôN³Þ䑳kwíùÆÖjÜæ«Ömzn“ߟ³¼aw’çÊáÚÚ¸[Ðë7Íx} ,@ÙJavÌÈÈ* –ÏšfÖS¨ª³üpžÿ틜¶½ìÇQ³TåTËð)[À÷®·à÷çˆ[ñ9ìîã|€NqÞÂí@­ÖIyí4ó6$PÑCO¦ÁAÛµ\«°¿¯µ×8©³ç¤ûmAÓ!Ê› ц›œ6n>½·_CL¿:˜µ_8*¤ñWwtô”æþd{Eï%.µŠsÇ>4{äæ9l-жx,ܧAÌn'ïÁýh±Ílyމ̦ÂÚ.OÙô⟯GÐú»kÑYå\<5˜½#ýzžoâ,{Œ_i¨¾/ÌØ|2ÏER×–x%7>ËËaõé]ö˜Êc»=N§WÚÐ}Ì&K£åÊãœ6 5ë==v~÷rÒ7ÜÌ£˜QðaùדNÞBÒŠñÏ…^«EeˆuÞ~‰|b?‚ LeCÛ¡¬~ÄЯóC= … ¹.ž}¤<ØZ3WÕhBqÞúñxß)‰ÓèSÛç6oÿÈ®Øq¹]°Uª‡Gœçv&ÿqæG>InÂê]ïn$\)¦9—®ÇÅÁû_•PÇUt¾(Pœ\ z‹öó’1Yuj¸Yè¡ÝÓxÍi~–UÔxJZ!¨øÖf¡zU„I8²XñÎK»¿Óºn¢úáŸÙæìhG5s£Žç-þ{I·GC[´ ðG<Æ$Þ¾ÃÛ¾ÓsV‡å\R³4ð*BˆÂ¦eIK¬D—öe!m‰wx•ë^ÕÇyŸ¢ó‹‹çUæ?öMcÏÔ¬œ»†ªL-š;Î7½r`jîD[Cïm¹p£?ô(:“- dXÎ3ÅËÏVàThYÖ¥0æÃcܲ9u§¦CøëS²…\aíbr~® ÈcâIÉ lÊ· KÕJrì:YIßдN˜ðc‹Z»sÿ ’ªS?*æÌ$%éõT Bÿ ¶L1ÔŒ:HOùµ'|Æ¥f¬((Ù_î0Λž„a„µN´Œ"SÒÈŽÕu‰f8Äï™íÈbˆ êHÈÌR `âÓ«@“kzCNx5Í)¶³JÑÉ| ãÉÒ‘I»À@sXR%PI~Gç54¬3¤€²®Ó.ËhG(G0{·Y²½ ¢DnVUçA¸qLw©SIo2_ŒC„®ùÓO3R¯qó2áê;ÜK[N’ã•[«½N™cKÆe«XªûFªvuºcT®Oi ¿ý¨”¾ÜöU«KL¥õ±<¯.=@>C›ÜͰÃ(¼r‘g%9²¶‘ûþ¤J!cíp’ñcÚ è¢è†×gpLDžXþ©Ô΋•¤ìËû‘„ïŒSe«’œ‰ï"ñ>½»*jÜÍ”“Å& IQŽ,f·í` âóã,y2úš.7Ì<§ÀgàºNb›Žß¯ôEéÃdµOUöEîwïz;–½a)Âm<{–eWõYTG™yº0Cäƒïâ«–¬¬hOÛ1NÏÃû~i-Ô={ä¨ÁÖ,I¢z3Gu½,s{'c==™JáIP'] è‘Ö ²ª‘À‘t\ôm ÿè£õ·dy½Sh¢,ee]0±µÖÑE4]{ÕH¦çóßÙQ›F9w€iȦáÌäˆã…gbü΢:áégЕKçiCnÒ¥êŠÌ÷å¤;âWõŽº¨ƒÒÙ:Rø¥³ƒb_"×è§k]>æ¡Yo|†lW•-e§*¥Q¿«œù)Ó¨œLÚ‹3Å(òkÒ7䲎ûz`:´#‹ƒ´ q¡X°ü²®äfï £¯Ý,Ή…ÃIšò õQË©œp‚6-\ÚHÎWdkž…J¿?6ñ4@AÝô—x­jJƒ¼À)_VÙ =ÎB®<äõ ¡O8£o%ÆÃ¨C”îM=PóWô“ª„Šoêå²pÁÐhÓÇÈö=8 ÂÝu“ç?ùFÌ/zI"W«‡j’ ,òúǨ6œõéŽårˆSÒ*ÐW²Ìˆ%B×/¥aȇã_oªÊÑÝì*vií ‹¸¤é ½­P­ÝÆ.z Ñ£x}Ãê…›Z4îÌ\ù÷†ì6–+³­a8§Œ!Šƒùçþ9nʃ8}ņŸ%3IÂ3ò®½p/n*)‘͈QÖÌ´·vý7K%µÏã…÷ÐÚšÕ??ò3>šÊ¡©ì¨Ån©¢ºÞË‚mˆ\{~,Ó£QÚ]NÌÄŸë-Û*ús¼ù’~9VŽ>Þu¥/2Àr×ðƒ 4å]ÏzFľYÝä—D™‰Ðlo:ê;¹†5â¦æˆ(³Æ´á†˜zqíW_ ‹L•6NÂÚ=#dâ³Þ]Òéh˜‘–íc;™"/¤NNJ¼PVM¢9©¸ðSšN4œ¿¬¨É1{ Æt¥Vª¥kŠáQGë%! {OM;Û±"êÈÌ[yÓGí˜\_.€âp>$‘„µù¦af¬JEéÇù#ðåQnàtxe†¡‘¹­žáë_¤C'¢<‰;x³qï–Wг쿊e ¶ûˆH9/-Ü WÂt’*&Ppº¨,̃óbÚØoÛJ¢ßéÕÖäXSì;H*²™°–æv|ã|Þ<±ÖJEݺä Nd< abŒ1ž:ö½ÍRŸ+å£ÌïÊöQT!:ù¾™·â1 Ìý– (#}Ovú¢>µö© hµºWF®NÉ4]0ÿ²itYÓçÎ3©væ23ß°M\¯¤ù>ƒ`û|Í-œd¤’%xòD`=þæÄI#GUl{ÈO“±lÈ}Fâ¶ëKë,¼œÝßîs¹u!tþzØ zbr“ ¬ˆ'\MYÿblóÚCõgÍòôvÖä©:YéLw!»+Çnz°)Ñ÷Úå_Á³$o×î²åíŸAÄ fºÍèÃd׸HóØ(QÓ|Ñfž¤®ž¤ÚõÑÎb0Øõ…(u—÷4–¶á|Ûu§6!*ŠˆGå·ì(mjª%Ó4à+Iàj‡‹[ qºRÏ~Üi¬bP}æ¸=…øcy$dü¾Z¡$|‚•Ûíñcâ™WçeÉ\e z?¼8 ëJ}ç“‘ž¯*Ø_?M¬ÉbM÷O‡»V^/»Ñ=Cêe6ÏÑH+h¥TJ6=ÍÁñMè¤òä14WÕ=2î_9û§1ŠÜ»‹ôë\¸¯ w¤¡a·JîáTfêØùOɲE¥°þÈ•òP³=jõºš¾†œµîœD4ÌDk¾£jBÄÖ&|]½z¿ø¬f⑇‡Â=C‹E;ŽNX¹ >®aI¢+(>ªý%?fטË€t*¹™àSè&$ÃÚpžW0Bµ¦ã€6;›wmˆû‚ê>Yo‰_“|3Ú›ÖXRÔRêL,Ùû¼[­„qŒôˆŠ 6¨…"e¶EskbØ*6Τ•‡Á,KÞH¦D®êÛ–BùEÑ¥³= ‹ºr5>ù…î•¶„رd"îr¶'›fq­}ñþ(^çæTצ1Öùt«#|iHBá Ï³ËÚL¤â!¦Îpfkk-pÁÒ>³0Z¤ê«!OÛÀð´Ë y$œ–5G{uJØû˜¬o8˜Ò¡oôÊsÃàyÂç»6ëï·7¿¬±Æ x~º ‡®ê–ï­•B"“ÜÄ«çkÉ óª6;/›€„_ \™òCè3€F]Ú¸ óM¯ø§¤O)¨b#ç,: sIÓ43rÁâ™ J©é2Ö“˜ðùÒœz>Œ““Ï7ªj™#ÞzÜ+#öÊN¯T_r»¦N¯,g¢ýZD„Éϱ_BëóL(iÆ¢ó”4/ž÷rœŽô#ZéðÜuUF`-Þ3€1?ȘM§!Ù“¤ØÏ>+ ¯Y¹ò7w¬A/)idô‹=…kü÷t“Yš¯5÷ˆËÄ(¶>­.£áî̉G—ÿØð;aÐ(4…©†\¾M¸›,èøN>ö\‡NE¶ÏŸÃõ9”ÔŽ¦‰ º².Áxû܇ŠRxR4¢Me3ûÓуÛXøª0 aJ‹º¸ƒw{ŒÖUzT²_ïšëúú\ÃÓM§VF½W]Mô9ŠÞ ™^>ã ŠI8ž„N9óœ?ÜñüÜ*Äa}±ö^[xò­Uøb)p$^3þ‘ê7 ´Ã‰´@Å%bÜÞ ç¬’ ?JGж³™ã‡|º2Á^ Èn0Ù¸+Y‰nÐm.!Z·¦ ”ìÚÈeõѺæùí FBW›>`ó»<_ž§bÐJ²+HR?ÒDÓ?ç°i#üºSß#Ó\ÂZnQtC³nvpZÆÝÛõ‰Ä›=´êèF!¥}ãÆT¤î»¾ê™wBYG¶ áŽÎ„Ò$*ußø“>Æ9ï+ž@Ôj†¦«¼9ø€¬ëhóìËy~ð$Œ÷m6„*ªFQΑs[‡”í_K¿?Æ,Oèì áxu<!p÷!Zˆö«ñ"’Ï4Z%®h¨å¶º°–ö÷þŽÅH5"Ú h‘Qâ+ßày!±’ªI.@•vo(ì}mia«ÆÍ{ ]T”Lº”çzF?¥¹t–\ëÔ’5×àƒ‘ÃØÉ2jÏGL} «[\^àÙÉXucéH™ €×D;#½›ÅZ‚Wr´ÁAù’L¨.k7Åž"Vm“äX“†½ß<$aÈ©Ú`™‚ösÉ(¡·ŠOkXKW[DéÝOò¾P±E«¢ºxO1ES^6¾¸K8!^:„GlçWMóx5¹ǵ磰-ߺ"ŒÖo3åéïµkkŒ›í"ÂjŒ\e‰Ûv‡IA­¯ÇÒåÛb Ò:^)…PÏãWIè¬]å1ð¿ËWk75ɺ#¼°Ìvˆ—PIñ›¸€pôùòÜ?& ʹçé§ dÍ–A#¼ë¹›ÙËÖýò=À¿¯",˜ÃÙk,ùAÜ#á …¹fÅëhd¾Â­Þý.‰•¢T{‡Óÿzk,ß1Ó°eøS!B!wókœ¢Ì¦:Þ°;Û89t<ñ£õu¥4Åq/ÎëYϾ÷VèŒl'UH(tÕIŸ1tò‹áÜ›û}è~,|³+Ùn|³Ò…Ô4§íxŲ@1b#CÖ¾k„—̇Þk7=ÊÅü±¯‰Z¥á{€;á¼2àðãQ¸¸pÅIE\ «p¢@ÎéÈdÊjñL—·Úx@žN;øâêW{{Ù”óþâK¿Ufí]¢Õà3]îÿ˃ýÿ þŸ2°tƒ`¨#fý•Æ endstream endobj 149 0 obj 8596 endobj 150 0 obj << /Type /FontDescriptor /Ascent 871 /CapHeight 0 /Descent -278 /Flags 96 /FontBBox [ -92 -309 871 902 ] /FontName /VDXOZN+NimbusMonL-BoldObli /ItalicAngle -12 /StemV 103 /MaxWidth -963 /StemH 101 /FontFile 148 0 R >> endobj 151 0 obj [ 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 ] endobj 152 0 obj 825 endobj 153 0 obj 1374 endobj 154 0 obj 540 endobj 155 0 obj << /Length 156 0 R /Length1 152 0 R /Length2 153 0 R /Length3 154 0 R /Filter /FlateDecode >> stream xÚíRYXim‘ˆÆ†f‘OiDLR·$ì$4M…¶H TR¤H4t@6Ü@@!(²Úˆ+*"¨8 hXE7ºã‡Ò(¶Îi§¿¡æeÞfª^êž{þ{Oó›.sÆDŸ¨Z‘(ö€ééïèénÁâpÜl…¢Æ(ÑÔ”…#°D€‰a b ;;à.EÕ Pèö4+{š5Ѱ°ˆ(\*«YæS$:`\ÀƒE€KB¡zFã I 0PxOˆÞH$‚ï@ø$"¾€'AHˆ@D$O tc€> ó¥_Z;ŒóÿLµyRGD’Ï÷Mmé—:X NAd¨ìÄx aÇ/&ïrRÜ/!˜G.Î,J¸W—x>ÓôªÏA¿¿ÔꃘŒé%ê… JuÓñ('óƒiOŒ.2¢›ä\râc½&íæùY\-ïÕ¶@Ûyõßsö>S.Џd¡êZ1Þ¿£Žp–ý¢ý’¢Yü¨óã›]á»ÿþD9?ƒ¿b8WÃNCüž÷jžuÁ˜òÔí…Û²Æ >)ê{ÛÂ{´3íöåqfwžy½Õålšjuñ-¸»'£!zÜÛkÖ£6¢‹ ×Ùë~]¤?Ø¡´;¹ûUh-ßÕÃ:|§ßQ#ñòï†9:í¦©·dGz'¸|ËŽUÅa-] K]^y?oÁñc#Âe–ŸnåaÌ莊lŸ¦‰Ô ›˜[UýðÈwüz~Ýãè¯_̼á>²èÁ'c½âÖ¼’¥TX¾eÿ0a¡ŠòÃÓÕdDwcyfcÌ¥1Vkd‹÷¯e–ìŒI.zØÒö2ämüüªfÚ³.[R\﹟çõò¸–’ÁºÀ[¾'\­ «2ŽKz$&éÁ’Òãçà——yžÐÚx#¬ŸøÑ¥áh*&m¼{xH˜Ü·r$®¯ÁcÓË”wž›Úýœµ¨^-=¼škæÛdRáøYoÚíÔuàVÝéfvVÍ2üMž£:¤«ÎaÕ¾Ÿl õ¬3<+k lª[F`SîÃ-6Ÿ¨Ê±å,îX!JÛ¬Z†…ŸShVOx×Ú48Î÷ S¾õ©Ž®)âÊ›u_ÕëºXÙïÝkÃÈIŒVŽçVƒŸÊjwm«4«pv—Çi'cÇ bRY[ziL|u1êªì7ñÇ*d©~óúÖº¶ÿ2/Ú'&ca¹}t‹ÅÎE¬Î¼$íBB–Øù·ëågrÀ¸°Ôl6Y£4Á,æò×U7È›SµowC)[ÃÝ×™”ÄUÝíÕç.˜u4‚PŒF‘]‘Ÿì7EGüÒl.&’¨Š‹)x¦AB°æù‡Áµ:Æåª¢½ n+Œ¶?2ë"åç¼}×ÍôC/Ù^YvT˜?ŸCl#ìI~&>:wóòí¦â×iwt.4†‚¹•œzç‡â¸%~о]›úÐËCµWßì®ô^zì໺ÁÖÉ›Ð"¶”§2Þ‡u<8èøÚÝæÒ훿Á¼ÄÛñº”>¿m‰Q\ýâ U†ÏI_6sý¤oci]ÖãF å×»ä&¾û¿Íšdüx!×·ïž«P9 iDgW*šòMR—gª†CNŠ>œê9âÑbWjÀFš"ÝOý¦c´¾ÃigyÖùu±õð{WûùZO †3CZÇGÉ–9¡7žÇÔy–-Ô*¯Y}èàï‹&4×oa¼ÿ :k'ËçÈL„m|{btUlÎ7JF÷9o2&ÎÎ~&íÞ•­³ËìZcàÞBÍ»lÍ„‚ølmÆsÚ3ósÛ©Œv¼hmóÛ×ìo×â¯SúHwnç®lK§–Î8¥×ÚkRîÒËx=Yæ:¾"§ýû®Œ(n‚¯Ý#ÛÑÓ„fú `âš÷iì [ÜýžÜÔ§òø|Ã'ôøøÆð2±8}øüã³ÛOµ– tÄSÄøSð*ܧ*ùêÖ»˜­é† ‹†~ˆ4‰`Å”o.ò®.¤ð’aW‘÷ ¿6Sþ?6£õ+¡!¾ø«s¥ëíæ|z“×õø^bºÉœJ„þå?<Äÿþ§<q &„ñpâ?Tù endstream endobj 156 0 obj 1970 endobj 157 0 obj << /Type /FontDescriptor /Ascent 750 /CapHeight 0 /Descent -250 /Flags 68 /FontBBox [ -55 -281 1141 781 ] /FontName /BNZDNJ+CMMI8 /ItalicAngle -14.03999 /StemV 78 /MaxWidth -1196 /StemH 32 /FontFile 155 0 R >> endobj 158 0 obj [ 682 596 ] endobj 159 0 obj << /Type /Encoding /Differences [ 33 /alpha /beta ] >> endobj 160 0 obj 1676 endobj 161 0 obj 17859 endobj 162 0 obj 540 endobj 163 0 obj << /Length 164 0 R /Length1 160 0 R /Length2 161 0 R /Length3 162 0 R /Filter /FlateDecode >> stream xÚ¬·ctem·&Û¨°’Û6+¶mgǶmÛ¶mWP±+¶ÍŠºž÷íÓ§Çù¾þÓ}~ì=Ö=qM\óžc-2"1;[g{S&:&zFn€š’´Œ–"œ¥‘‹“’œ— ’©¹‹¤³!ÀÈø×ˆ‘ ŽŒLÄÑÔÐÙÒÎVÔÐÙ” nj5503˜¸¸¸àÈ"vöŽ–æÎJU%u*Úÿ”üc0òøÍ_O'Ks[ùßWS ½©­ó_ˆÿkGeSS€³…)ÀÌh ‘WД”PŠË©ÄMmMÿÖ¡àb´4ÈX›Ú:™RÌìÀÆv¶&–ÿ”æDÿKÈ `p²75¶üëfênljÿŠ`oêhcéäô÷`é0w4´uþÛg;€¥­1ÐÅäŸþÊÍìþ•½£Ý_ ›¿º¿` vNÎNÆŽ–ö΀¿QDÅþ§³…¡ó?±,ÿªvf-MìŒ]þ)é_º¿0µÎ†–¶NgSwçb™L,ì†cÿ³w´üW.N–¶æÿ™-ÀÑÔÜÐÑhêäôæ/ö?ÝùÏ:ÿ[õ†öö@yÛýËêå`éìd 4£‡cbþÓØùolsK[8†ÆGÒÖÌÀÄøo¹‰‹ýè\MÿÕ Ê¿CÃFõ7 C;[ ÀÄÔ ŽAÎÎùoHåÿËôÿ}$ÿ7PüßBð ½ÿoäþWŽþ·KüÿzŸÿ+´˜ (ghówþ½jw¡-àïºÈþÙ7@CGÀ?;ÇÒøÿãjhc ôø?9ÿWkuÓgý?1ÿ«úß!„lÍÿ2DÇÄFÏöo±¥“˜¥»©‰‚¥³±ÀÌø·yÿ’«Úš˜:-mMÿ’ü¯þþubdü/: KckÛØ`û·ÊÔÖä¿Öð—·UÀ ¥*+¤"ñZ¸ÿ2Vø;ÿÚÑ€ÿI]ÖÎäþ¶sxÑ1±sè˜9ÿ^ƿב‹™Õçÿ'ì¿€˜þó,kèìhéÐfüg³þþÿÇï?Oºÿ懭±É?s¤ìlhkòwôþ—à6ÂÒÁÅTRôoùÌŒ\,ÿ’»8:þƒ툿ýøó¿®†©©»©1ÜÚ²1O°UzV†s=VÞ蔨ö`?øhˆ}Y“Jq¡­]Ÿ_zøW•Á{]}ó4÷g‡ÇÒ™ýÇõáÏþo@оTÓ«|ªBÔMò.šÃ@½2ÄŒsõh¯ëE™m-vFµÃÝ)E%½Òw¨ïÓ],Ž0×ÏTþ$®…þ¤OöH¾Æiq˜Ý(Í hõEgçäI'ÏOÃãc£#}·x4¹q°d<®ˆäQþ¹xZªU^±è²2-UÓ ™£lë ¬ée¯— ”åz™;DÛ«gE]<Ò2º€$p¯%lØOÙpX†«Föêr¯¼§ó£ŽäR¸Çeï)á57*VÛæQš ‚;úŸÊ5Êí6VÕ›„{R˜KÆg, î;Op‡HL[[/[yú7ÞUºßªž¼3?5j=Ÿ¯/#D…AÂ"Ö)üb -4'z…¯ç6é–¥„EQ©»]?ÛD-1‘ë[ÒË’?üç`ìa¤Â*hYÕ¯ÙlyCù£ BÎ5ßšLÍêð¶ s”>r‰z,œü³ºa‹!¡Géo#KF—9‘°ü•x„Œ`¤u€Aò³ g52‡õà¦Ùïþ £_âPcÖ]Ô è;UÉ7ƒbœóŽ}ò€?Á'9κÇ]å!S°Ž;Œ—rÏs¡Ò¼æ ¾ká ”Âl pöãh{!¸o/hß´c^Ñ~á‚òS³z˜‡-je„ ¯#çníŒPÀe̸¤rÒð,ÞÞQ™öýÜÏÓójÖVúû’åL©œd_Ê®U$´‹8t†r™#Dœx{Øh´¡~j¿I¥f'ŒQ#Õ¿"ã‘΢é·Ø¨}éò,ÛüL‘¬kC ˆÆ0ÈÛÊÄ LÜGs‘Ÿgnɤ†è·®ò<@ŠÛÔlgu æÂw ó§SQö&€×'¦;Í¿ª»ÂYIýâÐ" ¸©½Ä›~y¯Ý¼ÐÐÅÍñÀvØ,Ö¿&¨ ‰`ÂN÷:—ÍeÕ¡Ê;Ò“Pn†äX%Þ—¿Ýé¡Ä™'x‚NGÓ<ÉC,\YãÔ¨TpÉÎyØÜj„-tÿ4è!ƒ©Î°"Í„lU:ëÃ3·ù5lÜ-âå¸ïìÕrù¾òsW*Ö^wgU›]ÐùƾŇŔ;­Tœ_ ÿdøv:NÏÔÍ…õ.:µ/`ÏûÊEWh‡.ïU'¼(X=FØïŒ’HYnKÓß½ÏTÒó*wé;51Ø cŒ×ÆÝ &Vtg´ATÝøo¨[ŒuLñWoußQàuϽF¤A³fÇÄ»ÕÔ{)ÖaMç¼ÝûºÎ=«<¼µFÇÕ x&FËú§Ò™·ñPvÌx«~ŽêúŒ/$ÍÛÏdO¦2ãçu[œ¬1¢õDÇLŸRdR+¡ZiÇððƒ º5!mˆãyLß|Є3%Œ}š°Î˜I| xª8OÕ³q6g!ϵž à íÚvûsa‹\8¶>G"ïz…O2qH dðg˜G)ŸðÛ˶w£z~Éü¡©€]¨ 7¦z¢ßÝUÒˆÆ伫$5Rc'd C,ðᔑ~wìÑ»DˆÖ*Ùvƒõ’µüœ’pÔãT½1§²'çT3ù¾%0Ÿ8YlÒæCWWË9š î÷bQë숃ñ±¦êW/–D°ÄñE—Â>Õ÷×˰@Î->Ó‚ òï~|R·˜’´qà:‚¿ö¡W˜Ã¯q³%Rù´¾Fõ¤Œ¯ÄmIr\3—#óy­BœrA’ù;¼ÎäqÃ6`¤@ é‚ç ¯0êz8˜ýÝH4I邬×HâT{g©D}¦ÌŠ ›sà“á›ôÕÆ·¨¯ñsí <ý*Xëø=K¨¹þ‡ySýKP•-ê·±ýC¥*ÖÁé(%F¬fí†s6½ÖÇá˜ô`q £ò3-þMÓ¶°‚ÌzH0¯H,wë+DÓemò‡(¦\ÁÐ{vF´<­¸Ëæ0©øÊ …G|nÐàÞ —#lUôÔë¢Ü/ªc8lrw…€M N~ )þa ÿf¨õo¼_Úßkó) ;7aíÝLÊÜ™-ÍN¯;Ü=ÅtÎöE…u _&$ý:b,l…±0uÎÄL¸\d‰`µcf„Ž3YCäíiŸ!4ÉÚX½¥ ñ·)j‡FælWé².Ëýá,|xWû?ºúîœqËcê°¤N- Ÿ;T­1Ú6S“©#p†¶JÃ3!½m¨0³ÕÒØ& ;4 0 sd‹<,ì#Àµå$Mp¨g¤A •uð9Ôû¨–üdqMЧQ':/Â>²‚?ŸÖ¦ ¹žñ7,Íg7¾3Á9õª< š); 'âìÈ:Ú¼Øã^ÈîZt×-Ço\±ŸxwyÈŠÄóuL ™âoÏe{è)]rO|·C¡<¤Aº £ S å'·Rªs?¹™ ôÝÊÕ‡Ú¾•3 ^k¥ñ€ùtîþÜqQÊiŽžK¹íµkÁd¢fÕGü8@ƒ-ƃlÐ'¬ü¥–ShËb?OG‡y®…:"¥4d%­€o-|­¿,¶ ëû‹ÄáOãjÇ|í\¸ÖR!d@FÓ÷äþ8ZøÿCÎL•öß\Lï¶ì-±=–]8sL—QÉ{-•s,.˜*»—è­DóJŸª Ê»°Û·Œ›Õ¶WaJBc¥»Ê‰M;²$~s àÌTe6R³P&ȺOÕücà[câ8Õlbà'vø Bª€k áÌö?™úE«¡ KíÁqÊrÔËyµyS&P_Ó¨ßsR•zf•¿vÃIÛ¯’Žë;^˜~À«._\yÔ9Ô&+ÅÖR–ë”q½L.V;t*ä^_ãŒ8ç&ºAƒ&¤7eº©o™…l„ óïHÝÀÝE4S˜M¹JQùzg»êƒo óæ (PɃEÂÞõ˜­hõ…*¨h¹¢—áëÖ[°ö9âïãjéjL4Íì/ž¬¦È2¯,Щ‡#Úº7c4ÏÚ«þtžGZµ°” ^é˕íü÷\rDŽÇ´¢ÊM¸oWýo<^ß“]½ùª¬ÞwÎÛ$üì¹.úN”p™Z‡û,çºLž½G1µîJpb±ŠÒ÷þ꯭Ðc2\žÜ5*ùX¯;‡>æÓ ™£$›žÃ.UÃx#à V×eà·x:0ìvŠ4Jjßè’m, (V¼`—äøóc¥lïý›ËY”-ùŸv]Ñ•dŽÕÂp¨ ˜G‡#YYªúÀqÄúO䮾P 2á±Ì¼Ûíùk#È”ƒ·9Ç«½Pæ3̇Hæ±È/àj¬Ð%_ýÐ=Wã.‹P¯dvpcGçŽ,•ý6ú­‚+göÀW¸ÏÇê´h9cûPjü„,ìt@µè¨ú`mŒŠô8£À¢™¹¢È?¸^0{% QÛtÿÀdI>ZÜÿÊ©¤Vº"›IèÅwA%ôÎtÑ×:Z>Œ²–jµ»Y¾®7>BNÌè{£np@:·"-ÿÅ8¦D‰Ø´$Z8Aœbª= ©Þ3éc,ŠŒ›­—ãyO,?PTNo׉­AG©êû¹?Þ³]ü¨¸WzkÌÅΤWàãÅ >ê((Ÿ.óúvvk–´42ÆÇM+(úQ/ŵߩÚW:Ï:¨Mó"¶—A!¥ e¶-›YšÛq£ nãF†ãw%}zàÜLƒ*±ˆA1šwQA ǰâù^O~ËKûþHªWœ F¨>ìÚ¦?ÈJb=5ðcN¾—Ô õ—x¹âº›r:DWšÛÙÞCÅLýN|ß’ýlï¿OþÚʤp‰eDTGëõî4J; +0|¦ S³ & «hìÃ^DBø˜kä.×bf6'À:ÕŠÅ îD^,íCZ©k.xSʾ^‡q³¸-O*³Å•º ï0Û;VýJ·ÎêZ³³¥ï$\ì[‹¸Ï“•DX¬Nßà^‰‰k—¿a§;¿$˜“ }ÔAÊjt°I›{Èj^²™Üõ}‰÷NCeòô°¶ëµÆ I‡h€ànE¹½8¢Â>ìl•»6œ<9I律ätN”qÓßÀyƒWô_@#•XË«qúæ^¯4¸NŠùzYÔzE\†qÀï‡Õ½`ÓQÎ4×X¨ËJc–®üJ$Ë?Ɉ]<¹ß.­Û•‚ê—Õ¯i²x}%O„0ôpôãÉ¥–Ø’ JÚbÐðØU›íŽ0°€ÃÀw9À«¥Ãçè©JVN$öœPßåÖÀ'ñK$×eÍ– šYõÔÕsN€ö•çZ²Ì€¾\¨Nbc|åûLGqv›I&¸z[a‰xoõl_oòj?.-E$H~â w¬ÞêÑ«×ÕÛO˜ª|GjJc ¹z±¨LŠI-}§¡¤‹ÈH¹†½i‰I/¼glÏÏl娗¸‘T©êÒçöxæÙª'°¹9"¦mûS… s û­äOÆßsi?¦#5øŠÆê³wRˆ©!ázHs’ËoÇÄIO3~¬ü—úbùøwq~½¼_Ù:5ø-¸·­åsVˆœ–ÏÇsŸèÌ] 1xÇÈg¼?ú§7U²÷ÑR$G’x·à472G”mYˆiœ(½'jP_Õ†`·¹OÛ›jLj æ*:»ƒ Ý»L÷)”yŠ®¥I¶“OÊ׳pIó‚´T¬ÞY¤…ßzS‚©Ÿf{˜‘õxK¡²6vúk~ODT Jop"=,§Æ§70Èv8øVvß•ÌÍ”Œ< Þv1‡Xж}ú‡+³Â2ÈÔQs,D¶ÎšXêá!ä‹Ú0 ™,B&ÝÂô†D-€Åa8·9aŒÌ¾Wx;í¢u&‹”í‰äd•V½*Êûû…óL~»Ç+ lÀ±++\X¦ÊîÍBw;z;/§ƒ‚™§Ú¼š‰G§=.ÐFS0çñÍÈF5‹@l1D|hÍ3²hœÀ3;éJÚ²wqªPÉ–2¨¿ôk¯Ñ¥ï|‡ìþÚ¥6#8ËücúPëM‹Ý Ÿqs6QBßæð­(;|"/˜:©#\çKžð{²þ¸½ßîi߬ï—=:2,w2(ÍÅ\‡7å~N8æ™f* è¼±‰ £ÕÀC[û$%<;)+1"v“CXÆÒ‰e»E™=ôȼÂP‰µ3Lø®[Æò•ÍÌZÍáOôuÕT&³à^d¿~¿ÈX¥¸Ï—~½XàÑGH·ÑMæ+k¹Çÿ†h*½²F‡s ógš uÛæãÖ¬×ìÐøâX /?yëV’äYD?¤%ÃFX¬ýÞ‘Î/Põ&цŠ\ òCŽŒ@©^½¨blTƒx+Ø”€m;÷Ê(,çÓ C þŽƒéR§–¶å+`Rª~Â^ž'’0ª(í@HÍdM7ËÀìú¸––µP¯! ü\Å6:žÍálÝà $Í.d{Ž;-)*“8÷ʦ2^ØÂ).¯¢¨`º¦£(àÊt?`/°™Ž¸×it/çà—–“q²bB0áÍ]”½ G÷jg `r'ÆOÃ&ù÷v·ñµ÷¨¥eiSõzÀ½½š¦Ïñ·>Û&gÖ‘tÏúxø-½]”öFÌ£‹ª4D8—šaï¢ÞžxöäîL,XÄ8ÿ®¦ûVÁræ0{ïc/¯ n 1X_ÔãšYœÐ½ç¦eĉþ%$u .%Wi¥"l¸¾XßËØ7ÐdœÇ/QróÂÔuEl VîÇw•”q%ʬýàÂÂI óÔs­™µÔ¶Øz. a­Õæ$¦/Uí’ýWhïj®pÈOךÃu!%1ÊHîvß?ä_lÕTTU·òB ÏÛ/Rj¥.—]à×ù„£VÛ‡ð8Ñ;(#àñ&!0³‚"Σ>@ßìº÷»µ\—œ>ƒ÷lÄ+õ8;ª`âÙQdJä­t©þð|-Üý©‘ áË>P®{7íú4T½îVºwÀ99׋˫Þ2¿:«$ÓTVOÉ0æoFÎò§ý½¸ªqûà½=]Š_8«+g³ÌN‚.¶Ê·[È*„ݯØÍ ŒÇ¿}iÎõs³_+¨´„¥I»?)ÉÂϺ!à„ÁÝœXsWÙÛhІ$£A“õó1·u’í·!šÊtJ™¾w!„ÛÜ8õîZ橞¾çònr7—'â`ì&_£6(FVÏanfÝ*x$ãà †c-A6 KQƒ¨Š™ÏÔÁx+h1B˜<.©Z¬cÇ3aù¸ÿ6xh[á&»™©ƒk°!4t³ìIŒlŽhÂ.ë9¾DžÃt˜TÙ+Ib5ZȽPô³#²ÆqcÙ…MÃ5à ó]h7©8·Ú&9•N|2?§ùœb¡Žh0¾û­9³ót?Çä±f€±E†%´ Y#8Y&ú~dK–+¶fû£zÚÖøDÂL½y=;\s8$Wù3^Ѧ¶‘H“½3ï¼+kø›ßþNÑšíš‘jâŽåq»íü@èDÌk’ÛÚÀìAÆKï:î5sëÝ¥2™ö/Ê•é —•L.»H†~¤D>´Dæ}*ÿ ÕEÈTžKH(ÀƤïÀàÖÀ{‘Ï¥ÜïïÅŒ”ú›"ÇІ bÄήk”Ûm–akêæCFƒŠâè&ö…áÊ)^Ì+Z˜ïâØÏéØ1 šÂë¢#uÙŠûMÌ„qôÅË4e¬!À¸K”.û®µ?­V:ZH×®ÞÉ»>U0a…Ìn¬VÖÙŸoÝG¿æšÑç|zÙƒûÏ!È¢Pê®ß¾÷$]($á1ƒIÕͶe:ArâÍÀ^Ù¬ëtí‡ûÏÒáåXñ¦ 8MÞþ,…(Èrl*T^ìRàï÷AæQô"ZÌ!¨Û·ã ß°lûôÍÜ%OQ\¾£-›¾µrïw +˜Hø¾Ð )Éc³cÞ¼¦k×"‰ú^à£p2Žù»Ì[V/úõCIŸwݧÃ~v½pŽÍ”€$# yF†áe¹1?8ºÏSü"&¨UGRUî6ŸsZä*Ú07(9·íõ].ç¿_^w~!ju.<Ÿg‘¼ÑýTExfÞ(|B!É2‹¯HÊÝG˜ž­øxz w/Ç÷òÆj‡Lx¼1‚æ†d#ÃÆ¨h2EU&UÓ‡-š•“Ñ[yÐ?Ë?ózÞi‘Îù& ‚ä¿~03`ÞÎÞlc+ËÔ¿i•X)S lŽà V½y©RV2>ÿ8šE ‰ÀWÐÔEâ ¢ž1~‘϶q_¼@“­%U„àP¿ †Ð“ §Ow_ħ„$…^œ”.ù‘¬;ŠøŒEtj⾯6[Æ–À÷ô‘ijá¹î[mÍ¥³×C8ËÑC«§ŒkšFžŸšy™Ú–‘H¥lËp…,gŸŠ~ù„—vôFº[rúÔ»ïìY|g£Æ ²çJÁYD-‘öïåÏ^ê2˜|^a²à¼)ý‡ àiþ_ä•5ïXr»3+-*ûŸc‰±Ú??s/'gs‘+”Ò:Ô¨EI­¼ja~\0ÈÄ.¶ ŸÅ+‘:|Wp™ ÍãASol °¾ÞÇ7?¸KÝœ”¥ pŠÞñµÛÏW .8‘(þbªÒ ÑMWhôìU·U ù¾m&«AcQùê&”vØ2WPÙ_÷ÄD ÿ­Ó½wë#.9ì~èãÑ+À¤åô¹óB馧kO’¬–|¬úE…§*qùs%ü:~ãØÆkú½9Ñsa 4×&‡np´jý>ºŽ2ê*uåŒ$’«»Š_ÞyŸÐ$‹O׿J¹lY©fÖŒŽ) !ØŒTcå÷]-Å¿‘Òµµ«w<§­`“ÜJÏIî®ç’œ—¸^[½¸˜>jF£ÀãB!(Î¹ÒÆ¶®ÿëuRárï+ˆ]šTn7#·\ë›Ôà}lyg†äIà ­õ!n…Ãc '»8½Îi²ž¤ÃAk&ц¦ºø£Æ{Póhfâ/°p•nn_Ô ÞÛ´œËŽRÕ« ;rûœ’˜Á¶5r…Eýb‹"›²5<ßòŸ™Øi·ÀyÅ’YŠjÖ <’iÕé”ràó 2e Ën_å<œÕ.$¯¨ñ®Ýc8|Ô5_ gš‚|à)ˆ_²k6·> )•¸ít}ø¡¸?¤öû—¦Ci}«‹GçlšSƒ¢Þ²¿_ßêãµÉÕ£T|^ÁÀdpÕZ 1ÛºŠæhè.€Œ;šÇ·lÇoën™µÞHC–Ä>蔺rë…¶ñ¹ÚsÇá‘ ,ªøÛcrY#j~•'Wf÷sé ßwÙdu {’Nˆüì*õ± ÿÔ`œv§Ø¹‚]ôˆ›SÊs>s’#Fh@cÅÎFœTð¿ÈR°?‘xÉ'Ë7š»¹üÇ øÝ5—£·á7lô·kd3óoòQÀ´<4µHÚ¥–ÌA{FNQÐMÊã_r“½¥ƒ÷/— 9ë;DŒ¶£Pn0O$ >SËÎUÛø” ÙƒUãË"kEm±Vµ›öÊ`ïï„ï´w ̸.0N 8€ÓŠELÛ:Γª?U|§¿µZå|óRî£Öi‰#¥ï"R,˸y Q%—²>ËÎêõ1¬?~l«º¥ãŽïÄýˆï±´È£v`þžg䞌ˆHqšâê_S©·_@ÕR°r›­-åôVF‚PørÌ28fPtce|TÍ÷·È9*ö­k®c*ݪuVбÌQºM'ËZM¢f"&QºùÕÜûà $ÆÈTÿÜjdé¢;¹Çÿ»B6¨wÐÞbÝ5KìÏ|“áfî|OfLŠJÿ[7ÉÐyP¬„°˜òŸQutª«eì ¢›¢M“<ŸÌ½ôþ®9'`é7Utß,©:ðýÚQ}3H‚Ú Ã÷,¿Ÿ\ÌÓ0DˆñÉ$e˜oˆ]^Ì£ T]³ÌOž…–h\Ç *çë—-FGÜÒ¨I¥½µe€ NŒASÜÉ´„ô .½þðö'²)Z¸ŒyÉjÄÕ¸q–/òGǪ JÜEŠxª‰è*I»÷±Ž æÎÌ  ÏáœÅi‘z©Å¥¸B•Å„;QHõ„]óØíã´…E'w‡Rƒð5‰ó-£›ô©Ó›\¥c™öVOòT‹ežžîÜ*}ßšÈ901¡´;,ý˜c"|×b³Xv cÀ uàM*á]Œ\gÈÝ’£TN0Ž×ïò#ÄòlY\¡£á÷e;›ILÀyq¹àØÏ·k®¸‹æoËl ¨uWù4£s!„ ,Ðø_nOm]â·e:Ý1<çQ’wT>B6Ô¬ ëµ.(]'ø®ŸÈ%Àú`É:îGÏé­üæ¹¶ù^4k«µžòb»Wr$•j6×^(9åÇR·ï—MD§ó’¡þ «˜J©¿U š©×@¡¥ühp±åEÕ‚–zy¶“(†Ñ ‰Rw0Û&hÑhÅ ÛÅï%¤³îlP¤sx $Ѿ‹[¦š*ã™ôKó\ÆûM‘+Ь-2LÚ}§HNpؾ¡½ÁدO DAÆŒ ÐŒ÷Y¿YAih}3ÆÄYS8휸¾0ìþú%ÇÀå2rö–jH,(¿ãï ©†„ªàøaWvn·ËÌ(]Ìî[Ñö£zj=1¥S¹­å¦$ÜjËG.Ú_BË‚þj±êAÃ5o™«»{ÙõՈǘÉÖ/ v:3ã2RÈ0úòe/TÝ;ÔSÞ<˜?šä ykTj®P‚°IèX-kŒ&˜8‡e4Æõ ‘zMÈ¢qyÑEÜ©}­X×\vü>ëC…ÏÁöæ£èÍ*õ9Lj·50·ØO^¡kîŠ5q%SÜøs·=Ð3Ì®/êñóbx¬Êæn„‚’ßÝ6Ì¥Síšá;Ìz×ß×¼w­—kz°ßYØñ®SïÚ‹ äWò,ŒB'üw ›úÚ¡©L%lý—"ìïÎ÷¡:=9÷íð»aDýÌ¡ûªT$†[œHíÖ"4FägöÅ÷:èÙ=òï·{´í4í¦íóÔõR޲—<ùÇi]öeLš©^Yó]ÂÛ@[÷ef±( Ĭè»K‘Ø K½e—AûÇMQÚīѴx'vÙ¸Úü~CˆÝZ»Óz“¬ÖÂa~×uÄåB (êw-„ÃìAT½.xaô4H^¯V“{!+eò— bä¯2§1…dn¯þQÆt¶¹ô®†ùÚ  La΀óð¥Gäñåu4êJ¨­xA=p‰dí]âL¡B(â½ÚÖ´r 9'N6ïÎÒöäõ*”¦ïJ’‘KÛ]Ûó5-Ç>š‚%ǘĒR˜ª“~i«UÂý Q¹ódkËY¦Hqsëà ªz®í‡ÉÙ˜õ¾9¾/f½}tŸôëNšô?çDýƒ³BÞ¥P‚fp™ÐÎ 5qæº X>>ò” k@ ›0¿™ätl£òiO ‰P©:'ɲéѱíóxȯÊPHÉf“‹œ_ æ2dG¡B8¾ê/Mï–]P»'ã~À£Ðw•Mð–é~g+bûоLIÃÒe*Ùã\YÎT¨dµã„Sº68}¦ZÞkUyäš÷ºNSÖòý\á®s+¨h{yKh€OJÄúÞ—aÒu*À,½Ø°É{°H`ã}k›  >iã,¶"Â^/4my¾Å]Ó0rã MHξBéÈ¡ökzù¸ÁÁÅëñ~›V4Ñ”´JZ•ø‚ÏšŠæÄ&ÏŠèaãȯÕbwI4]W4OÕ¯éÁpYj“ƒ·ŽìB5ãDfÎxZ¾Ød+ëÔaXEHîÁ‚_3ƒ 5}é ©œ:ë]çŠÔ8ß²X\}9 ³×¥«ÿH¥ÜNg¯;qðrŠT§¢fW©„\‚eD0SÀÜ­HìIs¹u˜CÆqšp\$8êjGô¼b‚´'xU+ê¿ß:})‡‘»p¯ðæô€0‚žsÎêÓŒv÷ÓÑ|[ZŠ,>Œ?îݧÉDdG !ŠáÁŽÀßc]ÿÏd6=þaNòž…Æý Pê’m&âíÒLJû#l±U¢^TîØD Çî¡]·ß¼9ì•iøã×å¥Ý.1=ÉO¿/½èêšR«"Ô½¾ïÊÊÙWͽ6÷ò½ñú‹ßd?Wß=¾s ¤z«S‘›k@N¤TÜ?h¼žyè&Ôl|æ¥F!°xÆÛÝ'þÑrëo½*–íÄý™Ïû¸¢2]jáþ3ra;B;ˆÔKù²ü”¸(¾{ò|Px!¨³_°[ôÒèdÍÇ2ì‹Nú³ÛÊÛ«$W‰„qνnQ³®Ãø^ºþK*%7;GzV ˆ»Ï3Ž@‰75NTHŸ¨G×é&¥N«¼j½‘®PÊò çH}•ñâ×ׯäR,"»‹j­Ê÷gx51ÊÌ ¸]ÁŠ#‚¯Ár‘¾àAê­ª¥ÐX¨ÃA7¢‹?’mØîÇØÆQ‘`ñ£3VêZ´¨Á±°x÷1N`ßÐòÖ3Y9ºÍ|KÞ&UYk,Ö„õð¸ÈŸÏ¿éÀÈá<Þ…A€”ŒHÂÀÁl(Gί\93rT'&å 3É?Ìõ5Vvó¿N†Y'ff“¹îø7‚Ày37âè|y˜‘8´ŸpœÜ0Ž´ôг&ÎU7á‡UË¥^íi @­<Ó%¸QëS!T°NDÙê0¸Üܪ0úÑaìsH}é«=÷0=þèÎ`Í«ªgeÞ›Û £›‹=òžúØ Öeß$bŒF:¶ÏE5dk¹ÅÏ$kvSrÑ×ò*üX?8ª¸ ßxØ~܇ åQÎU]ÍцҗâÿFÞ UgÔèOIçµÎ" ôÇvtœÇßòGÁêý…C“$óPw`xXx=]¢ç‘…Y]^æOû36—Ü[ÁI¬ž;~4ø«Â+¢®Uc®®¨BëW M!{ç,ÓQÑ«ßhsÝšâÂ!SoÔ<¢J!ì£cøHwé!Q*©†xzX’a¾í^·Ôƒ–²“þ1ý±¶ÏÔjÆ^ÇB lý8'~ôª%jíH2†*¤ï °… ß>sf»ªñj4¦ÂZºT94–ŸÁþ š2è8¬.Cµ-@yÒÈ_~(ìö%—±¿1ª÷½¤!àÙ¢öƒoHärÊex·NußkÐf¯hÃöÑM±Q¢¹Ü“rö„DP—í— ï»}ófŽ4w»n:G@Õ?—ÒÍ—2´V\‘d¤wîš´µ·Bhª­åXá›L®uC<²ŠÐùaˆÚÚ¡‚¼ ;ËQ¾Ý«æ 9rЇpœ•ýi²Ž´&‚¡ZaÍFƒ'Ñ{ ž=Öå¯|½V¡§”ïüjLÁЇó- ÈAUc·;ã·£¡‹‚H§å2.)Â0?›Aý[ä׺¡ƒyåjG؆Ûpöƒ#Ic×=$nÛyƒ½^8œâÑB¬7>O-~aZFX–æÿø‚%‰uùu¹T"oÐ3ˆAËŸ 1ñ†ÍÚ¢ü"^x-Ú czãñ4AF ¨"»ä,î1±o0½¨¶œ *ŠÞÜ(ö7&ÔVhßÅŸ´ŸïŒ[Õ*[òEŒ²;Ç1F¨¥§¿Ä%í§œ²@¦ñŘ0¾ßImŸ‘ÅšÄ1P´AÁ™lùuàM…š‚Âg„P›`þQ/ -o«-âíÀØeÛ|¦£• ùl%~lI:²ôÚÆjÿ£(“stðÈs®ÇW™7Ų gÝ0¤œ SÊßÕUZ=äØF1ÑðR¹Š‡ˆl Ï à…=uNE iæƒtÔ¯æN_x Câ Æ9»,:Ak»ldꑞÏ1_æ[9):ákùêôaÈBð80~É+ü¨±þjl øìþëžN–_^ù¥¬‹ùy>«Y&è·(|jë¡B½”së]7Ÿ4gM){¼F®B-óÎ_‚o÷‹ú«ØUŽŸL÷‚øÏjd¥Ñ‚¡õÀOtaÁ×]ú.iðoÙ‘Ó²J-uS5’ÍÞ}½tcöäÁZƼãÂÞ‘ Ñ[]‘¤Îj×ÐÀWxVÙ´æKEî14tÄ?;±^tö"ÚÒóÂ= —i,ž³—>/Að’×#5ê¥ü1 T-ͼíû×Ã¥ƒÉ=êïáÂ…êÄ5(þ, þ B¥ë½g­A<µÛËúqùô4 ?òùïä&¡¹jmÄë?ѵåb¶ã¯ŠŸkõÇM@`£W~P qI3Œ­âh„Ë9F[FdŸ#R$Í-–»±ó’I¾wϨ$HðÊd•¡4Ø•`>ö´æˆ=×#¶‹ak%±œkL>ïF:n&Ìámäþ(³‚õ8-ì=ït=oYæ÷K,sšµ²È“ÖBñ@2`çÕ=«F}õüÊkØêÁÎï8ŠFuý¥D½¼Èn&·ÜsZYÜðxfàÕož]W ÅXFBÐ1§ª0Î’-uy§ã…ŽD&{Ÿ%{ˆH¹3{ìl³©…ôyÝA þÊ ’Å vs’Ë ¦kT´$›§†F“§<ø *m¼Ér^X,tJù‹d­ajmFû‰ÑT®OÚiTòÓf(*•ÿµm¡>BÈXAà†xtÈ‚Ë|qZãéÌQä“ÇjÙ(Ú}\T乼¯âW${Ûëòœ†lfÈà"O‚àò9yÅ?9g£OØ\µÄJ¶îEíäžôÞûn¿RTœ7oS>¨7b8<8­.‹y—ÅŒi^a N·…( ‚VþÌ®«5H v²EWBaÕüÅ/îà¤3qýËMÄóý(–¿É­Luà&{éµvÖ‹q4*¾™ÛznîììP«1ÝÅs™R¨6rÏQïˆ3ºŽ¨ðFb\I”@cYu#'¤¦ǃ¹g*¤“jĺ,ÁÁº•Ï?ˆ}þhFÐ LJå8-5¹øñ˜ºîªÐ m,Üw8È1ÝÔôï¶à7ˆ¾ƒåù1ðÖ ù9æÒòƒ4'Nçé°×zûw±h±ªÂçè·¢’NÌ4Ãî…ÙYqgdŽ^L,}H‹pŸŒ\ä»CE»æL q%J©/%QŠœ€.9YŠJ0rcA n]uù-[ìÏf¾§ƒ—X²äbÁµ¿ÄåT> a Z £gQðu´fÄïå¼>‰8ܱ<œ`e£ dÌK©ªs{؇;†CûÔÒŽ±Ú^¹R^ìašæ”F€g€Ÿ‰Ùÿ_º¢e×ο`G¿|Žõ±m$2Ö•—‚Q[br]ýÏpÒ.ôTÍÝò‘+ñOÛ–Ü #æ3žð6ZýÅ]ª @¯20ircÖU3NT¿aé«`ëß Ýá³:Ë3c7_ñ™`I®C…{u†‚}‹»Í£TcY›¯Œf§áp-B ôÕµ2®èª(¶‡ܶ½Áä ’ñ‘:vB˜õTÐékxІšw¿šëßãýçÝõš6a4°1Ìĸ ¨ÖÝ–aן¾ñÑïûß1§¬±àáœÊƒW³»þy¦$I4¶Óv]^y2£‹1æ…ÄSsǽ‹’á§õóõò;3‚ó<[^ÒÖmŽTðõ,Ü:vûîðéè$×*×ü)|çõè6ª–F:>H‘ƒ»WœÒÈëÏc×1<Œ$í°³†W0ßúRÕy |.a‡„”Q"|VÊVýÜz¬Î.BÛS§Ã!6Wu;ã“w!'Úݲ¤X޳>+˜C„k/i8ZyÀŒ¦‘'&õûRq!×K‰†¯õ{à˜Z^ùó+žU‰o¢sX ’cÄ ˜hó\½; ÿèW(Ñëcøèê#³ÊÔ‡ñZƵ[¥=ƒi´p\êpá¤öÞä©‚ß63óû Ì­'îÈ^(”d`ƒM•Á~ò!Ùˆôný…Ž×ËÛrAR·oÂ>‰bXJôj-‡‚¤¤g/½‘ý¿N,P±LŴ߈”ÆVù³”î 9I;Óz…Qã ¡€Ås4nƒ*AƒêÜõƒÖ I4¸*Î0{1d×C]? ê¤hRånSˆ9T_º(™6ßÐdʨJ4Z¡Ÿ¶úr—þ…Ï7 kÖ¶ÆÉ'Ž^t4àNЬ•s"óy„Ç ×îx–ûx9ÚäaÑ ßö†ùZa¤ N­ÿ|DЖ:ógÕ»~ä)ŸÍ2qÂH\xüLí9E—ö¤\¯ÔÕo[ði¯M ôÿ\[ƦuŒ‚rÏd…‘÷¼ØÚ"`¿ê<&H˜bd^²³CJ<ëj¼ŸOÕ†R“KÏü=ïôÈz`¸säþŠjŽ—O>ÁéT‰#ñ¾í¨¡‚düXSfÑØú"UH½dáÈSgÿ8NI6“¡•9ónHigt•Ó𵮃አ?¯ârô¶r—ò!úFÚƒ ß&dðAƒ±e"U…J>•ùÓ9’¿,%‘Ú%â/˜B—Š/϶]ƒÈ{פR8·ã˜Úec ˆoÔX‡žœFô¤Åxò&—ŽÿôvÍ¢u/óÃñ¼Óa:;¾QÇgwÍ2ÕD1œuÃø%  VgRmU¬ˆçDŸWÑB}GŒÈÝÓ´] ¼t íN;ák•g ‘é‚ ~"`@3ö(0Ï:ž-*šh2ŒŠÂ°%ðM+Æ4ãgº0ÕwÝ!ΕõÙ ý­ ¨ìä2„2™ÜŒ!#Ùzüî:˜€F@_ÏCõŽ N+”ÍMÊý.à‘kHkÒCÊ nHês2ÂúúéXKÓ»Í7Ô&1t‘ Íû‹4ùø«üì,=‘ߎGgò×áZŸV>òÛȯÆÐÆ•úçŒ1ÃlŸ"šÁÔV¯ã½bùNO’~„“$Óœ‚~2Z:6¥©Ûavk‰K8Y¼x,nª—g›ô‡‰´2ujstkÝ/Ôl™­)SaÃeÞ‹ù‡$FMÕMm ëå§e& Êß,ÔZÁ/_·s¨NxÒP¬ä«[_p¹ "Ô½r#ˆˆâ@†ØŒ]„MÔ:†$Ѓץ,ÕfÑ § V6H‘¼ªZ%H/Í:¶"“Ãä—¸; `(8ý6ÌÓ 5¶ÑÎ-xS†ø÷ƒÆÌ¿°Pð_/×k`®¾’µ®L8nñh+«çŸ3)¿¨b«Üóðuà~'ÅŽs×à£!Ƀ.÷u²ô>UC×!CIégÍÍ€‚з*y/̤èÏVÑ.UgsLØLëX%ë^ž´v_µM:ÂÝqp‡?R­¦bU|eÈ#2¶èýDs†Œ¢.îž4 }*o}à—ØGŠ#Êg{xòÝê†Æ‰ƒ_20#Pý©„Ö¹é=ÍõôĪ]Îøôhº±j2ÈЄvÞ›>œºwÑÄ]±GÕR°øÂV5Q³„”B²àÜ52Žü»t}SÇ(Š6 pÄ©C7ïÐîx_þTnßXÔ<éLr$­%&.bö[Û¨‚^#¹6½… 5O3x*8xšþ4ÔxVf1_–ß߆¦‹ÎEÌ<$ÁÛHfHçÛö źq}W߇Jþ;ØU¦hÆrA©˜ ×£µˆ›¤[Î?Åíi¹‡ÒHäòçV¡/e3MåìsÊ) 9qˆ!Bûî1ä]¢ ¸Ÿ×£{?¬xÅÏÇ;X}*òs%KžPe«ï䣋¯ù/ÚLâgrµÊW XûVñëÁC8o‹µÐUÏ¡d…sn@øîj1%Œ+Ul~쨿d,gh…åÿh·Î™`ŽK®ÛüÎcíðLÞ(ºŸ»ò¤k€ýëÊâzQ%/½õàÒ(ù7] ƒ¿ó1Ìsršrø‹ßÄ¢]S„2_éå;R—!IS *Ò.x©ËÄl*§f ×yL­ËswtÛ•ÇÒyàꜩ ?s´·Ñ¹Ì¶z —?åºM¹©@’»^€O­sÇ›=!AÅdèÂ\í•Ñ)MÁoCOWˆß;5PÓjñîÁ®Â>(&Ó<´AiØž °¨”·µèäÞïõÁ}ñ|¤ŒvhÄ=K]> —' ,KaoïºÝèfphm©Ö¼©-'µýéÌçxÛ”Êã|­›‹å É3Ùî‰É%›ÌœZsÕ%HAú—8ݾ‹Æ°a7ÔN¸põÊgpŸ žlYþK ‚84.H#>×TjŒÜ›êðxkÚë«Ñ ‡Ù)ðÜEŠWzS¼‚ÿê¨OfÚê¸Ä"Àà(úÉå©ÅÚ¨$އ…Úlaû¹’´éGp™ÂäúI}·ˆq:^[Xómå—èw¸,pB7Rá qÍvŒg=“d³ªN]Ég^º­¿®…ÚƒÈJ‡ÿlïý}›sc¨zúð#¬[˜Ôu]5Š¿+©ˆ³ñ(:FR’ãÈznn¸‚Þ«¼_>»iÐ`"»¾1düûxØŒrÀõôÒ5õ?QŠ*i«.¦} é ¾Yr‹™¯L|Ÿë+‘µz¦bâFšaoª8ž‚?c€Ð„ÏcgË5Ué“Õ–1ó{t¤¬™{k¼y eñâ ŒrÎÿV±Lê5Ð+ß!di‰ S†w2SÖ5‹§V.w­óE>’‘[W_X|/ž.cÆ(ó¦ŽðZëÏéˆôˆ·ÒdÒ’à?ç¢mèÕC¿ü ³ Ê7ôð)Œ T]Õ¯^‘}-|ìÄ•ó~xfú&#sߨ÷Î;¿Ž—`ì€ÐÒÈØÃæÁ½Drg‚nµÅ宨Uƒ[”ÅÊ{¨t^ù5knÏÍ(µ¹~Ÿê™Ö+1ìSÍÃM»'N`·XžiZ~s`²Ëæ‚­Ã|®|¨ ,I£KÄ$ÁûAÏù ì‰À^=ŸŸ1Ö!Šêù™À*<ñÛaØB’§{êSÁœäIãìô¤¤œ¿žò_4¶ ߤTÎŒÏ ÎåŠçÞ„ÇâÛ¾¦žBX÷Fô¿5Ug½T³v,¨ñudB6âÍÑ®~’}\ŠXý81u_)‹3º%Öså 0`PBåg&XH*Œ %]1(‘°¹÷{ºH`Wÿ¹¶.Ïñ%&袄Nõ6´ËÑ#À]Àò íL…(ñzªðkp„Fku²ÏYmTÒŽæVê…p˜pó¸ÿ’€¦Åk؈¯óÜ gUZ··e05*‡TIö‹à–P ÃBÒ½¸íÍë&ZöhÕ¬'¾NãÔ¤Ï-VÃ;ê:N[ᄺá¤Èב2`É4Á—Fì:Wêžk춦cí²7Ô\”>Èe’¸'1G5êN¤ÚàÝ:A4•³‰?=†ÉŸ"H¡*\èce œbOípüZID÷QúÚâSu“½†§®wÿÑ%kÖ֣Ѕ÷+ôx¹JÔ<²qÚ‡½PEWý €¹¼V¨:߬𔵗ad¯`ŸNI¢ñËjuÐXTDˆ²¤žÄeÿ澃­:(ÎëÑ¥é9Þý£]LTù/þþ§€wÆ+4ìøíw*u endstream endobj 164 0 obj 18816 endobj 165 0 obj << /Type /FontDescriptor /Ascent 924 /CapHeight 0 /Descent -270 /Flags 96 /FontBBox [ -200 -301 1041 955 ] /FontName /VRKLZQ+NimbusRomNo9L-ReguItal /ItalicAngle -15.5 /StemV 78 /MaxWidth -1241 /StemH 23 /FontFile 163 0 R >> endobj 166 0 obj [ 778 250 333 333 500 250 250 333 250 250 500 500 500 500 500 500 500 500 500 500 333 250 250 675 250 250 250 611 611 667 722 611 611 722 722 333 444 667 556 833 667 722 611 250 611 500 556 722 611 833 611 556 556 389 250 389 250 250 250 500 500 444 500 444 278 500 500 278 278 444 278 722 500 500 500 500 389 389 278 500 444 667 444 444 389 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 500 389 250 250 250 250 250 250 250 250 250 250 250 250 250 250 500 250 250 250 333 333 250 250 250 250 250 250 250 250 500 500 ] endobj 167 0 obj 900 endobj 168 0 obj 1591 endobj 169 0 obj 540 endobj 170 0 obj << /Length 171 0 R /Length1 167 0 R /Length2 168 0 R /Length3 169 0 R /Filter /FlateDecode >> stream xÚíR{“¹Pø  €%‘€§€à, Ñoiƒ'"€3‡+‚™ŒX>`âŒZG63© Sø± [ÖƒJa*ä‹,G ð_8ÁüAïi, 1©|`;È`Bô‚CˆÎˆŸiš€û¥´ „y2S€ Ö‹Á ™Ib‰HG }8²Û@™—ÿ†­¥ÍÝ,–…½Ð~qV«SØL–è_ ›+àƒ0@æÐ@Z* ?›#ƒ4¦€½´êÁ§°˜TGˆÁs¬•Æê3Ïä¹1… ͗ɧÆt ‹.ò D[êD6¿EhÏ OÇР/á.})ÌÏù˜¯êEŒýŠeC‚™B ³° 2¡ìýò¹ä2WˆÊ¡1!€Ã SDŒ¬°¢BÊ£- _vMf@çÀˆ…\qxÍe.p‹o-ƒ²¤8´¯ @S9l6å/†€Ð,ÇûJ`4EáÅ~epš±°Á² ¸¿Èɉ#L0·Äæ8¼Ì0ÆÊ â1{þ]1w @±&ZZã—ürŸÑ(0í/b¡LÀ0ñ7W–ÍLgÊâA!HEH»8TÛ”ÇjÓÊ“\KÛ+Q<ýü²”{×Skòm-^õÛj<„¯´‚†ãê©ê;˜çÕòÞx]@Óèøßtk[Щ=ê-ªZ¨’ߌR_EDÉß)ºÝ´Š]øÃˆôû!î³ÑÇÆSOw]W¬ô~%žÒ}sP¡¼»ëãDRÜÞû¿IUŽÓŒ‡ó‘E×¼sÁmÏŸfÿ2÷ÚSÊ‘ž¹³:âÄ”æRݦ¾Ž¸^Õ|Rfyù£|»ù”>p-ˆû^òO’g€²>áá¶â|@nQ~ˆ}Ä‹üVyðŠ4h”¿²Ã#yOÞ–` i½Š j¹ËÎýŒî2°ª)¬‘mÝHªòKÖˆ«jÇÙå`¹Wr‘þ1³‘ãë)LF~øÐÿþS¦nã(5ÁHNç¢|°™uÃ.³W¨{]ÅÎŒ£PJìѾ£Ã–~•Í™·Ù¿: $ÖÍÒ£}Z]ç2Œ¥8Ä ›Yö±âä0³K’–#\…r¤Ð›Ð¦Sc/o6fà¢ÜœÃûcê»Íîˆ/ÿ\ê¢)NWˆl‘¸¹•®“(szVÙkêÛj«9F ±YÒÂì×± ‰ø¹Yƒó6„ÂŽyÛá¶¼ –+oÊIŠÃôâ²,^š&X¿]~ÝK#j·W·´~·á-0ÑÜïXÜùr¯ò4¶èiEn©j »¼8±aÒQr‹^g•&^{§LQ·‘ÑwÅïøjÙ¾NÅXÀ¡õM ]œMØ…«ß·`üÑa_æúLÂὣﺭ ~ˆFب ô ’t¹®ñyIŸR¦{Ü*ê®’{áRh¤"¿¯õ7&ið@Ãiu±]È…õöº•?ÿ>³ÙϧNLÀ°BÍ.˜CÒêN±ÅZHšÖÐ' ÃDªÓBÖlö˜ÔZ긙in|äÙÕ¥yÛÐIC=›kF|ï™S6PÀzZ–©œ|ŸÂÌDžÎм¿°s ñrqÍ¡·Ä7lºdÎîéƒ9Á>Í»oÞrÍ’L' ÈYMçɹ6IÇ ›_õGíîíIö7 ú)°ÔºÎml%ãr†ß~çÎØ‹å%™Á¬ä¡Á¸ÒûöNë÷±®ÓHowíÔ©M|Cz†cVXë,R=³ä“ÿqŽ`C/qþªc—H[µÿìÐáׄ¹O̺KÂÚ‰ç¶Òˆ î?©=[•| ¸>Y¿>ÒøAn³†®öŠ Þ”òq3×}QDbÅÊÏ èÝ_Ÿ–³;ÖB •õqú~þ­Õg†ß3›Ÿ®ÓòñÐ÷½e/χÚSj{Y·£o*•FkºGÏÉÕó1øñÅãþ|ÓƒEçۉр'³'RA3“’ZT¾¬Ü;²[8J~­œvm'â-W•&/[›¼ò$*ÑjuP~[›ðYš ‹Q’–>¼Jù£ª$Æ)jMì!\M äÚÁÍJÝo›h°pHa">o¿=eô’«¡¥ßÜ(:mô$lìIzÅš$|üEƒG:Qç¢É‘•&A¿¼¼cÍH92˜x?gOÒÔ$µæ®xÛEßô{³e8;U³_•¿ÕZf2Ë0õe¢¸Õ„­Œò>ŸléÌ€Óè/ܿɉh®&øWïÓ9©ðëd@ÒZæÎ~ûê[Ý-R‹ Mœ¢¥ïö‹sMÇ[ÍõìG.qkÀMÉë©$IޱÑs/‘Otf{Ègï«–^jŒ};×î±Ô¸÷ÜPÛ¨lØtèÉU½I‡®±ËüII„—*ÞùA\†!6´ªÎ<ßO+‚˽œÍب×;~÷Yú*²2¥>¼£À°Šùþ™UÎn÷­jã¾> endobj 173 0 obj [ 278 333 278 500 333 333 333 333 333 333 333 333 333 333 333 333 778 333 778 ] endobj 174 0 obj [ 570 ] endobj 175 0 obj << /Type /Encoding /Differences [ 33 /pi ] >> endobj 176 0 obj 897 endobj 177 0 obj 1467 endobj 178 0 obj 540 endobj 179 0 obj << /Length 180 0 R /Length1 176 0 R /Length2 177 0 R /Length3 178 0 R /Filter /FlateDecode >> stream xÚíR{ š©ÍOl‘0) ‚Ä€¾íª)’` ¢ l®8 Å4x\!àŠð P,5l„B€3•!8 D#@¾1žBøO €Æ“¦ ÚÁ`6 ó%a_C *ÂLúS6«Ì$…R€âINvˆyùoØúQœ% ¸¡SòS¥úK˜ ¥_Hh˜D ¢áƒ(ü#ÕœöÆù$ôǨ˜+„x6°@äi± Hï‰yA@ W(?ã ÌÿÑV¹ÏHÌ-ÎŽÎv_ºú9æÂ…¦ûþUõë”?ÏXuP(ð!OMFÄÞ¯;¿îbÂ<„ÁÀ„F¸(Ê•âɘ” DS惑‰&ÈK°šÄŠŸj¨) …qQ‚â©Ð4Jù‚N·ïLÅ`¡Dô 0Çx(—Š¿Ë7§~ÃÿTøk $2ÚÈ„F°sM&›ætóØï™î0.í642™l†Iÿß®b.Ìç¢üoÀT˜'A1÷âÏs‹õçë9º ‚‘ ÿè³L άI*ŽcÞ-Q1PfÎíw:s±íïs¦+ ‹n8„tUy~<%_ ¦PQ,ß>¦-Ú]³ùkpgøþ¬ûŠˆm yÔymÏwr¶ôE˜î ó.Ô´¼¦);·vÝ,Îð:våÈÐÕ|ý n}³Ÿê(5úDœmÌI¤›y²äB÷äߪVRu8„¬ðâÓäÎ턌³:ï$Ä'«Ö>Fê%ó?ªæÉ&|ÿÐܧΫ_Nåôhpú¬^Ÿ<–L˜W9Ùt­Ü:¸¢€Bå±*ç†]Bò#QK˜þ÷†´n3S؃«Ï×{êŒé~]E½þTCÿ cö“‡"¥{Ušè}0/¨wíXÑ?3O&Îß»Åw•·ŠÎÏçƒõ´¼¯ÈsîjDQÔF»/±‰Ãë†YeLFK¬å~6±E"<ôœð1˜±j,Î9`즫k]^åjåV/sthâh¡¤eiÖÃÿd¤IË»}½]ÚR9êì±V¶ÛŒ˜âüNud¯Ëšsâ´kMAÜÎÞ‘‰·iÚvšVù¹xƒ¤¹Ñ\÷¤pò:ESM ¡¸pÖ@¾¢´~}Åè(ˉ“ÎoÌ[>…ºùTÕ7ån]˜ÉŸ}êH†»°}HuÅ GNRÍS‹òÄ9VWÕGéi– q'î½|Õ¨mÛŒ¶¬ Yê¬vèPÞžÂQžñFIvüè1Ò-!l,ï²^*×–©ÏË2;ôbç0NÃnó3É,“òxaµÄ{Mu_¦Á©F=\Þ’ì±‹Ž„×>9èR×xø|LCsË!»´Ùž%Z„š00ö•^‘דdh ü&œH¿ïùèåØE)U‰ûm•™s»ë5ßö+õ¦Þ⥼[û[ä È놣:ËÕb—-2R÷>-[¼ÝÄ»-½ÏØpA !Íle#!»G §·hwÉõ÷=Ô¢eçüF¯¢`õõ¸€5ªÁ5¦Þ £j[Û>B—ˆ6YÚ†c™„²ß«ñ{ªM)ÍgÛâ;tx¹J~!¬”· Fmû®¿øäs%eý/K+Lõ3-ü‡Ü/߬±ªª½8ü&=NqĮʾ`h'´yVaŠš‡ZêÝ‹ÐOžaɯ”tÿ•üÀ…v­Ð Óƒ>øº)ákä®ùë&^º¬M(teödãø™fE[ÇsÿÐÍ[ û–›ž£ êU%3²ÒÁø×µ­}¡¬¼ãïµ·ÀÄ…‚»aóˆY){t£ùÅaÛŒÜÙ÷t ­-«*M^îØ›øjoþ3)•ÖÎÌïLñ f»k*5õ"n1Õ$¤AÓÈ+]û¦ñl›ƒ#Û·£æ·,~6\q}´ÍÚݹÇ^°Tî,›ÑCÔB†œ~¾oñºõsáA‹òd©ãðQëóã÷™°îR¥_j¢º¤iu^XœU.›ª˜¸³¼gæÛÒ]îWéY;„ã“Õ‡î6Ȭ®€k±‡M’ÛÝî¨Ø–{žSŸÀKÿ1ÉÐ Ò ÐPÕzVØø;)GÖ_&«ÈÙ[·«o®c“ëxet—^^g}¸{Ñíø¿J‚QÍ·x õaPºÛ¶ÙîÛ ²Êþ}t[«¡÷æ­e#/½Ï©…1Ûé-¥r+zG™×Œk¿hwÕYJ³/í¨EÕ 26!é*•Fì:îµáç ïð/“^öç§|GZ–êJ?žÞЖ[©+ýÔzkÈ»ÁgæßZò*º}·wHÚêf[×âRݾ¸™IÙÄ·ìUr4³åd¯^ýW|ÉŽ.ˆßåôzœ^åz½?é1ËÛ÷þÓ•ä«ÈÒ:a‰á¢GÆ„‰ý«†ëcOµ¯½ 0·¨§Ò¨É¢dÇ{ [<¨Íý­EÆ—Ú³bH*޶½Ûg™ÛÆ(Ý}¢çÜ0Íø\í‡LË>Ê|çLm‡ßÕ z±ó.¤ê¦¾i¾¼©FW@ï#ÿ‡ÿÂÿ'¹¨ å¢!ø.ƒVö endstream endobj 180 0 obj 2086 endobj 181 0 obj << /Type /FontDescriptor /Ascent 969 /CapHeight 0 /Descent -250 /Flags 32 /FontBBox [ -282 -281 1040 1000 ] /FontName /JXODNJ+CMR10 /ItalicAngle 0 /StemV 69 /MaxWidth -1322 /StemH 31 /FontFile 179 0 R >> endobj 182 0 obj [ 389 389 333 778 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 278 333 278 ] endobj 183 0 obj 871 endobj 184 0 obj 1004 endobj 185 0 obj 540 endobj 186 0 obj << /Length 187 0 R /Length1 183 0 R /Length2 184 0 R /Length3 185 0 R /Filter /FlateDecode >> stream xÚíRmXåN‰¯…ФӆJ¾àµA*»3 ±ˆÄ.b(ì²v(‡™ØÁÙYÚUXÍ(rýèRÒ]D5¿ÑLɃ^àAò+ÌES<Šb‰žY̺¢çÏùW3æ¹ïûyÞ{îçùD34—hÌ…h*Fd qŽ:J9{ª".!E‚ð ‚ D" qŽbè(œƒ2€††¢ RŸ P !2)"ÃB" `r,•™ÅÅ›vQˆÔB–"pÄá\Ôò3\‚‚œQ "50×Þ¡s¡²y PÁt˜IщÝa Á€§0©Ï}FåAVÇ›þ¼Í7o‘dh0C Q2üYwòÿ05zx´^£QâZûø‘¤þÄãZJcüUÁhsõdACB–-M†OÍÅA’ÒkG³1®¡ˆH:SA$F±§¥‹¦ Œ§8" dàÁ!M޶ÂÇ7bD¢LI”'%?ÛíSO×ßÕ#5ú{ͧÄRð.b¿ ¼Ÿ}¥:l&M0$Eg) p–Å„%Å0°MB€Þ±DL3ßøh @à ìkE€DKÑz¤o‰êtZ=ßó $™öûÙ?à( $é8;ü9¹œ1,à›BƒyS( BB°‚? “hj¡ÆD A·¤È¨ßJàpšÄYò7ÀNz–…47r9ùüŸÕ¿3 ´_dˆ°ÙŸ.ÜišYyv—£ÄõaãžÛ¿N9b²RdAV¦öÉä¶Ý¬è¬Y]/Ìi{m6¶Á“=äeV®zïÞVÏÝ5ÅåÛSÖ.ÅêÄß%Ë‹K^x<ÕïfLýÂyKWvNÕ±]–'Ok¿7yI£{yC>¿òÄƒŽ‹nã¦ÌýtŠïøöζ1¯ ¶Þs“þsdÉg áDÿ™Ë±1ñB]t±_[Æ ·ô{øýë‚´Œ¼¶¶©êžÈ“çot~ðùÈCµªî]Ãmï|‹DwN%l7 ›&,¾Ô”ë,üö£[æŠÁ|•« Î[~Úv¶~EC§dÍÒY'¼c'6vfý2¾qª²ä•L¤#pìÁž#^ÍÙדìC‹žÜpÿ¹ih;žSZ»Þ;êö¢…UÇÂ$ Íâ9‡7¦l;VïvñØ?PψóíŠ5·¸*[œŠ¥qúšû%G²Vß’»û‚Z.žµ­k©ö9w¯Íùê´ZY…G?v2Ÿìîøät.²»{‘ýÆÚwP]~{A$«[.M2yÀ_ª½+ vÖ¸9®ä.~V~TñNËD¿;ëÛ‡ÓÎ9 ›•ãÒ¯|ªl jß#˜èДð¤Ñ1‰§ÿªéеËê;±{©–BK»×Øãiµgøž{NÅÖÔÏ)27J¦ï»ÅU^xƒúw’C­M;cýpZòÐÉjÏg®ZÖñm—æpüê|¡vøÂ]£Þ1__ѱuwìМ ƒuëÖz¾×µ¨äÀÛÑ—Ò}'å›_ô¯êÃ×p»ÛOd¹jk˜S!RÕ“t³þ•*ʘxT•»Y4Ùã…/ØÖÔyÖ'¶µ?¿Úê2@ÙîŽÉYzãÞºó.oÒzÓÁ{Kã/XÄÌš]Òìn«ãÆÙa‰.{±æAц™WMhJrÔ®sv-sÙVÖ»ÓÝ<›/¸PŽe­tP9ÏtDÝ=ª¥â¯“‹Ã] ye úç^RÛ\•pâKÚÉ¥ãZÝ÷¡E;îÎ%®Küûœ#ö‡Ö6X¿šTùCaeS`Ê¥EýO,WŒ×"Z››DÒÁ3œúè‡VyÕj5Ý»l¹¡gúq÷ÔaãÐK«³–½}ì`ú’D¢oKY…›wgb+ñºßâY±Žk{”^ÙCÞÿ2¼8àdNN7 v_ûfKoöå\µA¨h^P2¡ßš#|èñhZë?«ßÿ±ÀGVj¸_ ‹ËI•õãÎüCSä§ê¯8祖‡¯¿ÿkþ©†Ó–Æé'fˆ ÿIÝ4®¬­òÔcË~ÿ•¿¬2=Œß×oN©ž¼…⎺ßÚ…É„ïû/ö]¢RŒñüb|ÙâswÜ'=hÛÖªçÅ›>Á^ÏÉ'_pU7/9©—°ý„üGð·à/% 4g9F‹³9‚ÿn¤r1 endstream endobj 187 0 obj 1619 endobj 188 0 obj << /Type /FontDescriptor /Ascent 775 /CapHeight 0 /Descent -960 /Flags 68 /FontBBox [ -60 -991 1147 806 ] /FontName /TKQDNJ+CMSY10 /ItalicAngle -14.035 /StemV 85 /MaxWidth -1207 /StemH 40 /FontFile 186 0 R >> endobj 189 0 obj [ 278 ] endobj 190 0 obj [ 1000 1000 778 ] endobj 191 0 obj << /Type /Encoding /Differences [ 33 /greatermuch /lessmuch /minus ] >> endobj 192 0 obj 850 endobj 193 0 obj 856 endobj 194 0 obj 540 endobj 195 0 obj << /Length 196 0 R /Length1 192 0 R /Length2 193 0 R /Length3 194 0 R /Filter /FlateDecode >> stream xÚíRiTWQ°(RY¤Õ§A!ÉL „åHe7T(jËaÈL`J2“ ’¦Y±( E eµ@ (k‹¬¨`ñˆA‘Å£´ í·SüÑ?ý×¾÷çÝïûÞ}ß»÷Z­ô! :D‡Ál˜¹€€!^~¶žþÁ[‚ ‚YVVž†Ð8Ix!4æ`gg¸Ë£ÌÀ…»ðy,+àIÆ)(<:†6žkÔ"p—b.BàÐ1˜”É!B$ ˜á­àw‰lRßM˜ £0”Âa€â"DaÑ8Á⪠1 /aT÷šJÀ(c Ø06ׯ"J@11‹@2oaŒ“ÃÔÜä>r‰$‘ªÓ« õHq‰â•€”ÆÉiŒþ$ŠQÄ\iöÒ›?†âré\VH#\äNDK0À†8=ÿ%Ë|ðD ÄiQ #6‹c:× S½Y#\ßàp/ïWåüeïôV<Ãoc¦Fž¶AêI`„Ì~}úlÎ[Þ„ˆDq"ðøŽ¡(DÁ‚˜T<>(a€(–°DÆ0—C4s0•Ib’b©› ®'ä25: 88.Nˆq§o@ftQˆ(V&Ad1³ð»?öð •lf:ÙÎ|À<>œxI†x¼z>AN°`Î'‚i„@ }¨i‘œ¢0‚žD¦Ø¯c1Î4Ã1«¯—¹¦~ž2ýØï²®ïpu§;«Gú´›ÂvÂѤ`~QÐÊhº|´d þ«VÓØn3?‘k®1uÂ|_@VÄd©qU}æwáûSøg8¿›*veæ<·µ¶Æoþº0mÀÂå 5X°ÇÒ®oÒ2¹S¿öØZÖøçÍ^½%k7å¬]µLÐwT»_ÓÄTÑïrpùìXVñ@í¥}ÔÖ8sa¶ß‹!§Óµ–é¶e½œR³žº€¡%--‹Zjï3í+ÉÛy~¶ÊB¶i³¼T¯8bgFÞÕ0 ãgÂèÉó&®¼0ŒJ;×ЇéÞm+æµ쾄”±ÛÓÌîíì%Ð*£ù~êλ;Ée–Cý»wgJny7L­á‡é4gќ۹Æ] %7ÁöS‚âòìê@¯¶ëv]‰^9Ö¹:#öæ¹=ªÐÙ/¡0íŸíw)Ž;“ iK²Ÿ_sœï×a¯ÊšÖ;±áãfÉ…ç,"nyHúëùm¦.úP÷¸ ¥yÓëuxדUŽŒ™sAÁ'þ¿º©ÎUØœ´W~Sä^ßžKúÉ6ßF»ÙÅSG§¤ðÀ(Zú¸#ê‰#«§àdkÛàUàæúd鼌žHdz?µ"iò°Å­mUë3ÞkÒo,·]~bD¨õÃÕí=ÁHV婞…•×ÚTh÷õV4± zѰ¡IQd»rí ¤²Ø“s^ìºoÐR§xüvTeq—¬Å¨§½ƒÿѰ²«7-åàÈUu7·tWgäE}yŽFzQ+YCZS»¾Œ5{Ø0£sگ仆ÊÜ?Öe>¥<‚Öµqïׄþa±þü§" †P4)E¨XÖ_M!a endstream endobj 196 0 obj 1452 endobj 197 0 obj << /Type /FontDescriptor /Ascent 782 /CapHeight 0 /Descent -951 /Flags 68 /FontBBox [ -46 -982 1283 813 ] /FontName /NLTDNJ+CMSY7 /ItalicAngle -14.035 /StemV 93 /MaxWidth -1329 /StemH 49 /FontFile 195 0 R >> endobj 198 0 obj [ 585 ] endobj 199 0 obj [ 1139 893 ] endobj 200 0 obj << /Type /Encoding /Differences [ 33 /infinity /minus ] >> endobj 201 0 obj 1641 endobj 202 0 obj 16227 endobj 203 0 obj 540 endobj 204 0 obj << /Length 205 0 R /Length1 201 0 R /Length2 202 0 R /Length3 203 0 R /Filter /FlateDecode >> stream xÚ¬¸ctem·&ÛfeWlÛ6+6w’›[•Tl£bÛ¶mÛ£’¯Þç=ݧÇéþþtŸkŒuO\×¼çXcQ|•´·sQót²0°02óD%•D¤èA¶&®Î övò ߀®fæ¿Zf 1' ± ÈÞNÜØÈ ÐšĦVV @ÌÞÁÓ daé Vÿ¦ICGGÿŸ’™L<ÿ‡æ¯§3ÈÂ@ù÷Å hcï` ´sù ñí¨ \,s  ¦¤¬-£( –RTHí€NÆ6eW)@d ´sÒÌí6ÿ>LííÌ@ÿ*Í™ñ/–ˆ3Ààì4ýuz˜þ¥¢8lAÎÎß g€…“±Ë߸Ø@v¦6®fÿJà¯ÜÜþŸ„œìÿZØþÕýS¶wvq6u9¸þFU—üwž.–Æ.ÿŠí ú«Ø›ÿµ4³7uýWIÿèþÂüÕºƒìœ.@—Å2Ì@Î6Æžcÿspý“†«3ÈÎâ?3 8-ŒÌl€ÎÎaþbÿ«;ÿY'à©ÞØÁÁÆóoû¬þg g 9# ëߘ¦.c[€ì˜þ572væöæËÍ\þ‡Î èôOƒ¨ÿ Íß$ŒÍìíl<f@s&E{—¿!Ôÿw,3þ÷‘üß@ñ Áÿ-ôþ¿‘û_9ú_.ñÿë}þ¯Ð’®66ŠÆ¶àß;ðwÉØäÿZ36ÆNÿ›¹±-ÈÆóÿàð_ 5ÿNòÿGÆÅøo3Dì,þÂÌÈüo!ÈYä4S¹˜ZÌmþv깺ÐÉdüËè?Í0°03ÿš%ÈÔÚî_­çø· hgö_“ÿKÒ?©3iêhÈjKþokõ+å¿Üÿ³‚ÿBSÁÞìþ…!*jïðfø{XÙ¸œr³°øü¢ýÃòŸgc'@—ù_ÛûŸÂÿãùÏ“þ‘°3µ7û׬¨ºÛ™ý¯ÿ)øúAŽ®@ñ¿U³2ó°sü#5uurúËõ?{àoþÇùŸñ=€¦«Kö¦|ÁV©i.5¸9Câº}=,C!%õj…ùþUöÝ~©á;<åFïÕ!Œ S¼­ž‹gdiGzpl¨º“WyD>d4½ùè›”í\t‡L%ÈiçšÑÞ× òÛP:œÌ‡»*ß Šßaˆ§ÚٜடhüÉÜòý±ÈP|MSêb±;ÐÀ0j ÎÎ)Nž©F‡‡»o¡{é²cá)øÜ )£ü³ …tÔ˽#h`Ò‘oÛ®?H4»¼ r)È È#må_•-òÖìÚäß¡ÓÚ„øœ¤[*´pn榢øE¦xfs>×])$œqù‰&ƒú~ÏX“MgÀÖ}z€¸¡îs÷®±­¢}íEÉ™žVé(©so†9 `fŽp­@kqp¦ðÒ[•³¾ÿÊ ·‹Mx\Ð4h®>—7ËÑwªÉÀSfmä,0n¸ j¼ÑQ—&+:Wñl÷½Šrë#$ÿYê÷È¥¥‹X™zÏÔP¢ÞÑ,?¯ö”8ÒUÔŠÚjI¸œ%AîË“€NG†‚c2Ÿ9¦ûyÖœî±e‡‘Z~àuê:€CŠ03_ô¿b¢Å-Ë#·±Õ*dj§,»kzÒb«þÁ[šü5¦ºÈñmxle*3œ?@ 'Ú ´ýA¯ÞŽƒá`,÷yžÔÏiÚúMwÌúeÒ EÜ!†¿#ÿÎs,¦Ñ‘D%2Úô•`Iòj®Ú¤À,j¦c ’õÈyè8¸þ¼à÷ñ—´„VßHîgeéߤX¢•w;s4i5c´W’GôV³$8"(5†§›­!üèà MK¯Ô˜YXN‘Td»³†´Ï7ì¤ÓÕë®íE÷N»° r#"-Ò<©ãOÁÈgu“ Ä7\Òl{ûXÒX¾yX²)¨+,f$ÒU5uåµÏ®]IÜzŸ0œú7F…² bR$gñ `Tk«x`Ðý$¸8lÐe(.2¬ñU…ó®1œw[h´"n*UòÐη PžþŽêxÉ¿»·6þ Û} бM DFª·;±ÞQÞç"$ªjºn ßWÏft Î/IÐO=Y/3P¾™ŽN 9”Ïv­¨°=IG¥ Ä@ŽQ5ŒÉ¢!ÄÆ_§xF&{е:ƒêyvòõ=Ò~–ÎÑIèiÁ^1κ° „Rq˜9tžIÁKâ¶£¼ø»LãT\›B Ìã˦œµ»1u3ÃÊ9ò˜ÊÝ“xL%=ÛÕìÔK`„GYLIÓŠ‡G®eúÊ/ôŠ'Q!å[.¤{ªƒSIó¼$£"´úMÌœ¦÷¨9*Øö_'|8æcËÏð÷ÔÄüÙͺN60 Å„Ü ñ,œµóÿþlöã‡í×Ô9—ÊÞU/4æëVÐf ºzO „­­M9B\qÑPÏT÷fêÓ×Y/T¿$%n$Õ¼ L96n¤sJ2‡ÍÜÕ™u‰„ÀuÍfûdh¥„ ¿xÛ™Ïä—&Në,Ôdôyèç/aÛ«®RQ$p‡¶™ìa! *VßaæÈãâ@ÍòÓ«¯Çˆœj1PCa ¡Ä“Äz§>ŠF»¼cú#ïùç‹ö;œí;.»/¸|L€d¯j²|^BéMü²í½oKžãáÌy¹)ñ:d¦µ¿ºÍFHÜßQ|CHh zÆ¥ø‰÷ótF©²ÝTìúf(c8øIXA*& O‚X2)œ’k*åbàÕtŸêÓ3ÊcnŒ„»´ „s­Ù¸éBè2pNê5Ð\œ¼gr— ó{‹~½p3ø´ZüÝÓf ×b_þÌߣŒÀOd42¦À¥  ‚I÷V‡˜ô.…/Œ´˜\qx¨—AªO¯ð ¹¢£ÖÂeÓòвðOM?â—fß,…¤øT+ñ`v}4˱ ÓT)Uª%ziG¸uJÕ¯R Ű²»cÙF,¡!^‚g4ôÀa˶é“Ûyn„KT+WPÀý‰ÅÉoYI»¢GŒAÒÑrbZ"laÆ Êý‰9/ã,?ztA‹]E³ÊNÝ[ò 0<äþÎR~­e0„ôUù·dâðØ’næ?í."Î.Ê÷Ï&©Ö>}˜ö?Ö’’%·Xˆ¢¸vŠ ®¡1¹–+ØÃ> ­Õæ™u$QC£W´Ø®ö+øÓ`Û½-™á‡Ìmª´™ÿt…þÀaÀŒ·êÂ<Û¶5T Gøé-Öüg¥•v]/äÅÓ6÷>âœ#ÚäæO×ÏáÙ&UN:²ZGËD6­øtZrjéÍ2_sê=ʼfB ']R¬¤ ìáÊ4“g…³'¹ÙŒ~/_ý^`¢‘zµ¬ÝRM^ˆM]?Åúyˆ*f‰8900tc]ûÚ&Oc°wN-oU7Œ«¬J­ÐV™Š«ÀÍxy˜šv8s¸ÕYq¦ÈÓï6s1äkêîê`5œ–îšÓY¤7ë¾n¾Îðÿ®öåÚ凸ØHDcQ¢Â> ª­Fß›¬ݳïÎoÚ“Iûy»3Æ-”&€Ó,YõØ…ä'É;ÊWçùC·csa™G¥eœÒ”«"÷{±[øW*žN‹¹õUXœKyBƒ… CHØAý—‘CªÁÝ×@ü¸îÖ¾'Ø­7Ý‹ò—WgóV×ÇÀ“]CN›ÓHf’·ÕP3|ÑX™®Ð"Ú'«³çô\gº¨ꥩ®1î§WKèùZ«ÚSg|×Ã/Ú,±Â˜ÅÛiϳ“»ÜcÉwî¡©p?.ÑsBKº¤žmó¬^àªÀа¬E ±Ë³¢(JC'Ä Ù‹™D–Pˆ ë`\@B–JðYíÝ’:t§F(8Í„f4áPëb ñOÐ`Øë7:·Ýܦ´saöW*Æ6ªû ®ÁmõŠOãNøqŒÜvŒZ¼eãÙ{aÎõ°ÇŒ £ÃÅF{¦}®ëß«ïÑ¢8^bSwV©>Žß0 {„>ŠƒJt¢&:C˜cé$Ńì†iõ8q|ÃJÀ‰¡àz³ÝÜÛ×öGtmò É&¥$ã<âúu N“Îè²eÌ2‘ÐXÙ¤ƒó9_`™Wºà–úIQû6 (gã÷1˜ïÇ,—04k ôÍ ·€íêƒæ^7„ä²ËcÒÜ<ɾo9õÜ–l±u8N4KHF¼ßès“í)¹œ M`œÈ nÇÌ«€€¾~éÍc%ߺäó þ*+J˜€f}Y±gl¬°­=WÍ/N*Ã:g€Ò|:”»–Ú _¤©Jüj/4¸J&ö bÙ¶Úønq覆?xýÖ9»3aJ•ìj÷ôúÍYÔ„ä>¥ÄO…9ÕÈ£nó<Ù”* r˪ŠëxL8®äÛôøG\áæÉdÌMUHγ)‘e=èÁbºJp ùùàÏìY¿ÌsÚù„î?rÙ´‹ Ï>>()N0‚¯ù¦kE³+4ÜJƒ³»-²ÕQû«ÔÞ®;K¤D§+_°cì|A;rP×c§æ\rD«[§,iº²o_7 m&ï¦á³´vóî‘e²GÉÇ‘PçSm¶™odiÒò¼Ò6úu™éH^JOãžæåò¾áÄêšOeׄÇšÜÓ'#Îcï—Á~Ý1bNáãѼ[åì.Nc‚HÇ*‘•ÆmÜÜc´ˆð*9ñÍÊø. q~ùç,»‘_¶ðŸ®°?öHBïgíï½õSKËAzjy™¸]O4œx?„W¶&¯ÚIoâzâ=·Ëo¤]ü½/Ú›³¤7Oï~+Ø¿ž¯å¤Ê›—s ôÈ(â‹O6µ ~¬ Õb3ÖxMÀió~*®E`2^ R݆‹¤3NÖœÆT§Êþ¡h±ë;|*û€ÕÖÆK/Þiþ«’X£†ã}é趪H„éRÞ§¦¼½`ŠTïõ‘n»ÑƘR8ו{‹„âQu½qžé¹èøÁž˜pItö3¡EÞ¹:-°Aê.ãëÕ—×'RÁ,oòAŸ¥•dìuòcöz€!¿De«•¶Þ»Ëþx”\d9<›çOd.Ç|Éå!Ÿxл)Æëõ{êË0 «¥ÕiœO ÊM%ìâ ´itN÷ÊÆcŠò“”Ç`éCq–ŒhËç§;??–/ê1«cûŒÄeE2¼KÑ1´¡¤ƒ’&îªl=yÂCXIØÓùB…9¶¡_yîlšL¶î˜Yô&–'ƒÚ(DKGyúTpð O¥…–oï;òçËj·%ò&üþèSÛàדÌî×ú¯/Ïò*,g ­¹z9^æ -çÅJýÄlG)æïòñ´Œz™75¥‡zA’>ä¦kü¢Ú¿ZR”ØLu)Æ&›c‰k󄤯j//½8QìF ø¸<ùÚ—Çwy¦`|ie1Ù|è’¶HÜáFª‚œIuGXO0»*¶§Š;ž’ òyIÄ´“ðR8mÆ” »ÛOí±i§$˜ R°Õy8:`³%ÅŸã³K´`oA˜ôþøÁ²(åöòùÄ쌅N:Þ¸Fe$›¢ÇЄJ»4î)Íù–"Ð/co»³© Sj{C3óA`R[õEüõf0Dñ^™¾¶¼p´Ê5ö;Mÿ[ ]|7<Ól¼xOËð»EˆŽñ=þ ’4a%MòßSª*¯~;(¢ò ¤:HÒ¥ëQ”fMà ¸k3lí¼4»fß¹œ[Á|S¨áðYðÈÂ~ø{í,’½Ä«¹óãQTZš@#\Ñîî ³Ñkø7( ‡ g´\Z•^ÃÝiX;9ûRBº~»¤‚'!3*õlo™òî‹f>djë!14à&ãP‡e–œš^l’†«úOmº ¥Çi1ˆ[uT¦@Lq¾nÚá¥Å¯§3%È­ù¿òtŒ½¦6/)f5¥"œõ2kkœ×3– e¥ÄÞ}ó¬úáju´– ܯ\ò1½V÷¶äs Ká¤QζÔo„SöØÃ3Pu¹–ÆI†®²[ ¹fÇ9’sí"½ÀÏOoké#™ñÅõg„)öpµ à»œŒJ:Q™Ê(ž¹ÉɽpÖZ¼F"À1±u°¢Ï€ö•ž ¾•]Á`¢sÿâwjÂ’ ŽÆ”{Að·C«:~2cŪ‰ç|óãÜ 'Š œQ4ÍŒdöOdO­»~BŒÜKUŠ„5-'=ãa‚6 ¸E¯ èá¨òÓ{³£ÄØmk:¾º°É-¾r£ç™|…¾=(9ZrwÁJ%€ñhÿÊ= ì Lä9'ƒ/©¶Ã¶Ã4üE€Q9¼YŵǯB|äØFëÇ<,ë®ðAËϱ‰Ùb™neÔ:o¢ûlÈãºqçÏ6ù.烖GÃu¶ÚqÞy–d£¯x.böÃò(Tò¤ø:Çë­¡¶±þÇñk)Õ~²^åÎûýæÚzÆò-5»Pµ› Å>, ò—.¿éöE‹N°8Ò×Nd+°µ¢åf#=Ðe$p3Rñ穼œõÛèon”—&t-úÐhšÌÙSò¿•%7ïJPšú¥Ïd߱쟷£¡•H¼}=åƒpz w+`¸W¡…¡£É»[ ]]ü`,Ùü²Ti½Ø£è×+¬…ÛÊ&ZŠÇÅi[9‘P1p¾ \UòC…9ü‰ÕMw;}1#-;ýµÍ’%£he(´ݳïòË£½àüöQI‹þË[àñþpª•ÖèƒÂïôÎö d52ÉÑš)Ú–“ ˆðKŠ©}òðÆŽÙGÑÂß1lS´õrÖ'+Ø~qzh ØaÜ|éÀ¶û¤ûµ‹†‰F¡¦‹Xƺ€*×^ îlÂà ’~…<¹NãiiÞƒ7ë»}hJÂwþªÔvnäÑ€–PuqNn¿ái¥š².:zâþ²'½Z‚Ëäpü¸Á¨ó';õðÍëG¥¿R'®|‡É‹Z©º²›N–œŒ8pno<Âkwë9®™¦÷-MCð+Wà 0Oªš<Ô'‰œ3µªi/yJÌMZ˜ÆÁ»/ò‹º¼ái'^¶*ʪ8ôIÐ} ´ÖX«1Ž~§˜ù†“)¨ö™&iËSèM“ää†ú ý»{©4*Ž^tc Í»èÞÖ¥u>L‘\;Ø3n|ì\¶ÑÍùÉQyþÍè´~±~¿oèWÐR‚8Ò˜¨£‚£ˆOA°Á´cgÁÀ“Û7ØpÖ›–a÷¨­0‚dÕƒ¬%[>ÔË¿²&NÓUD­³ÿøIR؉mä`ù“ĺüî •€¦N÷ùØx‚¸Ð¯9+”}CúñZÛéX5._èP yŸæ·ÕOLOSŠÕzÂIí=} ã.¢¤“¶qD¨6É—!]œíðYû3ËkÑ»·‰Üí²±¹†Ð{69'L8‰iJXEË$TÊ|ÂbBÅþ(šxß@ÈÏ;ߘ1è_MžÅÒŠãþÄ(w/©ogúeßö.!à=ÍÈpJËy ´’Òù·îXA¥[1<—‘ô-@O9aŸrP,à[é”0iù’jïS/œ:¨ð§¯‚#í;'¾Ò3txÈá—·($Îúz‰mËEC\ϰ†(KöÔY±æºû¯öå'Ö¿¡­Øív¯<—2§Zî`)´=JL×íó)ØwB‡928ñ)‚MšÍ¨õ*ÕOõ›J¼úx‹^Uµ‘ŠØÚDÈŠÕèËù'íJŒF¼Zócˆ0zFÃõØ‘ ×Ô°õN毓H(ZU]?.]‘Õ„ÖJ¢™ú¨‚5Ô¼ÀânØäÌù_oæâ¿¢%)àƒU gŠ=Ö¬Òc™'exÁs”‰œ6Ed¤ÇÝîfŽyV“†àVB˜ýdc#I…oþè/Óµ¶Â‡/1ÁGg¦gg˜`­Û2hOâúaŸP–‰7ïÃÿ;i†bìϲ;çÒÀN„‚øíUPåÛgþz=8Á r¨Ú ý/öWïɯýÚJ4!mæƒe>î÷$¯"”î’¥©‹?i1K ÅËDò†‘£–]ü³[ÃtÔ7‡PªpRnÕºæÜѪl_ªÚh¯®‹};÷ÒÕ¥SÇÑxb5ØK²Ø"—6?;¤ÂiÊ(¯öÙº æõl°ä$&r°ÈÉ3”MW+ÊYsßq=\JÉúBA h$´z¡ßüâQto”´Àƒ:Ýâo­“abÜүൻK-b”Yʱd+êx5‚…ÃMj:Îð5nÆ+ˆ…¿†´àÄIZÂ0ünû?Ý9 Fªži‚Ž,zP$Û©rbLG +c¬}YWäݹO†1ãw=ݪsúUáÞ³G-íÍÂ9›A,Ä.yÅX¢qàÄ%m‰lÚ~ÒvÙð“4È„Ø[7?HéªMCÕ.z™˜8O…nmðhŒ5ãLáÆÅÕ…b_C¬¡å)réJ b1ÓZòÙ9` w| °íæ8Sð°H’ûκëˆ:®“~A¯‘É{ö’N$WçŽ Vá:G×»š‚/¯±²£¿¼"ƒ÷Æ‹OÓá¥F«ÄÖ]î2Ê$UðüRÁ"DS ?9lÿàçÇÏ„èU¿ÐÚ…$¢e—eùyh9 µâyDÜü€ÆfgQþYà´Û©„©b+)´ÉwºLú¥\.Œœêíä‘ùðÕBGbt0æ2¹XïKØô¾½[¼öÌ”R¬9ºÐ)Éx1˜w,Û-ÅŽÜ—P­;ËæUP²(eCŒ˜$íÎzâ0'ħ¬r¦{¼AÙyf–I”JËžPlâËe‚[ÿÀ\(Sì$ÞÙCà¹î›9ʆÁòž‹„13µ¥:®±[¤.Þ;-ßCA<Ô&Zƒ¦wÞƒa‰òégåa!…tël¥ä`âÍ­Kí0G¨µÕÓ™ïDå`,x‹f°reÈ.ž<5ˆ€Ý™|n1ÅQHÝk'Ï‹*¹I¥•B ›o’fÉpíkÞÆùSÿTçt¥6úi·y ô8Ù©‚Ìn¥ãp÷À¬OêÚ!0&…úËO¦@ƒ} <¸m×(' ~”‹U°Ù#Ïìùwêõ4äO½Ú!¨xüwˆüÒÖgyˆ™ò›ã«A,kÒ”WACöâ‘HéJŸp¼¤«œK,ŸéÉAˆŒíÁ£+<Óß·³]U%éªwV‘ÁhÉ,|¼ jK%](†°S¯¼w‰ºm Q=Åßù2$ƒº¶ú–WØqjzfP5Dž¯•ôƒ[Æ(†ž=Ò=`2óœF,:ŸŸG Õ âFßxD@&”¿GhãS5#”zÞø† ëY5cá嵯qÿ°†3Ìw7ެlˆr$Þ\)P€Ø.Ô`ÍÈÆ>Ñr?Vîäæ,晓—£´ïÇC*uv¦”…Û<ä ¬K£âÏ"JüΟ•ÐÐ;ÀBp\{/e«f¿œ°Ãz-M÷øY‘ÊSëuìòõјðLôйðÐô­NÉP.ÎöçÍ*ÕEq^÷Ûç½Z&!ÔÁVŸmWaˆÙ»Oªx¦´BÈžiÒhîÄÎÏ.°47Xu1öU>¡·}.Tï#ÒyeuƒQ„ÙëüM†s…?(ý8.å¬z«—dNâÐâ?­É˜ø÷êI߆¾X‡Ä&$T§åxfƒÏƒ7I­©ÿ®„âTí¥á-ÿ+¾AšŽ ®Õ‹Áeu=èúzEh0@¿ÙC5\6ˆUH'©ª×±Â?·†BP$È…1ô`M¯¶ˆVžºJÚo&‚Ê9ß7G³ya+1 ~Ú4Ð}´^'e&X{£Dž|bwD$ñ94=gtñß8Ó$f¼R¤³^$ÎnnOÓ'# /îá1°¼Ø§õ$'ÿ ‚âȧHGt©G¿FŸ0…° —úh?/lRzD9;|s1Ô4¹d¶kÖøÄaéÜ’H’Ñá4“}z»M }PØ|øè"XZç_êênÓæß—ñW<Óùùg£ Z‰Ræ|‰|úŽùüÉ|“¹]9€§ÎGMã­ddÕ¢4˜I ÕÕñm›{œå½„-–žêðwìs=Æûpqˆ;8< #¤æâŠ_]xãQà —ãcÏ$}z¬Cí–„Î85áÊ{`Yiœ«õgÜ ›n b,KøÐ‹œÂç.Ä:ÜEô]z 8"õj¦•”æÆEuþ-|1x“­8õ4&ê4ö×ìZ49C:˜u®_]œÉ1Ôœ¢ó0%FÛþÄùžÁg©RíøCåMaW~7)O æ†s–4(o!“É(]F=žZoÙyú9"«ý. æ· ¸—d‡9­¦¢-¼ q©nX~Ï{ŽÞ?Õ%C”™ÛAÀUBë;GƒðÕ°ï0}mªo 1MÎufíªÑ†¶œ©=Ùy¼åâœLà~àÊñ ;ÒÐož>’mNJ Úëv/xF«ú…òøE‡„ûöªœ“…VºÅ²4W&×°_ ãö¯£ËÓÂýÍ’ÑlRZªÔ¶9 ]ÚV„½Ÿ Ô$ZÀŽŸ¹ìÌÛ$›ž’Ouº×€îé5˜ŠEˇ'œJ­#9ÛGïbØg‡µJâi(¢ÚºB@òË›ÔoîwÛ+ÿmNµT¢²5WM9º­9ÕhÈÍqºpí‹m‰ø]ÔÄ…Œ® v 3­Cu]ÏŸ¤Ù@<Çð Äv/²Q¯wÕm¼üÇN1áø­"dã»w[wU« A¼›•Ðý¦Ó3i‘âUÝœQ5Î,$÷ØŠá®Ä‚°µ<¥<¯³8a]—õ–F<»P„À§F_µ€Z‡!Ô3û(ÜX…IQ§ãRÐgü%&å×ê Æ*qBŸð‹Ü;,òœÅ.OÉmÈ9c¥³¹W(q6ö߬zÚ"/´ÛYwëD©l )´V %?³!C¥"72dãícÂÙàcô¿ÙÏ(x¸—Ÿ¯{Üúa*Ú ,í¾]ðï€7'x>­|67Ú~õ`òºbpÅð™]¹‹Ž*ä\°`žp¤X)^ÅêápoY²«`D}·rªrð¡ù‰¼ ê_o·÷ZXúΗ~]M€ aϘÝrèïAÊÜYOã/RìC“é<7¥(iD|×ý†¤zq(OÖ1óHY¨IX[*úÑPiž÷éIóþ+ ™þÐÎMøÔs†òk*3dï&ÐlíïsB*žp? ðõ´ý¤Ó„ä^(Ú=\XÜpoï™ì°²½t#h²{èòÌ3õ’;ª—œ–kx'^<¤'›XzGwk¸°ÅØb··Yâ„ØÜŠçô Þ´êø5 ñ©BÂv‚YYf¡ô©ãÎ:$ *¥‘ˆ‰O. Á-$Pzû¡¯ùP›É-1¨ BŽ!$bÕ'K[`Ðä¾B¡-úBiÉ 2ZP0vƒ{ÇßòD·ÁâÖŠ€¹ܸ¬]u­Z”mÛÍgª[b¯DÓPy)­ß&ÙÉ,A¸šÔ Èa­àþpÁ¢;¡©Ãö¡i›@¦Ó=â~ ›.Æå«êÌzyÙöÆðAIÁ²´…ý°H®Ð™ÒšièÈZ5”Ý1<Õ‚IdÁy5øc=ìÅz3R]MÁjkÖËÛ{õøì°k¹òkhð/ÿŸ¾:øÈ$oµÞ…_–±ÐßÁ(•úˆ»W ¿÷mºæþT0­mŸS{ª(ð4ñJ«§¡AÔÎ|ßžDÙóú†G9 G3á?É¿´—Å¥]w!ŽÊCâå~³ÿFMûóó>»³×OÆ_¡0ÁÖ•@“tÃdA£Â,‰µÙzJ{ÓŠ'D7ýóÖ7 "âÒE¼a¾¬ûï‡jÞþpý‰^uïÏiÊùèq¡mí¦7t¹~ñKcÈ)]àfF‘G@ž<~O=üP&Ëj sŒÕÖÖÎâ²UGm ¬ª[²š¾÷ÚùïœÃÉÉc)i0×Jyñ/Qšc ý+i’ô§ï‹xÒ5êfì¯õì­- ßçÎïlØ=VÝW”ì/œ~^žWVèÝŸ‘»86+ï\gÊ×ÀA Yéºm"¾Þ ’d7:4H`n›Ë©"”B·Â’Ô_g >Ì1džf `œ^ð›.NKÃCe‘áð}ã["C‹¾½¨òmÎV-÷å±'ïÑAša-]h~DÂ{‘u`Í¿üJ´PNýTW!¸8 JÎ×{&,ú4µh¤%Fþp¬ë•F¬FëÈFú8„* hÆåáYJœú8b9;‘Oé†tFã%Pt9\·¨íþ™ÉÍÒbÜ;TWÂ=‚ãã.¤g Skø‡N†½Äò9÷ g¹ê…¼¸‚7ÖóÉrÇI%„c™^Þüå‹Cr“µ‚ÑKýÕÛ3PC(ŠùÌP¿}P‘(*žêàw.¼Ç˜Äذ\cÀ´²˜©ÌÞ¡úè³&Ðc$ªËøE‘à”!E5@G¡ëHŽð5 S{Ûö!±°üÔnvoV}§Jøôû}÷ÏÕÄIÁ[ÓžLÜmùÔ¤Ú\Õa³‚¡ß© œÅÆF:žxüèkgyÊÇ‘÷°‹•L–j>Ê?“uñ#º–0†~|ßÈÞ–ìN'‘ ºQëè7OXAN!¢ül¸}¾Eß´Lò"JWqìA[A¨i*Á"Œ(º ºÞ²Ð=á],‹ïÈ8CÍC™¶ÿ®oôZpè„ú™÷{¯mø*JSÇ~ö*åtÉÇhË„]•2ž·¤÷ÎÌŒÕÅ׳ÓÂñ5|‚Öª}ž)¥,“]R¹ÙC@LäôÈqeM…–»(Ë‚K1Ý«QMWL”ya¿i³- Ψ¡Ÿ]ð—תm$L,I9«¨zJ«Œïr˜UIÉÔµQkÏ‹{4ÆHÂ(.~H¯ªž‚Ê›Û×í“Ch¶oTAŸ—[ƒ‚´2¤¹»²|3Ó³n‰¯`Á虋W`ç°uƵ£ƒ'”¨©.ð¼=šdfO,Ì”:… ’e¨µA•PõXqÆÍzàÚO~c[2š$:–%pŽvÚ¤ŸˆÚUÃ0ÉXÐÜîhYfäݔأïÅ]%Rã‚]ß™á0'DC®e·k01+ïtC3êÐâ%ÈgÏ/4o¶ ¸kà;J»jŒŠóÂkK<ꮞßÏCünþ±fËôþ°˶ÖÚ^¸d¦I­d¾ftp2½ÑooŸK61 ©Éçò5ŽDOgÚ¡¾T…­éäNS#v.ß~6ÖËB—ø§jƵX¾o{Žd°ñ`»¯btê/ŸV?üˆÙç-Tþµy7v(…­ÑEB€zß9¢½z¶gJrä4É㈇3¨ÿ^¶Z˜k+šl‡Ñ¿ÝNº1¹Žú¢ª} ÖõâdbÔ5Ô³¥ñ¹¦;UáKMÛŠ±¦|†Ä6§[¬Òpò›¼ŠàN¡×8²eÒþ`‹`œr™õZ§¨EZé/‰"v½$®ÆZOF2p…üq<1Fl,sQá¶ ÐÃB_QW×x‘‰†ÊîÏV÷¶6Ý`üá"žÓ °¯’3óÓ$¥²áÑzÊ&åV­}Iõ^x`lLìiGê”Bž ËKÜÀä]oÁ@B †ÖB_£Y%›×gÚÌš¹xÑ4Í”¤ù4ƒT[÷ª1¼K÷פ³½óo*ž­T6©t%3'œ¯å;[e¸û¥~Ññt^ˆx#Q×ß{ýÕvuMA·™ša Ä|2 Å5bb.‹51½ý„F€ÉµkªóE…3[MœM4×,޲iž÷"4$N›|Ò^ªN'ëæ¦t˜ç×TNeÏŸÂÀ¾è"ãgT}.k¤,†”› MXæol?õÝô‰œàÔ®aiGKPZ}lG6­¤ü¾•QO%ìphY&¹CY¹„ÍiiµÙ²Eìöù¿Ñ'œ,‹H $:bU¾hG@êL\£1®Ú|£‚AŠŒ«A¿µÏ{3çîæžë”%à,c¾KÁm£äšwØ5™žE$ûQ»Ç¹‘#ôª˜<Ò%Á.ØÊtC™ uŰ»[¢åßÿ^‰Gí¢»Ñ9êgRq5ûÌö¹à}ðÍvgJˑ݌®Í¤BtëÅ6zl]ÐÙ7¹ºÇbÕtn­…×~¸R­<ÊàöT„2b{Cã'˜ÛXcD‡¼9Tf)]Æ-“C·mò*Ö»¢7B)`Ì…²Õ% V¯”ð‡Ö»´6òüI*Øæ¨Þ³úÄ_‘ƒÉQ/˜~Õ`c€¿,ï‚·àMJ÷; F‡e¹íhQ™Ô¸•£‡#Š¶Ê˜Ÿ-µ•O® âáÕïHeæhÁº>»©ÿ¸ d—‹´ÿòØû£¶pÍ8Æ: à]5Ž⼬¨Kf@ coòÛ°tا5¨úNi4ü±/¯'¦KÅ´»Ì$cFa¶ .›[W:êM²'À)ÓÀ° q¶}þ¢ÛÏËúõsP¥ì×`Õ*ì×ÅSGÄž­ž,—+ëž(1ÃòïƒS5EòLWÔØðÂ9‡+yÑ;4©S®Dpý•¡Naë¬H#5²Kï #EQÀëºÂtÅp§Sö‰ßEc§u4Ä,,5¦[5M¿s/­ÆglK*ûˆLdŸóGk³¹LÕHQüdôÀËžµåÕ¹ü2¾45¸Ùo……ÛòïEœûÏ·¹ï (âeOCGE¸oa¼A×Î5s( è¡x¨¸»x¿2ä»[{´r‡„ªüeÑsÔöqó˜)ÙìÉšÎÏ»ÉèˆóÆø>(ŸBåS™½S·¼åŸ|Â&O‘s¦t J¤!;ÑR|£ŽUä„Üva£¦ëÌC¤£‚„QéDéB·„tÍñoó7%Ai€®UáÇÕΤ èg34òþæ]gÙ!Ñ€$÷“Â>)ßÁ¨-î.B$ýTã_3¯XCÈ©¿ýc”Œ?PݤX]IÕ²‘,›VöÖê5ŒtyÎX¢­MS˜~± º/­ñóá”Úˆ†°°²œ)ÛÊü(Lw]òî˜Wü S^B S*âwó\?“=U æÛzð¶•¼›ß7l’Né¥h°rÁ9–kÂîý–„õ¤4Eìc‰|ç“Óß6WÑa½1Õ1£ÊŠ'¦¿¤úÝý=ÅÒÅà,ÈÿÔoK ûͨ¨žÜwXæ0RUòUmïZÉ5/¬<á0–‡iüÝsûΞ‚+E¡«Qt7Is^0àÏì`“À˜`Õ8›Ú®ÂÚdšìB'p–T¬Þö Ì ¶V%™ /‹®`ÐŒ{ƒ¦í¦;ûy©ãõÚÜ¡dtÄêö˺\hÊ5r—Ÿv¤w]ËÑHfÜMç>§C/–lÔD˜x* oa2Š•X˜žBx0NíÂŒ‹†º$KU-åݾú¦°³Ô¹­™u‚-À¦wP·Üãeȯ’Lahn—ž—«ùÙz\ÎX´éMÌÆÁS󦳦X<õô švÔÿ6Ÿl(èÛR)Ôì s¢ ûî—ž|–•èH!aáâÑ2ˆ³ƒ¢Z&æ-üU·%cÌ(PrÆQLU­ê¸@)âƒâaB&rb¸Zw›¼Q&1…±¥OSòE“Û¼é\ṫÉral‹«¤œ…¸êãâ ­ãö¹O8õ¤²3º™–8åjéʆtÞå3¾í4×È’-ÑŽÁ!r^y’˜ÜÅk5¬6º äíVÝšq¥dú(1„1áâM8rU»ê,NX†–þÓmn ºŒ¨ˆ¬h~šÜ²ÎßX‘pÃrl&Å—IÚ´?Ãg#¨j'ƒã–>#˜Îm3L¦ U-Ÿà£šÐ´U"߯Mc½«H°]÷ÄÐpƒáæÞ“±Ø'bÑv.ÐÕ§dƒø›‹¦–„ÒãõKmm¨¥æ/îˆNö¹¨¿dW W—…sƒ6‰¡†¦U‰B¦–*@¿œ°ÇñrFb墚Ùt°c|Ù¡F;çæW õAúB½¸¯Je‰¤þ”5»&Âèó†o)U5CŒXAW³³Är¯'ívòG`ÐŒ ä˱‰®ê{¡<ÅØïE;p Þ:ÉÌôst‰aåHŒHaäR2¶;ß“ï’MhB\ZŸKŽE_jE‘òbW¼Å¸i$p²-9’ÊÙm±û›s¶øö½‹ÖU¹ns ^'ȯü_S>O=E¼Áüôû@•†M·þ(Œ Š=ª Pýk÷cs¯¶òºI§ª ‡!UªûV‘„¼ÐþÝx (jUqíØzÐÕCA®–öΪ¡Ò TÅK«ù¨àLÉ.•ßcå ¹=6³&¡–¥Iå]ÿäìH<"ÆØÀ¶tPýÚ¬Šê˜BZGjäó¥KúdýF¥A•@Ý\€ùâ|ê¢[‘èZjl?‘8´i/îò_ÓúÎ;ç ô™wqž„wïB3¤mÊ‚xï}Æžå[-˜ƒ97—_DÞ}¿˜4ÓÞõ¿ÀºœÉÛ£)_‹aØiƒ¼U‹3ÓþÈTÊÌK¸6Ô7ËðObñkOÆ 3Ó]±gmê4³‘)îû!©ºŠ1oþ ¾88ÉE=u³ñ ÁÔLDÆw¢Né¾×ê¾ú9F-7xšhƒ]úf-v>úõ¦*kA<:99PÒļì@0ä$ eîrvs“7þAdØ\u?ó}š#"©$¥]ðˆeaŠFÃíeÕPÅÔvÿ„¬P©7ý&~Â9Éñ™nG¦®3qRÑÃ*høpÞ«ŸE&yàëty~fkQhˆ ‡Áˆ—ʇF}¥´á[Hƒ:A×ÅÔJ…MfÝâ ª¢àÊ!ûS/‹´2ììÈ£e·9â(ynXïÈ@ùPOi£RL(±õÕ2©íæÜŠÓ2§Wâxòϱã`¾ã01~jôè:+Bå P9Ö‡wÁÔyÈ]úYÁÏ=ƒó)¼qµº)ú?‰wgkp|…ˆß–>ÜBç*¾@³ö“~ߤoDÈ$A^?nÀ1³C>–“C"¤€âÒJW®UÅWç¬Jr/Bãêál,J'Sçä†yA¬ÜÈ ¥R®eOX)ö2½¤ß/—æ˜C1ý#=Ÿ#ÈÌK‹¢ÒÕ"ä'-OÚ? ¶A]B¯oÎÔØ¶Äš°Íù»j<¿ëøŽŠYBŽs„«î[ä=O&é†j£›é†UùY>ƒA­çšÀ¡w6Sw&ߤ YÚ1¤¼ÂÙËæT¸xFqÕ:v‡K÷fñy+Ý‚„D¯®YË[öD0ìÊRŸ%eÌ0‘fÕ_M]¨pªP@éMÒÉfÐfÀnýAÆh¤q._ªÅ1B—enˆ«`j™°…Ìk›ŽÞDrU°uSÉ—P/”˜ha†•ZÜ!s-Ó H,}PK"ÑtÃ|µ Å ™ìµ³à•TÜCƒó’LŒqe%ƒ¥+ѳ4mŠ\‹Ê.\šG–ÎgÙÜ Fìs¹ÒÌ­ZQ%šN <žèó „4¢Íxã¾`&´Ä¹?š ¼eë¼ÉŠìjõ†Â%Šá°0Ãí•(þ1 ºy²!ÏŸZ%B2q~Í.‰Ä™KoÕÆ°Ü´‘Âê†ón¼¹“¯ù2¦#¸åýÄ£—>ÝÙÏä)F¹Hºu÷Ú¯Sû&«@t«ÄrŽîåØ/3=‰÷x:N FÃ÷ôJ4ÓL4m\йÊÔe,mëU°i™MåÁD¾Õ4aˆqQŸQÍ#`Q[n±ÑA~¹Õo¾X%¢ló{HæÛ+·q-±zµO·Ì´~ þ~]4›Õ•uˆŠ$E’{µ}Ã܃ˆ8*Ž–Ã‹~ÙtH æ4:‡nÄlv•ó9¶–`ÞæïêÑ%ÚƒéDpĘwýñLÙbm…ˆ.F͸TUu-×ø?TýÉé÷r&//aH}SaÓÔßOc"7íÁxq¬+,̤ÅÌÞ¦3 Ði ZÜçvj­Ã“šG­oëÕ·ÿØ¢M‹tAúEfI±#OÇÌ Õð-—#𱲫°¢¥’ÂB”šEð*ùB~Ø8-°­É!B‹xÑ3ÁϼÂ6Üšzº ñH°úÒZÉq·zµÈŸ‘0IaÒ¹µL2Dè¤{™ÐöÖ~¶Ž¯ :kªÙÌl1 œ’,î†ô09(®|)‹”Œ‚‰ÐnGŠœœf# _ŠÐ–0NZäP©¶òð(¬ãý´âÊ…x!Ñ×­©··ÃÉAÝ5%>à ]S“‹ŒE=8W¿CÀšˆ)\C°ó8-u>»œE¨Ð‹ÕåËœÉ3Y§e¡°j±ší²ˆ,ÁÙÒ5ðP65L§ó˜Â,ÇcSï½åUJ;œFÕ¾›ý( ~°šÞÌG(Í8ÛEQÅL5ôC8 +7 Ú-ï%¾: }“ëÄqøx{S Ýþÿ¶»,ðì—W½ï"x?d6.—Ö{róû%é­Kü«í—.x¾õä7Ï j‹ïÏVnÑõ™?ÙìœÓ3IÿëËåUHZìH{º]ûÙ_݈-Œ_¦n<¿çI¤ç”å{xNÿ±ÿ$í²Ø®YVW6WpÅë~i% gÇ‚ ª¥ ?l?r‘×äÏÑœêH1 ­_™e[5ë²ïü¨âø±©GÕú`ÃIÏìûÒ˜ªJ>vLx‘~ÂÝRÑdþ¿ ñ&õ’“¸"ݔޯ-MÌÚ|<%§0F\»n}ZÁ ý2jßÏH“õ¹:1h²DMYã¹ë$£åü$¦Æ\6œþá’ ÉÈ2¹äŸ„ç»N^¨è0ÑSÈ»Ê;?‘iµŸàÁu-üßU,žÜ˜ v•µM?ÝË.û߯; ×ÙÿÝ*8aùï‹DÑgΉ»2æ/jX~ì¯Í—¨ÝN¶$\ßV»Ý¬ä0OvûÍ9±ów|/ðù»Bœ~½â+Ÿö¤ Ýÿ¨¤éÌy‘u¯ª‚öoðbœœö®q‡‹À5ª`D)HÎIM,*ÉÏM,ÊæT±Ý endstream endobj 205 0 obj 17128 endobj 206 0 obj << /Type /FontDescriptor /Ascent 811 /CapHeight 0 /Descent -237 /Flags 32 /FontBBox [ -43 -268 681 842 ] /FontName /BFPMAG+NimbusMonL-Regu /ItalicAngle 0 /StemV 41 /MaxWidth -724 /StemH 43 /FontFile 204 0 R >> endobj 207 0 obj [ 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 ] endobj 208 0 obj 1671 endobj 209 0 obj 2622 endobj 210 0 obj 540 endobj 211 0 obj << /Length 212 0 R /Length1 208 0 R /Length2 209 0 R /Length3 210 0 R /Filter /FlateDecode >> stream xÚíWy4”ý—J5ö5´=e‰ìckÃP2†û:f<ŒyÆÌØ %BZÄkʼEHŠÈ!´ˆdi·”tM´è•­Ü‡îûvO÷ÞsϹ÷ýïÞçœyÎóû.Ÿïòùþ¾çŒÂv+˜Æ"FÑA-5-uMC€€'âûTPˆ_Ó!À¼š-H¬Y$* ©‰ij¡, ‰Á4‰. Àd´0 J°€éQ ( (99¸(«¨¨þ,›~Q¿kO&@‘p ÓC@ øA`‚€?D ;{7kÂ@iÁ ØÒ@R‡}˜"xˆ Ò˜ 2à3ê÷@†ih¹4¦:‚…e$€IÉâF’Aú²J ƒŒˆÉD¾ˆ 0H4Ò @425Œ²œ"÷‡W¢3`Ä"Ñ!`ö0“Å$3 : @¢Ú㬾çÉ $±–c3!D Àþˆ%&‡-—´¢C`-‹ј Œd-Çò ĤSIQHlŒÎ€VÒcB´€¨ 0€Ä PA&A°—»ó£Nàïª'ÑéÔ¨oxÅê ¤ú«£´ÐHL2 ‰ÑPËãcMó‡-ÍïrJýw]8ÈXi24ºÊH$ L£FÐ¥A€YHH@é?cYýÏ#ùO øO!øO¡÷¿#÷gŽþîÿ·÷ùgh«0*•@ Aàûª]C¢ȺðÀò¾ –WDþORDúW¾?[»€ß“6‡©”Ÿußñ±´„5-]uíïbˆiE‚{ˆEüIT¤q+r'dP!ˆ¼Ò[ÄISó'1"Ó–™Ðý®i”Ÿ @8[I_çŽÝïdó¯–튱=2+ûø[$[˜òÇaÊÜŽª¡‘TÔ´Ñ:£`ôtbþIÔ­g[‹EšËK@Þ¿ÿ~œ¼~‚±¤‘aÊò9²H4 2uþÖ(4 ´Æ!Õ£51Ú˜)9ŒÁ@F`e= íøý¼r+@0$£ž Àd£„ ö™ÖÕ¿¶ßÇy´4k­n?J/¾F¼¸ n:ÄNÆ”ú.–U¯z`ø­.ª‚þõõ¾]cÍRÔMYàÔùÍ1rÊ·òE_(6諌Ñð.Ìẜ8ø¾?´Æ]OÓyläþ~ï¢E¾-´ëßQ>,žXB~†.KήL•¼!RÅ#vµ`‚«øËÛ/3;Ûît´ßnú¸öÖëM*œÔ Fákål2sw*=xj‹Suþ‘ã«ÊÇ-ÜL7E¼ÕŽW²2Od//ÞtÛK€?M&º“ l·¿KÍÖñV˜ÍU7~NÉ4d>Rõ]Cx|{£WônQšT#¯Çn½Ù 'wÓ3N9ªÔ&Z`Ω^&í"Ÿ¡f¼“3.ÚÛâ@?ó¤SXèÄëŸæöøeZ—ô¹x ÀòÆ SÒæj{‘&HáÜ:Nz¤OÂ0‡Yš]cÚþ­u œªÃ\m¹ Ä[¹9|(o.Ƨ‡ßVT›~7®&ä¼ö@Ћ™ºšG36md½ÎÙReÊ~צ¤ÃZ±© ;îaÚŽÈõò‰I‚-iKz„°A…=YT›XªøÖó_6÷¨PDìÂÄëE]Þx/:2­ÍêSpô²ö¶˜Œž´J%%˜ÉÍ‹¬ßf2õŠÛ(r}¼ªâÚÆšJQ6Q1lVöuôopšàBÒ1ŇðÃdâÁ rMë¸LqWñz§ç Áì®ø§uRiÐV…_L]ûDÔ•  ö¶zwÈo¬J9¥‡rnJCŸd·uW[çeñXˆVÑcfðŸõåå5®§$ß­6Q?ÄÊ;f²¨æn~¸-Gc@ 1oO„¤m¶·c7§‘1ãO(7ú½ –žÊ îÌC]Ÿƒ9b`Ó7,ôÉÍ{r¦†N{¹;$LôÕùÒR8[üL :ìæLŠ…º‹uÁdü(¦°*‘°×¡fêbïÄガ6ùªGÒõïR.Ÿ})MÖŽf·ˆä¦µ¼×¼£~Þ KÖ'ž@N¢‹ê£óÅ}y_Ò^Á«’O¬ºVŽ_Üçj„;"yÍŽ¤v•D:f~MºôÕ"°x ¦úöU„òÅü¸í«»ÏlCÝùhKÔáÆœìï±ä£Ä*õMëú骑¯ ¼!ôrìFÜÝÍh÷û1úž/‹^„Zúhð9–µto~þÜlÁ­(c>bC+pÛ³`΄(µ¿‹7æYûÎ@ð7~cì–©ðÂñÚÊ/ãF&¤îoôv¯<-ÎÖÂÙ¯Êøß °—êôdi}oJ”&æô±éþ†ûS¿…«eG^%“¼a}»'$ˆŽÌžÏ¬Í“ÅäìÖ3× › ÆM$§Þ9x‚­ŸY1;iá1ë¹h}ÝÙÌ—3a攫ڼÁò|³8.cA¢/EÐVJ¶Oiºa0]>@¡Šc\.–Ýßš7^Ìgž±Ô[¼A{Sž”Åq£uü>û죨¢&;$Uî]qõÔ_õh5ÍØùëW2§8ñîh=¿ £‘fyÑE?—îïK8«[Ø#ÿ-v¬Ûõú:ëjà4ºÝ8Ö&ðùºÍ]ø t=! +Æ3Š6ÝáyäLØöSojsƒ2­“y¶¼usÜz:¯v´Z#ø«‚{Á’‹v^oÉ(å—Æšh¿ö‚¤àÓg`ãèMƳpî £ƒ]«|XÞânü•ÂMà ÷·fåqNÍ ½ÞçÙâôÊxW|R¥5÷S«ìDžÌ|£cçaA£þT/܇ jrùù³\“yoRíúí|ú"tJF”Å*óÁ—*Êåáû xÏ1ãªdÃt`:o®âx|ñÃzÛ×k}ëYÚÀYŸS%hÉèKx\½`íãèÅ€Ò㌛NšUN®¢NŠV‰ ³Æ;Ñž;: 6Š—˜úðŽyÿvŠÁá«Ç:h6{&ŸêG•ù nTº»g7:¾©_íeËàÓ‹­UŠÉÊ;ç_~k„EØ`V½óeã…ôÎ 1ÝcHЖÕÒ]·eÌÕ Œð&^žIرeþ’)ÿa8æXIfÆÈÓÂÁNåc‚Áh8±÷-K”.’è;‘ÚÎêjá%Úû{æ@]xÔau@’}1|RºÆûq·â¶Öx›Pç*™6§îEØßþt¦«ËÖ([Ý©ÿP§gïíònÞ¡œ%´ ß´c阎û”Yš8Pª}“¼ö[ø¹KáOù·Çq΂3VÚ¶¬|zÑ4‡ÛÍáo:zÇŠ1éDí‘ +ìóé¼¾­TCáFÚ)ý¬ªåŽÌv‡õPâq|ëà¯'±iÖ†ºëööl®®¿’d˜¨*¯í3—  rC0íOð[™Ñ²rR¾<صkàóºWη׋äf–ä‘=ˆ¸œ>TQMº‹]ÉÛJq³Âq³ƒ'mB NNæ“b†s õÛ.Ï´¬—6ϦŸ>kR´è=ö8fSo›yÌùR¸P“/%Tg ò9™\ƒ²øÇü':>§†*º&¼{ø½ÈÀ5(XŸ½f™®õ::=_xÕÀ¯xkzë¬ö®•É[øL-}]ªÀ™vÔ­Æ Á¹3ã–ç:}lKõË©ܪ¡GfCØüš§øÍ‚)uÏ6äB™©Ä[{çoqqœÒ†¸ý+UŽö7‚jÛfÛŠêŠÙd64ß®Xr8 úK©PµHß´\ûG3+Çè{XÑj'ß.×h[ìÈÖO÷bß”%Ó¸ÊÍ\Íê̸-lÆšª§ð«…Šã¾3ŠŸ¸ŸÖü7êÿÿSd*Hb°ÿ„Œ`Ô_µ›N endstream endobj 212 0 obj 3470 endobj 213 0 obj << /Type /FontDescriptor /Ascent 964 /CapHeight 0 /Descent -324 /Flags 96 /FontBBox [ -231 -355 1027 995 ] /FontName /NLTDNJ+NimbusRomNo9L-MediItal /ItalicAngle -15.3 /StemV 120 /MaxWidth -1258 /StemH 27 /FontFile 211 0 R >> endobj 214 0 obj [ 722 250 250 250 250 250 250 250 250 889 250 250 250 250 250 250 250 250 250 250 250 611 ] endobj 215 0 obj 1655 endobj 216 0 obj 13581 endobj 217 0 obj 540 endobj 218 0 obj << /Length 219 0 R /Length1 215 0 R /Length2 216 0 R /Length3 217 0 R /Filter /FlateDecode >> stream xÚítuPÜí–&îîk ¸»»»{pšàÒHpww‡àÁ݃»Kp îlù¾;3wêîlmÕîü·ÛU]õ;öyÎ{(H%ííœÕÝ€, ,ŒÌ¼Qy9YeI:EK['U{[E{y ™%€™ùÙ‚B 4v¶´·7vò´€fq )€•ÀÂÃÃ@³wpY~µpPk¨jÑÐÑÑÿSó— ÀÄýß-‘N–_í”®@{[ óÄÿq p¶Ì-m€1%eE)µ”¢@ hÛ”]Ll,Mò–¦@;' Àܰù‡0µ·3³ü«5'Æ,'€1ÀÉhjùt3:üe¢8A¶–NNßK'ÀW±óÇ œí–v¦6.fð¡7·ÿ» ý‡‡í‡íLÙÞÉÙÉdéà øÈª,.ù:-ŒÿÊídùaØ›xšÙ›ºüÕÒß¶˜«³±¥ÀèæüW. ÀÌÒÉÁÆØý#÷˜Èòï2\œ,í¾þ³zøÕdftrú€ùÀþk:ÿìðŸº7vp°qÿ;Úþo¯ÿ¨ÁÒÙ hcΈÀÂú‘ÓÔù#÷WK;¦¿VGÆÎÜÀÂü½™‹Ã¿Û\ ¿Dý±44E›ÙÛٸ̀æLŠöÎ)Ôÿg,3þ÷‘üß@ñ Áÿ-ôþß‘û¯ý§GüûžÿZÒÅÆFÑØöcþqfwÆØðqjò€¿n‹íÿblkiãþ¿ úWo-à?ªµ·1ûW›Œ³ñÇHDì¾~ÐÂÌÈü¥¥“¤¥ÐLÙÒÙÔ`nló1¯¿õvf@¥ðƒ×¿G ``afþ›º…¥©µÝ_püô3û×ò?¨ú»x&5U9%©ÿê¾þí¨ü±ŸcÀ¿eÑR°7ûá/QQ{7€' '7€åãí}ÄÃÉìý_¤üˆåŸ²‚±3ÈÒ  Çü×!ÿ»ûûÿSÒÿ ;S{³¿ÖFÍÙØÎìcÓþCñoC°ttʈ´ÎÊÌÃÆö·ÖÔú ýï“ð1‹—ÿ~ @ ÐaeÑÞ”/È*-3ݹ÷ûุ^_ ä`°CI½za¾_µ}·oZØO…ÑË`ƆIÞ·V÷…c‡×=YÚýáªîày¡79Mo>ú:e;Ý~“A rú‰V”çżü&”.'³æþö¸ŠªAñ Ñd;îâÆÜ5ßëó½Šij],vZFMÁñ eâáÃ=UÿÈÐà@÷tï]N,<Ÿ+2e¤Ÿc®F…g n(k ¦á72ìcŸæcW‘9lˆíöペC—ê#(0ÌXÚ²!!C‚åâû£ _¿!`ùyV¦ÖÉÆ<£P}5º½#Âàë°žÊ`’±Šù 5¿†Âš2[K|…Q+sC½…ofŸ*‘ǘÀF„dMŽR\N|6AHJ– BWífbèv›ÁY8§”·ÛÝþŒ†w—,>¾/¨{Š!?¡àí­B<žñ*cWµN4©@¨7ƒµÉ`f¹Òig›jrz£@ÈOeh‡‚Œñ#“ôJM[Kô(=ñ\àÝ~" %¦]x¥ÏrB ([ñ•uC$ ösð+S»íKýë{ÉptR`D±œ6 ÛRNOrm j÷{CWVbbÐ.5Á¸5\qqÿžgS%V-ô{É™ÕQan½ÑLQŸ"j»Æ ½6zÑ PRˆï^ÚÿÓ ŽG86!:³2Z®·84aPZ–;ȳ –Ä<‰wÛÌó‹úS7ÝŽ«¾ø­idmÂvÎóúÃ7ŸPæ?Þ=@‚ }‹g~••ÉuH"‰¯ Ÿp:’PýRHòPiï¶aw-™C™ÓD±¬²À ì/TøóDͽhä`«šÓ´!jÓz×91;´ ¦ÚŠ$µ_¿À³ÇÌî§u*x“ë"“Ä”¡FJ;…ZPè²·v™§9ÉxW€ Ô‚¶Ã~ù˜àÁ=j”‰“Bʾª ^£™[zïÉ©Uw3ý¬=HˆÈ1}£Aœzr7;hzál†B›]¹>‡¦ôÝrƒê»‡ÁÑuúWeªÂY9ÂòÉÇM#Ï(| âüX«J”¯@îlèá?ÉÆ Všì”i$ºjO-j‡:zÈÉ.-ûhꢶ§ÇzÀ Ÿ¾Nr Ò¨EüÁœ'’VpÊ‘ö–ñ>^¾7òÐXòŽ'͘2·ÓTMà–¢Þù$§%ÈÞ€Y\¤ÜŸNã;%f)ßUnŒ?¬bhðkwBš/÷†Jì /Ü!âr̾­Žvøšêýt‹{˜[оa£Nª‚HöizV­Ø}÷Ͼ${ÇvQ‰ç]ú*38Ý!—JLú)ªQy)Ò{OÓFîH\ &ìýMçñ¦‘³]Ø¥0‹TÔ­ RH.`ñÃQ®Úm5–Ž,+“á¨å÷Xùõ(cÞRFg#Ø‘Ye…<á×'¾±ŽQ'¹«çêP¿”@–ÓO½@J%t¯<üŽK6uâø‚ñö#Ïéjß(öB¦çBzå†yðøwÑ ÕiíÓ±¯'Ëæ®?°5âr±+õ­ #u±¢¢^ðW%¼òÏ%¸ î5ôtIÓP_­Û—›ì?~­ù…‰› Ú,'–K(GP—c¼—ìØu³làÕ’bSj½bD»uÇS9­Òú߈h)ù ì…8!W+ã‘çZʆ\äÈJ1úΧÒgMÚx'¤‰ˆ-w²Ù´=¨{a0ãT5’š8µÊnùŽJˆÏ•`!—™“þtA0—˜¥H¿u]F)ÉmŸö;WÞ×ÄÝ|WH‡´‹D=ãÅЮ 4g ç„PcôèÈõ”¥Ñ.šY‘sQg¬õrË3ÅqMÄF\é?DuB€aûGÍõ 3_›ø^{Ñ(€f™j¶A‹sTß †ÍöÏt•û_ãbnŒS°MÏ;²ÓBV÷!ä ~âÁÊyÖO”Mgu@BöætÑ‚és!*zM^‘/gúfä¢3YÀ~N Ò!ÛìÕ? ²³ƒqðè‹.SlÆžß6(v_WÓXÈØ/ú+Œ*c©.Çðô¡e‡ÎMÔÖaU\QP¨EÝäqc«ðõ â~# g§¼üáà‡¯¼RÕYWD¾ôˆ7…ìHç˜"‘ÎB3®dµƒr ±ôâ¿XÖZ@ †¸»øò–s4ƒÖ™±ZÄI·ÀC öÛd»9­ÅôÛgó<žiq_W´/%è!µ¥ÑŽyÎaTaóε¶µS½( ì9tzØ“Iäy³skÄ¢Íym¿qŒ`Žšø>ƒ†c¸+áµÞ—)8Ê=,D)•{i¥Ðºu¯P(zMççög²0?~ê_}Õ Ó’Q‰=^Ññô±†ªcˆ‹ª³R •X"þ. Æh̵lð••zaT9éŠ t6õõ¡Ì±ö'oÉv3¢z¹Ì´!ưÅΗdjÄþôoð_¨3|·Þ×qáÇ›B>‰Ì©´ˆ'½Àõà@Ê QR€‰¯éX¹b~ßz4º]Ø#NÁ¼lîû}ÿò<­Z™ØMØŽÊ]Y¶’¶¯¢a&¤ï®ú6ÞI…§×„;‚Ú‡š£Ï§  û%ÿ6gÏ£nœõ~9j¹€HU\ vQ|æ¢ô³(òÖ-róNÂÉr€T[¸Æ$‘ªîVô‘©\‹ëÙ/–p[|å:G³mPQ^“vŸáÆÏŽ*SÿßÁPw›8ÖJå]…x];´^X·ø¨,L¬‹=éüîgˆÒ2ý¸ÚQ¤RàQp÷"Κ¯î\#.wË?éGÖ,ŸÛóm9˜iÞSF†ˆXÓ5žµl”Æ“p»Ÿ’É_ql~ÐóiJ̵b¬M_i´Ôàý Ð]B;¡94‚áêŽvpo+@hŒ™%Âc7Å^0ž)ÂäQ™!P9W"Ê.:}ÏÇfÄ%å(8ýT´=R&§EÈZ,´â{fËëæD!ZÜ#B5ø6O¾q¦úmßGþ,ÊPdz49ö 1d;Eãyúì‘ØÐ@—Vþˆ…Q¤ú½yb7/w5mZ?üm˜±cQq.Úýô‚’p»+ì£Xã0#Äs[Çü£;¹wqõ'ù}È1r%Ü2,¦Cð*˜8óO £ªƒ¸úüU°£aÑ ^¯‰z¼Õ j妽3PÜ'&®£=cŽÛ«t¤w5ªTRÁfòWÇÃu×ÕOÓ å0÷ìbe¦K¤ð ¨9“CÏ)CÚœj¢ 4îMf ¼¤üLtMºš7u —ÈažOWÔ©vÜ5«¼¯x‰C0?v1Ò¢ -žž³$8—ˆö‚|ð¢%f¶›çp–·8µ’JÆ(þ±a„Zk1¯õúíNÃÚ>BûÚC|•Å>R §n3ihS‡Q§q“{)7ÛbÏžA /|ÑÖz2µÏPíR~–(#Ã4ö¾X¿eŒØÐÛ@IN'ìw$ú¬eGçl;¸xY8ÝM®¿D°x÷:=c6ï½l1A×Q+s4\äâï –%ªyD1\‰á‚VfÑ:cQó{1Éø&ïΨU…®Uç˜2YƒtYÏ5kž½%7]¦ëUÞï=ϼI„ܽ–Ô¶ Âû­¨àÄa #Aªc¸æ~ Öî`ògð*V#/gÃÂ×Í©ð‚¨lóbj¤X‹q×#jµ–²¨GbóüÊI‘V%±˜ïpÞÑTõ'‰Ž 7—#†Î'½<žœ.c䯗 ªn3¸S|”€?tAúe@‰{9`ýp0Yõd™Ö=_pÉéûY¨hÿýL '[xCMe/tÁDc ŠŽÕúæ¦ß?§ûêúNÉzËÚúdâÏKã„\»´‡Ô¥B-•®-Ø“#âÝݽø1ù_¨‚Í©Q»ßÎT澸±·.%·Sïf¼c‘°ÃÓå`AvŽÇN&Žƒ\S3?ÇÒ•¹Ú²ÐIåú cPR©™ŒU7õ•LÁì²J^ãAøR;¹H¶c6q¢€å6ÖÍüZ¹w¶ê7ÈYëα†}5lj½›±‘i¦‰ŸÈ°4ÀKH®ˆu~JO*ËñRsŸ‚n…[ÛQ^§S4±?ëõ6Cºé8ÏÕ8N7i˜Û#ø­æÎ¡En©OФ8­) ý‰:ÄžŠî™²'ÒÝaë-3Ü 3âŠÀv$yËšé›–õ;ipŰJ‘Lu;—H¼!¹ ŸØ ‚ ÜòIçépF›æ½xEË?Õá“2ŒÇ-Œ¶Iðµµ½nãÂ9£⨥¾ô¦û²éGY®!1}g9Ê”2Ã3˜à"Ã*vnä5p8”)cF†®Á)ÊÆ/!5­Ί^ùé,:!3:Wþ¡¼Ëhlu‘o•Ó2&¬¤¸ç(CÈ;T»°Œæ6¡xb|ûô5a¦“æQå¤ß³ÝjÈ4-òÔuÍÈó‡­RÑ0‡LãlLÄcäg+ÑSáb¡¹ †×K¶ûåQqŸ FÔ™9"[]D›2m˜e2ÏbmåûÔoS¯ÌÂX'$Ú( ÐzjeeÍç.—Ñém,î¸aG"uãŠØ^Ñž^,µ=úc—s­^È-í´‹Ÿ?¯ÜöÁjb4Q×qU¨C”Ãlö{zQåX³gUaª¤ïk Ab‰oÎǤúü mË:ø´ž½Ia {S£”99ùÞ´Xý•ÍŒá$ß[ õ€‰š#Ó¼næk+1´¹F™ˆTG©}ÉÚˆÇy,Îüˆà"$ì õwÙhº¦¸çÉk†Å$ÒÔ—’¼tÖwá“ö“ l_#îFi/vÓ! ç¨àåù¢û©•éA‹Âæ¿&¸g¦ÎÃ?Ïü®Íg2Iìf6:ÝWÀ$K7öPŸ>QSë’Z¨Y^ »®ObÞÐ=†->¥KIûö5‰Áq¡0Ñ-:tÍ€‘„ChNžLH̦!:øÈ.òP|¦;]€#ÃSŒ.ÁúÈò(ukóG}O®Ð¥qúš“¸|ÕŹS3tQñíŠð÷þ‚Ä»e×4#SÁ¥+cêi7Ðmì™uw'Í6ýìQMåÍ:¬áa8-ŒÉLÖñä"–HÍ27’y¸6æ›m¼gjàÊnòˆœŸÝÁˆwr,dÂhuXÐÙös®1 e=§HC’¦Á0…:›t\LÙS¦÷É&cB Ó~ú±‰1ç\=—”ú÷êxìð5»ž›×˃›{½jÒ…?†ò­-IÈrxå³P=`ßEâ˜háj êkÚ q2zIÏ>Y:Rü{­ŸµÒšçXoëÉd=ÅBŸ´Yþí²õH°ÞdA乂î-£X\S¶9·bl© 9RûM«Iˆ$­‘§ÛúщMq¨ •ì>©¬¶ zL™µ×déª9šßä2»Ö ¯èª û§·`}ONžZÍ ް3ÛK©íÐIBÝä{Ââo}1Yø&¥ØR>) F/¡ëžrgºd©¶Ôº¬hhf•R¤ZÞÆ¬Â¡üWñ¸¥â‡ ><äÏ( «…óA×á½1²¦ªÙŽîÔE^õnO`!ŸO~—LÃøðáÇÍ@Tµþ‚gEw§†žŠµÎ5x:³XÍM•ò\ƒ¬Þyá)µ÷ôi[£ð©¬ÐäCæ~Óû§êÌqå=’gBÙ¨tñ¹Ãlz!¾Ô_к”ü±Üz ȕҙÇÁ&íþʃù©2½ùÏBå÷nn>6³Fdm££<3«„2a“6ΆÒþÅO)ý0›ò7¥bØÙ|å_¬œ`Yb&ý¾yÑ@"ºëæNF;ïÓÔ¸žH'ö3&¹PSb~÷EšôùäY(WHš¿:Oëôöº’W¸ì;j8 `Íø¾wôð±äù<é\脦¤za—%t#¦ˆ¶×CĺŸ¢Í6®n“Æ„D¢©˜}”‘J{¿B7Ìßwä.OI¼Ž› N þ:x3¸ßÚê«z¬Rê®Ü­:S‹\dBÑlbæf\žònV9²Ã=æóÑ‹ÁÃ[w±$Ê tÞg£º$î¸8¿ÅÂÊdÆ›:‘g&ÖØjm{àT¿B9hï!or!ó»îÍ$¾:žÖi4` s(Û´w0FóX˜èõ’“Ñ&²ækÛkþã{4÷÷`FC¶uUËuß\Fd¸^tQ—Ùäb´ÏŸ":éH´fÁš®js7V¾]8³ÌRJQý®´X@püQíG‘è¢ö,ÈçJG¢&¿UæEÅQÉ80Ìnhc¡(?gZ‰Ý«¼fœ×L¿ú•«—s´š¿{Úܘª¿'Ù©Ù Ø÷ÊåbÓg³œSj&ï³CØt’&®Pæ(‰j§Š˜ÀŒÞ^_>÷Ø£Çý:a»£ØåT}s`óð9ÙÂH•[›¾Ô6kUôIsZì³ì cÕ2D"3­Õg™2 ²dlgûvä;žµ0Ú>aÜÐØ€~†Ï#ÂÀž3qÇÇ1/T¢¯ÖÜŸ(ç<€6J]‡åº‹èÛéi“Õ³qye*A^òy%êÛ[$À¨&§<¦ÛÉ~/~ÖìꞃwBÑnixƒ‚j!Jè`[ þèyÓ9 s,àÈ 'Z뫉ùÃêv \q)0§ìx@ΨšLÍ„öòk¼¾âÉQ­+¼ …Eó'Ý#ië 6–í¨&dxË×M#éllv5€m2×YçcE[Óʺhø›¬Ê7½M¯)q†Õ üf›/ǹ+7B^"ù™#î;à ƒ8«óìAêŸùÞÙ«`uêÜîl¶ôÇ~á¾/i–G?{|Œìó˜È<™ÓÊS&-2M+ö4·°vh+gSr8ytVƒ²ß’FÊoø&… •Y}Ê>#ìq| -i}´Î¨ÔºùêÃNa½xѤÈ]%Û®UB0áÄ“!èf`8J ›Šn‘·}Í7Ž}/|ÈÓlx _}Ù¢PžL 0p Ðé‹p˜…žÇoø9X%HPLO¿ÐÇXH!1Ý>2AoAë¨éwú¹Ø¬ ,ÀÈÆ— ¡^8Köèþ ë¾RÔ¨ùŒ±;ˆ¢Â4ic+ÐhãZV‹ÎŠuÚ°Œr(*bùNeú‹{ÛïÙꌘSw×õ½b[TjqD¯ÔUsõ9*ãÓo§1í® ŒÞ¥ÅÇঈ™Îœ]ÎÀÒr'O=Ýïüeg¢‘:÷ ›®uŒ$iÒG¨{MmñtØ:ê=¸þh iÉÅ”²[Ž€T'Ü Ÿ%˜ûšÏÀ?ö}ÉÉ¿WBÚ⫹ì.®Çæ V Á9Ö¤ãDâ…]†"Åå²ëš5Ødä:8ߘïÞ¥’èh ¡½>—rnÚwK-˜ÕZY{ú †TM>)‰Tà ‚¯3r@)Ô®éÌð¶àùvxI)o àD²3¨µ¦lÛû>­Ý>ÉÝI ·u:L¡©ã¨L@x3T*UÈ…*‡“1.Pýâ^å©Ûñ/âyŒãN‚ÿ¡ð‹:ÔÓ:Ä“bè6­¥¢bk%ÀH)"à%Îk,²õÃÔѬ¡ÏöèŒr²“jW»í5ßË ¿ý6}}ÕkWAÒzÐ>rζ9‘ ]%ö²÷‹Hhc©Î0>\³.)RÆ1åœxT1±ôÅDaâRa˜–yð7ójEº(A±³åâP´ËÚn_ʤ}Dg% ‰ê®A“«±ôl5#M|Âۜáð²ßÄ$?WËçÑQŸ`úÜ礌=::J””Ôò9[ˇÝCþFÊm¼e•ªÉ÷Ëcõµ³I¬ïϺA•q{ ޭ׸‡.Þ©ÍVø¤ì¬.7xößÔ[âX¾qÝsM’·úÓª·Gìп\ÐÁ)1JR„ÉØ©ŽÎm[Æ–¦©K‹æÍèþŠ3w¿@d Ǧn£\6ÙÍ\±åØÌßAïKö³\zñó“!cxìA‹žÍ+.˹}n//‚Øk×üJÆ´º#ú\ßV˃Xc@®Óÿ“tšâk±÷ t2Á÷Áô§Þ+Ágõïáo昈„¥™\ÄÍ奦ŸZÇÕfÊÑí ÍCf6¤ Ù‡¶]Ïἃ ZíLú^táÚ„,ånů£ó†é ÈDsÓs˜¯EÍ6¥5*t(Í%¶ÙÚ:b0©+Њ5Õl;u¾÷»G¼ÌÑFB0 ÏŒO3‹WTG¢nei1*R#˜u;›×ÚŒ>"Q)%Éõ‰ÄÔ¬Ž;¯GK¥¹k}QjeØMq#ð\sùÖŒÈûÓEØp½?Ø|ÓúáÂO\ߘe#_$v}bqDaûí!fù¼L*¯%Pw‚(©éÓc¥S‰ˆSnã 1‡´NBbDìØÜ½©,´Ýæ”ÃbæƒøV æ™|SïÁ¾K?Œ û³âÝ3‰1¿–Ç"L’üs•»`6kÄwª_7_å4WÀ®¾Ö—¦3@Ù^‹¥l_iÌuB,ÿÏ ¬†¯HŠ™%’˜Ëbš?mC@±e]¡ÁćܻV ÒÜè”h[)sø^Ì4¹3nK|¬u­Äã$Š(£nôj¿¾'ÈNäzžš›Xhª¡Z&Üuel³V}AcøNjĦ01xΰ`âç^8on:À€ÄX2ä4N—-Öz°KÉTù}G@Ù=ú3^‡µlÔ£usìØ‹q!‰oPˆ¾å2ÖîIùP¤=£êNU`L¦ $µ×MGÄ¿=béµi÷±‡@ñK!"Z\Bø*v¨TŒŠ&ºÙø:´ È¿ÊEd Æ¥8º†‚­#R¨è˳_¬¬ÁU1Ü×È9フ®6ûé‹ÕCb”plšA/«âPÅ^ ß³ÃxÑj­ÒÛ°y^Ámøøí¦o)ËãJdñ÷­¥”´ÓÍ)ë‹\û‚â‚´;3;+j œf?ÄÒÓ®OF-OßåÑjGÑS:`¡ ÷;{´¥¾@wÀD€5k->­åW«Ã¢Ÿ¹1XÐiè¾2q{ƒïÝÙôþæ<ú!¾ÞQ=l>™®º¤úÐFßí‡èúŒŒJ3+VÔ ¬¢_O¥älihpC,.n ypIÓcP» !=ìúœ§Ãd…(E[æê{±ãur Hü&óãw„§uyíáW4@œ“/9Ø“M‰rAöÈ£ÉzëÁ‹Yd•Ž¡¶c9ÖwÃ^'…Àz«ÄÆÆ:V༳“ó®äÂIоg OL»3º@ÓV¢‹Ü2Z§õÕ¬Š'«…½!ú%x)íÛÂ9vüŸÔÝO¿aH[g³Â;1ˆ3]1[b$-¹c÷ÍöÃTQ”7¤5$™’ˆ¶à‚ÐèÆQ’ ¨ã•‹ö»ýõñ±!=ñ…¿í¹êtú0ßÖ¦¾ž²pâ]ŽðLxˉ<˜¾ O×å:E& kq)·b†LNÈbˆ-Vt¨§Cpà Ù_•T§`¿¦x*ðoë:»àЧÐ$iuNp +¤zI×áØûÉ^JUÔ^yaªƒ Áᆡ½5¸âÌ_¢”’ÂCjQ^“cårÐ0‚§#H^ýJ$G»,yÒƒ–f ûe=8äLp7Cºî—‰@üÒ9¾T!]ªDÂü¢¿PØ7=&3³ÖůÏm¼ÞïÇרÓAjs’¼Ýý`ë©êJŒ'QLóBôæþÁå¦è"ò¼á½÷ßævêÑ4¯qëڳ칽ºLŠÍGõHk׃hX–"Ooä^n‰ †ŽKu˜¥…yö.m.­^ô¨ÙâÍuÆÄ?•á _’ ›*’dxÅÆ™ôå‹¿ý)e7eÓaq¦¦7{.V˜µèÓ[¿E³l€·!ˆoºªö2¶3-tw:èQ5oµX¼Ð(Óc¿¬~áø!Nɘ®——1‚ºÂÁEöåú,Œ{_K6µ  fMìN°ŠŠCXœX/›1…J¾uZ½$„ó…'M)Ž0Ü8·®”å ¦,ì—¥HÎJeyé ß éZ¬(Í!¶Âb§oÑ(×¢DÐþÀͼ„úa‘n ×}k7³Æ´4¦ÂjdÉ;žå™–µ°‡ÓW†cA^XNTùÊéÊÚ`ˆEÍ©»OÎ;Ù¼Š}Žïüq6Zñ2@²ý)èA}û ¿è¶ÓCH˜§^¬K=V"«Gæ®<Ž&9r½Àó›éÉ`›l°ÅVxuÚ>¹ÛÇ&úÎ)2=¦*tÚÇ ”X›ÕB:ŹôoNÀŸMHµñUÄY™LY—ÞˆHÐkIÇT¢øë“HJ—[ÓENy¯Œàcè©é(›AâãW?<=òá^)£±Õ€ŸÅDµ;´nT`lÛxë¿÷÷Æ?”ò³Ê^šdPfŽ wI)±ŒòÓÍ«÷ð’Žsq䘳­ÑÈ1_i&ÏÚBè4¹³=€ÓØ\°³:ÿ²˜pù‚fPZ <‰ÂÊC+|œÁp¥ ¦ÛåÆW«‰ ÁÍf°Ëç™g1úËÙ“E†…ö˜mÐ:©Ä%µFhË‹]zðóǨL2¡˜‰û¤(ï9ÑvÝæÎ6¿&Ï4Þ=)'lFÈRþ@Óv6Óž«ËiM›=½¥žk‘Îä8/Ã#?B)“§‹ÈB.‡ïˬ}s0RÇL‰eÛ•ãÁŽ´ÉÕÃPeµdp.Ís1­®Æ^7À5¡,ž Xh]ê‹ 3‰Ž¥kÌ©YS9·n7B·'awKâć8ÐZÐb…NÝ9ƒ®={fÐ¥é >Ã^JDSóp…´üÂÕ<çÒvQZ~Æ ËŽ I°žEÔý½QÆ´"V;½Ãw~]ÍfAöd¶£'d«ÄŸµû¹ZI «%‘O½RžýûŸU5ÜNÙDðƒ\z‘,a€t`SsŠà‹¸jHð »PIŠ5ÁâVä½ßÞô¿`Ó ¯zSÛ#ºaûÚ¯Þ=Ã¥µÞIe’9ûéѪyw1dŠàRŠv5Ánx<ó}×›×Sdtr“ò¤š6Îñz›»x'+Žl] €‡cOõütijËg¹‹jEx.k&Þ}Ëéti†ê—ì;ÇÍ-ÂÜÈ1­• ò®"NñVßËDº| ½«–ãÏàk|ФËš&ˆ®b3bÀ²gR‹eªL8ðÅøŸu)Æqá»üÙ6Ñ7 Í‘ÓõEãŠH+2©ª»}óMŸaG¦ê—ÊÂ’}ýé# ç8ü>³ÇðºöÇ8²ÃÁ EÚÀ–£[v„=lRYJÊÀþæ8óÃn†5?”wb”íL¨Cáè°º¢ß.œé‹ nðÕh–oY “­þ·†]¬´ÑaéФ'‚—„›´]­hÚµ—unÇÑ ôJ ¯ZŽrsÂÄ„2$3œP__+]¡#ž}§"H7ª$")KÇ‹‹OÜÄ„ê:øÂH¤“RT¶^išƒ_&Ÿ‘Eļ¯'T3H ah Úüˆf5jŸJõtõ† ¡Güzø]Õ( +°Äi•…d$ýSE,ýä´³üÏ&ÄØ/. w®#f`ŸØ$•¼. ”¸o''ܧþä³ì¶B?Ö,IeSD7Òøz–®Q@¶Ý3hûBe’ñí2öN;» ܲL~‘z )½ÖäýݲicW‡öjŒ-CE‡K0ZWZó–o‘B¤ÉÊOùgo(óÁ:¿¢j¼JQF;WÄvYqc¶NO}*SšOøû7ÜšÚ¡ çFU«êámäÏ×ÒœI·<]|Y!‘eÍÄÉÜ s€dqoäžGK{¥“ M`#w¢lR¯<×&ùüºº=0õJ‡±K‚s:™L[HlâÇMaÛû¤ðXšÖºŠiBÞP“^T¯1*˜]©«¯íª¥(ãèÙg‚TVœîœÜ´™q «v y®£ÖN ·KOEÙÆøt8ofCùŒ@¡±u€(ïÂE$K‡›„á©‚¶“Ÿba$ß~õWœnÇð™…¶Èš””slúà4!û×"b™¹4ïoSѳA¿¨§U=QQøë¥-û9å{ĤìÔlêvò5§QŠ#l-±ìf<¬Ì…¿ *8MüëUâKj œÎ'gî hœ¢cœUÜN-WΘèO<Á4<Ý@ÿ ]ކxÅʪ5’90:qÍžƨso_t™­åúÞ9Bá;øcÅZXÂótc¢ÆoŸbt9–Ù ÂÏÊ’Úª!Ûç˜çfßÊžî¬UdÔÄùá]€qªŽZ2»o-â—ÆÐé›â§/ÌöÉIÉzSuýαêäU‹^8I•Y}©Íù.´A`™UÃG ,þXàЂÁ àÒÑâìÍòYiÔßI:B¥l8o[òM‚}nñ­«ÈÁ¦¹äï`‚WNNñ<ÞõžäÍ‚¹i}?i7ò…°I¦»'¿íòý°“Øh˜Îÿѧå8Ïî .x¿ ‹/* Á<Ÿ 'Yœ7ç#>d‰çn‚F ^í!{öòƒºäí­ùu¦Î?ÝÛí2ì·Ú“qÞV£´*£ œ«Y˜‰/ÄîúÃëÝ»-w£>þåQZN§¼÷w„ÏNK`;Ð’G{÷xvG8Ì_FXi£ZQ¾‚•$„ Ó¹.¬€m¯°ZSW}š"ºQÎòÀ¶ÄRè ½tQþFÞ® Wx9þk‰Óô»h½æœyéi´–QÝ–ª‰h=f½Þš>ðxÀuʆ³u*K)]š‡ßÈ+K/XŠ` &‹Á}‹ÁKMpGÙ¿ìéïtŽë–˜Ëša˜;ÑTœõ–î»ä … ·c¸¶'M2"ÌÞ”õg_xnÚ#À|g½hÒ·+õ É>v:ÿÔþ†ÍüôŠöȰžBÄÇQ;Qî4Ìì´v³™4‚QáÿÈw±ãVÓ 4ª¿Î¬ÉZðœ:Þ-¤Ûí€ôf&´h úfŠy„£}…*«ÍùcÅ”Ëï ƒÛµ¨GÖê¤è8ûŸÞKw˜Ášâ;Sûäk@ÊXð6FÊæ?ܤµT¶ñ« V§šÜ{鮓+ä9ãÛ—¾‰ 8gxzGä)B§©ã—™öº p¤=óÛ½a-ÿÜ™a—61–Øt,¯ºÊâ­ïK+ß*­Ö2B³bÌ„!OàÖÑÈðqÜãó.£ê`VÁWülm»w”5Óï‹$æL?ïB"½¡òÊ ÀˆŠxÔ)š}bˆ4ä$Ÿ=‚k,·˜ÎüßU8É7àúO+ôž€¸—$½;̸ÞsÖ­69Žè“û Øùv¯›iydîY¶^Ë®Žü63þÃíìåÝšä$„‡ž¸þ¥#:%[ͦĴÙþz,=!̯ö\¨ÀK¡ç(<´NŒbqá Ke¼gÒÂ@³.¸æsÑ…M’¼z…ÃÓ‰µI’Œ_Ãø^Ћý©ÝWZC©~ÇÅ ¹hUXQºdQÆ¡¯Ê¾±)ªŸˆUV†Áoíü 0ȃU7ç63@~F»‚˜¥…Tŵq]¡€Çä‰2Ì’œè¹/ô0¿®É“!SI¿l§ÁxQ¶vþµ9o°ºkû£­›PËœ-,æ–Ú5Óc¸žºÈ$¹hU»„Ö¥³úc‹«àÙàð']à£I¸«Oòtåe‰•HTŠÍ¶g†èÔ)QSÿrïW9n¼öåK½Ê5d*'iŽ¥VݦC-ÐêßÜäŽèVŠ9#‘u(ÊØ¨ô'KgŬ[;*ue3Æp› *ñ¢ï–”ªÜ¸ ‡àrËžæ­àQàµuuHäÉ|!Î*šê “ïj¬ã¿Xê½:ë‡/#­Òa^¡ØB[Ž÷ÂWƒì°M…­?‰ çêG*ž þŒ/¨T²Ÿ/õ=]16¹$­4YÝˉ¬önUÇàðµÛ3}¾öÃÜ…hWbq[‹Brõ¿À0œ(“¹˜,Éõ‚31?qÇ»äÝœEEüŒp–$ƒ“W .%üX4ë’)‘–Ìête8q›üÉ€vÕ/€4õ÷ž !’» ߟ9, \ö¸‰[[=зdœÄcAµºåˆ^hãh}Pßžý&3Aœñ-åN ’áþdîVô$@L»gˆz>õÇöóÌ5­ ÔPau£.E$ýÐOi7¡‘T•z ]^¹3§2û5'¾·”_j‘T xfÙ<*>ó;Þ$„ÊL—d¾éýTXðqa…ÂËh䌽Åò_¤V^ᢄ4H^N€Ô.0ªnš¿CQ×*m¤˜Õƒ³²¾LMåÙÅ8Òó¼9²h€mí‚*­Uh€ö#eÈÙÖ¸ |y4C´¿c¾æ`©Y`h¸¢¾%ò ÷w Œä Uxá9%Bß'ƒÇdáúŒºç²Y«ö‰ûÄÈx E¯+ôÕÐÎCþ˜ç² •Kºäru4»ÁIÎ<«Rv·àŠ‘§³]ÕúÉÃr‡õ–OO1Ùâ€F b¬òwJZýönî ub8{ ¡sæ‹!îM”ÕI’¸y=BRtƃûw¶ëŸdXšÅ»žñò/äéá/7¬}ê âwi#[‚Ä:ÑÓOÕ©½\’O|ý5¿šM‘vúÏ~VÝ»•‹š ¯^ŠUÅüô?K×#(¨ˆ–PnË>/áeL 2Gtàé'ê «ç$2'ÍÖ‹•L´õ’ÚÃ{¶R(ª¹WÈ<½ÆïLÌìCœ^uaß(÷pVæW»@ÚˆÐ÷3£”6¬(ìMÛQ†¢~†í®°Hˆ(AT;.¿Væ?QµÛ…tNp2Ý7C1e÷×½rÁMaiøï¾NjžN.“N—A\*[—p È;>û¬÷Š~9˜ ç4¶šÈöŸN‚ÌvÙ {ÞŸÁÐxWxÓ«â‚Kp胑v³óÁœ5bƒù} Õ“â$EÑ× †¦]=Ž˜dqŠ1)ho sZÐaõ’ß+IC§SÅœª7F”³¼öÈ}ƒ¸GFß—óÌ• P‰lð©$ˆˆ#6º‡B¶ÒJÈéOÈ›\£Ûã±úÑ-~«wÜ)F¸çål+ö–B¢+´EÍAiCMBñôh‹ga²{¾G‘›Ämr¿Þ­<Å< Ídê ÕnÆ{zé™Ûcêë­åyØ,µyRÚÄÔÊ-Re: ¦™âé.ê,ÓÅ’’}Æ#ªÀ šaFF óYÓe½PµÁÐã„Ù JV L<é5‹|ˆÔÝòmëîë«áÏæ„Oz¾f­xÄw_ ?û^Þ-3ixP&ÌÇãÖ'Urç J>n|Ǭ¢Í—‘ßt(ÚÊVÔ::aŠ©žM¬Ÿƒ/)·•„}@<ú~Ø{YI»zÐD¡þâûòÇÖû’rüŠlÖóZ7нñô(^(¦”üâ-¡Ð¤:ïsèñí`û™¦÷S¨RO¸?ÎŒØoµA¥A-D,+•q™4Hg_Áh‚˜ú)0}zÓ|ýô‚>ô·Jí7RaÒb˾k¼Q-€©e‡ws©fEné¢*Ú¯¯¼¶õ• Go~wZ{EÜf ̨˜àÝÒæn° 'ÔTç-²ízÑ%dÓ0º°½Œxè\„¢tìåýÇçûî|ß—;|ÙjxœšƒE¥†èQäU~÷f¡€Ÿxaㆲø$}Œ2ÁPÒ£rà„¢óì’B&É¥ÿ.3®Ç€“i^êÖ™«Â¼EeĺwCNIŠ«W,Ó® >òò\ÁF^ƒ2Ÿº±p½Ú’Š.@êÄ·»ðù{Ëü6ÆõN˜ñ œ*6?úT˜\t.nL¹ð¯æ@ÉÎx‹ÌÉ”Ýé(³A-Þ†W)Z©H!)ˆo_êïš(ÚÉê(´ýHVD¿”\Öê¿þÙñ`þßüþ¿ÃÿS¦6@c³½­1Èáõ÷ endstream endobj 219 0 obj 14472 endobj 220 0 obj << /Type /FontDescriptor /Ascent 960 /CapHeight 0 /Descent -341 /Flags 32 /FontBBox [ -199 -372 1031 991 ] /FontName /BLKJPF+NimbusRomNo9L-Medi /ItalicAngle 0 /StemV 140 /MaxWidth -1230 /StemH 33 /FontFile 218 0 R >> endobj 221 0 obj [ 333 250 250 250 500 500 250 500 250 500 500 250 250 333 250 250 250 250 250 930 722 250 722 722 667 611 778 250 389 250 250 667 944 722 778 250 250 722 556 667 722 722 1000 722 722 667 250 250 250 250 250 250 500 556 444 556 444 333 500 556 278 333 250 278 833 556 500 556 250 444 389 333 556 500 722 250 500 ] endobj 222 0 obj << /Type /Pages /Count 16 /Kids [ 4 0 R 59 0 R 105 0 R ] >> endobj 223 0 obj << /Type /Catalog /Pages 222 0 R /Metadata 226 0 R >> endobj 224 0 obj << /CreationDate (D:20060705162337-04'00') /Creator (TeXShop) /ModDate (D:20060705191930-04'00') /Producer (Mac OS X 10.3.9 Quartz PDFContext) >> endobj 226 0 obj << /Type /Metadata /Subtype /XML /Length 872 >> stream 2006-07-05T16:23:37-04:00 TeXShop 2006-07-05T19:19:30-04:00 Mac OS X 10.3.9 Quartz PDFContext 2006-07-05T16:23:37-04:00 2006-07-05T19:19:30-04:00 2006-07-05T19:19:30-04:00 endstream endobj xref 0 227 0000000225 65535 f 0000000016 00000 n 0000000035 00000 n 0000000176 00000 n 0000000319 00000 n 0000000435 00000 n 0000000504 00000 n 0000012638 00000 n 0000012660 00000 n 0000012852 00000 n 0000013041 00000 n 0000013234 00000 n 0000013428 00000 n 0000013625 00000 n 0000013805 00000 n 0000013984 00000 n 0000014153 00000 n 0000014343 00000 n 0000014539 00000 n 0000014732 00000 n 0000014752 00000 n 0000014895 00000 n 0000015039 00000 n 0000015110 00000 n 0000030041 00000 n 0000030064 00000 n 0000030245 00000 n 0000030427 00000 n 0000030597 00000 n 0000030617 00000 n 0000030760 00000 n 0000030906 00000 n 0000030977 00000 n 0000045036 00000 n 0000045059 00000 n 0000045226 00000 n 0000045246 00000 n 0000045389 00000 n 0000045535 00000 n 0000045606 00000 n 0000057804 00000 n 0000057827 00000 n 0000058007 00000 n 0000058027 00000 n 0000058170 00000 n 0000058316 00000 n 0000058387 00000 n 0000072358 00000 n 0000072381 00000 n 0000072508 00000 n 0000072528 00000 n 0000072671 00000 n 0000072817 00000 n 0000072888 00000 n 0000085234 00000 n 0000085257 00000 n 0000085398 00000 n 0000085418 00000 n 0000085561 00000 n 0000085708 00000 n 0000085826 00000 n 0000085897 00000 n 0000099013 00000 n 0000099036 00000 n 0000099216 00000 n 0000099236 00000 n 0000099379 00000 n 0000099526 00000 n 0000099597 00000 n 0000112199 00000 n 0000112222 00000 n 0000112363 00000 n 0000112383 00000 n 0000112526 00000 n 0000112673 00000 n 0000112744 00000 n 0000124280 00000 n 0000124303 00000 n 0000124496 00000 n 0000124675 00000 n 0000124695 00000 n 0000124839 00000 n 0000124986 00000 n 0000125058 00000 n 0000141086 00000 n 0000141109 00000 n 0000141344 00000 n 0000141514 00000 n 0000141534 00000 n 0000141678 00000 n 0000141825 00000 n 0000141897 00000 n 0000151376 00000 n 0000151398 00000 n 0000151619 00000 n 0000151788 00000 n 0000151808 00000 n 0000151952 00000 n 0000152099 00000 n 0000152171 00000 n 0000158846 00000 n 0000158869 00000 n 0000158996 00000 n 0000159017 00000 n 0000159163 00000 n 0000159314 00000 n 0000159423 00000 n 0000159497 00000 n 0000167068 00000 n 0000167091 00000 n 0000167218 00000 n 0000167239 00000 n 0000167385 00000 n 0000167536 00000 n 0000167610 00000 n 0000172806 00000 n 0000172829 00000 n 0000172930 00000 n 0000172951 00000 n 0000173097 00000 n 0000173248 00000 n 0000173322 00000 n 0000185140 00000 n 0000185164 00000 n 0000185371 00000 n 0000185392 00000 n 0000185538 00000 n 0000185689 00000 n 0000185763 00000 n 0000196929 00000 n 0000196953 00000 n 0000197147 00000 n 0000197170 00000 n 0000197194 00000 n 0000197216 00000 n 0000217521 00000 n 0000217545 00000 n 0000217788 00000 n 0000218542 00000 n 0000218565 00000 n 0000218589 00000 n 0000218611 00000 n 0000238952 00000 n 0000238976 00000 n 0000239223 00000 n 0000240119 00000 n 0000240142 00000 n 0000240165 00000 n 0000240187 00000 n 0000248915 00000 n 0000248938 00000 n 0000249187 00000 n 0000249522 00000 n 0000249544 00000 n 0000249567 00000 n 0000249589 00000 n 0000251691 00000 n 0000251714 00000 n 0000251955 00000 n 0000251986 00000 n 0000252062 00000 n 0000252085 00000 n 0000252109 00000 n 0000252131 00000 n 0000271079 00000 n 0000271103 00000 n 0000271358 00000 n 0000272136 00000 n 0000272158 00000 n 0000272181 00000 n 0000272203 00000 n 0000274556 00000 n 0000274579 00000 n 0000274821 00000 n 0000274921 00000 n 0000274948 00000 n 0000275015 00000 n 0000275037 00000 n 0000275060 00000 n 0000275082 00000 n 0000277300 00000 n 0000277323 00000 n 0000277558 00000 n 0000277800 00000 n 0000277822 00000 n 0000277845 00000 n 0000277867 00000 n 0000279618 00000 n 0000279641 00000 n 0000279881 00000 n 0000279908 00000 n 0000279945 00000 n 0000280038 00000 n 0000280060 00000 n 0000280082 00000 n 0000280104 00000 n 0000281688 00000 n 0000281711 00000 n 0000281950 00000 n 0000281977 00000 n 0000282009 00000 n 0000282089 00000 n 0000282112 00000 n 0000282136 00000 n 0000282158 00000 n 0000299418 00000 n 0000299442 00000 n 0000299683 00000 n 0000300563 00000 n 0000300586 00000 n 0000300609 00000 n 0000300631 00000 n 0000304233 00000 n 0000304256 00000 n 0000304512 00000 n 0000304624 00000 n 0000304647 00000 n 0000304671 00000 n 0000304693 00000 n 0000319297 00000 n 0000319321 00000 n 0000319569 00000 n 0000319905 00000 n 0000319987 00000 n 0000320063 00000 n 0000000000 00001 f 0000320228 00000 n trailer << /Size 227 /Info 224 0 R /Root 223 0 R /ID[<9411fe9b73231f0f34f91086b51a3dfa><66082f7c77d9852fa600ce40b0c10aab>] >> startxref 321185 %%EOF 3 0 obj << /Type /Page /Parent 4 0 R /Resources 5 0 R /Contents 2 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 30 0 obj << /Type /Page /Parent 4 0 R /Resources 31 0 R /Contents 29 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 37 0 obj << /Type /Page /Parent 4 0 R /Resources 38 0 R /Contents 36 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 44 0 obj << /Type /Page /Parent 4 0 R /Resources 45 0 R /Contents 43 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 51 0 obj << /Type /Page /Parent 4 0 R /Resources 52 0 R /Contents 50 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 58 0 obj << /Type /Page /Parent 59 0 R /Resources 60 0 R /Contents 57 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 66 0 obj << /Type /Page /Parent 59 0 R /Resources 67 0 R /Contents 65 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 73 0 obj << /Type /Page /Parent 59 0 R /Resources 74 0 R /Contents 72 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 81 0 obj << /Type /Page /Parent 59 0 R /Resources 82 0 R /Contents 80 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 89 0 obj << /Type /Page /Parent 59 0 R /Resources 90 0 R /Contents 88 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 97 0 obj << /Type /Page /Parent 59 0 R /Resources 98 0 R /Contents 96 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 104 0 obj << /Type /Page /Parent 105 0 R /Resources 106 0 R /Contents 103 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 112 0 obj << /Type /Page /Parent 105 0 R /Resources 113 0 R /Contents 111 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 119 0 obj << /Type /Page /Parent 105 0 R /Resources 120 0 R /Contents 118 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 126 0 obj << /Type /Page /Parent 105 0 R /Resources 127 0 R /Contents 125 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 223 0 obj << /Type /Catalog /Pages 222 0 R /Metadata 225 1 R >> endobj 224 0 obj << /CreationDate (D:20060705162337-04'00') /Creator (TeXShop) /ModDate (D:20060705192139-04'00') /Producer (Mac OS X 10.3.9 Quartz PDFContext) >> endobj 225 1 obj << /Type /Metadata /Subtype /XML /Length 872 >> stream 2006-07-05T16:23:37-04:00 TeXShop 2006-07-05T19:21:39-04:00 Mac OS X 10.3.9 Quartz PDFContext 2006-07-05T16:23:37-04:00 2006-07-05T19:21:39-04:00 2006-07-05T19:21:39-04:00 endstream endobj xref 0 1 0000000000 65535 f 3 1 0000325888 00000 n 30 1 0000326029 00000 n 37 1 0000326173 00000 n 44 1 0000326317 00000 n 51 1 0000326461 00000 n 58 1 0000326605 00000 n 66 1 0000326750 00000 n 73 1 0000326895 00000 n 81 1 0000327040 00000 n 89 1 0000327185 00000 n 97 1 0000327330 00000 n 104 1 0000327475 00000 n 112 1 0000327624 00000 n 119 1 0000327773 00000 n 126 1 0000327922 00000 n 223 3 0000328071 00000 n 0000328147 00000 n 0000328312 00001 n trailer << /Size 227 /Info 224 0 R /Root 223 0 R /Prev 321185 /ID[<9411fe9b73231f0f34f91086b51a3dfa><90c0724dbce351cf1d6ac7f413181478>] >> startxref 329269 %%EOF ./CBFlib-0.9.2.2/doc/Iaxis.vector[2].html0000644000076500007650000000516311603702115016166 0ustar yayayaya (IUCr) CIF Definition save__axis.vector[2]

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_axis.vector[2]

Name:
'_axis.vector[2]'

Definition:

        The [2] element of the three-element vector used to specify
               the direction of a rotation or translation axis.
               The vector should be normalized to be a unit vector and
               is dimensionless.

Type: float

Mandatory item: no


Enumeration default: 0.0

Category: axis

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_radiation.monochromator.html0000644000076500007650000000647211603702115021543 0ustar yayayaya (IUCr) CIF Definition save__diffrn_radiation.monochromator

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_radiation.monochromator

Name:
'_diffrn_radiation.monochromator'

Definition:

        The method used to obtain monochromatic radiation. If a
               monochromator crystal is used, the material and the
               indices of the Bragg reflection are specified.

Examples:

'Zr filter'
'Ge 220'
none
'equatorial mounted graphite'

Type: text

Mandatory item: no

Alias:
_diffrn_radiation_monochromator (cif_core.dic version 2.0.1)

Category: diffrn_radiation

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Iarray_structure_list_axis.angular_pitch.html0000644000076500007650000000614611603702115023505 0ustar yayayaya (IUCr) CIF Definition save__array_structure_list_axis.angular_pitch

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_array_structure_list_axis.angular_pitch

Name:
'_array_structure_list_axis.angular_pitch'

Definition:

        The pixel-centre-to-pixel-centre distance for a one-step
               change in the setting of the specified axis in millimetres.

               This is meaningful only for 'constant velocity' spiral scans
               or for uncoupled angular scans at a constant radius
               (cylindrical scans) and should not be specified for cases
               in which the angle between pixels (rather than the distance
               between pixels) is uniform.

               See _array_structure_list_axis.angle_increment.

Type: float

Mandatory item: no


Enumeration default: 0.0

Category: array_structure_list_axis

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_measurement_axis.measurement_id.html0000644000076500007650000000617011603702115023247 0ustar yayayaya (IUCr) CIF Definition save__diffrn_measurement_axis.measurement_id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_measurement_axis.measurement_id

Name:
'_diffrn_measurement_axis.measurement_id'

Definition:

        This data item is a pointer to _diffrn_measurement.id in
               the DIFFRN_MEASUREMENT category.

               This item was previously named _diffrn_measurement_axis.id,
               which is now a deprecated name.  The old name is
               provided as an alias but should not be used for new work.

Type: code

Mandatory item: implicit

Alias:
_diffrn_measurement_axis.id (cif_img.dic version 1.0)

Category: diffrn_measurement_axis

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Iarray_structure_list.direction.html0000644000076500007650000000570711603702115021623 0ustar yayayaya (IUCr) CIF Definition save__array_structure_list.direction

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_array_structure_list.direction

Name:
'_array_structure_list.direction'

Definition:

       Identifies the direction in which this array index changes.

Type: code

Mandatory item: yes


The data value must be one of the following:


increasing
Indicates the index changes from 1 to the maximum dimension.

decreasing
Indicates the index changes from the maximum dimension to 1.

Category: array_structure_list

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_detector_axis.detector_id.html0000644000076500007650000000610211603702115022012 0ustar yayayaya (IUCr) CIF Definition save__diffrn_detector_axis.detector_id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_detector_axis.detector_id

Name:
'_diffrn_detector_axis.detector_id'

Definition:

        This data item is a pointer to _diffrn_detector.id in
               the DIFFRN_DETECTOR category.

               This item was previously named _diffrn_detector_axis.id
               which is now a deprecated name.  The old name is
               provided as an alias but should not be used for new work.

Type: code

Mandatory item: yes

Alias:
_diffrn_detector_axis.id (cif_img.dic version 1.0)

Category: diffrn_detector_axis

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_measurement_axis.axis_id.html0000644000076500007650000000507611603702115021672 0ustar yayayaya (IUCr) CIF Definition save__diffrn_measurement_axis.axis_id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_measurement_axis.axis_id

Name:
'_diffrn_measurement_axis.axis_id'

Definition:

        This data item is a pointer to _axis.id in
               the AXIS category.

Type: code

Mandatory item: yes

Category: diffrn_measurement_axis

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/cif_img_1.5.dic0000777000076500007650000000000011603751102020737 2cif_img_1.5.4_28Jul07.dicustar yayayaya./CBFlib-0.9.2.2/doc/cif_img_1.6.dic0000777000076500007650000000000011603751102020644 2cif_img_1.6.4_2Jul11.dicustar yayayaya./CBFlib-0.9.2.2/doc/Iarray_structure.byte_order.html0000644000076500007650000000662711603702115020750 0ustar yayayaya (IUCr) CIF Definition save__array_structure.byte_order

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_array_structure.byte_order

Name:
'_array_structure.byte_order'

Definition:

        The order of bytes for integer values which require more
               than 1 byte.

               (IBM-PC's and compatibles and DEC VAXs use low-byte-first
               ordered integers, whereas Hewlett Packard 700
               series, Sun-4 and Silicon Graphics use high-byte-first
               ordered integers.  DEC Alphas can produce/use either
               depending on a compiler switch.)

Type: ucode

Mandatory item: yes


The data value must be one of the following:


big_endian
The first byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer.

little_endian
The last byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer.

Category: array_structure

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Iarray_intensities.undefined_value.html0000644000076500007650000000501711603702115022235 0ustar yayayaya (IUCr) CIF Definition save__array_intensities.undefined_value

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_array_intensities.undefined_value

Name:
'_array_intensities.undefined_value'

Definition:

        A value to be substituted for undefined values in
               the data array.

Type: float

Mandatory item: no

Category: array_intensities

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_scan_axis.angle_increment.html0000644000076500007650000000701211603702115021773 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan_axis.angle_increment

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_scan_axis.angle_increment

Name:
'_diffrn_scan_axis.angle_increment'

Definition:

        The increment for each step for the specified axis
               in degrees.  In general, this will agree with
               _diffrn_scan_frame_axis.angle_increment. The
               sum of the values of _diffrn_scan_frame_axis.angle and
               _diffrn_scan_frame_axis.angle_increment is the
               angular setting of the axis at the end of the integration
               time for a given frame.  If the individual frame values
               vary, then the value of
               _diffrn_scan_axis.angle_increment will be
               representative
               of the ensemble of values of
               _diffrn_scan_frame_axis.angle_increment (e.g.
               the mean).

Type: float

Mandatory item: no


Enumeration default: 0.0

Category: diffrn_scan_axis

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_detector_axis.axis_id.html0000644000076500007650000000505711603702115021155 0ustar yayayaya (IUCr) CIF Definition save__diffrn_detector_axis.axis_id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_detector_axis.axis_id

Name:
'_diffrn_detector_axis.axis_id'

Definition:

        This data item is a pointer to _axis.id in
               the AXIS category.

Type: code

Mandatory item: yes

Category: diffrn_detector_axis

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Iarray_structure_list.axis_set_id.html0000644000076500007650000000656111603702115022135 0ustar yayayaya (IUCr) CIF Definition save__array_structure_list.axis_set_id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_array_structure_list.axis_set_id

Name:
'_array_structure_list.axis_set_id'

Definition:

        This is a descriptor for the physical axis or set of axes
               corresponding to an array index.

               This data item is related to the axes of the detector
               itself given in DIFFRN_DETECTOR_AXIS, but usually differs
               in that the axes in this category are the axes of the
               coordinate system of reported data points, while the axes in
               DIFFRN_DETECTOR_AXIS are the physical axes
               of the detector describing the 'poise' of the detector as an
               overall physical object.

               If there is only one axis in the set, the identifier of
               that axis should be used as the identifier of the set.

Type: code

Mandatory item: yes

_array_structure_list_axis.axis_set_id

Category: array_structure_list

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/ddl_core_1.4.1.dic0000644000076500007650000004604511603702115015331 0ustar yayayaya############################################################################## # # # DDL CORE DICTIONARY # # # ############################################################################## data_on_this_dictionary _dictionary_name ddl_core.dic _dictionary_version 1.4.1 _dictionary_update 2005-06-29 _dictionary_history ; 1991-03-08 "Implementing SMD in STAR: Dictionary Definition Language" A F P Cook, ORAC Ltd., 8 March 1991. AFPC 1991-06-25 Adjustments and refinement for CIF applications. SRH 1991-09-02 Further refinements prior to "cifdic.c91". SRH 1993-05-10 Additions arising from discussions with Phil Bourne, Tony Cook, Brian McMahon. SRH 1993-05-11 Further adjustments and Cyclops tests. SRH 1993-05-14 Proposed additional changes. PEB 1993-05-17 Further adjustments. SRH 1993-06-01 Refinements and additions. SRH 1993-07-19 Some tidying up. SRH 1993-08-10 Final checks before Beijing. SRH 1993-12-12 Following the Cambridge meeting with FHA and AFPC. SRH 1993-12-16 Following discussions with Brian McMahon in Chester. SRH 1993-12-17 Further adjustments. SRH 1994-02-18 Add _include_file provisions. SRH 1994-08-08 Install _type_construct definitions and apply. SRH 1994-08-24 Adjustments following Brian McMahon's comments. SRH 1994-11-16 Changes following Brussels workshop. SRH 1995-05-16 Changes to _units definitions. SRH 2005-02-09 Minor corrections to spelling and punctuation. Reference to REGEX specifications updated. NJA 2005-06-11 Structural change to rationalise DDL1 dictionary against specification documents in IT Vol. G. Initial global_ block removed, "_enumeration_default none" added to definition of _type_conditions and "_enumeration_default .*" to definition of _type_construct. BMcM 2005-06-20 Minor corrections to reflect proof corrections for Chapter 4.9 of IT Vol. G. NJA 2005-06-29 Allow use of 'su' as synonym for 'esd' in _type_conditions and describe 'esd' as 'deprecated'. BMcM ; data_category _definition ; Character string which identifies the natural grouping of data items to which the specified data item belongs. If the data item belongs in a looped list, then it must be grouped only with items from the same category, but there may be more than one looped list of the same category provided that each loop has its own independent reference item (see _list_reference). ; _name '_category' _category category _type char data_definition _definition ; The text description of the defined item. ; _name '_definition' _category definition _type char data_dictionary_history _definition ; A chronological record of the changes to the dictionary file containing the definition. Normally this item is stored in the separate data block labelled data_on_this_dictionary. ; _name '_dictionary_history' _category dictionary _type char data_dictionary_name _definition ; The name string which identifies the generic identity of the dictionary. The standard construction for these names is _.dic Normally this item is stored in the separate data block labelled data_on_this_dictionary. ; _name '_dictionary_name' _category dictionary _type char loop_ _example ddl_core.dic cif_core.dic data_dictionary_update _definition ; The date that the dictionary was last updated. Normally this item is stored in the separate data block labelled data_on_this_dictionary. ; _name '_dictionary_update' _category dictionary _type char _type_construct (_chronology_year)-(_chronology_month)-(_chronology_day) data_dictionary_version _definition ; The dictionary version number. Version numbers cannot decrease with updates. Normally this item is stored in the separate data block labelled data_on_this_dictionary. ; _name '_dictionary_version' _category dictionary _type numb data_enumeration _definition ; Permitted value(s) for the defined item. ; _name '_enumeration' _category enumeration _type char _list both _list_mandatory yes data_enumeration_default _definition ; The default value for the defined item if it is not specified explicitly. If a data value is not declared, the default is assumed to be the "most likely" or "natural" value. ; _name '_enumeration_default' _category enumeration_default _type char data_enumeration_detail _definition ; A description of the permitted value(s) for the defined item, as identified by _enumeration. ; _name '_enumeration_detail' _category enumeration _type char _list both _list_reference '_enumeration' data_enumeration_range _definition ; The range of values permitted for a defined item. This can apply to 'numb' or 'char' items which have a preordained sequence (e.g. numbers or alphabetical characters). The minimum value 'min' and maximum value 'max' are separated by a colon character. If 'max' is omitted, then the item can have any permitted value greater than or equal to 'min'. ; _name '_enumeration_range' _category enumeration_range _type char _type_construct (_sequence_minimum):((_sequence_maximum)?) loop_ _example -4:10 a:z B:R 0: data_example _definition ; An example value of the defined item. ; _name '_example' _category example _type char _list both _list_mandatory yes data_example_detail _definition ; A description of an example value for the defined item. ; _name '_example_detail' _category example _type char _list both _list_reference '_example' data_list _definition ; Signals whether the defined item is declared in a looped list. ; _name '_list' _category list _type char loop_ _enumeration _enumeration_detail yes 'can only be declared in a looped list' no 'cannot be declared in a looped list' both 'declaration in a looped list optional' _enumeration_default no data_list_level _definition ; Specifies the level of the loop structure in which a defined item with the attribute _list 'yes' or 'both' must be declared. ; _name '_list_level' _category list _type numb _enumeration_range 1: _enumeration_default 1 data_list_link_child _definition ; Identifies data item(s) by name which must have a value which matches that of the defined item. These items are referred to as "child" references because they depend on the existence of the defined item. ; _name '_list_link_child' _category list_link_child _type char _list both data_list_link_parent _definition ; Identifies a data item by name which must have a value which matches that of the defined item, and which must be present in the same data block as the defined item. This provides for a reference to the "parent" data item. ; _name '_list_link_parent' _category list_link_parent _type char _list both data_list_mandatory _definition ; Signals whether the defined item must be present in the loop structure containing other items of the designated _category. This property is transferrable to another data item which is identified by _related_item and has _related_function set as 'alternate'. ; _name '_list_mandatory' _category list _type char loop_ _enumeration _enumeration_detail yes 'required item in this category of looped list' no 'optional item in this category of looped list' _enumeration_default no data_list_reference _definition ; Identifies the data item, or items, which must be present (collectively) in a looped list with the defined data item for the loop structure to be valid. The data item(s) identified by _list_reference provide a unique access code to each loop packet. Note that this property may be transferred to another item with _related_function 'alternate'. ; _name '_list_reference' _category list_reference _type char _list both data_list_uniqueness _definition ; Identifies data items which, collectively, must have unique values for the loop structure of the designated _category items to be valid. This attribute is specified in the definition of a data item with _list_mandatory set to 'yes'. ; _name '_list_uniqueness' _category list_uniqueness _type char _list both data_name _definition ; The data name(s) of the defined item(s). If data items are closely related or represent an irreducible set, their names may be declared as a looped sequence in the same definition. ; _name '_name' _category name _type char _list both loop_ _example '_atom_site_label' '_atom_attach_all _atom_attach_ring' '_index_h _index_k _index_l' '_matrix_11 _matrix_12 _matrix_21 _matrix_22' data_related_item _definition ; Identifies data item(s) which have a classified relationship to the defined data item. The nature of this relationship is specified by _related_function. ; _name '_related_item' _category related _type char _list both _list_mandatory yes data_related_function _definition ; Specifies the relationship between the defined item and the item specified by _related_item. The following classifications are recognized. 'alternate' signals that the item referred to in _related_item has attributes that permit it to be used as an alternative to the defined item for validation purposes. 'convention' signals that the item referred to in _related_item is equivalent to the defined item except for a predefined convention which requires a different _enumeration set. 'conversion' signals that the item referred to in _related_item is equivalent to the defined item except that different scaling or conversion factors are applied. 'replace' signals that the item referred to in _related_item may be used identically to replace the defined item. ; _name '_related_function' _category related _type char _list yes _list_reference '_related_item' loop_ _enumeration _enumeration_detail alternate 'used alternatively for validation tests' convention 'equivalent except for defined convention' conversion 'equivalent except for conversion factor' replace 'new definition replaces the current one' data_type _definition ; The type specification of the defined item. Type 'numb' identifies items which must have values that are identifiable numbers. The acceptable syntax for these numbers is application-dependent, but the formats illustrated by the following identical numbers are considered to be interchangeable: 42 42.000 0.42E2 .42E+2 4.2E1 420000D-4 0.0000042D+07 Type 'char' identifies items which need not be interpretable numbers. The specification of these items must comply with the STAR syntax specification of either a 'contiguous single-line string' bounded by blanks or blank-quotes, or a 'text string' bounded by semicolons as the first character of a line. Type 'null' identifies items which appear in the dictionary for data-definition and descriptive purposes. These items serve no function outside the dictionary files. ; _name '_type' _category type _type char loop_ _enumeration _enumeration_detail numb 'numerically interpretable string' char 'character or text string' null 'for dictionary purposes only' data_type_conditions _definition ; Codes defining conditions on the _type specification. 'su' permits a number string to contain an appended standard uncertainty number enclosed within parentheses. E.g. 4.37(5) 'esd' is a deprecated synonym for 'su', arising from the former use of the term 'estimated standard deviation' for 'standard uncertainty', and permitting a number string to contain an appended standard deviation within parentheses. E.g. 4.37(5) 'seq' permits data to be declared as a sequence of values separated by a comma <,> or a colon <:>. * The sequence v1,v2,v3,. signals that v1, v2, v3, etc. are alternative values. * The sequence v1:v2 signals that v1 and v2 are the boundary values of a continuous range of values satisfying the requirements of _enumeration for the defined item. Combinations of alternative and range sequences are permitted. ; _name '_type_conditions' _category type_conditions _type char _list both _enumeration_default none loop_ _enumeration _enumeration_detail none 'no extra conditions apply to the defined _type' esd 'synonym for su' seq 'data may be declared as a permitted sequence' su 'numbers *may* have s.u.'s appended within parentheses' data_type_construct _definition ; String of characters specifying the construction of the data value for the defined data item. The construction is composed of two entities: (1) data names (2) construction characters The rules of construction conform to the regular expression (REGEX) specifications detailed in IEEE (1991) and International Tables for Crystallography Volume G, Chapter 2.5. Ref: IEEE (1991). IEEE Standard for Information Technology - Portable Operating System Interface (POSIX) - Part 2: Shell and Utilities, Vol. 1, IEEE Standard 1003.2-1992. New York: The Institute of Electrical Engineers. International Tables for Crystallography (2005). Vol. G, Definition and Exchange of Crystallographic Data, edited by S. R. Hall and B. McMahon. Heidelberg: Springer. ; _name '_type_construct' _category type_construct _type char _enumeration_default .* _example (_year)-(_month)-(_day) _example_detail 'a typical construction for _date' data_units _definition ; A unique code which identifies the units of the defined data item. A description of the units is provided in _units_detail. ; _name '_units' _category units _type char loop_ _example _example_detail K 'kelvins' C 'degrees Celsius' rad 'radians' e 'electrons' V 'volts' Dal 'daltons' m 'metres' kg 'kilograms' s 'seconds' data_units_detail _definition ; A description of the numerical units applicable to the defined item and identified by the code _units. ; _name '_units_detail' _category units _type char #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof ./CBFlib-0.9.2.2/doc/Iarray_structure_list.array_id.html0000644000076500007650000000520511603702115021426 0ustar yayayaya (IUCr) CIF Definition save__array_structure_list.array_id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_array_structure_list.array_id

Name:
'_array_structure_list.array_id'

Definition:

       This item is a pointer to _array_structure.id in the
              ARRAY_STRUCTURE category.

Type: code

Mandatory item: implicit

Category: array_structure_list

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_frame_data.detector_element_id.html0000644000076500007650000000533211603702115022755 0ustar yayayaya (IUCr) CIF Definition save__diffrn_frame_data.detector_element_id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_frame_data.detector_element_id

Name:
'_diffrn_frame_data.detector_element_id'

Definition:

       This item is a pointer to _diffrn_detector_element.id
              in the DIFFRN_DETECTOR_ELEMENT category.

              DEPRECATED -- DO NOT USE

Type: code

Mandatory item: yes

Category: diffrn_frame_data

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/cif_img_1.3.2_IUCr.dic0000644000076500007650000054712511603702115016042 0ustar yayayaya############################################################################## # # # Image CIF Dictionary (imgCIF) # # and Crystallographic Binary File Dictionary (CBF) # # Extending the Macromolecular CIF Dictionary (mmCIF) # # # # Version 1.3.2 # # of 2005-06-25 # # # # by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook # # # # This dictionary was adapted from format discussed at the imgCIF Workshop, # # held at BNL Oct 1997 and the Crystallographic Binary File Format Draft # # Proposal by Andrew Hammersley. The first DDL 2.1 Version was created by # # John Westbrook. This version was drafted by Herbert J. Bernstein and # # incorporates comments by I. David Brown, John Westbrook, Brian McMahon, # # Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li, Gotzon Madariaga, # # Frances C. Bernstein and others. # ############################################################################## data_cif_img.dic _dictionary.title cif_img.dic _dictionary.version 1.3.2 _dictionary.datablock_id cif_img.dic ############################################################################## # CONTENTS # # CATEGORY_GROUP_LIST # # category ARRAY_DATA # # _array_data.array_id # _array_data.binary_id # _array_data.data # # category ARRAY_ELEMENT_SIZE # # _array_element_size.array_id # _array_element_size.index # _array_element_size.size # # category ARRAY_INTENSITIES # # _array_intensities.array_id # _array_intensities.binary_id # _array_intensities.gain # _array_intensities.gain_esd # _array_intensities.linearity # _array_intensities.offset # _array_intensities.scaling # _array_intensities.overload # _array_intensities.undefined_value # # category ARRAY_STRUCTURE # # _array_structure.byte_order # _array_structure.compression_type # _array_structure.encoding_type # _array_structure.id # # category ARRAY_STRUCTURE_LIST # # _array_structure_list.axis_set_id # _array_structure_list.array_id # _array_structure_list.dimension # _array_structure_list.direction # _array_structure_list.index # _array_structure_list.precedence # # category ARRAY_STRUCTURE_LIST_AXIS # # _array_structure_list_axis.axis_id # _array_structure_list_axis.axis_set_id # _array_structure_list_axis.angle # _array_structure_list_axis.angle_increment # _array_structure_list_axis.displacement_increment # _array_structure_list_axis.angular_pitch # _array_structure_list_axis.radial_pitch # # category AXIS # # _axis.depends_on # _axis.equipment # _axis.id # _axis.offset[1] # _axis.offset[2] # _axis.offset[3] # _axis.type # _axis.vector[1] # _axis.vector[2] # _axis.vector[3] # # category DIFFRN_DATA_FRAME # # _diffrn_data_frame.array_id # _diffrn_data_frame.binary_id # _diffrn_data_frame.detector_element_id # _diffrn_data_frame.id # # category DIFFRN_DETECTOR # # _diffrn_detector.details # _diffrn_detector.detector # _diffrn_detector.diffrn_id # _diffrn_detector.dtime # _diffrn_detector.id # _diffrn_detector.number_of_axes # _diffrn_detector.type # # category DIFFRN_DETECTOR_AXIS # # _diffrn_detector_axis.axis_id # _diffrn_detector_axis.detector_id # # category DIFFRN_DETECTOR_ELEMENT # # _diffrn_detector_element.center[1] # _diffrn_detector_element.center[2] # _diffrn_detector_element.id # _diffrn_detector_element.detector_id # # category DIFFRN_MEASUREMENT # # _diffrn_measurement.diffrn_id # _diffrn_measurement.details # _diffrn_measurement.device # _diffrn_measurement.device_details # _diffrn_measurement.device_type # _diffrn_measurement.id # _diffrn_measurement.method # _diffrn_measurement.number_of_axes # _diffrn_measurement.specimen_support # # category DIFFRN_MEASUREMENT_AXIS # # _diffrn_measurement_axis.axis_id # _diffrn_measurement_axis.measurement_device # _diffrn_measurement_axis.measurement_id # # category DIFFRN_RADIATION # # _diffrn_radiation.collimation # _diffrn_radiation.diffrn_id # _diffrn_radiation.div_x_source # _diffrn_radiation.div_y_source # _diffrn_radiation.div_x_y_source # _diffrn_radiation.filter_edge' # _diffrn_radiation.inhomogeneity # _diffrn_radiation.monochromator # _diffrn_radiation.polarisn_norm # _diffrn_radiation.polarisn_ratio # _diffrn_radiation.polarizn_source_norm # _diffrn_radiation.polarizn_source_ratio # _diffrn_radiation.probe # _diffrn_radiation.type # _diffrn_radiation.xray_symbol # _diffrn_radiation.wavelength_id # # category DIFFRN_REFLN # # _diffrn_refln.frame_id # # category DIFFRN_SCAN # # _diffrn_scan.id # _diffrn_scan.date_end # _diffrn_scan.date_start # _diffrn_scan.integration_time # _diffrn_scan.frame_id_start # _diffrn_scan.frame_id_end # _diffrn_scan.frames # # category DIFFRN_SCAN_AXIS # # _diffrn_scan_axis.axis_id # _diffrn_scan_axis.angle_start # _diffrn_scan_axis.angle_range # _diffrn_scan_axis.angle_increment # _diffrn_scan_axis.angle_rstrt_incr # _diffrn_scan_axis.displacement_start # _diffrn_scan_axis.displacement_range # _diffrn_scan_axis.displacement_increment # _diffrn_scan_axis.displacement_rstrt_incr # _diffrn_scan_axis.scan_id # # category DIFFRN_SCAN_FRAME # # _diffrn_scan_frame.date # _diffrn_scan_frame.frame_id # _diffrn_scan_frame.frame_number # _diffrn_scan_frame.integration_time # _diffrn_scan_frame.scan_id # # category DIFFRN_SCAN_FRAME_AXIS # # _diffrn_scan_frame_axis.axis_id # _diffrn_scan_frame_axis.angle # _diffrn_scan_frame_axis.angle_increment # _diffrn_scan_frame_axis.angle_rstrt_incr # _diffrn_scan_frame_axis.displacement # _diffrn_scan_frame_axis.displacement_increment # _diffrn_scan_frame_axis.displacement_rstrt_incr # _diffrn_scan_frame_axis.frame_id # # ***DEPRECATED*** data items # # _diffrn_detector_axis.id # _diffrn_measurement_axis.id # # ***DEPRECATED*** category DIFFRN_FRAME_DATA # # _diffrn_frame_data.array_id # _diffrn_frame_data.binary_id # _diffrn_frame_data.detector_element_id # _diffrn_frame_data.id # # # ITEM_TYPE_LIST # ITEM_UNITS_LIST # DICTIONARY_HISTORY # ############################################################################## ######################### ## CATEGORY_GROUP_LIST ## ######################### loop_ _category_group_list.id _category_group_list.parent_id _category_group_list.description 'inclusive_group' . ; Categories that belong to the dictionary extension. ; 'array_data_group' 'inclusive_group' ; Categories that describe array data. ; 'axis_group' 'inclusive_group' ; Categories that describe axes. ; 'diffrn_group' 'inclusive_group' ; Categories that describe details of the diffraction experiment. ; ############## # ARRAY_DATA # ############## save_ARRAY_DATA _category.description ; Data items in the ARRAY_DATA category are the containers for the array data items described in the category ARRAY_STRUCTURE. ; _category.id array_data _category.mandatory_code no loop_ _category_key.name '_array_data.array_id' '_array_data.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows two binary data blocks. The first one was compressed by the CBF_CANONICAL compression algorithm and is presented as hexadecimal data. The first character 'H' on the data lines means hexadecimal. It could have been 'O' for octal or 'D' for decimal. The second character on the line shows the number of bytes in each word (in this case '4'), which then requires eight hexadecimal digits per word. The third character gives the order of octets within a word, in this case '<' for the ordering 4321 (i.e. 'big-endian'). Alternatively, the character '>' could have been used for the ordering 1234 (i.e. 'little-endian'). The block has a 'message digest' to check the integrity of the data. The second block is similar, but uses CBF_PACKED compression and BASE64 encoding. Note that the size and the digest are different. ; ; loop_ _array_data.array_id _array_data.binary_id _array_data.data image_1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_CANONICAL" Content-Transfer-Encoding: X-BASE16 X-Binary-Size: 3927126 X-Binary-ID: 1 Content-MD5: u2sTJEovAHkmkDjPi+gWsg== # Hexadecimal encoding, byte 0, byte order ...21 # H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ... .... --CIF-BINARY-FORMAT-SECTION---- ; image_2 2 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF-PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3745758 X-Binary-ID: 2 Content-MD5: 1zsJjWPfol2GYl2V+QSXrw== ELhQAAAAAAAA... ... --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_data.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_data.array_id' _item.category_id array_data _item.mandatory_code yes _item_type.code code save_ save__array_data.binary_id _item_description.description ; This item is an integer identifier which, along with _array_data.array_id, should uniquely identify the particular block of array data. If _array_data.binary_id is not explicitly given, it defaults to 1. The value of _array_data.binary_id distinguishes among multiple sets of data with the same array structure. If the MIME header of the data array specifies a value for X-Binary-ID, the value of _array_data.binary_id should be equal to the value given for X-Binary-ID. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_data.binary_id' array_data implicit '_diffrn_data_frame.binary_id' diffrn_data_frame implicit '_array_intensities.binary_id' array_intensities implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.binary_id' '_array_data.binary_id' '_array_intensities.binary_id' '_array_data.binary_id' _item_default.value 1 _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_data.data _item_description.description ; The value of _array_data.data contains the array data encapsulated in a STAR string. The representation used is a variant on the Multipurpose Internet Mail Extensions (MIME) specified in RFC 2045-2049 by N. Freed et al. The boundary delimiter used in writing an imgCIF or CBF is "--CIF-BINARY-FORMAT-SECTION--" (including the required initial "--"). The Content-Type may be any of the discrete types permitted in RFC 2045; 'application/octet-stream' is recommended. If an octet stream was compressed, the compression should be specified by the parameter 'conversions="x-CBF_PACKED"' or the parameter 'conversions="x-CBF_CANONICAL"'. The Content-Transfer-Encoding may be 'BASE64', 'Quoted-Printable', 'X-BASE8', 'X-BASE10' or 'X-BASE16' for an imgCIF or 'BINARY' for a CBF. The octal, decimal and hexadecimal transfer encodings are for convenience in debugging and are not recommended for archiving and data interchange. In an imgCIF file, the encoded binary data begin after the empty line terminating the header. In a CBF, the raw binary data begin after an empty line terminating the header and after the sequence: Octet Hex Decimal Purpose 0 0C 12 (Ctrl-L) page break 1 1A 26 (Ctrl-Z) stop listings in MS-DOS 2 04 04 (Ctrl-D) stop listings in UNIX 3 D5 213 binary section begins None of these octets are included in the calculation of the message size or in the calculation of the message digest. The X-Binary-Size header specifies the size of the equivalent binary data in octets. If compression was used, this size is the size after compression, including any book-keeping fields. An adjustment is made for the deprecated binary formats in which eight bytes of binary header are used for the compression type. In this case, the eight bytes used for the compression type are subtracted from the size, so that the same size will be reported if the compression type is supplied in the MIME header. Use of the MIME header is the recommended way to supply the compression type. In general, no portion of the binary header is included in the calculation of the size. The X-Binary-Element-Type header specifies the type of binary data in the octets, using the same descriptive phrases as in _array_structure.encoding_type. The default value is 'unsigned 32-bit integer'. An MD5 message digest may, optionally, be used. The 'RSA Data Security, Inc. MD5 Message-Digest Algorithm' should be used. No portion of the header is included in the calculation of the message digest. If the Transfer Encoding is 'X-BASE8', 'X-BASE10' or 'X-BASE16', the data are presented as octal, decimal or hexadecimal data organized into lines or words. Each word is created by composing octets of data in fixed groups of 2, 3, 4, 6 or 8 octets, either in the order ...4321 ('big- endian') or 1234... ('little-endian'). If there are fewer than the specified number of octets to fill the last word, then the missing octets are presented as '==' for each missing octet. Exactly two equal signs are used for each missing octet even for octal and decimal encoding. The format of lines is: rnd xxxxxx xxxxxx xxxxxx where r is 'H', 'O' or 'D' for hexadecimal, octal or decimal, n is the number of octets per word and d is '<' or '>' for the '...4321' and '1234...' octet orderings, respectively. The '==' padding for the last word should be on the appropriate side to correspond to the missing octets, e.g. H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000 or H3> FF0700 00==== For these hexadecimal, octal and decimal formats only, comments beginning with '#' are permitted to improve readability. BASE64 encoding follows MIME conventions. Octets are in groups of three: c1, c2, c3. The resulting 24 bits are broken into four six-bit quantities, starting with the high-order six bits (c1 >> 2) of the first octet, then the low-order two bits of the first octet followed by the high-order four bits of the second octet [(c1 & 3)<<4 | (c2>>4)], then the bottom four bits of the second octet followed by the high-order two bits of the last octet [(c2 & 15)<<2 | (c3>>6)], then the bottom six bits of the last octet (c3 & 63). Each of these four quantities is translated into an ASCII character using the mapping: 1 2 3 4 5 6 0123456789012345678901234567890123456789012345678901234567890123 | | | | | | | ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/ with short groups of octets padded on the right with one '=' if c3 is missing, and with '==' if both c2 and c3 are missing. QUOTED-PRINTABLE encoding also follows MIME conventions, copying octets without translation if their ASCII values are 32...38, 42, 48...57, 59, 60, 62, 64...126 and the octet is not a ';' in column 1. All other characters are translated to =nn, where nn is the hexadecimal encoding of the octet. All lines are 'wrapped' with a terminating '=' (i.e. the MIME conventions for an implicit line terminator are never used). ; _item.name '_array_data.data' _item.category_id array_data _item.mandatory_code yes _item_type.code binary save_ ###################### # ARRAY_ELEMENT_SIZE # ###################### save_ARRAY_ELEMENT_SIZE _category.description ; Data items in the ARRAY_ELEMENT_SIZE category record the physical size of array elements along each array dimension. ; _category.id array_element_size _category.mandatory_code no loop_ _category_key.name '_array_element_size.array_id' '_array_element_size.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - a regular 2D array with a uniform element dimension of 1220 nanometres. ; ; loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size image_1 1 1.22e-6 image_1 2 1.22e-6 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_element_size.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_element_size.array_id' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.index _item_description.description ; This item is a pointer to _array_structure_list.index in the ARRAY_STRUCTURE_LIST category. ; _item.name '_array_element_size.index' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.size _item_description.description ; The size in metres of an image element in this dimension. This supposes that the elements are arranged on a regular grid. ; _item.name '_array_element_size.size' _item.category_id array_element_size _item.mandatory_code yes _item_type.code float _item_units.code 'metres' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ ##################### # ARRAY_INTENSITIES # ##################### save_ARRAY_INTENSITIES _category.description ; Data items in the ARRAY_INTENSITIES category record the information required to recover the intensity data from the set of data values stored in the ARRAY_DATA category. The detector may have a complex relationship between the raw intensity values and the number of incident photons. In most cases, the number stored in the final array will have a simple linear relationship to the actual number of incident photons, given by _array_intensities.gain. If raw, uncorrected values are presented (e.g. for calibration experiments), the value of _array_intensities.linearity will be 'raw' and _array_intensities.gain will not be used. ; _category.id array_intensities _category.mandatory_code no loop_ _category_key.name '_array_intensities.array_id' '_array_intensities.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 ; ; loop_ _array_intensities.array_id _array_intensities.linearity _array_intensities.gain _array_intensities.overload _array_intensities.undefined_value image_1 linear 1.2 655535 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_intensities.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_intensities.array_id' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code save_ save__array_intensities.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_array_intensities.binary_id' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code int save_ save__array_intensities.gain _item_description.description ; Detector 'gain'. The factor by which linearized intensity count values should be divided to produce true photon counts. ; _item.name '_array_intensities.gain' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain_esd' 'associated_value' save_ save__array_intensities.gain_esd _item_description.description ; The estimated standard deviation in detector 'gain'. ; _item.name '_array_intensities.gain_esd' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain' 'associated_esd' save_ save__array_intensities.linearity _item_description.description ; The intensity linearity scaling method used to convert from the raw intensity to the stored element value: 'linear' is linear. 'offset' means that the value defined by _array_intensities.offset should be added to each element value. 'scaling' means that the value defined by _array_intensities.scaling should be multiplied with each element value. 'scaling_offset' is the combination of the two previous cases, with the scale factor applied before the offset value. 'sqrt_scaled' means that the square root of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and squaring the result. 'logarithmic_scaled' means that the logarithm base 10 of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and calculating 10 to the power of this number. 'raw' means that the data are a set of raw values straight from the detector. ; _item.name '_array_intensities.linearity' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'linear' . 'offset' ; The value defined by _array_intensities.offset should be added to each element value. ; 'scaling' ; The value defined by _array_intensities.scaling should be multiplied with each element value. ; 'scaling_offset' ; The combination of the scaling and offset with the scale factor applied before the offset value. ; 'sqrt_scaled' ; The square root of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and squaring the result. ; 'logarithmic_scaled' ; The logarithm base 10 of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and calculating 10 to the power of this number. ; 'raw' ; The array consists of raw values to which no corrections have been applied. While the handling of the data is similar to that given for 'linear' data with no offset, the meaning of the data differs in that the number of incident photons is not necessarily linearly related to the number of counts reported. This value is intended for use either in calibration experiments or to allow for handling more complex data-fitting algorithms than are allowed for by this data item. ; save_ save__array_intensities.offset _item_description.description ; Offset value to add to array element values in the manner described by the item _array_intensities.linearity. ; _item.name '_array_intensities.offset' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.overload _item_description.description ; The saturation intensity level for this data array. ; _item.name '_array_intensities.overload' _item.category_id array_intensities _item.mandatory_code no _item_type.code float _item_units.code 'counts' save_ save__array_intensities.scaling _item_description.description ; Multiplicative scaling value to be applied to array data in the manner described by item _array_intensities.linearity. ; _item.name '_array_intensities.scaling' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.undefined_value _item_description.description ; A value to be substituted for undefined values in the data array. ; _item.name '_array_intensities.undefined_value' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ ################### # ARRAY_STRUCTURE # ################### save_ARRAY_STRUCTURE _category.description ; Data items in the ARRAY_STRUCTURE category record the organization and encoding of array data in the ARRAY_DATA category. ; _category.id array_structure _category.mandatory_code no _category_key.name '_array_structure.id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order image_1 "unsigned 16-bit integer" none little_endian ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure.byte_order _item_description.description ; The order of bytes for integer values which require more than 1 byte. (IBM PCs and compatibles, and Dec VAXs use low-byte-first ordered integers, whereas Hewlett Packard 700 series, Sun-4 and Silicon Graphics use high-byte-first ordered integers. Dec Alphas can produce/use either depending on a compiler switch.) ; _item.name '_array_structure.byte_order' _item.category_id array_structure _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'big_endian' ; The first byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; 'little_endian' ; The last byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; save_ save__array_structure.compression_type _item_description.description ; Type of data-compression method used to compress the array data. ; _item.name '_array_structure.compression_type' _item.category_id array_structure _item.mandatory_code no _item_type.code code _item_default.value 'none' loop_ _item_enumeration.value _item_enumeration.detail 'none' ; Data are stored in normal format as defined by _array_structure.encoding_type and _array_structure.byte_order. ; 'packed' ; Using the 'packed' compression scheme, a CCP4-style packing (International Tables for Crystallography Volume G, Section 5.6.3.2) ; 'canonical' ; Using the 'canonical' compression scheme (International Tables for Crystallography Volume G, Section 5.6.3.1) ; save_ save__array_structure.encoding_type _item_description.description ; Data encoding of a single element of array data. In several cases, the IEEE format is referenced. See IEEE Standard 754-1985 (IEEE, 1985). Ref: IEEE (1985). IEEE Standard for Binary Floating-Point Arithmetic. ANSI/IEEE Std 754-1985. New York: Institute of Electrical and Electronics Engineers. ; _item.name '_array_structure.encoding_type' _item.category_id array_structure _item.mandatory_code yes _item_type.code uline loop_ _item_enumeration.value 'unsigned 8-bit integer' 'signed 8-bit integer' 'unsigned 16-bit integer' 'signed 16-bit integer' 'unsigned 32-bit integer' 'signed 32-bit integer' 'signed 32-bit real IEEE' 'signed 64-bit real IEEE' 'signed 32-bit complex IEEE' save_ save__array_structure.id _item_description.description ; The value of _array_structure.id must uniquely identify each item of array data. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure.id' array_structure yes '_array_data.array_id' array_data yes '_array_structure_list.array_id' array_structure_list yes '_array_intensities.array_id' array_intensities yes '_diffrn_data_frame.array_id' diffrn_data_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_data.array_id' '_array_structure.id' '_array_structure_list.array_id' '_array_structure.id' '_array_intensities.array_id' '_array_structure.id' '_diffrn_data_frame.array_id' '_array_structure.id' save_ ######################## # ARRAY_STRUCTURE_LIST # ######################## save_ARRAY_STRUCTURE_LIST _category.description ; Data items in the ARRAY_STRUCTURE_LIST category record the size and organization of each array dimension. The relationship to physical axes may be given. ; _category.id array_structure_list _category.mandatory_code no loop_ _category_key.name '_array_structure_list.array_id' '_array_structure_list.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - An image array of 1300 x 1200 elements. The raster order of the image is left to right (increasing) in the first dimension and bottom to top (decreasing) in the second dimension. ; ; loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id image_1 1 1300 1 increasing ELEMENT_X image_1 2 1200 2 decreasing ELEMENY_Y ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure_list.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_structure_list.array_id' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code code save_ save__array_structure_list.axis_set_id _item_description.description ; This is a descriptor for the physical axis or set of axes corresponding to an array index. This data item is related to the axes of the detector itself given in DIFFRN_DETECTOR_AXIS, but usually differs in that the axes in this category are the axes of the coordinate system of reported data points, while the axes in DIFFRN_DETECTOR_AXIS are the physical axes of the detector describing the 'poise' of the detector as an overall physical object. If there is only one axis in the set, the identifier of that axis should be used as the identifier of the set. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.axis_set_id' array_structure_list yes '_array_structure_list_axis.axis_set_id' array_structure_list_axis implicit _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_structure_list_axis.axis_set_id' '_array_structure_list.axis_set_id' save_ save__array_structure_list.dimension _item_description.description ; The number of elements stored in the array structure in this dimension. ; _item.name '_array_structure_list.dimension' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.direction _item_description.description ; Identifies the direction in which this array index changes. ; _item.name '_array_structure_list.direction' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_enumeration.value _item_enumeration.detail 'increasing' ; Indicates the index changes from 1 to the maximum dimension ; 'decreasing' ; Indicates the index changes from the maximum dimension to 1 ; save_ save__array_structure_list.index _item_description.description ; Identifies the one-based index of the row or column in the array structure. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.index' array_structure_list yes '_array_structure_list.precedence' array_structure_list yes '_array_element_size.index' array_element_size yes _item_type.code int loop_ _item_linked.child_name _item_linked.parent_name '_array_element_size.index' '_array_structure_list.index' loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.precedence _item_description.description ; Identifies the rank order in which this array index changes with respect to other array indices. The precedence of 1 indicates the index which changes fastest. ; _item.name '_array_structure_list.precedence' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ ############################# # ARRAY_STRUCTURE_LIST_AXIS # ############################# save_ARRAY_STRUCTURE_LIST_AXIS _category.description ; Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe the physical settings of sets of axes for the centres of pixels that correspond to data points described in the ARRAY_STRUCTURE_LIST category. In the simplest cases, the physical increments of a single axis correspond to the increments of a single array index. More complex organizations, e.g. spiral scans, may require coupled motions along multiple axes. Note that a spiral scan uses two coupled axes: one for the angular direction and one for the radial direction. This differs from a cylindrical scan for which the two axes are not coupled into one set. ; _category.id array_structure_list_axis _category.mandatory_code no loop_ _category_key.name '_array_structure_list_axis.axis_set_id' '_array_structure_list_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' save_ save__array_structure_list_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes in the set of axes for which settings are being specified. Multiple axes may be specified for the same value of _array_structure_list_axis.axis_set_id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_array_structure_list_axis.axis_id' _item.category_id array_structure_list_axis _item.mandatory_code yes _item_type.code code save_ save__array_structure_list_axis.axis_set_id _item_description.description ; The value of this data item is the identifier of the set of axes for which axis settings are being specified. Multiple axes may be specified for the same value of _array_structure_list_axis.axis_set_id. This item is a pointer to _array_structure_list.axis_set_id in the ARRAY_STRUCTURE_LIST category. If this item is not specified, it defaults to the corresponding axis identifier. ; _item.name '_array_structure_list_axis.axis_set_id' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_type.code code save_ save__array_structure_list_axis.angle _item_description.description ; The setting of the specified axis in degrees for the first data point of the array index with the corresponding value of _array_structure_list.axis_set_id. If the index is specified as 'increasing', this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing', this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.angle' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.angle_increment _item_description.description ; The pixel-centre-to-pixel-centre increment in the angular setting of the specified axis in degrees. This is not meaningful in the case of 'constant velocity' spiral scans and should not be specified for this case. See _array_structure_list_axis.angular_pitch. ; _item.name '_array_structure_list_axis.angle_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for the first data point of the array index with the corresponding value of _array_structure_list.axis_set_id. If the index is specified as 'increasing', this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing', this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.displacement' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.displacement_increment _item_description.description ; The pixel-centre-to-pixel-centre increment for the displacement setting of the specified axis in millimetres. ; _item.name '_array_structure_list_axis.displacement_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.angular_pitch _item_description.description ; The pixel-centre-to-pixel-centre distance for a one-step change in the setting of the specified axis in millimetres. This is meaningful only for 'constant velocity' spiral scans or for uncoupled angular scans at a constant radius (cylindrical scans) and should not be specified for cases in which the angle between pixels (rather than the distance between pixels) is uniform. See _array_structure_list_axis.angle_increment. ; _item.name '_array_structure_list_axis.angular_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.radial_pitch _item_description.description ; The radial distance from one 'cylinder' of pixels to the next in millimetres. If the scan is a 'constant velocity' scan with differing angular displacements between pixels, the value of this item may differ significantly from the value of _array_structure_list_axis.displacement_increment. ; _item.name '_array_structure_list_axis.radial_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ ######## # AXIS # ######## save_AXIS _category.description ; Data items in the AXIS category record the information required to describe the various goniometer, detector, source and other axes needed to specify a data collection. The location of each axis is specified by two vectors: the axis itself, given as a unit vector, and an offset to the base of the unit vector. These vectors are referenced to a right-handed laboratory coordinate system with its origin in the sample or specimen: | Y (to complete right-handed system) | | | | | |________________X / principal goniometer axis / / / / /Z (to source) Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from the sample or specimen along the principal axis of the goniometer. Axis 2 (Y): The Y-axis completes an orthogonal right-handed system defined by the X-axis and the Z-axis (see below). Axis 3 (Z): The Z-axis is derived from the source axis which goes from the sample to the source. The Z-axis is the component of the source axis in the direction of the source orthogonal to the X-axis in the plane defined by the X-axis and the source axis. These axes are based on the goniometer, not on the orientation of the detector, gravity etc. The vectors necessary to specify all other axes are given by sets of three components in the order (X, Y, Z). If the axis involved is a rotation axis, it is right-handed, i.e. as one views the object to be rotated from the origin (the tail) of the unit vector, the rotation is clockwise. If a translation axis is specified, the direction of the unit vector specifies the sense of positive translation. Note: This choice of coordinate system is similar to but significantly different from the choice in MOSFLM (Leslie & Powell, 2004). In MOSFLM, X is along the X-ray beam (the CBF/imgCIF Z axis) and Z is along the rotation axis. All rotations are given in degrees and all translations are given in mm. Axes may be dependent on one another. The X-axis is the only goniometer axis the direction of which is strictly connected to the hardware. All other axes are specified by the positions they would assume when the axes upon which they depend are at their zero points. When specifying detector axes, the axis is given to the beam centre. The location of the beam centre on the detector should be given in the DIFFRN_DETECTOR category in distortion-corrected millimetres from the (0,0) corner of the detector. It should be noted that many different origins arise in the definition of an experiment. In particular, as noted above, it is necessary to specify the location of the beam centre on the detector in terms of the origin of the detector, which is, of course, not coincident with the centre of the sample. Ref: Leslie, A. G. W. & Powell, H. (2004). MOSFLM v6.11. MRC Laboratory of Molecular Biology, Hills Road, Cambridge, England. http://www.CCP4.ac.uk/dist/x-windows/Mosflm/. ; _category.id axis _category.mandatory_code no loop_ _category_key.name '_axis.id' '_axis.equipment' loop_ _category_group.id 'inclusive_group' 'axis_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 This example shows the axis specification of the axes of a kappa- geometry goniometer [see Stout, G. H. & Jensen, L. H. (1989). X-ray structure determination. A practical guide, 2nd ed. p. 134. New York: Wiley Interscience]. There are three axes specified, and no offsets. The outermost axis, omega, is pointed along the X axis. The next innermost axis, kappa, is at a 50 degree angle to the X axis, pointed away from the source. The innermost axis, phi, aligns with the X axis when omega and phi are at their zero points. If T-omega, T-kappa and T-phi are the transformation matrices derived from the axis settings, the complete transformation would be: x' = (T-omega) (T-kappa) (T-phi) x ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] omega rotation goniometer . 1 0 0 kappa rotation goniometer omega -.64279 0 -.76604 phi rotation goniometer kappa 1 0 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 This example show the axis specification of the axes of a detector, source and gravity. The order has been changed as a reminder that the ordering of presentation of tokens is not significant. The centre of rotation of the detector has been taken to be 68 millimetres in the direction away from the source. ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] source . source . 0 0 1 . . . gravity . gravity . 0 -1 0 . . . tranz translation detector rotz 0 0 1 0 0 -68 twotheta rotation detector . 1 0 0 . . . roty rotation detector twotheta 0 1 0 0 0 -68 rotz rotation detector roty 0 0 1 0 0 -68 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__axis.depends_on _item_description.description ; The value of _axis.depends_on specifies the next outermost axis upon which this axis depends. This item is a pointer to _axis.id in the same category. ; _item.name '_axis.depends_on' _item.category_id axis _item.mandatory_code no save_ save__axis.equipment _item_description.description ; The value of _axis.equipment specifies the type of equipment using the axis: 'goniometer', 'detector', 'gravity', 'source' or 'general'. ; _item.name '_axis.equipment' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail goniometer 'equipment used to orient or position samples' detector 'equipment used to detect reflections' general 'equipment used for general purposes' gravity 'axis specifying the downward direction' source 'axis specifying the direction sample to source' save_ save__axis.offset[1] _item_description.description ; The [1] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[2] _item_description.description ; The [2] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[3] _item_description.description ; The [3] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.id _item_description.description ; The value of _axis.id must uniquely identify each axis relevant to the experiment. Note that multiple pieces of equipment may share the same axis (e.g. a twotheta arm), so the category key for AXIS also includes the equipment. ; loop_ _item.name _item.category_id _item.mandatory_code '_axis.id' axis yes '_array_structure_list_axis.axis_id' array_structure_list_axis yes '_diffrn_detector_axis.axis_id' diffrn_detector_axis yes '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes '_diffrn_scan_axis.axis_id' diffrn_scan_axis yes '_diffrn_scan_frame_axis.axis_id' diffrn_scan_frame_axis yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_axis.depends_on' '_axis.id' '_array_structure_list_axis.axis_id' '_axis.id' '_diffrn_detector_axis.axis_id' '_axis.id' '_diffrn_measurement_axis.axis_id' '_axis.id' '_diffrn_scan_axis.axis_id' '_axis.id' '_diffrn_scan_frame_axis.axis_id' '_axis.id' save_ save__axis.type _item_description.description ; The value of _axis.type specifies the type of axis: 'rotation' or 'translation' (or 'general' when the type is not relevant, as for gravity). ; _item.name '_axis.type' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail rotation 'right-handed axis of rotation' translation 'translation in the direction of the axis' general 'axis for which the type is not relevant' save_ save__axis.vector[1] _item_description.description ; The [1] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[2] _item_description.description ; The [2] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[3] _item_description.description ; The [3] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ ##################### # DIFFRN_DATA_FRAME # ##################### save_DIFFRN_DATA_FRAME _category.description ; Data items in the DIFFRN_DATA_FRAME category record the details about each frame of data. The items in this category were previously in a DIFFRN_FRAME_DATA category, which is now deprecated. The items from the old category are provided as aliases but should not be used for new work. ; _category.id diffrn_data_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_data_frame.id' '_diffrn_data_frame.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - a frame containing data from four frame elements. Each frame element has a common array configuration 'array_1' described in ARRAY_STRUCTURE and related categories. The data for each detector element are stored in four groups of binary data in the ARRAY_DATA category, linked by the array_id and binary_id. ; ; loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id frame_1 d1_ccd_1 array_1 1 frame_1 d1_ccd_2 array_1 2 frame_1 d1_ccd_3 array_1 3 frame_1 d1_ccd_4 array_1 4 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_data_frame.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_diffrn_data_frame.array_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.array_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_diffrn_data_frame.binary_id' _item.category_id diffrn_data_frame _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_frame_data.binary_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code int save_ save__diffrn_data_frame.detector_element_id _item_description.description ; This item is a pointer to _diffrn_detector_element.id in the DIFFRN_DETECTOR_ELEMENT category. ; _item.name '_diffrn_data_frame.detector_element_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.detector_element_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.id _item_description.description ; The value of _diffrn_data_frame.id must uniquely identify each complete frame of data. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_data_frame.id' diffrn_data_frame yes '_diffrn_refln.frame_id' diffrn_refln yes '_diffrn_scan.frame_id_start' diffrn_scan yes '_diffrn_scan.frame_id_end' diffrn_scan yes '_diffrn_scan_frame.frame_id' diffrn_scan_frame yes '_diffrn_scan_frame_axis.frame_id' diffrn_scan_frame_axis yes _item_aliases.alias_name '_diffrn_frame_data.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_refln.frame_id' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_start' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_end' '_diffrn_data_frame.id' '_diffrn_scan_frame.frame_id' '_diffrn_data_frame.id' '_diffrn_scan_frame_axis.frame_id' '_diffrn_data_frame.id' save_ ########################################################################## # The following is a restatement of the mmCIF DIFFRN_DETECTOR, # # DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for # # the CBF/imgCIF extensions # ########################################################################## ################### # DIFFRN_DETECTOR # ################### save_DIFFRN_DETECTOR _category.description ; Data items in the DIFFRN_DETECTOR category describe the detector used to measure the scattered radiation, including any analyser and post-sample collimation. ; _category.id diffrn_detector _category.mandatory_code no loop_ _category_key.name '_diffrn_detector.diffrn_id' '_diffrn_detector.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _diffrn_detector.diffrn_id 'd1' _diffrn_detector.detector 'multiwire' _diffrn_detector.type 'Siemens' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector.details _item_description.description ; A description of special aspects of the radiation detector. ; _item.name '_diffrn_detector.details' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'slow mode' save_ save__diffrn_detector.detector _item_description.description ; The general class of the radiation detector. ; _item.name '_diffrn_detector.detector' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector' cifdic.c91 1.0 '_diffrn_detector' cif_core.dic 2.0 _item_type.code text loop_ _item_examples.case 'photographic film' 'scintillation counter' 'CCD plate' 'BF~3~ counter' save_ save__diffrn_detector.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. The value of _diffrn.id uniquely defines a set of diffraction data. ; _item.name '_diffrn_detector.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector.dtime _item_description.description ; The deadtime in microseconds of the detector(s) used to measure the diffraction intensities. ; _item.name '_diffrn_detector.dtime' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector_dtime' cifdic.c91 1.0 '_diffrn_detector_dtime' cif_core.dic 2.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code microseconds save_ save__diffrn_detector.id _item_description.description ; The value of _diffrn_detector.id must uniquely identify each detector used to collect each diffraction data set. If the value of _diffrn_detector.id is not given, it is implicitly equal to the value of _diffrn_detector.diffrn_id. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector.id' diffrn_detector implicit '_diffrn_detector_axis.detector_id' diffrn_detector_axis yes loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_detector_axis.detector_id' '_diffrn_detector.id' _item_type.code code save_ save__diffrn_detector.number_of_axes _item_description.description ; The value of _diffrn_detector.number_of_axes gives the number of axes of the positioner for the detector identified by _diffrn_detector.id. The word 'positioner' is a general term used in instrumentation design for devices that are used to change the positions of portions of apparatus by linear translation, rotation or combinations of such motions. Axes which are used to provide a coordinate system for the face of an area detetctor should not be counted for this data item. The description of each axis should be provided by entries in DIFFRN_DETECTOR_AXIS. ; _item.name '_diffrn_detector.number_of_axes' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_detector.type _item_description.description ; The make, model or name of the detector device used. ; _item.name '_diffrn_detector.type' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ ######################## # DIFFRN_DETECTOR_AXIS # ######################## save_DIFFRN_DETECTOR_AXIS _category.description ; Data items in the DIFFRN_DETECTOR_AXIS category associate axes with detectors. ; _category.id diffrn_detector_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_axis.detector_id' '_diffrn_detector_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_detector_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_detector_axis.axis_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_axis.detector_id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. This item was previously named _diffrn_detector_axis.id, which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_detector_axis.detector_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_aliases.alias_name '_diffrn_detector_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ ########################### # DIFFRN_DETECTOR_ELEMENT # ########################### save_DIFFRN_DETECTOR_ELEMENT _category.description ; Data items in the DIFFRN_DETECTOR_ELEMENT category record the details about spatial layout and other characteristics of each element of a detector which may have multiple elements. In most cases, giving more detailed information in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS is preferable to simply providing the centre of the detector element. ; _category.id diffrn_detector_element _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_element.id' '_diffrn_detector_element.detector_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Detector d1 is composed of four CCD detector elements, each 200 mm by 200 mm, arranged in a square, in the pattern 1 2 * 3 4 Note that the beam centre is slightly displaced from each of the detector elements, just beyond the lower right corner of 1, the lower left corner of 2, the upper right corner of 3 and the upper left corner of 4. ; ; loop_ _diffrn_detector_element.detector_id _diffrn_detector_element.id _diffrn_detector_element.center[1] _diffrn_detector_element.center[2] d1 d1_ccd_1 201.5 -1.5 d1 d1_ccd_2 -1.8 -1.5 d1 d1_ccd_3 201.6 201.4 d1 d1_ccd_4 -1.7 201.5 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector_element.center[1] _item_description.description ; The value of _diffrn_detector_element.center[1] is the X component of the distortion-corrected beam centre in millimetres from the (0, 0) (lower-left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. ; _item.name '_diffrn_detector_element.center[1]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.center[2] _item_description.description ; The value of _diffrn_detector_element.center[2] is the Y component of the distortion-corrected beam centre in millimetres from the (0, 0) (lower-left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. ; _item.name '_diffrn_detector_element.center[2]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.id _item_description.description ; The value of _diffrn_detector_element.id must uniquely identify each element of a detector. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector_element.id' diffrn_detector_element yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.detector_element_id' '_diffrn_detector_element.id' save_ save__diffrn_detector_element.detector_id _item_description.description ; This item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. ; _item.name '_diffrn_detector_element.detector_id' _item.category_id diffrn_detector_element _item.mandatory_code yes _item_type.code code save_ ######################## ## DIFFRN_MEASUREMENT ## ######################## save_DIFFRN_MEASUREMENT _category.description ; Data items in the DIFFRN_MEASUREMENT category record details about the device used to orient and/or position the crystal during data measurement and the manner in which the diffraction data were measured. ; _category.id diffrn_measurement _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement.device' '_diffrn_measurement.diffrn_id' '_diffrn_measurement.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _diffrn_measurement.diffrn_id 'd1' _diffrn_measurement.device '3-circle camera' _diffrn_measurement.device_type 'Supper model x' _diffrn_measurement.device_details 'none' _diffrn_measurement.method 'omega scan' _diffrn_measurement.details ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _diffrn_measurement.diffrn_id 's1' _diffrn_measurement.device_type 'Philips PW1100/20 diffractometer' _diffrn_measurement.method 'theta/2theta (\q/2\q)' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_measurement.device _item_description.description ; The general class of goniometer or device used to support and orient the specimen. If the value of _diffrn_measurement.device is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id. Either _diffrn_measurement.device or _diffrn_measurement.id may be used to link to other categories. If the experimental setup admits multiple devices, then _diffrn_measurement.id is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.device' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_device' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement.device' _item_aliases.alias_name '_diffrn_measurement_device' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '3-circle camera' '4-circle camera' 'kappa-geometry camera' 'oscillation camera' 'precession camera' save_ save__diffrn_measurement.device_details _item_description.description ; A description of special aspects of the device used to measure the diffraction intensities. ; _item.name '_diffrn_measurement.device_details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; commercial goniometer modified locally to allow for 90\% \t arc ; save_ save__diffrn_measurement.device_type _item_description.description ; The make, model or name of the measurement device (goniometer) used. ; _item.name '_diffrn_measurement.device_type' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Supper model q' 'Huber model r' 'Enraf-Nonius model s' 'home-made' save_ save__diffrn_measurement.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_measurement.diffrn_id' _item.mandatory_code yes save_ save__diffrn_measurement.details _item_description.description ; A description of special aspects of the intensity measurement. ; _item.name '_diffrn_measurement.details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; save_ save__diffrn_measurement.id _item_description.description ; The value of _diffrn_measurement.id must uniquely identify the set of mechanical characteristics of the device used to orient and/or position the sample used during the collection of each diffraction data set. If the value of _diffrn_measurement.id is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id. Either _diffrn_measurement.device or _diffrn_measurement.id may be used to link to other categories. If the experimental setup admits multiple devices, then _diffrn_measurement.id is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.id' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_id' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement.id' _item_type.code code save_ save__diffrn_measurement.method _item_description.description ; Method used to measure intensities. ; _item.name '_diffrn_measurement.method' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_method' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'profile data from theta/2theta (\q/2\q) scans' save_ save__diffrn_measurement.number_of_axes _item_description.description ; The value of _diffrn_measurement.number_of_axes gives the number of axes of the positioner for the goniometer or other sample orientation or positioning device identified by _diffrn_measurement.id. The description of the axes should be provided by entries in DIFFRN_MEASUREMENT_AXIS. ; _item.name '_diffrn_measurement.number_of_axes' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_measurement.specimen_support _item_description.description ; The physical device used to support the crystal during data collection. ; _item.name '_diffrn_measurement.specimen_support' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_specimen_support' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'glass capillary' 'quartz capillary' 'fiber' 'metal loop' save_ ########################### # DIFFRN_MEASUREMENT_AXIS # ########################### save_DIFFRN_MEASUREMENT_AXIS _category.description ; Data items in the DIFFRN_MEASUREMENT_AXIS category associate axes with goniometers. ; _category.id diffrn_measurement_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_measurement_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_measurement_axis.axis_id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.measurement_device _item_description.description ; This data item is a pointer to _diffrn_measurement.device in the DIFFRN_MEASUREMENT category. ; _item.name '_diffrn_measurement_axis.measurement_device' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit _item_type.code text save_ save__diffrn_measurement_axis.measurement_id _item_description.description ; This data item is a pointer to _diffrn_measurement.id in the DIFFRN_MEASUREMENT category. This item was previously named _diffrn_measurement_axis.id, which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_measurement_axis.measurement_id' _item.category_id diffrn_measurement_axis _item_aliases.alias_name '_diffrn_measurement_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item.mandatory_code implicit _item_type.code code save_ #################### # DIFFRN_RADIATION # #################### save_DIFFRN_RADIATION _category.description ; Data items in the DIFFRN_RADIATION category describe the radiation used for measuring diffraction intensities, its collimation and monochromatization before the sample. Post-sample treatment of the beam is described by data items in the DIFFRN_DETECTOR category. ; _category.id diffrn_radiation _category.mandatory_code no _category_key.name '_diffrn_radiation.diffrn_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _diffrn_radiation.diffrn_id 'set1' _diffrn_radiation.collimation '0.3 mm double pinhole' _diffrn_radiation.monochromator 'graphite' _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.wavelength_id 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _diffrn_radiation.wavelength_id 1 _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.monochromator 'graphite' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_radiation.collimation _item_description.description ; The collimation or focusing applied to the radiation. ; _item.name '_diffrn_radiation.collimation' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_collimation' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '0.3 mm double-pinhole' '0.5 mm' 'focusing mirrors' save_ save__diffrn_radiation.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_radiation.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_radiation.div_x_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory X axis (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the standard uncertainty (e.s.d.) of the directions of photons in the XZ plane around the mean source beam direction. Note that for some synchrotrons this value is specified in milliradians, in which case a conversion is needed. To convert a value in milliradians to a value in degrees, multiply by 0.180 and divide by pi. ; _item.name '_diffrn_radiation.div_x_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.div_y_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory Y axis (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the standard uncertainty (e.s.d.) of the directions of photons in the YZ plane around the mean source beam direction. Note that for some synchrotrons this value is specified in milliradians, in which case a conversion is needed. To convert a value in milliradians to a value in degrees, multiply by 0.180 and divide by pi. ; _item.name '_diffrn_radiation.div_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.div_x_y_source _item_description.description ; Beam crossfire correlation in degrees squared between the crossfire laboratory X-axis component and the crossfire laboratory Y-axis component (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the mean of the products of the deviations of the direction of each photon in XZ plane times the deviations of the direction of the same photon in the YZ plane around the mean source beam direction. This will be zero for uncorrelated crossfire. Note that for some synchrotrons, this value is specified in milliradians squared, in which case a conversion is needed. To convert a value in milliradians squared to a value in degrees squared, multiply by 0.180**2 and divide by pi**2. ; _item.name '_diffrn_radiation.div_x_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees_squared _item_default.value 0.0 save_ save__diffrn_radiation.filter_edge _item_description.description ; Absorption edge in angstroms of the radiation filter used. ; _item.name '_diffrn_radiation.filter_edge' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_filter_edge' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__diffrn_radiation.inhomogeneity _item_description.description ; Half-width in millimetres of the incident beam in the direction perpendicular to the diffraction plane. ; _item.name '_diffrn_radiation.inhomogeneity' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_inhomogeneity' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code millimetres save_ save__diffrn_radiation.monochromator _item_description.description ; The method used to obtain monochromatic radiation. If a monochromator crystal is used, the material and the indices of the Bragg reflection are specified. ; _item.name '_diffrn_radiation.monochromator' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_monochromator' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Zr filter' 'Ge 220' 'none' 'equatorial mounted graphite' save_ save__diffrn_radiation.polarisn_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the perpendicular component of the polarization and the diffraction plane. See _diffrn_radiation_polarisn_ratio. ; _item.name '_diffrn_radiation.polarisn_norm' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_norm' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.polarisn_ratio _item_description.description ; Polarization ratio of the diffraction beam incident on the crystal. This is the ratio of the perpendicularly polarized to the parallel polarized component of the radiation. The perpendicular component forms an angle of _diffrn_radiation.polarisn_norm to the normal to the diffraction plane of the sample (i.e. the plane containing the incident and reflected beams). ; _item.name '_diffrn_radiation.polarisn_ratio' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_ratio' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__diffrn_radiation.polarizn_source_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the normal to the polarization plane and the laboratory Y axis as defined in the AXIS category. Note that this is the angle of polarization of the source photons, either directly from a synchrotron beamline or from a monchromator. This differs from the value of _diffrn_radiation.polarisn_norm in that _diffrn_radiation.polarisn_norm refers to polarization relative to the diffraction plane rather than to the laboratory axis system. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane should be taken as the XZ plane and the angle as 0. See _diffrn_radiation.polarizn_source_ratio. ; _item.name '_diffrn_radiation.polarizn_source_norm' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.polarizn_source_ratio _item_description.description ; (Ip-In)/(Ip+In), where Ip is the intensity (amplitude squared) of the electric vector in the plane of polarization and In is the intensity (amplitude squared) of the electric vector in the plane of the normal to the plane of polarization. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane is to be taken as the XZ plane and the normal is parallel to the Y axis. Thus, if there was complete polarization in the plane of polarization, the value of _diffrn_radiation.polarizn_source_ratio would be 1, and for an unpolarized beam _diffrn_radiation.polarizn_source_ratio would have a value of 0. If the X axis has been chosen to lie in the plane of polarization, this definition will agree with the definition of 'MONOCHROMATOR' in the Denzo glossary, and values of near 1 should be expected for a bending-magnet source. However, if the X axis were perpendicular to the polarization plane (not a common choice), then the Denzo value would be the negative of _diffrn_radiation.polarizn_source_ratio. See http://www.hkl-xray.com for information on Denzo and Otwinowski & Minor (1997). This differs both in the choice of ratio and choice of orientation from _diffrn_radiation.polarisn_ratio, which, unlike _diffrn_radiation.polarizn_source_ratio, is unbounded. Reference: Otwinowski, Z. & Minor, W. (1997). 'Processing of X-ray diffraction data collected in oscillation mode.' Methods Enzymol. 276, 307-326. ; _item.name '_diffrn_radiation.polarizn_source_ratio' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 -1.0 -1.0 -1.0 _item_type.code float save_ save__diffrn_radiation.probe _item_description.description ; Name of the type of radiation used. It is strongly recommended that this be given so that the probe radiation is clearly specified. ; _item.name '_diffrn_radiation.probe' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_probe' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value 'x-ray' 'neutron' 'electron' 'gamma' save_ save__diffrn_radiation.type _item_description.description ; The nature of the radiation. This is typically a description of the X-ray wavelength in Siegbahn notation. ; _item.name '_diffrn_radiation.type' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'CuK\a' 'Cu K\a~1~' 'Cu K-L~2,3~' 'white-beam' save_ save__diffrn_radiation.xray_symbol _item_description.description ; The IUPAC symbol for the X-ray wavelength for the probe radiation. ; _item.name '_diffrn_radiation.xray_symbol' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_xray_symbol' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value _item_enumeration.detail 'K-L~3~' 'K\a~1~ in older Siegbahn notation' 'K-L~2~' 'K\a~2~ in older Siegbahn notation' 'K-M~3~' 'K\b~1~ in older Siegbahn notation' 'K-L~2,3~' 'use where K-L~3~ and K-L~2~ are not resolved' save_ save__diffrn_radiation.wavelength_id _item_description.description ; This data item is a pointer to _diffrn_radiation_wavelength.id in the DIFFRN_RADIATION_WAVELENGTH category. ; _item.name '_diffrn_radiation.wavelength_id' _item.category_id diffrn_radiation _item.mandatory_code yes _item_type.code code save_ ################ # DIFFRN_REFLN # ################ save_DIFFRN_REFLN _category.description ; This category redefinition has been added to extend the key of the standard DIFFRN_REFLN category. ; _category.id diffrn_refln _category.mandatory_code no _category_key.name '_diffrn_refln.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_refln.frame_id _item_description.description ; This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_refln.frame_id' _item.category_id diffrn_refln _item.mandatory_code yes _item_type.code code save_ ############### # DIFFRN_SCAN # ############### save_DIFFRN_SCAN _category.description ; Data items in the DIFFRN_SCAN category describe the parameters of one or more scans, relating axis positions to frames. ; _category.id diffrn_scan _category.mandatory_code no _category_key.name '_diffrn_scan.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - derived from a suggestion by R. M. Sweet. The vector of each axis is not given here, because it is provided in the AXIS category. By making _diffrn_scan_axis.scan_id and _diffrn_scan_axis.axis_id keys of the DIFFRN_SCAN_AXIS category, an arbitrary number of scanning and fixed axes can be specified for a scan. In this example, three rotation axes and one translation axis at nonzero values are specified, with one axis stepping. There is no reason why more axes could not have been specified to step. Range information has been specified, but note that it can be calculated from the number of frames and the increment, so the data item _diffrn_scan_axis.angle_range could be dropped. Both the sweep data and the data for a single frame are specified. Note that the information on how the axes are stepped is given twice, once in terms of the overall averages in the value of _diffrn_scan.integration_time and the values for DIFFRN_SCAN_AXIS, and precisely for the given frame in the value for _diffrn_scan_frame.integration_time and the values for DIFFRN_SCAN_FRAME_AXIS. If dose-related adjustments are made to scan times and nonlinear stepping is done, these values may differ. Therefore, in interpreting the data for a particular frame it is important to use the frame-specific data. ; ; _diffrn_scan.id 1 _diffrn_scan.date_start '2001-11-18T03:26:42' _diffrn_scan.date_end '2001-11-18T03:36:45' _diffrn_scan.integration_time 3.0 _diffrn_scan.frame_id_start mad_L2_000 _diffrn_scan.frame_id_end mad_L2_200 _diffrn_scan.frames 201 loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment 1 omega 200.0 20.0 0.1 . . . 1 kappa -40.0 0.0 0.0 . . . 1 phi 127.5 0.0 0.0 . . . 1 tranz . . . 2.3 0.0 0.0 _diffrn_scan_frame.scan_id 1 _diffrn_scan_frame.date '2001-11-18T03:27:33' _diffrn_scan_frame.integration_time 3.0 _diffrn_scan_frame.frame_id mad_L2_018 _diffrn_scan_frame.frame_number 18 loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.angle_increment _diffrn_scan_frame_axis.displacement _diffrn_scan_frame_axis.displacement_increment mad_L2_018 omega 201.8 0.1 . . mad_L2_018 kappa -40.0 0.0 . . mad_L2_018 phi 127.5 0.0 . . mad_L2_018 tranz . . 2.3 0.0 ; ; Example 2 - a more extensive example (R. M. Sweet, P. J. Ellis & H. J. Bernstein). A detector is placed 240 mm along the Z axis from the goniometer. This leads to a choice: either the axes of the detector are defined at the origin, and then a Z setting of -240 is entered, or the axes are defined with the necessary Z offset. In this case, the setting is used and the offset is left as zero. This axis is called DETECTOR_Z. The axis for positioning the detector in the Y direction depends on the detector Z axis. This axis is called DETECTOR_Y. The axis for positioning the detector in the X direction depends on the detector Y axis (and therefore on the detector Z axis). This axis is called DETECTOR_X. This detector may be rotated around the Y axis. This rotation axis depends on the three translation axes. It is called DETECTOR_PITCH. A coordinate system is defined on the face of the detector in terms of 2300 0.150 mm pixels in each direction. The ELEMENT_X axis is used to index the first array index of the data array and the ELEMENT_Y axis is used to index the second array index. Because the pixels are 0.150mm x 0.150mm, the centre of the first pixel is at (0.075, 0.075) in this coordinate system. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 172.43 -172.43 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 2300 1 increasing ELEMENT_X ARRAY1 2 2300 2 increasing ELEMENT_Y # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.075 0.150 ELEMENT_Y ELEMENT_Y 0.075 0.150 # category ARRAY_ELEMENT_SIZE loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 ARRAY1 2 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; ; Example 3 - Example 2 revised for a spiral scan (R. M. Sweet, P. J. Ellis & H. J. Bernstein). A detector is placed 240 mm along the Z axis from the goniometer, as in Example 2 above, but in this example the image plate is scanned in a spiral pattern from the outside edge in. The axis for positioning the detector in the Y direction depends on the detector Z axis. This axis is called DETECTOR_Y. The axis for positioning the detector in the X direction depends on the detector Y axis (and therefore on the detector Z axis). This axis is called DETECTOR_X. This detector may be rotated around the Y axis. This rotation axis depends on the three translation axes. It is called DETECTOR_PITCH. A coordinate system is defined on the face of the detector in terms of a coupled rotation axis and radial scan axis to form a spiral scan. The rotation axis is called ELEMENT_ROT and the radial axis is called ELEMENT_RAD. A 150 micrometre radial pitch and a 75 micrometre 'constant velocity' angular pitch are assumed. Indexing is carried out first on the rotation axis and the radial axis is made to be dependent on it. The two axes are coupled to form an axis set ELEMENT_SPIRAL. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_ROT translation detector DETECTOR_PITCH 0 0 1 0 0 0 ELEMENT_RAD translation detector ELEMENT_ROT 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.angle _array_structure_list_axis.displacement _array_structure_list_axis.angular_pitch _array_structure_list_axis.radial_pitch ELEMENT_SPIRAL ELEMENT_ROT 0 . 0.075 . ELEMENT_SPIRAL ELEMENT_RAD . 172.5 . -0.150 # category ARRAY_ELEMENT_SIZE # the actual pixels are 0.075 by 0.150 mm # We give the coarser dimension here. loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_scan.id _item_description.description ; The value of _diffrn_scan.id uniquely identifies each scan. The identifier is used to tie together all the information about the scan. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_scan.id' diffrn_scan yes '_diffrn_scan_axis.scan_id' diffrn_scan_axis yes '_diffrn_scan_frame.scan_id' diffrn_scan_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_scan_axis.scan_id' '_diffrn_scan.id' '_diffrn_scan_frame.scan_id' '_diffrn_scan.id' save_ save__diffrn_scan.date_end _item_description.description ; The date and time of the end of the scan. Note that this may be an estimate generated during the scan, before the precise time of the end of the scan is known. ; _item.name '_diffrn_scan.date_end' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.date_start _item_description.description ; The date and time of the start of the scan. ; _item.name '_diffrn_scan.date_start' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.integration_time _item_description.description ; Approximate average time in seconds to integrate each step of the scan. The precise time for integration of each particular step must be provided in _diffrn_scan_frame.integration_time, even if all steps have the same integration time. ; _item.name '_diffrn_scan.integration_time' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan.frame_id_start _item_description.description ; The value of this data item is the identifier of the first frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_start' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frame_id_end _item_description.description ; The value of this data item is the identifier of the last frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_end' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frames _item_description.description ; The value of this data item is the number of frames in the scan. ; _item.name '_diffrn_scan.frames' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 1 1 1 save_ #################### # DIFFRN_SCAN_AXIS # #################### save_DIFFRN_SCAN_AXIS _category.description ; Data items in the DIFFRN_SCAN_AXIS category describe the settings of axes for particular scans. Unspecified axes are assumed to be at their zero points. ; _category.id diffrn_scan_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_axis.scan_id' '_diffrn_scan_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_axis.scan_id _item_description.description ; The value of this data item is the identifier of the scan for which axis settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan.id. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_axis.scan_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the scan for which settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan.id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_axis.axis_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.angle_start _item_description.description ; The starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_range _item_description.description ; The range from the starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_increment _item_description.description ; The increment for each step for the specified axis in degrees. In general, this will agree with _diffrn_scan_frame_axis.angle_increment. The sum of the values of _diffrn_scan_frame_axis.angle and _diffrn_scan_frame_axis.angle_increment is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of _diffrn_scan_axis.angle_increment will be representative of the ensemble of values of _diffrn_scan_frame_axis.angle_increment (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_rstrt_incr _item_description.description ; The increment after each step for the specified axis in degrees. In general, this will agree with _diffrn_scan_frame_axis.angle_rstrt_incr. The sum of the values of _diffrn_scan_frame_axis.angle, _diffrn_scan_frame_axis.angle_increment and _diffrn_scan_frame_axis.angle_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame and should equal _diffrn_scan_frame_axis.angle for this next frame. If the individual frame values vary, then the value of _diffrn_scan_axis.angle_rstrt_incr will be representative of the ensemble of values of _diffrn_scan_frame_axis.angle_rstrt_incr (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.displacement_start _item_description.description ; The starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_range _item_description.description ; The range from the starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_increment _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with _diffrn_scan_frame_axis.displacement_increment. The sum of the values of _diffrn_scan_frame_axis.displacement and _diffrn_scan_frame_axis.displacement_increment is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of _diffrn_scan_axis.displacement_increment will be representative of the ensemble of values of _diffrn_scan_frame_axis.displacement_increment (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_rstrt_incr _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with _diffrn_scan_frame_axis.displacement_rstrt_incr. The sum of the values of _diffrn_scan_frame_axis.displacement, _diffrn_scan_frame_axis.displacement_increment and _diffrn_scan_frame_axis.displacement_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame and should equal _diffrn_scan_frame_axis.displacement for this next frame. If the individual frame values vary, then the value of _diffrn_scan_axis.displacement_rstrt_incr will be representative of the ensemble of values of _diffrn_scan_frame_axis.displacement_rstrt_incr (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ ##################### # DIFFRN_SCAN_FRAME # ##################### save_DIFFRN_SCAN_FRAME _category.description ; Data items in the DIFFRN_SCAN_FRAME category describe the relationships of particular frames to scans. ; _category.id diffrn_scan_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame.scan_id' '_diffrn_scan_frame.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame.date _item_description.description ; The date and time of the start of the frame being scanned. ; _item.name '_diffrn_scan_frame.date' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan_frame.frame_id _item_description.description ; The value of this data item is the identifier of the frame being examined. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame.frame_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame.frame_number _item_description.description ; The value of this data item is the number of the frame within the scan, starting with 1. It is not necessarily the same as the value of _diffrn_scan_frame.frame_id, but it may be. ; _item.name '_diffrn_scan_frame.frame_number' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 0 0 0 save_ save__diffrn_scan_frame.integration_time _item_description.description ; The time in seconds to integrate this step of the scan. This should be the precise time of integration of each particular frame. The value of this data item should be given explicitly for each frame and not inferred from the value of _diffrn_scan.integration_time. ; _item.name '_diffrn_scan_frame.integration_time' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame.scan_id _item_description.description ; The value of _diffrn_scan_frame.scan_id identifies the scan containing this frame. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_frame.scan_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ ########################## # DIFFRN_SCAN_FRAME_AXIS # ########################## save_DIFFRN_SCAN_FRAME_AXIS _category.description ; Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the settings of axes for particular frames. Unspecified axes are assumed to be at their zero points. If, for any given frame, nonzero values apply for any of the data items in this category, those values should be given explicitly in this category and not simply inferred from values in DIFFRN_SCAN_AXIS. ; _category.id diffrn_scan_frame_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame_axis.frame_id' '_diffrn_scan_frame_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the frame for which settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_frame_axis.axis_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_axis.angle _item_description.description ; The setting of the specified axis in degrees for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.angle' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_increment _item_description.description ; The increment for this frame for the angular setting of the specified axis in degrees. The sum of the values of _diffrn_scan_frame_axis.angle and _diffrn_scan_frame_axis.angle_increment is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.angle_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_rstrt_incr _item_description.description ; The increment after this frame for the angular setting of the specified axis in degrees. The sum of the values of _diffrn_scan_frame_axis.angle, _diffrn_scan_frame_axis.angle_increment and _diffrn_scan_frame_axis.angle_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame and should equal _diffrn_scan_frame_axis.angle for this next frame. ; _item.name '_diffrn_scan_frame_axis.angle_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.displacement' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_increment _item_description.description ; The increment for this frame for the displacement setting of the specified axis in millimetres. The sum of the values of _diffrn_scan_frame_axis.displacement and _diffrn_scan_frame_axis.displacement_increment is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.displacement_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_rstrt_incr _item_description.description ; The increment for this frame for the displacement setting of the specified axis in millimetres. The sum of the values of _diffrn_scan_frame_axis.displacement, _diffrn_scan_frame_axis.displacement_increment and _diffrn_scan_frame_axis.displacement_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame and should equal _diffrn_scan_frame_axis.displacement for this next frame. ; _item.name '_diffrn_scan_frame_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.frame_id _item_description.description ; The value of this data item is the identifier of the frame for which axis settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame_axis.frame_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ ######################## DEPRECATED DATA ITEMS ######################## save__diffrn_detector_axis.id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_detector_axis.id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.id _item_description.description ; This data item is a pointer to _diffrn_measurement.id in the DIFFRN_MEASUREMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_measurement_axis.id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ ######################### DEPRECATED CATEGORY ######################### ##################### # DIFFRN_FRAME_DATA # ##################### save_DIFFRN_FRAME_DATA _category.description ; Data items in the DIFFRN_FRAME_DATA category record the details about each frame of data. The items in this category are now in the DIFFRN_DATA_FRAME category. The items in the DIFFRN_FRAME_DATA category are now deprecated. The items from this category are provided as aliases in version 1.0 of the dictionary but should not be used for new work. The items from the old category are provided in this dictionary for completeness but should not be used or cited. To avoid confusion, the example has been removed and the redundant parent-child links to other categories have been removed. ; _category.id diffrn_frame_data _category.mandatory_code no loop_ _category_key.name '_diffrn_frame_data.id' '_diffrn_frame_data.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; THE DIFFRN_FRAME_DATA category is deprecated and should not be used. ; ; # EXAMPLE REMOVED # ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_frame_data.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.array_id' _item.category_id diffrn_frame_data _item.mandatory_code yes _item_type.code code save_ save__diffrn_frame_data.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.binary_id' _item.category_id diffrn_frame_data _item.mandatory_code implicit _item_type.code int save_ save__diffrn_frame_data.detector_element_id _item_description.description ; This item is a pointer to _diffrn_detector_element.id in the DIFFRN_DETECTOR_ELEMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.detector_element_id' _item.category_id diffrn_frame_data _item.mandatory_code yes _item_type.code code save_ save__diffrn_frame_data.id _item_description.description ; The value of _diffrn_frame_data.id must uniquely identify each complete frame of data. DEPRECATED -- DO NOT USE ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_frame_data.id' diffrn_frame_data yes _item_type.code code save_ ################ END DEPRECATED SECTION ########### #################### ## ITEM_TYPE_LIST ## #################### # # # The regular expressions defined here are not compliant # with the POSIX 1003.2 standard as they include the # '\n' and '\t' special characters. These regular expressions # have been tested using version 0.12 of Richard Stallman's # GNU regular expression library in POSIX mode. # In order to allow presentation of a regular expression # in a text field concatenate any line ending in a backslash # with the following line, after discarding the backslash. # # A formal definition of the '\n' and '\t' special characters # is most properly done in the DDL, but for completeness, please # note that '\n' is the line termination character ('newline') # and '\t' is the horizontal tab character. There is a formal # ambiguity in the use of '\n' for line termination, in that # the intention is that the equivalent machine/OS-dependent line # termination character sequence should be accepted as a match, e.g. # # '\r' (control-M) under MacOS # '\n' (control-J) under Unix # '\r\n' (control-M control-J) under DOS and MS Windows # loop_ _item_type_list.code _item_type_list.primitive_code _item_type_list.construct _item_type_list.detail code char '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words ... ; ucode uchar '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words (case insensitive) ... ; line char '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; char item types / multi-word items ... ; uline uchar '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; char item types / multi-word items (case insensitive)... ; text char '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; text item types / multi-line text ... ; binary char ;\n--CIF-BINARY-FORMAT-SECTION--\n\ [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\ \n--CIF-BINARY-FORMAT-SECTION---- ; ; binary items are presented as MIME-like ascii-encoded sections in an imgCIF. In a CBF, raw octet streams are used to convey the same information. ; int numb '-?[0-9]+' ; int item types are the subset of numbers that are the negative or positive integers. ; float numb '-?(([0-9]+)[.]?|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?' ; float item types are the subset of numbers that are the floating numbers. ; any char '.*' ; A catch all for items that may take any form... ; yyyy-mm-dd char ;\ [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9][0-9]\ (T[0-2][0-9]:[0-5][0-9]:[0-5][0-9](.[0-9]+)([+-][0-5][0-9]:[0-5][0-9]))? ; ; Standard format for CIF date and time strings (see http://www.iucr.org/iucr-top/cif/spec/datetime.html), consisting of a yyyy-mm-dd date optionally followed by the character "T" followed by a 24-hour clock time, optionally followed by a signed time-zone offset. The IUCr standard has been extended to allow for an optional decimal fraction on the seconds of time. Time is local time if no time-zone offset is given. ; ##################### ## ITEM_UNITS_LIST ## ##################### loop_ _item_units_list.code _item_units_list.detail # 'metres' 'metres' 'centimetres' 'centimetres (metres * 10^( -2))' 'millimetres' 'millimetres (metres * 10^( -3))' 'nanometres' 'nanometres (metres * 10^( -9))' 'angstroms' 'angstroms (metres * 10^(-10))' 'picometres' 'picometres (metres * 10^(-12))' 'femtometres' 'femtometres (metres * 10^(-15))' # 'reciprocal_metres' 'reciprocal metres (metres^(-1))' 'reciprocal_centimetres' 'reciprocal centimetres ((metres * 10^( -2))^(-1))' 'reciprocal_millimetres' 'reciprocal millimetres ((metres * 10^( -3))^(-1))' 'reciprocal_nanometres' 'reciprocal nanometres ((metres * 10^( -9))^(-1))' 'reciprocal_angstroms' 'reciprocal angstroms ((metres * 10^(-10))^(-1))' 'reciprocal_picometres' 'reciprocal picometres ((metres * 10^(-12))^(-1))' # 'nanometres_squared' 'nanometres squared (metres * 10^( -9))^2' 'angstroms_squared' 'angstroms squared (metres * 10^(-10))^2' '8pi2_angstroms_squared' '8pi^2 * angstroms squared (metres * 10^(-10))^2' 'picometres_squared' 'picometres squared (metres * 10^(-12))^2' # 'nanometres_cubed' 'nanometres cubed (metres * 10^( -9))^3' 'angstroms_cubed' 'angstroms cubed (metres * 10^(-10))^3' 'picometres_cubed' 'picometres cubed (metres * 10^(-12))^3' # 'kilopascals' 'kilopascals' 'gigapascals' 'gigapascals' # 'hours' 'hours' 'minutes' 'minutes' 'seconds' 'seconds' 'microseconds' 'microseconds' # 'degrees' 'degrees (of arc)' 'degrees_squared' 'degrees (of arc) squared' # 'degrees_per_minute' 'degrees (of arc) per minute' # 'celsius' 'degrees (of temperature) Celsius' 'kelvins' 'degrees (of temperature) Kelvin' # 'counts' 'counts' 'counts_per_photon' 'counts per photon' # 'electrons' 'electrons' # 'electrons_squared' 'electrons squared' # 'electrons_per_nanometres_cubed' ; electrons per nanometres cubed (electrons/(metres * 10^( -9))^(-3)) ; 'electrons_per_angstroms_cubed' ; electrons per angstroms cubed (electrons/(metres * 10^(-10))^(-3)) ; 'electrons_per_picometres_cubed' ; electrons per picometres cubed (electrons/(metres * 10^(-12))^(-3)) ; 'kilowatts' 'kilowatts' 'milliamperes' 'milliamperes' 'kilovolts' 'kilovolts' # 'arbitrary' ; arbitrary system of units. ; # loop_ _item_units_conversion.from_code _item_units_conversion.to_code _item_units_conversion.operator _item_units_conversion.factor ### 'metres' 'centimetres' '*' 1.0E+02 'metres' 'millimetres' '*' 1.0E+03 'metres' 'nanometres' '*' 1.0E+09 'metres' 'angstroms' '*' 1.0E+10 'metres' 'picometres' '*' 1.0E+12 'metres' 'femtometres' '*' 1.0E+15 # 'centimetres' 'metres' '*' 1.0E-02 'centimetres' 'millimetres' '*' 1.0E+01 'centimetres' 'nanometres' '*' 1.0E+07 'centimetres' 'angstroms' '*' 1.0E+08 'centimetres' 'picometres' '*' 1.0E+10 'centimetres' 'femtometres' '*' 1.0E+13 # 'millimetres' 'metres' '*' 1.0E-03 'millimetres' 'centimetres' '*' 1.0E-01 'millimetres' 'nanometres' '*' 1.0E+06 'millimetres' 'angstroms' '*' 1.0E+07 'millimetres' 'picometres' '*' 1.0E+09 'millimetres' 'femtometres' '*' 1.0E+12 # 'nanometres' 'metres' '*' 1.0E-09 'nanometres' 'centimetres' '*' 1.0E-07 'nanometres' 'millimetres' '*' 1.0E-06 'nanometres' 'angstroms' '*' 1.0E+01 'nanometres' 'picometres' '*' 1.0E+03 'nanometres' 'femtometres' '*' 1.0E+06 # 'angstroms' 'metres' '*' 1.0E-10 'angstroms' 'centimetres' '*' 1.0E-08 'angstroms' 'millimetres' '*' 1.0E-07 'angstroms' 'nanometres' '*' 1.0E-01 'angstroms' 'picometres' '*' 1.0E+02 'angstroms' 'femtometres' '*' 1.0E+05 # 'picometres' 'metres' '*' 1.0E-12 'picometres' 'centimetres' '*' 1.0E-10 'picometres' 'millimetres' '*' 1.0E-09 'picometres' 'nanometres' '*' 1.0E-03 'picometres' 'angstroms' '*' 1.0E-02 'picometres' 'femtometres' '*' 1.0E+03 # 'femtometres' 'metres' '*' 1.0E-15 'femtometres' 'centimetres' '*' 1.0E-13 'femtometres' 'millimetres' '*' 1.0E-12 'femtometres' 'nanometres' '*' 1.0E-06 'femtometres' 'angstroms' '*' 1.0E-05 'femtometres' 'picometres' '*' 1.0E-03 ### 'reciprocal_centimetres' 'reciprocal_metres' '*' 1.0E+02 'reciprocal_centimetres' 'reciprocal_millimetres' '*' 1.0E-01 'reciprocal_centimetres' 'reciprocal_nanometres' '*' 1.0E-07 'reciprocal_centimetres' 'reciprocal_angstroms' '*' 1.0E-08 'reciprocal_centimetres' 'reciprocal_picometres' '*' 1.0E-10 # 'reciprocal_millimetres' 'reciprocal_metres' '*' 1.0E+03 'reciprocal_millimetres' 'reciprocal_centimetres' '*' 1.0E+01 'reciprocal_millimetres' 'reciprocal_nanometres' '*' 1.0E-06 'reciprocal_millimetres' 'reciprocal_angstroms' '*' 1.0E-07 'reciprocal_millimetres' 'reciprocal_picometres' '*' 1.0E-09 # 'reciprocal_nanometres' 'reciprocal_metres' '*' 1.0E+09 'reciprocal_nanometres' 'reciprocal_centimetres' '*' 1.0E+07 'reciprocal_nanometres' 'reciprocal_millimetres' '*' 1.0E+06 'reciprocal_nanometres' 'reciprocal_angstroms' '*' 1.0E-01 'reciprocal_nanometres' 'reciprocal_picometres' '*' 1.0E-03 # 'reciprocal_angstroms' 'reciprocal_metres' '*' 1.0E+10 'reciprocal_angstroms' 'reciprocal_centimetres' '*' 1.0E+08 'reciprocal_angstroms' 'reciprocal_millimetres' '*' 1.0E+07 'reciprocal_angstroms' 'reciprocal_nanometres' '*' 1.0E+01 'reciprocal_angstroms' 'reciprocal_picometres' '*' 1.0E-02 # 'reciprocal_picometres' 'reciprocal_metres' '*' 1.0E+12 'reciprocal_picometres' 'reciprocal_centimetres' '*' 1.0E+10 'reciprocal_picometres' 'reciprocal_millimetres' '*' 1.0E+09 'reciprocal_picometres' 'reciprocal_nanometres' '*' 1.0E+03 'reciprocal_picometres' 'reciprocal_angstroms' '*' 1.0E+01 ### 'nanometres_squared' 'angstroms_squared' '*' 1.0E+02 'nanometres_squared' 'picometres_squared' '*' 1.0E+06 # 'angstroms_squared' 'nanometres_squared' '*' 1.0E-02 'angstroms_squared' 'picometres_squared' '*' 1.0E+04 'angstroms_squared' '8pi2_angstroms_squared' '*' 78.9568 # 'picometres_squared' 'nanometres_squared' '*' 1.0E-06 'picometres_squared' 'angstroms_squared' '*' 1.0E-04 ### 'nanometres_cubed' 'angstroms_cubed' '*' 1.0E+03 'nanometres_cubed' 'picometres_cubed' '*' 1.0E+09 # 'angstroms_cubed' 'nanometres_cubed' '*' 1.0E-03 'angstroms_cubed' 'picometres_cubed' '*' 1.0E+06 # 'picometres_cubed' 'nanometres_cubed' '*' 1.0E-09 'picometres_cubed' 'angstroms_cubed' '*' 1.0E-06 ### 'kilopascals' 'gigapascals' '*' 1.0E-06 'gigapascals' 'kilopascals' '*' 1.0E+06 ### 'hours' 'minutes' '*' 6.0E+01 'hours' 'seconds' '*' 3.6E+03 'hours' 'microseconds' '*' 3.6E+09 # 'minutes' 'hours' '/' 6.0E+01 'minutes' 'seconds' '*' 6.0E+01 'minutes' 'microseconds' '*' 6.0E+07 # 'seconds' 'hours' '/' 3.6E+03 'seconds' 'minutes' '/' 6.0E+01 'seconds' 'microseconds' '*' 1.0E+06 # 'microseconds' 'hours' '/' 3.6E+09 'microseconds' 'minutes' '/' 6.0E+07 'microseconds' 'seconds' '/' 1.0E+06 ### 'celsius' 'kelvins' '-' 273.0 'kelvins' 'celsius' '+' 273.0 ### 'electrons_per_nanometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E+03 'electrons_per_nanometres_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+09 # 'electrons_per_angstroms_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-03 'electrons_per_angstroms_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+06 # 'electrons_per_picometres_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-09 'electrons_per_picometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E-06 ### ######################## ## DICTIONARY_HISTORY ## ######################## loop_ _dictionary_history.version _dictionary_history.update _dictionary_history.revision 1.3.2 2005-06-25 ; 2005-06-25 ITEM_TYPE_LIST: code, ucode, line, uline regexps updated to those of current mmCIF; float modified by allowing integers terminated by a point as valid. The 'time' part of yyyy-mm-dd types made optional in the regexp. (BM) 2005-06-17 Minor corrections as for proofs for IT G Chapter 4.6 (NJA) 2005-02-21 Minor corrections to spelling and punctuation (NJA) 2005-01-08 Changes as per Nicola Ashcroft. + Updated example 1 for DIFFRN_MEASUREMENT to agree with mmCIF. + Spelled out "micrometres" for "um" and "millimetres" for "mm". + Removed phrase "which may be stored" from ARRAY_STRUCTURE description. + Removed unused 'byte-offsets' compressions and updated cites to ITVG for '_array_structure.compression_type'. (HJB) ; 1.3.1 2003-08-13 ; Changes as per Frances C. Bernstein. + Identify initials. + Adopt British spelling for centre in text. + Set \p and \%Angstrom and powers. + Clean up commas and unclear wordings. + Clean up tenses in history. Changes as per Gotzon Madariaga. + Fix the ARRAY_DATA example to align '_array_data.binary_id' and X-Binary-Id. + Add a range to '_array_intensities.gain_esd'. + In the example of DIFFRN_DETECTOR_ELEMENT, '_diffrn_detector_element.id' and '_diffrn_detector_element.detector_id' interchanged. + Fix typos for direction, detector and axes. + Clarify description of polarisation. + Clarify axes in '_diffrn_detector_element.center[1]' '_diffrn_detector_element.center[2]'. + Add local item types for items that are pointers. (HJB) ; 1.3.0 2003-07-24 ; Changes as per Brian McMahon. + Consistently quote tags embedded in text. + Clean up introductory comments. + Adjust line lengths to fit in 80 character window. + Fix several descriptions in AXIS category which referred to '_axis.type' instead of the current item. + Fix erroneous use of deprecated item '_diffrn_detector_axis.id' in examples for DIFFRN_SCAN_AXIS. + Add deprecated items '_diffrn_detector_axis.id' and '_diffrn_measurement_axis.id'. (HJB) ; 1.2.4 2003-07-14 ; Changes as per I. David Brown. + Enhance descriptions in DIFFRN_SCAN_AXIS to make them less dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS. + Provide a copy of the deprecated DIFFRN_FRAME_DATA category for completeness. (HJB) ; 1.2.3 2003-07-03 ; Cleanup to conform to ITVG. + Correct sign error in ..._cubed units. + Correct '_diffrn_radiation.polarisn_norm' range. (HJB) ; 1.2.2 2003-03-10 ; Correction of typos in various DIFFRN_SCAN_AXIS descriptions. (HJB) ; 1.2.1 2003-02-22 ; Correction of ATOM_ for ARRAY_ typos in various descriptions. (HJB) ; 1.2 2003-02-07 ; Corrections to encodings (remove extraneous hyphens) remove extraneous underscore in '_array_structure.encoding_type' enumeration. Correct typos in items units list. (HJB) ; 1.1.3 2001-04-19 ; Another typo corrections by Wilfred Li, and cleanup by HJB. ; 1.1.2 2001-03-06 ; Several typo corrections by Wilfred Li. ; 1.1.1 2001-02-16 ; Several typo corrections by JW. ; 1.1 2001-02-06 ; Draft resulting from discussions on header for use at NSLS. (HJB) + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME. + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'. + Add '_diffrn_measurement_axis.measurement_device' and change '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'. + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source', '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm', '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end', '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr', '_diffrn_scan_axis.displacement_rstrt_incr', '_diffrn_scan_frame_axis.angle_increment', '_diffrn_scan_frame_axis.angle_rstrt_incr', '_diffrn_scan_frame_axis.displacement', '_diffrn_scan_frame_axis.displacement_increment',and '_diffrn_scan_frame_axis.displacement_rstrt_incr'. + Add '_diffrn_measurement.device' to category key. + Update yyyy-mm-dd to allow optional time with fractional seconds for time stamps. + Fix typos caught by RS. + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to allow for coupled axes, as in spiral scans. + Add examples for fairly complete headers thanks to R. Sweet and P. Ellis. ; 1.0 2000-12-21 ; Release version - few typos and tidying up. (BM & HJB) + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end of dictionary. + Alphabetize dictionary. ; 0.7.1 2000-09-29 ; Cleanup fixes. (JW) + Correct spelling of diffrn_measurement_axis in '_axis.id' + Correct ordering of uses of '_item.mandatory_code' and '_item_default.value'. ; 0.7.0 2000-09-09 ; Respond to comments by I. David Brown. (HJB) + Add further comments on '\n' and '\t'. + Update ITEM_UNITS_LIST by taking section from mmCIF dictionary and adding metres. Change 'meter' to 'metre' throughout. + Add missing enumerations to '_array_structure.compression_type' and make 'none' the default. + Remove parent-child relationship between '_array_structure_list.index' and '_array_structure_list.precedence'. + Improve alphabetization. + Fix '_array_intensities_gain.esd' related function. + Improve comments in AXIS. + Fix DIFFRN_FRAME_DATA example. + Remove erroneous DIFFRN_MEASUREMENT example. + Add '_diffrn_measurement_axis.id' to the category key. ; 0.6.0 1999-01-14 ; Remove redundant information for ENC_NONE data. (HJB) + After the D5 remove binary section identifier, size and compression type. + Add Control-L to header. ; 0.5.1 1999-01-03 ; Cleanup of typos and syntax errors. (HJB) + Cleanup example details for DIFFRN_SCAN category. + Add missing quote marks for '_diffrn_scan.id' definition. ; 0.5 1999-01-01 ; Modifications for axis definitions and reduction of binary header. (HJB) + Restore '_diffrn_detector.diffrn_id' to DIFFRN_DETECTOR KEY. + Add AXIS category. + Bring in complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories from cif_mm.dic for clarity. + Change '_array_structure.encoding_type' from type code to uline and added X-Binary-Element-Type to MIME header. + Add detector beam centre '_diffrn_detector_element.center[1]' and '_diffrn_detector_element.center[2]'. + Correct item name of '_diffrn_refln.frame_id'. + Replace reference to '_array_intensities.undefined' by '_array_intensities.undefined_value'. + Replace references to '_array_intensity.scaling' with '_array_intensities.scaling'. + Add DIFFRN_SCAN... categories. ; 0.4 1998-08-11 ; Modifications to the 0.3 imgCIF draft. (HJB) + Reflow comment lines over 80 characters and corrected typos. + Update examples and descriptions of MIME encoded data. + Change name to cbfext98.dic. ; 0.3 1998-07-04 ; Modifications for imgCIF. (HJB) + Add binary type, which is a text field containing a variant on MIME encoded data. + Change type of '_array_data.data' to binary and specify internal structure of raw binary data. + Add '_array_data.binary_id', and make '_diffrn_frame_data.binary_id' and '_array_intensities.binary_id' into pointers to this item. ; 0.2 1997-12-02 ; Modifications to the CBF draft. (JW) + Add category hierarchy for describing frame data developed from discussions at the BNL imgCIF Workshop Oct 1997. The following changes are made in implementing the workshop draft. Category DIFFRN_ARRAY_DATA is renamed to DIFFRN_FRAME_DATA. Category DIFFRN_FRAME_TYPE is renamed to DIFFRN_DETECTOR_ELEMENT. The parent item for '_diffrn_frame_data.array_id' is changed from '_array_structure_list.array_id' to '_array_structure.id'. Item '_diffrn_detector.array_id' is deleted. + Add data item '_diffrn_frame_data.binary_id' to identify data groups within a binary section. The formal identification of the binary section is still fuzzy. ; 0.1 1997-01-24 ; First draft of this dictionary in DDL 2.1 compliant format by John Westbrook (JW). This version is adapted from the Crystallographic Binary File (CBF) Format Draft Proposal provided by Andy Hammersley (AH). Modifications to the CBF draft. (JW) + In this version the array description has been cast in the categories ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. These categories have been generalized to describe array data of arbitrary dimension. + Array data in this description are contained in the category ARRAY_DATA. This departs from the CBF notion of data existing in some special comment. In this description, data is handled as an ordinary data item encapsulated in a character data type. Although data this manner deviates from CIF conventions, it does not violate any DDL 2.1 rules. DDL 2.1 regular expressions can be used to define the binary representation which will permit some level of data validation. In this version, the placeholder type code "any" has been used. This translates to a regular expression which will match any pattern. It should be noted that DDL 2.1 already supports array data objects although these have not been used in the current mmCIF dictionary. It may be possible to use the DDL 2.1 ITEM_STRUCTURE and ITEM_STRUCTURE_LIST categories to provide the information that is carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. By moving the array structure to the DDL level it would be possible to define an array type as well as a regular expression defining the data format. + Multiple array sections can be properly handled within a single datablock. ; #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof ./CBFlib-0.9.2.2/doc/Iarray_data.array_id.html0000644000076500007650000000520211603702115017241 0ustar yayayaya (IUCr) CIF Definition save__array_data.array_id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_array_data.array_id

Name:
'_array_data.array_id'

Definition:

       This item is a pointer to _array_structure.id in the
              ARRAY_STRUCTURE category.

              If not given, it defaults to 1.

Type: code

Mandatory item: implicit

Category: array_data

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_radiation.div_x_source.html0000644000076500007650000000616511603702115021344 0ustar yayayaya (IUCr) CIF Definition save__diffrn_radiation.div_x_source

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_radiation.div_x_source

Name:
'_diffrn_radiation.div_x_source'

Definition:

        Beam crossfire in degrees parallel to the laboratory X axis
               (see AXIS category).

               This is a characteristic of the X-ray beam as it illuminates
               the sample (or specimen) after all monochromation and
               collimation.

               This is the standard uncertainty (e.s.d.)  of the directions of
               photons in the XZ plane around the mean source beam
               direction.

               Note that for some synchrotrons this value is specified
               in milliradians, in which case a conversion is needed.
               To convert a value in milliradians to a value in degrees,
               multiply by 0.180 and divide by \p.

Type: float

Mandatory item: no

Category: diffrn_radiation

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/cif_img_1.6.4.dic0000777000076500007650000000000011603751102021006 2cif_img_1.6.4_2Jul11.dicustar yayayaya./CBFlib-0.9.2.2/doc/Cdiffrn_frame_data.html0000644000076500007650000000762611603702115016762 0ustar yayayaya (IUCr) CIF Definition save_diffrn_frame_data

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

Category DIFFRN_FRAME_DATA

Name:
'diffrn_frame_data'

Description:

       Data items in the DIFFRN_FRAME_DATA category record
              the details about each frame of data.

              The items in this category are now in the
              DIFFRN_DATA_FRAME category.

              The items in the DIFFRN_FRAME_DATA category
              are now deprecated.  The items from this category
              are provided as aliases in the 1.0 dictionary
              or, in the case of _diffrn_frame_data.details,
              in the 1.4 dictionary.  THESE ITEMS SHOULD NOT
              BE USED FOR NEW WORK.

              The items from the old category are provided
              in this dictionary for completeness
              but should not be used or cited.  To avoid
              confusion, the example has been removed
              and the redundant parent-child links to other
              categories have been removed.

Example:

THE DIFFRN_FRAME_DATA category is deprecated and should not be used.
 
       # EXAMPLE REMOVED #



Category groups:
    inclusive_group
    array_data_group
Category keys:
    _diffrn_frame_data.id
    _diffrn_frame_data.detector_element_id

Mandatory category: no

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Iarray_structure_list_axis.displacement.html0000644000076500007650000000602111603702115023325 0ustar yayayaya (IUCr) CIF Definition save__array_structure_list_axis.displacement

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_array_structure_list_axis.displacement

Name:
'_array_structure_list_axis.displacement'

Definition:

        The setting of the specified axis in millimetres for the first
               data point of the array index with the corresponding value
               of _array_structure_list.axis_set_id.  If the index is
               specified as 'increasing', this will be the centre of the
               pixel with index value 1.  If the index is specified as
               'decreasing', this will be the centre of the pixel with
               maximum index value.

Type: float

Mandatory item: no


Enumeration default: 0.0

Category: array_structure_list_axis

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Imap_segment.array_id.html0000644000076500007650000000542211603702115017435 0ustar yayayaya (IUCr) CIF Definition save__map_segment.array_id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_map_segment.array_id

Name:
'_map_segment.array_id'

Definition:

       The value of _map_segment.array_id identifies the array
              structure into which the map is organized.

              This item is a pointer to _array_structure.id in the
              ARRAY_STRUCTURE category.

Type: code

Mandatory item: implicit

Category: map_segment

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Iarray_structure_list_axis.displacement_increment.html0000644000076500007650000000523411603702115025376 0ustar yayayaya (IUCr) CIF Definition save__array_structure_list_axis.displacement_increment

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_array_structure_list_axis.displacement_increment

Name:
'_array_structure_list_axis.displacement_increment'

Definition:

        The pixel-centre-to-pixel-centre increment for the displacement
               setting of the specified axis in millimetres.

Type: float

Mandatory item: no


Enumeration default: 0.0

Category: array_structure_list_axis

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_scan.frame_id_start.html0000644000076500007650000000533411603702115020605 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan.frame_id_start

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_scan.frame_id_start

Name:
'_diffrn_scan.frame_id_start'

Definition:

        The value of this data item is the identifier of the
               first frame in the scan.

               This item is a pointer to _diffrn_data_frame.id in the
               DIFFRN_DATA_FRAME category.

Type: code

Mandatory item: yes

Category: diffrn_scan

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Iaxis.vector[3].html0000644000076500007650000000516311603702115016167 0ustar yayayaya (IUCr) CIF Definition save__axis.vector[3]

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_axis.vector[3]

Name:
'_axis.vector[3]'

Definition:

        The [3] element of the three-element vector used to specify
               the direction of a rotation or translation axis.
               The vector should be normalized to be a unit vector and
               is dimensionless.

Type: float

Mandatory item: no


Enumeration default: 0.0

Category: axis

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_measurement.sample_detector_distance.html0000644000076500007650000000542711603702115024252 0ustar yayayaya (IUCr) CIF Definition save__diffrn_measurement.sample_detector_distance

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_measurement.sample_detector_distance

Name:
'_diffrn_measurement.sample_detector_distance'

Definition:

        The value of _diffrn_measurement.sample_detector_distance gives 
               the unsigned distance in millimetres from the sample to the
               detector along the beam.

Type: float

Mandatory item: no


The permitted range is [0.0, infinity)

Category: diffrn_measurement

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Iarray_element_size.index.html0000644000076500007650000000520711603702115020335 0ustar yayayaya (IUCr) CIF Definition save__array_element_size.index

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_array_element_size.index

Name:
'_array_element_size.index'

Definition:

       This item is a pointer to _array_structure_list.index in
              the ARRAY_STRUCTURE_LIST category.

Type: code

Mandatory item: yes

Category: array_element_size

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_scan_axis.axis_id.html0000644000076500007650000000550411603702115020265 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan_axis.axis_id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_scan_axis.axis_id

Name:
'_diffrn_scan_axis.axis_id'

Definition:

        The value of this data item is the identifier of one of
               the axes for the scan for which settings are being specified.

               Multiple axes may be specified for the same value of
               _diffrn_scan.id.

               This item is a pointer to _axis.id in the
               AXIS category.

Type: code

Mandatory item: yes

Category: diffrn_scan_axis

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_scan.id.html0000644000076500007650000000541611603702115016217 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan.id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_scan.id

Name:
'_diffrn_scan.id'

Definition:

       The value of _diffrn_scan.id uniquely identifies each
              scan.  The identifier is used to tie together all the
              information about the scan.

Type: code

Mandatory item: yes

_diffrn_scan_axis.scan_id
_diffrn_scan_frame.scan_id

Category: diffrn_scan

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_scan_frame.scan_id.html0000644000076500007650000000541511603702115020374 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan_frame.scan_id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_scan_frame.scan_id

Name:
'_diffrn_scan_frame.scan_id'

Definition:

       The value of _diffrn_scan_frame.scan_id identifies the scan
              containing this frame.

              This item is a pointer to _diffrn_scan.id in the
              DIFFRN_SCAN category.

Type: code

Mandatory item: yes

Category: diffrn_scan_frame

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/cif_mm.dic0000644000076500007650001224264411603702115014275 0ustar yayayaya########################################################################### # # File: mmcif_pdbx.dic # Date: Fri Jul 29 11:04:31 EDT 2005 # # Created from files in CVS module dict-mmcif_pdbx.dic unless noted: # mmcif_pdbx-header.dic # mmcif_pdbx-data.dic # mmcif_pdbx-def-1.dic # ../dict-mmcif_std/mmcif_std-def-2.dic # mmcif_pdbx-def-2.dic # mmcif_pdbx-def-3.dic # mmcif_pdbx-def-4.dic # mmcif_pdbx-def-5.dic # mmcif_pdbx-def-6.dic # ../dict-mmcif_iims/mmcif_iims-def-2.dic # mmcif_pdbx-def-8.dic # mmcif_pdbx-def-9.dic # mmcif_pdbx-def-10.dic # mmcif_pdbx-def-12.dic # ########################################################################### ########################################################################### # # File: mmcif_pdbx-header.dic # # PDB Exchange Data Dictionary # # This dictionary supplements the contents of the mmCIF data dictionary # with additional data items that may be required to store all of the # information currently included a Protein Data Bank (PDB) format data # file. Additional data items describing internal processing status # are also defined here. # # The mmCIF dictionary and this supplement provide the provisional # specifications for the data exchange protocol used by the wwPDB: # Resource Collaboratory for Structural Bioinformatics (RCSB) PDB, # Molecular Structure Database (MSD) Group/EBI, PDB Japan (PDBj) at # Osaka University. This dictionary also includes: data extensions # for structural genomics projects recommended by International Task # Force on Data Deposition and Archiving (including protein production), # NMR and 3D electron microscopy. # # # Header Section # ############################################################################## data_mmcif_pdbx.dic _datablock.id mmcif_pdbx.dic _datablock.description ; This data block holds the Protein Data Bank Exchange Data dictionary. ; _dictionary.title mmcif_pdbx.dic _dictionary.datablock_id mmcif_pdbx.dic _dictionary.version 1.019 # loop_ _dictionary_history.version _dictionary_history.update _dictionary_history.revision 0.001 2000-05-23 ; Initial revision based on RCSB local dictionaries and EBI database schema. J. Westbrook and J. Ionides ; 0.002 2000-06-06 ; Changes: (jdw) + Added items in refine_hist and exptl_crystal_grow ; 0.003 2000-10-16 ; Changes: (jdw) + Move enumerations to examples for: _pdbx_nmr_exptl.type _pdbx_nmr_ensemble.conformer_selection_criteria _pdbx_nmr_software.name _struct_keywords.pdbx_keywords + Added _atom_site_anisotrop.pdbx_auth_* items + Added _struct_mon_prot_cis.pdbx_ + Added _struct_conn.pdbx_ptnr3_auth_* items. ; 0.004 2000-10-24 ; Changes: (jdw) + Added optional timestamps to data items. + Repositioned parent items in PDBX_POLY_SEQ_SCHEME. ; 0.005 2000-10-25 ; Changes: (jdw) + drop category PDBX_DATABASE_REMARK ; 0.006 2000-10-26 ; Changes: (jdw) + Added _exptl_crystal_grow.rcsb_pH_range. + Added category PDBX_STRUCT_SHEET_HBOND to hold single hydrogen bond registration between beta sheet strands. ; 0.007 2000-11-09 ; Changes: (jdw) + Added mandatory codes for _exptl_crystal_grow.pdbx_details and _exptl_crystal_grow.pdbx_pH_range. + Added missing data types and category ids in category pdbx_struct_sheet_hbond. + Updated data type for atom name references to atcode. + Updated aliases for _refine.overall_SU_B and _refine.overall_SU_ML. + Trimmed line lengths > 80 characters. ; 0.008 2001-01-22 ; Changes: (jdw) + Added item _pdbx_database_status.dep_release_code_sequence ; 0.009 2001-03-02 ; Changes: (jdw) + Added missing mandatory codes and reset aliases for _diffrn_radiation.pdbx_wavelenth_list. ; 0.010 2001-04-18 ; Changes: (jdw) + Added missing _item_type.codes for _refine_hist.number_atoms_solvent _refine_hist.number_atoms_total _refine.overall_SU_B _refine.overall_SU_ML _refine.pdbx_overall_ESU_R + Added CCP4 data items output from REFMAC V5. ; 0.011 2001-06-14 ; Changes: (jdw) + Moved enumerations to examples for _pdbx_nmr_spectrometer.field_strength + _atom_site.pdb_auth_atom_name data type changed from code to atcode. ; 0.012 2001-06-28 ; Changes: (jdw) + _atom_site_anisotrop.pdbx_auth_* aliases corrected. + adjust regex for date:time type ; 0.013 2001-07-12 ; Changes: (jdw) + enumerations->examples for _pdbx_nmr_representative.selection_criteria and _pdbx_database_related.db_name. + add regex for int and float ranges ; 0.014 2002-02-28 ; Changes: (jdw) + Add items for NMR model and PDB insert code to GEOM_BOND, GEOM_ANGLE, GEOM_CONTACT, and GEOM_TORSION categories. ; 0.015 2002-05-22 ; Changes: (jdw) + Add PDBX_ENTITY_NONPOLY and fix missing data type codes. ; 0.016 2002-08-05 ; Changes: (jdw) + Add PDBX_AUDIT category. ; 0.017 2002-10-05 ; Changes: (jdw) + Final corrections of recommendations for NMR and X-ray deposition for structural genomics. ; 0.018 2003-07-07 ; Changes: (jdw) + Integrated protein production data items. ; 0.019 2003-09-21 ; Changes: (jdw/hy) + Added additional phasing items for PDB_EXTRACT. ; 0.020 2003-10-30 ; Changes: (jdw/zf) + Fix cases where category keys are not flagged as mandatory + Add category PDBX_AUDIT_AUTHOR ; 1.000 2004-04-22 ; Changes: (jdw) + New packaging and naming + Integrate 3d em definitions + Relax enumerations to comply with existing legacy data. + Version to 1.000 ; 1.001 2004-05-21 ; Changes: (jdw) + Fixed incorrect category in _pdbx_audit_author.address + Added _citation.pdbx_database_id_DOI + Fixed placement of _chem_comp.pdbx_align. Moved this item to _chem_comp_atom.pdbx_align ; 1.002 2004-06-09 ; Changes: (jdw) + Added categories PDBX_DOMAIN, PDBX_SEQUENCE_RANGE, PDBX_FEATURE_ENTRY, PDBX_FEATURE_ASSEMBLY, PDBX_FEATURE_DOMAIN, and PDBX_FEATURE_SEQUENCE_RANGE. ; 1.003 2004-06-16 ; Changes: (jdw) + Fix miscellaneous unresolved links. ; 1.004 2004-08-04 ; Changes: (jdw) + Fix many data type errors in phasing section. + Add pdbx_contact_author ; 1.005 2004-09-28 ; Changes: (zkf,jdw) + Add missing pdbx_contact_author.postal_code item + Add missing pdbx_contact_author.city item + Add missing pdbx_contact_author.state_province item + Add enumerations in pdbx_contact_author.id + Modify enumerations in pdbx_contact_author.role ; 1.006 2004-10-10 ; Changes: (jdw) + Update enumerations in cryo-em dictionary. ; 1.007 2004-11-02 ; Changes: (jdw) + added pdbx_entity_prod_protocol, pdbx_exptl_crystal_grow_sol, pdbx_exptl_crystal_grow_comp, and pdbx_exptl_crystal_cryo_treatment categories + relax enumerations in cryo-em dictionary. + remove upper-bound for refine.occupancy_max ; 1.008 2004-11-15 ; Changes: (jdw) + fix typo in category save frame name pdbx_exptl_crystal_grow_comp. ; 1.009 2005-01-13 ; Changes: (zkf) + add _pdbx_database_status.status_code_sf item + add _pdbx_database_status.date_of_sf_release item + add _pdbx_database_status.status_code_mr item + add _pdbx_database_status.date_of_mr_release item + add _pdbx_database_status.SG_entry item + add _entity_poly.pdbx_target_identifier item + add pdbx_SG_project category + fixed enumeration values for _software.language ; 1.010 2005-01-25 ; Changes: (jdw) + change mandatory doc for _pdbx_database_status.SG_entry + fix key in category pdbx_database_PDB_obs_spr ; 1.011 2005-03-08 ; Changes: (jdw) + Included extensions from mmCIF dictionary... Changes: (fzk) + add _pdbx_refine_tls_group.beg_auth_asym_id + add _pdbx_refine_tls_group.end_auth_asym_id + add enumeration values 'SGC' and 'NPPSFA' for _pdbx_SG_project.initial_of_center + add enumeration values 'Structural Genomics Consortium' and 'National Project on Protein Structural and Functional Analyses' for _pdbx_SG_project.full_name_of_center + fix _item_description.description for _entity_poly.pdbx_target_identifier ; 1.012 2005-03-29 ; Changes: (kh/jdw) + added preliminary set of extensions for macromolecular powder diffraction experiments, including: _pdbx_exptl_pd (category) _pdbx_exptl_pd.entry.id _pdbx_exptl_pd.spec_preparation_pH _pdbx_exptl_pd.spec_preparation_pH_range _pdbx_exptl_pd.spec_preparation _diffrn_radiation.pdbx_analyzer _refine.pdbx_pd_number_of_powder_patterns _refine.pdbx_pd_number_of_points _refine.pdbx_pd_meas_number_of_points _refine.pdbx_pd_proc_ls_prof_R_factor _refine.pdbx_pd_proc_ls_prof_wR_factor _refine.pdbx_pd_Marquardt_correlation_coeff _refine.pdbx_pd_Fsqrd_R_factor _refine.pdbx_pd_ls_matrix_band_width Changes: (fzk) removed 'National Project on Protein Structural and Functional Analyses' from _pdbx_SG_project.full_name_of_center, added 'National Project on Protein Structural and Functional Analyses' to _pdbx_SG_project.project_name ; 1.013 2005-04-05 ; Changes: (jdw) + Temporarily remove definitions from Image CIF dictionary + Added mandatory code for _cell.reciprocal_angle_beta + Added mandatory code for _pdbx_entity_nonpoly.entity_id + Fixed category attribute for _reflns_shell.pdbx_chi_squared + Changed mandatory code for _software.citation_id ; 1.014 2005-04-08 ; Changes: (jdw) + remove _struct_keywords.text from category key ; 1.015 2005-04-15 ; Changes: (jdw) + remove _entity_keywords.text from category key ; 1.016 2005-06-24 ; Changes: (jdw) + aliases repointed for items in category pdbx_database_remark + Added the following items: _diffrn_detector.pdbx_frames_total _diffrn_detector.pdbx_collection_time_total _refine.pdbx_ls_sigma_Fsqd _reflns.pdbx_Rmerge_I_all _reflns.pdbx_netI_over_sigmaI _reflns.pdbx_res_netI_over_av_sigmaI_2 _reflns.pdbx_res_netI_over_sigmaI_2 _reflns_shell.pdbx_netI_over_sigmaI_all _reflns_shell.pdbx_netI_over_sigmaI_obs _struct_biol.pdbx_formula_weight _struct_biol.pdbx_formula_weight_method _struct_biol_gen.pdbx_PDB_order _phasing_MAD.pdbx_number_data_sets _phasing_MAD.pdbx_anom_scat_method _phasing_MIR.pdbx_number_derivatives _phasing_set.pdbx_temp_details + miscellaneous editorial changes in descriptions and enumerations. ; 1.017 2005-06-27 ; Changes: (BMcM) + added _reflns.threshold_expression and _publ_author.email + numerous minor changes to wordings of definitions to align with mmcif version 2.0.09 as released on International Tables G CD-ROM ; 1.018 2005-07-14 ; Changes: (jdw) + Added PDB_SOLN_SCATTER* definitions + Added _refln.pdbx_[F,I]_[minus,plus] and _refln.pdbx_[F,I]_[minus,plus]_sigma + Extend enumeration for _pdbx_database_status.status_code_sf ; 1.019 2005-07-21 ; Changes: (jdw) + Added _struct.pdbx_formula_weight and _struct.pdbx_formula_weight_method + Added _refln.pdbx_HL_A_iso, _refln.pdbx_HL_B_iso, _refln.pdbx_HL_C_iso, and _refln.pdbx_HL_D_iso + Added _phasing_set.pdbx_d_res_low/high _pdbx_phasing_MR.native_data_set_id + Added category pdbx_feature_monomer ; ### EOF mmcif_pdbx-header.dic ########################################################################### # # File: mmcif_pdbx-data.dic # # Protein Data Bank Exchange Data Dictionary # # # Data Section # # ########################################################################### ################## ## SUB_CATEGORY ## ################## loop_ _sub_category.id _sub_category.description 'cartesian_coordinate' ; The collection of x, y, and z components of a position specified with reference to a Cartesian (orthogonal angstrom) coordinate system. ; 'cartesian_coordinate_esd' ; The collection of estimated standard deviations of the x, y, and z components of a position specified with reference to a Cartesian (orthogonal angstrom) coordinate system. ; 'fractional_coordinate' ; The collection of x, y, and z components of a position specified with reference to unit cell directions. ; 'fractional_coordinate_esd' ; The collection of estimated standard deviations of the x, y, and z components of a position specified with reference to unit cell directions. ; 'matrix' ; The collection of elements of a matrix. ; miller_index ; The collection of h, k, and l components of the Miller index of a reflection. ; 'cell_length' ; The collection of a, b, and c axis lengths of a unit cell. ; 'cell_length_esd' ; The collection of estimated standard deviations of the a, b, and c axis lengths of a unit cell. ; 'cell_angle' ; The collection of alpha, beta, and gamma angles of a unit cell. ; 'cell_angle_esd' ; The collection of estimated standard deviations of the alpha, beta, and gamma angles of a unit cell. ; 'mm_atom_site_auth_label' ; The collection of asym id, atom id, comp id and seq id components of an author's alternative specification for a macromolecular atom site. ; 'mm_atom_site_label' ; The collection of alt id, asym id, atom id, comp id and seq id components of the label for a macromolecular atom site. ; 'vector' ; The collection of elements of a vector. ; ######################### ## CATEGORY_GROUP_LIST ## ######################### loop_ _category_group_list.id _category_group_list.parent_id _category_group_list.description 'inclusive_group' . ; Categories that belong to the macromolecular dictionary. ; 'atom_group' 'inclusive_group' ; Categories that describe the properties of atoms. ; 'array_data_group' 'inclusive_group' ; Categories that describe array data. ; 'axis_group' 'inclusive_group' ; Categories that describe axes. ; 'audit_group' 'inclusive_group' ; Categories that describe dictionary maintenance and identification. ; 'cell_group' 'inclusive_group' ; Categories that describe the unit cell. ; 'chemical_group' 'inclusive_group' ; Categories that describe chemical properties and nomenclature. ; 'chem_comp_group' 'inclusive_group' ; Categories that describe components of chemical structure. ; 'chem_link_group' 'inclusive_group' ; Categories that describe links between components of chemical structure. ; 'citation_group' 'inclusive_group' ; Categories that provide bibliographic references. ; 'computing_group' 'inclusive_group' ; Categories that describe the computational details of the experiment. ; 'compliance_group' 'inclusive_group' ; Categories that are included in this dictionary specifically to comply with previous dictionaries. ; 'database_group' 'inclusive_group' ; Categories that hold references to entries in databases that contain related information. ; 'diffrn_group' 'inclusive_group' ; Categories that describe details of the diffraction experiment. ; 'em_group' 'inclusive_group' ; Categories that describe 3-dimensional electron microscopy. ; 'entity_group' 'inclusive_group' ; Categories that describe chemical entities. ; 'entry_group' 'inclusive_group' ; Categories that pertain to the entire data block. ; 'exptl_group' 'inclusive_group' ; Categories that hold details of the experimental conditions. ; 'geom_group' 'inclusive_group' ; Categories that hold details of molecular and crystal geometry. ; 'iucr_group' 'inclusive_group' ; Categories that are used for manuscript submission and internal processing by the staff of the International Union of Crystallography. ; 'pdb_group' 'inclusive_group' ; Categories that pertain to the file-format or data-processing codes used by the Protein Data Bank. ; 'phasing_group' 'inclusive_group' ; Categories that describe phasing. ; 'refine_group' 'inclusive_group' ; Categories that describe refinement. ; 'refln_group' 'inclusive_group' ; Categories that describe the details of reflection measurements. ; 'struct_group' 'inclusive_group' ; Categories that contain details about the crystallographic structure. ; 'symmetry_group' 'inclusive_group' ; Categories that describe symmetry information. ; 'pdbx_group' 'inclusive_group' ; Categories which are part of PDB data exchange protocol. ; 'pdbx_erf_group' 'inclusive_group' ; Categories which are used by RCSB PDB to store derived and computed data. ; 'ccp4_group' 'inclusive_group' ; Categories from the CCP4 harvest dictionary. ; 'ndb_group' 'inclusive_group' ; Categories which are used by the Nucleic Acid Database. ; 'rcsb_group' 'inclusive_group' ; Categories which are used internally by the RCSB PDB. ; 'protein_production_group' 'inclusive_group' ; Categories which describe the details of protein production. ; 'solution_scattering_group' 'inclusive_group' ; Categories which describe the details of solution scattering experiments. ; #################### ## ITEM_TYPE_LIST ## #################### # # # The regular expressions defined here are not compliant # with the POSIX 1003.2 standard as they include the # '\n' and '\t' special characters. These regular expressions # have been tested using version 0.12 of Richard Stallman's # GNU regular expression library in POSIX mode. # # # For some data items, a standard syntax is assumed. The syntax is # described for each data item in the dictionary, but is summarized here: # # Names: The family name(s) followed by a comma, precedes the first # name(s) or initial(s). # # Telephone numbers: # The international code is given in brackets and any extension # number is preceded by 'ext'. # # Dates: In the form yyyy-mm-dd. # ############################################################################## loop_ _item_type_list.code _item_type_list.primitive_code _item_type_list.construct _item_type_list.detail code char '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words ... ; ucode uchar '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words (case insensitive) ... ; line char '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; char item types / multi-word items ... ; uline uchar '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; char item types / multi-word items (case insensitive)... ; text char '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; text item types / multi-line text ... ; int numb '-?[0-9]+' ; int item types are the subset of numbers that are the negative or positive integers. ; float numb '-?(([0-9]+)[.]?|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?' ; float item types are the subset of numbers that are the floating numbers. ; name uchar '_[_A-Za-z0-9]+\.[][_A-Za-z0-9%-]+' ; name item types take the form... ; idname uchar '[_A-Za-z0-9]+' ; idname item types take the form... ; any char '.*' ; A catch all for items that may take any form... ; yyyy-mm-dd char '[0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9][0-9]' ; Standard format for CIF dates. ; uchar3 uchar '[+]?[A-Za-z0-9][A-Za-z0-9][A-Za-z0-9]' ; data item for 3 character codes ; uchar1 uchar '[+]?[A-Za-z0-9]' ; data item for 1 character codes ; symop char '([1-9]|[1-9][0-9]|1[0-8][0-9]|19[0-2])(_[1-9][1-9][1-9])?' ; symop item types take the form n_klm, where n refers to the symmetry operation that is applied to the coordinates in the ATOM_SITE category identified by _atom_site_label. It must match a number given in _symmetry_equiv_pos_site_id. k, l, and m refer to the translations that are subsequently applied to the symmetry transformed coordinates to generate the atom used. These translations (x,y,z) are related to (k,l,m) by k = 5 + x l = 5 + y m = 5 + z By adding 5 to the translations, the use of negative numbers is avoided. ; atcode char '[][ _(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; Character data type for atom names ... ; yyyy-mm-dd:hh:mm char '[0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9](-[0-9]?[0-9])?(:[0-9]?[0-9]:[0-9][0-9])?' ; Standard format for CIF dates with optional time stamp. ; fax uchar '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words (case insensitive) ... ; phone uchar '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words (case insensitive) ... ; email uchar '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words (case insensitive) ... ; int-range numb '-?[0-9]+(--?[0-9]+)?' ; int item types are the subset of numbers that are the negative or positive integers with optional range. ; float-range numb '-?(([0-9]+)[.]?|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?(--?(([0-9]+)[.]?|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?)?' ; int item types are the subset of numbers that are the floating numbers. ; code30 char '.?.?.?.?.?.?.?.?.?.?.?.?.?.?.?.?.?.?.?.?.?.?.?.?.?.?.?.?.?.?' 'A string value, not allowed to exceed 30 characters.' # binary char ;\n--CIF-BINARY-FORMAT-SECTION--\n\ [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\ \n--CIF-BINARY-FORMAT-SECTION---- ; ; binary items are presented as MIME-like ascii-encoded sections in an imgCIF. In a CBF, raw octet streams are used to convey the same information. ; ##################### ## ITEM_UNITS_LIST ## ##################### loop_ _item_units_list.code _item_units_list.detail # 'metres' 'metres (metres)' 'centimetres' 'centimetres (metres * 10^( -2))' 'millimetres' 'millimetres (metres * 10^( -3))' 'nanometres' 'nanometres (metres * 10^( -9))' 'angstroms' 'angstroms (metres * 10^(-10))' 'picometres' 'picometres (metres * 10^(-12))' 'femtometres' 'femtometres (metres * 10^(-15))' # 'reciprocal_metres' 'reciprocal metres (metres^(-1))' 'reciprocal_centimetres' 'reciprocal centimetres ((metres * 10^( -2))^(-1))' 'reciprocal_millimetres' 'reciprocal millimetres ((metres * 10^( -3))^(-1))' 'reciprocal_nanometres' 'reciprocal nanometres ((metres * 10^( -9))^(-1))' 'reciprocal_angstroms' 'reciprocal angstroms ((metres * 10^(-10))^(-1))' 'reciprocal_picometres' 'reciprocal picometres ((metres * 10^(-12))^(-1))' # 'nanometres_squared' 'nanometres squared (metres * 10^( -9))^2' 'angstroms_squared' 'angstroms squared (metres * 10^(-10))^2' '8pi2_angstroms_squared' '8pi^2 * angstroms squared (metres * 10^(-10))^2' 'picometres_squared' 'picometres squared (metres * 10^(-12))^2' # 'nanometres_cubed' 'nanometres cubed (metres * 10^( -9))^3' 'angstroms_cubed' 'angstroms cubed (metres * 10^(-10))^3' 'picometres_cubed' 'picometres cubed (metres * 10^(-12))^3' # 'kilopascals' 'kilopascals' 'gigapascals' 'gigapascals' # 'hours' 'hours' 'minutes' 'minutes' 'seconds' 'seconds' 'microseconds' 'microseconds' # 'degrees' 'degrees (of arc)' # 'degrees_per_minute' 'degrees (of arc) per minute' # 'celsius' 'degrees (of temperature) Celsius' 'kelvins' 'degrees (of temperature) Kelvin' # 'electrons' 'electrons' # 'electrons_squared' 'electrons squared' # 'electrons_per_nanometres_cubed' ; electrons per nanometres cubed (electrons/(metres * 10^( -9))^(-3)) ; 'electrons_per_angstroms_cubed' ; electrons per angstroms cubed (electrons/(metres * 10^(-10))^(-3)) ; 'electrons_per_picometres_cubed' ; electrons per picometres cubed (electrons/(metres * 10^(-12))^(-3)) ; 'kilowatts' 'kilowatts' 'milliamperes' 'milliamperes' 'kilovolts' 'kilovolts' # 'arbitrary' ; arbitrary system of units. ; # 'angstroms_degrees' 'angstroms * degrees' # 'degrees_squared' 'degrees squared' # 'mg_per_ml' 'milliliter per milligram' # 'ml_per_min' 'milliliter per minute' # 'milliliters' 'liter / 1000' # 'milligrams' 'grams / 1000' # 'megadaltons' 'megadaltons' 'microns_squared' 'microns squared' 'microns' 'microns' # 'millimeters' 'millimeters' 'electrons_angstrom_squared' 'electrons square angstrom' 'electron_volts' 'electron volts' # 'mg/ml' 'mg per milliliter' 'millimolar' 'millimolar' 'megagrams_per_cubic_metre' 'megagrams per cubic metre' 'pixels_per_millimetre' 'pixels per millimetre' 'counts' 'counts' 'counts_per_photon' 'counts per photon' # loop_ _item_units_conversion.from_code _item_units_conversion.to_code _item_units_conversion.operator _item_units_conversion.factor ### 'metres' 'centimetres' '*' 1.0E+02 'metres' 'millimetres' '*' 1.0E+03 'metres' 'nanometres' '*' 1.0E+09 'metres' 'angstroms' '*' 1.0E+10 'metres' 'picometres' '*' 1.0E+12 'metres' 'femtometres' '*' 1.0E+15 'centimetres' 'millimetres' '*' 1.0E+01 'centimetres' 'nanometres' '*' 1.0E+07 'centimetres' 'angstroms' '*' 1.0E+08 'centimetres' 'picometres' '*' 1.0E+10 'centimetres' 'femtometres' '*' 1.0E+13 # 'millimetres' 'centimetres' '*' 1.0E-01 'millimetres' 'nanometres' '*' 1.0E+06 'millimetres' 'angstroms' '*' 1.0E+07 'millimetres' 'picometres' '*' 1.0E+09 'millimetres' 'femtometres' '*' 1.0E+12 # 'nanometres' 'centimetres' '*' 1.0E-07 'nanometres' 'millimetres' '*' 1.0E-06 'nanometres' 'angstroms' '*' 1.0E+01 'nanometres' 'picometres' '*' 1.0E+03 'nanometres' 'femtometres' '*' 1.0E+06 # 'angstroms' 'centimetres' '*' 1.0E-08 'angstroms' 'millimetres' '*' 1.0E-07 'angstroms' 'nanometres' '*' 1.0E-01 'angstroms' 'picometres' '*' 1.0E+02 'angstroms' 'femtometres' '*' 1.0E+05 # 'picometres' 'centimetres' '*' 1.0E-10 'picometres' 'millimetres' '*' 1.0E-09 'picometres' 'nanometres' '*' 1.0E-03 'picometres' 'angstroms' '*' 1.0E-02 'picometres' 'femtometres' '*' 1.0E+03 # 'femtometres' 'centimetres' '*' 1.0E-13 'femtometres' 'millimetres' '*' 1.0E-12 'femtometres' 'nanometres' '*' 1.0E-06 'femtometres' 'angstroms' '*' 1.0E-05 'femtometres' 'picometres' '*' 1.0E-03 ### 'reciprocal_centimetres' 'reciprocal_millimetres' '*' 1.0E-01 'reciprocal_centimetres' 'reciprocal_nanometres' '*' 1.0E-07 'reciprocal_centimetres' 'reciprocal_angstroms' '*' 1.0E-08 'reciprocal_centimetres' 'reciprocal_picometres' '*' 1.0E-10 # 'reciprocal_millimetres' 'reciprocal_centimetres' '*' 1.0E+01 'reciprocal_millimetres' 'reciprocal_nanometres' '*' 1.0E-06 'reciprocal_millimetres' 'reciprocal_angstroms' '*' 1.0E-07 'reciprocal_millimetres' 'reciprocal_picometres' '*' 1.0E-09 # 'reciprocal_nanometres' 'reciprocal_centimetres' '*' 1.0E+07 'reciprocal_nanometres' 'reciprocal_millimetres' '*' 1.0E+06 'reciprocal_nanometres' 'reciprocal_angstroms' '*' 1.0E-01 'reciprocal_nanometres' 'reciprocal_picometres' '*' 1.0E-03 # 'reciprocal_angstroms' 'reciprocal_centimetres' '*' 1.0E+08 'reciprocal_angstroms' 'reciprocal_millimetres' '*' 1.0E+07 'reciprocal_angstroms' 'reciprocal_nanometres' '*' 1.0E+01 'reciprocal_angstroms' 'reciprocal_picometres' '*' 1.0E-02 # 'reciprocal_picometres' 'reciprocal_centimetres' '*' 1.0E+10 'reciprocal_picometres' 'reciprocal_millimetres' '*' 1.0E+09 'reciprocal_picometres' 'reciprocal_nanometres' '*' 1.0E+03 'reciprocal_picometres' 'reciprocal_angstroms' '*' 1.0E+01 ### 'nanometres_squared' 'angstroms_squared' '*' 1.0E+02 'nanometres_squared' 'picometres_squared' '*' 1.0E+06 # 'angstroms_squared' 'nanometres_squared' '*' 1.0E-02 'angstroms_squared' 'picometres_squared' '*' 1.0E+04 'angstroms_squared' '8pi2_angstroms_squared' '*' 78.9568 # 'picometres_squared' 'nanometres_squared' '*' 1.0E-06 'picometres_squared' 'angstroms_squared' '*' 1.0E-04 ### 'nanometres_cubed' 'angstroms_cubed' '*' 1.0E+03 'nanometres_cubed' 'picometres_cubed' '*' 1.0E+09 # 'angstroms_cubed' 'nanometres_cubed' '*' 1.0E-03 'angstroms_cubed' 'picometres_cubed' '*' 1.0E+06 # 'picometres_cubed' 'nanometres_cubed' '*' 1.0E-09 'picometres_cubed' 'angstroms_cubed' '*' 1.0E-06 ### 'kilopascals' 'gigapascals' '*' 1.0E-06 'gigapascals' 'kilopascals' '*' 1.0E+06 ### 'hours' 'minutes' '*' 6.0E+01 'hours' 'seconds' '*' 3.6E+03 'hours' 'microseconds' '*' 3.6E+09 # 'minutes' 'hours' '/' 6.0E+01 'minutes' 'seconds' '*' 6.0E+01 'minutes' 'microseconds' '*' 6.0E+07 # 'seconds' 'hours' '/' 3.6E+03 'seconds' 'minutes' '/' 6.0E+01 'seconds' 'microseconds' '*' 1.0E+06 # 'microseconds' 'hours' '/' 3.6E+09 'microseconds' 'minutes' '/' 6.0E+07 'microseconds' 'seconds' '/' 1.0E+06 ### 'celsius' 'kelvins' '-' 273.0 'kelvins' 'celsius' '+' 273.0 ### 'electrons_per_nanometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E+03 'electrons_per_nanometres_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+09 # 'electrons_per_angstroms_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-03 'electrons_per_angstroms_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+06 # 'electrons_per_picometres_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-09 'electrons_per_picometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E-06 ### ### EOF mmcif_pdbx-data.dic ########################################################################### # # File: mmcif_std-def-1.dic # # mmCIF Data Dictionary (standard defintions) # # This data dictionary contains the standard mmCIF data definitions. # # Defintion Section 1 # # ########################################################################### ############### ## ATOM_SITE ## ############### save_atom_site _category.description ; Data items in the ATOM_SITE category record details about the atom sites in a macromolecular crystal structure, such as the positional coordinates, atomic displacement parameters, magnetic moments and directions. The data items for describing anisotropic atomic displacement factors are only used if the corresponding items are not given in the ATOM_SITE_ANISOTROP category. ; _category.id atom_site _category.mandatory_code no _category_key.name '_atom_site.id' loop_ _category_group.id 'inclusive_group' 'atom_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _atom_site.group_PDB _atom_site.type_symbol _atom_site.label_atom_id _atom_site.label_comp_id _atom_site.label_asym_id _atom_site.label_seq_id _atom_site.label_alt_id _atom_site.Cartn_x _atom_site.Cartn_y _atom_site.Cartn_z _atom_site.occupancy _atom_site.B_iso_or_equiv _atom_site.footnote_id _atom_site.auth_seq_id _atom_site.id ATOM N N VAL A 11 . 25.369 30.691 11.795 1.00 17.93 . 11 1 ATOM C CA VAL A 11 . 25.970 31.965 12.332 1.00 17.75 . 11 2 ATOM C C VAL A 11 . 25.569 32.010 13.808 1.00 17.83 . 11 3 ATOM O O VAL A 11 . 24.735 31.190 14.167 1.00 17.53 . 11 4 ATOM C CB VAL A 11 . 25.379 33.146 11.540 1.00 17.66 . 11 5 ATOM C CG1 VAL A 11 . 25.584 33.034 10.030 1.00 18.86 . 11 6 ATOM C CG2 VAL A 11 . 23.933 33.309 11.872 1.00 17.12 . 11 7 ATOM N N THR A 12 . 26.095 32.930 14.590 1.00 18.97 4 12 8 ATOM C CA THR A 12 . 25.734 32.995 16.032 1.00 19.80 4 12 9 ATOM C C THR A 12 . 24.695 34.106 16.113 1.00 20.92 4 12 10 ATOM O O THR A 12 . 24.869 35.118 15.421 1.00 21.84 4 12 11 ATOM C CB THR A 12 . 26.911 33.346 17.018 1.00 20.51 4 12 12 ATOM O OG1 THR A 12 3 27.946 33.921 16.183 0.50 20.29 4 12 13 ATOM O OG1 THR A 12 4 27.769 32.142 17.103 0.50 20.59 4 12 14 ATOM C CG2 THR A 12 3 27.418 32.181 17.878 0.50 20.47 4 12 15 ATOM C CG2 THR A 12 4 26.489 33.778 18.426 0.50 20.00 4 12 16 ATOM N N ILE A 13 . 23.664 33.855 16.884 1.00 22.08 . 13 17 ATOM C CA ILE A 13 . 22.623 34.850 17.093 1.00 23.44 . 13 18 ATOM C C ILE A 13 . 22.657 35.113 18.610 1.00 25.77 . 13 19 ATOM O O ILE A 13 . 23.123 34.250 19.406 1.00 26.28 . 13 20 ATOM C CB ILE A 13 . 21.236 34.463 16.492 1.00 22.67 . 13 21 ATOM C CG1 ILE A 13 . 20.478 33.469 17.371 1.00 22.14 . 13 22 ATOM C CG2 ILE A 13 . 21.357 33.986 15.016 1.00 21.75 . 13 23 # - - - - data truncated for brevity - - - - HETATM C C1 APS C . 1 4.171 29.012 7.116 0.58 17.27 1 300 101 HETATM C C2 APS C . 1 4.949 27.758 6.793 0.58 16.95 1 300 102 HETATM O O3 APS C . 1 4.800 26.678 7.393 0.58 16.85 1 300 103 HETATM N N4 APS C . 1 5.930 27.841 5.869 0.58 16.43 1 300 104 # - - - - data truncated for brevity - - - - ; save_ save__atom_site.aniso_B[1][1] _item_description.description ; The [1][1] element of the anisotropic atomic displacement matrix B, which appears in the structure-factor term as: T = exp{-1/4 sum~i~[sum~j~(B^ij^ h~i~ h~j~ a*~i~ a*~j~)]} h = the Miller indices a* = the reciprocal space cell lengths These matrix elements may appear with atomic coordinates in the ATOM_SITE category, or they may appear in the separate ATOM_SITE_ANISOTROP category, but they may not appear in both places. Similarly, anisotropic displacements may appear as either B's or U's, but not as both. The unique elements of the real symmetric matrix are entered by row. The IUCr Commission on Nomenclature recommends against the use of B for reporting atomic displacement parameters. U, being directly proportional to B, is preferred. ; _item.name '_atom_site.aniso_B[1][1]' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.aniso_B[1][1]_esd' associated_esd '_atom_site.aniso_U[1][1]' conversion_constant '_atom_site_anisotrop.U[1][1]' conversion_constant '_atom_site.aniso_U[1][1]' alternate_exclusive '_atom_site_anisotrop.B[1][1]' alternate_exclusive '_atom_site_anisotrop.U[1][1]' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_type_conditions.code esd _item_units.code 8pi2_angstroms_squared save_ save__atom_site.aniso_B[1][1]_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site.aniso_B[1][1]. ; _item.name '_atom_site.aniso_B[1][1]_esd' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.aniso_B[1][1]' associated_value '_atom_site.aniso_U[1][1]_esd' conversion_constant '_atom_site_anisotrop.U[1][1]_esd' conversion_constant '_atom_site.aniso_U[1][1]_esd' alternate_exclusive '_atom_site_anisotrop.B[1][1]_esd' alternate_exclusive '_atom_site_anisotrop.U[1][1]_esd' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_units.code 8pi2_angstroms_squared save_ save__atom_site.aniso_B[1][2] _item_description.description ; The [1][2] element of the anisotropic atomic displacement matrix B, which appears in the structure-factor term as: T = exp{-1/4 sum~i~[sum~j~(B^ij^ h~i~ h~j~ a*~i~ a*~j~)]} h = the Miller indices a* = the reciprocal space cell lengths These matrix elements may appear with atomic coordinates in the ATOM_SITE category, or they may appear in the separate ATOM_SITE_ANISOTROP category, but they may not appear in both places. Similarly, anisotropic displacements may appear as either B's or U's, but not as both. The unique elements of the real symmetric matrix are entered by row. The IUCr Commission on Nomenclature recommends against the use of B for reporting atomic displacement parameters. U, being directly proportional to B, is preferred. ; _item.name '_atom_site.aniso_B[1][2]' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.aniso_B[1][2]_esd' associated_esd '_atom_site.aniso_U[1][2]' conversion_constant '_atom_site_anisotrop.U[1][2]' conversion_constant '_atom_site.aniso_U[1][2]' alternate_exclusive '_atom_site_anisotrop.B[1][2]' alternate_exclusive '_atom_site_anisotrop.U[1][2]' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_type_conditions.code esd _item_units.code 8pi2_angstroms_squared save_ save__atom_site.aniso_B[1][2]_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site.aniso_B[1][2]. ; _item.name '_atom_site.aniso_B[1][2]_esd' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.aniso_B[1][2]' associated_value '_atom_site.aniso_U[1][2]_esd' conversion_constant '_atom_site_anisotrop.U[1][2]_esd' conversion_constant '_atom_site.aniso_U[1][2]_esd' alternate_exclusive '_atom_site_anisotrop.B[1][2]_esd' alternate_exclusive '_atom_site_anisotrop.U[1][2]_esd' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_units.code 8pi2_angstroms_squared save_ save__atom_site.aniso_B[1][3] _item_description.description ; The [1][3] element of the anisotropic atomic displacement matrix B, which appears in the structure-factor term as: T = exp{-1/4 sum~i~[sum~j~(B^ij^ h~i~ h~j~ a*~i~ a*~j~)]} h = the Miller indices a* = the reciprocal space cell lengths These matrix elements may appear with atomic coordinates in the ATOM_SITE category, or they may appear in the separate ATOM_SITE_ANISOTROP category, but they may not appear in both places. Similarly, anisotropic displacements may appear as either B's or U's, but not as both. The unique elements of the real symmetric matrix are entered by row. The IUCr Commission on Nomenclature recommends against the use of B for reporting atomic displacement parameters. U, being directly proportional to B, is preferred. ; _item.name '_atom_site.aniso_B[1][3]' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.aniso_B[1][3]_esd' associated_esd '_atom_site.aniso_U[1][3]' conversion_constant '_atom_site_anisotrop.U[1][3]' conversion_constant '_atom_site.aniso_U[1][3]' alternate_exclusive '_atom_site_anisotrop.B[1][3]' alternate_exclusive '_atom_site_anisotrop.U[1][3]' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_type_conditions.code esd _item_units.code 8pi2_angstroms_squared save_ save__atom_site.aniso_B[1][3]_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site.aniso_B[1][3]. ; _item.name '_atom_site.aniso_B[1][3]_esd' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.aniso_B[1][3]' associated_value '_atom_site.aniso_U[1][3]_esd' conversion_constant '_atom_site_anisotrop.U[1][3]_esd' conversion_constant '_atom_site.aniso_U[1][3]_esd' alternate_exclusive '_atom_site_anisotrop.B[1][3]_esd' alternate_exclusive '_atom_site_anisotrop.U[1][3]_esd' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_units.code 8pi2_angstroms_squared save_ save__atom_site.aniso_B[2][2] _item_description.description ; The [2][2] element of the anisotropic atomic displacement matrix B, which appears in the structure-factor term as: T = exp{-1/4 sum~i~[sum~j~(B^ij^ h~i~ h~j~ a*~i~ a*~j~)]} h = the Miller indices a* = the reciprocal space cell lengths These matrix elements may appear with atomic coordinates in the ATOM_SITE category, or they may appear in the separate ATOM_SITE_ANISOTROP category, but they may not appear in both places. Similarly, anisotropic displacements may appear as either B's or U's, but not as both. The unique elements of the real symmetric matrix are entered by row. The IUCr Commission on Nomenclature recommends against the use of B for reporting atomic displacement parameters. U, being directly proportional to B, is preferred. ; _item.name '_atom_site.aniso_B[2][2]' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.aniso_B[2][2]_esd' associated_esd '_atom_site.aniso_U[2][2]' conversion_constant '_atom_site_anisotrop.U[2][2]' conversion_constant '_atom_site.aniso_U[2][2]' alternate_exclusive '_atom_site_anisotrop.B[2][2]' alternate_exclusive '_atom_site_anisotrop.U[2][2]' alternate_exclusive _item_type.code float _item_type_conditions.code esd _item_units.code 8pi2_angstroms_squared save_ save__atom_site.aniso_B[2][2]_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site.aniso_B[2][2]. ; _item.name '_atom_site.aniso_B[2][2]_esd' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.aniso_B[2][2]' associated_value '_atom_site.aniso_U[2][2]_esd' conversion_constant '_atom_site_anisotrop.U[2][2]_esd' conversion_constant '_atom_site.aniso_U[2][2]_esd' alternate_exclusive '_atom_site_anisotrop.B[2][2]_esd' alternate_exclusive '_atom_site_anisotrop.U[2][2]_esd' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_units.code 8pi2_angstroms_squared save_ save__atom_site.aniso_B[2][3] _item_description.description ; The [2][3] element of the anisotropic atomic displacement matrix B, which appears in the structure-factor term as: T = exp{-1/4 sum~i~[sum~j~(B^ij^ h~i~ h~j~ a*~i~ a*~j~)]} h = the Miller indices a* = the reciprocal space cell lengths These matrix elements may appear with atomic coordinates in the ATOM_SITE category, or they may appear in the separate ATOM_SITE_ANISOTROP category, but they may not appear in both places. Similarly, anisotropic displacements may appear as either B's or U's, but not as both. The unique elements of the real symmetric matrix are entered by row. The IUCr Commission on Nomenclature recommends against the use of B for reporting atomic displacement parameters. U, being directly proportional to B, is preferred. ; _item.name '_atom_site.aniso_B[2][3]' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.aniso_B[2][3]_esd' associated_esd '_atom_site.aniso_U[2][3]' conversion_constant '_atom_site_anisotrop.U[2][3]' conversion_constant '_atom_site.aniso_U[2][3]' alternate_exclusive '_atom_site_anisotrop.B[2][3]' alternate_exclusive '_atom_site_anisotrop.U[2][3]' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_type_conditions.code esd _item_units.code 8pi2_angstroms_squared save_ save__atom_site.aniso_B[2][3]_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site.aniso_B[2][3]. ; _item.name '_atom_site.aniso_B[2][3]_esd' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.aniso_B[2][3]' associated_value '_atom_site.aniso_U[2][3]_esd' conversion_constant '_atom_site_anisotrop.U[2][3]_esd' conversion_constant '_atom_site.aniso_U[2][3]_esd' alternate_exclusive '_atom_site_anisotrop.B[2][3]_esd' alternate_exclusive '_atom_site_anisotrop.U[2][3]_esd' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_units.code 8pi2_angstroms_squared save_ save__atom_site.aniso_B[3][3] _item_description.description ; The [3][3] element of the anisotropic atomic displacement matrix B, which appears in the structure-factor term as: T = exp{-1/4 sum~i~[sum~j~(B^ij^ h~i~ h~j~ a*~i~ a*~j~)]} h = the Miller indices a* = the reciprocal space cell lengths These matrix elements may appear with atomic coordinates in the ATOM_SITE category, or they may appear in the separate ATOM_SITE_ANISOTROP category, but they may not appear in both places. Similarly, anisotropic displacements may appear as either B's or U's, but not as both. The unique elements of the real symmetric matrix are entered by row. The IUCr Commission on Nomenclature recommends against the use of B for reporting atomic displacement parameters. U, being directly proportional to B, is preferred. ; _item.name '_atom_site.aniso_B[3][3]' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.aniso_B[3][3]_esd' associated_esd '_atom_site.aniso_U[3][3]' conversion_constant '_atom_site_anisotrop.U[3][3]' conversion_constant '_atom_site.aniso_U[3][3]' alternate_exclusive '_atom_site_anisotrop.B[3][3]' alternate_exclusive '_atom_site_anisotrop.U[3][3]' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_type_conditions.code esd _item_units.code 8pi2_angstroms_squared save_ save__atom_site.aniso_B[3][3]_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site.aniso_B[3][3]. ; _item.name '_atom_site.aniso_B[3][3]_esd' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.aniso_B[3][3]' associated_value '_atom_site.aniso_U[3][3]_esd' conversion_constant '_atom_site_anisotrop.U[3][3]_esd' conversion_constant '_atom_site.aniso_U[3][3]_esd' alternate_exclusive '_atom_site_anisotrop.B[3][3]_esd' alternate_exclusive '_atom_site_anisotrop.U[3][3]_esd' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_units.code 8pi2_angstroms_squared save_ save__atom_site.aniso_ratio _item_description.description ; Ratio of the maximum to minimum principal axes of displacement (thermal) ellipsoids. ; _item.name '_atom_site.aniso_ratio' _item.category_id atom_site _item.mandatory_code no _item_related.related_name '_atom_site_anisotrop.ratio' _item_related.function_code alternate_exclusive loop_ _item_range.maximum _item_range.minimum . 1.0 1.0 1.0 _item_type.code float save_ save__atom_site.aniso_U[1][1] _item_description.description ; The [1][1] element of the standard anisotropic atomic displacement matrix U, which appears in the structure-factor term as: T = exp{-2 pi^2^ sum~i~[sum~j~(U^ij^ h~i~ h~j~ a*~i~ a*~j~)]} h = the Miller indices a* = the reciprocal space cell lengths These matrix elements may appear with atomic coordinates in the ATOM_SITE category, or they may appear in the separate ATOM_SITE_ANISOTROP category, but they may not appear in both places. Similarly, anisotropic displacements may appear as either B's or U's, but not as both. The unique elements of the real symmetric matrix are entered by row. ; _item.name '_atom_site.aniso_U[1][1]' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.aniso_U[1][1]_esd' associated_esd '_atom_site.aniso_B[1][1]' conversion_constant '_atom_site_anisotrop.B[1][1]' conversion_constant '_atom_site.aniso_B[1][1]' alternate_exclusive '_atom_site_anisotrop.B[1][1]' alternate_exclusive '_atom_site_anisotrop.U[1][1]' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_type_conditions.code esd _item_units.code angstroms_squared save_ save__atom_site.aniso_U[1][1]_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site.aniso_U[1][1]. ; _item.name '_atom_site.aniso_U[1][1]_esd' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.aniso_U[1][1]' associated_value '_atom_site.aniso_B[1][1]_esd' conversion_constant '_atom_site_anisotrop.B[1][1]_esd' conversion_constant '_atom_site.aniso_B[1][1]_esd' alternate_exclusive '_atom_site_anisotrop.B[1][1]_esd' alternate_exclusive '_atom_site_anisotrop.U[1][1]_esd' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_units.code angstroms_squared save_ save__atom_site.aniso_U[1][2] _item_description.description ; The [1][2] element of the standard anisotropic atomic displacement matrix U, which appears in the structure-factor term as: T = exp{-2 pi^2^ sum~i~[sum~j~(U^ij^ h~i~ h~j~ a*~i~ a*~j~)]} h = the Miller indices a* = the reciprocal space cell lengths These matrix elements may appear with atomic coordinates in the ATOM_SITE category, or they may appear in the separate ATOM_SITE_ANISOTROP category, but they may not appear in both places. Similarly, anisotropic displacements may appear as either B's or U's, but not as both. The unique elements of the real symmetric matrix are entered by row. ; _item.name '_atom_site.aniso_U[1][2]' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.aniso_U[1][2]_esd' associated_esd '_atom_site.aniso_B[1][2]' conversion_constant '_atom_site_anisotrop.B[1][2]' conversion_constant '_atom_site.aniso_B[1][2]' alternate_exclusive '_atom_site_anisotrop.B[1][2]' alternate_exclusive '_atom_site_anisotrop.U[1][2]' alternate_exclusive _item_type.code float _item_type_conditions.code esd _item_units.code angstroms_squared save_ save__atom_site.aniso_U[1][2]_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site.aniso_U[1][2]. ; _item.name '_atom_site.aniso_U[1][2]_esd' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.aniso_U[1][2]' associated_value '_atom_site.aniso_B[1][2]_esd' conversion_constant '_atom_site_anisotrop.B[1][2]_esd' conversion_constant '_atom_site.aniso_B[1][2]_esd' alternate_exclusive '_atom_site_anisotrop.B[1][2]_esd' alternate_exclusive '_atom_site_anisotrop.U[1][2]_esd' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_units.code angstroms_squared save_ save__atom_site.aniso_U[1][3] _item_description.description ; The [1][3] element of the standard anisotropic atomic displacement matrix U, which appears in the structure-factor term as: T = exp{-2 pi^2^ sum~i~[sum~j~(U^ij^ h~i~ h~j~ a*~i~ a*~j~)]} h = the Miller indices a* = the reciprocal space cell lengths These matrix elements may appear with atomic coordinates in the ATOM_SITE category, or they may appear in the separate ATOM_SITE_ANISOTROP category, but they may not appear in both places. Similarly, anisotropic displacements may appear as either B's or U's, but not as both. The unique elements of the real symmetric matrix are entered by row. ; _item.name '_atom_site.aniso_U[1][3]' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.aniso_U[1][3]_esd' associated_esd '_atom_site.aniso_B[1][3]' conversion_constant '_atom_site_anisotrop.B[1][3]' conversion_constant '_atom_site.aniso_B[1][3]' alternate_exclusive '_atom_site_anisotrop.B[1][3]' alternate_exclusive '_atom_site_anisotrop.U[1][3]' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_type_conditions.code esd _item_units.code angstroms_squared save_ save__atom_site.aniso_U[1][3]_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site.aniso_U[1][3]. ; _item.name '_atom_site.aniso_U[1][3]_esd' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.aniso_U[1][3]' associated_value '_atom_site.aniso_B[1][3]_esd' conversion_constant '_atom_site_anisotrop.B[1][3]_esd' conversion_constant '_atom_site.aniso_B[1][3]_esd' alternate_exclusive '_atom_site_anisotrop.B[1][3]_esd' alternate_exclusive '_atom_site_anisotrop.U[1][3]_esd' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_units.code angstroms_squared save_ save__atom_site.aniso_U[2][2] _item_description.description ; The [2][2] element of the standard anisotropic atomic displacement matrix U, which appears in the structure-factor term as: T = exp{-2 pi^2^ sum~i~[sum~j~(U^ij^ h~i~ h~j~ a*~i~ a*~j~)]} h = the Miller indices a* = the reciprocal space cell lengths These matrix elements may appear with atomic coordinates in the ATOM_SITE category, or they may appear in the separate ATOM_SITE_ANISOTROP category, but they may not appear in both places. Similarly, anisotropic displacements may appear as either B's or U's, but not as both. The unique elements of the real symmetric matrix are entered by row. ; _item.name '_atom_site.aniso_U[2][2]' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.aniso_U[2][2]_esd' associated_esd '_atom_site.aniso_B[2][2]' conversion_constant '_atom_site_anisotrop.B[2][2]' conversion_constant '_atom_site.aniso_B[2][2]' alternate_exclusive '_atom_site_anisotrop.B[2][2]' alternate_exclusive '_atom_site_anisotrop.U[2][2]' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_type_conditions.code esd _item_units.code angstroms_squared save_ save__atom_site.aniso_U[2][2]_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site.aniso_U[2][2]. ; _item.name '_atom_site.aniso_U[2][2]_esd' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.aniso_U[2][2]' associated_value '_atom_site.aniso_B[2][2]_esd' conversion_constant '_atom_site_anisotrop.B[2][2]_esd' conversion_constant '_atom_site.aniso_B[2][2]_esd' alternate_exclusive '_atom_site_anisotrop.B[2][2]_esd' alternate_exclusive '_atom_site_anisotrop.U[2][2]_esd' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_units.code angstroms_squared save_ save__atom_site.aniso_U[2][3] _item_description.description ; The [2][3] element of the standard anisotropic atomic displacement matrix U, which appears in the structure-factor term as: T = exp{-2 pi^2^ sum~i~[sum~j~(U^ij^ h~i~ h~j~ a*~i~ a*~j~)]} h = the Miller indices a* = the reciprocal space cell lengths These matrix elements may appear with atomic coordinates in the ATOM_SITE category, or they may appear in the separate ATOM_SITE_ANISOTROP category, but they may not appear in both places. Similarly, anisotropic displacements may appear as either B's or U's, but not as both. The unique elements of the real symmetric matrix are entered by row. ; _item.name '_atom_site.aniso_U[2][3]' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.aniso_U[2][3]_esd' associated_esd '_atom_site.aniso_B[2][3]' conversion_constant '_atom_site_anisotrop.B[2][3]' conversion_constant '_atom_site.aniso_B[2][3]' alternate_exclusive '_atom_site_anisotrop.B[2][3]' alternate_exclusive '_atom_site_anisotrop.U[2][3]' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_type_conditions.code esd _item_units.code angstroms_squared save_ save__atom_site.aniso_U[2][3]_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site.aniso_U[2][3]. ; _item.name '_atom_site.aniso_U[2][3]_esd' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.aniso_U[2][3]' associated_value '_atom_site.aniso_B[2][3]_esd' conversion_constant '_atom_site_anisotrop.B[2][3]_esd' conversion_constant '_atom_site.aniso_B[2][3]_esd' alternate_exclusive '_atom_site_anisotrop.B[2][3]_esd' alternate_exclusive '_atom_site_anisotrop.U[2][3]_esd' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_units.code angstroms_squared save_ save__atom_site.aniso_U[3][3] _item_description.description ; The [3][3] element of the standard anisotropic atomic displacement matrix U, which appears in the structure-factor term as: T = exp{-2 pi^2^ sum~i~[sum~j~(U^ij^ h~i~ h~j~ a*~i~ a*~j~)]} h = the Miller indices a* = the reciprocal space cell lengths These matrix elements may appear with atomic coordinates in the ATOM_SITE category, or they may appear in the separate ATOM_SITE_ANISOTROP category, but they may not appear in both places. Similarly, anisotropic displacements may appear as either B's or U's, but not as both. The unique elements of the real symmetric matrix are entered by row. ; _item.name '_atom_site.aniso_U[3][3]' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.aniso_U[3][3]_esd' associated_esd '_atom_site.aniso_B[3][3]' conversion_constant '_atom_site_anisotrop.B[3][3]' conversion_constant '_atom_site.aniso_B[3][3]' alternate_exclusive '_atom_site_anisotrop.B[3][3]' alternate_exclusive '_atom_site_anisotrop.U[3][3]' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_type_conditions.code esd _item_units.code angstroms_squared save_ save__atom_site.aniso_U[3][3]_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site.aniso_U[3][3]. ; _item.name '_atom_site.aniso_U[3][3]_esd' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.aniso_U[3][3]' associated_value '_atom_site.aniso_B[3][3]_esd' conversion_constant '_atom_site_anisotrop.B[3][3]_esd' conversion_constant '_atom_site.aniso_B[3][3]_esd' alternate_exclusive '_atom_site_anisotrop.B[3][3]_esd' alternate_exclusive '_atom_site_anisotrop.U[3][3]_esd' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_units.code angstroms_squared save_ save__atom_site.attached_hydrogens _item_description.description ; The number of hydrogen atoms attached to the atom at this site excluding any hydrogen atoms for which coordinates (measured or calculated) are given. ; _item.name '_atom_site.attached_hydrogens' _item.category_id atom_site _item.mandatory_code no _item_aliases.alias_name '_atom_site_attached_hydrogens' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 # _item_default.value 0 loop_ _item_range.maximum _item_range.minimum 8 8 8 0 0 0 _item_type.code int loop_ _item_examples.case _item_examples.detail 2 'water oxygen' 1 'hydroxyl oxygen' 4 'ammonium nitrogen' save_ save__atom_site.auth_asym_id _item_description.description ; An alternative identifier for _atom_site.label_asym_id that may be provided by an author in order to match the identification used in the publication that describes the structure. ; loop_ _item.name _item.category_id _item.mandatory_code '_atom_site.auth_asym_id' atom_site yes '_geom_angle.atom_site_auth_asym_id_1' geom_angle no '_geom_angle.atom_site_auth_asym_id_2' geom_angle no '_geom_angle.atom_site_auth_asym_id_3' geom_angle no '_geom_bond.atom_site_auth_asym_id_1' geom_bond no '_geom_bond.atom_site_auth_asym_id_2' geom_bond no '_geom_contact.atom_site_auth_asym_id_1' geom_contact no '_geom_contact.atom_site_auth_asym_id_2' geom_contact no '_geom_hbond.atom_site_auth_asym_id_A' geom_hbond no '_geom_hbond.atom_site_auth_asym_id_D' geom_hbond no '_geom_hbond.atom_site_auth_asym_id_H' geom_hbond no '_geom_torsion.atom_site_auth_asym_id_1' geom_torsion no '_geom_torsion.atom_site_auth_asym_id_2' geom_torsion no '_geom_torsion.atom_site_auth_asym_id_3' geom_torsion no '_geom_torsion.atom_site_auth_asym_id_4' geom_torsion no '_struct_conf.beg_auth_asym_id' struct_conf no '_struct_conf.end_auth_asym_id' struct_conf no '_struct_conn.ptnr1_auth_asym_id' struct_conn no '_struct_conn.ptnr2_auth_asym_id' struct_conn no '_struct_mon_nucl.auth_asym_id' struct_mon_nucl no '_struct_mon_prot.auth_asym_id' struct_mon_prot no '_struct_mon_prot_cis.auth_asym_id' struct_mon_prot_cis no '_struct_ncs_dom_lim.beg_auth_asym_id' struct_ncs_dom_lim no '_struct_ncs_dom_lim.end_auth_asym_id' struct_ncs_dom_lim no '_struct_sheet_range.beg_auth_asym_id' struct_sheet_range no '_struct_sheet_range.end_auth_asym_id' struct_sheet_range no '_struct_site_gen.auth_asym_id' struct_site_gen no loop_ _item_linked.child_name _item_linked.parent_name '_geom_angle.atom_site_auth_asym_id_1' '_atom_site.auth_asym_id' '_geom_angle.atom_site_auth_asym_id_2' '_atom_site.auth_asym_id' '_geom_angle.atom_site_auth_asym_id_3' '_atom_site.auth_asym_id' '_geom_bond.atom_site_auth_asym_id_1' '_atom_site.auth_asym_id' '_geom_bond.atom_site_auth_asym_id_2' '_atom_site.auth_asym_id' '_geom_contact.atom_site_auth_asym_id_1' '_atom_site.auth_asym_id' '_geom_contact.atom_site_auth_asym_id_2' '_atom_site.auth_asym_id' '_geom_hbond.atom_site_auth_asym_id_A' '_atom_site.auth_asym_id' '_geom_hbond.atom_site_auth_asym_id_D' '_atom_site.auth_asym_id' '_geom_hbond.atom_site_auth_asym_id_H' '_atom_site.auth_asym_id' '_geom_torsion.atom_site_auth_asym_id_1' '_atom_site.auth_asym_id' '_geom_torsion.atom_site_auth_asym_id_2' '_atom_site.auth_asym_id' '_geom_torsion.atom_site_auth_asym_id_3' '_atom_site.auth_asym_id' '_geom_torsion.atom_site_auth_asym_id_4' '_atom_site.auth_asym_id' '_struct_conf.beg_auth_asym_id' '_atom_site.auth_asym_id' '_struct_conf.end_auth_asym_id' '_atom_site.auth_asym_id' '_struct_conn.ptnr1_auth_asym_id' '_atom_site.auth_asym_id' '_struct_conn.ptnr2_auth_asym_id' '_atom_site.auth_asym_id' '_struct_mon_nucl.auth_asym_id' '_atom_site.auth_asym_id' '_struct_mon_prot.auth_asym_id' '_atom_site.auth_asym_id' '_struct_mon_prot_cis.auth_asym_id' '_atom_site.auth_asym_id' '_struct_ncs_dom_lim.beg_auth_asym_id' '_atom_site.auth_asym_id' '_struct_ncs_dom_lim.end_auth_asym_id' '_atom_site.auth_asym_id' '_struct_sheet_range.beg_auth_asym_id' '_atom_site.auth_asym_id' '_struct_sheet_range.end_auth_asym_id' '_atom_site.auth_asym_id' '_struct_site_gen.auth_asym_id' '_atom_site.auth_asym_id' _item_sub_category.id mm_atom_site_auth_label _item_type.code code save_ save__atom_site.auth_atom_id _item_description.description ; An alternative identifier for _atom_site.label_atom_id that may be provided by an author in order to match the identification used in the publication that describes the structure. ; loop_ _item.name _item.category_id _item.mandatory_code '_atom_site.auth_atom_id' atom_site no '_geom_angle.atom_site_auth_atom_id_1' geom_angle no '_geom_angle.atom_site_auth_atom_id_2' geom_angle no '_geom_angle.atom_site_auth_atom_id_3' geom_angle no '_geom_bond.atom_site_auth_atom_id_1' geom_bond no '_geom_bond.atom_site_auth_atom_id_2' geom_bond no '_geom_contact.atom_site_auth_atom_id_1' geom_contact no '_geom_contact.atom_site_auth_atom_id_2' geom_contact no '_geom_hbond.atom_site_auth_atom_id_A' geom_hbond no '_geom_hbond.atom_site_auth_atom_id_D' geom_hbond no '_geom_hbond.atom_site_auth_atom_id_H' geom_hbond no '_geom_torsion.atom_site_auth_atom_id_1' geom_torsion no '_geom_torsion.atom_site_auth_atom_id_2' geom_torsion no '_geom_torsion.atom_site_auth_atom_id_3' geom_torsion no '_geom_torsion.atom_site_auth_atom_id_4' geom_torsion no '_struct_conn.ptnr1_auth_atom_id' struct_conn no '_struct_conn.ptnr2_auth_atom_id' struct_conn no '_struct_sheet_hbond.range_1_beg_auth_atom_id' struct_sheet_hbond no '_struct_sheet_hbond.range_1_end_auth_atom_id' struct_sheet_hbond no '_struct_sheet_hbond.range_2_beg_auth_atom_id' struct_sheet_hbond no '_struct_sheet_hbond.range_2_end_auth_atom_id' struct_sheet_hbond no '_struct_site_gen.auth_atom_id' struct_site_gen no loop_ _item_linked.child_name _item_linked.parent_name '_geom_angle.atom_site_auth_atom_id_1' '_atom_site.auth_atom_id' '_geom_angle.atom_site_auth_atom_id_2' '_atom_site.auth_atom_id' '_geom_angle.atom_site_auth_atom_id_3' '_atom_site.auth_atom_id' '_geom_bond.atom_site_auth_atom_id_1' '_atom_site.auth_atom_id' '_geom_bond.atom_site_auth_atom_id_2' '_atom_site.auth_atom_id' '_geom_contact.atom_site_auth_atom_id_1' '_atom_site.auth_atom_id' '_geom_contact.atom_site_auth_atom_id_2' '_atom_site.auth_atom_id' '_geom_hbond.atom_site_auth_atom_id_A' '_atom_site.auth_atom_id' '_geom_hbond.atom_site_auth_atom_id_D' '_atom_site.auth_atom_id' '_geom_hbond.atom_site_auth_atom_id_H' '_atom_site.auth_atom_id' '_geom_torsion.atom_site_auth_atom_id_1' '_atom_site.auth_atom_id' '_geom_torsion.atom_site_auth_atom_id_2' '_atom_site.auth_atom_id' '_geom_torsion.atom_site_auth_atom_id_3' '_atom_site.auth_atom_id' '_geom_torsion.atom_site_auth_atom_id_4' '_atom_site.auth_atom_id' '_struct_conn.ptnr1_auth_atom_id' '_atom_site.auth_atom_id' '_struct_conn.ptnr2_auth_atom_id' '_atom_site.auth_atom_id' '_struct_sheet_hbond.range_1_beg_auth_atom_id' '_atom_site.auth_atom_id' '_struct_sheet_hbond.range_1_end_auth_atom_id' '_atom_site.auth_atom_id' '_struct_sheet_hbond.range_2_beg_auth_atom_id' '_atom_site.auth_atom_id' '_struct_sheet_hbond.range_2_end_auth_atom_id' '_atom_site.auth_atom_id' '_struct_site_gen.auth_atom_id' '_atom_site.auth_atom_id' _item_sub_category.id mm_atom_site_auth_label _item_type.code atcode save_ save__atom_site.auth_comp_id _item_description.description ; An alternative identifier for _atom_site.label_comp_id that may be provided by an author in order to match the identification used in the publication that describes the structure. ; loop_ _item.name _item.category_id _item.mandatory_code '_atom_site.auth_comp_id' atom_site no '_geom_angle.atom_site_auth_comp_id_1' geom_angle no '_geom_angle.atom_site_auth_comp_id_2' geom_angle no '_geom_angle.atom_site_auth_comp_id_3' geom_angle no '_geom_bond.atom_site_auth_comp_id_1' geom_bond no '_geom_bond.atom_site_auth_comp_id_2' geom_bond no '_geom_contact.atom_site_auth_comp_id_1' geom_contact no '_geom_contact.atom_site_auth_comp_id_2' geom_contact no '_geom_hbond.atom_site_auth_comp_id_A' geom_hbond no '_geom_hbond.atom_site_auth_comp_id_D' geom_hbond no '_geom_hbond.atom_site_auth_comp_id_H' geom_hbond no '_geom_torsion.atom_site_auth_comp_id_1' geom_torsion no '_geom_torsion.atom_site_auth_comp_id_2' geom_torsion no '_geom_torsion.atom_site_auth_comp_id_3' geom_torsion no '_geom_torsion.atom_site_auth_comp_id_4' geom_torsion no '_struct_conf.beg_auth_comp_id' struct_conf no '_struct_conf.end_auth_comp_id' struct_conf no '_struct_conn.ptnr1_auth_comp_id' struct_conn no '_struct_conn.ptnr2_auth_comp_id' struct_conn no '_struct_mon_nucl.auth_comp_id' struct_mon_nucl no '_struct_mon_prot.auth_comp_id' struct_mon_prot no '_struct_mon_prot_cis.auth_comp_id' struct_mon_prot_cis no '_struct_ncs_dom_lim.beg_auth_comp_id' struct_ncs_dom_lim no '_struct_ncs_dom_lim.end_auth_comp_id' struct_ncs_dom_lim no '_struct_sheet_range.beg_auth_comp_id' struct_sheet_range no '_struct_sheet_range.end_auth_comp_id' struct_sheet_range no '_struct_site_gen.auth_comp_id' struct_site_gen no loop_ _item_linked.child_name _item_linked.parent_name '_geom_angle.atom_site_auth_comp_id_1' '_atom_site.auth_comp_id' '_geom_angle.atom_site_auth_comp_id_2' '_atom_site.auth_comp_id' '_geom_angle.atom_site_auth_comp_id_3' '_atom_site.auth_comp_id' '_geom_bond.atom_site_auth_comp_id_1' '_atom_site.auth_comp_id' '_geom_bond.atom_site_auth_comp_id_2' '_atom_site.auth_comp_id' '_geom_contact.atom_site_auth_comp_id_1' '_atom_site.auth_comp_id' '_geom_contact.atom_site_auth_comp_id_2' '_atom_site.auth_comp_id' '_geom_hbond.atom_site_auth_comp_id_A' '_atom_site.auth_comp_id' '_geom_hbond.atom_site_auth_comp_id_D' '_atom_site.auth_comp_id' '_geom_hbond.atom_site_auth_comp_id_H' '_atom_site.auth_comp_id' '_geom_torsion.atom_site_auth_comp_id_1' '_atom_site.auth_comp_id' '_geom_torsion.atom_site_auth_comp_id_2' '_atom_site.auth_comp_id' '_geom_torsion.atom_site_auth_comp_id_3' '_atom_site.auth_comp_id' '_geom_torsion.atom_site_auth_comp_id_4' '_atom_site.auth_comp_id' '_struct_conf.beg_auth_comp_id' '_atom_site.auth_comp_id' '_struct_conf.end_auth_comp_id' '_atom_site.auth_comp_id' '_struct_conn.ptnr1_auth_comp_id' '_atom_site.auth_comp_id' '_struct_conn.ptnr2_auth_comp_id' '_atom_site.auth_comp_id' '_struct_mon_nucl.auth_comp_id' '_atom_site.auth_comp_id' '_struct_mon_prot.auth_comp_id' '_atom_site.auth_comp_id' '_struct_mon_prot_cis.auth_comp_id' '_atom_site.auth_comp_id' '_struct_ncs_dom_lim.beg_auth_comp_id' '_atom_site.auth_comp_id' '_struct_ncs_dom_lim.end_auth_comp_id' '_atom_site.auth_comp_id' '_struct_sheet_range.beg_auth_comp_id' '_atom_site.auth_comp_id' '_struct_sheet_range.end_auth_comp_id' '_atom_site.auth_comp_id' '_struct_site_gen.auth_comp_id' '_atom_site.auth_comp_id' _item_sub_category.id mm_atom_site_auth_label _item_type.code code save_ save__atom_site.auth_seq_id _item_description.description ; An alternative identifier for _atom_site.label_seq_id that may be provided by an author in order to match the identification used in the publication that describes the structure. Note that this is not necessarily a number, that the values do not have to be positive, and that the value does not have to correspond to the value of _atom_site.label_seq_id. The value of _atom_site.label_seq_id is required to be a sequential list of positive integers. The author may assign values to _atom_site.auth_seq_id in any desired way. For instance, the values may be used to relate this structure to a numbering scheme in a homologous structure, including sequence gaps or insertion codes. Alternatively, a scheme may be used for a truncated polymer that maintains the numbering scheme of the full length polymer. In all cases, the scheme used here must match the scheme used in the publication that describes the structure. ; loop_ _item.name _item.category_id _item.mandatory_code '_atom_site.auth_seq_id' atom_site no '_geom_angle.atom_site_auth_seq_id_1' geom_angle no '_geom_angle.atom_site_auth_seq_id_2' geom_angle no '_geom_angle.atom_site_auth_seq_id_3' geom_angle no '_geom_bond.atom_site_auth_seq_id_1' geom_bond no '_geom_bond.atom_site_auth_seq_id_2' geom_bond no '_geom_contact.atom_site_auth_seq_id_1' geom_contact no '_geom_contact.atom_site_auth_seq_id_2' geom_contact no '_geom_hbond.atom_site_auth_seq_id_A' geom_hbond no '_geom_hbond.atom_site_auth_seq_id_D' geom_hbond no '_geom_hbond.atom_site_auth_seq_id_H' geom_hbond no '_geom_torsion.atom_site_auth_seq_id_1' geom_torsion no '_geom_torsion.atom_site_auth_seq_id_2' geom_torsion no '_geom_torsion.atom_site_auth_seq_id_3' geom_torsion no '_geom_torsion.atom_site_auth_seq_id_4' geom_torsion no '_struct_conf.beg_auth_seq_id' struct_conf no '_struct_conf.end_auth_seq_id' struct_conf no '_struct_conn.ptnr1_auth_seq_id' struct_conn no '_struct_conn.ptnr2_auth_seq_id' struct_conn no '_struct_mon_nucl.auth_seq_id' struct_mon_nucl no '_struct_mon_prot.auth_seq_id' struct_mon_prot no '_struct_mon_prot_cis.auth_seq_id' struct_mon_prot_cis no '_struct_ncs_dom_lim.beg_auth_seq_id' struct_ncs_dom_lim no '_struct_ncs_dom_lim.end_auth_seq_id' struct_ncs_dom_lim no '_struct_sheet_hbond.range_1_beg_auth_seq_id' struct_sheet_hbond no '_struct_sheet_hbond.range_1_end_auth_seq_id' struct_sheet_hbond no '_struct_sheet_hbond.range_2_beg_auth_seq_id' struct_sheet_hbond no '_struct_sheet_hbond.range_2_end_auth_seq_id' struct_sheet_hbond no '_struct_sheet_range.beg_auth_seq_id' struct_sheet_range no '_struct_sheet_range.end_auth_seq_id' struct_sheet_range no '_struct_site_gen.auth_seq_id' struct_site_gen no loop_ _item_linked.child_name _item_linked.parent_name '_geom_angle.atom_site_auth_seq_id_1' '_atom_site.auth_seq_id' '_geom_angle.atom_site_auth_seq_id_2' '_atom_site.auth_seq_id' '_geom_angle.atom_site_auth_seq_id_3' '_atom_site.auth_seq_id' '_geom_bond.atom_site_auth_seq_id_1' '_atom_site.auth_seq_id' '_geom_bond.atom_site_auth_seq_id_2' '_atom_site.auth_seq_id' '_geom_contact.atom_site_auth_seq_id_1' '_atom_site.auth_seq_id' '_geom_contact.atom_site_auth_seq_id_2' '_atom_site.auth_seq_id' '_geom_hbond.atom_site_auth_seq_id_A' '_atom_site.auth_seq_id' '_geom_hbond.atom_site_auth_seq_id_D' '_atom_site.auth_seq_id' '_geom_hbond.atom_site_auth_seq_id_H' '_atom_site.auth_seq_id' '_geom_torsion.atom_site_auth_seq_id_1' '_atom_site.auth_seq_id' '_geom_torsion.atom_site_auth_seq_id_2' '_atom_site.auth_seq_id' '_geom_torsion.atom_site_auth_seq_id_3' '_atom_site.auth_seq_id' '_geom_torsion.atom_site_auth_seq_id_4' '_atom_site.auth_seq_id' '_struct_conf.beg_auth_seq_id' '_atom_site.auth_seq_id' '_struct_conf.end_auth_seq_id' '_atom_site.auth_seq_id' '_struct_conn.ptnr1_auth_seq_id' '_atom_site.auth_seq_id' '_struct_conn.ptnr2_auth_seq_id' '_atom_site.auth_seq_id' '_struct_mon_nucl.auth_seq_id' '_atom_site.auth_seq_id' '_struct_mon_prot.auth_seq_id' '_atom_site.auth_seq_id' '_struct_mon_prot_cis.auth_seq_id' '_atom_site.auth_seq_id' '_struct_ncs_dom_lim.beg_auth_seq_id' '_atom_site.auth_seq_id' '_struct_ncs_dom_lim.end_auth_seq_id' '_atom_site.auth_seq_id' '_struct_sheet_hbond.range_1_beg_auth_seq_id' '_atom_site.auth_seq_id' '_struct_sheet_hbond.range_1_end_auth_seq_id' '_atom_site.auth_seq_id' '_struct_sheet_hbond.range_2_beg_auth_seq_id' '_atom_site.auth_seq_id' '_struct_sheet_hbond.range_2_end_auth_seq_id' '_atom_site.auth_seq_id' '_struct_sheet_range.beg_auth_seq_id' '_atom_site.auth_seq_id' '_struct_sheet_range.end_auth_seq_id' '_atom_site.auth_seq_id' '_struct_site_gen.auth_seq_id' '_atom_site.auth_seq_id' _item_sub_category.id mm_atom_site_auth_label _item_type.code code save_ save__atom_site.B_equiv_geom_mean _item_description.description ; Equivalent isotropic atomic displacement parameter, B~eq~, in angstroms squared, calculated as the geometric mean of the anisotropic atomic displacement parameters. B~eq~ = (B~i~ B~j~ B~k~)^1/3^ B~n~ = the principal components of the orthogonalized B^ij^ The IUCr Commission on Nomenclature recommends against the use of B for reporting atomic displacement parameters. U, being directly proportional to B, is preferred. ; _item.name '_atom_site.B_equiv_geom_mean' _item.category_id atom_site _item.mandatory_code no _item_aliases.alias_name '_atom_site_B_equiv_geom_mean' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.B_equiv_geom_mean_esd' associated_esd '_atom_site.U_equiv_geom_mean' conversion_constant _item_type.code float _item_type_conditions.code esd _item_units.code 8pi2_angstroms_squared save_ save__atom_site.B_equiv_geom_mean_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site.B_equiv_geom_mean. ; _item.name '_atom_site.B_equiv_geom_mean_esd' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.B_equiv_geom_mean' associated_value '_atom_site.U_equiv_geom_mean' conversion_constant _item_type.code float _item_units.code 8pi2_angstroms_squared save_ save__atom_site.B_iso_or_equiv _item_description.description ; Isotropic atomic displacement parameter, or equivalent isotropic atomic displacement parameter, B~eq~, calculated from the anisotropic displacement parameters. B~eq~ = (1/3) sum~i~[sum~j~(B^ij^ A~i~ A~j~ a*~i~ a*~j~)] A = the real space cell lengths a* = the reciprocal space cell lengths B^ij^ = 8 pi^2^ U^ij^ Ref: Fischer, R. X. & Tillmanns, E. (1988). Acta Cryst. C44, 775-776. The IUCr Commission on Nomenclature recommends against the use of B for reporting atomic displacement parameters. U, being directly proportional to B, is preferred. ; _item.name '_atom_site.B_iso_or_equiv' _item.category_id atom_site _item.mandatory_code no _item_aliases.alias_name '_atom_site_B_iso_or_equiv' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 # loop_ # _item_range.maximum # _item_range.minimum . 0.0 # 0.0 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.B_iso_or_equiv_esd' associated_esd '_atom_site.U_iso_or_equiv' conversion_constant _item_type.code float _item_type_conditions.code esd _item_units.code 8pi2_angstroms_squared save_ save__atom_site.B_iso_or_equiv_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site.B_iso_or_equiv. ; _item.name '_atom_site.B_iso_or_equiv_esd' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.B_iso_or_equiv' associated_value '_atom_site.U_iso_or_equiv_esd' conversion_constant _item_type.code float _item_units.code 8pi2_angstroms_squared save_ save__atom_site.calc_attached_atom _item_description.description ; The _atom_site.id of the atom site to which the 'geometry-calculated' atom site is attached. ; _item.name '_atom_site.calc_attached_atom' _item.category_id atom_site _item.mandatory_code no _item_aliases.alias_name '_atom_site_calc_attached_atom' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code code save_ save__atom_site.calc_flag _item_description.description ; A standard code to signal whether the site coordinates have been determined from the intensities or calculated from the geometry of surrounding sites, or have been assigned dummy values. The abbreviation 'c' may be used in place of 'calc'. ; _item.name '_atom_site.calc_flag' _item.category_id atom_site _item.mandatory_code no _item_aliases.alias_name '_atom_site_calc_flag' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 # _item_default.value d _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail d 'determined from experimental measurements' calc 'calculated from molecular geometry' c 'abbreviation for "calc"' dum 'dummy site with meaningless coordinates' save_ save__atom_site.Cartn_x _item_description.description ; The x atom-site coordinate in angstroms specified according to a set of orthogonal Cartesian axes related to the cell axes as specified by the description given in _atom_sites.Cartn_transform_axes. ; _item.name '_atom_site.Cartn_x' _item.category_id atom_site _item.mandatory_code no _item_aliases.alias_name '_atom_site_Cartn_x' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_atom_site.Cartn_y' '_atom_site.Cartn_z' _item_related.related_name '_atom_site.Cartn_x_esd' _item_related.function_code associated_esd _item_sub_category.id cartesian_coordinate _item_type.code float _item_type_conditions.code esd _item_units.code angstroms save_ save__atom_site.Cartn_x_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site.Cartn_x. ; _item.name '_atom_site.Cartn_x_esd' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_dependent.dependent_name '_atom_site.Cartn_y_esd' '_atom_site.Cartn_z_esd' _item_related.related_name '_atom_site.Cartn_x' _item_related.function_code associated_value _item_sub_category.id cartesian_coordinate_esd _item_type.code float _item_units.code angstroms save_ save__atom_site.Cartn_y _item_description.description ; The y atom-site coordinate in angstroms specified according to a set of orthogonal Cartesian axes related to the cell axes as specified by the description given in _atom_sites.Cartn_transform_axes. ; _item.name '_atom_site.Cartn_y' _item.category_id atom_site _item.mandatory_code no _item_aliases.alias_name '_atom_site_Cartn_y' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_atom_site.Cartn_x' '_atom_site.Cartn_z' _item_related.related_name '_atom_site.Cartn_y_esd' _item_related.function_code associated_esd _item_sub_category.id cartesian_coordinate _item_type.code float _item_type_conditions.code esd _item_units.code angstroms save_ save__atom_site.Cartn_y_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site.Cartn_y. ; _item.name '_atom_site.Cartn_y_esd' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_dependent.dependent_name '_atom_site.Cartn_x_esd' '_atom_site.Cartn_z_esd' _item_related.related_name '_atom_site.Cartn_y' _item_related.function_code associated_value _item_sub_category.id cartesian_coordinate_esd _item_type.code float _item_units.code angstroms save_ save__atom_site.Cartn_z _item_description.description ; The z atom-site coordinate in angstroms specified according to a set of orthogonal Cartesian axes related to the cell axes as specified by the description given in _atom_sites.Cartn_transform_axes. ; _item.name '_atom_site.Cartn_z' _item.category_id atom_site _item.mandatory_code no _item_aliases.alias_name '_atom_site_Cartn_z' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_atom_site.Cartn_x' '_atom_site.Cartn_y' _item_related.related_name '_atom_site.Cartn_z_esd' _item_related.function_code associated_esd _item_sub_category.id cartesian_coordinate _item_type.code float _item_type_conditions.code esd _item_units.code angstroms save_ save__atom_site.Cartn_z_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site.Cartn_z. ; _item.name '_atom_site.Cartn_z_esd' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_dependent.dependent_name '_atom_site.Cartn_x_esd' '_atom_site.Cartn_y_esd' _item_related.related_name '_atom_site.Cartn_z' _item_related.function_code associated_value _item_sub_category.id cartesian_coordinate_esd _item_type.code float _item_units.code angstroms save_ save__atom_site.chemical_conn_number _item_description.description ; This data item is a pointer to _chemical_conn_atom.number in the CHEMICAL_CONN_ATOM category. ; _item.name '_atom_site.chemical_conn_number' _item.mandatory_code no _item_aliases.alias_name '_atom_site_chemical_conn_number' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 save_ save__atom_site.constraints _item_description.description ; A description of the constraints applied to parameters at this site during refinement. See also _atom_site.refinement_flags and _refine.ls_number_constraints. ; _item.name '_atom_site.constraints' _item.category_id atom_site _item.mandatory_code no _item_aliases.alias_name '_atom_site_constraints' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line _item_examples.case 'pop=1.0-pop(Zn3)' save_ save__atom_site.details _item_description.description ; A description of special aspects of this site. See also _atom_site.refinement_flags. ; _item.name '_atom_site.details' _item.category_id atom_site _item.mandatory_code no _item_aliases.alias_name '_atom_site_description' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'Ag/Si disordered' save_ save__atom_site.disorder_assembly _item_description.description ; A code which identifies a cluster of atoms that show long-range positional disorder but are locally ordered. Within each such cluster of atoms, _atom_site.disorder_group is used to identify the sites that are simultaneously occupied. This field is only needed if there is more than one cluster of disordered atoms showing independent local order. *** This data item would not in general be used in a macromolecular data block. *** ; _item.name '_atom_site.disorder_assembly' _item.category_id atom_site _item.mandatory_code no _item_aliases.alias_name '_atom_site_disorder_assembly' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code code save_ save__atom_site.disorder_group _item_description.description ; A code which identifies a group of positionally disordered atom sites that are locally simultaneously occupied. Atoms that are positionally disordered over two or more sites (e.g. the hydrogen atoms of a methyl group that exists in two orientations) can be assigned to two or more groups. Sites belonging to the same group are simultaneously occupied, but those belonging to different groups are not. A minus prefix (e.g. '-1') is used to indicate sites disordered about a special position. *** This data item would not in general be used in a macromolecular data block. *** ; _item.name '_atom_site.disorder_group' _item.category_id atom_site _item.mandatory_code no _item_aliases.alias_name '_atom_site_disorder_group' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_default.value . _item_type.code code save_ save__atom_site.footnote_id _item_description.description ; The value of _atom_site.footnote_id must match an ID specified by _atom_sites_footnote.id in the ATOM_SITES_FOOTNOTE list. ; _item.name '_atom_site.footnote_id' _item.mandatory_code no save_ save__atom_site.fract_x _item_description.description ; The x coordinate of the atom-site position specified as a fraction of _cell.length_a. ; _item.name '_atom_site.fract_x' _item.category_id atom_site _item.mandatory_code no _item_aliases.alias_name '_atom_site_fract_x' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_atom_site.fract_y' '_atom_site.fract_z' _item_related.related_name '_atom_site.fract_x_esd' _item_related.function_code associated_esd _item_sub_category.id fractional_coordinate _item_type.code float _item_type_conditions.code esd save_ save__atom_site.fract_x_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site.fract_x. ; _item.name '_atom_site.fract_x_esd' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_dependent.dependent_name '_atom_site.fract_y_esd' '_atom_site.fract_z_esd' _item_related.related_name '_atom_site.fract_x' _item_related.function_code associated_value _item_sub_category.id fractional_coordinate_esd _item_type.code float save_ save__atom_site.fract_y _item_description.description ; The y coordinate of the atom-site position specified as a fraction of _cell.length_b. ; _item.name '_atom_site.fract_y' _item.category_id atom_site _item.mandatory_code no _item_aliases.alias_name '_atom_site_fract_y' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_atom_site.fract_x' '_atom_site.fract_z' _item_related.related_name '_atom_site.fract_y_esd' _item_related.function_code associated_esd _item_sub_category.id fractional_coordinate _item_type.code float _item_type_conditions.code esd save_ save__atom_site.fract_y_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site.fract_y. ; _item.name '_atom_site.fract_y_esd' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_dependent.dependent_name '_atom_site.fract_x_esd' '_atom_site.fract_z_esd' _item_related.related_name '_atom_site.fract_y' _item_related.function_code associated_value _item_sub_category.id fractional_coordinate_esd _item_type.code float save_ save__atom_site.fract_z _item_description.description ; The z coordinate of the atom-site position specified as a fraction of _cell.length_c. ; _item.name '_atom_site.fract_z' _item.category_id atom_site _item.mandatory_code no _item_aliases.alias_name '_atom_site_fract_z' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_atom_site.fract_x' '_atom_site.fract_y' _item_related.related_name '_atom_site.fract_z_esd' _item_related.function_code associated_esd _item_sub_category.id fractional_coordinate _item_type.code float _item_type_conditions.code esd save_ save__atom_site.fract_z_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site.fract_z. ; _item.name '_atom_site.fract_z_esd' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_dependent.dependent_name '_atom_site.fract_x_esd' '_atom_site.fract_y_esd' _item_related.related_name '_atom_site.fract_z' _item_related.function_code associated_value _item_sub_category.id fractional_coordinate_esd _item_type.code float save_ save__atom_site.group_PDB _item_description.description ; The group of atoms to which the atom site belongs. This data item is provided for compatibility with the original Protein Data Bank format, and only for that purpose. ; _item.name '_atom_site.group_PDB' _item.category_id atom_site _item.mandatory_code no _item_type.code code loop_ _item_enumeration.value ATOM HETATM save_ save__atom_site.id _item_description.description ; The value of _atom_site.id must uniquely identify a record in the ATOM_SITE list. Note that this item need not be a number; it can be any unique identifier. This data item was introduced to provide compatibility between small-molecule and macromolecular CIFs. In a small-molecule CIF, _atom_site_label is the identifier for the atom. In a macromolecular CIF, the atom identifier is the aggregate of _atom_site.label_alt_id, _atom_site.label_asym_id, _atom_site.label_atom_id, _atom_site.label_comp_id and _atom_site.label_seq_id. For the two types of files to be compatible, a formal identifier for the category had to be introduced that was independent of the different modes of identifying the atoms. For compatibility with older CIFs, _atom_site_label is aliased to _atom_site.id. ; loop_ _item.name _item.category_id _item.mandatory_code '_atom_site.id' atom_site yes '_atom_site_anisotrop.id' atom_site_anisotrop yes '_geom_angle.atom_site_id_1' geom_angle yes '_geom_angle.atom_site_id_2' geom_angle yes '_geom_angle.atom_site_id_3' geom_angle yes '_geom_bond.atom_site_id_1' geom_bond yes '_geom_bond.atom_site_id_2' geom_bond yes '_geom_contact.atom_site_id_1' geom_contact yes '_geom_contact.atom_site_id_2' geom_contact yes '_geom_hbond.atom_site_id_A' geom_hbond yes '_geom_hbond.atom_site_id_D' geom_hbond yes '_geom_hbond.atom_site_id_H' geom_hbond yes '_geom_torsion.atom_site_id_1' geom_torsion yes '_geom_torsion.atom_site_id_2' geom_torsion yes '_geom_torsion.atom_site_id_3' geom_torsion yes '_geom_torsion.atom_site_id_4' geom_torsion yes _item_aliases.alias_name '_atom_site_label' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_linked.child_name _item_linked.parent_name '_atom_site_anisotrop.id' '_atom_site.id' '_geom_angle.atom_site_id_1' '_atom_site.id' '_geom_angle.atom_site_id_2' '_atom_site.id' '_geom_angle.atom_site_id_3' '_atom_site.id' '_geom_bond.atom_site_id_1' '_atom_site.id' '_geom_bond.atom_site_id_2' '_atom_site.id' '_geom_contact.atom_site_id_1' '_atom_site.id' '_geom_contact.atom_site_id_2' '_atom_site.id' '_geom_hbond.atom_site_id_A' '_atom_site.id' '_geom_hbond.atom_site_id_D' '_atom_site.id' '_geom_hbond.atom_site_id_H' '_atom_site.id' '_geom_torsion.atom_site_id_1' '_atom_site.id' '_geom_torsion.atom_site_id_2' '_atom_site.id' '_geom_torsion.atom_site_id_3' '_atom_site.id' '_geom_torsion.atom_site_id_4' '_atom_site.id' _item_type.code code loop_ _item_examples.case '5' 'C12' 'Ca3g28' 'Fe3+17' 'H*251' 'boron2a' 'C_a_phe_83_a_0' 'Zn_Zn_301_A_0' save_ save__atom_site.label_alt_id _item_description.description ; A component of the identifier for this atom site. For further details, see the definition of the ATOM_SITE_ALT category. This data item is a pointer to _atom_sites_alt.id in the ATOM_SITES_ALT category. ; _item.name '_atom_site.label_alt_id' _item.mandatory_code yes _item_sub_category.id mm_atom_site_label save_ save__atom_site.label_asym_id _item_description.description ; A component of the identifier for this atom site. For further details, see the definition of the STRUCT_ASYM category. This data item is a pointer to _struct_asym.id in the STRUCT_ASYM category. ; _item.name '_atom_site.label_asym_id' _item.mandatory_code yes _item_sub_category.id mm_atom_site_label save_ save__atom_site.label_atom_id _item_description.description ; A component of the identifier for this atom site. This data item is a pointer to _chem_comp_atom.atom_id in the CHEM_COMP_ATOM category. ; _item.name '_atom_site.label_atom_id' _item.mandatory_code yes _item_sub_category.id mm_atom_site_label save_ save__atom_site.label_comp_id _item_description.description ; A component of the identifier for this atom site. This data item is a pointer to _chem_comp.id in the CHEM_COMP category. ; _item.name '_atom_site.label_comp_id' _item.mandatory_code yes _item_sub_category.id mm_atom_site_label save_ save__atom_site.label_entity_id _item_description.description ; This data item is a pointer to _entity.id in the ENTITY category. ; _item.name '_atom_site.label_entity_id' _item.mandatory_code yes save_ save__atom_site.label_seq_id _item_description.description ; This data item is a pointer to _entity_poly_seq.num in the ENTITY_POLY_SEQ category. ; _item.name '_atom_site.label_seq_id' _item.mandatory_code yes save_ save__atom_site.occupancy _item_description.description ; The fraction of the atom type present at this site. The sum of the occupancies of all the atom types at this site may not significantly exceed 1.0 unless it is a dummy site. ; _item.name '_atom_site.occupancy' _item.category_id atom_site _item.mandatory_code no _item_aliases.alias_name '_atom_site_occupancy' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_default.value 1.0 # JDW 17-Apr-2003 - Unsupportable restriction. # loop_ # _item_range.maximum # _item_range.minimum 1.0 1.0 # 1.0 0.0 # 0.0 0.0 _item_related.related_name '_atom_site.occupancy_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd save_ save__atom_site.occupancy_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site.occupancy. ; _item.name '_atom_site.occupancy_esd' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 _item_related.related_name '_atom_site.occupancy' _item_related.function_code associated_value _item_type.code float save_ #save__atom_site.refinement_flags # _item_description.description #; A concatenated series of single-letter codes which indicate the # refinement restraints or constraints applied to this site. #; # _item.name '_atom_site.refinement_flags' # _item.category_id atom_site # _item.mandatory_code no # _item_aliases.alias_name '_atom_site_refinement_flags' # _item_aliases.dictionary cif_core.dic # _item_aliases.version 2.0.1 # _item_type.code ucode # loop_ # _item_enumeration.value # _item_enumeration.detail . # 'no refinement constraints' # S # 'special-position constraint on site' # G # 'rigid-group refinement of site' # R # 'riding atom site attached to non-riding atom' # D # 'distance or angle restraint on site' # T # 'thermal displacement constraints' # U # 'Uiso or Uij restraint (rigid bond)' # P # 'partial occupancy constraint' # save_ save__atom_site.restraints _item_description.description ; A description of restraints applied to specific parameters at this site during refinement. See also _atom_site.refinement_flags and _refine.ls_number_restraints. ; _item.name '_atom_site.restraints' _item.category_id atom_site _item.mandatory_code no _item_aliases.alias_name '_atom_site_restraints' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'restrained to planar ring' save_ save__atom_site.symmetry_multiplicity _item_description.description ; The multiplicity of a site due to the space-group symmetry as is given in International Tables for Crystallography Vol. A (2002). ; _item.name '_atom_site.symmetry_multiplicity' _item.category_id atom_site _item.mandatory_code no _item_aliases.alias_name '_atom_site_symmetry_multiplicity' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 192 192 192 1 1 1 _item_type.code int save_ save__atom_site.thermal_displace_type _item_description.description ; A standard code used to describe the type of atomic displacement parameters used for the site. ; _item.name '_atom_site.thermal_displace_type' _item.category_id atom_site _item.mandatory_code no _item_aliases.alias_name '_atom_site_thermal_displace_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail Uani 'anisotropic Uij' Uiso 'isotropic U' Uovl 'overall U' Umpe 'multipole expansion U' Bani 'anisotropic Bij' Biso 'isotropic B' Bovl 'overall B' save_ save__atom_site.type_symbol _item_description.description ; This data item is a pointer to _atom_type.symbol in the ATOM_TYPE category. ; _item.name '_atom_site.type_symbol' _item.mandatory_code yes _item_aliases.alias_name '_atom_site_type_symbol' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 save_ save__atom_site.U_equiv_geom_mean _item_description.description ; Equivalent isotropic atomic displacement parameter, U~eq~, in angstroms squared, calculated as the geometric mean of the anisotropic atomic displacement parameters. U~eq~ = (U~i~ U~j~ U~k~)^1/3^ U~n~ = the principal components of the orthogonalized U^ij^ ; _item.name '_atom_site.U_equiv_geom_mean' _item.category_id atom_site _item.mandatory_code no _item_aliases.alias_name '_atom_site_U_equiv_geom_mean' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 10.0 10.0 10.0 0.0 0.0 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.U_equiv_geom_mean_esd' associated_esd '_atom_site.B_equiv_geom_mean' conversion_constant _item_type.code float _item_type_conditions.code esd _item_units.code angstroms_squared save_ save__atom_site.U_equiv_geom_mean_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site.U_equiv_geom_mean. ; _item.name '_atom_site.U_equiv_geom_mean_esd' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.U_equiv_geom_mean' associated_value '_atom_site.B_equiv_geom_mean' conversion_constant _item_type.code float _item_units.code angstroms_squared save_ save__atom_site.U_iso_or_equiv _item_description.description ; Isotropic atomic displacement parameter, or equivalent isotropic atomic displacement parameter, U~eq~, calculated from anisotropic atomic displacement parameters. U~eq~ = (1/3) sum~i~[sum~j~(U^ij^ A~i~ A~j~ a*~i~ a*~j~)] A = the real space cell lengths a* = the reciprocal space cell lengths Ref: Fischer, R. X. & Tillmanns, E. (1988). Acta Cryst. C44, 775-776. ; _item.name '_atom_site.U_iso_or_equiv' _item.category_id atom_site _item.mandatory_code no _item_aliases.alias_name '_atom_site_U_iso_or_equiv' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 10.0 10.0 10.0 0.0 0.0 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.U_iso_or_equiv_esd' associated_esd '_atom_site.B_iso_or_equiv' conversion_constant _item_type.code float _item_type_conditions.code esd _item_units.code angstroms_squared save_ save__atom_site.U_iso_or_equiv_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site.U_iso_or_equiv. ; _item.name '_atom_site.U_iso_or_equiv_esd' _item.category_id atom_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site.U_iso_or_equiv' associated_value '_atom_site.B_iso_or_equiv_esd' conversion_constant _item_type.code float _item_units.code angstroms_squared save_ save__atom_site.Wyckoff_symbol _item_description.description ; The Wyckoff symbol (letter) as listed in the space-group tables of International Tables for Crystallography, Vol. A (2002). ; _item.name '_atom_site.Wyckoff_symbol' _item.category_id atom_site _item.mandatory_code no _item_aliases.alias_name '_atom_site_Wyckoff_symbol' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ ######################### ## ATOM_SITE_ANISOTROP ## ######################### save_atom_site_anisotrop _category.description ; Data items in the ATOM_SITE_ANISOTROP category record details about anisotropic displacement parameters. If the ATOM_SITE_ANISOTROP category is used for storing these data, the corresponding ATOM_SITE data items are not used. ; _category.id atom_site_anisotrop _category.mandatory_code no _category_key.name '_atom_site_anisotrop.id' loop_ _category_group.id 'inclusive_group' 'atom_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on NDB structure BDL005 of Holbrook, Dickerson & Kim [Acta Cryst. (1985), B41, 255-262]. ; ; loop_ _atom_site_anisotrop.id _atom_site_anisotrop.type_symbol _atom_site_anisotrop.U[1][1] _atom_site_anisotrop.U[1][2] _atom_site_anisotrop.U[1][3] _atom_site_anisotrop.U[2][2] _atom_site_anisotrop.U[2][3] _atom_site_anisotrop.U[3][3] 1 O 8642 4866 7299 -342 -258 -1427 2 C 5174 4871 6243 -1885 -2051 -1377 3 C 6202 5020 4395 -1130 -556 -632 4 O 4224 4700 5046 1105 -161 345 5 C 8684 4688 4171 -1850 -433 -292 6 O 11226 5255 3532 -341 2685 1328 7 C 10214 2428 5614 -2610 -1940 902 8 C 4590 3488 5827 751 -770 986 9 N 5014 4434 3447 -17 -1593 539 # ---- abbreviated ---- ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__atom_site_anisotrop.B[1][1] _item_description.description ; The [1][1] element of the anisotropic atomic displacement matrix B, which appears in the structure-factor term as: T = exp{-1/4 sum~i~[sum~j~(B^ij^ h~i~ h~j~ a*~i~ a*~j~)]} h = the Miller indices a* = the reciprocal space cell lengths These matrix elements may appear with atomic coordinates in the ATOM_SITE category, or they may appear in the separate ATOM_SITE_ANISOTROP category, but they may not appear in both places. Similarly, anisotropic displacements may appear as either B's or U's, but not as both. The unique elements of the real symmetric matrix are entered by row. The IUCr Commission on Nomenclature recommends against the use of B for reporting atomic displacement parameters. U, being directly proportional to B, is preferred. ; _item.name '_atom_site_anisotrop.B[1][1]' _item.category_id atom_site_anisotrop _item.mandatory_code no _item_aliases.alias_name '_atom_site_aniso_B_11' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_related.related_name _item_related.function_code '_atom_site_anisotrop.B[1][1]_esd' associated_esd '_atom_site.aniso_U[1][1]' conversion_constant '_atom_site_anisotrop.U[1][1]' conversion_constant '_atom_site.aniso_B[1][1]' alternate_exclusive '_atom_site.aniso_U[1][1]' alternate_exclusive '_atom_site_anisotrop.U[1][1]' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_type_conditions.code esd _item_units.code 8pi2_angstroms_squared save_ save__atom_site_anisotrop.B[1][1]_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site_anisotrop.B[1][1]. ; _item.name '_atom_site_anisotrop.B[1][1]_esd' _item.category_id atom_site_anisotrop _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site_anisotrop.B[1][1]' associated_value '_atom_site.aniso_U[1][1]_esd' conversion_constant '_atom_site_anisotrop.U[1][1]_esd' conversion_constant '_atom_site.aniso_B[1][1]_esd' alternate_exclusive '_atom_site.aniso_U[1][1]_esd' alternate_exclusive '_atom_site_anisotrop.U[1][1]_esd' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_units.code 8pi2_angstroms_squared save_ save__atom_site_anisotrop.B[1][2] _item_description.description ; The [1][2] element of the anisotropic atomic displacement matrix B, which appears in the structure-factor term as: T = exp{-1/4 sum~i~[sum~j~(B^ij^ h~i~ h~j~ a*~i~ a*~j~)]} h = the Miller indices a* = the reciprocal space cell lengths These matrix elements may appear with atomic coordinates in the ATOM_SITE category, or they may appear in the separate ATOM_SITE_ANISOTROP category, but they may not appear in both places. Similarly, anisotropic displacements may appear as either B's or U's, but not as both. The unique elements of the real symmetric matrix are entered by row. The IUCr Commission on Nomenclature recommends against the use of B for reporting atomic displacement parameters. U, being directly proportional to B, is preferred. ; _item.name '_atom_site_anisotrop.B[1][2]' _item.category_id atom_site_anisotrop _item.mandatory_code no _item_aliases.alias_name '_atom_site_aniso_B_12' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_related.related_name _item_related.function_code '_atom_site_anisotrop.B[1][2]_esd' associated_esd '_atom_site.aniso_U[1][2]' conversion_constant '_atom_site_anisotrop.U[1][2]' conversion_constant '_atom_site.aniso_B[1][2]' alternate_exclusive '_atom_site.aniso_U[1][2]' alternate_exclusive '_atom_site_anisotrop.U[1][2]' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_type_conditions.code esd _item_units.code 8pi2_angstroms_squared save_ save__atom_site_anisotrop.B[1][2]_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site_anisotrop.B[1][2]. ; _item.name '_atom_site_anisotrop.B[1][2]_esd' _item.category_id atom_site_anisotrop _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site_anisotrop.B[1][2]' associated_value '_atom_site.aniso_U[1][2]_esd' conversion_constant '_atom_site_anisotrop.U[1][2]_esd' conversion_constant '_atom_site.aniso_B[1][2]_esd' alternate_exclusive '_atom_site.aniso_U[1][2]_esd' alternate_exclusive '_atom_site_anisotrop.U[1][2]_esd' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_units.code 8pi2_angstroms_squared save_ save__atom_site_anisotrop.B[1][3] _item_description.description ; The [1][3] element of the anisotropic atomic displacement matrix B, which appears in the structure-factor term as: T = exp{-1/4 sum~i~[sum~j~(B^ij^ h~i~ h~j~ a*~i~ a*~j~)]} h = the Miller indices a* = the reciprocal space cell lengths These matrix elements may appear with atomic coordinates in the ATOM_SITE category, or they may appear in the separate ATOM_SITE_ANISOTROP category, but they may not appear in both places. Similarly, anisotropic displacements may appear as either B's or U's, but not as both. The unique elements of the real symmetric matrix are entered by row. The IUCr Commission on Nomenclature recommends against the use of B for reporting atomic displacement parameters. U, being directly proportional to B, is preferred. ; _item.name '_atom_site_anisotrop.B[1][3]' _item.category_id atom_site_anisotrop _item.mandatory_code no _item_aliases.alias_name '_atom_site_aniso_B_13' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_related.related_name _item_related.function_code '_atom_site_anisotrop.B[1][3]_esd' associated_esd '_atom_site.aniso_U[1][3]' conversion_constant '_atom_site_anisotrop.U[1][3]' conversion_constant '_atom_site.aniso_B[1][3]' alternate_exclusive '_atom_site.aniso_U[1][3]' alternate_exclusive '_atom_site_anisotrop.U[1][3]' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_type_conditions.code esd _item_units.code 8pi2_angstroms_squared save_ save__atom_site_anisotrop.B[1][3]_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site_anisotrop.B[1][3]. ; _item.name '_atom_site_anisotrop.B[1][3]_esd' _item.category_id atom_site_anisotrop _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site_anisotrop.B[1][3]' associated_value '_atom_site.aniso_U[1][3]_esd' conversion_constant '_atom_site_anisotrop.U[1][3]_esd' conversion_constant '_atom_site.aniso_B[1][3]_esd' alternate_exclusive '_atom_site.aniso_U[1][3]_esd' alternate_exclusive '_atom_site_anisotrop.U[1][3]_esd' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_units.code 8pi2_angstroms_squared save_ save__atom_site_anisotrop.B[2][2] _item_description.description ; The [2][2] element of the anisotropic atomic displacement matrix B, which appears in the structure-factor term as: T = exp{-1/4 sum~i~[sum~j~(B^ij^ h~i~ h~j~ a*~i~ a*~j~)]} h = the Miller indices a* = the reciprocal space cell lengths These matrix elements may appear with atomic coordinates in the ATOM_SITE category, or they may appear in the separate ATOM_SITE_ANISOTROP category, but they may not appear in both places. Similarly, anisotropic displacements may appear as either B's or U's, but not as both. The unique elements of the real symmetric matrix are entered by row. The IUCr Commission on Nomenclature recommends against the use of B for reporting atomic displacement parameters. U, being directly proportional to B, is preferred. ; _item.name '_atom_site_anisotrop.B[2][2]' _item.category_id atom_site_anisotrop _item.mandatory_code no _item_aliases.alias_name '_atom_site_aniso_B_22' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_related.related_name _item_related.function_code '_atom_site_anisotrop.B[2][2]_esd' associated_esd '_atom_site.aniso_U[2][2]' conversion_constant '_atom_site_anisotrop.U[2][2]' conversion_constant '_atom_site.aniso_B[2][2]' alternate_exclusive '_atom_site.aniso_U[2][2]' alternate_exclusive '_atom_site_anisotrop.U[2][2]' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_type_conditions.code esd _item_units.code 8pi2_angstroms_squared save_ save__atom_site_anisotrop.B[2][2]_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site_anisotrop.B[2][2]. ; _item.name '_atom_site_anisotrop.B[2][2]_esd' _item.category_id atom_site_anisotrop _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site_anisotrop.B[2][2]' associated_value '_atom_site.aniso_U[2][2]_esd' conversion_constant '_atom_site_anisotrop.U[2][2]_esd' conversion_constant '_atom_site.aniso_B[2][2]_esd' alternate_exclusive '_atom_site.aniso_U[2][2]_esd' alternate_exclusive '_atom_site_anisotrop.U[2][2]_esd' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_units.code 8pi2_angstroms_squared save_ save__atom_site_anisotrop.B[2][3] _item_description.description ; The [2][3] element of the anisotropic atomic displacement matrix B, which appears in the structure-factor term as: T = exp{-1/4 sum~i~[sum~j~(B^ij^ h~i~ h~j~ a*~i~ a*~j~)]} h = the Miller indices a* = the reciprocal space cell lengths These matrix elements may appear with atomic coordinates in the ATOM_SITE category, or they may appear in the separate ATOM_SITE_ANISOTROP category, but they may not appear in both places. Similarly, anisotropic displacements may appear as either B's or U's, but not as both. The unique elements of the real symmetric matrix are entered by row. The IUCr Commission on Nomenclature recommends against the use of B for reporting atomic displacement parameters. U, being directly proportional to B, is preferred. ; _item.name '_atom_site_anisotrop.B[2][3]' _item.category_id atom_site_anisotrop _item.mandatory_code no _item_aliases.alias_name '_atom_site_aniso_B_23' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_related.related_name _item_related.function_code '_atom_site_anisotrop.B[2][3]_esd' associated_esd '_atom_site.aniso_U[2][3]' conversion_constant '_atom_site_anisotrop.U[2][3]' conversion_constant '_atom_site.aniso_B[2][3]' alternate_exclusive '_atom_site.aniso_U[2][3]' alternate_exclusive '_atom_site_anisotrop.U[2][3]' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_type_conditions.code esd _item_units.code 8pi2_angstroms_squared save_ save__atom_site_anisotrop.B[2][3]_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site_anisotrop.B[2][3]. ; _item.name '_atom_site_anisotrop.B[2][3]_esd' _item.category_id atom_site_anisotrop _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site_anisotrop.B[2][3]' associated_value '_atom_site.aniso_U[2][3]_esd' conversion_constant '_atom_site_anisotrop.U[2][3]_esd' conversion_constant '_atom_site.aniso_B[2][3]_esd' alternate_exclusive '_atom_site.aniso_U[2][3]_esd' alternate_exclusive '_atom_site_anisotrop.U[2][3]_esd' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_units.code 8pi2_angstroms_squared save_ save__atom_site_anisotrop.B[3][3] _item_description.description ; The [3][3] element of the anisotropic atomic displacement matrix B, which appears in the structure-factor term as: T = exp{-1/4 sum~i~[sum~j~(B^ij^ h~i~ h~j~ a*~i~ a*~j~)]} h = the Miller indices a* = the reciprocal space cell lengths These matrix elements may appear with atomic coordinates in the ATOM_SITE category, or they may appear in the separate ATOM_SITE_ANISOTROP category, but they may not appear in both places. Similarly, anisotropic displacements may appear as either B's or U's, but not as both. The unique elements of the real symmetric matrix are entered by row. The IUCr Commission on Nomenclature recommends against the use of B for reporting atomic displacement parameters. U, being directly proportional to B, is preferred. ; _item.name '_atom_site_anisotrop.B[3][3]' _item.category_id atom_site_anisotrop _item.mandatory_code no _item_aliases.alias_name '_atom_site_aniso_B_33' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_related.related_name _item_related.function_code '_atom_site_anisotrop.B[3][3]_esd' associated_esd '_atom_site.aniso_U[3][3]' conversion_constant '_atom_site_anisotrop.U[3][3]' conversion_constant '_atom_site.aniso_B[3][3]' alternate_exclusive '_atom_site.aniso_U[3][3]' alternate_exclusive '_atom_site_anisotrop.U[3][3]' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_type_conditions.code esd _item_units.code 8pi2_angstroms_squared save_ save__atom_site_anisotrop.B[3][3]_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site_anisotrop.B[3][3]. ; _item.name '_atom_site_anisotrop.B[3][3]_esd' _item.category_id atom_site_anisotrop _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site_anisotrop.B[3][3]' associated_value '_atom_site.aniso_U[3][3]_esd' conversion_constant '_atom_site_anisotrop.U[3][3]_esd' conversion_constant '_atom_site.aniso_B[3][3]_esd' alternate_exclusive '_atom_site.aniso_U[3][3]_esd' alternate_exclusive '_atom_site_anisotrop.U[3][3]_esd' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_units.code 8pi2_angstroms_squared save_ save__atom_site_anisotrop.ratio _item_description.description ; Ratio of the maximum to minimum principal axes of displacement (thermal) ellipsoids. ; _item.name '_atom_site_anisotrop.ratio' _item.category_id atom_site_anisotrop _item.mandatory_code no _item_aliases.alias_name '_atom_site_aniso_ratio' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 1.0 1.0 1.0 _item_related.related_name '_atom_site.aniso_ratio' _item_related.function_code alternate_exclusive _item_type.code float save_ save__atom_site_anisotrop.id _item_description.description ; This data item is a pointer to _atom_site.id in the ATOM_SITE category. ; _item.name '_atom_site_anisotrop.id' _item.mandatory_code yes _item_aliases.alias_name '_atom_site_aniso_label' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 save_ save__atom_site_anisotrop.type_symbol _item_description.description ; This data item is a pointer to _atom_type.symbol in the ATOM_TYPE category. ; _item.name '_atom_site_anisotrop.type_symbol' _item.mandatory_code yes _item_aliases.alias_name '_atom_site_aniso_type_symbol' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 save_ save__atom_site_anisotrop.U[1][1] _item_description.description ; The [1][1] element of the standard anisotropic atomic displacement matrix U, which appears in the structure-factor term as: T = exp{-2 pi^2^ sum~i~[sum~j~(U^ij^ h~i~ h~j~ a*~i~ a*~j~)]} h = the Miller indices a* = the reciprocal space cell lengths These matrix elements may appear with atomic coordinates in the ATOM_SITE category, or they may appear in the separate ATOM_SITE_ANISOTROP category, but they may not appear in both places. Similarly, anisotropic displacements may appear as either B's or U's, but not as both. The unique elements of the real symmetric matrix are entered by row. ; _item.name '_atom_site_anisotrop.U[1][1]' _item.category_id atom_site_anisotrop _item.mandatory_code no _item_aliases.alias_name '_atom_site_aniso_U_11' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_related.related_name _item_related.function_code '_atom_site_anisotrop.U[1][1]_esd' associated_esd '_atom_site.aniso_B[1][1]' conversion_constant '_atom_site_anisotrop.B[1][1]' conversion_constant '_atom_site.aniso_B[1][1]' alternate_exclusive '_atom_site.aniso_U[1][1]' alternate_exclusive '_atom_site_anisotrop.B[1][1]' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_type_conditions.code esd _item_units.code angstroms_squared save_ save__atom_site_anisotrop.U[1][1]_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site_anisotrop.U[1][1]. ; _item.name '_atom_site_anisotrop.U[1][1]_esd' _item.category_id atom_site_anisotrop _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site_anisotrop.U[1][1]' associated_value '_atom_site.aniso_B[1][1]_esd' conversion_constant '_atom_site_anisotrop.B[1][1]_esd' conversion_constant '_atom_site.aniso_B[1][1]_esd' alternate_exclusive '_atom_site.aniso_U[1][1]_esd' alternate_exclusive '_atom_site_anisotrop.B[1][1]_esd' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_units.code angstroms_squared save_ save__atom_site_anisotrop.U[1][2] _item_description.description ; The [1][2] element of the standard anisotropic atomic displacement matrix U, which appears in the structure-factor term as: T = exp{-2 pi^2^ sum~i~[sum~j~(U^ij^ h~i~ h~j~ a*~i~ a*~j~)]} h = the Miller indices a* = the reciprocal space cell lengths These matrix elements may appear with atomic coordinates in the ATOM_SITE category, or they may appear in the separate ATOM_SITE_ANISOTROP category, but they may not appear in both places. Similarly, anisotropic displacements may appear as either B's or U's, but not as both. The unique elements of the real symmetric matrix are entered by row. ; _item.name '_atom_site_anisotrop.U[1][2]' _item.category_id atom_site_anisotrop _item.mandatory_code no _item_aliases.alias_name '_atom_site_aniso_U_12' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_related.related_name _item_related.function_code '_atom_site_anisotrop.U[1][2]_esd' associated_esd '_atom_site.aniso_B[1][2]' conversion_constant '_atom_site_anisotrop.B[1][2]' conversion_constant '_atom_site.aniso_B[1][2]' alternate_exclusive '_atom_site.aniso_U[1][2]' alternate_exclusive '_atom_site_anisotrop.B[1][2]' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_type_conditions.code esd _item_units.code angstroms_squared save_ save__atom_site_anisotrop.U[1][2]_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site_anisotrop.U[1][2]. ; _item.name '_atom_site_anisotrop.U[1][2]_esd' _item.category_id atom_site_anisotrop _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site_anisotrop.U[1][2]' associated_value '_atom_site.aniso_B[1][2]_esd' conversion_constant '_atom_site_anisotrop.B[1][2]_esd' conversion_constant '_atom_site.aniso_B[1][2]_esd' alternate_exclusive '_atom_site.aniso_U[1][2]_esd' alternate_exclusive '_atom_site_anisotrop.B[1][2]_esd' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_units.code angstroms_squared save_ save__atom_site_anisotrop.U[1][3] _item_description.description ; The [1][3] element of the standard anisotropic atomic displacement matrix U, which appears in the structure-factor term as: T = exp{-2 pi^2^ sum~i~[sum~j~(U^ij^ h~i~ h~j~ a*~i~ a*~j~)]} h = the Miller indices a* = the reciprocal space cell lengths These matrix elements may appear with atomic coordinates in the ATOM_SITE category, or they may appear in the separate ATOM_SITE_ANISOTROP category, but they may not appear in both places. Similarly, anisotropic displacements may appear as either B's or U's, but not as both. The unique elements of the real symmetric matrix are entered by row. ; _item.name '_atom_site_anisotrop.U[1][3]' _item.category_id atom_site_anisotrop _item.mandatory_code no _item_aliases.alias_name '_atom_site_aniso_U_13' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_related.related_name _item_related.function_code '_atom_site_anisotrop.U[1][3]_esd' associated_esd '_atom_site.aniso_B[1][3]' conversion_constant '_atom_site_anisotrop.B[1][3]' conversion_constant '_atom_site.aniso_B[1][3]' alternate_exclusive '_atom_site.aniso_U[1][3]' alternate_exclusive '_atom_site_anisotrop.B[1][3]' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_type_conditions.code esd _item_units.code angstroms_squared save_ save__atom_site_anisotrop.U[1][3]_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site_anisotrop.U[1][3]. ; _item.name '_atom_site_anisotrop.U[1][3]_esd' _item.category_id atom_site_anisotrop _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site_anisotrop.U[1][3]' associated_value '_atom_site.aniso_B[1][3]_esd' conversion_constant '_atom_site_anisotrop.B[1][3]_esd' conversion_constant '_atom_site.aniso_B[1][3]_esd' alternate_exclusive '_atom_site.aniso_U[1][3]_esd' alternate_exclusive '_atom_site_anisotrop.B[1][3]_esd' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_units.code angstroms_squared save_ save__atom_site_anisotrop.U[2][2] _item_description.description ; The [2][2] element of the standard anisotropic atomic displacement matrix U, which appears in the structure-factor term as: T = exp{-2 pi^2^ sum~i~[sum~j~(U^ij^ h~i~ h~j~ a*~i~ a*~j~)]} h = the Miller indices a* = the reciprocal space cell lengths These matrix elements may appear with atomic coordinates in the ATOM_SITE category, or they may appear in the separate ATOM_SITE_ANISOTROP category, but they may not appear in both places. Similarly, anisotropic displacements may appear as either B's or U's, but not as both. The unique elements of the real symmetric matrix are entered by row. ; _item.name '_atom_site_anisotrop.U[2][2]' _item.category_id atom_site_anisotrop _item.mandatory_code no _item_aliases.alias_name '_atom_site_aniso_U_22' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_related.related_name _item_related.function_code '_atom_site_anisotrop.U[2][2]_esd' associated_esd '_atom_site.aniso_B[2][2]' conversion_constant '_atom_site_anisotrop.B[2][2]' conversion_constant '_atom_site.aniso_B[2][2]' alternate_exclusive '_atom_site.aniso_U[2][2]' alternate_exclusive '_atom_site_anisotrop.B[2][2]' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_type_conditions.code esd _item_units.code angstroms_squared save_ save__atom_site_anisotrop.U[2][2]_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site_anisotrop.U[2][2]. ; _item.name '_atom_site_anisotrop.U[2][2]_esd' _item.category_id atom_site_anisotrop _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site_anisotrop.U[2][2]' associated_value '_atom_site.aniso_B[2][2]_esd' conversion_constant '_atom_site_anisotrop.B[2][2]_esd' conversion_constant '_atom_site.aniso_B[2][2]_esd' alternate_exclusive '_atom_site.aniso_U[2][2]_esd' alternate_exclusive '_atom_site_anisotrop.B[2][2]_esd' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_units.code angstroms_squared save_ save__atom_site_anisotrop.U[2][3] _item_description.description ; The [2][3] element of the standard anisotropic atomic displacement matrix U, which appears in the structure-factor term as: T = exp{-2 pi^2^ sum~i~[sum~j~(U^ij^ h~i~ h~j~ a*~i~ a*~j~)]} h = the Miller indices a* = the reciprocal space cell lengths These matrix elements may appear with atomic coordinates in the ATOM_SITE category, or they may appear in the separate ATOM_SITE_ANISOTROP category, but they may not appear in both places. Similarly, anisotropic displacements may appear as either B's or U's, but not as both. The unique elements of the real symmetric matrix are entered by row. ; _item.name '_atom_site_anisotrop.U[2][3]' _item.category_id atom_site_anisotrop _item.mandatory_code no _item_aliases.alias_name '_atom_site_aniso_U_23' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_related.related_name _item_related.function_code '_atom_site_anisotrop.U[2][3]_esd' associated_esd '_atom_site.aniso_B[2][3]' conversion_constant '_atom_site_anisotrop.B[2][3]' conversion_constant '_atom_site.aniso_B[2][3]' alternate_exclusive '_atom_site.aniso_U[2][3]' alternate_exclusive '_atom_site_anisotrop.B[2][3]' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_type_conditions.code esd _item_units.code angstroms_squared save_ save__atom_site_anisotrop.U[2][3]_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site_anisotrop.U[2][3]. ; _item.name '_atom_site_anisotrop.U[2][3]_esd' _item.category_id atom_site_anisotrop _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site_anisotrop.U[2][3]' associated_value '_atom_site.aniso_B[2][3]_esd' conversion_constant '_atom_site_anisotrop.B[2][3]_esd' conversion_constant '_atom_site.aniso_B[2][3]_esd' alternate_exclusive '_atom_site.aniso_U[2][3]_esd' alternate_exclusive '_atom_site_anisotrop.B[2][3]_esd' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_units.code angstroms_squared save_ save__atom_site_anisotrop.U[3][3] _item_description.description ; The [3][3] element of the standard anisotropic atomic displacement matrix U, which appears in the structure-factor term as: T = exp{-2 pi^2^ sum~i~[sum~j~(U^ij^ h~i~ h~j~ a*~i~ a*~j~)]} h = the Miller indices a* = the reciprocal space cell lengths These matrix elements may appear with atomic coordinates in the ATOM_SITE category, or they may appear in the separate ATOM_SITE_ANISOTROP category, but they may not appear in both places. Similarly, anisotropic displacements may appear as either B's or U's, but not as both. The unique elements of the real symmetric matrix are entered by row. ; _item.name '_atom_site_anisotrop.U[3][3]' _item.category_id atom_site_anisotrop _item.mandatory_code no _item_aliases.alias_name '_atom_site_aniso_U_33' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_related.related_name _item_related.function_code '_atom_site_anisotrop.U[3][3]_esd' associated_esd '_atom_site.aniso_B[3][3]' conversion_constant '_atom_site_anisotrop.B[3][3]' conversion_constant '_atom_site.aniso_B[3][3]' alternate_exclusive '_atom_site.aniso_U[3][3]' alternate_exclusive '_atom_site_anisotrop.B[3][3]' alternate_exclusive _item_sub_category.id matrix _item_type.code float _item_type_conditions.code esd _item_units.code angstroms_squared save_ save__atom_site_anisotrop.U[3][3]_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _atom_site_anisotrop.U[3][3]. ; _item.name '_atom_site_anisotrop.U[3][3]_esd' _item.category_id atom_site_anisotrop _item.mandatory_code no # _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_atom_site_anisotrop.U[3][3]' associated_value '_atom_site.aniso_B[3][3]_esd' conversion_constant '_atom_site_anisotrop.B[3][3]_esd' conversion_constant '_atom_site.aniso_B[3][3]_esd' alternate_exclusive '_atom_site.aniso_U[3][3]_esd' alternate_exclusive '_atom_site_anisotrop.B[3][3]_esd' alternate_exclusive _item_type.code float _item_units.code angstroms_squared save_ ################ ## ATOM_SITES ## ################ save_atom_sites _category.description ; Data items in the ATOM_SITES category record details about the crystallographic cell and cell transformations, which are common to all atom sites. ; _category.id atom_sites _category.mandatory_code no _category_key.name '_atom_sites.entry_id' loop_ _category_group.id 'inclusive_group' 'atom_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _atom_sites.entry_id '5HVP' _atom_sites.Cartn_transform_axes 'c along z, astar along x, b along y' _atom_sites.Cartn_transf_matrix[1][1] 58.39 _atom_sites.Cartn_transf_matrix[1][2] 0.00 _atom_sites.Cartn_transf_matrix[1][3] 0.00 _atom_sites.Cartn_transf_matrix[2][1] 0.00 _atom_sites.Cartn_transf_matrix[2][2] 86.70 _atom_sites.Cartn_transf_matrix[2][3] 0.00 _atom_sites.Cartn_transf_matrix[3][1] 0.00 _atom_sites.Cartn_transf_matrix[3][2] 0.00 _atom_sites.Cartn_transf_matrix[3][3] 46.27 _atom_sites.Cartn_transf_vector[1] 0.00 _atom_sites.Cartn_transf_vector[2] 0.00 _atom_sites.Cartn_transf_vector[3] 0.00 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__atom_sites.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_atom_sites.entry_id' _item.mandatory_code yes save_ save__atom_sites.Cartn_transf_matrix[1][1] _item_description.description ; The [1][1] element of the 3x3 matrix used to transform fractional coordinates in the ATOM_SITE category to Cartesian coordinates in the same category. The axial alignments of this transformation are described in _atom_sites.Cartn_transform_axes. The 3x1 translation is defined in _atom_sites.Cartn_transf_vector[]. |x'| |11 12 13| |x| |1| |y'|~Cartesian~ = |21 22 23| |y|~fractional~ + |2| |z'| |31 32 33| |z| |3| ; _item.name '_atom_sites.Cartn_transf_matrix[1][1]' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_Cartn_tran_matrix_11' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__atom_sites.Cartn_transf_matrix[1][2] _item_description.description ; The [1][2] element of the 3x3 matrix used to transform fractional coordinates in the ATOM_SITE category to Cartesian coordinates in the same category. The axial alignments of this transformation are described in _atom_sites.Cartn_transform_axes. The 3x1 translation is defined in _atom_sites.Cartn_transf_vector[]. |x'| |11 12 13| |x| |1| |y'|~Cartesian~ = |21 22 23| |y|~fractional~ + |2| |z'| |31 32 33| |z| |3| ; _item.name '_atom_sites.Cartn_transf_matrix[1][2]' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_Cartn_tran_matrix_12' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__atom_sites.Cartn_transf_matrix[1][3] _item_description.description ; The [1][3] element of the 3x3 matrix used to transform fractional coordinates in the ATOM_SITE category to Cartesian coordinates in the same category. The axial alignments of this transformation are described in _atom_sites.Cartn_transform_axes. The 3x1 translation is defined in _atom_sites.Cartn_transf_vector[]. |x'| |11 12 13| |x| |1| |y'|~Cartesian~ = |21 22 23| |y|~fractional~ + |2| |z'| |31 32 33| |z| |3| ; _item.name '_atom_sites.Cartn_transf_matrix[1][3]' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_Cartn_tran_matrix_13' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__atom_sites.Cartn_transf_matrix[2][1] _item_description.description ; The [2][1] element of the 3x3 matrix used to transform fractional coordinates in the ATOM_SITE category to Cartesian coordinates in the same category. The axial alignments of this transformation are described in _atom_sites.Cartn_transform_axes. The 3x1 translation is defined in _atom_sites.Cartn_transf_vector[]. |x'| |11 12 13| |x| |1| |y'|~Cartesian~ = |21 22 23| |y|~fractional~ + |2| |z'| |31 32 33| |z| |3| ; _item.name '_atom_sites.Cartn_transf_matrix[2][1]' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_Cartn_tran_matrix_21' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__atom_sites.Cartn_transf_matrix[2][2] _item_description.description ; The [2][2] element of the 3x3 matrix used to transform fractional coordinates in the ATOM_SITE category to Cartesian coordinates in the same category. The axial alignments of this transformation are described in _atom_sites.Cartn_transform_axes. The 3x1 translation is defined in _atom_sites.Cartn_transf_vector[]. |x'| |11 12 13| |x| |1| |y'|~Cartesian~ = |21 22 23| |y|~fractional~ + |2| |z'| |31 32 33| |z| |3| ; _item.name '_atom_sites.Cartn_transf_matrix[2][2]' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_Cartn_tran_matrix_22' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__atom_sites.Cartn_transf_matrix[2][3] _item_description.description ; The [2][3] element of the 3x3 matrix used to transform fractional coordinates in the ATOM_SITE category to Cartesian coordinates in the same category. The axial alignments of this transformation are described in _atom_sites.Cartn_transform_axes. The 3x1 translation is defined in _atom_sites.Cartn_transf_vector[]. |x'| |11 12 13| |x| |1| |y'|~Cartesian~ = |21 22 23| |y|~fractional~ + |2| |z'| |31 32 33| |z| |3| ; _item.name '_atom_sites.Cartn_transf_matrix[2][3]' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_Cartn_tran_matrix_23' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__atom_sites.Cartn_transf_matrix[3][1] _item_description.description ; The [3][1] element of the 3x3 matrix used to transform fractional coordinates in the ATOM_SITE category to Cartesian coordinates in the same category. The axial alignments of this transformation are described in _atom_sites.Cartn_transform_axes. The 3x1 translation is defined in _atom_sites.Cartn_transf_vector[]. |x'| |11 12 13| |x| |1| |y'|~Cartesian~ = |21 22 23| |y|~fractional~ + |2| |z'| |31 32 33| |z| |3| ; _item.name '_atom_sites.Cartn_transf_matrix[3][1]' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_Cartn_tran_matrix_31' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__atom_sites.Cartn_transf_matrix[3][2] _item_description.description ; The [3][2] element of the 3x3 matrix used to transform fractional coordinates in the ATOM_SITE category to Cartesian coordinates in the same category. The axial alignments of this transformation are described in _atom_sites.Cartn_transform_axes. The 3x1 translation is defined in _atom_sites.Cartn_transf_vector[]. |x'| |11 12 13| |x| |1| |y'|~Cartesian~ = |21 22 23| |y|~fractional~ + |2| |z'| |31 32 33| |z| |3| ; _item.name '_atom_sites.Cartn_transf_matrix[3][2]' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_Cartn_tran_matrix_32' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__atom_sites.Cartn_transf_matrix[3][3] _item_description.description ; The [3][3] element of the 3x3 matrix used to transform fractional coordinates in the ATOM_SITE category to Cartesian coordinates in the same category. The axial alignments of this transformation are described in _atom_sites.Cartn_transform_axes. The 3x1 translation is defined in _atom_sites.Cartn_transf_vector[]. |x'| |11 12 13| |x| |1| |y'|~Cartesian~ = |21 22 23| |y|~fractional~ + |2| |z'| |31 32 33| |z| |3| ; _item.name '_atom_sites.Cartn_transf_matrix[3][3]' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_Cartn_tran_matrix_33' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__atom_sites.Cartn_transf_vector[1] _item_description.description ; The [1] element of the three-element vector used to transform fractional coordinates in the ATOM_SITE category to Cartesian coordinates in the same category. The axial alignments of this transformation are described in _atom_sites.Cartn_transform_axes. The rotation matrix is defined in _atom_sites.Cartn_transf_matrix[][]. |x'| |11 12 13| |x| |1| |y'|~Cartesian~ = |21 22 23| |y|~fractional~ + |2| |z'| |31 32 33| |z| |3| ; _item.name '_atom_sites.Cartn_transf_vector[1]' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_Cartn_tran_vector_1' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 # _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__atom_sites.Cartn_transf_vector[2] _item_description.description ; The [2] element of the three-element vector used to transform fractional coordinates in the ATOM_SITE category to Cartesian coordinates in the same category. The axial alignments of this transformation are described in _atom_sites.Cartn_transform_axes. The rotation matrix is defined in _atom_sites.Cartn_transf_matrix[][]. |x'| |11 12 13| |x| |1| |y'|~Cartesian~ = |21 22 23| |y|~fractional~ + |2| |z'| |31 32 33| |z| |3| ; _item.name '_atom_sites.Cartn_transf_vector[2]' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_Cartn_tran_vector_2' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 # _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__atom_sites.Cartn_transf_vector[3] _item_description.description ; The [3] element of the three-element vector used to transform fractional coordinates in the ATOM_SITE category to Cartesian coordinates in the same category. The axial alignments of this transformation are described in _atom_sites.Cartn_transform_axes. The rotation matrix is defined in _atom_sites.Cartn_transf_matrix[][]. |x'| |11 12 13| |x| |1| |y'|~Cartesian~ = |21 22 23| |y|~fractional~ + |2| |z'| |31 32 33| |z| |3| ; _item.name '_atom_sites.Cartn_transf_vector[3]' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_Cartn_tran_vector_3' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 # _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__atom_sites.Cartn_transform_axes _item_description.description ; A description of the relative alignment of the crystal cell axes to the Cartesian orthogonal axes as applied in the transformation matrix _atom_sites.Cartn_transf_matrix[][]. ; _item.name '_atom_sites.Cartn_transform_axes' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_Cartn_transform_axes' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'a parallel to x; b in the plane of y and z' save_ save__atom_sites.fract_transf_matrix[1][1] _item_description.description ; The [1][1] element of the 3x3 matrix used to transform Cartesian coordinates in the ATOM_SITE category to fractional coordinates in the same category. The axial alignments of this transformation are described in _atom_sites.Cartn_transform_axes. The 3x1 translation is defined in _atom_sites.fract_transf_vector[]. |x'| |11 12 13| |x| |1| |y'|~fractional~ = |21 22 23| |y|~Cartesian~ + |2| |z'| |31 32 33| |z| |3| ; _item.name '_atom_sites.fract_transf_matrix[1][1]' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_fract_tran_matrix_11' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__atom_sites.fract_transf_matrix[1][2] _item_description.description ; The [1][2] element of the 3x3 matrix used to transform Cartesian coordinates in the ATOM_SITE category to fractional coordinates in the same category. The axial alignments of this transformation are described in _atom_sites.Cartn_transform_axes. The 3x1 translation is defined in _atom_sites.fract_transf_vector[]. |x'| |11 12 13| |x| |1| |y'|~fractional~ = |21 22 23| |y|~Cartesian~ + |2| |z'| |31 32 33| |z| |3| ; _item.name '_atom_sites.fract_transf_matrix[1][2]' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_fract_tran_matrix_12' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__atom_sites.fract_transf_matrix[1][3] _item_description.description ; The [1][3] element of the 3x3 matrix used to transform Cartesian coordinates in the ATOM_SITE category to fractional coordinates in the same category. The axial alignments of this transformation are described in _atom_sites.Cartn_transform_axes. The 3x1 translation is defined in _atom_sites.fract_transf_vector[]. |x'| |11 12 13| |x| |1| |y'|~fractional~ = |21 22 23| |y|~Cartesian~ + |2| |z'| |31 32 33| |z| |3| ; _item.name '_atom_sites.fract_transf_matrix[1][3]' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_fract_tran_matrix_13' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__atom_sites.fract_transf_matrix[2][1] _item_description.description ; The [2][1] element of the 3x3 matrix used to transform Cartesian coordinates in the ATOM_SITE category to fractional coordinates in the same category. The axial alignments of this transformation are described in _atom_sites.Cartn_transform_axes. The 3x1 translation is defined in _atom_sites.fract_transf_vector[]. |x'| |11 12 13| |x| |1| |y'|~fractional~ = |21 22 23| |y|~Cartesian~ + |2| |z'| |31 32 33| |z| |3| ; _item.name '_atom_sites.fract_transf_matrix[2][1]' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_fract_tran_matrix_21' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__atom_sites.fract_transf_matrix[2][2] _item_description.description ; The [2][2] element of the 3x3 matrix used to transform Cartesian coordinates in the ATOM_SITE category to fractional coordinates in the same category. The axial alignments of this transformation are described in _atom_sites.Cartn_transform_axes. The 3x1 translation is defined in _atom_sites.fract_transf_vector[]. |x'| |11 12 13| |x| |1| |y'|~fractional~ = |21 22 23| |y|~Cartesian~ + |2| |z'| |31 32 33| |z| |3| ; _item.name '_atom_sites.fract_transf_matrix[2][2]' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_fract_tran_matrix_22' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__atom_sites.fract_transf_matrix[2][3] _item_description.description ; The [2][3] element of the 3x3 matrix used to transform Cartesian coordinates in the ATOM_SITE category to fractional coordinates in the same category. The axial alignments of this transformation are described in _atom_sites.Cartn_transform_axes. The 3x1 translation is defined in _atom_sites.fract_transf_vector[]. |x'| |11 12 13| |x| |1| |y'|~fractional~ = |21 22 23| |y|~Cartesian~ + |2| |z'| |31 32 33| |z| |3| ; _item.name '_atom_sites.fract_transf_matrix[2][3]' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_fract_tran_matrix_23' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__atom_sites.fract_transf_matrix[3][1] _item_description.description ; The [3][1] element of the 3x3 matrix used to transform Cartesian coordinates in the ATOM_SITE category to fractional coordinates in the same category. The axial alignments of this transformation are described in _atom_sites.Cartn_transform_axes. The 3x1 translation is defined in _atom_sites.fract_transf_vector[]. |x'| |11 12 13| |x| |1| |y'|~fractional~ = |21 22 23| |y|~Cartesian~ + |2| |z'| |31 32 33| |z| |3| ; _item.name '_atom_sites.fract_transf_matrix[3][1]' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_fract_tran_matrix_31' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__atom_sites.fract_transf_matrix[3][2] _item_description.description ; The [3][2] element of the 3x3 matrix used to transform Cartesian coordinates in the ATOM_SITE category to fractional coordinates in the same category. The axial alignments of this transformation are described in _atom_sites.Cartn_transform_axes. The 3x1 translation is defined in _atom_sites.fract_transf_vector[]. |x'| |11 12 13| |x| |1| |y'|~fractional~ = |21 22 23| |y|~Cartesian~ + |2| |z'| |31 32 33| |z| |3| ; _item.name '_atom_sites.fract_transf_matrix[3][2]' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_fract_tran_matrix_32' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__atom_sites.fract_transf_matrix[3][3] _item_description.description ; The [3][3] element of the 3x3 matrix used to transform Cartesian coordinates in the ATOM_SITE category to fractional coordinates in the same category. The axial alignments of this transformation are described in _atom_sites.Cartn_transform_axes. The 3x1 translation is defined in _atom_sites.fract_transf_vector[]. |x'| |11 12 13| |x| |1| |y'|~fractional~ = |21 22 23| |y|~Cartesian~ + |2| |z'| |31 32 33| |z| |3| ; _item.name '_atom_sites.fract_transf_matrix[3][3]' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_fract_tran_matrix_33' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__atom_sites.fract_transf_vector[1] _item_description.description ; The [1] element of the three-element vector used to transform Cartesian coordinates in the ATOM_SITE category to fractional coordinates in the same category. The axial alignments of this transformation are described in _atom_sites.Cartn_transform_axes. The 3x3 rotation is defined in _atom_sites.fract_transf_matrix[][]. |x'| |11 12 13| |x| |1| |y'|~fractional~ = |21 22 23| |y|~Cartesian~ + |2| |z'| |31 32 33| |z| |3| ; _item.name '_atom_sites.fract_transf_vector[1]' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_fract_tran_vector_1' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 # _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__atom_sites.fract_transf_vector[2] _item_description.description ; The [2] element of the three-element vector used to transform Cartesian coordinates in the ATOM_SITE category to fractional coordinates in the same category. The axial alignments of this transformation are described in _atom_sites.Cartn_transform_axes. The 3x3 rotation is defined in _atom_sites.fract_transf_matrix[][]. |x'| |11 12 13| |x| |1| |y'|~fractional~ = |21 22 23| |y|~Cartesian~ + |2| |z'| |31 32 33| |z| |3| ; _item.name '_atom_sites.fract_transf_vector[2]' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_fract_tran_vector_2' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 # _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__atom_sites.fract_transf_vector[3] _item_description.description ; The [3] element of the three-element vector used to transform Cartesian coordinates in the ATOM_SITE category to fractional coordinates in the same category. The axial alignments of this transformation are described in _atom_sites.Cartn_transform_axes. The 3x3 rotation is defined in _atom_sites.fract_transf_matrix[][]. |x'| |11 12 13| |x| |1| |y'|~fractional~ = |21 22 23| |y|~Cartesian~ + |2| |z'| |31 32 33| |z| |3| ; _item.name '_atom_sites.fract_transf_vector[3]' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_fract_tran_vector_3' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 # _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__atom_sites.solution_primary _item_description.description ; This code identifies the method used to locate the initial atom sites. *** This data item would not in general be used in a macromolecular data block. *** ; _item.name '_atom_sites.solution_primary' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_solution_primary' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail difmap 'difference Fourier map' vecmap 'real-space vector search' heavy 'heavy-atom method' direct 'structure-invariant direct methods' geom 'inferred from neighbouring sites' disper 'anomalous-dispersion techniques' isomor 'isomorphous structure methods' save_ save__atom_sites.solution_secondary _item_description.description ; This code identifies the method used to locate the non-hydrogen-atom sites not found by _atom_sites.solution_primary. *** This data item would not in general be used in a macromolecular data block. *** ; _item.name '_atom_sites.solution_secondary' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_solution_secondary' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail difmap 'difference Fourier map' vecmap 'real-space vector search' heavy 'heavy-atom method' direct 'structure-invariant direct methods' geom 'inferred from neighbouring sites' disper 'anomalous-dispersion techniques' isomor 'isomorphous structure methods' save_ save__atom_sites.solution_hydrogens _item_description.description ; This code identifies the method used to locate the hydrogen atoms. *** This data item would not in general be used in a macromolecular data block. *** ; _item.name '_atom_sites.solution_hydrogens' _item.category_id atom_sites _item.mandatory_code no _item_aliases.alias_name '_atom_sites_solution_hydrogens' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail difmap 'difference Fourier map' vecmap 'real-space vector search' heavy 'heavy-atom method' direct 'structure-invariant direct methods' geom 'inferred from neighbouring sites' disper 'anomalous-dispersion techniques' isomor 'isomorphous structure methods' save_ #################### ## ATOM_SITES_ALT ## #################### save_atom_sites_alt _category.description ; Data items in the ATOM_SITES_ALT category record details about the structural ensembles that should be generated from atom sites or groups of atom sites that are modelled in alternative conformations in this data block. ; _category.id atom_sites_alt _category.mandatory_code no _category_key.name '_atom_sites_alt.id' loop_ _category_group.id 'inclusive_group' 'atom_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _atom_sites_alt.id _atom_sites_alt.details . ; Atom sites with the alternative ID set to null are not modeled in alternative conformations ; 1 ; Atom sites with the alternative ID set to 1 have been modeled in alternative conformations with respect to atom sites marked with alternative ID 2. The conformations of amino-acid side chains and solvent atoms with alternative ID set to 1 correlate with the conformation of the inhibitor marked with alternative ID 1. They have been given an occupancy of 0.58 to match the occupancy assigned to the inhibitor. ; 2 ; Atom sites with the alternative ID set to 2 have been modeled in alternative conformations with respect to atom sites marked with alternative ID 1. The conformations of amino-acid side chains and solvent atoms with alternative ID set to 2 correlate with the conformation of the inhibitor marked with alternative ID 2. They have been given an occupancy of 0.42 to match the occupancy assigned to the inhibitor. ; 3 ; Atom sites with the alternative ID set to 3 have been modeled in alternative conformations with respect to atoms marked with alternative ID 4. The conformations of amino-acid side chains and solvent atoms with alternative ID set to 3 do not correlate with the conformation of the inhibitor. These atom sites have arbitrarily been given an occupancy of 0.50. ; 4 ; Atom sites with the alternative ID set to 4 have been modeled in alternative conformations with respect to atoms marked with alternative ID 3. The conformations of amino-acid side chains and solvent atoms with alternative ID set to 4 do not correlate with the conformation of the inhibitor. These atom sites have arbitrarily been given an occupancy of 0.50. ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__atom_sites_alt.details _item_description.description ; A description of special aspects of the modelling of atoms in alternative conformations. ; _item.name '_atom_sites_alt.details' _item.category_id atom_sites_alt _item.mandatory_code no _item_type.code text save_ save__atom_sites_alt.id _item_description.description ; The value of _atom_sites_alt.id must uniquely identify a record in the ATOM_SITES_ALT list. Note that this item need not be a number; it can be any unique identifier. ; loop_ _item.name _item.category_id _item.mandatory_code '_atom_sites_alt.id' atom_sites_alt yes '_atom_site.label_alt_id' atom_site no '_atom_sites_alt_gen.alt_id' atom_sites_alt_gen yes '_geom_angle.atom_site_label_alt_id_1' geom_angle no '_geom_angle.atom_site_label_alt_id_2' geom_angle no '_geom_angle.atom_site_label_alt_id_3' geom_angle no '_geom_bond.atom_site_label_alt_id_1' geom_bond no '_geom_bond.atom_site_label_alt_id_2' geom_bond no '_geom_contact.atom_site_label_alt_id_1' geom_contact no '_geom_contact.atom_site_label_alt_id_2' geom_contact no '_geom_hbond.atom_site_label_alt_id_A' geom_hbond no '_geom_hbond.atom_site_label_alt_id_D' geom_hbond no '_geom_hbond.atom_site_label_alt_id_H' geom_hbond no '_geom_torsion.atom_site_label_alt_id_1' geom_torsion no '_geom_torsion.atom_site_label_alt_id_2' geom_torsion no '_geom_torsion.atom_site_label_alt_id_3' geom_torsion no '_geom_torsion.atom_site_label_alt_id_4' geom_torsion no '_struct_conn.ptnr1_label_alt_id' struct_conn no '_struct_conn.ptnr2_label_alt_id' struct_conn no '_struct_mon_nucl.label_alt_id' struct_mon_nucl yes '_struct_mon_prot.label_alt_id' struct_mon_prot yes '_struct_mon_prot_cis.label_alt_id' struct_mon_prot_cis yes '_struct_ncs_dom_lim.beg_label_alt_id' struct_ncs_dom_lim yes '_struct_ncs_dom_lim.end_label_alt_id' struct_ncs_dom_lim yes '_struct_site_gen.label_alt_id' struct_site_gen yes loop_ _item_linked.child_name _item_linked.parent_name '_atom_site.label_alt_id' '_atom_sites_alt.id' '_atom_sites_alt_gen.alt_id' '_atom_sites_alt.id' '_geom_angle.atom_site_label_alt_id_1' '_atom_site.label_alt_id' '_geom_angle.atom_site_label_alt_id_2' '_atom_site.label_alt_id' '_geom_angle.atom_site_label_alt_id_3' '_atom_site.label_alt_id' '_geom_bond.atom_site_label_alt_id_1' '_atom_site.label_alt_id' '_geom_bond.atom_site_label_alt_id_2' '_atom_site.label_alt_id' '_geom_contact.atom_site_label_alt_id_1' '_atom_site.label_alt_id' '_geom_contact.atom_site_label_alt_id_2' '_atom_site.label_alt_id' '_geom_hbond.atom_site_label_alt_id_A' '_atom_site.label_alt_id' '_geom_hbond.atom_site_label_alt_id_D' '_atom_site.label_alt_id' '_geom_hbond.atom_site_label_alt_id_H' '_atom_site.label_alt_id' '_geom_torsion.atom_site_label_alt_id_1' '_atom_site.label_alt_id' '_geom_torsion.atom_site_label_alt_id_2' '_atom_site.label_alt_id' '_geom_torsion.atom_site_label_alt_id_3' '_atom_site.label_alt_id' '_geom_torsion.atom_site_label_alt_id_4' '_atom_site.label_alt_id' '_struct_conn.ptnr1_label_alt_id' '_atom_site.label_alt_id' '_struct_conn.ptnr2_label_alt_id' '_atom_site.label_alt_id' '_struct_mon_nucl.label_alt_id' '_atom_site.label_alt_id' '_struct_mon_prot.label_alt_id' '_atom_site.label_alt_id' '_struct_mon_prot_cis.label_alt_id' '_atom_site.label_alt_id' '_struct_ncs_dom_lim.beg_label_alt_id' '_atom_site.label_alt_id' '_struct_ncs_dom_lim.end_label_alt_id' '_atom_site.label_alt_id' '_struct_site_gen.label_alt_id' '_atom_site.label_alt_id' _item_type.code code loop_ _item_examples.case 'orientation 1' 'molecule abc' save_ ######################## ## ATOM_SITES_ALT_ENS ## ######################## save_atom_sites_alt_ens _category.description ; Data items in the ATOM_SITES_ALT_ENS category record details about the ensemble structure generated from atoms with various alternative conformation IDs. ; _category.id atom_sites_alt_ens _category.mandatory_code no _category_key.name '_atom_sites_alt_ens.id' loop_ _category_group.id 'inclusive_group' 'atom_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _atom_sites_alt_ens.id _atom_sites_alt_ens.details 'Ensemble 1-A' ; The inhibitor binds to the enzyme in two, roughly twofold symmetric alternative conformations. This conformational ensemble includes the more populated conformation of the inhibitor (ID=1) and the amino-acid side chains and solvent structure that correlate with this inhibitor conformation. Also included are one set (ID=3) of side chains with alternative conformations when the conformations are not correlated with the inhibitor conformation. ; 'Ensemble 1-B' ; The inhibitor binds to the enzyme in two, roughly twofold symmetric alternative conformations. This conformational ensemble includes the more populated conformation of the inhibitor (ID=1) and the amino-acid side chains and solvent structure that correlate with this inhibitor conformation. Also included are one set (ID=4) of side chains with alternative conformations when the conformations are not correlated with the inhibitor conformation. ; 'Ensemble 2-A' ; The inhibitor binds to the enzyme in two, roughly twofold symmetric alternative conformations. This conformational ensemble includes the less populated conformation of the inhibitor (ID=2) and the amino-acid side chains and solvent structure that correlate with this inhibitor conformation. Also included are one set (ID=3) of side chains with alternative conformations when the conformations are not correlated with the inhibitor conformation. ; 'Ensemble 2-B' ; The inhibitor binds to the enzyme in two, roughly twofold symmetric alternative conformations. This conformational ensemble includes the less populated conformation of the inhibitor (ID=2) and the amino-acid side chains and solvent structure that correlate with this inhibitor conformation. Also included are one set (ID=4) of side chains with alternative conformations when the conformations are not correlated with the inhibitor conformation. ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__atom_sites_alt_ens.details _item_description.description ; A description of special aspects of the ensemble structure generated from atoms with various alternative IDs. ; _item.name '_atom_sites_alt_ens.details' _item.category_id atom_sites_alt_ens _item.mandatory_code no _item_type.code text save_ save__atom_sites_alt_ens.id _item_description.description ; The value of _atom_sites_alt_ens.id must uniquely identify a record in the ATOM_SITES_ALT_ENS list. Note that this item need not be a number; it can be any unique identifier. ; loop_ _item.name _item.category_id _item.mandatory_code '_atom_sites_alt_ens.id' atom_sites_alt_ens yes '_atom_sites_alt_gen.ens_id' atom_sites_alt_gen yes loop_ _item_linked.child_name _item_linked.parent_name '_atom_sites_alt_gen.ens_id' '_atom_sites_alt_ens.id' _item_type.code code save_ ######################## ## ATOM_SITES_ALT_GEN ## ######################## save_atom_sites_alt_gen _category.description ; Data items in the ATOM_SITES_ALT_GEN category record details about the interpretation of multiple conformations in the structure. ; _category.id atom_sites_alt_gen _category.mandatory_code no loop_ _category_key.name '_atom_sites_alt_gen.ens_id' '_atom_sites_alt_gen.alt_id' loop_ _category_group.id 'inclusive_group' 'atom_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _atom_sites_alt_gen.ens_id _atom_sites_alt_gen.alt_id 'Ensemble 1-A' . 'Ensemble 1-A' 1 'Ensemble 1-A' 3 'Ensemble 1-B' . 'Ensemble 1-B' 1 'Ensemble 1-B' 4 'Ensemble 2-A' . 'Ensemble 2-A' 2 'Ensemble 2-A' 3 'Ensemble 2-B' . 'Ensemble 2-B' 2 'Ensemble 2-B' 4 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__atom_sites_alt_gen.alt_id _item_description.description ; This data item is a pointer to _atom_sites_alt.id in the ATOM_SITES_ALT category. ; _item.name '_atom_sites_alt_gen.alt_id' _item.mandatory_code yes save_ save__atom_sites_alt_gen.ens_id _item_description.description ; This data item is a pointer to _atom_sites_alt_ens.id in the ATOM_SITES_ALT_ENS category. ; _item.name '_atom_sites_alt_gen.ens_id' _item.mandatory_code yes save_ ######################### ## ATOM_SITES_FOOTNOTE ## ######################### save_atom_sites_footnote _category.description ; Data items in the ATOM_SITES_FOOTNOTE category record detailed comments about an atom site or a group of atom sites. ; _category.id atom_sites_footnote _category.mandatory_code no _category_key.name '_atom_sites_footnote.id' loop_ _category_group.id 'inclusive_group' 'atom_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _atom_sites_footnote.id _atom_sites_footnote.text 1 ; The inhibitor binds to the enzyme in two alternative orientations. The two orientations have been assigned alternative IDs *1* and *2*. ; 2 ; Side chains of these residues adopt alternative orientations that correlate with the alternative orientations of the inhibitor. Side chains with alternative ID *1* and occupancy 0.58 correlate with inhibitor orientation *1*. Side chains with alternative ID *2* and occupancy 0.42 correlate with inhibitor orientation *2*. ; 3 ; The positions of these water molecules correlate with the alternative orientations of the inhibitor. Water molecules with alternative ID *1* and occupancy 0.58 correlate with inhibitor orientation *1*. Water molecules with alternative ID *2* and occupancy 0.42 correlate with inhibitor orientation *2*. ; 4 ; Side chains of these residues adopt alternative orientations that do not correlate with the alternative orientation of the inhibitor. ; 5 ; The positions of these water molecules correlate with alternative orientations of amino-acid side chains that do not correlate with alternative orientations of the inhibitor. ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__atom_sites_footnote.id _item_description.description ; A code that identifies the footnote. ; loop_ _item.name _item.category_id _item.mandatory_code '_atom_sites_footnote.id' atom_sites_footnote yes '_atom_site.footnote_id' atom_site no loop_ _item_linked.child_name _item_linked.parent_name '_atom_site.footnote_id' '_atom_sites_footnote.id' _item_type.code code loop_ _item_examples.case 'a' 'b' '1' '2' save_ save__atom_sites_footnote.text _item_description.description ; The text of the footnote. Footnotes are used to describe an atom site or a group of atom sites in the ATOM_SITE list. For example, footnotes may be used to indicate atoms for which the electron density is very weak, or atoms for which static disorder has been modelled. ; _item.name '_atom_sites_footnote.text' _item.category_id atom_sites_footnote _item.mandatory_code no _item_type.code text save_ ############### ## ATOM_TYPE ## ############### save_atom_type _category.description ; Data items in the ATOM_TYPE category record details about the properties of the atoms that occupy the atom sites, such as the atomic scattering factors. ; _category.id atom_type _category.mandatory_code no _category_key.name '_atom_type.symbol' loop_ _category_group.id 'inclusive_group' 'atom_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _atom_type.symbol _atom_type.oxidation_number _atom_type.scat_Cromer_Mann_a1 _atom_type.scat_Cromer_Mann_a2 _atom_type.scat_Cromer_Mann_a3 _atom_type.scat_Cromer_Mann_a4 _atom_type.scat_Cromer_Mann_b1 _atom_type.scat_Cromer_Mann_b2 _atom_type.scat_Cromer_Mann_b3 _atom_type.scat_Cromer_Mann_b4 _atom_type.scat_Cromer_Mann_c C 0 2.31000 20.8439 1.02000 10.2075 1.58860 0.568700 0.865000 51.6512 0.21560 N 0 12.2126 0.005700 3.13220 9.89330 2.01250 28.9975 1.16630 0.582600 -11.529 O 0 3.04850 13.2771 2.28680 5.70110 1.54630 0.323900 0.867000 32.9089 0.250800 S 0 6.90530 1.46790 5.20340 22.2151 1.43790 0.253600 1.58630 56.1720 0.866900 CL -1 18.2915 0.006600 7.20840 1.17170 6.53370 19.5424 2.33860 60.4486 -16.378 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; loop_ _atom_type.symbol _atom_type.oxidation_number _atom_type.number_in_cell _atom_type.scat_dispersion_real _atom_type.scat_dispersion_imag _atom_type.scat_source C 0 72 .017 .009 International_Tables_Vol_IV_Table_2.2B H 0 100 0 0 International_Tables_Vol_IV_Table_2.2B O 0 12 .047 .032 International_Tables_Vol_IV_Table_2.2B N 0 4 .029 .018 International_Tables_Vol_IV_Table_2.2B ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__atom_type.analytical_mass_percent _item_description.description ; Mass percentage of this atom type derived from chemical analysis. ; _item.name '_atom_type.analytical_mass_percent' _item.category_id atom_type _item.mandatory_code no _item_aliases.alias_name '_atom_type_analytical_mass_%' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__atom_type.description _item_description.description ; A description of the atom(s) designated by this atom type. In most cases, this is the element name and oxidation state of a single atom species. For disordered or nonstoichiometric structures it will describe a combination of atom species. ; _item.name '_atom_type.description' _item.category_id atom_type _item.mandatory_code no _item_aliases.alias_name '_atom_type_description' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'deuterium' '0.34Fe+0.66Ni' save_ save__atom_type.number_in_cell _item_description.description ; Total number of atoms of this atom type in the unit cell. ; _item.name '_atom_type.number_in_cell' _item.category_id atom_type _item.mandatory_code no _item_aliases.alias_name '_atom_type_number_in_cell' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__atom_type.oxidation_number _item_description.description ; Formal oxidation state of this atom type in the structure. ; _item.name '_atom_type.oxidation_number' _item.category_id atom_type _item.mandatory_code no _item_aliases.alias_name '_atom_type_oxidation_number' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_default.value 0 loop_ _item_range.maximum _item_range.minimum 8 8 8 -8 -8 -8 _item_type.code int save_ save__atom_type.radius_bond _item_description.description ; The effective intramolecular bonding radius in angstroms of this atom type. ; _item.name '_atom_type.radius_bond' _item.category_id atom_type _item.mandatory_code no _item_aliases.alias_name '_atom_type_radius_bond' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 5.0 5.0 5.0 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__atom_type.radius_contact _item_description.description ; The effective intermolecular bonding radius in angstroms of this atom type. ; _item.name '_atom_type.radius_contact' _item.category_id atom_type _item.mandatory_code no _item_aliases.alias_name '_atom_type_radius_contact' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 5.0 5.0 5.0 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__atom_type.scat_Cromer_Mann_a1 _item_description.description ; The Cromer-Mann scattering-factor coefficient a1 used to calculate the scattering factors for this atom type. Ref: International Tables for X-ray Crystallography (1974). Vol. IV, Table 2.2B or: International Tables for Crystallography (2004). Vol. C, Tables 6.1.1.4 and 6.1.1.5. ; _item.name '_atom_type.scat_Cromer_Mann_a1' _item.category_id atom_type _item.mandatory_code no _item_aliases.alias_name '_atom_type_scat_Cromer_Mann_a1' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_atom_type.scat_Cromer_Mann_a2' '_atom_type.scat_Cromer_Mann_a3' '_atom_type.scat_Cromer_Mann_a4' '_atom_type.scat_Cromer_Mann_b1' '_atom_type.scat_Cromer_Mann_b2' '_atom_type.scat_Cromer_Mann_b3' '_atom_type.scat_Cromer_Mann_b4' '_atom_type.scat_Cromer_Mann_c' _item_type.code float save_ save__atom_type.scat_Cromer_Mann_a2 _item_description.description ; The Cromer-Mann scattering-factor coefficient a2 used to calculate the scattering factors for this atom type. Ref: International Tables for X-ray Crystallography (1974). Vol. IV, Table 2.2B or: International Tables for Crystallography (2004). Vol. C, Tables 6.1.1.4 and 6.1.1.5. ; _item.name '_atom_type.scat_Cromer_Mann_a2' _item.category_id atom_type _item.mandatory_code no _item_aliases.alias_name '_atom_type_scat_Cromer_Mann_a2' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_atom_type.scat_Cromer_Mann_a1' '_atom_type.scat_Cromer_Mann_a3' '_atom_type.scat_Cromer_Mann_a4' '_atom_type.scat_Cromer_Mann_b1' '_atom_type.scat_Cromer_Mann_b2' '_atom_type.scat_Cromer_Mann_b3' '_atom_type.scat_Cromer_Mann_b4' '_atom_type.scat_Cromer_Mann_c' _item_type.code float save_ save__atom_type.scat_Cromer_Mann_a3 _item_description.description ; The Cromer-Mann scattering-factor coefficient a3 used to calculate the scattering factors for this atom type. Ref: International Tables for X-ray Crystallography (1974). Vol. IV, Table 2.2B or: International Tables for Crystallography (2004). Vol. C, Tables 6.1.1.4 and 6.1.1.5. ; _item.name '_atom_type.scat_Cromer_Mann_a3' _item.category_id atom_type _item.mandatory_code no _item_aliases.alias_name '_atom_type_scat_Cromer_Mann_a3' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_atom_type.scat_Cromer_Mann_a1' '_atom_type.scat_Cromer_Mann_a2' '_atom_type.scat_Cromer_Mann_a4' '_atom_type.scat_Cromer_Mann_b1' '_atom_type.scat_Cromer_Mann_b2' '_atom_type.scat_Cromer_Mann_b3' '_atom_type.scat_Cromer_Mann_b4' '_atom_type.scat_Cromer_Mann_c' _item_type.code float save_ save__atom_type.scat_Cromer_Mann_a4 _item_description.description ; The Cromer-Mann scattering-factor coefficient a4 used to calculate the scattering factors for this atom type. Ref: International Tables for X-ray Crystallography (1974). Vol. IV, Table 2.2B or: International Tables for Crystallography (2004). Vol. C, Tables 6.1.1.4 and 6.1.1.5. ; _item.name '_atom_type.scat_Cromer_Mann_a4' _item.category_id atom_type _item.mandatory_code no _item_aliases.alias_name '_atom_type_scat_Cromer_Mann_a4' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_atom_type.scat_Cromer_Mann_a1' '_atom_type.scat_Cromer_Mann_a2' '_atom_type.scat_Cromer_Mann_a3' '_atom_type.scat_Cromer_Mann_b1' '_atom_type.scat_Cromer_Mann_b2' '_atom_type.scat_Cromer_Mann_b3' '_atom_type.scat_Cromer_Mann_b4' '_atom_type.scat_Cromer_Mann_c' _item_type.code float save_ save__atom_type.scat_Cromer_Mann_b1 _item_description.description ; The Cromer-Mann scattering-factor coefficient b1 used to calculate the scattering factors for this atom type. Ref: International Tables for X-ray Crystallography (1974). Vol. IV, Table 2.2B or: International Tables for Crystallography (2004). Vol. C, Tables 6.1.1.4 and 6.1.1.5. ; _item.name '_atom_type.scat_Cromer_Mann_b1' _item.category_id atom_type _item.mandatory_code no _item_aliases.alias_name '_atom_type_scat_Cromer_Mann_b1' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_atom_type.scat_Cromer_Mann_a1' '_atom_type.scat_Cromer_Mann_a2' '_atom_type.scat_Cromer_Mann_a3' '_atom_type.scat_Cromer_Mann_a4' '_atom_type.scat_Cromer_Mann_b2' '_atom_type.scat_Cromer_Mann_b3' '_atom_type.scat_Cromer_Mann_b4' '_atom_type.scat_Cromer_Mann_c' _item_type.code float save_ save__atom_type.scat_Cromer_Mann_b2 _item_description.description ; The Cromer-Mann scattering-factor coefficient b2 used to calculate the scattering factors for this atom type. Ref: International Tables for X-ray Crystallography (1974). Vol. IV, Table 2.2B or: International Tables for Crystallography (2004). Vol. C, Tables 6.1.1.4 and 6.1.1.5. ; _item.name '_atom_type.scat_Cromer_Mann_b2' _item.category_id atom_type _item.mandatory_code no _item_aliases.alias_name '_atom_type_scat_Cromer_Mann_b2' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_atom_type.scat_Cromer_Mann_a1' '_atom_type.scat_Cromer_Mann_a2' '_atom_type.scat_Cromer_Mann_a3' '_atom_type.scat_Cromer_Mann_a4' '_atom_type.scat_Cromer_Mann_b1' '_atom_type.scat_Cromer_Mann_b3' '_atom_type.scat_Cromer_Mann_b4' '_atom_type.scat_Cromer_Mann_c' _item_type.code float save_ save__atom_type.scat_Cromer_Mann_b3 _item_description.description ; The Cromer-Mann scattering-factor coefficient b3 used to calculate the scattering factors for this atom type. Ref: International Tables for X-ray Crystallography (1974). Vol. IV, Table 2.2B or: International Tables for Crystallography (2004). Vol. C, Tables 6.1.1.4 and 6.1.1.5. ; _item.name '_atom_type.scat_Cromer_Mann_b3' _item.category_id atom_type _item.mandatory_code no _item_aliases.alias_name '_atom_type_scat_Cromer_Mann_b3' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_atom_type.scat_Cromer_Mann_a1' '_atom_type.scat_Cromer_Mann_a2' '_atom_type.scat_Cromer_Mann_a3' '_atom_type.scat_Cromer_Mann_a4' '_atom_type.scat_Cromer_Mann_b1' '_atom_type.scat_Cromer_Mann_b2' '_atom_type.scat_Cromer_Mann_b4' '_atom_type.scat_Cromer_Mann_c' _item_type.code float save_ save__atom_type.scat_Cromer_Mann_b4 _item_description.description ; The Cromer-Mann scattering-factor coefficient b4 used to calculate the scattering factors for this atom type. Ref: International Tables for X-ray Crystallography (1974). Vol. IV, Table 2.2B or: International Tables for Crystallography (2004). Vol. C, Tables 6.1.1.4 and 6.1.1.5. ; _item.name '_atom_type.scat_Cromer_Mann_b4' _item.category_id atom_type _item.mandatory_code no _item_aliases.alias_name '_atom_type_scat_Cromer_Mann_b4' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_atom_type.scat_Cromer_Mann_a1' '_atom_type.scat_Cromer_Mann_a2' '_atom_type.scat_Cromer_Mann_a3' '_atom_type.scat_Cromer_Mann_a4' '_atom_type.scat_Cromer_Mann_b1' '_atom_type.scat_Cromer_Mann_b2' '_atom_type.scat_Cromer_Mann_b3' '_atom_type.scat_Cromer_Mann_c' _item_type.code float save_ save__atom_type.scat_Cromer_Mann_c _item_description.description ; The Cromer-Mann scattering-factor coefficient c used to calculate the scattering factors for this atom type. Ref: International Tables for X-ray Crystallography (1974). Vol. IV, Table 2.2B or: International Tables for Crystallography (2004). Vol. C, Tables 6.1.1.4 and 6.1.1.5. ; _item.name '_atom_type.scat_Cromer_Mann_c' _item.category_id atom_type _item.mandatory_code no _item_aliases.alias_name '_atom_type_scat_Cromer_Mann_c' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_atom_type.scat_Cromer_Mann_a1' '_atom_type.scat_Cromer_Mann_a2' '_atom_type.scat_Cromer_Mann_a3' '_atom_type.scat_Cromer_Mann_a4' '_atom_type.scat_Cromer_Mann_b1' '_atom_type.scat_Cromer_Mann_b2' '_atom_type.scat_Cromer_Mann_b3' '_atom_type.scat_Cromer_Mann_b4' _item_type.code float save_ save__atom_type.scat_dispersion_imag _item_description.description ; The imaginary component of the anomalous-dispersion scattering factor, f'', in electrons for this atom type and the radiation identified by _diffrn_radiation_wavelength.id. ; _item.name '_atom_type.scat_dispersion_imag' _item.category_id atom_type _item.mandatory_code no _item_aliases.alias_name '_atom_type_scat_dispersion_imag' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 # _item_default.value 0.0 _item_dependent.dependent_name '_atom_type.scat_dispersion_real' _item_type.code float save_ save__atom_type.scat_dispersion_real _item_description.description ; The real component of the anomalous-dispersion scattering factor, f', in electrons for this atom type and the radiation identified by _diffrn_radiation_wavelength.id. ; _item.name '_atom_type.scat_dispersion_real' _item.category_id atom_type _item.mandatory_code no _item_aliases.alias_name '_atom_type_scat_dispersion_real' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 # _item_default.value 0.0 _item_dependent.dependent_name '_atom_type.scat_dispersion_imag' _item_type.code float save_ save__atom_type.scat_length_neutron _item_description.description ; The bound coherent scattering length in femtometres for the atom type at the isotopic composition used for the diffraction experiment. ; _item.name '_atom_type.scat_length_neutron' _item.category_id atom_type _item.mandatory_code no _item_aliases.alias_name '_atom_type_scat_length_neutron' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_units.code femtometres save_ save__atom_type.scat_source _item_description.description ; Reference to the source of the scattering factors or scattering lengths used for this atom type. ; _item.name '_atom_type.scat_source' _item.category_id atom_type _item.mandatory_code no _item_aliases.alias_name '_atom_type_scat_source' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'International Tables Vol. IV Table 2.4.6B' save_ save__atom_type.scat_versus_stol_list _item_description.description ; A table of scattering factors as a function of sin theta over lambda. This table should be well commented to indicate the items present. Regularly formatted lists are strongly recommended. ; _item.name '_atom_type.scat_versus_stol_list' _item.category_id atom_type _item.mandatory_code no _item_aliases.alias_name '_atom_type_scat_versus_stol_list' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__atom_type.symbol _item_description.description ; The code used to identify the atom species (singular or plural) representing this atom type. Normally this code is the element symbol. The code may be composed of any character except an underscore with the additional proviso that digits designate an oxidation state and must be followed by a + or - character. ; loop_ _item.name _item.category_id _item.mandatory_code '_atom_type.symbol' atom_type yes '_atom_site.type_symbol' atom_site yes '_atom_site_anisotrop.type_symbol' atom_site_anisotrop yes '_chemical_conn_atom.type_symbol' chemical_conn_atom yes '_chem_comp_atom.type_symbol' chem_comp_atom yes '_phasing_MIR_der_site.atom_type_symbol' phasing_MIR_der_site yes _item_aliases.alias_name '_atom_type_symbol' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_linked.child_name _item_linked.parent_name '_atom_site.type_symbol' '_atom_type.symbol' '_atom_site_anisotrop.type_symbol' '_atom_type.symbol' '_chemical_conn_atom.type_symbol' '_atom_type.symbol' '_chem_comp_atom.type_symbol' '_atom_type.symbol' '_phasing_MIR_der_site.atom_type_symbol' '_atom_type.symbol' _item_type.code code loop_ _item_examples.case 'C' 'Cu2+' 'H(SDS)' 'dummy' 'FeNi' save_ ########### ## AUDIT ## ########### save_audit _category.description ; Data items in the AUDIT category record details about the creation and subsequent updating of the data block. Note that these items apply only to the creation and updating of the data block, and should not be confused with the data items in the JOURNAL category that record different stages in the publication of the material in the data block. ; _category.id audit _category.mandatory_code no _category_key.name '_audit.revision_id' loop_ _category_group.id 'inclusive_group' 'audit_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _audit.revision_id 1 _audit.creation_date '1992-12-08' _audit.creation_method ; Created by hand from PDB entry 5HVP, from the J. Biol. Chem. paper describing this structure and from laboratory records ; _audit.update_record ; 1992-12-09 adjusted to reflect comments from B. McKeever 1992-12-10 adjusted to reflect comments from H. Berman 1992-12-12 adjusted to reflect comments from K. Watenpaugh ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _audit.creation_date 1991-03-20 _audit.creation_method from_xtal_archive_file_using_CIFIO _audit.update_record ; 1991-04-09 text and data added by Tony Willis. 1991-04-15 rec'd by co-editor as manuscript HL0007. 1991-04-17 adjustments based on first referee report. 1991-04-18 adjustments based on second referee report. ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__audit.creation_date _item_description.description ; A date that the data block was created. The date format is yyyy-mm-dd. ; _item.name '_audit.creation_date' _item.category_id audit _item.mandatory_code no _item_aliases.alias_name '_audit_creation_date' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code yyyy-mm-dd _item_examples.case '1990-07-12' save_ save__audit.creation_method _item_description.description ; A description of how data were entered into the data block. ; _item.name '_audit.creation_method' _item.category_id audit _item.mandatory_code no _item_aliases.alias_name '_audit_creation_method' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'spawned by the program QBEE' save_ save__audit.revision_id _item_description.description ; The value of _audit.revision_id must uniquely identify a record in the AUDIT list. ; _item.name '_audit.revision_id' _item.category_id audit _item.mandatory_code yes _item_type.code code _item_examples.case 'rev1' save_ save__audit.update_record _item_description.description ; A record of any changes to the data block. The update format is a date (yyyy-mm-dd) followed by a description of the changes. The latest update entry is added to the bottom of this record. ; _item.name '_audit.update_record' _item.category_id audit _item.mandatory_code no _item_aliases.alias_name '_audit_update_record' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case '1990-07-15 Updated by the Co-editor' save_ ################## ## AUDIT_AUTHOR ## ################## save_audit_author _category.description ; Data items in the AUDIT_AUTHOR category record details about the author(s) of the data block. ; _category.id audit_author _category.mandatory_code no _category_key.name '_audit_author.name' loop_ _category_group.id 'inclusive_group' 'audit_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _audit_author.name _audit_author.address 'Fitzgerald, Paula M.D.' ; Department of Biophysical Chemistry Merck Research Laboratories P. O. Box 2000, Ry80M203 Rahway, New Jersey 07065 USA ; 'McKeever, Brian M.' ; Department of Biophysical Chemistry Merck Research Laboratories P. O. Box 2000, Ry80M203 Rahway, New Jersey 07065 USA ; 'Van Middlesworth, J.F.' ; Department of Biophysical Chemistry Merck Research Laboratories P. O. Box 2000, Ry80M203 Rahway, New Jersey 07065 USA ; 'Springer, James P.' ; Department of Biophysical Chemistry Merck Research Laboratories P. O. Box 2000, Ry80M203 Rahway, New Jersey 07065 USA ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__audit_author.address _item_description.description ; The address of an author of this data block. If there are multiple authors, _audit_author.address is looped with _audit_author.name. ; _item.name '_audit_author.address' _item.category_id audit_author _item.mandatory_code no _item_aliases.alias_name '_audit_author_address' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; Department Institute Street City and postcode COUNTRY ; save_ save__audit_author.name _item_description.description ; The name of an author of this data block. If there are multiple authors, _audit_author.name is looped with _audit_author.address. The family name(s), followed by a comma and including any dynastic components, precedes the first name(s) or initial(s). ; _item.name '_audit_author.name' _item.category_id audit_author _item.mandatory_code yes _item_aliases.alias_name '_audit_author_name' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'Bleary, Percival R.' "O'Neil, F.K." 'Van den Bossche, G.' 'Yang, D.-L.' 'Simonov, Yu.A' save_ ################### ## AUDIT_CONFORM ## ################### save_audit_conform _category.description ; Data items in the AUDIT_CONFORM category describe the dictionary versions against which the data names appearing in the current data block are conformant. ; _category.id audit_conform _category.mandatory_code no loop_ _category_key.name '_audit_conform.dict_name' '_audit_conform.dict_version' loop_ _category_group.id 'inclusive_group' 'audit_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - any file conforming to the current CIF core dictionary. ; ; _audit_conform.dict_name cif_core.dic _audit_conform.dict_version 2.3.1 _audit_conform.dict_location ftp://ftp.iucr.org/pub/cif_core.2.3.1.dic ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__audit_conform.dict_location _item_description.description ; A file name or uniform resource locator (URL) for the dictionary to which the current data block conforms. ; _item.name '_audit_conform.dict_location' _item.category_id audit_conform _item.mandatory_code no _item_aliases.alias_name '_audit_conform_dict_location' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__audit_conform.dict_name _item_description.description ; The string identifying the highest-level dictionary defining data names used in this file. ; _item.name '_audit_conform.dict_name' _item.category_id audit_conform _item.mandatory_code no _item_aliases.alias_name '_audit_conform_dict_name' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__audit_conform.dict_version _item_description.description ; The version number of the dictionary to which the current data block conforms. ; _item.name '_audit_conform.dict_version' _item.category_id audit_conform _item.mandatory_code no _item_aliases.alias_name '_audit_conform_dict_version' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ ########################## ## AUDIT_CONTACT_AUTHOR ## ########################## save_audit_contact_author _category.description ; Data items in the AUDIT_CONTACT_AUTHOR category record details about the name and address of the author to be contacted concerning the content of this data block. ; _category.id audit_contact_author _category.mandatory_code no _category_key.name '_audit_contact_author.name' loop_ _category_group.id 'inclusive_group' 'audit_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _audit_contact_author.name 'Fitzgerald, Paula M.D.' _audit_contact_author.address ; Department of Biophysical Chemistry Merck Research Laboratories PO Box 2000, Ry80M203 Rahway, New Jersey 07065 USA ; _audit_contact_author.phone '1(908)5945510' _audit_contact_author.fax '1(908)5946645' _audit_contact_author.email 'paula_fitzgerald@merck.com' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__audit_contact_author.address _item_description.description ; The mailing address of the author of the data block to whom correspondence should be addressed. ; _item.name '_audit_contact_author.address' _item.category_id audit_contact_author _item.mandatory_code no _item_aliases.alias_name '_audit_contact_author_address' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; Department Institute Street City and postcode COUNTRY ; save_ save__audit_contact_author.email _item_description.description ; The electronic mail address of the author of the data block to whom correspondence should be addressed, in a form recognizable to international networks. The format of e-mail addresses is given in Section 3.4, Address Specification, of Internet Message Format, RFC 2822, P. Resnick (Editor), Network Standards Group, April 2001. ; _item.name '_audit_contact_author.email' _item.category_id audit_contact_author _item.mandatory_code no _item_aliases.alias_name '_audit_contact_author_email' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'name@host.domain.country' 'bm@iucr.org' save_ save__audit_contact_author.fax _item_description.description ; The facsimile telephone number of the author of the data block to whom correspondence should be addressed. The recommended style starts with the international dialing prefix, followed by the area code in parentheses, followed by the local number with no spaces. ; _item.name '_audit_contact_author.fax' _item.category_id audit_contact_author _item.mandatory_code no _item_aliases.alias_name '_audit_contact_author_fax' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case '12(34)9477334' '12()349477334' save_ save__audit_contact_author.name _item_description.description ; The name of the author of the data block to whom correspondence should be addressed. The family name(s), followed by a comma and including any dynastic components, precedes the first name(s) or initial(s). ; _item.name '_audit_contact_author.name' _item.category_id audit_contact_author _item.mandatory_code yes _item_aliases.alias_name '_audit_contact_author_name' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'Bleary, Percival R.' "O'Neil, F.K." 'Van den Bossche, G.' 'Yang, D.-L.' 'Simonov, Yu.A' save_ save__audit_contact_author.phone _item_description.description ; The telephone number of the author of the data block to whom correspondence should be addressed. The recommended style starts with the international dialing prefix, followed by the area code in parentheses, followed by the local number and any extension number prefixed by 'x', with no spaces. ; _item.name '_audit_contact_author.phone' _item.category_id audit_contact_author _item.mandatory_code no _item_aliases.alias_name '_audit_contact_author_phone' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case '12(34)9477330' '12()349477330' '12(34)9477330x5543' save_ ########## ## CELL ## ########## save_cell _category.description ; Data items in the CELL category record details about the crystallographic cell parameters. ; _category.id cell _category.mandatory_code no _category_key.name '_cell.entry_id' loop_ _category_group.id 'inclusive_group' 'cell_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _cell.entry_id '5HVP' _cell.length_a 58.39 _cell.length_a_esd 0.05 _cell.length_b 86.70 _cell.length_b_esd 0.12 _cell.length_c 46.27 _cell.length_c_esd 0.06 _cell.angle_alpha 90.00 _cell.angle_beta 90.00 _cell.angle_gamma 90.00 _cell.volume 234237 _cell.details ; The cell parameters were refined every twenty frames during data integration. The cell lengths given are the mean of 55 such refinements; the esds given are the root mean square deviations of these 55 observations from that mean. ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _cell.length_a 5.959 _cell.length_a_esd 0.001 _cell.length_b 14.956 _cell.length_b_esd 0.001 _cell.length_c 19.737 _cell.length_c_esd 0.003 _cell.angle_alpha 90.0 _cell.angle_beta 90.0 _cell.angle_gamma 90.0 _cell.volume 1759.0 _cell.volume_esd 0.3 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__cell.angle_alpha _item_description.description ; Unit-cell angle alpha of the reported structure in degrees. ; _item.name '_cell.angle_alpha' _item.category_id cell _item.mandatory_code no _item_aliases.alias_name '_cell_angle_alpha' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_default.value 90.0 loop_ _item_dependent.dependent_name '_cell.angle_beta' '_cell.angle_gamma' loop_ _item_range.maximum _item_range.minimum 180.0 180.0 180.0 0.0 0.0 0.0 _item_related.related_name '_cell.angle_alpha_esd' _item_related.function_code associated_esd _item_sub_category.id cell_angle _item_type.code float _item_type_conditions.code esd _item_units.code degrees save_ save__cell.angle_alpha_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _cell.angle_alpha. ; _item.name '_cell.angle_alpha_esd' _item.category_id cell _item.mandatory_code no # _item_default.value 0.0 loop_ _item_dependent.dependent_name '_cell.angle_beta_esd' '_cell.angle_gamma_esd' _item_related.related_name '_cell.angle_alpha' _item_related.function_code associated_value _item_sub_category.id cell_angle_esd _item_type.code float _item_units.code degrees save_ save__cell.angle_beta _item_description.description ; Unit-cell angle beta of the reported structure in degrees. ; _item.name '_cell.angle_beta' _item.category_id cell _item.mandatory_code no _item_aliases.alias_name '_cell_angle_beta' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_default.value 90.0 loop_ _item_dependent.dependent_name '_cell.angle_alpha' '_cell.angle_gamma' loop_ _item_range.maximum _item_range.minimum 180.0 180.0 180.0 0.0 0.0 0.0 _item_related.related_name '_cell.angle_beta_esd' _item_related.function_code associated_esd _item_sub_category.id cell_angle _item_type.code float _item_type_conditions.code esd _item_units.code degrees save_ save__cell.angle_beta_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _cell.angle_beta. ; _item.name '_cell.angle_beta_esd' _item.category_id cell _item.mandatory_code no # _item_default.value 0.0 loop_ _item_dependent.dependent_name '_cell.angle_alpha_esd' '_cell.angle_gamma_esd' _item_related.related_name '_cell.angle_beta' _item_related.function_code associated_value _item_sub_category.id cell_angle_esd _item_type.code float _item_units.code degrees save_ save__cell.angle_gamma _item_description.description ; Unit-cell angle gamma of the reported structure in degrees. ; _item.name '_cell.angle_gamma' _item.category_id cell _item.mandatory_code no _item_aliases.alias_name '_cell_angle_gamma' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_default.value 90.0 loop_ _item_dependent.dependent_name '_cell.angle_alpha' '_cell.angle_beta' loop_ _item_range.maximum _item_range.minimum 180.0 180.0 180.0 0.0 0.0 0.0 _item_related.related_name '_cell.angle_gamma_esd' _item_related.function_code associated_esd _item_sub_category.id cell_angle _item_type.code float _item_type_conditions.code esd _item_units.code degrees save_ save__cell.angle_gamma_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _cell.angle_gamma. ; _item.name '_cell.angle_gamma_esd' _item.category_id cell _item.mandatory_code no # _item_default.value 0.0 loop_ _item_dependent.dependent_name '_cell.angle_alpha_esd' '_cell.angle_beta_esd' _item_related.related_name '_cell.angle_gamma' _item_related.function_code associated_value _item_sub_category.id cell_angle_esd _item_type.code float _item_units.code degrees save_ save__cell.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_cell.entry_id' _item.mandatory_code yes save_ save__cell.details _item_description.description ; A description of special aspects of the cell choice, noting possible alternative settings. ; _item.name '_cell.details' _item.category_id cell _item.mandatory_code no _item_aliases.alias_name '_cell_special_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'pseudo-orthorhombic' 'standard setting from 45 deg rotation around c' save_ save__cell.formula_units_Z _item_description.description ; The number of the formula units in the unit cell as specified by _chemical_formula.structural, _chemical_formula.moiety or _chemical_formula.sum. ; _item.name '_cell.formula_units_Z' _item.category_id cell _item.mandatory_code no _item_aliases.alias_name '_cell_formula_units_Z' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__cell.length_a _item_description.description ; Unit-cell length a corresponding to the structure reported in angstroms. ; _item.name '_cell.length_a' _item.category_id cell _item.mandatory_code no _item_aliases.alias_name '_cell_length_a' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_cell.length_b' '_cell.length_c' loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_cell.length_a_esd' _item_related.function_code associated_esd _item_sub_category.id cell_length _item_type.code float _item_type_conditions.code esd _item_units.code angstroms save_ save__cell.length_a_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _cell.length_a. ; _item.name '_cell.length_a_esd' _item.category_id cell _item.mandatory_code no # _item_default.value 0.0 loop_ _item_dependent.dependent_name '_cell.length_b_esd' '_cell.length_c_esd' _item_related.related_name '_cell.length_a' _item_related.function_code associated_value _item_sub_category.id cell_length_esd _item_type.code float _item_units.code angstroms save_ save__cell.length_b _item_description.description ; Unit-cell length b corresponding to the structure reported in angstroms. ; _item.name '_cell.length_b' _item.category_id cell _item.mandatory_code no _item_aliases.alias_name '_cell_length_b' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_cell.length_a' '_cell.length_c' loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_cell.length_b_esd' _item_related.function_code associated_esd _item_sub_category.id cell_length _item_type.code float _item_type_conditions.code esd _item_units.code angstroms save_ save__cell.length_b_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _cell.length_b. ; _item.name '_cell.length_b_esd' _item.category_id cell _item.mandatory_code no # _item_default.value 0.0 loop_ _item_dependent.dependent_name '_cell.length_a_esd' '_cell.length_c_esd' _item_related.related_name '_cell.length_b' _item_related.function_code associated_value _item_sub_category.id cell_length_esd _item_type.code float _item_units.code angstroms save_ save__cell.length_c _item_description.description ; Unit-cell length c corresponding to the structure reported in angstroms. ; _item.name '_cell.length_c' _item.category_id cell _item.mandatory_code no _item_aliases.alias_name '_cell_length_c' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_cell.length_a' '_cell.length_b' loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_cell.length_c_esd' _item_related.function_code associated_esd _item_sub_category.id cell_length _item_type.code float _item_type_conditions.code esd _item_units.code angstroms save_ save__cell.length_c_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _cell.length_c. ; _item.name '_cell.length_c_esd' _item.category_id cell _item.mandatory_code no # _item_default.value 0.0 loop_ _item_dependent.dependent_name '_cell.length_a_esd' '_cell.length_b_esd' _item_related.related_name '_cell.length_c' _item_related.function_code associated_value _item_sub_category.id cell_length_esd _item_type.code float _item_units.code angstroms save_ save__cell.volume _item_description.description ; Cell volume V in angstroms cubed. V = a b c (1 - cos^2^~alpha~ - cos^2^~beta~ - cos^2^~gamma~ + 2 cos~alpha~ cos~beta~ cos~gamma~)^1/2^ a = _cell.length_a b = _cell.length_b c = _cell.length_c alpha = _cell.angle_alpha beta = _cell.angle_beta gamma = _cell.angle_gamma ; _item.name '_cell.volume' _item.category_id cell _item.mandatory_code no _item_aliases.alias_name '_cell_volume' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_cell.volume_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code angstroms_cubed save_ save__cell.volume_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _cell.volume. ; _item.name '_cell.volume_esd' _item.category_id cell _item.mandatory_code no # _item_default.value 0.0 _item_related.related_name '_cell.volume' _item_related.function_code associated_value _item_type.code float _item_units.code angstroms_cubed save_ save__cell.Z_PDB _item_description.description ; The number of the polymeric chains in a unit cell. In the case of heteropolymers, Z is the number of occurrences of the most populous chain. This data item is provided for compatibility with the original Protein Data Bank format, and only for that purpose. ; _item.name '_cell.Z_PDB' _item.category_id cell _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ ###################### ## CELL_MEASUREMENT ## ###################### save_cell_measurement _category.description ; Data items in the CELL_MEASUREMENT category record details about the measurement of the crystallographic cell parameters. ; _category.id cell_measurement _category.mandatory_code no _category_key.name '_cell_measurement.entry_id' loop_ _category_group.id 'inclusive_group' 'cell_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _cell_measurement.entry_id '5HVP' _cell_measurement.temp 293 _cell_measurement.temp_esd 3 _cell_measurement.theta_min 11 _cell_measurement.theta_max 31 _cell_measurement.wavelength 1.54 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _cell_measurement.temp 293 _cell_measurement.reflns_used 25 _cell_measurement.theta_min 25 _cell_measurement.theta_max 31 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__cell_measurement.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_cell_measurement.entry_id' _item.mandatory_code yes save_ save__cell_measurement.pressure _item_description.description ; The pressure in kilopascals at which the unit-cell parameters were measured (not the pressure at which the sample was synthesized). ; _item.name '_cell_measurement.pressure' _item.category_id cell_measurement _item.mandatory_code no _item_aliases.alias_name '_cell_measurement_pressure' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_related.related_name '_cell_measurement.pressure_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code kilopascals save_ save__cell_measurement.pressure_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _cell_measurement.pressure. ; _item.name '_cell_measurement.pressure_esd' _item.category_id cell_measurement _item.mandatory_code no # _item_default.value 0.0 _item_related.related_name '_cell_measurement.pressure' _item_related.function_code associated_value _item_type.code float _item_units.code kilopascals save_ save__cell_measurement.radiation _item_description.description ; Description of the radiation used to measure the unit-cell data. See also _cell_measurement.wavelength. ; _item.name '_cell_measurement.radiation' _item.category_id cell_measurement _item.mandatory_code no _item_aliases.alias_name '_cell_measurement_radiation' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'neutron' 'Cu K\a' 'synchrotron' save_ save__cell_measurement.reflns_used _item_description.description ; The total number of reflections used to determine the unit cell. These reflections may be specified as CELL_MEASUREMENT_REFLN data items. ; _item.name '_cell_measurement.reflns_used' _item.category_id cell_measurement _item.mandatory_code no _item_aliases.alias_name '_cell_measurement_reflns_used' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code int save_ save__cell_measurement.temp _item_description.description ; The temperature in kelvins at which the unit-cell parameters were measured (not the temperature of synthesis). ; _item.name '_cell_measurement.temp' _item.category_id cell_measurement _item.mandatory_code no _item_aliases.alias_name '_cell_measurement_temperature' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_cell_measurement.temp_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code kelvins save_ save__cell_measurement.temp_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _cell_measurement.temp. ; _item.name '_cell_measurement.temp_esd' _item.category_id cell_measurement _item.mandatory_code no # _item_default.value 0.0 _item_related.related_name '_cell_measurement.temp' _item_related.function_code associated_value _item_type.code float _item_units.code kelvins save_ save__cell_measurement.theta_max _item_description.description ; The maximum theta angle of reflections used to measure the unit cell in degrees. ; _item.name '_cell_measurement.theta_max' _item.category_id cell_measurement _item.mandatory_code no _item_aliases.alias_name '_cell_measurement_theta_max' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 0.0 0.0 0.0 _item_type.code float _item_units.code degrees save_ save__cell_measurement.theta_min _item_description.description ; The minimum theta angle of reflections used to measure the unit cell in degrees. ; _item.name '_cell_measurement.theta_min' _item.category_id cell_measurement _item.mandatory_code no _item_aliases.alias_name '_cell_measurement_theta_min' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 0.0 0.0 0.0 _item_type.code float _item_units.code degrees save_ save__cell_measurement.wavelength _item_description.description ; The wavelength in angstroms of the radiation used to measure the unit cell. If this is not specified, the wavelength is assumed to be that specified in the category DIFFRN_RADIATION_WAVELENGTH. ; _item.name '_cell_measurement.wavelength' _item.category_id cell_measurement _item.mandatory_code no _item_aliases.alias_name '_cell_measurement_wavelength' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ ############################ ## CELL_MEASUREMENT_REFLN ## ############################ save_cell_measurement_refln _category.description ; Data items in the CELL_MEASUREMENT_REFLN category record details about the reflections used to determine the crystallographic cell parameters. The CELL_MEASUREMENT_REFLN data items would in general be used only for diffractometer data. ; _category.id cell_measurement_refln _category.mandatory_code no loop_ _category_key.name '_cell_measurement_refln.index_h' '_cell_measurement_refln.index_k' '_cell_measurement_refln.index_l' loop_ _category_group.id 'inclusive_group' 'cell_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - extracted from the CAD-4 listing of Rb~2~S~2~O~6~ at room temperature (unpublished). ; ; loop_ _cell_measurement_refln.index_h _cell_measurement_refln.index_k _cell_measurement_refln.index_l _cell_measurement_refln.theta -2 4 1 8.67 0 3 2 9.45 3 0 2 9.46 -3 4 1 8.93 -2 1 -2 7.53 10 0 0 23.77 0 10 0 23.78 -5 4 1 11.14 # - - - - data truncated for brevity - - - - ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__cell_measurement_refln.index_h _item_description.description ; Miller index h of a reflection used for measurement of the unit cell. ; _item.name '_cell_measurement_refln.index_h' _item.category_id cell_measurement_refln _item.mandatory_code yes _item_aliases.alias_name '_cell_measurement_refln_index_h' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_cell_measurement_refln.index_k' '_cell_measurement_refln.index_l' _item_sub_category.id miller_index _item_type.code int save_ save__cell_measurement_refln.index_k _item_description.description ; Miller index k of a reflection used for measurement of the unit cell. ; _item.name '_cell_measurement_refln.index_k' _item.category_id cell_measurement_refln _item.mandatory_code yes _item_aliases.alias_name '_cell_measurement_refln_index_k' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_cell_measurement_refln.index_h' '_cell_measurement_refln.index_l' _item_sub_category.id miller_index _item_type.code int save_ save__cell_measurement_refln.index_l _item_description.description ; Miller index l of a reflection used for measurement of the unit cell. ; _item.name '_cell_measurement_refln.index_l' _item.category_id cell_measurement_refln _item.mandatory_code yes _item_aliases.alias_name '_cell_measurement_refln_index_l' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_cell_measurement_refln.index_h' '_cell_measurement_refln.index_k' _item_sub_category.id miller_index _item_type.code int save_ save__cell_measurement_refln.theta _item_description.description ; Theta angle for a reflection used for measurement of the unit cell in degrees. ; _item.name '_cell_measurement_refln.theta' _item.category_id cell_measurement_refln _item.mandatory_code no _item_aliases.alias_name '_cell_measurement_refln_theta' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 0.0 0.0 0.0 _item_type.code float _item_units.code degrees save_ ############### ## CHEM_COMP ## ############### save_chem_comp _category.description ; Data items in the CHEM_COMP category give details about each of the chemical components from which the relevant chemical structures can be constructed, such as name, mass or charge. The related categories CHEM_COMP_ATOM, CHEM_COMP_BOND, CHEM_COMP_ANGLE etc. describe the detailed geometry of these chemical components. ; _category.id chem_comp _category.mandatory_code no _category_key.name '_chem_comp.id' loop_ _category_group.id 'inclusive_group' 'chem_comp_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _chem_comp.id _chem_comp.model_source _chem_comp.name phe '1987 Protin/Prolsq Ideals file' phenylalanine val '1987 Protin/Prolsq Ideals file' alanine # - - - - data truncated for brevity - - - - ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__chem_comp.formula _item_description.description ; The formula for the chemical component. Formulae are written according to the following rules: (1) Only recognized element symbols may be used. (2) Each element symbol is followed by a 'count' number. A count of '1' may be omitted. (3) A space or parenthesis must separate each cluster of (element symbol + count), but in general parentheses are not used. (4) The order of elements depends on whether carbon is present or not. If carbon is present, the order should be: C, then H, then the other elements in alphabetical order of their symbol. If carbon is not present, the elements are listed purely in alphabetic order of their symbol. This is the 'Hill' system used by Chemical Abstracts. ; _item.name '_chem_comp.formula' _item.category_id chem_comp _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'C18 H19 N7 O8 S' save_ save__chem_comp.formula_weight _item_description.description ; Formula mass in daltons of the chemical component. ; _item.name '_chem_comp.formula_weight' _item.category_id chem_comp _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1.0 1.0 1.0 _item_type.code float save_ save__chem_comp.id _item_description.description ; The value of _chem_comp.id must uniquely identify each item in the CHEM_COMP list. For protein polymer entities, this is the three-letter code for the amino acid. For nucleic acid polymer entities, this is the one-letter code for the base. ; loop_ _item.name _item.category_id _item.mandatory_code '_chem_comp.id' chem_comp yes '_atom_site.label_comp_id' atom_site no '_chem_comp.mon_nstd_parent_comp_id' chem_comp no '_chem_comp_atom.comp_id' chem_comp_atom yes '_chem_comp_angle.comp_id' chem_comp_angle yes '_chem_comp_bond.comp_id' chem_comp_bond yes '_chem_comp_chir.comp_id' chem_comp_chir yes '_chem_comp_chir_atom.comp_id' chem_comp_chir_atom yes '_chem_comp_plane.comp_id' chem_comp_plane yes '_chem_comp_plane_atom.comp_id' chem_comp_plane_atom yes '_chem_comp_tor.comp_id' chem_comp_tor yes '_chem_comp_tor_value.comp_id' chem_comp_tor_value yes '_entity_poly_seq.mon_id' entity_poly_seq yes '_geom_angle.atom_site_label_comp_id_1' geom_angle no '_geom_angle.atom_site_label_comp_id_2' geom_angle no '_geom_angle.atom_site_label_comp_id_3' geom_angle no '_geom_bond.atom_site_label_comp_id_1' geom_bond no '_geom_bond.atom_site_label_comp_id_2' geom_bond no '_geom_contact.atom_site_label_comp_id_1' geom_contact no '_geom_contact.atom_site_label_comp_id_2' geom_contact no '_geom_hbond.atom_site_label_comp_id_A' geom_hbond no '_geom_hbond.atom_site_label_comp_id_D' geom_hbond no '_geom_hbond.atom_site_label_comp_id_H' geom_hbond no '_geom_torsion.atom_site_label_comp_id_1' geom_torsion no '_geom_torsion.atom_site_label_comp_id_2' geom_torsion no '_geom_torsion.atom_site_label_comp_id_3' geom_torsion no '_geom_torsion.atom_site_label_comp_id_4' geom_torsion no '_struct_conf.beg_label_comp_id' struct_conf yes '_struct_conf.end_label_comp_id' struct_conf yes '_struct_conn.ptnr1_label_comp_id' struct_conn yes '_struct_conn.ptnr2_label_comp_id' struct_conn yes '_struct_mon_nucl.label_comp_id' struct_mon_nucl yes '_struct_mon_prot.label_comp_id' struct_mon_prot yes '_struct_mon_prot_cis.label_comp_id' struct_mon_prot_cis yes '_struct_ncs_dom_lim.beg_label_comp_id' struct_ncs_dom_lim yes '_struct_ncs_dom_lim.end_label_comp_id' struct_ncs_dom_lim yes '_struct_ref_seq_dif.db_mon_id' struct_ref_seq_dif yes '_struct_ref_seq_dif.mon_id' struct_ref_seq_dif yes '_struct_sheet_range.beg_label_comp_id' struct_sheet_range yes '_struct_sheet_range.end_label_comp_id' struct_sheet_range yes '_struct_site_gen.label_comp_id' struct_site_gen yes loop_ _item_linked.child_name _item_linked.parent_name '_atom_site.label_comp_id' '_chem_comp.id' '_chem_comp.mon_nstd_parent_comp_id' '_chem_comp.id' '_chem_comp_atom.comp_id' '_chem_comp.id' '_chem_comp_chir.comp_id' '_chem_comp.id' '_chem_comp_chir_atom.comp_id' '_chem_comp.id' '_chem_comp_plane.comp_id' '_chem_comp.id' '_chem_comp_plane_atom.comp_id' '_chem_comp.id' '_entity_poly_seq.mon_id' '_chem_comp.id' '_chem_comp_angle.comp_id' '_chem_comp_atom.comp_id' '_chem_comp_bond.comp_id' '_chem_comp_atom.comp_id' '_chem_comp_tor.comp_id' '_chem_comp_atom.comp_id' '_chem_comp_tor_value.comp_id' '_chem_comp_atom.comp_id' '_geom_angle.atom_site_label_comp_id_1' '_atom_site.label_comp_id' '_geom_angle.atom_site_label_comp_id_2' '_atom_site.label_comp_id' '_geom_angle.atom_site_label_comp_id_3' '_atom_site.label_comp_id' '_geom_bond.atom_site_label_comp_id_1' '_atom_site.label_comp_id' '_geom_bond.atom_site_label_comp_id_2' '_atom_site.label_comp_id' '_geom_contact.atom_site_label_comp_id_1' '_atom_site.label_comp_id' '_geom_contact.atom_site_label_comp_id_2' '_atom_site.label_comp_id' '_geom_hbond.atom_site_label_comp_id_A' '_atom_site.label_comp_id' '_geom_hbond.atom_site_label_comp_id_D' '_atom_site.label_comp_id' '_geom_hbond.atom_site_label_comp_id_H' '_atom_site.label_comp_id' '_geom_torsion.atom_site_label_comp_id_1' '_atom_site.label_comp_id' '_geom_torsion.atom_site_label_comp_id_2' '_atom_site.label_comp_id' '_geom_torsion.atom_site_label_comp_id_3' '_atom_site.label_comp_id' '_geom_torsion.atom_site_label_comp_id_4' '_atom_site.label_comp_id' '_struct_conf.beg_label_comp_id' '_atom_site.label_comp_id' '_struct_conf.end_label_comp_id' '_atom_site.label_comp_id' '_struct_conn.ptnr1_label_comp_id' '_atom_site.label_comp_id' '_struct_conn.ptnr2_label_comp_id' '_atom_site.label_comp_id' '_struct_mon_nucl.label_comp_id' '_atom_site.label_comp_id' '_struct_mon_prot.label_comp_id' '_atom_site.label_comp_id' '_struct_mon_prot_cis.label_comp_id' '_atom_site.label_comp_id' '_struct_ncs_dom_lim.beg_label_comp_id' '_atom_site.label_comp_id' '_struct_ncs_dom_lim.end_label_comp_id' '_atom_site.label_comp_id' '_struct_ref_seq_dif.db_mon_id' '_chem_comp.id' '_struct_ref_seq_dif.mon_id' '_chem_comp.id' '_struct_sheet_range.beg_label_comp_id' '_atom_site.label_comp_id' '_struct_sheet_range.end_label_comp_id' '_atom_site.label_comp_id' '_struct_site_gen.label_comp_id' '_atom_site.label_comp_id' _item_type.code ucode loop_ _item_examples.case 'ala' 'val' 'A' 'C' save_ save__chem_comp.model_details _item_description.description ; A description of special aspects of the generation of the coordinates for the model of the component. ; _item.name '_chem_comp.model_details' _item.category_id chem_comp _item.mandatory_code no _item_type.code text _item_examples.case 'geometry idealized but not minimized' save_ save__chem_comp.model_erf _item_description.description ; A pointer to an external reference file from which the atomic description of the component is taken. ; _item.name '_chem_comp.model_erf' _item.category_id chem_comp _item.mandatory_code no _item_type.code line save_ save__chem_comp.model_source _item_description.description ; The source of the coordinates for the model of the component. ; _item.name '_chem_comp.model_source' _item.category_id chem_comp _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'CSD entry ABCDEF' 'built using Quanta/Charmm' save_ save__chem_comp.mon_nstd_class _item_description.description ; A description of the class of a nonstandard monomer if the nonstandard monomer represents a modification of a standard monomer. ; _item.name '_chem_comp.mon_nstd_class' _item.category_id chem_comp _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'iodinated base' 'phosphorylated amino acid' 'brominated base' 'modified amino acid' 'glycosylated amino acid' save_ save__chem_comp.mon_nstd_details _item_description.description ; A description of special details of a nonstandard monomer. ; _item.name '_chem_comp.mon_nstd_details' _item.category_id chem_comp _item.mandatory_code no _item_type.code text save_ save__chem_comp.mon_nstd_flag _item_description.description ; 'yes' indicates that this is a 'standard' monomer, 'no' indicates that it is 'nonstandard'. Nonstandard monomers should be described in more detail using the _chem_comp.mon_nstd_parent, _chem_comp.mon_nstd_class and _chem_comp.mon_nstd_details data items. ; _item.name '_chem_comp.mon_nstd_flag' _item.category_id chem_comp _item.mandatory_code no _item_type.code ucode _item_default.value no loop_ _item_enumeration.value _item_enumeration.detail no 'the monomer is nonstandard' n 'abbreviation for "no"' yes 'the monomer is standard' y 'abbreviation for "yes"' save_ save__chem_comp.mon_nstd_parent _item_description.description ; The name of the parent monomer of the nonstandard monomer, if the nonstandard monomer represents a modification of a standard monomer. ; _item.name '_chem_comp.mon_nstd_parent' _item.category_id chem_comp _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'tyrosine' 'cytosine' save_ save__chem_comp.mon_nstd_parent_comp_id _item_description.description ; The identifier for the parent component of the nonstandard component. This data item is a pointer to _chem_comp.id in the CHEM_COMP category. ; _item.name '_chem_comp.mon_nstd_parent_comp_id' _item.mandatory_code no save_ save__chem_comp.name _item_description.description ; The full name of the component. ; _item.name '_chem_comp.name' _item.category_id chem_comp _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'alanine' 'valine' 'adenine' 'cytosine' save_ save__chem_comp.number_atoms_all _item_description.description ; The total number of atoms in the component. ; _item.name '_chem_comp.number_atoms_all' _item.category_id chem_comp _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__chem_comp.number_atoms_nh _item_description.description ; The number of non-hydrogen atoms in the component. ; _item.name '_chem_comp.number_atoms_nh' _item.category_id chem_comp _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__chem_comp.one_letter_code _item_description.description ; For standard polymer components, the one-letter code for the component. If there is not a standard one-letter code for this component, or if this is a non-polymer component, the one-letter code should be given as 'X'. This code may be preceded by a '+' character to indicate that the component is a modification of a standard component. ; _item.name '_chem_comp.one_letter_code' _item.category_id chem_comp _item.mandatory_code no _item_type.code uchar1 loop_ _item_examples.case _item_examples.detail A 'alanine or adenine' B 'ambiguous asparagine/aspartic acid' R 'arginine' N 'asparagine' D 'aspartic acid' C 'cysteine or cystine or cytosine' Q 'glutamine' E 'glutamic acid' Z 'ambiguous glutamine/glutamic acid' G 'glycine or guanine' H 'histidine' I 'isoleucine' L 'leucine' K 'lysine' M 'methionine' F 'phenylalanine' P 'proline' S 'serine' T 'threonine or thymine' W 'tryptophan' Y 'tyrosine' V 'valine' U 'uracil' O 'water' X 'other' save_ save__chem_comp.three_letter_code _item_description.description ; For standard polymer components, the three-letter code for the component. If there is not a standard three-letter code for this component, or if this is a non-polymer component, the three-letter code should be given as 'UNK'. This code may be preceded by a '+' character to indicate that the component is a modification of a standard component. ; _item.name '_chem_comp.three_letter_code' _item.category_id chem_comp _item.mandatory_code no _item_type.code uchar3 loop_ _item_examples.case _item_examples.detail ALA 'alanine' ARG 'arginine' ASN 'asparagine' ASP 'aspartic acid' ASX 'ambiguous asparagine/aspartic acid' CYS 'cysteine' GLN 'glutamine' GLU 'glutamic acid' GLY 'glycine' GLX 'ambiguous glutamine/glutamic acid' HIS 'histidine' ILE 'isoleucine' LEU 'leucine' LYS 'lysine' MET 'methionine' PHE 'phenylalanine' PRO 'proline' SER 'serine' THR 'threonine' TRP 'tryptophan' TRY 'tyrosine' VAL 'valine' 1MA '1-methyladenosine' 5MC '5-methylcytosine' OMC '2(prime)-O-methylcytodine' 1MG '1-methylguanosine' 2MG 'N(2)-methylguanosine' M2G 'N(2)-dimethylguanosine' 7MG '7-methylguanosine' 0MG '2(prime)-O-methylguanosine' H2U 'dihydrouridine' 5MU 'ribosylthymidine' PSU 'pseudouridine' ACE 'acetic acid' FOR 'formic acid' HOH 'water' UNK 'other' save_ save__chem_comp.type _item_description.description ; For standard polymer components, the type of the monomer. Note that monomers that will form polymers are of three types: linking monomers, monomers with some type of N-terminal (or 5') cap and monomers with some type of C-terminal (or 3') cap. ; loop_ _item.name _item.category_id _item.mandatory_code '_chem_comp.type' chem_comp yes '_chem_comp_link.type_comp_1' chem_comp_link yes '_chem_comp_link.type_comp_2' chem_comp_link yes loop_ _item_linked.child_name _item_linked.parent_name '_chem_comp_link.type_comp_1' '_chem_comp.type' '_chem_comp_link.type_comp_2' '_chem_comp.type' _item_type.code uline loop_ _item_enumeration.value 'D-peptide linking' 'L-peptide linking' 'D-peptide NH3 amino terminus' 'L-peptide NH3 amino terminus' 'D-peptide COOH carboxy terminus' 'L-peptide COOH carboxy terminus' 'DNA linking' 'RNA linking' 'DNA OH 5 prime terminus' 'RNA OH 5 prime terminus' 'DNA OH 3 prime terminus' 'RNA OH 3 prime terminus' 'D-saccharide 1,4 and 1,4 linking' 'L-saccharide 1,4 and 1,4 linking' 'D-saccharide 1,4 and 1,6 linking' 'L-saccharide 1,4 and 1,6 linking' 'L-saccharide' 'D-saccharide' 'saccharide' 'non-polymer' 'other' save_ ##################### ## CHEM_COMP_ANGLE ## ##################### save_chem_comp_angle _category.description ; Data items in the CHEM_COMP_ANGLE category record details about angles in a chemical component. Angles are designated by three atoms, with the second atom forming the vertex of the angle. Target values may be specified as angles in degrees, as a distance between the first and third atoms, or both. ; _category.id chem_comp_angle _category.mandatory_code no loop_ _category_key.name '_chem_comp_angle.comp_id' '_chem_comp_angle.atom_id_1' '_chem_comp_angle.atom_id_2' '_chem_comp_angle.atom_id_3' loop_ _category_group.id 'inclusive_group' 'chem_comp_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _chem_comp_angle.comp_id _chem_comp_angle.atom_id_1 _chem_comp_angle.atom_id_2 _chem_comp_angle.atom_id_3 _chem_comp_angle.value_angle _chem_comp_angle.value_dist phe N CA C xxx.xx x.xx phe CA C O xxx.xx x.xx phe CB CA C xxx.xx x.xx phe CB CA N xxx.xx x.xx phe CA CB CG xxx.xx x.xx phe CB CG CD1 xxx.xx x.xx phe CB CG CD2 xxx.xx x.xx phe CD1 CG CD2 xxx.xx x.xx phe CG CD1 CE1 xxx.xx x.xx phe CD1 CE1 CZ xxx.xx x.xx phe CE1 CZ CE2 xxx.xx x.xx phe CZ CE2 CD2 xxx.xx x.xx phe CG CD2 CE2 xxx.xx x.xx val N CA C xxx.xx x.xx val CA C O xxx.xx x.xx val CB CA C xxx.xx x.xx val CB CA N xxx.xx x.xx val CA CB CG1 xxx.xx x.xx val CA CB CG2 xxx.xx x.xx val CG1 CB CG2 xxx.xx x.xx ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__chem_comp_angle.atom_id_1 _item_description.description ; The ID of the first of the three atoms that define the angle. This data item is a pointer to _chem_comp_atom.atom_id in the CHEM_COMP_ATOM category. ; _item.name '_chem_comp_angle.atom_id_1' _item.mandatory_code yes loop_ _item_dependent.dependent_name '_chem_comp_angle.atom_id_2' '_chem_comp_angle.atom_id_3' save_ save__chem_comp_angle.atom_id_2 _item_description.description ; The ID of the second of the three atoms that define the angle. The second atom is taken to be the apex of the angle. This data item is a pointer to _chem_comp_atom.atom_id in the CHEM_COMP_ATOM category. ; _item.name '_chem_comp_angle.atom_id_2' _item.mandatory_code yes loop_ _item_dependent.dependent_name '_chem_comp_angle.atom_id_1' '_chem_comp_angle.atom_id_3' save_ save__chem_comp_angle.atom_id_3 _item_description.description ; The ID of the third of the three atoms that define the angle. This data item is a pointer to _chem_comp_atom.atom_id in the CHEM_COMP_ATOM category. ; _item.name '_chem_comp_angle.atom_id_3' _item.mandatory_code yes loop_ _item_dependent.dependent_name '_chem_comp_angle.atom_id_1' '_chem_comp_angle.atom_id_2' save_ save__chem_comp_angle.comp_id _item_description.description ; This data item is a pointer to _chem_comp.id in the CHEM_COMP category. ; _item.name '_chem_comp_angle.comp_id' _item.mandatory_code yes save_ save__chem_comp_angle.value_angle _item_description.description ; The value that should be taken as the target value for the angle associated with the specified atoms, expressed in degrees. ; _item.name '_chem_comp_angle.value_angle' _item.category_id chem_comp_angle _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 180.0 180.0 180.0 0.0 0.0 0.0 _item_related.related_name '_chem_comp_angle.value_angle_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code degrees save_ save__chem_comp_angle.value_angle_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _chem_comp_angle.value_angle. ; _item.name '_chem_comp_angle.value_angle_esd' _item.category_id chem_comp_angle _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 180.0 180.0 180.0 0.0 0.0 0.0 _item_related.related_name '_chem_comp_angle.value_angle' _item_related.function_code associated_value _item_type.code float _item_units.code degrees save_ save__chem_comp_angle.value_dist _item_description.description ; The value that should be taken as the target value for the angle associated with the specified atoms, expressed as the distance between the atoms specified by _chem_comp_angle.atom_id_1 and _chem_comp_angle.atom_id_3. ; _item.name '_chem_comp_angle.value_dist' _item.category_id chem_comp_angle _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_chem_comp_angle.value_dist_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code angstroms save_ save__chem_comp_angle.value_dist_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _chem_comp_angle.value_dist. ; _item.name '_chem_comp_angle.value_dist_esd' _item.category_id chem_comp_angle _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_chem_comp_angle.value_dist' _item_related.function_code associated_value _item_type.code float _item_units.code angstroms save_ #################### ## CHEM_COMP_ATOM ## #################### save_chem_comp_atom _category.description ; Data items in the CHEM_COMP_ATOM category record details about the atoms in a chemical component. Specifying the atomic coordinates for the components in this category is an alternative to specifying the structure of the component via bonds, angles, planes etc. in the appropriate CHEM_COMP subcategories. ; _category.id chem_comp_atom _category.mandatory_code no loop_ _category_key.name '_chem_comp_atom.comp_id' '_chem_comp_atom.atom_id' loop_ _category_group.id 'inclusive_group' 'chem_comp_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _chem_comp_atom.comp_id _chem_comp_atom.atom_id _chem_comp_atom.type_symbol _chem_comp_atom.substruct_code _chem_comp_atom.model_Cartn_x _chem_comp_atom.model_Cartn_y _chem_comp_atom.model_Cartn_z phe N N main 1.20134 0.84658 0.00000 phe CA C main 0.00000 0.00000 0.00000 phe C C main -1.25029 0.88107 0.00000 phe O O main -2.18525 0.66029 -0.78409 phe CB C side 0.00662 -1.03603 1.11081 phe CG C side 0.03254 -0.49711 2.50951 phe CD1 C side -1.15813 -0.12084 3.13467 phe CE1 C side -1.15720 0.38038 4.42732 phe CZ C side 0.05385 0.51332 5.11032 phe CE2 C side 1.26137 0.11613 4.50975 phe CD2 C side 1.23668 -0.38351 3.20288 val N N main 1.20134 0.84658 0.00000 val CA C main 0.00000 0.00000 0.00000 val C C main -1.25029 0.88107 0.00000 val O O main -2.18525 0.66029 -0.78409 val CB C side 0.05260 -0.99339 1.17429 val CG1 C side -0.13288 -0.31545 2.52668 val CG2 C side -0.94265 -2.12930 0.99811 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__chem_comp_atom.alt_atom_id _item_description.description ; An alternative identifier for the atom. This data item would be used in cases where alternative nomenclatures exist for labelling atoms in a group. ; _item.name '_chem_comp_atom.alt_atom_id' _item.category_id chem_comp_atom _item.mandatory_code no _item_type.code line save_ save__chem_comp_atom.atom_id _item_description.description ; The value of _chem_comp_atom.atom_id must uniquely identify each atom in each monomer in the CHEM_COMP_ATOM list. The atom identifiers need not be unique over all atoms in the data block; they need only be unique for each atom in a component. Note that this item need not be a number; it can be any unique identifier. ; loop_ _item.name _item.category_id _item.mandatory_code '_chem_comp_atom.atom_id' chem_comp_atom yes '_atom_site.label_atom_id' atom_site no '_chem_comp_angle.atom_id_1' chem_comp_angle yes '_chem_comp_angle.atom_id_2' chem_comp_angle yes '_chem_comp_angle.atom_id_3' chem_comp_angle yes '_chem_comp_bond.atom_id_1' chem_comp_bond yes '_chem_comp_bond.atom_id_2' chem_comp_bond yes '_chem_comp_chir.atom_id' chem_comp_chir yes '_chem_comp_chir_atom.atom_id' chem_comp_chir_atom yes '_chem_comp_plane_atom.atom_id' chem_comp_plane_atom yes '_chem_comp_tor.atom_id_1' chem_comp_tor yes '_chem_comp_tor.atom_id_2' chem_comp_tor yes '_chem_comp_tor.atom_id_3' chem_comp_tor yes '_chem_comp_tor.atom_id_4' chem_comp_tor yes '_geom_angle.atom_site_label_atom_id_1' geom_angle no '_geom_angle.atom_site_label_atom_id_2' geom_angle no '_geom_angle.atom_site_label_atom_id_3' geom_angle no '_geom_bond.atom_site_label_atom_id_1' geom_bond no '_geom_bond.atom_site_label_atom_id_2' geom_bond no '_geom_contact.atom_site_label_atom_id_1' geom_contact no '_geom_contact.atom_site_label_atom_id_2' geom_contact no '_geom_hbond.atom_site_label_atom_id_A' geom_hbond no '_geom_hbond.atom_site_label_atom_id_D' geom_hbond no '_geom_hbond.atom_site_label_atom_id_H' geom_hbond no '_geom_torsion.atom_site_label_atom_id_1' geom_torsion no '_geom_torsion.atom_site_label_atom_id_2' geom_torsion no '_geom_torsion.atom_site_label_atom_id_3' geom_torsion no '_geom_torsion.atom_site_label_atom_id_4' geom_torsion no '_struct_conn.ptnr1_label_atom_id' struct_conn yes '_struct_conn.ptnr2_label_atom_id' struct_conn yes '_struct_sheet_hbond.range_1_beg_label_atom_id' struct_sheet_hbond yes '_struct_sheet_hbond.range_1_end_label_atom_id' struct_sheet_hbond yes '_struct_sheet_hbond.range_2_beg_label_atom_id' struct_sheet_hbond yes '_struct_sheet_hbond.range_2_end_label_atom_id' struct_sheet_hbond yes '_struct_site_gen.label_atom_id' struct_site_gen yes loop_ _item_linked.child_name _item_linked.parent_name '_atom_site.label_atom_id' '_chem_comp_atom.atom_id' '_chem_comp_angle.atom_id_1' '_chem_comp_atom.atom_id' '_chem_comp_angle.atom_id_2' '_chem_comp_atom.atom_id' '_chem_comp_angle.atom_id_3' '_chem_comp_atom.atom_id' '_chem_comp_bond.atom_id_1' '_chem_comp_atom.atom_id' '_chem_comp_bond.atom_id_2' '_chem_comp_atom.atom_id' '_chem_comp_chir.atom_id' '_chem_comp_atom.atom_id' '_chem_comp_chir_atom.atom_id' '_chem_comp_atom.atom_id' '_chem_comp_plane_atom.atom_id' '_chem_comp_atom.atom_id' '_chem_comp_tor.atom_id_1' '_chem_comp_atom.atom_id' '_chem_comp_tor.atom_id_2' '_chem_comp_atom.atom_id' '_chem_comp_tor.atom_id_3' '_chem_comp_atom.atom_id' '_chem_comp_tor.atom_id_4' '_chem_comp_atom.atom_id' '_geom_angle.atom_site_label_atom_id_1' '_atom_site.label_atom_id' '_geom_angle.atom_site_label_atom_id_2' '_atom_site.label_atom_id' '_geom_angle.atom_site_label_atom_id_3' '_atom_site.label_atom_id' '_geom_bond.atom_site_label_atom_id_1' '_atom_site.label_atom_id' '_geom_bond.atom_site_label_atom_id_2' '_atom_site.label_atom_id' '_geom_contact.atom_site_label_atom_id_1' '_atom_site.label_atom_id' '_geom_contact.atom_site_label_atom_id_2' '_atom_site.label_atom_id' '_geom_hbond.atom_site_label_atom_id_A' '_atom_site.label_atom_id' '_geom_hbond.atom_site_label_atom_id_D' '_atom_site.label_atom_id' '_geom_hbond.atom_site_label_atom_id_H' '_atom_site.label_atom_id' '_geom_torsion.atom_site_label_atom_id_1' '_atom_site.label_atom_id' '_geom_torsion.atom_site_label_atom_id_2' '_atom_site.label_atom_id' '_geom_torsion.atom_site_label_atom_id_3' '_atom_site.label_atom_id' '_geom_torsion.atom_site_label_atom_id_4' '_atom_site.label_atom_id' '_struct_conn.ptnr1_label_atom_id' '_atom_site.label_atom_id' '_struct_conn.ptnr2_label_atom_id' '_atom_site.label_atom_id' '_struct_sheet_hbond.range_1_beg_label_atom_id' '_atom_site.label_atom_id' '_struct_sheet_hbond.range_1_end_label_atom_id' '_atom_site.label_atom_id' '_struct_sheet_hbond.range_2_beg_label_atom_id' '_atom_site.label_atom_id' '_struct_sheet_hbond.range_2_end_label_atom_id' '_atom_site.label_atom_id' '_struct_site_gen.label_atom_id' '_atom_site.label_atom_id' _item_type.code atcode save_ save__chem_comp_atom.charge _item_description.description ; The net integer charge assigned to this atom. This is the formal charge assignment normally found in chemical diagrams. ; _item.name '_chem_comp_atom.charge' _item.category_id chem_comp_atom _item.mandatory_code no _item_default.value 0 loop_ _item_range.maximum _item_range.minimum 8 8 8 -8 -8 -8 _item_type.code int loop_ _item_examples.case _item_examples.detail 1 'for an ammonium nitrogen' -1 'for a chloride ion' save_ save__chem_comp_atom.model_Cartn_x _item_description.description ; The x component of the coordinates for this atom in this component specified as orthogonal angstroms. The choice of reference axis frame for the coordinates is arbitrary. The set of coordinates input for the entity here is intended to correspond to the atomic model used to generate restraints for structure refinement, not to atom sites in the ATOM_SITE list. ; _item.name '_chem_comp_atom.model_Cartn_x' _item.category_id chem_comp_atom _item.mandatory_code no loop_ _item_dependent.dependent_name '_chem_comp_atom.model_Cartn_y' '_chem_comp_atom.model_Cartn_z' _item_related.related_name '_chem_comp_atom.model_Cartn_x_esd' _item_related.function_code associated_esd _item_sub_category.id cartesian_coordinate _item_type.code float _item_type_conditions.code esd _item_units.code angstroms save_ save__chem_comp_atom.model_Cartn_x_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _chem_comp_atom.model_Cartn_x. ; _item.name '_chem_comp_atom.model_Cartn_x_esd' _item.category_id chem_comp_atom _item.mandatory_code no # _item_default.value 0.0 loop_ _item_dependent.dependent_name '_chem_comp_atom.model_Cartn_y_esd' '_chem_comp_atom.model_Cartn_z_esd' _item_related.related_name '_chem_comp_atom.model_Cartn_x' _item_related.function_code associated_value _item_sub_category.id cartesian_coordinate_esd _item_type.code float _item_units.code angstroms save_ save__chem_comp_atom.model_Cartn_y _item_description.description ; The y component of the coordinates for this atom in this component specified as orthogonal angstroms. The choice of reference axis frame for the coordinates is arbitrary. The set of coordinates input for the entity here is intended to correspond to the atomic model used to generate restraints for structure refinement, not to atom sites in the ATOM_SITE list. ; _item.name '_chem_comp_atom.model_Cartn_y' _item.category_id chem_comp_atom _item.mandatory_code no loop_ _item_dependent.dependent_name '_chem_comp_atom.model_Cartn_x' '_chem_comp_atom.model_Cartn_z' _item_related.related_name '_chem_comp_atom.model_Cartn_y_esd' _item_related.function_code associated_esd _item_sub_category.id cartesian_coordinate _item_type.code float _item_type_conditions.code esd _item_units.code angstroms save_ save__chem_comp_atom.model_Cartn_y_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _chem_comp_atom.model_Cartn_y. ; _item.name '_chem_comp_atom.model_Cartn_y_esd' _item.category_id chem_comp_atom _item.mandatory_code no # _item_default.value 0.0 loop_ _item_dependent.dependent_name '_chem_comp_atom.model_Cartn_x_esd' '_chem_comp_atom.model_Cartn_z_esd' _item_related.related_name '_chem_comp_atom.model_Cartn_y' _item_related.function_code associated_value _item_sub_category.id cartesian_coordinate_esd _item_type.code float _item_units.code angstroms save_ save__chem_comp_atom.model_Cartn_z _item_description.description ; The z component of the coordinates for this atom in this component specified as orthogonal angstroms. The choice of reference axis frame for the coordinates is arbitrary. The set of coordinates input for the entity here is intended to correspond to the atomic model used to generate restraints for structure refinement, not to atom sites in the ATOM_SITE list. ; _item.name '_chem_comp_atom.model_Cartn_z' _item.category_id chem_comp_atom _item.mandatory_code no loop_ _item_dependent.dependent_name '_chem_comp_atom.model_Cartn_x' '_chem_comp_atom.model_Cartn_y' _item_related.related_name '_chem_comp_atom.model_Cartn_z_esd' _item_related.function_code associated_esd _item_sub_category.id cartesian_coordinate _item_type.code float _item_type_conditions.code esd _item_units.code angstroms save_ save__chem_comp_atom.model_Cartn_z_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _chem_comp_atom.model_Cartn_z. ; _item.name '_chem_comp_atom.model_Cartn_z_esd' _item.category_id chem_comp_atom _item.mandatory_code no # _item_default.value 0.0 loop_ _item_dependent.dependent_name '_chem_comp_atom.model_Cartn_x_esd' '_chem_comp_atom.model_Cartn_y_esd' _item_related.related_name '_chem_comp_atom.model_Cartn_z' _item_related.function_code associated_value _item_sub_category.id cartesian_coordinate_esd _item_type.code float _item_units.code angstroms save_ save__chem_comp_atom.comp_id _item_description.description ; This data item is a pointer to _chem_comp.id in the CHEM_COMP category. ; _item.name '_chem_comp_atom.comp_id' _item.mandatory_code yes save_ save__chem_comp_atom.partial_charge _item_description.description ; The partial charge assigned to this atom. ; _item.name '_chem_comp_atom.partial_charge' _item.category_id chem_comp_atom _item.mandatory_code no _item_type.code float save_ save__chem_comp_atom.substruct_code _item_description.description ; This data item assigns the atom to a substructure of the component, if appropriate. ; _item.name '_chem_comp_atom.substruct_code' _item.category_id chem_comp_atom _item.mandatory_code no _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail main 'main chain of an amino acid' side 'side chain of an amino acid' base 'base of a nucleic acid' phos 'phosphate of a nucleic acid' sugar 'sugar of a nucleic acid' none 'not appropriate for this monomer' save_ #save_chem_comp_atom.type_energy # _item_description.description #; This data item is a pointer to _atom_type_energy.type in the # ATOM_TYPE_ENERGY category. #; # save_ save__chem_comp_atom.type_symbol _item_description.description ; This data item is a pointer to _atom_type.symbol in the ATOM_TYPE category. ; _item.name '_chem_comp_atom.type_symbol' _item.mandatory_code yes save_ #################### ## CHEM_COMP_BOND ## #################### save_chem_comp_bond _category.description ; Data items in the CHEM_COMP_BOND category record details about the bonds between atoms in a chemical component. Target values may be specified as bond orders, as a distance between the two atoms, or both. ; _category.id chem_comp_bond _category.mandatory_code no loop_ _category_key.name '_chem_comp_bond.comp_id' '_chem_comp_bond.atom_id_1' '_chem_comp_bond.atom_id_2' loop_ _category_group.id 'inclusive_group' 'chem_comp_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _chem_comp_bond.comp_id _chem_comp_bond.atom_id_1 _chem_comp_bond.atom_id_2 _chem_comp_bond.value_order phe N CA sing phe CA C sing phe C O doub phe CB CA sing phe CB CG sing phe CG CD1 arom phe CD1 CE1 arom phe CE1 CZ arom phe CZ CE2 arom phe CE2 CD2 arom phe CD2 CG arom val N CA sing val CA C sing val C O doub val CB CA sing val CB CG1 sing val CB CG2 sing ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__chem_comp_bond.atom_id_1 _item_description.description ; The ID of the first of the two atoms that define the bond. This data item is a pointer to _chem_comp_atom.atom_id in the CHEM_COMP_ATOM category. ; _item.name '_chem_comp_bond.atom_id_1' _item.mandatory_code yes _item_dependent.dependent_name '_chem_comp_bond.atom_id_2' save_ save__chem_comp_bond.atom_id_2 _item_description.description ; The ID of the second of the two atoms that define the bond. This data item is a pointer to _chem_comp_atom.atom_id in the CHEM_COMP_ATOM category. ; _item.name '_chem_comp_bond.atom_id_2' _item.mandatory_code yes _item_dependent.dependent_name '_chem_comp_bond.atom_id_1' save_ save__chem_comp_bond.comp_id _item_description.description ; This data item is a pointer to _chem_comp.id in the CHEM_COMP category. ; _item.name '_chem_comp_bond.comp_id' _item.mandatory_code yes save_ save__chem_comp_bond.value_order _item_description.description ; The value that should be taken as the target for the chemical bond associated with the specified atoms, expressed as a bond order. ; _item.name '_chem_comp_bond.value_order' _item.category_id chem_comp_bond _item.mandatory_code no _item_default.value sing _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail sing 'single bond' doub 'double bond' trip 'triple bond' quad 'quadruple bond' arom 'aromatic bond' poly 'polymeric bond' delo 'delocalized double bond' pi 'pi bond' save_ save__chem_comp_bond.value_dist _item_description.description ; The value that should be taken as the target for the chemical bond associated with the specified atoms, expressed as a distance. ; _item.name '_chem_comp_bond.value_dist' _item.category_id chem_comp_bond _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_chem_comp_bond.value_dist_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code angstroms save_ save__chem_comp_bond.value_dist_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _chem_comp_bond.value_dist. ; _item.name '_chem_comp_bond.value_dist_esd' _item.category_id chem_comp_bond _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_chem_comp_bond.value_dist' _item_related.function_code associated_value _item_type.code float _item_units.code angstroms save_ #################### ## CHEM_COMP_CHIR ## #################### save_chem_comp_chir _category.description ; Data items in the CHEM_COMP_CHIR category provide details about the chiral centres in a chemical component. The atoms bonded to the chiral atom are specified in the CHEM_COMP_CHIR_ATOM category. ; _category.id chem_comp_chir _category.mandatory_code no loop_ _category_key.name '_chem_comp_chir.comp_id' '_chem_comp_chir.id' loop_ _category_group.id 'inclusive_group' 'chem_comp_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _chem_comp_chir.comp_id _chem_comp_chir.id _chem_comp_chir.atom_id phe phe1 CA val val1 CA # - - - - data truncated for brevity - - - - ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__chem_comp_chir.atom_id _item_description.description ; The ID of the atom that is a chiral centre. This data item is a pointer to _chem_comp_atom.atom_id in the CHEM_COMP_ATOM category. ; _item.name '_chem_comp_chir.atom_id' _item.mandatory_code yes save_ save__chem_comp_chir.atom_config _item_description.description ; The chiral configuration of the atom that is a chiral centre. ; _item.name '_chem_comp_chir.atom_config' _item.category_id chem_comp_chir _item.mandatory_code no _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail R 'absolute configuration R' S 'absolute configuration S' save_ save__chem_comp_chir.id _item_description.description ; The value of _chem_comp_chir.id must uniquely identify a record in the CHEM_COMP_CHIR list. ; loop_ _item.name _item.category_id _item.mandatory_code '_chem_comp_chir.id' chem_comp_chir yes '_chem_comp_chir_atom.chir_id' chem_comp_chir_atom yes loop_ _item_linked.child_name _item_linked.parent_name '_chem_comp_chir_atom.chir_id' '_chem_comp_chir.id' _item_type.code code save_ save__chem_comp_chir.comp_id _item_description.description ; This data item is a pointer to _chem_comp.id in the CHEM_COMP category. ; _item.name '_chem_comp_chir.comp_id' _item.mandatory_code yes save_ save__chem_comp_chir.number_atoms_all _item_description.description ; The total number of atoms bonded to the atom specified by _chem_comp_chir.atom_id. ; _item.name '_chem_comp_chir.number_atoms_all' _item.category_id chem_comp_chir _item.mandatory_code no _item_type.code int save_ save__chem_comp_chir.number_atoms_nh _item_description.description ; The number of non-hydrogen atoms bonded to the atom specified by _chem_comp_chir.atom_id. ; _item.name '_chem_comp_chir.number_atoms_nh' _item.category_id chem_comp_chir _item.mandatory_code no _item_type.code int save_ save__chem_comp_chir.volume_flag _item_description.description ; A flag to indicate whether a chiral volume should match the standard value in both magnitude and sign, or in magnitude only. ; _item.name '_chem_comp_chir.volume_flag' _item.category_id chem_comp_chir _item.mandatory_code no _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail sign 'match magnitude and sign' nosign 'match magnitude only' save_ save__chem_comp_chir.volume_three _item_description.description ; The chiral volume, V~c~, for chiral centres that involve a chiral atom bonded to three non-hydrogen atoms and one hydrogen atom. V~c~ = V1 * (V2 X V3) V1 = the vector distance from the atom specified by _chem_comp_chir.atom_id to the first atom in the CHEM_COMP_CHIR_ATOM list V2 = the vector distance from the atom specified by _chem_comp_chir.atom_id to the second atom in the CHEM_COMP_CHIR_ATOM list V3 = the vector distance from the atom specified by _chem_comp_chir.atom_id to the third atom in the CHEM_COMP_CHIR_ATOM list * = the vector dot product X = the vector cross product ; _item.name '_chem_comp_chir.volume_three' _item.category_id chem_comp_chir _item.mandatory_code no _item_related.related_name '_chem_comp_chir.volume_three_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code angstroms_cubed save_ save__chem_comp_chir.volume_three_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _chem_comp_chir.volume_three. ; _item.name '_chem_comp_chir.volume_three_esd' _item.category_id chem_comp_chir _item.mandatory_code no _item_related.related_name '_chem_comp_chir.volume_three' _item_related.function_code associated_value _item_type.code float _item_units.code angstroms_cubed save_ ######################### ## CHEM_COMP_CHIR_ATOM ## ######################### save_chem_comp_chir_atom _category.description ; Data items in the CHEM_COMP_CHIR_ATOM category enumerate the atoms bonded to a chiral atom within a chemical component. ; _category.id chem_comp_chir_atom _category.mandatory_code no loop_ _category_key.name '_chem_comp_chir_atom.chir_id' '_chem_comp_chir_atom.atom_id' '_chem_comp_chir_atom.comp_id' loop_ _category_group.id 'inclusive_group' 'chem_comp_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _chem_comp_chir_atom.comp_id _chem_comp_chir_atom.chir_id _chem_comp_chir_atom.atom_id phe 1 N phe 1 C phe 1 CB val 1 N val 1 C val 1 CB # - - - - data truncated for brevity - - - - ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__chem_comp_chir_atom.atom_id _item_description.description ; The ID of an atom bonded to the chiral atom. This data item is a pointer to _chem_comp_atom.atom_id in the CHEM_COMP_ATOM category. ; _item.name '_chem_comp_chir_atom.atom_id' _item.mandatory_code yes save_ save__chem_comp_chir_atom.chir_id _item_description.description ; This data item is a pointer to _chem_comp_chir.id in the CHEM_COMP_CHIR category. ; _item.name '_chem_comp_chir_atom.chir_id' _item.mandatory_code yes save_ save__chem_comp_chir_atom.comp_id _item_description.description ; This data item is a pointer to _chem_comp.id in the CHEM_COMP category. ; _item.name '_chem_comp_chir_atom.comp_id' _item.mandatory_code yes save_ save__chem_comp_chir_atom.dev _item_description.description ; The standard uncertainty (estimated standard deviation) of the position of this atom from the plane defined by all of the atoms in the plane. ; _item.name '_chem_comp_chir_atom.dev' _item.category_id chem_comp_chir_atom _item.mandatory_code no _item_type.code float _item_units.code angstroms save_ #################### ## CHEM_COMP_LINK ## #################### save_chem_comp_link _category.description ; Data items in the CHEM_COMP_LINK category give details about the links between chemical components. ; _category.id chem_comp_link _category.mandatory_code no _category_key.name '_chem_comp_link.link_id' loop_ _category_group.id 'inclusive_group' 'chem_link_group' # loop_ # _category_examples.detail # _category_examples.case # # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - # ; # Example 1 - from nucleotide external reference dictionary Nucleic # Database Project 1997. # ; # ; # _chem_comp_link.link_id ribose_adenine # _chem_comp_link.type_comp_1 ribose # _chem_comp_link.type_comp_2 adenine # _chem_comp_link.details # ; # Defines the linkage between adenine base and ribose sugar # ; # ; # # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__chem_comp_link.link_id _item_description.description ; This data item is a pointer to _chem_link.id in the CHEM_LINK category. ; _item.name '_chem_comp_link.link_id' _item.mandatory_code yes save_ save__chem_comp_link.details _item_description.description ; A description of special aspects of a link between chemical components in the structure. ; _item.name '_chem_comp_link.details' _item.category_id chem_comp_link _item.mandatory_code no _item_type.code text save_ save__chem_comp_link.type_comp_1 _item_description.description ; The type of the first of the two components joined by the link. This data item is a pointer to _chem_comp.type in the CHEM_COMP category. ; _item.name '_chem_comp_link.type_comp_1' _item.mandatory_code yes save_ save__chem_comp_link.type_comp_2 _item_description.description ; The type of the second of the two components joined by the link. This data item is a pointer to _chem_comp.type in the CHEM_COMP category. ; _item.name '_chem_comp_link.type_comp_2' _item.mandatory_code yes save_ ##################### ## CHEM_COMP_PLANE ## ##################### save_chem_comp_plane _category.description ; Data items in the CHEM_COMP_PLANE category provide identifiers for the planes in a chemical component. The atoms in the plane are specified in the CHEM_COMP_PLANE_ATOM category. ; _category.id chem_comp_plane _category.mandatory_code no loop_ _category_key.name '_chem_comp_plane.comp_id' '_chem_comp_plane.id' loop_ _category_group.id 'inclusive_group' 'chem_comp_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _chem_comp_plane.comp_id _chem_comp_plane.id phe phe1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__chem_comp_plane.id _item_description.description ; The value of _chem_comp_plane.id must uniquely identify a record in the CHEM_COMP_PLANE list. ; loop_ _item.name _item.category_id _item.mandatory_code '_chem_comp_plane.id' chem_comp_plane yes '_chem_comp_plane_atom.plane_id' chem_comp_plane_atom yes loop_ _item_linked.child_name _item_linked.parent_name '_chem_comp_plane_atom.plane_id' '_chem_comp_plane.id' _item_type.code code save_ save__chem_comp_plane.comp_id _item_description.description ; This data item is a pointer to _chem_comp.id in the CHEM_COMP category. ; _item.name '_chem_comp_plane.comp_id' _item.mandatory_code yes save_ save__chem_comp_plane.number_atoms_all _item_description.description ; The total number of atoms in the plane. ; _item.name '_chem_comp_plane.number_atoms_all' _item.category_id chem_comp_plane _item.mandatory_code no _item_type.code int save_ save__chem_comp_plane.number_atoms_nh _item_description.description ; The number of non-hydrogen atoms in the plane. ; _item.name '_chem_comp_plane.number_atoms_nh' _item.category_id chem_comp_plane _item.mandatory_code no _item_type.code int save_ ########################## ## CHEM_COMP_PLANE_ATOM ## ########################## save_chem_comp_plane_atom _category.description ; Data items in the CHEM_COMP_PLANE_ATOM category enumerate the atoms in a plane within a chemical component. ; _category.id chem_comp_plane_atom _category.mandatory_code no loop_ _category_key.name '_chem_comp_plane_atom.plane_id' '_chem_comp_plane_atom.atom_id' '_chem_comp_plane_atom.comp_id' loop_ _category_group.id 'inclusive_group' 'chem_comp_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _chem_comp_plane_atom.plane_id _chem_comp_plane_atom.comp_id _chem_comp_plane_atom.atom_id phe1 phe CB phe1 phe CG phe1 phe CD1 phe1 phe CE1 phe1 phe CZ phe1 phe CE2 phe1 phe CD2 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__chem_comp_plane_atom.atom_id _item_description.description ; The ID of an atom involved in the plane. This data item is a pointer to _chem_comp_atom.atom_id in the CHEM_COMP_ATOM category. ; _item.name '_chem_comp_plane_atom.atom_id' _item.mandatory_code yes save_ save__chem_comp_plane_atom.comp_id _item_description.description ; This data item is a pointer to _chem_comp.id in the CHEM_COMP category. ; _item.name '_chem_comp_plane_atom.comp_id' _item.mandatory_code yes save_ save__chem_comp_plane_atom.plane_id _item_description.description ; This data item is a pointer to _chem_comp_plane.id in the CHEM_COMP_PLANE category. ; _item.name '_chem_comp_plane_atom.plane_id' _item.mandatory_code yes save_ save__chem_comp_plane_atom.dist_esd _item_description.description ; This data item is the standard deviation of the out-of-plane distance for this atom. ; _item.name '_chem_comp_plane_atom.dist_esd' _item.mandatory_code no _item_type.code float _item_units.code angstroms save_ #################### ## CHEM_COMP_TOR ## #################### save_chem_comp_tor _category.description ; Data items in the CHEM_COMP_TOR category record details about the torsion angles in a chemical component. As torsion angles can have more than one target value, the target values are specified in the CHEM_COMP_TOR_VALUE category. ; _category.id chem_comp_tor _category.mandatory_code no loop_ _category_key.name '_chem_comp_tor.comp_id' '_chem_comp_tor.id' loop_ _category_group.id 'inclusive_group' 'chem_comp_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _chem_comp_tor.comp_id _chem_comp_tor.id _chem_comp_tor.atom_id_1 _chem_comp_tor.atom_id_2 _chem_comp_tor.atom_id_3 _chem_comp_tor.atom_id_4 phe phe_chi1 N CA CB CG phe phe_chi2 CA CB CG CD1 phe phe_ring1 CB CG CD1 CE1 phe phe_ring2 CB CG CD2 CE2 phe phe_ring3 CG CD1 CE1 CZ phe phe_ring4 CD1 CE1 CZ CE2 phe phe_ring5 CE1 CZ CE2 CD2 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__chem_comp_tor.atom_id_1 _item_description.description ; The ID of the first of the four atoms that define the torsion angle. This data item is a pointer to _chem_comp_atom.atom_id in the CHEM_COMP_ATOM category. ; _item.name '_chem_comp_tor.atom_id_1' _item.mandatory_code yes loop_ _item_dependent.dependent_name '_chem_comp_tor.atom_id_2' '_chem_comp_tor.atom_id_3' '_chem_comp_tor.atom_id_4' save_ save__chem_comp_tor.atom_id_2 _item_description.description ; The ID of the second of the four atoms that define the torsion angle. This data item is a pointer to _chem_comp_atom.atom_id in the CHEM_COMP_ATOM category. ; _item.name '_chem_comp_tor.atom_id_2' _item.mandatory_code yes loop_ _item_dependent.dependent_name '_chem_comp_tor.atom_id_1' '_chem_comp_tor.atom_id_3' '_chem_comp_tor.atom_id_4' save_ save__chem_comp_tor.atom_id_3 _item_description.description ; The ID of the third of the four atoms that define the torsion angle. This data item is a pointer to _chem_comp_atom.atom_id in the CHEM_COMP_ATOM category. ; _item.name '_chem_comp_tor.atom_id_3' _item.mandatory_code yes loop_ _item_dependent.dependent_name '_chem_comp_tor.atom_id_1' '_chem_comp_tor.atom_id_2' '_chem_comp_tor.atom_id_4' save_ save__chem_comp_tor.atom_id_4 _item_description.description ; The ID of the fourth of the four atoms that define the torsion angle. This data item is a pointer to _chem_comp_atom.atom_id in the CHEM_COMP_ATOM category. ; _item.name '_chem_comp_tor.atom_id_4' _item.mandatory_code yes loop_ _item_dependent.dependent_name '_chem_comp_tor.atom_id_1' '_chem_comp_tor.atom_id_2' '_chem_comp_tor.atom_id_3' save_ save__chem_comp_tor.id _item_description.description ; The value of _chem_comp_tor.id must uniquely identify a record in the CHEM_COMP_TOR list. ; loop_ _item.name _item.category_id _item.mandatory_code '_chem_comp_tor.id' chem_comp_tor yes '_chem_comp_tor_value.tor_id' chem_comp_tor_value yes loop_ _item_linked.child_name _item_linked.parent_name '_chem_comp_tor_value.tor_id' '_chem_comp_tor.id' _item_type.code code save_ save__chem_comp_tor.comp_id _item_description.description ; This data item is a pointer to _chem_comp.id in the CHEM_COMP category. ; _item.name '_chem_comp_tor.comp_id' _item.mandatory_code yes save_ ########################## ## CHEM_COMP_TOR_VALUE ## ########################## save_chem_comp_tor_value _category.description ; Data items in the CHEM_COMP_TOR_VALUE category record details about the target values for the torsion angles enumerated in the CHEM_COMP_TOR list. Target values may be specified as angles in degrees, as a distance between the first and fourth atoms, or both. ; _category.id chem_comp_tor_value _category.mandatory_code no loop_ _category_key.name '_chem_comp_tor_value.tor_id' '_chem_comp_tor_value.comp_id' loop_ _category_group.id 'inclusive_group' 'chem_comp_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _chem_comp_tor_value.tor_id _chem_comp_tor_value.comp_id _chem_comp_tor_value.angle _chem_comp_tor_value.dist phe_chi1 phe -60.0 2.88 phe_chi1 phe 180.0 3.72 phe_chi1 phe 60.0 2.88 phe_chi2 phe 90.0 3.34 phe_chi2 phe -90.0 3.34 phe_ring1 phe 180.0 3.75 phe_ring2 phe 180.0 3.75 phe_ring3 phe 0.0 2.80 phe_ring4 phe 0.0 2.80 phe_ring5 phe 0.0 2.80 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__chem_comp_tor_value.comp_id _item_description.description ; This data item is a pointer to _chem_comp_atom.comp_id in the CHEM_COMP_ATOM category. ; _item.name '_chem_comp_tor_value.comp_id' _item.mandatory_code yes save_ save__chem_comp_tor_value.tor_id _item_description.description ; This data item is a pointer to _chem_comp_tor.id in the CHEM_COMP_TOR category. ; _item.name '_chem_comp_tor_value.tor_id' _item.mandatory_code yes save_ save__chem_comp_tor_value.angle _item_description.description ; A value that should be taken as a potential target value for the torsion angle associated with the specified atoms, expressed in degrees. ; _item.name '_chem_comp_tor_value.angle' _item.category_id chem_comp_tor_value _item.mandatory_code yes loop_ _item_range.maximum _item_range.minimum 180.0 180.0 180.0 -180.0 -180.0 -180.0 _item_related.related_name '_chem_comp_tor_value.angle_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code degrees save_ save__chem_comp_tor_value.angle_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _chem_comp_tor_value.angle. ; _item.name '_chem_comp_tor_value.angle_esd' _item.category_id chem_comp_tor_value _item.mandatory_code yes loop_ _item_range.maximum _item_range.minimum 180.0 180.0 180.0 -180.0 -180.0 -180.0 _item_related.related_name '_chem_comp_tor_value.angle' _item_related.function_code associated_value _item_type.code float _item_units.code degrees save_ save__chem_comp_tor_value.dist _item_description.description ; A value that should be taken as a potential target value for the torsion angle associated with the specified atoms, expressed as the distance between the atoms specified by _chem_comp_tor.atom_id_1 and _chem_comp_tor.atom_id_4 in the referenced record in the CHEM_COMP_TOR list. Note that the torsion angle cannot be fully specified by a distance (for instance, a torsion angle of -60 degree will yield the same distance as a 60 degree angle). However, the distance specification can be useful for refinement in situations in which the angle is already close to the desired value. ; _item.name '_chem_comp_tor_value.dist' _item.category_id chem_comp_tor_value _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_chem_comp_tor_value.dist_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code angstroms save_ save__chem_comp_tor_value.dist_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _chem_comp_tor_value.dist. ; _item.name '_chem_comp_tor_value.dist_esd' _item.category_id chem_comp_tor_value _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_chem_comp_tor_value.dist' _item_related.function_code associated_value _item_type.code float _item_units.code angstroms save_ ############### ## CHEM_LINK ## ############### save_chem_link _category.description ; Data items in the CHEM_LINK category give details about the links between chemical components. ; _category.id chem_link _category.mandatory_code no _category_key.name '_chem_link.id' loop_ _category_group.id 'inclusive_group' 'chem_link_group' save_ save__chem_link.id _item_description.description ; The value of _chem_link.id must uniquely identify each item in the CHEM_LINK list. ; loop_ _item.name _item.category_id _item.mandatory_code '_chem_link.id' chem_link yes '_chem_link_angle.link_id' chem_link_angle yes '_chem_link_bond.link_id' chem_link_bond yes '_chem_link_chir.link_id' chem_link_chir yes '_chem_link_plane.link_id' chem_link_plane yes '_chem_link_tor.link_id' chem_link_tor yes '_chem_comp_link.link_id' chem_comp_link yes '_entity_link.link_id' entity_link yes loop_ _item_linked.child_name _item_linked.parent_name '_chem_link_angle.link_id' '_chem_link.id' '_chem_link_bond.link_id' '_chem_link.id' '_chem_link_chir.link_id' '_chem_link.id' '_chem_link_plane.link_id' '_chem_link.id' '_chem_link_tor.link_id' '_chem_link.id' '_chem_comp_link.link_id' '_chem_link.id' '_entity_link.link_id' '_chem_link.id' _item_type.code code loop_ _item_examples.case 'peptide' 'oligosaccharide 1,4' 'DNA' save_ save__chem_link.details _item_description.description ; A description of special aspects of a link between chemical components in the structure. ; _item.name '_chem_link.details' _item.category_id chem_link _item.mandatory_code no _item_type.code text save_ ##################### ## CHEM_LINK_ANGLE ## ##################### save_chem_link_angle _category.description ; Data items in the CHEM_LINK_ANGLE category record details about angles in a link between chemical components. ; _category.id chem_link_angle _category.mandatory_code no loop_ _category_key.name '_chem_link_angle.link_id' '_chem_link_angle.atom_id_1' '_chem_link_angle.atom_id_2' '_chem_link_angle.atom_id_3' loop_ _category_group.id 'inclusive_group' 'chem_link_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Engh & Huber parameters [Acta Cryst. (1991), A47, 392-400] as interpreted by J. P. Priestle (1995). Consistent Stereochemical Dictionaries for Refinement and Model Building. CCP4 Daresbury Study Weekend, DL-CONF-95-001, ISSN 1358-6254. Warrington: Daresbury Laboratory. ; ; loop_ _chem_link_angle.link_id _chem_link_angle.value_angle _chem_link_angle.value_angle_esd _chem_link_angle.atom_id_1 _chem_link_angle.atom_1_comp_id _chem_link_angle.atom_id_2 _chem_link_angle.atom_2_comp_id _chem_link_angle.atom_id_3 _chem_link_angle.atom_3_comp_id PEPTIDE 111.2 2.8 N 1 CA 1 C 1 PEPTIDE 120.8 1.7 CA 1 C 1 O 1 PEPTIDE 116.2 2.0 CA 1 C 1 N 2 PEPTIDE 123.0 1.6 O 1 C 1 N 2 PEPTIDE 121.7 1.8 C 1 N 2 CA 2 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__chem_link_angle.atom_1_comp_id _item_description.description ; This data item indicates whether atom 1 is found in the first or the second of the two components connected by the link. ; _item.name '_chem_link_angle.atom_1_comp_id' _item.category_id chem_link_angle _item.mandatory_code no loop_ _item_dependent.dependent_name '_chem_link_angle.atom_2_comp_id' '_chem_link_angle.atom_3_comp_id' loop_ _item_enumeration.value _item_enumeration.detail 1 'the atom is in component 1' 2 'the atom is in component 2' _item_type.code ucode save_ save__chem_link_angle.atom_2_comp_id _item_description.description ; This data item indicates whether atom 2 is found in the first or the second of the two components connected by the link. ; _item.name '_chem_link_angle.atom_2_comp_id' _item.category_id chem_link_angle _item.mandatory_code no loop_ _item_dependent.dependent_name '_chem_link_angle.atom_1_comp_id' '_chem_link_angle.atom_3_comp_id' loop_ _item_enumeration.value _item_enumeration.detail 1 'the atom is in component 1' 2 'the atom is in component 2' _item_type.code ucode save_ save__chem_link_angle.atom_3_comp_id _item_description.description ; This data item indicates whether atom 3 is found in the first or the second of the two components connected by the link. ; _item.name '_chem_link_angle.atom_3_comp_id' _item.category_id chem_link_angle _item.mandatory_code no loop_ _item_dependent.dependent_name '_chem_link_angle.atom_1_comp_id' '_chem_link_angle.atom_2_comp_id' loop_ _item_enumeration.value _item_enumeration.detail 1 'the atom is in component 1' 2 'the atom is in component 2' _item_type.code ucode save_ save__chem_link_angle.atom_id_1 _item_description.description ; The ID of the first of the three atoms that define the angle. An atom with this ID must exist in the component of the type specified by _chem_comp_link.type_comp_1 (or _chem_comp_link.type_comp_2, where the appropriate data item is indicated by the value of _chem_comp_angle.atom_1_comp_id). ; _item.name '_chem_link_angle.atom_id_1' _item.category_id chem_link_angle _item.mandatory_code yes loop_ _item_dependent.dependent_name '_chem_link_angle.atom_id_2' '_chem_link_angle.atom_id_3' _item_type.code code save_ save__chem_link_angle.atom_id_2 _item_description.description ; The ID of the second of the three atoms that define the angle. The second atom is taken to be the apex of the angle. An atom with this ID must exist in the component of the type specified by _chem_comp_link.type_comp_1 (or _chem_comp_link.type_comp_2, where the appropriate data item is indicated by the value of _chem_comp_angle.atom_2_comp_id). ; _item.name '_chem_link_angle.atom_id_2' _item.category_id chem_link_angle _item.mandatory_code yes loop_ _item_dependent.dependent_name '_chem_link_angle.atom_id_1' '_chem_link_angle.atom_id_3' _item_type.code code save_ save__chem_link_angle.atom_id_3 _item_description.description ; The ID of the third of the three atoms that define the angle. An atom with this ID must exist in the component of the type specified by _chem_comp_link.type_comp_1 (or _chem_comp_link.type_comp_2, where the appropriate data item is indicated by the value of _chem_comp_angle.atom_3_comp_id). ; _item.name '_chem_link_angle.atom_id_3' _item.category_id chem_link_angle _item.mandatory_code yes loop_ _item_dependent.dependent_name '_chem_link_angle.atom_id_1' '_chem_link_angle.atom_id_2' _item_type.code code save_ save__chem_link_angle.link_id _item_description.description ; This data item is a pointer to _chem_link.id in the CHEM_LINK category. ; _item.name '_chem_link_angle.link_id' _item.mandatory_code yes save_ save__chem_link_angle.value_angle _item_description.description ; The value that should be taken as the target value for the angle associated with the specified atoms, expressed in degrees. ; _item.name '_chem_link_angle.value_angle' _item.category_id chem_link_angle _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 180.0 180.0 180.0 0.0 0.0 0.0 _item_related.related_name '_chem_link_angle.value_angle_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code degrees save_ save__chem_link_angle.value_angle_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _chem_link_angle.value_angle. ; _item.name '_chem_link_angle.value_angle_esd' _item.category_id chem_link_angle _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 180.0 180.0 180.0 0.0 0.0 0.0 _item_related.related_name '_chem_link_angle.value_angle' _item_related.function_code associated_value _item_type.code float _item_units.code degrees save_ save__chem_link_angle.value_dist _item_description.description ; The value that should be taken as the target value for the angle associated with the specified atoms, expressed as the distance between the atoms specified by _chem_comp_angle.atom_id_1 and _chem_comp_angle.atom_id_3. ; _item.name '_chem_link_angle.value_dist' _item.category_id chem_link_angle _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_chem_link_angle.value_dist_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code angstroms save_ save__chem_link_angle.value_dist_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _chem_comp_angle.value_dist. ; _item.name '_chem_link_angle.value_dist_esd' _item.category_id chem_link_angle _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_chem_link_angle.value_dist' _item_related.function_code associated_value _item_type.code float _item_units.code angstroms save_ #################### ## CHEM_LINK_BOND ## #################### save_chem_link_bond _category.description ; Data items in the CHEM_LINK_BOND category record details about bonds in a link between components in the chemical structure. ; _category.id chem_link_bond _category.mandatory_code no loop_ _category_key.name '_chem_link_bond.link_id' '_chem_link_bond.atom_id_1' '_chem_link_bond.atom_id_2' loop_ _category_group.id 'inclusive_group' 'chem_link_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Engh & Huber parameters [Acta Cryst. (1991), A47, 392-400] as interpreted by J. P. Priestle (1995). Consistent Stereochemical Dictionaries for Refinement and Model Building. CCP4 Daresbury Study Weekend, DL-CONF-95-001, ISSN 1358-6254. Warrington: Daresbury Laboratory. ; ; loop_ _chem_link_bond.link_id _chem_link_bond.value_dist _chem_link_bond.value_dist_esd _chem_link_bond.atom_id_1 _chem_link_bond.atom_1_comp_id _chem_link_bond.atom_id_2 _chem_link_bond.atom_2_comp_id PEPTIDE 1.458 0.019 N 1 CA 1 PEPTIDE 1.525 0.021 CA 1 C 1 PEPTIDE 1.329 0.014 C 1 N 2 PEPTIDE 1.231 0.020 C 1 O 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__chem_link_bond.atom_1_comp_id _item_description.description ; This data item indicates whether atom 1 is found in the first or the second of the two components connected by the link. ; _item.name '_chem_link_bond.atom_1_comp_id' _item.category_id chem_link_bond _item.mandatory_code no loop_ _item_dependent.dependent_name '_chem_link_bond.atom_2_comp_id' loop_ _item_enumeration.value _item_enumeration.detail 1 'the atom is in component 1' 2 'the atom is in component 2' _item_type.code ucode save_ save__chem_link_bond.atom_2_comp_id _item_description.description ; This data item indicates whether atom 2 is found in the first or the second of the two chemical components connected by the link. ; _item.name '_chem_link_bond.atom_2_comp_id' _item.category_id chem_link_bond _item.mandatory_code no _item_dependent.dependent_name '_chem_link_bond.atom_1_comp_id' loop_ _item_enumeration.value _item_enumeration.detail 1 'the atom is in component 1' 2 'the atom is in component 2' _item_type.code ucode save_ save__chem_link_bond.atom_id_1 _item_description.description ; The ID of the first of the two atoms that define the bond. As this data item does not point to a specific atom in a specific chemical component, it is not a child in the linkage sense. ; _item.name '_chem_link_bond.atom_id_1' _item.category_id chem_link_bond _item.mandatory_code yes loop_ _item_dependent.dependent_name '_chem_link_bond.atom_id_2' _item_type.code code save_ save__chem_link_bond.atom_id_2 _item_description.description ; The ID of the second of the two atoms that define the bond. As this data item does not point to a specific atom in a specific component, it is not a child in the linkage sense. ; _item.name '_chem_link_bond.atom_id_2' _item.category_id chem_link_bond _item.mandatory_code yes _item_dependent.dependent_name '_chem_link_bond.atom_id_1' _item_type.code code save_ save__chem_link_bond.link_id _item_description.description ; This data item is a pointer to _chem_link.id in the CHEM_LINK category. ; _item.name '_chem_link_bond.link_id' _item.mandatory_code yes save_ save__chem_link_bond.value_dist _item_description.description ; The value that should be taken as the target for the chemical bond associated with the specified atoms, expressed as a distance. ; _item.name '_chem_link_bond.value_dist' _item.category_id chem_link_bond _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_chem_link_bond.value_dist_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code angstroms save_ save__chem_link_bond.value_dist_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _chem_link_bond.value_dist. ; _item.name '_chem_link_bond.value_dist_esd' _item.category_id chem_link_bond _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_chem_link_bond.value_dist' _item_related.function_code associated_value _item_type.code float _item_units.code angstroms save_ save__chem_link_bond.value_order _item_description.description ; The value that should be taken as the target for the chemical bond associated with the specified atoms, expressed as a bond order. ; _item.name '_chem_link_bond.value_order' _item.category_id chem_link_bond _item.mandatory_code no _item_default.value sing _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail sing 'single bond' doub 'double bond' trip 'triple bond' quad 'quadruple bond' arom 'aromatic bond' poly 'polymeric bond' delo 'delocalized double bond' pi 'pi bond' save_ #################### ## CHEM_LINK_CHIR ## #################### save_chem_link_chir _category.description ; Data items in the CHEM_LINK_CHIR category provide details about the chiral centres in a link between two chemical components. The atoms bonded to the chiral atom are specified in the CHEM_LINK_CHIR_ATOM category. ; _category.id chem_link_chir _category.mandatory_code no loop_ _category_key.name '_chem_link_chir.link_id' '_chem_link_chir.id' loop_ _category_group.id 'inclusive_group' 'chem_link_group' save_ save__chem_link_chir.atom_comp_id _item_description.description ; This data item indicates whether the chiral atom is found in the first or the second of the two components connected by the link. ; _item.name '_chem_link_chir.atom_comp_id' _item.category_id chem_link_chir _item.mandatory_code no loop_ _item_enumeration.value _item_enumeration.detail 1 'the atom is in component 1' 2 'the atom is in component 2' _item_type.code ucode save_ save__chem_link_chir.atom_id _item_description.description ; The ID of the atom that is a chiral centre. As this data item does not point to a specific atom in a specific chemical component, it is not a child in the linkage sense. ; _item.name '_chem_link_chir.atom_id' _item.mandatory_code yes _item_type.code code save_ save__chem_link_chir.atom_config _item_description.description ; The chiral configuration of the atom that is a chiral centre. ; _item.name '_chem_link_chir.atom_config' _item.category_id chem_link_chir _item.mandatory_code no _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail R 'absolute configuration R' S 'absolute configuration S' save_ save__chem_link_chir.id _item_description.description ; The value of _chem_link_chir.id must uniquely identify a record in the CHEM_LINK_CHIR list. ; loop_ _item.name _item.category_id _item.mandatory_code '_chem_link_chir.id' chem_link_chir yes '_chem_link_chir_atom.chir_id' chem_link_chir_atom yes loop_ _item_linked.child_name _item_linked.parent_name '_chem_link_chir_atom.chir_id' '_chem_link_chir.id' _item_type.code code save_ save__chem_link_chir.link_id _item_description.description ; This data item is a pointer to _chem_link.id in the CHEM_LINK category. ; _item.name '_chem_link_chir.link_id' _item.mandatory_code yes save_ save__chem_link_chir.number_atoms_all _item_description.description ; The total number of atoms bonded to the atom specified by _chem_link_chir.atom_id. ; _item.name '_chem_link_chir.number_atoms_all' _item.category_id chem_link_chir _item.mandatory_code no _item_type.code int save_ save__chem_link_chir.number_atoms_nh _item_description.description ; The number of non-hydrogen atoms bonded to the atom specified by _chem_link_chir.atom_id. ; _item.name '_chem_link_chir.number_atoms_nh' _item.category_id chem_link_chir _item.mandatory_code no _item_type.code int save_ save__chem_link_chir.volume_flag _item_description.description ; A flag to indicate whether a chiral volume should match the standard value in both magnitude and sign, or in magnitude only. ; _item.name '_chem_link_chir.volume_flag' _item.category_id chem_link_chir _item.mandatory_code no _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail sign 'match magnitude and sign' nosign 'match magnitude only' save_ save__chem_link_chir.volume_three _item_description.description ; The chiral volume, V(c), for chiral centres that involve a chiral atom bonded to three non-hydrogen atoms and one hydrogen atom. V~c~ = V1 * (V2 X V3) V1 = the vector distance from the atom specified by _chem_link_chir.atom_id to the first atom in the CHEM_LINK_CHIR_ATOM list V2 = the vector distance from the atom specified by _chem_link_chir.atom_id to the second atom in the CHEM_LINK_CHIR_ATOM list V3 = the vector distance from the atom specified by _chem_link_chir.atom_id to the third atom in the CHEM_LINK_CHIR_ATOM list * = the vector dot product X = the vector cross product ; _item.name '_chem_link_chir.volume_three' _item.category_id chem_link_chir _item.mandatory_code no _item_related.related_name '_chem_link_chir.volume_three_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code angstroms_cubed save_ save__chem_link_chir.volume_three_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _chem_link_chir.volume_three. ; _item.name '_chem_link_chir.volume_three_esd' _item.category_id chem_link_chir _item.mandatory_code no _item_related.related_name '_chem_link_chir.volume_three' _item_related.function_code associated_value _item_type.code float _item_units.code angstroms_cubed save_ ######################### ## CHEM_LINK_CHIR_ATOM ## ######################### save_chem_link_chir_atom _category.description ; Data items in the CHEM_LINK_CHIR_ATOM category enumerate the atoms bonded to a chiral atom in a link between two chemical components. ; _category.id chem_link_chir_atom _category.mandatory_code no loop_ _category_key.name '_chem_link_chir_atom.chir_id' '_chem_link_chir_atom.atom_id' loop_ _category_group.id 'inclusive_group' 'chem_link_group' save_ save__chem_link_chir_atom.atom_comp_id _item_description.description ; This data item indicates whether the atom bonded to a chiral atom is found in the first or the second of the two components connected by the link. ; _item.name '_chem_link_chir_atom.atom_comp_id' _item.category_id chem_link_chir_atom _item.mandatory_code no loop_ _item_enumeration.value _item_enumeration.detail 1 'the atom is in component 1' 2 'the atom is in component 2' _item_type.code ucode save_ save__chem_link_chir_atom.atom_id _item_description.description ; The ID of an atom bonded to the chiral atom. As this data item does not point to a specific atom in a specific chemical component, it is not a child in the linkage sense. ; _item.name '_chem_link_chir_atom.atom_id' _item.mandatory_code yes _item_type.code code save_ save__chem_link_chir_atom.chir_id _item_description.description ; This data item is a pointer to _chem_link_chir.id in the CHEM_LINK_CHIR category. ; _item.name '_chem_link_chir_atom.chir_id' _item.mandatory_code yes save_ save__chem_link_chir_atom.dev _item_description.description ; The standard uncertainty (estimated standard deviation) of the position of this atom from the plane defined by all of the atoms in the plane. ; _item.name '_chem_link_chir_atom.dev' _item.category_id chem_link_chir_atom _item.mandatory_code no _item_type.code float _item_units.code angstroms save_ ##################### ## CHEM_LINK_PLANE ## ##################### save_chem_link_plane _category.description ; Data items in the CHEM_LINK_PLANE category provide identifiers for the planes in a link between two chemical components. The atoms in the plane are specified in the CHEM_LINK_PLANE_ATOM category. ; _category.id chem_link_plane _category.mandatory_code no loop_ _category_key.name '_chem_link_plane.link_id' '_chem_link_plane.id' loop_ _category_group.id 'inclusive_group' 'chem_link_group' save_ save__chem_link_plane.id _item_description.description ; The value of _chem_link_plane.id must uniquely identify a record in the CHEM_LINK_PLANE list. ; loop_ _item.name _item.category_id _item.mandatory_code '_chem_link_plane.id' chem_link_plane yes '_chem_link_plane_atom.plane_id' chem_link_plane_atom yes loop_ _item_linked.child_name _item_linked.parent_name '_chem_link_plane_atom.plane_id' '_chem_link_plane.id' _item_type.code code save_ save__chem_link_plane.link_id _item_description.description ; This data item is a pointer to _chem_link.id in the CHEM_LINK category. ; _item.name '_chem_link_plane.link_id' _item.mandatory_code yes save_ save__chem_link_plane.number_atoms_all _item_description.description ; The total number of atoms in the plane. ; _item.name '_chem_link_plane.number_atoms_all' _item.category_id chem_link_plane _item.mandatory_code no _item_type.code int save_ save__chem_link_plane.number_atoms_nh _item_description.description ; The number of non-hydrogen atoms in the plane. ; _item.name '_chem_link_plane.number_atoms_nh' _item.category_id chem_link_plane _item.mandatory_code no _item_type.code int save_ ########################## ## CHEM_LINK_PLANE_ATOM ## ########################## save_chem_link_plane_atom _category.description ; Data items in the CHEM_LINK_PLANE_ATOM category enumerate the atoms in a plane in a link between two chemical components. ; _category.id chem_link_plane_atom _category.mandatory_code no loop_ _category_key.name '_chem_link_plane_atom.plane_id' '_chem_link_plane_atom.atom_id' loop_ _category_group.id 'inclusive_group' 'chem_link_group' save_ save__chem_link_plane_atom.atom_comp_id _item_description.description ; This data item indicates whether the atom in a plane is found in the first or the second of the two components connected by the link. ; _item.name '_chem_link_plane_atom.atom_comp_id' _item.category_id chem_link_plane_atom _item.mandatory_code no loop_ _item_enumeration.value _item_enumeration.detail 1 'the atom is in component 1' 2 'the atom is in component 2' _item_type.code ucode save_ save__chem_link_plane_atom.atom_id _item_description.description ; The ID of an atom involved in the plane. As this data item does not point to a specific atom in a specific chemical component, it is not a child in the linkage sense. ; _item.name '_chem_link_plane_atom.atom_id' _item.mandatory_code yes _item_type.code code save_ save__chem_link_plane_atom.plane_id _item_description.description ; This data item is a pointer to _chem_link_plane.id in the CHEM_LINK_PLANE category. ; _item.name '_chem_link_plane_atom.plane_id' _item.mandatory_code yes save_ ################### ## CHEM_LINK_TOR ## ################### save_chem_link_tor _category.description ; Data items in the CHEM_LINK_TOR category record details about the torsion angles in a link between two chemical components. As torsion angles can have more than one target value, the target values are specified in the CHEM_LINK_TOR_VALUE category. ; _category.id chem_link_tor _category.mandatory_code no loop_ _category_key.name '_chem_link_tor.link_id' '_chem_link_tor.id' loop_ _category_group.id 'inclusive_group' 'chem_link_group' save_ save__chem_link_tor.atom_1_comp_id _item_description.description ; This data item indicates whether atom 1 is found in the first or the second of the two components connected by the link. ; _item.name '_chem_link_tor.atom_1_comp_id' _item.category_id chem_link_tor _item.mandatory_code no loop_ _item_dependent.dependent_name '_chem_link_tor.atom_2_comp_id' '_chem_link_tor.atom_3_comp_id' '_chem_link_tor.atom_4_comp_id' loop_ _item_enumeration.value _item_enumeration.detail 1 'the atom is in component 1' 2 'the atom is in component 2' _item_type.code ucode save_ save__chem_link_tor.atom_2_comp_id _item_description.description ; This data item indicates whether atom 2 is found in the first or the second of the two components connected by the link. ; _item.name '_chem_link_tor.atom_2_comp_id' _item.category_id chem_link_tor _item.mandatory_code no loop_ _item_dependent.dependent_name '_chem_link_tor.atom_1_comp_id' '_chem_link_tor.atom_3_comp_id' '_chem_link_tor.atom_4_comp_id' loop_ _item_enumeration.value _item_enumeration.detail 1 'the atom is in component 1' 2 'the atom is in component 2' _item_type.code ucode save_ save__chem_link_tor.atom_3_comp_id _item_description.description ; This data item indicates whether atom 3 is found in the first or the second of the two components connected by the link. ; _item.name '_chem_link_tor.atom_3_comp_id' _item.category_id chem_link_tor _item.mandatory_code no loop_ _item_dependent.dependent_name '_chem_link_tor.atom_1_comp_id' '_chem_link_tor.atom_2_comp_id' '_chem_link_tor.atom_4_comp_id' loop_ _item_enumeration.value _item_enumeration.detail 1 'the atom is in component 1' 2 'the atom is in component 2' _item_type.code ucode save_ save__chem_link_tor.atom_4_comp_id _item_description.description ; This data item indicates whether atom 4 is found in the first or the second of the two components connected by the link. ; _item.name '_chem_link_tor.atom_4_comp_id' _item.category_id chem_link_tor _item.mandatory_code no loop_ _item_dependent.dependent_name '_chem_link_tor.atom_1_comp_id' '_chem_link_tor.atom_2_comp_id' '_chem_link_tor.atom_3_comp_id' loop_ _item_enumeration.value _item_enumeration.detail 1 'the atom is in component 1' 2 'the atom is in component 2' _item_type.code ucode save_ save__chem_link_tor.atom_id_1 _item_description.description ; The ID of the first of the four atoms that define the torsion angle. As this data item does not point to a specific atom in a specific chemical component, it is not a child in the linkage sense. ; _item.name '_chem_link_tor.atom_id_1' _item.mandatory_code yes loop_ _item_dependent.dependent_name '_chem_link_tor.atom_id_2' '_chem_link_tor.atom_id_3' '_chem_link_tor.atom_id_4' _item_type.code code save_ save__chem_link_tor.atom_id_2 _item_description.description ; The ID of the second of the four atoms that define the torsion angle. As this data item does not point to a specific atom in a specific chemical component, it is not a child in the linkage sense. ; _item.name '_chem_link_tor.atom_id_2' _item.mandatory_code yes loop_ _item_dependent.dependent_name '_chem_link_tor.atom_id_1' '_chem_link_tor.atom_id_3' '_chem_link_tor.atom_id_4' _item_type.code code save_ save__chem_link_tor.atom_id_3 _item_description.description ; The ID of the third of the four atoms that define the torsion angle. As this data item does not point to a specific atom in a specific chemical component, it is not a child in the linkage sense. ; _item.name '_chem_link_tor.atom_id_3' _item.mandatory_code yes loop_ _item_dependent.dependent_name '_chem_link_tor.atom_id_1' '_chem_link_tor.atom_id_2' '_chem_link_tor.atom_id_4' _item_type.code code save_ save__chem_link_tor.atom_id_4 _item_description.description ; The ID of the fourth of the four atoms that define the torsion angle. As this data item does not point to a specific atom in a specific chemical component, it is not a child in the linkage sense. ; _item.name '_chem_link_tor.atom_id_4' _item.mandatory_code yes loop_ _item_dependent.dependent_name '_chem_link_tor.atom_id_1' '_chem_link_tor.atom_id_2' '_chem_link_tor.atom_id_3' _item_type.code code save_ save__chem_link_tor.id _item_description.description ; The value of _chem_link_tor.id must uniquely identify a record in the CHEM_LINK_TOR list. ; loop_ _item.name _item.category_id _item.mandatory_code '_chem_link_tor.id' chem_link_tor yes '_chem_link_tor_value.tor_id' chem_link_tor_value yes loop_ _item_linked.child_name _item_linked.parent_name '_chem_link_tor_value.tor_id' '_chem_link_tor.id' _item_type.code code save_ save__chem_link_tor.link_id _item_description.description ; This data item is a pointer to _chem_link.id in the CHEM_LINK category. ; _item.name '_chem_link_tor.link_id' _item.mandatory_code yes save_ ######################### ## CHEM_LINK_TOR_VALUE ## ######################### save_chem_link_tor_value _category.description ; Data items in the CHEM_LINK_TOR_VALUE category record details about the target values for the torsion angles enumerated in the CHEM_LINK_TOR list. Target values may be specified as angles in degrees, as a distance between the first and fourth atoms, or both. ; _category.id chem_link_tor_value _category.mandatory_code no _category_key.name '_chem_link_tor_value.tor_id' loop_ _category_group.id 'inclusive_group' 'chem_link_group' save_ save__chem_link_tor_value.tor_id _item_description.description ; This data item is a pointer to _chem_link_tor.id in the CHEM_LINK_TOR category. ; _item.name '_chem_link_tor_value.tor_id' _item.mandatory_code yes save_ save__chem_link_tor_value.angle _item_description.description ; A value that should be taken as a potential target value for the torsion angle associated with the specified atoms, expressed in degrees. ; _item.name '_chem_link_tor_value.angle' _item.category_id chem_link_tor_value _item.mandatory_code yes loop_ _item_range.maximum _item_range.minimum 180.0 180.0 180.0 -180.0 -180.0 -180.0 _item_related.related_name '_chem_link_tor_value.angle_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code degrees save_ save__chem_link_tor_value.angle_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _chem_link_tor_value.angle. ; _item.name '_chem_link_tor_value.angle_esd' _item.category_id chem_link_tor_value _item.mandatory_code yes loop_ _item_range.maximum _item_range.minimum 180.0 180.0 180.0 -180.0 -180.0 -180.0 _item_related.related_name '_chem_link_tor_value.angle' _item_related.function_code associated_value _item_type.code float _item_units.code degrees save_ save__chem_link_tor_value.dist _item_description.description ; A value that should be taken as a potential target value for the torsion angle associated with the specified atoms, expressed as the distance between the atoms specified by _chem_link_tor.atom_id_1 and _chem_link_tor.atom_id_4 in the referenced record in the CHEM_LINK_TOR list. Note that the torsion angle cannot be fully specified by a distance (for instance, a torsion angle of -60 degree will yield the same distance as a 60 degree angle). However, the distance specification can be useful for refinement in situations in which the angle is already close to the desired value. ; _item.name '_chem_link_tor_value.dist' _item.category_id chem_link_tor_value _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_chem_link_tor_value.dist_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code angstroms save_ save__chem_link_tor_value.dist_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _chem_link_tor_value.dist. ; _item.name '_chem_link_tor_value.dist_esd' _item.category_id chem_link_tor_value _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_chem_link_tor_value.dist' _item_related.function_code associated_value _item_type.code float _item_units.code angstroms save_ ############## ## CHEMICAL ## ############## save_chemical _category.description ; Data items in the CHEMICAL category would not in general be used in a macromolecular CIF. See instead the ENTITY data items. Data items in the CHEMICAL category record details about the composition and chemical properties of the compounds. The formula data items must agree with those that specify the density, unit-cell and Z values. ; _category.id chemical _category.mandatory_code no _category_key.name '_chemical.entry_id' loop_ _category_group.id 'inclusive_group' 'chemical_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on data set 9597gaus of Alyea, Ferguson & Kannan [Acta Cryst. (1996), C52, 765-767]. ; ; _chemical.entry_id '9597gaus' _chemical.name_systematic trans-bis(tricyclohexylphosphine)tetracarbonylmolybdenum(0) ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__chemical.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_chemical.entry_id' _item.mandatory_code yes save_ save__chemical.compound_source _item_description.description ; Description of the source of the compound under study, or of the parent molecule if a simple derivative is studied. This includes the place of discovery for minerals or the actual source of a natural product. ; _item.name '_chemical.compound_source' _item.category_id chemical _item.mandatory_code no _item_aliases.alias_name '_chemical_compound_source' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'From Norilsk (USSR)' 'Extracted from the bark of Cinchona Naturalis' save_ save__chemical.melting_point _item_description.description ; The temperature in kelvins at which the crystalline solid changes to a liquid. ; _item.name '_chemical.melting_point' _item.category_id chemical _item.mandatory_code no _item_aliases.alias_name '_chemical_melting_point' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code kelvins save_ save__chemical.name_common _item_description.description ; Trivial name by which the compound is commonly known. ; _item.name '_chemical.name_common' _item.category_id chemical _item.mandatory_code no _item_aliases.alias_name '_chemical_name_common' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case '1-bromoestradiol' save_ save__chemical.name_mineral _item_description.description ; Mineral name accepted by the International Mineralogical Association. Use only for natural minerals. See also _chemical.compound_source. ; _item.name '_chemical.name_mineral' _item.category_id chemical _item.mandatory_code no _item_aliases.alias_name '_chemical_name_mineral' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'chalcopyrite' save_ save__chemical.name_structure_type _item_description.description ; Commonly used structure-type name. Usually only applied to minerals or inorganic compounds. ; _item.name '_chemical.name_structure_type' _item.category_id chemical _item.mandatory_code no _item_aliases.alias_name '_chemical_name_structure_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'perovskite' 'sphalerite' 'A15' save_ save__chemical.name_systematic _item_description.description ; IUPAC or Chemical Abstracts full name of the compound. ; _item.name '_chemical.name_systematic' _item.category_id chemical _item.mandatory_code no _item_aliases.alias_name '_chemical_name_systematic' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case '1-bromoestra-1,3,5(10)-triene-3,17\b-diol' save_ ######################## ## CHEMICAL_CONN_ATOM ## ######################## save_chemical_conn_atom _category.description ; Data items in the CHEMICAL_CONN_ATOM category would not, in general, be used in a macromolecular CIF. See instead the ENTITY data items. Data items in the CHEMICAL_CONN_ATOM and CHEMICAL_CONN_BOND categories record details about the two-dimensional (2D) chemical structure of the molecular species. They allow a 2D chemical diagram to be reconstructed for use in a publication or in a database search for structural and substructural relationships. The CHEMICAL_CONN_ATOM data items provide information about the chemical properties of the atoms in the structure. In cases where crystallographic and molecular symmetry elements coincide, they must also contain symmetry-generated atoms, so that the CHEMICAL_CONN_ATOM and CHEMICAL_CONN_BOND data items will always describe a complete chemical entity. ; _category.id chemical_conn_atom _category.mandatory_code no _category_key.name '_chemical_conn_atom.number' loop_ _category_group.id 'inclusive_group' 'chemical_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on data set DPTD of Yamin, Suwandi, Fun, Sivakumar & bin Shawkataly [Acta Cryst. (1996), C52, 951-953]. ; ; loop_ _chemical_conn_atom.number _chemical_conn_atom.type_symbol _chemical_conn_atom.display_x _chemical_conn_atom.display_y _chemical_conn_atom.NCA _chemical_conn_atom.NH 1 S .39 .81 1 0 2 S .39 .96 2 0 3 N .14 .88 3 0 4 C .33 .88 3 0 5 C .11 .96 2 2 6 C .03 .96 2 2 7 C .03 .80 2 2 8 C .11 .80 2 2 9 S .54 .81 1 0 10 S .54 .96 2 0 11 N .80 .88 3 0 12 C .60 .88 3 0 13 C .84 .96 2 2 14 C .91 .96 2 2 15 C .91 .80 2 2 16 C .84 .80 2 2 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__chemical_conn_atom.charge _item_description.description ; The net integer charge assigned to this atom. This is the formal charge assignment normally found in chemical diagrams. ; _item.name '_chemical_conn_atom.charge' _item.category_id chemical_conn_atom _item.mandatory_code no _item_aliases.alias_name '_chemical_conn_atom_charge' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_default.value 0 loop_ _item_range.maximum _item_range.minimum 8 8 8 -8 -8 -8 _item_type.code int loop_ _item_examples.case _item_examples.detail 1 'for an ammonium nitrogen' -1 'for a chloride ion' save_ save__chemical_conn_atom.display_x _item_description.description ; The 2D Cartesian x coordinate of the position of this atom in a recognizable chemical diagram. The coordinate origin is at the lower left corner, the x axis is horizontal and the y axis is vertical. The coordinates must lie in the range 0.0 to 1.0. These coordinates can be obtained from projections of a suitable uncluttered view of the molecular structure. ; _item.name '_chemical_conn_atom.display_x' _item.category_id chemical_conn_atom _item.mandatory_code no _item_aliases.alias_name '_chemical_conn_atom_display_x' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_dependent.dependent_name '_chemical_conn_atom.display_y' loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 0.0 0.0 0.0 _item_type.code float save_ save__chemical_conn_atom.display_y _item_description.description ; The 2D Cartesian y coordinate of the position of this atom in a recognizable chemical diagram. The coordinate origin is at the lower left corner, the x axis is horizontal and the y axis is vertical. The coordinates must lie in the range 0.0 to 1.0. These coordinates can be obtained from projections of a suitable uncluttered view of the molecular structure. ; _item.name '_chemical_conn_atom.display_y' _item.category_id chemical_conn_atom _item.mandatory_code no _item_aliases.alias_name '_chemical_conn_atom_display_y' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_dependent.dependent_name '_chemical_conn_atom.display_x' loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 0.0 0.0 0.0 _item_type.code float save_ save__chemical_conn_atom.NCA _item_description.description ; The number of connected atoms excluding terminal hydrogen atoms. ; _item.name '_chemical_conn_atom.NCA' _item.category_id chemical_conn_atom _item.mandatory_code no _item_aliases.alias_name '_chemical_conn_atom_NCA' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__chemical_conn_atom.NH _item_description.description ; The total number of hydrogen atoms attached to this atom, regardless of whether they are included in the refinement or the ATOM_SITE list. This number is the same as _atom_site.attached_hydrogens only if none of the hydrogen atoms appear in the ATOM_SITE list. ; _item.name '_chemical_conn_atom.NH' _item.category_id chemical_conn_atom _item.mandatory_code no _item_aliases.alias_name '_chemical_conn_atom_NH' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__chemical_conn_atom.number _item_description.description ; The chemical sequence number to be associated with this atom. Within an ATOM_SITE list, this number must match one of the _atom_site.chemical_conn_number values. ; loop_ _item.name _item.category_id _item.mandatory_code '_chemical_conn_atom.number' chemical_conn_atom yes '_atom_site.chemical_conn_number' atom_site no '_chemical_conn_bond.atom_1' chemical_conn_bond yes '_chemical_conn_bond.atom_2' chemical_conn_bond yes _item_aliases.alias_name '_chemical_conn_atom_number' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_linked.child_name _item_linked.parent_name '_atom_site.chemical_conn_number' '_chemical_conn_atom.number' '_chemical_conn_bond.atom_1' '_chemical_conn_atom.number' '_chemical_conn_bond.atom_2' '_chemical_conn_atom.number' loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__chemical_conn_atom.type_symbol _item_description.description ; This data item is a pointer to _atom_type.symbol in the ATOM_TYPE category. ; _item.name '_chemical_conn_atom.type_symbol' _item.mandatory_code yes _item_aliases.alias_name '_chemical_conn_atom_type_symbol' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 save_ ######################## ## CHEMICAL_CONN_BOND ## ######################## save_chemical_conn_bond _category.description ; Data items in the CHEMICAL_CONN_BOND category would not, in general, be used in a macromolecular CIF. See instead the ENTITY data items. Data items in the CHEMICAL_CONN_ATOM and CHEMICAL_CONN_BOND categories record details about the two-dimensional (2D) chemical structure of the molecular species. They allow a 2D chemical diagram to be reconstructed for use in a publication or in a database search for structural and substructural relationships. The CHEMICAL_CONN_BOND data items specify the connections between the atoms in the CHEMICAL_CONN_ATOM list and the nature of the chemical bond between these atoms. ; _category.id chemical_conn_bond _category.mandatory_code no loop_ _category_key.name '_chemical_conn_bond.atom_1' '_chemical_conn_bond.atom_2' loop_ _category_group.id 'inclusive_group' 'chemical_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on data set DPTD of Yamin, Suwandi, Fun, Sivakumar & bin Shawkataly [Acta Cryst. (1996), C52, 951-953]. ; ; loop_ _chemical_conn_bond.atom_1 _chemical_conn_bond.atom_2 _chemical_conn_bond.type 4 1 doub 4 3 sing 4 2 sing 5 3 sing 6 5 sing 7 6 sing 8 7 sing 8 3 sing 10 2 sing 12 9 doub 12 11 sing 12 10 sing 13 11 sing 14 13 sing 15 14 sing 16 15 sing 16 11 sing 17 5 sing 18 5 sing 19 6 sing 20 6 sing 21 7 sing 22 7 sing 23 8 sing 24 8 sing 25 13 sing 26 13 sing 27 14 sing 28 14 sing 29 15 sing 30 15 sing 31 16 sing 32 16 sing ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__chemical_conn_bond.atom_1 _item_description.description ; This data item is a pointer to _chemical_conn_atom.number in the CHEMICAL_CONN_ATOM category. ; _item.name '_chemical_conn_bond.atom_1' _item.mandatory_code yes _item_aliases.alias_name '_chemical_conn_bond_atom_1' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_dependent.dependent_name '_chemical_conn_bond.atom_2' save_ save__chemical_conn_bond.atom_2 _item_description.description ; This data item is a pointer to _chemical_conn_atom.number in the CHEMICAL_CONN_ATOM category. ; _item.name '_chemical_conn_bond.atom_2' _item.mandatory_code yes _item_aliases.alias_name '_chemical_conn_bond_atom_2' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_dependent.dependent_name '_chemical_conn_bond.atom_1' save_ save__chemical_conn_bond.type _item_description.description ; The chemical bond type associated with the connection between the two sites _chemical_conn_bond.atom_1 and _chemical_conn_bond.atom_2. ; _item.name '_chemical_conn_bond.type' _item.category_id chemical_conn_bond _item.mandatory_code no _item_aliases.alias_name '_chemical_conn_bond_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_default.value sing _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail sing 'single bond' doub 'double bond' trip 'triple bond' quad 'quadruple bond' arom 'aromatic bond' poly 'polymeric bond' delo 'delocalized double bond' pi 'pi bond' save_ ###################### ## CHEMICAL_FORMULA ## ###################### save_chemical_formula _category.description ; Data items in the CHEMICAL_FORMULA category would not, in general, be used in a macromolecular CIF. See instead the ENTITY data items. Data items in the CHEMICAL_FORMULA category specify the composition and chemical properties of the compound. The formula data items must agree with those that specify the density, unit-cell and Z values. The following rules apply to the construction of the data items _chemical_formula.analytical, _chemical_formula.structural and _chemical_formula.sum. For the data item _chemical_formula.moiety, the formula construction is broken up into residues or moieties, i.e. groups of atoms that form a molecular unit or molecular ion. The rules given below apply within each moiety but different requirements apply to the way that moieties are connected (see _chemical_formula.moiety). (1) Only recognized element symbols may be used. (2) Each element symbol is followed by a 'count' number. A count of '1' may be omitted. (3) A space or parenthesis must separate each cluster of (element symbol + count). (4) Where a group of elements is enclosed in parentheses, the multiplier for the group must follow the closing parenthesis. That is, all element and group multipliers are assumed to be printed as subscripted numbers. (An exception to this rule exists for _chemical_formula.moiety formulae where pre- and post-multipliers are permitted for molecular units.) (5) Unless the elements are ordered in a manner that corresponds to their chemical structure, as in _chemical_formula.structural, the order of the elements within any group or moiety should be: C, then H, then the other elements in alphabetical order of their symbol. This is the 'Hill' system used by Chemical Abstracts. This ordering is used in _chemical_formula.moiety and _chemical_formula.sum. ; _category.id chemical_formula _category.mandatory_code no _category_key.name '_chemical_formula.entry_id' loop_ _category_group.id 'inclusive_group' 'chemical_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991). Acta Cryst. C47, 2276-2277]. ; ; _chemical_formula.entry_id 'TOZ' _chemical_formula.moiety 'C18 H25 N O3' _chemical_formula.sum 'C18 H25 N O3' _chemical_formula.weight 303.40 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__chemical_formula.analytical _item_description.description ; Formula determined by standard chemical analysis including trace elements. See the CHEMICAL_FORMULA category description for rules for writing chemical formulae. Parentheses are used only for standard uncertainties (estimated standard deviations). ; _item.name '_chemical_formula.analytical' _item.category_id chemical_formula _item.mandatory_code no _item_aliases.alias_name '_chemical_formula_analytical' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'Fe2.45(2) Ni1.60(3) S4' save_ save__chemical_formula.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_chemical_formula.entry_id' _item.mandatory_code yes save_ save__chemical_formula.iupac _item_description.description ; Formula expressed in conformance with IUPAC rules for inorganic and metal-organic compounds where these conflict with the rules for any other CHEMICAL_FORMULA entries. Typically used for formatting a formula in accordance with journal rules. This should appear in the data block in addition to the most appropriate of the other CHEMICAL_FORMULA data names. Ref: IUPAC (1990). Nomenclature of Inorganic Chemistry. Oxford: Blackwell Scientific Publications. ; _item.name '_chemical_formula.iupac' _item.category_id chemical_formula _item.mandatory_code no _item_aliases.alias_name '_chemical_formula_iupac' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case '[Co Re (C12 H22 P)2 (C O)6].0.5C H3 O H' save_ save__chemical_formula.moiety _item_description.description ; Formula with each discrete bonded residue or ion shown as a separate moiety. See the CHEMICAL_FORMULA category description for rules for writing chemical formulae. In addition to the general formulae requirements, the following rules apply: (1) Moieties are separated by commas ','. (2) The order of elements within a moiety follows general rule (5) in the CHEMICAL_FORMULA category description. (3) Parentheses are not used within moieties but may surround a moiety. Parentheses may not be nested. (4) Charges should be placed at the end of the moiety. The charge '+' or '-' may be preceded by a numerical multiplier and should be separated from the last (element symbol + count) by a space. Pre- or post-multipliers may be used for individual moieties. ; _item.name '_chemical_formula.moiety' _item.category_id chemical_formula _item.mandatory_code no _item_aliases.alias_name '_chemical_formula_moiety' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'C7 H4 Cl Hg N O3 S' 'C12 H17 N4 O S 1+, C6 H2 N3 O7 1-' 'C12 H16 N2 O6, 5(H2 O1)' "(Cd 2+)3, (C6 N6 Cr 3-)2, 2(H2 O)" save_ save__chemical_formula.structural _item_description.description ; See the CHEMICAL_FORMULA category description for the rules for writing chemical formulae for inorganics, organometallics, metal complexes etc., in which bonded groups are preserved as discrete entities within parentheses, with post-multipliers as required. The order of the elements should give as much information as possible about the chemical structure. Parentheses may be used and nested as required. This formula should correspond to the structure as actually reported, i.e. trace elements not included in atom-type and atom-site data should not be included in this formula (see also _chemical_formula.analytical). ; _item.name '_chemical_formula.structural' _item.category_id chemical_formula _item.mandatory_code no _item_aliases.alias_name '_chemical_formula_structural' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Ca ((Cl O3)2 O)2 (H2 O)6' '(Pt (N H3)2 (C5 H7 N3 O)2) (Cl O4)2' save_ save__chemical_formula.sum _item_description.description ; See the CHEMICAL_FORMULA category description for the rules for writing chemical formulae in which all discrete bonded residues and ions are summed over the constituent elements, following the ordering given in general rule (5) in the CHEMICAL_FORMULA category description. Parentheses are not normally used. ; _item.name '_chemical_formula.sum' _item.category_id chemical_formula _item.mandatory_code no _item_aliases.alias_name '_chemical_formula_sum' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'C18 H19 N7 O8 S' save_ save__chemical_formula.weight _item_description.description ; Formula mass in daltons. This mass should correspond to the formulae given under _chemical_formula.structural, _chemical_formula.moiety or _chemical_formula.sum and, together with the Z value and cell parameters, should yield the density given as _exptl_crystal.density_diffrn. ; _item.name '_chemical_formula.weight' _item.category_id chemical_formula _item.mandatory_code no _item_aliases.alias_name '_chemical_formula_weight' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 1.0 1.0 1.0 _item_type.code float save_ save__chemical_formula.weight_meas _item_description.description ; Formula mass in daltons measured by a non-diffraction experiment. ; _item.name '_chemical_formula.weight_meas' _item.category_id chemical_formula _item.mandatory_code no _item_aliases.alias_name '_chemical_formula_weight_meas' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 1.0 1.0 1.0 _item_type.code float save_ ############## ## CITATION ## ############## save_citation _category.description ; Data items in the CITATION category record details about the literature cited as being relevant to the contents of the data block. ; _category.id citation _category.mandatory_code no _category_key.name '_citation.id' loop_ _category_group.id 'inclusive_group' 'citation_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _citation.id _citation.coordinate_linkage _citation.title _citation.country _citation.journal_abbrev _citation.journal_volume _citation.journal_issue _citation.page_first _citation.page_last _citation.year _citation.journal_id_ASTM _citation.journal_id_ISSN _citation.journal_id_CSD _citation.book_title _citation.book_publisher _citation.book_id_ISBN _citation.details primary yes ; Crystallographic analysis of a complex between human immunodeficiency virus type 1 protease and acetyl-pepstatin at 2.0-Angstroms resolution. ; US 'J. Biol. Chem.' 265 . 14209 14219 1990 HBCHA3 0021-9258 071 . . . ; The publication that directly relates to this coordinate set. ; 2 no ; Three-dimensional structure of aspartyl-protease from human immunodeficiency virus HIV-1. ; UK 'Nature' 337 . 615 619 1989 NATUAS 0028-0836 006 . . . ; Determination of the structure of the unliganded enzyme. ; 3 no ; Crystallization of the aspartylprotease from human immunodeficiency virus, HIV-1. ; US 'J. Biol. Chem.' 264 . 1919 1921 1989 HBCHA3 0021-9258 071 . . . ; Crystallization of the unliganded enzyme. ; 4 no ; Human immunodeficiency virus protease. Bacterial expression and characterization of the purified aspartic protease. ; US 'J. Biol. Chem.' 264 . 2307 2312 1989 HBCHA3 0021-9258 071 . . . ; Expression and purification of the enzyme. ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__citation.abstract _item_description.description ; Abstract for the citation. This is used most when the citation is extracted from a bibliographic database that contains full text or abstract information. ; _item.name '_citation.abstract' _item.category_id citation _item.mandatory_code no _item_aliases.alias_name '_citation_abstract' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__citation.abstract_id_CAS _item_description.description ; The Chemical Abstracts Service (CAS) abstract identifier; relevant for journal articles. ; _item.name '_citation.abstract_id_CAS' _item.category_id citation _item.mandatory_code no _item_aliases.alias_name '_citation_abstract_id_CAS' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__citation.book_id_ISBN _item_description.description ; The International Standard Book Number (ISBN) code assigned to the book cited; relevant for books or book chapters. ; _item.name '_citation.book_id_ISBN' _item.category_id citation _item.mandatory_code no _item_aliases.alias_name '_citation_book_id_ISBN' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__citation.book_publisher _item_description.description ; The name of the publisher of the citation; relevant for books or book chapters. ; _item.name '_citation.book_publisher' _item.category_id citation _item.mandatory_code no _item_aliases.alias_name '_citation_book_publisher' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'John Wiley and Sons' save_ save__citation.book_publisher_city _item_description.description ; The location of the publisher of the citation; relevant for books or book chapters. ; _item.name '_citation.book_publisher_city' _item.category_id citation _item.mandatory_code no _item_aliases.alias_name '_citation_book_publisher_city' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'London' save_ save__citation.book_title _item_description.description ; The title of the book in which the citation appeared; relevant for books or book chapters. ; _item.name '_citation.book_title' _item.category_id citation _item.mandatory_code no _item_aliases.alias_name '_citation_book_title' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__citation.coordinate_linkage _item_description.description ; _citation.coordinate_linkage states whether this citation is concerned with precisely the set of coordinates given in the data block. If, for instance, the publication described the same structure, but the coordinates had undergone further refinement prior to the creation of the data block, the value of this data item would be 'no'. ; _item.name '_citation.coordinate_linkage' _item.category_id citation _item.mandatory_code no _item_aliases.alias_name '_citation_coordinate_linkage' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail no 'citation unrelated to current coordinates' n 'abbreviation for "no"' yes 'citation related to current coordinates' y 'abbreviation for "yes"' save_ save__citation.country _item_description.description ; The country of publication; relevant for books and book chapters. ; _item.name '_citation.country' _item.category_id citation _item.mandatory_code no _item_aliases.alias_name '_citation_country' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__citation.database_id_Medline _item_description.description ; Accession number used by Medline to categorize a specific bibliographic entry. ; _item.name '_citation.database_id_Medline' _item.category_id citation _item.mandatory_code no _item_aliases.alias_name '_citation_database_id_Medline' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int _item_examples.case 89064067 save_ save__citation.details _item_description.description ; A description of special aspects of the relationship of the contents of the data block to the literature item cited. ; _item.name '_citation.details' _item.category_id citation _item.mandatory_code no _item_aliases.alias_name '_citation_special_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case ; citation relates to this precise coordinate set ; ; citation relates to earlier low-resolution structure ; ; citation relates to further refinement of structure reported in citation 2 ; save_ save__citation.id _item_description.description ; The value of _citation.id must uniquely identify a record in the CITATION list. The _citation.id 'primary' should be used to indicate the citation that the author(s) consider to be the most pertinent to the contents of the data block. Note that this item need not be a number; it can be any unique identifier. ; loop_ _item.name _item.category_id _item.mandatory_code '_citation.id' citation yes '_citation_author.citation_id' citation_author yes '_citation_editor.citation_id' citation_editor yes '_software.citation_id' software no _item_aliases.alias_name '_citation_id' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_linked.child_name _item_linked.parent_name '_citation_author.citation_id' '_citation.id' '_citation_editor.citation_id' '_citation.id' '_software.citation_id' '_citation.id' _item_type.code code loop_ _item_examples.case 'primary' '1' '2' save_ save__citation.journal_abbrev _item_description.description ; Abbreviated name of the cited journal as given in the Chemical Abstracts Service Source Index. ; _item.name '_citation.journal_abbrev' _item.category_id citation _item.mandatory_code no _item_aliases.alias_name '_citation_journal_abbrev' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line _item_examples.case 'J. Mol. Biol.' save_ save__citation.journal_id_ASTM _item_description.description ; The American Society for Testing and Materials (ASTM) code assigned to the journal cited (also referred to as the CODEN designator of the Chemical Abstracts Service); relevant for journal articles. ; _item.name '_citation.journal_id_ASTM' _item.category_id citation _item.mandatory_code no _item_aliases.alias_name '_citation_journal_id_ASTM' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__citation.journal_id_CSD _item_description.description ; The Cambridge Structural Database (CSD) code assigned to the journal cited; relevant for journal articles. This is also the system used at the Protein Data Bank (PDB). ; _item.name '_citation.journal_id_CSD' _item.category_id citation _item.mandatory_code no _item_aliases.alias_name '_citation_journal_id_CSD' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line _item_examples.case '0070' save_ save__citation.journal_id_ISSN _item_description.description ; The International Standard Serial Number (ISSN) code assigned to the journal cited; relevant for journal articles. ; _item.name '_citation.journal_id_ISSN' _item.category_id citation _item.mandatory_code no _item_aliases.alias_name '_citation_journal_id_ISSN' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__citation.journal_full _item_description.description ; Full name of the cited journal; relevant for journal articles. ; _item.name '_citation.journal_full' _item.category_id citation _item.mandatory_code no _item_aliases.alias_name '_citation_journal_full' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'Journal of Molecular Biology' save_ save__citation.journal_issue _item_description.description ; Issue number of the journal cited; relevant for journal articles. ; _item.name '_citation.journal_issue' _item.category_id citation _item.mandatory_code no _item_aliases.alias_name '_citation_journal_issue' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line _item_examples.case '2' save_ save__citation.journal_volume _item_description.description ; Volume number of the journal cited; relevant for journal articles. ; _item.name '_citation.journal_volume' _item.category_id citation _item.mandatory_code no _item_aliases.alias_name '_citation_journal_volume' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line _item_examples.case '174' save_ save__citation.language _item_description.description ; Language in which the cited article is written. ; _item.name '_citation.language' _item.category_id citation _item.mandatory_code no _item_aliases.alias_name '_citation_language' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line _item_examples.case 'German' save_ save__citation.page_first _item_description.description ; The first page of the citation; relevant for journal articles, books and book chapters. ; _item.name '_citation.page_first' _item.category_id citation _item.mandatory_code no _item_aliases.alias_name '_citation_page_first' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__citation.page_last _item_description.description ; The last page of the citation; relevant for journal articles, books and book chapters. ; _item.name '_citation.page_last' _item.category_id citation _item.mandatory_code no _item_aliases.alias_name '_citation_page_last' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__citation.title _item_description.description ; The title of the citation; relevant for journal articles, books and book chapters. ; _item.name '_citation.title' _item.category_id citation _item.mandatory_code no _item_aliases.alias_name '_citation_title' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; Structure of diferric duck ovotransferrin at 2.35 \%A resolution. ; save_ save__citation.year _item_description.description ; The year of the citation; relevant for journal articles, books and book chapters. ; _item.name '_citation.year' _item.category_id citation _item.mandatory_code no _item_aliases.alias_name '_citation_year' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code int _item_examples.case 1984 save_ ##################### ## CITATION_AUTHOR ## ##################### save_citation_author _category.description ; Data items in the CITATION_AUTHOR category record details about the authors associated with the citations in the CITATION list. ; _category.id citation_author _category.mandatory_code no loop_ _category_key.name '_citation_author.citation_id' '_citation_author.name' loop_ _category_group.id 'inclusive_group' 'citation_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _citation_author.citation_id _citation_author.ordinal _citation_author.name primary 1 'Fitzgerald, P.M.D.' primary 2 'McKeever, B.M.' primary 3 'Van Middlesworth, J.F.' primary 4 'Springer, J.P.' primary 5 'Heimbach, J.C.' primary 6 'Leu, C.-T.' primary 7 'Herber, W.K.' primary 8 'Dixon, R.A.F.' primary 9 'Darke, P.L.' 2 1 'Navia, M.A.' 2 2 'Fitzgerald, P.M.D.' 2 3 'McKeever, B.M.' 2 4 'Leu, C.-T.' 2 5 'Heimbach, J.C.' 2 6 'Herber, W.K.' 2 7 'Sigal, I.S.' 2 8 'Darke, P.L.' 2 9 'Springer, J.P.' 3 1 'McKeever, B.M.' 3 2 'Navia, M.A.' 3 3 'Fitzgerald, P.M.D.' 3 4 'Springer, J.P.' 3 5 'Leu, C.-T.' 3 6 'Heimbach, J.C.' 3 7 'Herber, W.K.' 3 8 'Sigal, I.S.' 3 9 'Darke, P.L.' 4 1 'Darke, P.L.' 4 2 'Leu, C.-T.' 4 3 'Davis, L.J.' 4 4 'Heimbach, J.C.' 4 5 'Diehl, R.E.' 4 6 'Hill, W.S.' 4 7 'Dixon, R.A.F.' 4 8 'Sigal, I.S.' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__citation_author.citation_id _item_description.description ; This data item is a pointer to _citation.id in the CITATION category. ; _item.name '_citation_author.citation_id' _item.mandatory_code yes _item_aliases.alias_name '_citation_author_citation_id' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 save_ save__citation_author.name _item_description.description ; Name of an author of the citation; relevant for journal articles, books and book chapters. The family name(s), followed by a comma and including any dynastic components, precedes the first name(s) or initial(s). ; _item.name '_citation_author.name' _item.category_id citation_author _item.mandatory_code yes _item_aliases.alias_name '_citation_author_name' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'Bleary, Percival R.' "O'Neil, F.K." 'Van den Bossche, G.' 'Yang, D.-L.' 'Simonov, Yu.A' save_ save__citation_author.ordinal _item_description.description ; This data item defines the order of the author's name in the list of authors of a citation. ; _item.name '_citation_author.ordinal' _item.category_id citation_author _item.mandatory_code no _item_aliases.alias_name '_citation_author_ordinal' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code int save_ ##################### ## CITATION_EDITOR ## ##################### save_citation_editor _category.description ; Data items in the CITATION_EDITOR category record details about the editors associated with the books or book chapters cited in the CITATION list. ; _category.id citation_editor _category.mandatory_code no loop_ _category_key.name '_citation_editor.citation_id' '_citation_editor.name' loop_ _category_group.id 'inclusive_group' 'citation_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - hypothetical example. ; ; loop_ _citation_editor.citation_id _citation_editor.name 5 'McKeever, B.M.' 5 'Navia, M.A.' 5 'Fitzgerald, P.M.D.' 5 'Springer, J.P.' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__citation_editor.citation_id _item_description.description ; This data item is a pointer to _citation.id in the CITATION category. ; _item.name '_citation_editor.citation_id' _item.mandatory_code yes _item_aliases.alias_name '_citation_editor_citation_id' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 save_ save__citation_editor.name _item_description.description ; Names of an editor of the citation; relevant for books and book chapters. The family name(s), followed by a comma and including any dynastic components, precedes the first name(s) or initial(s). ; _item.name '_citation_editor.name' _item.category_id citation_editor _item.mandatory_code no _item_aliases.alias_name '_citation_editor_name' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'Bleary, Percival R.' "O'Neil, F.K." 'Van den Bossche, G.' 'Yang, D.-L.' 'Simonov, Yu.A' save_ save__citation_editor.ordinal _item_description.description ; This data item defines the order of the editor's name in the list of editors of a citation. ; _item.name '_citation_editor.ordinal' _item.category_id citation_editor _item.mandatory_code no _item_aliases.alias_name '_citation_editor_ordinal' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code int save_ ############### ## COMPUTING ## ############### save_computing _category.description ; Data items in the COMPUTING category record details about the computer programs used in the crystal structure analysis. Data items in this category would not, in general, be used in a macromolecular CIF. The category SOFTWARE, which allows a more detailed description of computer programs and their attributes to be given, would be used instead. ; _category.id computing _category.mandatory_code no _category_key.name '_computing.entry_id' loop_ _category_group.id 'inclusive_group' 'computing_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Rodr\'iguez-Romera, Ruiz-P\'erez & Solans [Acta Cryst. (1996), C52, 1415-1417]. ; ; _computing.data_collection 'CAD-4 (Enraf-Nonius, 1989)' _computing.cell_refinement 'CAD-4 (Enraf-Nonius, 1989)' _computing.data_reduction 'CFEO (Solans, 1978)' _computing.structure_solution 'SHELXS86 (Sheldrick, 1990)' _computing.structure_refinement 'SHELXL93 (Sheldrick, 1993)' _computing.molecular_graphics 'ORTEPII (Johnson, 1976)' _computing.publication_material 'PARST (Nardelli, 1983)' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__computing.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_computing.entry_id' _item.mandatory_code yes save_ save__computing.cell_refinement _item_description.description ; Software used for cell refinement. Give the program or package name and a brief reference. ; _item.name '_computing.cell_refinement' _item.category_id computing _item.mandatory_code no _item_aliases.alias_name '_computing_cell_refinement' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'CAD4 (Enraf-Nonius, 1989)' save_ save__computing.data_collection _item_description.description ; Software used for data collection. Give the program or package name and a brief reference. ; _item.name '_computing.data_collection' _item.category_id computing _item.mandatory_code no _item_aliases.alias_name '_computing_data_collection' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'CAD4 (Enraf-Nonius, 1989)' save_ save__computing.data_reduction _item_description.description ; Software used for data reduction. Give the program or package name and a brief reference. ; _item.name '_computing.data_reduction' _item.category_id computing _item.mandatory_code no _item_aliases.alias_name '_computing_data_reduction' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'DIFDAT, SORTRF, ADDREF (Hall & Stewart, 1990)' save_ save__computing.molecular_graphics _item_description.description ; Software used for molecular graphics. Give the program or package name and a brief reference. ; _item.name '_computing.molecular_graphics' _item.category_id computing _item.mandatory_code no _item_aliases.alias_name '_computing_molecular_graphics' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'FRODO (Jones, 1986), ORTEP (Johnson, 1965)' save_ save__computing.publication_material _item_description.description ; Software used for generating material for publication. Give the program or package name and a brief reference. ; _item.name '_computing.publication_material' _item.category_id computing _item.mandatory_code no _item_aliases.alias_name '_computing_publication_material' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__computing.structure_refinement _item_description.description ; Software used for refinement of the structure. Give the program or package name and a brief reference. ; _item.name '_computing.structure_refinement' _item.category_id computing _item.mandatory_code no _item_aliases.alias_name '_computing_structure_refinement' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'SHELX85 (Sheldrick, 1985)' 'X-PLOR (Brunger, 1992)' save_ save__computing.structure_solution _item_description.description ; Software used for solution of the structure. Give the program or package name and a brief reference. ; _item.name '_computing.structure_solution' _item.category_id computing _item.mandatory_code no _item_aliases.alias_name '_computing_structure_solution' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'SHELX85 (Sheldrick, 1985)' save_ ############## ## DATABASE ## ############## save_database _category.description ; Data items in the DATABASE category have been superseded by data items in the DATABASE_2 category. They are included here only for compliance with older CIFs. ; _category.id database _category.mandatory_code no _category_key.name '_database.entry_id' loop_ _category_group.id 'inclusive_group' 'compliance_group' save_ save__database.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_database.entry_id' _item.mandatory_code yes save_ #save__database.code_CAS # _item_description.description #; The code assigned by Chemical Abstracts. #; # _item.name '_database.code_CAS' # _item.category_id database # _item.mandatory_code no # _item_aliases.alias_name '_database_code_CAS' # _item_aliases.dictionary cif_core.dic # _item_aliases.version 2.0.1 # loop_ # _item_related.related_name # _item_related.function_code '_database_2.database_id' # replacedby # '_database_2.database_code' # replacedby # _item_type.code line # save_ # #save__database.code_CSD # _item_description.description #; The code assigned by the Cambridge Structural Database # (organic and metal-organic compounds). #; # _item.name '_database.code_CSD' # _item.category_id database # _item.mandatory_code no # _item_aliases.alias_name '_database_code_CSD' # _item_aliases.dictionary cif_core.dic # _item_aliases.version 2.0.1 # loop_ # _item_related.related_name # _item_related.function_code '_database_2.database_id' # replacedby # '_database_2.database_code' # replacedby # _item_type.code line # save_ # #save__database.code_ICSD # _item_description.description #; The code assigned by the Inorganic Crystal Structure Database. #; # _item.name '_database.code_ICSD' # _item.category_id database # _item.mandatory_code no # _item_aliases.alias_name '_database_code_ICSD' # _item_aliases.dictionary cif_core.dic # _item_aliases.version 2.0.1 # loop_ # _item_related.related_name # _item_related.function_code '_database_2.database_id' # replacedby # '_database_2.database_code' # replacedby # _item_type.code line # save_ # #save__database.code_MDF # _item_description.description #; The code assigned by the Metals Data File (metal structures). #; # _item.name '_database.code_MDF' # _item.category_id database # _item.mandatory_code no # _item_aliases.alias_name '_database_code_MDF' # _item_aliases.dictionary cif_core.dic # _item_aliases.version 2.0.1 # loop_ # _item_related.related_name # _item_related.function_code '_database_2.database_id' # replacedby # '_database_2.database_code' # replacedby # _item_type.code line # save_ # #save__database.code_NBS # _item_description.description #; The code assigned by the NBS (NIST) Crystal Data Database # (lattice parameters). #; # _item.name '_database.code_NBS' # _item.category_id database # _item.mandatory_code no # _item_aliases.alias_name '_database_code_NBS' # _item_aliases.dictionary cif_core.dic # _item_aliases.version 2.0.1 # loop_ # _item_related.related_name # _item_related.function_code '_database_2.database_id' # replacedby # '_database_2.database_code' # replacedby # _item_type.code line # save_ # #save__database.code_PDF # _item_description.description #; The code assigned by the Powder Diffraction File (JCPDS/ICDD). #; # _item.name '_database.code_PDF' # _item.category_id database # _item.mandatory_code no # _item_aliases.alias_name '_database_code_PDF' # _item_aliases.dictionary cif_core.dic # _item_aliases.version 2.0.1 # loop_ # _item_related.related_name # _item_related.function_code '_database_2.database_id' # replacedby # '_database_2.database_code' # replacedby # _item_type.code line # save_ # save__database.journal_ASTM _item_description.description ; The ASTM CODEN designator for a journal as given in the Chemical Source List maintained by the Chemical Abstracts Service. ; _item.name '_database.journal_ASTM' _item.category_id database _item.mandatory_code no _item_aliases.alias_name '_database_journal_ASTM' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__database.journal_CSD _item_description.description ; The journal code used in the Cambridge Structural Database. ; _item.name '_database.journal_CSD' _item.category_id database _item.mandatory_code no _item_aliases.alias_name '_database_journal_CSD' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ ################ ## DATABASE_2 ## ################ save_database_2 _category.description ; Data items in the DATABASE_2 category record details about the database identifiers of the data block. These data items are assigned by database managers and should only appear in a data block if they originate from that source. The name of this category, DATABASE_2, arose because the category name DATABASE was already in use in the core CIF dictionary, but was used differently from the way it needed to be used in the mmCIF dictionary. Since CIF data names cannot be changed once they have been adopted, a new category had to be created. ; _category.id database_2 _category.mandatory_code no loop_ _category_key.name '_database_2.database_id' '_database_2.database_code' loop_ _category_group.id 'inclusive_group' 'database_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _database_2.database_id 'PDB' _database_2.database_code '5HVP' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__database_2.database_id _item_description.description ; An abbreviation that identifies the database. ; _item.name '_database_2.database_id' _item.category_id database_2 _item.mandatory_code yes loop_ _item_related.related_name _item_related.function_code '_database.code_CAS' replaces '_database.code_CSD' replaces '_database.code_ICSD' replaces '_database.code_MDF' replaces '_database.code_NBS' replaces '_database.code_PDF' replaces _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail CAS ; Chemical Abstracts ; CSD ; Cambridge Structural Database (organic and metal-organic compounds) ; ICSD ; Inorganic Crystal Structure Database ; MDF ; Metals Data File (metal structures) ; NDB ; Nucleic Acid Database ; NBS ; NBS (NIST) Crystal Data Database (lattice parameters) ; PDB ; Protein Data Bank ; PDF ; Powder Diffraction File (JCPDS/ICDD) ; RCSB ; Research Collaboratory for Structural Bioinformatics ; EBI ; European Bioinformatics Institute ; save_ save__database_2.database_code _item_description.description ; The code assigned by the database identified in _database_2.database_id. ; _item.name '_database_2.database_code' _item.category_id database_2 _item.mandatory_code yes loop_ _item_related.related_name _item_related.function_code '_database.code_CAS' replaces '_database.code_CSD' replaces '_database.code_ICSD' replaces '_database.code_MDF' replaces '_database.code_NBS' replaces '_database.code_PDF' replaces _item_type.code line loop_ _item_examples.case 1ABC ABCDEF save_ ######################### ## DATABASE_PDB_CAVEAT ## ######################### save_database_PDB_caveat _category.description ; Data items in the DATABASE_PDB_CAVEAT category record details about features of the data block flagged as 'caveats' by the Protein Data Bank (PDB). These data items are included only for consistency with PDB format files. They should appear in a data block only if that data block was created by reformatting a PDB format file. ; _category.id database_PDB_caveat _category.mandatory_code no _category_key.name '_database_PDB_caveat.id' loop_ _category_group.id 'inclusive_group' 'database_group' 'pdb_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - hypothetical example. ; ; loop_ _database_PDB_caveat.id _database_PDB_caveat.text 1 ; THE CRYSTAL TRANSFORMATION IS IN ERROR BUT IS ; 2 ; UNCORRECTABLE AT THIS TIME ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__database_PDB_caveat.id _item_description.description ; A unique identifier for the PDB caveat record. ; _item.name '_database_PDB_caveat.id' _item.category_id database_PDB_caveat _item.mandatory_code yes _item_type.code int save_ save__database_PDB_caveat.text _item_description.description ; The full text of the PDB caveat record. ; _item.name '_database_PDB_caveat.text' _item.category_id database_PDB_caveat _item.mandatory_code no _item_type.code text save_ ######################### ## DATABASE_PDB_MATRIX ## ######################### save_database_PDB_matrix _category.description ; The DATABASE_PDB_MATRIX category provides placeholders for transformation matrices and vectors used by the Protein Data Bank (PDB). These data items are included only for consistency with older PDB format files. They should appear in a data block only if that data block was created by reformatting a PDB format file. ; _category.id database_PDB_matrix _category.mandatory_code no _category_key.name '_database_PDB_matrix.entry_id' loop_ _category_group.id 'inclusive_group' 'database_group' 'pdb_group' save_ save__database_PDB_matrix.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_database_PDB_matrix.entry_id' _item.mandatory_code yes save_ save__database_PDB_matrix.origx[1][1] _item_description.description ; The [1][1] element of the PDB ORIGX matrix. ; _item.name '_database_PDB_matrix.origx[1][1]' _item.category_id database_PDB_matrix _item.mandatory_code no _item_default.value 1.0 _item_sub_category.id matrix _item_type.code float save_ save__database_PDB_matrix.origx[1][2] _item_description.description ; The [1][2] element of the PDB ORIGX matrix. ; _item.name '_database_PDB_matrix.origx[1][2]' _item.category_id database_PDB_matrix _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id matrix _item_type.code float save_ save__database_PDB_matrix.origx[1][3] _item_description.description ; The [1][3] element of the PDB ORIGX matrix. ; _item.name '_database_PDB_matrix.origx[1][3]' _item.category_id database_PDB_matrix _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id matrix _item_type.code float save_ save__database_PDB_matrix.origx[2][1] _item_description.description ; The [2][1] element of the PDB ORIGX matrix. ; _item.name '_database_PDB_matrix.origx[2][1]' _item.category_id database_PDB_matrix _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id matrix _item_type.code float save_ save__database_PDB_matrix.origx[2][2] _item_description.description ; The [2][2] element of the PDB ORIGX matrix. ; _item.name '_database_PDB_matrix.origx[2][2]' _item.category_id database_PDB_matrix _item.mandatory_code no _item_default.value 1.0 _item_sub_category.id matrix _item_type.code float save_ save__database_PDB_matrix.origx[2][3] _item_description.description ; The [2][3] element of the PDB ORIGX matrix. ; _item.name '_database_PDB_matrix.origx[2][3]' _item.category_id database_PDB_matrix _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id matrix _item_type.code float save_ save__database_PDB_matrix.origx[3][1] _item_description.description ; The [3][1] element of the PDB ORIGX matrix. ; _item.name '_database_PDB_matrix.origx[3][1]' _item.category_id database_PDB_matrix _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id matrix _item_type.code float save_ save__database_PDB_matrix.origx[3][2] _item_description.description ; The [3][2] element of the PDB ORIGX matrix. ; _item.name '_database_PDB_matrix.origx[3][2]' _item.category_id database_PDB_matrix _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id matrix _item_type.code float save_ save__database_PDB_matrix.origx[3][3] _item_description.description ; The [3][3] element of the PDB ORIGX matrix. ; _item.name '_database_PDB_matrix.origx[3][3]' _item.category_id database_PDB_matrix _item.mandatory_code no _item_default.value 1.0 _item_sub_category.id matrix _item_type.code float save_ save__database_PDB_matrix.origx_vector[1] _item_description.description ; The [1] element of the PDB ORIGX vector. ; _item.name '_database_PDB_matrix.origx_vector[1]' _item.category_id database_PDB_matrix _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__database_PDB_matrix.origx_vector[2] _item_description.description ; The [2] element of the PDB ORIGX vector. ; _item.name '_database_PDB_matrix.origx_vector[2]' _item.category_id database_PDB_matrix _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__database_PDB_matrix.origx_vector[3] _item_description.description ; The [3] element of the PDB ORIGX vector. ; _item.name '_database_PDB_matrix.origx_vector[3]' _item.category_id database_PDB_matrix _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__database_PDB_matrix.scale[1][1] _item_description.description ; The [1][1] element of the PDB SCALE matrix. ; _item.name '_database_PDB_matrix.scale[1][1]' _item.category_id database_PDB_matrix _item.mandatory_code no _item_default.value 1.0 _item_sub_category.id matrix _item_type.code float save_ save__database_PDB_matrix.scale[1][2] _item_description.description ; The [1][2] element of the PDB SCALE matrix. ; _item.name '_database_PDB_matrix.scale[1][2]' _item.category_id database_PDB_matrix _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id matrix _item_type.code float save_ save__database_PDB_matrix.scale[1][3] _item_description.description ; The [1][3] element of the PDB SCALE matrix. ; _item.name '_database_PDB_matrix.scale[1][3]' _item.category_id database_PDB_matrix _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id matrix _item_type.code float save_ save__database_PDB_matrix.scale[2][1] _item_description.description ; The [2][1] element of the PDB SCALE matrix. ; _item.name '_database_PDB_matrix.scale[2][1]' _item.category_id database_PDB_matrix _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id matrix _item_type.code float save_ save__database_PDB_matrix.scale[2][2] _item_description.description ; The [2][2] element of the PDB SCALE matrix. ; _item.name '_database_PDB_matrix.scale[2][2]' _item.category_id database_PDB_matrix _item.mandatory_code no _item_default.value 1.0 _item_sub_category.id matrix _item_type.code float save_ save__database_PDB_matrix.scale[2][3] _item_description.description ; The [2][3] element of the PDB SCALE matrix. ; _item.name '_database_PDB_matrix.scale[2][3]' _item.category_id database_PDB_matrix _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id matrix _item_type.code float save_ save__database_PDB_matrix.scale[3][1] _item_description.description ; The [3][1] element of the PDB SCALE matrix. ; _item.name '_database_PDB_matrix.scale[3][1]' _item.category_id database_PDB_matrix _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id matrix _item_type.code float save_ save__database_PDB_matrix.scale[3][2] _item_description.description ; The [3][2] element of the PDB SCALE matrix. ; _item.name '_database_PDB_matrix.scale[3][2]' _item.category_id database_PDB_matrix _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id matrix _item_type.code float save_ save__database_PDB_matrix.scale[3][3] _item_description.description ; The [3][3] element of the PDB SCALE matrix. ; _item.name '_database_PDB_matrix.scale[3][3]' _item.category_id database_PDB_matrix _item.mandatory_code no _item_default.value 1.0 _item_sub_category.id matrix _item_type.code float save_ save__database_PDB_matrix.scale_vector[1] _item_description.description ; The [1] element of the PDB SCALE vector. ; _item.name '_database_PDB_matrix.scale_vector[1]' _item.category_id database_PDB_matrix _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__database_PDB_matrix.scale_vector[2] _item_description.description ; The [2] element of the PDB SCALE vector. ; _item.name '_database_PDB_matrix.scale_vector[2]' _item.category_id database_PDB_matrix _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__database_PDB_matrix.scale_vector[3] _item_description.description ; The [3] element of the PDB SCALE vector. ; _item.name '_database_PDB_matrix.scale_vector[3]' _item.category_id database_PDB_matrix _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ ######################### ## DATABASE_PDB_REMARK ## ######################### save_database_PDB_remark _category.description ; Data items in the DATABASE_PDB_REMARK category record details about the data block as archived by the Protein Data Bank (PDB). Some data appearing in PDB REMARK records can be algorithmically extracted into the appropriate data items in the data block. These data items are included only for consistency with older PDB format files. They should appear in a data block only if that data block was created by reformatting a PDB format file. ; _category.id database_PDB_remark _category.mandatory_code no _category_key.name '_database_PDB_remark.id' loop_ _category_group.id 'inclusive_group' 'database_group' 'pdb_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _database_PDB_remark.id _database_PDB_remark.text 3 ; REFINEMENT. BY THE RESTRAINED LEAST-SQUARES PROCEDURE OF J. KONNERT AND W. HENDRICKSON (PROGRAM *PROLSQ*). THE R VALUE IS 0.176 FOR 12901 REFLECTIONS IN THE RESOLUTION RANGE 8.0 TO 2.0 ANGSTROMS WITH I .GT. SIGMA(I). RMS DEVIATIONS FROM IDEAL VALUES (THE VALUES OF SIGMA, IN PARENTHESES, ARE THE INPUT ESTIMATED STANDARD DEVIATIONS THAT DETERMINE THE RELATIVE WEIGHTS OF THE CORRESPONDING RESTRAINTS) DISTANCE RESTRAINTS (ANGSTROMS) BOND DISTANCE 0.018(0.020) ANGLE DISTANCE 0.038(0.030) PLANAR 1-4 DISTANCE 0.043(0.040) PLANE RESTRAINT (ANGSTROMS) 0.015(0.020) CHIRAL-CENTER RESTRAINT (ANGSTROMS**3) 0.177(0.150) NON-BONDED CONTACT RESTRAINTS (ANGSTROMS) SINGLE TORSION CONTACT 0.216(0.500) MULTIPLE TORSION CONTACT 0.207(0.500) POSSIBLE HYDROGEN BOND 0.245(0.500) CONFORMATIONAL TORSION ANGLE RESTRAINT (DEGREES) PLANAR (OMEGA) 2.6(3.0) STAGGERED 17.4(15.0) ORTHONORMAL 18.1(20.0) ; 4 ; THE TWO CHAINS OF THE DIMERIC ENZYME HAS BEEN ASSIGNED THE THE CHAIN INDICATORS *A* AND *B*. ; # - - - - data truncated for brevity - - - - ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__database_PDB_remark.id _item_description.description ; A unique identifier for the PDB remark record. ; _item.name '_database_PDB_remark.id' _item.category_id database_PDB_remark _item.mandatory_code yes _item_type.code int save_ save__database_PDB_remark.text _item_description.description ; The full text of the PDB remark record. ; _item.name '_database_PDB_remark.text' _item.category_id database_PDB_remark _item.mandatory_code no _item_type.code text save_ ###################### ## DATABASE_PDB_REV ## ###################### save_database_PDB_rev _category.description ; Data items in the DATABASE_PDB_REV category record details about the history of the data block as archived by the Protein Data Bank (PDB). These data items are assigned by the PDB database managers and should only appear in a data block if they originate from that source. ; _category.id database_PDB_rev _category.mandatory_code no _category_key.name '_database_PDB_rev.num' loop_ _category_group.id 'inclusive_group' 'database_group' 'pdb_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _database_PDB_rev.num _database_PDB_rev.author_name _database_PDB_rev.date _database_PDB_rev.date_original _database_PDB_rev.status _database_PDB_rev.mod_type 1 'Fitzgerald, Paula M.D' 1991-10-15 1990-04-30 'full release' 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__database_PDB_rev.author_name _item_description.description ; The name of the person responsible for submitting this revision to the PDB. The family name(s) followed by a comma precedes the first name(s) or initial(s). ; _item.name '_database_PDB_rev.author_name' _item.category_id database_PDB_rev _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'Bleary, Percival R.' "O'Neil, F.K." 'Van den Bossche, G.' 'Yang, D.-L.' 'Simonov, Yu.A' save_ save__database_PDB_rev.date _item_description.description ; Date the PDB revision took place. Taken from the REVDAT record. ; _item.name '_database_PDB_rev.date' _item.category_id database_PDB_rev _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__database_PDB_rev.date_original _item_description.description ; Date the entry first entered the PDB database in the form yyyy-mm-dd. Taken from the PDB HEADER record. ; _item.name '_database_PDB_rev.date_original' _item.category_id database_PDB_rev _item.mandatory_code no _item_type.code yyyy-mm-dd _item_examples.case '1980-08-21' save_ save__database_PDB_rev.mod_type _item_description.description ; Taken from the REVDAT record. Refer to the Protein Data Bank format description at http://www.rcsb.org/pdb/docs/format/pdbguide2.2/guide2.2_frame.html for details. ; _item.name '_database_PDB_rev.mod_type' _item.category_id database_PDB_rev _item.mandatory_code no _item_type.code int loop_ _item_enumeration.value _item_enumeration.detail 0 'initial entry' 1 'all other types of modification' 2 'modifications to CONECT records' 3 ; modifications affecting the coordinates or their transforms (CRYST1, ORIGX, SCALE, MTRIX, TVECT, ATOM, HETATM, SIGATM records) ; 4 ; layer 1 to layer 2 revision which may affect all record types ; 5 'data uniformity processing' save_ save__database_PDB_rev.num _item_description.description ; The value of _database_PDB_rev.num must uniquely and sequentially identify a record in the DATABASE_PDB_REV list. Note that this item must be a number and that modification numbers are assigned in increasing numerical order. ; loop_ _item.name _item.category_id _item.mandatory_code '_database_PDB_rev.num' database_PDB_rev yes '_database_PDB_rev_record.rev_num' database_PDB_rev_record yes loop_ _item_linked.child_name _item_linked.parent_name '_database_PDB_rev_record.rev_num' '_database_PDB_rev.num' _item_type.code int save_ save__database_PDB_rev.replaced_by _item_description.description ; The PDB code for a subsequent PDB entry that replaced the PDB file corresponding to this data block. ; _item.name '_database_PDB_rev.replaced_by' _item.category_id database_PDB_rev _item.mandatory_code no _item_type.code line save_ save__database_PDB_rev.replaces _item_description.description ; The PDB code for a previous PDB entry that was replaced by the PDB file corresponding to this data block. ; _item.name '_database_PDB_rev.replaces' _item.category_id database_PDB_rev _item.mandatory_code no _item_type.code line save_ save__database_PDB_rev.status _item_description.description ; The status of this revision. ; _item.name '_database_PDB_rev.status' _item.category_id database_PDB_rev _item.mandatory_code no _item_type.code uline loop_ _item_enumeration.value 'in preparation' 'prerelease' 'full release' 'obsolete' save_ ############################# ## DATABASE_PDB_REV_RECORD ## ############################# save_database_PDB_rev_record _category.description ; Data items in the DATABASE_PDB_REV_RECORD category record details about specific record types that were changed in a given revision of a PDB entry. These data items are assigned by the PDB database managers and should only appear in a data block if they originate from that source. ; _category.id database_PDB_rev_record _category.mandatory_code no loop_ _category_key.name '_database_PDB_rev_record.rev_num' '_database_PDB_rev_record.type' loop_ _category_group.id 'inclusive_group' 'database_group' 'pdb_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - hypothetical example. ; ; loop_ _database_PDB_rev_record.rev_num _database_PDB_rev_record.type _database_PDB_rev_record.details 1 CONECT ; Error fix - incorrect connection between atoms 2312 and 2317 ; 2 MATRIX 'For consistency with 1995-08-04 style-guide' 3 ORIGX 'Based on new data from author' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__database_PDB_rev_record.details _item_description.description ; A description of special aspects of the revision of records in this PDB entry. ; _item.name '_database_PDB_rev_record.details' _item.category_id database_PDB_rev_record _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'Based on new data from author' 'For consistency with 1995-08-04 style-guide' 'For consistency with structural class' save_ save__database_PDB_rev_record.rev_num _item_description.description ; This data item is a pointer to _database_PDB_rev.num in the DATABASE_PDB_REV category. ; _item.name '_database_PDB_rev_record.rev_num' _item.mandatory_code yes save_ save__database_PDB_rev_record.type _item_description.description ; The types of records that were changed in this revision to a PDB entry. ; _item.name '_database_PDB_rev_record.type' _item.category_id database_PDB_rev_record _item.mandatory_code yes _item_type.code line loop_ _item_examples.case 'CRYST1' 'SCALE' 'MTRIX' 'ATOM' 'HETATM' save_ ######################## ## DATABASE_PDB_TVECT ## ######################## save_database_PDB_tvect _category.description ; The DATABASE_PDB_TVECT category provides placeholders for the TVECT matrices and vectors used by the Protein Data Bank (PDB). These data items are included only for consistency with older PDB format files. They should appear in a data block only if the data block was created by reformatting a PDB format file. ; _category.id database_PDB_tvect _category.mandatory_code no _category_key.name '_database_PDB_tvect.id' loop_ _category_group.id 'inclusive_group' 'database_group' 'pdb_group' save_ save__database_PDB_tvect.details _item_description.description ; A description of special aspects of this TVECT. ; _item.name '_database_PDB_tvect.details' _item.category_id database_PDB_tvect _item.mandatory_code no _item_type.code text save_ save__database_PDB_tvect.id _item_description.description ; The value of _database_PDB_tvect.id must uniquely identify a record in the DATABASE_PDB_TVECT list. Note that this item need not be a number; it can be any unique identifier. ; _item.name '_database_PDB_tvect.id' _item.category_id database_PDB_tvect _item.mandatory_code yes _item_type.code code save_ save__database_PDB_tvect.vector[1] _item_description.description ; The [1] element of the PDB TVECT vector. ; _item.name '_database_PDB_tvect.vector[1]' _item.category_id database_PDB_tvect _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__database_PDB_tvect.vector[2] _item_description.description ; The [2] element of the PDB TVECT vector. ; _item.name '_database_PDB_tvect.vector[2]' _item.category_id database_PDB_tvect _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__database_PDB_tvect.vector[3] _item_description.description ; The [3] element of the PDB TVECT vector. ; _item.name '_database_PDB_tvect.vector[3]' _item.category_id database_PDB_tvect _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ ############ ## DIFFRN ## ############ save_diffrn _category.description ; Data items in the DIFFRN category record details about the diffraction data and their measurement. ; _category.id diffrn _category.mandatory_code no _category_key.name '_diffrn.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _diffrn.id 'Set1' _diffrn.ambient_temp 293(3) _diffrn.ambient_environment ; Mother liquor from the reservoir of the vapor diffusion experiment, mounted in room air ; _diffrn.crystal_support ; 0.7 mm glass capillary, sealed with dental wax ; _diffrn.crystal_treatment ; Equilibrated in rotating anode radiation enclosure for 18 hours prior to beginning of data collection ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991). Acta Cryst. C47, 2276-2277]. ; ; _diffrn.id 'd1' _diffrn.details ; \q scan width (1.0 + 0.14tan\q)\%, \q scan rate 1.2\% per min. Background counts for 5 sec on each side every scan. ; _diffrn.ambient_temp 293 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn.ambient_environment _item_description.description ; The gas or liquid surrounding the sample, if not air. ; _item.name '_diffrn.ambient_environment' _item.category_id diffrn _item.mandatory_code no _item_aliases.alias_name '_diffrn_ambient_environment' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ #save__diffrn.ambient_pressure # _item_description.description #; The mean pressure in kilopascals at which the intensities were # measured. #; # _item.name '_diffrn.ambient_pressure' # _item.category_id diffrn # _item.mandatory_code no # _item_aliases.alias_name '_diffrn_ambient_pressure' # _item_aliases.dictionary cif_core.dic # _item_aliases.version 2.0.1 # loop_ # _item_range.maximum # _item_range.minimum . 0.0 # 0.0 0.0 # _item_related.related_name '_diffrn.ambient_pressure_esd' # _item_related.function_code associated_esd # _item_type.code float # _item_type_conditions.code esd # _item_units.code kilopascals # save_ # #save__diffrn.ambient_pressure_esd # _item_description.description #; The standard uncertainty (estimated standard deviation) # of _diffrn.ambient_pressure. #; # _item.name '_diffrn.ambient_pressure_esd' # _item.category_id diffrn # _item.mandatory_code no # _item_default.value 0.0 # _item_related.related_name '_diffrn.ambient_pressure' # _item_related.function_code associated_value # _item_type.code float # _item_units.code kilopascals # save_ save__diffrn.ambient_temp _item_description.description ; The mean temperature in kelvins at which the intensities were measured. ; _item.name '_diffrn.ambient_temp' _item.category_id diffrn _item.mandatory_code no _item_aliases.alias_name '_diffrn_ambient_temperature' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_diffrn.ambient_temp_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code kelvins save_ save__diffrn.ambient_temp_details _item_description.description ; A description of special aspects of temperature control during data collection. ; _item.name '_diffrn.ambient_temp_details' _item.category_id diffrn _item.mandatory_code no _item_type.code text save_ save__diffrn.ambient_temp_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _diffrn.ambient_temp. ; _item.name '_diffrn.ambient_temp_esd' _item.category_id diffrn _item.mandatory_code no # _item_default.value 0.0 _item_related.related_name '_diffrn.ambient_temp' _item_related.function_code associated_value _item_type.code float _item_units.code kelvins save_ save__diffrn.crystal_id _item_description.description ; This data item is a pointer to _exptl_crystal.id in the EXPTL_CRYSTAL category. ; _item.name '_diffrn.crystal_id' _item.mandatory_code yes _item_aliases.alias_name '_diffrn_refln_crystal_id' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 save_ save__diffrn.crystal_support _item_description.description ; The physical device used to support the crystal during data collection. ; _item.name '_diffrn.crystal_support' _item.category_id diffrn _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'glass capillary' 'quartz capillary' 'fiber' 'metal loop' save_ save__diffrn.crystal_treatment _item_description.description ; Remarks about how the crystal was treated prior to intensity measurement. Particularly relevant when intensities were measured at low temperature. ; _item.name '_diffrn.crystal_treatment' _item.category_id diffrn _item.mandatory_code no _item_aliases.alias_name '_diffrn_crystal_treatment' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'equilibrated in hutch for 24 hours' 'flash frozen in liquid nitrogen' 'slow cooled with direct air stream' save_ save__diffrn.details _item_description.description ; Special details of the diffraction measurement process. Should include information about source instability, crystal motion, degradation and so on. ; _item.name '_diffrn.details' _item.category_id diffrn _item.mandatory_code no _item_aliases.alias_name '_diffrn_special_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__diffrn.id _item_description.description ; This data item uniquely identifies a set of diffraction data. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn.id' diffrn yes '_diffrn_detector.diffrn_id' diffrn_detector yes '_diffrn_measurement.diffrn_id' diffrn_measurement yes '_diffrn_orient_matrix.diffrn_id' diffrn_orient_matrix yes '_diffrn_orient_refln.diffrn_id' diffrn_orient_refln yes '_diffrn_radiation.diffrn_id' diffrn_radiation yes '_diffrn_refln.diffrn_id' diffrn_refln yes '_diffrn_reflns.diffrn_id' diffrn_reflns yes '_diffrn_source.diffrn_id' diffrn_source yes '_diffrn_standard_refln.diffrn_id' diffrn_standard_refln yes '_diffrn_standards.diffrn_id' diffrn_standards yes loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_detector.diffrn_id' '_diffrn.id' '_diffrn_measurement.diffrn_id' '_diffrn.id' '_diffrn_orient_matrix.diffrn_id' '_diffrn.id' '_diffrn_orient_refln.diffrn_id' '_diffrn.id' '_diffrn_radiation.diffrn_id' '_diffrn.id' '_diffrn_refln.diffrn_id' '_diffrn.id' '_diffrn_reflns.diffrn_id' '_diffrn.id' '_diffrn_source.diffrn_id' '_diffrn.id' '_diffrn_standard_refln.diffrn_id' '_diffrn.id' '_diffrn_standards.diffrn_id' '_diffrn.id' _item_type.code code save_ ####################### ## DIFFRN_ATTENUATOR ## ####################### save_diffrn_attenuator _category.description ; Data items in the DIFFRN_ATTENUATOR category record details about the diffraction attenuator scales employed. ; _category.id diffrn_attenuator _category.mandatory_code no _category_key.name '_diffrn_attenuator.code' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _diffrn_attenuator.code 1 _diffrn_attenuator.scale 16.976 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_attenuator.code _item_description.description ; A code associated with a particular attenuator setting. This code is referenced by the _diffrn_refln.attenuator_code which is stored with the diffraction data. See _diffrn_attenuator.scale. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_attenuator.code' diffrn_attenuator yes _item_aliases.alias_name '_diffrn_attenuator_code' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_refln.attenuator_code' '_diffrn_attenuator.code' _item_type.code code save_ save__diffrn_attenuator.scale _item_description.description ; The scale factor applied when an intensity measurement is reduced by an attenuator identified by _diffrn_attenuator.code. The measured intensity must be multiplied by this scale to convert it to the same scale as unattenuated intensities. ; _item.name '_diffrn_attenuator.scale' _item.category_id diffrn_attenuator _item.mandatory_code no _item_aliases.alias_name '_diffrn_attenuator_scale' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 1.0 1.0 1.0 _item_type.code float save_ ##################### ## DIFFRN_DETECTOR ## ##################### save_diffrn_detector _category.description ; Data items in the DIFFRN_DETECTOR category describe the detector used to measure the scattered radiation, including any analyser and post-sample collimation. ; _category.id diffrn_detector _category.mandatory_code no _category_key.name '_diffrn_detector.diffrn_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _diffrn_detector.diffrn_id 'd1' _diffrn_detector.detector 'multiwire' _diffrn_detector.type 'Siemens' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector.details _item_description.description ; A description of special aspects of the radiation detector. ; _item.name '_diffrn_detector.details' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__diffrn_detector.detector _item_description.description ; The general class of the radiation detector. ; _item.name '_diffrn_detector.detector' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector' cifdic.c91 1.0 '_diffrn_detector' cif_core.dic 2.0 _item_type.code text loop_ _item_examples.case 'photographic film' 'scintillation counter' 'CCD plate' 'BF~3~ counter' save_ save__diffrn_detector.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_detector.diffrn_id' _item.mandatory_code yes save_ #save__diffrn_detector.dtime # _item_description.description #; The deadtime in microseconds of the detectors used to measure # the diffraction intensities. #; # _item.name '_diffrn_detector.dtime' # _item.category_id diffrn_detector # _item.mandatory_code no # loop_ # _item_aliases.alias_name # _item_aliases.dictionary # _item_aliases.version '_diffrn_radiation_detector_dtime' # cifdic.c91 # 1.0 # '_diffrn_detector_dtime' # cif_core.dic # 2.0 # loop_ # _item_range.maximum # _item_range.minimum . 0.0 # 0.0 0.0 # _item_type.code float # _item_units.code microseconds # save_ save__diffrn_detector.type _item_description.description ; The make, model or name of the detector device used. ; _item.name '_diffrn_detector.type' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ ######################## ## DIFFRN_MEASUREMENT ## ######################## save_diffrn_measurement _category.description ; Data items in the DIFFRN_MEASUREMENT category record details about the device used to orient and/or position the crystal during data measurement and the manner in which the diffraction data were measured. ; _category.id diffrn_measurement _category.mandatory_code no _category_key.name '_diffrn_measurement.diffrn_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _diffrn_measurement.diffrn_id 'd1' _diffrn_measurement.device '3-circle camera' _diffrn_measurement.device_type 'Supper model x' _diffrn_measurement.device_details 'none' _diffrn_measurement.method 'omega scan' _diffrn_measurement.details ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _diffrn_measurement.diffrn_id 's1' _diffrn_measurement.device_type 'Philips PW1100/20 diffractometer' _diffrn_measurement.method \q/2\q ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_measurement.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_measurement.diffrn_id' _item.mandatory_code yes save_ save__diffrn_measurement.details _item_description.description ; A description of special aspects of the intensity measurement. ; _item.name '_diffrn_measurement.details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; save_ save__diffrn_measurement.device _item_description.description ; The general class of goniometer or device used to support and orient the specimen. ; _item.name '_diffrn_measurement.device' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '3-circle camera' '4-circle camera' 'kappa-geometry camera' 'oscillation camera' 'precession camera' save_ save__diffrn_measurement.device_details _item_description.description ; A description of special aspects of the device used to measure the diffraction intensities. ; _item.name '_diffrn_measurement.device_details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; commercial goniometer modified locally to allow for 90\% \t arc ; save_ save__diffrn_measurement.device_type _item_description.description ; The make, model or name of the measurement device (goniometer) used. ; _item.name '_diffrn_measurement.device_type' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Supper model q' 'Huber model r' 'Enraf-Nonius model s' 'homemade' save_ save__diffrn_measurement.method _item_description.description ; Method used to measure intensities. ; _item.name '_diffrn_measurement.method' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_method' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'profile data from theta/2theta scans' save_ save__diffrn_measurement.specimen_support _item_description.description ; The physical device used to support the crystal during data collection. ; _item.name '_diffrn_measurement.specimen_support' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_specimen_support' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'glass capillary' 'quartz capillary' 'fiber' 'metal loop' save_ ########################## ## DIFFRN_ORIENT_MATRIX ## ########################## save_diffrn_orient_matrix _category.description ; Data items in the DIFFRN_ORIENT_MATRIX category record details about the orientation matrix used in the measurement of the diffraction data. ; _category.id diffrn_orient_matrix _category.mandatory_code no _category_key.name '_diffrn_orient_matrix.diffrn_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on CAD-4 diffractometer data obtained for Yb(S-C5H4N)2(THF)4. ; ; _diffrn_orient_matrix.diffrn_id set1 _diffrn_orient_matrix.type ; reciprocal axis matrix, multiplies hkl vector to generate diffractometer xyz vector and diffractometer angles ; _diffrn_orient_matrix.UB[1][1] -0.071479 _diffrn_orient_matrix.UB[1][2] 0.020208 _diffrn_orient_matrix.UB[1][3] 0.039076 _diffrn_orient_matrix.UB[2][1] 0.035372 _diffrn_orient_matrix.UB[2][2] 0.056209 _diffrn_orient_matrix.UB[2][3] 0.078324 _diffrn_orient_matrix.UB[3][1] -0.007470 _diffrn_orient_matrix.UB[3][2] 0.067854 _diffrn_orient_matrix.UB[3][3] -0.017832 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_orient_matrix.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_orient_matrix.diffrn_id' _item.mandatory_code yes save_ save__diffrn_orient_matrix.type _item_description.description ; A description of the orientation matrix type and how it should be applied to define the orientation of the crystal precisely with respect to the diffractometer axes. ; _item.name '_diffrn_orient_matrix.type' _item.category_id diffrn_orient_matrix _item.mandatory_code no _item_aliases.alias_name '_diffrn_orient_matrix_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__diffrn_orient_matrix.UB[1][1] _item_description.description ; The [1][1] element of the 3x3 matrix that defines the dimensions of the reciprocal cell and its orientation with respect to the local diffractometer axes. See also _diffrn_orient_matrix.type. ; _item.name '_diffrn_orient_matrix.UB[1][1]' _item.category_id diffrn_orient_matrix _item.mandatory_code no _item_aliases.alias_name '_diffrn_orient_matrix_UB_11' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code float save_ save__diffrn_orient_matrix.UB[1][2] _item_description.description ; The [1][2] element of the 3x3 matrix that defines the dimensions of the reciprocal cell and its orientation with respect to the local diffractometer axes. See also _diffrn_orient_matrix.type. ; _item.name '_diffrn_orient_matrix.UB[1][2]' _item.category_id diffrn_orient_matrix _item.mandatory_code no _item_aliases.alias_name '_diffrn_orient_matrix_UB_12' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__diffrn_orient_matrix.UB[1][3] _item_description.description ; The [1][3] element of the 3x3 matrix that defines the dimensions of the reciprocal cell and its orientation with respect to the local diffractometer axes. See also _diffrn_orient_matrix.type. ; _item.name '_diffrn_orient_matrix.UB[1][3]' _item.category_id diffrn_orient_matrix _item.mandatory_code no _item_aliases.alias_name '_diffrn_orient_matrix_UB_13' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__diffrn_orient_matrix.UB[2][1] _item_description.description ; The [2][1] element of the 3x3 matrix that defines the dimensions of the reciprocal cell and its orientation with respect to the local diffractometer axes. See also _diffrn_orient_matrix.type. ; _item.name '_diffrn_orient_matrix.UB[2][1]' _item.category_id diffrn_orient_matrix _item.mandatory_code no _item_aliases.alias_name '_diffrn_orient_matrix_UB_21' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__diffrn_orient_matrix.UB[2][2] _item_description.description ; The [2][2] element of the 3x3 matrix that defines the dimensions of the reciprocal cell and its orientation with respect to the local diffractometer axes. See also _diffrn_orient_matrix.type. ; _item.name '_diffrn_orient_matrix.UB[2][2]' _item.category_id diffrn_orient_matrix _item.mandatory_code no _item_aliases.alias_name '_diffrn_orient_matrix_UB_22' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__diffrn_orient_matrix.UB[2][3] _item_description.description ; The [2][3] element of the 3x3 matrix that defines the dimensions of the reciprocal cell and its orientation with respect to the local diffractometer axes. See also _diffrn_orient_matrix.type. ; _item.name '_diffrn_orient_matrix.UB[2][3]' _item.category_id diffrn_orient_matrix _item.mandatory_code no _item_aliases.alias_name '_diffrn_orient_matrix_UB_23' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__diffrn_orient_matrix.UB[3][1] _item_description.description ; The [3][1] element of the 3x3 matrix that defines the dimensions of the reciprocal cell and its orientation with respect to the local diffractometer axes. See also _diffrn_orient_matrix.type. ; _item.name '_diffrn_orient_matrix.UB[3][1]' _item.category_id diffrn_orient_matrix _item.mandatory_code no _item_aliases.alias_name '_diffrn_orient_matrix_UB_31' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__diffrn_orient_matrix.UB[3][2] _item_description.description ; The [3][2] element of the 3x3 matrix that defines the dimensions of the reciprocal cell and its orientation with respect to the local diffractometer axes. See also _diffrn_orient_matrix.type. ; _item.name '_diffrn_orient_matrix.UB[3][2]' _item.category_id diffrn_orient_matrix _item.mandatory_code no _item_aliases.alias_name '_diffrn_orient_matrix_UB_32' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__diffrn_orient_matrix.UB[3][3] _item_description.description ; The [3][3] element of the 3x3 matrix that defines the dimensions of the reciprocal cell and its orientation with respect to the local diffractometer axes. See also _diffrn_orient_matrix.type. ; _item.name '_diffrn_orient_matrix.UB[3][3]' _item.category_id diffrn_orient_matrix _item.mandatory_code no _item_aliases.alias_name '_diffrn_orient_matrix_UB_33' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ ######################### ## DIFFRN_ORIENT_REFLN ## ######################### save_diffrn_orient_refln _category.description ; Data items in the DIFFRN_ORIENT_REFLN category record details about the reflections that define the orientation matrix used in the measurement of the diffraction intensities. ; _category.id diffrn_orient_refln _category.mandatory_code no loop_ _category_key.name '_diffrn_orient_refln.diffrn_id' '_diffrn_orient_refln.index_h' '_diffrn_orient_refln.index_k' '_diffrn_orient_refln.index_l' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on CAD-4 diffractometer data obtained for Yb(S-C5H4N)2(THF)4. ; ; _diffrn_orient_refln.diffrn_id myset1 _diffrn_orient_refln.index_h 2 _diffrn_orient_refln.index_k 0 _diffrn_orient_refln.index_l 2 _diffrn_orient_refln.angle_chi -28.45 _diffrn_orient_refln.angle_kappa -11.32 _diffrn_orient_refln.angle_omega 5.33 _diffrn_orient_refln.angle_phi 101.78 _diffrn_orient_refln.angle_psi 0.00 _diffrn_orient_refln.angle_theta 10.66 # ... data abbreviated ... ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_orient_refln.angle_chi _item_description.description ; Diffractometer angle chi of a reflection used to define the orientation matrix in degrees. See _diffrn_orient_matrix.UB[][] and the Miller indices in the DIFFRN_ORIENT_REFLN category. ; _item.name '_diffrn_orient_refln.angle_chi' _item.category_id diffrn_orient_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_orient_refln_angle_chi' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_diffrn_orient_refln.angle_kappa' '_diffrn_orient_refln.angle_omega' '_diffrn_orient_refln.angle_phi' '_diffrn_orient_refln.angle_psi' '_diffrn_orient_refln.angle_theta' _item_type.code float _item_units.code degrees save_ save__diffrn_orient_refln.angle_kappa _item_description.description ; Diffractometer angle kappa of a reflection used to define the orientation matrix in degrees. See _diffrn_orient_matrix.UB[][] and the Miller indices in the DIFFRN_ORIENT_REFLN category. ; _item.name '_diffrn_orient_refln.angle_kappa' _item.category_id diffrn_orient_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_orient_refln_angle_kappa' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_diffrn_orient_refln.angle_chi' '_diffrn_orient_refln.angle_omega' '_diffrn_orient_refln.angle_phi' '_diffrn_orient_refln.angle_psi' '_diffrn_orient_refln.angle_theta' _item_type.code float _item_units.code degrees save_ save__diffrn_orient_refln.angle_omega _item_description.description ; Diffractometer angle omega of a reflection used to define the orientation matrix in degrees. See _diffrn_orient_matrix.UB[][] and the Miller indices in the DIFFRN_ORIENT_REFLN category. ; _item.name '_diffrn_orient_refln.angle_omega' _item.category_id diffrn_orient_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_orient_refln_angle_omega' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_diffrn_orient_refln.angle_chi' '_diffrn_orient_refln.angle_kappa' '_diffrn_orient_refln.angle_phi' '_diffrn_orient_refln.angle_psi' '_diffrn_orient_refln.angle_theta' _item_type.code float _item_units.code degrees save_ save__diffrn_orient_refln.angle_phi _item_description.description ; Diffractometer angle phi of a reflection used to define the orientation matrix in degrees. See _diffrn_orient_matrix.UB[][] and the Miller indices in the DIFFRN_ORIENT_REFLN category. ; _item.name '_diffrn_orient_refln.angle_phi' _item.category_id diffrn_orient_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_orient_refln_angle_phi' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_diffrn_orient_refln.angle_chi' '_diffrn_orient_refln.angle_kappa' '_diffrn_orient_refln.angle_omega' '_diffrn_orient_refln.angle_psi' '_diffrn_orient_refln.angle_theta' _item_type.code float _item_units.code degrees save_ save__diffrn_orient_refln.angle_psi _item_description.description ; Diffractometer angle psi of a reflection used to define the orientation matrix in degrees. See _diffrn_orient_matrix.UB[][] and the Miller indices in the DIFFRN_ORIENT_REFLN category. ; _item.name '_diffrn_orient_refln.angle_psi' _item.category_id diffrn_orient_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_orient_refln_angle_psi' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_diffrn_orient_refln.angle_chi' '_diffrn_orient_refln.angle_kappa' '_diffrn_orient_refln.angle_omega' '_diffrn_orient_refln.angle_phi' '_diffrn_orient_refln.angle_theta' _item_type.code float _item_units.code degrees save_ save__diffrn_orient_refln.angle_theta _item_description.description ; Diffractometer angle theta of a reflection used to define the orientation matrix in degrees. See _diffrn_orient_matrix.UB[][] and the Miller indices in the DIFFRN_ORIENT_REFLN category. ; _item.name '_diffrn_orient_refln.angle_theta' _item.category_id diffrn_orient_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_orient_refln_angle_theta' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_diffrn_orient_refln.angle_chi' '_diffrn_orient_refln.angle_kappa' '_diffrn_orient_refln.angle_omega' '_diffrn_orient_refln.angle_phi' '_diffrn_orient_refln.angle_psi' _item_type.code float _item_units.code degrees save_ save__diffrn_orient_refln.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_orient_refln.diffrn_id' _item.mandatory_code yes save_ save__diffrn_orient_refln.index_h _item_description.description ; Miller index h of a reflection used to define the orientation matrix. ; _item.name '_diffrn_orient_refln.index_h' _item.category_id diffrn_orient_refln _item.mandatory_code yes _item_aliases.alias_name '_diffrn_orient_refln_index_h' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_diffrn_orient_refln.index_k' '_diffrn_orient_refln.index_l' _item_sub_category.id miller_index _item_type.code int save_ save__diffrn_orient_refln.index_k _item_description.description ; Miller index k of a reflection used to define the orientation matrix. ; _item.name '_diffrn_orient_refln.index_k' _item.category_id diffrn_orient_refln _item.mandatory_code yes _item_aliases.alias_name '_diffrn_orient_refln_index_k' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_diffrn_orient_refln.index_h' '_diffrn_orient_refln.index_l' _item_sub_category.id miller_index _item_type.code int save_ save__diffrn_orient_refln.index_l _item_description.description ; Miller index l of a reflection used to define the orientation matrix. ; _item.name '_diffrn_orient_refln.index_l' _item.category_id diffrn_orient_refln _item.mandatory_code yes _item_aliases.alias_name '_diffrn_orient_refln_index_l' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_diffrn_orient_refln.index_h' '_diffrn_orient_refln.index_l' _item_sub_category.id miller_index _item_type.code int save_ ###################### ## DIFFRN_RADIATION ## ###################### save_diffrn_radiation _category.description ; Data items in the DIFFRN_RADIATION category describe the radiation used in measuring the diffraction intensities, its collimation and monochromatization before the sample. Post-sample treatment of the beam is described by data items in the DIFFRN_DETECTOR category. ; _category.id diffrn_radiation _category.mandatory_code no _category_key.name '_diffrn_radiation.diffrn_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _diffrn_radiation.diffrn_id 'set1' _diffrn_radiation.collimation '0.3 mm double pinhole' _diffrn_radiation.monochromator 'graphite' _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.wavelength_id 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _diffrn_radiation.wavelength_id 1 _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.monochromator 'graphite' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_radiation.collimation _item_description.description ; The collimation or focusing applied to the radiation. ; _item.name '_diffrn_radiation.collimation' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_collimation' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '0.3 mm double-pinhole' '0.5 mm' 'focusing mirrors' save_ save__diffrn_radiation.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_radiation.diffrn_id' _item.mandatory_code yes save_ save__diffrn_radiation.filter_edge _item_description.description ; Absorption edge in angstroms of the radiation filter used. ; _item.name '_diffrn_radiation.filter_edge' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_filter_edge' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__diffrn_radiation.inhomogeneity _item_description.description ; Half-width in millimetres of the incident beam in the direction perpendicular to the diffraction plane. ; _item.name '_diffrn_radiation.inhomogeneity' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_inhomogeneity' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code millimetres save_ save__diffrn_radiation.monochromator _item_description.description ; The method used to obtain monochromatic radiation. If a mono- chromator crystal is used, the material and the indices of the Bragg reflection are specified. ; _item.name '_diffrn_radiation.monochromator' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_monochromator' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Zr filter' 'Ge 220' 'none' 'equatorial mounted graphite' save_ save__diffrn_radiation.polarisn_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the perpendicular component of the polarization and the diffraction plane. See _diffrn_radiation.polarisn_ratio. ; _item.name '_diffrn_radiation.polarisn_norm' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_norm' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.polarisn_ratio _item_description.description ; Polarization ratio of the diffraction beam incident on the crystal. This is the ratio of the perpendicularly polarized to the parallel-polarized component of the radiation. The perpendicular component forms an angle of _diffrn_radiation.polarisn_norm to the normal to the diffraction plane of the sample (i.e. the plane containing the incident and reflected beams). ; _item.name '_diffrn_radiation.polarisn_ratio' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_ratio' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__diffrn_radiation.probe _item_description.description ; The nature of the radiation used (i.e. the name of the subatomic particle or the region of the electromagnetic spectrum). It is strongly recommended that this information is given, so that the probe radiation can be simply determined. ; _item.name '_diffrn_radiation.probe' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_probe' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value 'x-ray' 'neutron' 'electron' 'gamma' save_ save__diffrn_radiation.type _item_description.description ; The nature of the radiation. This is typically a description of the X-ray wavelength in Siegbahn notation. ; _item.name '_diffrn_radiation.type' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'CuK\a' 'Cu K\a~1~' 'Cu K-L~2,3~' 'white-beam' save_ save__diffrn_radiation.xray_symbol _item_description.description ; The IUPAC symbol for the X-ray wavelength for the probe radiation. ; _item.name '_diffrn_radiation.xray_symbol' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_xray_symbol' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value _item_enumeration.detail 'K-L~3~' 'K\a~1~ in older Siegbahn notation' 'K-L~2~' 'K\a~2~ in older Siegbahn notation' 'K-M~3~' 'K\b~1~ in older Siegbahn notation' 'K-L~2,3~' 'use where K-L~3~ and K-L~2~ are not resolved' save_ save__diffrn_radiation.wavelength_id _item_description.description ; This data item is a pointer to _diffrn_radiation_wavelength.id in the DIFFRN_RADIATION_WAVELENGTH category. ; _item.name '_diffrn_radiation.wavelength_id' _item.mandatory_code yes save_ ################################# ## DIFFRN_RADIATION_WAVELENGTH ## ################################# save_diffrn_radiation_wavelength _category.description ; Data items in the DIFFRN_RADIATION_WAVELENGTH category describe the wavelength of the radiation used to measure the diffraction intensities. Items may be looped to identify and assign weights to distinct components of a polychromatic beam. ; _category.id diffrn_radiation_wavelength _category.mandatory_code no _category_key.name '_diffrn_radiation_wavelength.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _diffrn_radiation_wavelength.id 1 _diffrn_radiation_wavelength.wavelength 1.54 _diffrn_radiation_wavelength.wt 1.0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_radiation_wavelength.id _item_description.description ; The code identifying each value of _diffrn_radiation_wavelength.wavelength. Items in the DIFFRN_RADIATION_WAVELENGTH category are looped when multiple wavelengths are used. This code is used to link with the DIFFRN_REFLN category. The _diffrn_refln.wavelength_id codes must match one of the codes defined in this category. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_radiation_wavelength.id' diffrn_radiation_wavelength yes '_diffrn_radiation.wavelength_id' diffrn_radiation yes '_diffrn_refln.wavelength_id' diffrn_refln yes '_refln.wavelength_id' refln yes _item_aliases.alias_name '_diffrn_radiation_wavelength_id' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_radiation.wavelength_id' '_diffrn_radiation_wavelength.id' '_diffrn_refln.wavelength_id' '_diffrn_radiation_wavelength.id' '_refln.wavelength_id' '_diffrn_radiation_wavelength.id' _item_type.code code loop_ _item_examples.case 'x1' 'x2' 'neut' save_ save__diffrn_radiation_wavelength.wavelength _item_description.description ; The radiation wavelength in angstroms. ; _item.name '_diffrn_radiation_wavelength.wavelength' _item.category_id diffrn_radiation_wavelength _item.mandatory_code yes _item_aliases.alias_name '_diffrn_radiation_wavelength' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__diffrn_radiation_wavelength.wt _item_description.description ; The relative weight of a wavelength identified by the code _diffrn_radiation_wavelength.id in the list of wavelengths. ; _item.name '_diffrn_radiation_wavelength.wt' _item.category_id diffrn_radiation_wavelength _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_wavelength_wt' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_default.value 1.0 loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 0.0 0.0 0.0 _item_type.code float save_ ################## ## DIFFRN_REFLN ## ################## save_diffrn_refln _category.description ; Data items in the DIFFRN_REFLN category record details about the intensities in the diffraction data set identified by _diffrn_refln.diffrn_id. The DIFFRN_REFLN data items refer to individual intensity measurements and must be included in looped lists. The DIFFRN_REFLNS data items specify the parameters that apply to all intensity measurements in the particular diffraction data set identified by _diffrn_reflns.diffrn_id. ; _category.id diffrn_refln _category.mandatory_code no loop_ _category_key.name '_diffrn_refln.diffrn_id' '_diffrn_refln.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on CAD-4 diffractometer data obtained for Yb(S-C5H4N)2(THF)4 for data set 'set1' reflection 1102. ; ; _diffrn_refln.diffrn_id set1 _diffrn_refln.id 1102 _diffrn_refln.wavelength_id Cu1fixed _diffrn_refln.angle_chi 32.21 _diffrn_refln.angle_kappa 20.12 _diffrn_refln.angle_omega 11.54 _diffrn_refln.angle_phi 176.02 _diffrn_refln.angle_psi 0.00 _diffrn_refln.angle_theta 23.08 _diffrn_refln.attenuator_code 'Ni.005' _diffrn_refln.counts_bg_1 22 _diffrn_refln.counts_bg_2 25 _diffrn_refln.counts_net 3450 _diffrn_refln.counts_peak 321 _diffrn_refln.counts_total 3499 _diffrn_refln.detect_slit_horiz 0.04 _diffrn_refln.detect_slit_vert 0.02 _diffrn_refln.elapsed_time 1.00 _diffrn_refln.index_h 4 _diffrn_refln.index_k 0 _diffrn_refln.index_l 2 _diffrn_refln.intensity_net 202.56 _diffrn_refln.intensity_sigma 2.18 _diffrn_refln.scale_group_code A24 _diffrn_refln.scan_mode om _diffrn_refln.scan_mode_backgd mo _diffrn_refln.scan_rate 1.2 _diffrn_refln.scan_time_backgd 900.00 _diffrn_refln.scan_width 1.0 _diffrn_refln.sint_over_lambda 0.25426 _diffrn_refln.standard_code 1 _diffrn_refln.wavelength 1.54184 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_refln.angle_chi _item_description.description ; The diffractometer angle chi of a reflection in degrees. This angle corresponds to the specified orientation matrix and the original measured cell before any subsequent cell transformations. ; _item.name '_diffrn_refln.angle_chi' _item.category_id diffrn_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_refln_angle_chi' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code float _item_units.code degrees save_ save__diffrn_refln.angle_kappa _item_description.description ; The diffractometer angle kappa of a reflection in degrees. This angle corresponds to the specified orientation matrix and the original measured cell before any subsequent cell transformations. ; _item.name '_diffrn_refln.angle_kappa' _item.category_id diffrn_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_refln_angle_kappa' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code float _item_units.code degrees save_ save__diffrn_refln.angle_omega _item_description.description ; The diffractometer angle omega of a reflection in degrees. This angle corresponds to the specified orientation matrix and the original measured cell before any subsequent cell transformations. ; _item.name '_diffrn_refln.angle_omega' _item.category_id diffrn_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_refln_angle_omega' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code float _item_units.code degrees save_ save__diffrn_refln.angle_phi _item_description.description ; The diffractometer angle phi of a reflection in degrees. This angle corresponds to the specified orientation matrix and the original measured cell before any subsequent cell transformations. ; _item.name '_diffrn_refln.angle_phi' _item.category_id diffrn_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_refln_angle_phi' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code float _item_units.code degrees save_ save__diffrn_refln.angle_psi _item_description.description ; The diffractometer angle psi of a reflection in degrees. This angle corresponds to the specified orientation matrix and the original measured cell before any subsequent cell transformations. ; _item.name '_diffrn_refln.angle_psi' _item.category_id diffrn_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_refln_angle_psi' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code float _item_units.code degrees save_ save__diffrn_refln.angle_theta _item_description.description ; The diffractometer angle theta of a reflection in degrees. This angle corresponds to the specified orientation matrix and the original measured cell before any subsequent cell transformations. ; _item.name '_diffrn_refln.angle_theta' _item.category_id diffrn_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_refln_angle_theta' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code float _item_units.code degrees save_ save__diffrn_refln.attenuator_code _item_description.description ; The code identifying the attenuator setting for this reflection. This code must match one of the _diffrn_attenuator.code values. ; _item.name '_diffrn_refln.attenuator_code' _item.mandatory_code no _item_aliases.alias_name '_diffrn_refln_attenuator_code' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 save_ save__diffrn_refln.counts_bg_1 _item_description.description ; The diffractometer counts for the measurement of the background before the peak. ; _item.name '_diffrn_refln.counts_bg_1' _item.category_id diffrn_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_refln_counts_bg_1' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__diffrn_refln.counts_bg_2 _item_description.description ; The diffractometer counts for the measurement of the background after the peak. ; _item.name '_diffrn_refln.counts_bg_2' _item.category_id diffrn_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_refln_counts_bg_2' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__diffrn_refln.counts_net _item_description.description ; The diffractometer counts for the measurement of net counts after background removal. ; _item.name '_diffrn_refln.counts_net' _item.category_id diffrn_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_refln_counts_net' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__diffrn_refln.counts_peak _item_description.description ; The diffractometer counts for the measurement of counts for the peak scan or position. ; _item.name '_diffrn_refln.counts_peak' _item.category_id diffrn_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_refln_counts_peak' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__diffrn_refln.counts_total _item_description.description ; The diffractometer counts for the measurement of total counts (background plus peak). ; _item.name '_diffrn_refln.counts_total' _item.category_id diffrn_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_refln_counts_total' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__diffrn_refln.detect_slit_horiz _item_description.description ; Total slit aperture in degrees in the diffraction plane. ; _item.name '_diffrn_refln.detect_slit_horiz' _item.category_id diffrn_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_refln_detect_slit_horiz' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 0.0 0.0 0.0 _item_type.code float _item_units.code degrees save_ save__diffrn_refln.detect_slit_vert _item_description.description ; Total slit aperture in degrees perpendicular to the diffraction plane. ; _item.name '_diffrn_refln.detect_slit_vert' _item.category_id diffrn_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_refln_detect_slit_vert' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 0.0 0.0 0.0 _item_type.code float _item_units.code degrees save_ save__diffrn_refln.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_refln.diffrn_id' _item.mandatory_code yes save_ save__diffrn_refln.elapsed_time _item_description.description ; Elapsed time in minutes from the start of the diffraction experiment to the measurement of this intensity. ; _item.name '_diffrn_refln.elapsed_time' _item.category_id diffrn_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_refln_elapsed_time' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code minutes save_ save__diffrn_refln.id _item_description.description ; The value of _diffrn_refln.id must uniquely identify the reflection in the data set identified by the item _diffrn_refln.diffrn_id. Note that this item need not be a number; it can be any unique identifier. ; _item.name '_diffrn_refln.id' _item.category_id diffrn_refln _item.mandatory_code yes _item_type.code code save_ save__diffrn_refln.index_h _item_description.description ; Miller index h of a reflection. The values of the Miller indices in the DIFFRN_REFLN category need not match the values of the Miller indices in the REFLN category if a transformation of the original measured cell has taken place. Details of the cell transformation are given in _diffrn_reflns.reduction_process. See also _diffrn_reflns.transf_matrix[][]. ; _item.name '_diffrn_refln.index_h' _item.category_id diffrn_refln _item.mandatory_code yes _item_aliases.alias_name '_diffrn_refln_index_h' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_diffrn_refln.index_h' '_diffrn_refln.index_k' _item_sub_category.id miller_index _item_type.code int save_ save__diffrn_refln.index_k _item_description.description ; Miller index k of a reflection. The values of the Miller indices in the DIFFRN_REFLN category need not match the values of the Miller indices in the REFLN category if a transformation of the original measured cell has taken place. Details of the cell transformation are given in _diffrn_reflns.reduction_process. See also _diffrn_reflns.transf_matrix[][]. ; _item.name '_diffrn_refln.index_k' _item.category_id diffrn_refln _item.mandatory_code yes _item_aliases.alias_name '_diffrn_refln_index_k' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_diffrn_refln.index_h' '_diffrn_refln.index_l' _item_sub_category.id miller_index _item_type.code int save_ save__diffrn_refln.index_l _item_description.description ; Miller index l of a reflection. The values of the Miller indices in the DIFFRN_REFLN category need not match the values of the Miller indices in the REFLN category if a transformation of the original measured cell has taken place. Details of the cell transformation are given in _diffrn_reflns.reduction_process. See also _diffrn_reflns.transf_matrix[][]. ; _item.name '_diffrn_refln.index_l' _item.category_id diffrn_refln _item.mandatory_code yes _item_aliases.alias_name '_diffrn_refln_index_l' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_diffrn_refln.index_h' '_diffrn_refln.index_k' _item_sub_category.id miller_index _item_type.code int save_ save__diffrn_refln.intensity_net _item_description.description ; Net intensity calculated from the diffraction counts after the attenuator and standard scales have been applied. ; _item.name '_diffrn_refln.intensity_net' _item.category_id diffrn_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_refln_intensity_net' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code float save_ save__diffrn_refln.intensity_sigma _item_description.description ; Standard uncertainty (estimated standard deviation) of the intensity calculated from the diffraction counts after the attenuator and standard scales have been applied. ; _item.name '_diffrn_refln.intensity_sigma' _item.category_id diffrn_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_refln_intensity_sigma' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code float save_ save__diffrn_refln.scale_group_code _item_description.description ; The code identifying the scale applying to this reflection. This data item is a pointer to _diffrn_scale_group.code in the DIFFRN_SCALE_GROUP category. ; _item.name '_diffrn_refln.scale_group_code' _item.mandatory_code yes _item_aliases.alias_name '_diffrn_refln_scale_group_code' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 save_ save__diffrn_refln.scan_mode _item_description.description ; The code identifying the mode of scanning for measurements using a diffractometer. See _diffrn_refln.scan_width and _diffrn_refln.scan_mode_backgd. ; _item.name '_diffrn_refln.scan_mode' _item.category_id diffrn_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_refln_scan_mode' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail om 'omega scan' ot 'omega/2theta scan' q 'Q scans (arbitrary reciprocal directions)' save_ save__diffrn_refln.scan_mode_backgd _item_description.description ; The code identifying the mode of scanning a reflection to measure the background intensity. ; _item.name '_diffrn_refln.scan_mode_backgd' _item.category_id diffrn_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_refln_scan_mode_backgd' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail st 'stationary counter background' mo 'moving counter background' save_ save__diffrn_refln.scan_rate _item_description.description ; The rate of scanning a reflection in degrees per minute to measure the intensity. ; _item.name '_diffrn_refln.scan_rate' _item.category_id diffrn_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_refln_scan_rate' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code float _item_units.code degrees_per_minute save_ save__diffrn_refln.scan_time_backgd _item_description.description ; The time spent measuring each background in seconds. ; _item.name '_diffrn_refln.scan_time_backgd' _item.category_id diffrn_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_refln_scan_time_backgd' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code float _item_units.code seconds save_ save__diffrn_refln.scan_width _item_description.description ; The scan width in degrees of the scan mode defined by the code _diffrn_refln.scan_mode. ; _item.name '_diffrn_refln.scan_width' _item.category_id diffrn_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_refln_scan_width' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 0.0 0.0 0.0 _item_type.code float _item_units.code degrees save_ save__diffrn_refln.sint_over_lambda _item_description.description ; The (sin theta)/lambda value in reciprocal angstroms for this reflection. ; _item.name '_diffrn_refln.sint_over_lambda' _item.category_id diffrn_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_refln_sint/lambda' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code reciprocal_angstroms save_ save__diffrn_refln.standard_code _item_description.description ; The code identifying that this reflection was measured as a standard intensity. This data item is a pointer to _diffrn_standard_refln.code in the DIFFRN_STANDARD_REFLN category. ; _item.name '_diffrn_refln.standard_code' _item.mandatory_code yes _item_aliases.alias_name '_diffrn_refln_standard_code' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 save_ save__diffrn_refln.wavelength _item_description.description ; The mean wavelength in angstroms of the radiation used to measure the intensity of this reflection. This is an important parameter for data collected using energy-dispersive detectors or the Laue method. ; _item.name '_diffrn_refln.wavelength' _item.category_id diffrn_refln _item.mandatory_code no _item_aliases.alias_name '_diffrn_refln_wavelength' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__diffrn_refln.wavelength_id _item_description.description ; This data item is a pointer to _diffrn_radiation.wavelength_id in the DIFFRN_RADIATION category. ; _item.name '_diffrn_refln.wavelength_id' _item.mandatory_code yes _item_aliases.alias_name '_diffrn_refln_wavelength_id' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 save_ ################### ## DIFFRN_REFLNS ## ################### save_diffrn_reflns _category.description ; Data items in the DIFFRN_REFLNS category record details about the set of intensities measured in the diffraction experiment. The DIFFRN_REFLN data items refer to individual intensity measurements and must be included in looped lists. The DIFFRN_REFLNS data items specify the parameters that apply to all intensity measurements in a diffraction data set. ; _category.id diffrn_reflns _category.mandatory_code no _category_key.name '_diffrn_reflns.diffrn_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' # loop_ # _category_examples.detail # _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_reflns.av_R_equivalents _item_description.description ; The residual [sum|avdel(I)| / sum|av(I)|] for symmetry-equivalent reflections used to calculate the average intensity av(I). The avdel(I) term is the average absolute difference between av(I) and the individual symmetry-equivalent intensities. ; _item.name '_diffrn_reflns.av_R_equivalents' _item.category_id diffrn_reflns _item.mandatory_code no _item_aliases.alias_name '_diffrn_reflns_av_R_equivalents' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__diffrn_reflns.av_sigmaI_over_netI _item_description.description ; Measure [sum|sigma(I)|/sum|net(I)|] for all measured reflections. ; _item.name '_diffrn_reflns.av_sigmaI_over_netI' _item.category_id diffrn_reflns _item.mandatory_code no _item_aliases.alias_name '_diffrn_reflns_av_sigmaI/netI' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__diffrn_reflns.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_reflns.diffrn_id' _item.mandatory_code yes save_ save__diffrn_reflns.limit_h_max _item_description.description ; The maximum value of the Miller index h for the reflection data specified by _diffrn_refln.index_h. ; _item.name '_diffrn_reflns.limit_h_max' _item.category_id diffrn_reflns _item.mandatory_code no _item_aliases.alias_name '_diffrn_reflns_limit_h_max' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code int save_ save__diffrn_reflns.limit_h_min _item_description.description ; The minimum value of the Miller index h for the reflection data specified by _diffrn_refln.index_h. ; _item.name '_diffrn_reflns.limit_h_min' _item.category_id diffrn_reflns _item.mandatory_code no _item_aliases.alias_name '_diffrn_reflns_limit_h_min' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code int save_ save__diffrn_reflns.limit_k_max _item_description.description ; The maximum value of the Miller index k for the reflection data specified by _diffrn_refln.index_k. ; _item.name '_diffrn_reflns.limit_k_max' _item.category_id diffrn_reflns _item.mandatory_code no _item_aliases.alias_name '_diffrn_reflns_limit_k_max' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code int save_ save__diffrn_reflns.limit_k_min _item_description.description ; The minimum value of the Miller index k for the reflection data specified by _diffrn_refln.index_k. ; _item.name '_diffrn_reflns.limit_k_min' _item.category_id diffrn_reflns _item.mandatory_code no _item_aliases.alias_name '_diffrn_reflns_limit_k_min' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code int save_ save__diffrn_reflns.limit_l_max _item_description.description ; The maximum value of the Miller index l for the reflection data specified by _diffrn_refln.index_l. ; _item.name '_diffrn_reflns.limit_l_max' _item.category_id diffrn_reflns _item.mandatory_code no _item_aliases.alias_name '_diffrn_reflns_limit_l_max' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code int save_ save__diffrn_reflns.limit_l_min _item_description.description ; The minimum value of the Miller index l for the reflection data specified by _diffrn_refln.index_l. ; _item.name '_diffrn_reflns.limit_l_min' _item.category_id diffrn_reflns _item.mandatory_code no _item_aliases.alias_name '_diffrn_reflns_limit_l_min' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code int save_ save__diffrn_reflns.number _item_description.description ; The total number of measured intensities, excluding reflections that are classified as systematically absent. ; _item.name '_diffrn_reflns.number' _item.category_id diffrn_reflns _item.mandatory_code no _item_aliases.alias_name '_diffrn_reflns_number' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__diffrn_reflns.reduction_process _item_description.description ; A description of the process used to reduce the intensity data into structure-factor magnitudes. ; _item.name '_diffrn_reflns.reduction_process' _item.category_id diffrn_reflns _item.mandatory_code no _item_aliases.alias_name '_diffrn_reflns_reduction_process' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'data averaged using Fisher test' save_ save__diffrn_reflns.theta_max _item_description.description ; Maximum theta angle in degrees for the measured diffraction intensities. ; _item.name '_diffrn_reflns.theta_max' _item.category_id diffrn_reflns _item.mandatory_code no _item_aliases.alias_name '_diffrn_reflns_theta_max' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 0.0 0.0 0.0 _item_type.code float _item_units.code degrees save_ save__diffrn_reflns.theta_min _item_description.description ; Minimum theta angle in degrees for the measured diffraction intensities. ; _item.name '_diffrn_reflns.theta_min' _item.category_id diffrn_reflns _item.mandatory_code no _item_aliases.alias_name '_diffrn_reflns_theta_min' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 0.0 0.0 0.0 _item_type.code float _item_units.code degrees save_ save__diffrn_reflns.transf_matrix[1][1] _item_description.description ; The [1][1] element of the 3x3 matrix used to transform Miller indices in the DIFFRN_REFLN category into the Miller indices in the REFLN category. ; _item.name '_diffrn_reflns.transf_matrix[1][1]' _item.category_id diffrn_reflns _item.mandatory_code no _item_aliases.alias_name '_diffrn_reflns_transf_matrix_11' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__diffrn_reflns.transf_matrix[1][2] _item_description.description ; The [1][2] element of the 3x3 matrix used to transform Miller indices in the DIFFRN_REFLN category into the Miller indices in the REFLN category. ; _item.name '_diffrn_reflns.transf_matrix[1][2]' _item.category_id diffrn_reflns _item.mandatory_code no _item_aliases.alias_name '_diffrn_reflns_transf_matrix_12' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__diffrn_reflns.transf_matrix[1][3] _item_description.description ; The [1][3] element of the 3x3 matrix used to transform Miller indices in the DIFFRN_REFLN category into the Miller indices in the REFLN category. ; _item.name '_diffrn_reflns.transf_matrix[1][3]' _item.category_id diffrn_reflns _item.mandatory_code no _item_aliases.alias_name '_diffrn_reflns_transf_matrix_13' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__diffrn_reflns.transf_matrix[2][1] _item_description.description ; The [2][1] element of the 3x3 matrix used to transform Miller indices in the DIFFRN_REFLN category into the Miller indices in the REFLN category. ; _item.name '_diffrn_reflns.transf_matrix[2][1]' _item.category_id diffrn_reflns _item.mandatory_code no _item_aliases.alias_name '_diffrn_reflns_transf_matrix_21' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__diffrn_reflns.transf_matrix[2][2] _item_description.description ; The [2][2] element of the 3x3 matrix used to transform Miller indices in the DIFFRN_REFLN category into the Miller indices in the REFLN category. ; _item.name '_diffrn_reflns.transf_matrix[2][2]' _item.category_id diffrn_reflns _item.mandatory_code no _item_aliases.alias_name '_diffrn_reflns_transf_matrix_22' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__diffrn_reflns.transf_matrix[2][3] _item_description.description ; The [2][3] element of the 3x3 matrix used to transform Miller indices in the DIFFRN_REFLN category into the Miller indices in the REFLN category. ; _item.name '_diffrn_reflns.transf_matrix[2][3]' _item.category_id diffrn_reflns _item.mandatory_code no _item_aliases.alias_name '_diffrn_reflns_transf_matrix_23' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__diffrn_reflns.transf_matrix[3][1] _item_description.description ; The [3][1] element of the 3x3 matrix used to transform Miller indices in the DIFFRN_REFLN category into the Miller indices in the REFLN category. ; _item.name '_diffrn_reflns.transf_matrix[3][1]' _item.category_id diffrn_reflns _item.mandatory_code no _item_aliases.alias_name '_diffrn_reflns_transf_matrix_31' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__diffrn_reflns.transf_matrix[3][2] _item_description.description ; The [3][2] element of the 3x3 matrix used to transform Miller indices in the DIFFRN_REFLN category into the Miller indices in the REFLN category. ; _item.name '_diffrn_reflns.transf_matrix[3][2]' _item.category_id diffrn_reflns _item.mandatory_code no _item_aliases.alias_name '_diffrn_reflns_transf_matrix_32' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ save__diffrn_reflns.transf_matrix[3][3] _item_description.description ; The [3][3] element of the 3x3 matrix used to transform Miller indices in the DIFFRN_REFLN category into the Miller indices in the REFLN category. ; _item.name '_diffrn_reflns.transf_matrix[3][3]' _item.category_id diffrn_reflns _item.mandatory_code no _item_aliases.alias_name '_diffrn_reflns_transf_matrix_33' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_sub_category.id matrix _item_type.code float save_ ######################## ## DIFFRN_SCALE_GROUP ## ######################## save_diffrn_scale_group _category.description ; Data items in the DIFFRN_SCALE_GROUP category record details of the scaling factors applied to place all intensities in the reflection lists on a common scale. Scaling groups might, for example, correspond to each film in a multi-film data set or each crystal in a multi-crystal data set. ; _category.id diffrn_scale_group _category.mandatory_code no _category_key.name '_diffrn_scale_group.code' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on CAD-4 diffractometer data obtained for Yb(S-C5H4N)2(THF)4. ; ; _diffrn_scale_group.code A24 _diffrn_scale_group.I_net 1.021 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_scale_group.code _item_description.description ; The value of _diffrn_scale_group.code must uniquely identify a record in the DIFFRN_SCALE_GROUP list. Note that this item need not be a number; it can be any unique identifier. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_scale_group.code' diffrn_scale_group yes '_diffrn_refln.scale_group_code' diffrn_refln yes _item_aliases.alias_name '_diffrn_scale_group_code' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_refln.scale_group_code' '_diffrn_scale_group.code' _item_type.code code loop_ _item_examples.case '1' '2' 'c1' 'c2' save_ save__diffrn_scale_group.I_net _item_description.description ; The scale for a specific measurement group which is to be multiplied with the net intensity to place all intensities in the DIFFRN_REFLN or REFLN list on a common scale. ; _item.name '_diffrn_scale_group.I_net' _item.category_id diffrn_scale_group _item.mandatory_code no _item_aliases.alias_name '_diffrn_scale_group_I_net' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ ################### ## DIFFRN_SOURCE ## ################### save_diffrn_source _category.description ; Data items in the DIFFRN_SOURCE category record details of the source of radiation used in the diffraction experiment. ; _category.id diffrn_source _category.mandatory_code no _category_key.name '_diffrn_source.diffrn_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _diffrn_source.diffrn_id 's1' _diffrn_source.source 'rotating anode' _diffrn_source.type 'Rigaku RU-200' _diffrn_source.power 50 _diffrn_source.current 180 _diffrn_source.size '8mm x 0.4 mm broad-focus' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_source.current _item_description.description ; The current in milliamperes at which the radiation source was operated. ; _item.name '_diffrn_source.current' _item.category_id diffrn_source _item.mandatory_code no _item_aliases.alias_name '_diffrn_source_current' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code float _item_units.code milliamperes save_ save__diffrn_source.details _item_description.description ; A description of special aspects of the radiation source used. ; _item.name '_diffrn_source.details' _item.category_id diffrn_source _item.mandatory_code no _item_aliases.alias_name '_diffrn_source_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__diffrn_source.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_source.diffrn_id' _item.mandatory_code yes save_ save__diffrn_source.power _item_description.description ; The power in kilowatts at which the radiation source was operated. ; _item.name '_diffrn_source.power' _item.category_id diffrn_source _item.mandatory_code no _item_aliases.alias_name '_diffrn_source_power' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code float _item_units.code kilowatts save_ save__diffrn_source.size _item_description.description ; The dimensions of the source as viewed from the sample. ; _item.name '_diffrn_source.size' _item.category_id diffrn_source _item.mandatory_code no _item_aliases.alias_name '_diffrn_source_size' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '8mm x 0.4 mm fine-focus' 'broad focus' save_ save__diffrn_source.source _item_description.description ; The general class of the radiation source. ; _item.name '_diffrn_source.source' _item.category_id diffrn_source _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_source' cifdic.c91 1.0 '_diffrn_source' cif_core.dic 2.0 _item_type.code text loop_ _item_examples.case 'sealed X-ray tube' 'nuclear reactor' 'spallation source' 'electron microscope' 'rotating-anode X-ray tube' 'synchrotron' save_ save__diffrn_source.target _item_description.description ; The chemical element symbol for the X-ray target (usually the anode) used to generate X-rays. This can also be used for spallation sources. ; _item.name '_diffrn_source.target' _item.category_id diffrn_source _item.mandatory_code no _item_aliases.alias_name '_diffrn_source_target' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code code loop_ _item_enumeration.value H He Li Be B C N O F Ne Na Mg Al Si P S Cl Ar K Ca Sc Ti V Cr Mn Fe Co Ni Cu Zn Ga Ge As Se Br Kr Rb Sr Y Zr Nb Mo Tc Ru Rh Pd Ag Cd In Sn Sb Te I Xe Cs Ba La Ce Pr Nd Pm Sm Eu Gd Tb Dy Ho Er Tm Yb Lu Hf Ta W Re Os Ir Pt Au Hg Tl Pb Bi Po At Rn Fr Ra Ac Th Pa U Np Pu Am Cm Bk Cf Es Fm Md No Lr save_ save__diffrn_source.type _item_description.description ; The make, model or name of the source of radiation. ; _item.name '_diffrn_source.type' _item.category_id diffrn_source _item.mandatory_code no _item_aliases.alias_name '_diffrn_source_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'NSLS beamline X8C' 'Rigaku RU200' save_ save__diffrn_source.voltage _item_description.description ; The voltage in kilovolts at which the radiation source was operated. ; _item.name '_diffrn_source.voltage' _item.category_id diffrn_source _item.mandatory_code no _item_aliases.alias_name '_diffrn_source_voltage' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code float _item_units.code kilovolts save_ ########################### ## DIFFRN_STANDARD_REFLN ## ########################### save_diffrn_standard_refln _category.description ; Data items in the DIFFRN_STANDARD_REFLN category record details about the reflections treated as standards during the measurement of a set of diffraction intensities. Note that these are the individual standard reflections, not the results of the analysis of the standard reflections. ; _category.id diffrn_standard_refln _category.mandatory_code no loop_ _category_key.name '_diffrn_standard_refln.diffrn_id' '_diffrn_standard_refln.code' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; loop_ _diffrn_standard_refln.diffrn_id _diffrn_standard_refln.code _diffrn_standard_refln.index_h _diffrn_standard_refln.index_k _diffrn_standard_refln.index_l s1 1 3 2 4 s1 1 1 9 1 s1 1 3 0 10 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_standard_refln.code _item_description.description ; The code identifying a reflection measured as a standard reflection with the indices _diffrn_standard_refln.index_h, _diffrn_standard_refln.index_k and _diffrn_standard_refln.index_l. This is the same code as the _diffrn_refln.standard_code in the DIFFRN_REFLN list. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_standard_refln.code' diffrn_standard_refln yes '_diffrn_refln.standard_code' diffrn_refln yes _item_aliases.alias_name '_diffrn_standard_refln_code' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_refln.standard_code' '_diffrn_standard_refln.code' _item_type.code code loop_ _item_examples.case '1' '2' 'c1' 'c2' save_ save__diffrn_standard_refln.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_standard_refln.diffrn_id' _item.mandatory_code yes save_ save__diffrn_standard_refln.index_h _item_description.description ; Miller index h of a standard reflection used in the diffraction measurement process. ; _item.name '_diffrn_standard_refln.index_h' _item.category_id diffrn_standard_refln _item.mandatory_code yes _item_aliases.alias_name '_diffrn_standard_refln_index_h' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_diffrn_standard_refln.index_k' '_diffrn_standard_refln.index_l' _item_sub_category.id miller_index _item_type.code int save_ save__diffrn_standard_refln.index_k _item_description.description ; Miller index k of a standard reflection used in the diffraction measurement process. ; _item.name '_diffrn_standard_refln.index_k' _item.category_id diffrn_standard_refln _item.mandatory_code yes _item_aliases.alias_name '_diffrn_standard_refln_index_k' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_diffrn_standard_refln.index_h' '_diffrn_standard_refln.index_l' _item_sub_category.id miller_index _item_type.code int save_ save__diffrn_standard_refln.index_l _item_description.description ; Miller index l of a standard reflection used in the diffraction measurement process. ; _item.name '_diffrn_standard_refln.index_l' _item.category_id diffrn_standard_refln _item.mandatory_code yes _item_aliases.alias_name '_diffrn_standard_refln_index_l' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_diffrn_standard_refln.index_h' '_diffrn_standard_refln.index_k' _item_sub_category.id miller_index _item_type.code int save_ ###################### ## DIFFRN_STANDARDS ## ###################### save_diffrn_standards _category.description ; Data items in the DIFFRN_STANDARDS category record details about the set of standard reflections used to monitor intensity stability during the measurement of diffraction intensities. Note that these records describe properties common to the set of standard reflections, not the standard reflections themselves. ; _category.id diffrn_standards _category.mandatory_code no _category_key.name '_diffrn_standards.diffrn_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _diffrn_standards.diffrn_id 's1' _diffrn_standards.number 3 _diffrn_standards.interval_time 120 _diffrn_standards.decay_% 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_standards.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_standards.diffrn_id' _item.mandatory_code yes save_ save__diffrn_standards.decay_% _item_description.description ; The percentage decrease in the mean of the intensities for the set of standard reflections from the start of the measurement process to the end. This value usually affords a measure of the overall decay in crystal quality during the diffraction measurement process. Negative values are used in exceptional instances where the final intensities are greater than the initial ones. ; _item.name '_diffrn_standards.decay_%' _item.category_id diffrn_standards _item.mandatory_code no _item_aliases.alias_name '_diffrn_standards_decay_%' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 100.0 100.0 100.0 . _item_type.code float save_ save__diffrn_standards.interval_count _item_description.description ; The number of reflection intensities between the measurement of standard reflection intensities. ; _item.name '_diffrn_standards.interval_count' _item.category_id diffrn_standards _item.mandatory_code no _item_aliases.alias_name '_diffrn_standards_interval_count' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__diffrn_standards.interval_time _item_description.description ; The time in minutes between the measurement of standard reflection intensities. ; _item.name '_diffrn_standards.interval_time' _item.category_id diffrn_standards _item.mandatory_code no _item_aliases.alias_name '_diffrn_standards_interval_time' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code float _item_units.code minutes save_ save__diffrn_standards.number _item_description.description ; The number of unique standard reflections used during the measurement of the diffraction intensities. ; _item.name '_diffrn_standards.number' _item.category_id diffrn_standards _item.mandatory_code no _item_aliases.alias_name '_diffrn_standards_number' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__diffrn_standards.scale_sigma _item_description.description ; The standard uncertainty (estimated standard deviation) of the individual mean standard scales applied to the intensity data. ; _item.name '_diffrn_standards.scale_sigma' _item.category_id diffrn_standards _item.mandatory_code no _item_aliases.alias_name '_diffrn_standards_scale_sigma' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ ############ ## ENTITY ## ############ save_entity _category.description ; Data items in the ENTITY category record details (such as chemical composition, name and source) about the molecular entities that are present in the crystallographic structure. Items in the various ENTITY subcategories provide a full chemical description of these molecular entities. Entities are of three types: polymer, non-polymer and water. Note that the water category includes only water; ordered solvent such as sulfate ion or acetone would be described as individual non-polymer entities. The ENTITY category is specific to macromolecular CIF applications and replaces the function of the CHEMICAL category in the CIF core. It is important to remember that the ENTITY data are not the result of the crystallographic experiment; those results are represented by the ATOM_SITE data items. ENTITY data items describe the chemistry of the molecules under investigation and can most usefully be thought of as the ideal groups to which the structure is restrained or constrained during refinement. It is also important to remember that entities do not correspond directly to the enumeration of the contents of the asymmetric unit. Entities are described only once, even in those structures that contain multiple observations of an entity. The STRUCT_ASYM data items, which reference the entity list, describe and label the contents of the asymmetric unit. ; _category.id entity _category.mandatory_code no _category_key.name '_entity.id' loop_ _category_group.id 'inclusive_group' 'entity_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _entity.id _entity.type _entity.formula_weight _entity.details 1 polymer 10916 ; The enzymatically competent form of HIV protease is a dimer. This entity corresponds to one monomer of an active dimer. ; 2 non-polymer '762' . 3 water 18 . ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__entity.details _item_description.description ; A description of special aspects of the entity. ; _item.name '_entity.details' _item.category_id entity _item.mandatory_code no _item_type.code text save_ save__entity.formula_weight _item_description.description ; Formula mass in daltons of the entity. ; _item.name '_entity.formula_weight' _item.category_id entity _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1.0 1.0 1.0 _item_type.code float save_ save__entity.id _item_description.description ; The value of _entity.id must uniquely identify a record in the ENTITY list. Note that this item need not be a number; it can be any unique identifier. ; loop_ _item.name _item.category_id _item.mandatory_code '_entity.id' entity yes '_atom_site.label_entity_id' atom_site no '_entity_keywords.entity_id' entity_keywords yes '_entity_link.entity_id_1' entity_link yes '_entity_link.entity_id_2' entity_link yes '_entity_name_com.entity_id' entity_name_com yes '_entity_name_sys.entity_id' entity_name_sys yes '_entity_poly.entity_id' entity_poly yes '_entity_poly_seq.entity_id' entity_poly_seq yes '_entity_src_gen.entity_id' entity_src_gen yes '_entity_src_nat.entity_id' entity_src_nat yes '_struct_asym.entity_id' struct_asym yes '_struct_ref.entity_id' struct_ref yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_atom_site.label_entity_id' '_entity.id' '_entity_keywords.entity_id' '_entity.id' '_entity_link.entity_id_1' '_entity.id' '_entity_link.entity_id_2' '_entity.id' '_entity_name_com.entity_id' '_entity.id' '_entity_name_sys.entity_id' '_entity.id' '_entity_poly.entity_id' '_entity.id' '_entity_poly_seq.entity_id' '_entity_poly.entity_id' '_entity_src_gen.entity_id' '_entity.id' '_entity_src_nat.entity_id' '_entity.id' '_struct_asym.entity_id' '_entity.id' '_struct_ref.entity_id' '_entity.id' save_ save__entity.src_method _item_description.description ; The method by which the sample for the entity was produced. Entities isolated directly from natural sources (tissues, soil samples etc.) are expected to have further information in the ENTITY_SRC_NAT category. Entities isolated from genetically manipulated sources are expected to have further information in the ENTITY_SRC_GEN category. ; _item.name '_entity.src_method' _item.category_id entity _item.mandatory_code no _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail nat ; entity isolated from a natural source ; man ; entity isolated from a genetically manipulated source ; syn ; entity obtained synthetically ; save_ save__entity.type _item_description.description ; Defines the type of the entity. Polymer entities are expected to have corresponding ENTITY_POLY and associated entries. Non-polymer entities are expected to have corresponding CHEM_COMP and associated entries. Water entities are not expected to have corresponding entries in the ENTITY category. ; _item.name '_entity.type' _item.category_id entity _item.mandatory_code no _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail polymer 'entity is a polymer' non-polymer 'entity is not a polymer' water 'water in the solvent model' save_ ##################### ## ENTITY_KEYWORDS ## ##################### save_entity_keywords _category.description ; Data items in the ENTITY_KEYWORDS category specify keywords relevant to the molecular entities. Note that this list of keywords is separate from the list that is used for the STRUCT_BIOL data items and is intended to provide only the information that one would know about the molecular entity *if one did not know its structure*. Hence polypeptides are simply polypeptides, not cytokines or beta-alpha-barrels, and polyribonucleic acids are simply poly-RNA, not transfer- RNA. ; _category.id entity_keywords _category.mandatory_code no _category_key.name '_entity_keywords.entity_id' loop_ _category_group.id 'inclusive_group' 'entity_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _entity_keywords.entity_id _entity_keywords.text 2 'natural product, inhibitor, reduced peptide' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__entity_keywords.entity_id _item_description.description ; This data item is a pointer to _entity.id in the ENTITY category. ; _item.name '_entity_keywords.entity_id' _item.mandatory_code yes save_ save__entity_keywords.text _item_description.description ; Keywords describing this entity. ; _item.name '_entity_keywords.text' _item.category_id entity_keywords _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'polypeptide' 'natural product' 'polysaccharide' save_ ################# ## ENTITY_LINK ## ################# save_entity_link _category.description ; Data items in the ENTITY_LINK category give details about the links between entities. ; _category.id entity_link _category.mandatory_code no _category_key.name '_entity_link.link_id' loop_ _category_group.id 'inclusive_group' 'chem_link_group' save_ save__entity_link.link_id _item_description.description ; This data item is a pointer to _chem_link.id in the CHEM_LINK category. ; _item.name '_entity_link.link_id' _item.mandatory_code yes save_ save__entity_link.details _item_description.description ; A description of special aspects of a link between chemical components in the structure. ; _item.name '_entity_link.details' _item.category_id entity_link _item.mandatory_code no _item_type.code text save_ save__entity_link.entity_id_1 _item_description.description ; The entity ID of the first of the two entities joined by the link. This data item is a pointer to _entity.id in the ENTITY category. ; _item.name '_entity_link.entity_id_1' _item.mandatory_code yes save_ save__entity_link.entity_id_2 _item_description.description ; The entity ID of the second of the two entities joined by the link. This data item is a pointer to _entity.id in the ENTITY category. ; _item.name '_entity_link.entity_id_2' _item.mandatory_code yes save_ save__entity_link.entity_seq_num_1 _item_description.description ; For a polymer entity, the sequence number in the first of the two entities containing the link. This data item is a pointer to _entity_poly_seq.num in the ENTITY_POLY_SEQ category. ; _item.name '_entity_link.entity_seq_num_1' _item.mandatory_code no save_ save__entity_link.entity_seq_num_2 _item_description.description ; For a polymer entity, the sequence number in the second of the two entities containing the link. This data item is a pointer to _entity_poly_seq.num in the ENTITY_POLY_SEQ category. ; _item.name '_entity_link.entity_seq_num_2' _item.mandatory_code no save_ ##################### ## ENTITY_NAME_COM ## ##################### save_entity_name_com _category.description ; Data items in the ENTITY_NAME_COM category record the common name or names associated with the entity. In some cases, the entity name may not be the same as the name of the biological structure. For example, haemoglobin alpha chain would be the entity common name, not haemoglobin. ; _category.id entity_name_com _category.mandatory_code no loop_ _category_key.name '_entity_name_com.entity_id' '_entity_name_com.name' loop_ _category_group.id 'inclusive_group' 'entity_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _entity_name_com.entity_id _entity_name_com.name 1 'HIV-1 protease monomer' 1 'HIV-1 PR monomer' 2 'acetyl-pepstatin' 2 'acetyl-Ile-Val-Asp-Statine-Ala-Ile-Statine' 3 'water' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__entity_name_com.entity_id _item_description.description ; This data item is a pointer to _entity.id in the ENTITY category. ; _item.name '_entity_name_com.entity_id' _item.mandatory_code yes save_ save__entity_name_com.name _item_description.description ; A common name for the entity. ; _item.name '_entity_name_com.name' _item.category_id entity_name_com _item.mandatory_code yes _item_type.code text loop_ _item_examples.case 'HIV protease monomer' 'hemoglobin alpha chain' '2-fluoro-1,4-dichloro benzene' 'arbutin' save_ ##################### ## ENTITY_NAME_SYS ## ##################### save_entity_name_sys _category.description ; Data items in the ENTITY_NAME_SYS category record the systematic name or names associated with the entity and the system that was used to construct the systematic name. In some cases, the entity name may not be the same as the name of the biological structure. ; _category.id entity_name_sys _category.mandatory_code no loop_ _category_key.name '_entity_name_sys.entity_id' '_entity_name_sys.name' loop_ _category_group.id 'inclusive_group' 'entity_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _entity_name_sys.entity_id _entity_name_sys.name 1 'EC 3.4.23.16' 2 'acetyl-Ile-Val-Asp-Sta-Ala-Ile-Sta' 3 water ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__entity_name_sys.entity_id _item_description.description ; This data item is a pointer to _entity.id in the ENTITY category. ; _item.name '_entity_name_sys.entity_id' _item.mandatory_code yes save_ save__entity_name_sys.name _item_description.description ; The systematic name for the entity. ; _item.name '_entity_name_sys.name' _item.category_id entity_name_sys _item.mandatory_code yes _item_type.code text loop_ _item_examples.case 'hydroquinone-beta-D-pyranoside' 'EC 2.1.1.1' '2-fluoro-1,4-dichlorobenzene' save_ save__entity_name_sys.system _item_description.description ; The system used to generate the systematic name of the entity. ; _item.name '_entity_name_sys.system' _item.category_id entity_name_sys _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'Chemical Abstracts conventions' 'enzyme convention' 'Sigma catalog' save_ ################# ## ENTITY_POLY ## ################# save_entity_poly _category.description ; Data items in the ENTITY_POLY category record details about the polymer, such as the type of the polymer, the number of monomers and whether it has nonstandard features. ; _category.id entity_poly _category.mandatory_code no _category_key.name '_entity_poly.entity_id' loop_ _category_group.id 'inclusive_group' 'entity_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _entity_poly.entity_id _entity_poly.type _entity_poly.nstd_chirality _entity_poly.nstd_linkage _entity_poly.nstd_monomer _entity_poly.type_details 1 polypeptide(L) no no no . ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__entity_poly.entity_id _item_description.description ; This data item is a pointer to _entity.id in the ENTITY category. ; _item.name '_entity_poly.entity_id' _item.mandatory_code yes save_ save__entity_poly.nstd_chirality _item_description.description ; A flag to indicate whether the polymer contains at least one monomer unit with chirality different from that specified in _entity_poly.type. ; _item.name '_entity_poly.nstd_chirality' _item.category_id entity_poly _item.mandatory_code no _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail no ; polymer contains no monomers with different chirality ; n ; abbreviation for "no" ; yes ; polymer contains at least one monomer with different chirality ; y ; abbreviation for "yes" ; save_ save__entity_poly.nstd_linkage _item_description.description ; A flag to indicate whether the polymer contains at least one monomer-to-monomer link different from that implied by _entity_poly.type. ; _item.name '_entity_poly.nstd_linkage' _item.category_id entity_poly _item.mandatory_code no _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail no 'polymer contains no different links' n 'abbreviation for "no"' yes ; polymer contains at least one different link ; y 'abbreviation for "yes"' save_ save__entity_poly.nstd_monomer _item_description.description ; A flag to indicate whether the polymer contains at least one monomer that is not considered standard. ; _item.name '_entity_poly.nstd_monomer' _item.category_id entity_poly _item.mandatory_code no _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail no 'polymer contains no nonstandard monomers' n 'abbreviation for "no"' yes ; polymer contains at least one nonstandard monomer ; y 'abbreviation for "yes"' save_ save__entity_poly.number_of_monomers _item_description.description ; The number of monomers in the polymer. ; _item.name '_entity_poly.number_of_monomers' _item.category_id entity_poly _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__entity_poly.type _item_description.description ; The type of the polymer. ; _item.name '_entity_poly.type' _item.category_id entity_poly _item.mandatory_code no _item_type.code ucode loop_ _item_enumeration.value 'polypeptide(D)' 'polypeptide(L)' 'polydeoxyribonucleotide' 'polyribonucleotide' 'polysaccharide(D)' 'polysaccharide(L)' 'other' save_ save__entity_poly.type_details _item_description.description ; A description of special aspects of the polymer type. ; _item.name '_entity_poly.type_details' _item.category_id entity_poly _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'monomer Ala 16 is a D-amino acid' 'the oligomer contains alternating RNA and DNA units' save_ ##################### ## ENTITY_POLY_SEQ ## ##################### save_entity_poly_seq _category.description ; Data items in the ENTITY_POLY_SEQ category specify the sequence of monomers in a polymer. Allowance is made for the possibility of microheterogeneity in a sample by allowing a given sequence number to be correlated with more than one monomer ID. The corresponding ATOM_SITE entries should reflect this heterogeneity. ; _category.id entity_poly_seq _category.mandatory_code no loop_ _category_key.name '_entity_poly_seq.entity_id' '_entity_poly_seq.num' '_entity_poly_seq.mon_id' loop_ _category_group.id 'inclusive_group' 'entity_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _entity_poly_seq.entity_id _entity_poly_seq.num _entity_poly_seq.mon_id 1 1 PRO 1 2 GLN 1 3 ILE 1 4 THR 1 5 LEU 1 6 TRP 1 7 GLN 1 8 ARG 1 9 PRO 1 10 LEU 1 11 VAL 1 12 THR 1 13 ILE 1 14 LYS 1 15 ILE 1 16 GLY 1 17 GLY 1 18 GLN 1 19 LEU 1 20 LYS 1 21 GLU 1 22 ALA 1 23 LEU 1 24 LEU 1 25 ASP # - - - - data truncated for brevity - - - - ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__entity_poly_seq.entity_id _item_description.description ; This data item is a pointer to _entity.id in the ENTITY category. ; _item.name '_entity_poly_seq.entity_id' _item.mandatory_code yes save_ save__entity_poly_seq.hetero _item_description.description ; A flag to indicate whether this monomer in the polymer is heterogeneous in sequence. This would be rare. ; _item.name '_entity_poly_seq.hetero' _item.category_id entity_poly_seq _item.mandatory_code no _item_default.value no _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail no 'sequence is not heterogeneous at this monomer' n 'abbreviation for "no"' yes 'sequence is heterogeneous at this monomer' y 'abbreviation for "yes"' save_ save__entity_poly_seq.mon_id _item_description.description ; This data item is a pointer to _chem_comp.id in the CHEM_COMP category. ; _item.name '_entity_poly_seq.mon_id' _item.mandatory_code yes save_ save__entity_poly_seq.num _item_description.description ; The value of _entity_poly_seq.num must uniquely and sequentially identify a record in the ENTITY_POLY_SEQ list. Note that this item must be a number and that the sequence numbers must progress in increasing numerical order. ; loop_ _item.name _item.category_id _item.mandatory_code '_entity_poly_seq.num' entity_poly_seq yes '_atom_site.label_seq_id' atom_site no '_entity_link.entity_seq_num_1' entity_link no '_entity_link.entity_seq_num_2' entity_link no '_geom_angle.atom_site_label_seq_id_1' geom_angle no '_geom_angle.atom_site_label_seq_id_2' geom_angle no '_geom_angle.atom_site_label_seq_id_3' geom_angle no '_geom_bond.atom_site_label_seq_id_1' geom_bond no '_geom_bond.atom_site_label_seq_id_2' geom_bond no '_geom_contact.atom_site_label_seq_id_1' geom_contact no '_geom_contact.atom_site_label_seq_id_2' geom_contact no '_geom_hbond.atom_site_label_seq_id_A' geom_hbond no '_geom_hbond.atom_site_label_seq_id_D' geom_hbond no '_geom_hbond.atom_site_label_seq_id_H' geom_hbond no '_geom_torsion.atom_site_label_seq_id_1' geom_torsion no '_geom_torsion.atom_site_label_seq_id_2' geom_torsion no '_geom_torsion.atom_site_label_seq_id_3' geom_torsion no '_geom_torsion.atom_site_label_seq_id_4' geom_torsion no '_struct_conf.beg_label_seq_id' struct_conf yes '_struct_conf.end_label_seq_id' struct_conf yes '_struct_conn.ptnr1_label_seq_id' struct_conn yes '_struct_conn.ptnr2_label_seq_id' struct_conn yes '_struct_mon_nucl.label_seq_id' struct_mon_nucl yes '_struct_mon_prot.label_seq_id' struct_mon_prot yes '_struct_mon_prot_cis.label_seq_id' struct_mon_prot_cis yes '_struct_ncs_dom_lim.beg_label_seq_id' struct_ncs_dom_lim yes '_struct_ncs_dom_lim.end_label_seq_id' struct_ncs_dom_lim yes '_struct_ref_seq.seq_align_beg' struct_ref_seq yes '_struct_ref_seq.seq_align_end' struct_ref_seq yes '_struct_ref_seq_dif.seq_num' struct_ref_seq_dif yes '_struct_sheet_hbond.range_1_beg_label_seq_id' struct_sheet_hbond yes '_struct_sheet_hbond.range_1_end_label_seq_id' struct_sheet_hbond yes '_struct_sheet_hbond.range_2_beg_label_seq_id' struct_sheet_hbond yes '_struct_sheet_hbond.range_2_end_label_seq_id' struct_sheet_hbond yes '_struct_sheet_range.beg_label_seq_id' struct_sheet_range yes '_struct_sheet_range.end_label_seq_id' struct_sheet_range yes '_struct_site_gen.label_seq_id' struct_site_gen yes loop_ _item_linked.child_name _item_linked.parent_name '_atom_site.label_seq_id' '_entity_poly_seq.num' '_entity_link.entity_seq_num_1' '_entity_poly_seq.num' '_entity_link.entity_seq_num_2' '_entity_poly_seq.num' '_geom_angle.atom_site_label_seq_id_1' '_atom_site.label_seq_id' '_geom_angle.atom_site_label_seq_id_2' '_atom_site.label_seq_id' '_geom_angle.atom_site_label_seq_id_3' '_atom_site.label_seq_id' '_geom_bond.atom_site_label_seq_id_1' '_atom_site.label_seq_id' '_geom_bond.atom_site_label_seq_id_2' '_atom_site.label_seq_id' '_geom_contact.atom_site_label_seq_id_1' '_atom_site.label_seq_id' '_geom_contact.atom_site_label_seq_id_2' '_atom_site.label_seq_id' '_geom_hbond.atom_site_label_seq_id_A' '_atom_site.label_seq_id' '_geom_hbond.atom_site_label_seq_id_D' '_atom_site.label_seq_id' '_geom_hbond.atom_site_label_seq_id_H' '_atom_site.label_seq_id' '_geom_torsion.atom_site_label_seq_id_1' '_atom_site.label_seq_id' '_geom_torsion.atom_site_label_seq_id_2' '_atom_site.label_seq_id' '_geom_torsion.atom_site_label_seq_id_3' '_atom_site.label_seq_id' '_geom_torsion.atom_site_label_seq_id_4' '_atom_site.label_seq_id' '_struct_conf.beg_label_seq_id' '_atom_site.label_seq_id' '_struct_conf.end_label_seq_id' '_atom_site.label_seq_id' '_struct_conn.ptnr1_label_seq_id' '_atom_site.label_seq_id' '_struct_conn.ptnr2_label_seq_id' '_atom_site.label_seq_id' '_struct_mon_nucl.label_seq_id' '_atom_site.label_seq_id' '_struct_mon_prot.label_seq_id' '_atom_site.label_seq_id' '_struct_mon_prot_cis.label_seq_id' '_atom_site.label_seq_id' '_struct_ncs_dom_lim.beg_label_seq_id' '_atom_site.label_seq_id' '_struct_ncs_dom_lim.end_label_seq_id' '_atom_site.label_seq_id' '_struct_ref_seq.seq_align_beg' '_entity_poly_seq.num' '_struct_ref_seq.seq_align_end' '_entity_poly_seq.num' '_struct_ref_seq_dif.seq_num' '_entity_poly_seq.num' '_struct_sheet_hbond.range_1_beg_label_seq_id' '_atom_site.label_seq_id' '_struct_sheet_hbond.range_1_end_label_seq_id' '_atom_site.label_seq_id' '_struct_sheet_hbond.range_2_beg_label_seq_id' '_atom_site.label_seq_id' '_struct_sheet_hbond.range_2_end_label_seq_id' '_atom_site.label_seq_id' '_struct_sheet_range.beg_label_seq_id' '_atom_site.label_seq_id' '_struct_sheet_range.end_label_seq_id' '_atom_site.label_seq_id' '_struct_site_gen.label_seq_id' '_atom_site.label_seq_id' loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ #################### ## ENTITY_SRC_GEN ## #################### save_entity_src_gen _category.description ; Data items in the ENTITY_SRC_GEN category record details of the source from which the entity was obtained in cases where the source was genetically manipulated. The following are treated separately: items pertaining to the tissue from which the gene was obtained, items pertaining to the host organism for gene expression and items pertaining to the actual producing organism (plasmid). ; _category.id entity_src_gen _category.mandatory_code no _category_key.name '_entity_src_gen.entity_id' loop_ _category_group.id 'inclusive_group' 'entity_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _entity_src_gen.entity_id _entity_src_gen.gene_src_common_name _entity_src_gen.gene_src_genus _entity_src_gen.gene_src_species _entity_src_gen.gene_src_strain _entity_src_gen.host_org_common_name _entity_src_gen.host_org_genus _entity_src_gen.host_org_species _entity_src_gen.plasmid_name 1 'HIV-1' '?' '?' 'NY-5' 'bacteria' 'Escherichia' 'coli' 'pB322' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__entity_src_gen.entity_id _item_description.description ; This data item is a pointer to _entity.id in the ENTITY category. ; _item.name '_entity_src_gen.entity_id' _item.mandatory_code yes save_ save__entity_src_gen.gene_src_common_name _item_description.description ; The common name of the natural organism from which the gene was obtained. ; _item.name '_entity_src_gen.gene_src_common_name' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'man' 'yeast' 'bacteria' save_ save__entity_src_gen.gene_src_details _item_description.description ; A description of special aspects of the natural organism from which the gene was obtained. ; _item.name '_entity_src_gen.gene_src_details' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text save_ save__entity_src_gen.gene_src_genus _item_description.description ; The genus of the natural organism from which the gene was obtained. ; _item.name '_entity_src_gen.gene_src_genus' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'Homo' 'Saccharomyces' 'Escherichia' save_ save__entity_src_gen.gene_src_species _item_description.description ; The species of the natural organism from which the gene was obtained. ; _item.name '_entity_src_gen.gene_src_species' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'sapiens' 'cerevisiae' 'coli' save_ save__entity_src_gen.gene_src_strain _item_description.description ; The strain of the natural organism from which the gene was obtained, if relevant. ; _item.name '_entity_src_gen.gene_src_strain' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'DH5a' 'BMH 71-18' save_ save__entity_src_gen.gene_src_tissue _item_description.description ; The tissue of the natural organism from which the gene was obtained. ; _item.name '_entity_src_gen.gene_src_tissue' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'heart' 'liver' 'eye lens' save_ save__entity_src_gen.gene_src_tissue_fraction _item_description.description ; The subcellular fraction of the tissue of the natural organism from which the gene was obtained. ; _item.name '_entity_src_gen.gene_src_tissue_fraction' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'mitochondria' 'nucleus' 'membrane' save_ save__entity_src_gen.host_org_common_name _item_description.description ; The common name of the organism that served as host for the production of the entity. ; _item.name '_entity_src_gen.host_org_common_name' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'yeast' 'bacteria' save_ save__entity_src_gen.host_org_details _item_description.description ; A description of special aspects of the organism that served as host for the production of the entity. ; _item.name '_entity_src_gen.host_org_details' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text save_ save__entity_src_gen.host_org_genus _item_description.description ; The genus of the organism that served as host for the production of the entity. ; _item.name '_entity_src_gen.host_org_genus' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'Saccharomyces' 'Escherichia' save_ save__entity_src_gen.host_org_species _item_description.description ; The species of the organism that served as host for the production of the entity. ; _item.name '_entity_src_gen.host_org_species' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'cerevisiae' 'coli' save_ save__entity_src_gen.host_org_strain _item_description.description ; The strain of the organism that served as host for the production of the entity. ; _item.name '_entity_src_gen.host_org_strain' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'DH5a' 'BMH 71-18' save_ save__entity_src_gen.plasmid_details _item_description.description ; A description of special aspects of the plasmid that produced the entity in the host organism. ; _item.name '_entity_src_gen.plasmid_details' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text save_ save__entity_src_gen.plasmid_name _item_description.description ; The name of the plasmid that produced the entity in the host organism. ; _item.name '_entity_src_gen.plasmid_name' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'pET3C' 'pT123sab' save_ #################### ## ENTITY_SRC_NAT ## #################### save_entity_src_nat _category.description ; Data items in the ENTITY_SRC_NAT category record details of the source from which the entity was obtained in cases where the entity was isolated directly from a natural tissue. ; _category.id entity_src_nat _category.mandatory_code no _category_key.name '_entity_src_nat.entity_id' loop_ _category_group.id 'inclusive_group' 'entity_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _entity_src_nat.entity_id _entity_src_nat.common_name _entity_src_nat.genus _entity_src_nat.species _entity_src_nat.details 2 'bacteria' 'Actinomycetes' '?' ; Acetyl-pepstatin was isolated by Dr. K. Oda, Osaka Prefecture University, and provided to us by Dr. Ben Dunn, University of Florida, and Dr. J. Kay, University of Wales. ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__entity_src_nat.common_name _item_description.description ; The common name of the organism from which the entity was isolated. ; _item.name '_entity_src_nat.common_name' _item.category_id entity_src_nat _item.mandatory_code yes _item_type.code text loop_ _item_examples.case 'man' 'yeast' 'bacteria' save_ save__entity_src_nat.details _item_description.description ; A description of special aspects of the organism from which the entity was isolated. ; _item.name '_entity_src_nat.details' _item.category_id entity_src_nat _item.mandatory_code no _item_type.code text save_ save__entity_src_nat.entity_id _item_description.description ; This data item is a pointer to _entity.id in the ENTITY category. ; _item.name '_entity_src_nat.entity_id' _item.mandatory_code yes save_ save__entity_src_nat.genus _item_description.description ; The genus of the organism from which the entity was isolated. ; _item.name '_entity_src_nat.genus' _item.category_id entity_src_nat _item.mandatory_code yes _item_type.code text loop_ _item_examples.case 'Homo' 'Saccharomyces' 'Escherichia' save_ save__entity_src_nat.species _item_description.description ; The species of the organism from which the entity was isolated. ; _item.name '_entity_src_nat.species' _item.category_id entity_src_nat _item.mandatory_code yes _item_type.code text loop_ _item_examples.case 'sapiens' 'cerevisiae' 'coli' save_ save__entity_src_nat.strain _item_description.description ; The strain of the organism from which the entity was isolated. ; _item.name '_entity_src_nat.strain' _item.category_id entity_src_nat _item.mandatory_code yes _item_type.code text loop_ _item_examples.case 'DH5a' 'BMH 71-18' save_ save__entity_src_nat.tissue _item_description.description ; The tissue of the organism from which the entity was isolated. ; _item.name '_entity_src_nat.tissue' _item.category_id entity_src_nat _item.mandatory_code yes _item_type.code text loop_ _item_examples.case 'heart' 'liver' 'eye lens' save_ save__entity_src_nat.tissue_fraction _item_description.description ; The subcellular fraction of the tissue of the organism from which the entity was isolated. ; _item.name '_entity_src_nat.tissue_fraction' _item.category_id entity_src_nat _item.mandatory_code yes _item_type.code text loop_ _item_examples.case 'mitochondria' 'nucleus' 'membrane' save_ ########### ## ENTRY ## ########### save_entry _category.description ; There is only one item in the ENTRY category, _entry.id. This data item gives a name to this entry and is indirectly a key to the categories (such as CELL, GEOM, EXPTL) that describe information pertinent to the entire data block. ; _category.id entry _category.mandatory_code no _category_key.name '_entry.id' loop_ _category_group.id 'inclusive_group' 'entry_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _entry.id '5HVP' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _entry.id 'TOZ' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__entry.id _item_description.description ; The value of _entry.id identifies the data block. Note that this item need not be a number; it can be any unique identifier. ; loop_ _item.name _item.category_id _item.mandatory_code '_entry.id' entry yes '_atom_sites.entry_id' atom_sites yes '_cell.entry_id' cell yes '_cell_measurement.entry_id' cell_measurement yes '_chemical.entry_id' chemical yes '_chemical_formula.entry_id' chemical_formula yes '_computing.entry_id' computing yes '_database.entry_id' database yes '_database_PDB_matrix.entry_id' database_PDB_matrix yes '_entry_link.entry_id' entry_link yes '_exptl.entry_id' exptl yes '_geom.entry_id' geom yes '_journal.entry_id' journal yes '_phasing_averaging.entry_id' phasing_averaging yes '_phasing_isomorphous.entry_id' phasing_isomorphous yes '_phasing_MAD.entry_id' phasing_MAD yes '_phasing_MIR.entry_id' phasing_MIR yes '_publ.entry_id' publ yes '_publ_manuscript_incl.entry_id' publ_manuscript_incl yes '_refine.entry_id' refine yes '_refine_analyze.entry_id' refine_analyze yes '_reflns.entry_id' reflns yes '_struct.entry_id' struct yes '_struct_keywords.entry_id' struct_keywords yes '_struct_mon_details.entry_id' struct_mon_details yes '_symmetry.entry_id' symmetry yes _item_aliases.alias_name '_audit_block_code' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_linked.child_name _item_linked.parent_name '_atom_sites.entry_id' '_entry.id' '_cell.entry_id' '_entry.id' '_cell_measurement.entry_id' '_entry.id' '_chemical.entry_id' '_entry.id' '_chemical_formula.entry_id' '_entry.id' '_computing.entry_id' '_entry.id' '_database.entry_id' '_entry.id' '_database_PDB_matrix.entry_id' '_entry.id' '_entry_link.entry_id' '_entry.id' '_exptl.entry_id' '_entry.id' '_geom.entry_id' '_entry.id' '_journal.entry_id' '_entry.id' '_phasing_averaging.entry_id' '_entry.id' '_phasing_isomorphous.entry_id' '_entry.id' '_phasing_MAD.entry_id' '_entry.id' '_phasing_MIR.entry_id' '_entry.id' '_publ.entry_id' '_entry.id' '_publ_manuscript_incl.entry_id' '_entry.id' '_refine.entry_id' '_entry.id' '_refine_analyze.entry_id' '_entry.id' '_reflns.entry_id' '_entry.id' '_struct.entry_id' '_entry.id' '_struct_keywords.entry_id' '_entry.id' '_struct_mon_details.entry_id' '_entry.id' '_symmetry.entry_id' '_entry.id' _item_type.code code save_ save_entry_link _category.description ; Data items in the ENTRY_LINK category record the relationships between the current data block identified by _entry.id and other data blocks within the current file which may be referenced in the current data block. ; _category.id entry_link _category.mandatory_code no loop_ _category_key.name '_entry_link.id' '_entry_link.entry_id' loop_ _category_group.id 'inclusive_group' 'entry_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - example file for the one-dimensional incommensurately modulated structure of K~2~SeO~4~. ; ; loop_ _entry_link.id _entry_link.entry_id _entry_link.details KSE_COM KSE_TEXT 'experimental data common to ref./mod. structures' KSE_REF KSE_TEXT 'reference structure' KSE_MOD KSE_TEXT 'modulated structure' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__entry_link.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_entry_link.entry_id' _item.mandatory_code yes save_ save__entry_link.id _item_description.description ; The value of _entry_link.id identifies a data block related to the current data block. ; _item.name '_entry_link.id' _item.category_id entry_link _item.mandatory_code yes _item_aliases.alias_name '_audit_link_block_code' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code code save_ save__entry_link.details _item_description.description ; A description of the relationship between the data blocks identified by _entry_link.id and _entry_link.entry_id. ; _item.name '_entry_link.details' _item.category_id entry_link _item.mandatory_code no _item_aliases.alias_name '_audit_link_block_description' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ ########### ## EXPTL ## ########### save_exptl _category.description ; Data items in the EXPTL category record details about the experimental work prior to the intensity measurements and details about the absorption-correction technique employed. ; _category.id exptl _category.mandatory_code no _category_key.name '_exptl.entry_id' loop_ _category_group.id 'inclusive_group' 'exptl_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on laboratory records for Yb(S-C5H4N)2(THF)4. ; ; _exptl.entry_id datablock1 _exptl.absorpt_coefficient_mu 1.22 _exptl.absorpt_correction_T_max 0.896 _exptl.absorpt_correction_T_min 0.802 _exptl.absorpt_correction_type integration _exptl.absorpt_process_details ; Gaussian grid method from SHELX76 Sheldrick, G. M., "SHELX-76: structure determination and refinement program", Cambridge University, UK, 1976 ; _exptl.crystals_number 1 _exptl.details ; Enraf-Nonius LT2 liquid nitrogen variable-temperature device used ; _exptl.method 'single-crystal x-ray diffraction' _exptl.method_details ; graphite monochromatized Cu K(alpha) fixed tube and Enraf-Nonius CAD4 diffractometer used ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__exptl.absorpt_coefficient_mu _item_description.description ; The absorption coefficient mu in reciprocal millimetres calculated from the atomic content of the cell, the density and the radiation wavelength. ; _item.name '_exptl.absorpt_coefficient_mu' _item.category_id exptl _item.mandatory_code no _item_aliases.alias_name '_exptl_absorpt_coefficient_mu' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code reciprocal_millimetres save_ save__exptl.absorpt_correction_T_max _item_description.description ; The maximum transmission factor for the crystal and radiation. The maximum and minimum transmission factors are also referred to as the absorption correction A or 1/A*. ; _item.name '_exptl.absorpt_correction_T_max' _item.category_id exptl _item.mandatory_code no _item_aliases.alias_name '_exptl_absorpt_correction_T_max' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 0.0 0.0 0.0 _item_type.code float save_ save__exptl.absorpt_correction_T_min _item_description.description ; The minimum transmission factor for the crystal and radiation. The maximum and minimum transmission factors are also referred to as the absorption correction A or 1/A*. ; _item.name '_exptl.absorpt_correction_T_min' _item.category_id exptl _item.mandatory_code no _item_aliases.alias_name '_exptl_absorpt_correction_T_min' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 0.0 0.0 0.0 _item_type.code float save_ save__exptl.absorpt_correction_type _item_description.description ; The absorption correction type and method. The value 'empirical' should NOT be used unless more detailed information is not available. ; _item.name '_exptl.absorpt_correction_type' _item.category_id exptl _item.mandatory_code no _item_aliases.alias_name '_exptl_absorpt_correction_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail analytical 'analytical from crystal shape' cylinder 'cylindrical' empirical 'empirical from intensities' gaussian 'Gaussian from crystal shape' integration 'integration from crystal shape' multi-scan 'symmetry-related measurements' none 'no correction applied' numerical 'numerical from crystal shape' psi-scan 'psi-scan corrections' refdelf 'refined from delta-F' sphere 'spherical' save_ save__exptl.absorpt_process_details _item_description.description ; Description of the absorption process applied to the intensities. A literature reference should be supplied for psi-scan techniques. ; _item.name '_exptl.absorpt_process_details' _item.category_id exptl _item.mandatory_code no _item_aliases.alias_name '_exptl_absorpt_process_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'Tompa analytical' save_ save__exptl.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_exptl.entry_id' _item.mandatory_code yes save_ save__exptl.crystals_number _item_description.description ; The total number of crystals used in the measurement of intensities. ; _item.name '_exptl.crystals_number' _item.category_id exptl _item.mandatory_code no _item_aliases.alias_name '_exptl_crystals_number' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__exptl.details _item_description.description ; Any special information about the experimental work prior to the intensity measurement. See also _exptl_crystal.preparation. ; _item.name '_exptl.details' _item.category_id exptl _item.mandatory_code no _item_aliases.alias_name '_exptl_special_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__exptl.method _item_description.description ; The method used in the experiment. ; _item.name '_exptl.method' _item.category_id exptl _item.mandatory_code yes _item_type.code line loop_ _item_examples.case 'single-crystal x-ray diffraction' 'single-crystal neutron diffraction' 'single-crystal electron diffraction' 'fiber x-ray diffraction' 'fiber neutron diffraction' 'fiber electron diffraction' 'single-crystal joint x-ray and neutron diffraction' 'single-crystal joint x-ray and electron diffraction' 'solution nmr' 'solid-state nmr' 'theoretical model' 'other' save_ save__exptl.method_details _item_description.description ; A description of special aspects of the experimental method. ; _item.name '_exptl.method_details' _item.category_id exptl _item.mandatory_code no _item_type.code text loop_ _item_examples.case '29 structures' 'minimized average structure' save_ ################### ## EXPTL_CRYSTAL ## ################### save_exptl_crystal _category.description ; Data items in the EXPTL_CRYSTAL category record the results of experimental measurements on the crystal or crystals used, such as shape, size or density. ; _category.id exptl_crystal _category.mandatory_code no _category_key.name '_exptl_crystal.id' loop_ _category_group.id 'inclusive_group' 'exptl_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on laboratory records for Yb(S-C5H4N)2(THF)4. ; ; _exptl_crystal.id xst2l _exptl_crystal.colour 'pale yellow' _exptl_crystal.density_diffrn 1.113 _exptl_crystal.density_Matthews 1.01 _exptl_crystal.density_meas 1.11 _exptl_crystal.density_meas_temp 294.5 _exptl_crystal.density_method 'neutral buoyancy' _exptl_crystal.density_percent_sol 0.15 # P = 1 - (1.23*N*MMass) / V _exptl_crystal.description 'hexagonal rod, uncut' _exptl_crystal.F_000 202 _exptl_crystal.preparation ; hanging drop, crystal soaked in 10% ethylene glycol for 10 h, then placed in nylon loop at data collection time ; _exptl_crystal.size_max 0.30 _exptl_crystal.size_mid 0.20 _exptl_crystal.size_min 0.05 _exptl_crystal.size_rad 0.025 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - using separate items to define upper and lower limits for a value. ; ; _exptl_crystal.density_meas_gt 2.5 _exptl_crystal.density_meas_lt 5.0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 3 - here the density was measured at some unspecified temperature below room temperature. ; ; _exptl_crystal.density_meas_temp_lt 300 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__exptl_crystal.colour _item_description.description ; The colour of the crystal. ; _item.name '_exptl_crystal.colour' _item.category_id exptl_crystal _item.mandatory_code no _item_aliases.alias_name '_exptl_crystal_colour' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line _item_examples.case 'dark green' save_ save__exptl_crystal.density_diffrn _item_description.description ; Density values calculated from the crystal cell and contents. The units are megagrams per cubic metre (grams per cubic centimetre). ; _item.name '_exptl_crystal.density_diffrn' _item.category_id exptl_crystal _item.mandatory_code no _item_aliases.alias_name '_exptl_crystal_density_diffrn' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__exptl_crystal.density_Matthews _item_description.description ; The density of the crystal, expressed as the ratio of the volume of the asymmetric unit to the molecular mass of a monomer of the structure, in units of angstroms^3^ per dalton. Ref: Matthews, B. W. (1968). J. Mol. Biol. 33, 491-497. ; _item.name '_exptl_crystal.density_Matthews' _item.category_id exptl_crystal _item.mandatory_code no _item_type.code float save_ #save__exptl_crystal.density_meas # _item_description.description #; Density values measured using standard chemical and physical # methods. The units are megagrams per cubic metre (grams per # cubic centimetre). #; # _item.name '_exptl_crystal.density_meas' # _item.category_id exptl_crystal # _item.mandatory_code no # _item_aliases.alias_name '_exptl_crystal_density_meas' # _item_aliases.dictionary cif_core.dic # _item_aliases.version 2.0.1 # loop_ # _item_range.maximum # _item_range.minimum . 0.0 # 0.0 0.0 # _item_type.code float # save_ # #save__exptl_crystal.density_meas_temp # _item_description.description #; The temperature in kelvins at which _exptl_crystal.density_meas # was determined. #; # _item.name '_exptl_crystal.density_meas_temp' # _item.category_id exptl_crystal # _item.mandatory_code no # _item_aliases.alias_name '_exptl_crystal_density_meas_temp' # _item_aliases.dictionary cif_core.dic # _item_aliases.version 2.0.1 # loop_ # _item_range.maximum # _item_range.minimum . 0.0 # 0.0 0.0 # _item_type.code float # _item_units.code kelvins # save_ save__exptl_crystal.density_method _item_description.description ; The method used to measure _exptl_crystal.density_meas. ; _item.name '_exptl_crystal.density_method' _item.category_id exptl_crystal _item.mandatory_code no _item_aliases.alias_name '_exptl_crystal_density_method' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__exptl_crystal.density_percent_sol _item_description.description ; Density value P calculated from the crystal cell and contents, expressed as per cent solvent. P = 1 - (1.23 N MMass) / V N = the number of molecules in the unit cell MMass = the molecular mass of each molecule (gm/mole) V = the volume of the unit cell (A^3^) 1.23 = a conversion factor evaluated as: (0.74 cm^3^/g) (10^24^ A^3^/cm^3^) -------------------------------------- (6.02*10^23^) molecules/mole where 0.74 is an assumed value for the partial specific volume of the molecule ; _item.name '_exptl_crystal.density_percent_sol' _item.category_id exptl_crystal _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__exptl_crystal.description _item_description.description ; A description of the quality and habit of the crystal. The crystal dimensions should not normally be reported here; use instead the specific items in the EXPTL_CRYSTAL category relating to size for the gross dimensions of the crystal and data items in the EXPTL_CRYSTAL_FACE category to describe the relationship between individual faces. ; _item.name '_exptl_crystal.description' _item.category_id exptl_crystal _item.mandatory_code no _item_aliases.alias_name '_exptl_crystal_description' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__exptl_crystal.F_000 _item_description.description ; The effective number of electrons in the crystal unit cell contributing to F(000). This may contain dispersion contributions and is calculated as F(000) = [ sum (f~r~^2^ + f~i~^2^) ]^1/2^ f~r~ = real part of the scattering factors at theta = 0 degree f~i~ = imaginary part of the scattering factors at theta = 0 degree the sum is taken over each atom in the unit cell ; _item.name '_exptl_crystal.F_000' _item.category_id exptl_crystal _item.mandatory_code no _item_aliases.alias_name '_exptl_crystal_F_000' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__exptl_crystal.id _item_description.description ; The value of _exptl_crystal.id must uniquely identify a record in the EXPTL_CRYSTAL list. Note that this item need not be a number; it can be any unique identifier. ; loop_ _item.name _item.category_id _item.mandatory_code '_exptl_crystal.id' exptl_crystal yes '_exptl_crystal_face.crystal_id' exptl_crystal_face yes '_exptl_crystal_grow.crystal_id' exptl_crystal_grow yes '_exptl_crystal_grow_comp.crystal_id' exptl_crystal_grow_comp yes '_diffrn.crystal_id' diffrn yes '_refln.crystal_id' refln yes _item_aliases.alias_name '_exptl_crystal_id' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_linked.child_name _item_linked.parent_name '_diffrn.crystal_id' '_exptl_crystal.id' '_exptl_crystal_grow.crystal_id' '_exptl_crystal.id' '_exptl_crystal_face.crystal_id' '_exptl_crystal.id' '_exptl_crystal_grow_comp.crystal_id' '_exptl_crystal.id' '_refln.crystal_id' '_exptl_crystal.id' _item_type.code code save_ save__exptl_crystal.preparation _item_description.description ; Details of crystal growth and preparation of the crystal (e.g. mounting) prior to the intensity measurements. ; _item.name '_exptl_crystal.preparation' _item.category_id exptl_crystal _item.mandatory_code no _item_aliases.alias_name '_exptl_crystal_preparation' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'mounted in an argon-filled quartz capillary' save_ save__exptl_crystal.size_max _item_description.description ; The maximum dimension of the crystal. This item may appear in a list with _exptl_crystal.id if multiple crystals are used in the experiment. ; _item.name '_exptl_crystal.size_max' _item.category_id exptl_crystal _item.mandatory_code no _item_aliases.alias_name '_exptl_crystal_size_max' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code millimetres save_ save__exptl_crystal.size_mid _item_description.description ; The medial dimension of the crystal. This item may appear in a list with _exptl_crystal.id if multiple crystals are used in the experiment. ; _item.name '_exptl_crystal.size_mid' _item.category_id exptl_crystal _item.mandatory_code no _item_aliases.alias_name '_exptl_crystal_size_mid' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code millimetres save_ save__exptl_crystal.size_min _item_description.description ; The minimum dimension of the crystal. This item may appear in a list with _exptl_crystal.id if multiple crystals are used in the experiment. ; _item.name '_exptl_crystal.size_min' _item.category_id exptl_crystal _item.mandatory_code no _item_aliases.alias_name '_exptl_crystal_size_min' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code millimetres save_ save__exptl_crystal.size_rad _item_description.description ; The radius of the crystal, if the crystal is a sphere or a cylinder. This item may appear in a list with _exptl_crystal.id if multiple crystals are used in the experiment. ; _item.name '_exptl_crystal.size_rad' _item.category_id exptl_crystal _item.mandatory_code no _item_aliases.alias_name '_exptl_crystal_size_rad' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code millimetres save_ ######################## ## EXPTL_CRYSTAL_FACE ## ######################## save_exptl_crystal_face _category.description ; Data items in the EXPTL_CRYSTAL_FACE category record details of the crystal faces. ; _category.id exptl_crystal_face _category.mandatory_code no loop_ _category_key.name '_exptl_crystal_face.crystal_id' '_exptl_crystal_face.index_h' '_exptl_crystal_face.index_k' '_exptl_crystal_face.index_l' loop_ _category_group.id 'inclusive_group' 'exptl_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on laboratory records for Yb(S-C5H4N)2(THF)4 for the 100 face of crystal xstl1. ; ; _exptl_crystal_face.crystal_id xstl1 _exptl_crystal_face.index_h 1 _exptl_crystal_face.index_k 0 _exptl_crystal_face.index_l 0 _exptl_crystal_face.diffr_chi 42.56 _exptl_crystal_face.diffr_kappa 30.23 _exptl_crystal_face.diffr_phi -125.56 _exptl_crystal_face.diffr_psi -0.34 _exptl_crystal_face.perp_dist 0.025 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__exptl_crystal_face.crystal_id _item_description.description ; This data item is a pointer to _exptl_crystal.id in the EXPTL_CRYSTAL category. ; _item.name '_exptl_crystal_face.crystal_id' _item.mandatory_code yes save_ save__exptl_crystal_face.diffr_chi _item_description.description ; The chi diffractometer setting angle in degrees for a specific crystal face associated with _exptl_crystal_face.perp_dist. ; _item.name '_exptl_crystal_face.diffr_chi' _item.category_id exptl_crystal_face _item.mandatory_code no _item_aliases.alias_name '_exptl_crystal_face_diffr_chi' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code float _item_units.code degrees save_ save__exptl_crystal_face.diffr_kappa _item_description.description ; The kappa diffractometer setting angle in degrees for a specific crystal face associated with _exptl_crystal_face.perp_dist. ; _item.name '_exptl_crystal_face.diffr_kappa' _item.category_id exptl_crystal_face _item.mandatory_code no _item_aliases.alias_name '_exptl_crystal_face_diffr_kappa' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code float _item_units.code degrees save_ save__exptl_crystal_face.diffr_phi _item_description.description ; The phi diffractometer setting angle in degrees for a specific crystal face associated with _exptl_crystal_face.perp_dist. ; _item.name '_exptl_crystal_face.diffr_phi' _item.category_id exptl_crystal_face _item.mandatory_code no _item_aliases.alias_name '_exptl_crystal_face_diffr_phi' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code float _item_units.code degrees save_ save__exptl_crystal_face.diffr_psi _item_description.description ; The psi diffractometer setting angle in degrees for a specific crystal face associated with _exptl_crystal_face.perp_dist. ; _item.name '_exptl_crystal_face.diffr_psi' _item.category_id exptl_crystal_face _item.mandatory_code no _item_aliases.alias_name '_exptl_crystal_face_diffr_psi' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code float _item_units.code degrees save_ save__exptl_crystal_face.index_h _item_description.description ; Miller index h of the crystal face associated with the value _exptl_crystal_face.perp_dist. ; _item.name '_exptl_crystal_face.index_h' _item.category_id exptl_crystal_face _item.mandatory_code yes _item_aliases.alias_name '_exptl_crystal_face_index_h' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_exptl_crystal_face.index_k' '_exptl_crystal_face.index_l' _item_sub_category.id miller_index _item_type.code int save_ save__exptl_crystal_face.index_k _item_description.description ; Miller index k of the crystal face associated with the value _exptl_crystal_face.perp_dist. ; _item.name '_exptl_crystal_face.index_k' _item.category_id exptl_crystal_face _item.mandatory_code yes _item_aliases.alias_name '_exptl_crystal_face_index_k' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_exptl_crystal_face.index_h' '_exptl_crystal_face.index_l' _item_sub_category.id miller_index _item_type.code int save_ save__exptl_crystal_face.index_l _item_description.description ; Miller index l of the crystal face associated with the value _exptl_crystal_face.perp_dist. ; _item.name '_exptl_crystal_face.index_l' _item.category_id exptl_crystal_face _item.mandatory_code yes _item_aliases.alias_name '_exptl_crystal_face_index_l' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_exptl_crystal_face.index_h' '_exptl_crystal_face.index_k' _item_sub_category.id miller_index _item_type.code int save_ save__exptl_crystal_face.perp_dist _item_description.description ; The perpendicular distance in millimetres from the face to the centre of rotation of the crystal. ; _item.name '_exptl_crystal_face.perp_dist' _item.category_id exptl_crystal_face _item.mandatory_code no _item_aliases.alias_name '_exptl_crystal_face_perp_dist' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code millimetres save_ ######################## ## EXPTL_CRYSTAL_GROW ## ######################## save_exptl_crystal_grow _category.description ; Data items in the EXPTL_CRYSTAL_GROW category record details about the conditions and methods used to grow the crystal. ; _category.id exptl_crystal_grow _category.mandatory_code no _category_key.name '_exptl_crystal_grow.crystal_id' loop_ _category_group.id 'inclusive_group' 'exptl_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _exptl_crystal_grow.crystal_id 1 _exptl_crystal_grow.method 'hanging drop' _exptl_crystal_grow.apparatus 'Linbro plates' _exptl_crystal_grow.atmosphere 'room air' _exptl_crystal_grow.pH 4.7 _exptl_crystal_grow.temp 18(3) _exptl_crystal_grow.time 'approximately 2 days' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__exptl_crystal_grow.apparatus _item_description.description ; The physical apparatus in which the crystal was grown. ; _item.name '_exptl_crystal_grow.apparatus' _item.category_id exptl_crystal_grow _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'Linbro plate' 'sandwich box' 'ACA plates' save_ save__exptl_crystal_grow.atmosphere _item_description.description ; The nature of the gas or gas mixture in which the crystal was grown. ; _item.name '_exptl_crystal_grow.atmosphere' _item.category_id exptl_crystal_grow _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'room air' 'nitrogen' 'argon' save_ save__exptl_crystal_grow.crystal_id _item_description.description ; This data item is a pointer to _exptl_crystal.id in the EXPTL_CRYSTAL category. ; _item.name '_exptl_crystal_grow.crystal_id' _item.mandatory_code yes save_ save__exptl_crystal_grow.details _item_description.description ; A description of special aspects of the crystal growth. ; _item.name '_exptl_crystal_grow.details' _item.category_id exptl_crystal_grow _item.mandatory_code no _item_type.code text loop_ _item_examples.case ; Solution 2 was prepared as a well solution and mixed. A droplet containing 2 \ml of solution 1 was delivered onto a cover slip; 2 \ml of solution 2 was added to the droplet without mixing. ; ; Crystal plates were originally stored at room temperature for 1 week but no nucleation occurred. They were then transferred to 4 degrees C, at which temperature well formed single crystals grew in 2 days. ; ; The dependence on pH for successful crystal growth is very sharp. At pH 7.4 only showers of tiny crystals grew, at pH 7.5 well formed single crystals grew, at pH 7.6 no crystallization occurred at all. ; save_ save__exptl_crystal_grow.method _item_description.description ; The method used to grow the crystals. ; _item.name '_exptl_crystal_grow.method' _item.category_id exptl_crystal_grow _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'batch precipitation' 'batch dialysis' 'hanging drop vapor diffusion' 'sitting drop vapor diffusion' save_ save__exptl_crystal_grow.method_ref _item_description.description ; A literature reference that describes the method used to grow the crystals. ; _item.name '_exptl_crystal_grow.method_ref' _item.category_id exptl_crystal_grow _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'McPherson et al., 1988' save_ save__exptl_crystal_grow.pH _item_description.description ; The pH at which the crystal was grown. If more than one pH was employed during the crystallization process, the final pH should be noted here and the protocol involving multiple pH values should be described in _exptl_crystal_grow.details. ; _item.name '_exptl_crystal_grow.pH' _item.category_id exptl_crystal_grow _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float loop_ _item_examples.case 7.4 7.6 4.3 save_ save__exptl_crystal_grow.pressure _item_description.description ; The ambient pressure in kilopascals at which the crystal was grown. ; _item.name '_exptl_crystal_grow.pressure' _item.category_id exptl_crystal_grow _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_exptl_crystal_grow.pressure_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code kilopascals save_ save__exptl_crystal_grow.pressure_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _exptl_crystal_grow.pressure. ; _item.name '_exptl_crystal_grow.pressure_esd' _item.category_id exptl_crystal_grow _item.mandatory_code no # _item_default.value 0.0 _item_related.related_name '_exptl_crystal_grow.pressure' _item_related.function_code associated_value _item_type.code float _item_units.code kilopascals save_ save__exptl_crystal_grow.seeding _item_description.description ; A description of the protocol used for seeding the crystal growth. ; _item.name '_exptl_crystal_grow.seeding' _item.category_id exptl_crystal_grow _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'macroseeding' ; Microcrystals were introduced from a previous crystal growth experiment by transfer with a human hair. ; save_ save__exptl_crystal_grow.seeding_ref _item_description.description ; A literature reference that describes the protocol used to seed the crystal. ; _item.name '_exptl_crystal_grow.seeding_ref' _item.category_id exptl_crystal_grow _item.mandatory_code no _item_type.code text _item_examples.case 'Stura et al., 1989' save_ save__exptl_crystal_grow.temp _item_description.description ; The temperature in kelvins at which the crystal was grown. If more than one temperature was employed during the crystallization process, the final temperature should be noted here and the protocol involving multiple temperatures should be described in _exptl_crystal_grow.details. ; _item.name '_exptl_crystal_grow.temp' _item.category_id exptl_crystal_grow _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_exptl_crystal_grow.temp_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code kelvins save_ save__exptl_crystal_grow.temp_details _item_description.description ; A description of special aspects of temperature control during crystal growth. ; _item.name '_exptl_crystal_grow.temp_details' _item.category_id exptl_crystal_grow _item.mandatory_code no _item_type.code text save_ save__exptl_crystal_grow.temp_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _exptl_crystal_grow.temp. ; _item.name '_exptl_crystal_grow.temp_esd' _item.category_id exptl_crystal_grow _item.mandatory_code no # _item_default.value 0.0 _item_related.related_name '_exptl_crystal_grow.temp' _item_related.function_code associated_value _item_type.code float _item_units.code kelvins save_ save__exptl_crystal_grow.time _item_description.description ; The approximate time that the crystal took to grow to the size used for data collection. ; _item.name '_exptl_crystal_grow.time' _item.category_id exptl_crystal_grow _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'overnight' '2-4 days' '6 months' save_ ############################# ## EXPTL_CRYSTAL_GROW_COMP ## ############################# save_exptl_crystal_grow_comp _category.description ; Data items in the EXPTL_CRYSTAL_GROW_COMP category record details about the components of the solutions that were 'mixed' (by whatever means) to produce the crystal. In general, solution 1 is the solution that contains the molecule to be crystallized and solution 2 is the solution that contains the precipitant. However, the number of solutions required to describe the crystallization protocol is not limited to 2. Details of the crystallization protocol should be given in _exptl_crystal_grow_comp.details using the solutions described in EXPTL_CRYSTAL_GROW_COMP. ; _category.id exptl_crystal_grow_comp _category.mandatory_code no loop_ _category_key.name '_exptl_crystal_grow_comp.id' '_exptl_crystal_grow_comp.crystal_id' loop_ _category_group.id 'inclusive_group' 'exptl_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _exptl_crystal_grow_comp.crystal_id _exptl_crystal_grow_comp.id _exptl_crystal_grow_comp.sol_id _exptl_crystal_grow_comp.name _exptl_crystal_grow_comp.volume _exptl_crystal_grow_comp.conc _exptl_crystal_grow_comp.details 1 1 1 'HIV-1 protease' '0.002 ml' '6 mg/ml' ; The protein solution was in a buffer containing 25 mM NaCl, 100 mM NaMES/ MES buffer, pH 7.5, 3 mM NaAzide ; 1 2 2 'NaCl' '0.200 ml' '4 M' 'in 3 mM NaAzide' 1 3 2 'Acetic Acid' '0.047 ml' '100 mM' 'in 3 mM NaAzide' 1 4 2 'Na Acetate' '0.053 ml' '100 mM' ; in 3 mM NaAzide. Buffer components were mixed to produce a pH of 4.7 according to a ratio calculated from the pKa. The actual pH of solution 2 was not measured. ; 1 5 2 'water' '0.700 ml' 'neat' 'in 3 mM NaAzide' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__exptl_crystal_grow_comp.conc _item_description.description ; The concentration of the solution component. ; _item.name '_exptl_crystal_grow_comp.conc' _item.category_id exptl_crystal_grow_comp _item.mandatory_code no _item_type.code line loop_ _item_examples.case '200 \ml' '0.1 ml' save_ save__exptl_crystal_grow_comp.details _item_description.description ; A description of any special aspects of the solution component. When the solution component is the one that contains the macromolecule, this could be the specification of the buffer in which the macromolecule was stored. When the solution component is a buffer component, this could be the methods (or formula) used to achieve a desired pH. ; _item.name '_exptl_crystal_grow_comp.details' _item.category_id exptl_crystal_grow_comp _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'in 3 mM NaAzide' ; The protein solution was in a buffer containing 25 mM NaCl, 100 mM NaMES/MES buffer, pH 7.5, 3 mM NaAzide ; ; in 3 mM NaAzide. Buffer components were mixed to produce a pH of 4.7 according to a ratio calculated from the pKa. The actual pH of solution 2 was not measured. ; save_ save__exptl_crystal_grow_comp.crystal_id _item_description.description ; This data item is a pointer to _exptl_crystal.id in the EXPTL_CRYSTAL category. ; _item.name '_exptl_crystal_grow_comp.crystal_id' _item.mandatory_code yes save_ save__exptl_crystal_grow_comp.id _item_description.description ; The value of _exptl_crystal_grow_comp.id must uniquely identify each item in the EXPTL_CRYSTAL_GROW_COMP list. Note that this item need not be a number; it can be any unique identifier. ; _item.name '_exptl_crystal_grow_comp.id' _item.category_id exptl_crystal_grow_comp _item.mandatory_code yes _item_type.code line loop_ _item_examples.case '1' 'A' 'protein in buffer' save_ save__exptl_crystal_grow_comp.name _item_description.description ; A common name for the component of the solution. ; _item.name '_exptl_crystal_grow_comp.name' _item.category_id exptl_crystal_grow_comp _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'protein in buffer' 'acetic acid' save_ save__exptl_crystal_grow_comp.sol_id _item_description.description ; An identifier for the solution to which the given solution component belongs. ; _item.name '_exptl_crystal_grow_comp.sol_id' _item.category_id exptl_crystal_grow_comp _item.mandatory_code no _item_type.code line loop_ _item_examples.case '1' 'well solution' 'solution A' save_ save__exptl_crystal_grow_comp.volume _item_description.description ; The volume of the solution component. ; _item.name '_exptl_crystal_grow_comp.volume' _item.category_id exptl_crystal_grow_comp _item.mandatory_code no _item_type.code line loop_ _item_examples.case '200 \ml' '0.1 ml' save_ ########## ## GEOM ## ########## save_geom _category.description ; Data items in the GEOM and related (GEOM_ANGLE, GEOM_BOND, GEOM_CONTACT, GEOM_HBOND and GEOM_TORSION) categories record details about the molecular geometry as calculated from the contents of the ATOM, CELL and SYMMETRY data. Geometry data are therefore redundant, in that they can be calculated from other more fundamental quantities in the data block. However, they provide a check on the correctness of both sets of data and enable the most important geometric data to be identified for publication by setting the appropriate publication flag. ; _category.id geom _category.mandatory_code no _category_key.name '_geom.entry_id' loop_ _category_group.id 'inclusive_group' 'geom_group' save_ save__geom.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_geom.entry_id' _item.mandatory_code yes save_ save__geom.details _item_description.description ; A description of geometry not covered by the existing data names in the GEOM categories, such as least-squares planes. ; _item.name '_geom.details' _item.category_id geom _item.mandatory_code no _item_aliases.alias_name '_geom_special_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ ################ ## GEOM_ANGLE ## ################ save_geom_angle _category.description ; Data items in the GEOM_ANGLE category record details about the bond angles as calculated from the contents of the ATOM, CELL and SYMMETRY data. ; _category.id geom_angle _category.mandatory_code no loop_ _category_key.name '_geom_angle.atom_site_id_1' '_geom_angle.atom_site_id_2' '_geom_angle.atom_site_id_3' '_geom_angle.site_symmetry_1' '_geom_angle.site_symmetry_2' '_geom_angle.site_symmetry_3' loop_ _category_group.id 'inclusive_group' 'geom_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; loop_ _geom_angle.atom_site_id_1 _geom_angle.atom_site_id_2 _geom_angle.atom_site_id_3 _geom_angle.value _geom_angle.value_esd _geom_angle.site_symmetry_1 _geom_angle.site_symmetry_2 _geom_angle.site_symmetry_3 _geom_angle.publ_flag C2 O1 C5 111.6 0.2 1_555 1_555 1_555 yes O1 C2 C3 110.9 0.2 1_555 1_555 1_555 yes O1 C2 O21 122.2 0.3 1_555 1_555 1_555 yes C3 C2 O21 127.0 0.3 1_555 1_555 1_555 yes C2 C3 N4 101.3 0.2 1_555 1_555 1_555 yes C2 C3 C31 111.3 0.2 1_555 1_555 1_555 yes C2 C3 H3 107 1 1_555 1_555 1_555 no N4 C3 C31 116.7 0.2 1_555 1_555 1_555 yes # - - - - data truncated for brevity - - - - ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__geom_angle.atom_site_id_1 _item_description.description ; The identifier of the first of the three atom sites that define the angle. This data item is a pointer to _atom_site.id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_id_1' _item.mandatory_code yes _item_aliases.alias_name '_geom_angle_atom_site_label_1' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_geom_angle.atom_site_id_2' '_geom_angle.atom_site_id_3' save_ save__geom_angle.atom_site_label_alt_id_1 _item_description.description ; An optional identifier of the first of the three atom sites that define the angle. This data item is a pointer to _atom_site.label_alt_id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_label_alt_id_1' _item.mandatory_code no save_ save__geom_angle.atom_site_label_atom_id_1 _item_description.description ; An optional identifier of the first of the three atom sites that define the angle. This data item is a pointer to _atom_site.label_atom_id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_label_atom_id_1' _item.mandatory_code no save_ save__geom_angle.atom_site_label_comp_id_1 _item_description.description ; An optional identifier of the first of the three atom sites that define the angle. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_label_comp_id_1' _item.mandatory_code no save_ save__geom_angle.atom_site_label_seq_id_1 _item_description.description ; An optional identifier of the first of the three atom sites that define the angle. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_label_seq_id_1' _item.mandatory_code no save_ save__geom_angle.atom_site_label_asym_id_1 _item_description.description ; An optional identifier of the first of the three atom sites that define the angle. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_label_asym_id_1' _item.mandatory_code no save_ save__geom_angle.atom_site_id_2 _item_description.description ; The identifier of the second of the three atom sites that define the angle. The second atom is taken to be the apex of the angle. This data item is a pointer to _atom_site.id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_id_2' _item.mandatory_code yes _item_aliases.alias_name '_geom_angle_atom_site_label_2' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_geom_angle.atom_site_id_1' '_geom_angle.atom_site_id_3' save_ save__geom_angle.atom_site_label_alt_id_2 _item_description.description ; An optional identifier of the second of the three atom sites that define the angle. This data item is a pointer to _atom_site.label_alt_id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_label_alt_id_2' _item.mandatory_code no save_ save__geom_angle.atom_site_label_atom_id_2 _item_description.description ; An optional identifier of the second of the three atom sites that define the angle. This data item is a pointer to _atom_site.label_atom_id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_label_atom_id_2' _item.mandatory_code no save_ save__geom_angle.atom_site_label_comp_id_2 _item_description.description ; An optional identifier of the second of the three atom sites that define the angle. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_label_comp_id_2' _item.mandatory_code no save_ save__geom_angle.atom_site_label_seq_id_2 _item_description.description ; An optional identifier of the second of the three atom sites that define the angle. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_label_seq_id_2' _item.mandatory_code no save_ save__geom_angle.atom_site_label_asym_id_2 _item_description.description ; An optional identifier of the second of the three atom sites that define the angle. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_label_asym_id_2' _item.mandatory_code no save_ save__geom_angle.atom_site_id_3 _item_description.description ; The identifier of the third of the three atom sites that define the angle. This data item is a pointer to _atom_site.id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_id_3' _item.mandatory_code yes _item_aliases.alias_name '_geom_angle_atom_site_label_3' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_geom_angle.atom_site_id_1' '_geom_angle.atom_site_id_2' save_ save__geom_angle.atom_site_label_alt_id_3 _item_description.description ; An optional identifier of the third of the three atom sites that define the angle. This data item is a pointer to _atom_site.label_alt_id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_label_alt_id_3' _item.mandatory_code no save_ save__geom_angle.atom_site_label_atom_id_3 _item_description.description ; An optional identifier of the third of the three atom sites that define the angle. This data item is a pointer to _atom_site.label_atom_id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_label_atom_id_3' _item.mandatory_code no save_ save__geom_angle.atom_site_label_comp_id_3 _item_description.description ; An optional identifier of the third of the three atom sites that define the angle. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_label_comp_id_3' _item.mandatory_code no save_ save__geom_angle.atom_site_label_seq_id_3 _item_description.description ; An optional identifier of the third of the three atom sites that define the angle. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_label_seq_id_3' _item.mandatory_code no save_ save__geom_angle.atom_site_label_asym_id_3 _item_description.description ; An optional identifier of the third of the three atom sites that define the angle. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_label_asym_id_3' _item.mandatory_code no save_ save__geom_angle.atom_site_auth_asym_id_1 _item_description.description ; An optional identifier of the first of the three atom sites that define the angle. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_auth_asym_id_1' _item.mandatory_code no save_ save__geom_angle.atom_site_auth_atom_id_1 _item_description.description ; An optional identifier of the first of the three atom sites that define the angle. This data item is a pointer to _atom_site.auth_atom_id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_auth_atom_id_1' _item.mandatory_code no save_ save__geom_angle.atom_site_auth_comp_id_1 _item_description.description ; An optional identifier of the first of the three atom sites that define the angle. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_auth_comp_id_1' _item.mandatory_code no save_ save__geom_angle.atom_site_auth_seq_id_1 _item_description.description ; An optional identifier of the first of the three atom sites that define the angle. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_auth_seq_id_1' _item.mandatory_code no save_ save__geom_angle.atom_site_auth_atom_id_2 _item_description.description ; An optional identifier of the second of the three atom sites that define the angle. This data item is a pointer to _atom_site.auth_atom_id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_auth_atom_id_2' _item.mandatory_code no save_ save__geom_angle.atom_site_auth_asym_id_2 _item_description.description ; An optional identifier of the second of the three atom sites that define the angle. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_auth_asym_id_2' _item.mandatory_code no save_ save__geom_angle.atom_site_auth_comp_id_2 _item_description.description ; An optional identifier of the second of the three atom sites that define the angle. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_auth_comp_id_2' _item.mandatory_code no save_ save__geom_angle.atom_site_auth_seq_id_2 _item_description.description ; An optional identifier of the second of the three atom sites that define the angle. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_auth_seq_id_2' _item.mandatory_code no save_ save__geom_angle.atom_site_auth_atom_id_3 _item_description.description ; An optional identifier of the third of the three atom sites that define the angle. This data item is a pointer to _atom_site.auth_atom_id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_auth_atom_id_3' _item.mandatory_code no save_ save__geom_angle.atom_site_auth_asym_id_3 _item_description.description ; An optional identifier of the third of the three atom sites that define the angle. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_auth_asym_id_3' _item.mandatory_code no save_ save__geom_angle.atom_site_auth_comp_id_3 _item_description.description ; An optional identifier of the third of the three atom sites that define the angle. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_auth_comp_id_3' _item.mandatory_code no save_ save__geom_angle.atom_site_auth_seq_id_3 _item_description.description ; An optional identifier of the third of the three atom sites that define the angle. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_geom_angle.atom_site_auth_seq_id_3' _item.mandatory_code no save_ save__geom_angle.publ_flag _item_description.description ; This code signals whether the angle is referred to in a publication or should be placed in a table of significant angles. ; _item.name '_geom_angle.publ_flag' _item.category_id geom_angle _item.mandatory_code no _item_aliases.alias_name '_geom_angle_publ_flag' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail no 'do not include angle in special list' n 'abbreviation for "no"' yes 'do include angle in special list' y 'abbreviation for "yes"' save_ save__geom_angle.site_symmetry_1 _item_description.description ; The symmetry code of the first of the three atom sites that define the angle. ; _item.name '_geom_angle.site_symmetry_1' _item.category_id geom_angle _item.mandatory_code yes _item_aliases.alias_name '_geom_angle_site_symmetry_1' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_default.value 1_555 _item_type.code symop loop_ _item_examples.case _item_examples.detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' save_ save__geom_angle.site_symmetry_2 _item_description.description ; The symmetry code of the second of the three atom sites that define the angle. ; _item.name '_geom_angle.site_symmetry_2' _item.category_id geom_angle _item.mandatory_code yes _item_aliases.alias_name '_geom_angle_site_symmetry_2' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_default.value 1_555 _item_type.code symop loop_ _item_examples.case _item_examples.detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' save_ save__geom_angle.site_symmetry_3 _item_description.description ; The symmetry code of the third of the three atom sites that define the angle. ; _item.name '_geom_angle.site_symmetry_3' _item.category_id geom_angle _item.mandatory_code yes _item_aliases.alias_name '_geom_angle_site_symmetry_3' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_default.value 1_555 _item_type.code symop loop_ _item_examples.case _item_examples.detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' save_ save__geom_angle.value _item_description.description ; Angle in degrees defined by the three sites _geom_angle.atom_site_id_1, _geom_angle.atom_site_id_2 and _geom_angle.atom_site_id_3. ; _item.name '_geom_angle.value' _item.category_id geom_angle _item.mandatory_code no _item_aliases.alias_name '_geom_angle' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_related.related_name '_geom_angle.value_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code degrees save_ save__geom_angle.value_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _geom_angle.value. ; _item.name '_geom_angle.value_esd' _item.category_id geom_angle _item.mandatory_code no # _item_default.value 0.0 _item_related.related_name '_geom_angle.value' _item_related.function_code associated_value _item_type.code float _item_units.code degrees save_ ############### ## GEOM_BOND ## ############### save_geom_bond _category.description ; Data items in the GEOM_BOND category record details about the bond lengths as calculated from the contents of the ATOM, CELL and SYMMETRY data. ; _category.id geom_bond _category.mandatory_code no loop_ _category_key.name '_geom_bond.atom_site_id_1' '_geom_bond.atom_site_id_2' '_geom_bond.site_symmetry_1' '_geom_bond.site_symmetry_2' loop_ _category_group.id 'inclusive_group' 'geom_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; loop_ _geom_bond.atom_site_id_1 _geom_bond.atom_site_id_2 _geom_bond.dist _geom_bond.dist_esd _geom_bond.site_symmetry_1 _geom_bond.site_symmetry_2 _geom_bond.publ_flag O1 C2 1.342 0.004 1_555 1_555 yes O1 C5 1.439 0.003 1_555 1_555 yes C2 C3 1.512 0.004 1_555 1_555 yes C2 O21 1.199 0.004 1_555 1_555 yes C3 N4 1.465 0.003 1_555 1_555 yes C3 C31 1.537 0.004 1_555 1_555 yes C3 H3 1.00 0.03 1_555 1_555 no N4 C5 1.472 0.003 1_555 1_555 yes # - - - - data truncated for brevity - - - - ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__geom_bond.atom_site_id_1 _item_description.description ; The identifier of the first of the two atom sites that define the bond. This data item is a pointer to _atom_site.id in the ATOM_SITE category. ; _item.name '_geom_bond.atom_site_id_1' _item.mandatory_code yes _item_aliases.alias_name '_geom_bond_atom_site_label_1' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_dependent.dependent_name '_geom_bond.atom_site_id_2' save_ save__geom_bond.atom_site_label_alt_id_1 _item_description.description ; An optional identifier of the first of the two atom sites that define the bond. This data item is a pointer to _atom_site.label_alt_id in the ATOM_SITE category. ; _item.name '_geom_bond.atom_site_label_alt_id_1' _item.mandatory_code no save_ save__geom_bond.atom_site_label_atom_id_1 _item_description.description ; An optional identifier of the first of the two atom sites that define the bond. This data item is a pointer to _atom_site.label_atom_id in the ATOM_SITE category. ; _item.name '_geom_bond.atom_site_label_atom_id_1' _item.mandatory_code no save_ save__geom_bond.atom_site_label_comp_id_1 _item_description.description ; An optional identifier of the first of the two atom sites that define the bond. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_geom_bond.atom_site_label_comp_id_1' _item.mandatory_code no save_ save__geom_bond.atom_site_label_seq_id_1 _item_description.description ; An optional identifier of the first of the two atom sites that define the bond. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_geom_bond.atom_site_label_seq_id_1' _item.mandatory_code no save_ save__geom_bond.atom_site_label_asym_id_1 _item_description.description ; An optional identifier of the first of the two atom sites that define the bond. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_geom_bond.atom_site_label_asym_id_1' _item.mandatory_code no save_ save__geom_bond.atom_site_id_2 _item_description.description ; The identifier of the second of the two atom sites that define the bond. This data item is a pointer to _atom_site.id in the ATOM_SITE category. ; _item.name '_geom_bond.atom_site_id_2' _item.mandatory_code yes _item_aliases.alias_name '_geom_bond_atom_site_label_2' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_dependent.dependent_name '_geom_bond.atom_site_id_1' save_ save__geom_bond.atom_site_label_alt_id_2 _item_description.description ; An optional identifier of the second of the two atom sites that define the bond. This data item is a pointer to _atom_site.label_alt_id in the ATOM_SITE category. ; _item.name '_geom_bond.atom_site_label_alt_id_2' _item.mandatory_code no save_ save__geom_bond.atom_site_label_atom_id_2 _item_description.description ; An optional identifier of the second of the two atom sites that define the bond. This data item is a pointer to _atom_site.label_atom_id in the ATOM_SITE category. ; _item.name '_geom_bond.atom_site_label_atom_id_2' _item.mandatory_code no save_ save__geom_bond.atom_site_label_comp_id_2 _item_description.description ; An optional identifier of the second of the two atom sites that define the bond. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_geom_bond.atom_site_label_comp_id_2' _item.mandatory_code no save_ save__geom_bond.atom_site_label_seq_id_2 _item_description.description ; An optional identifier of the second of the two atom sites that define the bond. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_geom_bond.atom_site_label_seq_id_2' _item.mandatory_code no save_ save__geom_bond.atom_site_label_asym_id_2 _item_description.description ; An optional identifier of the second of the two atom sites that define the bond. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_geom_bond.atom_site_label_asym_id_2' _item.mandatory_code no save_ save__geom_bond.atom_site_auth_atom_id_1 _item_description.description ; An optional identifier of the first of the two atom sites that define the bond. This data item is a pointer to _atom_site.auth_atom_id in the ATOM_SITE category. ; _item.name '_geom_bond.atom_site_auth_atom_id_1' _item.mandatory_code no save_ save__geom_bond.atom_site_auth_asym_id_1 _item_description.description ; An optional identifier of the first of the two atom sites that define the bond. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_geom_bond.atom_site_auth_asym_id_1' _item.mandatory_code no save_ save__geom_bond.atom_site_auth_comp_id_1 _item_description.description ; An optional identifier of the first of the two atom sites that define the bond. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_geom_bond.atom_site_auth_comp_id_1' _item.mandatory_code no save_ save__geom_bond.atom_site_auth_seq_id_1 _item_description.description ; An optional identifier of the first of the two atom sites that define the bond. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_geom_bond.atom_site_auth_seq_id_1' _item.mandatory_code no save_ save__geom_bond.atom_site_auth_atom_id_2 _item_description.description ; An optional identifier of the second of the two atom sites that define the bond. This data item is a pointer to _atom_site.auth_atom_id in the ATOM_SITE category. ; _item.name '_geom_bond.atom_site_auth_atom_id_2' _item.mandatory_code no save_ save__geom_bond.atom_site_auth_asym_id_2 _item_description.description ; An optional identifier of the second of the two atom sites that define the bond. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_geom_bond.atom_site_auth_asym_id_2' _item.mandatory_code no save_ save__geom_bond.atom_site_auth_comp_id_2 _item_description.description ; An optional identifier of the second of the two atom sites that define the bond. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_geom_bond.atom_site_auth_comp_id_2' _item.mandatory_code no save_ save__geom_bond.atom_site_auth_seq_id_2 _item_description.description ; An optional identifier of the second of the two atom sites that define the bond. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_geom_bond.atom_site_auth_seq_id_2' _item.mandatory_code no save_ save__geom_bond.dist _item_description.description ; The intramolecular bond distance in angstroms. ; _item.name '_geom_bond.dist' _item.category_id geom_bond _item.mandatory_code no _item_aliases.alias_name '_geom_bond_distance' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_geom_bond.dist_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code angstroms save_ save__geom_bond.dist_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _geom_bond.dist. ; _item.name '_geom_bond.dist_esd' _item.category_id geom_bond _item.mandatory_code no # _item_default.value 0.0 _item_related.related_name '_geom_bond.dist' _item_related.function_code associated_value _item_type.code float _item_units.code angstroms save_ save__geom_bond.publ_flag _item_description.description ; This code signals whether the bond distance is referred to in a publication or should be placed in a list of significant bond distances. ; _item.name '_geom_bond.publ_flag' _item.category_id geom_bond _item.mandatory_code no _item_aliases.alias_name '_geom_bond_publ_flag' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail no 'do not include bond in special list' n 'abbreviation for "no"' yes 'do include bond in special list' y 'abbreviation for "yes"' save_ save__geom_bond.site_symmetry_1 _item_description.description ; The symmetry code of the first of the two atom sites that define the bond. ; _item.name '_geom_bond.site_symmetry_1' _item.category_id geom_bond _item.mandatory_code yes _item_aliases.alias_name '_geom_bond_site_symmetry_1' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_default.value 1_555 _item_type.code symop loop_ _item_examples.case _item_examples.detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' save_ save__geom_bond.site_symmetry_2 _item_description.description ; The symmetry code of the second of the two atom sites that define the bond. ; _item.name '_geom_bond.site_symmetry_2' _item.category_id geom_bond _item.mandatory_code yes _item_aliases.alias_name '_geom_bond_site_symmetry_2' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_default.value 1_555 _item_type.code symop loop_ _item_examples.case _item_examples.detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' save_ ################## ## GEOM_CONTACT ## ################## save_geom_contact _category.description ; Data items in the GEOM_CONTACT category record details about interatomic contacts as calculated from the contents of the ATOM, CELL and SYMMETRY data. ; _category.id geom_contact _category.mandatory_code no loop_ _category_key.name '_geom_contact.atom_site_id_1' '_geom_contact.atom_site_id_2' '_geom_contact.site_symmetry_1' '_geom_contact.site_symmetry_2' loop_ _category_group.id 'inclusive_group' 'geom_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on data set CLPHO6 of Ferguson, Ruhl, McKervey & Browne [Acta Cryst. (1992), C48, 2262-2264]. ; ; loop_ _geom_contact.atom_site_id_1 _geom_contact.atom_site_id_2 _geom_contact.dist _geom_contact.dist_esd _geom_contact.site_symmetry_1 _geom_contact.site_symmetry_2 _geom_contact.publ_flag O(1) O(2) 2.735 0.003 . . yes H(O1) O(2) 1.82 . . . no ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__geom_contact.atom_site_id_1 _item_description.description ; The identifier of the first of the two atom sites that define the contact. This data item is a pointer to _atom_site.id in the ATOM_SITE category. ; _item.name '_geom_contact.atom_site_id_1' _item.mandatory_code yes _item_aliases.alias_name '_geom_contact_atom_site_label_1' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_dependent.dependent_name '_geom_contact.atom_site_id_2' save_ save__geom_contact.atom_site_label_alt_id_1 _item_description.description ; An optional identifier of the first of the two atom sites that define the contact. This data item is a pointer to _atom_site.label_alt_id in the ATOM_SITE category. ; _item.name '_geom_contact.atom_site_label_alt_id_1' _item.mandatory_code no save_ save__geom_contact.atom_site_label_atom_id_1 _item_description.description ; An optional identifier of the first of the two atom sites that define the contact. This data item is a pointer to _atom_site.label_atom_id in the ATOM_SITE category. ; _item.name '_geom_contact.atom_site_label_atom_id_1' _item.mandatory_code no save_ save__geom_contact.atom_site_label_comp_id_1 _item_description.description ; An optional identifier of the first of the two atom sites that define the contact. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_geom_contact.atom_site_label_comp_id_1' _item.mandatory_code no save_ save__geom_contact.atom_site_label_seq_id_1 _item_description.description ; An optional identifier of the first of the two atom sites that define the contact. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_geom_contact.atom_site_label_seq_id_1' _item.mandatory_code no save_ save__geom_contact.atom_site_label_asym_id_1 _item_description.description ; An optional identifier of the first of the two atom sites that define the contact. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_geom_contact.atom_site_label_asym_id_1' _item.mandatory_code no save_ save__geom_contact.atom_site_id_2 _item_description.description ; The identifier of the second of the two atom sites that define the contact. This data item is a pointer to _atom_site.id in the ATOM_SITE category. ; _item.name '_geom_contact.atom_site_id_2' _item.mandatory_code yes _item_aliases.alias_name '_geom_contact_atom_site_label_2' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_dependent.dependent_name '_geom_contact.atom_site_id_1' save_ save__geom_contact.atom_site_label_alt_id_2 _item_description.description ; An optional identifier of the second of the two atom sites that define the contact. This data item is a pointer to _atom_site.label_alt_id in the ATOM_SITE category. ; _item.name '_geom_contact.atom_site_label_alt_id_2' _item.mandatory_code no save_ save__geom_contact.atom_site_label_atom_id_2 _item_description.description ; An optional identifier of the second of the two atom sites that define the contact. This data item is a pointer to _atom_site.label_atom_id in the ATOM_SITE category. ; _item.name '_geom_contact.atom_site_label_atom_id_2' _item.mandatory_code no save_ save__geom_contact.atom_site_label_comp_id_2 _item_description.description ; An optional identifier of the second of the two atom sites that define the contact. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_geom_contact.atom_site_label_comp_id_2' _item.mandatory_code no save_ save__geom_contact.atom_site_label_seq_id_2 _item_description.description ; An optional identifier of the second of the two atom sites that define the contact. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_geom_contact.atom_site_label_seq_id_2' _item.mandatory_code no save_ save__geom_contact.atom_site_label_asym_id_2 _item_description.description ; An optional identifier of the second of the two atom sites that define the contact. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_geom_contact.atom_site_label_asym_id_2' _item.mandatory_code no save_ save__geom_contact.atom_site_auth_atom_id_1 _item_description.description ; An optional identifier of the first of the two atom sites that define the contact. This data item is a pointer to _atom_site.auth_atom_id in the ATOM_SITE category. ; _item.name '_geom_contact.atom_site_auth_atom_id_1' _item.mandatory_code no save_ save__geom_contact.atom_site_auth_asym_id_1 _item_description.description ; An optional identifier of the first of the two atom sites that define the contact. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_geom_contact.atom_site_auth_asym_id_1' _item.mandatory_code no save_ save__geom_contact.atom_site_auth_comp_id_1 _item_description.description ; An optional identifier of the first of the two atom sites that define the contact. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_geom_contact.atom_site_auth_comp_id_1' _item.mandatory_code no save_ save__geom_contact.atom_site_auth_seq_id_1 _item_description.description ; An optional identifier of the first of the two atom sites that define the contact. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_geom_contact.atom_site_auth_seq_id_1' _item.mandatory_code no save_ save__geom_contact.atom_site_auth_atom_id_2 _item_description.description ; An optional identifier of the second of the two atom sites that define the contact. This data item is a pointer to _atom_site.auth_atom_id in the ATOM_SITE category. ; _item.name '_geom_contact.atom_site_auth_atom_id_2' _item.mandatory_code no save_ save__geom_contact.atom_site_auth_asym_id_2 _item_description.description ; An optional identifier of the second of the two atom sites that define the contact. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_geom_contact.atom_site_auth_asym_id_2' _item.mandatory_code no save_ save__geom_contact.atom_site_auth_comp_id_2 _item_description.description ; An optional identifier of the second of the two atom sites that define the contact. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_geom_contact.atom_site_auth_comp_id_2' _item.mandatory_code no save_ save__geom_contact.atom_site_auth_seq_id_2 _item_description.description ; An optional identifier of the second of the two atom sites that define the contact. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_geom_contact.atom_site_auth_seq_id_2' _item.mandatory_code no save_ save__geom_contact.dist _item_description.description ; The interatomic contact distance in angstroms. ; _item.name '_geom_contact.dist' _item.category_id geom_contact _item.mandatory_code no _item_aliases.alias_name '_geom_contact_distance' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_geom_contact.dist_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code angstroms save_ save__geom_contact.dist_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _geom_contact.dist. ; _item.name '_geom_contact.dist_esd' _item.category_id geom_contact _item.mandatory_code no # _item_default.value 0.0 _item_related.related_name '_geom_contact.dist' _item_related.function_code associated_value _item_type.code float _item_units.code angstroms save_ save__geom_contact.publ_flag _item_description.description ; This code signals whether the contact distance is referred to in a publication or should be placed in a list of significant contact distances. ; _item.name '_geom_contact.publ_flag' _item.category_id geom_contact _item.mandatory_code no _item_aliases.alias_name '_geom_contact_publ_flag' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail no 'do not include distance in special list' n 'abbreviation for "no"' yes 'do include distance in special list' y 'abbreviation for "yes"' save_ save__geom_contact.site_symmetry_1 _item_description.description ; The symmetry code of the first of the two atom sites that define the contact. ; _item.name '_geom_contact.site_symmetry_1' _item.category_id geom_contact _item.mandatory_code yes _item_aliases.alias_name '_geom_contact_site_symmetry_1' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_default.value 1_555 _item_type.code symop loop_ _item_examples.case _item_examples.detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' save_ save__geom_contact.site_symmetry_2 _item_description.description ; The symmetry code of the second of the two atom sites that define the contact. ; _item.name '_geom_contact.site_symmetry_2' _item.category_id geom_contact _item.mandatory_code yes _item_aliases.alias_name '_geom_contact_site_symmetry_2' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_default.value 1_555 _item_type.code symop loop_ _item_examples.case _item_examples.detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' save_ ################ ## GEOM_HBOND ## ################ save_geom_hbond _category.description ; Data items in the GEOM_HBOND category record details about hydrogen bonds as calculated from the contents of the ATOM, CELL and SYMMETRY data. ; _category.id geom_hbond _category.mandatory_code no loop_ _category_key.name '_geom_hbond.atom_site_id_A' '_geom_hbond.atom_site_id_D' '_geom_hbond.atom_site_id_H' '_geom_hbond.site_symmetry_A' '_geom_hbond.site_symmetry_D' '_geom_hbond.site_symmetry_H' loop_ _category_group.id 'inclusive_group' 'geom_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on C~14~H~13~ClN~2~O.H~2~O, reported by Palmer, Puddle & Lisgarten [Acta Cryst. (1993), C49, 1777-1779]. ; ; loop_ _geom_hbond.atom_site_id_D _geom_hbond.atom_site_id_H _geom_hbond.atom_site_id_A _geom_hbond.dist_DH _geom_hbond.dist_HA _geom_hbond.dist_DA _geom_hbond.angle_DHA _geom_hbond.publ_flag N6 HN6 OW 0.888 1.921 2.801 169.6 yes OW HO2 O7 0.917 1.923 2.793 153.5 yes OW HO1 N10 0.894 1.886 2.842 179.7 yes ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__geom_hbond.angle_DHA _item_description.description ; The angle in degrees defined by the donor-, hydrogen- and acceptor-atom sites in a hydrogen bond. ; _item.name '_geom_hbond.angle_DHA' _item.category_id geom_hbond _item.mandatory_code no _item_aliases.alias_name '_geom_hbond_angle_DHA' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_geom_hbond.angle_DHA_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code angstroms save_ save__geom_hbond.angle_DHA_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _geom_hbond.angle_DHA. ; _item.name '_geom_hbond.angle_DHA_esd' _item.category_id geom_hbond _item.mandatory_code no # _item_default.value 0.0 _item_related.related_name '_geom_hbond.angle_DHA' _item_related.function_code associated_value _item_type.code float _item_units.code angstroms save_ save__geom_hbond.atom_site_id_A _item_description.description ; The identifier of the acceptor-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_id_A' _item.mandatory_code yes _item_aliases.alias_name '_geom_hbond_atom_site_label_A' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_geom_hbond.atom_site_id_D' '_geom_hbond.atom_site_id_H' save_ save__geom_hbond.atom_site_label_alt_id_A _item_description.description ; An optional identifier of the acceptor-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.label_alt_id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_label_alt_id_A' _item.mandatory_code no save_ save__geom_hbond.atom_site_label_asym_id_A _item_description.description ; An optional identifier of the acceptor-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_label_asym_id_A' _item.mandatory_code no save_ save__geom_hbond.atom_site_label_atom_id_A _item_description.description ; An optional identifier of the acceptor-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.label_atom_id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_label_atom_id_A' _item.mandatory_code no save_ save__geom_hbond.atom_site_label_comp_id_A _item_description.description ; An optional identifier of the acceptor-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_label_comp_id_A' _item.mandatory_code no save_ save__geom_hbond.atom_site_label_seq_id_A _item_description.description ; An optional identifier of the acceptor-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_label_seq_id_A' _item.mandatory_code no save_ save__geom_hbond.atom_site_id_D _item_description.description ; The identifier of the donor-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_id_D' _item.mandatory_code yes _item_aliases.alias_name '_geom_hbond_atom_site_label_D' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_geom_hbond.atom_site_id_A' '_geom_hbond.atom_site_id_H' save_ save__geom_hbond.atom_site_label_alt_id_D _item_description.description ; An optional identifier of the donor-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.label_alt_id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_label_alt_id_D' _item.mandatory_code no save_ save__geom_hbond.atom_site_label_asym_id_D _item_description.description ; An optional identifier of the donor-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_label_asym_id_D' _item.mandatory_code no save_ save__geom_hbond.atom_site_label_atom_id_D _item_description.description ; An optional identifier of the donor-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.label_atom_id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_label_atom_id_D' _item.mandatory_code no save_ save__geom_hbond.atom_site_label_comp_id_D _item_description.description ; An optional identifier of the donor-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_label_comp_id_D' _item.mandatory_code no save_ save__geom_hbond.atom_site_label_seq_id_D _item_description.description ; An optional identifier of the donor-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_label_seq_id_D' _item.mandatory_code no save_ save__geom_hbond.atom_site_id_H _item_description.description ; The identifier of the hydrogen-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_id_H' _item.mandatory_code yes _item_aliases.alias_name '_geom_hbond_atom_site_label_H' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_geom_hbond.atom_site_id_A' '_geom_hbond.atom_site_id_D' save_ save__geom_hbond.atom_site_label_alt_id_H _item_description.description ; An optional identifier of the hydrogen-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.label_alt_id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_label_alt_id_H' _item.mandatory_code no save_ save__geom_hbond.atom_site_label_asym_id_H _item_description.description ; An optional identifier of the hydrogen-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_label_asym_id_H' _item.mandatory_code no save_ save__geom_hbond.atom_site_label_atom_id_H _item_description.description ; An optional identifier of the hydrogen-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.label_atom_id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_label_atom_id_H' _item.mandatory_code no save_ save__geom_hbond.atom_site_label_comp_id_H _item_description.description ; An optional identifier of the hydrogen-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_label_comp_id_H' _item.mandatory_code no save_ save__geom_hbond.atom_site_label_seq_id_H _item_description.description ; An optional identifier of the hydrogen-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_label_seq_id_H' _item.mandatory_code no save_ save__geom_hbond.atom_site_auth_asym_id_A _item_description.description ; An optional identifier of the acceptor-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_auth_asym_id_A' _item.mandatory_code no save_ save__geom_hbond.atom_site_auth_atom_id_A _item_description.description ; An optional identifier of the acceptor-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.auth_atom_id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_auth_atom_id_A' _item.mandatory_code no save_ save__geom_hbond.atom_site_auth_comp_id_A _item_description.description ; An optional identifier of the acceptor-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_auth_comp_id_A' _item.mandatory_code no save_ save__geom_hbond.atom_site_auth_seq_id_A _item_description.description ; An optional identifier of the acceptor-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_auth_seq_id_A' _item.mandatory_code no save_ save__geom_hbond.atom_site_auth_asym_id_D _item_description.description ; An optional identifier of the donor-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_auth_asym_id_D' _item.mandatory_code no save_ save__geom_hbond.atom_site_auth_atom_id_D _item_description.description ; An optional identifier of the donor-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.auth_atom_id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_auth_atom_id_D' _item.mandatory_code no save_ save__geom_hbond.atom_site_auth_comp_id_D _item_description.description ; An optional identifier of the donor-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_auth_comp_id_D' _item.mandatory_code no save_ save__geom_hbond.atom_site_auth_seq_id_D _item_description.description ; An optional identifier of the donor-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_auth_seq_id_D' _item.mandatory_code no save_ save__geom_hbond.atom_site_auth_asym_id_H _item_description.description ; An optional identifier of the hydrogen-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_auth_asym_id_H' _item.mandatory_code no save_ save__geom_hbond.atom_site_auth_atom_id_H _item_description.description ; An optional identifier of the hydrogen-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.auth_atom_id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_auth_atom_id_H' _item.mandatory_code no save_ save__geom_hbond.atom_site_auth_comp_id_H _item_description.description ; An optional identifier of the hydrogen-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_auth_comp_id_H' _item.mandatory_code no save_ save__geom_hbond.atom_site_auth_seq_id_H _item_description.description ; An optional identifier of the hydrogen-atom site that defines the hydrogen bond. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_geom_hbond.atom_site_auth_seq_id_H' _item.mandatory_code no save_ save__geom_hbond.dist_DA _item_description.description ; The distance in angstroms between the donor- and acceptor-atom sites in a hydrogen bond. ; _item.name '_geom_hbond.dist_DA' _item.category_id geom_hbond _item.mandatory_code no _item_aliases.alias_name '_geom_hbond_distance_DA' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_geom_hbond.dist_DA_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code angstroms save_ save__geom_hbond.dist_DA_esd _item_description.description ; The standard uncertainty (estimated standard deviation) in angstroms of _geom_hbond.dist_DA. ; _item.name '_geom_hbond.dist_DA_esd' _item.category_id geom_hbond _item.mandatory_code no # _item_default.value 0.0 _item_related.related_name '_geom_hbond.dist_DH' _item_related.function_code associated_value _item_type.code float _item_units.code angstroms save_ save__geom_hbond.dist_DH _item_description.description ; The distance in angstroms between the donor- and hydrogen-atom sites in a hydrogen bond. ; _item.name '_geom_hbond.dist_DH' _item.category_id geom_hbond _item.mandatory_code no _item_aliases.alias_name '_geom_hbond_distance_DH' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_geom_hbond.dist_DH_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code angstroms save_ save__geom_hbond.dist_DH_esd _item_description.description ; The standard uncertainty (estimated standard deviation) in angstroms of _geom_hbond.dist_DH. ; _item.name '_geom_hbond.dist_DH_esd' _item.category_id geom_hbond _item.mandatory_code no # _item_default.value 0.0 _item_related.related_name '_geom_hbond.dist_DH' _item_related.function_code associated_value _item_type.code float _item_units.code angstroms save_ save__geom_hbond.dist_HA _item_description.description ; The distance in angstroms between the hydrogen- and acceptor- atom sites in a hydrogen bond. ; _item.name '_geom_hbond.dist_HA' _item.category_id geom_hbond _item.mandatory_code no _item_aliases.alias_name '_geom_hbond_distance_HA' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_geom_hbond.dist_HA_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code angstroms save_ save__geom_hbond.dist_HA_esd _item_description.description ; The standard uncertainty (estimated standard deviation) in angstroms of _geom_hbond.dist_HA. ; _item.name '_geom_hbond.dist_HA_esd' _item.category_id geom_hbond _item.mandatory_code no # _item_default.value 0.0 _item_related.related_name '_geom_hbond.dist_HA' _item_related.function_code associated_value _item_type.code float _item_units.code angstroms save_ save__geom_hbond.publ_flag _item_description.description ; This code signals whether the hydrogen-bond information is referred to in a publication or should be placed in a table of significant hydrogen-bond geometry. ; _item.name '_geom_hbond.publ_flag' _item.category_id geom_hbond _item.mandatory_code no _item_aliases.alias_name '_geom_hbond_publ_flag' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail no 'do not include bond in special list' n 'abbreviation for "no"' yes 'do include bond in special list' y 'abbreviation for "yes"' save_ save__geom_hbond.site_symmetry_A _item_description.description ; The symmetry code of the acceptor-atom site that defines the hydrogen bond. ; _item.name '_geom_hbond.site_symmetry_A' _item.category_id geom_hbond _item.mandatory_code yes _item_aliases.alias_name '_geom_hbond_site_symmetry_A' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_default.value 1_555 _item_type.code symop loop_ _item_examples.case _item_examples.detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' save_ save__geom_hbond.site_symmetry_D _item_description.description ; The symmetry code of the donor-atom site that defines the hydrogen bond. ; _item.name '_geom_hbond.site_symmetry_D' _item.category_id geom_hbond _item.mandatory_code yes _item_aliases.alias_name '_geom_hbond_site_symmetry_D' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_default.value 1_555 _item_type.code symop loop_ _item_examples.case _item_examples.detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' save_ save__geom_hbond.site_symmetry_H _item_description.description ; The symmetry code of the hydrogen-atom site that defines the hydrogen bond. ; _item.name '_geom_hbond.site_symmetry_H' _item.category_id geom_hbond _item.mandatory_code yes _item_aliases.alias_name '_geom_hbond_site_symmetry_H' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_default.value 1_555 _item_type.code symop loop_ _item_examples.case _item_examples.detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' save_ ################## ## GEOM_TORSION ## ################## save_geom_torsion _category.description ; Data items in the GEOM_TORSION category record details about torsion angles as calculated from the contents of the ATOM, CELL and SYMMETRY data. The vector direction _geom_torsion.atom_site_id_2 to _geom_torsion.atom_site_id_3 is the viewing direction, and the torsion angle is the angle of twist required to superimpose the projection of the vector between site 2 and site 1 onto the projection of the vector between site 3 and site 4. Clockwise torsions are positive, anticlockwise torsions are negative. Ref: Klyne, W. & Prelog, V. (1960). Experientia, 16, 521-523. ; _category.id geom_torsion _category.mandatory_code no loop_ _category_key.name '_geom_torsion.atom_site_id_1' '_geom_torsion.atom_site_id_2' '_geom_torsion.atom_site_id_3' '_geom_torsion.atom_site_id_4' '_geom_torsion.site_symmetry_1' '_geom_torsion.site_symmetry_2' '_geom_torsion.site_symmetry_3' '_geom_torsion.site_symmetry_4' loop_ _category_group.id 'inclusive_group' 'geom_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on data set CLPHO6 of Ferguson, Ruhl, McKervey & Browne [Acta Cryst. (1992), C48, 2262-2264]. ; ; loop_ _geom_torsion.atom_site_id_1 _geom_torsion.atom_site_id_2 _geom_torsion.atom_site_id_3 _geom_torsion.atom_site_id_4 _geom_torsion.value _geom_torsion.site_symmetry_1 _geom_torsion.site_symmetry_2 _geom_torsion.site_symmetry_3 _geom_torsion.site_symmetry_4 _geom_torsion.publ_flag C(9) O(2) C(7) C(2) 71.8 . . . . yes C(7) O(2) C(9) C(10) -168.0 . . . 2_666 yes C(10) O(3) C(8) C(6) -167.7 . . . . yes C(8) O(3) C(10) C(9) -69.7 . . . 2_666 yes O(1) C(1) C(2) C(3) -179.5 . . . . no O(1) C(1) C(2) C(7) -0.6 . . . . no ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__geom_torsion.atom_site_id_1 _item_description.description ; The identifier of the first of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_id_1' _item.mandatory_code yes _item_aliases.alias_name '_geom_torsion_atom_site_label_1' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_geom_torsion.atom_site_id_2' '_geom_torsion.atom_site_id_3' '_geom_torsion.atom_site_id_4' save_ save__geom_torsion.atom_site_label_alt_id_1 _item_description.description ; An optional identifier of the first of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.label_alt_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_label_alt_id_1' _item.mandatory_code no save_ save__geom_torsion.atom_site_label_atom_id_1 _item_description.description ; An optional identifier of the first of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.label_atom_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_label_atom_id_1' _item.mandatory_code no save_ save__geom_torsion.atom_site_label_comp_id_1 _item_description.description ; An optional identifier of the first of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_label_comp_id_1' _item.mandatory_code no save_ save__geom_torsion.atom_site_label_seq_id_1 _item_description.description ; An optional identifier of the first of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_label_seq_id_1' _item.mandatory_code no save_ save__geom_torsion.atom_site_label_asym_id_1 _item_description.description ; An optional identifier of the first of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_label_asym_id_1' _item.mandatory_code no save_ save__geom_torsion.atom_site_id_2 _item_description.description ; The identifier of the second of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_id_2' _item.mandatory_code yes _item_aliases.alias_name '_geom_torsion_atom_site_label_2' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_geom_torsion.atom_site_id_1' '_geom_torsion.atom_site_id_3' '_geom_torsion.atom_site_id_4' save_ save__geom_torsion.atom_site_label_alt_id_2 _item_description.description ; An optional identifier of the second of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.label_alt_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_label_alt_id_2' _item.mandatory_code no save_ save__geom_torsion.atom_site_label_atom_id_2 _item_description.description ; An optional identifier of the second of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.label_atom_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_label_atom_id_2' _item.mandatory_code no save_ save__geom_torsion.atom_site_label_comp_id_2 _item_description.description ; An optional identifier of the second of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_label_comp_id_2' _item.mandatory_code no save_ save__geom_torsion.atom_site_label_seq_id_2 _item_description.description ; An optional identifier of the second of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_label_seq_id_2' _item.mandatory_code no save_ save__geom_torsion.atom_site_label_asym_id_2 _item_description.description ; An optional identifier of the second of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_label_asym_id_2' _item.mandatory_code no save_ save__geom_torsion.atom_site_id_3 _item_description.description ; The identifier of the third of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_id_3' _item.mandatory_code yes _item_aliases.alias_name '_geom_torsion_atom_site_label_3' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_geom_torsion.atom_site_id_1' '_geom_torsion.atom_site_id_2' '_geom_torsion.atom_site_id_4' save_ save__geom_torsion.atom_site_label_alt_id_3 _item_description.description ; An optional identifier of the third of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.label_alt_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_label_alt_id_3' _item.mandatory_code no save_ save__geom_torsion.atom_site_label_atom_id_3 _item_description.description ; An optional identifier of the third of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.label_atom_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_label_atom_id_3' _item.mandatory_code no save_ save__geom_torsion.atom_site_label_comp_id_3 _item_description.description ; An optional identifier of the third of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_label_comp_id_3' _item.mandatory_code no save_ save__geom_torsion.atom_site_label_seq_id_3 _item_description.description ; An optional identifier of the third of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_label_seq_id_3' _item.mandatory_code no save_ save__geom_torsion.atom_site_label_asym_id_3 _item_description.description ; An optional identifier of the third of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_label_asym_id_3' _item.mandatory_code no save_ save__geom_torsion.atom_site_id_4 _item_description.description ; The identifier of the fourth of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_id_4' _item.mandatory_code yes _item_aliases.alias_name '_geom_torsion_atom_site_label_4' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_geom_torsion.atom_site_id_1' '_geom_torsion.atom_site_id_2' '_geom_torsion.atom_site_id_3' save_ save__geom_torsion.atom_site_label_alt_id_4 _item_description.description ; An optional identifier of the fourth of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.label_alt_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_label_alt_id_4' _item.mandatory_code no save_ save__geom_torsion.atom_site_label_atom_id_4 _item_description.description ; An optional identifier of the fourth of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.label_atom_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_label_atom_id_4' _item.mandatory_code no save_ save__geom_torsion.atom_site_label_comp_id_4 _item_description.description ; An optional identifier of the fourth of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_label_comp_id_4' _item.mandatory_code no save_ save__geom_torsion.atom_site_label_seq_id_4 _item_description.description ; An optional identifier of the fourth of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_label_seq_id_4' _item.mandatory_code no save_ save__geom_torsion.atom_site_label_asym_id_4 _item_description.description ; An optional identifier of the fourth of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_label_asym_id_4' _item.mandatory_code no save_ save__geom_torsion.atom_site_auth_atom_id_1 _item_description.description ; An optional identifier of the first of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.auth_atom_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_auth_atom_id_1' _item.mandatory_code no save_ save__geom_torsion.atom_site_auth_asym_id_1 _item_description.description ; An optional identifier of the first of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_auth_asym_id_1' _item.mandatory_code no save_ save__geom_torsion.atom_site_auth_comp_id_1 _item_description.description ; An optional identifier of the first of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_auth_comp_id_1' _item.mandatory_code no save_ save__geom_torsion.atom_site_auth_seq_id_1 _item_description.description ; An optional identifier of the first of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_auth_seq_id_1' _item.mandatory_code no save_ save__geom_torsion.atom_site_auth_atom_id_2 _item_description.description ; An optional identifier of the second of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.auth_atom_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_auth_atom_id_2' _item.mandatory_code no save_ save__geom_torsion.atom_site_auth_asym_id_2 _item_description.description ; An optional identifier of the second of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_auth_asym_id_2' _item.mandatory_code no save_ save__geom_torsion.atom_site_auth_comp_id_2 _item_description.description ; An optional identifier of the second of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_auth_comp_id_2' _item.mandatory_code no save_ save__geom_torsion.atom_site_auth_seq_id_2 _item_description.description ; An optional identifier of the second of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_auth_seq_id_2' _item.mandatory_code no save_ save__geom_torsion.atom_site_auth_atom_id_3 _item_description.description ; An optional identifier of the third of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.auth_atom_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_auth_atom_id_3' _item.mandatory_code no save_ save__geom_torsion.atom_site_auth_asym_id_3 _item_description.description ; An optional identifier of the third of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_auth_asym_id_3' _item.mandatory_code no save_ save__geom_torsion.atom_site_auth_comp_id_3 _item_description.description ; An optional identifier of the third of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_auth_comp_id_3' _item.mandatory_code no save_ save__geom_torsion.atom_site_auth_seq_id_3 _item_description.description ; An optional identifier of the third of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_auth_seq_id_3' _item.mandatory_code no save_ save__geom_torsion.atom_site_auth_atom_id_4 _item_description.description ; An optional identifier of the fourth of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.auth_atom_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_auth_atom_id_4' _item.mandatory_code no save_ save__geom_torsion.atom_site_auth_asym_id_4 _item_description.description ; An optional identifier of the fourth of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_auth_asym_id_4' _item.mandatory_code no save_ save__geom_torsion.atom_site_auth_comp_id_4 _item_description.description ; An optional identifier of the fourth of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_auth_comp_id_4' _item.mandatory_code no save_ save__geom_torsion.atom_site_auth_seq_id_4 _item_description.description ; An optional identifier of the fourth of the four atom sites that define the torsion angle. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_geom_torsion.atom_site_auth_seq_id_4' _item.mandatory_code no save_ save__geom_torsion.publ_flag _item_description.description ; This code signals whether the torsion angle is referred to in a publication or should be placed in a table of significant torsion angles. ; _item.name '_geom_torsion.publ_flag' _item.category_id geom_torsion _item.mandatory_code no _item_aliases.alias_name '_geom_torsion_publ_flag' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail no 'do not include angle in special list' n 'abbreviation for "no"' yes 'do include angle in special list' y 'abbreviation for "yes"' save_ save__geom_torsion.site_symmetry_1 _item_description.description ; The symmetry code of the first of the four atom sites that define the torsion angle. ; _item.name '_geom_torsion.site_symmetry_1' _item.category_id geom_torsion _item.mandatory_code yes _item_aliases.alias_name '_geom_torsion_site_symmetry_1' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_default.value 1_555 _item_type.code symop loop_ _item_examples.case _item_examples.detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' save_ save__geom_torsion.site_symmetry_2 _item_description.description ; The symmetry code of the second of the four atom sites that define the torsion angle. ; _item.name '_geom_torsion.site_symmetry_2' _item.category_id geom_torsion _item.mandatory_code yes _item_aliases.alias_name '_geom_torsion_site_symmetry_2' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_default.value 1_555 _item_type.code symop loop_ _item_examples.case _item_examples.detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' save_ save__geom_torsion.site_symmetry_3 _item_description.description ; The symmetry code of the third of the four atom sites that define the torsion angle. ; _item.name '_geom_torsion.site_symmetry_3' _item.category_id geom_torsion _item.mandatory_code yes _item_aliases.alias_name '_geom_torsion_site_symmetry_3' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_default.value 1_555 _item_type.code symop loop_ _item_examples.case _item_examples.detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' save_ save__geom_torsion.site_symmetry_4 _item_description.description ; The symmetry code of the fourth of the four atom sites that define the torsion angle. ; _item.name '_geom_torsion.site_symmetry_4' _item.category_id geom_torsion _item.mandatory_code yes _item_aliases.alias_name '_geom_torsion_site_symmetry_4' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_default.value 1_555 _item_type.code symop loop_ _item_examples.case _item_examples.detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' save_ save__geom_torsion.value _item_description.description ; The value of the torsion angle in degrees. ; _item.name '_geom_torsion.value' _item.category_id geom_torsion _item.mandatory_code no _item_aliases.alias_name '_geom_torsion' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_related.related_name '_geom_torsion.value_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code degrees save_ save__geom_torsion.value_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _geom_torsion.value. ; _item.name '_geom_torsion.value_esd' _item.category_id geom_torsion _item.mandatory_code no # _item_default.value 0.0 _item_related.related_name '_geom_torsion.value' _item_related.function_code associated_value _item_type.code float _item_units.code degrees save_ ############# ## JOURNAL ## ############# save_journal _category.description ; Data items in the JOURNAL category record details about the book-keeping by the journal staff when processing a data block submitted for publication. The creator of a data block will not normally specify these data. The data names are not defined in the dictionary because they are for journal use only. ; _category.id journal _category.mandatory_code no _category_key.name '_journal.entry_id' loop_ _category_group.id 'inclusive_group' 'iucr_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on Acta Cryst. file for entry HL0007 [Willis, Beckwith & Tozer (1991). Acta Cryst. C47, 2276-2277]. ; ; _journal.entry_id 'TOZ' _journal.date_recd_electronic 1991-04-15 _journal.date_from_coeditor 1991-04-18 _journal.date_accepted 1991-04-18 _journal.date_printers_first 1991-08-07 _journal.date_proofs_out 1991-08-07 _journal.coeditor_code HL0007 _journal.techeditor_code C910963 _journal.coden_ASTM ACSCEE _journal.name_full 'Acta Crystallographica Section C' _journal.year 1991 _journal.volume 47 _journal.issue NOV91 _journal.page_first 2276 _journal.page_last 2277 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__journal.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_journal.entry_id' _item.mandatory_code yes save_ save__journal.coden_ASTM _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.coden_ASTM' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_coden_ASTM' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__journal.coden_Cambridge _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.coden_Cambridge' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_coden_Cambridge' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__journal.coeditor_address _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.coeditor_address' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_coeditor_address' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__journal.coeditor_code _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.coeditor_code' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_coeditor_code' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__journal.coeditor_email _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.coeditor_email' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_coeditor_email' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__journal.coeditor_fax _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.coeditor_fax' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_coeditor_fax' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__journal.coeditor_name _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.coeditor_name' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_coeditor_name' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__journal.coeditor_notes _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.coeditor_notes' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_coeditor_notes' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__journal.coeditor_phone _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.coeditor_phone' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_coeditor_phone' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__journal.data_validation_number _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.data_validation_number' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_data_validation_number' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code code save_ save__journal.date_accepted _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.date_accepted' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_date_accepted' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code yyyy-mm-dd save_ save__journal.date_from_coeditor _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.date_from_coeditor' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_date_from_coeditor' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code yyyy-mm-dd save_ save__journal.date_to_coeditor _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.date_to_coeditor' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_date_to_coeditor' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code yyyy-mm-dd save_ save__journal.date_printers_final _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.date_printers_final' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_date_printers_final' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code yyyy-mm-dd save_ save__journal.date_printers_first _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.date_printers_first' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_date_printers_first' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code yyyy-mm-dd save_ save__journal.date_proofs_in _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.date_proofs_in' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_date_proofs_in' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code yyyy-mm-dd save_ save__journal.date_proofs_out _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.date_proofs_out' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_date_proofs_out' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code yyyy-mm-dd save_ save__journal.date_recd_copyright _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.date_recd_copyright' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_date_recd_copyright' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code yyyy-mm-dd save_ save__journal.date_recd_electronic _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.date_recd_electronic' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_date_recd_electronic' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code yyyy-mm-dd save_ save__journal.date_recd_hard_copy _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.date_recd_hard_copy' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_date_recd_hard_copy' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code yyyy-mm-dd save_ save__journal.issue _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.issue' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_issue' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__journal.language _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.language' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_language' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__journal.name_full _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.name_full' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_name_full' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__journal.page_first _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.page_first' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_page_first' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__journal.page_last _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.page_last' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_page_last' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__journal.paper_category _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.paper_category' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_paper_category' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__journal.suppl_publ_number _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.suppl_publ_number' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_suppl_publ_number' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__journal.suppl_publ_pages _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.suppl_publ_pages' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_suppl_publ_pages' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__journal.techeditor_address _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.techeditor_address' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_techeditor_address' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__journal.techeditor_code _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.techeditor_code' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_techeditor_code' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__journal.techeditor_email _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.techeditor_email' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_techeditor_email' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__journal.techeditor_fax _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.techeditor_fax' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_techeditor_fax' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__journal.techeditor_name _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.techeditor_name' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_techeditor_name' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__journal.techeditor_notes _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.techeditor_notes' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_techeditor_notes' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__journal.techeditor_phone _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.techeditor_phone' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_techeditor_phone' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__journal.volume _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.volume' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_volume' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__journal.year _item_description.description ; Journal data items are defined by the journal staff. ; _item.name '_journal.year' _item.category_id journal _item.mandatory_code no _item_aliases.alias_name '_journal_year' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ ################### ## JOURNAL_INDEX ## ################### save_journal_index _category.description ; Data items in the JOURNAL_INDEX category are used to list terms used to generate the journal indexes. The creator of a data block will not normally specify these data items. ; _category.id journal_index _category.mandatory_code no loop_ _category_key.name '_journal_index.type' '_journal_index.term' loop_ _category_group.id 'inclusive_group' 'iucr_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on a paper by Zhu, Reynolds, Klein & Trudell [Acta Cryst. (1994), C50, 2067-2069]. ; ; loop_ _journal_index.type _journal_index.term _journal_index.subterm O C16H19NO4 . S alkaloids (-)-norcocaine S (-)-norcocaine . S ; [2R,3S-(2\b,3\b)]-methyl 3-(benzoyloxy)-8-azabicyclo[3.2.1]octane-2-carboxylate ; . ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__journal_index.subterm _item_description.description ; Journal index data items are defined by the journal staff. ; _item.name '_journal_index.subterm' _item.category_id journal_index _item.mandatory_code no _item_aliases.alias_name '_journal_index_subterm' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__journal_index.term _item_description.description ; Journal index data items are defined by the journal staff. ; _item.name '_journal_index.term' _item.category_id journal_index _item.mandatory_code no _item_aliases.alias_name '_journal_index_term' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__journal_index.type _item_description.description ; Journal index data items are defined by the journal staff. ; _item.name '_journal_index.type' _item.category_id journal_index _item.mandatory_code no _item_aliases.alias_name '_journal_index_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ ############# ## PHASING ## ############# save_phasing _category.description ; Data items in the PHASING category record details about the phasing of the structure, listing the various methods used in the phasing process. Details about the application of each method are listed in the appropriate subcategories. ; _category.id phasing _category.mandatory_code no _category_key.name '_phasing.method' loop_ _category_group.id 'inclusive_group' 'phasing_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - hypothetical example. ; ; loop_ _phasing.method 'mir' 'averaging' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__phasing.method _item_description.description ; A listing of the method or methods used to phase this structure. ; _item.name '_phasing.method' _item.category_id phasing _item.mandatory_code yes _item_type.code ucode loop_ _item_examples.case _item_examples.detail abinitio ; phasing by ab initio methods ; averaging ; phase improvement by averaging over multiple images of the structure ; dm ; phasing by direct methods ; isas ; phasing by iterative single-wavelength anomalous scattering ; isir ; phasing by iterative single-wavelength isomorphous replacement ; isomorphous ; phasing beginning with phases calculated from an isomorphous structure ; mad ; phasing by multiple-wavelength anomalous dispersion ; mir ; phasing by multiple isomorphous replacement ; miras ; phasing by multiple isomorphous replacement with anomalous scattering ; mr ; phasing by molecular replacement ; sir ; phasing by single isomorphous replacement ; siras ; phasing by single isomorphous replacement with anomalous scattering ; save_ ####################### ## PHASING_AVERAGING ## ####################### save_phasing_averaging _category.description ; Data items in the PHASING_AVERAGING category record details about the phasing of the structure where methods involving averaging of multiple observations of the molecule in the asymmetric unit are involved. ; _category.id phasing_averaging _category.mandatory_code no _category_key.name '_phasing_averaging.entry_id' loop_ _category_group.id 'inclusive_group' 'phasing_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - hypothetical example. ; ; _phasing_averaging.entry_id 'EXAMHYPO' _phasing_averaging.method ; Iterative threefold averaging alternating with phase extensions by 0.5 reciprocal lattice units per cycle. ; _phasing_averaging.details ; The position of the threefold axis was redetermined every five cycles. ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__phasing_averaging.details _item_description.description ; A description of special aspects of the averaging process. ; _item.name '_phasing_averaging.details' _item.category_id phasing_averaging _item.mandatory_code no _item_type.code text save_ save__phasing_averaging.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_phasing_averaging.entry_id' _item.mandatory_code yes save_ save__phasing_averaging.method _item_description.description ; A description of the phase-averaging phasing method used to phase this structure. Note that this is not the computer program used, which is described in the SOFTWARE category, but rather the method itself. This data item should be used to describe significant methodological options used within the phase-averaging program. ; _item.name '_phasing_averaging.method' _item.category_id phasing_averaging _item.mandatory_code no _item_type.code text save_ ######################### ## PHASING_ISOMORPHOUS ## ######################### save_phasing_isomorphous _category.description ; Data items in the PHASING_ISOMORPHOUS category record details about the phasing of the structure where a model isomorphous to the structure being phased was used to generate the initial phases. ; _category.id phasing_isomorphous _category.mandatory_code no _category_key.name '_phasing_isomorphous.entry_id' loop_ _category_group.id 'inclusive_group' 'phasing_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 4PHV and laboratory records for the structure corresponding to PDB entry 4PHV. ; ; _phasing_isomorphous.parent 'PDB entry 5HVP' _phasing_isomorphous.details ; The inhibitor and all solvent atoms were removed from the parent structure before beginning refinement. All static disorder present in the parent structure was also removed. ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__phasing_isomorphous.details _item_description.description ; A description of special aspects of the isomorphous phasing. ; _item.name '_phasing_isomorphous.details' _item.category_id phasing_isomorphous _item.mandatory_code no _item_type.code text _item_examples.case ; Residues 13-18 were eliminated from the starting model as it was anticipated that binding of the inhibitor would cause a structural rearrangement in this part of the structure. ; save_ save__phasing_isomorphous.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_phasing_isomorphous.entry_id' _item.mandatory_code yes save_ save__phasing_isomorphous.method _item_description.description ; A description of the isomorphous-phasing method used to phase this structure. Note that this is not the computer program used, which is described in the SOFTWARE category, but rather the method itself. This data item should be used to describe significant methodological options used within the isomorphous phasing program. ; _item.name '_phasing_isomorphous.method' _item.category_id phasing_isomorphous _item.mandatory_code no _item_type.code text _item_examples.case ; Iterative threefold averaging alternating with phase extension by 0.5 reciprocal lattice units per cycle. ; save_ save__phasing_isomorphous.parent _item_description.description ; Reference to the structure used to generate starting phases if the structure referenced in this data block was phased by virtue of being isomorphous to a known structure (e.g. a mutant that crystallizes in the same space group as the wild-type protein.) ; _item.name '_phasing_isomorphous.parent' _item.category_id phasing_isomorphous _item.mandatory_code no _item_type.code text save_ ################# ## PHASING_MAD ## ################# save_phasing_MAD _category.description ; Data items in the PHASING_MAD category record details about the phasing of the structure where methods involving multiple-wavelength anomalous-dispersion techniques are involved. ; _category.id phasing_MAD _category.mandatory_code no _category_key.name '_phasing_MAD.entry_id' loop_ _category_group.id 'inclusive_group' 'phasing_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on a paper by Shapiro et al. [Nature (London) (1995), 374, 327-337]. ; ; _phasing_MAD.entry_id 'NCAD' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__phasing_MAD.details _item_description.description ; A description of special aspects of the MAD phasing. ; _item.name '_phasing_MAD.details' _item.category_id phasing_MAD _item.mandatory_code no _item_type.code text save_ save__phasing_MAD.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_phasing_MAD.entry_id' _item.mandatory_code yes save_ save__phasing_MAD.method _item_description.description ; A description of the MAD phasing method used to phase this structure. Note that this is not the computer program used, which is described in the SOFTWARE category, but rather the method itself. This data item should be used to describe significant methodological options used within the MAD phasing program. ; _item.name '_phasing_MAD.method' _item.category_id phasing_MAD _item.mandatory_code no _item_type.code text save_ ####################### ## PHASING_MAD_CLUST ## ####################### save_phasing_MAD_clust _category.description ; Data items in the PHASING_MAD_CLUST category record details about a cluster of experiments that contributed to the generation of a set of phases. ; _category.id phasing_MAD_clust _category.mandatory_code no loop_ _category_key.name '_phasing_MAD_clust.expt_id' '_phasing_MAD_clust.id' loop_ _category_group.id 'inclusive_group' 'phasing_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on a paper by Shapiro et al. [Nature (London) (1995), 374, 327-337]. ; ; loop_ _phasing_MAD_clust.id _phasing_MAD_clust.expt_id _phasing_MAD_clust.number_set '4 wavelength' 1 4 '5 wavelength' 1 5 '5 wavelength' 2 5 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__phasing_MAD_clust.expt_id _item_description.description ; This data item is a pointer to _phasing_MAD_expt.id in the PHASING_MAD_EXPT category. ; _item.name '_phasing_MAD_clust.expt_id' _item.mandatory_code yes save_ save__phasing_MAD_clust.id _item_description.description ; The value of _phasing_MAD_clust.id must, together with _phasing_MAD_clust.expt_id, uniquely identify a record in the PHASING_MAD_CLUST list. Note that this item need not be a number; it can be any unique identifier. ; loop_ _item.name _item.category_id _item.mandatory_code '_phasing_MAD_clust.id' phasing_MAD_clust yes '_phasing_MAD_set.clust_id' phasing_MAD_set yes '_phasing_MAD_ratio.clust_id' phasing_MAD_ratio yes loop_ _item_linked.child_name _item_linked.parent_name '_phasing_MAD_set.clust_id' '_phasing_MAD_clust.id' '_phasing_MAD_ratio.clust_id' '_phasing_MAD_clust.id' _item_type.code code save_ save__phasing_MAD_clust.number_set _item_description.description ; The number of data sets in this cluster of data sets. ; _item.name '_phasing_MAD_clust.number_set' _item.category_id phasing_MAD_clust _item.mandatory_code no _item_type.code int save_ ###################### ## PHASING_MAD_EXPT ## ###################### save_phasing_MAD_expt _category.description ; Data items in the PHASING_MAD_EXPT category record details about a MAD phasing experiment, such as the number of experiments that were clustered together to produce a set of phases or the statistics for those phases. ; _category.id phasing_MAD_expt _category.mandatory_code no _category_key.name '_phasing_MAD_expt.id' loop_ _category_group.id 'inclusive_group' 'phasing_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on a paper by Shapiro et al. [Nature (London) (1995), 374, 327-337]. ; ; loop_ _phasing_MAD_expt.id _phasing_MAD_expt.number_clust _phasing_MAD_expt.R_normal_all _phasing_MAD_expt.R_normal_anom_scat _phasing_MAD_expt.delta_delta_phi _phasing_MAD_expt.delta_phi_sigma _phasing_MAD_expt.mean_fom 1 2 0.063 0.451 58.5 20.3 0.88 2 1 0.051 0.419 36.8 18.2 0.93 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__phasing_MAD_expt.delta_delta_phi _item_description.description ; The difference between two independent determinations of _phasing_MAD_expt.delta_phi. ; _item.name '_phasing_MAD_expt.delta_delta_phi' _item.category_id phasing_MAD_expt _item.mandatory_code no _item_type.code float save_ save__phasing_MAD_expt.delta_phi _item_description.description ; The phase difference between F~t~(h), the structure factor due to normal scattering from all atoms, and F~a~(h), the structure factor due to normal scattering from only the anomalous scatterers. ; _item.name '_phasing_MAD_expt.delta_phi' _item.category_id phasing_MAD_expt _item.mandatory_code no _item_type.code float _item_related.related_name '_phasing_MAD_expt.delta_phi_sigma' _item_related.function_code associated_esd save_ save__phasing_MAD_expt.delta_phi_sigma _item_description.description ; The standard uncertainty (estimated standard deviation) of _phasing_MAD_expt.delta_phi. ; _item.name '_phasing_MAD_expt.delta_phi_sigma' _item.category_id phasing_MAD_expt _item.mandatory_code no _item_related.related_name '_phasing_MAD_expt.delta_phi' _item_related.function_code associated_value _item_type.code float save_ save__phasing_MAD_expt.id _item_description.description ; The value of _phasing_MAD_expt.id must uniquely identify each record in the PHASING_MAD_EXPT list. ; loop_ _item.name _item.category_id _item.mandatory_code '_phasing_MAD_expt.id' phasing_MAD_expt yes '_phasing_MAD_clust.expt_id' phasing_MAD_clust yes '_phasing_MAD_set.expt_id' phasing_MAD_set yes '_phasing_MAD_ratio.expt_id' phasing_MAD_ratio yes loop_ _item_linked.child_name _item_linked.parent_name '_phasing_MAD_clust.expt_id' '_phasing_MAD_expt.id' '_phasing_MAD_set.expt_id' '_phasing_MAD_expt.id' '_phasing_MAD_ratio.expt_id' '_phasing_MAD_expt.id' _item_type.code code save_ save__phasing_MAD_expt.mean_fom _item_description.description ; The mean figure of merit. ; _item.name '_phasing_MAD_expt.mean_fom' _item.category_id phasing_MAD_expt _item.mandatory_code no _item_type.code float save_ save__phasing_MAD_expt.number_clust _item_description.description ; The number of clusters of data sets in this phasing experiment. ; _item.name '_phasing_MAD_expt.number_clust' _item.category_id phasing_MAD_expt _item.mandatory_code no _item_type.code int save_ save__phasing_MAD_expt.R_normal_all _item_description.description ; Definition... ; _item.name '_phasing_MAD_expt.R_normal_all' _item.category_id phasing_MAD_expt _item.mandatory_code no _item_type.code float save_ save__phasing_MAD_expt.R_normal_anom_scat _item_description.description ; Definition... ; _item.name '_phasing_MAD_expt.R_normal_anom_scat' _item.category_id phasing_MAD_expt _item.mandatory_code no _item_type.code float save_ ####################### ## PHASING_MAD_RATIO ## ####################### save_phasing_MAD_ratio _category.description ; Data items in the PHASING_MAD_RATIO category record the ratios of phasing statistics between pairs of data sets in a MAD phasing experiment, in given shells of resolution. ; _category.id phasing_MAD_ratio _category.mandatory_code no loop_ _category_key.name '_phasing_MAD_ratio.clust_id' '_phasing_MAD_ratio.expt_id' '_phasing_MAD_ratio.wavelength_1' '_phasing_MAD_ratio.wavelength_2' loop_ _category_group.id 'inclusive_group' 'phasing_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on a paper by Shapiro et al. [Nature (London) (1995), 374, 327-337]. ; ; loop_ _phasing_MAD_ratio.expt_id _phasing_MAD_ratio.clust_id _phasing_MAD_ratio.wavelength_1 _phasing_MAD_ratio.wavelength_2 _phasing_MAD_ratio.d_res_low _phasing_MAD_ratio.d_res_high _phasing_MAD_ratio.ratio_two_wl _phasing_MAD_ratio.ratio_one_wl _phasing_MAD_ratio.ratio_one_wl_centric 1 '4 wavelength' 1.4013 1.4013 20.00 4.00 . 0.084 0.076 1 '4 wavelength' 1.4013 1.3857 20.00 4.00 0.067 . . 1 '4 wavelength' 1.4013 1.3852 20.00 4.00 0.051 . . 1 '4 wavelength' 1.4013 1.3847 20.00 4.00 0.044 . . 1 '4 wavelength' 1.3857 1.3857 20.00 4.00 . 0.110 0.049 1 '4 wavelength' 1.3857 1.3852 20.00 4.00 0.049 . . 1 '4 wavelength' 1.3857 1.3847 20.00 4.00 0.067 . . 1 '4 wavelength' 1.3852 1.3852 20.00 4.00 . 0.149 0.072 1 '4 wavelength' 1.3852 1.3847 20.00 4.00 0.039 . . 1 '4 wavelength' 1.3847 1.3847 20.00 4.00 . 0.102 0.071 1 '4 wavelength' 1.4013 1.4013 4.00 3.00 . 0.114 0.111 1 '4 wavelength' 1.4013 1.3857 4.00 3.00 0.089 . . 1 '4 wavelength' 1.4013 1.3852 4.00 3.00 0.086 . . 1 '4 wavelength' 1.4013 1.3847 4.00 3.00 0.077 . . 1 '4 wavelength' 1.3857 1.3857 4.00 3.00 . 0.140 0.127 1 '4 wavelength' 1.3857 1.3852 4.00 3.00 0.085 . . 1 '4 wavelength' 1.3857 1.3847 4.00 3.00 0.089 . . 1 '4 wavelength' 1.3852 1.3852 4.00 3.00 . 0.155 0.119 1 '4 wavelength' 1.3852 1.3847 4.00 3.00 0.082 . . 1 '4 wavelength' 1.3847 1.3847 4.00 3.00 . 0.124 0.120 1 '5 wavelength' 1.3857 1.3857 20.00 4.00 . 0.075 0.027 1 '5 wavelength' 1.3857 1.3852 20.00 4.00 0.041 . . 1 '5 wavelength' 1.3857 1.3847 20.00 4.00 0.060 . . 1 '5 wavelength' 1.3857 1.3784 20.00 4.00 0.057 . . 1 '5 wavelength' 1.3857 1.2862 20.00 4.00 0.072 . . 1 '5 wavelength' 1.3852 1.3852 20.00 4.00 . 0.105 0.032 1 '5 wavelength' 1.3852 1.3847 20.00 4.00 0.036 . . 1 '5 wavelength' 1.3852 1.3784 20.00 4.00 0.044 . . 1 '5 wavelength' 1.3852 1.2862 20.00 4.00 0.065 . . 1 '5 wavelength' 1.3847 1.3847 20.00 4.00 . 0.072 0.031 1 '5 wavelength' 1.3847 1.3784 20.00 4.00 0.040 . . 1 '5 wavelength' 1.3847 1.2862 20.00 4.00 0.059 . . 1 '5 wavelength' 1.3784 1.3784 20.00 4.00 . 0.059 0.032 1 '5 wavelength' 1.3784 1.2862 20.00 4.00 0.059 . . 1 '5 wavelength' 1.2862 1.3847 20.00 4.00 . 0.058 0.028 1 '5 wavelength' 1.3857 1.3857 4.00 3.00 . 0.078 0.075 1 '5 wavelength' 1.3857 1.3852 4.00 3.00 0.059 . . 1 '5 wavelength' 1.3857 1.3847 4.00 3.00 0.067 . . 1 '5 wavelength' 1.3857 1.3784 4.00 3.00 0.084 . . 1 '5 wavelength' 1.3857 1.2862 4.00 3.00 0.073 . . 1 '5 wavelength' 1.3852 1.3852 4.00 3.00 . 0.101 0.088 1 '5 wavelength' 1.3852 1.3847 4.00 3.00 0.066 . . 1 '5 wavelength' 1.3852 1.3784 4.00 3.00 0.082 . . 1 '5 wavelength' 1.3852 1.2862 4.00 3.00 0.085 . . 1 '5 wavelength' 1.3847 1.3847 4.00 3.00 . 0.097 0.074 1 '5 wavelength' 1.3847 1.3784 4.00 3.00 0.081 . . 1 '5 wavelength' 1.3847 1.2862 4.00 3.00 0.085 . . 1 '5 wavelength' 1.3784 1.3784 4.00 3.00 . 0.114 0.089 1 '5 wavelength' 1.3784 1.2862 4.00 3.00 0.103 . . 1 '5 wavelength' 1.2862 1.2862 4.00 3.00 . 0.062 0.060 2 '5 wavelength' 0.7263 0.7263 15.00 3.00 . 0.035 0.026 2 '5 wavelength' 0.7263 0.7251 15.00 3.00 0.028 . . 2 '5 wavelength' 0.7263 0.7284 15.00 3.00 0.023 . . 2 '5 wavelength' 0.7263 0.7246 15.00 3.00 0.025 . . 2 '5 wavelength' 0.7263 0.7217 15.00 3.00 0.026 . . 2 '5 wavelength' 0.7251 0.7251 15.00 3.00 . 0.060 0.026 2 '5 wavelength' 0.7251 0.7284 15.00 3.00 0.029 . . 2 '5 wavelength' 0.7251 0.7246 15.00 3.00 0.031 . . 2 '5 wavelength' 0.7251 0.7217 15.00 3.00 0.035 . . 2 '5 wavelength' 0.7284 0.7284 15.00 3.00 . 0.075 0.030 2 '5 wavelength' 0.7284 0.7246 15.00 3.00 0.023 . . 2 '5 wavelength' 0.7284 0.7217 15.00 3.00 0.027 . . 2 '5 wavelength' 0.7246 0.7246 15.00 3.00 . 0.069 0.026 2 '5 wavelength' 0.7246 0.7217 15.00 3.00 0.024 . . 2 '5 wavelength' 0.7217 0.7284 15.00 3.00 . 0.060 0.028 2 '5 wavelength' 0.7263 0.7263 3.00 1.90 . 0.060 0.050 2 '5 wavelength' 0.7263 0.7251 3.00 1.90 0.056 . . 2 '5 wavelength' 0.7263 0.7284 3.00 1.90 0.055 . . 2 '5 wavelength' 0.7263 0.7246 3.00 1.90 0.053 . . 2 '5 wavelength' 0.7263 0.7217 3.00 1.90 0.056 . . 2 '5 wavelength' 0.7251 0.7251 3.00 1.90 . 0.089 0.050 2 '5 wavelength' 0.7251 0.7284 3.00 1.90 0.054 . . 2 '5 wavelength' 0.7251 0.7246 3.00 1.90 0.058 . . 2 '5 wavelength' 0.7251 0.7217 3.00 1.90 0.063 . . 2 '5 wavelength' 0.7284 0.7284 3.00 1.90 . 0.104 0.057 2 '5 wavelength' 0.7284 0.7246 3.00 1.90 0.052 . . 2 '5 wavelength' 0.7284 0.7217 3.00 1.90 0.057 . . 2 '5 wavelength' 0.7246 0.7246 3.00 1.90 . 0.098 0.052 2 '5 wavelength' 0.7246 0.7217 3.00 1.90 0.054 . . 2 '5 wavelength' 0.7217 0.7284 3.00 1.90 . 0.089 0.060 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__phasing_MAD_ratio.d_res_high _item_description.description ; The lowest value for the interplanar spacings for the reflection data used for the comparison of Bijvoet differences. This is called the highest resolution. ; _item.name '_phasing_MAD_ratio.d_res_high' _item.category_id phasing_MAD_ratio _item.mandatory_code no _item_type.code float save_ save__phasing_MAD_ratio.d_res_low _item_description.description ; The highest value for the interplanar spacings for the reflection data used for the comparison of Bijvoet differences. This is called the lowest resolution. ; _item.name '_phasing_MAD_ratio.d_res_low' _item.category_id phasing_MAD_ratio _item.mandatory_code no _item_type.code float save_ save__phasing_MAD_ratio.expt_id _item_description.description ; This data item is a pointer to _phasing_MAD_expt.id in the PHASING_MAD_EXPT category. ; _item.name '_phasing_MAD_ratio.expt_id' _item.mandatory_code yes save_ save__phasing_MAD_ratio.clust_id _item_description.description ; This data item is a pointer to _phasing_MAD_clust.id in the PHASING_MAD_CLUST category. ; _item.name '_phasing_MAD_ratio.clust_id' _item.mandatory_code yes save_ save__phasing_MAD_ratio.ratio_one_wl _item_description.description ; The root-mean-square Bijvoet difference at one wavelength for all reflections. ; _item.name '_phasing_MAD_ratio.ratio_one_wl' _item.category_id phasing_MAD_ratio _item.mandatory_code no _item_type.code float save_ save__phasing_MAD_ratio.ratio_one_wl_centric _item_description.description ; The root-mean-square Bijvoet difference at one wavelength for centric reflections. This would be equal to zero for perfect data and thus serves as an estimate of the noise in the anomalous signals. ; _item.name '_phasing_MAD_ratio.ratio_one_wl_centric' _item.category_id phasing_MAD_ratio _item.mandatory_code no _item_type.code float save_ save__phasing_MAD_ratio.ratio_two_wl _item_description.description ; The root-mean-square dispersive Bijvoet difference between two wavelengths for all reflections. ; _item.name '_phasing_MAD_ratio.ratio_two_wl' _item.category_id phasing_MAD_ratio _item.mandatory_code no _item_type.code float save_ save__phasing_MAD_ratio.wavelength_1 _item_description.description ; This data item is a pointer to _phasing_MAD_set.wavelength in the PHASING_MAD_SET category. ; _item.name '_phasing_MAD_ratio.wavelength_1' _item.mandatory_code yes save_ save__phasing_MAD_ratio.wavelength_2 _item_description.description ; This data item is a pointer to _phasing_MAD_set.wavelength in the PHASING_MAD_SET category. ; _item.name '_phasing_MAD_ratio.wavelength_2' _item.mandatory_code yes save_ ##################### ## PHASING_MAD_SET ## ##################### save_phasing_MAD_set _category.description ; Data items in the PHASING_MAD_SET category record details about the individual data sets used in a MAD phasing experiment. ; _category.id phasing_MAD_set _category.mandatory_code no loop_ _category_key.name '_phasing_MAD_set.expt_id' '_phasing_MAD_set.clust_id' '_phasing_MAD_set.set_id' '_phasing_MAD_set.wavelength' loop_ _category_group.id 'inclusive_group' 'phasing_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on a paper by Shapiro et al. [Nature (London) (1995), 374, 327-337]. ; ; loop_ _phasing_MAD_set.expt_id _phasing_MAD_set.clust_id _phasing_MAD_set.set_id _phasing_MAD_set.wavelength _phasing_MAD_set.wavelength_details _phasing_MAD_set.d_res_low _phasing_MAD_set.d_res_high _phasing_MAD_set.f_prime _phasing_MAD_set.f_double_prime 1 '4 wavelength' aa 1.4013 'pre-edge' 20.00 3.00 -12.48 3.80 1 '4 wavelength' bb 1.3857 'peak' 20.00 3.00 -31.22 17.20 1 '4 wavelength' cc 1.3852 'edge' 20.00 3.00 -13.97 29.17 1 '4 wavelength' dd 1.3847 'remote' 20.00 3.00 -6.67 17.34 1 '5 wavelength' ee 1.3857 'ascending edge' 20.00 3.00 -28.33 14.84 1 '5 wavelength' ff 1.3852 'peak' 20.00 3.00 -21.50 30.23 1 '5 wavelength' gg 1.3847 'descending edge' 20.00 3.00 -10.71 20.35 1 '5 wavelength' hh 1.3784 'remote 1' 20.00 3.00 -14.45 11.84 1 '5 wavelength' ii 1.2862 'remote 2' 20.00 3.00 -9.03 9.01 2 '5 wavelength' jj 0.7263 'pre-edge' 15.00 1.90 -21.10 4.08 2 '5 wavelength' kk 0.7251 'edge' 15.00 1.90 -34.72 7.92 2 '5 wavelength' ll 0.7248 'peak' 15.00 1.90 -24.87 10.30 2 '5 wavelength' mm 0.7246 'descending edge' 15.00 1.90 -17.43 9.62 2 '5 wavelength' nn 0.7217 'remote' 15.00 1.90 -13.26 8.40 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__phasing_MAD_set.clust_id _item_description.description ; This data item is a pointer to _phasing_MAD_clust.id in the PHASING_MAD_CLUST category. ; _item.name '_phasing_MAD_set.clust_id' _item.mandatory_code yes save_ save__phasing_MAD_set.d_res_high _item_description.description ; The lowest value for the interplanar spacings for the reflection data used for this set of data. This is called the highest resolution. ; _item.name '_phasing_MAD_set.d_res_high' _item.category_id phasing_MAD_set _item.mandatory_code no _item_type.code float save_ save__phasing_MAD_set.d_res_low _item_description.description ; The highest value for the interplanar spacings for the reflection data used for this set of data. This is called the lowest resolution. ; _item.name '_phasing_MAD_set.d_res_low' _item.category_id phasing_MAD_set _item.mandatory_code no _item_type.code float save_ save__phasing_MAD_set.expt_id _item_description.description ; This data item is a pointer to _phasing_MAD_expt.id in the PHASING_MAD_EXPT category. ; _item.name '_phasing_MAD_set.expt_id' _item.mandatory_code yes save_ save__phasing_MAD_set.f_double_prime _item_description.description ; The f'' component of the anomalous scattering factor for this wavelength. ; _item.name '_phasing_MAD_set.f_double_prime' _item.category_id phasing_MAD_set _item.mandatory_code no _item_type.code float save_ save__phasing_MAD_set.f_prime _item_description.description ; The f' component of the anomalous scattering factor for this wavelength. ; _item.name '_phasing_MAD_set.f_prime' _item.category_id phasing_MAD_set _item.mandatory_code no _item_type.code float save_ save__phasing_MAD_set.set_id _item_description.description ; This data item is a pointer to _phasing_set.id in the PHASING_SET category. ; _item.name '_phasing_MAD_set.set_id' _item.mandatory_code yes save_ save__phasing_MAD_set.wavelength _item_description.description ; The wavelength at which this data set was measured. ; loop_ _item.name _item.category_id _item.mandatory_code '_phasing_MAD_set.wavelength' phasing_MAD_set yes '_phasing_MAD_ratio.wavelength_1' phasing_MAD_ratio yes '_phasing_MAD_ratio.wavelength_2' phasing_MAD_ratio yes loop_ _item_linked.child_name _item_linked.parent_name '_phasing_MAD_ratio.wavelength_1' '_phasing_MAD_set.wavelength' '_phasing_MAD_ratio.wavelength_2' '_phasing_MAD_set.wavelength' _item_type.code float save_ save__phasing_MAD_set.wavelength_details _item_description.description ; A descriptor for this wavelength in this cluster of data sets. ; _item.name '_phasing_MAD_set.wavelength_details' _item.category_id phasing_MAD_set _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'peak' 'remote' 'ascending edge' save_ ################# ## PHASING_MIR ## ################# save_phasing_MIR _category.description ; Data items in the PHASING_MIR category record details about the phasing of the structure where methods involving isomorphous replacement are involved. All isomorphous-replacement-based techniques are covered by this category, including single isomorphous replacement (SIR), multiple isomorphous replacement (MIR) and single or multiple isomorphous replacement plus anomalous scattering (SIRAS, MIRAS). ; _category.id phasing_MIR _category.mandatory_code no _category_key.name '_phasing_MIR.entry_id' loop_ _category_group.id 'inclusive_group' 'phasing_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on a paper by Zanotti et al. [J. Biol. Chem. (1993), 268, 10728-10738]. ; ; _phasing_MIR.method ; Standard phase refinement (Blow & Crick, 1959) ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__phasing_MIR.details _item_description.description ; A description of special aspects of the isomorphous-replacement phasing. ; _item.name '_phasing_MIR.details' _item.category_id phasing_MIR _item.mandatory_code no _item_type.code text save_ save__phasing_MIR.d_res_high _item_description.description ; The lowest value in angstroms for the interplanar spacings for the reflection data used for the native data set. This is called the highest resolution. ; _item.name '_phasing_MIR.d_res_high' _item.category_id phasing_MIR _item.mandatory_code yes _item_aliases.alias_name '_phasing_MIR.ebi_d_res_high' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__phasing_MIR.d_res_low _item_description.description ; The highest value in angstroms for the interplanar spacings for the reflection data used for the native data set. This is called the lowest resolution. ; _item.name '_phasing_MIR.d_res_low' _item.category_id phasing_MIR _item.mandatory_code yes _item_aliases.alias_name '_phasing_MIR.ebi_d_res_low' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__phasing_MIR.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_phasing_MIR.entry_id' _item.mandatory_code yes save_ save__phasing_MIR.FOM _item_description.description ; The mean value of the figure of merit m for all reflections phased in the native data set. int P~alpha~ exp(i*alpha) dalpha m = -------------------------------- int P~alpha~ dalpha P~a~ = the probability that the phase angle a is correct the integral is taken over the range alpha = 0 to 2 pi. ; _item.name '_phasing_MIR.FOM' _item.category_id phasing_MIR _item.mandatory_code no _item_aliases.alias_name '_phasing_MIR.ebi_fom' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__phasing_MIR.FOM_acentric _item_description.description ; The mean value of the figure of merit m for the acentric reflections phased in the native data set. int P~alpha~ exp(i*alpha) dalpha m = -------------------------------- int P~alpha~ dalpha P~a~ = the probability that the phase angle a is correct the integral is taken over the range alpha = 0 to 2 pi. ; _item.name '_phasing_MIR.FOM_acentric' _item.category_id phasing_MIR _item.mandatory_code no _item_aliases.alias_name '_phasing_MIR.ebi_fom_acentric' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__phasing_MIR.FOM_centric _item_description.description ; The mean value of the figure of merit m for the centric reflections phased in the native data set. int P~alpha~ exp(i*alpha) dalpha m = -------------------------------- int P~alpha~ dalpha P~a~ = the probability that the phase angle a is correct the integral is taken over the range alpha = 0 to 2 pi. ; _item.name '_phasing_MIR.FOM_centric' _item.category_id phasing_MIR _item.mandatory_code no _item_aliases.alias_name '_phasing_MIR.ebi_fom_centric' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__phasing_MIR.method _item_description.description ; A description of the MIR phasing method applied to phase this structure. Note that this is not the computer program used, which is described in the SOFTWARE category, but rather the method itself. This data item should be used to describe significant methodological options used within the MIR phasing program. ; _item.name '_phasing_MIR.method' _item.category_id phasing_MIR _item.mandatory_code no _item_type.code text save_ save__phasing_MIR.reflns _item_description.description ; The total number of reflections phased in the native data set. ; _item.name '_phasing_MIR.reflns' _item.category_id phasing_MIR _item.mandatory_code no _item_aliases.alias_name '_phasing_MIR.ebi_reflns' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__phasing_MIR.reflns_acentric _item_description.description ; The number of acentric reflections phased in the native data set. ; _item.name '_phasing_MIR.reflns_acentric' _item.category_id phasing_MIR _item.mandatory_code no _item_aliases.alias_name '_phasing_MIR.ebi_reflns_acentric' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__phasing_MIR.reflns_centric _item_description.description ; The number of centric reflections phased in the native data set. ; _item.name '_phasing_MIR.reflns_centric' _item.category_id phasing_MIR _item.mandatory_code no _item_aliases.alias_name '_phasing_MIR.ebi_reflns_centric' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__phasing_MIR.reflns_criterion _item_description.description ; Criterion used to limit the reflections used in the phasing calculations. ; _item.name '_phasing_MIR.reflns_criterion' _item.category_id phasing_MIR _item.mandatory_code no _item_aliases.alias_name '_phasing_MIR.ebi_reflns_criteria' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 _item_type.code text _item_examples.case '> 4 \s(I)' save_ ##################### ## PHASING_MIR_DER ## ##################### save_phasing_MIR_der _category.description ; Data items in the PHASING_MIR_DER category record details about individual derivatives used in the phasing of the structure when methods involving isomorphous replacement are involved. A derivative in this context does not necessarily equate with a data set; for instance, the same data set could be used to one resolution limit as an isomorphous scatterer and to a different resolution (and with a different sigma cutoff) as an anomalous scatterer. These would be treated as two distinct derivatives, although both derivatives would point to the same data sets via _phasing_MIR_der.der_set_id and _phasing_MIR_der.native_set_id. ; _category.id phasing_MIR_der _category.mandatory_code no _category_key.name '_phasing_MIR_der.id' loop_ _category_group.id 'inclusive_group' 'phasing_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on a paper by Zanotti et al. [J. Biol. Chem. (1993), 268, 10728-10738]. ; ; loop_ _phasing_MIR_der.id _phasing_MIR_der.number_of_sites _phasing_MIR_der.details KAu(CN)2 3 'major site interpreted in difference Patterson' K2HgI4 6 'sites found in cross-difference Fourier' K3IrCl6 2 'sites found in cross-difference Fourier' All 11 'data for all three derivatives combined' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__phasing_MIR_der.d_res_high _item_description.description ; The lowest value for the interplanar spacings for the reflection data used for this derivative. This is called the highest resolution. ; _item.name '_phasing_MIR_der.d_res_high' _item.category_id phasing_MIR_der _item.mandatory_code yes loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__phasing_MIR_der.d_res_low _item_description.description ; The highest value for the interplanar spacings for the reflection data used for this derivative. This is called the lowest resolution. ; _item.name '_phasing_MIR_der.d_res_low' _item.category_id phasing_MIR_der _item.mandatory_code yes loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__phasing_MIR_der.der_set_id _item_description.description ; The data set that was treated as the derivative in this experiment. This data item is a pointer to _phasing_set.id in the PHASING_SET category. ; _item.name '_phasing_MIR_der.der_set_id' _item.mandatory_code yes save_ save__phasing_MIR_der.details _item_description.description ; A description of special aspects of this derivative, its data, its solution or its use in phasing. ; _item.name '_phasing_MIR_der.details' _item.category_id phasing_MIR_der _item.mandatory_code no _item_type.code text save_ save__phasing_MIR_der.id _item_description.description ; The value of _phasing_MIR_der.id must uniquely identify a record in the PHASING_MIR_DER list. Note that this item need not be a number; it can be any unique identifier. ; loop_ _item.name _item.category_id _item.mandatory_code '_phasing_MIR_der.id' phasing_MIR_der yes '_phasing_MIR_der_refln.der_id' phasing_MIR_der_refln yes '_phasing_MIR_der_shell.der_id' phasing_MIR_der_shell yes '_phasing_MIR_der_site.der_id' phasing_MIR_der_site yes loop_ _item_linked.child_name _item_linked.parent_name '_phasing_MIR_der_refln.der_id' '_phasing_MIR_der.id' '_phasing_MIR_der_shell.der_id' '_phasing_MIR_der.id' '_phasing_MIR_der_site.der_id' '_phasing_MIR_der.id' _item_type.code line loop_ _item_examples.case 'KAu(CN)2' 'K2HgI4_anom' 'K2HgI4_iso' save_ save__phasing_MIR_der.native_set_id _item_description.description ; The data set that was treated as the native in this experiment. This data item is a pointer to _phasing_set.id in the PHASING_SET category. ; _item.name '_phasing_MIR_der.native_set_id' _item.mandatory_code yes save_ save__phasing_MIR_der.number_of_sites _item_description.description ; The number of heavy-atom sites in this derivative. ; _item.name '_phasing_MIR_der.number_of_sites' _item.category_id phasing_MIR_der _item.mandatory_code no _item_type.code int save_ save__phasing_MIR_der.power_acentric _item_description.description ; The mean phasing power P for acentric reflections for this derivative. sum|Fh~calc~^2^| P = (----------------------------)^1/2^ sum|Fph~obs~ - Fph~calc~|^2^ Fph~obs~ = the observed structure-factor amplitude of this derivative Fph~calc~ = the calculated structure-factor amplitude of this derivative Fh~calc~ = the calculated structure-factor amplitude from the heavy-atom model sum is taken over the specified reflections ; _item.name '_phasing_MIR_der.power_acentric' _item.category_id phasing_MIR_der _item.mandatory_code no _item_aliases.alias_name '_phasing_MIR_der.ebi_power_acentric' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__phasing_MIR_der.power_centric _item_description.description ; The mean phasing power P for centric reflections for this derivative. sum|Fh~calc~^2^| P = (----------------------------)^1/2^ sum|Fph~obs~ - Fph~calc~|^2^ Fph~obs~ = the observed structure-factor amplitude of the derivative Fph~calc~ = the calculated structure-factor amplitude of the derivative Fh~calc~ = the calculated structure-factor amplitude from the heavy-atom model sum is taken over the specified reflections ; _item.name '_phasing_MIR_der.power_centric' _item.category_id phasing_MIR_der _item.mandatory_code no _item_aliases.alias_name '_phasing_MIR_der.ebi_power_centric' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__phasing_MIR_der.R_cullis_acentric _item_description.description ; Residual factor R~cullis,acen~ for acentric reflections for this derivative. The Cullis R factor was originally defined only for centric reflections. It is, however, also a useful statistical measure for acentric reflections, which is how it is used in this data item. sum| |Fph~obs~ +/- Fp~obs~| - Fh~calc~ | R~cullis,acen~ = ---------------------------------------- sum|Fph~obs~ - Fp~obs~| Fp~obs~ = the observed structure-factor amplitude of the native Fph~obs~ = the observed structure-factor amplitude of the derivative Fh~calc~ = the calculated structure-factor amplitude from the heavy-atom model sum is taken over the specified reflections Ref: Cullis, A. F., Muirhead, H., Perutz, M. F., Rossmann, M. G. & North, A. C. T. (1961). Proc. R. Soc. London Ser. A, 265, 15-38. ; _item.name '_phasing_MIR_der.R_cullis_acentric' _item.category_id phasing_MIR_der _item.mandatory_code no _item_aliases.alias_name '_phasing_MIR_der.ebi_Rcullis_acentric' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__phasing_MIR_der.R_cullis_anomalous _item_description.description ; Residual factor R~cullis,ano~ for anomalous reflections for this derivative. The Cullis R factor was originally defined only for centric reflections. It is, however, also a useful statistical measure for anomalous reflections, which is how it is used in this data item. This is tabulated for acentric terms. A value less than 1.0 means there is some contribution to the phasing from the anomalous data. sum |Fph+~obs~Fph-~obs~ - Fh+~calc~ - Fh-~calc~| R~cullis,ano~ = ------------------------------------------------ sum|Fph+~obs~ - Fph-~obs~| Fph+~obs~ = the observed positive Friedel structure-factor amplitude for the derivative Fph-~obs~ = the observed negative Friedel structure-factor amplitude for the derivative Fh+~calc~ = the calculated positive Friedel structure-factor amplitude from the heavy-atom model Fh-~calc~ = the calculated negative Friedel structure-factor amplitude from the heavy-atom model sum is taken over the specified reflections Ref: Cullis, A. F., Muirhead, H., Perutz, M. F., Rossmann, M. G. & North, A. C. T. (1961). Proc. R. Soc. London Ser. A, 265, 15-38. ; _item.name '_phasing_MIR_der.R_cullis_anomalous' _item.category_id phasing_MIR_der _item.mandatory_code no _item_aliases.alias_name '_phasing_MIR_der.ebi_Rcullis_anomalous' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__phasing_MIR_der.R_cullis_centric _item_description.description ; Residual factor R~cullis~ for centric reflections for this derivative. sum| |Fph~obs~ +/- Fp~obs~| - Fh~calc~ | R~cullis~ = ---------------------------------------- sum|Fph~obs~ - Fp~obs~| Fp~obs~ = the observed structure-factor amplitude of the native Fph~obs~ = the observed structure-factor amplitude of the derivative Fh~calc~ = the calculated structure-factor amplitude from the heavy-atom model sum is taken over the specified reflections Ref: Cullis, A. F., Muirhead, H., Perutz, M. F., Rossmann, M. G. & North, A. C. T. (1961). Proc. R. Soc. London Ser. A, 265, 15-38. ; _item.name '_phasing_MIR_der.R_cullis_centric' _item.category_id phasing_MIR_der _item.mandatory_code no _item_aliases.alias_name '_phasing_MIR_der.ebi_Rcullis_centric' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__phasing_MIR_der.reflns_acentric _item_description.description ; The number of acentric reflections used in phasing for this derivative. ; _item.name '_phasing_MIR_der.reflns_acentric' _item.category_id phasing_MIR_der _item.mandatory_code no _item_aliases.alias_name '_phasing_MIR_der.ebi_reflns_acentric' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__phasing_MIR_der.reflns_anomalous _item_description.description ; The number of anomalous reflections used in phasing for this derivative. ; _item.name '_phasing_MIR_der.reflns_anomalous' _item.category_id phasing_MIR_der _item.mandatory_code no _item_aliases.alias_name '_phasing_MIR_der.ebi_reflns_anomalous' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__phasing_MIR_der.reflns_centric _item_description.description ; The number of centric reflections used in phasing for this derivative. ; _item.name '_phasing_MIR_der.reflns_centric' _item.category_id phasing_MIR_der _item.mandatory_code no _item_aliases.alias_name '_phasing_MIR_der.ebi_reflns_centric' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__phasing_MIR_der.reflns_criteria _item_description.description ; Criteria used to limit the reflections used in the phasing calculations. ; _item.name '_phasing_MIR_der.reflns_criteria' _item.category_id phasing_MIR_der _item.mandatory_code no _item_type.code text _item_examples.case '> 4 \s(I)' save_ ########################### ## PHASING_MIR_DER_REFLN ## ########################### save_phasing_MIR_der_refln _category.description ; Data items in the PHASING_MIR_DER_REFLN category record details about the calculated structure factors obtained in an MIR phasing experiment. This list may contain information from a number of different derivatives; _phasing_MIR_der_refln.der_id indicates to which derivative a given record corresponds. (A derivative in this context does not necessarily equate with a data set; see the definition of the PHASING_MIR_DER category for a discussion of the meaning of derivative.) It is not necessary for the data items describing the measured value of F to appear in this list, as they will be given in the PHASING_SET_REFLN category. However, these items can also be listed here for completeness. ; _category.id phasing_MIR_der_refln _category.mandatory_code no loop_ _category_key.name '_phasing_MIR_der_refln.index_h' '_phasing_MIR_der_refln.index_k' '_phasing_MIR_der_refln.index_l' '_phasing_MIR_der_refln.der_id' '_phasing_MIR_der_refln.set_id' loop_ _category_group.id 'inclusive_group' 'phasing_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on laboratory records for the 6,1,25 reflection of an Hg/Pt derivative of protein NS1. ; ; _phasing_MIR_der_refln.index_h 6 _phasing_MIR_der_refln.index_k 1 _phasing_MIR_der_refln.index_l 25 _phasing_MIR_der_refln.der_id HGPT1 _phasing_MIR_der_refln.set_id 'NS1-96' _phasing_MIR_der_refln.F_calc_au 106.66 _phasing_MIR_der_refln.F_meas_au 204.67 _phasing_MIR_der_refln.F_meas_sigma 6.21 _phasing_MIR_der_refln.HL_A_iso -3.15 _phasing_MIR_der_refln.HL_B_iso -0.76 _phasing_MIR_der_refln.HL_C_iso 0.65 _phasing_MIR_der_refln.HL_D_iso 0.23 _phasing_MIR_der_refln.phase_calc 194.48 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__phasing_MIR_der_refln.der_id _item_description.description ; This data item is a pointer to _phasing_MIR_der.id in the PHASING_MIR_DER category. ; _item.name '_phasing_MIR_der_refln.der_id' _item.mandatory_code yes save_ save__phasing_MIR_der_refln.F_calc _item_description.description ; The calculated value of the structure factor for this derivative, in electrons. ; _item.name '_phasing_MIR_der_refln.F_calc' _item.category_id phasing_MIR_der_refln _item.mandatory_code no _item_related.related_name '_phasing_MIR_der_refln.F_calc_au' _item_related.function_code conversion_arbitrary _item_type.code float _item_units.code electrons save_ save__phasing_MIR_der_refln.F_calc_au _item_description.description ; The calculated value of the structure factor for this derivative, in arbitrary units. ; _item.name '_phasing_MIR_der_refln.F_calc_au' _item.category_id phasing_MIR_der_refln _item.mandatory_code no _item_related.related_name '_phasing_MIR_der_refln.F_calc' _item_related.function_code conversion_arbitrary _item_type.code float _item_units.code arbitrary save_ save__phasing_MIR_der_refln.F_meas _item_description.description ; The measured value of the structure factor for this derivative, in electrons. ; _item.name '_phasing_MIR_der_refln.F_meas' _item.category_id phasing_MIR_der_refln _item.mandatory_code no loop_ _item_related.related_name _item_related.function_code '_phasing_MIR_der_refln.F_meas_sigma' associated_esd '_phasing_MIR_der_refln.F_meas_au' conversion_arbitrary _item_type.code float _item_type_conditions.code esd _item_units.code electrons save_ save__phasing_MIR_der_refln.F_meas_au _item_description.description ; The measured value of the structure factor for this derivative, in arbitrary units. ; _item.name '_phasing_MIR_der_refln.F_meas_au' _item.category_id phasing_MIR_der_refln _item.mandatory_code no loop_ _item_related.related_name _item_related.function_code '_phasing_MIR_der_refln.F_meas_sigma_au' associated_esd '_phasing_MIR_der_refln.F_meas' conversion_arbitrary _item_type.code float _item_type_conditions.code esd _item_units.code arbitrary save_ save__phasing_MIR_der_refln.F_meas_sigma _item_description.description ; The standard uncertainty (estimated standard deviation) of _phasing_MIR_der_refln.F_meas, in electrons. ; _item.name '_phasing_MIR_der_refln.F_meas_sigma' _item.category_id phasing_MIR_der_refln _item.mandatory_code no loop_ _item_related.related_name _item_related.function_code '_phasing_MIR_der_refln.F_meas' associated_value '_phasing_MIR_der_refln.F_meas_sigma_au' conversion_arbitrary _item_type.code float _item_units.code electrons save_ save__phasing_MIR_der_refln.F_meas_sigma_au _item_description.description ; The standard uncertainty (estimated standard deviation) of _phasing_MIR_der_refln.F_meas_au, in arbitrary units. ; _item.name '_phasing_MIR_der_refln.F_meas_sigma_au' _item.category_id phasing_MIR_der_refln _item.mandatory_code no loop_ _item_related.related_name _item_related.function_code '_phasing_MIR_der_refln.F_meas_au' associated_value '_phasing_MIR_der_refln.F_meas_sigma' conversion_arbitrary _item_type.code float _item_units.code arbitrary save_ save__phasing_MIR_der_refln.HL_A_iso _item_description.description ; The isomorphous Hendrickson-Lattman coefficient A~iso~ for this reflection for this derivative. -2.0 * (Fp~obs~^2^ + Fh~calc~^2^ - Fph~obs~^2^) * Fp~obs~ * cos(alphah~calc~) A~iso~ = ----------------------------------------------- E^2^ E = (Fph~obs~ - Fp~obs~ - Fh~calc~)^2^ for centric reflections = [(Fph~obs~ - Fp~obs~) * 2^1/2^ - Fh~calc~]^2^ for acentric reflections Fp~obs~ = the observed structure-factor amplitude of the native Fph~obs~ = the observed structure-factor amplitude of the derivative Fh~calc~ = the calculated structure-factor amplitude from the heavy-atom model alphah~calc~ = the calculated phase from the heavy-atom model This coefficient appears in the expression for the phase probability of each isomorphous derivative: P~i~(alpha) = exp[k + A * cos(alpha) + B * sin(alpha) + C * cos(2 * alpha) + D * sin(2 * alpha)] Ref: Hendrickson, W. A. & Lattman, E. E. (1970). Acta Cryst. B26, 136-143. ; _item.name '_phasing_MIR_der_refln.HL_A_iso' _item.category_id phasing_MIR_der_refln _item.mandatory_code no _item_type.code float save_ save__phasing_MIR_der_refln.HL_B_iso _item_description.description ; The isomorphous Hendrickson-Lattman coefficient B~iso~ for this reflection for this derivative. -2.0 * (Fp~obs~^2^ + Fh~calc~^2^ - Fph~obs~^2^) * Fp~obs~ * sin(alphah~calc~) B~iso~ = ----------------------------------------------- E^2^ E = (Fph~obs~ - Fp~obs~ - Fh~calc~)^2^ for centric reflections = [(Fph~obs~ - Fp~obs~) * 2^1/2^ - Fh~calc~]^2^ for acentric reflections Fp~obs~ = the observed structure-factor amplitude of the native Fph~obs~ = the observed structure-factor amplitude of the derivative Fh~calc~ = the calculated structure-factor amplitude from the heavy-atom model alphah~calc~ = the phase calculated from the heavy-atom model This coefficient appears in the expression for the phase probability of each isomorphous derivative: P~i~(alpha) = exp[k + A * cos(alpha) + B * sin(alpha) + C * cos(2 * alpha) + D * sin(2 * alpha)] Ref: Hendrickson, W. A. & Lattman, E. E. (1970). Acta Cryst. B26, 136-143. ; _item.name '_phasing_MIR_der_refln.HL_B_iso' _item.category_id phasing_MIR_der_refln _item.mandatory_code no _item_type.code float save_ save__phasing_MIR_der_refln.HL_C_iso _item_description.description ; The isomorphous Hendrickson-Lattman coefficient C~iso~ for this reflection for this derivative. -Fp~obs~^2^ * [sin(alphah~calc~)^2^ - cos(alphah~calc~)^2^] C~iso~ = ------------------------------------ E^2^ E = (Fph~obs~ - Fp~obs~ - Fh~calc~)^2^ for centric reflections = [(Fph~obs~ - Fp~obs~) * 2^1/2^ - Fh~calc~]^2^ for acentric reflections Fp~obs~ = the observed structure-factor amplitude of the native Fph~obs~ = the observed structure-factor amplitude of the derivative Fh~calc~ = the calculated structure-factor amplitude from the heavy-atom model alphah~calc~ = the phase calculated from the heavy-atom model This coefficient appears in the expression for the phase probability of each isomorphous derivative: P~i~(alpha) = exp[k + A * cos(alpha) + B * sin(alpha) + C * cos(2 * alpha) + D * sin(2 * alpha)] Ref: Hendrickson, W. A. & Lattman, E. E. (1970). Acta Cryst. B26, 136-143. ; _item.name '_phasing_MIR_der_refln.HL_C_iso' _item.category_id phasing_MIR_der_refln _item.mandatory_code no _item_type.code float save_ save__phasing_MIR_der_refln.HL_D_iso _item_description.description ; The isomorphous Hendrickson-Lattman coefficient D~iso~ for this reflection for this derivative. -2.0 * Fp~obs~^2^ * sin(alphah~calc~)^2^ * cos(alphah~calc~)^2^ D~iso~ = ---------------------------------------- E^2^ E = (Fph~obs~ - Fp~obs~ - Fh~calc~)^2^ for centric reflections = [(Fph~obs~ - Fp~obs~) * 2^1/2^ - Fh~calc~]^2^ for acentric reflections Fp~obs~ = the observed structure-factor amplitude of the native Fph~obs~ = the observed structure-factor amplitude of the derivative Fh~calc~ = the calculated structure-factor amplitude from the heavy-atom model alphah~calc~ = the phase calculated from the heavy-atom model This coefficient appears in the expression for the phase probability of each isomorphous derivative: P~i~(alpha) = exp[k + A * cos(alpha) + B * sin(alpha) + C * cos(2 * alpha) + D * sin(2 * alpha)] Ref: Hendrickson, W. A. & Lattman, E. E. (1970). Acta Cryst. B26, 136-143. ; _item.name '_phasing_MIR_der_refln.HL_D_iso' _item.category_id phasing_MIR_der_refln _item.mandatory_code no _item_type.code float save_ save__phasing_MIR_der_refln.index_h _item_description.description ; Miller index h for this reflection for this derivative. ; _item.name '_phasing_MIR_der_refln.index_h' _item.category_id phasing_MIR_der_refln _item.mandatory_code yes loop_ _item_dependent.dependent_name '_phasing_MIR_der_refln.index_k' '_phasing_MIR_der_refln.index_l' _item_sub_category.id miller_index _item_type.code int save_ save__phasing_MIR_der_refln.index_k _item_description.description ; Miller index k for this reflection for this derivative. ; _item.name '_phasing_MIR_der_refln.index_k' _item.category_id phasing_MIR_der_refln _item.mandatory_code yes loop_ _item_dependent.dependent_name '_phasing_MIR_der_refln.index_h' '_phasing_MIR_der_refln.index_l' _item_sub_category.id miller_index _item_type.code int save_ save__phasing_MIR_der_refln.index_l _item_description.description ; Miller index l for this reflection for this derivative. ; _item.name '_phasing_MIR_der_refln.index_l' _item.category_id phasing_MIR_der_refln _item.mandatory_code yes loop_ _item_dependent.dependent_name '_phasing_MIR_der_refln.index_h' '_phasing_MIR_der_refln.index_k' _item_sub_category.id miller_index _item_type.code int save_ save__phasing_MIR_der_refln.phase_calc _item_description.description ; The calculated value of the structure-factor phase based on the heavy-atom model for this derivative in degrees. ; _item.name '_phasing_MIR_der_refln.phase_calc' _item.category_id phasing_MIR_der_refln _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__phasing_MIR_der_refln.set_id _item_description.description ; This data item is a pointer to _phasing_set.id in the PHASING_SET category. ; _item.name '_phasing_MIR_der_refln.set_id' _item.mandatory_code yes save_ ########################### ## PHASING_MIR_DER_SHELL ## ########################### save_phasing_MIR_der_shell _category.description ; Data items in the PHASING_MIR_DER_SHELL category record statistics, broken down into shells of resolution, for an MIR phasing experiment. This list may contain information from a number of different derivatives; _phasing_MIR_der_shell.der_id indicates to which derivative a given record corresponds. (A derivative in this context does not necessarily equate with a data set; see the definition of the PHASING_MIR_DER category for a discussion of the meaning of derivative.) ; _category.id phasing_MIR_der_shell _category.mandatory_code no loop_ _category_key.name '_phasing_MIR_der_shell.der_id' '_phasing_MIR_der_shell.d_res_low' '_phasing_MIR_der_shell.d_res_high' loop_ _category_group.id 'inclusive_group' 'phasing_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on a paper by Zanotti et al. [J. Biol. Chem. (1993), 268, 10728-10738] with addition of an arbitrary low-resolution limit. ; ; loop_ _phasing_MIR_der_shell.der_id _phasing_MIR_der_shell.d_res_low _phasing_MIR_der_shell.d_res_high _phasing_MIR_der_shell.ha_ampl _phasing_MIR_der_shell.loc KAu(CN)2 15.0 8.3 54 26 KAu(CN)2 8.3 6.4 54 20 KAu(CN)2 6.4 5.2 50 20 KAu(CN)2 5.2 4.4 44 23 KAu(CN)2 4.4 3.8 39 23 KAu(CN)2 3.8 3.4 33 21 KAu(CN)2 3.4 3.0 28 17 KAu(CN)2 15.0 3.0 38 21 K2HgI4 15.0 8.3 149 87 K2HgI4 8.3 6.4 121 73 K2HgI4 6.4 5.2 95 61 K2HgI4 5.2 4.4 80 60 K2HgI4 4.4 3.8 73 63 K2HgI4 3.8 3.4 68 57 K2HgI4 3.4 3.0 63 46 K2HgI4 15.0 3.0 79 58 K3IrCl6 15.0 8.3 33 27 K3IrCl6 8.3 6.4 40 23 K3IrCl6 6.4 5.2 31 22 K3IrCl6 5.2 4.4 27 23 K3IrCl6 4.4 3.8 22 23 K3IrCl6 3.8 3.4 19 20 K3IrCl6 3.4 3.0 16 20 K3IrCl6 15.0 3.0 23 21 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__phasing_MIR_der_shell.d_res_high _item_description.description ; The lowest value for the interplanar spacings for the reflection data for this derivative in this shell. This is called the highest resolution. ; _item.name '_phasing_MIR_der_shell.d_res_high' _item.category_id phasing_MIR_der_shell _item.mandatory_code yes loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__phasing_MIR_der_shell.d_res_low _item_description.description ; The highest value for the interplanar spacings for the reflection data for this derivative in this shell. This is called the lowest resolution. ; _item.name '_phasing_MIR_der_shell.d_res_low' _item.category_id phasing_MIR_der_shell _item.mandatory_code yes loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__phasing_MIR_der_shell.der_id _item_description.description ; This data item is a pointer to _phasing_MIR_der.id in the PHASING_MIR_DER category. ; _item.name '_phasing_MIR_der_shell.der_id' _item.mandatory_code yes save_ save__phasing_MIR_der_shell.fom _item_description.description ; The mean value of the figure of merit m for reflections for this derivative in this shell. int P~alpha~ exp(i*alpha) dalpha m = -------------------------------- int P~alpha~ dalpha P~alpha~ = the probability that the phase angle alpha is correct int is taken over the range alpha = 0 to 2 pi. ; _item.name '_phasing_MIR_der_shell.fom' _item.category_id phasing_MIR_der_shell _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__phasing_MIR_der_shell.ha_ampl _item_description.description ; The mean heavy-atom amplitude for reflections for this derivative in this shell. ; _item.name '_phasing_MIR_der_shell.ha_ampl' _item.category_id phasing_MIR_der_shell _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__phasing_MIR_der_shell.loc _item_description.description ; The mean lack-of-closure error loc for reflections for this derivative in this shell. loc = sum|Fph~obs~ - Fph~calc~| Fph~obs~ = the observed structure-factor amplitude of the derivative Fph~calc~ = the calculated structure-factor amplitude of the derivative sum is taken over the specified reflections ; _item.name '_phasing_MIR_der_shell.loc' _item.category_id phasing_MIR_der_shell _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__phasing_MIR_der_shell.phase _item_description.description ; The mean of the phase values for reflections for this derivative in this shell. ; _item.name '_phasing_MIR_der_shell.phase' _item.category_id phasing_MIR_der_shell _item.mandatory_code no _item_type.code float save_ save__phasing_MIR_der_shell.power _item_description.description ; The mean phasing power P for reflections for this derivative in this shell. sum|Fh~calc~^2^| P = (----------------------------)^1/2^ sum|Fph~obs~ - Fph~calc~|^2^ Fph~obs~ = the observed structure-factor amplitude of the derivative Fph~calc~ = the calculated structure-factor amplitude of the derivative Fh~calc~ = the calculated structure-factor amplitude from the heavy-atom model sum is taken over the specified reflections ; _item.name '_phasing_MIR_der_shell.power' _item.category_id phasing_MIR_der_shell _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__phasing_MIR_der_shell.R_cullis _item_description.description ; Residual factor R~cullis~ for centric reflections for this derivative in this shell. sum| |Fph~obs~ +/- Fp~obs~| - Fh~calc~ | R~cullis~ = ---------------------------------------- sum|Fph~obs~ - Fp~obs~| Fp~obs~ = the observed structure-factor amplitude of the native Fph~obs~ = the observed structure-factor amplitude of the derivative Fh~calc~ = the calculated structure-factor amplitude from the heavy-atom model sum is taken over the specified reflections Ref: Cullis, A. F., Muirhead, H., Perutz, M. F., Rossmann, M. G. & North, A. C. T. (1961). Proc. R. Soc. London Ser. A, 265, 15-38. ; _item.name '_phasing_MIR_der_shell.R_cullis' _item.category_id phasing_MIR_der_shell _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__phasing_MIR_der_shell.R_kraut _item_description.description ; Residual factor R~kraut~ for general reflections for this derivative in this shell. sum|Fph~obs~ - Fph~calc~| R~kraut~ = ------------------------- sum|Fph~obs~| Fph~obs~ = the observed structure-factor amplitude of the derivative Fph~calc~ = the calculated structure-factor amplitude of the derivative sum is taken over the specified reflections Ref: Kraut, J., Sieker, L. C., High, D. F. & Freer, S. T. (1962). Proc. Natl Acad. Sci. USA, 48, 1417-1424. ; _item.name '_phasing_MIR_der_shell.R_kraut' _item.category_id phasing_MIR_der_shell _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__phasing_MIR_der_shell.reflns _item_description.description ; The number of reflections in this shell. ; _item.name '_phasing_MIR_der_shell.reflns' _item.category_id phasing_MIR_der_shell _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ ########################## ## PHASING_MIR_DER_SITE ## ########################## save_phasing_MIR_der_site _category.description ; Data items in the PHASING_MIR_DER_SITE category record details about the heavy-atom sites in an MIR phasing experiment. This list may contain information from a number of different derivatives; _phasing_MIR_der_site.der_id indicates to which derivative a given record corresponds. (A derivative in this context does not necessarily equate with a data set; see the definition of the PHASING_MIR_DER category for a discussion of the meaning of derivative.) ; _category.id phasing_MIR_der_site _category.mandatory_code no loop_ _category_key.name '_phasing_MIR_der_site.der_id' '_phasing_MIR_der_site.id' loop_ _category_group.id 'inclusive_group' 'phasing_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on a paper by Zanotti et al. [J. Biol. Chem. (1993), 268, 10728-10738] with occupancies converted from electrons to fractional. ; ; loop_ _phasing_MIR_der_site.der_id _phasing_MIR_der_site.id _phasing_MIR_der_site.atom_type_symbol _phasing_MIR_der_site.occupancy _phasing_MIR_der_site.fract_x _phasing_MIR_der_site.fract_y _phasing_MIR_der_site.fract_z _phasing_MIR_der_site.B_iso KAu(CN)2 1 Au 0.40 0.082 0.266 0.615 33.0 KAu(CN)2 2 Au 0.03 0.607 0.217 0.816 25.9 KAu(CN)2 3 Au 0.02 0.263 0.782 0.906 15.7 K2HgI4 1 Hg 0.63 0.048 0.286 0.636 33.7 K2HgI4 2 Hg 0.34 0.913 0.768 0.889 36.7 K2HgI4 3 Hg 0.23 0.974 0.455 0.974 24.2 K2HgI4 4 Hg 0.28 0.903 0.836 0.859 14.7 K2HgI4 5 Hg 0.07 0.489 0.200 0.885 6.4 K2HgI4 6 Hg 0.07 0.162 0.799 0.889 32.9 K3IrCl6 1 Ir 0.26 0.209 0.739 0.758 40.8 K3IrCl6 2 Ir 0.05 0.279 0.613 0.752 24.9 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__phasing_MIR_der_site.atom_type_symbol _item_description.description ; This data item is a pointer to _atom_type.symbol in the ATOM_TYPE category. The scattering factors referenced via this data item should be those used in the refinement of the heavy-atom data; in some cases this is the scattering factor for the single heavy atom, in other cases these are the scattering factors for an atomic cluster. ; _item.name '_phasing_MIR_der_site.atom_type_symbol' _item.mandatory_code yes save_ save__phasing_MIR_der_site.B_iso _item_description.description ; Isotropic displacement parameter for this heavy-atom site in this derivative. ; _item.name '_phasing_MIR_der_site.B_iso' _item.category_id phasing_MIR_der_site _item.mandatory_code no _item_related.related_name '_phasing_MIR_der_site.B_iso_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code angstroms save_ save__phasing_MIR_der_site.B_iso_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _phasing_MIR_der_site.B_iso. ; _item.name '_phasing_MIR_der_site.B_iso_esd' _item.category_id phasing_MIR_der_site _item.mandatory_code no # _item_default.value 0.0 _item_related.related_name '_phasing_MIR_der_site.B_iso' _item_related.function_code associated_value _item_type.code float _item_units.code angstroms save_ save__phasing_MIR_der_site.Cartn_x _item_description.description ; The x coordinate of this heavy-atom position in this derivative specified as orthogonal angstroms. The orthogonal Cartesian axes are related to the cell axes as specified by the description given in _atom_sites.Cartn_transform_axes. ; _item.name '_phasing_MIR_der_site.Cartn_x' _item.category_id phasing_MIR_der_site _item.mandatory_code no loop_ _item_dependent.dependent_name '_phasing_MIR_der_site.Cartn_y' '_phasing_MIR_der_site.Cartn_z' _item_related.related_name '_phasing_MIR_der_site.Cartn_x_esd' _item_related.function_code associated_esd _item_sub_category.id cartesian_coordinate _item_type.code float _item_type_conditions.code esd _item_units.code angstroms save_ save__phasing_MIR_der_site.Cartn_x_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _phasing_MIR_der_site.Cartn_x. ; _item.name '_phasing_MIR_der_site.Cartn_x_esd' _item.category_id phasing_MIR_der_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_dependent.dependent_name '_phasing_MIR_der_site.Cartn_y_esd' '_phasing_MIR_der_site.Cartn_z_esd' _item_related.related_name '_phasing_MIR_der_site.Cartn_x' _item_related.function_code associated_value _item_sub_category.id cartesian_coordinate_esd _item_type.code float _item_units.code angstroms save_ save__phasing_MIR_der_site.Cartn_y _item_description.description ; The y coordinate of this heavy-atom position in this derivative specified as orthogonal angstroms. The orthogonal Cartesian axes are related to the cell axes as specified by the description given in _atom_sites.Cartn_transform_axes. ; _item.name '_phasing_MIR_der_site.Cartn_y' _item.category_id phasing_MIR_der_site _item.mandatory_code no loop_ _item_dependent.dependent_name '_phasing_MIR_der_site.Cartn_x' '_phasing_MIR_der_site.Cartn_z' _item_related.related_name '_phasing_MIR_der_site.Cartn_y_esd' _item_related.function_code associated_esd _item_sub_category.id cartesian_coordinate _item_type.code float _item_type_conditions.code esd _item_units.code angstroms save_ save__phasing_MIR_der_site.Cartn_y_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _phasing_MIR_der_site.Cartn_y. ; _item.name '_phasing_MIR_der_site.Cartn_y_esd' _item.category_id phasing_MIR_der_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_dependent.dependent_name '_phasing_MIR_der_site.Cartn_x_esd' '_phasing_MIR_der_site.Cartn_z_esd' _item_related.related_name '_phasing_MIR_der_site.Cartn_y' _item_related.function_code associated_value _item_sub_category.id cartesian_coordinate_esd _item_type.code float _item_units.code angstroms save_ save__phasing_MIR_der_site.Cartn_z _item_description.description ; The z coordinate of this heavy-atom position in this derivative specified as orthogonal angstroms. The orthogonal Cartesian axes are related to the cell axes as specified by the description given in _atom_sites.Cartn_transform_axes. ; _item.name '_phasing_MIR_der_site.Cartn_z' _item.category_id phasing_MIR_der_site _item.mandatory_code no loop_ _item_dependent.dependent_name '_phasing_MIR_der_site.Cartn_x' '_phasing_MIR_der_site.Cartn_y' _item_related.related_name '_phasing_MIR_der_site.Cartn_z_esd' _item_related.function_code associated_esd _item_sub_category.id cartesian_coordinate _item_type.code float _item_type_conditions.code esd _item_units.code angstroms save_ save__phasing_MIR_der_site.Cartn_z_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _phasing_MIR_der_site.Cartn_z. ; _item.name '_phasing_MIR_der_site.Cartn_z_esd' _item.category_id phasing_MIR_der_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_dependent.dependent_name '_phasing_MIR_der_site.Cartn_x_esd' '_phasing_MIR_der_site.Cartn_y_esd' _item_related.related_name '_phasing_MIR_der_site.Cartn_z' _item_related.function_code associated_value _item_sub_category.id cartesian_coordinate_esd _item_type.code float _item_units.code angstroms save_ save__phasing_MIR_der_site.der_id _item_description.description ; This data item is a pointer to _phasing_MIR_der.id in the PHASING_MIR_DER category. ; _item.name '_phasing_MIR_der_site.der_id' _item.mandatory_code yes save_ save__phasing_MIR_der_site.details _item_description.description ; A description of special aspects of the derivative site. ; _item.name '_phasing_MIR_der_site.details' _item.category_id phasing_MIR_der_site _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'binds to His 117' 'minor site obtained from difference Fourier' 'same as site 2 in the K2HgI4 derivative' save_ save__phasing_MIR_der_site.fract_x _item_description.description ; The x coordinate of this heavy-atom position in this derivative specified as a fraction of _cell.length_a. ; _item.name '_phasing_MIR_der_site.fract_x' _item.category_id phasing_MIR_der_site _item.mandatory_code no loop_ _item_dependent.dependent_name '_phasing_MIR_der_site.fract_y' '_phasing_MIR_der_site.fract_z' _item_related.related_name '_phasing_MIR_der_site.fract_x_esd' _item_related.function_code associated_esd _item_sub_category.id fractional_coordinate _item_type.code float _item_type_conditions.code esd save_ save__phasing_MIR_der_site.fract_x_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _phasing_MIR_der_site.fract_x. ; _item.name '_phasing_MIR_der_site.fract_x_esd' _item.category_id phasing_MIR_der_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_dependent.dependent_name '_phasing_MIR_der_site.fract_y_esd' '_phasing_MIR_der_site.fract_z_esd' _item_related.related_name '_phasing_MIR_der_site.fract_x' _item_related.function_code associated_value _item_sub_category.id fractional_coordinate_esd _item_type.code float save_ save__phasing_MIR_der_site.fract_y _item_description.description ; The y coordinate of this heavy-atom position in this derivative specified as a fraction of _cell.length_b. ; _item.name '_phasing_MIR_der_site.fract_y' _item.category_id phasing_MIR_der_site _item.mandatory_code no loop_ _item_dependent.dependent_name '_phasing_MIR_der_site.fract_x' '_phasing_MIR_der_site.fract_z' _item_related.related_name '_phasing_MIR_der_site.fract_y_esd' _item_related.function_code associated_esd _item_sub_category.id fractional_coordinate _item_type.code float _item_type_conditions.code esd save_ save__phasing_MIR_der_site.fract_y_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _phasing_MIR_der_site.fract_y. ; _item.name '_phasing_MIR_der_site.fract_y_esd' _item.category_id phasing_MIR_der_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_dependent.dependent_name '_phasing_MIR_der_site.fract_x_esd' '_phasing_MIR_der_site.fract_z_esd' _item_related.related_name '_phasing_MIR_der_site.fract_y' _item_related.function_code associated_value _item_sub_category.id fractional_coordinate_esd _item_type.code float save_ save__phasing_MIR_der_site.fract_z _item_description.description ; The z coordinate of this heavy-atom position in this derivative specified as a fraction of _cell.length_c. ; _item.name '_phasing_MIR_der_site.fract_z' _item.category_id phasing_MIR_der_site _item.mandatory_code no loop_ _item_dependent.dependent_name '_phasing_MIR_der_site.fract_x' '_phasing_MIR_der_site.fract_y' _item_related.related_name '_phasing_MIR_der_site.fract_z_esd' _item_related.function_code associated_esd _item_sub_category.id fractional_coordinate _item_type.code float _item_type_conditions.code esd save_ save__phasing_MIR_der_site.fract_z_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _phasing_MIR_der_site.fract_z. ; _item.name '_phasing_MIR_der_site.fract_z_esd' _item.category_id phasing_MIR_der_site _item.mandatory_code no # _item_default.value 0.0 loop_ _item_dependent.dependent_name '_phasing_MIR_der_site.fract_x_esd' '_phasing_MIR_der_site.fract_y_esd' _item_related.related_name '_phasing_MIR_der_site.fract_z' _item_related.function_code associated_value _item_sub_category.id fractional_coordinate_esd _item_type.code float save_ save__phasing_MIR_der_site.id _item_description.description ; The value of _phasing_MIR_der_site.id must uniquely identify each site in each derivative in the PHASING_MIR_DER_SITE list. The atom identifiers need not be unique over all sites in all derivatives; they need only be unique for each site in each derivative. Note that this item need not be a number; it can be any unique identifier. ; _item.name '_phasing_MIR_der_site.id' _item.category_id phasing_MIR_der_site _item.mandatory_code yes _item_type.code code save_ save__phasing_MIR_der_site.occupancy _item_description.description ; The fraction of the atom type present at this heavy-atom site in a given derivative. The sum of the occupancies of all the atom types at this site may not significantly exceed 1.0 unless it is a dummy site. ; _item.name '_phasing_MIR_der_site.occupancy' _item.category_id phasing_MIR_der_site _item.mandatory_code no _item_default.value 1.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__phasing_MIR_der_site.occupancy_anom _item_description.description ; The relative anomalous occupancy of the atom type present at this heavy-atom site in a given derivative. This atom occupancy will probably be on an arbitrary scale. ; _item.name '_phasing_MIR_der_site.occupancy_anom' _item.category_id phasing_MIR_der_site _item.mandatory_code no _item_aliases.alias_name '_phasing_MIR_der_site.ebi_occupancy_anom' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 _item_related.related_name '_phasing_MIR_der_site.occupancy_anom_su' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd save_ save__phasing_MIR_der_site.occupancy_anom_su _item_description.description ; The standard uncertainty (estimated standard deviation) of _phasing_MIR_der_site.occupancy_anom. ; _item.name '_phasing_MIR_der_site.occupancy_anom_su' _item.category_id phasing_MIR_der_site _item.mandatory_code no _item_aliases.alias_name '_phasing_MIR_der_site.ebi_occupancy_anom_esd' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 # _item_default.value 0.0 _item_related.related_name '_phasing_MIR_der_site.occupancy_anom' _item_related.function_code associated_value _item_type.code float save_ save__phasing_MIR_der_site.occupancy_iso _item_description.description ; The relative real isotropic occupancy of the atom type present at this heavy-atom site in a given derivative. This atom occupancy will probably be on an arbitrary scale. ; _item.name '_phasing_MIR_der_site.occupancy_iso' _item.category_id phasing_MIR_der_site _item.mandatory_code no _item_aliases.alias_name '_phasing_MIR_der_site.ebi_occupancy_iso' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 _item_related.related_name '_phasing_MIR_der_site.occupancy_iso_su' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd save_ save__phasing_MIR_der_site.occupancy_iso_su _item_description.description ; The standard uncertainty (estimated standard deviation) of _phasing_MIR_der_site.occupancy_iso. ; _item.name '_phasing_MIR_der_site.occupancy_iso_su' _item.category_id phasing_MIR_der_site _item.mandatory_code no _item_aliases.alias_name '_phasing_MIR_der_site.ebi_occupancy_iso_esd' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 # _item_default.value 0.0 _item_related.related_name '_phasing_MIR_der_site.occupancy_iso' _item_related.function_code associated_value _item_type.code float save_ ####################### ## PHASING_MIR_SHELL ## ####################### save_phasing_MIR_shell _category.description ; Data items in the PHASING_MIR_SHELL category record statistics for an isomorphous replacement phasing experiment.broken down into shells of resolution. ; _category.id phasing_MIR_shell _category.mandatory_code no loop_ _category_key.name '_phasing_MIR_shell.d_res_low' '_phasing_MIR_shell.d_res_high' loop_ _category_group.id 'inclusive_group' 'phasing_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on a paper by Zanotti et al. [J. Biol. Chem. (1993), 268, 10728-10738] with addition of an arbitrary low-resolution limit. ; ; loop_ _phasing_MIR_shell.d_res_low _phasing_MIR_shell.d_res_high _phasing_MIR_shell.reflns _phasing_MIR_shell.FOM 15.0 8.3 80 0.69 8.3 6.4 184 0.73 6.4 5.2 288 0.72 5.2 4.4 406 0.65 4.4 3.8 554 0.54 3.8 3.4 730 0.53 3.4 3.0 939 0.50 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__phasing_MIR_shell.d_res_high _item_description.description ; The lowest value for the interplanar spacings for the reflection data in this shell. This is called the highest resolution. Note that the resolution limits of shells in the items _phasing_MIR_shell.d_res_high and _phasing_MIR_shell.d_res_low are independent of the resolution limits of shells in the items _reflns_shell.d_res_high and _reflns_shell.d_res_low. ; _item.name '_phasing_MIR_shell.d_res_high' _item.category_id phasing_MIR_shell _item.mandatory_code yes loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__phasing_MIR_shell.d_res_low _item_description.description ; The highest value for the interplanar spacings for the reflection data in this shell. This is called the lowest resolution. Note that the resolution limits of shells in the items _phasing_MIR_shell.d_res_high and _phasing_MIR_shell.d_res_low are independent of the resolution limits of shells in the items _reflns_shell.d_res_high and _reflns_shell.d_res_low. ; _item.name '_phasing_MIR_shell.d_res_low' _item.category_id phasing_MIR_shell _item.mandatory_code yes loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__phasing_MIR_shell.FOM _item_description.description ; The mean value of the figure of merit m for reflections in this shell. int P~alpha~ exp(i*alpha) dalpha m = -------------------------------- int P~alpha~ dalpha P~alpha~ = the probability that the phase angle alpha is correct the integral is taken over the range alpha = 0 to 2 pi. ; _item.name '_phasing_MIR_shell.FOM' _item.category_id phasing_MIR_shell _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__phasing_MIR_shell.FOM_acentric _item_description.description ; The mean value of the figure of merit m for acentric reflections in this shell. int P~alpha~ exp(i*alpha) dalpha m = -------------------------------- int P~alpha~ dalpha P~a~ = the probability that the phase angle a is correct the integral is taken over the range alpha = 0 to 2 pi. ; _item.name '_phasing_MIR_shell.FOM_acentric' _item.category_id phasing_MIR_shell _item.mandatory_code no _item_aliases.alias_name '_phasing_MIR_shell.ebi_fom_acentric' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__phasing_MIR_shell.FOM_centric _item_description.description ; The mean value of the figure of merit m for centric reflections in this shell. int P~alpha~ exp(i*alpha) dalpha m = -------------------------------- int P~alpha~ dalpha P~a~ = the probability that the phase angle a is correct the integral is taken over the range alpha = 0 to 2 pi. ; _item.name '_phasing_MIR_shell.FOM_centric' _item.category_id phasing_MIR_shell _item.mandatory_code no _item_aliases.alias_name '_phasing_MIR_shell.ebi_fom_centric' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__phasing_MIR_shell.loc _item_description.description ; The mean lack-of-closure error loc for reflections in this shell. loc = sum|Fph~obs~ - Fph~calc~| Fph~obs~ = the observed structure-factor amplitude of the derivative Fph~calc~ = the calculated structure-factor amplitude of the derivative sum is taken over the specified reflections ; _item.name '_phasing_MIR_shell.loc' _item.category_id phasing_MIR_shell _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__phasing_MIR_shell.mean_phase _item_description.description ; The mean of the phase values for all reflections in this shell. ; _item.name '_phasing_MIR_shell.mean_phase' _item.category_id phasing_MIR_shell _item.mandatory_code no _item_type.code float save_ save__phasing_MIR_shell.power _item_description.description ; The mean phasing power P for reflections in this shell. sum|Fh~calc~^2^| P = (----------------------------)^1/2^ sum|Fph~obs~ - Fph~calc~|^2^ Fph~obs~ = the observed structure-factor amplitude of the derivative Fph~calc~ = the calculated structure-factor amplitude of the derivative Fh~calc~ = the calculated structure-factor amplitude from the heavy-atom model sum is taken over the specified reflections ; _item.name '_phasing_MIR_shell.power' _item.category_id phasing_MIR_shell _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__phasing_MIR_shell.R_cullis _item_description.description ; Residual factor R~cullis~ for centric reflections in this shell. sum| |Fph~obs~ +/- Fp~obs~| - Fh~calc~ | R~cullis~ = ---------------------------------------- sum|Fph~obs~ - Fp~obs~| Fp~obs~ = the observed structure-factor amplitude of the native Fph~obs~ = the observed structure-factor amplitude of the derivative Fh~calc~ = the calculated structure-factor amplitude from the heavy-atom model sum is taken over the specified reflections Ref: Cullis, A. F., Muirhead, H., Perutz, M. F., Rossmann, M. G. & North, A. C. T. (1961). Proc. R. Soc. London Ser. A, 265, 15-38. ; _item.name '_phasing_MIR_shell.R_cullis' _item.category_id phasing_MIR_shell _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__phasing_MIR_shell.R_kraut _item_description.description ; Residual factor R~kraut~ for general reflections in this shell. sum|Fph~obs~ - Fph~calc~| R~kraut~ = ------------------------- sum|Fph~obs~| Fph~obs~ = the observed structure-factor amplitude of the derivative Fph~calc~ = the calculated structure-factor amplitude of the derivative sum is taken over the specified reflections Ref: Kraut, J., Sieker, L. C., High, D. F. & Freer, S. T. (1962). Proc. Natl Acad. Sci. USA, 48, 1417-1424. ; _item.name '_phasing_MIR_shell.R_kraut' _item.category_id phasing_MIR_shell _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__phasing_MIR_shell.reflns _item_description.description ; The number of reflections in this shell. ; _item.name '_phasing_MIR_shell.reflns' _item.category_id phasing_MIR_shell _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__phasing_MIR_shell.reflns_acentric _item_description.description ; The number of acentric reflections in this shell. ; _item.name '_phasing_MIR_shell.reflns_acentric' _item.category_id phasing_MIR_shell _item.mandatory_code no _item_aliases.alias_name '_phasing_MIR_shell.ebi_reflns_acentric' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__phasing_MIR_shell.reflns_anomalous _item_description.description ; The number of anomalous reflections in this shell. ; _item.name '_phasing_MIR_shell.reflns_anomalous' _item.category_id phasing_MIR_shell _item.mandatory_code no # _item_aliases.alias_name '_phasing_MIR_shell.ebi_reflns_anomalous' # _item_aliases.dictionary ebi_extensions # _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__phasing_MIR_shell.reflns_centric _item_description.description ; The number of centric reflections in this shell. ; _item.name '_phasing_MIR_shell.reflns_centric' _item.category_id phasing_MIR_shell _item.mandatory_code no _item_aliases.alias_name '_phasing_MIR_shell.ebi_reflns_centric' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ ################# ## PHASING_SET ## ################# save_phasing_set _category.description ; Data items in the PHASING_SET category record details about the data sets used in a phasing experiment. A given data set may be used in a number of different ways; for instance, a single data set could be used both as an isomorphous derivative and as a component of a multiple-wavelength calculation. This category establishes identifiers for each data set and permits the archiving of a subset of experimental information for each data set (cell constants, wavelength, temperature etc.). This and related categories of data items are provided so that derivative intensity and phase information can be stored in the same data block as the information for the refined structure. If all the possible experimental information for each data set (raw data sets, crystal growth conditions etc.) is to be archived, these data items should be recorded in a separate data block. ; _category.id phasing_set _category.mandatory_code no _category_key.name '_phasing_set.id' loop_ _category_group.id 'inclusive_group' 'phasing_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on laboratory records for an Hg/Pt derivative of protein NS1. ; ; _phasing_set.id 'NS1-96' _phasing_set.cell_angle_alpha 90.0 _phasing_set.cell_angle_beta 90.0 _phasing_set.cell_angle_gamma 90.0 _phasing_set.cell_length_a 38.63 _phasing_set.cell_length_b 38.63 _phasing_set.cell_length_c 82.88 _phasing_set.radiation_wavelength 1.5145 _phasing_set.detector_type 'image plate' _phasing_set.detector_specific 'RXII' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__phasing_set.cell_angle_alpha _item_description.description ; Unit-cell angle alpha for this data set in degrees. ; _item.name '_phasing_set.cell_angle_alpha' _item.category_id phasing_set _item.mandatory_code no _item_default.value 90.0 loop_ _item_dependent.dependent_name '_phasing_set.cell_angle_beta' '_phasing_set.cell_angle_gamma' loop_ _item_range.maximum _item_range.minimum 180.0 180.0 180.0 0.0 0.0 0.0 _item_sub_category.id cell_angle _item_type.code float _item_units.code degrees save_ save__phasing_set.cell_angle_beta _item_description.description ; Unit-cell angle beta for this data set in degrees. ; _item.name '_phasing_set.cell_angle_beta' _item.category_id phasing_set _item.mandatory_code no _item_default.value 90.0 loop_ _item_dependent.dependent_name '_phasing_set.cell_angle_alpha' '_phasing_set.cell_angle_gamma' loop_ _item_range.maximum _item_range.minimum 180.0 180.0 180.0 0.0 0.0 0.0 _item_sub_category.id cell_angle _item_type.code float _item_units.code degrees save_ save__phasing_set.cell_angle_gamma _item_description.description ; Unit-cell angle gamma for this data set in degrees. ; _item.name '_phasing_set.cell_angle_gamma' _item.category_id phasing_set _item.mandatory_code no _item_default.value 90.0 loop_ _item_dependent.dependent_name '_phasing_set.cell_angle_alpha' '_phasing_set.cell_angle_beta' loop_ _item_range.maximum _item_range.minimum 180.0 180.0 180.0 0.0 0.0 0.0 _item_sub_category.id cell_angle _item_type.code float _item_units.code degrees save_ save__phasing_set.cell_length_a _item_description.description ; Unit-cell length a for this data set in angstroms. ; _item.name '_phasing_set.cell_length_a' _item.category_id phasing_set _item.mandatory_code no loop_ _item_dependent.dependent_name '_phasing_set.cell_length_b' '_phasing_set.cell_length_c' loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_sub_category.id cell_length _item_type.code float _item_units.code angstroms save_ save__phasing_set.cell_length_b _item_description.description ; Unit-cell length b for this data set in angstroms. ; _item.name '_phasing_set.cell_length_b' _item.category_id phasing_set _item.mandatory_code no loop_ _item_dependent.dependent_name '_phasing_set.cell_length_a' '_phasing_set.cell_length_c' loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_sub_category.id cell_length _item_type.code float _item_units.code angstroms save_ save__phasing_set.cell_length_c _item_description.description ; Unit-cell length c for this data set in angstroms. ; _item.name '_phasing_set.cell_length_c' _item.category_id phasing_set _item.mandatory_code no loop_ _item_dependent.dependent_name '_phasing_set.cell_length_a' '_phasing_set.cell_length_b' loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_sub_category.id cell_length _item_type.code float _item_units.code angstroms save_ save__phasing_set.detector_specific _item_description.description ; The particular radiation detector. In general, this will be a manufacturer, description, model number or some combination of these. ; _item.name '_phasing_set.detector_specific' _item.category_id phasing_set _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'Siemens model x' 'Kodak XG' 'MAR Research model y' save_ save__phasing_set.detector_type _item_description.description ; The general class of the radiation detector. ; _item.name '_phasing_set.detector_type' _item.category_id phasing_set _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'multiwire' 'imaging plate' 'CCD' 'film' save_ save__phasing_set.id _item_description.description ; The value of _phasing_set.id must uniquely identify a record in the PHASING_SET list. Note that this item need not be a number; it can be any unique identifier. ; loop_ _item.name _item.category_id _item.mandatory_code '_phasing_set.id' phasing_set yes '_phasing_set_refln.set_id' phasing_set_refln yes '_phasing_MAD_set.set_id' phasing_MAD_set yes '_phasing_MIR_der.der_set_id' phasing_MIR_der yes '_phasing_MIR_der.native_set_id' phasing_MIR_der yes '_phasing_MIR_der_refln.set_id' phasing_MIR_der_refln yes loop_ _item_linked.child_name _item_linked.parent_name '_phasing_set_refln.set_id' '_phasing_set.id' '_phasing_MAD_set.set_id' '_phasing_set.id' '_phasing_MIR_der.der_set_id' '_phasing_set.id' '_phasing_MIR_der.native_set_id' '_phasing_set.id' '_phasing_MIR_der_refln.set_id' '_phasing_set.id' _item_type.code line loop_ _item_examples.case 'KAu(CN)2' 'K2HgI4' save_ save__phasing_set.radiation_source_specific _item_description.description ; The particular source of radiation. In general, this will be a manufacturer, description, or model number (or some combination of these) for laboratory sources and an institution name and beamline name for synchrotron sources. ; _item.name '_phasing_set.radiation_source_specific' _item.category_id phasing_set _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'Rigaku RU200' 'Philips fine focus Mo' 'NSLS beamline X8C' save_ save__phasing_set.radiation_wavelength _item_description.description ; The mean wavelength of the radiation used to measure this data set. ; _item.name '_phasing_set.radiation_wavelength' _item.category_id phasing_set _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__phasing_set.temp _item_description.description ; The temperature in kelvins at which the data set was measured. ; _item.name '_phasing_set.temp' _item.category_id phasing_set _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code kelvins save_ ####################### ## PHASING_SET_REFLN ## ####################### save_phasing_set_refln _category.description ; Data items in the PHASING_SET_REFLN category record the values of the measured structure factors used in a phasing experiment. This list may contain information from a number of different data sets; _phasing_set_refln.set_id indicates the data set to which a given record corresponds. ; _category.id phasing_set_refln _category.mandatory_code no loop_ _category_key.name '_phasing_set_refln.index_h' '_phasing_set_refln.index_k' '_phasing_set_refln.index_l' '_phasing_set_refln.set_id' loop_ _category_group.id 'inclusive_group' 'phasing_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on laboratory records for the 15,15,32 reflection of an Hg/Pt derivative of protein NS1. ; ; _phasing_set_refln.set_id 'NS1-96' _phasing_set_refln.index_h 15 _phasing_set_refln.index_k 15 _phasing_set_refln.index_l 32 _phasing_set_refln.F_meas_au 181.79 _phasing_set_refln.F_meas_sigma_au 3.72 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__phasing_set_refln.set_id _item_description.description ; This data item is a pointer to _phasing_set.id in the PHASING_SET category. ; _item.name '_phasing_set_refln.set_id' _item.mandatory_code yes save_ save__phasing_set_refln.F_meas _item_description.description ; The measured value of the structure factor for this reflection in this data set in electrons. ; _item.name '_phasing_set_refln.F_meas' _item.category_id phasing_set_refln _item.mandatory_code no loop_ _item_related.related_name _item_related.function_code '_phasing_set_refln.F_meas_sigma' associated_esd '_phasing_set_refln.F_meas_au' conversion_arbitrary _item_type.code float _item_type_conditions.code esd _item_units.code electrons save_ save__phasing_set_refln.F_meas_au _item_description.description ; The measured value of the structure factor for this reflection in this data set in arbitrary units. ; _item.name '_phasing_set_refln.F_meas_au' _item.category_id phasing_set_refln _item.mandatory_code no loop_ _item_related.related_name _item_related.function_code '_phasing_set_refln.F_meas_sigma_au' associated_esd '_phasing_set_refln.F_meas' conversion_arbitrary _item_type.code float _item_type_conditions.code esd _item_units.code arbitrary save_ save__phasing_set_refln.F_meas_sigma _item_description.description ; The standard uncertainty (estimated standard deviation) of _phasing_set_refln.F_meas in electrons. ; _item.name '_phasing_set_refln.F_meas_sigma' _item.category_id phasing_set_refln _item.mandatory_code no loop_ _item_related.related_name _item_related.function_code '_phasing_set_refln.F_meas' associated_value '_phasing_set_refln.F_meas_sigma_au' conversion_arbitrary _item_type.code float _item_units.code electrons save_ save__phasing_set_refln.F_meas_sigma_au _item_description.description ; The standard uncertainty (estimated standard deviation) of _phasing_set_refln.F_meas_au in arbitrary units. ; _item.name '_phasing_set_refln.F_meas_sigma_au' _item.category_id phasing_set_refln _item.mandatory_code no loop_ _item_related.related_name _item_related.function_code '_phasing_set_refln.F_meas_au' associated_value '_phasing_set_refln.F_meas_sigma' conversion_arbitrary _item_type.code float _item_units.code arbitrary save_ save__phasing_set_refln.index_h _item_description.description ; Miller index h of this reflection in this data set. ; _item.name '_phasing_set_refln.index_h' _item.category_id phasing_set_refln _item.mandatory_code yes loop_ _item_dependent.dependent_name '_phasing_set_refln.index_k' '_phasing_set_refln.index_l' _item_sub_category.id miller_index _item_type.code int save_ save__phasing_set_refln.index_k _item_description.description ; Miller index k of this reflection in this data set. ; _item.name '_phasing_set_refln.index_k' _item.category_id phasing_set_refln _item.mandatory_code yes loop_ _item_dependent.dependent_name '_phasing_set_refln.index_h' '_phasing_set_refln.index_l' _item_sub_category.id miller_index _item_type.code int save_ save__phasing_set_refln.index_l _item_description.description ; Miller index l of this reflection in this data set. ; _item.name '_phasing_set_refln.index_l' _item.category_id phasing_set_refln _item.mandatory_code yes loop_ _item_dependent.dependent_name '_phasing_set_refln.index_h' '_phasing_set_refln.index_k' _item_sub_category.id miller_index _item_type.code int save_ ########## ## PUBL ## ########## save_publ _category.description ; Data items in the PUBL category are used when submitting a manuscript for publication. ; _category.id publ _category.mandatory_code no _category_key.name '_publ.entry_id' loop_ _category_group.id 'inclusive_group' 'iucr_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _publ.section_title ; trans-3-Benzoyl-2-(tert-butyl)-4-(iso-butyl)- 1,3-oxazolidin-5-one ; _publ.section_abstract ; The oxazolidinone ring is a shallow envelope conformation with the tert-butyl and iso-butyl groups occupying trans-positions with respect to the ring. The angles at the N atom sum to 356.2\%, indicating a very small degree of pyramidalization at this atom. This is consistent with electron delocalization between the N atom and the carbonyl centre [N-C=O = 1.374(3)\%A]. ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on C~31~H~48~N~4~O~4~, reported by Coleman, Patrick, Andersen & Rettig [Acta Cryst. (1996), C52, 1525-1527]. ; ; _publ.section_title ; Hemiasterlin methyl ester ; _publ.section_title_footnote ; IUPAC name: methyl 2,5-dimethyl-4-{2-[3-methyl- 2-methylamino-3-(N-methylbenzo[b]pyrrol- 3-yl)butanamido]-3,3-dimethyl-N-methyl- butanamido}-2-hexenoate. ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__publ.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_publ.entry_id' _item.mandatory_code yes save_ save__publ.contact_author _item_description.description ; The name and address of the author submitting the manuscript and data block. This is the person contacted by the journal editorial staff. It is preferable to use the separate data items _publ.contact_author_name and _publ.contact_author_address. ; _item.name '_publ.contact_author' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_contact_author' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; Professor George Ferguson Department of Chemistry and Biochemistry University of Guelph Ontario Canada N1G 2W1 ; save_ save__publ.contact_author_address _item_description.description ; The address of the author submitting the manuscript and data block. This is the person contacted by the journal editorial staff. ; _item.name '_publ.contact_author_address' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_contact_author_address' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; Department of Chemistry and Biochemistry University of Guelph Ontario Canada N1G 2W1 ; save_ save__publ.contact_author_email _item_description.description ; E-mail address in a form recognizable to international networks. The format of e-mail addresses is given in Section 3.4, Address Specification, of Internet Message Format, RFC 2822, P. Resnick (Editor), Network Standards Group, April 2001. ; _item.name '_publ.contact_author_email' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_contact_author_email' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'name@host.domain.country' 'uur5@banjo.bitnet' save_ save__publ.contact_author_fax _item_description.description ; Facsimile telephone number of the author submitting the manuscript and data block. The recommended style starts with the international dialing prefix, followed by the area code in parentheses, followed by the local number with no spaces. The earlier convention of including the international dialing prefix in parentheses is no longer recommended. ; _item.name '_publ.contact_author_fax' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_contact_author_fax' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case '12(34)9477330' '12()349477330' save_ save__publ.contact_author_name _item_description.description ; The name of the author submitting the manuscript and data block. This is the person contacted by the journal editorial staff. ; _item.name '_publ.contact_author_name' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_contact_author_name' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; Professor George Ferguson ; save_ save__publ.contact_author_phone _item_description.description ; Telephone number of the author submitting the manuscript and data block. The recommended style starts with the international dialing prefix, followed by the area code in parentheses, followed by the local number and any extension number prefixed by 'x', with no spaces. The earlier convention of including the international dialing prefix in parentheses is no longer recommended. ; _item.name '_publ.contact_author_phone' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_contact_author_phone' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case '12(34)9477330' '12()349477330' '12(34)9477330x5543' save_ save__publ.contact_letter _item_description.description ; A letter submitted to the journal editor by the contact author. ; _item.name '_publ.contact_letter' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_contact_letter' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__publ.manuscript_creation _item_description.description ; A description of the word-processor package and computer used to create the word-processed manuscript stored as _publ.manuscript_processed. ; _item.name '_publ.manuscript_creation' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_manuscript_creation' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'Tex file created by FrameMaker on a Sun 3/280' save_ save__publ.manuscript_processed _item_description.description ; The full manuscript of a paper (excluding possibly the figures and the tables) output in ASCII characters from a word processor. Information about the generation of this data item must be specified in the data item _publ.manuscript_creation. ; _item.name '_publ.manuscript_processed' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_manuscript_processed' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__publ.manuscript_text _item_description.description ; The full manuscript of a paper (excluding figures and possibly the tables) output as standard ASCII text. ; _item.name '_publ.manuscript_text' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_manuscript_text' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__publ.requested_category _item_description.description ; The category of paper submitted. For submission to Acta Crystallographica Section C or Acta Crystallographica Section E, ONLY the codes indicated for use with these journals should be used. ; _item.name '_publ.requested_category' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_requested_category' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_default.value FA _item_type.code line loop_ _item_enumeration.value _item_enumeration.detail FA 'Full article' FI 'Full submission - inorganic (Acta C)' FO 'Full submission - organic (Acta C)' FM 'Full submission - metal-organic (Acta C)' CI 'CIF-access paper - inorganic (Acta C) (no longer in use)' CO 'CIF-access paper - organic (Acta C) (no longer in use)' CM 'CIF-access paper - metal-organic (Acta C) (no longer in use)' EI 'Electronic submission - inorganic (Acta E)' EO 'Electronic submission - organic (Acta E)' EM 'Electronic submission - metal-organic (Acta E)' AD 'Addenda and Errata (Acta C, Acta E)' SC 'Short communication' save_ save__publ.requested_coeditor_name _item_description.description ; The name of the co-editor whom the authors would like to handle the submitted manuscript. ; _item.name '_publ.requested_coeditor_name' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_requested_coeditor_name' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__publ.requested_journal _item_description.description ; The name of the journal to which the manuscript is being submitted. ; _item.name '_publ.requested_journal' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_requested_journal' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line save_ save__publ.section_abstract _item_description.description ; The abstract section of a manuscript if the manuscript is submitted in parts. As an alternative see _publ.manuscript_text and _publ.manuscript_processed. ; _item.name '_publ.section_abstract' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_section_abstract' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__publ.section_acknowledgements _item_description.description ; The acknowledgements section of a manuscript if the manuscript is submitted in parts. As an alternative see _publ.manuscript_text and _publ.manuscript_processed. ; _item.name '_publ.section_acknowledgements' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_section_acknowledgements' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__publ.section_comment _item_description.description ; The comment section of a manuscript if the manuscript is submitted in parts. As an alternative see _publ.manuscript_text and _publ.manuscript_processed. ; _item.name '_publ.section_comment' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_section_comment' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__publ.section_discussion _item_description.description ; The discussion section of a manuscript if the manuscript is submitted in parts. As an alternative see _publ.manuscript_text and _publ.manuscript_processed. ; _item.name '_publ.section_discussion' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_section_discussion' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__publ.section_experimental _item_description.description ; The experimental section of a manuscript if the manuscript is submitted in parts. As an alternative see _publ.manuscript_text and _publ.manuscript_processed. The _publ.section_exptl_prep, _publ.section_exptl_solution and _publ.section_exptl_refinement items are preferred for separating the chemical preparation, structure solution and refinement aspects of the description of the experiment. ; _item.name '_publ.section_experimental' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_section_experimental' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__publ.section_exptl_prep _item_description.description ; The experimental preparation section of a manuscript if the manuscript is submitted in parts. As an alternative see _publ.manuscript_text and _publ.manuscript_processed. ; _item.name '_publ.section_exptl_prep' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_section_exptl_prep' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__publ.section_exptl_refinement _item_description.description ; The experimental refinement section of a manuscript if the manuscript is submitted in parts. As an alternative see _publ.manuscript_text and _publ.manuscript_processed. ; _item.name '_publ.section_exptl_refinement' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_section_exptl_refinement' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__publ.section_exptl_solution _item_description.description ; The experimental solution section of a manuscript if the manuscript is submitted in parts. As an alternative see _publ.manuscript_text and _publ.manuscript_processed. ; _item.name '_publ.section_exptl_solution' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_section_exptl_solution' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__publ.section_figure_captions _item_description.description ; The figure captions section of a manuscript if the manuscript is submitted in parts. As an alternative see _publ.manuscript_text and _publ.manuscript_processed. ; _item.name '_publ.section_figure_captions' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_section_figure_captions' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__publ.section_introduction _item_description.description ; The introduction section of a manuscript if the manuscript is submitted in parts. As an alternative see _publ.manuscript_text and _publ.manuscript_processed. ; _item.name '_publ.section_introduction' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_section_introduction' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__publ.section_references _item_description.description ; The references section of a manuscript if the manuscript is submitted in parts. As an alternative see _publ.manuscript_text and _publ.manuscript_processed. ; _item.name '_publ.section_references' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_section_references' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__publ.section_synopsis _item_description.description ; The synopsis section of a manuscript if the manuscript is submitted in parts. As an alternative see _publ.manuscript_text and _publ.manuscript_processed. ; _item.name '_publ.section_synopsis' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_section_synopsis' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__publ.section_table_legends _item_description.description ; The table legends section of a manuscript if the manuscript is submitted in parts. As an alternative see _publ.manuscript_text and _publ.manuscript_processed. ; _item.name '_publ.section_table_legends' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_section_table_legends' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__publ.section_title _item_description.description ; The title of a manuscript if the manuscript is submitted in parts. As an alternative see _publ.manuscript_text and _publ.manuscript_processed. ; _item.name '_publ.section_title' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_section_title' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__publ.section_title_footnote _item_description.description ; The footnote to the title of a manuscript if the manuscript is submitted in parts. As an alternative see _publ.manuscript_text and _publ.manuscript_processed. ; _item.name '_publ.section_title_footnote' _item.category_id publ _item.mandatory_code no _item_aliases.alias_name '_publ_section_title_footnote' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ ################# ## PUBL_AUTHOR ## ################# save_publ_author _category.description ; Data items in the PUBL_AUTHOR category record details of the authors of a manuscript submitted for publication. ; _category.id publ_author _category.mandatory_code no _category_key.name '_publ_author.name' loop_ _category_group.id 'inclusive_group' 'iucr_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; loop_ _publ_author.name _publ_author.address 'Willis, Anthony C.' ; Research School of Chemistry Australian National University GPO Box 4 Canberra, A.C.T. Australia 2601 ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__publ_author.address _item_description.description ; The address of a publication author. If there is more than one author this is looped with _publ_author.name. ; _item.name '_publ_author.address' _item.category_id publ_author _item.mandatory_code no _item_aliases.alias_name '_publ_author_address' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; Department Institute Street City and postcode COUNTRY ; save_ save__publ_author.email _item_description.description ; The e-mail address of a publication author. If there is more than one author, this will be looped with _publ_author.name. The format of e-mail addresses is given in Section 3.4, Address Specification, of Internet Message Format, RFC 2822, P. Resnick (Editor), Network Standards Group, April 2001. ; _item.name '_publ_author.email' _item.category_id publ_author _item.mandatory_code no _item_aliases.alias_name '_publ_author_email' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.3.1 _item_type.code text loop_ _item_examples.case name@host.domain.country bm@iucr.org save_ save__publ_author.footnote _item_description.description ; A footnote accompanying an author's name in the list of authors of a paper. Typically indicates sabbatical address, additional affiliations or date of decease. ; _item.name '_publ_author.footnote' _item.category_id publ_author _item.mandatory_code no _item_aliases.alias_name '_publ_author_footnote' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'On leave from U. Western Australia' 'Also at Department of Biophysics' save_ save__publ_author.name _item_description.description ; The name of a publication author. If there are multiple authors this will be looped with _publ_author.address. The family name(s), followed by a comma and including any dynastic components, precedes the first names or initials. ; _item.name '_publ_author.name' _item.category_id publ_author _item.mandatory_code yes _item_aliases.alias_name '_publ_author_name' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'Bleary, Percival R.' 'O'Neil, F.K.' 'Van den Bossche, G.' 'Yang, D.-L.' 'Simonov, Yu.A' save_ ############### ## PUBL_BODY ## ############### save_publ_body _category.description ; Data items in the PUBL_BODY category permit the labelling of different text sections within the body of a paper. Note that these should not be used in a paper which has a standard format with sections tagged by specific data names (such as in Acta Crystallographica Section C). Typically, each journal will supply a list of the specific items it requires in its Notes for Authors. ; _category.id publ_body _category.mandatory_code no loop_ _category_key.name '_publ_body.element' '_publ_body.label' loop_ _category_group.id 'inclusive_group' 'iucr_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on a paper by R. Restori & D. Schwarzenbach [Acta Cryst. (1996), A52, 369-378]. ; ; loop_ _publ_body.element _publ_body.label _publ_body.title _publ_body.format _publ_body.contents section 1 Introduction cif ; X-ray diffraction from a crystalline material provides information on the thermally and spatially averaged electron density in the crystal... ; section 2 Theory tex ; In the rigid-atom approximation, the dynamic electron density of an atom is described by the convolution product of the static atomic density and a probability density function, $\rho_{dyn}(\bf r) = \rho_{stat}(\bf r) * P(\bf r). \eqno(1)$ ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on a paper by R. J. Papoular, Y. Vekhter & P. Coppens [Acta Cryst. (1996), A52, 397-407]. ; ; loop_ _publ_body.element _publ_body.label _publ_body.title _publ_body.contents section 3 ; The two-channel method for retrieval of the deformation electron density ; . subsection 3.1 'The two-channel entropy S[\D\r(r)]' ; As the wide dynamic range involved in the total electron density... ; subsection 3.2 'Uniform vs informative prior model densities' . subsubsection 3.2.1 'Use of uniform models' ; Straightforward algebra leads to expressions analogous to... ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__publ_body.contents _item_description.description ; A text section of a paper. ; _item.name '_publ_body.contents' _item.category_id publ_body _item.mandatory_code no _item_aliases.alias_name '_publ_body_contents' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__publ_body.element _item_description.description ; The functional role of the associated text section. ; _item.name '_publ_body.element' _item.category_id publ_body _item.mandatory_code no _item_aliases.alias_name '_publ_body_element' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code code loop_ _item_enumeration.value 'section' 'subsection' 'subsubsection' 'appendix' 'footnote' save_ save__publ_body.format _item_description.description ; Code indicating the appropriate typesetting conventions for accented characters and special symbols in the text section. ; _item.name '_publ_body.format' _item.category_id publ_body _item.mandatory_code no _item_aliases.alias_name '_publ_body_format' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail ascii 'no coding for special symbols' cif 'CIF convention' latex 'LaTeX' sgml 'SGML (ISO 8879)' tex 'TeX' troff 'troff or nroff' save_ save__publ_body.label _item_description.description ; Code identifying the section of text. ; _item.name '_publ_body.label' _item.category_id publ_body _item.mandatory_code no _item_aliases.alias_name '_publ_body_label' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code code loop_ _item_examples.case '1' '1.1' '2.1.3' save_ save__publ_body.title _item_description.description ; Title of the associated section of text. ; _item.name '_publ_body.title' _item.category_id publ_body _item.mandatory_code no _item_aliases.alias_name '_publ_body_title' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ ########################## ## PUBL_MANUSCRIPT_INCL ## ########################## save_publ_manuscript_incl _category.description ; Data items in the PUBL_MANUSCRIPT_INCL category allow the authors of a manuscript submitted for publication to list data names that should be added to the standard request list used by the journal printing software. ; _category.id publ_manuscript_incl _category.mandatory_code no _category_key.name '_publ_manuscript_incl.entry_id' loop_ _category_group.id 'inclusive_group' 'iucr_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - hypothetical example. ; ; _publ_manuscript_incl.entry_id 'EXAMHYPO' loop_ _publ_manuscript_incl.extra_item _publ_manuscript_incl.extra_info _publ_manuscript_incl.extra_defn '_atom_site.symmetry_multiplicity' 'to emphasise special sites' yes '_chemical.compound_source' 'rare material, unusual source' yes '_reflns.d_resolution_high' 'limited data is a problem here' yes '_crystal.magnetic_permeability' 'unusual value for this material' no ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__publ_manuscript_incl.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_publ_manuscript_incl.entry_id' _item.mandatory_code yes save_ save__publ_manuscript_incl.extra_defn _item_description.description ; Flags whether the corresponding data item marked for inclusion in a journal request list is a standard CIF definition or not. ; _item.name '_publ_manuscript_incl.extra_defn' _item.category_id publ_manuscript_incl _item.mandatory_code no _item_aliases.alias_name '_publ_manuscript_incl_extra_defn' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value _item_enumeration.detail no 'not a standard CIF data name' n 'abbreviation for "no"' yes 'a standard CIF data name' y 'abbreviation for "yes"' save_ save__publ_manuscript_incl.extra_info _item_description.description ; A short note indicating the reason why the author wishes the corresponding data item marked for inclusion in the journal request list to be published. ; _item.name '_publ_manuscript_incl.extra_info' _item.category_id publ_manuscript_incl _item.mandatory_code no _item_aliases.alias_name '_publ_manuscript_incl_extra_info' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'to emphasise very special sites' 'rare material from unusual source' 'the limited data is a problem here' 'a new data quantity needed here' save_ save__publ_manuscript_incl.extra_item _item_description.description ; Specifies the inclusion of specific data into a manuscript which are not normally requested by the journal. The values of this item are the extra data names (which MUST be enclosed in single quotes) that will be added to the journal request list. ; _item.name '_publ_manuscript_incl.extra_item' _item.category_id publ_manuscript_incl _item.mandatory_code no _item_aliases.alias_name '_publ_manuscript_incl_extra_item' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case '_atom_site.symmetry_multiplicity' '_chemical.compound_source' '_reflns.d_resolution_high' '_crystal.magnetic_permeability' save_ ############ ## REFINE ## ############ save_refine _category.description ; Data items in the REFINE category record details about the structure-refinement parameters. ; _category.id refine _category.mandatory_code no _category_key.name '_refine.entry_id' loop_ _category_group.id 'inclusive_group' 'refine_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _refine.entry_id '5HVP' _refine.ls_number_reflns_obs 12901 _refine.ls_number_restraints 6609 _refine.ls_number_parameters 7032 _refine.ls_R_Factor_obs 0.176 _refine.ls_weighting_scheme calc _refine.ls_weighting_details ; Sigdel model of Konnert-Hendrickson: Sigdel: Afsig + Bfsig*(sin(theta)/lambda-1/6) Afsig = 22.0, Bfsig = -150.0 at beginning of refinement Afsig = 15.5, Bfsig = -50.0 at end of refinement ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _refine.details sfls:_F_calc_weight_full_matrix _refine.ls_structure_factor_coef F _refine.ls_matrix_type full _refine.ls_weighting_scheme calc _refine.ls_weighting_details 'w=1/(\s^2^(F)+0.0004F^2^)' _refine.ls_hydrogen_treatment 'refxyz except H332B noref' _refine.ls_extinction_method Zachariasen _refine.ls_extinction_coef 3514 _refine.ls_extinction_expression ; Larson, A. C. (1970). "Crystallographic Computing", edited by F. R. Ahmed. Eq. (22) p. 292. Copenhagen: Munksgaard. _refine.ls_abs_structure_details ; The absolute configuration was assigned to agree with the known chirality at C3 arising from its precursor l-leucine. ; _refine.ls_abs_structure_Flack 0 _refine.ls_number_reflns_obs 1408 _refine.ls_number_parameters 272 _refine.ls_number_restraints 0 _refine.ls_number_constraints 0 _refine.ls_R_factor_all .038 _refine.ls_R_factor_obs .034 _refine.ls_wR_factor_all .044 _refine.ls_wR_factor_obs .042 _refine.ls_goodness_of_fit_all 1.462 _refine.ls_goodness_of_fit_obs 1.515 _refine.ls_shift_over_esd_max .535 _refine.ls_shift_over_esd_mean .044 _refine.diff_density_min -.108 _refine.diff_density_max .131 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__refine.aniso_B[1][1] _item_description.description ; The [1][1] element of the matrix that defines the overall anisotropic displacement model if one was refined for this structure. ; _item.name '_refine.aniso_B[1][1]' _item.category_id refine _item.mandatory_code no _item_sub_category.id matrix _item_type.code float _item_units.code angstroms_squared save_ save__refine.aniso_B[1][2] _item_description.description ; The [1][2] element of the matrix that defines the overall anisotropic displacement model if one was refined for this structure. ; _item.name '_refine.aniso_B[1][2]' _item.category_id refine _item.mandatory_code no _item_sub_category.id matrix _item_type.code float _item_units.code angstroms_squared save_ save__refine.aniso_B[1][3] _item_description.description ; The [1][3] element of the matrix that defines the overall anisotropic displacement model if one was refined for this structure. ; _item.name '_refine.aniso_B[1][3]' _item.category_id refine _item.mandatory_code no _item_sub_category.id matrix _item_type.code float _item_units.code angstroms_squared save_ save__refine.aniso_B[2][2] _item_description.description ; The [2][2] element of the matrix that defines the overall anisotropic displacement model if one was refined for this structure. ; _item.name '_refine.aniso_B[2][2]' _item.category_id refine _item.mandatory_code no _item_sub_category.id matrix _item_type.code float _item_units.code angstroms_squared save_ save__refine.aniso_B[2][3] _item_description.description ; The [2][3] element of the matrix that defines the overall anisotropic displacement model if one was refined for this structure. ; _item.name '_refine.aniso_B[2][3]' _item.category_id refine _item.mandatory_code no _item_sub_category.id matrix _item_type.code float _item_units.code angstroms_squared save_ save__refine.aniso_B[3][3] _item_description.description ; The [3][3] element of the matrix that defines the overall anisotropic displacement model if one was refined for this structure. ; _item.name '_refine.aniso_B[3][3]' _item.category_id refine _item.mandatory_code no _item_sub_category.id matrix _item_type.code float _item_units.code angstroms_squared save_ save__refine.B_iso_max _item_description.description ; The maximum isotropic displacement parameter (B value) found in the coordinate set. ; _item.name '_refine.B_iso_max' _item.category_id refine _item.mandatory_code no _item_type.code float _item_units.code angstroms_squared save_ save__refine.B_iso_mean _item_description.description ; The mean isotropic displacement parameter (B value) for the coordinate set. ; _item.name '_refine.B_iso_mean' _item.category_id refine _item.mandatory_code no _item_type.code float _item_units.code angstroms_squared save_ save__refine.B_iso_min _item_description.description ; The minimum isotropic displacement parameter (B value) found in the coordinate set. ; _item.name '_refine.B_iso_min' _item.category_id refine _item.mandatory_code no _item_type.code float _item_units.code angstroms_squared save_ save__refine.correlation_coeff_Fo_to_Fc _item_description.description ; The correlation coefficient between the observed and calculated structure factors for reflections included in the refinement. The correlation coefficient is scale-independent and gives an idea of the quality of the refined model. sum~i~(Fo~i~ Fc~i~ - ) R~corr~ = ------------------------------------------------------------ SQRT{sum~i~(Fo~i~)^2^-^2^} SQRT{sum~i~(Fc~i~)^2^-^2^} Fo = observed structure factors Fc = calculated structure factors <> denotes average value summation is over reflections included in the refinement ; _item.name '_refine.correlation_coeff_Fo_to_Fc' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine.ebi_Correlation_coeff_Fo_to_Fc' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 _item_type.code float save_ save__refine.correlation_coeff_Fo_to_Fc_free _item_description.description ; The correlation coefficient between the observed and calculated structure factors for reflections not included in the refinement (free reflections). The correlation coefficient is scale-independent and gives an idea of the quality of the refined model. sum~i~(Fo~i~ Fc~i~ - ) R~corr~ = ------------------------------------------------------------ SQRT{sum~i~(Fo~i~)^2^-^2^} SQRT{sum~i~(Fc~i~)^2^-^2^} Fo = observed structure factors Fc = calculated structure factors <> denotes average value summation is over reflections not included in the refinement (free reflections) ; _item.name '_refine.correlation_coeff_Fo_to_Fc_free' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine.ebi_Correlation_coeff_Fo_to_Fc_free' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 _item_type.code float save_ save__refine.details _item_description.description ; Description of special aspects of the refinement process. ; _item.name '_refine.details' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_special_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__refine.diff_density_max _item_description.description ; The maximum value of the electron density in the final difference Fourier map. ; _item.name '_refine.diff_density_max' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_diff_density_max' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_related.related_name '_refine.diff_density_max_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code electrons_per_angstroms_cubed save_ save__refine.diff_density_max_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _refine.diff_density_max. ; _item.name '_refine.diff_density_max_esd' _item.category_id refine _item.mandatory_code no # _item_default.value 0.0 _item_related.related_name '_refine.diff_density_max' _item_related.function_code associated_value _item_type.code float _item_units.code electrons_per_angstroms_cubed save_ save__refine.diff_density_min _item_description.description ; The minimum value of the electron density in the final difference Fourier map. ; _item.name '_refine.diff_density_min' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_diff_density_min' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_related.related_name '_refine.diff_density_min_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code electrons_per_angstroms_cubed save_ save__refine.diff_density_min_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _refine.diff_density_min. ; _item.name '_refine.diff_density_min_esd' _item.category_id refine _item.mandatory_code no # _item_default.value 0.0 _item_related.related_name '_refine.diff_density_min' _item_related.function_code associated_value _item_type.code float _item_units.code electrons_per_angstroms_cubed save_ save__refine.diff_density_rms _item_description.description ; The root-mean-square-deviation of the electron density in the final difference Fourier map. This value is measured with respect to the arithmetic mean density and is derived from summations over each grid point in the asymmetric unit of the cell. This quantity is useful for assessing the significance of the values of _refine.diff_density_min and _refine.diff_density_max, and also for defining suitable contour levels. ; _item.name '_refine.diff_density_rms' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_diff_density_rms' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_related.related_name '_refine.diff_density_rms_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code electrons_per_angstroms_cubed save_ save__refine.diff_density_rms_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _refine.diff_density_rms. ; _item.name '_refine.diff_density_rms_esd' _item.category_id refine _item.mandatory_code no # _item_default.value 0.0 _item_related.related_name '_refine.diff_density_rms' _item_related.function_code associated_value _item_type.code float _item_units.code electrons_per_angstroms_cubed save_ save__refine.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_refine.entry_id' _item.mandatory_code yes save_ save__refine.ls_abs_structure_details _item_description.description ; The nature of the absolute structure and how it was determined. For example, this may describe the Friedel pairs used. ; _item.name '_refine.ls_abs_structure_details' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_ls_abs_structure_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__refine.ls_abs_structure_Flack _item_description.description ; The measure of absolute structure (enantiomorph or polarity) as defined by Flack (1983). For centrosymmetric structures, the only permitted value, if the data name is present, is 'inapplicable', represented by '.' . For noncentrosymmetric structures the value must lie in the 99.97% Gaussian confidence interval -3u =< x =< 1 + 3u and a standard uncertainty (estimated standard deviation) u must be supplied. The item range of [0.0:1.0] is correctly interpreted as meaning (0.0 - 3u) =< x =< (1.0 + 3u). Ref: Flack, H. D. (1983). Acta Cryst. A39, 876-881. ; _item.name '_refine.ls_abs_structure_Flack' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_ls_abs_structure_Flack' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 0.0 0.0 0.0 _item_related.related_name '_refine.ls_abs_structure_Flack_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd save_ save__refine.ls_abs_structure_Flack_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _refine.ls_abs_structure_Flack. ; _item.name '_refine.ls_abs_structure_Flack_esd' _item.category_id refine _item.mandatory_code no # _item_default.value 0.0 _item_related.related_name '_refine.ls_abs_structure_Flack' _item_related.function_code associated_value _item_type.code float save_ save__refine.ls_abs_structure_Rogers _item_description.description ; The measure of absolute structure (enantiomorph or polarity) as defined by Rogers. The value must lie in the 99.97% Gaussian confidence interval -1 -3u =< \h =< 1 + 3u and a standard uncertainty (estimated standard deviation) u must be supplied. The item range of [-1.0, 1.0] is correctly interpreted as meaning (-1.0 - 3u) =< \h =< (1.0 + 3u). Ref: Rogers, D. (1981). Acta Cryst. A37, 734-741. ; _item.name '_refine.ls_abs_structure_Rogers' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_ls_abs_structure_Rogers' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 -1.0 -1.0 -1.0 _item_related.related_name '_refine.ls_abs_structure_Rogers_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd save_ save__refine.ls_abs_structure_Rogers_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _refine.ls_abs_structure_Rogers. ; _item.name '_refine.ls_abs_structure_Rogers_esd' _item.category_id refine _item.mandatory_code no # _item_default.value 0.0 _item_related.related_name '_refine.ls_abs_structure_Rogers' _item_related.function_code associated_value _item_type.code float save_ save__refine.ls_d_res_high _item_description.description ; The smallest value for the interplanar spacings for the reflection data used in the refinement in angstroms. This is called the highest resolution. ; _item.name '_refine.ls_d_res_high' _item.category_id refine _item.mandatory_code yes _item_aliases.alias_name '_refine_ls_d_res_high' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__refine.ls_d_res_low _item_description.description ; The largest value for the interplanar spacings for the reflection data used in the refinement in angstroms. This is called the lowest resolution. ; _item.name '_refine.ls_d_res_low' _item.category_id refine _item.mandatory_code yes _item_aliases.alias_name '_refine_ls_d_res_low' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__refine.ls_extinction_coef _item_description.description ; The extinction coefficient used to calculate the correction factor applied to the structure-factor data. The nature of the extinction coefficient is given in the definitions of _refine.ls_extinction_expression and _refine.ls_extinction_method. For the 'Zachariasen' method it is the r* value; for the 'Becker-Coppens type 1 isotropic' method it is the 'g' value, and for 'Becker-Coppens type 2 isotropic' corrections it is the 'rho' value. Note that the magnitude of these values is usually of the order of 10000. Ref: Becker, P. J. & Coppens, P. (1974). Acta Cryst. A30, 129-47, 148-153. Zachariasen, W. H. (1967). Acta Cryst. 23, 558-564. Larson, A. C. (1967). Acta Cryst. 23, 664-665. ; _item.name '_refine.ls_extinction_coef' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_ls_extinction_coef' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_related.related_name '_refine.ls_extinction_coef_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd _item_examples.case 3472 _item_examples.detail 'Zachariasen coefficient r* = 0.347 E04' save_ save__refine.ls_extinction_coef_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _refine.ls_extinction_coef. ; _item.name '_refine.ls_extinction_coef_esd' _item.category_id refine _item.mandatory_code no # _item_default.value 0.0 _item_related.related_name '_refine.ls_extinction_coef' _item_related.function_code associated_value _item_type.code float save_ save__refine.ls_extinction_expression _item_description.description ; A description of or reference to the extinction-correction equation used to apply the data item _refine.ls_extinction_coef. This information must be sufficient to reproduce the extinction-correction factors applied to the structure factors. ; _item.name '_refine.ls_extinction_expression' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_ls_extinction_expression' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; Larson, A. C. (1970). "Crystallographic Computing", edited by F. R. Ahmed. Eq. (22), p.292. Copenhagen: Munksgaard. ; save_ save__refine.ls_extinction_method _item_description.description ; A description of the extinction-correction method applied. This description should include information about the correction method, either 'Becker-Coppens' or 'Zachariasen'. The latter is sometimes referred to as the 'Larson' method even though it employs Zachariasen's formula. The Becker-Coppens procedure is referred to as 'type 1' when correcting secondary extinction dominated by the mosaic spread; as 'type 2' when secondary extinction is dominated by particle size and includes a primary extinction component; and as 'mixed' when there is a mixture of types 1 and 2. For the Becker-Coppens method, it is also necessary to set the mosaic distribution as either 'Gaussian' or 'Lorentzian' and the nature of the extinction as 'isotropic' or 'anisotropic'. Note that if either the 'mixed' or 'anisotropic' corrections are applied, the multiple coefficients cannot be contained in *_extinction_coef and must be listed in _refine.details. Ref: Becker, P. J. & Coppens, P. (1974). Acta Cryst. A30, 129-147, 148-153. Zachariasen, W. H. (1967). Acta Cryst. 23, 558- 564. Larson, A. C. (1967). Acta Cryst. 23, 664-665. ; _item.name '_refine.ls_extinction_method' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_ls_extinction_method' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 # _item_default.value Zachariasen _item_type.code text _item_examples.case 'B-C type 2 Gaussian isotropic' save_ save__refine.ls_goodness_of_fit_all _item_description.description ; The least-squares goodness-of-fit parameter S for all data after the final cycle of refinement. Ideally, account should be taken of parameters restrained in the least-squares refinement. See also the definition of _refine.ls_restrained_S_all. ( sum|w |Y~obs~ - Y~calc~|^2^| )^1/2^ S = ( ---------------------------- ) ( N~ref~ - N~param~ ) Y~obs~ = the observed coefficients (see _refine.ls_structure_factor_coef) Y~calc~ = the calculated coefficients (see _refine.ls_structure_factor_coef) w = the least-squares reflection weight [1/(e.s.d. squared)] N~ref~ = the number of reflections used in the refinement N~param~ = the number of refined parameters sum is taken over the specified reflections ; _item.name '_refine.ls_goodness_of_fit_all' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_ls_goodness_of_fit_all' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_refine.ls_goodness_of_fit_all_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd save_ save__refine.ls_goodness_of_fit_all_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _refine.ls_goodness_of_fit_all. ; _item.name '_refine.ls_goodness_of_fit_all_esd' _item.category_id refine _item.mandatory_code no # _item_default.value 0.0 _item_related.related_name '_refine.ls_goodness_of_fit_all' _item_related.function_code associated_value _item_type.code float save_ save__refine.ls_goodness_of_fit_obs _item_description.description ; The least-squares goodness-of-fit parameter S for reflection data classified as 'observed' (see _reflns.observed_criterion) after the final cycle of refinement. Ideally, account should be taken of parameters restrained in the least-squares refinement. See also the definition of _refine.ls_restrained_S_obs. ( sum|w |Y~obs~ - Y~calc~|^2^| )^1/2^ S = ( ---------------------------- ) ( N~ref~ - N~param~ ) Y~obs~ = the observed coefficients (see _refine.ls_structure_factor_coef) Y~calc~ = the calculated coefficients (see _refine.ls_structure_factor_coef) w = the least-squares reflection weight [1/(e.s.d. squared)] N~ref~ = the number of reflections used in the refinement N~param~ = the number of refined parameters sum is taken over the specified reflections ; _item.name '_refine.ls_goodness_of_fit_obs' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_ls_goodness_of_fit_obs' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_refine.ls_goodness_of_fit_obs_esd' _item_related.function_code associated_esd _item_type.code float _item_type_conditions.code esd save_ save__refine.ls_goodness_of_fit_obs_esd _item_description.description ; The standard uncertainty (estimated standard deviation) of _refine.ls_goodness_of_fit_obs. ; _item.name '_refine.ls_goodness_of_fit_obs_esd' _item.category_id refine _item.mandatory_code no # _item_default.value 0.0 _item_related.related_name '_refine.ls_goodness_of_fit_obs' _item_related.function_code associated_value _item_type.code float save_ save__refine.ls_hydrogen_treatment _item_description.description ; Treatment of hydrogen atoms in the least-squares refinement. ; _item.name '_refine.ls_hydrogen_treatment' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_ls_hydrogen_treatment' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 # _item_default.value undef _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail refall 'refined all H-atom parameters' refxyz 'refined H-atom coordinates only' refU 'refined H-atom U's only' noref 'no refinement of H-atom parameters' constr 'H-atom parameters constrained' mixed 'some constrained, some independent' undef 'H-atom parameters not defined' save_ save__refine.ls_matrix_type _item_description.description ; Type of matrix used to accumulate the least-squares derivatives. ; _item.name '_refine.ls_matrix_type' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_ls_matrix_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 # _item_default.value full _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail full 'full' fullcycle 'full with fixed elements per cycle' atomblock 'block diagonal per atom' userblock 'user-defined blocks' diagonal 'diagonal elements only' sparse 'selected elements only' save_ save__refine.ls_number_constraints _item_description.description ; The number of constrained (non-refined or dependent) parameters in the least-squares process. These may be due to symmetry or any other constraint process (e.g. rigid-body refinement). See also _atom_site.constraints and _atom_site.refinement_flags. A general description of constraints may appear in _refine.details. ; _item.name '_refine.ls_number_constraints' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_ls_number_constraints' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 # _item_default.value 0 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__refine.ls_number_parameters _item_description.description ; The number of parameters refined in the least-squares process. If possible, this number should include some contribution from the restrained parameters. The restrained parameters are distinct from the constrained parameters (where one or more parameters are linearly dependent on the refined value of another). Least-squares restraints often depend on geometry or energy considerations and this makes their direct contribution to this number, and to the goodness-of-fit calculation, difficult to assess. ; _item.name '_refine.ls_number_parameters' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_ls_number_parameters' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__refine.ls_number_reflns_all _item_description.description ; The number of reflections that satisfy the resolution limits established by _refine.ls_d_res_high and _refine.ls_d_res_low. ; _item.name '_refine.ls_number_reflns_all' _item.category_id refine _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__refine.ls_number_reflns_obs _item_description.description ; The number of reflections that satisfy the resolution limits established by _refine.ls_d_res_high and _refine.ls_d_res_low and the observation limit established by _reflns.observed_criterion. ; _item.name '_refine.ls_number_reflns_obs' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_ls_number_reflns' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__refine.ls_number_reflns_R_free _item_description.description ; The number of reflections that satisfy the resolution limits established by _refine.ls_d_res_high and _refine.ls_d_res_low and the observation limit established by _reflns.observed_criterion, and that were used as the test reflections (i.e. were excluded from the refinement) when the refinement included the calculation of a 'free' R factor. Details of how reflections were assigned to the working and test sets are given in _reflns.R_free_details. ; _item.name '_refine.ls_number_reflns_R_free' _item.category_id refine _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__refine.ls_number_reflns_R_work _item_description.description ; The number of reflections that satisfy the resolution limits established by _refine.ls_d_res_high and _refine.ls_d_res_low and the observation limit established by _reflns.observed_criterion, and that were used as the working reflections (i.e. were included in the refinement) when the refinement included the calculation of a 'free' R factor. Details of how reflections were assigned to the working and test sets are given in _reflns.R_free_details. ; _item.name '_refine.ls_number_reflns_R_work' _item.category_id refine _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__refine.ls_number_restraints _item_description.description ; The number of restrained parameters. These are parameters which are not directly dependent on another refined parameter. Restrained parameters often involve geometry or energy dependencies. See also _atom_site.constraints and _atom_site.refinement_flags. A general description of refinement constraints may appear in _refine.details. ; _item.name '_refine.ls_number_restraints' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_ls_number_restraints' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__refine.ls_percent_reflns_obs _item_description.description ; The number of reflections that satisfy the resolution limits established by _refine.ls_d_res_high and _refine.ls_d_res_low and the observation limit established by _reflns.observed_criterion, expressed as a percentage of the number of geometrically observable reflections that satisfy the resolution limits. ; _item.name '_refine.ls_percent_reflns_obs' _item.category_id refine _item.mandatory_code no _item_type.code float save_ save__refine.ls_percent_reflns_R_free _item_description.description ; The number of reflections that satisfy the resolution limits established by _refine.ls_d_res_high and _refine.ls_d_res_low and the observation limit established by _reflns.observed_criterion, and that were used as the test reflections (i.e. were excluded from the refinement) when the refinement included the calculation of a 'free' R factor, expressed as a percentage of the number of geometrically observable reflections that satisfy the resolution limits. ; _item.name '_refine.ls_percent_reflns_R_free' _item.category_id refine _item.mandatory_code no _item_type.code float save_ save__refine.ls_R_factor_all _item_description.description ; Residual factor R for all reflections that satisfy the resolution limits established by _refine.ls_d_res_high and _refine.ls_d_res_low. sum|F~obs~ - F~calc~| R = --------------------- sum|F~obs~| F~obs~ = the observed structure-factor amplitudes F~calc~ = the calculated structure-factor amplitudes sum is taken over the specified reflections ; _item.name '_refine.ls_R_factor_all' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_ls_R_factor_all' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_refine.ls_wR_factor_all' _item_related.function_code alternate _item_type.code float save_ save__refine.ls_R_factor_obs _item_description.description ; Residual factor R for reflections that satisfy the resolution limits established by _refine.ls_d_res_high and _refine.ls_d_res_low and the observation limit established by _reflns.observed_criterion. _refine.ls_R_factor_obs should not be confused with _refine.ls_R_factor_R_work; the former reports the results of a refinement in which all observed reflections were used, the latter a refinement in which a subset of the observed reflections were excluded from refinement for the calculation of a 'free' R factor. However, it would be meaningful to quote both values if a 'free' R factor were calculated for most of the refinement, but all of the observed reflections were used in the final rounds of refinement; such a protocol should be explained in _refine.details. sum|F~obs~ - F~calc~| R = --------------------- sum|F~obs~| F~obs~ = the observed structure-factor amplitudes F~calc~ = the calculated structure-factor amplitudes sum is taken over the specified reflections ; _item.name '_refine.ls_R_factor_obs' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_ls_R_factor_obs' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_refine.ls_wR_factor_obs' _item_related.function_code alternate _item_type.code float save_ save__refine.ls_R_factor_R_free _item_description.description ; Residual factor R for reflections that satisfy the resolution limits established by _refine.ls_d_res_high and _refine.ls_d_res_low and the observation limit established by _reflns.observed_criterion, and that were used as the test reflections (i.e. were excluded from the refinement) when the refinement included the calculation of a 'free' R factor. Details of how reflections were assigned to the working and test sets are given in _reflns.R_free_details. sum|F~obs~ - F~calc~| R = --------------------- sum|F~obs~| F~obs~ = the observed structure-factor amplitudes F~calc~ = the calculated structure-factor amplitudes sum is taken over the specified reflections ; _item.name '_refine.ls_R_factor_R_free' _item.category_id refine _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 loop_ _item_related.related_name _item_related.function_code '_refine.ls_wR_factor_R_free' alternate '_refine.ls_R_factor_R_free_error' associated_error _item_type.code float save_ save__refine.ls_R_factor_R_free_error _item_description.description ; The estimated error in _refine.ls_R_factor_R_free. The method used to estimate the error is described in the item _refine.ls_R_factor_R_free_error_details. ; _item.name '_refine.ls_R_factor_R_free_error' _item.category_id refine _item.mandatory_code no _item_related.related_name '_refine.ls_R_factor_R_free' _item_related.function_code associated_value _item_type.code float save_ save__refine.ls_R_factor_R_free_error_details _item_description.description ; Special aspects of the method used to estimated the error in _refine.ls_R_factor_R_free. ; _item.name '_refine.ls_R_factor_R_free_error_details' _item.category_id refine _item.mandatory_code no _item_type.code text save_ save__refine.ls_R_factor_R_work _item_description.description ; Residual factor R for reflections that satisfy the resolution limits established by _refine.ls_d_res_high and _refine.ls_d_res_low and the observation limit established by _reflns.observed_criterion, and that were used as the working reflections (i.e. were included in the refinement) when the refinement included the calculation of a 'free' R factor. Details of how reflections were assigned to the working and test sets are given in _reflns.R_free_details. _refine.ls_R_factor_obs should not be confused with _refine.ls_R_factor_R_work; the former reports the results of a refinement in which all observed reflections were used, the latter a refinement in which a subset of the observed reflections were excluded from refinement for the calculation of a 'free' R factor. However, it would be meaningful to quote both values if a 'free' R factor were calculated for most of the refinement, but all of the observed reflections were used in the final rounds of refinement; such a protocol should be explained in _refine.details. sum|F~obs~ - F~calc~| R = --------------------- sum|F~obs~| F~obs~ = the observed structure-factor amplitudes F~calc~ = the calculated structure-factor amplitudes sum is taken over the specified reflections ; _item.name '_refine.ls_R_factor_R_work' _item.category_id refine _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_refine.ls_wR_factor_R_work' _item_related.function_code alternate _item_type.code float save_ save__refine.ls_R_Fsqd_factor_obs _item_description.description ; Residual factor R(Fsqd) for reflections that satisfy the resolution limits established by _refine.ls_d_res_high and _refine.ls_d_res_low and the observation limit established by _reflns.observed_criterion, calculated on the squares of the observed and calculated structure-factor amplitudes. sum|F~obs~^2^ - F~calc~^2^| R(Fsqd) = --------------------------- sum|F~obs~^2^| F~obs~^2^ = squares of the observed structure-factor amplitudes F~calc~^2^ = squares of the calculated structure-factor amplitudes sum is taken over the specified reflections ; _item.name '_refine.ls_R_Fsqd_factor_obs' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_ls_R_Fsqd_factor' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__refine.ls_R_I_factor_obs _item_description.description ; Residual factor R(I) for reflections that satisfy the resolution limits established by _refine.ls_d_res_high and _refine.ls_d_res_low and the observation limit established by _reflns.observed_criterion, calculated on the estimated reflection intensities. This is most often calculated in Rietveld refinements against powder data, where it is referred to as R~B~ or R~Bragg~. sum|I~obs~ - I~calc~| R(I) = --------------------- sum|I~obs~| I~obs~ = the net observed intensities I~calc~ = the net calculated intensities sum is taken over the specified reflections ; _item.name '_refine.ls_R_I_factor_obs' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_ls_R_I_factor' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__refine.ls_redundancy_reflns_all _item_description.description ; The ratio of the total number of observations of the reflections that satisfy the resolution limits established by _refine.ls_d_res_high and _refine.ls_d_res_low to the number of crystallographically unique reflections that satisfy the same limits. ; _item.name '_refine.ls_redundancy_reflns_all' _item.category_id refine _item.mandatory_code no _item_type.code float save_ save__refine.ls_redundancy_reflns_obs _item_description.description ; The ratio of the total number of observations of the reflections that satisfy the resolution limits established by _refine.ls_d_res_high and _refine.ls_d_res_low and the observation limit established by _reflns.observed_criterion to the number of crystallographically unique reflections that satisfy the same limits. ; _item.name '_refine.ls_redundancy_reflns_obs' _item.category_id refine _item.mandatory_code no _item_type.code float save_ save__refine.ls_restrained_S_all _item_description.description ; The least-squares goodness-of-fit parameter S' for all reflections after the final cycle of least-squares refinement. This parameter explicitly includes the restraints applied in the least-squares process. See also the definition of _refine.ls_goodness_of_fit_all. ( sum |w |Y~obs~ - Y~calc~|^2^| )^1/2^ ( + sum~r~|w~r~ |P~calc~ - P~targ~|^2^| ) S' = ( ------------------------------------- ) ( N~ref~ + N~restr~ - N~param~ ) Y~obs~ = the observed coefficients (see _refine.ls_structure_factor_coef) Y~calc~ = the calculated coefficients (see _refine.ls_structure_factor_coef) w = the least-squares reflection weight [1/(e.s.d. squared)] P~calc~ = the calculated restraint values P~targ~ = the target restraint values w~r~ = the restraint weight N~ref~ = the number of reflections used in the refinement (see _refine.ls_number_reflns_obs) N~restr~ = the number of restraints (see _refine.ls_number_restraints) N~param~ = the number of refined parameters (see _refine.ls_number_parameters) sum is taken over the specified reflections sumr is taken over the restraints ; _item.name '_refine.ls_restrained_S_all' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_ls_restrained_S_all' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__refine.ls_restrained_S_obs _item_description.description ; The least-squares goodness-of-fit parameter S' for reflection data classified as observed (see _reflns.observed_criterion) after the final cycle of least-squares refinement. This parameter explicitly includes the restraints applied in the least-squares process. See also the definition of _refine.ls_goodness_of_fit_obs. ( sum |w |Y~obs~ - Y~calc~|^2^| )^1/2^ ( + sum~r~|w~r~ |P~calc~ - P~targ~|^2^| ) S' = ( ------------------------------------- ) ( N~ref~ + N~restr~ - N~param~ ) Y~obs~ = the observed coefficients (see _refine.ls_structure_factor_coef) Y~calc~ = the calculated coefficients (see _refine.ls_structure_factor_coef) w = the least-squares reflection weight [1/(e.s.d. squared)] P~calc~ = the calculated restraint values P~targ~ = the target restraint values w~r~ = the restraint weight N~ref~ = the number of reflections used in the refinement (see _refine.ls_number_reflns_obs) N~restr~ = the number of restraints (see _refine.ls_number_restraints) N~param~ = the number of refined parameters (see _refine.ls_number_parameters) sum is taken over the specified reflections sumr is taken over the restraints ; _item.name '_refine.ls_restrained_S_obs' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_ls_restrained_S_obs' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__refine.ls_shift_over_esd_max _item_description.description ; The largest ratio of the final least-squares parameter shift to the final standard uncertainty (estimated standard deviation). ; _item.name '_refine.ls_shift_over_esd_max' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_ls_shift/esd_max' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__refine.ls_shift_over_esd_mean _item_description.description ; The average ratio of the final least-squares parameter shift to the final standard uncertainty (estimated standard deviation). ; _item.name '_refine.ls_shift_over_esd_mean' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_ls_shift/esd_mean' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__refine.ls_structure_factor_coef _item_description.description ; Structure-factor coefficient |F|, F^2^ or I used in the least- squares refinement process. ; _item.name '_refine.ls_structure_factor_coef' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_ls_structure_factor_coef' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 # _item_default.value F _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail F 'structure-factor magnitude' Fsqd 'structure factor squared' Inet 'net intensity' save_ save__refine.ls_weighting_details _item_description.description ; A description of special aspects of the weighting scheme used in least-squares refinement. Used to describe the weighting when the value of _refine.ls_weighting_scheme is specified as 'calc'. ; _item.name '_refine.ls_weighting_details' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_ls_weighting_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; Sigdel model of Konnert-Hendrickson: Sigdel = Afsig + Bfsig*(sin(theta)/lambda-1/6) Afsig = 22.0, Bfsig = 150.0 at the beginning of refinement. Afsig = 16.0, Bfsig = 60.0 at the end of refinement. ; save_ save__refine.ls_weighting_scheme _item_description.description ; The weighting scheme applied in the least-squares process. The standard code may be followed by a description of the weight (but see _refine.ls_weighting_details for a preferred approach). ; _item.name '_refine.ls_weighting_scheme' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_ls_weighting_scheme' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 # _item_default.value sigma _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail sigma 'based on measured e.s.d.'s' unit 'unit or no weights applied' calc 'calculated weights applied' save_ save__refine.ls_wR_factor_all _item_description.description ; Weighted residual factor wR for all reflections that satisfy the resolution limits established by _refine.ls_d_res_high and _refine.ls_d_res_low. ( sum|w |Y~obs~ - Y~calc~|^2^| )^1/2^ wR = ( ---------------------------- ) ( sum|w Y~obs~^2^| ) Y~obs~ = the observed amplitude specified by _refine.ls_structure_factor_coef Y~calc~ = the calculated amplitude specified by _refine.ls_structure_factor_coef w = the least-squares weight sum is taken over the specified reflections ; _item.name '_refine.ls_wR_factor_all' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_ls_wR_factor_all' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_refine.ls_R_factor_all' _item_related.function_code alternate _item_type.code float save_ save__refine.ls_wR_factor_obs _item_description.description ; Weighted residual factor wR for reflections that satisfy the resolution limits established by _refine.ls_d_res_high and _refine.ls_d_res_low and the observation limit established by _reflns.observed_criterion. ( sum|w |Y~obs~ - Y~calc~|^2^| )^1/2^ wR = ( ---------------------------- ) ( sum|w Y~obs~^2^| ) Y~obs~ = the observed amplitude specified by _refine.ls_structure_factor_coef Y~calc~ = the calculated amplitude specified by _refine.ls_structure_factor_coef w = the least-squares weight sum is taken over the specified reflections ; _item.name '_refine.ls_wR_factor_obs' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine_ls_wR_factor_obs' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_refine.ls_R_factor_obs' _item_related.function_code alternate _item_type.code float save_ save__refine.ls_wR_factor_R_free _item_description.description ; Weighted residual factor wR for reflections that satisfy the resolution limits established by _refine.ls_d_res_high and _refine.ls_d_res_low and the observation limit established by _reflns.observed_criterion, and that were used as the test reflections (i.e. were excluded from the refinement) when the refinement included the calculation of a 'free' R factor. Details of how reflections were assigned to the working and test sets are given in _reflns.R_free_details. ( sum|w |Y~obs~ - Y~calc~|^2^| )^1/2^ wR = ( ---------------------------- ) ( sum|w Y~obs~^2^| ) Y~obs~ = the observed amplitude specified by _refine.ls_structure_factor_coef Y~calc~ = the calculated amplitude specified by _refine.ls_structure_factor_coef w = the least-squares weight sum is taken over the specified reflections ; _item.name '_refine.ls_wR_factor_R_free' _item.category_id refine _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_refine.ls_R_factor_R_free' _item_related.function_code alternate _item_type.code float save_ save__refine.ls_wR_factor_R_work _item_description.description ; Weighted residual factor wR for reflections that satisfy the resolution limits established by _refine.ls_d_res_high and _refine.ls_d_res_low and the observation limit established by _reflns.observed_criterion, and that were used as the working reflections (i.e. were included in the refinement) when the refinement included the calculation of a 'free' R factor. Details of how reflections were assigned to the working and test sets are given in _reflns.R_free_details. ( sum|w |Y~obs~ - Y~calc~|^2^| )^1/2^ wR = ( ---------------------------- ) ( sum|w Y~obs~^2^| ) Y~obs~ = the observed amplitude specified by _refine.ls_structure_factor_coef Y~calc~ = the calculated amplitude specified by _refine.ls_structure_factor_coef w = the least-squares weight sum is taken over the specified reflections ; _item.name '_refine.ls_wR_factor_R_work' _item.category_id refine _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_refine.ls_R_factor_R_work' _item_related.function_code alternate _item_type.code float save_ save__refine.occupancy_max _item_description.description ; The maximum value for occupancy found in the coordinate set. ; _item.name '_refine.occupancy_max' _item.category_id refine _item.mandatory_code no # _item_default.value 1.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__refine.occupancy_min _item_description.description ; The minimum value for occupancy found in the coordinate set. ; _item.name '_refine.occupancy_min' _item.category_id refine _item.mandatory_code no # _item_default.value 1.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__refine.overall_SU_B _item_description.description ; The overall standard uncertainty (estimated standard deviation) of the displacement parameters based on a maximum-likelihood residual. The overall standard uncertainty (sigma~B~)^2 gives an idea of the uncertainty in the B values of averagely defined atoms (atoms with B values equal to the average B value). N_a (sigma~B~)^2 = 8 ---------------------------------------------- sum~i~ {[1/Sigma - (E_o)^2 (1-m^2)](SUM_AS)s^4} SUM_AS = (sigma_A)^2/Sigma^2 N_a = number of atoms Sigma = (sigma_{E;exp})^2 + epsilon [1-(sigma_A)^2] E_o = normalized structure factors sigma_{E;exp} = experimental uncertainties of normalized structure factors sigma_A = SQRT(Sigma_P/Sigma_N) estimated using maximum likelihood Sigma_P = sum_{atoms in model} f^2 Sigma_N = sum_{atoms in crystal} f^2 f = form factor of atoms delta_x = expected error m = figure of merit of phases of reflections included in the summation s = reciprocal-space vector epsilon = multiplicity of diffracting plane summation is over all reflections included in refinement Ref: (sigma_A estimation) "Refinement of macromolecular structures by the maximum-likelihood method", Murshudov, G. N., Vagin, A. A. & Dodson, E. J. (1997). Acta Cryst. D53, 240-255. (SU ML estimation) Murshudov, G. N. & Dodson, E. J. (1997). Simplified error estimation a la Cruickshank in macromolecular crystallography. CCP4 Newsletter on Protein Crystallography, No. 33, January 1997, pp. 31-39. http://www.ccp4.ac.uk/newsletters/newsletter33/murshudov.html ; _item.name '_refine.overall_SU_B' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine.ebi_Overall_ESU_B' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 _item_type.code float save_ save__refine.overall_SU_ML _item_description.description ; The overall standard uncertainty (estimated standard deviation) of the positional parameters based on a maximum likelihood residual. The overall standard uncertainty (sigma~X~)^2 gives an idea of the uncertainty in the position of averagely defined atoms (atoms with B values equal to average B value) 3 N_a (sigma~X~)^2 = ----------------------------------------------------- 8 pi^2 sum~i~ {[1/Sigma - (E_o)^2 (1-m^2)](SUM_AS)s^2} SUM_AS = (sigma_A)^2/Sigma^2) N_a = number of atoms Sigma = (sigma_{E;exp})^2 + epsilon [1-{sigma_A)^2] E_o = normalized structure factors sigma_{E;exp} = experimental uncertainties of normalized structure factors sigma_A = SQRT(Sigma_P/Sigma_N) estimated using maximum likelihood Sigma_P = sum_{atoms in model} f^2 Sigma_N = sum_{atoms in crystal} f^2 f = form factor of atoms delta_x = expected error m = figure of merit of phases of reflections included in the summation s = reciprocal-space vector epsilon = multiplicity of the diffracting plane summation is over all reflections included in refinement Ref: (sigma_A estimation) "Refinement of macromolecular structures by the maximum-likelihood method", Murshudov, G. N., Vagin, A. A. & Dodson, E. J. (1997). Acta Cryst. D53, 240-255. (SU ML estimation) Murshudov, G. N. & Dodson, E. J. (1997). Simplified error estimation a la Cruickshank in macromolecular crystallography. CCP4 Newsletter on Protein Crystallography, No. 33, January 1997, pp. 31-39. http://www.ccp4.ac.uk/newsletters/newsletter33/murshudov.html ; _item.name '_refine.overall_SU_ML' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine.ebi_Overall_ESU_ML' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 _item_type.code float save_ save__refine.overall_SU_R_Cruickshank_DPI _item_description.description ; The overall standard uncertainty (estimated standard deviation) of the displacement parameters based on the crystallographic R value, expressed in a formalism known as the dispersion precision indicator (DPI). The overall standard uncertainty (sigma~B~) gives an idea of the uncertainty in the B values of averagely defined atoms (atoms with B values equal to the average B value). N_a (sigma_B)^2 = 0.65 --------- (R_value)^2 (D_min)^2 C^(-2/3) (N_o-N_p) N_a = number of atoms N_o = number of reflections included in refinement N_p = number of refined parameters R_value = conventional crystallographic R value D_min = maximum resolution C = completeness of data Ref: Cruickshank, D. W. J. (1999). Acta Cryst. D55, 583-601. Murshudov, G. N. & Dodson, E. J. (1997). Simplified error estimation a la Cruickshank in macromolecular crystallography. CCP4 Newsletter on Protein Crystallography, No. 33, January 1997, pp. 31-39. http://www.ccp4.ac.uk/newsletters/newsletter33/murshudov.html ; _item.name '_refine.overall_SU_R_Cruickshank_DPI' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine.ebi_Overall_ESU_R_Cruickshanks_DPI' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 _item_type.code float save_ save__refine.overall_SU_R_free _item_description.description ; The overall standard uncertainty (estimated standard deviation) of the displacement parameters based on the free R value. The overall standard uncertainty gives an idea of the uncertainty in the B values of averagely defined atoms (atoms with B values equal to the average B value). N_a (sigma_B)^2 = 0.65 ----- (R_free)^2 (D_min)^2 C^(-2/3) N_o N_a = number of atoms N_o = number of reflections included in refinement R_free = conventional free crystallographic R value calculated using reflections not included in refinement D_min = maximum resolution C = completeness of data Ref: Cruickshank, D. W. J. (1999). Acta Cryst. D55, 583-601. Murshudov, G. N. & Dodson, E. J. (1997). Simplified error estimation a la Cruickshank in macromolecular crystallography. CCP4 Newsletter on Protein Crystallography, No. 33, January 1997, pp. 31-39. http://www.ccp4.ac.uk/newsletters/newsletter33/murshudov.html ; _item.name '_refine.overall_SU_R_free' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine.ebi_Overall_ESU_Rfree' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 _item_type.code float save_ save__refine.overall_FOM_free_R_set _item_description.description ; Average figure of merit of phases of reflections not included in the refinement. This value is derived from the likelihood function. FOM = I_1(X)/I_0(X) I_0, I_1 = zero- and first-order modified Bessel functions of the first kind X = sigma_A |E_o| |E_c|/SIGMA E_o, E_c = normalized observed and calculated structure factors sigma_A = SQRT(Sigma_P/Sigma_N) estimated using maximum likelihood Sigma_P = sum_{atoms in model} f^2 Sigma_N = sum_{atoms in crystal} f^2 f = form factor of atoms delta_x = expected error SIGMA = (sigma_{E;exp})^2 + epsilon [1-(sigma_A)^2] sigma_{E;exp} = uncertainties of normalized observed structure factors epsilon = multiplicity of the diffracting plane Ref: Murshudov, G. N., Vagin, A. A. & Dodson, E. J. (1997). Acta Cryst. D53, 240-255. ; _item.name '_refine.overall_FOM_free_R_set' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine.ebi_overall_FOM_free_Rset' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 _item_type.code float save_ save__refine.overall_FOM_work_R_set _item_description.description ; Average figure of merit of phases of reflections included in the refinement. This value is derived from the likelihood function FOM = I_1(X)/I_0(X) I_0, I_1 = zero- and first-order modified Bessel functions of the first kind X = sigma_A |E_o| |E_c|/SIGMA E_o, E_c = normalized observed and calculated structure factors sigma_A = SQRT(Sigma_P/Sigma_N) estimated using maximum likelihood Sigma_P = sum_{atoms in model} f^2 Sigma_N = sum_{atoms in crystal} f^2 f = form factor of atoms delta_x = expected error SIGMA = (sigma_{E;exp})^2 + epsilon [1-(sigma_A)^2] sigma_{E;exp} = uncertainties of normalized observed structure factors epsilon = multiplicity of diffracting plane Ref: Murshudov, G. N., Vagin, A. A. & Dodson, E. J. (1997). Acta Cryst. D53, 240-255. ; _item.name '_refine.overall_FOM_work_R_set' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine.ebi_overall_FOM_work_Rset' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 _item_type.code float save_ save__refine.solvent_model_details _item_description.description ; Special aspects of the solvent model used during refinement. ; _item.name '_refine.solvent_model_details' _item.category_id refine _item.mandatory_code no _item_type.code text save_ save__refine.solvent_model_param_bsol _item_description.description ; The value of the BSOL solvent-model parameter describing the average isotropic displacement parameter of disordered solvent atoms. This is one of the two parameters (the other is _refine.solvent_model_param_ksol) in Tronrud's method of modelling the contribution of bulk solvent to the scattering. The standard scale factor is modified according to the expression k0 exp(-B0 * s^2^)[1-KSOL * exp(-BSOL * s^2^)] where k0 and B0 are the scale factors for the protein. Ref: Tronrud, D. E. (1997). Methods Enzymol. 277, 243-268. ; _item.name '_refine.solvent_model_param_bsol' _item.category_id refine _item.mandatory_code no _item_type.code float save_ save__refine.solvent_model_param_ksol _item_description.description ; The value of the KSOL solvent-model parameter describing the ratio of the electron density in the bulk solvent to the electron density in the molecular solute. This is one of the two parameters (the other is _refine.solvent_model_param_bsol) in Tronrud's method of modelling the contribution of bulk solvent to the scattering. The standard scale factor is modified according to the expression k0 exp(-B0 * s^2^)[1-KSOL * exp(-BSOL * s^2^)] where k0 and B0 are the scale factors for the protein. Ref: Tronrud, D. E. (1997). Methods Enzymol. 277, 243-268. ; _item.name '_refine.solvent_model_param_ksol' _item.category_id refine _item.mandatory_code no _item_type.code float save_ #################### ## REFINE_ANALYZE ## #################### save_refine_analyze _category.description ; Data items in the REFINE_ANALYZE category record details about the refined structure that are often used to analyze the refinement and assess its quality. A given computer program may or may not produce values corresponding to these data names. ; _category.id refine_analyze _category.mandatory_code no _category_key.name '_refine_analyze.entry_id' loop_ _category_group.id 'inclusive_group' 'refine_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _refine_analyze.entry_id _refine_analyze.Luzzati_coordinate_error_obs _refine_analyze.Luzzati_d_res_low_obs 5HVP 0.056 2.51 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__refine_analyze.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_refine_analyze.entry_id' _item.category_id refine_analyze _item.mandatory_code yes save_ save__refine_analyze.Luzzati_coordinate_error_free _item_description.description ; The estimated coordinate error obtained from the plot of the R value versus sin(theta)/lambda for the reflections treated as a test set during refinement. Ref: Luzzati, V. (1952). Traitement statistique des erreurs dans la determination des structures cristallines. Acta Cryst. 5, 802-810. ; _item.name '_refine_analyze.Luzzati_coordinate_error_free' _item.category_id refine_analyze _item.mandatory_code no _item_type.code float _item_units.code angstroms save_ save__refine_analyze.Luzzati_coordinate_error_obs _item_description.description ; The estimated coordinate error obtained from the plot of the R value versus sin(theta)/lambda for reflections classified as observed. Ref: Luzzati, V. (1952). Traitement statistique des erreurs dans la determination des structures cristallines. Acta Cryst. 5, 802-810. ; _item.name '_refine_analyze.Luzzati_coordinate_error_obs' _item.category_id refine_analyze _item.mandatory_code no _item_type.code float _item_units.code angstroms save_ save__refine_analyze.Luzzati_d_res_low_free _item_description.description ; The value of the low-resolution cutoff used in constructing the Luzzati plot for reflections treated as a test set during refinement. Ref: Luzzati, V. (1952). Traitement statistique des erreurs dans la determination des structures cristallines. Acta Cryst. 5, 802-810. ; _item.name '_refine_analyze.Luzzati_d_res_low_free' _item.category_id refine_analyze _item.mandatory_code no _item_type.code float _item_units.code angstroms save_ save__refine_analyze.Luzzati_d_res_low_obs _item_description.description ; The value of the low-resolution cutoff used in constructing the Luzzati plot for reflections classified as observed. Ref: Luzzati, V. (1952). Traitement statistique des erreurs dans la determination des structures cristallines. Acta Cryst. 5, 802-810. ; _item.name '_refine_analyze.Luzzati_d_res_low_obs' _item.category_id refine_analyze _item.mandatory_code no _item_type.code float _item_units.code angstroms save_ save__refine_analyze.Luzzati_sigma_a_free _item_description.description ; The value of sigma~a~ used in constructing the Luzzati plot for the reflections treated as a test set during refinement. Details of the estimation of sigma~a~ can be specified in _refine_analyze.Luzzati_sigma_a_free_details. Ref: Luzzati, V. (1952). Traitement statistique des erreurs dans la determination des structures cristallines. Acta Cryst. 5, 802-810. ; _item.name '_refine_analyze.Luzzati_sigma_a_free' _item.category_id refine_analyze _item.mandatory_code no _item_type.code float _item_units.code angstroms save_ save__refine_analyze.Luzzati_sigma_a_free_details _item_description.description ; Details of the estimation of sigma~a~ for the reflections treated as a test set during refinement. Ref: Luzzati, V. (1952). Traitement statistique des erreurs dans la determination des structures cristallines. Acta Cryst. 5, 802-810. ; _item.name '_refine_analyze.Luzzati_sigma_a_free_details' _item.category_id refine_analyze _item.mandatory_code no _item_type.code text save_ save__refine_analyze.Luzzati_sigma_a_obs _item_description.description ; The value of sigma~a~ used in constructing the Luzzati plot for reflections classified as observed. Details of the estimation of sigma~a~ can be specified in _refine_analyze.Luzzati_sigma_a_obs_details. Ref: Luzzati, V. (1952). Traitement statistique des erreurs dans la determination des structures cristallines. Acta Cryst. 5, 802-810. ; _item.name '_refine_analyze.Luzzati_sigma_a_obs' _item.category_id refine_analyze _item.mandatory_code no _item_type.code float _item_units.code angstroms save_ save__refine_analyze.Luzzati_sigma_a_obs_details _item_description.description ; Special aspects of the estimation of sigma~a~ for the reflections classified as observed. Ref: Luzzati, V. (1952). Traitement statistique des erreurs dans la determination des structures cristallines. Acta Cryst. 5, 802-810. ; _item.name '_refine_analyze.Luzzati_sigma_a_obs_details' _item.category_id refine_analyze _item.mandatory_code no _item_type.code text save_ save__refine_analyze.number_disordered_residues _item_description.description ; The number of discretely disordered residues in the refined model. ; _item.name '_refine_analyze.number_disordered_residues' _item.category_id refine_analyze _item.mandatory_code no _item_type.code float save_ save__refine_analyze.occupancy_sum_hydrogen _item_description.description ; The sum of the occupancies of the hydrogen atoms in the refined model. ; _item.name '_refine_analyze.occupancy_sum_hydrogen' _item.category_id refine_analyze _item.mandatory_code no _item_type.code float save_ save__refine_analyze.occupancy_sum_non_hydrogen _item_description.description ; The sum of the occupancies of the non-hydrogen atoms in the refined model. ; _item.name '_refine_analyze.occupancy_sum_non_hydrogen' _item.category_id refine_analyze _item.mandatory_code no _item_type.code float save_ save__refine_analyze.RG_d_res_high _item_description.description ; The value of the high-resolution cutoff in angstroms used in the calculation of the Hamilton generalized R factor (RG) stored in _refine_analyze.RG_work and _refine_analyze.RG_free. Ref: Hamilton, W. C. (1965). Acta Cryst. 18, 502-510. ; _item.name '_refine_analyze.RG_d_res_high' _item.category_id refine_analyze _item.mandatory_code no _item_aliases.alias_name '_refine_analyze.ebi_RG_d_res_high' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__refine_analyze.RG_d_res_low _item_description.description ; The value of the low-resolution cutoff in angstroms used in the calculation of the Hamilton generalized R factor (RG) stored in _refine_analyze.RG_work and _refine_analyze.RG_free. Ref: Hamilton, W. C. (1965). Acta Cryst. 18, 502-510. ; _item.name '_refine_analyze.RG_d_res_low' _item.category_id refine_analyze _item.mandatory_code no _item_aliases.alias_name '_refine_analyze.ebi_RG_d_res_low' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__refine_analyze.RG_free _item_description.description ; The Hamilton generalized R factor for all reflections that satisfy the resolution limits established by _refine_analyze.RG_d_res_high and _refine_analyze.RG_d_res_low for the free R set of reflections that were excluded from the refinement. sum_i sum_j w_{i,j}(|Fobs|_i - G|Fcalc|_i)(|Fobs|_j - G|Fcalc|_j) RG = Sqrt( ----------------------------------------------------------------- ) sum_i sum_j w_{i,j} |Fobs|_i |Fobs|_j where |Fobs| = the observed structure-factor amplitudes |Fcalc| = the calculated structure-factor amplitudes G = the scale factor which puts |Fcalc| on the same scale as |Fobs| w_{i,j} = the weight for the combination of the reflections i and j. sum_i and sum_j are taken over the specified reflections When the covariance of the amplitudes of reflection i and reflection j is zero (i.e. the reflections are independent) w{i,i} can be redefined as w_i and the nested sums collapsed into one sum. sum_i w_i(|Fobs|_i - G|Fcalc|_i)^2 RG = Sqrt( ----------------------------------- ) sum_i w_i |Fobs|_i^2 Ref: Hamilton, W. C. (1965). Acta Cryst. 18, 502-510. ; _item.name '_refine_analyze.RG_free' _item.category_id refine_analyze _item.mandatory_code no _item_aliases.alias_name '_refine_analyze.ebi_RG_free' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__refine_analyze.RG_work _item_description.description ; The Hamilton generalized R factor for all reflections that satisfy the resolution limits established by _refine_analyze.RG_d_res_high and _refine_analyze.RG_d_res_low and for those reflections included in the working set when a free R set of reflections is omitted from the refinement. sum_i sum_j w_{i,j}(|Fobs|_i - G|Fcalc|_i)(|Fobs|_j - G|Fcalc|_j) RG = Sqrt( ----------------------------------------------------------------- ) sum_i sum_j w_{i,j} |Fobs|_i |Fobs|_j where |Fobs| = the observed structure-factor amplitudes |Fcalc| = the calculated structure-factor amplitudes G = the scale factor which puts |Fcalc| on the same scale as |Fobs| w_{i,j} = the weight for the combination of the reflections i and j. sum_i and sum_j are taken over the specified reflections When the covariance of the amplitudes of reflection i and reflection j is zero (i.e. the reflections are independent) w{i,i} can be redefined as w_i and the nested sums collapsed into one sum. sum_i w_i(|Fobs|_i - G|Fcalc|_i)^2 RG = Sqrt( ----------------------------------- ) sum_i w_i |Fobs|_i^2 Ref: Hamilton, W. C. (1965). Acta Cryst. 18, 502-510. ; _item.name '_refine_analyze.RG_work' _item.category_id refine_analyze _item.mandatory_code no _item_aliases.alias_name '_refine_analyze.ebi_RG_work' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__refine_analyze.RG_free_work_ratio _item_description.description ; The observed ratio of RGfree to RGwork. The expected RG ratio is the value that should be achievable at the end of a structure refinement when only random uncorrelated errors exist in the data and the model provided that the observations are properly weighted. When compared with the observed RG ratio it may indicate that a structure has not reached convergence or a model has been over-refined with no corresponding improvement in the model. In an unrestrained refinement, the ratio of RGfree to RGwork with only random uncorrelated errors at convergence depends only on the number of reflections and the number of parameters according to sqrt[(f + m) / (f - m) ] where f = the number of included structure amplitudes and target distances, and m = the number of parameters being refined. In the restrained case, RGfree is calculated from a random selection of residuals including both structure amplitudes and restraints. When restraints are included in the refinement, the RG ratio requires a term for the contribution to the minimized residual at convergence, D~restr~, due to those restraints: D~restr~ = r - sum [w_i . (a_i)^t . (H)^-1 a_i] where r is the number of geometrical, displacement-parameter and other restraints H is the (m,m) normal matrix given by A^t.W.A W is the (n,n) symmetric weight matrix of the included observations A is the least-squares design matrix of derivatives of order (n,m) a_i is the ith row of A Then the expected RGratio becomes sqrt [ (f + (m - r + D~restr~))/ (f - (m - r + D~restr~)) ] There is no data name for the expected value of RGfree/RGwork yet. Ref: Tickle, I. J., Laskowski, R. A. & Moss, D. S. (1998). Acta Cryst. D54, 547-557. ; _item.name '_refine_analyze.RG_free_work_ratio' _item.category_id refine_analyze _item.mandatory_code no _item_aliases.alias_name '_refine_analyze.ebi_RG_work_free_ratio' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ ################## ## REFINE_B_ISO ## ################## save_refine_B_iso _category.description ; Data items in the REFINE_B_ISO category record details about the treatment of isotropic B factors (displacement parameters) during refinement. ; _category.id refine_B_iso _category.mandatory_code no _category_key.name '_refine_B_iso.class' loop_ _category_group.id 'inclusive_group' 'refine_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _refine_B_iso.class _refine_B_iso.treatment 'protein' isotropic 'solvent' isotropic 'inhibitor' isotropic ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__refine_B_iso.class _item_description.description ; A class of atoms treated similarly for isotropic B-factor (displacement-parameter) refinement. ; _item.name '_refine_B_iso.class' _item.category_id refine_B_iso _item.mandatory_code yes _item_type.code text loop_ _item_examples.case 'all' 'protein' 'solvent' 'sugar-phosphate backbone' save_ save__refine_B_iso.details _item_description.description ; A description of special aspects of the isotropic B-factor (displacement-parameter) refinement for the class of atoms described in _refine_B_iso.class. ; _item.name '_refine_B_iso.details' _item.category_id refine_B_iso _item.mandatory_code no _item_type.code text _item_examples.case ; The temperature factors of atoms in the side chain of Arg 92 were held fixed due to unstable behavior in refinement. ; save_ save__refine_B_iso.treatment _item_description.description ; The treatment of isotropic B-factor (displacement-parameter) refinement for a class of atoms defined in _refine_B_iso.class. ; _item.name '_refine_B_iso.treatment' _item.category_id refine_B_iso _item.mandatory_code no _item_type.code ucode loop_ _item_enumeration.value fixed isotropic anisotropic save_ save__refine_B_iso.value _item_description.description ; The value of the isotropic B factor (displacement parameter) assigned to a class of atoms defined in _refine_B_iso.class. Meaningful only for atoms with fixed isotropic B factors. ; _item.name '_refine_B_iso.value' _item.category_id refine_B_iso _item.mandatory_code no _item_type.code float _item_units.code angstroms_squared save_ ############################### ## REFINE_FUNCTION_MINIMIZED ## ############################### save_refine_funct_minimized _category.description ; Data items in the REFINE_FUNCT_MINIMIZED category record details about the individual terms of the function minimized during refinement. ; _category.id refine_funct_minimized _category.mandatory_code no _category_key.name '_refine_funct_minimized.type' loop_ _category_group.id 'inclusive_group' 'refine_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on RESTRAIN refinement for the CCP4 test data set toxd. ; ; loop_ _refine_funct_minimized.type _refine_funct_minimized.number_terms _refine_funct_minimized.residual 'sum(W*Delta(Amplitude)^2' 3009 1621.3 'sum(W*Delta(Plane+Rigid)^2' 85 56.68 'sum(W*Delta(Distance)^2' 1219 163.59 'sum(W*Delta(U-tempfactors)^2' 1192 69.338 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__refine_funct_minimized.number_terms _item_description.description ; The number of observations in this term. For example, if the term is a residual of the X-ray intensities, this item would contain the number of reflections used in the refinement. ; _item.name '_refine_funct_minimized.number_terms' _item.category_id refine_funct_minimized _item.mandatory_code no _item_aliases.alias_name '_ebi_refine_funct_minimized.NumTerms' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__refine_funct_minimized.residual _item_description.description ; The residual for this term of the function that was minimized during the refinement. ; _item.name '_refine_funct_minimized.residual' _item.category_id refine_funct_minimized _item.mandatory_code no _item_aliases.alias_name '_ebi_refine_funct_minimized.Residual' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__refine_funct_minimized.type _item_description.description ; The type of the function being minimized. ; _item.name '_refine_funct_minimized.type' _item.category_id refine_funct_minimized _item.mandatory_code yes _item_aliases.alias_name '_ebi_refine_funct_minimized.type' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 _item_type.code line save_ save__refine_funct_minimized.weight _item_description.description ; The weight applied to this term of the function that was minimized during the refinement. ; _item.name '_refine_funct_minimized.weight' _item.category_id refine_funct_minimized _item.mandatory_code no _item_aliases.alias_name '_ebi_refine_funct_minimized.weight' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 _item_type.code float save_ ################# ## REFINE_HIST ## ################# save_refine_hist _category.description ; Data items in the REFINE_HIST category record details about the steps during the refinement of the structure. These data items are not meant to be as thorough a description of the refinement as is provided for the final model in other categories; rather, these data items provide a mechanism for sketching out the progress of the refinement, supported by a small set of representative statistics. ; _category.id refine_hist _category.mandatory_code no _category_key.name '_refine_hist.cycle_id' loop_ _category_group.id 'inclusive_group' 'refine_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on laboratory records for the collagen-like peptide [(POG)4 EKG (POG)5]3. ; ; _refine_hist.cycle_id C134 _refine_hist.d_res_high 1.85 _refine_hist.d_res_low 20.0 _refine_hist.number_atoms_solvent 217 _refine_hist.number_atoms_total 808 _refine_hist.number_reflns_all 6174 _refine_hist.number_reflns_obs 4886 _refine_hist.number_reflns_R_free 476 _refine_hist.number_reflns_R_work 4410 _refine_hist.R_factor_all .265 _refine_hist.R_factor_obs .195 _refine_hist.R_factor_R_free .274 _refine_hist.R_factor_R_work .160 _refine_hist.details ; Add majority of solvent molecules. B factors refined by group. Continued to remove misplaced water molecules. ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__refine_hist.cycle_id _item_description.description ; The value of _refine_hist.cycle_id must uniquely identify a record in the REFINE_HIST list. Note that this item need not be a number; it can be any unique identifier. ; _item.name '_refine_hist.cycle_id' _item.category_id refine_hist _item.mandatory_code yes _item_type.code code save_ save__refine_hist.details _item_description.description ; A description of special aspects of this cycle of the refinement process. ; _item.name '_refine_hist.details' _item.category_id refine_hist _item.mandatory_code no _item_type.code text _item_examples.case ; Residues 13-17 fit and added to model; substantial rebuilding of loop containing residues 43-48; addition of first atoms to solvent model; ten cycles of Prolsq refinement. ; save_ save__refine_hist.d_res_high _item_description.description ; The lowest value for the interplanar spacings for the reflection data for this cycle of refinement. This is called the highest resolution. ; _item.name '_refine_hist.d_res_high' _item.category_id refine_hist _item.mandatory_code yes loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__refine_hist.d_res_low _item_description.description ; The highest value for the interplanar spacings for the reflection data for this cycle of refinement. This is called the lowest resolution. ; _item.name '_refine_hist.d_res_low' _item.category_id refine_hist _item.mandatory_code yes loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__refine_hist.number_atoms_solvent _item_description.description ; The number of solvent atoms that were included in the model at this cycle of the refinement. ; _item.name '_refine_hist.number_atoms_solvent' _item.category_id refine_hist _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__refine_hist.number_atoms_total _item_description.description ; The total number of atoms that were included in the model at this cycle of the refinement. ; _item.name '_refine_hist.number_atoms_total' _item.category_id refine_hist _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__refine_hist.number_reflns_all _item_description.description ; The number of reflections that satisfy the resolution limits established by _refine_hist.d_res_high and _refine_hist.d_res_low. ; _item.name '_refine_hist.number_reflns_all' _item.category_id refine_hist _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__refine_hist.number_reflns_obs _item_description.description ; The number of reflections that satisfy the resolution limits established by _refine_hist.d_res_high and _refine_hist.d_res_low and the observation criterion established by _reflns.observed_criterion. ; _item.name '_refine_hist.number_reflns_obs' _item.category_id refine_hist _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__refine_hist.number_reflns_R_free _item_description.description ; The number of reflections that satisfy the resolution limits established by _refine_hist.d_res_high and _refine_hist.d_res_low and the observation limit established by _reflns.observed_criterion, and that were used as the test reflections (i.e. were excluded from the refinement) when the refinement included the calculation of a 'free' R factor. Details of how reflections were assigned to the working and test sets are given in _reflns.R_free_details. ; _item.name '_refine_hist.number_reflns_R_free' _item.category_id refine_hist _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__refine_hist.number_reflns_R_work _item_description.description ; The number of reflections that satisfy the resolution limits established by _refine_hist.d_res_high and _refine_hist.d_res_low and the observation limit established by _reflns.observed_criterion, and that were used as the working reflections (i.e. were included in the refinement) when the refinement included the calculation of a 'free' R factor. Details of how reflections were assigned to the working and test sets are given in _reflns.R_free_details. ; _item.name '_refine_hist.number_reflns_R_work' _item.category_id refine_hist _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__refine_hist.R_factor_all _item_description.description ; Residual factor R for reflections that satisfy the resolution limits established by _refine_hist.d_res_high and _refine_hist.d_res_low. sum|F~obs~ - F~calc~| R = --------------------- sum|F~obs~| F~obs~ = the observed structure-factor amplitudes F~calc~ = the calculated structure-factor amplitudes sum is taken over the specified reflections ; _item.name '_refine_hist.R_factor_all' _item.category_id refine_hist _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__refine_hist.R_factor_obs _item_description.description ; Residual factor R for reflections that satisfy the resolution limits established by _refine_hist.d_res_high and _refine_hist.d_res_low and the observation criterion established by _reflns.observed_criterion. sum|F~obs~ - F~calc~| R = --------------------- sum|F~obs~| F~obs~ = the observed structure-factor amplitudes F~calc~ = the calculated structure-factor amplitudes sum is taken over the specified reflections ; _item.name '_refine_hist.R_factor_obs' _item.category_id refine_hist _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__refine_hist.R_factor_R_free _item_description.description ; Residual factor R for reflections that satisfy the resolution limits established by _refine_hist.d_res_high and _refine_hist.d_res_low and the observation limit established by _reflns.observed_criterion, and that were used as the test reflections (i.e. were excluded from the refinement) when the refinement included the calculation of a 'free' R factor. Details of how reflections were assigned to the working and test sets are given in _reflns.R_free_details. sum|F~obs~ - F~calc~| R = --------------------- sum|F~obs~| F~obs~ = the observed structure-factor amplitudes F~calc~ = the calculated structure-factor amplitudes sum is taken over the specified reflections ; _item.name '_refine_hist.R_factor_R_free' _item.category_id refine_hist _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__refine_hist.R_factor_R_work _item_description.description ; Residual factor R for reflections that satisfy the resolution limits established by _refine_hist.d_res_high and _refine_hist.d_res_low and the observation limit established by _reflns.observed_criterion, and that were used as the working reflections (i.e. were included in the refinement) when the refinement included the calculation of a 'free' R factor. Details of how reflections were assigned to the working and test sets are given in _reflns.R_free_details. sum|F~obs~ - F~calc~| R = --------------------- sum|F~obs~| F~obs~ = the observed structure-factor amplitudes F~calc~ = the calculated structure-factor amplitudes sum is taken over the specified reflections ; _item.name '_refine_hist.R_factor_R_work' _item.category_id refine_hist _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ ##################### ## REFINE_LS_RESTR ## ##################### save_refine_ls_restr _category.description ; Data items in the REFINE_LS_RESTR category record details about the restraints applied to various classes of parameters during the least-squares refinement. ; _category.id refine_ls_restr _category.mandatory_code no _category_key.name '_refine_ls_restr.type' loop_ _category_group.id 'inclusive_group' 'refine_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _refine_ls_restr.type _refine_ls_restr.dev_ideal_target _refine_ls_restr.dev_ideal _refine_ls_restr.number _refine_ls_restr.criterion _refine_ls_restr.rejects 'bond_d' 0.020 0.018 1654 '> 2\s' 22 'angle_d' 0.030 0.038 2246 '> 2\s' 139 'planar_d' 0.040 0.043 498 '> 2\s' 21 'planar' 0.020 0.015 270 '> 2\s' 1 'chiral' 0.150 0.177 278 '> 2\s' 2 'singtor_nbd' 0.500 0.216 582 '> 2\s' 0 'multtor_nbd' 0.500 0.207 419 '> 2\s' 0 'xyhbond_nbd' 0.500 0.245 149 '> 2\s' 0 'planar_tor' 3.0 2.6 203 '> 2\s' 9 'staggered_tor' 15.0 17.4 298 '> 2\s' 31 'orthonormal_tor' 20.0 18.1 12 '> 2\s' 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__refine_ls_restr.criterion _item_description.description ; A criterion used to define a parameter value that deviates significantly from its ideal value in the model obtained by restrained least-squares refinement. ; _item.name '_refine_ls_restr.criterion' _item.category_id refine_ls_restr _item.mandatory_code no _item_type.code text _item_examples.case '> 3\s' save_ save__refine_ls_restr.dev_ideal _item_description.description ; For the given parameter type, the root-mean-square deviation between the ideal values used as restraints in the least-squares refinement and the values obtained by refinement. For instance, bond distances may deviate by 0.018 \%A (r.m.s.) from ideal values in the current model. ; _item.name '_refine_ls_restr.dev_ideal' _item.category_id refine_ls_restr _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__refine_ls_restr.dev_ideal_target _item_description.description ; For the given parameter type, the target root-mean-square deviation between the ideal values used as restraints in the least-squares refinement and the values obtained by refinement. ; _item.name '_refine_ls_restr.dev_ideal_target' _item.category_id refine_ls_restr _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__refine_ls_restr.number _item_description.description ; The number of parameters of this type subjected to restraint in least-squares refinement. ; _item.name '_refine_ls_restr.number' _item.category_id refine_ls_restr _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__refine_ls_restr.rejects _item_description.description ; The number of parameters of this type that deviate from ideal values by more than the amount defined in _refine_ls_restr.criterion in the model obtained by restrained least-squares refinement. ; _item.name '_refine_ls_restr.rejects' _item.category_id refine_ls_restr _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__refine_ls_restr.type _item_description.description ; The type of the parameter being restrained. Explicit sets of data values are provided for the programs PROTIN/PROLSQ (beginning with p_) and RESTRAIN (beginning with RESTRAIN_). As computer programs change, these data values are given as examples, not as an enumeration list. Computer programs that convert a data block to a refinement table will expect the exact form of the data values given here to be used. ; loop_ _item.name _item.category_id _item.mandatory_code '_refine_ls_restr.type' refine_ls_restr yes '_refine_ls_restr_type.type' refine_ls_restr_type yes loop_ _item_linked.child_name _item_linked.parent_name '_refine_ls_restr_type.type' '_refine_ls_restr.type' _item_type.code line loop_ _item_examples.case _item_examples.detail 'p_bond_d' 'bond distance' 'p_angle_d' 'bond angle expressed as a distance' 'p_planar_d' 'planar 1,4 distance' 'p_xhbond_d' 'X-H bond distance' 'p_xhangle_d' 'X-H bond angle expressed as a distance' 'p_hydrog_d' 'hydrogen distance' 'p_special_d' 'special distance' 'p_planar' 'planes' 'p_chiral' 'chiral centres' 'p_singtor_nbd' 'single-torsion non-bonded contact' 'p_multtor_nbd' 'multiple-torsion non-bonded contact' 'p_xyhbond_nbd' 'possible (X...Y) hydrogen bond' 'p_xhyhbond_nbd' 'possible (X-H...Y) hydrogen bond' 'p_special_tor' 'special torsion angle' 'p_planar_tor' 'planar torsion angle' 'p_staggered_tor' 'staggered torsion angle' 'p_orthonormal_tor' 'orthonormal torsion angle' 'p_mcbond_it' 'main-chain bond isotropic displacement parameter' 'p_mcangle_it' 'main-chain angle isotropic displacement parameter' 'p_scbond_it' 'side-chain bond isotropic displacement parameter' 'p_scangle_it' 'side-chain angle isotropic displacement parameter' 'p_xhbond_it' 'X-H bond isotropic displacement parameter' 'p_xhangle_it' 'X-H angle isotropic displacement parameter' 'p_special_it' 'special isotropic displacement parameter' 'RESTRAIN_Distances < 2.12' ; The root-mean-square deviation of the difference between the values calculated from the structures used to compile the restraints dictionary parameters and the dictionary values themselves in the distance range less than 2.12 Angstroms. ; 'RESTRAIN_Distances 2.12 < D < 2.625' ; The root-mean-square deviation of the difference between the values calculated from the structures used to compile the restraints dictionary parameters and the dictionary values themselves in the distance range 2.12 - 2.625 Angstroms. ; 'RESTRAIN_Distances > 2.625' ; The root-mean-square deviation of the difference between the values calculated from the structures used to compile the restraints dictionary parameters and the dictionary values themselves in the distance range greater than 2.625 Angstroms. ; 'RESTRAIN_Peptide Planes' ; The root-mean-square deviation of the difference between the values calculated from the structures used to compile the restraints dictionary parameters and the dictionary values themselves for peptide planes. ; 'RESTRAIN_Ring and other planes' ; The root-mean-square deviation of the difference between the values calculated from the structures used to compile the restraints dictionary parameters and the dictionary values themselves for rings and planes other than peptide planes. ; 'RESTRAIN_rms diffs for Uiso atoms at dist 1.2-1.4' . 'RESTRAIN_rms diffs for Uiso atoms at dist 1.4-1.6' . 'RESTRAIN_rms diffs for Uiso atoms at dist 1.8-2.0' . 'RESTRAIN_rms diffs for Uiso atoms at dist 2.0-2.2' . 'RESTRAIN_rms diffs for Uiso atoms at dist 2.2-2.4' . 'RESTRAIN_rms diffs for Uiso atoms at dist >2.4' . save_ save__refine_ls_restr.weight _item_description.description ; The weighting value applied to this type of restraint in the least-squares refinement. ; _item.name '_refine_ls_restr.weight' _item.category_id refine_ls_restr _item.mandatory_code no _item_type.code float save_ ######################### ## REFINE_LS_RESTR_NCS ## ######################### save_refine_ls_restr_ncs _category.description ; Data items in the REFINE_LS_RESTR_NCS category record details about the restraints applied to atom positions in domains related by noncrystallographic symmetry during least-squares refinement, and also about the deviation of the restrained atomic parameters at the end of the refinement. It is expected that these values will only be reported once for each set of restrained domains. ; _category.id refine_ls_restr_ncs _category.mandatory_code no _category_key.name '_refine_ls_restr_ncs.dom_id' loop_ _category_group.id 'inclusive_group' 'refine_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on laboratory records for the collagen-like peptide, HYP-. ; ; _refine_ls_restr_ncs.dom_id d2 _refine_ls_restr_ncs.weight_position 300.0 _refine_ls_restr_ncs.weight_B_iso 2.0 _refine_ls_restr_ncs.rms_dev_position 0.09 _refine_ls_restr_ncs.rms_dev_B_iso 0.16 _refine_ls_restr_ncs.ncs_model_details ; NCS restraint for pseudo-twofold symmetry between domains d1 and d2. Position weight coefficient given in Kcal/(mol \%A^2^) and isotropic B weight coefficient given in \%A^2^. ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__refine_ls_restr_ncs.dom_id _item_description.description ; This data item is a pointer to _struct_ncs_dom.id in the STRUCT_NCS_DOM category. ; _item.name '_refine_ls_restr_ncs.dom_id' _item.category_id refine_ls_restr_ncs _item.mandatory_code yes _item_type.code code save_ save__refine_ls_restr_ncs.ncs_model_details _item_description.description ; Special aspects of the manner in which noncrystallographic restraints were applied to atomic parameters in the domain specified by _refine_ls_restr_ncs.dom_id and equivalent atomic parameters in the domains against which it was restrained. ; _item.name '_refine_ls_restr_ncs.ncs_model_details' _item.category_id refine_ls_restr_ncs _item.mandatory_code no _item_type.code text save_ save__refine_ls_restr_ncs.rms_dev_B_iso _item_description.description ; The root-mean-square deviation in equivalent isotropic displacement parameters in the domain specified by _refine_ls_restr_ncs.dom_id and in the domains against which it was restrained. ; _item.name '_refine_ls_restr_ncs.rms_dev_B_iso' _item.category_id refine_ls_restr_ncs _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms_squared save_ save__refine_ls_restr_ncs.rms_dev_position _item_description.description ; The root-mean-square deviation in equivalent atom positions in the domain specified by _refine_ls_restr_ncs.dom_id and in the domains against which it was restrained. ; _item.name '_refine_ls_restr_ncs.rms_dev_position' _item.category_id refine_ls_restr_ncs _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__refine_ls_restr_ncs.weight_B_iso _item_description.description ; The value of the weighting coefficient used in noncrystallographic symmetry restraint of isotropic displacement parameters in the domain specified by _refine_ls_restr_ncs.dom_id to equivalent isotropic displacement parameters in the domains against which it was restrained. ; _item.name '_refine_ls_restr_ncs.weight_B_iso' _item.category_id refine_ls_restr_ncs _item.mandatory_code no _item_type.code float save_ save__refine_ls_restr_ncs.weight_position _item_description.description ; The value of the weighting coefficient used in noncrystallographic symmetry restraint of atom positions in the domain specified by _refine_ls_restr_ncs.dom_id to equivalent atom positions in the domains against which it was restrained. ; _item.name '_refine_ls_restr_ncs.weight_position' _item.category_id refine_ls_restr_ncs _item.mandatory_code no _item_type.code float save_ ########################## ## REFINE_LS_RESTR_TYPE ## ########################## save_refine_ls_restr_type _category.description ; Data items in the REFINE_LS_RESTR_TYPE category record details about the restraint types used in the least-squares refinement. ; _category.id refine_ls_restr_type _category.mandatory_code no _category_key.name '_refine_ls_restr_type.type' loop_ _category_group.id 'inclusive_group' 'refine_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on RESTRAIN refinement for the CCP4 test data set toxd. ; ; loop_ _refine_ls_restr.type _refine_ls_restr.number _refine_ls_restr.dev_ideal _refine_ls_restr.dev_ideal_target 'RESTRAIN_Distances < 2.12' 509 0.005 0.022 'RESTRAIN_Distances 2.12 < D < 2.625' 671 0.016 0.037 'RESTRAIN_Distances > 2.625' 39 0.034 0.043 'RESTRAIN_Peptide Planes' 59 0.002 0.010 'RESTRAIN_Ring and other planes' 26 0.014 0.010 'RESTRAIN_rms diffs for Uiso atoms at dist 1.2-1.4' 212 0.106 . 'RESTRAIN_rms diffs for Uiso atoms at dist 1.4-1.6' 288 0.101 . 'RESTRAIN_rms diffs for Uiso atoms at dist 1.8-2.0' 6 0.077 . 'RESTRAIN_rms diffs for Uiso atoms at dist 2.0-2.2' 10 0.114 . 'RESTRAIN_rms diffs for Uiso atoms at dist 2.2-2.4' 215 0.119 . 'RESTRAIN_rms diffs for Uiso atoms at dist >2.4' 461 0.106 . loop_ _refine_ls_restr_type.type _refine_ls_restr_type.distance_cutoff_low _refine_ls_restr_type.distance_cutoff_high 'RESTRAIN_Distances < 2.12' . 2.12 'RESTRAIN_Distances 2.12 < D < 2.625' 2.12 2.625 'RESTRAIN_Distances > 2.625' 2.625 . 'RESTRAIN_Peptide Planes' . . 'RESTRAIN_Ring and other planes' . . 'RESTRAIN_rms diffs for Uiso atoms at dist 1.2-1.4' 1.2 1.4 'RESTRAIN_rms diffs for Uiso atoms at dist 1.4-1.6' 1.4 1.6 'RESTRAIN_rms diffs for Uiso atoms at dist 1.8-2.0' 1.8 2.0 'RESTRAIN_rms diffs for Uiso atoms at dist 2.0-2.2' 2.0 2.2 'RESTRAIN_rms diffs for Uiso atoms at dist 2.2-2.4' 2.2 2.4 'RESTRAIN_rms diffs for Uiso atoms at dist >2.4' 2.4 . ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__refine_ls_restr_type.distance_cutoff_high _item_description.description ; The upper limit in angstroms of the distance range applied to the current restraint type. ; _item.name '_refine_ls_restr_type.distance_cutoff_high' _item.category_id refine_ls_restr_type _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__refine_ls_restr_type.distance_cutoff_low _item_description.description ; The lower limit in angstroms of the distance range applied to the current restraint type. ; _item.name '_refine_ls_restr_type.distance_cutoff_low' _item.category_id refine_ls_restr_type _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__refine_ls_restr_type.type _item_description.description ; This data item is a pointer to _refine_ls_restr.type in the REFINE_LS_RESTR category. ; _item.name '_refine_ls_restr_type.type' _item.category_id refine_ls_restr_type _item.mandatory_code yes _item_type.code line save_ ##################### ## REFINE_LS_SHELL ## ##################### save_refine_ls_shell _category.description ; Data items in the REFINE_LS_SHELL category record details about the results of the least-squares refinement broken down into shells of resolution. ; _category.id refine_ls_shell _category.mandatory_code no loop_ _category_key.name '_refine_ls_shell.d_res_low' '_refine_ls_shell.d_res_high' loop_ _category_group.id 'inclusive_group' 'refine_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _refine_ls_shell.d_res_low _refine_ls_shell.d_res_high _refine_ls_shell.number_reflns_obs _refine_ls_shell.R_factor_obs 8.00 4.51 1226 0.196 4.51 3.48 1679 0.146 3.48 2.94 2014 0.160 2.94 2.59 2147 0.182 2.59 2.34 2127 0.193 2.34 2.15 2061 0.203 2.15 2.00 1647 0.188 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__refine_ls_shell.d_res_high _item_description.description ; The lowest value for the interplanar spacings for the reflection data in this shell. This is called the highest resolution. ; _item.name '_refine_ls_shell.d_res_high' _item.category_id refine_ls_shell _item.mandatory_code yes loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__refine_ls_shell.d_res_low _item_description.description ; The highest value for the interplanar spacings for the reflection data in this shell. This is called the lowest resolution. ; _item.name '_refine_ls_shell.d_res_low' _item.category_id refine_ls_shell _item.mandatory_code yes loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__refine_ls_shell.number_reflns_all _item_description.description ; The number of reflections that satisfy the resolution limits established by _refine_ls_shell.d_res_high and _refine_ls_shell.d_res_low. ; _item.name '_refine_ls_shell.number_reflns_all' _item.category_id refine_ls_shell _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__refine_ls_shell.number_reflns_obs _item_description.description ; The number of reflections that satisfy the resolution limits established by _refine_ls_shell.d_res_high and _refine_ls_shell.d_res_low and the observation criterion established by _reflns.observed_criterion. ; _item.name '_refine_ls_shell.number_reflns_obs' _item.category_id refine_ls_shell _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__refine_ls_shell.number_reflns_R_free _item_description.description ; The number of reflections that satisfy the resolution limits established by _refine_ls_shell.d_res_high and _refine_ls_shell.d_res_low and the observation limit established by _reflns.observed_criterion, and that were used as the test reflections (i.e. were excluded from the refinement) when the refinement included the calculation of a 'free' R factor. Details of how reflections were assigned to the working and test sets are given in _reflns.R_free_details. ; _item.name '_refine_ls_shell.number_reflns_R_free' _item.category_id refine_ls_shell _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__refine_ls_shell.number_reflns_R_work _item_description.description ; The number of reflections that satisfy the resolution limits established by _refine_ls_shell.d_res_high and _refine_ls_shell.d_res_low and the observation limit established by _reflns.observed_criterion, and that were used as the working reflections (i.e. were included in the refinement) when the refinement included the calculation of a 'free' R factor. Details of how reflections were assigned to the working and test sets are given in _reflns.R_free_details. ; _item.name '_refine_ls_shell.number_reflns_R_work' _item.category_id refine_ls_shell _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__refine_ls_shell.percent_reflns_obs _item_description.description ; The number of reflections that satisfy the resolution limits established by _refine_ls_shell.d_res_high and _refine_ls_shell.d_res_low and the observation criterion established by _reflns.observed_criterion, expressed as a percentage of the number of geometrically observable reflections that satisfy the resolution limits. ; _item.name '_refine_ls_shell.percent_reflns_obs' _item.category_id refine_ls_shell _item.mandatory_code no _item_type.code float save_ save__refine_ls_shell.percent_reflns_R_free _item_description.description ; The number of reflections that satisfy the resolution limits established by _refine_ls_shell.d_res_high and _refine_ls_shell.d_res_low and the observation limit established by _reflns.observed_criterion, and that were used as the test reflections (i.e. were excluded from the refinement) when the refinement included the calculation of a 'free' R factor, expressed as a percentage of the number of geometrically observable reflections that satisfy the reflection limits. ; _item.name '_refine_ls_shell.percent_reflns_R_free' _item.category_id refine_ls_shell _item.mandatory_code no _item_type.code float save_ save__refine_ls_shell.R_factor_all _item_description.description ; Residual factor R for reflections that satisfy the resolution limits established by _refine_ls_shell.d_res_high and _refine_ls_shell.d_res_low. sum|F~obs~ - F~calc~| R = --------------------- sum|F~obs~| F~obs~ = the observed structure-factor amplitudes F~calc~ = the calculated structure-factor amplitudes sum is taken over the specified reflections ; _item.name '_refine_ls_shell.R_factor_all' _item.category_id refine_ls_shell _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_refine_ls_shell.wR_factor_all' _item_related.function_code alternate _item_type.code float save_ save__refine_ls_shell.R_factor_obs _item_description.description ; Residual factor R for reflections that satisfy the resolution limits established by _refine_ls_shell.d_res_high and _refine_ls_shell.d_res_low and the observation criterion established by _reflns.observed_criterion. sum|F~obs~ - F~calc~| R = --------------------- sum|F~obs~| F~obs~ = the observed structure-factor amplitudes F~calc~ = the calculated structure-factor amplitudes sum is taken over the specified reflections ; _item.name '_refine_ls_shell.R_factor_obs' _item.category_id refine_ls_shell _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_refine_ls_shell.wR_factor_obs' _item_related.function_code alternate _item_type.code float save_ save__refine_ls_shell.R_factor_R_free _item_description.description ; Residual factor R for reflections that satisfy the resolution limits established by _refine_ls_shell.d_res_high and _refine_ls_shell.d_res_low and the observation limit established by _reflns.observed_criterion, and that were used as the test reflections (i.e. were excluded from the refinement) when the refinement included the calculation of a 'free' R factor. Details of how reflections were assigned to the working and test sets are given in _reflns.R_free_details. sum|F~obs~ - F~calc~| R = --------------------- sum|F~obs~| F~obs~ = the observed structure-factor amplitudes F~calc~ = the calculated structure-factor amplitudes sum is taken over the specified reflections ; _item.name '_refine_ls_shell.R_factor_R_free' _item.category_id refine_ls_shell _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 loop_ _item_related.related_name _item_related.function_code '_refine_ls_shell.wR_factor_R_free' alternate '_refine_ls_shell.R_factor_R_free_error' associated_error _item_type.code float save_ save__refine_ls_shell.R_factor_R_free_error _item_description.description ; The estimated error in _refine_ls_shell.R_factor_R_free. The method used to estimate the error is described in the item _refine.ls_R_factor_R_free_error_details. ; _item.name '_refine_ls_shell.R_factor_R_free_error' _item.category_id refine_ls_shell _item.mandatory_code no _item_related.related_name '_refine_ls_shell.R_factor_R_free' _item_related.function_code associated_value _item_type.code float save_ save__refine_ls_shell.R_factor_R_work _item_description.description ; Residual factor R for reflections that satisfy the resolution limits established by _refine_ls_shell.d_res_high and _refine_ls_shell.d_res_low and the observation limit established by _reflns.observed_criterion, and that were used as the working reflections (i.e. were included in the refinement) when the refinement included the calculation of a 'free' R factor. Details of how reflections were assigned to the working and test sets are given in _reflns.R_free_details. sum|F~obs~ - F~calc~| R = --------------------- sum|F~obs~| F~obs~ = the observed structure-factor amplitudes F~calc~ = the calculated structure-factor amplitudes sum is taken over the specified reflections ; _item.name '_refine_ls_shell.R_factor_R_work' _item.category_id refine_ls_shell _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_refine_ls_shell.wR_factor_R_work' _item_related.function_code alternate _item_type.code float save_ save__refine_ls_shell.redundancy_reflns_all _item_description.description ; The ratio of the total number of observations of the reflections that satisfy the resolution limits established by _refine_ls_shell.d_res_high and _refine_ls_shell.d_res_low to the number of crystallographically unique reflections that satisfy the same limits. ; _item.name '_refine_ls_shell.redundancy_reflns_all' _item.category_id refine_ls_shell _item.mandatory_code no _item_type.code float save_ save__refine_ls_shell.redundancy_reflns_obs _item_description.description ; The ratio of the total number of observations of the reflections that satisfy the resolution limits established by _refine_ls_shell.d_res_high and _refine_ls_shell.d_res_low and the observation criterion established by _reflns.observed_criterion to the number of crystallographically unique reflections that satisfy the same limits. ; _item.name '_refine_ls_shell.redundancy_reflns_obs' _item.category_id refine_ls_shell _item.mandatory_code no _item_type.code float save_ save__refine_ls_shell.wR_factor_all _item_description.description ; Weighted residual factor wR for reflections that satisfy the resolution limits established by _refine_ls_shell.d_res_high and _refine_ls_shell.d_res_low. ( sum|w |Y~obs~ - Y~calc~|^2^| )^1/2^ wR = ( ---------------------------- ) ( sum|w Y~obs~^2^| ) Y~obs~ = the observed amplitude specified by _refine.ls_structure_factor_coef Y~calc~ = the calculated amplitude specified by _refine.ls_structure_factor_coef w = the least-squares weight sum is taken over the specified reflections ; _item.name '_refine_ls_shell.wR_factor_all' _item.category_id refine_ls_shell _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_refine_ls_shell.R_factor_all' _item_related.function_code alternate _item_type.code float save_ save__refine_ls_shell.wR_factor_obs _item_description.description ; Weighted residual factor wR for reflections that satisfy the resolution limits established by _refine_ls_shell.d_res_high and _refine_ls_shell.d_res_low and the observation criterion established by _reflns.observed_criterion. ( sum|w |Y~obs~ - Y~calc~|^2^| )^1/2^ wR = ( ---------------------------- ) ( sum|w Y~obs~^2^| ) Y~obs~ = the observed amplitude specified by _refine.ls_structure_factor_coef Y~calc~ = the calculated amplitude specified by _refine.ls_structure_factor_coef w = the least-squares weight sum is taken over the specified reflections ; _item.name '_refine_ls_shell.wR_factor_obs' _item.category_id refine_ls_shell _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_refine_ls_shell.R_factor_obs' _item_related.function_code alternate _item_type.code float save_ save__refine_ls_shell.wR_factor_R_free _item_description.description ; Weighted residual factor wR for reflections that satisfy the resolution limits established by _refine_ls_shell.d_res_high and _refine_ls_shell.d_res_low and the observation limit established by _reflns.observed_criterion, and that were used as the test reflections (i.e. were excluded from the refinement) when the refinement included the calculation of a 'free' R factor. Details of how reflections were assigned to the working and test sets are given in _reflns.R_free_details. ( sum|w |Y~obs~ - Y~calc~|^2^| )^1/2^ wR = ( ---------------------------- ) ( sum|w Y~obs~^2^| ) Y~obs~ = the observed amplitude specified by _refine.ls_structure_factor_coef Y~calc~ = the calculated amplitude specified by _refine.ls_structure_factor_coef w = the least-squares weight sum is taken over the specified reflections ; _item.name '_refine_ls_shell.wR_factor_R_free' _item.category_id refine_ls_shell _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_refine_ls_shell.R_factor_R_free' _item_related.function_code alternate _item_type.code float save_ save__refine_ls_shell.wR_factor_R_work _item_description.description ; Weighted residual factor wR for reflections that satisfy the resolution limits established by _refine_ls_shell.d_res_high and _refine_ls_shell.d_res_low and the observation limit established by _reflns.observed_criterion, and that were used as the working reflections (i.e. were included in the refinement) when the refinement included the calculation of a 'free' R factor. Details of how reflections were assigned to the working and test sets are given in _reflns.R_free_details. ( sum|w |Y~obs~ - Y~calc~|^2^| )^1/2^ wR = ( ---------------------------- ) ( sum|w Y~obs~^2^| ) Y~obs~ = the observed amplitude specified by _refine.ls_structure_factor_coef Y~calc~ = the calculated amplitude specified by _refine.ls_structure_factor_coef w = the least-squares weight sum is taken over the specified reflections ; _item.name '_refine_ls_shell.wR_factor_R_work' _item.category_id refine_ls_shell _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_related.related_name '_refine_ls_shell.R_factor_R_work' _item_related.function_code alternate _item_type.code float save_ ###################### ## REFINE_OCCUPANCY ## ###################### save_refine_occupancy _category.description ; Data items in the REFINE_OCCUPANCY category record details about the treatment of atom occupancies during refinement. ; _category.id refine_occupancy _category.mandatory_code no _category_key.name '_refine_occupancy.class' loop_ _category_group.id 'inclusive_group' 'refine_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _refine_occupancy.class _refine_occupancy.treatment _refine_occupancy.value _refine_occupancy.details 'protein' fix 1.00 . 'solvent' fix 1.00 . 'inhibitor orientation 1' fix 0.65 . 'inhibitor orientation 2' fix 0.35 ; The inhibitor binds to the enzyme in two alternative conformations. The occupancy of each conformation was adjusted so as to result in approximately equal mean thermal factors for the atoms in each conformation. ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__refine_occupancy.class _item_description.description ; The class of atoms treated similarly for occupancy refinement. ; _item.name '_refine_occupancy.class' _item.category_id refine_occupancy _item.mandatory_code yes _item_type.code text loop_ _item_examples.case 'all' 'protein' 'solvent' 'sugar-phosphate backbone' save_ save__refine_occupancy.details _item_description.description ; A description of special aspects of the occupancy refinement for a class of atoms described in _refine_occupancy.class. ; _item.name '_refine_occupancy.details' _item.category_id refine_occupancy _item.mandatory_code no _item_type.code text _item_examples.case ; The inhibitor binds to the enzyme in two alternative conformations. The occupancy of each conformation was adjusted so as to result in approximately equal mean thermal factors for the atoms in each conformation. ; save_ save__refine_occupancy.treatment _item_description.description ; The treatment of occupancies for a class of atoms described in _refine_occupancy.class. ; _item.name '_refine_occupancy.treatment' _item.category_id refine_occupancy _item.mandatory_code no _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail fix 'fixed' ref 'refined' save_ save__refine_occupancy.value _item_description.description ; The value of occupancy assigned to a class of atoms defined in _refine_occupancy.class. Meaningful only for atoms with fixed occupancy. ; _item.name '_refine_occupancy.value' _item.category_id refine_occupancy _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 0.0 0.0 0.0 _item_type.code float loop_ _item_examples.case 1.0 0.41 save_ ########### ## REFLN ## ########### save_refln _category.description ; Data items in the REFLN category record details about the reflection data used to determine the ATOM_SITE data items. The REFLN data items refer to individual reflections and must be included in looped lists. The REFLNS data items specify the parameters that apply to all reflections. The REFLNS data items are not looped. ; _category.id refln _category.mandatory_code no loop_ _category_key.name '_refln.index_h' '_refln.index_k' '_refln.index_l' loop_ _category_group.id 'inclusive_group' 'refln_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on data set fetod of Todres, Yanovsky, Ermekov & Struchkov [Acta Cryst. (1993), C49, 1352-1354]. ; ; loop_ _refln.index_h _refln.index_k _refln.index_l _refln.F_squared_calc _refln.F_squared_meas _refln.F_squared_sigma _refln.status 2 0 0 85.57 58.90 1.45 o 3 0 0 15718.18 15631.06 30.40 o 4 0 0 55613.11 49840.09 61.86 o 5 0 0 246.85 241.86 10.02 o 6 0 0 82.16 69.97 1.93 o 7 0 0 1133.62 947.79 11.78 o 8 0 0 2558.04 2453.33 20.44 o 9 0 0 283.88 393.66 7.79 o 10 0 0 283.70 171.98 4.26 o ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__refln.A_calc _item_description.description ; The calculated value of structure-factor component A in electrons. A = |F|cos(phase) ; _item.name '_refln.A_calc' _item.category_id refln _item.mandatory_code no _item_aliases.alias_name '_refln_A_calc' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_related.related_name '_refln.A_calc_au' _item_related.function_code conversion_arbitrary _item_type.code float _item_units.code electrons save_ save__refln.A_calc_au _item_description.description ; The calculated value of structure-factor component A in arbitrary units. A = |F|cos(phase) ; _item.name '_refln.A_calc_au' _item.category_id refln _item.mandatory_code no _item_related.related_name '_refln.A_calc' _item_related.function_code conversion_arbitrary _item_type.code float _item_units.code arbitrary save_ save__refln.A_meas _item_description.description ; The measured value of structure-factor component A in electrons. A = |F|cos(phase) ; _item.name '_refln.A_meas' _item.category_id refln _item.mandatory_code no _item_aliases.alias_name '_refln_A_meas' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_related.related_name '_refln.A_meas_au' _item_related.function_code conversion_arbitrary _item_type.code float _item_units.code electrons save_ save__refln.A_meas_au _item_description.description ; The measured value of structure-factor component A in arbitrary units. A = |F|cos(phase) ; _item.name '_refln.A_meas_au' _item.category_id refln _item.mandatory_code no _item_related.related_name '_refln.A_meas' _item_related.function_code conversion_arbitrary _item_type.code float _item_units.code arbitrary save_ save__refln.B_calc _item_description.description ; The calculated value of structure-factor component B in electrons. B = |F|sin(phase) ; _item.name '_refln.B_calc' _item.category_id refln _item.mandatory_code no _item_aliases.alias_name '_refln_B_calc' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_related.related_name '_refln.B_calc_au' _item_related.function_code conversion_arbitrary _item_type.code float _item_units.code electrons save_ save__refln.B_calc_au _item_description.description ; The calculated value of structure-factor component B in arbitrary units. B = |F|sin(phase) ; _item.name '_refln.B_calc_au' _item.category_id refln _item.mandatory_code no _item_related.related_name '_refln.B_calc' _item_related.function_code conversion_arbitrary _item_type.code float _item_units.code arbitrary save_ save__refln.B_meas _item_description.description ; The measured value of structure-factor component B in electrons. B = |F|sin(phase) ; _item.name '_refln.B_meas' _item.category_id refln _item.mandatory_code no _item_aliases.alias_name '_refln_B_meas' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_related.related_name '_refln.B_meas_au' _item_related.function_code conversion_arbitrary _item_type.code float _item_units.code electrons save_ save__refln.B_meas_au _item_description.description ; The measured value of structure-factor component B in arbitrary units. B = |F|sin(phase) ; _item.name '_refln.B_meas_au' _item.category_id refln _item.mandatory_code no _item_related.related_name '_refln.B_meas' _item_related.function_code conversion_arbitrary _item_type.code float _item_units.code arbitrary save_ save__refln.crystal_id _item_description.description ; This data item is a pointer to _exptl_crystal.id in the EXPTL_CRYSTAL category. ; _item.name '_refln.crystal_id' _item.mandatory_code yes _item_aliases.alias_name '_refln_crystal_id' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 save_ save__refln.F_calc _item_description.description ; The calculated value of the structure factor in electrons. ; _item.name '_refln.F_calc' _item.category_id refln _item.mandatory_code no _item_aliases.alias_name '_refln_F_calc' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_related.related_name '_refln.F_calc_au' _item_related.function_code conversion_arbitrary _item_type.code float _item_units.code electrons save_ save__refln.F_calc_au _item_description.description ; The calculated value of the structure factor in arbitrary units. ; _item.name '_refln.F_calc_au' _item.category_id refln _item.mandatory_code no _item_related.related_name '_refln.F_calc' _item_related.function_code conversion_arbitrary _item_type.code float _item_units.code arbitrary save_ save__refln.F_meas _item_description.description ; The measured value of the structure factor in electrons. ; _item.name '_refln.F_meas' _item.category_id refln _item.mandatory_code no _item_aliases.alias_name '_refln_F_meas' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_related.related_name _item_related.function_code '_refln.F_meas_sigma' associated_esd '_refln.F_meas_au' conversion_arbitrary _item_type.code float _item_type_conditions.code esd _item_units.code electrons save_ save__refln.F_meas_au _item_description.description ; The measured value of the structure factor in arbitrary units. ; _item.name '_refln.F_meas_au' _item.category_id refln _item.mandatory_code no loop_ _item_related.related_name _item_related.function_code '_refln.F_meas_sigma_au' associated_esd '_refln.F_meas' conversion_arbitrary _item_type.code float _item_type_conditions.code esd _item_units.code arbitrary save_ save__refln.F_meas_sigma _item_description.description ; The standard uncertainty (estimated standard deviation) of _refln.F_meas in electrons. ; _item.name '_refln.F_meas_sigma' _item.category_id refln _item.mandatory_code no _item_aliases.alias_name '_refln_F_sigma' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_related.related_name _item_related.function_code '_refln.F_meas' associated_value '_refln.F_meas_sigma_au' conversion_arbitrary _item_type.code float _item_units.code electrons save_ save__refln.F_meas_sigma_au _item_description.description ; The standard uncertainty (estimated standard deviation) of _refln.F_meas_au in arbitrary units. ; _item.name '_refln.F_meas_sigma_au' _item.category_id refln _item.mandatory_code no loop_ _item_related.related_name _item_related.function_code '_refln.F_meas_au' associated_value '_refln.F_meas_sigma' conversion_arbitrary _item_type.code float _item_units.code arbitrary save_ save__refln.F_squared_calc _item_description.description ; The calculated value of the squared structure factor in electrons squared. ; _item.name '_refln.F_squared_calc' _item.category_id refln _item.mandatory_code no _item_aliases.alias_name '_refln_F_squared_calc' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code float _item_units.code electrons_squared save_ save__refln.F_squared_meas _item_description.description ; The measured value of the squared structure factor in electrons squared. ; _item.name '_refln.F_squared_meas' _item.category_id refln _item.mandatory_code no _item_aliases.alias_name '_refln_F_squared_meas' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code float _item_units.code electrons_squared save_ save__refln.F_squared_sigma _item_description.description ; The standard uncertainty (derived from measurement) of the squared structure factor in electrons squared. ; _item.name '_refln.F_squared_sigma' _item.category_id refln _item.mandatory_code no _item_aliases.alias_name '_refln_F_squared_sigma' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code float _item_units.code electrons_squared save_ save__refln.fom _item_description.description ; The figure of merit m for this reflection. int P~alpha~ exp(i*alpha) dalpha m = -------------------------------- int P~alpha~ dalpha P~a~ = the probability that the phase angle a is correct int is taken over the range alpha = 0 to 2 pi. ; _item.name '_refln.fom' _item.category_id refln _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__refln.index_h _item_description.description ; Miller index h of the reflection. The values of the Miller indices in the REFLN category must correspond to the cell defined by cell lengths and cell angles in the CELL category. ; _item.name '_refln.index_h' _item.category_id refln _item.mandatory_code yes _item_aliases.alias_name '_refln_index_h' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_refln.index_k' '_refln.index_l' _item_sub_category.id miller_index _item_type.code int save_ save__refln.index_k _item_description.description ; Miller index k of the reflection. The values of the Miller indices in the REFLN category must correspond to the cell defined by cell lengths and cell angles in the CELL category. ; _item.name '_refln.index_k' _item.category_id refln _item.mandatory_code yes _item_aliases.alias_name '_refln_index_k' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_refln.index_h' '_refln.index_l' _item_sub_category.id miller_index _item_type.code int save_ save__refln.index_l _item_description.description ; Miller index l of the reflection. The values of the Miller indices in the REFLN category must correspond to the cell defined by cell lengths and cell angles in the CELL category. ; _item.name '_refln.index_l' _item.category_id refln _item.mandatory_code yes _item_aliases.alias_name '_refln_index_l' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_dependent.dependent_name '_refln.index_h' '_refln.index_k' _item_sub_category.id miller_index _item_type.code int save_ save__refln.intensity_calc _item_description.description ; The calculated value of the intensity in the same units as _refln.intensity_meas. ; _item.name '_refln.intensity_calc' _item.category_id refln _item.mandatory_code no _item_aliases.alias_name '_refln_intensity_calc' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code float save_ save__refln.intensity_meas _item_description.description ; The measured value of the intensity. ; _item.name '_refln.intensity_meas' _item.category_id refln _item.mandatory_code no _item_aliases.alias_name '_refln_intensity_meas' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code float save_ save__refln.intensity_sigma _item_description.description ; The standard uncertainty (derived from measurement) of the intensity in the same units as _refln.intensity_meas. ; _item.name '_refln.intensity_sigma' _item.category_id refln _item.mandatory_code no _item_aliases.alias_name '_refln_intensity_sigma' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code float save_ #save__refln.mean_path_length_tbar # _item_description.description #; Mean path length in millimetres through the crystal for this # reflection. #; # _item.name '_refln.mean_path_length_tbar' # _item.category_id refln # _item.mandatory_code no # _item_aliases.alias_name '_refln_mean_path_length_tbar' # _item_aliases.dictionary cif_core.dic # _item_aliases.version 2.0.1 # _item_type.code float # _item_units.code millimetres # save_ save__refln.status _item_description.description ; Classification of a reflection so as to indicate its status with respect to inclusion in the refinement and the calculation of R factors. ; _item.name '_refln.status' _item.category_id refln _item.mandatory_code no _item_aliases.alias_name '_refln_observed_status' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 # _item_default.value o _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail o ; satisfies _refine.ls_d_res_high, satisfies _refine.ls_d_res_low, observed by _reflns.observed_criterion, not flagged as systematically absent, not flagged as unreliable ; < ; satisfies _refine.ls_d_res_high, satisfies _refine.ls_d_res_low, unobserved by _reflns.observed_criterion, not flagged as systematically absent, not flagged as unreliable ; - 'systematically absent reflection' x 'unreliable measurement -- not used' h 'does not satisfy _refine.ls_d_res_high' l 'does not satisfy _refine.ls_d_res_low' f ; satisfies _refine.ls_d_res_high, satisfies _refine.ls_d_res_low, observed by _reflns.observed_criterion, not flagged as systematically absent, not flagged as unreliable, excluded from refinement so as to be included in the calculation of a 'free' R factor ; save_ save__refln.phase_calc _item_description.description ; The calculated structure-factor phase in degrees. ; _item.name '_refln.phase_calc' _item.category_id refln _item.mandatory_code no _item_aliases.alias_name '_refln_phase_calc' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code float _item_units.code degrees save_ save__refln.phase_meas _item_description.description ; The measured structure-factor phase in degrees. ; _item.name '_refln.phase_meas' _item.category_id refln _item.mandatory_code no _item_aliases.alias_name '_refln_phase_meas' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code float _item_units.code degrees save_ save__refln.refinement_status _item_description.description ; Status of a reflection in the structure-refinement process. ; _item.name '_refln.refinement_status' _item.category_id refln _item.mandatory_code no _item_aliases.alias_name '_refln_refinement_status' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_default.value incl _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail incl 'included in ls process' excl 'excluded from ls process' extn 'excluded due to extinction' save_ save__refln.scale_group_code _item_description.description ; This data item is a pointer to _reflns_scale.group_code in the REFLNS_SCALE category. ; _item.name '_refln.scale_group_code' _item.mandatory_code yes _item_aliases.alias_name '_refln_scale_group_code' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 save_ save__refln.sint_over_lambda _item_description.description ; The (sin theta)/lambda value in reciprocal angstroms for this reflection. ; _item.name '_refln.sint_over_lambda' _item.category_id refln _item.mandatory_code no _item_aliases.alias_name '_refln_sint/lambda' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code reciprocal_angstroms save_ save__refln.symmetry_epsilon _item_description.description ; The symmetry reinforcement factor corresponding to the number of times the reflection indices are generated identically from the space-group symmetry operations. ; _item.name '_refln.symmetry_epsilon' _item.category_id refln _item.mandatory_code no _item_aliases.alias_name '_refln_symmetry_epsilon' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 48 48 48 1 1 1 _item_type.code int save_ save__refln.symmetry_multiplicity _item_description.description ; The number of symmetry-equivalent reflections. The equivalent reflections have the same structure-factor magnitudes because of the space-group symmetry and the Friedel relationship. ; _item.name '_refln.symmetry_multiplicity' _item.category_id refln _item.mandatory_code no _item_aliases.alias_name '_refln_symmetry_multiplicity' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 48 48 48 1 1 1 _item_type.code int save_ save__refln.wavelength _item_description.description ; The mean wavelength in angstroms of radiation used to measure this reflection. This is an important parameter for data collected using energy-dispersive detectors or the Laue method. ; _item.name '_refln.wavelength' _item.category_id refln _item.mandatory_code no _item_aliases.alias_name '_refln_wavelength' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__refln.wavelength_id _item_description.description ; This data item is a pointer to _diffrn_radiation.wavelength_id in the DIFFRN_RADIATION category. ; _item.name '_refln.wavelength_id' _item.mandatory_code yes _item_aliases.alias_name '_refln_wavelength_id' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 save_ ################### ## REFLN_SYS_ABS ## ################### save_refln_sys_abs _category.description ; Data items in the REFLN_SYS_ABS category record details about the reflection data that should be systematically absent, given the designated space group. ; _category.id refln_sys_abs _category.mandatory_code no loop_ _category_key.name '_refln_sys_abs.index_h' '_refln_sys_abs.index_k' '_refln_sys_abs.index_l' loop_ _category_group.id 'inclusive_group' 'refln_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - hypothetical example. ; ; loop_ _refln_sys_abs.index_h _refln_sys_abs.index_k _refln_sys_abs.index_l _refln_sys_abs.I _refln_sys_abs.sigmaI _refln_sys_abs.I_over_sigmaI 0 3 0 28.32 22.95 1.23 0 5 0 14.11 16.38 0.86 0 7 0 114.81 20.22 5.67 0 9 0 32.99 24.51 1.35 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__refln_sys_abs.I _item_description.description ; The measured value of the intensity in arbitrary units. ; _item.name '_refln_sys_abs.I' _item.category_id refln_sys_abs _item.mandatory_code no _item_aliases.alias_name '_ebi_refln_sys_abs.I' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_related.related_name _item_related.function_code '_refln_sys_abs.sigmaI' associated_esd _item_type.code float _item_type_conditions.code esd _item_units.code arbitrary save_ save__refln_sys_abs.I_over_sigmaI _item_description.description ; The ratio of _refln_sys_abs.I to _refln_sys_abs.sigmaI. Used to evaluate whether a reflection that should be systematically absent according to the designated space group is in fact absent. ; _item.name '_refln_sys_abs.I_over_sigmaI' _item.category_id refln_sys_abs _item.mandatory_code no _item_aliases.alias_name '_ebi_refln_sys_abs.I_over_sigma' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 _item_type.code float save_ save__refln_sys_abs.index_h _item_description.description ; Miller index h of the reflection. The values of the Miller indices in the REFLN_SYS_ABS category must correspond to the cell defined by cell lengths and cell angles in the CELL category. ; _item.name '_refln_sys_abs.index_h' _item.category_id refln_sys_abs _item.mandatory_code yes _item_aliases.alias_name '_ebi_refln_sys_abs.h' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_dependent.dependent_name '_refln_sys_abs.index_k' '_refln_sys_abs.index_l' _item_sub_category.id miller_index _item_type.code int save_ save__refln_sys_abs.index_k _item_description.description ; Miller index k of the reflection. The values of the Miller indices in the REFLN_SYS_ABS category must correspond to the cell defined by cell lengths and cell angles in the CELL category. ; _item.name '_refln_sys_abs.index_k' _item.category_id refln_sys_abs _item.mandatory_code yes _item_aliases.alias_name '_ebi_refln_sys_abs.k' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_dependent.dependent_name '_refln_sys_abs.index_h' '_refln_sys_abs.index_l' _item_sub_category.id miller_index _item_type.code int save_ save__refln_sys_abs.index_l _item_description.description ; Miller index l of the reflection. The values of the Miller indices in the REFLN_SYS_ABS category must correspond to the cell defined by cell lengths and cell angles in the CELL category. ; _item.name '_refln_sys_abs.index_l' _item.category_id refln_sys_abs _item.mandatory_code yes _item_aliases.alias_name '_ebi_refln_sys_abs.l' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_dependent.dependent_name '_refln_sys_abs.index_h' '_refln_sys_abs.index_k' _item_sub_category.id miller_index _item_type.code int save_ save__refln_sys_abs.sigmaI _item_description.description ; The standard uncertainty (estimated standard deviation) of _refln_sys_abs.I in arbitrary units. ; _item.name '_refln_sys_abs.sigmaI' _item.category_id refln_sys_abs _item.mandatory_code no _item_aliases.alias_name '_ebi_refln_sys_abs.sigmaI' _item_aliases.dictionary ebi_extensions _item_aliases.version 1.0 loop_ _item_related.related_name _item_related.function_code '_refln_sys_abs.I' associated_value _item_type.code float _item_units.code arbitrary save_ ############ ## REFLNS ## ############ save_reflns _category.description ; Data items in the REFLNS category record details about the reflection data used to determine the ATOM_SITE data items. The REFLN data items refer to individual reflections and must be included in looped lists. The REFLNS data items specify the parameters that apply to all reflections. The REFLNS data items are not looped. ; _category.id reflns _category.mandatory_code no _category_key.name '_reflns.entry_id' loop_ _category_group.id 'inclusive_group' 'refln_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _reflns.entry_id '5HVP' _reflns.data_reduction_method ; Xengen program scalei. Anomalous pairs were merged. Scaling proceeded in several passes, beginning with 1-parameter fit and ending with 3-parameter fit. ; _reflns.data_reduction_details ; Merging and scaling based on only those reflections with I > \s(I). ; _reflns.d_resolution_high 2.00 _reflns.d_resolution_low 8.00 _reflns.limit_h_max 22 _reflns.limit_h_min 0 _reflns.limit_k_max 46 _reflns.limit_k_min 0 _reflns.limit_l_max 57 _reflns.limit_l_min 0 _reflns.number_obs 7228 _reflns.observed_criterion '> 1 \s(I)' _reflns.details none ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _reflns.limit_h_min 0 _reflns.limit_h_max 6 _reflns.limit_k_min 0 _reflns.limit_k_max 17 _reflns.limit_l_min 0 _reflns.limit_l_max 22 _reflns.number_all 1592 _reflns.number_obs 1408 _reflns.observed_criterion F_>_6.0_\s(F) _reflns.d_resolution_high 0.8733 _reflns.d_resolution_low 11.9202 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__reflns.B_iso_Wilson_estimate _item_description.description ; The value of the overall isotropic displacement parameter estimated from the slope of the Wilson plot. ; _item.name '_reflns.B_iso_Wilson_estimate' _item.category_id reflns _item.mandatory_code no _item_type.code float _item_units.code angstroms_squared save_ save__reflns.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_reflns.entry_id' _item.mandatory_code yes save_ save__reflns.data_reduction_details _item_description.description ; A description of special aspects of the data-reduction procedures. ; _item.name '_reflns.data_reduction_details' _item.category_id reflns _item.mandatory_code no _item_type.code text _item_examples.case ; Merging and scaling based on only those reflections with I > sig(I). ; save_ save__reflns.data_reduction_method _item_description.description ; The method used for data reduction. Note that this is not the computer program used, which is described in the SOFTWARE category, but the method itself. This data item should be used to describe significant methodological options used within the data-reduction programs. ; _item.name '_reflns.data_reduction_method' _item.category_id reflns _item.mandatory_code no _item_type.code text _item_examples.case ; Profile fitting by method of Kabsch (1987). Scaling used spherical harmonic coefficients. ; save_ save__reflns.d_resolution_high _item_description.description ; The smallest value for the interplanar spacings for the reflection data. This is called the highest resolution. ; _item.name '_reflns.d_resolution_high' _item.category_id reflns _item.mandatory_code no _item_aliases.alias_name '_reflns_d_resolution_high' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__reflns.d_resolution_low _item_description.description ; The largest value for the interplanar spacings for the reflection data. This is called the lowest resolution. ; _item.name '_reflns.d_resolution_low' _item.category_id reflns _item.mandatory_code no _item_aliases.alias_name '_reflns_d_resolution_low' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__reflns.details _item_description.description ; A description of reflection data not covered by other data names. This should include details of the Friedel pairs. ; _item.name '_reflns.details' _item.category_id reflns _item.mandatory_code no _item_aliases.alias_name '_reflns_special_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__reflns.limit_h_max _item_description.description ; Maximum value of the Miller index h for the reflection data. This need not have the same value as _diffrn_reflns.limit_h_max. ; _item.name '_reflns.limit_h_max' _item.category_id reflns _item.mandatory_code no _item_aliases.alias_name '_reflns_limit_h_max' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code int save_ save__reflns.limit_h_min _item_description.description ; Minimum value of the Miller index h for the reflection data. This need not have the same value as _diffrn_reflns.limit_h_min. ; _item.name '_reflns.limit_h_min' _item.category_id reflns _item.mandatory_code no _item_aliases.alias_name '_reflns_limit_h_min' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code int save_ save__reflns.limit_k_max _item_description.description ; Maximum value of the Miller index k for the reflection data. This need not have the same value as _diffrn_reflns.limit_k_max. ; _item.name '_reflns.limit_k_max' _item.category_id reflns _item.mandatory_code no _item_aliases.alias_name '_reflns_limit_k_max' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code int save_ save__reflns.limit_k_min _item_description.description ; Minimum value of the Miller index k for the reflection data. This need not have the same value as _diffrn_reflns.limit_k_min. ; _item.name '_reflns.limit_k_min' _item.category_id reflns _item.mandatory_code no _item_aliases.alias_name '_reflns_limit_k_min' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code int save_ save__reflns.limit_l_max _item_description.description ; Maximum value of the Miller index l for the reflection data. This need not have the same value as _diffrn_reflns.limit_l_max. ; _item.name '_reflns.limit_l_max' _item.category_id reflns _item.mandatory_code no _item_aliases.alias_name '_reflns_limit_l_max' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code int save_ save__reflns.limit_l_min _item_description.description ; Minimum value of the Miller index l for the reflection data. This need not have the same value as _diffrn_reflns.limit_l_min. ; _item.name '_reflns.limit_l_min' _item.category_id reflns _item.mandatory_code no _item_aliases.alias_name '_reflns_limit_l_min' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code int save_ save__reflns.number_all _item_description.description ; The total number of reflections in the REFLN list (not the DIFFRN_REFLN list). This number may contain Friedel-equivalent reflections according to the nature of the structure and the procedures used. The item _reflns.details describes the reflection data. ; _item.name '_reflns.number_all' _item.category_id reflns _item.mandatory_code no _item_aliases.alias_name '_reflns_number_total' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__reflns.number_obs _item_description.description ; The number of reflections in the REFLN list (not the DIFFRN_REFLN list) classified as observed (see _reflns.observed_criterion). This number may contain Friedel-equivalent reflections according to the nature of the structure and the procedures used. ; _item.name '_reflns.number_obs' _item.category_id reflns _item.mandatory_code no _item_aliases.alias_name '_reflns_number_observed' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__reflns.observed_criterion _item_description.description ; The criterion used to classify a reflection as 'observed'. This criterion is usually expressed in terms of a sigma(I) or sigma(F) threshold. ; _item.name '_reflns.observed_criterion' _item.category_id reflns _item.mandatory_code no _item_aliases.alias_name '_reflns_observed_criterion' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_related.related_name _item_related.function_code '_reflns.observed_criterion_sigma_F' alternate '_reflns.observed_criterion_sigma_I' alternate '_reflns.observed_criterion_I_min' alternate '_reflns.observed_criterion_I_max' alternate '_reflns.observed_criterion_F_min' alternate '_reflns.observed_criterion_F_max' alternate _item_type.code text _item_examples.case '>2sigma(I)' save_ save__reflns.observed_criterion_F_max _item_description.description ; The criterion used to classify a reflection as 'observed' expressed as an upper limit for the value of F. ; _item.name '_reflns.observed_criterion_F_max' _item.category_id reflns _item.mandatory_code no loop_ _item_related.related_name _item_related.function_code '_reflns.observed_criterion' alternate '_reflns.observed_criterion_I_max' convention _item_type.code float save_ save__reflns.observed_criterion_F_min _item_description.description ; The criterion used to classify a reflection as 'observed' expressed as a lower limit for the value of F. ; _item.name '_reflns.observed_criterion_F_min' _item.category_id reflns _item.mandatory_code no loop_ _item_related.related_name _item_related.function_code '_reflns.observed_criterion' alternate '_reflns.observed_criterion_I_min' convention _item_type.code float save_ save__reflns.observed_criterion_I_max _item_description.description ; The criterion used to classify a reflection as 'observed' expressed as an upper limit for the value of I. ; _item.name '_reflns.observed_criterion_I_max' _item.category_id reflns _item.mandatory_code no loop_ _item_related.related_name _item_related.function_code '_reflns.observed_criterion' alternate '_reflns.observed_criterion_F_max' convention _item_type.code float save_ save__reflns.observed_criterion_I_min _item_description.description ; The criterion used to classify a reflection as 'observed' expressed as a lower limit for the value of I. ; _item.name '_reflns.observed_criterion_I_min' _item.category_id reflns _item.mandatory_code no loop_ _item_related.related_name _item_related.function_code '_reflns.observed_criterion' alternate '_reflns.observed_criterion_F_min' convention _item_type.code float save_ save__reflns.observed_criterion_sigma_F _item_description.description ; The criterion used to classify a reflection as 'observed' expressed as a multiple of the value of sigma(F). ; _item.name '_reflns.observed_criterion_sigma_F' _item.category_id reflns _item.mandatory_code no loop_ _item_related.related_name _item_related.function_code '_reflns.observed_criterion' alternate '_reflns.observed_criterion_sigma_I' convention _item_type.code float save_ save__reflns.observed_criterion_sigma_I _item_description.description ; The criterion used to classify a reflection as 'observed' expressed as a multiple of the value of sigma(I). ; _item.name '_reflns.observed_criterion_sigma_I' _item.category_id reflns _item.mandatory_code no loop_ _item_related.related_name _item_related.function_code '_reflns.observed_criterion' alternate '_reflns.observed_criterion_sigma_F' convention _item_type.code float save_ save__reflns.percent_possible_obs _item_description.description ; The percentage of geometrically possible reflections represented by reflections that satisfy the resolution limits established by _reflns.d_resolution_high and _reflns.d_resolution_low and the observation limit established by _reflns.observed_criterion. ; _item.name '_reflns.percent_possible_obs' _item.category_id reflns _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__reflns.R_free_details _item_description.description ; A description of the method by which a subset of reflections was selected for exclusion from refinement so as to be used in the calculation of a 'free' R factor. ; _item.name '_reflns.R_free_details' _item.category_id reflns _item.mandatory_code no _item_type.code text _item_examples.case ; The data set was sorted with l varying most rapidly and h varying least rapidly. Every 10th reflection in this sorted list was excluded from refinement and included in the calculation of a 'free' R factor. ; save_ save__reflns.Rmerge_F_all _item_description.description ; Residual factor Rmerge for all reflections that satisfy the resolution limits established by _reflns.d_resolution_high and _reflns.d_resolution_low. sum~i~(sum~j~|F~j~ - |) Rmerge(F) = -------------------------- sum~i~(sum~j~) F~j~ = the amplitude of the jth observation of reflection i = the mean of the amplitudes of all observations of reflection i sum~i~ is taken over all reflections sum~j~ is taken over all observations of each reflection ; _item.name '_reflns.Rmerge_F_all' _item.category_id reflns _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__reflns.Rmerge_F_obs _item_description.description ; Residual factor Rmerge for reflections that satisfy the resolution limits established by _reflns.d_resolution_high and _reflns.d_resolution_low and the observation limit established by _reflns.observed_criterion. sum~i~(sum~j~|F~j~ - |) Rmerge(F) = -------------------------- sum~i~(sum~j~) F~j~ = the amplitude of the jth observation of reflection i = the mean of the amplitudes of all observations of reflection i sum~i~ is taken over all reflections sum~j~ is taken over all observations of each reflection ; _item.name '_reflns.Rmerge_F_obs' _item.category_id reflns _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ ################## ## REFLNS_SCALE ## ################## save_reflns_scale _category.description ; Data items in the REFLNS_SCALE category record details about the structure-factor scales. They are referenced from within the REFLN list through _refln.scale_group_code. ; _category.id reflns_scale _category.mandatory_code no _category_key.name '_reflns_scale.group_code' loop_ _category_group.id 'inclusive_group' 'refln_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on laboratory records for the collagen-like peptide [(POG)4 EKG (POG)5]3. ; ; _reflns_scale.group_code SG1 _reflns_scale.meas_F 4.0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__reflns_scale.group_code _item_description.description ; The code identifying a scale _reflns_scale.meas_F, _reflns_scale.meas_F_squared or _reflns_scale.meas_intensity. These are linked to the REFLN list by the _refln.scale_group_code. These codes need not correspond to those in the DIFFRN_SCALE list. ; loop_ _item.name _item.category_id _item.mandatory_code '_reflns_scale.group_code' reflns_scale yes '_refln.scale_group_code' refln yes _item_aliases.alias_name '_reflns_scale_group_code' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_linked.child_name _item_linked.parent_name '_refln.scale_group_code' '_reflns_scale.group_code' _item_type.code line loop_ _item_examples.case '1' '2' 'c1' 'c2' save_ save__reflns_scale.meas_F _item_description.description ; A scale associated with _reflns_scale.group_code. ; _item.name '_reflns_scale.meas_F' _item.category_id reflns_scale _item.mandatory_code no _item_aliases.alias_name '_reflns_scale_meas_F' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__reflns_scale.meas_F_squared _item_description.description ; A scale associated with _reflns_scale.group_code. ; _item.name '_reflns_scale.meas_F_squared' _item.category_id reflns_scale _item.mandatory_code no _item_aliases.alias_name '_reflns_scale_meas_F_squared' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__reflns_scale.meas_intensity _item_description.description ; A scale associated with _reflns_scale.group_code. ; _item.name '_reflns_scale.meas_intensity' _item.category_id reflns_scale _item.mandatory_code no _item_aliases.alias_name '_reflns_scale_meas_intensity' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ ################## ## REFLNS_SHELL ## ################## save_reflns_shell _category.description ; Data items in the REFLNS_SHELL category record details about the reflection data used to determine the ATOM_SITE data items broken down into shells of resolution. ; _category.id reflns_shell _category.mandatory_code no loop_ _category_key.name '_reflns_shell.d_res_high' '_reflns_shell.d_res_low' loop_ _category_group.id 'inclusive_group' 'refln_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _reflns_shell.d_res_high _reflns_shell.d_res_low _reflns_shell.meanI_over_sigI_obs _reflns_shell.number_measured_obs _reflns_shell.number_unique_obs _reflns_shell.percent_possible_obs _reflns_shell.Rmerge_F_obs 31.38 3.82 69.8 9024 2540 96.8 1.98 3.82 3.03 26.1 7413 2364 95.1 3.85 3.03 2.65 10.5 5640 2123 86.2 6.37 2.65 2.41 6.4 4322 1882 76.8 8.01 2.41 2.23 4.3 3247 1714 70.4 9.86 2.23 2.10 3.1 1140 812 33.3 13.99 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__reflns_shell.d_res_high _item_description.description ; The smallest value in angstroms for the interplanar spacings for the reflections in this shell. This is called the highest resolution. ; _item.name '_reflns_shell.d_res_high' _item.category_id reflns_shell _item.mandatory_code yes _item_aliases.alias_name '_reflns_shell_d_res_high' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__reflns_shell.d_res_low _item_description.description ; The highest value in angstroms for the interplanar spacings for the reflections in this shell. This is called the lowest resolution. ; _item.name '_reflns_shell.d_res_low' _item.category_id reflns_shell _item.mandatory_code yes _item_aliases.alias_name '_reflns_shell_d_res_low' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__reflns_shell.meanI_over_sigI_all _item_description.description ; The ratio of the mean of the intensities of all reflections in this shell to the mean of the standard uncertainties of the intensities of all reflections in this shell. ; _item.name '_reflns_shell.meanI_over_sigI_all' _item.category_id reflns_shell _item.mandatory_code no _item_aliases.alias_name '_reflns_shell_meanI_over_sigI_all' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code float save_ save__reflns_shell.meanI_over_sigI_obs _item_description.description ; The ratio of the mean of the intensities of the reflections classified as 'observed' (see _reflns.observed_criterion) in this shell to the mean of the standard uncertainties of the intensities of the 'observed' reflections in this shell. ; _item.name '_reflns_shell.meanI_over_sigI_obs' _item.category_id reflns_shell _item.mandatory_code no _item_aliases.alias_name '_reflns_shell_meanI_over_sigI_obs' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code float save_ save__reflns_shell.number_measured_all _item_description.description ; The total number of reflections measured for this shell. ; _item.name '_reflns_shell.number_measured_all' _item.category_id reflns_shell _item.mandatory_code no _item_aliases.alias_name '_reflns_shell_number_measured_all' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code int save_ save__reflns_shell.number_measured_obs _item_description.description ; The number of reflections classified as 'observed' (see _reflns.observed_criterion) for this shell. ; _item.name '_reflns_shell.number_measured_obs' _item.category_id reflns_shell _item.mandatory_code no _item_aliases.alias_name '_reflns_shell_number_measured_obs' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code int save_ save__reflns_shell.number_possible _item_description.description ; The number of unique reflections it is possible to measure in this shell. ; _item.name '_reflns_shell.number_possible' _item.category_id reflns_shell _item.mandatory_code no _item_aliases.alias_name '_reflns_shell_number_possible' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__reflns_shell.number_unique_all _item_description.description ; The total number of measured reflections which are symmetry- unique after merging for this shell. ; _item.name '_reflns_shell.number_unique_all' _item.category_id reflns_shell _item.mandatory_code no _item_aliases.alias_name '_reflns_shell_number_unique_all' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code int save_ save__reflns_shell.number_unique_obs _item_description.description ; The total number of measured reflections classified as 'observed' (see _reflns.observed_criterion) which are symmetry-unique after merging for this shell. ; _item.name '_reflns_shell.number_unique_obs' _item.category_id reflns_shell _item.mandatory_code no _item_aliases.alias_name '_reflns_shell_number_unique_obs' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code int save_ save__reflns_shell.percent_possible_all _item_description.description ; The percentage of geometrically possible reflections represented by all reflections measured for this shell. ; _item.name '_reflns_shell.percent_possible_all' _item.category_id reflns_shell _item.mandatory_code no _item_aliases.alias_name '_reflns_shell_percent_possible_all' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__reflns_shell.percent_possible_obs _item_description.description ; The percentage of geometrically possible reflections represented by reflections classified as 'observed' (see _reflns.observed_criterion) for this shell. ; _item.name '_reflns_shell.percent_possible_obs' _item.category_id reflns_shell _item.mandatory_code no _item_aliases.alias_name '_reflns_shell_percent_possible_obs' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__reflns_shell.Rmerge_F_all _item_description.description ; Residual factor Rmerge for all reflections that satisfy the resolution limits established by _reflns_shell.d_res_high and _reflns_shell.d_res_low. sum~i~(sum~j~|F~j~ - |) Rmerge(F) = -------------------------- sum~i~(sum~j~) F~j~ = the amplitude of the jth observation of reflection i = the mean of the amplitudes of all observations of reflection i sum~i~ is taken over all reflections sum~j~ is taken over all observations of each reflection ; _item.name '_reflns_shell.Rmerge_F_all' _item.category_id reflns_shell _item.mandatory_code no _item_aliases.alias_name '_reflns_shell_Rmerge_F_all' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__reflns_shell.Rmerge_F_obs _item_description.description ; Residual factor Rmerge for reflections that satisfy the resolution limits established by _reflns_shell.d_res_high and _reflns_shell.d_res_low and the observation criterion established by _reflns.observed_criterion. sum~i~(sum~j~|F~j~ - |) Rmerge(F) = -------------------------- sum~i~(sum~j~) F~j~ = the amplitude of the jth observation of reflection i = the mean of the amplitudes of all observations of reflection i sum~i~ is taken over all reflections sum~j~ is taken over all observations of each reflection ; _item.name '_reflns_shell.Rmerge_F_obs' _item.category_id reflns_shell _item.mandatory_code no _item_aliases.alias_name '_reflns_shell_Rmerge_F_obs' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__reflns_shell.Rmerge_I_all _item_description.description ; The value of Rmerge(I) for all reflections in a given shell. sum~i~(sum~j~|I~j~ - |) Rmerge(I) = -------------------------- sum~i~(sum~j~) I~j~ = the intensity of the jth observation of reflection i = the mean of the intensities of all observations of reflection i sum~i~ is taken over all reflections sum~j~ is taken over all observations of each reflection ; _item.name '_reflns_shell.Rmerge_I_all' _item.category_id reflns_shell _item.mandatory_code no _item_aliases.alias_name '_reflns_shell_Rmerge_I_all' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__reflns_shell.Rmerge_I_obs _item_description.description ; The value of Rmerge(I) for reflections classified as 'observed' (see _reflns.observed_criterion) in a given shell. sum~i~(sum~j~|I~j~ - |) Rmerge(I) = -------------------------- sum~i~(sum~j~) I~j~ = the intensity of the jth observation of reflection i = the mean of the intensities of all observations of reflection i sum~i~ is taken over all reflections sum~j~ is taken over all observations of each reflection ; _item.name '_reflns_shell.Rmerge_I_obs' _item.category_id reflns_shell _item.mandatory_code no _item_aliases.alias_name '_reflns_shell_Rmerge_I_obs' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ ############## ## SOFTWARE ## ############## save_software _category.description ; Data items in the SOFTWARE category record details about the software used in the structure analysis, which implies any software used in the generation of any data items associated with the structure determination and structure representation. These data items allow computer programs to be referenced in more detail than data items in the COMPUTING category do. ; _category.id software _category.mandatory_code no loop_ _category_key.name '_software.name' '_software.version' loop_ _category_group.id 'inclusive_group' 'computing_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _software.name _software.version _software.date _software.type _software.contact_author _software.contact_author_email _software.location _software.classification _software.citation_id _software.language _software.compiler_name _software.compiler_version _software.hardware _software.os _software.os_version _software.dependencies _software.mods _software.description Prolsq unknown . program 'Wayne A. Hendrickson' ? 'ftp://rosebud.sdsc.edu/pub/sdsc/xtal/CCP4/ccp4/' refinement ref5 Fortran 'Convex Fortran' v8.0 'Convex C220' ConvexOS v10.1 'Requires that Protin be run first' optimized 'restrained least-squares refinement' ; save_ # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save__software.citation_id _item_description.description ; This data item is a pointer to _citation.id in the CITATION category. ; _item.name '_software.citation_id' _item.mandatory_code no save_ save__software.classification _item_description.description ; The classification of the program according to its major function. ; _item.name '_software.classification' _item.category_id software _item.mandatory_code no _item_type.code uline loop_ _item_examples.case 'data collection' 'data reduction' 'phasing' 'model building' 'refinement' 'validation' 'other' save_ save__software.compiler_name _item_description.description ; The compiler used to compile the software. ; _item.name '_software.compiler_name' _item.category_id software _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'Convex Fortran' 'gcc' 'DEC C' save_ save__software.compiler_version _item_description.description ; The version of the compiler used to compile the software. ; _item.name '_software.compiler_version' _item.category_id software _item.mandatory_code no _item_type.code line loop_ _item_examples.case '3.1' '2.1 alpha' save_ save__software.contact_author _item_description.description ; The recognized contact author of the software. This could be the original author, someone who has modified the code or someone who maintains the code. It should be the person most commonly associated with the code. ; _item.name '_software.contact_author' _item.category_id software _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'T. Alwyn Jones' 'Axel Brunger' save_ save__software.contact_author_email _item_description.description ; The e-mail address of the person specified in _software.contact_author. ; _item.name '_software.contact_author_email' _item.category_id software _item.mandatory_code no _item_type.code line _item_examples.case 'bourne@sdsc.edu' save_ save__software.date _item_description.description ; The date the software was released. ; _item.name '_software.date' _item.category_id software _item.mandatory_code no _item_type.code line loop_ _item_examples.case 1991-10-01 1990-04-30 save_ save__software.description _item_description.description ; Description of the software. ; _item.name '_software.description' _item.category_id software _item.mandatory_code no _item_type.code line _item_examples.case 'Uses method of restrained least squares' save_ save__software.dependencies _item_description.description ; Any prerequisite software required to run _software.name. ; _item.name '_software.dependencies' _item.category_id software _item.mandatory_code no _item_type.code line _item_examples.case 'PDBlib class library' save_ save__software.hardware _item_description.description ; The hardware upon which the software was run. ; _item.name '_software.hardware' _item.category_id software _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'Sun Sparc 10 model 41' 'Dec Alpha 3000 model 500S' 'Silicon Graphics Elan' 'Compaq PC 486/66' save_ save__software.language _item_description.description ; The major computing language in which the software is coded. ; _item.name '_software.language' _item.category_id software _item.mandatory_code no _item_type.code uline loop_ _item_enumeration.value Ada assembler Awk Basic 'C++' 'C/C++' C csh Fortran Fortran_77 'Fortran 77' 'Fortran 90' Java ksh Pascal Perl Python sh Tcl Other save_ save__software.location _item_description.description ; The URL for an Internet address at which details of the software can be found. ; _item.name '_software.location' _item.category_id software _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'http://rosebud.sdsc.edu/projects/pb/IUCr/software.html' 'ftp://ftp.sdsc.edu/pub/sdsc/biology/' save_ save__software.mods _item_description.description ; Any noteworthy modifications to the base software, if applicable. ; _item.name '_software.mods' _item.category_id software _item.mandatory_code no _item_type.code line _item_examples.case 'Added support for space group F432' save_ save__software.name _item_description.description ; The name of the software. ; _item.name '_software.name' _item.category_id software _item.mandatory_code yes _item_type.code text loop_ _item_examples.case 'Merlot' 'O' 'Xengen' 'X-plor' save_ save__software.os _item_description.description ; The name of the operating system under which the software runs. ; _item.name '_software.os' _item.category_id software _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'Ultrix' 'OpenVMS' 'DOS' 'Windows 95' 'Windows NT' 'Irix' 'HPUX' 'DEC Unix' save_ save__software.os_version _item_description.description ; The version of the operating system under which the software runs. ; _item.name '_software.os_version' _item.category_id software _item.mandatory_code no _item_type.code text loop_ _item_examples.case '3.1' '4.2.1' save_ save__software.type _item_description.description ; The classification of the software according to the most common types. ; _item.name '_software.type' _item.category_id software _item.mandatory_code no _item_type.code uline loop_ _item_enumeration.value _item_enumeration.detail program ; individual program with limited functionality ; library ; used by a program at load time ; package ; collections of programs with multiple functionality ; filter ; filters input and output streams ; jiffy ; short, simple program ; other ; all other kinds of software ; save_ save__software.version _item_description.description ; The version of the software. ; _item.name '_software.version' _item.category_id software _item.mandatory_code yes _item_type.code line loop_ _item_examples.case 'v1.0' 'beta' '3.1-2' 'unknown' save_ ############ ## STRUCT ## ############ save_struct _category.description ; Data items in the STRUCT category record details about the description of the crystallographic structure. ; _category.id struct _category.mandatory_code no _category_key.name '_struct.entry_id' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _struct.entry_id '5HVP' _struct.title ; HIV-1 protease complex with acetyl-pepstatin ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_struct.entry_id' _item.mandatory_code yes save_ save__struct.title _item_description.description ; A title for the data block. The author should attempt to convey the essence of the structure archived in the CIF in the title, and to distinguish this structural result from others. ; _item.name '_struct.title' _item.category_id struct _item.mandatory_code no _item_type.code text loop_ _item_examples.case '5'-D(*(I)CP*CP*GP*G)-3' 'T4 lysozyme mutant - S32A' 'hen egg white lysozyme at -30 degrees C' 'quail egg white lysozyme at 2 atmospheres' save_ ################# ## STRUCT_ASYM ## ################# save_struct_asym _category.description ; Data items in the STRUCT_ASYM category record details about the structural elements in the asymmetric unit. ; _category.id struct_asym _category.mandatory_code no _category_key.name '_struct_asym.id' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _struct_asym.id _struct_asym.entity_id _struct_asym.details A 1 'one monomer of the dimeric enzyme' B 1 'one monomer of the dimeric enzyme' C 2 'one partially occupied position for the inhibitor' D 2 'one partially occupied position for the inhibitor' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_asym.details _item_description.description ; A description of special aspects of this portion of the contents of the asymmetric unit. ; _item.name '_struct_asym.details' _item.category_id struct_asym _item.mandatory_code no _item_type.code text _item_examples.case ; The drug binds to this enzyme in two roughly twofold symmetric modes. Hence this biological unit (3) is roughly twofold symmetric to biological unit (2). Disorder in the protein chain indicated with alternative ID 2 should be used with this biological unit. ; save_ save__struct_asym.entity_id _item_description.description ; This data item is a pointer to _entity.id in the ENTITY category. ; _item.name '_struct_asym.entity_id' _item.mandatory_code yes save_ save__struct_asym.id _item_description.description ; The value of _struct_asym.id must uniquely identify a record in the STRUCT_ASYM list. Note that this item need not be a number; it can be any unique identifier. ; loop_ _item.name _item.category_id _item.mandatory_code '_struct_asym.id' struct_asym yes '_atom_site.label_asym_id' atom_site no '_geom_angle.atom_site_label_asym_id_1' geom_angle no '_geom_angle.atom_site_label_asym_id_2' geom_angle no '_geom_angle.atom_site_label_asym_id_3' geom_angle no '_geom_bond.atom_site_label_asym_id_1' geom_bond no '_geom_bond.atom_site_label_asym_id_2' geom_bond no '_geom_contact.atom_site_label_asym_id_1' geom_contact no '_geom_contact.atom_site_label_asym_id_2' geom_contact no '_geom_hbond.atom_site_label_asym_id_A' geom_hbond no '_geom_hbond.atom_site_label_asym_id_D' geom_hbond no '_geom_hbond.atom_site_label_asym_id_H' geom_hbond no '_geom_torsion.atom_site_label_asym_id_1' geom_torsion no '_geom_torsion.atom_site_label_asym_id_2' geom_torsion no '_geom_torsion.atom_site_label_asym_id_3' geom_torsion no '_geom_torsion.atom_site_label_asym_id_4' geom_torsion no '_struct_biol_gen.asym_id' struct_biol_gen yes '_struct_conf.beg_label_asym_id' struct_conf yes '_struct_conf.end_label_asym_id' struct_conf yes '_struct_conn.ptnr1_label_asym_id' struct_conn yes '_struct_conn.ptnr2_label_asym_id' struct_conn yes '_struct_mon_nucl.label_asym_id' struct_mon_nucl yes '_struct_mon_prot.label_asym_id' struct_mon_prot yes '_struct_mon_prot_cis.label_asym_id' struct_mon_prot_cis yes '_struct_ncs_dom_lim.beg_label_asym_id' struct_ncs_dom_lim yes '_struct_ncs_dom_lim.end_label_asym_id' struct_ncs_dom_lim yes '_struct_sheet_range.beg_label_asym_id' struct_sheet_range yes '_struct_sheet_range.end_label_asym_id' struct_sheet_range yes '_struct_site_gen.label_asym_id' struct_site_gen yes loop_ _item_linked.child_name _item_linked.parent_name '_atom_site.label_asym_id' '_struct_asym.id' '_struct_biol_gen.asym_id' '_struct_asym.id' '_geom_angle.atom_site_label_asym_id_1' '_atom_site.label_asym_id' '_geom_angle.atom_site_label_asym_id_2' '_atom_site.label_asym_id' '_geom_angle.atom_site_label_asym_id_3' '_atom_site.label_asym_id' '_geom_bond.atom_site_label_asym_id_1' '_atom_site.label_asym_id' '_geom_bond.atom_site_label_asym_id_2' '_atom_site.label_asym_id' '_geom_contact.atom_site_label_asym_id_1' '_atom_site.label_asym_id' '_geom_contact.atom_site_label_asym_id_2' '_atom_site.label_asym_id' '_geom_hbond.atom_site_label_asym_id_A' '_atom_site.label_asym_id' '_geom_hbond.atom_site_label_asym_id_D' '_atom_site.label_asym_id' '_geom_hbond.atom_site_label_asym_id_H' '_atom_site.label_asym_id' '_geom_torsion.atom_site_label_asym_id_1' '_atom_site.label_asym_id' '_geom_torsion.atom_site_label_asym_id_2' '_atom_site.label_asym_id' '_geom_torsion.atom_site_label_asym_id_3' '_atom_site.label_asym_id' '_geom_torsion.atom_site_label_asym_id_4' '_atom_site.label_asym_id' '_struct_conf.beg_label_asym_id' '_atom_site.label_asym_id' '_struct_conf.end_label_asym_id' '_atom_site.label_asym_id' '_struct_conn.ptnr1_label_asym_id' '_atom_site.label_asym_id' '_struct_conn.ptnr2_label_asym_id' '_atom_site.label_asym_id' '_struct_mon_nucl.label_asym_id' '_atom_site.label_asym_id' '_struct_mon_prot.label_asym_id' '_atom_site.label_asym_id' '_struct_mon_prot_cis.label_asym_id' '_atom_site.label_asym_id' '_struct_ncs_dom_lim.beg_label_asym_id' '_atom_site.label_asym_id' '_struct_ncs_dom_lim.end_label_asym_id' '_atom_site.label_asym_id' '_struct_sheet_range.beg_label_asym_id' '_atom_site.label_asym_id' '_struct_sheet_range.end_label_asym_id' '_atom_site.label_asym_id' '_struct_site_gen.label_asym_id' '_atom_site.label_asym_id' _item_type.code code loop_ _item_examples.case '1' 'A' '2B3' save_ ################# ## STRUCT_BIOL ## ################# save_struct_biol _category.description ; Data items in the STRUCT_BIOL category record details about the structural elements that form each structure of biological significance. A given crystal structure may contain many different biological structures. A given structural component in the asymmetric unit may be part of more than one biological unit. A given biological structure may involve crystallographic symmetry. For instance, in a structure of a lysozyme-FAB structure, the light- and heavy-chain components of the FAB could be one biological unit, while the two chains of the FAB and the lysozyme could constitute a second biological unit. ; _category.id struct_biol _category.mandatory_code no _category_key.name '_struct_biol.id' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _struct_biol.id _struct_biol.details 1 ; significant deviations from twofold symmetry exist in this dimeric enzyme ; 2 ; The drug binds to this enzyme in two roughly twofold symmetric modes. Hence this biological unit (2) is roughly twofold symmetric to biological unit (3). Disorder in the protein chain indicated with alternative ID 1 should be used with this biological unit. ; 3 ; The drug binds to this enzyme in two roughly twofold symmetric modes. Hence this biological unit (3) is roughly twofold symmetric to biological unit (2). Disorder in the protein chain indicated with alternative ID 2 should be used with this biological unit. ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_biol.details _item_description.description ; A description of special aspects of the biological unit. ; _item.name '_struct_biol.details' _item.category_id struct_biol _item.mandatory_code no _item_type.code text _item_examples.case ; The drug binds to this enzyme in two roughly twofold symmetric modes. Hence this biological unit (3) is roughly twofold symmetric to biological unit (2). Disorder in the protein chain indicated with alternative ID 2 should be used with this biological unit. ; save_ save__struct_biol.id _item_description.description ; The value of _struct_biol.id must uniquely identify a record in the STRUCT_BIOL list. Note that this item need not be a number; it can be any unique identifier. ; loop_ _item.name _item.category_id _item.mandatory_code '_struct_biol.id' struct_biol yes '_struct_biol_gen.biol_id' struct_biol_gen yes '_struct_biol_keywords.biol_id' struct_biol_keywords yes '_struct_biol_view.biol_id' struct_biol_view yes '_struct_ref.biol_id' struct_ref no loop_ _item_linked.child_name _item_linked.parent_name '_struct_biol_gen.biol_id' '_struct_biol.id' '_struct_biol_keywords.biol_id' '_struct_biol.id' '_struct_biol_view.biol_id' '_struct_biol.id' '_struct_ref.biol_id' '_struct_biol.id' _item_type.code line save_ ##################### ## STRUCT_BIOL_GEN ## ##################### save_struct_biol_gen _category.description ; Data items in the STRUCT_BIOL_GEN category record details about the generation of each biological unit. The STRUCT_BIOL_GEN data items provide the specifications of the components that constitute that biological unit, which may include symmetry elements. ; _category.id struct_biol_gen _category.mandatory_code no loop_ _category_key.name '_struct_biol_gen.biol_id' '_struct_biol_gen.asym_id' '_struct_biol_gen.symmetry' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _struct_biol_gen.biol_id _struct_biol_gen.asym_id _struct_biol_gen.symmetry 1 A 1_555 1 B 1_555 2 A 1_555 2 B 1_555 2 C 1_555 3 A 1_555 3 B 1_555 3 D 1_555 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_biol_gen.asym_id _item_description.description ; This data item is a pointer to _struct_asym.id in the STRUCT_ASYM category. ; _item.name '_struct_biol_gen.asym_id' _item.mandatory_code yes save_ save__struct_biol_gen.biol_id _item_description.description ; This data item is a pointer to _struct_biol.id in the STRUCT_BIOL category. ; _item.name '_struct_biol_gen.biol_id' _item.mandatory_code yes save_ save__struct_biol_gen.details _item_description.description ; A description of special aspects of the symmetry generation of this portion of the biological structure. ; _item.name '_struct_biol_gen.details' _item.category_id struct_biol_gen _item.mandatory_code no _item_type.code text _item_examples.case ; The zinc atom lies on a special position; application of symmetry elements to generate the insulin hexamer will generate excess zinc atoms, which must be removed by hand. ; save_ save__struct_biol_gen.symmetry _item_description.description ; Describes the symmetry operation that should be applied to the atom set specified by _struct_biol_gen.asym_id to generate a portion of the biological structure. ; _item.name '_struct_biol_gen.symmetry' _item.category_id struct_biol_gen _item.mandatory_code yes # _item_default.value 1_555 _item_type.code symop loop_ _item_examples.case _item_examples.detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' save_ ########################## ## STRUCT_BIOL_KEYWORDS ## ########################## save_struct_biol_keywords _category.description ; Data items in the STRUCT_BIOL_KEYWORDS category record keywords that describe each biological unit. ; _category.id struct_biol_keywords _category.mandatory_code no loop_ _category_key.name '_struct_biol_keywords.biol_id' '_struct_biol_keywords.text' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _struct_biol_keywords.biol_id _struct_biol_keywords.text 1 'aspartyl-protease' 1 'aspartic-protease' 1 'acid-protease' 1 'aspartyl-proteinase' 1 'aspartic-proteinase' 1 'acid-proteinase' 1 'enzyme' 1 'protease' 1 'proteinase' 1 'dimer' 2 'drug-enzyme complex' 2 'inhibitor-enzyme complex' 2 'drug-protease complex' 2 'inhibitor-protease complex' 3 'drug-enzyme complex' 3 'inhibitor-enzyme complex' 3 'drug-protease complex' 3 'inhibitor-protease complex' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_biol_keywords.biol_id _item_description.description ; This data item is a pointer to _struct_biol.id in the STRUCT_BIOL category. ; _item.name '_struct_biol_keywords.biol_id' _item.mandatory_code yes save_ save__struct_biol_keywords.text _item_description.description ; Keywords describing this biological entity. ; _item.name '_struct_biol_keywords.text' _item.category_id struct_biol_keywords _item.mandatory_code yes _item_type.code text loop_ _item_examples.case 'antibody' 'antigen' 'enzyme' 'cytokine' 'tRNA' save_ ###################### ## STRUCT_BIOL_VIEW ## ###################### save_struct_biol_view _category.description ; Data items in the STRUCT_BIOL_VIEW category record details about how to draw and annotate an informative view of the biological structure. ; _category.id struct_biol_view _category.mandatory_code no loop_ _category_key.name '_struct_biol_view.biol_id' '_struct_biol_view.id' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on NDB structure GDL001 by Coll, Aymami, Van Der Marel, Van Boom, Rich & Wang [Biochemistry, (1989), 28, 310-320]. ; ; _struct_biol_view.biol_id c1 _struct_biol_view.id 1 _struct_biol_view.rot_matrix[1][1] 0.132 _struct_biol_view.rot_matrix[1][2] 0.922 _struct_biol_view.rot_matrix[1][3] -0.363 _struct_biol_view.rot_matrix[2][1] 0.131 _struct_biol_view.rot_matrix[2][2] -0.380 _struct_biol_view.rot_matrix[2][3] -0.916 _struct_biol_view.rot_matrix[3][1] -0.982 _struct_biol_view.rot_matrix[3][2] 0.073 _struct_biol_view.rot_matrix[3][3] -0.172 _struct_biol_view.details ; This view highlights the ATAT-Netropsin interaction in the DNA-drug complex. ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_biol_view.biol_id _item_description.description ; This data item is a pointer to _struct_biol.id in the STRUCT_BIOL category. ; _item.name '_struct_biol_view.biol_id' _item.mandatory_code yes save_ save__struct_biol_view.details _item_description.description ; A description of special aspects of this view of the biological structure. This data item can be used as a figure legend. ; _item.name '_struct_biol_view.details' _item.category_id struct_biol_view _item.mandatory_code no _item_type.code text _item_examples.case ; The enzyme has been oriented with the molecular twofold axis aligned with the horizontal axis of the figure. ; save_ save__struct_biol_view.id _item_description.description ; The value of _struct_biol_view.id must uniquely identify a record in the STRUCT_BIOL_VIEW list. Note that this item need not be a number; it can be any unique identifier. ; _item.name '_struct_biol_view.id' _item.category_id struct_biol_view _item.mandatory_code yes _item_type.code line loop_ _item_examples.case 'Figure 1' 'unliganded enzyme' 'view down enzyme active site' save_ save__struct_biol_view.rot_matrix[1][1] _item_description.description ; The [1][1] element of the matrix used to rotate the subset of the Cartesian coordinates in the ATOM_SITE category identified in the STRUCT_BIOL_GEN category to give a view useful for describing the structure. The conventions used in the rotation are described in _struct_biol_view.details. |x'| |11 12 13| |x| |y'|~reoriented Cartesian~ = |21 22 23| |y|~Cartesian~ |z'| |31 32 33| |z| ; _item.name '_struct_biol_view.rot_matrix[1][1]' _item.category_id struct_biol_view _item.mandatory_code no _item_sub_category.id matrix _item_type.code float save_ save__struct_biol_view.rot_matrix[1][2] _item_description.description ; The [1][2] element of the matrix used to rotate the subset of the Cartesian coordinates in the ATOM_SITE category identified in the STRUCT_BIOL_GEN category to give a view useful for describing the structure. The conventions used in the rotation are described in _struct_biol_view.details. |x'| |11 12 13| |x| |y'|~reoriented Cartesian~ = |21 22 23| |y|~Cartesian~ |z'| |31 32 33| |z| ; _item.name '_struct_biol_view.rot_matrix[1][2]' _item.category_id struct_biol_view _item.mandatory_code no _item_sub_category.id matrix _item_type.code float save_ save__struct_biol_view.rot_matrix[1][3] _item_description.description ; The [1][3] element of the matrix used to rotate the subset of the Cartesian coordinates in the ATOM_SITE category identified in the STRUCT_BIOL_GEN category to give a view useful for describing the structure. The conventions used in the rotation are described in _struct_biol_view.details. |x'| |11 12 13| |x| |y'|~reoriented Cartesian~ = |21 22 23| |y|~Cartesian~ |z'| |31 32 33| |z| ; _item.name '_struct_biol_view.rot_matrix[1][3]' _item.category_id struct_biol_view _item.mandatory_code no _item_sub_category.id matrix _item_type.code float save_ save__struct_biol_view.rot_matrix[2][1] _item_description.description ; The [2][1] element of the matrix used to rotate the subset of the Cartesian coordinates in the ATOM_SITE category identified in the STRUCT_BIOL_GEN category to give a view useful for describing the structure. The conventions used in the rotation are described in _struct_biol_view.details. |x'| |11 12 13| |x| |y'|~reoriented Cartesian~ = |21 22 23| |y|~Cartesian~ |z'| |31 32 33| |z| ; _item.name '_struct_biol_view.rot_matrix[2][1]' _item.category_id struct_biol_view _item.mandatory_code no _item_sub_category.id matrix _item_type.code float save_ save__struct_biol_view.rot_matrix[2][2] _item_description.description ; The [2][2] element of the matrix used to rotate the subset of the Cartesian coordinates in the ATOM_SITE category identified in the STRUCT_BIOL_GEN category to give a view useful for describing the structure. The conventions used in the rotation are described in _struct_biol_view.details. |x'| |11 12 13| |x| |y'|~reoriented Cartesian~ = |21 22 23| |y|~Cartesian~ |z'| |31 32 33| |z| ; _item.name '_struct_biol_view.rot_matrix[2][2]' _item.category_id struct_biol_view _item.mandatory_code no _item_sub_category.id matrix _item_type.code float save_ save__struct_biol_view.rot_matrix[2][3] _item_description.description ; The [2][3] element of the matrix used to rotate the subset of the Cartesian coordinates in the ATOM_SITE category identified in the STRUCT_BIOL_GEN category to give a view useful for describing the structure. The conventions used in the rotation are described in _struct_biol_view.details. |x'| |11 12 13| |x| |y'|~reoriented Cartesian~ = |21 22 23| |y|~Cartesian~ |z'| |31 32 33| |z| ; _item.name '_struct_biol_view.rot_matrix[2][3]' _item.category_id struct_biol_view _item.mandatory_code no _item_sub_category.id matrix _item_type.code float save_ save__struct_biol_view.rot_matrix[3][1] _item_description.description ; The [3][1] element of the matrix used to rotate the subset of the Cartesian coordinates in the ATOM_SITE category identified in the STRUCT_BIOL_GEN category to give a view useful for describing the structure. The conventions used in the rotation are described in _struct_biol_view.details. |x'| |11 12 13| |x| |y'|~reoriented Cartesian~ = |21 22 23| |y|~Cartesian~ |z'| |31 32 33| |z| ; _item.name '_struct_biol_view.rot_matrix[3][1]' _item.category_id struct_biol_view _item.mandatory_code no _item_sub_category.id matrix _item_type.code float save_ save__struct_biol_view.rot_matrix[3][2] _item_description.description ; The [3][2] element of the matrix used to rotate the subset of the Cartesian coordinates in the ATOM_SITE category identified in the STRUCT_BIOL_GEN category to give a view useful for describing the structure. The conventions used in the rotation are described in _struct_biol_view.details. |x'| |11 12 13| |x| |y'|~reoriented Cartesian~ = |21 22 23| |y|~Cartesian~ |z'| |31 32 33| |z| ; _item.name '_struct_biol_view.rot_matrix[3][2]' _item.category_id struct_biol_view _item.mandatory_code no _item_sub_category.id matrix _item_type.code float save_ save__struct_biol_view.rot_matrix[3][3] _item_description.description ; The [3][3] element of the matrix used to rotate the subset of the Cartesian coordinates in the ATOM_SITE category identified in the STRUCT_BIOL_GEN category to give a view useful for describing the structure. The conventions used in the rotation are described in _struct_biol_view.details. |x'| |11 12 13| |x| |y'|~reoriented Cartesian~ = |21 22 23| |y|~Cartesian~ |z'| |31 32 33| |z| ; _item.name '_struct_biol_view.rot_matrix[3][3]' _item.category_id struct_biol_view _item.mandatory_code no _item_sub_category.id matrix _item_type.code float save_ ################# ## STRUCT_CONF ## ################# save_struct_conf _category.description ; Data items in the STRUCT_CONF category record details about the backbone conformation of a segment of polymer. Data items in the STRUCT_CONF_TYPE category define the criteria used to identify the backbone conformations. ; _category.id struct_conf _category.mandatory_code no _category_key.name '_struct_conf.id' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _struct_conf.id _struct_conf.conf_type_id _struct_conf.beg_label_comp_id _struct_conf.beg_label_asym_id _struct_conf.beg_label_seq_id _struct_conf.end_label_comp_id _struct_conf.end_label_asym_id _struct_conf.end_label_seq_id _struct_conf.details HELX1 HELX_RH_AL_P ARG A 87 GLN A 92 . HELX2 HELX_RH_AL_P ARG B 287 GLN B 292 . STRN1 STRN_P PRO A 1 LEU A 5 . STRN2 STRN_P CYS B 295 PHE B 299 . STRN3 STRN_P CYS A 95 PHE A 299 . STRN4 STRN_P PRO B 201 LEU B 205 . # - - - - data truncated for brevity - - - - TURN1 TURN_TY1P_P ILE A 15 GLN A 18 . TURN2 TURN_TY2_P GLY A 49 GLY A 52 . TURN3 TURN_TY1P_P ILE A 55 HIS A 69 . TURN4 TURN_TY1_P THR A 91 GLY A 94 . # - - - - data truncated for brevity - - - - ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_conf.beg_label_asym_id _item_description.description ; A component of the identifier for the residue at which the conformation segment begins. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_struct_conf.beg_label_asym_id' _item.mandatory_code yes save_ save__struct_conf.beg_label_comp_id _item_description.description ; A component of the identifier for the residue at which the conformation segment begins. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_struct_conf.beg_label_comp_id' _item.mandatory_code yes save_ save__struct_conf.beg_label_seq_id _item_description.description ; A component of the identifier for the residue at which the conformation segment begins. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_struct_conf.beg_label_seq_id' _item.mandatory_code yes save_ save__struct_conf.beg_auth_asym_id _item_description.description ; A component of the identifier for the residue at which the conformation segment begins. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_struct_conf.beg_auth_asym_id' _item.mandatory_code no save_ save__struct_conf.beg_auth_comp_id _item_description.description ; A component of the identifier for the residue at which the conformation segment begins. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_struct_conf.beg_auth_comp_id' _item.mandatory_code no save_ save__struct_conf.beg_auth_seq_id _item_description.description ; A component of the identifier for the residue at which the conformation segment begins. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_struct_conf.beg_auth_seq_id' _item.mandatory_code no save_ save__struct_conf.conf_type_id _item_description.description ; This data item is a pointer to _struct_conf_type.id in the STRUCT_CONF_TYPE category. ; _item.name '_struct_conf.conf_type_id' _item.mandatory_code yes save_ save__struct_conf.details _item_description.description ; A description of special aspects of the conformation assignment. ; _item.name '_struct_conf.details' _item.category_id struct_conf _item.mandatory_code no _item_type.code text save_ save__struct_conf.end_label_asym_id _item_description.description ; A component of the identifier for the residue at which the conformation segment ends. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_struct_conf.end_label_asym_id' _item.mandatory_code yes save_ save__struct_conf.end_label_comp_id _item_description.description ; A component of the identifier for the residue at which the conformation segment ends. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_struct_conf.end_label_comp_id' _item.mandatory_code yes save_ save__struct_conf.end_label_seq_id _item_description.description ; A component of the identifier for the residue at which the conformation segment ends. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_struct_conf.end_label_seq_id' _item.mandatory_code yes save_ save__struct_conf.end_auth_asym_id _item_description.description ; A component of the identifier for the residue at which the conformation segment ends. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_struct_conf.end_auth_asym_id' _item.mandatory_code no save_ save__struct_conf.end_auth_comp_id _item_description.description ; A component of the identifier for the residue at which the conformation segment ends. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_struct_conf.end_auth_comp_id' _item.mandatory_code no save_ save__struct_conf.end_auth_seq_id _item_description.description ; A component of the identifier for the residue at which the conformation segment ends. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_struct_conf.end_auth_seq_id' _item.mandatory_code no save_ save__struct_conf.id _item_description.description ; The value of _struct_conf.id must uniquely identify a record in the STRUCT_CONF list. Note that this item need not be a number; it can be any unique identifier. ; _item.name '_struct_conf.id' _item.category_id struct_conf _item.mandatory_code yes _item_type.code code save_ ###################### ## STRUCT_CONF_TYPE ## ###################### save_struct_conf_type _category.description ; Data items in the STRUCT_CONF_TYPE category record details about the criteria used to identify backbone conformations of a segment of polymer. ; _category.id struct_conf_type _category.mandatory_code no _category_key.name '_struct_conf_type.id' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _struct_conf_type.id _struct_conf_type.criteria _struct_conf_type.reference HELX_RH_AL_P 'author judgement' . STRN_P 'author judgement' . TURN_TY1_P 'author judgement' . TURN_TY1P_P 'author judgement' . TURN_TY2_P 'author judgement' . TURN_TY2P_P 'author judgement' . ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_conf_type.criteria _item_description.description ; The criteria used to assign this conformation type. ; _item.name '_struct_conf_type.criteria' _item.category_id struct_conf_type _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'author judgement' 'phi=54-74, psi=30-50' save_ save__struct_conf_type.id _item_description.description ; The descriptor that categorizes the type of the conformation of the backbone of the polymer (whether protein or nucleic acid). Explicit values for the torsion angles that define each conformation are not given here, but it is expected that the author would provide such information in either the _struct_conf_type.criteria or _struct_conf_type.reference data items, or both. ; loop_ _item.name _item.category_id _item.mandatory_code '_struct_conf_type.id' struct_conf_type yes '_struct_conf.conf_type_id' struct_conf yes loop_ _item_linked.child_name _item_linked.parent_name '_struct_conf.conf_type_id' '_struct_conf_type.id' _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail HELX_P ; helix with handedness and type not specified (protein) ; HELX_OT_P ; helix with handedness and type that do not conform to an accepted category (protein) ; # HELX_RH_P ; right-handed helix with type not specified (protein) ; HELX_RH_OT_P ; right-handed helix with type that does not conform to an accepted category (protein) ; HELX_RH_AL_P 'right-handed alpha helix (protein)' HELX_RH_GA_P 'right-handed gamma helix (protein)' HELX_RH_OM_P 'right-handed omega helix (protein)' HELX_RH_PI_P 'right-handed pi helix (protein)' HELX_RH_27_P 'right-handed 2-7 helix (protein)' HELX_RH_3T_P 'right-handed 3-10 helix (protein)' HELX_RH_PP_P 'right-handed polyproline helix (protein)' # HELX_LH_P ; left-handed helix with type not specified (protein) ; HELX_LH_OT_P ; left-handed helix with type that does not conform to an accepted category (protein) ; HELX_LH_AL_P 'left-handed alpha helix (protein)' HELX_LH_GA_P 'left-handed gamma helix (protein)' HELX_LH_OM_P 'left-handed omega helix (protein)' HELX_LH_PI_P 'left-handed pi helix (protein)' HELX_LH_27_P 'left-handed 2-7 helix (protein)' HELX_LH_3T_P 'left-handed 3-10 helix (protein)' HELX_LH_PP_P 'left-handed polyproline helix (protein)' # HELX_N ; helix with handedness and type not specified (nucleic acid) ; HELX_OT_N ; helix with handedness and type that do not conform to an accepted category (nucleic acid) ; # HELX_RH_N ; right-handed helix with type not specified (nucleic acid) ; HELX_RH_OT_N ; right-handed helix with type that does not conform to an accepted category (nucleic acid) ; HELX_RH_A_N 'right-handed A helix (nucleic acid)' HELX_RH_B_N 'right-handed B helix (nucleic acid)' HELX_RH_Z_N 'right-handed Z helix (nucleic acid)' # HELX_LH_N ; left-handed helix with type not specified (nucleic acid) ; HELX_LH_OT_N ; left-handed helix with type that does not conform to an accepted category (nucleic acid) ; HELX_LH_A_N 'left-handed A helix (nucleic acid)' HELX_LH_B_N 'left-handed B helix (nucleic acid)' HELX_LH_Z_N 'left-handed Z helix (nucleic acid)' # TURN_P 'turn with type not specified (protein)' TURN_OT_P ; turn with type that does not conform to an accepted category (protein) ; TURN_TY1_P 'type I turn (protein)' TURN_TY1P_P 'type I prime turn (protein)' TURN_TY2_P 'type II turn (protein)' TURN_TY2P_P 'type II prime turn (protein)' TURN_TY3_P 'type III turn (protein)' TURN_TY3P_P 'type III prime turn (protein)' # STRN 'beta strand (protein)' save_ save__struct_conf_type.reference _item_description.description ; A literature reference that defines the criteria used to assign this conformation type and subtype. ; _item.name '_struct_conf_type.reference' _item.category_id struct_conf_type _item.mandatory_code no _item_type.code text save_ ################# ## STRUCT_CONN ## ################# save_struct_conn _category.description ; Data items in the STRUCT_CONN category record details about the connections between portions of the structure. These can be hydrogen bonds, salt bridges, disulfide bridges and so on. The STRUCT_CONN_TYPE records define the criteria used to identify these connections. ; _category.id struct_conn _category.mandatory_code no _category_key.name '_struct_conn.id' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _struct_conn.id _struct_conn.conn_type_id _struct_conn.ptnr1_label_comp_id _struct_conn.ptnr1_label_asym_id _struct_conn.ptnr1_label_seq_id _struct_conn.ptnr1_label_atom_id _struct_conn.ptnr1_role _struct_conn.ptnr1_symmetry _struct_conn.ptnr2_label_comp_id _struct_conn.ptnr2_label_asym_id _struct_conn.ptnr2_label_seq_id _struct_conn.ptnr2_label_atom_id _struct_conn.ptnr2_role _struct_conn.ptnr2_symmetry _struct_conn.details C1 saltbr ARG A 87 NZ1 positive 1_555 GLU A 92 OE1 negative 1_555 . C2 hydrog ARG B 287 N donor 1_555 GLY B 292 O acceptor 1_555 . # - - - - data truncated for brevity - - - - ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_conn.conn_type_id _item_description.description ; This data item is a pointer to _struct_conn_type.id in the STRUCT_CONN_TYPE category. ; _item.name '_struct_conn.conn_type_id' _item.mandatory_code yes save_ save__struct_conn.details _item_description.description ; A description of special aspects of the connection. ; _item.name '_struct_conn.details' _item.category_id struct_conn _item.mandatory_code no _item_type.code text _item_examples.case 'disulfide bridge C-S-S-C is highly distorted' save_ save__struct_conn.id _item_description.description ; The value of _struct_conn.id must uniquely identify a record in the STRUCT_CONN list. Note that this item need not be a number; it can be any unique identifier. ; _item.name '_struct_conn.id' _item.category_id struct_conn _item.mandatory_code yes _item_type.code code save_ save__struct_conn.ptnr1_label_alt_id _item_description.description ; A component of the identifier for partner 1 of the structure connection. This data item is a pointer to _atom_sites_alt.id in the ATOM_SITES_ALT category. ; _item.name '_struct_conn.ptnr1_label_alt_id' _item.mandatory_code no save_ save__struct_conn.ptnr1_label_asym_id _item_description.description ; A component of the identifier for partner 1 of the structure connection. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_struct_conn.ptnr1_label_asym_id' _item.mandatory_code yes save_ save__struct_conn.ptnr1_label_atom_id _item_description.description ; A component of the identifier for partner 1 of the structure connection. This data item is a pointer to _chem_comp_atom.atom_id in the CHEM_COMP_ATOM category. ; _item.name '_struct_conn.ptnr1_label_atom_id' _item.mandatory_code yes save_ save__struct_conn.ptnr1_label_comp_id _item_description.description ; A component of the identifier for partner 1 of the structure connection. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_struct_conn.ptnr1_label_comp_id' _item.mandatory_code yes save_ save__struct_conn.ptnr1_label_seq_id _item_description.description ; A component of the identifier for partner 1 of the structure connection. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_struct_conn.ptnr1_label_seq_id' _item.mandatory_code yes save_ save__struct_conn.ptnr1_auth_asym_id _item_description.description ; A component of the identifier for partner 1 of the structure connection. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_struct_conn.ptnr1_auth_asym_id' _item.mandatory_code no save_ save__struct_conn.ptnr1_auth_atom_id _item_description.description ; A component of the identifier for partner 1 of the structure connection. This data item is a pointer to _atom_site.auth_atom_id in the ATOM_SITE category. ; _item.name '_struct_conn.ptnr1_auth_atom_id' _item.mandatory_code no save_ save__struct_conn.ptnr1_auth_comp_id _item_description.description ; A component of the identifier for partner 1 of the structure connection. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_struct_conn.ptnr1_auth_comp_id' _item.mandatory_code no save_ save__struct_conn.ptnr1_auth_seq_id _item_description.description ; A component of the identifier for partner 1 of the structure connection. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_struct_conn.ptnr1_auth_seq_id' _item.mandatory_code no save_ save__struct_conn.ptnr1_role _item_description.description ; The chemical or structural role of the first partner in the structure connection. ; _item.name '_struct_conn.ptnr1_role' _item.category_id struct_conn _item.mandatory_code no _item_type.code uline loop_ _item_examples.case 'donor' 'acceptor' 'negative' 'positive' 'metal' 'metal coordination' save_ save__struct_conn.ptnr1_symmetry _item_description.description ; Describes the symmetry operation that should be applied to the atom set specified by _struct_conn.ptnr1_label* to generate the first partner in the structure connection. ; _item.name '_struct_conn.ptnr1_symmetry' _item.category_id struct_conn _item.mandatory_code no # _item_default.value 1_555 _item_type.code symop loop_ _item_examples.case _item_examples.detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' save_ save__struct_conn.ptnr2_label_alt_id _item_description.description ; A component of the identifier for partner 2 of the structure connection. This data item is a pointer to _atom_sites_alt.id in the ATOM_SITES_ALT category. ; _item.name '_struct_conn.ptnr2_label_alt_id' _item.mandatory_code no save_ save__struct_conn.ptnr2_label_asym_id _item_description.description ; A component of the identifier for partner 2 of the structure connection. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_struct_conn.ptnr2_label_asym_id' _item.mandatory_code yes save_ save__struct_conn.ptnr2_label_atom_id _item_description.description ; A component of the identifier for partner 2 of the structure connection. This data item is a pointer to _chem_comp_atom.atom_id in the CHEM_COMP_ATOM category. ; _item.name '_struct_conn.ptnr2_label_atom_id' _item.mandatory_code yes save_ save__struct_conn.ptnr2_label_comp_id _item_description.description ; A component of the identifier for partner 2 of the structure connection. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_struct_conn.ptnr2_label_comp_id' _item.mandatory_code yes save_ save__struct_conn.ptnr2_label_seq_id _item_description.description ; A component of the identifier for partner 2 of the structure connection. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_struct_conn.ptnr2_label_seq_id' _item.mandatory_code yes save_ save__struct_conn.ptnr2_auth_asym_id _item_description.description ; A component of the identifier for partner 2 of the structure connection. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_struct_conn.ptnr2_auth_asym_id' _item.mandatory_code no save_ save__struct_conn.ptnr2_auth_atom_id _item_description.description ; A component of the identifier for partner 2 of the structure connection. This data item is a pointer to _atom_site.auth_atom_id in the ATOM_SITE category. ; _item.name '_struct_conn.ptnr2_auth_atom_id' _item.mandatory_code no save_ save__struct_conn.ptnr2_auth_comp_id _item_description.description ; A component of the identifier for partner 2 of the structure connection. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_struct_conn.ptnr2_auth_comp_id' _item.mandatory_code no save_ save__struct_conn.ptnr2_auth_seq_id _item_description.description ; A component of the identifier for partner 2 of the structure connection. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_struct_conn.ptnr2_auth_seq_id' _item.mandatory_code no save_ save__struct_conn.ptnr2_role _item_description.description ; The chemical or structural role of the second partner in the structure connection. ; _item.name '_struct_conn.ptnr2_role' _item.category_id struct_conn _item.mandatory_code no _item_type.code uline loop_ _item_examples.case 'donor' 'acceptor' 'negative' 'positive' 'metal' 'metal coordination' save_ save__struct_conn.ptnr2_symmetry _item_description.description ; Describes the symmetry operation that should be applied to the atom set specified by _struct_conn.ptnr2_label* to generate the second partner in the structure connection. ; _item.name '_struct_conn.ptnr2_symmetry' _item.category_id struct_conn _item.mandatory_code no # _item_default.value 1_555 _item_type.code symop loop_ _item_examples.case _item_examples.detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' save_ ###################### ## STRUCT_CONN_TYPE ## ###################### save_struct_conn_type _category.description ; Data items in the STRUCT_CONN_TYPE category record details about the criteria used to identify interactions between portions of the structure. ; _category.id struct_conn_type _category.mandatory_code no _category_key.name '_struct_conn_type.id' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _struct_conn_type.id _struct_conn_type.criteria _struct_conn_type.reference saltbr 'negative to positive distance > 2.5 \%A, < 3.2 \%A' . hydrog 'NO distance > 2.5\%A, < 3.5\%A, NOC angle < 120 degrees' . ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_conn_type.criteria _item_description.description ; The criteria used to define the interaction. ; _item.name '_struct_conn_type.criteria' _item.category_id struct_conn_type _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'O to N distance > 2.5 \%A, < 3.2 \%A' 'authors judgement' save_ save__struct_conn_type.id _item_description.description ; The chemical or structural type of the interaction. ; loop_ _item.name _item.category_id _item.mandatory_code '_struct_conn_type.id' struct_conn_type yes '_struct_conn.conn_type_id' struct_conn yes loop_ _item_linked.child_name _item_linked.parent_name '_struct_conn.conn_type_id' '_struct_conn_type.id' _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail covale 'covalent bond' disulf 'disulfide bridge' hydrog 'hydrogen bond' metalc 'metal coordination' mismat 'mismatched base pairs' saltbr 'ionic interaction' modres 'covalent residue modification' covale_base 'covalent modification of a nucleotide base' covale_sugar 'covalent modification of a nucleotide sugar' covale_phosphate 'covalent modification of a nucleotide phosphate' save_ save__struct_conn_type.reference _item_description.description ; A reference that specifies the criteria used to define the interaction. ; _item.name '_struct_conn_type.reference' _item.category_id struct_conn_type _item.mandatory_code no _item_type.code text save_ ##################### ## STRUCT_KEYWORDS ## ##################### save_struct_keywords _category.description ; Data items in the STRUCT_KEYWORDS category specify keywords that describe the chemical structure in this entry. ; _category.id struct_keywords _category.mandatory_code no _category_key.name '_struct_keywords.entry_id' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _struct_keywords.entry_id _struct_keywords.text '5HVP' 'enzyme-inhibitor complex, aspartyl protease, static disorder' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_keywords.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_struct_keywords.entry_id' _item.mandatory_code yes save_ save__struct_keywords.text _item_description.description ; Keywords describing this structure. ; _item.name '_struct_keywords.text' _item.category_id struct_keywords _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'serine protease' 'inhibited complex' 'high-resolution refinement' save_ ######################## ## STRUCT_MON_DETAILS ## ######################## save_struct_mon_details _category.description ; Data items in the STRUCT_MON_DETAILS category record details about specifics of calculations summarized in data items in the STRUCT_MON_PROT and STRUCT_MON_NUCL categories. These can include the coefficients used in map calculations, the radii used for including points in a calculation and so on. ; _category.id struct_mon_details _category.mandatory_code no _category_key.name '_struct_mon_details.entry_id' loop_ _category_group.id 'inclusive_group' 'struct_group' save_ save__struct_mon_details.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_struct_mon_details.entry_id' _item.mandatory_code yes save_ save__struct_mon_details.prot_cis _item_description.description ; An ideal cis peptide bond would have an omega torsion angle of zero. This data item gives the value in degrees by which the observed torsion angle can differ from 0.0 and still be considered cis. ; _item.name '_struct_mon_details.prot_cis' _item.category_id struct_mon_details _item.mandatory_code no _item_type.code float _item_units.code degrees _item_examples.case 30.0 save_ save__struct_mon_details.RSCC _item_description.description ; This data item describes the specifics of the calculations that generated the values given in _struct_mon_prot.RSCC_all, _struct_mon_prot.RSCC_main and _struct_mon_prot.RSCC_side. The coefficients used to calculate the p(o) and p(c) maps should be given as well as the criterion for the inclusion of map grid points in the calculation. ; _item.name '_struct_mon_details.RSCC' _item.category_id struct_mon_details _item.mandatory_code no _item_type.code text loop_ _item_examples.case ; The map p(o) was calculated with coefficients 2F(o) - F(c) and with phase alpha(c). F(o) are the observed structure-factor amplitudes, F(c) are the amplitudes calculated from the current model and alpha(c) are the phases calculated from the current model. The map p(c) was calculated in program O using a Gaussian distribution function around the atoms in the current model. Map grid points within 1.5 A of the designated atoms were included in the calculation. ; ; The map p(o) was calculated with coefficients F(o) and with phase alpha(c). F(o) are the observed structure-factor amplitudes, and alpha(c) are the phases calculated from the current model. The map p(c) was calculated with coefficients F(c) and with phases alpha(c). F(c) and alpha(c) are the structure-factor amplitudes and phases, respectively, calculated from the current model. Map grid points within a van der Waals radius of the designated atoms were included in the calculation. ; save_ save__struct_mon_details.RSR _item_description.description ; This data item describes the specifics of the calculations that generated the values given in _struct_mon_prot.RSR_all, _struct_mon_prot.RSR_main and _struct_mon_prot.RSR_side. The coefficients used to calculate the p(o) and p(c) maps should be given as well as the criterion for the inclusion of map grid points in the calculation. ; _item.name '_struct_mon_details.RSR' _item.category_id struct_mon_details _item.mandatory_code no _item_type.code text loop_ _item_examples.case ; The map p(o) was calculated with coefficients 2F(o) - F(c) and with phase alpha(c). F(o) are the observed structure-factor amplitudes, F(c) are the amplitudes calculated from the current model and alpha(c) are the phases calculated from the current model. The map p(c) was calculated in program O using a Gaussian distribution function around the atoms in the current model. Map grid points within 1.5 A of the designated atoms were included in the calculation. ; ; The map p(o) was calculated with coefficients F(o) and with phase alpha(c). F(o) are the observed structure-factor amplitudes, and alpha(c) are the phases calculated from the current model. The map p(c) was calculated with coefficients F(c) and with phases alpha(c). F(c) and alpha(c) are the structure-factor amplitudes and phases, respectively, calculated from the current model. Map grid points within a van der Waals radius of the designated atoms were included in the calculation. ; save_ ##################### ## STRUCT_MON_NUCL ## ##################### save_struct_mon_nucl _category.description ; Data items in the STRUCT_MON_NUCL category record details about structural properties of a nucleic acid when analyzed at the monomer level. Analogous data items for proteins are given in the STRUCT_MON_PROT category. For items where the value of the property depends on the method employed to calculate it, details of the method of calculation are given using data items in the STRUCT_MON_DETAILS category. ; _category.id struct_mon_nucl _category.mandatory_code no loop_ _category_key.name '_struct_mon_nucl.label_alt_id' '_struct_mon_nucl.label_asym_id' '_struct_mon_nucl.label_comp_id' '_struct_mon_nucl.label_seq_id' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on NDB structure BDL028. ; ; loop_ _struct_mon_nucl.label_comp_id _struct_mon_nucl.label_seq_id _struct_mon_nucl.label_asym_id _struct_mon_nucl.label_alt_id _struct_mon_nucl.alpha _struct_mon_nucl.beta _struct_mon_nucl.gamma _struct_mon_nucl.delta _struct_mon_nucl.epsilon _struct_mon_nucl.zeta C 1 A . . . 29.9 131.9 222.1 174.2 G 2 A . 334.0 130.6 33.1 125.6 167.6 270.9 T 3 A . 258.2 178.7 101.0 114.6 216.6 259.3 # ---- abbreviated list ----- ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_mon_nucl.alpha _item_description.description ; The value in degrees of the backbone torsion angle alpha (O3'-P-O5'-C5'). ; _item.name '_struct_mon_nucl.alpha' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__struct_mon_nucl.auth_asym_id _item_description.description ; A component of the identifier for participants in the site. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_struct_mon_nucl.auth_asym_id' _item.mandatory_code no save_ save__struct_mon_nucl.auth_comp_id _item_description.description ; A component of the identifier for participants in the site. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_struct_mon_nucl.auth_comp_id' _item.mandatory_code no save_ save__struct_mon_nucl.auth_seq_id _item_description.description ; A component of the identifier for participants in the site. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_struct_mon_nucl.auth_seq_id' _item.mandatory_code no save_ save__struct_mon_nucl.beta _item_description.description ; The value in degrees of the backbone torsion angle beta (P-O5'-C5'-C4'). ; _item.name '_struct_mon_nucl.beta' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__struct_mon_nucl.chi1 _item_description.description ; The value in degrees of the sugar-base torsion angle chi1 (O4'-C1'-N1-C2). ; _item.name '_struct_mon_nucl.chi1' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__struct_mon_nucl.chi2 _item_description.description ; The value in degrees of the sugar-base torsion angle chi2 (O4'-C1'-N9-C4). ; _item.name '_struct_mon_nucl.chi2' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__struct_mon_nucl.delta _item_description.description ; The value in degrees of the backbone torsion angle delta (C5'-C4'-C3'-O3'). ; _item.name '_struct_mon_nucl.delta' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__struct_mon_nucl.details _item_description.description ; A description of special aspects of the residue, its conformation, behaviour in refinement, or any other aspect that requires annotation. ; _item.name '_struct_mon_nucl.details' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float _item_examples.case ; Part of the phosphodiester backbone not in density. ; save_ save__struct_mon_nucl.epsilon _item_description.description ; The value in degrees of the backbone torsion angle epsilon (C4'-C3'-O3'-P). ; _item.name '_struct_mon_nucl.epsilon' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__struct_mon_nucl.gamma _item_description.description ; The value in degrees of the backbone torsion angle gamma (O5'-C5'-C4'-C3'). ; _item.name '_struct_mon_nucl.gamma' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__struct_mon_nucl.label_alt_id _item_description.description ; A component of the identifier for participants in the site. This data item is a pointer to _atom_sites_alt.id in the ATOM_SITES_ALT category. ; _item.name '_struct_mon_nucl.label_alt_id' _item.mandatory_code yes save_ save__struct_mon_nucl.label_asym_id _item_description.description ; A component of the identifier for participants in the site. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_struct_mon_nucl.label_asym_id' _item.mandatory_code yes save_ save__struct_mon_nucl.label_comp_id _item_description.description ; A component of the identifier for participants in the site. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_struct_mon_nucl.label_comp_id' _item.mandatory_code yes save_ save__struct_mon_nucl.label_seq_id _item_description.description ; A component of the identifier for participants in the site. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_struct_mon_nucl.label_seq_id' _item.mandatory_code yes save_ save__struct_mon_nucl.mean_B_all _item_description.description ; The mean value of the isotropic displacement parameter for all atoms in the monomer. ; _item.name '_struct_mon_nucl.mean_B_all' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float save_ save__struct_mon_nucl.mean_B_base _item_description.description ; The mean value of the isotropic displacement parameter for atoms in the base moiety of the nucleic acid monomer. ; _item.name '_struct_mon_nucl.mean_B_base' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float save_ save__struct_mon_nucl.mean_B_phos _item_description.description ; The mean value of the isotropic displacement parameter for atoms in the phosphate moiety of the nucleic acid monomer. ; _item.name '_struct_mon_nucl.mean_B_phos' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float save_ save__struct_mon_nucl.mean_B_sugar _item_description.description ; The mean value of the isotropic displacement parameter for atoms in the sugar moiety of the nucleic acid monomer. ; _item.name '_struct_mon_nucl.mean_B_sugar' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float save_ save__struct_mon_nucl.nu0 _item_description.description ; The value in degrees of the sugar torsion angle nu0 (C4'-O4'-C1'-C2'). ; _item.name '_struct_mon_nucl.nu0' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__struct_mon_nucl.nu1 _item_description.description ; The value in degrees of the sugar torsion angle nu1 (O4'-C1'-C2'-C3'). ; _item.name '_struct_mon_nucl.nu1' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__struct_mon_nucl.nu2 _item_description.description ; The value in degrees of the sugar torsion angle nu2 (C1'-C2'-C3'-C4'). ; _item.name '_struct_mon_nucl.nu2' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__struct_mon_nucl.nu3 _item_description.description ; The value in degrees of the sugar torsion angle nu3 (C2'-C3'-C4'-O4'). ; _item.name '_struct_mon_nucl.nu3' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__struct_mon_nucl.nu4 _item_description.description ; The value in degrees of the sugar torsion angle nu4 (C3'-C4'-O4'-C1'). ; _item.name '_struct_mon_nucl.nu4' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__struct_mon_nucl.P _item_description.description ; P is the phase angle of pseudorotation for five-membered rings. For ribose and deoxyribose sugars in nucleic acids (tau4 +tau1)-(tau3+tau0) P = ATAN (-------------------------) 2tau2 (sin 36+sin 72) If tau2 is <0, then P=P+180 degree (Altona & Sundaralingam, 1972). Ref: Altona, C. & Sundaralingam, M. (1972). J. Am. Chem. Soc. 94, 8205-8212. ; _item.name '_struct_mon_nucl.P' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__struct_mon_nucl.RSCC_all _item_description.description ; The real-space (linear) correlation coefficient RSCC, as described by Jones et al. (1991), evaluated over all atoms in the nucleic acid monomer. sum|p~obs~ - | * sum|p~calc~ - | RSCC = ------------------------------------------------- [ sum|p~obs~ - |^2^ * sum|p~calc~ - |^2^ ]^1/2^ p~obs~ = the density in an 'experimental' map p~calc~ = the density in a 'calculated' map sum is taken over the specified grid points Details of how these maps were calculated should be given in _struct_mon_details.RSCC. < > indicates an average and the sums are taken over all map grid points near the relevant atoms. The radius for including grid points in the calculation should also be given in _struct_mon_details.RSCC. Ref: Jones, T. A., Zou, J.-Y., Cowan, S. W. & Kjeldgaard, M. (1991). Acta Cryst. A47, 110-119. ; _item.name '_struct_mon_nucl.RSCC_all' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float save_ save__struct_mon_nucl.RSCC_base _item_description.description ; The real-space (linear) correlation coefficient RSCC, as described by Jones et al. (1991), evaluated over all atoms in the base moiety of the nucleic acid monomer. sum|p~obs~ - | * sum|p~calc~ - | RSCC = ------------------------------------------------- [ sum|p~obs~ - |^2^ * sum|p~calc~ - |^2^ ]^1/2^ p~obs~ = the density in an 'experimental' map p~calc~ = the density in a 'calculated' map sum is taken over the specified grid points Details of how these maps were calculated should be given in _struct_mon_details.RSCC. < > indicates an average and the sums are taken over all map grid points near the relevant atoms. The radius for including grid points in the calculation should also be given in _struct_mon_details.RSCC. Ref: Jones, T. A., Zou, J.-Y., Cowan, S. W. & Kjeldgaard, M. (1991). Acta Cryst. A47, 110-119. ; _item.name '_struct_mon_nucl.RSCC_base' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float save_ save__struct_mon_nucl.RSCC_phos _item_description.description ; The real-space (linear) correlation coefficient RSCC, as described by Jones et al. (1991), evaluated over all atoms in the phosphate moiety of the nucleic acid monomer. sum|p~obs~ - | * sum|p~calc~ - | RSCC = ------------------------------------------------- [ sum|p~obs~ - |^2^ * sum|p~calc~ - |^2^ ]^1/2^ p~obs~ = the density in an 'experimental' map p~calc~ = the density in a 'calculated' map sum is taken over the specified grid points Details of how these maps were calculated should be given in _struct_mon_details.RSCC. < > indicates an average and the sums are taken over all map grid points near the relevant atoms. The radius for including grid points in the calculation should also be given in _struct_mon_details.RSCC. Ref: Jones, T. A., Zou, J.-Y., Cowan, S. W. & Kjeldgaard, M. (1991). Acta Cryst. A47, 110-119. ; _item.name '_struct_mon_nucl.RSCC_phos' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float save_ save__struct_mon_nucl.RSCC_sugar _item_description.description ; The real-space (linear) correlation coefficient RSCC, as described by Jones et al. (1991), evaluated over all atoms in the sugar moiety of the nucleic acid monomer. sum|p~obs~ - | * sum|p~calc~ - | RSCC = ------------------------------------------------- [ sum|p~obs~ - |^2^ * sum|p~calc~ - |^2^ ]^1/2^ p~obs~ = the density in an 'experimental' map p~calc~ = the density in a 'calculated' map sum is taken over the specified grid points Details of how these maps were calculated should be given in _struct_mon_details.RSCC. < > indicates an average and the sums are taken over all map grid points near the relevant atoms. The radius for including grid points in the calculation should also be given in _struct_mon_details.RSCC. Ref: Jones, T. A., Zou, J.-Y., Cowan, S. W. & Kjeldgaard, M. (1991). Acta Cryst. A47, 110-119. ; _item.name '_struct_mon_nucl.RSCC_sugar' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float save_ save__struct_mon_nucl.RSR_all _item_description.description ; The real-space residual RSR, as described by Branden & Jones (1990), evaluated over all atoms in the nucleic acid monomer. sum|p~obs~ - p~calc~| RSR = --------------------- sum|p~obs~ + p~calc~| p~obs~ = the density in an 'experimental' map p~calc~ = the density in a 'calculated' map sum is taken over the specified grid points Details of how these maps were calculated should be given in _struct_mon_details.RSR. The sums are taken over all map grid points near the relevant atoms. The radius for including grid points in the calculation should also be given in _struct_mon_details.RSR. Ref: Branden, C.-I. & Jones, T. A. (1990). Nature (London), 343, 687-689. ; _item.name '_struct_mon_nucl.RSR_all' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float save_ save__struct_mon_nucl.RSR_base _item_description.description ; The real-space residual RSR, as described by Branden & Jones (1990), evaluated over all atoms in the base moiety of the nucleic acid monomer. sum|p~obs~ - p~calc~| RSR = --------------------- sum|p~obs~ + p~calc~| p~obs~ = the density in an 'experimental' map p~calc~ = the density in a 'calculated' map sum is taken over the specified grid points Details of how these maps were calculated should be given in _struct_mon_details.RSR. The sums are taken over all map grid points near the relevant atoms. The radius for including grid points in the calculation should also be given in _struct_mon_details.RSR. Ref: Branden, C.-I. & Jones, T. A. (1990). Nature (London), 343, 687-689. ; _item.name '_struct_mon_nucl.RSR_base' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float save_ save__struct_mon_nucl.RSR_phos _item_description.description ; The real-space residual RSR, as described by Branden & Jones (1990), evaluated over all atoms in the phosphate moiety of the nucleic acid monomer. sum|p~obs~ - p~calc~| RSR = --------------------- sum|p~obs~ + p~calc~| p~obs~ = the density in an 'experimental' map p~calc~ = the density in a 'calculated' map sum is taken over the specified grid points Details of how these maps were calculated should be given in _struct_mon_details.RSR. The sums are taken over all map grid points near the relevant atoms. The radius for including grid points in the calculation should also be given in _struct_mon_details.RSR. Ref: Branden, C.-I. & Jones, T. A. (1990). Nature (London), 343, 687-689. ; _item.name '_struct_mon_nucl.RSR_phos' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float save_ save__struct_mon_nucl.RSR_sugar _item_description.description ; The real-space residual RSR, as described by Branden & Jones (1990), evaluated over all atoms in the sugar moiety of the nucleic acid monomer. sum|p~obs~ - p~calc~| RSR = --------------------- sum|p~obs~ + p~calc~| p~obs~ = the density in an 'experimental' map p~calc~ = the density in a 'calculated' map sum is taken over the specified grid points Details of how these maps were calculated should be given in _struct_mon_details.RSR. The sums are taken over all map grid points near the relevant atoms. The radius for including grid points in the calculation should also be given in _struct_mon_details.RSR. Ref: Branden, C.-I. & Jones, T. A. (1990). Nature (London), 343, 687-689. ; _item.name '_struct_mon_nucl.RSR_sugar' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float save_ save__struct_mon_nucl.tau0 _item_description.description ; The value in degrees of the sugar torsion angle tau0 (C4'-O4'-C1'-C2'). ; _item.name '_struct_mon_nucl.tau0' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__struct_mon_nucl.tau1 _item_description.description ; The value in degrees of the sugar torsion angle tau1 (O4'-C1'-C2'-C3'). ; _item.name '_struct_mon_nucl.tau1' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__struct_mon_nucl.tau2 _item_description.description ; The value in degrees of the sugar torsion angle tau2 (C1'-C2'-C3'-C4'). ; _item.name '_struct_mon_nucl.tau2' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__struct_mon_nucl.tau3 _item_description.description ; The value in degrees of the sugar torsion angle tau3 (C2'-C3'-C4'-O4'). ; _item.name '_struct_mon_nucl.tau3' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__struct_mon_nucl.tau4 _item_description.description ; The value in degrees of the sugar torsion angle tau4 (C3'-C4'-O4'-C1'). ; _item.name '_struct_mon_nucl.tau4' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__struct_mon_nucl.taum _item_description.description ; The maximum amplitude of puckering. This is derived from the pseudorotation value P and the torsion angles in the ribose ring. Tau2= Taum cosP Tau3= Taum cos(P+144) Tau4= Taum cos(P+288) Tau0= Taum cos(P+ 72) Tau1= Taum cos(P+216) ; _item.name '_struct_mon_nucl.taum' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__struct_mon_nucl.zeta _item_description.description ; The value in degrees of the backbone torsion angle zeta (C3'-O3'-P-O5'). ; _item.name '_struct_mon_nucl.zeta' _item.category_id struct_mon_nucl _item.mandatory_code no _item_type.code float _item_units.code degrees save_ ##################### ## STRUCT_MON_PROT ## ##################### save_struct_mon_prot _category.description ; Data items in the STRUCT_MON_PROT category record details about structural properties of a protein when analyzed at the monomer level. Analogous data items for nucleic acids are given in the STRUCT_MON_NUCL category. For items where the value of the property depends on the method employed to calculate it, details of the method of calculation are given using data items in the STRUCT_MON_DETAILS category. ; _category.id struct_mon_prot _category.mandatory_code no loop_ _category_key.name '_struct_mon_prot.label_alt_id' '_struct_mon_prot.label_asym_id' '_struct_mon_prot.label_comp_id' '_struct_mon_prot.label_seq_id' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on laboratory records for protein NS1. This example provides details for residue ARG 35. ; ; _struct_mon_prot.label_comp_id ARG _struct_mon_prot.label_seq_id 35 _struct_mon_prot.label_asym_id A _struct_mon_prot.label_alt_id . _struct_mon_prot.chi1 -67.9 _struct_mon_prot.chi2 -174.7 _struct_mon_prot.chi3 -67.7 _struct_mon_prot.chi4 -86.3 _struct_mon_prot.chi5 4.2 _struct_mon_prot.RSCC_all 0.90 _struct_mon_prot.RSR_all 0.18 _struct_mon_prot.mean_B_all 30.0 _struct_mon_prot.mean_B_main 25.0 _struct_mon_prot.mean_B_side 35.1 _struct_mon_prot.omega 180.1 _struct_mon_prot.phi -60.3 _struct_mon_prot.psi -46.0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_mon_prot.chi1 _item_description.description ; The value in degrees of the side-chain torsion angle chi1, for those residues containing such an angle. ; _item.name '_struct_mon_prot.chi1' _item.category_id struct_mon_prot _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__struct_mon_prot.chi2 _item_description.description ; The value in degrees of the side-chain torsion angle chi2, for those residues containing such an angle. ; _item.name '_struct_mon_prot.chi2' _item.category_id struct_mon_prot _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__struct_mon_prot.chi3 _item_description.description ; The value in degrees of the side-chain torsion angle chi3, for those residues containing such an angle. ; _item.name '_struct_mon_prot.chi3' _item.category_id struct_mon_prot _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__struct_mon_prot.chi4 _item_description.description ; The value in degrees of the side-chain torsion angle chi4, for those residues containing such an angle. ; _item.name '_struct_mon_prot.chi4' _item.category_id struct_mon_prot _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__struct_mon_prot.chi5 _item_description.description ; The value in degrees of the side-chain torsion angle chi5, for those residues containing such an angle. ; _item.name '_struct_mon_prot.chi5' _item.category_id struct_mon_prot _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__struct_mon_prot.details _item_description.description ; A description of special aspects of the residue, its conformation, behaviour in refinement, or any other aspect that requires annotation. ; _item.name '_struct_mon_prot.details' _item.category_id struct_mon_prot _item.mandatory_code no _item_type.code float loop_ _item_examples.case 'very poor density' ; The side chain of this density may occupy alternative conformations, but alternative conformations were not fit in this model. ; ; This residue has a close contact with the bound inhibitor, which may account for the nonstandard conformation of the side chain. ; save_ save__struct_mon_prot.label_alt_id _item_description.description ; A component of the identifier for the monomer. This data item is a pointer to _atom_sites_alt.id in the ATOM_SITES_ALT category. ; _item.name '_struct_mon_prot.label_alt_id' _item.mandatory_code yes save_ save__struct_mon_prot.label_asym_id _item_description.description ; A component of the identifier for the monomer. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_struct_mon_prot.label_asym_id' _item.mandatory_code yes save_ save__struct_mon_prot.label_comp_id _item_description.description ; A component of the identifier for the monomer. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_struct_mon_prot.label_comp_id' _item.mandatory_code yes save_ save__struct_mon_prot.label_seq_id _item_description.description ; A component of the identifier for the monomer. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_struct_mon_prot.label_seq_id' _item.mandatory_code yes save_ save__struct_mon_prot.auth_asym_id _item_description.description ; A component of the identifier for the monomer. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_struct_mon_prot.auth_asym_id' _item.mandatory_code no save_ save__struct_mon_prot.auth_comp_id _item_description.description ; A component of the identifier for the monomer. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_struct_mon_prot.auth_comp_id' _item.mandatory_code no save_ save__struct_mon_prot.auth_seq_id _item_description.description ; A component of the identifier for the monomer. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_struct_mon_prot.auth_seq_id' _item.mandatory_code no save_ save__struct_mon_prot.RSCC_all _item_description.description ; The real-space (linear) correlation coefficient RSCC, as described by Jones et al. (1991), evaluated over all atoms in the monomer. sum|p~obs~ - | * sum|p~calc~ - | RSCC = ------------------------------------------------- [ sum|p~obs~ - |^2^ * sum|p~calc~ - |^2^ ]^1/2^ p~obs~ = the density in an 'experimental' map p~calc~ = the density in a 'calculated' map sum is taken over the specified grid points Details of how these maps were calculated should be given in _struct_mon_details.RSCC. < > indicates an average and the sums are taken over all map grid points near the relevant atoms. The radius for including grid points in the calculation should also be given in _struct_mon_details.RSCC. Ref: Jones, T. A., Zou, J.-Y., Cowan, S. W. & Kjeldgaard, M. (1991). Acta Cryst. A47, 110-119. ; _item.name '_struct_mon_prot.RSCC_all' _item.category_id struct_mon_prot _item.mandatory_code no _item_type.code float save_ save__struct_mon_prot.RSCC_main _item_description.description ; The real-space (linear) correlation coefficient RSCC, as described by Jones et al. (1991), evaluated over all atoms in the main chain of the monomer. sum|p~obs~ - | * sum|p~calc~ - | RSCC = ------------------------------------------------- [ sum|p~obs~ - |^2^ * sum|p~calc~ - |^2^ ]^1/2^ p~obs~ = the density in an 'experimental' map p~calc~ = the density in a 'calculated' map sum is taken over the specified grid points Details of how these maps were calculated should be given in _struct_mon_details.RSCC. < > indicates an average and the sums are taken over all map grid points near the relevant atoms. The radius for including grid points in the calculation should also be given in _struct_mon_details.RSCC. Ref: Jones, T. A., Zou, J.-Y., Cowan, S. W. & Kjeldgaard, M. (1991). Acta Cryst. A47, 110-119. ; _item.name '_struct_mon_prot.RSCC_main' _item.category_id struct_mon_prot _item.mandatory_code no _item_type.code float save_ save__struct_mon_prot.RSCC_side _item_description.description ; The real-space (linear) correlation coefficient RSCC, as described by Jones et al. (1991), evaluated over all atoms in the side chain of the monomer. sum|p~obs~ - | * sum|p~calc~ - | RSCC = ------------------------------------------------- [ sum|p~obs~ - |^2^ * sum|p~calc~ - |^2^ ]^1/2^ p~obs~ = the density in an 'experimental' map p~calc~ = the density in a 'calculated' map sum is taken over the specified grid points Details of how these maps were calculated should be given in _struct_mon_details.RSCC. < > indicates an average and the sums are taken over all map grid points near the relevant atoms. The radius for including grid points in the calculation should also be given in _struct_mon_details.RSCC. Ref: Jones, T. A., Zou, J.-Y., Cowan, S. W. & Kjeldgaard, M. (1991). Acta Cryst. A47, 110-119. ; _item.name '_struct_mon_prot.RSCC_side' _item.category_id struct_mon_prot _item.mandatory_code no _item_type.code float save_ save__struct_mon_prot.RSR_all _item_description.description ; The real-space residual RSR, as described by Branden & Jones (1990), evaluated over all atoms in the monomer. sum|p~obs~ - p~calc~| RSR = --------------------- sum|p~obs~ + p~calc~| p~obs~ = the density in an 'experimental' map p~calc~ = the density in a 'calculated' map sum is taken over the specified grid points Details of how these maps were calculated should be given in _struct_mon_details.RSR. The sums are taken over all map grid points near the relevant atoms. The radius for including grid points in the calculation should also be given in _struct_mon_details.RSR. Ref: Branden, C.-I. & Jones, T. A. (1990). Nature (London), 343, 687-689. ; _item.name '_struct_mon_prot.RSR_all' _item.category_id struct_mon_prot _item.mandatory_code no _item_type.code float save_ save__struct_mon_prot.RSR_main _item_description.description ; The real-space residual RSR, as described by Branden & Jones (1990), evaluated over all atoms in the main chain of the monomer. sum|p~obs~ - p~calc~| RSR = --------------------- sum|p~obs~ + p~calc~| p~obs~ = the density in an 'experimental' map p~calc~ = the density in a 'calculated' map sum is taken over the specified grid points Details of how these maps were calculated should be given in _struct_mon_details.RSR. The sums are taken over all map grid points near the relevant atoms. The radius for including grid points in the calculation should also be given in _struct_mon_details.RSR. Ref: Branden, C.-I. & Jones, T. A. (1990). Nature (London), 343, 687-689. ; _item.name '_struct_mon_prot.RSR_main' _item.category_id struct_mon_prot _item.mandatory_code no _item_type.code float save_ save__struct_mon_prot.RSR_side _item_description.description ; The real-space residual RSR, as described by Branden & Jones (1990), evaluated over all atoms in the side chain of the monomer. sum|p~obs~ - p~calc~| RSR = --------------------- sum|p~obs~ + p~calc~| p~obs~ = the density in an 'experimental' map p~calc~ = the density in a 'calculated' map sum is taken over the specified grid points Details of how these maps were calculated should be given in _struct_mon_details.RSR. The sums are taken over all map grid points near the relevant atoms. The radius for including grid points in the calculation should also be given in _struct_mon_details.RSR. Ref: Branden, C.-I. & Jones, T. A. (1990). Nature (London), 343, 687-689. ; _item.name '_struct_mon_prot.RSR_side' _item.category_id struct_mon_prot _item.mandatory_code no _item_type.code float save_ save__struct_mon_prot.mean_B_all _item_description.description ; The mean value of the isotropic displacement parameter for all atoms in the monomer. ; _item.name '_struct_mon_prot.mean_B_all' _item.category_id struct_mon_prot _item.mandatory_code no _item_type.code float save_ save__struct_mon_prot.mean_B_main _item_description.description ; The mean value of the isotropic displacement parameter for atoms in the main chain of the monomer. ; _item.name '_struct_mon_prot.mean_B_main' _item.category_id struct_mon_prot _item.mandatory_code no _item_type.code float save_ save__struct_mon_prot.mean_B_side _item_description.description ; The mean value of the isotropic displacement parameter for atoms in the side chain of the monomer. ; _item.name '_struct_mon_prot.mean_B_side' _item.category_id struct_mon_prot _item.mandatory_code no _item_type.code float save_ save__struct_mon_prot.omega _item_description.description ; The value in degrees of the main-chain torsion angle omega. ; _item.name '_struct_mon_prot.omega' _item.category_id struct_mon_prot _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__struct_mon_prot.phi _item_description.description ; The value in degrees of the main-chain torsion angle phi. ; _item.name '_struct_mon_prot.phi' _item.category_id struct_mon_prot _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__struct_mon_prot.psi _item_description.description ; The value in degrees of the main-chain torsion angle psi. ; _item.name '_struct_mon_prot.psi' _item.category_id struct_mon_prot _item.mandatory_code no _item_type.code float _item_units.code degrees save_ ######################### ## STRUCT_MON_PROT_CIS ## ######################### save_struct_mon_prot_cis _category.description ; Data items in the STRUCT_MON_PROT_CIS category identify monomers that have been found to have the peptide bond in the cis conformation. The criterion used to select residues to be designated as containing cis peptide bonds is given in _struct_mon_details.prot_cis. ; _category.id struct_mon_prot_cis _category.mandatory_code no loop_ _category_key.name '_struct_mon_prot_cis.label_alt_id' '_struct_mon_prot_cis.label_asym_id' '_struct_mon_prot_cis.label_comp_id' '_struct_mon_prot_cis.label_seq_id' '_struct_mon_prot_cis.pdbx_PDB_model_num' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB structure 1ACY of Ghiara, Stura, Stanfield, Profy & Wilson [Science (1994), 264, 82-85]. ; ; loop_ _struct_mon_prot_cis.label_comp_id _struct_mon_prot_cis.label_seq_id _struct_mon_prot_cis.label_asym_id _struct_mon_prot_cis.label_alt_id _struct_mon_prot_cis.pdbx_PDB_model_num PRO 8 L . 1 PRO 77 L . 1 PRO 95 L . 1 PRO 141 L . 1 # ----- abbreviated ----- ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_mon_prot_cis.label_alt_id _item_description.description ; A component of the identifier for the monomer. This data item is a pointer to _atom_sites_alt.id in the ATOM_SITES_ALT category. ; _item.name '_struct_mon_prot_cis.label_alt_id' _item.mandatory_code yes save_ save__struct_mon_prot_cis.label_asym_id _item_description.description ; A component of the identifier for the monomer. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_struct_mon_prot_cis.label_asym_id' _item.mandatory_code yes save_ save__struct_mon_prot_cis.label_comp_id _item_description.description ; A component of the identifier for the monomer. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_struct_mon_prot_cis.label_comp_id' _item.mandatory_code yes save_ save__struct_mon_prot_cis.label_seq_id _item_description.description ; A component of the identifier for the monomer. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_struct_mon_prot_cis.label_seq_id' _item.mandatory_code yes save_ save__struct_mon_prot_cis.auth_asym_id _item_description.description ; A component of the identifier for the monomer. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_struct_mon_prot_cis.auth_asym_id' _item.mandatory_code no save_ save__struct_mon_prot_cis.auth_comp_id _item_description.description ; A component of the identifier for the monomer. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_struct_mon_prot_cis.auth_comp_id' _item.mandatory_code no save_ save__struct_mon_prot_cis.auth_seq_id _item_description.description ; A component of the identifier for the monomer. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_struct_mon_prot_cis.auth_seq_id' _item.mandatory_code no save_ #################### ## STRUCT_NCS_DOM ## #################### save_struct_ncs_dom _category.description ; Data items in the STRUCT_NCS_DOM category record information about the domains in an ensemble of domains related by one or more noncrystallographic symmetry operators. A domain need not correspond to a complete polypeptide chain; it can be composed of one or more segments in a single chain, or by segments from more than one chain. ; _category.id struct_ncs_dom _category.mandatory_code no _category_key.name '_struct_ncs_dom.id' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on laboratory records for the collagen-like peptide, HYP-. ; ; loop_ _struct_ncs_dom.id _struct_ncs_dom.details d1 'Chains A, B, and C' d2 'Chains D, E, and F' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_ncs_dom.details _item_description.description ; A description of special aspects of the structural elements that comprise a domain in an ensemble of domains related by noncrystallographic symmetry. ; _item.name '_struct_ncs_dom.details' _item.category_id struct_ncs_dom _item.mandatory_code no _item_type.code text _item_examples.case ; The loop between residues 18 and 23 in this domain interacts with a symmetry-related molecule, and thus deviates significantly from the noncrystallographic threefold. ; save_ save__struct_ncs_dom.id _item_description.description ; The value of _struct_ncs_dom.id must uniquely identify a record in the STRUCT_NCS_DOM list. Note that this item need not be a number; it can be any unique identifier. ; loop_ _item.name _item.category_id _item.mandatory_code '_struct_ncs_dom.id' struct_ncs_dom yes '_struct_ncs_dom_lim.dom_id' struct_ncs_dom_lim yes '_struct_ncs_ens_gen.dom_id_1' struct_ncs_ens_gen yes '_struct_ncs_ens_gen.dom_id_2' struct_ncs_ens_gen yes loop_ _item_linked.child_name _item_linked.parent_name '_struct_ncs_dom_lim.dom_id' '_struct_ncs_dom.id' '_struct_ncs_ens_gen.dom_id_1' '_struct_ncs_dom.id' '_struct_ncs_ens_gen.dom_id_2' '_struct_ncs_dom.id' _item_type.code code save_ ######################## ## STRUCT_NCS_DOM_LIM ## ######################## save_struct_ncs_dom_lim _category.description ; Data items in the STRUCT_NCS_DOM_LIM category identify the start and end points of polypeptide chain segments that form all or part of a domain in an ensemble of domains related by noncrystallographic symmetry. ; _category.id struct_ncs_dom_lim _category.mandatory_code no loop_ _category_key.name '_struct_ncs_dom_lim.dom_id' '_struct_ncs_dom_lim.beg_label_alt_id' '_struct_ncs_dom_lim.beg_label_asym_id' '_struct_ncs_dom_lim.beg_label_comp_id' '_struct_ncs_dom_lim.beg_label_seq_id' '_struct_ncs_dom_lim.end_label_alt_id' '_struct_ncs_dom_lim.end_label_asym_id' '_struct_ncs_dom_lim.end_label_comp_id' '_struct_ncs_dom_lim.end_label_seq_id' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on laboratory records for the collagen-like peptide, HYP-. ; ; loop_ _struct_ncs_dom_lim.dom_id _struct_ncs_dom_lim.beg_label_alt_id _struct_ncs_dom_lim.beg_label_asym_id _struct_ncs_dom_lim.beg_label_comp_id _struct_ncs_dom_lim.beg_label_seq_id _struct_ncs_dom_lim.end_label_alt_id _struct_ncs_dom_lim.end_label_asym_id _struct_ncs_dom_lim.end_label_comp_id _struct_ncs_dom_lim.end_label_seq_id d1 . A PRO 1 . A GLY 29 d1 . B PRO 31 . B GLY 59 d1 . C PRO 61 . B GLY 89 d2 . D PRO 91 . D GLY 119 d2 . E PRO 121 . E GLY 149 d2 . F PRO 151 . F GLY 179 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_ncs_dom_lim.beg_label_alt_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain begins. This data item is a pointer to _atom_sites_alt.id in the ATOM_SITES_ALT category. ; _item.name '_struct_ncs_dom_lim.beg_label_alt_id' _item.mandatory_code yes save_ save__struct_ncs_dom_lim.beg_label_asym_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain begins. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_struct_ncs_dom_lim.beg_label_asym_id' _item.mandatory_code yes save_ save__struct_ncs_dom_lim.beg_label_comp_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain begins. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_struct_ncs_dom_lim.beg_label_comp_id' _item.mandatory_code yes save_ save__struct_ncs_dom_lim.beg_label_seq_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain begins. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_struct_ncs_dom_lim.beg_label_seq_id' _item.mandatory_code yes save_ save__struct_ncs_dom_lim.beg_auth_asym_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain begins. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_struct_ncs_dom_lim.beg_auth_asym_id' _item.mandatory_code no save_ save__struct_ncs_dom_lim.beg_auth_comp_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain begins. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_struct_ncs_dom_lim.beg_auth_comp_id' _item.mandatory_code no save_ save__struct_ncs_dom_lim.beg_auth_seq_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain begins. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_struct_ncs_dom_lim.beg_auth_seq_id' _item.mandatory_code no save_ save__struct_ncs_dom_lim.dom_id _item_description.description ; This data item is a pointer to _struct_ncs_dom.id in the STRUCT_NCS_DOM category. ; _item.name '_struct_ncs_dom_lim.dom_id' _item.mandatory_code yes save_ save__struct_ncs_dom_lim.end_label_alt_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain ends. This data item is a pointer to _atom_sites_alt.id in the ATOM_SITES_ALT category. ; _item.name '_struct_ncs_dom_lim.end_label_alt_id' _item.mandatory_code yes save_ save__struct_ncs_dom_lim.end_label_asym_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain ends. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_struct_ncs_dom_lim.end_label_asym_id' _item.mandatory_code yes save_ save__struct_ncs_dom_lim.end_label_comp_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain ends. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_struct_ncs_dom_lim.end_label_comp_id' _item.mandatory_code yes save_ save__struct_ncs_dom_lim.end_label_seq_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain ends. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_struct_ncs_dom_lim.end_label_seq_id' _item.mandatory_code yes save_ save__struct_ncs_dom_lim.end_auth_asym_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain ends. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_struct_ncs_dom_lim.end_auth_asym_id' _item.mandatory_code no save_ save__struct_ncs_dom_lim.end_auth_comp_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain ends. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_struct_ncs_dom_lim.end_auth_comp_id' _item.mandatory_code no save_ save__struct_ncs_dom_lim.end_auth_seq_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain ends. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_struct_ncs_dom_lim.end_auth_seq_id' _item.mandatory_code no save_ #################### ## STRUCT_NCS_ENS ## #################### save_struct_ncs_ens _category.description ; Data items in the STRUCT_NCS_ENS category record information about ensembles of domains related by noncrystallographic symmetry. The point group of the ensemble when taken as a whole may be specified, as well as any special aspects of the ensemble that require description. ; _category.id struct_ncs_ens _category.mandatory_code no _category_key.name '_struct_ncs_ens.id' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on laboratory records for the collagen-like peptide, HYP-. ; ; _struct_ncs_ens.id en1 _struct_ncs_ens.details ; The ensemble represents the pseudo-twofold symmetry between domains d1 and d2. ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_ncs_ens.details _item_description.description ; A description of special aspects of the ensemble. ; _item.name '_struct_ncs_ens.details' _item.category_id struct_ncs_ens _item.mandatory_code no _item_type.code text _item_examples.case ; The ensemble has a slight translation between domains 1 and 4, but overall it can accurately be described as point group 222 ; save_ save__struct_ncs_ens.id _item_description.description ; The value of _struct_ncs_ens.id must uniquely identify a record in the STRUCT_NCS_ENS list. Note that this item need not be a number; it can be any unique identifier. ; loop_ _item.name _item.category_id _item.mandatory_code '_struct_ncs_ens.id' struct_ncs_ens yes '_struct_ncs_ens_gen.ens_id' struct_ncs_ens_gen yes loop_ _item_linked.child_name _item_linked.parent_name '_struct_ncs_ens_gen.ens_id' '_struct_ncs_ens.id' _item_type.code code save_ save__struct_ncs_ens.point_group _item_description.description ; The point group of the ensemble of structural elements related by one or more noncrystallographic symmetry operations. The relationships need not be precise; this data item is intended to give a rough description of the noncrystallographic symmetry relationships. ; _item.name '_struct_ncs_ens.point_group' _item.category_id struct_ncs_ens _item.mandatory_code no _item_type.code line loop_ _item_examples.case '3' '422' 'non-proper' save_ ######################## ## STRUCT_NCS_ENS_GEN ## ######################## save_struct_ncs_ens_gen _category.description ; Data items in the STRUCT_NCS_ENS_GEN category list domains related by a noncrystallographic symmetry operation and identify the operator. ; _category.id struct_ncs_ens_gen _category.mandatory_code no loop_ _category_key.name '_struct_ncs_ens_gen.ens_id' '_struct_ncs_ens_gen.dom_id_1' '_struct_ncs_ens_gen.dom_id_2' '_struct_ncs_ens_gen.oper_id' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on laboratory records for the collagen-like peptide, HYP-. ; ; _struct_ncs_ens_gen.dom_id_1 d1 _struct_ncs_ens_gen.dom_id_2 d2 _struct_ncs_ens_gen.ens_id en1 _struct_ncs_ens_gen.oper_id ncsop1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_ncs_ens_gen.dom_id_1 _item_description.description ; The identifier for the domain that will remain unchanged by the transformation operator. This data item is a pointer to _struct_ncs_dom.id in the STRUCT_NCS_DOM category. ; _item.name '_struct_ncs_ens_gen.dom_id_1' _item.mandatory_code yes save_ save__struct_ncs_ens_gen.dom_id_2 _item_description.description ; The identifier for the domain that will be transformed by application of the transformation operator. This data item is a pointer to _struct_ncs_dom.id in the STRUCT_NCS_DOM category. ; _item.name '_struct_ncs_ens_gen.dom_id_2' _item.mandatory_code yes save_ save__struct_ncs_ens_gen.ens_id _item_description.description ; This data item is a pointer to _struct_ncs_ens.id in the STRUCT_NCS_ENS category. ; _item.name '_struct_ncs_ens_gen.ens_id' _item.mandatory_code yes save_ save__struct_ncs_ens_gen.oper_id _item_description.description ; This data item is a pointer to _struct_ncs_oper.id in the STRUCT_NCS_OPER category. ; _item.name '_struct_ncs_ens_gen.oper_id' _item.mandatory_code yes save_ ##################### ## STRUCT_NCS_OPER ## ##################### save_struct_ncs_oper _category.description ; Data items in the STRUCT_NCS_OPER category describe the noncrystallographic symmetry operations. Each operator is specified as a matrix and a subsequent translation vector. Operators need not represent proper rotations. ; _category.id struct_ncs_oper _category.mandatory_code no _category_key.name '_struct_ncs_oper.id' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on laboratory records for the protein NS1. ; ; _struct_ncs_oper.id ncsop1 _struct_ncs_oper.code given _struct_ncs_oper.matrix[1][1] 0.247 _struct_ncs_oper.matrix[1][2] 0.935 _struct_ncs_oper.matrix[1][3] 0.256 _struct_ncs_oper.matrix[2][1] 0.929 _struct_ncs_oper.matrix[2][2] 0.153 _struct_ncs_oper.matrix[2][3] 0.337 _struct_ncs_oper.matrix[3][1] 0.276 _struct_ncs_oper.matrix[3][2] 0.321 _struct_ncs_oper.matrix[3][3] -0.906 _struct_ncs_oper.vector[1] -8.253 _struct_ncs_oper.vector[2] -11.743 _struct_ncs_oper.vector[3] -1.782 _struct_ncs_oper.details ; Matrix and translation vector for pseudo-twofold operation. ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_ncs_oper.code _item_description.description ; A code to indicate whether this operator describes a relationship between coordinates all of which are given in the data block (in which case the value of code is 'given'), or whether the operator is used to generate new coordinates from those that are given in the data block (in which case the value of code is 'generate'). ; _item.name '_struct_ncs_oper.code' _item.category_id struct_ncs_oper _item.mandatory_code no _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail given ; operator relates coordinates given in the data block ; generate ; operator generates new coordinates from those given in the data block ; save_ save__struct_ncs_oper.details _item_description.description ; A description of special aspects of the noncrystallographic symmetry operator. ; _item.name '_struct_ncs_oper.details' _item.category_id struct_ncs_oper _item.mandatory_code no _item_type.code text _item_examples.case ; The operation is given as a precise threefold rotation, despite the fact the best rms fit between domain 1 and domain 2 yields a rotation of 119.7 degrees and a translation of 0.13 angstroms. ; save_ save__struct_ncs_oper.id _item_description.description ; The value of _struct_ncs_oper.id must uniquely identify a record in the STRUCT_NCS_OPER list. Note that this item need not be a number; it can be any unique identifier. ; loop_ _item.name _item.category_id _item.mandatory_code '_struct_ncs_oper.id' struct_ncs_oper yes '_struct_ncs_ens_gen.oper_id' struct_ncs_ens_gen yes loop_ _item_linked.child_name _item_linked.parent_name '_struct_ncs_ens_gen.oper_id' '_struct_ncs_oper.id' _item_type.code code save_ save__struct_ncs_oper.matrix[1][1] _item_description.description ; The [1][1] element of the 3x3 matrix component of a noncrystallographic symmetry operation. ; _item.name '_struct_ncs_oper.matrix[1][1]' _item.category_id struct_ncs_oper _item.mandatory_code no _item_sub_category.id matrix _item_type.code float save_ save__struct_ncs_oper.matrix[1][2] _item_description.description ; The [1][2] element of the 3x3 matrix component of a noncrystallographic symmetry operation. ; _item.name '_struct_ncs_oper.matrix[1][2]' _item.category_id struct_ncs_oper _item.mandatory_code no _item_sub_category.id matrix _item_type.code float save_ save__struct_ncs_oper.matrix[1][3] _item_description.description ; The [1][3] element of the 3x3 matrix component of a noncrystallographic symmetry operation. ; _item.name '_struct_ncs_oper.matrix[1][3]' _item.category_id struct_ncs_oper _item.mandatory_code no _item_sub_category.id matrix _item_type.code float save_ save__struct_ncs_oper.matrix[2][1] _item_description.description ; The [2][1] element of the 3x3 matrix component of a noncrystallographic symmetry operation. ; _item.name '_struct_ncs_oper.matrix[2][1]' _item.category_id struct_ncs_oper _item.mandatory_code no _item_sub_category.id matrix _item_type.code float save_ save__struct_ncs_oper.matrix[2][2] _item_description.description ; The [2][2] element of the 3x3 matrix component of a noncrystallographic symmetry operation. ; _item.name '_struct_ncs_oper.matrix[2][2]' _item.category_id struct_ncs_oper _item.mandatory_code no _item_sub_category.id matrix _item_type.code float save_ save__struct_ncs_oper.matrix[2][3] _item_description.description ; The [2][3] element of the 3x3 matrix component of a noncrystallographic symmetry operation. ; _item.name '_struct_ncs_oper.matrix[2][3]' _item.category_id struct_ncs_oper _item.mandatory_code no _item_sub_category.id matrix _item_type.code float save_ save__struct_ncs_oper.matrix[3][1] _item_description.description ; The [3][1] element of the 3x3 matrix component of a noncrystallographic symmetry operation. ; _item.name '_struct_ncs_oper.matrix[3][1]' _item.category_id struct_ncs_oper _item.mandatory_code no _item_sub_category.id matrix _item_type.code float save_ save__struct_ncs_oper.matrix[3][2] _item_description.description ; The [3][2] element of the 3x3 matrix component of a noncrystallographic symmetry operation. ; _item.name '_struct_ncs_oper.matrix[3][2]' _item.category_id struct_ncs_oper _item.mandatory_code no _item_sub_category.id matrix _item_type.code float save_ save__struct_ncs_oper.matrix[3][3] _item_description.description ; The [3][3] element of the 3x3 matrix component of a noncrystallographic symmetry operation. ; _item.name '_struct_ncs_oper.matrix[3][3]' _item.category_id struct_ncs_oper _item.mandatory_code no _item_sub_category.id matrix _item_type.code float save_ save__struct_ncs_oper.vector[1] _item_description.description ; The [1] element of the three-element vector component of a noncrystallographic symmetry operation. ; _item.name '_struct_ncs_oper.vector[1]' _item.category_id struct_ncs_oper _item.mandatory_code no # _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__struct_ncs_oper.vector[2] _item_description.description ; The [2] element of the three-element vector component of a noncrystallographic symmetry operation. ; _item.name '_struct_ncs_oper.vector[2]' _item.category_id struct_ncs_oper _item.mandatory_code no # _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__struct_ncs_oper.vector[3] _item_description.description ; The [3] element of the three-element vector component of a noncrystallographic symmetry operation. ; _item.name '_struct_ncs_oper.vector[3]' _item.category_id struct_ncs_oper _item.mandatory_code no # _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ ################ ## STRUCT_REF ## ################ save_struct_ref _category.description ; Data items in the STRUCT_REF category allow the author of a data block to relate the entities or biological units described in the data block to information archived in external databases. For references to the sequence of a polymer, the value of the data item _struct_ref.seq_align is used to indicate whether the correspondence between the sequence of the entity or biological unit in the data block and the sequence in the referenced database entry is 'complete' or 'partial'. If this value is 'partial', the region (or regions) of the alignment may be delimited using data items in the STRUCT_REF_SEQ category. Similarly, the value of _struct_ref.seq_dif is used to indicate whether the two sequences contain point differences. If the value is 'yes', the differences may be identified and annotated using data items in the STRUCT_REF_SEQ_DIF category. ; _category.id struct_ref _category.mandatory_code no _category_key.name '_struct_ref.id' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _struct_ref.id _struct_ref.entity_id _struct_ref.biol_id _struct_ref.db_name _struct_ref.db_code _struct_ref.seq_align _struct_ref.seq_dif _struct_ref.details 1 1 . 'Genbank' '12345' 'entire' 'yes' . 2 . 2 'PDB' '1ABC' . . ; The structure of the closely related compound, isobutyryl-pepstatin (pepstatin A) in complex with rhizopuspepsin ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_ref.biol_id _item_description.description ; This data item is a pointer to _struct_biol.id in the STRUCT_BIOL category. ; _item.name '_struct_ref.biol_id' _item.mandatory_code no save_ save__struct_ref.db_code _item_description.description ; The code for this entity or biological unit or for a closely related entity or biological unit in the named database. ; _item.name '_struct_ref.db_code' _item.category_id struct_ref _item.mandatory_code yes _item_type.code line loop_ _item_examples.case '1ABC' 'ABCDEF' save_ save__struct_ref.db_name _item_description.description ; The name of the database containing reference information about this entity or biological unit. ; _item.name '_struct_ref.db_name' _item.category_id struct_ref _item.mandatory_code yes _item_type.code line loop_ _item_examples.case 'PDB' 'CSD' 'Genbank' save_ save__struct_ref.details _item_description.description ; A description of special aspects of the relationship between the entity or biological unit described in the data block and that in the referenced database entry. ; _item.name '_struct_ref.details' _item.category_id struct_ref _item.mandatory_code no _item_type.code text save_ save__struct_ref.entity_id _item_description.description ; This data item is a pointer to _entity.id in the ENTITY category. ; _item.name '_struct_ref.entity_id' _item.mandatory_code yes save_ save__struct_ref.id _item_description.description ; The value of _struct_ref.id must uniquely identify a record in the STRUCT_REF list. Note that this item need not be a number; it can be any unique identifier. ; loop_ _item.name _item.category_id _item.mandatory_code '_struct_ref.id' struct_ref yes '_struct_ref_seq.ref_id' struct_ref_seq yes loop_ _item_linked.child_name _item_linked.parent_name '_struct_ref_seq.ref_id' '_struct_ref.id' _item_type.code code save_ save__struct_ref.seq_align _item_description.description ; A flag to indicate the scope of the alignment between the sequence of the entity or biological unit described in the data block and that in the referenced database entry. 'entire' indicates that alignment spans the entire length of both sequences (although point differences may occur and can be annotated using the data items in the STRUCT_REF_SEQ_DIF category). 'partial' indicates a partial alignment. The region (or regions) of the alignment may be delimited using data items in the STRUCT_REF_SEQ category. This data item may also take the value '.', indicating that the reference is not to a sequence. ; _item.name '_struct_ref.seq_align' _item.category_id struct_ref _item.mandatory_code no _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail complete 'alignment is complete' partial 'alignment is partial' . 'reference is not to a sequence' save_ save__struct_ref.seq_dif _item_description.description ; A flag to indicate the presence ('yes') or absence ('no') of point differences between the sequence of the entity or biological unit described in the data block and that in the referenced database entry. This data item may also take the value '.', indicating that the reference is not to a sequence. ; _item.name '_struct_ref.seq_dif' _item.category_id struct_ref _item.mandatory_code no _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail no 'there are no point differences' n 'abbreviation for "no"' yes 'there are point difference' y 'abbreviation for "yes"' . 'reference is not to a sequence' save_ #################### ## STRUCT_REF_SEQ ## #################### save_struct_ref_seq _category.description ; Data items in the STRUCT_REF_SEQ category provide a mechanism for indicating and annotating a region (or regions) of alignment between the sequence of an entity or biological unit described in the data block and the sequence in the referenced database entry. ; _category.id struct_ref_seq _category.mandatory_code no _category_key.name '_struct_ref_seq.align_id' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on the sequence alignment of CHER from M. xantus (36 to 288) and CHER from S. typhimurium (18 to 276). ; ; _struct_ref_seq.align_id alg1 _struct_ref_seq.ref_id seqdb1 _struct_ref_seq.seq_align_beg 36 _struct_ref_seq.seq_align_end 288 _struct_ref_seq.db_align_beg 18 _struct_ref_seq.db_align_end 276 _struct_ref_seq.details ; The alignment contains 3 gaps larger than 2 residues ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_ref_seq.align_id _item_description.description ; The value of _struct_ref_seq.align_id must uniquely identify a record in the STRUCT_REF_SEQ list. Note that this item need not be a number; it can be any unique identifier. ; loop_ _item.name _item.category_id _item.mandatory_code '_struct_ref_seq.align_id' struct_ref_seq yes '_struct_ref_seq_dif.align_id' struct_ref_seq_dif yes loop_ _item_linked.child_name _item_linked.parent_name '_struct_ref_seq_dif.align_id' '_struct_ref_seq.align_id' _item_type.code code save_ save__struct_ref_seq.db_align_beg _item_description.description ; The sequence position in the referenced database entry at which the alignment begins. ; _item.name '_struct_ref_seq.db_align_beg' _item.mandatory_code yes # loop_ # _item_range.maximum # _item_range.minimum . 1 # 1 1 _item_type.code int save_ save__struct_ref_seq.db_align_end _item_description.description ; The sequence position in the referenced database entry at which the alignment ends. ; _item.name '_struct_ref_seq.db_align_end' _item.mandatory_code yes # loop_ # _item_range.maximum # _item_range.minimum . 1 # 1 1 _item_type.code int save_ save__struct_ref_seq.details _item_description.description ; A description of special aspects of the sequence alignment. ; _item.name '_struct_ref_seq.details' _item.category_id struct_ref_seq _item.mandatory_code no _item_type.code text save_ save__struct_ref_seq.ref_id _item_description.description ; This data item is a pointer to _struct_ref.id in the STRUCT_REF category. ; _item.name '_struct_ref_seq.ref_id' _item.mandatory_code yes save_ save__struct_ref_seq.seq_align_beg _item_description.description ; The sequence position in the entity or biological unit described in the data block at which the alignment begins. This data item is a pointer to _entity_poly_seq.num in the ENTITY_POLY_SEQ category. ; _item.name '_struct_ref_seq.seq_align_beg' _item.mandatory_code yes save_ save__struct_ref_seq.seq_align_end _item_description.description ; The sequence position in the entity or biological unit described in the data block at which the alignment ends. This data item is a pointer to _entity_poly_seq.num in the ENTITY_POLY_SEQ category. ; _item.name '_struct_ref_seq.seq_align_end' _item.mandatory_code yes save_ ######################## ## STRUCT_REF_SEQ_DIF ## ######################## save_struct_ref_seq_dif _category.description ; Data items in the STRUCT_REF_SEQ_DIF category provide a mechanism for indicating and annotating point differences between the sequence of the entity or biological unit described in the data block and the sequence of the referenced database entry. ; _category.id struct_ref_seq_dif _category.mandatory_code no _category_key.name '_struct_ref_seq_dif.pdbx_ordinal' # # loop_ # _category_key.name '_struct_ref_seq_dif.align_id' # '_struct_ref_seq_dif.seq_num' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on laboratory records for CAP-DNA complex. ; ; _struct_ref_seq_dif.pdbx_ordinal 1 _struct_ref_seq_dif.align_id algn2 _struct_ref_seq_dif.seq_num 181 _struct_ref_seq_dif.db_mon_id GLU _struct_ref_seq_dif.mon_id PHE _struct_ref_seq_dif.details ; A point mutation was introduced in the CAP at position 181 substituting PHE for GLU. ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_ref_seq_dif.align_id _item_description.description ; This data item is a pointer to _struct_ref_seq.align_id in the STRUCT_REF_SEQ category. ; _item.name '_struct_ref_seq_dif.align_id' _item.mandatory_code yes save_ save__struct_ref_seq_dif.db_mon_id _item_description.description ; The monomer type found at this position in the referenced database entry. This data item is a pointer to _chem_comp.id in the CHEM_COMP category. ; _item.name '_struct_ref_seq_dif.db_mon_id' _item.mandatory_code yes save_ save__struct_ref_seq_dif.details _item_description.description ; A description of special aspects of the point differences between the sequence of the entity or biological unit described in the data block and that in the referenced database entry. ; _item.name '_struct_ref_seq_dif.details' _item.category_id struct_ref_seq_dif _item.mandatory_code no _item_type.code text save_ save__struct_ref_seq_dif.mon_id _item_description.description ; The monomer type found at this position in the sequence of the entity or biological unit described in this data block. This data item is a pointer to _chem_comp.id in the CHEM_COMP category. ; _item.name '_struct_ref_seq_dif.mon_id' _item.mandatory_code yes save_ save__struct_ref_seq_dif.seq_num _item_description.description ; This data item is a pointer to _entity_poly_seq.num in the ENTITY_POLY_SEQ category. ; _item.name '_struct_ref_seq_dif.seq_num' _item.mandatory_code yes save_ ################## ## STRUCT_SHEET ## ################## save_struct_sheet _category.description ; Data items in the STRUCT_SHEET category record details about the beta-sheets. ; _category.id struct_sheet _category.mandatory_code no _category_key.name '_struct_sheet.id' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - simple beta-barrel. N O N O N O N O N O N O 10--11--12--13--14--15--16--17--18--19--20 strand_a N O N O N O N O N O / \ / \ / \ / \ / \ N O N O N O N O N O N O 30--31--32--33--34--35--36--37--38--39--40 strand_b N O N O N O N O N O / \ / \ / \ / \ / \ N O N O N O N O N O N O 50--51--52--53--54--55--56--57--58--59--60 strand_c N O N O N O N O N O / \ / \ / \ / \ / \ N O N O N O N O N O N O 70--71--72--73--74--75--76--77--78--79--80 strand_d N O N O N O N O N O / \ / \ / \ / \ / \ N O N O N O N O N O N O 90--91--92--93--94--95--96--97--98--99-100 strand_e N O N O N O N O N O / \ / \ / \ / \ / \ N O N O N O N O N O N O 110-111-112-113-114-115-116-117-118-119-120 strand_f N O N O N O N O N O / \ / \ / \ / \ / \ N O N O N O N O N O N O 130-131-132-133-134-135-136-137-138-139-140 strand_g N O N O N O N O N O / \ / \ / \ / \ / \ N O N O N O N O N O N O 150-151-152-153-154-155-156-157-158-159-160 strand_h N O N O N O N O N O / \ / \ / \ / \ / \ ; ; _struct_sheet.id sheet_1 _struct_sheet.type 'beta-barrel' _struct_sheet.number_strands 8 _struct_sheet.details . ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - five stranded mixed-sense sheet with one two-piece strand. N O N O N O N O -10--11--12--13--14--15--16--17--18-> strand_a N O N O N O N O N O | | | | | | | | | | O N O N O N O N O N <-119-118-117-116-115-114-113-112-111-110- strand_b O N O N O N O N O N \ / \ / \ / \ / \ O N O N O N O N O N O N <-41--40--39--38--37--36--35--34--33--32--31--30- strand_c O N O N O N O N O N O N | | | | | | | | | | | | N O N O N O N O N O N O strand_d1 -50--51--52-> -90--91--92--93--95--95--96--97-> strand_d2 N O N O N O N O N O | | | | | | | | | | | | O N O N O N O N O N O N <-80--79--78--77--76--75--74--73--72--71--70- strand_e O N O N O N O N O N ; ; _struct_sheet.id sheet_2 _struct_sheet.type 'five stranded, mixed-sense' _struct_sheet.number_strands 5 _struct_sheet.details 'strand_d is in two pieces' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_sheet.details _item_description.description ; A description of special aspects of the beta-sheet. ; _item.name '_struct_sheet.details' _item.category_id struct_sheet _item.mandatory_code no _item_type.code text save_ save__struct_sheet.id _item_description.description ; The value of _struct_sheet.id must uniquely identify a record in the STRUCT_SHEET list. Note that this item need not be a number; it can be any unique identifier. ; loop_ _item.name _item.category_id _item.mandatory_code '_struct_sheet.id' struct_sheet yes '_struct_sheet_hbond.sheet_id' struct_sheet_hbond yes '_struct_sheet_order.sheet_id' struct_sheet_order yes '_struct_sheet_range.sheet_id' struct_sheet_range yes '_struct_sheet_topology.sheet_id' struct_sheet_topology yes loop_ _item_linked.child_name _item_linked.parent_name '_struct_sheet_hbond.sheet_id' '_struct_sheet.id' '_struct_sheet_order.sheet_id' '_struct_sheet.id' '_struct_sheet_range.sheet_id' '_struct_sheet.id' '_struct_sheet_topology.sheet_id' '_struct_sheet.id' _item_type.code code save_ save__struct_sheet.number_strands _item_description.description ; The number of strands in the sheet. If a given range of residues bulges out from the strands, it is still counted as one strand. If a strand is composed of two different regions of polypeptide, it is still counted as one strand, as long as the proper hydrogen- bonding connections are made to adjacent strands. ; _item.name '_struct_sheet.number_strands' _item.category_id struct_sheet _item.mandatory_code no _item_type.code int save_ save__struct_sheet.type _item_description.description ; A simple descriptor for the type of the sheet. ; _item.name '_struct_sheet.type' _item.category_id struct_sheet _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'jelly-roll' 'Rossmann fold' 'beta barrel' save_ ######################## ## STRUCT_SHEET_HBOND ## ######################## save_struct_sheet_hbond _category.description ; Data items in the STRUCT_SHEET_HBOND category record details about the hydrogen bonding between residue ranges in a beta- sheet. It is necessary to treat hydrogen bonding independently of the designation of ranges, because the hydrogen bonding may begin in different places for the interactions of a given strand with the one preceding it and the one following it in the sheet. ; _category.id struct_sheet_hbond _category.mandatory_code no loop_ _category_key.name '_struct_sheet_hbond.sheet_id' '_struct_sheet_hbond.range_id_1' '_struct_sheet_hbond.range_id_2' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - simple beta-barrel. ; ; loop_ _struct_sheet_hbond.sheet_id _struct_sheet_hbond.range_id_1 _struct_sheet_hbond.range_id_2 _struct_sheet_hbond.range_1_beg_label_seq_id _struct_sheet_hbond.range_1_beg_label_atom_id _struct_sheet_hbond.range_2_beg_label_seq_id _struct_sheet_hbond.range_2_beg_label_atom_id _struct_sheet_hbond.range_1_end_label_seq_id _struct_sheet_hbond.range_1_end_label_atom_id _struct_sheet_hbond.range_2_end_label_seq_id _struct_sheet_hbond.range_2_end_label_atom_id sheet_1 strand_a strand_b 11 N 30 O 19 O 40 N sheet_1 strand_b strand_c 31 N 50 O 39 O 60 N sheet_1 strand_c strand_d 51 N 70 O 59 O 80 N sheet_1 strand_d strand_e 71 N 90 O 89 O 100 N sheet_1 strand_e strand_f 91 N 110 O 99 O 120 N sheet_1 strand_f strand_g 111 N 130 O 119 O 140 N sheet_1 strand_g strand_h 131 N 150 O 139 O 160 N sheet_1 strand_h strand_a 151 N 10 O 159 O 180 N ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - five stranded mixed-sense sheet with one two-piece strand. ; ; loop_ _struct_sheet_hbond.sheet_id _struct_sheet_hbond.range_id_1 _struct_sheet_hbond.range_id_2 _struct_sheet_hbond.range_1_beg_label_seq_id _struct_sheet_hbond.range_1_beg_label_atom_id _struct_sheet_hbond.range_2_beg_label_seq_id _struct_sheet_hbond.range_2_beg_label_atom_id _struct_sheet_hbond.range_1_end_label_seq_id _struct_sheet_hbond.range_1_end_label_atom_id _struct_sheet_hbond.range_2_end_label_seq_id _struct_sheet_hbond.range_2_end_label_atom_id sheet_2 strand_a strand_b 20 N 119 O 18 O 111 N sheet_2 strand_b strand_c 110 N 33 O 118 N 41 O sheet_2 strand_c strand_d1 38 N 52 O 40 O 50 N sheet_2 strand_c strand_d2 30 N 96 O 36 O 90 N sheet_2 strand_d1 strand_e 51 N 80 O 51 O 80 N sheet_2 strand_d2 strand_e 91 N 76 O 97 O 70 N ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_sheet_hbond.range_1_beg_label_atom_id _item_description.description ; A component of the identifier for the residue for the first partner of the first hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.label_atom_id in the ATOM_SITE category. ; _item.name '_struct_sheet_hbond.range_1_beg_label_atom_id' _item.mandatory_code yes save_ save__struct_sheet_hbond.range_1_beg_label_seq_id _item_description.description ; A component of the identifier for the residue for the first partner of the first hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_struct_sheet_hbond.range_1_beg_label_seq_id' _item.mandatory_code yes save_ save__struct_sheet_hbond.range_1_end_label_atom_id _item_description.description ; A component of the identifier for the residue for the first partner of the last hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.label_atom_id in the ATOM_SITE category. ; _item.name '_struct_sheet_hbond.range_1_end_label_atom_id' _item.mandatory_code yes save_ save__struct_sheet_hbond.range_1_end_label_seq_id _item_description.description ; A component of the identifier for the residue for the first partner of the last hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_struct_sheet_hbond.range_1_end_label_seq_id' _item.mandatory_code yes save_ save__struct_sheet_hbond.range_2_beg_label_atom_id _item_description.description ; A component of the identifier for the residue for the second partner of the first hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.label_atom_id in the ATOM_SITE category. ; _item.name '_struct_sheet_hbond.range_2_beg_label_atom_id' _item.mandatory_code yes save_ save__struct_sheet_hbond.range_2_beg_label_seq_id _item_description.description ; A component of the identifier for the residue for the second partner of the first hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_struct_sheet_hbond.range_2_beg_label_seq_id' _item.mandatory_code yes save_ save__struct_sheet_hbond.range_2_end_label_atom_id _item_description.description ; A component of the identifier for the residue for the second partner of the last hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.label_atom_id in the ATOM_SITE category. ; _item.name '_struct_sheet_hbond.range_2_end_label_atom_id' _item.mandatory_code yes save_ save__struct_sheet_hbond.range_2_end_label_seq_id _item_description.description ; A component of the identifier for the residue for the second partner of the last hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_struct_sheet_hbond.range_2_end_label_seq_id' _item.mandatory_code yes save_ save__struct_sheet_hbond.range_1_beg_auth_atom_id _item_description.description ; A component of the identifier for the residue for the first partner of the first hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.auth_atom_id in the ATOM_SITE category. ; _item.name '_struct_sheet_hbond.range_1_beg_auth_atom_id' _item.mandatory_code no save_ save__struct_sheet_hbond.range_1_beg_auth_seq_id _item_description.description ; A component of the identifier for the residue for the first partner of the first hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_struct_sheet_hbond.range_1_beg_auth_seq_id' _item.mandatory_code no save_ save__struct_sheet_hbond.range_1_end_auth_atom_id _item_description.description ; A component of the identifier for the residue for the first partner of the last hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.auth_atom_id in the ATOM_SITE category. ; _item.name '_struct_sheet_hbond.range_1_end_auth_atom_id' _item.mandatory_code no save_ save__struct_sheet_hbond.range_1_end_auth_seq_id _item_description.description ; A component of the identifier for the residue for the first partner of the last hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_struct_sheet_hbond.range_1_end_auth_seq_id' _item.mandatory_code no save_ save__struct_sheet_hbond.range_2_beg_auth_atom_id _item_description.description ; A component of the identifier for the residue for the second partner of the first hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.auth_atom_id in the ATOM_SITE category. ; _item.name '_struct_sheet_hbond.range_2_beg_auth_atom_id' _item.mandatory_code no save_ save__struct_sheet_hbond.range_2_beg_auth_seq_id _item_description.description ; A component of the identifier for the residue for the second partner of the first hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_struct_sheet_hbond.range_2_beg_auth_seq_id' _item.mandatory_code no save_ save__struct_sheet_hbond.range_2_end_auth_atom_id _item_description.description ; A component of the identifier for the residue for the second partner of the last hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.auth_atom_id in the ATOM_SITE category. ; _item.name '_struct_sheet_hbond.range_2_end_auth_atom_id' _item.mandatory_code no save_ save__struct_sheet_hbond.range_2_end_auth_seq_id _item_description.description ; A component of the identifier for the residue for the second partner of the last hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_struct_sheet_hbond.range_2_end_auth_seq_id' _item.mandatory_code no save_ save__struct_sheet_hbond.range_id_1 _item_description.description ; This data item is a pointer to _struct_sheet_range.id in the STRUCT_SHEET_RANGE category. ; _item.name '_struct_sheet_hbond.range_id_1' _item.mandatory_code yes save_ save__struct_sheet_hbond.range_id_2 _item_description.description ; This data item is a pointer to _struct_sheet_range.id in the STRUCT_SHEET_RANGE category. ; _item.name '_struct_sheet_hbond.range_id_2' _item.mandatory_code yes save_ save__struct_sheet_hbond.sheet_id _item_description.description ; This data item is a pointer to _struct_sheet.id in the STRUCT_SHEET category. ; _item.name '_struct_sheet_hbond.sheet_id' _item.mandatory_code yes save_ ######################## ## STRUCT_SHEET_ORDER ## ######################## save_struct_sheet_order _category.description ; Data items in the STRUCT_SHEET_ORDER category record details about the order of the residue ranges that form a beta-sheet. All order links are pairwise and the specified pairs are assumed to be adjacent to one another in the sheet. These data items are an alternative to the STRUCT_SHEET_TOPOLOGY data items and they allow all manner of sheets to be described. ; _category.id struct_sheet_order _category.mandatory_code no loop_ _category_key.name '_struct_sheet_order.sheet_id' '_struct_sheet_order.range_id_1' '_struct_sheet_order.range_id_2' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - simple beta-barrel. ; ; loop_ _struct_sheet_order.sheet_id _struct_sheet_order.range_id_1 _struct_sheet_order.range_id_2 _struct_sheet_order.offset _struct_sheet_order.sense sheet_1 strand_a strand_b +1 parallel sheet_1 strand_b strand_c +1 parallel sheet_1 strand_c strand_d +1 parallel sheet_1 strand_d strand_e +1 parallel sheet_1 strand_e strand_f +1 parallel sheet_1 strand_f strand_g +1 parallel sheet_1 strand_g strand_h +1 parallel sheet_1 strand_h strand_a +1 parallel ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - five stranded mixed-sense sheet with one two-piece strand. ; ; loop_ _struct_sheet_order.sheet_id _struct_sheet_order.range_id_1 _struct_sheet_order.range_id_2 _struct_sheet_order.offset _struct_sheet_order.sense sheet_2 strand_a strand_b +1 anti-parallel sheet_2 strand_b strand_c +1 parallel sheet_2 strand_c strand_d1 +1 anti-parallel sheet_2 strand_c strand_d2 +1 anti-parallel sheet_2 strand_d1 strand_e +1 anti-parallel sheet_2 strand_d2 strand_e +1 anti-parallel ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_sheet_order.offset _item_description.description ; Designates the relative position in the sheet, plus or minus, of the second residue range to the first. ; _item.name '_struct_sheet_order.offset' _item.category_id struct_sheet_order _item.mandatory_code no _item_type.code int save_ save__struct_sheet_order.range_id_1 _item_description.description ; This data item is a pointer to _struct_sheet_range.id in the STRUCT_SHEET_RANGE category. ; _item.name '_struct_sheet_order.range_id_1' _item.mandatory_code yes save_ save__struct_sheet_order.range_id_2 _item_description.description ; This data item is a pointer to _struct_sheet_range.id in the STRUCT_SHEET_RANGE category. ; _item.name '_struct_sheet_order.range_id_2' _item.mandatory_code yes save_ save__struct_sheet_order.sense _item_description.description ; A flag to indicate whether the two designated residue ranges are parallel or antiparallel to one another. ; _item.name '_struct_sheet_order.sense' _item.category_id struct_sheet_order _item.mandatory_code no _item_type.code ucode loop_ _item_enumeration.value 'parallel' 'anti-parallel' save_ save__struct_sheet_order.sheet_id _item_description.description ; This data item is a pointer to _struct_sheet.id in the STRUCT_SHEET category. ; _item.name '_struct_sheet_order.sheet_id' _item.mandatory_code yes save_ ######################## ## STRUCT_SHEET_RANGE ## ######################## save_struct_sheet_range _category.description ; Data items in the STRUCT_SHEET_RANGE category record details about the residue ranges that form a beta-sheet. Residues are included in a range if they made beta-sheet-type hydrogen-bonding interactions with at least one adjacent strand and if there are at least two residues in the range. ; _category.id struct_sheet_range _category.mandatory_code no loop_ _category_key.name '_struct_sheet_range.sheet_id' '_struct_sheet_range.id' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - simple beta-barrel. ; ; loop_ _struct_sheet_range.sheet_id _struct_sheet_range.id _struct_sheet_range.beg_label_comp_id _struct_sheet_range.beg_label_asym_id _struct_sheet_range.beg_label_seq_id _struct_sheet_range.end_label_comp_id _struct_sheet_range.end_label_asym_id _struct_sheet_range.end_label_seq_id _struct_sheet_range.symmetry sheet_1 strand_a ala A 20 ala A 30 1_555 sheet_1 strand_b ala A 40 ala A 50 1_555 sheet_1 strand_c ala A 60 ala A 70 1_555 sheet_1 strand_d ala A 80 ala A 90 1_555 sheet_1 strand_e ala A 100 ala A 110 1_555 sheet_1 strand_f ala A 120 ala A 130 1_555 sheet_1 strand_g ala A 140 ala A 150 1_555 sheet_1 strand_h ala A 160 ala A 170 1_555 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - five stranded mixed-sense sheet with one two-piece strand. ; ; loop_ _struct_sheet_range.sheet_id _struct_sheet_range.id _struct_sheet_range.beg_label_comp_id _struct_sheet_range.beg_label_asym_id _struct_sheet_range.beg_label_seq_id _struct_sheet_range.end_label_comp_id _struct_sheet_range.end_label_asym_id _struct_sheet_range.end_label_seq_id _struct_sheet_range.symmetry sheet_2 strand_a ala A 10 ala A 18 1_555 sheet_2 strand_b ala A 110 ala A 119 1_555 sheet_2 strand_c ala A 30 ala A 41 1_555 sheet_2 strand_d1 ala A 50 ala A 52 1_555 sheet_2 strand_d2 ala A 90 ala A 97 1_555 sheet_2 strand_e ala A 70 ala A 80 1_555 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_sheet_range.beg_label_asym_id _item_description.description ; A component of the identifier for the residue at which the beta-sheet range begins. This data item is a pointer to _struct_asym.id in the STRUCT_ASYM category. ; _item.name '_struct_sheet_range.beg_label_asym_id' _item.mandatory_code yes save_ save__struct_sheet_range.beg_label_comp_id _item_description.description ; A component of the identifier for the residue at which the beta-sheet range begins. This data item is a pointer to _chem_comp.id in the CHEM_COMP category. ; _item.name '_struct_sheet_range.beg_label_comp_id' _item.mandatory_code yes save_ save__struct_sheet_range.beg_label_seq_id _item_description.description ; A component of the identifier for the residue at which the beta-sheet range begins. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_struct_sheet_range.beg_label_seq_id' _item.mandatory_code yes save_ save__struct_sheet_range.end_label_asym_id _item_description.description ; A component of the identifier for the residue at which the beta-sheet range ends. This data item is a pointer to _struct_asym.id in the STRUCT_ASYM category. ; _item.name '_struct_sheet_range.end_label_asym_id' _item.mandatory_code yes save_ save__struct_sheet_range.end_label_comp_id _item_description.description ; A component of the identifier for the residue at which the beta-sheet range ends. This data item is a pointer to _chem_comp.id in the CHEM_COMP category. ; _item.name '_struct_sheet_range.end_label_comp_id' _item.mandatory_code yes save_ save__struct_sheet_range.end_label_seq_id _item_description.description ; A component of the identifier for the residue at which the beta-sheet range ends. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_struct_sheet_range.end_label_seq_id' _item.mandatory_code yes save_ save__struct_sheet_range.beg_auth_asym_id _item_description.description ; A component of the identifier for the residue at which the beta-sheet range begins. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_struct_sheet_range.beg_auth_asym_id' _item.mandatory_code no save_ save__struct_sheet_range.beg_auth_comp_id _item_description.description ; A component of the identifier for the residue at which the beta-sheet range begins. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_struct_sheet_range.beg_auth_comp_id' _item.mandatory_code no save_ save__struct_sheet_range.beg_auth_seq_id _item_description.description ; A component of the identifier for the residue at which the beta-sheet range begins. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_struct_sheet_range.beg_auth_seq_id' _item.mandatory_code no save_ save__struct_sheet_range.end_auth_asym_id _item_description.description ; A component of the identifier for the residue at which the beta-sheet range ends. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_struct_sheet_range.end_auth_asym_id' _item.mandatory_code no save_ save__struct_sheet_range.end_auth_comp_id _item_description.description ; A component of the identifier for the residue at which the beta-sheet range ends. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_struct_sheet_range.end_auth_comp_id' _item.mandatory_code no save_ save__struct_sheet_range.end_auth_seq_id _item_description.description ; A component of the identifier for the residue at which the beta-sheet range ends. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_struct_sheet_range.end_auth_seq_id' _item.mandatory_code no save_ save__struct_sheet_range.id _item_description.description ; The value of _struct_sheet_range.id must uniquely identify a range in a given sheet in the STRUCT_SHEET_RANGE list. Note that this item need not be a number; it can be any unique identifier. ; loop_ _item.name _item.category_id _item.mandatory_code '_struct_sheet_range.id' struct_sheet_range yes '_struct_sheet_hbond.range_id_1' struct_sheet_hbond yes '_struct_sheet_hbond.range_id_2' struct_sheet_hbond yes '_struct_sheet_order.range_id_1' struct_sheet_order yes '_struct_sheet_order.range_id_2' struct_sheet_order yes '_struct_sheet_topology.range_id_1' struct_sheet_topology yes '_struct_sheet_topology.range_id_2' struct_sheet_topology yes loop_ _item_linked.child_name _item_linked.parent_name '_struct_sheet_hbond.range_id_1' '_struct_sheet_range.id' '_struct_sheet_hbond.range_id_2' '_struct_sheet_range.id' '_struct_sheet_order.range_id_1' '_struct_sheet_range.id' '_struct_sheet_order.range_id_2' '_struct_sheet_range.id' '_struct_sheet_topology.range_id_1' '_struct_sheet_range.id' '_struct_sheet_topology.range_id_2' '_struct_sheet_range.id' _item_type.code code save_ save__struct_sheet_range.sheet_id _item_description.description ; This data item is a pointer to _struct_sheet.id in the STRUCT_SHEET category. ; _item.name '_struct_sheet_range.sheet_id' _item.mandatory_code yes save_ save__struct_sheet_range.symmetry _item_description.description ; Describes the symmetry operation that should be applied to the residues delimited by the start and end designators in order to generate the appropriate strand in this sheet. ; _item.name '_struct_sheet_range.symmetry' _item.category_id struct_sheet_range _item.mandatory_code no # _item_default.value 1_555 _item_type.code symop save_ ########################### ## STRUCT_SHEET_TOPOLOGY ## ########################### save_struct_sheet_topology _category.description ; Data items in the STRUCT_SHEET_TOPOLOGY category record details about the topology of the residue ranges that form a beta-sheet. All topology links are pairwise and the specified pairs are assumed to be successive in the amino-acid sequence. These data items are useful in describing various simple and complex folds, but they become inadequate when the strands in the sheet come from more than one chain. The STRUCT_SHEET_ORDER data items can be used to describe single- and multiple-chain-containing sheets. ; _category.id struct_sheet_topology _category.mandatory_code no loop_ _category_key.name '_struct_sheet_topology.sheet_id' '_struct_sheet_topology.range_id_1' '_struct_sheet_topology.range_id_2' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - simple beta-barrel. ; ; loop_ _struct_sheet_topology.sheet_id _struct_sheet_topology.range_id_1 _struct_sheet_topology.range_id_2 _struct_sheet_topology.offset _struct_sheet_topology.sense sheet_1 strand_a strand_b +1 parallel sheet_1 strand_b strand_c +1 parallel sheet_1 strand_c strand_d +1 parallel sheet_1 strand_d strand_e +1 parallel sheet_1 strand_e strand_f +1 parallel sheet_1 strand_f strand_g +1 parallel sheet_1 strand_g strand_h +1 parallel sheet_1 strand_h strand_a +1 parallel ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - five stranded mixed-sense sheet with one two-piece strand. ; ; loop_ _struct_sheet_topology.sheet_id _struct_sheet_topology.range_id_1 _struct_sheet_topology.range_id_2 _struct_sheet_topology.offset _struct_sheet_topology.sense sheet_2 strand_a strand_c +2 anti-parallel sheet_2 strand_c strand_d1 +1 anti-parallel sheet_2 strand_d1 strand_e +1 anti-parallel sheet_2 strand_e strand_d2 -1 anti-parallel sheet_2 strand_d2 strand_b -2 anti-parallel ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_sheet_topology.offset _item_description.description ; Designates the relative position in the sheet, plus or minus, of the second residue range to the first. ; _item.name '_struct_sheet_topology.offset' _item.category_id struct_sheet_topology _item.mandatory_code no _item_type.code int save_ save__struct_sheet_topology.range_id_1 _item_description.description ; This data item is a pointer to _struct_sheet_range.id in the STRUCT_SHEET_RANGE category. ; _item.name '_struct_sheet_topology.range_id_1' _item.mandatory_code yes save_ save__struct_sheet_topology.range_id_2 _item_description.description ; This data item is a pointer to _struct_sheet_range.id in the STRUCT_SHEET_RANGE category. ; _item.name '_struct_sheet_topology.range_id_2' _item.mandatory_code yes save_ save__struct_sheet_topology.sense _item_description.description ; A flag to indicate whether the two designated residue ranges are parallel or antiparallel to one another. ; _item.name '_struct_sheet_topology.sense' _item.category_id struct_sheet_topology _item.mandatory_code no _item_type.code ucode loop_ _item_enumeration.value 'parallel' 'anti-parallel' save_ save__struct_sheet_topology.sheet_id _item_description.description ; This data item is a pointer to _struct_sheet.id in the STRUCT_SHEET category. ; _item.name '_struct_sheet_topology.sheet_id' _item.mandatory_code yes save_ ################# ## STRUCT_SITE ## ################# save_struct_site _category.description ; Data items in the STRUCT_SITE category record details about portions of the structure that contribute to structurally relevant sites (e.g. active sites, substrate-binding subsites, metal-coordination sites). ; _category.id struct_site _category.mandatory_code no _category_key.name '_struct_site.id' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _struct_site.id _struct_site.details 'P2 site C' ; residues with a contact < 3.7 \%A to an atom in the P2 moiety of the inhibitor in the conformation with _struct_asym.id = C ; 'P2 site D' ; residues with a contact < 3.7 \%A to an atom in the P1 moiety of the inhibitor in the conformation with _struct_asym.id = D) ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_site.details _item_description.description ; A description of special aspects of the site. ; _item.name '_struct_site.details' _item.category_id struct_site _item.mandatory_code no _item_type.code text save_ save__struct_site.id _item_description.description ; The value of _struct_site.id must uniquely identify a record in the STRUCT_SITE list. Note that this item need not be a number; it can be any unique identifier. ; loop_ _item.name _item.category_id _item.mandatory_code '_struct_site.id' struct_site yes '_struct_site_gen.site_id' struct_site_gen yes '_struct_site_keywords.site_id' struct_site_keywords yes '_struct_site_view.site_id' struct_site_view yes loop_ _item_linked.child_name _item_linked.parent_name '_struct_site_gen.site_id' '_struct_site.id' '_struct_site_keywords.site_id' '_struct_site.id' '_struct_site_view.site_id' '_struct_site.id' _item_type.code line save_ ##################### ## STRUCT_SITE_GEN ## ##################### save_struct_site_gen _category.description ; Data items in the STRUCT_SITE_GEN category record details about the generation of portions of the structure that contribute to structurally relevant sites. ; _category.id struct_site_gen _category.mandatory_code no loop_ _category_key.name '_struct_site_gen.id' '_struct_site_gen.site_id' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _struct_site_gen.id _struct_site_gen.site_id _struct_site_gen.label_comp_id _struct_site_gen.label_asym_id _struct_site_gen.label_seq_id _struct_site_gen.symmetry _struct_site_gen.details 1 1 VAL A 32 1_555 . 2 1 ILE A 47 1_555 . 3 1 VAL A 82 1_555 . 4 1 ILE A 84 1_555 . 5 2 VAL B 232 1_555 . 6 2 ILE B 247 1_555 . 7 2 VAL B 282 1_555 . 8 2 ILE B 284 1_555 . ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_site_gen.details _item_description.description ; A description of special aspects of the symmetry generation of this portion of the structural site. ; _item.name '_struct_site_gen.details' _item.category_id struct_site_gen _item.mandatory_code no _item_type.code text _item_examples.case ; The zinc atom lies on a special position; application of symmetry elements to generate the insulin hexamer will generate excess zinc atoms, which must be removed by hand. ; save_ save__struct_site_gen.id _item_description.description ; The value of _struct_site_gen.id must uniquely identify a record in the STRUCT_SITE_GEN list. Note that this item need not be a number; it can be any unique identifier. ; _item.name '_struct_site_gen.id' _item.category_id struct_site_gen _item.mandatory_code yes _item_type.code line save_ save__struct_site_gen.label_alt_id _item_description.description ; A component of the identifier for participants in the site. This data item is a pointer to _atom_sites_alt.id in the ATOM_SITES_ALT category. ; _item.name '_struct_site_gen.label_alt_id' _item.mandatory_code yes save_ save__struct_site_gen.label_asym_id _item_description.description ; A component of the identifier for participants in the site. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_struct_site_gen.label_asym_id' _item.mandatory_code yes save_ save__struct_site_gen.label_atom_id _item_description.description ; A component of the identifier for participants in the site. This data item is a pointer to _chem_comp_atom.atom_id in the CHEM_COMP_ATOM category. ; _item.name '_struct_site_gen.label_atom_id' _item.mandatory_code yes save_ save__struct_site_gen.label_comp_id _item_description.description ; A component of the identifier for participants in the site. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_struct_site_gen.label_comp_id' _item.mandatory_code yes save_ save__struct_site_gen.label_seq_id _item_description.description ; A component of the identifier for participants in the site. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_struct_site_gen.label_seq_id' _item.mandatory_code yes save_ save__struct_site_gen.auth_asym_id _item_description.description ; A component of the identifier for participants in the site. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_struct_site_gen.auth_asym_id' _item.mandatory_code no save_ save__struct_site_gen.auth_atom_id _item_description.description ; A component of the identifier for participants in the site. This data item is a pointer to _atom_site.auth_atom_id in the ATOM_SITE category. ; _item.name '_struct_site_gen.auth_atom_id' _item.mandatory_code no save_ save__struct_site_gen.auth_comp_id _item_description.description ; A component of the identifier for participants in the site. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_struct_site_gen.auth_comp_id' _item.mandatory_code no save_ save__struct_site_gen.auth_seq_id _item_description.description ; A component of the identifier for participants in the site. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_struct_site_gen.auth_seq_id' _item.mandatory_code no save_ save__struct_site_gen.site_id _item_description.description ; This data item is a pointer to _struct_site.id in the STRUCT_SITE category. ; _item.name '_struct_site_gen.site_id' _item.mandatory_code yes save_ save__struct_site_gen.symmetry _item_description.description ; Describes the symmetry operation that should be applied to the atom set specified by _struct_site_gen.label* to generate a portion of the site. ; _item.name '_struct_site_gen.symmetry' _item.category_id struct_site_gen _item.mandatory_code no # _item_default.value 1_555 _item_type.code symop loop_ _item_examples.case _item_examples.detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' save_ ########################## ## STRUCT_SITE_KEYWORDS ## ########################## save_struct_site_keywords _category.description ; Data items in the STRUCT_SITE_KEYWORDS category record keywords describing the site. ; _category.id struct_site_keywords _category.mandatory_code no loop_ _category_key.name '_struct_site_keywords.site_id' '_struct_site_keywords.text' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _struct_site_keywords.site_id _struct_site_keywords.text 'P2 site C' 'binding site' 'P2 site C' 'binding pocket' 'P2 site C' 'P2 site' 'P2 site C' 'P2 pocket' 'P2 site D' 'binding site' 'P2 site D' 'binding pocket' 'P2 site D' 'P2 site' 'P2 site D' 'P2 pocket' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_site_keywords.site_id _item_description.description ; This data item is a pointer to _struct_site.id in the STRUCT_SITE category. ; _item.name '_struct_site_keywords.site_id' _item.mandatory_code yes save_ save__struct_site_keywords.text _item_description.description ; Keywords describing this site. ; _item.name '_struct_site_keywords.text' _item.category_id struct_site_keywords _item.mandatory_code yes _item_type.code text loop_ _item_examples.case 'active site' 'binding pocket' 'Ca coordination' save_ ###################### ## STRUCT_SITE_VIEW ## ###################### save_struct_site_view _category.description ; Data items in the STRUCT_SITE_VIEW category record details about how to draw and annotate an informative view of the site. ; _category.id struct_site_view _category.mandatory_code no _category_key.name '_struct_site_view.id' loop_ _category_group.id 'inclusive_group' 'struct_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on NDB structure GDL001 by Coll, Aymami, Van Der Marel, Van Boom, Rich & Wang [Biochemistry (1989), 28, 310-320]. ; ; _struct_site_view.id 1 _struct_site_view.rot_matrix[1][1] 0.132 _struct_site_view.rot_matrix[1][2] 0.922 _struct_site_view.rot_matrix[1][3] -0.363 _struct_site_view.rot_matrix[2][1] 0.131 _struct_site_view.rot_matrix[2][2] -0.380 _struct_site_view.rot_matrix[2][3] -0.916 _struct_site_view.rot_matrix[3][1] -0.982 _struct_site_view.rot_matrix[3][2] 0.073 _struct_site_view.rot_matrix[3][3] -0.172 _struct_site_view.details ; This view highlights the site of ATAT-Netropsin interaction. ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__struct_site_view.details _item_description.description ; A description of special aspects of this view of the site. This data item can be used as a figure legend. ; _item.name '_struct_site_view.details' _item.category_id struct_site_view _item.mandatory_code no _item_type.code text _item_examples.case ; The active site has been oriented with the specificity pocket on the right and the active site machinery on the left. ; save_ save__struct_site_view.id _item_description.description ; The value of _struct_site_view.id must uniquely identify a record in the STRUCT_SITE_VIEW list. Note that this item need not be a number; it can be any unique identifier. ; _item.name '_struct_site_view.id' _item.category_id struct_site_view _item.mandatory_code yes _item_type.code line loop_ _item_examples.case 'Figure 1' 'unliganded enzyme' 'view down enzyme active site' save_ save__struct_site_view.rot_matrix[1][1] _item_description.description ; The [1][1] element of the matrix used to rotate the subset of the Cartesian coordinates in the ATOM_SITE category identified in the STRUCT_SITE_GEN category to an orientation useful for visualizing the site. The conventions used in the rotation are described in _struct_site_view.details. |x'| |11 12 13| |x| |y'|~reoriented Cartesian~ = |21 22 23| |y|~Cartesian~ |z'| |31 32 33| |z| ; _item.name '_struct_site_view.rot_matrix[1][1]' _item.category_id struct_site_view _item.mandatory_code no _item_sub_category.id matrix _item_type.code float save_ save__struct_site_view.rot_matrix[1][2] _item_description.description ; The [1][2] element of the matrix used to rotate the subset of the Cartesian coordinates in the ATOM_SITE category identified in the STRUCT_SITE_GEN category to an orientation useful for visualizing the site. The conventions used in the rotation are described in _struct_site_view.details. |x'| |11 12 13| |x| |y'|~reoriented Cartesian~ = |21 22 23| |y|~Cartesian~ |z'| |31 32 33| |z| ; _item.name '_struct_site_view.rot_matrix[1][2]' _item.category_id struct_site_view _item.mandatory_code no _item_sub_category.id matrix _item_type.code float save_ save__struct_site_view.rot_matrix[1][3] _item_description.description ; The [1][3] element of the matrix used to rotate the subset of the Cartesian coordinates in the ATOM_SITE category identified in the STRUCT_SITE_GEN category to an orientation useful for visualizing the site. The conventions used in the rotation are described in _struct_site_view.details. |x'| |11 12 13| |x| |y'|~reoriented Cartesian~ = |21 22 23| |y|~Cartesian~ |z'| |31 32 33| |z| ; _item.name '_struct_site_view.rot_matrix[1][3]' _item.category_id struct_site_view _item.mandatory_code no _item_sub_category.id matrix _item_type.code float save_ save__struct_site_view.rot_matrix[2][1] _item_description.description ; The [2][1] element of the matrix used to rotate the subset of the Cartesian coordinates in the ATOM_SITE category identified in the STRUCT_SITE_GEN category to an orientation useful for visualizing the site. The conventions used in the rotation are described in _struct_site_view.details. |x'| |11 12 13| |x| |y'|~reoriented Cartesian~ = |21 22 23| |y|~Cartesian~ |z'| |31 32 33| |z| ; _item.name '_struct_site_view.rot_matrix[2][1]' _item.category_id struct_site_view _item.mandatory_code no _item_sub_category.id matrix _item_type.code float save_ save__struct_site_view.rot_matrix[2][2] _item_description.description ; The [2][2] element of the matrix used to rotate the subset of the Cartesian coordinates in the ATOM_SITE category identified in the STRUCT_SITE_GEN category to an orientation useful for visualizing the site. The conventions used in the rotation are described in _struct_site_view.details. |x'| |11 12 13| |x| |y'|~reoriented Cartesian~ = |21 22 23| |y|~Cartesian~ |z'| |31 32 33| |z| ; _item.name '_struct_site_view.rot_matrix[2][2]' _item.category_id struct_site_view _item.mandatory_code no _item_sub_category.id matrix _item_type.code float save_ save__struct_site_view.rot_matrix[2][3] _item_description.description ; The [2][3] element of the matrix used to rotate the subset of the Cartesian coordinates in the ATOM_SITE category identified in the STRUCT_SITE_GEN category to an orientation useful for visualizing the site. The conventions used in the rotation are described in _struct_site_view.details. |x'| |11 12 13| |x| |y'|~reoriented Cartesian~ = |21 22 23| |y|~Cartesian~ |z'| |31 32 33| |z| ; _item.name '_struct_site_view.rot_matrix[2][3]' _item.category_id struct_site_view _item.mandatory_code no _item_sub_category.id matrix _item_type.code float save_ save__struct_site_view.rot_matrix[3][1] _item_description.description ; The [3][1] element of the matrix used to rotate the subset of the Cartesian coordinates in the ATOM_SITE category identified in the STRUCT_SITE_GEN category to an orientation useful for visualizing the site. The conventions used in the rotation are described in _struct_site_view.details. |x'| |11 12 13| |x| |y'|~reoriented Cartesian~ = |21 22 23| |y|~Cartesian~ |z'| |31 32 33| |z| ; _item.name '_struct_site_view.rot_matrix[3][1]' _item.category_id struct_site_view _item.mandatory_code no _item_sub_category.id matrix _item_type.code float save_ save__struct_site_view.rot_matrix[3][2] _item_description.description ; The [3][2] element of the matrix used to rotate the subset of the Cartesian coordinates in the ATOM_SITE category identified in the STRUCT_SITE_GEN category to an orientation useful for visualizing the site. The conventions used in the rotation are described in _struct_site_view.details. |x'| |11 12 13| |x| |y'|~reoriented Cartesian~ = |21 22 23| |y|~Cartesian~ |z'| |31 32 33| |z| ; _item.name '_struct_site_view.rot_matrix[3][2]' _item.category_id struct_site_view _item.mandatory_code no _item_sub_category.id matrix _item_type.code float save_ save__struct_site_view.rot_matrix[3][3] _item_description.description ; The [3][3] element of the matrix used to rotate the subset of the Cartesian coordinates in the ATOM_SITE category identified in the STRUCT_SITE_GEN category an orientation useful for visualizing the site. The conventions used in the rotation are described in _struct_site_view.details. |x'| |11 12 13| |x| |y'|~reoriented Cartesian~ = |21 22 23| |y|~Cartesian~ |z'| |31 32 33| |z| ; _item.name '_struct_site_view.rot_matrix[3][3]' _item.category_id struct_site_view _item.mandatory_code no _item_sub_category.id matrix _item_type.code float save_ save__struct_site_view.site_id _item_description.description ; This data item is a pointer to _struct_site.id in the STRUCT_SITE category. ; _item.name '_struct_site_view.site_id' _item.mandatory_code yes save_ ############## ## SYMMETRY ## ############## save_symmetry _category.description ; Data items in the SYMMETRY category record details about the space-group symmetry. ; _category.id symmetry _category.mandatory_code no _category_key.name '_symmetry.entry_id' loop_ _category_group.id 'inclusive_group' 'symmetry_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _symmetry.entry_id '5HVP' _symmetry.cell_setting orthorhombic _symmetry.Int_Tables_number 18 _symmetry.space_group_name_H-M 'P 21 21 2' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__symmetry.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_symmetry.entry_id' _item.mandatory_code yes save_ save__symmetry.cell_setting _item_description.description ; The cell settings for this space-group symmetry. ; _item.name '_symmetry.cell_setting' _item.category_id symmetry _item.mandatory_code no _item_aliases.alias_name '_symmetry_cell_setting' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code ucode loop_ _item_enumeration.value triclinic monoclinic orthorhombic tetragonal rhombohedral trigonal hexagonal cubic save_ save__symmetry.Int_Tables_number _item_description.description ; Space-group number from International Tables for Crystallography Vol. A (2002). ; _item.name '_symmetry.Int_Tables_number' _item.category_id symmetry _item.mandatory_code no _item_aliases.alias_name '_symmetry_Int_Tables_number' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code int save_ save__symmetry.space_group_name_Hall _item_description.description ; Space-group symbol as described by Hall (1981). This symbol gives the space-group setting explicitly. Leave spaces between the separate components of the symbol. Ref: Hall, S. R. (1981). Acta Cryst. A37, 517-525; erratum (1981) A37, 921. ; _item.name '_symmetry.space_group_name_Hall' _item.category_id symmetry _item.mandatory_code no _item_aliases.alias_name '_symmetry_space_group_name_Hall' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case '-P 2ac 2n' '-R 3 2"' 'P 61 2 2 (0 0 -1)' save_ save__symmetry.space_group_name_H-M _item_description.description ; Hermann-Mauguin space-group symbol. Note that the Hermann-Mauguin symbol does not necessarily contain complete information about the symmetry and the space-group origin. If used, always supply the FULL symbol from International Tables for Crystallography Vol. A (2002) and indicate the origin and the setting if it is not implicit. If there is any doubt that the equivalent positions can be uniquely deduced from this symbol, specify the _symmetry_equiv.pos_as_xyz or _symmetry.space_group_name_Hall data items as well. Leave spaces between symbols referring to different axes. ; _item.name '_symmetry.space_group_name_H-M' _item.category_id symmetry _item.mandatory_code no _item_aliases.alias_name '_symmetry_space_group_name_H-M' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'P 1 21/m 1' 'P 2/n 2/n 2/n (origin at -1)' 'R -3 2/m' save_ #################### ## SYMMETRY_EQUIV ## #################### save_symmetry_equiv _category.description ; Data items in the SYMMETRY_EQUIV category list the symmetry-equivalent positions for the space group. ; _category.id symmetry_equiv _category.mandatory_code no _category_key.name '_symmetry_equiv.id' loop_ _category_group.id 'inclusive_group' 'symmetry_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; loop_ _symmetry_equiv.id _symmetry_equiv.pos_as_xyz 1 '+x,+y,+z' 2 '-x,-y,z' 3 '1/2+x,1/2-y,-z' 4 '1/2-x,1/2+y,-z' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__symmetry_equiv.id _item_description.description ; The value of _symmetry_equiv.id must uniquely identify a record in the SYMMETRY_EQUIV category. Note that this item need not be a number; it can be any unique identifier. ; _item.name '_symmetry_equiv.id' _item.category_id symmetry_equiv _item.mandatory_code yes _item_aliases.alias_name '_symmetry_equiv_pos_site_id' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code code save_ save__symmetry_equiv.pos_as_xyz _item_description.description ; Symmetry-equivalent position in the 'xyz' representation. Except for the space group P1, these data will be repeated in a loop. The format of the data item is as per International Tables for Crystallography Vol. A (2002). All equivalent positions should be entered, including those for lattice centring and a centre of symmetry, if present. ; _item.name '_symmetry_equiv.pos_as_xyz' _item.category_id symmetry_equiv _item.mandatory_code no _item_aliases.alias_name '_symmetry_equiv_pos_as_xyz' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line _item_examples.case '-y+x,-y,1/3+z' save_ ### EOF mmcif_std-def-1.dic ########################################################################### # # File: mmcif_std-def-2.dic # # mmCIF Data Dictionary # # This data dictionary contains the standard mmCIF data definitions. # # Defintion Section 2 # # Section 2 contains definitions added to maintain correspondence # with the Core CIF dictionary V2.3 # # # ########################################################################### save__atom_site.adp_type _item_description.description ; A standard code used to describe the type of atomic displacement parameters used for the site. ; _item.name '_atom_site.adp_type' _item.category_id atom_site _item.mandatory_code no _item_type.code code _item_related.related_name '_atom_site.thermal_displace_type' _item_related.function_code alternate loop_ _item_enumeration.value _item_enumeration.detail Uani 'anisotropic Uij' Uiso 'isotropic U' Uovl 'overall U' Umpe 'multipole expansion U' Bani 'anisotropic Bij' Biso 'isotropic B' Bovl 'overall B' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_atom_site_adp_type' cif_core.dic 2.3 save_ save__atom_site.refinement_flags _item_description.description ; A concatenated series of single-letter codes which indicate the refinement restraints or constraints applied to this site. This item should not be used. It has been replaced by _atom_site.refinement_flags_posn, *_adp and *_occupancy. It is retained in this dictionary only to provide compatibility with old CIFs. ; _item.name '_atom_site.refinement_flags' _item.category_id atom_site _item.mandatory_code no _item_type.code code loop_ _item_related.related_name _item_related.function_code '_atom_site.refinement_flags_posn' replaces '_atom_site.refinement_flags_adp' replaces '_atom_site.refinement_flags_occupancy' replaces loop_ _item_enumeration.value _item_enumeration.detail . 'no refinement constraints' S 'special-position constraint on site' G 'rigid-group refinement of site' R 'riding-atom site attached to non-riding atom' D 'distance or angle restraint on site' T 'thermal displacement constraints' U 'Uiso or Uij restraint (rigid bond)' P 'partial occupancy constraint' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_atom_site_refinement_flags' cif_core.dic 2.3 save_ save__atom_site.refinement_flags_adp _item_description.description ; A code which indicates the refinement restraints or constraints applied to the atomic displacement parameters of this site. ; _item.name '_atom_site.refinement_flags_adp' _item.category_id atom_site _item.mandatory_code no _item_type.code code _item_related.related_name '_atom_site.refinement_flags_posn' _item_related.function_code alternate loop_ _item_enumeration.value _item_enumeration.detail . 'no constraints on atomic displacement parameters' T 'special-position constraints on atomic displacement parameters' U 'Uiso or Uij restraint (rigid bond)' TU 'both constraints applied' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_atom_site_refinement_flags_adp' cif_core.dic 2.3 save_ save__atom_site.refinement_flags_occupancy _item_description.description ; A code which indicates that refinement restraints or constraints were applied to the occupancy of this site. ; _item.name '_atom_site.refinement_flags_occupancy' _item.category_id atom_site _item.mandatory_code no _item_type.code code _item_related.related_name '_atom_site.refinement_flags_posn' _item_related.function_code alternate loop_ _item_enumeration.value _item_enumeration.detail . 'no constraints on site-occupancy parameters' P 'site-occupancy constraint' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_atom_site_refinement_flags_occupancy' cif_core.dic 2.3 save_ save__atom_site.refinement_flags_posn _item_description.description ; A code which indicates the refinement restraints or constraints applied to the positional coordinates of this site. ; _item.name '_atom_site.refinement_flags_posn' _item.category_id atom_site _item.mandatory_code no _item_type.code code _item_related.related_name '_atom_site.refinement_flags_posn' _item_related.function_code alternate loop_ _item_enumeration.value _item_enumeration.detail . 'no constraints on positional coordinates' D 'distance or angle restraint on positional coordinates' G 'rigid-group refinement of positional coordinates' R 'riding-atom site attached to non-riding atom' S 'special-position constraint on positional coordinates' DG 'combination of the above constraints' DR 'combination of the above constraints' DS 'combination of the above constraints' GR 'combination of the above constraints' GS 'combination of the above constraints' RS 'combination of the above constraints' DGR 'combination of the above constraints' DGS 'combination of the above constraints' DRS 'combination of the above constraints' GRS 'combination of the above constraints' DGRS 'combination of the above constraints' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_atom_site_refinement_flags_posn' cif_core.dic 2.3 save_ save__atom_sites.special_details _item_description.description ; Additional information about the atomic coordinates not coded elsewhere in the CIF. ; _item.name '_atom_sites.special_details' _item.category_id atom_sites _item.mandatory_code no _item_type.code text loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_atom_sites_special_details' cif_core.dic 2.3 save_ save__atom_type.scat_dispersion_source _item_description.description ; Reference to the source of the real and imaginary dispersion corrections for scattering factors used for this atom type. ; _item.name '_atom_type.scat_dispersion_source' _item.category_id atom_type _item.mandatory_code no _item_type.code text _item_examples.case 'International Tables Vol. IV Table 2.3.1' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_atom_type_scat_dispersion_source' cif_core.dic 2.3 save_ ################ ## AUDIT_LINK ## ################ save_audit_link _category.description ; Data items in the AUDIT_LINK category record details about the relationships between data blocks in the current CIF. ; _category.id 'audit_link' _category.mandatory_code no loop_ _category_key.name '_audit_link.block_code' '_audit_link.block_description' loop_ _category_examples.case _category_examples.detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _audit_link.block_code _audit_link.block_description . 'discursive text of paper with two structures' morA_(1) 'structure 1 of 2' morA_(2) 'structure 2 of 2' ; ; Example 1 - multiple structure paper, as illustrated in A Guide to CIF for Authors (1995). IUCr: Chester. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _audit_link.block_code _audit_link.block_description . 'publication details' KSE_COM 'experimental data common to ref./mod. structures' KSE_REF 'reference structure' KSE_MOD 'modulated structure' ; ; Example 2 - example file for the one-dimensional incommensurately modulated structure of K~2~SeO~4~. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__audit_link.block_code _item_description.description ; The value of _audit_block.code associated with a data block in the current file related to the current data block. The special value '.' may be used to refer to the current data block for completeness. ; _item.name '_audit_link.block_code' _item.category_id audit_link _item.mandatory_code yes _item_type.code code loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_audit_link_block_code' cif_core.dic 2.3 save_ save__audit_link.block_description _item_description.description ; A textual description of the relationship of the referenced data block to the current one. ; _item.name '_audit_link.block_description' _item.category_id audit_link _item.mandatory_code yes _item_type.code text loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_audit_link_block_description' cif_core.dic 2.3 save_ ## save__cell.reciprocal_angle_alpha _item_description.description ; The angle (recip-alpha) defining the reciprocal cell in degrees. (recip-alpha), (recip-alpha) and (recip-alpha) related to the angles in the real cell by: cos(recip-alpha) = [cos(beta)*cos(gamma) - cos(alpha)]/[sin(beta)*sin(gamma)] cos(recip-beta) = [cos(gamma)*cos(alpha) - cos(beta)]/[sin(gamma)*sin(alpha)] cos(recip-gamma) = [cos(alpha)*cos(beta) - cos(gamma)]/[sin(alpha)*sin(beta)] Ref: Buerger, M. J. (1942). X-ray Crystallography, p. 360. New York: John Wiley & Sons Inc. ; _item.name '_cell.reciprocal_angle_alpha' _item.category_id cell _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 180.0 180.0 180.0 _item_default.value 90.0 _item_type_conditions.code esd _item_units.code 'degrees' _item_related.related_name '_cell.reciprocal_angle_alpha_esd' _item_related.function_code associated_esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_cell_reciprocal_angle_alpha' cif_core.dic 2.3 save_ save__cell.reciprocal_angle_beta _item_description.description ; The angle (recip-beta) defining the reciprocal cell in degrees. (recip-alpha), (recip-alpha) and (recip-alpha) related to the angles in the real cell by: cos(recip-alpha) = [cos(beta)*cos(gamma) - cos(alpha)]/[sin(beta)*sin(gamma)] cos(recip-beta) = [cos(gamma)*cos(alpha) - cos(beta)]/[sin(gamma)*sin(alpha)] cos(recip-gamma) = [cos(alpha)*cos(beta) - cos(gamma)]/[sin(alpha)*sin(beta)] Ref: Buerger, M. J. (1942). X-ray Crystallography, p. 360. New York: John Wiley & Sons Inc. ; _item.name '_cell.reciprocal_angle_beta' _item.category_id cell _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 180.0 180.0 180.0 _item_default.value 90.0 _item_type_conditions.code esd _item_units.code 'degrees' _item_related.related_name '_cell.reciprocal_angle_beta_esd' _item_related.function_code associated_esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_cell_reciprocal_angle_beta' cif_core.dic 2.3 save_ # save__cell.reciprocal_angle_gamma _item_description.description ; The angle (recip-gamma) defining the reciprocal cell in degrees. (recip-alpha), (recip-alpha) and (recip-alpha) related to the angles in the real cell by: cos(recip-alpha) = [cos(beta)*cos(gamma) - cos(alpha)]/[sin(beta)*sin(gamma)] cos(recip-beta) = [cos(gamma)*cos(alpha) - cos(beta)]/[sin(gamma)*sin(alpha)] cos(recip-gamma) = [cos(alpha)*cos(beta) - cos(gamma)]/[sin(alpha)*sin(beta)] Ref: Buerger, M. J. (1942). X-ray Crystallography, p. 360. New York: John Wiley & Sons Inc. ; _item.name '_cell.reciprocal_angle_gamma' _item.category_id cell _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 180.0 180.0 180.0 _item_default.value 90.0 _item_type_conditions.code esd _item_units.code 'degrees' _item_related.related_name '_cell.reciprocal_angle_gamma_esd' _item_related.function_code associated_esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_cell_reciprocal_angle_gamma' cif_core.dic 2.3 save_ # save__cell.reciprocal_angle_alpha_esd _item_description.description ; The estimated standard deviation of _cell.reciprocal_angle_alpha. ; _item.name '_cell.reciprocal_angle_alpha_esd' _item.category_id cell _item.mandatory_code no _item_type.code float _item_units.code 'degrees' _item_related.related_name '_cell.reciprocal_angle_alpha' _item_related.function_code associated_value # loop_ # _item_aliases.alias_name # _item_aliases.dictionary # _item_aliases.version # '_cell_reciprocal_angle_alpha_esd' cif_core.dic 2.3 save_ # save__cell.reciprocal_angle_beta_esd _item_description.description ; The estimated standard deviation of _cell.reciprocal_angle_beta. ; _item.name '_cell.reciprocal_angle_beta_esd' _item.category_id cell _item.mandatory_code no _item_type.code float _item_units.code 'degrees' _item_related.related_name '_cell.reciprocal_angle_beta' _item_related.function_code associated_value # loop_ # _item_aliases.alias_name # _item_aliases.dictionary # _item_aliases.version # '_cell_reciprocal_angle_beta_esd' cif_core.dic 2.3 save_ # save__cell.reciprocal_angle_gamma_esd _item_description.description ; The estimated standard deviation of _cell.reciprocal_angle_gamma. ; _item.name '_cell.reciprocal_angle_gamma_esd' _item.category_id cell _item.mandatory_code no _item_type.code float _item_units.code 'degrees' _item_related.related_name '_cell.reciprocal_angle_gamma' _item_related.function_code associated_value # loop_ # _item_aliases.alias_name # _item_aliases.dictionary # _item_aliases.version # '_cell_reciprocal_angle_gamma_esd' cif_core.dic 2.3 save_ # save__cell.reciprocal_length_a _item_description.description ; The reciprocal cell length (recip-a) in inverse Angstroms. (recip-a), (recip-b) and (recip-c) are related to the real cell by the following equation: recip-a = b*c*sin(alpha)/V recip-b = c*a*sin(beta)/V recip-c = a*b*sin(gamma)/V where V is the cell volume. Ref: Buerger, M. J. (1942). X-ray Crystallography, p. 360. New York: John Wiley & Sons Inc. ; _item.name '_cell.reciprocal_length_a' _item.category_id cell _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code 'reciprocal_angstroms' _item_type_conditions.code esd _item_related.related_name '_cell.reciprocal_length_a_esd' _item_related.function_code associated_esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_cell_reciprocal_length_a' cif_core.dic 2.3 save_ save__cell.reciprocal_length_b _item_description.description ; The reciprocal cell length (recip-b) in inverse Angstroms. (recip-a), (recip-b) and (recip-c) are related to the real cell by the following equation: recip-a = b*c*sin(alpha)/V recip-b = c*a*sin(beta)/V recip-c = a*b*sin(gamma)/V where V is the cell volume. Ref: Buerger, M. J. (1942). X-ray Crystallography, p. 360. New York: John Wiley & Sons Inc. ; _item.name '_cell.reciprocal_length_b' _item.category_id cell _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code 'reciprocal_angstroms' _item_type_conditions.code esd _item_related.related_name '_cell.reciprocal_length_b_esd' _item_related.function_code associated_esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_cell_reciprocal_length_b' cif_core.dic 2.3 save_ save__cell.reciprocal_length_c _item_description.description ; The reciprocal cell length (recip-c) in inverse Angstroms. (recip-a), (recip-b) and (recip-c) are related to the real cell by the following equation: recip-a = b*c*sin(alpha)/V recip-b = c*a*sin(beta)/V recip-c = a*b*sin(gamma)/V where V is the cell volume. Ref: Buerger, M. J. (1942). X-ray Crystallography, p. 360. New York: John Wiley & Sons Inc. ; _item.name '_cell.reciprocal_length_c' _item.category_id cell _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code 'reciprocal_angstroms' _item_type_conditions.code esd _item_related.related_name '_cell.reciprocal_length_c_esd' _item_related.function_code associated_esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_cell_reciprocal_length_c' cif_core.dic 2.3 save_ save__cell.reciprocal_length_a_esd _item_description.description ; The estimated standard deviation of _cell.reciprocal_length_a. ; _item.name '_cell.reciprocal_length_a_esd' _item.category_id cell _item.mandatory_code no _item_type.code float _item_units.code 'reciprocal_angstroms' _item_related.related_name '_cell.reciprocal_length_a' _item_related.function_code associated_value # loop_ # _item_aliases.alias_name # _item_aliases.dictionary # _item_aliases.version # '_cell_reciprocal_length_a_esd' cif_core.dic 2.3 save_ save__cell.reciprocal_length_b_esd _item_description.description ; The estimated standard deviation of _cell.reciprocal_length_b. ; _item.name '_cell.reciprocal_length_b_esd' _item.category_id cell _item.mandatory_code no _item_type.code float _item_units.code 'reciprocal_angstroms' _item_related.related_name '_cell.reciprocal_length_b' _item_related.function_code associated_value # loop_ # _item_aliases.alias_name # _item_aliases.dictionary # _item_aliases.version # '_cell_reciprocal_length_b_esd' cif_core.dic 2.3 save_ save__cell.reciprocal_length_c_esd _item_description.description ; The estimated standard deviation of _cell.reciprocal_length_c. ; _item.name '_cell.reciprocal_length_c_esd' _item.category_id cell _item.mandatory_code no _item_type.code float _item_units.code 'reciprocal_angstroms' _item_related.related_name '_cell.reciprocal_length_c' _item_related.function_code associated_value # loop_ # _item_aliases.alias_name # _item_aliases.dictionary # _item_aliases.version # '_cell_reciprocal_length_c_esd' cif_core.dic 2.3 save_ # save__cell.special_details # _item_description.description # ; A description of special aspects of the cell choice, noting # possible alternative settings. # ; # _item.name '_cell.special_details' # _item.category_id cell # _item.mandatory_code no # _item_type.code text # loop_ # _item_examples.case # 'pseudo-orthorhombic' # 'standard setting from 45 deg rotation around c' # loop_ # _item_aliases.alias_name # _item_aliases.dictionary # _item_aliases.version # '_cell_special_details' cif_core.dic 2.3 # save_ # # save__chemical.absolute_configuration _item_description.description ; Necessary conditions for the assignment of _chemical.absolute_configuration are given by H. D. Flack and G. Bernardinelli (1999, 2000). Ref: Flack, H. D. & Bernardinelli, G. (1999). Acta Cryst. A55, 908-915. (http://www.iucr.org/paper?sh0129) Flack, H. D. & Bernardinelli, G. (2000). J. Appl. Cryst. 33, 1143-1148. (http://www.iucr.org/paper?ks0021) ; _item.name '_chemical.absolute_configuration' _item.category_id chemical _item.mandatory_code no _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail rm ; absolute configuration established by the structure determination of a compound containing a chiral reference molecule of known absolute configuration ; ad ; absolute configuration established by anomalous-dispersion effects in diffraction measurements on the crystal ; rmad ; absolute configuration established by the structure determination of a compound containing a chiral reference molecule of known absolute configuration and confirmed by anomalous-dispersion effects in diffraction measurements on the crystal ; syn ; absolute configuration has not been established by anomalous-dispersion effects in diffraction measurements on the crystal. The enantiomer has been assigned by reference to an unchanging chiral centre in the synthetic procedure ; unk ; absolute configuration is unknown, there being no firm chemical evidence for its assignment to hand and it having not been established by anomalous-dispersion effects in diffraction measurements on the crystal. An arbitrary choice of enantiomer has been made ; . 'inapplicable' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_chemical_absolute_configuration' cif_core.dic 2.3 save_ save__chemical.melting_point_gt _item_description.description ; A temperature in kelvins above which the melting point (the temperature at which the crystalline solid changes to a liquid) lies. _chemical.melting_point_gt and _chemical.melting_point_lt allow a range of temperatures to be given. _chemical.melting_point should always be used in preference to these two items whenever possible. ; _item.name '_chemical.melting_point_gt' _item.category_id chemical _item.mandatory_code no _item_type.code float _item_related.related_name '_chemical.melting_point' _item_related.function_code alternate loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code kelvins loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_chemical_melting_point_gt' cif_core.dic 2.3 save_ save__chemical.melting_point_lt _item_description.description ; A temperature in kelvins below which the melting point (the temperature at which the crystalline solid changes to a liquid) lies. _chemical.melting_point_gt and _chemical.melting_point_lt allow a range of temperatures to be given. _chemical.melting_point should always be used in preference to these two items whenever possible. ; _item.name '_chemical.melting_point_lt' _item.category_id chemical _item.mandatory_code no _item_type.code float _item_related.related_name '_chemical.melting_point' _item_related.function_code alternate loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code kelvins loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_chemical_melting_point_lt' cif_core.dic 2.3 save_ save__chemical.optical_rotation _item_description.description ; The optical rotation in solution of the compound is specified in the following format: '[\a]^TEMP^~WAVE~ = SORT (c = CONC, SOLV)' where: TEMP is the temperature of the measurement in degrees Celsius, WAVE is an indication of the wavelength of the light used for the measurement, CONC is the concentration of the solution given as the mass of the substance in g in 100 ml of solution, SORT is the signed value (preceded by a + or a - sign) of 100.\a/(l.c), where \a is the signed optical rotation in degrees measured in a cell of length l in dm and c is the value of CONC as defined above, and SOLV is the chemical formula of the solvent. ; _item.name '_chemical.optical_rotation' _item.category_id chemical _item.mandatory_code no _item_type.code line _item_examples.case '[\a]^25^~D~ = +108 (c = 3.42, CHCl~3~)' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_chemical_optical_rotation' cif_core.dic 2.3 save_ save__chemical.properties_biological _item_description.description ; A free-text description of the biological properties of the material. ; _item.name '_chemical.properties_biological' _item.category_id chemical _item.mandatory_code no _item_type.code text loop_ _item_examples.case ; diverse biological activities including use as a laxative and strong antibacterial activity against S. aureus and weak activity against cyclooxygenase-1 (COX-1) ; ; antibiotic activity against Bacillus subtilis (ATCC 6051) but no significant activity against Candida albicans (ATCC 14053), Aspergillus flavus (NRRL 6541) and Fusarium verticillioides (NRRL 25457) ; ; weakly potent lipoxygenase nonredox inhibitor ; ; no influenza A virus sialidase inhibitory and plaque reduction activities ; ; low toxicity against Drosophila melanogaster ; loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_chemical_properties_biological' cif_core.dic 2.3 save_ save__chemical.properties_physical _item_description.description ; A free-text description of the physical properties of the material. ; _item.name '_chemical.properties_physical' _item.category_id chemical _item.mandatory_code no _item_type.code text loop_ _item_examples.case air-sensitive moisture-sensitive hygroscopic deliquescent oxygen-sensitive photo-sensitive pyrophoric semiconductor 'ferromagnetic at low temperature' 'paramagnetic and thermochromic' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_chemical_properties_physical' cif_core.dic 2.3 save_ save__chemical.temperature_decomposition _item_description.description ; The temperature in kelvins at which the solid decomposes. ; _item.name '_chemical.temperature_decomposition' _item.category_id chemical _item.mandatory_code no _item_type.code float _item_type_conditions.code esd loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code kelvins _item_examples.case 350 _item_related.related_name '_chemical.temperature_decomposition_esd' _item_related.function_code associated_esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_chemical_temperature_decomposition' cif_core.dic 2.3 save_ save__chemical.temperature_decomposition_esd _item_description.description ; The estimated standard deviation of _chemical.temperature_decomposition. ; _item.name '_chemical.temperature_decomposition_esd' _item.category_id chemical _item.mandatory_code no _item_type.code float _item_units.code kelvins _item_related.related_name '_chemical.temperature_decomposition' _item_related.function_code associated_value # loop_ # _item_aliases.alias_name # _item_aliases.dictionary # _item_aliases.version # '_chemical_temperature_decomposition_esd' cif_core.dic 2.3 save_ save__chemical.temperature_decomposition_gt _item_description.description ; A temperature in kelvins above which the solid is known to decompose. _chemical.temperature_decomposition_gt and _chemical.temperature_decomposition_lt allow a range of temperatures to be given. _chemical.temperature_decomposition should always be used in preference to these two items whenever possible. ; _item.name '_chemical.temperature_decomposition_gt' _item.category_id chemical _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code kelvins _item_related.related_name '_chemical.temperature_decomposition' _item_related.function_code alternate _item_examples.case 350 loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_chemical_temperature_decomposition_gt' cif_core.dic 2.3 save_ save__chemical.temperature_decomposition_lt _item_description.description ; A temperature in kelvins below which the solid is known to decompose. _chemical.temperature_decomposition_gt and _chemical.temperature_decomposition_lt allow a range of temperatures to be given. _chemical.temperature_decomposition should always be used in preference to these two items whenever possible. ; _item.name '_chemical.temperature_decomposition_lt' _item.category_id chemical _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code kelvins _item_related.related_name '_chemical.temperature_decomposition' _item_related.function_code alternate _item_examples.case 350 loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_chemical_temperature_decomposition_lt' cif_core.dic 2.3 save_ save__chemical.temperature_sublimation _item_description.description ; The temperature in kelvins at which the solid sublimes. ; _item.name '_chemical.temperature_sublimation' _item.category_id chemical _item.mandatory_code no _item_type.code float _item_type_conditions.code esd loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code kelvins _item_examples.case 350 _item_related.related_name '_chemical.temperature_sublimation_esd' _item_related.function_code associated_esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_chemical_temperature_sublimation' cif_core.dic 2.3 save_ save__chemical.temperature_sublimation_esd _item_description.description ; The estimated standard deviation of _chemical.temperature_sublimation. ; _item.name '_chemical.temperature_sublimation_esd' _item.category_id chemical _item.mandatory_code no _item_type.code float _item_units.code kelvins _item_related.related_name '_chemical.temperature_sublimation' _item_related.function_code associated_value # loop_ # _item_aliases.alias_name # _item_aliases.dictionary # _item_aliases.version # '_chemical_temperature_sublimation_esd' cif_core.dic 2.3 save_ save__chemical.temperature_sublimation_gt _item_description.description ; A temperature in kelvins above which the solid is known to sublime. _chemical.temperature_sublimation_gt and _chemical.temperature_sublimation_lt allow a range of temperatures to be given. _chemical.temperature_sublimation should always be used in preference to these two items whenever possible. ; _item.name '_chemical.temperature_sublimation_gt' _item.category_id chemical _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code kelvins _item_related.related_name '_chemical.temperature_sublimation' _item_related.function_code alternate _item_examples.case 350 loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_chemical_temperature_sublimation_gt' cif_core.dic 2.3 save_ save__chemical.temperature_sublimation_lt _item_description.description ; A temperature in kelvins below which the solid is known to sublime. _chemical.temperature_sublimation_gt and _chemical.temperature_sublimation_lt allow a range of temperatures to be given. _chemical.temperature_sublimation should always be used in preference to these two items whenever possible. ; _item.name '_chemical.temperature_sublimation_lt' _item.category_id chemical _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code kelvins _item_related.related_name '_chemical.temperature_sublimation' _item_related.function_code alternate _item_examples.case 350 loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_chemical_temperature_sublimation_lt' cif_core.dic 2.3 save_ # save__citation.database_id_CSD _item_description.description ; Identifier ('refcode') of the database record in the Cambridge Structural Database that contains details of the cited structure. ; _item.name '_citation.database_id_CSD' _item.category_id citation _item.mandatory_code no _item_type.code code _item_examples.case LEKKUH loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_citation_database_id_CSD' cif_core.dic 2.3 save_ save__database.CSD_history _item_description.description ; A history of changes made by the Cambridge Crystallographic Data Centre and incorporated into the Cambridge Structural Database (CSD). ; _item.name '_database.CSD_history' _item.category_id database _item.mandatory_code no _item_type.code text loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_database_CSD_history' cif_core.dic 2.3 save_ save__database.code_CAS _item_description.description ; The code assigned by Chemical Abstracts. ; _item.name '_database.code_CAS' _item.category_id database _item.mandatory_code no _item_type.code line loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_database_code_CAS' cif_core.dic 2.3 save_ save__database.code_CSD _item_description.description ; The code assigned by the Cambridge Structural Database. ; _item.name '_database.code_CSD' _item.category_id database _item.mandatory_code no _item_type.code line loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_database_code_CSD' cif_core.dic 2.3 save_ save__database.code_ICSD _item_description.description ; The code assigned by the Inorganic Crystal Structure Database. ; _item.name '_database.code_ICSD' _item.category_id database _item.mandatory_code no _item_type.code line loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_database_code_ICSD' cif_core.dic 2.3 save_ save__database.code_MDF _item_description.description ; The code assigned by the Metals Data File. ; _item.name '_database.code_MDF' _item.category_id database _item.mandatory_code no _item_type.code line loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_database_code_MDF' cif_core.dic 2.3 save_ save__database.code_NBS _item_description.description ; The code assigned by the NBS (NIST) Crystal Data Database. ; _item.name '_database.code_NBS' _item.category_id database _item.mandatory_code no _item_type.code line loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_database_code_NBS' cif_core.dic 2.3 save_ save__database.code_PDB _item_description.description ; The code assigned by the Protein Data Bank. ; _item.name '_database.code_PDB' _item.category_id database _item.mandatory_code no _item_type.code line loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_database_code_PDB' cif_core.dic 2.3 save_ save__database.code_PDF _item_description.description ; The code assigned by the Powder Diffraction File (JCPDS/ICDD). ; _item.name '_database.code_PDF' _item.category_id database _item.mandatory_code no _item_type.code line loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_database_code_PDF' cif_core.dic 2.3 save_ save__database.code_depnum_ccdc_fiz _item_description.description ; Deposition numbers assigned by the Fachinformationszentrum Karlsruhe (FIZ) to files containing structural information archived by the Cambridge Crystallographic Data Centre (CCDC). ; _item.name '_database.code_depnum_ccdc_fiz' _item.category_id database _item.mandatory_code no _item_type.code line loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_database_code_depnum_ccdc_fiz' cif_core.dic 2.3 save_ save__database.code_depnum_ccdc_journal _item_description.description ; Deposition numbers assigned by various journals to files containing structural information archived by the Cambridge Crystallographic Data Centre (CCDC). ; _item.name '_database.code_depnum_ccdc_journal' _item.category_id database _item.mandatory_code no _item_type.code line loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_database_code_depnum_ccdc_journal' cif_core.dic 2.3 save_ save__database.code_depnum_ccdc_archive _item_description.description ; Deposition numbers assigned by the Cambridge Crystallographic Data Centre (CCDC) to files containing structural information archived by the CCDC. ; _item.name '_database.code_depnum_ccdc_archive' _item.category_id database _item.mandatory_code no _item_type.code line loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_database_code_depnum_ccdc_archive' cif_core.dic 2.3 save_ save__diffrn.ambient_pressure _item_description.description ; The mean hydrostatic pressure in kilopascals at which the intensities were measured. ; _item.name '_diffrn.ambient_pressure' _item.category_id diffrn _item.mandatory_code no _item_type.code float _item_type_conditions.code esd loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code 'kilopascals' _item_related.related_name '_diffrn.ambient_pressure_esd' _item_related.function_code associated_esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_ambient_pressure' cif_core.dic 2.3 save_ save__diffrn.ambient_pressure_esd _item_description.description ; The estimated standard deviation of _diffrn.ambient_pressure. ; _item.name '_diffrn.ambient_pressure_esd' _item.category_id diffrn _item.mandatory_code no _item_type.code float _item_units.code 'kilopascals' _item_related.related_name '_diffrn.ambient_pressure' _item_related.function_code associated_value # loop_ # _item_aliases.alias_name # _item_aliases.dictionary # _item_aliases.version # '_diffrn_ambient_pressure' cif_core.dic 2.3 save_ save__diffrn.ambient_pressure_gt _item_description.description ; The mean hydrostatic pressure in kilopascals above which the intensities were measured. _diffrn.ambient_pressure_gt and _diffrn.ambient_pressure_lt allow a pressure range to be given. _diffrn.ambient_pressure should always be used in preference to these two items whenever possible. ; _item.name '_diffrn.ambient_pressure_gt' _item.category_id diffrn _item.mandatory_code no _item_type.code float _item_related.related_name '_diffrn.ambient_pressure' _item_related.function_code alternate loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code 'kilopascals' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_ambient_pressure_gt' cif_core.dic 2.3 save_ save__diffrn.ambient_pressure_lt _item_description.description ; The mean hydrostatic pressure in kilopascals below which the intensities were measured. _diffrn.ambient_pressure_gt and _diffrn.ambient_pressure_lt allow a pressure range to be given. _diffrn.ambient_pressure should always be used in preference to these two items whenever possible. ; _item.name '_diffrn.ambient_pressure_lt' _item.category_id diffrn _item.mandatory_code no _item_type.code float _item_related.related_name '_diffrn.ambient_pressure' _item_related.function_code alternate loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code 'kilopascals' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_ambient_pressure_lt' cif_core.dic 2.3 save_ # save__diffrn.ambient_temperature # _item_description.description # ; The mean temperature in kelvins at which the intensities # were measured. # ; # _item.name '_diffrn.ambient_temperature' # _item.category_id diffrn # _item.mandatory_code no # _item_type.code float # _item_type_conditions.code esd # loop_ # _item_range.minimum # _item_range.maximum # 0.0 0.0 # 0.0 . # _item_units.code kelvins # _item_related.related_name '_diffrn.ambient_temperature_esd' # _item_related.function_code associated_esd # loop_ # _item_aliases.alias_name # _item_aliases.dictionary # _item_aliases.version # '_diffrn_ambient_temperature' cif_core.dic 2.3 # save_ #save__diffrn.ambient_temperature_esd # _item_description.description #; The estimated standard deviation of _diffrn.ambient_temp. #; # _item.name '_diffrn.ambient_temperature_esd' # _item.category_id diffrn # _item.mandatory_code no # _item_type.code float # _item_units.code kelvins # _item_related.related_name '_diffrn.ambient_temp' # _item_related.function_code associated_value # loop_ # _item_aliases.alias_name # _item_aliases.dictionary # _item_aliases.version # '_diffrn_ambient_temperature_esd' cif_core.dic 2.3 # save_ save__diffrn.ambient_temp_gt _item_description.description ; The mean temperature in kelvins above which the intensities were measured. _diffrn.ambient_temp_gt and _diffrn.ambient_temp_lt allow a range of temperatures to be given. _diffrn.ambient_temp should always be used in preference to these two items whenever possible. ; _item.name '_diffrn.ambient_temp_gt' _item.category_id diffrn _item.mandatory_code no _item_type.code float _item_related.related_name '_diffrn.ambient_temp' _item_related.function_code alternate loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code kelvins loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_ambient_temperature_gt' cif_core.dic 2.3 save_ save__diffrn.ambient_temp_lt _item_description.description ; The mean temperature in kelvins below which the intensities were measured. _diffrn.ambient_temp_gt and _diffrn.ambient_temp_lt allow a range of temperatures to be given. _diffrn.ambient_temp should always be used in preference to these two items whenever possible. ; _item.name '_diffrn.ambient_temp_lt' _item.category_id diffrn _item.mandatory_code no _item_type.code float _item_related.related_name '_diffrn.ambient_temp' _item_related.function_code alternate loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code kelvins loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_ambient_temperature_lt' cif_core.dic 2.3 save_ save__diffrn_attenuator.material _item_description.description ; Material from which the attenuator is made. ; _item.name '_diffrn_attenuator.material' _item.category_id diffrn_attenuator _item.mandatory_code no _item_type.code text loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_attenuator_material' cif_core.dic 2.3 save_ save__diffrn_detector.area_resol_mean _item_description.description ; The resolution of an area detector, in pixels/mm. ; _item.name '_diffrn_detector.area_resol_mean' _item.category_id diffrn_detector _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code 'pixels_per_millimetre' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_detector_area_resol_mean' cif_core.dic 2.3 save_ save__diffrn_detector.dtime _item_description.description ; The deadtime in microseconds of the detector used to measure the diffraction intensities. ; _item.name '_diffrn_detector.dtime' _item.category_id diffrn_detector _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . # _item_related.related_name '_diffrn_radiation_detector.dtime' # _item_related.function_code alternate loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_detector_dtime' cif_core.dic 2.3 save_ save__diffrn_refln.class_code _item_description.description ; The code identifying the class to which this reflection has been assigned. This code must match a value of _diffrn_reflns_class.code. Reflections may be grouped into classes for a variety of purposes. For example, for modulated structures each reflection class may be defined by the number m=sum|m~i~|, where the m~i~ are the integer coefficients that, in addition to h,k,l, index the corresponding diffraction vector in the basis defined for the reciprocal lattice. ; _item.name '_diffrn_refln.class_code' _item.category_id diffrn_refln _item.mandatory_code no _item_type.code code loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_refln_class_code' cif_core.dic 2.3 save_ save__diffrn_refln.intensity_u _item_description.description ; Standard uncertainty of the net intensity calculated from the diffraction counts after the attenuator and standard scales have been applied. ; _item.name '_diffrn_refln.intensity_u' _item.category_id diffrn_refln _item.mandatory_code no _item_type.code float _item_related.related_name '_diffrn_refln.intensity_sigma' _item_related.function_code alternate loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_refln_intensity_u' cif_core.dic 2.3 save_ save__diffrn_reflns.av_unetI/netI _item_description.description ; Measure [sum u(net I)|/sum|net I|] for all measured reflections. ; _item.name '_diffrn_reflns.av_unetI/netI' _item.category_id diffrn_reflns _item.mandatory_code no _item_type.code float # _item_related.related_name '_diffrn_reflns.av_sigmaI/netI' # _item_related.function_code alternate loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_reflns_av_unetI/netI' cif_core.dic 2.3 save_ ######################### ## DIFFRN_REFLNS_CLASS ## ######################### save_diffrn_reflns_class _category.description ; Data items in the DIFFRN_REFLNS_CLASS category record details about the classes of reflections measured in the diffraction experiment. ; _category.id 'diffrn_reflns_class' _category.mandatory_code no _category_key.name '_diffrn_reflns_class.code' loop_ _category_examples.case _category_examples.detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _diffrn_reflns_class.number _diffrn_reflns_class.d_res_high _diffrn_reflns_class.d_res_low _diffrn_reflns_class.av_R_eq _diffrn_reflns_class.code _diffrn_reflns_class.description 1580 0.551 6.136 0.015 'Main' 'm=0; main reflections' 1045 0.551 6.136 0.010 'Sat1' 'm=1; first-order satellites' ; ; Example 1 - example corresponding to the one-dimensional incommensurately modulated structure of K~2~SeO~4~. Each reflection class is defined by the number m=sum|m~i~|, where the m~i~ are the integer coefficients that, in addition to h,k,l, index the corresponding diffraction vector in the basis defined for the reciprocal lattice. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_reflns_class.av_R_eq _item_description.description ; For each reflection class, the residual [sum av|del(I)|/sum|av(I)|] for symmetry-equivalent reflections used to calculate the average intensity av(I). The av|del(I)| term is the average absolute difference between av(I) and the individual intensities. ; _item.name '_diffrn_reflns_class.av_R_eq' _item.category_id diffrn_reflns_class _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_reflns_class_av_R_eq' cif_core.dic 2.3 save_ save__diffrn_reflns_class.av_sgI/I _item_description.description ; Measure [sum|sigma(net I)|/sum|net I|] for all measured intensities in a reflection class. ; _item.name '_diffrn_reflns_class.av_sgI/I' _item.category_id diffrn_reflns_class _item.mandatory_code no _item_type.code float _item_related.related_name '_diffrn_reflns_class.av_uI/I' _item_related.function_code replaces loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_reflns_class_av_sgI/I' cif_core.dic 2.3 save_ save__diffrn_reflns_class.av_uI/I _item_description.description ; Measure [sum|u(net I)|/sum|net I|] for all measured intensities in a reflection class. ; _item.name '_diffrn_reflns_class.av_uI/I' _item.category_id diffrn_reflns_class _item.mandatory_code no _item_type.code float _item_related.related_name '_diffrn_reflns_class.av_sgI/I' _item_related.function_code alternate loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_reflns_class_av_uI/I' cif_core.dic 2.3 save_ save__diffrn_reflns_class.code _item_description.description ; The code identifying a certain reflection class. ; _item.name '_diffrn_reflns_class.code' _item.category_id diffrn_reflns_class _item.mandatory_code yes _item_type.code code loop_ _item_examples.case '1' 'm1' 's2' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_reflns_class_code' cif_core.dic 2.3 save_ save__diffrn_reflns_class.description _item_description.description ; Description of each reflection class. ; _item.name '_diffrn_reflns_class.description' _item.category_id diffrn_reflns_class _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'm=1 first order satellites' 'H0L0 common projection reflections' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_reflns_class_description' cif_core.dic 2.3 save_ save__diffrn_reflns_class.d_res_high _item_description.description ; The smallest value in angstroms for the interplanar spacings for the reflections in each measured reflection class. This is called the highest resolution for this reflection class. ; _item.name '_diffrn_reflns_class.d_res_high' _item.category_id diffrn_reflns_class _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code 'angstroms' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_reflns_class_d_res_high' cif_core.dic 2.3 save_ save__diffrn_reflns_class.d_res_low _item_description.description ; The largest value in angstroms of the interplanar spacings for the reflections for each measured reflection class. This is called the lowest resolution for this reflection class. ; _item.name '_diffrn_reflns_class.d_res_low' _item.category_id diffrn_reflns_class _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code 'angstroms' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_reflns_class_d_res_low' cif_core.dic 2.3 save_ save__diffrn_reflns_class.number _item_description.description ; The total number of measured intensities for each reflection class, excluding the systematic absences arising from centring translations. ; _item.name '_diffrn_reflns_class.number' _item.category_id diffrn_reflns_class _item.mandatory_code no _item_type.code int loop_ _item_range.minimum _item_range.maximum 0 0 0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_reflns_class_number' cif_core.dic 2.3 save_ save__diffrn_source.take-off_angle _item_description.description ; The complement of the angle in degrees between the normal to the surface of the X-ray tube target and the primary X-ray beam for beams generated by traditional X-ray tubes. ; _item.name '_diffrn_source.take-off_angle' _item.category_id diffrn_source _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.00 0.00 0.00 90.0 90.0 90.0 _item_examples.case 1.5 _item_units.code 'degrees' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_source_take-off_angle' cif_core.dic 2.3 save_ save__diffrn_standards.scale_u _item_description.description ; The standard uncertainty of the individual mean standard scales applied to the intensity data. ; _item.name '_diffrn_standards.scale_u' _item.category_id diffrn_standards _item.mandatory_code no _item_type.code float _item_related.related_name '_diffrn_standards.scale_sigma' _item_related.function_code alternate loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_standards_scale_u' cif_core.dic 2.3 save_ save__exptl_crystal.colour_lustre _item_description.description ; The enumeration list of standardized names developed for the International Centre for Diffraction Data. The colour of a crystal is given by the combination of _exptl_crystal.colour_modifier with _exptl_crystal.colour_primary, as in 'dark-green' or 'bluish-violet', if necessary combined with _exptl_crystal.colour_lustre, as in 'metallic-green'. ; _item.name '_exptl_crystal.colour_lustre' _item.category_id exptl_crystal _item.mandatory_code no _item_type.code line loop_ _item_enumeration.value metallic dull clear _item_related.related_name '_exptl_crystal.colour' _item_related.function_code alternate loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_exptl_crystal_colour_lustre' cif_core.dic 2.3 save_ save__exptl_crystal.colour_modifier _item_description.description ; The enumeration list of standardized names developed for the International Centre for Diffraction Data. The colour of a crystal is given by the combination of _exptl_crystal.colour_modifier with _exptl_crystal.colour_primary, as in 'dark-green' or 'bluish-violet', if necessary combined with _exptl_crystal.colour_lustre, as in 'metallic-green'. ; _item.name '_exptl_crystal.colour_modifier' _item.category_id exptl_crystal _item.mandatory_code no _item_type.code line loop_ _item_enumeration.value light dark whitish blackish grayish brownish reddish pinkish orangish yellowish greenish bluish _item_related.related_name '_exptl_crystal.colour' _item_related.function_code alternate loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_exptl_crystal_colour_modifier' cif_core.dic 2.3 save_ save__exptl_crystal.colour_primary _item_description.description ; The enumeration list of standardized names developed for the International Centre for Diffraction Data. The colour of a crystal is given by the combination of _exptl_crystal.colour_modifier with _exptl_crystal.colour_primary, as in 'dark-green' or 'bluish-violet', if necessary combined with _exptl_crystal.colour_lustre, as in 'metallic-green'. ; _item.name '_exptl_crystal.colour_primary' _item.category_id exptl_crystal _item.mandatory_code no _item_type.code line loop_ _item_enumeration.value colourless white black gray brown red pink orange yellow green blue violet _item_related.related_name '_exptl_crystal.colour' _item_related.function_code alternate loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_exptl_crystal_colour_primary' cif_core.dic 2.3 save_ save__exptl_crystal.density_meas _item_description.description ; Density values measured using standard chemical and physical methods. The units are megagrams per cubic metre (grams per cubic centimetre). ; _item.name '_exptl_crystal.density_meas' _item.category_id exptl_crystal _item.mandatory_code no _item_type.code float _item_type_conditions.code esd loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code 'megagrams_per_cubic_metre' _item_related.related_name '_exptl_crystal.density_meas_esd' _item_related.function_code associated_esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_exptl_crystal_density_meas' cif_core.dic 2.3 save_ save__exptl_crystal.density_meas_esd _item_description.description ; The estimated standard deviation of _exptl_crystal.density_meas. ; _item.name '_exptl_crystal.density_meas_esd' _item.category_id exptl_crystal _item.mandatory_code no _item_type.code float _item_units.code 'megagrams_per_cubic_metre' _item_related.related_name '_exptl_crystal.density_meas' _item_related.function_code associated_value # loop_ # _item_aliases.alias_name # _item_aliases.dictionary # _item_aliases.version # '_exptl_crystal_density_meas_esd' cif_core.dic 2.3 save_ save__exptl_crystal.density_meas_gt _item_description.description ; The value above which the density measured using standard chemical and physical methods lies. The units are megagrams per cubic metre (grams per cubic centimetre). _exptl_crystal.density_meas_gt and _exptl_crystal.density_meas_lt should not be used to report new experimental work, for which _exptl_crystal.density_meas should be used. These items are intended for use in reporting information in existing databases and archives which would be misleading if reported under _exptl_crystal.density_meas. ; _item.name '_exptl_crystal.density_meas_gt' _item.category_id exptl_crystal _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code 'megagrams_per_cubic_metre' _item_related.related_name '_exptl_crystal.density_meas' _item_related.function_code alternate loop_ _item_examples.case _item_examples.detail 2.5 ; lower limit for the density (only the range within which the density lies was given in the original paper) ; loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_exptl_crystal_density_meas_gt' cif_core.dic 2.3 save_ save__exptl_crystal.density_meas_lt _item_description.description ; The value below which the density measured using standard chemical and physical methods lies. The units are megagrams per cubic metre (grams per cubic centimetre). _exptl_crystal.density_meas_gt and _exptl_crystal.density_meas_lt should not be used to report new experimental work, for which _exptl_crystal.density_meas should be used. These items are intended for use in reporting information in existing databases and archives which would be misleading if reported under _exptl_crystal.density_meas. ; _item.name '_exptl_crystal.density_meas_lt' _item.category_id exptl_crystal _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code 'megagrams_per_cubic_metre' _item_related.related_name '_exptl_crystal.density_meas' _item_related.function_code alternate loop_ _item_examples.case _item_examples.detail 1.0 'specimen floats in water' 5.0 ; upper limit for the density (only the range within which the density lies was given in the original paper) ; loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_exptl_crystal_density_meas_lt' cif_core.dic 2.3 save_ save__exptl_crystal.density_meas_temp _item_description.description ; Temperature in kelvins at which _exptl_crystal.density_meas was determined. ; _item.name '_exptl_crystal.density_meas_temp' _item.category_id exptl_crystal _item.mandatory_code no _item_type.code float _item_type_conditions.code esd loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code kelvins loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_exptl_crystal_density_meas_temp' cif_core.dic 2.3 save_ save__exptl_crystal.density_meas_temp_esd _item_description.description ; The estimated standard deviation of _exptl_crystal.density_meas_temp. ; _item.name '_exptl_crystal.density_meas_temp_esd' _item.category_id exptl_crystal _item.mandatory_code no _item_type.code float _item_units.code kelvins # loop_ # _item_aliases.alias_name # _item_aliases.dictionary # _item_aliases.version # '_exptl_crystal_density_meas_temp_esd' cif_core.dic 2.3 save_ save__exptl_crystal.density_meas_temp_gt _item_description.description ; Temperature in kelvins above which _exptl_crystal.density_meas was determined. _exptl_crystal.density_meas_temp_gt and _exptl_crystal.density_meas_temp_lt should not be used for reporting new work, for which the correct temperature of measurement should be given. These items are intended for use in reporting information stored in databases or archives which would be misleading if reported under _exptl_crystal.density_meas_temp. ; _item.name '_exptl_crystal.density_meas_temp_gt' _item.category_id exptl_crystal _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code kelvins _item_related.related_name '_exptl_crystal.density_meas_temp' _item_related.function_code alternate loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_exptl_crystal_density_meas_temp_gt' cif_core.dic 2.3 save_ save__exptl_crystal.density_meas_temp_lt _item_description.description ; Temperature in kelvins below which _exptl_crystal.density_meas was determined. _exptl_crystal.density_meas_temp_gt and _exptl_crystal.density_meas_temp_lt should not be used for reporting new work, for which the correct temperature of measurement should be given. These items are intended for use in reporting information stored in databases or archives which would be misleading if reported under _exptl_crystal.density_meas_temp. ; _item.name '_exptl_crystal.density_meas_temp_lt' _item.category_id exptl_crystal _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code kelvins _item_related.related_name '_exptl_crystal.density_meas_temp' _item_related.function_code alternate loop_ _item_examples.case _item_examples.detail 300 ; The density was measured at some unspecified temperature below room temperature. ; loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_exptl_crystal_density_meas_temp_lt' cif_core.dic 2.3 save_ save__geom_bond.valence _item_description.description ; The bond valence calculated from _geom_bond.dist. ; _item.name '_geom_bond.valence' _item.category_id geom_bond _item.mandatory_code no _item_type.code int loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_geom_bond_valence' cif_core.dic 2.3 save_ save__publ_author.id_iucr _item_description.description ; Identifier in the IUCr contact database of a publication author. This identifier may be available from the World Directory of Crystallographers (http://wdc.iucr.org). ; _item.name '_publ_author.id_iucr' _item.category_id publ_author _item.mandatory_code no _item_type.code code _item_examples.case 2985 loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_publ_author_id_iucr' cif_core.dic 2.3 save_ save__refine.ls_R_factor_gt _item_description.description ; Residual factor for the reflections (with number given by _reflns.number_gt) judged significantly intense (i.e. satisfying the threshold specified by _reflns.threshold_expression) and included in the refinement. The reflections also satisfy the resolution limits established by _refine.ls_d_res_high and _refine.ls_d_res_low. This is the conventional R factor. See also _refine.ls_wR_factor_ definitions. sum | F(obs) - F(calc) | R = ------------------------ sum | F(obs) | F(obs) = the observed structure-factor amplitudes F(calc) = the calculated structure-factor amplitudes and the sum is taken over the specified reflections ; _item.name '_refine.ls_R_factor_gt' _item.category_id refine _item.mandatory_code no _item_type.code float _item_related.related_name '_refine.ls_R_factor_obs' _item_related.function_code alternate loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_refine_ls_R_factor_gt' cif_core.dic 2.3 save_ save__refine.ls_goodness_of_fit_gt _item_description.description ; The least-squares goodness-of-fit parameter S for significantly intense reflections (see _reflns.threshold_expression) after the final cycle of refinement. Ideally, account should be taken of parameters restrained in the least-squares refinement. See also _refine.ls_restrained_S_ definitions. { sum { w [ Y(obs) - Y(calc) ]^2^ } }^1/2^ S = { ----------------------------------- } { Nref - Nparam } Y(obs) = the observed coefficients (see _refine_ls_structure_factor_coef) Y(calc) = the calculated coefficients (see _refine_ls_structure_factor_coef) w = the least-squares reflection weight [1/(u^2^)] u = standard uncertainty Nref = the number of reflections used in the refinement Nparam = the number of refined parameters and the sum is taken over the specified reflections ; _item.name '_refine.ls_goodness_of_fit_gt' _item.category_id refine _item.mandatory_code no _item_type.code float _item_related.related_name '_refine.ls_goodness_of_fit_obs' _item_related.function_code alternate loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_refine_ls_goodness_of_fit_gt' cif_core.dic 2.3 save_ save__refine.ls_goodness_of_fit_ref _item_description.description ; The least-squares goodness-of-fit parameter S for all reflections included in the refinement after the final cycle of refinement. Ideally, account should be taken of parameters restrained in the least-squares refinement. See also _refine_ls_restrained_S_ definitions. { sum | w | Y(obs) - Y(calc) |^2^ | }^1/2^ S = { ----------------------------------- } { Nref - Nparam } Y(obs) = the observed coefficients (see _refine_ls_structure_factor_coef) Y(calc) = the calculated coefficients (see _refine_ls_structure_factor_coef) w = the least-squares reflection weight [1/(u^2^)] u = standard uncertainty Nref = the number of reflections used in the refinement Nparam = the number of refined parameters and the sum is taken over the specified reflections ; _item.name '_refine.ls_goodness_of_fit_ref' _item.category_id refine _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_refine_ls_goodness_of_fit_ref' cif_core.dic 2.3 save_ # save__refine.ls_shift/esd_max # _item_description.description # ; The largest ratio of the final least-squares parameter # shift to the final standard uncertainty (s.u., # formerly described as estimated standard deviation, e.s.d.). # ; # _item.name '_refine.ls_shift/esd_max' # _item.category_id refine # _item.mandatory_code no # _item_type.code float # _item_related.related_name '_refine.ls_shift/su_max' # _item_related.function_code replaces # loop_ # _item_range.minimum # _item_range.maximum # 0.0 0.0 # 0.0 . # loop_ # _item_aliases.alias_name # _item_aliases.dictionary # _item_aliases.version # '_refine_ls_shift/esd_max' cif_core.dic 2.3 # save_ # # save__refine.ls_shift/esd_mean # _item_description.description # ; The average ratio of the final least-squares parameter # shift to the final standard uncertainty (s.u., # formerly described as estimated standard deviation, e.s.d.). # ; # # _item.name '_refine.ls_shift/esd_mean' # _item.category_id refine # _item.mandatory_code no # _item_type.code float # _item_related.related_name '_refine.ls_shift/su_mean' # _item_related.function_code replaces # loop_ # _item_range.minimum # _item_range.maximum # 0.0 0.0 # 0.0 . # loop_ # _item_aliases.alias_name # _item_aliases.dictionary # _item_aliases.version # '_refine_ls_shift/esd_mean' cif_core.dic 2.3 # save_ save__refine.ls_shift_over_su_max _item_description.description ; The largest ratio of the final least-squares parameter shift to the final standard uncertainty. ; _item.name '_refine.ls_shift_over_su_max' _item.category_id refine _item.mandatory_code no _item_type.code float _item_related.related_name '_refine.ls_shift_over_esd_max' _item_related.function_code alternate loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_refine_ls_shift/su_max' cif_core.dic 2.3 save_ save__refine.ls_shift_over_su_max_lt _item_description.description ; An upper limit for the largest ratio of the final least-squares parameter shift to the final standard uncertainty. This item is used when the largest value of the shift divided by the final standard uncertainty is too small to measure. ; _item.name '_refine.ls_shift_over_su_max_lt' _item.category_id refine _item.mandatory_code no _item_type.code float _item_related.related_name '_refine.ls_shift_over_su_max' _item_related.function_code alternate loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_refine_ls_shift/su_max_lt' cif_core.dic 2.3 save_ save__refine.ls_shift_over_su_mean _item_description.description ; The average ratio of the final least-squares parameter shift to the final standard uncertainty. ; _item.name '_refine.ls_shift_over_su_mean' _item.category_id refine _item.mandatory_code no _item_type.code float _item_related.related_name '_refine.ls_shift_over_esd_mean' _item_related.function_code alternate loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_refine_ls_shift/su_mean' cif_core.dic 2.3 save_ save__refine.ls_shift_over_su_mean_lt _item_description.description ; An upper limit for the average ratio of the final least-squares parameter shift to the final standard uncertainty. This item is used when the average value of the shift divided by the final standard uncertainty is too small to measure. ; _item.name '_refine.ls_shift_over_su_mean_lt' _item.category_id refine _item.mandatory_code no _item_type.code float _item_related.related_name '_refine.ls_shift_over_su_mean' _item_related.function_code alternate loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_refine_ls_shift/su_mean_lt' cif_core.dic 2.3 save_ ##################### ## REFINE_LS_CLASS ## ##################### save_refine_ls_class _category.description ; Data items in the REFINE_LS_CLASS category record details about the reflections used for the structure refinement for each reflection class separately. ; _category.id 'refine_ls_class' _category.mandatory_code no _category_key.name '_refine_ls_class.code' loop_ _category_examples.case _category_examples.detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _refine_ls_class.R_factor_gt _refine_ls_class.code 0.057 'Main' 0.074 'Com' 0.064 'NbRefls' 0.046 'LaRefls' 0.112 'Sat1' 0.177 'Sat2' ; ; Example 1 - data for a modulated structure from van Smaalen [J. Phys. Condens. Matter (1991), 3, 1247-1263]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__refine_ls_class.code _item_description.description ; The code identifying a certain reflection class. This code must match a _reflns_class.code. ; _item.name '_refine_ls_class.code' _item.category_id refine_ls_class _item.mandatory_code yes _item_type.code code loop_ _item_examples.case '1' 'm1' 's2' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_refine_ls_class_code' cif_core.dic 2.3 save_ save__refine_ls_class.d_res_high _item_description.description ; For each reflection class, the lowest value in angstroms for the interplanar spacings for the reflections used in the refinement. This is called the highest resolution. ; _item.name '_refine_ls_class.d_res_high' _item.category_id refine_ls_class _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code 'angstroms' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_refine_ls_class_d_res_high' cif_core.dic 2.3 save_ save__refine_ls_class.d_res_low _item_description.description ; For each reflection class, the highest value in angstroms for the interplanar spacings for the reflections used in the refinement. This is called the lowest resolution. ; _item.name '_refine_ls_class.d_res_low' _item.category_id refine_ls_class _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code 'angstroms' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_refine_ls_class_d_res_low' cif_core.dic 2.3 save_ save__refine_ls_class.R_factor_gt _item_description.description ; For each reflection class, the residual factor for significantly intense reflections (see _reflns.threshold_expression) included in the refinement. The reflections also satisfy the resolution limits established by _refine_ls_class.d_res_high and _refine_ls_class.d_res_low. This is the conventional R factor. See also the definition of _refine_ls_class.wR_factor_all. sum | F(obs) - F(calc) | R = ------------------------ sum | F(obs) | F(obs) = the observed structure-factor amplitudes F(calc) = the calculated structure-factor amplitudes and the sum is taken over the reflections of this class. ; _item.name '_refine_ls_class.R_factor_gt' _item.category_id refine_ls_class _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_refine_ls_class_R_factor_gt' cif_core.dic 2.3 save_ save__refine_ls_class.R_factor_all _item_description.description ; For each reflection class, the residual factor for all reflections satisfying the resolution limits established by _refine_ls_class.d_res_high and _refine_ls_class.d_res_low. This is the conventional R factor. See also the definition of _refine_ls_class.wR_factor_all. sum | F(obs) - F(calc) | R = ------------------------ sum | F(obs) | F(obs) = the observed structure-factor amplitudes F(calc) = the calculated structure-factor amplitudes and the sum is taken over the reflections of this class. ; _item.name '_refine_ls_class.R_factor_all' _item.category_id refine_ls_class _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_refine_ls_class_R_factor_all' cif_core.dic 2.3 save_ save__refine_ls_class.R_Fsqd_factor _item_description.description ; For each reflection class, the residual factor R(F^2^) calculated on the squared amplitudes of the observed and calculated structure factors, for the reflections judged significantly intense (i.e. satisfying the threshold specified by _reflns.threshold_expression) and included in the refinement. The reflections also satisfy the resolution limits established by _refine_ls_class.d_res_high and _refine_ls_class.d_res_low. sum | F(obs)^2^ - F(calc)^2^ | R(Fsqd) = ------------------------------- sum F(obs)^2^ F(obs)^2^ = squares of the observed structure-factor amplitudes F(calc)^2^ = squares of the calculated structure-factor amplitudes and the sum is taken over the reflections of this class. ; _item.name '_refine_ls_class.R_Fsqd_factor' _item.category_id refine_ls_class _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_refine_ls_class_R_Fsqd_factor' cif_core.dic 2.3 save_ save__refine_ls_class.R_I_factor _item_description.description ; For each reflection class, the residual factor R(I) for the reflections judged significantly intense (i.e. satisfying the threshold specified by _reflns.threshold_expression) and included in the refinement. This is most often calculated in Rietveld refinements against powder data, where it is referred to as R~B~ or R~Bragg~ sum | I(obs) - I(calc) | R(I) = ------------------------ sum | I(obs) | I(obs) = the net observed intensities I(calc) = the net calculated intensities and the sum is taken over the reflections of this class. ; _item.name '_refine_ls_class.R_I_factor' _item.category_id refine_ls_class _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_refine_ls_class_R_I_factor' cif_core.dic 2.3 save_ save__refine_ls_class.wR_factor_all _item_description.description ; For each reflection class, the weighted residual factor for all reflections included in the refinement. The reflections also satisfy the resolution limits established by _refine_ls_class.d_res_high and _refine_ls_class.d_res_low. See also the _refine_ls_class.R_factor_ definitions. ( sum w [ Y(obs) - Y(calc) ]^2^ )^1/2^ wR = ( ------------------------------ ) ( sum w Y(obs)^2^ ) Y(obs) = the observed amplitude specified by _refine.ls_structure_factor_coef Y(calc) = the calculated amplitude specified by _refine.ls_structure_factor_coef w = the least-squares weight and the sum is taken over the reflections of this class. ; _item.name '_refine_ls_class.wR_factor_all' _item.category_id refine_ls_class _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_refine_ls_class_wR_factor_all' cif_core.dic 2.3 save_ save__refln.class_code _item_description.description ; The code identifying the class to which this reflection has been assigned. This code must match a value of _reflns_class.code. Reflections may be grouped into classes for a variety of purposes. For example, for modulated structures each reflection class may be defined by the number m=sum|m~i~|, where the m~i~ are the integer coefficients that, in addition to h,k,l, index the corresponding diffraction vector in the basis defined for the reciprocal lattice. ; _item.name '_refln.class_code' _item.category_id refln _item.mandatory_code no _item_type.code code loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_refln_class_code' cif_core.dic 2.3 save_ save__refln.d_spacing _item_description.description ; The d spacing in angstroms for this reflection. This is related to the (sin theta)/lambda value by the expression _refln.d_spacing = 2/(_refln.sint/lambda). ; _item.name '_refln.d_spacing' _item.category_id refln _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code 'angstroms' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_refln_d_spacing' cif_core.dic 2.3 save_ save__refln.include_status _item_description.description ; Classification of a reflection so as to indicate its status with respect to inclusion in the refinement and the calculation of R factors. ; _item.name '_refln.include_status' _item.category_id refln _item.mandatory_code no _item_type.code code _item_related.related_name '_refln.status' _item_related.function_code alternate loop_ _item_enumeration.value _item_enumeration.detail o ; (lower-case letter o for 'observed') satisfies _refine.ls_d_res_high satisfies _refine.ls_d_res_low exceeds _reflns.threshold_expression ; < ; satisfies _refine.ls_d_res_high satisfies _refine.ls_d_res_low does not exceed _reflns.threshold_expression ; - 'systematically absent reflection' x 'unreliable measurement -- not used' h 'does not satisfy _refine.ls_d_res_high' l 'does not satisfy _refine.ls_d_res_low' # _item_default.value o loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_refln_include_status' cif_core.dic 2.3 save_ save__refln.mean_path_length_tbar _item_description.description ; Mean path length in millimetres through the crystal for this reflection. ; _item.name '_refln.mean_path_length_tbar' _item.category_id refln _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code 'millimetres' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_refln_mean_path_length_tbar' cif_core.dic 2.3 save_ # save__refln.observed_status # _item_description.description # ; Classification of a reflection so as to indicate its status # with respect to inclusion in refinement and calculation of # R factors. # ; # # _item.name '_refln.observed_status' # _item.category_id refln # _item.mandatory_code no # _item_type.code code # _item_related.related_name '_refln.include_status' # _item_related.function_code replaces # loop_ # _item_enumeration.value # _item_enumeration.detail # o # ; satisfies _refine.ls_d_res_high # satisfies _refine.ls_d_res_low # observed by _reflns_observed_criterion # ; # < # ; satisfies _refine.ls_d_res_high # satisfies _refine.ls_d_res_low # unobserved by _reflns.observed_criterion # ; # - 'systematically absent reflection' # x 'unreliable measurement -- not used' # h 'does not satisfy _refine.ls_d_res_high' # l 'does not satisfy _refine.ls_d_res_low' # # # _item_default.value o # loop_ # _item_aliases.alias_name # _item_aliases.dictionary # _item_aliases.version # '_refln_observed_status' cif_core.dic 2.3 # save_ # save__refln.sint/lambda # _item_description.description # ; The (sin theta)/lambda value in reciprocal angstroms for this # reflection. # ; # _item.name '_refln.sint/lambda' # _item.category_id refln # _item.mandatory_code no # _item_type.code float # loop_ # _item_range.minimum # _item_range.maximum # 0.0 0.0 # 0.0 . # _item_units.code 'reciprocal_angstroms' # loop_ # _item_aliases.alias_name # _item_aliases.dictionary # _item_aliases.version # '_refln_sint/lambda' cif_core.dic 2.3 # save_ save__reflns.Friedel_coverage _item_description.description ; The proportion of Friedel-related reflections present in the number of 'independent' reflections specified by the item _reflns.number_all. This proportion is calculated as the ratio: [N(Crystal class) - N(Laue symmetry)] / N(Laue symmetry) where, working from the DIFFRN_REFLN list, N(Crystal class) is the number of reflections obtained on averaging under the symmetry of the crystal class N(Laue symmetry) is the number of reflections obtained on averaging under the Laue symmetry. Examples: (a) For centrosymmetric structures, the value of _reflns.Friedel_coverage is necessarily equal to 0.0, as the crystal class is identical to the Laue symmetry. (b) For whole-sphere data for a crystal in the space group P1, _reflns.Friedel_coverage is equal to 1.0, as no reflection h k l is equivalent to -h -k -l in the crystal class and all Friedel pairs {h k l; -h -k -l} have been measured. (c) For whole-sphere data in space group Pmm2, _reflns.Friedel_coverage will be < 1.0 because although reflections h k l and -h -k -l are not equivalent when h k l indices are nonzero, they are when l=0. (d) For a crystal in space group Pmm2, measurements of the two inequivalent octants h >= 0, k >=0, l lead to the same value as in (c), whereas measurements of the two equivalent octants h >= 0, k, l >= 0 will lead to a zero value for _reflns.Friedel_coverage. ; _item.name '_reflns.Friedel_coverage' _item.category_id reflns _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 1.0 1.0 1.0 loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_reflns_Friedel_coverage' cif_core.dic 2.3 save_ save__reflns.number_gt _item_description.description ; The number of reflections in the REFLN list (not the DIFFRN_REFLN list) that are significantly intense, satisfying the criterion specified by _reflns.threshold_expression. This may include Friedel-equivalent reflections (i.e. those which are symmetry-equivalent under the Laue symmetry but inequivalent under the crystal class) according to the nature of the structure and the procedures used. Any special characteristics of the reflections included in the REFLN list should be described using the item _reflns.details. ; _item.name '_reflns.number_gt' _item.category_id reflns _item.mandatory_code no _item_type.code int # _item_related.related_name '_reflns.number_observed' # _item_related.function_code alternate loop_ _item_range.minimum _item_range.maximum 0 0 0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_reflns_number_gt' cif_core.dic 2.3 save_ save__reflns.threshold_expression _item_description.description ; The threshold, usually based on multiples of u(I), u(F^2^) or u(F), that serves to identify significantly intense reflections, the number of which is given by _reflns.number_gt. These reflections are used in the calculation of _refine.ls_R_factor_gt. ; _item.name '_reflns.threshold_expression' _item.category_id reflns _item.mandatory_code no _item_aliases.alias_name '_reflns_threshold_expression' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.3 loop_ _item_related.related_name _item_related.function_code '_reflns.observed_criterion' alternate _item_type.code text _item_examples.case 'I>2u(I)' save_ ################## ## REFLNS_CLASS ## ################## save_reflns_class _category.description ; Data items in the REFLNS_CLASS category record details of the reflections used to determine the structural parameters for each reflection class. ; _category.id 'reflns_class' _category.mandatory_code no _category_key.name '_reflns_class.code' loop_ _category_examples.case _category_examples.detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _reflns_class.number_gt _reflns_class.code 584 'Main' 226 'Sat1' 50 'Sat2' ; ; Example 1 - example corresponding to the one-dimensional incommensurately modulated structure of K~2~SeO~4~. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__reflns_class.code _item_description.description ; The code identifying a certain reflection class. ; _item.name '_reflns_class.code' _item.category_id reflns_class _item.mandatory_code yes _item_type.code code loop_ _item_examples.case '1' 'm1' 's2' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_reflns_class_code' cif_core.dic 2.3 save_ save__reflns_class.description _item_description.description ; Description of each reflection class. ; _item.name '_reflns_class.description' _item.category_id reflns_class _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'm=1 first order satellites' 'H0L0 common projection reflections' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_reflns_class_description' cif_core.dic 2.3 save_ save__reflns_class.d_res_high _item_description.description ; For each reflection class, the smallest value in angstroms for the interplanar spacings for the reflections used in the refinement. This is called the highest resolution. ; _item.name '_reflns_class.d_res_high' _item.category_id reflns_class _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code 'angstroms' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_reflns_class_d_res_high' cif_core.dic 2.3 save_ save__reflns_class.d_res_low _item_description.description ; For each reflection class, the largest value in angstroms for the interplanar spacings for the reflections used in the refinement. This is called the lowest resolution. ; _item.name '_reflns_class.d_res_low' _item.category_id reflns_class _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . _item_units.code 'angstroms' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_reflns_class_d_res_low' cif_core.dic 2.3 save_ save__reflns_class.number_gt _item_description.description ; For each reflection class, the number of significantly intense reflections (see _reflns.threshold_expression) in the REFLN list (not the DIFFRN_REFLN list). This may include Friedel- equivalent reflections (i.e. those which are symmetry-equivalent under the Laue symmetry but inequivalent under the crystal class) according to the nature of the structure and the procedures used. Any special characteristics of the reflections included in the REFLN list should be described using the item _reflns.details. ; _item.name '_reflns_class.number_gt' _item.category_id reflns_class _item.mandatory_code no _item_type.code int loop_ _item_range.minimum _item_range.maximum 0 0 0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_reflns_class_number_gt' cif_core.dic 2.3 save_ save__reflns_class.number_total _item_description.description ; For each reflection class, the total number of reflections in the REFLN list (not the DIFFRN_REFLN list). This may include Friedel-equivalent reflections (i.e. those which are symmetry-equivalent under the Laue symmetry but inequivalent under the crystal class) according to the nature of the structure and the procedures used. Any special characteristics of the reflections included in the REFLN list should be described using the item _reflns.details. ; _item.name '_reflns_class.number_total' _item.category_id reflns_class _item.mandatory_code no _item_type.code int loop_ _item_range.minimum _item_range.maximum 0 0 0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_reflns_class_number_total' cif_core.dic 2.3 save_ save__reflns_class.R_factor_all _item_description.description ; For each reflection class, the residual factor for all reflections included in the refinement. The reflections also satisfy the resolution limits established by _reflns_class.d_res_high and _reflns_class.d_res_low. This is the conventional R factor. See also the definition of _reflns_class.wR_factor_all. sum | F(obs) - F(calc) | R = ------------------------ sum | F(obs) | F(obs) = the observed structure-factor amplitudes F(calc) = the calculated structure-factor amplitudes and the sum is taken over the reflections of this class. ; _item.name '_reflns_class.R_factor_all' _item.category_id reflns_class _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_reflns_class_R_factor_all' cif_core.dic 2.3 save_ save__reflns_class.R_factor_gt _item_description.description ; For each reflection class, the residual factor for significantly intense reflections (see _reflns.threshold_expression) included in the refinement. The reflections also satisfy the resolution limits established by _reflns_class.d_res_high and _reflns_class.d_res_low. This is the conventional R factor. See also the definition of _reflns_class.wR_factor_all. sum | F(obs) - F(calc) | R = ------------------------ sum | F(obs) | F(obs) = the observed structure-factor amplitudes F(calc) = the calculated structure-factor amplitudes and the sum is taken over the reflections of this class. ; _item.name '_reflns_class.R_factor_gt' _item.category_id reflns_class _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_reflns_class_R_factor_gt' cif_core.dic 2.3 save_ save__reflns_class.R_Fsqd_factor _item_description.description ; For each reflection class, the residual factor R(F^2^) calculated on the squared amplitudes of the observed and calculated structure factors for the reflections judged significantly intense (i.e. satisfying the threshold specified by _reflns.threshold_expression) and included in the refinement. The reflections also satisfy the resolution limits established by _reflns_class.d_res_high and _reflns_class.d_res_low. sum | F(obs)^2^ - F(calc)^2^ | R(Fsqd) = ------------------------------- sum F(obs)^2^ F(obs)^2^ = squares of the observed structure-factor amplitudes F(calc)^2^ = squares of the calculated structure-factor amplitudes and the sum is taken over the reflections of this class. ; _item.name '_reflns_class.R_Fsqd_factor' _item.category_id reflns_class _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_reflns_class_R_Fsqd_factor' cif_core.dic 2.3 save_ save__reflns_class.R_I_factor _item_description.description ; For each reflection class, the residual factor R(I) for the reflections judged significantly intense (i.e. satisfying the threshold specified by _reflns.threshold_expression) and included in the refinement. This is most often calculated in Rietveld refinements against powder data, where it is referred to as R~B~ or R~Bragg~. sum | I(obs) - I(calc) | R(I) = ------------------------ sum | I(obs) | I(obs) = the net observed intensities I(calc) = the net calculated intensities and the sum is taken over the reflections of this class. ; _item.name '_reflns_class.R_I_factor' _item.category_id reflns_class _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_reflns_class_R_I_factor' cif_core.dic 2.3 save_ save__reflns_class.wR_factor_all _item_description.description ; For each reflection class, the weighted residual factors for all reflections included in the refinement. The reflections also satisfy the resolution limits established by _reflns_class.d_res_high and _reflns_class.d_res_low. See also _reflns_class.R_factor_ definitions. ( sum w [ Y(obs) - Y(calc) ]^2^ )^1/2^ wR = ( ------------------------------ ) ( sum w Y(obs)^2^ ) Y(obs) = the observed amplitude specified by _refine.ls_structure_factor_coef Y(calc) = the calculated amplitude specified by _refine.ls_structure_factor_coef w = the least-squares weight and the sum is taken over the reflections of this class. ; _item.name '_reflns_class.wR_factor_all' _item.category_id reflns_class _item.mandatory_code no _item_type.code float loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_reflns_class_wR_factor_all' cif_core.dic 2.3 save_ save__reflns_shell.meanI_over_sigI_gt _item_description.description ; The ratio of the mean of the intensities of the significantly intense reflections (see _reflns.threshold_expression) in this shell to the mean of the standard uncertainties of the intensities of the significantly intense reflections in this shell. ; _item.name '_reflns_shell.meanI_over_sigI_gt' _item.category_id reflns_shell _item.mandatory_code no _item_type.code float _item_related.related_name '_reflns_shell.meanI_over_uI_gt' _item_related.function_code replaces loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_reflns_shell_meanI_over_sigI_gt' cif_core.dic 2.3 save_ save__reflns_shell.meanI_over_uI_all _item_description.description ; The ratio of the mean of the intensities of all reflections in this shell to the mean of the standard uncertainties of the intensities of all reflections in this shell. ; _item.name '_reflns_shell.meanI_over_uI_all' _item.category_id reflns_shell _item.mandatory_code no _item_type.code float _item_related.related_name '_reflns_shell.meanI_over_sigI_all' _item_related.function_code alternate loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_reflns_shell_meanI_over_uI_all' cif_core.dic 2.3 save_ save__reflns_shell.meanI_over_uI_gt _item_description.description ; The ratio of the mean of the intensities of the significantly intense reflections (see _reflns.threshold_expression) in this shell to the mean of the standard uncertainties of the intensities of the significantly intense reflections in this shell. ; _item.name '_reflns_shell.meanI_over_uI_gt' _item.category_id reflns_shell _item.mandatory_code no _item_type.code float loop_ _item_related.related_name _item_related.function_code '_reflns_shell.meanI_over_sigI_gt' alternate '_reflns_shell.meanI_over_sigI_obs' alternate loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_reflns_shell_meanI_over_uI_gt' cif_core.dic 2.3 save_ save__reflns_shell.number_measured_gt _item_description.description ; The number of significantly intense reflections (see _reflns.threshold_expression) measured for this shell. ; _item.name '_reflns_shell.number_measured_gt' _item.category_id reflns_shell _item.mandatory_code no _item_type.code int _item_related.related_name '_reflns_shell.number_measured_obs' _item_related.function_code alternate loop_ _item_range.minimum _item_range.maximum 0 0 0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_reflns_shell_number_measured_gt' cif_core.dic 2.3 save_ save__reflns_shell.number_unique_gt _item_description.description ; The total number of significantly intense reflections (see _reflns.threshold_expression) resulting from merging measured symmetry-equivalent reflections for this resolution shell. ; _item.name '_reflns_shell.number_unique_gt' _item.category_id reflns_shell _item.mandatory_code no _item_type.code int _item_related.related_name '_reflns_shell.number_unique_obs' _item_related.function_code alternate loop_ _item_range.minimum _item_range.maximum 0 0 0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_reflns_shell_number_unique_gt' cif_core.dic 2.3 save_ save__reflns_shell.percent_possible_gt _item_description.description ; The percentage of geometrically possible reflections represented by significantly intense reflections (see _reflns.threshold_expression) measured for this shell. ; _item.name '_reflns_shell.percent_possible_gt' _item.category_id reflns_shell _item.mandatory_code no _item_type.code float _item_related.related_name '_reflns_shell.percent_possible_obs' _item_related.function_code alternate loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 100.0 100.0 100.0 loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_reflns_shell_percent_possible_gt' cif_core.dic 2.3 save_ save__reflns_shell.Rmerge_F_gt _item_description.description ; The value of Rmerge(F) for significantly intense reflections (see _reflns.threshold_expression) in a given shell. sum~i~ ( sum~j~ | F~j~ - | ) Rmerge(F) = -------------------------------- sum~i~ ( sum~j~ ) F~j~ = the amplitude of the jth observation of reflection i = the mean of the amplitudes of all observations of reflection i sum~i~ is taken over all reflections sum~j~ is taken over all observations of each reflection. ; _item.name '_reflns_shell.Rmerge_F_gt' _item.category_id reflns_shell _item.mandatory_code no _item_type.code float _item_related.related_name '_reflns_shell.Rmerge_F_obs' _item_related.function_code alternate loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_reflns_shell_Rmerge_F_gt' cif_core.dic 2.3 save_ save__reflns_shell.Rmerge_I_gt _item_description.description ; The value of Rmerge(I) for significantly intense reflections (see _reflns.threshold_expression) in a given shell. sum~i~ ( sum~j~ | I~j~ - | ) Rmerge(I) = -------------------------------- sum~i~ ( sum~j~ ) I~j~ = the intensity of the jth observation of reflection i = the mean of the intensities of all observations of reflection i sum~i~ is taken over all reflections sum~j~ is taken over all observations of each reflection. ; _item.name '_reflns_shell.Rmerge_I_gt' _item.category_id reflns_shell _item.mandatory_code no _item_type.code float _item_related.related_name '_reflns_shell.Rmerge_I_obs' _item_related.function_code alternate loop_ _item_range.minimum _item_range.maximum 0.0 0.0 0.0 . loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_reflns_shell_Rmerge_I_gt' cif_core.dic 2.3 save_ ################# ## SPACE_GROUP ## ################# save_space_group _category.description ; Contains all the data items that refer to the space group as a whole, such as its name or crystal system. They may be looped, for example, in a list of space groups and their properties. Only a subset of the SPACE_GROUP category items appear in this dictionary. The remainder are found in the symmetry CIF dictionary. Space-group types are identified by their number as given in International Tables for Crystallography Vol. A. Specific settings of the space groups can be identified either by their Hall symbol or by specifying their symmetry operations. The commonly used Hermann-Mauguin symbol determines the space-group type uniquely but several different Hermann-Mauguin symbols may refer to the same space-group type. A Hermann-Mauguin symbol contains information on the choice of the basis, but not on the choice of origin. Different formats for the Hermann-Mauguin symbol are found in the symmetry CIF dictionary. ; _category.id 'space_group' _category.mandatory_code no _category_key.name '_space_group.id' loop_ _category_examples.case _category_examples.detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _space_group.id 1 _space_group.name_H-M_alt 'C 2/c' _space_group.IT_number 15 _space_group.name_Hall '-C 2yc' _space_group.crystal_system monoclinic ; ; Example 1 - the monoclinic space group No. 15 with unique axis b. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__space_group.crystal_system _item_description.description ; The name of the system of geometric crystal classes of space groups (crystal system) to which the space group belongs. Note that rhombohedral space groups belong to the trigonal system. ; _item.name '_space_group.crystal_system' _item.category_id space_group _item.mandatory_code no _item_type.code code _item_related.related_name '_symmetry.cell_setting' _item_related.function_code alternate loop_ _item_enumeration.value triclinic monoclinic orthorhombic tetragonal trigonal hexagonal cubic loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_space_group_crystal_system' cif_core.dic 2.3 save_ save__space_group.id _item_description.description ; This is the unique identifier for the SPACE_GROUP category. ; _item.name '_space_group.id' _item.category_id space_group _item.mandatory_code yes _item_type.code code loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_space_group_id' cif_core.dic 2.3 save_ save__space_group.IT_number _item_description.description ; The number as assigned in International Tables for Crystallography Vol. A, specifying the proper affine class (i.e. the orientation-preserving affine class) of space groups (crystallographic space-group type) to which the space group belongs. This number defines the space-group type but not the coordinate system in which it is expressed. ; _item.name '_space_group.IT_number' _item.category_id space_group _item.mandatory_code no _item_type.code int _item_related.related_name '_symmetry.Int_Tables_number' _item_related.function_code alternate loop_ _item_range.minimum _item_range.maximum 1 1 1 230 230 230 loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_space_group_IT_number' cif_core.dic 2.3 save_ save__space_group.name_Hall _item_description.description ; Space-group symbol defined by Hall. Each component of the space-group name is separated by a space or an underscore. The use of a space is strongly recommended. The underscore is only retained because it was used in old CIFs. It should not be used in new CIFs. _space_group.name_Hall uniquely defines the space group and its reference to a particular coordinate system. Ref: Hall, S. R. (1981). Acta Cryst. A37, 517-525; erratum (1981), A37, 921. [See also International Tables for Crystallography Vol. B (2001), Chapter 1.4, Appendix 1.4.2.] ; _item.name '_space_group.name_Hall' _item.category_id space_group _item.mandatory_code no _item_type.code line _item_related.related_name '_symmetry.space_group_name_Hall' _item_related.function_code alternate loop_ _item_examples.case _item_examples.detail 'P 2c -2ac' 'equivalent to Pca21' '-I 4bd 2ab 3' 'equivalent to Ia3d' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_space_group_name_Hall' cif_core.dic 2.3 save_ save__space_group.name_H-M_alt _item_description.description ; _space_group.name_H-M_alt allows any Hermann-Mauguin symbol to be given. The way in which this item is used is determined by the user and in general is not intended to be interpreted by computer. It may, for example, be used to give one of the extended Hermann-Mauguin symbols given in Table 4.3.2.1 of International Tables for Crystallography Vol. A (2002) or a Hermann-Mauguin symbol for a conventional or unconventional setting. Each component of the space-group name is separated by a space or an underscore. The use of a space is strongly recommended. The underscore is only retained because it was used in old CIFs. It should not be used in new CIFs. Subscripts should appear without special symbols. Bars should be given as negative signs before the numbers to which they apply. The commonly used Hermann-Mauguin symbol determines the space- group type uniquely but a given space-group type may be described by more than one Hermann-Mauguin symbol. The space- group type is best described using _space_group.IT_number. The Hermann-Mauguin symbol may contain information on the choice of basis, but not on the choice of origin. To define the setting uniquely, use _space_group.name_Hall or list the symmetry operations. ; _item.name '_space_group.name_H-M_alt' _item.category_id space_group _item.mandatory_code no _item_type.code line _item_related.related_name '_symmetry.space_group_name_H-M' _item_related.function_code alternate loop_ _item_examples.case _item_examples.detail ; loop_ _space_group.name_H-M_alt 'C m c m' 'C 2/c 2/m 21/m' 'A m a m' ; 'three examples for space group No. 63' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_space_group_name_H-M_alt' cif_core.dic 2.3 save_ ####################### ## SPACE_GROUP_SYMOP ## ####################### save_space_group_symop _category.description ; Contains information about the symmetry operations of the space group. ; _category.id 'space_group_symop' _category.mandatory_code no _category_key.name '_space_group_symop.id' loop_ _category_examples.case _category_examples.detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _space_group_symop.id _space_group_symop.operation_xyz 1 x,y,z 2 -x,-y,-z 3 -x,1/2+y,1/2-z 4 x,1/2-y,1/2+z ; ; Example 1 - The symmetry operations for the space group P21/c. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__space_group_symop.id _item_description.description ; An arbitrary identifier that uniquely labels each symmetry operation in the list. ; _item.name '_space_group_symop.id' _item.category_id space_group_symop _item.mandatory_code yes _item_type.code code _item_related.related_name '_symmetry_equiv.id' _item_related.function_code alternate loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_space_group_symop_id' cif_core.dic 2.3 save_ save__space_group_symop.operation_xyz _item_description.description ; A parsable string giving one of the symmetry operations of the space group in algebraic form. If W is a matrix representation of the rotational part of the symmetry operation defined by the positions and signs of x, y and z, and w is a column of translations defined by the fractions, an equivalent position X' is generated from a given position X by the equation X' = WX + w (Note: X is used to represent bold_italics_x in International Tables for Crystallography Vol. A, Part 5) When a list of symmetry operations is given, it must contain a complete set of coordinate representatives which generates all the operations of the space group by the addition of all primitive translations of the space group. Such representatives are to be found as the coordinates of the general-equivalent position in International Tables for Crystallography Vol. A (2002), to which it is necessary to add any centring translations shown above the general-equivalent position. That is to say, it is necessary to list explicity all the symmetry operations required to generate all the atoms in the unit cell defined by the setting used. ; _item.name '_space_group_symop.operation_xyz' _item.category_id space_group_symop _item.mandatory_code no _item_type.code line # _item_default.value 'x,y,z' _item_related.related_name '_symmetry_equiv.pos_as_xyz' _item_related.function_code alternate loop_ _item_examples.case _item_examples.detail 'x,1/2-y,1/2+z' ; glide reflection through the plane (x,1/4,z), with glide vector 1/2 c ; loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_space_group_symop_operation_xyz' cif_core.dic 2.3 save_ save__space_group_symop.sg_id _item_description.description ; This must match a particular value of _space_group.id, allowing the symmetry operation to be identified with a particular space group. ; _item.name '_space_group_symop.sg_id' _item.category_id space_group_symop _item.mandatory_code no _item_type.code code loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_space_group_symop_sg_id' cif_core.dic 2.3 save_ ################### ## VALENCE_PARAM ## ################### save_valence_param _category.description ; Data items in the VALENCE_PARAM category define the parameters used for calculating bond valences from bond lengths. In addition to the parameters, a pointer is given to the reference (in VALENCE_REF) from which the bond-valence parameters were taken. ; _category.id 'valence_param' _category.mandatory_code no loop_ _category_key.name '_valence_param.atom_1' '_valence_param.atom_1_valence' '_valence_param.atom_2' '_valence_param.atom_2_valence' loop_ _category_examples.case _category_examples.detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _valence_param.atom_1 _valence_param.atom_1_valence _valence_param.atom_2 _valence_param.atom_2_valence _valence_param.Ro _valence_param.B _valence_param.ref_id _valence_param.details Cu 2 O -2 1.679 0.37 a . Cu 2 O -2 1.649 0.37 j . Cu 2 N -3 1.64 0.37 m '2-coordinate N' Cu 2 N -3 1.76 0.37 m '3-coordinate N' loop_ _valence_ref.id _valence_ref.reference a 'Brown & Altermatt (1985), Acta Cryst. B41, 244-247' j 'Liu & Thorp (1993), Inorg. Chem. 32, 4102-4205' m 'See, Krause & Strub (1998), Inorg. Chem. 37, 5369-5375' ; ; Example 1 - a bond-valence parameter list with accompanying references. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__valence_param.atom_1 _item_description.description ; The element symbol of the first atom forming the bond whose bond-valence parameters are given in this category. ; _item.name '_valence_param.atom_1' _item.category_id valence_param _item.mandatory_code yes _item_type.code code loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_valence_param_atom_1' cif_core.dic 2.3 save_ save__valence_param.atom_1_valence _item_description.description ; The valence (formal charge) of the first atom whose bond-valence parameters are given in this category. ; _item.name '_valence_param.atom_1_valence' _item.category_id valence_param _item.mandatory_code yes _item_type.code int loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_valence_param_atom_1_valence' cif_core.dic 2.3 save_ save__valence_param.atom_2 _item_description.description ; The element symbol of the second atom forming the bond whose bond-valence parameters are given in this category. ; _item.name '_valence_param.atom_2' _item.category_id valence_param _item.mandatory_code yes _item_type.code code loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_valence_param_atom_2' cif_core.dic 2.3 save_ save__valence_param.atom_2_valence _item_description.description ; The valence (formal charge) of the second atom whose bond-valence parameters are given in this category. ; _item.name '_valence_param.atom_2_valence' _item.category_id valence_param _item.mandatory_code yes _item_type.code int loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_valence_param_atom_2_valence' cif_core.dic 2.3 save_ save__valence_param.B _item_description.description ; The bond-valence parameter B used in the expression s = exp[(Ro - R)/B] where s is the valence of a bond of length R. ; _item.name '_valence_param.B' _item.category_id valence_param _item.mandatory_code no _item_type.code float _item_units.code 'angstroms' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_valence_param_B' cif_core.dic 2.3 save_ save__valence_param.details _item_description.description ; Details of or comments on the bond-valence parameters. ; _item.name '_valence_param.details' _item.category_id valence_param _item.mandatory_code no _item_type.code text loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_valence_param_details' cif_core.dic 2.3 save_ save__valence_param.id _item_description.description ; An identifier for the valence parameters of a bond between the given atoms. ; _item.name '_valence_param.id' _item.category_id valence_param _item.mandatory_code no _item_type.code code loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_valence_param_id' cif_core.dic 2.3 save_ save__valence_param.ref_id _item_description.description ; An identifier which links to the reference to the source from which the bond-valence parameters are taken. A child of _valence_ref.id which it must match. ; _item.name '_valence_param.ref_id' _item.category_id valence_param _item.mandatory_code no _item_type.code code loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_valence_param_ref_id' cif_core.dic 2.3 save_ save__valence_param.Ro _item_description.description ; The bond-valence parameter Ro used in the expression s = exp[(Ro - R)/B] where s is the valence of a bond of length R. ; _item.name '_valence_param.Ro' _item.category_id valence_param _item.mandatory_code no _item_type.code float _item_units.code angstroms loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_valence_param_Ro' cif_core.dic 2.3 save_ ################# ## VALENCE_REF ## ################# save_valence_ref _category.description ; Data items in the VALENCE_REF category list the references from which the bond-valence parameters have been taken. ; _category.id 'valence_ref' _category.mandatory_code no _category_key.name '_valence_ref.id' save_ save__valence_ref.id _item_description.description ; An identifier for items in this category. Parent of _valence_param.ref_id, which must have the same value. ; _item.name '_valence_ref.id' _item.category_id valence_ref _item.mandatory_code yes _item_type.code code loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_valence_ref_id' cif_core.dic 2.3 save_ save__valence_ref.reference _item_description.description ; Literature reference from which the valence parameters identified by _valence_param.id were taken. ; _item.name '_valence_ref.reference' _item.category_id valence_ref _item.mandatory_code no _item_type.code text loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_valence_ref_reference' cif_core.dic 2.3 save_ #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof ########################################################################### # # File: mmcif_pdbx-def-2.dic # # PDB Exchange Data Dictionary # # This data dictionary contains definitions used by wwPDB for data exchange # and data processing. # # Definition Section 2 # # ########################################################################### save_pdbx_audit _category.description ; The PDBX_AUDIT holds current version information. ; _category.id 'pdbx_audit' _category.mandatory_code no loop_ _category_key.name '_pdbx_audit.entry_id' loop_ _category_group.id 'inclusive_group' 'audit_group' save_ save__pdbx_audit.entry_id _item_description.description ; The value of _pdbx_audit.entry_id identifies the data block. ; _item.name '_pdbx_audit.entry_id' _item.category_id pdbx_audit _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_audit.entry_id' _item_linked.parent_name '_entry.id' _item_examples.case 'BDL001' save_ save__pdbx_audit.current_version _item_description.description ; The value of _pdbx_audit.entry_id identifies the data block. ; _item.name '_pdbx_audit.current_version' _item.category_id pdbx_audit _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_audit.current_version' _item_linked.parent_name '_audit.revision_id' _item_examples.case '1' save_ ### ### ####################### ## PDBX_AUDIT_AUTHOR ## ####################### save_pdbx_audit_author _category.description ; Data items in the PDBX_AUDIT_AUTHOR category record details about the author(s) of the data block. ; _category.id pdbx_audit_author _category.mandatory_code no _category_key.name '_pdbx_audit_author.ordinal' loop_ _category_group.id 'inclusive_group' 'audit_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; loop_ _pdbx_audit_author.name _pdbx_audit_author.address _pdbx_audit_author.ordinal 'Fitzgerald, Paula M.D.' ; Department of Biophysical Chemistry Merck Research Laboratories P. O. Box 2000, Ry80M203 Rahway, New Jersey 07065 USA ; 1 'McKeever, Brian M.' ; Department of Biophysical Chemistry Merck Research Laboratories P. O. Box 2000, Ry80M203 Rahway, New Jersey 07065 USA ; 2 'Van Middlesworth, J.F.' ; Department of Biophysical Chemistry Merck Research Laboratories P. O. Box 2000, Ry80M203 Rahway, New Jersey 07065 USA ; 3 'Springer, James P.' ; Department of Biophysical Chemistry Merck Research Laboratories P. O. Box 2000, Ry80M203 Rahway, New Jersey 07065 USA ; 4 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_audit_author.address _item_description.description ; The address of an author of this data block. If there are multiple authors, _pdbx_audit_author.address is looped with _pdbx_audit_author.name. ; _item.name '_pdbx_audit_author.address' _item.category_id pdbx_audit_author _item.mandatory_code no _item_type.code text _item_examples.case ; Department Institute Street City and postcode COUNTRY ; save_ save__pdbx_audit_author.name _item_description.description ; The name of an author of this data block. If there are multiple authors, _pdbx_audit_author.name is looped with _pdbx_audit_author.address. The family name(s), followed by a comma and including any dynastic compoents, precedes the first name(s) or initial(s). ; _item.name '_pdbx_audit_author.name' _item.category_id pdbx_audit_author _item.mandatory_code yes _item_type.code line loop_ _item_examples.case 'Bleary, Percival R.' "O'Neil, F.K." 'Van den Bossche, G.' 'Yang, D.-L.' 'Simonov, Yu.A' save_ save__pdbx_audit_author.ordinal _item_description.description ; A unique sequential integer identifier for each author. ; _item.name '_pdbx_audit_author.ordinal' _item.category_id pdbx_audit_author _item.mandatory_code yes _item_type.code int loop_ _item_examples.case 1 2 3 save_ ### ### save_pdbx_database_message _category.description ; The PDBX_DATABASE_MESSAGE category provides information about correspondance related to a structure deposition. ; _category.id 'pdbx_database_message' _category.mandatory_code no loop_ _category_key.name '_pdbx_database_message.message_id' '_pdbx_database_message.entry_id' loop_ _category_group.id 'inclusive_group' 'database_group' 'pdbx_group' save_ save__pdbx_database_message.entry_id _item_description.description ; The value of _pdbx_database_message.entry_id identifies the data block. ; _item.name '_pdbx_database_message.entry_id' _item.category_id pdbx_database_message _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_database_message.entry_id' _item_linked.parent_name '_entry.id' _item_examples.case 'BDL001' _item_aliases.alias_name '_ndb_database_message.entry_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_message.message_id _item_description.description ; This is an unique and sequential identifier for a message. ; _item.name '_pdbx_database_message.message_id' _item.category_id pdbx_database_message _item.mandatory_code yes _item_type.code text _item_examples.case 'message 1' _item_aliases.alias_name '_ndb_database_message.message_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_message.date _item_description.description ; This is the date when a message was sent or received. ; _item.name '_pdbx_database_message.date' _item.category_id pdbx_database_message _item.mandatory_code yes _item_type.code yyyy-mm-dd:hh:mm _item_aliases.alias_name '_ndb_database_message.date' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_message.content_type _item_description.description ; This code defines the content of the message. ; _item.name '_pdbx_database_message.content_type' _item.category_id pdbx_database_message _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail DEPOSIT 'A component of a deposition or revision' REMINDER 'A message reminding the depositor to send materials' QUERY 'A query to a depositor for specific information' OTHER 'A miscellaneous message' _item_aliases.alias_name '_ndb_database_message.content_type' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_message.message_type _item_description.description ; Defines how the message was sent or received. ; _item.name '_pdbx_database_message.message_type' _item.category_id pdbx_database_message _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail FAX 'A facsimile message' EMAIL 'An electronic mail message' MAIL 'A conventional mail message' PHONE 'A phone message' _item_aliases.alias_name '_ndb_database_message.message_type' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_message.sender _item_description.description ; The name of the sender. ; _item.name '_pdbx_database_message.sender' _item.category_id pdbx_database_message _item.mandatory_code no _item_type.code text _item_aliases.alias_name '_ndb_database_message.sender' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_message.sender_address_fax _item_description.description ; The FAX phone number of the sender. ; _item.name '_pdbx_database_message.sender_address_fax' _item.category_id pdbx_database_message _item.mandatory_code no _item_type.code fax _item_aliases.alias_name '_ndb_database_message.sender_address_fax' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_message.sender_address_phone _item_description.description ; The phone number of the sender. ; _item.name '_pdbx_database_message.sender_address_phone' _item.category_id pdbx_database_message _item.mandatory_code no _item_type.code phone _item_aliases.alias_name '_ndb_database_message.sender_address_phone' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_message.sender_address_email _item_description.description ; The email address of the sender. ; _item.name '_pdbx_database_message.sender_address_email' _item.category_id pdbx_database_message _item.mandatory_code no _item_type.code email _item_aliases.alias_name '_ndb_database_message.sender_address_email' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_message.sender_address_mail _item_description.description ; The postal address of the sender. ; _item.name '_pdbx_database_message.sender_address_mail' _item.category_id pdbx_database_message _item.mandatory_code no _item_type.code text _item_aliases.alias_name '_ndb_database_message.sender_address_mail' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_message.receiver _item_description.description ; The name of the receiver. ; _item.name '_pdbx_database_message.receiver' _item.category_id pdbx_database_message _item.mandatory_code no _item_type.code text _item_aliases.alias_name '_ndb_database_message.receiver' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_message.receiver_address_fax _item_description.description ; The FAX phone number of the receiver. ; _item.name '_pdbx_database_message.receiver_address_fax' _item.category_id pdbx_database_message _item.mandatory_code no _item_type.code fax _item_aliases.alias_name '_ndb_database_message.receiver_address_fax' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_message.receiver_address_phone _item_description.description ; The phone number of the receiver. ; _item.name '_pdbx_database_message.receiver_address_phone' _item.category_id pdbx_database_message _item.mandatory_code no _item_type.code phone _item_aliases.alias_name '_ndb_database_message.receiver_address_phone' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_message.receiver_address_email _item_description.description ; The email address of the receiver. ; _item.name '_pdbx_database_message.receiver_address_email' _item.category_id pdbx_database_message _item.mandatory_code no _item_type.code email _item_aliases.alias_name '_ndb_database_message.receiver_address_email' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_message.receiver_address_mail _item_description.description ; The postal address of the receiver. ; _item.name '_pdbx_database_message.receiver_address_mail' _item.category_id pdbx_database_message _item.mandatory_code no _item_type.code text _item_aliases.alias_name '_ndb_database_message.receiver_address_mail' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_message.message _item_description.description ; The text of the message. ; _item.name '_pdbx_database_message.message' _item.category_id pdbx_database_message _item.mandatory_code no _item_type.code text _item_aliases.alias_name '_ndb_database_message.message' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### ### save_pdbx_database_PDB_obs_spr _category.description ; The PDBX_DATABASE_PDB_OBS_SPR category provides placeholders for information on obsolete/superseded PDB entries ; _category.id 'pdbx_database_PDB_obs_spr' _category.mandatory_code no loop_ _category_key.name '_pdbx_database_PDB_obs_spr.pdb_id' '_pdbx_database_PDB_obs_spr.replace_pdb_id' loop_ _category_group.id 'inclusive_group' 'database_group' 'pdbx_group' save_ save__pdbx_database_PDB_obs_spr.id _item_description.description ; Identifier for the type of obsolete entry to be added to this entry. ; _item.name '_pdbx_database_PDB_obs_spr.id' _item.category_id pdbx_database_PDB_obs_spr _item.mandatory_code yes _item_type.code code _item_examples.case 'OBSLTE' loop_ _item_enumeration.value 'OBSLTE' 'SPRSDE' _item_aliases.alias_name '_ndb_database_PDB_obs_spr.id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_PDB_obs_spr.date _item_description.description ; The date of replacement. ; _item.name '_pdbx_database_PDB_obs_spr.date' _item.category_id pdbx_database_PDB_obs_spr _item.mandatory_code yes _item_type.code yyyy-mm-dd:hh:mm _item_examples.case '1997-03-30' _item_aliases.alias_name '_ndb_database_PDB_obs_spr.date' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_PDB_obs_spr.pdb_id _item_description.description ; The new PDB identifier for the replaced entry. ; _item.name '_pdbx_database_PDB_obs_spr.pdb_id' _item.category_id pdbx_database_PDB_obs_spr _item.mandatory_code yes _item_type.code code _item_examples.case 2ABC _item_aliases.alias_name '_ndb_database_PDB_obs_spr.pdb_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_PDB_obs_spr.replace_pdb_id _item_description.description ; The PDB identifier for the replaced (OLD) entry. ; _item.name '_pdbx_database_PDB_obs_spr.replace_pdb_id' _item.category_id pdbx_database_PDB_obs_spr _item.mandatory_code yes _item_type.code code _item_examples.case 3ABC _item_aliases.alias_name '_ndb_database_PDB_obs_spr.replace_pdb_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### ### ### save_pdbx_database_proc _category.description ; Internal records to track the data processing cycle. ; _category.id 'pdbx_database_proc' _category.mandatory_code no loop_ _category_key.name '_pdbx_database_proc.cycle_id' '_pdbx_database_proc.entry_id' loop_ _category_group.id 'inclusive_group' 'database_group' 'pdbx_group' _category_examples.case ; _pdbx_database_proc.entry_id 'BDL001' _pdbx_database_proc.cycle_id 1 _pdbx_database_proc.date_begin_cycle 1998-02-27 _pdbx_database_proc.date_end_cycle 1998-02-27 ; save_ save__pdbx_database_proc.entry_id _item_description.description ; The value of _pdbx_database_proc.entry_id identifies the data block. ; _item.name '_pdbx_database_proc.entry_id' _item.category_id pdbx_database_proc _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_database_proc.entry_id' _item_linked.parent_name '_entry.id' _item_examples.case 'BDL001' _item_aliases.alias_name '_ndb_database_proc.entry_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_proc.cycle_id _item_description.description ; This is a number of the processing cycle. ; _item.name '_pdbx_database_proc.cycle_id' _item.category_id pdbx_database_proc _item.mandatory_code yes _item_type.code code _item_examples.case '1 for the initial cycle' _item_aliases.alias_name '_ndb_database_proc.cycle_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_proc.date_begin_cycle _item_description.description ; This is the date of the start of the processing cycle. ; _item.name '_pdbx_database_proc.date_begin_cycle' _item.category_id pdbx_database_proc _item.mandatory_code yes _item_type.code yyyy-mm-dd:hh:mm _item_examples.case 1983-02-27 _item_aliases.alias_name '_ndb_database_proc.date_begin_cycle' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_proc.date_end_cycle _item_description.description ; This is the date of the end of the processing cycle. ; _item.name '_pdbx_database_proc.date_end_cycle' _item.category_id pdbx_database_proc _item.mandatory_code yes _item_type.code yyyy-mm-dd:hh:mm _item_examples.case 1983-02-27 _item_aliases.alias_name '_ndb_database_proc.date_end_cycle' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_proc.details _item_description.description ; Special details about the current processing cycle. ; _item.name '_pdbx_database_proc.details' _item.category_id pdbx_database_proc _item.mandatory_code no _item_type.code text _item_aliases.alias_name '_ndb_database_proc.details' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### ### ### save_pdbx_database_remark _category.description ; Data items in the PDBX_DATABASE_REMARK category record keep additional information about the entry. They are mostly used to create 'non-standard' PDB REMARK annotations (6-99). ; _category.id pdbx_database_remark _category.mandatory_code no _category_key.name '_pdbx_database_remark.id' loop_ _category_group.id 'inclusive_group' 'database_group' 'pdbx_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 1ABC ; ; loop_ _pdbx_database_remark.id _pdbx_database_remark.text 1 ; THE NON-CRYSTALLOGRAPHIC RELATIONSHIP BETWEEN THE THREE DOUBLE HELICES IN THE ASYMMETRIC UNIT IS DESCRIBED IN THE MTRIX1-3 RECORDS. ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_database_remark.id _item_description.description ; A unique identifier for the PDB remark record. ; _item.name '_pdbx_database_remark.id' _item.category_id pdbx_database_remark _item.mandatory_code yes _item_type.code int _item_aliases.alias_name '_rcsb_database_PDB_remark.id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_remark.text _item_description.description ; The full text of the PDB remark record. ; _item.name '_pdbx_database_remark.text' _item.category_id pdbx_database_remark _item.mandatory_code no _item_type.code text _item_aliases.alias_name '_rcsb_database_PDB_remark.text' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### ### save_pdbx_database_status _category.description ; These are internal RCSB records to keep track of data processing and status of the entry. ; _category.id 'pdbx_database_status' _category.mandatory_code no _category_key.name '_pdbx_database_status.entry_id' loop_ _category_group.id 'inclusive_group' 'database_group' 'pdbx_group' _category_examples.case ; _pdbx_database_status.entry_id 1ABC _pdbx_database_status.status_code REL _pdbx_database_status.author_release_status_code REL _pdbx_database_status.deposit_site RCSB _pdbx_database_status.process_site RCSB _pdbx_database_status.recvd_initial_deposition_date 1996-02-13 _pdbx_database_status.date_author_approval 1996-02-13 _pdbx_database_status.recvd_author_approval Y _pdbx_database_status.author_approval_type EXPLICIT _pdbx_database_status.hold_for_publication N _pdbx_database_status.date_hold_coordinates 1996-02-13 _pdbx_database_status.date_hold_struct_fact 1996-02-13 _pdbx_database_status.date_of_PDB_release 1996-02-14 _pdbx_database_status.date_deposition_form 1996-02-13 _pdbx_database_status.date_coordinates 1996-02-13 _pdbx_database_status.date_struct_fact 1996-02-13 _pdbx_database_status.date_manuscript 1996-02-13 _pdbx_database_status.date_nmr_constraints ? _pdbx_database_status.recvd_deposit_form Y _pdbx_database_status.recvd_coordinates Y _pdbx_database_status.recvd_struct_fact Y _pdbx_database_status.recvd_manuscript Y _pdbx_database_status.recvd_nmr_constraints N ; save_ save__pdbx_database_status.status_code _item_description.description ; Code for status of file. ; _item.name '_pdbx_database_status.status_code' _item.category_id pdbx_database_status _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail PROC 'Processing in progress' WAIT 'Awaiting author approval' REL 'Released' HOLD 'On hold until yyyy-mm-dd' HPUB 'On hold until publication' OBS 'Entry has been obsoleted and replaced by another entry' DEL 'Entry has been deleted' WDRN 'Entry has been withdrawn' BIB 'Only a bibliographic entry exists for this entry; there are no coordinates' REV 'Entry currently under revision' UPD 'Deprecated code' loop_ _item_examples.case REL HOLD REV BIB _item_aliases.alias_name '_ndb_database_status.status_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.author_release_status_code _item_description.description ; The release status authorized by the depositor. ; _item.name '_pdbx_database_status.author_release_status_code' _item.category_id pdbx_database_status _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail REL 'Release' HOLD 'On hold until yyyy-mm-dd' HPUB 'On hold until publication' OBS 'Entry has been obsoleted and replaced by another entry' WDRN 'Entry has been withdrawn' _item_examples.case ; REL = Release HOLD = On hold until yyyy-mm-dd HPUB = On hold until publication OBS = Entry has been obsoleted and replaced by another entry WDRN = Entry has been withdrawn by depositor ; _item_aliases.alias_name '_ndb_database_status.author_release_status_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.status_code_sf _item_description.description ; Code for status of structure factor file. ; _item.name '_pdbx_database_status.status_code_sf' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail PROC 'Processing in progress' REL 'Release' HOLD 'On hold until yyyy-mm-dd' HPUB 'On hold until publication' OBS 'Entry has been obsoleted and replaced by another entry' WDRN 'Entry has been withdrawn' WAIT 'Awaiting author approval' _item_examples.case ; PROC = Processing in progress REL = Release HOLD = On hold until yyyy-mm-dd HPUB = On hold until publication OBS = Entry has been obsoleted and replaced by another entry WDRN = Entry has been withdrawn by depositor WAIT = Awaiting author approval ; _item_aliases.alias_name '_ndb_database_status.status_code_sf' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.status_code_mr _item_description.description ; Code for status of NMR constraints file. ; _item.name '_pdbx_database_status.status_code_mr' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail PROC 'Processing in progress' REL 'Release' HOLD 'On hold until yyyy-mm-dd' HPUB 'On hold until publication' OBS 'Entry has been obsoleted and replaced by another entry' WDRN 'Entry has been withdrawn' WAIT 'Awaiting author approval' _item_examples.case ; PROC = Processing in progress REL = Release HOLD = On hold until yyyy-mm-dd HPUB = On hold until publication OBS = Entry has been obsoleted and replaced by another entry WDRN = Entry has been withdrawn by depositor WAIT = Awaiting author approval ; _item_aliases.alias_name '_ndb_database_status.status_code_mr' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.dep_release_code_coordinates _item_description.description ; The deposited coordinates for this deposition will be released according the value of this item. ; _item.name '_pdbx_database_status.dep_release_code_coordinates' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code line _item_default.value 'RELEASE NOW' loop_ _item_enumeration.value _item_enumeration.detail 'RELEASE NOW' 'Release immediately' 'HOLD FOR PUBLICATION' 'Hold until primary citation is published' 'HOLD FOR 6 WEEKS' 'Hold for 6 weeks' 'HOLD FOR 6 MONTHS' 'Hold for 6 months' 'HOLD FOR 1 YEAR' 'Hold for 1 year' _item_examples.case ; RELEASE NOW = Release immediately HOLD FOR PUBLICATION = Hold until the primary citation is published HOLD FOR 6 WEEKS = Hold for 6 weeks HOLD FOR 6 MONTHS = Hold for 6 months HOLD FOR 1 YEAR = Hold for 1 year ; _item_aliases.alias_name '_ndb_database_status.dep_release_code_coordinates' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.dep_release_code_sequence _item_description.description ; The sequence information for this deposition will be released according the value of this item. Setting this status code to "RELEASE NOW" indicates that the macromolecular sequence(s) for this entry may be displayed in PDB status reports prior to the release of the entry. Setting this status code to "HOLD FOR RELEASE" conceals the sequence information in PDB status reports until the coordinate data for this entry are released. ; _item.name '_pdbx_database_status.dep_release_code_sequence' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code line # _item_default.value 'RELEASE NOW' loop_ _item_enumeration.value _item_enumeration.detail 'RELEASE NOW' 'Release sequence information in status reports immediately' 'HOLD FOR RELEASE' ;Conceal sequence information in status reports until coordinate data is released ; _item_examples.case ; RELEASE NOW = Release sequence information in status reports immediately HOLD FOR RELEASE = Conceal sequence information in status reports until coordinate data is release ; _item_aliases.alias_name '_ndb_database_status.dep_release_code_sequence' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.dep_release_code_struct_fact _item_description.description ; The deposited structure factors for this deposition will be released according the value of this item. ; _item.name '_pdbx_database_status.dep_release_code_struct_fact' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code line _item_default.value 'RELEASE NOW' # loop_ # _item_enumeration.value # _item_enumeration.detail # 'RELEASE NOW' 'Release immediately' # 'HOLD FOR PUBLICATION' 'Hold until primary citation is published' # 'HOLD FOR 6 MONTHS' 'Hold for 6 months' # 'HOLD FOR 1 YEAR' 'Hold for 1 year' # 'HOLD FOR 4 YEARS' 'Hold for 4 years' _item_examples.case ; RELEASE NOW = Release immediately HOLD FOR PUBLICATION = Hold until the primary citation is published HOLD FOR 6 WEEKS = Hold for 6 weeks HOLD FOR 6 MONTHS = Hold for 6 months HOLD FOR 1 YEAR = Hold for 1 year ; _item_aliases.alias_name '_ndb_database_status.dep_release_code_struct_fact' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.dep_release_code_nmr_constraints _item_description.description ; The deposited NMR constrait data for this deposition will be released according the value of this item. ; _item.name '_pdbx_database_status.dep_release_code_nmr_constraints' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code line _item_default.value 'RELEASE NOW' # loop_ # _item_enumeration.value # _item_enumeration.detail # 'RELEASE NOW' 'Release immediately' # 'HOLD FOR PUBLICATION' 'Hold until primary citation is published' # 'HOLD FOR 6 MONTHS' 'Hold for 6 months' # 'HOLD FOR 1 YEAR' 'Hold for 1 year' _item_examples.case ; RELEASE NOW = Release immediately HOLD FOR PUBLICATION = Hold until the primary citation is published HOLD FOR 6 WEEKS = Hold for 6 weeks HOLD FOR 6 MONTHS = Hold for 6 months HOLD FOR 1 YEAR = Hold for 1 year ; _item_aliases.alias_name '_ndb_database_status.dep_release_code_nmr_constraints' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.entry_id _item_description.description ; The value of _pdbx_database_status.entry_id identifies the data block. ; _item.name '_pdbx_database_status.entry_id' _item.category_id pdbx_database_status _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_database_status.entry_id' _item_linked.parent_name '_entry.id' _item_examples.case 'BDL001' _item_aliases.alias_name '_ndb_database_status.entry_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.recvd_deposit_form _item_description.description ; This code indicates whether the deposition form for an entry has been received. ; _item.name '_pdbx_database_status.recvd_deposit_form' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code uchar1 loop_ _item_enumeration.value _item_enumeration.detail Y 'Yes' N 'No' _item_examples.case Y _item_aliases.alias_name '_ndb_database_status.recvd_deposit_form' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.date_deposition_form _item_description.description ; The date the deposition form is received. ; _item.name '_pdbx_database_status.date_deposition_form' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code yyyy-mm-dd:hh:mm _item_examples.case 1982-02-21 _item_aliases.alias_name '_ndb_database_status.date_deposition_form' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.recvd_coordinates _item_description.description ; This code indicates whether the coordinates for an entry have been received. ; _item.name '_pdbx_database_status.recvd_coordinates' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code uchar1 loop_ _item_enumeration.value _item_enumeration.detail Y 'Yes' N 'No' _item_examples.case Y _item_aliases.alias_name '_ndb_database_status.recvd_coordinates' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.date_coordinates _item_description.description ; The date the coordinates are received. ; _item.name '_pdbx_database_status.date_coordinates' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code yyyy-mm-dd:hh:mm _item_examples.case 1983-02-21 _item_aliases.alias_name '_ndb_database_status.date_coordinates' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.recvd_struct_fact _item_description.description ; This code indicates whether the structure factors for an entry have been received. ; _item.name '_pdbx_database_status.recvd_struct_fact' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code uchar1 loop_ _item_enumeration.value _item_enumeration.detail Y 'Yes' N 'No' _item_examples.case Y _item_aliases.alias_name '_ndb_database_status.recvd_struct_fact' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.date_struct_fact _item_description.description ; The date the structure factors are received. ; _item.name '_pdbx_database_status.date_struct_fact' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code yyyy-mm-dd:hh:mm _item_examples.case 1983-02-28 _item_aliases.alias_name '_ndb_database_status.date_struct_fact' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ # save__pdbx_database_status.recvd_nmr_constraints _item_description.description ; This code indicates whether the NMR contraint data for an entry have been received. ; _item.name '_pdbx_database_status.recvd_nmr_constraints' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code uchar1 loop_ _item_enumeration.value _item_enumeration.detail Y 'Yes' N 'No' _item_examples.case Y _item_aliases.alias_name '_ndb_database_status.recvd_nmr_constraints' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.date_nmr_constraints _item_description.description ; The date the structure factors are received. ; _item.name '_pdbx_database_status.date_nmr_constraints' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code yyyy-mm-dd:hh:mm _item_examples.case 1983-02-28 _item_aliases.alias_name '_ndb_database_status.date_nmr_constraints' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.recvd_internal_approval _item_description.description ; This code indicates whether the internal approval for an entry have been received. ; _item.name '_pdbx_database_status.recvd_internal_approval' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code uchar1 loop_ _item_enumeration.value _item_enumeration.detail Y 'Yes' N 'No' _item_examples.case Y _item_aliases.alias_name '_ndb_database_status.recvd_internal_approval' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.recvd_manuscript _item_description.description ; This code indicates whether the manuscript for an entry has been received. ; _item.name '_pdbx_database_status.recvd_manuscript' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code uchar1 loop_ _item_enumeration.value _item_enumeration.detail Y 'Yes' N 'No' _item_examples.case Y _item_aliases.alias_name '_ndb_database_status.recvd_manuscript' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.date_manuscript _item_description.description ; The date the manuscript is received. ; _item.name '_pdbx_database_status.date_manuscript' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code yyyy-mm-dd:hh:mm _item_examples.case 1983-02-28 _item_aliases.alias_name '_ndb_database_status.date_manuscript' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.name_depositor _item_description.description ; The last name of the depositor to be used in correspondance. ; _item.name '_pdbx_database_status.name_depositor' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code text _item_examples.case 'Smith' _item_aliases.alias_name '_ndb_database_status.name_depositor' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.recvd_author_approval _item_description.description ; This code indicates whether the author's approval for an entry has been received. ; _item.name '_pdbx_database_status.recvd_author_approval' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code uchar1 loop_ _item_enumeration.value _item_enumeration.detail Y 'Yes' N 'No' _item_examples.case Y _item_aliases.alias_name '_ndb_database_status.recvd_author_approval' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.author_approval_type _item_description.description ; This code indicates whether the author's approval for an entry was received explicitly or implicitly. The latter is automatically implied by failure to respond to the validation summary within the prescribed period. ; _item.name '_pdbx_database_status.author_approval_type' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code code loop_ _item_enumeration.value implicit explicit _item_examples.case ; implicit = automatic approval by failure to acknowledge explicit = approval via depositor acknowledgement ; _item_aliases.alias_name '_ndb_database_status.author_approval_type' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.date_author_approval _item_description.description ; The date the author's approval is received. ; _item.name '_pdbx_database_status.date_author_approval' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code yyyy-mm-dd:hh:mm _item_examples.case 1983-02-20 _item_aliases.alias_name '_ndb_database_status.date_author_approval' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.recvd_initial_deposition_date _item_description.description ; The date of initial deposition. (The first message for deposition has been received.) ; _item.name '_pdbx_database_status.recvd_initial_deposition_date' _item.category_id pdbx_database_status _item.mandatory_code yes _item_type.code yyyy-mm-dd:hh:mm _item_examples.case 1983-02-21 _item_aliases.alias_name '_ndb_database_status.recvd_initial_deposition_date' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.date_submitted _item_description.description ; The date of complete deposition. This corresponds to the date at which the PDB identifier is assigned. ; _item.name '_pdbx_database_status.date_submitted' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code yyyy-mm-dd:hh:mm _item_examples.case 1983-02-20 _item_aliases.alias_name '_ndb_database_status.date_submitted' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.rcsb_annotator _item_description.description ; The initials of the annotator processing this entry. ; _item.name '_pdbx_database_status.rcsb_annotator' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'BS' 'SJ' 'KB' _item_aliases.alias_name '_ndb_database_status.rcsb_annotator' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.date_of_sf_release _item_description.description ; The date of PDB/RCSB release. This corresponds to the date at which the entry is placed into the public archive. ; _item.name '_pdbx_database_status.date_of_sf_release' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code yyyy-mm-dd _item_examples.case 1999-02-28 _item_aliases.alias_name '_ndb_database_status.date_of_sf_release' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.date_of_mr_release _item_description.description ; The date of PDB/RCSB release. This corresponds to the date at which the entry is placed into the public archive. ; _item.name '_pdbx_database_status.date_of_mr_release' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code yyyy-mm-dd _item_examples.case 1999-02-28 _item_aliases.alias_name '_ndb_database_status.date_of_mr_release' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.date_of_PDB_release _item_description.description ; PDB release date. This is the date that appears in the PDB REVDAT record. ; _item.name '_pdbx_database_status.date_of_PDB_release' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code yyyy-mm-dd:hh:mm _item_examples.case 1983-02-28 _item_aliases.alias_name '_ndb_database_status.date_of_PDB_release' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.date_hold_coordinates _item_description.description ; At an author's request, a coordinate entry may be held after processing for some period of time. ; _item.name '_pdbx_database_status.date_hold_coordinates' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code yyyy-mm-dd:hh:mm _item_examples.case 1983-02-28 _item_aliases.alias_name '_ndb_database_status.date_hold_coordinates' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.date_hold_struct_fact _item_description.description ; At an author's request, the structure factors may be held after processing for some period of time. ; _item.name '_pdbx_database_status.date_hold_struct_fact' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code yyyy-mm-dd:hh:mm _item_examples.case 1983-02-28 _item_aliases.alias_name '_ndb_database_status.date_hold_struct_fact' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.date_hold_nmr_constraints _item_description.description ; At an author's request, the NMR constraint data may be held after processing for some period of time. ; _item.name '_pdbx_database_status.date_hold_nmr_constraints' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code yyyy-mm-dd:hh:mm _item_examples.case 1983-02-28 _item_aliases.alias_name '_ndb_database_status.date_hold_nmr_constraints' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.hold_for_publication _item_description.description ; At an author's request, an entry is to be held until publication. ; _item.name '_pdbx_database_status.hold_for_publication' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code uchar1 loop_ _item_enumeration.value _item_enumeration.detail Y 'Yes' N 'No' _item_examples.case Y _item_aliases.alias_name '_ndb_database_status.hold_for_publication' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.SG_entry _item_description.description ; This code indicates whether the entry belongs to Structural Genomics Project. ; _item.name '_pdbx_database_status.SG_entry' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code uchar1 loop_ _item_enumeration.value _item_enumeration.detail Y 'Yes' N 'No' _item_examples.case Y _item_aliases.alias_name '_ndb_database_status.SG_entry' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.pdb_date_of_author_approval _item_description.description ; This is the date when PDB received the author's approval for an entry which has been processed by NDB. (This is a place holder for entries processed before Jan. 1, 1996.) ; _item.name '_pdbx_database_status.pdb_date_of_author_approval' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code yyyy-mm-dd:hh:mm _item_examples.case 1983-02-27 _item_aliases.alias_name '_ndb_database_status.pdb_date_of_author_approval' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.deposit_site _item_description.description ; The site where the file was deposited. ; _item.name '_pdbx_database_status.deposit_site' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code code loop_ _item_examples.case NDB RCSB PDB EBI OSAKA BNL loop_ _item_enumeration.value NDB RCSB PDB EBI OSAKA BNL _item_aliases.alias_name '_ndb_database_status.deposit_site' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_status.process_site _item_description.description ; The site where the file was deposited. ; _item.name '_pdbx_database_status.process_site' _item.category_id pdbx_database_status _item.mandatory_code no _item_type.code code loop_ _item_examples.case NDB RCSB EBI OSAKA PDB PRAGUE loop_ _item_enumeration.value NDB RCSB EBI OSAKA PDB PRAGUE _item_aliases.alias_name '_ndb_database_status.process_site' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### ### save_pdbx_entity_name _category.description ; The PDBX_ENTITY_NAME records additional name information for each entity. ; _category.id pdbx_entity_name _category.mandatory_code no loop_ _category_key.name '_pdbx_entity_name.entity_id' '_pdbx_entity_name.name' '_pdbx_entity_name.name_type' loop_ _category_group.id 'inclusive_group' 'entity_group' 'pdbx_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; loop_ _pdbx_entity_name.entity_id _pdbx_entity_name.name _pdbx_entity_name.name_type 1 "PLASTOCYANIN" 'SWS-NAME' 1 "Electron transport" 'SWS-KEYWORD' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_entity_name.entity_id _item_description.description ; Pointer to _entity.id. ; _item.name '_pdbx_entity_name.entity_id' _item.category_id pdbx_entity_name _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_entity_name.entity_id' _item_linked.parent_name '_entity.id' _item_aliases.alias_name '_rcsb_entity_name.entity_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_entity_name.name _item_description.description ; Entity name. ; _item.name '_pdbx_entity_name.name' _item.category_id pdbx_entity_name _item.mandatory_code yes _item_type.code line _item_aliases.alias_name '_rcsb_entity_name.name' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_entity_name.name_type _item_description.description ; Entity name type. ; _item.name '_pdbx_entity_name.name_type' _item.category_id pdbx_entity_name _item.mandatory_code yes _item_type.code line _item_aliases.alias_name '_rcsb_entity_name.name_type' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 loop_ _item_enumeration.value 'RCSB_NAME' 'RCSB_SYNONYM' 'SWS-NAME' 'SWS-SYNONYM' 'SWS-KEYWORD' 'GB-NAME' 'GB-SYNONYM' 'GB-KEYWORD' save_ ### ### save_pdbx_prerelease_seq _category.description ; This category provides a placeholder for pre-release sequence information. After release this category should be discarded. ; _category.id pdbx_prerelease_seq _category.mandatory_code no _category_key.name '_pdbx_prerelease_seq.entity_id' loop_ _category_group.id 'inclusive_group' 'entity_group' 'pdbx_group' loop_ _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _pdbx_prerelease_seq.entity_id _pdbx_prerelease_seq.seq_one_letter_code 1 'GKHNGPEHWHKDFPIAKGERQSPVDIDTHTAKYDPSLKPLSVSYDQATSLRILNNGAAFNVEFD' 2 'HKDFPIAKGERQSPVDIDTHTAKYDPSLKPLSVSYDQATSLRILNN' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_prerelease_seq.entity_id _item_description.description ; This data item is a pointer to _entity.id in the ENTITY category. ; _item.name '_pdbx_prerelease_seq.entity_id' _item.category_id pdbx_prerelease_seq _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_prerelease_seq.entity_id' _item_linked.parent_name '_entity.id' _item_aliases.alias_name '_rcsb_prerelease_seq.entity_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_prerelease_seq.seq_one_letter_code _item_description.description ; Chemical sequence expressed as string of one-letter amino acid codes. A for alanine or adenine B for ambiguous asparagine/aspartic-acid R for arginine N for asparagine D for aspartic-acid C for cysteine or cystine or cytosine Q for glutamine E for glutamic-acid Z for ambiguous glutamine/glutamic acid G for glycine or guanine H for histidine I for isoleucine L for leucine K for lysine M for methionine F for phenylalanine P for proline S for serine T for threonine or thymine W for tryptophan Y for tyrosine V for valine U for uracil ; _item.name '_pdbx_prerelease_seq.seq_one_letter_code' _item.category_id pdbx_prerelease_seq _item.mandatory_code no _item_type.code text _item_examples.case ; MSHHWGYGKHNGPEHWHKDFPIAKGERQSPVDIDTHTAKYDPSLKPLSVSYDQATSLRILNNGAAFNVEFD ; _item_aliases.alias_name '_rcsb_prerelease_seq.seq_one_letter_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### ### ### save_pdbx_poly_seq_scheme _category.description ; The PDBX_POLY_SEQ_SCHEME category provides residue level nomenclature mapping for polymer entities. ; _category.id pdbx_poly_seq_scheme _category.mandatory_code no loop_ _category_key.name '_pdbx_poly_seq_scheme.asym_id' '_pdbx_poly_seq_scheme.entity_id' '_pdbx_poly_seq_scheme.seq_id' '_pdbx_poly_seq_scheme.mon_id' loop_ _category_group.id 'inclusive_group' 'struct_group' 'pdbx_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on NDB entry DDFB25 ; ; loop_ _pdbx_poly_seq_scheme.asym_id _pdbx_poly_seq_scheme.entity_id _pdbx_poly_seq_scheme.seq_id _pdbx_poly_seq_scheme.mon_id _pdbx_poly_seq_scheme.ndb_num _pdbx_poly_seq_scheme.pdb_num _pdbx_poly_seq_scheme.auth_num _pdbx_poly_seq_scheme.pdb_mon_id _pdbx_poly_seq_scheme.auth_mon_id _pdbx_poly_seq_scheme.pdb_strand_id _pdbx_poly_seq_scheme.pdb_ins_code A 1 1 C 1 1 1 C C A . A 1 2 G 2 2 2 G G A . A 1 3 T 3 3 3 T T A . A 1 4 +A 4 4 4 +A +A A . A 1 5 C 5 5 5 C C A . A 1 6 G 6 6 6 G G A . ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_poly_seq_scheme.asym_id _item_description.description ; Pointer to _atom_site.label_asym_id. ; _item.name '_pdbx_poly_seq_scheme.asym_id' _item.category_id pdbx_poly_seq_scheme _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_poly_seq_scheme.asym_id' _item_linked.parent_name '_struct_asym.id' loop_ _item_examples.case '1' 'A' '2B3' _item_aliases.alias_name '_ndb_poly_seq_scheme.id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_poly_seq_scheme.entity_id _item_description.description ; Pointer to _entity.id. ; _item.name '_pdbx_poly_seq_scheme.entity_id' _item.category_id pdbx_poly_seq_scheme _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_poly_seq_scheme.entity_id' _item_linked.parent_name '_entity.id' _item_aliases.alias_name '_ndb_poly_seq_scheme.entity_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_poly_seq_scheme.seq_id _item_description.description ; Pointer to _entity_poly_seq.num ; _item.name '_pdbx_poly_seq_scheme.seq_id' _item.category_id pdbx_poly_seq_scheme _item.mandatory_code yes _item_type.code code _item_linked.parent_name '_pdbx_poly_seq_scheme.seq_id' _item_linked.child_name '_entity_poly_seq.num' _item_aliases.alias_name '_ndb_poly_seq_scheme.seq_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_poly_seq_scheme.mon_id _item_description.description ; Pointer to _entity_poly_seq.mon_id. ; _item.name '_pdbx_poly_seq_scheme.mon_id' _item.category_id pdbx_poly_seq_scheme _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_poly_seq_scheme.mon_id' _item_linked.parent_name '_entity_poly_seq.mon_id' _item_aliases.alias_name '_ndb_poly_seq_scheme.mon_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_poly_seq_scheme.pdb_strand_id _item_description.description ; PDB strand/chain id. ; _item.name '_pdbx_poly_seq_scheme.pdb_strand_id' _item.category_id pdbx_poly_seq_scheme _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_ndb_poly_seq_scheme.pdb_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_poly_seq_scheme.ndb_seq_num _item_description.description ; NDB residue number. ; _item.name '_pdbx_poly_seq_scheme.ndb_seq_num' _item.category_id pdbx_poly_seq_scheme _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_ndb_poly_seq_scheme.ndb_num' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_poly_seq_scheme.pdb_seq_num _item_description.description ; PDB residue number. ; _item.name '_pdbx_poly_seq_scheme.pdb_seq_num' _item.category_id pdbx_poly_seq_scheme _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_ndb_poly_seq_scheme.pdb_num' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_poly_seq_scheme.auth_seq_num _item_description.description ; _atom_site.auth_seq_id ; _item.name '_pdbx_poly_seq_scheme.auth_seq_num' _item.category_id pdbx_poly_seq_scheme _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_ndb_poly_seq_scheme.auth_num' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_poly_seq_scheme.pdb_mon_id _item_description.description ; PDB residue name. ; _item.name '_pdbx_poly_seq_scheme.pdb_mon_id' _item.category_id pdbx_poly_seq_scheme _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_ndb_poly_seq_scheme.pdb_mon_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_poly_seq_scheme.auth_mon_id _item_description.description ; _atom_site.auth_comp_id ; _item.name '_pdbx_poly_seq_scheme.auth_mon_id' _item.category_id pdbx_poly_seq_scheme _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_ndb_poly_seq_scheme.auth_mon_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_poly_seq_scheme.pdb_ins_code _item_description.description ; PDB insertion code. ; _item.name '_pdbx_poly_seq_scheme.pdb_ins_code' _item.category_id pdbx_poly_seq_scheme _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_ndb_poly_seq_scheme.pdb_ins_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save_pdbx_nonpoly_scheme _category.description ; The PDBX_NONPOLY_SCHEME category provides residue level nomenclature mapping for non-polymer entities. ; _category.id pdbx_nonpoly_scheme _category.mandatory_code no loop_ _category_key.name '_pdbx_nonpoly_scheme.asym_id' '_pdbx_nonpoly_scheme.ndb_seq_num' loop_ _category_group.id 'inclusive_group' 'struct_group' 'pdbx_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; loop_ _pdbx_nonpoly_scheme.asym_id _pdbx_nonpoly_scheme.entity_id _pdbx_nonpoly_scheme.mon_id _pdbx_nonpoly_scheme.ndb_seq_num _pdbx_nonpoly_scheme.pdb_seq_num _pdbx_nonpoly_scheme.auth_seq_num _pdbx_nonpoly_scheme.pdb_mon_id _pdbx_nonpoly_scheme.auth_mon_id _pdbx_nonpoly_scheme.pdb_strand_id _pdbx_nonpoly_scheme.pdb_ins_code C 3 HOH 100 100 100 HOH HOH C . ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_nonpoly_scheme.asym_id _item_description.description ; Pointer to _atom_site.label_asym_id. ; _item.name '_pdbx_nonpoly_scheme.asym_id' _item.category_id pdbx_nonpoly_scheme _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_nonpoly_scheme.asym_id' _item_linked.parent_name '_atom_site.label_asym_id' loop_ _item_examples.case '1' 'A' '2B3' _item_aliases.alias_name '_ndb_nonpoly_scheme.asym_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nonpoly_scheme.entity_id _item_description.description ; Pointer to _atom_site.label_entity_id. ; _item.name '_pdbx_nonpoly_scheme.entity_id' _item.category_id pdbx_nonpoly_scheme _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_nonpoly_scheme.entity_id' _item_linked.parent_name '_atom_site.label_entity_id' _item_aliases.alias_name '_ndb_nonpoly_scheme.entity_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nonpoly_scheme.mon_id _item_description.description ; Pointer to _atom_site.label_comp_id. ; _item.name '_pdbx_nonpoly_scheme.mon_id' _item.category_id pdbx_nonpoly_scheme _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_nonpoly_scheme.mon_id' _item_linked.parent_name '_atom_site.label_comp_id' _item_aliases.alias_name '_ndb_nonpoly_scheme.mon_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nonpoly_scheme.pdb_strand_id _item_description.description ; PDB strand/chain id. ; _item.name '_pdbx_nonpoly_scheme.pdb_strand_id' _item.category_id pdbx_nonpoly_scheme _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_ndb_nonpoly_scheme.pdb_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nonpoly_scheme.ndb_seq_num _item_description.description ; NDB/RCSB residue number. ; _item.name '_pdbx_nonpoly_scheme.ndb_seq_num' _item.category_id pdbx_nonpoly_scheme _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_ndb_nonpoly_scheme.ndb_num' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nonpoly_scheme.pdb_seq_num _item_description.description ; PDB residue number. ; _item.name '_pdbx_nonpoly_scheme.pdb_seq_num' _item.category_id pdbx_nonpoly_scheme _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_ndb_nonpoly_scheme.pdb_num' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nonpoly_scheme.auth_seq_num _item_description.description ; _atom_site.auth_seq_id ; _item.name '_pdbx_nonpoly_scheme.auth_seq_num' _item.category_id pdbx_nonpoly_scheme _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_ndb_nonpoly_scheme.auth_num' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nonpoly_scheme.pdb_mon_id _item_description.description ; PDB residue name. ; _item.name '_pdbx_nonpoly_scheme.pdb_mon_id' _item.category_id pdbx_nonpoly_scheme _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_ndb_nonpoly_scheme.pdb_mon_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nonpoly_scheme.auth_mon_id _item_description.description ; _atom_site.auth_comp_id ; _item.name '_pdbx_nonpoly_scheme.auth_mon_id' _item.category_id pdbx_nonpoly_scheme _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_ndb_nonpoly_scheme.auth_mon_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nonpoly_scheme.pdb_ins_code _item_description.description ; PDB insertion code. ; _item.name '_pdbx_nonpoly_scheme.pdb_ins_code' _item.category_id pdbx_nonpoly_scheme _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_ndb_nonpoly_scheme.pdb_ins_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### ### ### save_pdbx_refine _category.description ; Data items in the PDBX_REFINE category record details about additional structure refinement parameters which are needed to complete legacy REMARK 3 refinement templates in PDB format files. ; _category.id pdbx_refine _category.mandatory_code no _category_key.name '_pdbx_refine.entry_id' loop_ _category_group.id 'inclusive_group' 'refine_group' 'pdbx_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - PDB placeholders for refinement program SHELX ; ; _pdbx_refine.entry_id ABC001 _pdbx_refine.R_factor_all_4sig_cutoff 0.174 _pdbx_refine.R_factor_obs_4sig_cutoff 0.169 _pdbx_refine.number_reflns_obs_4sig_cutoff 1263 _pdbx_refine.free_R_factor_4sig_cutoff 0.216 _pdbx_refine.free_R_val_test_set_ct_4sig_cutoff 164 _pdbx_refine.free_R_val_test_set_size_perc_4sig_cutoff 1.29 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_refine.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_pdbx_refine.entry_id' _item.category_id pdbx_refine _item.mandatory_code yes _item_linked.child_name '_pdbx_refine.entry_id' _item_linked.parent_name '_entry.id' _item_aliases.alias_name '_ndb_refine.entry_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_refine.R_factor_all_no_cutoff _item_description.description ; R-value (all reflections, no cutoff) Placeholder for PDB mapping of SHELXL refinement data. ; _item.name '_pdbx_refine.R_factor_all_no_cutoff' _item.category_id pdbx_refine _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_ndb_refine.R_factor_all_no_cutoff' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_refine.R_factor_obs_no_cutoff _item_description.description ; R-value (working set reflections, no cutoff) Placeholder for PDB mapping of SHELXL refinement data. ; _item.name '_pdbx_refine.R_factor_obs_no_cutoff' _item.category_id pdbx_refine _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_ndb_refine.R_factor_obs_no_cutoff' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_refine.free_R_factor_4sig_cutoff _item_description.description ; R free value (4 sigma cutoff). Placeholder for PDB mapping of SHELXL refinement data. ; _item.name '_pdbx_refine.free_R_factor_4sig_cutoff' _item.category_id pdbx_refine _item.mandatory_code no _item_type.code float _item_examples.case 0.216 _item_aliases.alias_name '_ndb_refine.free_R_factor_4sig_cutoff' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_refine.free_R_factor_no_cutoff _item_description.description ; Free R-value (no cutoff) Placeholder for PDB mapping of SHELXL refinement data. ; _item.name '_pdbx_refine.free_R_factor_no_cutoff' _item.category_id pdbx_refine _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_ndb_refine.free_R_factor_no_cutoff' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_refine.free_R_val_test_set_size_perc_no_cutoff _item_description.description ; Free R-value test set size (in percent, no cutoff) Placeholder for PDB mapping of SHELXL refinement data. ; _item.name '_pdbx_refine.free_R_val_test_set_size_perc_no_cutoff' _item.category_id pdbx_refine _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_ndb_refine.free_R_val_test_set_size_perc_no_cutoff' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_refine.free_R_val_test_set_ct_no_cutoff _item_description.description ; Free R-value test set count (no cutoff) Placeholder for PDB mapping of SHELXL refinement data. ; _item.name '_pdbx_refine.free_R_val_test_set_ct_no_cutoff' _item.category_id pdbx_refine _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_ndb_refine.free_R_val_test_set_ct_no_cutoff' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_refine.number_reflns_obs_no_cutoff _item_description.description ; Total number of reflections (no cutoff). Placeholder for PDB mapping of SHELXL refinement data. ; _item.name '_pdbx_refine.number_reflns_obs_no_cutoff' _item.category_id pdbx_refine _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_ndb_refine.number_reflns_obs_no_cutoff' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_refine.R_factor_all_4sig_cutoff _item_description.description ; R-value (all reflections, 4 sigma cutoff) Placeholder for PDB mapping of SHELXL refinement data. ; _item.name '_pdbx_refine.R_factor_all_4sig_cutoff' _item.category_id pdbx_refine _item.mandatory_code no _item_type.code float _item_examples.case 0.174 _item_aliases.alias_name '_ndb_refine.R_factor_all_4sig_cutoff' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_refine.R_factor_obs_4sig_cutoff _item_description.description ; R-value (working set, 4 sigma cutoff) Placeholder for PDB mapping of SHELXL refinement data. ; _item.name '_pdbx_refine.R_factor_obs_4sig_cutoff' _item.category_id pdbx_refine _item.mandatory_code no _item_type.code float _item_examples.case 0.169 _item_aliases.alias_name '_ndb_refine.R_factor_obs_4sig_cutoff' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_refine.free_R_val_4sig_cutoff _item_description.description ; Free R-value (4 sigma cutoff) Placeholder for PDB mapping of SHELXL refinement data. ; _item.name '_pdbx_refine.free_R_val_4sig_cutoff' _item.category_id pdbx_refine _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_ndb_refine.free_R_val_4sig_cutoff' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_refine.free_R_val_test_set_size_perc_4sig_cutoff _item_description.description ; Free R-value test set size (in percent, 4 sigma cutoff) Placeholder for PDB mapping of SHELXL refinement data. ; _item.name '_pdbx_refine.free_R_val_test_set_size_perc_4sig_cutoff' _item.category_id pdbx_refine _item.mandatory_code no _item_type.code float _item_examples.case 1.29 _item_aliases.alias_name '_ndb_refine.free_R_val_test_set_size_perc_4sig_cutoff' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_refine.free_R_val_test_set_ct_4sig_cutoff _item_description.description ; Free R-value test set count (4 sigma cutoff) Placeholder for PDB mapping of SHELXL refinement data. ; _item.name '_pdbx_refine.free_R_val_test_set_ct_4sig_cutoff' _item.category_id pdbx_refine _item.mandatory_code no _item_type.code float _item_examples.case 164 _item_aliases.alias_name '_ndb_refine.free_R_val_test_set_ct_4sig_cutoff' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_refine.number_reflns_obs_4sig_cutoff _item_description.description ; Total number of reflections (4 sigma cutoff). Placeholder for PDB mapping of SHELXL refinement data. ; _item.name '_pdbx_refine.number_reflns_obs_4sig_cutoff' _item.category_id pdbx_refine _item.mandatory_code no _item_type.code float _item_examples.case 1263 _item_aliases.alias_name '_ndb_refine.number_reflns_obs_4sig_cutoff' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ############################# ## PDBX_STRUCT_SHEET_HBOND ## ############################# save_pdbx_struct_sheet_hbond _category.description ; Data items in the PDBX_STRUCT_SHEET_HBOND category record details about the hydrogen bonding between residue ranges in a beta sheet. This category is provided for cases where only a single hydrogen bond is used to register the two residue ranges. Category STRUCT_SHEET_HBOND should be used when the initial and terminal hydrogen bonds for strand pair are known. ; _category.id pdbx_struct_sheet_hbond _category.mandatory_code no loop_ _category_key.name '_pdbx_struct_sheet_hbond.sheet_id' '_pdbx_struct_sheet_hbond.range_id_1' '_pdbx_struct_sheet_hbond.range_id_2' loop_ _category_group.id 'inclusive_group' 'struct_group' 'pdbx_group' save_ save__pdbx_struct_sheet_hbond.range_id_1 _item_description.description ; This data item is a pointer to _struct_sheet_range.id in the STRUCT_SHEET_RANGE category. ; _item.name '_pdbx_struct_sheet_hbond.range_id_1' _item.category_id pdbx_struct_sheet_hbond _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_struct_sheet_hbond.range_id_1' _item_linked.parent_name '_struct_sheet_range.id' _item_aliases.alias_name '_rcsb_struct_sheet_hbond.range_id_1' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_struct_sheet_hbond.range_id_2 _item_description.description ; This data item is a pointer to _struct_sheet_range.id in the STRUCT_SHEET_RANGE category. ; _item.name '_pdbx_struct_sheet_hbond.range_id_2' _item.category_id pdbx_struct_sheet_hbond _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_struct_sheet_hbond.range_id_2' _item_linked.parent_name '_struct_sheet_range.id' _item_aliases.alias_name '_rcsb_struct_sheet_hbond.range_id_2' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_struct_sheet_hbond.sheet_id _item_description.description ; This data item is a pointer to _struct_sheet.id in the STRUCT_SHEET category. ; _item.name '_pdbx_struct_sheet_hbond.sheet_id' _item.category_id pdbx_struct_sheet_hbond _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_struct_sheet_hbond.sheet_id' _item_linked.parent_name '_struct_sheet.id' _item_aliases.alias_name '_rcsb_struct_sheet_hbond.sheet_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## save__pdbx_struct_sheet_hbond.range_1_label_atom_id _item_description.description ; A component of the residue identifier for the first partner of the registration hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.label_atom_id in the ATOM_SITE category. ; _item.name '_pdbx_struct_sheet_hbond.range_1_label_atom_id' _item.category_id pdbx_struct_sheet_hbond _item.mandatory_code yes _item_type.code atcode _item_linked.child_name '_pdbx_struct_sheet_hbond.range_1_label_atom_id' _item_linked.parent_name '_atom_site.label_atom_id' _item_aliases.alias_name '_rcsb_struct_sheet_hbond.range_1_label_atom_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_struct_sheet_hbond.range_1_label_seq_id _item_description.description ; A component of the residue identifier for the first partner of the registration hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_pdbx_struct_sheet_hbond.range_1_label_seq_id' _item.category_id pdbx_struct_sheet_hbond _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_struct_sheet_hbond.range_1_label_seq_id' _item_linked.parent_name '_atom_site.label_seq_id' _item_aliases.alias_name '_rcsb_struct_sheet_hbond.range_1_label_seq_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_struct_sheet_hbond.range_1_label_comp_id _item_description.description ; A component of the residue identifier for the first partner of the registration hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_pdbx_struct_sheet_hbond.range_1_label_comp_id' _item.category_id pdbx_struct_sheet_hbond _item.mandatory_code no _item_type.code ucode _item_linked.child_name '_pdbx_struct_sheet_hbond.range_1_label_comp_id' _item_linked.parent_name '_atom_site.label_comp_id' _item_aliases.alias_name '_rcsb_struct_sheet_hbond.range_1_label_comp_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_struct_sheet_hbond.range_1_label_asym_id _item_description.description ; A component of the residue identifier for the first partner of the registration hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_pdbx_struct_sheet_hbond.range_1_label_asym_id' _item.category_id pdbx_struct_sheet_hbond _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_struct_sheet_hbond.range_1_label_asym_id' _item_linked.parent_name '_atom_site.label_asym_id' _item_aliases.alias_name '_rcsb_struct_sheet_hbond.range_1_label_asym_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_struct_sheet_hbond.range_1_auth_atom_id _item_description.description ; A component of the residue identifier for the first partner of the registration hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.auth_atom_id in the ATOM_SITE category. ; _item.name '_pdbx_struct_sheet_hbond.range_1_auth_atom_id' _item.category_id pdbx_struct_sheet_hbond _item.mandatory_code no _item_type.code atcode _item_linked.child_name '_pdbx_struct_sheet_hbond.range_1_auth_atom_id' _item_linked.parent_name '_atom_site.auth_atom_id' _item_aliases.alias_name '_rcsb_struct_sheet_hbond.range_1_auth_atom_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_struct_sheet_hbond.range_1_auth_seq_id _item_description.description ; A component of the residue identifier for the first partner of the registration hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_pdbx_struct_sheet_hbond.range_1_auth_seq_id' _item.category_id pdbx_struct_sheet_hbond _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_struct_sheet_hbond.range_1_auth_seq_id' _item_linked.parent_name '_atom_site.auth_seq_id' _item_aliases.alias_name '_rcsb_struct_sheet_hbond.range_1_auth_seq_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_struct_sheet_hbond.range_1_auth_comp_id _item_description.description ; A component of the residue identifier for the first partner of the registration hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_pdbx_struct_sheet_hbond.range_1_auth_comp_id' _item.category_id pdbx_struct_sheet_hbond _item.mandatory_code no _item_type.code ucode _item_linked.child_name '_pdbx_struct_sheet_hbond.range_1_auth_comp_id' _item_linked.parent_name '_atom_site.auth_comp_id' _item_aliases.alias_name '_rcsb_struct_sheet_hbond.range_1_auth_comp_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_struct_sheet_hbond.range_1_auth_asym_id _item_description.description ; A component of the residue identifier for the first partner of the registration hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_pdbx_struct_sheet_hbond.range_1_auth_asym_id' _item.category_id pdbx_struct_sheet_hbond _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_struct_sheet_hbond.range_1_auth_asym_id' _item_linked.parent_name '_atom_site.auth_asym_id' _item_aliases.alias_name '_rcsb_struct_sheet_hbond.range_1_auth_asym_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_struct_sheet_hbond.range_1_PDB_ins_code _item_description.description ; A component of the residue identifier for the first partner of the registration hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_pdbx_struct_sheet_hbond.range_1_PDB_ins_code' _item.category_id pdbx_struct_sheet_hbond _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_struct_sheet_hbond.range_1_PDB_ins_code' _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' _item_aliases.alias_name '_rcsb_struct_sheet_hbond.range_1_PDB_ins_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## save__pdbx_struct_sheet_hbond.range_2_label_atom_id _item_description.description ; A component of the residue identifier for the second partner of the registration hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.label_atom_id in the ATOM_SITE category. ; _item.name '_pdbx_struct_sheet_hbond.range_2_label_atom_id' _item.category_id pdbx_struct_sheet_hbond _item.mandatory_code yes _item_type.code atcode _item_linked.child_name '_pdbx_struct_sheet_hbond.range_2_label_atom_id' _item_linked.parent_name '_atom_site.label_atom_id' _item_aliases.alias_name '_rcsb_struct_sheet_hbond.range_2_label_atom_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_struct_sheet_hbond.range_2_label_seq_id _item_description.description ; A component of the residue identifier for the second partner of the registration hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_pdbx_struct_sheet_hbond.range_2_label_seq_id' _item.category_id pdbx_struct_sheet_hbond _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_struct_sheet_hbond.range_2_label_seq_id' _item_linked.parent_name '_atom_site.label_seq_id' _item_aliases.alias_name '_rcsb_struct_sheet_hbond.range_2_label_seq_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_struct_sheet_hbond.range_2_label_comp_id _item_description.description ; A component of the residue identifier for the second partner of the registration hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_pdbx_struct_sheet_hbond.range_2_label_comp_id' _item.category_id pdbx_struct_sheet_hbond _item.mandatory_code no _item_type.code ucode _item_linked.child_name '_pdbx_struct_sheet_hbond.range_2_label_comp_id' _item_linked.parent_name '_atom_site.label_comp_id' _item_aliases.alias_name '_rcsb_struct_sheet_hbond.range_2_label_comp_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_struct_sheet_hbond.range_2_label_asym_id _item_description.description ; A component of the residue identifier for the second partner of the registration hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_pdbx_struct_sheet_hbond.range_2_label_asym_id' _item.category_id pdbx_struct_sheet_hbond _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_struct_sheet_hbond.range_2_label_asym_id' _item_linked.parent_name '_atom_site.label_asym_id' _item_aliases.alias_name '_rcsb_struct_sheet_hbond.range_2_label_asym_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_struct_sheet_hbond.range_2_auth_atom_id _item_description.description ; A component of the residue identifier for the second partner of the registration hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.auth_atom_id in the ATOM_SITE category. ; _item.name '_pdbx_struct_sheet_hbond.range_2_auth_atom_id' _item.category_id pdbx_struct_sheet_hbond _item.mandatory_code no _item_type.code atcode _item_linked.child_name '_pdbx_struct_sheet_hbond.range_2_auth_atom_id' _item_linked.parent_name '_atom_site.auth_atom_id' _item_aliases.alias_name '_rcsb_struct_sheet_hbond.range_2_auth_atom_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_struct_sheet_hbond.range_2_auth_seq_id _item_description.description ; A component of the residue identifier for the second partner of the registration hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_pdbx_struct_sheet_hbond.range_2_auth_seq_id' _item.category_id pdbx_struct_sheet_hbond _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_struct_sheet_hbond.range_2_auth_seq_id' _item_linked.parent_name '_atom_site.auth_seq_id' _item_aliases.alias_name '_rcsb_struct_sheet_hbond.range_2_auth_seq_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_struct_sheet_hbond.range_2_auth_comp_id _item_description.description ; A component of the residue identifier for the second partner of the registration hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_pdbx_struct_sheet_hbond.range_2_auth_comp_id' _item.category_id pdbx_struct_sheet_hbond _item.mandatory_code no _item_type.code ucode _item_linked.child_name '_pdbx_struct_sheet_hbond.range_2_auth_comp_id' _item_linked.parent_name '_atom_site.auth_comp_id' _item_aliases.alias_name '_rcsb_struct_sheet_hbond.range_2_auth_comp_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_struct_sheet_hbond.range_2_auth_asym_id _item_description.description ; A component of the residue identifier for the second partner of the registration hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_pdbx_struct_sheet_hbond.range_2_auth_asym_id' _item.category_id pdbx_struct_sheet_hbond _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_struct_sheet_hbond.range_2_auth_asym_id' _item_linked.parent_name '_atom_site.auth_asym_id' _item_aliases.alias_name '_rcsb_struct_sheet_hbond.range_2_auth_asym_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_struct_sheet_hbond.range_2_PDB_ins_code _item_description.description ; A component of the residue identifier for the second partner of the registration hydrogen bond between two residue ranges in a sheet. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_pdbx_struct_sheet_hbond.range_2_PDB_ins_code' _item.category_id pdbx_struct_sheet_hbond _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_struct_sheet_hbond.range_2_PDB_ins_code' _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' _item_aliases.alias_name '_rcsb_struct_sheet_hbond.range_2_PDB_ins_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### ### save_pdbx_xplor_file _category.description ; Parameter and topology files used in X-PLOR/CNS refinement. ; _category.id pdbx_xplor_file _category.mandatory_code no _category_key.name '_pdbx_xplor_file.serial_no' loop_ _category_group.id 'inclusive_group' 'refine_group' 'pdbx_group' loop_ _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _pdbx_xplor_file.serial_no 1 _pdbx_xplor_file.param_file parm_hol.dat _pdbx_xplor_file.topol_file topol_hol.dat ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_xplor_file.serial_no _item_description.description ; Serial number. ; _item.name '_pdbx_xplor_file.serial_no' _item.category_id pdbx_xplor_file _item.mandatory_code yes _item_type.code code _item_aliases.alias_name '_ndb_xplor_file.serial_no' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_xplor_file.param_file _item_description.description ; Parameter file name in X-PLOR/CNS refinement. ; _item.name '_pdbx_xplor_file.param_file' _item.category_id pdbx_xplor_file _item.mandatory_code no _item_type.code line _item_examples.case 'PARAM_NDBX_HIGH.DNA' _item_aliases.alias_name '_ndb_xplor_file.param_file' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_xplor_file.topol_file _item_description.description ; Topology file name in X-PLOR/CNS refinement. ; _item.name '_pdbx_xplor_file.topol_file' _item.category_id pdbx_xplor_file _item.mandatory_code no _item_type.code line _item_examples.case 'TOP_NDBX.DNA' _item_aliases.alias_name '_ndb_xplor_file.topol_file' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ## save_pdbx_refine_aux_file _category.description ; Auxilary parameter and topology files used in refinement. ; _category.id pdbx_refine_aux_file _category.mandatory_code no _category_key.name '_pdbx_refine_aux_file.serial_no' loop_ _category_group.id 'inclusive_group' 'refine_group' 'pdbx_group' loop_ _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _pdbx_refine_aux_file.serial_no 1 _pdbx_refine_aux_file.file_name parm_hol.dat _pdbx_refine_aux_file.file_type PARAMETER ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_refine_aux_file.serial_no _item_description.description ; Serial number. ; _item.name '_pdbx_refine_aux_file.serial_no' _item.category_id pdbx_refine_aux_file _item.mandatory_code yes _item_type.code code _item_aliases.alias_name '_rcsb_refine_aux_file.serial_no' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_refine_aux_file.file_name _item_description.description ; Auxilary file name. ; _item.name '_pdbx_refine_aux_file.file_name' _item.category_id pdbx_refine_aux_file _item.mandatory_code no _item_type.code line _item_examples.case 'PARAM_NDBX_HIGH.DNA' _item_aliases.alias_name '_rcsb_refine_aux_file.file_name' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_refine_aux_file.file_type _item_description.description ; Auxilary file type. ; _item.name '_pdbx_refine_aux_file.file_type' _item.category_id pdbx_refine_aux_file _item.mandatory_code no _item_type.code line _item_examples.case 'PARAMETER' loop_ _item_enumeration.value 'PARAMETER' 'TOPOLOGY' _item_aliases.alias_name '_rcsb_refine_aux_file.file_type' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ## ## save_pdbx_database_related _category.description ; Data items in PDBX_DATABASE_RELATED contain references to entries that are related to the this entry. ; _category.id pdbx_database_related _category.mandatory_code no loop_ _category_key.name '_pdbx_database_related.db_name' '_pdbx_database_related.db_id' loop_ _category_group.id 'inclusive_group' 'pdbx_group' _category_examples.case ; _pdbx_database_related.db_name PDB _pdbx_database_related.db_id 1ABC ; save_ save__pdbx_database_related.db_name _item_description.description ; The name of the database containing the related entry. ; _item.name '_pdbx_database_related.db_name' _item.category_id pdbx_database_related _item.mandatory_code yes _item_type.code code # loop_ # _item_enumeration.value 'PDB' 'NDB' 'BMRB' 'BMCD' _item_examples.case ; PDB - Protein Databank NDB - Nucleic Acid Database BMRB - BioMagResBank BMCD - Biological Macromolecule Crystallization Database ; _item_aliases.alias_name '_rcsb_database_related.db_name' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_database_related.details _item_description.description ; A description of the related entry. ; _item.name '_pdbx_database_related.details' _item.category_id pdbx_database_related _item.mandatory_code no _item_type.code text loop_ _item_examples.case ; 1ABC contains the same protein complexed with Netropsin. ; _item_aliases.alias_name '_rcsb_database_related.details' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ # # save__pdbx_database_related.db_id _item_description.description ; The identifying code in the related database. ; _item.name '_pdbx_database_related.db_id' _item.category_id pdbx_database_related _item.mandatory_code yes _item_type.code line loop_ _item_examples.case '1ABC' 'BDL001' _item_aliases.alias_name '_rcsb_database_related.db_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ # save__pdbx_database_related.content_type _item_description.description ; The identifying content type of the related entry. ; _item.name '_pdbx_database_related.content_type' _item.category_id pdbx_database_related _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'minimized average structure' 'representative structure' 'ensemble' 'derivative structure' 'native structure' 'other' loop_ _item_enumeration.value 'minimized average structure' 'representative structure' 'ensemble' 'derivative structure' 'native structure' 'other' _item_aliases.alias_name '_rcsb_database_related.content_type' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ########################## ## PDBX_ENTITY_ASSEMBLY ## ########################## save_pdbx_entity_assembly _category.description ; The PDBX_ENTITY_ASSEMBLY category provides a chemical description of the biological assembly studied in terms of its constituent entities. ; _category.id pdbx_entity_assembly _category.mandatory_code no loop_ _category_key.name '_pdbx_entity_assembly.id' '_pdbx_entity_assembly.entity_id' loop_ _category_group.id 'inclusive_group' 'entity_group' 'pdbx_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; A complex composed of one copy of entities 1 and 2. ; ; loop_ _pdbx_entity_assembly.id _pdbx_entity_assembly.biol_id _pdbx_entity_assembly.entity_id _pdbx_entity_assembly.num_copies 1 1 1 1 1 1 2 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_entity_assembly.id _item_description.description ; An identifier for the assembly. ; _item.name '_pdbx_entity_assembly.id' _item.category_id pdbx_entity_assembly _item.mandatory_code yes _item_type.code code _item_aliases.alias_name '_rcsb_entity_assembly.id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_entity_assembly.entity_id _item_description.description ; An enity identifier. A reference to _entity.id. ; _item.name '_pdbx_entity_assembly.entity_id' _item.category_id pdbx_entity_assembly _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_entity_assembly.entity_id' _item_linked.parent_name '_entity.id' _item_aliases.alias_name '_rcsb_entity_assembly.entity_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_entity_assembly.biol_id _item_description.description ; An identifier for the assembly. ; _item.name '_pdbx_entity_assembly.biol_id' _item.category_id pdbx_entity_assembly _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_entity_assembly.biol_id' _item_linked.parent_name '_struct_biol.id' _item_aliases.alias_name '_rcsb_entity_assembly.biol_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_entity_assembly.num_copies _item_description.description ; The number of copies of this entity in the assembly. ; _item.name '_pdbx_entity_assembly.num_copies' _item.category_id pdbx_entity_assembly _item.mandatory_code yes _item_type.code int _item_aliases.alias_name '_rcsb_entity_assembly.num_copies' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ######################### ## PDBX_ENTITY_SRC_SYN ## ######################### save_pdbx_entity_src_syn _category.description ; PDBX_ENTITY_SRC_SYN records the details about each chemically synthesized molecule (entity) in the asymmetric unit. ; _category.id pdbx_entity_src_syn _category.mandatory_code no _category_key.name '_pdbx_entity_src_syn.entity_id' loop_ _category_group.id 'inclusive_group' 'entity_group' 'pdbx_group' save_ save__pdbx_entity_src_syn.details _item_description.description ; A description of special aspects of the source for the synthetic entity. ; _item.name '_pdbx_entity_src_syn.details' _item.category_id pdbx_entity_src_syn _item.mandatory_code no _item_type.code text _item_examples.case 'This sequence occurs naturally in humans.' _item_aliases.alias_name '_rcsb_entity_src_syn.details' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_entity_src_syn.entity_id _item_description.description ; This data item is a pointer to _entity.id in the ENTITY category. ; _item.name '_pdbx_entity_src_syn.entity_id' _item.category_id pdbx_entity_src_syn _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_entity_src_syn.entity_id' _item_linked.parent_name '_entity.id' loop_ _item_examples.case '1' '2' '3' '4' _item_aliases.alias_name '_rcsb_entity_src_syn.entity_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### --------------------------------------------------------------------------- ### Supplemental items in existing mmCIF categories ... ### ### save__atom_site.pdbx_auth_alt_id _item_description.description ; Author's alternate location identifier. ; _item.name '_atom_site.pdbx_auth_alt_id' _item.category_id atom_site _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_atom_site.ndb_auth_alt_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__atom_site.pdbx_PDB_ins_code _item_description.description ; PDB insertion code. ; _item.name '_atom_site.pdbx_PDB_ins_code' _item.category_id atom_site _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_atom_site.ndb_ins_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__atom_site.pdbx_PDB_model_num _item_description.description ; PDB model number. ; _item.name '_atom_site.pdbx_PDB_model_num' _item.category_id atom_site _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_atom_site.ndb_model' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__atom_site.pdbx_PDB_residue_no _item_description.description ; PDB residue number. ; _item.name '_atom_site.pdbx_PDB_residue_no' _item.category_id atom_site _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_atom_site.ndb_PDB_residue_no' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__atom_site.pdbx_PDB_residue_name _item_description.description ; PDB residue name. ; _item.name '_atom_site.pdbx_PDB_residue_name' _item.category_id atom_site _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_atom_site.ndb_PDB_residue_name' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__atom_site.pdbx_PDB_strand_id _item_description.description ; PDB strand id. ; _item.name '_atom_site.pdbx_PDB_strand_id' _item.category_id atom_site _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_atom_site.ndb_PDB_strand_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__atom_site.pdbx_PDB_atom_name _item_description.description ; PDB atom name. ; _item.name '_atom_site.pdbx_PDB_atom_name' _item.category_id atom_site _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_atom_site.ndb_PDB_atom_name' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__atom_site.pdbx_auth_atom_name _item_description.description ; Author's atom name. ; _item.name '_atom_site.pdbx_auth_atom_name' _item.category_id atom_site _item.mandatory_code no _item_type.code atcode _item_aliases.alias_name '_atom_site.ndb_auth_atom_name' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ## save__atom_site_anisotrop.pdbx_auth_seq_id _item_description.description ; Pointer to _atom_site.auth_seq_id ; _item.name '_atom_site_anisotrop.pdbx_auth_seq_id' _item.category_id atom_site_anisotrop _item.mandatory_code no _item_type.code code _item_linked.child_name '_atom_site_anisotrop.pdbx_auth_seq_id' _item_linked.parent_name '_atom_site.auth_seq_id' _item_aliases.alias_name '_atom_site_anisotrop.ndb_PDB_residue_no' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__atom_site_anisotrop.pdbx_auth_alt_id _item_description.description ; Pointer to _atom_site.pdbx_auth_alt_id. ; _item.name '_atom_site_anisotrop.pdbx_auth_alt_id' _item.category_id atom_site_anisotrop _item.mandatory_code no _item_type.code code _item_linked.child_name '_atom_site_anisotrop.pdbx_auth_alt_id' _item_linked.parent_name '_atom_site.pdbx_auth_alt_id' # _item_aliases.alias_name '_atom_site_anisotrop.ndb_auth_alt_id' # _item_aliases.dictionary 'cif_rcsb.dic' # _item_aliases.version 1.1 save_ save__atom_site_anisotrop.pdbx_auth_asym_id _item_description.description ; Pointer to _atom_site.auth_asym_id ; _item.name '_atom_site_anisotrop.pdbx_auth_asym_id' _item.category_id atom_site_anisotrop _item.mandatory_code no _item_type.code code _item_linked.child_name '_atom_site_anisotrop.pdbx_auth_asym_id' _item_linked.parent_name '_atom_site.auth_asym_id' _item_aliases.alias_name '_atom_site_anisotrop.ndb_PDB_strand_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__atom_site_anisotrop.pdbx_auth_atom_id _item_description.description ; Pointer to _atom_site.auth_atom_id ; _item.name '_atom_site_anisotrop.pdbx_auth_atom_id' _item.category_id atom_site_anisotrop _item.mandatory_code no _item_type.code atcode _item_linked.child_name '_atom_site_anisotrop.pdbx_auth_atom_id' _item_linked.parent_name '_atom_site.auth_atom_id' _item_aliases.alias_name '_atom_site_anisotrop.ndb_PDB_atom_name' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__atom_site_anisotrop.pdbx_auth_comp_id _item_description.description ; Pointer to _atom_site.auth_comp_id ; _item.name '_atom_site_anisotrop.pdbx_auth_comp_id' _item.category_id atom_site_anisotrop _item.mandatory_code no _item_type.code code _item_linked.child_name '_atom_site_anisotrop.pdbx_auth_comp_id' _item_linked.parent_name '_atom_site.auth_comp_id' _item_aliases.alias_name '_atom_site_anisotrop.ndb_PDB_residue_name' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__atom_site_anisotrop.pdbx_label_seq_id _item_description.description ; Pointer to _atom_site.label_seq_id ; _item.name '_atom_site_anisotrop.pdbx_label_seq_id' _item.category_id atom_site_anisotrop _item.mandatory_code no _item_type.code code _item_linked.child_name '_atom_site_anisotrop.pdbx_label_seq_id' _item_linked.parent_name '_atom_site.label_seq_id' _item_aliases.alias_name '_atom_site_anisotrop.ndb_label_seq_num' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__atom_site_anisotrop.pdbx_label_alt_id _item_description.description ; Pointer to _atom_site.label_alt_id. ; _item.name '_atom_site_anisotrop.pdbx_label_alt_id' _item.category_id atom_site_anisotrop _item.mandatory_code no _item_type.code code _item_linked.child_name '_atom_site_anisotrop.pdbx_label_alt_id' _item_linked.parent_name '_atom_site.label_alt_id' _item_aliases.alias_name '_atom_site_anisotrop.ndb_label_alt_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__atom_site_anisotrop.pdbx_label_asym_id _item_description.description ; Pointer to _atom_site.label_asym_id ; _item.name '_atom_site_anisotrop.pdbx_label_asym_id' _item.category_id atom_site_anisotrop _item.mandatory_code no _item_type.code code _item_linked.child_name '_atom_site_anisotrop.pdbx_label_asym_id' _item_linked.parent_name '_atom_site.label_asym_id' _item_aliases.alias_name '_atom_site_anisotrop.ndb_label_asym_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__atom_site_anisotrop.pdbx_label_atom_id _item_description.description ; Pointer to _atom_site.label_atom_id ; _item.name '_atom_site_anisotrop.pdbx_label_atom_id' _item.category_id atom_site_anisotrop _item.mandatory_code no _item_type.code atcode _item_linked.child_name '_atom_site_anisotrop.pdbx_label_atom_id' _item_linked.parent_name '_atom_site.label_atom_id' _item_aliases.alias_name '_atom_site_anisotrop.ndb_label_atom_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__atom_site_anisotrop.pdbx_label_comp_id _item_description.description ; Pointer to _atom_site.label_comp_id ; _item.name '_atom_site_anisotrop.pdbx_label_comp_id' _item.category_id atom_site_anisotrop _item.mandatory_code no _item_type.code code _item_linked.child_name '_atom_site_anisotrop.pdbx_label_comp_id' _item_linked.parent_name '_atom_site.label_comp_id' _item_aliases.alias_name '_atom_site_anisotrop.ndb_label_comp_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__atom_site_anisotrop.pdbx_PDB_ins_code _item_description.description ; Pointer to _atom_site.pdbx_PDB_ins_code ; _item.name '_atom_site_anisotrop.pdbx_PDB_ins_code' _item.category_id atom_site_anisotrop _item.mandatory_code no _item_type.code code _item_linked.child_name '_atom_site_anisotrop.pdbx_PDB_ins_code' _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' _item_aliases.alias_name '_atom_site_anisotrop.ndb_ins_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ## save__cell.pdbx_unique_axis _item_description.description ; To further identify unique axis if necessary. E.g., P 21 with an unique C axis will have 'C' in this field. ; _item.name '_cell.pdbx_unique_axis' _item.category_id cell _item.mandatory_code no _item_type.code text _item_aliases.alias_name '_cell.ndb_unique_axis' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ## save__chem_comp.pdbx_synonyms _item_description.description ; Synonym list for the component. ; _item.name '_chem_comp.pdbx_synonyms' _item.category_id chem_comp _item.mandatory_code no _item_type.code line _item_examples.case ATP _item_aliases.alias_name '_chem_comp.ndb_synonyms' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__chem_comp.pdbx_modification_details _item_description.description ; For nonstandard components a text description of modification of the parent component. ; _item.name '_chem_comp.pdbx_modification_details' _item.category_id chem_comp _item.mandatory_code no _item_type.code line _item_examples.case ATP _item_aliases.alias_name '_chem_comp.rcsb_modification_details' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__chem_comp.pdbx_component_no _item_description.description ; A serial number used by PDB in the FORMUL record. ; _item.name '_chem_comp.pdbx_component_no' _item.category_id chem_comp _item.mandatory_code no _item_type.code int _item_examples.case 3 _item_aliases.alias_name '_chem_comp.ndb_component_no' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__chem_comp.pdbx_type _item_description.description ; A preliminary classification used by PDB. ; _item.name '_chem_comp.pdbx_type' _item.category_id chem_comp _item.mandatory_code no _item_type.code uline save_ save__chem_comp.pdbx_formal_charge _item_description.description ; The net integer charge assigned to this component. This is the formal charge assignment normally found in chemical diagrams. ; _item.name '_chem_comp.pdbx_formal_charge' _item.category_id chem_comp _item.mandatory_code no _item_default.value 0 _item_type.code int save_ save__chem_comp_atom.pdbx_align _item_description.description ; Atom name alignment offset in PDB atom field. ; _item.name '_chem_comp_atom.pdbx_align' _item.category_id chem_comp _item.mandatory_code no _item_type.code int save_ ### ### save__citation.pdbx_database_id_DOI _item_description.description ; Document Object Identifier used by doi.org to uniquely specify bibliographic entry. ; _item.name '_citation.pdbx_database_id_DOI' _item.category_id citation _item.mandatory_code no _item_type.code code _item_examples.case 'DOI:10.2345/S1384107697000225' _item_aliases.alias_name '_citation.rcsb_database_id_DOI' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__citation.pdbx_database_id_PubMed _item_description.description ; Ascession number used by PubMed to categorize a specific bibliographic entry. ; _item.name '_citation.pdbx_database_id_PubMed' _item.category_id citation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int _item_examples.case 12627512 _item_aliases.alias_name '_citation.rcsb_database_id_PubMed' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## save__computing.pdbx_structure_refinement_method _item_description.description ; Program/package name for structure refinement method. ; _item.name '_computing.pdbx_structure_refinement_method' _item.category_id computing _item.mandatory_code no _item_type.code text _item_aliases.alias_name '_computing.ndb_structure_refinement_method' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__computing.pdbx_data_reduction_ii _item_description.description ; Program/package name for data reduction/intensity integration software ; _item.name '_computing.pdbx_data_reduction_ii' _item.category_id computing _item.mandatory_code no _item_type.code text _item_aliases.alias_name '_computing.rcsb_data_reduction_ii' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__computing.pdbx_data_reduction_ds _item_description.description ; Program/package name for data reduction/data scaling ; _item.name '_computing.pdbx_data_reduction_ds' _item.category_id computing _item.mandatory_code no _item_type.code text _item_aliases.alias_name '_computing.rcsb_data_reduction_ds' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ## ## ## save__diffrn_detector.pdbx_frames_total _item_description.description ; The total number of data frames collected for this data set. ; _item.name '_diffrn_detector.pdbx_frames_total' _item.category_id diffrn_detector _item.mandatory_code no _item_type.code int loop_ _item_examples.case 20 100 save_ save__diffrn_detector.pdbx_collection_time_total _item_description.description ; The total number of seconds required to measure this data set. ; _item.name '_diffrn_detector.pdbx_collection_time_total' _item.category_id diffrn_detector _item.mandatory_code no _item_type.code float _item_units.code seconds loop_ _item_examples.case 120.0 save_ save__diffrn_detector.pdbx_collection_date _item_description.description ; The date of data collection. ; _item.name '_diffrn_detector.pdbx_collection_date' _item.category_id diffrn_detector _item.mandatory_code no _item_type.code yyyy-mm-dd:hh:mm _item_examples.case '1996-12-25' _item_aliases.alias_name '_diffrn_detector.ndb_collection_date' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ## save__diffrn_radiation.pdbx_monochromatic_or_laue_m_l _item_description.description ; Monochromatic or Laue. ; _item.name '_diffrn_radiation.pdbx_monochromatic_or_laue_m_l' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code code _item_default.value 'M' loop_ _item_enumeration.value _item_enumeration.detail 'M' . 'L' . loop_ _item_examples.case 'M' 'L' _item_aliases.alias_name '_diffrn_radiation.ndb_monochromatic_or_laue_m_l' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__diffrn_radiation.pdbx_wavelength_list _item_description.description ; Comma separated list of wavelengths or wavelength range. ; _item.name '_diffrn_radiation.pdbx_wavelength_list' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code line _item_aliases.alias_name '_diffrn_source.rcsb_wavelength_list' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__diffrn_radiation.pdbx_wavelength _item_description.description ; Wavelength of radiation. ; _item.name '_diffrn_radiation.pdbx_wavelength' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code line _item_aliases.alias_name '_diffrn_source.rcsb_wavelength' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__diffrn_radiation.pdbx_diffrn_protocol _item_description.description ; SINGLE WAVELENGTH, LAUE, or MAD. ; _item.name '_diffrn_radiation.pdbx_diffrn_protocol' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code line _item_default.value 'SINGLE WAVELENGTH' # loop_ # _item_enumeration.value # 'SINGLE WAVELENGTH' # 'MONOCHROMATIC' # 'LAUE' # 'MAD' # 'OTHER' loop_ _item_examples.case 'SINGLE WAVELENGTH' 'MONOCHROMATIC' 'LAUE' 'MAD' 'OTHER' _item_aliases.alias_name '_diffrn_radiation.rcsb_diffrn_protocol' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__diffrn_source.pdbx_synchrotron_beamline _item_description.description ; Synchrotron beamline. ; _item.name '_diffrn_source.pdbx_synchrotron_beamline' _item.category_id diffrn_source _item.mandatory_code no _item_type.code line _item_aliases.alias_name '_diffrn_source.ndb_synchrotron_beamline' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__diffrn_source.pdbx_synchrotron_site _item_description.description ; Synchrotron site. ; _item.name '_diffrn_source.pdbx_synchrotron_site' _item.category_id diffrn_source _item.mandatory_code no _item_type.code line _item_aliases.alias_name '_diffrn_source.ndb_synchrotron_site' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ## save__entity.pdbx_description _item_description.description ; A description of the entity, with the name of the entity in parenthesis. Maps to PDB compound name. ; _item.name '_entity.pdbx_description' _item.category_id entity _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'DNA (5'-D(*GP*(CH3)CP*GP*(CH3)CP*GP*C)-3')' PROFLAVINE 'PROTEIN (DEOXYRIBONUCLEASE I (E.C.3.1.21.1))' _item_aliases.alias_name '_entity.ndb_description' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity.pdbx_number_of_molecules _item_description.description ; A place holder for the number of molecules of the entity in the entry. ; _item.name '_entity.pdbx_number_of_molecules' _item.category_id entity _item.mandatory_code no _item_type.code float loop_ _item_examples.case 1.0 2.0 3.0 _item_aliases.alias_name '_entity.ndb_number_of_molecules' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity.pdbx_parent_entity_id _item_description.description ; An identifier for the parent entity if this entity is part of a complex entity. For instance a chimeric entity may be decomposed into several independent chemical entities where each component entity was obtained from a different source. ; _item.name '_entity.pdbx_parent_entity_id' _item.category_id entity _item.mandatory_code no _item_type.code code _item_linked.child_name '_entity.pdbx_parent_entity_id' _item_linked.parent_name '_entity.id' loop_ _item_examples.case 1 2 3 _item_aliases.alias_name '_entity.rcsb_parent_entity_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity.pdbx_mutation _item_description.description ; Details about any entity mutation(s). ; _item.name '_entity.pdbx_mutation' _item.category_id entity _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'Y31H' 'DEL(298-323)' _item_aliases.alias_name '_entity_keywords.ndb_mutation' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity.pdbx_fragment _item_description.description ; Entity fragment description(s). ; _item.name '_entity.pdbx_fragment' _item.category_id entity _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'KLENOW FRAGMENT' 'REPLICASE OPERATOR HAIRPIN' 'C-TERMINAL DOMAIN' _item_aliases.alias_name '_entity_keywords.ndb_fragment' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity.pdbx_ec _item_description.description ; Enzyme Commission (EC) number(s) ; _item.name '_entity.pdbx_ec' _item.category_id entity _item.mandatory_code no _item_type.code line _item_examples.case 2.7.7.7 _item_aliases.alias_name '_entity_keywords.ndb_ec' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity.pdbx_modification _item_description.description ; Description(s) of any chemical or post-translational modifications ; _item.name '_entity.pdbx_modification' _item.category_id entity _item.mandatory_code no _item_type.code line _item_aliases.alias_name '_entity_keywords.rcsb_modification' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity.pdbx_formula_weight_exptl _item_description.description ; Experimentally determined formula mass in daltons of the entity ; _item.name '_entity.pdbx_formula_weight_exptl' _item.category_id entity _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1.0 1.0 1.0 _item_type.code float _item_aliases.alias_name '_entity.rcsb_formula_weight_exptl' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity.pdbx_formula_weight_exptl_method _item_description.description ; Method used to determine _entity.pdbx_formula_weight_exptl. ; _item.name '_entity.pdbx_formula_weight_exptl_method' _item.category_id entity _item.mandatory_code no _item_type.code line _item_examples.case 'MASS SPEC' loop_ _item_enumeration.value 'MASS SPEC' save_ ## ## #### save__entity_keywords.pdbx_mutation _item_description.description ; Entity mutation description(s). ; _item.name '_entity_keywords.pdbx_mutation' _item.category_id entity_keywords _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'Y31H' 'DEL(298-323)' # _item_aliases.alias_name '_entity_keywords.ndb_mutation' # _item_aliases.dictionary 'cif_rcsb.dic' # _item_aliases.version 1.1 _item_related.related_name '_entity.pdbx_mutation' _item_related.function_code replacedby save_ save__entity_keywords.pdbx_fragment _item_description.description ; Entity fragment description(s). ; _item.name '_entity_keywords.pdbx_fragment' _item.category_id entity_keywords _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'KLENOW FRAGMENT' 'REPLICASE OPERATOR HAIRPIN' 'C-TERMINAL DOMAIN' # _item_aliases.alias_name '_entity_keywords.ndb_fragment' # _item_aliases.dictionary 'cif_rcsb.dic' # _item_aliases.version 1.1 _item_related.related_name '_entity.pdbx_fragment' _item_related.function_code replacedby save_ save__entity_keywords.pdbx_ec _item_description.description ; Enzyme Commission (EC) number(s) ; _item.name '_entity_keywords.pdbx_ec' _item.category_id entity_keywords _item.mandatory_code no _item_type.code line _item_examples.case 2.7.7.7 # _item_aliases.alias_name '_entity_keywords.ndb_ec' # _item_aliases.dictionary 'cif_rcsb.dic' # _item_aliases.version 1.1 _item_related.related_name '_entity.pdbx_mutation' _item_related.function_code replacedby save_ ## ## save__entity_poly.pdbx_strand_id _item_description.description ; The PDB strand/chain id(s) corresponding to this polymer entity. ; _item.name '_entity_poly.pdbx_strand_id' _item.category_id entity_poly _item.mandatory_code no _item_type.code line loop_ _item_examples.case A B 'A,B,C' _item_aliases.alias_name '_entity_poly.ndb_chain_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_poly.pdbx_seq_one_letter_code _item_description.description ; Chemical sequence expressed as string of one-letter amino acid codes. Modifications and non-standard amino acids are coded as X. ; _item.name '_entity_poly.pdbx_seq_one_letter_code' _item.category_id entity_poly _item.mandatory_code no _item_type.code text _item_examples.case ; A for alanine or adenine B for ambiguous asparagine/aspartic-acid R for arginine N for asparagine D for aspartic-acid C for cysteine or cystine or cytosine Q for glutamine E for glutamic-acid Z for ambiguous glutamine/glutamic acid G for glycine or guanine H for histidine I for isoleucine L for leucine K for lysine M for methionine F for phenylalanine P for proline S for serine T for threonine or thymine W for tryptophan Y for tyrosine V for valine U for uracil O for water X for other ; _item_aliases.alias_name '_entity_poly.ndb_seq_one_letter_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_poly.pdbx_seq_one_letter_code_can _item_description.description ; Cannonical chemical sequence expressed as string of one-letter amino acid codes. Modifications are coded as the parent amino acid where possible. A for alanine or adenine B for ambiguous asparagine/aspartic-acid R for arginine N for asparagine D for aspartic-acid C for cysteine or cystine or cytosine Q for glutamine E for glutamic-acid Z for ambiguous glutamine/glutamic acid G for glycine or guanine H for histidine I for isoleucine L for leucine K for lysine M for methionine F for phenylalanine P for proline S for serine T for threonine or thymine W for tryptophan Y for tyrosine V for valine U for uracil ; _item.name '_entity_poly.pdbx_seq_one_letter_code_can' _item.category_id entity_poly _item.mandatory_code no _item_type.code text _item_examples.case ; MSHHWGYGKHNGPEHWHKDFPIAKGERQSPVDIDTHTAKYDPSLKPLSVSYDQATSLRILNNGAAFNVEFD ; _item_aliases.alias_name '_entity_poly.ndb_seq_one_letter_code_can' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_poly.pdbx_target_identifier _item_description.description ; The sequence's target identifier registered at target database. ; _item.name '_entity_poly.pdbx_target_identifier' _item.category_id entity_poly _item.mandatory_code no _item_type.code line _item_examples.case 356560 save_ ## ## save__entity_src_gen.pdbx_gene_src_fragment _item_description.description ; A domain or fragment of the molecule. ; _item.name '_entity_src_gen.pdbx_gene_src_fragment' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'CYTOPLASM' 'NUCLEUS' _item_aliases.alias_name '_entity_src_gen.ndb_gene_src_fragment' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_gen.pdbx_gene_src_gene _item_description.description ; Identifies the gene. ; _item.name '_entity_src_gen.pdbx_gene_src_gene' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text _item_aliases.alias_name '_entity_src_gen.ndb_gene_src_gene' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_gen.pdbx_gene_src_scientific_name _item_description.description ; Scientific name of the organism. ; _item.name '_entity_src_gen.pdbx_gene_src_scientific_name' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text _item_examples.case ; ESCHERICHIA COLI HOMO SAPIENS SACCHAROMYCES CEREVISIAE ; _item_aliases.alias_name '_entity_src_gen.ndb_gene_src_scientific_name' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_gen.pdbx_gene_src_variant _item_description.description ; Identifies the variant. ; _item.name '_entity_src_gen.pdbx_gene_src_variant' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text _item_examples.case 'DELTAH1DELTATRP' _item_aliases.alias_name '_entity_src_gen.ndb_gene_src_variant' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_gen.pdbx_gene_src_cell_line _item_description.description ; The specific line of cells. ; _item.name '_entity_src_gen.pdbx_gene_src_cell_line' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text _item_examples.case 'HELA CELLS' _item_aliases.alias_name '_entity_src_gen.ndb_gene_src_cell_line' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_gen.pdbx_gene_src_atcc _item_description.description ; American Type Culture Collection tissue culture number. ; _item.name '_entity_src_gen.pdbx_gene_src_atcc' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text _item_examples.case '6051' _item_aliases.alias_name '_entity_src_gen.ndb_gene_src_atcc' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_gen.pdbx_gene_src_organ _item_description.description ; Organized group of tissues that carries on a specialized function. ; _item.name '_entity_src_gen.pdbx_gene_src_organ' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'KIDNEY' 'LIVER' 'PANCREAS' _item_aliases.alias_name '_entity_src_gen.ndb_gene_src_organ' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_gen.pdbx_gene_src_organelle _item_description.description ; Organized structure within cell. ; _item.name '_entity_src_gen.pdbx_gene_src_organelle' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text _item_examples.case 'MITOCHONDRIA' _item_aliases.alias_name '_entity_src_gen.ndb_gene_src_organelle' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_gen.pdbx_gene_src_plasmid _item_description.description ; The source plasmid. ; _item.name '_entity_src_gen.pdbx_gene_src_plasmid' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text _item_aliases.alias_name '_entity_src_gen.ndb_gene_src_plasmid' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_gen.pdbx_gene_src_plasmid_name _item_description.description ; The source plasmid. ; _item.name '_entity_src_gen.pdbx_gene_src_plasmid_name' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text _item_aliases.alias_name '_entity_src_gen.ndb_gene_src_plasmid_name' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_gen.pdbx_gene_src_cell _item_description.description ; Cell type. ; _item.name '_entity_src_gen.pdbx_gene_src_cell' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text _item_examples.case 'ENDOTHELIAL' _item_aliases.alias_name '_entity_src_gen.ndb_gene_src_cell' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_gen.pdbx_gene_src_cellular_location _item_description.description ; Identifies the location inside (or outside) the cell. ; _item.name '_entity_src_gen.pdbx_gene_src_cellular_location' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'CYTOPLASM' 'NUCLEUS' _item_aliases.alias_name '_entity_src_gen.ndb_gene_src_cellular_location' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_gen.pdbx_host_org_gene _item_description.description ; Specific gene which expressed the molecule. ; _item.name '_entity_src_gen.pdbx_host_org_gene' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'HIV-1 POL' 'GLNS7' 'U1A (2-98, Y31H, Q36R)' _item_aliases.alias_name '_entity_src_gen.ndb_host_org_gene' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_gen.pdbx_host_org_organ _item_description.description ; Specific organ which expressed the molecule. ; _item.name '_entity_src_gen.pdbx_host_org_organ' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text _item_examples.case KIDNEY _item_aliases.alias_name '_entity_src_gen.ndb_host_org_organ' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_gen.pdbx_host_org_variant _item_description.description ; Variant of the organism used as the expression system. ; _item.name '_entity_src_gen.pdbx_host_org_variant' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'TRP-LAC' 'LAMBDA DE3' _item_aliases.alias_name '_entity_src_gen.ndb_host_org_variant' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_gen.pdbx_host_org_cell_line _item_description.description ; A specific line of cells used as the expression system. ; _item.name '_entity_src_gen.pdbx_host_org_cell_line' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text _item_examples.case 'HELA' _item_aliases.alias_name '_entity_src_gen.ndb_host_org_cell_line' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_gen.pdbx_host_org_atcc _item_description.description ; Americal Tissue Culture Collection of the expression system. ; _item.name '_entity_src_gen.pdbx_host_org_atcc' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text _item_aliases.alias_name '_entity_src_gen.ndb_host_org_atcc' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_gen.pdbx_host_org_culture_collection _item_description.description ; Culture collection of the expression system. ; _item.name '_entity_src_gen.pdbx_host_org_culture_collection' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text _item_aliases.alias_name '_entity_src_gen.ndb_host_org_culture_collection' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_gen.pdbx_host_org_cell _item_description.description ; Specific cell type which expressed the molecule. ; _item.name '_entity_src_gen.pdbx_host_org_cell' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text _item_examples.case ENDOTHELIAL _item_aliases.alias_name '_entity_src_gen.ndb_host_org_cell' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_gen.pdbx_host_org_organelle _item_description.description ; Specific organelle which expressed the molecule. ; _item.name '_entity_src_gen.pdbx_host_org_organelle' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text _item_examples.case 'MITOCHONDRIA' _item_aliases.alias_name '_entity_src_gen.ndb_host_org_organelle' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_gen.pdbx_host_org_cellular_location _item_description.description ; Identifies the location inside (or outside) the cell which expressed the molecule. ; _item.name '_entity_src_gen.pdbx_host_org_cellular_location' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'CYTOPLASM' 'NUCLEUS' _item_aliases.alias_name '_entity_src_gen.ndb_host_org_cellular_location' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_gen.pdbx_host_org_scientific_name _item_description.description ; The scientific name of the organism that served as host for the production of the entity. ; _item.name '_entity_src_gen.pdbx_host_org_scientific_name' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text _item_examples.case ; ESCHERICHIA COLI HOMO SAPIENS SACCHAROMYCES CEREVISIAE ; _item_aliases.alias_name '_entity_src_gen.ndb_host_org_scientific_name' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_gen.pdbx_host_org_strain _item_description.description ; The strain of the organism in which the entity was expressed. ; _item.name '_entity_src_gen.pdbx_host_org_strain' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text _item_examples.case 'AR120' _item_aliases.alias_name '_entity_src_gen.ndb_host_org_strain' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_gen.pdbx_host_org_tissue _item_description.description ; The specific tissue which expressed the molecule. ; _item.name '_entity_src_gen.pdbx_host_org_tissue' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'heart' 'liver' 'eye lens' _item_aliases.alias_name '_entity_src_gen.ndb_host_org_tissue' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_gen.pdbx_host_org_tissue_fraction _item_description.description ; The fraction of the tissue which expressed the molecule. ; _item.name '_entity_src_gen.pdbx_host_org_tissue_fraction' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'mitochondria' 'nucleus' 'membrane' _item_aliases.alias_name '_entity_src_gen.ndb_host_org_tissue_fraction' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_gen.pdbx_host_org_vector _item_description.description ; Identifies the vector used. ; _item.name '_entity_src_gen.pdbx_host_org_vector' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'PBIT36' 'PET15B' 'PUC18' _item_aliases.alias_name '_entity_src_gen.ndb_host_org_vector' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_gen.pdbx_host_org_vector_type _item_description.description ; Identifies the type of vector used (plasmid, virus, or cosmid). ; _item.name '_entity_src_gen.pdbx_host_org_vector_type' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'COSMID' 'PLASMID' _item_aliases.alias_name '_entity_src_gen.ndb_host_org_vector_type' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_gen.pdbx_description _item_description.description ; Information on the source which is not given elsewhere. ; _item.name '_entity_src_gen.pdbx_description' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text _item_aliases.alias_name '_entity_src_gen.ndb_description' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ## save__entity_src_nat.pdbx_organism_scientific _item_description.description ; Scientific name of the organism of the natural source. ; _item.name '_entity_src_nat.pdbx_organism_scientific' _item.category_id entity_src_nat _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'BOS TAURUS' 'SUS SCROFA' 'ASPERGILLUS ORYZAE' _item_aliases.alias_name '_entity_src_nat.ndb_organism_scientific' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_nat.pdbx_secretion _item_description.description ; Identifies the secretion from which the molecule was isolated. ; _item.name '_entity_src_nat.pdbx_secretion' _item.category_id entity_src_nat _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'saliva' 'urine' 'venom' _item_aliases.alias_name '_entity_src_nat.ndb_secretion' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_nat.pdbx_fragment _item_description.description ; A domain or fragment of the molecule. ; _item.name '_entity_src_nat.pdbx_fragment' _item.category_id entity_src_nat _item.mandatory_code no _item_type.code text _item_aliases.alias_name '_entity_src_nat.ndb_fragment' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_nat.pdbx_variant _item_description.description ; Identifies the variant. ; _item.name '_entity_src_nat.pdbx_variant' _item.category_id entity_src_nat _item.mandatory_code no _item_type.code text _item_aliases.alias_name '_entity_src_nat.ndb_variant' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_nat.pdbx_cell_line _item_description.description ; The specific line of cells. ; _item.name '_entity_src_nat.pdbx_cell_line' _item.category_id entity_src_nat _item.mandatory_code no _item_type.code text _item_examples.case 'HELA' _item_aliases.alias_name '_entity_src_nat.ndb_cell_line' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_nat.pdbx_atcc _item_description.description ; Americal Tissue Culture Collection number. ; _item.name '_entity_src_nat.pdbx_atcc' _item.category_id entity_src_nat _item.mandatory_code no _item_type.code text _item_examples.case '6051' _item_aliases.alias_name '_entity_src_nat.ndb_atcc' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_nat.pdbx_cellular_location _item_description.description ; Identifies the location inside (or outside) the cell. ; _item.name '_entity_src_nat.pdbx_cellular_location' _item.category_id entity_src_nat _item.mandatory_code no _item_type.code text _item_aliases.alias_name '_entity_src_nat.ndb_cellular_location' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_nat.pdbx_organ _item_description.description ; Organized group of tissues that carries on a specialized function. ; _item.name '_entity_src_nat.pdbx_organ' _item.category_id entity_src_nat _item.mandatory_code no _item_type.code text _item_examples.case KIDNEY _item_aliases.alias_name '_entity_src_nat.ndb_organ' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_nat.pdbx_organelle _item_description.description ; Organized structure within cell. ; _item.name '_entity_src_nat.pdbx_organelle' _item.category_id entity_src_nat _item.mandatory_code no _item_type.code text _item_examples.case MITOCHONDRIA _item_aliases.alias_name '_entity_src_nat.ndb_organelle' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_nat.pdbx_cell _item_description.description ; A particular cell type. ; _item.name '_entity_src_nat.pdbx_cell' _item.category_id entity_src_nat _item.mandatory_code no _item_type.code text _item_examples.case 'BHK-21' _item_aliases.alias_name '_entity_src_nat.ndb_cell' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_nat.pdbx_plasmid_name _item_description.description ; The plasmid containing the gene. ; _item.name '_entity_src_nat.pdbx_plasmid_name' _item.category_id entity_src_nat _item.mandatory_code no _item_type.code text _item_examples.case 'pB322' _item_aliases.alias_name '_entity_src_nat.ndb_plasmid_name' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__entity_src_nat.pdbx_plasmid_details _item_description.description ; Details about the plasmid. ; _item.name '_entity_src_nat.pdbx_plasmid_details' _item.category_id entity_src_nat _item.mandatory_code no _item_type.code text _item_examples.case 'PLC28 DERIVATIVE' _item_aliases.alias_name '_entity_src_nat.ndb_plasmid_details' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## save__exptl_crystal_grow.pdbx_details _item_description.description ; Text description of crystal grow procedure. ; _item.name '_exptl_crystal_grow.pdbx_details' _item.category_id exptl_crystal_grow _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'PEG 4000, potassium phosphate, magnesium chloride, cacodylate' _item_aliases.alias_name '_exptl_crystal_grow.rcsb_details' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__exptl_crystal_grow.pdbx_pH_range _item_description.description ; The range of pH values at which the crystal was grown. Used when a point estimate of pH is not appropriate. ; _item.name '_exptl_crystal_grow.pdbx_pH_range' _item.category_id exptl_crystal_grow _item.mandatory_code no _item_type.code line loop_ _item_examples.case '5.6 - 6.4' _item_aliases.alias_name '_exptl_crystal_grow.rcsb_pH_range' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__exptl_crystal.pdbx_crystal_image_url _item_description.description ; The URL for an a file containing the image of crystal. ; _item.name '_exptl_crystal.pdbx_crystal_image_url' _item.category_id exptl_crystal _item.mandatory_code no _item_type.code line _item_aliases.alias_name '_exptl_crystal.rcsb_crystal_image_url' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__exptl_crystal.pdbx_crystal_image_format _item_description.description ; The image format for the file containing the image of crystal specified as an RFC2045/RFC2046 mime type. ; _item.name '_exptl_crystal.pdbx_crystal_image_format' _item.category_id exptl_crystal _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'jpeg' 'gif' 'tiff' _item_aliases.alias_name '_exptl_crystal.rcsb_crystal_image_format' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### ### ################################## ## PDBX_EXPTL_CRYSTAL_GROW_COMP ## ################################## save_pdbx_exptl_crystal_grow_comp _category.description ; Data items in the PDBX_EXPTL_CRYSTAL_GROW_COMP category record details about the components of the solutions that were 'mixed' to produce the crystal. ; _category.id pdbx_exptl_crystal_grow_comp _category.mandatory_code no loop_ _category_key.name '_pdbx_exptl_crystal_grow_comp.comp_id' '_pdbx_exptl_crystal_grow_comp.crystal_id' loop_ _category_group.id 'inclusive_group' 'exptl_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ;loop_ _pdbx_exptl_crystal_grow_comp.crystal_id _pdbx_exptl_crystal_grow_comp.sol_id _pdbx_exptl_crystal_grow_comp.comp_id _pdbx_exptl_crystal_grow_comp.comp_name _pdbx_exptl_crystal_grow_comp.conc _pdbx_exptl_crystal_grow_comp.conc_range _pdbx_exptl_crystal_grow_comp.conc_units 4 'protein' 1 'protein' 25. . 'mg/ml' 4 'protein' 2 'Tris HCl' 20. . 'millimolar' 4 'protein' 3 'NaCl' 0.2 . 'molar' 4 'precipitant' 1 'PEG 4000' 12.5 . 'percent_weight_by_volume' 4 'precipitant' 2 'MES' 0.1 . 'molar' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_exptl_crystal_grow_comp.crystal_id _item_description.description ; This data item is a pointer to _exptl_crystal.id in the EXPTL_CRYSTAL category. ; _item.name '_pdbx_exptl_crystal_grow_comp.crystal_id' _item.category_id pdbx_exptl_crystal_grow_comp _item.mandatory_code yes _item_linked.child_name '_pdbx_exptl_crystal_grow_comp.crystal_id' _item_linked.parent_name '_exptl_crystal.id' save_ save__pdbx_exptl_crystal_grow_comp.comp_id _item_description.description ; The value of _exptl_crystal_grow_comp.comp_id must uniquely identify each item in the PDBX_EXPTL_CRYSTAL_GROW_COMP list. Note that this item need not be a number; it can be any unique identifier. ; _item.name '_pdbx_exptl_crystal_grow_comp.comp_id' _item.category_id pdbx_exptl_crystal_grow_comp _item.mandatory_code yes _item_type.code code loop_ _item_examples.case '1' '2' save_ save__pdbx_exptl_crystal_grow_comp.comp_name _item_description.description ; A common name for the component of the solution. ; _item.name '_pdbx_exptl_crystal_grow_comp.comp_name' _item.category_id pdbx_exptl_crystal_grow_comp _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'protein in buffer' 'acetic acid' save_ save__pdbx_exptl_crystal_grow_comp.sol_id _item_description.description ; An identifier for the solution to which the given solution component belongs. ; _item.name '_pdbx_exptl_crystal_grow_comp.sol_id' _item.category_id pdbx_exptl_crystal_grow_comp _item.mandatory_code no _item_type.code line _item_linked.child_name '_pdbx_exptl_crystal_grow_comp.sol_id' _item_linked.parent_name '_pdbx_exptl_crystal_grow_sol.sol_id' save_ save__pdbx_exptl_crystal_grow_comp.conc _item_description.description ; The concentration value of the solution component. ; _item.name '_pdbx_exptl_crystal_grow_comp.conc' _item.category_id pdbx_exptl_crystal_grow_comp _item.mandatory_code no _item_type.code float loop_ _item_examples.case '200.' '0.1' save_ # save__pdbx_exptl_crystal_grow_comp.conc_range _item_description.description ; The concentration range of the solution component. ; _item.name '_pdbx_exptl_crystal_grow_comp.conc_range' _item.category_id pdbx_exptl_crystal_grow_comp _item.mandatory_code no _item_type.code line loop_ _item_examples.case '200. - 230.' '0.1 - 0.2' save_ save__pdbx_exptl_crystal_grow_comp.conc_units _item_description.description ; The concentration units for the solution component. ; _item.name '_pdbx_exptl_crystal_grow_comp.conc_units' _item.category_id pdbx_exptl_crystal_grow_comp _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'millimolar' 'percent_weight_by_volume' 'milligrams_per_milliliter' save_ ## ## ############################ ## PDBX_EXPTL_CRYSTAL_SOL ## ############################ save_pdbx_exptl_crystal_grow_sol _category.description ; Data items in the PDBX_EXPTL_CRYSTAL_GROW_SOL category record details about the solutions that were 'mixed' to produce the crystal. ; _category.id pdbx_exptl_crystal_grow_sol _category.mandatory_code no loop_ _category_key.name '_pdbx_exptl_crystal_grow_sol.sol_id' '_pdbx_exptl_crystal_grow_sol.crystal_id' loop_ _category_group.id 'inclusive_group' 'exptl_group' loop_ _category_examples.detail _category_examples.case ; Example 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _pdbx_exptl_crystal_grow_sol.crystal_id _pdbx_exptl_crystal_grow_sol.sol_id _pdbx_exptl_crystal_grow_sol.volume _pdbx_exptl_crystal_grow_sol.volume_units _pdbx_exptl_crystal_grow_sol.pH 1 'protein' 0.5 'microliter' 7.5 1 'precipitant' 0.5 'microliter' 7.3 1 'reservoir' 0.5 'milliliter' 7.3 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_exptl_crystal_grow_sol.crystal_id _item_description.description ; This data item is a pointer to _exptl_crystal.id in the EXPTL_CRYSTAL category. ; _item.name '_pdbx_exptl_crystal_grow_sol.crystal_id' _item.category_id pdbx_exptl_crystal_grow_sol _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_exptl_crystal_grow_sol.crystal_id' _item_linked.parent_name '_exptl_crystal.id' save_ save__pdbx_exptl_crystal_grow_sol.sol_id _item_description.description ; An identifier for this solution (e.g. precipitant, reservoir, macromolecule) ; _item.name '_pdbx_exptl_crystal_grow_sol.sol_id' _item.category_id pdbx_exptl_crystal_grow_sol _item.mandatory_code yes _item_type.code line loop_ _item_enumeration.value "precipitant" "reservoir" "macromolecule" save_ save__pdbx_exptl_crystal_grow_sol.volume _item_description.description ; The volume of the solution. ; _item.name '_pdbx_exptl_crystal_grow_sol.volume' _item.category_id pdbx_exptl_crystal_grow_sol _item.mandatory_code no _item_type.code float loop_ _item_examples.case '200.' '0.1' save_ save__pdbx_exptl_crystal_grow_sol.volume_units _item_description.description ; The volume units of the solution. ; _item.name '_pdbx_exptl_crystal_grow_sol.volume_units' _item.category_id pdbx_exptl_crystal_grow_sol _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'milliliter' 'micoliter' save_ save__pdbx_exptl_crystal_grow_sol.pH _item_description.description ; The pH of the solution. ; _item.name '_pdbx_exptl_crystal_grow_sol.pH' _item.category_id pdbx_exptl_crystal_grow_sol _item.mandatory_code no _item_type.code float loop_ _item_examples.case '7.2' save_ ## ## ####################################### ## PDBX_EXPTL_CRYSTAL_CRYO_TREATMENT ## ####################################### save_pdbx_exptl_crystal_cryo_treatment _category.description ; Data items in the PDBX_EXPTL_CRYSTAL_CRYO_TREATMENT category record details cryogenic treatments applied to this crystal. ; _category.id pdbx_exptl_crystal_cryo_treatment _category.mandatory_code no loop_ _category_key.name '_pdbx_exptl_crystal_cryo_treatment.crystal_id' loop_ _category_group.id 'inclusive_group' 'exptl_group' loop_ _category_examples.detail _category_examples.case ; Example 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _pdbx_exptl_crystal_cryo_treatment.crystal_id 4 _pdbx_exptl_crystal_cryo_treatment.final_solution_details ; 25% (v/v) glycerol in precipitant solution ; _pdbx_exptl_crystal_cryo_treatment.soaking_details ; A series of 1 min soaks beginning at 5% (v/v) glycerol in precipitant, transiting to 20% (v/v) glycerol, and finally to 25% glycerol ; _pdbx_exptl_crystal_cryo_treatment.cooling_details ; Direct immersion in liquid nitrogen ; _pdbx_exptl_crystal_cryo_treatment.annealing_details ? ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_exptl_crystal_cryo_treatment.crystal_id _item_description.description ; This data item is a pointer to _exptl_crystal.id in the EXPTL_CRYSTAL category. ; _item.name '_pdbx_exptl_crystal_cryo_treatment.crystal_id' _item.category_id pdbx_exptl_crystal_cryo_treatment _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_exptl_crystal_cryo_treatment.crystal_id' _item_linked.parent_name '_exptl_crystal.id' save_ save__pdbx_exptl_crystal_cryo_treatment.final_solution_details _item_description.description ; Details of the final solution used in the treatment of this crystal ; _item.name '_pdbx_exptl_crystal_cryo_treatment.final_solution_details' _item.category_id pdbx_exptl_crystal_cryo_treatment _item.mandatory_code no _item_type.code text loop_ _item_examples.case ; 25% (v/v) glycerol in precipitant solution ; save_ save__pdbx_exptl_crystal_cryo_treatment.soaking_details _item_description.description ; Details of the soaking treatment applied to this crystal. ; _item.name '_pdbx_exptl_crystal_cryo_treatment.soaking_details' _item.category_id pdbx_exptl_crystal_cryo_treatment _item.mandatory_code no _item_type.code text loop_ _item_examples.case ; A series of 1 min soaks beginning at 5% (v/v) glycerol in precipitant, transiting to 20% (v/v) glycerol, and finally to 25% glycerol ; save_ save__pdbx_exptl_crystal_cryo_treatment.cooling_details _item_description.description ; Details of the cooling treatment applied to this crystal. ; _item.name '_pdbx_exptl_crystal_cryo_treatment.cooling_details' _item.category_id pdbx_exptl_crystal_cryo_treatment _item.mandatory_code no _item_type.code text loop_ _item_examples.case ; Direct immersion in liquid nitrogen ; save_ save__pdbx_exptl_crystal_cryo_treatment.annealing_details _item_description.description ; Details of the annealing treatment applied to this crystal. ; _item.name '_pdbx_exptl_crystal_cryo_treatment.annealing_details' _item.category_id pdbx_exptl_crystal_cryo_treatment _item.mandatory_code no _item_type.code text loop_ _item_examples.case ; 10 sec interruption of cold stream with plastic ruler. Performed twice. ; save_ ## save__geom_angle.pdbx_atom_site_PDB_ins_code_1 _item_description.description ; Pointer to _atom_site.pdbx_PDB_ins_code. ; _item.name '_geom_angle.pdbx_atom_site_PDB_ins_code_1' _item.category_id geom_angle _item.mandatory_code no _item_type.code code _item_linked.child_name '_geom_angle.pdbx_atom_site_PDB_ins_code_1' _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' _item_aliases.alias_name '_geom_angle.ndb_atom_site_PDB_ins_code_1' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__geom_angle.pdbx_atom_site_PDB_ins_code_2 _item_description.description ; Pointer to _atom_site.pdbx_PDB_ins_code. ; _item.name '_geom_angle.pdbx_atom_site_PDB_ins_code_2' _item.category_id geom_angle _item.mandatory_code no _item_type.code code _item_linked.child_name '_geom_angle.pdbx_atom_site_PDB_ins_code_2' _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' _item_aliases.alias_name '_geom_angle.ndb_atom_site_PDB_ins_code_2' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__geom_angle.pdbx_atom_site_PDB_ins_code_3 _item_description.description ; Pointer to _atom_site.pdbx_PDB_ins_code. ; _item.name '_geom_angle.pdbx_atom_site_PDB_ins_code_3' _item.category_id geom_angle _item.mandatory_code no _item_type.code code _item_linked.child_name '_geom_angle.pdbx_atom_site_PDB_ins_code_3' _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' _item_aliases.alias_name '_geom_angle.ndb_atom_site_PDB_ins_code_3' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__geom_angle.pdbx_PDB_model_num _item_description.description ; Pointer to _atom_site.pdbx_PDB_model_num ; _item.name '_geom_angle.pdbx_PDB_model_num' _item.category_id geom_angle _item.mandatory_code no _item_type.code code _item_linked.child_name '_geom_angle.pdbx_PDB_model_num' _item_linked.parent_name '_atom_site.pdbx_PDB_model_num' _item_aliases.alias_name '_geom_angle.ndb_model_num' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__geom_bond.pdbx_atom_site_PDB_ins_code_1 _item_description.description ; Pointer to _atom_site.pdbx_PDB_ins_code. ; _item.name '_geom_bond.pdbx_atom_site_PDB_ins_code_1' _item.category_id geom_bond _item.mandatory_code no _item_type.code code _item_linked.child_name '_geom_bond.pdbx_atom_site_PDB_ins_code_1' _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' _item_aliases.alias_name '_geom_bond.ndb_atom_site_PDB_ins_code_1' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__geom_bond.pdbx_atom_site_PDB_ins_code_2 _item_description.description ; Pointer to _atom_site.pdbx_PDB_ins_code. ; _item.name '_geom_bond.pdbx_atom_site_PDB_ins_code_2' _item.category_id geom_bond _item.mandatory_code no _item_type.code code _item_linked.child_name '_geom_bond.pdbx_atom_site_PDB_ins_code_2' _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' _item_aliases.alias_name '_geom_bond.ndb_atom_site_PDB_ins_code_2' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__geom_bond.pdbx_PDB_model_num _item_description.description ; Pointer to _atom_site.pdbx_PDB_model_num ; _item.name '_geom_bond.pdbx_PDB_model_num' _item.category_id geom_bond _item.mandatory_code no _item_type.code code _item_linked.child_name '_geom_bond.pdbx_PDB_model_num' _item_linked.parent_name '_atom_site.pdbx_PDB_model_num' _item_aliases.alias_name '_geom_bond.ndb_model_num' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__geom_contact.pdbx_atom_site_PDB_ins_code_1 _item_description.description ; Pointer to _atom_site.pdbx_PDB_ins_code. ; _item.name '_geom_contact.pdbx_atom_site_PDB_ins_code_1' _item.category_id geom_contact _item.mandatory_code no _item_type.code code _item_linked.child_name '_geom_contact.pdbx_atom_site_PDB_ins_code_1' _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' _item_aliases.alias_name '_geom_contact.ndb_atom_site_PDB_ins_code_1' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__geom_contact.pdbx_atom_site_PDB_ins_code_2 _item_description.description ; Pointer to _atom_site.pdbx_PDB_ins_code. ; _item.name '_geom_contact.pdbx_atom_site_PDB_ins_code_2' _item.category_id geom_contact _item.mandatory_code no _item_type.code code _item_linked.child_name '_geom_contact.pdbx_atom_site_PDB_ins_code_2' _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' _item_aliases.alias_name '_geom_contact.ndb_atom_site_PDB_ins_code_2' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__geom_contact.pdbx_PDB_model_num _item_description.description ; Pointer to _atom_site.pdbx_PDB_model_num ; _item.name '_geom_contact.pdbx_PDB_model_num' _item.category_id geom_contact _item.mandatory_code no _item_type.code code _item_linked.child_name '_geom_contact.pdbx_PDB_model_num' _item_linked.parent_name '_atom_site.pdbx_PDB_model_num' _item_aliases.alias_name '_geom_contact.ndb_model_num' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__geom_torsion.pdbx_atom_site_PDB_ins_code_1 _item_description.description ; Pointer to _atom_site.pdbx_PDB_ins_code. ; _item.name '_geom_torsion.pdbx_atom_site_PDB_ins_code_1' _item.category_id geom_torsion _item.mandatory_code no _item_type.code code _item_linked.child_name '_geom_torsion.pdbx_atom_site_PDB_ins_code_1' _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' _item_aliases.alias_name '_geom_torsion.ndb_atom_site_PDB_ins_code_1' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__geom_torsion.pdbx_atom_site_PDB_ins_code_2 _item_description.description ; Pointer to _atom_site.pdbx_PDB_ins_code. ; _item.name '_geom_torsion.pdbx_atom_site_PDB_ins_code_2' _item.category_id geom_torsion _item.mandatory_code no _item_type.code code _item_linked.child_name '_geom_torsion.pdbx_atom_site_PDB_ins_code_2' _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' _item_aliases.alias_name '_geom_torsion.ndb_atom_site_PDB_ins_code_2' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__geom_torsion.pdbx_atom_site_PDB_ins_code_3 _item_description.description ; Pointer to _atom_site.pdbx_PDB_ins_code. ; _item.name '_geom_torsion.pdbx_atom_site_PDB_ins_code_3' _item.category_id geom_torsion _item.mandatory_code no _item_type.code code _item_linked.child_name '_geom_torsion.pdbx_atom_site_PDB_ins_code_3' _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' _item_aliases.alias_name '_geom_torsion.ndb_atom_site_PDB_ins_code_3' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__geom_torsion.pdbx_atom_site_PDB_ins_code_4 _item_description.description ; Pointer to _atom_site.pdbx_PDB_ins_code. ; _item.name '_geom_torsion.pdbx_atom_site_PDB_ins_code_4' _item.category_id geom_torsion _item.mandatory_code no _item_type.code code _item_linked.child_name '_geom_torsion.pdbx_atom_site_PDB_ins_code_4' _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' _item_aliases.alias_name '_geom_torsion.ndb_atom_site_PDB_ins_code_4' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__geom_torsion.pdbx_PDB_model_num _item_description.description ; Pointer to _atom_site.pdbx_PDB_model_num ; _item.name '_geom_torsion.pdbx_PDB_model_num' _item.category_id geom_torsion _item.mandatory_code no _item_type.code code _item_linked.child_name '_geom_torsion.pdbx_PDB_model_num' _item_linked.parent_name '_atom_site.pdbx_PDB_model_num' _item_aliases.alias_name '_geom_torsion.ndb_model_num' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## save__refine.pdbx_ls_sigma_I _item_description.description ; Data cutoff (SIGMA(I)) ; _item.name '_refine.pdbx_ls_sigma_I' _item.category_id refine _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_refine.ndb_ls_sigma_I' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__refine.pdbx_ls_sigma_F _item_description.description ; Data cutoff (SIGMA(F)) ; _item.name '_refine.pdbx_ls_sigma_F' _item.category_id refine _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_refine.ndb_ls_sigma_F' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__refine.pdbx_ls_sigma_Fsqd _item_description.description ; Data cutoff (SIGMA(F^2)) ; _item.name '_refine.pdbx_ls_sigma_Fsqd' _item.category_id refine _item.mandatory_code no _item_type.code float save_ save__refine.pdbx_data_cutoff_high_absF _item_description.description ; Value of F at "high end" of data cutoff. ; _item.name '_refine.pdbx_data_cutoff_high_absF' _item.category_id refine _item.mandatory_code no _item_type.code float _item_examples.case 17600 _item_aliases.alias_name '_refine.ndb_data_cutoff_high_absF' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__refine.pdbx_data_cutoff_high_rms_absF _item_description.description ; Value of RMS |F| used as high data cutoff. ; _item.name '_refine.pdbx_data_cutoff_high_rms_absF' _item.category_id refine _item.mandatory_code no _item_type.code float _item_examples.case 205.1 _item_aliases.alias_name '_refine.rcsb_data_cutoff_high_rms_absF' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__refine.pdbx_data_cutoff_low_absF _item_description.description ; Value of F at "low end" of data cutoff. ; _item.name '_refine.pdbx_data_cutoff_low_absF' _item.category_id refine _item.mandatory_code no _item_type.code float _item_examples.case 0.30 _item_aliases.alias_name '_refine.ndb_data_cutoff_low_absF' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__refine.pdbx_isotropic_thermal_model _item_description.description ; Whether the structure was refined with indvidual isotropic, anisotropic or overall temperature factor. ; _item.name '_refine.pdbx_isotropic_thermal_model' _item.category_id refine _item.mandatory_code no _item_type.code text loop_ _item_examples.case Isotropic Overall _item_aliases.alias_name '_refine.ndb_isotropic_thermal_model' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__refine.pdbx_ls_cross_valid_method _item_description.description ; Whether the cross validataion method was used through out or only at the end. ; _item.name '_refine.pdbx_ls_cross_valid_method' _item.category_id refine _item.mandatory_code no _item_type.code text _item_examples.case 'FREE R-VALUE' _item_aliases.alias_name '_refine.ndb_ls_cross_valid_method' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__refine.pdbx_method_to_determine_struct _item_description.description ; Method(s) used to determine the structure. ; _item.name '_refine.pdbx_method_to_determine_struct' _item.category_id refine _item.mandatory_code no _item_type.code text loop_ _item_examples.case _item_examples.detail 'AB INITIO PHASING' ? 'DM' 'Direct Methods' 'ISAS ' 'Iterative Single wavelength Anomalous Scattering' 'ISIR' 'Iterative Single Isomorphous Replacement' 'ISIRAS' 'Iterative Single Isomorphous Replacement with Anomalous Scattering' 'MAD' 'Multi wavelength Anomalous Diffraction' 'MIR' 'Multiple Isomorphous Replacement' 'MIRAS' 'Multiple Isomorphous Replacement with Anomalous Scattering' 'MR' 'Molecular Replacement' 'SIR' 'Single Isomorphous Replacement' 'SIRAS' 'Single Isomorphous Replacement with Anomalous Scattering' _item_aliases.alias_name '_refine.ndb_method_to_determine_struct' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__refine.pdbx_starting_model _item_description.description ; Starting model for refinement. Starting model for molecular replacement should refer to a previous structure or experiment. ; _item.name '_refine.pdbx_starting_model' _item.category_id refine _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'BDL001' _item_aliases.alias_name '_refine.ndb_starting_model' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__refine.pdbx_stereochemistry_target_values _item_description.description ; Stereochemistry target values used in refinement. ; _item.name '_refine.pdbx_stereochemistry_target_values' _item.category_id refine _item.mandatory_code no _item_type.code text _item_aliases.alias_name '_refine.ndb_stereochemistry_target_values' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__refine.pdbx_R_Free_selection_details _item_description.description ; Details of the manner in which the cross validation reflections were selected. ; _item.name '_refine.pdbx_R_Free_selection_details' _item.category_id refine _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'Random selection' _item_aliases.alias_name '_refine.ndb_R_Free_selection_details' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__refine.pdbx_stereochem_target_val_spec_case _item_description.description ; Special case of stereochemistry target values used in SHELXL refinement. ; _item.name '_refine.pdbx_stereochem_target_val_spec_case' _item.category_id refine _item.mandatory_code no _item_type.code text _item_aliases.alias_name '_refine.ndb_stereochem_target_val_spec_case' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__refine_hist.pdbx_number_atoms_protein _item_description.description ; Number of protein atoms included in refinement ; _item.name '_refine_hist.pdbx_number_atoms_protein' _item.category_id refine_hist _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_refine_hist.rcsb_number_atoms_protein' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__refine_hist.pdbx_number_atoms_nucleic_acid _item_description.description ; Number of nucleic atoms included in refinement ; _item.name '_refine_hist.pdbx_number_atoms_nucleic_acid' _item.category_id refine_hist _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_refine_hist.rcsb_number_atoms_nucleic_acid' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__refine_hist.pdbx_number_atoms_ligand _item_description.description ; Number of ligand atoms included in refinement ; _item.name '_refine_hist.pdbx_number_atoms_ligand' _item.category_id refine_hist _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_refine_hist.rcsb_number_atoms_ligand' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ # save__refine_hist.pdbx_number_atoms_lipid _item_description.description ; Number of lipid atoms included in refinement ; _item.name '_refine_hist.pdbx_number_atoms_lipid' _item.category_id refine_hist _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_refine_hist.rcsb_number_atoms_lipid' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__refine_hist.pdbx_number_atoms_carb _item_description.description ; Number of carbohydrate atoms included in refinement ; _item.name '_refine_hist.pdbx_number_atoms_carb' _item.category_id refine_hist _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_refine_hist.rcsb_number_atoms_carb' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__refine_hist.pdbx_pseudo_atom_details _item_description.description ; Details of pseduo atoms used to model unexplained density ; _item.name '_refine_hist.pdbx_pseudo_atom_details' _item.category_id refine_hist _item.mandatory_code no _item_type.code text _item_aliases.alias_name '_refine_hist.rcsb_pseudo_atom_details' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### ### ### save__refine_ls_shell.pdbx_total_number_of_bins_used _item_description.description ; Total number of bins used. ; _item.name '_refine_ls_shell.pdbx_total_number_of_bins_used' _item.category_id refine_ls_shell _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_refine_ls_shell.ndb_total_number_of_bins_used' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ## save__refln.pdbx_F_calc_part_solvent _item_description.description ; The calculated value of the structure factor in arbitrary units reflecting only the contribution of the solvent model. ; _item.name '_refln.pdbx_F_calc_part_solvent' _item.category_id refln _item.mandatory_code no _item_type.code float _item_units.code arbitrary _item_aliases.alias_name '_refln.rcsb_F_calc_part_solvent' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__refln.pdbx_phase_calc_part_solvent _item_description.description ; The calculated structure-factor phase in degrees reflecting only the contribution of the solvent model. ; _item.name '_refln.pdbx_phase_calc_part_solvent' _item.category_id refln _item.mandatory_code no _item_aliases.alias_name '_refln.rcsb_phase_calc_part_solvent' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 _item_type.code float _item_units.code degrees save_ save__refln.pdbx_F_calc_with_solvent _item_description.description ; The calculated value of the structure factor in arbitrary units including the contribution of the solvent model. ; _item.name '_refln.pdbx_F_calc_with_solvent' _item.category_id refln _item.mandatory_code no _item_type.code float _item_units.code arbitrary _item_aliases.alias_name '_refln.rcsb_F_calc_with_solvent' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__refln.pdbx_phase_calc_with_solvent _item_description.description ; The calculated structure-factor phase in degrees including the contribution of the solvent model. ; _item.name '_refln.pdbx_phase_calc_with_solvent' _item.category_id refln _item.mandatory_code no _item_aliases.alias_name '_refln.rcsb_phase_calc_with_solvent' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 _item_type.code float _item_units.code degrees save_ ## ## save__reflns.pdbx_redundancy _item_description.description ; Overall redundancy for this data set (%). ; _item.name '_reflns.pdbx_redundancy' _item.category_id reflns _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_reflns.ndb_redundancy' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__reflns.pdbx_Rmerge_I_obs _item_description.description ; The R value for merging intensities satisfying the observed criteria in this data set. ; _item.name '_reflns.pdbx_Rmerge_I_obs' _item.category_id reflns _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_reflns.ndb_Rmerge_I_obs' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__reflns.pdbx_Rmerge_I_all _item_description.description ; The R value for merging all intensities in this data set. ; _item.name '_reflns.pdbx_Rmerge_I_all' _item.category_id reflns _item.mandatory_code no _item_type.code float save_ save__reflns.pdbx_Rsym_value _item_description.description ; R Sym value in percent. ; _item.name '_reflns.pdbx_Rsym_value' _item.category_id reflns _item.mandatory_code no _item_examples.case 2.0 _item_type.code float _item_aliases.alias_name '_reflns.ndb_Rsym_value' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__reflns.pdbx_netI_over_av_sigmaI _item_description.description ; Overall / ; _item.name '_reflns.pdbx_netI_over_av_sigmaI' _item.category_id reflns _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_reflns.ndb_netI_over_av_sigmaI' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__reflns.pdbx_netI_over_sigmaI _item_description.description ; Overall ; _item.name '_reflns.pdbx_netI_over_sigmaI' _item.category_id reflns _item.mandatory_code no _item_type.code float save_ save__reflns.pdbx_res_netI_over_av_sigmaI_2 _item_description.description ; Resolution (angstrom) for reflections with / = 2. ; _item.name '_reflns.pdbx_res_netI_over_av_sigmaI_2' _item.category_id reflns _item.mandatory_code no _item_type.code float _item_units.code angstroms save_ save__reflns.pdbx_res_netI_over_sigmaI_2 _item_description.description ; Resolution (angstroms) for reflections with = 2. ; _item.name '_reflns.pdbx_res_netI_over_sigmaI_2' _item.category_id reflns _item.mandatory_code no _item_type.code float _item_units.code angstroms save_ save__reflns.pdbx_chi_squared _item_description.description ; Overall Chi-squared statistic. ; _item.name '_reflns.pdbx_chi_squared' _item.category_id reflns _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_reflns.rcsb_chi_squared' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__reflns.pdbx_scaling_rejects _item_description.description ; Number of reflections rejected in scaling operations. ; _item.name '_reflns.pdbx_scaling_rejects' _item.category_id reflns _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_reflns.rcsb_scaling_rejects' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__reflns.pdbx_d_res_high_opt _item_description.description ; The highest optical resolution for this reflection data set as determined by computational method _reflns.pdbx_d_res_opt_method. ; _item.name '_reflns.pdbx_d_res_high_opt' _item.category_id reflns _item.mandatory_code no _item_aliases.alias_name '_reflns.rcsb_d_res_high_opt' _item_aliases.dictionary cif_rcsb.dic _item_aliases.version 1.1 _item_examples.case '1.2' loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__reflns.pdbx_d_res_low_opt _item_description.description ; The lowest optical resolution for this reflection data set as determined by computational method _reflns.pdbx_d_res_opt_method. ; _item.name '_reflns.pdbx_d_res_low_opt' _item.category_id reflns _item.mandatory_code no _item_aliases.alias_name '_reflns.rcsb_d_res_low_opt' _item_aliases.dictionary cif_rcsb.dic _item_aliases.version 1.1 _item_examples.case '20.5' loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__reflns.pdbx_d_res_opt_method _item_description.description ; The computational method used to determine the optical resolution limits _reflns.pdbx_d_res_high_opt and _reflns.pdbx_d_res_low_opt. ; _item.name '_reflns.pdbx_d_res_opt_method' _item.category_id reflns _item.mandatory_code no _item_aliases.alias_name '_reflns.rcsb_d_res_opt_method' _item_aliases.dictionary cif_rcsb.dic _item_aliases.version 1.1 _item_examples.case 'SFCHECK' _item_type.code text save_ ## ## save__reflns_shell.pdbx_redundancy _item_description.description ; Redundancy for the current shell. ; _item.name '_reflns_shell.pdbx_redundancy' _item.category_id reflns_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_reflns_shell.ndb_redundancy' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__reflns_shell.pdbx_Rsym_value _item_description.description ; R sym value in percent. ; _item.name '_reflns_shell.pdbx_Rsym_value' _item.category_id reflns_shell _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_aliases.alias_name '_reflns_shell.ndb_Rsym_value' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__reflns_shell.pdbx_chi_squared _item_description.description ; Chi-squared statistic for this resolution shell. ; _item.name '_reflns_shell.pdbx_chi_squared' _item.category_id reflns_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_reflns_shell.rcsb_chi_squared' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__reflns_shell.pdbx_netI_over_sigmaI_all _item_description.description ; The mean of the ratio of the intensities to their standard uncertainties of all reflections in the resolution shell. _reflns_shell.pdbx_meanI_over_sigmaI_all = ; _item.name '_reflns_shell.pdbx_netI_over_sigmaI_all' _item.category_id reflns_shell _item.mandatory_code no _item_type.code float save_ save__reflns_shell.pdbx_netI_over_sigmaI_obs _item_description.description ; The mean of the ratio of the intensities to their standard uncertainties of observed reflections (see _reflns.observed_criterion) in the resolution shell. _reflns_shell.pdbx_meanI_over_sigmaI_obs = ; _item.name '_reflns_shell.pdbx_netI_over_sigmaI_obs' _item.category_id reflns_shell _item.mandatory_code no _item_type.code float save_ ## save__struct.pdbx_descriptor _item_description.description ; An automatically generated descriptor for an NDB structure or the unstructured content of the PDB COMPND record. ; _item.name '_struct.pdbx_descriptor' _item.category_id struct _item.mandatory_code no _item_type.code text loop_ _item_examples.case ; 5'-D(*CP*GP*CP*(HYD)AP*AP*AP*TP*TP*TP*GP*CP*G)-3' ; _item_aliases.alias_name '_struct.ndb_descriptor' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct.pdbx_model_details _item_description.description ; Text description of the methodology which produced this model structure. ; _item.name '_struct.pdbx_model_details' _item.category_id struct _item.mandatory_code no _item_type.code text loop_ _item_examples.case ; This model was produced from a 10 nanosecond Amber/MD simulation starting from PDB structure ID 1ABC. ; _item_aliases.alias_name '_struct.rcsb_model_details' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct.pdbx_formula_weight _item_description.description ; Estimated formula mass in daltons of the deposited structure assembly. ; _item.name '_struct.pdbx_formula_weight' _item.category_id struct _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1.0 1.0 1.0 _item_type.code float save_ save__struct.pdbx_formula_weight_method _item_description.description ; Method used to determine _struct.pdbx_formula_weight. ; _item.name '_struct.pdbx_formula_weight_method' _item.category_id struct _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'MASS SPEC' 'CALCULATION' save_ ## save__struct_asym.pdbx_modified _item_description.description ; This data item indicates whether the structural elements are modified. ; _item.name '_struct_asym.pdbx_modified' _item.category_id struct_asym _item.mandatory_code no _item_type.code text _item_examples.case 'y' _item_aliases.alias_name '_struct_asym.ndb_modified' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_asym.pdbx_blank_PDB_chainid_flag _item_description.description ; A flag indicating that this entity was originally labeled with a blank PDB chain id. ; _item.name '_struct_asym.pdbx_blank_PDB_chainid_flag' _item.category_id struct_asym _item.mandatory_code no _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail Y 'Yes' N 'No' _item_aliases.alias_name '_struct_asym.rcsb_blank_PDB_chainid_flag' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ## save__struct_biol.pdbx_parent_biol_id _item_description.description ; An identifier for the parent biological assembly if this biological unit is part of a complex assembly. ; _item.name '_struct_biol.pdbx_parent_biol_id' _item.category_id struct_biol _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_biol.pdbx_parent_biol_id' _item_linked.parent_name '_struct_biol.id' loop_ _item_examples.case 1 2 3 _item_aliases.alias_name '_struct_biol.rcsb_parent_biol_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_biol.pdbx_formula_weight _item_description.description ; Estimated formula mass in daltons of the biological assembly. ; _item.name '_struct_biol.pdbx_formula_weight' _item.category_id struct_biol _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1.0 1.0 1.0 _item_type.code float save_ save__struct_biol.pdbx_formula_weight_method _item_description.description ; Method used to determine _struct_biol.pdbx_formula_weight. ; _item.name '_struct_biol.pdbx_formula_weight_method' _item.category_id struct_biol _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'MASS SPEC' 'CALCULATION' save_ ## ## save__struct_biol_gen.pdbx_full_symmetry_operation _item_description.description ; This item expresses category _struct_biol_gen.symmetry on an X, Y and Z basis. ; _item.name '_struct_biol_gen.pdbx_full_symmetry_operation' _item.category_id struct_biol_gen _item.mandatory_code no _item_type.code code _item_examples.case '-X, Y+1/2, -Z' _item_aliases.alias_name '_struct_biol_gen.ndb_full_symmetry_operation' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_biol_gen.pdbx_PDB_order _item_description.description ; An ordering index used to reproduce the presentation of chain order in the original PDB format data files. ; _item.name '_struct_biol_gen.pdbx_PDB_order' _item.category_id struct_biol_gen _item.mandatory_code no _item_type.code int loop_ _item_examples.case 1 2 3 _item_aliases.alias_name '_struct_biol_gen.rcsb_pdb_order' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ## save__struct_conf.pdbx_beg_PDB_ins_code _item_description.description ; A component of the identifier for the residue at which the conformation segment starts. ; _item.name '_struct_conf.pdbx_beg_PDB_ins_code' _item.category_id struct_conf _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_conf.pdbx_beg_PDB_ins_code' _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' _item_aliases.alias_name '_struct_conf.ndb_beg_label_ins_code_pdb' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_conf.pdbx_end_PDB_ins_code _item_description.description ; A component of the identifier for the residue at which the conformation segment ends. ; _item.name '_struct_conf.pdbx_end_PDB_ins_code' _item.category_id struct_conf _item.mandatory_code no _item_linked.child_name '_struct_conf.pdbx_end_PDB_ins_code' _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' _item_aliases.alias_name '_struct_conf.ndb_end_label_ins_code_pdb' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_conf.pdbx_PDB_helix_class _item_description.description ; This item is a place holder for the helix class used in the PDB HELIX record. ; _item.name '_struct_conf.pdbx_PDB_helix_class' _item.category_id struct_conf _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_struct_conf.ndb_helix_class_pdb' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_conf.pdbx_PDB_helix_length _item_description.description ; A placeholder for the lengths of the helix of the PDB HELIX record. ; _item.name '_struct_conf.pdbx_PDB_helix_length' _item.category_id struct_conf _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_struct_conf.ndb_length' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_conf.pdbx_PDB_helix_id _item_description.description ; A placeholder for the helix identifier of the PDB HELIX record. ; _item.name '_struct_conf.pdbx_PDB_helix_id' _item.category_id struct_conf _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_struct_conf.pdb_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ## save__struct_conn.pdbx_ptnr1_PDB_ins_code _item_description.description ; A component of the identifier for partner 1 of the structure connection. This data item is a pointer to _atom_site.ins_code in the ATOM_SITE category. ; _item.name '_struct_conn.pdbx_ptnr1_PDB_ins_code' _item.category_id struct_conn _item.mandatory_code no _item_type.code code loop_ _item_examples.case '1' '2' _item_linked.child_name '_struct_conn.pdbx_ptnr1_PDB_ins_code' _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' _item_aliases.alias_name '_struct_conn.ndb_ptnr1_label_ins_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_conn.pdbx_ptnr1_auth_alt_id _item_description.description ; A component of the identifier for partner 1 of the structure connection. This data item is a pointer to _atom_site.pdbx_auth_alt_id in the ATOM_SITE category. ; _item.name '_struct_conn.pdbx_ptnr1_auth_alt_id' _item.category_id struct_conn _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'A' 'B' _item_linked.child_name '_struct_conn.pdbx_ptnr1_auth_alt_id' _item_linked.parent_name '_atom_site.pdbx_auth_alt_id' _item_aliases.alias_name '_struct_conn.ndb_ptnr1_auth_alt_loc' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_conn.pdbx_ptnr1_label_alt_id _item_description.description ; A component of the identifier for partner 1 of the structure connection. This data item is a pointer to _atom_site.label_alt_id in the ATOM_SITE category. ; _item.name '_struct_conn.pdbx_ptnr1_label_alt_id' _item.category_id struct_conn _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'A' 'B' _item_linked.child_name '_struct_conn.pdbx_ptnr1_label_alt_id' _item_linked.parent_name '_atom_site.label_alt_id' _item_aliases.alias_name '_struct_conn.ndb_ptnr1_label_alt_loc' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_conn.pdbx_ptnr1_standard_comp_id _item_description.description ; A placeholder for the standard residue name found in the MODRES record of a PDB file. ; _item.name '_struct_conn.pdbx_ptnr1_standard_comp_id' _item.category_id struct_conn _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'A' 'T' 'C' 'G' 'GLY' 'ALA' 'MET' _item_aliases.alias_name '_struct_conn.ndb_ptnr1_standard_comp_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_conn.pdbx_ptnr2_PDB_ins_code _item_description.description ; A component of the identifier for partner 1 of the structure connection. This data item is a pointer to _atom_site.pdbx_PDB_ins_code in the ATOM_SITE category. ; _item.name '_struct_conn.pdbx_ptnr2_PDB_ins_code' _item.category_id struct_conn _item.mandatory_code no _item_type.code code loop_ _item_examples.case '1' '2' _item_linked.child_name '_struct_conn.pdbx_ptnr2_PDB_ins_code' _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' _item_aliases.alias_name '_struct_conn.ndb_ptnr2_label_ins_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_conn.pdbx_ptnr2_auth_alt_id _item_description.description ; A component of the identifier for partner 2 of the structure connection. This data item is a pointer to _atom_site.pdbx_auth_alt_id in the ATOM_SITE category. ; _item.name '_struct_conn.pdbx_ptnr2_auth_alt_id' _item.category_id struct_conn _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'A' 'B' _item_linked.child_name '_struct_conn.pdbx_ptnr2_auth_alt_id' _item_linked.parent_name '_atom_site.pdbx_auth_alt_id' _item_aliases.alias_name '_struct_conn.ndb_ptnr2_auth_alt_loc' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_conn.pdbx_ptnr2_label_alt_id _item_description.description ; A component of the identifier for partner 2 of the structure connection. This data item is a pointer to _atom_site.label_alt_id in the ATOM_SITE category. ; _item.name '_struct_conn.pdbx_ptnr2_label_alt_id' _item.category_id struct_conn _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'A' 'B' _item_linked.child_name '_struct_conn.pdbx_ptnr2_label_alt_id' _item_linked.parent_name '_atom_site.label_alt_id' _item_aliases.alias_name '_struct_conn.ndb_ptnr2_label_alt_loc' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_conn.pdbx_ptnr3_auth_alt_id _item_description.description ; A component of the identifier for partner 3 of the structure connection. This data item is a pointer to _atom_site.auth_alt_id in the ATOM_SITE category. ; _item.name '_struct_conn.pdbx_ptnr3_auth_alt_id' _item.category_id struct_conn _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'A' 'B' _item_linked.child_name '_struct_conn.pdbx_ptnr3_auth_alt_id' _item_linked.parent_name '_atom_site.pdbx_auth_alt_id' _item_aliases.alias_name '_struct_conn.ndb_ptnr3_auth_alt_loc' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_conn.pdbx_ptnr3_auth_asym_id _item_description.description ; A component of the identifier for partner 3 of the structure connection. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_struct_conn.pdbx_ptnr3_auth_asym_id' _item.category_id struct_conn _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'A' 'B' 'C' _item_linked.child_name '_struct_conn.pdbx_ptnr3_auth_asym_id' _item_linked.parent_name '_atom_site.auth_asym_id' _item_aliases.alias_name '_struct_conn.ndb_ptnr3_auth_asym_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_conn.pdbx_ptnr3_auth_atom_id _item_description.description ; A component of the identifier for partner 3 of the structure connection. This data item is a pointer to _atom_site.auth_atom_id in the ATOM_SITE category. ; _item.name '_struct_conn.pdbx_ptnr3_auth_atom_id' _item.category_id struct_conn _item.mandatory_code no _item_type.code atcode _item_examples.case 'O5*' _item_linked.child_name '_struct_conn.pdbx_ptnr3_auth_atom_id' _item_linked.parent_name '_atom_site.auth_atom_id' _item_aliases.alias_name '_struct_conn.ndb_ptnr3_auth_atom_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_conn.pdbx_ptnr3_auth_comp_id _item_description.description ; A component of the identifier for partner 3 of the structure connection. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_struct_conn.pdbx_ptnr3_auth_comp_id' _item.category_id struct_conn _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'A' 'T' 'C' 'G' 'GLY' 'ALA' 'MET' _item_linked.child_name '_struct_conn.pdbx_ptnr3_auth_comp_id' _item_linked.parent_name '_atom_site.auth_comp_id' _item_aliases.alias_name '_struct_conn.ndb_ptnr3_auth_comp_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_conn.pdbx_ptnr3_PDB_ins_code _item_description.description ; A component of the identifier for partner 3 of the structure connection. This data item is a pointer to _atom_site.pdbx_PDB_ins_code in the ATOM_SITE category. ; _item.name '_struct_conn.pdbx_ptnr3_PDB_ins_code' _item.category_id struct_conn _item.mandatory_code no _item_type.code code loop_ _item_examples.case '1' '2' _item_linked.child_name '_struct_conn.pdbx_ptnr3_PDB_ins_code' _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' _item_aliases.alias_name '_struct_conn.ndb_ptnr3_label_ins_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_conn.pdbx_ptnr3_auth_seq_id _item_description.description ; A component of the identifier for partner 1 of the structure connection. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_struct_conn.pdbx_ptnr3_auth_seq_id' _item.category_id struct_conn _item.mandatory_code no _item_type.code code _item_examples.case '12' _item_linked.child_name '_struct_conn.pdbx_ptnr3_auth_seq_id' _item_linked.parent_name '_atom_site.auth_seq_id' _item_aliases.alias_name '_struct_conn.ndb_ptnr3_auth_seq_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## save__struct_conn.pdbx_ptnr3_label_alt_id _item_description.description ; A component of the identifier for partner 3 of the structure connection. This data item is a pointer to _atom_site.label_alt_id in the ATOM_SITE category. ; _item.name '_struct_conn.pdbx_ptnr3_label_alt_id' _item.category_id struct_conn _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'A' 'B' _item_linked.child_name '_struct_conn.pdbx_ptnr3_label_alt_id' _item_linked.parent_name '_atom_site.label_alt_id' _item_aliases.alias_name '_struct_conn.ndb_ptnr3_label_alt_loc' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_conn.pdbx_ptnr3_label_asym_id _item_description.description ; A component of the identifier for partner 3 of the structure connection. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_struct_conn.pdbx_ptnr3_label_asym_id' _item.category_id struct_conn _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'A' 'B' 'C' _item_linked.child_name '_struct_conn.pdbx_ptnr3_label_asym_id' _item_linked.parent_name '_atom_site.label_asym_id' _item_aliases.alias_name '_struct_conn.ndb_ptnr3_label_asym_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_conn.pdbx_ptnr3_label_atom_id _item_description.description ; A component of the identifier for partner 3 of the structure connection. This data item is a pointer to _atom_site.label_atom_id in the ATOM_SITE category. ; _item.name '_struct_conn.pdbx_ptnr3_label_atom_id' _item.category_id struct_conn _item.mandatory_code no _item_type.code atcode _item_examples.case 'O5*' _item_linked.child_name '_struct_conn.pdbx_ptnr3_label_atom_id' _item_linked.parent_name '_atom_site.label_atom_id' _item_aliases.alias_name '_struct_conn.ndb_ptnr3_label_atom_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_conn.pdbx_ptnr3_label_comp_id _item_description.description ; A component of the identifier for partner 3 of the structure connection. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_struct_conn.pdbx_ptnr3_label_comp_id' _item.category_id struct_conn _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'A' 'T' 'C' 'G' 'GLY' 'ALA' 'MET' _item_linked.child_name '_struct_conn.pdbx_ptnr3_label_comp_id' _item_linked.parent_name '_atom_site.label_comp_id' _item_aliases.alias_name '_struct_conn.ndb_ptnr3_label_comp_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_conn.pdbx_ptnr3_label_seq_id _item_description.description ; A component of the identifier for partner 1 of the structure connection. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_struct_conn.pdbx_ptnr3_label_seq_id' _item.category_id struct_conn _item.mandatory_code no _item_type.code code _item_examples.case '12' _item_linked.child_name '_struct_conn.pdbx_ptnr3_label_seq_id' _item_linked.parent_name '_atom_site.label_seq_id' _item_aliases.alias_name '_struct_conn.ndb_ptnr3_label_seq_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## save__struct_conn.pdbx_PDB_id _item_description.description ; A placeholder for the PDB id in the case the category is used to hold the information of the MODRES record of a PDB file. ; _item.name '_struct_conn.pdbx_PDB_id' _item.category_id struct_conn _item.mandatory_code no _item_type.code code _item_examples.case 1ABC _item_aliases.alias_name '_struct_conn.ndb_PDB_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ## save__struct_keywords.pdbx_keywords _item_description.description ; ; _item.name '_struct_keywords.pdbx_keywords' _item.category_id struct_keywords _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'DNA' 'RNA' 'T-RNA' 'DNA/RNA' 'RIBOZYME' 'PROTEIN/DNA' 'PROTEIN/RNA' 'PEPTIDE NUCLEIC ACID' 'PEPTIDE NUCLEIC ACID/DNA' 'DNA-BINDING PROTEIN' 'RNA-BINDING PROTEIN' _item_aliases.alias_name '_struct_keywords.ndb_keywords' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ## ## save__struct_mon_prot_cis.pdbx_auth_asym_id_2 _item_description.description ; Pointer to _atom_site.auth_asym_id. ; _item.name '_struct_mon_prot_cis.pdbx_auth_asym_id_2' _item.category_id struct_mon_prot_cis _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_mon_prot_cis.pdbx_auth_asym_id_2' _item_linked.parent_name '_atom_site.auth_asym_id' _item_aliases.alias_name '_struct_mon_prot_cis.ndb_auth_asym_id_2' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_mon_prot_cis.pdbx_auth_comp_id_2 _item_description.description ; Pointer to _atom_site.auth_comp_id. ; _item.name '_struct_mon_prot_cis.pdbx_auth_comp_id_2' _item.category_id struct_mon_prot_cis _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_mon_prot_cis.pdbx_auth_comp_id_2' _item_linked.parent_name '_atom_site.auth_comp_id' _item_aliases.alias_name '_struct_mon_prot_cis.ndb_auth_comp_id_2' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_mon_prot_cis.pdbx_auth_seq_id_2 _item_description.description ; Pointer to _atom_site.auth_seq_id ; _item.name '_struct_mon_prot_cis.pdbx_auth_seq_id_2' _item.category_id struct_mon_prot_cis _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_mon_prot_cis.pdbx_auth_seq_id_2' _item_linked.parent_name '_atom_site.auth_seq_id' _item_aliases.alias_name '_struct_mon_prot_cis.ndb_auth_seq_id_2' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ##jdw save__struct_mon_prot_cis.pdbx_label_asym_id_2 _item_description.description ; Pointer to _atom_site.label_asym_id. ; _item.name '_struct_mon_prot_cis.pdbx_label_asym_id_2' _item.category_id struct_mon_prot_cis _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_mon_prot_cis.pdbx_label_asym_id_2' _item_linked.parent_name '_atom_site.label_asym_id' _item_aliases.alias_name '_struct_mon_prot_cis.ndb_label_asym_id_2' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_mon_prot_cis.pdbx_label_comp_id_2 _item_description.description ; Pointer to _atom_site.label_comp_id. ; _item.name '_struct_mon_prot_cis.pdbx_label_comp_id_2' _item.category_id struct_mon_prot_cis _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_mon_prot_cis.pdbx_label_comp_id_2' _item_linked.parent_name '_atom_site.label_comp_id' _item_aliases.alias_name '_struct_mon_prot_cis.ndb_label_comp_id_2' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_mon_prot_cis.pdbx_label_seq_id_2 _item_description.description ; Pointer to _atom_site.label_seq_id ; _item.name '_struct_mon_prot_cis.pdbx_label_seq_id_2' _item.category_id struct_mon_prot_cis _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_mon_prot_cis.pdbx_label_seq_id_2' _item_linked.parent_name '_atom_site.label_seq_id' _item_aliases.alias_name '_struct_mon_prot_cis.ndb_label_seq_id_2' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_mon_prot_cis.pdbx_PDB_ins_code _item_description.description ; Pointer to _atom_site.pdbx_PDB_ins_code ; _item.name '_struct_mon_prot_cis.pdbx_PDB_ins_code' _item.category_id struct_mon_prot_cis _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_mon_prot_cis.pdbx_PDB_ins_code' _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' _item_aliases.alias_name '_struct_mon_prot_cis.ndb_label_ins_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_mon_prot_cis.pdbx_PDB_ins_code_2 _item_description.description ; Pointer to _atom_site.pdbx_PDB_ins_code ; _item.name '_struct_mon_prot_cis.pdbx_PDB_ins_code_2' _item.category_id struct_mon_prot_cis _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_mon_prot_cis.pdbx_PDB_ins_code_2' _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' _item_aliases.alias_name '_struct_mon_prot_cis.ndb_label_ins_code_2' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_mon_prot_cis.pdbx_PDB_model_num _item_description.description ; Pointer to _atom_site.pdbx_PDB_model_num ; _item.name '_struct_mon_prot_cis.pdbx_PDB_model_num' _item.category_id struct_mon_prot_cis _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_mon_prot_cis.pdbx_PDB_model_num' _item_linked.parent_name '_atom_site.pdbx_PDB_model_num' _item_aliases.alias_name '_struct_mon_prot_cis.ndb_model_num' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_mon_prot_cis.pdbx_omega_angle _item_description.description ; omega torsion angle ; _item.name '_struct_mon_prot_cis.pdbx_omega_angle' _item.category_id struct_mon_prot_cis _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_struct_mon_prot_cis.ndb_omega_angle' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_mon_prot_cis.pdbx_id _item_description.description ; ordinal index ; _item.name '_struct_mon_prot_cis.pdbx_id' _item.category_id struct_mon_prot_cis _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_struct_mon_prot_cis.id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ## save__struct_ref.pdbx_db_accession _item_description.description ; Accession code of the reference database. ; _item.name '_struct_ref.pdbx_db_accession' _item.category_id struct_ref _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'P07617' _item_aliases.alias_name '_struct_ref.rcsb_db_accession' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_ref.pdbx_seq_one_letter_code _item_description.description ; Database chemical sequence expressed as string of one-letter amino acid codes. ; _item.name '_struct_ref.pdbx_seq_one_letter_code' _item.category_id struct_ref _item.mandatory_code no _item_type.code text _item_examples.case ; A for alanine or adenine B for ambiguous asparagine/aspartic-acid R for arginine N for asparagine D for aspartic-acid C for cysteine or cystine or cytosine Q for glutamine E for glutamic-acid Z for ambiguous glutamine/glutamic acid G for glycine or guanine H for histidine I for isoleucine L for leucine K for lysine M for methionine F for phenylalanine P for proline S for serine T for threonine or thymine W for tryptophan Y for tyrosine V for valine U for uracil O for water X for other ; _item_aliases.alias_name '_struct_ref.rcsb_seq_one_letter_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_ref.pdbx_align_begin _item_description.description ; Beginning index in the chemical sequence from the reference database. ; _item.name '_struct_ref.pdbx_align_begin' _item.category_id struct_ref _item.mandatory_code no _item_type.code code loop_ _item_examples.case '1' '2' _item_aliases.alias_name '_struct_ref.rcsb_align_begin' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ## save__struct_ref_seq.pdbx_strand_id _item_description.description ; The PDB strand/chain ID . ; _item.name '_struct_ref_seq.pdbx_strand_id' _item.category_id struct_ref_seq _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'A' 'B' _item_aliases.alias_name '_struct_ref_seq.ndb_chain_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_ref_seq.pdbx_db_accession _item_description.description ; Accession code of the reference database. ; _item.name '_struct_ref_seq.pdbx_db_accession' _item.category_id struct_ref_seq _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'P07617' _item_aliases.alias_name '_struct_ref_seq.ndb_db_accession' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_ref_seq.pdbx_db_align_beg_ins_code _item_description.description ; Initial insertion code of the sequence segment of the reference database. ; _item.name '_struct_ref_seq.pdbx_db_align_beg_ins_code' _item.category_id struct_ref_seq _item.mandatory_code no _item_type.code code loop_ _item_examples.case '1' '2' _item_aliases.alias_name '_struct_ref_seq.ndb_db_align_beg_ins_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_ref_seq.pdbx_db_align_end_ins_code _item_description.description ; Ending insertion code of the sequence segment of the reference database. ; _item.name '_struct_ref_seq.pdbx_db_align_end_ins_code' _item.category_id struct_ref_seq _item.mandatory_code no _item_type.code code loop_ _item_examples.case '1' '2' _item_aliases.alias_name '_struct_ref_seq.ndb_db_align_end_ins_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_ref_seq.pdbx_PDB_id_code _item_description.description ; The PDB code of the structure. ; _item.name '_struct_ref_seq.pdbx_PDB_id_code' _item.category_id struct_ref_seq _item.mandatory_code no _item_type.code code _item_examples.case '1BBP' _item_aliases.alias_name '_struct_ref_seq.ndb_pdb_id_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_ref_seq.pdbx_auth_seq_align_beg _item_description.description ; Initial position in the PDB sequence segment. ; _item.name '_struct_ref_seq.pdbx_auth_seq_align_beg' _item.category_id struct_ref_seq _item.mandatory_code no _item_type.code code loop_ _item_examples.case '1' '2' _item_aliases.alias_name '_struct_ref_seq.ndb_auth_seq_align_beg' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_ref_seq.pdbx_auth_seq_align_end _item_description.description ; Ending position in the PDB sequence segment ; _item.name '_struct_ref_seq.pdbx_auth_seq_align_end' _item.category_id struct_ref_seq _item.mandatory_code no _item_type.code code loop_ _item_examples.case '1' '2' _item_aliases.alias_name '_struct_ref_seq.ndb_auth_seq_align_end' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## save__struct_ref_seq.pdbx_seq_align_beg_ins_code _item_description.description ; Initial insertion code of the PDB sequence segment. ; _item.name '_struct_ref_seq.pdbx_seq_align_beg_ins_code' _item.category_id struct_ref_seq _item.mandatory_code no _item_type.code code loop_ _item_examples.case '1' '2' _item_aliases.alias_name '_struct_ref_seq.ndb_seq_align_beg_ins_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_ref_seq.pdbx_seq_align_end_ins_code _item_description.description ; Ending insertion code of the sequence segment ; _item.name '_struct_ref_seq.pdbx_seq_align_end_ins_code' _item.category_id struct_ref_seq _item.mandatory_code no _item_type.code code loop_ _item_examples.case '1' '2' _item_aliases.alias_name '_struct_ref_seq.ndb_seq_align_end_ins_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ## save__struct_ref_seq_dif.pdbx_pdb_id_code _item_description.description ; The PDB ID code. ; _item.name '_struct_ref_seq_dif.pdbx_pdb_id_code' _item.category_id struct_ref_seq_dif _item.mandatory_code no _item_type.code code _item_examples.case '1BBP' _item_aliases.alias_name '_struct_ref_seq_dif.ndb_pdb_id_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_ref_seq_dif.pdbx_pdb_strand_id _item_description.description ; PDB strand/chain id. ; _item.name '_struct_ref_seq_dif.pdbx_pdb_strand_id' _item.category_id struct_ref_seq_dif _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'A' 'B' _item_aliases.alias_name '_struct_ref_seq_dif.ndb_pdb_chain_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_ref_seq_dif.pdbx_pdb_ins_code _item_description.description ; Insertion code in PDB sequence ; _item.name '_struct_ref_seq_dif.pdbx_pdb_ins_code' _item.category_id struct_ref_seq_dif _item.mandatory_code no _item_type.code code loop_ _item_examples.case '1' '2' _item_aliases.alias_name '_struct_ref_seq_dif.ndb_pdb_ins_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_ref_seq_dif.pdbx_auth_seq_num _item_description.description ; Insertion code in PDB sequence ; _item.name '_struct_ref_seq_dif.pdbx_auth_seq_num' _item.category_id struct_ref_seq_dif _item.mandatory_code no _item_type.code code loop_ _item_examples.case '1' '2' _item_aliases.alias_name '_struct_ref_seq_dif.ndb_auth_seq_num' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_ref_seq_dif.pdbx_seq_db_name _item_description.description ; Sequence database name. ; _item.name '_struct_ref_seq_dif.pdbx_seq_db_name' _item.category_id struct_ref_seq_dif _item.mandatory_code no _item_type.code code _item_examples.case 'SWS' _item_aliases.alias_name '_struct_ref_seq_dif.ndb_seq_db_name' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_ref_seq_dif.pdbx_seq_db_accession_code _item_description.description ; Sequence database accession number. ; _item.name '_struct_ref_seq_dif.pdbx_seq_db_accession_code' _item.category_id struct_ref_seq_dif _item.mandatory_code no _item_type.code code _item_examples.case 'P07617' _item_aliases.alias_name '_struct_ref_seq_dif.ndb_seq_db_accession_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_ref_seq_dif.pdbx_seq_db_seq_num _item_description.description ; Sequence database sequence number. ; _item.name '_struct_ref_seq_dif.pdbx_seq_db_seq_num' _item.category_id struct_ref_seq_dif _item.mandatory_code no _item_type.code code _item_examples.case '142' _item_aliases.alias_name '_struct_ref_seq_dif.ndb_seq_db_seq_num' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ## save__struct_sheet_range.pdbx_beg_PDB_ins_code _item_description.description ; A component of the identifier for the residue at which the beta sheet range begins. Insertion code. ; _item.name '_struct_sheet_range.pdbx_beg_PDB_ins_code' _item.category_id struct_sheet_range _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_sheet_range.pdbx_beg_PDB_ins_code' _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' _item_aliases.alias_name '_struct_sheet_range.ndb_beg_label_ins_code_pdb' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_sheet_range.pdbx_end_PDB_ins_code _item_description.description ; A component of the identifier for the residue at which the beta sheet range ends. Insertion code. ; _item.name '_struct_sheet_range.pdbx_end_PDB_ins_code' _item.category_id struct_sheet_range _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_sheet_range.pdbx_end_PDB_ins_code' _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' _item_aliases.alias_name '_struct_sheet_range.ndb_end_label_ins_code_pdb' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ## save__struct_sheet_hbond.pdbx_range_1_beg_auth_comp_id _item_description.description ; Pointer to _atom_site.auth_comp_id ; _item.name '_struct_sheet_hbond.pdbx_range_1_beg_auth_comp_id' _item.category_id struct_sheet_hbond _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_sheet_hbond.pdbx_range_1_beg_auth_comp_id' _item_linked.parent_name '_atom_site.auth_comp_id' _item_aliases.alias_name '_struct_sheet_hbond.ndb_range_1_beg_auth_comp_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_sheet_hbond.pdbx_range_1_beg_auth_asym_id _item_description.description ; Pointer to _atom_site.auth_asym_id. ; _item.name '_struct_sheet_hbond.pdbx_range_1_beg_auth_asym_id' _item.category_id struct_sheet_hbond _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_sheet_hbond.pdbx_range_1_beg_auth_asym_id' _item_linked.parent_name '_atom_site.auth_asym_id' _item_aliases.alias_name '_struct_sheet_hbond.ndb_range_1_beg_auth_asym_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_sheet_hbond.pdbx_range_1_end_auth_comp_id _item_description.description ; Pointer to _atom_site.auth_comp_id. ; _item.name '_struct_sheet_hbond.pdbx_range_1_end_auth_comp_id' _item.category_id struct_sheet_hbond _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_sheet_hbond.pdbx_range_1_end_auth_comp_id' _item_linked.parent_name '_atom_site.auth_comp_id' _item_aliases.alias_name '_struct_sheet_hbond.ndb_range_1_end_auth_comp_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_sheet_hbond.pdbx_range_1_end_auth_asym_id _item_description.description ; Pointer to _atom_site.auth_comp_id. ; _item.name '_struct_sheet_hbond.pdbx_range_1_end_auth_asym_id' _item.category_id struct_sheet_hbond _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_sheet_hbond.pdbx_range_1_end_auth_asym_id' _item_linked.parent_name '_atom_site.auth_asym_id' _item_aliases.alias_name '_struct_sheet_hbond.ndb_range_1_end_auth_asym_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_sheet_hbond.pdbx_range_1_beg_label_comp_id _item_description.description ; Pointer to _atom_site.label_comp_id ; _item.name '_struct_sheet_hbond.pdbx_range_1_beg_label_comp_id' _item.category_id struct_sheet_hbond _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_sheet_hbond.pdbx_range_1_beg_label_comp_id' _item_linked.parent_name '_atom_site.label_comp_id' _item_aliases.alias_name '_struct_sheet_hbond.ndb_range_1_beg_label_comp_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_sheet_hbond.pdbx_range_1_beg_label_asym_id _item_description.description ; Pointer to _atom_site.label_asym_id. ; _item.name '_struct_sheet_hbond.pdbx_range_1_beg_label_asym_id' _item.category_id struct_sheet_hbond _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_sheet_hbond.pdbx_range_1_beg_label_asym_id' _item_linked.parent_name '_atom_site.label_asym_id' _item_aliases.alias_name '_struct_sheet_hbond.ndb_range_1_beg_label_asym_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_sheet_hbond.pdbx_range_1_beg_PDB_ins_code _item_description.description ; Pointer to _atom_site.pdbx_PDB_ins_code. ; _item.name '_struct_sheet_hbond.pdbx_range_1_beg_PDB_ins_code' _item.category_id struct_sheet_hbond _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_sheet_hbond.pdbx_range_1_beg_PDB_ins_code' _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' _item_aliases.alias_name '_struct_sheet_hbond.ndb_range_1_beg_label_ins_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_sheet_hbond.pdbx_range_1_end_label_comp_id _item_description.description ; Pointer to _atom_site.label_comp_id. ; _item.name '_struct_sheet_hbond.pdbx_range_1_end_label_comp_id' _item.category_id struct_sheet_hbond _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_sheet_hbond.pdbx_range_1_end_label_comp_id' _item_linked.parent_name '_atom_site.label_comp_id' _item_aliases.alias_name '_struct_sheet_hbond.ndb_range_1_end_label_comp_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_sheet_hbond.pdbx_range_1_end_label_asym_id _item_description.description ; Pointer to _atom_site.label_asym_id. ; _item.name '_struct_sheet_hbond.pdbx_range_1_end_label_asym_id' _item.category_id struct_sheet_hbond _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_sheet_hbond.pdbx_range_1_end_label_asym_id' _item_linked.parent_name '_atom_site.label_asym_id' _item_aliases.alias_name '_struct_sheet_hbond.ndb_range_1_end_label_asym_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_sheet_hbond.pdbx_range_1_end_PDB_ins_code _item_description.description ; Pointer to _atom_site.pdbx_PDB_ins_code. ; _item.name '_struct_sheet_hbond.pdbx_range_1_end_PDB_ins_code' _item.category_id struct_sheet_hbond _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_sheet_hbond.pdbx_range_1_end_PDB_ins_code' _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' _item_aliases.alias_name '_struct_sheet_hbond.ndb_range_1_end_label_ins_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_sheet_hbond.pdbx_range_2_beg_label_comp_id _item_description.description ; Pointer to _atom_site.label_comp_id. ; _item.name '_struct_sheet_hbond.pdbx_range_2_beg_label_comp_id' _item.category_id struct_sheet_hbond _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_sheet_hbond.pdbx_range_2_beg_label_comp_id' _item_linked.parent_name '_atom_site.label_comp_id' _item_aliases.alias_name '_struct_sheet_hbond.ndb_range_2_beg_label_comp_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_sheet_hbond.pdbx_range_2_beg_label_asym_id _item_description.description ; Pointer to _atom_site.label_asym_id. ; _item.name '_struct_sheet_hbond.pdbx_range_2_beg_label_asym_id' _item.category_id struct_sheet_hbond _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_sheet_hbond.pdbx_range_2_beg_label_asym_id' _item_linked.parent_name '_atom_site.label_asym_id' _item_aliases.alias_name '_struct_sheet_hbond.ndb_range_2_beg_label_asym_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_sheet_hbond.pdbx_range_2_beg_PDB_ins_code _item_description.description ; Pointer to _atom_site.pdbx_PDB_ins_code. ; _item.name '_struct_sheet_hbond.pdbx_range_2_beg_PDB_ins_code' _item.category_id struct_sheet_hbond _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_sheet_hbond.pdbx_range_2_beg_PDB_ins_code' _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' _item_aliases.alias_name '_struct_sheet_hbond.ndb_range_2_beg_label_ins_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_sheet_hbond.pdbx_range_2_end_label_comp_id _item_description.description ; Pointer to _atom_site.label_comp_id. ; _item.name '_struct_sheet_hbond.pdbx_range_2_end_label_comp_id' _item.category_id struct_sheet_hbond _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_sheet_hbond.pdbx_range_2_end_label_comp_id' _item_linked.parent_name '_atom_site.label_comp_id' _item_aliases.alias_name '_struct_sheet_hbond.ndb_range_2_end_label_comp_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_sheet_hbond.pdbx_range_2_end_label_asym_id _item_description.description ; Pointer to _atom_site.label_asym_id. ; _item.name '_struct_sheet_hbond.pdbx_range_2_end_label_asym_id' _item.category_id struct_sheet_hbond _item.mandatory_code no _item_type.code code _item_linked.child_name '_struct_sheet_hbond.pdbx_range_2_end_label_asym_id' _item_linked.parent_name '_atom_site.label_asym_id' _item_aliases.alias_name '_struct_sheet_hbond.ndb_range_2_end_label_asym_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_sheet_hbond.pdbx_range_2_end_label_ins_code _item_description.description ; Place holder for PDB insertion code. ; _item.name '_struct_sheet_hbond.pdbx_range_2_end_label_ins_code' _item.category_id struct_sheet_hbond _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_struct_sheet_hbond.ndb_range_2_end_label_ins_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ## ## save__struct_site.pdbx_num_residues _item_description.description ; Number of residues in the site. ; _item.name '_struct_site.pdbx_num_residues' _item.category_id struct_site _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_struct_site.rcsb_num_residues' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_site_gen.pdbx_auth_ins_code _item_description.description ; PDB insertion code. ; _item.name '_struct_site_gen.pdbx_auth_ins_code' _item.category_id struct_site_gen _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_struct_site_gen.ndb_ins_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_site_gen.pdbx_num_res _item_description.description ; Number of residues in the site. ; _item.name '_struct_site_gen.pdbx_num_res' _item.category_id struct_site_gen _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_struct_site_gen.ndb_num_res' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ## save__symmetry.pdbx_full_space_group_name_H-M _item_description.description ; Used for PDB space group: Example: 'C 1 2 1' (instead of C 2) 'P 1 2 1' (instead of P 2) 'P 1 21 1' (instead of P 21) 'P 1 1 21' (instead of P 21 -unique C axis) 'H 3' (instead of R 3 -hexagonal) 'H 3 2' (instead of R 3 2 -hexagonal) ; _item.name '_symmetry.pdbx_full_space_group_name_H-M' _item.category_id symmetry _item.mandatory_code no _item_type.code line _item_examples.case ; Example: 'C 1 2 1' (instead of C 2) 'P 1 2 1' (instead of P 2) 'P 1 21 1' (instead of P 21) 'P 1 1 21' (instead of P 21 -unique C axis) 'H 3' (instead of R 3 -hexagonal) 'H 3 2' (instead of R 3 2 -hexagonal) ; _item_aliases.alias_name '_symmetry.ndb_full_space_group_name_H-M' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ## save__refine.pdbx_overall_ESU_R _item_description.description ; Overall estimated standard uncertainties of positional parameters based on R value. ; _item.name '_refine.pdbx_overall_ESU_R' _item.category_id refine _item.mandatory_code no _item_aliases.alias_name '_refine.ebi_overall_ESU_R' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 _item_type.code float save_ save__refine.pdbx_overall_ESU_R_Free _item_description.description ; Overall estimated standard uncertainties of positional parameters based on R value. ; _item.name '_refine.pdbx_overall_ESU_R_Free' _item.category_id refine _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_refine.rcsb_overall_ESU_R_Free' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### ### save_pdbx_refine_tls _category.description ; Data items in the REFINE_TLS category record details about TLS parameters used in structure refinement. Note that the intention is primarily to describe directly refined TLS parameters, although other methods of obtaining TLS parameters may be covered, see item _pdbx_refine_tls.method ; _category.id pdbx_refine_tls _category.mandatory_code no loop_ _category_key.name '_pdbx_refine_tls.id' loop_ _category_group.id 'inclusive_group' 'refine_group' 'ccp4_group' save_ save__pdbx_refine_tls.id _item_description.description ; The value of _pdbx_refine_tls.id must uniquely identify a record in the PDBX_REFINE_TLS list. Note that this item need not be a number; it can be any unique identifier. ; _item.name '_pdbx_refine_tls.id' _item.category_id pdbx_refine_tls _item.mandatory_code yes loop_ _item_linked.child_name _item_linked.parent_name '_pdbx_refine_tls_group.refine_tls_id' '_pdbx_refine_tls.id' _item_type.code code loop_ _item_examples.case 1 A loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.id' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.id' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.details _item_description.description ; A description of the TLS group, such as a domain name or a chemical group name. ; _item.name '_pdbx_refine_tls.details' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'Chain A catalytic domain' 'Chain A Tyr 56 side chain' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.details' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.details' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.method _item_description.description ; The method by which the TLS parameters were obtained. ; _item.name '_pdbx_refine_tls.method' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail refined ; TLS parameters refined directly against crystallographic residual ; fitted ; TLS parameters fitted to previously refined anisotropic displacement parameters ; loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.method' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.method' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.origin_x _item_description.description ; The x coordinate in angstroms of the origin to which the TLS parameters are referred, specified according to a set of orthogonal Cartesian axes related to the cell axes as given in _atom_sites.Cartn_transform_axes. If the origin is omitted, it is assumed to be the centre of reaction of the group, in which case S must be symmetric ; _item.name '_pdbx_refine_tls.origin_x' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float _item_units.code angstroms loop_ _item_dependent.dependent_name '_pdbx_refine_tls.origin_y' '_pdbx_refine_tls.origin_z' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.origin_x' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.origin_x' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.origin_y _item_description.description ; The y coordinate in angstroms of the origin to which the TLS parameters are referred, specified according to a set of orthogonal Cartesian axes related to the cell axes as given in _atom_sites.Cartn_transform_axes. If the origin is omitted, it is assumed to be the centre of reaction of the group, in which case S must be symmetric ; _item.name '_pdbx_refine_tls.origin_y' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float _item_units.code angstroms loop_ _item_dependent.dependent_name '_pdbx_refine_tls.origin_x' '_pdbx_refine_tls.origin_z' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.origin_y' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.origin_y' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.origin_z _item_description.description ; The z coordinate in angstroms of the origin to which the TLS parameters are referred, specified according to a set of orthogonal Cartesian axes related to the cell axes as given in _atom_sites.Cartn_transform_axes. If the origin is omitted, it is assumed to be the centre of reaction of the group, in which case S must be symmetric ; _item.name '_pdbx_refine_tls.origin_z' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float _item_units.code angstroms loop_ _item_dependent.dependent_name '_pdbx_refine_tls.origin_x' '_pdbx_refine_tls.origin_y' loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.origin_z' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.origin_z' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.T[1][1] _item_description.description ; The [1][1] element of the translation tensor T. This should be given in the same coordinate frame and units as the corresponding anisotropic displacement parameters. ; _item.name '_pdbx_refine_tls.T[1][1]' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.T[1][1]_esd' associated_esd _item_units.code angstroms_squared _item_type_conditions.code esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.T[1][1]' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.T[1][1]' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.T[1][1]_esd _item_description.description ; The estimated standard deviation of _pdbx_refine_tls.T[1][1]. ; _item.name '_pdbx_refine_tls.T[1][1]_esd' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.T[1][1]' associated_value _item_units.code angstroms_squared loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.T[1][1]_esd' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.T[1][1]_esd' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.T[1][2] _item_description.description ; The [1][2] element of the translation tensor T. This should be given in the same coordinate frame and units as the corresponding anisotropic displacement parameters. ; _item.name '_pdbx_refine_tls.T[1][2]' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.T[1][2]_esd' associated_esd _item_units.code angstroms_squared _item_type_conditions.code esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.T[1][2]' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.T[1][2]' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.T[1][2]_esd _item_description.description ; The estimated standard deviation of _pdbx_refine_tls.T[1][2]. ; _item.name '_pdbx_refine_tls.T[1][2]_esd' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.T[1][2]' associated_value _item_units.code angstroms_squared loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.T[1][2]_esd' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.T[1][2]_esd' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.T[1][3] _item_description.description ; The [1][3] element of the translation tensor T. This should be given in the same coordinate frame and units as the corresponding anisotropic displacement parameters. ; _item.name '_pdbx_refine_tls.T[1][3]' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.T[1][3]_esd' associated_esd _item_units.code angstroms_squared _item_type_conditions.code esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.T[1][3]' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.T[1][3]' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.T[1][3]_esd _item_description.description ; The estimated standard deviation of _pdbx_refine_tls.T[1][3]. ; _item.name '_pdbx_refine_tls.T[1][3]_esd' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.T[1][3]' associated_value _item_units.code angstroms_squared loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.T[1][3]_esd' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.T[1][3]_esd' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.T[2][2] _item_description.description ; The [2][2] element of the translation tensor T. This should be given in the same coordinate frame and units as the corresponding anisotropic displacement parameters. ; _item.name '_pdbx_refine_tls.T[2][2]' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.T[2][2]_esd' associated_esd _item_units.code angstroms_squared _item_type_conditions.code esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.T[2][2]' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.T[2][2]' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.T[2][2]_esd _item_description.description ; The estimated standard deviation of _pdbx_refine_tls.T[2][2]. ; _item.name '_pdbx_refine_tls.T[2][2]_esd' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.T[2][2]' associated_value _item_units.code angstroms_squared loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.T[2][2]_esd' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.T[2][2]_esd' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.T[2][3] _item_description.description ; The [2][3] element of the translation tensor T. This should be given in the same coordinate frame and units as the corresponding anisotropic displacement parameters. ; _item.name '_pdbx_refine_tls.T[2][3]' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.T[2][3]_esd' associated_esd _item_units.code angstroms_squared _item_type_conditions.code esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.T[2][3]' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.T[2][3]' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.T[2][3]_esd _item_description.description ; The estimated standard deviation of _pdbx_refine_tls.T[2][3]. ; _item.name '_pdbx_refine_tls.T[2][3]_esd' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.T[2][3]' associated_value _item_units.code angstroms_squared loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.T[2][3]_esd' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.T[2][3]_esd' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.T[3][3] _item_description.description ; The [3][3] element of the translation tensor T. This should be given in the same coordinate frame and units as the corresponding anisotropic displacement parameters. ; _item.name '_pdbx_refine_tls.T[3][3]' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.T[3][3]_esd' associated_esd _item_units.code angstroms_squared _item_type_conditions.code esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.T[3][3]' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.T[3][3]' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.T[3][3]_esd _item_description.description ; The estimated standard deviation of _pdbx_refine_tls.T[3][3]. ; _item.name '_pdbx_refine_tls.T[3][3]_esd' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.T[3][3]' associated_value _item_units.code angstroms_squared loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.T[3][3]_esd' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.T[3][3]_esd' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.L[1][1] _item_description.description ; The [1][1] element of the libration tensor L. This should be given in the same coordinate frame as the corresponding anisotropic displacement parameters. ; _item.name '_pdbx_refine_tls.L[1][1]' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.L[1][1]_esd' associated_esd _item_units.code degrees_squared _item_type_conditions.code esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.L[1][1]' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.L[1][1]' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.L[1][1]_esd _item_description.description ; The estimated standard deviation of _pdbx_refine_tls.L[1][1]. ; _item.name '_pdbx_refine_tls.L[1][1]_esd' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.L[1][1]' associated_value _item_units.code degrees_squared loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.L[1][1]_esd' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.L[1][1]_esd' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.L[1][2] _item_description.description ; The [1][2] element of the libration tensor L. This should be given in the same coordinate frame as the corresponding anisotropic displacement parameters. ; _item.name '_pdbx_refine_tls.L[1][2]' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.L[1][2]_esd' associated_esd _item_units.code degrees_squared _item_type_conditions.code esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.L[1][2]' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.L[1][2]' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.L[1][2]_esd _item_description.description ; The estimated standard deviation of _pdbx_refine_tls.L[1][2]. ; _item.name '_pdbx_refine_tls.L[1][2]_esd' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.L[1][2]' associated_value _item_units.code degrees_squared loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.L[1][2]_esd' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.L[1][2]_esd' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.L[1][3] _item_description.description ; The [1][3] element of the libration tensor L. This should be given in the same coordinate frame as the corresponding anisotropic displacement parameters. ; _item.name '_pdbx_refine_tls.L[1][3]' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.L[1][3]_esd' associated_esd _item_units.code degrees_squared _item_type_conditions.code esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.L[1][3]' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.L[1][3]' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.L[1][3]_esd _item_description.description ; The estimated standard deviation of _pdbx_refine_tls.L[1][3]. ; _item.name '_pdbx_refine_tls.L[1][3]_esd' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.L[1][3]' associated_value _item_units.code degrees_squared loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.L[1][3]_esd' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.L[1][3]_esd' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.L[2][2] _item_description.description ; The [2][2] element of the libration tensor L. This should be given in the same coordinate frame as the corresponding anisotropic displacement parameters. ; _item.name '_pdbx_refine_tls.L[2][2]' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.L[2][2]_esd' associated_esd _item_units.code degrees_squared _item_type_conditions.code esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.L[2][2]' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.L[2][2]' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.L[2][2]_esd _item_description.description ; The estimated standard deviation of _pdbx_refine_tls.L[2][2]. ; _item.name '_pdbx_refine_tls.L[2][2]_esd' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.L[2][2]' associated_value _item_units.code degrees_squared loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.L[2][2]_esd' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.L[2][2]_esd' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.L[2][3] _item_description.description ; The [2][3] element of the libration tensor L. This should be given in the same coordinate frame as the corresponding anisotropic displacement parameters. ; _item.name '_pdbx_refine_tls.L[2][3]' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.L[2][3]_esd' associated_esd _item_units.code degrees_squared _item_type_conditions.code esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.L[2][3]' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.L[2][3]' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.L[2][3]_esd _item_description.description ; The estimated standard deviation of _pdbx_refine_tls.L[2][3]. ; _item.name '_pdbx_refine_tls.L[2][3]_esd' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.L[2][3]' associated_value _item_units.code degrees_squared loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.L[2][3]_esd' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.L[2][3]_esd' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.L[3][3] _item_description.description ; The [3][3] element of the libration tensor L. This should be given in the same coordinate frame as the corresponding anisotropic displacement parameters. ; _item.name '_pdbx_refine_tls.L[3][3]' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.L[3][3]_esd' associated_esd _item_units.code degrees_squared _item_type_conditions.code esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.L[3][3]' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.L[3][3]' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.L[3][3]_esd _item_description.description ; The estimated standard deviation of _pdbx_refine_tls.L[3][3]. ; _item.name '_pdbx_refine_tls.L[3][3]_esd' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.L[3][3]' associated_value _item_units.code degrees_squared loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.L[3][3]_esd' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.L[3][3]_esd' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.S[1][1] _item_description.description ; The [1][1] element of the screw-rotation tensor S. This should be given in the same coordinate frame as the corresponding anisotropic displacement parameters. The trace of S is indeterminate by crystallography, and should be set to zero. ; _item.name '_pdbx_refine_tls.S[1][1]' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.S[1][1]_esd' associated_esd _item_units.code angstroms_degrees _item_type_conditions.code esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.S[1][1]' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.S[1][1]' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.S[1][1]_esd _item_description.description ; The estimated standard deviation of _pdbx_refine_tls.S[1][1]. ; _item.name '_pdbx_refine_tls.S[1][1]_esd' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.S[1][1]' associated_value _item_units.code angstroms_degrees loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.S[1][1]_esd' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.S[1][1]_esd' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.S[1][2] _item_description.description ; The [1][2] element of the screw-rotation tensor S. This should be given in the same coordinate frame as the corresponding anisotropic displacement parameters. If the origin is omitted, it is assumed to be the centre of reaction of the group, in which case S must be symmetric ; _item.name '_pdbx_refine_tls.S[1][2]' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.S[1][2]_esd' associated_esd _item_units.code angstroms_degrees _item_type_conditions.code esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.S[1][2]' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.S[1][2]' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.S[1][2]_esd _item_description.description ; The estimated standard deviation of _pdbx_refine_tls.S[1][2]. ; _item.name '_pdbx_refine_tls.S[1][2]_esd' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.S[1][2]' associated_value _item_units.code angstroms_degrees loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.S[1][2]_esd' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.S[1][2]_esd' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.S[1][3] _item_description.description ; The [1][3] element of the screw-rotation tensor S. This should be given in the same coordinate frame as the corresponding anisotropic displacement parameters. If the origin is omitted, it is assumed to be the centre of reaction of the group, in which case S must be symmetric ; _item.name '_pdbx_refine_tls.S[1][3]' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.S[1][3]_esd' associated_esd _item_units.code angstroms_degrees _item_type_conditions.code esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.S[1][3]' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.S[1][3]' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.S[1][3]_esd _item_description.description ; The estimated standard deviation of _pdbx_refine_tls.S[1][3]. ; _item.name '_pdbx_refine_tls.S[1][3]_esd' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.S[1][3]' associated_value _item_units.code angstroms_degrees loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.S[1][3]_esd' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.S[1][3]_esd' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.S[2][1] _item_description.description ; The [2][1] element of the screw-rotation tensor S. This should be given in the same coordinate frame as the corresponding anisotropic displacement parameters. If the origin is omitted, it is assumed to be the centre of reaction of the group, in which case S must be symmetric ; _item.name '_pdbx_refine_tls.S[2][1]' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.S[2][1]_esd' associated_esd _item_units.code angstroms_degrees _item_type_conditions.code esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.S[2][1]' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.S[2][1]' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.S[2][1]_esd _item_description.description ; The estimated standard deviation of _pdbx_refine_tls.S[2][1]. ; _item.name '_pdbx_refine_tls.S[2][1]_esd' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.S[2][1]' associated_value _item_units.code angstroms_degrees loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.S[2][1]_esd' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.S[2][1]_esd' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.S[2][2] _item_description.description ; The [2][2] element of the screw-rotation tensor S. This should be given in the same coordinate frame as the corresponding anisotropic displacement parameters. The trace of S is indeterminate by crystallography, and should be set to zero. ; _item.name '_pdbx_refine_tls.S[2][2]' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.S[2][2]_esd' associated_esd _item_units.code angstroms_degrees _item_type_conditions.code esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.S[2][2]' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.S[2][2]' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.S[2][2]_esd _item_description.description ; The estimated standard deviation of _pdbx_refine_tls.S[2][2]. ; _item.name '_pdbx_refine_tls.S[2][2]_esd' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.S[2][2]' associated_value _item_units.code angstroms_degrees loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.S[2][2]_esd' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.S[2][2]_esd' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.S[2][3] _item_description.description ; The [2][3] element of the screw-rotation tensor S. This should be given in the same coordinate frame as the corresponding anisotropic displacement parameters. If the origin is omitted, it is assumed to be the centre of reaction of the group, in which case S must be symmetric ; _item.name '_pdbx_refine_tls.S[2][3]' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.S[2][3]_esd' associated_esd _item_units.code angstroms_degrees _item_type_conditions.code esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.S[2][3]' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.S[2][3]' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.S[2][3]_esd _item_description.description ; The estimated standard deviation of _pdbx_refine_tls.S[2][3]. ; _item.name '_pdbx_refine_tls.S[2][3]_esd' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.S[2][3]' associated_value _item_units.code angstroms_degrees loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.S[2][3]_esd' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.S[2][3]_esd' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.S[3][1] _item_description.description ; The [3][1] element of the screw-rotation tensor S. This should be given in the same coordinate frame as the corresponding anisotropic displacement parameters. If the origin is omitted, it is assumed to be the centre of reaction of the group, in which case S must be symmetric ; _item.name '_pdbx_refine_tls.S[3][1]' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.S[3][1]_esd' associated_esd _item_units.code angstroms_degrees _item_type_conditions.code esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.S[3][1]' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.S[3][1]' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.S[3][1]_esd _item_description.description ; The estimated standard deviation of _pdbx_refine_tls.S[3][1]. ; _item.name '_pdbx_refine_tls.S[3][1]_esd' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.S[3][1]' associated_value _item_units.code angstroms_degrees loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.S[3][1]_esd' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.S[3][1]_esd' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.S[3][2] _item_description.description ; The [3][2] element of the screw-rotation tensor S. This should be given in the same coordinate frame as the corresponding anisotropic displacement parameters. If the origin is omitted, it is assumed to be the centre of reaction of the group, in which case S must be symmetric ; _item.name '_pdbx_refine_tls.S[3][2]' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.S[3][2]_esd' associated_esd _item_units.code angstroms_degrees _item_type_conditions.code esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.S[3][2]' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.S[3][2]' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.S[3][2]_esd _item_description.description ; The estimated standard deviation of _pdbx_refine_tls.S[3][2]. ; _item.name '_pdbx_refine_tls.S[3][2]_esd' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.S[3][2]' associated_value _item_units.code angstroms_degrees loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.S[3][2]_esd' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.S[3][2]_esd' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.S[3][3] _item_description.description ; The [3][3] element of the screw-rotation tensor S. This should be given in the same coordinate frame as the corresponding anisotropic displacement parameters. The trace of S is indeterminate by crystallography, and should be set to zero. ; _item.name '_pdbx_refine_tls.S[3][3]' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.S[3][3]_esd' associated_esd _item_units.code angstroms_degrees _item_type_conditions.code esd loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.S[3][3]' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.S[3][3]' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls.S[3][3]_esd _item_description.description ; The estimated standard deviation of _pdbx_refine_tls.S[3][3]. ; _item.name '_pdbx_refine_tls.S[3][3]_esd' _item.category_id pdbx_refine_tls _item.mandatory_code no _item_type.code float _item_default.value 0.0 loop_ _item_related.related_name _item_related.function_code '_pdbx_refine_tls.S[3][3]' associated_value _item_units.code angstroms_degrees loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls.S[3][3]_esd' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls.S[3][3]_esd' 'cif_ccp4.dic' 1.0 save_ save_pdbx_refine_tls_group _category.description ; Data items in the PDBX_REFINE_TLS_GROUP category record details about a fragment of a TLS group. Properties of the TLS group are recorded in PDBX_REFINE_TLS ; _category.id pdbx_refine_tls_group _category.mandatory_code no loop_ _category_key.name '_pdbx_refine_tls_group.id' loop_ _category_group.id 'inclusive_group' 'refine_group' 'ccp4_group' save_ save__pdbx_refine_tls_group.id _item_description.description ; The value of _pdbx_refine_tls_group.id must uniquely identify a record in the REFINE_TLS_GROUP list. Note that this item need not be a number; it can be any unique identifier. ; _item.name '_pdbx_refine_tls_group.id' _item.category_id pdbx_refine_tls_group _item.mandatory_code yes _item_type.code code loop_ _item_examples.case 1 A loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls_group.id' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls_group.id' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls_group.refine_tls_id _item_description.description ; This data item is a pointer to _pdbx_refine_tls.id in the REFINE_TLS category. ; _item.name '_pdbx_refine_tls_group.refine_tls_id' _item.category_id pdbx_refine_tls_group _item.mandatory_code yes _item_type.code code loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls_group.refine_tls_id' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls_group.refine_tls_id' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls_group.beg_label_asym_id _item_description.description ; A component of the identifier for the residue at which the TLS fragment range begins. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_pdbx_refine_tls_group.beg_label_asym_id' _item.category_id pdbx_refine_tls_group _item.mandatory_code no loop_ _item_linked.child_name _item_linked.parent_name '_pdbx_refine_tls_group.beg_label_asym_id' '_atom_site.label_asym_id' loop_ _item_examples.case O 2B3 loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls_group.beg_label_asym_id' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls_group.beg_label_asym_id' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls_group.beg_label_seq_id _item_description.description ; A component of the identifier for the residue at which the TLS fragment range begins. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_pdbx_refine_tls_group.beg_label_seq_id' _item.category_id pdbx_refine_tls_group _item.mandatory_code no loop_ _item_linked.child_name _item_linked.parent_name '_pdbx_refine_tls_group.beg_label_seq_id' '_atom_site.label_seq_id' loop_ _item_examples.case 1 303 loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls_group.beg_label_seq_id' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls_group.beg_label_seq_id' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls_group.beg_auth_asym_id _item_description.description ; A component of the identifier for the residue at which the TLS fragment range begins. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_pdbx_refine_tls_group.beg_auth_asym_id' _item.category_id pdbx_refine_tls_group _item.mandatory_code no loop_ _item_linked.child_name _item_linked.parent_name '_pdbx_refine_tls_group.beg_auth_asym_id' '_atom_site.auth_asym_id' loop_ _item_examples.case O 2B3 loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls_group.beg_auth_asym_id' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls_group.beg_auth_asym_id' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls_group.beg_auth_seq_id _item_description.description ; A component of the identifier for the residue at which the TLS fragment range begins. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_pdbx_refine_tls_group.beg_auth_seq_id' _item.category_id pdbx_refine_tls_group _item.mandatory_code no loop_ _item_linked.child_name _item_linked.parent_name '_pdbx_refine_tls_group.beg_auth_seq_id' '_atom_site.auth_seq_id' loop_ _item_examples.case 1 5A loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls_group.beg_auth_asym_id' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls_group.beg_auth_asym_id' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls_group.end_label_asym_id _item_description.description ; A component of the identifier for the residue at which the TLS fragment range ends. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_pdbx_refine_tls_group.end_label_asym_id' _item.category_id pdbx_refine_tls_group _item.mandatory_code no loop_ _item_linked.child_name _item_linked.parent_name '_pdbx_refine_tls_group.end_label_asym_id' '_atom_site.label_asym_id' loop_ _item_examples.case O 2B3 loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls_group.end_label_asym_id' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls_group.end_label_asym_id' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls_group.end_label_seq_id _item_description.description ; A component of the identifier for the residue at which the TLS fragment range ends. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_pdbx_refine_tls_group.end_label_seq_id' _item.category_id pdbx_refine_tls_group _item.mandatory_code no loop_ _item_linked.child_name _item_linked.parent_name '_pdbx_refine_tls_group.end_label_seq_id' '_atom_site.label_seq_id' loop_ _item_examples.case 1 303 loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls_group.end_label_seq_id' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls_group.end_label_seq_id' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls_group.end_auth_asym_id _item_description.description ; A component of the identifier for the residue at which the TLS fragment range ends. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_pdbx_refine_tls_group.end_auth_asym_id' _item.category_id pdbx_refine_tls_group _item.mandatory_code no loop_ _item_linked.child_name _item_linked.parent_name '_pdbx_refine_tls_group.end_auth_asym_id' '_atom_site.auth_asym_id' loop_ _item_examples.case O 2B3 loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls_group.end_auth_asym_id' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls_group.end_auth_asym_id' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls_group.end_auth_seq_id _item_description.description ; A component of the identifier for the residue at which the TLS fragment range ends. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_pdbx_refine_tls_group.end_auth_seq_id' _item.category_id pdbx_refine_tls_group _item.mandatory_code no loop_ _item_linked.child_name _item_linked.parent_name '_pdbx_refine_tls_group.end_auth_seq_id' '_atom_site.auth_seq_id' loop_ _item_examples.case 1 5A loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls_group.end_auth_seq_id' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls_group.end_auth_seq_id' 'cif_ccp4.dic' 1.0 save_ save__pdbx_refine_tls_group.selection _item_description.description ; A description of the subset of atoms in the specified range included in the TLS fragment. ; _item.name '_pdbx_refine_tls_group.selection' _item.category_id pdbx_refine_tls_group _item.mandatory_code no _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail all ; all atoms in specified range ; mnc ; main chain atoms only ; sdc ; side chain atoms only ; loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_ccp4_refine_tls_group.selection' 'cif_rcsb.dic' 1.1 '_ccp4_refine_tls_group.selection' 'cif_ccp4.dic' 1.0 save_ # save__refine.pdbx_solvent_vdw_probe_radii _item_description.description ; CCP4 solvent proble van der Waals radii ; _item.name '_refine.pdbx_solvent_vdw_probe_radii' _item.category_id refine _item.mandatory_code no _item_type.code float _item_units.code angstroms loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_refine.ccp4_solvent_vdw_probe_radii' 'cif_rcsb.dic' 1.1 '_refine.ccp4_solvent_vdw_probe_radii' 'cif_ccp4.dic' 1.0 save_ save__refine.pdbx_solvent_ion_probe_radii _item_description.description ; CCP4 solvent ion proble radii ; _item.name '_refine.pdbx_solvent_ion_probe_radii' _item.category_id refine _item.mandatory_code no _item_type.code float _item_units.code angstroms loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_refine.ccp4_solvent_ion_probe_radii' 'cif_rcsb.dic' 1.1 '_refine.ccp4_solvent_ion_probe_radii' 'cif_ccp4.dic' 1.0 save_ save__refine.pdbx_solvent_shrinkage_radii _item_description.description ; CCP4 solvent shrinkage radii ; _item.name '_refine.pdbx_solvent_shrinkage_radii' _item.category_id refine _item.mandatory_code no _item_type.code float _item_units.code angstroms loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_refine.ccp4_solvent_shrinkage_radii' 'cif_rcsb.dic' 1.1 '_refine.ccp4_solvent_shrinkage_radii' 'cif_ccp4.dic' 1.0 save_ ######################### ## PDBX_CONTACT_AUTHOR ## ######################### save_pdbx_contact_author _category.description ; Data items in the PDBX_CONTACT_AUTHOR category record details about the name and address of the author to be contacted concerning the contents of this data block. This category atomizes information to a greater degree than the standard AUDIT_CONTACT_AUTHOR category. ; _category.id pdbx_contact_author _category.mandatory_code no _category_key.name '_pdbx_contact_author.id' loop_ _category_group.id 'inclusive_group' 'audit_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; _pdbx_contact_author.id 1 _pdbx_contact_author.name_salutation 'Dr.' _pdbx_contact_author.name_first 'Paula' _pdbx_contact_author.name_last 'Fitzgerald' _pdbx_contact_author.name_mi 'M.D.' _pdbx_contact_author.address_1 'Department of Biophysical Chemistry' _pdbx_contact_author.address_2 'Merck Research Laboratories' _pdbx_contact_author.address_3 'P. O. Box 2000, Ry80M203' _pdbx_contact_author.city 'Rahway' _pdbx_contact_author.state_province 'New Jersey' _pdbx_contact_author.postal_code 07065 _pdbx_contact_author.country 'UNITED STATES' _pdbx_contact_author.phone '908 594 5510' _pdbx_contact_author.fax '908 594 6645' _pdbx_contact_author.email 'paula_fitzgerald@merck.com' _pdbx_contact_author.role 'principal investigator' _pdbx_contact_author.organization_type 'commercial' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_contact_author.id _item_description.description ; A unique integer identifier for this author ; _item.name '_pdbx_contact_author.id' _item.category_id pdbx_contact_author _item.mandatory_code no _item_type.code int _item_examples.case ; 1 2 3 ; loop_ _item_enumeration.value 1 2 3 4 5 6 7 8 9 10 save_ save__pdbx_contact_author.address_1 _item_description.description ; The mailing address of the author of the data block to whom correspondence should be addressed, line 1 of 3. ; _item.name '_pdbx_contact_author.address_1' _item.category_id pdbx_contact_author _item.mandatory_code no _item_type.code text _item_examples.case ; 610 Taylor Road ; save_ save__pdbx_contact_author.address_2 _item_description.description ; The mailing address of the author of the data block to whom correspondence should be addressed, line 2 of 3. ; _item.name '_pdbx_contact_author.address_2' _item.category_id pdbx_contact_author _item.mandatory_code no _item_type.code text _item_examples.case ; Department of Chemistry and Chemical Biology ; save_ save__pdbx_contact_author.address_3 _item_description.description ; The mailing address of the author of the data block to whom correspondence should be addressed, line 3 of 3. ; _item.name '_pdbx_contact_author.address_3' _item.category_id pdbx_contact_author _item.mandatory_code no _item_type.code text _item_examples.case ; Busch Campus ; save_ save__pdbx_contact_author.city _item_description.description ; The mailing address of the author of the data block to whom correspondence should be addressed, city. ; _item.name '_pdbx_contact_author.city' _item.category_id pdbx_contact_author _item.mandatory_code no _item_type.code line _item_examples.case ; Piscataway ; save_ save__pdbx_contact_author.state_province _item_description.description ; The mailing address of the author of the data block to whom correspondence should be addressed, state or province. ; _item.name '_pdbx_contact_author.state_province' _item.category_id pdbx_contact_author _item.mandatory_code no _item_type.code line _item_examples.case ; New Jersey ; save_ save__pdbx_contact_author.postal_code _item_description.description ; The mailing address of the author of the data block to whom correspondence should be addressed, zip code. ; _item.name '_pdbx_contact_author.postal_code' _item.category_id pdbx_contact_author _item.mandatory_code no _item_type.code line _item_examples.case ; 08854 ; save_ save__pdbx_contact_author.email _item_description.description ; The electronic mail address of the author of the data block to whom correspondence should be addressed, in a form recognisable to international networks. ; _item.name '_pdbx_contact_author.email' _item.category_id pdbx_contact_author _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'name@host.domain.country' 'bm@iucr.ac.uk' save_ save__pdbx_contact_author.fax _item_description.description ; The facsimile telephone number of the author of the data block to whom correspondence should be addressed. The recommended style includes the international dialing prefix, the area code in parentheses, followed by the local number with no spaces. ; _item.name '_pdbx_contact_author.fax' _item.category_id pdbx_contact_author _item.mandatory_code no _item_type.code line loop_ _item_examples.case '12(34) 947 7334' '732 445 0103' save_ save__pdbx_contact_author.name_first _item_description.description ; The first name of the author of the data block to whom correspondence should be addressed. ; _item.name '_pdbx_contact_author.name_first' _item.category_id pdbx_contact_author _item.mandatory_code yes _item_type.code line loop_ _item_examples.case 'Percival' 'Loyd' 'Susan' save_ save__pdbx_contact_author.name_last _item_description.description ; The last name of the author of the data block to whom correspondence should be addressed. ; _item.name '_pdbx_contact_author.name_last' _item.category_id pdbx_contact_author _item.mandatory_code yes _item_type.code line loop_ _item_examples.case 'Samuels' 'Rodgers' save_ save__pdbx_contact_author.name_mi _item_description.description ; The middle initial(s) of the author of the data block to whom correspondence should be addressed. ; _item.name '_pdbx_contact_author.name_mi' _item.category_id pdbx_contact_author _item.mandatory_code yes _item_type.code line loop_ _item_examples.case 'T.' 'M.F.' save_ save__pdbx_contact_author.name_salutation _item_description.description ; The salutation of the author of the data block to whom correspondence should be addressed. ; _item.name '_pdbx_contact_author.name_salutation' _item.category_id pdbx_contact_author _item.mandatory_code yes _item_type.code line loop_ _item_examples.case 'Dr.' 'Prof.' 'Mr.' 'Ms.' 'Mrs.' loop_ _item_enumeration.value 'Dr.' 'Prof.' 'Mr.' 'Ms.' 'Mrs.' save_ save__pdbx_contact_author.country _item_description.description ; The country of the author of the data block to whom correspondence should be addressed. ; _item.name '_pdbx_contact_author.country' _item.category_id pdbx_contact_author _item.mandatory_code yes _item_type.code line loop_ _item_examples.case 'UNITED STATES' 'UNITED KINGDOM' 'AUSTRALIA' loop_ _item_enumeration.value 'UNITED STATES' 'AFGHANISTAN' 'ALBANIA' 'ALGERIA' 'AMERICAN SAMOA' 'ANDORRA' 'ANGOLA' 'ANGUILLA' 'ANTARCTICA' 'ANTIGUA AND BARBUDA' 'ARGENTINA' 'ARMENIA' 'ARUBA' 'AUSTRALIA' 'AUSTRIA' 'AZERBAIJAN' 'BAHAMAS' 'BAHRAIN' 'BANGLADESH' 'BARBADOS' 'BELARUS' 'BELGIUM' 'BELIZE' 'BENIN' 'BERMUDA' 'BHUTAN' 'BOLIVIA' 'BOSNIA AND HERZEGOVINA' 'BOTSWANA' 'BOUVET ISLAND' 'BRAZIL' 'BRITISH INDIAN OCEAN TERRITORY' 'BRUNEI DARUSSALAM' 'BULGARIA' 'BURKINA FASO' 'BURUNDI' 'CAMBODIA' 'CAMEROON' 'CANADA' 'CAPE VERDE' 'CAYMAN ISLANDS' 'CENTRAL AFRICAN REPUBLIC' 'CHAD' 'CHILE' 'CHINA' 'CHRISTMAS ISLAND' 'COCOS (KEELING) ISLANDS' 'COLOMBIA' 'COMOROS' 'CONGO' 'CONGO, THE DEMOCRATIC REPUBLIC OF THE' 'COOK ISLANDS' 'COSTA RICA' 'COTE D'IVOIRE' 'CROATIA' 'CUBA' 'CYPRUS' 'CZECH REPUBLIC' 'DENMARK' 'DJIBOUTI' 'DOMINICA' 'DOMINICAN REPUBLIC' v'ECUADOR' 'EGYPT' 'EL SALVADOR' 'EQUATORIAL GUINEA' 'ERITREA' 'ESTONIA' 'ETHIOPIA' 'FALKLAND ISLANDS (MALVINAS)' 'FAROE ISLANDS' 'FIJI' 'FINLAND' 'FRANCE' 'FRENCH GUIANA' 'FRENCH POLYNESIA' 'FRENCH SOUTHERN TERRITORIES' 'GABON' 'GAMBIA' 'GEORGIA' 'GERMANY' 'GHANA' 'GIBRALTAR' 'GREECE' 'GREENLAND' 'GRENADA' 'GUADELOUPE' 'GUAM' 'GUATEMALA' 'GUINEA' 'GUINEA-BISSAU' 'GUYANA' 'HAITI' 'HEARD ISLAND AND MCDONALD ISLANDS' 'HOLY SEE (VATICAN CITY STATE)' 'HONDURAS' 'HONG KONG' 'HUNGARY' 'ICELAND' 'INDIA' 'INDONESIA' 'IRAN, ISLAMIC REPUBLIC OF' 'IRAQ' 'IRELAND' 'ISRAEL' 'ITALY' 'JAMAICA' 'JAPAN' 'JORDAN' 'KAZAKHSTAN' 'KENYA' 'KIRIBATI' 'KOREA, DEMOCRATIC PEOPLE'S REPUBLIC OF' 'KOREA, REPUBLIC OF' 'KUWAIT' 'KYRGYZSTAN' 'LAO PEOPLE'S DEMOCRATIC REPUBLIC' 'LATVIA' 'LEBANON' 'LESOTHO' 'LIBERIA' 'LIBYAN ARAB JAMAHIRIYA' 'LIECHTENSTEIN' 'LITHUANIA' 'LUXEMBOURG' 'MACAO' 'MACEDONIA, THE FORMER YUGOSLAV REPUBLIC OF' 'MADAGASCAR' 'MALAWI' 'MALAYSIA' 'MALDIVES' 'MALI' 'MALTA' 'MARSHALL ISLANDS' 'MARTINIQUE' 'MAURITANIA' 'MAURITIUS' 'MAYOTTE' 'MEXICO' 'MICRONESIA, FEDERATED STATES OF' 'MOLDOVA, REPUBLIC OF' 'MONACO' 'MONGOLIA' 'MONTSERRAT' 'MOROCCO' 'MOZAMBIQUE' 'MYANMAR' 'NAMIBIA' 'NAURU' 'NEPAL' 'NETHERLANDS' 'NETHERLANDS ANTILLES' 'NEW CALEDONIA' 'NEW ZEALAND' 'NICARAGUA' 'NIGER' 'NIGERIA' 'NIUE' 'NORFOLK ISLAND' 'NORTHERN MARIANA ISLANDS' 'NORWAY' 'OMAN' 'PAKISTAN' 'PALAU' 'PALESTINIAN TERRITORY, OCCUPIED' 'PANAMA' 'PAPUA NEW GUINEA' 'PARAGUAY' 'PERU' 'PHILIPPINES' 'PITCAIRN' 'POLAND' 'PORTUGAL' 'PUERTO RICO' 'QATAR' 'REUNION' 'ROMANIA' 'RUSSIAN FEDERATION' 'RWANDA' 'SAINT HELENA' 'SAINT KITTS AND NEVIS' 'SAINT LUCIA' 'SAINT PIERRE AND MIQUELON' 'SAINT VINCENT AND THE GRENADINES' 'SAMOA' 'SAN MARINO' 'SAO TOME AND PRINCIPE' 'SAUDI ARABIA' 'SENEGAL' 'SERBIA AND MONTENEGRO' 'SEYCHELLES' 'SIERRA LEONE' 'SINGAPORE' 'SLOVAKIA' 'SLOVENIA' 'SOLOMON ISLANDS' 'SOMALIA' 'SOUTH AFRICA' 'SOUTH GEORGIA AND THE SOUTH SANDWICH ISLANDS' 'SPAIN' 'SRI LANKA' 'SUDAN' 'SURINAME' 'SVALBARD AND JAN MAYEN' 'SWAZILAND' 'SWEDEN' 'SWITZERLAND' 'SYRIAN ARAB REPUBLIC' 'TAIWAN, PROVINCE OF CHINA' 'TAJIKISTAN' 'TANZANIA, UNITED REPUBLIC OF' 'THAILAND' 'TIMOR-LESTE' 'TOGO' 'TOKELAU' 'TONGA' 'TRINIDAD AND TOBAGO' 'TUNISIA' 'TURKEY' 'TURKMENISTAN' 'TURKS AND CAICOS ISLANDS' 'TUVALU' 'UGANDA' 'UKRAINE' 'UNITED ARAB EMIRATES' 'UNITED KINGDOM' 'UNITED STATES MINOR OUTLYING ISLANDS' 'URUGUAY' 'UZBEKISTAN' 'VANUATU' 'VENEZUELA' 'VIET NAM' 'VIRGIN ISLANDS, BRITISH' 'VIRGIN ISLANDS, U.S.' 'WALLIS AND FUTUNA' 'WESTERN SAHARA' 'YEMEN' 'ZAMBIA' 'ZIMBABWE' save_ save__pdbx_contact_author.phone _item_description.description ; The telephone number of the author of the data block to whom correspondence should be addressed. The recommended style includes the international dialing prefix, the area code in parentheses, followed by the local number and any extension number prefixed by 'x', with no spaces. The earlier convention of including the international dialing prefixes in parentheses is no longer recommended. ; _item.name '_pdbx_contact_author.phone' _item.category_id pdbx_contact_author _item.mandatory_code no _item_type.code line loop_ _item_examples.case '12 (34) 947 7330' '947 732 0103 x8320' save_ save__pdbx_contact_author.role _item_description.description ; The role of this author in the project depositing this data. ; _item.name '_pdbx_contact_author.role' _item.category_id pdbx_contact_author _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'principal investigator' 'responsible scientist' 'investigator' loop_ _item_enumeration.value 'principal investigator' 'responsible scientist' 'investigator' save_ save__pdbx_contact_author.organization_type _item_description.description ; The organization type to which this author is affiliated. ; _item.name '_pdbx_contact_author.organization_type' _item.category_id pdbx_contact_author _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'academic' 'commercial' 'government' 'other' loop_ _item_enumeration.value 'academic' 'commercial' 'government' 'other' save_ save__struct_ref_seq_dif.pdbx_ordinal _item_description.description ; A synthetic integer primary key for this category. ; _item.name '_struct_ref_seq_dif.pdbx_ordinal' _item.category_id struct_ref_seq_dif _item.mandatory_code yes _item_type.code int _item_aliases.alias_name '_struct_ref_seq_dif.rcsb_ordinal' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ##################### ## PDBX_SG_PROJECT ## ##################### save_pdbx_SG_project _category.description ; Data items in the PDBX_CONTACT_AUTHOR category record details about the Structural Genomics Project and name and initials for each Center. ; _category.id pdbx_SG_project _category.mandatory_code no _category_key.name '_pdbx_SG_project.id' loop_ _category_group.id 'inclusive_group' 'audit_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; _pdbx_SG_project.id 1 _pdbx_SG_project.project_name 'PSI, Protein Structure Initiative' _pdbx_SG_project.full_name_of_center 'Berkeley Structural Genomics Center' _pdbx_SG_project.initial_of_center BSGC ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_SG_project.id _item_description.description ; A unique integer identifier for this center ; _item.name '_pdbx_SG_project.id' _item.category_id pdbx_SG_project _item.mandatory_code yes _item_type.code int _item_examples.case ; 1 2 3 ; loop_ _item_enumeration.value 1 2 3 4 5 6 7 8 9 10 save_ save__pdbx_SG_project.project_name _item_description.description ; The value identifies the Structural Genomics project. ; _item.name '_pdbx_SG_project.project_name' _item.category_id pdbx_SG_project _item.mandatory_code no _item_type.code text _item_examples.case 'PSI, Protein Structure Initiative' loop_ _item_enumeration.value 'PSI, Protein Structure Initiative' 'NPPSFA, National Project on Protein Structural and Functional Analyses' save_ save__pdbx_SG_project.full_name_of_center _item_description.description ; The value identifies the full name of center. ; _item.name '_pdbx_SG_project.full_name_of_center' _item.category_id pdbx_SG_project _item.mandatory_code no _item_type.code text _item_examples.case 'Berkeley Structural Genomics Center' loop_ _item_enumeration.value 'Bacterial targets at IGS-CNRS France' 'Berkeley Structural Genomics Center' 'Center for Eukaryotic Structural Genomics' 'Israel Structural Proteomics Center' 'Joint Center for Structural Genomics' 'Marseilles Structural Genomics Program @ AFMB' 'Midwest Center for Structural Genomics' 'Montreal-Kingston Bacterial Structural Genomics Initiative' 'Mycobacterium Tuberculosis Structural Proteomics Project' 'New York Structural Genomics Research Consortium' 'Northeast Structural Genomics Consortium' 'Oxford Protein Production Facility' 'Paris-Sud Yeast Structural Genomics' 'Protein Structure Factory' 'RIKEN Structural Genomics/Proteomics Initiative' 'Southeast Collaboratory for Structural Genomics' 'Structural Genomics Consortium' 'Structural Genomics of Pathogenic Protozoa Consortium' 'Structural Proteomics in Europe' 'Structure 2 Function Project' 'TB Structural Genomics Consortium' save_ save__pdbx_SG_project.initial_of_center _item_description.description ; The value identifies the full name of center. ; _item.name '_pdbx_SG_project.initial_of_center' _item.category_id pdbx_SG_project _item.mandatory_code no _item_type.code text _item_examples.case 'BSGC' loop_ _item_enumeration.value 'BIGS' 'BSGC' 'CESG' 'ISPC' 'JCSG' 'MSGP' 'MCSG' 'BSGI' 'XMTB' 'NYSGRC' 'NESG' 'OPPF' 'YSG' 'PSF' 'RSGI' 'SECSG' 'SGC' 'SGPP' 'SPINE' 'S2F' 'TBSGC' save_ ### EOF mmcif_pdbx-def-1.dic ########################################################################### # # File: mmcif_pdbx-def-3.dic # # PDB Exchange Data Dictionary # # This data dictionary contains definitions used by wwPDB for data exchange # and data processing. # # Definition Section 3 # # ########################################################################### ## ## save_pdbx_nmr_details _category.description ; Experimental details of the NMR study that have not been described elsewhere in this deposition. ; _category.id pdbx_nmr_details _category.mandatory_code no loop_ _category_key.name '_pdbx_nmr_details.entry_id' loop_ _category_group.id 'inclusive_group' 'pdbx_group' save_ save__pdbx_nmr_details.entry_id _item_description.description ; The entry ID for the structure determination. ; _item.name '_pdbx_nmr_details.entry_id' _item.category_id pdbx_nmr_details _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_nmr_details.entry_id' _item_linked.parent_name '_entry.id' _item_aliases.alias_name '_rcsb_nmr_details.entry_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_details.text _item_description.description ; Additional details describing the NMR experiment. ; _item.name '_pdbx_nmr_details.text' _item.category_id pdbx_nmr_details _item.mandatory_code no _item_type.code text loop_ _item_examples.case ; This structure was determined using standard 2D homonuclear techniques. ; ; The structure was determined using triple-resonance NMR spectroscopy. ; _item_aliases.alias_name '_rcsb_nmr_details.text' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ## ## provided to hold a simple solution description. save_pdbx_nmr_sample_details _category.description ; Complete description of each NMR sample, including the solvent system used. ; _category.id pdbx_nmr_sample_details _category.mandatory_code no loop_ _category_key.name '_pdbx_nmr_sample_details.solution_id' loop_ _category_group.id 'inclusive_group' 'pdbx_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; This example was taken from the study of MCP-1 which is a dimer under the conditions studied. Three solutions with different isotope compositions were studied. ; ; loop_ _pdbx_nmr_sample_details.solution_id _pdbx_nmr_sample_details.solvent_system _pdbx_nmr_sample_details.contents 1 MCP-1 '2 mM U-15N,13C, H2O 90 %, D2O 10 %' 2 MCP-1 '1 mM U-50% 15N, MCP-1 1 mM U-50% 13C, H2O 90 %, D2O 10 %' 3 MCP-1 '2 mM U-15N, H2O 90 %, D2O 10 %' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_nmr_sample_details.solution_id _item_description.description ; The name (number) of the sample. ; _item.name '_pdbx_nmr_sample_details.solution_id' _item.category_id pdbx_nmr_sample_details _item.mandatory_code yes _item_type.code code loop_ _item_examples.case '1' '2' '3' _item_aliases.alias_name '_rcsb_nmr_sample_details.solution_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_sample_details.contents _item_description.description ; A complete description of each NMR sample. Include the concentration and concentration units for each component (include buffers, etc.). For each component describe the isotopic composition, including the % labeling level, if known. For example: 1. Uniform (random) labeling with 15N: U-15N 2. Uniform (random) labeling with 13C, 15N at known labeling levels: U-95% 13C;U-98% 15N 3. Residue selective labeling: U-95% 15N-Thymine 4. Site specific labeling: 95% 13C-Ala18, 5. Natural abundance labeling in an otherwise uniformly labeled biomolecule is designated by NA: U-13C; NA-K,H ; _item.name '_pdbx_nmr_sample_details.contents' _item.category_id pdbx_nmr_sample_details _item.mandatory_code no _item_type.code text _item_examples.case ; 2mM Ribonuclease U-15N,13C; 50mM phosphate buffer NA; 90% H2O, 10% D2O ; _item_aliases.alias_name '_rcsb_nmr_sample_details.contents' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_sample_details.solvent_system _item_description.description ; The solvent system used for this sample. ; _item.name '_pdbx_nmr_sample_details.solvent_system' _item.category_id pdbx_nmr_sample_details _item.mandatory_code no _item_type.code text _item_examples.case ; 90% H2O, 10% D2O ; _item_aliases.alias_name '_rcsb_nmr_sample_details.solvent_system' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ## save_pdbx_nmr_exptl_sample _category.description ; The chemical constituents of each NMR sample. Each sample is identified by a number and each component in the sample is identified by name. ; _category.id pdbx_nmr_exptl_sample _category.mandatory_code no loop_ _category_key.name '_pdbx_nmr_exptl_sample.solution_id' '_pdbx_nmr_exptl_sample.component' loop_ _category_group.id 'inclusive_group' 'pdbx_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 This example was taken from the study of MCP-1 which is a dimer under the conditions studied. Three solutions with different isotope compositions were studied. ; # ; loop_ _pdbx_nmr_exptl_sample.solution_id _pdbx_nmr_exptl_sample.component _pdbx_nmr_exptl_sample.concentration _pdbx_nmr_exptl_sample.concentration_units _pdbx_nmr_exptl_sample.isotopic_labeling 1 MCP-1 2 'mM' 'U-15N,13C' 1 H2O 90 '%' . 1 D2O 10 '%' . ; ; Example 2 This example was taken from the study of MCP-1 which is a dimer under the conditions studied. Three solutions with different isotope compositions were studied. ; # ; loop_ _pdbx_nmr_exptl_sample.solution_id _pdbx_nmr_exptl_sample.component _pdbx_nmr_exptl_sample.concentration _pdbx_nmr_exptl_sample.concentration_units _pdbx_nmr_exptl_sample.isotopic_labeling 2 MCP-1 1 'mM' 'U-50% 15N' 2 H2O 90 '%' . 2 D2O 10 '%' . ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_nmr_exptl_sample.solution_id _item_description.description ; The name (number) of the sample. ; _item.name '_pdbx_nmr_exptl_sample.solution_id' _item.category_id pdbx_nmr_exptl_sample _item.mandatory_code yes _item_type.code code loop_ _item_examples.case '1' '2' '3' _item_aliases.alias_name '_rcsb_nmr_exptl_sample.solution_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_exptl_sample.component _item_description.description ; The name of each component in the sample ; _item.name '_pdbx_nmr_exptl_sample.component' _item.category_id pdbx_nmr_exptl_sample _item.mandatory_code yes _item_type.code line loop_ _item_examples.case 'ribonuclease' 'DNA strand 1' 'TRIS buffer' 'sodium chloride' 'H2O' 'D2O' _item_aliases.alias_name '_rcsb_nmr_exptl_sample.component' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_exptl_sample.concentration _item_description.description ; The concentration value of the component. ; _item.name '_pdbx_nmr_exptl_sample.concentration' _item.category_id pdbx_nmr_exptl_sample _item.mandatory_code no _item_type.code float loop_ _item_examples.case '2.0' '2.7' '0.01' _item_aliases.alias_name '_rcsb_nmr_exptl_sample.concentration' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_exptl_sample.concentration_units _item_description.description ; The concentration units of the component. ; _item.name '_pdbx_nmr_exptl_sample.concentration_units' _item.category_id pdbx_nmr_exptl_sample _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'mg/mL for mg per milliliter' 'mM for millimolar' '% for percent by volume' loop_ _item_enumeration.value _item_enumeration.detail '%' 'percent by volume' 'mM' 'millimolar' 'mg/mL' 'mg per milliliter' 'M' 'molar' 'g/L' 'grams per liter' _item_aliases.alias_name '_rcsb_nmr_exptl_sample.concentration_units' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_exptl_sample.isotopic_labeling _item_description.description ; The isotopic composition of each component, including the % labeling level, if known. For example: 1. Uniform (random) labeling with 15N: U-15N 2. Uniform (random) labeling with 13C, 15N at known labeling levels: U-95% 13C;U-98% 15N 3. Residue selective labeling: U-95% 15N-Thymine 4. Site specific labeling: 95% 13C-Ala18, 5. Natural abundance labeling in an otherwise uniformly labled biomolecule is designated by NA: U-13C; NA-K,H ; _item.name '_pdbx_nmr_exptl_sample.isotopic_labeling' _item.category_id pdbx_nmr_exptl_sample _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'U-13C,15N' 'U-2H' loop_ _item_enumeration.value 'U-15N' 'U-13C' 'U-15N,13C' 'U-2H' 'other' _item_aliases.alias_name '_rcsb_nmr_exptl_sample.isotopic_labeling' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### ### ########################################################################## ### save_pdbx_nmr_exptl_sample_conditions _category.description ; The experimental conditions used to for each sample. Each set of conditions is identified by a numerical code. ; _category.id pdbx_nmr_exptl_sample_conditions _category.mandatory_code no loop_ _category_key.name '_pdbx_nmr_exptl_sample_conditions.conditions_id' loop_ _category_group.id 'inclusive_group' 'pdbx_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; This example was taken from a pH stability study. ; # ; loop_ _pdbx_nmr_exptl_sample_conditions.conditions_id _pdbx_nmr_exptl_sample_conditions.temperature _pdbx_nmr_exptl_sample_conditions.pressure _pdbx_nmr_exptl_sample_conditions.pH _pdbx_nmr_exptl_sample_conditions.ionic_strength 1 298 ambient 7 '25mM NaCl' 2 298 ambient 3 '25mM NaCl' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_nmr_exptl_sample_conditions.conditions_id _item_description.description ; The condition number as defined above. ; _item.name '_pdbx_nmr_exptl_sample_conditions.conditions_id' _item.category_id pdbx_nmr_exptl_sample_conditions _item.mandatory_code yes _item_type.code code loop_ _item_examples.case '1' '2' '3' _item_aliases.alias_name '_rcsb_nmr_exptl_sample_conditions.conditions_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_exptl_sample_conditions.temperature _item_description.description ; The temperature (in Kelvin) at which NMR data were collected. ; _item.name '_pdbx_nmr_exptl_sample_conditions.temperature' _item.category_id pdbx_nmr_exptl_sample_conditions _item.mandatory_code no _item_type.code float-range loop_ _item_examples.case '298' _item_aliases.alias_name '_rcsb_nmr_exptl_sample_conditions.temperature' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_exptl_sample_conditions.pressure_units _item_description.description ; The units of pressure at which NMR data were collected. ; _item.name '_pdbx_nmr_exptl_sample_conditions.pressure_units' _item.category_id pdbx_nmr_exptl_sample_conditions _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'Pa' 'atm' 'Torr' _item_aliases.alias_name '_rcsb_nmr_exptl_sample_conditions.pressure_units' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_exptl_sample_conditions.pressure _item_description.description ; The pressure at which NMR data were collected. ; _item.name '_pdbx_nmr_exptl_sample_conditions.pressure' _item.category_id pdbx_nmr_exptl_sample_conditions _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'ambient' '1atm' _item_aliases.alias_name '_rcsb_nmr_exptl_sample_conditions.pressure' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_exptl_sample_conditions.pH _item_description.description ; The pH at which the NMR data were collected. ; _item.name '_pdbx_nmr_exptl_sample_conditions.pH' _item.category_id pdbx_nmr_exptl_sample_conditions _item.mandatory_code no _item_type.code float-range loop_ _item_examples.case '3.1' '7.0' _item_aliases.alias_name '_rcsb_nmr_exptl_sample_conditions.pH' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_exptl_sample_conditions.ionic_strength _item_description.description ; The ionic strength at which the NMR data were collected -in lieu of this enter the concentration and identity of the salt in the sample. ; _item.name '_pdbx_nmr_exptl_sample_conditions.ionic_strength' _item.category_id pdbx_nmr_exptl_sample_conditions _item.mandatory_code no _item_type.code line # loop_ # _item_examples.case # '3.1' # '7.0' _item_aliases.alias_name '_rcsb_nmr_exptl_sample_conditions.ionic_strength' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### ### ########################################################################## ### save_pdbx_nmr_spectrometer _category.description ; The details about each spectrometer used to collect data for this deposition. ; _category.id pdbx_nmr_spectrometer _category.mandatory_code no _category_key.name '_pdbx_nmr_spectrometer.spectrometer_id' loop_ _category_group.id 'inclusive_group' 'pdbx_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; The instruments described here are the ones used for the MCP-1 studies. ; # ; loop_ _pdbx_nmr_spectrometer.spectrometer_id _pdbx_nmr_spectrometer.type _pdbx_nmr_spectrometer.field_strength 1 'Bruker AMX' 600 2 'Bruker AMX' 500 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_nmr_spectrometer.spectrometer_id _item_description.description ; Assign a numerical ID to each instrument. ; _item.name '_pdbx_nmr_spectrometer.spectrometer_id' _item.category_id pdbx_nmr_spectrometer _item.mandatory_code yes _item_type.code code loop_ _item_examples.case '1' '2' '3' _item_aliases.alias_name '_rcsb_nmr_spectrometer.spectrometer_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_spectrometer.model _item_description.description ; The model of the NMR spectrometer. ; _item.name '_pdbx_nmr_spectrometer.model' _item.category_id pdbx_nmr_spectrometer _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'AVANCE' 'WH' 'WM' 'AM' 'AMX' 'DMX' 'DRX' 'MSL' 'OMEGA' 'OMEGA PSG' 'GX' 'GSX' 'A' 'AL' 'EC' 'EX' 'LA' 'ECP' 'VXRS' 'UNITY' 'UNITYPLUS' 'INOVA' _item_aliases.alias_name '_rcsb_nmr_spectrometer.model' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_spectrometer.type _item_description.description ; Select the instrument manufacturer(s) and the model(s) of the NMR(s) used for this work. ; _item.name '_pdbx_nmr_spectrometer.type' _item.category_id pdbx_nmr_spectrometer _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'Bruker WH' 'Bruker WM' 'Bruker AM' 'Bruker AMX' 'Bruker DMX' 'Bruker DRX' 'Bruker MSL' 'Bruker AVANCE' 'GE Omega' 'GE Omega PSG' 'JEOL GX' 'JEOL GSX' 'JEOL A' 'JEOL AL' 'JEOL EC' 'JEOL EX' 'JEOL LA' 'JEOL ECP' 'Varian VXRS' 'Varian UNITY' 'Varian UNITYplus' 'Varian INOVA' 'other' _item_aliases.alias_name '_rcsb_nmr_spectrometer.type' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_spectrometer.manufacturer _item_description.description ; The name of the manufacturer of the spectrometer. ; _item.name '_pdbx_nmr_spectrometer.manufacturer' _item.category_id pdbx_nmr_spectrometer _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'Varian' 'Bruker' 'JEOL' 'GE' _item_aliases.alias_name '_rcsb_nmr_spectrometer.manufacturer' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_spectrometer.field_strength _item_description.description ; Select the field strength for protons in MHz. ; _item.name '_pdbx_nmr_spectrometer.field_strength' _item.category_id pdbx_nmr_spectrometer _item.mandatory_code no _item_type.code float loop_ _item_examples.case '360' '400' '500' '600' '750' '800' '850' '900' '950' '1000' _item_aliases.alias_name '_rcsb_nmr_spectrometer.field_strength' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### ### ########################################################################## ### save_pdbx_nmr_exptl _category.description ; In this section, enter information on those experiments that were used to generate constraint data. For each NMR experiment indicate which sample and which sample conditions were used for the experiment. ; _category.id pdbx_nmr_exptl _category.mandatory_code no loop_ _category_key.name '_pdbx_nmr_exptl.experiment_id' '_pdbx_nmr_exptl.conditions_id' '_pdbx_nmr_exptl.solution_id' loop_ _category_group.id 'inclusive_group' 'pdbx_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; This example was taken from the MCP-1 study. ; # ; loop_ _pdbx_nmr_exptl.experiment_id _pdbx_nmr_exptl.solution_id _pdbx_nmr_exptl.conditions_id _pdbx_nmr_exptl.type 1 3 1 '3D_15N-separated_NOESY' 2 1 1 '3D_13C-separated_NOESY' 3 1 2 '4D_13C/15N-separated_NOESY' 4 1 1 '4D_13C-separated_NOESY' 5 1 1 '3D_15N-separated_ROESY' 6 3 1 '3D_13C-separated_ROESY' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_nmr_exptl.experiment_id _item_description.description ; A numerical ID for each experiment. ; _item.name '_pdbx_nmr_exptl.experiment_id' _item.category_id pdbx_nmr_exptl _item.mandatory_code yes _item_type.code code loop_ _item_examples.case '1' '2' '3' _item_aliases.alias_name '_rcsb_nmr_exptl.experiment_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_exptl.conditions_id _item_description.description ; The number to identify the set of sample conditions. ; _item.name '_pdbx_nmr_exptl.conditions_id' _item.category_id pdbx_nmr_exptl _item.mandatory_code yes _item_type.code code loop_ _item_examples.case '1' '2' '3' _item_aliases.alias_name '_rcsb_nmr_exptl.conditions_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_exptl.solution_id _item_description.description ; The solution_id from the Experimental Sample to identify the sample that these conditions refer to. [Remember to save the entries here before returning to the Experimental Sample form] ; _item.name '_pdbx_nmr_exptl.solution_id' _item.category_id pdbx_nmr_exptl _item.mandatory_code yes _item_type.code code loop_ _item_examples.case '1' '2' '3' _item_aliases.alias_name '_rcsb_nmr_exptl.solution_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_exptl.type _item_description.description ; The type of NMR experiment. ; _item.name '_pdbx_nmr_exptl.type' _item.category_id pdbx_nmr_exptl _item.mandatory_code no _item_type.code line loop_ _item_examples.case '2D NOESY' '3D_15N-separated_NOESY' '3D_13C-separated_NOESY' '4D_13C-separated_NOESY' '4D_13C/15N-separated_NOESY' '3D_15N-separated_ROESY' '3D_13C-separated_ROESY' 'HNCA-J' 'HNHA' 'DQF-COSY' 'P-COSY' 'PE-COSY' 'E-COSY' _item_aliases.alias_name '_rcsb_nmr_exptl.type' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### ### ########################################################################## ### save_pdbx_nmr_software _category.description ; Description of the software that was used for data collection, data processing, data analysis, structure calculations and refinement. The description should include the name of the software, the author of the software and the version used. ; _category.id pdbx_nmr_software _category.mandatory_code no loop_ _category_key.name '_pdbx_nmr_software.name' '_pdbx_nmr_software.version' '_pdbx_nmr_software.classification' loop_ _category_group.id 'inclusive_group' 'pdbx_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; This example describes the software used in the MCP-1 study. ; # ; loop_ _pdbx_nmr_software.name _pdbx_nmr_software.authors _pdbx_nmr_software.version _pdbx_nmr_software.classification UXNMR Bruker 940501.3 'collection' FELIX Hare 1.1 'processing' ANSIG Kraulis 3.0 'data analysis' X-PLOR Brunger 3.8 'structure calculation' X-PLOR Brunger 3.8 'refinement' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_nmr_software.classification _item_description.description ; The purpose of the software. ; _item.name '_pdbx_nmr_software.classification' _item.category_id pdbx_nmr_software _item.mandatory_code yes _item_type.code line loop_ _item_examples.case 'collection' 'processing' 'data analysis' 'structure solution' 'refinement' 'iterative matrix relaxation' # loop_ # _item_enumeration.value # 'collection' # 'processing' # 'data analysis' # 'structure solution' # 'refinement' # 'iterative matrix relaxation' _item_aliases.alias_name '_rcsb_nmr_software.classification' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_software.name _item_description.description ; The name of the software used for the task. ; _item.name '_pdbx_nmr_software.name' _item.category_id pdbx_nmr_software _item.mandatory_code yes _item_type.code line loop_ _item_examples.case 'ANSIG' 'AURELIA' 'AZARA' 'CHARMM' 'CORMA' 'DIANA' 'DYANA' 'DSPACE' 'DISGEO' 'DGII' 'DISMAN' 'DINOSAUR' 'DISCOVER' 'FELIX' 'FT_NMR' 'GROMOS' 'IRMA' 'MARDIGRAS' 'NMRPipe' 'SA' 'UXNMR' 'VNMR' 'X-PLOR' 'XWINNMR' _item_aliases.alias_name '_rcsb_nmr_software.name' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_software.version _item_description.description ; The version of the software. ; _item.name '_pdbx_nmr_software.version' _item.category_id pdbx_nmr_software _item.mandatory_code yes _item_type.code line loop_ _item_examples.case '940501.3' '2.1' _item_aliases.alias_name '_rcsb_nmr_software.version' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_software.authors _item_description.description ; The name of the authors of the software used in this procedure. ; _item.name '_pdbx_nmr_software.authors' _item.category_id pdbx_nmr_software _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'Brunger' 'Guentert' _item_aliases.alias_name '_rcsb_nmr_software.authors' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### ### ########################################################################## ### save_pdbx_nmr_constraints _category.description ; This section provides a tabulation of constraint data. ; _category.id pdbx_nmr_constraints _category.mandatory_code no _category_key.name '_pdbx_nmr_constraints.entry_id' loop_ _category_group.id 'inclusive_group' 'pdbx_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; This example uses the data from the MCP-1 structure determination. Remember this is a dimer so there are intersubunit constraints as well as intrasubunit constraints. ; # ; loop_ _pdbx_nmr_constraints.entry_id _pdbx_nmr_constraints.NOE_constraints_total _pdbx_nmr_constraints.NOE_intraresidue_total_count _pdbx_nmr_constraints.NOE_sequential_total_count _pdbx_nmr_constraints.NOE_medium_range_total_count _pdbx_nmr_constraints.NOE_long_range_total_count _pdbx_nmr_constraints.protein_phi_angle_constraints_total_count 1ABC 4458 1144 272 1004 1356 96 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_nmr_constraints.entry_id _item_description.description ; You can leave this blank as an ID will be assigned by the MSD to the constraint file. ; _item.name '_pdbx_nmr_constraints.entry_id' _item.category_id pdbx_nmr_constraints _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_nmr_constraints.entry_id' _item_linked.parent_name '_entry.id' _item_aliases.alias_name '_rcsb_nmr_constraints.entry_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_constraints.NOE_constraints_total _item_description.description ; The total number of all NOE constraints used in the final structure calculation. ; _item.name '_pdbx_nmr_constraints.NOE_constraints_total' _item.category_id pdbx_nmr_constraints _item.mandatory_code no _item_type.code int loop_ _item_examples.case '4458' _item_aliases.alias_name '_rcsb_nmr_constraints.NOE_constraints_total' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_constraints.NOE_intraresidue_total_count _item_description.description ; The total number of all intraresidue, [i-j]=0, NOE constraints used in the final structure calculation. ; _item.name '_pdbx_nmr_constraints.NOE_intraresidue_total_count' _item.category_id pdbx_nmr_constraints _item.mandatory_code no _item_type.code int loop_ _item_examples.case '1144' _item_aliases.alias_name '_rcsb_nmr_constraints.NOE_intraresidue_total_count' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_constraints.NOE_interentity_total_count _item_description.description ; The total number of interentity, NOE constraints used in the final structure calculation. This field should only be if system is complex -i.e more than one entity e.g. a dimer or ligand-protein complex ; _item.name '_pdbx_nmr_constraints.NOE_interentity_total_count' _item.category_id pdbx_nmr_constraints _item.mandatory_code no _item_type.code int loop_ _item_examples.case '272' _item_aliases.alias_name '_rcsb_nmr_constraints.NOE_interentity_total_count' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_constraints.NOE_sequential_total_count _item_description.description ; The total number of sequential, [i-j]=1, NOE constraints used in the final structure calculation. ; _item.name '_pdbx_nmr_constraints.NOE_sequential_total_count' _item.category_id pdbx_nmr_constraints _item.mandatory_code no _item_type.code int loop_ _item_examples.case '1004' _item_aliases.alias_name '_rcsb_nmr_constraints.NOE_sequential_total_count' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_constraints.NOE_medium_range_total_count _item_description.description ; The total number of medium range 1<[i-j]<=5 NOE constraints used in the final structure calculation. ; _item.name '_pdbx_nmr_constraints.NOE_medium_range_total_count' _item.category_id pdbx_nmr_constraints _item.mandatory_code no _item_type.code int loop_ _item_examples.case '682' _item_aliases.alias_name '_rcsb_nmr_constraints.NOE_medium_range_total_count' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_constraints.NOE_long_range_total_count _item_description.description ; The total number of long range [i-j]>5 NOE constraints used in the final structure calculation. ; _item.name '_pdbx_nmr_constraints.NOE_long_range_total_count' _item.category_id pdbx_nmr_constraints _item.mandatory_code no _item_type.code int loop_ _item_examples.case '1356' _item_aliases.alias_name '_rcsb_nmr_constraints.NOE_long_range_total_count' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_constraints.protein_phi_angle_constraints_total_count _item_description.description ; The total number of phi angle constraints used in the final structure calculation ; _item.name '_pdbx_nmr_constraints.protein_phi_angle_constraints_total_count' _item.category_id pdbx_nmr_constraints _item.mandatory_code no _item_type.code int loop_ _item_examples.case '96' _item_aliases.alias_name '_rcsb_nmr_constraints.protein_phi_angle_constraints_total_count' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_constraints.protein_psi_angle_constraints_total_count _item_description.description ; The total number of psi angle constraints used in the final structure calculation. ; _item.name '_pdbx_nmr_constraints.protein_psi_angle_constraints_total_count' _item.category_id pdbx_nmr_constraints _item.mandatory_code no _item_type.code int loop_ _item_examples.case '0' _item_aliases.alias_name '_rcsb_nmr_constraints.protein_psi_angle_constraints_total_count' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_constraints.protein_chi_angle_constraints_total_count _item_description.description ; The total number of chi angle constraints used in the final structure calculation. ; _item.name '_pdbx_nmr_constraints.protein_chi_angle_constraints_total_count' _item.category_id pdbx_nmr_constraints _item.mandatory_code no _item_type.code int loop_ _item_examples.case '66' _item_aliases.alias_name '_rcsb_nmr_constraints.protein_chi_angle_constraints_total_count' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_constraints.protein_other_angle_constraints_total_count _item_description.description ; The total number of other angle constraints used in the final structure calculation. ; _item.name '_pdbx_nmr_constraints.protein_other_angle_constraints_total_count' _item.category_id pdbx_nmr_constraints _item.mandatory_code no _item_type.code int loop_ _item_examples.case '0' _item_aliases.alias_name '_rcsb_nmr_constraints.protein_other_angle_constraints_total_count' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_constraints.NOE_interproton_distance_evaluation _item_description.description ; Describe the method used to quantify the NOE and ROE values. ; _item.name '_pdbx_nmr_constraints.NOE_interproton_distance_evaluation' _item.category_id pdbx_nmr_constraints _item.mandatory_code no _item_type.code text loop_ _item_examples.case ; NOE buildup curves with 50, 75, 150 ms mixing times were analyzed. ; ; Noesy cross peak intensities were classified into three different catagories with distances of 1.8-2.7 A, 1.8-3.5 A, 1.8- 5.0 A for strong, medium and weak NOEs. ; _item_aliases.alias_name '_rcsb_nmr_constraints.NOE_interproton_distance_evaluation' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_constraints.NOE_pseudoatom_corrections _item_description.description ; Describe any corrections made for pseudoatoms ; _item.name '_pdbx_nmr_constraints.NOE_pseudoatom_corrections' _item.category_id pdbx_nmr_constraints _item.mandatory_code no _item_type.code text loop_ _item_examples.case ; Pseudo-atoms nomenclature and corrections according to Wuethrich, Billeter, and Braun, J. Mol.Biol.(1983) 169, 949-961. ; ; Pseudoatoms were not used. ; _item_aliases.alias_name '_rcsb_nmr_constraints.NOE_pseudoatom_corrections' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_constraints.NOE_motional_averaging_correction _item_description.description ;Describe any corrections that were made to the NOE data for motional averaging. ; _item.name '_pdbx_nmr_constraints.NOE_motional_averaging_correction' _item.category_id pdbx_nmr_constraints _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'Replace with item example text' _item_aliases.alias_name '_rcsb_nmr_constraints.NOE_motional_averaging_correction' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## save__pdbx_nmr_constraints.hydrogen_bond_constraints_total_count _item_description.description ; The total number of hydrogen bond constraints used in the final structure calculation. ; _item.name '_pdbx_nmr_constraints.hydrogen_bond_constraints_total_count' _item.category_id pdbx_nmr_constraints _item.mandatory_code no _item_type.code int loop_ _item_examples.case '6' _item_aliases.alias_name '_rcsb_nmr_constraints.hydrogen_bond_constraints_total_count' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_constraints.disulfide_bond_constraints_total_count _item_description.description ; The total number of disulfide bond constraints used in the final structure calculation. ; _item.name '_pdbx_nmr_constraints.disulfide_bond_constraints_total_count' _item.category_id pdbx_nmr_constraints _item.mandatory_code no _item_type.code int loop_ _item_examples.case '3' _item_aliases.alias_name '_rcsb_nmr_constraints.disulfide_bond_constraints_total_count' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_constraints.NA_alpha-angle_constraints_total_count _item_description.description ; The total number of nucleic acid alpha-angle constraints used in the final structure calculation. ; _item.name '_pdbx_nmr_constraints.NA_alpha-angle_constraints_total_count' _item.category_id pdbx_nmr_constraints _item.mandatory_code no _item_type.code int loop_ _item_examples.case '18' _item_aliases.alias_name '_rcsb_nmr_constraints.NA_alpha-angle_constraints_total_count' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_constraints.NA_beta-angle_constraints_total_count _item_description.description ; The total number of nucleic acid beta-angle constraints used in the final structure calculation. ; _item.name '_pdbx_nmr_constraints.NA_beta-angle_constraints_total_count' _item.category_id pdbx_nmr_constraints _item.mandatory_code no _item_type.code int loop_ _item_examples.case '24' _item_aliases.alias_name '_rcsb_nmr_constraints.NA_beta-angle_constraints_total_count' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_constraints.NA_gamma-angle_constraints_total_count _item_description.description ; The total number of nucleic acid gamma-angle constraints used in the final structure calculation. ; _item.name '_pdbx_nmr_constraints.NA_gamma-angle_constraints_total_count' _item.category_id pdbx_nmr_constraints _item.mandatory_code no _item_type.code int loop_ _item_examples.case '12' _item_aliases.alias_name '_rcsb_nmr_constraints.NA_gamma-angle_constraints_total_count' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_constraints.NA_delta-angle_constraints_total_count _item_description.description ; The total number of nucleic acid delta-angle constraints used in the final structure calculation. ; _item.name '_pdbx_nmr_constraints.NA_delta-angle_constraints_total_count' _item.category_id pdbx_nmr_constraints _item.mandatory_code no _item_type.code int loop_ _item_examples.case '15' _item_aliases.alias_name '_rcsb_nmr_constraints.NA_delta-angle_constraints_total_count' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_constraints.NA_epsilon-angle_constraints_total_count _item_description.description ; The total number of nucleic acid epsilon-angle constraints used in the final structure calculation. ; _item.name '_pdbx_nmr_constraints.NA_epsilon-angle_constraints_total_count' _item.category_id pdbx_nmr_constraints _item.mandatory_code no _item_type.code int loop_ _item_examples.case '31' _item_aliases.alias_name '_rcsb_nmr_constraints.NA_epsilon-angle_constraints_total_count' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_constraints.NA_chi-angle_constraints_total_count _item_description.description ; The total number of nucleic acid chi-angle constraints used in the final structure calculation. ; _item.name '_pdbx_nmr_constraints.NA_chi-angle_constraints_total_count' _item.category_id pdbx_nmr_constraints _item.mandatory_code no _item_type.code int loop_ _item_examples.case '15' _item_aliases.alias_name '_rcsb_nmr_constraints.NA_chi-angle_constraints_total_count' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_constraints.NA_other-angle_constraints_total_count _item_description.description ; The total number of nucleic acid other-angle constraints used in the final structure calculation. ; _item.name '_pdbx_nmr_constraints.NA_other-angle_constraints_total_count' _item.category_id pdbx_nmr_constraints _item.mandatory_code no _item_type.code int loop_ _item_examples.case '5' _item_aliases.alias_name '_rcsb_nmr_constraints.NA_other-angle_constraints_total_count' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_constraints.NA_sugar_pucker_constraints_total_count _item_description.description ; The total number of nucleic acid sugar pucker constraints used in the final structure calculation. ; _item.name '_pdbx_nmr_constraints.NA_sugar_pucker_constraints_total_count' _item.category_id pdbx_nmr_constraints _item.mandatory_code no _item_type.code int loop_ _item_examples.case '10' _item_aliases.alias_name '_rcsb_nmr_constraints.NA_sugar_pucker_constraints_total_count' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ### ### ########################################################################## ### save_pdbx_nmr_ensemble _category.description ; This category contains the information that describes the ensemble of deposited structures. If only an average structure has been deposited skip this section. ; _category.id pdbx_nmr_ensemble _category.mandatory_code no _category_key.name '_pdbx_nmr_ensemble.entry_id' loop_ _category_group.id 'inclusive_group' 'pdbx_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ;This example uses the data from the MCP-1 study. ; # ; loop_ _pdbx_nmr_ensemble.entry_id _pdbx_nmr_ensemble.conformers_calculated_total_number _pdbx_nmr_ensemble.conformers_submitted_total_number _pdbx_nmr_ensemble.conformer_selection_criteria _pdbx_nmr_ensemble.representative_conformer 1ABC 40 20 'structures with the least restraint violations' 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_nmr_ensemble.entry_id _item_description.description ; Leave this blank as the ID is provided by the MSD ; _item.name '_pdbx_nmr_ensemble.entry_id' _item.category_id pdbx_nmr_ensemble _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_nmr_ensemble.entry_id' _item_linked.parent_name '_entry.id' _item_aliases.alias_name '_rcsb_nmr_ensemble.entry_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble.conformers_calculated_total_number _item_description.description ; The total number of conformer (models) that were calculated in the final round. ; _item.name '_pdbx_nmr_ensemble.conformers_calculated_total_number' _item.category_id pdbx_nmr_ensemble _item.mandatory_code no _item_type.code int loop_ _item_examples.case '40' _item_aliases.alias_name '_rcsb_nmr_ensemble.conformers_calculated_total_number' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble.conformers_submitted_total_number _item_description.description ; The number of conformer (models) that are submitted for the ensemble. ; _item.name '_pdbx_nmr_ensemble.conformers_submitted_total_number' _item.category_id pdbx_nmr_ensemble _item.mandatory_code no _item_type.code int loop_ _item_examples.case '20' _item_aliases.alias_name '_rcsb_nmr_ensemble.conformers_submitted_total_number' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble.conformer_selection_criteria _item_description.description ; By highlighting the appropriate choice(s), describe how the submitted conformer (models) were selected. ; _item.name '_pdbx_nmr_ensemble.conformer_selection_criteria' _item.category_id pdbx_nmr_ensemble _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'structures with the lowest energy' 'structures with the least restraint violations' 'structures with acceptable covalent geometry' 'structures with favorable non-bond energy' 'target function' 'back calculated data agree with experimental NOESY spectrum' 'all calculated structures submitted' ; The submitted conformer models are the 25 structures with the lowest energy. ; ; The submitted conformer models are those with the fewest number of constraint violations. ; _item_aliases.alias_name '_rcsb_nmr_ensemble.conformer_selection_criteria' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble.representative_conformer _item_description.description ; The number of the conformer identified as most representative. ; _item.name '_pdbx_nmr_ensemble.representative_conformer' _item.category_id pdbx_nmr_ensemble _item.mandatory_code no _item_type.code int loop_ _item_examples.case '20' _item_aliases.alias_name '_rcsb_nmr_ensemble.representative_conformer' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble.average_constraints_per_residue _item_description.description ; The average number of constraints per residue for the ensemble ; _item.name '_pdbx_nmr_ensemble.average_constraints_per_residue' _item.category_id pdbx_nmr_ensemble _item.mandatory_code no _item_type.code int loop_ _item_examples.case '30.2' _item_aliases.alias_name '_rcsb_nmr_ensemble.average_constraints_per_residue' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble.average_constraint_violations_per_residue _item_description.description ; The average number of constraint violations on a per residue basis for the ensemble. ; _item.name '_pdbx_nmr_ensemble.average_constraint_violations_per_residue' _item.category_id pdbx_nmr_ensemble _item.mandatory_code no _item_type.code int loop_ _item_examples.case '0.25' _item_aliases.alias_name '_rcsb_nmr_ensemble.average_constraint_violations_per_residue' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble.maximum_distance_constraint_violation _item_description.description ; The maximum distance constraint violation for the ensemble. ; _item.name '_pdbx_nmr_ensemble.maximum_distance_constraint_violation' _item.category_id pdbx_nmr_ensemble _item.mandatory_code no _item_type.code float _item_units.code angstroms loop_ _item_examples.case '0.4' _item_aliases.alias_name '_rcsb_nmr_ensemble.maximum_distance_constraint_violation' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble.average_distance_constraint_violation _item_description.description ; The average distance restraint violation for the ensemble. ; _item.name '_pdbx_nmr_ensemble.average_distance_constraint_violation' _item.category_id pdbx_nmr_ensemble _item.mandatory_code no _item_type.code float _item_units.code angstroms loop_ _item_examples.case '0.11' _item_aliases.alias_name '_rcsb_nmr_ensemble.average_distance_constraint_violation' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble.maximum_upper_distance_constraint_violation _item_description.description ; The maximum upper distance constraint violation for the ensemble. ; _item.name '_pdbx_nmr_ensemble.maximum_upper_distance_constraint_violation' _item.category_id pdbx_nmr_ensemble _item.mandatory_code no _item_type.code float _item_units.code angstroms loop_ _item_examples.case '0.4' _item_aliases.alias_name '_rcsb_nmr_ensemble.maximum_upper_distance_constraint_violation' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble.maximum_lower_distance_constraint_violation _item_description.description ; The maximum lower distance constraint violation for the ensemble. ; _item.name '_pdbx_nmr_ensemble.maximum_lower_distance_constraint_violation' _item.category_id pdbx_nmr_ensemble _item.mandatory_code no _item_type.code float _item_units.code angstroms loop_ _item_examples.case '0.3' _item_aliases.alias_name '_rcsb_nmr_ensemble.maximum_lower_distance_constraint_violation' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble.distance_constraint_violation_method _item_description.description ; Describe the method used to calculate the distance constraint violation statistics, i.e. are they calculated over all the distance constraints or calculated for violations only? ; _item.name '_pdbx_nmr_ensemble.distance_constraint_violation_method' _item.category_id pdbx_nmr_ensemble _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'Statistics were calculated over all of the distance constraints.' 'Statistics were calculated for violations only' _item_aliases.alias_name '_rcsb_nmr_ensemble.distance_constraint_violation_method' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble.maximum_torsion_angle_constraint_violation _item_description.description ; The maximum torsion angle constraint violation for the ensemble. ; _item.name '_pdbx_nmr_ensemble.maximum_torsion_angle_constraint_violation' _item.category_id pdbx_nmr_ensemble _item.mandatory_code no _item_type.code float _item_units.code degrees loop_ _item_examples.case '4' _item_aliases.alias_name '_rcsb_nmr_ensemble.maximum_torsion_angle_constraint_violation' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble.average_torsion_angle_constraint_violation _item_description.description ; The average torsion angle constraint violation for the ensemble. ; _item.name '_pdbx_nmr_ensemble.average_torsion_angle_constraint_violation' _item.category_id pdbx_nmr_ensemble _item.mandatory_code no _item_type.code float _item_units.code degrees loop_ _item_examples.case '2.4' _item_aliases.alias_name '_rcsb_nmr_ensemble.average_torsion_angle_constraint_violation' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble.torsion_angle_constraint_violation_method _item_description.description ; This item describes the method used to calculate the torsion angle constraint violation statistics. i.e. are the entered values based on all torsion angle or calculated for violations only? ; _item.name '_pdbx_nmr_ensemble.torsion_angle_constraint_violation_method' _item.category_id pdbx_nmr_ensemble _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'Statistics were calculated over all the torsion angle constraints.' 'Statistics were calculated for torsion angle constraints violations only.' _item_aliases.alias_name '_rcsb_nmr_ensemble.torsion_angle_constraint_violation_method' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### ### ########################################################################## ### save_pdbx_nmr_ensemble_rms _category.description ; Structural statistics are derived from molecular dynamics and simulated annealing programs. ; _category.id pdbx_nmr_ensemble_rms _category.mandatory_code no _category_key.name '_pdbx_nmr_ensemble_rms.entry_id' loop_ _category_group.id 'inclusive_group' 'pdbx_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; This example is derived from the MCP-1 structure calculation statistics. For this structure the statistics were calculated over residues 5-69 for both the monomer and dimer . ; # ; loop_ _pdbx_nmr_ensemble_rms.entry_id _pdbx_nmr_ensemble_rms.residue_range_begin _pdbx_nmr_ensemble_rms.chain_range_begin _pdbx_nmr_ensemble_rms.residue_range_end _pdbx_nmr_ensemble_rms.chain_range_end _pdbx_nmr_ensemble_rms.atom_type _pdbx_nmr_ensemble_rms.distance_rms_dev _pdbx_nmr_ensemble_rms.distance_rms_dev_error 1ABC 5 A 69 A 'all heavy atoms' 0.22 0.06 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_nmr_ensemble_rms.entry_id _item_description.description ; '?' ; _item.name '_pdbx_nmr_ensemble_rms.entry_id' _item.category_id pdbx_nmr_ensemble_rms _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_nmr_ensemble_rms.entry_id' _item_linked.parent_name '_entry.id' _item_aliases.alias_name '_rcsb_nmr_ensemble_rms.entry_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble_rms.residue_range_begin _item_description.description ; Structure statistics are often calculated only over the well-ordered region(s) of the biopolymer. Portions of the macromolecule are often mobile and disordered, hence they are excluded in calculating the statistics. To define the range(s) over which the statistics are calculated, enter the beginning residue number(s): e.g. if the regions used were 5-32 and 41-69, enter 5,41 ; _item.name '_pdbx_nmr_ensemble_rms.residue_range_begin' _item.category_id pdbx_nmr_ensemble_rms _item.mandatory_code no _item_type.code int loop_ _item_examples.case 5 41 _item_aliases.alias_name '_rcsb_nmr_ensemble_rms.residue_range_begin' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble_rms.chain_range_begin _item_description.description ; The beginning chain id. ; _item.name '_pdbx_nmr_ensemble_rms.chain_range_begin' _item.category_id pdbx_nmr_ensemble_rms _item.mandatory_code no _item_type.code code _item_examples.case A _item_aliases.alias_name '_rcsb_nmr_ensemble_rms.chain_range_begin' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble_rms.residue_range_end _item_description.description ; The ending residue number: e.g. 32,69. ; _item.name '_pdbx_nmr_ensemble_rms.residue_range_end' _item.category_id pdbx_nmr_ensemble_rms _item.mandatory_code no _item_type.code int loop_ _item_examples.case 32 69 _item_aliases.alias_name '_rcsb_nmr_ensemble_rms.residue_range_end' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble_rms.chain_range_end _item_description.description ; The ending chain id: ; _item.name '_pdbx_nmr_ensemble_rms.chain_range_end' _item.category_id pdbx_nmr_ensemble_rms _item.mandatory_code no _item_type.code code _item_examples.case A _item_aliases.alias_name '_rcsb_nmr_ensemble_rms.chain_range_end' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble_rms.atom_type _item_description.description ; Statistics are often calculated over only some of the atoms, e.g. backbone, or heavy atoms. Describe which type of atoms are used for the statistical analysis. ; _item.name '_pdbx_nmr_ensemble_rms.atom_type' _item.category_id pdbx_nmr_ensemble_rms _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'backbone atoms' 'heavy atoms' loop_ _item_enumeration.value 'backbone heavy atoms' 'side chain heavy atoms' 'all heavy atoms' 'all atoms' 'all backbone atoms' _item_aliases.alias_name '_rcsb_nmr_ensemble_rms.atom_type' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble_rms.distance_rms_dev _item_description.description ; The distance rmsd to the mean structure for the ensemble of structures. ; _item.name '_pdbx_nmr_ensemble_rms.distance_rms_dev' _item.category_id pdbx_nmr_ensemble_rms _item.mandatory_code no _item_type.code float _item_units.code angstroms loop_ _item_examples.case '0.22' _item_aliases.alias_name '_rcsb_nmr_ensemble_rms.distance_rms_dev' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble_rms.distance_rms_dev_error _item_description.description ; The error in the distance rmsd. ; _item.name '_pdbx_nmr_ensemble_rms.distance_rms_dev_error' _item.category_id pdbx_nmr_ensemble_rms _item.mandatory_code no _item_type.code float _item_units.code angstroms loop_ _item_examples.case '0.07' _item_aliases.alias_name '_rcsb_nmr_ensemble_rms.distance_rms_dev_error' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble_rms.covalent_bond_rms_dev _item_description.description ; The covalent bond rmsd to the target value for the ensemble. ; _item.name '_pdbx_nmr_ensemble_rms.covalent_bond_rms_dev' _item.category_id pdbx_nmr_ensemble_rms _item.mandatory_code no _item_type.code float _item_units.code angstroms loop_ _item_examples.case '0.0066' _item_aliases.alias_name '_rcsb_nmr_ensemble_rms.covalent_bond_rms_dev' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble_rms.covalent_bond_rms_dev_error _item_description.description ; The error in the covalent bond rmsd. ; _item.name '_pdbx_nmr_ensemble_rms.covalent_bond_rms_dev_error' _item.category_id pdbx_nmr_ensemble_rms _item.mandatory_code no _item_type.code float _item_units.code angstroms loop_ _item_examples.case '0.0001' _item_aliases.alias_name '_rcsb_nmr_ensemble_rms.covalent_bond_rms_dev_error' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble_rms.bond_angle_rms_dev _item_description.description ; The bond angle rmsd to the target values for the ensemble. ; _item.name '_pdbx_nmr_ensemble_rms.bond_angle_rms_dev' _item.category_id pdbx_nmr_ensemble_rms _item.mandatory_code no _item_type.code float _item_units.code degrees loop_ _item_examples.case '0.60' _item_aliases.alias_name '_rcsb_nmr_ensemble_rms.bond_angle_rms_dev' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble_rms.bond_angle_rms_dev_error _item_description.description ; The error in the bond angle rmsd. ; _item.name '_pdbx_nmr_ensemble_rms.bond_angle_rms_dev_error' _item.category_id pdbx_nmr_ensemble_rms _item.mandatory_code no _item_type.code float _item_units.code degrees loop_ _item_examples.case '0.01' _item_aliases.alias_name '_rcsb_nmr_ensemble_rms.bond_angle_rms_dev_error' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble_rms.improper_torsion_angle_rms_dev _item_description.description ; The improper torsion angle rmsd to the target values for the ensemble. ; _item.name '_pdbx_nmr_ensemble_rms.improper_torsion_angle_rms_dev' _item.category_id pdbx_nmr_ensemble_rms _item.mandatory_code no _item_type.code float _item_units.code degrees loop_ _item_examples.case '0.64' _item_aliases.alias_name '_rcsb_nmr_ensemble_rms.improper_torsion_angle_rms_dev' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble_rms.improper_torsion_angle_rms_dev_error _item_description.description ; The error in the improper torsion angle rmsd. ; _item.name '_pdbx_nmr_ensemble_rms.improper_torsion_angle_rms_dev_error' _item.category_id pdbx_nmr_ensemble_rms _item.mandatory_code no _item_type.code float _item_units.code degrees loop_ _item_examples.case '0.04' _item_aliases.alias_name '_rcsb_nmr_ensemble_rms.improper_torsion_angle_rms_dev_error' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble_rms.peptide_planarity_rms_dev _item_description.description ; The peptide planarity rmsd. ; _item.name '_pdbx_nmr_ensemble_rms.peptide_planarity_rms_dev' _item.category_id pdbx_nmr_ensemble_rms _item.mandatory_code no _item_type.code float _item_units.code angstroms loop_ _item_examples.case '0.11' _item_aliases.alias_name '_rcsb_nmr_ensemble_rms.peptide_planarity_rms_dev' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble_rms.peptide_planarity_rms_dev_error _item_description.description ; The error in the peptide planarity rmsd. ; _item.name '_pdbx_nmr_ensemble_rms.peptide_planarity_rms_dev_error' _item.category_id pdbx_nmr_ensemble_rms _item.mandatory_code no _item_type.code float _item_units.code angstroms loop_ _item_examples.case '0.05' _item_aliases.alias_name '_rcsb_nmr_ensemble_rms.peptide_planarity_rms_dev_error' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble_rms.dihedral_angles_rms_dev _item_description.description ; The dihedral angle rmsd to the target values for the ensemble. ; _item.name '_pdbx_nmr_ensemble_rms.dihedral_angles_rms_dev' _item.category_id pdbx_nmr_ensemble_rms _item.mandatory_code no _item_type.code float _item_units.code degrees loop_ _item_examples.case '0.66' _item_aliases.alias_name '_rcsb_nmr_ensemble_rms.dihedral_angles_rms_dev' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble_rms.dihedral_angles_rms_dev_error _item_description.description ; The error of the rmsd dihedral angles. ; _item.name '_pdbx_nmr_ensemble_rms.dihedral_angles_rms_dev_error' _item.category_id pdbx_nmr_ensemble_rms _item.mandatory_code no _item_type.code float _item_units.code degrees loop_ _item_examples.case '0.07' _item_aliases.alias_name '_rcsb_nmr_ensemble_rms.dihedral_angles_rms_dev_error' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_ensemble_rms.coord_average_rmsd_method _item_description.description ; Describe the method for calculating the coordinate average rmsd. ; _item.name '_pdbx_nmr_ensemble_rms.coord_average_rmsd_method' _item.category_id pdbx_nmr_ensemble_rms _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'Replace with item example text' _item_aliases.alias_name '_rcsb_nmr_ensemble_rms.coord_average_rmsd_method' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### ### ########################################################################## ### save_pdbx_nmr_representative _category.description ; An average structure is often calculated in addition to the ensemble, or one of the ensemble is selected as a representative structure. This section describes selection of the representative structure. ; _category.id pdbx_nmr_representative _category.mandatory_code no _category_key.name '_pdbx_nmr_representative.entry_id' loop_ _category_group.id 'inclusive_group' 'pdbx_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; This example is drawn from the MCP-1 structure. ; # ; _pdbx_nmr_representative.entry_id 1ABC _pdbx_nmr_representative.conformer_id 15 _pdbx_nmr_representative.selection_criteria 'lowest energy' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_nmr_representative.entry_id _item_description.description ; msd will assign the ID. ; _item.name '_pdbx_nmr_representative.entry_id' _item.category_id pdbx_nmr_representative _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_nmr_representative.entry_id' _item_linked.parent_name '_entry.id' _item_aliases.alias_name '_rcsb_nmr_representative.entry_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_representative.conformer_id _item_description.description ; If a member of the ensemble has been selected as a representative structure, identify it by its model number. ; _item.name '_pdbx_nmr_representative.conformer_id' _item.category_id pdbx_nmr_representative _item.mandatory_code no _item_type.code line loop_ _item_examples.case '15' _item_aliases.alias_name '_rcsb_nmr_representative.conformer_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_representative.selection_criteria _item_description.description ; By highlighting the appropriate choice(s), describe the criteria used to select this structure as a representative structure, or if an average structure has been calculated describe how this was done. ; _item.name '_pdbx_nmr_representative.selection_criteria' _item.category_id pdbx_nmr_representative _item.mandatory_code no _item_type.code line # loop_ # _item_enumeration.value # 'closest to the average' # 'lowest energy' # 'fewest violations' # 'minimized average structure' _item_examples.case ; The structure closest to the average. The structure with the lowest energy was selected. The structure with the fewest number of violations was selected. A minimized average structure was calculated. ; _item_aliases.alias_name '_rcsb_nmr_representative.selection_criteria' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save_pdbx_nmr_refine _category.description ; Describe the method and details of the refinement of the deposited structure. ; _category.id pdbx_nmr_refine _category.mandatory_code no _category_key.name '_pdbx_nmr_refine.entry_id' loop_ _category_group.id 'inclusive_group' 'pdbx_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; This example is drawn from the MCP-1 structure. ; ; loop_ _pdbx_nmr_refine.entry_id _pdbx_nmr_refine.method 1ABC 'torsion angle dynamics' ; save_ save__pdbx_nmr_refine.entry_id _item_description.description ; You can leave this blank as an ID will be assigned by the RCSB to the constraint file. ; _item.name '_pdbx_nmr_refine.entry_id' _item.category_id pdbx_nmr_refine _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_nmr_refine.entry_id' _item_linked.parent_name '_entry.id' _item_aliases.alias_name '_rcsb_nmr_refine.entry_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_refine.method _item_description.description ; The method used to determine the structure. ; _item.name '_pdbx_nmr_refine.method' _item.category_id pdbx_nmr_refine _item.mandatory_code yes _item_type.code text _item_examples.case ; distance geometry simulated annealing molecular dynamics matrix relaxation torsion angle dynamics ; _item_aliases.alias_name '_rcsb_nmr_refine.method' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_refine.details _item_description.description ; Additional details about the NMR refinement. ; _item.name '_pdbx_nmr_refine.details' _item.category_id pdbx_nmr_refine _item.mandatory_code no _item_type.code text _item_examples.case ; Additional comments about the NMR refinement can be placed here, e.g. the structures are based on a total of 3344 restraints, 3167 are NOE-derived distance constraints, 68 dihedral angle restraints,109 distance restraints from hydrogen bonds. ; _item_aliases.alias_name '_rcsb_nmr_refine.details' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ## save_pdbx_nmr_force_constants _category.description ; The final force constants, including units, employed for the various experimental constraints, covalent geometry constraints, and the non-bonded interaction terms in the target function used for simulated annealing. ; _category.id pdbx_nmr_force_constants _category.mandatory_code no loop_ _category_key.name '_pdbx_nmr_force_constants.entry_id' loop_ _category_group.id 'inclusive_group' 'pdbx_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - ; This example is taken from a study of BAF, a dimeric DNA binding protein. The final force constants in the target function used for simulated annealing are: Experimental Constraint terms: Distance (NOE,H-bonds), Torsion angles, J coupling, 13C shifts, 1H shifts, Dipolar coupling, D isotope shifts Covalent Geometry Constraint terms: Bond lengths, Angles, Impropers Non-bonded Interaction terms: van der Waals, Type of van der Waals term, Conformational database potential, Radius of gyration. ; # ; _pdbx_nmr_force_constants.entry_id 1ABC _pdbx_nmr_force_constants.exptl_distance_term 30. _pdbx_nmr_force_constants.exptl_distance_term_units 'kcal/mol/A**2' _pdbx_nmr_force_constants.exptl_torsion_angles_term 200. _pdbx_nmr_force_constants.exptl_torsion_angles_term_units 'kcal/mol/rad**2' _pdbx_nmr_force_constants.exptl_J_coupling_term 1. _pdbx_nmr_force_constants.exptl_J_coupling_term_units 'kcal/mol/Hz**2' _pdbx_nmr_force_constants.exptl_13C_shift_term 0.5 _pdbx_nmr_force_constants.exptl_13C_shift_term_units 'kcal/mol/ppm**2' _pdbx_nmr_force_constants.exptl_1H_shift_term 7.5 _pdbx_nmr_force_constants.exptl_1H_shift_term_units 'kcal/mol/ppm**2' _pdbx_nmr_force_constants.covalent_geom_bond_term 1000. _pdbx_nmr_force_constants.covalent_geom_bond_term_units 'kcal/mol/A**2' _pdbx_nmr_force_constants.non-bonded_inter_van_der_Waals_term_type 4. _pdbx_nmr_force_constants.non-bonded_inter_van_der_Waals_term_type_units 'kcal/mol/A**4' ; save_ save__pdbx_nmr_force_constants.entry_id _item_description.description ; You can leave this blank as an ID will be assigned by the RCSB. ; _item.name '_pdbx_nmr_force_constants.entry_id' _item.category_id pdbx_nmr_force_constants _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_nmr_force_constants.entry_id' _item_linked.parent_name '_entry.id' _item_aliases.alias_name '_rcsb_nmr_force_constants.entry_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_force_constants.exptl_distance_term _item_description.description ; The final force constant for distance (NOEs) constraints term employed in the target function used for simulated annealing. ; _item.name '_pdbx_nmr_force_constants.exptl_distance_term' _item.category_id pdbx_nmr_force_constants _item.mandatory_code no _item_type.code float loop_ _item_examples.case '30' _item_aliases.alias_name '_rcsb_nmr_force_constants.exptl_distance_term' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## save__pdbx_nmr_force_constants.exptl_distance_term_units _item_description.description ; The units for the force constant for the distance constraints term. ; _item.name '_pdbx_nmr_force_constants.exptl_distance_term_units' _item.category_id pdbx_nmr_force_constants _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'kcal/mol/ A**2' loop_ _item_enumeration.value _item_enumeration.detail 'kcal/mol/A**2' 'kilocalories per mole per square angstrom' 'kJ/mol/nm**2' 'kilojoules per mole per square nanometer' 'other' 'author added units' _item_aliases.alias_name '_rcsb_nmr_force_constants.exptl_distance_term_units' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_force_constants.exptl_torsion_angles_term _item_description.description ; The final force constant for the torsion angle term employed in the target function used for simulated annealing. ; _item.name '_pdbx_nmr_force_constants.exptl_torsion_angles_term' _item.category_id pdbx_nmr_force_constants _item.mandatory_code no _item_type.code float loop_ _item_examples.case '200' _item_aliases.alias_name '_rcsb_nmr_force_constants.exptl_torsion_angles_term' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_force_constants.exptl_torsion_angles_term_units _item_description.description ; The units for the force constant for the torsion angle constraints term. ; _item.name '_pdbx_nmr_force_constants.exptl_torsion_angles_term_units' _item.category_id pdbx_nmr_force_constants _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'kcal/mol/rad**2' loop_ _item_enumeration.value _item_enumeration.detail 'kcal/mol/rad**2' 'kilocalories per mole per square radian' 'kJ/mol/rad**2' 'kilojoules per mole per square radian' 'author' 'author added units' _item_aliases.alias_name '_rcsb_nmr_force_constants.exptl_torsion_angles_term_units' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## save__pdbx_nmr_force_constants.exptl_J_coupling_term _item_description.description ; The final force constant for J coupling term employed in the target function used for simulated annealing. ; _item.name '_pdbx_nmr_force_constants.exptl_J_coupling_term' _item.category_id pdbx_nmr_force_constants _item.mandatory_code no _item_type.code float loop_ _item_examples.case '1' _item_aliases.alias_name '_rcsb_nmr_force_constants.exptl_J_coupling_term' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_force_constants.exptl_J_coupling_term_units _item_description.description ; The units for the force constant for the J coupling term. ; _item.name '_pdbx_nmr_force_constants.exptl_J_coupling_term_units' _item.category_id pdbx_nmr_force_constants _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'kcal/mol/Hz**2' loop_ _item_enumeration.value _item_enumeration.detail 'kcal/mol/Hz**2' 'kilocalories per mole per square angstrom' 'kJ/mol/Hz**2' 'kilojoules per mole per square nanometer' 'other' 'author added units' _item_aliases.alias_name '_rcsb_nmr_force_constants.exptl_J_coupling_term_units' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_force_constants.exptl_13C_shift_term _item_description.description ; The final force constant for 13C shift constraints term employed in the target function used for simulated annealing. ; _item.name '_pdbx_nmr_force_constants.exptl_13C_shift_term' _item.category_id pdbx_nmr_force_constants _item.mandatory_code no _item_type.code float loop_ _item_examples.case '0.5' _item_aliases.alias_name '_rcsb_nmr_force_constants.exptl_13C_shift_term' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_force_constants.exptl_13C_shift_term_units _item_description.description ; The units for the force constant for the 13C shift constraints term. ; _item.name '_pdbx_nmr_force_constants.exptl_13C_shift_term_units' _item.category_id pdbx_nmr_force_constants _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'kcal/mol/ppm**2' loop_ _item_enumeration.value _item_enumeration.detail 'kcal/mol/ppm**2' 'kilocalories per mole per part per million squared' 'kJ/mol/ppm**2' 'kilojoules per mole per part per million squared' 'other' 'author added units' _item_aliases.alias_name '_rcsb_nmr_force_constants.exptl_13C_shift_term_units' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## save__pdbx_nmr_force_constants.exptl_1H_shift_term _item_description.description ; The final force constant for 1H shift constraints term employed in the target function used for simulated annealing. ; _item.name '_pdbx_nmr_force_constants.exptl_1H_shift_term' _item.category_id pdbx_nmr_force_constants _item.mandatory_code no _item_type.code float loop_ _item_examples.case '7.5' _item_aliases.alias_name '_rcsb_nmr_force_constants.exptl_1H_shift_term' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_force_constants.exptl_1H_shift_term_units _item_description.description ; The units for the force constant for the 1H shift constraints term. ; _item.name '_pdbx_nmr_force_constants.exptl_1H_shift_term_units' _item.category_id pdbx_nmr_force_constants _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'kcal/mol/ppm**2' loop_ _item_enumeration.value _item_enumeration.detail 'kcal/mol/ppm**2' 'kilocalories per mole per part per million squared' 'kJ/mol/ppm**2' 'kilojoules per mole per part per million squared' 'other' 'author added units' _item_aliases.alias_name '_rcsb_nmr_force_constants.exptl_1H_shift_term_units' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_force_constants.exptl_dipolar_coupling_term _item_description.description ; The final force constant for dipolar coupling constraint term employed in the target function used for simulated annealing. ; _item.name '_pdbx_nmr_force_constants.exptl_dipolar_coupling_term' _item.category_id pdbx_nmr_force_constants _item.mandatory_code no _item_type.code float loop_ _item_examples.case '1' _item_aliases.alias_name '_rcsb_nmr_force_constants.exptl_dipolar_coupling_term' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_force_constants.exptl_dipolar_coupling_term_units _item_description.description ; The units for the force constant for the dipolar coupling constraints term. ; _item.name '_pdbx_nmr_force_constants.exptl_dipolar_coupling_term_units' _item.category_id pdbx_nmr_force_constants _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'kcal/mol/Hz**2' loop_ _item_enumeration.value _item_enumeration.detail 'kcal/mol/Hz**2' 'kilocalories per mole per Hertz squared' 'kJ/mol/Hz**2' 'kilojoules per mole per Hertz squared' 'other' 'author added units' _item_aliases.alias_name '_rcsb_nmr_force_constants.exptl_dipolar_coupling_term_units' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_force_constants.exptl_D_isotope_shift_term _item_description.description ; The final force constant for Deuterium isotope shift constraints term employed in the target function used for simulated annealing. ; _item.name '_pdbx_nmr_force_constants.exptl_D_isotope_shift_term' _item.category_id pdbx_nmr_force_constants _item.mandatory_code no _item_type.code float loop_ _item_examples.case '0.5' _item_aliases.alias_name '_rcsb_nmr_force_constants.exptl_D_isotope_shift_term' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### ### NEXT save__pdbx_nmr_force_constants.exptl_D_isotope_shift_term_units _item_description.description ; The units for the force constant for the Deuterium isotope shift constraints term. ; _item.name '_pdbx_nmr_force_constants.exptl_D_isotope_shift_term_units' _item.category_id pdbx_nmr_force_constants _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'kcal/mol/ppb**2' loop_ _item_enumeration.value _item_enumeration.detail 'kcal/mol/ppb**2' 'kilocalories per mole per part per billion squared' 'kJ/mol/ppb**2' 'kilojoules per mole per part per billion squared' 'other' 'author added units' _item_aliases.alias_name '_rcsb_nmr_force_constants.exptl_D_isotope_shift_term_units' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_force_constants.covalent_geom_bond_term _item_description.description ; The final force constant for the covalent geometry bond length constraints term employed in the target function used for simulated annealing. ; _item.name '_pdbx_nmr_force_constants.covalent_geom_bond_term' _item.category_id pdbx_nmr_force_constants _item.mandatory_code no _item_type.code float loop_ _item_examples.case '1000' _item_aliases.alias_name '_rcsb_nmr_force_constants.covalent_geom_bond_term' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_force_constants.covalent_geom_bond_term_units _item_description.description ; The units for the force constant for the covalent geometry bond length constraints term. ; _item.name '_pdbx_nmr_force_constants.covalent_geom_bond_term_units' _item.category_id pdbx_nmr_force_constants _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'kcal/mol/A**2' loop_ _item_enumeration.value _item_enumeration.detail 'kcal/mol/A**2' 'kilocalories per mole per square angstrom' 'kJ/mol/nm**2' 'kilojoules per mole per square nanometer' 'other' 'author added units' _item_aliases.alias_name '_rcsb_nmr_force_constants.covalent_geom_bond_term_units' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_force_constants.covalent_geom_angles_term _item_description.description ; The final force constant for covalent geometry angle constraints term employed in the target function used for simulated annealing. ; _item.name '_pdbx_nmr_force_constants.covalent_geom_angles_term' _item.category_id pdbx_nmr_force_constants _item.mandatory_code no _item_type.code float loop_ _item_examples.case '500' _item_aliases.alias_name '_rcsb_nmr_force_constants.covalent_geom_angles_term' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_force_constants.covalent_geom_angles_term_units _item_description.description ; The units for the force constant for the covalent geometry angle constraints term. ; _item.name '_pdbx_nmr_force_constants.covalent_geom_angles_term_units' _item.category_id pdbx_nmr_force_constants _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'kcal/mol/rad**2' loop_ _item_enumeration.value _item_enumeration.detail 'kcal/mol/rad**2' 'kilocalories per mole per radian squared' 'kJ/mol/rad**2' 'kilojoules per mole per radian squared' 'other' 'author added units' _item_aliases.alias_name '_rcsb_nmr_force_constants.covalent_geom_angles_term_units' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_force_constants.covalent_geom_impropers_term _item_description.description ; The final force constant for covalent geometry impropers contstraints term employed in the target function used for simulated annealing. ; _item.name '_pdbx_nmr_force_constants.covalent_geom_impropers_term' _item.category_id pdbx_nmr_force_constants _item.mandatory_code no _item_type.code float loop_ _item_examples.case '500' _item_aliases.alias_name '_rcsb_nmr_force_constants.covalent_geom_impropers_term' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_force_constants.covalent_geom_impropers_term_units _item_description.description ; The units for the force constant for the covalent geometry impropers constraints term. ; _item.name '_pdbx_nmr_force_constants.covalent_geom_impropers_term_units' _item.category_id pdbx_nmr_force_constants _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'kcal/mol/rad**2' loop_ _item_enumeration.value _item_enumeration.detail 'kcal/mol/rad**2' 'kilocalories per mole per radian squared' 'kJ/mol/rad**2' 'kilojoules per mole per radian squared' 'other' 'author added units' _item_aliases.alias_name '_rcsb_nmr_force_constants.covalent_geom_impropers_term_units' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_force_constants.non-bonded_inter_van_der_Waals_term_type _item_description.description ; The type of van der Waals term employed in the target function used for simulated annealing. ; _item.name '_pdbx_nmr_force_constants.non-bonded_inter_van_der_Waals_term_type' _item.category_id pdbx_nmr_force_constants _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'quartic' loop_ _item_enumeration.value 'quartic' 'other' _item_aliases.alias_name '_rcsb_nmr_force_constants.non-bonded_inter_van_der_Waals_term_type' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_force_constants.non-bonded_inter_van_der_Waals_term _item_description.description ; The force constant used for the non-bonded interaction van der Waals term employed in the target function used for simulated annealing. ; _item.name '_pdbx_nmr_force_constants.non-bonded_inter_van_der_Waals_term' _item.category_id pdbx_nmr_force_constants _item.mandatory_code no _item_type.code float loop_ _item_examples.case '4' _item_aliases.alias_name '_rcsb_nmr_force_constants.non-bonded_inter_van_der_Waals_term' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_force_constants.non-bonded_inter_van_der_Waals_term_units _item_description.description ; The units for the force constant for the van der Waals term. ; _item.name '_pdbx_nmr_force_constants.non-bonded_inter_van_der_Waals_term_units' _item.category_id pdbx_nmr_force_constants _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'kcal/mol/ A**4' loop_ _item_enumeration.value _item_enumeration.detail 'kcal/mol/A**4' 'kilocalories per mole per Angstrom to the 4th power' 'kJ/mol/nm**4' 'kilojoules per mole per nanometer to the 4th power' 'other' 'author added units' _item_aliases.alias_name '_rcsb_nmr_force_constants.non-bonded_inter_van_der_Waals_term_units' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_force_constants.non-bonded_inter_conf_db_potential_term _item_description.description ; The force constant used for the non-bonded interaction conformational database potential term employed in the target function used for simulated annealing. ; _item.name '_pdbx_nmr_force_constants.non-bonded_inter_conf_db_potential_term' _item.category_id pdbx_nmr_force_constants _item.mandatory_code no _item_type.code float loop_ _item_examples.case '1.0' _item_aliases.alias_name '_rcsb_nmr_force_constants.non-bonded_inter_conf_db_potential_term' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_force_constants.non-bonded_inter_radius_of_gyration_term _item_description.description ; The force constant used for the non-bonded interaction radius of gyration term employed in the target function used for simulated annealing. ; _item.name '_pdbx_nmr_force_constants.non-bonded_inter_radius_of_gyration_term' _item.category_id pdbx_nmr_force_constants _item.mandatory_code no _item_type.code float loop_ _item_examples.case '100' _item_aliases.alias_name '_rcsb_nmr_force_constants.non-bonded_inter_radius_of_gyration_term' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_nmr_force_constants.non-bonded_inter_radius_of_gyration_term_units _item_description.description ; The units for the force constant for the radius of gyration term. ; _item.name '_pdbx_nmr_force_constants.non-bonded_inter_radius_of_gyration_term_units' _item.category_id pdbx_nmr_force_constants _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'kcal/mol/ A**2' loop_ _item_enumeration.value _item_enumeration.detail 'kcal/mol/ A**2' 'kilocalories per mole per square Angstrom' 'kJ/mol/ nm**4' 'kilojoules per mole per square nanometer' 'other' 'author added units' _item_aliases.alias_name '_rcsb_nmr_force_constants.non-bonded_inter_radius_of_gyration_term_units' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ### EOF mmcif_pdbx-def-2.dic########################################################################### # # File: mmcif_pdbx-def-4.dic # # PDB Exchange Data Dictionary # # This data dictionary contains definitions used by wwPDB for data exchange # and data processing. # # Definition Section 4 # # ########################################################################### ## ## Additional aliases required only for NDB/RCSB use: ## save__refine.overall_SU_B # _item.name '_refine.overall_SU_B' # _item.category_id refine # _item.mandatory_code no _item_aliases.alias_name '_refine.ebi_overall_ESU_B' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 # _item_type.code float save_ save__refine.overall_SU_ML # _item.name '_refine.overall_SU_ML' # _item.category_id refine # _item.mandatory_code no _item_aliases.alias_name '_refine.ebi_overall_ESU_ML' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 # _item_type.code float save_ save__refine_hist.number_atoms_solvent # _item.name '_refine_hist.number_atoms_solvent' # _item.category_id refine_hist # _item.mandatory_code no _item_aliases.alias_name '_refine_hist.rcsb_number_atoms_solvent' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 # _item_type.code int save_ save__refine_hist.number_atoms_total # _item.name '_refine_hist.number_atoms_total' # _item.category_id refine_hist # _item.mandatory_code no _item_aliases.alias_name '_refine_hist.rcsb_number_atoms_total' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 # _item_type.code int save_ ## ## NDB Specific definitions ## ########################## ## NDB_STRUCT_CONF_NA ## ########################## save_ndb_struct_conf_na _category.description ; Data items in the NDB_STRUCT_CONF_NA category describes secondary structure features in this entry. ; _category.id ndb_struct_conf_na _category.mandatory_code no loop_ _category_key.name '_ndb_struct_conf_na.entry_id' '_ndb_struct_conf_na.feature' loop_ _category_group.id 'inclusive_group' 'struct_group' 'ndb_group' _ndb_category_examples.case ; loop_ _ndb_struct_conf_na.entry_id _ndb_struct_conf_na.feature _ndb_struct_conf_na.feature_count rcsb000001 'double helix' 1 rcsb000001 'b-form double helix' 1 rcsb000001 'quadruple helix' 1 ; save_ save__ndb_struct_conf_na.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_ndb_struct_conf_na.entry_id' _item.category_id ndb_struct_conf_na _item.mandatory_code yes _item_linked.child_name '_ndb_struct_conf_na.entry_id' _item_linked.parent_name '_entry.id' save_ save__ndb_struct_conf_na.feature _item_description.description ; This data item identifies a secondary structure feature of this entry. ; _item.name '_ndb_struct_conf_na.feature' _item.category_id ndb_struct_conf_na _item.mandatory_code yes _item_type.code line loop_ _item_enumeration.value _item_enumeration.detail 'double helix' . 'a-form double helix' . 'b-form double helix' . 'z-form double helix' . 'other right-handed double helix' . 'triple helix' . 'quadruple helix' . 'parallel strands' . 'internal loop' . 'bulge loop' . 'tetraloop' . 'hairpin loop' . 'two-way junction' . 'three-way junction' . 'four-way junction' . 'mismatched base pair' . save_ save__ndb_struct_conf_na.feature_count _item_description.description ; This data item counts the number of occurences of this feature in this entry. ; _item.name '_ndb_struct_conf_na.feature_count' _item.category_id ndb_struct_conf_na _item.mandatory_code no _item_type.code int save_ ############################# ## NDB_STRUCT_FEATURE_NA ## ############################# save_ndb_struct_feature_na _category.description ; Data items in the NDB_STRUCT_FEATURE_NA category describes tertiary and other special structural features in this entry. ; _category.id ndb_struct_feature_na _category.mandatory_code no loop_ _category_key.name '_ndb_struct_feature_na.entry_id' '_ndb_struct_feature_na.feature' loop_ _category_group.id 'inclusive_group' 'struct_group' 'ndb_group' _ndb_category_examples.case ; loop_ _ndb_struct_feature_na.entry_id _ndb_struct_feature_na.feature _ndb_struct_feature_na.feature_count rcsb000001 'intercalated base' 1 rcsb000001 'bent/kinked double helix' 1 ; save_ save__ndb_struct_feature_na.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_ndb_struct_feature_na.entry_id' _item.category_id ndb_struct_feature_na _item.mandatory_code yes _item_linked.child_name '_ndb_struct_feature_na.entry_id' _item_linked.parent_name '_entry.id' save_ save__ndb_struct_feature_na.feature _item_description.description ; This data item identifies a structural feature of this entry. ; _item.name '_ndb_struct_feature_na.feature' _item.category_id ndb_struct_feature_na _item.mandatory_code yes _item_type.code line loop_ _item_enumeration.value _item_enumeration.detail 'pseudoknot' . 'intercalated base' . 'backbone turn' . 'intramolecular base triplet' . 'ribose zipper' . 'purine platform' . 'bent/kinked double helix' . save_ save__ndb_struct_feature_na.feature_count _item_description.description ; This data item counts the number of occurences of this feature in this entry. ; _item.name '_ndb_struct_feature_na.feature_count' _item.category_id ndb_struct_feature_na _item.mandatory_code no _item_type.code int save_ ############################# ## NDB_STRUCT_NA_BASE_PAIR ## ############################# save_ndb_struct_na_base_pair _category.description ; Data items in the NDB_STRUCT_NA_BASE_PAIR category record details of base pairing interactions. ; _category.id ndb_struct_na_base_pair _category.mandatory_code no loop_ _category_key.name '_ndb_struct_na_base_pair.model_number' '_ndb_struct_na_base_pair.i_label_comp_id' '_ndb_struct_na_base_pair.i_label_asym_id' '_ndb_struct_na_base_pair.i_label_seq_id' '_ndb_struct_na_base_pair.i_symmetry' '_ndb_struct_na_base_pair.j_label_comp_id' '_ndb_struct_na_base_pair.j_label_asym_id' '_ndb_struct_na_base_pair.j_label_seq_id' '_ndb_struct_na_base_pair.j_symmetry' loop_ _category_group.id 'inclusive_group' 'struct_group' 'ndb_group' loop_ _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _ndb_struct_na_base_pair.model_number _ndb_struct_na_base_pair.i_label_comp_id _ndb_struct_na_base_pair.i_label_asym_id _ndb_struct_na_base_pair.i_label_seq_id _ndb_struct_na_base_pair.i_symmetry _ndb_struct_na_base_pair.j_label_comp_id _ndb_struct_na_base_pair.j_label_asym_id _ndb_struct_na_base_pair.j_label_seq_id _ndb_struct_na_base_pair.j_symmetry _ndb_struct_na_base_pair.shear _ndb_struct_na_base_pair.stretch _ndb_struct_na_base_pair.stagger _ndb_struct_na_base_pair.buckle _ndb_struct_na_base_pair.propeller _ndb_struct_na_base_pair.opening 1 G A 1 1_555 C A 8 7_555 -0.396 -0.156 -0.018 -5.523 -6.752 -3.291 1 G A 2 1_555 C A 7 7_555 -0.094 -0.220 -0.334 -4.727 -9.765 2.311 1 G A 3 1_555 C A 6 7_555 -0.285 -0.239 0.008 -6.454 -12.575 -1.181 # ... ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__ndb_struct_na_base_pair.model_number _item_description.description ; Describes the model number of the the base pair. This data item is a pointer to _atom_site.ndb_model in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair.model_number' _item.category_id ndb_struct_na_base_pair _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair.model_number' _item_linked.parent_name '_atom_site.pdbx_PDB_model_num' save_ save__ndb_struct_na_base_pair.pair_number _item_description.description ; Sequential number of pair in the pair sequence. ; _item.name '_ndb_struct_na_base_pair.pair_number' _item.category_id ndb_struct_na_base_pair _item.mandatory_code yes _item_type.code int save_ save__ndb_struct_na_base_pair.pair_name _item_description.description ; Text label for this base pair. ; _item.name '_ndb_struct_na_base_pair.pair_name' _item.category_id ndb_struct_na_base_pair _item.mandatory_code yes _item_type.code line save_ save__ndb_struct_na_base_pair.i_label_asym_id _item_description.description ; Describes the asym id of the i-th base in the base pair. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair.i_label_asym_id' _item.category_id ndb_struct_na_base_pair _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair.i_label_asym_id' _item_linked.parent_name '_atom_site.label_asym_id' save_ save__ndb_struct_na_base_pair.i_label_comp_id _item_description.description ; Describes the component id of the i-th base in the base pair. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair.i_label_comp_id' _item.category_id ndb_struct_na_base_pair _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair.i_label_comp_id' _item_linked.parent_name '_atom_site.label_comp_id' save_ save__ndb_struct_na_base_pair.i_label_seq_id _item_description.description ; Describes the sequence number of the i-th base in the base pair. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair.i_label_seq_id' _item.category_id ndb_struct_na_base_pair _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair.i_label_seq_id' _item_linked.parent_name '_atom_site.label_seq_id' save_ save__ndb_struct_na_base_pair.i_symmetry _item_description.description ; Describes the symmetry operation that should be applied to the coordinates of the i-th base to generate the first partner in the base pair. ; _item.name '_ndb_struct_na_base_pair.i_symmetry' _item.category_id ndb_struct_na_base_pair _item.mandatory_code no _item_default.value 1_555 _item_type.code symop loop_ _item_examples.case _item_examples.detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' save_ save__ndb_struct_na_base_pair.j_label_asym_id _item_description.description ; Describes the asym id of the j-th base in the base pair. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair.j_label_asym_id' _item.category_id ndb_struct_na_base_pair _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair.j_label_asym_id' _item_linked.parent_name '_atom_site.label_asym_id' save_ save__ndb_struct_na_base_pair.j_label_comp_id _item_description.description ; Describes the component id of the j-th base in the base pair. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair.j_label_comp_id' _item.category_id ndb_struct_na_base_pair _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair.j_label_comp_id' _item_linked.parent_name '_atom_site.label_comp_id' save_ save__ndb_struct_na_base_pair.j_label_seq_id _item_description.description ; Describes the sequence number of the j-th base in the base pair. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair.j_label_seq_id' _item.category_id ndb_struct_na_base_pair _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair.j_label_seq_id' _item_linked.parent_name '_atom_site.label_seq_id' save_ save__ndb_struct_na_base_pair.j_symmetry _item_description.description ; Describes the symmetry operation that should be applied to the coordinates of the j-th base to generate the second partner in the base pair. ; _item.name '_ndb_struct_na_base_pair.j_symmetry' _item.category_id ndb_struct_na_base_pair _item.mandatory_code no _item_default.value 1_555 _item_type.code symop loop_ _item_examples.case _item_examples.detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' save_ save__ndb_struct_na_base_pair.i_auth_asym_id _item_description.description ; Describes the asym id of the i-th base in the base pair. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair.i_auth_asym_id' _item.category_id ndb_struct_na_base_pair _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair.i_auth_asym_id' _item_linked.parent_name '_atom_site.auth_asym_id' save_ save__ndb_struct_na_base_pair.i_auth_seq_id _item_description.description ; Describes the sequence number of the i-th base in the base pair. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair.i_auth_seq_id' _item.category_id ndb_struct_na_base_pair _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair.i_auth_seq_id' _item_linked.parent_name '_atom_site.auth_seq_id' save_ save__ndb_struct_na_base_pair.i_PDB_ins_code _item_description.description ; Describes the PDB insertion code of the i-th base in the base pair. This data item is a pointer to _atom_site.pdbx_PDB_ins_code in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair.i_PDB_ins_code' _item.category_id ndb_struct_na_base_pair _item.mandatory_code yes _item_type.code code # _item_linked.child_name '_ndb_struct_na_base_pair.i_PDB_ins_code' # _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' save_ save__ndb_struct_na_base_pair.j_auth_asym_id _item_description.description ; Describes the asym id of the j-th base in the base pair. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair.j_auth_asym_id' _item.category_id ndb_struct_na_base_pair _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair.j_auth_asym_id' _item_linked.parent_name '_atom_site.auth_asym_id' save_ save__ndb_struct_na_base_pair.j_auth_seq_id _item_description.description ; Describes the sequence number of the j-th base in the base pair. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair.j_auth_seq_id' _item.category_id ndb_struct_na_base_pair _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair.j_auth_seq_id' _item_linked.parent_name '_atom_site.auth_seq_id' save_ save__ndb_struct_na_base_pair.j_PDB_ins_code _item_description.description ; Describes the PDB insertion code of the j-th base in the base pair. This data item is a pointer to _atom_site.pdbx_PDB_ins_code in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair.j_PDB_ins_code' _item.category_id ndb_struct_na_base_pair _item.mandatory_code yes _item_type.code code # _item_linked.child_name '_ndb_struct_na_base_pair.j_PDB_ins_code' # _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' save_ save__ndb_struct_na_base_pair.shear _item_description.description ; The value of the base pair shear parameter. ; _item.name '_ndb_struct_na_base_pair.shear' _item.category_id ndb_struct_na_base_pair _item.mandatory_code no _item_type.code float save_ save__ndb_struct_na_base_pair.stretch _item_description.description ; The value of the base pair stretch parameter. ; _item.name '_ndb_struct_na_base_pair.stretch' _item.category_id ndb_struct_na_base_pair _item.mandatory_code no _item_type.code float save_ save__ndb_struct_na_base_pair.stagger _item_description.description ; The value of the base pair stagger parameter. ; _item.name '_ndb_struct_na_base_pair.stagger' _item.category_id ndb_struct_na_base_pair _item.mandatory_code no _item_type.code float save_ save__ndb_struct_na_base_pair.buckle _item_description.description ; The value of the base pair buckle parameter. ; _item.name '_ndb_struct_na_base_pair.buckle' _item.category_id ndb_struct_na_base_pair _item.mandatory_code no _item_type.code float save_ save__ndb_struct_na_base_pair.propeller _item_description.description ; The value of the base pair propeller parameter. ; _item.name '_ndb_struct_na_base_pair.propeller' _item.category_id ndb_struct_na_base_pair _item.mandatory_code no _item_type.code float save_ save__ndb_struct_na_base_pair.opening _item_description.description ; The value of the base pair opening parameter. ; _item.name '_ndb_struct_na_base_pair.opening' _item.category_id ndb_struct_na_base_pair _item.mandatory_code no _item_type.code float save_ save__ndb_struct_na_base_pair.hbond_type_12 _item_description.description ; Base pair classification of Westhoff and Leontis. ; _item.name '_ndb_struct_na_base_pair.hbond_type_12' _item.category_id ndb_struct_na_base_pair _item.mandatory_code no _item_type.code int save_ save__ndb_struct_na_base_pair.hbond_type_28 _item_description.description ; Base pair classification of Saenger ; _item.name '_ndb_struct_na_base_pair.hbond_type_28' _item.category_id ndb_struct_na_base_pair _item.mandatory_code no _item_type.code int save_ ################################## ## NDB_STRUCT_NA_BASE_PAIR_STEP ## ################################## save_ndb_struct_na_base_pair_step _category.description ; Data items in the NDB_STRUCT_NA_BASE_PAIR_STEP category record details of base pair step interactions. ; _category.id ndb_struct_na_base_pair_step _category.mandatory_code no loop_ _category_key.name '_ndb_struct_na_base_pair_step.model_number' '_ndb_struct_na_base_pair_step.i_label_comp_id_1' '_ndb_struct_na_base_pair_step.i_label_asym_id_1' '_ndb_struct_na_base_pair_step.i_label_seq_id_1' '_ndb_struct_na_base_pair_step.i_symmetry_1' '_ndb_struct_na_base_pair_step.j_label_comp_id_1' '_ndb_struct_na_base_pair_step.j_label_asym_id_1' '_ndb_struct_na_base_pair_step.j_label_seq_id_1' '_ndb_struct_na_base_pair_step.j_symmetry_1' '_ndb_struct_na_base_pair_step.i_label_comp_id_2' '_ndb_struct_na_base_pair_step.i_label_asym_id_2' '_ndb_struct_na_base_pair_step.i_label_seq_id_2' '_ndb_struct_na_base_pair_step.i_symmetry_2' '_ndb_struct_na_base_pair_step.j_label_comp_id_2' '_ndb_struct_na_base_pair_step.j_label_asym_id_2' '_ndb_struct_na_base_pair_step.j_label_seq_id_2' '_ndb_struct_na_base_pair_step.j_symmetry_2' loop_ _category_group.id 'inclusive_group' 'struct_group' 'ndb_group' loop_ _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _ndb_struct_na_base_pair_step.model_number _ndb_struct_na_base_pair_step.i_label_comp_id_1 _ndb_struct_na_base_pair_step.i_label_asym_id_1 _ndb_struct_na_base_pair_step.i_label_seq_id_1 _ndb_struct_na_base_pair_step.i_symmetry_1 _ndb_struct_na_base_pair_step.j_label_comp_id_1 _ndb_struct_na_base_pair_step.j_label_asym_id_1 _ndb_struct_na_base_pair_step.j_label_seq_id_1 _ndb_struct_na_base_pair_step.j_symmetry_1 _ndb_struct_na_base_pair_step.i_label_comp_id_2 _ndb_struct_na_base_pair_step.i_label_asym_id_2 _ndb_struct_na_base_pair_step.i_label_seq_id_2 _ndb_struct_na_base_pair_step.i_symmetry_2 _ndb_struct_na_base_pair_step.j_label_comp_id_2 _ndb_struct_na_base_pair_step.j_label_asym_id_2 _ndb_struct_na_base_pair_step.j_label_seq_id_2 _ndb_struct_na_base_pair_step.j_symmetry_2 _ndb_struct_na_base_pair_step.shift _ndb_struct_na_base_pair_step.slide _ndb_struct_na_base_pair_step.rise _ndb_struct_na_base_pair_step.tilt _ndb_struct_na_base_pair_step.roll _ndb_struct_na_base_pair_step.twist 1 G A 1 1_555 C A 8 7_555 G A 2 1_555 C A 7 7_555 0.369 -1.414 3.339 3.056 9.755 33.530 1 G A 2 1_555 C A 7 7_555 G A 3 1_555 C A 6 7_555 0.176 -1.672 3.371 -1.176 6.725 30.004 # ... ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__ndb_struct_na_base_pair_step.model_number _item_description.description ; Describes the model number of the the base pair step. This data item is a pointer to _atom_site.ndb_model in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair_step.model_number' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair_step.model_number' _item_linked.parent_name '_atom_site.pdbx_PDB_model_num' save_ save__ndb_struct_na_base_pair_step.step_number _item_description.description ; The sequence number of this step in the step sequence. ; _item.name '_ndb_struct_na_base_pair_step.step_number' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code yes _item_type.code int save_ save__ndb_struct_na_base_pair_step.step_name _item_description.description ; The text name of this step. ; _item.name '_ndb_struct_na_base_pair_step.step_name' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code yes _item_type.code line save_ save__ndb_struct_na_base_pair_step.i_label_asym_id_1 _item_description.description ; Describes the asym id of the i-th base in the first base pair of the step. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair_step.i_label_asym_id_1' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair_step.i_label_asym_id_1' _item_linked.parent_name '_atom_site.label_asym_id' save_ save__ndb_struct_na_base_pair_step.i_label_comp_id_1 _item_description.description ; Describes the component id of the i-th base in the first base pair of the step. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair_step.i_label_comp_id_1' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair_step.i_label_comp_id_1' _item_linked.parent_name '_atom_site.label_comp_id' save_ save__ndb_struct_na_base_pair_step.i_label_seq_id_1 _item_description.description ; Describes the sequence number of the i-th base in the first base pair of the step. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair_step.i_label_seq_id_1' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair_step.i_label_seq_id_1' _item_linked.parent_name '_atom_site.label_seq_id' save_ save__ndb_struct_na_base_pair_step.i_symmetry_1 _item_description.description ; Describes the symmetry operation that should be applied to the coordinates of the i-th base to generate the first partner in the first base pair of the step. ; _item.name '_ndb_struct_na_base_pair_step.i_symmetry_1' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code no _item_default.value 1_555 _item_type.code symop loop_ _item_examples.case _item_examples.detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' save_ save__ndb_struct_na_base_pair_step.j_label_asym_id_1 _item_description.description ; Describes the asym id of the j-th base in the first base pair of the step. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair_step.j_label_asym_id_1' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair_step.j_label_asym_id_1' _item_linked.parent_name '_atom_site.label_asym_id' save_ save__ndb_struct_na_base_pair_step.j_label_comp_id_1 _item_description.description ; Describes the component id of the j-th base in the first base pair of the step. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair_step.j_label_comp_id_1' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair_step.j_label_comp_id_1' _item_linked.parent_name '_atom_site.label_comp_id' save_ save__ndb_struct_na_base_pair_step.j_label_seq_id_1 _item_description.description ; Describes the sequence number of the j-th base in the first base pair of the step. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair_step.j_label_seq_id_1' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair_step.j_label_seq_id_1' _item_linked.parent_name '_atom_site.label_seq_id' save_ save__ndb_struct_na_base_pair_step.j_symmetry_1 _item_description.description ; Describes the symmetry operation that should be applied to the coordinates of the j-th base to generate the second partner in the first base pair of the step. ; _item.name '_ndb_struct_na_base_pair_step.j_symmetry_1' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code no _item_default.value 1_555 _item_type.code symop loop_ _item_examples.case _item_examples.detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' save_ save__ndb_struct_na_base_pair_step.i_label_asym_id_2 _item_description.description ; Describes the asym id of the i-th base in the second base pair of the step. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair_step.i_label_asym_id_2' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair_step.i_label_asym_id_2' _item_linked.parent_name '_atom_site.label_asym_id' save_ save__ndb_struct_na_base_pair_step.i_label_comp_id_2 _item_description.description ; Describes the component id of the i-th base in the second base pair of the step. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair_step.i_label_comp_id_2' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair_step.i_label_comp_id_2' _item_linked.parent_name '_atom_site.label_comp_id' save_ save__ndb_struct_na_base_pair_step.i_label_seq_id_2 _item_description.description ; Describes the sequence number of the i-th base in the second base pair of the step. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair_step.i_label_seq_id_2' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair_step.i_label_seq_id_2' _item_linked.parent_name '_atom_site.label_seq_id' save_ save__ndb_struct_na_base_pair_step.i_symmetry_2 _item_description.description ; Describes the symmetry operation that should be applied to the coordinates of the i-th base to generate the first partner in the second base pair of the step. ; _item.name '_ndb_struct_na_base_pair_step.i_symmetry_2' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code no _item_default.value 1_555 _item_type.code symop loop_ _item_examples.case _item_examples.detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' save_ save__ndb_struct_na_base_pair_step.j_label_asym_id_2 _item_description.description ; Describes the asym id of the j-th base in the second base pair of the step. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair_step.j_label_asym_id_2' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair_step.j_label_asym_id_2' _item_linked.parent_name '_atom_site.label_asym_id' save_ save__ndb_struct_na_base_pair_step.j_label_comp_id_2 _item_description.description ; Describes the component id of the j-th base in the second base pair of the step. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair_step.j_label_comp_id_2' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair_step.j_label_comp_id_2' _item_linked.parent_name '_atom_site.label_comp_id' save_ save__ndb_struct_na_base_pair_step.j_label_seq_id_2 _item_description.description ; Describes the sequence number of the j-th base in the second base pair of the step. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair_step.j_label_seq_id_2' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair_step.j_label_seq_id_2' _item_linked.parent_name '_atom_site.label_seq_id' save_ save__ndb_struct_na_base_pair_step.j_symmetry_2 _item_description.description ; Describes the symmetry operation that should be applied to the coordinates of the j-th base to generate the second partner in the second base pair of the step. ; _item.name '_ndb_struct_na_base_pair_step.j_symmetry_2' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code no _item_default.value 1_555 _item_type.code symop loop_ _item_examples.case _item_examples.detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' save_ save__ndb_struct_na_base_pair_step.i_auth_asym_id_1 _item_description.description ; Describes the author's asym id of the i-th base in the first base pair of the step. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair_step.i_auth_asym_id_1' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair_step.i_auth_asym_id_1' _item_linked.parent_name '_atom_site.auth_asym_id' save_ save__ndb_struct_na_base_pair_step.i_auth_seq_id_1 _item_description.description ; Describes the author's sequence number of the i-th base in the first base pair of the step. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair_step.i_auth_seq_id_1' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair_step.i_auth_seq_id_1' _item_linked.parent_name '_atom_site.auth_seq_id' save_ save__ndb_struct_na_base_pair_step.i_PDB_ins_code_1 _item_description.description ; Describes the PDB insertion code of the i-th base in the first base pair of the step. This data item is a pointer to _atom_site.pdbx_PDB_ins_code in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair_step.i_PDB_ins_code_1' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code yes _item_type.code code # _item_linked.child_name '_ndb_struct_na_base_pair_step.i_PDB_ins_code_1' # _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' save_ save__ndb_struct_na_base_pair_step.j_auth_asym_id_1 _item_description.description ; Describes the author's asym id of the j-th base in the first base pair of the step. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair_step.j_auth_asym_id_1' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair_step.j_auth_asym_id_1' _item_linked.parent_name '_atom_site.auth_asym_id' save_ save__ndb_struct_na_base_pair_step.j_auth_seq_id_1 _item_description.description ; Describes the author's sequence number of the j-th base in the first base pair of the step. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair_step.j_auth_seq_id_1' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair_step.j_auth_seq_id_1' _item_linked.parent_name '_atom_site.auth_seq_id' save_ save__ndb_struct_na_base_pair_step.j_PDB_ins_code_1 _item_description.description ; Describes the PDB insertion code of the j-th base in the first base pair of the step. This data item is a pointer to _atom_site.pdbx_PDB_ins_code in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair_step.j_PDB_ins_code_1' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code yes _item_type.code code # _item_linked.child_name '_ndb_struct_na_base_pair_step.j_PDB_ins_code_1' # _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' save_ save__ndb_struct_na_base_pair_step.i_auth_asym_id_2 _item_description.description ; Describes the author's asym id of the i-th base in the second base pair of the step. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair_step.i_auth_asym_id_2' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair_step.i_auth_asym_id_2' _item_linked.parent_name '_atom_site.auth_asym_id' save_ save__ndb_struct_na_base_pair_step.i_auth_seq_id_2 _item_description.description ; Describes the author's sequence number of the i-th base in the second base pair of the step. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair_step.i_auth_seq_id_2' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair_step.i_auth_seq_id_2' _item_linked.parent_name '_atom_site.auth_seq_id' save_ save__ndb_struct_na_base_pair_step.i_PDB_ins_code_2 _item_description.description ; Describes the PDB insertion code of the i-th base in the second base pair of the step. This data item is a pointer to _atom_site.pdbx_PDB_ins_code in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair_step.i_PDB_ins_code_2' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code yes _item_type.code code # _item_linked.child_name '_ndb_struct_na_base_pair_step.i_PDB_ins_code_2' # _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' save_ save__ndb_struct_na_base_pair_step.j_auth_asym_id_2 _item_description.description ; Describes the author's asym id of the j-th base in the second base pair of the step. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair_step.j_auth_asym_id_2' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair_step.j_auth_asym_id_2' _item_linked.parent_name '_atom_site.auth_asym_id' save_ save__ndb_struct_na_base_pair_step.j_auth_seq_id_2 _item_description.description ; Describes the author's sequence number of the j-th base in the second base pair of the step. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair_step.j_auth_seq_id_2' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code yes _item_type.code code _item_linked.child_name '_ndb_struct_na_base_pair_step.j_auth_seq_id_2' _item_linked.parent_name '_atom_site.auth_seq_id' save_ save__ndb_struct_na_base_pair_step.j_PDB_ins_code_2 _item_description.description ; Describes the PDB insertion code of the j-th base in the second base pair of the step. This data item is a pointer to _atom_site.pdbx_PDB_ins_code in the ATOM_SITE category. ; _item.name '_ndb_struct_na_base_pair_step.j_PDB_ins_code_2' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code yes _item_type.code code # _item_linked.child_name '_ndb_struct_na_base_pair_step.j_PDB_ins_code_2' # _item_linked.parent_name '_atom_site.pdbx_PDB_ins_code' save_ save__ndb_struct_na_base_pair_step.shift _item_description.description ; The value of the base pair step shift parameter. ; _item.name '_ndb_struct_na_base_pair_step.shift' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code no _item_type.code float save_ save__ndb_struct_na_base_pair_step.slide _item_description.description ; The value of the base pair step slide parameter. ; _item.name '_ndb_struct_na_base_pair_step.slide' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code no _item_type.code float save_ save__ndb_struct_na_base_pair_step.rise _item_description.description ; The value of the base pair step rise parameter. ; _item.name '_ndb_struct_na_base_pair_step.rise' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code no _item_type.code float save_ save__ndb_struct_na_base_pair_step.tilt _item_description.description ; The value of the base pair step tilt parameter. ; _item.name '_ndb_struct_na_base_pair_step.tilt' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code no _item_type.code float save_ save__ndb_struct_na_base_pair_step.roll _item_description.description ; The value of the base pair step roll parameter. ; _item.name '_ndb_struct_na_base_pair_step.roll' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code no _item_type.code float save_ save__ndb_struct_na_base_pair_step.twist _item_description.description ; The value of the base pair step twist parameter. ; _item.name '_ndb_struct_na_base_pair_step.twist' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code no _item_type.code float save_ save__ndb_struct_na_base_pair_step.x_displacement _item_description.description ; The value of the base pair step X displacement parameter. ; _item.name '_ndb_struct_na_base_pair_step.x_displacement' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code no _item_type.code float save_ save__ndb_struct_na_base_pair_step.y_displacement _item_description.description ; The value of the base pair step Y displacement parameter. ; _item.name '_ndb_struct_na_base_pair_step.y_displacement' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code no _item_type.code float save_ save__ndb_struct_na_base_pair_step.helical_rise _item_description.description ; The value of the base pair step helical rise parameter. ; _item.name '_ndb_struct_na_base_pair_step.helical_rise' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code no _item_type.code float save_ save__ndb_struct_na_base_pair_step.inclination _item_description.description ; The value of the base pair step inclination parameter. ; _item.name '_ndb_struct_na_base_pair_step.inclination' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code no _item_type.code float save_ save__ndb_struct_na_base_pair_step.tip _item_description.description ; The value of the base pair step twist parameter. ; _item.name '_ndb_struct_na_base_pair_step.tip' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code no _item_type.code float save_ save__ndb_struct_na_base_pair_step.helical_twist _item_description.description ; The value of the base pair step helical twist parameter. ; _item.name '_ndb_struct_na_base_pair_step.helical_twist' _item.category_id ndb_struct_na_base_pair_step _item.mandatory_code no _item_type.code float save_ ## ## save_ndb_original_ndb_coordinates _category.description ; Placeholder category for PDB coordinate data. ; _category.id ndb_original_ndb_coordinates _category.mandatory_code no loop_ _category_key.name '_ndb_original_ndb_coordinates.coord_section' loop_ _category_group.id 'inclusive_group' 'ndb_group' save_ save__ndb_original_ndb_coordinates.coord_section _item_description.description ; ; _item.name '_ndb_original_ndb_coordinates.coord_section' _item.category_id ndb_original_ndb_coordinates _item.mandatory_code yes _item_type.code text save_ ## ## save_pdbx_entity_nonpoly _category.description ; ; _category.id pdbx_entity_nonpoly _category.mandatory_code no _category_key.name '_pdbx_entity_nonpoly.entity_id' loop_ _category_group.id 'inclusive_group' 'entity_group' 'rcsb_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_entity_nonpoly.entity_id _item_description.description ; This data item is a pointer to _entity.id in the ENTITY category. ; _item.name '_pdbx_entity_nonpoly.entity_id' _item.category_id pdbx_entity_nonpoly _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_entity_nonpoly.entity_id' _item_linked.parent_name '_entity.id' _item_aliases.alias_name '_rcsb_entity_nonpoly.entity_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_entity_nonpoly.comp_id _item_description.description ; This data item is a pointer to _chem_comp.id in the CHEM_COMP category. ; _item.name '_pdbx_entity_nonpoly.comp_id' _item.category_id pdbx_entity_nonpoly _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_entity_nonpoly.comp_id' _item_linked.parent_name '_chem_comp.id' _item_aliases.alias_name '_rcsb_entity_nonpoly.comp_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_entity_nonpoly.name _item_description.description ; A name for the non-polymer entity ; _item.name '_pdbx_entity_nonpoly.name' _item.category_id pdbx_entity_nonpoly _item.mandatory_code no _item_type.code text _item_aliases.alias_name '_rcsb_entity_nonpoly.name' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ # ### EOF mmcif_pdbx-def-4.dic ########################################################################### # # File: mmcif_pdbx-def-5.dic # # PDB Exchange Data Dictionary # # This data dictionary contains definitions used by wwPDB for data exchange # and data processing. # # Definition Section 5 # This section primarily contains extensions for # data extraction by PDB_EXTRACT. # ########################################################################### save_pdbx_phasing_dm _category.description ; Data items in the PDBX_PHASING_DM category record details about density modification ; _category.id pdbx_phasing_dm _category.mandatory_code no _category_key.name '_pdbx_phasing_dm.entry_id' loop_ _category_group.id 'inclusive_group' 'pdbx_group' 'phasing_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - density modification from resolve ; ; _pdbx_phasing_dm.entry_id ABC001 _pdbx_phasing_dm.fom_acentric 0.85 _pdbx_phasing_dm.fom_centric 0.79 _pdbx_phasing_dm.fom 0.85 _pdbx_phasing_dm.reflns_acentric 11351 _pdbx_phasing_dm.reflns_centric 1135 _pdbx_phasing_dm.reflns 12486 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_phasing_dm.entry_id _item_description.description ; The value of _pdbx_phasing_dm.entry_id identifies the data block. ; _item.name '_pdbx_phasing_dm.entry_id' _item.category_id pdbx_phasing_dm _item.mandatory_code yes _item_type.code code _item_aliases.alias_name '_pdbx_phasing_dm.entry_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_dm.method _item_description.description ; The value of _pdbx_phasing_dm.method identifies the method used for density modification ; _item.name '_pdbx_phasing_dm.method' _item.category_id pdbx_phasing_dm _item.mandatory_code no _item_type.code line _item_aliases.alias_name '_pdbx_phasing_dm.method' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_dm.mask_type _item_description.description ; The value of _pdbx_phasing_dm.mask_type identifies the type of mask used for density modification ; _item.name '_pdbx_phasing_dm.mask_type' _item.category_id pdbx_phasing_dm _item.mandatory_code no _item_type.code line _item_aliases.alias_name '_pdbx_phasing_dm.mask_type' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_dm.fom_acentric _item_description.description ; The value of _pdbx_phasing_dm.fom_acentric identifies the figure of merit for acentric data ; _item.name '_pdbx_phasing_dm.fom_acentric' _item.category_id pdbx_phasing_dm _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_dm.fom_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_dm.fom_centric _item_description.description ; The value of _pdbx_phasing_dm.fom_centric identifies the figure of merit for acentric data ; _item.name '_pdbx_phasing_dm.fom_centric' _item.category_id pdbx_phasing_dm _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_dm.fom_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_dm.fom _item_description.description ; The value of _pdbx_phasing_dm.fom identifies the figure of merit for all the data ; _item.name '_pdbx_phasing_dm.fom' _item.category_id pdbx_phasing_dm _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_dm.fom' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_dm.reflns_acentric _item_description.description ; The value of _pdbx_phasing_dm.reflns_acentric identifies the number of acentric reflections. ; _item.name '_pdbx_phasing_dm.reflns_acentric' _item.category_id pdbx_phasing_dm _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_pdbx_phasing_dm.reflns_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_dm.reflns_centric _item_description.description ; The value of _pdbx_phasing_dm.reflns_centric identifies the number of centric reflections. ; _item.name '_pdbx_phasing_dm.reflns_centric' _item.category_id pdbx_phasing_dm _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_pdbx_phasing_dm.reflns_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_dm.reflns _item_description.description ; The value of _pdbx_phasing_dm.reflns identifies the number of centric and acentric reflections. ; _item.name '_pdbx_phasing_dm.reflns' _item.category_id pdbx_phasing_dm _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_pdbx_phasing_dm.reflns' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_dm.delta_phi_initial _item_description.description ; The value of _pdbx_phasing_dm.delta_phi_initial identifies phase difference before density modification ; _item.name '_pdbx_phasing_dm.delta_phi_initial' _item.category_id pdbx_phasing_dm _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_dm.delta_phi_initial' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_dm.delta_phi_final _item_description.description ; The value of _pdbx_phasing_dm.delta_phi_final identifies phase difference after density modification ; _item.name '_pdbx_phasing_dm.delta_phi_final' _item.category_id pdbx_phasing_dm _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_dm.delta_phi_final' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### next category, _pdbx_phasing_dm_shell ### save_pdbx_phasing_dm_shell _category.description ; Data items in the PDBX_PHASING_DM_SHELL category record details about density modification in resolution shell. ; _category.id pdbx_phasing_dm_shell _category.mandatory_code no loop_ _category_key.name '_pdbx_phasing_dm_shell.d_res_low' '_pdbx_phasing_dm_shell.d_res_high' loop_ _category_group.id 'inclusive_group' 'pdbx_group' 'phasing_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - density modification with shells ; ; loop_ _pdbx_phasing_dm_shell.d_res_low _pdbx_phasing_dm_shell.d_res_high _pdbx_phasing_dm_shell.reflns _pdbx_phasing_dm_shell.fom _pdbx_phasing_dm_shell.delta_phi_final 100.00 7.73 502 0.879 24.7 7.73 6.24 506 0.857 29.2 6.24 5.50 504 0.838 29.2 5.50 5.02 502 0.851 25.3 5.02 4.67 503 0.831 22.7 # ....... ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_phasing_dm_shell.d_res_high _item_description.description ; The value of _pdbx_phasing_dm_shell.d_res_high identifies high resolution ; _item.name '_pdbx_phasing_dm_shell.d_res_high' _item.category_id pdbx_phasing_dm_shell _item.mandatory_code yes _item_type.code float _item_aliases.alias_name '_pdbx_phasing_dm_shell.d_res_high' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_dm_shell.d_res_low _item_description.description ; The value of _pdbx_phasing_dm_shell.d_res_low identifies low resolution ; _item.name '_pdbx_phasing_dm_shell.d_res_low' _item.category_id pdbx_phasing_dm_shell _item.mandatory_code yes _item_type.code float _item_aliases.alias_name '_pdbx_phasing_dm_shell.d_res_low' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_dm_shell.fom_acentric _item_description.description ; The value of _pdbx_phasing_dm_shell.fom_acentric identifies the figure of merit for acentric data with resolution shells ; _item.name '_pdbx_phasing_dm_shell.fom_acentric' _item.category_id pdbx_phasing_dm_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_dm_shell.fom_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_dm_shell.fom_centric _item_description.description ; The value of _pdbx_phasing_dm_shell.fom_centric identifies the figure of merit for centric data with resolution shells. ; _item.name '_pdbx_phasing_dm_shell.fom_centric' _item.category_id pdbx_phasing_dm_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_dm_shell.fom_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_dm_shell.fom _item_description.description ; The value of _pdbx_phasing_dm_shell.fom identifies the figure of merit for all the data with resolution shells. ; _item.name '_pdbx_phasing_dm_shell.fom' _item.category_id pdbx_phasing_dm_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_dm_shell.fom' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_dm_shell.reflns_acentric _item_description.description ; The value of _pdbx_phasing_dm_shell.reflns_acentric identifies the number of acentric reflections with resolution shells. ; _item.name '_pdbx_phasing_dm_shell.reflns_acentric' _item.category_id pdbx_phasing_dm_shell _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_pdbx_phasing_dm_shell.reflns_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_dm_shell.reflns_centric _item_description.description ; The value of _pdbx_phasing_dm_shell.reflns_centric identifies the number of centric reflections with resolution shells. ; _item.name '_pdbx_phasing_dm_shell.reflns_centric' _item.category_id pdbx_phasing_dm_shell _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_pdbx_phasing_dm_shell.reflns_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_dm_shell.reflns _item_description.description ; The value of _pdbx_phasing_dm_shell.reflns identifies the number of centric and acentric reflections with resolution shells. ; _item.name '_pdbx_phasing_dm_shell.reflns' _item.category_id pdbx_phasing_dm_shell _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_pdbx_phasing_dm_shell.reflns' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_dm_shell.delta_phi_initial _item_description.description ; The value of _pdbx_phasing_dm_shell.delta_phi_initial identifies phase difference before density modification with resolution shells. ; _item.name '_pdbx_phasing_dm_shell.delta_phi_initial' _item.category_id pdbx_phasing_dm_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_dm_shell.delta_phi_initial' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_dm_shell.delta_phi_final _item_description.description ; The value of _pdbx_phasing_dm_shell.delta_phi_final identifies phase difference after density modification with resolution shells. ; _item.name '_pdbx_phasing_dm_shell.delta_phi_final' _item.category_id pdbx_phasing_dm_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_dm_shell.delta_phi_final' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MAD.pdbx_d_res_low _item_description.description ; _phasing_MAD.pdbx_d_res_low records the lowest resolution for MAD phasing. ; _item.name '_phasing_MAD.pdbx_d_res_low' _item.category_id phasing_MAD _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MAD.pdbx_d_res_low' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MAD.pdbx_d_res_high _item_description.description ; _phasing_MAD.pdbx_d_res_high records the highest resolution for MAD phasing. ; _item.name '_phasing_MAD.pdbx_d_res_high' _item.category_id phasing_MAD _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MAD.pdbx_d_res_high' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MAD.pdbx_reflns_acentric _item_description.description ; _phasing_MAD.pdbx_reflns_acentric records the number of acentric reflections for MAD phasing. ; _item.name '_phasing_MAD.pdbx_reflns_acentric' _item.category_id phasing_MAD _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_phasing_MAD.pdbx_reflns_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MAD.pdbx_reflns_centric _item_description.description ; _phasing_MAD.pdbx_reflns_centric records the number of centric reflections for MAD phasing. ; _item.name '_phasing_MAD.pdbx_reflns_centric' _item.category_id phasing_MAD _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_phasing_MAD.pdbx_reflns_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MAD.pdbx_reflns _item_description.description ; _phasing_MAD.pdbx_reflns records the number of reflections used for MAD phasing. ; _item.name '_phasing_MAD.pdbx_reflns' _item.category_id phasing_MAD _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_phasing_MAD.pdbx_reflns' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MAD.pdbx_fom_acentric _item_description.description ; _phasing_MAD.pdbx_fom_acentric records the figure of merit using acentric data for MAD phasing. ; _item.name '_phasing_MAD.pdbx_fom_acentric' _item.category_id phasing_MAD _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MAD.pdbx_fom_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MAD.pdbx_fom_centric _item_description.description ; _phasing_MAD.pdbx_fom_centric records the figure of merit using centric data for MAD phasing. ; _item.name '_phasing_MAD.pdbx_fom_centric' _item.category_id phasing_MAD _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MAD.pdbx_fom_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MAD.pdbx_fom _item_description.description ; _phasing_MAD.pdbx_fom records the figure of merit for MAD phasing. ; _item.name '_phasing_MAD.pdbx_fom' _item.category_id phasing_MAD _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MAD.pdbx_fom' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MAD.pdbx_R_cullis_centric _item_description.description ; _phasing_MAD.pdbx_R_cullis_centric records R_cullis using centric data for MAD phasing. ; _item.name '_phasing_MAD.pdbx_R_cullis_centric' _item.category_id phasing_MAD _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MAD.pdbx_R_cullis_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MAD.pdbx_R_cullis_acentric _item_description.description ; _phasing_MAD.pdbx_R_cullis_acentric records R_cullis using acentric data for MAD phasing. ; _item.name '_phasing_MAD.pdbx_R_cullis_acentric' _item.category_id phasing_MAD _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MAD.pdbx_R_cullis_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MAD.pdbx_R_cullis _item_description.description ; _phasing_MAD.pdbx_R_cullis records R_cullis for MAD phasing. ; _item.name '_phasing_MAD.pdbx_R_cullis' _item.category_id phasing_MAD _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MAD.pdbx_R_cullis' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MAD.pdbx_R_kraut_centric _item_description.description ; _phasing_MAD.pdbx_R_kraut_centric records R_kraut using centric data for MAD phasing. ; _item.name '_phasing_MAD.pdbx_R_kraut_centric' _item.category_id phasing_MAD _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MAD.pdbx_R_kraut_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MAD.pdbx_R_kraut_acentric _item_description.description ; _phasing_MAD.pdbx_R_kraut_acentric records R_kraut using acentric data for MAD phasing. ; _item.name '_phasing_MAD.pdbx_R_kraut_acentric' _item.category_id phasing_MAD _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MAD.pdbx_R_kraut_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MAD.pdbx_R_kraut _item_description.description ; _phasing_MAD.pdbx_R_kraut records R_kraut for MAD phasing. ; _item.name '_phasing_MAD.pdbx_R_kraut' _item.category_id phasing_MAD _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MAD.pdbx_R_kraut' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MAD.pdbx_loc_centric _item_description.description ; _phasing_MAD.pdbx_loc_centric records lack of closure using centric data for MAD phasing. ; _item.name '_phasing_MAD.pdbx_loc_centric' _item.category_id phasing_MAD _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MAD.pdbx_loc_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MAD.pdbx_loc_acentric _item_description.description ; _phasing_MAD.pdbx_loc_acentric records lack of closure using acentric data for MAD phasing. ; _item.name '_phasing_MAD.pdbx_loc_acentric' _item.category_id phasing_MAD _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MAD.pdbx_loc_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MAD.pdbx_loc _item_description.description ; _phasing_MAD.pdbx_loc records lack of closure for MAD phasing. ; _item.name '_phasing_MAD.pdbx_loc' _item.category_id phasing_MAD _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MAD.pdbx_loc' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MAD.pdbx_power_centric _item_description.description ; _phasing_MAD.pdbx_power_centric records phasing power using centric data for MAD phasing. ; _item.name '_phasing_MAD.pdbx_power_centric' _item.category_id phasing_MAD _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MAD.pdbx_power_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MAD.pdbx_power_acentric _item_description.description ; _phasing_MAD.pdbx_power_acentric records phasing power using acentric data for MAD phasing. ; _item.name '_phasing_MAD.pdbx_power_acentric' _item.category_id phasing_MAD _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MAD.pdbx_power_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MAD.pdbx_power _item_description.description ; _phasing_MAD.pdbx_power records phasing power for MAD phasing. ; _item.name '_phasing_MAD.pdbx_power' _item.category_id phasing_MAD _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MAD.pdbx_power' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MAD.pdbx_number_data_sets _item_description.description ; _phasing_MAD.pdbx_loc records the number of data sets used for MAD phasing. ; _item.name '_phasing_MAD.pdbx_number_data_sets' _item.category_id phasing_MAD _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_phasing_MAD.pdbx_number_data_sets' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MAD.pdbx_anom_scat_method _item_description.description ; _phasing_MAD.pdbx_anom_scat_method records the method used to locate anomalous scatterers for MAD phasing. ; _item.name '_phasing_MAD.pdbx_anom_scat_method' _item.category_id phasing_MAD _item.mandatory_code no _item_type.code text _item_aliases.alias_name '_phasing_MAD.pdbx_anom_scat_method' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## save_pdbx_phasing_MAD_shell _category.description ; Data items in the PDBX_PHASING_MAD_SHELL category record details about the phasing of the structure, when methods involving multiple anomalous dispersion techniques are involved (note: the values are overall, but broken down into shells of resolution) ; _category.id pdbx_phasing_MAD_shell _category.mandatory_code no loop_ _category_key.name '_pdbx_phasing_MAD_shell.d_res_low' '_pdbx_phasing_MAD_shell.d_res_high' loop_ _category_group.id 'inclusive_group' 'pdbx_group' 'phasing_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; loop_ _pdbx_phasing_MAD_shell.d_res_low _pdbx_phasing_MAD_shell.d_res_high _pdbx_phasing_MAD_shell.reflns_acentric _pdbx_phasing_MAD_shell.fom_acentric _pdbx_phasing_MAD_shell.reflns_centric _pdbx_phasing_MAD_shell.fom_centric 22.60 7.77 64 0.886 23 0.641 7.77 5.67 132 0.863 32 0.642 5.67 4.68 182 0.842 27 0.737 4.68 4.07 209 0.789 24 0.682 4.07 3.65 246 0.772 27 0.633 3.65 3.34 260 0.752 31 0.700 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_phasing_MAD_shell.d_res_low _item_description.description ; _pdbx_phasing_MAD_shell.d_res_low records the lower resolution for the shell. ; _item.name '_pdbx_phasing_MAD_shell.d_res_low' _item.category_id pdbx_phasing_MAD_shell _item.mandatory_code yes _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_shell.d_res_low' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_shell.d_res_high _item_description.description ; _pdbx_phasing_MAD_shell.d_res_high records the higher resolution for the shell. ; _item.name '_pdbx_phasing_MAD_shell.d_res_high' _item.category_id pdbx_phasing_MAD_shell _item.mandatory_code yes _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_shell.d_res_high' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_shell.reflns_acentric _item_description.description ; _pdbx_phasing_MAD_shell.reflns_acentric records the number of acentric reflections for MAD phasing. ; _item.name '_pdbx_phasing_MAD_shell.reflns_acentric' _item.category_id pdbx_phasing_MAD_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_shell.reflns_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_shell.reflns_centric _item_description.description ; _pdbx_phasing_MAD_shell.reflns_centric records the number of centric reflections for MAD phasing. ; _item.name '_pdbx_phasing_MAD_shell.reflns_centric' _item.category_id pdbx_phasing_MAD_shell _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_pdbx_phasing_MAD_shell.reflns_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_shell.reflns _item_description.description ; _pdbx_phasing_MAD_shell.reflns records the number of reflections used for MAD phasing. ; _item.name '_pdbx_phasing_MAD_shell.reflns' _item.category_id pdbx_phasing_MAD_shell _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_pdbx_phasing_MAD_shell.reflns' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_shell.fom_acentric _item_description.description ; _pdbx_phasing_MAD_shell.fom_acentric records the figure of merit using acentric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_shell.fom_acentric' _item.category_id pdbx_phasing_MAD_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_shell.fom_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_shell.fom_centric _item_description.description ; _pdbx_phasing_MAD_shell.fom_centric records the figure of merit using centric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_shell.fom_centric' _item.category_id pdbx_phasing_MAD_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_shell.fom_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_shell.fom _item_description.description ; _pdbx_phasing_MAD_shell.fom records the figure of merit for MAD phasing. ; _item.name '_pdbx_phasing_MAD_shell.fom' _item.category_id pdbx_phasing_MAD_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_shell.fom' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_shell.R_cullis_centric _item_description.description ; _pdbx_phasing_MAD_shell.R_cullis_centric records R_cullis using centric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_shell.R_cullis_centric' _item.category_id pdbx_phasing_MAD_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_shell.R_cullis_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_shell.R_cullis_acentric _item_description.description ; _pdbx_phasing_MAD_shell.R_cullis_acentric records R_cullis using acentric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_shell.R_cullis_acentric' _item.category_id pdbx_phasing_MAD_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_shell.R_cullis_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_shell.R_cullis _item_description.description ; _pdbx_phasing_MAD_shell.R_cullis records R_cullis for MAD phasing. ; _item.name '_pdbx_phasing_MAD_shell.R_cullis' _item.category_id pdbx_phasing_MAD_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_shell.R_cullis' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_shell.R_kraut_centric _item_description.description ; _pdbx_phasing_MAD_shell.R_kraut_centric records R_kraut using centric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_shell.R_kraut_centric' _item.category_id pdbx_phasing_MAD_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_shell.R_kraut_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_shell.R_kraut_acentric _item_description.description ; _pdbx_phasing_MAD_shell.r_kraut_acentric records R_kraut using acentric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_shell.R_kraut_acentric' _item.category_id pdbx_phasing_MAD_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_shell.R_kraut_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_shell.R_kraut _item_description.description ; _pdbx_phasing_MAD_shell.R_kraut records R_kraut for MAD phasing. ; _item.name '_pdbx_phasing_MAD_shell.R_kraut' _item.category_id pdbx_phasing_MAD_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_shell.R_kraut' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_shell.loc_centric _item_description.description ; _pdbx_phasing_MAD_shell.loc_centric records lack of closure using centric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_shell.loc_centric' _item.category_id pdbx_phasing_MAD_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_shell.loc_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_shell.loc_acentric _item_description.description ; _pdbx_phasing_MAD_shell.loc_acentric records lack of closure using acentric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_shell.loc_acentric' _item.category_id pdbx_phasing_MAD_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_shell.loc_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_shell.loc _item_description.description ; _pdbx_phasing_MAD_shell.loc records lack of closure for MAD phasing. ; _item.name '_pdbx_phasing_MAD_shell.loc' _item.category_id pdbx_phasing_MAD_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_shell.loc' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_shell.power_centric _item_description.description ; _pdbx_phasing_MAD_shell.power_centric records phasing powe using centric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_shell.power_centric' _item.category_id pdbx_phasing_MAD_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_shell.power_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_shell.power_acentric _item_description.description ; _pdbx_phasing_MAD_shell.power_acentric records phasing powe using acentric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_shell.power_acentric' _item.category_id pdbx_phasing_MAD_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_shell.power_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_shell.power _item_description.description ; _pdbx_phasing_MAD_shell.loc records phasing power for MAD phasing. ; _item.name '_pdbx_phasing_MAD_shell.power' _item.category_id pdbx_phasing_MAD_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_shell.power' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### next category, _pdbx_phasing_MAD_set ### save_pdbx_phasing_MAD_set _category.description ; Record details about each phasing set: (Note: the phasing set is different from data set. for example: if there are three data sets, the inflection point (IP), the peak (PK) and the high remote (HR), the combination of the phasing set will be IP_iso, PK_iso (the isomorphous repleacement with HR as 'native'), IP_ano, PK_ano and HR_ano (the anomalous difference with itself). Therefore, there are five set used for phasing. ; _category.id pdbx_phasing_MAD_set _category.mandatory_code no _category_key.name '_pdbx_phasing_MAD_set.id' loop_ _category_group.id 'inclusive_group' 'pdbx_group' 'phasing_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - three wavelengths ; ; loop_ _pdbx_phasing_MAD_set.id _pdbx_phasing_MAD_set.d_res_low _pdbx_phasing_MAD_set.d_res_high _pdbx_phasing_MAD_set.reflns_acentric _pdbx_phasing_MAD_set.reflns_centric _pdbx_phasing_MAD_set.R_cullis_acentric _pdbx_phasing_MAD_set.R_cullis_centric ISO_1 22.60 2.00 5387 471 0.000 0.000 ISO_2 22.60 2.00 5365 469 0.803 0.718 ISO_3 22.60 2.00 5317 460 0.658 0.500 ANO_1 22.60 2.00 5278 0 0.841 0.000 ANO_2 22.60 2.00 5083 0 0.649 0.000 ANO_3 22.60 2.00 5329 0 0.829 0.000 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_phasing_MAD_set.id _item_description.description ; _pdbx_phasing_MAD_set.id records phase set name for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set.id' _item.category_id pdbx_phasing_MAD_set _item.mandatory_code yes _item_type.code code _item_aliases.alias_name '_pdbx_phasing_MAD_set.id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set.d_res_low _item_description.description ; _pdbx_phasing_MAD_set.d_res_low records the lowerest resolution for phasing set. ; _item.name '_pdbx_phasing_MAD_set.d_res_low' _item.category_id pdbx_phasing_MAD_set _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set.d_res_low' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set.d_res_high _item_description.description ; _pdbx_phasing_MAD_set.d_res_high records the highest resolution for the phasing set. ; _item.name '_pdbx_phasing_MAD_set.d_res_high' _item.category_id pdbx_phasing_MAD_set _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set.d_res_high' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set.number_of_sites _item_description.description ; _pdbx_phasing_MAD_set.number_of_sites records the number of site refined for the phasing set. ; _item.name '_pdbx_phasing_MAD_set.number_of_sites' _item.category_id pdbx_phasing_MAD_set _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_pdbx_phasing_MAD_set.number_of_sites' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set.reflns_acentric _item_description.description ; _pdbx_phasing_MAD_set.reflns_acentric records the number of acentric reflections for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set.reflns_acentric' _item.category_id pdbx_phasing_MAD_set _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_pdbx_phasing_MAD_set.reflns_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set.reflns_centric _item_description.description ; _pdbx_phasing_MAD_set.reflns_centric records the number of centric reflections for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set.reflns_centric' _item.category_id pdbx_phasing_MAD_set _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_pdbx_phasing_MAD_set.reflns_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set.reflns _item_description.description ; _pdbx_phasing_MAD_set.reflns records the number of reflections used for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set.reflns' _item.category_id pdbx_phasing_MAD_set _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_pdbx_phasing_MAD_set.reflns' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set.fom_acentric _item_description.description ; _pdbx_phasing_MAD_set.fom_acentric records the figure of merit using acentric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set.fom_acentric' _item.category_id pdbx_phasing_MAD_set _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set.fom_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set.fom_centric _item_description.description ; _pdbx_phasing_MAD_set.fom_centric records the figure of merit using centric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set.fom_centric' _item.category_id pdbx_phasing_MAD_set _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set.fom_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set.fom _item_description.description ; _pdbx_phasing_MAD_set.fom records the figure of merit for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set.fom' _item.category_id pdbx_phasing_MAD_set _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set.fom' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set.R_cullis_centric _item_description.description ; _pdbx_phasing_MAD_set.R_cullis_centric records R_cullis using centric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set.R_cullis_centric' _item.category_id pdbx_phasing_MAD_set _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set.R_cullis_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set.R_cullis_acentric _item_description.description ; _pdbx_phasing_MAD_set.R_cullis_acentric records R_cullis using acentric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set.R_cullis_acentric' _item.category_id pdbx_phasing_MAD_set _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set.R_cullis_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set.R_cullis _item_description.description ; _pdbx_phasing_MAD_set.R_cullis records R_cullis for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set.R_cullis' _item.category_id pdbx_phasing_MAD_set _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set.R_cullis' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set.R_kraut_centric _item_description.description ; _pdbx_phasing_MAD_set.R_kraut_centric records r_kraut using centric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set.R_kraut_centric' _item.category_id pdbx_phasing_MAD_set _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set.R_kraut_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set.R_kraut_acentric _item_description.description ; _pdbx_phasing_MAD_set.r_kraut_acentric records r_kraut using acentric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set.R_kraut_acentric' _item.category_id pdbx_phasing_MAD_set _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set.R_kraut_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set.R_kraut _item_description.description ; _pdbx_phasing_MAD_set.R_kraut records R_kraut for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set.R_kraut' _item.category_id pdbx_phasing_MAD_set _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set.R_kraut' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set.loc_centric _item_description.description ; _pdbx_phasing_MAD_set.loc_centric records lack of closure using centric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set.loc_centric' _item.category_id pdbx_phasing_MAD_set _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set.loc_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set.loc_acentric _item_description.description ; _pdbx_phasing_MAD_set.loc_acentric records lack of closure using acentric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set.loc_acentric' _item.category_id pdbx_phasing_MAD_set _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set.loc_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set.loc _item_description.description ; _pdbx_phasing_MAD_set.loc records lack of closure for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set.loc' _item.category_id pdbx_phasing_MAD_set _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set.loc' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set.power_centric _item_description.description ; _pdbx_phasing_MAD_set.power_centric records phasing powe using centric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set.power_centric' _item.category_id pdbx_phasing_MAD_set _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set.power_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set.power_acentric _item_description.description ; _pdbx_phasing_MAD_set.power_acentric records phasing powe using acentric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set.power_acentric' _item.category_id pdbx_phasing_MAD_set _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set.power_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set.power _item_description.description ; _pdbx_phasing_MAD_set.power records phasing power for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set.power' _item.category_id pdbx_phasing_MAD_set _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set.power' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### next category, _pdbx_phasing_MAD_set_shell ### save_pdbx_phasing_MAD_set_shell _category.description ; The same as category pdbx_phasing_MAD_set, but broken into shells. ; _category.id pdbx_phasing_MAD_set_shell _category.mandatory_code no loop_ _category_key.name '_pdbx_phasing_MAD_set_shell.id' '_pdbx_phasing_MAD_set_shell.d_res_low' '_pdbx_phasing_MAD_set_shell.d_res_high' loop_ _category_group.id 'inclusive_group' 'pdbx_group' 'phasing_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - three wavelengths (SHARP example) ; ; loop_ _pdbx_phasing_MAD_set_shell.id _pdbx_phasing_MAD_set_shell.d_res_low _pdbx_phasing_MAD_set_shell.d_res_high _pdbx_phasing_MAD_set_shell.reflns_acentric _pdbx_phasing_MAD_set_shell.reflns_centric _pdbx_phasing_MAD_set_shell.R_cullis_acentric _pdbx_phasing_MAD_set_shell.R_cullis_centric _pdbx_phasing_MAD_set_shell.power_acentric _pdbx_phasing_MAD_set_shell.power_centric ISO_1 22.60 7.77 64 23 0.000 0.000 0.000 0.000 ISO_1 7.77 5.67 130 32 0.000 0.000 0.000 0.000 ISO_1 5.67 4.68 182 27 0.000 0.000 0.000 0.000 ISO_1 4.68 4.07 207 24 0.000 0.000 0.000 0.000 ANO_1 22.60 7.77 62 0 0.610 0.000 1.804 0.000 ANO_1 7.77 5.67 129 0 0.532 0.000 2.382 0.000 ANO_1 5.67 4.68 178 0 0.673 0.000 1.858 0.000 ANO_1 4.68 4.07 204 0 0.755 0.000 1.605 0.000 # ......... ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_phasing_MAD_set_shell.id _item_description.description ; _pdbx_phasing_MAD_set_shell.id records phase set name for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_shell.id' _item.category_id pdbx_phasing_MAD_set_shell _item.mandatory_code yes _item_type.code code _item_aliases.alias_name '_pdbx_phasing_MAD_set_shell.id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_shell.d_res_low _item_description.description ; _pdbx_phasing_MAD_set_shell.d_res_low records the lowerest resolution for phasing set. ; _item.name '_pdbx_phasing_MAD_set_shell.d_res_low' _item.category_id pdbx_phasing_MAD_set_shell _item.mandatory_code yes _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_shell.d_res_low' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_shell.d_res_high _item_description.description ; _pdbx_phasing_MAD_set_shell.d_res_high records the highest resolution for the phasing set. ; _item.name '_pdbx_phasing_MAD_set_shell.d_res_high' _item.category_id pdbx_phasing_MAD_set_shell _item.mandatory_code yes _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_shell.d_res_high' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_shell.reflns_acentric _item_description.description ; _pdbx_phasing_MAD_set_shell.reflns_acentric records the number of acentric reflections for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_shell.reflns_acentric' _item.category_id pdbx_phasing_MAD_set_shell _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_pdbx_phasing_MAD_set_shell.reflns_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_shell.reflns_centric _item_description.description ; _pdbx_phasing_MAD_set_shell.reflns_centric records the number of centric reflections for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_shell.reflns_centric' _item.category_id pdbx_phasing_MAD_set_shell _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_pdbx_phasing_MAD_set_shell.reflns_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_shell.reflns _item_description.description ; _pdbx_phasing_MAD_set_shell.reflns records the number of reflections used for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_shell.reflns' _item.category_id pdbx_phasing_MAD_set_shell _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_pdbx_phasing_MAD_set_shell.reflns' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_shell.fom_acentric _item_description.description ; _pdbx_phasing_MAD_set_shell.fom_acentric records the figure of merit using acentric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_shell.fom_acentric' _item.category_id pdbx_phasing_MAD_set_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_shell.fom_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_shell.fom_centric _item_description.description ; _pdbx_phasing_MAD_set_shell.fom_centric records the figure of merit using centric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_shell.fom_centric' _item.category_id pdbx_phasing_MAD_set_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_shell.fom_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_shell.fom _item_description.description ; _pdbx_phasing_MAD_set_shell.fom records the figure of merit for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_shell.fom' _item.category_id pdbx_phasing_MAD_set_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_shell.fom' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_shell.R_cullis_centric _item_description.description ; _pdbx_phasing_MAD_set_shell.R_cullis_centric records R_cullis using centric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_shell.R_cullis_centric' _item.category_id pdbx_phasing_MAD_set_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_shell.R_cullis_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_shell.R_cullis_acentric _item_description.description ; _pdbx_phasing_MAD_set_shell.R_cullis_acentric records R_cullis using acentric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_shell.R_cullis_acentric' _item.category_id pdbx_phasing_MAD_set_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_shell.R_cullis_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_shell.R_cullis _item_description.description ; _pdbx_phasing_MAD_set_shell.R_cullis records R_cullis for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_shell.R_cullis' _item.category_id pdbx_phasing_MAD_set_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_shell.R_cullis' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_shell.R_kraut_centric _item_description.description ; _pdbx_phasing_MAD_set_shell.R_kraut_centric records R_kraut using centric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_shell.R_kraut_centric' _item.category_id pdbx_phasing_MAD_set_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_shell.R_kraut_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_shell.R_kraut_acentric _item_description.description ; _pdbx_phasing_MAD_set_shell.R_kraut_acentric records R_kraut using acentric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_shell.R_kraut_acentric' _item.category_id pdbx_phasing_MAD_set_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_shell.R_kraut_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_shell.R_kraut _item_description.description ; _pdbx_phasing_MAD_set_shell.R_kraut records R_kraut for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_shell.R_kraut' _item.category_id pdbx_phasing_MAD_set_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_shell.R_kraut' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_shell.loc_centric _item_description.description ; _pdbx_phasing_MAD_set_shell.loc_centric records lack of closure using centric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_shell.loc_centric' _item.category_id pdbx_phasing_MAD_set_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_shell.loc_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_shell.loc_acentric _item_description.description ; _pdbx_phasing_MAD_set_shell.loc_acentric records lack of closure using acentric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_shell.loc_acentric' _item.category_id pdbx_phasing_MAD_set_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_shell.loc_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_shell.loc _item_description.description ; _pdbx_phasing_MAD_set_shell.loc records lack of closure for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_shell.loc' _item.category_id pdbx_phasing_MAD_set_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_shell.loc' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_shell.power_centric _item_description.description ; _pdbx_phasing_MAD_set_shell.power_centric records phasing power using centric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_shell.power_centric' _item.category_id pdbx_phasing_MAD_set_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_shell.power_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_shell.power_acentric _item_description.description ; _pdbx_phasing_MAD_set_shell.power_acentric records phasing power using acentric data for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_shell.power_acentric' _item.category_id pdbx_phasing_MAD_set_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_shell.power_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_shell.power _item_description.description ; _pdbx_phasing_MAD_set_shell.power records phasing power for MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_shell.power' _item.category_id pdbx_phasing_MAD_set_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_shell.power' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### next category, _pdbx_phasing_MAD_set_site ### save_pdbx_phasing_MAD_set_site _category.description ; record the details (coordinates etc.) of anomalous scatters. ; _category.id pdbx_phasing_MAD_set_site _category.mandatory_code no _category_key.name '_pdbx_phasing_MAD_set_site.id' loop_ _category_group.id 'inclusive_group' 'pdbx_group' 'phasing_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - anomalous scatters is Se ; ; loop_ _pdbx_phasing_MAD_set_site.id _pdbx_phasing_MAD_set_site.atom_type_symbol _pdbx_phasing_MAD_set_site.Cartn_x _pdbx_phasing_MAD_set_site.Cartn_y _pdbx_phasing_MAD_set_site.Cartn_z _pdbx_phasing_MAD_set_site.B_iso _pdbx_phasing_MAD_set_site.Occupancy 1 SE 25.9407 -0.103471 17.4094 15.2561 1 2 SE 30.6534 6.62359 9.93063 12.9102 1 3 SE -3.26506 15.5546 53.9529 30.5239 1 # ....... ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_phasing_MAD_set_site.id _item_description.description ; _pdbx_phasing_MAD_set_site.id records the number of site obtained from MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_site.id' _item.category_id pdbx_phasing_MAD_set_site _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_pdbx_phasing_MAD_set_site.id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_site.atom_type_symbol _item_description.description ; _pdbx_phasing_MAD_set_site.atom_type_symbol records the name of site obtained from MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_site.atom_type_symbol' _item.category_id pdbx_phasing_MAD_set_site _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_pdbx_phasing_MAD_set_site.atom_type_symbol' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_site.Cartn_x _item_description.description ; _pdbx_phasing_MAD_set_site.Cartn_x records the X Cartesian coordinate of site obtained from MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_site.Cartn_x' _item.category_id pdbx_phasing_MAD_set_site _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_site.Cartn_x' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_site.Cartn_y _item_description.description ; _pdbx_phasing_MAD_set_site.Cartn_y records the Y Cartesian coordinate of site obtained from MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_site.Cartn_y' _item.category_id pdbx_phasing_MAD_set_site _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_site.Cartn_y' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_site.Cartn_z _item_description.description ; _pdbx_phasing_MAD_set_site.Cartn_z records the Z Cartesian coordinate of site obtained from MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_site.Cartn_z' _item.category_id pdbx_phasing_MAD_set_site _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_site.Cartn_z' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_site.Cartn_x_esd _item_description.description ; _pdbx_phasing_MAD_set_site.Cartn_x_esd records the estimated standard deviation X Cartesian coordinate of site obtained from MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_site.Cartn_x_esd' _item.category_id pdbx_phasing_MAD_set_site _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_site.Cartn_x_esd' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_site.Cartn_y_esd _item_description.description ; _pdbx_phasing_MAD_set_site.Cartn_y_esd records the estimated standard deviation Y Cartesian coordinate of site obtained from MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_site.Cartn_y_esd' _item.category_id pdbx_phasing_MAD_set_site _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_site.Cartn_y_esd' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_site.Cartn_z_esd _item_description.description ; _pdbx_phasing_MAD_set_site.Cartn_z_esd records the estimated standard deviation Z Cartesian coordinate of site obtained from MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_site.Cartn_z_esd' _item.category_id pdbx_phasing_MAD_set_site _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_site.Cartn_z_esd' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_site.fract_x _item_description.description ; _pdbx_phasing_MAD_set_site.fract_x records the X fractional coordinate of site obtained from MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_site.fract_x' _item.category_id pdbx_phasing_MAD_set_site _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_site.fract_x' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_site.fract_y _item_description.description ; _pdbx_phasing_MAD_set_site.fract_y records the Y fractional coordinate of site obtained from MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_site.fract_y' _item.category_id pdbx_phasing_MAD_set_site _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_site.fract_y' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_site.fract_z _item_description.description ; _pdbx_phasing_MAD_set_site.fract_z records the Z fractional coordinate of site obtained from MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_site.fract_z' _item.category_id pdbx_phasing_MAD_set_site _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_site.fract_z' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_site.fract_x_esd _item_description.description ; _pdbx_phasing_MAD_set_site.fract_x_esd records the estimated standard deviation X fractional coordinate of site obtained from MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_site.fract_x_esd' _item.category_id pdbx_phasing_MAD_set_site _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_site.fract_x_esd' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_site.fract_y_esd _item_description.description ; _pdbx_phasing_MAD_set_site.fract_y_esd records the estimated standard deviation Y fractional coordinate of site obtained from MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_site.fract_y_esd' _item.category_id pdbx_phasing_MAD_set_site _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_site.fract_y_esd' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_site.fract_z_esd _item_description.description ; _pdbx_phasing_MAD_set_site.fract_z_esd records the estimated standard deviation Z fractional coordinate of site obtained from MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_site.fract_z_esd' _item.category_id pdbx_phasing_MAD_set_site _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_site.fract_z_esd' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_site.b_iso _item_description.description ; _pdbx_phasing_MAD_set_site.b_iso records isotropic temperature factor parameterthe for the site obtained from MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_site.b_iso' _item.category_id pdbx_phasing_MAD_set_site _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_site.b_iso' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_site.b_iso_esd _item_description.description ; _pdbx_phasing_MAD_set_site.b_iso_esd records estimated standard deviation of isotropic temperature factor parameterthe for the site obtained from MAD phasing. ; _item.name '_pdbx_phasing_MAD_set_site.b_iso_esd' _item.category_id pdbx_phasing_MAD_set_site _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_site.b_iso_esd' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_site.occupancy _item_description.description ; _pdbx_phasing_MAD_set_site.occupancy records the fraction of the atom type presented at this site. ; _item.name '_pdbx_phasing_MAD_set_site.occupancy' _item.category_id pdbx_phasing_MAD_set_site _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_site.occupancy' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_site.occupancy_esd _item_description.description ; _pdbx_phasing_MAD_set_site.occupancy_esd records estimated standard deviation of the fraction of the atom type presented at this site. ; _item.name '_pdbx_phasing_MAD_set_site.occupancy_esd' _item.category_id pdbx_phasing_MAD_set_site _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_site.occupancy_esd' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ### new items for _phasing_MAD_set ### save__phasing_MAD_set.pdbx_atom_type _item_description.description ; record the type of heavy atoms which produce anomolous singal. ; _item.name '_phasing_MAD_set.pdbx_atom_type' _item.category_id phasing_MAD_set _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_phasing_MAD_set.pdbx_atom_type' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MAD_set.pdbx_f_prime_refined _item_description.description ; record the refined f_prime (not from experiment). ; _item.name '_phasing_MAD_set.pdbx_f_prime_refined' _item.category_id phasing_MAD_set _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MAD_set.pdbx_f_prime_refined' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MAD_set.pdbx_f_double_prime_refined _item_description.description ; record the refined f_double_prime (not from experiment). ; _item.name '_phasing_MAD_set.pdbx_f_double_prime_refined' _item.category_id phasing_MAD_set _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MAD_set.pdbx_f_double_prime_refined' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### new items for _pdbx_phasing_MAD_set_site ### save__pdbx_phasing_MAD_set_site.set_id _item_description.description ; record the phasing set. ; _item.name '_pdbx_phasing_MAD_set_site.set_id' _item.category_id pdbx_phasing_MAD_set_site _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_pdbx_phasing_MAD_set_site.set_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MAD_set_site.occupancy_iso _item_description.description ; The relative real isotropic occupancy of the atom type present at this heavy-atom site in a given atom site. ; _item.name '_pdbx_phasing_MAD_set_site.occupancy_iso' _item.category_id pdbx_phasing_MAD_set_site _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MAD_set_site.occupancy_iso' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### new items for _refine_ls_restr_ncs ### save__refine_ls_restr_ncs.pdbx_type _item_description.description ; record the type of NCS restraint. (for example: tight positional) ; _item.name '_refine_ls_restr_ncs.pdbx_type' _item.category_id refine_ls_restr_ncs _item.mandatory_code no _item_type.code text _item_aliases.alias_name '_refine_ls_restr_ncs.pdbx_type' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__refine_ls_restr_ncs.pdbx_asym_id _item_description.description ; record the chain ID. ; _item.name '_refine_ls_restr_ncs.pdbx_asym_id' _item.category_id refine_ls_restr_ncs _item.mandatory_code no _item_type.code code _item_aliases.alias_name '_refine_ls_restr_ncs.pdbx_asym_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__refine_ls_restr_ncs.pdbx_number _item_description.description ; record the residue number . ; _item.name '_refine_ls_restr_ncs.pdbx_number' _item.category_id refine_ls_restr_ncs _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_refine_ls_restr_ncs.pdbx_number' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__refine_ls_restr_ncs.pdbx_rms _item_description.description ; record the standard divation between one segment to another ; _item.name '_refine_ls_restr_ncs.pdbx_rms' _item.category_id refine_ls_restr_ncs _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_refine_ls_restr_ncs.pdbx_rms' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__refine_ls_restr_ncs.pdbx_weight _item_description.description ; record the weight used for NCS restraint. ; _item.name '_refine_ls_restr_ncs.pdbx_weight' _item.category_id refine_ls_restr_ncs _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_refine_ls_restr_ncs.pdbx_weight' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### new items for _struct_ncs_dom_lim ### save__struct_ncs_dom_lim.pdbx_component_id _item_description.description ; record the number of component used for NCS. ; _item.name '_struct_ncs_dom_lim.pdbx_component_id' _item.category_id struct_ncs_dom_lim _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_struct_ncs_dom_lim.pdbx_component_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__struct_ncs_dom_lim.pdbx_refine_code _item_description.description ; record the refinement code number (from CCP4.) ; _item.name '_struct_ncs_dom_lim.pdbx_refine_code' _item.category_id struct_ncs_dom_lim _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_struct_ncs_dom_lim.pdbx_refine_code' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### new items for _refine_analyze ### save__refine_analyze.pdbx_Luzzati_d_res_high_obs _item_description.description ; record the high resolution for calculating Luzzati statistics. ; _item.name '_refine_analyze.pdbx_Luzzati_d_res_high_obs' _item.category_id refine_analyze _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_refine_analyze.pdbx_Luzzati_d_res_high_obs' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ #------------------------------- ### new items for _phasing_MIR_shell ### save__phasing_MIR.pdbx_number_derivatives _item_description.description ; The number of derivatives used in this phasing experiment. ; _item.name '_phasing_MIR.pdbx_number_derivatives' _item.category_id phasing_MIR _item.mandatory_code no _item_type.code int save_ save__phasing_MIR_shell.pdbx_loc_centric _item_description.description ; record lack of closure from centric reflection for each shell. ; _item.name '_phasing_MIR_shell.pdbx_loc_centric' _item.category_id phasing_MIR_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_shell.pdbx_loc_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_shell.pdbx_loc_acentric _item_description.description ; record lack of closure from acentric reflection for each shell. ; _item.name '_phasing_MIR_shell.pdbx_loc_acentric' _item.category_id phasing_MIR_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_shell.pdbx_loc_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_shell.pdbx_power_centric _item_description.description ; record phasing power from centric reflection for each shell. ; _item.name '_phasing_MIR_shell.pdbx_power_centric' _item.category_id phasing_MIR_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_shell.pdbx_power_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_shell.pdbx_power_acentric _item_description.description ; record phasing power from acentric reflection for each shell. ; _item.name '_phasing_MIR_shell.pdbx_power_acentric' _item.category_id phasing_MIR_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_shell.pdbx_power_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_shell.pdbx_R_kraut_centric _item_description.description ; record R_Kraut from from centric reflection for each shell. ; _item.name '_phasing_MIR_shell.pdbx_R_kraut_centric' _item.category_id phasing_MIR_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_shell.pdbx_R_kraut_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_shell.pdbx_R_kraut_acentric _item_description.description ; record R_kraut from from acentric reflection for each shell. ; _item.name '_phasing_MIR_shell.pdbx_R_kraut_acentric' _item.category_id phasing_MIR_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_shell.pdbx_R_kraut_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_shell.pdbx_R_cullis_centric _item_description.description ; record R_Cullis from from centric reflection for each shell. ; _item.name '_phasing_MIR_shell.pdbx_R_cullis_centric' _item.category_id phasing_MIR_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_shell.pdbx_R_cullis_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_shell.pdbx_R_cullis_acentric _item_description.description ; record R_Cullis from from acentric reflection for each shell. ; _item.name '_phasing_MIR_shell.pdbx_R_cullis_acentric' _item.category_id phasing_MIR_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_shell.pdbx_R_cullis_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### new items for _phasing_MIR_der ### save__phasing_MIR_der.pdbx_R_kraut_centric _item_description.description ; record R_kraut obtained from centric data for each derivative. ; _item.name '_phasing_MIR_der.pdbx_R_kraut_centric' _item.category_id phasing_MIR_der _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_der.pdbx_R_kraut_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_der.pdbx_R_kraut_acentric _item_description.description ; record R_kraut obtained from acentric data for each derivative. ; _item.name '_phasing_MIR_der.pdbx_R_kraut_acentric' _item.category_id phasing_MIR_der _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_der.pdbx_R_kraut_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_der.pdbx_R_kraut _item_description.description ; record R_kraut obtained from all data data for each derivative. ; _item.name '_phasing_MIR_der.pdbx_R_kraut' _item.category_id phasing_MIR_der _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_der.pdbx_R_kraut' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_der.pdbx_loc_centric _item_description.description ; record lack of closure obtained from centric data for each derivative. ; _item.name '_phasing_MIR_der.pdbx_loc_centric' _item.category_id phasing_MIR_der _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_der.pdbx_loc_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_der.pdbx_loc_acentric _item_description.description ; record lack of closure obtained from acentric data for each derivative. ; _item.name '_phasing_MIR_der.pdbx_loc_acentric' _item.category_id phasing_MIR_der _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_der.pdbx_loc_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_der.pdbx_loc _item_description.description ; record lack of closure obtained from all data for each derivative. ; _item.name '_phasing_MIR_der.pdbx_loc' _item.category_id phasing_MIR_der _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_der.pdbx_loc' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_der.pdbx_fom_centric _item_description.description ; record figure of merit obtained from centric data for each derivative. ; _item.name '_phasing_MIR_der.pdbx_fom_centric' _item.category_id phasing_MIR_der _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_der.pdbx_fom_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_der.pdbx_fom_acentric _item_description.description ; record figure of merit obtained from acentric data for each derivative. ; _item.name '_phasing_MIR_der.pdbx_fom_acentric' _item.category_id phasing_MIR_der _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_der.pdbx_fom_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_der.pdbx_fom _item_description.description ; record figure of merit obtained from all data for each derivative. ; _item.name '_phasing_MIR_der.pdbx_fom' _item.category_id phasing_MIR_der _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_der.pdbx_fom' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_der.pdbx_power _item_description.description ; record phasing power for each derivative. ; _item.name '_phasing_MIR_der.pdbx_power' _item.category_id phasing_MIR_der _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_der.pdbx_power' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_der.pdbx_R_cullis _item_description.description ; record R_cullis for each derivative. ; _item.name '_phasing_MIR_der.pdbx_R_cullis' _item.category_id phasing_MIR_der _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_der.pdbx_R_cullis' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_der.pdbx_reflns _item_description.description ; record number of reflections used for each derivative. ; _item.name '_phasing_MIR_der.pdbx_reflns' _item.category_id phasing_MIR_der _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_phasing_MIR_der.pdbx_reflns' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ### new items for _phasing_MIR_der_shell ### save__phasing_MIR_der_shell.pdbx_R_cullis_centric _item_description.description ; record R Cullis obtained from centric data for each derivative, but broken into resolution shells ; _item.name '_phasing_MIR_der_shell.pdbx_R_cullis_centric' _item.category_id phasing_MIR_der_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_der_shell.pdbx_R_cullis_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_der_shell.pdbx_R_cullis_acentric _item_description.description ; record R Cullis obtained from acentric data for each derivative, but broken into resolution shells ; _item.name '_phasing_MIR_der_shell.pdbx_R_cullis_acentric' _item.category_id phasing_MIR_der_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_der_shell.pdbx_R_cullis_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_der_shell.pdbx_R_kraut_centric _item_description.description ; record R Kraut obtained from centric data for each derivative, but broken into resolution shells ; _item.name '_phasing_MIR_der_shell.pdbx_R_kraut_centric' _item.category_id phasing_MIR_der_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_der_shell.pdbx_R_kraut_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_der_shell.pdbx_R_kraut_acentric _item_description.description ; record R Kraut obtained from acentric data for each derivative, but broken into resolution shells ; _item.name '_phasing_MIR_der_shell.pdbx_R_kraut_acentric' _item.category_id phasing_MIR_der_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_der_shell.pdbx_R_kraut_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_der_shell.pdbx_loc_centric _item_description.description ; record lack of closure obtained from centric data for each derivative, but broken into resolution shells ; _item.name '_phasing_MIR_der_shell.pdbx_loc_centric' _item.category_id phasing_MIR_der_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_der_shell.pdbx_loc_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_der_shell.pdbx_loc_acentric _item_description.description ; record lack of closure obtained from acentric data for each derivative, but broken into resolution shells ; _item.name '_phasing_MIR_der_shell.pdbx_loc_acentric' _item.category_id phasing_MIR_der_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_der_shell.pdbx_loc_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_der_shell.pdbx_power_centric _item_description.description ; record phasing power obtained from centric data for each derivative, but broken into resolution shells ; _item.name '_phasing_MIR_der_shell.pdbx_power_centric' _item.category_id phasing_MIR_der_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_der_shell.pdbx_power_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_der_shell.pdbx_power_acentric _item_description.description ; record phasing power obtained from acentric data for each derivative, but broken into resolution shells ; _item.name '_phasing_MIR_der_shell.pdbx_power_acentric' _item.category_id phasing_MIR_der_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_der_shell.pdbx_power_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_der_shell.pdbx_fom_centric _item_description.description ; record figure of merit obtained from centric data for each derivative, but broken into resolution shells ; _item.name '_phasing_MIR_der_shell.pdbx_fom_centric' _item.category_id phasing_MIR_der_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_der_shell.pdbx_fom_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_der_shell.pdbx_fom_acentric _item_description.description ; record figure of merit obtained from acentric data for each derivative, but broken into resolution shells ; _item.name '_phasing_MIR_der_shell.pdbx_fom_acentric' _item.category_id phasing_MIR_der_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_der_shell.pdbx_fom_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_der_shell.pdbx_reflns_centric _item_description.description ; record number of centric reflections used for phasing for each derivative, but broken into resolution shells ; _item.name '_phasing_MIR_der_shell.pdbx_reflns_centric' _item.category_id phasing_MIR_der_shell _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_phasing_MIR_der_shell.pdbx_reflns_centric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__phasing_MIR_der_shell.pdbx_reflns_acentric _item_description.description ; record number of acentric reflections used for phasing for each derivative, but broken into resolution shells ; _item.name '_phasing_MIR_der_shell.pdbx_reflns_acentric' _item.category_id phasing_MIR_der_shell _item.mandatory_code no _item_type.code int _item_aliases.alias_name '_phasing_MIR_der_shell.pdbx_reflns_acentric' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ ## ### category, _pdbx_phasing_MR save_pdbx_phasing_MR _category.description ; Data items in the PDBX_PHASING_MR category record details about molecular replacement. ; _category.id pdbx_phasing_MR _category.mandatory_code no _category_key.name '_pdbx_phasing_MR.entry_id' loop_ _category_group.id 'inclusive_group' 'pdbx_group' 'phasing_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - molecular replacement example from program CNS. ; ; _pdbx_phasing_MR.entry_id ABC001 _pdbx_phasing_MR.method_rotation 'real-space rotation search' _pdbx_phasing_MR.d_res_high_rotation 3.8 _pdbx_phasing_MR.d_res_low_rotation 13.0 _pdbx_phasing_MR.sigma_F_rotation 1.0 _pdbx_phasing_MR.reflns_percent_rotation 97.8 _pdbx_phasing_MR.method_translation 'gerneral using PC-refinement= e2e2' _pdbx_phasing_MR.d_res_high_translation 4.0 _pdbx_phasing_MR.d_res_low_translation 15.0 _pdbx_phasing_MR.sigma_F_translation 0 _pdbx_phasing_MR.reflns_percent_translation 97.7 _pdbx_phasing_MR.correlation_coeff_Fo_to_Fc 0.586 _pdbx_phasing_MR.packing 0.3086 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_phasing_MR.entry_id _item_description.description ; The value of _pdbx_phasing_MR.entry_id identifies the data block. ; _item.name '_pdbx_phasing_MR.entry_id' _item.category_id pdbx_phasing_MR _item.mandatory_code yes _item_type.code code _item_aliases.alias_name '_pdbx_phasing_MR.entry_id' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MR.method_rotation _item_description.description ; The value of _pdbx_phasing_MR.method_rotation identifies the method used for rotation search. For example, the rotation method may be realspace, fastdirect, or direct. . ; _item.name '_pdbx_phasing_MR.method_rotation' _item.category_id pdbx_phasing_MR _item.mandatory_code no _item_type.code line _item_aliases.alias_name '_pdbx_phasing_MR.method_rotation' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MR.d_res_high_rotation _item_description.description ; The value of _pdbx_phasing_MR.d_res_high_rotation identifies the highest resolution used for rotation search. ; _item.name '_pdbx_phasing_MR.d_res_high_rotation' _item.category_id pdbx_phasing_MR _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MR.d_res_high_rotation' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MR.d_res_low_rotation _item_description.description ; The value of _pdbx_phasing_MR.d_res_low_rotation identifies the lowest resolution used for rotation search. ; _item.name '_pdbx_phasing_MR.d_res_low_rotation' _item.category_id pdbx_phasing_MR _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MR.d_res_low_rotation' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MR.sigma_F_rotation _item_description.description ; The value of _pdbx_phasing_MR.sigma_F_rotation identifies the sigma cut off of structure factor used for rotation search. ; _item.name '_pdbx_phasing_MR.sigma_F_rotation' _item.category_id pdbx_phasing_MR _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MR.sigma_F_rotation' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MR.sigma_I_rotation _item_description.description ; The value of _pdbx_phasing_MR.sigma_I_rotation identifies the sigma cut off of intensity used for rotation search. ; _item.name '_pdbx_phasing_MR.sigma_I_rotation' _item.category_id pdbx_phasing_MR _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MR.sigma_I_rotation' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MR.reflns_percent_rotation _item_description.description ; The value of _pdbx_phasing_MR.reflns_percent_rotation identifies the completness of data used for rotation search. ; _item.name '_pdbx_phasing_MR.reflns_percent_rotation' _item.category_id pdbx_phasing_MR _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MR.reflns_percent_rotation' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MR.method_translation _item_description.description ; The value of _pdbx_phasing_MR.method_translation identifies the method used for translation search. For example in CNS, the translation method may be "general" or "phased" with PC refinement target using "fastf2f2" "e2e2" "e1e1" "f2f2" "f1f1" "residual" "vector". . ; _item.name '_pdbx_phasing_MR.method_translation' _item.category_id pdbx_phasing_MR _item.mandatory_code no _item_type.code line _item_aliases.alias_name '_pdbx_phasing_MR.method_translation' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MR.d_res_high_translation _item_description.description ; The value of _pdbx_phasing_MR.d_res_high_translation identifies the highest resolution used for translation search. ; _item.name '_pdbx_phasing_MR.d_res_high_translation' _item.category_id pdbx_phasing_MR _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MR.d_res_high_translation' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MR.d_res_low_translation _item_description.description ; The value of _pdbx_phasing_MR.d_res_low_translation identifies the lowest resolution used for translation search. ; _item.name '_pdbx_phasing_MR.d_res_low_translation' _item.category_id pdbx_phasing_MR _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MR.d_res_low_translation' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MR.sigma_F_translation _item_description.description ; The value of _pdbx_phasing_MR.sigma_F_translation identifies the sigma cut off of structure factor used for translation search. ; _item.name '_pdbx_phasing_MR.sigma_F_translation' _item.category_id pdbx_phasing_MR _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MR.sigma_F_translation' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MR.sigma_I_translation _item_description.description ; The value of _pdbx_phasing_MR.sigma_I_translation identifies the sigma cut off of intensity used for translation search. ; _item.name '_pdbx_phasing_MR.sigma_I_translation' _item.category_id pdbx_phasing_MR _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MR.sigma_I_translation' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MR.reflns_percent_translation _item_description.description ; The value of _pdbx_phasing_MR.reflns_percent_translation identifies the completness of data used for translation search. ; _item.name '_pdbx_phasing_MR.reflns_percent_translation' _item.category_id pdbx_phasing_MR _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MR.reflns_percent_translation' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MR.correlation_coeff_Io_to_Ic _item_description.description ; The value of _pdbx_phasing_MR.correlation_coeff_Io_to_Ic identifies the correlation between the observed and the calculated intensity (~|F|^2) after rotation and translation. ; _item.name '_pdbx_phasing_MR.correlation_coeff_Io_to_Ic' _item.category_id pdbx_phasing_MR _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MR.correlation_coeff_Io_to_Ic' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MR.correlation_coeff_Fo_to_Fc _item_description.description ; The value of _pdbx_phasing_MR.correlation_coeff_Fo_to_Fc identifies the correlation between the observed and the calculated structure factor after rotation and translation. ; _item.name '_pdbx_phasing_MR.correlation_coeff_Fo_to_Fc' _item.category_id pdbx_phasing_MR _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MR.correlation_coeff_Fo_to_Fc' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MR.R_factor _item_description.description ; The value of _pdbx_phasing_MR.R_factor identifies the R factor (defined as uasual) after rotation and translation. ; _item.name '_pdbx_phasing_MR.R_factor' _item.category_id pdbx_phasing_MR _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MR.R_factor' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MR.R_rigid_body _item_description.description ; The value of _pdbx_phasing_MR.R_rigid_body identifies the R factor for rigid body refinement after rotation and translation.(In general, rigid body refinement has to be carried out after molecular replacement. ; _item.name '_pdbx_phasing_MR.R_rigid_body' _item.category_id pdbx_phasing_MR _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MR.R_rigid_body' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MR.packing _item_description.description ; The value of _pdbx_phasing_MR.packing identifies the packing of search model in the unit cell. Too many crystallographic contacts may indicate a bad search. ; _item.name '_pdbx_phasing_MR.packing' _item.category_id pdbx_phasing_MR _item.mandatory_code no _item_type.code float _item_aliases.alias_name '_pdbx_phasing_MR.packing' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MR.model_details _item_description.description ; The value of _pdbx_phasing_MR.model_details records the details of model used. For example, the original model can be truncated by deleting side chains, doubtful parts, using the monomer if the original model was an oligomer. The search model may be one domain of a large molecule. What is the pdb IDs. ; _item.name '_pdbx_phasing_MR.model_details' _item.category_id pdbx_phasing_MR _item.mandatory_code no _item_type.code text _item_aliases.alias_name '_pdbx_phasing_MR.model_details' _item_aliases.dictionary 'cif_rcsb.dic' _item_aliases.version 1.1 save_ save__pdbx_phasing_MR.native_set_id _item_description.description ; The data set that was treated as the native in this experiment. This data item is a pointer to _phasing_set.id in the PHASING_SET category. ; _item.name '_pdbx_phasing_MR.native_set_id' _item.category_id pdbx_phasing_MR _item.mandatory_code no _item_type.code line _item_linked.child_name '_pdbx_phasing_MR.native_set_id' _item_linked.parent_name '_phasing_set.id' save_ save__phasing_set.pdbx_temp_details _item_description.description ; The value of _phasing_set.pdbx_temp_details describes any special details about the data collection temperature for this phasing data set. ; _item.name '_phasing_set.pdbx_temp_details' _item.category_id phasing_set _item.mandatory_code no _item_type.code text save_ save__phasing_set.pdbx_d_res_high _item_description.description ; The smallest value in angstroms for the interplanar spacings for the reflections in this shell. This is called the highest resolution. ; _item.name '_phasing_set.pdbx_d_res_high' _item.category_id phasing_set _item.mandatory_code yes loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__phasing_set.pdbx_d_res_low _item_description.description ; The highest value in angstroms for the interplanar spacings for the reflections in this shell. This is called the lowest resolution. ; _item.name '_phasing_set.pdbx_d_res_low' _item.category_id phasing_set _item.mandatory_code yes loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__refln.pdbx_I_plus _item_description.description ; The intensity of the I(h,k,l) partner of the Friedel pair. ; _item.name '_refln.pdbx_I_plus' _item.category_id refln _item.mandatory_code no _item_type.code float save_ save__refln.pdbx_I_minus _item_description.description ; The intensity of the I(-h,-k,-l) partner of the Friedel pair. ; _item.name '_refln.pdbx_I_minus' _item.category_id refln _item.mandatory_code no _item_type.code float save_ save__refln.pdbx_F_plus _item_description.description ; The structure factor F(h,k,l) of the Friedel pair. ; _item.name '_refln.pdbx_F_plus' _item.category_id refln _item.mandatory_code no _item_type.code float save_ save__refln.pdbx_F_minus _item_description.description ; The structure factor F(-h,-k,-l) of the Friedel pair. ; _item.name '_refln.pdbx_F_minus' _item.category_id refln _item.mandatory_code no _item_type.code float save_ save__refln.pdbx_I_plus_sigma _item_description.description ; The standard uncertainty (derived from measurement) of the intensity I(h,k,l) partner of the Friedel pair. ; _item.name '_refln.pdbx_I_plus_sigma' _item.category_id refln _item.mandatory_code no _item_type.code float save_ save__refln.pdbx_I_minus_sigma _item_description.description ; The standard uncertainty (derived from measurement) of the intensity I(-h,-k,-l) partner of the Friedel pair. ; _item.name '_refln.pdbx_I_minus_sigma' _item.category_id refln _item.mandatory_code no _item_type.code float save_ save__refln.pdbx_F_minus_sigma _item_description.description ; The standard uncertainty (derived from measurement) of the structure factor F(-h,-k,-l) of the Friedel pair. ; _item.name '_refln.pdbx_F_minus_sigma' _item.category_id refln _item.mandatory_code no _item_type.code float save_ save__refln.pdbx_F_plus_sigma _item_description.description ; The standard uncertainty (derived from measurement) of the structure factor F(h,k,l) of the Friedel pair. ; _item.name '_refln.pdbx_F_plus_sigma' _item.category_id refln _item.mandatory_code no _item_type.code float save_ save__refln.pdbx_HL_A_iso _item_description.description ; The isomorphous Hendrickson-Lattman coefficient A~iso~ for this reflection. Ref: Hendrickson, W. A. & Lattman, E. E. (1970). Acta Cryst. B26, 136-143. ; _item.name '_refln.pdbx_HL_A_iso' _item.category_id refln _item.mandatory_code no _item_type.code float save_ save__refln.pdbx_HL_B_iso _item_description.description ; The isomorphous Hendrickson-Lattman coefficient B~iso~ for this reflection. Ref: Hendrickson, W. A. & Lattman, E. E. (1970). Acta Cryst. B26, 136-143. ; _item.name '_refln.pdbx_HL_B_iso' _item.category_id refln _item.mandatory_code no _item_type.code float save_ save__refln.pdbx_HL_C_iso _item_description.description ; The isomorphous Hendrickson-Lattman coefficient C~iso~ for this reflection. Ref: Hendrickson, W. A. & Lattman, E. E. (1970). Acta Cryst. B26, 136-143. ; _item.name '_refln.pdbx_HL_C_iso' _item.category_id refln _item.mandatory_code no _item_type.code float save_ save__refln.pdbx_HL_D_iso _item_description.description ; The isomorphous Hendrickson-Lattman coefficient D~iso~ for this reflection. Ref: Hendrickson, W. A. & Lattman, E. E. (1970). Acta Cryst. B26, 136-143. ; _item.name '_refln.pdbx_HL_D_iso' _item.category_id refln _item.mandatory_code no _item_type.code float save_ ### EOF mmcif_pdbx-def-5.dic ########################################################################### # # File: mmcif_pdbx-def-6.dic # # PDB Exchange Data Dictionary # # This data dictionary contains definitions used by wwPDB for data exchange # and data processing. # # Definition Section 6 # # ########################################################################### save__entity.pdbx_target_id _item_description.description ; The value of _entity.target_id points to a TARGETDB target idenitifier from which this entity was generated. ; _item.name '_entity.pdbx_target_id' _item.category_id entity _item.mandatory_code no _item_type.code code save_ save_pdbx_entity_prod_protocol _category.description ; This category contains descriptive protocols for the production of this entity. ; _category.id pdbx_entity_prod_protocol _category.mandatory_code no loop_ _category_group.id 'inclusive_group' 'protein_production_group' 'entity_group' 'pdbx_group' loop_ _category_key.name '_pdbx_entity_prod_protocol.entry_id' '_pdbx_entity_prod_protocol.entity_id' '_pdbx_entity_prod_protocol.protocol_type' save_ save__pdbx_entity_prod_protocol.entry_id _item_description.description ; The value of _pdbx_entity_prod_protocol.entry_id uniquely identifies a sample consisting of one or more proteins whose structure is to be determined. This is a pointer to _entry.id. ; _item.name '_pdbx_entity_prod_protocol.entry_id' _item.category_id pdbx_entity_prod_protocol _item.mandatory_code yes _item_type.code code _item_linked.parent_name '_entry.id' _item_linked.child_name '_pdbx_entity_prod_protocol.entry_id' save_ save__pdbx_entity_prod_protocol.entity_id _item_description.description ; The value of _pdbx_entity_prod_protocol.entity_id uniquely identifies each protein contained in the project target protein complex whose structure is to be determined. This data item is a pointer to _entity.id in the ENTITY category. ; _item.name '_pdbx_entity_prod_protocol.entity_id' _item.category_id pdbx_entity_prod_protocol _item.mandatory_code yes _item_type.code code _item_linked.parent_name '_entity.id' _item_linked.child_name '_pdbx_entity_prod_protocol.entity_id' save_ save__pdbx_entity_prod_protocol.protocol _item_description.description ; The protocol description associated with the protocol_type employed in the production of this entity. ; _item.name '_pdbx_entity_prod_protocol.protocol' _item.category_id pdbx_entity_prod_protocol _item.mandatory_code yes _item_type.code text save_ save__pdbx_entity_prod_protocol.protocol_type _item_description.description ; The one of a set of protocol types associated with the production of this entity. ; _item.name '_pdbx_entity_prod_protocol.protocol_type' _item.category_id pdbx_entity_prod_protocol _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value "selection" "PCR" "cloning" "expression" "growth" "purification" "NMR" "other" save_ #################### ## ENTITY_SRC_GEN ## #################### save__entity_src_gen.entity_id _item_description.description ; This data item is a pointer to _entity.id in the ENTITY category. ; _item.name '_entity_src_gen.entity_id' _item.mandatory_code yes save_ save__entity_src_gen.host_org_common_name _item_description.description ; The common name of the organism that served as host for the production of the entity. Where full details of the protein production are available it would be expected that this item be derived from _entity_src_gen_express.host_org_common_name or via _entity_src_gen_express.host_org_tax_id ; _item.name '_entity_src_gen.host_org_common_name' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'yeast' 'bacteria' save_ save__entity_src_gen.host_org_details _item_description.description ; A description of special aspects of the organism that served as host for the production of the entity. Where full details of the protein production are available it would be expected that this item would derived from _entity_src_gen_express.host_org_details ; _item.name '_entity_src_gen.host_org_details' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text save_ save__entity_src_gen.host_org_strain _item_description.description ; The strain of the organism in which the entity was expressed. Where full details of the protein production are available it would be expected that this item be derived from _entity_src_gen_express.host_org_strain or via _entity_src_gen_express.host_org_tax_id ; _item.name '_entity_src_gen.host_org_strain' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'DH5a' 'BMH 71-18' save_ save__entity_src_gen.plasmid_details _item_description.description ; A description of special aspects of the plasmid that produced the entity in the host organism. Where full details of the protein production are available it would be expected that this item would be derived from _pdbx_construct.details of the construct pointed to from _entity_src_gen_express.plasmid_id. ; _item.name '_entity_src_gen.plasmid_details' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text save_ save__entity_src_gen.plasmid_name _item_description.description ; The name of the plasmid that produced the entity in the host organism. Where full details of the protein production are available it would be expected that this item would be derived from _pdbx_construct.name of the construct pointed to from _entity_src_gen_express.plasmid_id. ; _item.name '_entity_src_gen.plasmid_name' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'pET3C' 'pT123sab' save_ save__entity_src_gen.pdbx_host_org_variant _item_description.description ; Variant of the organism used as the expression system. Where full details of the protein production are available it would be expected that this item be derived from entity_src_gen_express.host_org_variant or via _entity_src_gen_express.host_org_tax_id ; _item.name '_entity_src_gen.pdbx_host_org_variant' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'TRP-LAC' 'LAMBDA DE3' save_ save__entity_src_gen.pdbx_host_org_cell_line _item_description.description ; A specific line of cells used as the expression system. Where full details of the protein production are available it would be expected that this item would be derived from entity_src_gen_express.host_org_cell_line ; _item.name '_entity_src_gen.pdbx_host_org_cell_line' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text _item_examples.case 'HELA' save_ save__entity_src_gen.pdbx_host_org_atcc _item_description.description ; Americal Tissue Culture Collection of the expression system. Where full details of the protein production are available it would be expected that this item would be derived from _entity_src_gen_express.host_org_culture_collection ; _item.name '_entity_src_gen.pdbx_host_org_atcc' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text save_ save__entity_src_gen.pdbx_host_org_culture_collection _item_description.description ; Culture collection of the expression system. Where full details of the protein production are available it would be expected that this item would be derived somehwere, but exactly where is not clear. ; _item.name '_entity_src_gen.pdbx_host_org_culture_collection' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text save_ save__entity_src_gen.pdbx_host_org_cell _item_description.description ; Cell type from which the gene is derived. Where entity.target_id is provided this should be derived from details of the target. ; _item.name '_entity_src_gen.pdbx_host_org_cell' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text _item_examples.case ENDOTHELIAL save_ save__entity_src_gen.pdbx_host_org_scientific_name _item_description.description ; The scientific name of the organism that served as host for the production of the entity. Where full details of the protein production are available it would be expected that this item would be derived from _entity_src_gen_express.host_org_scientific_name or via _entity_src_gen_express.host_org_tax_id ; _item.name '_entity_src_gen.pdbx_host_org_scientific_name' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'ESCHERICHIA COLI' 'SACCHAROMYCES CEREVISIAE' save_ save__entity_src_gen.pdbx_host_org_tissue _item_description.description ; The specific tissue which expressed the molecule. Where full details of the protein production are available it would be expected that this item would be derived from _entity_src_gen_express.host_org_tissue ; _item.name '_entity_src_gen.pdbx_host_org_tissue' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'heart' 'liver' 'eye lens' save_ save__entity_src_gen.pdbx_host_org_vector _item_description.description ; Identifies the vector used. Where full details of the protein production are available it would be expected that this item would be derived from _entity_src_gen_clone.vector_name. ; _item.name '_entity_src_gen.pdbx_host_org_vector' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'PBIT36' 'PET15B' 'PUC18' save_ save__entity_src_gen.pdbx_host_org_vector_type _item_description.description ; Identifies the type of vector used (plasmid, virus, or cosmid). Where full details of the protein production are available it would be expected that this item would be derived from _entity_src_gen_express.vector_type. ; _item.name '_entity_src_gen.pdbx_host_org_vector_type' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'COSMID' 'PLASMID' save_ save__entity_src_gen.expression_system_id _item_description.description ; A unique identifier for the expression system. This should be extracted from a local list of expression systems. ; _item.name '_entity_src_gen.expression_system_id' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code uline save_ save__entity_src_gen.gene_src_dev_stage _item_description.description ; A string to indicate the life-cycle or cell development cycle in which the gene is expressed and the mature protein is active. ; _item.name '_entity_src_gen.gene_src_dev_stage' _item.category_id entity_src_gen _item.mandatory_code no _item_type.code text save_ save__entity_src_gen.start_construct_id _item_description.description ; A pointer to _pdbx_construct.id in the PDBX_CONSTRUCT category. The indentified sequence is the initial construct. ; _item.name '_entity_src_gen.start_construct_id' _item.category_id entity_src_gen _item.mandatory_code no _item_linked.parent_name '_pdbx_construct.id' _item_linked.child_name '_entity_src_gen.start_construct_id' save_ ############################# # ENTITY_SRC_GEN_PROD_OTHER # ############################# # # _pdbx_entity_src_gen_prod_other.entry_id # _pdbx_entity_src_gen_prod_other.entity_id # _pdbx_entity_src_gen_prod_other.step_id # _pdbx_entity_src_gen_prod_other.next_step_id # _pdbx_entity_src_gen_prod_other.end_construct_id # _pdbx_entity_src_gen_prod_other.process_name # _pdbx_entity_src_gen_prod_other.date # _pdbx_entity_src_gen_prod_other.robot_id # _pdbx_entity_src_gen_prod_other.details # save_pdbx_entity_src_gen_prod_other _category.description ; This category contains details for process steps that are not explicitly catered for elsewhere. It provides some basic details as well as placeholders for a list of parameters and values (the category PDBX_ENTITY_SRC_GEN_PROD_OTHER_PARAMETER). Note that processes that have been modelled explicitly should not be represented using this category. ; _category.id pdbx_entity_src_gen_prod_other _category.mandatory_code no loop_ _category_group.id 'inclusive_group' 'protein_production_group' 'entity_group' 'pdbx_group' loop_ _category_key.name '_pdbx_entity_src_gen_prod_other.entry_id' '_pdbx_entity_src_gen_prod_other.entity_id' '_pdbx_entity_src_gen_prod_other.step_id' save_ save__pdbx_entity_src_gen_prod_other.entry_id _item_description.description ; The value of _pdbx_entity_src_gen_prod_other.entry_id uniquely identifies a sample consisting of one or more proteins whose structure is to be determined. This is a pointer to _entry.id. This item may be a site dependent bar code. ; _item.name '_pdbx_entity_src_gen_prod_other.entry_id' _item.category_id pdbx_entity_src_gen_prod_other _item.mandatory_code yes _item_linked.parent_name '_entry.id' _item_linked.child_name '_pdbx_entity_src_gen_prod_other.entry_id' save_ save__pdbx_entity_src_gen_prod_other.entity_id _item_description.description ; The value of _pdbx_entity_src_gen_prod_other.entity_id uniquely identifies each protein contained in the project target protein complex whose structure is to be determined. This data item is a pointer to _entity.id in the ENTITY category. This item may be a site dependent bar code. ; _item.name '_pdbx_entity_src_gen_prod_other.entity_id' _item.category_id pdbx_entity_src_gen_prod_other _item.mandatory_code yes _item_linked.parent_name '_entity.id' _item_linked.child_name '_pdbx_entity_src_gen_prod_other.entity_id' save_ save__pdbx_entity_src_gen_prod_other.step_id _item_description.description ; This item is the unique identifier for this process step. ; _item.name '_pdbx_entity_src_gen_prod_other.step_id' _item.category_id pdbx_entity_src_gen_prod_other _item.mandatory_code yes _item_type.code int save_ save__pdbx_entity_src_gen_prod_other.next_step_id _item_description.description ; This item unique identifier for the next production step. This allows a workflow to have multiple entry points leading to a single product. ; _item.name '_pdbx_entity_src_gen_prod_other.next_step_id' _item.category_id pdbx_entity_src_gen_prod_other _item.mandatory_code yes _item_type.code int save_ save__pdbx_entity_src_gen_prod_other.end_construct_id _item_description.description ; This item is a pointer to pdbx_construct.id in the PDBX_CONSTRUCT category. The referenced nucleic acid sequence is that of the product of the process step. ; _item.name '_pdbx_entity_src_gen_prod_other.end_construct_id' _item.category_id pdbx_entity_src_gen_prod_other _item.mandatory_code no _item_linked.parent_name '_pdbx_construct.id' _item_linked.child_name '_pdbx_entity_src_gen_prod_other.end_construct_id' save_ save__pdbx_entity_src_gen_prod_other.robot_id _item_description.description ; This data item is a pointer to pdbx_robot_system.id in the PDBX_ROBOT_SYSTEM category. The referenced robot is the robot responsible for the process step ; _item.name '_pdbx_entity_src_gen_prod_other.robot_id' _item.category_id pdbx_entity_src_gen_prod_other _item.mandatory_code no _item_linked.parent_name '_pdbx_robot_system.id' _item_linked.child_name '_pdbx_entity_src_gen_prod_other.robot_id' save_ save__pdbx_entity_src_gen_prod_other.date _item_description.description ; The date of this process step. ; _item.name '_pdbx_entity_src_gen_prod_other.date' _item.category_id pdbx_entity_src_gen_prod_other _item.mandatory_code no _item_type.code yyyy-mm-dd:hh:mm loop_ _item_examples.case '2003-12-25' '2003-12-25:09:00' save_ save__pdbx_entity_src_gen_prod_other.process_name _item_description.description ; Name of this process step. ; _item.name '_pdbx_entity_src_gen_prod_other.process_name' _item.category_id pdbx_entity_src_gen_prod_other _item.mandatory_code no _item_type.code text save_ save__pdbx_entity_src_gen_prod_other.details _item_description.description ; Additional details of this process step. ; _item.name '_pdbx_entity_src_gen_prod_other.details' _item.category_id pdbx_entity_src_gen_prod_other _item.mandatory_code no _item_type.code text save_ ############################################ # PDBX_ENTITY_SRC_GEN_PROD_OTHER_PARAMETER # ############################################ # # _pdbx_entity_src_gen_prod_other_parameter.entry_id # _pdbx_entity_src_gen_prod_other_parameter.entity_id # _pdbx_entity_src_gen_prod_other_parameter.step_id # _pdbx_entity_src_gen_prod_other_parameter.name # _pdbx_entity_src_gen_prod_other_parameter.value # save_pdbx_entity_src_gen_prod_other_parameter _category.description ; This category contains parameters and values required to capture information about a particular process step ; _category.id pdbx_entity_src_gen_prod_other_parameter _category.mandatory_code no loop_ _category_group.id 'inclusive_group' 'protein_production_group' 'entity_group' 'pdbx_group' loop_ _category_key.name '_pdbx_entity_src_gen_prod_other_parameter.entry_id' '_pdbx_entity_src_gen_prod_other_parameter.entity_id' '_pdbx_entity_src_gen_prod_other_parameter.step_id' '_pdbx_entity_src_gen_prod_other_parameter.parameter' save_ save__pdbx_entity_src_gen_prod_other_parameter.entry_id _item_description.description ; The value of _pdbx_entity_src_gen_prod_other_parameter.entry_id is a pointer to _pdbx_entity_src_gen_prod_other.entry.id ; _item.name '_pdbx_entity_src_gen_prod_other_parameter.entry_id' _item.category_id pdbx_entity_src_gen_prod_other_parameter _item.mandatory_code yes _item_linked.parent_name '_pdbx_entity_src_gen_prod_other.entry_id' _item_linked.child_name '_pdbx_entity_src_gen_prod_other_parameter.entry_id' save_ save__pdbx_entity_src_gen_prod_other_parameter.entity_id _item_description.description ; The value of _pdbx_entity_src_gen_prod_other_parameter.entity_id is a pointer to _pdbx_entity_src_gen_prod_other.entity_id ; _item.name '_pdbx_entity_src_gen_prod_other_parameter.entity_id' _item.category_id pdbx_entity_src_gen_prod_other_parameter _item.mandatory_code yes _item_linked.parent_name '_pdbx_entity_src_gen_prod_other.entity_id' _item_linked.child_name '_pdbx_entity_src_gen_prod_other_parameter.entity_id' save_ save__pdbx_entity_src_gen_prod_other_parameter.step_id _item_description.description ; This item is a pointer to _pdbx_entity_src_gen_prod_other.step_id ; _item.name '_pdbx_entity_src_gen_prod_other_parameter.step_id' _item.category_id pdbx_entity_src_gen_prod_other_parameter _item.mandatory_code yes _item_linked.parent_name '_pdbx_entity_src_gen_prod_other.step_id' _item_linked.child_name '_pdbx_entity_src_gen_prod_other_parameter.step_id' save_ save__pdbx_entity_src_gen_prod_other_parameter.parameter _item_description.description ; The name of the parameter associated with the process step ; _item.name '_pdbx_entity_src_gen_prod_other_parameter.parameter' _item.category_id pdbx_entity_src_gen_prod_other_parameter _item.mandatory_code yes _item_type.code line save_ save__pdbx_entity_src_gen_prod_other_parameter.value _item_description.description ; The value of the parameter ; _item.name '_pdbx_entity_src_gen_prod_other_parameter.value' _item.category_id pdbx_entity_src_gen_prod_other_parameter _item.mandatory_code yes _item_type.code text save_ save__pdbx_entity_src_gen_prod_other_parameter.details _item_description.description ; Additional details about the parameter ; _item.name '_pdbx_entity_src_gen_prod_other_parameter.details' _item.category_id pdbx_entity_src_gen_prod_other_parameter _item.mandatory_code yes _item_type.code text save_ ################################ # PDBX_ENTITY_SRC_GEN_PROD_PCR # ################################ # # _pdbx_entity_src_gen_prod_pcr.entry_id # _pdbx_entity_src_gen_prod_pcr.entity_id # _pdbx_entity_src_gen_prod_pcr.step_id # _pdbx_entity_src_gen_prod_pcr.next_step_id # _pdbx_entity_src_gen_prod_pcr.end_construct_id # _pdbx_entity_src_gen_prod_pcr.forward_primer_id # _pdbx_entity_src_gen_prod_pcr.reverse_primer_id # _pdbx_entity_src_gen_prod_pcr.reaction_details # _pdbx_entity_src_gen_prod_pcr.purification_details # _pdbx_entity_src_gen_prod_pcr.date # _pdbx_entity_src_gen_prod_pcr.robot_id # # _pdbx_entity_src_gen_prod_pcr.summary # save_pdbx_entity_src_gen_prod_pcr _category.description ; This category contains details for the PCR steps used in the overall protein production process. The PCR is assumed to be applied to the result of the previous production step, or the gene source if this is the first production step. ; _category.id pdbx_entity_src_gen_prod_pcr _category.mandatory_code no loop_ _category_key.name '_pdbx_entity_src_gen_prod_pcr.entry_id' '_pdbx_entity_src_gen_prod_pcr.entity_id' '_pdbx_entity_src_gen_prod_pcr.step_id' loop_ _category_group.id 'inclusive_group' 'protein_production_group' 'entity_group' 'pdbx_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - hypothetical example ; ; _pdbx_entity_src_gen_prod_pcr.entry_id 111000111 _pdbx_entity_src_gen_prod_pcr.entity_id 222000111 _pdbx_entity_src_gen_prod_pcr.step_id 1 _pdbx_entity_src_gen_prod_pcr.next_step_id 2 _pdbx_entity_src_gen_prod_pcr.end_construct_id 440050000111 _pdbx_entity_src_gen_prod_pcr.robot_id 5 _pdbx_entity_src_gen_prod_pcr.date '2002-07-12:15:13' _pdbx_entity_src_gen_prod_pcr.forward_primer_id 2 _pdbx_entity_src_gen_prod_pcr.reverse_primer_id 3 _pdbx_entity_src_gen_prod_pcr.reaction_details ; Annealing temperature = 70 C Annealing time = 60 s Extending temperature = 74 C Extending time = 120 s Melting temperature = 95 C Melting time = 120 s Number of cycles = 40 Polymerase = KOD Template = 10 pmol Primer = 25 pmol Total volume = 25 ul ; _pdbx_entity_src_gen_prod_pcr.purification_details ; No purification ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_entity_src_gen_prod_pcr.entry_id _item_description.description ; The value of _pdbx_entity_src_gen_prod_pcr.entry_id uniquely identifies a sample consisting of one or more proteins whose structure is to be determined. This is a pointer to _entry.id. This item may be a site dependent bar code. ; _item.name '_pdbx_entity_src_gen_prod_pcr.entry_id' _item.category_id pdbx_entity_src_gen_prod_pcr _item.mandatory_code yes _item_linked.parent_name '_entry.id' _item_linked.child_name '_pdbx_entity_src_gen_prod_pcr.entry_id' save_ save__pdbx_entity_src_gen_prod_pcr.entity_id _item_description.description ; The value of _pdbx_entity_src_gen_prod_pcr.entity_id uniquely identifies each protein contained in the project target protein complex whose structure is to be determined. This data item is a pointer to _entity.id in the ENTITY category. This item may be a site dependent bar code. ; _item.name '_pdbx_entity_src_gen_prod_pcr.entity_id' _item.category_id pdbx_entity_src_gen_prod_pcr _item.mandatory_code yes _item_linked.parent_name '_entity.id' _item_linked.child_name '_pdbx_entity_src_gen_prod_pcr.entity_id' save_ save__pdbx_entity_src_gen_prod_pcr.step_id _item_description.description ; This item is the unique identifier for this PCR step. ; _item.name '_pdbx_entity_src_gen_prod_pcr.step_id' _item.category_id pdbx_entity_src_gen_prod_pcr _item.mandatory_code yes _item_type.code int save_ save__pdbx_entity_src_gen_prod_pcr.next_step_id _item_description.description ; This item unique identifier for the next production step. This allows a workflow to have multiple entry points leading to a single product. ; _item.name '_pdbx_entity_src_gen_prod_pcr.next_step_id' _item.category_id pdbx_entity_src_gen_prod_pcr _item.mandatory_code yes _item_type.code int save_ save__pdbx_entity_src_gen_prod_pcr.end_construct_id _item_description.description ; This item is a pointer to pdbx_construct.id in the PDBX_CONSTRUCT category. The referenced nucleic acid sequence is that of the PCR product. ; _item.name '_pdbx_entity_src_gen_prod_pcr.end_construct_id' _item.category_id pdbx_entity_src_gen_prod_pcr _item.mandatory_code no _item_linked.parent_name '_pdbx_construct.id' _item_linked.child_name '_pdbx_entity_src_gen_prod_pcr.end_construct_id' save_ save__pdbx_entity_src_gen_prod_pcr.robot_id _item_description.description ; This data item is a pointer to pdbx_robot_system.id in the PDBX_ROBOT_SYSTEM category. The referenced robot is the robot responsible for the PCR reaction (normally the heat cycler). ; _item.name '_pdbx_entity_src_gen_prod_pcr.robot_id' _item.category_id pdbx_entity_src_gen_prod_pcr _item.mandatory_code no _item_linked.parent_name '_pdbx_robot_system.id' _item_linked.child_name '_pdbx_entity_src_gen_prod_pcr.robot_id' save_ save__pdbx_entity_src_gen_prod_pcr.date _item_description.description ; The date of this production step. ; _item.name '_pdbx_entity_src_gen_prod_pcr.date' _item.category_id pdbx_entity_src_gen_prod_pcr _item.mandatory_code no _item_type.code yyyy-mm-dd:hh:mm loop_ _item_examples.case '2003-12-25' '2003-12-25:09:00' save_ save__pdbx_entity_src_gen_prod_pcr.forward_primer_id _item_description.description ; This item is a pointer to pdbx_construct.id in the PDBX_CONSTRUCT category. The referenced nucleic acid sequence is that of the forward primer. ; _item.name '_pdbx_entity_src_gen_prod_pcr.forward_primer_id' _item.category_id pdbx_entity_src_gen_prod_pcr _item.mandatory_code yes _item_linked.parent_name '_pdbx_construct.id' _item_linked.child_name '_pdbx_entity_src_gen_prod_pcr.forward_primer_id' save_ save__pdbx_entity_src_gen_prod_pcr.reverse_primer_id _item_description.description ; This item is a pointer to pdbx_construct.id in the PDBX_CONSTRUCT category. The referenced nucleic acid sequence is that of the reverse primer. ; _item.name '_pdbx_entity_src_gen_prod_pcr.reverse_primer_id' _item.category_id pdbx_entity_src_gen_prod_pcr _item.mandatory_code yes _item_linked.parent_name '_pdbx_construct.id' _item_linked.child_name '_pdbx_entity_src_gen_prod_pcr.reverse_primer_id' save_ save__pdbx_entity_src_gen_prod_pcr.reaction_details _item_description.description ; String value containing details of the PCR reaction. ; _item.name '_pdbx_entity_src_gen_prod_pcr.reaction_details' _item.category_id pdbx_entity_src_gen_prod_pcr _item.mandatory_code no _item_type.code text save_ save__pdbx_entity_src_gen_prod_pcr.purification_details _item_description.description ; String value containing details of any purification of the product of the PCR reaction. ; _item.name '_pdbx_entity_src_gen_prod_pcr.purification_details' _item.category_id pdbx_entity_src_gen_prod_pcr _item.mandatory_code no _item_type.code text save_ save__pdbx_entity_src_gen_prod_pcr.summary _item_description.description ; Summary of the details of the PCR reaction any purification of the product of the PCR reaction. ; _item.name '_pdbx_entity_src_gen_prod_pcr.summary' _item.category_id pdbx_entity_src_gen_prod_pcr _item.mandatory_code no _item_type.code text save_ ################################### # PDBX_ENTITY_SRC_GEN_PROD_DIGEST # ################################### # # _pdbx_entity_src_gen_prod_digest.entry_id # _pdbx_entity_src_gen_prod_digest.entity_id # _pdbx_entity_src_gen_prod_digest.step_id # _pdbx_entity_src_gen_prod_digest.next_step_id # _pdbx_entity_src_gen_prod_digest.restriction_enzyme_1 # _pdbx_entity_src_gen_prod_digest.restriction_enzyme_2 # _pdbx_entity_src_gen_prod_digest.purification_details # _pdbx_entity_src_gen_prod_digest.date # _pdbx_entity_src_gen_prod_digest.robot_id # # _pdbx_entity_src_gen_prod_digest.summary # save_pdbx_entity_src_gen_prod_digest _category.description ; This category contains details for the DIGEST steps used in the overall protein production process. The digestion is assumed to be applied to the result of the previous production step, or the gene source if this is the first production step. ; _category.id pdbx_entity_src_gen_prod_digest _category.mandatory_code no loop_ _category_group.id 'inclusive_group' 'protein_production_group' 'entity_group' 'pdbx_group' loop_ _category_key.name '_pdbx_entity_src_gen_prod_digest.entry_id' '_pdbx_entity_src_gen_prod_digest.entity_id' '_pdbx_entity_src_gen_prod_digest.step_id' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - hypothetical example ; ; _pdbx_entity_src_gen_prod_digest.entry_id 111000111 _pdbx_entity_src_gen_prod_digest.entity_id 222000111 _pdbx_entity_src_gen_prod_digest.step_id 2 _pdbx_entity_src_gen_prod_digest.next_step_id 3 _pdbx_entity_src_gen_prod_digest.end_construct_id 440050000123 _pdbx_entity_src_gen_prod_digest.robot_id 5 _pdbx_entity_src_gen_prod_digest.date '2002-07-12:15:13' _pdbx_entity_src_gen_prod_digest.restriction_enzyme_1 'NcoI' _pdbx_entity_src_gen_prod_digest.restriction_enzyme_2 'BamII' _pdbx_entity_src_gen_prod_digest.purification_details ; No purification ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_entity_src_gen_prod_digest.entry_id _item_description.description ; The value of _pdbx_entity_src_gen_prod_digest.entry_id uniquely identifies a sample consisting of one or more proteins whose structure is to be determined. This is a pointer to _entry.id. This item may be a site dependent bar code. ; _item.name '_pdbx_entity_src_gen_prod_digest.entry_id' _item.category_id pdbx_entity_src_gen_prod_digest _item.mandatory_code yes _item_linked.parent_name '_entry.id' _item_linked.child_name '_pdbx_entity_src_gen_prod_digest.entry_id' save_ save__pdbx_entity_src_gen_prod_digest.entity_id _item_description.description ; The value of _pdbx_entity_src_gen_prod_digest.entity_id uniquely identifies each protein contained in the project target protein complex whose structure is to be determined. This data item is a pointer to _entity.id in the ENTITY category. This item may be a site dependent bar code. ; _item.name '_pdbx_entity_src_gen_prod_digest.entity_id' _item.category_id pdbx_entity_src_gen_prod_digest _item.mandatory_code yes _item_linked.parent_name '_entity.id' _item_linked.child_name '_pdbx_entity_src_gen_prod_digest.entity_id' save_ save__pdbx_entity_src_gen_prod_digest.step_id _item_description.description ; This item is the unique identifier for this digestion step. ; _item.name '_pdbx_entity_src_gen_prod_digest.step_id' _item.category_id pdbx_entity_src_gen_prod_digest _item.mandatory_code yes _item_type.code int save_ save__pdbx_entity_src_gen_prod_digest.next_step_id _item_description.description ; This item unique identifier for the next production step. This allows a workflow to have multiple entry points leading to a single product. ; _item.name '_pdbx_entity_src_gen_prod_digest.next_step_id' _item.category_id pdbx_entity_src_gen_prod_digest _item.mandatory_code yes _item_type.code int save_ save__pdbx_entity_src_gen_prod_digest.end_construct_id _item_description.description ; This item is a pointer to pdbx_construct.id in the PDBX_CONSTRUCT category. The referenced nucleic acid sequence is that of the digest product ; _item.name '_pdbx_entity_src_gen_prod_digest.end_construct_id' _item.category_id pdbx_entity_src_gen_prod_digest _item.mandatory_code no _item_linked.parent_name '_pdbx_construct.id' _item_linked.child_name '_pdbx_entity_src_gen_prod_digest.end_construct_id' save_ save__pdbx_entity_src_gen_prod_digest.robot_id _item_description.description ; This data item is a pointer to pdbx_robot_system.id in the PDBX_ROBOT_SYSTEM category. ; _item.name '_pdbx_entity_src_gen_prod_digest.robot_id' _item.category_id pdbx_entity_src_gen_prod_digest _item.mandatory_code no _item_type.code code _item_linked.parent_name '_pdbx_robot_system.id' _item_linked.child_name '_pdbx_entity_src_gen_prod_digest.robot_id' save_ save__pdbx_entity_src_gen_prod_digest.date _item_description.description ; The date of this production step. ; _item.name '_pdbx_entity_src_gen_prod_digest.date' _item.category_id pdbx_entity_src_gen_prod_digest _item.mandatory_code no _item_type.code yyyy-mm-dd:hh:mm _item_examples.case '2003-12-25' save_ save__pdbx_entity_src_gen_prod_digest.restriction_enzyme_1 _item_description.description ; The first enzyme used in the restriction digestion. The sites at which this cuts can be derived from the sequence. ; _item.name '_pdbx_entity_src_gen_prod_digest.restriction_enzyme_1' _item.category_id pdbx_entity_src_gen_prod_digest _item.mandatory_code yes _item_type.code text _item_examples.case 'BamIII' save_ save__pdbx_entity_src_gen_prod_digest.restriction_enzyme_2 _item_description.description ; The second enzyme used in the restriction digestion. The sites at which this cuts can be derived from the sequence. ; _item.name '_pdbx_entity_src_gen_prod_digest.restriction_enzyme_2' _item.category_id pdbx_entity_src_gen_prod_digest _item.mandatory_code no _item_type.code text save_ save__pdbx_entity_src_gen_prod_digest.purification_details _item_description.description ; String value containing details of any purification of the product of the digestion. ; _item.name '_pdbx_entity_src_gen_prod_digest.purification_details' _item.category_id pdbx_entity_src_gen_prod_digest _item.mandatory_code no _item_type.code text save_ save__pdbx_entity_src_gen_prod_digest.summary _item_description.description ; Summary of the details of restriction digestion any purification of the product of the digestion. ; _item.name '_pdbx_entity_src_gen_prod_digest.summary' _item.category_id pdbx_entity_src_gen_prod_digest _item.mandatory_code no _item_type.code text save_ ######################## # ENTITY_SRC_GEN_CLONE # ######################## # # _pdbx_entity_src_gen_clone.entry_id # _pdbx_entity_src_gen_clone.entity_id # _pdbx_entity_src_gen_clone.step_id # _pdbx_entity_src_gen_clone.next_step_id # _pdbx_entity_src_gen_clone.end_construct_id # _pdbx_entity_src_gen_clone.robot_id # _pdbx_entity_src_gen_clone.date # _pdbx_entity_src_gen_clone.gene_insert_method # _pdbx_entity_src_gen_clone.vector_name # _pdbx_entity_src_gen_clone.vector_details # _pdbx_entity_src_gen_clone.transformation_method # _pdbx_entity_src_gen_clone.marker # _pdbx_entity_src_gen_clone.verification_method # _pdbx_entity_src_gen_clone.purification_details # # # _pdbx_entity_src_gen_clone.summary # save_pdbx_entity_src_gen_clone _category.description ; This category contains details for the cloning steps used in the overall protein production process. Each row in PDBX_ENTITY_SRC_GEN_CLONE should have an equivalent row in either PDBX_ENTITY_SRC_GEN_CLONE_LIGATION or PDBX_ENTITY_SRC_GEN_CLONE_RECOMBINATION. If only summary information is provided data in the later two categories may be omitted. ; _category.id pdbx_entity_src_gen_clone _category.mandatory_code no loop_ _category_group.id 'inclusive_group' 'protein_production_group' 'entity_group' 'pdbx_group' loop_ _category_key.name '_pdbx_entity_src_gen_clone.entry_id' '_pdbx_entity_src_gen_clone.entity_id' '_pdbx_entity_src_gen_clone.step_id' save_ save__pdbx_entity_src_gen_clone.entry_id _item_description.description ; The value of _pdbx_entity_src_gen_clone.entry_id uniquely identifies a sample consisting of one or more proteins whose structure is to be determined. This is a pointer to _entry.id. This item may be a site dependent bar code. ; _item.name '_pdbx_entity_src_gen_clone.entry_id' _item.category_id pdbx_entity_src_gen_clone _item.mandatory_code yes _item_linked.parent_name '_entry.id' _item_linked.child_name '_pdbx_entity_src_gen_clone.entry_id' save_ save__pdbx_entity_src_gen_clone.entity_id _item_description.description ; The value of _pdbx_entity_src_gen_clone.entity_id uniquely identifies each protein contained in the project target protein complex whose structure is to be determined. This data item is a pointer to _entity.id in the ENTITY category. This item may be a site dependent bar code. ; _item.name '_pdbx_entity_src_gen_clone.entity_id' _item.category_id pdbx_entity_src_gen_clone _item.mandatory_code yes _item_linked.parent_name '_entity.id' _item_linked.child_name '_pdbx_entity_src_gen_clone.entity_id' save_ save__pdbx_entity_src_gen_clone.step_id _item_description.description ; This item is the unique identifier for this cloning step. ; _item.name '_pdbx_entity_src_gen_clone.step_id' _item.category_id pdbx_entity_src_gen_clone _item.mandatory_code yes _item_type.code int save_ save__pdbx_entity_src_gen_clone.next_step_id _item_description.description ; This item unique identifier for the next production step. This allows a workflow to have multiple entry points leading to a single product. ; _item.name '_pdbx_entity_src_gen_clone.next_step_id' _item.category_id pdbx_entity_src_gen_clone _item.mandatory_code yes _item_type.code int save_ save__pdbx_entity_src_gen_clone.end_construct_id _item_description.description ; This item is a pointer to pdbx_construct.id in the PDBX_CONSTRUCT category. The referenced nucleic acid sequence is that of the cloned product. ; _item.name '_pdbx_entity_src_gen_clone.end_construct_id' _item.category_id pdbx_entity_src_gen_clone _item.mandatory_code no _item_linked.parent_name '_pdbx_construct.id' _item_linked.child_name '_pdbx_entity_src_gen_clone.end_construct_id' save_ save__pdbx_entity_src_gen_clone.robot_id _item_description.description ; This data item is a pointer to pdbx_robot_system.id in the PDBX_ROBOT_SYSTEM category. ; _item.name '_pdbx_entity_src_gen_clone.robot_id' _item.category_id pdbx_entity_src_gen_clone _item.mandatory_code no _item_linked.parent_name '_pdbx_robot_system.id' _item_linked.child_name '_pdbx_entity_src_gen_clone.robot_id' save_ save__pdbx_entity_src_gen_clone.date _item_description.description ; The date of this production step. ; _item.name '_pdbx_entity_src_gen_clone.date' _item.category_id pdbx_entity_src_gen_clone _item.mandatory_code no _item_type.code yyyy-mm-dd:hh:mm loop_ _item_examples.case '2003-12-25' '2003-12-25:09:00' save_ save__pdbx_entity_src_gen_clone.gene_insert_method _item_description.description ; The method used to insert the gene into the vector. For 'Ligation', an PDBX_ENTITY_SRC_GEN_CLONE_LIGATION entry with matching .step_id is expected. For 'Recombination', an PDBX_ENTITY_SRC_GEN_CLONE_RECOMBINATION entry with matching .step_id is expected. ; _item.name '_pdbx_entity_src_gen_clone.gene_insert_method' _item.category_id pdbx_entity_src_gen_clone _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail L 'Ligation' R 'Recombination' save_ save__pdbx_entity_src_gen_clone.vector_name _item_description.description ; The name of the vector used in this cloning step. ; _item.name '_pdbx_entity_src_gen_clone.vector_name' _item.category_id pdbx_entity_src_gen_clone _item.mandatory_code no _item_type.code text save_ save__pdbx_entity_src_gen_clone.vector_details _item_description.description ; Details of any modifications made to the named vector. ; _item.name '_pdbx_entity_src_gen_clone.vector_details' _item.category_id pdbx_entity_src_gen_clone _item.mandatory_code no _item_type.code text save_ save__pdbx_entity_src_gen_clone.transformation_method _item_description.description ; The method used to transform the expression cell line with the vector ; _item.name '_pdbx_entity_src_gen_clone.transformation_method' _item.category_id pdbx_entity_src_gen_clone _item.mandatory_code no _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail H 'Heat shock' E 'Electroporation' C 'Calcium shock' save_ save__pdbx_entity_src_gen_clone.marker _item_description.description ; The type of marker included to allow selection of transformed cells ; _item.name '_pdbx_entity_src_gen_clone.marker' _item.category_id pdbx_entity_src_gen_clone _item.mandatory_code no _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail A 'Antibiotic resistance' F 'Fluorescence' save_ save__pdbx_entity_src_gen_clone.verification_method _item_description.description ; The method used to verify that the incorporated gene is correct ; _item.name '_pdbx_entity_src_gen_clone.verification_method' _item.category_id pdbx_entity_src_gen_clone _item.mandatory_code no _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail P 'PCR on plasmid' R 'Restriction enzyme digestion' D 'DNA sequencing' save_ save__pdbx_entity_src_gen_clone.purification_details _item_description.description ; Details of any purification of the product. ; _item.name '_pdbx_entity_src_gen_clone.purification_details' _item.category_id pdbx_entity_src_gen_clone _item.mandatory_code no _item_type.code text save_ save__pdbx_entity_src_gen_clone.summary _item_description.description ; Summary of ligation or recombionation cloning used, the associated verification method and any purification of the product. ; _item.name '_pdbx_entity_src_gen_clone.summary' _item.category_id pdbx_entity_src_gen_clone _item.mandatory_code no _item_type.code text save_ ###################################### # PDBX_ENTITY_SRC_GEN_CLONE_LIGATION # ###################################### # # _pdbx_entity_src_gen_clone_ligation.entry_id # _pdbx_entity_src_gen_clone_ligation.entity_id # _pdbx_entity_src_gen_clone_ligation.step_id # _pdbx_entity_src_gen_clone_ligation.cleavage_enzymes # _pdbx_entity_src_gen_clone_ligation.ligation_enzymes # _pdbx_entity_src_gen_clone_ligation.temperature # _pdbx_entity_src_gen_clone_ligation.time # _pdbx_entity_src_gen_clone_ligation.details # save_pdbx_entity_src_gen_clone_ligation _category.description ; This category contains details for the ligation-based cloning steps used in the overall protein production process. _pdbx_entity_src_gen_clone_ligation.clone_step_id in this category must point at a defined _pdbx_entity_src_gen_clone.step_id. The details in PDBX_ENTITY_SRC_GEN_CLONE_LIGATION extend the details in PDBX_ENTITY_SRC_GEN_CLONE to cover ligation dependent cloning steps. ; _category.id pdbx_entity_src_gen_clone_ligation _category.mandatory_code no loop_ _category_group.id 'inclusive_group' 'protein_production_group' 'entity_group' 'pdbx_group' loop_ _category_key.name '_pdbx_entity_src_gen_clone_ligation.entry_id' '_pdbx_entity_src_gen_clone_ligation.entity_id' '_pdbx_entity_src_gen_clone_ligation.step_id' save_ save__pdbx_entity_src_gen_clone_ligation.entry_id _item_description.description ; This item is a pointer to _pdbx_entity_src_gen_clone.entry_id in the PDBX_ENTITY_SRC_GEN_CLONE category. ; _item.name '_pdbx_entity_src_gen_clone_ligation.entry_id' _item.category_id pdbx_entity_src_gen_clone_ligation _item.mandatory_code yes _item_linked.parent_name '_pdbx_entity_src_gen_clone.entry_id' _item_linked.child_name '_pdbx_entity_src_gen_clone_ligation.entry_id' save_ save__pdbx_entity_src_gen_clone_ligation.entity_id _item_description.description ; This item is a pointer to _pdbx_entity_src_gen_clone.entity_id in the PDBX_ENTITY_SRC_GEN_CLONE category. ; _item.name '_pdbx_entity_src_gen_clone_ligation.entity_id' _item.category_id pdbx_entity_src_gen_clone_ligation _item.mandatory_code yes _item_linked.parent_name '_pdbx_entity_src_gen_clone.entity_id' _item_linked.child_name '_pdbx_entity_src_gen_clone_ligation.entity_id' save_ save__pdbx_entity_src_gen_clone_ligation.step_id _item_description.description ; This item is a pointer to _pdbx_entity_src_gen_clone.step_id in the PDBX_ENTITY_SRC_GEN_CLONE category. ; _item.name '_pdbx_entity_src_gen_clone_ligation.step_id' _item.category_id pdbx_entity_src_gen_clone_ligation _item.mandatory_code yes _item_linked.parent_name '_pdbx_entity_src_gen_clone.step_id' _item_linked.child_name '_pdbx_entity_src_gen_clone_ligation.step_id' save_ save__pdbx_entity_src_gen_clone_ligation.cleavage_enzymes _item_description.description ; The names of the enzymes used to cleave the vector. In addition an enzyme used to blunt the cut ends, etc., should be named here. ; _item.name '_pdbx_entity_src_gen_clone_ligation.cleavage_enzymes' _item.category_id pdbx_entity_src_gen_clone_ligation _item.mandatory_code yes _item_type.code text save_ save__pdbx_entity_src_gen_clone_ligation.ligation_enzymes _item_description.description ; The names of the enzymes used to ligate the gene into the cleaved vector. ; _item.name '_pdbx_entity_src_gen_clone_ligation.ligation_enzymes' _item.category_id pdbx_entity_src_gen_clone_ligation _item.mandatory_code yes _item_type.code text save_ save__pdbx_entity_src_gen_clone_ligation.temperature _item_description.description ; The temperature at which the ligation experiment was performed, in degrees celsius. ; _item.name '_pdbx_entity_src_gen_clone_ligation.temperature' _item.category_id pdbx_entity_src_gen_clone_ligation _item.mandatory_code yes _item_type.code float _item_units.code celsius save_ save__pdbx_entity_src_gen_clone_ligation.time _item_description.description ; The duration of the ligation reaction in minutes. ; _item.name '_pdbx_entity_src_gen_clone_ligation.time' _item.category_id pdbx_entity_src_gen_clone_ligation _item.mandatory_code yes _item_type.code int _item_units.code minutes save_ save__pdbx_entity_src_gen_clone_ligation.details _item_description.description ; Any details to be associated with this ligation step, e.g. the protocol. ; _item.name '_pdbx_entity_src_gen_clone_ligation.details' _item.category_id pdbx_entity_src_gen_clone_ligation _item.mandatory_code no _item_type.code text save_ ########################################### # PDBX_ENTITY_SRC_GEN_CLONE_RECOMBINATION # ########################################### # # _pdbx_entity_src_gen_clone_recombination.entry__id # _pdbx_entity_src_gen_clone_recombination.entity_id # _pdbx_entity_src_gen_clone_recombination.step_id # _pdbx_entity_src_gen_clone_recombination.system # _pdbx_entity_src_gen_clone_recombination.recombination_enzymes # _pdbx_entity_src_gen_clone_recombination.details # save_pdbx_entity_src_gen_clone_recombination _category.description ; This category contains details for the recombination-based cloning steps used in the overall protein production process. It is assumed that these reactions will use commercially available kits. _pdbx_entity_src_gen_clone_recombination.clone_step_id in this category must point at a defined _pdbx_entity_src_gen_clone.step_id. The details in PDBX_ENTITY_SRC_GEN_CLONE_RECOMBINATION extend the details in PDBX_ENTITY_SRC_GEN_CLONE to cover recombination dependent cloning steps. ; _category.id pdbx_entity_src_gen_clone_recombination _category.mandatory_code no loop_ _category_group.id 'inclusive_group' 'protein_production_group' 'entity_group' 'pdbx_group' loop_ _category_key.name '_pdbx_entity_src_gen_clone_recombination.entry_id' '_pdbx_entity_src_gen_clone_recombination.entity_id' '_pdbx_entity_src_gen_clone_recombination.step_id' save_ save__pdbx_entity_src_gen_clone_recombination.entry_id _item_description.description ; This item is a pointer to _pdbx_entity_src_gen_clone.entry_id in the PDBX_ENTITY_SRC_GEN_CLONE category. ; _item.name '_pdbx_entity_src_gen_clone_recombination.entry_id' _item.category_id pdbx_entity_src_gen_clone_recombination _item.mandatory_code yes _item_linked.parent_name '_pdbx_entity_src_gen_clone.entry_id' _item_linked.child_name '_pdbx_entity_src_gen_clone_recombination.entry_id' save_ save__pdbx_entity_src_gen_clone_recombination.entity_id _item_description.description ; This item is a pointer to _pdbx_entity_src_gen_clone.entity_id in the PDBX_ENTITY_SRC_GEN_CLONE category. ; _item.name '_pdbx_entity_src_gen_clone_recombination.entity_id' _item.category_id pdbx_entity_src_gen_clone_recombination _item.mandatory_code yes _item_linked.parent_name '_pdbx_entity_src_gen_clone.entity_id' _item_linked.child_name '_pdbx_entity_src_gen_clone_recombination.entity_id' save_ save__pdbx_entity_src_gen_clone_recombination.step_id _item_description.description ; This item is a pointer to _pdbx_entity_src_gen_clone.step_id in the PDBX_ENTITY_SRC_GEN_CLONE category. ; _item.name '_pdbx_entity_src_gen_clone_recombination.step_id' _item.category_id pdbx_entity_src_gen_clone_recombination _item.mandatory_code yes _item_linked.parent_name '_pdbx_entity_src_gen_clone.step_id' _item_linked.child_name '_pdbx_entity_src_gen_clone_recombination.step_id' save_ save__pdbx_entity_src_gen_clone_recombination.system _item_description.description ; The name of the recombination system. ; _item.name '_pdbx_entity_src_gen_clone_recombination.system' _item.category_id pdbx_entity_src_gen_clone_recombination _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail G 'Gateway Tm' I 'Infusion/Creator Tm' N 'Novagen's system - name?' save_ save__pdbx_entity_src_gen_clone_recombination.recombination_enzymes _item_description.description ; The names of the enzymes used for this recombination step. ; _item.name '_pdbx_entity_src_gen_clone_recombination.recombination_enzymes' _item.category_id pdbx_entity_src_gen_clone_recombination _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail B 'Gateway BP clonase' L 'Gateway LR clonase' T 'Topoisomerase' C 'Cre recombinase' I 'Infusion enzyme - name?' save_ save__pdbx_entity_src_gen_clone_recombination.details _item_description.description ; Any details to be associated with this recombination step, e.g. the protocol or differences from the manufacturer's specified protocol. ; _item.name '_pdbx_entity_src_gen_clone_recombination.details' _item.category_id pdbx_entity_src_gen_clone_recombination _item.mandatory_code no _item_type.code text save_ ############################### # PDBX_ENTITY_SRC_GEN_EXPRESS # ############################### # # _pdbx_entity_src_gen_express.entry_id # _pdbx_entity_src_gen_express.entity_id # _pdbx_entity_src_gen_express.step_id # _pdbx_entity_src_gen_express.next_step_id # _pdbx_entity_src_gen_express.end_construct_id # _pdbx_entity_src_gen_express.robot_id # _pdbx_entity_src_gen_express.date # _pdbx_entity_src_gen_express.promoter_type # _pdbx_entity_src_gen_express.plasmid_id # _pdbx_entity_src_gen_express.vector_type # _pdbx_entity_src_gen_express.N_terminal_seq_tag # _pdbx_entity_src_gen_express.C_terminal_seq_tag # _pdbx_entity_src_gen_express.host_org_scientific_name # _pdbx_entity_src_gen_express.host_org_common_name # _pdbx_entity_src_gen_express.host_org_variant # _pdbx_entity_src_gen_express.host_org_strain # _pdbx_entity_src_gen_express.host_org_tissue # _pdbx_entity_src_gen_express.host_org_tax_id # _pdbx_entity_src_gen_express.host_org_culture_collection # _pdbx_entity_src_gen_express.host_org_cell_line # _pdbx_entity_src_gen_express.host_org_details # _pdbx_entity_src_gen_express.culture_base_media # _pdbx_entity_src_gen_express.culture_additives # _pdbx_entity_src_gen_express.culture_volume # _pdbx_entity_src_gen_express.culture_time # _pdbx_entity_src_gen_express.culture_temperature # _pdbx_entity_src_gen_express.inducer # _pdbx_entity_src_gen_express.inducer_concentration # _pdbx_entity_src_gen_express.induction_details # _pdbx_entity_src_gen_express.multiplicity_of_infection # _pdbx_entity_src_gen_express.induction_growth_time # _pdbx_entity_src_gen_express.induction_temperature # _pdbx_entity_src_gen_express.harvesting_details # _pdbx_entity_src_gen_express.storage_details # # _pdbx_entity_src_gen_express.summary # save_pdbx_entity_src_gen_express _category.description ; This category contains details for the EXPRESSION steps used in the overall protein production process. It is hoped that this category will cover all forms of cell-based expression by reading induction as induction/transformation/transfection. ; _category.id pdbx_entity_src_gen_express _category.mandatory_code no loop_ _category_group.id 'inclusive_group' 'protein_production_group' 'entity_group' 'pdbx_group' loop_ _category_key.name '_pdbx_entity_src_gen_express.entry_id' '_pdbx_entity_src_gen_express.entity_id' '_pdbx_entity_src_gen_express.step_id' save_ save__pdbx_entity_src_gen_express.entry_id _item_description.description ; The value of _pdbx_entity_src_gen_express.entry_id uniquely identifies a sample consisting of one or more proteins whose structure is to be determined. This is a pointer to _entry.id. This item may be a site dependent bar code. ; _item.name '_pdbx_entity_src_gen_express.entry_id' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code yes _item_type.code code _item_linked.parent_name '_entry.id' _item_linked.child_name '_pdbx_entity_src_gen_express.entry_id' save_ save__pdbx_entity_src_gen_express.entity_id _item_description.description ; The value of _pdbx_entity_src_gen_express.entity_id uniquely identifies each protein contained in the project target complex proteins whose structure is to be determined. This data item is a pointer to _entity.id in the ENTITY category. This item may be a site dependent bar code. ; _item.name '_pdbx_entity_src_gen_express.entity_id' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code yes _item_type.code code _item_linked.parent_name '_entity.id' _item_linked.child_name '_pdbx_entity_src_gen_express.entity_id' save_ save__pdbx_entity_src_gen_express.step_id _item_description.description ; This item is the unique identifier for this expression step. ; _item.name '_pdbx_entity_src_gen_express.step_id' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code yes _item_type.code int save_ save__pdbx_entity_src_gen_express.next_step_id _item_description.description ; This item unique identifier for the next production step. This allows a workflow to have multiple entry points leading to a single product. ; _item.name '_pdbx_entity_src_gen_express.next_step_id' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code yes _item_type.code int save_ save__pdbx_entity_src_gen_express.end_construct_id _item_description.description ; This item is a pointer to pdbx_construct.id in the PDBX_CONSTRUCT category. The referenced sequence is expected to be the amino acid sequence of the expressed product. ; _item.name '_pdbx_entity_src_gen_express.end_construct_id' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code no _item_type.code int _item_linked.parent_name '_pdbx_construct.id' _item_linked.child_name '_pdbx_entity_src_gen_express.end_construct_id' save_ save__pdbx_entity_src_gen_express.robot_id _item_description.description ; This data item is a pointer to pdbx_robot_system.id in the PDBX_ROBOT_SYSTEM category. ; _item.name '_pdbx_entity_src_gen_express.robot_id' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code no _item_linked.parent_name '_pdbx_robot_system.id' _item_linked.child_name '_pdbx_entity_src_gen_express.robot_id' save_ save__pdbx_entity_src_gen_express.date _item_description.description ; The date of production step. ; _item.name '_pdbx_entity_src_gen_express.date' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code no _item_type.code yyyy-mm-dd:hh:mm loop_ _item_examples.case '2003-12-25' '2003-12-25:09:00' save_ save__pdbx_entity_src_gen_express.promoter_type _item_description.description ; The nature of the promoter controlling expression of the gene. ; _item.name '_pdbx_entity_src_gen_express.promoter_type' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code yes _item_type.code text _item_examples.case 'T7 LacZ' save_ save__pdbx_entity_src_gen_express.plasmid_id _item_description.description ; This item is a pointer to _pdbx_construct.id in the PDBX_CONSTRUCT category. The referenced entry will contain the nucleotide sequence that is to be expressed, including tags. ; _item.name '_pdbx_entity_src_gen_express.plasmid_id' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code yes _item_type.code code _item_linked.parent_name '_pdbx_construct.id' _item_linked.child_name '_pdbx_entity_src_gen_express.plasmid_id' save_ save__pdbx_entity_src_gen_express.vector_type _item_description.description ; Identifies the type of vector used (plasmid, virus, or cosmid) in the expression system. ; _item.name '_pdbx_entity_src_gen_express.vector_type' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code yes _item_type.code code save_ save__pdbx_entity_src_gen_express.N_terminal_seq_tag _item_description.description ; Any N-terminal sequence tag as a string of one letter amino acid codes. ; _item.name '_pdbx_entity_src_gen_express.N_terminal_seq_tag' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code yes _item_type.code text save_ save__pdbx_entity_src_gen_express.C_terminal_seq_tag _item_description.description ; Any C-terminal sequence tag as a string of one letter amino acid codes ; _item.name '_pdbx_entity_src_gen_express.C_terminal_seq_tag' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code yes _item_type.code text save_ save__pdbx_entity_src_gen_express.host_org_scientific_name _item_description.description ; The scientific name of the organism that served as host for the expression system. It is expected that either this item or _pdbx_entity_src_gen_express.host_org_tax_id should be populated. ; _item.name '_pdbx_entity_src_gen_express.host_org_scientific_name' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code no _item_type.code line save_ save__pdbx_entity_src_gen_express.host_org_common_name _item_description.description ; The common name of the organism that served as host for the expression system. Where _pdbx_entity_src_gen_express.host_org_tax_id is populated it is expected that this item may be derived by look up against the taxonomy database. ; _item.name '_pdbx_entity_src_gen_express.host_org_common_name' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code no _item_type.code line save_ save__pdbx_entity_src_gen_express.host_org_variant _item_description.description ; The vairant of the organism that served as host for the expression system. Where _pdbx_entity_src_gen_express.host_org_tax_id is populated it is expected that this item may be derived by a look up against the taxonomy database. ; _item.name '_pdbx_entity_src_gen_express.host_org_variant' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code no _item_type.code line save_ save__pdbx_entity_src_gen_express.host_org_strain _item_description.description ; The strain of the organism that served as host for the expression system. Where _pdbx_entity_src_gen_express.host_org_tax_id is populated it is expected that this item may be derived by a look up against the taxonomy database. ; _item.name '_pdbx_entity_src_gen_express.host_org_strain' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code no _item_type.code line save_ save__pdbx_entity_src_gen_express.host_org_tissue _item_description.description ; The specific tissue which expressed the molecule. ; _item.name '_pdbx_entity_src_gen_express.host_org_tissue' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code no _item_type.code line save_ save__pdbx_entity_src_gen_express.host_org_culture_collection _item_description.description ; Culture collection of the expression system ; _item.name '_pdbx_entity_src_gen_express.host_org_culture_collection' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code no _item_type.code line save_ save__pdbx_entity_src_gen_express.host_org_cell_line _item_description.description ; A specific line of cells used as the expression system ; _item.name '_pdbx_entity_src_gen_express.host_org_cell_line' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code no _item_type.code line save_ save__pdbx_entity_src_gen_express.host_org_tax_id _item_description.description ; The id for the NCBI taxonomy node corresponding to the organism that served as host for the expression system. ; _item.name '_pdbx_entity_src_gen_express.host_org_tax_id' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code no _item_type.code line save_ save__pdbx_entity_src_gen_express.host_org_details _item_description.description ; A description of special aspects of the organism that served as host for the expression system. ; _item.name '_pdbx_entity_src_gen_express.host_org_details' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code no _item_type.code text save_ save__pdbx_entity_src_gen_express.culture_base_media _item_description.description ; The name of the base media in which the expression host was grown. ; _item.name '_pdbx_entity_src_gen_express.culture_base_media' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code no _item_type.code text save_ save__pdbx_entity_src_gen_express.culture_additives _item_description.description ; Any additives to the base media in which the expression host was grown. ; _item.name '_pdbx_entity_src_gen_express.culture_additives' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code no _item_type.code text save_ save__pdbx_entity_src_gen_express.culture_volume _item_description.description ; The volume of media in milliliters in which the expression host was grown. ; _item.name '_pdbx_entity_src_gen_express.culture_volume' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code yes _item_type.code float _item_units.code milliliters save_ save__pdbx_entity_src_gen_express.culture_time _item_description.description ; The time in hours for which the expression host was allowed to grow prior to induction/transformation/transfection. ; _item.name '_pdbx_entity_src_gen_express.culture_time' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code yes _item_type.code float _item_units.code hours save_ save__pdbx_entity_src_gen_express.culture_temperature _item_description.description ; The temperature in degrees celsius at which the expression host was allowed to grow prior to induction/transformation/transfection. ; _item.name '_pdbx_entity_src_gen_express.culture_temperature' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code yes _item_type.code float _item_units.code celsius save_ save__pdbx_entity_src_gen_express.inducer _item_description.description ; The chemical name of the inducing agent. ; _item.name '_pdbx_entity_src_gen_express.inducer' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code no _item_type.code line save_ save__pdbx_entity_src_gen_express.inducer_concentration _item_description.description ; Concentration of the inducing agent. ; _item.name '_pdbx_entity_src_gen_express.inducer_concentration' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code no _item_type.code float _item_units.code mg_per_ml save_ save__pdbx_entity_src_gen_express.induction_details _item_description.description ; Details of induction/transformation/transfection. ; _item.name '_pdbx_entity_src_gen_express.induction_details' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code no _item_type.code text save_ save__pdbx_entity_src_gen_express.multiplicity_of_infection _item_description.description ; The multiplicity of infection for genes introduced by transfection, eg. for baculovirus-based expression. ; _item.name '_pdbx_entity_src_gen_express.multiplicity_of_infection' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code no _item_type.code float _item_units.code arbitrary save_ save__pdbx_entity_src_gen_express.induction_timepoint _item_description.description ; The time in hours after induction/transformation/transfection at which the optical density of the culture was measured. ; _item.name '_pdbx_entity_src_gen_express.induction_timepoint' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code no _item_type.code float _item_units.code hours save_ save__pdbx_entity_src_gen_express.induction_temperature _item_description.description ; The temperature in celsius at which the induced/transformed/transfected cells were grown. ; _item.name '_pdbx_entity_src_gen_express.induction_temperature' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code yes _item_type.code float _item_units.code celsius save_ save__pdbx_entity_src_gen_express.harvesting_details _item_description.description ; Details of the harvesting protocol. ; _item.name '_pdbx_entity_src_gen_express.harvesting_details' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code no _item_type.code text save_ save__pdbx_entity_src_gen_express.storage_details _item_description.description ; Details of how the harvested culture was stored. ; _item.name '_pdbx_entity_src_gen_express.storage_details' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code no _item_type.code text save_ save__pdbx_entity_src_gen_express.summary _item_description.description ; Summary of the details of the expression steps used in protein production. ; _item.name '_pdbx_entity_src_gen_express.summary' _item.category_id pdbx_entity_src_gen_express _item.mandatory_code no _item_type.code text save_ ######################################### # PDBX_ENTITY_SRC_GEN_EXPRESS_TIMEPOINT # ######################################### # # _pdbx_entity_src_gen_express_timepoint.entry_id # _pdbx_entity_src_gen_express_timepoint.entity_id # _pdbx_entity_src_gen_express_timepoint.step_id # _pdbx_entity_src_gen_express_timepoint.serial # _pdbx_entity_src_gen_express_timepoint.time # _pdbx_entity_src_gen_express_timepoint.OD # save_pdbx_entity_src_gen_express_timepoint _category.description ; This category contains details for OD time series used to monitor a given EXPRESSION step used in the overall protein production process. ; _category.id pdbx_entity_src_gen_express_timepoint _category.mandatory_code no loop_ _category_group.id 'inclusive_group' 'protein_production_group' 'entity_group' 'pdbx_group' loop_ _category_key.name '_pdbx_entity_src_gen_express_timepoint.entry_id' '_pdbx_entity_src_gen_express_timepoint.entity_id' '_pdbx_entity_src_gen_express_timepoint.step_id' '_pdbx_entity_src_gen_express_timepoint.serial' save_ save__pdbx_entity_src_gen_express_timepoint.entry_id _item_description.description ; The value of _pdbx_entity_src_gen_express_timepoint.entry_id is a pointer to _pdbx_entity_src_gen_express.entry_id ; _item.name '_pdbx_entity_src_gen_express_timepoint.entry_id' _item.category_id pdbx_entity_src_gen_express_timepoint _item.mandatory_code yes _item_linked.parent_name '_pdbx_entity_src_gen_express.entry_id' _item_linked.child_name '_pdbx_entity_src_gen_express_timepoint.entry_id' save_ save__pdbx_entity_src_gen_express_timepoint.entity_id _item_description.description ; The value of _pdbx_entity_src_gen_express_timepoint.entity_id is a pointer to _pdbx_entity_src_gen_express.entity_id ; _item.name '_pdbx_entity_src_gen_express_timepoint.entity_id' _item.category_id pdbx_entity_src_gen_express_timepoint _item.mandatory_code yes _item_linked.parent_name '_pdbx_entity_src_gen_express.entity_id' _item_linked.child_name '_pdbx_entity_src_gen_express_timepoint.entity_id' save_ save__pdbx_entity_src_gen_express_timepoint.step_id _item_description.description ; This item is a pointer to _pdbx_entity_src_gen_express.step_id ; _item.name '_pdbx_entity_src_gen_express_timepoint.step_id' _item.category_id pdbx_entity_src_gen_express_timepoint _item.mandatory_code yes _item_linked.parent_name '_pdbx_entity_src_gen_express.step_id' _item_linked.child_name '_pdbx_entity_src_gen_express_timepoint.step_id' save_ save__pdbx_entity_src_gen_express_timepoint.serial _item_description.description ; This items uniquely defines a timepoint within a series. ; _item.name '_pdbx_entity_src_gen_express_timepoint.serial' _item.category_id pdbx_entity_src_gen_express_timepoint _item.mandatory_code yes _item_type.code int save_ save__pdbx_entity_src_gen_express_timepoint.OD _item_description.description ; The optical density of the expression culture in arbitrary units at the timepoint specified. ; _item.name '_pdbx_entity_src_gen_express_timepoint.OD' _item.category_id pdbx_entity_src_gen_express_timepoint _item.mandatory_code yes _item_type.code int save_ save__pdbx_entity_src_gen_express_timepoint.time _item_description.description ; The time in hours after induction/transformation/transfection at which the optical density of the culture was measured. ; _item.name '_pdbx_entity_src_gen_express_timepoint.time' _item.category_id pdbx_entity_src_gen_express_timepoint _item.mandatory_code yes _item_type.code int save_ ############################# # PDBX_ENTITY_SRC_GEN_LYSIS # ############################# # # _pdbx_entity_src_gen_lysis.entry_id # _pdbx_entity_src_gen_lysis.entity_id # _pdbx_entity_src_gen_lysis.step_id # _pdbx_entity_src_gen_lysis.next_step_id # _pdbx_entity_src_gen_lysis.end_construct_id # _pdbx_entity_src_gen_lysis.date # _pdbx_entity_src_gen_lysis.robot_id # _pdbx_entity_src_gen_lysis.method # _pdbx_entity_src_gen_lysis.buffer_id # _pdbx_entity_src_gen_lysis.buffer_volume # _pdbx_entity_src_gen_lysis.temperature # _pdbx_entity_src_gen_lysis.time # _pdbx_entity_src_gen_lysis.details # save_pdbx_entity_src_gen_lysis _category.description ; This category contains details for the cell lysis steps used in the overall protein production process. ; _category.id pdbx_entity_src_gen_lysis _category.mandatory_code no loop_ _category_group.id 'inclusive_group' 'protein_production_group' 'entity_group' 'pdbx_group' loop_ _category_key.name '_pdbx_entity_src_gen_lysis.entry_id' '_pdbx_entity_src_gen_lysis.entity_id' '_pdbx_entity_src_gen_lysis.step_id' save_ save__pdbx_entity_src_gen_lysis.entry_id _item_description.description ; The value of _pdbx_entity_src_gen_lysis.entry_id uniquely identifies a sample consisting of one or more proteins whose structure is to be determined. This is a pointer to _entry.id. This item may be a site dependent bar code. ; _item.name '_pdbx_entity_src_gen_lysis.entry_id' _item.category_id pdbx_entity_src_gen_lysis _item.mandatory_code yes _item_linked.parent_name '_entry.id' _item_linked.child_name '_pdbx_entity_src_gen_lysis.entry_id' save_ save__pdbx_entity_src_gen_lysis.entity_id _item_description.description ; The value of _pdbx_entity_src_gen_lysis.entity_id uniquely identifies each protein contained in the project target protein complex whose structure is to be determined. This data item is a pointer to _entity.id in the ENTITY category. This item may be a site dependent bar code. ; _item.name '_pdbx_entity_src_gen_lysis.entity_id' _item.category_id pdbx_entity_src_gen_lysis _item.mandatory_code yes _item_linked.parent_name '_entity.id' _item_linked.child_name '_pdbx_entity_src_gen_lysis.entity_id' save_ save__pdbx_entity_src_gen_lysis.step_id _item_description.description ; This item is the unique identifier for this lysis step. ; _item.name '_pdbx_entity_src_gen_lysis.step_id' _item.category_id pdbx_entity_src_gen_lysis _item.mandatory_code yes _item_type.code int save_ save__pdbx_entity_src_gen_lysis.next_step_id _item_description.description ; This item unique identifier for the next production step. This allows a workflow to have multiple entry points leading to a single product. ; _item.name '_pdbx_entity_src_gen_lysis.next_step_id' _item.category_id pdbx_entity_src_gen_lysis _item.mandatory_code yes _item_type.code int save_ save__pdbx_entity_src_gen_lysis.end_construct_id _item_description.description ; This item is a pointer to pdbx_construct.id in the PDBX_CONSTRUCT category. The referenced sequence is expected to be the amino acid sequence of the expressed product after lysis. ; _item.name '_pdbx_entity_src_gen_lysis.end_construct_id' _item.category_id pdbx_entity_src_gen_lysis _item.mandatory_code no _item_linked.parent_name '_pdbx_construct.id' _item_linked.child_name '_pdbx_entity_src_gen_lysis.end_construct_id' save_ save__pdbx_entity_src_gen_lysis.robot_id _item_description.description ; This data item is a pointer to pdbx_robot_system.id in the PDBX_ROBOT_SYSTEM category. ; _item.name '_pdbx_entity_src_gen_lysis.robot_id' _item.category_id pdbx_entity_src_gen_lysis _item.mandatory_code no _item_linked.parent_name '_pdbx_robot_system.id' _item_linked.child_name '_pdbx_entity_src_gen_lysis.robot_id' save_ save__pdbx_entity_src_gen_lysis.date _item_description.description ; The date of this production step. ; _item.name '_pdbx_entity_src_gen_lysis.date' _item.category_id pdbx_entity_src_gen_lysis _item.mandatory_code no _item_type.code yyyy-mm-dd:hh:mm loop_ _item_examples.case '2003-12-25' '2003-12-25:09:00' save_ save__pdbx_entity_src_gen_lysis.method _item_description.description ; The lysis method. ; _item.name '_pdbx_entity_src_gen_lysis.method' _item.category_id pdbx_entity_src_gen_lysis _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail S 'Sonication' D 'Detergent' B 'Sonication and detergent' save_ save__pdbx_entity_src_gen_lysis.buffer_id _item_description.description ; This item is a pointer to pdbx_buffer.id in the PDBX_BUFFER category. The referenced buffer is that in which the lysis was performed. ; _item.name '_pdbx_entity_src_gen_lysis.buffer_id' _item.category_id pdbx_entity_src_gen_lysis _item.mandatory_code yes _item_type.code code _item_linked.parent_name '_pdbx_buffer.id' _item_linked.child_name '_pdbx_entity_src_gen_lysis.buffer_id' save_ save__pdbx_entity_src_gen_lysis.buffer_volume _item_description.description ; The volume in milliliters of buffer in which the lysis was performed. ; _item.name '_pdbx_entity_src_gen_lysis.buffer_volume' _item.category_id pdbx_entity_src_gen_lysis _item.mandatory_code yes _item_type.code float _item_units.code milliliters save_ save__pdbx_entity_src_gen_lysis.temperature _item_description.description ; The temperature in degrees celsius at which the lysis was performed. ; _item.name '_pdbx_entity_src_gen_lysis.temperature' _item.category_id pdbx_entity_src_gen_lysis _item.mandatory_code yes _item_type.code float _item_units.code celsius save_ save__pdbx_entity_src_gen_lysis.time _item_description.description ; The time in seconds of the lysis experiment. ; _item.name '_pdbx_entity_src_gen_lysis.time' _item.category_id pdbx_entity_src_gen_lysis _item.mandatory_code yes _item_type.code float _item_units.code minutes save_ save__pdbx_entity_src_gen_lysis.details _item_description.description ; String value containing details of the lysis protocol. ; _item.name '_pdbx_entity_src_gen_lysis.details' _item.category_id pdbx_entity_src_gen_lysis _item.mandatory_code no _item_type.code text save_ ############################## # PDBX_ENTITY_SRC_GEN_REFOLD # ############################## # # _pdbx_entity_src_gen_refold.entry_id # _pdbx_entity_src_gen_refold.entity_id # _pdbx_entity_src_gen_refold.step_id # _pdbx_entity_src_gen_refold.next_step_id # _pdbx_entity_src_gen_refold.end_construct_id # _pdbx_entity_src_gen_refold.robot_id # _pdbx_entity_src_gen_refold.date # _pdbx_entity_src_gen_refold.denature_buffer_id # _pdbx_entity_src_gen_refold.refold_buffer_id # _pdbx_entity_src_gen_refold.temperature # _pdbx_entity_src_gen_refold.time # _pdbx_entity_src_gen_refold.storage_buffer_id # _pdbx_entity_src_gen_refold.details # save_pdbx_entity_src_gen_refold _category.description ; This category contains details for the refolding steps used in the overall protein production process. ; _category.id pdbx_entity_src_gen_refold _category.mandatory_code no loop_ _category_group.id 'inclusive_group' 'protein_production_group' 'entity_group' 'pdbx_group' loop_ _category_key.name '_pdbx_entity_src_gen_refold.entry_id' '_pdbx_entity_src_gen_refold.entity_id' '_pdbx_entity_src_gen_refold.step_id' save_ save__pdbx_entity_src_gen_refold.entry_id _item_description.description ; The value of _pdbx_entity_src_gen_refold.entry_id uniquely identifies a sample consisting of one or more proteins whose structure is to be determined. This is a pointer to _entry.id. This item may be a site dependent bar code. ; _item.name '_pdbx_entity_src_gen_refold.entry_id' _item.category_id pdbx_entity_src_gen_refold _item.mandatory_code yes _item_linked.parent_name '_entry.id' _item_linked.child_name '_pdbx_entity_src_gen_refold.entry_id' save_ save__pdbx_entity_src_gen_refold.entity_id _item_description.description ; The value of _pdbx_entity_src_gen_refold.entity_id uniquely identifies each protein contained in the project target protein complex whose structure is to be determined. This data item is a pointer to _entity.id in the ENTITY category. This item may be a site dependent bar code. ; _item.name '_pdbx_entity_src_gen_refold.entity_id' _item.category_id pdbx_entity_src_gen_refold _item.mandatory_code yes _item_linked.parent_name '_entity.id' _item_linked.child_name '_pdbx_entity_src_gen_refold.entity_id' save_ save__pdbx_entity_src_gen_refold.step_id _item_description.description ; This item is the unique identifier for this refolding step. ; _item.name '_pdbx_entity_src_gen_refold.step_id' _item.category_id pdbx_entity_src_gen_refold _item.mandatory_code yes _item_type.code int save_ save__pdbx_entity_src_gen_refold.next_step_id _item_description.description ; This item unique identifier for the next production step. This allows a workflow to have multiple entry points leading to a single product. ; _item.name '_pdbx_entity_src_gen_refold.next_step_id' _item.category_id pdbx_entity_src_gen_refold _item.mandatory_code yes _item_type.code int save_ save__pdbx_entity_src_gen_refold.end_construct_id _item_description.description ; This item is a pointer to pdbx_construct.id in the PDBX_CONSTRUCT category. The referenced sequence is expected to be the amino acid sequence of the expressed product after the refolding step. ; _item.name '_pdbx_entity_src_gen_refold.end_construct_id' _item.category_id pdbx_entity_src_gen_refold _item.mandatory_code no _item_linked.parent_name '_pdbx_construct.id' _item_linked.child_name '_pdbx_entity_src_gen_refold.end_construct_id' save_ save__pdbx_entity_src_gen_refold.robot_id _item_description.description ; This data item is a pointer to pdbx_robot_system.id in the PDBX_ROBOT_SYSTEM category. ; _item.name '_pdbx_entity_src_gen_refold.robot_id' _item.category_id pdbx_entity_src_gen_refold _item.mandatory_code no _item_linked.parent_name '_pdbx_robot_system.id' _item_linked.child_name '_pdbx_entity_src_gen_refold.robot_id' save_ save__pdbx_entity_src_gen_refold.date _item_description.description ; The date of this production step. ; _item.name '_pdbx_entity_src_gen_refold.date' _item.category_id pdbx_entity_src_gen_refold _item.mandatory_code no _item_type.code yyyy-mm-dd:hh:mm loop_ _item_examples.case '2003-12-25' '2003-12-25:09:00' save_ save__pdbx_entity_src_gen_refold.denature_buffer_id _item_description.description ; This item is a pointer to pdbx_buffer.id in the PDBX_BUFFER category. The referenced buffer is that in which the protein was denatured. ; _item.name '_pdbx_entity_src_gen_refold.denature_buffer_id' _item.category_id pdbx_entity_src_gen_refold _item.mandatory_code yes _item_linked.parent_name '_pdbx_buffer.id' _item_linked.child_name '_pdbx_entity_src_gen_refold.denature_buffer_id' save_ save__pdbx_entity_src_gen_refold.refold_buffer_id _item_description.description ; This item is a pointer to pdbx_buffer.id in the PDBX_BUFFER category. The referenced buffer is that in which the protein was refolded. ; _item.name '_pdbx_entity_src_gen_refold.refold_buffer_id' _item.category_id pdbx_entity_src_gen_refold _item.mandatory_code yes _item_linked.parent_name '_pdbx_buffer.id' _item_linked.child_name '_pdbx_entity_src_gen_refold.refold_buffer_id' save_ save__pdbx_entity_src_gen_refold.temperature _item_description.description ; The temperature in degrees celsius at which the protein was refolded. ; _item.name '_pdbx_entity_src_gen_refold.temperature' _item.category_id pdbx_entity_src_gen_refold _item.mandatory_code yes _item_type.code float _item_units.code celsius save_ save__pdbx_entity_src_gen_refold.time _item_description.description ; The time in hours over which the protein was refolded. ; _item.name '_pdbx_entity_src_gen_refold.time' _item.category_id pdbx_entity_src_gen_refold _item.mandatory_code yes _item_type.code float _item_units.code hours save_ save__pdbx_entity_src_gen_refold.storage_buffer_id _item_description.description ; This item is a pointer to pdbx_buffer.id in the PDBX_BUFFER category. The referenced buffer is that in which the refolded protein was stored. ; _item.name '_pdbx_entity_src_gen_refold.storage_buffer_id' _item.category_id pdbx_entity_src_gen_refold _item.mandatory_code yes _item_linked.parent_name '_pdbx_buffer.id' _item_linked.child_name '_pdbx_entity_src_gen_refold.storage_buffer_id' save_ save__pdbx_entity_src_gen_refold.details _item_description.description ; String value containing details of the refolding. ; _item.name '_pdbx_entity_src_gen_refold.details' _item.category_id pdbx_entity_src_gen_refold _item.mandatory_code no _item_type.code text save_ ################################### # PDBX_ENTITY_SRC_GEN_PROTEOLYSIS # ################################### # # _pdbx_entity_src_gen_proteolysis.entry_id # _pdbx_entity_src_gen_proteolysis.entity_id # _pdbx_entity_src_gen_proteolysis.step_id # _pdbx_entity_src_gen_proteolysis.next_step_id # _pdbx_entity_src_gen_proteolysis.end_construct_id # _pdbx_entity_src_gen_proteolysis.date # _pdbx_entity_src_gen_proteolysis.robot_id # _pdbx_entity_src_gen_proteolysis.details # _pdbx_entity_src_gen_proteolysis.protease # _pdbx_entity_src_gen_proteolysis.protein_protease_ratio # _pdbx_entity_src_gen_proteolysis.cleavage_buffer # _pdbx_entity_src_gen_proteolysis.cleavage_temperature # _pdbx_entity_src_gen_proteolysis.cleavage_time # save_pdbx_entity_src_gen_proteolysis _category.description ; This category contains details for the protein purification tag removal steps used in the overall protein production process ; _category.id pdbx_entity_src_gen_proteolysis _category.mandatory_code no loop_ _category_group.id 'inclusive_group' 'protein_production_group' 'entity_group' 'pdbx_group' loop_ _category_key.name '_pdbx_entity_src_gen_proteolysis.entry_id' '_pdbx_entity_src_gen_proteolysis.entity_id' '_pdbx_entity_src_gen_proteolysis.step_id' save_ save__pdbx_entity_src_gen_proteolysis.entry_id _item_description.description ; The value of _pdbx_entity_src_gen_proteolysis.entry_id uniquely identifies a sample consisting of one or more proteins whose structure is to be determined. This is a pointer to _entry.id. This item may be a site dependent bar code. ; _item.name '_pdbx_entity_src_gen_proteolysis.entry_id' _item.category_id pdbx_entity_src_gen_proteolysis _item.mandatory_code yes _item_linked.parent_name '_entry.id' _item_linked.child_name '_pdbx_entity_src_gen_proteolysis.entry_id' save_ save__pdbx_entity_src_gen_proteolysis.entity_id _item_description.description ; The value of _pdbx_entity_src_gen_proteolysis.entity_id uniquely identifies each protein contained in the project target complex proteins whose structure is to be determined. This data item is a pointer to _entity.id in the ENTITY category. This item may be a site dependent bar code. ; _item.name '_pdbx_entity_src_gen_proteolysis.entity_id' _item.category_id pdbx_entity_src_gen_proteolysis _item.mandatory_code yes _item_linked.parent_name '_entity.id' _item_linked.child_name '_pdbx_entity_src_gen_proteolysis.entity_id' save_ save__pdbx_entity_src_gen_proteolysis.step_id _item_description.description ; This item is the unique identifier for this tag removal step. ; _item.name '_pdbx_entity_src_gen_proteolysis.step_id' _item.category_id pdbx_entity_src_gen_proteolysis _item.mandatory_code yes _item_type.code int save_ save__pdbx_entity_src_gen_proteolysis.next_step_id _item_description.description ; This item unique identifier for the next production step. This allows a workflow to have multiple entry points leading to a single product. ; _item.name '_pdbx_entity_src_gen_proteolysis.next_step_id' _item.category_id pdbx_entity_src_gen_proteolysis _item.mandatory_code yes _item_type.code int save_ save__pdbx_entity_src_gen_proteolysis.end_construct_id _item_description.description ; This item is a pointer to pdbx_construct.id in the PDBX_CONSTRUCT category. The referenced sequence is expected to be the amino acid sequence of the expressed product after the proteolysis step. ; _item.name '_pdbx_entity_src_gen_proteolysis.end_construct_id' _item.category_id pdbx_entity_src_gen_proteolysis _item.mandatory_code no _item_linked.parent_name '_pdbx_construct.id' _item_linked.child_name '_pdbx_entity_src_gen_proteolysis.end_construct_id' save_ save__pdbx_entity_src_gen_proteolysis.robot_id _item_description.description ; This data item is a pointer to pdbx_robot_system.id in the PDBX_ROBOT_SYSTEM category. ; _item.name '_pdbx_entity_src_gen_proteolysis.robot_id' _item.category_id pdbx_entity_src_gen_proteolysis _item.mandatory_code no _item_linked.parent_name '_pdbx_robot_system.id' _item_linked.child_name '_pdbx_entity_src_gen_proteolysis.robot_id' save_ save__pdbx_entity_src_gen_proteolysis.date _item_description.description ; The date of production step. ; _item.name '_pdbx_entity_src_gen_proteolysis.date' _item.category_id pdbx_entity_src_gen_proteolysis _item.mandatory_code no _item_type.code yyyy-mm-dd:hh:mm loop_ _item_examples.case '2003-12-25' '2003-12-25:09:00' save_ save__pdbx_entity_src_gen_proteolysis.details _item_description.description ; Details of this tag removal step. ; _item.name '_pdbx_entity_src_gen_proteolysis.details' _item.category_id pdbx_entity_src_gen_proteolysis _item.mandatory_code no _item_type.code text save_ save__pdbx_entity_src_gen_proteolysis.protease _item_description.description ; The name of the protease used for cleavage. ; _item.name '_pdbx_entity_src_gen_proteolysis.protease' _item.category_id pdbx_entity_src_gen_proteolysis _item.mandatory_code yes _item_type.code text save_ save__pdbx_entity_src_gen_proteolysis.protein_protease_ratio _item_description.description ; The ratio of protein to protease used for the cleavage. = mol protein / mol protease ; _item.name '_pdbx_entity_src_gen_proteolysis.protein_protease_ratio' _item.category_id pdbx_entity_src_gen_proteolysis _item.mandatory_code no _item_type.code float save_ save__pdbx_entity_src_gen_proteolysis.cleavage_buffer_id _item_description.description ; This item is a pointer to pdbx_buffer.id in the PDBX_BUFFER category. The referenced buffer is that in which the cleavage was performed. ; _item.name '_pdbx_entity_src_gen_proteolysis.cleavage_buffer_id' _item.category_id pdbx_entity_src_gen_proteolysis _item.mandatory_code no _item_linked.parent_name '_pdbx_buffer.id' _item_linked.child_name '_pdbx_entity_src_gen_proteolysis.cleavage_buffer_id' save_ save__pdbx_entity_src_gen_proteolysis.cleavage_temperature _item_description.description ; The temperature in degrees celsius at which the cleavage was performed. ; _item.name '_pdbx_entity_src_gen_proteolysis.cleavage_temperature' _item.category_id pdbx_entity_src_gen_proteolysis _item.mandatory_code no _item_type.code float _item_units.code celsius save_ save__pdbx_entity_src_gen_proteolysis.cleavage_time _item_description.description ; The time in minutes for the cleavage reaction ; _item.name '_pdbx_entity_src_gen_proteolysis.cleavage_time' _item.category_id pdbx_entity_src_gen_proteolysis _item.mandatory_code no _item_type.code float _item_units.code minutes save_ ############################# # PDBX_ENTITY_SRC_GEN_CHROM # ############################# # # _pdbx_entity_src_gen_chrom.entry_id # _pdbx_entity_src_gen_chrom.entity_id # _pdbx_entity_src_gen_chrom.step_id # _pdbx_entity_src_gen_chrom.next_step_id # _pdbx_entity_src_gen_chrom.end_construct_id # _pdbx_entity_src_gen_chrom.robot_id # _pdbx_entity_src_gen_chrom.date # _pdbx_entity_src_gen_chrom.column_type # _pdbx_entity_src_gen_chrom.column_volume # _pdbx_entity_src_gen_chrom.column_temperature # _pdbx_entity_src_gen_chrom.equilibration_buffer # _pdbx_entity_src_gen_chrom.flow_rate # _pdbx_entity_src_gen_chrom.elution_protocol # _pdbx_entity_src_gen_chrom.sample_prep_details # _pdbx_entity_src_gen_chrom.sample_volume # _pdbx_entity_src_gen_chrom.protein_concentration # _pdbx_entity_src_gen_chrom.volume_fraction # _pdbx_entity_src_gen_chrom.volume_pooled_fractions # _pdbx_entity_src_gen_chrom.yield_pooled_fractions # _pdbx_entity_src_gen_chrom.yield_method # _pdbx_entity_src_gen_chrom.post_treatment save_pdbx_entity_src_gen_chrom _category.description ; This category contains details for the chromatographic steps used in the purification of the protein. ; _category.id pdbx_entity_src_gen_chrom _category.mandatory_code no loop_ _category_group.id 'inclusive_group' 'protein_production_group' 'entity_group' 'pdbx_group' loop_ _category_key.name '_pdbx_entity_src_gen_chrom.entry_id' '_pdbx_entity_src_gen_chrom.entity_id' '_pdbx_entity_src_gen_chrom.step_id' save_ save__pdbx_entity_src_gen_chrom.entry_id _item_description.description ; The value of _pdbx_entity_src_gen_chrom.entry_id uniquely identifies a sample consisting of one or more proteins whose structure is to be determined. This is a pointer to _entry.id. This item may be a site dependent bar code. ; _item.name '_pdbx_entity_src_gen_chrom.entry_id' _item.category_id pdbx_entity_src_gen_chrom _item.mandatory_code yes _item_linked.parent_name '_entry.id' _item_linked.child_name '_pdbx_entity_src_gen_chrom.entry_id' save_ save__pdbx_entity_src_gen_chrom.entity_id _item_description.description ; The value of _pdbx_entity_src_gen_chrom.entity_id uniquely identifies each protein contained in the project target complex proteins whose structure is to be determined. This data item is a pointer to _entity.id in the ENTITY category. This item may be a site dependent bar code. ; _item.name '_pdbx_entity_src_gen_chrom.entity_id' _item.category_id pdbx_entity_src_gen_chrom _item.mandatory_code yes _item_linked.parent_name '_entity.id' _item_linked.child_name '_pdbx_entity_src_gen_chrom.entity_id' save_ save__pdbx_entity_src_gen_chrom.step_id _item_description.description ; This item is the unique identifier for this chromatography step. ; _item.name '_pdbx_entity_src_gen_chrom.step_id' _item.category_id pdbx_entity_src_gen_chrom _item.mandatory_code yes _item_type.code int save_ save__pdbx_entity_src_gen_chrom.next_step_id _item_description.description ; This item unique identifier for the next production step. This allows a workflow to have multiple entry points leading to a single product. ; _item.name '_pdbx_entity_src_gen_chrom.next_step_id' _item.category_id pdbx_entity_src_gen_chrom _item.mandatory_code yes _item_type.code int save_ save__pdbx_entity_src_gen_chrom.end_construct_id _item_description.description ; This item is a pointer to pdbx_construct.id in the PDBX_CONSTRUCT category. The referenced sequence is expected to be the amino acid sequence of the expressed product after the chromatography step. ; _item.name '_pdbx_entity_src_gen_chrom.end_construct_id' _item.category_id pdbx_entity_src_gen_chrom _item.mandatory_code no _item_linked.parent_name '_pdbx_construct.id' _item_linked.child_name '_pdbx_entity_src_gen_chrom.end_construct_id' save_ save__pdbx_entity_src_gen_chrom.robot_id _item_description.description ; This data item is a pointer to pdbx_robot_system.id in the PDBX_ROBOT_SYSTEM category. ; _item.name '_pdbx_entity_src_gen_chrom.robot_id' _item.category_id pdbx_entity_src_gen_chrom _item.mandatory_code no _item_linked.parent_name '_pdbx_robot_system.id' _item_linked.child_name '_pdbx_entity_src_gen_chrom.robot_id' save_ save__pdbx_entity_src_gen_chrom.date _item_description.description ; The date of production step. ; _item.name '_pdbx_entity_src_gen_chrom.date' _item.category_id pdbx_entity_src_gen_chrom _item.mandatory_code no _item_type.code yyyy-mm-dd:hh:mm loop_ _item_examples.case '2003-12-25' '2003-12-25:09:00' save_ save__pdbx_entity_src_gen_chrom.column_type _item_description.description ; The type of column used in this step. ; _item.name '_pdbx_entity_src_gen_chrom.column_type' _item.category_id pdbx_entity_src_gen_chrom _item.mandatory_code yes _item_type.code text save_ save__pdbx_entity_src_gen_chrom.column_volume _item_description.description ; The volume of the column used in this step. ; _item.name '_pdbx_entity_src_gen_chrom.column_volume' _item.category_id pdbx_entity_src_gen_chrom _item.mandatory_code yes _item_type.code float _item_units.code milliliters save_ save__pdbx_entity_src_gen_chrom.column_temperature _item_description.description ; The temperature in degrees celsius at which this column was run. ; _item.name '_pdbx_entity_src_gen_chrom.column_temperature' _item.category_id pdbx_entity_src_gen_chrom _item.mandatory_code yes _item_type.code float _item_units.code celsius save_ save__pdbx_entity_src_gen_chrom.equilibration_buffer_id _item_description.description ; This item is a pointer to pdbx_buffer.id in the PDBX_BUFFER category. The referenced buffer is that in which the column was equilibrated. ; _item.name '_pdbx_entity_src_gen_chrom.equilibration_buffer_id' _item.category_id pdbx_entity_src_gen_chrom _item.mandatory_code yes _item_linked.parent_name '_pdbx_buffer.id' _item_linked.child_name '_pdbx_entity_src_gen_chrom.equilibration_buffer_id' save_ save__pdbx_entity_src_gen_chrom.flow_rate _item_description.description ; The rate at which the equilibration buffer flowed through the column. ; _item.name '_pdbx_entity_src_gen_chrom.flow_rate' _item.category_id pdbx_entity_src_gen_chrom _item.mandatory_code no _item_type.code float _item_units.code ml_per_min save_ save__pdbx_entity_src_gen_chrom.elution_buffer_id _item_description.description ; This item is a pointer to pdbx_buffer.id in the PDBX_BUFFER category. The referenced buffer is that with which the protein was eluted. ; _item.name '_pdbx_entity_src_gen_chrom.elution_buffer_id' _item.category_id pdbx_entity_src_gen_chrom _item.mandatory_code yes _item_linked.parent_name '_pdbx_buffer.id' _item_linked.child_name '_pdbx_entity_src_gen_chrom.elution_buffer_id' save_ save__pdbx_entity_src_gen_chrom.elution_protocol _item_description.description ; Details of the elution protocol. ; _item.name '_pdbx_entity_src_gen_chrom.elution_protocol' _item.category_id pdbx_entity_src_gen_chrom _item.mandatory_code no _item_type.code text save_ save__pdbx_entity_src_gen_chrom.sample_prep_details _item_description.description ; Details of the sample preparation prior to running the column. ; _item.name '_pdbx_entity_src_gen_chrom.sample_prep_details' _item.category_id pdbx_entity_src_gen_chrom _item.mandatory_code no _item_type.code text save_ save__pdbx_entity_src_gen_chrom.sample_volume _item_description.description ; The volume of protein solution run on the column. ; _item.name '_pdbx_entity_src_gen_chrom.sample_volume' _item.category_id pdbx_entity_src_gen_chrom _item.mandatory_code yes _item_type.code float _item_units.code milliliters save_ save__pdbx_entity_src_gen_chrom.sample_concentration _item_description.description ; The concentration of the protein solution put onto the column. ; _item.name '_pdbx_entity_src_gen_chrom.sample_concentration' _item.category_id pdbx_entity_src_gen_chrom _item.mandatory_code no _item_type.code float _item_units.code mg_per_ml save_ save__pdbx_entity_src_gen_chrom.sample_conc_method _item_description.description ; The method used to determine the concentration of the protein solution put onto the column. ; _item.name '_pdbx_entity_src_gen_chrom.sample_conc_method' _item.category_id pdbx_entity_src_gen_chrom _item.mandatory_code no _item_type.code text save_ save__pdbx_entity_src_gen_chrom.volume_pooled_fractions _item_description.description ; The total volume of all the fractions pooled to give the purified protein solution. ; _item.name '_pdbx_entity_src_gen_chrom.volume_pooled_fractions' _item.category_id pdbx_entity_src_gen_chrom _item.mandatory_code yes _item_type.code float _item_units.code milliliters save_ save__pdbx_entity_src_gen_chrom.yield_pooled_fractions _item_description.description ; The yield in milligrams of protein recovered in the pooled fractions. ; _item.name '_pdbx_entity_src_gen_chrom.yield_pooled_fractions' _item.category_id pdbx_entity_src_gen_chrom _item.mandatory_code yes _item_type.code float _item_units.code milligrams save_ save__pdbx_entity_src_gen_chrom.yield_method _item_description.description ; The method used to determine the yield ; _item.name '_pdbx_entity_src_gen_chrom.yield_method' _item.category_id pdbx_entity_src_gen_chrom _item.mandatory_code yes _item_type.code text save_ save__pdbx_entity_src_gen_chrom.post_treatment _item_description.description ; Details of any post-chromatographic treatment of the protein sample. ; _item.name '_pdbx_entity_src_gen_chrom.post_treatment' _item.category_id pdbx_entity_src_gen_chrom _item.mandatory_code no _item_type.code text save_ ############################# # PDBX_ENTITY_SRC_GEN_FRACT # ############################# # # _pdbx_entity_src_gen_fract.entry_id # _pdbx_entity_src_gen_fract.entity_id # _pdbx_entity_src_gen_fract.step_id # _pdbx_entity_src_gen_fract.next_step_id # _pdbx_entity_src_gen_fract.end_construct_id # _pdbx_entity_src_gen_fract.robot_id # _pdbx_entity_src_gen_fract.date # _pdbx_entity_src_gen_fract.method # _pdbx_entity_src_gen_fract.temperature # _pdbx_entity_src_gen_fract.details # _pdbx_entity_src_gen_fract.protein_location # _pdbx_entity_src_gen_fract.protein_yield # _pdbx_entity_src_gen_fract.protein_yield_method # save_pdbx_entity_src_gen_fract _category.description ; This category contains details for the fraction steps used in the overall protein production process. Examples of fractionation steps are centrifugation and magnetic bead pull-down purification. ; _category.id pdbx_entity_src_gen_fract _category.mandatory_code no loop_ _category_group.id 'inclusive_group' 'protein_production_group' 'entity_group' 'pdbx_group' loop_ _category_key.name '_pdbx_entity_src_gen_fract.entry_id' '_pdbx_entity_src_gen_fract.entity_id' '_pdbx_entity_src_gen_fract.step_id' save_ save__pdbx_entity_src_gen_fract.entry_id _item_description.description ; The value of _pdbx_entity_src_gen_fract.entry_id uniquely identifies a sample consisting of one or more proteins whose structure is to be determined. This is a pointer to _entry.id. This item may be a site dependent bar code. ; _item.name '_pdbx_entity_src_gen_fract.entry_id' _item.category_id pdbx_entity_src_gen_fract _item.mandatory_code yes _item_linked.parent_name '_entry.id' _item_linked.child_name '_pdbx_entity_src_gen_fract.entry_id' save_ save__pdbx_entity_src_gen_fract.entity_id _item_description.description ; The value of _pdbx_entity_src_gen_fract.entity_id uniquely identifies each protein contained in the project target protein complex whose structure is to be determined. This data item is a pointer to _entity.id in the ENTITY category. This item may be a site dependent bar code. ; _item.name '_pdbx_entity_src_gen_fract.entity_id' _item.category_id pdbx_entity_src_gen_fract _item.mandatory_code yes _item_linked.parent_name '_entity.id' _item_linked.child_name '_pdbx_entity_src_gen_fract.entity_id' save_ save__pdbx_entity_src_gen_fract.step_id _item_description.description ; This item is the unique identifier for this fractionation step. ; _item.name '_pdbx_entity_src_gen_fract.step_id' _item.category_id pdbx_entity_src_gen_fract _item.mandatory_code yes _item_type.code int save_ save__pdbx_entity_src_gen_fract.next_step_id _item_description.description ; This item unique identifier for the next production step. This allows a workflow to have multiple entry points leading to a single product. ; _item.name '_pdbx_entity_src_gen_fract.next_step_id' _item.category_id pdbx_entity_src_gen_fract _item.mandatory_code yes _item_type.code int save_ save__pdbx_entity_src_gen_fract.end_construct_id _item_description.description ; This item is a pointer to pdbx_construct.id in the PDBX_CONSTRUCT category. The referenced sequence is expected to be the amino acid sequence of the expressed product after the fractionation step. ; _item.name '_pdbx_entity_src_gen_fract.end_construct_id' _item.category_id pdbx_entity_src_gen_fract _item.mandatory_code no _item_linked.parent_name '_pdbx_construct.id' _item_linked.child_name '_pdbx_entity_src_gen_fract.end_construct_id' save_ save__pdbx_entity_src_gen_fract.robot_id _item_description.description ; This data item is a pointer to pdbx_robot_system.id in the PDBX_ROBOT_SYSTEM category. ; _item.name '_pdbx_entity_src_gen_fract.robot_id' _item.category_id pdbx_entity_src_gen_fract _item.mandatory_code no _item_linked.parent_name '_pdbx_robot_system.id' _item_linked.child_name '_pdbx_entity_src_gen_fract.robot_id' save_ save__pdbx_entity_src_gen_fract.date _item_description.description ; The date of this production step. ; _item.name '_pdbx_entity_src_gen_fract.date' _item.category_id pdbx_entity_src_gen_fract _item.mandatory_code no _item_type.code yyyy-mm-dd:hh:mm loop_ _item_examples.case '2003-12-25' '2003-12-25:09:00' save_ save__pdbx_entity_src_gen_fract.method _item_description.description ; This item describes the method of fractionation. ; _item.name '_pdbx_entity_src_gen_fract.method' _item.category_id pdbx_entity_src_gen_fract _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail C 'Centrifugation' M 'Magnetic beads' P 'Phase separation' save_ save__pdbx_entity_src_gen_fract.temperature _item_description.description ; The temperature in degrees celsius at which the fractionation was performed. ; _item.name '_pdbx_entity_src_gen_fract.temperature' _item.category_id pdbx_entity_src_gen_fract _item.mandatory_code yes _item_type.code float _item_units.code celsius save_ save__pdbx_entity_src_gen_fract.details _item_description.description ; String value containing details of the fractionation. ; _item.name '_pdbx_entity_src_gen_fract.details' _item.category_id pdbx_entity_src_gen_fract _item.mandatory_code no _item_type.code text save_ save__pdbx_entity_src_gen_fract.protein_location _item_description.description ; The fraction containing the protein of interest. ; _item.name '_pdbx_entity_src_gen_fract.protein_location' _item.category_id pdbx_entity_src_gen_fract _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail S 'Supernatant' P 'Pellet' B 'Band in gradient' M 'Magnetic beads' A 'Aqueous phase' L 'Lipid phase' save_ save__pdbx_entity_src_gen_fract.protein_volume _item_description.description ; The volume of the fraction containing the protein. ; _item.name '_pdbx_entity_src_gen_fract.protein_volume' _item.category_id pdbx_entity_src_gen_fract _item.mandatory_code no _item_type.code float _item_units.code milliliters save_ save__pdbx_entity_src_gen_fract.protein_yield _item_description.description ; The yield in milligrams of protein from the fractionation. ; _item.name '_pdbx_entity_src_gen_fract.protein_yield' _item.category_id pdbx_entity_src_gen_fract _item.mandatory_code yes _item_type.code float _item_units.code milligrams save_ save__pdbx_entity_src_gen_fract.protein_yield_method _item_description.description ; The method used to determine the yield ; _item.name '_pdbx_entity_src_gen_fract.protein_yield_method' _item.category_id pdbx_entity_src_gen_fract _item.mandatory_code yes _item_type.code text save_ ############################ # PDBX_ENTITY_SRC_GEN_PURE # ############################ # # _pdbx_entity_src_gen_pure.entry_id # _pdbx_entity_src_gen_pure.entity_id # _pdbx_entity_src_gen_pure.next_step_id # _pdbx_entity_src_gen_pure.date # _pdbx_entity_src_gen_pure.conc_device_id # _pdbx_entity_src_gen_pure.conc_details # _pdbx_entity_src_gen_pure.conc_assay_method # _pdbx_entity_src_gen_pure.protein_concentration # _pdbx_entity_src_gen_pure.protein_yield # _pdbx_entity_src_gen_pure.protein_purity # _pdbx_entity_src_gen_pure.protein_oligomeric_state # _pdbx_entity_src_gen_pure.storage_buffer_id # _pdbx_entity_src_gen_pure.storage_temperature # # _pdbx_entity_src_gen_pure.summary # save_pdbx_entity_src_gen_pure _category.description ; This category contains details for the final purified protein product. Note that this category does not contain the amino acid sequence of the protein. The sequence will be found in the ENTITY_POLY_SEQ entry with matching entity_id. Only one PDBX_ENTITY_SRC_GEN_PURE category is allowed per entity, hence there is no step_id for this category. ; _category.id pdbx_entity_src_gen_pure _category.mandatory_code no loop_ _category_group.id 'inclusive_group' 'protein_production_group' 'entity_group' 'pdbx_group' loop_ _category_key.name '_pdbx_entity_src_gen_pure.entry_id' '_pdbx_entity_src_gen_pure.entity_id' '_pdbx_entity_src_gen_pure.step_id' save_ save__pdbx_entity_src_gen_pure.entry_id _item_description.description ; The value of _pdbx_entity_src_gen_pure.entry_id uniquely identifies a sample consisting of one or more proteins whose structure is to be determined. This is a pointer to _entry.id. This item may be a site dependent bar code. ; _item.name '_pdbx_entity_src_gen_pure.entry_id' _item.category_id pdbx_entity_src_gen_pure _item.mandatory_code yes _item_linked.parent_name '_entry.id' _item_linked.child_name '_pdbx_entity_src_gen_pure.entry_id' save_ save__pdbx_entity_src_gen_pure.entity_id _item_description.description ; The value of _pdbx_entity_src_gen_pure.entity_id uniquely identifies each protein contained in the project target complex proteins whose structure is to be determined. This data item is a pointer to _entity.id in the ENTITY category. This item may be a site dependent bar code. ; _item.name '_pdbx_entity_src_gen_pure.entity_id' _item.category_id pdbx_entity_src_gen_pure _item.mandatory_code yes _item_linked.parent_name '_entity.id' _item_linked.child_name '_pdbx_entity_src_gen_pure.entity_id' save_ save__pdbx_entity_src_gen_pure.step_id _item_description.description ; This item unique identifier the production step. ; _item.name '_pdbx_entity_src_gen_pure.step_id' _item.category_id pdbx_entity_src_gen_pure _item.mandatory_code yes _item_type.code int save_ save__pdbx_entity_src_gen_pure.product_id _item_description.description ; When present, this item should be a globally unique identifier that identifies the final product. It is envisaged that this should be the same as and product code associated with the sample and would provide the key by which information about the production process may be extracted from the protein production facility. For files describing the protein production process (i.e. where _entity.type is 'P' or 'E') this should have the same value as _entry.id ; _item.name '_pdbx_entity_src_gen_pure.product_id' _item.category_id pdbx_entity_src_gen_pure _item.mandatory_code no _item_type.code code save_ save__pdbx_entity_src_gen_pure.date _item_description.description ; The date of production step. ; _item.name '_pdbx_entity_src_gen_pure.date' _item.category_id pdbx_entity_src_gen_pure _item.mandatory_code no _item_type.code yyyy-mm-dd:hh:mm loop_ _item_examples.case '2003-12-25' '2003-12-25:09:00' save_ save__pdbx_entity_src_gen_pure.conc_device_id _item_description.description ; This data item is a pointer to pdbx_robot_system.id in the PDBX_ROBOT_SYSTEM category. ; _item.name '_pdbx_entity_src_gen_pure.conc_device_id' _item.category_id pdbx_entity_src_gen_pure _item.mandatory_code no _item_linked.parent_name '_pdbx_robot_system.id' _item_linked.child_name '_pdbx_entity_src_gen_pure.conc_device_id' save_ save__pdbx_entity_src_gen_pure.conc_details _item_description.description ; Details of the protein concentration procedure ; _item.name '_pdbx_entity_src_gen_pure.conc_details' _item.category_id pdbx_entity_src_gen_pure _item.mandatory_code no _item_type.code text save_ save__pdbx_entity_src_gen_pure.conc_assay_method _item_description.description ; The method used to measure the protein concentration ; _item.name '_pdbx_entity_src_gen_pure.conc_assay_method' _item.category_id pdbx_entity_src_gen_pure _item.mandatory_code yes _item_type.code text save_ save__pdbx_entity_src_gen_pure.protein_concentration _item_description.description ; The final concentration of the protein. ; _item.name '_pdbx_entity_src_gen_pure.protein_concentration' _item.category_id pdbx_entity_src_gen_pure _item.mandatory_code yes _item_type.code float _item_units.code mg_per_ml save_ save__pdbx_entity_src_gen_pure.protein_yield _item_description.description ; The yield of protein in milligrams. ; _item.name '_pdbx_entity_src_gen_pure.protein_yield' _item.category_id pdbx_entity_src_gen_pure _item.mandatory_code no _item_type.code float _item_units.code milligrams save_ save__pdbx_entity_src_gen_pure.protein_purity _item_description.description ; The purity of the protein (percent). ; _item.name '_pdbx_entity_src_gen_pure.protein_purity' _item.category_id pdbx_entity_src_gen_pure _item.mandatory_code no _item_type.code float # _item_units.code percent save_ save__pdbx_entity_src_gen_pure.protein_oligomeric_state _item_description.description ; The oligomeric state of the protein. Monomeric is 1, dimeric 2, etc. ; _item.name '_pdbx_entity_src_gen_pure.protein_oligomeric_state' _item.category_id pdbx_entity_src_gen_pure _item.mandatory_code no _item_type.code int save_ save__pdbx_entity_src_gen_pure.storage_buffer_id _item_description.description ; This item is a pointer to pdbx_buffer.id in the PDBX_BUFFER category. The referenced buffer is that in which the protein was stored. ; _item.name '_pdbx_entity_src_gen_pure.storage_buffer_id' _item.category_id pdbx_entity_src_gen_pure _item.mandatory_code yes _item_linked.parent_name '_pdbx_buffer.id' _item_linked.child_name '_pdbx_entity_src_gen_pure.storage_buffer_id' save_ save__pdbx_entity_src_gen_pure.storage_temperature _item_description.description ; The temperature in degrees celsius at which the protein was stored. ; _item.name '_pdbx_entity_src_gen_pure.storage_temperature' _item.category_id pdbx_entity_src_gen_pure _item.mandatory_code no _item_type.code float _item_units.code celsius save_ save__pdbx_entity_src_gen_pure.summary _item_description.description ; Summary of the details of protein purification method used to obtain the final protein product. This description should include any lysis, fractionation, proteolysis, refolding, chromatography used as well as the method used the characterize the final product. ; _item.name '_pdbx_entity_src_gen_pure.summary' _item.category_id pdbx_entity_src_gen_pure _item.mandatory_code no _item_type.code text save_ ################################# # PDBX_ENTITY_SRC_GEN_CHARACTER # ################################# # # _pdbx_entity_src_gen_character.entry_id # _pdbx_entity_src_gen_character.entity_id # _pdbx_entity_src_gen_character.step_id # _pdbx_entity_src_gen_character.robot_id # _pdbx_entity_src_gen_character.date # _pdbx_entity_src_gen_character.method # _pdbx_entity_src_gen_character.value # _pdbx_entity_src_gen_character.details # save_pdbx_entity_src_gen_character _category.description ; This category contains details of protein characterisation. It refers to the characteristion of the product of a specific step. ; _category.id pdbx_entity_src_gen_character _category.mandatory_code no loop_ _category_group.id 'inclusive_group' 'protein_production_group' 'entity_group' 'pdbx_group' loop_ _category_key.name '_pdbx_entity_src_gen_character.entry_id' '_pdbx_entity_src_gen_character.entity_id' '_pdbx_entity_src_gen_character.step_id' save_ save__pdbx_entity_src_gen_character.entry_id _item_description.description ; The value of _pdbx_entity_src_gen_character.entry_id uniquely identifies a sample consisting of one or more proteins whose structure is to be determined. This is a pointer to _entry.id. This item may be a site dependent bar code. ; _item.name '_pdbx_entity_src_gen_character.entry_id' _item.category_id pdbx_entity_src_gen_character _item.mandatory_code yes _item_linked.parent_name '_entry.id' _item_linked.child_name '_pdbx_entity_src_gen_character.entry_id' save_ save__pdbx_entity_src_gen_character.entity_id _item_description.description ; The value of _pdbx_entity_src_gen_character.entity_id uniquely identifies each protein contained in the project target complex proteins whose structure is to be determined. This data item is a pointer to _entity.id in the ENTITY category. This item may be a site dependent bar code. ; _item.name '_pdbx_entity_src_gen_character.entity_id' _item.category_id pdbx_entity_src_gen_character _item.mandatory_code yes _item_linked.parent_name '_entity.id' _item_linked.child_name '_pdbx_entity_src_gen_character.entity_id' save_ save__pdbx_entity_src_gen_character.step_id _item_description.description ; This item is the unique identifier for the step whose product has been characterised. ; _item.name '_pdbx_entity_src_gen_character.step_id' _item.category_id pdbx_entity_src_gen_character _item.mandatory_code yes _item_type.code int save_ save__pdbx_entity_src_gen_character.robot_id _item_description.description ; This data item is a pointer to pdbx_robot_system.id in the PDBX_ROBOT_SYSTEM category. ; _item.name '_pdbx_entity_src_gen_character.robot_id' _item.category_id pdbx_entity_src_gen_character _item.mandatory_code no _item_linked.parent_name '_pdbx_robot_system.id' _item_linked.child_name '_pdbx_entity_src_gen_character.robot_id' save_ save__pdbx_entity_src_gen_character.date _item_description.description ; The date of characterisation step. ; _item.name '_pdbx_entity_src_gen_character.date' _item.category_id pdbx_entity_src_gen_character _item.mandatory_code no _item_type.code yyyy-mm-dd:hh:mm loop_ _item_examples.case '2003-12-25' '2003-12-25:09:00' save_ save__pdbx_entity_src_gen_character.method _item_description.description ; The method used for protein characterisation. ; _item.name '_pdbx_entity_src_gen_character.method' _item.category_id pdbx_entity_src_gen_character _item.mandatory_code yes _item_type.code text loop_ _item_examples.case 'Dynamic light scattering' 'Mass spectrometry' save_ save__pdbx_entity_src_gen_character.result _item_description.description ; The result from this method of protein characterisation. ; _item.name '_pdbx_entity_src_gen_character.result' _item.category_id pdbx_entity_src_gen_character _item.mandatory_code yes _item_type.code text save_ save__pdbx_entity_src_gen_character.details _item_description.description ; Any details associated with this method of protein characterisation. ; _item.name '_pdbx_entity_src_gen_character.details' _item.category_id pdbx_entity_src_gen_character _item.mandatory_code no _item_type.code text save_ ################## # PDBX_CONSTRUCT # ################## # # _pdbx_construct.entry_id # _pdbx_construct.id # _pdbx_construct.name # _pdbx_construct.class # _pdbx_construct.type # _pdbx_construct.seq # _pdbx_construct.date # _pdbx_construct.details # _pdbx_construct.robot_id # _pdbx_construct.ref_db_code # _pdbx_construct.ref_db_name # _pdbx_construct.ref_db_align_beg # _pdbx_construct.ref_db_align_end # _pdbx_construct.flag_align # _pdbx_construct.flag_diff # save_pdbx_construct _category.description ; Data items in the PDBX_CONSTRUCT category specify a sequence of nucleic acids or amino acids. It is a catch-all that may be used to provide details of sequences known to be relevant to the project as well as primers, plasmids, proteins and such like that are either used or produced during the protein production process. Molecules described here are not necessarily complete, so for instance it would be possible to include either a complete plasmid or just its insert. This category may be considered as an abbreviated form of _entity where the molecules described are not required to appear in the final co-ordinates. Note that the details provided here all pertain to a single entry as defined at deposition. It is anticipated that _pdbx_construct.id would also be composed of a sequence that is unique within a given site prefixed by a code that identifies that site and would, therefore, be GLOBALLY unique. Thus this category could also be used locally to store details about the different constructs used during protein production without reference to the entry_id (which only becomes a meaningful concept during deposition). ; _category.id pdbx_construct _category.mandatory_code no loop_ _category_key.name '_pdbx_construct.id' loop_ _category_group.id 'inclusive_group' 'entity_group' 'protein_production_group' 'pdbx_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - hypothetical example ; ; _pdbx_construct.entry_id 111000111 _pdbx_construct.id 1 _pdbx_construct.type DNA _pdbx_construct.entity_id 1 _pdbx_construct.seq ; gatgctgtag gcataggctt ggttatgccg gtactgccgg gcctcttgcg ggatatcgtc gctcaaggcg cactcccgtt ctggataatg ttttttgcgc cgacatcata acggttctgg caaatattct gaaatgagct gttgacaatt aatcatcgat aagcttcttg # - - - - data truncated for brevity - - - - ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_construct.entry_id _item_description.description ; The value of _pdbx_construct.entry_id uniquely identifies a sample consisting of one or more proteins whose structure is to be determined. This is a pointer to _entry.id. This item may be a site dependent bar code. ; _item.name '_pdbx_construct.entry_id' _item.category_id pdbx_construct _item.mandatory_code yes _item_linked.parent_name '_entry.id' _item_linked.child_name '_pdbx_construct.entry_id' save_ save__pdbx_construct.id _item_description.description ; The value of _pdbx_construct.id must uniquely identify a record in the PDBX_CONSTRUCT list and should be arranged so that it is composed of a site-speicific prefix combined with a value that is unique within a given site.Note that this item need not be a number; it can be any unique identifier. ; loop_ _item.name '_pdbx_construct.id' _item.category_id pdbx_construct _item.mandatory_code yes _item_type.code code save_ save__pdbx_construct.name _item_description.description ; _pdbx_construct.name provides a placeholder for the local name of the construct, for example the plasmid name if this category is used to list plasmids. ; loop_ _item.name '_pdbx_construct.name' _item.category_id pdbx_construct _item.mandatory_code yes _item_type.code line save_ save__pdbx_construct.organisation _item_description.description ; _pdbx_construct.organisation describes the organisation in which the _pdbx_construct.id is unique. This will normally be the lab in which the constrcut originated. It is envisaged that this item will permit a globally unique identifier to be constructed in cases where this is not possible from the _pdbx_construct.id alone. ; loop_ _item.name '_pdbx_construct.organisation' _item.category_id pdbx_construct _item.mandatory_code yes _item_type.code line save_ save__pdbx_construct.entity_id _item_description.description ; In cases where the construct IS found in the co-ordinates then this item provides a pointer to _entity.id in the ENTITY category for the corresponding molecule. ; _item.name '_pdbx_construct.entity_id' _item.category_id pdbx_construct _item.mandatory_code no _item_linked.parent_name '_entity.id' _item_linked.child_name '_pdbx_construct.entity_id' save_ save__pdbx_construct.robot_id _item_description.description ; In cases where the sequence has been determined by a robot this data item provides a pointer to pdbx_robot_system.id in the PDBX_ROBOT_SYSTEM category for the robot responsible ; _item.name '_pdbx_construct.robot_id' _item.category_id pdbx_construct _item.mandatory_code no _item_linked.parent_name '_pdbx_robot_system.id' _item_linked.child_name '_pdbx_construct.robot_id' save_ save__pdbx_construct.date _item_description.description ; The date that the sequence was determined. ; _item.name '_pdbx_construct.date' _item.category_id pdbx_construct _item.mandatory_code no _item_type.code yyyy-mm-dd:hh:mm loop_ _item_examples.case '2003-12-25' '2003-12-25:09:00' save_ save__pdbx_construct.details _item_description.description ; Additional details about the construct that cannot be represented in the category _pdbx_construct_feature. ; _item.name '_pdbx_construct.details' _item.category_id pdbx_construct _item.mandatory_code no _item_type.code text save_ save__pdbx_construct.class _item_description.description ; The primary function of the construct. This should be considered as a guideline only. ; _item.name '_pdbx_construct.class' _item.category_id pdbx_construct _item.mandatory_code no _item_type.code code loop_ _item_enumeration.value plasmid protein insert primer transcript save_ save__pdbx_construct.type _item_description.description ; The type of nucleic acid sequence in the construct. Note that to find all the DNA molecules it is necessary to search for DNA + cDNA and for RNA, RNA + mRNA + tRNA. ; _item.name '_pdbx_construct.type' _item.category_id pdbx_construct _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value DNA RNA cDNA mRNA tRNA protein save_ save__pdbx_construct.seq _item_description.description ; sequence expressed as string of one-letter base codes or one letter amino acid codes. Unusual residues may be represented either using the appropriate one letter code wild cards or by the three letter code in parentheses. ; _item.name '_pdbx_construct.seq' _item.category_id pdbx_construct _item.mandatory_code yes _item_type.code text _item_examples.case ; gatgctgtag gcataggctt ggttatgccg gtactgccgg gcctcttgcg ggatatcgtc gctcaaggcg cactcccgtt ctggataatg ttttttgcgc cgacatcata acggttctgg caaatattct gaaatgagct gttgacaatt aatcatcgat aagcttcttg ; save_ ########################### # PDBX_CONSTRUCT_FEATURE # ########################### # # _pdbx_construct_feature.id # _pdbx_construct_feature.entry_id # _pdbx_construct_feature.entity_id # _pdbx_construct_feature.construct_id # _pdbx_construct_feature.start_seq # _pdbx_construct_feature.end_seq # _pdbx_construct_feature.type # _pdbx_construct_feature.details # save_pdbx_construct_feature _category.description ; Data items in the PDBX_CONSTRUCT_FEATURE category may be used to specify various properties of a nucleic acid sequence used during protein production. ; _category.id pdbx_construct_feature _category.mandatory_code no loop_ _category_key.name '_pdbx_construct_feature.construct_id' '_pdbx_construct_feature.id' loop_ _category_group.id 'inclusive_group' 'entity_group' 'protein_production_group' 'pdbx_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - vector pUC28 ; ; loop_ _pdbx_construct_feature.id _pdbx_construct_feature.entry_id _pdbx_construct_feature.construct_id _pdbx_construct_feature.start_seq _pdbx_construct_feature.end_seq _pdbx_construct_feature.type _pdbx_construct_feature.details 1 111000111 1 . . . "pKK84-1 ClaI 5260bp 5247..5247 ptac11 TaqI-TaqI 192bp, -35 trp promoter -> pEA300 5452bp" 2 111000111 1 . . . "pKK84-1 1..5246 5246bp ClaI = AT^CGAT TaqI = T^CGA cgact..." 3 111000111 1 5247 5436 . "ptac11 190bp ...cat TaqI = T^CGA ClaI = AT^CGAT" 4 111000111 1 5437 5450 . "pKK84-1 5247..5260 14bp" 5 111000111 1 . . misc_binding "SIT unique EcoRI-ClaI-HindIII-BamHI-PvuII" 6 111000111 1 . . rep_origin "ORI E. coli pMB1 (ColE1 and pBR322)" 7 111000111 1 . . promoter "PRO E. coli trp" 8 111000111 1 . . CDS "ANT E. coli beta-lactamase gene (bla) ampicillin resistance gene (apr/amp)" ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_construct_feature.id _item_description.description ; The value of _pdbx_construct_feature.id must uniquely identify a record in the PDBX_CONSTRUCT_FEATURE list. Note that this item need not be a number; it can be any unique identifier. ; loop_ _item.name '_pdbx_construct_feature.id' _item.category_id pdbx_construct_feature _item.mandatory_code yes _item_type.code code save_ save__pdbx_construct_feature.construct_id _item_description.description ; The value of _pdbx_construct_feature.construct_id uniquely identifies the construct with which the feature is associated. This is a pointer to _pdbx_construct.id This item may be a site dependent bar code. ; _item.name '_pdbx_construct_feature.construct_id' _item.category_id pdbx_construct_feature _item.mandatory_code yes _item_linked.parent_name '_pdbx_construct.id' _item_linked.child_name '_pdbx_construct_feature.construct_id' save_ save__pdbx_construct_feature.entry_id _item_description.description ; The value of _pdbx_construct_feature.entry_id uniquely identifies a sample consisting of one or more proteins whose structure is to be determined. This is a pointer to _entry.id. This item may be a site dependent bar code. ; _item.name '_pdbx_construct_feature.entry_id' _item.category_id pdbx_construct _item.mandatory_code yes _item_linked.parent_name '_entry.id' _item_linked.child_name '_pdbx_construct_feature.entry_id' save_ save__pdbx_construct_feature.start_seq _item_description.description ; The sequence position at which the feature begins ; _item.name '_pdbx_construct_feature.start_seq' _item.category_id pdbx_construct_feature _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__pdbx_construct_feature.end_seq _item_description.description ; The sequence position at which the feature ends ; _item.name '_pdbx_construct_feature.end_seq' _item.category_id pdbx_construct_feature _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__pdbx_construct_feature.type _item_description.description ; The type of the feature ; _item.name '_pdbx_construct_feature.type' _item.category_id pdbx_construct_feature _item.mandatory_code no _item_type.code line save_ save__pdbx_construct_feature.details _item_description.description ; Details that describe the feature ; _item.name '_pdbx_construct_feature.details' _item.category_id pdbx_construct_feature _item.mandatory_code no _item_type.code text save_ ##################### # PDBX_ROBOT_SYSTEM # ##################### # # _pdbx_robot_system.id # _pdbx_robot_system.model # _pdbx_robot_system.type # _pdbx_robot_system.manufacturer # save_pdbx_robot_system _category.description ; The details about each robotic system used to collect data for this project. ; _category.id pdbx_robot_system _category.mandatory_code no _category_key.name '_pdbx_robot_system.id' loop_ _category_group.id 'inclusive_group' 'protein_production_group' 'pdbx_group' save_ save__pdbx_robot_system.id _item_description.description ; Assign a numerical ID to each instrument. ; _item.name '_pdbx_robot_system.id' _item.category_id pdbx_robot_system _item.mandatory_code no _item_type.code code save_ save__pdbx_robot_system.model _item_description.description ; The model of the robotic system. ; _item.name '_pdbx_robot_system.model' _item.category_id pdbx_robot_system _item.mandatory_code no _item_type.code line save_ save__pdbx_robot_system.type _item_description.description ; The type of robotic system used for in the production pathway. ; _item.name '_pdbx_robot_system.type' _item.category_id pdbx_robot_system _item.mandatory_code no _item_type.code line save_ save__pdbx_robot_system.manufacturer _item_description.description ; The name of the manufacturer of the robotic system. ; _item.name '_pdbx_robot_system.manufacturer' _item.category_id pdbx_robot_system _item.mandatory_code no _item_type.code line save_ ################# ## PDB_BUFFER ## ################# # # _pdbx_buffer.id # _pdbx_buffer.name # _pdbx_buffer.details # _pdbx_buffer_components.id # _pdbx_buffer_components.buffer_id # _pdbx_buffer_components.name # _pdbx_buffer_components.volume # _pdbx_buffer_components.conc # _pdbx_buffer_components.details # _pdbx_buffer_components.conc_units # _pdbx_buffer_components.isotopic_labeling # save_pdbx_buffer _category.description ; Data items in the PDBX_BUFFER category record details of the sample buffer. ; _category.id pdbx_buffer _category.mandatory_code no _category_key.name '_pdbx_buffer.id' loop_ _category_group.id 'inclusive_group' 'protein_production_group' 'pdbx_group' save_ save__pdbx_buffer.id _item_description.description ; The value of _pdbx_buffer.id must uniquely identify the sample buffer. ; _item.name '_pdbx_buffer.id' _item.category_id pdbx_buffer _item.mandatory_code yes _item_type.code code save_ save__pdbx_buffer.name _item_description.description ; The name of each buffer. ; _item.name '_pdbx_buffer.name' _item.category_id pdbx_buffer _item.mandatory_code no _item_type.code line _item_examples.case 'Acetic acid' save_ save__pdbx_buffer.details _item_description.description ; Any additional details to do with buffer. ; _item.name '_pdbx_buffer.details' _item.category_id pdbx_buffer _item.mandatory_code no _item_type.code text _item_examples.case 'aerated' save_ ############################### ## PDBX_BUFFER_COMPONENTS ## ############################### # # _pdbx_buffer_components.id # _pdbx_buffer_components.buffer_id # _pdbx_buffer_components.name # _pdbx_buffer_components.volume # _pdbx_buffer_components.conc # _pdbx_buffer_components.details # _pdbx_buffer_components.conc_units # _pdbx_buffer_components.isotopic_labeling # save_pdbx_buffer_components _category.description ; Constituents of buffer in sample ; _category.id pdbx_buffer_components _category.mandatory_code no loop_ _category_key.name '_pdbx_buffer_components.buffer_id' '_pdbx_buffer_components.id' loop_ _category_group.id 'inclusive_group' 'protein_production_group' 'pdbx_group' loop_ _category_examples.detail _category_examples.case ; Example 1 - based on PDB entry 1DYL and laboratory records for the structure corresponding to PDB entry 1DYL ; ;loop_ _pdbx_buffer_components.buffer_id _pdbx_buffer_components.id _pdbx_buffer_components.name _pdbx_buffer_components.volume _pdbx_buffer_components.conc _pdbx_buffer_components.details 1 1 'NaCl' '0.200 ' '4 ' . 1 2 'Acetic Acid' '0.047 ' '100' . 1 3 'water' '0.700 ' 'neat' . ; save_ save__pdbx_buffer_components.id _item_description.description ; The value of _pdbx_buffer_components.id must uniquely identify a component of the buffer. ; _item.name '_pdbx_buffer_components.id' _item.category_id pdbx_buffer_components _item.mandatory_code yes _item_type.code code save_ save__pdbx_buffer_components.buffer_id _item_description.description ; This data item is a pointer to _pdbx_buffer.id in the BUFFER category. ; _item.name '_pdbx_buffer_components.buffer_id' _item.category_id pdbx_buffer_components _item.mandatory_code yes _item_linked.parent_name '_pdbx_buffer.id' _item_linked.child_name '_pdbx_buffer_components.buffer_id' save_ save__pdbx_buffer_components.name _item_description.description ; The name of each buffer component. ; _item.name '_pdbx_buffer_components.name' _item.category_id pdbx_buffer_components _item.mandatory_code no _item_type.code line _item_examples.case 'Acetic acid' save_ save__pdbx_buffer_components.volume _item_description.description ; The volume of buffer component. ; _item.name '_pdbx_buffer_components.volume' _item.category_id pdbx_buffer_components _item.mandatory_code no _item_type.code code _item_examples.case 0.200 save_ save__pdbx_buffer_components.conc _item_description.description ; The millimolar concentration of buffer component. ; _item.name '_pdbx_buffer_components.conc' _item.category_id pdbx_buffer_components _item.mandatory_code no _item_type.code code _item_examples.case 200 save_ save__pdbx_buffer_components.details _item_description.description ; Any additional details to do with buffer composition. ; _item.name '_pdbx_buffer_components.details' _item.category_id pdbx_buffer_components _item.mandatory_code no _item_type.code text _item_examples.case 'pH adjusted with NaOH' save_ # save__pdbx_buffer_components.conc_units _item_description.description ; The concentration units of the component. ; _item.name '_pdbx_buffer_components.conc_units' _item.category_id pdbx_buffer_components _item.mandatory_code no _item_type.code code loop_ _item_examples.case 'mg/mL for mg per milliliter' 'mM for millimolar' '% for percent by volume' loop_ _item_enumeration.value _item_enumeration.detail '%' 'percent by volume' 'mM' 'millimolar' 'mg/mL' 'mg per milliliter' 'M' 'molar' 'g/L' 'grams per liter' save_ save__pdbx_buffer_components.isotopic_labeling _item_description.description ; The isotopic composition of each component, including the % labeling level, if known. For example: 1. Uniform (random) labeling with 15N: U-15N 2. Uniform (random) labeling with 13C, 15N at known labeling levels: U-95% 13C;U-98% 15N 3. Residue selective labeling: U-95% 15N-Thymine 4. Site specific labeling: 95% 13C-Ala18, 5. Natural abundance labeling in an otherwise uniformly labled biomolecule is designated by NA: U-13C; NA-K,H ; _item.name '_pdbx_buffer_components.isotopic_labeling' _item.category_id pdbx_buffer_components _item.mandatory_code no _item_type.code line loop_ _item_enumeration.value 'U-15N' 'U-13C' 'U-15N,13C' 'U-2H' 'other' save_ ### EOF mmcif_pdbx-def-6.dic ########################################################################### # # File: mmcif_iims-def-2.dic # # PDB Extension Dictionary for 3-Dimensional # Electron Microscopy # # Definition Section 2 # # ########################################################################### ## ### # Please note the data items listed below are not for the PDB # but are intended solely for the EM database # _em_entity_assembly.ebi_organism_scientific # _em_entity_assembly.ebi_organism_common # _em_entity_assembly.ebi_strain # _em_entity_assembly.ebi_tissue # _em_entity_assembly.ebi_cell # _em_entity_assembly.ebi_organelle # _em_entity_assembly.ebi_cellular_location # _em_entity_assembly.ebi_engineered # _em_entity_assembly.ebi_expression_system # _em_entity_assembly.ebi_expression_system_plasmid ### # # categories # # EM_ASSEMBLY # _em_assembly.id # _em_assembly.entry_id # _em_assembly.name # _em_assembly.aggregation_state # _em_assembly.composition # _em_assembly.num_components # _em_assembly.mol_wt_exp # _em_assembly.mol_wt_theo # _em_assembly.mol_wt_method # _em_assembly.details # EM_ENTITY_ASSEMBLY # _em_entity_assembly.id # _em_entity_assembly.assembly_id # _em_entity_assembly.type # _em_entity_assembly.name # _em_entity_assembly.details # _em_entity_assembly.go_id # _em_entity_assembly.ipr_id # _em_entity_assembly.synonym # EM_ENTITY_ASSEMBLY_LIST # _em_entity_assembly_list.id # _em_entity_assembly_list.entity_id # _em_entity_assembly_list.entity_assembly_id # _em_entity_assembly_list.oligomeric_details # _em_entity_assembly_list.number_of_copies # EM_VIRUS_ENTITY # _em_virus_entity.id # _em_virus_entity.virus_host_category # _em_virus_entity.virus_host_species # _em_virus_entity.virus_host_growth_cell # _em_virus_entity.virus_type # _em_virus_entity.virus_isolate # _em_virus_entity.ictvdb_id # _em_virus_entity.entity_assembly_id # _em_virus_entity.enveloped # _em_virus_entity.empty # EM_ICOS_VIRUS_SHELLS # _em_icos_virus_shells.virus_entity_id # _em_icos_virus_shells.id # _em_icos_virus_shells.shell_diameter # _em_icos_virus_shells.triangulation_num # EM_SAMPLE_PREPARATION # _em_sample_preparation.entry_id # _em_sample_preparation.id # _em_sample_preparation.ph # _em_sample_preparation.buffer_id # _em_sample_preparation.sample_concentration # _em_sample_preparation.2d_crystal_grow_id # _em_sample_preparation.support_id # EM_SAMPLE_SUPPORT # _em_sample_support.id # _em_sample_support.film_material # _em_sample_support.method # _em_sample_support.grid_material # _em_sample_support.grid_mesh_size # _em_sample_support.grid_type # _em_sample_support.pretreatment # _em_sample_support.details # _em_sample_support.citation_id # EM_2D_CRYSTAL_GROW # _em_2d_crystal_grow.id # _em_2d_crystal_grow.method # _em_2d_crystal_grow.apparatus # _em_2d_crystal_grow.atmosphere # _em_2d_crystal_grow.pH # _em_2d_crystal_grow.temp # _em_2d_crystal_grow.time # _em_2d_crystal_grow.buffer_id # _em_2d_crystal_grow.details # _em_2d_crystal_grow.number_2d_crystals # _em_2d_crystal_grow.mean_2d_crystal_size # _em_2d_crystal_grow.citation_id # EM_BUFFER # _em_buffer.id # _em_buffer.name # _em_buffer.details # EM_BUFFER_COMPONENTS # _em_buffer_components.id # _em_buffer_components.buffer_id # _em_buffer_components.name # _em_buffer_components.volume # _em_buffer_components.conc # _em_buffer_components.details # EM_VITRIFICATION # _em_vitrification.entry_id # _em_vitrification.id # _em_vitrification.sample_preparation_id # _em_vitrification.cryogen_name # _em_vitrification.humidity # _em_vitrification.temp # _em_vitrification.instrument # _em_vitrification.method # _em_vitrification.time_resolved_state # _em_vitrification.citation_id # _em_vitrification.details # EM_IMAGING # _em_imaging.entry_id # _em_imaging.id # _em_imaging.sample_support_id # _em_imaging.detector_id # _em_imaging.scans_id # _em_imaging.microscope_model # _em_imaging.specimen_holder_type # _em_imaging.specimen_holder_model # _em_imaging.details # _em_imaging.date # _em_imaging.accelerating_voltage # _em_imaging.illumination_mode # _em_imaging.mode # _em_imaging.nominal_cs # _em_imaging.nominal_defocus_min # _em_imaging.nominal_defocus_max # _em_imaging.tilt_angle_min # _em_imaging.tilt_angle_max # _em_imaging.nominal_magnification # _em_imaging.calibrated_magnification # _em_imaging.electron_source # _em_imaging.electron_dose # _em_imaging.energy_filter # _em_imaging.energy_window # _em_imaging.citation_id # _em_imaging.temperature # _em_imaging.detector_distance # _em_imaging.recording_temperature_minimum # _em_imaging.recording_temperature_maximum # EM_DETECTOR # _em_detector.entry_id # _em_detector.id # _em_detector.details # _em_detector.type # _em_detector.detective_quantum_efficiency # EM_IMAGE_SCANS # _em_image_scans.entry_id # _em_image_scans.id # _em_image_scans.number_digital_images # _em_image_scans.details # _em_image_scans.scanner_model # _em_image_scans.sampling_size # _em_image_scans.od_range # _em_image_scans.quant_bit_size # _em_image_scans.citation_id # EM_2D_PROJECTION_SELECTION # _em_2d_projection_selection.entry_id # _em_2d_projection_selection.num_particles # _em_2d_projection_selection.software_name # _em_2d_projection_selection.method # _em_2d_projection_selection.details # _em_2d_projection_selection.citation_id # EM_EULER_ANGLE_DISTRIBUTION # _em_euler_angle_distribution.id # _em_euler_angle_distribution.entry_id # _em_euler_angle_distribution.details # _em_euler_angle_distribution.alpha # _em_euler_angle_distribution.beta # _em_euler_angle_distribution.gamma # EM_3D_RECONSTRUCTION # _em_3d_reconstruction.entry_id # _em_3d_reconstruction.id # _em_3d_reconstruction.method # _em_3d_reconstruction.citation_id # _em_3d_reconstruction.details # _em_3d_reconstruction.resolution # _em_3d_reconstruction.resolution_method # _em_3d_reconstruction.magnification_calibration # _em_3d_reconstruction.ctf_correction_method # _em_3d_reconstruction.nominal_pixel_size # _em_3d_reconstruction.actual_pixel_size # EM_3D_FITTING # _em_3d_fitting.id # _em_3d_fitting.entry_id # _em_3d_fitting.method # _em_3d_fitting.target_criteria # _em_3d_fitting.software_name # _em_3d_fitting.details # _em_3d_fitting.overall_b_value # _em_3d_fitting.ref_space # _em_3d_fitting.ref_protocol # EM_3D_FITTING_LIST # _em_3d_fitting_list.id # _em_3d_fitting_list.3d_fitting_id # _em_3d_fitting_list.pdb_entry_id # _em_3d_fitting_list.pdb_chain_id ################# ## EM_ASSEMBLY ## ################# save_em_assembly _category.description ; Data items in the EM_ASSEMBLY category record details about the type of complex assembly that describes the nature of the sample studied. ; _category.id em_assembly _category.mandatory_code no loop_ _category_key.name '_em_assembly.id' '_em_assembly.entry_id' loop_ _category_group.id 'inclusive_group' 'em_group' loop_ _category_examples.detail _category_examples.case ; Example 1 - based on PDB entry 1DYL and laboratory records for the structure corresponding to PDB entry 1DYL ; ; _em_assembly.id 1 _em_assembly.entry_id 1DYL _em_assembly.name virus _em_assembly.aggregation_state icosahedral _em_assembly.composition virus _em_assembly.num_components 1 _em_assembly.mol_wt_exp . _em_assembly.mol_wt_theo . _em_assembly.mol_wt_method . _em_assembly.details . ; save_ save__em_assembly.id _item_description.description ; The value of _em_assembly.id must uniquely identify a collection of observed complexes. ; _item.name '_em_assembly.id' _item.category_id em_assembly _item.mandatory_code yes _item_type.code code _item_linked.child_name '_em_entity_assembly.assembly_id' _item_linked.parent_name '_em_assembly.id' save_ save__em_assembly.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_em_assembly.entry_id' _item.category_id em_assembly _item.mandatory_code yes _item_type.code code _item_linked.child_name '_em_assembly.entry_id' _item_linked.parent_name '_entry.id' save_ save__em_assembly.name _item_description.description ; The name of the assembly of observed complexes. ; _item.name '_em_assembly.name' _item.category_id em_assembly _item.mandatory_code no _item_type.code line save_ save__em_assembly.aggregation_state _item_description.description ; A description of the aggregation state of the assembly. ; _item.name '_em_assembly.aggregation_state' _item.category_id em_assembly _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'SINGLE PARTICLE' 'INDIVIDUAL STRUCTURE' '2D-CRYSTAL' ICOSAHEDRAL HELICAL FILAMENT 'HELICAL FILAMENTS' TISSUE save_ save__em_assembly.composition _item_description.description ; The known composition of the assembly. ; _item.name '_em_assembly.composition' _item.category_id em_assembly _item.mandatory_code no _item_type.code line save_ save__em_assembly.num_components _item_description.description ; The number of components of the biological assembly. ; _item.name '_em_assembly.num_components' _item.category_id em_assembly _item.mandatory_code no _item_type.code int save_ save__em_assembly.mol_wt_exp _item_description.description ; The value (in megadaltons) of the experimentally determined molecular weight of the assembly. ; _item.name '_em_assembly.mol_wt_exp' _item.category_id em_assembly _item.mandatory_code no _item_type.code float _item_units.code megadaltons save_ save__em_assembly.mol_wt_theo _item_description.description ; The value (in megadaltons) of the theoretically determined molecular weight of the assembly. ; _item.name '_em_assembly.mol_wt_theo' _item.category_id em_assembly _item.mandatory_code no _item_type.code float _item_units.code megadaltons save_ save__em_assembly.mol_wt_method _item_description.description ; The method used in determining the molecular weight. ; _item.name '_em_assembly.mol_wt_method' _item.category_id em_assembly _item.mandatory_code no _item_type.code text save_ save__em_assembly.details _item_description.description ; A description of any additional details describing the observed sample. ; _item.name '_em_assembly.details' _item.category_id em_assembly _item.mandatory_code no _item_type.code text loop_ _item_examples.case ; This structure was preferentially oriented (end-on)on the grid. ; ; The structure was monodisperse. ; save_ ######################## ## EM_ENTITY_ASSEMBLY ## ######################## save_em_entity_assembly _category.description ; Data items in the EM_ENTITY_ASSEMBLY category record details about each component of the complex. ; _category.id em_entity_assembly _category.mandatory_code no loop_ _category_key.name '_em_entity_assembly.id' '_em_entity_assembly.assembly_id' loop_ _category_group.id 'inclusive_group' 'em_group' loop_ _category_examples.detail _category_examples.case ; Example 1 - based on PDB entry 1DYL and laboratory records for the structure corresponding to PDB entry 1DYL ; ; _em_entity_assembly.id 1 _em_entity_assembly.assembly_id 1 _em_entity_assembly.type VIRUS ; save_ save__em_entity_assembly.id _item_description.description ; The value of _em_entity_assembly.id must uniquely identify each of the components of the complex. ; _item.name '_em_entity_assembly.id' _item.category_id em_entity_assembly _item.mandatory_code yes _item_type.code code _item_linked.child_name '_em_virus_entity.entity_assembly_id' _item_linked.parent_name '_em_entity_assembly.id' save_ save__em_entity_assembly.assembly_id _item_description.description ; This data item is a pointer to _em_assembly.id in the ASSEMBLY category. ; _item.name '_em_entity_assembly.assembly_id' _item.category_id em_entity_assembly _item.mandatory_code yes _item_type.code code save_ save__em_entity_assembly.type _item_description.description ; A description of types of components of the assembly of the biological structure. ; _item.name '_em_entity_assembly.type' _item.category_id em_entity_assembly _item.mandatory_code no _item_type.code line loop_ _item_enumeration.value VIRUS PROTEIN 'NUCLEIC ACID' LIGAND LABEL 'CELLULAR COMPONENT' save_ save__em_entity_assembly.name _item_description.description ; The name of the component of the observed assembly. ; _item.name '_em_entity_assembly.name' _item.category_id em_entity_assembly _item.mandatory_code no _item_type.code text save_ save__em_entity_assembly.details _item_description.description ; Additional details about the component. ; _item.name '_em_entity_assembly.details' _item.category_id em_entity_assembly _item.mandatory_code no _item_type.code text save_ save__em_entity_assembly.ebi_organism_scientific _item_description.description ; The species of the natural organism from which the component was obtained. ; _item.name '_em_entity_assembly.ebi_organism_scientific' _item.category_id em_entity_assembly _item.mandatory_code no _item_type.code text save_ save__em_entity_assembly.ebi_organism_common _item_description.description ; The common name of the species of the natural organism from which the component was obtained. ; _item.name '_em_entity_assembly.ebi_organism_common' _item.category_id em_entity_assembly _item.mandatory_code no _item_type.code text save_ save__em_entity_assembly.ebi_strain _item_description.description ; The strain of the natural organism from which the component was obtained, if relevant. ; _item.name '_em_entity_assembly.ebi_strain' _item.category_id em_entity_assembly _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'DH5a' 'BMH 71-18' save_ save__em_entity_assembly.ebi_tissue _item_description.description ; The tissue of the natural organism from which the component was obtained. ; _item.name '_em_entity_assembly.ebi_tissue' _item.category_id em_entity_assembly _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'heart' 'liver' 'eye lens' save_ save__em_entity_assembly.ebi_cell _item_description.description ; The cell from which the component was obtained. ; _item.name '_em_entity_assembly.ebi_cell' _item.category_id em_entity_assembly _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'CHO' 'HELA' '3T3' save_ save__em_entity_assembly.ebi_organelle _item_description.description ; The organelle from which the component was obtained. ; _item.name '_em_entity_assembly.ebi_organelle' _item.category_id em_entity_assembly _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'golgi' 'mitochondrion' 'cytoskeleton' save_ save__em_entity_assembly.ebi_cellular_location _item_description.description ; The cellular location of the component. ; _item.name '_em_entity_assembly.ebi_cellular_location' _item.category_id em_entity_assembly _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'cytoplasm' 'endoplasmic reticulum' 'plasma membrane' save_ save__em_entity_assembly.ebi_engineered _item_description.description ; A flag to indicate whether the component is engineered. ; _item.name '_em_entity_assembly.ebi_engineered' _item.category_id em_entity_assembly _item.mandatory_code no _item_type.code line loop_ _item_enumeration.value YES NO save_ save__em_entity_assembly.ebi_expression_system _item_description.description ; The expression system used to produce the component. ; _item.name '_em_entity_assembly.ebi_expression_system' _item.category_id em_entity_assembly _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'eschericia coli' 'saccharomyces cerevisiae' save_ save__em_entity_assembly.ebi_expression_system_plasmid _item_description.description ; The plasmid used in the expression system used to produce the component. ; _item.name '_em_entity_assembly.ebi_expression_system_plasmid' _item.category_id em_entity_assembly _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'pBR322' 'pMB9' save_ save__em_entity_assembly.go_id _item_description.description ; The Gene Ontology (GO) identifier for the component. The GO id is the appropriate identifier used by the Gene Ontology Consortium. Reference: Nature Genetics vol 25:25-29 (2000). ; _item.name '_em_entity_assembly.go_id' _item.category_id em_entity_assembly _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'GO:0005876' 'GO:0015630' save_ save__em_entity_assembly.ipr_id _item_description.description ; The InterPro (IPR) identifier for the component. The IPR id is the appropriate identifier used by the Interpro Resource. Reference: Nucleic Acid Research vol 29(1):37-40(2001). ; _item.name '_em_entity_assembly.ipr_id' _item.category_id em_entity_assembly _item.mandatory_code no _item_type.code line loop_ _item_examples.case '001304' '002353' save_ save__em_entity_assembly.synonym _item_description.description ; Alternative name of the component. ; _item.name '_em_entity_assembly.synonym' _item.category_id em_entity_assembly _item.mandatory_code no _item_type.code line _item_examples.case 'FADV-1' save_ ############################# ## EM_ENTITY_ASSEMBLY_LIST ## ############################# save_em_entity_assembly_list _category.description ; Data items in the EM_ENTITY_ASSEMBLY_LIST category record details of the structural elements in each component. ; _category.id em_entity_assembly_list _category.mandatory_code no loop_ _category_key.name '_em_entity_assembly_list.entity_assembly_id' '_em_entity_assembly_list.id' '_em_entity_assembly_list.entity_id' loop_ _category_group.id 'inclusive_group' 'em_group' loop_ _category_examples.detail _category_examples.case ; Example 1 - microtubule ; ; loop_ _em_entity_assembly_list.entity_assembly_id _em_entity_assembly_list.id _em_entity_assembly_list.entity_id _em_entity_assembly_list.oligomeric_details _em_entity_assembly_list.number_of_copies 1 1 1 'DIMER' 2 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__em_entity_assembly_list.id _item_description.description ; The value of _em_entity_assembly_list.id must uniquely identify the component. ; _item.name '_em_entity_assembly_list.id' _item.category_id em_entity_assembly_list _item.mandatory_code yes _item_type.code code save_ save__em_entity_assembly_list.entity_id _item_description.description ; A pointer to entity id. ; _item.name '_em_entity_assembly_list.entity_id' _item.category_id em_entity_assembly_list _item.mandatory_code yes _item_type.code code _item_linked.child_name '_em_entity_assembly_list.entity_id' _item_linked.parent_name '_entity.id' save_ save__em_entity_assembly_list.entity_assembly_id _item_description.description ; This data item is a pointer to _em_entity_assembly.id in the ENTITY_ASSEMBLY category. ; _item.name '_em_entity_assembly_list.entity_assembly_id' _item.category_id em_entity_assembly_list _item.mandatory_code yes _item_type.code code save_ save__em_entity_assembly_list.oligomeric_details _item_description.description ; The oligomeric state of the entity. ; _item.name '_em_entity_assembly_list.oligomeric_details' _item.category_id em_entity_assembly_list _item.mandatory_code no _item_type.code line save_ save__em_entity_assembly_list.number_of_copies _item_description.description ; The number of copies of the entity. ; _item.name '_em_entity_assembly_list.number_of_copies' _item.category_id em_entity_assembly_list _item.mandatory_code no _item_type.code int save_ ##################### ## EM_VIRUS_ENTITY ## ##################### save_em_virus_entity _category.description ; Data items in the EM_VIRUS_ENTITY category record details of the icosahedral virus. ; _category.id em_virus_entity _category.mandatory_code no loop_ _category_key.name '_em_virus_entity.id' '_em_virus_entity.entity_assembly_id' loop_ _category_group.id 'inclusive_group' 'em_group' loop_ _category_examples.detail _category_examples.case ; Example 1 - based on PDB entry 1DYL and laboratory records for the structure corresponding to PDB entry 1DYL ; ; loop_ _em_virus_entity.id _em_virus_entity.virus_host_category _em_virus_entity.virus_host_species _em_virus_entity.virus_type _em_virus_entity.virus_isolate _em_virus_entity.ictvdb_id _em_virus_entity.entity_assembly_id _em_virus_entity.enveloped _em_virus_entity.empty 1 'VERTERBRATES' 'HOMO SAPIENS' 'VIRUS' 'STRAIN' '00.073.0.01.023' 1 'YES' 'NO' ; save_ save__em_virus_entity.id _item_description.description ; Is the unique identifier for VIRUS_ENTITY category. ; _item.name '_em_virus_entity.id' _item.category_id em_virus_entity _item.mandatory_code yes _item_type.code code save_ save__em_virus_entity.virus_host_category _item_description.description ; The host category description for the virus. ; _item.name '_em_virus_entity.virus_host_category' _item.category_id em_virus_entity _item.mandatory_code no _item_type.code line loop_ _item_examples.case ALGAE ARCHAEA 'BACTERIA(EUBACTERIA)' FUNGI INVERTEBRATES 'PLANTAE (HIGHER PLANTS)' PROTOZOA VERTEBRATES save_ save__em_virus_entity.virus_host_species _item_description.description ; The host species from which the virus was isolated. ; _item.name '_em_virus_entity.virus_host_species' _item.category_id em_virus_entity _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'homo sapiens' 'gallus gallus' save_ save__em_virus_entity.virus_host_growth_cell _item_description.description ; The host cell from which the virus was isolated. ; _item.name '_em_virus_entity.virus_host_growth_cell' _item.category_id em_virus_entity _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'HELA' 'CHO' save_ save__em_virus_entity.virus_type _item_description.description ; The type of virus. ; _item.name '_em_virus_entity.virus_type' _item.category_id em_virus_entity _item.mandatory_code no _item_type.code line loop_ _item_examples.case VIRION SATELLITE PRION VIROID 'VIRUS-LIKE PARTICLE' save_ save__em_virus_entity.virus_isolate _item_description.description ; The isolate from which the virus was obtained. ; _item.name '_em_virus_entity.virus_isolate' _item.category_id em_virus_entity _item.mandatory_code no _item_type.code line loop_ _item_enumeration.value STRAIN SEROTYPE SEROCOMPLEX SUBSPECIES SPECIES save_ save__em_virus_entity.ictvdb_id _item_description.description ; The International Committee on Taxonomy of Viruses (ICTV) Taxon Identifier is the Virus Code used throughout the ICTV database (ICTVdb). The ICTVdb id is the appropriate identifier used by the International Committee on Taxonomy of Viruses Resource. Reference: Virus Taxonomy, Academic Press (1999). ISBN:0123702003. ; _item.name '_em_virus_entity.ictvdb_id' _item.category_id em_virus_entity _item.mandatory_code no _item_type.code line loop_ _item_examples.case '01.0.2.0.001' '01.0.2.0.002' save_ save__em_virus_entity.entity_assembly_id _item_description.description ; This data item is a pointer to _em_virus_entity.id in the ENTITY_ASSEMBLY category. ; _item.name '_em_virus_entity.entity_assembly_id' _item.category_id em_virus_entity _item.mandatory_code yes _item_type.code code save_ save__em_virus_entity.enveloped _item_description.description ; Flag to indicate if the virus is enveloped or not. ; _item.name '_em_virus_entity.enveloped' _item.category_id em_virus_entity _item.mandatory_code no _item_type.code line loop_ _item_enumeration.value YES NO save_ save__em_virus_entity.empty _item_description.description ; Flag to indicate if the virus is empty or not. ; _item.name '_em_virus_entity.empty' _item.category_id em_virus_entity _item.mandatory_code no _item_type.code line loop_ _item_enumeration.value YES NO save_ save__em_virus_entity.details _item_description.description ; Additional details about this virus entity ; _item.name '_em_virus_entity.details' _item.category_id em_virus_entity _item.mandatory_code no _item_type.code text save_ ########################## ## EM_ICOS_VIRUS_SHELLS ## ########################## save_em_icos_virus_shells _category.description ; Data items in the EM_ICOS_VIRUS_SHELLS category record details of the viral shell number, diameter of each shell and triangulation number. ; _category.id em_icos_virus_shells _category.mandatory_code no loop_ _category_key.name '_em_icos_virus_shells.virus_entity_id' '_em_icos_virus_shells.id' loop_ _category_group.id 'inclusive_group' 'em_group' loop_ _category_examples.detail _category_examples.case ; Example 1 - based on PDB entry 1DYL and laboratory records for the structure corresponding to PDB entry 1DYL ; ; loop_ _em_icos_virus_shells.virus_entity_id _em_icos_virus_shells.id _em_icos_virus_shells.shell_diameter _em_icos_virus_shells.triangulation_num 1 1 400 4 ; save_ save__em_icos_virus_shells.virus_entity_id _item_description.description ; The value of _em_icos_virus_shells.virus_entity_id is a pointer to _em_virus_entity.id in the VIRUS_ENTITY category. ; _item.name '_em_icos_virus_shells.virus_entity_id' _item.category_id em_icos_virus_shells _item.mandatory_code yes _item_type.code code _item_linked.child_name '_em_icos_virus_shells.virus_entity_id' _item_linked.parent_name '_em_virus_entity.id' save_ save__em_icos_virus_shells.id _item_description.description ; The value of _em_em_icos_virus_shells.id must uniquely identify the number and diameter of each virus protein shell and its triangulation number. ; _item.name '_em_icos_virus_shells.id' _item.category_id em_icos_virus_shells _item.mandatory_code yes _item_type.code code save_ save__em_icos_virus_shells.shell_diameter _item_description.description ; The value of the diameter (in angstroms) for each protein shell of the virus. ; _item.name '_em_icos_virus_shells.shell_diameter' _item.category_id em_icos_virus_shells _item.mandatory_code no _item_type.code float _item_units.code angstroms save_ save__em_icos_virus_shells.triangulation_num _item_description.description ; The triangulation number (T number) is a geometric and abstract concept that does not correspond to the structural components of an individul virus. It refers to the organisation of the geometric figure. The triangulation number, T is given by the following relationship: T= h*2 + hk +k*2, where h and k are positive integers which define the position of the five-fold vertex on the original hexagonal net. ; _item.name '_em_icos_virus_shells.triangulation_num' _item.category_id em_icos_virus_shells _item.mandatory_code no _item_type.code int _item_examples.case 4 save_ ########################### ## EM_SAMPLE_PREPARATION ## ########################### save_em_sample_preparation _category.description ; Data items in the EM_SAMPLE_PREPARATION category record details of sample conditions prior to loading onto grid support. ; _category.id em_sample_preparation _category.mandatory_code no loop_ _category_key.name '_em_sample_preparation.id' '_em_sample_preparation.entry_id' loop_ _category_group.id 'inclusive_group' 'em_group' loop_ _category_examples.detail _category_examples.case ; Example 1 - based on PDB entry 1DYL and laboratory records for the structure corresponding to PDB entry 1DYL ; ; _em_sample_preparation.entry_id 1DYL _em_sample_preparation.id 1 _em_sample_preparation.ph 7.6 _em_sample_preparation.buffer_id 1 _em_sample_preparation.sample_concentration 5 _em_sample_preparation.2d_crystal_grow_id . _em_sample_preparation.support.id 1 ; save_ save__em_sample_preparation.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_em_sample_preparation.entry_id' _item.category_id em_sample_preparation _item.mandatory_code yes _item_type.code code _item_linked.child_name '_em_sample_preparation.entry_id' _item_linked.parent_name '_entry.id' save_ save__em_sample_preparation.id _item_description.description ; The value of _em_sample_preparation.id must uniquely identify the sample preparation. ; _item.name '_em_sample_preparation.id' _item.category_id em_sample_preparation _item.mandatory_code yes _item_type.code code save_ save__em_sample_preparation.ph _item_description.description ; The pH value of the observed sample buffer. ; _item.name '_em_sample_preparation.ph' _item.category_id em_sample_preparation _item.mandatory_code no _item_type.code float save_ save__em_sample_preparation.buffer_id _item_description.description ; This data item is a pointer to _em_buffer.id in the BUFFER category. ; _item.name '_em_sample_preparation.buffer_id' _item.category_id em_sample_preparation _item.mandatory_code no _item_type.code code save_ save__em_sample_preparation.sample_concentration _item_description.description ; The value of the concentration (mg/mL for mg per milliliter) of the complex in the sample. ; _item.name '_em_sample_preparation.sample_concentration' _item.category_id em_sample_preparation _item.mandatory_code no _item_type.code float _item_units.code mg_per_ml save_ save__em_sample_preparation.2d_crystal_grow_id _item_description.description ; This data item is a pointer to _em_2d_crystal_grow.id in the 2D_CRYSTAL_GROW category. ; _item.name '_em_sample_preparation.2d_crystal_grow_id' _item.category_id em_sample_preparation _item.mandatory_code no _item_type.code code save_ save__em_sample_preparation.support_id _item_description.description ; This data item is a pointer to _em_sample_support.id in the EM_SAMPLE_SUPPORT category. ; _item.name '_em_sample_preparation.support_id' _item.category_id em_sample_preparation _item.mandatory_code no _item_type.code code save_ ####################### ## EM_SAMPLE_SUPPORT ## ####################### save_em_sample_support _category.description ; Data items in the EM_SAMPLE_SUPPORT category record details of the electron microscope grid type, grid support film and pretreatment of whole before sample is applied ; _category.id em_sample_support _category.mandatory_code no _category_key.name '_em_sample_support.id' loop_ _category_group.id 'inclusive_group' 'em_group' loop_ _category_examples.detail _category_examples.case ; Example 1 - based on PDB entry 1DYL and laboratory records for the structure corresponding to PDB entry 1DYL ; ; _em_sample_support.id 1 _em_sample_support.film_material 'HOLEY CARBON' _em_sample_support.method . _em_sample_support.grid_material COPPER _em_sample_support.grid_mesh_size 400 _em_sample_support.grid_type MESH _em_sample_support.pretreatment 'GLOW DISCHARGE' _em_sample_support.details . _em_sample_support.citation_id 2 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__em_sample_support.id _item_description.description ; The value of _em_sample_support.id must uniquely identify the sample support. ; _item.name '_em_sample_support.id' _item.category_id em_sample_support _item.mandatory_code yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_em_imaging.sample_support_id' '_em_sample_support.id' '_em_sample_preparation.support_id' '_em_sample_support.id' save_ save__em_sample_support.film_material _item_description.description ; The support material covering the em grid. ; _item.name '_em_sample_support.film_material' _item.category_id em_sample_support _item.mandatory_code no _item_type.code line loop_ _item_enumeration.value CARBON 'FORMVAR PLUS CARBON' 'CELLULOSE ACETATE PLUS CARBON' 'PARLODION PLUS CARBON' 'HOLEY CARBON' save_ save__em_sample_support.method _item_description.description ; A description of the method used to produce the support film. ; _item.name '_em_sample_support.method' _item.category_id em_sample_support _item.mandatory_code no _item_type.code text _item_examples.case '1%formvar in chloroform cast on distilled water' save_ save__em_sample_support.grid_material _item_description.description ; The name of the material from which the grid is made. ; _item.name '_em_sample_support.grid_material' _item.category_id em_sample_support _item.mandatory_code no _item_type.code line loop_ _item_enumeration.value COPPER COPPER/PALLADIUM COPPER/RHODIUM GOLD NICKEL PLATINUM TUNGSTEN TITANIUM MOLYBDENUM save_ save__em_sample_support.grid_mesh_size _item_description.description ; The value of the mesh size (per inch) of the em grid. ; _item.name '_em_sample_support.grid_mesh_size' _item.category_id em_sample_support _item.mandatory_code no _item_type.code int _item_examples.case 400 save_ save__em_sample_support.grid_type _item_description.description ; A description of the grid type. ; _item.name '_em_sample_support.grid_type' _item.category_id em_sample_support _item.mandatory_code no _item_type.code line loop_ _item_enumeration.value SLOT APERTURE DIAMOND HEXAGONAL save_ save__em_sample_support.pretreatment _item_description.description ; A description of the grid plus support film pretreatment. ; _item.name '_em_sample_support.pretreatment' _item.category_id em_sample_support _item.mandatory_code no _item_type.code text _item_examples.case 'glow-discharged for 30 sec in argon' save_ save__em_sample_support.details _item_description.description ; A description of any additional details concerning the sample support. ; _item.name '_em_sample_support.details' _item.category_id em_sample_support _item.mandatory_code no _item_type.code text _item_examples.case 'This grid plus sample was kept at -170 deg C for a month before use' save_ save__em_sample_support.citation_id _item_description.description ; This data item is a pointer to _citation.id in the CITATION category. ; _item.name '_em_sample_support.citation_id' _item.category_id em_sample_support _item.mandatory_code no _item_linked.child_name '_em_sample_support.citation_id' _item_linked.parent_name '_citation.id' _item_type.code code save_ ########################## ## EM_2D_CRYSTAL_GROW ## ########################## save_em_2d_crystal_grow _category.description ; Data items in the EM_2D_CRYSTAL_GROW category record details of growth conditions for 2d crystal samples. ; _category.id em_2d_crystal_grow _category.mandatory_code no _category_key.name '_em_2d_crystal_grow.id' loop_ _category_group.id 'inclusive_group' 'em_group' loop_ _category_examples.detail _category_examples.case ; Example 1 - based on PDB entry 1AT9 and laboratory records for the structure corresponding to PDB entry 1DYL ; ; _em_2d_crystal_grow.id 1 _em_2d_crystal_grow.method . _em_2d_crystal_grow.apparatus . _em_2d_crystal_grow.atmosphere 'room air' _em_2d_crystal_grow.pH 5.2 _em_2d_crystal_grow.temp 18 _em_2d_crystal_grow.time . _em_2d_crystal_grow.buffer_id 2 _em_2d_crystal_grow.details 'on grid' _em_2d_crystal_grow.number_2d_crystals 129 _em_2d_crystal_grow.mean_2d_crystal_size . _em_2d_crystal_grow.citation_id 2 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__em_2d_crystal_grow.id _item_description.description ; The value of _em_2d_crystal_grow.crystal_id must uniquely identify the sample 2d crystal. ; _item.name '_em_2d_crystal_grow.id' _item.category_id em_2d_crystal_grow _item.mandatory_code yes _item_type.code code save_ save__em_2d_crystal_grow.method _item_description.description ; The method used for growing the crystals. ; _item.name '_em_2d_crystal_grow.method' _item.category_id em_2d_crystal_grow _item.mandatory_code no _item_type.code line _item_examples.case 'lipid monolayer' save_ save__em_2d_crystal_grow.apparatus _item_description.description ; The type of the apparatus used for growing the crystals. ; _item.name '_em_2d_crystal_grow.apparatus' _item.category_id em_2d_crystal_grow _item.mandatory_code no _item_type.code line _item_examples.case 'Langmuir trough' save_ save__em_2d_crystal_grow.atmosphere _item_description.description ; The type of atmosphere in which crystals were grown. ; _item.name '_em_2d_crystal_grow.atmosphere' _item.category_id em_2d_crystal_grow _item.mandatory_code no _item_type.code line _item_examples.case 'room air' save_ save__em_2d_crystal_grow.pH _item_description.description ; the pH value used for growing the crystals. ; _item.name '_em_2d_crystal_grow.pH' _item.category_id em_2d_crystal_grow _item.mandatory_code no _item_type.code float _item_examples.case 4.7 save_ save__em_2d_crystal_grow.temp _item_description.description ; The value of the temperature in degrees Kelvin used for growing the crystals. ; _item.name '_em_2d_crystal_grow.temp' _item.category_id em_2d_crystal_grow _item.mandatory_code no _item_type.code float _item_units.code kelvins _item_examples.case 293 save_ save__em_2d_crystal_grow.time _item_description.description ; The length of time required to grow the crystals. ; _item.name '_em_2d_crystal_grow.time' _item.category_id em_2d_crystal_grow _item.mandatory_code no _item_type.code line _item_examples.case 'approximately 2 days' save_ save__em_2d_crystal_grow.buffer_id _item_description.description ; This data item is a pointer to _em_buffer.id in the BUFFER category. ; _item.name '_em_2d_crystal_grow.buffer_id' _item.category_id em_2d_crystal_grow _item.mandatory_code no _item_type.code code save_ save__em_2d_crystal_grow.details _item_description.description ; Any additional items concerning 2d crystal growth. ; _item.name '_em_2d_crystal_grow.details' _item.category_id em_2d_crystal_grow _item.mandatory_code no _item_type.code text save_ save__em_2d_crystal_grow.number_2d_crystals _item_description.description ; The number of 2d crystals imaged. ; _item.name '_em_2d_crystal_grow.number_2d_crystals' _item.category_id em_2d_crystal_grow _item.mandatory_code no _item_type.code int save_ save__em_2d_crystal_grow.mean_2d_crystal_size _item_description.description ; The approximate size (microns squared) of 2d crystals imaged. ; _item.name '_em_2d_crystal_grow.mean_2d_crystal_size' _item.category_id em_2d_crystal_grow _item.mandatory_code no _item_type.code float _item_units.code microns_squared save_ save__em_2d_crystal_grow.citation_id _item_description.description ; This data item is a pointer to _citation.id in the CITATION category. ; _item.name '_em_2d_crystal_grow.citation_id' _item.category_id em_2d_crystal_grow _item.mandatory_code no _item_linked.child_name '_em_2d_crystal_grow.citation_id' _item_linked.parent_name '_citation.id' _item_type.code code save_ ############### ## EM_BUFFER ## ############### save_em_buffer _category.description ; Data items in the BUFFER category record details of the sample buffer. ; _category.id em_buffer _category.mandatory_code no _category_key.name '_em_buffer.id' loop_ _category_group.id 'inclusive_group' 'em_group' save_ save__em_buffer.id _item_description.description ; The value of _em_buffer.id must uniquely identify the sample buffer. ; _item.name '_em_buffer.id' _item.category_id em_buffer _item.mandatory_code yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_em_2d_crystal_grow.buffer_id' '_em_buffer.id' '_em_sample_preparation.buffer_id' '_em_buffer.id' '_em_buffer_components.buffer_id' '_em_buffer.id' save_ save__em_buffer.name _item_description.description ; The name of the buffer. ; _item.name '_em_buffer.name' _item.category_id em_buffer _item.mandatory_code no _item_type.code line _item_examples.case 'Acetic acid' save_ save__em_buffer.details _item_description.description ; Any additional details to do with buffer. ; _item.name '_em_buffer.details' _item.category_id em_buffer _item.mandatory_code no _item_type.code text _item_examples.case 'aerated' save_ ########################## ## EM_BUFFER_COMPONENTS ## ########################## save_em_buffer_components _category.description ; Constituents of buffer in sample ; _category.id em_buffer_components _category.mandatory_code no loop_ _category_key.name '_em_buffer_components.buffer_id' '_em_buffer_components.id' loop_ _category_group.id 'inclusive_group' 'em_group' loop_ _category_examples.detail _category_examples.case ; Example 1 - based on PDB entry 1DYL and laboratory records for the structure corresponding to PDB entry 1DYL ; ;loop_ _em_buffer_components.buffer_id _em_buffer_components.id _em_buffer_components.name _em_buffer_components.volume _em_buffer_components.conc _em_buffer_components.details 1 1 'NaCl' '0.200 ' '4 ' . 1 2 'Acetic Acid' '0.047 ' '100' . 1 3 'water' '0.700 ' 'neat' . ; save_ save__em_buffer_components.id _item_description.description ; The value of _em_buffer_components.id must uniquely identify a component of the buffer. ; _item.name '_em_buffer_components.id' _item.category_id em_buffer_components _item.mandatory_code yes _item_type.code code save_ save__em_buffer_components.buffer_id _item_description.description ; This data item is a pointer to _em_buffer.id in the BUFFER category. ; _item.name '_em_buffer_components.buffer_id' _item.category_id em_buffer_components _item.mandatory_code yes _item_type.code code save_ save__em_buffer_components.name _item_description.description ; The name of each buffer component. ; _item.name '_em_buffer_components.name' _item.category_id em_buffer_components _item.mandatory_code no _item_type.code line _item_examples.case 'Acetic acid' save_ save__em_buffer_components.volume _item_description.description ; The volume of buffer component. ; _item.name '_em_buffer_components.volume' _item.category_id em_buffer_components _item.mandatory_code no _item_type.code code _item_examples.case 0.200 save_ save__em_buffer_components.conc _item_description.description ; The millimolar concentration of buffer component. ; _item.name '_em_buffer_components.conc' _item.category_id em_buffer_components _item.mandatory_code no _item_type.code code _item_examples.case 200 save_ save__em_buffer_components.details _item_description.description ; Any additional details to do with buffer composition. ; _item.name '_em_buffer_components.details' _item.category_id em_buffer_components _item.mandatory_code no _item_type.code text _item_examples.case 'pH adjusted with NaOH' save_ ###################### ## EM_VITRIFICATION ## ###################### save_em_vitrification _category.description ; Data items in the EM_VITRIFICATION category record details about the method and cryogen used in rapid freezing of the sample on the grid prior to its insertion in the electron microscope ; _category.id em_vitrification _category.mandatory_code no loop_ _category_key.name '_em_vitrification.id' '_em_vitrification.entry_id' loop_ _category_group.id 'inclusive_group' 'em_group' loop_ _category_examples.detail _category_examples.case ; Example 1 - based on PDB entry 1DYL and laboratory records for the structure corresponding to PDB entry 1DYL ; ; _em_vitrification.entry_id 1DYL _em_vitrification.id 1 _em_vitrification.sample_preparation_id 1 _em_vitrification.cryogen_name "ETHANE" _em_vitrification.humidity 90 _em_vitrification.temp 95 _em_vitrification.instrument . _em_vitrification.method "PLUNGE VITRIFICATION" _em_vitrification.time_resolved_state . _em_vitrification.citation_id 1 _em_vitrification.details ; SAMPLES WERE PREPARED AS THIN LAYERS OF VITREOUS ICE AND MAINTAINED AT NEAR LIQUID NITROGEN TEMPERATURE IN THE ELECTRON MICROSCOPE WITH A GATAN 626-0300 CRYOTRANSFER HOLDER. ; ; save_ save__em_vitrification.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_em_vitrification.entry_id' _item.category_id em_vitrification _item.mandatory_code yes _item_type.code code _item_linked.child_name '_em_vitrification.entry_id' _item_linked.parent_name '_entry.id' save_ save__em_vitrification.id _item_description.description ; The value of _em_vitrification.id must uniquely identify the vitrification procedure. ; _item.name '_em_vitrification.id' _item.category_id em_vitrification _item.mandatory_code yes _item_type.code code save_ save__em_vitrification.sample_preparation_id _item_description.description ; This data item is a pointer to _em_sample_preparation.id in the EM_SAMPLE_PREPARATION category. ; _item.name '_em_vitrification.sample_preparation_id' _item.category_id em_vitrification _item.mandatory_code no _item_type.code code _item_linked.child_name '_em_vitrification.sample_preparation_id' _item_linked.parent_name '_em_sample_preparation.id' save_ save__em_vitrification.cryogen_name _item_description.description ; This is the name of the cryogen. ; _item.name '_em_vitrification.cryogen_name' _item.category_id em_vitrification _item.mandatory_code no _item_type.code line loop_ _item_enumeration.value HELIUM NITROGEN PROPANE ETHANE METHANE 'FREON 22' 'FREON 12' save_ save__em_vitrification.humidity _item_description.description ; The humidity (%) in the vicinity of the vitrification process. ; _item.name '_em_vitrification.humidity' _item.category_id em_vitrification _item.mandatory_code no _item_type.code line _item_examples.case 90 save_ save__em_vitrification.temp _item_description.description ; The temperature (in degrees Kelvin) at which vitrification took place. ; _item.name '_em_vitrification.temp' _item.category_id em_vitrification _item.mandatory_code no _item_type.code float _item_units.code kelvins _item_examples.case 4.2 save_ save__em_vitrification.instrument _item_description.description ; The type of instrument used in the vitrification process. ; _item.name '_em_vitrification.instrument' _item.category_id em_vitrification _item.mandatory_code no _item_type.code line _item_examples.case 'Reichert plunger' save_ save__em_vitrification.method _item_description.description ; The procedure for vitrification. ; _item.name '_em_vitrification.method' _item.category_id em_vitrification _item.mandatory_code no _item_type.code text _item_examples.case 'blot for 2 seconds before plunging' save_ save__em_vitrification.time_resolved_state _item_description.description ; The length of time after an event effecting the sample that vitrification was induced and a description of the event. ; _item.name '_em_vitrification.time_resolved_state' _item.category_id em_vitrification _item.mandatory_code no _item_type.code text _item_examples.case '30 msec after spraying with effector'' save_ save__em_vitrification.citation_id _item_description.description ; This data item is a pointer to _citation.id in the CITATION category. ; _item.name '_em_vitrification.citation_id' _item.category_id em_vitrification _item.mandatory_code no _item_type.code code _item_linked.child_name '_em_vitrification.citation_id' _item_linked.parent_name '_citation.id' save_ save__em_vitrification.details _item_description.description ; Any additional details relating to vitrification. ; _item.name '_em_vitrification.details' _item.category_id em_vitrification _item.mandatory_code no _item_type.code text _item_examples.case 'argon atmosphere' save_ ################ ## EM_IMAGING ## ################ save_em_imaging _category.description ; Data items in the EM_IMAGING category record details about the parameters used in imaging the sample in the electron microscope. ; _category.id em_imaging _category.mandatory_code no loop_ _category_key.name '_em_imaging.entry_id' '_em_imaging.id' loop_ _category_group.id 'inclusive_group' 'em_group' loop_ _category_examples.detail _category_examples.case ; Example 1 - based on PDB entry 1DYL and laboratory records for the structure corresponding to PDB entry 1DYL ; ; _em_imaging.entry_id 1DYL _em_imaging.id 1 _em_imaging.sample_support_id 1 _em_imaging.microscope_model 'FEI/PHILIPS CM200 FEG' _em_imaging.specimen_holder_type 'cryotransfer' _em_imaging.specimen_holder_model 'gatan 626-0300' _em_imaging.details . _em_imaging.date 1998-15-06 _em_imaging.accelerating_voltage 200 _em_imaging.illumination_mode 'bright field' _em_imaging.mode 'low dose' _em_imaging.nominal_cs 2.0 _em_imaging.nominal_defocus_min 975 _em_imaging.nominal_defocus_max 7600 _em_imaging.tilt_angle_min 0 _em_imaging.tilt_angle_max 0 _em_imaging.nominal_magnification 50000 _em_imaging.calibrated_magnification . _em_imaging.electron_source 'FEG' _em_imaging.electron_dose . _em_imaging.energy_filter . _em_imaging.energy_window . _em_imaging.citation_id 1 _em_imaging.temperature 95 _em_imaging.detector_distance . _em_imaging.recording_temp_range . ; save_ save__em_imaging.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_em_imaging.entry_id' _item.category_id em_imaging _item.mandatory_code yes _item_type.code code _item_linked.child_name '_em_imaging.entry_id' _item_linked.parent_name '_entry.id' save_ save__em_imaging.id _item_description.description ; The value of _em_imaging.id must uniquely identify each imaging experiment. ; _item.name '_em_imaging.id' _item.category_id em_imaging _item.mandatory_code yes _item_type.code code save_ save__em_imaging.sample_support_id _item_description.description ; This data item is a pointer to _em_sample_support.id in the EM_SAMPLE_SUPPORT category. ; _item.name '_em_imaging.sample_support_id' _item.category_id em_imaging _item.mandatory_code yes _item_type.code code save_ save__em_imaging.detector_id _item_description.description ; The value of _em_imaging.detector_id must uniquely identify the type of detector used in the experiment. ; _item.name '_em_imaging.detector_id' _item.category_id em_imaging _item.mandatory_code yes _item_type.code code save_ save__em_imaging.scans_id _item_description.description ; The value of _em_imaging.scans_id must uniquely identify the image_scans used in the experiment. ; _item.name '_em_imaging.scans_id' _item.category_id em_imaging _item.mandatory_code yes _item_type.code code save_ save__em_imaging.microscope_model _item_description.description ; The name of the model of microscope. ; _item.name '_em_imaging.microscope_model' _item.category_id em_imaging _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'HITACHI H8100' 'HITACHI HF2000' 'HITACHI HF2000-UHR' 'HITACHI H9000-UHR' 'HITACHI H9000-NAR' 'HITACHI 300KEV FEG' 'HITACHI HU1250' 'HITACHI H-1500' 'JEOL 2000EX' 'JEOL 2010HT' 'JEOL 2010UHR' 'JEOL 2010F' 'JEOL 3010HT' 'JEOL 3010UHR' 'JEOL KYOTO-3000SFF' 'JEOL 4000EX' 'JEOL HAREM' 'JEOL ARM-1000' 'JEOL KYOTO-1000' 'JEOL ARM-1250' 'FEI/PHILIPS CM120T' 'FEI/PHILIPS CM200T' 'FEI/PHILIPS CM20/ST' 'FEI/PHILIPS CM20/SOPHIE' 'FEI/PHILIPS CM200FEG/ST' 'FEI/PHILIPS CM20/UT' 'FEI/PHILIPS CM200FEG/UT' 'FEI/PHILIPS CM30/T' 'FEI/PHILIPS CM300FEG/T' 'FEI/PHILIPS CM300FEG/HE' 'FEI/PHILIPS CM30/ST' 'FEI/PHILIPS CM300FEG/ST' 'FEI/PHILIPS CM300FEG/UT' 'FEI TECNAI 12' 'FEI TECNAI 20' 'FEI TECNAI F20' 'FEI TECNAI F30' 'FEI MORGAGNI' save_ save__em_imaging.specimen_holder_type _item_description.description ; The type of specimen holder used during imaging. ; _item.name '_em_imaging.specimen_holder_type' _item.category_id em_imaging _item.mandatory_code no _item_type.code line _item_examples.case 'cryo' save_ save__em_imaging.specimen_holder_model _item_description.description ; The name of the model of specimen holder used during imaging. ; _item.name '_em_imaging.specimen_holder_model' _item.category_id em_imaging _item.mandatory_code no _item_type.code line loop_ _item_enumeration.value 'GATAN HELIUM' 'GATAN LIQUID NITROGEN' OTHER save_ save__em_imaging.details _item_description.description ; Any additional imaging details. ; _item.name '_em_imaging.details' _item.category_id em_imaging _item.mandatory_code no _item_type.code text _item_examples.case 'weak beam illumination' save_ save__em_imaging.date _item_description.description ; Date (YYYY-MM-DD) of imaging experiment or the date at which a series of experiments began. ; _item.name '_em_imaging.date' _item.category_id em_imaging _item.mandatory_code no # _item_type.code yyyy-mm-dd _item_type.code line _item_examples.case '2001-05-08' save_ save__em_imaging.accelerating_voltage _item_description.description ; A value of accelerating voltage (in kV) used for imaging. ; _item.name '_em_imaging.accelerating_voltage' _item.category_id em_imaging _item.mandatory_code no _item_type.code int _item_units.code kilovolts _item_examples.case 300 save_ save__em_imaging.illumination_mode _item_description.description ; The mode of illumination. ; _item.name '_em_imaging.illumination_mode' _item.category_id em_imaging _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'FLOOD BEAM' 'FLOOD BEAM LOW DOSE' 'SPOT SCAN' OTHER save_ save__em_imaging.mode _item_description.description ; The mode of imaging. ; _item.name '_em_imaging.mode' _item.category_id em_imaging _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'BRIGHT FIELD' 'DARK FIELD' DIFFRACTION OTHER save_ save__em_imaging.nominal_cs _item_description.description ; The spherical aberration coefficient (Cs) in millimetres, of the objective lens. ; _item.name '_em_imaging.nominal_cs' _item.category_id em_imaging _item.mandatory_code no _item_type.code float _item_units.code millimetres _item_examples.case 1.4 save_ save__em_imaging.nominal_defocus_min _item_description.description ; The minimum defocus value of the objective lens (in nanometres) used to obtain the recorded images. ; _item.name '_em_imaging.nominal_defocus_min' _item.category_id em_imaging _item.mandatory_code no _item_type.code float _item_units.code nanometres _item_examples.case 975 save_ save__em_imaging.nominal_defocus_max _item_description.description ; The maximum defocus value of the objective lens (in nanometres) used to obtain the recorded images. ; _item.name '_em_imaging.nominal_defocus_max' _item.category_id em_imaging _item.mandatory_code no _item_type.code float _item_units.code nanometres _item_examples.case 7600 save_ save__em_imaging.tilt_angle_min _item_description.description ; The minimum angle at which the specimen was tilted to obtain recorded images. ; _item.name '_em_imaging.tilt_angle_min' _item.category_id em_imaging _item.mandatory_code no _item_type.code float _item_units.code degrees _item_examples.case 0 save_ save__em_imaging.tilt_angle_max _item_description.description ; The maximum angle at which the specimen was tilted to obtain recorded images. ; _item.name '_em_imaging.tilt_angle_max' _item.category_id em_imaging _item.mandatory_code no _item_type.code float _item_units.code degrees _item_examples.case 60 save_ save__em_imaging.nominal_magnification _item_description.description ; The magnification indicated by the microscope readout. ; _item.name '_em_imaging.nominal_magnification' _item.category_id em_imaging _item.mandatory_code no _item_type.code int _item_examples.case 60000 save_ save__em_imaging.calibrated_magnification _item_description.description ; The magnification value obtained for a known standard just prior to, during or just after the imaging experiment. ; _item.name '_em_imaging.calibrated_magnification' _item.category_id em_imaging _item.mandatory_code no _item_type.code int _item_examples.case 61200 save_ save__em_imaging.electron_source _item_description.description ; The source of electrons. The electron gun. ; _item.name '_em_imaging.electron_source' _item.category_id em_imaging _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'FIELD EMISSION GUN' LAB6 'TUNGSTEN HAIRPIN' 'SCHOTTKY FIELD EMISSION GUN' OTHER save_ save__em_imaging.electron_dose _item_description.description ; The electron dose received by the specimen (electrons per square angstrom). ; _item.name '_em_imaging.electron_dose' _item.category_id em_imaging _item.mandatory_code no _item_type.code float _item_units.code electrons_angstrom_squared _item_examples.case 0.9 save_ save__em_imaging.energy_filter _item_description.description ; The type of energy filter spectrometer apparatus. ; _item.name '_em_imaging.energy_filter' _item.category_id em_imaging _item.mandatory_code no _item_type.code line _item_examples.case 'FEI' save_ save__em_imaging.energy_window _item_description.description ; The energy filter range in electron volts (eV)set by spectrometer. ; _item.name '_em_imaging.energy_window' _item.category_id em_imaging _item.mandatory_code no _item_type.code line _item_units.code electron_volts _item_examples.case '0 - 15' save_ save__em_imaging.citation_id _item_description.description ; This data item is a pointer to _citation.id in the CITATION category. ; _item.name '_em_imaging.citation_id' _item.category_id em_imaging _item.mandatory_code no _item_linked.child_name '_em_imaging.citation_id' _item_linked.parent_name '_citation.id' _item_type.code code save_ save__em_imaging.temperature _item_description.description ; The mean specimen stage temperature (degrees Kelvin) during imaging in the microscope. ; _item.name '_em_imaging.temperature' _item.category_id em_imaging _item.mandatory_code no _item_type.code float _item_units.code kelvins save_ save__em_imaging.detector_distance _item_description.description ; The camera length (in millimetres). The camera length is the product of the objective focal length and the combined magnification of the intermediate and projector lenses when the microscope is operated in the diffraction mode. ; _item.name '_em_imaging.detector_distance' _item.category_id em_imaging _item.mandatory_code no _item_type.code float _item_units.code millimetres save_ save__em_imaging.recording_temperature_minimum _item_description.description ; The specimen temperature minimum (degrees Kelvin) for the duration of imaging. ; _item.name '_em_imaging.recording_temperature_minimum' _item.category_id em_imaging _item.mandatory_code no _item_type.code float _item_units.code kelvins save_ save__em_imaging.recording_temperature_maximum _item_description.description ; The specimen temperature maximum (degrees Kelvin) for the duration of imaging. ; _item.name '_em_imaging.recording_temperature_maximum' _item.category_id em_imaging _item.mandatory_code no _item_type.code float _item_units.code kelvins save_ ################# ## EM_DETECTOR ## ################# save_em_detector _category.description ; Data items in the EM_DETECTOR category record details of the image detector type. ; _category.id em_detector _category.mandatory_code no loop_ _category_key.name '_em_detector.entry_id' '_em_detector.id' loop_ _category_group.id 'inclusive_group' 'em_group' loop_ _category_examples.detail _category_examples.case ; Example 1 - based on PDB entry 1DYL and laboratory records for the structure corresponding to PDB entry 1DYL ; ; _em_detector.entry_id 1DYL _em_detector.id 1 _em_detector.details . _em_detector.type 'KODAK SO163 FILM' _em_detector.detective_quantum_efficiency . ; save_ save__em_detector.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_em_detector.entry_id' _item.category_id em_detector _item.mandatory_code yes _item_type.code code _item_linked.child_name '_em_detector.entry_id' _item_linked.parent_name '_entry.id' save_ save__em_detector.id _item_description.description ; The value of _em_detector.id must uniquely identify the detector used for imaging. ; _item.name '_em_detector.id' _item.category_id em_detector _item.mandatory_code yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_em_imaging.detector_id' '_em_detector.id' save_ save__em_detector.details _item_description.description ; Any additional information about the detection system. ; _item.name '_em_detector.details' _item.category_id em_detector _item.mandatory_code no _item_type.code text save_ save__em_detector.type _item_description.description ; The detector type used for recording images. Usually film or CCD camera. ; _item.name '_em_detector.type' _item.category_id em_detector _item.mandatory_code no _item_type.code line loop_ _item_examples.case 'KODAK SO163 FILM' 'GATAN 673' 'GATAN 676' 'GATAN 692' 'GATAN 794' 'GATAN 1000' 'GATAN 4000' 'TVIPS BIOCAM' 'TVIPS TEMCAM F214' 'TVIPS TEMCAM F224' 'TVIPS FASTSCAN F114' PROSCAN AMT save_ save__em_detector.detective_quantum_efficiency _item_description.description ; The detective_quantum_efficiency (DQE)is defined as the square of the signal-to-noise ratio in the recording device divided by the square of the signal-to-ratio in the electron beam: (SIGNAL/NOISE)2 recording device DQE = ------------------------------- (SIGNAL/NOISE)2 electron beam A DQE value of 1 indicates a perfect recorder. "DQE = 0.25" menas that the signal-to-noise ratio is reduced by half in the recording step. (0.5)**2 DQE = --------- = 0.25. (1.0)**2 ; _item.name '_em_detector.detective_quantum_efficiency' _item.category_id em_detector _item.mandatory_code no _item_type.code float _item_examples.case 0.25 save_ #################### ## EM_IMAGE_SCANS ## #################### save_em_image_scans _category.description ; Data items in the EM_IMAGE_SCANS category record details of the image scanning device (microdensitometer) and parameters for digitization of the image. ; _category.id em_image_scans _category.mandatory_code no loop_ _category_key.name '_em_image_scans.entry_id' '_em_image_scans.id' loop_ _category_group.id 'inclusive_group' 'em_group' loop_ _category_examples.detail _category_examples.case ; Example 1 - based on PDB entry 1DYL and laboratory records for the structure corresponding to PDB entry 1DYL ; ; _em_image_scans.entry_id 1DYL _em_image_scans.id 2 _em_image_scans.number_digital_images 48 _em_image_scans.details . _em_image_scans.scanner_model . _em_image_scans.sampling_size . _em_image_scans.od_range . _em_image_scans.quant_bit_number . _em_image_scans.citation_id 1 ; save_ save__em_image_scans.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_em_image_scans.entry_id' _item.category_id em_image_scans _item.mandatory_code yes _item_type.code code _item_linked.child_name '_em_image_scans.entry_id' _item_linked.parent_name '_entry.id' save_ save__em_image_scans.id _item_description.description ; The value of _em_image_scans.id must uniquely identify the images scanned. ; _item.name '_em_image_scans.id' _item.category_id em_image_scans _item.mandatory_code yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_em_imaging.scans_id' '_em_image_scans.id' save_ save__em_image_scans.number_digital_images _item_description.description ; The number of images scanned and digitised. ; _item.name '_em_image_scans.number_digital_images' _item.category_id em_image_scans _item.mandatory_code no _item_type.code int save_ save__em_image_scans.details _item_description.description ; Any additional details about scanning images. ; _item.name '_em_image_scans.details' _item.category_id em_image_scans _item.mandatory_code no _item_type.code text save_ save__em_image_scans.scanner_model _item_description.description ; The scanner model. ; _item.name '_em_image_scans.scanner_model' _item.category_id em_image_scans _item.mandatory_code no _item_type.code line loop_ _item_enumeration.value 'ZEISS SCAI' 'EMIL 10' OPTRONICS 'PERKIN ELMER' TEMSCAN OTHER save_ save__em_image_scans.sampling_size _item_description.description ; The sampling step size (microns) set on the scanner. ; _item.name '_em_image_scans.sampling_size' _item.category_id em_image_scans _item.mandatory_code no _item_type.code float _item_units.code microns save_ save__em_image_scans.od_range _item_description.description ; The optical density range (OD=-log 10 transmission). To the eye OD=1 appears light grey and OD=3 is opaque. ; _item.name '_em_image_scans.od_range' _item.category_id em_image_scans _item.mandatory_code no _item_type.code float _item_examples.case 1.4 save_ save__em_image_scans.quant_bit_size _item_description.description ; The number of bits per pixel. ; _item.name '_em_image_scans.quant_bit_size' _item.category_id em_image_scans _item.mandatory_code no _item_type.code int _item_examples.case 8 save_ save__em_image_scans.citation_id _item_description.description ; This data item is a pointer to _citation.id in the CITATION category. ; _item.name '_em_image_scans.citation_id' _item.category_id em_image_scans _item.mandatory_code no _item_type.code code _item_linked.child_name '_em_image_scans.citation_id' _item_linked.parent_name '_citation.id' save_ ################################ ## EM_2D_PROJECTION_SELECTION ## ################################ save_em_2d_projection_selection _category.description ; Data items in the EM_2D_PROJECTION_SELECTION category record details of images from scanned micrographs and the number of particles selected from a scanned set of micrographs. ; _category.id em_2d_projection_selection _category.mandatory_code no _category_key.name '_em_2d_projection_selection.entry_id' loop_ _category_group.id 'inclusive_group' 'em_group' loop_ _category_examples.detail _category_examples.case ; Example 1 - based on PDB entry 1DYL and laboratory records for the structure corresponding to PDB entry 1DYL ; ; _em_2d_projection_selection.entry_id 1 _em_2d_projection_selection.number_particles 5267 _em_2d_projection_selection.software_name 1 _em_2d_projection_selection.method 'INTERACTIVE' _em_2d_projection_selection.details . _em_2d_projection_selection.citation_id 1 ; save_ save__em_2d_projection_selection.entry_id _item_description.description ; The value of _em_2d_projection_selection.entry_id points to the ENTRY category. ; _item.name '_em_2d_projection_selection.entry_id' _item.category_id em_2d_projection_selection _item.mandatory_code yes _item_type.code code _item_linked.child_name '_em_2d_projection_selection.entry_id' _item_linked.parent_name '_entry.id' save_ save__em_2d_projection_selection.num_particles _item_description.description ; The number of particles selected from the projection set of images. ; _item.name '_em_2d_projection_selection.num_particles' _item.category_id em_2d_projection_selection _item.mandatory_code no _item_type.code int _item_examples.case 840 save_ save__em_2d_projection_selection.software_name _item_description.description ; This data item is a pointer to _software.name in the SOFTWARE category. ; _item.name '_em_2d_projection_selection.software_name' _item.category_id em_2d_projection_selection _item.mandatory_code no _item_type.code line # _item_linked.child_name '_em_2d_projection_selection.software_name' # _item_linked.parent_name '_software.name' save_ save__em_2d_projection_selection.method _item_description.description ; The method used for selecting observed assemblies. ; _item.name '_em_2d_projection_selection.method' _item.category_id em_2d_projection_selection _item.mandatory_code no _item_type.code text _item_examples.case 'particles picked interactively from monitor' save_ save__em_2d_projection_selection.details _item_description.description ; Any additional details used for selecting observed assemblies. ; _item.name '_em_2d_projection_selection.details' _item.category_id em_2d_projection_selection _item.mandatory_code no _item_type.code text _item_examples.case 'negative monitor contrast facilitated particle picking' save_ save__em_2d_projection_selection.citation_id _item_description.description ; This data item is a pointer to _citation.id in the CITATION category. ; _item.name '_em_2d_projection_selection.citation_id' _item.category_id em_2d_projection_selection _item.mandatory_code no _item_type.code code _item_linked.child_name '_em_2d_projection_selection.citation_id' _item_linked.parent_name '_citation.id' save_ ################################# ## EM_EULER_ANGLE_DISTRIBUTION ## ################################# save_em_euler_angle_distribution _category.description ; Data items in the EM_EULER_ANGLE_DISTRIBUTION category record details of assignment of Euler angles for projection sets of particles. ; _category.id em_euler_angle_distribution _category.mandatory_code no loop_ _category_key.name '_em_euler_angle_distribution.id' '_em_euler_angle_distribution.entry_id' loop_ _category_group.id 'inclusive_group' 'em_group' loop_ _category_examples.detail _category_examples.case ; Example 1 - based on PDB entry 1DYL and laboratory records for the structure corresponding to PDB entry 1DYL ; ; _em_euler_angle_distribution.entry_id 1DYL _em_euler_angle_distribution.id 1 _em_euler_angle_distribution.details . _em_euler_angle_distribution.alpha . _em_euler_angle_distribution.beta . _em_euler_angle_distribution.gamma . ; save_ save__em_euler_angle_distribution.id _item_description.description ; The value of _em_euler_angle_distribution.id must uniquely identify the euler angle assignments of the projection set used in the final reconstruction. ; _item.name '_em_euler_angle_distribution.id' _item.category_id em_euler_angle_distribution _item.mandatory_code yes _item_type.code code save_ save__em_euler_angle_distribution.entry_id _item_description.description ; The value of _em_euler_angle_distribution.entry_id is a pointer to the ENTRY category. ; _item.name '_em_euler_angle_distribution.entry_id' _item.category_id em_euler_angle_distribution _item.mandatory_code yes _item_type.code code _item_linked.child_name '_em_euler_angle_distribution.entry_id' _item_linked.parent_name '_entry.id' save_ save__em_euler_angle_distribution.details _item_description.description ; Any additional details of the euler angles distribution and assignment. ; _item.name '_em_euler_angle_distribution.details' _item.category_id em_euler_angle_distribution _item.mandatory_code no _item_type.code text save_ save__em_euler_angle_distribution.alpha _item_description.description ; The euler-alpha angle assignment. ; _item.name '_em_euler_angle_distribution.alpha' _item.category_id em_euler_angle_distribution _item.mandatory_code no _item_type.code float _item_units.code degrees _item_examples.case 90 save_ save__em_euler_angle_distribution.beta _item_description.description ; The euler-beta angle assignment. ; _item.name '_em_euler_angle_distribution.beta' _item.category_id em_euler_angle_distribution _item.mandatory_code no _item_type.code float _item_units.code degrees _item_examples.case 90 save_ save__em_euler_angle_distribution.gamma _item_description.description ; The euler-gamma angle assignment. ; _item.name '_em_euler_angle_distribution.gamma' _item.category_id em_euler_angle_distribution _item.mandatory_code no _item_type.code float _item_units.code degrees _item_examples.case 0 save_ ########################## ## EM_3D_RECONSTRUCTION ## ########################## save_em_3d_reconstruction _category.description ; Data items in the EM_3D_RECONSTRUCTION category record details of the 3D reconstruction procedure from 2D projections. ; _category.id em_3d_reconstruction _category.mandatory_code no loop_ _category_key.name '_em_3d_reconstruction.entry_id' '_em_3d_reconstruction.id' loop_ _category_group.id 'inclusive_group' 'em_group' loop_ _category_examples.detail _category_examples.case ; Example 1 - based on PDB entry 1DYL and laboratory records for the structure corresponding to PDB entry 1DYL ; ; _em_3d_reconstruction.entry_id 1DYL _em_3d_reconstruction.id 1 _em_3d_reconstruction.method 'CROSS-COMMON LINES' _em_3d_reconstruction.citation_id 1 _em_3d_reconstruction.details . _em_3d_reconstruction.resolution 9 _em_3d_reconstruction.resolution_method . _em_3d_reconstruction.ctf_correction_method . _em_3d_reconstruction.nominal_pixel_size 2.64 _em_3d_reconstruction.actual_pixel_size 2.52 ; save_ save__em_3d_reconstruction.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_em_3d_reconstruction.entry_id' _item.category_id em_3d_reconstruction _item.mandatory_code yes _item_type.code code _item_linked.child_name '_em_3d_reconstruction.entry_id' _item_linked.parent_name '_entry.id' save_ save__em_3d_reconstruction.id _item_description.description ; The value of _em_3d_reconstruction.id must uniquely identify the 3d reconstruction. ; _item.name '_em_3d_reconstruction.id' _item.category_id em_3d_reconstruction _item.mandatory_code yes _item_type.code code save_ save__em_3d_reconstruction.method _item_description.description ; The algorithm method used for the 3d-reconstruction. ; _item.name '_em_3d_reconstruction.method' _item.category_id em_3d_reconstruction _item.mandatory_code no _item_type.code text _item_examples.case 'cross-common lines' save_ save__em_3d_reconstruction.citation_id _item_description.description ; This data item is a pointer to _citation.id in the CITATION category. ; _item.name '_em_3d_reconstruction.citation_id' _item.category_id em_3d_reconstruction _item.mandatory_code no _item_type.code code _item_linked.child_name '_em_3d_reconstruction.citation_id' _item_linked.parent_name '_citation.id' save_ save__em_3d_reconstruction.details _item_description.description ; Any additional details used in the 3d reconstruction. ; _item.name '_em_3d_reconstruction.details' _item.category_id em_3d_reconstruction _item.mandatory_code no _item_type.code text save_ save__em_3d_reconstruction.resolution _item_description.description ; The final resolution (in angstroms)of the 3d reconstruction. ; _item.name '_em_3d_reconstruction.resolution' _item.category_id em_3d_reconstruction _item.mandatory_code no _item_type.code float _item_units.code angstroms save_ save__em_3d_reconstruction.resolution_method _item_description.description ; The method used to determine the final resolution of the 3d reconstruction. The Fourier Shell Correlation criterion as a measure of resolution is based on the concept of splitting the (2D) data set into two halves; averaging each and comparing them using the Fourier Ring Correlation (FRC) technique. ; _item.name '_em_3d_reconstruction.resolution_method' _item.category_id em_3d_reconstruction _item.mandatory_code no _item_type.code text _item_examples.case 'FSC at 0.5 cut-off' save_ save__em_3d_reconstruction.magnification_calibration _item_description.description ; The magnification calibration method for the 3d reconstruction. ; _item.name '_em_3d_reconstruction.magnification_calibration' _item.category_id em_3d_reconstruction _item.mandatory_code no _item_type.code text save_ save__em_3d_reconstruction.ctf_correction_method _item_description.description ; The CTF-correction method. The Contrast Transfer Function CTF compensation for low contrast specimens (e.g. frozen-hydrated), for which phase contrast is the only significant mechanism, then higher defocus levels must be used to achieve any significant transfer, and several images at different focus levels must be combined to complete the information lost from the transfer gaps of any one image. The CTF correction can be applied to each extracted particle separately or to the whole micrograph after digitisation. The simplest level of compensation is to reverse phases at the negative lobes of the CTF. ; _item.name '_em_3d_reconstruction.ctf_correction_method' _item.category_id em_3d_reconstruction _item.mandatory_code no _item_type.code text _item_examples.case 'CTF correction of each particle' save_ save__em_3d_reconstruction.nominal_pixel_size _item_description.description ; The nominal pixel size of the projection set of images. ; _item.name '_em_3d_reconstruction.nominal_pixel_size' _item.category_id em_3d_reconstruction _item.mandatory_code no _item_type.code float save_ save__em_3d_reconstruction.actual_pixel_size _item_description.description ; The actual pixel size of projection set of images. ; _item.name '_em_3d_reconstruction.actual_pixel_size' _item.category_id em_3d_reconstruction _item.mandatory_code no _item_type.code float save_ ################### ## EM_3D_FITTING ## ################### save_em_3d_fitting _category.description ; Data items in the 3D_FITTING category record details of the method of fitting atomic coordinates from a PDB file into a 3d-em volume map file ; _category.id em_3d_fitting _category.mandatory_code no loop_ _category_key.name '_em_3d_fitting.id' '_em_3d_fitting.entry_id' loop_ _category_group.id 'em_group' 'inclusive_group' loop_ _category_examples.detail _category_examples.case ; Example 1 - based on PDB entry 1DYL and laboratory records for the structure corresponding to PDB entry 1DYL ; ; _em_3d_fitting.id 1 _em_3d_fitting.entry_id 1DYL _em_3d_fitting.method AUTOMATIC _em_3d_fitting.target_criteria R-FACTOR _em_3d_fitting.software_name 1 _em_3d_fitting.over_all_b_value . _em_3d_fitting.ref_space REAL _em_3d_fitting.ref_protocol 'RIGID BODY REFINEMENT' _em_3d_fitting.details ; THE CRYSTAL STRUCTURE OF THE CAPSID PROTEIN FROM CHOI ET AL (1997) PROTEINS 3 27:345-359 (SUBUNIT A OF PDB FILE 1VCQ) WAS PLACED INTO THE CRYO-EM DENSITY MAP. THE CAPSID PROTEIN WAS FIRST MANUALLY POSITIONED INTO THE CRYO-EM DENSITY CORRESPONDING TO POSITIONS OF THE FOUR INDEPENDENT MONOMER DENSITIES BETWEEN THE INNER LEAFLET OF THE BILAYER AND THE RNA. THESE POSITIONS WERE THEN REFINED BY RIGID BODY REFINEMENT IN REAL SPACE WITH THE PROGRAM EMFIT (CHENG ET AL. 1995, CELL 80, 621-630). THE QUALITY OF THE FIT CAN BE SEEN FROM THE MAP DENSITY WITHIN THE PROTEIN. ALL 4563 ATOMS ARE IN DENSITY OF AT LEAST 4 SIGMA (96.73) ABOVE THE AVERAGE (512.04), 1167 ATOMS ARE IN DENSITY BETWEEN 4 AND 5 SIGMA, 3174 ATOMS ARE IN DENSITY BETWEEN 5 AND 6 SIGMA, AND 222 ATOMS ARE IN DENSTY OF 6 SIGMA OR ABOVE. THE VARIATION IN DENSITY OVER THE FITTED PROTEIN CAN BE VISUALIZED WITH THE PSEUDO TEMPERATURE FACTOR. THE DENSITY VALUE AT EACH ATOM IS GIVEN IN THE 8TH COLUM (USUALLY THE OCCUPANCY) AS THE NUMBER OF STANDARD DEVIATION ABOVE BACKGROUND. COLUMN NINE (USUALLY THE TEMPERATURE FACTOR) CONTAINS THE VALUE OF THE RELATIVE DENSITY WITHIN THE FITTED PROTEIN SCALED LINEARLY SO THAT THE MINIMUM DENSITY IS 100.0 AND THE MAXIMUM DENSITY IS 1.0. THE ATOMS THAT LIE IN THE LOWER DENSITY REGIONS WILL HAVE THE HIGHEST PSEUDO TEMPERATURE FACTORS. ; ; save_ save__em_3d_fitting.id _item_description.description ; The value of _em_3d_fitting.id must uniquely identify a fitting procedure of atomic coordinates into 3dem reconstructed volume map. ; loop_ _item.name _item.category_id _item.mandatory_code '_em_3d_fitting.id' em_3d_fitting yes '_em_3d_fitting_list.3d_fitting_id' em_3d_fitting_list yes loop_ _item_linked.child_name _item_linked.parent_name '_em_3d_fitting_list.3d_fitting_id' '_em_3d_fitting.id' _item_type.code code save_ save__em_3d_fitting.entry_id _item_description.description ; This data item is a pointer to _entry_id in the ENTRY category. ; _item.name '_em_3d_fitting.entry_id' _item.category_id em_3d_fitting _item.mandatory_code yes _item_type.code code _item_linked.child_name '_em_3d_fitting.entry_id' _item_linked.parent_name '_entry.id' save_ save__em_3d_fitting.method _item_description.description ; The method used to fit atomic coordinates into the 3dem reconstructed map. ; _item.name '_em_3d_fitting.method' _item.category_id em_3d_fitting _item.mandatory_code no _item_type.code line save_ save__em_3d_fitting.target_criteria _item_description.description ; The quality of fit of the atomic coordinates into the 3dem volume map. ; _item.name '_em_3d_fitting.target_criteria' _item.category_id em_3d_fitting _item.mandatory_code no _item_type.code text _item_examples.case 'best visual fit using the program O' save_ save__em_3d_fitting.software_name _item_description.description ; This data item is a pointer to _software.name in the category. ; _item.name '_em_3d_fitting.software_name' _item.category_id em_3d_fitting _item.mandatory_code no _item_type.code line # _item_linked.child_name '_em_3d_fitting.software_name' # _item_linked.parent_name '_software.name' save_ save__em_3d_fitting.details _item_description.description ; Any additional details regarding fitting of atomic coordinates into the 3d-em volume. ; _item.name '_em_3d_fitting.details' _item.category_id em_3d_fitting _item.mandatory_code no _item_type.code text _item_examples.case 'partial' save_ save__em_3d_fitting.overall_b_value _item_description.description ; The overall B (temperature factor) value for the 3d-em volume. ; _item.name '_em_3d_fitting.overall_b_value' _item.category_id em_3d_fitting _item.mandatory_code no _item_type.code float save_ save__em_3d_fitting.ref_space _item_description.description ; A flag to indicate whether fitting was carried out in real or reciprocal refinement space. ; _item.name '_em_3d_fitting.ref_space' _item.category_id em_3d_fitting _item.mandatory_code no _item_type.code line loop_ _item_enumeration.value REAL RECIPROCAL save_ save__em_3d_fitting.ref_protocol _item_description.description ; The type of protocol used in the refinement. ; _item.name '_em_3d_fitting.ref_protocol' _item.category_id em_3d_fitting _item.mandatory_code no _item_type.code text _item_examples.case 'rigid body' save_ ######################## ## EM_3D_FITTING_LIST ## ######################## save_em_3d_fitting_list _category.description ; Data items in the 3D_FITTING_LIST category lists the methods of fitting atomic coordinates from a PDB file into a 3d-em volume map file ; _category.id em_3d_fitting_list _category.mandatory_code no loop_ _category_key.name '_em_3d_fitting_list.id' '_em_3d_fitting_list.3d_fitting_id' loop_ _category_group.id 'inclusive_group' 'em_group' loop_ _category_examples.detail _category_examples.case ; Example 1 - based on PDB entry 1DYL and laboratory records for the structure corresponding to PDB entry 1DYL ; ; _em_3d_fitting_list.id 1 _em_3d_fitting_list.fitting_id l _em_3d_fitting_list.pdb_entry_id 1VCQ _em_3d_fitting_list.pdb_chain_id . ; save_ save__em_3d_fitting_list.id _item_description.description ; This data item is a unique identifier. ; _item.name '_em_3d_fitting_list.id' _item.category_id em_3d_fitting_list _item.mandatory_code yes _item_type.code code save_ save__em_3d_fitting_list.3d_fitting_id _item_description.description ; The value of _em_3d_fitting_list.3d_fitting_id is a pointer to _em_3d_fitting.id in the 3d_fitting category ; _item.name '_em_3d_fitting_list.3d_fitting_id' _item.mandatory_code yes save_ save__em_3d_fitting_list.pdb_entry_id _item_description.description ; The PDB code for the entry used in fitting. ; _item.name '_em_3d_fitting_list.pdb_entry_id' _item.category_id em_3d_fitting_list _item.mandatory_code no _item_type.code line save_ save__em_3d_fitting_list.pdb_chain_id _item_description.description ; The chain id for the entry used in fitting. ; _item.name '_em_3d_fitting_list.pdb_chain_id' _item.category_id em_3d_fitting_list _item.mandatory_code no _item_type.code code save_ ############################# ## EM_ELECTRON_DIFFRACTION ## ############################# save_em_electron_diffraction _category.description ; Data items in the EM_ELECTRON_DIFFRACTION category record details about the electron diffraction data from the electron crystallography experiment. ; _category.id em_electron_diffraction _category.mandatory_code no loop_ _category_key.name '_em_electron_diffraction.id' '_em_electron_diffraction.entry_id' loop_ _category_group.id 'inclusive_group' 'em_group' loop_ _category_examples.detail _category_examples.case ; Example 1 - based on PDB entry 1TUB and laboratory records for the structure corresponding to PDB entry 1TUB ; ; _em_electron_diffraction.entry_id 1TUB _em_electron_diffraction.id 1 _em_electron_diffraction.num_structure_factors 12000 _em_electron_diffraction.num_diff_patterns . _em_electron_diffraction.details . ; save_ save__em_electron_diffraction.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_em_electron_diffraction.entry_id' _item.category_id em_electron_diffraction _item.mandatory_code yes _item_type.code code _item_linked.child_name '_em_electron_diffraction.entry_id' _item_linked.parent_name '_entry.id' save_ save__em_electron_diffraction.id _item_description.description ; The value of _electron_diffraction.id must uniquely identify the electron diffraction experiment. ; _item.name '_em_electron_diffraction.id' _item.category_id em_electron_diffraction _item.mandatory_code yes _item_type.code code save_ save__em_electron_diffraction.num_structure_factors _item_description.description ; The number of structure factors from the electron diffraction experiment. ; _item.name '_em_electron_diffraction.num_structure_factors' _item.category_id em_electron_diffraction _item.mandatory_code no _item_type.code int _item_examples.case '12000' save_ save__em_electron_diffraction.num_diff_patterns _item_description.description ; The number of diffraction patterns used from the electron diffraction experiment. ; _item.name '_em_electron_diffraction.num_diff_patterns' _item.category_id em_electron_diffraction _item.mandatory_code no _item_type.code int save_ save__em_electron_diffraction.details _item_description.description ; Details of the electron diffraction experiment ; _item.name '_em_electron_diffraction.details' _item.category_id em_electron_diffraction _item.mandatory_code yes _item_type.code text loop_ _item_examples.case _item_examples.detail 1 ; THE MODEL WAS DERIVED USING ELECTRON DIFFRACTION AND IMAGE DATA FROM TWO DIMENSIONAL CRYSTALS OF TUBULIN INDUCED BY THE PRESENCE OF ZN++ IONS. WHAT FOLLOWS ARE THE COORDINATES FOR THE AB-TUBULIN DIMER BOUND TO TAXOL AS OBTAINED BY ELECTRON CRYSTALLOGRAPHY OF ZINC-INDUCED SHEETS. THIS IS THE UNREFINED MODEL, BUILT INTO A RAW DENSITY MAP WHERE THE RESOLUTION IN THE PLANE OF THE SHEET WAS 3.7 ANGSTROMS AND THAT PERPENDICULAR TO THE SHEET ABOUT 4.8 ANGSTROMS. THE MODEL DOES NOT CONTAIN MOST OF THE C-TERMINAL RESIDUES OF EITHER MONOMER WHICH WERE DISORDERED IN THE MAP. THE LOOP BETWEEN HELIX H1 AND STRAND S2, AND THAT BETWEEN H2 AND S3 ARE PRESENT FOR COMPLETENESS BUT WERE BUILT INTO VERY WEAK DENSITY. GIVEN THE LIMITED RESOLUTION OF THE MAP, THE CONFORMATION OF THE SIDE CHAINS, ESPECIALLY THOSE CORRESPONDING TO RESIDUES ON THE SURFACE OF THE DIMER, MUST BE TAKEN CAUTIOUSLY. IN ADDITION, BECAUSE THIS IS AN UNREFINED MODEL, CERTAIN GEOMETRY ERRORS MAY STILL BE PRESENT IN THE STRUCTURE. PLEASE TAKE THIS INTO ACCOUNT WHEN INTERPRETING YOUR OWN DATA BASED ON THE PRESENT TUBULIN STRUCTURE. ALTHOUGH THE POSITION OF RESIDUES (WITH THE EXCEPTION OF THOSE IN THE LOOPS MENTIONED ABOVE) SHOULD NOT CHANGE SIGNIFICANTLY UPON REFINEMENT, DRAWING INFORMATION AT THE LEVEL OF SIDE CHAIN CONFORMATION IS CLEARLY NOT ADVISED. FINALLY, PLEASE NOTICE THAT THE TAXOID IN THE MODEL IS THE TAXOL DERIVATIVE TAXOTERE. ; save_ ################################### ## EM_ELECTRON_DIFFRACTION_PHASE ## ################################### save_em_electron_diffraction_phase _category.description ; data items in the em_electron_diffraction_phase category record details about the phase information from the electron diffraction experiment. ; _category.id em_electron_diffraction_phase _category.mandatory_code no loop_ _category_key.name '_em_electron_diffraction_phase.id' '_em_electron_diffraction_phase.entry_id' loop_ _category_group.id 'inclusive_group' 'em_group' loop_ _category_examples.detail _category_examples.case ; example 1 - based on pdb entry 1tub and laboratory records for the structure corresponding to pdb entry 1tub ; ; _em_electron_diffraction_phase.entry_id 1TUB _em_electron_diffraction_phase.id 1 _em_electron_diffraction_phase.d_res_low 5.0 _em_electron_diffraction_phase.d_res_high 4.0 _em_electron_diffraction_phase.residual . _em_electron_diffraction_phase.highest_resolution_shell_error . _em_electron_diffraction_phase.overall_error . _em_electron_diffraction_phase.rejection_criteria_error . ; save_ save__em_electron_diffraction_phase.entry_id _item_description.description ; this data item is a pointer to _entry.id in the entry category. ; _item.name '_em_electron_diffraction_phase.entry_id' _item.category_id em_electron_diffraction_phase _item.mandatory_code yes _item_type.code code _item_linked.child_name '_em_electron_diffraction_phase.entry_id' _item_linked.parent_name '_entry.id' save_ save__em_electron_diffraction_phase.id _item_description.description ; the value of _electron_diffraction_phase.id must uniquely identify the electron diffraction phase experiment. ; _item.name '_em_electron_diffraction_phase.id' _item.category_id em_electron_diffraction_phase _item.mandatory_code yes _item_type.code code save_ save__em_electron_diffraction_phase.d_res_high _item_description.description ; the highest resolution d-value for the electron diffraction experiment. ; _item.name '_em_electron_diffraction_phase.d_res_high' _item.category_id em_electron_diffraction_phase _item.mandatory_code no _item_type.code int _item_examples.case '5.0' save_ save__em_electron_diffraction_phase.residual _item_description.description ; the phase residual value for the electron diffraction experiment. ; _item.name '_em_electron_diffraction_phase.residual' _item.category_id em_electron_diffraction_phase _item.mandatory_code no _item_type.code int save_ save__em_electron_diffraction_phase.highest_resolution_shell_error _item_description.description ; the highest resolution shell error in degrees. ; _item.name '_em_electron_diffraction_phase.highest_resolution_shell_error' _item.category_id em_electron_diffraction_phase _item.mandatory_code no _item_type.code int save_ save__em_electron_diffraction_phase.overall_error _item_description.description ; the overall phase error in degrees. ; _item.name '_em_electron_diffraction_phase.overall_error' _item.category_id em_electron_diffraction_phase _item.mandatory_code no _item_type.code int save_ save__em_electron_diffraction_phase.rejection_criteria_error _item_description.description ; the rejection criteria (phase error) in degrees. ; _item.name '_em_electron_diffraction_phase.rejection_criteria_error' _item.category_id em_electron_diffraction_phase _item.mandatory_code no _item_type.code int save_ ##################################### ## EM_ELECTRON_DIFFRACTION_PATTERN ## ##################################### save_em_electron_diffraction_pattern _category.description ; data items in the em_electron_diffraction_pattern category record details about the pattern information from the electron diffraction experiment. ; _category.id em_electron_diffraction_pattern _category.mandatory_code no loop_ _category_key.name '_em_electron_diffraction_pattern.id' '_em_electron_diffraction_pattern.entry_id' loop_ _category_group.id 'inclusive_group' 'em_group' loop_ _category_examples.detail _category_examples.case ; example 1 - based on pdb entry 1tub and laboratory records for the structure corresponding to pdb entry 1tub ; ; _em_electron_diffraction_pattern.entry_id 1TUB _em_electron_diffraction_pattern.id 1 _em_electron_diffraction_pattern.num_patterns_by_tilt_angle 1 _em_electron_diffraction_pattern.num_images_by_tilt_angle 4 _em_electron_diffraction_pattern.tilt_angle . ; save_ save__em_electron_diffraction_pattern.entry_id _item_description.description ; this data item is a pointer to _entry.id in the entry category. ; _item.name '_em_electron_diffraction_pattern.entry_id' _item.category_id em_electron_diffraction_pattern _item.mandatory_code yes _item_type.code code _item_linked.child_name '_em_electron_diffraction_pattern.entry_id' _item_linked.parent_name '_entry.id' save_ save__em_electron_diffraction_pattern.id _item_description.description ; the value of _electron_diffraction_pattern.id must uniquely identify the electron diffraction pattern experiment. ; _item.name '_em_electron_diffraction_pattern.id' _item.category_id em_electron_diffraction_pattern _item.mandatory_code yes _item_type.code code save_ save__em_electron_diffraction_pattern.num_patterns_by_tilt_angle _item_description.description ; the number of diffraction patterns by tilt angle. ; _item.name '_em_electron_diffraction_pattern.num_patterns_by_tilt_angle' _item.category_id em_electron_diffraction_pattern _item.mandatory_code no _item_type.code int _item_examples.case '1' save_ save__em_electron_diffraction_pattern.num_images_by_tilt_angle _item_description.description ; the number of images by tilt angle. ; _item.name '_em_electron_diffraction_pattern.num_images_by_tilt_angle' _item.category_id em_electron_diffraction_pattern _item.mandatory_code no _item_type.code int _item_examples.case '4' save_ save__em_electron_diffraction_pattern.tilt_angle _item_description.description ; the tilt angle at which the diffraction pattern was obtained. ; _item.name '_em_electron_diffraction_pattern.tilt_angle' _item.category_id em_electron_diffraction_pattern _item.mandatory_code no _item_type.code int save_ ### EOF mmcif_iims-def-2.dic ########################################################################### # # File: mmcif_pdbx-def-8.dic # # PDB Exchange Data Dictionary # # This data dictionary contains definitions used by wwPDB for data exchange # and data processing. # # Definition Section 8 # # ########################################################################### #################### ## RCSB_TABLEINFO ## #################### save_rcsb_tableinfo _category.description ; ; _category.id rcsb_tableinfo _category.mandatory_code no loop_ _category_key.name '_rcsb_tableinfo.tablename' loop_ _category_group.id 'inclusive_group' 'rcsb_group' _category_examples.case ; loop_ _rcsb_tableinfo.tablename _rcsb_tableinfo.description _rcsb_tableinfo.type _rcsb_tableinfo.table_serial_no _rcsb_tableinfo.group_name _rcsb_tableinfo.WWW_Selection_Criteria _rcsb_tableinfo.WWW_Report_Criteria summary 'summary data' 1 1 STRUCTURE 1 1 # ... ; save_ save__rcsb_tableinfo.tablename _item_description.description ; SQL table name. ; _item.name '_rcsb_tableinfo.tablename' _item.category_id rcsb_tableinfo _item.mandatory_code yes _item_type.code code30 _item_examples.case 'structure_summary' save_ save__rcsb_tableinfo.description _item_description.description ; SQL table description. ; _item.name '_rcsb_tableinfo.description' _item.category_id rcsb_tableinfo _item.mandatory_code yes _item_type.code text _item_examples.case 'Table of solvent coordinates' save_ save__rcsb_tableinfo.type _item_description.description ; SQL table type. ; _item.name '_rcsb_tableinfo.type' _item.category_id rcsb_tableinfo _item.mandatory_code yes _item_type.code int _item_examples.case '0=general, 1=coordinate, 2=derived, 3=schema' save_ save__rcsb_tableinfo.table_serial_no _item_description.description ; SQL table serial number. ; _item.name '_rcsb_tableinfo.table_serial_no' _item.category_id rcsb_tableinfo _item.mandatory_code yes _item_type.code int _item_examples.case '1,2,3,4,...' save_ save__rcsb_tableinfo.column_serial_no _item_description.description ; SQL column serial number. ; _item.name '_rcsb_tableinfo.column_serial_no' _item.category_id rcsb_tableinfo _item.mandatory_code yes _item_type.code int _item_examples.case '1,2,3,4,...' save_ save__rcsb_tableinfo.group_name _item_description.description ; SQL table group name.. ; _item.name '_rcsb_tableinfo.group_name' _item.category_id rcsb_tableinfo _item.mandatory_code yes _item_type.code line _item_examples.case 'STRUCTURE FEATURES, SOURCE ORGANISM' save_ save__rcsb_tableinfo.WWW_Selection_Criteria _item_description.description ; SQL table visibility in WWW selection querires. ; _item.name '_rcsb_tableinfo.WWW_Selection_Criteria' _item.category_id rcsb_tableinfo _item.mandatory_code yes _item_type.code int _item_examples.case '0=no, 1=yes' save_ save__rcsb_tableinfo.WWW_Report_Criteria _item_description.description ; SQL table visibility in WWW reports queries. ; _item.name '_rcsb_tableinfo.WWW_Report_Criteria' _item.category_id rcsb_tableinfo _item.mandatory_code yes _item_type.code int _item_examples.case '0=no, 1=yes' save_ ##################### ## RCSB_COLUMNINFO ## ##################### save_rcsb_columninfo _category.description ; ; _category.id rcsb_columninfo _category.mandatory_code no loop_ _category_key.name '_rcsb_columninfo.tablename' '_rcsb_columninfo.columnname' loop_ _category_group.id 'inclusive_group' 'rcsb_group' _category_examples.case ; loop_ _rcsb_columninfo.tablename _rcsb_columninfo.columnname _rcsb_columninfo.description _rcsb_columninfo.example _rcsb_columninfo.type _rcsb_columninfo.table_serial_no _rcsb_columninfo.column_serial_no _rcsb_columninfo.WWW_Selection_Criteria _rcsb_columninfo.WWW_Report_Criteria summary id 'id code' 'id1, id2' 1 1 1 1 1 # ... ; save_ save__rcsb_columninfo.columnname _item_description.description ; SQL column name. ; _item.name '_rcsb_columninfo.columnname' _item.category_id rcsb_columninfo _item.mandatory_code yes _item_type.code code30 _item_examples.case 'id' save_ save__rcsb_columninfo.tablename _item_description.description ; SQL table name. ; _item.name '_rcsb_columninfo.tablename' _item.category_id rcsb_columninfo _item.mandatory_code yes _item_type.code code30 _item_examples.case 'structure_summary' save_ save__rcsb_columninfo.description _item_description.description ; SQL column description. ; _item.name '_rcsb_columninfo.description' _item.category_id rcsb_columninfo _item.mandatory_code yes _item_type.code text _item_examples.case 'Table of solvent coordinates' save_ save__rcsb_columninfo.example _item_description.description ; SQL column example. ; _item.name '_rcsb_columninfo.example' _item.category_id rcsb_columninfo _item.mandatory_code yes _item_type.code text _item_examples.case 'Table of solvent coordinates' save_ save__rcsb_columninfo.type _item_description.description ; SQL column type. ; _item.name '_rcsb_columninfo.type' _item.category_id rcsb_columninfo _item.mandatory_code yes _item_type.code int _item_examples.case ;1:integer, 2:float, 3:string-single-left, 4:string-single-right, 5:string-multi-left, 6:string-multi-right, 7:angle, 8:boolean, 9:single character, 10:author or atom name column, 11: Date ; save_ save__rcsb_columninfo.table_serial_no _item_description.description ; SQL table serial number. ; _item.name '_rcsb_columninfo.table_serial_no' _item.category_id rcsb_columninfo _item.mandatory_code yes _item_type.code int _item_examples.case '1,2,3,4,...' save_ save__rcsb_columninfo.column_serial_no _item_description.description ; SQL column serial number. ; _item.name '_rcsb_columninfo.column_serial_no' _item.category_id rcsb_columninfo _item.mandatory_code yes _item_type.code int _item_examples.case '1,2,3,4,...' save_ save__rcsb_columninfo.WWW_Selection_Criteria _item_description.description ; SQL column visibility in WWW selection querires. ; _item.name '_rcsb_columninfo.WWW_Selection_Criteria' _item.category_id rcsb_columninfo _item.mandatory_code yes _item_type.code int _item_examples.case '0=no, 1=yes' save_ save__rcsb_columninfo.WWW_Report_Criteria _item_description.description ; SQL column visibility in WWW reports queries. ; _item.name '_rcsb_columninfo.WWW_Report_Criteria' _item.category_id rcsb_columninfo _item.mandatory_code yes _item_type.code int _item_examples.case '0=no, 1=yes' save_ ## ### EOF mmcif_pdbx-def-8.dic ########################################################################### # # File: mmcif_pdbx-def-9.dic # # PDB Exchange Data Dictionary # # This data dictionary contains definitions used by RCSB for describing # derived data and computation. # # Definition Section 9 # # ########################################################################### ################# ## PDBX_DOMAIN ## ################# save_pdbx_domain _category.description ; Data items in the PDBX_DOMAIN category record information about domain definitions. A domain need not correspond to a completely polypeptide chain; it can be composed of one more more segments in a single chain, or by segments from more than one chain. ; _category.id pdbx_domain _category.mandatory_code no _category_key.name '_pdbx_domain.id' loop_ _category_group.id 'inclusive_group' 'pdbx_group' 'pdbx_erf_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; loop_ _pdbx_domain.id _pdbx_domain.details d1 'Chains A, B' d2 'Asym_id D Residues 1-134' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_domain.details _item_description.description ; A description of special aspects of the structural elements that comprise a domain. ; _item.name '_pdbx_domain.details' _item.category_id pdbx_domain _item.mandatory_code no _item_type.code text _item_examples.case ; The loop between residues 18 and 23. ; save_ save__pdbx_domain.id _item_description.description ; The value of _pdbx_domain.id must uniquely identify a record in the PDBX_DOMAIN list. Note that this item need not be a number; it can be any unique identifier. ; _item.name '_pdbx_domain.id' _item.category_id pdbx_domain _item.mandatory_code yes _item_type.code code save_ ####################### ## PDBX_DOMAIN_RANGE ## ####################### save_pdbx_domain_range _category.description ; Data items in the PDBX_DOMAIN_RANGE category identify the beginning and ending points of polypeptide chain segments that form all or part of a domain. ; _category.id pdbx_domain_range _category.mandatory_code no loop_ _category_key.name '_pdbx_domain_range.domain_id' '_pdbx_domain_range.beg_label_alt_id' '_pdbx_domain_range.beg_label_asym_id' '_pdbx_domain_range.beg_label_comp_id' '_pdbx_domain_range.beg_label_seq_id' '_pdbx_domain_range.end_label_alt_id' '_pdbx_domain_range.end_label_asym_id' '_pdbx_domain_range.end_label_comp_id' '_pdbx_domain_range.end_label_seq_id' loop_ _category_group.id 'inclusive_group' 'pdbx_group' 'pdbx_erf_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; loop_ _pdbx_domain_range.domain_id _pdbx_domain_range.beg_label_alt_id _pdbx_domain_range.beg_label_asym_id _pdbx_domain_range.beg_label_comp_id _pdbx_domain_range.beg_label_seq_id _pdbx_domain_range.end_label_alt_id _pdbx_domain_range.end_label_asym_id _pdbx_domain_range.end_label_comp_id _pdbx_domain_range.end_label_seq_id d1 . A PRO 1 . A GLY 29 d1 . B PRO 31 . B GLY 59 d1 . C PRO 61 . B GLY 89 d2 . D PRO 91 . D GLY 119 d2 . E PRO 121 . E GLY 149 d2 . F PRO 151 . F GLY 179 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_domain_range.beg_label_alt_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain begins. This data item is a pointer to _atom_sites_alt.id in the ATOM_SITES_ALT category. ; _item.name '_pdbx_domain_range.beg_label_alt_id' _item.category_id pdbx_domain_range _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_domain_range.beg_label_alt_id' _item_linked.parent_name '_atom_site.label_alt_id' save_ save__pdbx_domain_range.beg_label_asym_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain begins. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_pdbx_domain_range.beg_label_asym_id' _item.category_id pdbx_domain_range _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_domain_range.beg_label_asym_id' _item_linked.parent_name '_atom_site.label_asym_id' save_ save__pdbx_domain_range.beg_label_comp_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain begins. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_pdbx_domain_range.beg_label_comp_id' _item.category_id pdbx_domain_range _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_domain_range.beg_label_comp_id' _item_linked.parent_name '_atom_site.label_comp_id' save_ save__pdbx_domain_range.beg_label_seq_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain begins. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_pdbx_domain_range.beg_label_seq_id' _item.category_id pdbx_domain_range _item.mandatory_code yes _item_type.code int _item_linked.child_name '_pdbx_domain_range.beg_label_seq_id' _item_linked.parent_name '_atom_site.label_seq_id' save_ save__pdbx_domain_range.beg_auth_asym_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain begins. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_pdbx_domain_range.beg_auth_asym_id' _item.category_id pdbx_domain_range _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_domain_range.beg_auth_asym_id' _item_linked.parent_name '_atom_site.auth_asym_id' save_ save__pdbx_domain_range.beg_auth_comp_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain begins. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_pdbx_domain_range.beg_auth_comp_id' _item.category_id pdbx_domain_range _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_domain_range.beg_auth_comp_id' _item_linked.parent_name '_atom_site.auth_comp_id' save_ save__pdbx_domain_range.beg_auth_seq_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain begins. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_pdbx_domain_range.beg_auth_seq_id' _item.category_id pdbx_domain_range _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_domain_range.beg_auth_seq_id' _item_linked.parent_name '_atom_site.auth_seq_id' save_ save__pdbx_domain_range.domain_id _item_description.description ; This data item is a pointer to _pdbx_domain.id in the PDBX_DOMAIN category. ; _item.name '_pdbx_domain_range.domain_id' _item.category_id pdbx_domain_range _item.mandatory_code yes _item_linked.child_name '_pdbx_domain_range.domain_id' _item_linked.parent_name '_pdbx_domain.id' save_ save__pdbx_domain_range.end_label_alt_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain ends. This data item is a pointer to _atom_sites_alt.id in the ATOM_SITES_ALT category. ; _item.name '_pdbx_domain_range.end_label_alt_id' _item.category_id pdbx_domain_range _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_domain_range.end_label_alt_id' _item_linked.parent_name '_atom_site.label_alt_id' save_ save__pdbx_domain_range.end_label_asym_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain ends. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_pdbx_domain_range.end_label_asym_id' _item.category_id pdbx_domain_range _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_domain_range.end_label_asym_id' _item_linked.parent_name '_atom_site.label_asym_id' save_ save__pdbx_domain_range.end_label_comp_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain ends. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_pdbx_domain_range.end_label_comp_id' _item.category_id pdbx_domain_range _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_domain_range.end_label_comp_id' _item_linked.parent_name '_atom_site.label_comp_id' save_ save__pdbx_domain_range.end_label_seq_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain ends. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_pdbx_domain_range.end_label_seq_id' _item.category_id pdbx_domain_range _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_domain_range.end_label_seq_id' _item_linked.parent_name '_atom_site.label_seq_id' save_ save__pdbx_domain_range.end_auth_asym_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain ends. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_pdbx_domain_range.end_auth_asym_id' _item.category_id pdbx_domain_range _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_domain_range.end_auth_asym_id' _item_linked.parent_name '_atom_site.auth_asym_id' save_ save__pdbx_domain_range.end_auth_comp_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain ends. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_pdbx_domain_range.end_auth_comp_id' _item.category_id pdbx_domain_range _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_domain_range.end_auth_comp_id' _item_linked.parent_name '_atom_site.auth_comp_id' save_ save__pdbx_domain_range.end_auth_seq_id _item_description.description ; A component of the identifier for the monomer at which this segment of the domain ends. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_pdbx_domain_range.end_auth_seq_id' _item.category_id pdbx_domain_range _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_domain_range.end_auth_seq_id' _item_linked.parent_name '_atom_site.auth_seq_id' save_ ######################### ## PDBX_SEQUENCE_RANGE ## ######################### save_pdbx_sequence_range _category.description ; Data items in the PDBX_SEQUENCE_RANGE category identify the beginning and ending points of polypeptide sequence segments. ; _category.id pdbx_sequence_range _category.mandatory_code no loop_ _category_key.name '_pdbx_sequence_range.seq_range_id' '_pdbx_sequence_range.beg_label_alt_id' '_pdbx_sequence_range.beg_label_asym_id' '_pdbx_sequence_range.beg_label_comp_id' '_pdbx_sequence_range.beg_label_seq_id' '_pdbx_sequence_range.end_label_alt_id' '_pdbx_sequence_range.end_label_asym_id' '_pdbx_sequence_range.end_label_comp_id' '_pdbx_sequence_range.end_label_seq_id' loop_ _category_group.id 'inclusive_group' 'pdbx_group' 'pdbx_erf_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; loop_ _pdbx_sequence_range.seq_range_id _pdbx_sequence_range.beg_label_alt_id _pdbx_sequence_range.beg_label_asym_id _pdbx_sequence_range.beg_label_comp_id _pdbx_sequence_range.beg_label_seq_id _pdbx_sequence_range.end_label_alt_id _pdbx_sequence_range.end_label_asym_id _pdbx_sequence_range.end_label_comp_id _pdbx_sequence_range.end_label_seq_id s1 . A PRO 1 . A GLY 29 s2 . D PRO 91 . D GLY 119 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_sequence_range.beg_label_alt_id _item_description.description ; A component of the identifier for the monomer at which this segment of the sequence range begins. This data item is a pointer to _atom_sites_alt.id in the ATOM_SITES_ALT category. ; _item.name '_pdbx_sequence_range.beg_label_alt_id' _item.category_id pdbx_sequence_range _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_sequence_range.beg_label_alt_id' _item_linked.parent_name '_atom_site.label_alt_id' save_ save__pdbx_sequence_range.beg_label_asym_id _item_description.description ; A component of the identifier for the monomer at which this segment of the sequence range begins. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_pdbx_sequence_range.beg_label_asym_id' _item.category_id pdbx_sequence_range _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_sequence_range.beg_label_asym_id' _item_linked.parent_name '_atom_site.label_asym_id' save_ save__pdbx_sequence_range.beg_label_comp_id _item_description.description ; A component of the identifier for the monomer at which this segment of the sequence range begins. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_pdbx_sequence_range.beg_label_comp_id' _item.category_id pdbx_sequence_range _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_sequence_range.beg_label_comp_id' _item_linked.parent_name '_atom_site.label_comp_id' save_ save__pdbx_sequence_range.beg_label_seq_id _item_description.description ; A component of the identifier for the monomer at which this segment of the sequence range begins. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_pdbx_sequence_range.beg_label_seq_id' _item.category_id pdbx_sequence_range _item.mandatory_code yes _item_type.code int _item_linked.child_name '_pdbx_sequence_range.beg_label_seq_id' _item_linked.parent_name '_atom_site.label_seq_id' save_ save__pdbx_sequence_range.beg_auth_asym_id _item_description.description ; A component of the identifier for the monomer at which this segment of the sequence range begins. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_pdbx_sequence_range.beg_auth_asym_id' _item.category_id pdbx_sequence_range _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_sequence_range.beg_auth_asym_id' _item_linked.parent_name '_atom_site.auth_asym_id' save_ save__pdbx_sequence_range.beg_auth_comp_id _item_description.description ; A component of the identifier for the monomer at which this segment of the sequence range begins. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_pdbx_sequence_range.beg_auth_comp_id' _item.category_id pdbx_sequence_range _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_sequence_range.beg_auth_comp_id' _item_linked.parent_name '_atom_site.auth_comp_id' save_ save__pdbx_sequence_range.beg_auth_seq_id _item_description.description ; A component of the identifier for the monomer at which this segment of the sequence range begins. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_pdbx_sequence_range.beg_auth_seq_id' _item.category_id pdbx_sequence_range _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_sequence_range.beg_auth_seq_id' _item_linked.parent_name '_atom_site.auth_seq_id' save_ save__pdbx_sequence_range.seq_range_id _item_description.description ; This data item is an identifier for a sequence range. ; _item.name '_pdbx_sequence_range.seq_range_id' _item.category_id pdbx_sequence_range _item.mandatory_code yes _item_type.code code save_ save__pdbx_sequence_range.end_label_alt_id _item_description.description ; A component of the identifier for the monomer at which this segment of the sequence range ends. This data item is a pointer to _atom_sites_alt.id in the ATOM_SITES_ALT category. ; _item.name '_pdbx_sequence_range.end_label_alt_id' _item.category_id pdbx_sequence_range _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_sequence_range.end_label_alt_id' _item_linked.parent_name '_atom_site.label_alt_id' save_ save__pdbx_sequence_range.end_label_asym_id _item_description.description ; A component of the identifier for the monomer at which this segment of the sequence range ends. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_pdbx_sequence_range.end_label_asym_id' _item.category_id pdbx_sequence_range _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_sequence_range.end_label_asym_id' _item_linked.parent_name '_atom_site.label_asym_id' save_ save__pdbx_sequence_range.end_label_comp_id _item_description.description ; A component of the identifier for the monomer at which this segment of the sequence range ends. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_pdbx_sequence_range.end_label_comp_id' _item.category_id pdbx_sequence_range _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_sequence_range.end_label_comp_id' _item_linked.parent_name '_atom_site.label_comp_id' save_ save__pdbx_sequence_range.end_label_seq_id _item_description.description ; A component of the identifier for the monomer at which this segment of the sequence range ends. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_pdbx_sequence_range.end_label_seq_id' _item.category_id pdbx_sequence_range _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_sequence_range.end_label_seq_id' _item_linked.parent_name '_atom_site.label_seq_id' save_ save__pdbx_sequence_range.end_auth_asym_id _item_description.description ; A component of the identifier for the monomer at which this segment of the sequence range ends. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_pdbx_sequence_range.end_auth_asym_id' _item.category_id pdbx_sequence_range _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_sequence_range.end_auth_asym_id' _item_linked.parent_name '_atom_site.auth_asym_id' save_ save__pdbx_sequence_range.end_auth_comp_id _item_description.description ; A component of the identifier for the monomer at which this segment of the sequence range ends. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_pdbx_sequence_range.end_auth_comp_id' _item.category_id pdbx_sequence_range _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_sequence_range.end_auth_comp_id' _item_linked.parent_name '_atom_site.auth_comp_id' save_ save__pdbx_sequence_range.end_auth_seq_id _item_description.description ; A component of the identifier for the monomer at which this segment of the sequence range ends. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_pdbx_sequence_range.end_auth_seq_id' _item.category_id pdbx_sequence_range _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_sequence_range.end_auth_seq_id' _item_linked.parent_name '_atom_site.auth_seq_id' save_ ######################## ## PDBX_FEATURE_ENTRY ## ######################## save_pdbx_feature_entry _category.description ; Data items in the PDBX_FEATURE_ENTRY category records information about properties pertaining to this structure entry. ; _category.id pdbx_feature_entry _category.mandatory_code no _category_key.name '_pdbx_feature_entry.id' loop_ _category_group.id 'inclusive_group' 'pdbx_group' 'pdbx_erf_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Gene Ontology data by entry ; ; loop_ _pdbx_feature_entry.id _pdbx_feature_entry.feature_name _pdbx_feature_entry.feature _pdbx_feature_entry.feature_type _pdbx_feature_entry.feature_assigned_by _pdbx_feature_entry.feature_citation_id 1 'molecular function' 'DNA binding activity' value GO GO 2 'biological process' 'regulation of transcription, DNA-dependent' value GO GO ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_feature_entry.id _item_description.description ; The value of _pdbx_feature_entry.id uniquely identifies a feature in the PDBX_FEATURE_ENTRY category. ; _item.name '_pdbx_feature_entry.id' _item.category_id pdbx_feature_entry _item.mandatory_code yes _item_type.code code save_ save__pdbx_feature_entry.feature_name _item_description.description ; _pdbx_feature_entry.feature_name identifies a feature by name. ; _item.name '_pdbx_feature_entry.feature_name' _item.category_id pdbx_feature_entry _item.mandatory_code yes _item_type.code text save_ save__pdbx_feature_entry.feature_type _item_description.description ; _pdbx_feature_entry.feature_type identifies the type of feature. ; _item.name '_pdbx_feature_entry.feature_type' _item.category_id pdbx_feature_entry _item.mandatory_code yes _item_type.code text loop_ _item_enumeration.value 'value' 'uri' save_ save__pdbx_feature_entry.feature _item_description.description ; The value of _pdbx_feature_entry.feature_name. ; _item.name '_pdbx_feature_entry.feature' _item.category_id pdbx_feature_entry _item.mandatory_code yes _item_type.code text save_ save__pdbx_feature_entry.feature_identifier _item_description.description ; _pdbx_feature_entry.feature_identifier is an additional identifier used to identify or accession this feature. ; _item.name '_pdbx_feature_entry.feature_identifier' _item.category_id pdbx_feature_entry _item.mandatory_code no _item_type.code text save_ save__pdbx_feature_entry.feature_assigned_by _item_description.description ; _pdbx_feature_entry.feature_assigned_by identifies the individual, organization or program that assigned the feature. ; _item.name '_pdbx_feature_entry.feature_assigned_by' _item.category_id pdbx_feature_entry _item.mandatory_code yes _item_type.code text save_ save__pdbx_feature_entry.feature_citation_id _item_description.description ; _pdbx_feature_entry.feature_citation_id is a reference to a citation in the CITATION category ; _item.name '_pdbx_feature_entry.feature_citation_id' _item.category_id pdbx_feature_entry _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_feature_entry.feature_citation_id' _item_linked.parent_name '_citation.id' save_ save__pdbx_feature_entry.feature_software_id _item_description.description ; _pdbx_feature_entry.feature_software_id is a reference to an application described in the SOFTWARE category. ; _item.name '_pdbx_feature_entry.feature_software_id' _item.category_id pdbx_feature_entry _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_feature_entry.feature_software_id' _item_linked.parent_name '_software.name' save_ ######################### ## PDBX_FEATURE_DOMAIN ## ######################### save_pdbx_feature_domain _category.description ; Data items in the PDBX_FEATURE_DOMAIN category records information about properties pertaining to this structure domain. ; _category.id pdbx_feature_domain _category.mandatory_code no _category_key.name '_pdbx_feature_domain.id' loop_ _category_group.id 'inclusive_group' 'pdbx_group' 'pdbx_erf_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - SCOP data for PDB Entry 1KIP domain d1kipa_ ; ; loop_ _pdbx_feature_domain.id _pdbx_feature_domain.domain_id _pdbx_feature_domain.feature_name _pdbx_feature_domain.feature _pdbx_feature_domain.feature_type _pdbx_feature_domain.feature_assigned_by _pdbx_feature_domain.feature_citation_id 1 'd1kipa_' class 'All beta proteins' value SCOP scop 2 'd1kipa_' fold 'Immunoglobulin-like beta-sandwich' value SCOP scop 3 'd1kipa_' superfamily 'Immunoglobulin' value SCOP scop 4 'd1kipa_' family 'V set domains (antibody variable domain-like)' value SCOP scop 5 'd1kipa_' domain 'Immunoglobulin light chain kappa variable domain' value SCOP scop 6 'd1kipa_' species 'Mouse (Mus musculus), cluster 4' value SCOP scop ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_feature_domain.id _item_description.description ; The value of _pdbx_feature_domain.id uniquely identifies a feature in the PDBX_FEATURE_DOMAIN category. ; _item.name '_pdbx_feature_domain.id' _item.category_id pdbx_feature_domain _item.mandatory_code yes _item_type.code code save_ save__pdbx_feature_domain.domain_id _item_description.description ; The value of _pdbx_feature_domain.id references a domain definition in category PDBX_DOMAIN. ; _item.name '_pdbx_feature_domain.domain_id' _item.category_id pdbx_feature_domain _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_feature_domain.domain_id' _item_linked.parent_name '_pdbx_domain.id' save_ save__pdbx_feature_domain.feature_name _item_description.description ; _pdbx_feature_domain.feature_name identifies a feature by name. ; _item.name '_pdbx_feature_domain.feature_name' _item.category_id pdbx_feature_domain _item.mandatory_code yes _item_type.code text save_ save__pdbx_feature_domain.feature_type _item_description.description ; _pdbx_feature_domain.feature_type identifies the type of feature. ; _item.name '_pdbx_feature_domain.feature_type' _item.category_id pdbx_feature_domain _item.mandatory_code yes _item_type.code text loop_ _item_enumeration.value 'value' 'uri' save_ save__pdbx_feature_domain.feature _item_description.description ; The value of _pdbx_feature_domain.feature_name. ; _item.name '_pdbx_feature_domain.feature' _item.category_id pdbx_feature_domain _item.mandatory_code yes _item_type.code text save_ save__pdbx_feature_domain.feature_identifier _item_description.description ; _pdbx_feature_domain.feature_identifier is an additional identifier used to identify or accession this feature. ; _item.name '_pdbx_feature_domain.feature_identifier' _item.category_id pdbx_feature_domain _item.mandatory_code no _item_type.code text save_ save__pdbx_feature_domain.feature_assigned_by _item_description.description ; _pdbx_feature_domain.feature_assigned_by identifies the individual, organization or program that assigned the feature. ; _item.name '_pdbx_feature_domain.feature_assigned_by' _item.category_id pdbx_feature_domain _item.mandatory_code yes _item_type.code text save_ save__pdbx_feature_domain.feature_citation_id _item_description.description ; _pdbx_feature_domain.feature_citation_id is a reference to a citation in the CITATION category. ; _item.name '_pdbx_feature_domain.feature_citation_id' _item.category_id pdbx_feature_domain _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_feature_domain.feature_citation_id' _item_linked.parent_name '_citation.id' save_ save__pdbx_feature_domain.feature_software_id _item_description.description ; _pdbx_feature_domain.feature_software_id is a reference to an application described in the SOFTWARE category. ; _item.name '_pdbx_feature_domain.feature_software_id' _item.category_id pdbx_feature_domain _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_feature_domain.feature_software_id' _item_linked.parent_name '_software.name' save_ ################################# ## PDBX_FEATURE_SEQUENCE_RANGE ## ################################# save_pdbx_feature_sequence_range _category.description ; Data items in the PDBX_FEATURE_SEQUENCE_RANGE category records information about properties pertaining to this structure sequence_range. ; _category.id pdbx_feature_sequence_range _category.mandatory_code no _category_key.name '_pdbx_feature_sequence_range.id' loop_ _category_group.id 'inclusive_group' 'pdbx_group' 'pdbx_erf_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Secondary structure computed by program DSSP. ; ; loop_ _pdbx_feature_sequence_range.id _pdbx_feature_sequence_range.seq_range_id _pdbx_feature_sequence_range.feature_name _pdbx_feature_sequence_range.feature _pdbx_feature_sequence_range.feature_type _pdbx_feature_sequence_range.feature_assigned_by _pdbx_feature_sequence_range.feature_software_id 1 H1 'secondary structure' '4-helix (alpha-helix)' value DSSP DSSP 2 T1 'secondary structure' 'hydrogen-bonded turn in beta-ladder' value DSSP DSSP ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_feature_sequence_range.id _item_description.description ; The value of _pdbx_feature_sequence_range.id uniquely identifies a feature in the PDBX_FEATURE_SEQUENCE_RANGE category ; _item.name '_pdbx_feature_sequence_range.id' _item.category_id pdbx_feature_sequence_range _item.mandatory_code yes _item_type.code code save_ save__pdbx_feature_sequence_range.seq_range_id _item_description.description ; The value of _pdbx_feature_sequence_range.seq_range_id references a sequence_range definition in category PDBX_SEQUENCE_RANGE. ; _item.name '_pdbx_feature_sequence_range.seq_range_id' _item.category_id pdbx_feature_sequence_range _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_feature_sequence_range.seq_range_id' _item_linked.parent_name '_pdbx_sequence_range.seq_range_id' save_ save__pdbx_feature_sequence_range.feature_name _item_description.description ; _pdbx_feature_sequence_range.feature_name identifies a feature by name. ; _item.name '_pdbx_feature_sequence_range.feature_name' _item.category_id pdbx_feature_sequence_range _item.mandatory_code yes _item_type.code text save_ save__pdbx_feature_sequence_range.feature_type _item_description.description ; _pdbx_feature_sequence_range.feature_type identifies the type of feature. ; _item.name '_pdbx_feature_sequence_range.feature_type' _item.category_id pdbx_feature_sequence_range _item.mandatory_code yes _item_type.code text loop_ _item_enumeration.value 'value' 'uri' save_ save__pdbx_feature_sequence_range.feature _item_description.description ; The value of _pdbx_feature_sequence_range.feature_name. ; _item.name '_pdbx_feature_sequence_range.feature' _item.category_id pdbx_feature_sequence_range _item.mandatory_code yes _item_type.code text save_ save__pdbx_feature_sequence_range.feature_identifier _item_description.description ; _pdbx_feature_sequence_range.feature_identifier is an additional identifier used to identify or accession this feature. ; _item.name '_pdbx_feature_sequence_range.feature_identifier' _item.category_id pdbx_feature_sequence_range _item.mandatory_code no _item_type.code text save_ save__pdbx_feature_sequence_range.feature_assigned_by _item_description.description ; _pdbx_feature_sequence_range.feature_assigned_by identifies the individual, organization or program that assigned the feature. ; _item.name '_pdbx_feature_sequence_range.feature_assigned_by' _item.category_id pdbx_feature_sequence_range _item.mandatory_code yes _item_type.code text save_ save__pdbx_feature_sequence_range.feature_citation_id _item_description.description ; _pdbx_feature_sequence_range.feature_citation_id is a reference to a citation in the CITATION category ; _item.name '_pdbx_feature_sequence_range.feature_citation_id' _item.category_id pdbx_feature_sequence_range _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_feature_sequence_range.feature_citation_id' _item_linked.parent_name '_citation.id' save_ save__pdbx_feature_sequence_range.feature_software_id _item_description.description ; _pdbx_feature_sequence_range.feature_software_id is a reference to an application descripted in the SOFTWARE category. ; _item.name '_pdbx_feature_sequence_range.feature_software_id' _item.category_id pdbx_feature_sequence_range _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_feature_sequence_range.feature_software_id' _item_linked.parent_name '_software.name' save_ ########################### ## PDBX_FEATURE_ASSEMBLY ## ########################### save_pdbx_feature_assembly _category.description ; Data items in the PDBX_FEATURE_ASSEMBLY category records information about properties pertaining to this structural assembly. ; _category.id pdbx_feature_assembly _category.mandatory_code no _category_key.name '_pdbx_feature_assembly.id' loop_ _category_group.id 'inclusive_group' 'pdbx_group' 'pdbx_erf_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Biological process for functional assembly ; ; loop_ _pdbx_feature_assembly.id _pdbx_feature_assembly.assembly_id _pdbx_feature_assembly.feature_name _pdbx_feature_assembly.feature _pdbx_feature_assembly.feature_type _pdbx_feature_assembly.feature_assigned_by _pdbx_feature_assembly.feature_citation_id 1 b1 'biological process' 'nitrogen metabolism' value GO GO ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_feature_assembly.id _item_description.description ; The value of _pdbx_feature_assembly.id uniquely identifies a feature in the PDBX_FEATURE_ASSEMBLY category. ; _item.name '_pdbx_feature_assembly.id' _item.category_id pdbx_feature_assembly _item.mandatory_code yes _item_type.code code save_ save__pdbx_feature_assembly.assembly_id _item_description.description ; The value of _pdbx_feature_assembly.assembly_id references an assembly definition in category STRUCT_BIOL ; _item.name '_pdbx_feature_assembly.assembly_id' _item.category_id pdbx_feature_assembly _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_feature_assembly.assembly_id' _item_linked.parent_name '_struct_biol.id' save_ save__pdbx_feature_assembly.feature_name _item_description.description ; _pdbx_feature_assembly.feature_name identifies a feature by name. ; _item.name '_pdbx_feature_assembly.feature_name' _item.category_id pdbx_feature_assembly _item.mandatory_code yes _item_type.code text save_ save__pdbx_feature_assembly.feature_type _item_description.description ; _pdbx_feature_assembly.feature_type identifies the type of feature. ; _item.name '_pdbx_feature_assembly.feature_type' _item.category_id pdbx_feature_assembly _item.mandatory_code yes _item_type.code text loop_ _item_enumeration.value 'value' 'uri' save_ save__pdbx_feature_assembly.feature _item_description.description ; The value of _pdbx_feature_assembly.feature_name. ; _item.name '_pdbx_feature_assembly.feature' _item.category_id pdbx_feature_assembly _item.mandatory_code yes _item_type.code text save_ save__pdbx_feature_assembly.feature_identifier _item_description.description ; _pdbx_feature_assembly_range.feature_identifier is an additional identifier used to identify or accession this feature. ; _item.name '_pdbx_feature_assembly.feature_identifier' _item.category_id pdbx_feature_assembly _item.mandatory_code no _item_type.code text save_ save__pdbx_feature_assembly.feature_assigned_by _item_description.description ; _pdbx_feature_assembly.feature_assigned_by identifies the individual, organization or program that assigned the feature. ; _item.name '_pdbx_feature_assembly.feature_assigned_by' _item.category_id pdbx_feature_assembly _item.mandatory_code yes _item_type.code text save_ save__pdbx_feature_assembly.feature_citation_id _item_description.description ; _pdbx_feature_assembly.feature_citation_id is a reference to a citation in the CITATION category ; _item.name '_pdbx_feature_assembly.feature_citation_id' _item.category_id pdbx_feature_assembly _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_feature_assembly.feature_citation_id' _item_linked.parent_name '_citation.id' save_ save__pdbx_feature_assembly.feature_software_id _item_description.description ; _pdbx_feature_assembly.feature_software_id is a reference to an application described in the SOFTWARE category. ; _item.name '_pdbx_feature_assembly.feature_software_id' _item.category_id pdbx_feature_assembly _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_feature_assembly.feature_software_id' _item_linked.parent_name '_software.name' save_ ########################## ## PDBX_FEATURE_MONOMER ## ########################## save_pdbx_feature_monomer _category.description ; Data items in the PDBX_FEATURE_MONOMER category records information about properties pertaining to particular monomers in this structure. ; _category.id pdbx_feature_monomer _category.mandatory_code no _category_key.name '_pdbx_feature_monomer.id' loop_ _category_group.id 'inclusive_group' 'pdbx_group' 'pdbx_erf_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; loop_ _pdbx_feature_monomer.id _pdbx_feature_monomer.label_alt_id _pdbx_feature_monomer.label_asym_id _pdbx_feature_monomer.label_comp_id _pdbx_feature_monomer.label_seq_id _pdbx_feature_monomer.feature_name _pdbx_feature_monomer.feature _pdbx_feature_monomer.feature_type _pdbx_feature_monomer.feature_assigned_by _pdbx_feature_monomer.feature_citation_id 1 . A ASP 1 'SASA' 129.4 value POPS pops 1 . A ILE 2 'SASA' 35.5 value POPS pops 1 . A VAL 3 'SASA' 87.2 value POPS pops ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__pdbx_feature_monomer.id _item_description.description ; The value of _pdbx_feature_monomer.id uniquely identifies a feature in the PDBX_FEATURE_MONOMER category. ; _item.name '_pdbx_feature_monomer.id' _item.category_id pdbx_feature_monomer _item.mandatory_code yes _item_type.code code save_ save__pdbx_feature_monomer.feature_name _item_description.description ; _pdbx_feature_monomer.feature_name identifies a feature by name. ; _item.name '_pdbx_feature_monomer.feature_name' _item.category_id pdbx_feature_monomer _item.mandatory_code yes _item_type.code text save_ save__pdbx_feature_monomer.feature_type _item_description.description ; _pdbx_feature_monomer.feature_type identifies the type of feature. ; _item.name '_pdbx_feature_monomer.feature_type' _item.category_id pdbx_feature_monomer _item.mandatory_code yes _item_type.code text loop_ _item_enumeration.value 'value' 'uri' save_ save__pdbx_feature_monomer.feature _item_description.description ; The value of _pdbx_feature_monomer.feature_name. ; _item.name '_pdbx_feature_monomer.feature' _item.category_id pdbx_feature_monomer _item.mandatory_code yes _item_type.code text save_ save__pdbx_feature_monomer.feature_identifier _item_description.description ; _pdbx_feature_monomer.feature_identifier is an additional identifier used to identify or accession this feature. ; _item.name '_pdbx_feature_monomer.feature_identifier' _item.category_id pdbx_feature_monomer _item.mandatory_code no _item_type.code text save_ save__pdbx_feature_monomer.feature_assigned_by _item_description.description ; _pdbx_feature_monomer.feature_assigned_by identifies the individual, organization or program that assigned the feature. ; _item.name '_pdbx_feature_monomer.feature_assigned_by' _item.category_id pdbx_feature_monomer _item.mandatory_code yes _item_type.code text save_ save__pdbx_feature_monomer.feature_citation_id _item_description.description ; _pdbx_feature_monomer.feature_citation_id is a reference to a citation in the CITATION category. ; _item.name '_pdbx_feature_monomer.feature_citation_id' _item.category_id pdbx_feature_monomer _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_feature_monomer.feature_citation_id' _item_linked.parent_name '_citation.id' save_ save__pdbx_feature_monomer.feature_software_id _item_description.description ; _pdbx_feature_monomer.feature_software_id is a reference to an application described in the SOFTWARE category. ; _item.name '_pdbx_feature_monomer.feature_software_id' _item.category_id pdbx_feature_monomer _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_feature_monomer.feature_software_id' _item_linked.parent_name '_software.name' save_ ## save__pdbx_feature_monomer.label_alt_id _item_description.description ; A component of the identifier for the monomer. This data item is a pointer to _atom_sites_alt.id in the ATOM_SITES_ALT category. ; _item.name '_pdbx_feature_monomer.label_alt_id' _item.category_id pdbx_sequence_range _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_feature_monomer.label_alt_id' _item_linked.parent_name '_atom_site.label_alt_id' save_ save__pdbx_feature_monomer.label_asym_id _item_description.description ; A component of the identifier for the monomer. This data item is a pointer to _atom_site.label_asym_id in the ATOM_SITE category. ; _item.name '_pdbx_feature_monomer.label_asym_id' _item.category_id pdbx_sequence_range _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_feature_monomer.label_asym_id' _item_linked.parent_name '_atom_site.label_asym_id' save_ save__pdbx_feature_monomer.label_comp_id _item_description.description ; A component of the identifier for the monomer. This data item is a pointer to _atom_site.label_comp_id in the ATOM_SITE category. ; _item.name '_pdbx_feature_monomer.label_comp_id' _item.category_id pdbx_sequence_range _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_feature_monomer.label_comp_id' _item_linked.parent_name '_atom_site.label_comp_id' save_ save__pdbx_feature_monomer.label_seq_id _item_description.description ; A component of the identifier for the monomer. This data item is a pointer to _atom_site.label_seq_id in the ATOM_SITE category. ; _item.name '_pdbx_feature_monomer.label_seq_id' _item.category_id pdbx_sequence_range _item.mandatory_code yes _item_type.code int _item_linked.child_name '_pdbx_feature_monomer.label_seq_id' _item_linked.parent_name '_atom_site.label_seq_id' save_ save__pdbx_feature_monomer.auth_asym_id _item_description.description ; A component of the identifier for the monomer. This data item is a pointer to _atom_site.auth_asym_id in the ATOM_SITE category. ; _item.name '_pdbx_feature_monomer.auth_asym_id' _item.category_id pdbx_sequence_range _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_feature_monomer.auth_asym_id' _item_linked.parent_name '_atom_site.auth_asym_id' save_ save__pdbx_feature_monomer.auth_comp_id _item_description.description ; A component of the identifier for the monomer. This data item is a pointer to _atom_site.auth_comp_id in the ATOM_SITE category. ; _item.name '_pdbx_feature_monomer.auth_comp_id' _item.category_id pdbx_sequence_range _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_feature_monomer.auth_comp_id' _item_linked.parent_name '_atom_site.auth_comp_id' save_ save__pdbx_feature_monomer.auth_seq_id _item_description.description ; A component of the identifier for the monomer. This data item is a pointer to _atom_site.auth_seq_id in the ATOM_SITE category. ; _item.name '_pdbx_feature_monomer.auth_seq_id' _item.category_id pdbx_sequence_range _item.mandatory_code no _item_type.code code _item_linked.child_name '_pdbx_feature_monomer.auth_seq_id' _item_linked.parent_name '_atom_site.auth_seq_id' save_ ## ## End of file: mmcif_pdbx-def-9.dic ## ########################################################################### # # File: mmcif_pdbx-def-10.dic # # PDB Exchange Data Dictionary # # This data dictionary contains preliminary extensions for describing # macromolecular powder diffraction experiments. # # Definition Section 10 # # ########################################################################### save__diffrn_radiation.pdbx_analyzer _item_description.description ; Indicates the method used to obtain monochromatic radiation. _diffrn_radiation.monochromator describes the primary beam monochromator (pre-specimen monochromation). _diffrn_radiation.pdbx_analyzer specifies the post-diffraction analyser (post-specimen) monochromation. Note that monochromators may have either 'parallel' or 'antiparallel' orientation. It is assumed that the geometry is parallel unless specified otherwise. In a parallel geometry, the position of the monochromator allows the incident beam and the final post-specimen and post-monochromator beam to be as close to parallel as possible. In a parallel geometry, the diffracting planes in the specimen and monochromator will be parallel when 2*theta(monochromator) is equal to 2*theta (specimen). For further discussion see R. Jenkins and R. Snyder, Introduction to X-ray Powder Diffraction, Wiley (1996), pp. 164-5. ; _item.name '_diffrn_radiation.pdbx_analyzer' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'GE(111)' 'Zr filter' 'Ge 220' 'none' 'equatorial mounted graphite (0001)' 'Si (111), antiparallel' _item_aliases.dictionary cif_pd.dic _item_aliases.version 1.0 _item_aliases.alias_name '_pd_instr_monochr_post_spec' save_ save_pdbx_exptl_pd _category.description ; Data items in the pdbx_exptl_pd record information about powder sample preparations. ; _category.id pdbx_exptl_pd _category.mandatory_code no _category_key.name '_pdbx_exptl_pd.entry_id' loop_ _category_group.id 'inclusive_group' 'pdbx_group' save_ save__pdbx_exptl_pd.entry_id _item_description.description ; The value of _pdbx_exptl_pd.entry_id uniquely identifies a record in the PDBX_EXPTL_PD category. ; _item.name '_pdbx_exptl_pd.entry_id' _item.category_id pdbx_exptl_pd _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_exptl_pd.entry_id' _item_linked.parent_name '_entry.id' save_ save__pdbx_exptl_pd.spec_preparation_pH _item_description.description ; The pH at which the powder sample was prepared. ; _item.name '_pdbx_exptl_pd.spec_preparation_pH' _item.category_id pdbx_exptl_pd _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__pdbx_exptl_pd.spec_preparation_pH_range _item_description.description ; The range of pH values at which the sample was prepared. Used when a point estimate of pH is not appropriate. ; _item.name '_pdbx_exptl_pd.spec_preparation_pH_range' _item.category_id pdbx_exptl_pd _item.mandatory_code no _item_type.code line loop_ _item_examples.case '5.6 - 6.4' save_ save__pdbx_exptl_pd.spec_preparation _item_description.description ; A description of preparation steps for producing the diffraction specimen from the sample. Include any procedures related to grinding, sieving, spray drying, etc. ; _item.name '_pdbx_exptl_pd.spec_preparation' _item.category_id pdbx_exptl_pd _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'POLYCRYSTAL SLURRY' 'wet grinding in acetone' 'sieved through a 44 micron (325 mesh/inch) sieve' 'spray dried in water with 1% clay' _item_aliases.dictionary cif_pd.dic _item_aliases.version 1.0 _item_aliases.alias_name '_pd_spec_preparation' save_ save__refine.pdbx_pd_number_of_powder_patterns _item_description.description ; The total number of powder patterns used. ; _item.name '_refine.pdbx_pd_number_of_powder_patterns' _item.category_id refine _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ save__refine.pdbx_pd_number_of_points _item_description.description ; The total number of data points in the processed diffractogram. ; _item.name '_refine.pdbx_pd_number_of_points' _item.category_id refine _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int _item_aliases.dictionary cif_pd.dic _item_aliases.version 1.0 _item_aliases.alias_name '_pd_proc_number_of_points' save_ save__refine.pdbx_pd_meas_number_of_points _item_description.description ; The total number of points in the measured diffractogram. ; _item.name '_refine.pdbx_pd_meas_number_of_points' _item.category_id refine _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int _item_aliases.dictionary cif_pd.dic _item_aliases.version 1.0 _item_aliases.alias_name '_pd_meas_number_of_points' save_ save__refine.pdbx_pd_proc_ls_prof_R_factor _item_description.description ; Rietveld/Profile fit R factors. Note that the R factor computed for Rietveld refinements using the extracted reflection intensity values (often called the Rietveld or Bragg R factor, R~B~) is not properly a profile R factor. pdbx_pd_proc_ls_prof_R_factor, often called R~p~, is an unweighted fitness metric for the agreement between the observed and computed diffraction patterns R~p~ = sum~i~ | I~obs~(i) - I~calc~(i) | / sum~i~ ( I~obs~(i) ) Note that in the above equations, w(i) is the weight for the ith data point I~obs~(i) is the observed intensity for the ith data point, sometimes referred to as y~i~(obs) or y~oi~. I~calc~(i) is the computed intensity for the ith data point with background and other corrections applied to match the scale of the observed dataset, sometimes referred to as y~i~(calc) or y~ci~. n is the total number of data points (see _refine.pdbx_pd_number_of_points) less the number of data points excluded from the refinement. p is the total number of refined parameters. ; _item.name '_refine.pdbx_pd_proc_ls_prof_R_factor' _item.category_id refine _item.mandatory_code no _item_type.code float _item_aliases.dictionary cif_pd.dic _item_aliases.version 1.0 _item_aliases.alias_name '_pd_proc_ls_prof_R_factor' save_ save__refine.pdbx_pd_proc_ls_prof_wR_factor _item_description.description ; Rietveld/Profile fit R factors. Note that the R factor computed for Rietveld refinements using the extracted reflection intensity values (often called the Rietveld or Bragg R factor, R~B~) is not properly a profile R factor. pdbx_pd_proc_ls_prof_wR_factor often called R~wp~, is a weighted fitness metric for the agreement between the observed and computed diffraction patterns R~wp~ = SQRT { sum~i~ ( w(i) [ I~obs~(i) - I~calc~(i) ]^2^ ) / sum~i~ ( w(i) [I~obs~(i)]^2^ ) } Note that in the above equations, w(i) is the weight for the ith data point I~obs~(i) is the observed intensity for the ith data point, sometimes referred to as y~i~(obs) or y~oi~. I~calc~(i) is the computed intensity for the ith data point with background and other corrections applied to match the scale of the observed dataset, sometimes referred to as y~i~(calc) or y~ci~. n is the total number of data points (see _refine.pdbx_pd_number_of_points) less the number of data points excluded from the refinement. p is the total number of refined parameters. ; _item.name '_refine.pdbx_pd_proc_ls_prof_wR_factor' _item.category_id refine _item.mandatory_code no _item_type.code float _item_aliases.dictionary cif_pd.dic _item_aliases.version 1.0 _item_aliases.alias_name '_pd_proc_ls_prof_wR_factor' save_ save__refine.pdbx_pd_Marquardt_correlation_coeff _item_description.description ; The correlation coefficient between the observed and calculated structure factors for reflections included in the refinement. This correlation factor is found in the fitting using the Levenberg-Marquardt algorithm to search for the minimum value of chisquare. Almost all computer codes for Rietveld refinement employ the Gauss-Newton algorithm to find parameters which minimize the weighted sum of squares of the residuals. A description of the equations is given on http://www.water.hut.fi/~tkarvone/fr_org_s.htm ; _item.name '_refine.pdbx_pd_Marquardt_correlation_coeff' _item.category_id refine _item.mandatory_code no _item_type.code float save_ save__refine.pdbx_pd_Fsqrd_R_factor _item_description.description ; Residual factor R for reflections that satisfy the resolution limits established by _refine.ls_d_res_high and _refine.ls_d_res_low and the observation limit established by _reflns.observed_criterion. sum|F~obs~**2 - F~calc~**2| R = --------------------- sum|F~obs~**2| F~obs~ = the observed structure-factor amplitudes F~calc~ = the calculated structure-factor amplitudes sum is taken over the specified reflections ; _item.name '_refine.pdbx_pd_Fsqrd_R_factor' _item.category_id refine _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 _item_type.code float save_ save__refine.pdbx_pd_ls_matrix_band_width _item_description.description ; The least squares refinement "band matrix" approximation to the full matrix. ; _item.name '_refine.pdbx_pd_ls_matrix_band_width' _item.category_id refine _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0 0 0 _item_type.code int save_ ### EOF mmcif_pdbx-def-10.dic ####################### ## PDBX_SOLN_SCATTER ## ####################### save_pdbx_soln_scatter _category.description ; Data items in the PDBX_SOLN_SCATTER category record details about a solution scattering experiment ; _category.id pdbx_soln_scatter _category.mandatory_code no loop_ _category_key.name '_pdbx_soln_scatter.entry_id' '_pdbx_soln_scatter.id' loop_ _category_group.id 'inclusive_group' 'solution_scattering_group' loop_ _category_examples.detail _category_examples.case ; Example 1 - based on PDB entry 1HAQ ; ; loop_ _pdbx_soln_scatter.entry_id _pdbx_soln_scatter.id _pdbx_soln_scatter.type _pdbx_soln_scatter.source_type _pdbx_soln_scatter.source_class _pdbx_soln_scatter.source_beamline _pdbx_soln_scatter.source_beamline_instrument _pdbx_soln_scatter.detector_specific _pdbx_soln_scatter.detector_type _pdbx_soln_scatter.temperature _pdbx_soln_scatter.pH _pdbx_soln_scatter.num_time_frames _pdbx_soln_scatter.concentration_range _pdbx_soln_scatter.buffer_name _pdbx_soln_scatter.mean_guiner_radius _pdbx_soln_scatter.mean_guiner_radius_esd _pdbx_soln_scatter.min_mean_cross_sectional_radii_gyration _pdbx_soln_scatter.min_mean_cross_sectional_radii_gyration_esd _pdbx_soln_scatter.max_mean_cross_sectional_radii_gyration _pdbx_soln_scatter.max_mean_cross_sectional_radii_gyration_eds _pdbx_soln_scatter.protein_length 1HAQ 1 x-ray 'SRS BEAMLINE 2.1' 'synchrotron' '2.1' . . '500-channel quadrant' 288 . 10 '0.7 - 14' tris 11.1 0.4 4.4 0.2 1.7 0.1 40 1HAQ 2 neutron 'ILL' 'neutron source' . 'D11, D22' . 'area' . . . '0.4 - 9.6' 'PBS in 99.9% D2O' 11.3 0.4 3.9 0.2 1.51 0.06 '37.0 - 39.0' 1HAQ 3 neutron 'ISIS' 'neutron source' 'Pulsed Neutron' 'LOQ' . 'AREA (TIME-OF-FLIGHT)' . . . '3.7, 6.1' 'PBS in 99.9% D2O' 11.7 0.5 . . . . 40.0 ; save_ save__pdbx_soln_scatter.entry_id _item_description.description ; This data item is a pointer to _entry.id in the ENTRY category. ; _item.name '_pdbx_soln_scatter.entry_id' _item.category_id pdbx_soln_scatter _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_soln_scatter.entry_id' _item_linked.parent_name '_entry.id' save_ save__pdbx_soln_scatter.id _item_description.description ; The value of _pdbx_soln_scatter.id must uniquely identify the sample in the category PDBX_SOLN_SCATTER ; _item.name '_pdbx_soln_scatter.id' _item.category_id pdbx_soln_scatter _item.mandatory_code yes _item_type.code code save_ save__pdbx_soln_scatter.type _item_description.description ; The type of solution scattering experiment carried out ; _item.name '_pdbx_soln_scatter.type' _item.category_id pdbx_soln_scatter _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value 'x-ray' 'neutron' 'modelling' save_ save__pdbx_soln_scatter.source_beamline _item_description.description ; The beamline name used for the experiment ; _item.name '_pdbx_soln_scatter.source_beamline' _item.category_id pdbx_soln_scatter _item.mandatory_code no _item_type.code text save_ save__pdbx_soln_scatter.source_beamline_instrument _item_description.description ; The instrumentation used on the beamline ; _item.name '_pdbx_soln_scatter.source_beamline_instrument' _item.category_id pdbx_soln_scatter _item.mandatory_code no _item_type.code text save_ save__pdbx_soln_scatter.detector_type _item_description.description ; The general class of the radiation detector. ; _item.name '_pdbx_soln_scatter.detector_type' _item.category_id pdbx_soln_scatter _item.mandatory_code no _item_type.code text save_ save__pdbx_soln_scatter.detector_specific _item_description.description ; The particular radiation detector. In general this will be a manufacturer, description, model number or some combination of these. ; _item.name '_pdbx_soln_scatter.detector_specific' _item.category_id pdbx_soln_scatter _item.mandatory_code no _item_type.code text save_ save__pdbx_soln_scatter.source_type _item_description.description ; The make, model, name or beamline of the source of radiation. ; _item.name '_pdbx_soln_scatter.source_type' _item.category_id pdbx_soln_scatter _item.mandatory_code no _item_type.code text save_ save__pdbx_soln_scatter.source_class _item_description.description ; The general class of the radiation source. ; _item.name '_pdbx_soln_scatter.source_class' _item.category_id pdbx_soln_scatter _item.mandatory_code no _item_type.code text loop_ _item_examples.case 'neutron source' 'synchrotron' save_ save__pdbx_soln_scatter.num_time_frames _item_description.description ; The number of time frame solution scattering images used. ; _item.name '_pdbx_soln_scatter.num_time_frames' _item.category_id pdbx_soln_scatter _item.mandatory_code no _item_type.code int save_ save__pdbx_soln_scatter.sample_pH _item_description.description ; The pH value of the buffered sample. ; _item.name '_pdbx_soln_scatter.sample_pH' _item.category_id pdbx_soln_scatter _item.mandatory_code no _item_type.code float save_ save__pdbx_soln_scatter.temperature _item_description.description ; The temperature in kelvins at which the experiment was conducted ; _item.name '_pdbx_soln_scatter.temperature' _item.category_id pdbx_soln_scatter _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code kelvins save_ save__pdbx_soln_scatter.concentration_range _item_description.description ; The concentration range (mg/mL) of the complex in the sample used in the solution scattering experiment to determine the mean radius of structural elongation. ; _item.name '_pdbx_soln_scatter.concentration_range' _item.category_id pdbx_soln_scatter _item.mandatory_code no _item_type.code line _item_units.code mg_per_ml _item_examples.case '0.7 - 14' save_ save__pdbx_soln_scatter.buffer_name _item_description.description ; The name of the buffer used for the sample in the solution scattering experiment. ; _item.name '_pdbx_soln_scatter.buffer_name' _item.category_id pdbx_soln_scatter _item.mandatory_code no _item_type.code line _item_examples.case 'acetic acid' save_ save__pdbx_soln_scatter.mean_guiner_radius _item_description.description ; The mean radius of structural elongation of the sample. In a given solute-solvent contrast, the radius of gyration R_G is a measure of structural elongation if the internal inhomogeneity of scattering densities has no effect. Guiner analysis at low Q gives the R_G and the forward scattering at zero angle I(0). lnl(Q) = lnl(0) - R_G^2Q^2/3 where Q = 4(pi)sin(theta/lamda) 2theta = scattering angle lamda = wavelength The above expression is valid in a QR_G range for extended rod-like particles. The relative I(0)/c values ( where c = sample concentration) for sample measurements in a constant buffer for a single sample data session, gives the relative masses of the protein(s) studied when referenced against a standard. see: O.Glatter & O.Kratky, (1982). Editors of "Small angle X-ray Scattering, Academic Press, New York. O.Kratky. (1963). X-ray small angle scattering with substances of biological interest in diluted solutions. Prog. Biophys. Chem., 13, 105-173. G.D.Wignall & F.S.Bates, (1987). The small-angle approximation of X-ray and neutron scatter from rigid rods of non-uniform cross section and finite length. J.Appl. Crystallog., 18, 452-460. If the structure is elongated, the mean radius of gyration of the cross-sectional structure R_XS and the mean cross sectional intensity at zero angle [I(Q).Q]_Q->0 is obtained from ln[I(Q).Q] = ln[l(Q).(Q)]_Q->0 - ((R_XS)^2Q^2)/2 ; _item.name '_pdbx_soln_scatter.mean_guiner_radius' _item.category_id pdbx_soln_scatter _item.mandatory_code no _item_units.code nanometres _item_type.code float _item_related.related_name '_pdbx_soln_scatter.mean_guiner_radius_esd' _item_related.function_code associated_esd save_ save__pdbx_soln_scatter.mean_guiner_radius_esd _item_description.description ; The estimated standard deviation for the mean radius of structural elongation of the sample. In a given solute-solvent contrast, the radius of gyration R_G is a measure of structural elongation if the internal inhomogeneity of scattering densities has no effect. Guiner analysis at low Q give the R_G and the forward scattering at zero angle I(0). lnl(Q) = lnl(0) - R_G^2Q^2/3 where Q = 4(pi)sin(theta/lamda) 2theta = scattering angle lamda = wavelength The above expression is valid in a QR_G range for extended rod-like particles. The relative I(0)/c values ( where c = sample concentration) for sample measurements in a constant buffer for a single sample data session, gives the relative masses of the protein(s) studied when referenced against a standard. see: O.Glatter & O.Kratky, (1982). Editors of "Small angle X-ray Scattering, Academic Press, New York. O.Kratky. (1963). X-ray small angle scattering with substances of biological interest in diluted solutions. Prog. Biophys. Chem., 13, 105-173. G.D.Wignall & F.S.Bates, (1987). The small-angle approximation of X-ray and neutron scatter from rigid rods of non-uniform cross section and finite length. J.Appl. Crystallog., 18, 452-460. If the structure is elongated, the mean radius of gyration of the cross-sectional structure R_XS and the mean cross sectional intensity at zero angle [I(Q).Q]_Q->0 is obtained from ln[I(Q).Q] = ln[l(Q).(Q)]_Q->0 - ((R_XS)^2Q^2)/2 ; _item.name '_pdbx_soln_scatter.mean_guiner_radius_esd' _item.category_id pdbx_soln_scatter _item.mandatory_code no _item_type.code float _item_units.code nanometres _item_related.related_name '_pdbx_soln_scatter.mean_guiner_radius' _item_related.function_code associated_value save_ save__pdbx_soln_scatter.min_mean_cross_sectional_radii_gyration _item_description.description ; The minimum mean radius of structural elongation of the sample. In a given solute-solvent contrast, the radius of gyration R_G is a measure of structural elongation if the internal inhomogeneity of scattering densities has no effect. Guiner analysis at low Q give the R_G and the forward scattering at zero angle I(0). lnl(Q) = lnl(0) - R_G^2Q^2/3 where Q = 4(pi)sin(theta/lamda) 2theta = scattering angle lamda = wavelength The above expression is valid in a QR_G range for extended rod-like particles. The relative I(0)/c values ( where c = sample concentration) for sample measurements in a constant buffer for a single sample data session, gives the relative masses of the protein(s) studied when referenced against a standard. see: O.Glatter & O.Kratky, (1982). Editors of "Small angle X-ray Scattering, Academic Press, New York. O.Kratky. (1963). X-ray small angle scattering with substances of biological interest in diluted solutions. Prog. Biophys. Chem., 13, 105-173. G.D.Wignall & F.S.Bates, (1987). The small-angle approximation of X-ray and neutron scatter from rigid rods of non-uniform cross section and finite length. J.Appl. Crystallog., 18, 452-460. If the structure is elongated, the mean radius of gyration of the cross-sectional structure R_XS and the mean cross sectional intensity at zero angle [I(Q).Q]_Q->0 is obtained from ln[I(Q).Q] = ln[l(Q).(Q)]_Q->0 - ((R_XS)^2Q^2)/2 ; _item.name '_pdbx_soln_scatter.min_mean_cross_sectional_radii_gyration' _item.category_id pdbx_soln_scatter _item.mandatory_code no _item_type.code float _item_units.code nanometres _item_related.related_name '_pdbx_soln_scatter.min_mean_cross_sectional_radii_gyration_esd' _item_related.function_code associated_esd save_ save__pdbx_soln_scatter.min_mean_cross_sectional_radii_gyration_esd _item_description.description ; The estimated standard deviation for the minimum mean radius of structural elongation of the sample. In a given solute-solvent contrast, the radius of gyration R_G is a measure of structural elongation if the internal inhomogeneity of scattering densities has no effect. Guiner analysis at low Q give the R_G and the forward scattering at zero angle I(0). lnl(Q) = lnl(0) - R_G^2Q^2/3 where Q = 4(pi)sin(theta/lamda) 2theta = scattering angle lamda = wavelength The above expression is valid in a QR_G range for extended rod-like particles. The relative I(0)/c values ( where c = sample concentration) for sample measurements in a constant buffer for a single sample data session, gives the relative masses of the protein(s) studied when referenced against a standard. see: O.Glatter & O.Kratky, (1982). Editors of "Small angle X-ray Scattering, Academic Press, New York. O.Kratky. (1963). X-ray small angle scattering with substances of biological interest in diluted solutions. Prog. Biophys. Chem., 13, 105-173. G.D.Wignall & F.S.Bates, (1987). The small-angle approximation of X-ray and neutron scatter from rigid rods of non-uniform cross section and finite length. J.Appl. Crystallog., 18, 452-460. If the structure is elongated, the mean radius of gyration of the cross-sectional structure R_XS and the mean cross sectional intensity at zero angle [I(Q).Q]_Q->0 is obtained from ln[I(Q).Q] = ln[l(Q).(Q)]_Q->0 - ((R_XS)^2Q^2)/2 ; _item.name '_pdbx_soln_scatter.min_mean_cross_sectional_radii_gyration_esd' _item.category_id pdbx_soln_scatter _item.mandatory_code no _item_type.code float _item_units.code nanometres _item_related.related_name '_pdbx_soln_scatter.min_mean_cross_sectional_radii_gyration' _item_related.function_code associated_value save_ save__pdbx_soln_scatter.max_mean_cross_sectional_radii_gyration _item_description.description ; The maximum mean radius of structural elongation of the sample. In a given solute-solvent contrast, the radius of gyration R_G is a measure of structural elongation if the internal inhomogeneity of scattering densities has no effect. Guiner analysis at low Q give the R_G and the forward scattering at zero angle I(0). lnl(Q) = lnl(0) - R_G^2Q^2/3 where Q = 4(pi)sin(theta/lamda) 2theta = scattering angle lamda = wavelength The above expression is valid in a QR_G range for extended rod-like particles. The relative I(0)/c values ( where c = sample concentration) for sample measurements in a constant buffer for a single sample data session, gives the relative masses of the protein(s) studied when referenced against a standard. see: O.Glatter & O.Kratky, (1982). Editors of "Small angle X-ray Scattering, Academic Press, New York. O.Kratky. (1963). X-ray small angle scattering with substances of biological interest in diluted solutions. Prog. Biophys. Chem., 13, 105-173. G.D.Wignall & F.S.Bates, (1987). The small-angle approximation of X-ray and neutron scatter from rigid rods of non-uniform cross section and finite length. J.Appl. Crystallog., 18, 452-460. If the structure is elongated, the mean radius of gyration of the cross-sectional structure R_XS and the mean cross sectional intensity at zero angle [I(Q).Q]_Q->0 is obtained from ln[I(Q).Q] = ln[l(Q).(Q)]_Q->0 - ((R_XS)^2Q^2)/2 ; _item.name '_pdbx_soln_scatter.max_mean_cross_sectional_radii_gyration' _item.category_id pdbx_soln_scatter _item.mandatory_code no _item_type.code float _item_units.code nanometres _item_related.related_name '_pdbx_soln_scatter.max_mean_cross_sectional_radii_gyration_esd' _item_related.function_code associated_esd save_ save__pdbx_soln_scatter.max_mean_cross_sectional_radii_gyration_esd _item_description.description ; The estimated standard deviation for the minimum mean radius of structural elongation of the sample. In a given solute-solvent contrast, the radius of gyration R_G is a measure of structural elongation if the internal inhomogeneity of scattering densities has no effect. Guiner analysis at low Q give the R_G and the forward scattering at zero angle I(0). lnl(Q) = lnl(0) - R_G^2Q^2/3 where Q = 4(pi)sin(theta/lamda) 2theta = scattering angle lamda = wavelength The above expression is valid in a QR_G range for extended rod-like particles. The relative I(0)/c values ( where c = sample concentration) for sample measurements in a constant buffer for a single sample data session, gives the relative masses of the protein(s) studied when referenced against a standard. see: O.Glatter & O.Kratky, (1982). Editors of "Small angle X-ray Scattering, Academic Press, New York. O.Kratky. (1963). X-ray small angle scattering with substances of biological interest in diluted solutions. Prog. Biophys. Chem., 13, 105-173. G.D.Wignall & F.S.Bates, (1987). The small-angle approximation of X-ray and neutron scatter from rigid rods of non-uniform cross section and finite length. J.Appl. Crystallog., 18, 452-460. If the structure is elongated, the mean radius of gyration of the cross-sectional structure R_XS and the mean cross sectional intensity at zero angle [I(Q).Q]_Q->0 is obtained from ln[I(Q).Q] = ln[l(Q).(Q)]_Q->0 - ((R_XS)^2Q^2)/2 ; _item.name '_pdbx_soln_scatter.max_mean_cross_sectional_radii_gyration_esd' _item.category_id pdbx_soln_scatter _item.mandatory_code no _item_type.code float _item_units.code nanometres _item_related.related_name '_pdbx_soln_scatter.max_mean_cross_sectional_radii_gyration' _item_related.function_code associated_value save_ save__pdbx_soln_scatter.protein_length _item_description.description ; The length (or range) of the protein sample under study. If the solution structure is approximated as an elongated elliptical cyclinder the the length L is determined from, L = sqrt [12( (R_G)^2 - (R_XS)^2 ) ] The length should also be given by L = pi I(0) / [ I(Q).Q]_Q->0 ; _item.name '_pdbx_soln_scatter.protein_length' _item.category_id pdbx_soln_scatter _item.mandatory_code no _item_type.code line save_ save__pdbx_soln_scatter.data_reduction_software_list _item_description.description ; A list of the software used in the data reduction ; _item.name '_pdbx_soln_scatter.data_reduction_software_list' _item.category_id pdbx_soln_scatter _item.mandatory_code no _item_type.code text _item_examples.case 'OTOKO' save_ save__pdbx_soln_scatter.data_analysis_software_list _item_description.description ; A list of the software used in the data analysis ; _item.name '_pdbx_soln_scatter.data_analysis_software_list' _item.category_id pdbx_soln_scatter _item.mandatory_code no _item_type.code text _item_examples.case 'SCTPL5 GNOM' save_ ############################# ## PDBX_SOLN_SCATTER_MODEL ## ############################# save_pdbx_soln_scatter_model _category.description ; Data items in the PDBX_SOLN_SCATTER_MODEL category record details about the homology model fitting to the solution scatter data. ; _category.id pdbx_soln_scatter_model _category.mandatory_code no loop_ _category_key.name '_pdbx_soln_scatter_model.id' '_pdbx_soln_scatter_model.scatter_id' loop_ _category_group.id 'inclusive_group' 'solution_scattering_group' save_ save__pdbx_soln_scatter_model.scatter_id _item_description.description ; This data item is a pointer to _pdbx_soln_scatter.id in the PDBX_SOLN_SCATTER category. ; _item.name '_pdbx_soln_scatter_model.scatter_id' _item.category_id pdbx_soln_scatter_model _item.mandatory_code yes _item_type.code code _item_linked.child_name '_pdbx_soln_scatter_model.scatter_id' _item_linked.parent_name '_pdbx_soln_scatter.id' save_ save__pdbx_soln_scatter_model.id _item_description.description ; The value of _pdbx_soln_scatter_model.id must uniquely identify the sample in the category PDBX_SOLN_SCATTER_MODEL ; _item.name '_pdbx_soln_scatter_model.id' _item.category_id pdbx_soln_scatter_model _item.mandatory_code yes _item_type.code code save_ save__pdbx_soln_scatter_model.details _item_description.description ; A description of any additional details concerning the experiment. ; _item.name '_pdbx_soln_scatter_model.details' _item.category_id pdbx_soln_scatter_model _item.mandatory_code no _item_type.code text _item_examples.case ; Homology models were built for the 17 SCR domains and energy minimisations were performed to improve the connectivity in the fh model. triantennary complex-type carbohydrate structures (MAN3GLCNAC6GAL3FUC3NEUNAC1) were added to each of the N-linked glycosylation sites. a library of linker peptide conformations was used in domain modelling constrained by the solution scattering fits. modelling with the scattering data was also carried out by rotational search methods. the x-ray and neutron scattering curve I(Q) was calculated assuming a uniform scattering density for the spheres using the debye equation as adapted to spheres. x-ray curves were calculated from the hydrated sphere models without corrections for wavelength spread or beam divergence, while these corrections were applied for the neutron curves but now using unhydrated models. ; save_ save__pdbx_soln_scatter_model.method _item_description.description ; A description of the methods used in the modelling ; _item.name '_pdbx_soln_scatter_model.method' _item.category_id pdbx_soln_scatter_model _item.mandatory_code no _item_type.code text _item_examples.case ; Constrained scattering fitting of homology models ; save_ save__pdbx_soln_scatter_model.software_list _item_description.description ; A list of the software used in the modeeling ; _item.name '_pdbx_soln_scatter_model.software_list' _item.category_id pdbx_soln_scatter_model _item.mandatory_code no _item_type.code text _item_examples.case ; INSIGHT II, HOMOLOGY, DISCOVERY, BIOPOLYMER, DELPHI ; save_ save__pdbx_soln_scatter_model.software_author_list _item_description.description ; A list of the software authors ; _item.name '_pdbx_soln_scatter_model.software_author_list' _item.category_id pdbx_soln_scatter_model _item.mandatory_code no _item_type.code text _item_examples.case ; MSI ; save_ save__pdbx_soln_scatter_model.entry_fitting_list _item_description.description ; A list of the entries used to fit the model to the scattering data ; _item.name '_pdbx_soln_scatter_model.entry_fitting_list' _item.category_id pdbx_soln_scatter_model _item.mandatory_code no _item_type.code text _item_examples.case ; PDB CODE 1HFI, 1HCC, 1HFH, 1VCC ; save_ save__pdbx_soln_scatter_model.num_conformers_calculated _item_description.description ; The number of model conformers calculated. ; _item.name '_pdbx_soln_scatter_model.num_conformers_calculated' _item.category_id pdbx_soln_scatter_model _item.mandatory_code no _item_type.code int save_ save__pdbx_soln_scatter_model.num_conformers_submitted _item_description.description ; The number of model conformers submitted in the entry ; _item.name '_pdbx_soln_scatter_model.num_conformers_submitted' _item.category_id pdbx_soln_scatter_model _item.mandatory_code no _item_type.code int save_ save__pdbx_soln_scatter_model.conformer_selection_criteria _item_description.description ; A description of the conformer selection criteria used. ; _item.name '_pdbx_soln_scatter_model.conformer_selection_criteria' _item.category_id pdbx_soln_scatter_model _item.mandatory_code no _item_type.code text _item_examples.case ; The modelled scattering curves were assessed by calculation of the RG, RSX-1 and RXS-2 values in the same Q ranges used in the experimental Guinier fits. models were then ranked using a goodness-of-fit R-factor defined by analogy with protein crystallography and based on the experimental curves in the Q range extending to 1.4 nm-1. ; save_ ## ## ./CBFlib-0.9.2.2/doc/Idiffrn_radiation.polarizn_source_norm.html0000644000076500007650000000727311603702115023125 0ustar yayayaya (IUCr) CIF Definition save__diffrn_radiation.polarizn_source_norm

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_radiation.polarizn_source_norm

Name:
'_diffrn_radiation.polarizn_source_norm'

Definition:

        The angle in degrees, as viewed from the specimen, between
               the normal to the polarization plane and the laboratory Y
               axis as defined in the AXIS category.

               Note that this is the angle of polarization of the source
               photons, either directly from a synchrotron beamline or
               from a monochromater.

               This differs from the value of
               _diffrn_radiation.polarisn_norm
               in that _diffrn_radiation.polarisn_norm refers to
               polarization relative to the diffraction plane rather than
               to the laboratory axis system.

               In the case of an unpolarized beam, or a beam with true
               circular polarization, in which no single plane of
               polarization can be determined, the plane should be taken
               as the XZ plane and the angle as 0.

               See _diffrn_radiation.polarizn_source_ratio.

Type: float

Mandatory item: no


The permitted range is [-90.0, 90.0]

Enumeration default: 0.0

Category: diffrn_radiation

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Imap.details.html0000644000076500007650000000601711603702115015547 0ustar yayayaya (IUCr) CIF Definition save__map.details

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_map.details

Name:
'_map.details'

Definition:

        The value of _map.details should give a
               description of special aspects of each map.


Example:

;   Example 1 - Identifying an observed density map
                and a calculated density map
;
loop_ _map.id _map.details rho_calc ; density calculated from F_calc derived from the ATOM_SITE list ; rho_obs ; density combining the observed structure factors with the calculated phases ;

Type: text

Mandatory item: no

Category: map

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Cdiffrn_scan_axis.html0000644000076500007650000000542111603702115016636 0ustar yayayaya (IUCr) CIF Definition save_diffrn_scan_axis

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

Category DIFFRN_SCAN_AXIS

Name:
'diffrn_scan_axis'

Description:

    Data items in the DIFFRN_SCAN_AXIS category describe the settings of
     axes for particular scans.  Unspecified axes are assumed to be at
     their zero points.

Category groups:
    inclusive_group
    diffrn_group
Category keys:
    _diffrn_scan_axis.scan_id
    _diffrn_scan_axis.axis_id

Mandatory category: no

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Iarray_structure_list.dimension.html0000644000076500007650000000510411603702115021617 0ustar yayayaya (IUCr) CIF Definition save__array_structure_list.dimension

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_array_structure_list.dimension

Name:
'_array_structure_list.dimension'

Definition:

        The number of elements stored in the array structure in 
               this dimension.

Type: int

Mandatory item: yes


The permitted range is [1, infinity)

Category: array_structure_list

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_refln.frame_id.html0000644000076500007650000000514211603702115017547 0ustar yayayaya (IUCr) CIF Definition save__diffrn_refln.frame_id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_refln.frame_id

Name:
'_diffrn_refln.frame_id'

Definition:

        This item is a pointer to _diffrn_data_frame.id
               in the DIFFRN_DATA_FRAME category.

Type: code

Mandatory item: yes

Category: diffrn_refln

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/cif_img_1.6.3_26Aug10.html0000644000076500007650000136502411603702115016473 0ustar yayayaya cif_img.dic v1.6.3

# [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib] #

# imgCIF/CBF #

# Extensions Dictionary #

data_cif_img.dic

    _datablock.id               cif_img.dic
    _datablock.description
;
##############################################################################
#                                                                            #
#                       Image CIF Dictionary (imgCIF)                        #
#             and Crystallographic Binary File Dictionary (CBF)              #
#            Extending the Macromolecular CIF Dictionary (mmCIF)             #
#                                                                            #
#                              Version 1.6.3                                 #
#                              of 2010-08-26                                 #
#    ###################################################################     #
#    # *** WARNING *** THIS IS A DRAFT FOR DISCUSSSION *** WARNING *** #     #
#    #                 SUBJECT TO CHANGE WITHOUT NOTICE                #     #
#    #       SEND COMMENTS TO imgcif-l@iucr.org CITING THE VERSION     #     #
#    ###################################################################     #
#                  This draft edited by H. J. Bernstein                      #
#                                                                            #
#     by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook    #
#                                                                            #
# This dictionary was adapted from format discussed at the imgCIF Workshop,  #
# held at BNL Oct 1997 and the Crystallographic Binary File Format Draft     #
# Proposal by Andrew Hammersley.  The first DDL 2.1 Version was created by   #
# John Westbrook.  This version was drafted by Herbert J. Bernstein and      #
# incorporates comments by I. David Brown, John Westbrook, Brian McMahon,    #
# Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li, Gotzon Madariaga,         #
# Frances C. Bernstein, Chris Nielsen, Nicola Ashcroft and others.           #
##############################################################################

##############################################################################
#    CONTENTS
#
#        CATEGORY_GROUP_LIST
#        SUB_CATEGORY
#
#        category  ARRAY_DATA
#
#                  _array_data.array_id
#                  _array_data.binary_id
#                  _array_data.data
#                  _array_data.header_contents
#                  _array_data.header_convention
#                  _array_data.variant
#
#        category  ARRAY_ELEMENT_SIZE
#
#                  _array_element_size.array_id
#                  _array_element_size.index
#                  _array_element_size.size
#                  _array_element_size.variant
#
#        category  ARRAY_INTENSITIES
#
#                  _array_intensities.array_id
#                  _array_intensities.binary_id
#                  _array_intensities.gain
#                  _array_intensities.gain_esd
#                  _array_intensities.linearity
#                  _array_intensities.offset
#                  _array_intensities.scaling
#                  _array_intensities.overload
#                  _array_intensities.undefined_value
#                  _array_intensities.pixel_fast_bin_size
#                  _array_intensities.pixel_slow_bin_size
#                  _array_intensities.pixel_binning_method
#                  _array_intensities.variant
#
#        category  ARRAY_STRUCTURE
#
#                  _array_structure.byte_order
#                  _array_structure.compression_type
#                  _array_structure.compression_type_flag
#                  _array_structure.encoding_type
#                  _array_structure.id
#                  _array_structure.variant
#
#        category  ARRAY_STRUCTURE_LIST
#
#                  _array_structure_list.axis_set_id
#                  _array_structure_list.array_id
#                  _array_structure_list.dimension
#                  _array_structure_list.direction
#                  _array_structure_list.index
#                  _array_structure_list.precedence
#                  _array_structure_list.variant
#
#        category  ARRAY_STRUCTURE_LIST_AXIS
#
#                  _array_structure_list_axis.axis_id
#                  _array_structure_list_axis.axis_set_id
#                  _array_structure_list_axis.angle
#                  _array_structure_list_axis.angle_increment
#                  _array_structure_list_axis.displacement
#                  _array_structure_list_axis.fract_displacement
#                  _array_structure_list_axis.displacement_increment
#                  _array_structure_list_axis.fract_displacement_increment
#                  _array_structure_list_axis.angular_pitch
#                  _array_structure_list_axis.radial_pitch
#                  _array_structure_list_axis.reference_angle
#                  _array_structure_list_axis.reference_displacement
#                  _array_structure_list_axis.variant
#
#        category  AXIS
#
#                  _axis.depends_on
#                  _axis.equipment
#                  _axis.id
#                  _axis.offset[1]
#                  _axis.offset[2]
#                  _axis.offset[3]
#                  _axis.type
#                  _axis.system
#                  _axis.vector[1]
#                  _axis.vector[2]
#                  _axis.vector[3]
#                  _axis.variant
#
#        category  DIFFRN_DATA_FRAME
#
#                  _diffrn_data_frame.array_id
#                  _diffrn_data_frame.binary_id
#                  _diffrn_data_frame.center_fast
#                  _diffrn_data_frame.center_slow
#                  _diffrn_data_frame.center_units
#                  _diffrn_data_frame.detector_element_id
#                  _diffrn_data_frame.id
#                  _diffrn_data_frame.details
#                  _diffrn_data_frame.variant
#
#        category  DIFFRN_DETECTOR
#
#                  _diffrn_detector.details
#                  _diffrn_detector.detector
#                  _diffrn_detector.diffrn_id
#                  _diffrn_detector.dtime
#                  _diffrn_detector.id
#                  _diffrn_detector.number_of_axes
#                  _diffrn_detector.type
#                  _diffrn_detector.variant
#
#        category  DIFFRN_DETECTOR_AXIS
#
#                  _diffrn_detector_axis.axis_id
#                  _diffrn_detector_axis.detector_id
#                  _diffrn_detector_axis.variant
#
#        category  DIFFRN_DETECTOR_ELEMENT
#
#                  _diffrn_detector_element.id
#                  _diffrn_detector_element.detector_id
#                  _diffrn_detector_element.reference_center_fast
#                  _diffrn_detector_element.reference_center_slow
#                  _diffrn_detector_element.reference_center_units
#                  _diffrn_detector_element.variant
#
#        category  DIFFRN_MEASUREMENT
#
#                  _diffrn_measurement.diffrn_id
#                  _diffrn_measurement.details
#                  _diffrn_measurement.device
#                  _diffrn_measurement.device_details
#                  _diffrn_measurement.device_type
#                  _diffrn_measurement.id
#                  _diffrn_measurement.method
#                  _diffrn_measurement.number_of_axes
#                  _diffrn_measurement.sample_detector_distance
#                  _diffrn_measurement.sample_detector_voffset
#                  _diffrn_measurement.specimen_support
#                  _diffrn_measurement.variant
#
#        category  DIFFRN_MEASUREMENT_AXIS
#
#                  _diffrn_measurement_axis.axis_id
#                  _diffrn_measurement_axis.measurement_device
#                  _diffrn_measurement_axis.measurement_id
#                  _diffrn_measurement_axis.variant
#
#        category  DIFFRN_RADIATION
#
#                  _diffrn_radiation.collimation
#                  _diffrn_radiation.diffrn_id
#                  _diffrn_radiation.div_x_source
#                  _diffrn_radiation.div_y_source
#                  _diffrn_radiation.div_x_y_source
#                  _diffrn_radiation.filter_edge'
#                  _diffrn_radiation.inhomogeneity
#                  _diffrn_radiation.monochromator
#                  _diffrn_radiation.polarisn_norm
#                  _diffrn_radiation.polarisn_ratio
#                  _diffrn_radiation.polarizn_source_norm
#                  _diffrn_radiation.polarizn_source_ratio
#                  _diffrn_radiation.probe
#                  _diffrn_radiation.type
#                  _diffrn_radiation.xray_symbol
#                  _diffrn_radiation.wavelength_id
#                  _diffrn_radiation.variant
#
#        category  DIFFRN_REFLN
#
#                  _diffrn_refln.frame_id
#                  _diffrn_refln.variant
#
#        category  DIFFRN_SCAN
#
#                  _diffrn_scan.id
#                  _diffrn_scan.date_end
#                  _diffrn_scan.date_start
#                  _diffrn_scan.integration_time
#                  _diffrn_scan.frame_id_start
#                  _diffrn_scan.frame_id_end
#                  _diffrn_scan.frames
#                  _diffrn_scan.variant
#
#        category  DIFFRN_SCAN_AXIS
#
#                  _diffrn_scan_axis.axis_id
#                  _diffrn_scan_axis.angle_start
#                  _diffrn_scan_axis.angle_range
#                  _diffrn_scan_axis.angle_increment
#                  _diffrn_scan_axis.angle_rstrt_incr
#                  _diffrn_scan_axis.displacement_start
#                  _diffrn_scan_axis.displacement_range
#                  _diffrn_scan_axis.displacement_increment
#                  _diffrn_scan_axis.displacement_rstrt_incr
#                  _diffrn_scan_axis.reference_angle
#                  _diffrn_scan_axis.reference_displacement
#                  _diffrn_scan_axis.scan_id
#                  _diffrn_scan_axis.variant
#
#        category  DIFFRN_SCAN_FRAME
#
#                  _diffrn_scan_frame.date
#                  _diffrn_scan_frame.frame_id
#                  _diffrn_scan_frame.frame_number
#                  _diffrn_scan_frame.integration_time
#                  _diffrn_scan_frame.scan_id
#                  _diffrn_scan_frame.variant
#
#        category  DIFFRN_SCAN_FRAME_AXIS
#
#                  _diffrn_scan_frame_axis.axis_id
#                  _diffrn_scan_frame_axis.angle
#                  _diffrn_scan_frame_axis.angle_increment
#                  _diffrn_scan_frame_axis.angle_rstrt_incr
#                  _diffrn_scan_frame_axis.displacement
#                  _diffrn_scan_frame_axis.displacement_increment
#                  _diffrn_scan_frame_axis.displacement_rstrt_incr
#                  _diffrn_scan_frame_axis.reference_angle
#                  _diffrn_scan_frame_axis.reference_displacement
#                  _diffrn_scan_frame_axis.frame_id
#                  _diffrn_scan_frame_axis.variant
#
#        category  DIFFRN_SCAN_FRAME_MONITOR
#
#                  _diffrn_scan_frame_monitor.id
#                  _diffrn_scan_frame_monitor.detector_id
#                  _diffrn_scan_frame_monitor.scan_id
#                  _diffrn_data_frame_monitor.frame_id
#                  _diffrn_data_frame_monitor.integration_time
#                  _diffrn_data_frame_monitor.monitor_value
#                  _diffrn_data_frame_monitor.variant
#
#        category  MAP
#
#                  _map.details
#                  _map.diffrn_id
#                  _map.entry_id
#                  _map.id
#                  _map.variant
#
#       category   MAP_SEGMENT
#
#                  _map_segment.array_id
#                  _map_segment.binary_id
#                  _map_segment.mask_array_id
#                  _map_segment.mask_binary_id
#                  _map_segment.id
#                  _map_segment.map_id
#                  _map_segment.details
#                  _map_segment.variant
#
#       category   VARIANT
#
#                  _variant.details
#                  _variant.role
#                  _variant.timestamp
#                  _variant.variant
#                  _variant.variant_of
#
#       ***DEPRECATED*** data items
#
#                  _diffrn_detector_axis.id
#                  _diffrn_detector_element.center[1]
#                  _diffrn_detector_element.center[2]
#                  _diffrn_measurement_axis.id
#
#       ***DEPRECATED*** category  DIFFRN_FRAME_DATA
#
#                  _diffrn_frame_data.array_id
#                  _diffrn_frame_data.binary_id
#                  _diffrn_frame_data.detector_element_id
#                  _diffrn_frame_data.id
#                  _diffrn_frame_data.details
#
#
#        ITEM_TYPE_LIST
#        ITEM_UNITS_LIST
#        DICTIONARY_HISTORY
#
##############################################################################


ARRAY_DATA_GROUP Categories that describe array data.
ARRAY_DATA Data items in the ARRAY_DATA category are the containers for the array data items described in the category ARRAY_STRUCTURE.

It is recognized that the data in this category needs to be used in two distinct ways. During a data collection the lack of ancillary data and timing constraints in processing data may dictate the need to make a 'miniCBF' nothing more than an essential minimum of information to record the results of the data collection. In that case it is proper to use the ARRAY_DATA category as a container for just a single image and a compacted, beam-line dependent list of data collection parameter values. In such a case, only the tags '_array_data.header_convention', '_array_data.header_contents' and '_array_data.data' need be populated.

For full processing and archiving, most of the tags in this dictionary will need to be populated.

ARRAY_ELEMENT_SIZE Data items in the ARRAY_ELEMENT_SIZE category record the physical size of array elements along each array dimension.
ARRAY_INTENSITIES Data items in the ARRAY_INTENSITIES category record the information required to recover the intensity data from the set of data values stored in the ARRAY_DATA category.

The detector may have a complex relationship between the raw intensity values and the number of incident photons. In most cases, the number stored in the final array will have a simple linear relationship to the actual number of incident photons, given by _array_intensities.gain. If raw, uncorrected values are presented (e.g. for calibration experiments), the value of _array_intensities.linearity will be 'raw' and _array_intensities.gain will not be used.

ARRAY_STRUCTURE Data items in the ARRAY_STRUCTURE category record the organization and encoding of array data that may be stored in the ARRAY_DATA category.
  ARRAY_STRUCTURE_LIST Data items in the ARRAY_STRUCTURE_LIST category record the size and organization of each array dimension.

The relationship to physical axes may be given.

  ARRAY_STRUCTURE_LIST_AXIS Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe the physical settings of sets of axes for the centres of pixels that correspond to data points described in the ARRAY_STRUCTURE_LIST category.

In the simplest cases, the physical increments of a single axis correspond to the increments of a single array index. More complex organizations, e.g. spiral scans, may require coupled motions along multiple axes.

Note that a spiral scan uses two coupled axes: one for the angular direction and one for the radial direction. This differs from a cylindrical scan for which the two axes are not coupled into one set.

AXIS_GROUP Categories that describe axes.
AXIS Data items in the AXIS category record the information required to describe the various goniometer, detector, source and other axes needed to specify a data collection or the axes defining the coordinate system of an image.

The location of each axis is specified by two vectors: the axis itself, given by a unit vector in the direction of the axis, and an offset to the base of the unit vector.

The vectors defining an axis are referenced to an appropriate coordinate system. The axis vector, itself, is a dimensionless unit vector. Where meaningful, the offset vector is given in millimetres. In coordinate systems not measured in metres, the offset is not specified and is taken as zero.

The available coordinate systems are:

The imgCIF standard laboratory coordinate system
The direct lattice (fractional atomic coordinates)
The orthogonal Cartesian coordinate system (real space)
The reciprocal lattice
An abstract orthogonal Cartesian coordinate frame

DIFFRN_GROUP Categories that describe details of the diffraction experiment.
DIFFRN_DATA_FRAME Data items in the DIFFRN_DATA_FRAME category record the details about each frame of data.

The items in this category were previously in a DIFFRN_FRAME_DATA category, which is now deprecated. The items from the old category are provided as aliases but should not be used for new work.

DIFFRN_DETECTOR Data items in the DIFFRN_DETECTOR category describe the detector used to measure the scattered radiation, including any analyser and post-sample collimation.
  DIFFRN_DETECTOR_AXIS Data items in the DIFFRN_DETECTOR_AXIS category associate axes with detectors.
  DIFFRN_DETECTOR_ELEMENT Data items in the DIFFRN_DETECTOR_ELEMENT category record the details about spatial layout and other characteristics of each element of a detector which may have multiple elements.

In most cases, giving more detailed information in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS is preferable to simply providing the centre of the detector element.

DIFFRN_MEASUREMENT Data items in the DIFFRN_MEASUREMENT category record details about the device used to orient and/or position the crystal during data measurement and the manner in which the diffraction data were measured.
  DIFFRN_MEASUREMENT_AXIS Data items in the DIFFRN_MEASUREMENT_AXIS category associate axes with goniometers.
DIFFRN_RADIATION Data items in the DIFFRN_RADIATION category describe the radiation used for measuring diffraction intensities, its collimation and monochromatization before the sample.

Post-sample treatment of the beam is described by data items in the DIFFRN_DETECTOR category.

DIFFRN_REFLN This category redefinition has been added to extend the key of the standard DIFFRN_REFLN category.

Data items in the DIFFRN_REFLN category record details about the intensities in the diffraction data set identified by _diffrn_refln.diffrn_id.

The DIFFRN_REFLN data items refer to individual intensity measurements and must be included in looped lists.

The DIFFRN_REFLNS data items specify the parameters that apply to all intensity measurements in the particular diffraction data set identified by _diffrn_reflns.diffrn_id and _diffrn_refln.frame_id

DIFFRN_SCAN Data items in the DIFFRN_SCAN category describe the parameters of one or more scans, relating axis positions to frames.
  DIFFRN_SCAN_AXIS Data items in the DIFFRN_SCAN_AXIS category describe the settings of axes for particular scans. Unspecified axes are assumed to be at their zero points.
  DIFFRN_SCAN_FRAME Data items in the DIFFRN_SCAN_FRAME category describe the relationships of particular frames to scans.
 
  DIFFRN_SCAN_FRAME_AXIS Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the settings of axes for particular frames. Unspecified axes are assumed to be at their zero points. If, for any given frame, nonzero values apply for any of the data items in this category, those values should be given explicitly in this category and not simply inferred from values in DIFFRN_SCAN_AXIS.
 
  DIFFRN_SCAN_FRAME_MONITOR Data items in the DIFFRN_SCAN_FRAME_MONITOR category record the values and details about each monitor for each frame of data during a scan.

Each monitor value is uniquely identified by the combination of the scan_id given by _diffrn_scan_frame.scan_id the frame_id given by _diffrn_scan_frame_monitor.frame_id, the monitor's detector_id given by _diffrn_scan_frame_monitor.monitor_id, and a 1-based ordinal given by _diffrn_scan_frame_monitor.id.

If there is only one frame for the scan, the value of _diffrn_scan_frame_monitor.frame_id may be omitted.

A single frame may have more than one monitor value, and each monitor value may be the result of integration over the entire frame integration time given by the value of _diffrn_scan_frame.integration_time or many monitor values may be reported over shorter times given by the value of _diffrn_scan_frame_monitor.integration_time. If only one monitor value for a given monitor is collected during the integration time of the frame, the value of _diffrn_scan_frame_monitor.id may be omitted.

MAP_GROUP Categories that describe maps.
MAP Data items in the MAP category record the details of a maps. Maps record values of parameters, such as density, that are functions of position within a cell or are functions of orthogonal coordinates in three space.

A map may is composed of one or more map segments specified in the MAP_SEGMENT category.

Examples are given in the MAP_SEGMENT category.

  MAP_SEGMENT Data items in the MAP_SEGMENT category record the details about each segment (section or brick) of a map.
VARIANT_GROUP Categories that describe variants
VARIANT Data items in the VARIANT category record the details about sets of variants of data items.

There is sometimes a need to allow for multiple versions of the same data items in order to allow for refinements and corrections to earlier assumptions, observations and calculations. In order to allow data sets to contain more than one variant of the same information, an optional ...variant data item as a pointer to _variant.variant has been added to the key of every category, as an implicit data item with a null (empty) default value.

All rows in a category with the same variant value are considered to be related to one another and to all rows in other categories with the same variant value. For a given variant, all such rows are also considered to be related to all rows with a null variant value, except that a row with a null variant value is for which all other components of its key are identical to those entries in another row with a non-null variant value is not related the the rows with that non-null variant value. This behavior is similar to the convention for identifying alternate conformers in an atom list.

An optional role may be specified for a variant as the value of _variant.role. Possible roles are null, "preferred", "raw data", "unsuccessful trial".

Variants may carry an optional timestamp as the value of _variant.timestamp.

Variants may be related to other variants from which they were derived by the value of _variant.variant_of

Further details about the variant may be specified as the value of _variant.details.

In order to allow variant information from multiple datasets to be combined, _variant.diffrn_id and/or _variant.entry_id may be used.

; _dictionary.title cif_img.dic _dictionary.version 1.6.3 _dictionary.datablock_id cif_img.dic ######################### ## CATEGORY_GROUP_LIST ## ######################### loop_ _category_group_list.id _category_group_list.parent_id _category_group_list.description 'inclusive_group' . ; Categories that belong to the dictionary extension. ; 'array_data_group' 'inclusive_group' ; Categories that describe array data. ; 'axis_group' 'inclusive_group' ; Categories that describe axes. ; 'diffrn_group' 'inclusive_group' ; Categories that describe details of the diffraction experiment. ; 'map_group' 'inclusive_group' ; Categories that describe details of map data. ; 'variant_group' 'inclusive_group' ; Categories that describe details of map data. ; ################## ## SUB_CATEGORY ## ################## loop_ _sub_category.id _sub_category.description 'matrix' ; The collection of elements of a matrix. ; 'vector' ; The collection of elements of a vector. ; ############## # ARRAY_DATA # ############## save_ARRAY_DATA _category.description ; Data items in the ARRAY_DATA category are the containers for the array data items described in the category ARRAY_STRUCTURE. It is recognized that the data in this category needs to be used in two distinct ways. During a data collection the lack of ancillary data and timing constraints in processing data may dictate the need to make a 'miniCBF' nothing more than an essential minimum of information to record the results of the data collection. In that case it is proper to use the ARRAY_DATA category as a container for just a single image and a compacted, beam-line dependent list of data collection parameter values. In such a case, only the tags '_array_data.header_convention', '_array_data.header_contents' and '_array_data.data' need be populated. For full processing and archiving, most of the tags in this dictionary will need to be populated. ; _category.id array_data _category.mandatory_code no loop_ _category_key.name '_array_data.array_id' '_array_data.binary_id' '_array_data.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows two binary data blocks. The first one was compressed by the CBF_CANONICAL compression algorithm and is presented as hexadecimal data. The first character 'H' on the data lines means hexadecimal. It could have been 'O' for octal or 'D' for decimal. The second character on the line shows the number of bytes in each word (in this case '4'), which then requires eight hexadecimal digits per word. The third character gives the order of octets within a word, in this case '<' for the ordering 4321 (i.e. 'big-endian'). Alternatively, the character '>' could have been used for the ordering 1234 (i.e. 'little-endian'). The block has a 'message digest' to check the integrity of the data. The second block is similar, but uses CBF_PACKED compression and BASE64 encoding. Note that the size and the digest are different. ; ; loop_ _array_data.array_id _array_data.binary_id _array_data.data image_1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF_CANONICAL" Content-Transfer-Encoding: X-BASE16 X-Binary-Size: 3927126 X-Binary-ID: 1 Content-MD5: u2sTJEovAHkmkDjPi+gWsg== # Hexadecimal encoding, byte 0, byte order ...21 # H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ... .... --CIF-BINARY-FORMAT-SECTION---- ; image_2 2 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF-PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3745758 X-Binary-ID: 2 Content-MD5: 1zsJjWPfol2GYl2V+QSXrw== ELhQAAAAAAAA... ... --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - This example shows a single image in a miniCBF, provided by E. Eikenberry. The entire CBF consists of one data block containing one category and three tags. The CBFlib program convert_miniCBF and a suitable template file can be used to convert this miniCBF to a full imgCIF file. ; ; ###CBF: VERSION 1.5 # CBF file written by CBFlib v0.7.8 data_insulin_pilatus6m _array_data.header_convention SLS_1.0 _array_data.header_contents ; # Detector: PILATUS 6M SN: 60-0001 # 2007/Jun/17 15:12:36.928 # Pixel_size 172e-6 m x 172e-6 m # Silicon sensor, thickness 0.000320 m # Exposure_time 0.995000 s # Exposure_period 1.000000 s # Tau = 194.0e-09 s # Count_cutoff 1048575 counts # Threshold_setting 5000 eV # Wavelength 1.2398 A # Energy_range (0, 0) eV # Detector_distance 0.15500 m # Detector_Voffset -0.01003 m # Beam_xy (1231.00, 1277.00) pixels # Flux 22487563295 ph/s # Filter_transmission 0.0008 # Start_angle 13.0000 deg. # Angle_increment 1.0000 deg. # Detector_2theta 0.0000 deg. # Polarization 0.990 # Alpha 0.0000 deg. # Kappa 0.0000 deg. # Phi 0.0000 deg. # Chi 0.0000 deg. # Oscillation_axis X, CW # N_oscillations 1 ; _array_data.data ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_BYTE_OFFSET" Content-Transfer-Encoding: BINARY X-Binary-Size: 6247567 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" X-Binary-Element-Byte-Order: LITTLE_ENDIAN Content-MD5: 8wO6i2+899lf5iO8QPdgrw== X-Binary-Number-of-Elements: 6224001 X-Binary-Size-Fastest-Dimension: 2463 X-Binary-Size-Second-Dimension: 2527 X-Binary-Size-Padding: 4095 ... --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_data.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. If not given, it defaults to 1. ; _item.name '_array_data.array_id' _item.category_id array_data _item.mandatory_code implicit _item_default.value 1 _item_type.code code save_ save__array_data.binary_id _item_description.description ; This item is an integer identifier which, along with _array_data.array_id, should uniquely identify the particular block of array data. If _array_data.binary_id is not explicitly given, it defaults to 1. The value of _array_data.binary_id distinguishes among multiple sets of data with the same array structure. If the MIME header of the data array specifies a value for X-Binary-ID, the value of _array_data.binary_id should be equal to the value given for X-Binary-ID. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_data.binary_id' array_data implicit '_diffrn_data_frame.binary_id' diffrn_data_frame implicit '_array_intensities.binary_id' array_intensities implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.binary_id' '_array_data.binary_id' '_array_intensities.binary_id' '_array_data.binary_id' _item_default.value 1 _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_data.data _item_description.description ; The value of _array_data.data contains the array data encapsulated in a STAR string. The representation used is a variant on the Multipurpose Internet Mail Extensions (MIME) specified in RFC 2045-2049 by N. Freed et al. The boundary delimiter used in writing an imgCIF or CBF is '\n--CIF-BINARY-FORMAT-SECTION--' (including the required initial '\n--'). The Content-Type may be any of the discrete types permitted in RFC 2045; 'application/octet-stream' is recommended for diffraction images in the ARRAY_DATA category. Note: When appropriate in other categories, e.g. for photographs of crystals, more precise types, such as 'image/jpeg', 'image/tiff', 'image/png', etc. should be used. If an octet stream was compressed, the compression should be specified by the parameter 'conversions="X-CBF_PACKED"' or the parameter 'conversions="X-CBF_CANONICAL"' or the parameter 'conversions="X-CBF_BYTE_OFFSET"' or the parameter 'conversions="X-CBF_BACKGROUND_OFFSET_DELTA"' If the parameter 'conversions="X-CBF_PACKED"' is given it may be further modified with the parameters '"uncorrelated_sections"' or '"flat"' If the '"uncorrelated_sections"' parameter is given, each section will be compressed without using the prior section for averaging. If the '"flat"' parameter is given, each the image will be treated as one long row. Note that the X-CBF_CANONICAL and X-CBF_PACKED are slower but more efficient compressions that the others. The X-CBF_BYTE_OFFSET compression is a good compromise between speed and efficiency for ordinary diffraction images. The X-CBF_BACKGROUND_OFFSET_DELTA compression is oriented towards sparse data, such as masks and tables of replacement pixel values for images with overloaded spots. The Content-Transfer-Encoding may be 'BASE64', 'Quoted-Printable', 'X-BASE8', 'X-BASE10', 'X-BASE16' or 'X-BASE32K', for an imgCIF or 'BINARY' for a CBF. The octal, decimal and hexadecimal transfer encodings are provided for convenience in debugging and are not recommended for archiving and data interchange. In a CIF, one of the parameters 'charset=us-ascii', 'charset=utf-8' or 'charset=utf-16' may be used on the Content-Transfer-Encoding to specify the character set used for the external presentation of the encoded data. If no charset parameter is given, the character set of the enclosing CIF is assumed. In any case, if a BOM flag is detected (FE FF for big-endian UTF-16, FF FE for little-endian UTF-16 or EF BB BF for UTF-8) is detected, the indicated charset will be assumed until the end of the encoded data or the detection of a different BOM. The charset of the Content-Transfer-Encoding is not the character set of the encoded data, only the character set of the presentation of the encoded data and should be respecified for each distinct STAR string. In an imgCIF file, the encoded binary data begins after the empty line terminating the header. In an imgCIF file, the encoded binary data ends with the terminating boundary delimiter '\n--CIF-BINARY-FORMAT-SECTION----' in the currently effective charset or with the '\n; ' that terminates the STAR string. In a CBF, the raw binary data begins after an empty line terminating the header and after the sequence: Octet Hex Decimal Purpose 0 0C 12 (ctrl-L) Page break 1 1A 26 (ctrl-Z) Stop listings in MS-DOS 2 04 04 (Ctrl-D) Stop listings in UNIX 3 D5 213 Binary section begins None of these octets are included in the calculation of the message size or in the calculation of the message digest. The X-Binary-Size header specifies the size of the equivalent binary data in octets. If compression was used, this size is the size after compression, including any book-keeping fields. An adjustment is made for the deprecated binary formats in which eight bytes of binary header are used for the compression type. In this case, the eight bytes used for the compression type are subtracted from the size, so that the same size will be reported if the compression type is supplied in the MIME header. Use of the MIME header is the recommended way to supply the compression type. In general, no portion of the binary header is included in the calculation of the size. The X-Binary-Element-Type header specifies the type of binary data in the octets, using the same descriptive phrases as in _array_structure.encoding_type. The default value is 'unsigned 32-bit integer'. An MD5 message digest may, optionally, be used. The 'RSA Data Security, Inc. MD5 Message-Digest Algorithm' should be used. No portion of the header is included in the calculation of the message digest. If the Transfer Encoding is 'X-BASE8', 'X-BASE10' or 'X-BASE16', the data are presented as octal, decimal or hexadecimal data organized into lines or words. Each word is created by composing octets of data in fixed groups of 2, 3, 4, 6 or 8 octets, either in the order ...4321 ('big- endian') or 1234... ('little-endian'). If there are fewer than the specified number of octets to fill the last word, then the missing octets are presented as '==' for each missing octet. Exactly two equal signs are used for each missing octet even for octal and decimal encoding. The format of lines is: rnd xxxxxx xxxxxx xxxxxx where r is 'H', 'O' or 'D' for hexadecimal, octal or decimal, n is the number of octets per word and d is '<' or '>' for the '...4321' and '1234...' octet orderings, respectively. The '==' padding for the last word should be on the appropriate side to correspond to the missing octets, e.g. H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000 or H3> FF0700 00==== For these hexadecimal, octal and decimal formats only, comments beginning with '#' are permitted to improve readability. BASE64 encoding follows MIME conventions. Octets are in groups of three: c1, c2, c3. The resulting 24 bits are broken into four six-bit quantities, starting with the high-order six bits (c1 >> 2) of the first octet, then the low-order two bits of the first octet followed by the high-order four bits of the second octet [(c1 & 3)<<4 | (c2>>4)], then the bottom four bits of the second octet followed by the high-order two bits of the last octet [(c2 & 15)<<2 | (c3>>6)], then the bottom six bits of the last octet (c3 & 63). Each of these four quantities is translated into an ASCII character using the mapping: 1 2 3 4 5 6 0123456789012345678901234567890123456789012345678901234567890123 | | | | | | | ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/ With short groups of octets padded on the right with one '=' if c3 is missing, and with '==' if both c2 and c3 are missing. X-BASE32K encoding is similar to BASE64 encoding, except that sets of 15 octets are encoded as sets of 8 16-bit unicode characters, by breaking the 120 bits into 8 15-bit quantities. 256 is added to each 15 bit quantity to bring it into a printable uncode range. When encoding, zero padding is used to fill out the last 15 bit quantity. If 8 or more bits of padding are used, a single equals sign (hexadecimal 003D) is appended. Embedded whitespace and newlines are introduced to produce lines of no more than 80 characters each. On decoding, all printable ascii characters and ascii whitespace characters are ignored except for any trailing equals signs. The number of trailing equals signs indicated the number of trailing octets to be trimmed from the end of the decoded data. (see Georgi Darakev, Vassil Litchev, Kostadin Z. Mitev, Herbert J. Bernstein, 'Efficient Support of Binary Data in the XML Implementation of the NeXus File Format',absract W0165, ACA Summer Meeting, Honolulu, HI, July 2006). QUOTED-PRINTABLE encoding also follows MIME conventions, copying octets without translation if their ASCII values are 32...38, 42, 48...57, 59, 60, 62, 64...126 and the octet is not a ';' in column 1. All other characters are translated to =nn, where nn is the hexadecimal encoding of the octet. All lines are 'wrapped' with a terminating '=' (i.e. the MIME conventions for an implicit line terminator are never used). The "X-Binary-Element-Byte-Order" can specify either '"BIG_ENDIAN"' or '"LITTLE_ENDIAN"' byte order of the imaage data. Only LITTLE_ENDIAN is recommended. Processors may treat BIG_ENDIAN as a warning of data that can only be processed by special software. The "X-Binary-Number-of-Elements" specifies the number of elements (not the number of octets) in the decompressed, decoded image. The optional "X-Binary-Size-Fastest-Dimension" specifies the number of elements (not the number of octets) in one row of the fastest changing dimension of the binary data array. This information must be in the MIME header for proper operation of some of the decompression algorithms. The optional "X-Binary-Size-Second-Dimension" specifies the number of elements (not the number of octets) in one column of the second-fastest changing dimension of the binary data array. This information must be in the MIME header for proper operation of some of the decompression algorithms. The optional "X-Binary-Size-Third-Dimension" specifies the number of sections for the third-fastest changing dimension of the binary data array. The optional "X-Binary-Size-Padding" specifies the size in octets of an optional padding after the binary array data and before the closing flags for a binary section. ; _item.name '_array_data.data' _item.category_id array_data _item.mandatory_code yes _item_type.code binary save_ save__array_data.header_contents _item_description.description ; This item is an text field for use in minimal CBF files to carry essential header information to be kept with image data in _array_data.data when the tags that normally carry the structured metadata for the image have not been populated. Normally this data item should not appear when the full set of tags have been populated and _diffrn_data_frame.details appears. ; _item.name '_array_data.header_contents' _item.category_id array_data _item.mandatory_code no _item_type.code text save_ save__array_data.header_convention _item_description.description ; This item is an identifier for the convention followed in constructing the contents of _array_data.header_contents The permitted values are of the of an image creator identifier followed by an underscore and a version string. To avoid confusion about conventions, all creator identifiers should be registered with the IUCr and the conventions for all identifiers and versions should be posted on the MEDSBIO.org web site. ; _item.name '_array_data.header_convention' _item.category_id array_data _item.mandatory_code no _item_type.code code save_ save__array_data.variant _item_description.description ; The value of _array_data.variant gives the variant to which the given array_data row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_array_data.variant' _item.category_id array_data _item.mandatory_code no _item_type.code code save_ ###################### # ARRAY_ELEMENT_SIZE # ###################### save_ARRAY_ELEMENT_SIZE _category.description ; Data items in the ARRAY_ELEMENT_SIZE category record the physical size of array elements along each array dimension. ; _category.id array_element_size _category.mandatory_code no loop_ _category_key.name '_array_element_size.array_id' '_array_element_size.index' '_array_element_size.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A regular 2D array with a uniform element dimension of 1220 nanometres. ; ; loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size image_1 1 1.22e-6 image_1 2 1.22e-6 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_element_size.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_element_size.array_id' _item.category_id array_element_size _item.mandatory_code implicit _item_type.code code save_ save__array_element_size.index _item_description.description ; This item is a pointer to _array_structure_list.index in the ARRAY_STRUCTURE_LIST category. ; _item.name '_array_element_size.index' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.size _item_description.description ; The size in metres of an image element in this dimension. This supposes that the elements are arranged on a regular grid. ; _item.name '_array_element_size.size' _item.category_id array_element_size _item.mandatory_code yes _item_type.code float _item_units.code 'metres' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__array_element_size.variant _item_description.description ; The value of _array_element_size.variant gives the variant to which the given array_element_size row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_array_element_size.variant' _item.category_id array_element_size _item.mandatory_code no _item_type.code code save_ ##################### # ARRAY_INTENSITIES # ##################### save_ARRAY_INTENSITIES _category.description ; Data items in the ARRAY_INTENSITIES category record the information required to recover the intensity data from the set of data values stored in the ARRAY_DATA category. The detector may have a complex relationship between the raw intensity values and the number of incident photons. In most cases, the number stored in the final array will have a simple linear relationship to the actual number of incident photons, given by _array_intensities.gain. If raw, uncorrected values are presented (e.g. for calibration experiments), the value of _array_intensities.linearity will be 'raw' and _array_intensities.gain will not be used. ; _category.id array_intensities _category.mandatory_code no loop_ _category_key.name '_array_intensities.array_id' '_array_intensities.binary_id' '_array_intensities.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 ; ; loop_ _array_intensities.array_id _array_intensities.linearity _array_intensities.gain _array_intensities.overload _array_intensities.undefined_value _array_intensities.pixel_fast_bin_size _array_intensities.pixel_slow_bin_size _array_intensities.pixel_binning_method image_1 linear 1.2 655535 0 2 2 hardware ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_intensities.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_intensities.array_id' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code code save_ save__array_intensities.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_array_intensities.binary_id' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code int save_ save__array_intensities.gain _item_description.description ; Detector 'gain'. The factor by which linearized intensity count values should be divided to produce true photon counts. ; _item.name '_array_intensities.gain' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain_esd' 'associated_value' save_ save__array_intensities.gain_esd _item_description.description ; The estimated standard deviation in detector 'gain'. ; _item.name '_array_intensities.gain_esd' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain' 'associated_esd' save_ save__array_intensities.linearity _item_description.description ; The intensity linearity scaling method used to convert from the raw intensity to the stored element value: 'linear' is linear. 'offset' means that the value defined by _array_intensities.offset should be added to each element value. 'scaling' means that the value defined by _array_intensities.scaling should be multiplied with each element value. 'scaling_offset' is the combination of the two previous cases, with the scale factor applied before the offset value. 'sqrt_scaled' means that the square root of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and squaring the result. 'logarithmic_scaled' means that the logarithm base 10 of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and calculating 10 to the power of this number. 'raw' means that the data are a set of raw values straight from the detector. ; _item.name '_array_intensities.linearity' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'linear' . 'offset' ; The value defined by _array_intensities.offset should be added to each element value. ; 'scaling' ; The value defined by _array_intensities.scaling should be multiplied with each element value. ; 'scaling_offset' ; The combination of the scaling and offset with the scale factor applied before the offset value. ; 'sqrt_scaled' ; The square root of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and squaring the result. ; 'logarithmic_scaled' ; The logarithm base 10 of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and calculating 10 to the power of this number. ; 'raw' ; The array consists of raw values to which no corrections have been applied. While the handling of the data is similar to that given for 'linear' data with no offset, the meaning of the data differs in that the number of incident photons is not necessarily linearly related to the number of counts reported. This value is intended for use either in calibration experiments or to allow for handling more complex data-fitting algorithms than are allowed for by this data item. ; save_ save__array_intensities.offset _item_description.description ; Offset value to add to array element values in the manner described by the item _array_intensities.linearity. ; _item.name '_array_intensities.offset' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.overload _item_description.description ; The saturation intensity level for this data array. ; _item.name '_array_intensities.overload' _item.category_id array_intensities _item.mandatory_code no _item_type.code float _item_units.code 'counts' save_ save__array_intensities.pixel_fast_bin_size _item_description.description ; The value of _array_intensities.pixel_fast_bin_size specifies the number of pixels that compose one element in the direction of the most rapidly varying array dimension. Typical values are 1, 2, 4 or 8. When there is 1 pixel per array element in both directions, the value given for _array_intensities.pixel_binning_method normally should be 'none'. It is specified as a float to allow for binning algorithms that create array elements that are not integer multiples of the detector pixel size. ; _item.name '_array_intensities.pixel_fast_bin_size' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code float _item_default.value 1. loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'pixels_per_element' save_ save__array_intensities.pixel_slow_bin_size _item_description.description ; The value of _array_intensities.pixel_slow_bin_size specifies the number of pixels that compose one element in the direction of the second most rapidly varying array dimension. Typical values are 1, 2, 4 or 8. When there is 1 pixel per array element in both directions, the value given for _array_intensities.pixel_binning_method normally should be 'none'. It is specified as a float to allow for binning algorithms that create array elements that are not integer multiples of the detector pixel size. ; _item.name '_array_intensities.pixel_slow_bin_size' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code float _item_default.value 1. loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'pixels_per_element' save_ save__array_intensities.pixel_binning_method _item_description.description ; The value of _array_intensities.pixel_binning_method specifies the method used to derive array elements from multiple pixels. ; _item.name '_array_intensities.pixel_binning_method' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'hardware' ; The element intensities were derived from the raw data of one or more pixels by used of hardware in the detector, e.g. by use of shift registers in a CCD to combine pixels into super-pixels. ; 'software' ; The element intensities were derived from the raw data of more than one pixel by use of software. ; 'combined' ; The element intensities were derived from the raw data of more than one pixel by use of both hardware and software, as when hardware binning is used in one direction and software in the other. ; 'none' ; In the both directions, the data has not been binned. The number of pixels is equal to the number of elements. When the value of _array_intensities.pixel_binning_method is 'none' the values of _array_intensities.pixel_fast_bin_size and _array_intensities.pixel_slow_bin_size both must be 1. ; 'unspecified' ; The method used to derive element intensities is not specified. ; _item_default.value 'unspecified' save_ save__array_intensities.scaling _item_description.description ; Multiplicative scaling value to be applied to array data in the manner described by item _array_intensities.linearity. ; _item.name '_array_intensities.scaling' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.undefined_value _item_description.description ; A value to be substituted for undefined values in the data array. ; _item.name '_array_intensities.undefined_value' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.variant _item_description.description ; The value of _array_intensities.variant gives the variant to which the given array_intensities row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_array_intensities.variant' _item.category_id array_intensities _item.mandatory_code no _item_type.code code save_ ################### # ARRAY_STRUCTURE # ################### save_ARRAY_STRUCTURE _category.description ; Data items in the ARRAY_STRUCTURE category record the organization and encoding of array data that may be stored in the ARRAY_DATA category. ; _category.id array_structure _category.mandatory_code no loop_ _category_key.name '_array_structure.id' '_array_structure.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order image_1 "unsigned 16-bit integer" none little_endian ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure.byte_order _item_description.description ; The order of bytes for integer values which require more than 1 byte. (IBM-PC's and compatibles and DEC VAXs use low-byte-first ordered integers, whereas Hewlett Packard 700 series, Sun-4 and Silicon Graphics use high-byte-first ordered integers. DEC Alphas can produce/use either depending on a compiler switch.) ; _item.name '_array_structure.byte_order' _item.category_id array_structure _item.mandatory_code yes _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail 'big_endian' ; The first byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; 'little_endian' ; The last byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; save_ save__array_structure.compression_type _item_description.description ; Type of data-compression method used to compress the array data. ; _item.name '_array_structure.compression_type' _item.category_id array_structure _item.mandatory_code no _item_type.code ucode _item_default.value 'none' loop_ _item_enumeration.value _item_enumeration.detail 'byte_offset' ; Using the 'byte_offset' compression scheme as per A. Hammersley and the CBFlib manual, section 3.3.3 ; 'canonical' ; Using the 'canonical' compression scheme (International Tables for Crystallography Volume G, Section 5.6.3.1) and CBFlib manual section 3.3.1 ; 'none' ; Data are stored in normal format as defined by _array_structure.encoding_type and _array_structure.byte_order. ; 'packed' ; Using the 'packed' compression scheme, a CCP4-style packing as per J. P. Abrahams pack_c.c and CBFlib manual, section 3.3.2. ; 'packed_v2' ; Using the 'packed' compression scheme, version 2, as per J. P. Abrahams pack_c.c and CBFlib manual, section 3.3.2. ; save_ save__array_structure.compression_type_flag _item_description.description ; Flags modifying the type of data-compression method used to compress the arraydata. ; _item.name '_array_structure.compression_type_flag' _item.category_id array_structure _item.mandatory_code no _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail 'uncorrelated_sections' ; When applying packed or packed_v2 compression on an array with uncorrelated sections, do not average in points from the prior section. ; 'flat' ; When applying packed or packed_v2 compression on an array with treat the entire image as a single line set the maximum number of bits for an offset to 65 bits. The flag is included for compatibility with software prior to CBFlib_0.7.7, and should not be used for new data sets. ; save_ save__array_structure.encoding_type _item_description.description ; Data encoding of a single element of array data. The type 'unsigned 1-bit integer' is used for packed Booleans arrays for masks. Each element of the array corresponds to a single bit packed in unsigned 8-bit data. In several cases, the IEEE format is referenced. See IEEE Standard 754-1985 (IEEE, 1985). Ref: IEEE (1985). IEEE Standard for Binary Floating-Point Arithmetic. ANSI/IEEE Std 754-1985. New York: Institute of Electrical and Electronics Engineers. ; _item.name '_array_structure.encoding_type' _item.category_id array_structure _item.mandatory_code yes _item_type.code uline loop_ _item_enumeration.value 'unsigned 1-bit integer' 'unsigned 8-bit integer' 'signed 8-bit integer' 'unsigned 16-bit integer' 'signed 16-bit integer' 'unsigned 32-bit integer' 'signed 32-bit integer' 'signed 32-bit real IEEE' 'signed 64-bit real IEEE' 'signed 32-bit complex IEEE' save_ save__array_structure.id _item_description.description ; The value of _array_structure.id must uniquely identify each item of array data. This item has been made implicit and given a default value of 1 as a convenience in writing miniCBF files. Normally an explicit name with useful content should be used. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure.id' array_structure implicit '_array_data.array_id' array_data implicit '_array_structure_list.array_id' array_structure_list implicit '_array_intensities.array_id' array_intensities implicit '_diffrn_data_frame.array_id' diffrn_data_frame implicit _item_default.value 1 _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_data.array_id' '_array_structure.id' '_array_structure_list.array_id' '_array_structure.id' '_array_intensities.array_id' '_array_structure.id' '_diffrn_data_frame.array_id' '_array_structure.id' save_ save__array_structure.variant _item_description.description ; The value of _array_structure.variant gives the variant to which the given array_structure row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_array_structure.variant' _item.category_id array_structure _item.mandatory_code no _item_type.code code save_ ######################## # ARRAY_STRUCTURE_LIST # ######################## save_ARRAY_STRUCTURE_LIST _category.description ; Data items in the ARRAY_STRUCTURE_LIST category record the size and organization of each array dimension. The relationship to physical axes may be given. ; _category.id array_structure_list _category.mandatory_code no loop_ _category_key.name '_array_structure_list.array_id' '_array_structure_list.index' '_array_structure_list.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - An image array of 1300 x 1200 elements. The raster order of the image is left to right (increasing) in the first dimension and bottom to top (decreasing) in the second dimension. ; ; loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id image_1 1 1300 1 increasing ELEMENT_X image_1 2 1200 2 decreasing ELEMENY_Y ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure_list.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_structure_list.array_id' _item.category_id array_structure_list _item.mandatory_code implicit _item_type.code code save_ save__array_structure_list.axis_set_id _item_description.description ; This is a descriptor for the physical axis or set of axes corresponding to an array index. This data item is related to the axes of the detector itself given in DIFFRN_DETECTOR_AXIS, but usually differs in that the axes in this category are the axes of the coordinate system of reported data points, while the axes in DIFFRN_DETECTOR_AXIS are the physical axes of the detector describing the 'poise' of the detector as an overall physical object. If there is only one axis in the set, the identifier of that axis should be used as the identifier of the set. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.axis_set_id' array_structure_list yes '_array_structure_list_axis.axis_set_id' array_structure_list_axis implicit _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_structure_list_axis.axis_set_id' '_array_structure_list.axis_set_id' save_ save__array_structure_list.dimension _item_description.description ; The number of elements stored in the array structure in this dimension. ; _item.name '_array_structure_list.dimension' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.direction _item_description.description ; Identifies the direction in which this array index changes. ; _item.name '_array_structure_list.direction' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'increasing' ; Indicates the index changes from 1 to the maximum dimension. ; 'decreasing' ; Indicates the index changes from the maximum dimension to 1. ; save_ save__array_structure_list.index _item_description.description ; Identifies the one-based index of the row or column in the array structure. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.index' array_structure_list yes '_array_structure_list.precedence' array_structure_list yes '_array_element_size.index' array_element_size yes _item_type.code int loop_ _item_linked.child_name _item_linked.parent_name '_array_element_size.index' '_array_structure_list.index' loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.precedence _item_description.description ; Identifies the rank order in which this array index changes with respect to other array indices. The precedence of 1 indicates the index which changes fastest. ; _item.name '_array_structure_list.precedence' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.variant _item_description.description ; The value of _array_structure_list.variant gives the variant to which the given array_structure_list row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_array_structure_list.variant' _item.category_id array_structure_list _item.mandatory_code no _item_type.code code save_ ############################# # ARRAY_STRUCTURE_LIST_AXIS # ############################# save_ARRAY_STRUCTURE_LIST_AXIS _category.description ; Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe the physical settings of sets of axes for the centres of pixels that correspond to data points described in the ARRAY_STRUCTURE_LIST category. In the simplest cases, the physical increments of a single axis correspond to the increments of a single array index. More complex organizations, e.g. spiral scans, may require coupled motions along multiple axes. Note that a spiral scan uses two coupled axes: one for the angular direction and one for the radial direction. This differs from a cylindrical scan for which the two axes are not coupled into one set. ; _category.id array_structure_list_axis _category.mandatory_code no loop_ _category_key.name '_array_structure_list_axis.axis_set_id' '_array_structure_list_axis.axis_id' '_array_structure_list_axis.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' save_ save__array_structure_list_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes in the set of axes for which settings are being specified. Multiple axes may be specified for the same value of _array_structure_list_axis.axis_set_id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_array_structure_list_axis.axis_id' _item.category_id array_structure_list_axis _item.mandatory_code yes _item_type.code code save_ save__array_structure_list_axis.axis_set_id _item_description.description ; The value of this data item is the identifier of the set of axes for which axis settings are being specified. Multiple axes may be specified for the same value of _array_structure_list_axis.axis_set_id. This item is a pointer to _array_structure_list.axis_set_id in the ARRAY_STRUCTURE_LIST category. If this item is not specified, it defaults to the corresponding axis identifier. ; _item.name '_array_structure_list_axis.axis_set_id' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_type.code code save_ save__array_structure_list_axis.angle _item_description.description ; The setting of the specified axis in degrees for the first data point of the array index with the corresponding value of _array_structure_list.axis_set_id. If the index is specified as 'increasing', this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing', this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.angle' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.angle_increment _item_description.description ; The pixel-centre-to-pixel-centre increment in the angular setting of the specified axis in degrees. This is not meaningful in the case of 'constant velocity' spiral scans and should not be specified for this case. See _array_structure_list_axis.angular_pitch. ; _item.name '_array_structure_list_axis.angle_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for the first data point of the array index with the corresponding value of _array_structure_list.axis_set_id. If the index is specified as 'increasing', this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing', this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.displacement' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.fract_displacement _item_description.description ; The setting of the specified axis as a decimal fraction of the axis unit vector for the first data point of the array index with the corresponding value of _array_structure_list.axis_set_id. If the index is specified as 'increasing', this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing', this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.fract_displacement' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float save_ save__array_structure_list_axis.displacement_increment _item_description.description ; The pixel-centre-to-pixel-centre increment for the displacement setting of the specified axis in millimetres. ; _item.name '_array_structure_list_axis.displacement_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.fract_displacement_increment _item_description.description ; The pixel-centre-to-pixel-centre increment for the displacement setting of the specified axis as a decimal fraction of the axis unit vector. ; _item.name '_array_structure_list_axis.fract_displacement_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.angular_pitch _item_description.description ; The pixel-centre-to-pixel-centre distance for a one-step change in the setting of the specified axis in millimetres. This is meaningful only for 'constant velocity' spiral scans or for uncoupled angular scans at a constant radius (cylindrical scans) and should not be specified for cases in which the angle between pixels (rather than the distance between pixels) is uniform. See _array_structure_list_axis.angle_increment. ; _item.name '_array_structure_list_axis.angular_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.radial_pitch _item_description.description ; The radial distance from one 'cylinder' of pixels to the next in millimetres. If the scan is a 'constant velocity' scan with differing angular displacements between pixels, the value of this item may differ significantly from the value of _array_structure_list_axis.displacement_increment. ; _item.name '_array_structure_list_axis.radial_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.reference_angle _item_description.description ; The value of _array_structure_list_axis.reference_angle specifies the setting of the angle of this axis used for determining a reference beam center and a reference detector distance. It is normally expected to be identical to the value of _array_structure_list.angle. ; _item.name '_array_structure_list_axis.reference_angle' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.reference_displacement _item_description.description ; The value of _array_structure_list_axis.reference_displacement specifies the setting of the displacement of this axis used for determining a reference beam center and a reference detector distance. It is normally expected to be identical to the value of _array_structure_list.displacement. ; _item.name '_array_structure_list_axis.reference_displacement' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.variant _item_description.description ; The value of _array_structure_list_axis.variant gives the variant to which the given array_structure_list_axis row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_array_structure_list_axis.variant' _item.category_id array_structure_list_axis _item.mandatory_code no _item_type.code code save_ ######## # AXIS # ######## save_AXIS _category.description ; Data items in the AXIS category record the information required to describe the various goniometer, detector, source and other axes needed to specify a data collection or the axes defining the coordinate system of an image. The location of each axis is specified by two vectors: the axis itself, given by a unit vector in the direction of the axis, and an offset to the base of the unit vector. The vectors defining an axis are referenced to an appropriate coordinate system. The axis vector, itself, is a dimensionless unit vector. Where meaningful, the offset vector is given in millimetres. In coordinate systems not measured in metres, the offset is not specified and is taken as zero. The available coordinate systems are: The imgCIF standard laboratory coordinate system The direct lattice (fractional atomic coordinates) The orthogonal Cartesian coordinate system (real space) The reciprocal lattice An abstract orthogonal Cartesian coordinate frame For consistency in this discussion, we call the three coordinate system axes X, Y and Z. This is appropriate for the imgCIF standard laboratory coordinate system, and last two Cartesian coordinate systems, but for the direct lattice, X corresponds to a, Y to b and Z to c, while for the reciprocal lattice, X corresponds to a*, Y to b* and Z to c*. For purposes of visualization, all the coordinate systems are taken as right-handed, i.e., using the convention that the extended thumb of a right hand could point along the first (X) axis, the straightened pointer finger could point along the second (Y) axis and the middle finger folded inward could point along the third (Z) axis. THE IMGCIF STANDARD LABORATORY COORDINATE SYSTEM The imgCIF standard laboratory coordinate system is a right-handed orthogonal coordinate similar to the MOSFLM coordinate system, but imgCIF puts Z along the X-ray beam, rather than putting X along the X-ray beam as in MOSFLM. The vectors for the imgCIF standard laboratory coordinate system form a right-handed Cartesian coordinate system with its origin in the sample or specimen. The origin of the axis system should, if possible, be defined in terms of mechanically stable axes to be be both in the sample and in the beam. If the sample goniometer or other sample positioner has two axes the intersection of which defines a unique point at which the sample should be mounted to be bathed by the beam, that will be the origin of the axis system. If no such point is defined, then the midpoint of the line of intersection between the sample and the center of the beam will define the origin. For this definition the sample positioning system will be set at its initial reference position for the experiment. | Y (to complete right-handed system) | | | | | |________________X / principal goniometer axis / / / / /Z (to source) Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from the sample or specimen along the principal axis of the goniometer or sample positioning system if the sample positioning system has an axis that intersects the origin and which form an angle of more than 22.5 degrees with the beam axis. Axis 2 (Y): The Y-axis completes an orthogonal right-handed system defined by the X-axis and the Z-axis (see below). Axis 3 (Z): The Z-axis is derived from the source axis which goes from the sample to the source. The Z-axis is the component of the source axis in the direction of the source orthogonal to the X-axis in the plane defined by the X-axis and the source axis. If the conditions for the X-axis can be met, the coordinate system will be based on the goniometer or other sample positioning system and the beam and not on the orientation of the detector, gravity etc. The vectors necessary to specify all other axes are given by sets of three components in the order (X, Y, Z). If the axis involved is a rotation axis, it is right-handed, i.e. as one views the object to be rotated from the origin (the tail) of the unit vector, the rotation is clockwise. If a translation axis is specified, the direction of the unit vector specifies the sense of positive translation. Note: This choice of coordinate system is similar to but significantly different from the choice in MOSFLM (Leslie & Powell, 2004). In MOSFLM, X is along the X-ray beam (the CBF/imgCIF Z axis) and Z is along the rotation axis. In some experimental techniques, there is no goniometer or the principal axis of the goniometer is at a small acute angle with respect to the source axis. In such cases, other reference axes are needed to define a useful coordinate system. The order of priority in defining directions in such cases is to use the detector, then gravity, then north. If the X-axis cannot be defined as above, then the direction (not the origin) of the X-axis should be parallel to the axis of the primary detector element corresponding to the most rapidly varying dimension of that detector element's data array, with its positive sense corresponding to increasing values of the index for that dimension. If the detector is such that such a direction cannot be defined (as with a point detector) or that direction forms an angle of less than 22.5 degrees with respect to the source axis, then the X-axis should be chosen so that if the Y-axis is chosen in the direction of gravity, and the Z-axis is chosen to be along the source axis, a right-handed orthogonal coordinate system is chosen. In the case of a vertical source axis, as a last resort, the X-axis should be chosen to point North. All rotations are given in degrees and all translations are given in mm. Axes may be dependent on one another. The X-axis is the only goniometer axis the direction of which is strictly connected to the hardware. All other axes are specified by the positions they would assume when the axes upon which they depend are at their zero points. When specifying detector axes, the axis is given to the beam centre. The location of the beam centre on the detector should be given in the DIFFRN_DETECTOR category in distortion-corrected millimetres from the (0,0) corner of the detector. It should be noted that many different origins arise in the definition of an experiment. In particular, as noted above, it is necessary to specify the location of the beam centre on the detector in terms of the origin of the detector, which is, of course, not coincident with the centre of the sample. The unit cell, reciprocal cell and crystallographic orthogonal Cartesian coordinate system are defined by the CELL and the matrices in the ATOM_SITES category. THE DIRECT LATTICE (FRACTIONAL COORDINATES) The direct lattice coordinate system is a system of fractional coordinates aligned to the crystal, rather than to the laboratory. This is a natural coordinate system for maps and atomic coordinates. It is the simplest coordinate system in which to apply symmetry. The axes are determined by the cell edges, and are not necessarily othogonal. This coordinate system is not uniquely defined and depends on the cell parameters in the CELL category and the settings chosen to index the crystal. Molecules in a crystal studied by X-ray diffracraction are organized into a repeating regular array of unit cells. Each unit cell is defined by three vectors, a, b and c. To quote from Drenth, "The choice of the unit cell is not unique and therefore, guidelines have been established for selecting the standard basis vectors and the origin. They are based on symmetry and metric considerations: "(1) The axial system should be right handed. (2) The basis vectors should coincide as much as possible with directions of highest symmetry." (3) The cell taken should be the smallest one that satisfies condition (2) (4) Of all the lattice vectors, none is shorter than a. (5) Of those not directed along a, none is shorter than b. (6) Of those not lying in the ab plane, none is shorter than c. (7) The three angles between the basis vectors a, b and c are either all acute (<90\%) or all obtuse (≥90\%)." These rules do not produce a unique result that is stable under the assumption of experimental errors, and the the resulting cell may not be primitive. In this coordinate system, the vector (.5, .5, .5) is in the middle of the given unit cell. Grid coordinates are an important variation on fractional coordinates used when working with maps. In imgCIF, the conversion from fractional to grid coordinates is implicit in the array indexing specified by _array_structure_list.dimension. Note that this implicit grid-coordinate scheme is 1-based, not zero-based, i.e. the origin of the cell for axes along the cell edges with no specified _array_structure_list_axis.displacement will have grid coordinates of (1,1,1), i.e. array indices of (1,1,1). THE ORTHOGONAL CARTESIAN COORDINATE SYSTEM (REAL SPACE) The orthogonal Cartesian coordinate system is a transformation of the direct lattice to the actual physical coordinates of atoms in space. It is similar to the laboratory coordinate system, but is anchored to and moves with the crystal, rather than being schored to the laboratory. The transformation from fractional to orthogonal cartesian coordinates is given by the _atom_sites.Cartn_transf_matrix[i][j] and _atom_sites.Cartn_transf_vector[i] tags. A common choice for the matrix of the transformation is given in the 1992 PDB format document | a b cos(\g) c cos(\b) | | 0 b sin(\g) c (cos(\a) - cos(\b)cos(\g))/sin(\g) | | 0 0 V/(a b sin(\g)) | This is a convenient coordinate system in which to do fitting of models to maps and in which to understand the chemistry of a molecule. THE RECIPROCAL LATTICE The reciprocal lattice coordinate system is used for diffraction intensitities. It is based on the reciprocal cell, the dual of the cell, in which reciprocal cell edges are derived from direct cell faces: a* = bc sin(\a)/V b* = ac sin(\b)/V c* = ab sin(\g)/V cos(\a*) = (cos(\b) cos(\g) - cos(\a))/(sin(\b) sin(\g)) cos(\b*) = (cos(\a) cos(\g) - cos(\b))/(sin(\a) sin(\g)) cos(\g*) = (cos(\a) cos(\b) - cos(\g))/(sin(\a) sin(\b)) V = abc SQRT(1 - cos(\a)^2^ - cos(\b)^2^ - cos(\g)^2^ + 2 cos(\a) cos(\b) cos(\g) ) In this form the dimensions of the reciprocal lattice are in reciprocal \%Angstroms (\%A^-1^). A dimensionless form can be obtained by multiplying by the wavelength. Reflections are commonly indexed against this coordinate system as (h, k, l) triples. References: Drenth, J., "Introduction to basic crystallography." chapter 2.1 in Rossmann, M. G. and Arnold, E. "Crystallography of biological macromolecules", Volume F of the IUCr's "International tables for crystallography", Kluwer, Dordrecht 2001, pp 44 -- 63 Leslie, A. G. W. and Powell, H. (2004). MOSFLM v6.11. MRC Laboratory of Molecular Biology, Hills Road, Cambridge, England. http://www.CCP4.ac.uk/dist/X-windows/Mosflm/. Stout, G. H. and Jensen, L. H., "X-ray structure determination", 2nd ed., Wiley, New York, 1989, 453 pp. __, "PROTEIN DATA BANK ATOMIC COORDINATE AND BIBLIOGRAPHIC ENTRY FORMAT DESCRIPTION," Brookhaven National Laboratory, February 1992. ; _category.id axis _category.mandatory_code no loop_ _category_key.name '_axis.id' '_axis.equipment' '_axis.variant' loop_ _category_group.id 'inclusive_group' 'axis_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows the axis specification of the axes of a kappa- geometry goniometer [see Stout, G. H. & Jensen, L. H. (1989). X-ray structure determination. A practical guide, 2nd ed. p. 134. New York: Wiley Interscience]. There are three axes specified, and no offsets. The outermost axis, omega, is pointed along the X axis. The next innermost axis, kappa, is at a 50 degree angle to the X axis, pointed away from the source. The innermost axis, phi, aligns with the X axis when omega and phi are at their zero points. If T-omega, T-kappa and T-phi are the transformation matrices derived from the axis settings, the complete transformation would be: X' = (T-omega) (T-kappa) (T-phi) X ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] omega rotation goniometer . 1 0 0 kappa rotation goniometer omega -.64279 0 -.76604 phi rotation goniometer kappa 1 0 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - This example shows the axis specification of the axes of a detector, source and gravity. The order has been changed as a reminder that the ordering of presentation of tokens is not significant. The centre of rotation of the detector has been taken to be 68 millimetres in the direction away from the source. ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] source . source . 0 0 1 . . . gravity . gravity . 0 -1 0 . . . tranz translation detector rotz 0 0 1 0 0 -68 twotheta rotation detector . 1 0 0 . . . roty rotation detector twotheta 0 1 0 0 0 -68 rotz rotation detector roty 0 0 1 0 0 -68 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 3 - This example show the axis specification of the axes for a map, using fractional coordinates. Each cell edge has been divided into a grid of 50 divisions in the ARRAY_STRUCTURE_LIST_AXIS category. The map is using only the first octant of the grid in the ARRAY_STRUCTURE_LIST category. The fastest changing axis is the gris along A, then along B, and the slowest is along C. The map sampling is being done in the middle of each grid division ; ; loop_ _axis.id _axis.system _axis.vector[1] _axis.vector[2] _axis.vector[3] CELL_A_AXIS fractional 1 0 0 CELL_B_AXIS fractional 0 1 0 CELL_C_AXIS fractional 0 0 1 loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_id MAP 1 25 1 increasing CELL_A_AXIS MAP 1 25 2 increasing CELL_B_AXIS MAP 1 25 3 increasing CELL_C_AXIS loop_ _array_structure_list_axis.axis_id _array_structure_list_axis.fract_displacement _array_structure_list_axis.fract_displacement_increment CELL_A_AXIS 0.01 0.02 CELL_B_AXIS 0.01 0.02 CELL_C_AXIS 0.01 0.02 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 4 - This example show the axis specification of the axes for a map, this time as orthogonal \%Angstroms, using the same coordinate system as for the atomic coordinates. The map is sampling every 1.5 \%Angstroms (1.5e-7 millimeters) in a map segment 37.5 \%Angstroms on a side. ; ; loop_ _axis.id _axis.system _axis.vector[1] _axis.vector[2] _axis.vector[3] X orthogonal 1 0 0 Y orthogonal 0 1 0 Z orthogonal 0 0 1 loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_id MAP 1 25 1 increasing X MAP 2 25 2 increasing Y MAP 3 25 3 increasing Z loop_ _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment X 7.5e-8 1.5e-7 Y 7.5e-8 1.5e-7 Z 7.5e-8 1.5e-7 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__axis.depends_on _item_description.description ; The value of _axis.depends_on specifies the next outermost axis upon which this axis depends. This item is a pointer to _axis.id in the same category. ; _item.name '_axis.depends_on' _item.category_id axis _item.mandatory_code no save_ save__axis.equipment _item_description.description ; The value of _axis.equipment specifies the type of equipment using the axis: 'goniometer', 'detector', 'gravity', 'source' or 'general'. ; _item.name '_axis.equipment' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail goniometer 'equipment used to orient or position samples' detector 'equipment used to detect reflections' general 'equipment used for general purposes' gravity 'axis specifying the downward direction' source 'axis specifying the direction sample to source' save_ save__axis.offset[1] _item_description.description ; The [1] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[2] _item_description.description ; The [2] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[3] _item_description.description ; The [3] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.id _item_description.description ; The value of _axis.id must uniquely identify each axis relevant to the experiment. Note that multiple pieces of equipment may share the same axis (e.g. a twotheta arm), so the category key for AXIS also includes the equipment. ; loop_ _item.name _item.category_id _item.mandatory_code '_axis.id' axis yes '_array_structure_list_axis.axis_id' array_structure_list_axis yes '_diffrn_detector_axis.axis_id' diffrn_detector_axis yes '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes '_diffrn_scan_axis.axis_id' diffrn_scan_axis yes '_diffrn_scan_frame_axis.axis_id' diffrn_scan_frame_axis yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_axis.depends_on' '_axis.id' '_array_structure_list_axis.axis_id' '_axis.id' '_diffrn_detector_axis.axis_id' '_axis.id' '_diffrn_measurement_axis.axis_id' '_axis.id' '_diffrn_scan_axis.axis_id' '_axis.id' '_diffrn_scan_frame_axis.axis_id' '_axis.id' save_ save__axis.system _item_description.description ; The value of _axis.system specifies the coordinate system used to define the axis: 'laboratory', 'direct', 'orthogonal', 'reciprocal' or 'abstract'. ; _item.name '_axis.system' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value laboratory loop_ _item_enumeration.value _item_enumeration.detail laboratory ; the axis is referenced to the imgCIF standard laboratory Cartesian coordinate system ; direct ; the axis is referenced to the direct lattice ; orthogonal ; the axis is referenced to the cell Cartesian orthogonal coordinates ; reciprocal ; the axis is referenced to the reciprocal lattice ; abstract ; the axis is referenced to abstract Cartesian cooridinate system ; save_ save__axis.type _item_description.description ; The value of _axis.type specifies the type of axis: 'rotation' or 'translation' (or 'general' when the type is not relevant, as for gravity). ; _item.name '_axis.type' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail rotation 'right-handed axis of rotation' translation 'translation in the direction of the axis' general 'axis for which the type is not relevant' save_ save__axis.vector[1] _item_description.description ; The [1] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[2] _item_description.description ; The [2] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[3] _item_description.description ; The [3] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.variant _item_description.description ; The value of _axis.variant gives the variant to which the given axis row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_axis.variant' _item.category_id axis _item.mandatory_code no _item_type.code code save_ ##################### # DIFFRN_DATA_FRAME # ##################### save_DIFFRN_DATA_FRAME _category.description ; Data items in the DIFFRN_DATA_FRAME category record the details about each frame of data. The items in this category were previously in a DIFFRN_FRAME_DATA category, which is now deprecated. The items from the old category are provided as aliases but should not be used for new work. ; _category.id diffrn_data_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_data_frame.id' '_diffrn_data_frame.detector_element_id' '_diffrn_data_frame.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A frame containing data from 4 frame elements. Each frame element has a common array configuration 'array_1' described in ARRAY_STRUCTURE and related categories. The data for each detector element are stored in four groups of binary data in the ARRAY_DATA category, linked by the array_id and binary_id. ; ; loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id frame_1 d1_ccd_1 array_1 1 frame_1 d1_ccd_2 array_1 2 frame_1 d1_ccd_3 array_1 3 frame_1 d1_ccd_4 array_1 4 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_data_frame.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_diffrn_data_frame.array_id' _item.category_id diffrn_data_frame _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_frame_data.array_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_diffrn_data_frame.binary_id' _item.category_id diffrn_data_frame _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_frame_data.binary_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code int save_ save__diffrn_data_frame.center_fast _item_description.description ; The value of _diffrn_data_frame.center_fast is the fast index axis beam center position relative to the detector element face in the units specified in the data item '_diffrn_data_frame.center_units' along the fast axis of the detector from the center of the first pixel to the point at which the Z-axis (which should be colinear with the beam) intersects the face of the detector, if in fact is does. At the time of the measurement the current setting of detector positioner given frame are used. It is important to note that for measurements in millimetres, the sense of the axis is used, rather than the sign of the pixel-to-pixel increments. ; _item.name '_diffrn_data_frame.center_fast' _item.category_id diffrn_data_frame _item.mandatory_code no _item_type.code float save_ save__diffrn_data_frame.center_slow _item_description.description ; The value of _diffrn_data_frame.center_slow is the slow index axis beam center position relative to the detector element face in the units specified in the data item '_diffrn_data_frame.center_units' along the slow axis of the detector from the center of the first pixel to the point at which the Z-axis (which should be colinear with the beam) intersects the face of the detector, if in fact is does. At the time of the measurement the current setting of detector positioner given frame are used. It is important to note that the sense of the axis is used, rather than the sign of the pixel-to-pixel increments. ; _item.name '_diffrn_data_frame.center_slow' _item.category_id diffrn_data_frame _item.mandatory_code no _item_type.code float save_ save__diffrn_data_frame.center_units _item_description.description ; The value of _diffrn_data_frame.center_units specifies the units in which the values of '_diffrn_data_frame.center_fast' and '_diffrn_data_frame.center_slow' are presented. The default is 'mm' for millimetres. The alternatives are 'pixels' and 'bins'. In all cases the center distances are measured from the center of the first pixel, i.e. in a 2x2 binning, the measuring origin is offset from the centers of the bins by one half pixel towards the first pixel. If 'bins' is specified, the data in '_array_intensities.pixel_fast_bin_size', '_array_intensities.pixel_slow_bin_size', and '_array_intensities.pixel_binning_method' is used to define the binning scheme. ; _item.name '_diffrn_data_frame.center_units' _item.category_id diffrn_data_frame _item.mandatory_code no _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail mm 'millimetres' pixels 'detector pixels' bins 'detector bins' save_ save__diffrn_data_frame.detector_element_id _item_description.description ; This item is a pointer to _diffrn_detector_element.id in the DIFFRN_DETECTOR_ELEMENT category. ; _item.name '_diffrn_data_frame.detector_element_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.detector_element_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.id _item_description.description ; The value of _diffrn_data_frame.id must uniquely identify each complete frame of data. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_data_frame.id' diffrn_data_frame yes '_diffrn_refln.frame_id' diffrn_refln yes '_diffrn_scan.frame_id_start' diffrn_scan yes '_diffrn_scan.frame_id_end' diffrn_scan yes '_diffrn_scan_frame.frame_id' diffrn_scan_frame yes '_diffrn_scan_frame_axis.frame_id' diffrn_scan_frame_axis yes '_diffrn_scan_frame_monitor.frame_id' diffrn_scan_frame_monitor implicit _item_aliases.alias_name '_diffrn_frame_data.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_refln.frame_id' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_start' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_end' '_diffrn_data_frame.id' '_diffrn_scan_frame.frame_id' '_diffrn_data_frame.id' '_diffrn_scan_frame_axis.frame_id' '_diffrn_data_frame.id' '_diffrn_scan_frame_monitor.frame_id' '_diffrn_data_frame.id' save_ save__diffrn_data_frame.details _item_description.description ; The value of _diffrn_data_frame.details should give a description of special aspects of each frame of data. This is an appropriate location in which to record information from vendor headers as presented in those headers, but it should never be used as a substitute for providing the fully parsed information within the appropriate imgCIF/CBF categories. Normally, when a conversion from a miniCBF has been done the data from '_array_data.header_convention' should be transferred to this data item and '_array_data.header_convention' should be removed. ; _item.name '_diffrn_data_frame.details' _item.category_id diffrn_data_frame _item.mandatory_code no _item_aliases.alias_name '_diffrn_frame_data.details' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.4 _item_type.code text loop_ _item_examples.case _item_examples.detail ; HEADER_BYTES = 512; DIM = 2; BYTE_ORDER = big_endian; TYPE = unsigned_short; SIZE1 = 3072; SIZE2 = 3072; PIXEL_SIZE = 0.102588; BIN = 2x2; DETECTOR_SN = 901; TIME = 29.945155; DISTANCE = 200.000000; PHI = 85.000000; OSC_START = 85.000000; OSC_RANGE = 1.000000; WAVELENGTH = 0.979381; BEAM_CENTER_X = 157.500000; BEAM_CENTER_Y = 157.500000; PIXEL SIZE = 0.102588; OSCILLATION RANGE = 1; EXPOSURE TIME = 29.9452; TWO THETA = 0; BEAM CENTRE = 157.5 157.5; ; ; Example of header information extracted from an ADSC Quantum 315 detector header by CBFlib_0.7.6. Image provided by Chris Nielsen of ADSC from a data collection at SSRL beamline 1-5. ; save_ save__diffrn_data_frame.variant _item_description.description ; The value of _diffrn_data_frame.variant gives the variant to which the given diffrn_data_frame row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_data_frame.variant' _item.category_id diffrn_data_frame _item.mandatory_code no _item_type.code code save_ ########################################################################## # The following is a restatement of the mmCIF DIFFRN_DETECTOR, # # DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for # # the CBF/imgCIF extensions # ########################################################################## ################### # DIFFRN_DETECTOR # ################### save_DIFFRN_DETECTOR _category.description ; Data items in the DIFFRN_DETECTOR category describe the detector used to measure the scattered radiation, including any analyser and post-sample collimation. ; _category.id diffrn_detector _category.mandatory_code no loop_ _category_key.name '_diffrn_detector.diffrn_id' '_diffrn_detector.id' '_diffrn_detector.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _diffrn_detector.diffrn_id 'd1' _diffrn_detector.detector 'multiwire' _diffrn_detector.type 'Siemens' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector.details _item_description.description ; A description of special aspects of the radiation detector. ; _item.name '_diffrn_detector.details' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'slow mode' save_ save__diffrn_detector.detector _item_description.description ; The general class of the radiation detector. ; _item.name '_diffrn_detector.detector' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector' cifdic.c91 1.0 '_diffrn_detector' cif_core.dic 2.0 _item_type.code text loop_ _item_examples.case 'photographic film' 'scintillation counter' 'CCD plate' 'BF~3~ counter' save_ save__diffrn_detector.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. The value of _diffrn.id uniquely defines a set of diffraction data. ; _item.name '_diffrn_detector.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector.dtime _item_description.description ; The deadtime in microseconds of the detector(s) used to measure the diffraction intensities. ; _item.name '_diffrn_detector.dtime' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector_dtime' cifdic.c91 1.0 '_diffrn_detector_dtime' cif_core.dic 2.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code microseconds save_ save__diffrn_detector.id _item_description.description ; The value of _diffrn_detector.id must uniquely identify each detector used to collect each diffraction data set. If the value of _diffrn_detector.id is not given, it is implicitly equal to the value of _diffrn_detector.diffrn_id. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector.id' diffrn_detector implicit '_diffrn_detector_axis.detector_id' diffrn_detector_axis yes '_diffrn_scan_frame_monitor.detector_id' _diffrn_scan_frame_monitor.detector_id yes loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_detector_axis.detector_id' '_diffrn_detector.id' '_diffrn_scan_frame_monitor.detector_id' '_diffrn_detector.id' _item_type.code code save_ save__diffrn_detector.number_of_axes _item_description.description ; The value of _diffrn_detector.number_of_axes gives the number of axes of the positioner for the detector identified by _diffrn_detector.id. The word 'positioner' is a general term used in instrumentation design for devices that are used to change the positions of portions of apparatus by linear translation, rotation or combinations of such motions. Axes which are used to provide a coordinate system for the face of an area detetctor should not be counted for this data item. The description of each axis should be provided by entries in DIFFRN_DETECTOR_AXIS. ; _item.name '_diffrn_detector.number_of_axes' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_detector.type _item_description.description ; The make, model or name of the detector device used. ; _item.name '_diffrn_detector.type' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__diffrn_detector.variant _item_description.description ; The value of _diffrn_detector.variant gives the variant to which the given diffrn_detector row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_detector.variant' _item.category_id diffrn_detector _item.mandatory_code no _item_type.code code save_ ######################## # DIFFRN_DETECTOR_AXIS # ######################## save_DIFFRN_DETECTOR_AXIS _category.description ; Data items in the DIFFRN_DETECTOR_AXIS category associate axes with detectors. ; _category.id diffrn_detector_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_axis.detector_id' '_diffrn_detector_axis.axis_id' '_diffrn_detector_axis.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_detector_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_detector_axis.axis_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_axis.detector_id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. This item was previously named _diffrn_detector_axis.id which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_detector_axis.detector_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_aliases.alias_name '_diffrn_detector_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_detector_axis.variant _item_description.description ; The value of _diffrn_detector_axis.variant gives the variant to which the given diffrn_detector_axis row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_detector_axis.variant' _item.category_id diffrn_detector_axis _item.mandatory_code no _item_type.code code save_ ########################### # DIFFRN_DETECTOR_ELEMENT # ########################### save_DIFFRN_DETECTOR_ELEMENT _category.description ; Data items in the DIFFRN_DETECTOR_ELEMENT category record the details about spatial layout and other characteristics of each element of a detector which may have multiple elements. In most cases, giving more detailed information in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS is preferable to simply providing the centre of the detector element. ; _category.id diffrn_detector_element _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_element.id' '_diffrn_detector_element.detector_id' '_diffrn_detector_element.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Detector d1 is composed of four CCD detector elements, each 200 mm by 200 mm, arranged in a square, in the pattern 1 2 * 3 4 Note that the beam centre is slightly displaced from each of the detector elements, just beyond the lower right corner of 1, the lower left corner of 2, the upper right corner of 3 and the upper left corner of 4. For each element, the detector face coordiate system, is assumed to have the fast axis running from left to right and the slow axis running from top to bottom with the origin at the top left corner. ; ; loop_ _diffrn_detector_element.detector_id _diffrn_detector_element.id _diffrn_detector_element.reference_center_fast _diffrn_detector_element.reference_center_slow _diffrn_detector_element.reference_center_units d1 d1_ccd_1 201.5 201.5 mm d1 d1_ccd_2 -1.8 201.5 mm d1 d1_ccd_3 201.6 -1.4 mm d1 d1_ccd_4 -1.7 -1.5 mm ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector_element.id _item_description.description ; The value of _diffrn_detector_element.id must uniquely identify each element of a detector. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector_element.id' diffrn_detector_element yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.detector_element_id' '_diffrn_detector_element.id' save_ save__diffrn_detector_element.detector_id _item_description.description ; This item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. ; _item.name '_diffrn_detector_element.detector_id' _item.category_id diffrn_detector_element _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_element.reference_center_fast _item_description.description ; The value of _diffrn_detector_element.reference_center_fast is the fast index axis beam center position relative to the detector element face in the units specified in the data item '_diffrn_detector_element.reference_center_units' along the fast axis of the detector from the center of the first pixel to the point at which the Z-axis (which should be colinear with the beam) intersects the face of the detector, if in fact is does. At the time of the measurement all settings of the detector positioner should be at their reference settings. If more than one reference setting has been used the value given whould be representive of the beam center as determined from the ensemble of settings. It is important to note that for measurements in millimetres, the sense of the axis is used, rather than the sign of the pixel-to-pixel increments. ; _item.name '_diffrn_detector_element.reference_center_fast' _item.category_id diffrn_detector_element _item.mandatory_code no _item_type.code float save_ save__diffrn_detector_element.reference_center_slow _item_description.description ; The value of _diffrn_detector_element.reference_center_slow is the slow index axis beam center position relative to the detector element face in the units specified in the data item '_diffrn_detector_element.reference_center_units' along the slow axis of the detector from the center of the first pixel to the point at which the Z-axis (which should be colinear with the beam) intersects the face of the detector, if in fact is does. At the time of the measurement all settings of the detector positioner should be at their reference settings. If more than one reference setting has been used the value givien whould be representive of the beam center as determined from the ensemble of settings. It is important to note that the sense of the axis is used, rather than the sign of the pixel-to-pixel increments. ; _item.name '_diffrn_detector_element.reference_center_slow' _item.category_id diffrn_detector_element _item.mandatory_code no _item_type.code float save_ save__diffrn_detector_element.reference_center_units _item_description.description ; The value of _diffrn_detector_element.reference_center_units specifies the units in which the values of '_diffrn_detector_element.reference_center_fast' and '_diffrn_detector_element.reference_center_slow' are presented. The default is 'mm' for millimetres. The alternatives are 'pixels' and 'bins'. In all cases the center distances are measured from the center of the first pixel, i.e. in a 2x2 binning, the measuring origin is offset from the centers of the bins by one half pixel towards the first pixel. If 'bins' is specified, the data in '_array_intensities.pixel_fast_bin_size', '_array_intensities.pixel_slow_bin_size', and '_array_intensities.pixel_binning_method' is used to define the binning scheme. ; _item.name '_diffrn_detector_element.reference_center_units' _item.category_id diffrn_detector_element _item.mandatory_code no _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail mm 'millimetres' pixels 'detector pixels' bins 'detector bins' save_ save__diffrn_detector_element.variant _item_description.description ; The value of _diffrn_detector_element.variant gives the variant to which the given diffrn_detector_element row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_detector_element.variant' _item.category_id diffrn_detector_element _item.mandatory_code no _item_type.code code save_ ######################## ## DIFFRN_MEASUREMENT ## ######################## save_DIFFRN_MEASUREMENT _category.description ; Data items in the DIFFRN_MEASUREMENT category record details about the device used to orient and/or position the crystal during data measurement and the manner in which the diffraction data were measured. ; _category.id diffrn_measurement _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement.device' '_diffrn_measurement.diffrn_id' '_diffrn_measurement.id' '_diffrn_measurement.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_measurement.diffrn_id 'd1' _diffrn_measurement.device '3-circle camera' _diffrn_measurement.device_type 'Supper model X' _diffrn_measurement.device_details 'none' _diffrn_measurement.method 'omega scan' _diffrn_measurement.details ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _diffrn_measurement.diffrn_id 's1' _diffrn_measurement.device_type 'Philips PW1100/20 diffractometer' _diffrn_measurement.method 'theta/2theta (\q/2\q)' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_measurement.device _item_description.description ; The general class of goniometer or device used to support and orient the specimen. If the value of _diffrn_measurement.device is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id. Either _diffrn_measurement.device or _diffrn_measurement.id may be used to link to other categories. If the experimental setup admits multiple devices, then _diffrn_measurement.id is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.device' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_device' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement.device' _item_aliases.alias_name '_diffrn_measurement_device' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '3-circle camera' '4-circle camera' 'kappa-geometry camera' 'oscillation camera' 'precession camera' save_ save__diffrn_measurement.device_details _item_description.description ; A description of special aspects of the device used to measure the diffraction intensities. ; _item.name '_diffrn_measurement.device_details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; commercial goniometer modified locally to allow for 90\% \t arc ; save_ save__diffrn_measurement.device_type _item_description.description ; The make, model or name of the measurement device (goniometer) used. ; _item.name '_diffrn_measurement.device_type' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Supper model q' 'Huber model r' 'Enraf-Nonius model s' 'home-made' save_ save__diffrn_measurement.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_measurement.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement.details _item_description.description ; A description of special aspects of the intensity measurement. ; _item.name '_diffrn_measurement.details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; save_ save__diffrn_measurement.id _item_description.description ; The value of _diffrn_measurement.id must uniquely identify the set of mechanical characteristics of the device used to orient and/or position the sample used during the collection of each diffraction data set. If the value of _diffrn_measurement.id is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id. Either _diffrn_measurement.device or _diffrn_measurement.id may be used to link to other categories. If the experimental setup admits multiple devices, then _diffrn_measurement.id is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.id' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_id' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement.id' _item_type.code code save_ save__diffrn_measurement.method _item_description.description ; Method used to measure intensities. ; _item.name '_diffrn_measurement.method' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_method' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'profile data from theta/2theta (\q/2\q) scans' save_ save__diffrn_measurement.number_of_axes _item_description.description ; The value of _diffrn_measurement.number_of_axes gives the number of axes of the positioner for the goniometer or other sample orientation or positioning device identified by _diffrn_measurement.id. The description of the axes should be provided by entries in DIFFRN_MEASUREMENT_AXIS. ; _item.name '_diffrn_measurement.number_of_axes' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ # _diffrn_measurement.sample_detector_distance # _diffrn_measurement.sample_detector_voffset save__diffrn_measurement.sample_detector_distance _item_description.description ; The value of _diffrn_measurement.sample_detector_distance gives the unsigned distance in millimetres from the sample to the detector along the beam. ; _item.name '_diffrn_measurement.sample_detector_distance' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 _item_type.code float _item_units.code mm save_ save__diffrn_measurement.sample_detector_voffset _item_description.description ; The value of _diffrn_measurement.sample_detector_voffset gives the signed distance in millimetres in the vertical direction (positive for up) from the center of the beam to the center of the detector. ; _item.name '_diffrn_measurement.sample_detector_voffset' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . . . . _item_type.code float _item_units.code mm save_ save__diffrn_measurement.specimen_support _item_description.description ; The physical device used to support the crystal during data collection. ; _item.name '_diffrn_measurement.specimen_support' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_specimen_support' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'glass capillary' 'quartz capillary' 'fiber' 'metal loop' save_ save__diffrn_measurement.variant _item_description.description ; The value of _diffrn_measurement.variant gives the variant to which the given diffrn_measurement row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_measurement.variant' _item.category_id diffrn_measurement _item.mandatory_code no _item_type.code code save_ ########################### # DIFFRN_MEASUREMENT_AXIS # ########################### save_DIFFRN_MEASUREMENT_AXIS _category.description ; Data items in the DIFFRN_MEASUREMENT_AXIS category associate axes with goniometers. ; _category.id diffrn_measurement_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement_axis.axis_id' '_diffrn_measurement_axis.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_measurement_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_measurement_axis.axis_id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.measurement_device _item_description.description ; This data item is a pointer to _diffrn_measurement.device in the DIFFRN_MEASUREMENT category. ; _item.name '_diffrn_measurement_axis.measurement_device' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit _item_type.code text save_ save__diffrn_measurement_axis.measurement_id _item_description.description ; This data item is a pointer to _diffrn_measurement.id in the DIFFRN_MEASUREMENT category. This item was previously named _diffrn_measurement_axis.id, which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_measurement_axis.measurement_id' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_measurement_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_measurement_axis.variant _item_description.description ; The value of _diffrn_measurement_axis.variant gives the variant to which the given diffrn_measurement_axis row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_measurement_axis.variant' _item.category_id diffrn_measurement_axis _item.mandatory_code no _item_type.code code save_ #################### # DIFFRN_RADIATION # #################### save_DIFFRN_RADIATION _category.description ; Data items in the DIFFRN_RADIATION category describe the radiation used for measuring diffraction intensities, its collimation and monochromatization before the sample. Post-sample treatment of the beam is described by data items in the DIFFRN_DETECTOR category. ; _category.id diffrn_radiation _category.mandatory_code no loop_ _category_key.name '_diffrn_radiation.diffrn_id' '_diffrn_radiation.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_radiation.diffrn_id 'set1' _diffrn_radiation.collimation '0.3 mm double pinhole' _diffrn_radiation.monochromator 'graphite' _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.wavelength_id 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _diffrn_radiation.wavelength_id 1 _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.monochromator 'graphite' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_radiation.collimation _item_description.description ; The collimation or focusing applied to the radiation. ; _item.name '_diffrn_radiation.collimation' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_collimation' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '0.3 mm double-pinhole' '0.5 mm' 'focusing mirrors' save_ save__diffrn_radiation.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_radiation.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_radiation.div_x_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory X axis (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the standard uncertainty (e.s.d.) of the directions of photons in the XZ plane around the mean source beam direction. Note that for some synchrotrons this value is specified in milliradians, in which case a conversion is needed. To convert a value in milliradians to a value in degrees, multiply by 0.180 and divide by \p. ; _item.name '_diffrn_radiation.div_x_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.div_y_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory Y axis (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the standard uncertainty (e.s.d.) of the directions of photons in the YZ plane around the mean source beam direction. Note that for some synchrotrons this value is specified in milliradians, in which case a conversion is needed. To convert a value in milliradians to a value in degrees, multiply by 0.180 and divide by \p. ; _item.name '_diffrn_radiation.div_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.div_x_y_source _item_description.description ; Beam crossfire correlation degrees^2^ between the crossfire laboratory X-axis component and the crossfire laboratory Y-axis component (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the mean of the products of the deviations of the direction of each photon in XZ plane times the deviations of the direction of the same photon in the YZ plane around the mean source beam direction. This will be zero for uncorrelated crossfire. Note that some synchrotrons, this value is specified in milliradians^2^, in which case a conversion would be needed. To go from a value in milliradians^2^ to a value in degrees^2^, multiply by 0.180^2^ and divide by \p^2^. ; _item.name '_diffrn_radiation.div_x_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees_squared _item_default.value 0.0 save_ save__diffrn_radiation.filter_edge _item_description.description ; Absorption edge in \%Angstroms of the radiation filter used. ; _item.name '_diffrn_radiation.filter_edge' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_filter_edge' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__diffrn_radiation.inhomogeneity _item_description.description ; Half-width in millimetres of the incident beam in the direction perpendicular to the diffraction plane. ; _item.name '_diffrn_radiation.inhomogeneity' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_inhomogeneity' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code millimetres save_ save__diffrn_radiation.monochromator _item_description.description ; The method used to obtain monochromatic radiation. If a monochromator crystal is used, the material and the indices of the Bragg reflection are specified. ; _item.name '_diffrn_radiation.monochromator' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_monochromator' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Zr filter' 'Ge 220' 'none' 'equatorial mounted graphite' save_ save__diffrn_radiation.polarisn_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the perpendicular component of the polarization and the diffraction plane. See _diffrn_radiation_polarisn_ratio. ; _item.name '_diffrn_radiation.polarisn_norm' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_norm' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.polarisn_ratio _item_description.description ; Polarization ratio of the diffraction beam incident on the crystal. This is the ratio of the perpendicularly polarized to the parallel polarized component of the radiation. The perpendicular component forms an angle of _diffrn_radiation.polarisn_norm to the normal to the diffraction plane of the sample (i.e. the plane containing the incident and reflected beams). ; _item.name '_diffrn_radiation.polarisn_ratio' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_ratio' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__diffrn_radiation.polarizn_source_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the normal to the polarization plane and the laboratory Y axis as defined in the AXIS category. Note that this is the angle of polarization of the source photons, either directly from a synchrotron beamline or from a monochromater. This differs from the value of _diffrn_radiation.polarisn_norm in that _diffrn_radiation.polarisn_norm refers to polarization relative to the diffraction plane rather than to the laboratory axis system. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane should be taken as the XZ plane and the angle as 0. See _diffrn_radiation.polarizn_source_ratio. ; _item.name '_diffrn_radiation.polarizn_source_norm' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.polarizn_source_ratio _item_description.description ; (Ip-In)/(Ip+In), where Ip is the intensity (amplitude squared) of the electric vector in the plane of polarization and In is the intensity (amplitude squared) of the electric vector in the plane of the normal to the plane of polarization. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane is to be taken as the XZ plane and the normal is parallel to the Y axis. Thus, if there was complete polarization in the plane of polarization, the value of _diffrn_radiation.polarizn_source_ratio would be 1, and for an unpolarized beam _diffrn_radiation.polarizn_source_ratio would have a value of 0. If the X axis has been chosen to lie in the plane of polarization, this definition will agree with the definition of 'MONOCHROMATOR' in the Denzo glossary, and values of near 1 should be expected for a bending-magnet source. However, if the X axis were perpendicular to the polarization plane (not a common choice), then the Denzo value would be the negative of _diffrn_radiation.polarizn_source_ratio. See http://www.hkl-xray.com for information on Denzo and Otwinowski & Minor (1997). This differs both in the choice of ratio and choice of orientation from _diffrn_radiation.polarisn_ratio, which, unlike _diffrn_radiation.polarizn_source_ratio, is unbounded. Reference: Otwinowski, Z. & Minor, W. (1997). 'Processing of X-ray diffraction data collected in oscillation mode.' Methods Enzymol. 276, 307-326. ; _item.name '_diffrn_radiation.polarizn_source_ratio' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 -1.0 -1.0 -1.0 _item_type.code float save_ save__diffrn_radiation.probe _item_description.description ; Name of the type of radiation used. It is strongly recommended that this be given so that the probe radiation is clearly specified. ; _item.name '_diffrn_radiation.probe' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_probe' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value 'X-ray' 'neutron' 'electron' 'gamma' save_ save__diffrn_radiation.type _item_description.description ; The nature of the radiation. This is typically a description of the X-ray wavelength in Siegbahn notation. ; _item.name '_diffrn_radiation.type' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'CuK\a' 'Cu K\a~1~' 'Cu K-L~2,3~' 'white-beam' save_ save__diffrn_radiation.xray_symbol _item_description.description ; The IUPAC symbol for the X-ray wavelength for the probe radiation. ; _item.name '_diffrn_radiation.xray_symbol' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_xray_symbol' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value _item_enumeration.detail 'K-L~3~' 'K\a~1~ in older Siegbahn notation' 'K-L~2~' 'K\a~2~ in older Siegbahn notation' 'K-M~3~' 'K\b~1~ in older Siegbahn notation' 'K-L~2,3~' 'use where K-L~3~ and K-L~2~ are not resolved' save_ save__diffrn_radiation.wavelength_id _item_description.description ; This data item is a pointer to _diffrn_radiation_wavelength.id in the DIFFRN_RADIATION_WAVELENGTH category. ; _item.name '_diffrn_radiation.wavelength_id' _item.category_id diffrn_radiation _item.mandatory_code yes _item_type.code code save_ save__diffrn_radiation.variant _item_description.description ; The value of _diffrn_radiation.variant gives the variant to which the given diffrn_radiation row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_radiation.variant' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code code save_ ################ # DIFFRN_REFLN # ################ save_DIFFRN_REFLN _category.description ; This category redefinition has been added to extend the key of the standard DIFFRN_REFLN category. Data items in the DIFFRN_REFLN category record details about the intensities in the diffraction data set identified by _diffrn_refln.diffrn_id. The DIFFRN_REFLN data items refer to individual intensity measurements and must be included in looped lists. The DIFFRN_REFLNS data items specify the parameters that apply to all intensity measurements in the particular diffraction data set identified by _diffrn_reflns.diffrn_id and _diffrn_refln.frame_id ; ; _category.id diffrn_refln _category.mandatory_code no loop_ _category_key.name '_diffrn_refln.diffrn_id' '_diffrn_refln.id' '_diffrn_refln.frame_id' '_diffrn_refln.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_refln.frame_id _item_description.description ; This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_refln.frame_id' _item.category_id diffrn_refln _item.mandatory_code yes _item_type.code code save_ save__diffrn_refln.variant _item_description.description ; The value of _diffrn_refln.variant gives the variant to which the given diffrn_refln row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_refln.variant' _item.category_id diffrn_refln _item.mandatory_code no _item_type.code code save_ ############### # DIFFRN_SCAN # ############### save_DIFFRN_SCAN _category.description ; Data items in the DIFFRN_SCAN category describe the parameters of one or more scans, relating axis positions to frames. ; _category.id diffrn_scan _category.mandatory_code no loop_ _category_key.name '_diffrn_scan.id' '_diffrn_scan.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - derived from a suggestion by R. M. Sweet. The vector of each axis is not given here, because it is provided in the AXIS category. By making _diffrn_scan_axis.scan_id and _diffrn_scan_axis.axis_id keys of the DIFFRN_SCAN_AXIS category, an arbitrary number of scanning and fixed axes can be specified for a scan. In this example, three rotation axes and one translation axis at nonzero values are specified, with one axis stepping. There is no reason why more axes could not have been specified to step. Range information has been specified, but note that it can be calculated from the number of frames and the increment, so the data item _diffrn_scan_axis.angle_range could be dropped. Both the sweep data and the data for a single frame are specified. Note that the information on how the axes are stepped is given twice, once in terms of the overall averages in the value of _diffrn_scan.integration_time and the values for DIFFRN_SCAN_AXIS, and precisely for the given frame in the value for _diffrn_scan_frame.integration_time and the values for DIFFRN_SCAN_FRAME_AXIS. If dose-related adjustments are made to scan times and nonlinear stepping is done, these values may differ. Therefore, in interpreting the data for a particular frame it is important to use the frame-specific data. ; ; _diffrn_scan.id 1 _diffrn_scan.date_start '2001-11-18T03:26:42' _diffrn_scan.date_end '2001-11-18T03:36:45' _diffrn_scan.integration_time 3.0 _diffrn_scan.frame_id_start mad_L2_000 _diffrn_scan.frame_id_end mad_L2_200 _diffrn_scan.frames 201 loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment 1 omega 200.0 20.0 0.1 . . . 1 kappa -40.0 0.0 0.0 . . . 1 phi 127.5 0.0 0.0 . . . 1 tranz . . . 2.3 0.0 0.0 _diffrn_scan_frame.scan_id 1 _diffrn_scan_frame.date '2001-11-18T03:27:33' _diffrn_scan_frame.integration_time 3.0 _diffrn_scan_frame.frame_id mad_L2_018 _diffrn_scan_frame.frame_number 18 loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.angle_increment _diffrn_scan_frame_axis.displacement _diffrn_scan_frame_axis.displacement_increment mad_L2_018 omega 201.8 0.1 . . mad_L2_018 kappa -40.0 0.0 . . mad_L2_018 phi 127.5 0.0 . . mad_L2_018 tranz . . 2.3 0.0 ; ; Example 2 - a more extensive example (R. M. Sweet, P. J. Ellis & H. J. Bernstein). A detector is placed 240 mm along the Z axis from the goniometer. This leads to a choice: either the axes of the detector are defined at the origin, and then a Z setting of -240 is entered, or the axes are defined with the necessary Z offset. In this case, the setting is used and the offset is left as zero. This axis is called DETECTOR_Z. The axis for positioning the detector in the Y direction depends on the detector Z axis. This axis is called DETECTOR_Y. The axis for positioning the detector in the X direction depends on the detector Y axis (and therefore on the detector Z axis). This axis is called DETECTOR_X. This detector may be rotated around the Y axis. This rotation axis depends on the three translation axes. It is called DETECTOR_PITCH. A coordinate system is defined on the face of the detector in terms of 2300 0.150 mm pixels in each direction. The ELEMENT_X axis is used to index the first array index of the data array and the ELEMENT_Y axis is used to index the second array index. Because the pixels are 0.150mm X 0.150mm, the centre of the first pixel is at (0.075, 0.075) in this coordinate system. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 172.43 -172.43 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 2300 1 increasing ELEMENT_X ARRAY1 2 2300 2 increasing ELEMENT_Y # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.075 0.150 ELEMENT_Y ELEMENT_Y 0.075 0.150 # category ARRAY_ELEMENT_SIZE loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 ARRAY1 2 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; ; Example 3 - Example 2 revised for a spiral scan (R. M. Sweet, P. J. Ellis & H. J. Bernstein). A detector is placed 240 mm along the Z axis from the goniometer, as in Example 2 above, but in this example the image plate is scanned in a spiral pattern from the outside edge in. The axis for positioning the detector in the Y direction depends on the detector Z axis. This axis is called DETECTOR_Y. The axis for positioning the detector in the X direction depends on the detector Y axis (and therefore on the detector Z axis). This axis is called DETECTOR_X. This detector may be rotated around the Y axis. This rotation axis depends on the three translation axes. It is called DETECTOR_PITCH. A coordinate system is defined on the face of the detector in terms of a coupled rotation axis and radial scan axis to form a spiral scan. The rotation axis is called ELEMENT_ROT and the radial axis is called ELEMENT_RAD. A 150 micrometre radial pitch and a 75 micrometre 'constant velocity' angular pitch are assumed. Indexing is carried out first on the rotation axis and the radial axis is made to be dependent on it. The two axes are coupled to form an axis set ELEMENT_SPIRAL. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_ROT translation detector DETECTOR_PITCH 0 0 1 0 0 0 ELEMENT_RAD translation detector ELEMENT_ROT 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.angle _array_structure_list_axis.displacement _array_structure_list_axis.angular_pitch _array_structure_list_axis.radial_pitch ELEMENT_SPIRAL ELEMENT_ROT 0 . 0.075 . ELEMENT_SPIRAL ELEMENT_RAD . 172.5 . -0.150 # category ARRAY_ELEMENT_SIZE # the actual pixels are 0.075 by 0.150 mm # We give the coarser dimension here. loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_scan.id _item_description.description ; The value of _diffrn_scan.id uniquely identifies each scan. The identifier is used to tie together all the information about the scan. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_scan.id' diffrn_scan yes '_diffrn_scan_axis.scan_id' diffrn_scan_axis yes '_diffrn_scan_frame.scan_id' diffrn_scan_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_scan_axis.scan_id' '_diffrn_scan.id' '_diffrn_scan_frame.scan_id' '_diffrn_scan.id' save_ save__diffrn_scan.date_end _item_description.description ; The date and time of the end of the scan. Note that this may be an estimate generated during the scan, before the precise time of the end of the scan is known. ; _item.name '_diffrn_scan.date_end' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.date_start _item_description.description ; The date and time of the start of the scan. ; _item.name '_diffrn_scan.date_start' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.integration_time _item_description.description ; Approximate average time in seconds to integrate each step of the scan. The precise time for integration of each particular step must be provided in _diffrn_scan_frame.integration_time, even if all steps have the same integration time. ; _item.name '_diffrn_scan.integration_time' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan.frame_id_start _item_description.description ; The value of this data item is the identifier of the first frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_start' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frame_id_end _item_description.description ; The value of this data item is the identifier of the last frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_end' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frames _item_description.description ; The value of this data item is the number of frames in the scan. ; _item.name '_diffrn_scan.frames' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 1 1 1 save_ save__diffrn_scan.variant _item_description.description ; The value of _diffrn_scan.variant gives the variant to which the given diffrn_scan row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_scan.variant' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code code save_ #################### # DIFFRN_SCAN_AXIS # #################### save_DIFFRN_SCAN_AXIS _category.description ; Data items in the DIFFRN_SCAN_AXIS category describe the settings of axes for particular scans. Unspecified axes are assumed to be at their zero points. ; _category.id diffrn_scan_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_axis.scan_id' '_diffrn_scan_axis.axis_id' '_diffrn_scan_axis.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_axis.scan_id _item_description.description ; The value of this data item is the identifier of the scan for which axis settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan.id. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_axis.scan_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the scan for which settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan.id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_axis.axis_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.angle_start _item_description.description ; The starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_range _item_description.description ; The range from the starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_increment _item_description.description ; The increment for each step for the specified axis in degrees. In general, this will agree with _diffrn_scan_frame_axis.angle_increment. The sum of the values of _diffrn_scan_frame_axis.angle and _diffrn_scan_frame_axis.angle_increment is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of _diffrn_scan_axis.angle_increment will be representative of the ensemble of values of _diffrn_scan_frame_axis.angle_increment (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_rstrt_incr _item_description.description ; The increment after each step for the specified axis in degrees. In general, this will agree with _diffrn_scan_frame_axis.angle_rstrt_incr. The sum of the values of _diffrn_scan_frame_axis.angle, _diffrn_scan_frame_axis.angle_increment and _diffrn_scan_frame_axis.angle_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame and should equal _diffrn_scan_frame_axis.angle for this next frame. If the individual frame values vary, then the value of _diffrn_scan_axis.angle_rstrt_incr will be representative of the ensemble of values of _diffrn_scan_frame_axis.angle_rstrt_incr (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.displacement_start _item_description.description ; The starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_range _item_description.description ; The range from the starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_increment _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with _diffrn_scan_frame_axis.displacement_increment. The sum of the values of _diffrn_scan_frame_axis.displacement and _diffrn_scan_frame_axis.displacement_increment is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of _diffrn_scan_axis.displacement_increment will be representative of the ensemble of values of _diffrn_scan_frame_axis.displacement_increment (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_rstrt_incr _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with _diffrn_scan_frame_axis.displacement_rstrt_incr. The sum of the values of _diffrn_scan_frame_axis.displacement, _diffrn_scan_frame_axis.displacement_increment and _diffrn_scan_frame_axis.displacement_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame and should equal _diffrn_scan_frame_axis.displacement for this next frame. If the individual frame values vary, then the value of _diffrn_scan_axis.displacement_rstrt_incr will be representative of the ensemble of values of _diffrn_scan_frame_axis.displacement_rstrt_incr (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.reference_angle _item_description.description ; The setting of the specified axis in degrees against which measurements of the reference beam center and reference detector distance should be made. In general, this will agree with _diffrn_scan_frame_axis.reference_angle. If the individual frame values vary, then the value of _diffrn_scan_axis.reference_angle will be representative of the ensemble of values of _diffrn_scan_frame_axis.reference_angle (e.g. the mean). If not specified, the value defaults to zero. ; _item.name '_diffrn_scan_axis.reference_angle' _item.category_id diffrn_scan_axis _item.mandatory_code implicit _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.reference_displacement _item_description.description ; The setting of the specified axis in millimetres against which measurements of the reference beam center and reference detector distance should be made. In general, this will agree with _diffrn_scan_frame_axis.reference_displacement. If the individual frame values vary, then the value of _diffrn_scan_axis.reference_displacement will be representative of the ensemble of values of _diffrn_scan_frame_axis.reference_displacement (e.g. the mean). If not specified, the value defaults to to the value of _diffrn_scan_axis.displacement. ; _item.name '_diffrn_scan_axis.reference_displacement' _item.category_id diffrn_scan_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.variant _item_description.description ; The value of _diffrn_scan_axis.variant gives the variant to which the given diffrn_scan_axis row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_scan_axis.variant' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_type.code code save_ ##################### # DIFFRN_SCAN_FRAME # ##################### save_DIFFRN_SCAN_FRAME _category.description ; Data items in the DIFFRN_SCAN_FRAME category describe the relationships of particular frames to scans. ; _category.id diffrn_scan_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame.scan_id' '_diffrn_scan_frame.frame_id' '_diffrn_scan_frame.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame.date _item_description.description ; The date and time of the start of the frame being scanned. ; _item.name '_diffrn_scan_frame.date' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan_frame.frame_id _item_description.description ; The value of this data item is the identifier of the frame being examined. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame.frame_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame.frame_number _item_description.description ; The value of this data item is the number of the frame within the scan, starting with 1. It is not necessarily the same as the value of _diffrn_scan_frame.frame_id, but it may be. ; _item.name '_diffrn_scan_frame.frame_number' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 0 0 0 save_ save__diffrn_scan_frame.integration_time _item_description.description ; The time in seconds to integrate this step of the scan. This should be the precise time of integration of each particular frame. The value of this data item should be given explicitly for each frame and not inferred from the value of _diffrn_scan.integration_time. ; _item.name '_diffrn_scan_frame.integration_time' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame.scan_id _item_description.description ; The value of _diffrn_scan_frame.scan_id identifies the scan containing this frame. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_frame.scan_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame.variant _item_description.description ; The value of _diffrn_scan_frame.variant gives the variant to which the given diffrn_scan_frame row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_scan_frame.variant' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code code save_ ########################## # DIFFRN_SCAN_FRAME_AXIS # ########################## save_DIFFRN_SCAN_FRAME_AXIS _category.description ; Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the settings of axes for particular frames. Unspecified axes are assumed to be at their zero points. If, for any given frame, nonzero values apply for any of the data items in this category, those values should be given explicitly in this category and not simply inferred from values in DIFFRN_SCAN_AXIS. ; _category.id diffrn_scan_frame_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame_axis.frame_id' '_diffrn_scan_frame_axis.axis_id' '_diffrn_scan_frame_axis.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the frame for which settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_frame_axis.axis_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_axis.angle _item_description.description ; The setting of the specified axis in degrees for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.angle' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_increment _item_description.description ; The increment for this frame for the angular setting of the specified axis in degrees. The sum of the values of _diffrn_scan_frame_axis.angle and _diffrn_scan_frame_axis.angle_increment is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.angle_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_rstrt_incr _item_description.description ; The increment after this frame for the angular setting of the specified axis in degrees. The sum of the values of _diffrn_scan_frame_axis.angle, _diffrn_scan_frame_axis.angle_increment and _diffrn_scan_frame_axis.angle_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame and should equal _diffrn_scan_frame_axis.angle for this next frame. ; _item.name '_diffrn_scan_frame_axis.angle_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.displacement' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_increment _item_description.description ; The increment for this frame for the displacement setting of the specified axis in millimetres. The sum of the values of _diffrn_scan_frame_axis.displacement and _diffrn_scan_frame_axis.displacement_increment is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.displacement_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_rstrt_incr _item_description.description ; The increment for this frame for the displacement setting of the specified axis in millimetres. The sum of the values of _diffrn_scan_frame_axis.displacement, _diffrn_scan_frame_axis.displacement_increment and _diffrn_scan_frame_axis.displacement_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame and should equal _diffrn_scan_frame_axis.displacement for this next frame. ; _item.name '_diffrn_scan_frame_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.frame_id _item_description.description ; The value of this data item is the identifier of the frame for which axis settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame_axis.frame_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_axis.reference_angle _item_description.description ; The setting of the specified axis in degrees against which measurements of the reference beam center and reference detector distance should be made. This is normally the same for all frames, but the option is provided here of making changes when needed. If not provided, it is assumed to be zero. ; _item.name '_diffrn_scan_frame_axis.reference_angle' _item.category_id diffrn_scan_frame_axis _item.mandatory_code implicit _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.reference_displacement _item_description.description ; The setting of the specified axis in millimetres for this frame against which measurements of the reference beam center and reference detector distance should be made. This is normally the same for all frames, but the option is provided here of making changes when needed. If not provided, it is assumed to be equal to _diffrn_scan_frame_axis.displacement. ; _item.name '_diffrn_scan_frame_axis.reference_displacement' _item.category_id diffrn_scan_frame_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.variant _item_description.description ; The value of _diffrn_scan_frame_axis.variant gives the variant to which the given diffrn_scan_frame_axis row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_scan_frame_axis.variant' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_type.code code save_ ############################# # DIFFRN_SCAN_FRAME_MONITOR # ############################# save_DIFFRN_SCAN_FRAME_MONITOR _category.description ; Data items in the DIFFRN_SCAN_FRAME_MONITOR category record the values and details about each monitor for each frame of data during a scan. Each monitor value is uniquely identified by the combination of the scan_id given by _diffrn_scan_frame.scan_id the frame_id given by _diffrn_scan_frame_monitor.frame_id, the monitor's detector_id given by _diffrn_scan_frame_monitor.monitor_id, and a 1-based ordinal given by _diffrn_scan_frame_monitor.id. If there is only one frame for the scan, the value of _diffrn_scan_frame_monitor.frame_id may be omitted. A single frame may have more than one monitor value, and each monitor value may be the result of integration over the entire frame integration time given by the value of _diffrn_scan_frame.integration_time or many monitor values may be reported over shorter times given by the value of _diffrn_scan_frame_monitor.integration_time. If only one monitor value for a given monitor is collected during the integration time of the frame, the value of _diffrn_scan_frame_monitor.id may be omitted. ; _category.id diffrn_data_frame_monitor _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame_monitor.id' '_diffrn_scan_frame_monitor.detector_id' '_diffrn_scan_frame_monitor.scan_id' '_diffrn_data_frame_monitor.frame_id' '_diffrn_data_frame_monitor.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - The beam intensity for frame FRAME1 is being tracked by a beamstop monitor detector BSM01, made from metal foil and a PIN diode, locate 20 mm in front of a MAR345 detector and being sampled every 2 seconds in a 20 second scan. ; ; # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 P6MB BSM01 'metal foil and PIN diode' 1 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH BSM01 MONITOR_Z # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 MONITOR_Z 0.0 0.0 0.0 -220.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_MONITOR loop_ _diffrn_scan_frame_monitor.id _diffrn_scan_frame_monitor.detector_id _diffrn_scan_frame_monitor.scan_id _diffrn_data_frame_monitor.frame_id _diffrn_data_frame_monitor.integration_time _diffrn_data_frame_monitor.monitor_value 1 BSM01 SCAN1 FRAME1 2.0 23838345642 2 BSM01 SCAN1 FRAME1 2.0 23843170669 3 BSM01 SCAN1 FRAME1 2.0 23839478690 4 BSM01 SCAN1 FRAME1 2.0 23856642085 5 BSM01 SCAN1 FRAME1 2.0 23781717656 6 BSM01 SCAN1 FRAME1 2.0 23788850775 7 BSM01 SCAN1 FRAME1 2.0 23815576677 8 BSM01 SCAN1 FRAME1 2.0 23789299964 9 BSM01 SCAN1 FRAME1 2.0 23830195536 10 BSM01 SCAN1 FRAME1 2.0 23673082270 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 FRAME1 MONITOR_Z 0.0 -220.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 172.43 -172.43 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 MONITOR_Z translation detector . 0 0 1 0 0 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_scan_frame_monitor.id _item_description.description ; This item is an integer identifier which, along with _diffrn_scan_frame_monitor.detector_id, _diffrn_scan_frame_monitor.scan_id, and _diffrn_data_frame_monitor.frame_id should uniquely identify the monitor value being recorded If _array_data.binary_id is not explicitly given, it defaults to 1. ; loop_ _item.name _diffrn_scan_frame_monitor.id _item.category_id diffrn_scan_frame_monitor _item.mandatory_code implicit _item_default.value 1 _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__diffrn_scan_frame_monitor.detector_id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. ; _item.name '_diffrn_scan_frame_monitor.detector_id' _item.category_id diffrn_scan_frame_monitor _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_monitor.frame_id _item_description.description ; This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame_monitor.frame_id' _item.category_id diffrn_scan_frame_monitor _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_monitor.integration_time _item_description.description ; The precise time for integration of the monitor value given in _diffrn_scan_frame_monitor.value must be given in _diffrn_scan_frame_monitor.integration_time. ; _item.name '_diffrn_scan_frame_monitor.integration_time' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame_monitor.value _item_description.description ; The value reported by the monitor detector should be given in _diffrn_scan_frame_monitor.value. The value is typed as float to allow of monitors for very intense beams that cannot report all digits, but when available, all digits of the monitor should be recorded. ; _item.name '_diffrn_scan_frame_monitor.value' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame_monitor.variant _item_description.description ; The value of _diffrn_scan_frame_monitor.variant gives the variant to which the given diffrn_scan_frame_monitor row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_scan_frame_monitor.variant' _item.category_id diffrn_scan_frame_monitor _item.mandatory_code no _item_type.code code save_ ####### # MAP # ####### save_MAP _category.description ; Data items in the MAP category record the details of a maps. Maps record values of parameters, such as density, that are functions of position within a cell or are functions of orthogonal coordinates in three space. A map may is composed of one or more map segments specified in the MAP_SEGMENT category. Examples are given in the MAP_SEGMENT category. ; _category.id map _category.mandatory_code no loop_ _category_key.name '_map.id' '_map.diffrn_id' '_map.entry_id' '_map.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' 'map_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Identifying an observed density map and a calculated density map ; ; loop_ _map.id _map.details rho_calc ; density calculated from F_calc derived from the ATOM_SITE list ; rho_obs ; density combining the observed structure factors with the calculated phases ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__map.details _item_description.description ; The value of _map.details should give a description of special aspects of each map. ; _item.name '_map.details' _item.category_id map _item.mandatory_code no _item_type.code text loop_ _item_examples.case _item_examples.detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Identifying an observed density map and a calculated density map ; ; loop_ _map.id _map.details rho_calc ; density calculated from F_calc derived from the ATOM_SITE list ; rho_obs ; density combining the observed structure factors with the calculated phases ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__map.diffrn_id _item_description.description ; This item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_map.diffrn_id' _item.category_id map _item.mandatory_code implicit _item_type.code code save_ save__map.entry_id _item_description.description ; This item is a pointer to _entry.id in the ENTRY category. ; _item.name '_map.entry_id' _item.category_id map _item.mandatory_code implicit _item_type.code code save_ save__map.id _item_description.description ; The value of _map.id must uniquely identify each map for the given diffrn.id or entry.id. ; loop_ _item.name _item.category_id _item.mandatory_code '_map.id' map yes '_map_segment.id' map_segment yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_map_segment.id' '_map.id' save_ save__map.variant _item_description.description ; The value of _map.variant gives the variant to which the given map row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_map.variant' _item.category_id map _item.mandatory_code no _item_type.code code save_ ############### # MAP_SEGMENT # ############### save_MAP_SEGMENT _category.description ; Data items in the MAP_SEGMENT category record the details about each segment (section or brick) of a map. ; _category.id map_segment _category.mandatory_code no loop_ _category_key.name '_map_segment.id' '_map_segment.map_id' '_map_segment.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' 'map_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Identifying an observed density map and a calculated density map, each consisting of one segment, both using the same array structure and mask. ; ; loop_ _map.id _map.details rho_calc ; density calculated from F_calc derived from the ATOM_SITE list ; rho_obs ; density combining the observed structure factors with the calculated phases ; loop_ _map_segment.map_id _map_segment.id _map_segment.array_id _map_segment.binary_id _map_segment.mask_array_id _map_segment.mask_binary_id rho_calc rho_calc map_structure 1 mask_structure 1 rho_obs rho_obs map_structure 2 mask_structure 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__map_segment.array_id _item_description.description ; The value of _map_segment.array_id identifies the array structure into which the map is organized. This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_map_segment.array_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code code save_ save__map_segment.binary_id _item_description.description ; The value of _map_segment.binary_id distinguishes the particular set of data organized according to _map_segment.array_id in which the data values of the map are stored. This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_map_segment.binary_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code int save_ save__map_segment.mask_array_id _item_description.description ; The value of _map_segment.mask_array_id, if given, the array structure into which the mask for the map is organized. If no value is given, then all elements of the map are valid. If a value is given, then only elements of the map for which the corresponding element of the mask is non-zero are valid. The value of _map_segment.mask_array_id differs from the value of _map_segment.array_id in order to permit the mask to be given as, say, unsigned 8-bit integers, while the map is given as a data type with more range. However, the two array structures must be aligned, using the same axes in the same order with the same displacements and increments This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_map_segment.mask_array_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code code save_ save__map_segment.mask_binary_id _item_description.description ; The value of _map_segment.mask_binary_id identifies the particular set of data organized according to _map_segment.mask_array_id specifying the mask for the map. This item is a pointer to _array_data.mask_binary_id in the ARRAY_DATA category. ; _item.name '_map_segment.mask_binary_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code int save_ save__map_segment.id _item_description.description ; The value of _map_segment.id must uniquely identify each segment of a map. ; loop_ _item.name _item.category_id _item.mandatory_code '_map_segment.id' map_segment yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_map_data_frame.map_segment_id' '_map_segment.id' save_ save__map_segment.map_id _item_description.description ; This item is a pointer to _map.id in the MAP category. ; _item.name '_map_segment.map_id' _item.category_id map_segment _item.mandatory_code yes _item_type.code code save_ save__map_segment.details _item_description.description ; The value of _map_segment.details should give a description of special aspects of each segment of a map. ; _item.name '_map_segment.details' _item.category_id map_segment _item.mandatory_code no _item_type.code text loop_ _item_examples.case _item_examples.detail ; Example to be provided ; ; ; save_ save__map_segment.variant _item_description.description ; The value of _map_segment.variant gives the variant to which the given map segment is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_map_segment.variant' _item.category_id map_segment _item.mandatory_code no _item_type.code code save_ ########### # VARIANT # ########### save_VARIANT _category.description ; Data items in the VARIANT category record the details about sets of variants of data items. There is sometimes a need to allow for multiple versions of the same data items in order to allow for refinements and corrections to earlier assumptions, observations and calculations. In order to allow data sets to contain more than one variant of the same information, an optional ...variant data item as a pointer to _variant.variant has been added to the key of every category, as an implicit data item with a null (empty) default value. All rows in a category with the same variant value are considered to be related to one another and to all rows in other categories with the same variant value. For a given variant, all such rows are also considered to be related to all rows with a null variant value, except that a row with a null variant value is for which all other components of its key are identical to those entries in another row with a non-null variant value is not related the the rows with that non-null variant value. This behavior is similar to the convention for identifying alternate conformers in an atom list. An optional role may be specified for a variant as the value of _variant.role. Possible roles are null, "preferred", "raw data", "unsuccessful trial". Variants may carry an optional timestamp as the value of _variant.timestamp. Variants may be related to other variants from which they were derived by the value of _variant.variant_of Further details about the variant may be specified as the value of _variant.details. In order to allow variant information from multiple datasets to be combined, _variant.diffrn_id and/or _variant.entry_id may be used. ; _category.id variant _category.mandatory_code no loop_ _category_key.name '_variant.variant' '_variant.diffrn_id' '_variant.entry_id' loop_ _category_group.id 'inclusive_group' 'variant_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Distinguishing between a raw beam center and a refined beam center inferred after indexing. Detector d1 is composed of four CCD detector elements, each 200 mm by 200 mm, arranged in a square, in the pattern 1 2 * 3 4 Note that the beam centre is slightly displaced from each of the detector elements, just beyond the lower right corner of 1, the lower left corner of 2, the upper right corner of 3 and the upper left corner of 4. For each element, the detector face coordiate system, is assumed to have the fast axis running from left to right and the slow axis running from top to bottom with the origin at the top left corner. After indexing and refinement, the center is shifted by .2 mm left and .1 mm down. ; ; loop_ _variant.variant _variant.role _variant.timestamp _variant.variant_of _variant.details . "raw data" 2007-08-03T23:20:00 . . indexed "preferred" 2007-08-04T01:17:28 . "indexed cell and refined beam center" loop_ _diffrn_detector_element.detector_id _diffrn_detector_element.id _diffrn_detector_element.reference_center_fast _diffrn_detector_element.reference_center_slow _diffrn_detector_element.reference_center_units _diffrn_detector_element.variant d1 d1_ccd_1 201.5 201.5 mm . d1 d1_ccd_2 -1.8 201.5 mm . d1 d1_ccd_3 201.6 -1.4 mm . d1 d1_ccd_4 -1.7 -1.5 mm . d1 d1_ccd_1 201.3 201.6 mm indexed d1 d1_ccd_2 -2.0 201.6 mm indexed d1 d1_ccd_3 201.3 -1.5 mm indexed d1 d1_ccd_4 -1.9 -1.6 mm indexed ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__variant.details _item_description.description ; A description of special aspects of the variant. ; _item.name '_variant.details' _item.category_id variant _item.mandatory_code no _item_type.code text _item_examples.case ; indexed cell and refined beam center ; save_ save__variant.role _item_description.description ; The value of _variant.role specified a role for this variant. Possible roles are null, "preferred", "raw data", and "unsuccessful trial". ; _item.name '_variant.role' _item.category_id variant _item.mandatory_code no _item_type.code uline loop_ _item_enumeration.value _item_enumeration.detail . ; A null value for _variant.role leaves the precise role of the variant unspecified. No inference should be made that the variant with the latest time stamp is preferred. ; "preferred" ; A value of "preferred" indicates that rows of any categories specifying this variant should be used in preference to rows with the same key specifying other variants or the null variant. It is an error to specify two variants that appear in the same category with the same key as being preferred, but it is not an error to specify more than one variant as preferred in other cases. ; "raw data" ; A value of "raw data" indicates data prior to any corrections, calculations or refinements. It is not necessarily an error for raw data to also be a variant of an earlier variant. It may be replacement raw data for earlier data believed to be erroneous. ; "unsuccessful trial" ; A value of "unsuccessful trial" indicates data that should not be used for further calculation. ; save_ save__variant.timestamp _item_description.description ; The date and time identifying a variant. This is not necessarily the precise time of the measurement or calculation of the individual related data items, but a timestamp that reflects the order in which the variants were defined. ; _item.name '_variant.timestamp' _item.category_id variant _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__variant.variant _item_description.description ; The value of _variant.variant must uniquely identify each variant for the given diffraction experiment and/or entry This item has been made implicit and given a default value of null. ; loop_ _item.name _item.category_id _item.mandatory_code '_variant.variant' variant implicit '_variant.variant_of' variant implicit '_array_data.variant' array_data implicit '_array_element_size.variant' array_element_size implicit '_array_intensities.variant' array_intensities implicit '_array_structure.variant' array_structure implicit '_array_structure_list.variant' array_structure_list implicit '_array_structure_list_axis.variant' array_structure_list_axis implicit '_axis.variant' axis implicit '_diffrn_data_frame.variant' diffrn_data_frame implicit '_diffrn_detector.variant' diffrn_detector implicit '_diffrn_detector_axis.variant' diffrn_detector_axis implicit '_diffrn_detector_element.variant' diffrn_detector_element implicit '_diffrn_measurement.variant' diffrn_measurement implicit '_diffrn_measurement_axis.variant' diffrn_measurement_axis implicit '_diffrn_radiation.variant' diffrn_radiation implicit '_diffrn_refln.variant' diffrn_refln implicit '_diffrn_scan.variant' diffrn_scan implicit '_diffrn_scan_axis.variant' diffrn_scan_axis implicit '_diffrn_scan_frame.variant' diffrn_scan_frame implicit '_diffrn_scan_frame_axis.variant' diffrn_scan_frame_axis implicit '_diffrn_scan_frame_monitor.variant' diffrn_scan_frame_monitor implicit '_map.variant' map implicit '_map_segment.variant' map_segment implicit _item_default.value . _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_data.variant' '_variant.variant' '_array_data.variant_of' '_variant.variant' '_array_element_size.variant' '_variant.variant' '_array_intensities.variant' '_variant.variant' '_array_structure.variant' '_variant.variant' '_array_structure_list.variant' '_variant.variant' '_array_structure_list_axis.variant' '_variant.variant' '_axis.variant' '_variant.variant' '_diffrn_data_frame.variant' '_variant.variant' '_diffrn_detector.variant' '_variant.variant' '_diffrn_detector_axis.variant' '_variant.variant' '_diffrn_detector_element.variant' '_variant.variant' '_diffrn_measurement.variant' '_variant.variant' '_diffrn_measurement_axis.variant' '_variant.variant' '_diffrn_radiation.variant' '_variant.variant' '_diffrn_refln.variant' '_variant.variant' '_diffrn_scan.variant' '_variant.variant' '_diffrn_scan_axis.variant' '_variant.variant' '_diffrn_scan_frame.variant' '_variant.variant' '_diffrn_scan_frame_axis.variant' '_variant.variant' '_diffrn_scan_frame_monitor.variant' '_variant.variant' '_map.variant' '_variant.variant' '_map_segment.variant' '_variant.variant' save_ save__variant.variant_of _item_description.description ; The value of _variant.variant_of gives the variant from which this variant was derived. If this value is not given, the variant is assumed to be derived from the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_variant.variant_of' _item.category_id variant _item.mandatory_code no _item_type.code code save_ ######################## DEPRECATED DATA ITEMS ######################## save__diffrn_detector_axis.id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_detector_axis.id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_element.center[1] _item_description.description ; The value of _diffrn_detector_element.center[1] is the X component of the distortion-corrected beam centre in millimetres from the (0, 0) (lower-left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. Because of ambiguity about the setting used to determine this center, use of this data item is deprecated. The data item _diffrn_data_frame.center_fast which is referenced to the detector coordinate system and not directly to the laboratory coordinate system should be used instead. ; _item.name '_diffrn_detector_element.center[1]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.center[2] _item_description.description ; The value of _diffrn_detector_element.center[2] is the Y component of the distortion-corrected beam centre in millimetres from the (0, 0) (lower-left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. Because of ambiguity about the setting used to determine this center, use of this data item is deprecated. The data item _diffrn_data_frame.center_slow which is referenced to the detector coordinate system and not directly to the laboratory coordinate system should be used instead. ; _item.name '_diffrn_detector_element.center[2]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_measurement_axis.id _item_description.description ; This data item is a pointer to _diffrn_measurement.id in the DIFFRN_MEASUREMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_measurement_axis.id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ ######################### DEPRECATED CATEGORY ######################### ##################### # DIFFRN_FRAME_DATA # ##################### save_DIFFRN_FRAME_DATA _category.description ; Data items in the DIFFRN_FRAME_DATA category record the details about each frame of data. The items in this category are now in the DIFFRN_DATA_FRAME category. The items in the DIFFRN_FRAME_DATA category are now deprecated. The items from this category are provided as aliases in the 1.0 dictionary or, in the case of _diffrn_frame_data.details, in the 1.4 dictionary. THESE ITEMS SHOULD NOT BE USED FOR NEW WORK. The items from the old category are provided in this dictionary for completeness but should not be used or cited. To avoid confusion, the example has been removed and the redundant parent-child links to other categories have been removed. ; _category.id diffrn_frame_data _category.mandatory_code no loop_ _category_key.name '_diffrn_frame_data.id' '_diffrn_frame_data.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; THE DIFFRN_FRAME_DATA category is deprecated and should not be used. ; ; # EXAMPLE REMOVED # ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_frame_data.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.array_id' _item.category_id diffrn_frame_data _item.mandatory_code implicit _item_type.code code save_ save__diffrn_frame_data.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.binary_id' _item.category_id diffrn_frame_data _item.mandatory_code implicit _item_type.code int save_ save__diffrn_frame_data.detector_element_id _item_description.description ; This item is a pointer to _diffrn_detector_element.id in the DIFFRN_DETECTOR_ELEMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.detector_element_id' _item.category_id diffrn_frame_data _item.mandatory_code yes _item_type.code code save_ save__diffrn_frame_data.id _item_description.description ; The value of _diffrn_frame_data.id must uniquely identify each complete frame of data. DEPRECATED -- DO NOT USE ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_frame_data.id' diffrn_frame_data yes _item_type.code code save_ save__diffrn_frame_data.details _item_description.description ; The value of _diffrn_data_frame.details should give a description of special aspects of each frame of data. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.details' _item.category_id diffrn_frame_data _item.mandatory_code no _item_type.code text save_ ################ END DEPRECATED SECTION ########### #################### ## ITEM_TYPE_LIST ## #################### # # # The regular expressions defined here are not compliant # with the POSIX 1003.2 standard as they include the # '\n' and '\t' special characters. These regular expressions # have been tested using version 0.12 of Richard Stallman's # GNU regular expression library in POSIX mode. # In order to allow presentation of a regular expression # in a text field concatenate any line ending in a backslash # with the following line, after discarding the backslash. # # A formal definition of the '\n' and '\t' special characters # is most properly done in the DDL, but for completeness, please # note that '\n' is the line termination character ('newline') # and '\t' is the horizontal tab character. There is a formal # ambiguity in the use of '\n' for line termination, in that # the intention is that the equivalent machine/OS-dependent line # termination character sequence should be accepted as a match, e.g. # # '\r' (control-M) under MacOS # '\n' (control-J) under Unix # '\r\n' (control-M control-J) under DOS and MS Windows # loop_ _item_type_list.code _item_type_list.primitive_code _item_type_list.construct _item_type_list.detail code char '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words ... ; ucode uchar '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words (case insensitive) ... ; line char '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; char item types / multi-word items ... ; uline uchar '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; char item types / multi-word items (case insensitive)... ; text char '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; text item types / multi-line text ... ; binary char ;\n--CIF-BINARY-FORMAT-SECTION--\n\ [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\ \n--CIF-BINARY-FORMAT-SECTION---- ; ; binary items are presented as MIME-like ascii-encoded sections in an imgCIF. In a CBF, raw octet streams are used to convey the same information. ; int numb '-?[0-9]+' ; int item types are the subset of numbers that are the negative or positive integers. ; float numb '-?(([0-9]+)[.]?|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?' ; float item types are the subset of numbers that are the floating point numbers. ; any char '.*' ; A catch all for items that may take any form... ; yyyy-mm-dd char ;\ [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9]?[0-9]\ ((T[0-2][0-9](:[0-5][0-9](:[0-5][0-9](.[0-9]+)?)?)?)?\ ([+-][0-5][0-9]:[0-5][0-9]))? ; ; Standard format for CIF date and time strings (see http://www.iucr.org/iucr-top/cif/spec/datetime.html), consisting of a yyyy-mm-dd date optionally followed by the character 'T' followed by a 24-hour clock time, optionally followed by a signed time-zone offset. The IUCr standard has been extended to allow for an optional decimal fraction on the seconds of time. Time is local time if no time-zone offset is given. Note that this type extends the mmCIF yyyy-mm-dd type but does not conform to the mmCIF yyyy-mm-dd:hh:mm type that uses a ':' in place if the 'T' specified by the IUCr standard. For reading, both forms should be accepted, but for writing, only the IUCr form should be used. For maximal compatibility, the special time zone indicator 'Z' (for 'zulu') should be accepted on reading in place of '+00:00' for GMT. ; ##################### ## ITEM_UNITS_LIST ## ##################### loop_ _item_units_list.code _item_units_list.detail # 'metres' 'metres' 'centimetres' 'centimetres (metres * 10^( -2)^)' 'millimetres' 'millimetres (metres * 10^( -3)^)' 'nanometres' 'nanometres (metres * 10^( -9)^)' 'angstroms' '\%Angstroms (metres * 10^(-10)^)' 'picometres' 'picometres (metres * 10^(-12)^)' 'femtometres' 'femtometres (metres * 10^(-15)^)' # 'reciprocal_metres' 'reciprocal metres (metres^(-1)^)' 'reciprocal_centimetres' 'reciprocal centimetres ((metres * 10^( -2)^)^(-1)^)' 'reciprocal_millimetres' 'reciprocal millimetres ((metres * 10^( -3)^)^(-1)^)' 'reciprocal_nanometres' 'reciprocal nanometres ((metres * 10^( -9)^)^(-1)^)' 'reciprocal_angstroms' 'reciprocal \%Angstroms ((metres * 10^(-10)^)^(-1)^)' 'reciprocal_picometres' 'reciprocal picometres ((metres * 10^(-12)^)^(-1)^)' # 'nanometres_squared' 'nanometres squared (metres * 10^( -9)^)^2^' 'angstroms_squared' '\%Angstroms squared (metres * 10^(-10)^)^2^' '8pi2_angstroms_squared' '8\p^2^ * \%Angstroms squared (metres * 10^(-10)^)^2^' 'picometres_squared' 'picometres squared (metres * 10^(-12)^)^2^' # 'nanometres_cubed' 'nanometres cubed (metres * 10^( -9)^)^3^' 'angstroms_cubed' '\%Angstroms cubed (metres * 10^(-10)^)^3^' 'picometres_cubed' 'picometres cubed (metres * 10^(-12)^)^3^' # 'kilopascals' 'kilopascals' 'gigapascals' 'gigapascals' # 'hours' 'hours' 'minutes' 'minutes' 'seconds' 'seconds' 'microseconds' 'microseconds' # 'degrees' 'degrees (of arc)' 'degrees_squared' 'degrees (of arc) squared' # 'degrees_per_minute' 'degrees (of arc) per minute' # 'celsius' 'degrees (of temperature) Celsius' 'kelvins' 'degrees (of temperature) Kelvin' # 'counts' 'counts' 'counts_per_photon' 'counts per photon' # 'electrons' 'electrons' # 'electrons_squared' 'electrons squared' # 'electrons_per_nanometres_cubed' ; electrons per nanometres cubed (electrons/(metres * 10^( -9)^)^(-3)^) ; 'electrons_per_angstroms_cubed' ; electrons per \%Angstroms cubed (electrons/(metres * 10^(-10)^)^(-3)^) ; 'electrons_per_picometres_cubed' ; electrons per picometres cubed (electrons/(metres * 10^(-12)^)^(-3)^) ; 'kilowatts' 'kilowatts' 'milliamperes' 'milliamperes' 'kilovolts' 'kilovolts' # 'pixels_per_element' '(image) pixels per (array) element' # 'arbitrary' ; arbitrary system of units. ; # loop_ _item_units_conversion.from_code _item_units_conversion.to_code _item_units_conversion.operator _item_units_conversion.factor ### 'metres' 'centimetres' '*' 1.0E+02 'metres' 'millimetres' '*' 1.0E+03 'metres' 'nanometres' '*' 1.0E+09 'metres' 'angstroms' '*' 1.0E+10 'metres' 'picometres' '*' 1.0E+12 'metres' 'femtometres' '*' 1.0E+15 # 'centimetres' 'metres' '*' 1.0E-02 'centimetres' 'millimetres' '*' 1.0E+01 'centimetres' 'nanometres' '*' 1.0E+07 'centimetres' 'angstroms' '*' 1.0E+08 'centimetres' 'picometres' '*' 1.0E+10 'centimetres' 'femtometres' '*' 1.0E+13 # 'millimetres' 'metres' '*' 1.0E-03 'millimetres' 'centimetres' '*' 1.0E-01 'millimetres' 'nanometres' '*' 1.0E+06 'millimetres' 'angstroms' '*' 1.0E+07 'millimetres' 'picometres' '*' 1.0E+09 'millimetres' 'femtometres' '*' 1.0E+12 # 'nanometres' 'metres' '*' 1.0E-09 'nanometres' 'centimetres' '*' 1.0E-07 'nanometres' 'millimetres' '*' 1.0E-06 'nanometres' 'angstroms' '*' 1.0E+01 'nanometres' 'picometres' '*' 1.0E+03 'nanometres' 'femtometres' '*' 1.0E+06 # 'angstroms' 'metres' '*' 1.0E-10 'angstroms' 'centimetres' '*' 1.0E-08 'angstroms' 'millimetres' '*' 1.0E-07 'angstroms' 'nanometres' '*' 1.0E-01 'angstroms' 'picometres' '*' 1.0E+02 'angstroms' 'femtometres' '*' 1.0E+05 # 'picometres' 'metres' '*' 1.0E-12 'picometres' 'centimetres' '*' 1.0E-10 'picometres' 'millimetres' '*' 1.0E-09 'picometres' 'nanometres' '*' 1.0E-03 'picometres' 'angstroms' '*' 1.0E-02 'picometres' 'femtometres' '*' 1.0E+03 # 'femtometres' 'metres' '*' 1.0E-15 'femtometres' 'centimetres' '*' 1.0E-13 'femtometres' 'millimetres' '*' 1.0E-12 'femtometres' 'nanometres' '*' 1.0E-06 'femtometres' 'angstroms' '*' 1.0E-05 'femtometres' 'picometres' '*' 1.0E-03 ### 'reciprocal_centimetres' 'reciprocal_metres' '*' 1.0E+02 'reciprocal_centimetres' 'reciprocal_millimetres' '*' 1.0E-01 'reciprocal_centimetres' 'reciprocal_nanometres' '*' 1.0E-07 'reciprocal_centimetres' 'reciprocal_angstroms' '*' 1.0E-08 'reciprocal_centimetres' 'reciprocal_picometres' '*' 1.0E-10 # 'reciprocal_millimetres' 'reciprocal_metres' '*' 1.0E+03 'reciprocal_millimetres' 'reciprocal_centimetres' '*' 1.0E+01 'reciprocal_millimetres' 'reciprocal_nanometres' '*' 1.0E-06 'reciprocal_millimetres' 'reciprocal_angstroms' '*' 1.0E-07 'reciprocal_millimetres' 'reciprocal_picometres' '*' 1.0E-09 # 'reciprocal_nanometres' 'reciprocal_metres' '*' 1.0E+09 'reciprocal_nanometres' 'reciprocal_centimetres' '*' 1.0E+07 'reciprocal_nanometres' 'reciprocal_millimetres' '*' 1.0E+06 'reciprocal_nanometres' 'reciprocal_angstroms' '*' 1.0E-01 'reciprocal_nanometres' 'reciprocal_picometres' '*' 1.0E-03 # 'reciprocal_angstroms' 'reciprocal_metres' '*' 1.0E+10 'reciprocal_angstroms' 'reciprocal_centimetres' '*' 1.0E+08 'reciprocal_angstroms' 'reciprocal_millimetres' '*' 1.0E+07 'reciprocal_angstroms' 'reciprocal_nanometres' '*' 1.0E+01 'reciprocal_angstroms' 'reciprocal_picometres' '*' 1.0E-02 # 'reciprocal_picometres' 'reciprocal_metres' '*' 1.0E+12 'reciprocal_picometres' 'reciprocal_centimetres' '*' 1.0E+10 'reciprocal_picometres' 'reciprocal_millimetres' '*' 1.0E+09 'reciprocal_picometres' 'reciprocal_nanometres' '*' 1.0E+03 'reciprocal_picometres' 'reciprocal_angstroms' '*' 1.0E+01 ### 'nanometres_squared' 'angstroms_squared' '*' 1.0E+02 'nanometres_squared' 'picometres_squared' '*' 1.0E+06 # 'angstroms_squared' 'nanometres_squared' '*' 1.0E-02 'angstroms_squared' 'picometres_squared' '*' 1.0E+04 'angstroms_squared' '8pi2_angstroms_squared' '*' 78.9568 # 'picometres_squared' 'nanometres_squared' '*' 1.0E-06 'picometres_squared' 'angstroms_squared' '*' 1.0E-04 ### 'nanometres_cubed' 'angstroms_cubed' '*' 1.0E+03 'nanometres_cubed' 'picometres_cubed' '*' 1.0E+09 # 'angstroms_cubed' 'nanometres_cubed' '*' 1.0E-03 'angstroms_cubed' 'picometres_cubed' '*' 1.0E+06 # 'picometres_cubed' 'nanometres_cubed' '*' 1.0E-09 'picometres_cubed' 'angstroms_cubed' '*' 1.0E-06 ### 'kilopascals' 'gigapascals' '*' 1.0E-06 'gigapascals' 'kilopascals' '*' 1.0E+06 ### 'hours' 'minutes' '*' 6.0E+01 'hours' 'seconds' '*' 3.6E+03 'hours' 'microseconds' '*' 3.6E+09 # 'minutes' 'hours' '/' 6.0E+01 'minutes' 'seconds' '*' 6.0E+01 'minutes' 'microseconds' '*' 6.0E+07 # 'seconds' 'hours' '/' 3.6E+03 'seconds' 'minutes' '/' 6.0E+01 'seconds' 'microseconds' '*' 1.0E+06 # 'microseconds' 'hours' '/' 3.6E+09 'microseconds' 'minutes' '/' 6.0E+07 'microseconds' 'seconds' '/' 1.0E+06 ### 'celsius' 'kelvins' '-' 273.0 'kelvins' 'celsius' '+' 273.0 ### 'electrons_per_nanometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E+03 'electrons_per_nanometres_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+09 # 'electrons_per_angstroms_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-03 'electrons_per_angstroms_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+06 # 'electrons_per_picometres_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-09 'electrons_per_picometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E-06 ### ######################## ## DICTIONARY_HISTORY ## ######################## loop_ _dictionary_history.version _dictionary_history.update _dictionary_history.revision 1.6.3 2010-08-26 ; Cummulative corrections from 1.6.0, 1, 2 drafts (HJB) + Move descriptive dictionary comments into _datablock.description with catgeory tree described + add default _array_data.array_id value of 1 + add option of CBF_BACKGROUND_OFFSET_DELTA compression + add VARIANT catgeory and tags + add DIFFRN_SCAN_FRAME_MONITOR category ; 1.5.4 2007-07-28 ; Typographics corrections (HJB) + Corrected embedded degree characters to \% + Corrected embedded Aring to \%A + Added trailing ^ for a power + Removed 2 cases of a space after an underscore in tag name. ; 1.5.3 2007-07-08 ; Changes to support SLS miniCBF and suggestions from the 24 May 07 BNL imgCIF workshop (HJB) + Added new data items '_array_data.header_contents', '_array_data.header_convention', '_diffrn_data_frame.center_fast', '_diffrn_data_frame.center_slow', '_diffrn_data_frame.center_units', '_diffrn_measurement.sample_detector_distance', '_diffrn_measurement.sample_detector_voffset + Deprecated data items '_diffrn_detector_element.center[1]', '_diffrn_detector_element.center[2]' + Added comments and example on miniCBF + Changed all array_id data items to implicit ; 1.5.2 2007-05-06 ; Further clarifications of the coordinate system. (HJB) ; 1.5.1 2007-04-26 ; Improve defintion of X-axis to cover the case of no goniometer and clean up more line folds (HJB) ; 1.5 2007-07-25 ; This is a cummulative list of the changes proposed since the imgCIF workshop in Hawaii in July 2006. It is the result of contributions by H. J. Bernstein, A. Hammersley, J. Wright and W. Kabsch. 2007-02-19 Consolidated changes (edited by HJB) + Added new data items '_array_structure.compression_type_flag', '_array_structure_list_axis.fract_displacement', '_array_structure_list_axis.displacement_increment', '_array_structure_list_axis.reference_angle', '_array_structure_list_axis.reference_displacement', '_axis.system', '_diffrn_detector_element.reference_center_fast', '_diffrn_detector_element.reference_center_slow', '_diffrn_scan_axis.reference_angle', '_diffrn_scan_axis.reference_displacement', '_map.details', '_map.diffrn_id', '_map.entry_id', '_map.id', '_map_segment.array_id', '_map_segment.binary_id', '_map_segment.mask_array_id', '_map_segment.mask_binary_id', '_map_segment.id', '_map_segment.map_id', '_map_segment.details. + Change type of '_array_structure.byte_order' and '_array_structure.compression_type' to ucode to make these values case-insensitive + Add values 'packed_v2' and 'byte_offset' to enumeration of values for '_array_structure.compression_type' + Add to definitions for the binary data type to handle new compression types, maps, and a variety of new axis types. 2007-07-25 Cleanup of typos for formal release (HJB) + Corrected text fields for reference_ tag descriptions that were off by one column + Fix typos in comments listing fract_ tags + Changed name of release from 1.5_DRAFT to 1.5 + Fix unclosed text fields in various map definitions ; 1.4 2006-07-04 ; This is a change to reintegrate all changes made in the course of publication of ITVG, by the RCSB from April 2005 through August 2008 and changes for the 2006 imgCIF workshop in Hawaii. 2006-07-04 Consolidated changes for the 2006 imgCIF workshop (edited by HJB) + Correct type of '_array_structure_list.direction' from 'int' to 'code'. + Added new data items suggested by CN '_diffrn_data_frame.details' '_array_intensities.pixel_fast_bin_size', '_array_intensities.pixel_slow_bin_size and '_array_intensities.pixel_binning_method + Added deprecated item for completeness '_diffrn_frame_data.details' + Added entry for missing item in contents list '_array_structure_list_axis.displacement' + Added new MIME type X-BASE32K based on work by VL, KM, GD, HJB + Correct description of MIME boundary delimiter to start in column 1. + General cleanup of text fields to conform to changes for ITVG by removing empty lines at start and finish of text field. + Amend example for ARRAY_INTENSITIES to include binning. + Add local copy of type specification (as 'code') for all children of '_diffrn.id'. + For consistency, change all references to 'pi' to '\p' and all references to 'Angstroms' to '\%Angstroms'. + Clean up all powers to use IUCr convention of '^power^', as in '10^3^' for '10**3'. + Update 'yyyy-mm-dd' type regex to allow truncation from the right and improve comments to explain handling of related mmCIF 'yyyy-mm-dd:hh:mm' type, and use of 'Z' for GMT time zone. 2005-03-08 and 2004-08-08 fixed cases where _item_units.code used instead of _item_type.code (JDW) 2004-04-15 fixed item ordering in _diffrn_measurement_axis.measurement_id added sub_category 'vector' (JDW) ; 1.3.2 2005-06-25 ; 2005-06-25 ITEM_TYPE_LIST: code, ucode, line, uline regexps updated to those of current mmCIF; float modified by allowing integers terminated by a point as valid. The 'time' part of yyyy-mm-dd types made optional in the regexp. (BM) 2005-06-17 Minor corrections as for proofs for IT G Chapter 4.6 (NJA) 2005-02-21 Minor corrections to spelling and punctuation (NJA) 2005-01-08 Changes as per Nicola Ashcroft. + Updated example 1 for DIFFRN_MEASUREMENT to agree with mmCIF. + Spelled out "micrometres" for "um" and "millimetres" for "mm". + Removed phrase "which may be stored" from ARRAY_STRUCTURE description. + Removed unused 'byte-offsets' compressions and updated cites to ITVG for '_array_structure.compression_type'. (HJB) ; 1.3.1 2003-08-13 ; Changes as per Frances C. Bernstein. + Identify initials. + Adopt British spelling for centre in text. + Set \p and \%Angstrom and powers. + Clean up commas and unclear wordings. + Clean up tenses in history. Changes as per Gotzon Madariaga. + Fix the ARRAY_DATA example to align '_array_data.binary_id' and X-Binary-ID. + Add a range to '_array_intensities.gain_esd'. + In the example of DIFFRN_DETECTOR_ELEMENT, '_diffrn_detector_element.id' and '_diffrn_detector_element.detector_id' interchanged. + Fix typos for direction, detector and axes. + Clarify description of polarisation. + Clarify axes in '_diffrn_detector_element.center[1]' '_diffrn_detector_element.center[2]'. + Add local item types for items that are pointers. (HJB) ; 1.3.0 2003-07-24 ; Changes as per Brian McMahon. + Consistently quote tags embedded in text. + Clean up introductory comments. + Adjust line lengths to fit in 80 character window. + Fix several descriptions in AXIS category which referred to '_axis.type' instead of the current item. + Fix erroneous use of deprecated item '_diffrn_detector_axis.id' in examples for DIFFRN_SCAN_AXIS. + Add deprecated items '_diffrn_detector_axis.id' and '_diffrn_measurement_axis.id'. (HJB) ; 1.2.4 2003-07-14 ; Changes as per I. David Brown. + Enhance descriptions in DIFFRN_SCAN_AXIS to make them less dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS. + Provide a copy of the deprecated DIFFRN_FRAME_DATA category for completeness. (HJB) ; 1.2.3 2003-07-03 ; Cleanup to conform to ITVG. + Correct sign error in ..._cubed units. + Correct '_diffrn_radiation.polarisn_norm' range. (HJB) ; 1.2.2 2003-03-10 ; Correction of typos in various DIFFRN_SCAN_AXIS descriptions. (HJB) ; 1.2.1 2003-02-22 ; Correction of ATOM_ for ARRAY_ typos in various descriptions. (HJB) ; 1.2 2003-02-07 ; Corrections to encodings (remove extraneous hyphens) remove extraneous underscore in '_array_structure.encoding_type' enumeration. Correct typos in items units list. (HJB) ; 1.1.3 2001-04-19 ; Another typo corrections by Wilfred Li, and cleanup by HJB. ; 1.1.2 2001-03-06 ; Several typo corrections by Wilfred Li. ; 1.1.1 2001-02-16 ; Several typo corrections by JW. ; 1.1 2001-02-06 ; Draft resulting from discussions on header for use at NSLS. (HJB) + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME. + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'. + Add '_diffrn_measurement_axis.measurement_device' and change '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'. + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source', '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm', '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end', '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr', '_diffrn_scan_axis.displacement_rstrt_incr', '_diffrn_scan_frame_axis.angle_increment', '_diffrn_scan_frame_axis.angle_rstrt_incr', '_diffrn_scan_frame_axis.displacement', '_diffrn_scan_frame_axis.displacement_increment',and '_diffrn_scan_frame_axis.displacement_rstrt_incr'. + Add '_diffrn_measurement.device' to category key. + Update yyyy-mm-dd to allow optional time with fractional seconds for time stamps. + Fix typos caught by RS. + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to allow for coupled axes, as in spiral scans. + Add examples for fairly complete headers thanks to R. Sweet and P. Ellis. ; 1.0 2000-12-21 ; Release version - few typos and tidying up. (BM & HJB) + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end of dictionary. + Alphabetize dictionary. ; 0.7.1 2000-09-29 ; Cleanup fixes. (JW) + Correct spelling of diffrn_measurement_axis in '_axis.id' + Correct ordering of uses of '_item.mandatory_code' and '_item_default.value'. ; 0.7.0 2000-09-09 ; Respond to comments by I. David Brown. (HJB) + Add further comments on '\n' and '\t'. + Update ITEM_UNITS_LIST by taking section from mmCIF dictionary and adding metres. Change 'meter' to 'metre' throughout. + Add missing enumerations to '_array_structure.compression_type' and make 'none' the default. + Remove parent-child relationship between '_array_structure_list.index' and '_array_structure_list.precedence'. + Improve alphabetization. + Fix '_array_intensities_gain.esd' related function. + Improve comments in AXIS. + Fix DIFFRN_FRAME_DATA example. + Remove erroneous DIFFRN_MEASUREMENT example. + Add '_diffrn_measurement_axis.id' to the category key. ; 0.6.0 1999-01-14 ; Remove redundant information for ENC_NONE data. (HJB) + After the D5 remove binary section identifier, size and compression type. + Add Control-L to header. ; 0.5.1 1999-01-03 ; Cleanup of typos and syntax errors. (HJB) + Cleanup example details for DIFFRN_SCAN category. + Add missing quote marks for '_diffrn_scan.id' definition. ; 0.5 1999-01-01 ; Modifications for axis definitions and reduction of binary header. (HJB) + Restore '_diffrn_detector.diffrn_id' to DIFFRN_DETECTOR KEY. + Add AXIS category. + Bring in complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories from cif_mm.dic for clarity. + Change '_array_structure.encoding_type' from type code to uline and added X-Binary-Element-Type to MIME header. + Add detector beam centre '_diffrn_detector_element.center[1]' and '_diffrn_detector_element.center[2]'. + Correct item name of '_diffrn_refln.frame_id'. + Replace reference to '_array_intensities.undefined' by '_array_intensities.undefined_value'. + Replace references to '_array_intensity.scaling' with '_array_intensities.scaling'. + Add DIFFRN_SCAN... categories. ; 0.4 1998-08-11 ; Modifications to the 0.3 imgCIF draft. (HJB) + Reflow comment lines over 80 characters and corrected typos. + Update examples and descriptions of MIME encoded data. + Change name to cbfext98.dic. ; 0.3 1998-07-04 ; Modifications for imgCIF. (HJB) + Add binary type, which is a text field containing a variant on MIME encoded data. + Change type of '_array_data.data' to binary and specify internal structure of raw binary data. + Add '_array_data.binary_id', and make '_diffrn_frame_data.binary_id' and '_array_intensities.binary_id' into pointers to this item. ; 0.2 1997-12-02 ; Modifications to the CBF draft. (JW) + Add category hierarchy for describing frame data developed from discussions at the BNL imgCIF Workshop Oct 1997. The following changes are made in implementing the workshop draft. Category DIFFRN_ARRAY_DATA is renamed to DIFFRN_FRAME_DATA. Category DIFFRN_FRAME_TYPE is renamed to DIFFRN_DETECTOR_ELEMENT. The parent item for '_diffrn_frame_data.array_id' is changed from '_array_structure_list.array_id' to '_array_structure.id'. Item '_diffrn_detector.array_id' is deleted. + Add data item '_diffrn_frame_data.binary_id' to identify data groups within a binary section. The formal identification of the binary section is still fuzzy. ; 0.1 1997-01-24 ; First draft of this dictionary in DDL 2.1 compliant format by John Westbrook (JW). This version is adapted from the Crystallographic Binary File (CBF) Format Draft Proposal provided by Andy Hammersley (AH). Modifications to the CBF draft. (JW) + In this version the array description has been cast in the categories ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. These categories have been generalized to describe array data of arbitrary dimension. + Array data in this description are contained in the category ARRAY_DATA. This departs from the CBF notion of data existing in some special comment. In this description, data are handled as an ordinary data item encapsulated in a character data type. Although data this manner deviates from CIF conventions, it does not violate any DDL 2.1 rules. DDL 2.1 regular expressions can be used to define the binary representation which will permit some level of data validation. In this version, the placeholder type code "any" has been used. This translates to a regular expression which will match any pattern. It should be noted that DDL 2.1 already supports array data objects although these have not been used in the current mmCIF dictionary. It may be possible to use the DDL 2.1 ITEM_STRUCTURE and ITEM_STRUCTURE_LIST categories to provide the information that is carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. By moving the array structure to the DDL level it would be possible to define an array type as well as a regular expression defining the data format. + Multiple array sections can be properly handled within a single datablock. ; #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof
./CBFlib-0.9.2.2/doc/Idiffrn_radiation.wavelength_id.html0000644000076500007650000000507511603702115021472 0ustar yayayaya (IUCr) CIF Definition save__diffrn_radiation.wavelength_id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_radiation.wavelength_id

Name:
'_diffrn_radiation.wavelength_id'

Definition:

        This data item is a pointer to
               _diffrn_radiation_wavelength.id in the
               DIFFRN_RADIATION_WAVELENGTH category.

Type: code

Mandatory item: yes

Category: diffrn_radiation

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_radiation.filter_edge.html0000644000076500007650000000517111603702115021120 0ustar yayayaya (IUCr) CIF Definition save__diffrn_radiation.filter_edge

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_radiation.filter_edge

Name:
'_diffrn_radiation.filter_edge'

Definition:

        Absorption edge in \%Angstroms of the radiation filter used.

Type: float

Mandatory item: no

Alias:
_diffrn_radiation_filter_edge (cif_core.dic version 2.0.1)
The permitted range is [0.0, infinity)

Category: diffrn_radiation

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_data_frame.id.html0000644000076500007650000000627111603702115017356 0ustar yayayaya (IUCr) CIF Definition save__diffrn_data_frame.id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_data_frame.id

Name:
'_diffrn_data_frame.id'

Definition:

       The value of _diffrn_data_frame.id must uniquely identify
              each complete frame of data.

Type: code

Mandatory item: yes

Alias:
_diffrn_frame_data.id (cif_img.dic version 1.0) _diffrn_refln.frame_id
_diffrn_scan.frame_id_start
_diffrn_scan.frame_id_end
_diffrn_scan_frame.frame_id
_diffrn_scan_frame_axis.frame_id

Category: diffrn_data_frame

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/cif_img_1_2_3.html0000644000076500007650000065572611603702115015536 0ustar yayayaya cif_img.dic v1.2.3

# [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib] #

# imgCIF/CBF #

# Extensions Dictionary #

##############################################################################
#                                                                            #
#                       Image CIF Dictionary (imgCIF)                        #
#             and Crystallographic Binary File Dictionary (CBF)              #
#            Extending the Macromolecular CIF Dictionary (mmCIF)             #
#                                                                            #
#                              Version 1.2.3                                 #
#                              of 2001-07-04                                 #
#     by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook    #
#                                                                            #
# This dictionary was  adapted from the imgCIF Workshop, held at BNL Oct 1997#
# and the Crystallographic Binary File Format Draft Proposal by Andy         #
# Hammersley.  The first DDL 2.1 Version was created by  John Westbrook.     #
# This version was drafted by Herbert J. Bernstein and incorporates comments #
# by I. David Brown, John Westbrook, Brian McMahon, Bob Sweet, Paul Ellis,   #
# Harry Powell, Wilfred Li and others.                                       #
##############################################################################

                                                                            
data_cif_img.dic


    _dictionary.title           cif_img.dic
    _dictionary.version         1.2.3
    _dictionary.datablock_id    cif_img.dic

##############################################################################
#    CONTENTS
#
#        CATEGORY_GROUP_LIST
#
#        category  ARRAY_DATA
#
#                  _array_data.array_id
#                  _array_data.binary_id
#                  _array_data.data
#
#        category  ARRAY_ELEMENT_SIZE
#        
#                  _array_element_size.array_id
#                  _array_element_size.index
#                  _array_element_size.size
#        
#        category  ARRAY_INTENSITIES
#        
#                  _array_intensities.array_id
#                  _array_intensities.binary_id
#                  _array_intensities.gain
#                  _array_intensities.gain_esd
#                  _array_intensities.linearity
#                  _array_intensities.offset
#                  _array_intensities.scaling
#                  _array_intensities.overload
#                  _array_intensities.undefined_value
#        
#        category  ARRAY_STRUCTURE
#        
#                  _array_structure.byte_order
#                  _array_structure.compression_type
#                  _array_structure.encoding_type
#                  _array_structure.id
#        
#        category  ARRAY_STRUCTURE_LIST
#        
#                  _array_structure_list.axis_set_id
#                  _array_structure_list.array_id
#                  _array_structure_list.dimension
#                  _array_structure_list.direction
#                  _array_structure_list.index
#                  _array_structure_list.precedence
#
#        category  ARRAY_STRUCTURE_LIST_AXIS
#        
#                  _array_structure_list_axis.axis_id
#                  _array_structure_list_axis.axis_set_id
#                  _array_structure_list_axis.angle
#                  _array_structure_list_axis.angle_increment
#                  _array_structure_list_axis.displacement_increment
#                  _array_structure_list_axis.angular_pitch
#                  _array_structure_list_axis.radial_pitch
#
#        category  AXIS
#        
#                  _axis.depends_on
#                  _axis.equipment
#                  _axis.id
#                  _axis.offset[1]
#                  _axis.offset[2]
#                  _axis.offset[3]
#                  _axis.type
#                  _axis.vector[1]
#                  _axis.vector[2]
#                  _axis.vector[3]
#
#        category  DIFFRN_DATA_FRAME
#
#                  _diffrn_data_frame.array_id
#                  _diffrn_data_frame.binary_id
#                  _diffrn_data_frame.detector_element_id
#                  _diffrn_data_frame.id
#
#        category  DIFFRN_DETECTOR
#        
#                  _diffrn_detector.details
#                  _diffrn_detector.detector
#                  _diffrn_detector.diffrn_id
#                  _diffrn_detector.dtime
#                  _diffrn_detector.id
#                  _diffrn_detector.number_of_axes
#                  _diffrn_detector.type
#
#        category  DIFFRN_DETECTOR_AXIS
#        
#                  _diffrn_detector_axis.axis_id
#                  _diffrn_detector_axis.detector_id    
#        
#        category  DIFFRN_DETECTOR_ELEMENT
#
#                  _diffrn_detector_element.center[1]
#                  _diffrn_detector_element.center[2]
#                  _diffrn_detector_element.id
#                  _diffrn_detector_element.detector_id
#        
#        category  DIFFRN_MEASUREMENT
#        
#                  _diffrn_measurement.diffrn_id
#                  _diffrn_measurement.details
#                  _diffrn_measurement.device
#                  _diffrn_measurement.device_details
#                  _diffrn_measurement.device_type
#                  _diffrn_measurement.id
#                  _diffrn_measurement.method
#                  _diffrn_measurement.number_of_axes
#                  _diffrn_measurement.specimen_support
#
#        category  DIFFRN_MEASUREMENT_AXIS
#        
#                  _diffrn_measurement_axis.axis_id
#                  _diffrn_measurement_axis.measurement_device
#                  _diffrn_measurement_axis.measurement_id
#
#        category  DIFFRN_RADIATION
#
#                  _diffrn_radiation.collimation
#                  _diffrn_radiation.diffrn_id
#                  _diffrn_radiation.div_x_source
#                  _diffrn_radiation.div_y_source
#                  _diffrn_radiation.div_x_y_source
#                  _diffrn_radiation.filter_edge'
#                  _diffrn_radiation.inhomogeneity
#                  _diffrn_radiation.monochromator
#                  _diffrn_radiation.polarisn_norm
#                  _diffrn_radiation.polarisn_ratio
#                  _diffrn_radiation.polarizn_source_norm
#                  _diffrn_radiation.polarizn_source_ratio
#                  _diffrn_radiation.probe
#                  _diffrn_radiation.type
#                  _diffrn_radiation.xray_symbol
#                  _diffrn_radiation.wavelength_id
#        
#        category  DIFFRN_REFLN
#        
#                  _diffrn_refln.frame_id
#
#        category  DIFFRN_SCAN
#        
#                  _diffrn_scan.id
#                  _diffrn_scan.date_end
#                  _diffrn_scan.date_start
#                  _diffrn_scan.integration_time
#                  _diffrn_scan.frame_id_start
#                  _diffrn_scan.frame_id_end
#                  _diffrn_scan.frames
#
#        category  DIFFRN_SCAN_AXIS
#        
#                  _diffrn_scan_axis.axis_id
#                  _diffrn_scan_axis.angle_start
#                  _diffrn_scan_axis.angle_range
#                  _diffrn_scan_axis.angle_increment
#                  _diffrn_scan_axis.angle_rstrt_incr
#                  _diffrn_scan_axis.displacement_start
#                  _diffrn_scan_axis.displacement_range
#                  _diffrn_scan_axis.displacement_increment
#                  _diffrn_scan_axis.displacement_rstrt_incr
#                  _diffrn_scan_axis.scan_id
#
#        category  DIFFRN_SCAN_FRAME
#        
#                  _diffrn_scan_frame.date
#                  _diffrn_scan_frame.frame_id
#                  _diffrn_scan_frame.frame_number
#                  _diffrn_scan_frame.integration_time
#                  _diffrn_scan_frame.scan_id
#
#        category  DIFFRN_SCAN_FRAME_AXIS
#        
#                  _diffrn_scan_frame_axis.axis_id
#                  _diffrn_scan_frame_axis.angle
#                  _diffrn_scan_frame_axis.angle_increment
#                  _diffrn_scan_frame_axis.angle_rstrt_incr
#                  _diffrn_scan_frame_axis.displacement
#                  _diffrn_scan_frame_axis.displacement_increment
#                  _diffrn_scan_frame_axis.displacement_rstrt_incr
#                  _diffrn_scan_frame_axis.frame_id
#
#        ITEM_TYPE_LIST
#        ITEM_UNITS_LIST
#        DICTIONARY_HISTORY
#
##############################################################################


#########################
## CATEGORY_GROUP_LIST ##
#########################

     loop_
    _category_group_list.id
    _category_group_list.parent_id
    _category_group_list.description
             'inclusive_group'   .
;             Categories that belong to the dictionary extension.
;
             'array_data_group'
             'inclusive_group'
;             Categories that describe array data.
;
             'axis_group'
             'inclusive_group'
;             Categories that describe axes.
;
             'diffrn_group'
             'inclusive_group'
;            Categories that describe details of the diffraction experiment.
;
 
 
 
 
##############
# ARRAY_DATA #
##############
 
  
save_ARRAY_DATA
    _category.description
;
     Data items in the ARRAY_DATA category are the containers for
     the array data items described in category ARRAY_STRUCTURE.
;
    _category.id                   array_data
    _category.mandatory_code       no
     loop_
    _category_key.name             '_array_data.array_id'
                                   '_array_data.binary_id'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
        Example 1 -

        This example shows two binary data blocks.  The first one
        was compressed by the CBF_CANONICAL compression algorithm and
        presented as hexadecimal data.  The first character "H" on the
        data lines means hexadecimal.  It could have been "O" for octal
        or "D" for decimal.  The second character on the line shows
        the number of bytes in each word (in this case "4"), which then
        requires 8 hexadecimal digits per word.  The third character
        gives the order of octets within a word, in this case "<"
        for the ordering 4321 (i.e. "big-endian").  Alternatively the
        character ">" could have been used for the ordering 1234
        (i.e. "little-endian").  The block has a "message digest"
        to check the integrity of the data.

        The second block is similar, but uses CBF_PACKED compression
        and BASE64 encoding.  Note that the size and the digest are
        different.
;
;

        loop_
        _array_data.array_id
        _array_data.binary_id
        _array_data.data
        image_1 1
        ;
        --CIF-BINARY-FORMAT-SECTION--
        Content-Type: application/octet-stream;
             conversions="x-CBF_CANONICAL"
        Content-Transfer-Encoding: X-BASE16
        X-Binary-Size: 3927126
        X-Binary-ID: 1
        Content-MD5: u2sTJEovAHkmkDjPi+gWsg==

        # Hexadecimal encoding, byte 0, byte order ...21
        #
        H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ...
        ....
        --CIF-BINARY-FORMAT-SECTION----
        ;
        image_2 2
        ;
        --CIF-BINARY-FORMAT-SECTION--
        Content-Type: application/octet-stream;
             conversions="x-CBF-PACKED"
        Content-Transfer-Encoding: BASE64
        X-Binary-Size: 3745758
        X-Binary-ID: 1
        Content-MD5: 1zsJjWPfol2GYl2V+QSXrw==

        ELhQAAAAAAAA...
        ...
        --CIF-BINARY-FORMAT-SECTION----
        ;
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
save_
 
 
save__array_data.array_id
    _item_description.description
;             This item is a pointer to _array_structure.id in the
              ARRAY_STRUCTURE category. 
;
    _item.name                  '_array_data.array_id'
    _item.category_id             array_data
    _item.mandatory_code          yes
    _item_type.code               code
     save_
 
 
save__array_data.binary_id
    _item_description.description
;             This item is an integer identifier which, along with
              _array_data.array_id should uniquely identify the 
              particular block of array data.
              
              If _array_data.binary_id is not explicitly given,
              it defaults to 1.
              
              The value of _array_data.binary_id distinguishes
              among multiple sets of data with the same array
              structure.
              
              If the MIME header of the data array specifies a 
              value for X-Binary-Id, these values should be equal.
;
     loop_
    _item.name                  
    _item.category_id             
    _item.mandatory_code          
             '_array_data.binary_id'            array_data      
                                                                implicit
             '_diffrn_data_frame.binary_id'     diffrn_data_frame
                                                                implicit
             '_array_intensities.binary_id'     array_intensities
                                                                implicit
     loop_
    _item_linked.child_name
    _item_linked.parent_name
             '_diffrn_data_frame.binary_id'     '_array_data.binary_id'
             '_array_intensities.binary_id'     '_array_data.binary_id'

    _item_default.value           1
    _item_type.code               int
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            1  1
                            .  1
     save_
 
 
save__array_data.data
    _item_description.description
;             The value of _array_data.data contains the array data 
              encapsulated in a STAR string.
              
              The representation used is a variant on the
              Multipurpose Internet Mail Extensions (MIME) specified
              in RFC 2045-2049 by N. Freed et al.  The boundary
              delimiter used in writing an imgCIF or CBF is
              "--CIF-BINARY-FORMAT-SECTION--" (including the
              required initial "--").

              The Content-Type may be any of the discrete types permitted
              in RFC 2045; "application/octet-stream" is recommended.  
              If an octet stream was compressed, the compression should 
              be specified by the parameter 'conversions="x-CBF_PACKED"' 
              or the parameter 'conversions="x-CBF_CANONICAL"'.
              
              The Content-Transfer-Encoding may be "BASE64",
              "Quoted-Printable", "X-BASE8", "X-BASE10", or
              "X-BASE16" for an imgCIF or "BINARY" for a CBF.  The
              octal, decimal and hexadecimal transfer encodings are
              for convenience in debugging, and are not recommended
              for archiving and data interchange.
              
              In an imgCIF file, the encoded binary data begins after
              the empty line terminating the header.  In a CBF, the
              raw binary data begins after an empty line terminating
              the header and after the sequence:
                    
              Octet   Hex   Decimal  Purpose
                0     0C       12    (ctrl-L) Page break
                1     1A       26    (ctrl-Z) Stop listings in MS-DOS
                2     04       04    (Ctrl-D) Stop listings in UNIX
                3     D5      213    Binary section begins

              None of these octets are included in the calculation of
              the message size, nor in the calculation of the
              message digest.
                             
              The X-Binary-Size header specifies the size of the
              equivalent binary data in octets.  If compression was
              used, this size is the size after compression, including
              any book-keeping fields.  An adjustment is made for
              the deprecated binary formats in which 8 bytes of binary
              header are used for the compression type.  In that case,
              the 8 bytes used for the compression type is subtracted
              from the size, so that the same size will be reported
              if the compression type is supplied in the MIME header.
              Use of the MIME header is the recommended way to
              supply the compression type.  In general, no portion of
              the  binary header is included in the calculation of the size.

              The X-Binary-Element-Type header specifies the type of
              binary data in the octets, using the same descriptive
              phrases as in _array_structure.encoding_type.  The default
              value is "unsigned 32-bit integer".
              
              An MD5 message digest may, optionally, be used. The "RSA Data
              Security, Inc. MD5 Message-Digest Algorithm" should be used.
              No portion of the header is included in the calculation of the
              message digest.

              If the Transfer Encoding is "X-BASE8", "X-BASE10", or
              "X-BASE16", the data is presented as octal, decimal or
              hexadecimal data organized into lines or words.  Each word
              is created by composing octets of data in fixed groups of
              2, 3, 4, 6 or 8 octets, either in the order ...4321 ("big-
              endian") or 1234... (little-endian).  If there are fewer
              than the specified number of octets to fill the last word,
              then the missing octets are presented as "==" for each
              missing octet.  Exactly two equal signs are used for each
              missing octet even for octal and decimal encoding.
              The format of lines is:

              rnd xxxxxx xxxxxx xxxxxx

              where r is "H", "O", or "D" for hexadecimal, octal or
              decimal, n is the number of octets per word. and d is "<"
              for ">" for the "...4321" and "1234..." octet orderings
              respectively.  The "==" padding for the last word should
              be on the appropriate side to correspond to the missing
              octets, e.g.

              H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000

              or

              H3> FF0700 00====

              For these hex, octal and decimal formats, only, comments
              beginning with "#" are permitted to improve readability.

              BASE64 encoding follows MIME conventions.  Octets are
              in groups of three, c1, c2, c3.  The resulting 24 bits 
              are broken into four 6-bit quantities, starting with 
              the high-order six bits (c1 >> 2) of the first octet, then
              the low-order two bits of the first octet followed by the
              high-order 4 bits of the second octet ((c1 & 3)<<4 | (c2>>4)),
              then the bottom 4 bits of the second octet followed by the
              high order two bits of the last octet ((c2 & 15)<<2 | (c3>>6)),
              then the bottom six bits of the last octet (c3 & 63).  Each
              of these four quantities is translated into an ASCII character
              using the mapping:

                        1         2         3         4         5         6
              0123456789012345678901234567890123456789012345678901234567890123
              |         |         |         |         |         |         |
              ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/

              With short groups of octets padded on the right with one "="
              if c3 is missing, and with "==" if both c2 and c3 are missing.

              QUOTED-PRINTABLE encoding also follows MIME conventions, copying
              octets without translation if their ASCII values are 32..38,
              42, 48..57, 59..60, 62, 64..126 and the octet is not a ";"
              in column 1.  All other characters are translated to =nn, where
              nn is the hexadecimal encoding of the octet.  All lines are
              "wrapped" with a terminating "=" (i.e. the MIME conventions
              for an implicit line terminator are never used).
;
    _item.name                  '_array_data.data'
    _item.category_id             array_data
    _item.mandatory_code          yes
    _item_type.code               binary
save_
 
 
######################
# ARRAY_ELEMENT_SIZE #
######################
 
 
save_ARRAY_ELEMENT_SIZE
    _category.description
;
     Data items in the ARRAY_ELEMENT_SIZE category record the physical 
     size of array elements along each array dimension.
;
    _category.id                   array_element_size
    _category.mandatory_code       no
     loop_
    _category_key.name             '_array_element_size.array_id'
                                   '_array_element_size.index'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
        Example 1 - A regular 2D array with a uniform element dimension
                    of 1220 nanometres.
;
;
        loop_
       _array_element_size.array_id  
       _array_element_size.index
       _array_element_size.size
        image_1   1    1.22e-6
        image_1   2    1.22e-6
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_
 
 
save__array_element_size.array_id
    _item_description.description
;             
              This item is a pointer to _array_structure.id in the
              ARRAY_STRUCTURE category. 
;
    _item.name                  '_array_element_size.array_id'
    _item.category_id             array_element_size
    _item.mandatory_code          yes
    _item_type.code               code
     save_
 
 
save__array_element_size.index
    _item_description.description
;             
              This item is a pointer to _array_structure_list.index in the
              ARRAY_STRUCTURE_LIST category. 
;
    _item.name                  '_array_element_size.index'
    _item.category_id             array_element_size
    _item.mandatory_code          yes
    _item_type.code               code
     save_
 
 
save__array_element_size.size
    _item_description.description
;
               The size in metres of an image element in this 
               dimension. This supposes that the elements are arranged
               on a regular grid.
;
    _item.name               '_array_element_size.size'
    _item.category_id          array_element_size
    _item.mandatory_code       yes 
    _item_type.code            float
    _item_units.code           'metres'
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            .   0.0
     save_
 
 
#####################
# ARRAY_INTENSITIES #
#####################
 
 
save_ARRAY_INTENSITIES
    _category.description
;
              Data items in the ARRAY_INTENSITIES category record the
              information required to recover the intensity data from 
              the set of data values stored in the ARRAY_DATA category.

              The actual detector may have a complex relationship
              between the raw intensity values and the number of
              incident photons.  In most cases, the number stored
              in the final array will have a simple linear relationship
              to the actual number of incident photons, given by
              '_array_intensities.gain'.  If raw, uncorrected values
              are presented (e.g for calibration experiments), the
              value of '_array_intensities.linearity' will be 'raw'
              and '_array_intensities.gain' will not be used.

;
    _category.id                   array_intensities
    _category.mandatory_code       no
    loop_
    _category_key.name             '_array_intensities.array_id'
                                   '_array_intensities.binary_id'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
        Example 1
;
;
        loop_
        _array_intensities.array_id
        _array_intensities.linearity 
        _array_intensities.gain      
        _array_intensities.overload  
        _array_intensities.undefined_value 
        image_1   linear  1.2    655535   0
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_
 
 
save__array_intensities.array_id
    _item_description.description
;             
              This item is a pointer to _array_structure.id in the
              ARRAY_STRUCTURE category. 
;
    _item.name                  '_array_intensities.array_id'
    _item.category_id             array_intensities
    _item.mandatory_code          yes
    _item_type.code               code
     save_
 
 
save__array_intensities.binary_id
    _item_description.description
;             This item is a pointer to _array_data.binary_id in the
              ARRAY_DATA category. 
;
    _item.name                  '_array_intensities.binary_id'
    _item.category_id             array_intensities
    _item.mandatory_code          implicit
    _item_type.code               int
     save_
 
 
save__array_intensities.gain
    _item_description.description
;              
               Detector "gain". The factor by which linearized 
               intensity count values should be divided to produce
               true photon counts.
;
    _item.name              '_array_intensities.gain'
    _item.category_id          array_intensities
    _item.mandatory_code       yes
    _item_type.code            float
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            .   0.0
    _item_units.code           'counts_per_photon'
     loop_
    _item_related.related_name
    _item_related.function_code  '_array_intensities.gain_esd'
                                 'associated_value'
    save_
 
  
save__array_intensities.gain_esd
    _item_description.description
;              
              The estimated standard deviation in detector "gain".
;
    _item.name              '_array_intensities.gain_esd'
    _item.category_id          array_intensities
    _item.mandatory_code       yes
    _item_type.code            float

    _item_units.code          'counts_per_photon'
     loop_
    _item_related.related_name
    _item_related.function_code  '_array_intensities.gain'
                                 'associated_esd'
    save_
 
 
save__array_intensities.linearity
    _item_description.description
;
               The intensity linearity scaling used from raw intensity
               to the stored element value:

               'linear' is obvious

               'offset'  means that the value defined by 
               '_array_intensities.offset' should be added to each
                element value.  

               'scaling' means that the value defined by 
               '_array_intensities.scaling' should be multiplied with each 
               element value.  

               'scaling_offset' is the combination of the two previous cases, 
               with the scale factor applied before the offset value.

               'sqrt_scaled' means that the square root of raw 
               intensities multiplied by '_array_intensities.scaling' is
               calculated and stored, perhaps rounded to the nearest 
               integer. Thus, linearization involves dividing the stored
               values by '_array_intensities.scaling' and squaring the 
               result. 

               'logarithmic_scaled' means that the logarithm based 10 of
               raw intensities multiplied by '_array_intensities.scaling' 
               is calculated and stored, perhaps rounded to the nearest 
               integer. Thus, linearization involves dividing the stored
               values by '_array_intensities.scaling' and calculating 10
               to the power of this number.

               'raw' means that the data is the raw is a set of raw values
               straight from the detector.
;

    _item.name               '_array_intensities.linearity'
    _item.category_id          array_intensities
    _item.mandatory_code       yes
    _item_type.code            code
     loop_
    _item_enumeration.value   
    _item_enumeration.detail   
                              'linear' .
                              'offset'           
;
               The value defined by  '_array_intensities.offset' should 
               be added to each element value.  
;
                              'scaling'
;
               The value defined by '_array_intensities.scaling' should be 
               multiplied with each element value.  
;
                              'scaling_offset'   
;
               The combination of the scaling and offset 
               with the scale factor applied before the offset value.
;
                              'sqrt_scaled'      
;
               The square root of raw intensities multiplied by 
               '_array_intensities.scaling' is calculated and stored, 
               perhaps rounded to the nearest integer. Thus, 
               linearization involves dividing the stored
               values by '_array_intensities.scaling' and squaring the 
               result. 
;
                              'logarithmic_scaled'
;
               The logarithm based 10 of raw intensities multiplied by 
               '_array_intensities.scaling'  is calculated and stored, 
               perhaps rounded to the nearest integer. Thus, 
               linearization involves dividing the stored values by 
               '_array_intensities.scaling' and calculating 10 to the 
               power of this number.
;
                              'raw'
;
               The array consists of raw values to which no corrections have
               been applied.  While the handling of the data is similar to 
               that given for 'linear' data with no offset, the meaning of 
               the data differs in that the number of incident photons is 
               not necessarily linearly related to the number of counts 
               reported.  This value is intended for use either in 
               calibration experiments or to allow for handling more 
               complex data fitting algorithms than are allowed for by 
               this data item.
;

    save_
  
  
save__array_intensities.offset
    _item_description.description
;
               Offset value to add to array element values in the manner
               described by item _array_intensities.linearity.
;
    _item.name                 '_array_intensities.offset'
    _item.category_id          array_intensities
    _item.mandatory_code       no
    _item_type.code            float
    save_
 
 
save__array_intensities.scaling
    _item_description.description
;
               Multiplicative scaling value to be applied to array data
               in the manner described by item _array_intensities.linearity.
;
    _item.name                 '_array_intensities.scaling'
    _item.category_id          array_intensities
    _item.mandatory_code       no
    _item_type.code            float
    save_
 
 
save__array_intensities.overload
    _item_description.description
;
               The saturation intensity level for this data array.
;
    _item.name                 '_array_intensities.overload'
    _item.category_id          array_intensities
    _item.mandatory_code       no
    _item_type.code            float
    _item_units.code          'counts'
    save_
 
  
save__array_intensities.undefined_value
    _item_description.description
;
               A value to be substituted for undefined values in 
               the data array.
;
    _item.name                 '_array_intensities.undefined_value'
    _item.category_id          array_intensities
    _item.mandatory_code       no
    _item_type.code            float
    save_
 
 
###################
# ARRAY_STRUCTURE #
###################
 
 
save_ARRAY_STRUCTURE
    _category.description
;
     Data items in the ARRAY_STRUCTURE category record the organization and 
     encoding of array data which may be stored in the ARRAY_DATA category.
;
    _category.id                   array_structure
    _category.mandatory_code       no
    _category_key.name             '_array_structure.id'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
    Example 1 -
;
;
     loop_
    _array_structure.id 
    _array_structure.encoding_type        
    _array_structure.compression_type     
    _array_structure.byte_order           
     image_1       "unsigned 16-bit integer"  none  little_endian
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_
 
 
save__array_structure.byte_order
    _item_description.description
;
               The order of bytes for integer values which require more
               than 1-byte. 

               (IBM-PC's and compatibles, and Dec-Vaxes use low-byte-first
               ordered integers, whereas Hewlett Packard 700 
               series, Sun-4 and Silicon Graphics use high-byte-first
               ordered integers.  Dec-Alphas can produce/use either
               depending on a compiler switch.)
;

    _item.name                     '_array_structure.byte_order'
    _item.category_id               array_structure
    _item.mandatory_code            yes 
    _item_type.code                 code
     loop_
    _item_enumeration.value        
    _item_enumeration.detail        
                                   'big_endian'
;
        The first byte in the byte stream of the bytes which make up an 
        integer value is the most significant byte of an integer. 
;
                                   'little_endian'
;
        The last byte in the byte stream of the bytes which make up an 
        integer value is the most significant byte of an integer.
;
     save_
 
 
save__array_structure.compression_type 
    _item_description.description
;
              Type of data compression method used to compress the array
              data. 
;
    _item.name                   '_array_structure.compression_type'
    _item.category_id             array_structure
    _item.mandatory_code          no 
    _item_type.code               code
    _item_default.value           'none'
     loop_
    _item_enumeration.value       
    _item_enumeration.detail
                                  'none'
;
        Data are stored in normal format as defined by 
        '_array_structure.encoding_type' and 
        '_array_structure.byte_order'.
;
                                  'byte_offsets'
;
        Using the compression scheme defined in CBF definition
        Section 5.0.
;
                                  'packed'
;
        Using the 'packed' compression scheme, a CCP4-style packing
        (CBFlib section 3.3.2)
;
                                  'canonical'
;
        Using the 'canonical' compression scheme (CBFlib section
        3.3.1)
;
    save_
 
 
save__array_structure.encoding_type
    _item_description.description
;
               Data encoding of a single element of array data. 
               
               In several cases, the IEEE format is referenced.
               See "IEEE Standard for Binary Floating-Point Arithmetic",
               ANSI/IEEE Std 754-1985, the Institute of Electrical and
               Electronics Engineers, Inc., NY 1985.  
;

    _item.name                '_array_structure.encoding_type'
    _item.category_id          array_structure
    _item.mandatory_code       yes 
    _item_type.code            uline
     loop_
    _item_enumeration.value   
                              'unsigned 8-bit integer'
                              'signed 8-bit integer'
                              'unsigned 16-bit integer'
                              'signed 16-bit integer'
                              'unsigned 32-bit integer'
                              'signed 32-bit integer'
                              'signed 32-bit real IEEE'
                              'signed 64-bit real IEEE'
                              'signed 32-bit complex IEEE'
     save_
 
 
save__array_structure.id
    _item_description.description
;             The value of _array_structure.id must uniquely identify 
              each item of array data. 
;
    loop_
    _item.name                  
    _item.category_id             
    _item.mandatory_code          
             '_array_structure.id'              array_structure      yes
             '_array_data.array_id'             array_data           yes
             '_array_structure_list.array_id'   array_structure_list yes
             '_array_intensities.array_id'      array_intensities    yes
             '_diffrn_data_frame.array_id'      diffrn_data_frame    yes
 

    _item_type.code               code
     loop_
    _item_linked.child_name
    _item_linked.parent_name
             '_array_data.array_id'             '_array_structure.id'
             '_array_structure_list.array_id'   '_array_structure.id'
             '_array_intensities.array_id'      '_array_structure.id'
             '_diffrn_data_frame.array_id'      '_array_structure.id'

     save_
 
 
########################
# ARRAY_STRUCTURE_LIST #
########################
 
 
save_ARRAY_STRUCTURE_LIST
    _category.description
;
     Data items in the ARRAY_STRUCTURE_LIST category record the size 
     and organization of each array dimension.

     The relationship to physical axes may be given.
;
    _category.id                   array_structure_list
    _category.mandatory_code       no
     loop_
    _category_key.name             '_array_structure_list.array_id'
                                   '_array_structure_list.index'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
        Example 1 - An image array of 1300 x 1200 elements.  The raster 
                    order of the image is left-to-right (increasing) in 
                    first dimension and bottom-to-top (decreasing) in 
                    the second dimension.
;
;
        loop_
       _array_structure_list.array_id  
       _array_structure_list.index
       _array_structure_list.dimension 
       _array_structure_list.precedence 
       _array_structure_list.direction
       _array_structure_list.axis_set_id
        image_1   1    1300    1     increasing  ELEMENT_X
        image_1   2    1200    2     decreasing  ELEMENY_Y
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_
 
 
save__array_structure_list.array_id
    _item_description.description
;             
              This item is a pointer to _array_structure.id in the
              ARRAY_STRUCTURE category. 
;
    _item.name                  '_array_structure_list.array_id'
    _item.category_id             array_structure_list
    _item.mandatory_code          yes
    _item_type.code               code
save_
 
 
save__array_structure_list.axis_set_id
    _item_description.description
;              This is a descriptor for the physical axis or set of axes 
               corresponding to an array index.
               
               This data item is related to the axes of the detector 
               itself given in DIFFRN_DETECTOR_AXIS, but usually differ
               in that the axes in this category are the axes of the
               coordinate system of reported data points, while the axes in
               DIFFRN_DETECTOR_AXIS are the physical axes 
               of the detector describing the "poise" of the detector as an
               overall physical object.
               
               If there is only one axis in the set, the identifier of 
               that axis should be used as the identifier of the set.
               
;
     loop_
    _item.name                
    _item.category_id          
    _item.mandatory_code       
           '_array_structure_list.axis_set_id'
                                  array_structure_list            yes
           '_array_structure_list_axis.axis_set_id'
                                  array_structure_list_axis       implicit
    _item_type.code               code
     loop_
    _item_linked.child_name
    _item_linked.parent_name
           '_array_structure_list_axis.axis_set_id'
                               '_array_structure_list.axis_set_id'


     save_
 
 
save__array_structure_list.dimension
    _item_description.description
;              
               The number of elements stored in the array structure in this 
               dimension.
;
    _item.name                '_array_structure_list.dimension'
    _item.category_id          array_structure_list
    _item.mandatory_code       yes 
    _item_type.code            int
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            1  1
                            .  1
     save_
 
 
save__array_structure_list.direction
    _item_description.description
;
              Identifies the direction in which this array index changes.
;
    _item.name                '_array_structure_list.direction'
    _item.category_id          array_structure_list
    _item.mandatory_code       yes 
    _item_type.code            int
     loop_
    _item_enumeration.value
    _item_enumeration.detail        

                              'increasing'
;
         Indicates the index changes from 1 to the maximum dimension.
;
                              'decreasing'
;
         Indicates the index changes from the maximum dimension to 1.
;
     save_
 
 
save__array_structure_list.index
    _item_description.description
;              
               Identifies the one-based index of the row or column in the
               array structure.
;
     loop_
    _item.name                
    _item.category_id          
    _item.mandatory_code       
           '_array_structure_list.index'        array_structure_list   yes
           '_array_structure_list.precedence'   array_structure_list   yes
           '_array_element_size.index'          array_element_size     yes

    _item_type.code            int

     loop_
    _item_linked.child_name
    _item_linked.parent_name
          '_array_element_size.index'         '_array_structure_list.index'
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            1  1
                            .  1
     save_
 
 
save__array_structure_list.precedence
    _item_description.description
;
               Identifies the rank order in which this array index changes 
               with respect to other array indices.  The precedence of 1  
               indicates the index which changes fastest.
;
    _item.name                '_array_structure_list.precedence'
    _item.category_id          array_structure_list
    _item.mandatory_code       yes 
    _item_type.code            int
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            1  1
                            .  1
     save_
 
 
#############################
# ARRAY_STRUCTURE_LIST_AXIS #
#############################
 
save_ARRAY_STRUCTURE_LIST_AXIS
    _category.description
;
     Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe
     the physical settings of sets axes for the centres of pixels that 
     correspond to data points described in the 
     ARRAY_STRUCTURE_LIST category. 
     
     In the simplest cases, the physical increments of a single axis correspond
     to the increments of a single array index.  More complex organizations,
     e.g. spiral scans, may require coupled motions along multiple axes.
     
     Note that a spiral scan uses two coupled axis, one for the angular 
     direction, one for the radial direction.  This differs from a 
     cylindrical scan for which the two axes are not coupled into one set.
     
;
    _category.id                   array_structure_list_axis
    _category.mandatory_code       no
     loop_
    _category_key.name
                                  '_array_structure_list_axis.axis_set_id'
                                  '_array_structure_list_axis.axis_id'
     loop_
    _category_group.id           'inclusive_group'
                                 'array_data_group'
     save_
 
 
save__array_structure_list_axis.axis_id
    _item_description.description
;
               The value of this data item is the identifier of one of
               the axes for the set of axes for which settings are being 
               specified.

               Multiple axes may be specified for the same value of
               '_array_structure_list_axis.axis_set_id'

               This item is a pointer to _axis.id in the
               AXIS category.
;
    _item.name                 '_array_structure_list_axis.axis_id'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       yes
     save_
 
 
save__array_structure_list_axis.axis_set_id
    _item_description.description
;
               The value of this data item is the identifier of the
               set of axes for which axis settings are being specified.

               Multiple axes may be specified for the same value of
               _array_structure_list_axis.axis_set_id .

               This item is a pointer to _array_structure_list.axis_set_id
               in the ARRAY_STRUCTURE_LIST category.
               
               If this item is not specified, it defaults to the corresponding
               axis identifier.
;
    _item.name                 '_array_structure_list_axis.axis_set_id'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       implicit
     save_
 
 
save__array_structure_list_axis.angle
    _item_description.description
;
               The setting of the specified axis in degrees for the first
               data point of the array index with the corresponding value
               of '_array_structure_list.axis_set_id'.  If the index is
               specified as 'increasing' this will be the center of the
               pixel with index value 1.  If the index is specified as
               'decreasing' this will be the center of the pixel with
               maximum index value. 
;
    _item.name                 '_array_structure_list_axis.angle'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       no 
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_
 
 
save__array_structure_list_axis.angle_increment
    _item_description.description
;
               The pixel-center-to-pixel-center increment in the angular 
               setting of the specified axis in degrees.  This is not 
               meaningful in the case of 'constant velocity' spiral scans  
               and should not be specified in that case.  

               See '_array_structure_list_axis.angular_pitch'.
               
;
    _item.name                 '_array_structure_list_axis.angle_increment'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_
 
 
save__array_structure_list_axis.displacement
    _item_description.description
;
               The setting of the specified axis in millimetres for the first
               data point of the array index with the corresponding value
               of '_array_structure_list.axis_set_id'.  If the index is
               specified as 'increasing' this will be the center of the
               pixel with index value 1.  If the index is specified as
               'decreasing' this will be the center of the pixel with
               maximum index value. 

;
    _item.name               '_array_structure_list_axis.displacement'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
 
 
save__array_structure_list_axis.displacement_increment
    _item_description.description
;
               The pixel-center-to-pixel-center increment for the displacement 
               setting of the specified axis in millimetres.
               
;
    _item.name                 
        '_array_structure_list_axis.displacement_increment'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
  
 
save__array_structure_list_axis.angular_pitch
    _item_description.description
;
               The pixel-center-to-pixel-center distance for a one step 
               change in the setting of the specified axis in millimetres.
               
               This is meaningful only for 'constant velocity' spiral scans,
               or for uncoupled angular scans at a constant radius
               (cylindrical scan) and should not be specified for cases
               in which the angle between pixels, rather than the distance
               between pixels is uniform.
               
               See '_array_structure_list_axis.angle_increment'.
               
;
    _item.name               '_array_structure_list_axis.angular_pitch'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
   
 
save__array_structure_list_axis.radial_pitch
    _item_description.description
;
               The radial distance from one "cylinder" of pixels to the
               next in millimetres.  If the scan is a 'constant velocity'
               scan with differing angular displacements between pixels,
               the value of this item may differ significantly from the
               value of '_array_structure_list_axis.displacement_increment'.
               
;
    _item.name               '_array_structure_list_axis.radial_pitch'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
  

 
########
# AXIS #
########

save_AXIS
    _category.description
;
     Data items in the AXIS category record the information required
     to describe the various goniometer, detector, source and other
     axes needed to specify a data collection.  The location of each
     axis is specified by two vectors: the axis itself, given as a unit
     vector, and an offset to the base of the unit vector.  These vectors
     are referenced to a right-handed laboratory coordinate system with
     its origin in the sample or specimen:
     
                             | Y (to complete right-handed system)
                             |
                             |
                             |
                             |
                             |
                             |________________X
                            /       principal goniometer axis
                           /
                          /
                         /
                        /
                       /Z (to source)
 
 
                                                      
     Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from
     the sample or specimen along the  principal axis of the goniometer.
     
     Axis 2 (Y): The Y-axis completes an orthogonal right-handed system
     defined by the X-axis and the Z-axis (see below).
     
     Axis 3 (Z): The Z-axis is derived from the source axis which goes from 
     the sample to the source.  The Z-axis is the component of the source axis
     in the direction of the source orthogonal to the X-axis in the plane 
     defined by the X-axis and the source axis.
          
     These axes are based on the goniometer, not on the orientation of the 
     detector, gravity, etc.  The vectors necessary to specify all other
     axes are given by sets of three components in the order (X, Y, Z).
     If the axis involved is a rotation axis, it is right handed, i.e. as
     one views the object to be rotated from the origin (the tail) of the 
     unit vector, the rotation is clockwise.  If a translation axis is
     specified, the direction of the unit vector specifies the sense of
     positive translation.
     
     Note:  This choice of coordinate system is similar to, but significantly
     different from the choice in MOSFLM (Andrew G.W. Leslie, Harry Powell,
     MRC Laboratory of Molecular Biology, Hills Road, Cambridge CB2 2QH,UK
     http://www.dl.ac.uk/CCP/CCP4/dist/x-windows/Mosflm/).  In MOSFLM,
     X is along the X-ray beam (our Z axis) and Z is along the rotation axis.

     All rotations are given in degrees and all translations are given in mm.
     
     Axes may be dependent on one another.  The X-axis is the only goniometer
     axis the direction of which is strictly connected to the hardware.  All
     other axes are specified by the positions they would assume when the
     axes upon which they depend are at their zero points.
     
     When specifying detector axes, the axis is given to the beam center.
     The location of the beam center on the detector should be given in the
     DIFFRN_DETECTOR category in distortion-corrected mm from the (0,0) corner
     of the detector.
     
     It should be noted that many different origins arise in the definition
     of an experiment.  In particular, as noted above, we need to specify the
     location of the beam center on the detector in terms of the origin of the
     detector, which is, of course, not coincident with the center of the
     sample.  
;
    _category.id                   axis
    _category.mandatory_code       no
     loop_
    _category_key.name          '_axis.id' 
                                '_axis.equipment'               
     loop_
    _category_group.id           'inclusive_group'
                                 'axis_group'
                                 'diffrn_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
        Example 1 -
        
        This example shows the axis specification of the axes of a kappa
        geometry goniometer (See "X-Ray Structure Determination, A Practical
        Guide", 2nd ed. by  G. H. Stout, L. H. Jensen, Wiley Interscience,
        1989, 453 pp, p 134.).
        
        There are three axes specified, and no offsets.  The outermost axis,
        omega, is pointed along the X-axis.  The next innermost axis, kappa,
        is at a 50 degree angle to the X-axis, pointed away from the source.
        The innermost axis, phi, aligns with the X-axis when omega and
        phi are at their zero-points.  If T-omega, T-kappa and T-phi
        are the transformation matrices derived from the axis settings,
        the complete transformation would be:
            x' = (T-omega) (T-kappa) (T-phi) x
;
;
         loop_
        _axis.id
        _axis.type
        _axis.equipment
        _axis.depends_on
        _axis.vector[1] _axis.vector[2] _axis.vector[3]
        omega rotation goniometer     .    1        0        0
        kappa rotation goniometer omega    -.64279  0       -.76604
        phi   rotation goniometer kappa    1        0        0   
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
        Example 2 -
        
        This example show the axis specification of the axes of a
        detector, source and gravity.  We have juggled the order as a
        reminder that the ordering of presentation of tokens is not
        significant.  We have taken the center of rotation of the detector
        to be 68 millimetres in the direction away from the source.
;
;
        loop_
        _axis.id
        _axis.type
        _axis.equipment
        _axis.depends_on
        _axis.vector[1] _axis.vector[2] _axis.vector[3]
        _axis.offset[1] _axis.offset[2] _axis.offset[3]
        source       .        source     .       0     0     1   . . .
        gravity      .        gravity    .       0    -1     0   . . .
        tranz     translation detector rotz      0     0     1   0 0 -68
        twotheta  rotation    detector   .       1     0     0   . . .
        roty      rotation    detector twotheta  0     1     0   0 0 -68
        rotz      rotation    detector roty      0     0     1   0 0 -68
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_
 
 
save__axis.depends_on
    _item_description.description
;             The value of  _axis.type specifies the next outermost
              axis upon which this axis depends.
              
              This item is a pointer to axis.id in the same category.
;
    _item.name                      '_axis.depends_on'
    _item.category_id                 axis
    _item.mandatory_code              no

     save_
 
 
save__axis.equipment
    _item_description.description
;             The value of  _axis.type specifies the type of equipment
              using the axis:  goniometer, detector, gravity, source
              or general
;
    _item.name                      '_axis.equipment'
    _item.category_id                 axis
    _item.mandatory_code              no
    _item_type.code                   ucode
    _item_default.value               general
     loop_
    _item_enumeration.value
    _item_enumeration.detail   goniometer
                              'equipment used to orient or position samples'
                               detector
                              'equipment used to detect reflections'
                               general
                              'equipment used for general purposes'
                               gravity
                              'axis specifying the downward direction'
                               source
                              'axis specifying the direction sample to source'

     save_
 
 
save__axis.offset[1]
    _item_description.description
;              The [1] element of the 3-element vector used to specify
               the offset to the base of a rotation or translation axis.
               
               The vector is specified in millimetres
;
    _item.name                  '_axis.offset[1]'
    _item.category_id             axis
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
    _item_units.code              millimetres
     save_
 
 
save__axis.offset[2]
    _item_description.description
;              The [2] element of the 3-element vector used to specify
               the offset to the base of a rotation or translation axis.
               
               The vector is specified in millimetres
;
    _item.name                  '_axis.offset[2]'
    _item.category_id             axis
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
    _item_units.code              millimetres
     save_
 
 
save__axis.offset[3]
    _item_description.description
;              The [3] element of the 3-element vector used to specify
               the offset to the base of a rotation or translation axis.
               
               The vector is specified in millimetres
;
    _item.name                  '_axis.offset[3]'
    _item.category_id             axis
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
    _item_units.code              millimetres
     save_
 
 
save__axis.id
    _item_description.description
;             The value of _axis.id must uniquely identify
              each axis relevant to the experiment.  Note that multiple
              pieces of equipment may share the same axis (e.g. a twotheta
              arm), so that the category key for AXIS also includes the
              equipment.
;
    loop_
    _item.name
    _item.category_id
    _item.mandatory_code
         '_axis.id'                         axis                    yes
         '_array_structure_list_axis.axis_id'
                                            array_structure_list_axis
                                                                    yes
         '_diffrn_detector_axis.axis_id'    diffrn_detector_axis    yes
         '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes
         '_diffrn_scan_axis.axis_id'        diffrn_scan_axis        yes
         '_diffrn_scan_frame_axis.axis_id'  diffrn_scan_frame_axis  yes

    _item_type.code               code
     loop_
    _item_linked.child_name
    _item_linked.parent_name
         '_axis.depends_on'                   '_axis.id'
         '_array_structure_list_axis.axis_id' '_axis.id'
         '_diffrn_detector_axis.axis_id'      '_axis.id'
         '_diffrn_measurement_axis.axis_id'   '_axis.id'
         '_diffrn_scan_axis.axis_id'          '_axis.id'      
         '_diffrn_scan_frame_axis.axis_id'    '_axis.id'

     save_
 
 
save__axis.type
    _item_description.description
;             The value of _axis.type specifies the type of
              axis:  rotation, translation (or general when the type is
              not relevant, as for gravity)
;
    _item.name                      '_axis.type'
    _item.category_id                 axis
    _item.mandatory_code              no
    _item_type.code                   ucode
    _item_default.value               general
     loop_
    _item_enumeration.value
    _item_enumeration.detail      rotation
                                 'right-handed axis of rotation'
                                  translation
                                 'translation in the direction of the axis'
                                  general
                                 'axis for which the type is not relevant'

     save_


save__axis.vector[1]
    _item_description.description
;              The [1] element of the 3-element vector used to specify
               the direction of a rotation or translation axis.
               The vector should be normalized to be a unit vector, and
               is dimensionless.
;
    _item.name                  '_axis.vector[1]'
    _item.category_id             axis
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
     save_

save__axis.vector[2]
    _item_description.description
;              The [2] element of the 3-element vector used to specify
               the direction of a rotation or translation axis.
               The vector should be normalized to be a unit vector, and
               is dimensionless.
;
    _item.name                  '_axis.vector[2]'
    _item.category_id             axis
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
     save_

save__axis.vector[3]
    _item_description.description
;              The [3] element of the 3-element vector used to specify
               the direction of a rotation or translation axis.
               The vector should be normalized to be a unit vector, and
               is dimensionless.
;
    _item.name                  '_axis.vector[3]'
    _item.category_id             axis
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
     save_
 

 
#####################
# DIFFRN_DATA_FRAME #
#####################
 
 
save_DIFFRN_DATA_FRAME
    _category.description
;
              Data items in the DIFFRN_DATA_FRAME category record
              the details about each frame of data. 
              
              The items in this category were previously in a
              DIFFRN_FRAME_DATA category, which is now deprecated.
              The items from the old category are provided
              as aliases, but should not be used for new work.
;
    _category.id                   diffrn_data_frame
    _category.mandatory_code       no
     loop_
    _category_key.name             '_diffrn_data_frame.id'
                                   '_diffrn_data_frame.detector_element_id'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
    Example 1 - A frame containing data from 4 frame elements.
                Each frame element has a common array configuration
                'array_1' described in ARRAY_STRUCTURE and related
                categories.  The data for each detector element is 
                stored in four groups of binary data in the
                ARRAY_DATA category, linked by the array_id and
                binary_id
;
;
        loop_
        _diffrn_data_frame.id
        _diffrn_data_frame.detector_element_id
        _diffrn_data_frame.array_id
        _diffrn_data_frame.binary_id
        frame_1   d1_ccd_1  array_1  1  
        frame_1   d1_ccd_2  array_1  2 
        frame_1   d1_ccd_3  array_1  3 
        frame_1   d1_ccd_4  array_1  4 
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    save_
 
 
save__diffrn_data_frame.array_id
    _item_description.description
;             
              This item is a pointer to _array_structure.id in the
              ARRAY_STRUCTURE category. 
;
    _item.name                  '_diffrn_data_frame.array_id'
    _item.category_id             diffrn_data_frame
    _item.mandatory_code          yes
    _item_aliases.alias_name    '_diffrn_frame_data.array_id'
    _item_aliases.dictionary      cif_img.dic
    _item_aliases.version         1.0.00
    _item_type.code               code
     save_
 
 
save__diffrn_data_frame.binary_id
    _item_description.description
;             This item is a pointer to _array_data.binary_id in the
              ARRAY_DATA category. 
;
    _item.name                  '_diffrn_data_frame.binary_id'
    _item.category_id             diffrn_data_frame
    _item.mandatory_code          implicit
    _item_aliases.alias_name    '_diffrn_frame_data.binary_id'
    _item_aliases.dictionary      cif_img.dic
    _item_aliases.version         1.0
    _item_type.code               int
     save_
 
 
save__diffrn_data_frame.detector_element_id
    _item_description.description
;             
               This item is a pointer to _diffrn_detector_element.id
               in the DIFFRN_DETECTOR_ELEMENT category. 
;
    _item.name                  '_diffrn_data_frame.detector_element_id'
    _item.category_id             diffrn_data_frame
    _item.mandatory_code          yes
    _item_aliases.alias_name    '_diffrn_frame_data.detector_element_id'
    _item_aliases.dictionary      cif_img.dic
    _item_aliases.version         1.0
    _item_type.code               code
     save_
 
 
save__diffrn_data_frame.id
    _item_description.description
;             
              The value of _diffrn_data_frame.id must uniquely identify
              each complete frame of data.
;
     loop_
    _item.name                
    _item.category_id          
    _item.mandatory_code       
           '_diffrn_data_frame.id'        diffrn_data_frame  yes
           '_diffrn_refln.frame_id'       diffrn_refln       yes
           '_diffrn_scan.frame_id_start'  diffrn_scan        yes
           '_diffrn_scan.frame_id_end'    diffrn_scan        yes
           '_diffrn_scan_frame.frame_id'  diffrn_scan_frame  yes
           '_diffrn_scan_frame_axis.frame_id'  
                                          diffrn_scan_frame_axis
                                                             yes
    _item_aliases.alias_name    '_diffrn_frame_data.id'
    _item_aliases.dictionary      cif_img.dic
    _item_aliases.version         1.0
    _item_type.code               code
     loop_
    _item_linked.child_name
    _item_linked.parent_name
           '_diffrn_refln.frame_id'        '_diffrn_data_frame.id'
           '_diffrn_scan.frame_id_start'   '_diffrn_data_frame.id'
           '_diffrn_scan.frame_id_end'     '_diffrn_data_frame.id'
           '_diffrn_scan_frame.frame_id'   '_diffrn_data_frame.id'
           '_diffrn_scan_frame_axis.frame_id'
                                           '_diffrn_data_frame.id'
     save_
 

##########################################################################
#  The following is a restatement of the mmCIF DIFFRN_DETECTOR,          #
#  DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for      #
#  the CBF/imgCIF extensions                                             #
##########################################################################

###################
# DIFFRN_DETECTOR #
###################
 
 
save_DIFFRN_DETECTOR
    _category.description
;              Data items in the DIFFRN_DETECTOR category describe the 
               detector used to measure the scattered radiation, including
               any analyser and post-sample collimation.
;
    _category.id                  diffrn_detector
    _category.mandatory_code      no
     loop_
    _category_key.name          '_diffrn_detector.diffrn_id'
                                '_diffrn_detector.id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
    Example 1 - based on PDB entry 5HVP and laboratory records for the
                structure corresponding to PDB entry 5HVP
;
;
    _diffrn_detector.diffrn_id             'd1'
    _diffrn_detector.detector              'multiwire'
    _diffrn_detector.type                  'Siemens'
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_
 
 
save__diffrn_detector.details
    _item_description.description
;              A description of special aspects of the radiation detector.
;
    _item.name                  '_diffrn_detector.details'
    _item.category_id             diffrn_detector
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_detector_details'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
    _item_examples.case
;                                 Need new example here.
;
     save_
 
 
save__diffrn_detector.detector
    _item_description.description
;              The general class of the radiation detector.
;
    _item.name                  '_diffrn_detector.detector'
    _item.category_id             diffrn_detector
    _item.mandatory_code          no
     loop_
    _item_aliases.alias_name
    _item_aliases.dictionary
    _item_aliases.version       '_diffrn_radiation_detector'
                                  cifdic.c91
                                  1.0
                                '_diffrn_detector'
                                  cif_core.dic
                                  2.0
    _item_type.code               text
     loop_
    _item_examples.case          'photographic film'
                                 'scintillation counter'
                                 'CCD plate'
                                 'BF~3~ counter'
     save_
 
 
save__diffrn_detector.diffrn_id
    _item_description.description
;              This data item is a pointer to _diffrn.id in the DIFFRN
               category.

               The value of _diffrn.id uniquely defines a set of
               diffraction data.
;
    _item.name                  '_diffrn_detector.diffrn_id'
    _item.mandatory_code          yes
     save_
 
 
save__diffrn_detector.dtime
    _item_description.description
;              The deadtime in microseconds of the detectors used to measure
               the diffraction intensities.
;
    _item.name                  '_diffrn_detector.dtime'
    _item.category_id             diffrn_detector
    _item.mandatory_code          no
     loop_
    _item_aliases.alias_name
    _item_aliases.dictionary
    _item_aliases.version       '_diffrn_radiation_detector_dtime'
                                  cifdic.c91
                                  1.0
                                '_diffrn_detector_dtime'
                                  cif_core.dic
                                  2.0
     loop_  
    _item_range.maximum           
    _item_range.minimum            .    0.0
                                  0.0   0.0
    _item_type.code               float
    _item_units.code              microseconds
     save_
 
 
save__diffrn_detector.id
    _item_description.description
;             
               The value of _diffrn_detector.id must uniquely identify
               each detector used to collect each diffraction data set.

               If the value of _diffrn_detector.id is not given, it is
               implicitly equal to the value of _diffrn_detector.diffrn_id
;
     loop_
    _item.name                 
    _item.category_id
    _item.mandatory_code
             '_diffrn_detector.id'         diffrn_detector       implicit
             '_diffrn_detector_axis.detector_id'
                                           diffrn_detector_axis       yes
     loop_
    _item_linked.child_name
    _item_linked.parent_name
             '_diffrn_detector_axis.detector_id'
                                         '_diffrn_detector.id'

    _item_type.code               code
     save_
 
 
save__diffrn_detector.number_of_axes
    _item_description.description
;             
               The value of _diffrn_detector.number_of_axes gives the 
               number of axes of the positioner for the detector identified 
               by _diffrn_detector.id
               
               The word "positioner" is a general term used in instrumentation
               design for devices that are used to change the positions of 
               portions of apparatus by linear translation, rotation, or 
               combinations of such motions.
               
               Axes which are used to provide a coordinate system for the
               face of an area detetctor should not be counted for this
               data item.

               The description of each axis should be provided by entries 
               in DIFFRN_DETECTOR_AXIS.
;
    _item.name                  '_diffrn_detector.number_of_axes'
    _item.category_id             diffrn_detector
    _item.mandatory_code          no
     loop_
    _item_range.maximum
    _item_range.minimum           .   1
                                  1   1
    _item_type.code               int
     save_
 
 
save__diffrn_detector.type
    _item_description.description
;              The make, model or name of the detector device used.
;
    _item.name                  '_diffrn_detector.type'
    _item.category_id             diffrn_detector
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_detector_type'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
     save_
 
 
########################
# DIFFRN_DETECTOR_AXIS #
########################
 
 
save_DIFFRN_DETECTOR_AXIS
    _category.description
;
     Data items in the DIFFRN_DETECTOR_AXIS category associate
     axes with detectors.
;
    _category.id                   diffrn_detector_axis
    _category.mandatory_code       no
     loop_
    _category_key.name          '_diffrn_detector_axis.detector_id'
                                '_diffrn_detector_axis.axis_id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     save_
 
 
save__diffrn_detector_axis.axis_id
    _item_description.description
;
               This data item is a pointer to _axis.id in
               the AXIS category.
;
    _item.name                  '_diffrn_detector_axis.axis_id'
    _item.category_id             diffrn_detector_axis
    _item.mandatory_code          yes
    _item_type.code               code
     save_
 
 
save__diffrn_detector_axis.detector_id
    _item_description.description
;
               This data item is a pointer to _diffrn_detector.id in
               the DIFFRN_DETECTOR category.

               This item was previously named '_diffrn_detector_axis.id'
               which is now a deprecated name.  The old name is
               provided as an alias, but should not be used for new work.

;
    _item.name                  '_diffrn_detector_axis.detector_id'
    _item.category_id             diffrn_detector_axis
    _item.mandatory_code          yes
    _item_aliases.alias_name    '_diffrn_detector_axis.id'
    _item_aliases.dictionary      cif_img.dic
    _item_aliases.version         1.0
     save_
 
 
###########################
# DIFFRN_DETECTOR_ELEMENT #
###########################
 
 
save_DIFFRN_DETECTOR_ELEMENT
    _category.description
;
              Data items in the DIFFRN_DETECTOR_ELEMENT category record
              the details about spatial layout and other characteristics
              of each element of a detector which may have multiple elements.
              
              In most cases, the more detailed information provided
              in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS
              are preferable to simply providing the centre.

;
    _category.id                   diffrn_detector_element
    _category.mandatory_code       no
     loop_
    _category_key.name             '_diffrn_detector_element.id'
                                   '_diffrn_detector_element.detector_id'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
        Example 1 - Detector d1 is composed of four CCD detector elements,
        each 200 mm by 200 mm, arranged in a square. in the pattern
                    
                   1     2
                      *
                   3     4

        Note that the beam center is slightly off of each of the
        detector elements, just beyond the lower right corner of 1,
        the lower left corner of 2, the upper right corner of 3 and
        the upper left corner of 4.
;
;
        loop_
        _diffrn_detector_element.id
        _diffrn_detector_element.detector_id
        _diffrn_detector_element.center[1]
        _diffrn_detector_element.center[2]
        d1     d1_ccd_1  201.5 -1.5
        d1     d1_ccd_2  -1.8  -1.5
        d1     d1_ccd_3  201.6 201.4  
        d1     d1_ccd_4  -1.7  201.5
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    save_
 
 
save__diffrn_detector_element.center[1]
    _item_description.description
;             
              The value of _diffrn_detector_element.center[1] is the X
              component of the distortion-corrected beam-center in mm from the
              (0, 0) (lower left) corner of the detector element viewed from 
              the sample side.
;
    _item.name                  '_diffrn_detector_element.center[1]'
    _item.category_id             diffrn_detector_element
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
    _item_units.code              millimetres

    save_
 
 
save__diffrn_detector_element.center[2]
    _item_description.description
;             
              The value of _diffrn_detector_element.center[2] is the Y
              component of the distortion-corrected beam-center in mm from the
              (0, 0) (lower left) corner of the detector element viewed from 
              the sample side.
;
    _item.name                  '_diffrn_detector_element.center[2]'
    _item.category_id             diffrn_detector_element
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
    _item_units.code              millimetres

    save_
 
 
save__diffrn_detector_element.id
    _item_description.description
;             
              The value of _diffrn_detector_element.id must uniquely identify
              each element of a detector.
;
     loop_
    _item.name                
    _item.category_id          
    _item.mandatory_code       
           '_diffrn_detector_element.id'
           diffrn_detector_element
           yes
    _item_type.code               code
     loop_
    _item_linked.child_name
    _item_linked.parent_name
           '_diffrn_data_frame.detector_element_id'
           '_diffrn_detector_element.id'

     save_
 
 
save__diffrn_detector_element.detector_id
    _item_description.description
;             
               This item is a pointer to _diffrn_detector.id
               in the DIFFRN_DETECTOR category. 
;
    _item.name                  '_diffrn_detector_element.detector_id'
    _item.category_id             diffrn_detector_element
    _item.mandatory_code          yes
    _item_type.code               code
     save_
 
 
 
########################
## DIFFRN_MEASUREMENT ##
########################
 
 
save_DIFFRN_MEASUREMENT
    _category.description
;              Data items in the DIFFRN_MEASUREMENT category record details
               about the device used to orient and/or position the crystal
               during data measurement and the manner in which the diffraction
               data were measured.
;
    _category.id                  diffrn_measurement
    _category.mandatory_code      no
     loop_
    _category_key.name          '_diffrn_measurement.device'
                                '_diffrn_measurement.diffrn_id'
                                '_diffrn_measurement.id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
    Example 1 - based on PDB entry 5HVP and laboratory records for the
                structure corresponding to PDB entry 5HVP
;
;
    _diffrn_measurement.diffrn_id          'd1'
    _diffrn_measurement.device             '3-circle camera'
    _diffrn_measurement.device_type        'Supper model x'
    _diffrn_measurement.device_details     'none'
    _diffrn_measurement.method             'omega scan'
    _diffrn_measurement.details
    ; Need new example here
    ;
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
    Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991).
                Acta Cryst. C47, 2276-2277].
;
;
    _diffrn_measurement.diffrn_id       's1'
    _diffrn_measurement.device_type     'Philips PW1100/20 diffractometer'
    _diffrn_measurement.method          'theta/2theta (\q/2\q)'
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_
 
 
save__diffrn_measurement.device
    _item_description.description
;              The general class of goniometer or device used to support and
               orient the specimen.
               
               If the value of _diffrn_measurement.device is not given, it is
               implicitly equal to the value of _diffrn_measurement.diffrn_id

               Either '_diffrn_measurement.device' or '_diffrn_measurement.id'
               may be used to link to other categories.  If the experimental
               setup admits multiple devices, then '_diffrn_measurement.id'
               is used to provide a unique link.
               
;
     loop_
    _item.name
    _item.category_id
    _item.mandatory_code
             '_diffrn_measurement.device'  diffrn_measurement      implicit
             '_diffrn_measurement_axis.measurement_device' 
                                           diffrn_measurement_axis implicit
     loop_
    _item_linked.child_name
    _item_linked.parent_name
             '_diffrn_measurement_axis.measurement_device'  
                                         '_diffrn_measurement.device'
    _item_aliases.alias_name    '_diffrn_measurement_device'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
     loop_
    _item_examples.case          '3-circle camera'
                                 '4-circle camera'
                                 'kappa-geometry camera'
                                 'oscillation camera'
                                 'precession camera'
     save_
 
 
save__diffrn_measurement.device_details
    _item_description.description
;              A description of special aspects of the device used to measure
               the diffraction intensities.
;
    _item.name                  '_diffrn_measurement.device_details'
    _item.category_id             diffrn_measurement
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_measurement_device_details'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
    _item_examples.case
;                                 commercial goniometer modified locally to
                                  allow for 90\% \t arc
;
     save_
 
 
save__diffrn_measurement.device_type
    _item_description.description
;              The make, model or name of the measurement device
               (goniometer) used.
;
    _item.name                  '_diffrn_measurement.device_type'
    _item.category_id             diffrn_measurement
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_measurement_device_type'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
     loop_
    _item_examples.case          'Supper model q'
                                 'Huber model r'
                                 'Enraf-Nonius model s'
                                 'homemade'
     save_
 
 
save__diffrn_measurement.diffrn_id
    _item_description.description
;              This data item is a pointer to _diffrn.id in the DIFFRN 
               category.
;
    _item.name                  '_diffrn_measurement.diffrn_id'
    _item.mandatory_code          yes
     save_
 
 
save__diffrn_measurement.details
    _item_description.description
;              A description of special aspects of the intensity measurement.
;
    _item.name                  '_diffrn_measurement.details'
    _item.category_id             diffrn_measurement
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_measurement_details'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
    _item_examples.case
;                                 440 frames, 0.20 degrees, 150 sec, detector
                                  distance 12 cm, detector angle 22.5 degrees
;
     save_
 
 
save__diffrn_measurement.id
    _item_description.description
;             
               The value of _diffrn_measurement.id must uniquely identify
               the set of mechanical characteristics of the device used to 
               orient and/or position the sample used during collection 
               of each diffraction data set.

               If the value of _diffrn_measurement.id is not given, it is
               implicitly equal to the value of _diffrn_measurement.diffrn_id

               Either '_diffrn_measurement.device' or '_diffrn_measurement.id'
               may be used to link to other categories.  If the experimental
               setup admits multiple devices, then '_diffrn_measurement.id'
               is used to provide a unique link.
;
     loop_
    _item.name                 
    _item.category_id
    _item.mandatory_code
             '_diffrn_measurement.id'      diffrn_measurement      implicit
             '_diffrn_measurement_axis.measurement_id'
                                           diffrn_measurement_axis implicit
     loop_
    _item_linked.child_name
    _item_linked.parent_name
             '_diffrn_measurement_axis.measurement_id'
                                         '_diffrn_measurement.id'

    _item_type.code               code
     save_
 
 
save__diffrn_measurement.method
    _item_description.description
;              Method used to measure intensities.
;
    _item.name                  '_diffrn_measurement.method'
    _item.category_id             diffrn_measurement
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_measurement_method'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
    _item_examples.case         'profile data from theta/2theta (\q/2\q) scans'
     save_
 
 
save__diffrn_measurement.number_of_axes
    _item_description.description
;             
               The value of _diffrn_measurement.number_of_axes gives the 
               number of axes of the positioner for the goniometer or
               other sample orientation or positioning device identified 
               by _diffrn_measurement.id

               The description of the axes should be provided by entries in 
               DIFFRN_MEASUREMENT_AXIS.
;
    _item.name                  '_diffrn_measurement.number_of_axes'
    _item.category_id             diffrn_measurement
    _item.mandatory_code          no
     loop_
    _item_range.maximum
    _item_range.minimum           .   1
                                  1   1
    _item_type.code               int
     save_
 
 
save__diffrn_measurement.specimen_support
    _item_description.description
;              The physical device used to support the crystal during data
               collection.
;
    _item.name                  '_diffrn_measurement.specimen_support'
    _item.category_id             diffrn_measurement
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_measurement_specimen_support'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
     loop_
    _item_examples.case          'glass capillary'
                                 'quartz capillary'
                                 'fiber'
                                 'metal loop'
     save_
 
 
###########################
# DIFFRN_MEASUREMENT_AXIS #
###########################
 
 
save_DIFFRN_MEASUREMENT_AXIS
    _category.description
;
     Data items in the DIFFRN_MEASUREMENT_AXIS category associate
     axes with goniometers.
;
    _category.id                   diffrn_measurement_axis
    _category.mandatory_code       no
     loop_
    _category_key.name          '_diffrn_measurement_axis.measurement_device'
                                '_diffrn_measurement_axis.measurement_id'
                                '_diffrn_measurement_axis.axis_id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     save_
 
 
save__diffrn_measurement_axis.axis_id
    _item_description.description
;
               This data item is a pointer to _axis.id in
               the AXIS category.
;
    _item.name                  '_diffrn_measurement_axis.axis_id'
    _item.category_id             diffrn_measurement_axis
    _item.mandatory_code          yes
    _item_type.code               code
     save_
 
 
save__diffrn_measurement_axis.measurement_device
    _item_description.description
;
               This data item is a pointer to _diffrn_measurement.device in
               the DIFFRN_MEASUREMENT category.

;
    _item.name                  '_diffrn_measurement_axis.measurement_device'
    _item.category_id             diffrn_measurement_axis
    _item.mandatory_code          implicit
     save_
 
 
save__diffrn_measurement_axis.measurement_id
    _item_description.description
;
               This data item is a pointer to _diffrn_measurement.id in
               the DIFFRN_MEASUREMENT category.
              
               This item was previously named '_diffrn_measurement_axis.id'
               which is now a deprecated name.  The old name is
               provided as an alias, but should not be used for new work.

;
    _item.name                  '_diffrn_measurement_axis.measurement_id'
    _item.category_id             diffrn_measurement_axis
    _item_aliases.alias_name    '_diffrn_measurement_axis.id'
    _item_aliases.dictionary      cif_img.dic
    _item_aliases.version         1.0.00
    _item.mandatory_code          implicit
     save_

 
####################
# DIFFRN_RADIATION #
####################
 
 
save_DIFFRN_RADIATION
    _category.description
;              Data items in the DIFFRN_RADIATION category describe
               the radiation used in measuring diffraction intensities,
               its collimation and monochromatisation before the sample.

               Post-sample treatment of the beam is described by data
               items in the DIFFRN_DETECTOR category.

;
    _category.id                  diffrn_radiation
    _category.mandatory_code      no
    _category_key.name          '_diffrn_radiation.diffrn_id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
    Example 1 - based on PDB entry 5HVP and laboratory records for the
                structure corresponding to PDB entry 5HVP
;
;
    _diffrn_radiation.diffrn_id            'set1'

    _diffrn_radiation.collimation          '0.3 mm double pinhole'
    _diffrn_radiation.monochromator        'graphite'
    _diffrn_radiation.type                 'Cu K\a'
    _diffrn_radiation.wavelength_id         1
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
    Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991).
                Acta Cryst. C47, 2276-2277].
;
;
    _diffrn_radiation.wavelength_id    1
    _diffrn_radiation.type             'Cu K\a'
    _diffrn_radiation.monochromator    'graphite'
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_

save__diffrn_radiation.collimation
    _item_description.description
;              The collimation or focusing applied to the radiation.
;
    _item.name                  '_diffrn_radiation.collimation'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_collimation'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
     loop_
    _item_examples.case          '0.3 mm double-pinhole'
                                 '0.5 mm'
                                 'focusing mirrors'
     save_


save__diffrn_radiation.diffrn_id
    _item_description.description
;              This data item is a pointer to _diffrn.id in the DIFFRN
               category.
;
    _item.name                  '_diffrn_radiation.diffrn_id'
    _item.mandatory_code          yes
     save_

 
 
save__diffrn_radiation.div_x_source
    _item_description.description
;              Beam crossfire in degrees parallel to the laboratory X axis
               (see AXIS category).
               
               This is a characteristic of the xray beam as it illuminates
               the sample (or specimen) after all monochromation and 
               collimation.
               
               This is the esd of the directions of photons in the X-Z plane
               around the mean source beam direction.
               
               Note that some synchrotrons specify this value in milliradians,
               in which case a conversion would be needed.  To go from a
               value in milliradians to a value in degrees, multiply by 0.180
               and divide by Pi.

;
    _item.name                  '_diffrn_radiation.div_x_source'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_type.code               float
    _item_units.code              degrees
     save_
 
 
save__diffrn_radiation.div_y_source
    _item_description.description
;              Beam crossfire in degrees parallel to the laboratory Y axis
               (see AXIS category).
               
               This is a characteristic of the xray beam as it illuminates
               the sample (or specimen) after all monochromation and 
               collimation.
               
               This is the esd of the directions of photons in the Y-Z plane
               around the mean source beam direction.

               Note that some synchrotrons specify this value in milliradians,
               in which case a conversion would be needed.  To go from a
               value in milliradians to a value in degrees, multiply by 0.180
               and divide by Pi.

;
    _item.name                  '_diffrn_radiation.div_y_source'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_type.code               float
    _item_units.code              degrees
    _item_default.value           0.0
     save_
 
 
save__diffrn_radiation.div_x_y_source
    _item_description.description
;              Beam crossfire correlation degrees**2 between the
               crossfire laboratory X-axis component and the crossfire
               laboratory Y-axis component (see AXIS category).
               
               This is a characteristic of the xray beam as it illuminates
               the sample (or specimen) after all monochromation and 
               collimation.
               
               This is the mean of the products of the deviations of the
               directin of each photons in X-Z plane times the deviations
               of the direction of the same photon in the Y-Z plane
               around the mean source beam direction.  This will be zero
               for uncorrelated crossfire.
               
               Note that some synchrotrons specify this value in 
               milliradians**2, in which case a conversion would be needed.  
               To go from a value in milliradians**2 to a value in
               degrees**2, multiply by 0.180**2 and divide by Pi**2.

;
    _item.name                  '_diffrn_radiation.div_x_y_source'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_type.code               float
    _item_units.code              degrees_squared
    _item_default.value           0.0
     save_

save__diffrn_radiation.filter_edge
    _item_description.description
;              Absorption edge in angstroms of the radiation filter used.
;
    _item.name                  '_diffrn_radiation.filter_edge'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_filter_edge'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
     loop_
    _item_range.maximum           
    _item_range.minimum            .    0.0
                                  0.0   0.0
    _item_type.code               float
    _item_units.code              angstroms
     save_

save__diffrn_radiation.inhomogeneity
    _item_description.description
;              Half-width in millimetres of the incident beam in the
               direction perpendicular to the diffraction plane.
;
    _item.name                  '_diffrn_radiation.inhomogeneity'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_inhomogeneity'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
     loop_
    _item_range.maximum           
    _item_range.minimum            .    0.0
                                  0.0   0.0
    _item_type.code               float
    _item_units.code              millimetres
     save_

save__diffrn_radiation.monochromator
    _item_description.description
;              The method used to obtain monochromatic radiation. If a mono-
               chromator crystal is used the material and the indices of the
               Bragg reflection are specified.
;
    _item.name                  '_diffrn_radiation.monochromator'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_monochromator'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
     loop_
    _item_examples.case          'Zr filter'
                                 'Ge 220'
                                 'none'
                                 'equatorial mounted graphite'
     save_

save__diffrn_radiation.polarisn_norm
    _item_description.description
;              The angle in degrees, as viewed from the specimen, between the
               perpendicular component of the polarisation and the diffraction
               plane. See _diffrn_radiation_polarisn_ratio.
;
    _item.name                  '_diffrn_radiation.polarisn_norm'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_polarisn_norm'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
     loop_
    _item_range.maximum           
    _item_range.minimum           90.0  90.0
                                  90.0 -90.0
                                 -90.0 -90.0
    _item_type.code               float
    _item_units.code              degrees
     save_

save__diffrn_radiation.polarisn_ratio
    _item_description.description
;              Polarisation ratio of the diffraction beam incident on the
               crystal. It is the ratio of the perpendicularly polarised to the
               parallel polarised component of the radiation. The perpendicular
               component forms an angle of _diffrn_radiation.polarisn_norm to
               the normal to the diffraction plane of the sample (i.e. the
               plane containing the incident and reflected beams).
;
    _item.name                  '_diffrn_radiation.polarisn_ratio'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_polarisn_ratio'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
     loop_
    _item_range.maximum           
    _item_range.minimum            .    0.0
                                  0.0   0.0
    _item_type.code               float
     save_

 
 
save__diffrn_radiation.polarizn_source_norm
    _item_description.description
;              The angle in degrees, as viewed from the specimen, between the
               normal to the polarization plane and the laboratory Y axis as
               defined in the AXIS category.
               
               Note that this is the angle of polarization of the source 
               photons, either directly from a synchrotron beamline or
               from a monchromater.
               
               This differs from the value of '_diffrn_radiation.polarisn_norm'
               in that '_diffrn_radiation.polarisn_norm' refers to polarization
               relative to the diffraction plane rather than to the laboratory
               axis system.
               
               In the case of an unpolarized beam, or a beam with true circular
               polarization, in which no single plane of polarization can be
               determined, the plane should be taken as the X-Z plane, and the
               angle as 0.
               
               See '_diffrn_radiation.polarizn_source_ratio'.
;
    _item.name                  '_diffrn_radiation.polarizn_source_norm'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
     loop_
    _item_range.maximum           
    _item_range.minimum           90.0   90.0
                                  90.0  -90.0
                                 -90.0  -90.0
    _item_type.code               float
    _item_units.code              degrees
    _item_default.value           0.0
     save_
 
 
save__diffrn_radiation.polarizn_source_ratio
    _item_description.description
;              (Ip-In)/(Ip+In), where Ip is the intensity (amplitude squared)
               of the electric vector in the plane of polarization and In is
               the intensity (amplitude squared) of the electric vector
               in plane of the normal to the plane of polarization.
               
               Thus, if we had complete polarization in the plane of
               polarization, the value of 
               '_diffrn_radiation.polarizn_source_ratio' would
               be 1, and an unpolarized beam would have a value of 0.
               
               If the X-axis has been chosen to lie in the plane of
               polarization, this definition will agree with the definition
               of "MONOCHROMATOR" in the Denzo glossary, and values of near
               1 should be expected for a bending magnet source.  However,
               if the X-axis were, for some reason to be, say, perpendicular
               to the polarization plane (not a common choice), then the
               Denzo value would be the negative of
               '_diffrn_radiation.polarizn_source_ratio'.
               
               See http://www.hkl-xray.com for information on Denzo, and
               Z. Otwinowski and W. Minor, " Processing of X-ray Diffraction
               Data Collected in Oscillation Mode ", Methods in Enzymology, 
               Volume 276: Macromolecular Crystallography, part A, p.307-326,
               1997,C.W. Carter, Jr. & R. M. Sweet, Eds., Academic Press.

               This differs both in the choice of ratio and choice of
               orientation from '_diffrn_radiation.polarisn_ratio', which,
               unlike '_diffrn_radiation.polarizn_source_ratio', is unbounded.

;
    _item.name                  '_diffrn_radiation.polarizn_source_ratio'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
     loop_
    _item_range.maximum           
    _item_range.minimum           1.0    1.0
                                  1.0   -1.0
                                 -1.0   -1.0
    _item_type.code               float
     save_


save__diffrn_radiation.probe
    _item_description.description
;              Name of the type of radiation used. It is strongly encouraged
               that this field be specified so that the probe radiation
               can be simply determined.
;
    _item.name                  '_diffrn_radiation.probe'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_probe'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               line
     loop_
    _item_enumeration.value      'x-ray'
                                 'neutron'
                                 'electron'
                                 'gamma'
     save_

save__diffrn_radiation.type
    _item_description.description
;              The nature of the radiation. This is typically a description
               of the X-ray wavelength in Siegbahn notation.
;
    _item.name                  '_diffrn_radiation.type'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_type'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               line
     loop_
    _item_examples.case          'CuK\a'
                                 'Cu K\a~1~'
                                 'Cu K-L~2,3~' 
                                 'white-beam'

     save_

save__diffrn_radiation.xray_symbol
    _item_description.description
;              The IUPAC symbol for the X-ray wavelength for probe radiation.
;
    _item.name                  '_diffrn_radiation.xray_symbol'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_xray_symbol'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               line
     loop_
    _item_enumeration.value
    _item_enumeration.detail     'K-L~3~'
                                 'K\a~1~ in older Siegbahn notation'
                                 'K-L~2~'
                                 'K\a~2~ in older Siegbahn notation'
                                 'K-M~3~'
                                 'K\b~1~ in older Siegbahn notation'
                                 'K-L~2,3~'
                                 'use where K-L~3~ and K-L~2~ are not resolved'
     save_

save__diffrn_radiation.wavelength_id
    _item_description.description
;              This data item is a pointer to _diffrn_radiation_wavelength.id
               in the DIFFRN_RADIATION_WAVELENGTH category.
;
    _item.name                  '_diffrn_radiation.wavelength_id'
    _item.mandatory_code          yes
     save_


 
################
# DIFFRN_REFLN #
################
 
 
save_DIFFRN_REFLN
    _category.description 
;
     This category redefinition has been added to extend the key of 
     the standard DIFFRN_REFLN category.
;
    _category.id                   diffrn_refln
    _category.mandatory_code       no
    _category_key.name             '_diffrn_refln.frame_id'
     loop_
    _category_group.id             'inclusive_group'
                                   'diffrn_group'
     save_
 
 
save__diffrn_refln.frame_id
    _item_description.description
;             
               This item is a pointer to _diffrn_data_frame.id
               in the DIFFRN_DATA_FRAME category. 
;
    _item.name                  '_diffrn_refln.frame_id'
    _item.category_id             diffrn_refln
    _item.mandatory_code          yes
    _item_type.code               code
     save_
 
 
###############
# DIFFRN_SCAN #
###############

save_DIFFRN_SCAN
    _category.description 
;
     Data items in the DIFFRN_SCAN category describe the parameters of one
     or more scans, relating axis positions to frames.

;
    _category.id                   diffrn_scan
    _category.mandatory_code       no
    _category_key.name            '_diffrn_scan.id'
     loop_
    _category_group.id            'inclusive_group'
                                  'diffrn_group'
     loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
    Example 1 - derived from a suggestion by R. M. Sweet.

   The vector of each axis is not given here, because it is provided in
   the AXIS category.  By making _diffrn_scan_axis.scan_id and
   _diffrn_scan_axis.axis_id keys of the DIFFRN_SCAN_AXIS category,
   an arbitrary number of scanning and fixed axes can be specified for a 
   scan.  We have specified three rotation axes and one translation axis 
   at non-zero values, with one axis stepping.  There is no reason why 
   more axes could not have been specified to step.   We have specified
   range information, but note that it is redundant from the  number of 
   frames and the increment, so we could drop the data item
   _diffrn_scan_axis.angle_range .
   
   We have specified both the sweep data and the data for a single frame.
 
   Note that the information on how the axes are stepped is given twice,
   once in terms of the overall averages in the value of
   '_diffrn_scan.integration_time' and the values for DIFFRN_SCAN_AXIS,
   and precisely for the given frame in the value for 
   '_diffrn_scan_frame.integration_time' and the values for
   DIFFRN_SCAN_FRAME_AXIS.  If dose-related adjustements are made to
   scan times and non-linear stepping is done, these values may differ.
   Therefore, in interpreting the data for a particular frame it is
   important to use the frame-specific data.
 
;
;
      _diffrn_scan.id                   1
      _diffrn_scan.date_start         '2001-11-18T03:26:42'
      _diffrn_scan.date_end           '2001-11-18T03:36:45'
      _diffrn_scan.integration_time    3.0
      _diffrn_scan.frame_id_start      mad_L2_000
      _diffrn_scan.frame_id_end        mad_L2_200
      _diffrn_scan.frames              201

       loop_
      _diffrn_scan_axis.scan_id
      _diffrn_scan_axis.axis_id
      _diffrn_scan_axis.angle_start
      _diffrn_scan_axis.angle_range
      _diffrn_scan_axis.angle_increment
      _diffrn_scan_axis.displacement_start
      _diffrn_scan_axis.displacement_range
      _diffrn_scan_axis.displacement_increment

       1 omega 200.0 20.0 0.1 . . . 
       1 kappa -40.0  0.0 0.0 . . . 
       1 phi   127.5  0.0 0.0 . . . 
       1 tranz  . . .   2.3 0.0 0.0 

      _diffrn_scan_frame.scan_id                   1
      _diffrn_scan_frame.date               '2001-11-18T03:27:33'
      _diffrn_scan_frame.integration_time    3.0
      _diffrn_scan_frame.frame_id            mad_L2_018
      _diffrn_scan_frame.frame_number        18

      loop_
      _diffrn_scan_frame_axis.frame_id
      _diffrn_scan_frame_axis.axis_id
      _diffrn_scan_frame_axis.angle
      _diffrn_scan_frame_axis.angle_increment
      _diffrn_scan_frame_axis.displacement
      _diffrn_scan_frame_axis.displacement_increment

       mad_L2_018 omega 201.8  0.1 . .
       mad_L2_018 kappa -40.0  0.0 . .
       mad_L2_018 phi   127.5  0.0 . .
       mad_L2_018 tranz  .     .  2.3 0.0

;

;
    Example 2 - a more extensive example, R. M. Sweet, P. Ellis, H. Bernstein.
    
   We place a detector 240 mm along the Z axis from the goniometer.
   This presents us with a choice -- either we define the axes of
   the detector at the origin, and then put a Z setting of -240 in
   for the actual use, or we define the axes with the necessary Z-offset.
   In this case we use the setting, and leave the offset as zero.
   We call this axis DETECTOR_Z.
   
   The axis for positioning the detector in the Y-direction depends
   on the detector Z-axis.  We call this axis, DETECTOR_Y.
   
   The axis for positioning the dector in the X-direction depends
   on the detector Y-axis (and therefore on the detector Z-axis).
   We call this axis DETECTOR_X.
   
   This detector may be rotated around the Y-axis.  This rotation axis
   depends on the three translation axies.  We call it DETECTOR_PITCH.
   
   We define a coordinate system on the face of the detector in terms of
   2300 0.150 mm pixels in each direction.  The ELEMENT_X axis is used to
   index the first array index of the data array and the ELEMENT_Y
   axis is used to index the second array index.  Because the pixels
   are 0.150mm x 0.150mm, the center of the first pixel is at (0.075, 
   0.075) in this coordinate system.
 
;
;
     ###CBF: VERSION 1.1 

     data_image_1 
 

     # category DIFFRN 

     _diffrn.id P6MB 
     _diffrn.crystal_id P6MB_CRYSTAL7 
 

     # category DIFFRN_SOURCE 

     loop_ 
     _diffrn_source.diffrn_id 
     _diffrn_source.source 
     _diffrn_source.type 
      P6MB synchrotron 'SSRL beamline 9-1' 
 

     # category DIFFRN_RADIATION 

          loop_ 
     _diffrn_radiation.diffrn_id 
     _diffrn_radiation.wavelength_id 
     _diffrn_radiation.monochromator 
     _diffrn_radiation.polarizn_source_ratio 
     _diffrn_radiation.polarizn_source_norm 
     _diffrn_radiation.div_x_source 
     _diffrn_radiation.div_y_source 
     _diffrn_radiation.div_x_y_source 
      P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08
     0.01 0.00 
 

     # category DIFFRN_RADIATION_WAVELENGTH 

     loop_ 
     _diffrn_radiation_wavelength.id 
     _diffrn_radiation_wavelength.wavelength 
     _diffrn_radiation_wavelength.wt 
      WAVELENGTH1 0.98 1.0 
 

     # category DIFFRN_DETECTOR 

     loop_ 
     _diffrn_detector.diffrn_id 
     _diffrn_detector.id 
     _diffrn_detector.type 
     _diffrn_detector.number_of_axes 
      P6MB MAR345-SN26 'MAR 345' 4 
 

     # category DIFFRN_DETECTOR_AXIS 

     loop_ 
     _diffrn_detector_axis.id 
     _diffrn_detector_axis.axis_id 
      MAR345-SN26 DETECTOR_X 
      MAR345-SN26 DETECTOR_Y 
      MAR345-SN26 DETECTOR_Z 
      MAR345-SN26 DETECTOR_PITCH 
 

     # category DIFFRN_DETECTOR_ELEMENT 

     loop_ 
     _diffrn_detector_element.id 
     _diffrn_detector_element.detector_id 
      ELEMENT1 MAR345-SN26 
 

     # category DIFFRN_DATA_FRAME 

     loop_ 
     _diffrn_data_frame.id 
     _diffrn_data_frame.detector_element_id 
     _diffrn_data_frame.array_id 
     _diffrn_data_frame.binary_id 
      FRAME1 ELEMENT1 ARRAY1 1 
 

     # category DIFFRN_MEASUREMENT 

     loop_ 
     _diffrn_measurement.diffrn_id 
     _diffrn_measurement.id 
     _diffrn_measurement.number_of_axes 
     _diffrn_measurement.method 
      P6MB GONIOMETER 3 rotation 
 

     # category DIFFRN_MEASUREMENT_AXIS 

     loop_ 
     _diffrn_measurement_axis.measurement_id 
     _diffrn_measurement_axis.axis_id 
      GONIOMETER GONIOMETER_PHI 
      GONIOMETER GONIOMETER_KAPPA 
      GONIOMETER GONIOMETER_OMEGA 
 

     # category DIFFRN_SCAN 

     loop_ 
     _diffrn_scan.id 
     _diffrn_scan.frame_id_start 
     _diffrn_scan.frame_id_end 
     _diffrn_scan.frames 
      SCAN1 FRAME1 FRAME1 1 
 

     # category DIFFRN_SCAN_AXIS 

     loop_ 
     _diffrn_scan_axis.scan_id 
     _diffrn_scan_axis.axis_id 
     _diffrn_scan_axis.angle_start 
     _diffrn_scan_axis.angle_range 
     _diffrn_scan_axis.angle_increment 
     _diffrn_scan_axis.displacement_start 
     _diffrn_scan_axis.displacement_range 
     _diffrn_scan_axis.displacement_increment 
      SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 
      SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 
      SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 
      SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 
      SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 
      SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 
      SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 
 

     # category DIFFRN_SCAN_FRAME 

     loop_ 
     _diffrn_scan_frame.frame_id 
     _diffrn_scan_frame.frame_number 
     _diffrn_scan_frame.integration_time 
     _diffrn_scan_frame.scan_id 
     _diffrn_scan_frame.date 
      FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 
 

     # category DIFFRN_SCAN_FRAME_AXIS 

     loop_ 
     _diffrn_scan_frame_axis.frame_id 
     _diffrn_scan_frame_axis.axis_id 
     _diffrn_scan_frame_axis.angle 
     _diffrn_scan_frame_axis.displacement 
      FRAME1 GONIOMETER_OMEGA 12.0 0.0 
      FRAME1 GONIOMETER_KAPPA 23.3 0.0 
      FRAME1 GONIOMETER_PHI -165.8 0.0 
      FRAME1 DETECTOR_Z 0.0 -240.0 
      FRAME1 DETECTOR_Y 0.0 0.6 
      FRAME1 DETECTOR_X 0.0 -0.5 
      FRAME1 DETECTOR_PITCH 0.0 0.0 
 

     # category AXIS 

     loop_ 
     _axis.id 
     _axis.type 
     _axis.equipment 
     _axis.depends_on 
     _axis.vector[1] _axis.vector[2] _axis.vector[3] 
     _axis.offset[1] _axis.offset[2] _axis.offset[3] 
      GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . 
      GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279
      0 0.76604 . . . 
      GONIOMETER_PHI   rotation goniometer GONIOMETER_KAPPA 1 0 0
     . . . 
      SOURCE           general source . 0 0 1 . . . 
      GRAVITY          general gravity . 0 -1 0 . . . 
      DETECTOR_Z       translation detector . 0 0 1 0 0 0
      DETECTOR_Y       translation detector DETECTOR_Z 0 1 0 0 0 0 
      DETECTOR_X       translation detector DETECTOR_Y 1 0 0 0 0 0 
      DETECTOR_PITCH   rotation    detector DETECTOR_X 0 1 0 0 0 0 
      ELEMENT_X        translation detector DETECTOR_PITCH
     1 0 0 172.43 -172.43 0
      ELEMENT_Y        translation detector ELEMENT_X
     0 1 0 0 0 0 
 
     # category ARRAY_STRUCTURE_LIST 

     loop_ 
     _array_structure_list.array_id 
     _array_structure_list.index 
     _array_structure_list.dimension 
     _array_structure_list.precedence 
     _array_structure_list.direction 
     _array_structure_list.axis_set_id 
      ARRAY1 1 2300 1 increasing ELEMENT_X 
      ARRAY1 2 2300 2 increasing ELEMENT_Y 
 
 
     # category ARRAY_STRUCTURE_LIST_AXIS 

     loop_
     _array_structure_list_axis.axis_set_id
     _array_structure_list_axis.axis_id
     _array_structure_list_axis.displacement
     _array_structure_list_axis.displacement_increment
      ELEMENT_X ELEMENT_X 0.075 0.150
      ELEMENT_Y ELEMENT_Y 0.075 0.150

     # category ARRAY_ELEMENT_SIZE 

     loop_ 
     _array_element_size.array_id 
     _array_element_size.index 
     _array_element_size.size 
      ARRAY1 1 150e-6 
      ARRAY1 2 150e-6 
 

     # category ARRAY_INTENSITIES 

     loop_ 
     _array_intensities.array_id 
     _array_intensities.binary_id 
     _array_intensities.linearity 
     _array_intensities.gain 
     _array_intensities.gain_esd 
     _array_intensities.overload
     _array_intensities.undefined_value 
      ARRAY1 1 linear 1.15 0.2 240000 0 
 

      # category ARRAY_STRUCTURE 

      loop_ 
      _array_structure.id 
      _array_structure.encoding_type 
      _array_structure.compression_type 
      _array_structure.byte_order 
      ARRAY1 "signed 32-bit integer" packed little_endian 
 

     # category ARRAY_DATA         

     loop_ 
     _array_data.array_id 
     _array_data.binary_id 
     _array_data.data 
      ARRAY1 1 
     ; 
     --CIF-BINARY-FORMAT-SECTION-- 
     Content-Type: application/octet-stream; 
         conversions="x-CBF_PACKED" 
     Content-Transfer-Encoding: BASE64 
     X-Binary-Size: 3801324 
     X-Binary-ID: 1 
     X-Binary-Element-Type: "signed 32-bit integer" 
     Content-MD5: 07lZFvF+aOcW85IN7usl8A== 

     AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg 
     ... 
     8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE 

     --CIF-BINARY-FORMAT-SECTION---- 
     ; 
;

;
    Example 3 - Example 2 revised for a spiral scan, R. M. Sweet, 
    P. Ellis, H. Bernstein.
    
   We place a detector 240 mm along the Z axis from the goniometer,
   as in Example 2, above, but in this example, the image plate is
   scanned in a spiral pattern outside edge in.
   
   The axis for positioning the detector in the Y-direction depends
   on the detector Z-axis.  We call this axis, DETECTOR_Y.
   
   The axis for positioning the dector in the X-direction depends
   on the detector Y-axis (and therefore on the detector Z-axis).
   We call this axis DETECTOR_X.
   
   This detector may be rotated around the Y-axis.  This rotation axis
   depends on the three translation axies.  We call it DETECTOR_PITCH.
 
   We define a coordinate system on the face of the detector in
   terms of a coupled rotation axis and radial scan axis to form 
   a spiral scan.  Let us call rotation axis ELEMENT_ROT, and the
   radial axis ELEMENT_RAD.   We assume 150 um radial pitch and 75 um 
   'constant velocity' angular pitch. 

   We index first on the rotation axis and make the radial axis
   dependent on 
   it. 

   The two axes are coupled to form an axis set ELEMENT_SPIRAL. 
 
;
;
     ###CBF: VERSION 1.1 

     data_image_1 
 

     # category DIFFRN 

     _diffrn.id P6MB 
     _diffrn.crystal_id P6MB_CRYSTAL7 
 

     # category DIFFRN_SOURCE 

     loop_ 
     _diffrn_source.diffrn_id 
     _diffrn_source.source 
     _diffrn_source.type 
      P6MB synchrotron 'SSRL beamline 9-1' 
 

     # category DIFFRN_RADIATION 

          loop_ 
     _diffrn_radiation.diffrn_id 
     _diffrn_radiation.wavelength_id 
     _diffrn_radiation.monochromator 
     _diffrn_radiation.polarizn_source_ratio 
     _diffrn_radiation.polarizn_source_norm 
     _diffrn_radiation.div_x_source 
     _diffrn_radiation.div_y_source 
     _diffrn_radiation.div_x_y_source 
      P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08
     0.01 0.00 
 

     # category DIFFRN_RADIATION_WAVELENGTH 

     loop_ 
     _diffrn_radiation_wavelength.id 
     _diffrn_radiation_wavelength.wavelength 
     _diffrn_radiation_wavelength.wt 
      WAVELENGTH1 0.98 1.0 
 

     # category DIFFRN_DETECTOR 

     loop_ 
     _diffrn_detector.diffrn_id 
     _diffrn_detector.id 
     _diffrn_detector.type 
     _diffrn_detector.number_of_axes 
      P6MB MAR345-SN26 'MAR 345' 4 
 

     # category DIFFRN_DETECTOR_AXIS 

     loop_ 
     _diffrn_detector_axis.id 
     _diffrn_detector_axis.axis_id 
      MAR345-SN26 DETECTOR_X 
      MAR345-SN26 DETECTOR_Y 
      MAR345-SN26 DETECTOR_Z 
      MAR345-SN26 DETECTOR_PITCH 
 

     # category DIFFRN_DETECTOR_ELEMENT 

     loop_ 
     _diffrn_detector_element.id 
     _diffrn_detector_element.detector_id 
      ELEMENT1 MAR345-SN26 
 

     # category DIFFRN_DATA_FRAME 

     loop_ 
     _diffrn_data_frame.id 
     _diffrn_data_frame.detector_element_id 
     _diffrn_data_frame.array_id 
     _diffrn_data_frame.binary_id 
      FRAME1 ELEMENT1 ARRAY1 1 
 

     # category DIFFRN_MEASUREMENT 

     loop_ 
     _diffrn_measurement.diffrn_id 
     _diffrn_measurement.id 
     _diffrn_measurement.number_of_axes 
     _diffrn_measurement.method 
      P6MB GONIOMETER 3 rotation 
 

     # category DIFFRN_MEASUREMENT_AXIS 

     loop_ 
     _diffrn_measurement_axis.measurement_id 
     _diffrn_measurement_axis.axis_id 
      GONIOMETER GONIOMETER_PHI 
      GONIOMETER GONIOMETER_KAPPA 
      GONIOMETER GONIOMETER_OMEGA 
 

     # category DIFFRN_SCAN 

     loop_ 
     _diffrn_scan.id 
     _diffrn_scan.frame_id_start 
     _diffrn_scan.frame_id_end 
     _diffrn_scan.frames 
      SCAN1 FRAME1 FRAME1 1 
 

     # category DIFFRN_SCAN_AXIS 

     loop_ 
     _diffrn_scan_axis.scan_id 
     _diffrn_scan_axis.axis_id 
     _diffrn_scan_axis.angle_start 
     _diffrn_scan_axis.angle_range 
     _diffrn_scan_axis.angle_increment 
     _diffrn_scan_axis.displacement_start 
     _diffrn_scan_axis.displacement_range 
     _diffrn_scan_axis.displacement_increment 
      SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 
      SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 
      SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 
      SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 
      SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 
      SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 
      SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 
 

     # category DIFFRN_SCAN_FRAME 

     loop_ 
     _diffrn_scan_frame.frame_id 
     _diffrn_scan_frame.frame_number 
     _diffrn_scan_frame.integration_time 
     _diffrn_scan_frame.scan_id 
     _diffrn_scan_frame.date 
      FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 
 

     # category DIFFRN_SCAN_FRAME_AXIS 

     loop_ 
     _diffrn_scan_frame_axis.frame_id 
     _diffrn_scan_frame_axis.axis_id 
     _diffrn_scan_frame_axis.angle 
     _diffrn_scan_frame_axis.displacement 
      FRAME1 GONIOMETER_OMEGA 12.0 0.0 
      FRAME1 GONIOMETER_KAPPA 23.3 0.0 
      FRAME1 GONIOMETER_PHI -165.8 0.0 
      FRAME1 DETECTOR_Z 0.0 -240.0 
      FRAME1 DETECTOR_Y 0.0 0.6 
      FRAME1 DETECTOR_X 0.0 -0.5 
      FRAME1 DETECTOR_PITCH 0.0 0.0 
 

     # category AXIS 

     loop_ 
     _axis.id 
     _axis.type 
     _axis.equipment 
     _axis.depends_on 
     _axis.vector[1] _axis.vector[2] _axis.vector[3] 
     _axis.offset[1] _axis.offset[2] _axis.offset[3] 
      GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . 
      GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279
      0 0.76604 . . . 
      GONIOMETER_PHI   rotation goniometer GONIOMETER_KAPPA 1 0 0
     . . . 
      SOURCE           general source . 0 0 1 . . . 
      GRAVITY          general gravity . 0 -1 0 . . . 
      DETECTOR_Z       translation detector . 0 0 1 0 0 0
      DETECTOR_Y       translation detector DETECTOR_Z 0 1 0 0 0 0 
      DETECTOR_X       translation detector DETECTOR_Y 1 0 0 0 0 0 
      DETECTOR_PITCH   rotation    detector DETECTOR_X 0 1 0 0 0 0 
      ELEMENT_ROT      translation detector DETECTOR_PITCH 0 0 1 0 0 0
      ELEMENT_RAD      translation detector ELEMENT_ROT 0 1 0 0 0 0 
 
     # category ARRAY_STRUCTURE_LIST 

     loop_ 
     _array_structure_list.array_id 
     _array_structure_list.index 
     _array_structure_list.dimension 
     _array_structure_list.precedence 
     _array_structure_list.direction 
     _array_structure_list.axis_set_id 
      ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL
 
 
     # category ARRAY_STRUCTURE_LIST_AXIS 

     loop_
     _array_structure_list_axis.axis_set_id
     _array_structure_list_axis.axis_id
     _array_structure_list_axis.angle
     _array_structure_list_axis.displacement
     _array_structure_list_axis.angular_pitch
     _array_structure_list_axis.radial_pitch
      ELEMENT_SPIRAL ELEMENT_ROT 0    .  0.075   .
      ELEMENT_SPIRAL ELEMENT_RAD . 172.5  .    -0.150

     # category ARRAY_ELEMENT_SIZE 
     # the actual pixels are 0.075 by 0.150 mm
     # We give the coarser dimension here.

     loop_ 
     _array_element_size.array_id 
     _array_element_size.index 
     _array_element_size.size 
      ARRAY1 1 150e-6 
 

     # category ARRAY_INTENSITIES 

     loop_ 
     _array_intensities.array_id 
     _array_intensities.binary_id 
     _array_intensities.linearity 
     _array_intensities.gain 
     _array_intensities.gain_esd 
     _array_intensities.overload
     _array_intensities.undefined_value 
      ARRAY1 1 linear 1.15 0.2 240000 0 
 

      # category ARRAY_STRUCTURE 

      loop_ 
      _array_structure.id 
      _array_structure.encoding_type 
      _array_structure.compression_type 
      _array_structure.byte_order 
      ARRAY1 "signed 32-bit integer" packed little_endian 
 

     # category ARRAY_DATA         

     loop_ 
     _array_data.array_id 
     _array_data.binary_id 
     _array_data.data 
      ARRAY1 1 
     ; 
     --CIF-BINARY-FORMAT-SECTION-- 
     Content-Type: application/octet-stream; 
         conversions="x-CBF_PACKED" 
     Content-Transfer-Encoding: BASE64 
     X-Binary-Size: 3801324 
     X-Binary-ID: 1 
     X-Binary-Element-Type: "signed 32-bit integer" 
     Content-MD5: 07lZFvF+aOcW85IN7usl8A== 

     AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg 
     ... 
     8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE 

     --CIF-BINARY-FORMAT-SECTION---- 
     ; 
;


# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
       save_
 
 
save__diffrn_scan.id
    _item_description.description
;             The value of _diffrn_scan.id uniquely identifies each
              scan.  The identifier is used to tie together all the 
              information about the scan.
;
     loop_
    _item.name                
    _item.category_id          
    _item.mandatory_code       
       '_diffrn_scan.id'                 diffrn_scan             yes
       '_diffrn_scan_axis.scan_id'       diffrn_scan_axis        yes
       '_diffrn_scan_frame.scan_id'      diffrn_scan_frame       yes
    _item_type.code               code
     loop_
    _item_linked.child_name
    _item_linked.parent_name
       '_diffrn_scan_axis.scan_id'          '_diffrn_scan.id'
       '_diffrn_scan_frame.scan_id'         '_diffrn_scan.id'
     save_
 
 
save__diffrn_scan.date_end
    _item_description.description
;
               The date and time of the end of the scan.  Note that this
               may be an estimate generated during the scan, before the
               precise time of the end of the scan is known.
;
    _item.name                 '_diffrn_scan.date_end'
    _item.category_id          diffrn_scan
    _item.mandatory_code       no
    _item_type.code            yyyy-mm-dd
     save_
 
 
save__diffrn_scan.date_start
    _item_description.description
;
               The date and time of the start of the scan.
;
    _item.name                 '_diffrn_scan.date_start'
    _item.category_id          diffrn_scan
    _item.mandatory_code       no
    _item_type.code            yyyy-mm-dd
     save_
 
 
save__diffrn_scan.integration_time
    _item_description.description
;
               Approximate average time in seconds to integrate each 
               step of the scan.  The precise time for integration
               of each particular step must be provided in
               '_diffrn_scan_frame.integration_time', even
               if all steps have the same integration time.
;
    _item.name                 '_diffrn_scan.integration_time'
    _item.category_id          diffrn_scan
    _item.mandatory_code       no
    _item_type.code            float
    _item_units.code           'seconds'
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            .   0.0
     save_
 
 
save__diffrn_scan.frame_id_start
    _item_description.description
;
               The value of this data item is the identifier of the
               first frame in the scan.

               This item is a pointer to _diffrn_data_frame.id in the
               DIFFRN_DATA_FRAME category.
;
    _item.name                 '_diffrn_scan.frame_id_start'
    _item.category_id          diffrn_scan
    _item.mandatory_code       yes
     save_
 
 
save__diffrn_scan.frame_id_end
    _item_description.description
;
               The value of this data item is the identifier of the
               last frame in the scan.

               This item is a pointer to _diffrn_data_frame.id in the
               DIFFRN_DATA_FRAME category.
;
    _item.name                 '_diffrn_scan.frame_id_end'
    _item.category_id          diffrn_scan
    _item.mandatory_code       yes 
     save_
 
 
save__diffrn_scan.frames
    _item_description.description
;
               The value of this data item is the number of frames in
               the scan.

;
    _item.name                 '_diffrn_scan.frames'
    _item.category_id          diffrn_scan
    _item.mandatory_code       no 
    _item_type.code            int
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            .   1
                            1   1
     save_
 
 
####################
# DIFFRN_SCAN_AXIS #
####################

save_DIFFRN_SCAN_AXIS
    _category.description 
;
     Data items in the DIFFRN_SCAN_AXIS category describe the settings of
     axes for particular scans.  Unspecified axes are assumed to be at
     their zero points.

;
    _category.id                   diffrn_scan_axis
    _category.mandatory_code       no
     loop_
    _category_key.name            
                                  '_diffrn_scan_axis.scan_id'
                                  '_diffrn_scan_axis.axis_id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     save_
 
 
save__diffrn_scan_axis.scan_id
    _item_description.description
;
               The value of this data item is the identifier of the
               scan for which axis settings are being specified.

               Multiple axes may be specified for the same value of
               '_diffrn_scan.id'.

               This item is a pointer to _diffrn_scan.id in the
               DIFFRN_SCAN category.
;
    _item.name                 '_diffrn_scan_axis.scan_id'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       yes
     save_
 
 
save__diffrn_scan_axis.axis_id
    _item_description.description
;
               The value of this data item is the identifier of one of
               the axes for the scan for which settings are being specified.

               Multiple axes may be specified for the same value of
               '_diffrn_scan.id'.

               This item is a pointer to _axis.id in the
               AXIS category.
;
    _item.name                 '_diffrn_scan_axis.axis_id'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       yes
     save_
 
 
save__diffrn_scan_axis.angle_start
    _item_description.description
;
               The starting position for the specified axis in degrees.
;
    _item.name                 '_diffrn_scan_axis.angle_start'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no 
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_
 
 
save__diffrn_scan_axis.angle_range
    _item_description.description
;
               The range from the starting position for the specified axis 
               in degrees.
;
    _item.name                 '_diffrn_scan_axis.angle_range'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no 
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_
 
 
save__diffrn_scan_axis.angle_increment
    _item_description.description
;
               The increment for each step for the specified axis
               in degrees.  In general, this will agree with
               '_diffrn_scan_frame_axis.angle_increment', which
               see for a precise description.
;
    _item.name                 '_diffrn_scan_axis.angle_increment'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no 
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_
 
 
save__diffrn_scan_axis.angle_rstrt_incr
    _item_description.description
;
               The increment after each step for the specified axis
               in degrees.  In general, this will agree with
               '_diffrn_scan_frame_axis.angle_increment', which
               see for a precise description.
;
    _item.name                 '_diffrn_scan_axis.angle_rstrt_incr'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_
 
 
save__diffrn_scan_axis.displacement_start
    _item_description.description
;
               The starting position for the specified axis in millimetres.
;
    _item.name                 '_diffrn_scan_axis.displacement_start'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no 
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
 
 
save__diffrn_scan_axis.displacement_range
    _item_description.description
;
               The range from the starting position for the specified axis 
               in millimetres.
;
    _item.name                 '_diffrn_scan_axis.displacement_range'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no 
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
 
 
save__diffrn_scan_axis.displacement_increment
    _item_description.description
;
               The increment for each step for the specified axis
               in millimetres.  In general, this will agree with
               '_diffrn_scan_frame_axis.displacement_increment', which
               see for a precise description.
;
    _item.name                 '_diffrn_scan_axis.displacement_increment'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no 
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
 
 
save__diffrn_scan_axis.displacement_rstrt_incr
    _item_description.description
;
               The increment for each step for the specified axis
               in millimetres.  In general, this will agree with
               '_diffrn_scan_frame_axis.displacement_rstrt_incr', which
               see for a precise description.
;
    _item.name                 '_diffrn_scan_axis.displacement_rstrt_incr'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
 
 
#####################
# DIFFRN_SCAN_FRAME #
#####################

save_DIFFRN_SCAN_FRAME
    _category.description 
;
            Data items in the DIFFRN_SCAN_FRAME category describe
            the relationship of particular frames to scans.

;
    _category.id                   diffrn_scan_frame
    _category.mandatory_code       no
     loop_
    _category_key.name     
                                  '_diffrn_scan_frame.scan_id'
                                  '_diffrn_scan_frame.frame_id'
     loop_
    _category_group.id            'inclusive_group'
                                  'diffrn_group'
     save_
 
 
save__diffrn_scan_frame.date
    _item_description.description
;
               The date and time of the start of the frame being scanned.
;
    _item.name                 '_diffrn_scan_frame.date'
    _item.category_id          diffrn_scan_frame
    _item.mandatory_code       no
    _item_type.code            yyyy-mm-dd
     save_
 
 
save__diffrn_scan_frame.frame_id
    _item_description.description
;
               The value of this data item is the identifier of the
               frame being examined.

               This item is a pointer to _diffrn_data_frame.id in the
               DIFFRN_DATA_FRAME category.
;
    _item.name                 '_diffrn_scan_frame.frame_id'
    _item.category_id          diffrn_scan_frame
    _item.mandatory_code       yes
     save_
 
 
save__diffrn_scan_frame.frame_number
    _item_description.description
;
               The value of this data item is the number of the frame within
               the scan, starting with 1.  It is not necessarily the same as
               the value of _diffrn_scan_frame.frame_id, but may
               be.

;
    _item.name                 '_diffrn_scan_frame.frame_number'
    _item.category_id          diffrn_scan_frame
    _item.mandatory_code       no 
    _item_type.code            int
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            .   0
                            0   0
     save_
 
 
save__diffrn_scan_frame.integration_time
    _item_description.description
;
               The time in seconds to integrate this step of the scan.
               This should be the precise time of integration of each
               particular frame.  The value of this data item should
               be given explicitly for each frame and not inferred
               from the value of '_diffrn_scan.integration_time'.
;
    _item.name                 '_diffrn_scan_frame.integration_time'
    _item.category_id          diffrn_scan_frame
    _item.mandatory_code       yes 
    _item_type.code            float
    _item_units.code           'seconds'
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            .   0.0
     save_
 
 
save__diffrn_scan_frame.scan_id
    _item_description.description
;             The value of _diffrn_scan_frame.scan_id identifies the scan
              containing this frame.

              This item is a pointer to _diffrn_scan.id in the
              DIFFRN_SCAN category.
;
    _item.name             '_diffrn_scan_frame.scan_id'    
    _item.category_id        diffrn_scan_frame        
    _item.mandatory_code     yes     
     save_
 
 
##########################
# DIFFRN_SCAN_FRAME_AXIS #
##########################

save_DIFFRN_SCAN_FRAME_AXIS
    _category.description
;
     Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the settings
     of axes for particular frames.  Unspecified axes are assumed to be at
     their zero points.  If, for any given frame, non-zero values apply
     for any of the data items in this category, those values should be
     given explicitly in this category and not simply inferred from values
     in DIFFRN_SCAN_AXIS.

;
    _category.id                   diffrn_scan_frame_axis
    _category.mandatory_code       no
     loop_
    _category_key.name
                                  '_diffrn_scan_frame_axis.frame_id'
                                  '_diffrn_scan_frame_axis.axis_id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     save_
 
 
save__diffrn_scan_frame_axis.axis_id
    _item_description.description
;
               The value of this data item is the identifier of one of
               the axes for the frame for which settings are being specified.

               Multiple axes may be specified for the same value of
               _diffrn_scan_frame.frame_id

               This item is a pointer to _axis.id in the
               AXIS category.
;
    _item.name                 '_diffrn_scan_frame_axis.axis_id'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       yes
     save_
 
 
save__diffrn_scan_frame_axis.angle
    _item_description.description
;
               The setting of the specified axis in degrees for this frame.
               This is the setting at the start of the integration time.
;
    _item.name                 '_diffrn_scan_frame_axis.angle'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       no 
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_
 
 
save__diffrn_scan_frame_axis.angle_increment
    _item_description.description
;
               The increment for this frame for angular setting of
               the specified axis in degrees.  The sum of the values
               of '_diffrn_scan_frame_axis.angle' and
               '_diffrn_scan_frame_axis.angle_increment' is the
               angular setting of the axis at the end of the integration
               time for this frame.
;
    _item.name                 '_diffrn_scan_frame_axis.angle_increment'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_
 
 
save__diffrn_scan_frame_axis.angle_rstrt_incr
    _item_description.description
;
               The increment after this frame for angular setting of
               the specified axis in degrees.  The sum of the values
               of '_diffrn_scan_frame_axis.angle' and
               '_diffrn_scan_frame_axis.angle_increment' and
               '_diffrn_scan_frame_axis.angle_rstrt_incr' is the
               angular setting of the axis at the start of the integration
               time for the next frame, and should equal
               '_diffrn_scan_frame_axis.angle' for that next frame.
;
    _item.name               '_diffrn_scan_frame_axis.angle_rstrt_incr'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_
 
 
save__diffrn_scan_frame_axis.displacement
    _item_description.description
;
               The setting of the specified axis in millimetres for this
               frame.  This is the setting at the start of the integration
               time.

;
    _item.name               '_diffrn_scan_frame_axis.displacement'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
 
 
save__diffrn_scan_frame_axis.displacement_increment
    _item_description.description
;
               The increment for this frame for displacement setting of
               the specified axis in millimetres.  The sum of the values
               of '_diffrn_scan_frame_axis.displacement' and
               '_diffrn_scan_frame_axis.displacement_increment' is the
               angular setting of the axis at the end of the integration
               time for this frame.
;
    _item.name               '_diffrn_scan_frame_axis.displacement_increment'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
 
 
save__diffrn_scan_frame_axis.displacement_rstrt_incr
    _item_description.description
;
               The increment for this frame for displacement setting of
               the specified axis in millimetres.  The sum of the values
               of '_diffrn_scan_frame_axis.displacement' and
               '_diffrn_scan_frame_axis.displacement_increment' and
               '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the
               angular setting of the axis at the start of the integration
               time for the next frame, and should equal
               '_diffrn_scan_frame_axis.displacement' for that next frame.
;
    _item.name               '_diffrn_scan_frame_axis.displacement_rstrt_incr'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_

save__diffrn_scan_frame_axis.frame_id
    _item_description.description
;
               The value of this data item is the identifier of the
               frame for which axis settings are being specified.

               Multiple axes may be specified for the same value of
               _diffrn_scan_frame.frame_id .

               This item is a pointer to _diffrn_data_frame.id in the
               DIFFRN_DATA_FRAME category.
;
    _item.name               '_diffrn_scan_frame_axis.frame_id'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       yes
     save_
 
 
####################
## ITEM_TYPE_LIST ##
####################
#
#
#  The regular expressions defined here are not compliant
#  with the POSIX 1003.2 standard as they include the
#  '\n' and '\t' special characters.  These regular expressions
#  have been tested using version 0.12 of Richard Stallman's
#  GNU regular expression library in POSIX mode.
#  In order to allow presentation of a regular expression
#  in a text field concatenate any line ending in a backslash
#  with the following line, after discarding the backslash.
#
#  A formal definition of the '\n' and '\t' special characters
#  is most properly done in the DDL, but for completeness, please
#  note that '\n' is the line termination character ('newline')
#  and '\t' is the horizontal tab character.  There is a formal
#  ambiguity in the use of '\n' for line termination, in that
#  the intention is that the equivalent machine/OS-dependent line
#  termination character sequence should be accepted as a match, e.g.
#
#      '\r' (control-M) under MacOS
#      '\n' (control-J) under Unix
#      '\r\n' (control-M control-J) under DOS and MS Windows
#
     loop_
    _item_type_list.code
    _item_type_list.primitive_code
    _item_type_list.construct
    _item_type_list.detail
               code      char
'[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
;              code item types/single words ...
;
               ucode      uchar
'[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
;              code item types/single words (case insensitive)
;
               line      char
'[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
;              code item types / multi-word items  ...
;
               uline     uchar
'[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
;              code item types / multi-word items (case insensitive)
;
               text      char
'[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*'
;              text item types / multi-line text ...
;
               binary    char
;\n--CIF-BINARY-FORMAT-SECTION--\n\
[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\
\n--CIF-BINARY-FORMAT-SECTION----
;
;              binary items are presented as MIME-like ascii-encoded
               sections in an imgCIF.  In a CBF, raw octet streams
               are used to convey the same information.
;
               int       numb
'-?[0-9]+'
;              int item types are the subset of numbers that are the negative
               or positive integers.
;
               float     numb
'-?(([0-9]+)|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?'
;              float item types are the subset of numbers that are the floating
               numbers.
;
               any       char
'.*'
;              A catch all for items that may take any form...
;
               yyyy-mm-dd  char
;\
[0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9][0-9]\
(T[0-2][0-9]:[0-5][0-9]:[0-5][0-9](.[0-9]+)([+-][0-5][0-9]:[0-5][0-9]))
;
;
               Standard format for CIF date and time strings (see
               http://www.iucr.orgiucr-top/cif/spec/datetime.html),
               consisting of a yyyy-mm-dd date optionally followed by
               the character "T" followed by a 24-hour clock time,
               optionally followed by a signed time-zone offset.
               
               The IUCr standard has been extended to allow for an optional
               decimal fraction on the seconds of time.
               
               Time is local time if no time-zone offset is given.
;
 
 
#####################
## ITEM_UNITS_LIST ##
#####################

     loop_
    _item_units_list.code
    _item_units_list.detail
#
     'metres'                 'metres'
     'centimetres'            'centimetres (metres * 10^( -2))'
     'millimetres'            'millimetres (metres * 10^( -3))'
     'nanometres'             'nanometres  (metres * 10^( -9))'
     'angstroms'              'angstroms   (metres * 10^(-10))'
     'picometres'             'picometres  (metres * 10^(-12))'
     'femtometres'            'femtometres (metres * 10^(-15))'
#
     'reciprocal_metres'      'reciprocal metres (metres^(-1))'
     'reciprocal_centimetres' 'reciprocal centimetres ((metres * 10^( -2))^(-1))'
     'reciprocal_millimetres' 'reciprocal millimetres ((metres * 10^( -3))^(-1))'
     'reciprocal_nanometres'  'reciprocal nanometres  ((metres * 10^( -9))^(-1))'
     'reciprocal_angstroms'   'reciprocal angstroms   ((metres * 10^(-10))^(-1))'
     'reciprocal_picometres'  'reciprocal picometres  ((metres * 10^(-12))^(-1))'

     'reciprocal_metres'      'reciprocal metres (metres * 10^-1)'
     'reciprocal_centimetres' 'reciprocal centimetres (metres * 10^( -2)^-1)'
     'reciprocal_millimetres' 'reciprocal millimetres (metres * 10^( -3)^-1)'
     'reciprocal_nanometres'  'reciprocal nanometres  (metres * 10^( -9)^-1)'
     'reciprocal_angstroms'   'reciprocal angstroms   (metres * 10^(-10)^-1)'
     'reciprocal_picometres'  'reciprocal picometres  (metres * 10^(-12)^-1)'
#
     'nanometres_squared'     'nanometres squared (metres * 10^( -9))^2'
     'angstroms_squared'      'angstroms squared  (metres * 10^(-10))^2'
     '8pi2_angstroms_squared' '8pi^2 * angstroms squared (metres * 10^(-10))^2'
     'picometres_squared'     'picometres squared (metres * 10^(-12))^2'
#
     'nanometres_cubed'       'nanometres cubed (metres * 10^( -9))^3'
     'angstroms_cubed'        'angstroms cubed  (metres * 10^(-10))^3'
     'picometres_cubed'       'picometres cubed (metres * 10^(-12))^3'
#
     'kilopascals'            'kilopascals'
     'gigapascals'            'gigapascals'
#
     'hours'                  'hours'
     'minutes'                'minutes'
     'seconds'                'seconds'
     'microseconds'           'microseconds'
#
     'degrees'                'degrees (of arc)'
     'degrees_squared'        'degrees (of arc) squared'
#
     'degrees_per_minute'     'degrees (of arc) per minute'
#
     'celsius'                'degrees (of temperature) Celsius'
     'kelvins'                'degrees (of temperature) Kelvin'
#
     'counts'                 'counts'
     'counts_per_photon'      'counts per photon'
#
     'electrons'              'electrons'
#
     'electrons_squared'      'electrons squared'
#
     'electrons_per_nanometres_cubed'
; electrons per nanometres cubed (electrons/(metres * 10^( -9))^(-3))
;
     'electrons_per_angstroms_cubed'
; electrons per nanometres cubed (electrons/(metres * 10^(-10))^(-3)); 
;
     'electrons_per_picometres_cubed'
; electrons per nanometres cubed (electrons/(metres * 10^(-12))^(-3)); 
;
     'kilowatts'              'kilowatts'
     'milliamperes'           'milliamperes'
     'kilovolts'              'kilovolts'
#
     'arbitrary'
; arbitrary system of units.
;
#

     loop_
    _item_units_conversion.from_code
    _item_units_conversion.to_code
    _item_units_conversion.operator
    _item_units_conversion.factor
###
     'metres'                   'centimetres'              '*'   1.0E+02
     'metres'                   'millimetres'              '*'   1.0E+03
     'metres'                   'nanometres'               '*'   1.0E+09
     'metres'                   'angstroms'                '*'   1.0E+10
     'metres'                   'picometres'               '*'   1.0E+12
     'metres'                   'femtometres'              '*'   1.0E+15
#
     'centimetres'              'metres'                   '*'   1.0E-02
     'centimetres'              'millimetres'              '*'   1.0E+01
     'centimetres'              'nanometres'               '*'   1.0E+07
     'centimetres'              'angstroms'                '*'   1.0E+08
     'centimetres'              'picometres'               '*'   1.0E+10
     'centimetres'              'femtometres'              '*'   1.0E+13
#
     'millimetres'              'metres'                   '*'   1.0E-03
     'millimetres'              'centimetres'              '*'   1.0E-01
     'millimetres'              'nanometres'               '*'   1.0E+06
     'millimetres'              'angstroms'                '*'   1.0E+07
     'millimetres'              'picometres'               '*'   1.0E+09
     'millimetres'              'femtometres'              '*'   1.0E+12
#
     'nanometres'               'metres'                   '*'   1.0E-09
     'nanometres'               'centimetres'              '*'   1.0E-07
     'nanometres'               'millimetres'              '*'   1.0E-06
     'nanometres'               'angstroms'                '*'   1.0E+01
     'nanometres'               'picometres'               '*'   1.0E+03
     'nanometres'               'femtometres'              '*'   1.0E+06
#
     'angstroms'                'metres'                   '*'   1.0E-10
     'angstroms'                'centimetres'              '*'   1.0E-08
     'angstroms'                'millimetres'              '*'   1.0E-07
     'angstroms'                'nanometres'               '*'   1.0E-01
     'angstroms'                'picometres'               '*'   1.0E+02
     'angstroms'                'femtometres'              '*'   1.0E+05
#
     'picometres'               'metres'                   '*'   1.0E-12
     'picometres'               'centimetres'              '*'   1.0E-10
     'picometres'               'millimetres'              '*'   1.0E-09
     'picometres'               'nanometres'               '*'   1.0E-03
     'picometres'               'angstroms'                '*'   1.0E-02
     'picometres'               'femtometres'              '*'   1.0E+03
#
     'femtometres'              'metres'                   '*'   1.0E-15
     'femtometres'              'centimetres'              '*'   1.0E-13
     'femtometres'              'millimetres'              '*'   1.0E-12
     'femtometres'              'nanometres'               '*'   1.0E-06
     'femtometres'              'angstroms'                '*'   1.0E-05
     'femtometres'              'picometres'               '*'   1.0E-03
###
     'reciprocal_centimetres'   'reciprocal_metres'        '*'   1.0E+02
     'reciprocal_centimetres'   'reciprocal_millimetres'   '*'   1.0E-01
     'reciprocal_centimetres'   'reciprocal_nanometres'    '*'   1.0E-07
     'reciprocal_centimetres'   'reciprocal_angstroms'     '*'   1.0E-08
     'reciprocal_centimetres'   'reciprocal_picometres'    '*'   1.0E-10
#
     'reciprocal_millimetres'   'reciprocal_metres'        '*'   1.0E+03
     'reciprocal_millimetres'   'reciprocal_centimetres'   '*'   1.0E+01
     'reciprocal_millimetres'   'reciprocal_nanometres'    '*'   1.0E-06
     'reciprocal_millimetres'   'reciprocal_angstroms'     '*'   1.0E-07
     'reciprocal_millimetres'   'reciprocal_picometres'    '*'   1.0E-09
#
     'reciprocal_nanometres'    'reciprocal_metres'        '*'   1.0E+09
     'reciprocal_nanometres'    'reciprocal_centimetres'   '*'   1.0E+07
     'reciprocal_nanometres'    'reciprocal_millimetres'   '*'   1.0E+06
     'reciprocal_nanometres'    'reciprocal_angstroms'     '*'   1.0E-01
     'reciprocal_nanometres'    'reciprocal_picometres'    '*'   1.0E-03
#
     'reciprocal_angstroms'     'reciprocal_metres'        '*'   1.0E+10
     'reciprocal_angstroms'     'reciprocal_centimetres'   '*'   1.0E+08
     'reciprocal_angstroms'     'reciprocal_millimetres'   '*'   1.0E+07
     'reciprocal_angstroms'     'reciprocal_nanometres'    '*'   1.0E+01
     'reciprocal_angstroms'     'reciprocal_picometres'    '*'   1.0E-02
#
     'reciprocal_picometres'    'reciprocal_metres'        '*'   1.0E+12
     'reciprocal_picometres'    'reciprocal_centimetres'   '*'   1.0E+10
     'reciprocal_picometres'    'reciprocal_millimetres'   '*'   1.0E+09
     'reciprocal_picometres'    'reciprocal_nanometres'    '*'   1.0E+03
     'reciprocal_picometres'    'reciprocal_angstroms'     '*'   1.0E+01
###
     'nanometres_squared'       'angstroms_squared'        '*'   1.0E+02
     'nanometres_squared'       'picometres_squared'       '*'   1.0E+06
#
     'angstroms_squared'        'nanometres_squared'       '*'   1.0E-02
     'angstroms_squared'        'picometres_squared'       '*'   1.0E+04
     'angstroms_squared'        '8pi2_angstroms_squared'   '*'   78.9568

#
     'picometres_squared'       'nanometres_squared'       '*'   1.0E-06
     'picometres_squared'       'angstroms_squared'        '*'   1.0E-04
###
     'nanometres_cubed'         'angstroms_cubed'          '*'   1.0E+03
     'nanometres_cubed'         'picometres_cubed'         '*'   1.0E+09
#
     'angstroms_cubed'          'nanometres_cubed'         '*'   1.0E-03
     'angstroms_cubed'          'picometres_cubed'         '*'   1.0E+06
#
     'picometres_cubed'         'nanometres_cubed'         '*'   1.0E-09
     'picometres_cubed'         'angstroms_cubed'          '*'   1.0E-06
###
     'kilopascals'              'gigapascals'              '*'   1.0E-06
     'gigapascals'              'kilopascals'              '*'   1.0E+06
###
     'hours'                    'minutes'                  '*'   6.0E+01
     'hours'                    'seconds'                  '*'   3.6E+03
     'hours'                    'microseconds'             '*'   3.6E+09
#
     'minutes'                  'hours'                    '/'   6.0E+01
     'minutes'                  'seconds'                  '*'   6.0E+01
     'minutes'                  'microseconds'             '*'   6.0E+07
#
     'seconds'                  'hours'                    '/'   3.6E+03
     'seconds'                  'minutes'                  '/'   6.0E+01
     'seconds'                  'microseconds'             '*'   1.0E+06
#
     'microseconds'             'hours'                    '/'   3.6E+09
     'microseconds'             'minutes'                  '/'   6.0E+07
     'microseconds'             'seconds'                  '/'   1.0E+06
###
     'celsius'                  'kelvins'                  '-'     273.0
     'kelvins'                  'celsius'                  '+'     273.0
###
     'electrons_per_nanometres_cubed'
     'electrons_per_angstroms_cubed'                       '*'   1.0E+03
     'electrons_per_nanometres_cubed'
     'electrons_per_picometres_cubed'                      '*'   1.0E+09
#
     'electrons_per_angstroms_cubed'
     'electrons_per_nanometres_cubed'                      '*'   1.0E-03
     'electrons_per_angstroms_cubed'
     'electrons_per_picometres_cubed'                      '*'   1.0E+06
#
     'electrons_per_picometres_cubed'
     'electrons_per_nanometres_cubed'                      '*'   1.0E-09
     'electrons_per_picometres_cubed'
     'electrons_per_angstroms_cubed'                       '*'   1.0E-06
###
 
 
########################
## DICTIONARY_HISTORY ##
########################

     loop_
    _dictionary_history.version
    _dictionary_history.update
    _dictionary_history.revision

   1.2.3   2003-07-03
;
   Cleanup to conform to ITVG. 
   +  Correct sign error in ..._cubed units.
   +  Correct '_diffrn_radiation.polarisn_norm' range.
   (HJB)
;
   1.2.2   2003-03-10
;
   Correction of  typos in various DIFFRN_SCAN_AXIS descriptions. 
   (HJB)
;

   1.2.1   2003-02-22
;
   Correction of ATOM_ for ARRAY_ typos in various descriptions. 
   (HJB)
;


   1.2     2003-02-07
;
   Corrections to encodings (remove extraneous hyphens) remove
   extraneous underscore in _array_structure.encoding_type
   enumeration.  Correct typos in items units list. 
   (HJB)
;


   1.1.3   2001-04-19
;
   Another typo corrections by Wilfred Li, and cleanup by HJB
;

   1.1.2   2001-03-06
;
   Several typo corrections by Wilfred Li
;


   1.1.1   2001-02-16
;
   Several typo corrections by JW
;


   1.1     2001-02-06
;
   Draft resulting from discussions on header for use at NSLS (HJB)
   
   + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME
   
   + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'.
   
   + Add '_diffrn_measurement_axis.measurement_device' and change
   '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'.
   
   + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source',
   '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm',
   '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end',
   '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr',
   '_diffrn_scan_axis.displacement_rstrt_incr', 
   '_diffrn_scan_frame_axis.angle_increment',
   '_diffrn_scan_frame_axis.angle_rstrt_incr',
   '_diffrn_scan_frame_axis.displacement',
   '_diffrn_scan_frame_axis.displacement_increment',and
   '_diffrn_scan_frame_axis.displacement_rstrt_incr'.
   
   + Add _diffrn_measurement.device to category key
   
   + Update yyyy-mm-dd to allow optional time with fractional seconds
   for time stamps.

   + Fix typos caught by RS.
   
   + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to allow
   for coupled axes, as in spiral scans.

   + Add examples for fairly complete headers thanks to R. Sweet and P. 
   Ellis.
;


   1.0     2000-12-21
;
   Release version - few typos and tidying up (BM & HJB)
   
   + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end
   of dictionary.
   
   + Alphabetize dictionary.
;

   0.7.1   2000-09-29
;
   Cleanup fixes (JW)

   + Correct spelling of diffrn_measurement_axis in _axis.id

   + Correct ordering of uses of _item.mandatory_code and _item_default.value
;

   0.7.0   2000-09-09
;
   Respond to comments by I. David Brown (HJB)

   + Added further comments on '\n' and '\t'

   + Updated ITEM_UNITS_LIST by taking section from mmCIF dictionary
 and adding metres.  Changed all spelling 'meter' to 'metre' throughout.

   + Added missing enumerations to _array_structure.compression_type
 and made 'none' the default.

   + Removed parent-child relationship between _array_structure_list.index
 and _array_structure_list.precedence .

   + Improve alphabetization.

   + Fix _array_intensities_gain.esd related function.

   + Improved comments in AXIS.

   + Fixed DIFFRN_FRAME_DATA example.

   + Removed erroneous DIFFRN_MEASUREMENT example.

   + Added _diffrn_measurement_axis.id to the category key.
;

   0.6.0   1999-01-14
;
   Remove redundant information for ENC_NONE data (HJB)

   + After the D5 remove binary section identifier, size and
 compression type.

   + Add Control-L to header.
;
   0.5.1   1999-01-03
;
   Cleanup of typos and syntax errors (HJB)

   + Cleanup example details for DIFFRN_SCAN category.

   + Add missing quote marks for _diffrn_scan.id definition.
;

   0.5   1999-01-01
;
   Modifications for axis definitions and reduction of binary header (HJB)

   + Restored _diffrn_detector.diffrn_id to DIFFRN_DETECTOR KEY.

   + Added AXIS category.

   + Brought complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories
 in from cif_mm.dic for clarity.

   + changed _array_structure.encoding_type from type code to uline and
 added X-Binary-Element-Type to MIME header.

   + added detector beam center _diffrn_detector_element.center[1] and 
_diffrn_detector_element.center[2]

   + corrected item name of _diffrn_refln.frame_id

   + replace reference to _array_intensities.undefined by
 _array_intensities.undefined_value

   + replace references to _array_intensity.scaling with
 _array_intensities.scaling

   + added DIFFRN_SCAN... categories
;

   0.4   1998-08-11
;
   Modifications to the 0.3 imgCIF draft (HJB)

   +  Reflowed comment lines over 80 characters and corrected typos.

   +  Updated examples and descriptions of MIME encoded data.

   +  Change name to cbfext98.dic.
;

   0.3   1998-07-04
;
   Modifications for imgCIF (HJB)

   +  Added binary type, which is a text field containing a variant on
      MIME encoded data.
      
   +  Changed type of _array_data.data to binary and specified internal
      structure of raw binary data.
      
   +  Added _array_data.binary_id, and made 
      _diffrn_frame_data.binary_id and _array_intensities.binary_id
      into pointers to this item.
;

   0.2   1997-12-02
;
   Modifications to the CBF draft (JW):  

   +  Added category hierarchy for describing frame data developed from
      discussions at the BNL imgCIF Workshop Oct 1997.   The following
      changes were made in implementing the workshop draft.  Category
      DIFFRN_ARRAY_DATA was renamed to DIFFRN_FRAME_DATA.  Category
      DIFFRN_FRAME_TYPE was renamed to DIFFRN_DETECTOR_ELEMENT.   The
      parent item for _diffrn_frame_data.array_id was changed from
      array_structure_list.array_id to array_structure.id. Item 
      _diffrn_detector.array_id was deleted.  
   +  Added data item _diffrn_frame_data.binary_id to identify data groups
      within a binary section.  The formal identification of the binary section
      is still fuzzy.  
;

   0.1   1997-01-24
;
   First draft of this dictionary in DDL 2.1 compliant format by John 
   Westbrook (JW).  This version was adapted from the Crystallographic 
   Binary File (CBF) Format Draft Proposal provided by Andy Hammersley (AH).  
 
   Modifications to the CBF draft (JW):  
 
   + In this version the array description has been cast in the categories 
     ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST.  These categories have been 
     generalized to describe array data  of arbitrary dimension.  

   + Array data in this description are contained in the category ARRAY_DATA        .
     This departs from the CBF notion of data existing in some special comment.
     In this description, data is handled as an ordinary data item encapsulated
     in a character data type.   Although handling binary data this manner
     deviates from CIF conventions, it does not violate any DDL 2.1 rules.
     DDL 2.1 regular expressions can be used to define the binary 
     representation which will permit some level of data validation.  In 
     this version, the placeholder type code "any" has been used.
     This translates to a regular expression which will match any pattern.  

     It should be noted that DDL 2.1 already supports array data objects 
     although these have not been used in the current mmCIF dictionary.  It 
     may be possible to use the DDL 2.1 ITEM_STRUCTURE and ITEM_STRUCTURE_LIST
     categories to provide the information that is carried in by the 
     ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST.  By moving the array 
     structure to the DDL level it would be possible to define an array 
     type as well as a regular expression defining the data format. 

   + Multiple array sections can be properly handled within a single datablock.
;
 
 
#-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof
./CBFlib-0.9.2.2/doc/CBFlib.txt0000644000076500007650000121511111603702115014167 0ustar yayayaya CBFlib An API for CBF/imgCIF Crystallographic Binary Files with ASCII Support Version 0.9.2 12 February 2011 by Paul J. Ellis Stanford Synchrotron Radiation Laboratory and Herbert J. Bernstein Bernstein + Sons yaya at bernstein-plus-sons dot com (c) Copyright 2006, 2007, 2008, 2011 Herbert J. Bernstein ---------------------------------------------------------------------- YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL. ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS OF THE LGPL. ---------------------------------------------------------------------- Before using this software, please read the NOTICE for important disclaimers and the IUCr Policy on the Use of the Crystallographic Information File (CIF) and for other important information. Work on imgCIF and CBFlib supported in part by the U. S. Department of Energy (DOE) under grants ER63601-1021466-0009501 and ER64212-1027708-0011962, by the U. S. National Science Foundation (NSF) under grants DBI-0610407, DBI-0315281 and EF-0312612, the U. S. National Institutes of Health (NIH) under grants 1R15GM078077 from NIGMS and 1R13RR023192 from NCRR and funding from the International Union for Crystallographyn (IUCr). The content is solely the responsibility of the authors and does not necessarily represent the official views of DOE, NSF, NIH, NIGMS, NCRR or IUCr. ---------------------------------------------------------------------- Version History Version Date By Description 0.1 Apr. 1998 PJE This was the first CBFlib release. It supported binary CBF files using binary strings. 0.2 Aug. 1998 HJB This release added ascii imgCIF support using MIME-encoded binary sections, added the option of MIME headers for the binary strings was well. MIME code adapted from mpack 1.5. Added hooks needed for DDL1-style names without categories. 0.3 Sep. 1998 PJE This release cleaned up the changes made for version 0.2, allowing multi-threaded use of the code, and removing dependence on the mpack package. 0.4 Nov. 1998 HJB This release merged much of the message digest code into the general file reading and writing to reduce the number of passes. More consistency checking between the MIME header and the binary header was introduced. The size in the MIME header was adjusted to agree with the version 0.2 documentation. 0.5 Dec. 1998 PJE This release greatly increased the speed of processing by allowing for deferred digest evaluation. 0.6 Jan. 1999 HJB This release removed the redundant information (binary id, size, compression id) from a binary header when there is a MIME header, removed the unused repeat argument, and made the memory allocation for buffering and tables with many rows sensitive to the current memory allocation already used. 0.6.1 Feb. 2001 HP (per This release fixed a memory leak due HJB) to misallocation by size of cbf_handle instead of cbf_handle_struct 0.7 Mar. 2001 PJE This release added high-level instructions based on the imgCIF dictionary version 1.1. 0.7.1 Mar. 2001 PJE The high-level functions were revised to permit future expansion to files with multiple images. 0.7.2 Apr. 2001 HJB This release adjusted cbf_cimple.c to conform to cif_img.dic version 1.1.3 0.7.2.1 May 2001 PJE This release corrected an if nesting error in the prior mod to cbf_cimple.c. 0.7.3 Oct. 2002 PJE This release modified cbf_simple.c to reorder image data on read so that the indices are always increasing in memory (this behavior was undefined previously). 0.7.4 Jan 2004 HJB This release fixes a parse error for quoted strings, adds code to get and set character string types, and removes compiler warnings 0.7.5 Apr 2006 HJB This release cleans up some compiler warnings, corrects a parse error on quoted strings with a leading blank as adds the new routines for support of aliases, dictionaries and real arrays, higher level routines to get and set pixel sizes, do cell computations, and to set beam centers, improves support for conversion of images, picking up more data from headers. 0.7.6 Jul 2006 HJB This release reorganizes the kit into two pieces: CBFlib_0.7.6_Data_Files and CBFlib_0.7.6. An optional local copy of getopt is added. The 1.4 draft dictionary has been added. cif2cbf updated to support vcif2 validation. convert_image and cif2cbf updated to report text of error messages. convert_image updated to support tag and category aliases, default to adxv images. convert_image and img updated to support row-major images. Support added for binning. API Support added for validation, wide files and line folding. Logic changed for beam center reporting. Added new routines: cbf_validate, cbf_get_bin_sizes, cbf_set_bin_sizes, cbf_find_last_typed_child, cbf_compose_itemname, cbf_set_cbf_logfile, cbf_make_widefile, cbf_read_anyfile, cbf_read_widefile, cbf_write_local_file, cbf_write_widefile, cbf_column_number, cbf_blockitem_number, cbf_log, cbf_check_category_tags, cbf_set_beam_center 0.7.7 February 2007 HJB This release reflects changes for base 32K support developed by G. Darakev, and changes for support of reals, 3d arrays, byte_offset compression and J. P. Abrahams packed compression made in consultation with (in alphabetic order) E. Eikenberry, A. Hammerley, W. Kabsch, M. Kobas, J. Wright and others at PSI and ESRF in January 2007, as well accumulated changes fixing problems in release 0.7.6. 0.7.7.1 February 2007 HJB This release is a patch to 0.7.7 to change the treatment of the byteorder parameter from strcpy semantics to return of a pointer to a string constant. Our thanks to E. Eikenberry for pointing out the problem. 0.7.7.2 February 2007 HJB This release is a patch to 0.7.7.1 to add testing for JPA packed compression and to respect signs declared in the MIME header. 0.7.7.3 April 2007 HJB This release is a patch to 0.7.7.3 to add f90 support for reading of CBF byte-offset and packed compression, to fix problems with gcc 4.4.1 and to correct errors in multidimensional packed compression. 0.7.7.4 May 2007 HJB Corrects in handling SLS detector mincbfs and reorder dimensions versus arrays for some f90 compilers as per H. Powell. 0.7.7.5 May 2007 HJB Fix to cbf_get_image for bug reported by F. Remacle, fixes for windows builds as per J. Wright and F. Remacle. 0.7.7.6 Jun 2007 HJB Fix to CBF byte-offset compression writes, fix to Makefiles and m4 for f90 test programs to allow adjustable record length. 0.7.8 Jul 2007 HJB Release for full support of SLS data files with updated convert_minicbf, and support for gfortran from gcc 4.2. 0.7.8.1 Jul 2007 HJB Update to 0.7.8 release to fix memory leaks reported by N. Sauter and to update validation checks for recent changes. 0.7.8.2 Dec 2007 CN, HJB Update to 0.7.8.1 to add ADSC jiffie by Chris Nielsen, and to add ..._fs and ..._sf macros. 0.7.9 Dec 2007 CN, HJB Identical to 0.7.8.2 except for a cleanup of deprecated examples, e.g. diffrn_frame_data 0.7.9.1 Jan 2008 CN, HJB Update to 0.7.8.2 to add inverse ADSC jiffie by Chris Nielsen, to clean up problems in handling maps for RasMol. 0.8.0 Jul 2008 GT, HJB Cleanup of 0.7.9.1 to start 0.8 series. 0.8.1 Jul 2009 EZ, CN, Release with EZ's 2008 DDLm support PC, GW, using JH's PyCifRW, also cbff f95 JH, HJB wrapper code, PC's java bindings. 0.9.1 Aug 2010 PC, EE, Release with EE's Dectris template JLM, NS, software, also with vcif3, new EZ, HJB arvai_test, sequence_match. 0.9.2 Feb 2011 PC, EE, New default release with updated JLM, NS, pycbf, tiff support, removal of EZ, HJB default use of PyCifRW to avoid Fedora license issue. ---------------------------------------------------------------------- Known Problems The example program tiff2cbf needs the enviroment variable LD_LIBRARY_PATH set to the location of the lib directory in CBFlib_0.9.2, unless a system install of tiff-3.9.4-rev-6Feb11 has been done. Due to license issues, PyCifRW is not included with default releases of CBFlib. Users can download PyCifRW separately. There are some issues with Peter Chang's lastest java wrapper under the CBFlib 0.9.2 release. Until they are resolved, the CBFlib 0.8.1 release should be used for Java applications. This version does not have support for predictor compression. Code is needed to support array sub-sections. Foreword In order to work with CBFlib, you need: * the source code, in the form of a "gzipped" tar, CBFlib_0.9.2.tar.gz; and * the test data: * CBFlib_0.9.2_Data_Files_Input.tar.gz (17 MB) a "gzipped" tar of the input data files needed to test the API; * CBFlib_0.9.2_Data_Files_Output.tar.gz (36 MB) a "gzipped" tar of the output data files needed to test the API, or, if space is at a premium; * CBFlib_0.9.2_Data_Files_Output_Sigs_Only.tar.gz (1 KB) is a "gzipped" tar of only the MD5 signatures of the output data files needed to test the API. If your system has the program wget, you only need the source code. The download of the other tar balls will be handled automatically. Be careful about space. A full build and test can use 350 MB or more. If space is tight, be sure to read the instructions below on using only the signatures of the test files. Uncompress and unpack : * gunzip < CBFlib_0.9.2.tar.gz | tar xvf - To run the test programs, you will also need Paul Ellis's sample MAR345 image, example.mar2300, Chris Nielsen's sample ADSC Quantum 315 image, mb_LP_1_001.img, and Eric Eikenberry's SLS sample Pilatus 6m image, insulin_pilatus6m, as sample data. In addition there are is a PDB mmCIF file, 9ins.cif, and 3 special test files testflatin.cbf, testflatpackedin.cbf and testrealin.cbf. All these files will be dowloaded and extracted by the Makefile from CBFlib_0.9.2_Data_Files_Input. Do not download copies into the top level directory. Thare are various sample Makefiles for common configurations. The Makefile_OSX samples is for systems with gfortran from prior to the release of gcc 4.2. For the most recent gfortran, use Makefile_OSX_gcc42. All the Makefiles are generated from m4/Makefile.m4. The Makefiles use GNU make constructs, such as ifeq and ifneq. If you need to use a different version of make, you will need to edit out the conditionals The operation of the Makefiles is sensitive to the following environment variables: * CBFLIB_USE_PYCIFRW If you define this environment variable, you may rebuild the Makefiles to include James Hester's PyCifRW. The process under bash is: export CBFLIB_USE_PYCIFRW=yes cd CBFlib_0.9.2 touch m4/Makefile.m4 make Makefiles * CBF_DONT_USE_LONG_LONG If you define this environment variable, use of the long long data type in CBFlib is replaced by use of a struct. The Makefiles do not need to be rebuilt. Makefile_MINGW does not use the long long data type even without defining this variable. * NOFORTRAN If you define this environment variable, use of the fortran compiler is suppressed. If necessary, adjust the definition of CC and C++ and other defintions in Makefile to point to your compilers. Set the definition of CFLAGS to an appropriate value for your C and C++ compilers, the definition of F90C to point to your Fortan-90/95 compiler, and the definitions of F90FLAGS and F90LDFLAGS to approriate values for your Fortan-90/95 compilers, and then make all make tests or, if space is at a premium: make all make tests_sigs_only If you do not have a fortran compiler, you will need edit the Makefile or to define the variable NOFORTRAN, either in the Makefile or in the environment We have included examples of CBF/imgCIF files produced by CBFlib in the test data CBFlib_0.9.2_Data_Files_Output.tar.gz, the current best draft of the CBF Extensions Dictionary, and of Andy Hammersley's CBF definition, updated to become a DRAFT CBF/ImgCIF DEFINITION. CBFlib 0.9.2 includes a program, tiff2cbf, to convert from tiff files to CBF files, that requires an augmented version of tiff-3.9.4 called tiff-3.9.4-rev-6Feb11, that installs into the CBFlib_0.9.2 directory. If a system copy is desired, download and install http://downloads.sf.net/cbflib/tiff-3.9.4-rev-6Feb11.tar.gz ---------------------------------------------------------------------- Contents * 1. Introduction * 2. Function descriptions * 2.1 General description * 2.1.1 CBF handles * 2.1.2 CBF goniometer handles * 2.1.3 CBF detector handles * 2.1.4 Return values * 2.2 Reading and writing files containing binary sections * 2.2.1 Reading binary sections * 2.2.2 Writing binary sections * 2.2.3 Summary of reading and writing files containing binary sections * 2.2.4 Ordering of array indices * 2.3 Low-level function prototypes * 2.3.1 cbf_make_handle * 2.3.2 cbf_free_handle * 2.3.3 cbf_read_file, cbf_read_widefile * 2.3.4 cbf_write_file, cbf_write_widefile * 2.3.5 cbf_new_datablock, cbf_new_saveframe * 2.3.6 cbf_force_new_datablock, cbf_force_new_saveframe * 2.3.7 cbf_new_category * 2.3.8 cbf_force_new_category * 2.3.9 cbf_new_column * 2.3.10 cbf_new_row * 2.3.11 cbf_insert_row * 2.3.12 cbf_delete_row * 2.3.13 cbf_set_datablockname, cbf_set_saveframename * 2.3.14 cbf_reset_datablocks * 2.3.15 cbf_reset_datablock, cbf_reset_saveframe * 2.3.16 cbf_reset_category * 2.3.17 cbf_remove_datablock, cbf_remove_saveframe * 2.3.18 cbf_remove_category * 2.3.19 cbf_remove_column * 2.3.20 cbf_remove_row * 2.3.21 cbf_rewind_datablock * 2.3.22 cbf_rewind_category, cbf_rewind_saveframe, cbf_rewind_blockitem * 2.3.23 cbf_rewind_column * 2.3.24 cbf_rewind_row * 2.3.25 cbf_next_datablock * 2.3.26 cbf_next_category, cbf_next_saveframe, cbf_next_blockitem * 2.3.27 cbf_next_column * 2.3.28 cbf_next_row * 2.3.29 cbf_find_datablock * 2.3.30 cbf_find_category, cbf_find_saveframe, cbf_find_blockitem * 2.3.31 cbf_find_column * 2.3.32 cbf_find_row * 2.3.33 cbf_find_nextrow * 2.3.34 cbf_count_datablocks * 2.3.35 cbf_count_categories, cbf_count_saveframes, cbf_count_blockitems * 2.3.36 cbf_count_columns * 2.3.37 cbf_count_rows * 2.3.38 cbf_select_datablock * 2.3.39 cbf_select_category, cbf_select_saveframe, cbf_select_blockitem * 2.3.40 cbf_select_column * 2.3.41 cbf_select_row * 2.3.42 cbf_datablock_name * 2.3.43 cbf_category_name * 2.3.44 cbf_column_name, cbf_set_column_name * 2.3.45 cbf_row_number * 2.3.46 cbf_get_value, cbf_require_value * 2.3.47 cbf_set_value * 2.3.48 cbf_get_typeofvalue * 2.3.49 cbf_set_typeofvalue * 2.3.50 cbf_get_integervalue, cbf_require_integervalue * 2.3.51 cbf_set_integervalue * 2.3.52 cbf_get_doublevalue, cbf_require_doublevalue * 2.3.53 cbf_set_doublevalue * 2.3.54 cbf_get_integerarrayparameters, cbf_get_integerarrayparameters_wdims, cbf_get_integerarrayparameters_wdims_fs, cbf_get_integerarrayparameters_wdims_sf cbf_get_realarrayparameters, cbf_get_realarrayparameters_wdims, cbf_get_realarrayparameters_wdims_fs, cbf_get_realarrayparameters_wdims_sf * 2.3.55 cbf_get_integerarray, cbf_get_realarray * 2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, cbf_set_integerarray_wdims_sf, cbf_set_realarray, cbf_set_realarray_wdims, cbf_set_realarray_wdims_fs, cbf_set_realarray_wdims_sf * 2.3.57 cbf_failnez * 2.3.58 cbf_onfailnez * 2.3.59 cbf_require_datablock * 2.3.60 cbf_require_category * 2.3.61 cbf_require_column * 2.3.62 cbf_require_column_value * 2.3.63 cbf_require_column_integervalue * 2.3.64 cbf_require_column_doublevalue * 2.3.65 cbf_get_local_integer_byte_order, cbf_get_local_real_byte_order, cbf_get_local_real_format * 2.3.66 cbf_get_dictionary, cbf_set_dictionary, cbf_require_dictionary * 2.3.67 cbf_convert_dictionary * 2.3.68 cbf_find_tag, cbf_find_local_tag * 2.3.69 cbf_find_category_root, cbf_set_category_root, cbf_require_category_root * 2.3.70 cbf_find_tag_root, cbf_set_tag_root, cbf_require_tag_root * 2.3.71 cbf_find_tag_category, cbf_set_tag_category * 2.4 High-level function prototypes (new for version 0.7) * 2.4.1 cbf_read_template * 2.4.2 cbf_get_diffrn_id, cbf_require_diffrn_id * 2.4.3 cbf_set_diffrn_id * 2.4.4 cbf_get_crystal_id * 2.4.5 cbf_set_crystal_id * 2.4.6 cbf_get_wavelength * 2.4.7 cbf_set_wavelength * 2.4.8 cbf_get_polarization * 2.4.9 cbf_set_polarization * 2.4.10 cbf_get_divergence * 2.4.11 cbf_set_divergence * 2.4.12 cbf_count_elements * 2.4.13 cbf_get_element_id * 2.4.14 cbf_get_gain * 2.4.15 cbf_set_gain * 2.4.16 cbf_get_overload * 2.4.17 cbf_set_overload * 2.4.18 cbf_get_integration_time * 2.4.19 cbf_set_integration_time * 2.4.20 cbf_get_time * 2.4.21 cbf_set_time * 2.4.22 cbf_get_date * 2.4.23 cbf_set_date * 2.4.24 cbf_set_current_time * 2.4.25 cbf_get_image_size, cbf_get_image_size_fs, cbf_get_image_size_fs, cbf_get_3d_image_size, cbf_get_3d_image_size_fs, cbf_get_3d_image_size_sf * 2.4.26 cbf_get_image, cbf_get_image_fs, cbf_get_image_sf, cbf_get_real_image, cbf_get_real_image_fs, cbf_get_real_image_sf, cbf_get_3d_image, cbf_get_3d_image_fs, cbf_get_3d_image_sf, cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf * 2.4.27 cbf_set_image, cbf_set_image_fs, cbf_set_image_sf, cbf_set_real_image, cbf_set_real_image_fs, cbf_set_real_image_sf, cbf_set_3d_image, cbf_set_3d_image, cbf_set_3d_image, cbf_set_real_3d_image, cbf_set_real_3d_image_fs, cbf_set_real_3d_image_sf * 2.4.28 cbf_get_axis_setting * 2.4.29 cbf_set_axis_setting * 2.4.30 cbf_construct_goniometer * 2.4.31 cbf_free_goniometer * 2.4.32 cbf_get_rotation_axis * 2.4.33 cbf_get_rotation_range * 2.4.34 cbf_rotate_vector * 2.4.35 cbf_get_reciprocal * 2.4.36 cbf_construct_detector, cbf_construct_reference_detector, cbf_require_reference_detector * 2.4.37 cbf_free_detector * 2.4.38 cbf_get_beam_center, cbf_get_beam_center_fs, cbf_get_beam_center_sf, cbf_set_beam_center, cbf_set_beam_center_fs, cbf_set_beam_center_sf, cbf_set_reference_beam_center, cbf_set_reference_beam_center_fs, cbf_set_reference_beam_center_sf * 2.4.39 cbf_get_detector_distance * 2.4.40 cbf_get_detector_normal * 2.4.41 cbf_get_detector_axis_slow, cbf_get_detector_axis_fast, cbf_get_detector_axes, cbf_get_detector_axes_fs, cbf_get_detector_axes_sf * 2.4.42 cbf_get_pixel_coordinates, cbf_get_pixel_coordinates_fs, cbf_get_pixel_coordinates_sf * 2.4.43 cbf_get_pixel_normal, cbf_get_pixel_normal_fs, cbf_get_pixel_normal_sf * 2.4.44 cbf_get_pixel_area, cbf_get_pixel_area_fs, cbf_get_pixel_area_sf * 2.4.45 cbf_get_pixel_size, cbf_get_pixel_size_fs, cbf_get_pixel_size_sf * 2.4.46 cbf_set_pixel_size, cbf_set_pixel_size_fs, cbf_set_pixel_size_sf * 2.4.47 cbf_get_inferred_pixel_size, cbf_get_inferred_pixel_size_fs, cbf_get_inferred_pixel_size_sf * 2.4.48 cbf_get_unit_cell * 2.4.49 cbf_set_unit_cell * 2.4.50 cbf_get_reciprocal_cell * 2.4.51 cbf_set_reciprocal_cell * 2.4.52 cbf_compute_cell_volume * 2.4.53 cbf_compute_reciprocal_cell * 2.4.54 cbf_get_orientation_matrix, cbf_set_orientation_matrix * 2.4.55 cbf_get_bin_sizes, cbf_set_bin_sizes * 2.5 F90 function interfaces * 2.5.1 FCB_ATOL_WCNT * 2.5.2 FCB_CI_STRNCMPARR * 2.5.3 FCB_EXIT_BINARY * 2.5.4 FCB_NBLEN_ARRAY * 2.5.5 FCB_NEXT_BINARY * 2.5.6 FCB_OPEN_CIFIN * 2.5.7 FCB_PACKED: FCB_DECOMPRESS_PACKED_I2, FCB_DECOMPRESS_PACKED_I4, FCB_DECOMPRESS_PACKED_3D_I2, FCB_DECOMPRESS_PACKED_3D_I4 * 2.5.8 FCB_READ_BITS * 2.5.9 FCB_READ_BYTE * 2.5.10 FCB_READ_IMAGE_I2, FCB_READ_IMAGE_I4, FCB_READ_IMAGE_3D_I2, FCB_READ_IMAGE_3D_I4 * 2.5.11 FCB_READ_LINE * 2.5.12 FCB_READ_XDS_I2 * 2.5.13 FCB_SKIP_WHITESPACE * 3. File format * 3.1 General description * 3.2 Format of the binary sections * 3.2.1 Format of imgCIF binary sections * 3.2.2 Format of CBF binary sections * 3.3 Compression schemes * 3.3.1 Canonical-code compression * 3.3.2 CCP4-style compression * 3.3.3 Byte_offset compression * 4. Installation * 5. Example programs 1. Introduction CBFlib (Crystallographic Binary File library) is a library of ANSI-C functions providing a simple mechanism for accessing Crystallographic Binary Files (CBF files) and Image-supporting CIF (imgCIF) files. The CBFlib API is loosely based on the CIFPARSE API for mmCIF files. Like CIFPARSE, CBFlib does not perform any semantic integrity checks; rather it simply provides functions to create, read, modify and write CBF binary data files and imgCIF ASCII data files. Starting with version 0.7.7, an envolving FCBlib (Fortran Crystallographic Binary library) has been added. As of this release it includes code for reading byte-offset and packed compression image files created by CBFlib. 2. Function descriptions 2.1 General description Almost all of the CBFlib functions receive a value of type cbf_handle (a CBF handle) as the first argument. Several of the high-level CBFlib functions dealing with geometry receive a value of type cbf_goniometer (a handle for a CBF goniometer object) or cbf_detector (a handle for a CBF detector object). All functions return an integer equal to 0 for success or an error code for failure. 2.1.1 CBF handles CBFlib permits a program to use multiple CBF objects simultaneously. To identify the CBF object on which a function will operate, CBFlib uses a value of type cbf_handle. All functions in the library except cbf_make_handle expect a value of type cbf_handle as the first argument. The function cbf_make_handle creates and initializes a new CBF handle. The function cbf_free_handle destroys a handle and frees all memory associated with the corresponding CBF object. 2.1.2 CBF goniometer handles To represent the goniometer used to orient a sample, CBFlib uses a value of type cbf_goniometer. A goniometer object is created and initialized from a CBF object using the function cbf_construct_goniometer. The function cbf_free_goniometer destroys a goniometer handle and frees all memory associated with the corresponding object. 2.1.3 CBF detector handles To represent a detector surface mounted on a positioning system, CBFlib uses a value of type cbf_detector. A goniometer object is created and initialized from a CBF object using one of the functions cbf_construct_detector, cbf_construct_reference_detector or cbf_require_reference_detector. The function cbf_free_detector destroys a detector handle and frees all memory associated with the corresponding object. 2.1.4 Return values All of the CBFlib functions return 0 on success and an error code on failure. The error codes are: CBF_FORMAT The file format is invalid CBF_ALLOC Memory allocation failed CBF_ARGUMENT Invalid function argument CBF_ASCII The value is ASCII (not binary) CBF_BINARY The value is binary (not ASCII) CBF_BITCOUNT The expected number of bits does not match the actual number written CBF_ENDOFDATA The end of the data was reached before the end of the array CBF_FILECLOSE File close error CBF_FILEOPEN File open error CBF_FILEREAD File read error CBF_FILESEEK File seek error CBF_FILETELL File tell error CBF_FILEWRITE File write error CBF_IDENTICAL A data block with the new name already exists CBF_NOTFOUND The data block, category, column or row does not exist CBF_OVERFLOW The number read cannot fit into the destination argument. The destination has been set to the nearest value. CBF_UNDEFINED The requested number is not defined (e.g. 0/0; new for version 0.7). CBF_NOTIMPLEMENTED The requested functionality is not yet implemented (New for version 0.7). If more than one error has occurred, the error code is the logical OR of the individual error codes. 2.2 Reading and writing files containing binary sections 2.2.1 Reading binary sections The current version of CBFlib only decompresses a binary section from disk when requested by the program. When a file containing one or more binary sections is read, CBFlib saves the file pointer and the position of the binary section within the file and then jumps past the binary section. When the program attempts to access the binary data, CBFlib sets the file position back to the start of the binary section and then reads the data. For this scheme to work: 1. The file must be a random-access file opened in binary mode (fopen ( ," rb")). 2. The program must not close the file. CBFlib will close the file using fclose ( ) when it is no longer needed. At present, this also means that a program cant read a file and then write back to the same file. This restriction will be eliminated in a future version. When reading an imgCIF vs a CBF, the difference is detected automatically. 2.2.2 Writing binary sections When a program passes CBFlib a binary value, the data is compressed to a temporary file. If the CBF object is subsequently written to a file, the data is simply copied from the temporary file to the output file. The output file can be of any type. If the program indicates to CBFlib that the file is a random-access and readable, CBFlib will conserve disk space by closing the temporary file and using the output file as the location at which the binary value is stored. For this option to work: 1. The file must be a random-access file opened in binary update mode (fopen ( , "w+b")). 2. The program must not close the file. CBFlib will close the file using fclose ( ) when it is no longer needed. If this option is not used: 1. CBFlib will continue using the temporary file. 2. CBFlib will not close the file. This is the responsibility of the main program. 2.2.3 Summary of reading and writing files containing binary sections 1. Open disk files to read using the mode "rb". 2. If possible, open disk files to write using the mode "w+b" and tell CBFlib that it can use the file as a buffer. 3. Do not close any files read by CBFlib or written by CBFlib with buffering turned on. 4. Do not attempt to read from a file, then write to the same file. 2.2.4 Ordering of array indices There are two major conventions in the ordering of array indices: * fs: Fast to slow. The first array index (the one numbered "1") is the one for which the values of that index change "fastest". That is, as we move forward in memory, the value of this index changes more rapidly than any other. * sf: Slow to fast. The first array index (the one numbered "1") is the one for which the values of that index change "slowest". That is as we move forward in memory, the value of this index changes more slowly than any other. During the development of CBFlib, both conventions have been used. In order to avoid confusion, the functions for which array indices are used are available in three forms: a default version which may used either one convention or the other, a form in which the name of the function has an "_fs" suffix for the fast to slow convention and a form in which the name of the function has a "_sf" suffix for the slow to fast convention. Designers of applications are advised to use one of the two suffix conventions. There is no burden on performance for using one convention or the other. The differences are resolved at compile time by use of preprocessor macros. ---------------------------------------------------------------------- ---------------------------------------------------------------------- 2.3 Low-level function prototypes 2.3.1 cbf_make_handle PROTOTYPE #include "cbf.h" int cbf_make_handle (cbf_handle *handle); DESCRIPTION cbf_make_handle creates and initializes a new internal CBF object. All other CBFlib functions operating on this object receive the CBF handle as the first argument. ARGUMENTS handle Pointer to a CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.2 cbf_free_handle ---------------------------------------------------------------------- 2.3.2 cbf_free_handle PROTOTYPE #include "cbf.h" int cbf_free_handle (cbf_handle handle); DESCRIPTION cbf_free_handle destroys the CBF object specified by the handle and frees all associated memory. ARGUMENTS handle CBF handle to free. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.1 cbf_make_handle ---------------------------------------------------------------------- 2.3.3 cbf_read_file, cbf_read_widefile PROTOTYPE #include "cbf.h" int cbf_read_file (cbf_handle handle, FILE *file, int flags); int cbf_read_widefile (cbf_handle handle, FILE *file, int flags); DESCRIPTION cbf_read_file reads the CBF or CIF file file into the CBF object specified by handle, using the CIF 1.0 convention of 80 character lines. cbf_read_widefile reads the CBF or CIF file file into the CBF object specified by handle, using the CIF 1.1 convention of 2048 character lines. A warning is issued to stderr for ascii lines over the limit. No test is performed on binary sections. Validation is performed in three ways levels: during the lexical scan, during the parse, and, if a dictionary was converted, against the value types, value enumerations, categories and parent-child relationships specified in the dictionary. flags controls the interpretation of binary section headers, the parsing of brackets constructs and the parsing of treble-quoted strings. MSG_DIGEST: Instructs CBFlib to check that the digest of the binary section matches any header digest value. If the digests do not match, the call will return CBF_FORMAT. This evaluation and comparison is delayed (a "lazy" evaluation) to ensure maximal processing efficiency. If an immediately evaluation is required, see MSG_DIGESTNOW, below. MSG_DIGESTNOW: Instructs CBFlib to check that the digest of the binary section matches any header digeste value. If the digests do not match, the call will return CBF_FORMAT. This evaluation and comparison is performed during initial parsing of the section to ensure timely error reporting at the expense of processing efficiency. If a more efficient delayed ("lazy") evaluation is required, see MSG_DIGEST, above. MSG_DIGESTWARN: Instructs CBFlib to check that the digest of the binary section matches any header digeste value. If the digests do not match, a warning message will be sent to stderr, but processing will attempt to continue. This evaluation and comparison is first performed during initial parsing of the section to ensure timely error reporting at the expense of processing efficiency. An mismatch of the message digest usually indicates a serious error, but it is sometimes worth continuing processing to try to isolate the cause of the error. Use this option with caution. MSG_NODIGEST: Do not check the digest (default). PARSE_BRACKETS: Accept DDLm bracket-delimited [item,item,...item] or {item,item,...item} or (item,item,...item) constructs as valid, stripping non-quoted embedded whitespace and comments. These constructs may span multiple lines. PARSE_LIBERAL_BRACKETS: Accept DDLm bracket-delimited [item,item,...item] or {item,item,...item} or (item,item,...item) constructs as valid, stripping embedded non-quoted, non-separating whitespace and comments. These constructs may span multiple lines. In this case, whitespace may be used as an alternative to the comma. PARSE_TRIPLE_QUOTES: Accept DDLm triple-quoted """item,item,...item""" or '''item,item,...item''' constructs as valid, stripping embedded whitespace and comments. These constructs may span multiple lines. If this flag is set, then ''' will not be interpreted as a quoted apoptrophe and """ will not be interpreted as a quoted double quote mark and PARSE_NOBRACKETS: Do not accept DDLm bracket-delimited [item,item,...item] or {item,item,...item} or (item,item,...item) constructs as valid, stripping non-quoted embedded whitespace and comments. These constructs may span multiple lines. PARSE_NOTRIPLE_QUOTES: No not accept DDLm triple-quoted """item,item,...item""" or '''item,item,...item''' constructs as valid, stripping embedded whitespace and comments. These constructs may span multiple lines. If this flag is set, then ''' will be interpreted as a quoted apostrophe and """ will be interpreted as a quoted double quote mark. CBFlib defers reading binary sections as long as possible. In the current version of CBFlib, this means that: 1. The file must be a random-access file opened in binary mode (fopen ( , "rb")). 2. The program must not close the file. CBFlib will close the file using fclose ( ) when it is no longer needed. These restrictions may change in a future release. ARGUMENTS handle CBF handle. file Pointer to a file descriptor. headers Controls interprestation of binary section headers. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.4 cbf_write_file ---------------------------------------------------------------------- 2.3.4 cbf_write_file PROTOTYPE #include "cbf.h" int cbf_write_file (cbf_handle handle, FILE *file, int readable, int ciforcbf, int flags, int encoding); int cbf_write_widefile (cbf_handle handle, FILE *file, int readable, int ciforcbf, int flags, int encoding); DESCRIPTION cbf_write_file writes the CBF object specified by handle into the file file, following CIF 1.0 conventions of 80 character lines. cbf_write_widefile writes the CBF object specified by handle into the file file, following CIF 1.1 conventions of 2048 character lines. A warning is issued to stderr for ascii lines over the limit, and an attempt is made to fold lines to fit. No test is performed on binary sections. If a dictionary has been provided, aliases will be applied on output. Unlike cbf_read_file, the file does not have to be random-access. If the file is random-access and readable, readable can be set to non-0 to indicate to CBFlib that the file can be used as a buffer to conserve disk space. If the file is not random-access or not readable, readable must be 0. If readable is non-0, CBFlib will close the file when it is no longer required, otherwise this is the responsibility of the program. ciforcbf selects the format in which the binary sections are written: CIF Write an imgCIF file. CBF Write a CBF file (default). flags selects the type of header used in CBF binary sections, selects whether message digests are generated, and controls the style of output. The value of flags can be a logical OR of any of: MIME_HEADERS Use MIME-type headers (default). MIME_NOHEADERS Use a simple ASCII headers. MSG_DIGEST Generate message digests for binary data validation. MSG_NODIGEST Do not generate message digests (default). PARSE_BRACKETS Do not convert bracketed strings to text fields (default). PARSE_LIBERAL_BRACKETS Do not convert bracketed strings to text fields (default). PARSE_NOBRACKETS Convert bracketed strings to text fields (default). PARSE_TRIPLE_QUOTES Do not convert triple-quoted strings to text fields (default). PARSE_NOTRIPLE_QUOTES Convert triple-quoted strings to text fields (default). PAD_1K Pad binary sections with 1023 nulls. PAD_2K Pad binary sections with 2047 nulls. PAD_4K Pad binary sections with 4095 nulls. Note that on output, the types "prns&, "brcs" and "bkts" will be converted to "text" fields if PARSE_NOBRACKETS has been set flags, and that the types "tsqs" and "tdqs" will be converted to "text" fields if the flag PARSE_NOTRIPLE_QUOTES has been set in the flags. It is an error to set PARSE_NOBRACKETS and to set either PARSE_BRACKETS or PARSE_LIBERAL_BRACKETS. It is an error to set both PARSE_NOTRIPLE_QUOTES and PARSE_TRIPLE_QUOTES. encoding selects the type of encoding used for binary sections and the type of line-termination in imgCIF files. The value can be a logical OR of any of: ENC_BASE64 Use BASE64 encoding (default). ENC_QP Use QUOTED-PRINTABLE encoding. ENC_BASE8 Use BASE8 (octal) encoding. ENC_BASE10 Use BASE10 (decimal) encoding. ENC_BASE16 Use BASE16 (hexadecimal) encoding. ENC_FORWARD For BASE8, BASE10 or BASE16 encoding, map bytes to words forward (1234) (default on little-endian machines). ENC_BACKWARD Map bytes to words backward (4321) (default on big-endian machines). ENC_CRTERM Terminate lines with CR. ENC_LFTERM Terminate lines with LF (default). ARGUMENTS handle CBF handle. file Pointer to a file descriptor. readable If non-0: this file is random-access and readable and can be used as a buffer. ciforcbf Selects the format in which the binary sections are written (CIF/CBF). headers Selects the type of header in CBF binary sections and message digest generation. encoding Selects the type of encoding used for binary sections and the type of line-termination in imgCIF files. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.3 cbf_read_file ---------------------------------------------------------------------- 2.3.5 cbf_new_datablock, cbf_new_saveframe PROTOTYPE #include "cbf.h" int cbf_new_datablock (cbf_handle handle, const char *datablockname); int cbf_new_saveframe (cbf_handle handle, const char *saveframename); DESCRIPTION cbf_new_datablock creates a new data block with name datablockname and makes it the current data block. cbf_new_saveframe creates a new save frame with name saveframename within the current data block and makes the new save frame the current save frame. If a data block or save frame with this name already exists, the existing data block or save frame becomes the current data block or save frame. ARGUMENTS handle CBF handle. datablockname The name of the new data block. saveframename The name of the new save frame. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.6 cbf_force_new_datablock, cbf_force_new_saveframe 2.3.7 cbf_new_category 2.3.8 cbf_force_new_category 2.3.9 cbf_new_column 2.3.10 cbf_new_row 2.3.11 cbf_insert_row 2.3.12 cbf_set_datablockname, cbf_set_saveframename 2.3.17 cbf_remove_datablock, cbf_remove_saveframe 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.6 cbf_force_new_datablock, cbf_force_new_saveframe PROTOTYPE #include "cbf.h" int cbf_force_new_datablock (cbf_handle handle, const char *datablockname); int cbf_force_new_saveframe (cbf_handle handle, const char *saveframename); DESCRIPTION cbf_force_new_datablock creates a new data block with name datablockname and makes it the current data block. Duplicate data block names are allowed. cbf_force_new_saveframe creates a new savew frame with name saveframename and makes it the current save frame. Duplicate save frame names are allowed. Even if a save frame with this name already exists, a new save frame is created and becomes the current save frame. ARGUMENTS handle CBF handle. datablockname The name of the new data block. saveframename The name of the new save frame. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.5 cbf_new_datablock, cbf_new_saveframe 2.3.7 cbf_new_category 2.3.8 cbf_force_new_category 2.3.9 cbf_new_column 2.3.10 cbf_new_row 2.3.11 cbf_insert_row 2.3.12 cbf_set_datablockname, cbf_set_saveframename 2.3.17 cbf_remove_datablock, cbf_remove_saveframe 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.7 cbf_new_category PROTOTYPE #include "cbf.h" int cbf_new_category (cbf_handle handle, const char *categoryname); DESCRIPTION cbf_new_category creates a new category in the current data block with name categoryname and makes it the current category. If a category with this name already exists, the existing category becomes the current category. ARGUMENTS handle CBF handle. categoryname The name of the new category. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.5 cbf_new_datablock, cbf_new_saveframe 2.3.6 cbf_force_new_datablock, cbf_force_new_saveframe 2.3.8 cbf_force_new_category 2.3.9 cbf_new_column 2.3.10 cbf_new_row 2.3.11 cbf_insert_row 2.3.18 cbf_remove_category 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.8 cbf_force_new_category PROTOTYPE #include "cbf.h" int cbf_force_new_category (cbf_handle handle, const char *categoryname); DESCRIPTION cbf_force_new_category creates a new category in the current data block with name categoryname and makes it the current category. Duplicate category names are allowed. Even if a category with this name already exists, a new category of the same name is created and becomes the current category. The allows for the creation of unlooped tag/value lists drawn from the same category. ARGUMENTS handle CBF handle. categoryname The name of the new category. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.5 cbf_new_datablock, cbf_new_saveframe 2.3.6 cbf_force_new_datablock, cbf_force_new_saveframe 2.3.7 cbf_new_category 2.3.9 cbf_new_column 2.3.10 cbf_new_row 2.3.11 cbf_insert_row 2.3.18 cbf_remove_category 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.9 cbf_new_column PROTOTYPE #include "cbf.h" int cbf_new_column (cbf_handle handle, const char *columnname); DESCRIPTION cbf_new_column creates a new column in the current category with name columnname and makes it the current column. If a column with this name already exists, the existing column becomes the current category. ARGUMENTS handle CBF handle. columnname The name of the new column. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.5 cbf_new_datablock, cbf_new_saveframe 2.3.6 cbf_force_new_datablock, cbf_force_new_saveframe 2.3.7 cbf_new_category 2.3.8 cbf_force_new_category 2.3.10 cbf_new_row 2.3.11 cbf_insert_row 2.3.19 cbf_remove_column 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.10 cbf_new_row PROTOTYPE #include "cbf.h" int cbf_new_row (cbf_handle handle); DESCRIPTION cbf_new_row adds a new row to the current category and makes it the current row. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.5 cbf_new_datablock, cbf_new_saveframe 2.3.6 cbf_force_new_datablock, cbf_force_new_saveframe 2.3.7 cbf_new_category 2.3.8 cbf_force_new_category 2.3.9 cbf_new_column 2.3.11 cbf_insert_row 2.3.12 cbf_delete_row 2.3.20 cbf_remove_row 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.11 cbf_insert_row PROTOTYPE #include "cbf.h" int cbf_insert_row (cbf_handle handle, unsigned int rownumber); DESCRIPTION cbf_insert_row adds a new row to the current category. The new row is inserted as row rownumber and existing rows starting from rownumber are moved up by 1. The new row becomes the current row. If the category has fewer than rownumber rows, the function returns CBF_NOTFOUND. The row numbers start from 0. ARGUMENTS handle CBF handle. rownumber The row number of the new row. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.5 cbf_new_datablock, cbf_new_saveframe 2.3.6 cbf_force_new_datablock, cbf_force_new_saveframe 2.3.7 cbf_new_category 2.3.8 cbf_force_new_category 2.3.9 cbf_new_column 2.3.10 cbf_new_row 2.3.12 cbf_delete_row 2.3.20 cbf_remove_row 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.12 cbf_delete_row PROTOTYPE #include "cbf.h" int cbf_delete_row (cbf_handle handle, unsigned int rownumber); DESCRIPTION cbf_delete_row deletes a row from the current category. Rows starting from rownumber +1 are moved down by 1. If the current row was higher than rownumber, or if the current row is the last row, it will also move down by 1. The row numbers start from 0. ARGUMENTS handle CBF handle. rownumber The number of the row to delete. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.10 cbf_new_row 2.3.11 cbf_insert_row 2.3.17 cbf_remove_datablock, cbf_remove_saveframe 2.3.18 cbf_remove_category 2.3.19 cbf_remove_column 2.3.20 cbf_remove_row 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.13 cbf_set_datablockname, cbf_set_saveframename PROTOTYPE #include "cbf.h" int cbf_set_datablockname (cbf_handle handle, const char *datablockname); int cbf_set_saveframename (cbf_handle handle, const char *saveframename); DESCRIPTION cbf_set_datablockname changes the name of the current data block to datablockname. cbf_set_saveframename changes the name of the current save frame to saveframename. If a data block or save frame with this name already exists (comparison is case-insensitive), the function returns CBF_IDENTICAL. ARGUMENTS handle CBF handle. datablockname The new data block name. datablockname The new save frame name. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.5 cbf_new_datablock, cbf_new_saveframe 2.3.14 cbf_reset_datablocks 2.3.15 cbf_reset_datablock, cbf_reset_saveframe 2.3.17 cbf_remove_datablock, cbf_remove_saveframe 2.3.42 cbf_datablock_name ---------------------------------------------------------------------- 2.3.14 cbf_reset_datablocks PROTOTYPE #include "cbf.h" int cbf_reset_datablocks (cbf_handle handle); DESCRIPTION cbf_reset_datablocks deletes all categories from all data blocks. The current data block does not change. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.15 cbf_reset_datablock, cbf_reset_saveframe 2.3.18 cbf_remove_category ---------------------------------------------------------------------- 2.3.15 cbf_reset_datablock, cbf_reset_datablock PROTOTYPE #include "cbf.h" int cbf_reset_datablock (cbf_handle handle); int cbf_reset_saveframe (cbf_handle handle); DESCRIPTION cbf_reset_datablock deletes all categories from the current data block. cbf_reset_saveframe deletes all categories from the current save frame. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.14 cbf_reset_datablocks 2.3.18 cbf_remove_category ---------------------------------------------------------------------- 2.3.16 cbf_reset_category PROTOTYPE #include "cbf.h" int cbf_reset_category (cbf_handle handle); DESCRIPTION cbf_reset_category deletes all columns and rows from current category. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.16 cbf_reset_category 2.3.19 cbf_remove_column 2.3.20 cbf_remove_row ---------------------------------------------------------------------- 2.3.17 cbf_remove_datablock, cbf_remove_saveframe PROTOTYPE #include "cbf.h" int cbf_remove_datablock (cbf_handle handle); int cbf_remove_saveframe (cbf_handle handle); DESCRIPTION cbf_remove_datablock deletes the current data block. cbf_remove_saveframe deletes the current save frame. The current data block becomes undefined. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.5 cbf_new_datablock, cbf_new_saveframe 2.3.6 cbf_force_new_datablock, cbf_force_new_saveframe 2.3.18 cbf_remove_category 2.3.19 cbf_remove_column 2.3.20 cbf_remove_row 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.18 cbf_remove_category PROTOTYPE #include "cbf.h" int cbf_remove_category (cbf_handle handle); DESCRIPTION cbf_remove_category deletes the current category. The current category becomes undefined. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.7 cbf_new_category 2.3.8 cbf_force_new_category 2.3.17 cbf_remove_datablock, cbf_remove_saveframe 2.3.19 cbf_remove_column 2.3.20 cbf_remove_row 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.19 cbf_remove_column PROTOTYPE #include "cbf.h" int cbf_remove_column (cbf_handle handle); DESCRIPTION cbf_remove_column deletes the current column. The current column becomes undefined. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.9 cbf_new_column 2.3.17 cbf_remove_datablock, cbf_remove_saveframe 2.3.18 cbf_remove_category 2.3.20 cbf_remove_row 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.20 cbf_remove_row PROTOTYPE #include "cbf.h" int cbf_remove_row (cbf_handle handle); DESCRIPTION cbf_remove_row deletes the current row in the current category. If the current row was the last row, it will move down by 1, otherwise, it will remain the same. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.10 cbf_new_row 2.3.11 cbf_insert_row 2.3.17 cbf_remove_datablock, cbf_remove_saveframe 2.3.18 cbf_remove_category 2.3.19 cbf_remove_column 2.3.12 cbf_delete_row 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.21 cbf_rewind_datablock PROTOTYPE #include "cbf.h" int cbf_rewind_datablock (cbf_handle handle); DESCRIPTION cbf_rewind_datablock makes the first data block the current data block. If there are no data blocks, the function returns CBF_NOTFOUND. The current category becomes undefined. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.22 cbf_rewind_category, cbf_rewind_saveframe, cbf_rewind_blockitem 2.3.19 cbf_rewind_column 2.3.24 cbf_rewind_row 2.3.25 cbf_next_datablock ---------------------------------------------------------------------- 2.3.22 cbf_rewind_category, cbf_rewind_saveframe, cbf_rewind_blockitem PROTOTYPE #include "cbf.h" int cbf_rewind_category (cbf_handle handle); int cbf_rewind_saveframe (cbf_handle handle); int cbf_rewind_blockitem (cbf_handle handle, CBF_NODETYPE * type); DESCRIPTION cbf_rewind_category makes the first category in the current data block the current category. cbf_rewind_saveframe makes the first saveframe in the current data block the current saveframe. cbf_rewind_blockitem makes the first blockitem (category or saveframe) in the current data block the current blockitem. The type of the blockitem (CBF_CATEGORY or CBF_SAVEFRAME) is returned in type. If there are no categories, saveframes or blockitems the function returns CBF_NOTFOUND. The current column and row become undefined. ARGUMENTS handle CBF handle. type CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.21 cbf_rewind_datablock 2.3.19 cbf_rewind_column 2.3.24 cbf_rewind_row 2.3.26 cbf_next_category, cbf_next_saveframe, cbf_next_blockitem ---------------------------------------------------------------------- 2.3.23 cbf_rewind_column PROTOTYPE #include "cbf.h" int cbf_rewind_column (cbf_handle handle); DESCRIPTION cbf_rewind_column makes the first column in the current category the current column. If there are no columns, the function returns CBF_NOTFOUND. The current row is not affected. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.21 cbf_rewind_datablock 2.3.22 cbf_rewind_category, cbf_rewind_saveframe, cbf_rewind_blockitem 2.3.24 cbf_rewind_row 2.3.27 cbf_next_column ---------------------------------------------------------------------- 2.3.24 cbf_rewind_row PROTOTYPE #include "cbf.h" int cbf_rewind_row (cbf_handle handle); DESCRIPTION cbf_rewind_row makes the first row in the current category the current row. If there are no rows, the function returns CBF_NOTFOUND. The current column is not affected. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.21 cbf_rewind_datablock 2.3.22 cbf_rewind_category, cbf_rewind_saveframe, cbf_rewind_blockitem 2.3.19 cbf_rewind_column 2.3.28 cbf_next_row ---------------------------------------------------------------------- 2.3.25 cbf_next_datablock PROTOTYPE #include "cbf.h" int cbf_next_datablock (cbf_handle handle); DESCRIPTION cbf_next_datablock makes the data block following the current data block the current data block. If there are no more data blocks, the function returns CBF_NOTFOUND. The current category becomes undefined. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.21 cbf_rewind_datablock 2.3.26 cbf_next_category, cbf_next_saveframe, cbf_next_blockitem 2.3.27 cbf_next_column 2.3.28 cbf_next_row ---------------------------------------------------------------------- 2.3.26 cbf_next_category PROTOTYPE #include "cbf.h" int cbf_next_category (cbf_handle handle); DESCRIPTION cbf_next_category makes the category following the current category in the current data block the current category. If there are no more categories, the function returns CBF_NOTFOUND. The current column and row become undefined. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.22 cbf_rewind_category, cbf_rewind_saveframe, cbf_rewind_blockitem 2.3.25 cbf_next_datablock 2.3.27 cbf_next_column 2.3.27 cbf_next_row ---------------------------------------------------------------------- 2.3.27 cbf_next_column PROTOTYPE #include "cbf.h" int cbf_next_column (cbf_handle handle); DESCRIPTION cbf_next_column makes the column following the current column in the current category the current column. If there are no more columns, the function returns CBF_NOTFOUND. The current row is not affected. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.19 cbf_rewind_column 2.3.25 cbf_next_datablock 2.3.26 cbf_next_category, cbf_next_saveframe, cbf_next_blockitem 2.3.28 cbf_next_row ---------------------------------------------------------------------- 2.3.28 cbf_next_row PROTOTYPE #include "cbf.h" int cbf_next_row (cbf_handle handle); DESCRIPTION cbf_next_row makes the row following the current row in the current category the current row. If there are no more rows, the function returns CBF_NOTFOUND. The current column is not affected. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.24 cbf_rewind_row 2.3.25 cbf_next_datablock 2.3.26 cbf_next_category, cbf_next_saveframe, cbf_next_blockitem 2.3.27 cbf_next_column ---------------------------------------------------------------------- 2.3.29 cbf_find_datablock PROTOTYPE #include "cbf.h" int cbf_find_datablock (cbf_handle handle, const char *datablockname); DESCRIPTION cbf_find_datablock makes the data block with name datablockname the current data block. The comparison is case-insensitive. If the data block does not exist, the function returns CBF_NOTFOUND. The current category becomes undefined. ARGUMENTS handle CBF handle. datablockname The name of the data block to find. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.21 cbf_rewind_datablock 2.3.25 cbf_next_datablock 2.3.30 cbf_find_category, cbf_find_saveframe, cbf_find_blockitem 2.3.31 cbf_find_column 2.3.32 cbf_find_row 2.3.42 cbf_datablock_name 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.30 cbf_find_category PROTOTYPE #include "cbf.h" int cbf_find_category (cbf_handle handle, const char *categoryname); DESCRIPTION cbf_find_category makes the category in the current data block with name categoryname the current category. The comparison is case-insensitive. If the category does not exist, the function returns CBF_NOTFOUND. The current column and row become undefined. ARGUMENTS handle CBF handle. categoryname The name of the category to find. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.22 cbf_rewind_category, cbf_rewind_saveframe, cbf_rewind_blockitem 2.3.26 cbf_next_category, cbf_next_saveframe, cbf_next_blockitem 2.3.29 cbf_find_datablock 2.3.31 cbf_find_column 2.3.32 cbf_find_row 2.3.43 cbf_category_name 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.31 cbf_find_column PROTOTYPE #include "cbf.h" int cbf_find_column (cbf_handle handle, const char *columnname); DESCRIPTION cbf_find_column makes the columns in the current category with name columnname the current column. The comparison is case-insensitive. If the column does not exist, the function returns CBF_NOTFOUND. The current row is not affected. ARGUMENTS handle CBF handle. columnname The name of column to find. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.19 cbf_rewind_column 2.3.27 cbf_next_column 2.3.29 cbf_find_datablock 2.3.30 cbf_find_category, cbf_find_saveframe, cbf_find_blockitem 2.3.32 cbf_find_row 2.3.44 cbf_column_name 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.32 cbf_find_row PROTOTYPE #include "cbf.h" int cbf_find_row (cbf_handle handle, const char *value); DESCRIPTION cbf_find_row makes the first row in the current column with value value the current row. The comparison is case-sensitive. If a matching row does not exist, the function returns CBF_NOTFOUND. The current column is not affected. ARGUMENTS handle CBF handle. value The value of the row to find. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.24 cbf_rewind_row 2.3.28 cbf_next_row 2.3.29 cbf_find_datablock 2.3.30 cbf_find_category, cbf_find_saveframe, cbf_find_blockitem 2.3.31 cbf_find_column 2.3.33 cbf_find_nextrow 2.3.46 cbf_get_value, cbf_require_value 2.3.48 cbf_get_typeofvalue 2.3.33 cbf_find_nextrow PROTOTYPE #include "cbf.h" int cbf_find_nextrow (cbf_handle handle, const char *value); DESCRIPTION cbf_find_nextrow makes the makes the next row in the current column with value value the current row. The search starts from the row following the last row found with cbf_find_row or cbf_find_nextrow, or from the current row if the current row was defined using any other function. The comparison is case-sensitive. If no more matching rows exist, the function returns CBF_NOTFOUND. The current column is not affected. ARGUMENTS handle CBF handle. value the value to search for. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.24 cbf_rewind_row 2.3.28 cbf_next_row 2.3.29 cbf_find_datablock 2.3.30 cbf_find_category, cbf_find_saveframe, cbf_find_blockitem 2.3.31 cbf_find_column 2.3.32 cbf_find_row 2.3.46 cbf_get_value, cbf_require_value 2.3.48 cbf_get_typeofvalue ---------------------------------------------------------------------- 2.3.34 cbf_count_datablocks PROTOTYPE #include "cbf.h" int cbf_count_datablocks (cbf_handle handle, unsigned int *datablocks); DESCRIPTION cbf_count_datablocks puts the number of data blocks in *datablocks . ARGUMENTS handle CBF handle. datablocks Pointer to the destination data block count. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.35 cbf_count_categories, cbf_count_saveframes, cbf_count_blockitems 2.3.36 cbf_count_columns 2.3.37 cbf_count_rows 2.3.38 cbf_select_datablock ---------------------------------------------------------------------- 2.3.35 cbf_count_categories PROTOTYPE #include "cbf.h" int cbf_count_categories (cbf_handle handle, unsigned int *categories); DESCRIPTION cbf_count_categories puts the number of categories in the current data block in *categories. ARGUMENTS handle CBF handle. categories Pointer to the destination category count. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.34 cbf_count_datablocks 2.3.36 cbf_count_columns 2.3.37 cbf_count_rows 2.3.39 cbf_select_category, cbf_select_saveframe, cbf_select_blockitem ---------------------------------------------------------------------- 2.3.36 cbf_count_columns PROTOTYPE #include "cbf.h" int cbf_count_columns (cbf_handle handle, unsigned int *columns); DESCRIPTION cbf_count_columns puts the number of columns in the current category in *columns. ARGUMENTS handle CBF handle. columns Pointer to the destination column count. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.34 cbf_count_datablocks 2.3.35 cbf_count_categories, cbf_count_saveframes, cbf_count_blockitems 2.3.37 cbf_count_rows 2.3.40 cbf_select_column ---------------------------------------------------------------------- 2.3.37 cbf_count_rows PROTOTYPE #include "cbf.h" int cbf_count_rows (cbf_handle handle, unsigned int *rows); DESCRIPTION cbf_count_rows puts the number of rows in the current category in *rows . ARGUMENTS handle CBF handle. rows Pointer to the destination row count. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.34 cbf_count_datablocks 2.3.35 cbf_count_categories, cbf_count_saveframes, cbf_count_blockitems 2.3.36 cbf_count_columns 2.3.41 cbf_select_row ---------------------------------------------------------------------- 2.3.38 cbf_select_datablock PROTOTYPE #include "cbf.h" int cbf_select_datablock (cbf_handle handle, unsigned int datablock); DESCRIPTION cbf_select_datablock selects data block number datablock as the current data block. The first data block is number 0. If the data block does not exist, the function returns CBF_NOTFOUND. ARGUMENTS handle CBF handle. datablock Number of the data block to select. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.34 cbf_count_datablocks 2.3.39 cbf_select_category, cbf_select_saveframe, cbf_select_blockitem 2.3.40 cbf_select_column 2.3.41 cbf_select_row ---------------------------------------------------------------------- 2.3.39 cbf_select_category PROTOTYPE #include "cbf.h" int cbf_select_category (cbf_handle handle, unsigned int category); DESCRIPTION cbf_select_category selects category number category in the current data block as the current category. The first category is number 0. The current column and row become undefined. If the category does not exist, the function returns CBF_NOTFOUND. ARGUMENTS handle CBF handle. category Number of the category to select. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.35 cbf_count_categories, cbf_count_saveframes, cbf_count_blockitems 2.3.38 cbf_select_datablock 2.3.40 cbf_select_column 2.3.41 cbf_select_row ---------------------------------------------------------------------- 2.3.40 cbf_select_column PROTOTYPE #include "cbf.h" int cbf_select_column (cbf_handle handle, unsigned int column); DESCRIPTION cbf_select_column selects column number column in the current category as the current column. The first column is number 0. The current row is not affected If the column does not exist, the function returns CBF_NOTFOUND. ARGUMENTS handle CBF handle. column Number of the column to select. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.36 cbf_count_columns 2.3.38 cbf_select_datablock 2.3.39 cbf_select_category, cbf_select_saveframe, cbf_select_blockitem 2.3.41 cbf_select_row ---------------------------------------------------------------------- 2.3.41 cbf_select_row PROTOTYPE #include "cbf.h" int cbf_select_row (cbf_handle handle, unsigned int row); DESCRIPTION cbf_select_row selects row number row in the current category as the current row. The first row is number 0. The current column is not affected If the row does not exist, the function returns CBF_NOTFOUND. ARGUMENTS handle CBF handle. row Number of the row to select. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.37 cbf_count_rows 2.3.38 cbf_select_datablock 2.3.39 cbf_select_category, cbf_select_saveframe, cbf_select_blockitem 2.3.40 cbf_select_column ---------------------------------------------------------------------- 2.3.42 cbf_datablock_name PROTOTYPE #include "cbf.h" int cbf_datablock_name (cbf_handle handle, const char **datablockname); DESCRIPTION cbf_datablock_name sets *datablockname to point to the name of the current data block. The data block name will be valid as long as the data block exists and has not been renamed. The name must not be modified by the program in any way. ARGUMENTS handle CBF handle. datablockname Pointer to the destination data block name pointer. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.29 cbf_find_datablock ---------------------------------------------------------------------- 2.3.43 cbf_category_name PROTOTYPE #include "cbf.h" int cbf_category_name (cbf_handle handle, const char **categoryname); DESCRIPTION cbf_category_name sets *categoryname to point to the name of the current category of the current data block. The category name will be valid as long as the category exists. The name must not be modified by the program in any way. ARGUMENTS handle CBF handle. categoryname Pointer to the destination category name pointer. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.30 cbf_find_category, cbf_find_saveframe, cbf_find_blockitem ---------------------------------------------------------------------- 2.3.44 cbf_column_name, cbf_set_column_name PROTOTYPE #include "cbf.h" int cbf_column_name (cbf_handle handle, const char **columnname); int cbf_set_column_name (cbf_handle handle, const char *newcolumnname) DESCRIPTION cbf_column_name sets *columnname to point to the name of the current column of the current category. The column name will be valid as long as the column exists. The name must not be modified by the program in any way. cbf_set_column_name sets the name of the current column to newcolumnname ARGUMENTS handle CBF handle. columnname Pointer to the destination column name pointer. newcolumnname New column name pointer. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.31 cbf_find_column ---------------------------------------------------------------------- 2.3.45 cbf_row_number PROTOTYPE #include "cbf.h" int cbf_row_number (cbf_handle handle, unsigned int *row); DESCRIPTION cbf_row_number sets *row to the number of the current row of the current category. ARGUMENTS handle CBF handle. row Pointer to the destination row number. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.41 cbf_select_row ---------------------------------------------------------------------- 2.3.46 cbf_get_value, cbf_require_value PROTOTYPE #include "cbf.h" int cbf_get_value (cbf_handle handle, const char **value); int cbf_require_value (cbf_handle handle, const char **value, const char *defaultvalue ); DESCRIPTION cbf_get_value sets *value to point to the ASCII value of the item at the current column and row. cbf_require_value sets *value to point to the ASCII value of the item at the current column and row, creating the data item if necessary and initializing it to a copy of defaultvalue. If the value is not ASCII, the function returns CBF_BINARY. The value will be valid as long as the item exists and has not been set to a new value. The value must not be modified by the program in any way. ARGUMENTS handle CBF handle. value Pointer to the destination value pointer. defaultvalue Default value character string. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.47 cbf_set_value 2.3.48 cbf_get_typeofvalue 2.3.49 cbf_set_typeofvalue 2.3.50 cbf_get_integervalue, cbf_require_integervalue 2.3.52 cbf_get_doublevalue, cbf_require_doublevalue 2.3.54 cbf_get_integerarrayparameters, cbf_get_integerarrayparameters_wdims, cbf_get_realarrayparameters, cbf_get_realarrayparameters_wdims 2.3.55 cbf_get_integerarray, cbf_get_realarray 2.3.62 cbf_require_column_value 2.3.63 cbf_require_column_integervalue 2.3.64 cbf_require_column_doublevalue ---------------------------------------------------------------------- 2.3.47 cbf_set_value PROTOTYPE #include "cbf.h" int cbf_set_value (cbf_handle handle, const char *value); DESCRIPTION cbf_set_value sets the item at the current column and row to the ASCII value value. ARGUMENTS handle CBF handle. value ASCII value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.46 cbf_get_value, cbf_require_value 2.3.48 cbf_get_typeofvalue 2.3.49 cbf_set_typeofvalue 2.3.51 cbf_set_integervalue 2.3.53 cbf_set_doublevalue 2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_realarray, cbf_set_realarray_wdims 2.3.62 cbf_require_column_value 2.3.63 cbf_require_column_integervalue 2.3.64 cbf_require_column_doublevalue ---------------------------------------------------------------------- 2.3.48 cbf_get_typeofvalue PROTOTYPE #include "cbf.h" int cbf_get_typeofvalue (cbf_handle handle, const char **typeofvalue); DESCRIPTION cbf_get_value sets *typeofvalue to point an ASCII descriptor of the value of the item at the current column and row. The strings that may be returned are: "null" for a null value indicated by a "." or a "?" "bnry" for a binary value "word" for an unquoted string "dblq" for a double-quoted string "sglq" for a single-quoted string "text" for a semicolon-quoted string (multiline text field) "prns" for a parenthesis-bracketed string (multiline text field) "brcs" for a brace-bracketed string (multiline text field) "bkts" for a square-bracket-bracketed string (multiline text field) "tsqs" for a treble-single-quote quoted string (multiline text field) "tdqs" for a treble-double-quote quoted string (multiline text field) Not all types are valid for all type of CIF files. In partcular the types "prns", "brcs", "bkts" were introduced with DDLm and are not valid in DDL1 or DDL2 CIFS. The types "tsqs" and "tdqs" are not formally part of the CIF syntax. A field for which no value has been set sets *typeofvalue to NULL rather than to the string "null". The typeofvalue must not be modified by the program in any way. ARGUMENTS handle CBF handle. typeofvalue Pointer to the destination type-of-value string pointer. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.46 cbf_get_value, cbf_require_value 2.3.47 cbf_set_value 2.3.49 cbf_set_typeofvalue 2.3.50 cbf_get_integervalue, cbf_require_integervalue 2.3.52 cbf_get_doublevalue, cbf_require_doublevalue 2.3.54 cbf_get_integerarrayparameters, cbf_get_integerarrayparameters_wdims, cbf_get_realarrayparameters, cbf_get_realarrayparameters_wdims 2.3.55 cbf_get_integerarray, cbf_get_realarray 2.3.62 cbf_require_column_value 2.3.63 cbf_require_column_integervalue 2.3.64 cbf_require_column_doublevalue ---------------------------------------------------------------------- 2.3.49 cbf_set_typeofvalue PROTOTYPE #include "cbf.h" int cbf_set_typeofvalue (cbf_handle handle, const char *typeofvalue); DESCRIPTION cbf_set_typeofvalue sets the type of the item at the current column and row to the type specified by the ASCII character string given by typeofvalue. The strings that may be used are: "null" for a null value indicated by a "." or a "?" "bnry" for a binary value "word" for an unquoted string "dblq" for a double-quoted string "sglq" for a single-quoted string "text" for a semicolon-quoted string (multiline text field) "prns" for a parenthesis-bracketed string (multiline text field) "brcs" for a brace-bracketed string (multiline text field) "bkts" for a square-bracket-bracketed string (multiline text field) "tsqs" for a treble-single-quote quoted string (multiline text field) "tdqs" for a treble-double-quote quoted string (multiline text field) Not all types may be used for all values. Not all types are valid for all type of CIF files. In partcular the types "prns", "brcs", "bkts" were introduced with DDLm and are not valid in DDL1 or DDL2 CIFS. The types "tsqs" and "tdqs" are not formally part of the CIF syntax. No changes may be made to the type of binary values. You may not set the type of a string that contains a single quote followed by a blank or a tab or which contains multiple lines to "sglq". You may not set the type of a string that contains a double quote followed by a blank or a tab or which contains multiple lines to "dblq". ARGUMENTS handle CBF handle. typeofvalue ASCII string for desired type of value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.46 cbf_get_value, cbf_require_value 2.3.47 cbf_set_value 2.3.48 cbf_get_typeofvalue 2.3.51 cbf_set_integervalue 2.3.53 cbf_set_doublevalue 2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_realarray, cbf_set_realarray_wdims 2.3.62 cbf_require_column_value 2.3.63 cbf_require_column_integervalue 2.3.64 cbf_require_column_doublevalue ---------------------------------------------------------------------- 2.3.50 cbf_get_integervalue, cbf_require_integervalue PROTOTYPE #include "cbf.h" int cbf_get_integervalue (cbf_handle handle, int *number); int cbf_require_integervalue (cbf_handle handle, int *number, int defaultvalue); DESCRIPTION cbf_get_integervalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal integer. cbf_require_integervalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal integer, setting it to defaultvalue if necessary. If the value is not ASCII, the function returns CBF_BINARY. ARGUMENTS handle CBF handle. number pointer to the number. defaultvalue default number value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.46 cbf_get_value, cbf_require_value 2.3.48 cbf_get_typeofvalue 2.3.51 cbf_set_integervalue 2.3.52 cbf_get_doublevalue, cbf_require_doublevalue 2.3.54 cbf_get_integerarrayparameters, cbf_get_integerarrayparameters_wdims, cbf_get_realarrayparameters, cbf_get_realarrayparameters_wdims 2.3.55 cbf_get_integerarray, cbf_get_realarray 2.3.62 cbf_require_column_value 2.3.63 cbf_require_column_integervalue 2.3.64 cbf_require_column_doublevalue ---------------------------------------------------------------------- 2.3.51 cbf_set_integervalue PROTOTYPE #include "cbf.h" int cbf_set_integervalue (cbf_handle handle, int number); DESCRIPTION cbf_set_integervalue sets the item at the current column and row to the integer value number written as a decimal ASCII string. ARGUMENTS handle CBF handle. number Integer value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.46 cbf_get_value, cbf_require_value 2.3.47 cbf_set_value 2.3.48 cbf_get_typeofvalue 2.3.49 cbf_set_typeofvalue 2.3.50 cbf_get_integervalue, cbf_require_integervalue 2.3.51 cbf_set_integervalue 2.3.53 cbf_set_doublevalue 2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_realarray, cbf_set_realarray_wdims 2.3.62 cbf_require_column_value 2.3.63 cbf_require_column_integervalue 2.3.64 cbf_require_column_doublevalue ---------------------------------------------------------------------- 2.3.52 cbf_get_doublevalue, cbf_require_doublevalue PROTOTYPE #include "cbf.h" int cbf_get_doublevalue (cbf_handle handle, double *number); int cbf_require_doublevalue (cbf_handle handle, double *number, double defaultvalue); DESCRIPTION cbf_get_doublevalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal floating-point number. cbf_require_doublevalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal floating-point number, setting it to defaultvalue if necessary. If the value is not ASCII, the function returns CBF_BINARY. ARGUMENTS handle CBF handle. number Pointer to the destination number. defaultvalue default number value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.46 cbf_get_value, cbf_require_value 2.3.48 cbf_get_typeofvalue 2.3.49 cbf_set_typeofvalue 2.3.50 cbf_get_integervalue, cbf_require_integervalue 2.3.53 cbf_set_doublevalue 2.3.54 cbf_get_integerarrayparameters, cbf_get_integerarrayparameters_wdims, cbf_get_realarrayparameters, cbf_get_realarrayparameters_wdims 2.3.55 cbf_get_integerarray, cbf_get_realarray 2.3.62 cbf_require_column_value 2.3.63 cbf_require_column_integervalue 2.3.64 cbf_require_column_doublevalue ---------------------------------------------------------------------- 2.3.53 cbf_set_doublevalue PROTOTYPE #include "cbf.h" int cbf_set_doublevalue (cbf_handle handle, const char *format, double number); DESCRIPTION cbf_set_doublevalue sets the item at the current column and row to the floating-point value number written as an ASCII string with the format specified by format as appropriate for the printf function. ARGUMENTS handle CBF handle. format Format for the number. number Floating-point value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.46 cbf_get_value, cbf_require_value 2.3.47 cbf_set_value 2.3.48 cbf_get_typeofvalue 2.3.49 cbf_set_typeofvalue 2.3.51 cbf_set_integervalue 2.3.52 cbf_get_doublevalue, cbf_require_doublevalue 2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_realarray, cbf_set_realarray_wdims 2.3.62 cbf_require_column_value 2.3.63 cbf_require_column_integervalue 2.3.64 cbf_require_column_doublevalue ---------------------------------------------------------------------- 2.3.54 cbf_get_integerarrayparameters, cbf_get_integerarrayparameters_wdims, cbf_get_integerarrayparameters_wdims_fs, cbf_get_integerarrayparameters_wdims_sf, cbf_get_realarrayparameters, cbf_get_realarrayparameters_wdims, cbf_get_realarrayparameters_wdims_fs, cbf_get_realarrayparameters_wdims_sf PROTOTYPE #include "cbf.h" int cbf_get_integerarrayparameters (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, int *elsigned, int *elunsigned, size_t *elements, int *minelement, int *maxelement); int cbf_get_integerarrayparameters_wdims (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, int *elsigned, int *elunsigned, size_t *elements, int *minelement, int *maxelement, const char **byteorder, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding); int cbf_get_integerarrayparameters_wdims_fs (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, int *elsigned, int *elunsigned, size_t *elements, int *minelement, int *maxelement, const char **byteorder, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding); int cbf_get_integerarrayparameters_wdims_sf (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, int *elsigned, int *elunsigned, size_t *elements, int *minelement, int *maxelement, const char **byteorder, size_t *dimslow, size_t *dimmid, size_t *dimfast, size_t *padding); int cbf_get_realarrayparameters (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, size_t *elements); int cbf_get_realarrayparameters_wdims (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, size_t *elements, const char **byteorder, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding); int cbf_get_realarrayparameters_wdims_fs (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, size_t *elements, const char **byteorder, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding); int cbf_get_realarrayparameters_wdims_sf (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, size_t *elements, const char **byteorder, size_t *dimslow, size_t *dimmid, size_t *dimfast, size_t *padding); DESCRIPTION cbf_get_integerarrayparameters sets *compression, *binary_id, *elsize, *elsigned, *elunsigned, *elements, *minelement and *maxelement to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_integerarray, if a copy of the array is to be made into another CIF or CBF. cbf_get_realarrayparameters sets *compression, *binary_id, *elsize, *elements to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_realarray, if a copy of the arry is to be made into another CIF or CBF. The variants cbf_get_integerarrayparameters_wdims, cbf_get_integerarrayparameters_wdims_fs, cbf_get_integerarrayparameters_wdims_sf, cbf_get_realarrayparameters_wdims, cbf_get_realarrayparameters_wdims_fs, cbf_get_realarrayparameters_wdims_sf set **byteorder, *dimfast, *dimmid, *dimslow, and *padding as well, providing the additional parameters needed for a subsequent call to cbf_set_integerarray_wdims or cbf_set_realarray_wdims. The value returned in *byteorder is a pointer either to the string "little_endian" or to the string "big_endian". This should be the byte order of the data, not necessarily of the host machine. No attempt should be made to modify this string. At this time only "little_endian" will be returned. The values returned in *dimfast, *dimmid and *dimslow are the sizes of the fastest changing, second fastest changing and third fastest changing dimensions of the array, if specified, or zero, if not specified. The value returned in *padding is the size of the post-data padding, if any and if specified in the data header. The value is given as a count of octets. If the value is not binary, the function returns CBF_ASCII. ARGUMENTS handle CBF handle. compression Compression method used. elsize Size in bytes of each array element. binary_id Pointer to the destination integer binary identifier. elsigned Pointer to an integer. Set to 1 if the elements can be read as signed integers. elunsigned Pointer to an integer. Set to 1 if the elements can be read as unsigned integers. elements Pointer to the destination number of elements. minelement Pointer to the destination smallest element. maxelement Pointer to the destination largest element. byteorder Pointer to the destination byte order. dimfast Pointer to the destination fastest dimension. dimmid Pointer to the destination second fastest dimension. dimslow Pointer to the destination third fastest dimension. padding Pointer to the destination padding size. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.46 cbf_get_value, cbf_require_value 2.3.48 cbf_get_typeofvalue 2.3.49 cbf_set_typeofvalue 2.3.50 cbf_get_integervalue, cbf_require_integervalue 2.3.52 cbf_get_doublevalue, cbf_require_doublevalue 2.3.55 cbf_get_integerarray, cbf_get_realarray 2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_realarray, cbf_set_realarray_wdims 2.3.62 cbf_require_column_value 2.3.63 cbf_require_column_integervalue 2.3.64 cbf_require_column_doublevalue ---------------------------------------------------------------------- 2.3.55 cbf_get_integerarray, cbf_get_realarray PROTOTYPE #include "cbf.h" int cbf_get_integerarray (cbf_handle handle, int *binary_id, void *array, size_t elsize, int elsigned, size_t elements, size_t *elements_read); int cbf_get_realarray (cbf_handle handle, int *binary_id, void *array, size_t elsize, size_t elements, size_t *elements_read); DESCRIPTION cbf_get_integerarray reads the binary value of the item at the current column and row into an integer array. The array consists of elements elements of elsize bytes each, starting at array. The elements are signed if elsigned is non-0 and unsigned otherwise. *binary_id is set to the binary section identifier and *elements_read to the number of elements actually read. cbf_get_realarray reads the binary value of the item at the current column and row into a real array. The array consists of elements elements of elsize bytes each, starting at array. *binary_id is set to the binary section identifier and *elements_read to the number of elements actually read. If any element in the integer binary data cant fit into the destination element, the destination is set the nearest possible value. If the value is not binary, the function returns CBF_ASCII. If the requested number of elements cant be read, the function will read as many as it can and then return CBF_ENDOFDATA. Currently, the destination array must consist of chars, shorts or ints (signed or unsigned). If elsize is not equal to sizeof (char), sizeof (short) or sizeof (int), for cbf_get_integerarray, or sizeof(double) or sizeof(float), for cbf_get_realarray the function returns CBF_ARGUMENT. An additional restriction in the current version of CBFlib is that values too large to fit in an int are not correctly decompressed. As an example, if the machine with 32-bit ints is reading an array containing a value outside the range 0 .. 2^32-1 (unsigned) or -2^31 .. 2^31-1 (signed), the array will not be correctly decompressed. This restriction will be removed in a future release. For cbf_get_realarray, only IEEE format is supported. No conversion to other floating point formats is done at this time. ARGUMENTS handle CBF handle. binary_id Pointer to the destination integer binary identifier. array Pointer to the destination array. elsize Size in bytes of each destination array element. elsigned Set to non-0 if the destination array elements are signed. elements The number of elements to read. elements_read Pointer to the destination number of elements actually read. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.46 cbf_get_value, cbf_require_value 2.3.48 cbf_get_typeofvalue 2.3.49 cbf_set_typeofvalue 2.3.50 cbf_get_integervalue, cbf_require_integervalue 2.3.52 cbf_get_doublevalue, cbf_require_doublevalue 2.3.54 cbf_get_integerarrayparameters, cbf_get_integerarrayparameters_wdims, cbf_get_realarrayparameters, cbf_get_realarrayparameters_wdims 2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_realarray, cbf_set_realarray_wdims 2.3.62 cbf_require_column_value 2.3.63 cbf_require_column_integervalue 2.3.64 cbf_require_column_doublevalue ---------------------------------------------------------------------- 2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, cbf_set_integerarray_wdims_sf, cbf_set_realarray, cbf_set_realarray_wdims, cbf_set_realarray_wdims_fs, cbf_set_realarray_wdims_sf PROTOTYPE #include "cbf.h" int cbf_set_integerarray (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, int elsigned, size_t elements); int cbf_set_integerarray_wdims (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, int elsigned, size_t elements, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); int cbf_set_integerarray_wdims_fs (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, int elsigned, size_t elements, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); int cbf_set_integerarray_wdims_sf (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, int elsigned, size_t elements, const char *byteorder, size_t dimslow, size_t dimmid, size_t dimfast, size_t padding); int cbf_set_realarray (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, size_t elements); int cbf_set_realarray_wdims (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, size_t elements, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); int cbf_set_realarray_wdims_fs (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, size_t elements, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); int cbf_set_realarray_wdims_sf (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, size_t elements, const char *byteorder, size_t dimslow, size_t dimmid, size_t dimfast, size_t padding); DESCRIPTION cbf_set_integerarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. The elements are signed if elsigned is non-0 and unsigned otherwise. binary_id is the binary section identifier. cbf_set_realarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. binary_id is the binary section identifier. The cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, cbf_set_integerarray_wdims_sf, cbf_set_realarray_wdims, cbf_set_realarray_wdims_fs and cbf_set_realarray_wdims_sf variants allow the data header values of byteorder, dimfast, dimmid, dimslow and padding to be set to the data byte order, the fastest, second fastest and third fastest array dimensions and the size in byte of the post data padding to be used. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple "byte_offset" compression. CBF_NONE No compression. NOTE: This scheme is by far the slowest of the four and uses much more disk space. It is intended for routine use with small arrays only. With large arrays (like images) it should be used only for debugging. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned), for cbf_set_integerarray, or IEEE doubles or floats for cbf_set_realarray. If elsize is not equal to sizeof (char), sizeof (short) or sizeof (int), the function returns CBF_ARGUMENT. ARGUMENTS handle CBF handle. compression Compression method to use. binary_id Integer binary identifier. array Pointer to the source array. elsize Size in bytes of each source array element. elsigned Set to non-0 if the source array elements are signed. elements: The number of elements in the array. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.47 cbf_set_value 2.3.48 cbf_get_typeofvalue 2.3.49 cbf_set_typeofvalue 2.3.51 cbf_set_integervalue 2.3.53 cbf_set_doublevalue 2.3.54 cbf_get_integerarrayparameters, cbf_get_integerarrayparameters_wdims, cbf_get_realarrayparameters, cbf_get_realarrayparameters_wdims 2.3.55 cbf_get_integerarray, cbf_get_realarray 2.3.62 cbf_require_column_value 2.3.63 cbf_require_column_integervalue 2.3.64 cbf_require_column_doublevalue ---------------------------------------------------------------------- 2.3.57 cbf_failnez DEFINITION #include "cbf.h" #define cbf_failnez(f) {int err; err = (f); if (err) return err; } DESCRIPTION cbf_failnez is a macro used for error propagation throughout CBFlib. cbf_failnez executes the function f and saves the returned error value. If the error value is non-0, cbf_failnez executes a return with the error value as argument. If CBFDEBUG is defined, then a report of the error is also printed to the standard error stream, stderr, in the form CBFlib error f in "symbol" where f is the decimal value of the error and symbol is the symbolic form. ARGUMENTS f Integer error value. SEE ALSO 2.3.58 cbf_onfailnez ---------------------------------------------------------------------- 2.3.58 cbf_onfailnez DEFINITION #include "cbf.h" #define cbf_onfailnez(f,c) {int err; err = (f); if (err) {{c; }return err; }} DESCRIPTION cbf_onfailnez is a macro used for error propagation throughout CBFlib. cbf_onfailnez executes the function f and saves the returned error value. If the error value is non-0, cbf_failnez executes first the statement c and then a return with the error value as argument. If CBFDEBUG is defined, then a report of the error is also printed to the standard error stream, stderr, in the form CBFlib error f in "symbol" where f is the decimal value of the error and symbol is the symbolic form. ARGUMENTS f integer function to execute. c statement to execute on failure. SEE ALSO * 2.3.57 cbf_failnez ---------------------------------------------------------------------- 2.3.59 cbf_require_datablock PROTOTYPE #include "cbf.h" int cbf_require_datablock (cbf_handle handle, const char *datablockname); DESCRIPTION cbf_require_datablock makes the data block with name datablockname the current data block, if it exists, or creates it if it does not. The comparison is case-insensitive. The current category becomes undefined. ARGUMENTS handle CBF handle. datablockname The name of the data block to find or create. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.21 cbf_rewind_datablock 2.3.25 cbf_next_datablock 2.3.29 cbf_find_datablock 2.3.30 cbf_find_category, cbf_find_saveframe, cbf_find_blockitem 2.3.31 cbf_find_column 2.3.32 cbf_find_row 2.3.42 cbf_datablock_name 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.60 cbf_require_category PROTOTYPE #include "cbf.h" int cbf_require_category (cbf_handle handle, const char *categoryname); DESCRIPTION cbf_rewuire_category makes the category in the current data block with name categoryname the current category, if it exists, or creates the catagory if it does not exist. The comparison is case-insensitive. The current column and row become undefined. ARGUMENTS handle CBF handle. categoryname The name of the category to find. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.22 cbf_rewind_category, cbf_rewind_saveframe, cbf_rewind_blockitem 2.3.26 cbf_next_category, cbf_next_saveframe, cbf_next_blockitem 2.3.29 cbf_find_datablock 2.3.31 cbf_find_column 2.3.32 cbf_find_row 2.3.43 cbf_category_name 2.3.59 cbf_require_datablock 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.61 cbf_require_column PROTOTYPE #include "cbf.h" int cbf_require_column (cbf_handle handle, const char *columnname); DESCRIPTION cbf_require_column makes the columns in the current category with name columnname the current column, if it exists, or creates it if it does not. The comparison is case-insensitive. The current row is not affected. ARGUMENTS handle CBF handle. columnname The name of column to find. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.19 cbf_rewind_column 2.3.27 cbf_next_column 2.3.29 cbf_find_datablock 2.3.30 cbf_find_category, cbf_find_saveframe, cbf_find_blockitem 2.3.32 cbf_find_row 2.3.44 cbf_column_name, cbf_set_column_name 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category ---------------------------------------------------------------------- 2.3.62 cbf_require_column_value PROTOTYPE #include "cbf.h" int cbf_require_column_value (cbf_handle handle, const char *columnname, const char **value, const char *defaultvalue); DESCRIPTION cbf_require_column_doublevalue sets *value to the ASCII item at the current row for the column given with the name given by *columnname, or to the string given by defaultvalue if the item cannot be found. ARGUMENTS handle CBF handle. columnname Name of the column containing the number. value pointer to the location to receive the value. defaultvalue Value to use if the requested column and value cannot be found. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.46 cbf_get_value, cbf_require_value 2.3.47 cbf_set_value 2.3.48 cbf_get_typeofvalue 2.3.49 cbf_set_typeofvalue 2.3.51 cbf_set_integervalue 2.3.52 cbf_get_doublevalue, cbf_require_doublevalue 2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_realarray, cbf_set_realarray_wdims 2.3.63 cbf_require_column_integervalue 2.3.64 cbf_require_column_doublevalue ---------------------------------------------------------------------- 2.3.63 cbf_require_column_integervalue PROTOTYPE #include "cbf.h" int cbf_require_column_integervalue (cbf_handle handle, const char *columnname, int *number, const int defaultvalue); DESCRIPTION cbf_require_column_doublevalue sets *number to the value of the ASCII item at the current row for the column given with the name given by *columnname, with the value interpreted as an integer number, or to the number given by defaultvalue if the item cannot be found. ARGUMENTS handle CBF handle. columnname Name of the column containing the number. number pointer to the location to receive the integer value. defaultvalue Value to use if the requested column and value cannot be found. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.46 cbf_get_value, cbf_require_value 2.3.47 cbf_set_value 2.3.48 cbf_get_typeofvalue 2.3.49 cbf_set_typeofvalue 2.3.51 cbf_set_integervalue 2.3.52 cbf_get_doublevalue, cbf_require_doublevalue 2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_realarray, cbf_set_realarray_wdims 2.3.62 cbf_require_column_value 2.3.64 cbf_require_column_doublevalue ---------------------------------------------------------------------- 2.3.64 cbf_require_column_doublevalue PROTOTYPE #include "cbf.h" int cbf_require_column_doublevalue (cbf_handle handle, const char *columnname, double *number, const double defaultvalue); DESCRIPTION cbf_require_column_doublevalue sets *number to the value of the ASCII item at the current row for the column given with the name given by *columnname, with the value interpreted as a decimal floating-point number, or to the number given by defaultvalue if the item cannot be found. ARGUMENTS handle CBF handle. columnname Name of the column containing the number. number pointer to the location to receive the floating-point value. defaultvalue Value to use if the requested column and value cannot be found. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.46 cbf_get_value, cbf_require_value 2.3.47 cbf_set_value 2.3.48 cbf_get_typeofvalue 2.3.49 cbf_set_typeofvalue 2.3.51 cbf_set_integervalue 2.3.52 cbf_get_doublevalue, cbf_require_doublevalue 2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_realarray, cbf_set_realarray_wdims 2.3.62 cbf_require_column_value 2.3.63 cbf_require_column_integervalue ---------------------------------------------------------------------- 2.3.65 cbf_get_local_integer_byte_order, cbf_get_local_real_byte_order, cbf_get_local_real_format PROTOTYPE #include "cbf.h" int cbf_get_local_integer_byte_order (char ** byte_order); int cbf_get_local_real_byte_order (char ** byte_order); int cbf_get_local_real_format (char ** real_format ); DESCRIPTION cbf_get_local_integer_byte_order returns the byte order of integers on the machine on which the API is being run in the form of a character string returned as the value pointed to by byte_order. cbf_get_local_real_byte_order returns the byte order of reals on the machine on which the API is being run in the form of a character string returned as the value pointed to by byte_order. cbf_get_local_real_format returns the format of floats on the machine on which the API is being run in the form of a character string returned as the value pointed to by real_format. The strings returned must not be modified in any way. The values returned in byte_order may be the strings "little_endian" or "big-endian". The values returned in real_format may be the strings "ieee 754-1985" or "other". Additional values may be returned by future versions of the API. ARGUMENTS byte_order pointer to the returned string real_format pointer to the returned string RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.3.66 cbf_get_dictionary, cbf_set_dictionary, cbf_require_dictionary PROTOTYPE #include "cbf.h" int cbf_get_dictionary (cbf_handle handle, cbf_handle * dictionary); int cbf_set_dictionary (cbf_handle handle, cbf_handle dictionary_in); int cbf_require_dictionary (cbf_handle handle, cbf_handle * dictionary) DESCRIPTION cbf_get_dictionary sets *dictionary to the handle of a CBF which has been associated with the CBF handle by cbf_set_dictionary. cbf_set_dictionary associates the CBF handle dictionary_in with handle as its dictionary. cbf_require_dictionary sets *dictionary to the handle of a CBF which has been associated with the CBF handle by cbf_set_dictionary or creates a new empty CBF and associates it with handle, returning the new handle in *dictionary. ARGUMENTS handle CBF handle. dictionary Pointer to CBF handle of dictionary. dictionary_in CBF handle of dcitionary. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.3.67 cbf_convert_dictionary PROTOTYPE #include "cbf.h" int cbf_convert_dictionary (cbf_handle handle, cbf_handle dictionary ) DESCRIPTION cbf_convert_dictionary converts dictionary as a DDL1 or DDL2 dictionary to a CBF dictionary of category and item properties for handle, creating a new dictionary if none exists or layering the definitions in dictionary onto the existing dictionary of handle if one exists. If a CBF is read into handle after calling cbf_convert_dictionary, then the dictionary will be used for validation of the CBF as it is read. ARGUMENTS handle CBF handle. dictionary CBF handle of dictionary. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.3.68 cbf_find_tag, cbf_find_local_tag PROTOTYPE #include "cbf.h" int cbf_find_tag (cbf_handle handle, const char *tag) int cbf_find_local_tag (cbf_handle handle, const char *tag) DESCRIPTION cbf_find_tag searches all of the CBF handle for the CIF tag given by the string tag and makes it the current tag. The search does not include the dictionary, but does include save frames as well as categories. The string tag is the complete tag in either DDL1 or DDL2 format, starting with the leading underscore, not just a category or column. ARGUMENTS handle CBF handle. tag CIF tag. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.3.69 cbf_find_category_root, cbf_set_category_root, cbf_require_category_root PROTOTYPE #include "cbf.h" int cbf_find_category_root (cbf_handle handle, const char* categoryname, const char** categoryroot); int cbf_set_category_root (cbf_handle handle, const char* categoryname_in, const char*categoryroot); int cbf_require_category_root (cbf_handle handle, const char* categoryname, const char** categoryroot); DESCRIPTION cbf_find_category_root sets *categoryroot to the root category of which categoryname is an alias. cbf_set_category_root sets categoryname_in as an alias of categoryroot in the dictionary associated with handle, creating the dictionary if necessary. cbf_require_category_root sets *categoryroot to the root category of which categoryname is an alias, if there is one, or to the value of categoryname, if categoryname is not an alias. A returned categoryroot string must not be modified in any way. ARGUMENTS handle CBF handle. categoryname category name which may be an alias. categoryroot pointer to a returned category root name. categoryroot_in input category root name. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.3.70 cbf_find_tag_root, cbf_set_tag_root, cbf_require_tag_root PROTOTYPE #include "cbf.h" int cbf_find_tag_root (cbf_handle handle, const char* tagname, const char** tagroot); int cbf_set_tag_root (cbf_handle handle, const char* tagname, const char*tagroot_in); int cbf_require_tag_root (cbf_handle handle, const char* tagname, const char** tagroot); DESCRIPTION cbf_find_tag_root sets *tagroot to the root tag of which tagname is an alias. cbf_set_tag_root sets tagname as an alias of tagroot_in in the dictionary associated with handle, creating the dictionary if necessary. cbf_require_tag_root sets *tagroot to the root tag of which tagname is an alias, if there is one, or to the value of tagname, if tagname is not an alias. A returned tagroot string must not be modified in any way. ARGUMENTS handle CBF handle. tagname tag name which may be an alias. tagroot pointer to a returned tag root name. tagroot_in input tag root name. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.3.71 cbf_find_tag_category, cbf_set_tag_category PROTOTYPE #include "cbf.h" int cbf_find_tag_category (cbf_handle handle, const char* tagname, const char** categoryname); int cbf_set_tag_category (cbf_handle handle, const char* tagname, const char* categoryname_in); DESCRIPTION cbf_find_tag_category sets categoryname to the category associated with tagname in the dictionary associated with handle. cbf_set_tag_category upddates the dictionary associated with handle to indicated that tagname is in category categoryname_in. ARGUMENTS handle CBF handle. tagname tag name. categoryname pointer to a returned category name. categoryname_in input category name. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ---------------------------------------------------------------------- 2.4 High-level function prototypes 2.4.1 cbf_read_template PROTOTYPE #include "cbf_simple.h" int cbf_read_template (cbf_handle handle, FILE *file); DESCRIPTION cbf_read_template reads the CBF or CIF file file into the CBF object specified by handle and selects the first datablock as the current datablock. ARGUMENTS handle Pointer to a CBF handle. file Pointer to a file descriptor. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.2 cbf_get_diffrn_id, cbf_require_diffrn_id PROTOTYPE #include "cbf_simple.h" int cbf_get_diffrn_id (cbf_handle handle, const char **diffrn_id); int cbf_require_diffrn_id (cbf_handle handle, const char **diffrn_id, const char *default_id) DESCRIPTION cbf_get_diffrn_id sets *diffrn_id to point to the ASCII value of the "diffrn.id" entry. cbf_require_diffrn_id also sets *diffrn_id to point to the ASCII value of the "diffrn.id" entry, but, if the "diffrn.id" entry does not exist, it sets the value in the CBF and in*diffrn_id to the character string given by default_id, creating the category and column is necessary. The diffrn_id will be valid as long as the item exists and has not been set to a new value. The diffrn_id must not be modified by the program in any way. ARGUMENTS handle CBF handle. diffrn_id Pointer to the destination value pointer. default_id Character string default value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.3 cbf_set_diffrn_id PROTOTYPE #include "cbf_simple.h" int cbf_set_diffrn_id (cbf_handle handle, const char *diffrn_id); DESCRIPTION cbf_set_diffrn_id sets the "diffrn.id" entry of the current datablock to the ASCII value diffrn_id. This function also changes corresponding "diffrn_id" entries in the "diffrn_source", "diffrn_radiation", "diffrn_detector" and "diffrn_measurement" categories. ARGUMENTS handle CBF handle. diffrn_id ASCII value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.4 cbf_get_crystal_id PROTOTYPE #include "cbf_simple.h" int cbf_get_crystal_id (cbf_handle handle, const char **crystal_id); DESCRIPTION cbf_get_crystal_id sets *crystal_id to point to the ASCII value of the "diffrn.crystal_id" entry. If the value is not ASCII, the function returns CBF_BINARY. The value will be valid as long as the item exists and has not been set to a new value. The value must not be modified by the program in any way. ARGUMENTS handle CBF handle. crystal_id Pointer to the destination value pointer. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.5 cbf_set_crystal_id PROTOTYPE #include "cbf_simple.h" int cbf_set_crystal_id (cbf_handle handle, const char *crystal_id); DESCRIPTION cbf_set_crystal_id sets the "diffrn.crystal_id" entry to the ASCII value crystal_id. ARGUMENTS handle CBF handle. crystal_id ASCII value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.6 cbf_get_wavelength PROTOTYPE #include "cbf_simple.h" int cbf_get_wavelength (cbf_handle handle, double *wavelength); DESCRIPTION cbf_get_wavelength sets *wavelength to the current wavelength in AA. ARGUMENTS handle CBF handle. wavelength Pointer to the destination. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.7 cbf_set_wavelength PROTOTYPE #include "cbf_simple.h" int cbf_set_wavelength (cbf_handle handle, double wavelength); DESCRIPTION cbf_set_wavelength sets the current wavelength in AA to wavelength. ARGUMENTS handle CBF handle. wavelength Wavelength in AA. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.8 cbf_get_polarization PROTOTYPE #include "cbf_simple.h" int cbf_get_polarization (cbf_handle handle, double *polarizn_source_ratio, double *polarizn_source_norm); DESCRIPTION cbf_get_polarization sets *polarizn_source_ratio and *polarizn_source_norm to the corresponding source polarization parameters. Either destination pointer may be NULL. ARGUMENTS handle CBF handle. polarizn_source_ratio Pointer to the destination polarizn_source_ratio. polarizn_source_norm Pointer to the destination polarizn_source_norm. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.9 cbf_set_polarization PROTOTYPE #include "cbf_simple.h" int cbf_set_polarization (cbf_handle handle, double polarizn_source_ratio, double polarizn_source_norm); DESCRIPTION cbf_set_polarization sets the source polarization to the values specified by polarizn_source_ratio and polarizn_source_norm. ARGUMENTS handle CBF handle. polarizn_source_ratio New value of polarizn_source_ratio. polarizn_source_norm New value of polarizn_source_norm. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.10 cbf_get_divergence PROTOTYPE #include "cbf_simple.h" int cbf_get_divergence (cbf_handle handle, double *div_x_source, double *div_y_source, double *div_x_y_source); DESCRIPTION cbf_get_divergence sets *div_x_source, *div_y_source and *div_x_y_source to the corresponding source divergence parameters. Any of the destination pointers may be NULL. ARGUMENTS handle CBF handle. div_x_source Pointer to the destination div_x_source. div_y_source Pointer to the destination div_y_source. div_x_y_source Pointer to the destination div_x_y_source. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.11 cbf_ set_divergence PROTOTYPE #include "cbf_simple.h" int cbf_set_divergence (cbf_handle handle, double div_x_source, double div_y_source, double div_x_y_source); DESCRIPTION cbf_set_divergence sets the source divergence parameters to the values specified by div_x_source, div_y_source and div_x_y_source. ARGUMENTS handle CBF handle. div_x_source New value of div_x_source. div_y_source New value of div_y_source. div_x_y_source New value of div_x_y_source. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.12 cbf_count_elements PROTOTYPE #include "cbf_simple.h" int cbf_count_elements (cbf_handle handle, unsigned int *elements); DESCRIPTION cbf_count_elements sets *elements to the number of detector elements. ARGUMENTS handle CBF handle. elements Pointer to the destination count. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.13 cbf_get_element_id PROTOTYPE #include "cbf_simple.h" int cbf_get_element_id (cbf_handle handle, unsigned int element_number, const char **element_id); DESCRIPTION cbf_get_element_id sets *element_id to point to the ASCII value of the element_number'th "diffrn_data_frame.detector_element_id" entry, counting from 0. If the detector element does not exist, the function returns CBF_NOTFOUND. The element_id will be valid as long as the item exists and has not been set to a new value. The element_id must not be modified by the program in any way. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category. element_id Pointer to the destination. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.14 cbf_get_gain PROTOTYPE #include "cbf_simple.h" int cbf_get_gain (cbf_handle handle, unsigned int element_number, double *gain, double *gain_esd); DESCRIPTION cbf_get_gain sets *gain and *gain_esd to the corresponding gain parameters for element number element_number. Either of the destination pointers may be NULL. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category. gain Pointer to the destination gain. gain_esd Pointer to the destination gain_esd. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.15 cbf_ set_gain PROTOTYPE #include "cbf_simple.h" int cbf_set_gain (cbf_handle handle, unsigned int element_number, double gain, double gain_esd); DESCRIPTION cbf_set_gain sets the gain of element number element_number to the values specified by gain and gain_esd. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category. gain New gain value. gain_esd New gain_esd value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.16 cbf_get_overload PROTOTYPE #include "cbf_simple.h" int cbf_get_overload (cbf_handle handle, unsigned int element_number, double *overload); DESCRIPTION cbf_get_overload sets *overload to the overload value for element number element_number. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category. overload Pointer to the destination overload. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.17 cbf_ set_overload PROTOTYPE #include "cbf_simple.h" int cbf_set_overload (cbf_handle handle, unsigned int element_number, double overload); DESCRIPTION cbf_set_overload sets the overload value of element number element_number to overload. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category. overload New overload value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.18 cbf_get_integration_time PROTOTYPE #include "cbf_simple.h" int cbf_get_integration_time (cbf_handle handle, unsigned int reserved, double *time); DESCRIPTION cbf_get_integration_time sets *time to the integration time in seconds. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. time Pointer to the destination time. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.19 cbf_set_integration_time PROTOTYPE #include "cbf_simple.h" int cbf_set_integration_time (cbf_handle handle, unsigned int reserved, double time); DESCRIPTION cbf_set_integration_time sets the integration time in seconds to the value specified by time. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. time Integration time in seconds. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.20 cbf_get_timestamp PROTOTYPE #include "cbf_simple.h" int cbf_get_timestamp (cbf_handle handle, unsigned int reserved, double *time, int *timezone); DESCRIPTION cbf_get_timestamp sets *time to the collection timestamp in seconds since January 1 1970. *timezone is set to timezone difference from UTC in minutes. The parameter reserved is presently unused and should be set to 0. Either of the destination pointers may be NULL. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. time Pointer to the destination collection timestamp. timezone Pointer to the destination timezone difference. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.21 cbf_set_timestamp PROTOTYPE #include "cbf_simple.h" int cbf_set_timestamp (cbf_handle handle, unsigned int reserved, double time, int timezone, double precision); DESCRIPTION cbf_set_timestamp sets the collection timestamp in seconds since January 1 1970 to the value specified by time. The timezone difference from UTC in minutes is set to timezone. If no timezone is desired, timezone should be CBF_NOTIM EZONE. The parameter reserved is presently unused and should be set to 0. The precision of the new timestamp is specified by the value precision in seconds. If precision is 0, the saved timestamp is assumed accurate to 1 second. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. time Timestamp in seconds since January 1 1970. timezone Timezone difference from UTC in minutes or CBF_NOTIMEZONE. precision Timestamp precision in seconds. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.22 cbf_get_datestamp PROTOTYPE #include "cbf_simple.h" int cbf_get_datestamp (cbf_handle handle, unsigned int reserved, int *year, int *month, int *day, int *hour, int *minute, double *second, int *timezone); DESCRIPTION cbf_get_datestamp sets *year, *month, *day, *hour, *minute and *second to the corresponding values of the collection timestamp. *timezone is set to timezone difference from UTC in minutes. The parameter < i>reserved is presently unused and should be set to 0. Any of the destination pointers may be NULL. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. year Pointer to the destination timestamp year. month Pointer to the destination timestamp month (1-12). day Pointer to the destination timestamp day (1-31). hour Pointer to the destination timestamp hour (0-23). minute Pointer to the destination timestamp minute (0-59). second Pointer to the destination timestamp second (0-60.0). timezone Pointer to the destination timezone difference from UTC in minutes. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.23 cbf_set_datestamp PROTOTYPE #include "cbf_simple.h" int cbf_set_datestamp (cbf_handle handle, unsigned int reserved, int year, int month, int day, int hour, int minute, double second, int timezone, double precision); DESCRIPTION cbf_set_datestamp sets the collection timestamp in seconds since January 1 1970 to the value specified by time. The timezone difference from UTC in minutes is set to timezone. If no timezone is desired, timezone should be CBF_NOTIM EZONE. The parameter reserved is presently unused and should be set to 0. The precision of the new timestamp is specified by the value precision in seconds. If precision is 0, the saved timestamp is assumed accurate to 1 second. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. time Timestamp in seconds since January 1 1970. timezone Timezone difference from UTC in minutes or CBF_NOTIMEZONE. precision Timestamp precision in seconds. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.24 cbf_set_current_timestamp PROTOTYPE #include "cbf_simple.h" int cbf_set_current_timestamp (cbf_handle handle, unsigned int reserved, int timezone); DESCRIPTION cbf_set_current_timestamp sets the collection timestamp to the current time. The timezone difference from UTC in minutes is set to timezone. If no timezone is desired, timezone should be CBF_NOTIMEZONE. If no timezone is used, the timest amp will be UTC. The parameter reserved is presently unused and should be set to 0. The new timestamp will have a precision of 1 second. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. timezone Timezone difference from UTC in minutes or CBF_NOTIMEZONE. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.25 cbf_get_image_size, cbf_get_image_size_fs, cbf_get_image_size_sf, cbf_get_3d_image_size, cbf_get_3d_image_size_fs, cbf_get_3d_image_size_sf PROTOTYPE #include "cbf_simple.h" int cbf_get_image_size (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimslow, size_t *ndimfast); int cbf_get_image_size_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimfast, size_t *ndimslow); int cbf_get_image_size_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimslow, size_t *ndimfast); int cbf_get_3d_image_size (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimslow, size_t *ndimmid, size_t *ndimfast); int cbf_get_3d_image_size_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimfast, size_t *ndimmid, size_t *ndimslow); int cbf_get_3d_image_size_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimslow, size_t *ndimmid, size_t *ndimfast); DESCRIPTION cbf_get_image_size, cbf_get_image_size_fs and cbf_get_image_size_sf set *ndimslow and *ndimfast to the slow and fast dimensions of the image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimfast will be set to 1. If the array is 3-dimensional an error code will be returned. cbf_get_3d_image_size, cbf_get_3d_image_size_fs and cbf_get_3d_image_size_sf set *ndimslow, *ndimmid and *ndimfast to the slowest, next fastest and fastest dimensions, respectively, of the 3D image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimmid and *ndimfast will be set to 1. If the array is 2-dimensional *ndimslow and *ndimmid will be set as for a call to cbf_get_image_size and *ndimfast will be set to 1. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order Note that the ordering of dimensions is specified by values of the tag _array_structure_list.precedence with a precedence of 1 for the fastest dimension, 2 for the next slower, etc., which is opposite to the ordering of the dimension arguments for these functions, except for the ones with the _fs suffix.. Any of the destination pointers may be NULL. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category. ndimslow Pointer to the destination slowest dimension. ndimmid Pointer to the destination next faster dimension. ndimfast Pointer to the destination fastest dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.26 cbf_get_image, cbf_get_image_fs, cbf_get_image_sf, cbf_get_real_image, cbf_get_real_image_fs, cbf_get_real_image_sf, cbf_get_3d_image, cbf_get_3d_image_fs, cbf_get_3d_image_sf, cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf PROTOTYPE #include "cbf_simple.h" int cbf_get_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast); int cbf_get_image_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimfast, size_t ndimslow); int cbf_get_image_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast); int cbf_get_real_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimslow, size_t ndimfast); int cbf_get_real_image_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimfast, size_t ndimslow); int cbf_get_real_image_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimslow, size_t ndimfast); int cbf_get_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); int cbf_get_3d_image_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimfast, size_t ndimmid, size_t ndimslow); int cbf_get_3d_image_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); int cbf_get_real_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); int cbf_get_real_3d_image_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimfast, size_t ndimmid, size_t ndimslow); int cbf_get_real_3d_image_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); DESCRIPTION cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image array for element number element_number into an array. The array consists of ndimslow *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and cbf_get_real_image_sf read the image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. cbf_get_3d_image, cbf_get_3d_image_fs and cbf_get_3d_image_sf read the 3D image array for element number element_number into an array. The array consists of ndimslow *ndimmid *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order The structure of the array as a 1-, 2- or 3-dimensional array should agree with the structure of the array given in the ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1 both in the call and in the imgCIF data being processed. If the array is 2-dimensional and a 3D call is used, ndimslow and ndimmid should be the array dimensions and ndimfast should be set to 1 both in the call and in the imgCIF data being processed. If any element in the binary data canOt fit into the destination element, the destination is set the nearest possible value. If the value is not binary, the function returns CBF_ASCII. If the requested number of elements canOt be read, the function will read as many as it can and then return CBF_ENDOFDATA. Currently, the destination array must consist of chars, shorts or ints (signed or unsigned) for cbf_get_image, or IEEE doubles or floats for cbf_get_real_image. If elsize is not equal to sizeof (char), sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category. array Pointer to the destination array. elsize Size in bytes of each destination array element. elsigned Set to non-0 if the destination array elements are signed. ndimslow Slowest array dimension. ndimmid Next faster array dimension. ndimfast Fastest array dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.27 cbf_set_image, cbf_set_image_fs, cbf_set_image_sf, cbf_set_real_image, cbf_set_real_image_fs, cbf_set_real_image_sf, cbf_set_3d_image, cbf_set_3d_image, cbf_set_3d_image, cbf_set_real_3d_image, cbf_set_real_3d_image_fs, cbf_set_real_3d_image_sf PROTOTYPE #include "cbf_simple.h" int cbf_set_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast); int cbf_set_image_fs(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimfast, size_t ndimslow); int cbf_set_image_sf(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast); int cbf_set_real_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimslow, size_t ndimfast); int cbf_set_real_image_fs(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimfast, size_t ndimslow); int cbf_set_real_image_sf(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimslow, size_t ndimfast); int cbf_set_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); int cbf_set_3d_image_fs(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimfast, size_t ndimmid, size_t ndimslow); int cbf_set_3d_image_sf(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); int cbf_set_real_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); int cbf_set_real_3d_image_fs(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimfast, size_t ndimmid, size_t ndimslow); int cbf_set_real_3d_image_sf(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); DESCRIPTION cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-zero and unsigned otherwise. cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow IEEE double or float elements of elsize bytes each, starting at array. cbf_set_3d_image, cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_set_real_3d_image, cbf_set_real_3d_image_fs and cbf_set_real_3d_image_sf writes the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow IEEE double or float elements of elsize bytes each, starting at array. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the array is 2-dimensional and the 3D calls are used, ndimslow and ndimmid should be used for the array dimensions and ndimfast should be set to 1. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple "byte_offset" compression. CBF_NONE No compression. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned)for cbf_set_image, or IEEE doubles or floats for cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category. compression Compression type. array Pointer to the image array. elsize Size in bytes of each image array element. elsigned Set to non-0 if the image array elements are signed. ndimslow Slowest array dimension. ndimmid Second slowest array dimension. ndimfast Fastest array dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.28 cbf_get_axis_setting PROTOTYPE #include "cbf_simple.h" int cbf_get_axis_setting (cbf_handle handle, unsigned int reserved, const char *axis_id, double *start, double *increment); DESCRIPTION cbf_get_axis_setting sets *start and *increment to the corresponding values of the axis axis_id. Either of the destination pointers may be NULL. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. axis_id Axis id. start Pointer to the destination start value. increment Pointer to the destination increment value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.29 cbf_set_axis_setting PROTOTYPE #include "cbf_simple.h" int cbf_set_axis_setting (cbf_handle handle, unsigned int reserved, const char *axis_id, double start, double increment); DESCRIPTION cbf_set_axis_setting sets the starting and increment values of the axis axis_id to start and increment. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. axis_id Axis id. start Start value. increment Increment value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.30 cbf_construct_goniometer PROTOTYPE #include "cbf_simple.h" int cbf_construct_goniometer (cbf_handle handle, cbf_goniometer *goniometer); DESCRIPTION cbf_construct_goniometer constructs a goniometer object using the description in the CBF object handle and initialises the goniometer handle *goniometer. ARGUMENTS handle CBF handle. goniometer Pointer to the destination goniometer handle. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.31 cbf_free_goniometer PROTOTYPE #include "cbf_simple.h" int cbf_free_goniometer (cbf_goniometer goniometer); DESCRIPTION cbf_free_goniometer destroys the goniometer object specified by goniometer and frees all associated memory. ARGUMENTS goniometer Goniometer handle to free. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.32 cbf_get_rotation_axis PROTOTYPE #include "cbf_simple.h" int cbf_get_rotation_axis (cbf_goniometer goniometer, unsigned int reserved, double *vector1, double *vector2, double *vector3); DESCRIPTION cbf_get_rotation_axis sets *vector1, *vector2, and *vector3 to the 3 components of the goniometer rotation axis used for the exposure. Any of the destination pointers may be NULL. The parameter reserved is presently unused and should be set to 0. ARGUMENTS goniometer Goniometer handle. reserved Unused. Any value other than 0 is invalid. vector1 Pointer to the destination x component of the rotation axis. vector2 Pointer to the destination y component of the rotation axis. vector3 Pointer to the destination z component of the rotation axis. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.33 cbf_get_rotation_range PROTOTYPE #include "cbf_simple.h" int cbf_get_rotation_range (cbf_goniometer goniometer, unsigned int reserved, double *start, double *increment); DESCRIPTION cbf_get_rotation_range sets *start and *increment to the corresponding values of the goniometer rotation axis used for the exposure. Either of the destination pointers may be NULL. The parameter reserved is presently unused and should be set to 0. ARGUMENTS goniometer Goniometer handle. reserved Unused. Any value other than 0 is invalid. start Pointer to the destination start value. increment Pointer to the destination increment value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.34 cbf_rotate_vector PROTOTYPE #include "cbf_simple.h" int cbf_rotate_vector (cbf_goniometer goniometer, unsigned int reserved, double ratio, double initial1, double initial2, double initial3, double *final1, double *final2, double *final3); DESCRIPTION cbf_rotate_vector sets *final1, *final2, and *final3 to the 3 components of the of the vector (initial1, initial2, initial3) after reorientation by applying the goniometer rotations. The value ratio specif ies the goniometer setting and varies from 0.0 at the beginning of the exposure to 1.0 at the end, irrespective of the actual rotation range. Any of the destination pointers may be NULL. The parameter reserved is presently unused and should be set to 0. ARGUMENTS goniometer Goniometer handle. reserved Unused. Any value other than 0 is invalid. ratio Goniometer setting. 0 = beginning of exposure, 1 = end. initial1 x component of the initial vector. initial2 y component of the initial vector. initial3 z component of the initial vector. vector1 Pointer to the destination x component of the final vector. vector2 Pointer to the destination y component of the final vector. vector3 Pointer to the destination z component of the final vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.35 cbf_get_reciprocal PROTOTYPE #include "cbf_simple.h" int cbf_get_reciprocal (cbf_goniometer goniometer, unsigned int reserved, double ratio, double wavelength, double real1, double real2, double real3, double *reciprocal1, double *reciprocal2, double *reciprocal3); DESCRIPTION cbf_get_reciprocal sets *reciprocal1, * reciprocal2, and * reciprocal3 to the 3 components of the of the reciprocal-space vector corresponding to the real-space vector (real1, real2, real3). The reciprocal-space vector is oriented to correspond to the goniometer setting with all axes at 0. The value wavelength is the wavlength in AA and the value ratio specifies the current goniometer setting and varies from 0.0 at the beginning of the exposur e to 1.0 at the end, irrespective of the actual rotation range. Any of the destination pointers may be NULL. The parameter reserved is presently unused and should be set to 0. ARGUMENTS goniometer Goniometer handle. reserved Unused. Any value other than 0 is invalid. ratio Goniometer setting. 0 = beginning of exposure, 1 = end. wavelength Wavelength in AA. real1 x component of the real-space vector. real2 y component of the real-space vector. real3 z component of the real-space vector. reciprocal1 Pointer to the destination x component of the reciprocal-space vector. reciprocal2 Pointer to the destination y component of the reciprocal-space vector. reciprocal3 Pointer to the destination z component of the reciprocal-space vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.36 cbf_construct_detector, cbf_construct_reference_detector, cbf_require_reference_detector PROTOTYPE #include "cbf_simple.h" int cbf_construct_detector (cbf_handle handle, cbf_detector *detector, unsigned int element_number); int cbf_construct_reference_detector (cbf_handle handle, cbf_detector *detector, unsigned int element_number); int cbf_require_reference_detector (cbf_handle handle, cbf_detector *detector, unsigned int element_number); DESCRIPTION cbf_construct_detector constructs a detector object for detector element number element_number using the description in the CBF object handle and initialises the detector handle *detector. cbf_construct_reference_detector constructs a detector object for detector element number element_number using the description in the CBF object handle and initialises the detector handle *detector using the reference settings of the axes. cbf_require_reference_detector is similar, but try to force the creations of missing intermediate categories needed to construct a detector object. ARGUMENTS handle CBF handle. detector Pointer to the destination detector handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.37 cbf_free_detector PROTOTYPE #include "cbf_simple.h" int cbf_free_detector (cbf_detector detector); DESCRIPTION cbf_free_detector destroys the detector object specified by detector and frees all associated memory. ARGUMENTS detector Detector handle to free. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.38 cbf_get_beam_center, cbf_get_beam_center_fs, cbf_get_beam_center_sf, cbf_set_beam_center, cbf_set_beam_center_fs, cbf_set_beam_center_sf, set_reference_beam_center, set_reference_beam_center_fs, set_reference_beam_center_fs PROTOTYPE #include "cbf_simple.h" int cbf_get_beam_center (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast); int cbf_get_beam_center_fs (cbf_detector detector, double *indexfast, double *indexslow, double *centerfast, double *centerslow); int cbf_get_beam_center_sf (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast); int cbf_set_beam_center (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast); int cbf_set_beam_center_fs (cbf_detector detector, double *indexfast, double *indexslow, double *centerfast, double *centerslow); int cbf_set_beam_center_sf (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast); int cbf_set_reference_beam_center (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast); int cbf_set_reference_beam_center_fs (cbf_detector detector, double *indexfast, double *indexslow, double *centerfast, double *centerslow); int cbf_set_reference_beam_center_sf (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast); DESCRIPTION cbf_get_beam_center sets *centerfast and *centerslow to the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector and *indexfast and *indexslow to the corresponding indices. cbf_set_beam_center sets the offsets in the axis category for the detector element axis with precedence 1 to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given *indexfast and *indexslow. cbf_set_reference_beam_center sets the displacments in the array_structure_list_axis category to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given by *indexfast and *indexslow. In order to achieve consistent results, a reference detector should be used for detector to have all axes at their reference settings. Note that the precedence 1 axis is the fastest axis, so that *centerfast and *indexfast are the fast axis components of the center and *centerslow and *indexslow are the slow axis components of the center. The _fs calls give the displacments in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the displacements in slow-to-fast order Any of the destination pointers may be NULL for getting the beam center. For setting the beam axis, either the indices of the center must not be NULL. The indices are non-negative for beam centers within the detector surface, but the center for an axis with a negative increment will be negative for a beam center within the detector surface. For cbf_set_beam_center if the diffrn_data_frame category exists with a row for the corresponding element id, the values will be set for _diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in millimetres and the value of _diffrn_data_frame.center_units will be set to 'mm'. For cbf_set_reference_beam_center if the diffrn_detector_element category exists with a row for the corresponding element id, the values will be set for _diffrn_detector_element.reference_center_fast and _diffrn_detector_element.reference_center_slow in millimetres and the value of _diffrn_detector_element.reference_units will be set to 'mm'. ARGUMENTS detector Detector handle. indexfast Pointer to the destination fast index. indexslow Pointer to the destination slow index. centerfast Pointer to the destination displacement along the fast axis. centerslow Pointer to the destination displacement along the slow axis. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.39 cbf_get_detector_distance PROTOTYPE #include "cbf_simple.h" int cbf_get_detector_distance (cbf_detector detector, double *distance); DESCRIPTION cbf_get_detector_distance sets *distance to the nearest distance from the sample position to the detector plane. ARGUMENTS detector Detector handle. distance Pointer to the destination distance. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.40 cbf_get_detector_normal PROTOTYPE #include "cbf_simple.h" int cbf_get_detector_normal (cbf_detector detector, double *normal1, double *normal2, double *normal3); DESCRIPTION cbf_get_detector_normal sets *normal1, *normal2, and *normal3 to the 3 components of the of the normal vector to the detector plane. The vector is normalized. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. normal1 Pointer to the destination x component of the normal vector. normal2 Pointer to the destination y component of the normal vector. normal3 Pointer to the destination z component of the normal vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.41 cbf_get_detector_axis_slow, cbf_get_detector_axis_slow, cbf_get_detector_axes, cbf_get_detector_axes_fs, cbf_get_detector_axes_sf PROTOTYPE #include "cbf_simple.h" int cbf_get_detector_axis_slow (cbf_detector detector, double *slowaxis1, double *slowaxis2, double *slowaxis3); int cbf_get_detector_axis_fast (cbf_detector detector, double *fastaxis1, double *fastaxis2, double *fastaxis3); int cbf_get_detector_axes (cbf_detector detector, double *slowaxis1, double *slowaxis2, double *slowaxis3, double *fastaxis1, double *fastaxis2, double *fastaxis3); int cbf_get_detector_axes_fs (cbf_detector detector, double *fastaxis1, double *fastaxis2, double *fastaxis3, double *slowaxis1, double *slowaxis2, double *slowaxis3); int cbf_get_detector_axes_sf (cbf_detector detector, double *slowaxis1, double *slowaxis2, double *slowaxis3, double *fastaxis1, double *fastaxis2, double *fastaxis3); DESCRIPTION cbf_get_detector_axis_slow sets *slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the slow axis of the specified detector at the current settings of all axes. cbf_get_detector_axis_slow sets *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 components of the fast axis of the specified detector at the current settings of all axes. cbf_get_detector_axes, cbf_get_detector_axes_fs and int cbf_get_detector_axes_sf set *slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the slow axis and *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 components of the fast axis of the specified detector at the current settings of all axes. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. slowaxis1 Pointer to the destination x component of the slow axis vector. slowaxis2 Pointer to the destination y component of the slow axis vector. slowaxis3 Pointer to the destination z component of the slow axis vector. fastaxis1 Pointer to the destination x component of the fast axis vector. fastaxis2 Pointer to the destination y component of the fast axis vector. fastaxis3 Pointer to the destination z component of the fast axis vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.42 cbf_get_pixel_coordinates, cbf_get_pixel_coordinates_fs, cbf_get_pixel_coordinates_sf PROTOTYPE #include "cbf_simple.h" int cbf_get_pixel_coordinates (cbf_detector detector, double indexslow, double indexfast, double *coordinate1, double *coordinate2, double *coordinate3); int cbf_get_pixel_coordinates_fs (cbf_detector detector, double indexfast, double indexslow, double *coordinate1, double *coordinate2, double *coordinate3); int cbf_get_pixel_coordinates_sf (cbf_detector detector, double indexslow, double indexfast, double *coordinate1, double *coordinate2, double *coordinate3); DESCRIPTION cbf_get_pixel_coordinates, cbf_get_pixel_coordinates_fs and cbf_get_pixel_coordinates_sf ses *coordinate1, *coordinate2, and *coordinate3 to the vector position of pixel (indexfast, indexslow) on the detector surface. If indexslow and indexfast are integers then the coordinates correspond to the center of a pixel. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. indexslow Slow index. indexfast Fast index. coordinate1 Pointer to the destination x component. coordinate2 Pointer to the destination y component. coordinate3 Pointer to the destination z component. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.43 cbf_get_pixel_normal, cbf_get_pixel_normal_fs, cbf_get_pixel_normal_sf PROTOTYPE #include "cbf_simple.h" int cbf_get_pixel_normal (cbf_detector detector, double indexslow, double indexfast, double *normal1, double *normal2, double *normal3); int cbf_get_pixel_normal_fs (cbf_detector detector, double indexfast, double indexslow, double *normal1, double *normal2, double *normal3); int cbf_get_pixel_normal (cbf_detector detector, double indexslow, double indexfast, double *normal1, double *normal2, double *normal3); DESCRIPTION cbf_get_detector_normal, cbf_get_pixel_normal_fs and cbf_get_pixel_normal_sf set *normal1, *normal2, and *normal3 to the 3 components of the of the normal vector to the pixel at (indexfast, indexslow). The vector is normalized. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. indexslow Slow index. indexfast Fast index. normal1 Pointer to the destination x component of the normal vector. normal2 Pointer to the destination y component of the normal vector. normal3 Pointer to the destination z component of the normal vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.44 cbf_get_pixel_area, cbf_get_pixel_area_fs, cbf_get_pixel_area_sf PROTOTYPE #include "cbf_simple.h" int cbf_get_pixel_area (cbf_detector detector, double indexslow, double indexfast, double *area, double *projected_area); int cbf_get_pixel_area_fs(cbf_detector detector, double indexfast, double indexslow, double *area, double *projected_area); int cbf_get_pixel_area_sf(cbf_detector detector, double indexslow, double indexfast, double *area, double *projected_area); DESCRIPTION cbf_get_pixel_area, cbf_get_pixel_area_fs and cbf_get_pixel_area_sf set *area to the area of the pixel at (indexfast, indexslow) on the detector surface and *projected_area to the apparent area of the pixel as viewed from the sample position, with indexslow being the slow axis and indexfast being the fast axis. Either of the destination pointers may be NULL. ARGUMENTS detector Detector handle. indexfast Fast index. indexslow Slow index. area Pointer to the destination area in mm2. projected_area Pointer to the destination apparent area in mm2. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.45 cbf_get_pixel_size, cbf_get_pixel_size_fs, cbf_get_pixel_size_sf PROTOTYPE #include "cbf_simple.h" int cbf_get_pixel_size (cbf_handle handle, unsigned int element_number, int axis_number, double *psize); int cbf_get_pixel_size_fs(cbf_handle handle, unsigned int element_number, int axis_number, double *psize); int cbf_get_pixel_size_sf(cbf_handle handle, unsigned int element_number, int axis_number, double *psize); DESCRIPTION cbf_get_pixel_size and cbf_get_pixel_size_sf set *psize to point to the double value in millimeters of the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the slowest axis. cbf_get_pixel_size_fs sets *psize to point to the double value in millimeters of the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the fastest axis. If a negative axis number is given, the order of axes is reversed, so that -1 specifies the slowest axis for cbf_get_pixel_size_fs and the fastest axis for cbf_get_pixel_size_sf. If the pixel size is not given explcitly in the "array_element_size" category, the function returns CBF_NOTFOUND. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category. axis_number The number of the axis, starting from 1 for the fastest for cbf_get_pixel_size and cbf_get_pixel_size_fs and the slowest for cbf_get_pixel_size_sf. psize Pointer to the destination pixel size. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.46 cbf_set_pixel_size, cbf_set_pixel_size_fs, cbf_set_pixel_size_sf PROTOTYPE #include "cbf_simple.h" int cbf_set_pixel_size (cbf_handle handle, unsigned int element_number, int axis_number, double psize); int cbf_set_pixel_size_fs(cbf_handle handle, unsigned int element_number, int axis_number, double psize); int cbf_set_pixel_size_sf(cbf_handle handle, unsigned int element_number, int axis_number, double psize); DESCRIPTION cbf_set_pixel_size and cbf_set_pixel_size_sf set the item in the "e;size"e; column of the "array_structure_list" category at the row which matches axis axis_number of the detector element element_number converting the double pixel size psize from meters to millimeters in storing it in the "size" column for the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the slowest axis. cbf_set_pixel_size_fs sets the item in the "e;size"e; column of the "array_structure_list" category at the row which matches axis axis_number of the detector element element_number converting the double pixel size psize from meters to millimeters in storing it in the "size" column for the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the fastest axis. If a negative axis number is given, the order of axes is reversed, so that -1 specifies the slowest axis for cbf_get_pixel_size_fs and the fastest axis for cbf_get_pixel_size_sf. If the "array_structure_list" category does not already exist, it is created. If the appropriate row in the "array_structure_list" catgeory does not already exist, it is created. If the pixel size is not given explcitly in the "array_element_size category", the function returns CBF_NOTFOUND. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category. axis_number The number of the axis, fastest first, starting from 1. psize The pixel size in millimeters. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.47 cbf_get_inferred_pixel_size, cbf_get_inferred_pixel_size_fs, cbf_get_inferred_pixel_size_sf PROTOTYPE #include "cbf_simple.h" int cbf_get_inferred_pixel_size (cbf_detector detector, int axis_number, double *psize); int cbf_get_inferred_pixel_size_fs(cbf_detector detector, int axis_number, double *psize); int cbf_get_inferred_pixel_size_sf(cbf_detector detector, int axis_number, double *psize); DESCRIPTION cbf_get_inferred_pixel_size, cbf_get_inferred_pixel_size_sf set *psize to point to the double value in millimeters of the pixel size for the axis axis_number value. The slow index is treated as axis 1 and the next faster index is treated as axis 2. cbf_get_inferred_pixel_size_fs sets *psize to point to the double value in millimeters of the pixel size for the axis axis_number value. The fast index is treated as axis 1 and the next slower index is treated as axis 2. If the axis number is negative, the axes are used in the reverse order so that an axis_number of -1 indicates the fast axes in a call to cbf_get_inferred_pixel_size or cbf_get_inferred_pixel_size_sf and indicates the fast axis in a call to cbf_get_inferred_pixel_size_fs. ARGUMENTS detector Detector handle. axis_number The number of the axis. area Pointer to the destination pizel size in mm. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.48 cbf_get_unit_cell PROTOTYPE #include "cbf_simple.h" int cbf_get_unit_cell (cbf_handle handle, double cell[6], double cell_esd[6] ); DESCRIPTION cbf_get_unit_cell sets cell[0:2] to the double values of the cell edge lengths a, b and c in AAngstroms, cell[3:5] to the double values of the cell angles a, b and g in degrees, cell_esd[0:2] to the double values of the estimated strandard deviations of the cell edge lengths a, b and c in AAngstroms, cell_esd[3:5] to the double values of the estimated standard deviations of the the cell angles a, b and g in degrees. The values returned are retrieved from the first row of the "cell" category. The value of "_cell.entry_id" is ignored. cell or cell_esd may be NULL. If cell is NULL, the cell parameters are not retrieved. If cell_esd is NULL, the cell parameter esds are not retrieved. If the "cell" category is present, but some of the values are missing, zeros are returned for the missing values. ARGUMENTS handle CBF handle. cell Pointer to the destination array of 6 doubles for the cell parameters. cell_esd Pointer to the destination array of 6 doubles for the cell parameter esds. RETURN VALUE Returns an error code on failure or 0 for success. No errors is returned for missing values if the "cell" category exists. SEE ALSO 2.4.49 cbf_set_unit_cell 2.4.50 cbf_get_reciprocal_cell 2.4.51 cbf_set_reciprocal_cell 2.4.52 cbf_compute_cell_volume 2.4.53 cbf_compute_reciprocal_cell ---------------------------------------------------------------------- 2.4.49 cbf_set_unit_cell PROTOTYPE #include "cbf_simple.h" int cbf_set_unit_cell (cbf_handle handle, double cell[6], double cell_esd[6] ); DESCRIPTION cbf_set_unit_cell sets the cell parameters to the double values given in cell[0:2] for the cell edge lengths a, b and c in AAngstroms, the double values given in cell[3:5] for the cell angles a, b and g in degrees, the double values given in cell_esd[0:2] for the estimated strandard deviations of the cell edge lengths a, b and c in AAngstroms, and the double values given in cell_esd[3:5] for the estimated standard deviations of the the cell angles a, b and g in degrees. The values are placed in the first row of the "cell" category. If no value has been given for "_cell.entry_id", it is set to the value of the "diffrn.id" entry of the current data block. cell or cell_esd may be NULL. If cell is NULL, the cell parameters are not set. If cell_esd is NULL, the cell parameter esds are not set. If the "cell" category is not present, it is created. If any of the necessary columns are not present, they are created. ARGUMENTS handle CBF handle. cell Pointer to the array of 6 doubles for the cell parameters. cell_esd Pointer to the array of 6 doubles for the cell parameter esds. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.4.48 cbf_get_unit_cell 2.4.50 cbf_get_reciprocal_cell 2.4.51 cbf_set_reciprocal_cell 2.4.52 cbf_compute_cell_volume 2.4.53 cbf_compute_reciprocal_cell ---------------------------------------------------------------------- SEE ALSO 2.4.50 cbf_get_reciprocal_cell PROTOTYPE #include "cbf_simple.h" int cbf_get_reciprocal_cell (cbf_handle handle, double cell[6], double cell_esd[6] ); DESCRIPTION cbf_get_reciprocal_cell sets cell[0:2] to the double values of the reciprocal cell edge lengths a*, b* and c* in AAngstroms-1, cell[3:5] to the double values of the reciprocal cell angles a*, b* and g* in degrees, cell_esd[0:2] to the double values of the estimated strandard deviations of the reciprocal cell edge lengths a*, b* and c* in AAngstroms-1, cell_esd[3:5] to the double values of the estimated standard deviations of the the reciprocal cell angles a*, b* and g* in degrees. The values returned are retrieved from the first row of the "cell" category. The value of "_cell.entry_id" is ignored. cell or cell_esd may be NULL. If cell is NULL, the reciprocal cell parameters are not retrieved. If cell_esd is NULL, the reciprocal cell parameter esds are not retrieved. If the "cell" category is present, but some of the values are missing, zeros are returned for the missing values. ARGUMENTS handle CBF handle. cell Pointer to the destination array of 6 doubles for the reciprocal cell parameters. cell_esd Pointer to the destination array of 6 doubles for the reciprocal cell parameter esds. RETURN VALUE Returns an error code on failure or 0 for success. No errors is returned for missing values if the "cell" category exists. SEE ALSO 2.4.48 cbf_get_unit_cell 2.4.49 cbf_set_unit_cell 2.4.51 cbf_set_reciprocal_cell 2.4.52 cbf_compute_cell_volume 2.4.53 cbf_compute_reciprocal_cell ---------------------------------------------------------------------- 2.4.51 cbf_set_reciprocal_cell PROTOTYPE #include "cbf_simple.h" int cbf_set_reciprocal_cell (cbf_handle handle, double cell[6], double cell_esd[6] ); DESCRIPTION cbf_set_reciprocal_cell sets the reciprocal cell parameters to the double values given in cell[0:2] for the reciprocal cell edge lengths a*, b* and c* in AAngstroms-1, the double values given in cell[3:5] for the reciprocal cell angles a*, b* and g* in degrees, the double values given in cell_esd[0:2] for the estimated strandard deviations of the reciprocal cell edge lengths a*, b* and c* in AAngstroms, and the double values given in cell_esd[3:5] for the estimated standard deviations of the reciprocal cell angles a*, b* and g* in degrees. The values are placed in the first row of the "cell" category. If no value has been given for "_cell.entry_id", it is set to the value of the "diffrn.id" entry of the current data block. cell or cell_esd may be NULL. If cell is NULL, the reciprocal cell parameters are not set. If cell_esd is NULL, the reciprocal cell parameter esds are not set. If the "cell" category is not present, it is created. If any of the necessary columns are not present, they are created. ARGUMENTS handle CBF handle. cell Pointer to the array of 6 doubles for the reciprocal cell parameters. cell_esd Pointer to the array of 6 doubles for the reciprocal cell parameter esds. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.4.48 cbf_get_unit_cell 2.4.49 cbf_set_unit_cell 2.4.50 cbf_get_reciprocal_cell 2.4.52 cbf_compute_cell_volume 2.4.53 cbf_compute_reciprocal_cell ---------------------------------------------------------------------- 2.4.52 cbf_compute_cell_volume PROTOTYPE #include "cbf_simple.h" int cbf_compute_cell_volume ( double cell[6], double *volume ); DESCRIPTION cbf_compute_cell_volume sets *volume to point to the volume of the unit cell computed from the double values in cell[0:2] for the cell edge lengths a, b and c in AAngstroms and the double values given in cell[3:5] for the cell angles a, b and g in degrees. ARGUMENTS cell Pointer to the array of 6 doubles giving the cell parameters. volume Pointer to the doubles for cell volume. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.4.48 cbf_get_unit_cell 2.4.49 cbf_set_unit_cell 2.4.50 cbf_get_reciprocal_cell 2.4.51 cbf_set_reciprocal_cell 2.4.53 cbf_compute_reciprocal_cell ---------------------------------------------------------------------- 2.4.53 cbf_compute_reciprocal_cell PROTOTYPE #include "cbf_simple.h" int cbf_compute_reciprocal_cell ( double cell[6], double rcell[6] ); DESCRIPTION cbf_compute_reciprocal_cell sets rcell to point to the array of reciprocal cell parameters computed from the double values cell[0:2] giving the cell edge lengths a, b and c in AAngstroms, and the double values cell[3:5] giving the cell angles a, b and g in degrees. The double values rcell[0:2] will be set to the reciprocal cell lengths a*, b* and c* in AAngstroms-1 and the double values rcell[3:5] will be set to the reciprocal cell angles a*, b* and g* in degrees. ARGUMENTS cell Pointer to the array of 6 doubles giving the cell parameters. rcell Pointer to the destination array of 6 doubles giving the reciprocal cell parameters. volume Pointer to the doubles for cell volume. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.4.48 cbf_get_unit_cell 2.4.49 cbf_set_unit_cell 2.4.50 cbf_get_reciprocal_cell 2.4.51 cbf_set_reciprocal_cell 2.4.52 cbf_compute_cell_volume ---------------------------------------------------------------------- 2.4.54 cbf_get_orientation_matrix, cbf_set_orientation_matrix PROTOTYPE #include "cbf_simple.h" int cbf_get_orientation_matrix (cbf_handle handle, double ub_matrix[9]); int cbf_set_orientation_matrix (cbf_handle handle, double ub_matrix[9]); DESCRIPTION cbf_get_orientation_matrix sets ub_matrix to point to the array of orientation matrix entries in the "diffrn" category in the order of columns: "UB[1][1]" "UB[1][2]" "UB[1][3]" "UB[2][1]" "UB[2][2]" "UB[2][3]" "UB[3][1]" "UB[3][2]" "UB[3][3]" cbf_set_orientation_matrix sets the values in the "diffrn" category to the values pointed to by ub_matrix. ARGUMENTS handle CBF handle. ubmatric Source or destination array of 9 doubles giving the orientation matrix parameters. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.55 cbf_get_bin_sizes, cbf_set_bin_sizes PROTOTYPE #include "cbf_simple.h" int cbf_get_bin_sizes(cbf_handle handle, unsigned int element_number, double * slowbinsize, double * fastbinsize); int cbf_set_bin_sizes(cbf_handle handle, unsigned int element_number, double slowbinsize_in,double fastbinsize_in); DESCRIPTION cbf_get_bin_sizes sets slowbinsize to point to the value of the number of pixels composing one array element in the dimension that changes at the second-fastest rate and fastbinsize to point to the value of the number of pixels composing one array element in the dimension that changes at the fastest rate for the dectector element with the ordinal element_number. cbf_set_bin_sizes sets the the pixel bin sizes in the "array_intensities" category to the values of slowbinsize_in for the number of pixels composing one array element in the dimension that changes at the second-fastest rate and fastbinsize_in for the number of pixels composing one array element in the dimension that changes at the fastest rate for the dectector element with the ordinal element_number. In order to allow for software binning involving fractions of pixels, the bin sizes are doubles rather than ints. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category. slowbinsize Pointer to the returned number of pixels composing one array element in the dimension that changes at the second-fastest rate. fastbinsize Pointer to the returned number of pixels composing one array element in the dimension that changes at the fastest rate. slowbinsize_in The number of pixels composing one array element in the dimension that changes at the second-fastest rate. fastbinsize_in The number of pixels composing one array element in the dimension that changes at the fastest rate. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.5 F90 function interfaces At the suggestion of W. Kabsch, Fortran 90/95 routines have been added to CBFlib. As of this writing code has been written to allow the reading of CBF_BYTE_OFFSET, CBF_PACKED and CBF_PACKED_V2 binary images. This code has been gather into FCBlib (Fortran Crystallographic Binary library) as lib/libfcb. In general, most of the FCBlib functions return 0 for normal completion and a non-zero value in case of an error. In a few cases, such as FCB_ATOL_WCNT and FCB_NBLEN_ARRAY in order to conform to the conventions for commonly used C-equivalent functions, the function return is the value being computed. For each function, an interface is given to be included in the declarations of your Fortran 90/95 code. Some functions in FCBlIB are not intended for external use and are subject to change: FCB_UPDATE_JPA_POINTERS_I2, FCB_UPDATE_JPA_POINTERS_I4, FCB_UPDATE_JPA_POINTERS_3D_I2, FCB_UPDATE_JPA_POINTERS_3D_I4 and CNT2PIX. These names should not be used for user routines. The functions involving reading of a CBF have been done strictly in Fortran without the use of C code. This has required some compromises and the use of direct access I/O. Rather than putting the buffer and its control variables into COMMON these are passed as local arguments to make the routines inherently 'threadsafe' in a parallel programming environment. Note also, that a reading error could occur for the last record if it does not fill a full block. The code is written to recover from end-of-record and end-of-file errors, if possible. On many modern system, no special action is required, but on some systems it may be necessary to make use of the padding between the end of binary data and the terminal MIME boundary marker in binary sections. To ensure maximum portability of CBF files, a padding of 4095 bytes is recommended. Existing files without padding can be converted to files with padding by use of the new -p4 option for cif2cbf. 2.5.1 FCB_ATOL_WCNT INTERFACE INTEGER(8) FUNCTION FCB_ATOL_WCNT(ARRAY, N, CNT) INTEGER(1),INTENT(IN):: ARRAY(N) INTEGER, INTENT(IN):: N INTEGER, INTENT(OUT):: CNT END FUNCTION END INTERFACE FCB_ATOL_WCNT converts INTEGER(1) bytes in ARRAY of N bytes to an INTEGER(8) value returned as the function value. The number of bytes of ARRAY actually used before encountering a character not used to form the number is returned in CNT. The scan stops at the first byte in ARRAY that cannot be properly parsed as part of the integer result. ARGUMENTS ARRAY The array of INTEGER(1) bytes to be scanned N The INTEGER size of ARRAY CNT The INTEGER size of the portion of ARRAY scanned. RETURN VALUE Returns the INTEGER(8) value derived from the characters ARRAY(1:CNT) scanned. ---------------------------------------------------------------------- 2.5.2 FCB_CI_STRNCMPARR INTERFACE INTEGER FUNCTION FCB_CI_STRNCMPARR(STRING>, ARRAY, N, LIMIT) CHARACTER(LEN=*),INTENT(IN):: STRING> INTEGER, INTENT(IN):: N, LIMIT INTEGER(1), INTENT(IN):: ARRAY(N) END FUNCTION END INTERFACE The function FCB_CI_STRNCMPARR compares up to LIMIT characters of character string STRING and INTEGER(1) byte array ARRAY of dimension N in a case-insensitive manner, returning 0 for a match. ARGUMENTS STRING A character string ARRAY The array of INTEGER(1) bytes to be scanned N The INTEGER size of ARRAY N The INTEGER limit on the number of characters to consider in the comparison RETURN VALUE Returns 0 if the string and array match, a non-zero value otherwise. ---------------------------------------------------------------------- 2.5.3 FCB_EXIT_BINARY INTERFACE INTEGER FUNCTION FCB_EXIT_BINARY(TAPIN,LAST_CHAR,FCB_BYTES_IN_REC,& BYTE_IN_FILE,REC_IN_FILE,BUFFER, & PADDING ) INTEGER, INTENT(IN) :: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: BYTE_IN_FILE,REC_IN_FILE INTEGER(1),INTENT(INOUT):: LAST_CHAR,BUFFER(FCB_BYTES_IN_REC) INTEGER(8),INTENT(IN) :: PADDING END FUNCTION END INTERFACE The function FCB_EXIT_BINARY is used to skip from the end of a binary section past any padding to the end of the text section that encloses the binary section. The values of the arguments must be consistent with those in the last call to FCB_NEXT_BINARY ARGUMENTS TAPIN The INTEGER Fortran device unit number assigned to image file. LAST_CHAR The last character (as an INTEGER(1) byte) read. FCB_BYTES_IN_REC The INTEGER number of bytes in a record. BYTE_IN_FILE The INTEGER byte (counting from 1) of the byte to read. REC_IN_FILE The INTEGER record number (counting from 1) of next record to read. BUFFER The INTEGER(1) array of length FCB_BYTES_IN_REC to hold the appropriate record from TAPIN PADDING The INTEGER(8) number of bytes of padding after the binary data and before the closing MIME boundary. RETURN VALUE Returns 0 if the function is successful. Returns whatever non-zero error value is reported by FCB_READ_LINE if a necessary next line cannot be read. SEE ALSO 2.5.5 FCB_NEXT_BINARY 2.5.6 FCB_OPEN_CIFIN 2.5.9 FCB_READ_BYTE 2.5.11 FCB_READ_LINE ---------------------------------------------------------------------- 2.5.4 FCB_NBLEN_ARRAY INTERFACE INTEGER FUNCTION FCB_NBLEN_ARRAY(ARRAY, ARRAYLEN) INTEGER, INTENT(IN):: ARRAYLEN INTEGER(1), INTENT(IN):: ARRAY(ARRAYLEN) END FUNCTION END INTERFACE The function FCB_NBLEN_ARRAY returns the trimmed length of the INTEGER(1) byte array ARRAY of dimension ARRAYLEN after removal of trailing ASCII blanks, horizontal tabs (Z'09'), newlines (Z'0A') and carriage returns (Z'0D'). The resulting length may be zero. The INTEGER trimmed length is returned as the function value. ARGUMENTS ARRAY The array of bytes for which the trimmed length is required. ARRAYLEN The dimension of the array of bytes to be scanned. RETURN VALUE Returns the trimmed length of the array ARRAY. ---------------------------------------------------------------------- 2.5.5 FCB_NEXT_BINARY INTERFACE INTEGER FUNCTION FCB_NEXT_BINARY(TAPIN,LAST_CHAR,FCB_BYTES_IN_REC,& BYTE_IN_FILE,REC_IN_FILE,BUFFER, & ENCODING,SIZE,ID,DIGEST, & COMPRESSION,BITS,VORZEICHEN,REELL,& BYTEORDER,DIMOVER,DIM1,DIM2,DIM3, & PADDING ) INTEGER, INTENT(IN) :: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: BYTE_IN_FILE,REC_IN_FILE INTEGER(1),INTENT(INOUT):: LAST_CHAR,BUFFER(FCB_BYTES_IN_REC) INTEGER, INTENT(OUT) :: ENCODING INTEGER, INTENT(OUT) :: SIZE !Binary size INTEGER, INTENT(OUT) :: ID !Binary ID CHARACTER(len=*),INTENT(OUT):: DIGEST !Message digest INTEGER, INTENT(OUT):: COMPRESSION INTEGER, INTENT(OUT):: BITS,VORZEICHEN,REELL CHARACTER(len=*),INTENT(OUT):: BYTEORDER INTEGER(8), INTENT(OUT):: DIMOVER INTEGER(8), INTENT(OUT):: DIM1 INTEGER(8), INTENT(OUT):: DIM2 INTEGER(8), INTENT(OUT):: DIM3 INTEGER(8), INTENT(OUT):: PADDING END FUNCTION END INTERFACE The function FCB_NEXT_BINARY skips to the start of the next binary section in the image file on unit TAPIN leaving the file positioned for a subsequent read of the image data. The skip may prior to the text field that contains the binary section. When the text filed is reached, it will be scanned for a MIME boundary marker, and, if it is found the subsequence MIME headers will be used to populate the arguments ENCODING, SIZE, ID, DIGEST, COMPRESSION, BITS, VORZEICHEN,REELL, BYTEORDER, DIMOVER, DIM1, DIM2,DIM3, PADDING. The value returned in ENCODING is taken from the MIME header Content-Transfer-Encoding as an INTEGER. It is returned as 0 if not specified. The reported value is one of the integer values ENC_NONE (Z'0001') for BINARY encoding, ENC_BASE64 (Z'0002') for BASE64 encoding, ENC_BASE32K (Z'0004') for X-BASE32K encoding, ENC_QP (Z'0008') for QUOTED-PRINTABLE encoding, ENC_BASE10 (Z'0010') for BASE10 encoding, ENC_BASE16 (Z'0020') for BASE16 encoding or ENC_BASE8 (Z'0040') for BASE8 encoding. At this time FCBlib only supports ENC_NONE BINARY encoding. The value returned in SIZE is taken from the MIME header X-Binary-Size as an INTEGER. It is returned as 0 if not specified. The value returned in ID is taken from the MIME header X-Binary-ID as an INTEGER. It is returned as 0 if not specified. The value returned in DIGEST is taken from the MIME header Content-MD5. It is returned as a character string. If no digest is given, an empty string is returned. The value returned in COMPRESSION is taken from the MIME header Content-Type in the conversions parameter. The reported value is one of the INTEGER values CBF_CANONICAL (Z'0050'), CBF_PACKED (Z'0060'), CBF_PACKED_V2 (Z'0090'), CBF_BYTE_OFFSET (Z'0070'), CBF_PREDICTOR (Z'0080'), CBF_NONE (Z'0040'). Two flags may be combined with CBF_PACKED or CBF_PACKED_V2: CBF_UNCORRELATED_SECTIONS (Z'0100') or CBF_FLAT_IMAGE (Z'0200'). At this time FCBlib does not support CBF_PREDICTOR or CBF_NONE compression. The values returned in BITS, VORZEICHEN and REELL are the parameters of the data types of the elements. These values are taken from the MIME header X-Binary-Element-Type, which has values of the form "signed BITS-bit integer", "unsigned BITS-bit integer", "signed BITS-bit real IEEE" or "signed BITS-bit complex IEEE". If no value is given, REELL is reported as -1. If the value in one of the integer types, REELL is reported as 0. If the value is one of the real or complex types, REELL is reported as 1. In the current release of FCBlib only the integer types for BITS equal to 16 or 32 are supported. The value returned in BYTEORDER is the byte order of the data in the image file as reported in the MIME header. The value, if specified, will be either the character string "LITTLE_ENDIAN" or the character string "BIG_ENDIAN". If no byte order is specified, "LITTLE_ENDIAN" is reported. This value is taken from the MIME header X-Binary-Element-Byte-Order. As of this writing, CBFlib will not generate "BIG_ENDIAN" byte-order files. However, both CBFlib and FCBlib read "LITTLE_ENDIAN" byte-order files, even on big-endian machines. The value returned in DIMOVER is the overall number of elements in the image array, if specified, or zero, if not specified. This value is taken from the MIME header X-Binary-Number-of-Elements. The values returned in DIM1, DIM2 and DIM3 are the sizes of the fastest changing, second fastest changing and third fastest changing dimensions of the array, if specified, or zero, if not specified. These values are taken from the MIME header X-Binary-Size-Fastest-Dimension, X-Binary-Size-Second-Dimension and X-Binary-Size-Third-Dimension respectively. The value returned in PADDING is the size of the post-data padding, if any, if specified or zero, if not specified. The value is given as a count of octets. This value is taken from the MIME header X-Binary-Size-Padding. ARGUMENTS TAPIN The INTEGER Fortran device unit number assigned to image file. LAST_CHAR The last character (as an INTEGER(1) byte) read. FCB_BYTES_IN_REC The INTEGER number of bytes in a record. BYTE_IN_FILE The INTEGER byte (counting from 1) of the byte to read. REC_IN_FILE The INTEGER record number (counting from 1) of next record to read. BUFFER The INTEGER(1) array of length FCB_BYTES_IN_REC to hold the appropriate record from TAPIN ENCODING INTEGER type of encoding for the binary section as reported in the MIME header. ID INTEGER binary identifier as reported in the MIME header. SIZE INTEGER size of compressed binary section as reported in the MIME header. DIGEST The MD5 message digest as reported in the MIME header. COMPRESSION INTEGER compression method as reported in the MIME header. BITS INTEGER number of bits in each element as reported in the MIME header. VORZEICHEN INTEGER flag for signed or unsigned elements as reported in the MIME header. Set to 1 if the elements can be read as signed values, 0 otherwise. REELL INTEGER flag for real elements as reported in the MIME header. Set to 1 if the elements can be read as REAL BYTEORDER The byte order as reported in the MIME header. DIM1 Pointer to the destination fastest dimension. DIM2 Pointer to the destination second fastest dimension. DIM3 Pointer to the destination third fastest dimension. PADDING Pointer to the destination padding size. RETURN VALUE Returns 0 if the function is successful. SEE ALSO 2.5.3 FCB_EXIT_BINARY 2.5.6 FCB_OPEN_CIFIN 2.5.9 FCB_READ_BYTE 2.5.11 FCB_READ_LINE ---------------------------------------------------------------------- 2.5.6 FCB_OPEN_CIFIN INTERFACE INTEGER FUNCTION FCB_OPEN_CIFIN(FILNAM,TAPIN,LAST_CHAR, & FCB_BYTES_IN_REC,BYTE_IN_FILE,REC_IN_FILE,BUFFER) CHARACTER(len=*),INTENT(IN) :: FILNAM INTEGER, INTENT(IN) :: TAPIN,FCB_BYTES_IN_REC INTEGER(1), INTENT(OUT):: LAST_CHAR INTEGER, INTENT(OUT):: BYTE_IN_FILE,REC_IN_FILE INTEGER(1), INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) INTEGER FCB_RECORD_SIZE END FUNCTION END INTERFACE The function FCB_OPEN_CIFIN opens the CBF image file given by the file name in the character string FILNAM on the logical unit TAPIN. The calling routine must provide an INTEGER(1) byte buffer BUFFER of some appropriate INTEGER size FCB_BYTES_IN_REC. The size must be chosen to suit the machine, but in most cases, 4096 will work. The values returned in LAST_CHAR, BYTE_IN_FILE, and REC_IN_FILE are for use in subsequent FCBlib I/O routines. The image file will be checked for the initial characters "###CBF: ". If there is no match the error value CBF_FILEREAD is returned. ARGUMENTS FILNAM The character string name of the image file to be opened. TAPIN The INTEGER Fortran device unit number assigned to image file. LAST_CHAR The last character (as an INTEGER(1) byte) read. FCB_BYTES_IN_REC The INTEGER number of bytes in a record. BYTE_IN_FILE The INTEGER byte (counting from 1) of the byte to read. REC_IN_FILE The INTEGER record number (counting from 1) of next record to read. BUFFER The INTEGER(1) array of length FCB_BYTES_IN_REC to hold the appropriate record from TAPIN RETURN VALUE Returns 0 if the function is successful. SEE ALSO 2.5.3 FCB_EXIT_BINARY 2.5.5 FCB_NEXT_BINARY 2.5.9 FCB_READ_BYTE 2.5.11 FCB_READ_LINE ---------------------------------------------------------------------- 2.5.7 FCB_PACKED: FCB_DECOMPRESS_PACKED_I2, FCB_DECOMPRESS_PACKED_I4, FCB_DECOMPRESS_PACKED_3D_I2, FCB_DECOMPRESS_PACKED_3D_I4 INTERFACE INTEGER FUNCTION FCB_DECOMPRESS_PACKED_I2 (ARRAY,NELEM,NELEM_READ, & ELSIGN, COMPRESSION, DIM1, DIM2, & TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) INTEGER(2), INTENT(OUT):: ARRAY(DIM1,DIM2) INTEGER(8), INTENT(OUT):: NELEM_READ INTEGER(8), INTENT(IN):: NELEM INTEGER, INTENT(IN):: ELSIGN, COMPRESSION INTEGER(8), INTENT(IN):: DIM1,DIM2 INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) END FUNCTION END INTERFACE INTERFACE INTEGER FUNCTION FCB_DECOMPRESS_PACKED_I4 (ARRAY,NELEM,NELEM_READ, & ELSIGN, COMPRESSION, DIM1, DIM2, & TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) INTEGER(4), INTENT(OUT):: ARRAY(DIM1,DIM2) INTEGER(8), INTENT(OUT):: NELEM_READ INTEGER(8), INTENT(IN):: NELEM INTEGER, INTENT(IN):: ELSIGN, COMPRESSION INTEGER(8), INTENT(IN):: DIM1,DIM2 INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) END FUNCTION END INTERFACE INTERFACE INTEGER FUNCTION FCB_DECOMPRESS_PACKED_3D_I2 (ARRAY,NELEM,NELEM_READ, & ELSIGN, COMPRESSION, DIM1, DIM2, DIM3, & TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) INTEGER(2), INTENT(OUT):: ARRAY(DIM1,DIM2,DIM3) INTEGER(8), INTENT(OUT):: NELEM_READ INTEGER(8), INTENT(IN):: NELEM INTEGER, INTENT(IN):: ELSIGN, COMPRESSION INTEGER(8), INTENT(IN):: DIM1,DIM2,DIM3 INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) END FUNCTION END INTERFACE INTERFACE INTEGER FUNCTION FCB_DECOMPRESS_PACKED_3D_I4 (ARRAY,NELEM,NELEM_READ, & ELSIGN, COMPRESSION, DIM1, DIM2, DIM3, & TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) INTEGER(4), INTENT(OUT):: ARRAY(DIM1,DIM2,DIM3) INTEGER(8), INTENT(OUT):: NELEM_READ INTEGER(8), INTENT(IN):: NELEM INTEGER, INTENT(IN):: ELSIGN, COMPRESSION INTEGER(8), INTENT(IN):: DIM1,DIM2,DIM3 INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) END FUNCTION END INTERFACE The functions FCB_DECOMPRESS_PACKED_I2, FCB_DECOMPRESS_PACKED_I4, FCB_DECOMPRESS_PACKED_3D_I2 and FCB_DECOMPRESS_PACKED_3D_I4, decompress images compress according the the CBF_PACKED or CBF_PACKED_V2 compression described in section 3.3.2 on J. P. Abrahams CCP4 packed compression. The relevant function should be called immediately after a call to FCB_NEXT_BINARY, using the values returned by FCB_NEXT_BINARY to select the appropriate version of the function. ARGUMENTS ARRAY The array to receive the image NELEM The INTEGER(8) number of elements to be read NELEM_READ The INTEGER(8) returned value of the number of elements actually read ELSIGN The INTEGER value of the flag for signed (1) OR unsigned (0) data COMPRESSION The compression of the image DIM1 The INTEGER(8) value of the fastest dimension of ARRAY DIM2 The INTEGER(8) value of the second fastest dimension DIM3 The INTEGER(8) value of the third fastest dimension TAPIN The INTEGER Fortran device unit number assigned to image file. FCB_BYTES_IN_REC The INTEGER number of bytes in a record. BYTE_IN_FILE The INTEGER byte (counting from 1) of the byte to read. REC_IN_FILE The INTEGER record number (counting from 1) of next record to read. BUFFER The INTEGER(1) array of length FCB_BYTES_IN_REC to hold the appropriate record from TAPIN RETURN VALUE Returns 0 if the function is successful. SEE ALSO 2.5.3 FCB_EXIT_BINARY 2.5.5 FCB_NEXT_BINARY 2.5.6 FCB_OPEN_CIFIN 2.5.9 FCB_READ_BYTE 2.5.11 FCB_READ_LINE ---------------------------------------------------------------------- 2.5.8 FCB_READ_BITS INTERFACE INTEGER FUNCTION FCB_READ_BITS(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,BCOUNT,BBYTE, & BITCOUNT,IINT,LINT) INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) INTEGER, INTENT(INOUT):: BCOUNT INTEGER(1),INTENT(INOUT):: BBYTE INTEGER, INTENT(IN):: BITCOUNT INTEGER, INTENT(IN):: LINT INTEGER(4), INTENT(OUT):: IINT(LINT) END FUNCTION END INTERFACE The function FCB_READ_BITS gets the integer value starting at BYTE_IN_FILE from file TAPIN continuing through BITCOUNT bits, with sign extension. BYTE_IN_FILE is left at the entry value and not incremented. The resulting, sign-extended integer value is stored in the INTEGER(4) array IINT of dimension LINT with the least significant portion in IINT(1). ARGUMENTS TAPIN The INTEGER Fortran device unit number assigned to image file. FCB_BYTES_IN_REC The INTEGER number of bytes in a record. BUFFER The INTEGER(1) array of length FCB_BYTES_IN_REC to hold the appropriate record from TAPIN REC_IN_FILE The INTEGER record number (counting from 1) of next record to read. BYTE_IN_FILE The INTEGER byte (counting from 1) of the byte to read. BCOUNT The INTEGER count of bits remaining unused from the last call to FCB_READ_BITS. BBYTE The INTEGER(1) byte containing the unused bits from the last call to FCB_READ_BITS. BITCOUNT The INTEGER count of the number of bits to be extracted from the image file. IINT The INTEGER(4) array into which to store the value extracted from the image file. LINT The INTEGER length of the array IINT. RETURN VALUE Returns 0 if the function is successful. Because of the use of direct access I/O in blocks of size FCB_BYTES_IN_REC the precise location of the end of file may not be detected. SEE ALSO 2.5.3 FCB_EXIT_BINARY 2.5.5 FCB_NEXT_BINARY 2.5.6 FCB_OPEN_CIFIN 2.5.9 FCB_READ_BYTE 2.5.11 FCB_READ_LINE ---------------------------------------------------------------------- 2.5.9 FCB_READ_BYTE INTERFACE INTEGER FUNCTION FCB_READ_BYTE(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,IBYTE) INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) INTEGER(1), INTENT(OUT):: IBYTE END FUNCTION END INTERFACE The function FCB_READ_BYTE reads the byte at the position BYTE_IN_FILE in the image file TAPIN. The first byte in the file is at BYTE_IN_FILE = 1. BYTE_IN_FILE should be set to the desired value before the call to the function and is not incremented within the function. The function attempts to suppress the error caused by a read of a short last record, and in most systems cannot determine the exact location of the end of the image file, returning zero bytes until the equivalent of a full final record has been read. ARGUMENTS TAPIN The INTEGER Fortran device unit number assigned to image file. FCB_BYTES_IN_REC The INTEGER number of bytes in a record. BUFFER The INTEGER(1) array of length FCB_BYTES_IN_REC to hold the appropriate record from TAPIN REC_IN_FILE The INTEGER record number (counting from 1) of next record to read. BYTE_IN_FILE The INTEGER byte (counting from 1) of the byte to read. IBYTE The INTEGER(1) byte found in the image file at the byte position BYTE_IN_FILE. RETURN VALUE Returns 0 if the function is successful. Because of the use of direct access I/O in blocks of size FCB_BYTES_IN_REC the precise location of the end of file may not be detected. SEE ALSO 2.5.3 FCB_EXIT_BINARY 2.5.5 FCB_NEXT_BINARY 2.5.6 FCB_OPEN_CIFIN 2.5.9 FCB_READ_BITS 2.5.11 FCB_READ_LINE ---------------------------------------------------------------------- 2.5.10 FCB_READ_IMAGE_I2, FCB_READ_IMAGE_I4, FCB_READ_IMAGE_3D_I2, FCB_READ_IMAGE_3D_I4 INTERFACE INTEGER FUNCTION FCB_READ_IMAGE_I2(ARRAY,NELEM,NELEM_READ, & ELSIGN, COMPRESSION, DIM1, DIM2, & PADDING,TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) INTEGER(2), INTENT(OUT):: ARRAY(DIM1,DIM2) INTEGER(8), INTENT(OUT):: NELEM_READ INTEGER(8), INTENT(IN):: NELEM INTEGER, INTENT(IN):: ELSIGN INTEGER, INTENT(OUT):: COMPRESSION INTEGER(8), INTENT(IN):: DIM1,DIM2 INTEGER(8), INTENT(OUT):: PADDING INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) END FUNCTION END INTERFACE INTERFACE INTEGER FUNCTION FCB_READ_IMAGE_I4(ARRAY,NELEM,NELEM_READ, & ELSIGN, COMPRESSION, DIM1, DIM2, & PADDING,TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) INTEGER(4), INTENT(OUT):: ARRAY(DIM1,DIM2) INTEGER(8), INTENT(OUT):: NELEM_READ INTEGER(8), INTENT(IN):: NELEM INTEGER, INTENT(IN):: ELSIGN INTEGER, INTENT(OUT):: COMPRESSION INTEGER(8), INTENT(IN):: DIM1,DIM2 INTEGER(8), INTENT(OUT):: PADDING INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) END FUNCTION END INTERFACE INTERFACE INTEGER FUNCTION FCB_READ_IMAGE_3D_I2(ARRAY,NELEM,NELEM_READ, & ELSIGN, COMPRESSION, DIM1, DIM2, DIM3, & PADDING,TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) INTEGER(2), INTENT(OUT):: ARRAY(DIM1,DIM2,DIM3) INTEGER(8), INTENT(OUT):: NELEM_READ INTEGER(8), INTENT(IN):: NELEM INTEGER, INTENT(IN):: ELSIGN INTEGER, INTENT(OUT):: COMPRESSION INTEGER(8), INTENT(IN):: DIM1,DIM2,DIM3 INTEGER(8), INTENT(OUT):: PADDING INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) END FUNCTION END INTERFACE INTERFACE INTEGER FUNCTION FCB_READ_IMAGE_3D_I4(ARRAY,NELEM,NELEM_READ, & ELSIGN, COMPRESSION, DIM1, DIM2, DIM3, & PADDING,TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) INTEGER(4), INTENT(OUT):: ARRAY(DIM1,DIM2,DIM3) INTEGER(8), INTENT(OUT):: NELEM_READ INTEGER(8), INTENT(IN):: NELEM INTEGER, INTENT(IN):: ELSIGN INTEGER, INTENT(OUT):: COMPRESSION INTEGER(8), INTENT(IN):: DIM1,DIM2,DIM3 INTEGER(8), INTENT(OUT):: PADDING INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) END FUNCTION END INTERFACE The function FCB_READ_IMAGE_I2 reads a 16-bit twos complement INTEGER(2) 2D image. The function FCB_READ_IMAGE_I4 read a 32-bit twos complement INTEGER(4) 2D image. The function FCB_READ_IMAGE_3D_I2 reads a 16-bit twos complement INTEGER(2) 3D image. The function FCB_READ_IMAGE_3D_I4 reads a 32-bit twos complement INTEGER(4) 3D image. In each case the image is compressed either by a BYTE_OFFSET algorithm by W. Kabsch based on a proposal by A. Hammersley or by a PACKED algorithm by J. P. Abrahams as used in CCP4, with modifications by P. Ellis and H. J. Bernstein. The relevant function automatically first calls FCB_NEXT_BINARY to skip to the next binary section and then starts to read. An error return will result if the parameters of this call are inconsistent with the values in MIME header. ARGUMENTS ARRAY The array to receive the image NELEM The INTEGER(8) number of elements to be read NELEM_READ The INTEGER(8) returned value of the number of elements actually read ELSIGN The INTEGER value of the flag for signed (1) OR unsigned (0) data COMPRESSION The actual compression of the image DIM1 The INTEGER(8) value of the fastest dimension of ARRAY DIM2 The INTEGER(8) value of the second fastest dimension DIM3 The INTEGER(8) value of the third fastest dimension TAPIN The INTEGER Fortran device unit number assigned to image file. FCB_BYTES_IN_REC The INTEGER number of bytes in a record. BYTE_IN_FILE The INTEGER byte (counting from 1) of the byte to read. REC_IN_FILE The INTEGER record number (counting from 1) of next record to read. BUFFER The INTEGER(1) array of length FCB_BYTES_IN_REC to hold the appropriate record from TAPIN RETURN VALUE Returns 0 if the function is successful. SEE ALSO 2.5.3 FCB_EXIT_BINARY 2.5.5 FCB_NEXT_BINARY 2.5.6 FCB_OPEN_CIFIN 2.5.7 FCB_DECOMPRESS: FCB_DECOMPRESS_PACKED_I2, FCB_DECOMPRESS_PACKED_I4, FCB_DECOMPRESS_PACKED_3D_I2, FCB_DECOMPRESS_PACKED_3D_I4 2.5.9 FCB_READ_BYTE 2.5.11 FCB_READ_LINE ---------------------------------------------------------------------- 2.5.11 FCB_READ_LINE INTERFACE INTEGER FUNCTION FCB_READ_LINE(TAPIN,LAST_CHAR,FCB_BYTES_IN_REC, & BYTE_IN_FILE,REC_IN_FILE,BUFFER,LINE,N,LINELEN) INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC,N INTEGER, INTENT(INOUT):: BYTE_IN_FILE,REC_IN_FILE INTEGER, INTENT(OUT):: LINELEN INTEGER(1),INTENT(INOUT):: LAST_CHAR,BUFFER,(FCB_BYTES_IN_REC) INTEGER(1), INTENT(OUT):: LINE(N) END FUNCTION END INTERFACE The function FCB_READ_LINE reads successive bytes into the INTEGER(1) byte array LINE of dimension N), stopping at N bytes or the first error or the first CR (Z'0D') or LF (Z'0A'), whichever comes first. It discards an LF after a CR. The variable LAST_CHAR is checked for the last character from the previous line to make this determination. The actual number of bytes read into the line, not including any terminal CR or LF is stored in LINELEN. ARGUMENTS TAPIN The INTEGER Fortran device unit number assigned to image file. LAST_CHAR The INTEGER(1) byte holding the ASCII value of the last character read for each line read. FCB_BYTES_IN_REC The INTEGER number of bytes in a record. BYTE_IN_FILE The INTEGER byte (counting from 1) of the byte to read. REC_IN_FILE The INTEGER record number (counting from 1) of next record to read. BUFFER The INTEGER(1) array of length FCB_BYTES_IN_REC to hold the appropriate record from TAPIN. LINE The INTEGER(1) array of length N to hold the line to be read from TAPIN. N The INTEGER dimension of LINE. LINELEN The INTEGER number of characters read into LINE. RETURN VALUE Returns 0 if the function is successful. SEE ALSO 2.5.3 FCB_EXIT_BINARY 2.5.5 FCB_NEXT_BINARY 2.5.6 FCB_OPEN_CIFIN 2.5.7 FCB_DECOMPRESS: FCB_DECOMPRESS_PACKED_I2, FCB_DECOMPRESS_PACKED_I4, FCB_DECOMPRESS_PACKED_3D_I2, FCB_DECOMPRESS_PACKED_3D_I4 2.5.9 FCB_READ_BYTE 2.5.12 FCB_READ_XDS_I2 INTERFACE INTEGER FUNCTION FCB_READ_XDS_I2(FILNAM,TAPIN,NX,NY,IFRAME,JFRAME) CHARACTER(len=*),INTENT(IN) :: FILNAM INTEGER, INTENT(IN) :: TAPIN,NX,NY INTEGER(2), INTENT(OUT):: IFRAME(NX*NY) INTEGER(4), INTENT(OUT):: JFRAME(NX,NY) END FUNCTION END INTERFACE The function FCB_READ_XDS_I2 read a 32-bit integer twos complement image into a 16-bit INTEGER(2) XDS image using the CBF_BYTE_OFFSET, CBF_PACKED or CBF_PACKED_V2 compressions for the 32-bit data. The BYTE_OFFSET algorithm is a variant of the September 2006 version by W. Kabsch which was based on a suggestion by A. Hammersley and which was further modified by H. Bernstein. The file named FILNAM is opened on the logical unit TAPIN and FCB_NEXT_BINARY is used to skip to the next binary image. The binary image is then decompressed to produce an XDS 16-bit integer image array IFRAME which is NX by NY. The dimensions must agree with the dimensions specified in MIME header. The conversion from a 32-bit integer I32 to 16-bit XDS pixel I16 is done as per W. Kabsch as follows: The value I32 is limited to the range -1023 =< I32 =< 1048576. If I32 is outside that range it is truncated to the closer boundary. The generate I16, the 16-bit result, if I32 > 32767, it is divided by 32 (producing a number between 1024 and 32768), and then negated (producing a number between -1024 and -32768). For CBF_BYTE_OFFSET this conversion can be done on the fly directly into the target array IFRAME, but for the CBF_PACKED or CBF_PACKED_V2, the full 32 bit precision is needed during the decompression, forcing the use of an intermediate INTEGER(4) array JFRAME to hold the 32-bit image in that case. The image file is closed after reading one image. ARGUMENTS FILNAM The character string name of the image file to be opened. TAPIN The INTEGER Fortran device unit number assigned to image file. NX The INTEGER fast dimension of the image array. NY The INTEGER slow dimension of the image array. IFRAME The INTEGER(2) XDS image array. JFRAME The INTEGER(4) 32-bit image scratch array needed for CBF_PACKED or CBF_PACKED_V2 images. RETURN VALUE Returns 0 if the function is successful, CBF_FORMAT (=1) if it cannot handle this CBF format (not implemented), -1 if it cannot determine endian architecture of this machine, -2: if it cannot open the image file, -3: if it finds the wrong image format and -4 if it cannot read the image. ---------------------------------------------------------------------- 2.5.13 FCB_SKIP_WHITESPACE INTERFACE INTEGER FUNCTION FCB_SKIP_WHITESPACE(TAPIN,LAST_CHAR, & FCB_BYTES_IN_REC,BYTE_IN_FILE,REC_IN_FILE,BUFFER,& LINE,N,LINELEN,ICUR,FRESH_LINE) INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC,N INTEGER, INTENT(INOUT):: BYTE_IN_FILE,REC_IN_FILE,LINELEN,ICUR, & FRESH_LINE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC),LINE(N), & LAST_CHAR END INTERFACE The function FCB_SKIP_WHITESPACE skips forward on the current INTEGER(1) byte array LINE of size N with valid data in LINE(1:LINELEN) from the current position ICUR moving over MIME header whitespace and comments, reading new lines into LINE if needed. The flag FRESH_LINE indicates that a fresh line should be read on entry. ARGUMENTS TAPIN The INTEGER Fortran device unit number assigned to image file. LAST_CHAR The INTEGER(1) byte holding the ASCII value of the last character read for each line read. FCB_BYTES_IN_REC The INTEGER number of bytes in a record. BYTE_IN_FILE The INTEGER byte (counting from 1) of the byte to read. REC_IN_FILE The INTEGER record number (counting from 1) of next record to read. BUFFER The INTEGER(1) array of length FCB_BYTES_IN_REC to hold the appropriate record from TAPIN. LINE The INTEGER(1) array of length N to hold the line to be read from TAPIN. N The INTEGER dimension of LINE. LINELEN The INTEGER number of characters read into LINE. ICUR The INTEGER position within the line. FRESH_LINE The INTEGER flag that a fresh line is needed. RETURN VALUE Returns 0 if the function is successful. SEE ALSO 2.5.3 FCB_EXIT_BINARY 2.5.5 FCB_NEXT_BINARY 2.5.6 FCB_OPEN_CIFIN 2.5.7 FCB_DECOMPRESS: FCB_DECOMPRESS_PACKED_I2, FCB_DECOMPRESS_PACKED_I4, FCB_DECOMPRESS_PACKED_3D_I2, FCB_DECOMPRESS_PACKED_3D_I4 2.5.9 FCB_READ_BYTE ---------------------------------------------------------------------- 3. File format 3.1 General description With the exception of the binary sections, a CBF file is an mmCIF-format ASCII file, so a CBF file with no binary sections is a CIF file. An imgCIF file has any binary sections encoded as CIF-format ASCII strings and is a CIF file whether or not it contains binary sections. In most cases, CBFlib can also be used to access normal CIF files as well as CBF and imgCIF files. 3.2 Format of the binary sections Before getting to the binary data itself, there are some preliminaries to allow a smooth transition from the conventions of CIF to those of raw or encoded streams of "octets" (8-bit bytes). The binary data is given as the essential part of a specially formatted semicolon-delimited CIF multi-line text string. This text string is the value associated with the tag "_array_data.data". The specific format of the binary sections differs between an imgCIF and a CBF file. 3.2.1 Format of imgCIF binary sections Each binary section is encoded as a semicolon-delimited string. Within the text string, the conventions developed for transmitting email messages including binary attachments are followed. There is secondary ASCII header information, formatted as Multipurpose Internet Mail Extensions (MIME) headers (see RFCs 2045-49 by Freed, et al.). The boundary marker for the beginning of all this is the special string --CIF-BINARY-FORMAT-SECTION-- at the beginning of a line. The initial "--" says that this is a MIME boundary. We cannot put "###" in front of it and conform to MIME conventions. Immediately after the boundary marker are MIME headers, describing some useful information we will need to process the binary section. MIME headers can appear in different orders, and can be very confusing (look at the raw contents of a email message with attachments), but there is only one header which is has to be understood to process an imgCIF: "Content-Transfer-Encoding". If the value given on this header is "BINARY", this is a CBF and the data will be presented as raw binary, containing a count (in the header described in 3.2.2 Format of CBF binary sections) so that we'll know when to start looking for more information. If the value given for "Content-Transfer-Encoding" is one of the real encodings: "BASE64", "QUOTED-PRINTABLE", "X-BASE8", "X-BASE10" or "X-BASE16", the file is an imgCIF, and we'll need some other headers to process the encoded binary data properly. It is a good practice to give headers in all cases. The meanings of various encodings is given in the CBF extensions dictionary, cif_img_1.5.4.dic, as one html file, or as separate pages for each defintion. For certain compressions (e.g. CBF_PACKED) MIME headers are essential to determine the parameters of the compression. The full list of MIME headers recognized by and generated by CBFlib is: * Content-Type: * Content-Transfer-Encoding: * Content-MD5: * X-Binary-Size: * X-Binary-ID: * X-Binary-Element-Type: * X-Binary-Element-Byte-Order: * X-Binary-Number-of-Elements: * X-Binary-Size-Fastest-Dimension: * X-Binary-Size-Second-Dimension: * X-Binary-Size-Third-Dimension: * X-Binary-Size-Padding: * Content-Type: The "Content-Type" header tells us what sort of data we have (currently always "application/octet-stream" for a miscellaneous stream of binary data) and, optionally, the conversions that were applied to the original data. The default is to compress the data with the "CBF-PACKED" algorithm. The Content-Type may be any of the discrete types permitted in RFC 2045; 'application/octet-stream' is recommended. If an octet stream was compressed, the compression should be specified by the parameter 'conversions="X-CBF_PACKED"' or the parameter 'conversions="X-CBF_PACKED_V2"' or the parameter 'conversions="X-CBF_CANONICAL"' or the parameter 'conversions="X-CBF_BYTE_OFFSET"' If the parameter 'conversions="X-CBF_PACKED"' or 'conversions="X-CBF_PACKED_V2"' is given it may be further modified with the parameters '"uncorrelated_sections"' or '"flat"' If the '"uncorrelated_sections"' parameter is given, each section will be compressed without using the prior section for averaging. If the '"flat"' parameter is given, each the image will be treated as one long row. * Content-Transfer-Encoding: The "Content-Transfer-Encoding" may be 'BASE64', 'Quoted-Printable', 'X-BASE8', 'X-BASE10', 'X-BASE16' or 'X-BASE32K', for an imgCIF or 'BINARY' for a CBF. The octal, decimal and hexadecimal transfer encodings are provided for convenience in debugging and are not recommended for archiving and data interchange. In a CIF, one of the parameters 'charset=us-ascii', 'charset=utf-8' or 'charset=utf-16' may be used on the Content-Transfer-Encoding to specify the character set used for the external presentation of the encoded data. If no charset parameter is given, the character set of the enclosing CIF is assumed. In any case, if a BOM flag is detected (FE FF for big-endian UTF-16, FF FE for little-endian UTF-16 or EF BB BF for UTF-8) is detected, the indicated charset will be assumed until the end of the encoded data or the detection of a different BOM. The charset of the Content-Transfer-Encoding is not the character set of the encoded data, only the character set of the presentation of the encoded data and should be respecified for each distinct STAR string. In an imgCIF file, the encoded binary data begins after the empty line terminating the header. In an imgCIF file, the encoded binary data ends with the terminating boundary delimiter '\n--CIF-BINARY-FORMAT-SECTION----' in the currently effective charset or with the '\n; ' that terminates the STAR string. In a CBF, the raw binary data begins after an empty line terminating the header and after the sequence: Octet Hex Decimal Purpose 0 0C 12 (ctrl-L) Page break 1 1A 26 (ctrl-Z) Stop listings in MS-DOS 2 04 04 (Ctrl-D) Stop listings in UNIX 3 D5 213 Binary section begins None of these octets are included in the calculation of the message size or in the calculation of the message digest. * Content-MD5: An MD5 message digest may, optionally, be used. The 'RSA Data Security, Inc. MD5 Message-Digest Algorithm' should be used. No portion of the header is included in the calculation of the message digest. The optional "Content-MD5" header provides a much more sophisticated check on the integrity of the binary data than size checks alone can provide. * X-Binary-Size: The "X-Binary-Size" header specifies the size of the equivalent binary data in octets. This is the size after any compressions, but before any ascii encodings. This is useful in making a simple check for a missing portion of this file. The 8 bytes for the Compression type (see below) are not counted in this field, so the value of "X-Binary-Size" is 8 less than the quantity in bytes 12-19 of the raw binary data ( 3.2.2 Format of CBF binary sections). * X-Binary-ID: The "X-Binary-ID" header should contain the same value as was given for "_array_data.binary_id". * X-Binary-Element-Type: The "X-Binary-Element-Type" header specifies the type of binary data in the octets, using the same descriptive phrases as in _array_structure.encoding_type. The default value is 'unsigned 32-bit integer'. * X-Binary-Element-Byte-Order: The "X-Binary-Element-Byte-Order" can specify either '"BIG_ENDIAN"' or '"LITTLE_ENDIAN"' byte order of the image data. CBFlib only writes '"LITTLE_ENDIAN"', and in general can only process LITTLE_ENDIAN even on machines that are BIG_ENDIAN. * X-Binary-Number-of-Elements: The "X-Binary-Number-of-Elements" specifies the number of elements (not the number of octets) in the decompressed, decoded image. * X-Binary-Size-Fastest-Dimension: The optional "X-Binary-Size-Fastest-Dimension" specifies the number of elements (not the number of octets) in one row of the fastest changing dimension of the binary data array. This information must be in the MIME header for proper operation of some of the decompression algorithms. * X-Binary-Size-Second-Dimension: The optional "X-Binary-Size-Second-Dimension" specifies the number of elements (not the number of octets) in one column of the second-fastest changing dimension of the binary data array. This information must be in the MIME header for proper operation of some of the decompression algorithms. * X-Binary-Size-Third-Dimension: The optional "X-Binary-Size-Third-Dimension" specifies the number of sections for the third-fastest changing dimension of the binary data array. * X-Binary-Size-Padding: The optional "X-Binary-Size-Padding" specifies the size in octets of an optional padding after the binary array data and before the closing flags for a binary section. CBFlib always writes this padding as zeros, but this information should be in the MIME header for a binary section that uses padding, especially if non-zero padding is used. A blank line separator immediately precedes the start of the encoded binary data. Blank spaces may be added prior to the preceding "line separator" if desired (e.g. to force word or block alignment). Because CBFLIB may jump forward in the file from the MIME header, the length of encoded data cannot be greater than the value defined by "X-Binary-Size" (except when "X-Binary-Size" is zero, which means that the size is unknown), unless "X-Binary-Size-Padding" is specified to allow for the padding. At exactly the byte following the full binary section as defined by the length and padding values is the end of binary section identifier. This consists of the line-termination sequence followed by: --CIF-BINARY-FORMAT-SECTION---- ; with each of these lines followed by a line-termination sequence. This brings us back into a normal CIF environment. This identifier is, in a sense, redundant because the binary data length value tells the a program how many bytes to jump over to the end of the binary data. This redundancy has been deliberately added for error checking, and for possible file recovery in the case of a corrupted file and this identifier must be present at the end of every block of binary data. 3.2.2 Format of CBF binary sections In a CBF file, each binary section is encoded as a ;-delimited string, starting with an arbitrary number of pure-ASCII characters. Note: For historical reasons, CIFlib has the option of writing simple header and footer sections: "START OF BINARY SECTION" at the start of a binary section and "END OF BINARY SECTION" at the end of a binary section, or writing MIME-type header and footer sections (3.2.1 Format of imgCIF binary sections). If the simple header is used, the actual ASCII text is ignored when the binary section is read. Use of the simple binary header is deprecated. The MIME header is recommended. Between the ASCII header and the actual CBF binary data is a series of bytes ("octets") to try to stop the listing of the header, bytes which define the binary identifier which should match the "binary_id" defined in the header, and bytes which define the length of the binary section. Octet Hex Decimal Purpose 1 0C 12 (ctrl-L) End of Page 2 1A 26 (ctrl-Z) Stop listings in MS-DOS 3 04 04 (Ctrl-D) Stop listings in UNIX 4 D5 213 Binary section begins 5..5+n-1 Binary data (n octets) NOTE: When a MIME header is used, only bytes 5 through 5+n-1 are considered in computing the size and the message digest, and only these bytes are encoded for the equivalent imgCIF file using the indicated Content-Transfer-Encoding. If no MIME header has been requested (a deprecated use), then bytes 5 through 28 are used for three 8-byte words to hold the binary_id, the size and the compression type: 5..12 Binary Section Identifier (See _array_data.binary_id) 64-bit, little endian 13..20 The size (n) of the binary section in octets (i.e. the offset from octet 29 to the first byte following the data) 21..28 Compression type: CBF_NONE 0x0040 (64) CBF_CANONICAL 0x0050 (80) CBF_PACKED 0x0060 (96) CBF_BYTE_OFFSET 0x0070 (112) CBF_PREDICTOR 0x0080 (128) ... The binary data then follows in bytes 29 through 29+n-1. The binary characters serve specific purposes: o The Control-L (from-feed) will terminate printing of the current page on most operating systems. o The Control-Z will stop the listing of the file on MS-DOS type operating systems. o The Control-D will stop the listing of the file on Unix type operating systems. o The unsigned byte value 213 (decimal) is binary 11010101. (Octal 325, and hexadecimal D5). This has the eighth bit set so can be used for error checking on 7-bit transmission. It is also asymmetric, but with the first bit also set in the case that the bit order could be reversed (which is not a known concern). o (The carriage return, line-feed pair before the START_OF_BIN and other lines can also be used to check that the file has not been corrupted e.g. by being sent by ftp in ASCII mode.) At present four compression schemes are implemented are defined: CBF_NONE (for no compression), CBF_CANONICAL (for and entropy-coding scheme based on the canonical-code algorithm described by Moffat, et al. (International Journal of High Speed Electronics and Systems, Vol 8, No 1 (1997) 179-231)), CBF_PACKED or CBF_PACKED_V2 for J. P. Abrahams CCP4-style packing schemes and CBF_BYTE_OFFSET for a simple byte_offset compression scheme.. Other compression schemes will be added to this list in the future. For historical reasons, CBFlib can read or write a binary string without a MIME header. The structure of a binary string with simple headers is: Byte ASCII Decimal Description symbol value 1 ; 59 Initial ; delimiter 2 carriage-return 13 3 line-feed 10 The CBF new-line code is carriage-return, line-feed 4 S 83 5 T 84 6 A 65 7 R 83 8 T 84 9 32 10 O 79 11 F 70 12 32 13 B 66 14 I 73 15 N 78 16 A 65 17 R 83 18 Y 89 19 32 20 S 83 21 E 69 22 C 67 23 T 84 24 I 73 25 O 79 26 N 78 27 carriage-return 13 28 line-feed 10 29 form-feed 12 30 substitute 26 Stop the listing of the file in MS-DOS 31 end-of-transmission 4 Stop the listing of the file in unix 32 213 First non-ASCII value 33 .. 40 Binary section identifier (64-bit little-endien) 41 .. 48 Offset from byte 57 to the first ASCII character following the binary data 49 .. 56 Compression type 57 .. 57 + n-1 Binary data (nbytes) 57 + n carriage-return 13 58 + n line-feed 10 59 + n E 69 60 + n N 78 61 + n D 68 62 + n 32 63 + n O 79 64 + n F 70 65 + n 32 66 + n B 66 67 + n I 73 68 + n N 78 69 + n A 65 70 + n R 83 71 + n Y 89 72 + n 32 73 + n S 83 74 + n E 69 75 + n C 67 76 + n T 84 77 + n I 73 78 + n O 79 79 + n N 78 80 + n carriage-return 13 81 + n line-feed 10 82 + n ; 59 Final ; delimiter 3.3 Compression schemes Two schemes for lossless compression of integer arrays (such as images) have been implemented in this version of CBFlib: 1. An entropy-encoding scheme using canonical coding 2. A CCP4-style packing scheme. Both encode the difference (or error) between the current element in the array and the prior element. Parameters required for more sophisticated predictors have been included in the compression functions and will be used in a future version of the library. 3.3.1 Canonical-code compression The canonical-code compression scheme encodes errors in two ways: directly or indirectly. Errors are coded directly using a symbol corresponding to the error value. Errors are coded indirectly using a symbol for the number of bits in the (signed) error, followed by the error iteslf. At the start of the compression, CBFlib constructs a table containing a set of symbols, one for each of the 2^n direct codes from -2^(n-1) .. 2^(n-1)-1, one for a stop code, and one for each of the maxbits -n indirect codes, where n is chosen at compress time and maxbits is the maximum number of bits in an error. CBFlib then assigns to each symbol a bit-code, using a shorter bit code for the more common symbols and a longer bit code for the less common symbols. The bit-code lengths are calculated using a Huffman-type algorithm, and the actual bit-codes are constructed using the canonical-code algorithm described by Moffat, et al. (International Journal of High Speed Electronics and Systems, Vol 8, No 1 (1997) 179-231). The structure of the compressed data is: Byte Value 1 .. 8 Number of elements (64-bit little-endian number) 9 .. 16 Minimum element 17 .. 24 Maximum element 25 .. 32 (reserved for future use) 33 Number of bits directly coded, n 34 Maximum number of bits encoded, maxbits 35 .. 35+2^n-1 Number of bits in each direct code 35+2^n Number of bits in the stop code 35+2^n+1 .. 35+2^n+maxbits-n Number of bits in each indirect code 35+2^n+maxbits-n+1 .. Coded data 3.3.2 CCP4-style compression Starting with CBFlib 0.7.7, CBFlib supports three variations on CCP4-style compression: the "flat" version supported in versions of CBFlib prior to release 0.7.7, as well as both version 1 and version 2 of J. P. Abrahams "pack_c" compression. The CBF_PACKED and CBF_PACKED_V2 compression and decompression code incorporated in CBFlib is derived in large part from the J. P. Abrahams pack_c.c compression code in CCP4. This code is incorporated in CBFlib under the GPL and the LGPL with both the permission Jan Pieter Abrahams, the original author of pack_c.c (email from Jan Pieter Abrahams of 15 January 2007) and of the CCP4 project (email from Martyn Winn on 12 January 2007). The cooperation of J. P. Abrahams and of the CCP4 project is gratefully acknowledged. The basis for all three versions is a scheme to pack offsets (differences from a base value) into a small-endian bit stream. The stream is organized into blocks. Each block begins with a header of 6 bits in the flat packed version and version 1 of J. P. Abrahams compression, and 7 bits in version 2 of J. P. Abrahams compression. The header gives the number of offsets that follow and the number of bits in each offset. Each offset is a signed, 2's complement integer. The first 3 bits in the header gives the logarithm base 2 of the numer of offsets that follow the header. For example, if a header has a zero in bits, only one offset follows the header. If those same bits contain the number n, the number of offsets in the block is 2n. The following 3 bits (flat and version 1) or 4 bits (version 2) contains a number giving an index into a table of bit-lengths for the offsets. All offsets in a given block are of the same length. Bits 3 .. 5 (flat and version 1) or bits 3 .. 6 (version 2) encode the number of bits in each offset as follows: Value in Number of bits Number of bits bits 3 .. 5 in each V1 offset in each V2 offset 0 0 0 1 4 3 2 5 4 3 6 5 4 7 6 5 8 7 6 16 8 7 max 9 8 10 9 11 10 12 11 13 12 14 13 15 14 16 15 max The value "max" is determined by the compression version and the element size. If the compression used is "flat", then "max" is 65. If the compression is version 1 or version 2 of the JPA compression, then "max" is the number of bits in each element, i.e. 8, 16, 32 or 64 bits. The major difference between the three variants of packed compression is the choice of the base value from which the offset is measured. In all cases the first offset is measured from zero, i.e. the first offset is the value of the first pixel of the image. If "flat" is chosen or if the dimensions of the data array are not given, then the remaining offset are measure against the prior value, making it similar in approach to the "byte offset" compression described in section 3.3.3 Byte offset compression, but with a more efficient representation of the offsets. In version 1 and version 2 of the J. P. Abrahams compression, the offsets are measured against an average of earlier pixels. If there is only one row only the prior pxiel is used, starting with the same offsets for that row as for "flat". After the first row, three pixels from the prior row are used in addition to using the immediately prior pixel. If there are multiple sections, and the sections are marked as correlated, after the first section, 4 pixels from the prior section are included in the average. The CBFlib code differs from the pack_c code in the handling of the beginnings and ends of rows and sections. The pack_c code will use pixels from the other side of the image in doing the averaging. The CBFlib code drops pixels from the other side of the image from the pool. The details follow. After dealing with the special case of the first pixel, The algorithm uses an array of pointers, trail_char_data. The assignment of pixels to the pool to be averaged begins with trail_char_data[0] points to the pixel immediately prior to the next pixel to be processed, either in the same row (fastest index) or, at the end of the prior row if the next data element to be processed is at the end of a row. The location of the pixel pointed to by trail_char_data[0] is used to compute the locations of the other pixels in the pool. It will be dropped from the pool before averaging if it is on the opposite side of the image. The pool will consist of 1, 2, 4 or 8 pixels. Assume ndim1, ndim2, ndim3 are the indices of the same pixel as trail_char_data[0] points to. These indices are incremented to be the indices of the next pixel to be processed before populating trail_char_data. On exit, trail_char_data[0 .. 7] will have been populated with pointers to the pixels to be used in forming the average. Pixels that will not be used will be set to NULL. Note that trail_char_data[0] may be set to NULL. If we mark the next element to be processed with a "*" and the entries in trail_char_data with their array indices 0 .. 7, the possible patterns of settings in the general case are: current section: - - - - 0 * - - - - - - - - 3 2 1 - - - - - - - - - - - - - prior section: - - - - - 4 - - - - - - - - 7 6 5 - - - - - - - - - - - - - If there is no prior section (i.e. ndim3 is 0, or the CBF_UNCORRELATED_SECTIONS flag is set to indicate discontinuous sections), the values for trail_char_data[4 .. 7] will all be NULL. When there is a prior section, trail_char_data[5..7] are pointers to the pixels immediately below the elements pointed to by trail_char_data[1..3], except trail_char_data[4] is one element further along its row to be directly below the next element to be processed. The first element of the first row of the first section is a special case, with no averaging. In the first row of the first section (ndim2 == 0, and ndim3 == 0), after the first element (ndim1 > 0), only trail_char_data[0] is used current section: - - - - 0 * - - - - For subsequent rows of the first section (ndim2 > 0, and ndim3 == 0), for the first element (ndim1 == 0), two elements from the prior row are used: current section: * - - - - - - - - - 2 1 - - - - - - - - - - - - - - - - - - while for element after the first element, but before the last element of the row, a full set of 4 elements is used: current section: - - - - 0 * - - - - - - - - 3 2 1 - - - - - - - - - - - - - For the last element of a row (ndim1 == dim1-1), two elements are used current section: - - - - - - - - 0 * - - - - - - - - - 2 - - - - - - - - - - For sections after the first section, provided the CBF_UNCORRELATED_SECTIONS flag is not set in the compression, for each non-NULL entry in trail_char_data [0..3] an entry is made in trail_char_data [4..7], except for the first element of the first row of a section. In that case an entry is made in trail_char_data[4]. The structure of the compressed data is: Byte Value 1 .. 8 Number of elements (64-bit little-endian number) 9 .. 16 Minumum element (currently unused) 17 .. 24 Maximum element (currently unused) 25 .. 32 (reserved for future use) 33 .. Coded data 3.3.3 Byte_offset compression Starting with CBFlib 0.7.7, CBFlib supports a simple and efficient "byte_offset" algorithm originally proposed by Andy Hammerley and modified by Wolgang Kabsch and Herbert Bernstein. The original proposal was called "byte_offsets". We distinguish this variant by calling it "byte_offset". The major differences are that the "byte_offsets" algorithm started with explicit storage of the first element of the array as a 4-byte signed two's integer, and checked for image edges to changes the selection of prior pixel. The CBFlib "byte_offset" alogorithm starts with an assumed zero before the first pixel and represents the value of the first pixel as an offset of whatever number of size is needed to hold the value, and for speed, treats the entire image as a simple linear array, allowing use of the last pixel of one row as the base against which to compute the offset for the first element of the next row. The algorithm is simple and easily implemented. This algorithm can never achieve better than a factor of two compression relative to 16-bit raw data or 4 relative to 32-bit raw data, but for most diffraction data the compression will indeed be very close to these ideal values. It also has the advantage that integer values up to 32 bits (or 31 bits and sign) may be stored efficiently without the need for special over-load tables. It is a fixed algorithm which does not need to calculate any image statistics, so is fast. The algorithm works because of the following property of almost all diffraction data and much other image data: The value of one element tends to be close to the value of the adjacent elements, and the vast majority of the differences use little of the full dynamic range. However, noise in experimental data means that run-length encoding is not useful (unless the image is separated into different bit-planes). If a variable length code is used to store the differences, with the number of bits used being inversely proportional to the probability of occurrence, then compression ratios of 2.5 to 3.0 may be achieved. However, the optimum encoding becomes dependent of the exact properties of the image, and in particular on the noise. Here a lower compression ratio is achieved, but the resulting algorithm is much simpler and more robust. The "byte_offset" compression algorithm is the following: 1. Start with a base pixel value of 0. 2. Compute the difference delta between the next pixel value and the base pixel value. 3. If -127 =< delta =< 127, output delta as one byte, make the current pixel value the base pixel value and return to step 2. 4. Otherwise output -128 (80 hex). 5. We still have to output delta. If -32767 =< delta =< 32767, output delta as a little_endian 16-bit quantity, make the current pixel value the base pixel value and return to step 2. 6. Otherwise output -32768 (8000 hex, little_endian, i.e. 00 then 80) 7. We still have to output delta. If -2147483647 =< delta =< 2147483647, output delta as a little_endian 32 bit quantity, make the current pixel value the base pixel value and return to step 2. 8. Otherwise output -2147483648 (80000000 hex, little_endian, i.e. 00, then 00, then 00, then 80) and then output the pixel value as a little-endian 64 bit quantity, make the current pixel value the base pixel value and return to step 2. The "byte_offset" decompression algorithm is the following: 1. Start with a base pixel value of 0. 2. Read the next byte as delta 3. If -127 =< delta =< 127, add delta to the base pixel value, make that the new base pixel value, place it on the output array and return to step 2. 4. If delta is 80 hex, read the next two bytes as a little_endian 16-bit number and make that delta. 5. If -32767 =< delta =< 32767, add delta to the base pixel value, make that the new base pixel value, place it on the output array and return to step 2. 6. If delta is 8000 hex, read the next 4 bytes as a little_endian 32-bit number and make that delta 7. If -2147483647 =< delta =< 2147483647, add delta to the base pixel value, make that the new base pixel value, place it on the output array and return to step 2. 8. If delta is 80000000 hex, read the next 8 bytes as a little_endian 64-bit number and make that delta, add delta to the base pixel value, make that the new base pixel value, place it on the output array and return to step 2. Let us look at an example, of two 1000 x 1000 flat field images presented as a mimimal imgCIF file. The first image uses 32-bit unsigned integers and the second image uses 16-bit unsigned integers. The imgCIF file begins with some identifying comments (magic numbers) to track the version of the dictionary and library: ###CBF: VERSION 1.5 # CBF file written by CBFlib v0.7.7 This is followed by the necessary syntax to start a CIF data block and by whatever tags and values are appropriate to describe the experiment. The minimum is something like data_testflat eventually we come to the actual binary data, which begins the loop header for the array_data category loop_ _array_data.data with any additional tags needed, and then the data itself, which starts with the mini-header: ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_BYTE_OFFSET" Content-Transfer-Encoding: BINARY X-Binary-Size: 1000002 X-Binary-ID: 1 X-Binary-Element-Type: "unsigned 32-bit integer" X-Binary-Element-Byte-Order: LITTLE_ENDIAN Content-MD5: +FqUJGxXhvCijXMFHC0kaA== X-Binary-Number-of-Elements: 1000000 X-Binary-Size-Fastest-Dimension: 1000 X-Binary-Size-Second-Dimension: 1000 X-Binary-Size-Padding: 4095 followed by an empty line and then the sequence of characters: ^L^Z^D followed immediately by the compressed data. The binary data begins with the hex byte 80 to flag the need for a value that will not fit in one byte. That is followed by the small_endian hex value 3E8 saying that the first delta is 1000. Then 999,999 bytes of zero follow, since this is a flat field, with all values equal to zero. That gives us our entire 1000x1000 compressed flat field. However, because we asked for 4095 bytes of padding, there is an additional 4095 bytes of zero that are not part of the compressed field. They are just pad and can be ignored. Finally, after the pad, the CIF text field that began with ; --CIF-BINARY-FORMAT-SECTION-- is completed with --CIF-BINARY-FORMAT-SECTION---- ; notice the extra -- The second flat field then follows, with a very similar mini-header: ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_BYTE_OFFSET" Content-Transfer-Encoding: BINARY X-Binary-Size: 1000002 X-Binary-ID: 2 X-Binary-Element-Type: "unsigned 16-bit integer" X-Binary-Element-Byte-Order: LITTLE_ENDIAN Content-MD5: +FqUJGxXhvCijXMFHC0kaA== X-Binary-Number-of-Elements: 1000000 X-Binary-Size-Fastest-Dimension: 1000 X-Binary-Size-Second-Dimension: 1000 X-Binary-Size-Padding: 4095 ^L^Z^D The only difference is that we have declared this array to be 16-bit and have chosen a different binary id (2 instead of 1). Even the checksum is the same. 4. Installation CBFlib should be built on a disk with at least 200 megabytes of free space. CBFlib.tar.gz is a "gzipped" tar of the code as it now stands. Place the gzipped tar in the directory that is intended to contain a new directory, named CBFlib_0.7.5 (the "top-level" directory) and uncompress it with gunzip and unpack it with tar: gunzip CBFlib.tar.gz tar xvf CBFLIB.tar As with prior releases, to run the test programs, you will also need Paul Ellis's sample MAR345 image, example.mar2300, and Chris Nielsen's sample ADSC Quantum 315 image, mb_LP_1_001.img as sample data. Both these files will be extracted by the Makefile from CBFlib_0.7.7_Data_Files. Do not download copies into the top level directory. After unpacking the archive, the top-level directory should contain a makefile: Makefile Makefile for unix and the subdirectories: src/ CBFLIB source files include/ CBFLIB header files m4/ CBFLIB m4 macro files (used to build .f90 files) examples/ Example program source files doc/ Documentation lib/ Compiled CBFLIB library bin/ Executable example programs html_images/ JPEG images used in rendering the HTML files For instructions on compiling and testing the library, go to the top-level directory and type: make The CBFLIB source and header files are in the "src" and "include" subdirectories. The FCBLIB source and m4 files are in the "src" and "m4" subdirectories. The files are: src/ include/ m4/ Description cbf.c cbf.h CBFLIB API functions cbf_alloc.c cbf_alloc.h Memory allocation functions cbf_ascii.c cbf_ascii.h Function for writing ASCII values cbf_binary.c cbf_binary.h Functions for binary values cbf_byte_offset.c cbf_byte_offset.h Byte-offset compression cbf_canonical.c cbf_canonical.h Canonical-code compression cbf_codes.c cbf_codes.h Encoding and message digest functions cbf_compress.c cbf_compress.h General compression routines cbf_context.c cbf_context.h Control of temporary files cbf_file.c cbf_file.h File in/out functions cbf_lex.c cbf_lex.h Lexical analyser cbf_packed.c cbf_packed.h CCP4-style packing compression cbf_predictor.c cbf_predictor.h Predictor-Huffman compression (not implemented) cbf_read_binary.c cbf_read_binary.h Read binary headers cbf_read_mime.c cbf_read_mime.h Read MIME-encoded binary sections cbf_simple.c cbf_simple.h Higher-level CBFlib functions cbf_string.c cbf_string.h Case-insensitive string comparisons cbf_stx.c cbf_stx.h Parser (generated from cbf.stx.y) cbf_tree.c cbf_tree.h CBF tree-structure functions cbf_uncompressed.c cbf_uncompressed.h Uncompressed binary sections cbf_write.c cbf_write.h Functions for writing cbf_write_binary.c cbf_write_binary.h Write binary sections cbf.stx.y bison grammar to define cbf_stx.c (see WARNING) md5c.c md5.h RSA message digest software from mpack global.h fcb_atol_wcnt.f90 Function to convert a string to an integer fcb_ci_strncmparr.f90 Function to do a case-insensitive comparison of a string to a byte array fcb_nblen_array.f90 Function to determine the non-blank length of a byte array fcb_read_byte.f90 Function to read a single byte fcb_read_line.f90 Function to read a line into a byte array fcb_skip_whitespace.f90 Function to skip whitespace and comments in a MIME header fcb_exit_binary.m4 Function to skip past the end of the current binary text field fcb_next_binary.m4 Function to skip to the next binary fcb_open_cifin.m4 Function to open a CBF file for reading fcb_packed.m4 Functions to read a JPA CCP4 compressed image fcb_read_bits.m4 Functions to read nay number of bits as an integer fcb_read_image.m4 Functions to read the next image in I2, I4, 3D_I2 and 3D_I4 format fcb_read_xds_i2.m4 Function to read a single xds image. fcblib_defines.m4 General m4 macro file for FCBLIB routines. In the "examples" subdirectory, there are 2 additional files used by the example programs (section 5) for reading MAR300, MAR345 or ADSC CCD images: img.c img.h Simple image library and the example programs themselves: makecbf.c Make a CBF file from an image img2cif.c Make an imgCIF or CBF from an image cif2cbf.c Copy a CIF/CBF to a CIF/CBF convert_image.c Convert an image file to a cbf using a template file cif2c.c Convert a template cbf file into a function to produce the same template in an internal cbf data structure testcell.C Exercise the cell functions as well as three template files: template_adscquantum4_2304x2304.cbf, template_mar345_2300x2300.cbf, and template_adscquantum315_3072x3072.cbf. Two additional examples (test_fcb_read_image.f90 and test_xds_binary.f90) are created from two files (test_fcb_read_image.m4 and test_xds_binary.m4) in the m4 directory. The documentation files are in the "doc" subdirectory: CBFlib.html This document (HTML) CBFlib.txt This document (ASCII) CBFlib_NOTICES.html Important NOTICES -- PLEASE READ CBFlib_NOTICES.txt Important NOTICES -- PLEASE READ gpl.txt GPL -- PLEASE READ lgpl.txt LGPL -- PLEASE READ cbf_definition_rev.txt Draft CBF/ImgCIF definition (ASCII) cbf_definition_rev.html Draft CBF/ImgCIF definition (HTML) cif_img.html CBF/ImgCIF extensions dictionary (HTML) cif_img.dic CBF/ImgCIF extensions dictionary (ASCII) ChangeLog,html Summary of change history (HTML) ChangeLog Summary of change history (ASCII) 5. Example programs The example programs makecbf.c, img2cif.c and convert_image.c read an image file from a MAR300, MAR345 or ADSC CCD detector and then uses CBFlib to convert it to CBF format (makecbf) or either imgCIF or CBF format (img2cif). makecbf writes the CBF-format image to disk, reads it in again, and then compares it to the original. img2cif just writes the desired file. makecbf works only from stated files on disk, so that random I/O can be used. img2cif includes code to process files from stdin and to stdout. convert_image reads a template as well as the image file and produces a complete CBF. The program convert_minicbf reads a minimal CBF file with just and image and some lines of text specifying the parameters of the data collection as done at SLS and combines the result with a template to produce a full CBF. The program cif2cbf can be used to convert among carious compression and encoding schemes. The program sauter_test.C is a C++ test program contributed by Nick Sauter to help in resolving a memory leak he found. The programs adscimg2cbf and cbf2adscimg are a "jiffies" contributed by Chris Nielsen of ADSC to convert ADSC images to imgCIF/CBF format and vice versa. makecbf.c is a good example of how many of the CBFlib functions can be used. To compile makecbf and the other example programs use the Makefile in the top-level directory: make all This will place the programs in the bin directory. makecbf To run makecbf with the example image, type: ./bin/makecbf example.mar2300 test.cbf The program img2cif has the following command line interface: img2cif [-i input_image] \ [-o output_cif] \ [-c {p[acked]|c[annonical]|[n[one]}] \ [-m {h[eaders]|n[oheaders]}] \ [-d {d[igest]|n[odigest]}] \ [-e {b[ase64]|q[uoted-printable]| \ d[ecimal]|h[exadecimal]|o[ctal]|n[one]}] \ [-b {f[orward]|b[ackwards]}] \ [input_image] [output_cif] the options are: -i input_image (default: stdin) the input_image file in MAR300, MAR345 or ADSC CCD detector format is given. If no input_image file is specified or is given as "-", an image is copied from stdin to a temporary file. -o output_cif (default: stdout) the output cif (if base64 or quoted-printable encoding is used) or cbf (if no encoding is used). if no output_cif is specified or is given as "-", the output is written to stdout -c compression_scheme (packed, canonical or none, default packed) -m [no]headers (default headers for cifs, noheaders for cbfs) selects MIME (N. Freed, N. Borenstein, RFC 2045, November 1996) headers within binary data value text fields. -d [no]digest (default md5 digest [R. Rivest, RFC 1321, April 1992 using"RSA Data Security, Inc. MD5 Message-Digest Algorithm"] when MIME headers are selected) -e encoding (base64, quoted-printable, decimal, hexadecimal, octal or none, default: base64) specifies one of the standard MIME encodings (base64 or quoted-printable) or a non-standard decimal, hexamdecimal or octal encoding for an ascii cif or "none" for a binary cbf -b direction (forward or backwards, default: backwards) specifies the direction of mapping of bytes into words for decimal, hexadecimal or octal output, marked by '>' for forward or '<' for backwards as the second character of each line of output, and in '#' comment lines. cif2cbf The test program cif2cbf uses many of the same command line options as img2cif, but accepts either a CIF or a CBF as input instead of an image file: cif2cbf [-i input_cif] [-o output_cbf] \ [-u update_cif] \ [-c {p[acked]|c[annonical]|{b[yte_offset]}|\ {v[2packed}|{f[latpacked}[n[one]}] \ [-C highclipvalue] \ [-D ] \ [-I {0|2|4|8}] \ [-R {0|4|8}] \ [-L {0|4|8}] \ [-m {h[eaders]|noh[eaders]}] \ [-m {d[imensions]|nod[imensions}] \ [-d {d[igest]|n[odigest]|w[arndigest]}] \ [-B {read|liberal|noread}] [-B {write|nowrite}] \ [-S {read|noread}] [-S {write|nowrite}] \ [-T {read|noread}] [-T {write|nowrite}] \ [-e {b[ase64]|q[uoted-printable]|\ d[ecimal]|h[examdecimal|o[ctal]|n[one]}] \ [-b {f[orward]|b[ackwards]}\ [-p {1|2|4}\ [-v dictionary]* [-w] [-W]\ [input_cif] [output_cbf] the options are: -i input_cif (default: stdin) the input file in CIF or CBF format. If input_cif is not specified or is given as "-", it is copied from stdin to a temporary file. -o output_cbf (default: stdout) the output cif (if base64 or quoted-printable encoding is used) or cbf (if no encoding is used). if no output_cif is specified or is given as "-", the output is written to stdout if the output_cbf is /dev/null, no output is written. -u update_cif (no default) and optional second input file in CIF or CBF format containing data blocks to be merged with data blocks from the primary input CIF or CBF The remaining options specify the characteristics of the output cbf. Most of the characteristics of the input cif are derived from context, except when modified by the -B, -S, -T, -v and -w flags. -b byte_order (forward or backwards, default forward (1234) on little-endian machines, backwards (4321) on big-endian machines -B [no]read or liberal (default noread) read to enable reading of DDLm style brackets liberal to accept whitespace for commas -B [no]write (default write) write to enable writing of DDLm style brackets -c compression_scheme (packed, canonical, byte_offset, v2packed, flatpacked or none, default packed) -C highclipvalue specifies a double precision value to which to clip the data -d [no]digest or warndigest (default md5 digest [R. Rivest, RFC 1321, April 1992 using"RSA Data Security, Inc. MD5 Message-Digest Algorithm"] when MIME headers are selected) -D test cbf_construct_detector -e encoding (base64, k, quoted-printable or none, default base64) specifies one of the standard MIME encodings for an ascii cif or "none" for a binary cbf -I 0 or integer element size specifies integer conversion of the data, 0 to use the input number of bytes, 2, 4 or 8 for short, long or long long output integers -L lowclipvalue specifies a double precision value to cut off the data from below -m [no]headers (default headers) selects MIME (N. Freed, N. Borenstein, RFC 2045, November 1996) headers within binary data value text fields. -m [nod]imensions (default dimensions) selects detailed recovery of dimensions from the input CIF for use in the MIME header of the output CIF -p K_of_padding (0, 1, 2, 4) for no padding after binary data 1023, 2047 or 4095 bytes of padding after binary data -R 0 or integer element size specifies real conversion of the data, 0 to use the input number of bytes, 4 or 8 for float or double output reals -S [no]read or (default noread) read to enable reading of whitespace and comments -S [no]write (default write) write to enable writing of whitespace and comments -T [no]read or (default noread) read to enable reading of DDLm style triple quotes -T [no]write (default write) write to enable writing of DDLm style triple quotes -v dictionary specifies a dictionary to be used to validate the input cif and to apply aliases to the output cif. This option may be specified multiple times, with dictionaries layered in the order given. -w process wide (2048 character) lines -W write wide (2048 character) lines convert_image The program convert_image requires two arguments: imagefile and cbffile. Those are the primary input and output. The detector type is extracted from the image file or from the command line, converted to lower case and used to construct the name of a template cbf file to use for the copy. The template file name is of the form template_name_columnsxrows. The full set of options is: convert_image [-i input_img] [-o output_cbf] [-p template_cbf]\ [-d detector name] -m [x|y|x=y] [-z distance] \ [-c category_alias=category_root]* \ [-t tag_alias=tag_root]* [-F] [-R] \ [input_img] [output_cbf] the options are: -i input_img (default: stdin) the input file as an image in smv, mar300, or mar345 format. If input_img is not specified or is given as "-", it is copied from stdin to a temporary file. -p template_cbf the template for the final cbf to be produced. If template_cbf is not specified the name is constructed from the first token of the detector name and the image size as template__x.cbf -o output_cbf (default: stdout ) the output cbf combining the image and the template. If the output_cbf is not specified or is given as "-", it is written to stdout. -d detectorname a detector name to be used if none is provided in the image header. -F when writing packed compression, treat the entire image as one line with no averaging -m [x|y|x=y] (default x=y, square arrays only) mirror the array in the x-axis (y -> -y) in the y-axis (x -> -x) or in x=y ( x -> y, y-> x) -r n rotate the array n times 90 degrees counter clockwise x -> y, y -> -x for each rotation, n = 1, 2 or 3 -R if setting a beam center, set reference values of axis settings as well as standard settings -z distance detector distance along Z-axis -c category_alias=category_root -t tag_alias=tagroot map the given alias to the given root, so that instead of outputting the alias, the root will be presented in the output cbf instead. These options may be repeated as many times as needed. convert_minicbf The program convert_minicbf requires two arguments: minicbf and cbffile. Those are the primary input and output. The detector type is extracted from the image file or from the command line, converted to lower case and used to construct the name of a template cbf file to use for the copy. The template file name is of the form template_name_columnsxrows. The full set of options is: convert_minicbf [-i input_cbf] [-o output_cbf] [-p template_cbf]\ [-q] [-C convention] \ [-d detector name] -m [x|y|x=y] [-z distance] \ [-c category_alias=category_root]* \ [-t tag_alias=tag_root]* [-F] [-R] \ [input_cbf] [output_cbf] the options are: -i input_cbf (default: stdin) the input file as a CBF with at least an image. -p template_cbf the template for the final cbf to be produced. If template_cbf is not specified the name is constructed from the first token of the detector name and the image size as template__x.cbf -o output_cbf (default: stdout ) the output cbf combining the image and the template. If the output_cbf is not specified or is given as "-", it is written to stdout. -q exit quickly with just the miniheader expanded after the data. No template is used. -Q exit quickly with just the miniheader unexpanded before the data. No template is used. -C convention convert the comment form of miniheader into the _array_data.header_convention convention _array_data.header_contents overriding any existing values -d detectorname a detector name to be used if none is provided in the image header. -F when writing packed compression, treat the entire image as one line with no averaging -m [x|y|x=y] (default x=y, square arrays only) mirror the array in the x-axis (y -> -y) in the y-axis (x -> -x) or in x=y ( x -> y, y-> x) -r n rotate the array n times 90 degrees counter clockwise x -> y, y -> -x for each rotation, n = 1, 2 or 3 -R if setting a beam center, set reference values of axis settings as well as standard settings -z distance detector distance along Z-axis -c category_alias=category_root -t tag_alias=tagroot map the given alias to the given root, so that instead of outputting the alias, the root will be presented in the output cbf instead. These options may be repeated as many times as needed. testreals, testflat and testflatpacked The example programs testreals, testflat and testflatpacked exercise the handling of reals, byte_offset compression and packed compression. Each is run without any arguments. testreals will read real images from the data file testrealin.cbf and write a file with real images in testrealout.cbf, which should be identical to testrealin.cbf. testflat and testflatpacked read 4 1000x1000 2D images and one 50x60x70 3D image and produce an output file that should be identical to the input. testflat reads testflatin.cbf and produces testflatout.cbf using CBF_BYTE_OFFSET compression. testflatpacked reads testflatpackedin.cbf and produces testflatpackedout.cbf. The images are: * A 1000 x 1000 array of 32-bit integers forming a flat field with all pixels set to 1000. * A 1000 x 1000 array of 16-bit integers forming a flat field with all pixels set to 1000. * A 1000 x 1000 array of 32-bit integers forming a flat field with all pixels set to 1000, except for -3 along the main diagonal and its transpose. * A 1000 x 1000 array of 16-bit integers forming a flat field with all pixels set to 1000, except for -3 along the main diagonal and its transpose. * A 50 x 60 x 70 array of 32-bit integers in a flat field of 1000, except for -3 along the main diagonal and the values i+j+k (counting from zero) every 1000th pixel test_fcb_read_image, test_xds_binary The example programs test_fcb_read_image and test_xds_binary are designed read the output of testflat and testflatpacked using the FCBlib routines in lib/libfcb. test_xds_binary reads only the first image and closes the file immediately. test_fcb_read_image reads all 5 images from the input file. The name of the input file should be provided on stdin, as in: * echo testflatout.cbf | bin/test_xds_binary * echo testflatpackedout.cbf | bin/test_xds_binary * echo testflatout.cbf | bin/test_fcb_read_image * echo testflatpackedout.cbf | bin/test_fcb_read_image In order to compile these programs correctly for the G95 compiler it is important to set the record size for reading to be no larger than the padding after binary images. This in controlled in Makefile by the line M4FLAGS = -Dfcb_bytes_in_rec=131072 which provides good performance for gfortran. For g95, this line must be changed to M4FLAGS = -Dfcb_bytes_in_rec=4096 sauter_test The program sauter_test.C is a C++ test program contributed by Nick Sauter to help in resolving a memory leak he found. The program is run as bin/sauter_test and should run long enough to allow a check with top to ensure that it has constant memory demands. In addition, starting with release 0.7.8.1, the addition of -DCBFLIB_MEM_DEBUG to the compiler flags will cause detailed reports on memory use to stderr to be reported. adscimg2cbf The example program adscimg2cbf accepts any number of raw or compressed ADSC images with .img, .img.gz, .img.bz2 or .img.Z extensions and converts each of them to an imgCIF/CBF file with a .cbf extension. adscimg2cbf [--flag[,modifier]] file1.img ... filen.img (creates file1.cbf ... filen.cbf) Image files may also be compressed (.gz, .bz2, .Z) Flags: --cbf_byte_offset Use BYTE_OFFSET compression (DEFAULT) --cbf_packed Use CCP4 packing (JPA) compression. --cbf_packed_v2 Use CCP4 packing version 2 (JPA) compression. --no_compression No compression. The following two modifiers can be appended to the flags (syntax: --flag,modifier): flat Flat (linear) images. uncorrelated Uncorrelated sections. adscimg2cbf The example program cbf2adscimg accepts any number of cbfs of ADSC images created by adscimg1cbf or convert_image and produces raw or compressed adsc image files with .img, .img.gz or .img.bz2 extensions. cbf2adscimg [--flag] file1.cbf ... filen.cbf (creates file1.img ... filen.img) Image files may be compressed on output: (.gz, .bz2) by using the flags below.\n"); Flags: --gz Output a .gz file (e.g., filen.img.gz). --bz2 Output a .bz2 file (e.g., filen.img.bz2). tiff2cbf The test program tiff2cbf converts a tiff data file to a cbf data file. The program converts the tiff data samples directly into a minicbf with the tiff header stored at the value of _array_data.header_contents. This conversion is supported for the sample formats SAMPLEFORMAT_UINT (unsigned integer data), SAMPLEFORMAT_INT (unsigned integer data), SAMPLEFORMAT_INT (signed integer data), SAMPLEFORMAT_IEEEFP (IEEE floating point data), SAMPLEFORMAT_COMPLEXINT (complex signed int) and SAMPLEFORMAT_COMPLEXIEEEFP (complex ieee floating). Conversions from these formats to other CBF formats can be handled by cif2cbf. If you wish to convert and xxx.tif written with IEEE floating point samples into a CBF with integer values compressed by byte-offset compression for use by XDS, creating an xxx_view.cbf with values clipped between 0 and 100, and an xxx_xds.cbf with unclipped values for processing: tiff2cbf xxx.tif xxx.cbf cif2cbf -I 4 -C 100. -L 0. -e n -c b -i xxx.cbf -o xxx_view.cbf cif2cbf -I 4 -e n -c b -i xxx.cbf -o xxx_xds.cbf ---------------------------------------------------------------------- ---------------------------------------------------------------------- Updated 29 March 2011. Contact: yaya at bernstein-plus-sons dot com ./CBFlib-0.9.2.2/doc/cif_img_1_2_4.html0000644000076500007650000067647611603702115015544 0ustar yayayaya cif_img.dic v1.2.4

# [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib] #

# imgCIF/CBF #

# Extensions Dictionary #

##############################################################################
#                                                                            #
#                       Image CIF Dictionary (imgCIF)                        #
#             and Crystallographic Binary File Dictionary (CBF)              #
#            Extending the Macromolecular CIF Dictionary (mmCIF)             #
#                                                                            #
#                              Version 1.2.4                                 #
#                              of 2001-07-14                                 #
#     by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook    #
#                                                                            #
# This dictionary was  adapted from the imgCIF Workshop, held at BNL Oct 1997#
# and the Crystallographic Binary File Format Draft Proposal by Andy         #
# Hammersley.  The first DDL 2.1 Version was created by  John Westbrook.     #
# This version was drafted by Herbert J. Bernstein and incorporates comments #
# by I. David Brown, John Westbrook, Brian McMahon, Bob Sweet, Paul Ellis,   #
# Harry Powell, Wilfred Li and others.                                       #
##############################################################################

                                                                            
data_cif_img.dic


    _dictionary.title           cif_img.dic
    _dictionary.version         1.2.3
    _dictionary.datablock_id    cif_img.dic

##############################################################################
#    CONTENTS
#
#        CATEGORY_GROUP_LIST
#
#        category  ARRAY_DATA
#
#                  _array_data.array_id
#                  _array_data.binary_id
#                  _array_data.data
#
#        category  ARRAY_ELEMENT_SIZE
#        
#                  _array_element_size.array_id
#                  _array_element_size.index
#                  _array_element_size.size
#        
#        category  ARRAY_INTENSITIES
#        
#                  _array_intensities.array_id
#                  _array_intensities.binary_id
#                  _array_intensities.gain
#                  _array_intensities.gain_esd
#                  _array_intensities.linearity
#                  _array_intensities.offset
#                  _array_intensities.scaling
#                  _array_intensities.overload
#                  _array_intensities.undefined_value
#        
#        category  ARRAY_STRUCTURE
#        
#                  _array_structure.byte_order
#                  _array_structure.compression_type
#                  _array_structure.encoding_type
#                  _array_structure.id
#        
#        category  ARRAY_STRUCTURE_LIST
#        
#                  _array_structure_list.axis_set_id
#                  _array_structure_list.array_id
#                  _array_structure_list.dimension
#                  _array_structure_list.direction
#                  _array_structure_list.index
#                  _array_structure_list.precedence
#
#        category  ARRAY_STRUCTURE_LIST_AXIS
#        
#                  _array_structure_list_axis.axis_id
#                  _array_structure_list_axis.axis_set_id
#                  _array_structure_list_axis.angle
#                  _array_structure_list_axis.angle_increment
#                  _array_structure_list_axis.displacement_increment
#                  _array_structure_list_axis.angular_pitch
#                  _array_structure_list_axis.radial_pitch
#
#        category  AXIS
#        
#                  _axis.depends_on
#                  _axis.equipment
#                  _axis.id
#                  _axis.offset[1]
#                  _axis.offset[2]
#                  _axis.offset[3]
#                  _axis.type
#                  _axis.vector[1]
#                  _axis.vector[2]
#                  _axis.vector[3]
#
#        category  DIFFRN_DATA_FRAME
#
#                  _diffrn_data_frame.array_id
#                  _diffrn_data_frame.binary_id
#                  _diffrn_data_frame.detector_element_id
#                  _diffrn_data_frame.id
#
#        category  DIFFRN_DETECTOR
#        
#                  _diffrn_detector.details
#                  _diffrn_detector.detector
#                  _diffrn_detector.diffrn_id
#                  _diffrn_detector.dtime
#                  _diffrn_detector.id
#                  _diffrn_detector.number_of_axes
#                  _diffrn_detector.type
#
#        category  DIFFRN_DETECTOR_AXIS
#        
#                  _diffrn_detector_axis.axis_id
#                  _diffrn_detector_axis.detector_id    
#        
#        category  DIFFRN_DETECTOR_ELEMENT
#
#                  _diffrn_detector_element.center[1]
#                  _diffrn_detector_element.center[2]
#                  _diffrn_detector_element.id
#                  _diffrn_detector_element.detector_id
#        
#        category  DIFFRN_MEASUREMENT
#        
#                  _diffrn_measurement.diffrn_id
#                  _diffrn_measurement.details
#                  _diffrn_measurement.device
#                  _diffrn_measurement.device_details
#                  _diffrn_measurement.device_type
#                  _diffrn_measurement.id
#                  _diffrn_measurement.method
#                  _diffrn_measurement.number_of_axes
#                  _diffrn_measurement.specimen_support
#
#        category  DIFFRN_MEASUREMENT_AXIS
#        
#                  _diffrn_measurement_axis.axis_id
#                  _diffrn_measurement_axis.measurement_device
#                  _diffrn_measurement_axis.measurement_id
#
#        category  DIFFRN_RADIATION
#
#                  _diffrn_radiation.collimation
#                  _diffrn_radiation.diffrn_id
#                  _diffrn_radiation.div_x_source
#                  _diffrn_radiation.div_y_source
#                  _diffrn_radiation.div_x_y_source
#                  _diffrn_radiation.filter_edge'
#                  _diffrn_radiation.inhomogeneity
#                  _diffrn_radiation.monochromator
#                  _diffrn_radiation.polarisn_norm
#                  _diffrn_radiation.polarisn_ratio
#                  _diffrn_radiation.polarizn_source_norm
#                  _diffrn_radiation.polarizn_source_ratio
#                  _diffrn_radiation.probe
#                  _diffrn_radiation.type
#                  _diffrn_radiation.xray_symbol
#                  _diffrn_radiation.wavelength_id
#        
#        category  DIFFRN_REFLN
#        
#                  _diffrn_refln.frame_id
#
#        category  DIFFRN_SCAN
#        
#                  _diffrn_scan.id
#                  _diffrn_scan.date_end
#                  _diffrn_scan.date_start
#                  _diffrn_scan.integration_time
#                  _diffrn_scan.frame_id_start
#                  _diffrn_scan.frame_id_end
#                  _diffrn_scan.frames
#
#        category  DIFFRN_SCAN_AXIS
#        
#                  _diffrn_scan_axis.axis_id
#                  _diffrn_scan_axis.angle_start
#                  _diffrn_scan_axis.angle_range
#                  _diffrn_scan_axis.angle_increment
#                  _diffrn_scan_axis.angle_rstrt_incr
#                  _diffrn_scan_axis.displacement_start
#                  _diffrn_scan_axis.displacement_range
#                  _diffrn_scan_axis.displacement_increment
#                  _diffrn_scan_axis.displacement_rstrt_incr
#                  _diffrn_scan_axis.scan_id
#
#        category  DIFFRN_SCAN_FRAME
#        
#                  _diffrn_scan_frame.date
#                  _diffrn_scan_frame.frame_id
#                  _diffrn_scan_frame.frame_number
#                  _diffrn_scan_frame.integration_time
#                  _diffrn_scan_frame.scan_id
#
#        category  DIFFRN_SCAN_FRAME_AXIS
#        
#                  _diffrn_scan_frame_axis.axis_id
#                  _diffrn_scan_frame_axis.angle
#                  _diffrn_scan_frame_axis.angle_increment
#                  _diffrn_scan_frame_axis.angle_rstrt_incr
#                  _diffrn_scan_frame_axis.displacement
#                  _diffrn_scan_frame_axis.displacement_increment
#                  _diffrn_scan_frame_axis.displacement_rstrt_incr
#                  _diffrn_scan_frame_axis.frame_id
#
#       ***DEPRECATED*** category  DIFFRN_FRAME_DATA
#
#                  _diffrn_frame_data.array_id
#                  _diffrn_frame_data.binary_id
#                  _diffrn_frame_data.detector_element_id
#                  _diffrn_frame_data.id
#
#
#        ITEM_TYPE_LIST
#        ITEM_UNITS_LIST
#        DICTIONARY_HISTORY
#
##############################################################################


#########################
## CATEGORY_GROUP_LIST ##
#########################

     loop_
    _category_group_list.id
    _category_group_list.parent_id
    _category_group_list.description
             'inclusive_group'   .
;             Categories that belong to the dictionary extension.
;
             'array_data_group'
             'inclusive_group'
;             Categories that describe array data.
;
             'axis_group'
             'inclusive_group'
;             Categories that describe axes.
;
             'diffrn_group'
             'inclusive_group'
;            Categories that describe details of the diffraction experiment.
;
 
 
 
 
##############
# ARRAY_DATA #
##############
 
  
save_ARRAY_DATA
    _category.description
;
     Data items in the ARRAY_DATA category are the containers for
     the array data items described in category ARRAY_STRUCTURE.
;
    _category.id                   array_data
    _category.mandatory_code       no
     loop_
    _category_key.name             '_array_data.array_id'
                                   '_array_data.binary_id'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
        Example 1 -

        This example shows two binary data blocks.  The first one
        was compressed by the CBF_CANONICAL compression algorithm and
        presented as hexadecimal data.  The first character "H" on the
        data lines means hexadecimal.  It could have been "O" for octal
        or "D" for decimal.  The second character on the line shows
        the number of bytes in each word (in this case "4"), which then
        requires 8 hexadecimal digits per word.  The third character
        gives the order of octets within a word, in this case "<"
        for the ordering 4321 (i.e. "big-endian").  Alternatively the
        character ">" could have been used for the ordering 1234
        (i.e. "little-endian").  The block has a "message digest"
        to check the integrity of the data.

        The second block is similar, but uses CBF_PACKED compression
        and BASE64 encoding.  Note that the size and the digest are
        different.
;
;

        loop_
        _array_data.array_id
        _array_data.binary_id
        _array_data.data
        image_1 1
        ;
        --CIF-BINARY-FORMAT-SECTION--
        Content-Type: application/octet-stream;
             conversions="x-CBF_CANONICAL"
        Content-Transfer-Encoding: X-BASE16
        X-Binary-Size: 3927126
        X-Binary-ID: 1
        Content-MD5: u2sTJEovAHkmkDjPi+gWsg==

        # Hexadecimal encoding, byte 0, byte order ...21
        #
        H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ...
        ....
        --CIF-BINARY-FORMAT-SECTION----
        ;
        image_2 2
        ;
        --CIF-BINARY-FORMAT-SECTION--
        Content-Type: application/octet-stream;
             conversions="x-CBF-PACKED"
        Content-Transfer-Encoding: BASE64
        X-Binary-Size: 3745758
        X-Binary-ID: 1
        Content-MD5: 1zsJjWPfol2GYl2V+QSXrw==

        ELhQAAAAAAAA...
        ...
        --CIF-BINARY-FORMAT-SECTION----
        ;
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
save_
 
 
save__array_data.array_id
    _item_description.description
;             This item is a pointer to _array_structure.id in the
              ARRAY_STRUCTURE category. 
;
    _item.name                  '_array_data.array_id'
    _item.category_id             array_data
    _item.mandatory_code          yes
    _item_type.code               code
     save_
 
 
save__array_data.binary_id
    _item_description.description
;             This item is an integer identifier which, along with
              _array_data.array_id should uniquely identify the 
              particular block of array data.
              
              If _array_data.binary_id is not explicitly given,
              it defaults to 1.
              
              The value of _array_data.binary_id distinguishes
              among multiple sets of data with the same array
              structure.
              
              If the MIME header of the data array specifies a 
              value for X-Binary-Id, these values should be equal.
;
     loop_
    _item.name                  
    _item.category_id             
    _item.mandatory_code          
             '_array_data.binary_id'            array_data      
                                                                implicit
             '_diffrn_data_frame.binary_id'     diffrn_data_frame
                                                                implicit
             '_array_intensities.binary_id'     array_intensities
                                                                implicit
     loop_
    _item_linked.child_name
    _item_linked.parent_name
             '_diffrn_data_frame.binary_id'     '_array_data.binary_id'
             '_array_intensities.binary_id'     '_array_data.binary_id'

    _item_default.value           1
    _item_type.code               int
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            1  1
                            .  1
     save_
 
 
save__array_data.data
    _item_description.description
;             The value of _array_data.data contains the array data 
              encapsulated in a STAR string.
              
              The representation used is a variant on the
              Multipurpose Internet Mail Extensions (MIME) specified
              in RFC 2045-2049 by N. Freed et al.  The boundary
              delimiter used in writing an imgCIF or CBF is
              "--CIF-BINARY-FORMAT-SECTION--" (including the
              required initial "--").

              The Content-Type may be any of the discrete types permitted
              in RFC 2045; "application/octet-stream" is recommended.  
              If an octet stream was compressed, the compression should 
              be specified by the parameter 'conversions="x-CBF_PACKED"' 
              or the parameter 'conversions="x-CBF_CANONICAL"'.
              
              The Content-Transfer-Encoding may be "BASE64",
              "Quoted-Printable", "X-BASE8", "X-BASE10", or
              "X-BASE16" for an imgCIF or "BINARY" for a CBF.  The
              octal, decimal and hexadecimal transfer encodings are
              for convenience in debugging, and are not recommended
              for archiving and data interchange.
              
              In an imgCIF file, the encoded binary data begins after
              the empty line terminating the header.  In a CBF, the
              raw binary data begins after an empty line terminating
              the header and after the sequence:
                    
              Octet   Hex   Decimal  Purpose
                0     0C       12    (ctrl-L) Page break
                1     1A       26    (ctrl-Z) Stop listings in MS-DOS
                2     04       04    (Ctrl-D) Stop listings in UNIX
                3     D5      213    Binary section begins

              None of these octets are included in the calculation of
              the message size, nor in the calculation of the
              message digest.
                             
              The X-Binary-Size header specifies the size of the
              equivalent binary data in octets.  If compression was
              used, this size is the size after compression, including
              any book-keeping fields.  An adjustment is made for
              the deprecated binary formats in which 8 bytes of binary
              header are used for the compression type.  In that case,
              the 8 bytes used for the compression type is subtracted
              from the size, so that the same size will be reported
              if the compression type is supplied in the MIME header.
              Use of the MIME header is the recommended way to
              supply the compression type.  In general, no portion of
              the  binary header is included in the calculation of the size.

              The X-Binary-Element-Type header specifies the type of
              binary data in the octets, using the same descriptive
              phrases as in _array_structure.encoding_type.  The default
              value is "unsigned 32-bit integer".
              
              An MD5 message digest may, optionally, be used. The "RSA Data
              Security, Inc. MD5 Message-Digest Algorithm" should be used.
              No portion of the header is included in the calculation of the
              message digest.

              If the Transfer Encoding is "X-BASE8", "X-BASE10", or
              "X-BASE16", the data is presented as octal, decimal or
              hexadecimal data organized into lines or words.  Each word
              is created by composing octets of data in fixed groups of
              2, 3, 4, 6 or 8 octets, either in the order ...4321 ("big-
              endian") or 1234... (little-endian).  If there are fewer
              than the specified number of octets to fill the last word,
              then the missing octets are presented as "==" for each
              missing octet.  Exactly two equal signs are used for each
              missing octet even for octal and decimal encoding.
              The format of lines is:

              rnd xxxxxx xxxxxx xxxxxx

              where r is "H", "O", or "D" for hexadecimal, octal or
              decimal, n is the number of octets per word. and d is "<"
              for ">" for the "...4321" and "1234..." octet orderings
              respectively.  The "==" padding for the last word should
              be on the appropriate side to correspond to the missing
              octets, e.g.

              H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000

              or

              H3> FF0700 00====

              For these hex, octal and decimal formats, only, comments
              beginning with "#" are permitted to improve readability.

              BASE64 encoding follows MIME conventions.  Octets are
              in groups of three, c1, c2, c3.  The resulting 24 bits 
              are broken into four 6-bit quantities, starting with 
              the high-order six bits (c1 >> 2) of the first octet, then
              the low-order two bits of the first octet followed by the
              high-order 4 bits of the second octet ((c1 & 3)<<4 | (c2>>4)),
              then the bottom 4 bits of the second octet followed by the
              high order two bits of the last octet ((c2 & 15)<<2 | (c3>>6)),
              then the bottom six bits of the last octet (c3 & 63).  Each
              of these four quantities is translated into an ASCII character
              using the mapping:

                        1         2         3         4         5         6
              0123456789012345678901234567890123456789012345678901234567890123
              |         |         |         |         |         |         |
              ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/

              With short groups of octets padded on the right with one "="
              if c3 is missing, and with "==" if both c2 and c3 are missing.

              QUOTED-PRINTABLE encoding also follows MIME conventions, copying
              octets without translation if their ASCII values are 32..38,
              42, 48..57, 59..60, 62, 64..126 and the octet is not a ";"
              in column 1.  All other characters are translated to =nn, where
              nn is the hexadecimal encoding of the octet.  All lines are
              "wrapped" with a terminating "=" (i.e. the MIME conventions
              for an implicit line terminator are never used).
;
    _item.name                  '_array_data.data'
    _item.category_id             array_data
    _item.mandatory_code          yes
    _item_type.code               binary
save_
 
 
######################
# ARRAY_ELEMENT_SIZE #
######################
 
 
save_ARRAY_ELEMENT_SIZE
    _category.description
;
     Data items in the ARRAY_ELEMENT_SIZE category record the physical 
     size of array elements along each array dimension.
;
    _category.id                   array_element_size
    _category.mandatory_code       no
     loop_
    _category_key.name             '_array_element_size.array_id'
                                   '_array_element_size.index'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
        Example 1 - A regular 2D array with a uniform element dimension
                    of 1220 nanometres.
;
;
        loop_
       _array_element_size.array_id  
       _array_element_size.index
       _array_element_size.size
        image_1   1    1.22e-6
        image_1   2    1.22e-6
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_
 
 
save__array_element_size.array_id
    _item_description.description
;             
              This item is a pointer to _array_structure.id in the
              ARRAY_STRUCTURE category. 
;
    _item.name                  '_array_element_size.array_id'
    _item.category_id             array_element_size
    _item.mandatory_code          yes
    _item_type.code               code
     save_
 
 
save__array_element_size.index
    _item_description.description
;             
              This item is a pointer to _array_structure_list.index in the
              ARRAY_STRUCTURE_LIST category. 
;
    _item.name                  '_array_element_size.index'
    _item.category_id             array_element_size
    _item.mandatory_code          yes
    _item_type.code               code
     save_
 
 
save__array_element_size.size
    _item_description.description
;
               The size in metres of an image element in this 
               dimension. This supposes that the elements are arranged
               on a regular grid.
;
    _item.name               '_array_element_size.size'
    _item.category_id          array_element_size
    _item.mandatory_code       yes 
    _item_type.code            float
    _item_units.code           'metres'
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            .   0.0
     save_
 
 
#####################
# ARRAY_INTENSITIES #
#####################
 
 
save_ARRAY_INTENSITIES
    _category.description
;
              Data items in the ARRAY_INTENSITIES category record the
              information required to recover the intensity data from 
              the set of data values stored in the ARRAY_DATA category.

              The actual detector may have a complex relationship
              between the raw intensity values and the number of
              incident photons.  In most cases, the number stored
              in the final array will have a simple linear relationship
              to the actual number of incident photons, given by
              '_array_intensities.gain'.  If raw, uncorrected values
              are presented (e.g for calibration experiments), the
              value of '_array_intensities.linearity' will be 'raw'
              and '_array_intensities.gain' will not be used.

;
    _category.id                   array_intensities
    _category.mandatory_code       no
    loop_
    _category_key.name             '_array_intensities.array_id'
                                   '_array_intensities.binary_id'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
        Example 1
;
;
        loop_
        _array_intensities.array_id
        _array_intensities.linearity 
        _array_intensities.gain      
        _array_intensities.overload  
        _array_intensities.undefined_value 
        image_1   linear  1.2    655535   0
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_
 
 
save__array_intensities.array_id
    _item_description.description
;             
              This item is a pointer to _array_structure.id in the
              ARRAY_STRUCTURE category. 
;
    _item.name                  '_array_intensities.array_id'
    _item.category_id             array_intensities
    _item.mandatory_code          yes
    _item_type.code               code
     save_
 
 
save__array_intensities.binary_id
    _item_description.description
;             This item is a pointer to _array_data.binary_id in the
              ARRAY_DATA category. 
;
    _item.name                  '_array_intensities.binary_id'
    _item.category_id             array_intensities
    _item.mandatory_code          implicit
    _item_type.code               int
     save_
 
 
save__array_intensities.gain
    _item_description.description
;              
               Detector "gain". The factor by which linearized 
               intensity count values should be divided to produce
               true photon counts.
;
    _item.name              '_array_intensities.gain'
    _item.category_id          array_intensities
    _item.mandatory_code       yes
    _item_type.code            float
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            .   0.0
    _item_units.code           'counts_per_photon'
     loop_
    _item_related.related_name
    _item_related.function_code  '_array_intensities.gain_esd'
                                 'associated_value'
    save_
 
  
save__array_intensities.gain_esd
    _item_description.description
;              
              The estimated standard deviation in detector "gain".
;
    _item.name              '_array_intensities.gain_esd'
    _item.category_id          array_intensities
    _item.mandatory_code       yes
    _item_type.code            float

    _item_units.code          'counts_per_photon'
     loop_
    _item_related.related_name
    _item_related.function_code  '_array_intensities.gain'
                                 'associated_esd'
    save_
 
 
save__array_intensities.linearity
    _item_description.description
;
               The intensity linearity scaling used from raw intensity
               to the stored element value:

               'linear' is obvious

               'offset'  means that the value defined by 
               '_array_intensities.offset' should be added to each
                element value.  

               'scaling' means that the value defined by 
               '_array_intensities.scaling' should be multiplied with each 
               element value.  

               'scaling_offset' is the combination of the two previous cases, 
               with the scale factor applied before the offset value.

               'sqrt_scaled' means that the square root of raw 
               intensities multiplied by '_array_intensities.scaling' is
               calculated and stored, perhaps rounded to the nearest 
               integer. Thus, linearization involves dividing the stored
               values by '_array_intensities.scaling' and squaring the 
               result. 

               'logarithmic_scaled' means that the logarithm based 10 of
               raw intensities multiplied by '_array_intensities.scaling' 
               is calculated and stored, perhaps rounded to the nearest 
               integer. Thus, linearization involves dividing the stored
               values by '_array_intensities.scaling' and calculating 10
               to the power of this number.

               'raw' means that the data is the raw is a set of raw values
               straight from the detector.
;

    _item.name               '_array_intensities.linearity'
    _item.category_id          array_intensities
    _item.mandatory_code       yes
    _item_type.code            code
     loop_
    _item_enumeration.value   
    _item_enumeration.detail   
                              'linear' .
                              'offset'           
;
               The value defined by  '_array_intensities.offset' should 
               be added to each element value.  
;
                              'scaling'
;
               The value defined by '_array_intensities.scaling' should be 
               multiplied with each element value.  
;
                              'scaling_offset'   
;
               The combination of the scaling and offset 
               with the scale factor applied before the offset value.
;
                              'sqrt_scaled'      
;
               The square root of raw intensities multiplied by 
               '_array_intensities.scaling' is calculated and stored, 
               perhaps rounded to the nearest integer. Thus, 
               linearization involves dividing the stored
               values by '_array_intensities.scaling' and squaring the 
               result. 
;
                              'logarithmic_scaled'
;
               The logarithm based 10 of raw intensities multiplied by 
               '_array_intensities.scaling'  is calculated and stored, 
               perhaps rounded to the nearest integer. Thus, 
               linearization involves dividing the stored values by 
               '_array_intensities.scaling' and calculating 10 to the 
               power of this number.
;
                              'raw'
;
               The array consists of raw values to which no corrections have
               been applied.  While the handling of the data is similar to 
               that given for 'linear' data with no offset, the meaning of 
               the data differs in that the number of incident photons is 
               not necessarily linearly related to the number of counts 
               reported.  This value is intended for use either in 
               calibration experiments or to allow for handling more 
               complex data fitting algorithms than are allowed for by 
               this data item.
;

    save_
  
  
save__array_intensities.offset
    _item_description.description
;
               Offset value to add to array element values in the manner
               described by item _array_intensities.linearity.
;
    _item.name                 '_array_intensities.offset'
    _item.category_id          array_intensities
    _item.mandatory_code       no
    _item_type.code            float
    save_
 
 
save__array_intensities.scaling
    _item_description.description
;
               Multiplicative scaling value to be applied to array data
               in the manner described by item _array_intensities.linearity.
;
    _item.name                 '_array_intensities.scaling'
    _item.category_id          array_intensities
    _item.mandatory_code       no
    _item_type.code            float
    save_
 
 
save__array_intensities.overload
    _item_description.description
;
               The saturation intensity level for this data array.
;
    _item.name                 '_array_intensities.overload'
    _item.category_id          array_intensities
    _item.mandatory_code       no
    _item_type.code            float
    _item_units.code          'counts'
    save_
 
  
save__array_intensities.undefined_value
    _item_description.description
;
               A value to be substituted for undefined values in 
               the data array.
;
    _item.name                 '_array_intensities.undefined_value'
    _item.category_id          array_intensities
    _item.mandatory_code       no
    _item_type.code            float
    save_
 
 
###################
# ARRAY_STRUCTURE #
###################
 
 
save_ARRAY_STRUCTURE
    _category.description
;
     Data items in the ARRAY_STRUCTURE category record the organization and 
     encoding of array data which may be stored in the ARRAY_DATA category.
;
    _category.id                   array_structure
    _category.mandatory_code       no
    _category_key.name             '_array_structure.id'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
    Example 1 -
;
;
     loop_
    _array_structure.id 
    _array_structure.encoding_type        
    _array_structure.compression_type     
    _array_structure.byte_order           
     image_1       "unsigned 16-bit integer"  none  little_endian
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_
 
 
save__array_structure.byte_order
    _item_description.description
;
               The order of bytes for integer values which require more
               than 1-byte. 

               (IBM-PC's and compatibles, and Dec-Vaxes use low-byte-first
               ordered integers, whereas Hewlett Packard 700 
               series, Sun-4 and Silicon Graphics use high-byte-first
               ordered integers.  Dec-Alphas can produce/use either
               depending on a compiler switch.)
;

    _item.name                     '_array_structure.byte_order'
    _item.category_id               array_structure
    _item.mandatory_code            yes 
    _item_type.code                 code
     loop_
    _item_enumeration.value        
    _item_enumeration.detail        
                                   'big_endian'
;
        The first byte in the byte stream of the bytes which make up an 
        integer value is the most significant byte of an integer. 
;
                                   'little_endian'
;
        The last byte in the byte stream of the bytes which make up an 
        integer value is the most significant byte of an integer.
;
     save_
 
 
save__array_structure.compression_type 
    _item_description.description
;
              Type of data compression method used to compress the array
              data. 
;
    _item.name                   '_array_structure.compression_type'
    _item.category_id             array_structure
    _item.mandatory_code          no 
    _item_type.code               code
    _item_default.value           'none'
     loop_
    _item_enumeration.value       
    _item_enumeration.detail
                                  'none'
;
        Data are stored in normal format as defined by 
        '_array_structure.encoding_type' and 
        '_array_structure.byte_order'.
;
                                  'byte_offsets'
;
        Using the compression scheme defined in CBF definition
        Section 5.0.
;
                                  'packed'
;
        Using the 'packed' compression scheme, a CCP4-style packing
        (CBFlib section 3.3.2)
;
                                  'canonical'
;
        Using the 'canonical' compression scheme (CBFlib section
        3.3.1)
;
    save_
 
 
save__array_structure.encoding_type
    _item_description.description
;
               Data encoding of a single element of array data. 
               
               In several cases, the IEEE format is referenced.
               See "IEEE Standard for Binary Floating-Point Arithmetic",
               ANSI/IEEE Std 754-1985, the Institute of Electrical and
               Electronics Engineers, Inc., NY 1985.  
;

    _item.name                '_array_structure.encoding_type'
    _item.category_id          array_structure
    _item.mandatory_code       yes 
    _item_type.code            uline
     loop_
    _item_enumeration.value   
                              'unsigned 8-bit integer'
                              'signed 8-bit integer'
                              'unsigned 16-bit integer'
                              'signed 16-bit integer'
                              'unsigned 32-bit integer'
                              'signed 32-bit integer'
                              'signed 32-bit real IEEE'
                              'signed 64-bit real IEEE'
                              'signed 32-bit complex IEEE'
     save_
 
 
save__array_structure.id
    _item_description.description
;             The value of _array_structure.id must uniquely identify 
              each item of array data. 
;
    loop_
    _item.name                  
    _item.category_id             
    _item.mandatory_code          
             '_array_structure.id'              array_structure      yes
             '_array_data.array_id'             array_data           yes
             '_array_structure_list.array_id'   array_structure_list yes
             '_array_intensities.array_id'      array_intensities    yes
             '_diffrn_data_frame.array_id'      diffrn_data_frame    yes
 

    _item_type.code               code
     loop_
    _item_linked.child_name
    _item_linked.parent_name
             '_array_data.array_id'             '_array_structure.id'
             '_array_structure_list.array_id'   '_array_structure.id'
             '_array_intensities.array_id'      '_array_structure.id'
             '_diffrn_data_frame.array_id'      '_array_structure.id'

     save_
 
 
########################
# ARRAY_STRUCTURE_LIST #
########################
 
 
save_ARRAY_STRUCTURE_LIST
    _category.description
;
     Data items in the ARRAY_STRUCTURE_LIST category record the size 
     and organization of each array dimension.

     The relationship to physical axes may be given.
;
    _category.id                   array_structure_list
    _category.mandatory_code       no
     loop_
    _category_key.name             '_array_structure_list.array_id'
                                   '_array_structure_list.index'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
        Example 1 - An image array of 1300 x 1200 elements.  The raster 
                    order of the image is left-to-right (increasing) in 
                    first dimension and bottom-to-top (decreasing) in 
                    the second dimension.
;
;
        loop_
       _array_structure_list.array_id  
       _array_structure_list.index
       _array_structure_list.dimension 
       _array_structure_list.precedence 
       _array_structure_list.direction
       _array_structure_list.axis_set_id
        image_1   1    1300    1     increasing  ELEMENT_X
        image_1   2    1200    2     decreasing  ELEMENY_Y
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_
 
 
save__array_structure_list.array_id
    _item_description.description
;             
              This item is a pointer to _array_structure.id in the
              ARRAY_STRUCTURE category. 
;
    _item.name                  '_array_structure_list.array_id'
    _item.category_id             array_structure_list
    _item.mandatory_code          yes
    _item_type.code               code
save_
 
 
save__array_structure_list.axis_set_id
    _item_description.description
;              This is a descriptor for the physical axis or set of axes 
               corresponding to an array index.
               
               This data item is related to the axes of the detector 
               itself given in DIFFRN_DETECTOR_AXIS, but usually differ
               in that the axes in this category are the axes of the
               coordinate system of reported data points, while the axes in
               DIFFRN_DETECTOR_AXIS are the physical axes 
               of the detector describing the "poise" of the detector as an
               overall physical object.
               
               If there is only one axis in the set, the identifier of 
               that axis should be used as the identifier of the set.
               
;
     loop_
    _item.name                
    _item.category_id          
    _item.mandatory_code       
           '_array_structure_list.axis_set_id'
                                  array_structure_list            yes
           '_array_structure_list_axis.axis_set_id'
                                  array_structure_list_axis       implicit
    _item_type.code               code
     loop_
    _item_linked.child_name
    _item_linked.parent_name
           '_array_structure_list_axis.axis_set_id'
                               '_array_structure_list.axis_set_id'


     save_
 
 
save__array_structure_list.dimension
    _item_description.description
;              
               The number of elements stored in the array structure in this 
               dimension.
;
    _item.name                '_array_structure_list.dimension'
    _item.category_id          array_structure_list
    _item.mandatory_code       yes 
    _item_type.code            int
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            1  1
                            .  1
     save_
 
 
save__array_structure_list.direction
    _item_description.description
;
              Identifies the direction in which this array index changes.
;
    _item.name                '_array_structure_list.direction'
    _item.category_id          array_structure_list
    _item.mandatory_code       yes 
    _item_type.code            int
     loop_
    _item_enumeration.value
    _item_enumeration.detail        

                              'increasing'
;
         Indicates the index changes from 1 to the maximum dimension.
;
                              'decreasing'
;
         Indicates the index changes from the maximum dimension to 1.
;
     save_
 
 
save__array_structure_list.index
    _item_description.description
;              
               Identifies the one-based index of the row or column in the
               array structure.
;
     loop_
    _item.name                
    _item.category_id          
    _item.mandatory_code       
           '_array_structure_list.index'        array_structure_list   yes
           '_array_structure_list.precedence'   array_structure_list   yes
           '_array_element_size.index'          array_element_size     yes

    _item_type.code            int

     loop_
    _item_linked.child_name
    _item_linked.parent_name
          '_array_element_size.index'         '_array_structure_list.index'
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            1  1
                            .  1
     save_
 
 
save__array_structure_list.precedence
    _item_description.description
;
               Identifies the rank order in which this array index changes 
               with respect to other array indices.  The precedence of 1  
               indicates the index which changes fastest.
;
    _item.name                '_array_structure_list.precedence'
    _item.category_id          array_structure_list
    _item.mandatory_code       yes 
    _item_type.code            int
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            1  1
                            .  1
     save_
 
 
#############################
# ARRAY_STRUCTURE_LIST_AXIS #
#############################
 
save_ARRAY_STRUCTURE_LIST_AXIS
    _category.description
;
     Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe
     the physical settings of sets axes for the centres of pixels that 
     correspond to data points described in the 
     ARRAY_STRUCTURE_LIST category. 
     
     In the simplest cases, the physical increments of a single axis correspond
     to the increments of a single array index.  More complex organizations,
     e.g. spiral scans, may require coupled motions along multiple axes.
     
     Note that a spiral scan uses two coupled axis, one for the angular 
     direction, one for the radial direction.  This differs from a 
     cylindrical scan for which the two axes are not coupled into one set.
     
;
    _category.id                   array_structure_list_axis
    _category.mandatory_code       no
     loop_
    _category_key.name
                                  '_array_structure_list_axis.axis_set_id'
                                  '_array_structure_list_axis.axis_id'
     loop_
    _category_group.id           'inclusive_group'
                                 'array_data_group'
     save_
 
 
save__array_structure_list_axis.axis_id
    _item_description.description
;
               The value of this data item is the identifier of one of
               the axes for the set of axes for which settings are being 
               specified.

               Multiple axes may be specified for the same value of
               '_array_structure_list_axis.axis_set_id'

               This item is a pointer to _axis.id in the
               AXIS category.
;
    _item.name                 '_array_structure_list_axis.axis_id'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       yes
     save_
 
 
save__array_structure_list_axis.axis_set_id
    _item_description.description
;
               The value of this data item is the identifier of the
               set of axes for which axis settings are being specified.

               Multiple axes may be specified for the same value of
               _array_structure_list_axis.axis_set_id .

               This item is a pointer to _array_structure_list.axis_set_id
               in the ARRAY_STRUCTURE_LIST category.
               
               If this item is not specified, it defaults to the corresponding
               axis identifier.
;
    _item.name                 '_array_structure_list_axis.axis_set_id'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       implicit
     save_
 
 
save__array_structure_list_axis.angle
    _item_description.description
;
               The setting of the specified axis in degrees for the first
               data point of the array index with the corresponding value
               of '_array_structure_list.axis_set_id'.  If the index is
               specified as 'increasing' this will be the center of the
               pixel with index value 1.  If the index is specified as
               'decreasing' this will be the center of the pixel with
               maximum index value. 
;
    _item.name                 '_array_structure_list_axis.angle'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       no 
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_
 
 
save__array_structure_list_axis.angle_increment
    _item_description.description
;
               The pixel-center-to-pixel-center increment in the angular 
               setting of the specified axis in degrees.  This is not 
               meaningful in the case of 'constant velocity' spiral scans  
               and should not be specified in that case.  

               See '_array_structure_list_axis.angular_pitch'.
               
;
    _item.name                 '_array_structure_list_axis.angle_increment'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_
 
 
save__array_structure_list_axis.displacement
    _item_description.description
;
               The setting of the specified axis in millimetres for the first
               data point of the array index with the corresponding value
               of '_array_structure_list.axis_set_id'.  If the index is
               specified as 'increasing' this will be the center of the
               pixel with index value 1.  If the index is specified as
               'decreasing' this will be the center of the pixel with
               maximum index value. 

;
    _item.name               '_array_structure_list_axis.displacement'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
 
 
save__array_structure_list_axis.displacement_increment
    _item_description.description
;
               The pixel-center-to-pixel-center increment for the displacement 
               setting of the specified axis in millimetres.
               
;
    _item.name                 
        '_array_structure_list_axis.displacement_increment'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
  
 
save__array_structure_list_axis.angular_pitch
    _item_description.description
;
               The pixel-center-to-pixel-center distance for a one step 
               change in the setting of the specified axis in millimetres.
               
               This is meaningful only for 'constant velocity' spiral scans,
               or for uncoupled angular scans at a constant radius
               (cylindrical scan) and should not be specified for cases
               in which the angle between pixels, rather than the distance
               between pixels is uniform.
               
               See '_array_structure_list_axis.angle_increment'.
               
;
    _item.name               '_array_structure_list_axis.angular_pitch'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
   
 
save__array_structure_list_axis.radial_pitch
    _item_description.description
;
               The radial distance from one "cylinder" of pixels to the
               next in millimetres.  If the scan is a 'constant velocity'
               scan with differing angular displacements between pixels,
               the value of this item may differ significantly from the
               value of '_array_structure_list_axis.displacement_increment'.
               
;
    _item.name               '_array_structure_list_axis.radial_pitch'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
  

 
########
# AXIS #
########

save_AXIS
    _category.description
;
     Data items in the AXIS category record the information required
     to describe the various goniometer, detector, source and other
     axes needed to specify a data collection.  The location of each
     axis is specified by two vectors: the axis itself, given as a unit
     vector, and an offset to the base of the unit vector.  These vectors
     are referenced to a right-handed laboratory coordinate system with
     its origin in the sample or specimen:
     
                             | Y (to complete right-handed system)
                             |
                             |
                             |
                             |
                             |
                             |________________X
                            /       principal goniometer axis
                           /
                          /
                         /
                        /
                       /Z (to source)
 
 
                                                      
     Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from
     the sample or specimen along the  principal axis of the goniometer.
     
     Axis 2 (Y): The Y-axis completes an orthogonal right-handed system
     defined by the X-axis and the Z-axis (see below).
     
     Axis 3 (Z): The Z-axis is derived from the source axis which goes from 
     the sample to the source.  The Z-axis is the component of the source axis
     in the direction of the source orthogonal to the X-axis in the plane 
     defined by the X-axis and the source axis.
          
     These axes are based on the goniometer, not on the orientation of the 
     detector, gravity, etc.  The vectors necessary to specify all other
     axes are given by sets of three components in the order (X, Y, Z).
     If the axis involved is a rotation axis, it is right handed, i.e. as
     one views the object to be rotated from the origin (the tail) of the 
     unit vector, the rotation is clockwise.  If a translation axis is
     specified, the direction of the unit vector specifies the sense of
     positive translation.
     
     Note:  This choice of coordinate system is similar to, but significantly
     different from the choice in MOSFLM (Andrew G.W. Leslie, Harry Powell,
     MRC Laboratory of Molecular Biology, Hills Road, Cambridge CB2 2QH,UK
     http://www.dl.ac.uk/CCP/CCP4/dist/x-windows/Mosflm/).  In MOSFLM,
     X is along the X-ray beam (our Z axis) and Z is along the rotation axis.

     All rotations are given in degrees and all translations are given in mm.
     
     Axes may be dependent on one another.  The X-axis is the only goniometer
     axis the direction of which is strictly connected to the hardware.  All
     other axes are specified by the positions they would assume when the
     axes upon which they depend are at their zero points.
     
     When specifying detector axes, the axis is given to the beam center.
     The location of the beam center on the detector should be given in the
     DIFFRN_DETECTOR category in distortion-corrected mm from the (0,0) corner
     of the detector.
     
     It should be noted that many different origins arise in the definition
     of an experiment.  In particular, as noted above, we need to specify the
     location of the beam center on the detector in terms of the origin of the
     detector, which is, of course, not coincident with the center of the
     sample.  
;
    _category.id                   axis
    _category.mandatory_code       no
     loop_
    _category_key.name          '_axis.id' 
                                '_axis.equipment'               
     loop_
    _category_group.id           'inclusive_group'
                                 'axis_group'
                                 'diffrn_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
        Example 1 -
        
        This example shows the axis specification of the axes of a kappa
        geometry goniometer (See "X-Ray Structure Determination, A Practical
        Guide", 2nd ed. by  G. H. Stout, L. H. Jensen, Wiley Interscience,
        1989, 453 pp, p 134.).
        
        There are three axes specified, and no offsets.  The outermost axis,
        omega, is pointed along the X-axis.  The next innermost axis, kappa,
        is at a 50 degree angle to the X-axis, pointed away from the source.
        The innermost axis, phi, aligns with the X-axis when omega and
        phi are at their zero-points.  If T-omega, T-kappa and T-phi
        are the transformation matrices derived from the axis settings,
        the complete transformation would be:
            x' = (T-omega) (T-kappa) (T-phi) x
;
;
         loop_
        _axis.id
        _axis.type
        _axis.equipment
        _axis.depends_on
        _axis.vector[1] _axis.vector[2] _axis.vector[3]
        omega rotation goniometer     .    1        0        0
        kappa rotation goniometer omega    -.64279  0       -.76604
        phi   rotation goniometer kappa    1        0        0   
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
        Example 2 -
        
        This example show the axis specification of the axes of a
        detector, source and gravity.  We have juggled the order as a
        reminder that the ordering of presentation of tokens is not
        significant.  We have taken the center of rotation of the detector
        to be 68 millimetres in the direction away from the source.
;
;
        loop_
        _axis.id
        _axis.type
        _axis.equipment
        _axis.depends_on
        _axis.vector[1] _axis.vector[2] _axis.vector[3]
        _axis.offset[1] _axis.offset[2] _axis.offset[3]
        source       .        source     .       0     0     1   . . .
        gravity      .        gravity    .       0    -1     0   . . .
        tranz     translation detector rotz      0     0     1   0 0 -68
        twotheta  rotation    detector   .       1     0     0   . . .
        roty      rotation    detector twotheta  0     1     0   0 0 -68
        rotz      rotation    detector roty      0     0     1   0 0 -68
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_
 
 
save__axis.depends_on
    _item_description.description
;             The value of  _axis.type specifies the next outermost
              axis upon which this axis depends.
              
              This item is a pointer to axis.id in the same category.
;
    _item.name                      '_axis.depends_on'
    _item.category_id                 axis
    _item.mandatory_code              no

     save_
 
 
save__axis.equipment
    _item_description.description
;             The value of  _axis.type specifies the type of equipment
              using the axis:  goniometer, detector, gravity, source
              or general
;
    _item.name                      '_axis.equipment'
    _item.category_id                 axis
    _item.mandatory_code              no
    _item_type.code                   ucode
    _item_default.value               general
     loop_
    _item_enumeration.value
    _item_enumeration.detail   goniometer
                              'equipment used to orient or position samples'
                               detector
                              'equipment used to detect reflections'
                               general
                              'equipment used for general purposes'
                               gravity
                              'axis specifying the downward direction'
                               source
                              'axis specifying the direction sample to source'

     save_
 
 
save__axis.offset[1]
    _item_description.description
;              The [1] element of the 3-element vector used to specify
               the offset to the base of a rotation or translation axis.
               
               The vector is specified in millimetres
;
    _item.name                  '_axis.offset[1]'
    _item.category_id             axis
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
    _item_units.code              millimetres
     save_
 
 
save__axis.offset[2]
    _item_description.description
;              The [2] element of the 3-element vector used to specify
               the offset to the base of a rotation or translation axis.
               
               The vector is specified in millimetres
;
    _item.name                  '_axis.offset[2]'
    _item.category_id             axis
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
    _item_units.code              millimetres
     save_
 
 
save__axis.offset[3]
    _item_description.description
;              The [3] element of the 3-element vector used to specify
               the offset to the base of a rotation or translation axis.
               
               The vector is specified in millimetres
;
    _item.name                  '_axis.offset[3]'
    _item.category_id             axis
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
    _item_units.code              millimetres
     save_
 
 
save__axis.id
    _item_description.description
;             The value of _axis.id must uniquely identify
              each axis relevant to the experiment.  Note that multiple
              pieces of equipment may share the same axis (e.g. a twotheta
              arm), so that the category key for AXIS also includes the
              equipment.
;
    loop_
    _item.name
    _item.category_id
    _item.mandatory_code
         '_axis.id'                         axis                    yes
         '_array_structure_list_axis.axis_id'
                                            array_structure_list_axis
                                                                    yes
         '_diffrn_detector_axis.axis_id'    diffrn_detector_axis    yes
         '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes
         '_diffrn_scan_axis.axis_id'        diffrn_scan_axis        yes
         '_diffrn_scan_frame_axis.axis_id'  diffrn_scan_frame_axis  yes

    _item_type.code               code
     loop_
    _item_linked.child_name
    _item_linked.parent_name
         '_axis.depends_on'                   '_axis.id'
         '_array_structure_list_axis.axis_id' '_axis.id'
         '_diffrn_detector_axis.axis_id'      '_axis.id'
         '_diffrn_measurement_axis.axis_id'   '_axis.id'
         '_diffrn_scan_axis.axis_id'          '_axis.id'      
         '_diffrn_scan_frame_axis.axis_id'    '_axis.id'

     save_
 
 
save__axis.type
    _item_description.description
;             The value of _axis.type specifies the type of
              axis:  rotation, translation (or general when the type is
              not relevant, as for gravity)
;
    _item.name                      '_axis.type'
    _item.category_id                 axis
    _item.mandatory_code              no
    _item_type.code                   ucode
    _item_default.value               general
     loop_
    _item_enumeration.value
    _item_enumeration.detail      rotation
                                 'right-handed axis of rotation'
                                  translation
                                 'translation in the direction of the axis'
                                  general
                                 'axis for which the type is not relevant'

     save_


save__axis.vector[1]
    _item_description.description
;              The [1] element of the 3-element vector used to specify
               the direction of a rotation or translation axis.
               The vector should be normalized to be a unit vector, and
               is dimensionless.
;
    _item.name                  '_axis.vector[1]'
    _item.category_id             axis
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
     save_

save__axis.vector[2]
    _item_description.description
;              The [2] element of the 3-element vector used to specify
               the direction of a rotation or translation axis.
               The vector should be normalized to be a unit vector, and
               is dimensionless.
;
    _item.name                  '_axis.vector[2]'
    _item.category_id             axis
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
     save_

save__axis.vector[3]
    _item_description.description
;              The [3] element of the 3-element vector used to specify
               the direction of a rotation or translation axis.
               The vector should be normalized to be a unit vector, and
               is dimensionless.
;
    _item.name                  '_axis.vector[3]'
    _item.category_id             axis
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
     save_
 

 
#####################
# DIFFRN_DATA_FRAME #
#####################
 
 
save_DIFFRN_DATA_FRAME
    _category.description
;
              Data items in the DIFFRN_DATA_FRAME category record
              the details about each frame of data. 
              
              The items in this category were previously in a
              DIFFRN_FRAME_DATA category, which is now deprecated.
              The items from the old category are provided
              as aliases, but should not be used for new work.
;
    _category.id                   diffrn_data_frame
    _category.mandatory_code       no
     loop_
    _category_key.name             '_diffrn_data_frame.id'
                                   '_diffrn_data_frame.detector_element_id'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
    Example 1 - A frame containing data from 4 frame elements.
                Each frame element has a common array configuration
                'array_1' described in ARRAY_STRUCTURE and related
                categories.  The data for each detector element is 
                stored in four groups of binary data in the
                ARRAY_DATA category, linked by the array_id and
                binary_id
;
;
        loop_
        _diffrn_data_frame.id
        _diffrn_data_frame.detector_element_id
        _diffrn_data_frame.array_id
        _diffrn_data_frame.binary_id
        frame_1   d1_ccd_1  array_1  1  
        frame_1   d1_ccd_2  array_1  2 
        frame_1   d1_ccd_3  array_1  3 
        frame_1   d1_ccd_4  array_1  4 
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    save_
 
 
save__diffrn_data_frame.array_id
    _item_description.description
;             
              This item is a pointer to _array_structure.id in the
              ARRAY_STRUCTURE category. 
;
    _item.name                  '_diffrn_data_frame.array_id'
    _item.category_id             diffrn_data_frame
    _item.mandatory_code          yes
    _item_aliases.alias_name    '_diffrn_frame_data.array_id'
    _item_aliases.dictionary      cif_img.dic
    _item_aliases.version         1.0.00
    _item_type.code               code
     save_
 
 
save__diffrn_data_frame.binary_id
    _item_description.description
;             This item is a pointer to _array_data.binary_id in the
              ARRAY_DATA category. 
;
    _item.name                  '_diffrn_data_frame.binary_id'
    _item.category_id             diffrn_data_frame
    _item.mandatory_code          implicit
    _item_aliases.alias_name    '_diffrn_frame_data.binary_id'
    _item_aliases.dictionary      cif_img.dic
    _item_aliases.version         1.0
    _item_type.code               int
     save_
 
 
save__diffrn_data_frame.detector_element_id
    _item_description.description
;             
               This item is a pointer to _diffrn_detector_element.id
               in the DIFFRN_DETECTOR_ELEMENT category. 
;
    _item.name                  '_diffrn_data_frame.detector_element_id'
    _item.category_id             diffrn_data_frame
    _item.mandatory_code          yes
    _item_aliases.alias_name    '_diffrn_frame_data.detector_element_id'
    _item_aliases.dictionary      cif_img.dic
    _item_aliases.version         1.0
    _item_type.code               code
     save_
 
 
save__diffrn_data_frame.id
    _item_description.description
;             
              The value of _diffrn_data_frame.id must uniquely identify
              each complete frame of data.
;
     loop_
    _item.name                
    _item.category_id          
    _item.mandatory_code       
           '_diffrn_data_frame.id'        diffrn_data_frame  yes
           '_diffrn_refln.frame_id'       diffrn_refln       yes
           '_diffrn_scan.frame_id_start'  diffrn_scan        yes
           '_diffrn_scan.frame_id_end'    diffrn_scan        yes
           '_diffrn_scan_frame.frame_id'  diffrn_scan_frame  yes
           '_diffrn_scan_frame_axis.frame_id'  
                                          diffrn_scan_frame_axis
                                                             yes
    _item_aliases.alias_name    '_diffrn_frame_data.id'
    _item_aliases.dictionary      cif_img.dic
    _item_aliases.version         1.0
    _item_type.code               code
     loop_
    _item_linked.child_name
    _item_linked.parent_name
           '_diffrn_refln.frame_id'        '_diffrn_data_frame.id'
           '_diffrn_scan.frame_id_start'   '_diffrn_data_frame.id'
           '_diffrn_scan.frame_id_end'     '_diffrn_data_frame.id'
           '_diffrn_scan_frame.frame_id'   '_diffrn_data_frame.id'
           '_diffrn_scan_frame_axis.frame_id'
                                           '_diffrn_data_frame.id'
     save_
 

##########################################################################
#  The following is a restatement of the mmCIF DIFFRN_DETECTOR,          #
#  DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for      #
#  the CBF/imgCIF extensions                                             #
##########################################################################

###################
# DIFFRN_DETECTOR #
###################
 
 
save_DIFFRN_DETECTOR
    _category.description
;              Data items in the DIFFRN_DETECTOR category describe the 
               detector used to measure the scattered radiation, including
               any analyser and post-sample collimation.
;
    _category.id                  diffrn_detector
    _category.mandatory_code      no
     loop_
    _category_key.name          '_diffrn_detector.diffrn_id'
                                '_diffrn_detector.id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
    Example 1 - based on PDB entry 5HVP and laboratory records for the
                structure corresponding to PDB entry 5HVP
;
;
    _diffrn_detector.diffrn_id             'd1'
    _diffrn_detector.detector              'multiwire'
    _diffrn_detector.type                  'Siemens'
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_
 
 
save__diffrn_detector.details
    _item_description.description
;              A description of special aspects of the radiation detector.
;
    _item.name                  '_diffrn_detector.details'
    _item.category_id             diffrn_detector
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_detector_details'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
    _item_examples.case
;                                 Need new example here.
;
     save_
 
 
save__diffrn_detector.detector
    _item_description.description
;              The general class of the radiation detector.
;
    _item.name                  '_diffrn_detector.detector'
    _item.category_id             diffrn_detector
    _item.mandatory_code          no
     loop_
    _item_aliases.alias_name
    _item_aliases.dictionary
    _item_aliases.version       '_diffrn_radiation_detector'
                                  cifdic.c91
                                  1.0
                                '_diffrn_detector'
                                  cif_core.dic
                                  2.0
    _item_type.code               text
     loop_
    _item_examples.case          'photographic film'
                                 'scintillation counter'
                                 'CCD plate'
                                 'BF~3~ counter'
     save_
 
 
save__diffrn_detector.diffrn_id
    _item_description.description
;              This data item is a pointer to _diffrn.id in the DIFFRN
               category.

               The value of _diffrn.id uniquely defines a set of
               diffraction data.
;
    _item.name                  '_diffrn_detector.diffrn_id'
    _item.mandatory_code          yes
     save_
 
 
save__diffrn_detector.dtime
    _item_description.description
;              The deadtime in microseconds of the detectors used to measure
               the diffraction intensities.
;
    _item.name                  '_diffrn_detector.dtime'
    _item.category_id             diffrn_detector
    _item.mandatory_code          no
     loop_
    _item_aliases.alias_name
    _item_aliases.dictionary
    _item_aliases.version       '_diffrn_radiation_detector_dtime'
                                  cifdic.c91
                                  1.0
                                '_diffrn_detector_dtime'
                                  cif_core.dic
                                  2.0
     loop_  
    _item_range.maximum           
    _item_range.minimum            .    0.0
                                  0.0   0.0
    _item_type.code               float
    _item_units.code              microseconds
     save_
 
 
save__diffrn_detector.id
    _item_description.description
;             
               The value of _diffrn_detector.id must uniquely identify
               each detector used to collect each diffraction data set.

               If the value of _diffrn_detector.id is not given, it is
               implicitly equal to the value of _diffrn_detector.diffrn_id
;
     loop_
    _item.name                 
    _item.category_id
    _item.mandatory_code
             '_diffrn_detector.id'         diffrn_detector       implicit
             '_diffrn_detector_axis.detector_id'
                                           diffrn_detector_axis       yes
     loop_
    _item_linked.child_name
    _item_linked.parent_name
             '_diffrn_detector_axis.detector_id'
                                         '_diffrn_detector.id'

    _item_type.code               code
     save_
 
 
save__diffrn_detector.number_of_axes
    _item_description.description
;             
               The value of _diffrn_detector.number_of_axes gives the 
               number of axes of the positioner for the detector identified 
               by _diffrn_detector.id
               
               The word "positioner" is a general term used in instrumentation
               design for devices that are used to change the positions of 
               portions of apparatus by linear translation, rotation, or 
               combinations of such motions.
               
               Axes which are used to provide a coordinate system for the
               face of an area detetctor should not be counted for this
               data item.

               The description of each axis should be provided by entries 
               in DIFFRN_DETECTOR_AXIS.
;
    _item.name                  '_diffrn_detector.number_of_axes'
    _item.category_id             diffrn_detector
    _item.mandatory_code          no
     loop_
    _item_range.maximum
    _item_range.minimum           .   1
                                  1   1
    _item_type.code               int
     save_
 
 
save__diffrn_detector.type
    _item_description.description
;              The make, model or name of the detector device used.
;
    _item.name                  '_diffrn_detector.type'
    _item.category_id             diffrn_detector
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_detector_type'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
     save_
 
 
########################
# DIFFRN_DETECTOR_AXIS #
########################
 
 
save_DIFFRN_DETECTOR_AXIS
    _category.description
;
     Data items in the DIFFRN_DETECTOR_AXIS category associate
     axes with detectors.
;
    _category.id                   diffrn_detector_axis
    _category.mandatory_code       no
     loop_
    _category_key.name          '_diffrn_detector_axis.detector_id'
                                '_diffrn_detector_axis.axis_id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     save_
 
 
save__diffrn_detector_axis.axis_id
    _item_description.description
;
               This data item is a pointer to _axis.id in
               the AXIS category.
;
    _item.name                  '_diffrn_detector_axis.axis_id'
    _item.category_id             diffrn_detector_axis
    _item.mandatory_code          yes
    _item_type.code               code
     save_
 
 
save__diffrn_detector_axis.detector_id
    _item_description.description
;
               This data item is a pointer to _diffrn_detector.id in
               the DIFFRN_DETECTOR category.

               This item was previously named '_diffrn_detector_axis.id'
               which is now a deprecated name.  The old name is
               provided as an alias, but should not be used for new work.

;
    _item.name                  '_diffrn_detector_axis.detector_id'
    _item.category_id             diffrn_detector_axis
    _item.mandatory_code          yes
    _item_aliases.alias_name    '_diffrn_detector_axis.id'
    _item_aliases.dictionary      cif_img.dic
    _item_aliases.version         1.0
     save_
 
 
###########################
# DIFFRN_DETECTOR_ELEMENT #
###########################
 
 
save_DIFFRN_DETECTOR_ELEMENT
    _category.description
;
              Data items in the DIFFRN_DETECTOR_ELEMENT category record
              the details about spatial layout and other characteristics
              of each element of a detector which may have multiple elements.
              
              In most cases, the more detailed information provided
              in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS
              are preferable to simply providing the centre.

;
    _category.id                   diffrn_detector_element
    _category.mandatory_code       no
     loop_
    _category_key.name             '_diffrn_detector_element.id'
                                   '_diffrn_detector_element.detector_id'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
        Example 1 - Detector d1 is composed of four CCD detector elements,
        each 200 mm by 200 mm, arranged in a square. in the pattern
                    
                   1     2
                      *
                   3     4

        Note that the beam center is slightly off of each of the
        detector elements, just beyond the lower right corner of 1,
        the lower left corner of 2, the upper right corner of 3 and
        the upper left corner of 4.
;
;
        loop_
        _diffrn_detector_element.id
        _diffrn_detector_element.detector_id
        _diffrn_detector_element.center[1]
        _diffrn_detector_element.center[2]
        d1     d1_ccd_1  201.5 -1.5
        d1     d1_ccd_2  -1.8  -1.5
        d1     d1_ccd_3  201.6 201.4  
        d1     d1_ccd_4  -1.7  201.5
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    save_
 
 
save__diffrn_detector_element.center[1]
    _item_description.description
;             
              The value of _diffrn_detector_element.center[1] is the X
              component of the distortion-corrected beam-center in mm from the
              (0, 0) (lower left) corner of the detector element viewed from 
              the sample side.
;
    _item.name                  '_diffrn_detector_element.center[1]'
    _item.category_id             diffrn_detector_element
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
    _item_units.code              millimetres

    save_
 
 
save__diffrn_detector_element.center[2]
    _item_description.description
;             
              The value of _diffrn_detector_element.center[2] is the Y
              component of the distortion-corrected beam-center in mm from the
              (0, 0) (lower left) corner of the detector element viewed from 
              the sample side.
;
    _item.name                  '_diffrn_detector_element.center[2]'
    _item.category_id             diffrn_detector_element
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
    _item_units.code              millimetres

    save_
 
 
save__diffrn_detector_element.id
    _item_description.description
;             
              The value of _diffrn_detector_element.id must uniquely identify
              each element of a detector.
;
     loop_
    _item.name                
    _item.category_id          
    _item.mandatory_code       
           '_diffrn_detector_element.id'
           diffrn_detector_element
           yes
    _item_type.code               code
     loop_
    _item_linked.child_name
    _item_linked.parent_name
           '_diffrn_data_frame.detector_element_id'
           '_diffrn_detector_element.id'

     save_
 
 
save__diffrn_detector_element.detector_id
    _item_description.description
;             
               This item is a pointer to _diffrn_detector.id
               in the DIFFRN_DETECTOR category. 
;
    _item.name                  '_diffrn_detector_element.detector_id'
    _item.category_id             diffrn_detector_element
    _item.mandatory_code          yes
    _item_type.code               code
     save_
 
 
 
########################
## DIFFRN_MEASUREMENT ##
########################
 
 
save_DIFFRN_MEASUREMENT
    _category.description
;              Data items in the DIFFRN_MEASUREMENT category record details
               about the device used to orient and/or position the crystal
               during data measurement and the manner in which the diffraction
               data were measured.
;
    _category.id                  diffrn_measurement
    _category.mandatory_code      no
     loop_
    _category_key.name          '_diffrn_measurement.device'
                                '_diffrn_measurement.diffrn_id'
                                '_diffrn_measurement.id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
    Example 1 - based on PDB entry 5HVP and laboratory records for the
                structure corresponding to PDB entry 5HVP
;
;
    _diffrn_measurement.diffrn_id          'd1'
    _diffrn_measurement.device             '3-circle camera'
    _diffrn_measurement.device_type        'Supper model x'
    _diffrn_measurement.device_details     'none'
    _diffrn_measurement.method             'omega scan'
    _diffrn_measurement.details
    ; Need new example here
    ;
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
    Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991).
                Acta Cryst. C47, 2276-2277].
;
;
    _diffrn_measurement.diffrn_id       's1'
    _diffrn_measurement.device_type     'Philips PW1100/20 diffractometer'
    _diffrn_measurement.method          'theta/2theta (\q/2\q)'
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_
 
 
save__diffrn_measurement.device
    _item_description.description
;              The general class of goniometer or device used to support and
               orient the specimen.
               
               If the value of _diffrn_measurement.device is not given, it is
               implicitly equal to the value of _diffrn_measurement.diffrn_id

               Either '_diffrn_measurement.device' or '_diffrn_measurement.id'
               may be used to link to other categories.  If the experimental
               setup admits multiple devices, then '_diffrn_measurement.id'
               is used to provide a unique link.
               
;
     loop_
    _item.name
    _item.category_id
    _item.mandatory_code
             '_diffrn_measurement.device'  diffrn_measurement      implicit
             '_diffrn_measurement_axis.measurement_device' 
                                           diffrn_measurement_axis implicit
     loop_
    _item_linked.child_name
    _item_linked.parent_name
             '_diffrn_measurement_axis.measurement_device'  
                                         '_diffrn_measurement.device'
    _item_aliases.alias_name    '_diffrn_measurement_device'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
     loop_
    _item_examples.case          '3-circle camera'
                                 '4-circle camera'
                                 'kappa-geometry camera'
                                 'oscillation camera'
                                 'precession camera'
     save_
 
 
save__diffrn_measurement.device_details
    _item_description.description
;              A description of special aspects of the device used to measure
               the diffraction intensities.
;
    _item.name                  '_diffrn_measurement.device_details'
    _item.category_id             diffrn_measurement
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_measurement_device_details'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
    _item_examples.case
;                                 commercial goniometer modified locally to
                                  allow for 90\% \t arc
;
     save_
 
 
save__diffrn_measurement.device_type
    _item_description.description
;              The make, model or name of the measurement device
               (goniometer) used.
;
    _item.name                  '_diffrn_measurement.device_type'
    _item.category_id             diffrn_measurement
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_measurement_device_type'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
     loop_
    _item_examples.case          'Supper model q'
                                 'Huber model r'
                                 'Enraf-Nonius model s'
                                 'homemade'
     save_
 
 
save__diffrn_measurement.diffrn_id
    _item_description.description
;              This data item is a pointer to _diffrn.id in the DIFFRN 
               category.
;
    _item.name                  '_diffrn_measurement.diffrn_id'
    _item.mandatory_code          yes
     save_
 
 
save__diffrn_measurement.details
    _item_description.description
;              A description of special aspects of the intensity measurement.
;
    _item.name                  '_diffrn_measurement.details'
    _item.category_id             diffrn_measurement
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_measurement_details'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
    _item_examples.case
;                                 440 frames, 0.20 degrees, 150 sec, detector
                                  distance 12 cm, detector angle 22.5 degrees
;
     save_
 
 
save__diffrn_measurement.id
    _item_description.description
;             
               The value of _diffrn_measurement.id must uniquely identify
               the set of mechanical characteristics of the device used to 
               orient and/or position the sample used during collection 
               of each diffraction data set.

               If the value of _diffrn_measurement.id is not given, it is
               implicitly equal to the value of _diffrn_measurement.diffrn_id

               Either '_diffrn_measurement.device' or '_diffrn_measurement.id'
               may be used to link to other categories.  If the experimental
               setup admits multiple devices, then '_diffrn_measurement.id'
               is used to provide a unique link.
;
     loop_
    _item.name                 
    _item.category_id
    _item.mandatory_code
             '_diffrn_measurement.id'      diffrn_measurement      implicit
             '_diffrn_measurement_axis.measurement_id'
                                           diffrn_measurement_axis implicit
     loop_
    _item_linked.child_name
    _item_linked.parent_name
             '_diffrn_measurement_axis.measurement_id'
                                         '_diffrn_measurement.id'

    _item_type.code               code
     save_
 
 
save__diffrn_measurement.method
    _item_description.description
;              Method used to measure intensities.
;
    _item.name                  '_diffrn_measurement.method'
    _item.category_id             diffrn_measurement
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_measurement_method'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
    _item_examples.case         'profile data from theta/2theta (\q/2\q) scans'
     save_
 
 
save__diffrn_measurement.number_of_axes
    _item_description.description
;             
               The value of _diffrn_measurement.number_of_axes gives the 
               number of axes of the positioner for the goniometer or
               other sample orientation or positioning device identified 
               by _diffrn_measurement.id

               The description of the axes should be provided by entries in 
               DIFFRN_MEASUREMENT_AXIS.
;
    _item.name                  '_diffrn_measurement.number_of_axes'
    _item.category_id             diffrn_measurement
    _item.mandatory_code          no
     loop_
    _item_range.maximum
    _item_range.minimum           .   1
                                  1   1
    _item_type.code               int
     save_
 
 
save__diffrn_measurement.specimen_support
    _item_description.description
;              The physical device used to support the crystal during data
               collection.
;
    _item.name                  '_diffrn_measurement.specimen_support'
    _item.category_id             diffrn_measurement
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_measurement_specimen_support'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
     loop_
    _item_examples.case          'glass capillary'
                                 'quartz capillary'
                                 'fiber'
                                 'metal loop'
     save_
 
 
###########################
# DIFFRN_MEASUREMENT_AXIS #
###########################
 
 
save_DIFFRN_MEASUREMENT_AXIS
    _category.description
;
     Data items in the DIFFRN_MEASUREMENT_AXIS category associate
     axes with goniometers.
;
    _category.id                   diffrn_measurement_axis
    _category.mandatory_code       no
     loop_
    _category_key.name          '_diffrn_measurement_axis.measurement_device'
                                '_diffrn_measurement_axis.measurement_id'
                                '_diffrn_measurement_axis.axis_id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     save_
 
 
save__diffrn_measurement_axis.axis_id
    _item_description.description
;
               This data item is a pointer to _axis.id in
               the AXIS category.
;
    _item.name                  '_diffrn_measurement_axis.axis_id'
    _item.category_id             diffrn_measurement_axis
    _item.mandatory_code          yes
    _item_type.code               code
     save_
 
 
save__diffrn_measurement_axis.measurement_device
    _item_description.description
;
               This data item is a pointer to _diffrn_measurement.device in
               the DIFFRN_MEASUREMENT category.

;
    _item.name                  '_diffrn_measurement_axis.measurement_device'
    _item.category_id             diffrn_measurement_axis
    _item.mandatory_code          implicit
     save_
 
 
save__diffrn_measurement_axis.measurement_id
    _item_description.description
;
               This data item is a pointer to _diffrn_measurement.id in
               the DIFFRN_MEASUREMENT category.
              
               This item was previously named '_diffrn_measurement_axis.id'
               which is now a deprecated name.  The old name is
               provided as an alias, but should not be used for new work.

;
    _item.name                  '_diffrn_measurement_axis.measurement_id'
    _item.category_id             diffrn_measurement_axis
    _item_aliases.alias_name    '_diffrn_measurement_axis.id'
    _item_aliases.dictionary      cif_img.dic
    _item_aliases.version         1.0.00
    _item.mandatory_code          implicit
     save_

 
####################
# DIFFRN_RADIATION #
####################
 
 
save_DIFFRN_RADIATION
    _category.description
;              Data items in the DIFFRN_RADIATION category describe
               the radiation used in measuring diffraction intensities,
               its collimation and monochromatisation before the sample.

               Post-sample treatment of the beam is described by data
               items in the DIFFRN_DETECTOR category.

;
    _category.id                  diffrn_radiation
    _category.mandatory_code      no
    _category_key.name          '_diffrn_radiation.diffrn_id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
    Example 1 - based on PDB entry 5HVP and laboratory records for the
                structure corresponding to PDB entry 5HVP
;
;
    _diffrn_radiation.diffrn_id            'set1'

    _diffrn_radiation.collimation          '0.3 mm double pinhole'
    _diffrn_radiation.monochromator        'graphite'
    _diffrn_radiation.type                 'Cu K\a'
    _diffrn_radiation.wavelength_id         1
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
    Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991).
                Acta Cryst. C47, 2276-2277].
;
;
    _diffrn_radiation.wavelength_id    1
    _diffrn_radiation.type             'Cu K\a'
    _diffrn_radiation.monochromator    'graphite'
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_

save__diffrn_radiation.collimation
    _item_description.description
;              The collimation or focusing applied to the radiation.
;
    _item.name                  '_diffrn_radiation.collimation'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_collimation'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
     loop_
    _item_examples.case          '0.3 mm double-pinhole'
                                 '0.5 mm'
                                 'focusing mirrors'
     save_


save__diffrn_radiation.diffrn_id
    _item_description.description
;              This data item is a pointer to _diffrn.id in the DIFFRN
               category.
;
    _item.name                  '_diffrn_radiation.diffrn_id'
    _item.mandatory_code          yes
     save_

 
 
save__diffrn_radiation.div_x_source
    _item_description.description
;              Beam crossfire in degrees parallel to the laboratory X axis
               (see AXIS category).
               
               This is a characteristic of the xray beam as it illuminates
               the sample (or specimen) after all monochromation and 
               collimation.
               
               This is the esd of the directions of photons in the X-Z plane
               around the mean source beam direction.
               
               Note that some synchrotrons specify this value in milliradians,
               in which case a conversion would be needed.  To go from a
               value in milliradians to a value in degrees, multiply by 0.180
               and divide by Pi.

;
    _item.name                  '_diffrn_radiation.div_x_source'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_type.code               float
    _item_units.code              degrees
     save_
 
 
save__diffrn_radiation.div_y_source
    _item_description.description
;              Beam crossfire in degrees parallel to the laboratory Y axis
               (see AXIS category).
               
               This is a characteristic of the xray beam as it illuminates
               the sample (or specimen) after all monochromation and 
               collimation.
               
               This is the esd of the directions of photons in the Y-Z plane
               around the mean source beam direction.

               Note that some synchrotrons specify this value in milliradians,
               in which case a conversion would be needed.  To go from a
               value in milliradians to a value in degrees, multiply by 0.180
               and divide by Pi.

;
    _item.name                  '_diffrn_radiation.div_y_source'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_type.code               float
    _item_units.code              degrees
    _item_default.value           0.0
     save_
 
 
save__diffrn_radiation.div_x_y_source
    _item_description.description
;              Beam crossfire correlation degrees**2 between the
               crossfire laboratory X-axis component and the crossfire
               laboratory Y-axis component (see AXIS category).
               
               This is a characteristic of the xray beam as it illuminates
               the sample (or specimen) after all monochromation and 
               collimation.
               
               This is the mean of the products of the deviations of the
               directin of each photons in X-Z plane times the deviations
               of the direction of the same photon in the Y-Z plane
               around the mean source beam direction.  This will be zero
               for uncorrelated crossfire.
               
               Note that some synchrotrons specify this value in 
               milliradians**2, in which case a conversion would be needed.  
               To go from a value in milliradians**2 to a value in
               degrees**2, multiply by 0.180**2 and divide by Pi**2.

;
    _item.name                  '_diffrn_radiation.div_x_y_source'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_type.code               float
    _item_units.code              degrees_squared
    _item_default.value           0.0
     save_

save__diffrn_radiation.filter_edge
    _item_description.description
;              Absorption edge in angstroms of the radiation filter used.
;
    _item.name                  '_diffrn_radiation.filter_edge'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_filter_edge'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
     loop_
    _item_range.maximum           
    _item_range.minimum            .    0.0
                                  0.0   0.0
    _item_type.code               float
    _item_units.code              angstroms
     save_

save__diffrn_radiation.inhomogeneity
    _item_description.description
;              Half-width in millimetres of the incident beam in the
               direction perpendicular to the diffraction plane.
;
    _item.name                  '_diffrn_radiation.inhomogeneity'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_inhomogeneity'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
     loop_
    _item_range.maximum           
    _item_range.minimum            .    0.0
                                  0.0   0.0
    _item_type.code               float
    _item_units.code              millimetres
     save_

save__diffrn_radiation.monochromator
    _item_description.description
;              The method used to obtain monochromatic radiation. If a mono-
               chromator crystal is used the material and the indices of the
               Bragg reflection are specified.
;
    _item.name                  '_diffrn_radiation.monochromator'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_monochromator'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
     loop_
    _item_examples.case          'Zr filter'
                                 'Ge 220'
                                 'none'
                                 'equatorial mounted graphite'
     save_

save__diffrn_radiation.polarisn_norm
    _item_description.description
;              The angle in degrees, as viewed from the specimen, between the
               perpendicular component of the polarisation and the diffraction
               plane. See _diffrn_radiation_polarisn_ratio.
;
    _item.name                  '_diffrn_radiation.polarisn_norm'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_polarisn_norm'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
     loop_
    _item_range.maximum           
    _item_range.minimum           90.0  90.0
                                  90.0 -90.0
                                 -90.0 -90.0
    _item_type.code               float
    _item_units.code              degrees
     save_

save__diffrn_radiation.polarisn_ratio
    _item_description.description
;              Polarisation ratio of the diffraction beam incident on the
               crystal. It is the ratio of the perpendicularly polarised to the
               parallel polarised component of the radiation. The perpendicular
               component forms an angle of _diffrn_radiation.polarisn_norm to
               the normal to the diffraction plane of the sample (i.e. the
               plane containing the incident and reflected beams).
;
    _item.name                  '_diffrn_radiation.polarisn_ratio'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_polarisn_ratio'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
     loop_
    _item_range.maximum           
    _item_range.minimum            .    0.0
                                  0.0   0.0
    _item_type.code               float
     save_

 
 
save__diffrn_radiation.polarizn_source_norm
    _item_description.description
;              The angle in degrees, as viewed from the specimen, between the
               normal to the polarization plane and the laboratory Y axis as
               defined in the AXIS category.
               
               Note that this is the angle of polarization of the source 
               photons, either directly from a synchrotron beamline or
               from a monchromater.
               
               This differs from the value of '_diffrn_radiation.polarisn_norm'
               in that '_diffrn_radiation.polarisn_norm' refers to polarization
               relative to the diffraction plane rather than to the laboratory
               axis system.
               
               In the case of an unpolarized beam, or a beam with true circular
               polarization, in which no single plane of polarization can be
               determined, the plane should be taken as the X-Z plane, and the
               angle as 0.
               
               See '_diffrn_radiation.polarizn_source_ratio'.
;
    _item.name                  '_diffrn_radiation.polarizn_source_norm'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
     loop_
    _item_range.maximum           
    _item_range.minimum           90.0   90.0
                                  90.0  -90.0
                                 -90.0  -90.0
    _item_type.code               float
    _item_units.code              degrees
    _item_default.value           0.0
     save_
 
 
save__diffrn_radiation.polarizn_source_ratio
    _item_description.description
;              (Ip-In)/(Ip+In), where Ip is the intensity (amplitude squared)
               of the electric vector in the plane of polarization and In is
               the intensity (amplitude squared) of the electric vector
               in plane of the normal to the plane of polarization.
               
               Thus, if we had complete polarization in the plane of
               polarization, the value of 
               '_diffrn_radiation.polarizn_source_ratio' would
               be 1, and an unpolarized beam would have a value of 0.
               
               If the X-axis has been chosen to lie in the plane of
               polarization, this definition will agree with the definition
               of "MONOCHROMATOR" in the Denzo glossary, and values of near
               1 should be expected for a bending magnet source.  However,
               if the X-axis were, for some reason to be, say, perpendicular
               to the polarization plane (not a common choice), then the
               Denzo value would be the negative of
               '_diffrn_radiation.polarizn_source_ratio'.
               
               See http://www.hkl-xray.com for information on Denzo, and
               Z. Otwinowski and W. Minor, " Processing of X-ray Diffraction
               Data Collected in Oscillation Mode ", Methods in Enzymology, 
               Volume 276: Macromolecular Crystallography, part A, p.307-326,
               1997,C.W. Carter, Jr. & R. M. Sweet, Eds., Academic Press.

               This differs both in the choice of ratio and choice of
               orientation from '_diffrn_radiation.polarisn_ratio', which,
               unlike '_diffrn_radiation.polarizn_source_ratio', is unbounded.

;
    _item.name                  '_diffrn_radiation.polarizn_source_ratio'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
     loop_
    _item_range.maximum           
    _item_range.minimum           1.0    1.0
                                  1.0   -1.0
                                 -1.0   -1.0
    _item_type.code               float
     save_


save__diffrn_radiation.probe
    _item_description.description
;              Name of the type of radiation used. It is strongly encouraged
               that this field be specified so that the probe radiation
               can be simply determined.
;
    _item.name                  '_diffrn_radiation.probe'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_probe'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               line
     loop_
    _item_enumeration.value      'x-ray'
                                 'neutron'
                                 'electron'
                                 'gamma'
     save_

save__diffrn_radiation.type
    _item_description.description
;              The nature of the radiation. This is typically a description
               of the X-ray wavelength in Siegbahn notation.
;
    _item.name                  '_diffrn_radiation.type'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_type'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               line
     loop_
    _item_examples.case          'CuK\a'
                                 'Cu K\a~1~'
                                 'Cu K-L~2,3~' 
                                 'white-beam'

     save_

save__diffrn_radiation.xray_symbol
    _item_description.description
;              The IUPAC symbol for the X-ray wavelength for probe radiation.
;
    _item.name                  '_diffrn_radiation.xray_symbol'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_xray_symbol'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               line
     loop_
    _item_enumeration.value
    _item_enumeration.detail     'K-L~3~'
                                 'K\a~1~ in older Siegbahn notation'
                                 'K-L~2~'
                                 'K\a~2~ in older Siegbahn notation'
                                 'K-M~3~'
                                 'K\b~1~ in older Siegbahn notation'
                                 'K-L~2,3~'
                                 'use where K-L~3~ and K-L~2~ are not resolved'
     save_

save__diffrn_radiation.wavelength_id
    _item_description.description
;              This data item is a pointer to _diffrn_radiation_wavelength.id
               in the DIFFRN_RADIATION_WAVELENGTH category.
;
    _item.name                  '_diffrn_radiation.wavelength_id'
    _item.mandatory_code          yes
     save_


 
################
# DIFFRN_REFLN #
################
 
 
save_DIFFRN_REFLN
    _category.description 
;
     This category redefinition has been added to extend the key of 
     the standard DIFFRN_REFLN category.
;
    _category.id                   diffrn_refln
    _category.mandatory_code       no
    _category_key.name             '_diffrn_refln.frame_id'
     loop_
    _category_group.id             'inclusive_group'
                                   'diffrn_group'
     save_
 
 
save__diffrn_refln.frame_id
    _item_description.description
;             
               This item is a pointer to _diffrn_data_frame.id
               in the DIFFRN_DATA_FRAME category. 
;
    _item.name                  '_diffrn_refln.frame_id'
    _item.category_id             diffrn_refln
    _item.mandatory_code          yes
    _item_type.code               code
     save_
 
 
###############
# DIFFRN_SCAN #
###############

save_DIFFRN_SCAN
    _category.description 
;
     Data items in the DIFFRN_SCAN category describe the parameters of one
     or more scans, relating axis positions to frames.

;
    _category.id                   diffrn_scan
    _category.mandatory_code       no
    _category_key.name            '_diffrn_scan.id'
     loop_
    _category_group.id            'inclusive_group'
                                  'diffrn_group'
     loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
    Example 1 - derived from a suggestion by R. M. Sweet.

   The vector of each axis is not given here, because it is provided in
   the AXIS category.  By making _diffrn_scan_axis.scan_id and
   _diffrn_scan_axis.axis_id keys of the DIFFRN_SCAN_AXIS category,
   an arbitrary number of scanning and fixed axes can be specified for a 
   scan.  We have specified three rotation axes and one translation axis 
   at non-zero values, with one axis stepping.  There is no reason why 
   more axes could not have been specified to step.   We have specified
   range information, but note that it is redundant from the  number of 
   frames and the increment, so we could drop the data item
   _diffrn_scan_axis.angle_range .
   
   We have specified both the sweep data and the data for a single frame.
 
   Note that the information on how the axes are stepped is given twice,
   once in terms of the overall averages in the value of
   '_diffrn_scan.integration_time' and the values for DIFFRN_SCAN_AXIS,
   and precisely for the given frame in the value for 
   '_diffrn_scan_frame.integration_time' and the values for
   DIFFRN_SCAN_FRAME_AXIS.  If dose-related adjustements are made to
   scan times and non-linear stepping is done, these values may differ.
   Therefore, in interpreting the data for a particular frame it is
   important to use the frame-specific data.
 
;
;
      _diffrn_scan.id                   1
      _diffrn_scan.date_start         '2001-11-18T03:26:42'
      _diffrn_scan.date_end           '2001-11-18T03:36:45'
      _diffrn_scan.integration_time    3.0
      _diffrn_scan.frame_id_start      mad_L2_000
      _diffrn_scan.frame_id_end        mad_L2_200
      _diffrn_scan.frames              201

       loop_
      _diffrn_scan_axis.scan_id
      _diffrn_scan_axis.axis_id
      _diffrn_scan_axis.angle_start
      _diffrn_scan_axis.angle_range
      _diffrn_scan_axis.angle_increment
      _diffrn_scan_axis.displacement_start
      _diffrn_scan_axis.displacement_range
      _diffrn_scan_axis.displacement_increment

       1 omega 200.0 20.0 0.1 . . . 
       1 kappa -40.0  0.0 0.0 . . . 
       1 phi   127.5  0.0 0.0 . . . 
       1 tranz  . . .   2.3 0.0 0.0 

      _diffrn_scan_frame.scan_id                   1
      _diffrn_scan_frame.date               '2001-11-18T03:27:33'
      _diffrn_scan_frame.integration_time    3.0
      _diffrn_scan_frame.frame_id            mad_L2_018
      _diffrn_scan_frame.frame_number        18

      loop_
      _diffrn_scan_frame_axis.frame_id
      _diffrn_scan_frame_axis.axis_id
      _diffrn_scan_frame_axis.angle
      _diffrn_scan_frame_axis.angle_increment
      _diffrn_scan_frame_axis.displacement
      _diffrn_scan_frame_axis.displacement_increment

       mad_L2_018 omega 201.8  0.1 . .
       mad_L2_018 kappa -40.0  0.0 . .
       mad_L2_018 phi   127.5  0.0 . .
       mad_L2_018 tranz  .     .  2.3 0.0

;

;
    Example 2 - a more extensive example, R. M. Sweet, P. Ellis, H. Bernstein.
    
   We place a detector 240 mm along the Z axis from the goniometer.
   This presents us with a choice -- either we define the axes of
   the detector at the origin, and then put a Z setting of -240 in
   for the actual use, or we define the axes with the necessary Z-offset.
   In this case we use the setting, and leave the offset as zero.
   We call this axis DETECTOR_Z.
   
   The axis for positioning the detector in the Y-direction depends
   on the detector Z-axis.  We call this axis, DETECTOR_Y.
   
   The axis for positioning the dector in the X-direction depends
   on the detector Y-axis (and therefore on the detector Z-axis).
   We call this axis DETECTOR_X.
   
   This detector may be rotated around the Y-axis.  This rotation axis
   depends on the three translation axies.  We call it DETECTOR_PITCH.
   
   We define a coordinate system on the face of the detector in terms of
   2300 0.150 mm pixels in each direction.  The ELEMENT_X axis is used to
   index the first array index of the data array and the ELEMENT_Y
   axis is used to index the second array index.  Because the pixels
   are 0.150mm x 0.150mm, the center of the first pixel is at (0.075, 
   0.075) in this coordinate system.
 
;
;
     ###CBF: VERSION 1.1 

     data_image_1 
 

     # category DIFFRN 

     _diffrn.id P6MB 
     _diffrn.crystal_id P6MB_CRYSTAL7 
 

     # category DIFFRN_SOURCE 

     loop_ 
     _diffrn_source.diffrn_id 
     _diffrn_source.source 
     _diffrn_source.type 
      P6MB synchrotron 'SSRL beamline 9-1' 
 

     # category DIFFRN_RADIATION 

          loop_ 
     _diffrn_radiation.diffrn_id 
     _diffrn_radiation.wavelength_id 
     _diffrn_radiation.monochromator 
     _diffrn_radiation.polarizn_source_ratio 
     _diffrn_radiation.polarizn_source_norm 
     _diffrn_radiation.div_x_source 
     _diffrn_radiation.div_y_source 
     _diffrn_radiation.div_x_y_source 
      P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08
     0.01 0.00 
 

     # category DIFFRN_RADIATION_WAVELENGTH 

     loop_ 
     _diffrn_radiation_wavelength.id 
     _diffrn_radiation_wavelength.wavelength 
     _diffrn_radiation_wavelength.wt 
      WAVELENGTH1 0.98 1.0 
 

     # category DIFFRN_DETECTOR 

     loop_ 
     _diffrn_detector.diffrn_id 
     _diffrn_detector.id 
     _diffrn_detector.type 
     _diffrn_detector.number_of_axes 
      P6MB MAR345-SN26 'MAR 345' 4 
 

     # category DIFFRN_DETECTOR_AXIS 

     loop_ 
     _diffrn_detector_axis.id 
     _diffrn_detector_axis.axis_id 
      MAR345-SN26 DETECTOR_X 
      MAR345-SN26 DETECTOR_Y 
      MAR345-SN26 DETECTOR_Z 
      MAR345-SN26 DETECTOR_PITCH 
 

     # category DIFFRN_DETECTOR_ELEMENT 

     loop_ 
     _diffrn_detector_element.id 
     _diffrn_detector_element.detector_id 
      ELEMENT1 MAR345-SN26 
 

     # category DIFFRN_DATA_FRAME 

     loop_ 
     _diffrn_data_frame.id 
     _diffrn_data_frame.detector_element_id 
     _diffrn_data_frame.array_id 
     _diffrn_data_frame.binary_id 
      FRAME1 ELEMENT1 ARRAY1 1 
 

     # category DIFFRN_MEASUREMENT 

     loop_ 
     _diffrn_measurement.diffrn_id 
     _diffrn_measurement.id 
     _diffrn_measurement.number_of_axes 
     _diffrn_measurement.method 
      P6MB GONIOMETER 3 rotation 
 

     # category DIFFRN_MEASUREMENT_AXIS 

     loop_ 
     _diffrn_measurement_axis.measurement_id 
     _diffrn_measurement_axis.axis_id 
      GONIOMETER GONIOMETER_PHI 
      GONIOMETER GONIOMETER_KAPPA 
      GONIOMETER GONIOMETER_OMEGA 
 

     # category DIFFRN_SCAN 

     loop_ 
     _diffrn_scan.id 
     _diffrn_scan.frame_id_start 
     _diffrn_scan.frame_id_end 
     _diffrn_scan.frames 
      SCAN1 FRAME1 FRAME1 1 
 

     # category DIFFRN_SCAN_AXIS 

     loop_ 
     _diffrn_scan_axis.scan_id 
     _diffrn_scan_axis.axis_id 
     _diffrn_scan_axis.angle_start 
     _diffrn_scan_axis.angle_range 
     _diffrn_scan_axis.angle_increment 
     _diffrn_scan_axis.displacement_start 
     _diffrn_scan_axis.displacement_range 
     _diffrn_scan_axis.displacement_increment 
      SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 
      SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 
      SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 
      SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 
      SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 
      SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 
      SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 
 

     # category DIFFRN_SCAN_FRAME 

     loop_ 
     _diffrn_scan_frame.frame_id 
     _diffrn_scan_frame.frame_number 
     _diffrn_scan_frame.integration_time 
     _diffrn_scan_frame.scan_id 
     _diffrn_scan_frame.date 
      FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 
 

     # category DIFFRN_SCAN_FRAME_AXIS 

     loop_ 
     _diffrn_scan_frame_axis.frame_id 
     _diffrn_scan_frame_axis.axis_id 
     _diffrn_scan_frame_axis.angle 
     _diffrn_scan_frame_axis.displacement 
      FRAME1 GONIOMETER_OMEGA 12.0 0.0 
      FRAME1 GONIOMETER_KAPPA 23.3 0.0 
      FRAME1 GONIOMETER_PHI -165.8 0.0 
      FRAME1 DETECTOR_Z 0.0 -240.0 
      FRAME1 DETECTOR_Y 0.0 0.6 
      FRAME1 DETECTOR_X 0.0 -0.5 
      FRAME1 DETECTOR_PITCH 0.0 0.0 
 

     # category AXIS 

     loop_ 
     _axis.id 
     _axis.type 
     _axis.equipment 
     _axis.depends_on 
     _axis.vector[1] _axis.vector[2] _axis.vector[3] 
     _axis.offset[1] _axis.offset[2] _axis.offset[3] 
      GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . 
      GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279
      0 0.76604 . . . 
      GONIOMETER_PHI   rotation goniometer GONIOMETER_KAPPA 1 0 0
     . . . 
      SOURCE           general source . 0 0 1 . . . 
      GRAVITY          general gravity . 0 -1 0 . . . 
      DETECTOR_Z       translation detector . 0 0 1 0 0 0
      DETECTOR_Y       translation detector DETECTOR_Z 0 1 0 0 0 0 
      DETECTOR_X       translation detector DETECTOR_Y 1 0 0 0 0 0 
      DETECTOR_PITCH   rotation    detector DETECTOR_X 0 1 0 0 0 0 
      ELEMENT_X        translation detector DETECTOR_PITCH
     1 0 0 172.43 -172.43 0
      ELEMENT_Y        translation detector ELEMENT_X
     0 1 0 0 0 0 
 
     # category ARRAY_STRUCTURE_LIST 

     loop_ 
     _array_structure_list.array_id 
     _array_structure_list.index 
     _array_structure_list.dimension 
     _array_structure_list.precedence 
     _array_structure_list.direction 
     _array_structure_list.axis_set_id 
      ARRAY1 1 2300 1 increasing ELEMENT_X 
      ARRAY1 2 2300 2 increasing ELEMENT_Y 
 
 
     # category ARRAY_STRUCTURE_LIST_AXIS 

     loop_
     _array_structure_list_axis.axis_set_id
     _array_structure_list_axis.axis_id
     _array_structure_list_axis.displacement
     _array_structure_list_axis.displacement_increment
      ELEMENT_X ELEMENT_X 0.075 0.150
      ELEMENT_Y ELEMENT_Y 0.075 0.150

     # category ARRAY_ELEMENT_SIZE 

     loop_ 
     _array_element_size.array_id 
     _array_element_size.index 
     _array_element_size.size 
      ARRAY1 1 150e-6 
      ARRAY1 2 150e-6 
 

     # category ARRAY_INTENSITIES 

     loop_ 
     _array_intensities.array_id 
     _array_intensities.binary_id 
     _array_intensities.linearity 
     _array_intensities.gain 
     _array_intensities.gain_esd 
     _array_intensities.overload
     _array_intensities.undefined_value 
      ARRAY1 1 linear 1.15 0.2 240000 0 
 

      # category ARRAY_STRUCTURE 

      loop_ 
      _array_structure.id 
      _array_structure.encoding_type 
      _array_structure.compression_type 
      _array_structure.byte_order 
      ARRAY1 "signed 32-bit integer" packed little_endian 
 

     # category ARRAY_DATA         

     loop_ 
     _array_data.array_id 
     _array_data.binary_id 
     _array_data.data 
      ARRAY1 1 
     ; 
     --CIF-BINARY-FORMAT-SECTION-- 
     Content-Type: application/octet-stream; 
         conversions="x-CBF_PACKED" 
     Content-Transfer-Encoding: BASE64 
     X-Binary-Size: 3801324 
     X-Binary-ID: 1 
     X-Binary-Element-Type: "signed 32-bit integer" 
     Content-MD5: 07lZFvF+aOcW85IN7usl8A== 

     AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg 
     ... 
     8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE 

     --CIF-BINARY-FORMAT-SECTION---- 
     ; 
;

;
    Example 3 - Example 2 revised for a spiral scan, R. M. Sweet, 
    P. Ellis, H. Bernstein.
    
   We place a detector 240 mm along the Z axis from the goniometer,
   as in Example 2, above, but in this example, the image plate is
   scanned in a spiral pattern outside edge in.
   
   The axis for positioning the detector in the Y-direction depends
   on the detector Z-axis.  We call this axis, DETECTOR_Y.
   
   The axis for positioning the dector in the X-direction depends
   on the detector Y-axis (and therefore on the detector Z-axis).
   We call this axis DETECTOR_X.
   
   This detector may be rotated around the Y-axis.  This rotation axis
   depends on the three translation axies.  We call it DETECTOR_PITCH.
 
   We define a coordinate system on the face of the detector in
   terms of a coupled rotation axis and radial scan axis to form 
   a spiral scan.  Let us call rotation axis ELEMENT_ROT, and the
   radial axis ELEMENT_RAD.   We assume 150 um radial pitch and 75 um 
   'constant velocity' angular pitch. 

   We index first on the rotation axis and make the radial axis
   dependent on 
   it. 

   The two axes are coupled to form an axis set ELEMENT_SPIRAL. 
 
;
;
     ###CBF: VERSION 1.1 

     data_image_1 
 

     # category DIFFRN 

     _diffrn.id P6MB 
     _diffrn.crystal_id P6MB_CRYSTAL7 
 

     # category DIFFRN_SOURCE 

     loop_ 
     _diffrn_source.diffrn_id 
     _diffrn_source.source 
     _diffrn_source.type 
      P6MB synchrotron 'SSRL beamline 9-1' 
 

     # category DIFFRN_RADIATION 

          loop_ 
     _diffrn_radiation.diffrn_id 
     _diffrn_radiation.wavelength_id 
     _diffrn_radiation.monochromator 
     _diffrn_radiation.polarizn_source_ratio 
     _diffrn_radiation.polarizn_source_norm 
     _diffrn_radiation.div_x_source 
     _diffrn_radiation.div_y_source 
     _diffrn_radiation.div_x_y_source 
      P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08
     0.01 0.00 
 

     # category DIFFRN_RADIATION_WAVELENGTH 

     loop_ 
     _diffrn_radiation_wavelength.id 
     _diffrn_radiation_wavelength.wavelength 
     _diffrn_radiation_wavelength.wt 
      WAVELENGTH1 0.98 1.0 
 

     # category DIFFRN_DETECTOR 

     loop_ 
     _diffrn_detector.diffrn_id 
     _diffrn_detector.id 
     _diffrn_detector.type 
     _diffrn_detector.number_of_axes 
      P6MB MAR345-SN26 'MAR 345' 4 
 

     # category DIFFRN_DETECTOR_AXIS 

     loop_ 
     _diffrn_detector_axis.id 
     _diffrn_detector_axis.axis_id 
      MAR345-SN26 DETECTOR_X 
      MAR345-SN26 DETECTOR_Y 
      MAR345-SN26 DETECTOR_Z 
      MAR345-SN26 DETECTOR_PITCH 
 

     # category DIFFRN_DETECTOR_ELEMENT 

     loop_ 
     _diffrn_detector_element.id 
     _diffrn_detector_element.detector_id 
      ELEMENT1 MAR345-SN26 
 

     # category DIFFRN_DATA_FRAME 

     loop_ 
     _diffrn_data_frame.id 
     _diffrn_data_frame.detector_element_id 
     _diffrn_data_frame.array_id 
     _diffrn_data_frame.binary_id 
      FRAME1 ELEMENT1 ARRAY1 1 
 

     # category DIFFRN_MEASUREMENT 

     loop_ 
     _diffrn_measurement.diffrn_id 
     _diffrn_measurement.id 
     _diffrn_measurement.number_of_axes 
     _diffrn_measurement.method 
      P6MB GONIOMETER 3 rotation 
 

     # category DIFFRN_MEASUREMENT_AXIS 

     loop_ 
     _diffrn_measurement_axis.measurement_id 
     _diffrn_measurement_axis.axis_id 
      GONIOMETER GONIOMETER_PHI 
      GONIOMETER GONIOMETER_KAPPA 
      GONIOMETER GONIOMETER_OMEGA 
 

     # category DIFFRN_SCAN 

     loop_ 
     _diffrn_scan.id 
     _diffrn_scan.frame_id_start 
     _diffrn_scan.frame_id_end 
     _diffrn_scan.frames 
      SCAN1 FRAME1 FRAME1 1 
 

     # category DIFFRN_SCAN_AXIS 

     loop_ 
     _diffrn_scan_axis.scan_id 
     _diffrn_scan_axis.axis_id 
     _diffrn_scan_axis.angle_start 
     _diffrn_scan_axis.angle_range 
     _diffrn_scan_axis.angle_increment 
     _diffrn_scan_axis.displacement_start 
     _diffrn_scan_axis.displacement_range 
     _diffrn_scan_axis.displacement_increment 
      SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 
      SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 
      SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 
      SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 
      SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 
      SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 
      SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 
 

     # category DIFFRN_SCAN_FRAME 

     loop_ 
     _diffrn_scan_frame.frame_id 
     _diffrn_scan_frame.frame_number 
     _diffrn_scan_frame.integration_time 
     _diffrn_scan_frame.scan_id 
     _diffrn_scan_frame.date 
      FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 
 

     # category DIFFRN_SCAN_FRAME_AXIS 

     loop_ 
     _diffrn_scan_frame_axis.frame_id 
     _diffrn_scan_frame_axis.axis_id 
     _diffrn_scan_frame_axis.angle 
     _diffrn_scan_frame_axis.displacement 
      FRAME1 GONIOMETER_OMEGA 12.0 0.0 
      FRAME1 GONIOMETER_KAPPA 23.3 0.0 
      FRAME1 GONIOMETER_PHI -165.8 0.0 
      FRAME1 DETECTOR_Z 0.0 -240.0 
      FRAME1 DETECTOR_Y 0.0 0.6 
      FRAME1 DETECTOR_X 0.0 -0.5 
      FRAME1 DETECTOR_PITCH 0.0 0.0 
 

     # category AXIS 

     loop_ 
     _axis.id 
     _axis.type 
     _axis.equipment 
     _axis.depends_on 
     _axis.vector[1] _axis.vector[2] _axis.vector[3] 
     _axis.offset[1] _axis.offset[2] _axis.offset[3] 
      GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . 
      GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279
      0 0.76604 . . . 
      GONIOMETER_PHI   rotation goniometer GONIOMETER_KAPPA 1 0 0
     . . . 
      SOURCE           general source . 0 0 1 . . . 
      GRAVITY          general gravity . 0 -1 0 . . . 
      DETECTOR_Z       translation detector . 0 0 1 0 0 0
      DETECTOR_Y       translation detector DETECTOR_Z 0 1 0 0 0 0 
      DETECTOR_X       translation detector DETECTOR_Y 1 0 0 0 0 0 
      DETECTOR_PITCH   rotation    detector DETECTOR_X 0 1 0 0 0 0 
      ELEMENT_ROT      translation detector DETECTOR_PITCH 0 0 1 0 0 0
      ELEMENT_RAD      translation detector ELEMENT_ROT 0 1 0 0 0 0 
 
     # category ARRAY_STRUCTURE_LIST 

     loop_ 
     _array_structure_list.array_id 
     _array_structure_list.index 
     _array_structure_list.dimension 
     _array_structure_list.precedence 
     _array_structure_list.direction 
     _array_structure_list.axis_set_id 
      ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL
 
 
     # category ARRAY_STRUCTURE_LIST_AXIS 

     loop_
     _array_structure_list_axis.axis_set_id
     _array_structure_list_axis.axis_id
     _array_structure_list_axis.angle
     _array_structure_list_axis.displacement
     _array_structure_list_axis.angular_pitch
     _array_structure_list_axis.radial_pitch
      ELEMENT_SPIRAL ELEMENT_ROT 0    .  0.075   .
      ELEMENT_SPIRAL ELEMENT_RAD . 172.5  .    -0.150

     # category ARRAY_ELEMENT_SIZE 
     # the actual pixels are 0.075 by 0.150 mm
     # We give the coarser dimension here.

     loop_ 
     _array_element_size.array_id 
     _array_element_size.index 
     _array_element_size.size 
      ARRAY1 1 150e-6 
 

     # category ARRAY_INTENSITIES 

     loop_ 
     _array_intensities.array_id 
     _array_intensities.binary_id 
     _array_intensities.linearity 
     _array_intensities.gain 
     _array_intensities.gain_esd 
     _array_intensities.overload
     _array_intensities.undefined_value 
      ARRAY1 1 linear 1.15 0.2 240000 0 
 

      # category ARRAY_STRUCTURE 

      loop_ 
      _array_structure.id 
      _array_structure.encoding_type 
      _array_structure.compression_type 
      _array_structure.byte_order 
      ARRAY1 "signed 32-bit integer" packed little_endian 
 

     # category ARRAY_DATA         

     loop_ 
     _array_data.array_id 
     _array_data.binary_id 
     _array_data.data 
      ARRAY1 1 
     ; 
     --CIF-BINARY-FORMAT-SECTION-- 
     Content-Type: application/octet-stream; 
         conversions="x-CBF_PACKED" 
     Content-Transfer-Encoding: BASE64 
     X-Binary-Size: 3801324 
     X-Binary-ID: 1 
     X-Binary-Element-Type: "signed 32-bit integer" 
     Content-MD5: 07lZFvF+aOcW85IN7usl8A== 

     AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg 
     ... 
     8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE 

     --CIF-BINARY-FORMAT-SECTION---- 
     ; 
;


# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
       save_
 
 
save__diffrn_scan.id
    _item_description.description
;             The value of _diffrn_scan.id uniquely identifies each
              scan.  The identifier is used to tie together all the 
              information about the scan.
;
     loop_
    _item.name                
    _item.category_id          
    _item.mandatory_code       
       '_diffrn_scan.id'                 diffrn_scan             yes
       '_diffrn_scan_axis.scan_id'       diffrn_scan_axis        yes
       '_diffrn_scan_frame.scan_id'      diffrn_scan_frame       yes
    _item_type.code               code
     loop_
    _item_linked.child_name
    _item_linked.parent_name
       '_diffrn_scan_axis.scan_id'          '_diffrn_scan.id'
       '_diffrn_scan_frame.scan_id'         '_diffrn_scan.id'
     save_
 
 
save__diffrn_scan.date_end
    _item_description.description
;
               The date and time of the end of the scan.  Note that this
               may be an estimate generated during the scan, before the
               precise time of the end of the scan is known.
;
    _item.name                 '_diffrn_scan.date_end'
    _item.category_id          diffrn_scan
    _item.mandatory_code       no
    _item_type.code            yyyy-mm-dd
     save_
 
 
save__diffrn_scan.date_start
    _item_description.description
;
               The date and time of the start of the scan.
;
    _item.name                 '_diffrn_scan.date_start'
    _item.category_id          diffrn_scan
    _item.mandatory_code       no
    _item_type.code            yyyy-mm-dd
     save_
 
 
save__diffrn_scan.integration_time
    _item_description.description
;
               Approximate average time in seconds to integrate each 
               step of the scan.  The precise time for integration
               of each particular step must be provided in
               '_diffrn_scan_frame.integration_time', even
               if all steps have the same integration time.
;
    _item.name                 '_diffrn_scan.integration_time'
    _item.category_id          diffrn_scan
    _item.mandatory_code       no
    _item_type.code            float
    _item_units.code           'seconds'
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            .   0.0
     save_
 
 
save__diffrn_scan.frame_id_start
    _item_description.description
;
               The value of this data item is the identifier of the
               first frame in the scan.

               This item is a pointer to _diffrn_data_frame.id in the
               DIFFRN_DATA_FRAME category.
;
    _item.name                 '_diffrn_scan.frame_id_start'
    _item.category_id          diffrn_scan
    _item.mandatory_code       yes
     save_
 
 
save__diffrn_scan.frame_id_end
    _item_description.description
;
               The value of this data item is the identifier of the
               last frame in the scan.

               This item is a pointer to _diffrn_data_frame.id in the
               DIFFRN_DATA_FRAME category.
;
    _item.name                 '_diffrn_scan.frame_id_end'
    _item.category_id          diffrn_scan
    _item.mandatory_code       yes 
     save_
 
 
save__diffrn_scan.frames
    _item_description.description
;
               The value of this data item is the number of frames in
               the scan.

;
    _item.name                 '_diffrn_scan.frames'
    _item.category_id          diffrn_scan
    _item.mandatory_code       no 
    _item_type.code            int
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            .   1
                            1   1
     save_
 
 
####################
# DIFFRN_SCAN_AXIS #
####################

save_DIFFRN_SCAN_AXIS
    _category.description 
;
     Data items in the DIFFRN_SCAN_AXIS category describe the settings of
     axes for particular scans.  Unspecified axes are assumed to be at
     their zero points.

;
    _category.id                   diffrn_scan_axis
    _category.mandatory_code       no
     loop_
    _category_key.name            
                                  '_diffrn_scan_axis.scan_id'
                                  '_diffrn_scan_axis.axis_id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     save_
 
 
save__diffrn_scan_axis.scan_id
    _item_description.description
;
               The value of this data item is the identifier of the
               scan for which axis settings are being specified.

               Multiple axes may be specified for the same value of
               '_diffrn_scan.id'.

               This item is a pointer to _diffrn_scan.id in the
               DIFFRN_SCAN category.
;
    _item.name                 '_diffrn_scan_axis.scan_id'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       yes
     save_
 
 
save__diffrn_scan_axis.axis_id
    _item_description.description
;
               The value of this data item is the identifier of one of
               the axes for the scan for which settings are being specified.

               Multiple axes may be specified for the same value of
               '_diffrn_scan.id'.

               This item is a pointer to _axis.id in the
               AXIS category.
;
    _item.name                 '_diffrn_scan_axis.axis_id'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       yes
     save_
 
 
save__diffrn_scan_axis.angle_start
    _item_description.description
;
               The starting position for the specified axis in degrees.
;
    _item.name                 '_diffrn_scan_axis.angle_start'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no 
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_
 
 
save__diffrn_scan_axis.angle_range
    _item_description.description
;
               The range from the starting position for the specified axis 
               in degrees.
;
    _item.name                 '_diffrn_scan_axis.angle_range'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no 
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_
 
 
save__diffrn_scan_axis.angle_increment
    _item_description.description
;
               The increment for each step for the specified axis
               in degrees.  In general, this will agree with
               '_diffrn_scan_frame_axis.angle_increment'. The 
               sum of the values of '_diffrn_scan_frame_axis.angle' and
               '_diffrn_scan_frame_axis.angle_increment' is the
               angular setting of the axis at the end of the integration
               time for a given frame.  If the individual frame values
               vary, then the value of 
               '_diffrn_scan_axis.angle_increment' will be 
               representative
               of the ensemble of values of
               '_diffrn_scan_frame_axis.angle_increment' (e.g.
               the mean).

;
    _item.name                 '_diffrn_scan_axis.angle_increment'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no 
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_
 
 
save__diffrn_scan_axis.angle_rstrt_incr
    _item_description.description
;
               The increment after each step for the specified axis
               in degrees.  In general, this will agree with
               '_diffrn_scan_frame_axis.angle_increment'.  The
               sum of the values of '_diffrn_scan_frame_axis.angle' 
               and  '_diffrn_scan_frame_axis.angle_increment' 
               and  '_diffrn_scan_frame_axis.angle_rstrt_incr' is the
               angular setting of the axis at the start of the integration
               time for the next frame relative to a given frame, and 
               should equal '_diffrn_scan_frame_axis.angle' for that 
               next frame.   If the individual frame values
               vary, then the value of 
               '_diffrn_scan_axis.angle_rstrt_incr' will be 
               representative
               of the ensemble of values of
               '_diffrn_scan_frame_axis.angle_rstrt_inc' (e.g.
               the mean).

;
    _item.name                 '_diffrn_scan_axis.angle_rstrt_incr'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_
 
 
save__diffrn_scan_axis.displacement_start
    _item_description.description
;
               The starting position for the specified axis in millimetres.
;
    _item.name                 '_diffrn_scan_axis.displacement_start'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no 
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
 
 
save__diffrn_scan_axis.displacement_range
    _item_description.description
;
               The range from the starting position for the specified axis 
               in millimetres.
;
    _item.name                 '_diffrn_scan_axis.displacement_range'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no 
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
 
 
save__diffrn_scan_axis.displacement_increment
    _item_description.description
;
               The increment for each step for the specified axis
               in millimetres.  In general, this will agree with
               '_diffrn_scan_frame_axis.displacement_increment'.
               The sum of the values of 
               '_diffrn_scan_frame_axis.displacement' and
               '_diffrn_scan_frame_axis.displacement_increment' is the
               angular setting of the axis at the end of the integration
               time for a given frame.  If the individual frame values
               vary, then the value of 
               '_diffrn_scan_axis.displacement_increment' will be 
               representative
               of the ensemble of values of
               '_diffrn_scan_frame_axis.displacement_increment' (e.g.
               the mean).

               
;
    _item.name                 '_diffrn_scan_axis.displacement_increment'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no 
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
 
 
save__diffrn_scan_axis.displacement_rstrt_incr
    _item_description.description
;
               The increment for each step for the specified axis
               in millimetres.  In general, this will agree with
               '_diffrn_scan_frame_axis.displacement_rstrt_incr'.
               The sum of the values of 
               '_diffrn_scan_frame_axis.displacement' and
               '_diffrn_scan_frame_axis.displacement_increment' and
               '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the
               angular setting of the axis at the start of the integration
               time for the next frame relative to a given frame, and 
               should equal '_diffrn_scan_frame_axis.displacement' 
               for that next frame.  If the individual frame values
               vary, then the value of 
               '_diffrn_scan_axis.displacement_rstrt_incr' will be 
               representative
               of the ensemble of values of
               '_diffrn_scan_frame_axis.displacement_rstrt_incr' (e.g.
               the mean).
;
    _item.name                 '_diffrn_scan_axis.displacement_rstrt_incr'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
 
 
#####################
# DIFFRN_SCAN_FRAME #
#####################

save_DIFFRN_SCAN_FRAME
    _category.description 
;
            Data items in the DIFFRN_SCAN_FRAME category describe
            the relationship of particular frames to scans.

;
    _category.id                   diffrn_scan_frame
    _category.mandatory_code       no
     loop_
    _category_key.name     
                                  '_diffrn_scan_frame.scan_id'
                                  '_diffrn_scan_frame.frame_id'
     loop_
    _category_group.id            'inclusive_group'
                                  'diffrn_group'
     save_
 
 
save__diffrn_scan_frame.date
    _item_description.description
;
               The date and time of the start of the frame being scanned.
;
    _item.name                 '_diffrn_scan_frame.date'
    _item.category_id          diffrn_scan_frame
    _item.mandatory_code       no
    _item_type.code            yyyy-mm-dd
     save_
 
 
save__diffrn_scan_frame.frame_id
    _item_description.description
;
               The value of this data item is the identifier of the
               frame being examined.

               This item is a pointer to _diffrn_data_frame.id in the
               DIFFRN_DATA_FRAME category.
;
    _item.name                 '_diffrn_scan_frame.frame_id'
    _item.category_id          diffrn_scan_frame
    _item.mandatory_code       yes
     save_
 
 
save__diffrn_scan_frame.frame_number
    _item_description.description
;
               The value of this data item is the number of the frame within
               the scan, starting with 1.  It is not necessarily the same as
               the value of _diffrn_scan_frame.frame_id, but may
               be.

;
    _item.name                 '_diffrn_scan_frame.frame_number'
    _item.category_id          diffrn_scan_frame
    _item.mandatory_code       no 
    _item_type.code            int
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            .   0
                            0   0
     save_
 
 
save__diffrn_scan_frame.integration_time
    _item_description.description
;
               The time in seconds to integrate this step of the scan.
               This should be the precise time of integration of each
               particular frame.  The value of this data item should
               be given explicitly for each frame and not inferred
               from the value of '_diffrn_scan.integration_time'.
;
    _item.name                 '_diffrn_scan_frame.integration_time'
    _item.category_id          diffrn_scan_frame
    _item.mandatory_code       yes 
    _item_type.code            float
    _item_units.code           'seconds'
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            .   0.0
     save_
 
 
save__diffrn_scan_frame.scan_id
    _item_description.description
;             The value of _diffrn_scan_frame.scan_id identifies the scan
              containing this frame.

              This item is a pointer to _diffrn_scan.id in the
              DIFFRN_SCAN category.
;
    _item.name             '_diffrn_scan_frame.scan_id'    
    _item.category_id        diffrn_scan_frame        
    _item.mandatory_code     yes     
     save_
 
 
##########################
# DIFFRN_SCAN_FRAME_AXIS #
##########################

save_DIFFRN_SCAN_FRAME_AXIS
    _category.description
;
     Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the settings
     of axes for particular frames.  Unspecified axes are assumed to be at
     their zero points.  If, for any given frame, non-zero values apply
     for any of the data items in this category, those values should be
     given explicitly in this category and not simply inferred from values
     in DIFFRN_SCAN_AXIS.

;
    _category.id                   diffrn_scan_frame_axis
    _category.mandatory_code       no
     loop_
    _category_key.name
                                  '_diffrn_scan_frame_axis.frame_id'
                                  '_diffrn_scan_frame_axis.axis_id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     save_
 
 
save__diffrn_scan_frame_axis.axis_id
    _item_description.description
;
               The value of this data item is the identifier of one of
               the axes for the frame for which settings are being specified.

               Multiple axes may be specified for the same value of
               _diffrn_scan_frame.frame_id

               This item is a pointer to _axis.id in the
               AXIS category.
;
    _item.name                 '_diffrn_scan_frame_axis.axis_id'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       yes
     save_
 
 
save__diffrn_scan_frame_axis.angle
    _item_description.description
;
               The setting of the specified axis in degrees for this frame.
               This is the setting at the start of the integration time.
;
    _item.name                 '_diffrn_scan_frame_axis.angle'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       no 
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_
 
 
save__diffrn_scan_frame_axis.angle_increment
    _item_description.description
;
               The increment for this frame for angular setting of
               the specified axis in degrees.  The sum of the values
               of '_diffrn_scan_frame_axis.angle' and
               '_diffrn_scan_frame_axis.angle_increment' is the
               angular setting of the axis at the end of the integration
               time for this frame.
;
    _item.name                 '_diffrn_scan_frame_axis.angle_increment'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_
 
 
save__diffrn_scan_frame_axis.angle_rstrt_incr
    _item_description.description
;
               The increment after this frame for angular setting of
               the specified axis in degrees.  The sum of the values
               of '_diffrn_scan_frame_axis.angle' and
               '_diffrn_scan_frame_axis.angle_increment' and
               '_diffrn_scan_frame_axis.angle_rstrt_incr' is the
               angular setting of the axis at the start of the integration
               time for the next frame, and should equal
               '_diffrn_scan_frame_axis.angle' for that next frame.
;
    _item.name               '_diffrn_scan_frame_axis.angle_rstrt_incr'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_
 
 
save__diffrn_scan_frame_axis.displacement
    _item_description.description
;
               The setting of the specified axis in millimetres for this
               frame.  This is the setting at the start of the integration
               time.

;
    _item.name               '_diffrn_scan_frame_axis.displacement'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
 
 
save__diffrn_scan_frame_axis.displacement_increment
    _item_description.description
;
               The increment for this frame for displacement setting of
               the specified axis in millimetres.  The sum of the values
               of '_diffrn_scan_frame_axis.displacement' and
               '_diffrn_scan_frame_axis.displacement_increment' is the
               angular setting of the axis at the end of the integration
               time for this frame.
;
    _item.name               '_diffrn_scan_frame_axis.displacement_increment'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
 
 
save__diffrn_scan_frame_axis.displacement_rstrt_incr
    _item_description.description
;
               The increment for this frame for displacement setting of
               the specified axis in millimetres.  The sum of the values
               of '_diffrn_scan_frame_axis.displacement' and
               '_diffrn_scan_frame_axis.displacement_increment' and
               '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the
               angular setting of the axis at the start of the integration
               time for the next frame, and should equal
               '_diffrn_scan_frame_axis.displacement' for that next frame.
;
    _item.name               '_diffrn_scan_frame_axis.displacement_rstrt_incr'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_

save__diffrn_scan_frame_axis.frame_id
    _item_description.description
;
               The value of this data item is the identifier of the
               frame for which axis settings are being specified.

               Multiple axes may be specified for the same value of
               _diffrn_scan_frame.frame_id .

               This item is a pointer to _diffrn_data_frame.id in the
               DIFFRN_DATA_FRAME category.
;
    _item.name               '_diffrn_scan_frame_axis.frame_id'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       yes
     save_


#########################   DEPRECATED CATEGORY  ##############################
#####################
# DIFFRN_FRAME_DATA #
#####################
 
 
save_DIFFRN_FRAME_DATA
    _category.description
;
              Data items in the DIFFRN_FRAME_DATA category record
              the details about each frame of data. 

              The items in this category are now in the
              DIFFRN_DATA_FRAME category.
              
              The items in the DIFFRN_FRAME_DATA category
              are now deprecated.  The items from this category 
              are provided as aliases in the 1.0.0 dictionary, 
              but should not be used for new work.
              The items from the old category are provided
              in this dictionary for completeness,
              but should not be used or cited.  To avoid
              confusion, the example has been removed,
              and the redundant parent child-links to other
              categories removed.
;
    _category.id                   diffrn_frame_data
    _category.mandatory_code       no
     loop_
    _category_key.name             '_diffrn_frame_data.id'
                                   '_diffrn_frame_data.detector_element_id'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
    THE DIFFRN_DATA_FRAME category is deprecated and should not be used.
;
;
       # EXAMPLE REMOVED #
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    save_
 
 
save__diffrn_frame_data.array_id
    _item_description.description
;             
              This item is a pointer to _array_structure.id in the
              ARRAY_STRUCTURE category.

              DEPRECATED -- DO NOT USE
;
    _item.name                  '_diffrn_frame_data.array_id'
    _item.category_id             diffrn_frame_data
    _item.mandatory_code          yes
    _item_type.code               code
     save_
 
 
save__diffrn_frame_data.binary_id
    _item_description.description
;             This item is a pointer to _array_data.binary_id in the
              ARRAY_STRUCTURE category. 
              
              DEPRECATED -- DO NOT USE
;
    _item.name                  '_diffrn_frame_data.binary_id'
    _item.category_id             diffrn_frame_data
    _item.mandatory_code          implicit
    _item_type.code               int
     save_
 
 
save__diffrn_frame_data.detector_element_id
    _item_description.description
;             
              This item is a pointer to _diffrn_detector_element.id
              in the DIFFRN_DETECTOR_ELEMENT category.

              DEPRECATED -- DO NOT USE 
;
    _item.name                  '_diffrn_frame_data.detector_element_id'
    _item.category_id             diffrn_frame_data
    _item.mandatory_code          yes
    _item_type.code               code
     save_
 
 
save__diffrn_frame_data.id
    _item_description.description
;             
              The value of _diffrn_frame_data.id must uniquely identify
              each complete frame of data.

              DEPRECATED -- DO NOT USE 
;
     loop_
    _item.name                
    _item.category_id          
    _item.mandatory_code       
           '_diffrn_frame_data.id'        diffrn_frame_data  yes
    _item_type.code               code
     save_

################ END DEPRECATED SECTION ###########


####################
## ITEM_TYPE_LIST ##
####################
#
#
#  The regular expressions defined here are not compliant
#  with the POSIX 1003.2 standard as they include the
#  '\n' and '\t' special characters.  These regular expressions
#  have been tested using version 0.12 of Richard Stallman's
#  GNU regular expression library in POSIX mode.
#  In order to allow presentation of a regular expression
#  in a text field concatenate any line ending in a backslash
#  with the following line, after discarding the backslash.
#
#  A formal definition of the '\n' and '\t' special characters
#  is most properly done in the DDL, but for completeness, please
#  note that '\n' is the line termination character ('newline')
#  and '\t' is the horizontal tab character.  There is a formal
#  ambiguity in the use of '\n' for line termination, in that
#  the intention is that the equivalent machine/OS-dependent line
#  termination character sequence should be accepted as a match, e.g.
#
#      '\r' (control-M) under MacOS
#      '\n' (control-J) under Unix
#      '\r\n' (control-M control-J) under DOS and MS Windows
#
     loop_
    _item_type_list.code
    _item_type_list.primitive_code
    _item_type_list.construct
    _item_type_list.detail
               code      char
'[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
;              code item types/single words ...
;
               ucode      uchar
'[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
;              code item types/single words (case insensitive)
;
               line      char
'[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
;              code item types / multi-word items  ...
;
               uline     uchar
'[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
;              code item types / multi-word items (case insensitive)
;
               text      char
'[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*'
;              text item types / multi-line text ...
;
               binary    char
;\n--CIF-BINARY-FORMAT-SECTION--\n\
[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\
\n--CIF-BINARY-FORMAT-SECTION----
;
;              binary items are presented as MIME-like ascii-encoded
               sections in an imgCIF.  In a CBF, raw octet streams
               are used to convey the same information.
;
               int       numb
'-?[0-9]+'
;              int item types are the subset of numbers that are the negative
               or positive integers.
;
               float     numb
'-?(([0-9]+)|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?'
;              float item types are the subset of numbers that are the floating
               numbers.
;
               any       char
'.*'
;              A catch all for items that may take any form...
;
               yyyy-mm-dd  char
;\
[0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9][0-9]\
(T[0-2][0-9]:[0-5][0-9]:[0-5][0-9](.[0-9]+)([+-][0-5][0-9]:[0-5][0-9]))
;
;
               Standard format for CIF date and time strings (see
               http://www.iucr.orgiucr-top/cif/spec/datetime.html),
               consisting of a yyyy-mm-dd date optionally followed by
               the character "T" followed by a 24-hour clock time,
               optionally followed by a signed time-zone offset.
               
               The IUCr standard has been extended to allow for an optional
               decimal fraction on the seconds of time.
               
               Time is local time if no time-zone offset is given.
;
 
 
#####################
## ITEM_UNITS_LIST ##
#####################

     loop_
    _item_units_list.code
    _item_units_list.detail
#
     'metres'                 'metres'
     'centimetres'            'centimetres (metres * 10^( -2))'
     'millimetres'            'millimetres (metres * 10^( -3))'
     'nanometres'             'nanometres  (metres * 10^( -9))'
     'angstroms'              'angstroms   (metres * 10^(-10))'
     'picometres'             'picometres  (metres * 10^(-12))'
     'femtometres'            'femtometres (metres * 10^(-15))'
#
     'reciprocal_metres'      'reciprocal metres (metres^(-1))'
     'reciprocal_centimetres' 'reciprocal centimetres ((metres * 10^( -2))^(-1))'
     'reciprocal_millimetres' 'reciprocal millimetres ((metres * 10^( -3))^(-1))'
     'reciprocal_nanometres'  'reciprocal nanometres  ((metres * 10^( -9))^(-1))'
     'reciprocal_angstroms'   'reciprocal angstroms   ((metres * 10^(-10))^(-1))'
     'reciprocal_picometres'  'reciprocal picometres  ((metres * 10^(-12))^(-1))'

     'reciprocal_metres'      'reciprocal metres (metres * 10^-1)'
     'reciprocal_centimetres' 'reciprocal centimetres (metres * 10^( -2)^-1)'
     'reciprocal_millimetres' 'reciprocal millimetres (metres * 10^( -3)^-1)'
     'reciprocal_nanometres'  'reciprocal nanometres  (metres * 10^( -9)^-1)'
     'reciprocal_angstroms'   'reciprocal angstroms   (metres * 10^(-10)^-1)'
     'reciprocal_picometres'  'reciprocal picometres  (metres * 10^(-12)^-1)'
#
     'nanometres_squared'     'nanometres squared (metres * 10^( -9))^2'
     'angstroms_squared'      'angstroms squared  (metres * 10^(-10))^2'
     '8pi2_angstroms_squared' '8pi^2 * angstroms squared (metres * 10^(-10))^2'
     'picometres_squared'     'picometres squared (metres * 10^(-12))^2'
#
     'nanometres_cubed'       'nanometres cubed (metres * 10^( -9))^3'
     'angstroms_cubed'        'angstroms cubed  (metres * 10^(-10))^3'
     'picometres_cubed'       'picometres cubed (metres * 10^(-12))^3'
#
     'kilopascals'            'kilopascals'
     'gigapascals'            'gigapascals'
#
     'hours'                  'hours'
     'minutes'                'minutes'
     'seconds'                'seconds'
     'microseconds'           'microseconds'
#
     'degrees'                'degrees (of arc)'
     'degrees_squared'        'degrees (of arc) squared'
#
     'degrees_per_minute'     'degrees (of arc) per minute'
#
     'celsius'                'degrees (of temperature) Celsius'
     'kelvins'                'degrees (of temperature) Kelvin'
#
     'counts'                 'counts'
     'counts_per_photon'      'counts per photon'
#
     'electrons'              'electrons'
#
     'electrons_squared'      'electrons squared'
#
     'electrons_per_nanometres_cubed'
; electrons per nanometres cubed (electrons/(metres * 10^( -9))^(-3))
;
     'electrons_per_angstroms_cubed'
; electrons per nanometres cubed (electrons/(metres * 10^(-10))^(-3)); 
;
     'electrons_per_picometres_cubed'
; electrons per nanometres cubed (electrons/(metres * 10^(-12))^(-3)); 
;
     'kilowatts'              'kilowatts'
     'milliamperes'           'milliamperes'
     'kilovolts'              'kilovolts'
#
     'arbitrary'
; arbitrary system of units.
;
#

     loop_
    _item_units_conversion.from_code
    _item_units_conversion.to_code
    _item_units_conversion.operator
    _item_units_conversion.factor
###
     'metres'                   'centimetres'              '*'   1.0E+02
     'metres'                   'millimetres'              '*'   1.0E+03
     'metres'                   'nanometres'               '*'   1.0E+09
     'metres'                   'angstroms'                '*'   1.0E+10
     'metres'                   'picometres'               '*'   1.0E+12
     'metres'                   'femtometres'              '*'   1.0E+15
#
     'centimetres'              'metres'                   '*'   1.0E-02
     'centimetres'              'millimetres'              '*'   1.0E+01
     'centimetres'              'nanometres'               '*'   1.0E+07
     'centimetres'              'angstroms'                '*'   1.0E+08
     'centimetres'              'picometres'               '*'   1.0E+10
     'centimetres'              'femtometres'              '*'   1.0E+13
#
     'millimetres'              'metres'                   '*'   1.0E-03
     'millimetres'              'centimetres'              '*'   1.0E-01
     'millimetres'              'nanometres'               '*'   1.0E+06
     'millimetres'              'angstroms'                '*'   1.0E+07
     'millimetres'              'picometres'               '*'   1.0E+09
     'millimetres'              'femtometres'              '*'   1.0E+12
#
     'nanometres'               'metres'                   '*'   1.0E-09
     'nanometres'               'centimetres'              '*'   1.0E-07
     'nanometres'               'millimetres'              '*'   1.0E-06
     'nanometres'               'angstroms'                '*'   1.0E+01
     'nanometres'               'picometres'               '*'   1.0E+03
     'nanometres'               'femtometres'              '*'   1.0E+06
#
     'angstroms'                'metres'                   '*'   1.0E-10
     'angstroms'                'centimetres'              '*'   1.0E-08
     'angstroms'                'millimetres'              '*'   1.0E-07
     'angstroms'                'nanometres'               '*'   1.0E-01
     'angstroms'                'picometres'               '*'   1.0E+02
     'angstroms'                'femtometres'              '*'   1.0E+05
#
     'picometres'               'metres'                   '*'   1.0E-12
     'picometres'               'centimetres'              '*'   1.0E-10
     'picometres'               'millimetres'              '*'   1.0E-09
     'picometres'               'nanometres'               '*'   1.0E-03
     'picometres'               'angstroms'                '*'   1.0E-02
     'picometres'               'femtometres'              '*'   1.0E+03
#
     'femtometres'              'metres'                   '*'   1.0E-15
     'femtometres'              'centimetres'              '*'   1.0E-13
     'femtometres'              'millimetres'              '*'   1.0E-12
     'femtometres'              'nanometres'               '*'   1.0E-06
     'femtometres'              'angstroms'                '*'   1.0E-05
     'femtometres'              'picometres'               '*'   1.0E-03
###
     'reciprocal_centimetres'   'reciprocal_metres'        '*'   1.0E+02
     'reciprocal_centimetres'   'reciprocal_millimetres'   '*'   1.0E-01
     'reciprocal_centimetres'   'reciprocal_nanometres'    '*'   1.0E-07
     'reciprocal_centimetres'   'reciprocal_angstroms'     '*'   1.0E-08
     'reciprocal_centimetres'   'reciprocal_picometres'    '*'   1.0E-10
#
     'reciprocal_millimetres'   'reciprocal_metres'        '*'   1.0E+03
     'reciprocal_millimetres'   'reciprocal_centimetres'   '*'   1.0E+01
     'reciprocal_millimetres'   'reciprocal_nanometres'    '*'   1.0E-06
     'reciprocal_millimetres'   'reciprocal_angstroms'     '*'   1.0E-07
     'reciprocal_millimetres'   'reciprocal_picometres'    '*'   1.0E-09
#
     'reciprocal_nanometres'    'reciprocal_metres'        '*'   1.0E+09
     'reciprocal_nanometres'    'reciprocal_centimetres'   '*'   1.0E+07
     'reciprocal_nanometres'    'reciprocal_millimetres'   '*'   1.0E+06
     'reciprocal_nanometres'    'reciprocal_angstroms'     '*'   1.0E-01
     'reciprocal_nanometres'    'reciprocal_picometres'    '*'   1.0E-03
#
     'reciprocal_angstroms'     'reciprocal_metres'        '*'   1.0E+10
     'reciprocal_angstroms'     'reciprocal_centimetres'   '*'   1.0E+08
     'reciprocal_angstroms'     'reciprocal_millimetres'   '*'   1.0E+07
     'reciprocal_angstroms'     'reciprocal_nanometres'    '*'   1.0E+01
     'reciprocal_angstroms'     'reciprocal_picometres'    '*'   1.0E-02
#
     'reciprocal_picometres'    'reciprocal_metres'        '*'   1.0E+12
     'reciprocal_picometres'    'reciprocal_centimetres'   '*'   1.0E+10
     'reciprocal_picometres'    'reciprocal_millimetres'   '*'   1.0E+09
     'reciprocal_picometres'    'reciprocal_nanometres'    '*'   1.0E+03
     'reciprocal_picometres'    'reciprocal_angstroms'     '*'   1.0E+01
###
     'nanometres_squared'       'angstroms_squared'        '*'   1.0E+02
     'nanometres_squared'       'picometres_squared'       '*'   1.0E+06
#
     'angstroms_squared'        'nanometres_squared'       '*'   1.0E-02
     'angstroms_squared'        'picometres_squared'       '*'   1.0E+04
     'angstroms_squared'        '8pi2_angstroms_squared'   '*'   78.9568

#
     'picometres_squared'       'nanometres_squared'       '*'   1.0E-06
     'picometres_squared'       'angstroms_squared'        '*'   1.0E-04
###
     'nanometres_cubed'         'angstroms_cubed'          '*'   1.0E+03
     'nanometres_cubed'         'picometres_cubed'         '*'   1.0E+09
#
     'angstroms_cubed'          'nanometres_cubed'         '*'   1.0E-03
     'angstroms_cubed'          'picometres_cubed'         '*'   1.0E+06
#
     'picometres_cubed'         'nanometres_cubed'         '*'   1.0E-09
     'picometres_cubed'         'angstroms_cubed'          '*'   1.0E-06
###
     'kilopascals'              'gigapascals'              '*'   1.0E-06
     'gigapascals'              'kilopascals'              '*'   1.0E+06
###
     'hours'                    'minutes'                  '*'   6.0E+01
     'hours'                    'seconds'                  '*'   3.6E+03
     'hours'                    'microseconds'             '*'   3.6E+09
#
     'minutes'                  'hours'                    '/'   6.0E+01
     'minutes'                  'seconds'                  '*'   6.0E+01
     'minutes'                  'microseconds'             '*'   6.0E+07
#
     'seconds'                  'hours'                    '/'   3.6E+03
     'seconds'                  'minutes'                  '/'   6.0E+01
     'seconds'                  'microseconds'             '*'   1.0E+06
#
     'microseconds'             'hours'                    '/'   3.6E+09
     'microseconds'             'minutes'                  '/'   6.0E+07
     'microseconds'             'seconds'                  '/'   1.0E+06
###
     'celsius'                  'kelvins'                  '-'     273.0
     'kelvins'                  'celsius'                  '+'     273.0
###
     'electrons_per_nanometres_cubed'
     'electrons_per_angstroms_cubed'                       '*'   1.0E+03
     'electrons_per_nanometres_cubed'
     'electrons_per_picometres_cubed'                      '*'   1.0E+09
#
     'electrons_per_angstroms_cubed'
     'electrons_per_nanometres_cubed'                      '*'   1.0E-03
     'electrons_per_angstroms_cubed'
     'electrons_per_picometres_cubed'                      '*'   1.0E+06
#
     'electrons_per_picometres_cubed'
     'electrons_per_nanometres_cubed'                      '*'   1.0E-09
     'electrons_per_picometres_cubed'
     'electrons_per_angstroms_cubed'                       '*'   1.0E-06
###
 
 
########################
## DICTIONARY_HISTORY ##
########################

     loop_
    _dictionary_history.version
    _dictionary_history.update
    _dictionary_history.revision

   1.2.4   2003-07-14
;
   Changes as per I. David Brown. 
   +  Enhance descriptions in DIFFRN_SCAN_AXIS to make them less
   dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS.
   +  Provide a copy of the deprecated DIFFRN_FRAME_DATA
   category for completeness.
   (HJB)
;

   1.2.3   2003-07-03
;
   Cleanup to conform to ITVG. 
   +  Correct sign error in ..._cubed units.
   +  Correct '_diffrn_radiation.polarisn_norm' range.
   (HJB)
;

   1.2.2   2003-03-10
;
   Correction of  typos in various DIFFRN_SCAN_AXIS descriptions. 
   (HJB)
;

   1.2.1   2003-02-22
;
   Correction of ATOM_ for ARRAY_ typos in various descriptions. 
   (HJB)
;


   1.2     2003-02-07
;
   Corrections to encodings (remove extraneous hyphens) remove
   extraneous underscore in _array_structure.encoding_type
   enumeration.  Correct typos in items units list. 
   (HJB)
;


   1.1.3   2001-04-19
;
   Another typo corrections by Wilfred Li, and cleanup by HJB
;

   1.1.2   2001-03-06
;
   Several typo corrections by Wilfred Li
;


   1.1.1   2001-02-16
;
   Several typo corrections by JW
;


   1.1     2001-02-06
;
   Draft resulting from discussions on header for use at NSLS (HJB)
   
   + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME
   
   + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'.
   
   + Add '_diffrn_measurement_axis.measurement_device' and change
   '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'.
   
   + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source',
   '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm',
   '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end',
   '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr',
   '_diffrn_scan_axis.displacement_rstrt_incr', 
   '_diffrn_scan_frame_axis.angle_increment',
   '_diffrn_scan_frame_axis.angle_rstrt_incr',
   '_diffrn_scan_frame_axis.displacement',
   '_diffrn_scan_frame_axis.displacement_increment',and
   '_diffrn_scan_frame_axis.displacement_rstrt_incr'.
   
   + Add _diffrn_measurement.device to category key
   
   + Update yyyy-mm-dd to allow optional time with fractional seconds
   for time stamps.

   + Fix typos caught by RS.
   
   + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to allow
   for coupled axes, as in spiral scans.

   + Add examples for fairly complete headers thanks to R. Sweet and P. 
   Ellis.
;


   1.0     2000-12-21
;
   Release version - few typos and tidying up (BM & HJB)
   
   + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end
   of dictionary.
   
   + Alphabetize dictionary.
;

   0.7.1   2000-09-29
;
   Cleanup fixes (JW)

   + Correct spelling of diffrn_measurement_axis in _axis.id

   + Correct ordering of uses of _item.mandatory_code and _item_default.value
;

   0.7.0   2000-09-09
;
   Respond to comments by I. David Brown (HJB)

   + Added further comments on '\n' and '\t'

   + Updated ITEM_UNITS_LIST by taking section from mmCIF dictionary
 and adding metres.  Changed all spelling 'meter' to 'metre' throughout.

   + Added missing enumerations to _array_structure.compression_type
 and made 'none' the default.

   + Removed parent-child relationship between _array_structure_list.index
 and _array_structure_list.precedence .

   + Improve alphabetization.

   + Fix _array_intensities_gain.esd related function.

   + Improved comments in AXIS.

   + Fixed DIFFRN_FRAME_DATA example.

   + Removed erroneous DIFFRN_MEASUREMENT example.

   + Added _diffrn_measurement_axis.id to the category key.
;

   0.6.0   1999-01-14
;
   Remove redundant information for ENC_NONE data (HJB)

   + After the D5 remove binary section identifier, size and
 compression type.

   + Add Control-L to header.
;
   0.5.1   1999-01-03
;
   Cleanup of typos and syntax errors (HJB)

   + Cleanup example details for DIFFRN_SCAN category.

   + Add missing quote marks for _diffrn_scan.id definition.
;

   0.5   1999-01-01
;
   Modifications for axis definitions and reduction of binary header (HJB)

   + Restored _diffrn_detector.diffrn_id to DIFFRN_DETECTOR KEY.

   + Added AXIS category.

   + Brought complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories
 in from cif_mm.dic for clarity.

   + changed _array_structure.encoding_type from type code to uline and
 added X-Binary-Element-Type to MIME header.

   + added detector beam center _diffrn_detector_element.center[1] and 
_diffrn_detector_element.center[2]

   + corrected item name of _diffrn_refln.frame_id

   + replace reference to _array_intensities.undefined by
 _array_intensities.undefined_value

   + replace references to _array_intensity.scaling with
 _array_intensities.scaling

   + added DIFFRN_SCAN... categories
;

   0.4   1998-08-11
;
   Modifications to the 0.3 imgCIF draft (HJB)

   +  Reflowed comment lines over 80 characters and corrected typos.

   +  Updated examples and descriptions of MIME encoded data.

   +  Change name to cbfext98.dic.
;

   0.3   1998-07-04
;
   Modifications for imgCIF (HJB)

   +  Added binary type, which is a text field containing a variant on
      MIME encoded data.
      
   +  Changed type of _array_data.data to binary and specified internal
      structure of raw binary data.
      
   +  Added _array_data.binary_id, and made 
      _diffrn_frame_data.binary_id and _array_intensities.binary_id
      into pointers to this item.
;

   0.2   1997-12-02
;
   Modifications to the CBF draft (JW):  

   +  Added category hierarchy for describing frame data developed from
      discussions at the BNL imgCIF Workshop Oct 1997.   The following
      changes were made in implementing the workshop draft.  Category
      DIFFRN_ARRAY_DATA was renamed to DIFFRN_FRAME_DATA.  Category
      DIFFRN_FRAME_TYPE was renamed to DIFFRN_DETECTOR_ELEMENT.   The
      parent item for _diffrn_frame_data.array_id was changed from
      array_structure_list.array_id to array_structure.id. Item 
      _diffrn_detector.array_id was deleted.  
   +  Added data item _diffrn_frame_data.binary_id to identify data groups
      within a binary section.  The formal identification of the binary section
      is still fuzzy.  
;

   0.1   1997-01-24
;
   First draft of this dictionary in DDL 2.1 compliant format by John 
   Westbrook (JW).  This version was adapted from the Crystallographic 
   Binary File (CBF) Format Draft Proposal provided by Andy Hammersley (AH).  
 
   Modifications to the CBF draft (JW):  
 
   + In this version the array description has been cast in the categories 
     ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST.  These categories have been 
     generalized to describe array data  of arbitrary dimension.  

   + Array data in this description are contained in the category ARRAY_DATA        .
     This departs from the CBF notion of data existing in some special comment.
     In this description, data is handled as an ordinary data item encapsulated
     in a character data type.   Although handling binary data this manner
     deviates from CIF conventions, it does not violate any DDL 2.1 rules.
     DDL 2.1 regular expressions can be used to define the binary 
     representation which will permit some level of data validation.  In 
     this version, the placeholder type code "any" has been used.
     This translates to a regular expression which will match any pattern.  

     It should be noted that DDL 2.1 already supports array data objects 
     although these have not been used in the current mmCIF dictionary.  It 
     may be possible to use the DDL 2.1 ITEM_STRUCTURE and ITEM_STRUCTURE_LIST
     categories to provide the information that is carried in by the 
     ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST.  By moving the array 
     structure to the DDL level it would be possible to define an array 
     type as well as a regular expression defining the data format. 

   + Multiple array sections can be properly handled within a single datablock.
;
 
 
#-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof
./CBFlib-0.9.2.2/doc/cif_img_1.5.3_8Jul07.html0000644000076500007650000114116311603702115016432 0ustar yayayaya cif_img.dic v1.5_DRAFT

# [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib] #

# imgCIF/CBF #

# Extensions Dictionary #

##############################################################################
#                                                                            #
#                       Image CIF Dictionary (imgCIF)                        #
#             and Crystallographic Binary File Dictionary (CBF)              #
#            Extending the Macromolecular CIF Dictionary (mmCIF)             #
#                                                                            #
#                              Version 1.5.3                                 #
#                              of 2007-07-08                                 #
#    ###################################################################     #
#    # *** WARNING *** THIS IS A DRAFT FOR DISCUSSSION *** WARNING *** #     #
#    #                 SUBJECT TO CHANGE WITHOUT NOTICE                #     #
#    #       SEND COMMENTS TO imgcif-l@iucr.org CITING THE VERSION     #     #
#    ###################################################################     #
#                  This draft edited by H. J. Bernstein                      #
#                                                                            #
#     by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook    #
#                                                                            #
# This dictionary was adapted from format discussed at the imgCIF Workshop,  #
# held at BNL Oct 1997 and the Crystallographic Binary File Format Draft     #
# Proposal by Andrew Hammersley.  The first DDL 2.1 Version was created by   #
# John Westbrook.  This version was drafted by Herbert J. Bernstein and      #
# incorporates comments by I. David Brown, John Westbrook, Brian McMahon,    #
# Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li, Gotzon Madariaga,         #
# Frances C. Bernstein, Chris Nielsen, Nicola Ashcroft and others.           #
##############################################################################

data_cif_img.dic

    _dictionary.title           cif_img.dic
    _dictionary.version         1.5.3
    _dictionary.datablock_id    cif_img.dic

##############################################################################
#    CONTENTS
#
#        CATEGORY_GROUP_LIST
#        SUB_CATEGORY
#
#        category  ARRAY_DATA
#
#                  _array_data.array_id
#                  _array_data.binary_id
#                  _array_data.data
#                  _array_data.header_contents
#                  _array_data.header_convention
#
#        category  ARRAY_ELEMENT_SIZE
#
#                  _array_element_size.array_id
#                  _array_element_size.index
#                  _array_element_size.size
#
#        category  ARRAY_INTENSITIES
#
#                  _array_intensities.array_id
#                  _array_intensities.binary_id
#                  _array_intensities.gain
#                  _array_intensities.gain_esd
#                  _array_intensities.linearity
#                  _array_intensities.offset
#                  _array_intensities.scaling
#                  _array_intensities.overload
#                  _array_intensities.undefined_value
#                  _array_intensities.pixel_fast_bin_size
#                  _array_intensities.pixel_slow_bin_size
#                  _array_intensities.pixel_binning_method
#
#        category  ARRAY_STRUCTURE
#
#                  _array_structure.byte_order
#                  _array_structure.compression_type
#                  _array_structure.compression_type_flag
#                  _array_structure.encoding_type
#                  _array_structure.id
#
#        category  ARRAY_STRUCTURE_LIST
#
#                  _array_structure_list.axis_set_id
#                  _array_structure_list.array_id
#                  _array_structure_list.dimension
#                  _array_structure_list.direction
#                  _array_structure_list.index
#                  _array_structure_list.precedence
#
#        category  ARRAY_STRUCTURE_LIST_AXIS
#
#                  _array_structure_list_axis.axis_id
#                  _array_structure_list_axis.axis_set_id
#                  _array_structure_list_axis.angle
#                  _array_structure_list_axis.angle_increment
#                  _array_structure_list_axis.displacement
#                  _array_structure_list_axis.fract_displacement
#                  _array_structure_list_axis.displacement_increment
#                  _array_structure_list_axis.fract_displacement_increment
#                  _array_structure_list_axis.angular_pitch
#                  _array_structure_list_axis.radial_pitch
#                  _array_structure_list_axis.reference_angle
#                  _array_structure_list_axis.reference_displacement
#
#        category  AXIS
#
#                  _axis.depends_on
#                  _axis.equipment
#                  _axis.id
#                  _axis.offset[1]
#                  _axis.offset[2]
#                  _axis.offset[3]
#                  _axis.type
#                  _axis.system
#                  _axis.vector[1]
#                  _axis.vector[2]
#                  _axis.vector[3]
#
#        category  DIFFRN_DATA_FRAME
#
#                  _diffrn_data_frame.array_id
#                  _diffrn_data_frame.binary_id
#                  _diffrn_data_frame.center_fast
#                  _diffrn_data_frame.center_slow
#                  _diffrn_data_frame.center_units
#                  _diffrn_data_frame.detector_element_id
#                  _diffrn_data_frame.id
#                  _diffrn_data_frame.details
#
#        category  DIFFRN_DETECTOR
#
#                  _diffrn_detector.details
#                  _diffrn_detector.detector
#                  _diffrn_detector.diffrn_id
#                  _diffrn_detector.dtime
#                  _diffrn_detector.id
#                  _diffrn_detector.number_of_axes
#                  _diffrn_detector.type
#
#        category  DIFFRN_DETECTOR_AXIS
#
#                  _diffrn_detector_axis.axis_id
#                  _diffrn_detector_axis.detector_id
#
#        category  DIFFRN_DETECTOR_ELEMENT
#
#                  _diffrn_detector_element.id
#                  _diffrn_detector_element.detector_id
#                  _diffrn_detector_element.reference_center_fast
#                  _diffrn_detector_element.reference_center_slow
#                  _diffrn_detector_element.reference_center_units
#
#        category  DIFFRN_MEASUREMENT
#
#                  _diffrn_measurement.diffrn_id
#                  _diffrn_measurement.details
#                  _diffrn_measurement.device
#                  _diffrn_measurement.device_details
#                  _diffrn_measurement.device_type
#                  _diffrn_measurement.id
#                  _diffrn_measurement.method
#                  _diffrn_measurement.number_of_axes
#                  _diffrn_measurement.sample_detector_distance
#                  _diffrn_measurement.sample_detector_voffset
#                  _diffrn_measurement.specimen_support
#
#        category  DIFFRN_MEASUREMENT_AXIS
#
#                  _diffrn_measurement_axis.axis_id
#                  _diffrn_measurement_axis.measurement_device
#                  _diffrn_measurement_axis.measurement_id
#
#        category  DIFFRN_RADIATION
#
#                  _diffrn_radiation.collimation
#                  _diffrn_radiation.diffrn_id
#                  _diffrn_radiation.div_x_source
#                  _diffrn_radiation.div_y_source
#                  _diffrn_radiation.div_x_y_source
#                  _diffrn_radiation.filter_edge'
#                  _diffrn_radiation.inhomogeneity
#                  _diffrn_radiation.monochromator
#                  _diffrn_radiation.polarisn_norm
#                  _diffrn_radiation.polarisn_ratio
#                  _diffrn_radiation.polarizn_source_norm
#                  _diffrn_radiation.polarizn_source_ratio
#                  _diffrn_radiation.probe
#                  _diffrn_radiation.type
#                  _diffrn_radiation.xray_symbol
#                  _diffrn_radiation.wavelength_id
#
#        category  DIFFRN_REFLN
#
#                  _diffrn_refln.frame_id
#
#        category  DIFFRN_SCAN
#
#                  _diffrn_scan.id
#                  _diffrn_scan.date_end
#                  _diffrn_scan.date_start
#                  _diffrn_scan.integration_time
#                  _diffrn_scan.frame_id_start
#                  _diffrn_scan.frame_id_end
#                  _diffrn_scan.frames
#
#        category  DIFFRN_SCAN_AXIS
#
#                  _diffrn_scan_axis.axis_id
#                  _diffrn_scan_axis.angle_start
#                  _diffrn_scan_axis.angle_range
#                  _diffrn_scan_axis.angle_increment
#                  _diffrn_scan_axis.angle_rstrt_incr
#                  _diffrn_scan_axis.displacement_start
#                  _diffrn_scan_axis.displacement_range
#                  _diffrn_scan_axis.displacement_increment
#                  _diffrn_scan_axis.displacement_rstrt_incr
#                  _diffrn_scan_axis.reference_angle
#                  _diffrn_scan_axis.reference_displacement
#                  _diffrn_scan_axis.scan_id
#
#        category  DIFFRN_SCAN_FRAME
#
#                  _diffrn_scan_frame.date
#                  _diffrn_scan_frame.frame_id
#                  _diffrn_scan_frame.frame_number
#                  _diffrn_scan_frame.integration_time
#                  _diffrn_scan_frame.scan_id
#
#        category  DIFFRN_SCAN_FRAME_AXIS
#
#                  _diffrn_scan_frame_axis.axis_id
#                  _diffrn_scan_frame_axis.angle
#                  _diffrn_scan_frame_axis.angle_increment
#                  _diffrn_scan_frame_axis.angle_rstrt_incr
#                  _diffrn_scan_frame_axis.displacement
#                  _diffrn_scan_frame_axis.displacement_increment
#                  _diffrn_scan_frame_axis.displacement_rstrt_incr
#                  _diffrn_scan_frame_axis.reference_angle
#                  _diffrn_scan_frame_axis.reference_displacement
#                  _diffrn_scan_frame_axis.frame_id
#
#       categor    MAP
#
#                  _map.details
#                  _map.diffrn_id
#                  _map.entry_id
#                  _map.id
#
#       categor    MAP_SEGMENT
#
#                  _map_segment.array_id
#                  _map_segment.binary_id
#                  _map_segment.mask_array_id
#                  _map_segment.mask_binary_id
#                  _map_segment.id
#                  _map_segment.map_id
#                  _map_segment.details
#
#       ***DEPRECATED*** data items
#
#                  _diffrn_detector_axis.id
#                  _diffrn_detector_element.center[1]
#                  _diffrn_detector_element.center[2]
#                  _diffrn_measurement_axis.id
#
#       ***DEPRECATED*** category  DIFFRN_FRAME_DATA
#
#                  _diffrn_frame_data.array_id
#                  _diffrn_frame_data.binary_id
#                  _diffrn_frame_data.detector_element_id
#                  _diffrn_frame_data.id
#                  _diffrn_frame_data.details
#
#
#        ITEM_TYPE_LIST
#        ITEM_UNITS_LIST
#        DICTIONARY_HISTORY
#
##############################################################################


#########################
## CATEGORY_GROUP_LIST ##
#########################

     loop_
    _category_group_list.id
    _category_group_list.parent_id
    _category_group_list.description
             'inclusive_group'   .
;             Categories that belong to the dictionary extension.
;
             'array_data_group'
             'inclusive_group'
;             Categories that describe array data.
;
             'axis_group'
             'inclusive_group'
;             Categories that describe axes.
;
             'diffrn_group'
             'inclusive_group'
;            Categories that describe details of the diffraction experiment.
;


##################
## SUB_CATEGORY ##
##################

     loop_
    _sub_category.id
    _sub_category.description
              'matrix'
;              The collection of elements of a matrix.
;
              'vector'
;              The collection of elements of a vector.
;




##############
# ARRAY_DATA #
##############


save_ARRAY_DATA
    _category.description
;    Data items in the ARRAY_DATA category are the containers for
     the array data items described in the category ARRAY_STRUCTURE.
     
     It is recognized that the data in this category needs to be used in
     two distinct ways.  During a data collection the lack of ancillary
     data and timing constraints in processing data may dictate the
     need to make a 'miniCBF' nothing more than an essential minimum
     of information to record the results of the data collection.  In that
     case it is proper to use the ARRAY_DATA category as a
     container for just a single image and a compacted, beam-line
     dependent list of data collection parameter values.  In such
     a case, only the tags '_array_data.header_convention',
     '_array_data.header_contents' and '_array_data.data' need be
     populated.
     
     For full processing and archiving, most of the tags in this
     dictionary will need to be populated.
     
;
    _category.id                   array_data
    _category.mandatory_code       no
     loop_
    _category_key.name             '_array_data.array_id'
                                   '_array_data.binary_id'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
        Example 1 -

        This example shows two binary data blocks.  The first one
        was compressed by the CBF_CANONICAL compression algorithm and is
        presented as hexadecimal data.  The first character 'H' on the
        data lines means hexadecimal.  It could have been 'O' for octal
        or 'D' for decimal.  The second character on the line shows
        the number of bytes in each word (in this case '4'), which then
        requires eight hexadecimal digits per word.  The third character
        gives the order of octets within a word, in this case '<'
        for the ordering 4321 (i.e. 'big-endian').  Alternatively, the
        character '>' could have been used for the ordering 1234
        (i.e. 'little-endian').  The block has a 'message digest'
        to check the integrity of the data.

        The second block is similar, but uses CBF_PACKED compression
        and BASE64 encoding.  Note that the size and the digest are
        different.
;
;

        loop_
        _array_data.array_id
        _array_data.binary_id
        _array_data.data
        image_1 1
        ;
        --CIF-BINARY-FORMAT-SECTION--
        Content-Type: application/octet-stream;
             conversions="X-CBF_CANONICAL"
        Content-Transfer-Encoding: X-BASE16
        X-Binary-Size: 3927126
        X-Binary-ID: 1
        Content-MD5: u2sTJEovAHkmkDjPi+gWsg==

        # Hexadecimal encoding, byte 0, byte order ...21
        #
        H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ...
        ....
        --CIF-BINARY-FORMAT-SECTION----
        ;
        image_2 2
        ;
        --CIF-BINARY-FORMAT-SECTION--
        Content-Type: application/octet-stream;
             conversions="X-CBF-PACKED"
        Content-Transfer-Encoding: BASE64
        X-Binary-Size: 3745758
        X-Binary-ID: 2
        Content-MD5: 1zsJjWPfol2GYl2V+QSXrw==

        ELhQAAAAAAAA...
        ...
        --CIF-BINARY-FORMAT-SECTION----
        ;
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
        Example 2 -

        This example shows a single image in a miniCBF, provided by
        E. Eikenberry.  The entire CBF consists of one data block
        containing one category and three tags.  The CBFlib
        program convert_miniCBF and a suitable template file
        can be used to convert this miniCBF to a full imgCIF
        file.
;
;
        ###CBF: VERSION 1.5
        # CBF file written by CBFlib v0.7.8

        data_insulin_pilatus6m

        _array_data.header_convention SLS_1.0
        _array_data.header_contents
        ;
        # Detector: PILATUS 6M SN: 60-0001
        # 2007/Jun/17 15:12:36.928
        # Pixel_size 172e-6 m x 172e-6 m
        # Silicon sensor, thickness 0.000320 m
        # Exposure_time 0.995000 s
        # Exposure_period 1.000000 s
        # Tau = 194.0e-09 s
        # Count_cutoff 1048575 counts
        # Threshold_setting 5000 eV
        # Wavelength 1.2398 A
        # Energy_range (0, 0) eV
        # Detector_distance 0.15500 m
        # Detector_Voffset -0.01003 m
        # Beam_xy (1231.00, 1277.00) pixels
        # Flux 22487563295 ph/s
        # Filter_transmission 0.0008
        # Start_angle 13.0000 deg.
        # Angle_increment 1.0000 deg.
        # Detector_2theta 0.0000 deg.
        # Polarization 0.990
        # Alpha 0.0000 deg.
        # Kappa 0.0000 deg.
        # Phi 0.0000 deg.
        # Chi 0.0000 deg.
        # Oscillation_axis  X, CW
        # N_oscillations 1
        ;

        _array_data.data
        ;
        --CIF-BINARY-FORMAT-SECTION--
        Content-Type: application/octet-stream;
             conversions="x-CBF_BYTE_OFFSET"
        Content-Transfer-Encoding: BINARY
        X-Binary-Size: 6247567
        X-Binary-ID: 1
        X-Binary-Element-Type: "signed 32-bit integer"
        X-Binary-Element-Byte-Order: LITTLE_ENDIAN
        Content-MD5: 8wO6i2+899lf5iO8QPdgrw==
        X-Binary-Number-of-Elements: 6224001
        X-Binary-Size-Fastest-Dimension: 2463
        X-Binary-Size-Second-Dimension: 2527
        X-Binary-Size-Padding: 4095

        ...
        
        --CIF-BINARY-FORMAT-SECTION----
        ;
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -

save_


save__array_data.array_id
    _item_description.description
;             This item is a pointer to _array_structure.id in the
              ARRAY_STRUCTURE category.
              
              If not given, it defaults to 1.
;
    _item.name                  '_array_data.array_id'
    _item.category_id             array_data
    _item.mandatory_code          implicit
    _item_type.code               code
     save_


save__array_data.binary_id
    _item_description.description
;             This item is an integer identifier which, along with
              _array_data.array_id, should uniquely identify the
              particular block of array data.

              If _array_data.binary_id is not explicitly given,
              it defaults to 1.

              The value of _array_data.binary_id distinguishes
              among multiple sets of data with the same array
              structure.

              If the MIME header of the data array specifies a
              value for X-Binary-ID, the value of  _array_data.binary_id
              should be equal to the value given for X-Binary-ID.
;
     loop_
    _item.name
    _item.category_id
    _item.mandatory_code
             '_array_data.binary_id'            array_data
                                                                implicit
             '_diffrn_data_frame.binary_id'     diffrn_data_frame
                                                                implicit
             '_array_intensities.binary_id'     array_intensities
                                                                implicit
     loop_
    _item_linked.child_name
    _item_linked.parent_name
             '_diffrn_data_frame.binary_id'     '_array_data.binary_id'
             '_array_intensities.binary_id'     '_array_data.binary_id'

    _item_default.value           1
    _item_type.code               int
     loop_
    _item_range.maximum
    _item_range.minimum
                            1  1
                            .  1
     save_


save__array_data.data
    _item_description.description
;             The value of _array_data.data contains the array data
              encapsulated in a STAR string.

              The representation used is a variant on the
              Multipurpose Internet Mail Extensions (MIME) specified
              in RFC 2045-2049 by N. Freed et al.  The boundary
              delimiter used in writing an imgCIF or CBF is
              '\n--CIF-BINARY-FORMAT-SECTION--' (including the
              required initial '\n--').

              The Content-Type may be any of the discrete types permitted
              in RFC 2045; 'application/octet-stream' is recommended
              for diffraction images in the ARRAY_DATA category.
              Note:  When appropriate in other categories, e.g. for
              photographs of crystals, more precise types, such as
              'image/jpeg', 'image/tiff', 'image/png', etc. should be used.
              
              If an octet stream was compressed, the compression should
              be specified by the parameter 
                'conversions="X-CBF_PACKED"'
              or the parameter 
                'conversions="X-CBF_CANONICAL"'
              or the parameter 
                'conversions="X-CBF_BYTE_OFFSET"'
                
              If the parameter 
                'conversions="X-CBF_PACKED"'
              is given it may be further modified with the parameters
                '"uncorrelated_sections"'
              or
                '"flat"'
              
              If the '"uncorrelated_sections"' parameter is
              given, each section will be compressed without using
              the prior section for averaging.
              
              If the '"flat"' parameter is given, each the
              image will be treated as one long row.

              The Content-Transfer-Encoding may be 'BASE64',
              'Quoted-Printable', 'X-BASE8', 'X-BASE10',
              'X-BASE16' or 'X-BASE32K', for an imgCIF or 'BINARY'
              for a CBF.  The octal, decimal and hexadecimal transfer
              encodings are provided for convenience in debugging and
              are not recommended for archiving and data interchange.

              In a CIF, one of the parameters 'charset=us-ascii',
              'charset=utf-8' or 'charset=utf-16' may be used on the
              Content-Transfer-Encoding to specify the character set
              used for the external presentation of the encoded data.
              If no charset parameter is given, the character set of
              the enclosing CIF is assumed.  In any case, if a BOM
              flag is detected (FE FF for big-endian UTF-16, FF FE for
              little-endian UTF-16 or EF BB BF for UTF-8) is detected,
              the indicated charset will be assumed until the end of the
              encoded data or the detection of a different BOM.  The
              charset of the Content-Transfer-Encoding is not the character
              set of the encoded data, only the character set of the
              presentation of the encoded data and should be respecified
              for each distinct STAR string.

              In an imgCIF file, the encoded binary data begins after
              the empty line terminating the header.  In an imgCIF file,
              the encoded binary data ends with the terminating boundary
              delimiter '\n--CIF-BINARY-FORMAT-SECTION----'
              in the currently effective charset or with the '\n; '
              that terminates the STAR string.

              In a CBF, the raw binary data begins after an empty line
              terminating the header and after the sequence:

              Octet   Hex   Decimal  Purpose
                0     0C       12    (ctrl-L) Page break
                1     1A       26    (ctrl-Z) Stop listings in MS-DOS
                2     04       04    (Ctrl-D) Stop listings in UNIX
                3     D5      213    Binary section begins

              None of these octets are included in the calculation of
              the message size or in the calculation of the
              message digest.

              The X-Binary-Size header specifies the size of the
              equivalent binary data in octets.  If compression was
              used, this size is the size after compression, including
              any book-keeping fields.  An adjustment is made for
              the deprecated binary formats in which eight bytes of binary
              header are used for the compression type.  In this case,
              the eight bytes used for the compression type are subtracted
              from the size, so that the same size will be reported
              if the compression type is supplied in the MIME header.
              Use of the MIME header is the recommended way to
              supply the compression type.  In general, no portion of
              the  binary header is included in the calculation of the size.

              The X-Binary-Element-Type header specifies the type of
              binary data in the octets, using the same descriptive
              phrases as in _array_structure.encoding_type.  The default
              value is 'unsigned 32-bit integer'.

              An MD5 message digest may, optionally, be used. The 'RSA Data
              Security, Inc. MD5 Message-Digest Algorithm' should be used.
              No portion of the header is included in the calculation of the
              message digest.

              If the Transfer Encoding is 'X-BASE8', 'X-BASE10' or
              'X-BASE16', the data are presented as octal, decimal or
              hexadecimal data organized into lines or words.  Each word
              is created by composing octets of data in fixed groups of
              2, 3, 4, 6 or 8 octets, either in the order ...4321 ('big-
              endian') or 1234... ('little-endian').  If there are fewer
              than the specified number of octets to fill the last word,
              then the missing octets are presented as '==' for each
              missing octet.  Exactly two equal signs are used for each
              missing octet even for octal and decimal encoding.
              The format of lines is:

              rnd xxxxxx xxxxxx xxxxxx

              where r is 'H', 'O' or 'D' for hexadecimal, octal or
              decimal, n is the number of octets per word and d is '<'
              or '>' for the '...4321' and '1234...' octet orderings,
              respectively.  The '==' padding for the last word should
              be on the appropriate side to correspond to the missing
              octets, e.g.

              H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000

              or

              H3> FF0700 00====

              For these hexadecimal, octal and decimal formats only,
              comments beginning with '#' are permitted to improve
              readability.

              BASE64 encoding follows MIME conventions.  Octets are
              in groups of three: c1, c2, c3.  The resulting 24 bits
              are broken into four six-bit quantities, starting with
              the high-order six bits (c1 >> 2) of the first octet, then
              the low-order two bits of the first octet followed by the
              high-order four bits of the second octet [(c1 & 3)<<4 | (c2>>4)],
              then the bottom four bits of the second octet followed by the
              high-order two bits of the last octet [(c2 & 15)<<2 | (c3>>6)],
              then the bottom six bits of the last octet (c3 & 63).  Each
              of these four quantities is translated into an ASCII character
              using the mapping:

                        1         2         3         4         5         6
              0123456789012345678901234567890123456789012345678901234567890123
              |         |         |         |         |         |         |
              ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/

              With short groups of octets padded on the right with one '='
              if c3 is missing, and with '==' if both c2 and c3 are missing.

              X-BASE32K encoding is similar to BASE64 encoding, except that
              sets of 15 octets are encoded as sets of 8 16-bit unicode
              characters, by breaking the 120 bits into 8 15-bit quantities.
              256 is added to each 15 bit quantity to bring it into a
              printable uncode range.  When encoding, zero padding is used
              to fill out the last 15 bit quantity.  If 8 or more bits of
              padding are used, a single equals sign (hexadecimal 003D) is
              appended.  Embedded whitespace and newlines are introduced
              to produce lines of no more than 80 characters each.  On
              decoding, all printable ascii characters and ascii whitespace
              characters are ignored except for any trailing equals signs.
              The number of trailing equals signs indicated the number of
              trailing octets to be trimmed from the end of the decoded data.
              (see Georgi Darakev, Vassil Litchev, Kostadin Z. Mitev, Herbert
              J. Bernstein, 'Efficient Support of Binary Data in the XML
              Implementation of the NeXus File Format',absract W0165,
              ACA Summer Meeting, Honolulu, HI, July 2006).

              QUOTED-PRINTABLE encoding also follows MIME conventions, copying
              octets without translation if their ASCII values are 32...38,
              42, 48...57, 59, 60, 62, 64...126 and the octet is not a ';'
              in column 1.  All other characters are translated to =nn, where
              nn is the hexadecimal encoding of the octet.  All lines are
              'wrapped' with a terminating '=' (i.e. the MIME conventions
              for an implicit line terminator are never used).
              
              The "X-Binary-Element-Byte-Order" can specify either 
              '"BIG_ENDIAN"' or '"LITTLE_ENDIAN"' byte order of the imaage 
              data.  Only LITTLE_ENDIAN is recommended.  Processors
              may treat BIG_ENDIAN as a warning of data that can
              only be processed by special software.

              The "X-Binary-Number-of-Elements" specifies the number of 
              elements (not the number of octets) in the decompressed, decoded 
              image.

              The optional "X-Binary-Size-Fastest-Dimension" specifies the 
              number of elements (not the number of octets) in one row of the 
              fastest changing dimension of the binary data array. This 
              information must be in the MIME header for proper operation of 
              some of the decompression algorithms.

              The optional "X-Binary-Size-Second-Dimension" specifies the 
              number of elements (not the number of octets) in one column of 
              the second-fastest changing dimension of the binary data array. 
              This information must be in the MIME header for proper operation 
              of some of the decompression algorithms.

              The optional "X-Binary-Size-Third-Dimension" specifies the number 
              of sections for the third-fastest changing dimension of the
              binary data array.
              
              The optional "X-Binary-Size-Padding" specifies the size in 
              octets of an optional padding after the binary array data and 
              before the closing flags for a binary section.
;
    _item.name                  '_array_data.data'
    _item.category_id             array_data
    _item.mandatory_code          yes
    _item_type.code               binary
save_


save__array_data.header_contents
    _item_description.description
;             This item is an text field for use in minimal CBF files to carry
              essential header information to be kept with image data
              in _array_data.data when the tags that normally carry the
              structured metadata for the image have not been populated.
              
              Normally this data item should not appear when the full set
              of tags have been populated and _diffrn_data_frame.details
              appears.
;
    _item.name                  '_array_data.header_contents'
    _item.category_id            array_data
    _item.mandatory_code         no
    _item_type.code              text
     save_



save__array_data.header_convention
    _item_description.description
;             This item is an identifier for the convention followed in
              constructing the contents of _array_data.header_contents
              
              The permitted values are of the of an image creator identifier
              followed by an underscore and a version string.  To avoid
              confusion about conventions, all creator identifiers
              should be registered with the IUCr and the conventions
              for all identifiers and versions should be posted on
              the MEDSBIO.org web site.
;
    _item.name                  '_array_data.header_convention'
    _item.category_id            array_data
    _item.mandatory_code         no
    _item_type.code              code
     save_




######################
# ARRAY_ELEMENT_SIZE #
######################


save_ARRAY_ELEMENT_SIZE
    _category.description
;    Data items in the ARRAY_ELEMENT_SIZE category record the physical
     size of array elements along each array dimension.
;
    _category.id                   array_element_size
    _category.mandatory_code       no
     loop_
    _category_key.name             '_array_element_size.array_id'
                                   '_array_element_size.index'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;       Example 1 - A regular 2D array with a uniform element dimension
                    of 1220 nanometres.
;
;
        loop_
       _array_element_size.array_id
       _array_element_size.index
       _array_element_size.size
        image_1   1    1.22e-6
        image_1   2    1.22e-6
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_


save__array_element_size.array_id
    _item_description.description
;             This item is a pointer to _array_structure.id in the
              ARRAY_STRUCTURE category.
;
    _item.name                  '_array_element_size.array_id'
    _item.category_id             array_element_size
    _item.mandatory_code          implicit
    _item_type.code               code
     save_


save__array_element_size.index
    _item_description.description
;             This item is a pointer to _array_structure_list.index in
              the ARRAY_STRUCTURE_LIST category.
;
    _item.name                  '_array_element_size.index'
    _item.category_id             array_element_size
    _item.mandatory_code          yes
    _item_type.code               code
     save_


save__array_element_size.size
    _item_description.description
;              The size in metres of an image element in this
               dimension. This supposes that the elements are arranged
               on a regular grid.
;
    _item.name               '_array_element_size.size'
    _item.category_id          array_element_size
    _item.mandatory_code       yes
    _item_type.code            float
    _item_units.code           'metres'
     loop_
    _item_range.maximum
    _item_range.minimum
                            .   0.0
     save_


#####################
# ARRAY_INTENSITIES #
#####################


save_ARRAY_INTENSITIES
    _category.description
;             Data items in the ARRAY_INTENSITIES category record the
              information required to recover the intensity data from
              the set of data values stored in the ARRAY_DATA category.

              The detector may have a complex relationship
              between the raw intensity values and the number of
              incident photons.  In most cases, the number stored
              in the final array will have a simple linear relationship
              to the actual number of incident photons, given by
              _array_intensities.gain.  If raw, uncorrected values
              are presented (e.g. for calibration experiments), the
              value of _array_intensities.linearity will be 'raw'
              and _array_intensities.gain will not be used.

;
    _category.id                   array_intensities
    _category.mandatory_code       no
    loop_
    _category_key.name             '_array_intensities.array_id'
                                   '_array_intensities.binary_id'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
        Example 1
;
;
        loop_
        _array_intensities.array_id
        _array_intensities.linearity
        _array_intensities.gain
        _array_intensities.overload
        _array_intensities.undefined_value
        _array_intensities.pixel_fast_bin_size
        _array_intensities.pixel_slow_bin_size
        _array_intensities.pixel_binning_method
        image_1   linear  1.2    655535   0   2   2    hardware
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_


save__array_intensities.array_id
    _item_description.description
;             This item is a pointer to _array_structure.id in the
              ARRAY_STRUCTURE category.
;
    _item.name                  '_array_intensities.array_id'
    _item.category_id             array_intensities
    _item.mandatory_code          implicit
    _item_type.code               code
     save_


save__array_intensities.binary_id
    _item_description.description
;             This item is a pointer to _array_data.binary_id in the
              ARRAY_DATA category.
;
    _item.name                  '_array_intensities.binary_id'
    _item.category_id             array_intensities
    _item.mandatory_code          implicit
    _item_type.code               int
     save_


save__array_intensities.gain
    _item_description.description
;              Detector 'gain'. The factor by which linearized
               intensity count values should be divided to produce
               true photon counts.
;
    _item.name              '_array_intensities.gain'
    _item.category_id          array_intensities
    _item.mandatory_code       yes
    _item_type.code            float
     loop_
    _item_range.maximum
    _item_range.minimum
                            .   0.0
    _item_units.code           'counts_per_photon'
     loop_
    _item_related.related_name
    _item_related.function_code  '_array_intensities.gain_esd'
                                 'associated_value'
    save_


save__array_intensities.gain_esd
    _item_description.description
;            The estimated standard deviation in detector 'gain'.
;
    _item.name              '_array_intensities.gain_esd'
    _item.category_id          array_intensities
    _item.mandatory_code       yes
    _item_type.code            float
     loop_
    _item_range.maximum
    _item_range.minimum
                            .   0.0

    _item_units.code          'counts_per_photon'
     loop_
    _item_related.related_name
    _item_related.function_code  '_array_intensities.gain'
                                 'associated_esd'
    save_


save__array_intensities.linearity
    _item_description.description
;              The intensity linearity scaling method used to convert
               from the raw intensity to the stored element value:

               'linear' is linear.

               'offset'  means that the value defined by
               _array_intensities.offset should be added to each
                element value.

               'scaling' means that the value defined by
               _array_intensities.scaling should be multiplied with each
               element value.

               'scaling_offset' is the combination of the two previous cases,
               with the scale factor applied before the offset value.

               'sqrt_scaled' means that the square root of raw
               intensities multiplied by _array_intensities.scaling is
               calculated and stored, perhaps rounded to the nearest
               integer. Thus, linearization involves dividing the stored
               values by _array_intensities.scaling and squaring the
               result.

               'logarithmic_scaled' means that the logarithm base 10 of
               raw intensities multiplied by _array_intensities.scaling
               is calculated and stored, perhaps rounded to the nearest
               integer. Thus, linearization involves dividing the stored
               values by _array_intensities.scaling and calculating 10
               to the power of this number.

               'raw' means that the data are a set of raw values straight
               from the detector.
;

    _item.name               '_array_intensities.linearity'
    _item.category_id          array_intensities
    _item.mandatory_code       yes
    _item_type.code            code
     loop_
    _item_enumeration.value
    _item_enumeration.detail
                              'linear' .
                              'offset'
;              The value defined by  _array_intensities.offset should
               be added to each element value.
;
                              'scaling'
;              The value defined by _array_intensities.scaling should be
               multiplied with each element value.
;
                              'scaling_offset'
;              The combination of the scaling and offset
               with the scale factor applied before the offset value.
;
                              'sqrt_scaled'
;              The square root of raw intensities multiplied by
               _array_intensities.scaling is calculated and stored,
               perhaps rounded to the nearest integer. Thus,
               linearization involves dividing the stored
               values by _array_intensities.scaling and squaring the
               result.
;
                              'logarithmic_scaled'
;              The logarithm base 10 of raw intensities multiplied by
               _array_intensities.scaling  is calculated and stored,
               perhaps rounded to the nearest integer. Thus,
               linearization involves dividing the stored values by
               _array_intensities.scaling and calculating 10 to the
               power of this number.
;
                              'raw'
;              The array consists of raw values to which no corrections have
               been applied.  While the handling of the data is similar to
               that given for 'linear' data with no offset, the meaning of
               the data differs in that the number of incident photons is
               not necessarily linearly related to the number of counts
               reported.  This value is intended for use either in
               calibration experiments or to allow for handling more
               complex data-fitting algorithms than are allowed for by
               this data item.
;

    save_


save__array_intensities.offset
    _item_description.description
;              Offset value to add to array element values in the manner
               described by the item _array_intensities.linearity.
;
    _item.name                 '_array_intensities.offset'
    _item.category_id          array_intensities
    _item.mandatory_code       no
    _item_type.code            float
    save_


save__array_intensities.overload
    _item_description.description
;              The saturation intensity level for this data array.
;
    _item.name                 '_array_intensities.overload'
    _item.category_id          array_intensities
    _item.mandatory_code       no
    _item_type.code            float
    _item_units.code          'counts'
    save_


save__array_intensities.pixel_fast_bin_size
    _item_description.description
;              The value of _array_intensities.pixel_fast_bin_size specifies
               the number of pixels that compose one element in the direction
               of the most rapidly varying array dimension.

               Typical values are 1, 2, 4 or 8.  When there is 1 pixel per
               array element in both directions, the value given for
               _array_intensities.pixel_binning_method normally should be
               'none'.

               It is specified as a float to allow for binning algorithms that
               create array elements that are not integer multiples of the 
               detector pixel size.
;
    _item.name              '_array_intensities.pixel_fast_bin_size'
    _item.category_id          array_intensities
    _item.mandatory_code       implicit
    _item_type.code            float
    _item_default.value        1.
     loop_
    _item_range.maximum
    _item_range.minimum
                            .   0.0
    _item_units.code           'pixels_per_element'
    save_


save__array_intensities.pixel_slow_bin_size
    _item_description.description
;              The value of _array_intensities.pixel_slow_bin_size specifies
               the number of pixels that compose one element in the direction
               of the second most rapidly varying array dimension.

               Typical values are 1, 2, 4 or 8.  When there is 1 pixel per
               array element in both directions, the value given for
               _array_intensities.pixel_binning_method normally should be
               'none'.

               It is specified as a float to allow for binning algorithms that
               create array elements that are not integer multiples of the
               detector pixel size.
;
    _item.name              '_array_intensities.pixel_slow_bin_size'
    _item.category_id          array_intensities
    _item.mandatory_code       implicit
    _item_type.code            float
    _item_default.value        1.
     loop_
    _item_range.maximum
    _item_range.minimum
                            .   0.0
    _item_units.code           'pixels_per_element'
    save_


save__array_intensities.pixel_binning_method
    _item_description.description
;              The value of _array_intensities.pixel_binning_method specifies
               the method used to derive array elements from multiple pixels.
;
    _item.name              '_array_intensities.pixel_binning_method'
    _item.category_id          array_intensities
    _item.mandatory_code       implicit
    _item_type.code            code
     loop_
    _item_enumeration.value
    _item_enumeration.detail
                               'hardware'
;              The element intensities were derived from the raw data of one
               or more pixels by used of hardware in the detector, e.g. by use
               of shift registers in a CCD to combine pixels into super-pixels.
;
                               'software'
;              The element intensities were derived from the raw data of more
               than one pixel by use of software.
;
                               'combined'
;              The element intensities were derived from the raw data of more
               than one pixel by use of both hardware and software, as when
               hardware binning is used in one direction and software in the
               other.
;
                               'none'
;              In the both directions, the data has not been binned.  The
               number of pixels is equal to the number of elements.

               When the value of _array_intensities.pixel_binning_method is
               'none' the values of _array_intensities.pixel_fast_bin_size
               and _array_intensities.pixel_slow_bin_size both must be 1.
;
                               'unspecified'
;              The method used to derive element intensities is not specified.
;
    _item_default.value        'unspecified'
    save_

save__array_intensities.scaling
    _item_description.description
;              Multiplicative scaling value to be applied to array data
               in the manner described by item
               _array_intensities.linearity.
;
    _item.name                 '_array_intensities.scaling'
    _item.category_id          array_intensities
    _item.mandatory_code       no
    _item_type.code            float
    save_



save__array_intensities.undefined_value
    _item_description.description
;              A value to be substituted for undefined values in
               the data array.
;
    _item.name                 '_array_intensities.undefined_value'
    _item.category_id          array_intensities
    _item.mandatory_code       no
    _item_type.code            float
    save_


###################
# ARRAY_STRUCTURE #
###################


save_ARRAY_STRUCTURE
    _category.description
;    Data items in the ARRAY_STRUCTURE category record the organization and
     encoding of array data that may be stored in the ARRAY_DATA category.
;
    _category.id                   array_structure
    _category.mandatory_code       no
    _category_key.name             '_array_structure.id'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;   Example 1 -
;
;
     loop_
    _array_structure.id
    _array_structure.encoding_type
    _array_structure.compression_type
    _array_structure.byte_order
     image_1       "unsigned 16-bit integer"  none  little_endian
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_


save__array_structure.byte_order
    _item_description.description
;              The order of bytes for integer values which require more
               than 1 byte.

               (IBM-PC's and compatibles and DEC VAXs use low-byte-first
               ordered integers, whereas Hewlett Packard 700
               series, Sun-4 and Silicon Graphics use high-byte-first
               ordered integers.  DEC Alphas can produce/use either
               depending on a compiler switch.)
;

    _item.name                     '_array_structure.byte_order'
    _item.category_id               array_structure
    _item.mandatory_code            yes
    _item_type.code                 ucode
     loop_
    _item_enumeration.value
    _item_enumeration.detail
                                   'big_endian'
;       The first byte in the byte stream of the bytes which make up an
        integer value is the most significant byte of an integer.
;
                                   'little_endian'
;       The last byte in the byte stream of the bytes which make up an
        integer value is the most significant byte of an integer.
;
     save_


save__array_structure.compression_type
    _item_description.description
;             Type of data-compression method used to compress the array
              data.
;
    _item.name                   '_array_structure.compression_type'
    _item.category_id             array_structure
    _item.mandatory_code          no
    _item_type.code               ucode
    _item_default.value           'none'
     loop_
    _item_enumeration.value
    _item_enumeration.detail
                                  'byte_offset'
;       Using the 'byte_offset' compression scheme as per A. Hammersley
        and the CBFlib manual, section 3.3.3
;
                                  'canonical'
;       Using the 'canonical' compression scheme (International Tables
        for Crystallography Volume G, Section 5.6.3.1) and CBFlib
        manual section 3.3.1
;
                                  'none'
;       Data are stored in normal format as defined by
        _array_structure.encoding_type and
        _array_structure.byte_order.
;
                                  'packed'
;       Using the 'packed' compression scheme, a CCP4-style packing
        as per J. P. Abrahams pack_c.c and CBFlib manual, section 3.3.2.
;
                                  'packed_v2'
;       Using the 'packed' compression scheme, version 2, as per
        J. P. Abrahams pack_c.c and CBFlib manual, section 3.3.2.
;
    save_

save__array_structure.compression_type_flag
    _item_description.description
;             Flags modifying the type of data-compression method used to 
              compress the arraydata.
;
    _item.name                   '_array_structure.compression_type_flag'
    _item.category_id             array_structure
    _item.mandatory_code          no
    _item_type.code               ucode
     loop_
    _item_enumeration.value
    _item_enumeration.detail
                                  'uncorrelated_sections'
;       When applying packed or packed_v2 compression on an array with
        uncorrelated sections, do not average in points from the prior
        section.
;
                                  'flat'
;       When applying packed or packed_v2 compression on an array with
        treat the entire image as a single line set the maximum number
        of bits for an offset to 65 bits.
        
        The flag is included for compatibility with software prior to
        CBFlib_0.7.7, and should not be used for new data sets.

;

    save_

save__array_structure.encoding_type
    _item_description.description
;              Data encoding of a single element of array data.

               The type 'unsigned 1-bit integer' is used for
               packed Booleans arrays for masks.  Each element
               of the array corresponds to a single bit
               packed in unsigned 8-bit data.
               
               In several cases, the IEEE format is referenced.
               See IEEE Standard 754-1985 (IEEE, 1985).

               Ref: IEEE (1985). IEEE Standard for Binary Floating-Point
               Arithmetic. ANSI/IEEE Std 754-1985. New York: Institute of
               Electrical and Electronics Engineers.
;

    _item.name                '_array_structure.encoding_type'
    _item.category_id          array_structure
    _item.mandatory_code       yes
    _item_type.code            uline
     loop_
    _item_enumeration.value
                              'unsigned 1-bit integer'
                              'unsigned 8-bit integer'
                              'signed 8-bit integer'
                              'unsigned 16-bit integer'
                              'signed 16-bit integer'
                              'unsigned 32-bit integer'
                              'signed 32-bit integer'
                              'signed 32-bit real IEEE'
                              'signed 64-bit real IEEE'
                              'signed 32-bit complex IEEE'
     save_


save__array_structure.id
    _item_description.description
;             The value of _array_structure.id must uniquely identify
              each item of array data.
              
              This item has been made implicit and given a default value of 1
              as a convenience in writing miniCBF files.  Normally an
              explicit name with useful content should be used.
;
    loop_
    _item.name
    _item.category_id
    _item.mandatory_code
             '_array_structure.id'              array_structure      implicit
             '_array_data.array_id'             array_data           implicit
             '_array_structure_list.array_id'   array_structure_list implicit
             '_array_intensities.array_id'      array_intensities    implicit
             '_diffrn_data_frame.array_id'      diffrn_data_frame    implicit


    _item_default.value           1
    _item_type.code               code
     loop_
    _item_linked.child_name
    _item_linked.parent_name
             '_array_data.array_id'             '_array_structure.id'
             '_array_structure_list.array_id'   '_array_structure.id'
             '_array_intensities.array_id'      '_array_structure.id'
             '_diffrn_data_frame.array_id'      '_array_structure.id'

     save_


########################
# ARRAY_STRUCTURE_LIST #
########################


save_ARRAY_STRUCTURE_LIST
    _category.description
;    Data items in the ARRAY_STRUCTURE_LIST category record the size
     and organization of each array dimension.

     The relationship to physical axes may be given.
;
    _category.id                   array_structure_list
    _category.mandatory_code       no
     loop_
    _category_key.name             '_array_structure_list.array_id'
                                   '_array_structure_list.index'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;       Example 1 - An image array of 1300 x 1200 elements.  The raster
                    order of the image is left to right (increasing) in the
                    first dimension and bottom to top (decreasing) in
                    the second dimension.
;
;
        loop_
       _array_structure_list.array_id
       _array_structure_list.index
       _array_structure_list.dimension
       _array_structure_list.precedence
       _array_structure_list.direction
       _array_structure_list.axis_set_id
        image_1   1    1300    1     increasing  ELEMENT_X
        image_1   2    1200    2     decreasing  ELEMENY_Y
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_


save__array_structure_list.array_id
    _item_description.description
;             This item is a pointer to _array_structure.id in the
              ARRAY_STRUCTURE category.
;
    _item.name                  '_array_structure_list.array_id'
    _item.category_id             array_structure_list
    _item.mandatory_code          implicit
    _item_type.code               code
save_


save__array_structure_list.axis_set_id
    _item_description.description
;              This is a descriptor for the physical axis or set of axes
               corresponding to an array index.

               This data item is related to the axes of the detector
               itself given in DIFFRN_DETECTOR_AXIS, but usually differs
               in that the axes in this category are the axes of the
               coordinate system of reported data points, while the axes in
               DIFFRN_DETECTOR_AXIS are the physical axes
               of the detector describing the 'poise' of the detector as an
               overall physical object.

               If there is only one axis in the set, the identifier of
               that axis should be used as the identifier of the set.
;
     loop_
    _item.name
    _item.category_id
    _item.mandatory_code
           '_array_structure_list.axis_set_id'
                                  array_structure_list            yes
           '_array_structure_list_axis.axis_set_id'
                                  array_structure_list_axis       implicit
    _item_type.code               code
     loop_
    _item_linked.child_name
    _item_linked.parent_name
           '_array_structure_list_axis.axis_set_id'
                               '_array_structure_list.axis_set_id'


     save_


save__array_structure_list.dimension
    _item_description.description
;              The number of elements stored in the array structure in this
               dimension.
;
    _item.name                '_array_structure_list.dimension'
    _item.category_id          array_structure_list
    _item.mandatory_code       yes
    _item_type.code            int
     loop_
    _item_range.maximum
    _item_range.minimum
                            1  1
                            .  1
     save_


save__array_structure_list.direction
    _item_description.description
;             Identifies the direction in which this array index changes.
;
    _item.name                '_array_structure_list.direction'
    _item.category_id          array_structure_list
    _item.mandatory_code       yes
    _item_type.code            code
     loop_
    _item_enumeration.value
    _item_enumeration.detail

                              'increasing'
;        Indicates the index changes from 1 to the maximum dimension.
;
                              'decreasing'
;        Indicates the index changes from the maximum dimension to 1.
;
     save_


save__array_structure_list.index
    _item_description.description
;              Identifies the one-based index of the row or column in the
               array structure.
;
     loop_
    _item.name
    _item.category_id
    _item.mandatory_code
           '_array_structure_list.index'        array_structure_list   yes
           '_array_structure_list.precedence'   array_structure_list   yes
           '_array_element_size.index'          array_element_size     yes

    _item_type.code            int

     loop_
    _item_linked.child_name
    _item_linked.parent_name
          '_array_element_size.index'         '_array_structure_list.index'
     loop_
    _item_range.maximum
    _item_range.minimum
                            1  1
                            .  1
     save_


save__array_structure_list.precedence
    _item_description.description
;              Identifies the rank order in which this array index changes
               with respect to other array indices.  The precedence of 1
               indicates the index which changes fastest.
;
    _item.name                '_array_structure_list.precedence'
    _item.category_id          array_structure_list
    _item.mandatory_code       yes
    _item_type.code            int
     loop_
    _item_range.maximum
    _item_range.minimum
                            1  1
                            .  1
     save_


#############################
# ARRAY_STRUCTURE_LIST_AXIS #
#############################

save_ARRAY_STRUCTURE_LIST_AXIS
    _category.description
;    Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe
     the physical settings of sets of axes for the centres of pixels that
     correspond to data points described in the
     ARRAY_STRUCTURE_LIST category.

     In the simplest cases, the physical increments of a single axis correspond
     to the increments of a single array index.  More complex organizations,
     e.g. spiral scans, may require coupled motions along multiple axes.

     Note that a spiral scan uses two coupled axes: one for the angular
     direction and one for the radial direction.  This differs from a
     cylindrical scan for which the two axes are not coupled into one set.
;
    _category.id                   array_structure_list_axis
    _category.mandatory_code       no
     loop_
    _category_key.name
                                  '_array_structure_list_axis.axis_set_id'
                                  '_array_structure_list_axis.axis_id'
     loop_
    _category_group.id           'inclusive_group'
                                 'array_data_group'
     save_


save__array_structure_list_axis.axis_id
    _item_description.description
;              The value of this data item is the identifier of one of
               the axes in the set of axes for which settings are being
               specified.

               Multiple axes may be specified for the same value of
               _array_structure_list_axis.axis_set_id.

               This item is a pointer to _axis.id in the
               AXIS category.
;
    _item.name                 '_array_structure_list_axis.axis_id'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       yes
    _item_type.code            code
     save_


save__array_structure_list_axis.axis_set_id
    _item_description.description
;              The value of this data item is the identifier of the
               set of axes for which axis settings are being specified.

               Multiple axes may be specified for the same value of
               _array_structure_list_axis.axis_set_id.

               This item is a pointer to
               _array_structure_list.axis_set_id
               in the ARRAY_STRUCTURE_LIST category.

               If this item is not specified, it defaults to the corresponding
               axis identifier.
;
    _item.name                 '_array_structure_list_axis.axis_set_id'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       implicit
    _item_type.code            code
     save_


save__array_structure_list_axis.angle
    _item_description.description
;              The setting of the specified axis in degrees for the first
               data point of the array index with the corresponding value
               of _array_structure_list.axis_set_id.  If the index is
               specified as 'increasing', this will be the centre of the
               pixel with index value 1.  If the index is specified as
               'decreasing', this will be the centre of the pixel with
               maximum index value.
;
    _item.name                 '_array_structure_list_axis.angle'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_


save__array_structure_list_axis.angle_increment
    _item_description.description
;              The pixel-centre-to-pixel-centre increment in the angular
               setting of the specified axis in degrees.  This is not
               meaningful in the case of 'constant velocity' spiral scans
               and should not be specified for this case.

               See _array_structure_list_axis.angular_pitch.

;
    _item.name                 '_array_structure_list_axis.angle_increment'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_


save__array_structure_list_axis.displacement
    _item_description.description
;              The setting of the specified axis in millimetres for the first
               data point of the array index with the corresponding value
               of _array_structure_list.axis_set_id.  If the index is
               specified as 'increasing', this will be the centre of the
               pixel with index value 1.  If the index is specified as
               'decreasing', this will be the centre of the pixel with
               maximum index value.
;
    _item.name               '_array_structure_list_axis.displacement'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_

save__array_structure_list_axis.fract_displacement
    _item_description.description
;              The setting of the specified axis as a decimal fraction of 
               the axis unit vector for the first data point of the array 
               index with the corresponding value of 
               _array_structure_list.axis_set_id.  
               If the index is specified as 'increasing', this will be the 
               centre of the pixel with index value 1.  If the index is 
               specified as 'decreasing', this will be the centre of the 
               pixel with maximum index value.
;
    _item.name               '_array_structure_list_axis.fract_displacement'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
     save_

save__array_structure_list_axis.displacement_increment
    _item_description.description
;              The pixel-centre-to-pixel-centre increment for the displacement
               setting of the specified axis in millimetres.
;
    _item.name
        '_array_structure_list_axis.displacement_increment'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_

save__array_structure_list_axis.fract_displacement_increment
    _item_description.description
;              The pixel-centre-to-pixel-centre increment for the displacement
               setting of the specified axis as a decimal fraction of the
               axis unit vector.
;
    _item.name
        '_array_structure_list_axis.fract_displacement_increment'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_


save__array_structure_list_axis.angular_pitch
    _item_description.description
;              The pixel-centre-to-pixel-centre distance for a one-step
               change in the setting of the specified axis in millimetres.

               This is meaningful only for 'constant velocity' spiral scans
               or for uncoupled angular scans at a constant radius
               (cylindrical scans) and should not be specified for cases
               in which the angle between pixels (rather than the distance
               between pixels) is uniform.

               See _array_structure_list_axis.angle_increment.
;
    _item.name               '_array_structure_list_axis.angular_pitch'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_


save__array_structure_list_axis.radial_pitch
    _item_description.description
;              The radial distance from one 'cylinder' of pixels to the
               next in millimetres.  If the scan is a 'constant velocity'
               scan with differing angular displacements between pixels,
               the value of this item may differ significantly from the
               value of _array_structure_list_axis.displacement_increment.
;
    _item.name               '_array_structure_list_axis.radial_pitch'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_


save__array_structure_list_axis.reference_angle
     _item_description.description
;              The value of _array_structure_list_axis.reference_angle
               specifies the setting of the angle of this axis used for 
               determining a reference beam center and a reference detector 
               distance.  It is normally expected to be identical to the 
               value of _array_structure_list.angle.

;
     _item.name '_array_structure_list_axis.reference_angle'
     _item.category_id          array_structure_list_axis
     _item.mandatory_code       implicit
     _item_type.code            float
     _item_units.code           'degrees'
      save_


save__array_structure_list_axis.reference_displacement
     _item_description.description
;              The value of _array_structure_list_axis.reference_displacement
               specifies the setting of the displacement of this axis used 
               for determining a reference beam center and a reference detector
               distance.  It is normally expected to be identical to the value
               of _array_structure_list.displacement.

;
     _item.name '_array_structure_list_axis.reference_displacement'
     _item.category_id          array_structure_list_axis
     _item.mandatory_code       implicit
     _item_type.code            float
     _item_units.code           'millimetres'
      save_




########
# AXIS #
########

save_AXIS
    _category.description
;    Data items in the AXIS category record the information required
     to describe the various goniometer, detector, source and other
     axes needed to specify a data collection or the axes defining the
     coordinate system of an image.  
     
     The location of each axis is specified by two vectors: the axis 
     itself, given by a  unit vector in the direction of the axis, and 
     an offset to the base of the unit vector.  
     
     The vectors defining an axis are referenced to an appropriate
     coordinate system.  The axis vector, itself, is a dimensionless
     unit vector.  Where meaningful, the offset vector is given in
     millimetres.  In coordinate systems not measured in metres,
     the offset is not specified and is taken as zero. 
     
     The available coordinate systems are:
     
         The imgCIF standard laboratory coordinate system
         The direct lattice (fractional atomic coordinates)
         The orthogonal Cartesian coordinate system (real space)
         The reciprocal lattice
         An abstract orthogonal Cartesian coordinate frame
      
     For consistency in this discussion, we call the three coordinate 
     system axes X, Y and Z.  This is appropriate for the imgCIF
     standard laboratory coordinate system, and last two Cartesian
     coordinate systems, but for the direct lattice, X corresponds
     to a, Y to b and Z to c, while for the reciprocal lattice,
     X corresponds to a*, Y to b* and Z to c*.
     
     For purposes of visualization, all the coordinate systems are 
     taken as right-handed, i.e., using the convention that the extended 
     thumb of a right hand could point along the first (X) axis, the 
     straightened pointer finger could point along the second (Y) axis 
     and the middle finger folded inward could point along the third (Z)
     axis.  
     
     THE IMGCIF STANDARD LABORATORY COORDINATE SYSTEM
     
     The imgCIF standard laboratory coordinate system is a right-handed   
     orthogonal coordinate similar to the MOSFLM coordinate system,  
     but imgCIF puts Z along the X-ray beam, rather than putting X along the
     X-ray beam as in MOSFLM.
     
     The vectors for the imgCIF standard laboratory coordinate system
     form a right-handed Cartesian coordinate system with its origin
     in the sample or specimen.  The origin of the axis system should,
     if possible, be defined in terms of mechanically stable axes to be
     be both in the sample and in the beam.  If the sample goniometer or other
     sample positioner has two axes the intersection of which defines a
     unique point at which the sample should be mounted to be bathed
     by the beam, that will be the origin of the axis system.  If no such
     point is defined, then the midpoint of the line of intersection
     between the sample and the center of the beam will define the origin.
     For this definition the sample positioning system will be set at 
     its initial reference position for the experiment.


                             | Y (to complete right-handed system)
                             |
                             |
                             |
                             |
                             |
                             |________________X
                            /       principal goniometer axis
                           /
                          /
                         /
                        /
                       /Z (to source)




     Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from
     the sample or specimen along the  principal axis of the goniometer or
     sample positioning system if the sample positioning system has an axis that
     intersects the origin and which form an angle of more than 22.5 degrees
     with the beam axis.
     
     Axis 2 (Y): The Y-axis completes an orthogonal right-handed system
     defined by the X-axis and the Z-axis (see below).

     Axis 3 (Z): The Z-axis is derived from the source axis which goes from
     the sample to the source.  The Z-axis is the component of the source axis
     in the direction of the source orthogonal to the X-axis in the plane
     defined by the X-axis and the source axis.

     If the conditions for the X-axis can be met, the coordinate system
     will be based on the goniometer or other sample positioning system
     and the beam and not on the orientation of the detector, gravity etc.  
     The vectors necessary to specify all other axes are given by sets of 
     three components in the order (X, Y, Z).
     If the axis involved is a rotation axis, it is right-handed, i.e. as
     one views the object to be rotated from the origin (the tail) of the
     unit vector, the rotation is clockwise.  If a translation axis is
     specified, the direction of the unit vector specifies the sense of
     positive translation.

     Note:  This choice of coordinate system is similar to but significantly
     different from the choice in MOSFLM (Leslie & Powell, 2004).  In MOSFLM,
     X is along the X-ray beam (the CBF/imgCIF Z axis) and Z is along the
     rotation axis.
     
     In some experimental techniques, there is no goniometer or the principal
     axis of the goniometer is at a small acute angle with respect to
     the source axis.  In such cases, other reference axes are needed
     to define a useful coordinate system.  The order of priority in
     defining directions in such cases is to use the detector, then
     gravity, then north.
     
     
     If the X-axis cannot be defined as above, then the
     direction (not the origin) of the X-axis should be parallel to the axis 
     of the primary detector element corresponding to the most rapidly 
     varying dimension of that detector element's data array, with its 
     positive sense corresponding to increasing values of the index for 
     that dimension.  If the detector is such that such a direction cannot 
     be defined (as with a point detector) or that direction forms an
     angle of less than 22.5 degrees with respect to the source axis, then 
     the X-axis should be chosen so that if the Y-axis is chosen 
     in the direction of gravity, and the Z-axis is chosen to be along 
     the source axis, a right-handed orthogonal coordinate system is chosen.  
     In the case of a vertical source axis, as a last resort, the 
     X-axis should be chosen to point North.
     
     All rotations are given in degrees and all translations are given in mm.

     Axes may be dependent on one another.  The X-axis is the only goniometer
     axis the direction of which is strictly connected to the hardware.  All
     other axes are specified by the positions they would assume when the
     axes upon which they depend are at their zero points.

     When specifying detector axes, the axis is given to the beam centre.
     The location of the beam centre on the detector should be given in the
     DIFFRN_DETECTOR category in distortion-corrected millimetres from
     the (0,0) corner of the detector.

     It should be noted that many different origins arise in the definition
     of an experiment.  In particular, as noted above, it is necessary to
     specify the location of the beam centre on the detector in terms
     of the origin of the detector, which is, of course, not coincident
     with the centre of the sample.
     
     The unit cell, reciprocal cell and crystallographic orthogonal 
     Cartesian coordinate system are defined by the CELL and the matrices 
     in the ATOM_SITES category.
     
     THE DIRECT LATTICE (FRACTIONAL COORDINATES)
     
     The direct lattice coordinate system is a system of fractional
     coordinates aligned to the crystal, rather than to the laboratory.
     This is a natural coordinate system for maps and atomic coordinates.
     It is the simplest coordinate system in which to apply symmetry.
     The axes are determined by the cell edges, and are not necessarily
     othogonal.  This coordinate system is not uniquely defined and 
     depends on the cell parameters in the CELL category and the
     settings chosen to index the crystal. 
     
     Molecules in a crystal studied by X-ray diffracraction are organized
     into a repeating regular array of unit cells.  Each unit cell is defined 
     by three vectors, a, b and c.  To quote from Drenth,
     
     
     "The choice of the unit cell is not unique and therefore, guidelines
     have been established for selecting the standard basis vectors and
     the origin.  They are based on symmetry and metric considerations:
     
      "(1)  The axial system should be right handed.
       (2)  The basis vectors should coincide as much as possible with
       directions of highest symmetry."
       (3)  The cell taken should be the smallest one that satisfies
       condition (2)
       (4)  Of all the lattice vectors, none is shorter than a.
       (5)  Of those not directed along a, none is shorter than b.
       (6)  Of those not lying in the ab plane, none is shorter than c.
       (7)  The three angles between the basis vectors a, b and c are
       either all acute (<90°) or all obtuse (≥90°)."
     
     These rules do not produce a unique result that is stable under
     the assumption of experimental errors, and the the resulting cell
     may not be primitive.
     
     In this coordinate system, the vector (.5, .5, .5) is in the middle
     of the given unit cell.
     
     Grid coordinates are an important variation on fractional coordinates
     used when working with maps.  In imgCIF, the conversion from
     fractional to grid coordinates is implicit in the array indexing
     specified by _array_structure_list.dimension.  Note that this
     implicit grid-coordinate scheme is 1-based, not zero-based, i.e.
     the origin of the cell for axes along the cell edges with no
     specified _array_structure_list_axis.displacement will have
     grid coordinates of (1,1,1), i.e. array indices of (1,1,1).
     
     THE ORTHOGONAL CARTESIAN COORDINATE SYSTEM (REAL SPACE)
     
     The orthogonal Cartesian coordinate system is a transformation of
     the direct lattice to the actual physical coordinates of atoms in
     space.  It is similar to the laboratory coordinate system, but
     is anchored to and moves with the crystal, rather than being
     schored to the laboratory.  The transformation from fractional
     to orthogonal cartesian coordinates is given by the
              _atom_sites.Cartn_transf_matrix[i][j]  and
              _atom_sites.Cartn_transf_vector[i]
     tags.  A common choice for the matrix of the transformation is 
     given in the 1992 PDB format document
     
              | a      b cos(γ)   c cos(β)                         |
              | 0      b sin(γ)   c (cos(α) - cos(β)cos(γ))/sin(γ) |
              | 0      0          V/(a b sin(γ))                   |
     
     This is a convenient coordinate system in which to do fitting
     of models to maps and in which to understand the chemistry of
     a molecule.
     
     THE RECIPROCAL LATTICE
     
     The reciprocal lattice coordinate system is used for diffraction
     intensitities.  It is based on the reciprocal cell, the dual of the cell,
     in which reciprocal cell edges are derived from direct cell faces:
     
        a* = bc sin(α)/V  b* = ac sin(β)/V  c* = ab sin(γ)/V
        cos(α*) = (cos(β)  cos(γ) - cos(α))/(sin(β)  sin(γ))
        cos(β*)  = (cos(γ) cos(γ) - cos(β) )/(sin(α) sin(γ))
        cos(γ*) = (cos(α) cos(β)  - cos(γ))/(sin(α) sin(β))
        V = abc √(1 - cos(α)2 -  cos(β)2 - cos(γ)2 
                           + 2 cos(α) cos(β) cos(γ) )
     
     In this form the dimensions of the reciprocal lattice are in reciprocal
     Ångstroms (&A-1).  A dimensionless form can be obtained by 
     multiplying by the wavelength.  Reflections are commonly indexed against
     this coordinate system as (h, k, l) triples.
     
     
     References:
     
     Drenth, J., "Introduction to basic crystallography." chapter
     2.1 in Rossmann, M. G. and Arnold, E. "Crystallography of 
     biological macromolecules", Volume F of the IUCr's "International 
     tables for crystallography", Kluwer, Dordrecht 2001, pp 44 -- 63

     Leslie, A. G. W. and Powell, H. (2004). MOSFLM v6.11.
     MRC Laboratory of Molecular Biology, Hills Road, Cambridge, England.
     http://www.CCP4.ac.uk/dist/X-windows/Mosflm/.
     
     Stout, G. H. and Jensen, L. H., "X-ray structure determination",
     2nd ed., Wiley, New York, 1989, 453 pp.
     
     __, "PROTEIN DATA BANK ATOMIC COORDINATE AND BIBLIOGRAPHIC ENTRY
     FORMAT DESCRIPTION," Brookhaven National Laboratory, February 1992.
;
    _category.id                   axis
    _category.mandatory_code       no
     loop_
    _category_key.name          '_axis.id'
                                '_axis.equipment'
     loop_
    _category_group.id           'inclusive_group'
                                 'axis_group'
                                 'diffrn_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;       Example 1 -

        This example shows the axis specification of the axes of a kappa-
        geometry goniometer [see Stout, G. H. & Jensen, L. H. (1989). X-ray
        structure determination. A practical
        guide, 2nd ed. p. 134. New York: Wiley Interscience].

        There are three axes specified, and no offsets.  The outermost axis,
        omega, is pointed along the X axis.  The next innermost axis, kappa,
        is at a 50 degree angle to the X axis, pointed away from the source.
        The innermost axis, phi, aligns with the X axis when omega and
        phi are at their zero points.  If T-omega, T-kappa and T-phi
        are the transformation matrices derived from the axis settings,
        the complete transformation would be:
            X' = (T-omega) (T-kappa) (T-phi) X
;
;
         loop_
        _axis.id
        _axis.type
        _axis.equipment
        _axis.depends_on
        _axis.vector[1] _axis.vector[2] _axis.vector[3]
        omega rotation goniometer     .    1        0        0
        kappa rotation goniometer omega    -.64279  0       -.76604
        phi   rotation goniometer kappa    1        0        0
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;       Example 2 -

        This example shows the axis specification of the axes of a
        detector, source and gravity.  The order has been changed as a
        reminder that the ordering of presentation of tokens is not
        significant.  The centre of rotation of the detector has been taken
        to be 68 millimetres in the direction away from the source.
;
;
        loop_
        _axis.id
        _axis.type
        _axis.equipment
        _axis.depends_on
        _axis.vector[1] _axis.vector[2] _axis.vector[3]
        _axis.offset[1] _axis.offset[2] _axis.offset[3]
        source       .        source     .       0     0     1   . . .
        gravity      .        gravity    .       0    -1     0   . . .
        tranz     translation detector rotz      0     0     1   0 0 -68
        twotheta  rotation    detector   .       1     0     0   . . .
        roty      rotation    detector twotheta  0     1     0   0 0 -68
        rotz      rotation    detector roty      0     0     1   0 0 -68
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;       Example 3 -

        This example show the axis specification of the axes for a map,
        using fractional coordinates.  Each cell edge has been divided
        into a grid of 50 divisions in the ARRAY_STRUCTURE_LIST_AXIS 
        category.  The map is using only the first octant of the grid
        in the ARRAY_STRUCTURE_LIST category.

        The fastest changing axis is the gris along A, then along B,
        and the slowest is along C. 
        
        The map sampling is being done in the middle of each grid
        division
        
;
;
        loop_
        _axis.id
        _axis.system
        _axis.vector[1] _axis.vector[2] _axis.vector[3]
        CELL_A_AXIS    fractional       1 0 0
        CELL_B_AXIS    fractional       0 1 0
        CELL_C_AXIS    fractional       0 0 1
        
        loop_
        _array_structure_list.array_id
        _array_structure_list.index
        _array_structure_list.dimension
        _array_structure_list.precedence
        _array_structure_list.direction
        _array_structure_list.axis_id
        MAP 1 25 1 increasing CELL_A_AXIS
        MAP 1 25 2 increasing CELL_B_AXIS
        MAP 1 25 3 increasing CELL_C_AXIS
        
        loop_
        _array_structure_list_axis.axis_id
        _array_structure_list_axis.fract_displacement
        _array_structure_list_axis.fract_displacement_increment
        CELL_A_AXIS 0.01 0.02
        CELL_B_AXIS 0.01 0.02
        CELL_C_AXIS 0.01 0.02

        
        
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;       Example 4 -

        This example show the axis specification of the axes for a map,
        this time as orthogonal Angstroms, using the same coordinate system 
        as for the atomic coordinates.  The map is sampling every 1.5
        Angstroms (1.5e-7 millimeters) in a map segment 37.5 Angstroms on 
        a side.
        
;
;
        loop_
        _axis.id
        _axis.system
        _axis.vector[1] _axis.vector[2] _axis.vector[3]
        X    orthogonal       1 0 0
        Y    orthogonal       0 1 0
        Z    orthogonal       0 0 1
        
                loop_
        _array_structure_list.array_id
        _array_structure_list.index
        _array_structure_list.dimension
        _array_structure_list.precedence
        _array_structure_list.direction
        _array_structure_list.axis_id
        MAP 1 25 1 increasing X
        MAP 2 25 2 increasing Y
        MAP 3 25 3 increasing Z
        
        loop_
        _array_structure_list_axis.axis_id
        _array_structure_list_axis.displacement
        _array_structure_list_axis.displacement_increment
        X 7.5e-8 1.5e-7
        Y 7.5e-8 1.5e-7
        Z 7.5e-8 1.5e-7


;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_


save__axis.depends_on
    _item_description.description
;             The value of _axis.depends_on specifies the next outermost
              axis upon which this axis depends.

              This item is a pointer to _axis.id in the same category.
;
    _item.name                      '_axis.depends_on'
    _item.category_id                 axis
    _item.mandatory_code              no

     save_


save__axis.equipment
    _item_description.description
;             The value of  _axis.equipment specifies the type of
              equipment using the axis:  'goniometer', 'detector',
              'gravity', 'source' or 'general'.
;
    _item.name                      '_axis.equipment'
    _item.category_id                 axis
    _item.mandatory_code              no
    _item_type.code                   ucode
    _item_default.value               general
     loop_
    _item_enumeration.value
    _item_enumeration.detail   goniometer
                              'equipment used to orient or position samples'
                               detector
                              'equipment used to detect reflections'
                               general
                              'equipment used for general purposes'
                               gravity
                              'axis specifying the downward direction'
                               source
                              'axis specifying the direction sample to source'

     save_


save__axis.offset[1]
    _item_description.description
;              The [1] element of the three-element vector used to specify
               the offset to the base of a rotation or translation axis.

               The vector is specified in millimetres.
;
    _item.name                  '_axis.offset[1]'
    _item.category_id             axis
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
    _item_units.code              millimetres
     save_


save__axis.offset[2]
    _item_description.description
;              The [2] element of the three-element vector used to specify
               the offset to the base of a rotation or translation axis.

               The vector is specified in millimetres.
;
    _item.name                  '_axis.offset[2]'
    _item.category_id             axis
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
    _item_units.code              millimetres
     save_


save__axis.offset[3]
    _item_description.description
;              The [3] element of the three-element vector used to specify
               the offset to the base of a rotation or translation axis.

               The vector is specified in millimetres.
;
    _item.name                  '_axis.offset[3]'
    _item.category_id             axis
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
    _item_units.code              millimetres
     save_


save__axis.id
    _item_description.description
;             The value of _axis.id must uniquely identify
              each axis relevant to the experiment.  Note that multiple
              pieces of equipment may share the same axis (e.g. a twotheta
              arm), so the category key for AXIS also includes the
              equipment.
;
    loop_
    _item.name
    _item.category_id
    _item.mandatory_code
         '_axis.id'                         axis                    yes
         '_array_structure_list_axis.axis_id'
                                            array_structure_list_axis
                                                                    yes
         '_diffrn_detector_axis.axis_id'    diffrn_detector_axis    yes
         '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes
         '_diffrn_scan_axis.axis_id'        diffrn_scan_axis        yes
         '_diffrn_scan_frame_axis.axis_id'  diffrn_scan_frame_axis  yes

    _item_type.code               code
     loop_
    _item_linked.child_name
    _item_linked.parent_name
         '_axis.depends_on'                   '_axis.id'
         '_array_structure_list_axis.axis_id' '_axis.id'
         '_diffrn_detector_axis.axis_id'      '_axis.id'
         '_diffrn_measurement_axis.axis_id'   '_axis.id'
         '_diffrn_scan_axis.axis_id'          '_axis.id'
         '_diffrn_scan_frame_axis.axis_id'    '_axis.id'

     save_

save__axis.system
    _item_description.description
;             The value of  _axis.system specifies the coordinate
              system used to define the axis: 'laboratory', 'direct', 'orthogonal',
              'reciprocal' or 'abstract'.
;
    _item.name                      '_axis.system'
    _item.category_id                 axis
    _item.mandatory_code              no
    _item_type.code                   ucode
    _item_default.value               laboratory
     loop_
    _item_enumeration.value
    _item_enumeration.detail   

laboratory
;  the axis is referenced to the imgCIF standard laboratory Cartesian
   coordinate system
;

direct
;  the axis is referenced to the direct lattice
;

orthogonal
;  the axis is referenced to the cell Cartesian orthogonal coordinates
;

reciprocal
;  the axis is referenced to the reciprocal lattice
;

abstract
;  the axis is referenced to abstract Cartesian cooridinate system
;

     save_


save__axis.type
    _item_description.description
;             The value of _axis.type specifies the type of
              axis:  'rotation' or 'translation' (or 'general' when
              the type is not relevant, as for gravity).
;
    _item.name                      '_axis.type'
    _item.category_id                 axis
    _item.mandatory_code              no
    _item_type.code                   ucode
    _item_default.value               general
     loop_
    _item_enumeration.value
    _item_enumeration.detail      rotation
                                 'right-handed axis of rotation'
                                  translation
                                 'translation in the direction of the axis'
                                  general
                                 'axis for which the type is not relevant'

     save_


save__axis.vector[1]
    _item_description.description
;              The [1] element of the three-element vector used to specify
               the direction of a rotation or translation axis.
               The vector should be normalized to be a unit vector and
               is dimensionless.
;
    _item.name                  '_axis.vector[1]'
    _item.category_id             axis
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
     save_

save__axis.vector[2]
    _item_description.description
;              The [2] element of the three-element vector used to specify
               the direction of a rotation or translation axis.
               The vector should be normalized to be a unit vector and
               is dimensionless.
;
    _item.name                  '_axis.vector[2]'
    _item.category_id             axis
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
     save_

save__axis.vector[3]
    _item_description.description
;              The [3] element of the three-element vector used to specify
               the direction of a rotation or translation axis.
               The vector should be normalized to be a unit vector and
               is dimensionless.
;
    _item.name                  '_axis.vector[3]'
    _item.category_id             axis
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
     save_



#####################
# DIFFRN_DATA_FRAME #
#####################


save_DIFFRN_DATA_FRAME
    _category.description
;             Data items in the DIFFRN_DATA_FRAME category record
              the details about each frame of data.

              The items in this category were previously in a
              DIFFRN_FRAME_DATA category, which is now deprecated.
              The items from the old category are provided
              as aliases but should not be used for new work.
;
    _category.id                   diffrn_data_frame
    _category.mandatory_code       no
     loop_
    _category_key.name             '_diffrn_data_frame.id'
                                   '_diffrn_data_frame.detector_element_id'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;   Example 1 - A frame containing data from 4 frame elements.
                Each frame element has a common array configuration
                'array_1' described in ARRAY_STRUCTURE and related
                categories.  The data for each detector element are
                stored in four groups of binary data in the
                ARRAY_DATA category, linked by the array_id and
                binary_id.
;
;
        loop_
        _diffrn_data_frame.id
        _diffrn_data_frame.detector_element_id
        _diffrn_data_frame.array_id
        _diffrn_data_frame.binary_id
        frame_1   d1_ccd_1  array_1  1
        frame_1   d1_ccd_2  array_1  2
        frame_1   d1_ccd_3  array_1  3
        frame_1   d1_ccd_4  array_1  4
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    save_


save__diffrn_data_frame.array_id
    _item_description.description
;             This item is a pointer to _array_structure.id in the
              ARRAY_STRUCTURE category.
;
    _item.name                  '_diffrn_data_frame.array_id'
    _item.category_id             diffrn_data_frame
    _item.mandatory_code          implicit
    _item_aliases.alias_name    '_diffrn_frame_data.array_id'
    _item_aliases.dictionary      cif_img.dic
    _item_aliases.version         1.0
    _item_type.code               code
     save_


save__diffrn_data_frame.binary_id
    _item_description.description
;             This item is a pointer to _array_data.binary_id in the
              ARRAY_DATA category.
;
    _item.name                  '_diffrn_data_frame.binary_id'
    _item.category_id             diffrn_data_frame
    _item.mandatory_code          implicit
    _item_aliases.alias_name    '_diffrn_frame_data.binary_id'
    _item_aliases.dictionary      cif_img.dic
    _item_aliases.version         1.0
    _item_type.code               int
     save_


save__diffrn_data_frame.center_fast
     _item_description.description
;             The value of _diffrn_data_frame.center_fast is 
              the fast index axis beam center position relative to the detector
              element face in the units specified in the data item
              '_diffrn_data_frame.center_units' along the fast
              axis of the detector from the center of the first pixel to 
              the point at which the Z-axis (which should be colinear with the
              beam) intersects the face of the detector, if in fact is does.
              At the time of the measurement the current setting of detector
              positioner given frame are used.

              It is important to note that for measurements in millimetres,
              the sense of the axis is used, rather than the sign of the 
              pixel-to-pixel increments.

;
     _item.name '_diffrn_data_frame.center_fast'
     _item.category_id             diffrn_data_frame
     _item.mandatory_code          no
     _item_type.code               float

     save_


save__diffrn_data_frame.center_slow
     _item_description.description
;             The value of _diffrn_data_frame.center_slow is
              the slow index axis beam center position relative to the detector
              element face in the units specified in the data item
              '_diffrn_data_frame.center_units' along the slow
              axis of the detector from the center of the first pixel to 
              the point at which the Z-axis (which should be colinear with the
              beam) intersects the face of the detector, if in fact is does.
              At the time of the measurement the current setting of detector
              positioner given frame are used.

              It is important to note that the sense of the axis is used,
              rather than the sign of the pixel-to-pixel increments.

;
     _item.name '_diffrn_data_frame.center_slow'
     _item.category_id             diffrn_data_frame
     _item.mandatory_code          no
     _item_type.code               float

     save_


save__diffrn_data_frame.center_units
     _item_description.description
;             The value of _diffrn_data_frame.center_units
              specifies the units in which the values of 
              '_diffrn_data_frame.center_fast' and
              '_diffrn_data_frame.center_slow'
              are presented.  The default is 'mm' for millimetres.  The 
              alternatives are 'pixels' and 'bins'.  In all cases the
              center distances are measured from the center of the
              first pixel, i.e. in a 2x2 binning, the measuring origin
              is offset from the centers of the bins by one half pixel
              towards the first pixel.
              
              If 'bins' is specified, the data in
                  '_array_intensities.pixel_fast_bin_size',
                  '_array_intensities.pixel_slow_bin_size', and
                  '_array_intensities.pixel_binning_method'
              is used to define the binning scheme.


;
     _item.name '_diffrn_data_frame.center_units'
     _item.category_id             diffrn_data_frame
     _item.mandatory_code          no
     _item_type.code               code
      loop_
    _ item_enumeration.value
    _ item_enumeration.detail
                                   mm        'millimetres'
                                   pixels    'detector pixels'
                                   bins      'detector bins'

     save_




save__diffrn_data_frame.detector_element_id
    _item_description.description
;              This item is a pointer to _diffrn_detector_element.id
               in the DIFFRN_DETECTOR_ELEMENT category.
;
    _item.name                  '_diffrn_data_frame.detector_element_id'
    _item.category_id             diffrn_data_frame
    _item.mandatory_code          yes
    _item_aliases.alias_name    '_diffrn_frame_data.detector_element_id'
    _item_aliases.dictionary      cif_img.dic
    _item_aliases.version         1.0
    _item_type.code               code
     save_


save__diffrn_data_frame.id
    _item_description.description
;             The value of _diffrn_data_frame.id must uniquely identify
              each complete frame of data.
;
     loop_
    _item.name
    _item.category_id
    _item.mandatory_code
           '_diffrn_data_frame.id'        diffrn_data_frame  yes
           '_diffrn_refln.frame_id'       diffrn_refln       yes
           '_diffrn_scan.frame_id_start'  diffrn_scan        yes
           '_diffrn_scan.frame_id_end'    diffrn_scan        yes
           '_diffrn_scan_frame.frame_id'  diffrn_scan_frame  yes
           '_diffrn_scan_frame_axis.frame_id'
                                          diffrn_scan_frame_axis
                                                             yes
    _item_aliases.alias_name    '_diffrn_frame_data.id'
    _item_aliases.dictionary      cif_img.dic
    _item_aliases.version         1.0
    _item_type.code               code
     loop_
    _item_linked.child_name
    _item_linked.parent_name
           '_diffrn_refln.frame_id'        '_diffrn_data_frame.id'
           '_diffrn_scan.frame_id_start'   '_diffrn_data_frame.id'
           '_diffrn_scan.frame_id_end'     '_diffrn_data_frame.id'
           '_diffrn_scan_frame.frame_id'   '_diffrn_data_frame.id'
           '_diffrn_scan_frame_axis.frame_id'
                                           '_diffrn_data_frame.id'
     save_


save__diffrn_data_frame.details
     _item_description.description
;              The value of _diffrn_data_frame.details should give a
               description of special aspects of each frame of data.

               This is an appropriate location in which to record
               information from vendor headers as presented in those
               headers, but it should never be used as a substitute
               for providing the fully parsed information within
               the appropriate imgCIF/CBF categories.
               
               Normally, when a conversion from a miniCBF has been done
               the data from '_array_data.header_convention'
               should be transferred to this data item and 
               '_array_data.header_convention'
               should be removed.
;
    _item.name                  '_diffrn_data_frame.details'
    _item.category_id             diffrn_data_frame
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_frame_data.details'
    _item_aliases.dictionary      cif_img.dic
    _item_aliases.version         1.4
    _item_type.code               text
     loop_
    _item_examples.case
    _item_examples.detail
;
 HEADER_BYTES = 512;
 DIM = 2;
 BYTE_ORDER = big_endian;
 TYPE = unsigned_short;
 SIZE1 = 3072;
 SIZE2 = 3072;
 PIXEL_SIZE = 0.102588;
 BIN = 2x2;
 DETECTOR_SN = 901;
 TIME = 29.945155;
 DISTANCE = 200.000000;
 PHI = 85.000000;
 OSC_START = 85.000000;
 OSC_RANGE = 1.000000;
 WAVELENGTH = 0.979381;
 BEAM_CENTER_X = 157.500000;
 BEAM_CENTER_Y = 157.500000;
 PIXEL SIZE = 0.102588;
 OSCILLATION RANGE = 1;
 EXPOSURE TIME = 29.9452;
 TWO THETA = 0;
 BEAM CENTRE = 157.5 157.5;
;
;               Example of header information extracted from an ADSC Quantum
                315 detector header by CBFlib_0.7.6.  Image provided by Chris
                Nielsen of ADSC from a data collection at SSRL beamline 1-5.
;
      save_



##########################################################################
#  The following is a restatement of the mmCIF DIFFRN_DETECTOR,          #
#  DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for      #
#  the CBF/imgCIF extensions                                             #
##########################################################################

###################
# DIFFRN_DETECTOR #
###################


save_DIFFRN_DETECTOR
    _category.description
;              Data items in the DIFFRN_DETECTOR category describe the
               detector used to measure the scattered radiation, including
               any analyser and post-sample collimation.
;
    _category.id                  diffrn_detector
    _category.mandatory_code      no
     loop_
    _category_key.name          '_diffrn_detector.diffrn_id'
                                '_diffrn_detector.id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;   Example 1 - based on PDB entry 5HVP and laboratory records for the
                structure corresponding to PDB entry 5HVP.
;
;
    _diffrn_detector.diffrn_id             'd1'
    _diffrn_detector.detector              'multiwire'
    _diffrn_detector.type                  'Siemens'
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_


save__diffrn_detector.details
    _item_description.description
;              A description of special aspects of the radiation detector.
;
    _item.name                  '_diffrn_detector.details'
    _item.category_id             diffrn_detector
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_detector_details'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code                   text
    _item_examples.case        'slow mode'
     save_


save__diffrn_detector.detector
    _item_description.description
;              The general class of the radiation detector.
;
    _item.name                  '_diffrn_detector.detector'
    _item.category_id             diffrn_detector
    _item.mandatory_code          no
     loop_
    _item_aliases.alias_name
    _item_aliases.dictionary
    _item_aliases.version       '_diffrn_radiation_detector'
                                  cifdic.c91
                                  1.0
                                '_diffrn_detector'
                                  cif_core.dic
                                  2.0
    _item_type.code               text
     loop_
    _item_examples.case          'photographic film'
                                 'scintillation counter'
                                 'CCD plate'
                                 'BF~3~ counter'
     save_


save__diffrn_detector.diffrn_id
    _item_description.description
;              This data item is a pointer to _diffrn.id in the DIFFRN
               category.

               The value of _diffrn.id uniquely defines a set of
               diffraction data.
;
    _item.name                  '_diffrn_detector.diffrn_id'
    _item.mandatory_code          yes
    _item_type.code               code
     save_


save__diffrn_detector.dtime
    _item_description.description
;              The deadtime in microseconds of the detector(s) used to
               measure the diffraction intensities.
;
    _item.name                  '_diffrn_detector.dtime'
    _item.category_id             diffrn_detector
    _item.mandatory_code          no
     loop_
    _item_aliases.alias_name
    _item_aliases.dictionary
    _item_aliases.version       '_diffrn_radiation_detector_dtime'
                                  cifdic.c91
                                  1.0
                                '_diffrn_detector_dtime'
                                  cif_core.dic
                                  2.0
     loop_
    _item_range.maximum
    _item_range.minimum            .    0.0
                                  0.0   0.0
    _item_type.code               float
    _item_units.code              microseconds
     save_


save__diffrn_detector.id
    _item_description.description
;              The value of _diffrn_detector.id must uniquely identify
               each detector used to collect each diffraction data set.

               If the value of _diffrn_detector.id is not given, it is
               implicitly equal to the value of
               _diffrn_detector.diffrn_id.
;
     loop_
    _item.name
    _item.category_id
    _item.mandatory_code
             '_diffrn_detector.id'         diffrn_detector       implicit
             '_diffrn_detector_axis.detector_id'
                                           diffrn_detector_axis       yes
     loop_
    _item_linked.child_name
    _item_linked.parent_name
             '_diffrn_detector_axis.detector_id'
                                         '_diffrn_detector.id'

    _item_type.code               code
     save_


save__diffrn_detector.number_of_axes
    _item_description.description
;              The value of _diffrn_detector.number_of_axes gives the
               number of axes of the positioner for the detector identified
               by _diffrn_detector.id.

               The word 'positioner' is a general term used in
               instrumentation design for devices that are used to change
               the positions of portions of apparatus by linear
               translation, rotation or combinations of such motions.

               Axes which are used to provide a coordinate system for the
               face of an area detetctor should not be counted for this
               data item.

               The description of each axis should be provided by entries
               in DIFFRN_DETECTOR_AXIS.
;
    _item.name                  '_diffrn_detector.number_of_axes'
    _item.category_id             diffrn_detector
    _item.mandatory_code          no
     loop_
    _item_range.maximum
    _item_range.minimum           .   1
                                  1   1
    _item_type.code               int
     save_


save__diffrn_detector.type
    _item_description.description
;              The make, model or name of the detector device used.
;
    _item.name                  '_diffrn_detector.type'
    _item.category_id             diffrn_detector
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_detector_type'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
     save_


########################
# DIFFRN_DETECTOR_AXIS #
########################


save_DIFFRN_DETECTOR_AXIS
    _category.description
;    Data items in the DIFFRN_DETECTOR_AXIS category associate
     axes with detectors.
;
    _category.id                   diffrn_detector_axis
    _category.mandatory_code       no
     loop_
    _category_key.name          '_diffrn_detector_axis.detector_id'
                                '_diffrn_detector_axis.axis_id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     save_


save__diffrn_detector_axis.axis_id
    _item_description.description
;              This data item is a pointer to _axis.id in
               the AXIS category.
;
    _item.name                  '_diffrn_detector_axis.axis_id'
    _item.category_id             diffrn_detector_axis
    _item.mandatory_code          yes
    _item_type.code               code
     save_


save__diffrn_detector_axis.detector_id
    _item_description.description
;              This data item is a pointer to _diffrn_detector.id in
               the DIFFRN_DETECTOR category.

               This item was previously named _diffrn_detector_axis.id
               which is now a deprecated name.  The old name is
               provided as an alias but should not be used for new work.
;
    _item.name                  '_diffrn_detector_axis.detector_id'
    _item.category_id             diffrn_detector_axis
    _item.mandatory_code          yes
    _item_aliases.alias_name    '_diffrn_detector_axis.id'
    _item_aliases.dictionary      cif_img.dic
    _item_aliases.version         1.0
    _item_type.code               code
     save_


###########################
# DIFFRN_DETECTOR_ELEMENT #
###########################


save_DIFFRN_DETECTOR_ELEMENT
    _category.description
;             Data items in the DIFFRN_DETECTOR_ELEMENT category record
              the details about spatial layout and other characteristics
              of each element of a detector which may have multiple elements.

              In most cases, giving more detailed information
              in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS
              is preferable to simply providing the centre of the
              detector element.
;
    _category.id                   diffrn_detector_element
    _category.mandatory_code       no
     loop_
    _category_key.name             '_diffrn_detector_element.id'
                                   '_diffrn_detector_element.detector_id'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;       Example 1 - Detector d1 is composed of four CCD detector elements,
        each 200 mm by 200 mm, arranged in a square, in the pattern

                   1     2
                      *
                   3     4

        Note that the beam centre is slightly displaced from each of the
        detector elements, just beyond the lower right corner of 1,
        the lower left corner of 2, the upper right corner of 3 and
        the upper left corner of 4.  For each element, the detector
        face coordiate system, is assumed to have the fast axis
        running from left to right and the slow axis running from
        top to bottom with the origin at the top left corner.
;
;
        loop_
        _diffrn_detector_element.detector_id
        _diffrn_detector_element.id
        _diffrn_detector_element.reference_center_fast
        _diffrn_detector_element.reference_center_slow
        _diffrn_detector_element.reference_center_units
        d1     d1_ccd_1  201.5 201.5  mm
        d1     d1_ccd_2  -1.8  201.5  mm
        d1     d1_ccd_3  201.6  -1.4  mm
        d1     d1_ccd_4  -1.7   -1.5  mm
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    save_



save__diffrn_detector_element.id
    _item_description.description
;             The value of _diffrn_detector_element.id must uniquely
              identify each element of a detector.
;
     loop_
    _item.name
    _item.category_id
    _item.mandatory_code
           '_diffrn_detector_element.id'
           diffrn_detector_element
           yes
    _item_type.code               code
     loop_
    _item_linked.child_name
    _item_linked.parent_name
           '_diffrn_data_frame.detector_element_id'
           '_diffrn_detector_element.id'

     save_


save__diffrn_detector_element.detector_id
    _item_description.description
;              This item is a pointer to _diffrn_detector.id
               in the DIFFRN_DETECTOR category.
;
    _item.name                  '_diffrn_detector_element.detector_id'
    _item.category_id             diffrn_detector_element
    _item.mandatory_code          yes
    _item_type.code               code
     save_

save__diffrn_detector_element.reference_center_fast
     _item_description.description
;             The value of _diffrn_detector_element.reference_center_fast is 
              the fast index axis beam center position relative to the detector
              element face in the units specified in the data item
              '_diffrn_detector_element.reference_center_units' along the fast
              axis of the detector from the center of the first pixel to 
              the point at which the Z-axis (which should be colinear with the 
              beam) intersects the face of the detector, if in fact is does.   
              At the time of the measurement all settings of the detector
              positioner should be at their reference settings.  If more than 
              one reference setting has been used the value given whould be 
              representive of the beam center as determined from the ensemble 
              of settings.

              It is important to note that for measurements in millimetres,
              the sense of the axis is used, rather than the sign of the 
              pixel-to-pixel increments.

;
     _item.name '_diffrn_detector_element.reference_center_fast'
     _item.category_id             diffrn_detector_element
     _item.mandatory_code          no
     _item_type.code               float

     save_


save__diffrn_detector_element.reference_center_slow
     _item_description.description
;             The value of _diffrn_detector_element.reference_center_slow is
              the slow index axis beam center position relative to the detector
              element face in the units specified in the data item
              '_diffrn_detector_element.reference_center_units' along the slow
              axis of the detector from the center of the first pixel to 
              the point at which the Z-axis (which should be colinear with the
              beam) intersects the face of the detector, if in fact is does.
              At the time of the measurement all settings of the detector
              positioner should be at their reference settings.  If more than
              one reference setting has been used the value givien whould be 
              representive of the beam center as determined from the ensemble
              of settings.

              It is important to note that the sense of the axis is used,
              rather than the sign of the pixel-to-pixel increments.

;
     _item.name '_diffrn_detector_element.reference_center_slow'
     _item.category_id             diffrn_detector_element
     _item.mandatory_code          no
     _item_type.code               float

     save_


save__diffrn_detector_element.reference_center_units
     _item_description.description
;             The value of _diffrn_detector_element.reference_center_units
              specifies the units in which the values of 
              '_diffrn_detector_element.reference_center_fast' and
              '_diffrn_detector_element.reference_center_slow'
              are presented.  The default is 'mm' for millimetres.  The 
              alternatives are 'pixels' and 'bins'.  In all cases the
              center distances are measured from the center of the
              first pixel, i.e. in a 2x2 binning, the measuring origin
              is offset from the centers of the bins by one half pixel
              towards the first pixel.
              
              If 'bins' is specified, the data in
                  '_array_intensities.pixel_fast_bin_size',
                  '_array_intensities.pixel_slow_bin_size', and
                  '_array_intensities.pixel_binning_method'
              is used to define the binning scheme.


;
     _item.name '_diffrn_detector_element.reference_center_units'
     _item.category_id             diffrn_detector_element
     _item.mandatory_code          no
     _item_type.code               code
      loop_
    _ item_enumeration.value
    _ item_enumeration.detail
                                   mm        'millimetres'
                                   pixels    'detector pixels'
                                   bins      'detector bins'

     save_


########################
## DIFFRN_MEASUREMENT ##
########################


save_DIFFRN_MEASUREMENT
    _category.description
;              Data items in the DIFFRN_MEASUREMENT category record details
               about the device used to orient and/or position the crystal
               during data measurement and the manner in which the
               diffraction data were measured.
;
    _category.id                  diffrn_measurement
    _category.mandatory_code      no
     loop_
    _category_key.name          '_diffrn_measurement.device'
                                '_diffrn_measurement.diffrn_id'
                                '_diffrn_measurement.id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;    Example 1 - based on PDB entry 5HVP and laboratory records for the
                 structure corresponding to PDB entry 5HVP
;
;
    _diffrn_measurement.diffrn_id          'd1'
    _diffrn_measurement.device             '3-circle camera'
    _diffrn_measurement.device_type        'Supper model X'
    _diffrn_measurement.device_details     'none'
    _diffrn_measurement.method             'omega scan'
    _diffrn_measurement.details
    ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector
      angle 22.5 degrees
    ;
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;     Example 2 - based on data set TOZ of Willis, Beckwith & Tozer
                  [Acta Cryst. (1991), C47, 2276-2277].
;
;
    _diffrn_measurement.diffrn_id       's1'
    _diffrn_measurement.device_type     'Philips PW1100/20 diffractometer'
    _diffrn_measurement.method          'theta/2theta (\q/2\q)'
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_


save__diffrn_measurement.device
    _item_description.description
;              The general class of goniometer or device used to support
               and orient the specimen.

               If the value of _diffrn_measurement.device is not given,
               it is implicitly equal to the value of
               _diffrn_measurement.diffrn_id.

               Either _diffrn_measurement.device or
               _diffrn_measurement.id may be used to link to other
               categories.  If the experimental setup admits multiple
               devices, then _diffrn_measurement.id is used to provide
               a unique link.
;
     loop_
    _item.name
    _item.category_id
    _item.mandatory_code
             '_diffrn_measurement.device'  diffrn_measurement      implicit
             '_diffrn_measurement_axis.measurement_device'
                                           diffrn_measurement_axis implicit
     loop_
    _item_linked.child_name
    _item_linked.parent_name
             '_diffrn_measurement_axis.measurement_device'
                                         '_diffrn_measurement.device'
    _item_aliases.alias_name    '_diffrn_measurement_device'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
     loop_
    _item_examples.case          '3-circle camera'
                                 '4-circle camera'
                                 'kappa-geometry camera'
                                 'oscillation camera'
                                 'precession camera'
     save_


save__diffrn_measurement.device_details
    _item_description.description
;              A description of special aspects of the device used to
               measure the diffraction intensities.
;
    _item.name                  '_diffrn_measurement.device_details'
    _item.category_id             diffrn_measurement
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_measurement_device_details'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
    _item_examples.case
;                                 commercial goniometer modified locally to
                                  allow for 90\% \t arc
;
     save_


save__diffrn_measurement.device_type
    _item_description.description
;              The make, model or name of the measurement device
               (goniometer) used.
;
    _item.name                  '_diffrn_measurement.device_type'
    _item.category_id             diffrn_measurement
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_measurement_device_type'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
     loop_
    _item_examples.case          'Supper model q'
                                 'Huber model r'
                                 'Enraf-Nonius model s'
                                 'home-made'
     save_


save__diffrn_measurement.diffrn_id
    _item_description.description
;              This data item is a pointer to _diffrn.id in the DIFFRN
               category.
;
    _item.name                  '_diffrn_measurement.diffrn_id'
    _item.mandatory_code          yes
    _item_type.code               code
     save_


save__diffrn_measurement.details
    _item_description.description
;              A description of special aspects of the intensity
               measurement.
;
    _item.name                  '_diffrn_measurement.details'
    _item.category_id             diffrn_measurement
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_measurement_details'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
    _item_examples.case
;                                 440 frames, 0.20 degrees, 150 sec, detector
                                  distance 12 cm, detector angle 22.5 degrees
;
     save_


save__diffrn_measurement.id
    _item_description.description
;              The value of _diffrn_measurement.id must uniquely identify
               the set of mechanical characteristics of the device used to
               orient and/or position the sample used during the collection
               of each diffraction data set.

               If the value of _diffrn_measurement.id is not given, it is
               implicitly equal to the value of
               _diffrn_measurement.diffrn_id.

               Either _diffrn_measurement.device or
               _diffrn_measurement.id may be used to link to other
               categories.  If the experimental setup admits multiple
               devices, then _diffrn_measurement.id is used to provide
               a unique link.
;
     loop_
    _item.name
    _item.category_id
    _item.mandatory_code
             '_diffrn_measurement.id'      diffrn_measurement      implicit
             '_diffrn_measurement_axis.measurement_id'
                                           diffrn_measurement_axis implicit
     loop_
    _item_linked.child_name
    _item_linked.parent_name
             '_diffrn_measurement_axis.measurement_id'
                                         '_diffrn_measurement.id'

    _item_type.code               code
     save_


save__diffrn_measurement.method
    _item_description.description
;              Method used to measure intensities.
;
    _item.name                  '_diffrn_measurement.method'
    _item.category_id             diffrn_measurement
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_measurement_method'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
    _item_examples.case
      'profile data from theta/2theta (\q/2\q) scans'
     save_


save__diffrn_measurement.number_of_axes
    _item_description.description
;              The value of _diffrn_measurement.number_of_axes gives the
               number of axes of the positioner for the goniometer or
               other sample orientation or positioning device identified
               by _diffrn_measurement.id.

               The description of the axes should be provided by entries in
               DIFFRN_MEASUREMENT_AXIS.
;
    _item.name                  '_diffrn_measurement.number_of_axes'
    _item.category_id             diffrn_measurement
    _item.mandatory_code          no
     loop_
    _item_range.maximum
    _item_range.minimum           .   1
                                  1   1
    _item_type.code               int
     save_


#                  _diffrn_measurement.sample_detector_distance
#                  _diffrn_measurement.sample_detector_voffset

save__diffrn_measurement.sample_detector_distance
    _item_description.description
;              The value of _diffrn_measurement.sample_detector_distance gives the
               unsigned distance in millimetres from the sample to the 
               detector along the beam.
;
    _item.name                  '_diffrn_measurement.sample_detector_distance'
    _item.category_id             diffrn_measurement
    _item.mandatory_code          no
     loop_
    _item_range.maximum
    _item_range.minimum           .   0.0
    _item_type.code               float
    _item_units.code              mm
     save_

save__diffrn_measurement.sample_detector_voffset
    _item_description.description
;              The value of _diffrn_measurement.sample_detector_voffset gives the
               signed distance in millimetres in the vertical
               direction (positive for up) from the center of
               the beam to the center of the detector. 
;
    _item.name                  '_diffrn_measurement.sample_detector_voffset'
    _item.category_id             diffrn_measurement
    _item.mandatory_code          no
     loop_
    _item_range.maximum
    _item_range.minimum           .   .
                                  .   .
    _item_type.code               float
    _item_units.code              mm
     save_


save__diffrn_measurement.specimen_support
    _item_description.description
;              The physical device used to support the crystal during data
               collection.
;
    _item.name                  '_diffrn_measurement.specimen_support'
    _item.category_id             diffrn_measurement
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_measurement_specimen_support'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
     loop_
    _item_examples.case          'glass capillary'
                                 'quartz capillary'
                                 'fiber'
                                 'metal loop'
     save_


###########################
# DIFFRN_MEASUREMENT_AXIS #
###########################


save_DIFFRN_MEASUREMENT_AXIS
    _category.description
;    Data items in the DIFFRN_MEASUREMENT_AXIS category associate
     axes with goniometers.
;
    _category.id                   diffrn_measurement_axis
    _category.mandatory_code       no
     loop_
    _category_key.name
                              '_diffrn_measurement_axis.measurement_device'
                                '_diffrn_measurement_axis.measurement_id'
                                '_diffrn_measurement_axis.axis_id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     save_


save__diffrn_measurement_axis.axis_id
    _item_description.description
;              This data item is a pointer to _axis.id in
               the AXIS category.
;
    _item.name                  '_diffrn_measurement_axis.axis_id'
    _item.category_id             diffrn_measurement_axis
    _item.mandatory_code          yes
    _item_type.code               code
     save_


save__diffrn_measurement_axis.measurement_device
    _item_description.description
;              This data item is a pointer to _diffrn_measurement.device
               in the DIFFRN_MEASUREMENT category.
;
    _item.name
      '_diffrn_measurement_axis.measurement_device'
    _item.category_id             diffrn_measurement_axis
    _item.mandatory_code          implicit
    _item_type.code               text
     save_


save__diffrn_measurement_axis.measurement_id
    _item_description.description
;              This data item is a pointer to _diffrn_measurement.id in
               the DIFFRN_MEASUREMENT category.

               This item was previously named _diffrn_measurement_axis.id,
               which is now a deprecated name.  The old name is
               provided as an alias but should not be used for new work.
;
    _item.name                  '_diffrn_measurement_axis.measurement_id'
    _item.category_id             diffrn_measurement_axis
    _item.mandatory_code          implicit
    _item_aliases.alias_name    '_diffrn_measurement_axis.id'
    _item_aliases.dictionary      cif_img.dic
    _item_aliases.version         1.0
    _item_type.code               code
     save_


####################
# DIFFRN_RADIATION #
####################


save_DIFFRN_RADIATION
    _category.description
;              Data items in the DIFFRN_RADIATION category describe
               the radiation used for measuring diffraction intensities,
               its collimation and monochromatization before the sample.

               Post-sample treatment of the beam is described by data
               items in the DIFFRN_DETECTOR category.
;
    _category.id                  diffrn_radiation
    _category.mandatory_code      no
    _category_key.name          '_diffrn_radiation.diffrn_id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;   Example 1 - based on PDB entry 5HVP and laboratory records for the
                structure corresponding to PDB entry 5HVP
;
;
    _diffrn_radiation.diffrn_id            'set1'

    _diffrn_radiation.collimation          '0.3 mm double pinhole'
    _diffrn_radiation.monochromator        'graphite'
    _diffrn_radiation.type                 'Cu K\a'
    _diffrn_radiation.wavelength_id         1
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;    Example 2 - based on data set TOZ of Willis, Beckwith & Tozer
                [Acta Cryst. (1991), C47, 2276-2277].
;
;
    _diffrn_radiation.wavelength_id    1
    _diffrn_radiation.type             'Cu K\a'
    _diffrn_radiation.monochromator    'graphite'
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_

save__diffrn_radiation.collimation
    _item_description.description
;              The collimation or focusing applied to the radiation.
;
    _item.name                  '_diffrn_radiation.collimation'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_collimation'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
     loop_
    _item_examples.case          '0.3 mm double-pinhole'
                                 '0.5 mm'
                                 'focusing mirrors'
     save_


save__diffrn_radiation.diffrn_id
    _item_description.description
;              This data item is a pointer to _diffrn.id in the DIFFRN
               category.
;
    _item.name                  '_diffrn_radiation.diffrn_id'
    _item.mandatory_code          yes
    _item_type.code               code
     save_



save__diffrn_radiation.div_x_source
    _item_description.description
;              Beam crossfire in degrees parallel to the laboratory X axis
               (see AXIS category).

               This is a characteristic of the X-ray beam as it illuminates
               the sample (or specimen) after all monochromation and
               collimation.

               This is the standard uncertainty (e.s.d.)  of the directions of
               photons in the XZ plane around the mean source beam
               direction.

               Note that for some synchrotrons this value is specified
               in milliradians, in which case a conversion is needed.
               To convert a value in milliradians to a value in degrees,
               multiply by 0.180 and divide by \p.
;
    _item.name                  '_diffrn_radiation.div_x_source'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_type.code               float
    _item_units.code              degrees
     save_


save__diffrn_radiation.div_y_source
    _item_description.description
;              Beam crossfire in degrees parallel to the laboratory Y axis
               (see AXIS category).

               This is a characteristic of the X-ray beam as it illuminates
               the sample (or specimen) after all monochromation and
               collimation.

               This is the standard uncertainty (e.s.d.) of the directions
               of photons in the YZ plane around the mean source beam
               direction.

               Note that for some synchrotrons this value is specified
               in milliradians, in which case a conversion is needed.
               To convert a value in milliradians to a value in degrees,
               multiply by 0.180 and divide by \p.
;
    _item.name                  '_diffrn_radiation.div_y_source'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_type.code               float
    _item_units.code              degrees
    _item_default.value           0.0
     save_


save__diffrn_radiation.div_x_y_source
    _item_description.description
;              Beam crossfire correlation degrees^2^ between the
               crossfire laboratory X-axis component and the crossfire
               laboratory Y-axis component (see AXIS category).

               This is a characteristic of the X-ray beam as it illuminates
               the sample (or specimen) after all monochromation and
               collimation.

               This is the mean of the products of the deviations of the
               direction of each photon in XZ plane times the deviations
               of the direction of the same photon in the YZ plane
               around the mean source beam direction.  This will be zero
               for uncorrelated crossfire.

               Note that some synchrotrons, this value is specified in
               milliradians^2^, in which case a conversion would be needed.
               To go from a value in milliradians^2^ to a value in
               degrees^2^, multiply by 0.180^2^ and divide by \p^2^.

;
    _item.name                  '_diffrn_radiation.div_x_y_source'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_type.code               float
    _item_units.code              degrees_squared
    _item_default.value           0.0
     save_

save__diffrn_radiation.filter_edge
    _item_description.description
;              Absorption edge in \%Angstroms of the radiation filter used.
;
    _item.name                  '_diffrn_radiation.filter_edge'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_filter_edge'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
     loop_
    _item_range.maximum
    _item_range.minimum            .    0.0
                                  0.0   0.0
    _item_type.code               float
    _item_units.code              angstroms
     save_

save__diffrn_radiation.inhomogeneity
    _item_description.description
;              Half-width in millimetres of the incident beam in the
               direction perpendicular to the diffraction plane.
;
    _item.name                  '_diffrn_radiation.inhomogeneity'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_inhomogeneity'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
     loop_
    _item_range.maximum
    _item_range.minimum            .    0.0
                                  0.0   0.0
    _item_type.code               float
    _item_units.code              millimetres
     save_

save__diffrn_radiation.monochromator
    _item_description.description
;              The method used to obtain monochromatic radiation. If a
               monochromator crystal is used, the material and the
               indices of the Bragg reflection are specified.
;
    _item.name                  '_diffrn_radiation.monochromator'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_monochromator'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
     loop_
    _item_examples.case          'Zr filter'
                                 'Ge 220'
                                 'none'
                                 'equatorial mounted graphite'
     save_

save__diffrn_radiation.polarisn_norm
    _item_description.description
;              The angle in degrees, as viewed from the specimen, between the
               perpendicular component of the polarization and the diffraction
               plane. See _diffrn_radiation_polarisn_ratio.
;
    _item.name                  '_diffrn_radiation.polarisn_norm'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_polarisn_norm'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
     loop_
    _item_range.maximum
    _item_range.minimum           90.0  90.0
                                  90.0 -90.0
                                 -90.0 -90.0
    _item_type.code               float
    _item_units.code              degrees
     save_

save__diffrn_radiation.polarisn_ratio
    _item_description.description
;              Polarization ratio of the diffraction beam incident on the
               crystal. This is the ratio of the perpendicularly polarized to
               the parallel polarized component of the radiation. The
               perpendicular component forms an angle of
               _diffrn_radiation.polarisn_norm to the normal to the
               diffraction plane of the sample (i.e. the plane containing
               the incident and reflected beams).
;
    _item.name                  '_diffrn_radiation.polarisn_ratio'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_polarisn_ratio'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
     loop_
    _item_range.maximum
    _item_range.minimum            .    0.0
                                  0.0   0.0
    _item_type.code               float
     save_



save__diffrn_radiation.polarizn_source_norm
    _item_description.description
;              The angle in degrees, as viewed from the specimen, between
               the normal to the polarization plane and the laboratory Y
               axis as defined in the AXIS category.

               Note that this is the angle of polarization of the source
               photons, either directly from a synchrotron beamline or
               from a monochromater.

               This differs from the value of
               _diffrn_radiation.polarisn_norm
               in that _diffrn_radiation.polarisn_norm refers to
               polarization relative to the diffraction plane rather than
               to the laboratory axis system.

               In the case of an unpolarized beam, or a beam with true
               circular polarization, in which no single plane of
               polarization can be determined, the plane should be taken
               as the XZ plane and the angle as 0.

               See _diffrn_radiation.polarizn_source_ratio.
;
    _item.name                  '_diffrn_radiation.polarizn_source_norm'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
     loop_
    _item_range.maximum
    _item_range.minimum           90.0   90.0
                                  90.0  -90.0
                                 -90.0  -90.0
    _item_type.code               float
    _item_units.code              degrees
    _item_default.value           0.0
     save_


save__diffrn_radiation.polarizn_source_ratio
    _item_description.description
;              (Ip-In)/(Ip+In), where Ip is the intensity
               (amplitude squared) of the electric vector in the plane of
               polarization and In is the intensity (amplitude squared)
               of the electric vector in the plane of the normal to the
               plane of polarization.

               In the case of an unpolarized beam, or a beam with true
               circular polarization, in which no single plane of
               polarization can be determined, the plane is to be taken
               as the XZ plane and the normal is parallel to the Y axis.

               Thus, if there was complete polarization in the plane of
               polarization, the value of
               _diffrn_radiation.polarizn_source_ratio would be 1, and
               for an unpolarized beam
               _diffrn_radiation.polarizn_source_ratio would have a
               value of 0.

               If the X axis has been chosen to lie in the plane of
               polarization, this definition will agree with the definition
               of 'MONOCHROMATOR' in the Denzo glossary, and values of near
               1 should be expected for a bending-magnet source.  However,
               if the X axis were perpendicular to the polarization plane
               (not a common choice), then the Denzo value would be the
               negative of _diffrn_radiation.polarizn_source_ratio.

               See http://www.hkl-xray.com for information on Denzo and
               Otwinowski & Minor (1997).

               This differs both in the choice of ratio and choice of
               orientation from _diffrn_radiation.polarisn_ratio, which,
               unlike _diffrn_radiation.polarizn_source_ratio, is
               unbounded.

               Reference: Otwinowski, Z. & Minor, W. (1997). 'Processing of
               X-ray diffraction data collected in oscillation mode.' Methods
               Enzymol. 276, 307-326.
;
    _item.name                  '_diffrn_radiation.polarizn_source_ratio'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
     loop_
    _item_range.maximum
    _item_range.minimum           1.0    1.0
                                  1.0   -1.0
                                 -1.0   -1.0
    _item_type.code               float
     save_


save__diffrn_radiation.probe
    _item_description.description
;              Name of the type of radiation used. It is strongly
               recommended that this be given so that the
               probe radiation is clearly specified.
;
    _item.name                  '_diffrn_radiation.probe'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_probe'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               line
     loop_
    _item_enumeration.value      'X-ray'
                                 'neutron'
                                 'electron'
                                 'gamma'
     save_

save__diffrn_radiation.type
    _item_description.description
;              The nature of the radiation. This is typically a description
               of the X-ray wavelength in Siegbahn notation.
;
    _item.name                  '_diffrn_radiation.type'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_type'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               line
     loop_
    _item_examples.case          'CuK\a'
                                 'Cu K\a~1~'
                                 'Cu K-L~2,3~'
                                 'white-beam'

     save_

save__diffrn_radiation.xray_symbol
    _item_description.description
;              The IUPAC symbol for the X-ray wavelength for the probe
               radiation.
;
    _item.name                  '_diffrn_radiation.xray_symbol'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_xray_symbol'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               line
     loop_
    _item_enumeration.value
    _item_enumeration.detail     'K-L~3~'
                                 'K\a~1~ in older Siegbahn notation'
                                 'K-L~2~'
                                 'K\a~2~ in older Siegbahn notation'
                                 'K-M~3~'
                                 'K\b~1~ in older Siegbahn notation'
                                 'K-L~2,3~'
                                 'use where K-L~3~ and K-L~2~ are not resolved'
     save_

save__diffrn_radiation.wavelength_id
    _item_description.description
;              This data item is a pointer to
               _diffrn_radiation_wavelength.id in the
               DIFFRN_RADIATION_WAVELENGTH category.
;
    _item.name                  '_diffrn_radiation.wavelength_id'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          yes
    _item_type.code               code
     save_



################
# DIFFRN_REFLN #
################


save_DIFFRN_REFLN
    _category.description
;    This category redefinition has been added to extend the key of
     the standard DIFFRN_REFLN category.
;
    _category.id                   diffrn_refln
    _category.mandatory_code       no
    _category_key.name             '_diffrn_refln.frame_id'
     loop_
    _category_group.id             'inclusive_group'
                                   'diffrn_group'
     save_


save__diffrn_refln.frame_id
    _item_description.description
;              This item is a pointer to _diffrn_data_frame.id
               in the DIFFRN_DATA_FRAME category.
;
    _item.name                  '_diffrn_refln.frame_id'
    _item.category_id             diffrn_refln
    _item.mandatory_code          yes
    _item_type.code               code
     save_


###############
# DIFFRN_SCAN #
###############

save_DIFFRN_SCAN
    _category.description
;    Data items in the DIFFRN_SCAN category describe the parameters of one
     or more scans, relating axis positions to frames.

;
    _category.id                   diffrn_scan
    _category.mandatory_code       no
    _category_key.name            '_diffrn_scan.id'
     loop_
    _category_group.id            'inclusive_group'
                                  'diffrn_group'
     loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;   Example 1 - derived from a suggestion by R. M. Sweet.

   The vector of each axis is not given here, because it is provided in
   the AXIS category.  By making _diffrn_scan_axis.scan_id and
   _diffrn_scan_axis.axis_id keys of the DIFFRN_SCAN_AXIS category,
   an arbitrary number of scanning and fixed axes can be specified for a
   scan.  In this example, three rotation axes and one translation axis
   at nonzero values are specified, with one axis stepping.  There is no
   reason why more axes could not have been specified to step. Range
   information has been specified, but note that it can be calculated from
   the  number of frames and the increment, so the data item
   _diffrn_scan_axis.angle_range could be dropped.

   Both the sweep data and the data for a single frame are specified.

   Note that the information on how the axes are stepped is given twice,
   once in terms of the overall averages in the value of
   _diffrn_scan.integration_time and the values for DIFFRN_SCAN_AXIS,
   and precisely for the given frame in the value for
   _diffrn_scan_frame.integration_time and the values for
   DIFFRN_SCAN_FRAME_AXIS.  If dose-related adjustments are made to
   scan times and nonlinear stepping is done, these values may differ.
   Therefore, in interpreting the data for a particular frame it is
   important to use the frame-specific data.
;
;
      _diffrn_scan.id                   1
      _diffrn_scan.date_start         '2001-11-18T03:26:42'
      _diffrn_scan.date_end           '2001-11-18T03:36:45'
      _diffrn_scan.integration_time    3.0
      _diffrn_scan.frame_id_start      mad_L2_000
      _diffrn_scan.frame_id_end        mad_L2_200
      _diffrn_scan.frames              201

       loop_
      _diffrn_scan_axis.scan_id
      _diffrn_scan_axis.axis_id
      _diffrn_scan_axis.angle_start
      _diffrn_scan_axis.angle_range
      _diffrn_scan_axis.angle_increment
      _diffrn_scan_axis.displacement_start
      _diffrn_scan_axis.displacement_range
      _diffrn_scan_axis.displacement_increment

       1 omega 200.0 20.0 0.1 . . .
       1 kappa -40.0  0.0 0.0 . . .
       1 phi   127.5  0.0 0.0 . . .
       1 tranz  . . .   2.3 0.0 0.0

      _diffrn_scan_frame.scan_id                   1
      _diffrn_scan_frame.date               '2001-11-18T03:27:33'
      _diffrn_scan_frame.integration_time    3.0
      _diffrn_scan_frame.frame_id            mad_L2_018
      _diffrn_scan_frame.frame_number        18

      loop_
      _diffrn_scan_frame_axis.frame_id
      _diffrn_scan_frame_axis.axis_id
      _diffrn_scan_frame_axis.angle
      _diffrn_scan_frame_axis.angle_increment
      _diffrn_scan_frame_axis.displacement
      _diffrn_scan_frame_axis.displacement_increment

       mad_L2_018 omega 201.8  0.1 . .
       mad_L2_018 kappa -40.0  0.0 . .
       mad_L2_018 phi   127.5  0.0 . .
       mad_L2_018 tranz  .     .  2.3 0.0
;

;  Example 2 - a more extensive example (R. M. Sweet, P. J. Ellis &
   H. J. Bernstein).

   A detector is placed 240 mm along the Z axis from the goniometer.
   This leads to a choice:  either the axes of
   the detector are defined at the origin, and then a Z setting of -240
   is entered, or the axes are defined with the necessary Z offset.
   In this case, the setting is used and the offset is left as zero.
   This axis is called DETECTOR_Z.

   The axis for positioning the detector in the Y direction depends
   on the detector Z axis.  This axis is called DETECTOR_Y.

   The axis for positioning the detector in the X direction depends
   on the detector Y axis (and therefore on the detector Z axis).
   This axis is called DETECTOR_X.

   This detector may be rotated around the Y axis.  This rotation axis
   depends on the three translation axes.  It is called DETECTOR_PITCH.

   A coordinate system is defined on the face of the detector in terms of
   2300 0.150 mm pixels in each direction.  The ELEMENT_X axis is used to
   index the first array index of the data array and the ELEMENT_Y
   axis is used to index the second array index.  Because the pixels
   are 0.150mm X 0.150mm, the centre of the first pixel is at (0.075,
   0.075) in this coordinate system.
;

;    ###CBF: VERSION 1.1

     data_image_1

     # category DIFFRN
     _diffrn.id P6MB
     _diffrn.crystal_id P6MB_CRYSTAL7

     # category DIFFRN_SOURCE
     loop_
     _diffrn_source.diffrn_id
     _diffrn_source.source
     _diffrn_source.type
      P6MB synchrotron 'SSRL beamline 9-1'

     # category DIFFRN_RADIATION
     loop_
     _diffrn_radiation.diffrn_id
     _diffrn_radiation.wavelength_id
     _diffrn_radiation.monochromator
     _diffrn_radiation.polarizn_source_ratio
     _diffrn_radiation.polarizn_source_norm
     _diffrn_radiation.div_x_source
     _diffrn_radiation.div_y_source
     _diffrn_radiation.div_x_y_source
      P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08
     0.01 0.00

     # category DIFFRN_RADIATION_WAVELENGTH
     loop_
     _diffrn_radiation_wavelength.id
     _diffrn_radiation_wavelength.wavelength
     _diffrn_radiation_wavelength.wt
      WAVELENGTH1 0.98 1.0

     # category DIFFRN_DETECTOR
     loop_
     _diffrn_detector.diffrn_id
     _diffrn_detector.id
     _diffrn_detector.type
     _diffrn_detector.number_of_axes
      P6MB MAR345-SN26 'MAR 345' 4

     # category DIFFRN_DETECTOR_AXIS
     loop_
     _diffrn_detector_axis.detector_id
     _diffrn_detector_axis.axis_id
      MAR345-SN26 DETECTOR_X
      MAR345-SN26 DETECTOR_Y
      MAR345-SN26 DETECTOR_Z
      MAR345-SN26 DETECTOR_PITCH

     # category DIFFRN_DETECTOR_ELEMENT
     loop_
     _diffrn_detector_element.id
     _diffrn_detector_element.detector_id
      ELEMENT1 MAR345-SN26

     # category DIFFRN_DATA_FRAME
     loop_
     _diffrn_data_frame.id
     _diffrn_data_frame.detector_element_id
     _diffrn_data_frame.array_id
     _diffrn_data_frame.binary_id
      FRAME1 ELEMENT1 ARRAY1 1

     # category DIFFRN_MEASUREMENT
     loop_
     _diffrn_measurement.diffrn_id
     _diffrn_measurement.id
     _diffrn_measurement.number_of_axes
     _diffrn_measurement.method
      P6MB GONIOMETER 3 rotation

     # category DIFFRN_MEASUREMENT_AXIS
     loop_
     _diffrn_measurement_axis.measurement_id
     _diffrn_measurement_axis.axis_id
      GONIOMETER GONIOMETER_PHI
      GONIOMETER GONIOMETER_KAPPA
      GONIOMETER GONIOMETER_OMEGA

     # category DIFFRN_SCAN
     loop_
     _diffrn_scan.id
     _diffrn_scan.frame_id_start
     _diffrn_scan.frame_id_end
     _diffrn_scan.frames
      SCAN1 FRAME1 FRAME1 1

     # category DIFFRN_SCAN_AXIS
     loop_
     _diffrn_scan_axis.scan_id
     _diffrn_scan_axis.axis_id
     _diffrn_scan_axis.angle_start
     _diffrn_scan_axis.angle_range
     _diffrn_scan_axis.angle_increment
     _diffrn_scan_axis.displacement_start
     _diffrn_scan_axis.displacement_range
     _diffrn_scan_axis.displacement_increment
      SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0
      SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0
      SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0
      SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0
      SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0
      SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0
      SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0

     # category DIFFRN_SCAN_FRAME
     loop_
     _diffrn_scan_frame.frame_id
     _diffrn_scan_frame.frame_number
     _diffrn_scan_frame.integration_time
     _diffrn_scan_frame.scan_id
     _diffrn_scan_frame.date
      FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48

     # category DIFFRN_SCAN_FRAME_AXIS
     loop_
     _diffrn_scan_frame_axis.frame_id
     _diffrn_scan_frame_axis.axis_id
     _diffrn_scan_frame_axis.angle
     _diffrn_scan_frame_axis.displacement
      FRAME1 GONIOMETER_OMEGA 12.0 0.0
      FRAME1 GONIOMETER_KAPPA 23.3 0.0
      FRAME1 GONIOMETER_PHI -165.8 0.0
      FRAME1 DETECTOR_Z 0.0 -240.0
      FRAME1 DETECTOR_Y 0.0 0.6
      FRAME1 DETECTOR_X 0.0 -0.5
      FRAME1 DETECTOR_PITCH 0.0 0.0

     # category AXIS
     loop_
     _axis.id
     _axis.type
     _axis.equipment
     _axis.depends_on
     _axis.vector[1] _axis.vector[2] _axis.vector[3]
     _axis.offset[1] _axis.offset[2] _axis.offset[3]
      GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . .
      GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279
      0 0.76604 . . .
      GONIOMETER_PHI   rotation goniometer GONIOMETER_KAPPA 1 0 0
     . . .
      SOURCE           general source . 0 0 1 . . .
      GRAVITY          general gravity . 0 -1 0 . . .
      DETECTOR_Z       translation detector . 0 0 1 0 0 0
      DETECTOR_Y       translation detector DETECTOR_Z 0 1 0 0 0 0
      DETECTOR_X       translation detector DETECTOR_Y 1 0 0 0 0 0
      DETECTOR_PITCH   rotation    detector DETECTOR_X 0 1 0 0 0 0
      ELEMENT_X        translation detector DETECTOR_PITCH
     1 0 0 172.43 -172.43 0
      ELEMENT_Y        translation detector ELEMENT_X
     0 1 0 0 0 0

     # category ARRAY_STRUCTURE_LIST
     loop_
     _array_structure_list.array_id
     _array_structure_list.index
     _array_structure_list.dimension
     _array_structure_list.precedence
     _array_structure_list.direction
     _array_structure_list.axis_set_id
      ARRAY1 1 2300 1 increasing ELEMENT_X
      ARRAY1 2 2300 2 increasing ELEMENT_Y

     # category ARRAY_STRUCTURE_LIST_AXIS
     loop_
     _array_structure_list_axis.axis_set_id
     _array_structure_list_axis.axis_id
     _array_structure_list_axis.displacement
     _array_structure_list_axis.displacement_increment
      ELEMENT_X ELEMENT_X 0.075 0.150
      ELEMENT_Y ELEMENT_Y 0.075 0.150

     # category ARRAY_ELEMENT_SIZE
     loop_
     _array_element_size.array_id
     _array_element_size.index
     _array_element_size.size
      ARRAY1 1 150e-6
      ARRAY1 2 150e-6

     # category ARRAY_INTENSITIES
     loop_
     _array_intensities.array_id
     _array_intensities.binary_id
     _array_intensities.linearity
     _array_intensities.gain
     _array_intensities.gain_esd
     _array_intensities.overload
     _array_intensities.undefined_value
      ARRAY1 1 linear 1.15 0.2 240000 0

      # category ARRAY_STRUCTURE
      loop_
      _array_structure.id
      _array_structure.encoding_type
      _array_structure.compression_type
      _array_structure.byte_order
      ARRAY1 "signed 32-bit integer" packed little_endian

     # category ARRAY_DATA
     loop_
     _array_data.array_id
     _array_data.binary_id
     _array_data.data
      ARRAY1 1
     ;
     --CIF-BINARY-FORMAT-SECTION--
     Content-Type: application/octet-stream;
         conversions="X-CBF_PACKED"
     Content-Transfer-Encoding: BASE64
     X-Binary-Size: 3801324
     X-Binary-ID: 1
     X-Binary-Element-Type: "signed 32-bit integer"
     Content-MD5: 07lZFvF+aOcW85IN7usl8A==

     AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg
     ...
     8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE

     --CIF-BINARY-FORMAT-SECTION----
     ;
;

;   Example 3 - Example 2 revised for a spiral scan (R. M. Sweet,
    P. J. Ellis & H. J. Bernstein).

   A detector is placed 240 mm along the Z axis from the
   goniometer, as in Example 2 above, but in this example the
   image plate is scanned in a spiral pattern from the outside edge in.

   The axis for positioning the detector in the Y direction depends
   on the detector Z axis.  This axis is called DETECTOR_Y.

   The axis for positioning the detector in the X direction depends
   on the detector Y axis (and therefore on the detector Z axis).
   This axis is called DETECTOR_X.

   This detector may be rotated around the Y axis.  This rotation axis
   depends on the three translation axes.  It is called DETECTOR_PITCH.

   A coordinate system is defined on the face of the detector in
   terms of a coupled rotation axis and radial scan axis to form
   a spiral scan.  The rotation axis is called  ELEMENT_ROT  and the
   radial axis is called ELEMENT_RAD.  A 150 micrometre radial pitch
   and a 75 micrometre 'constant velocity' angular pitch are assumed.

   Indexing is carried out first on the rotation axis and the radial axis
   is made to be dependent on it.

   The two axes are coupled to form an axis set ELEMENT_SPIRAL.
;
;    ###CBF: VERSION 1.1

     data_image_1

     # category DIFFRN
     _diffrn.id P6MB
     _diffrn.crystal_id P6MB_CRYSTAL7

     # category DIFFRN_SOURCE
     loop_
     _diffrn_source.diffrn_id
     _diffrn_source.source
     _diffrn_source.type
      P6MB synchrotron 'SSRL beamline 9-1'

     # category DIFFRN_RADIATION
          loop_
     _diffrn_radiation.diffrn_id
     _diffrn_radiation.wavelength_id
     _diffrn_radiation.monochromator
     _diffrn_radiation.polarizn_source_ratio
     _diffrn_radiation.polarizn_source_norm
     _diffrn_radiation.div_x_source
     _diffrn_radiation.div_y_source
     _diffrn_radiation.div_x_y_source
      P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08
     0.01 0.00

     # category DIFFRN_RADIATION_WAVELENGTH
     loop_
     _diffrn_radiation_wavelength.id
     _diffrn_radiation_wavelength.wavelength
     _diffrn_radiation_wavelength.wt
      WAVELENGTH1 0.98 1.0

     # category DIFFRN_DETECTOR
     loop_
     _diffrn_detector.diffrn_id
     _diffrn_detector.id
     _diffrn_detector.type
     _diffrn_detector.number_of_axes
      P6MB MAR345-SN26 'MAR 345' 4

     # category DIFFRN_DETECTOR_AXIS
     loop_
     _diffrn_detector_axis.detector_id
     _diffrn_detector_axis.axis_id
      MAR345-SN26 DETECTOR_X
      MAR345-SN26 DETECTOR_Y
      MAR345-SN26 DETECTOR_Z
      MAR345-SN26 DETECTOR_PITCH

     # category DIFFRN_DETECTOR_ELEMENT
     loop_
     _diffrn_detector_element.id
     _diffrn_detector_element.detector_id
      ELEMENT1 MAR345-SN26

     # category DIFFRN_DATA_FRAME
     loop_
     _diffrn_data_frame.id
     _diffrn_data_frame.detector_element_id
     _diffrn_data_frame.array_id
     _diffrn_data_frame.binary_id
      FRAME1 ELEMENT1 ARRAY1 1

     # category DIFFRN_MEASUREMENT
     loop_
     _diffrn_measurement.diffrn_id
     _diffrn_measurement.id
     _diffrn_measurement.number_of_axes
     _diffrn_measurement.method
      P6MB GONIOMETER 3 rotation

     # category DIFFRN_MEASUREMENT_AXIS
     loop_
     _diffrn_measurement_axis.measurement_id
     _diffrn_measurement_axis.axis_id
      GONIOMETER GONIOMETER_PHI
      GONIOMETER GONIOMETER_KAPPA
      GONIOMETER GONIOMETER_OMEGA

     # category DIFFRN_SCAN
     loop_
     _diffrn_scan.id
     _diffrn_scan.frame_id_start
     _diffrn_scan.frame_id_end
     _diffrn_scan.frames
      SCAN1 FRAME1 FRAME1 1

     # category DIFFRN_SCAN_AXIS
     loop_
     _diffrn_scan_axis.scan_id
     _diffrn_scan_axis.axis_id
     _diffrn_scan_axis.angle_start
     _diffrn_scan_axis.angle_range
     _diffrn_scan_axis.angle_increment
     _diffrn_scan_axis.displacement_start
     _diffrn_scan_axis.displacement_range
     _diffrn_scan_axis.displacement_increment
      SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0
      SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0
      SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0
      SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0
      SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0
      SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0
      SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0

     # category DIFFRN_SCAN_FRAME
     loop_
     _diffrn_scan_frame.frame_id
     _diffrn_scan_frame.frame_number
     _diffrn_scan_frame.integration_time
     _diffrn_scan_frame.scan_id
     _diffrn_scan_frame.date
      FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48

     # category DIFFRN_SCAN_FRAME_AXIS
     loop_
     _diffrn_scan_frame_axis.frame_id
     _diffrn_scan_frame_axis.axis_id
     _diffrn_scan_frame_axis.angle
     _diffrn_scan_frame_axis.displacement
      FRAME1 GONIOMETER_OMEGA 12.0 0.0
      FRAME1 GONIOMETER_KAPPA 23.3 0.0
      FRAME1 GONIOMETER_PHI -165.8 0.0
      FRAME1 DETECTOR_Z 0.0 -240.0
      FRAME1 DETECTOR_Y 0.0 0.6
      FRAME1 DETECTOR_X 0.0 -0.5
      FRAME1 DETECTOR_PITCH 0.0 0.0

     # category AXIS
     loop_
     _axis.id
     _axis.type
     _axis.equipment
     _axis.depends_on
     _axis.vector[1] _axis.vector[2] _axis.vector[3]
     _axis.offset[1] _axis.offset[2] _axis.offset[3]
      GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . .
      GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279
      0 0.76604 . . .
      GONIOMETER_PHI   rotation goniometer GONIOMETER_KAPPA 1 0 0
     . . .
      SOURCE           general source . 0 0 1 . . .
      GRAVITY          general gravity . 0 -1 0 . . .
      DETECTOR_Z       translation detector . 0 0 1 0 0 0
      DETECTOR_Y       translation detector DETECTOR_Z 0 1 0 0 0 0
      DETECTOR_X       translation detector DETECTOR_Y 1 0 0 0 0 0
      DETECTOR_PITCH   rotation    detector DETECTOR_X 0 1 0 0 0 0
      ELEMENT_ROT      translation detector DETECTOR_PITCH 0 0 1 0 0 0
      ELEMENT_RAD      translation detector ELEMENT_ROT 0 1 0 0 0 0

     # category ARRAY_STRUCTURE_LIST
     loop_
     _array_structure_list.array_id
     _array_structure_list.index
     _array_structure_list.dimension
     _array_structure_list.precedence
     _array_structure_list.direction
     _array_structure_list.axis_set_id
      ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL

     # category ARRAY_STRUCTURE_LIST_AXIS
     loop_
     _array_structure_list_axis.axis_set_id
     _array_structure_list_axis.axis_id
     _array_structure_list_axis.angle
     _array_structure_list_axis.displacement
     _array_structure_list_axis.angular_pitch
     _array_structure_list_axis.radial_pitch
      ELEMENT_SPIRAL ELEMENT_ROT 0    .  0.075   .
      ELEMENT_SPIRAL ELEMENT_RAD . 172.5  .    -0.150

     # category ARRAY_ELEMENT_SIZE
     # the actual pixels are 0.075 by 0.150 mm
     # We give the coarser dimension here.
     loop_
     _array_element_size.array_id
     _array_element_size.index
     _array_element_size.size
      ARRAY1 1 150e-6

     # category ARRAY_INTENSITIES
     loop_
     _array_intensities.array_id
     _array_intensities.binary_id
     _array_intensities.linearity
     _array_intensities.gain
     _array_intensities.gain_esd
     _array_intensities.overload
     _array_intensities.undefined_value
      ARRAY1 1 linear 1.15 0.2 240000 0

      # category ARRAY_STRUCTURE
      loop_
      _array_structure.id
      _array_structure.encoding_type
      _array_structure.compression_type
      _array_structure.byte_order
      ARRAY1 "signed 32-bit integer" packed little_endian

     # category ARRAY_DATA
     loop_
     _array_data.array_id
     _array_data.binary_id
     _array_data.data
      ARRAY1 1
     ;
     --CIF-BINARY-FORMAT-SECTION--
     Content-Type: application/octet-stream;
         conversions="X-CBF_PACKED"
     Content-Transfer-Encoding: BASE64
     X-Binary-Size: 3801324
     X-Binary-ID: 1
     X-Binary-Element-Type: "signed 32-bit integer"
     Content-MD5: 07lZFvF+aOcW85IN7usl8A==

     AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg
     ...
     8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE

     --CIF-BINARY-FORMAT-SECTION----
     ;
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
       save_


save__diffrn_scan.id
    _item_description.description
;             The value of _diffrn_scan.id uniquely identifies each
              scan.  The identifier is used to tie together all the
              information about the scan.
;
     loop_
    _item.name
    _item.category_id
    _item.mandatory_code
       '_diffrn_scan.id'                 diffrn_scan             yes
       '_diffrn_scan_axis.scan_id'       diffrn_scan_axis        yes
       '_diffrn_scan_frame.scan_id'      diffrn_scan_frame       yes
    _item_type.code               code
     loop_
    _item_linked.child_name
    _item_linked.parent_name
       '_diffrn_scan_axis.scan_id'          '_diffrn_scan.id'
       '_diffrn_scan_frame.scan_id'         '_diffrn_scan.id'
     save_


save__diffrn_scan.date_end
    _item_description.description
;              The date and time of the end of the scan.  Note that this
               may be an estimate generated during the scan, before the
               precise time of the end of the scan is known.
;
    _item.name                 '_diffrn_scan.date_end'
    _item.category_id          diffrn_scan
    _item.mandatory_code       no
    _item_type.code            yyyy-mm-dd
     save_


save__diffrn_scan.date_start
    _item_description.description
;              The date and time of the start of the scan.
;
    _item.name                 '_diffrn_scan.date_start'
    _item.category_id          diffrn_scan
    _item.mandatory_code       no
    _item_type.code            yyyy-mm-dd
     save_


save__diffrn_scan.integration_time
    _item_description.description
;              Approximate average time in seconds to integrate each
               step of the scan.  The precise time for integration
               of each particular step must be provided in
               _diffrn_scan_frame.integration_time, even
               if all steps have the same integration time.
;
    _item.name                 '_diffrn_scan.integration_time'
    _item.category_id          diffrn_scan
    _item.mandatory_code       no
    _item_type.code            float
    _item_units.code           'seconds'
     loop_
    _item_range.maximum
    _item_range.minimum
                            .   0.0
     save_


save__diffrn_scan.frame_id_start
    _item_description.description
;              The value of this data item is the identifier of the
               first frame in the scan.

               This item is a pointer to _diffrn_data_frame.id in the
               DIFFRN_DATA_FRAME category.
;
    _item.name                 '_diffrn_scan.frame_id_start'
    _item.category_id          diffrn_scan
    _item.mandatory_code       yes
    _item_type.code            code
     save_


save__diffrn_scan.frame_id_end
    _item_description.description
;              The value of this data item is the identifier of the
               last frame in the scan.

               This item is a pointer to _diffrn_data_frame.id in the
               DIFFRN_DATA_FRAME category.
;
    _item.name                 '_diffrn_scan.frame_id_end'
    _item.category_id          diffrn_scan
    _item.mandatory_code       yes
    _item_type.code            code
     save_


save__diffrn_scan.frames
    _item_description.description
;              The value of this data item is the number of frames in
               the scan.
;
    _item.name                 '_diffrn_scan.frames'
    _item.category_id          diffrn_scan
    _item.mandatory_code       no
    _item_type.code            int
     loop_
    _item_range.maximum
    _item_range.minimum
                            .   1
                            1   1
     save_


####################
# DIFFRN_SCAN_AXIS #
####################

save_DIFFRN_SCAN_AXIS
    _category.description
;    Data items in the DIFFRN_SCAN_AXIS category describe the settings of
     axes for particular scans.  Unspecified axes are assumed to be at
     their zero points.
;
    _category.id                   diffrn_scan_axis
    _category.mandatory_code       no
     loop_
    _category_key.name
                                  '_diffrn_scan_axis.scan_id'
                                  '_diffrn_scan_axis.axis_id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     save_


save__diffrn_scan_axis.scan_id
    _item_description.description
;              The value of this data item is the identifier of the
               scan for which axis settings are being specified.

               Multiple axes may be specified for the same value of
               _diffrn_scan.id.

               This item is a pointer to _diffrn_scan.id in the
               DIFFRN_SCAN category.
;
    _item.name                 '_diffrn_scan_axis.scan_id'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       yes
    _item_type.code            code
     save_


save__diffrn_scan_axis.axis_id
    _item_description.description
;              The value of this data item is the identifier of one of
               the axes for the scan for which settings are being specified.

               Multiple axes may be specified for the same value of
               _diffrn_scan.id.

               This item is a pointer to _axis.id in the
               AXIS category.
;
    _item.name                 '_diffrn_scan_axis.axis_id'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       yes
    _item_type.code            code
     save_


save__diffrn_scan_axis.angle_start
    _item_description.description
;              The starting position for the specified axis in degrees.
;
    _item.name                 '_diffrn_scan_axis.angle_start'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_


save__diffrn_scan_axis.angle_range
    _item_description.description
;              The range from the starting position for the specified axis
               in degrees.
;
    _item.name                 '_diffrn_scan_axis.angle_range'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_


save__diffrn_scan_axis.angle_increment
    _item_description.description
;              The increment for each step for the specified axis
               in degrees.  In general, this will agree with
               _diffrn_scan_frame_axis.angle_increment. The
               sum of the values of _diffrn_scan_frame_axis.angle and
               _diffrn_scan_frame_axis.angle_increment is the
               angular setting of the axis at the end of the integration
               time for a given frame.  If the individual frame values
               vary, then the value of
               _diffrn_scan_axis.angle_increment will be
               representative
               of the ensemble of values of
               _diffrn_scan_frame_axis.angle_increment (e.g.
               the mean).
;
    _item.name                 '_diffrn_scan_axis.angle_increment'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_


save__diffrn_scan_axis.angle_rstrt_incr
    _item_description.description
;              The increment after each step for the specified axis
               in degrees.  In general, this will agree with
               _diffrn_scan_frame_axis.angle_rstrt_incr.  The
               sum of the values of _diffrn_scan_frame_axis.angle,
               _diffrn_scan_frame_axis.angle_increment
               and  _diffrn_scan_frame_axis.angle_rstrt_incr is the
               angular setting of the axis at the start of the integration
               time for the next frame relative to a given frame and
               should equal _diffrn_scan_frame_axis.angle for this
               next frame.   If the individual frame values
               vary, then the value of
               _diffrn_scan_axis.angle_rstrt_incr will be
               representative
               of the ensemble of values of
               _diffrn_scan_frame_axis.angle_rstrt_incr (e.g.
               the mean).
;
    _item.name                 '_diffrn_scan_axis.angle_rstrt_incr'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_


save__diffrn_scan_axis.displacement_start
    _item_description.description
;              The starting position for the specified axis in millimetres.
;
    _item.name                 '_diffrn_scan_axis.displacement_start'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_


save__diffrn_scan_axis.displacement_range
    _item_description.description
;              The range from the starting position for the specified axis
               in millimetres.
;
    _item.name                 '_diffrn_scan_axis.displacement_range'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_


save__diffrn_scan_axis.displacement_increment
    _item_description.description
;              The increment for each step for the specified axis
               in millimetres.  In general, this will agree with
               _diffrn_scan_frame_axis.displacement_increment.
               The sum of the values of
               _diffrn_scan_frame_axis.displacement and
               _diffrn_scan_frame_axis.displacement_increment is the
               angular setting of the axis at the end of the integration
               time for a given frame.  If the individual frame values
               vary, then the value of
               _diffrn_scan_axis.displacement_increment will be
               representative
               of the ensemble of values of
               _diffrn_scan_frame_axis.displacement_increment (e.g.
               the mean).
;
    _item.name                 '_diffrn_scan_axis.displacement_increment'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_


save__diffrn_scan_axis.displacement_rstrt_incr
    _item_description.description
;              The increment for each step for the specified axis
               in millimetres.  In general, this will agree with
               _diffrn_scan_frame_axis.displacement_rstrt_incr.
               The sum of the values of
               _diffrn_scan_frame_axis.displacement,
               _diffrn_scan_frame_axis.displacement_increment and
               _diffrn_scan_frame_axis.displacement_rstrt_incr is the
               angular setting of the axis at the start of the integration
               time for the next frame relative to a given frame and
               should equal _diffrn_scan_frame_axis.displacement
               for this next frame.  If the individual frame values
               vary, then the value of
               _diffrn_scan_axis.displacement_rstrt_incr will be
               representative
               of the ensemble of values of
               _diffrn_scan_frame_axis.displacement_rstrt_incr (e.g.
               the mean).
;
    _item.name                 '_diffrn_scan_axis.displacement_rstrt_incr'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_

save__diffrn_scan_axis.reference_angle
     _item_description.description
;              The setting of the specified axis in degrees
               against which measurements of the reference beam center
               and reference detector distance should be made.

               In general, this will agree with
               _diffrn_scan_frame_axis.reference_angle.

               If the individual frame values vary, then the value of
               _diffrn_scan_axis.reference_angle will be
               representative of the ensemble of values of
               _diffrn_scan_frame_axis.reference_angle (e.g.
               the mean).

               If not specified, the value defaults to zero.
;
     _item.name                 '_diffrn_scan_axis.reference_angle'
     _item.category_id          diffrn_scan_axis
     _item.mandatory_code       implicit
     _item_default.value        0.0
     _item_type.code            float
     _item_units.code           'degrees'
      save_


save__diffrn_scan_axis.reference_displacement
     _item_description.description
;              The setting of the specified axis in millimetres
               against which measurements of the reference beam center
               and reference detector distance should be made.

               In general, this will agree with
               _diffrn_scan_frame_axis.reference_displacement.

               If the individual frame values vary, then the value of
               _diffrn_scan_axis.reference_displacement will be
               representative of the ensemble of values of
               _diffrn_scan_frame_axis.reference_displacement (e.g.
               the mean).

               If not specified, the value defaults to to the value of
               _diffrn_scan_axis.displacement.
;
     _item.name                 '_diffrn_scan_axis.reference_displacement'
     _item.category_id          diffrn_scan_axis
     _item.mandatory_code       implicit
     _item_type.code            float
     _item_units.code           'millimetres'
      save_



#####################
# DIFFRN_SCAN_FRAME #
#####################

save_DIFFRN_SCAN_FRAME
    _category.description
;           Data items in the DIFFRN_SCAN_FRAME category describe
            the relationships of particular frames to scans.
;
    _category.id                   diffrn_scan_frame
    _category.mandatory_code       no
     loop_
    _category_key.name
                                  '_diffrn_scan_frame.scan_id'
                                  '_diffrn_scan_frame.frame_id'
     loop_
    _category_group.id            'inclusive_group'
                                  'diffrn_group'
     save_


save__diffrn_scan_frame.date
    _item_description.description
;              The date and time of the start of the frame being scanned.
;
    _item.name                 '_diffrn_scan_frame.date'
    _item.category_id          diffrn_scan_frame
    _item.mandatory_code       no
    _item_type.code            yyyy-mm-dd
     save_


save__diffrn_scan_frame.frame_id
    _item_description.description
;              The value of this data item is the identifier of the
               frame being examined.

               This item is a pointer to _diffrn_data_frame.id in the
               DIFFRN_DATA_FRAME category.
;
    _item.name                 '_diffrn_scan_frame.frame_id'
    _item.category_id          diffrn_scan_frame
    _item.mandatory_code       yes
    _item_type.code            code
     save_


save__diffrn_scan_frame.frame_number
    _item_description.description
;              The value of this data item is the number of the frame
               within the scan, starting with 1.  It is not necessarily
               the same as the value of _diffrn_scan_frame.frame_id,
               but it may be.

;
    _item.name                 '_diffrn_scan_frame.frame_number'
    _item.category_id          diffrn_scan_frame
    _item.mandatory_code       no
    _item_type.code            int
     loop_
    _item_range.maximum
    _item_range.minimum
                            .   0
                            0   0
     save_


save__diffrn_scan_frame.integration_time
    _item_description.description
;              The time in seconds to integrate this step of the scan.
               This should be the precise time of integration of each
               particular frame.  The value of this data item should
               be given explicitly for each frame and not inferred
               from the value of _diffrn_scan.integration_time.
;
    _item.name                 '_diffrn_scan_frame.integration_time'
    _item.category_id          diffrn_scan_frame
    _item.mandatory_code       yes
    _item_type.code            float
    _item_units.code           'seconds'
     loop_
    _item_range.maximum
    _item_range.minimum
                            .   0.0
     save_


save__diffrn_scan_frame.scan_id
    _item_description.description
;             The value of _diffrn_scan_frame.scan_id identifies the scan
              containing this frame.

              This item is a pointer to _diffrn_scan.id in the
              DIFFRN_SCAN category.
;
    _item.name             '_diffrn_scan_frame.scan_id'
    _item.category_id        diffrn_scan_frame
    _item.mandatory_code     yes
    _item_type.code          code
     save_


##########################
# DIFFRN_SCAN_FRAME_AXIS #
##########################

save_DIFFRN_SCAN_FRAME_AXIS
    _category.description
;    Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the
     settings of axes for particular frames.  Unspecified axes are
     assumed to be at their zero points.  If, for any given frame,
     nonzero values apply for any of the data items in this category,
     those values should be given explicitly in this category and not
     simply inferred from values in DIFFRN_SCAN_AXIS.
;
    _category.id                   diffrn_scan_frame_axis
    _category.mandatory_code       no
     loop_
    _category_key.name
                                  '_diffrn_scan_frame_axis.frame_id'
                                  '_diffrn_scan_frame_axis.axis_id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     save_


save__diffrn_scan_frame_axis.axis_id
    _item_description.description
;              The value of this data item is the identifier of one of
               the axes for the frame for which settings are being specified.

               Multiple axes may be specified for the same value of
               _diffrn_scan_frame.frame_id.

               This item is a pointer to _axis.id in the
               AXIS category.
;
    _item.name                 '_diffrn_scan_frame_axis.axis_id'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       yes
    _item_type.code            code
     save_


save__diffrn_scan_frame_axis.angle
    _item_description.description
;              The setting of the specified axis in degrees for this frame.
               This is the setting at the start of the integration time.
;
    _item.name                 '_diffrn_scan_frame_axis.angle'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_


save__diffrn_scan_frame_axis.angle_increment
    _item_description.description
;              The increment for this frame for the angular setting of
               the specified axis in degrees.  The sum of the values
               of _diffrn_scan_frame_axis.angle and
               _diffrn_scan_frame_axis.angle_increment is the
               angular setting of the axis at the end of the integration
               time for this frame.
;
    _item.name                 '_diffrn_scan_frame_axis.angle_increment'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_


save__diffrn_scan_frame_axis.angle_rstrt_incr
    _item_description.description
;              The increment after this frame for the angular setting of
               the specified axis in degrees.  The sum of the values
               of _diffrn_scan_frame_axis.angle,
               _diffrn_scan_frame_axis.angle_increment and
               _diffrn_scan_frame_axis.angle_rstrt_incr is the
               angular setting of the axis at the start of the integration
               time for the next frame and should equal
               _diffrn_scan_frame_axis.angle for this next frame.
;
    _item.name               '_diffrn_scan_frame_axis.angle_rstrt_incr'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_


save__diffrn_scan_frame_axis.displacement
    _item_description.description
;              The setting of the specified axis in millimetres for this
               frame.  This is the setting at the start of the integration
               time.
;
    _item.name               '_diffrn_scan_frame_axis.displacement'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_


save__diffrn_scan_frame_axis.displacement_increment
    _item_description.description
;              The increment for this frame for the displacement setting of
               the specified axis in millimetres.  The sum of the values
               of _diffrn_scan_frame_axis.displacement and
               _diffrn_scan_frame_axis.displacement_increment is the
               angular setting of the axis at the end of the integration
               time for this frame.
;
    _item.name               '_diffrn_scan_frame_axis.displacement_increment'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_


save__diffrn_scan_frame_axis.displacement_rstrt_incr
    _item_description.description
;              The increment for this frame for the displacement setting of
               the specified axis in millimetres.  The sum of the values
               of _diffrn_scan_frame_axis.displacement,
               _diffrn_scan_frame_axis.displacement_increment and
               _diffrn_scan_frame_axis.displacement_rstrt_incr is the
               angular setting of the axis at the start of the integration
               time for the next frame and should equal
               _diffrn_scan_frame_axis.displacement for this next frame.
;
    _item.name               '_diffrn_scan_frame_axis.displacement_rstrt_incr'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_

save__diffrn_scan_frame_axis.frame_id
    _item_description.description
;              The value of this data item is the identifier of the
               frame for which axis settings are being specified.

               Multiple axes may be specified for the same value of
               _diffrn_scan_frame.frame_id.

               This item is a pointer to _diffrn_data_frame.id in the
               DIFFRN_DATA_FRAME category.
;
    _item.name               '_diffrn_scan_frame_axis.frame_id'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       yes
    _item_type.code            code
     save_

save__diffrn_scan_frame_axis.reference_angle
     _item_description.description
;              The setting of the specified axis in degrees
               against which measurements of the reference beam center
               and reference detector distance should be made.

               This is normally the same for all frames, but the
               option is provided here of making changes when
               needed.

               If not provided, it is assumed to be zero.
;
     _item.name               '_diffrn_scan_frame_axis.reference_angle'
     _item.category_id          diffrn_scan_frame_axis
     _item.mandatory_code       implicit
     _item_default.value        0.0
     _item_type.code            float
     _item_units.code           'degrees'
      save_


save__diffrn_scan_frame_axis.reference_displacement
     _item_description.description
;              The setting of the specified axis in millimetres for this
               frame against which measurements of the reference beam center
               and reference detector distance should be made.

               This is normally the same for all frames, but the
               option is provided here of making changes when
               needed.

               If not provided, it is assumed to be equal to
               _diffrn_scan_frame_axis.displacement.
;
     _item.name               '_diffrn_scan_frame_axis.reference_displacement'
     _item.category_id          diffrn_scan_frame_axis
     _item.mandatory_code       implicit
     _item_type.code            float
     _item_units.code           'millimetres'
      save_



#######
# MAP #
#######

save_MAP
    _category.description
;             Data items in the MAP category record
              the details of a maps. Maps record values of parameters,
              such as density, that are functions of position within
              a cell or are functions of orthogonal coordinates in
              three space.
              
              A map may is composed of one or more map segments
              specified in the MAP_SEGMENT category.
                            
              Examples are given in the MAP_SEGMENT category.
;
    _category.id                   map
    _category.mandatory_code       no
     loop_
    _category_key.name             '_map.id'
                                   '_map.diffrn_id'
                                   '_map.entry_id'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;   Example 1 - Identifying an observed density map
                and a calculated density map
;
;
        
        loop_
        _map.id
        _map.details
        
        rho_calc
   ;
        density calculated from F_calc derived from the ATOM_SITE list
   ;
        rho_obs
   ;
        density combining the observed structure factors with the
        calculated phases
   ;
;

# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    save_


save__map.details
     _item_description.description
;              The value of _map.details should give a
               description of special aspects of each map.

;
    _item.name                  '_map.details'
    _item.category_id             map
    _item.mandatory_code          no
    _item_type.code               text
     loop_
    _item_examples.case
    _item_examples.detail
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;   Example 1 - Identifying an observed density map
                and a calculated density map
;
;
        
        loop_
        _map.id
        _map.details
        
        rho_calc
    ;
        density calculated from F_calc derived from the ATOM_SITE list
    ;
        rho_obs
    ;
        density combining the observed structure factors with the
        calculated phases
    ;
;

# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
      save_
      
save__map.diffrn_id
    _item_description.description
;             This item is a pointer to _diffrn.id in the
              DIFFRN category.
;
    _item.name                  '_map.diffrn_id'
    _item.category_id             map
    _item.mandatory_code          implicit
    _item_type.code               code
     save_

save__map.entry_id
    _item_description.description
;             This item is a pointer to _entry.id in the
              ENTRY category.
;
    _item.name                  '_map.entry_id'
    _item.category_id             map
    _item.mandatory_code          implicit
    _item_type.code               code
     save_


save__map.id
    _item_description.description
;             The value of _map.id must uniquely identify
              each map for the given diffrn.id or entry.id.
;
     loop_
    _item.name
    _item.category_id
    _item.mandatory_code
           '_map.id'                map          yes
           '_map_segment.id'        map_segment  yes
    _item_type.code               code
     loop_
    _item_linked.child_name
    _item_linked.parent_name
           '_map_segment.id'        '_map.id'
     save_




###########################
# MAP_SEGMENT #
###########################


save_MAP_SEGMENT
    _category.description
;             Data items in the MAP_SEGMENT category record
              the details about each segment (section or brick) of a map. 
;
    _category.id                   map_segment
    _category.mandatory_code       no
     loop_
    _category_key.name             '_map_segment.id'
                                   '_map_segment.map_id'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;   Example 1 - Identifying an observed density map
                and a calculated density map, each consisting of one
                segment, both using the same array structure
                and mask.
;
;
        
        loop_
        _map.id
        _map.details
        
        rho_calc
     ;
        density calculated from F_calc derived from the ATOM_SITE list
     ;
        rho_obs
     ;
        density combining the observed structure factors with the
        calculated phases
     ;

        loop_
        _map_segment.map_id
        _map_segment.id
        _map_segment.array_id
        _map_segment.binary_id
        _map_segment.mask_array_id
        _map_segment.mask_binary_id
        rho_calc rho_calc map_structure 1 mask_structure 1
        rho_obs  rho_obs  map_structure 2 mask_structure 1
;

# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    save_


save__map_segment.array_id
    _item_description.description
;             The value of _map_segment.array_id identifies the array structure 
              into which the map is organized.

              This item is a pointer to _array_structure.id in the
              ARRAY_STRUCTURE category.
;
    _item.name                  '_map_segment.array_id'
    _item.category_id             map_segment
    _item.mandatory_code          implicit
    _item_type.code               code
     save_


save__map_segment.binary_id
    _item_description.description
;             The value of _map_segment.binary_id distinguishes the particular 
              set of data organized according to _map_segment.array_id in 
              which the data values of the map are stored.

              This item is a pointer to _array_data.binary_id in the
              ARRAY_DATA category.
;
    _item.name                  '_map_segment.binary_id'
    _item.category_id             map_segment
    _item.mandatory_code          implicit
    _item_type.code               int
     save_

save__map_segment.mask_array_id
    _item_description.description
;             The value of _map_segment.mask_array_id, if given, the array 
              structure into which the mask for the map is organized.  If no 
              value is given, then all elements of the map are valid.  If a 
              value is given, then only elements of the map for which the 
              corresponding element of the mask is non-zero are valid.  The 
              value of _map_segment.mask_array_id differs from the value of
              _map_segment.array_id in order to permit the mask to be given
              as, say, unsigned 8-bit integers, while the map is given as
              a data type with more range.  However, the two array structures
              must be aligned, using the same axes in the same order with the
              same displacements and increments

              This item is a pointer to _array_structure.id in the
              ARRAY_STRUCTURE category.
;
    _item.name                  '_map_segment.mask_array_id'
    _item.category_id             map_segment
    _item.mandatory_code          implicit
    _item_type.code               code
     save_


save__map_segment.mask_binary_id
    _item_description.description
;             The value of _map_segment.mask_binary_id identifies the 
              particular set of data organized according to 
              _map_segment.mask_array_id specifying the mask for the map.

              This item is a pointer to _array_data.mask_binary_id in the
              ARRAY_DATA category.
;
    _item.name                  '_map_segment.mask_binary_id'
    _item.category_id             map_segment
    _item.mandatory_code          implicit
    _item_type.code               int
     save_


save__map_segment.id
    _item_description.description
;             The value of _map_segment.id must uniquely
              identify each segment of a map.
;
     loop_
    _item.name
    _item.category_id
    _item.mandatory_code
           '_map_segment.id'
           map_segment
           yes
    _item_type.code               code
     loop_
    _item_linked.child_name
    _item_linked.parent_name
           '_map_data_frame.map_segment_id'
           '_map_segment.id'

     save_


save__map_segment.map_id
    _item_description.description
;              This item is a pointer to _map.id
               in the MAP category.
;
    _item.name                  '_map_segment.map_id'
    _item.category_id             map_segment
    _item.mandatory_code          yes
    _item_type.code               code
     save_

save__map_segment.details
     _item_description.description
;              The value of _map_segment.details should give a
               description of special aspects of each segment of a map.

;
    _item.name                  '_map_segment.details'
    _item.category_id             map_segment
    _item.mandatory_code          no
    _item_type.code               text
     loop_
    _item_examples.case
    _item_examples.detail
;               Example to be provided
;
;               

;
      save_


########################   DEPRECATED DATA ITEMS ########################

save__diffrn_detector_axis.id
    _item_description.description
;              This data item is a pointer to _diffrn_detector.id in
               the DIFFRN_DETECTOR category.

               DEPRECATED -- DO NOT USE
;
    _item.name                  '_diffrn_detector_axis.id'
    _item.category_id             diffrn_detector_axis
    _item.mandatory_code          yes
    _item_type.code               code
     save_

save__diffrn_detector_element.center[1]
    _item_description.description
;             The value of _diffrn_detector_element.center[1] is the X
              component of the distortion-corrected beam centre in
              millimetres from the (0, 0) (lower-left) corner of the
              detector element viewed from the sample side.

              The X and Y axes are the laboratory coordinate system
              coordinates defined in the AXIS category measured
              when all positioning axes for the detector are at their zero
              settings.  If the resulting X or Y axis is then orthogonal to the
              detector, the Z axis is used instead of the orthogonal axis.
              
              Because of ambiguity about the setting used to determine this center,
              use of this data item is deprecated.  The data item
              _diffrn_data_frame.center_fast
              which is referenced to the detector coordinate system and not
              directly to the laboratory coordinate system should be used instead.

;
    _item.name                  '_diffrn_detector_element.center[1]'
    _item.category_id             diffrn_detector_element
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
    _item_units.code              millimetres

    save_


save__diffrn_detector_element.center[2]
    _item_description.description
;             The value of _diffrn_detector_element.center[2] is the Y
              component of the distortion-corrected beam centre in
              millimetres from the (0, 0) (lower-left) corner of the
              detector element viewed from the sample side.

              The X and Y axes are the laboratory coordinate system
              coordinates defined in the AXIS category measured
              when all positioning axes for the detector are at their zero
              settings.  If the resulting X or Y axis is then orthogonal to the
              detector, the Z axis is used instead of the orthogonal axis.
              
              Because of ambiguity about the setting used to determine this center,
              use of this data item is deprecated. The data item
              _diffrn_data_frame.center_slow
              which is referenced to the detector coordinate system and not
              directly to the laboratory coordinate system should be used instead.


;
    _item.name                  '_diffrn_detector_element.center[2]'
    _item.category_id             diffrn_detector_element
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
    _item_units.code              millimetres

    save_



save__diffrn_measurement_axis.id
    _item_description.description
;              This data item is a pointer to _diffrn_measurement.id in
               the DIFFRN_MEASUREMENT category.

               DEPRECATED -- DO NOT USE
;
    _item.name                  '_diffrn_measurement_axis.id'
    _item.category_id             diffrn_measurement_axis
    _item.mandatory_code          yes
    _item_type.code               code
     save_

#########################   DEPRECATED CATEGORY #########################
#####################
# DIFFRN_FRAME_DATA #
#####################


save_DIFFRN_FRAME_DATA
    _category.description
;             Data items in the DIFFRN_FRAME_DATA category record
              the details about each frame of data.

              The items in this category are now in the
              DIFFRN_DATA_FRAME category.

              The items in the DIFFRN_FRAME_DATA category
              are now deprecated.  The items from this category
              are provided as aliases in the 1.0 dictionary
              or, in the case of _diffrn_frame_data.details,
              in the 1.4 dictionary.  THESE ITEMS SHOULD NOT
              BE USED FOR NEW WORK.

              The items from the old category are provided
              in this dictionary for completeness
              but should not be used or cited.  To avoid
              confusion, the example has been removed
              and the redundant parent-child links to other
              categories have been removed.
;
    _category.id                   diffrn_frame_data
    _category.mandatory_code       no
     loop_
    _category_key.name             '_diffrn_frame_data.id'
                                   '_diffrn_frame_data.detector_element_id'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
    THE DIFFRN_FRAME_DATA category is deprecated and should not be used.
;
;
       # EXAMPLE REMOVED #
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    save_


save__diffrn_frame_data.array_id
    _item_description.description
;             This item is a pointer to _array_structure.id in the
              ARRAY_STRUCTURE category.

              DEPRECATED -- DO NOT USE
;
    _item.name                  '_diffrn_frame_data.array_id'
    _item.category_id             diffrn_frame_data
    _item.mandatory_code          implicit
    _item_type.code               code
     save_


save__diffrn_frame_data.binary_id
    _item_description.description
;             This item is a pointer to _array_data.binary_id in the
              ARRAY_STRUCTURE category.

              DEPRECATED -- DO NOT USE
;
    _item.name                  '_diffrn_frame_data.binary_id'
    _item.category_id             diffrn_frame_data
    _item.mandatory_code          implicit
    _item_type.code               int
     save_


save__diffrn_frame_data.detector_element_id
    _item_description.description
;             This item is a pointer to _diffrn_detector_element.id
              in the DIFFRN_DETECTOR_ELEMENT category.

              DEPRECATED -- DO NOT USE
;
    _item.name                  '_diffrn_frame_data.detector_element_id'
    _item.category_id             diffrn_frame_data
    _item.mandatory_code          yes
    _item_type.code               code
     save_


save__diffrn_frame_data.id
    _item_description.description
;             The value of _diffrn_frame_data.id must uniquely identify
              each complete frame of data.

              DEPRECATED -- DO NOT USE
;
     loop_
    _item.name
    _item.category_id
    _item.mandatory_code
           '_diffrn_frame_data.id'        diffrn_frame_data  yes
    _item_type.code               code
     save_

save__diffrn_frame_data.details
     _item_description.description
;             The value of _diffrn_data_frame.details should give a
              description of special aspects of each frame of data.

              DEPRECATED -- DO NOT USE
;
     _item.name                  '_diffrn_frame_data.details'
     _item.category_id             diffrn_frame_data
     _item.mandatory_code          no
     _item_type.code               text
      save_

################ END DEPRECATED SECTION ###########


####################
## ITEM_TYPE_LIST ##
####################
#
#
#  The regular expressions defined here are not compliant
#  with the POSIX 1003.2 standard as they include the
#  '\n' and '\t' special characters.  These regular expressions
#  have been tested using version 0.12 of Richard Stallman's
#  GNU regular expression library in POSIX mode.
#  In order to allow presentation of a regular expression
#  in a text field concatenate any line ending in a backslash
#  with the following line, after discarding the backslash.
#
#  A formal definition of the '\n' and '\t' special characters
#  is most properly done in the DDL, but for completeness, please
#  note that '\n' is the line termination character ('newline')
#  and '\t' is the horizontal tab character.  There is a formal
#  ambiguity in the use of '\n' for line termination, in that
#  the intention is that the equivalent machine/OS-dependent line
#  termination character sequence should be accepted as a match, e.g.
#
#      '\r' (control-M) under MacOS
#      '\n' (control-J) under Unix
#      '\r\n' (control-M control-J) under DOS and MS Windows
#
     loop_
    _item_type_list.code
    _item_type_list.primitive_code
    _item_type_list.construct
    _item_type_list.detail
               code      char
               '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*'
;              code item types/single words ...
;
               ucode      uchar
               '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*'
;              code item types/single words (case insensitive) ...
;
               line      char
               '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*'
;              char item types / multi-word items ...
;
               uline     uchar
               '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*'
;              char item types / multi-word items (case insensitive)...
;
               text      char
             '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*'
;              text item types / multi-line text ...
;
               binary    char
;\n--CIF-BINARY-FORMAT-SECTION--\n\
[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\
\n--CIF-BINARY-FORMAT-SECTION----
;
;              binary items are presented as MIME-like ascii-encoded
               sections in an imgCIF.  In a CBF, raw octet streams
               are used to convey the same information.
;
               int       numb
               '-?[0-9]+'
;              int item types are the subset of numbers that are the negative
               or positive integers.
;
               float     numb
          '-?(([0-9]+)[.]?|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?'
;              float item types are the subset of numbers that are the floating
               point numbers.
;
               any       char
               '.*'
;              A catch all for items that may take any form...
;
               yyyy-mm-dd  char
;\
[0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9]?[0-9]\
((T[0-2][0-9](:[0-5][0-9](:[0-5][0-9](.[0-9]+)?)?)?)?\
([+-][0-5][0-9]:[0-5][0-9]))?
;
;
               Standard format for CIF date and time strings (see
               http://www.iucr.org/iucr-top/cif/spec/datetime.html),
               consisting of a yyyy-mm-dd date optionally followed by
               the character 'T' followed by a 24-hour clock time,
               optionally followed by a signed time-zone offset.

               The IUCr standard has been extended to allow for an optional
               decimal fraction on the seconds of time.

               Time is local time if no time-zone offset is given.

               Note that this type extends the mmCIF yyyy-mm-dd type
               but does not conform to the mmCIF yyyy-mm-dd:hh:mm
               type that uses a ':' in place if the 'T' specified
               by the IUCr standard.  For reading, both forms should
               be accepted,  but for writing, only the IUCr form should
               be used.

               For maximal compatibility, the special time zone
               indicator 'Z' (for 'zulu') should be accepted on
               reading in place of '+00:00' for GMT.
;


#####################
## ITEM_UNITS_LIST ##
#####################

     loop_
    _item_units_list.code
    _item_units_list.detail
#
     'metres'                 'metres'
     'centimetres'            'centimetres (metres * 10^( -2)^)'
     'millimetres'            'millimetres (metres * 10^( -3)^)'
     'nanometres'             'nanometres  (metres * 10^( -9)^)'
     'angstroms'              '\%Angstroms   (metres * 10^(-10)^)'
     'picometres'             'picometres  (metres * 10^(-12)^)'
     'femtometres'            'femtometres (metres * 10^(-15)^)'
#
     'reciprocal_metres'      'reciprocal metres (metres^(-1)^)'
     'reciprocal_centimetres'
        'reciprocal centimetres ((metres * 10^( -2)^)^(-1)^)'
     'reciprocal_millimetres'
        'reciprocal millimetres ((metres * 10^( -3)^)^(-1)^)'
     'reciprocal_nanometres'
        'reciprocal nanometres  ((metres * 10^( -9)^)^(-1)^)'
     'reciprocal_angstroms'
        'reciprocal \%Angstroms   ((metres * 10^(-10)^)^(-1)^)'
     'reciprocal_picometres'
        'reciprocal picometres  ((metres * 10^(-12)^)^(-1)^)'
#
     'nanometres_squared'     'nanometres squared (metres * 10^( -9)^)^2^'
     'angstroms_squared'      '\%Angstroms squared  (metres * 10^(-10)^)^2^'
     '8pi2_angstroms_squared'
       '8\p^2^ * \%Angstroms squared (metres * 10^(-10)^)^2^'
     'picometres_squared'     'picometres squared (metres * 10^(-12)^)^2^'
#
     'nanometres_cubed'       'nanometres cubed (metres * 10^( -9)^)^3^'
     'angstroms_cubed'        '\%Angstroms cubed  (metres * 10^(-10)^)^3^'
     'picometres_cubed'       'picometres cubed (metres * 10^(-12)^)^3^'
#
     'kilopascals'            'kilopascals'
     'gigapascals'            'gigapascals'
#
     'hours'                  'hours'
     'minutes'                'minutes'
     'seconds'                'seconds'
     'microseconds'           'microseconds'
#
     'degrees'                'degrees (of arc)'
     'degrees_squared'        'degrees (of arc) squared'
#
     'degrees_per_minute'     'degrees (of arc) per minute'
#
     'celsius'                'degrees (of temperature) Celsius'
     'kelvins'                'degrees (of temperature) Kelvin'
#
     'counts'                 'counts'
     'counts_per_photon'      'counts per photon'
#
     'electrons'              'electrons'
#
     'electrons_squared'      'electrons squared'
#
     'electrons_per_nanometres_cubed'
; electrons per nanometres cubed (electrons/(metres * 10^( -9)^)^(-3)^)
;
     'electrons_per_angstroms_cubed'
; electrons per \%Angstroms cubed (electrons/(metres * 10^(-10)^)^(-3)^)
;
     'electrons_per_picometres_cubed'
; electrons per picometres cubed (electrons/(metres * 10^(-12)^)^(-3)^)
;
     'kilowatts'              'kilowatts'
     'milliamperes'           'milliamperes'
     'kilovolts'              'kilovolts'
#
     'pixels_per_element'     '(image) pixels per (array) element'
#
     'arbitrary'
; arbitrary system of units.
;
#

     loop_
    _item_units_conversion.from_code
    _item_units_conversion.to_code
    _item_units_conversion.operator
    _item_units_conversion.factor
###
     'metres'                   'centimetres'              '*'   1.0E+02
     'metres'                   'millimetres'              '*'   1.0E+03
     'metres'                   'nanometres'               '*'   1.0E+09
     'metres'                   'angstroms'                '*'   1.0E+10
     'metres'                   'picometres'               '*'   1.0E+12
     'metres'                   'femtometres'              '*'   1.0E+15
#
     'centimetres'              'metres'                   '*'   1.0E-02
     'centimetres'              'millimetres'              '*'   1.0E+01
     'centimetres'              'nanometres'               '*'   1.0E+07
     'centimetres'              'angstroms'                '*'   1.0E+08
     'centimetres'              'picometres'               '*'   1.0E+10
     'centimetres'              'femtometres'              '*'   1.0E+13
#
     'millimetres'              'metres'                   '*'   1.0E-03
     'millimetres'              'centimetres'              '*'   1.0E-01
     'millimetres'              'nanometres'               '*'   1.0E+06
     'millimetres'              'angstroms'                '*'   1.0E+07
     'millimetres'              'picometres'               '*'   1.0E+09
     'millimetres'              'femtometres'              '*'   1.0E+12
#
     'nanometres'               'metres'                   '*'   1.0E-09
     'nanometres'               'centimetres'              '*'   1.0E-07
     'nanometres'               'millimetres'              '*'   1.0E-06
     'nanometres'               'angstroms'                '*'   1.0E+01
     'nanometres'               'picometres'               '*'   1.0E+03
     'nanometres'               'femtometres'              '*'   1.0E+06
#
     'angstroms'                'metres'                   '*'   1.0E-10
     'angstroms'                'centimetres'              '*'   1.0E-08
     'angstroms'                'millimetres'              '*'   1.0E-07
     'angstroms'                'nanometres'               '*'   1.0E-01
     'angstroms'                'picometres'               '*'   1.0E+02
     'angstroms'                'femtometres'              '*'   1.0E+05
#
     'picometres'               'metres'                   '*'   1.0E-12
     'picometres'               'centimetres'              '*'   1.0E-10
     'picometres'               'millimetres'              '*'   1.0E-09
     'picometres'               'nanometres'               '*'   1.0E-03
     'picometres'               'angstroms'                '*'   1.0E-02
     'picometres'               'femtometres'              '*'   1.0E+03
#
     'femtometres'              'metres'                   '*'   1.0E-15
     'femtometres'              'centimetres'              '*'   1.0E-13
     'femtometres'              'millimetres'              '*'   1.0E-12
     'femtometres'              'nanometres'               '*'   1.0E-06
     'femtometres'              'angstroms'                '*'   1.0E-05
     'femtometres'              'picometres'               '*'   1.0E-03
###
     'reciprocal_centimetres'   'reciprocal_metres'        '*'   1.0E+02
     'reciprocal_centimetres'   'reciprocal_millimetres'   '*'   1.0E-01
     'reciprocal_centimetres'   'reciprocal_nanometres'    '*'   1.0E-07
     'reciprocal_centimetres'   'reciprocal_angstroms'     '*'   1.0E-08
     'reciprocal_centimetres'   'reciprocal_picometres'    '*'   1.0E-10
#
     'reciprocal_millimetres'   'reciprocal_metres'        '*'   1.0E+03
     'reciprocal_millimetres'   'reciprocal_centimetres'   '*'   1.0E+01
     'reciprocal_millimetres'   'reciprocal_nanometres'    '*'   1.0E-06
     'reciprocal_millimetres'   'reciprocal_angstroms'     '*'   1.0E-07
     'reciprocal_millimetres'   'reciprocal_picometres'    '*'   1.0E-09
#
     'reciprocal_nanometres'    'reciprocal_metres'        '*'   1.0E+09
     'reciprocal_nanometres'    'reciprocal_centimetres'   '*'   1.0E+07
     'reciprocal_nanometres'    'reciprocal_millimetres'   '*'   1.0E+06
     'reciprocal_nanometres'    'reciprocal_angstroms'     '*'   1.0E-01
     'reciprocal_nanometres'    'reciprocal_picometres'    '*'   1.0E-03
#
     'reciprocal_angstroms'     'reciprocal_metres'        '*'   1.0E+10
     'reciprocal_angstroms'     'reciprocal_centimetres'   '*'   1.0E+08
     'reciprocal_angstroms'     'reciprocal_millimetres'   '*'   1.0E+07
     'reciprocal_angstroms'     'reciprocal_nanometres'    '*'   1.0E+01
     'reciprocal_angstroms'     'reciprocal_picometres'    '*'   1.0E-02
#
     'reciprocal_picometres'    'reciprocal_metres'        '*'   1.0E+12
     'reciprocal_picometres'    'reciprocal_centimetres'   '*'   1.0E+10
     'reciprocal_picometres'    'reciprocal_millimetres'   '*'   1.0E+09
     'reciprocal_picometres'    'reciprocal_nanometres'    '*'   1.0E+03
     'reciprocal_picometres'    'reciprocal_angstroms'     '*'   1.0E+01
###
     'nanometres_squared'       'angstroms_squared'        '*'   1.0E+02
     'nanometres_squared'       'picometres_squared'       '*'   1.0E+06
#
     'angstroms_squared'        'nanometres_squared'       '*'   1.0E-02
     'angstroms_squared'        'picometres_squared'       '*'   1.0E+04
     'angstroms_squared'        '8pi2_angstroms_squared'   '*'   78.9568

#
     'picometres_squared'       'nanometres_squared'       '*'   1.0E-06
     'picometres_squared'       'angstroms_squared'        '*'   1.0E-04
###
     'nanometres_cubed'         'angstroms_cubed'          '*'   1.0E+03
     'nanometres_cubed'         'picometres_cubed'         '*'   1.0E+09
#
     'angstroms_cubed'          'nanometres_cubed'         '*'   1.0E-03
     'angstroms_cubed'          'picometres_cubed'         '*'   1.0E+06
#
     'picometres_cubed'         'nanometres_cubed'         '*'   1.0E-09
     'picometres_cubed'         'angstroms_cubed'          '*'   1.0E-06
###
     'kilopascals'              'gigapascals'              '*'   1.0E-06
     'gigapascals'              'kilopascals'              '*'   1.0E+06
###
     'hours'                    'minutes'                  '*'   6.0E+01
     'hours'                    'seconds'                  '*'   3.6E+03
     'hours'                    'microseconds'             '*'   3.6E+09
#
     'minutes'                  'hours'                    '/'   6.0E+01
     'minutes'                  'seconds'                  '*'   6.0E+01
     'minutes'                  'microseconds'             '*'   6.0E+07
#
     'seconds'                  'hours'                    '/'   3.6E+03
     'seconds'                  'minutes'                  '/'   6.0E+01
     'seconds'                  'microseconds'             '*'   1.0E+06
#
     'microseconds'             'hours'                    '/'   3.6E+09
     'microseconds'             'minutes'                  '/'   6.0E+07
     'microseconds'             'seconds'                  '/'   1.0E+06
###
     'celsius'                  'kelvins'                  '-'     273.0
     'kelvins'                  'celsius'                  '+'     273.0
###
     'electrons_per_nanometres_cubed'
     'electrons_per_angstroms_cubed'                       '*'   1.0E+03
     'electrons_per_nanometres_cubed'
     'electrons_per_picometres_cubed'                      '*'   1.0E+09
#
     'electrons_per_angstroms_cubed'
     'electrons_per_nanometres_cubed'                      '*'   1.0E-03
     'electrons_per_angstroms_cubed'
     'electrons_per_picometres_cubed'                      '*'   1.0E+06
#
     'electrons_per_picometres_cubed'
     'electrons_per_nanometres_cubed'                      '*'   1.0E-09
     'electrons_per_picometres_cubed'
     'electrons_per_angstroms_cubed'                       '*'   1.0E-06
###

########################
## DICTIONARY_HISTORY ##
########################

     loop_
    _dictionary_history.version
    _dictionary_history.update
    _dictionary_history.revision
   
   1.5.3   2007-07-08
   
;  Changes to support SLS miniCBF and suggestions
   from the 24 May 07 BNL imgCIF workshop (HJB)
 
     + Added new data items
       '_array_data.header_contents',
       '_array_data.header_convention',
       '_diffrn_data_frame.center_fast',
       '_diffrn_data_frame.center_slow',
       '_diffrn_data_frame.center_units',
       '_diffrn_measurement.sample_detector_distance',
       '_diffrn_measurement.sample_detector_voffset
     + Deprecated data items
       '_diffrn_detector_element.center[1]',
       '_diffrn_detector_element.center[2]'
     + Added comments and example on miniCBF
     + Changed all array_id data items to implicit
;
   
   1.5.2   2007-05-06
   
;  Further clarifications of the coordinate system. (HJB)
;

   1.5.1   2007-04-26
   
;  Improve defintion of X-axis to cover the case of no goniometer
   and clean up more line folds (HJB)
;

   1.5     2007-07-25
   
;  This is a cummulative list of the changes proposed since the
   imgCIF workshop in Hawaii in July 2006.  It is the result
   of contributions by H. J. Bernstein, A. Hammersley,
   J. Wright and W. Kabsch.
   
   2007-02-19 Consolidated changes (edited by HJB)
     + Added new data items
       '_array_structure.compression_type_flag',
       '_array_structure_list_axis.fract_displacement',
       '_array_structure_list_axis.displacement_increment',
       '_array_structure_list_axis.reference_angle',
       '_array_structure_list_axis.reference_displacement',
       '_axis.system',
       '_diffrn_detector_element.reference_center_fast',
       '_diffrn_detector_element.reference_center_slow',
       '_diffrn_scan_axis.reference_angle',
       '_diffrn_scan_axis.reference_displacement',
       '_map.details', '_map.diffrn_id',
       '_map.entry_id', '_map.id',
       '_map_segment.array_id', '_map_segment.binary_id',
       '_map_segment.mask_array_id', '_map_segment.mask_binary_id',
       '_map_segment.id', '_map_segment.map_id',
       '_map_segment.details.
     + Change type of 
       '_array_structure.byte_order' and
       '_array_structure.compression_type'
       to ucode to make these values case-insensitive
     + Add values 'packed_v2' and 'byte_offset' to enumeration of values for
       '_array_structure.compression_type'
     + Add to defintions for the binary data type to handle new compression types, maps,
       and a variety of new axis types.
    2007-07-25 Cleanup of typos for formal release (HJB)
     + Corrected text fields for reference_ tag descriptions that
       were off by one column
     + Fix typos in comments listing fract_ tags
     + Changed name of release from 1.5_DRAFT to 1.5
     + Fix unclosed text fields in various map definitions
      
;

   1.4     2006-07-04

;  This is a change to reintegrate all changes made in the course of
   publication of ITVG, by the RCSB from April 2005 through
   August 2008 and changes for the 2006 imgCIF workshop in
   Hawaii.

   2006-07-04 Consolidated changes for the 2006 imgCIF workshop (edited by HJB)
     + Correct type of '_array_structure_list.direction' from 'int' to 'code'.
     + Added new data items suggested by CN
       '_diffrn_data_frame.details'
       '_array_intensities.pixel_fast_bin_size',
       '_array_intensities.pixel_slow_bin_size and
       '_array_intensities.pixel_binning_method
     + Added deprecated item for completeness
       '_diffrn_frame_data.details'
     + Added entry for missing item in contents list
       '_array_structure_list_axis.displacement'
     + Added new MIME type X-BASE32K based on work by VL, KM, GD, HJB
     + Correct description of MIME boundary delimiter to start in
       column 1.
     + General cleanup of text fields to conform to changes for ITVG
       by removing empty lines at start and finish of text field.
     + Amend example for ARRAY_INTENSITIES to include binning.
     + Add local copy of type specification (as 'code') for all children
       of '_diffrn.id'.
     + For consistency, change all references to 'pi' to '\p' and all
       references to 'Angstroms' to '\%Angstroms'.
     + Clean up all powers to use IUCr convention of '^power^', as in
       '10^3^' for '10**3'.
     + Update 'yyyy-mm-dd' type regex to allow truncation from the right
       and improve comments to explain handling of related mmCIF
       'yyyy-mm-dd:hh:mm' type, and use of 'Z' for GMT time zone.

   2005-03-08 and
   2004-08-08 fixed cases where _item_units.code  used
              instead of _item_type.code (JDW)
   2004-04-15 fixed item ordering in
               _diffrn_measurement_axis.measurement_id
               added sub_category 'vector' (JDW)
;

   1.3.2   2005-06-25

;  2005-06-25 ITEM_TYPE_LIST: code, ucode, line, uline regexps updated
              to those of current mmCIF; float modified by allowing integers
              terminated by a point as valid. The 'time' part of
              yyyy-mm-dd types made optional in the regexp. (BM)

   2005-06-17 Minor corrections as for proofs for IT G Chapter 4.6
   (NJA)

   2005-02-21  Minor corrections to spelling and punctuation
   (NJA)

   2005-01-08 Changes as per Nicola Ashcroft.
   + Updated example 1 for DIFFRN_MEASUREMENT to agree with mmCIF.
   + Spelled out "micrometres" for "um" and "millimetres" for "mm".
   + Removed phrase "which may be stored" from ARRAY_STRUCTURE
     description.
   + Removed unused 'byte-offsets' compressions and updated
     cites to ITVG for '_array_structure.compression_type'.
   (HJB)
;

   1.3.1   2003-08-13
;
   Changes as per Frances C. Bernstein.
   + Identify initials.
   + Adopt British spelling for centre in text.
   + Set \p and \%Angstrom and powers.
   + Clean up commas and unclear wordings.
   + Clean up tenses in history.
   Changes as per Gotzon Madariaga.
   + Fix the ARRAY_DATA example to align '_array_data.binary_id'
   and X-Binary-ID.
   + Add a range to '_array_intensities.gain_esd'.
   + In the example of DIFFRN_DETECTOR_ELEMENT,
   '_diffrn_detector_element.id' and
   '_diffrn_detector_element.detector_id' interchanged.
   + Fix typos for direction, detector and axes.
   + Clarify description of polarisation.
   + Clarify axes in '_diffrn_detector_element.center[1]'
    '_diffrn_detector_element.center[2]'.
   + Add local item types for items that are pointers.
   (HJB)
;


   1.3.0   2003-07-24
;
   Changes as per Brian McMahon.
   + Consistently quote tags embedded in text.
   + Clean up introductory comments.
   + Adjust line lengths to fit in 80 character window.
   + Fix several descriptions in AXIS category which
     referred to '_axis.type' instead of the current item.
   + Fix erroneous use of deprecated item
     '_diffrn_detector_axis.id' in examples for
     DIFFRN_SCAN_AXIS.
   + Add deprecated items '_diffrn_detector_axis.id'
     and '_diffrn_measurement_axis.id'.
   (HJB)
;


   1.2.4   2003-07-14
;
   Changes as per I. David Brown.
   + Enhance descriptions in DIFFRN_SCAN_AXIS to make them less
     dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS.
   + Provide a copy of the deprecated DIFFRN_FRAME_DATA
     category for completeness.
   (HJB)
;


   1.2.3   2003-07-03
;
   Cleanup to conform to ITVG.
   + Correct sign error in ..._cubed units.
   + Correct '_diffrn_radiation.polarisn_norm' range.
   (HJB)
;


   1.2.2   2003-03-10
;
   Correction of typos in various DIFFRN_SCAN_AXIS descriptions.
   (HJB)
;


   1.2.1   2003-02-22
;
   Correction of ATOM_ for ARRAY_ typos in various descriptions.
   (HJB)
;


   1.2     2003-02-07
;
   Corrections to encodings (remove extraneous hyphens) remove
   extraneous underscore in '_array_structure.encoding_type'
   enumeration.  Correct typos in items units list.  (HJB)
;


   1.1.3   2001-04-19
;
   Another typo corrections by Wilfred Li, and cleanup by HJB.
;


   1.1.2   2001-03-06
;
   Several typo corrections by Wilfred Li.
;


   1.1.1   2001-02-16
;
   Several typo corrections by JW.
;


   1.1     2001-02-06
;
   Draft resulting from discussions on header for use at NSLS.  (HJB)

   + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME.

   + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'.

   + Add '_diffrn_measurement_axis.measurement_device' and change
     '_diffrn_measurement_axis.id' to
     '_diffrn_measurement_axis.measurement_id'.

   + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source',
    '_diffrn_radiation.div_x_y_source',
    '_diffrn_radiation.polarizn_source_norm',
   '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end',
   '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr',
   '_diffrn_scan_axis.displacement_rstrt_incr',
   '_diffrn_scan_frame_axis.angle_increment',
   '_diffrn_scan_frame_axis.angle_rstrt_incr',
   '_diffrn_scan_frame_axis.displacement',
   '_diffrn_scan_frame_axis.displacement_increment',and
   '_diffrn_scan_frame_axis.displacement_rstrt_incr'.

   + Add '_diffrn_measurement.device' to category key.

   + Update yyyy-mm-dd to allow optional time with fractional seconds
     for time stamps.

   + Fix typos caught by RS.

   + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to
     allow for coupled axes, as in spiral scans.

   + Add examples for fairly complete headers thanks to R. Sweet and P.
     Ellis.
;


   1.0     2000-12-21
;
   Release version - few typos and tidying up.  (BM & HJB)

   + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end
   of dictionary.

   + Alphabetize dictionary.
;


   0.7.1   2000-09-29
;
   Cleanup fixes.  (JW)

   + Correct spelling of diffrn_measurement_axis in '_axis.id'

   + Correct ordering of uses of '_item.mandatory_code' and
   '_item_default.value'.
;


   0.7.0   2000-09-09
;
   Respond to comments by I. David Brown.  (HJB)

   + Add further comments on '\n' and '\t'.

   + Update ITEM_UNITS_LIST by taking section from mmCIF dictionary
     and adding metres.  Change 'meter' to 'metre' throughout.

   + Add missing enumerations to '_array_structure.compression_type'
     and make 'none' the default.

   + Remove parent-child relationship between
     '_array_structure_list.index' and '_array_structure_list.precedence'.

   + Improve alphabetization.

   + Fix '_array_intensities_gain.esd' related function.

   + Improve comments in AXIS.

   + Fix DIFFRN_FRAME_DATA example.

   + Remove erroneous DIFFRN_MEASUREMENT example.

   + Add '_diffrn_measurement_axis.id' to the category key.
;


   0.6.0   1999-01-14
;
   Remove redundant information for ENC_NONE data.  (HJB)

   + After the D5 remove binary section identifier, size and
     compression type.

   + Add Control-L to header.
;


   0.5.1   1999-01-03
;
   Cleanup of typos and syntax errors.  (HJB)

   + Cleanup example details for DIFFRN_SCAN category.

   + Add missing quote marks for '_diffrn_scan.id' definition.
;


   0.5   1999-01-01
;
   Modifications for axis definitions and reduction of binary header.  (HJB)

   + Restore '_diffrn_detector.diffrn_id' to DIFFRN_DETECTOR KEY.

   + Add AXIS category.

   + Bring in complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories
     from cif_mm.dic for clarity.

   + Change '_array_structure.encoding_type' from type code to uline and
     added X-Binary-Element-Type to MIME header.

   + Add detector beam centre '_diffrn_detector_element.center[1]' and
     '_diffrn_detector_element.center[2]'.

   + Correct item name of '_diffrn_refln.frame_id'.

   + Replace reference to '_array_intensities.undefined' by
     '_array_intensities.undefined_value'.

   + Replace references to '_array_intensity.scaling' with
     '_array_intensities.scaling'.

   + Add DIFFRN_SCAN... categories.
;


   0.4   1998-08-11
;
   Modifications to the 0.3 imgCIF draft.  (HJB)

   + Reflow comment lines over 80 characters and corrected typos.

   + Update examples and descriptions of MIME encoded data.

   + Change name to cbfext98.dic.
;


   0.3   1998-07-04
;
   Modifications for imgCIF.  (HJB)

   + Add binary type, which is a text field containing a variant on
     MIME encoded data.

   + Change type of '_array_data.data' to binary and specify internal
     structure of raw binary data.

   + Add '_array_data.binary_id', and make
     '_diffrn_frame_data.binary_id' and '_array_intensities.binary_id'
     into pointers to this item.
;


   0.2   1997-12-02
;
   Modifications to the CBF draft.  (JW)

   + Add category hierarchy for describing frame data developed from
     discussions at the BNL imgCIF Workshop Oct 1997.   The following
     changes are made in implementing the workshop draft.  Category
     DIFFRN_ARRAY_DATA is renamed to DIFFRN_FRAME_DATA.  Category
     DIFFRN_FRAME_TYPE is renamed to DIFFRN_DETECTOR_ELEMENT.   The
     parent item for '_diffrn_frame_data.array_id' is changed from
     '_array_structure_list.array_id' to '_array_structure.id'. Item
     '_diffrn_detector.array_id' is deleted.
   + Add data item '_diffrn_frame_data.binary_id' to identify data
     groups within a binary section.  The formal identification of the
     binary section is still fuzzy.
;


   0.1   1997-01-24
;
   First draft of this dictionary in DDL 2.1 compliant format by John
   Westbrook (JW).  This version is adapted from the Crystallographic
   Binary File (CBF) Format Draft Proposal provided by Andy Hammersley
   (AH).

   Modifications to the CBF draft.  (JW)

   + In this version the array description has been cast in the categories
     ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST.  These categories
     have been generalized to describe array data  of arbitrary dimension.

   + Array data in this description are contained in the category
     ARRAY_DATA.  This departs from the CBF notion of data existing
     in some special comment. In this description, data are handled as an
     ordinary data item encapsulated in a character data type.   Although
     data this manner deviates from CIF conventions, it does not violate
     any DDL 2.1 rules.  DDL 2.1 regular expressions can be used to define
     the binary representation which will permit some level of data
     validation.  In this version, the placeholder type code "any" has
     been used. This translates to a regular expression which will match
     any pattern.

     It should be noted that DDL 2.1 already supports array data objects
     although these have not been used in the current mmCIF dictionary.
     It may be possible to use the DDL 2.1 ITEM_STRUCTURE and
     ITEM_STRUCTURE_LIST categories to provide the information that is
     carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST.  By
     moving the array structure to the DDL level it would be possible to
     define an array type as well as a regular expression defining the
     data format.

   + Multiple array sections can be properly handled within a single
     datablock.
;


#-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof
./CBFlib-0.9.2.2/doc/Cdiffrn_detector_axis.html0000644000076500007650000000533511603702115017527 0ustar yayayaya (IUCr) CIF Definition save_diffrn_detector_axis

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

Category DIFFRN_DETECTOR_AXIS

Name:
'diffrn_detector_axis'

Description:

    Data items in the DIFFRN_DETECTOR_AXIS category associate
     axes with detectors.

Category groups:
    inclusive_group
    diffrn_group
Category keys:
    _diffrn_detector_axis.detector_id
    _diffrn_detector_axis.axis_id

Mandatory category: no

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_detector_element.id.html0000644000076500007650000000513611603702115020614 0ustar yayayaya (IUCr) CIF Definition save__diffrn_detector_element.id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_detector_element.id

Name:
'_diffrn_detector_element.id'

Definition:

       The value of _diffrn_detector_element.id must uniquely
              identify each element of a detector.

Type: code

Mandatory item: yes

Category: diffrn_detector_element

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/cbf_definition_rev.html0000644000076500007650000020436111603702115017055 0ustar yayayaya DRAFT CBF/ImgCIF DEFINITION [IUCr Home Page] [CIF Home Page] [CBFlib]


Proposed Revised
DRAFT CBF/imgCIF DEFINITION
14 January 1999

Revisions
by
Herbert J. Bernstein
Bernstein + Sons, P.O. Box 177, Bellport, NY 11713-0177
yaya@bernstein-plus-sons.com

based on

DRAFT CBF DEFINITION

by
Andy Hammersley
European Synchrotron Radiation Facility, BP 200, Grenoble, 38043, CEDEX, France
hammersley@esrf.fr


This document and the CBF definitions are still subject to change. This document is a draft proposal for discussion.

This is a version of the CBF draft proposal, revised to include a coordinated pure ASCII ImgCIF definition, based on the Draft CBF Definition by Andy Hammersley, the work done at the Brookhaven imgCIF workshop, and the work on "CBFLIB: An ANSI-C API for Crystallographic Binary File" by Paul Ellis, ellis@SSRL.SLAC.STANFORD.EDU. For the binary CBF format, a "binary-string" approach, as proposed by Paul Ellis, is used, while for the ASCII imgCIF format, binary information is encoded using a variant on MIME (Multipurpose Internet Mail Extensions) format, which makes the CBF and ImgCIF formats very similar.

We have included an updated version of John Westbrook's DDL2-compliant CBF Extensions Dictionary, of Paul Ellis's CBFLIB manual, and examples of CBF/imgCIF files.

This is just a proposal. My apologies in advance, especially to Andy, John and especially to Paul for whatever I may have muddled here. Please be careful about basing any code on this until and unless there has been a general agreement.



Notices

Please read the NOTICES, which are part of this package, before making use of this software.


Most of this document is adapted from Andy's, so we follow his convention by "...[separating] the definition from comments on discussion items by using round brackets to refer to notes kept separate from the main text e.g. (1) refers to point 1 in the notes section.". We have integrated all comments to date into this document without special annotation.


A Draft Proposal
for
A Combined
Crystallographic Binary File (CBF)
and
Image-supporting Crystallographic Information File (ImgCIF)
Format

ABSTRACT

This document describes a proposal for a combined Crystallographic Binary File (CBF) and Image-supporting Crystallographic Information File (ImgCIF) format; a simple self-describing binary format for efficient transport and archiving of experimental data for the crystallographic community, and well as for the presentation of other image data, such as PICT, GIF and JPEG, within publication CIFs. With minor differences, both the binary CBF format and the ASCII ImgCIF have a similar, CIF-like structure. All the information other than actual binary data is presented as ASCII strings in both formats. The formats differ only in the handling of line termination and the actual presentation of the binary data of an image. The CBF format, presents binary information as a raw string of octets, while the ImgCIF format presents the binary information as ASCII-encoded lines. The format of the binary file, and the new CIF data-items are defined. In this document we concentrate on the representation of images per se. The CBF/imgCIF dictionary includes additional data items related to crystallographic data acquisition. Those additional data items are not discussed here.

Note:

  • All numbers are decimal unless otherwise stated.
  • The terms octet and byte refer to a group of eight bits.

1.0 INTRODUCTION

The Crystallographic Binary File (CBF) format is a complementary format to the Crystallographic Information File (CIF) [1], supporting efficient storage of large quantities of experimental data in a self-describing binary format (1). The Image-supporting Crystallographic Information File (ImgCIF) format is a proposed extension to CIF to assist in ASCII debugging and archiving of CBF files and to allow for convenient and standardized inclusion of images, such as maps, diagrams and molecular drawing into publication CIFs. It is our expectation that, for large images, the raw binary CBF format will be used both with in laboratories and for interchange among collaborating groups. For smaller chunks of binary data, either format should be be suitable, with the ASCII ImgCIF format being more appropriate for interchange and archiving.

The initial aim is to support efficient storage of raw experimental data from area-detectors (images) with no loss of information compared to existing formats. The format should be both efficient in terms of writing and reading speeds, and in terms of stored file sizes, and should be simple enough to be easily coded, or ported to new computer systems.

Flexibility and extensibility are required, and later the storage of other forms of data may be added without affecting the present definitions.

The aims are achieved by a simple file format, consisting of lines of ASCII information defining information about the binary data as CIF tag-value pairs and tables, and either raw octets of binary data in delimited sections, or ASCII-based presentations of the same binary information in similarly delimited sections.

The present version of the format only tries to deal with simple Cartesian data. This is essentially the "raw" data from detectors that is typically stored in commercial formats or individual formats internal to particular institutes, but could be other forms of data. It is hoped that CBF can replace individual laboratory or institute formats for "home" built detector systems, be used as a inter-program data exchange format, and may be offered as an output choice by a number of commercial detector manufacturers specialising in X-ray and other detector systems.

This format does not imply any particular demands on processing software nor on the manner in which such software should work. Definitions of units, coordinate systems, etc. may quite different. The clear precise definitions within CIF, and hence CBF, help, when necessary, to convert from one system to another. Whilst no strict demands are made, it is clearly to be hoped that software will make as much use as is reasonable of information relevant to the processing which is stored within the file. It is expected that processing software will give clear and informative error messages when they encounter problems within CBF's or do not support necessary mechanisms for inputting a file.

1.1 CBF and "imgCIF"

CBF and "imgCIF" are two aspects of the same format. Since CIF's are pure ASCII text files, a separate binary format is needed to be defined to allow the combination of pseudo-ASCII sections and binary data sections. The binary file format is the Crystallographic Binary File (CBF). The ASCII sections are very close to the CIF standard, but must use operating system independent "line separators". In describing the ASCII sections, we use the notation "\r\n" (for the pair of characters carriage return, line-feed) for a line terminator would allow the ASCII sections to viewed with standard system utilities on a very wide range of operating systems. However, an API to read the binary format must accept any of the following three alternative line terminators as the end of an ascii line: "\r", "\n" or "\r\n". An API to write CBF should write "\r\n" as the line terminator, if at all possible.

imgCIF is also the name of the CIF dictionary which contains the terms specific to describing the binary data (the orginal, designed by John Westbrook, without the modifications in this proposal is avaliable from http://ndbserver.rutgers.edu/NDB/mmcif. Thus a CBF or ImgCIF files uses data names from the imgCIF dictionary and other CIF dictionaries.

2.0 A SIMPLE EXAMPLE

Before fully describing the format we start by showing a simple, but important and complete usage of the format; that of storing a single detector image in a file together with a small amount of useful auxiliary information. It is intened to be a useful example for people who like working from examples, as opposed to full definitions. It should also serve as an introduction or overview of the format defintion. This example uses CIF DDL2 based dictionary items.

The example is an image of 768 by 512 pixels stored as 16 bit unsigned integers, in little endian byte order. (This is the native byte ordering on a PC.) The pixel sizes are 100.5 by 99.5 microns. Comment lines starting with a hash sign (#) are used to explain the contents of the header. Only the ASCII part of the file is shown, but comments are used to describe the start of the binary section.

First the file is shown with the minimum of comments that a typical outputting program might add. Then it is repeated, but with "over- commenting" to explain the format.

Here is how a file might appear if listed on a PC or on a Unix system using "more":


###CBF: VERSION 0.6
# Data block for image 1
data_image_1

_entry.id 'image_1'

                                  
# Sample details
_chemical.entry_id                           'image_1'
_chemical.name_common                        'Protein X'

# Experimental details
_exptl_crystal.id                            'CX-1A'
_exptl_crystal.colour                        'pale yellow'

_diffrn.id                                    DS1
_diffrn.crystal_id                            'CX-1A' 

_diffrn_measurement.diffrn_id                 DS1
_diffrn_measurement.method                    Oscillation
_diffrn_measurement.sample_detector_distance  0.15 
                                                  
_diffrn_radiation_wavelength.id               L1 
_diffrn_radiation_wavelength.wavelength       0.7653 
_diffrn_radiation_wavelength.wt               1.0

_diffrn_radiation.diffrn_id                   DS1 
_diffrn_radiation.wavelength_id               L1 

_diffrn_source.diffrn_id                      DS1
_diffrn_source.source                         synchrotron
_diffrn_source.type                          'ESRF BM-14'

_diffrn_detector.diffrn_id                    DS1
_diffrn_detector.id                           ESRFCCD1
_diffrn_detector.detector                     CCD
_diffrn_detector.type                        'ESRF Be XRII/CCD'


_diffrn_detector_element.id                   1
_diffrn_detector_element.detector_id          ESRFCCD1


_diffrn_frame_data.id                         F1
_diffrn_frame_data.detector_element_id        1
_diffrn_frame_data.array_id                   'image_1'
_diffrn_frame_data.binary_id                  1


# Define image storage mechanism
#

loop_
_array_structure.id 
_array_structure.encoding_type        
_array_structure.compression_type     
_array_structure.byte_order           
image_1       "unsigned 16-bit integer"  none  little_endian
                                      
loop_
_array_intensities.array_id    
_array_intensities.binary_id       
_array_intensities.linearity          
_array_intensities.undefined_value    
_array_intensities.overload_value     
image_1     1    linear     0      65535

# Define dimensionality and element rastering
loop_
_array_structure_list.array_id
_array_structure_list.index
_array_structure_list.dimension
_array_structure_list.precedence
_array_structure_list.direction
image_1    1      768    1    increasing    
image_1    2      512    2    decreasing     

loop_
_array_element_size.array_id
_array_element_size.index
_array_element_size.size
image_1  1  100.5e-6
image_1  2  99.5e-6

loop_
_array_data.array_id
_array_data.binary_id
_array_data.data

image_1 1
;
--CIF-BINARY-FORMAT-SECTION--
Content-Type: application/octet-stream;
     conversions="x-CBF_PACKED"
Content-Transfer-Encoding: BINARY
X-Binary-Size: 374578
X-Binary-ID: 1
X-Binary-Element-Type: "unsigned 16-bit integer"
Content-MD5: jGmkxiOetd9T/Np4NufAmA==

START_OF_BIN
*************'9*****`********* ...
[This is where the raw binary data would be -- we can't print it here]

--CIF-BINARY-FORMAT-SECTION----
;
Here the file is shown again, but this time with many comment lines added to explain the format:
###CBF: VERSION 0.6

# This line starting with a "#" is a CIF and CBF comment line,
# but the first line with the three "#"s is a CBF identifier.
# (a "magic number")  The text "###_CBF: VERSION" identifies
# the file as a CBF and must be present as the very first line of
# every CBF file. Following "VERSION" is the version number of 
# the  file, which is the corresponding version of the CBF/imgCIF
# extensions dictionary and supporting documentation.   A version 
# 0.6 CIF should be readable by any program which fully supports 
# the version 1.0 CBF definitions.

# Comment lines and white space (blanks and new lines) may appear
# anywhere outside the binary sections.
  
# In a CIF, the descriptive tags and values may be presented in
# any convenient order, e.g. the data could come first, and the
# parameters necessary to interpret the data could come later.
# This order-independent convention holds for an imgCIF file, but
# for a CBF, all the tags and values describing binary data (i.e.
# all the tags other than those in the ARRAY_DATA category) should
# be presented before the binary data, in the form of a header.
# This does not mean that there cannot be more useful information
# after the binary data.  There could be another full header and
# more blocks of binary data.  All we are saying is that, in
# the interest of efficiency in processing a CBF, the parameters 
# that relate to a particular block of binary data must appear 
# earlier in the CBF than the block itself.

# The header begins with "data_", which is the CIF token to 
# identify a data block.  Within a data block, any given tag may 
# be presented only once, either directly with an immediately 
# following  value, or as one of the column headings for the rows
# of a table.  If you will need to resuse the same tag, you will 
# have to start a new data block.

# Data block for image 1
data_image_1

# We've chosen to call this data block 'image_1', but this was an 
# arbitary choice. Within a data block a data item may only be used 
# once.

_entry.id 'image_1'
                                  
# Sample details
_chemical.entry_id                           'image_1'
_chemical.name_common                        'Protein X'

# The apostrophes enclose the string which contains a space.
# A double quote (") could have been used, just as well.
# There is also a third way to quote string, with the string
# "\n;", i.e. with a semicolon at the beginning of a line
# which allows multi-lined strings to be presented.  We'll
# use that form of text quotation for the binary data.

# Experimental details
_exptl_crystal.id                            'CX-1A'
_exptl_crystal.colour                        'pale yellow'

_diffrn.id                                    DS1
_diffrn.crystal_id                            'CX-1A' 

_diffrn_measurement.diffrn_id                 DS1
_diffrn_measurement.method                    Oscillation
_diffrn_measurement.sample_detector_distance  0.15 
                                                  
_diffrn_radiation_wavelength.id               L1 
_diffrn_radiation_wavelength.wavelength       0.7653 
_diffrn_radiation_wavelength.wt               1.0

_diffrn_radiation.diffrn_id                   DS1 
_diffrn_radiation.wavelength_id               L1 

_diffrn_source.diffrn_id                      DS1
_diffrn_source.source                         synchrotron
_diffrn_source.type                          'ESRF BM-14'

_diffrn_detector.diffrn_id                    DS1
_diffrn_detector.id                           ESRFCCD1
_diffrn_detector.detector                     CCD
_diffrn_detector.type                        'ESRF Be XRII/CCD'


_diffrn_detector_element.id                   1
_diffrn_detector_element.detector_id          ESRFCCD1


_diffrn_frame_data.id                         F1
_diffrn_frame_data.detector_element_id        1
_diffrn_frame_data.array_id                   'image_1'
_diffrn_frame_data.binary_id                  1

# Many more data items can be defined, but the above gives the idea
# of a useful minimum set (but not minimum in the sense of 
# compulsory, the above data items are optional in a CIF or CBF).
 
# Define image storage mechanism
#
# Notice that we did not include a binary ID here.  The idea of
# the ARRAY_STRUCTURE category is to present parameters which
# could be common to multiple blocks of binary data, which would 
# all have the same array ID, but would have distinct binary ID's

loop_
_array_structure.id 
_array_structure.encoding_type        
_array_structure.compression_type     
_array_structure.byte_order           
image_1      "unsigned 16-bit integer"  none  little_endian
                                      
# On the other hand, we do provide a binary ID for ARRAY_INTENSITIES,
# since there might be different paremeters for each binary block. 
# We could have left it out here, since there is only one block and
# the default binary ID happens to be 1

loop_
_array_intensities.array_id  
_array_intensities.binary_id       
_array_intensities.linearity          
_array_intensities.undefined_value    
_array_intensities.overload_value     
image_1     1   linear     0      65535

# Define dimensionality and element rastering

# Here the size of the image and the ordering (rastering) of the  data 
# elements is defined. The CIF "loop_" structure is used to
# define different dimensions. (It can be used for defining multiple
# images.)

loop_
_array_structure_list.array_id
_array_structure_list.index
_array_structure_list.dimension
_array_structure_list.precedence
_array_structure_list.direction
image_1    1      768    1    increasing    
image_1    2      512    2    decreasing     

loop_
_array_element_size.array_id
_array_element_size.index
_array_element_size.size
image_1  1  100.5e-6
image_1  2  99.5e-6


# The "array_id" identifies data items belong to the same array. 
# Here we have chosen the name "image_1", but another name could 
# have been used, so long as it's used consistently. The "index" 
# component refers to the dimension being defined, and the 
# "dimension" component defines  the number of elements in that 
# dimension. The "precedence" component defines which precedence 
# of rastering of the data. In this case the first dimension is the faster 
# changing dimension. The "direction" component tells us the 
# direction in which the data rasters within a dimension. Here the 
# data  rasters faster from minimum elements towards the maximum 
# element ("increasing") in the first dimension, and more 
# slowly from the maximum element towards the minimum element in 
# the second dimension. (This is the default rastering order.)

# The storage of the binary data is now fully defined.

# Further data items could be defined, but  we are ready to
# present the data.  That is done with the ARRAY_DATA category.
# The start of this category marks the end of the header
# (Well, almost the end, there is a bit more header information
# below).

loop_
_array_data.array_id
_array_data.binary_id
_array_data.data

image_1 1

# The binary data itself will come just a little further down,
# as the essential part of the value of _array_data.data, which 
# begins as semicolon-quoted text.  The line immediately after 
# the line with the semicolon is a MIME boundary marker.  As for
# all MIME boundary markers, it begins with "--".  The next
# few lines are MIME headers, describing some useful information
# we will need to process the binary section.  MIME headers can
# appear in different orders, and can be very confusing (look
# at the raw contents of a email message with attachments), but
# there is only a few headers which is have to be understood to
# process a CBF: 
#
#      The "Content-Type" header may be any of discrete types 
#      permitted in RFC 2045; "application/octet-stream" is 
#      recommended.  If an octet stream was compressed, the 
#      compression should be specified by the parameter 
#      'conversions="x-CBF_PACKED"' or by specifying 
#      one of the other compression types.
#          
#      The "Content-Transfer-Encoding" header should be 'BINARY' 
#      for a CBF.  We'll consider the other values used for imgCIF 
#      below.
#                           
#      The "X-Binary-Size" header specifies the size of the
#      binary data in octets.  If compression was used, this size 
#      is the  size after compression, including any book-keeping
#      fields, but not the 8 bytes for the compression type.
#
#      The "X-Binary-Element-Type" header specifies the 
#      type of binary data in the octets, using the same 
#      descriptive phrases as in _array_structure.encoding_type. 
#      The default value is "unsigned 32-bit integer".
#
# The MIME header items are followed by an empty line and then by
# a special sequence marked here as 'START_OF_BIN', consisting of
# Control-L, Control-Z, Control-D to stop printing on most systems,
# and then a single binary flag  character of hexadecimal value D5 
# (213 decimal).  The binary data follows immediately after this 
# flag character.
#
;
--CIF-BINARY-FORMAT-SECTION--
Content-Type: application/octet-stream;
     conversions="x-CBF_PACKED"
Content-Transfer-Encoding: BINARY
X-Binary-Size: 374578
X-Binary-ID: 1
X-Binary-Element-Type: "unsigned 16-bit integer"
Content-MD5: jGmkxkrpnizOetd9T/Np4NufAmA==

START_OF_BIN
*************'9*****`********* ...
[This is where the raw binary data would be -- we can't print it here]

--CIF-BINARY-FORMAT-SECTION----
;

# After the last octet (i.e. byte) of the binary data, there is a
# special trailer "\n--CIF-BINARY-FORMAT-SECTION----\n;"
# which repeats the initial bounday marker with an extra "--"
# at the end (a MIME convention for the last boundary marker), and
# then the closing semicolon quote for a text section.  This
# is essential in an imgCIF, and we include it in a CBF for 
# consistency.

OVERVIEW OF THE FORMAT

This section describes the major "components" of the CBF format.
  1. CBF is a binary file, containing self-describing array data e.g. one or more images, and auxiliary data e.g. describing the experiment.

  2. Except for the handling of line terminators, the way binary data is presented, and more liberal rules in ordinger information, an ASCII imgCIF file is the same as a CBF binary file.

  3. A CBF consists of pseudo-ASCII text header sections, which are "lines" of no more than 80 ASCII characters separated by "line separators" which are the pair of ASCII characters carriage return and line-feed (ASCII 13, ASCII 10), followed by zero, one, or more binary sections presented as "binary strings". This structure may be repeated.

  4. An imgCIF consists of ASCII lines of no more than 80 characters using the the normal line termination conventions of the current system (e.g. ASCII 10 in UNIX) with MIME-encoded binary strings at any appropriate point in the file.

  5. The very start of the file has an identification item (magic number) (2). This item also describes the CBF version or level. The identifier is:
    ###CBF: VERSION
    
    which must always be present so that a program can easily identify whether or not a file is a CBF, by simply inputting the first 15 characters. (The space is a blank (ASCII 32) and not a tab. All identifier characters are uppercase only.)

    The first hash means that this line within a CIF would be a comment line, but the three hashes mean that this is a line describing the binary file layout for CBF. (All CBF internal identifiers start with the three hashes, and all other must immediately follow a "line separator".) No whitespace may precede the first hash sign.

    Following the file identifier is the version number of the file. e.g. the full line might appear as:

    ###CBF: VERSION 0.6
    
    The version number must be separated from the file identifier characters by whitespace e.g. a blank (ASCII 32).

    The version number is defined as a major version number and minor version number separated by the decimal point. A change in the major version may well mean that a program for the previous version cannot input the new version as some major change has occurred to CBF (3). A change in the minor version may also mean incompatibility, if the CBF has been written using some new feature. e.g. a new form of linearity scaling may be specified and this would be considered a minor version change. A file containing the new feature would not be readable by a program supporting only an older version of the format.

    Note: Until we reach major version 1 (the first official release), the rules are a little more relaxed. While there will be some effort at upwards compatability, in order to ensure a reasonable agreed specification without too many strange artifacts, changes between minor versions may, unfortunately, introduce incompatabilities which require program changes to still read CBFs compliant with an earlier draft, e.g. the change in the "magic number" and from binary sections to binary strings in going to version 0.3, and a removal of the redundant parts of the binary header in going to version 0.6. Naturally, such changes should be sufficiently well documented to allow for conversions.>>>

  6. Header Information:

    1. The start of an header section is delimited by the usual CIF "data_" token. Optionally, the formerly specified header identifier,
      ###_START_OF_HEADER
      
      may be used before the "data_" taken, followed by the carriage return, line-feed pair, as an aid in debugging, but it is no longer required. (Naturally, another carriage return, line-feed pair should immediately precedes this and all other CBF identifiers, with the exception of the CBF file identifier which is at the very start of the file.)

    2. A header section, including the identification items which delimit it, uses only ASCII characters, and is divided into "lines". The "line separator" symbols, "\r\n" (carriage return, line-feed) are the same regardless of the operating system on which the file is written. (This is an importance difference with CIF, but must be so, as the file contains binary data, so cannot be translated from one O.S. to another, which is the case for ASCII text files.) While a properly functioning CBF API should write the full "\r\n" line separator, it should recognize any of three sequences "\r", "\n", "\r\n" as valid line separators, so that hand-edited headers will not be rejected.

    3. The header section within the delimiting identification items obeys all CIF rules [1] with the exception of the line separators.

      e.g.

      • "Lines" are a maximum of 80 characters long. (For CBF it is probably best to allow for this maximum to be larger.)

      • The tokens "data_" and "loop_" have special meaning to CIF, and should not be used except in their indicated places. The tokens "save_", "stop_" and "global_" also have special meaning to CIF's parent language, STAR, and also should not be used.

      • All data names (tags) start with an underscore character.

      • The hash symbol (#) (outside a character string) means that all text up to the line separator is a comment.

      • Whitespace outside of character strings is not significant.

      • Data names are case insensitive.

      • The data item follows the data name separator, and may be of one of two types: character string (char) or number (numb). (The type is specified for each data name.)

      • Character strings may be delimited with single of double quotes, or blocks of text may be delimited by semi-colons occurring as the first character on a line.

      • The "loop_" mechanism allows a data name to have multiple values. Immediately following the "loop_", one or more data names are listed without their values, as column headings. Then one or more rows of values are given.

      Any CIF data name may occur within the header section.

    4. A single header section may contain one or more data blocks (CIF terminology).

    5. The end of the header information is marked by coming to the tags from the "ARRAY_DATA" category. The formerly specifier special identifier:
      ###_END_OF_HEADER
      
      followed by carriage return, line-feed, may be used as well as an aid to debugging, but it is not required.

  7. The header information must contain sufficient data names to fully describe the binary data section(s) which follow(s).

  8. Binary Information:

    Note: Under CBFlib "binary sections" have been replaced by "binary strings" values within a data name/value pair. The structure of the proposed "binary string" is similar to the former binary sections, but there are significant differences.

    1. Before getting to the binary data, itself, there are some preliminaries to allow a smooth transition from the conventions of CIF to those of raw streams of "octets" (8-bit bytes). The binary data is given as the essential part of a specially formatted semicolon-delimited CIF multi-line text string. This text string is the value associated with the tag "_array_data.data".

    2. Within that text string, the conventions developed for transmitting email messages including binary attachments are followed. There is secondary ASCII header information, formatted as Multipurpose Internet Mail Extensions (MIME) headers (see RFCs 2045-49 by Freed, et. al). The bounday marker for the beginning of all this is the special string


      --CIF-BINARY-FORMAT-SECTION--


      at the beginning of a line. The initial "--" says that this is a MIME boundary. We cannot put "###" in front of it and conform to MIME conventions. Immediately after the boundary marker are MIME headers, describing some useful information we will need to process the binary section. MIME headers can appear in different orders, and can be very confusing (look at the raw contents of a email message with attachments), but there is only a few headers with a narrow range of values which is have to be understood to process a CBF (as opposed of an imgCIF, for which the headers can be more varied):

      • The "Content-Type" header may be any of discrete types permitted in RFC 2045; "application/octet-stream" is recommended. If an octet stream was compressed, the compression should be specified by the parameter 'conversions="x-CBF_PACKED"' or by specifying one of the other compression types.

      • The "Content-Transfer-Encoding" header should be 'BINARY' for a CBF. We'll consider the other values used for imgCIF below.

      • The "X-Binary-Size" header specifies the size of the binary data in octets. If compression was used, this size is the size after compression, including any book-keeping fields, but not the 8 bytes for the compression type.

      • The "X-Binary-Element-Type" header specifies the type of binary data in the octets, using the same descriptive phrases as in _array_structure.encoding_type. The default value is "unsigned 32-bit integer".

      The MIME header items are followed by an empty line and then by a special sequence marked here as 'START_OF_BIN', consisting of Control-L, Control-Z, Control-D to stop printing on most systems, and then a single binary flag character of hexadecimal value D5 (213 decimal). The binary data follows immediately after this flag character.


      In general, if the value given for "Content-Transfer-Encoding" is one of the real encodings: "BASE64", "QUOTED-PRINTABLE", "X-BASE8", "X-BASE10" or "X-BASE16", this file is an imgCIF.

      For either a CBF or an imgCIF the optional "Content-MD5" header provides a much more sophisticated check on the integrity of the binary data.


      In a CBF, the raw binary data begins after an empty line terminating the MIME headers and after the START_OF_BIN identifier. "START_OF_BIN" contains bytes to separate the "ASCII" lines from the binary data, bytes to try to stop the listing of the header, bytes which define the binary identifier which should match the "binary_id" defined in the header, and bytes which define the length of the binary section.


      Octet Hex Decimal Purpose
      1 0C 12 (ctrl-L) End the current page
      2 1A 26 (ctrl-Z) Stop listings in MS-DOS
      3 04 04 (Ctrl-D) Stop listings in UNIX
      4 D5 213 Binary section begins
      5..5+n-1   Binary data (n octets)


      Only bytes 5..5+n-1 are encoded for an imgCIF file using the indicated Content-Transfer-Encoding.

      Note: Earlier versions of the specification included three 8-byte words of information in binary which replicated information now available in the MIME header:

      5..12    Binary Section Identifier
      (See _array_data.binary_id)
      64-bit, little endian
      13..20    the size (n) of the
      binary section in octets
      (i.e. the offset from octet
      29 to the first byte following
      the data)
      21..28   Compression type:
      CBF_NONE 0x0040 (64)
      CBF_CANONICAL 0x0050 (80)
      CBF_PACKED 0x0060 (96)
      ... &NBSP;
      followed by binary data. These three 8-byte words are no longer included when a MIME header is provided. In addition, in still earlier versions, the size given in the second 8-byte word was n+8, rather than n.


      The binary characters serve specific purposes:


      • The Control-L will terminate the current page in listings on most operating systems.


      • The Control-Z will stop the listing of the file on MS-DOS type operating systems.


      • The Control-D will stop the listing of the file on Unix type operating systems.


      • The unsigned byte value 213 (decimal) is binary 11010101. (Octal 325, and hexadecimal D5). This has the eighth bit set so can be used for error checking on 7-bit transmission. It is also asymmetric, but with the first bit also set in the case that the bit order could be reversed (which is not a known concern).


      • (The carriage return, line-feed pair before the START_OF_BIN and other lines can also be used to check that the file has not been corrupted e.g. by being sent by ftp in ASCII mode.)



    3. The "line separator" immediately precedes the "start of binary identifier", but blank spaces may be added prior to the preceding "line separator" if desired (e.g. to force word or block alignment).


    4. The binary data does not have to completely fill the bytes defined by the byte length value, but clearly cannot be greater than this value (except when the value zero has been stored, which means that the size is unknown, and no other headers follow). The values of any unused bytes are undefined.


    5. At exactly the byte following the full binary section as defined by the length value is the end of binary section identifier. This consists of the carriage return / line feed pair followed by:


      --CIF-BINARY-FORMAT-SECTION--
      ;


      with each of these lines followed by the carriage return / line feed pair. This brings us back into a normal CIF environment


      The first "line separator" separates the binary data from the pseudo-ASCII line.


      This identifier is in a sense redundant since the binary data length value tells the a program how many bytes to jump over to the end of the binary data. However, this redundancy has been deliberately added for error checking, and for possible file recovery in the case of a corrupted file.


      This identifier must be present at the end of every block of binary data.


  9. Whitespace may be used within the pseudo-ASCII sections prior to the "start of binary section" identifier to align the start binary data sections to word or block boundaries. Similar use may be made of unused bytes in binary sections. However, no blank lines should be introduced among the MIME headers, since that would terminate processing of those headers and start the scan for binary data.


    However, in general no guarantee is made of block nor word alignment in a CBF of unknown origin.


  10. The end of the file need not be not explicitly indicated, but including a comment of the form:


    ###_END_OF_CBF


    (including the carriage return, line-feed pair) can help in debugging.


  11. All binary data described in a single data block should follow the header section prior to another data block, or the end of the file, so allow for the most efficient processing of CBF files. However, since binary strings can be parsed anywhere within the context of a CBF or imgCIf file, it is recommended that processing software from CBF accept such strings in any order and it is mandatory that processing software for imgCIF accept such string in any order.


    The binary identifier values used within a given data block section, and hence the binary data must be unique for any given array_id, and, it would be best to make them truly unique.


    A different data block may reuse binary identifier values.


    (This allows concatenation of files without re-numbering the binary identifiers, and provides a certain level of localization of data within the file, to avoid programs having to search potentially huge files for missing binary sections.)


  12. The recommended file extension for a CBF is: cbf
    This allows users to recognise file types easily, and gives programs a chance to "know" the file type without having to prompt the user. Although they should check for at least the file identifier to ensure that the file type is indeed a CBF.


  13. The recommended file extensions for imgCIF are: icf or cif
    (use of "cif" subject to IUCr approval).


  14. CBF format files are binary files and when ftp is used to transfer files between different computer systems "binary" or "image" mode transfer should be selected.


  15. imgCIF files are ASCII files and when ftp is used to transfer files between different computer systems "ascii" transfer should be selected.

3.1 SIMPLE EXAMPLE OF THE ORDERING OF IDENTIFIERS

Here only the ASCII part of the file structuring identifiers is shown. The CIF data items are not shown, apart from the "data_" identifier which indicates the beginning of a data block.

This shows the structuring of a simple example e.g. one header section followed by one binary section. Such as could be used to store a single image.

###CBF: VERSION 0.3

data_

### ... various CIF tags and values here

loop_
array_data.id
array_data.binary_id
array_data.data

image_1 1
;
--CIF-BINARY-FORMAT-SECTION--
Content-Type: application/octet-stream;
     conversions="x-CBF_PACKED"
Content-Transfer-Encoding: BINARY
X-Binary-ID: 1
Content-MD5: jGmkxiOetd9T/Np4NufAmA==

START_OF_BIN
*************'9*****`********* ...
[This is where the raw binary data would be -- we can't print it here]

--CIF-BINARY-FORMAT-SECTION----
;
###_END_OF_CBF

3.2 MORE COMPLICATED EXAMPLE OF THE ORDERING OF IDENTIFIERS

Here only the ASCII part of the file structuring identifiers is shown. The CIF data items are not shown, apart from the "data_" identifier which indicates the beginning of a data block.

This shows the a possible structuring of a more complicated example. Two header sections, the first contains two data blocks and defines three binary sections. CIF comment lines, starting with a hash (#) are used to example the structure.

###CBF: VERSION 0.6
# CBF file written by cbflib v0.6

# A comment cannot appear before the file identifier, but can appear
# anywhere else, except within the binary sections.

# Here the first data block starts
data_

### ... various CIF tags and values here
###     but none that define array data items


# The "data_" identifier finishes the first data block and starts the
# second
data_

### ... various CIF tags and values here
###     including ones that define array data items

loop_
array_data.array_id
array_data.binary_id
array_data.data

image_1 1
;
--CIF-BINARY-FORMAT-SECTION--
Content-Type: application/octet-stream;
     conversions="x-CBF_PACKED"
Content-Transfer-Encoding: BINARY
X-Binary-Size: 3745758
X-Binary-ID: 1
X-Binary-Element-Type: "signed 32-bit integer"
Content-MD5: 1zsJjWPfol2GYl2V+QSXrw==

START_OF_BIN
<D5>^P<B8>P^@^@^@^@^@^@^@^@^@^@^@^@^@^@^@^@^@ ...
[This is where the raw binary data would be -- we can't print it here]

--CIF-BINARY-FORMAT-SECTION----
;

# Following the "end of binary" identifier the file is pseudo-ASCII
# again, so comments are valid up to the next "start of binary"
# identifier.  Note that we have bumped the binary ID.

image_1 2
;
--CIF-BINARY-FORMAT-SECTION--
Content-Type: application/octet-stream;
     conversions="x-CBF_PACKED"
Content-Transfer-Encoding: BINARY
X-Binary-Size: 3745758
X-Binary-ID: 2
X-Binary-Element-Type: "signed 32-bit integer"
Content-MD5: xR5kxiOetd9T/Nr5vMfAmA==

START_OF_BIN
<D5>^P<B8>P^@^@^@^@^@^@^@^@^@^@^@^@^@^@^@^@^@ ...
[This is where the raw binary data would be -- we can't print it here]

--CIF-BINARY-FORMAT-SECTION----
;

# Third binary section, note that we have a new array id.

image_2 3
;
--CIF-BINARY-FORMAT-SECTION--
Content-Type: application/octet-stream;
     conversions="x-CBF_PACKED"
Content-Transfer-Encoding: BINARY
X-Binary-ID: 3
Content-MD5: yS5kxiOetd9T/NrqTLfAmA==

START_OF_BIN
*************'9*****`********* ...
[This is where the raw binary data would be -- we can't print it here]

--CIF-BINARY-FORMAT-SECTION----
;


# Second Header section

data_

### ... various CIF tags and values here
###     including ones that define array data items

# Since we only have one block left, we won't use a loop


array_data.id         image
array_data.binary_id  1
array_data.data

# Note that I can put a comment here
;
--CIF-BINARY-FORMAT-SECTION--
Content-Type: application/octet-stream;
     conversions="x-CBF_PACKED"
Content-Transfer-Encoding: BINARY
X-Binary-ID: 1
Content-MD5: fooxiOetd9T/serNufAmA==

START_OF_BIN
*************'9*****`********* ...
[This is where the raw binary data would be -- we can't print it here]

--CIF-BINARY-FORMAT-SECTION----
;

###_END_OF_CBF

DATA NAME CATEGORIES

John Westbrook has proposed a number of data name categories as part of his DDL2 based "imgCIF" dictionary. This category list may be expanded to cover a structuring of the often multiple data-sets which might be used in a structurial investigation. Here we only consider the categories concerned with storing an image (or other N-dimensional topographically regular cartesian grid).

The _array_* categories cover all data names concerned with the storage of images or regular array data.

Data names from any of the existing categories may be relevant as auxiliary information in the header section, but data names from the _diffrn_ category, are likely to be the most relevant, and a number of new data names in this category are necessary.

The "array" Class of Binary Data

The "array" class is used to store regular arrays of data values, such as 1-D histograms, area-detector data, series of area-detector data, and volume data. Normally such data is regularly spaced in space or time, however spatial distorted data could nevertheless be stored in such a format. There is only one data "value" stored per lattice position, although that value may be of type complex.

The "array" class is defined by data names from the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST categories.

Here is a short summary of the data names and their purposes.

  • _array_structure.id: Alpha numeric identifier for the array structure
  • _array_structure.compression_type: Type of data compression used
  • _array_structure.byte_order: Order of bytes for multi-byte integer or reals
  • _array_structure.encoding_type: Native data type used to store elements.

    e.g. "unsigned_16_bit_integer" is used if the stored image was 16 bit unsigned integer values, regardless of any compression scheme used.

"Array" Dimensions and Element Rastering and Orientation

The array dimension sizes, i.e. the number of elements in each dimension are defined by _array_structure_list.dimension. Which takes an integer value. This is used in a loop together with the _array_structure_list.index item to define the different dimensions for one or more arrays.

Fundamental to treating a long line of data values as a 2-D image or an N-dimensional volume or hyper-volume is the knowledge of the manner in which the values need to be wrapped. For the raster orientation to be meaningful we define the sense of the view:

For a detector image the sense of the view is defined as that looking from the crystal towards the detector.

(For the present we consider only an equatorial plane geometry, with 2-theta = 0; the detector as being vertically mounted.)

The rastering is defined by the three data names _array_structure_list.index, _array_structure_list.precedence, and _array_structure_list.direction data names.

index refers to the dimension index i.e. In an image 1 refers to the X-direction (horizontal), 2 refers to the Y-direction (vertical).

precedence refers to the order in which the data in wrapped.

direction refers the direction of the rastering for that index.

We define a preferred rastering orientation, which is the default if the keyword is not defined. This is with the start in the upper-left-hand corner and the fastest changing direction for the rastering horizontally, and the slower change from top to bottom.

(Note: With off-line scanners the rastering type depending on which way round the imaging plate or film is entered into the scanner. Care may need to be taken to make this consistent.)

"Array_Structure" Examples

To define an image array of 1300 times 1200 elements, with the raster faster in the first dimension, from left to right, and slower in the second dimension from top to bottom, the following header section might be used:

# Define image size and rastering
loop_
_array_structure_list.array_id
_array_structure_list.index
_array_structure_list.dimension
_array_structure_list.precedence
_array_structure_list.direction
image_1    1      1300    1    increasing
image_1    2      1200    2    decreasing
To define two arrays, the first a volume of 100 times 100 times 50 elements, fastest changing in the first dimension, from left to right, changing from bottom to top in the second dimension, and slowest changing in the third dimension from front to back; the second an image of 1024 times 1280 pixels, with the second dimension changing fastest from top to bottom, and the first dimension changing slower from left to right; the following header section might be used:

# Define array sizes and rasterings
loop_
_array_structure_list.array_id
_array_structure_list.index
_array_structure_list.dimension
_array_structure.precedence
_array_structure.direction
volume_a    1      100    1    increasing
volume_a    2      100    2    increasing
volume_a    3       50    3    increasing
slice_1     1      1024   2    increasing
slice_1     2      1280   1    decreasing

"Array" Element Intensity Scaling

Existing data storage formats use a wide variety of methods for storing physical intensities as element values. The simplest is a linear relationship, but square root and logarithm scaling methods have attractions and are used. Additionally some formats use a lower dynamic range to store the vast majority of element values, and use some other mechanism to store the elements which over-flow this limited dynamic range. The problem of limited dynamic range storage is solved by the data compression methods byte_offsets and predictor_huffman (see next Section), but the possibility of defining non-linear scaling must also be provided.

The _array_intensities.linearity data item specifies how the intensity scaling is defined. Apart from linear scaling, which is specified by the value linear, two other methods are available to specify the scaling.

One is to refer to the detector system, and then knowledge of the manufacturers method will either be known or not by a program. This has the advantage that any system can be easily accommodated, but requires external knowledge of the scaling system.

The recommended alternative is to define a number of standard intensity linearity scaling methods, with additional data items when needed. A number of standard methods are defined by _array_intensities.linearity values: offset, scaling_offset, sqrt_scaled, and logarithmic_scaled. The "offset" methods require the data item _array_intensities.offset to be defined, and the "scaling" methods require the data item _array_intensities.scaling to be defined. The above scaling methods allow the element values to be converted to a linear scale, but do not necessarily relate the linear intensities to physical units. When appropriate the data item _array_intensities.gain can be defined. Dividing the linearized intensities by the value of _array_intensities.gain should produce counts. Two special optional data flag values may be defined which both refer to the values of the "raw" stored intensities in the file (after decompression if necessary), and not to the linearized scaled values. _array_intensities.undefined_value specifies a value which indicates that the element value is not known. This may be due to data missing e.g. a circular image stored in a square array, or where the data values are flagged as missing e.g. behind a beam-stop. _array_intensities.overload_value indicates the intensity value at which and above, values are considered unreliable. This is usually due to saturation.

"Array_intensities" Example

To define the characteristics of image_1 as linear with a gain of 1.2, and an undefined value of 0, and a saturated (overloaded) value of 65535, the following header section might be used:
# Define image intensity scaling
loop_
_array_intensities.array_id
_array_intensities.binary_id
_array_intensities.linearity
_array_intensities.gain
_array_intensities.undefined_value
_array_intensities.overload_value
image_1    1    linear   1.2    0   65535

DATA COMPRESSION

One of the primary aims of imgCIF / CBF is to allow efficient storage, and efficient reading and writing of data, so data compression is of great interest. Despite the extra CPU over-heads it can very often be faster to compress data prior to storage, as much smaller amounts of data need to be written to disk, and disk I/O is relatively slow. However, optimum data compression can result in complicated algorithms, and be highly data specific.

In CBFlib version 0.1, Paul Ellis has coded two lossless compression algorithms: canonical and packed.

Canonical-code compression

The canonical-code compression scheme encodes errors in two ways: directly or indirectly. Errors are coded directly using a symbol corresponding to the error value. Errors are coded indirectly using a symbol for the number of bits in the (signed) error, followed by the error iteslf.

At the start of the compression, CBFLIB constructs a table containing a set of symbols, one for each of the 2^n direct codes from -(2^(n-1)) .. 2^(n-1) -1, one for a stop code, and one for each of the maxbits -n indirect codes, where n is chosen at compress time and maxbits is the maximum number of bits in an error. CBFLIB then assigns to each symbol a bit-code, using a shorter bit code for the more common symbols and a longer bit code for the less common symbols. The bit-code lengths are calculated using a Huffman-type algorithm, and the actual bit-codes are constructed using the canonical-code algorithm described by Moffat, et al. (International Journal of High Speed Electronics and Systems, Vol 8, No 1 (1997) 179-231).

The structure of the compressed data is:

ByteValue
1 .. 8Number of elements (64-bit little-endian number)
9 .. 16Minimum element
17 .. 24Maximum element
25 .. 32Repeat length (currently unused)
33Number of bits directly coded, n
34Maximum number of bits encoded, maxbits
35 .. 35+2^n-1Number of bits in each direct code
35+2^nNumber of bits in the stop code
35+2^n+1 .. 35+2^n+maxbits-n Number of bits in each indirect code
35+2^n+maxbits-n+1 .. Coded data

CCP4-style compression

The CCP4-style compression writes the errors in blocks . Each block begins with a 6-bit code. The number of errors in the block is 2^n, where n is the value in bits 0 .. 2. Bits 3 .. 5 encode the number of bits in each error:
Value in
bits 3 .. 5
Number of bits
in each error

00
14
25
36
47
58
616
765


The structure of the compressed data is:



ByteValue
1 .. 8Number of elements (64-bit little-endian number)
9 .. 16Minumum element (currently unused)
17 .. 24Maximum element (currently unused)
25 .. 32Repeat length (used, starting with version 0.2)
33 ..Coded data

Additional Compression Schemes

In addition, Andy Hammersley has proposed two types of lossless data compression algorithms for CBF version 1.0. In later versions other types including lossy algorithms may be added.

The first algorithm is referred to as byte_offsets and has been chosen for the following characteristics: it is very simple, may be easily implemented, and can easily lead to faster reading and writing to hard disk as the arithmetic complication is very small. This algorithm can never achieve better than a factor of two compression relative to 16-bit raw data, but for most diffraction data the compression will indeed be very close to a factor 2.

The second algorithm is referred to as predictor_huffman and has been chosen as it can achieve close to optimum compression on typical diffraction patterns, with a relatively fast algorithm, whilst avoiding patent problems and licensing fees. This will typically provide a compression ratio between 2.5 and 3 on well exposed diffraction images, and will achieve greater ratios on more weakly exposed data e.g. 4 - 5 on "thin phi-slicing" images. Normally, this would be a two pass algorithm; 1st pass to define symbol probabilities; second pass to entropy encode the data symbols. However, the Huffman algorithm makes it possible to use a fixed table of symbol codes, so faster single pass compression may be implemented with a small loss in compression ratio. With very fast cpus this approach may provide faster hard disk reading and writing than the "byte_offsets" algorithm owing to the smaller amounts of data to be stored.

There are practical disadvantages to data compression: the value of a particular element cannot be obtained without calculating the values of all previous elements, and there is no simple relationship between element position and stored bytes. If generally the whole array is required this disadvantage does not apply. These disadvantages can be reduced by compressing separately different regions of the arrays, which is an approach available in TIFF, but this adds to the complexity reading and writing images.

For simple predictor algorithms such as the byte_offsets algorithm a simple alternative is an optional data item, which defines a look-up table of element addresses, values, and byte positions within the compressed data, and it is suggested that this approach is followed.

THE "BYTE_OFFSETS" ALGORITHM

The byte_offsets algorithm will typically result in close to a factor of two reduction in data storage size relative to typical 2-byte diffraction images. It should give similar gains in disk I/O and network transfer. It also has the advantage that integer values up to 32 bits (31 bits unsigned) may be stored efficiently without the need for special over-load tables. It is a fixed algorithm which does not need to calculate any image statistics, so is fast.

The algorithm works because of the following property of almost all diffraction data and much other image data: The value of one element tends to be close to the value of the adjacent elements, and the vast majority of the differences use little of the full dynamic range. However, noise in experimental data means that run-length encoding is not useful (unless the image is separated into different bit-planes). If a variable length code is used to store the differences, with the number of bits used being inversely proportional to the probability of occurrence, then compression ratios of 2.5 to 3.0 may be achieved. However, the optimum encoding becomes dependent of the exact properties of the image, and in particular on the noise. Here a lower compression ratio is achieved, but the resulting algorithm is much simpler and more robust.

The byte_offsets algorithm is the following:

  1. The first element of the array is stored as a 4-byte signed two's integer regardless of the raw array element type. The byte order for this and all subsequent multi-byte integers is little_endian regardless of the native computer architecture i.e. the first byte is the least significant, and the last byte the most. This value is the first reference value ("previous element") for calculating pixel to pixel differences.

  2. For all elements, including the first element, the value of the previous element is subtracted to produce the difference. For the first element on a line the value to subtract is the value of the first element of the previous line. For the first element of a subsequent image (or plane) the value to subtract is the value of the first element of the previous image (or plane).

  3. If the difference is less than +-127, then one byte is used to store the difference as a signed two's complement integer, otherwise the byte is set to -128 (80 in hex) and if the difference is less than +-32767, then the next two bytes are used to store the difference as a signed two byte two's complement integer, otherwise -32768 (8000 in hex, which will be output as 00 80 in little-endian format) is written into the two bytes and the following 4-bytes store the difference as a full signed 32-bit two's complement integer.

  4. The array element order follows the normal ordering as defined by the _array_structure_list entries index, precedence and direction.

It may be noted that one element value may require up to 7 bytes for storage, however for almost all 16-bit experimental data the vast majority of element values will be within +-127 units of the previous element and so only require 1 byte for storage and a compression factor of close to 2 is achieved.

The PREDICTOR_HUFFMAN ALGORITHM

Section to be added.

OTHER SECTIONS

Other sections will be added.

9.0 REFERENCES

1. S R Hall, F H Allen, and I D Brown, "The Crystallographic Information File (CIF): a New Standard Archive File for Crystallography", Acta Cryst., A47, 655-685 (1991)

10.0 NOTES

(1) A pure ASCII CIF based format has been considered inappropriate given the enormous size of many raw experimental data-sets and the desire for efficient storage, and reading and writing. However, an ASCII format is helpful for debugging software and in understanding what has been written in a CBF when problems arise, and there are other CIF application for which a convenience binary format should be useful (e.g. illustrations in a manuscript).

(2) Some simple method of checking whether the file is a CBF or not is needed. Ideally this would be right at the start of the file. Thus, a program only needs to read in n bytes and should then know immediately if the file is of the right type or not. Andy though this identifier should be some straightforward and clear ASCII string. With the use of binary strings and MIME conventions identification of a CBF versus a CIF is less critical than it was before, but the distinct header as a simple ASCII string is still a good idea for the sake of the most efficient processing of large files.

The underscore character has been used to avoid any ambiguity in the spaces.

(Such an identifier should be long enough that it is highly unlikely to occur randomly, and if it is ASCII text, should be very slightly obscure, again to reduce the chances that it is found accidently. Hence I added the three hashes, but some other form may be equally valid.)

(3) The format should maintain backward compatibility e.g. a version 1.0 file can be read in by a version 1.1, 3.0, etc. program, but to allow future extensions the reverse cannot be guaranteed to be true. However, prior to actual adoption of version 1.0, we are not yet trying to ensure full upwards compatibility, just that the effort to convert won't be unreasonable.


Examples of CBF and imgCIF Files


This page was produced on 23 April 2001
by Herbert J. Bernstein (email: yaya@bernstein-plus-sons.com),
based on the 14 November 1998 and 8 July 1998 versions and the page produced by Andy Hammersley (E-mail: hammersley@esrf.fr).


./CBFlib-0.9.2.2/doc/Idiffrn_scan_frame_axis.displacement.html0000644000076500007650000000521411603702115022465 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan_frame_axis.displacement

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_scan_frame_axis.displacement

Name:
'_diffrn_scan_frame_axis.displacement'

Definition:

        The setting of the specified axis in millimetres for this
               frame.  This is the setting at the start of the integration
               time.

Type: float

Mandatory item: no


Enumeration default: 0.0

Category: diffrn_scan_frame_axis

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/cif_img_1.5.2_6May07.dic0000644000076500007650000071227011603702115016220 0ustar yayayaya############################################################################## # # # Image CIF Dictionary (imgCIF) # # and Crystallographic Binary File Dictionary (CBF) # # Extending the Macromolecular CIF Dictionary (mmCIF) # # # # Version 1.5.2 # # of 2007-05-07 # # ################################################################### # # # *** WARNING *** THIS IS A DRAFT FOR DISCUSSSION *** WARNING *** # # # # SUBJECT TO CHANGE WITHOUT NOTICE # # # # VERSIONS WILL BE POSTED AS cif_img_1.5_DDMMMYY_draft.html # # # # SEND COMMENTS TO imgcif-l@iucr.org CITING THE VERSION # # # ################################################################### # # This draft edited by H. J. Bernstein # # # # by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook # # # # This dictionary was adapted from format discussed at the imgCIF Workshop, # # held at BNL Oct 1997 and the Crystallographic Binary File Format Draft # # Proposal by Andrew Hammersley. The first DDL 2.1 Version was created by # # John Westbrook. This version was drafted by Herbert J. Bernstein and # # incorporates comments by I. David Brown, John Westbrook, Brian McMahon, # # Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li, Gotzon Madariaga, # # Frances C. Bernstein, Chris Nielsen, Nicola Ashcroft and others. # ############################################################################## data_cif_img.dic _dictionary.title cif_img.dic _dictionary.version 1.5.2 _dictionary.datablock_id cif_img.dic ############################################################################## # CONTENTS # # CATEGORY_GROUP_LIST # SUB_CATEGORY # # category ARRAY_DATA # # _array_data.array_id # _array_data.binary_id # _array_data.data # # category ARRAY_ELEMENT_SIZE # # _array_element_size.array_id # _array_element_size.index # _array_element_size.size # # category ARRAY_INTENSITIES # # _array_intensities.array_id # _array_intensities.binary_id # _array_intensities.gain # _array_intensities.gain_esd # _array_intensities.linearity # _array_intensities.offset # _array_intensities.scaling # _array_intensities.overload # _array_intensities.undefined_value # _array_intensities.pixel_fast_bin_size # _array_intensities.pixel_slow_bin_size # _array_intensities.pixel_binning_method # # category ARRAY_STRUCTURE # # _array_structure.byte_order # _array_structure.compression_type # _array_structure.compression_type_flag # _array_structure.encoding_type # _array_structure.id # # category ARRAY_STRUCTURE_LIST # # _array_structure_list.axis_set_id # _array_structure_list.array_id # _array_structure_list.dimension # _array_structure_list.direction # _array_structure_list.index # _array_structure_list.precedence # # category ARRAY_STRUCTURE_LIST_AXIS # # _array_structure_list_axis.axis_id # _array_structure_list_axis.axis_set_id # _array_structure_list_axis.angle # _array_structure_list_axis.angle_increment # _array_structure_list_axis.displacement # _array_structure_list_axis.fract_displacement # _array_structure_list_axis.displacement_increment # _array_structure_list_axis.fract_displacement_increment # _array_structure_list_axis.angular_pitch # _array_structure_list_axis.radial_pitch # _array_structure_list_axis.reference_angle # _array_structure_list_axis.reference_displacement # # category AXIS # # _axis.depends_on # _axis.equipment # _axis.id # _axis.offset[1] # _axis.offset[2] # _axis.offset[3] # _axis.type # _axis.system # _axis.vector[1] # _axis.vector[2] # _axis.vector[3] # # category DIFFRN_DATA_FRAME # # _diffrn_data_frame.array_id # _diffrn_data_frame.binary_id # _diffrn_data_frame.detector_element_id # _diffrn_data_frame.id # _diffrn_data_frame.details # # category DIFFRN_DETECTOR # # _diffrn_detector.details # _diffrn_detector.detector # _diffrn_detector.diffrn_id # _diffrn_detector.dtime # _diffrn_detector.id # _diffrn_detector.number_of_axes # _diffrn_detector.type # # category DIFFRN_DETECTOR_AXIS # # _diffrn_detector_axis.axis_id # _diffrn_detector_axis.detector_id # # category DIFFRN_DETECTOR_ELEMENT # # _diffrn_detector_element.center[1] # _diffrn_detector_element.center[2] # _diffrn_detector_element.id # _diffrn_detector_element.detector_id # _diffrn_detector_element.reference_center_fast # _diffrn_detector_element.reference_center_slow # # category DIFFRN_MEASUREMENT # # _diffrn_measurement.diffrn_id # _diffrn_measurement.details # _diffrn_measurement.device # _diffrn_measurement.device_details # _diffrn_measurement.device_type # _diffrn_measurement.id # _diffrn_measurement.method # _diffrn_measurement.number_of_axes # _diffrn_measurement.specimen_support # # category DIFFRN_MEASUREMENT_AXIS # # _diffrn_measurement_axis.axis_id # _diffrn_measurement_axis.measurement_device # _diffrn_measurement_axis.measurement_id # # category DIFFRN_RADIATION # # _diffrn_radiation.collimation # _diffrn_radiation.diffrn_id # _diffrn_radiation.div_x_source # _diffrn_radiation.div_y_source # _diffrn_radiation.div_x_y_source # _diffrn_radiation.filter_edge' # _diffrn_radiation.inhomogeneity # _diffrn_radiation.monochromator # _diffrn_radiation.polarisn_norm # _diffrn_radiation.polarisn_ratio # _diffrn_radiation.polarizn_source_norm # _diffrn_radiation.polarizn_source_ratio # _diffrn_radiation.probe # _diffrn_radiation.type # _diffrn_radiation.xray_symbol # _diffrn_radiation.wavelength_id # # category DIFFRN_REFLN # # _diffrn_refln.frame_id # # category DIFFRN_SCAN # # _diffrn_scan.id # _diffrn_scan.date_end # _diffrn_scan.date_start # _diffrn_scan.integration_time # _diffrn_scan.frame_id_start # _diffrn_scan.frame_id_end # _diffrn_scan.frames # # category DIFFRN_SCAN_AXIS # # _diffrn_scan_axis.axis_id # _diffrn_scan_axis.angle_start # _diffrn_scan_axis.angle_range # _diffrn_scan_axis.angle_increment # _diffrn_scan_axis.angle_rstrt_incr # _diffrn_scan_axis.displacement_start # _diffrn_scan_axis.displacement_range # _diffrn_scan_axis.displacement_increment # _diffrn_scan_axis.displacement_rstrt_incr # _diffrn_scan_axis.reference_angle # _diffrn_scan_axis.reference_displacement # _diffrn_scan_axis.scan_id # # category DIFFRN_SCAN_FRAME # # _diffrn_scan_frame.date # _diffrn_scan_frame.frame_id # _diffrn_scan_frame.frame_number # _diffrn_scan_frame.integration_time # _diffrn_scan_frame.scan_id # # category DIFFRN_SCAN_FRAME_AXIS # # _diffrn_scan_frame_axis.axis_id # _diffrn_scan_frame_axis.angle # _diffrn_scan_frame_axis.angle_increment # _diffrn_scan_frame_axis.angle_rstrt_incr # _diffrn_scan_frame_axis.displacement # _diffrn_scan_frame_axis.displacement_increment # _diffrn_scan_frame_axis.displacement_rstrt_incr # _diffrn_scan_frame_axis.reference_angle # _diffrn_scan_frame_axis.reference_displacement # _diffrn_scan_frame_axis.frame_id # # categor MAP # # _map.details # _map.diffrn_id # _map.entry_id # _map.id # # categor MAP_SEGMENT # # _map_segment.array_id # _map_segment.binary_id # _map_segment.mask_array_id # _map_segment.mask_binary_id # _map_segment.id # _map_segment.map_id # _map_segment.details # # ***DEPRECATED*** data items # # _diffrn_detector_axis.id # _diffrn_measurement_axis.id # # ***DEPRECATED*** category DIFFRN_FRAME_DATA # # _diffrn_frame_data.array_id # _diffrn_frame_data.binary_id # _diffrn_frame_data.detector_element_id # _diffrn_frame_data.id # _diffrn_frame_data.details # # # ITEM_TYPE_LIST # ITEM_UNITS_LIST # DICTIONARY_HISTORY # ############################################################################## ######################### ## CATEGORY_GROUP_LIST ## ######################### loop_ _category_group_list.id _category_group_list.parent_id _category_group_list.description 'inclusive_group' . ; Categories that belong to the dictionary extension. ; 'array_data_group' 'inclusive_group' ; Categories that describe array data. ; 'axis_group' 'inclusive_group' ; Categories that describe axes. ; 'diffrn_group' 'inclusive_group' ; Categories that describe details of the diffraction experiment. ; ################## ## SUB_CATEGORY ## ################## loop_ _sub_category.id _sub_category.description 'matrix' ; The collection of elements of a matrix. ; 'vector' ; The collection of elements of a vector. ; ############## # ARRAY_DATA # ############## save_ARRAY_DATA _category.description ; Data items in the ARRAY_DATA category are the containers for the array data items described in the category ARRAY_STRUCTURE. ; _category.id array_data _category.mandatory_code no loop_ _category_key.name '_array_data.array_id' '_array_data.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows two binary data blocks. The first one was compressed by the CBF_CANONICAL compression algorithm and is presented as hexadecimal data. The first character 'H' on the data lines means hexadecimal. It could have been 'O' for octal or 'D' for decimal. The second character on the line shows the number of bytes in each word (in this case '4'), which then requires eight hexadecimal digits per word. The third character gives the order of octets within a word, in this case '<' for the ordering 4321 (i.e. 'big-endian'). Alternatively, the character '>' could have been used for the ordering 1234 (i.e. 'little-endian'). The block has a 'message digest' to check the integrity of the data. The second block is similar, but uses CBF_PACKED compression and BASE64 encoding. Note that the size and the digest are different. ; ; loop_ _array_data.array_id _array_data.binary_id _array_data.data image_1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF_CANONICAL" Content-Transfer-Encoding: X-BASE16 X-Binary-Size: 3927126 X-Binary-ID: 1 Content-MD5: u2sTJEovAHkmkDjPi+gWsg== # Hexadecimal encoding, byte 0, byte order ...21 # H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ... .... --CIF-BINARY-FORMAT-SECTION---- ; image_2 2 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF-PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3745758 X-Binary-ID: 2 Content-MD5: 1zsJjWPfol2GYl2V+QSXrw== ELhQAAAAAAAA... ... --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_data.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_data.array_id' _item.category_id array_data _item.mandatory_code yes _item_type.code code save_ save__array_data.binary_id _item_description.description ; This item is an integer identifier which, along with _array_data.array_id, should uniquely identify the particular block of array data. If _array_data.binary_id is not explicitly given, it defaults to 1. The value of _array_data.binary_id distinguishes among multiple sets of data with the same array structure. If the MIME header of the data array specifies a value for X-Binary-ID, the value of _array_data.binary_id should be equal to the value given for X-Binary-ID. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_data.binary_id' array_data implicit '_diffrn_data_frame.binary_id' diffrn_data_frame implicit '_array_intensities.binary_id' array_intensities implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.binary_id' '_array_data.binary_id' '_array_intensities.binary_id' '_array_data.binary_id' _item_default.value 1 _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_data.data _item_description.description ; The value of _array_data.data contains the array data encapsulated in a STAR string. The representation used is a variant on the Multipurpose Internet Mail Extensions (MIME) specified in RFC 2045-2049 by N. Freed et al. The boundary delimiter used in writing an imgCIF or CBF is '\n--CIF-BINARY-FORMAT-SECTION--' (including the required initial '\n--'). The Content-Type may be any of the discrete types permitted in RFC 2045; 'application/octet-stream' is recommended. If an octet stream was compressed, the compression should be specified by the parameter 'conversions="X-CBF_PACKED"' or the parameter 'conversions="X-CBF_CANONICAL"' or the parameter 'conversions="X-CBF_BYTE_OFFSET"' If the parameter 'conversions="X-CBF_PACKED"' is given it may be further modified with the parameters '"uncorrelated_sections"' or '"flat"' If the '"uncorrelated_sections"' parameter is given, each section will be compressed without using the prior section for averaging. If the '"flat"' parameter is given, each the image will be treated as one long row. The Content-Transfer-Encoding may be 'BASE64', 'Quoted-Printable', 'X-BASE8', 'X-BASE10', 'X-BASE16' or 'X-BASE32K', for an imgCIF or 'BINARY' for a CBF. The octal, decimal and hexadecimal transfer encodings are provided for convenience in debugging and are not recommended for archiving and data interchange. In a CIF, one of the parameters 'charset=us-ascii', 'charset=utf-8' or 'charset=utf-16' may be used on the Content-Transfer-Encoding to specify the character set used for the external presentation of the encoded data. If no charset parameter is given, the character set of the enclosing CIF is assumed. In any case, if a BOM flag is detected (FE FF for big-endian UTF-16, FF FE for little-endian UTF-16 or EF BB BF for UTF-8) is detected, the indicated charset will be assumed until the end of the encoded data or the detection of a different BOM. The charset of the Content-Transfer-Encoding is not the character set of the encoded data, only the character set of the presentation of the encoded data and should be respecified for each distinct STAR string. In an imgCIF file, the encoded binary data begins after the empty line terminating the header. In an imgCIF file, the encoded binary data ends with the terminating boundary delimiter '\n--CIF-BINARY-FORMAT-SECTION----' in the currently effective charset or with the '\n; ' that terminates the STAR string. In a CBF, the raw binary data begins after an empty line terminating the header and after the sequence: Octet Hex Decimal Purpose 0 0C 12 (ctrl-L) Page break 1 1A 26 (ctrl-Z) Stop listings in MS-DOS 2 04 04 (Ctrl-D) Stop listings in UNIX 3 D5 213 Binary section begins None of these octets are included in the calculation of the message size or in the calculation of the message digest. The X-Binary-Size header specifies the size of the equivalent binary data in octets. If compression was used, this size is the size after compression, including any book-keeping fields. An adjustment is made for the deprecated binary formats in which eight bytes of binary header are used for the compression type. In this case, the eight bytes used for the compression type are subtracted from the size, so that the same size will be reported if the compression type is supplied in the MIME header. Use of the MIME header is the recommended way to supply the compression type. In general, no portion of the binary header is included in the calculation of the size. The X-Binary-Element-Type header specifies the type of binary data in the octets, using the same descriptive phrases as in _array_structure.encoding_type. The default value is 'unsigned 32-bit integer'. An MD5 message digest may, optionally, be used. The 'RSA Data Security, Inc. MD5 Message-Digest Algorithm' should be used. No portion of the header is included in the calculation of the message digest. If the Transfer Encoding is 'X-BASE8', 'X-BASE10' or 'X-BASE16', the data are presented as octal, decimal or hexadecimal data organized into lines or words. Each word is created by composing octets of data in fixed groups of 2, 3, 4, 6 or 8 octets, either in the order ...4321 ('big- endian') or 1234... ('little-endian'). If there are fewer than the specified number of octets to fill the last word, then the missing octets are presented as '==' for each missing octet. Exactly two equal signs are used for each missing octet even for octal and decimal encoding. The format of lines is: rnd xxxxxx xxxxxx xxxxxx where r is 'H', 'O' or 'D' for hexadecimal, octal or decimal, n is the number of octets per word and d is '<' or '>' for the '...4321' and '1234...' octet orderings, respectively. The '==' padding for the last word should be on the appropriate side to correspond to the missing octets, e.g. H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000 or H3> FF0700 00==== For these hexadecimal, octal and decimal formats only, comments beginning with '#' are permitted to improve readability. BASE64 encoding follows MIME conventions. Octets are in groups of three: c1, c2, c3. The resulting 24 bits are broken into four six-bit quantities, starting with the high-order six bits (c1 >> 2) of the first octet, then the low-order two bits of the first octet followed by the high-order four bits of the second octet [(c1 & 3)<<4 | (c2>>4)], then the bottom four bits of the second octet followed by the high-order two bits of the last octet [(c2 & 15)<<2 | (c3>>6)], then the bottom six bits of the last octet (c3 & 63). Each of these four quantities is translated into an ASCII character using the mapping: 1 2 3 4 5 6 0123456789012345678901234567890123456789012345678901234567890123 | | | | | | | ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/ With short groups of octets padded on the right with one '=' if c3 is missing, and with '==' if both c2 and c3 are missing. X-BASE32K encoding is similar to BASE64 encoding, except that sets of 15 octets are encoded as sets of 8 16-bit unicode characters, by breaking the 120 bits into 8 15-bit quantities. 256 is added to each 15 bit quantity to bring it into a printable uncode range. When encoding, zero padding is used to fill out the last 15 bit quantity. If 8 or more bits of padding are used, a single equals sign (hexadecimal 003D) is appended. Embedded whitespace and newlines are introduced to produce lines of no more than 80 characters each. On decoding, all printable ascii characters and ascii whitespace characters are ignored except for any trailing equals signs. The number of trailing equals signs indicated the number of trailing octets to be trimmed from the end of the decoded data. (see Georgi Darakev, Vassil Litchev, Kostadin Z. Mitev, Herbert J. Bernstein, 'Efficient Support of Binary Data in the XML Implementation of the NeXus File Format',absract W0165, ACA Summer Meeting, Honolulu, HI, July 2006). QUOTED-PRINTABLE encoding also follows MIME conventions, copying octets without translation if their ASCII values are 32...38, 42, 48...57, 59, 60, 62, 64...126 and the octet is not a ';' in column 1. All other characters are translated to =nn, where nn is the hexadecimal encoding of the octet. All lines are 'wrapped' with a terminating '=' (i.e. the MIME conventions for an implicit line terminator are never used). The "X-Binary-Element-Byte-Order" can specify either '"BIG_ENDIAN"' or '"LITTLE_ENDIAN"' byte order of the imaage data. Only LITTLE_ENDIAN is recommended. Processors may treat BIG_ENDIAN as a warning of data that can only be processed by special software. The "X-Binary-Number-of-Elements" specifies the number of elements (not the number of octets) in the decompressed, decoded image. The optional "X-Binary-Size-Fastest-Dimension" specifies the number of elements (not the number of octets) in one row of the fastest changing dimension of the binary data array. This information must be in the MIME header for proper operation of some of the decompression algorithms. The optional "X-Binary-Size-Second-Dimension" specifies the number of elements (not the number of octets) in one column of the second-fastest changing dimension of the binary data array. This information must be in the MIME header for proper operation of some of the decompression algorithms. The optional "X-Binary-Size-Third-Dimension" specifies the number of sections for the third-fastest changing dimension of the binary data array. The optional "X-Binary-Size-Padding" specifies the size in octets of an optional padding after the binary array data and before the closing flags for a binary section. ; _item.name '_array_data.data' _item.category_id array_data _item.mandatory_code yes _item_type.code binary save_ ###################### # ARRAY_ELEMENT_SIZE # ###################### save_ARRAY_ELEMENT_SIZE _category.description ; Data items in the ARRAY_ELEMENT_SIZE category record the physical size of array elements along each array dimension. ; _category.id array_element_size _category.mandatory_code no loop_ _category_key.name '_array_element_size.array_id' '_array_element_size.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A regular 2D array with a uniform element dimension of 1220 nanometres. ; ; loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size image_1 1 1.22e-6 image_1 2 1.22e-6 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_element_size.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_element_size.array_id' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.index _item_description.description ; This item is a pointer to _array_structure_list.index in the ARRAY_STRUCTURE_LIST category. ; _item.name '_array_element_size.index' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.size _item_description.description ; The size in metres of an image element in this dimension. This supposes that the elements are arranged on a regular grid. ; _item.name '_array_element_size.size' _item.category_id array_element_size _item.mandatory_code yes _item_type.code float _item_units.code 'metres' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ ##################### # ARRAY_INTENSITIES # ##################### save_ARRAY_INTENSITIES _category.description ; Data items in the ARRAY_INTENSITIES category record the information required to recover the intensity data from the set of data values stored in the ARRAY_DATA category. The detector may have a complex relationship between the raw intensity values and the number of incident photons. In most cases, the number stored in the final array will have a simple linear relationship to the actual number of incident photons, given by _array_intensities.gain. If raw, uncorrected values are presented (e.g. for calibration experiments), the value of _array_intensities.linearity will be 'raw' and _array_intensities.gain will not be used. ; _category.id array_intensities _category.mandatory_code no loop_ _category_key.name '_array_intensities.array_id' '_array_intensities.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 ; ; loop_ _array_intensities.array_id _array_intensities.linearity _array_intensities.gain _array_intensities.overload _array_intensities.undefined_value _array_intensities.pixel_fast_bin_size _array_intensities.pixel_slow_bin_size _array_intensities.pixel_binning_method image_1 linear 1.2 655535 0 2 2 hardware ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_intensities.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_intensities.array_id' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code save_ save__array_intensities.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_array_intensities.binary_id' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code int save_ save__array_intensities.gain _item_description.description ; Detector 'gain'. The factor by which linearized intensity count values should be divided to produce true photon counts. ; _item.name '_array_intensities.gain' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain_esd' 'associated_value' save_ save__array_intensities.gain_esd _item_description.description ; The estimated standard deviation in detector 'gain'. ; _item.name '_array_intensities.gain_esd' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain' 'associated_esd' save_ save__array_intensities.linearity _item_description.description ; The intensity linearity scaling method used to convert from the raw intensity to the stored element value: 'linear' is linear. 'offset' means that the value defined by _array_intensities.offset should be added to each element value. 'scaling' means that the value defined by _array_intensities.scaling should be multiplied with each element value. 'scaling_offset' is the combination of the two previous cases, with the scale factor applied before the offset value. 'sqrt_scaled' means that the square root of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and squaring the result. 'logarithmic_scaled' means that the logarithm base 10 of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and calculating 10 to the power of this number. 'raw' means that the data are a set of raw values straight from the detector. ; _item.name '_array_intensities.linearity' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'linear' . 'offset' ; The value defined by _array_intensities.offset should be added to each element value. ; 'scaling' ; The value defined by _array_intensities.scaling should be multiplied with each element value. ; 'scaling_offset' ; The combination of the scaling and offset with the scale factor applied before the offset value. ; 'sqrt_scaled' ; The square root of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and squaring the result. ; 'logarithmic_scaled' ; The logarithm base 10 of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and calculating 10 to the power of this number. ; 'raw' ; The array consists of raw values to which no corrections have been applied. While the handling of the data is similar to that given for 'linear' data with no offset, the meaning of the data differs in that the number of incident photons is not necessarily linearly related to the number of counts reported. This value is intended for use either in calibration experiments or to allow for handling more complex data-fitting algorithms than are allowed for by this data item. ; save_ save__array_intensities.offset _item_description.description ; Offset value to add to array element values in the manner described by the item _array_intensities.linearity. ; _item.name '_array_intensities.offset' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.overload _item_description.description ; The saturation intensity level for this data array. ; _item.name '_array_intensities.overload' _item.category_id array_intensities _item.mandatory_code no _item_type.code float _item_units.code 'counts' save_ save__array_intensities.pixel_fast_bin_size _item_description.description ; The value of _array_intensities.pixel_fast_bin_size specifies the number of pixels that compose one element in the direction of the most rapidly varying array dimension. Typical values are 1, 2, 4 or 8. When there is 1 pixel per array element in both directions, the value given for _array_intensities.pixel_binning_method normally should be 'none'. It is specified as a float to allow for binning algorithms that create array elements that are not integer multiples of the detector pixel size. ; _item.name '_array_intensities.pixel_fast_bin_size' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code float _item_default.value 1. loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'pixels_per_element' save_ save__array_intensities.pixel_slow_bin_size _item_description.description ; The value of _array_intensities.pixel_slow_bin_size specifies the number of pixels that compose one element in the direction of the second most rapidly varying array dimension. Typical values are 1, 2, 4 or 8. When there is 1 pixel per array element in both directions, the value given for _array_intensities.pixel_binning_method normally should be 'none'. It is specified as a float to allow for binning algorithms that create array elements that are not integer multiples of the detector pixel size. ; _item.name '_array_intensities.pixel_slow_bin_size' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code float _item_default.value 1. loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'pixels_per_element' save_ save__array_intensities.pixel_binning_method _item_description.description ; The value of _array_intensities.pixel_binning_method specifies the method used to derive array elements from multiple pixels. ; _item.name '_array_intensities.pixel_binning_method' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'hardware' ; The element intensities were derived from the raw data of one or more pixels by used of hardware in the detector, e.g. by use of shift registers in a CCD to combine pixels into super-pixels. ; 'software' ; The element intensities were derived from the raw data of more than one pixel by use of software. ; 'combined' ; The element intensities were derived from the raw data of more than one pixel by use of both hardware and software, as when hardware binning is used in one direction and software in the other. ; 'none' ; In the both directions, the data has not been binned. The number of pixels is equal to the number of elements. When the value of _array_intensities.pixel_binning_method is 'none' the values of _array_intensities.pixel_fast_bin_size and _array_intensities.pixel_slow_bin_size both must be 1. ; 'unspecified' ; The method used to derive element intensities is not specified. ; _item_default.value 'unspecified' save_ save__array_intensities.scaling _item_description.description ; Multiplicative scaling value to be applied to array data in the manner described by item _array_intensities.linearity. ; _item.name '_array_intensities.scaling' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.undefined_value _item_description.description ; A value to be substituted for undefined values in the data array. ; _item.name '_array_intensities.undefined_value' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ ################### # ARRAY_STRUCTURE # ################### save_ARRAY_STRUCTURE _category.description ; Data items in the ARRAY_STRUCTURE category record the organization and encoding of array data that may be stored in the ARRAY_DATA category. ; _category.id array_structure _category.mandatory_code no _category_key.name '_array_structure.id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order image_1 "unsigned 16-bit integer" none little_endian ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure.byte_order _item_description.description ; The order of bytes for integer values which require more than 1 byte. (IBM-PC's and compatibles and DEC VAXs use low-byte-first ordered integers, whereas Hewlett Packard 700 series, Sun-4 and Silicon Graphics use high-byte-first ordered integers. DEC Alphas can produce/use either depending on a compiler switch.) ; _item.name '_array_structure.byte_order' _item.category_id array_structure _item.mandatory_code yes _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail 'big_endian' ; The first byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; 'little_endian' ; The last byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; save_ save__array_structure.compression_type _item_description.description ; Type of data-compression method used to compress the array data. ; _item.name '_array_structure.compression_type' _item.category_id array_structure _item.mandatory_code no _item_type.code ucode _item_default.value 'none' loop_ _item_enumeration.value _item_enumeration.detail 'byte_offset' ; Using the 'byte_offset' compression scheme as per A. Hammersley and the CBFlib manual, section 3.3.3 ; 'canonical' ; Using the 'canonical' compression scheme (International Tables for Crystallography Volume G, Section 5.6.3.1) and CBFlib manual section 3.3.1 ; 'none' ; Data are stored in normal format as defined by _array_structure.encoding_type and _array_structure.byte_order. ; 'packed' ; Using the 'packed' compression scheme, a CCP4-style packing as per J. P. Abrahams pack_c.c and CBFlib manual, section 3.3.2. ; 'packed_v2' ; Using the 'packed' compression scheme, version 2, as per J. P. Abrahams pack_c.c and CBFlib manual, section 3.3.2. ; save_ save__array_structure.compression_type_flag _item_description.description ; Flags modifying the type of data-compression method used to compress the arraydata. ; _item.name '_array_structure.compression_type_flag' _item.category_id array_structure _item.mandatory_code no _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail 'uncorrelated_sections' ; When applying packed or packed_v2 compression on an array with uncorrelated sections, do not average in points from the prior section. ; 'flat' ; When applying packed or packed_v2 compression on an array with treat the entire image as a single line set the maximum number of bits for an offset to 65 bits. The flag is included for compatibility with software prior to CBFlib_0.7.7, and should not be used for new data sets. ; save_ save__array_structure.encoding_type _item_description.description ; Data encoding of a single element of array data. In several cases, the IEEE format is referenced. See IEEE Standard 754-1985 (IEEE, 1985). Ref: IEEE (1985). IEEE Standard for Binary Floating-Point Arithmetic. ANSI/IEEE Std 754-1985. New York: Institute of Electrical and Electronics Engineers. ; _item.name '_array_structure.encoding_type' _item.category_id array_structure _item.mandatory_code yes _item_type.code uline loop_ _item_enumeration.value 'unsigned 8-bit integer' 'signed 8-bit integer' 'unsigned 16-bit integer' 'signed 16-bit integer' 'unsigned 32-bit integer' 'signed 32-bit integer' 'signed 32-bit real IEEE' 'signed 64-bit real IEEE' 'signed 32-bit complex IEEE' save_ save__array_structure.id _item_description.description ; The value of _array_structure.id must uniquely identify each item of array data. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure.id' array_structure yes '_array_data.array_id' array_data yes '_array_structure_list.array_id' array_structure_list yes '_array_intensities.array_id' array_intensities yes '_diffrn_data_frame.array_id' diffrn_data_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_data.array_id' '_array_structure.id' '_array_structure_list.array_id' '_array_structure.id' '_array_intensities.array_id' '_array_structure.id' '_diffrn_data_frame.array_id' '_array_structure.id' save_ ######################## # ARRAY_STRUCTURE_LIST # ######################## save_ARRAY_STRUCTURE_LIST _category.description ; Data items in the ARRAY_STRUCTURE_LIST category record the size and organization of each array dimension. The relationship to physical axes may be given. ; _category.id array_structure_list _category.mandatory_code no loop_ _category_key.name '_array_structure_list.array_id' '_array_structure_list.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - An image array of 1300 x 1200 elements. The raster order of the image is left to right (increasing) in the first dimension and bottom to top (decreasing) in the second dimension. ; ; loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id image_1 1 1300 1 increasing ELEMENT_X image_1 2 1200 2 decreasing ELEMENY_Y ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure_list.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_structure_list.array_id' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code code save_ save__array_structure_list.axis_set_id _item_description.description ; This is a descriptor for the physical axis or set of axes corresponding to an array index. This data item is related to the axes of the detector itself given in DIFFRN_DETECTOR_AXIS, but usually differs in that the axes in this category are the axes of the coordinate system of reported data points, while the axes in DIFFRN_DETECTOR_AXIS are the physical axes of the detector describing the 'poise' of the detector as an overall physical object. If there is only one axis in the set, the identifier of that axis should be used as the identifier of the set. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.axis_set_id' array_structure_list yes '_array_structure_list_axis.axis_set_id' array_structure_list_axis implicit _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_structure_list_axis.axis_set_id' '_array_structure_list.axis_set_id' save_ save__array_structure_list.dimension _item_description.description ; The number of elements stored in the array structure in this dimension. ; _item.name '_array_structure_list.dimension' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.direction _item_description.description ; Identifies the direction in which this array index changes. ; _item.name '_array_structure_list.direction' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'increasing' ; Indicates the index changes from 1 to the maximum dimension. ; 'decreasing' ; Indicates the index changes from the maximum dimension to 1. ; save_ save__array_structure_list.index _item_description.description ; Identifies the one-based index of the row or column in the array structure. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.index' array_structure_list yes '_array_structure_list.precedence' array_structure_list yes '_array_element_size.index' array_element_size yes _item_type.code int loop_ _item_linked.child_name _item_linked.parent_name '_array_element_size.index' '_array_structure_list.index' loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.precedence _item_description.description ; Identifies the rank order in which this array index changes with respect to other array indices. The precedence of 1 indicates the index which changes fastest. ; _item.name '_array_structure_list.precedence' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ ############################# # ARRAY_STRUCTURE_LIST_AXIS # ############################# save_ARRAY_STRUCTURE_LIST_AXIS _category.description ; Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe the physical settings of sets of axes for the centres of pixels that correspond to data points described in the ARRAY_STRUCTURE_LIST category. In the simplest cases, the physical increments of a single axis correspond to the increments of a single array index. More complex organizations, e.g. spiral scans, may require coupled motions along multiple axes. Note that a spiral scan uses two coupled axes: one for the angular direction and one for the radial direction. This differs from a cylindrical scan for which the two axes are not coupled into one set. ; _category.id array_structure_list_axis _category.mandatory_code no loop_ _category_key.name '_array_structure_list_axis.axis_set_id' '_array_structure_list_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' save_ save__array_structure_list_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes in the set of axes for which settings are being specified. Multiple axes may be specified for the same value of _array_structure_list_axis.axis_set_id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_array_structure_list_axis.axis_id' _item.category_id array_structure_list_axis _item.mandatory_code yes _item_type.code code save_ save__array_structure_list_axis.axis_set_id _item_description.description ; The value of this data item is the identifier of the set of axes for which axis settings are being specified. Multiple axes may be specified for the same value of _array_structure_list_axis.axis_set_id. This item is a pointer to _array_structure_list.axis_set_id in the ARRAY_STRUCTURE_LIST category. If this item is not specified, it defaults to the corresponding axis identifier. ; _item.name '_array_structure_list_axis.axis_set_id' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_type.code code save_ save__array_structure_list_axis.angle _item_description.description ; The setting of the specified axis in degrees for the first data point of the array index with the corresponding value of _array_structure_list.axis_set_id. If the index is specified as 'increasing', this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing', this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.angle' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.angle_increment _item_description.description ; The pixel-centre-to-pixel-centre increment in the angular setting of the specified axis in degrees. This is not meaningful in the case of 'constant velocity' spiral scans and should not be specified for this case. See _array_structure_list_axis.angular_pitch. ; _item.name '_array_structure_list_axis.angle_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for the first data point of the array index with the corresponding value of _array_structure_list.axis_set_id. If the index is specified as 'increasing', this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing', this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.displacement' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.fract_displacement _item_description.description ; The setting of the specified axis as a decimal fraction of the axis unit vector for the first data point of the array index with the corresponding value of _array_structure_list.axis_set_id. If the index is specified as 'increasing', this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing', this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.fract_displacement' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float save_ save__array_structure_list_axis.displacement_increment _item_description.description ; The pixel-centre-to-pixel-centre increment for the displacement setting of the specified axis in millimetres. ; _item.name '_array_structure_list_axis.displacement_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.fract_displacement_increment _item_description.description ; The pixel-centre-to-pixel-centre increment for the displacement setting of the specified axis as a decimal fraction of the axis unit vector. ; _item.name '_array_structure_list_axis.fract_displacement_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.angular_pitch _item_description.description ; The pixel-centre-to-pixel-centre distance for a one-step change in the setting of the specified axis in millimetres. This is meaningful only for 'constant velocity' spiral scans or for uncoupled angular scans at a constant radius (cylindrical scans) and should not be specified for cases in which the angle between pixels (rather than the distance between pixels) is uniform. See _array_structure_list_axis.angle_increment. ; _item.name '_array_structure_list_axis.angular_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.radial_pitch _item_description.description ; The radial distance from one 'cylinder' of pixels to the next in millimetres. If the scan is a 'constant velocity' scan with differing angular displacements between pixels, the value of this item may differ significantly from the value of _array_structure_list_axis.displacement_increment. ; _item.name '_array_structure_list_axis.radial_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.reference_angle _item_description.description ; The value of _array_structure_list_axis.reference_angle specifies the setting of the angle of this axis used for determining a reference beam center and a reference detector distance. It is normally expected to be identical to the value of _array_structure_list.angle. ; _item.name '_array_structure_list_axis.reference_angle' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.reference_displacement _item_description.description ; The value of _array_structure_list_axis.reference_displacement specifies the setting of the displacement of this axis used for determining a reference beam center and a reference detector distance. It is normally expected to be identical to the value of _array_structure_list.displacement. ; _item.name '_array_structure_list_axis.reference_displacement' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'millimetres' save_ ######## # AXIS # ######## save_AXIS _category.description ; Data items in the AXIS category record the information required to describe the various goniometer, detector, source and other axes needed to specify a data collection or the axes defining the coordinate system of an image. The location of each axis is specified by two vectors: the axis itself, given by a unit vector in the direction of the axis, and an offset to the base of the unit vector. The vectors defining an axis are referenced to an appropriate coordinate system. The axis vector, itself, is a dimensionless unit vector. Where meaningful, the offset vector is given in millimetres. In coordinate systems not measured in metres, the offset is not specified and is taken as zero. The available coordinate systems are: The imgCIF standard laboratory coordinate system The direct lattice (fractional atomic coordinates) The orthogonal Cartesian coordinate system (real space) The reciprocal lattice An abstract orthogonal Cartesian coordinate frame For consistency in this discussion, we call the three coordinate system axes X, Y and Z. This is appropriate for the imgCIF standard laboratory coordinate system, and last two Cartesian coordinate systems, but for the direct lattice, X corresponds to a, Y to b and Z to c, while for the reciprocal lattice, X corresponds to a*, Y to b* and Z to c*. For purposes of visualization, all the coordinate systems are taken as right-handed, i.e., using the convention that the extended thumb of a right hand could point along the first (X) axis, the straightened pointer finger could point along the second (Y) axis and the middle finger folded inward could point along the third (Z) axis. THE IMGCIF STANDARD LABORATORY COORDINATE SYSTEM The imgCIF standard laboratory coordinate system is a right-handed orthogonal coordinate similar to the MOSFLM coordinate system, but imgCIF puts Z along the X-ray beam, rather than putting X along the X-ray beam as in MOSFLM. The vectors for the imgCIF standard laboratory coordinate system form a right-handed Cartesian coordinate system with its origin in the sample or specimen. The origin of the axis system should, if possible, be defined in terms of mechanically stable axes to be in the sample and in the beam. If the sample goniometer or other sample positioner has two axes the intersection which defines a unique point at which the sample should be mounted to be bathed by the beam, that will be the origin of the axis system. If no such point is defined, then the midpoint of the line of intersection between the sample and the center of the beam will define the origin. For this definition the sample positioning system will be set at its initial reference position for the experiment. | Y (to complete right-handed system) | | | | | |________________X / principal goniometer axis / / / / /Z (to source) Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from the sample or specimen along the principal axis of the goniometer or sample positioning system if the sample positioning system has an axis that intersects the origin and which form an angle of more than 22.5 degrees with the beam axis. Axis 2 (Y): The Y-axis completes an orthogonal right-handed system defined by the X-axis and the Z-axis (see below). Axis 3 (Z): The Z-axis is derived from the source axis which goes from the sample to the source. The Z-axis is the component of the source axis in the direction of the source orthogonal to the X-axis in the plane defined by the X-axis and the source axis. If the conditions for the X-axis can be met, the coordinate system will be based on the goniometer or other sample positioning system and the beam and not on the orientation of the detector, gravity etc. The vectors necessary to specify all other axes are given by sets of three components in the order (X, Y, Z). If the axis involved is a rotation axis, it is right-handed, i.e. as one views the object to be rotated from the origin (the tail) of the unit vector, the rotation is clockwise. If a translation axis is specified, the direction of the unit vector specifies the sense of positive translation. Note: This choice of coordinate system is similar to but significantly different from the choice in MOSFLM (Leslie & Powell, 2004). In MOSFLM, X is along the X-ray beam (the CBF/imgCIF Z axis) and Z is along the rotation axis. In some experimental techniques, there is no goniometer or the principal axis of the goniometer is at a small acute angle with respect to the source axis. In such cases, other reference axes are needed to define a useful coordinate system. The order of priority in defining directions in such cases is to use the detector, then gravity, then north. If the X-axis cannot be defined as above, then the direction (not the origin) of the X-axis should be parallel to the axis of the primary detector element corresponding to the most rapidly varying dimension of that detector element's data array, with its positive sense corresponding to increasing values of the index for that dimension. If the detector is such that such a direction cannot be defined (as with a point detector) or that direction forms an angle of less than 22.5 degrees with respect to the source axis, then the X-axis should be chosen so that if the Y-axis is chosen in the direction of gravity, and the Z-axis is chosen to be along the source axis, a right-handed orthogonal coordinate system is chosen. In the case of a vertical source axis, as a last resort, the X-axis should be chosen to point North. All rotations are given in degrees and all translations are given in mm. Axes may be dependent on one another. The X-axis is the only goniometer axis the direction of which is strictly connected to the hardware. All other axes are specified by the positions they would assume when the axes upon which they depend are at their zero points. When specifying detector axes, the axis is given to the beam centre. The location of the beam centre on the detector should be given in the DIFFRN_DETECTOR category in distortion-corrected millimetres from the (0,0) corner of the detector. It should be noted that many different origins arise in the definition of an experiment. In particular, as noted above, it is necessary to specify the location of the beam centre on the detector in terms of the origin of the detector, which is, of course, not coincident with the centre of the sample. The unit cell, reciprocal cell and crystallographic orthogonal Cartesian coordinate system are defined by the CELL and the matrices in the ATOM_SITES category. THE DIRECT LATTICE (FRACTIONAL COORDINATES) The direct lattice coordinate system is a system of fractional coordinates aligned to the crystal, rather than to the laboratory. This is a natural coordinate system for maps and atomic coordinates. It is the simplest coordinate system in which to apply symmetry. The axes are determined by the cell edges, and are not necessarily othogonal. This coordinate system is not uniquely defined and depends on the cell parameters in the CELL category and the settings chosen to index the crystal. Molecules in a crystal studied by X-ray diffracraction are organized into a repeating regular array of unit cells. Each unit cell is defined by three vectors, a, b and c. To quote from Drenth, "The choice of the unit cell is not unique and therefore, guidelines have been established for selecting the standard basis vectors and the origin. They are based on symmetry and metric considerations: "(1) The axial system should be right handed. (2) The basis vectors should coincide as much as possible with directions of highest symmetry." (3) The cell taken should be the smallest one that satisfies condition (2) (4) Of all the lattice vectors, none is shorter than a. (5) Of those not directed along a, none is shorter than b. (6) Of those not lying in the ab plane, none is shorter than c. (7) The three angles between the basis vectors a, b and c are either all acute (<90 degrees) or all obtuse (>=90 degrees)." These rules do not produce a unique result that is stable under the assumption of experimental errors, and the the resulting cell may not be primitive. In this coordinate system, the vector (.5, .5, .5) is in the middle of the given unit cell. Grid coordinates are an important variation on fractional coordinates used when working with maps. In imgCIF, the conversion from fractional to grid coordinates is implicit in the array indexing specified by _array_structure_list.dimension. Note that this implicit grid-coordinate scheme is 1-based, not zero-based, i.e. the origin of the cell for axes along the cell edges with no specified _array_structure_list_axis.displacement will have grid coordinates of (1,1,1), i.e. array indices of (1,1,1). THE ORTHOGONAL CARTESIAN COORDINATE SYSTEM (REAL SPACE) The orthogonal Cartesian coordinate system is a transformation of the direct lattice to the actual physical coordinates of atoms in space. It is similar to the laboratory coordinate system, but is anchored to and moves with the crystal, rather than being schored to the laboratory. The transformation from fractional to orthogonal cartesian coordinates is given by the _atom_sites.Cartn_transf_matrix[i][j] and _atom_sites.Cartn_transf_vector[i] tags. A common choice for the matrix of the transformation is given in the 1992 PDB format document | a b cos(g) c cos(b) | | 0 b sin(g) c (cos(a) - cos(b)cos(g))/sin(g) | | 0 0 V/(a b sin(g)) | This is a convenient coordinate system in which to do fitting of models to maps and in which to understand the chemistry of a molecule. THE RECIPROCAL LATTICE The reciprocal lattice coordinate system is used for diffraction intensitities. It is based on the reciprocal cell, the dual of the cell, in which reciprocal cell edges are derived from direct cell faces: a* = bc sin(a)/V b* = ac sin(b)/V c* = ab sin(g)/V cos(a*) = (cos(b) cos(g) - cos(a))/(sin(b) sin(g)) cos(b*) = (cos(g) cos(g) - cos(b) )/(sin(a) sin(g)) cos(g*) = (cos(a) cos(b) - cos(g))/(sin(a) sin(b)) V = abc SQRT (1 - cos(a)2 - cos(b)2 - cos(g)2 + 2 cos(a) cos(b) cos(g) ) In this form the dimensions of the reciprocal lattice are in reciprocal \%Angstroms (\%A^-1). A dimensionless form can be obtained by multiplying by the wavelength. Reflections are commonly indexed against this coordinate system as (h, k, l) triples. References: Drenth, J., "Introduction to basic crystallography." chapter 2.1 in Rossmann, M. G. and Arnold, E. "Crystallography of biological macromolecules", Volume F of the IUCr's "International tables for crystallography", Kluwer, Dordrecht 2001, pp 44 -- 63 Leslie, A. G. W. and Powell, H. (2004). MOSFLM v6.11. MRC Laboratory of Molecular Biology, Hills Road, Cambridge, England. http://www.CCP4.ac.uk/dist/X-windows/Mosflm/. Stout, G. H. and Jensen, L. H., "X-ray structure determination", 2nd ed., Wiley, New York, 1989, 453 pp. __, "PROTEIN DATA BANK ATOMIC COORDINATE AND BIBLIOGRAPHIC ENTRY FORMAT DESCRIPTION," Brookhaven National Laboratory, February 1992. ; _category.id axis _category.mandatory_code no loop_ _category_key.name '_axis.id' '_axis.equipment' loop_ _category_group.id 'inclusive_group' 'axis_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows the axis specification of the axes of a kappa- geometry goniometer [see Stout, G. H. & Jensen, L. H. (1989). X-ray structure determination. A practical guide, 2nd ed. p. 134. New York: Wiley Interscience]. There are three axes specified, and no offsets. The outermost axis, omega, is pointed along the X axis. The next innermost axis, kappa, is at a 50 degree angle to the X axis, pointed away from the source. The innermost axis, phi, aligns with the X axis when omega and phi are at their zero points. If T-omega, T-kappa and T-phi are the transformation matrices derived from the axis settings, the complete transformation would be: X' = (T-omega) (T-kappa) (T-phi) X ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] omega rotation goniometer . 1 0 0 kappa rotation goniometer omega -.64279 0 -.76604 phi rotation goniometer kappa 1 0 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - This example shows the axis specification of the axes of a detector, source and gravity. The order has been changed as a reminder that the ordering of presentation of tokens is not significant. The centre of rotation of the detector has been taken to be 68 millimetres in the direction away from the source. ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] source . source . 0 0 1 . . . gravity . gravity . 0 -1 0 . . . tranz translation detector rotz 0 0 1 0 0 -68 twotheta rotation detector . 1 0 0 . . . roty rotation detector twotheta 0 1 0 0 0 -68 rotz rotation detector roty 0 0 1 0 0 -68 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 3 - This example show the axis specification of the axes for a map, using fractional coordinates. Each cell edge has been divided into a grid of 50 divisions in the ARRAY_STRUCTURE_LIST_AXIS category. The map is using only the first octant of the grid in the ARRAY_STRUCTURE_LIST category. The fastest changing axis is the gris along A, then along B, and the slowest is along C. The map sampling is being done in the middle of each grid division ; ; loop_ _axis.id _axis.system _axis.vector[1] _axis.vector[2] _axis.vector[3] CELL_A_AXIS fractional 1 0 0 CELL_B_AXIS fractional 0 1 0 CELL_C_AXIS fractional 0 0 1 loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_id MAP 1 25 1 increasing CELL_A_AXIS MAP 1 25 2 increasing CELL_B_AXIS MAP 1 25 3 increasing CELL_C_AXIS loop_ _array_structure_list_axis.axis_id _array_structure_list_axis.fract_displacement _array_structure_list_axis.fract_displacement_increment CELL_A_AXIS 0.01 0.02 CELL_B_AXIS 0.01 0.02 CELL_C_AXIS 0.01 0.02 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 4 - This example show the axis specification of the axes for a map, this time as orthogonal Angstroms, using the same coordinate system as for the atomic coordinates. The map is sampling every 1.5 Angstroms (1.5e-7 millimeters) in a map segment 37.5 Angstroms on a side. ; ; loop_ _axis.id _axis.system _axis.vector[1] _axis.vector[2] _axis.vector[3] X orthogonal 1 0 0 Y orthogonal 0 1 0 Z orthogonal 0 0 1 loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_id MAP 1 25 1 increasing X MAP 2 25 2 increasing Y MAP 3 25 3 increasing Z loop_ _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment X 7.5e-8 1.5e-7 Y 7.5e-8 1.5e-7 Z 7.5e-8 1.5e-7 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__axis.depends_on _item_description.description ; The value of _axis.depends_on specifies the next outermost axis upon which this axis depends. This item is a pointer to _axis.id in the same category. ; _item.name '_axis.depends_on' _item.category_id axis _item.mandatory_code no save_ save__axis.equipment _item_description.description ; The value of _axis.equipment specifies the type of equipment using the axis: 'goniometer', 'detector', 'gravity', 'source' or 'general'. ; _item.name '_axis.equipment' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail goniometer 'equipment used to orient or position samples' detector 'equipment used to detect reflections' general 'equipment used for general purposes' gravity 'axis specifying the downward direction' source 'axis specifying the direction sample to source' save_ save__axis.offset[1] _item_description.description ; The [1] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[2] _item_description.description ; The [2] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[3] _item_description.description ; The [3] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.id _item_description.description ; The value of _axis.id must uniquely identify each axis relevant to the experiment. Note that multiple pieces of equipment may share the same axis (e.g. a twotheta arm), so the category key for AXIS also includes the equipment. ; loop_ _item.name _item.category_id _item.mandatory_code '_axis.id' axis yes '_array_structure_list_axis.axis_id' array_structure_list_axis yes '_diffrn_detector_axis.axis_id' diffrn_detector_axis yes '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes '_diffrn_scan_axis.axis_id' diffrn_scan_axis yes '_diffrn_scan_frame_axis.axis_id' diffrn_scan_frame_axis yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_axis.depends_on' '_axis.id' '_array_structure_list_axis.axis_id' '_axis.id' '_diffrn_detector_axis.axis_id' '_axis.id' '_diffrn_measurement_axis.axis_id' '_axis.id' '_diffrn_scan_axis.axis_id' '_axis.id' '_diffrn_scan_frame_axis.axis_id' '_axis.id' save_ save__axis.system _item_description.description ; The value of _axis.system specifies the coordinate system used to define the axis: 'laboratory', 'direct', 'orthogonal', 'reciprocal' or 'abstract'. ; _item.name '_axis.system' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value laboratory loop_ _item_enumeration.value _item_enumeration.detail laboratory ; the axis is referenced to the imgCIF standard laboratory Cartesian coordinate system ; direct ; the axis is referenced to the direct lattice ; orthogonal ; the axis is referenced to the cell Cartesian orthogonal coordinates ; reciprocal ; the axis is referenced to the reciprocal lattice ; abstract ; the axis is referenced to abstract Cartesian cooridinate system ; save_ save__axis.type _item_description.description ; The value of _axis.type specifies the type of axis: 'rotation' or 'translation' (or 'general' when the type is not relevant, as for gravity). ; _item.name '_axis.type' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail rotation 'right-handed axis of rotation' translation 'translation in the direction of the axis' general 'axis for which the type is not relevant' save_ save__axis.vector[1] _item_description.description ; The [1] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[2] _item_description.description ; The [2] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[3] _item_description.description ; The [3] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ ##################### # DIFFRN_DATA_FRAME # ##################### save_DIFFRN_DATA_FRAME _category.description ; Data items in the DIFFRN_DATA_FRAME category record the details about each frame of data. The items in this category were previously in a DIFFRN_FRAME_DATA category, which is now deprecated. The items from the old category are provided as aliases but should not be used for new work. ; _category.id diffrn_data_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_data_frame.id' '_diffrn_data_frame.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A frame containing data from 4 frame elements. Each frame element has a common array configuration 'array_1' described in ARRAY_STRUCTURE and related categories. The data for each detector element are stored in four groups of binary data in the ARRAY_DATA category, linked by the array_id and binary_id. ; ; loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id frame_1 d1_ccd_1 array_1 1 frame_1 d1_ccd_2 array_1 2 frame_1 d1_ccd_3 array_1 3 frame_1 d1_ccd_4 array_1 4 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_data_frame.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_diffrn_data_frame.array_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.array_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_diffrn_data_frame.binary_id' _item.category_id diffrn_data_frame _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_frame_data.binary_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code int save_ save__diffrn_data_frame.detector_element_id _item_description.description ; This item is a pointer to _diffrn_detector_element.id in the DIFFRN_DETECTOR_ELEMENT category. ; _item.name '_diffrn_data_frame.detector_element_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.detector_element_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.id _item_description.description ; The value of _diffrn_data_frame.id must uniquely identify each complete frame of data. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_data_frame.id' diffrn_data_frame yes '_diffrn_refln.frame_id' diffrn_refln yes '_diffrn_scan.frame_id_start' diffrn_scan yes '_diffrn_scan.frame_id_end' diffrn_scan yes '_diffrn_scan_frame.frame_id' diffrn_scan_frame yes '_diffrn_scan_frame_axis.frame_id' diffrn_scan_frame_axis yes _item_aliases.alias_name '_diffrn_frame_data.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_refln.frame_id' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_start' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_end' '_diffrn_data_frame.id' '_diffrn_scan_frame.frame_id' '_diffrn_data_frame.id' '_diffrn_scan_frame_axis.frame_id' '_diffrn_data_frame.id' save_ save__diffrn_data_frame.details _item_description.description ; The value of _diffrn_data_frame.details should give a description of special aspects of each frame of data. This is an appropriate location in which to record information from vendor headers as presented in those headers, but it should never be used as a substitute for providing the fully parsed information within the appropriate imgCIF/CBF categories. ; _item.name '_diffrn_data_frame.details' _item.category_id diffrn_data_frame _item.mandatory_code no _item_aliases.alias_name '_diffrn_frame_data.details' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.4 _item_type.code text loop_ _item_examples.case _item_examples.detail ; HEADER_BYTES = 512; DIM = 2; BYTE_ORDER = big_endian; TYPE = unsigned_short; SIZE1 = 3072; SIZE2 = 3072; PIXEL_SIZE = 0.102588; BIN = 2x2; DETECTOR_SN = 901; TIME = 29.945155; DISTANCE = 200.000000; PHI = 85.000000; OSC_START = 85.000000; OSC_RANGE = 1.000000; WAVELENGTH = 0.979381; BEAM_CENTER_X = 157.500000; BEAM_CENTER_Y = 157.500000; PIXEL SIZE = 0.102588; OSCILLATION RANGE = 1; EXPOSURE TIME = 29.9452; TWO THETA = 0; BEAM CENTRE = 157.5 157.5; ; ; Example of header information extracted from an ADSC Quantum 315 detector header by CBFlib_0.7.6. Image provided by Chris Nielsen of ADSC from a data collection at SSRL beamline 1-5. ; save_ ########################################################################## # The following is a restatement of the mmCIF DIFFRN_DETECTOR, # # DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for # # the CBF/imgCIF extensions # ########################################################################## ################### # DIFFRN_DETECTOR # ################### save_DIFFRN_DETECTOR _category.description ; Data items in the DIFFRN_DETECTOR category describe the detector used to measure the scattered radiation, including any analyser and post-sample collimation. ; _category.id diffrn_detector _category.mandatory_code no loop_ _category_key.name '_diffrn_detector.diffrn_id' '_diffrn_detector.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _diffrn_detector.diffrn_id 'd1' _diffrn_detector.detector 'multiwire' _diffrn_detector.type 'Siemens' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector.details _item_description.description ; A description of special aspects of the radiation detector. ; _item.name '_diffrn_detector.details' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'slow mode' save_ save__diffrn_detector.detector _item_description.description ; The general class of the radiation detector. ; _item.name '_diffrn_detector.detector' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector' cifdic.c91 1.0 '_diffrn_detector' cif_core.dic 2.0 _item_type.code text loop_ _item_examples.case 'photographic film' 'scintillation counter' 'CCD plate' 'BF~3~ counter' save_ save__diffrn_detector.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. The value of _diffrn.id uniquely defines a set of diffraction data. ; _item.name '_diffrn_detector.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector.dtime _item_description.description ; The deadtime in microseconds of the detector(s) used to measure the diffraction intensities. ; _item.name '_diffrn_detector.dtime' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector_dtime' cifdic.c91 1.0 '_diffrn_detector_dtime' cif_core.dic 2.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code microseconds save_ save__diffrn_detector.id _item_description.description ; The value of _diffrn_detector.id must uniquely identify each detector used to collect each diffraction data set. If the value of _diffrn_detector.id is not given, it is implicitly equal to the value of _diffrn_detector.diffrn_id. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector.id' diffrn_detector implicit '_diffrn_detector_axis.detector_id' diffrn_detector_axis yes loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_detector_axis.detector_id' '_diffrn_detector.id' _item_type.code code save_ save__diffrn_detector.number_of_axes _item_description.description ; The value of _diffrn_detector.number_of_axes gives the number of axes of the positioner for the detector identified by _diffrn_detector.id. The word 'positioner' is a general term used in instrumentation design for devices that are used to change the positions of portions of apparatus by linear translation, rotation or combinations of such motions. Axes which are used to provide a coordinate system for the face of an area detetctor should not be counted for this data item. The description of each axis should be provided by entries in DIFFRN_DETECTOR_AXIS. ; _item.name '_diffrn_detector.number_of_axes' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_detector.type _item_description.description ; The make, model or name of the detector device used. ; _item.name '_diffrn_detector.type' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ ######################## # DIFFRN_DETECTOR_AXIS # ######################## save_DIFFRN_DETECTOR_AXIS _category.description ; Data items in the DIFFRN_DETECTOR_AXIS category associate axes with detectors. ; _category.id diffrn_detector_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_axis.detector_id' '_diffrn_detector_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_detector_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_detector_axis.axis_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_axis.detector_id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. This item was previously named _diffrn_detector_axis.id which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_detector_axis.detector_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_aliases.alias_name '_diffrn_detector_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ ########################### # DIFFRN_DETECTOR_ELEMENT # ########################### save_DIFFRN_DETECTOR_ELEMENT _category.description ; Data items in the DIFFRN_DETECTOR_ELEMENT category record the details about spatial layout and other characteristics of each element of a detector which may have multiple elements. In most cases, giving more detailed information in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS is preferable to simply providing the centre of the detector element. ; _category.id diffrn_detector_element _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_element.id' '_diffrn_detector_element.detector_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Detector d1 is composed of four CCD detector elements, each 200 mm by 200 mm, arranged in a square, in the pattern 1 2 * 3 4 Note that the beam centre is slightly displaced from each of the detector elements, just beyond the lower right corner of 1, the lower left corner of 2, the upper right corner of 3 and the upper left corner of 4. ; ; loop_ _diffrn_detector_element.detector_id _diffrn_detector_element.id _diffrn_detector_element.center[1] _diffrn_detector_element.center[2] d1 d1_ccd_1 201.5 -1.5 d1 d1_ccd_2 -1.8 -1.5 d1 d1_ccd_3 201.6 201.4 d1 d1_ccd_4 -1.7 201.5 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector_element.center[1] _item_description.description ; The value of _diffrn_detector_element.center[1] is the X component of the distortion-corrected beam centre in millimetres from the (0, 0) (lower-left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. ; _item.name '_diffrn_detector_element.center[1]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.center[2] _item_description.description ; The value of _diffrn_detector_element.center[2] is the Y component of the distortion-corrected beam centre in millimetres from the (0, 0) (lower-left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. ; _item.name '_diffrn_detector_element.center[2]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.id _item_description.description ; The value of _diffrn_detector_element.id must uniquely identify each element of a detector. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector_element.id' diffrn_detector_element yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.detector_element_id' '_diffrn_detector_element.id' save_ save__diffrn_detector_element.detector_id _item_description.description ; This item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. ; _item.name '_diffrn_detector_element.detector_id' _item.category_id diffrn_detector_element _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_element.reference_center_fast _item_description.description ; The value of _diffrn_detector_element.reference_center_fast is the fast index axis beam center position relative to the detector element face in millimetres along that from the first pixel to the point at which the Z-axis (which should be colinear with the beam) intersects the face of the detector, if in fact is does. At the time of the measurement all settings of the detector positioner should be at their reference settings. If more than one reference setting has been used the value given whould be representive of the beam center as determined from the ensemble of settings. It is important to note that the sense of the axis is used, rather than the sign of the pixel-to-pixel increments. ; _item.name '_diffrn_detector_element.reference_center_fast' _item.category_id diffrn_detector_element _item.mandatory_code no _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.reference_center_slow _item_description.description ; The value of _diffrn_detector_element.reference_center_slow is the slow index axis beam center position relative to the detector element face in millimetres along that from the first pixel to the point at which the Z-axis (which should be colinear with the beam) intersects the face of the detector, if in fact is does. At the time of the measurement all settings of the detector positioner should be at their reference settings. If more than one reference setting has been used the value givien whould be representive of the beam center as determined from the ensemble of settings. It is important to note that the sense of the axis is used, rather than the sign of the pixel-to-pixel increments. ; _item.name '_diffrn_detector_element.reference_center_slow' _item.category_id diffrn_detector_element _item.mandatory_code no _item_type.code float _item_units.code millimetres save_ ######################## ## DIFFRN_MEASUREMENT ## ######################## save_DIFFRN_MEASUREMENT _category.description ; Data items in the DIFFRN_MEASUREMENT category record details about the device used to orient and/or position the crystal during data measurement and the manner in which the diffraction data were measured. ; _category.id diffrn_measurement _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement.device' '_diffrn_measurement.diffrn_id' '_diffrn_measurement.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_measurement.diffrn_id 'd1' _diffrn_measurement.device '3-circle camera' _diffrn_measurement.device_type 'Supper model X' _diffrn_measurement.device_details 'none' _diffrn_measurement.method 'omega scan' _diffrn_measurement.details ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _diffrn_measurement.diffrn_id 's1' _diffrn_measurement.device_type 'Philips PW1100/20 diffractometer' _diffrn_measurement.method 'theta/2theta (\q/2\q)' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_measurement.device _item_description.description ; The general class of goniometer or device used to support and orient the specimen. If the value of _diffrn_measurement.device is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id. Either _diffrn_measurement.device or _diffrn_measurement.id may be used to link to other categories. If the experimental setup admits multiple devices, then _diffrn_measurement.id is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.device' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_device' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement.device' _item_aliases.alias_name '_diffrn_measurement_device' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '3-circle camera' '4-circle camera' 'kappa-geometry camera' 'oscillation camera' 'precession camera' save_ save__diffrn_measurement.device_details _item_description.description ; A description of special aspects of the device used to measure the diffraction intensities. ; _item.name '_diffrn_measurement.device_details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; commercial goniometer modified locally to allow for 90\% \t arc ; save_ save__diffrn_measurement.device_type _item_description.description ; The make, model or name of the measurement device (goniometer) used. ; _item.name '_diffrn_measurement.device_type' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Supper model q' 'Huber model r' 'Enraf-Nonius model s' 'home-made' save_ save__diffrn_measurement.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_measurement.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement.details _item_description.description ; A description of special aspects of the intensity measurement. ; _item.name '_diffrn_measurement.details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; save_ save__diffrn_measurement.id _item_description.description ; The value of _diffrn_measurement.id must uniquely identify the set of mechanical characteristics of the device used to orient and/or position the sample used during the collection of each diffraction data set. If the value of _diffrn_measurement.id is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id. Either _diffrn_measurement.device or _diffrn_measurement.id may be used to link to other categories. If the experimental setup admits multiple devices, then _diffrn_measurement.id is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.id' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_id' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement.id' _item_type.code code save_ save__diffrn_measurement.method _item_description.description ; Method used to measure intensities. ; _item.name '_diffrn_measurement.method' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_method' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'profile data from theta/2theta (\q/2\q) scans' save_ save__diffrn_measurement.number_of_axes _item_description.description ; The value of _diffrn_measurement.number_of_axes gives the number of axes of the positioner for the goniometer or other sample orientation or positioning device identified by _diffrn_measurement.id. The description of the axes should be provided by entries in DIFFRN_MEASUREMENT_AXIS. ; _item.name '_diffrn_measurement.number_of_axes' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_measurement.specimen_support _item_description.description ; The physical device used to support the crystal during data collection. ; _item.name '_diffrn_measurement.specimen_support' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_specimen_support' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'glass capillary' 'quartz capillary' 'fiber' 'metal loop' save_ ########################### # DIFFRN_MEASUREMENT_AXIS # ########################### save_DIFFRN_MEASUREMENT_AXIS _category.description ; Data items in the DIFFRN_MEASUREMENT_AXIS category associate axes with goniometers. ; _category.id diffrn_measurement_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_measurement_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_measurement_axis.axis_id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.measurement_device _item_description.description ; This data item is a pointer to _diffrn_measurement.device in the DIFFRN_MEASUREMENT category. ; _item.name '_diffrn_measurement_axis.measurement_device' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit _item_type.code text save_ save__diffrn_measurement_axis.measurement_id _item_description.description ; This data item is a pointer to _diffrn_measurement.id in the DIFFRN_MEASUREMENT category. This item was previously named _diffrn_measurement_axis.id, which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_measurement_axis.measurement_id' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_measurement_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ #################### # DIFFRN_RADIATION # #################### save_DIFFRN_RADIATION _category.description ; Data items in the DIFFRN_RADIATION category describe the radiation used for measuring diffraction intensities, its collimation and monochromatization before the sample. Post-sample treatment of the beam is described by data items in the DIFFRN_DETECTOR category. ; _category.id diffrn_radiation _category.mandatory_code no _category_key.name '_diffrn_radiation.diffrn_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_radiation.diffrn_id 'set1' _diffrn_radiation.collimation '0.3 mm double pinhole' _diffrn_radiation.monochromator 'graphite' _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.wavelength_id 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _diffrn_radiation.wavelength_id 1 _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.monochromator 'graphite' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_radiation.collimation _item_description.description ; The collimation or focusing applied to the radiation. ; _item.name '_diffrn_radiation.collimation' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_collimation' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '0.3 mm double-pinhole' '0.5 mm' 'focusing mirrors' save_ save__diffrn_radiation.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_radiation.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_radiation.div_x_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory X axis (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the standard uncertainty (e.s.d.) of the directions of photons in the XZ plane around the mean source beam direction. Note that for some synchrotrons this value is specified in milliradians, in which case a conversion is needed. To convert a value in milliradians to a value in degrees, multiply by 0.180 and divide by \p. ; _item.name '_diffrn_radiation.div_x_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.div_y_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory Y axis (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the standard uncertainty (e.s.d.) of the directions of photons in the YZ plane around the mean source beam direction. Note that for some synchrotrons this value is specified in milliradians, in which case a conversion is needed. To convert a value in milliradians to a value in degrees, multiply by 0.180 and divide by \p. ; _item.name '_diffrn_radiation.div_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.div_x_y_source _item_description.description ; Beam crossfire correlation degrees^2^ between the crossfire laboratory X-axis component and the crossfire laboratory Y-axis component (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the mean of the products of the deviations of the direction of each photon in XZ plane times the deviations of the direction of the same photon in the YZ plane around the mean source beam direction. This will be zero for uncorrelated crossfire. Note that some synchrotrons, this value is specified in milliradians^2^, in which case a conversion would be needed. To go from a value in milliradians^2^ to a value in degrees^2^, multiply by 0.180^2^ and divide by \p^2^. ; _item.name '_diffrn_radiation.div_x_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees_squared _item_default.value 0.0 save_ save__diffrn_radiation.filter_edge _item_description.description ; Absorption edge in \%Angstroms of the radiation filter used. ; _item.name '_diffrn_radiation.filter_edge' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_filter_edge' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__diffrn_radiation.inhomogeneity _item_description.description ; Half-width in millimetres of the incident beam in the direction perpendicular to the diffraction plane. ; _item.name '_diffrn_radiation.inhomogeneity' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_inhomogeneity' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code millimetres save_ save__diffrn_radiation.monochromator _item_description.description ; The method used to obtain monochromatic radiation. If a monochromator crystal is used, the material and the indices of the Bragg reflection are specified. ; _item.name '_diffrn_radiation.monochromator' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_monochromator' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Zr filter' 'Ge 220' 'none' 'equatorial mounted graphite' save_ save__diffrn_radiation.polarisn_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the perpendicular component of the polarization and the diffraction plane. See _diffrn_radiation_polarisn_ratio. ; _item.name '_diffrn_radiation.polarisn_norm' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_norm' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.polarisn_ratio _item_description.description ; Polarization ratio of the diffraction beam incident on the crystal. This is the ratio of the perpendicularly polarized to the parallel polarized component of the radiation. The perpendicular component forms an angle of _diffrn_radiation.polarisn_norm to the normal to the diffraction plane of the sample (i.e. the plane containing the incident and reflected beams). ; _item.name '_diffrn_radiation.polarisn_ratio' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_ratio' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__diffrn_radiation.polarizn_source_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the normal to the polarization plane and the laboratory Y axis as defined in the AXIS category. Note that this is the angle of polarization of the source photons, either directly from a synchrotron beamline or from a monochromater. This differs from the value of _diffrn_radiation.polarisn_norm in that _diffrn_radiation.polarisn_norm refers to polarization relative to the diffraction plane rather than to the laboratory axis system. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane should be taken as the XZ plane and the angle as 0. See _diffrn_radiation.polarizn_source_ratio. ; _item.name '_diffrn_radiation.polarizn_source_norm' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.polarizn_source_ratio _item_description.description ; (Ip-In)/(Ip+In), where Ip is the intensity (amplitude squared) of the electric vector in the plane of polarization and In is the intensity (amplitude squared) of the electric vector in the plane of the normal to the plane of polarization. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane is to be taken as the XZ plane and the normal is parallel to the Y axis. Thus, if there was complete polarization in the plane of polarization, the value of _diffrn_radiation.polarizn_source_ratio would be 1, and for an unpolarized beam _diffrn_radiation.polarizn_source_ratio would have a value of 0. If the X axis has been chosen to lie in the plane of polarization, this definition will agree with the definition of 'MONOCHROMATOR' in the Denzo glossary, and values of near 1 should be expected for a bending-magnet source. However, if the X axis were perpendicular to the polarization plane (not a common choice), then the Denzo value would be the negative of _diffrn_radiation.polarizn_source_ratio. See http://www.hkl-xray.com for information on Denzo and Otwinowski & Minor (1997). This differs both in the choice of ratio and choice of orientation from _diffrn_radiation.polarisn_ratio, which, unlike _diffrn_radiation.polarizn_source_ratio, is unbounded. Reference: Otwinowski, Z. & Minor, W. (1997). 'Processing of X-ray diffraction data collected in oscillation mode.' Methods Enzymol. 276, 307-326. ; _item.name '_diffrn_radiation.polarizn_source_ratio' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 -1.0 -1.0 -1.0 _item_type.code float save_ save__diffrn_radiation.probe _item_description.description ; Name of the type of radiation used. It is strongly recommended that this be given so that the probe radiation is clearly specified. ; _item.name '_diffrn_radiation.probe' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_probe' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value 'X-ray' 'neutron' 'electron' 'gamma' save_ save__diffrn_radiation.type _item_description.description ; The nature of the radiation. This is typically a description of the X-ray wavelength in Siegbahn notation. ; _item.name '_diffrn_radiation.type' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'CuK\a' 'Cu K\a~1~' 'Cu K-L~2,3~' 'white-beam' save_ save__diffrn_radiation.xray_symbol _item_description.description ; The IUPAC symbol for the X-ray wavelength for the probe radiation. ; _item.name '_diffrn_radiation.xray_symbol' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_xray_symbol' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value _item_enumeration.detail 'K-L~3~' 'K\a~1~ in older Siegbahn notation' 'K-L~2~' 'K\a~2~ in older Siegbahn notation' 'K-M~3~' 'K\b~1~ in older Siegbahn notation' 'K-L~2,3~' 'use where K-L~3~ and K-L~2~ are not resolved' save_ save__diffrn_radiation.wavelength_id _item_description.description ; This data item is a pointer to _diffrn_radiation_wavelength.id in the DIFFRN_RADIATION_WAVELENGTH category. ; _item.name '_diffrn_radiation.wavelength_id' _item.category_id diffrn_radiation _item.mandatory_code yes _item_type.code code save_ ################ # DIFFRN_REFLN # ################ save_DIFFRN_REFLN _category.description ; This category redefinition has been added to extend the key of the standard DIFFRN_REFLN category. ; _category.id diffrn_refln _category.mandatory_code no _category_key.name '_diffrn_refln.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_refln.frame_id _item_description.description ; This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_refln.frame_id' _item.category_id diffrn_refln _item.mandatory_code yes _item_type.code code save_ ############### # DIFFRN_SCAN # ############### save_DIFFRN_SCAN _category.description ; Data items in the DIFFRN_SCAN category describe the parameters of one or more scans, relating axis positions to frames. ; _category.id diffrn_scan _category.mandatory_code no _category_key.name '_diffrn_scan.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - derived from a suggestion by R. M. Sweet. The vector of each axis is not given here, because it is provided in the AXIS category. By making _diffrn_scan_axis.scan_id and _diffrn_scan_axis.axis_id keys of the DIFFRN_SCAN_AXIS category, an arbitrary number of scanning and fixed axes can be specified for a scan. In this example, three rotation axes and one translation axis at nonzero values are specified, with one axis stepping. There is no reason why more axes could not have been specified to step. Range information has been specified, but note that it can be calculated from the number of frames and the increment, so the data item _diffrn_scan_axis.angle_range could be dropped. Both the sweep data and the data for a single frame are specified. Note that the information on how the axes are stepped is given twice, once in terms of the overall averages in the value of _diffrn_scan.integration_time and the values for DIFFRN_SCAN_AXIS, and precisely for the given frame in the value for _diffrn_scan_frame.integration_time and the values for DIFFRN_SCAN_FRAME_AXIS. If dose-related adjustments are made to scan times and nonlinear stepping is done, these values may differ. Therefore, in interpreting the data for a particular frame it is important to use the frame-specific data. ; ; _diffrn_scan.id 1 _diffrn_scan.date_start '2001-11-18T03:26:42' _diffrn_scan.date_end '2001-11-18T03:36:45' _diffrn_scan.integration_time 3.0 _diffrn_scan.frame_id_start mad_L2_000 _diffrn_scan.frame_id_end mad_L2_200 _diffrn_scan.frames 201 loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment 1 omega 200.0 20.0 0.1 . . . 1 kappa -40.0 0.0 0.0 . . . 1 phi 127.5 0.0 0.0 . . . 1 tranz . . . 2.3 0.0 0.0 _diffrn_scan_frame.scan_id 1 _diffrn_scan_frame.date '2001-11-18T03:27:33' _diffrn_scan_frame.integration_time 3.0 _diffrn_scan_frame.frame_id mad_L2_018 _diffrn_scan_frame.frame_number 18 loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.angle_increment _diffrn_scan_frame_axis.displacement _diffrn_scan_frame_axis.displacement_increment mad_L2_018 omega 201.8 0.1 . . mad_L2_018 kappa -40.0 0.0 . . mad_L2_018 phi 127.5 0.0 . . mad_L2_018 tranz . . 2.3 0.0 ; ; Example 2 - a more extensive example (R. M. Sweet, P. J. Ellis & H. J. Bernstein). A detector is placed 240 mm along the Z axis from the goniometer. This leads to a choice: either the axes of the detector are defined at the origin, and then a Z setting of -240 is entered, or the axes are defined with the necessary Z offset. In this case, the setting is used and the offset is left as zero. This axis is called DETECTOR_Z. The axis for positioning the detector in the Y direction depends on the detector Z axis. This axis is called DETECTOR_Y. The axis for positioning the detector in the X direction depends on the detector Y axis (and therefore on the detector Z axis). This axis is called DETECTOR_X. This detector may be rotated around the Y axis. This rotation axis depends on the three translation axes. It is called DETECTOR_PITCH. A coordinate system is defined on the face of the detector in terms of 2300 0.150 mm pixels in each direction. The ELEMENT_X axis is used to index the first array index of the data array and the ELEMENT_Y axis is used to index the second array index. Because the pixels are 0.150mm X 0.150mm, the centre of the first pixel is at (0.075, 0.075) in this coordinate system. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 172.43 -172.43 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 2300 1 increasing ELEMENT_X ARRAY1 2 2300 2 increasing ELEMENT_Y # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.075 0.150 ELEMENT_Y ELEMENT_Y 0.075 0.150 # category ARRAY_ELEMENT_SIZE loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 ARRAY1 2 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; ; Example 3 - Example 2 revised for a spiral scan (R. M. Sweet, P. J. Ellis & H. J. Bernstein). A detector is placed 240 mm along the Z axis from the goniometer, as in Example 2 above, but in this example the image plate is scanned in a spiral pattern from the outside edge in. The axis for positioning the detector in the Y direction depends on the detector Z axis. This axis is called DETECTOR_Y. The axis for positioning the detector in the X direction depends on the detector Y axis (and therefore on the detector Z axis). This axis is called DETECTOR_X. This detector may be rotated around the Y axis. This rotation axis depends on the three translation axes. It is called DETECTOR_PITCH. A coordinate system is defined on the face of the detector in terms of a coupled rotation axis and radial scan axis to form a spiral scan. The rotation axis is called ELEMENT_ROT and the radial axis is called ELEMENT_RAD. A 150 micrometre radial pitch and a 75 micrometre 'constant velocity' angular pitch are assumed. Indexing is carried out first on the rotation axis and the radial axis is made to be dependent on it. The two axes are coupled to form an axis set ELEMENT_SPIRAL. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_ROT translation detector DETECTOR_PITCH 0 0 1 0 0 0 ELEMENT_RAD translation detector ELEMENT_ROT 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.angle _array_structure_list_axis.displacement _array_structure_list_axis.angular_pitch _array_structure_list_axis.radial_pitch ELEMENT_SPIRAL ELEMENT_ROT 0 . 0.075 . ELEMENT_SPIRAL ELEMENT_RAD . 172.5 . -0.150 # category ARRAY_ELEMENT_SIZE # the actual pixels are 0.075 by 0.150 mm # We give the coarser dimension here. loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_scan.id _item_description.description ; The value of _diffrn_scan.id uniquely identifies each scan. The identifier is used to tie together all the information about the scan. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_scan.id' diffrn_scan yes '_diffrn_scan_axis.scan_id' diffrn_scan_axis yes '_diffrn_scan_frame.scan_id' diffrn_scan_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_scan_axis.scan_id' '_diffrn_scan.id' '_diffrn_scan_frame.scan_id' '_diffrn_scan.id' save_ save__diffrn_scan.date_end _item_description.description ; The date and time of the end of the scan. Note that this may be an estimate generated during the scan, before the precise time of the end of the scan is known. ; _item.name '_diffrn_scan.date_end' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.date_start _item_description.description ; The date and time of the start of the scan. ; _item.name '_diffrn_scan.date_start' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.integration_time _item_description.description ; Approximate average time in seconds to integrate each step of the scan. The precise time for integration of each particular step must be provided in _diffrn_scan_frame.integration_time, even if all steps have the same integration time. ; _item.name '_diffrn_scan.integration_time' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan.frame_id_start _item_description.description ; The value of this data item is the identifier of the first frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_start' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frame_id_end _item_description.description ; The value of this data item is the identifier of the last frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_end' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frames _item_description.description ; The value of this data item is the number of frames in the scan. ; _item.name '_diffrn_scan.frames' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 1 1 1 save_ #################### # DIFFRN_SCAN_AXIS # #################### save_DIFFRN_SCAN_AXIS _category.description ; Data items in the DIFFRN_SCAN_AXIS category describe the settings of axes for particular scans. Unspecified axes are assumed to be at their zero points. ; _category.id diffrn_scan_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_axis.scan_id' '_diffrn_scan_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_axis.scan_id _item_description.description ; The value of this data item is the identifier of the scan for which axis settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan.id. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_axis.scan_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the scan for which settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan.id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_axis.axis_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.angle_start _item_description.description ; The starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_range _item_description.description ; The range from the starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_increment _item_description.description ; The increment for each step for the specified axis in degrees. In general, this will agree with _diffrn_scan_frame_axis.angle_increment. The sum of the values of _diffrn_scan_frame_axis.angle and _diffrn_scan_frame_axis.angle_increment is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of _diffrn_scan_axis.angle_increment will be representative of the ensemble of values of _diffrn_scan_frame_axis.angle_increment (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_rstrt_incr _item_description.description ; The increment after each step for the specified axis in degrees. In general, this will agree with _diffrn_scan_frame_axis.angle_rstrt_incr. The sum of the values of _diffrn_scan_frame_axis.angle, _diffrn_scan_frame_axis.angle_increment and _diffrn_scan_frame_axis.angle_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame and should equal _diffrn_scan_frame_axis.angle for this next frame. If the individual frame values vary, then the value of _diffrn_scan_axis.angle_rstrt_incr will be representative of the ensemble of values of _diffrn_scan_frame_axis.angle_rstrt_incr (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.displacement_start _item_description.description ; The starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_range _item_description.description ; The range from the starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_increment _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with _diffrn_scan_frame_axis.displacement_increment. The sum of the values of _diffrn_scan_frame_axis.displacement and _diffrn_scan_frame_axis.displacement_increment is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of _diffrn_scan_axis.displacement_increment will be representative of the ensemble of values of _diffrn_scan_frame_axis.displacement_increment (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_rstrt_incr _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with _diffrn_scan_frame_axis.displacement_rstrt_incr. The sum of the values of _diffrn_scan_frame_axis.displacement, _diffrn_scan_frame_axis.displacement_increment and _diffrn_scan_frame_axis.displacement_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame and should equal _diffrn_scan_frame_axis.displacement for this next frame. If the individual frame values vary, then the value of _diffrn_scan_axis.displacement_rstrt_incr will be representative of the ensemble of values of _diffrn_scan_frame_axis.displacement_rstrt_incr (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.reference_angle _item_description.description ; The setting of the specified axis in degrees against which measurements of the reference beam center and reference detector distance should be made. In general, this will agree with _diffrn_scan_frame_axis.reference_angle. If the individual frame values vary, then the value of _diffrn_scan_axis.reference_angle will be representative of the ensemble of values of _diffrn_scan_frame_axis.reference_angle (e.g. the mean). If not specified, the value defaults to zero. ; _item.name '_diffrn_scan_axis.reference_angle' _item.category_id diffrn_scan_axis _item.mandatory_code implicit _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.reference_displacement _item_description.description ; The setting of the specified axis in millimetres against which measurements of the reference beam center and reference detector distance should be made. In general, this will agree with _diffrn_scan_frame_axis.reference_displacement. If the individual frame values vary, then the value of _diffrn_scan_axis.reference_displacement will be representative of the ensemble of values of _diffrn_scan_frame_axis.reference_displacement (e.g. the mean). If not specified, the value defaults to to the value of _diffrn_scan_axis.displacement. ; _item.name '_diffrn_scan_axis.reference_displacement' _item.category_id diffrn_scan_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'millimetres' save_ ##################### # DIFFRN_SCAN_FRAME # ##################### save_DIFFRN_SCAN_FRAME _category.description ; Data items in the DIFFRN_SCAN_FRAME category describe the relationships of particular frames to scans. ; _category.id diffrn_scan_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame.scan_id' '_diffrn_scan_frame.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame.date _item_description.description ; The date and time of the start of the frame being scanned. ; _item.name '_diffrn_scan_frame.date' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan_frame.frame_id _item_description.description ; The value of this data item is the identifier of the frame being examined. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame.frame_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame.frame_number _item_description.description ; The value of this data item is the number of the frame within the scan, starting with 1. It is not necessarily the same as the value of _diffrn_scan_frame.frame_id, but it may be. ; _item.name '_diffrn_scan_frame.frame_number' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 0 0 0 save_ save__diffrn_scan_frame.integration_time _item_description.description ; The time in seconds to integrate this step of the scan. This should be the precise time of integration of each particular frame. The value of this data item should be given explicitly for each frame and not inferred from the value of _diffrn_scan.integration_time. ; _item.name '_diffrn_scan_frame.integration_time' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame.scan_id _item_description.description ; The value of _diffrn_scan_frame.scan_id identifies the scan containing this frame. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_frame.scan_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ ########################## # DIFFRN_SCAN_FRAME_AXIS # ########################## save_DIFFRN_SCAN_FRAME_AXIS _category.description ; Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the settings of axes for particular frames. Unspecified axes are assumed to be at their zero points. If, for any given frame, nonzero values apply for any of the data items in this category, those values should be given explicitly in this category and not simply inferred from values in DIFFRN_SCAN_AXIS. ; _category.id diffrn_scan_frame_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame_axis.frame_id' '_diffrn_scan_frame_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the frame for which settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_frame_axis.axis_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_axis.angle _item_description.description ; The setting of the specified axis in degrees for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.angle' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_increment _item_description.description ; The increment for this frame for the angular setting of the specified axis in degrees. The sum of the values of _diffrn_scan_frame_axis.angle and _diffrn_scan_frame_axis.angle_increment is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.angle_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_rstrt_incr _item_description.description ; The increment after this frame for the angular setting of the specified axis in degrees. The sum of the values of _diffrn_scan_frame_axis.angle, _diffrn_scan_frame_axis.angle_increment and _diffrn_scan_frame_axis.angle_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame and should equal _diffrn_scan_frame_axis.angle for this next frame. ; _item.name '_diffrn_scan_frame_axis.angle_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.displacement' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_increment _item_description.description ; The increment for this frame for the displacement setting of the specified axis in millimetres. The sum of the values of _diffrn_scan_frame_axis.displacement and _diffrn_scan_frame_axis.displacement_increment is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.displacement_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_rstrt_incr _item_description.description ; The increment for this frame for the displacement setting of the specified axis in millimetres. The sum of the values of _diffrn_scan_frame_axis.displacement, _diffrn_scan_frame_axis.displacement_increment and _diffrn_scan_frame_axis.displacement_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame and should equal _diffrn_scan_frame_axis.displacement for this next frame. ; _item.name '_diffrn_scan_frame_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.frame_id _item_description.description ; The value of this data item is the identifier of the frame for which axis settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame_axis.frame_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_axis.reference_angle _item_description.description ; The setting of the specified axis in degrees against which measurements of the reference beam center and reference detector distance should be made. This is normally the same for all frames, but the option is provided here of making changes when needed. If not provided, it is assumed to be zero. ; _item.name '_diffrn_scan_frame_axis.reference_angle' _item.category_id diffrn_scan_frame_axis _item.mandatory_code implicit _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.reference_displacement _item_description.description ; The setting of the specified axis in millimetres for this frame against which measurements of the reference beam center and reference detector distance should be made. This is normally the same for all frames, but the option is provided here of making changes when needed. If not provided, it is assumed to be equal to _diffrn_scan_frame_axis.displacement. ; _item.name '_diffrn_scan_frame_axis.reference_displacement' _item.category_id diffrn_scan_frame_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'millimetres' save_ ####### # MAP # ####### save_MAP _category.description ; Data items in the MAP category record the details of a maps. Maps record values of parameters, such as density, that are functions of position within a cell or are functions of orthogonal coordinates in three space. A map may is composed of one or more map segments specified in the MAP_SEGMENT category. Examples are given in the MAP_SEGMENT category. ; _category.id map _category.mandatory_code no loop_ _category_key.name '_map.id' '_map.diffrn_id' '_map.entry_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Identifying an observed density map and a calculated density map ; ; loop_ _map.id _map.details rho_calc ; density calculated from F_calc derived from the ATOM_SITE list ; rho_obs ; density combining the observed structure factors with the calculated phases ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__map.details _item_description.description ; The value of _map.details should give a description of special aspects of each map. ; _item.name '_map.details' _item.category_id map _item.mandatory_code no _item_type.code text loop_ _item_examples.case _item_examples.detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Identifying an observed density map and a calculated density map ; ; loop_ _map.id _map.details rho_calc ; density calculated from F_calc derived from the ATOM_SITE list ; rho_obs ; density combining the observed structure factors with the calculated phases ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__map.diffrn_id _item_description.description ; This item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_map.diffrn_id' _item.category_id map _item.mandatory_code implicit _item_type.code code save_ save__map.entry_id _item_description.description ; This item is a pointer to _entry.id in the ENTRY category. ; _item.name '_map.entry_id' _item.category_id map _item.mandatory_code implicit _item_type.code code save_ save__map.id _item_description.description ; The value of _map.id must uniquely identify each map for the given diffrn.id or entry.id. ; loop_ _item.name _item.category_id _item.mandatory_code '_map.id' map yes '_map_segment.id' map_segment yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_map_segment.id' '_map.id' save_ ########################### # MAP_SEGMENT # ########################### save_MAP_SEGMENT _category.description ; Data items in the MAP_SEGMENT category record the details about each segment (section or brick) of a map. ; _category.id map_segment _category.mandatory_code no loop_ _category_key.name '_map_segment.id' '_map_segment.map_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Identifying an observed density map and a calculated density map, each consisting of one segment, both using the same array structure and mask. ; ; loop_ _map.id _map.details rho_calc ; density calculated from F_calc derived from the ATOM_SITE list ; rho_obs ; density combining the observed structure factors with the calculated phases ; loop_ _map_segment.map_id _map_segment.id _map_segment.array_id _map_segment.binary_id _map_segment.mask_array_id _map_segment.mask_binary_id rho_calc rho_calc map_structure 1 mask_structure 1 rho_obs rho_obs map_structure 2 mask_structure 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__map_segment.array_id _item_description.description ; The value of _map_segment.array_id identifies the array structure into which the map is organized. This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_map_segment.array_id' _item.category_id map_segment _item.mandatory_code yes _item_type.code code save_ save__map_segment.binary_id _item_description.description ; The value of _map_segment.binary_id distinguishes the particular set of data organized according to _map_segment.array_id in which the data values of the map are stored. This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_map_segment.binary_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code int save_ save__map_segment.mask_array_id _item_description.description ; The value of _map_segment.mask_array_id, if given, the array structure into which the mask for the map is organized. If no value is given, then all elements of the map are valid. If a value is given, then only elements of the map for which the corresponding element of the mask is non-zero are valid. The value of _map_segment.mask_array_id differs from the value of _map_segment.array_id in order to permit the mask to be given as, say, unsigned 8-bit integers, while the map is given as a data type with more range. However, the two array structures must be aligned, using the same axes in the same order with the same displacements and increments This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_map_segment.mask_array_id' _item.category_id map_segment _item.mandatory_code no _item_type.code code save_ save__map_segment.mask_binary_id _item_description.description ; The value of _map_segment.mask_binary_id identifies the particular set of data organized according to _map_segment.mask_array_id specifying the mask for the map. This item is a pointer to _array_data.mask_binary_id in the ARRAY_DATA category. ; _item.name '_map_segment.mask_binary_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code int save_ save__map_segment.id _item_description.description ; The value of _map_segment.id must uniquely identify each segment of a map. ; loop_ _item.name _item.category_id _item.mandatory_code '_map_segment.id' map_segment yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_map_data_frame.map_segment_id' '_map_segment.id' save_ save__map_segment.map_id _item_description.description ; This item is a pointer to _map.id in the MAP category. ; _item.name '_map_segment.map_id' _item.category_id map_segment _item.mandatory_code yes _item_type.code code save_ save__map_segment.details _item_description.description ; The value of _map_segment.details should give a description of special aspects of each segment of a map. ; _item.name '_map_segment.details' _item.category_id map_segment _item.mandatory_code no _item_type.code text loop_ _item_examples.case _item_examples.detail ; Example to be provided ; ; ; save_ ######################## DEPRECATED DATA ITEMS ######################## save__diffrn_detector_axis.id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_detector_axis.id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.id _item_description.description ; This data item is a pointer to _diffrn_measurement.id in the DIFFRN_MEASUREMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_measurement_axis.id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ ######################### DEPRECATED CATEGORY ######################### ##################### # DIFFRN_FRAME_DATA # ##################### save_DIFFRN_FRAME_DATA _category.description ; Data items in the DIFFRN_FRAME_DATA category record the details about each frame of data. The items in this category are now in the DIFFRN_DATA_FRAME category. The items in the DIFFRN_FRAME_DATA category are now deprecated. The items from this category are provided as aliases in the 1.0 dictionary or, in the case of _diffrn_frame_data.details, in the 1.4 dictionary. THESE ITEMS SHOULD NOT BE USED FOR NEW WORK. The items from the old category are provided in this dictionary for completeness but should not be used or cited. To avoid confusion, the example has been removed and the redundant parent-child links to other categories have been removed. ; _category.id diffrn_frame_data _category.mandatory_code no loop_ _category_key.name '_diffrn_frame_data.id' '_diffrn_frame_data.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; THE DIFFRN_FRAME_DATA category is deprecated and should not be used. ; ; # EXAMPLE REMOVED # ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_frame_data.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.array_id' _item.category_id diffrn_frame_data _item.mandatory_code yes _item_type.code code save_ save__diffrn_frame_data.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.binary_id' _item.category_id diffrn_frame_data _item.mandatory_code implicit _item_type.code int save_ save__diffrn_frame_data.detector_element_id _item_description.description ; This item is a pointer to _diffrn_detector_element.id in the DIFFRN_DETECTOR_ELEMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.detector_element_id' _item.category_id diffrn_frame_data _item.mandatory_code yes _item_type.code code save_ save__diffrn_frame_data.id _item_description.description ; The value of _diffrn_frame_data.id must uniquely identify each complete frame of data. DEPRECATED -- DO NOT USE ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_frame_data.id' diffrn_frame_data yes _item_type.code code save_ save__diffrn_frame_data.details _item_description.description ; The value of _diffrn_data_frame.details should give a description of special aspects of each frame of data. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.details' _item.category_id diffrn_frame_data _item.mandatory_code no _item_type.code text save_ ################ END DEPRECATED SECTION ########### #################### ## ITEM_TYPE_LIST ## #################### # # # The regular expressions defined here are not compliant # with the POSIX 1003.2 standard as they include the # '\n' and '\t' special characters. These regular expressions # have been tested using version 0.12 of Richard Stallman's # GNU regular expression library in POSIX mode. # In order to allow presentation of a regular expression # in a text field concatenate any line ending in a backslash # with the following line, after discarding the backslash. # # A formal definition of the '\n' and '\t' special characters # is most properly done in the DDL, but for completeness, please # note that '\n' is the line termination character ('newline') # and '\t' is the horizontal tab character. There is a formal # ambiguity in the use of '\n' for line termination, in that # the intention is that the equivalent machine/OS-dependent line # termination character sequence should be accepted as a match, e.g. # # '\r' (control-M) under MacOS # '\n' (control-J) under Unix # '\r\n' (control-M control-J) under DOS and MS Windows # loop_ _item_type_list.code _item_type_list.primitive_code _item_type_list.construct _item_type_list.detail code char '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words ... ; ucode uchar '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words (case insensitive) ... ; line char '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; char item types / multi-word items ... ; uline uchar '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; char item types / multi-word items (case insensitive)... ; text char '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; text item types / multi-line text ... ; binary char ;\n--CIF-BINARY-FORMAT-SECTION--\n\ [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\ \n--CIF-BINARY-FORMAT-SECTION---- ; ; binary items are presented as MIME-like ascii-encoded sections in an imgCIF. In a CBF, raw octet streams are used to convey the same information. ; int numb '-?[0-9]+' ; int item types are the subset of numbers that are the negative or positive integers. ; float numb '-?(([0-9]+)[.]?|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?' ; float item types are the subset of numbers that are the floating point numbers. ; any char '.*' ; A catch all for items that may take any form... ; yyyy-mm-dd char ;\ [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9]?[0-9]\ ((T[0-2][0-9](:[0-5][0-9](:[0-5][0-9](.[0-9]+)?)?)?)?\ ([+-][0-5][0-9]:[0-5][0-9]))? ; ; Standard format for CIF date and time strings (see http://www.iucr.org/iucr-top/cif/spec/datetime.html), consisting of a yyyy-mm-dd date optionally followed by the character 'T' followed by a 24-hour clock time, optionally followed by a signed time-zone offset. The IUCr standard has been extended to allow for an optional decimal fraction on the seconds of time. Time is local time if no time-zone offset is given. Note that this type extends the mmCIF yyyy-mm-dd type but does not conform to the mmCIF yyyy-mm-dd:hh:mm type that uses a ':' in place if the 'T' specified by the IUCr standard. For reading, both forms should be accepted, but for writing, only the IUCr form should be used. For maximal compatibility, the special time zone indicator 'Z' (for 'zulu') should be accepted on reading in place of '+00:00' for GMT. ; ##################### ## ITEM_UNITS_LIST ## ##################### loop_ _item_units_list.code _item_units_list.detail # 'metres' 'metres' 'centimetres' 'centimetres (metres * 10^( -2)^)' 'millimetres' 'millimetres (metres * 10^( -3)^)' 'nanometres' 'nanometres (metres * 10^( -9)^)' 'angstroms' '\%Angstroms (metres * 10^(-10)^)' 'picometres' 'picometres (metres * 10^(-12)^)' 'femtometres' 'femtometres (metres * 10^(-15)^)' # 'reciprocal_metres' 'reciprocal metres (metres^(-1)^)' 'reciprocal_centimetres' 'reciprocal centimetres ((metres * 10^( -2)^)^(-1)^)' 'reciprocal_millimetres' 'reciprocal millimetres ((metres * 10^( -3)^)^(-1)^)' 'reciprocal_nanometres' 'reciprocal nanometres ((metres * 10^( -9)^)^(-1)^)' 'reciprocal_angstroms' 'reciprocal \%Angstroms ((metres * 10^(-10)^)^(-1)^)' 'reciprocal_picometres' 'reciprocal picometres ((metres * 10^(-12)^)^(-1)^)' # 'nanometres_squared' 'nanometres squared (metres * 10^( -9)^)^2^' 'angstroms_squared' '\%Angstroms squared (metres * 10^(-10)^)^2^' '8pi2_angstroms_squared' '8\p^2^ * \%Angstroms squared (metres * 10^(-10)^)^2^' 'picometres_squared' 'picometres squared (metres * 10^(-12)^)^2^' # 'nanometres_cubed' 'nanometres cubed (metres * 10^( -9)^)^3^' 'angstroms_cubed' '\%Angstroms cubed (metres * 10^(-10)^)^3^' 'picometres_cubed' 'picometres cubed (metres * 10^(-12)^)^3^' # 'kilopascals' 'kilopascals' 'gigapascals' 'gigapascals' # 'hours' 'hours' 'minutes' 'minutes' 'seconds' 'seconds' 'microseconds' 'microseconds' # 'degrees' 'degrees (of arc)' 'degrees_squared' 'degrees (of arc) squared' # 'degrees_per_minute' 'degrees (of arc) per minute' # 'celsius' 'degrees (of temperature) Celsius' 'kelvins' 'degrees (of temperature) Kelvin' # 'counts' 'counts' 'counts_per_photon' 'counts per photon' # 'electrons' 'electrons' # 'electrons_squared' 'electrons squared' # 'electrons_per_nanometres_cubed' ; electrons per nanometres cubed (electrons/(metres * 10^( -9)^)^(-3)^) ; 'electrons_per_angstroms_cubed' ; electrons per \%Angstroms cubed (electrons/(metres * 10^(-10)^)^(-3)^) ; 'electrons_per_picometres_cubed' ; electrons per picometres cubed (electrons/(metres * 10^(-12)^)^(-3)^) ; 'kilowatts' 'kilowatts' 'milliamperes' 'milliamperes' 'kilovolts' 'kilovolts' # 'pixels_per_element' '(image) pixels per (array) element' # 'arbitrary' ; arbitrary system of units. ; # loop_ _item_units_conversion.from_code _item_units_conversion.to_code _item_units_conversion.operator _item_units_conversion.factor ### 'metres' 'centimetres' '*' 1.0E+02 'metres' 'millimetres' '*' 1.0E+03 'metres' 'nanometres' '*' 1.0E+09 'metres' 'angstroms' '*' 1.0E+10 'metres' 'picometres' '*' 1.0E+12 'metres' 'femtometres' '*' 1.0E+15 # 'centimetres' 'metres' '*' 1.0E-02 'centimetres' 'millimetres' '*' 1.0E+01 'centimetres' 'nanometres' '*' 1.0E+07 'centimetres' 'angstroms' '*' 1.0E+08 'centimetres' 'picometres' '*' 1.0E+10 'centimetres' 'femtometres' '*' 1.0E+13 # 'millimetres' 'metres' '*' 1.0E-03 'millimetres' 'centimetres' '*' 1.0E-01 'millimetres' 'nanometres' '*' 1.0E+06 'millimetres' 'angstroms' '*' 1.0E+07 'millimetres' 'picometres' '*' 1.0E+09 'millimetres' 'femtometres' '*' 1.0E+12 # 'nanometres' 'metres' '*' 1.0E-09 'nanometres' 'centimetres' '*' 1.0E-07 'nanometres' 'millimetres' '*' 1.0E-06 'nanometres' 'angstroms' '*' 1.0E+01 'nanometres' 'picometres' '*' 1.0E+03 'nanometres' 'femtometres' '*' 1.0E+06 # 'angstroms' 'metres' '*' 1.0E-10 'angstroms' 'centimetres' '*' 1.0E-08 'angstroms' 'millimetres' '*' 1.0E-07 'angstroms' 'nanometres' '*' 1.0E-01 'angstroms' 'picometres' '*' 1.0E+02 'angstroms' 'femtometres' '*' 1.0E+05 # 'picometres' 'metres' '*' 1.0E-12 'picometres' 'centimetres' '*' 1.0E-10 'picometres' 'millimetres' '*' 1.0E-09 'picometres' 'nanometres' '*' 1.0E-03 'picometres' 'angstroms' '*' 1.0E-02 'picometres' 'femtometres' '*' 1.0E+03 # 'femtometres' 'metres' '*' 1.0E-15 'femtometres' 'centimetres' '*' 1.0E-13 'femtometres' 'millimetres' '*' 1.0E-12 'femtometres' 'nanometres' '*' 1.0E-06 'femtometres' 'angstroms' '*' 1.0E-05 'femtometres' 'picometres' '*' 1.0E-03 ### 'reciprocal_centimetres' 'reciprocal_metres' '*' 1.0E+02 'reciprocal_centimetres' 'reciprocal_millimetres' '*' 1.0E-01 'reciprocal_centimetres' 'reciprocal_nanometres' '*' 1.0E-07 'reciprocal_centimetres' 'reciprocal_angstroms' '*' 1.0E-08 'reciprocal_centimetres' 'reciprocal_picometres' '*' 1.0E-10 # 'reciprocal_millimetres' 'reciprocal_metres' '*' 1.0E+03 'reciprocal_millimetres' 'reciprocal_centimetres' '*' 1.0E+01 'reciprocal_millimetres' 'reciprocal_nanometres' '*' 1.0E-06 'reciprocal_millimetres' 'reciprocal_angstroms' '*' 1.0E-07 'reciprocal_millimetres' 'reciprocal_picometres' '*' 1.0E-09 # 'reciprocal_nanometres' 'reciprocal_metres' '*' 1.0E+09 'reciprocal_nanometres' 'reciprocal_centimetres' '*' 1.0E+07 'reciprocal_nanometres' 'reciprocal_millimetres' '*' 1.0E+06 'reciprocal_nanometres' 'reciprocal_angstroms' '*' 1.0E-01 'reciprocal_nanometres' 'reciprocal_picometres' '*' 1.0E-03 # 'reciprocal_angstroms' 'reciprocal_metres' '*' 1.0E+10 'reciprocal_angstroms' 'reciprocal_centimetres' '*' 1.0E+08 'reciprocal_angstroms' 'reciprocal_millimetres' '*' 1.0E+07 'reciprocal_angstroms' 'reciprocal_nanometres' '*' 1.0E+01 'reciprocal_angstroms' 'reciprocal_picometres' '*' 1.0E-02 # 'reciprocal_picometres' 'reciprocal_metres' '*' 1.0E+12 'reciprocal_picometres' 'reciprocal_centimetres' '*' 1.0E+10 'reciprocal_picometres' 'reciprocal_millimetres' '*' 1.0E+09 'reciprocal_picometres' 'reciprocal_nanometres' '*' 1.0E+03 'reciprocal_picometres' 'reciprocal_angstroms' '*' 1.0E+01 ### 'nanometres_squared' 'angstroms_squared' '*' 1.0E+02 'nanometres_squared' 'picometres_squared' '*' 1.0E+06 # 'angstroms_squared' 'nanometres_squared' '*' 1.0E-02 'angstroms_squared' 'picometres_squared' '*' 1.0E+04 'angstroms_squared' '8pi2_angstroms_squared' '*' 78.9568 # 'picometres_squared' 'nanometres_squared' '*' 1.0E-06 'picometres_squared' 'angstroms_squared' '*' 1.0E-04 ### 'nanometres_cubed' 'angstroms_cubed' '*' 1.0E+03 'nanometres_cubed' 'picometres_cubed' '*' 1.0E+09 # 'angstroms_cubed' 'nanometres_cubed' '*' 1.0E-03 'angstroms_cubed' 'picometres_cubed' '*' 1.0E+06 # 'picometres_cubed' 'nanometres_cubed' '*' 1.0E-09 'picometres_cubed' 'angstroms_cubed' '*' 1.0E-06 ### 'kilopascals' 'gigapascals' '*' 1.0E-06 'gigapascals' 'kilopascals' '*' 1.0E+06 ### 'hours' 'minutes' '*' 6.0E+01 'hours' 'seconds' '*' 3.6E+03 'hours' 'microseconds' '*' 3.6E+09 # 'minutes' 'hours' '/' 6.0E+01 'minutes' 'seconds' '*' 6.0E+01 'minutes' 'microseconds' '*' 6.0E+07 # 'seconds' 'hours' '/' 3.6E+03 'seconds' 'minutes' '/' 6.0E+01 'seconds' 'microseconds' '*' 1.0E+06 # 'microseconds' 'hours' '/' 3.6E+09 'microseconds' 'minutes' '/' 6.0E+07 'microseconds' 'seconds' '/' 1.0E+06 ### 'celsius' 'kelvins' '-' 273.0 'kelvins' 'celsius' '+' 273.0 ### 'electrons_per_nanometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E+03 'electrons_per_nanometres_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+09 # 'electrons_per_angstroms_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-03 'electrons_per_angstroms_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+06 # 'electrons_per_picometres_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-09 'electrons_per_picometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E-06 ### ######################## ## DICTIONARY_HISTORY ## ######################## loop_ _dictionary_history.version _dictionary_history.update _dictionary_history.revision 1.5.2 2007-05-06 ; Further clarifications of the coordinate system. (HJB) ; 1.5.1 2007-04-26 ; Improve defintion of X-axis to cover the case of no goniometer and clean up more line folds (HJB) ; 1.5 2007-07-25 ; This is a cummulative list of the changes proposed since the imgCIF workshop in Hawaii in July 2006. It is the result of contributions by H. J. Bernstein, A. Hammersley, J. Wright and W. Kabsch. 2007-02-19 Consolidated changes (edited by HJB) + Added new data items '_array_structure.compression_type_flag', '_array_structure_list_axis.fract_displacement', '_array_structure_list_axis.displacement_increment', '_array_structure_list_axis.reference_angle', '_array_structure_list_axis.reference_displacement', '_axis.system', '_diffrn_detector_element.reference_center_fast', '_diffrn_detector_element.reference_center_slow', '_diffrn_scan_axis.reference_angle', '_diffrn_scan_axis.reference_displacement', '_map.details', '_map.diffrn_id', '_map.entry_id', '_map.id', '_map_segment.array_id', '_map_segment.binary_id', '_map_segment.mask_array_id', '_map_segment.mask_binary_id', '_map_segment.id', '_map_segment.map_id', '_map_segment.details. + Change type of '_array_structure.byte_order' and '_array_structure.compression_type' to ucode to make these values case-insensitive + Add values 'packed_v2' and 'byte_offset' to enumeration of values for '_array_structure.compression_type' + Add to defintions for the binary data type to handle new compression types, maps, and a variety of new axis types. 2007-07-25 Cleanup of typos for formal release (HJB) + Corrected text fields for reference_ tag descriptions that were off by one column + Fix typos in comments listing fract_ tags + Changed name of release from 1.5_DRAFT to 1.5 + Fix unclosed text fields in various map definitions ; 1.4 2006-07-04 ; This is a change to reintegrate all changes made in the course of publication of ITVG, by the RCSB from April 2005 through August 2008 and changes for the 2006 imgCIF workshop in Hawaii. 2006-07-04 Consolidated changes for the 2006 imgCIF workshop (edited by HJB) + Correct type of '_array_structure_list.direction' from 'int' to 'code'. + Added new data items suggested by CN '_diffrn_data_frame.details' '_array_intensities.pixel_fast_bin_size', '_array_intensities.pixel_slow_bin_size and '_array_intensities.pixel_binning_method + Added deprecated item for completeness '_diffrn_frame_data.details' + Added entry for missing item in contents list '_array_structure_list_axis.displacement' + Added new MIME type X-BASE32K based on work by VL, KM, GD, HJB + Correct description of MIME boundary delimiter to start in column 1. + General cleanup of text fields to conform to changes for ITVG by removing empty lines at start and finish of text field. + Amend example for ARRAY_INTENSITIES to include binning. + Add local copy of type specification (as 'code') for all children of '_diffrn.id'. + For consistency, change all references to 'pi' to '\p' and all references to 'Angstroms' to '\%Angstroms'. + Clean up all powers to use IUCr convention of '^power^', as in '10^3^' for '10**3'. + Update 'yyyy-mm-dd' type regex to allow truncation from the right and improve comments to explain handling of related mmCIF 'yyyy-mm-dd:hh:mm' type, and use of 'Z' for GMT time zone. 2005-03-08 and 2004-08-08 fixed cases where _item_units.code used instead of _item_type.code (JDW) 2004-04-15 fixed item ordering in _diffrn_measurement_axis.measurement_id added sub_category 'vector' (JDW) ; 1.3.2 2005-06-25 ; 2005-06-25 ITEM_TYPE_LIST: code, ucode, line, uline regexps updated to those of current mmCIF; float modified by allowing integers terminated by a point as valid. The 'time' part of yyyy-mm-dd types made optional in the regexp. (BM) 2005-06-17 Minor corrections as for proofs for IT G Chapter 4.6 (NJA) 2005-02-21 Minor corrections to spelling and punctuation (NJA) 2005-01-08 Changes as per Nicola Ashcroft. + Updated example 1 for DIFFRN_MEASUREMENT to agree with mmCIF. + Spelled out "micrometres" for "um" and "millimetres" for "mm". + Removed phrase "which may be stored" from ARRAY_STRUCTURE description. + Removed unused 'byte-offsets' compressions and updated cites to ITVG for '_array_structure.compression_type'. (HJB) ; 1.3.1 2003-08-13 ; Changes as per Frances C. Bernstein. + Identify initials. + Adopt British spelling for centre in text. + Set \p and \%Angstrom and powers. + Clean up commas and unclear wordings. + Clean up tenses in history. Changes as per Gotzon Madariaga. + Fix the ARRAY_DATA example to align '_array_data.binary_id' and X-Binary-ID. + Add a range to '_array_intensities.gain_esd'. + In the example of DIFFRN_DETECTOR_ELEMENT, '_diffrn_detector_element.id' and '_diffrn_detector_element.detector_id' interchanged. + Fix typos for direction, detector and axes. + Clarify description of polarisation. + Clarify axes in '_diffrn_detector_element.center[1]' '_diffrn_detector_element.center[2]'. + Add local item types for items that are pointers. (HJB) ; 1.3.0 2003-07-24 ; Changes as per Brian McMahon. + Consistently quote tags embedded in text. + Clean up introductory comments. + Adjust line lengths to fit in 80 character window. + Fix several descriptions in AXIS category which referred to '_axis.type' instead of the current item. + Fix erroneous use of deprecated item '_diffrn_detector_axis.id' in examples for DIFFRN_SCAN_AXIS. + Add deprecated items '_diffrn_detector_axis.id' and '_diffrn_measurement_axis.id'. (HJB) ; 1.2.4 2003-07-14 ; Changes as per I. David Brown. + Enhance descriptions in DIFFRN_SCAN_AXIS to make them less dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS. + Provide a copy of the deprecated DIFFRN_FRAME_DATA category for completeness. (HJB) ; 1.2.3 2003-07-03 ; Cleanup to conform to ITVG. + Correct sign error in ..._cubed units. + Correct '_diffrn_radiation.polarisn_norm' range. (HJB) ; 1.2.2 2003-03-10 ; Correction of typos in various DIFFRN_SCAN_AXIS descriptions. (HJB) ; 1.2.1 2003-02-22 ; Correction of ATOM_ for ARRAY_ typos in various descriptions. (HJB) ; 1.2 2003-02-07 ; Corrections to encodings (remove extraneous hyphens) remove extraneous underscore in '_array_structure.encoding_type' enumeration. Correct typos in items units list. (HJB) ; 1.1.3 2001-04-19 ; Another typo corrections by Wilfred Li, and cleanup by HJB. ; 1.1.2 2001-03-06 ; Several typo corrections by Wilfred Li. ; 1.1.1 2001-02-16 ; Several typo corrections by JW. ; 1.1 2001-02-06 ; Draft resulting from discussions on header for use at NSLS. (HJB) + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME. + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'. + Add '_diffrn_measurement_axis.measurement_device' and change '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'. + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source', '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm', '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end', '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr', '_diffrn_scan_axis.displacement_rstrt_incr', '_diffrn_scan_frame_axis.angle_increment', '_diffrn_scan_frame_axis.angle_rstrt_incr', '_diffrn_scan_frame_axis.displacement', '_diffrn_scan_frame_axis.displacement_increment',and '_diffrn_scan_frame_axis.displacement_rstrt_incr'. + Add '_diffrn_measurement.device' to category key. + Update yyyy-mm-dd to allow optional time with fractional seconds for time stamps. + Fix typos caught by RS. + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to allow for coupled axes, as in spiral scans. + Add examples for fairly complete headers thanks to R. Sweet and P. Ellis. ; 1.0 2000-12-21 ; Release version - few typos and tidying up. (BM & HJB) + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end of dictionary. + Alphabetize dictionary. ; 0.7.1 2000-09-29 ; Cleanup fixes. (JW) + Correct spelling of diffrn_measurement_axis in '_axis.id' + Correct ordering of uses of '_item.mandatory_code' and '_item_default.value'. ; 0.7.0 2000-09-09 ; Respond to comments by I. David Brown. (HJB) + Add further comments on '\n' and '\t'. + Update ITEM_UNITS_LIST by taking section from mmCIF dictionary and adding metres. Change 'meter' to 'metre' throughout. + Add missing enumerations to '_array_structure.compression_type' and make 'none' the default. + Remove parent-child relationship between '_array_structure_list.index' and '_array_structure_list.precedence'. + Improve alphabetization. + Fix '_array_intensities_gain.esd' related function. + Improve comments in AXIS. + Fix DIFFRN_FRAME_DATA example. + Remove erroneous DIFFRN_MEASUREMENT example. + Add '_diffrn_measurement_axis.id' to the category key. ; 0.6.0 1999-01-14 ; Remove redundant information for ENC_NONE data. (HJB) + After the D5 remove binary section identifier, size and compression type. + Add Control-L to header. ; 0.5.1 1999-01-03 ; Cleanup of typos and syntax errors. (HJB) + Cleanup example details for DIFFRN_SCAN category. + Add missing quote marks for '_diffrn_scan.id' definition. ; 0.5 1999-01-01 ; Modifications for axis definitions and reduction of binary header. (HJB) + Restore '_diffrn_detector.diffrn_id' to DIFFRN_DETECTOR KEY. + Add AXIS category. + Bring in complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories from cif_mm.dic for clarity. + Change '_array_structure.encoding_type' from type code to uline and added X-Binary-Element-Type to MIME header. + Add detector beam centre '_diffrn_detector_element.center[1]' and '_diffrn_detector_element.center[2]'. + Correct item name of '_diffrn_refln.frame_id'. + Replace reference to '_array_intensities.undefined' by '_array_intensities.undefined_value'. + Replace references to '_array_intensity.scaling' with '_array_intensities.scaling'. + Add DIFFRN_SCAN... categories. ; 0.4 1998-08-11 ; Modifications to the 0.3 imgCIF draft. (HJB) + Reflow comment lines over 80 characters and corrected typos. + Update examples and descriptions of MIME encoded data. + Change name to cbfext98.dic. ; 0.3 1998-07-04 ; Modifications for imgCIF. (HJB) + Add binary type, which is a text field containing a variant on MIME encoded data. + Change type of '_array_data.data' to binary and specify internal structure of raw binary data. + Add '_array_data.binary_id', and make '_diffrn_frame_data.binary_id' and '_array_intensities.binary_id' into pointers to this item. ; 0.2 1997-12-02 ; Modifications to the CBF draft. (JW) + Add category hierarchy for describing frame data developed from discussions at the BNL imgCIF Workshop Oct 1997. The following changes are made in implementing the workshop draft. Category DIFFRN_ARRAY_DATA is renamed to DIFFRN_FRAME_DATA. Category DIFFRN_FRAME_TYPE is renamed to DIFFRN_DETECTOR_ELEMENT. The parent item for '_diffrn_frame_data.array_id' is changed from '_array_structure_list.array_id' to '_array_structure.id'. Item '_diffrn_detector.array_id' is deleted. + Add data item '_diffrn_frame_data.binary_id' to identify data groups within a binary section. The formal identification of the binary section is still fuzzy. ; 0.1 1997-01-24 ; First draft of this dictionary in DDL 2.1 compliant format by John Westbrook (JW). This version is adapted from the Crystallographic Binary File (CBF) Format Draft Proposal provided by Andy Hammersley (AH). Modifications to the CBF draft. (JW) + In this version the array description has been cast in the categories ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. These categories have been generalized to describe array data of arbitrary dimension. + Array data in this description are contained in the category ARRAY_DATA. This departs from the CBF notion of data existing in some special comment. In this description, data are handled as an ordinary data item encapsulated in a character data type. Although data this manner deviates from CIF conventions, it does not violate any DDL 2.1 rules. DDL 2.1 regular expressions can be used to define the binary representation which will permit some level of data validation. In this version, the placeholder type code "any" has been used. This translates to a regular expression which will match any pattern. It should be noted that DDL 2.1 already supports array data objects although these have not been used in the current mmCIF dictionary. It may be possible to use the DDL 2.1 ITEM_STRUCTURE and ITEM_STRUCTURE_LIST categories to provide the information that is carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. By moving the array structure to the DDL level it would be possible to define an array type as well as a regular expression defining the data format. + Multiple array sections can be properly handled within a single datablock. ; #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof ./CBFlib-0.9.2.2/doc/cif_core.dic0000644000076500007650000157577211603702115014625 0ustar yayayaya############################################################################## # # # CIF CORE DEFINITIONS # # -------------------- # # # # This dictionary contains the names and definitions of the Core data items # # recognised by the International Union of Crystallography for the exchange # # of data between laboratories and submissions to journals and databases. # # # # The STAR/DDL dictionary is available as the file "ddl_core.dic" # # located at URL ftp://ftp.iucr.org/pub/ddldic.c95 # # # # Copyright 2004 International Union of Crystallography # ############################################################################## data_on_this_dictionary _dictionary_name cif_core.dic _dictionary_version 2.3.1 _dictionary_update 2005-06-27 _dictionary_history ; 1991-05-27 Created from CIF Dictionary text. SRH 1991-05-30 Validated with CYCLOPS & CIF ms. SRH 1991-06-03 Adjustments to some definitions. SRH 1991-06-06 Adjustments a la B. McMahon. SRH 1991-06-18 Additions & some redefinitions. SRH 1991-07-04 Corrected 90:0 in *_detect_slit_. SRH 1991-09-20 Additions & some redefinitions. SRH 1991-09-20 Final published version. IUCr 1991-11-12 Add _diffrn_ambient_environment. SRH 1991-11-12 Allow 'c' for _atom_site_calc_flag. SRH 1993-02-23 Apply global_ and 'unknown' -> '?' SRH 1993-03-05 Changes resulting from MM dictionary. SRH 1993-05-20 Changes arising from new DDL commands. SRH 1993-08-05 Additional finetuning pre-Beijing. SRH 1993-12-22 Introductory sections added to categories. BMcM 1993-12-22 Additional categories from mm work: audit_author, citation, atom_sites_fract_tran_matrix. BMcM 1994-03-01 Add 'undef' to _refine_ls_hydrogen_treatment. BMcM 1994-03-01 Add '_publ_section_exptl_prep' and '*_refinement'. BMcM 1994-03-01 Add 'atom_site_aniso_ratio'. BMcM 1994-04-15 Comments from IDB on draft version for circulation. BMcM 1994-04-15 Added _publ_section_exptl_solution. BMcM 1994-07-14 Added B. H. Toby's suggested _diffrn_radiation_xray_symbol and _diffrn_radiation_xray_target. BMcM 1994-08-05 Revised definition for _diffrn_reflns_number (S.R. Hall). BMcM 1994-08-05 Added _atom_type_scat_length_neutron (B.H. Toby). BMcM 1994-10-13 Reworded _diffrn_standards_ a la S.R. Hall. BMcM 1994-10-13 Added _diffrn_radiation_probe for non-X-ray experiments. BMcM 1995-01-17 Rewording of definition of _chemical_melting_point. BMcM 1995-02-24 Changed text references to e.s.d to 'standard uncertainty'. BMcM 1995-07-08 Added _chemical_formula_iupac. BMcM 1995-07-09 Finally added _symmetry_equiv_pos_id. BMcM 1995-07-09 _units_extension, _units_conversion and _units_description superseded by _units and _units_detail. Suffixed datanames retained as separate entries. BMcM 1995-10-23 Added _refine_ls_R_Fsqd_factor and _refine_ls_R_I_factor BMcM 1996-03-25 Correlated with mmCIF release 0.8 BMcM 1996-05-16 Added some extra datanames for use by Acta: _publ_section_synopsis, _publ_section_title_footnote, _publ_author_footnote, _journal_paper_category, and various _journal_index_ categories BMcM 1996-05-20 Added geom_hbond category BMcM 1996-06-10 Datanames with suffixes to indicate units moved to a new compatibility dictionary cif_compat.dic BMcM 1996-06-10 Embarrassing _units_ stuff removed from geom_hbond BMcM 1996-06-10 _list_mandatory and _list_reference added to _publ_author_ datanames (where _list was given as "both") BMcM 1996-06-10 Added audit_conform category BMcM 1996-06-11 Added audit_link category BMcM 1996-06-11 Reworded _exptl_crystal_F_000 definition BMcM 1996-06-11 Added _atom_site_U_equiv_geom BMcM 1996-06-11 Added publ_body category BMcM 1996-06-27 Added examples for most of the remaining category overviews BMcM 1996-06-27 Added _journal_language BMcM 1996-06-28 Added area-detector definitions from mmCIF dictionary: _diffrn_measurement_device_details, *_specific and *_type; _diffrn_radiation_detector_details, *_specific, *_type; _diffrn_radiation_source_details, *_power, *_specific, *_target, *_type; reflns_shell category BMcM Added _refine_ls_d_res_high and *_low and changed wording of definitions for R factors to include these. BMcM Added 'h' and 'f' flags to _refln_observed_status. BMcM 1996-07-05 Some typos fixed and examples modified as suggested by P.Strickland and I.D.Brown. BMcM 1996-07-27 BMcM: Added example for _diffrn_orient_refln_[] from G. Madariaga U~ij~ changed to U^ij^ a la Nomenclature Commission Definition of _diffrn_ambient_environment changed to omit vacuum as a possible default environment Changed definitions of *_site_symmetry_* items to I.D.Brown's suggested wording. Compressed various journal indexing categories into one Changed upper enumeration values for _refln_symmetry_epsilon and _refln_symmetry_multiplicity to 48. Added references to deprecated use of B values. Modified descriptions of phone, fax number conventions _publ_manuscript_incl_ entries reworded for greater clarity and given individual data blocks Added _list_reference to _symmetry_equiv_pos_id and changed _list value to 'both' for *_as_xyz to allow the P1 case Added _atom_site_B_equiv_geom for completeness Modified definitions of _atom_sites_[Cartn,fract]_tran_vector_ Added _units stuff to _chemical_formula_weight_* and _exptl_crystal_density_ items Added *_theta, *_omega to _diffrn_orient_refln_angle_ Added 'q' to enumeration list for _diffrn_refln_scan_mode Reworded definition in _diffrn_scale_group_[] Permitted esd for _refln_phase_meas (necessitates splitting _refln_phase_ datablock in two) Added _type_conditions esd for _reflns_scale_meas_ 1996-07-28 BMcM: Added example for refln_scale_[] and second example for _refln_[] from Xtal test data set. Changed references to category names to CAPITALS. Merged CELL and CELL_MEASUREMENT categories. Added _units deg to all angle quantities. Renamed _citation_journal_coden_CAS as _citation_journal_abstract_id_CAS Removed _diffrn_measurement_device_details, *_specific, *_type, _diffrn_radiation_detector_details, *_specific, *_type, _diffrn_radiation_source_power, *_specific, *_target, *_type, pending full analysis of requirements for describing diffraction apparatus. Reworded _exptl_crystal_F_000 definition again 1996-08-03 Reworded _refine_ls_number_reflns definition a la S.R.Hall BMcM 1996-09-10 BMcM: Clarified _diffrn_attenuator_scale definition with help from SRH In _refln_symmetry_multiplicity, changed 'structure-factor value' to 'structure-factor magnitudes' Slight modification to _diffrn_reflns_number to exclude all systematic absences, not just those due to centring Removed footnote markers from example of _publ_section_title_footnote Added new example to SYMMETRY_EQUIV category to explain the use of _symmetry_equiv_pos_id Reworking of DIFFRN_RADIATION and DIFFRN_MEASUREMENT categories and introduction of DIFFRN_DETECTOR and DIFFRN_SOURCE a la I.D.Brown 1996-09-11 Corrected category assignment for _diffrn_standards_ items BMcM 1996-09-12 BMcM: Added _cell_id and _cell_measurement_refln_id Changed the term "id" to "identifier" in definitions Renamed _citation_journal_abstract_id_CAS as _citation_abstract_id_CAS Added _audit_block_code and changed definition of _audit_link_block_code to refer to it 1996-09-18 BMcM: Fine tuning of IDB's new DIFFRN categories: in DIFFRN_DETECTOR changed *_type to *_device and added *_device_type. Moved _diffrn_radiation_detector back to DIFFRN_RADIATION category with expanded definition. Reworded definitions of _diffrn_measurement_device and *_device_type. In DIFFRN_RADIATION changed enumeration range for *_polarisn_norm to -180:180 and added 'as viewed from the specimen' to the definition; also added 'Cu K-L~2,3~' to examples for *_type. Reworded definitions for _diffrn_refln_index and _diffrn_source_target, and changed _type of _diffrn_source_power to "numb". Introduced _diffrn_detector_dtime in the DIFFRN_DETECTOR category and restored _diffrn_radiation_detector_dtime to DIFFRN_RADIATION 1996-09-25 BMcM: Reworded definitions of _atom_site_disorder_assembly and *_group 1996-10-02 BMcM: Changed _symmetry_equiv_pos_id to _symmetry_equiv_pos_site_id in recognition of the technical meaning of 'position' in International Tables Addition of the names of the relevant units to definitions of _atom_type_scat_length_neutron, _exptl_crystal_size_, _geom_hbond_distance_, _refine_ls_d_res_high and *_low, _reflns_shell_d_res_high and *_low; and cosmetic expansion of units listed in the definitions for _diffrn_source_current, *_power and *_voltage Addition of '_related_function conversion' to _atom_site_B_equiv_geom and *_U_equiv_geom and _atom_site_B_iso_or_equiv and *_U_iso_or_equiv Examples for CELL_MEASUREMENT_REFLN and DIFFRN_REFLN from Gotzon Madariaga Renamed _atom_site_U_equiv_geom as _atom_site_U_equiv_geom_mean and likewise for *_B_* to increase the consistency of abbreviations, as suggested by I.D. Brown Added disorder example to the ATOM_SITE category description 1996-10-15 BMcM: Modified description of example for DIFFRN_REFLN Changed _enumeration_range of _atom_site_attached_hydrogens from 0:4 to 0:8 (cf CSD entry with refcode DUTMAG01) (PRE) Added '_enumeration_default cif' to _publ_body_format Changed underscores to spaces in the example for the Hall spacegroup symbol in data_symmetry_[] Deleted extraneous '_' in data_(_)citation_abstract_id_CAS 1996-10-27 BMcM: Changed psiscan to psi-scan at request of SRH 1996-11-05 BMcM: Changed _citation_book_coden_ISBN to _citation_book_id_ISBN, _citation_journal_coden_ASTM to _citation_journal_id_ASTM, _citation_journal_coden_CSD to _citation_journal_id_CSD, _citation_journal_coden_ISSN to _citation_journal_id_ISSN, and _citation_Medline_AN to _citation_database_id_Medline. Also modified description of CODEN in _citation_journal_id_ASTM and _database_journal_ASTM (suggested by PMDF) The phrase 'diffraction data' modified to 'intensities' in several places, some other cosmetic commas and enforcement of consistent lower-case units names (PMDF) Clarification of the definition for _diffrn_radiation_polarisn_norm (PMDF) Added 'constr' to _refine_ls_hydrogen_treatment (SRH) Corrected misassignment of category of _diffrn_radiation_detector_dtime (H.J.Bernstein) 1996-11-06 BMcM: Added "_list yes" to items in the REFLNS_SHELL category (IDB) Added "measured" to definition of _reflns_shell_number_unique_all Changed enumeration range for _diffrn_standards_decay_% to ":100" and added statement about negative values (PMDF/SRH) 1996-11-08 BMcM: _diffrn_radiation_detector, _diffrn_radiation_detector_dtime and _diffrn_radiation_source removed (these will be transferred to cif_compat.dic for compatibility with files conforming to the original dictionary) _diffrn_radiation_wavelength_* items moved to new category 1996-11-12 BMcM: Deleted _cell_id and _cell_measurement_refln_id, and clarified the intent of the CELL category in _cell_[] (PMDF) Some small rewordings of various _diffrn_* items due to B.H.Toby 1996-11-14 BMcM: Imposed consistency on the nomenclature of diffraction device data names: _diffrn_detector_device_type -> *_detector_type, _diffrn_measurement_device_details -> *_measurement_details, *_measurement_device_type -> *_measurement_type; introduction of _diffrn_source_device and parallel definitions. Existing *_measurement_details example moved to *_special_details (PMDF) 1996-11-21 BMcM: Reintroduced _diffrn_measurement_device_details, further tidying of data names thus: _diffrn_measurement_type -> *_device_type; _diffrn_detector_device and _diffrn_source_device both drop "_device" (PMDF) Added _journal_data_validation_number and _publ_requested_category to enable handling of CIF-access submissions by Acta Cryst. C 1996-11-23 A few typos fixed. BMcM 1996-11-24 BMcM: Added 'gaussian', 'multi-scan' and 'numerical' to enumeration list for _exptl_absorpt_correction_type (SRH) Added 'mixed' to enumeration list for _refine_ls_hydrogen_treatment (SRH) 1996-11-25 A few typos fixed (BMcM) 1996-11-27 BMcM: Removed looped _related_item from _publ_contact_author and reintroduced _diffrn_radiation_detector, *_dtime and _diffrn_radiation_source (see 1996-11-08) with "_related_function replace" as a preparation for using this mechanism further in version 2.1. 1996-11-27 Release version 2.0. IUCr 1997-01-20 BMcM: Some small changes thanks to PMDF. Double space after period at end of sentence changed to single space throughout; _citation_database_id_Medline _diffrn_detector_type moved to correct alphabetic sequence; space introduced between sentences in definition of _citation_journal_id_CSD; some other minor grammatical changes 1997-10-30 BMcM: (changes to align with Acta C Notes for Authors) Obsoleted *_obs_* entries in REFLNS and REFINE_LS categories and replaced with *_gt_*; obsoleted _refine_ls_shift/esd_ by _refine_ls_shift/su_; obsoleted _atom_site_thermal_displace_type by *_adp_type 1997-11-05 BMcM: (changes to align with Acta C Notes for Authors) Added _diffrn_detector_area_resol_mean, _diffrn_measured_fraction_theta_max and *_full, _diffrn_reflns_theta_full 1997-11-05 BMcM: Added _reflns_number_Friedel; changed various *_obs items in examples to *_gt equivalents and likewise for other obsoleted items 1997-11-24 BMcM: Slightly changed wording of _reflns_number_Friedel and _reflns_threshold_expression at suggestion of I.D.Brown. Modified definition of _refine_ls_abs_structure_Flack and changed the text of the example in category REFINE at the request of H.D.Flack. 1997-12-08 BMcM: Removed the phrase "(enantiomorph or polarity)" from _refine_ls_abs_structure_Flack and *_Rogers because "absolute structure" is a phrase uniquely defined (H.D.Flack) 1997-12-08 BMcM: Several instances of \s changed to u 1997-12-08 BMcM: Modified definitions of _reflns_number_total and *_Friedel (after H.D.Flack) to clarify the distinction between crystal-class and Laue-symmetry independent reflection sets 1997-12-08 BMcM: Added _chemical_absolute_configuration and _chemical_optical_rotation (H.D.Flack) 1998-08-04 BMcM: Moved _diffrn_pressure_history and _diffrn_thermal_history from draft msCIF dictionary to core as _exptl_crystal_pressure_history and _exptl_crystal_thermal_history (G. Madariaga/I.D.Brown) Moved _diffrn_symmetry_description and REFINE_LS_CLASS from draft msCIF dictionary to core (G. Madariaga/I.D.Brown) 1998-08-04 BMcM: Minor rewordings of _refine_ls_R_Fsqd_factor, _refine_ls_R_I_factor, various definitions referring to F_calc in electrons, and _reflns_shell_number_unique_* (I.D.Brown) 1998-08-04 BMcM: added _reflns_Friedel_coverage (H.D.Flack/S.R.Hall) 1998-08-04 BMcM: changed formula for F(000) (from F(000) = [ sum (f~r~^2^ + f~i~^2^) ]^1/2^ to F(000) = [ (sum f~r~)^2^ + (sum f~i~)^2^ ]^1/2^ ) (H.D.Flack) 1998-08-04 BMcM: added 'syn' and 'unk' as enumerations to _chemical_absolute_configuration (H.D.Flack/A.Linden) 1998-09-02 BMcM: added _exptl_crystal_size_length and modified slightly the definition of _exptl_crystal_size_ (W.Clegg/I.D.Brown) Added _diffrn_attenuator_material (I.D.Brown) Added sentence explaining the physical meaning of the _enumeration_range to _refine_ls_abs_structure_Flack (H.D.Flack) Some rewording in _chemical_absolute_configuration implying that for absolute configuration determination the measurement and reporting of the optical rotation in solution are considered mandatory. (H.D.Flack) Some rewording in _reflns_number_total and *_gt to clarify the inclusion of Friedel reflections; addition of _reflns_Friedel_coverage; deletion of _reflns_number_Friedel (H.D.Flack/S.R.Hall) Further minor rewording to _reflns_shell_number_unique_all, *_gt, *_obs (H.D.Flack) 1998-09-10 BMcM: transferred _diffrn_reflns_number_of_classes and the categories DIFFRN_REFLNS_CLASS, REFLNS_CLASS and REFLNS_SHELL_CLASS from the draft msCIF dictionary; added _diffrn_refln_class_code and _refln_class_code to link individual reflections to their related categories. 1998-12-08 BMcM: implemented H.D. Flack's reworking of DIFFRN_REFLNS_CLASS, REFLNS_CLASS, REFLNS_SHELL_CLASS and REFINE_LS_CLASS, deleting the latter two; removed _diffrn_reflns_number_of_classes. 1998-12-15 BMcM: completed the above reworking; fixed embarrassing typo for _related_function 1999-01-16 BMcM: coreDMG review of version 2.1beta5. Numerous small changes from I.D.Brown, the most significant being: _atom_site_occupancy definition clarifies how to impose an experimental uncertainty on the _enumeration_range; _atom_site_U_iso_or_equiv enumeration range set to infinity; _atom_type_analytical_mass_% enumeration range set as 0:100; expanded definitions of _diffrn_radiation_probe and *_type to clarify the distinction between these two items; added reference to _exptl_crystal_size to the definition of _exptl_crystal_description, and modified the definition of _exptl_crystal_face_diffr_ ; new data item _refln_d_spacing; clarified the role of _reflns_special_details in specifying whether Friedel pairs have been averaged; Numerous small changes from H.D.Flack, most significantly: removed enumeration range from _diffrn_refln_counts_ because *_net can go negative; fixed various typos in equations for wR and S; removed reference to Friedel reflections from _refln_symmetry_multiplicity 1999-01-24 BMcM: further revision to wording of _refln_symmetry_multiplicity following discussions by HDF and IDB Numerous small changes from G.Madariaga, most significantly: a instead of A for real-space cell lengths (_atom_site_B_iso_or_equiv and _atom_site_U_iso_or_equiv); _related_function alternate for _atom_site_Cartn_ & _fract_; "or scattering lengths" added to _atom_type_scat_source; deleted incorrect _list_reference in DIFFRN_RADIATION; added rtf to enumeration in _publ_body_format; added enumeration range to _refine_ls_abs_structure_Rogers 1999-02-04 BMcM: fixed some long lines 1999-02-06 BMcM: data names using sigma as an indicator of experimental standard uncertainty replaced by equivalents using the preferred 'u' notation (HDF): _diffrn_refln_intensity_sigma _diffrn_reflns_av_sigmaI/netI _diffrn_reflns_class_av_sgI/I _diffrn_standards_scale_sigma _reflns_shell_meanI_over_sigI_all _reflns_shell_meanI_over_sigI_gt (_reflns_shell_meanI_over_sigI_obs already replaced by *_gt) addition of '_related function alternate' to new data items corresponding to old items with '_related_function replace' (SRH) Example for _citation_journal_id_CSD changed to 0070 to reflect current practice at PDB (F.C.Bernstein) Added _atom_type_scat_dispersion_source (GM) 1999-03-24 Some minor cosmetic modifications (BMcM) 1999-03-24 Release version 2.1. IUCr 2001-01-09 BMcM: simplified entry for _chemical_absolute_configuration (H.D.Flack) Added _geom_bond_valence and the new categories VALENCE_PARAM and VALENCE_REF (I.D.Brown) 2001-01-11 BMcM: Categories EI, EO, EM added to _publ_requested_category 2001-01-11 Release version 2.2. IUCr 2003-09-28 BMcM: incorporated changes approved by COMCIFS following discussions of the core Dictionary Management Group: _atom_site_fract_ nonsense enumeration default value removed _atom_site_refinement_flags deprecated in favour of new *_flags_posn, *_adp and *_occupancy items _atom_sites_special_details added _cell_reciprocal_angle_ and *_length_ added '_type_conditions esd' added to _chemical_melting_point _chemical_melting_point_gt and *_lt added Added several new items describing chemical properties to the CHEMICAL category: _chemical_properties_biological and *_physical, _chemical_temperature_decomposition_* and *_sublimation_*, at the request of CCDC _citation_database_id_CSD added at request of CCDC Several additional tags storing deposition numbers of database entries and record revision history at request of CCDC: _database_code_depnum_ccdc_fiz, *_journal, *_archive and _database_CSD_history Added _diffrn_ambient_pressure_gt,lt and *_temperature_gt,lt Added _diffrn_source_take-off_angle Added _diffrn_standards_decay_%_lt _diffrn_reflns_measured_fraction_resolution_full and *_max introduced as replacements for _diffrn_measured_fraction_theta_full and *_max, moved to a more appropriate category and defined in terms of resolution rather than angle which depends on the radiation used. Likewise for _diffrn_reflns_resolution_full and *_max as replacements for _diffrn_reflns_theta_full and *_max More specific parsable tags for crystal colour introduced as _exptl_crystal_colour_primary, *_modifier and *_lustre Added _exptl_crystal_density_meas_gt,lt and *_meas_temp_gt,lt Added _exptl_crystal_recrystallization_method Added _publ_contact_author_id_iucr and _publ_author_id_iucr to allow unique author identification by IUCr database reference identifier More datanames for recording imprecise quantities: _refine_ls_shift/su_max_lt and _refine_ls_shift/su_mean_lt Added the categories SPACE_GROUP and SPACE_GROUP_SYMOP as imports from the symmetry dictionary cif_sym.dic Added _related_function 'replace' to a number of items in the old SYMMETRY category pointing to the preferred items from the new SPACE_GROUP category 2003-08-19 BMcM: formal approval for COMCIFS for the additions and contingent changes discussed on the coreDMG discussion list from June 2002 2003-09-29 BMcM: second round of changes from coreDMG discussions: Added _enumeration_range to new _chemical_temperature_* items; Expanded definition of _space_group_symop_operation_xyz to make explicit the need for inclusion of centring translations (HDF/IDB) Removed _diffrn_reflns_measured_fraction_resolution_full and *_max for reconsideration following suggestion by Curt Haltiwanger that terms are needed that do not refer to resolution or theta Likewise removed _diffrn_standards_decay_%_lt for further consideration, and added _type_conditions esd to _diffrn_standards_decay_% as a measurable quantity (CH/HDF) Modified _example_detail for _space_group_symop_operation_xyz to use a full and unambiguous wording in accordance with International Tables A (CH/IDB/HDF) 2003-09-29 Removed "_type_conditions esd" from the remaining *_gt and *_lt items at the suggestion of Gotzon Madariaga: since these are ceiling/floor values a measurable uncertainty is pointless (BMcM) 2003-10-01 Fixed some typos following checking by IDB (BMcM) 2003-10-03 BMcM: Final editorial pass. Added _related_function alternate to _exptl_crystal_colour. Also added this flag to the new items which replace existing ones: _atom_site_refinement_flags_* and the _space_group_ items 2003-10-04 Release version 2.3. IUCr 2004-06-06 BMcM: minor editorial changes for International Tables Volume G. Text of _atom_sites_*_tran_* definitions changed to ATOM_SITE from STOM_SITES. Some realignment of examples to fit column width. 2004-09-11 BMcM: corrected related item error in _atom_site_refinement_flags_posn, *_adp and *_occupancy 2004-11-26 NJA: updated reference to IT Vol A from 1987 to 2002 2004-12-22 NJA: minor corrections to hyphenation, spelling and punctuation atom_site definition: ', and so on' removed _atom_site_aniso_B_: 1/4 in formula replaced by (1/4) _atom_site_aniso_label: '...atom coordinate list' changed to '...atom in the atom coordinate list' _atom_site_B_iso_or_equiv: 'anisotropic temperature factor parameters' changed to 'anisotropic displacement components' _atom_site_label: 'Each label may have...' changed to 'Different labels may have...' _atom_site_type_symbol: '...atom specie(s)...' changed to 'atom species (singular or plural)...' _atom_type_scat_Cromer_Mann_: reference to Volume C updated to 2004 _atom_type_symbol: 'atom specie(s)' changed to 'atom species (singular or plural)' _audit_conform_dict_location: 'where the conformant dictionary resides' changed to 'for the dictionary to which the current data block conforms' _audit_conform_dict_version: 'conformant dictionary' changed to 'dictionary to which the current data block conforms' 2004-12-23 NJA: minor corrections to hyphenation, spelling and punctuation _audit_contact_author_fax,_audit_contact_author_phone: edited slightly _cell_angle_: 'in degrees of the reported structure' changed to 'of the reported structure in degrees' _cell_measurement_pressure: 'pressure used to synthesize the sample' changed to 'pressure at which the sample was synthesized' _cell_measurement_theta_: 'angles in degrees of reflections used to measure the unit cell' changed to 'angles of reflections used to measure the unit cell in degrees' _cell_reciprocal_angle_: 'angles in degrees defining the reciprocal cell' changed to 'angles defining the reciprocal cell in degrees' _chemical_[]: 'compounds' changed to 'compound' _chemical_optical_rotation: 'c is the value of CONC in g' changed to 'c is the value of CONC as defined above'. _chemical_properties_physical, _biological: 'free description' changed to 'free-text description' _chemical_conn_atom_display_: 'if absent...staff.' deleted _citation_[]: 'literature cited relevant' changed to 'literature cited as being relevant' _citation_*: 'book chapters' changed to 'books or book chapters' _citation_country: 'both journal articles and' deleted _citation_database_id_CSD: 'containing' changed to 'that contains' _citation_language: 'citation appears' changed to 'cited article is written' _diffrn_crystal_treatment: 'intensity measurement' changed to 'the intensity measurements' _diffrn_special_details: 'diffraction measurement' changed to 'intensity-measurement' _diffrn_attenuator_scale: 'This scale must be multiplied by the measured intensity to convert it...' changed to 'The measured intensity must be multiplied by this scale to convert it...' _diffrn_orient_matrix_[]: 'used in data measurement' changed to 'used in the measurement of the diffraction intensities' _diffrn_orient_refln_angle_: 'in degrees of a reflection... matrix' changed to 'of a reflection...matrix in degrees' _diffrn_radiation_probe,_diffrn_radiation_type: definitions reworded slightly _diffrn_refln_angle_: 'in degrees of a reflection' changed to 'of a reflection in degrees' _diffrn_refln_elapsed_time: 'diffraction measurement' changed to 'the diffraction experiment' _diffrn_refln_scale_group_code: 'applying' changed to 'applicable' _diffrn_refln_scan_mode: 'with a diffractometer' changed to 'for measurements using a diffractometer' _diffrn_refln_scan_rate: 'to measure the intensity in degrees per minute' changed to 'in degrees per minute to measure the intensity' _diffrn_refln_standard_code: 'identifying' changed to 'indicating'; 'intensity' changed to 'reflection' _diffrn_reflns_class_d_res_high,_low: defintions rephrased. _diffrn_source_details: 'used' deleted. _diffrn_source_target: 'for generation of' changed to 'to generate' _diffrn_standards_decay_%: 'at the start of the measurement process and at the finish' changed to 'from the start of the measurement process to the end' _diffrn_standards_number: 'used in the diffraction measurements' changed to 'used during the measurement of the diffraction intensities' _exptl_absorpt_correction_type: 'no more detailed information is' changed to 'more detailed information is not'. _exptl_crystal_[]: 'and so on' deleted _exptl_crystal_face_perp_dist: 'millimetres of the face' changed to 'millimetres from the face' _geom_[], _geom_angle_[], _geom_bond_[], _geom_contact_[], _geom_hbond_[], _geom_torsion_[]: 'contents of the' deleted _geom_contact_[], _geom_torsion_[]: year for reference for example 1 corrected from 1991 to 1992 _geom_hbond_angle_DHA: 'Site at *_D' changed to 'Site at *_H' _publ_contact_author_fax: definition rephrased slightly _publ_requested_category: Cif-access codes marked as '(no longer in use)' 2005-01-05 NJA: minor corrections to hyphenation, spelling and punctuation _refine_ls_*: 'least squares' changed to 'least-squares refinement' _refine_ls_restrained_S_all: `Y(calc) = the observed coefficients` changed to `Y(calc) = the calculated coefficients` _refine_ls_restrained_S_gt: `Y(calc) = the observed coefficients` changed to `Y(calc) = the calculated coefficients` _refine_ls_restrained_S_obs: `Y(calc) = the observed coefficients` changed to `Y(calc) = the calculated coefficients` _refine_ls_shift/esd_*: 'divided by' changed to 'to' _refine_ls_shift/su_*: 'divided by' changed to 'to' _refine_ls_class_d_res_*: edited slightly _refine_ls_d_res_*: edited slightly _refln_intensity_*: edited slightly _refln_symmetry_multiplicity: reference to Volume A updated to (2002), Chapter 10.1 _reflns_d_resolution_*: edited slightly _reflns_class_d_res_*: edited slightly _reflns_shell_d_res_*: edited slightly _space_group_name_Hall: erratum added to reference to Hall (1981); reference to Volume B updated to 2001. _space_group_name_H-M_alt: reference to Volume A updated to (2002) _symmetry_Int_Tables_number: reference to Volume A updated to (2002) _symmetry_space_group_name_Hall: erratum added to reference to Hall (1981) _symmetry_space_group_name_H-M: reference to Volume A updated to (2002) _symmetry_equiv_pos_as_xyz: reference to Volume A updated to (2002) 2005-01-11 NJA: more minor corrections to hyphenation, spelling and punctuation 2005-01-21 NJA: _reflns_shell_Rmerge_I_obs: related item changed from _reflns_shell_Rmerge_I_obs to _reflns_shell_Rmerge_I_gt 2005-06-21 NJA: corrections to proofs of Intl Tables G Chapter 4.1 included. New data name _publ_author_email added. 2005-06-27 BMcM: Removed _list_mandatory yes from _atom_site_aniso_label in response to cif-developers list discussion ; ############### ## ATOM_SITE ## ############### data_atom_site_[] _name '_atom_site_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _atom_site_label _atom_site_fract_x _atom_site_fract_y _atom_site_fract_z _atom_site_U_iso_or_equiv _atom_site_adp_type _atom_site_calc_flag _atom_site_calc_attached_atom O1 .4154(4) .5699(1) .3026(0) .060(1) Uani ? ? C2 .5630(5) .5087(2) .3246(1) .060(2) Uani ? ? C3 .5350(5) .4920(2) .3997(1) .048(1) Uani ? ? N4 .3570(3) .5558(1) .4167(0) .039(1) Uani ? ? C5 .3000(5) .6122(2) .3581(1) .045(1) Uani ? ? O21 .6958(5) .4738(2) .2874(1) .090(2) Uani ? ? C31 .4869(6) .3929(2) .4143(2) .059(2) Uani ? ? # - - - - data truncated for brevity - - - - H321C .04(1) .318(3) .320(2) .14000 Uiso ? ? H322A .25(1) .272(4) .475(3) .19000 Uiso ? ? H322B .34976 .22118 .40954 .19000 Uiso calc C322 H322C .08(1) .234(4) .397(3) .19000 Uiso ? ? ; ; Example 1 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _atom_site_aniso_label _atom_site_aniso_B_11 _atom_site_aniso_B_22 _atom_site_aniso_B_33 _atom_site_aniso_B_12 _atom_site_aniso_B_13 _atom_site_aniso_B_23 _atom_site_aniso_type_symbol O1 .071(1) .076(1) .0342(9) .008(1) .0051(9) -.0030(9) O C2 .060(2) .072(2) .047(1) .002(2) .013(1) -.009(1) C C3 .038(1) .060(2) .044(1) .007(1) .001(1) -.005(1) C N4 .037(1) .048(1) .0325(9) .0025(9) .0011(9) -.0011(9) N C5 .043(1) .060(1) .032(1) .001(1) -.001(1) .001(1) C # - - - - data truncated for brevity - - - - O21 .094(2) .109(2) .068(1) .023(2) .038(1) -.010(1) O C51 .048(2) .059(2) .049(1) .002(1) -.000(1) .007(1) C C511 .048(2) .071(2) .097(3) -.008(2) -.003(2) .010(2) C C512 .078(2) .083(2) .075(2) .009(2) -.005(2) .033(2) C C513 .074(2) .055(2) .075(2) .004(2) .001(2) -.010(2) C # - - - - data truncated for brevity - - - - ; ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _atom_site_label _atom_site_chemical_conn_number _atom_site_fract_x _atom_site_fract_y _atom_site_fract_z _atom_site_U_iso_or_equiv S1 1 0.74799(9) -0.12482(11) 0.27574(9) 0.0742(3) S2 2 1.08535(10) 0.16131(9) 0.34061(9) 0.0741(3) N1 3 1.0650(2) -0.1390(2) 0.2918(2) 0.0500(5) C1 4 0.9619(3) -0.0522(3) 0.3009(2) 0.0509(6) # - - - - data truncated for brevity - - - - ; ; Example 3 - based on data set DPTD of Yamin, Suwandi, Fun, Sivakumar & bin Shawkataly [Acta Cryst. (1996), C52, 951-953]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _atom_site_label # *_assembly 'M' is a disordered methyl _atom_site_occupancy # with configurations 'A' and 'B': _atom_site_disorder_assembly # _atom_site_disorder_group # H11B H11A H13B # . | . C1 1 . . # . | . H11A .5 M A # . | . H12A .5 M A # C1 --------C2--- H13A .5 M A # / . \ H11B .5 M B # / . \ H12B .5 M B # / . \ H13B .5 M B # H12A H12B H13A ; ; Example 4 - hypothetical example to illustrate the description of a disordered methyl group. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the ATOM_SITE category record details about the atom sites in a crystal structure, such as the positional coordinates, atomic displacement parameters, and magnetic moments and directions. ; data_atom_site_adp_type _name '_atom_site_adp_type' _category atom_site _type char _related_item '_atom_site_thermal_displace_type' _related_function alternate _list yes _list_reference '_atom_site_label' loop_ _enumeration _enumeration_detail Uani 'anisotropic Uij' Uiso 'isotropic U' Uovl 'overall U' Umpe 'multipole expansion U' Bani 'anisotropic Bij' Biso 'isotropic B' Bovl 'overall B' _definition ; A standard code used to describe the type of atomic displacement parameters used for the site. ; data_atom_site_aniso_B_ loop_ _name '_atom_site_aniso_B_11' '_atom_site_aniso_B_12' '_atom_site_aniso_B_13' '_atom_site_aniso_B_22' '_atom_site_aniso_B_23' '_atom_site_aniso_B_33' _category atom_site _type numb _type_conditions esd _list yes _list_reference '_atom_site_aniso_label' _related_item '_atom_site_aniso_U_' _related_function conversion _units A^2^ _units_detail 'angstroms squared' _definition ; These are the standard anisotropic atomic displacement components in angstroms squared which appear in the structure-factor term T = exp{-(1/4) sum~i~ [ sum~j~ (B^ij^ h~i~ h~j~ a*~i~ a*~j~) ] } h = the Miller indices a* = the reciprocal-space cell lengths The unique elements of the real symmetric matrix are entered by row. The IUCr Commission on Nomenclature recommends against the use of B for reporting atomic displacement parameters. U, being directly proportional to B, is preferred. ; data_atom_site_aniso_label _name '_atom_site_aniso_label' _category atom_site _type char _list yes _list_link_parent '_atom_site_label' _definition ; Anisotropic atomic displacement parameters are usually looped in a separate list. If this is the case, this code must match the _atom_site_label of the associated atom in the atom coordinate list and conform with the same rules described in _atom_site_label. ; data_atom_site_aniso_ratio _name '_atom_site_aniso_ratio' _category atom_site _type numb _list yes _list_reference '_atom_site_aniso_label' _enumeration_range 1.0: _definition ; Ratio of the maximum to minimum principal axes of displacement (thermal) ellipsoids. ; data_atom_site_aniso_type_symbol _name '_atom_site_aniso_type_symbol' _category atom_site _type char _list yes _list_reference '_atom_site_aniso_label' _list_link_parent '_atom_site_type_symbol' _definition ; This _atom_type_symbol code links the anisotropic atom parameters to the atom-type data associated with this site and must match one of the _atom_type_symbol codes in this list. ; data_atom_site_aniso_U_ loop_ _name '_atom_site_aniso_U_11' '_atom_site_aniso_U_12' '_atom_site_aniso_U_13' '_atom_site_aniso_U_22' '_atom_site_aniso_U_23' '_atom_site_aniso_U_33' _category atom_site _type numb _type_conditions esd _list yes _list_reference '_atom_site_aniso_label' _related_item '_atom_site_aniso_B_' _related_function conversion _units A^2^ _units_detail 'angstroms squared' _definition ; These are the standard anisotropic atomic displacement components in angstroms squared which appear in the structure-factor term T = exp{-2pi^2^ sum~i~ [sum~j~ (U^ij^ h~i~ h~j~ a*~i~ a*~j~) ] } h = the Miller indices a* = the reciprocal-space cell lengths The unique elements of the real symmetric matrix are entered by row. ; data_atom_site_attached_hydrogens _name '_atom_site_attached_hydrogens' _category atom_site _type numb _list yes _list_reference '_atom_site_label' _enumeration_range 0:8 _enumeration_default 0 loop_ _example _example_detail 2 'water oxygen' 1 'hydroxyl oxygen' 4 'ammonium nitrogen' _definition ; The number of hydrogen atoms attached to the atom at this site excluding any hydrogen atoms for which coordinates (measured or calculated) are given. ; data_atom_site_B_equiv_geom_mean _name '_atom_site_B_equiv_geom_mean' _category atom_site _type numb _type_conditions esd _list yes _list_reference '_atom_site_label' _enumeration_range 0.0: loop_ _related_item _related_function '_atom_site_B_iso_or_equiv' alternate '_atom_site_U_equiv_geom_mean' conversion _units A^2^ _units_detail 'angstroms squared' _definition ; Equivalent isotropic atomic displacement parameter, B(equiv), in angstroms squared, calculated as the geometric mean of the anisotropic atomic displacement parameters. B(equiv) = (B~i~ B~j~ B~k~)^1/3^ B~n~ = the principal components of the orthogonalized B^ij^ The IUCr Commission on Nomenclature recommends against the use of B for reporting atomic displacement parameters. U, being directly proportional to B, is preferred. ; data_atom_site_B_iso_or_equiv _name '_atom_site_B_iso_or_equiv' _category atom_site _type numb _type_conditions esd _list yes _list_reference '_atom_site_label' _enumeration_range 0.0: loop_ _related_item _related_function '_atom_site_B_equiv_geom_mean' alternate '_atom_site_U_iso_or_equiv' conversion _units A^2^ _units_detail 'angstroms squared' _definition ; Isotropic atomic displacement parameter, or equivalent isotropic atomic displacement parameter, B(equiv), in angstroms squared, calculated from anisotropic displacement components. B(equiv) = (1/3) sum~i~[sum~j~(B^ij^ a*~i~ a*~j~ a~i~ a~j~)] a = the real-space cell lengths a* = the reciprocal-space cell lengths B^ij^ = 8 pi^2^ U^ij^ Ref: Fischer, R. X. & Tillmanns, E. (1988). Acta Cryst. C44, 775-776. The IUCr Commission on Nomenclature recommends against the use of B for reporting atomic displacement parameters. U, being directly proportional to B, is preferred. ; data_atom_site_calc_attached_atom _name '_atom_site_calc_attached_atom' _category atom_site _type char _list yes _list_reference '_atom_site_label' _enumeration_default '.' _definition ; The _atom_site_label of the atom site to which the 'geometry- calculated' atom site is attached. ; data_atom_site_calc_flag _name '_atom_site_calc_flag' _category atom_site _type char _list yes _list_reference '_atom_site_label' loop_ _enumeration _enumeration_detail d 'determined from diffraction measurements' calc 'calculated from molecular geometry' c 'abbreviation for "calc"' dum 'dummy site with meaningless coordinates' _enumeration_default d _definition ; A standard code to signal whether the site coordinates have been determined from the intensities or calculated from the geometry of surrounding sites, or have been assigned dummy coordinates. The abbreviation 'c' may be used in place of 'calc'. ; data_atom_site_Cartn_ loop_ _name '_atom_site_Cartn_x' '_atom_site_Cartn_y' '_atom_site_Cartn_z' _category atom_site _type numb _type_conditions esd _related_item '_atom_site_fract_' _related_function alternate _list yes _list_reference '_atom_site_label' _units A _units_detail 'angstroms' _definition ; The atom-site coordinates in angstroms specified according to a set of orthogonal Cartesian axes related to the cell axes as specified by the _atom_sites_Cartn_transform_axes description. ; data_atom_site_chemical_conn_number _name '_atom_site_chemical_conn_number' _category atom_site _type numb _list yes _list_link_parent '_chemical_conn_atom_number' _list_reference '_atom_site_label' _enumeration_range 1: _definition ; This number links an atom site to the chemical connectivity list. It must match a number specified by _chemical_conn_atom_number. ; data_atom_site_constraints _name '_atom_site_constraints' _category atom_site _type char _list yes _list_reference '_atom_site_label' _enumeration_default '.' _example 'pop=1.0-pop(Zn3)' _definition ; A description of the constraints applied to parameters at this site during refinement. See also _atom_site_refinement_flags and _refine_ls_number_constraints. ; data_atom_site_description _name '_atom_site_description' _category atom_site _type char _list yes _list_reference '_atom_site_label' _example 'Ag/Si disordered' _definition ; A description of special aspects of this site. See also _atom_site_refinement_flags. ; data_atom_site_disorder_assembly _name '_atom_site_disorder_assembly' _category atom_site _type char _list yes _list_reference '_atom_site_label' loop_ _example _example_detail A 'disordered methyl assembly with groups 1 and 2' B 'disordered sites related by a mirror' S 'disordered sites independent of symmetry' _definition ; A code which identifies a cluster of atoms that show long-range positional disorder but are locally ordered. Within each such cluster of atoms, _atom_site_disorder_group is used to identify the sites that are simultaneously occupied. This field is only needed if there is more than one cluster of disordered atoms showing independent local order. ; data_atom_site_disorder_group _name '_atom_site_disorder_group' _category atom_site _type char _list yes _list_reference '_atom_site_label' loop_ _example _example_detail 1 'unique disordered site in group 1' 2 'unique disordered site in group 2' -1 'symmetry-independent disordered site' _definition ; A code which identifies a group of positionally disordered atom sites that are locally simultaneously occupied. Atoms that are positionally disordered over two or more sites (e.g. the hydrogen atoms of a methyl group that exists in two orientations) can be assigned to two or more groups. Sites belonging to the same group are simultaneously occupied, but those belonging to different groups are not. A minus prefix (e.g. "-1") is used to indicate sites disordered about a special position. ; data_atom_site_fract_ loop_ _name '_atom_site_fract_x' '_atom_site_fract_y' '_atom_site_fract_z' _category atom_site _type numb _type_conditions esd _related_item '_atom_site_Cartn_' _related_function alternate _list yes _list_reference '_atom_site_label' _definition ; Atom-site coordinates as fractions of the _cell_length_ values. ; data_atom_site_label _name '_atom_site_label' _category atom_site _type char _list yes _list_mandatory yes loop_ _list_link_child '_atom_site_aniso_label' '_geom_angle_atom_site_label_1' '_geom_angle_atom_site_label_2' '_geom_angle_atom_site_label_3' '_geom_bond_atom_site_label_1' '_geom_bond_atom_site_label_2' '_geom_contact_atom_site_label_1' '_geom_contact_atom_site_label_2' '_geom_hbond_atom_site_label_D' '_geom_hbond_atom_site_label_H' '_geom_hbond_atom_site_label_A' '_geom_torsion_atom_site_label_1' '_geom_torsion_atom_site_label_2' '_geom_torsion_atom_site_label_3' '_geom_torsion_atom_site_label_4' loop_ _example C12 Ca3g28 Fe3+17 H*251 boron2a C_a_phe_83_a_0 Zn_Zn_301_A_0 _definition ; The _atom_site_label is a unique identifier for a particular site in the crystal. This code is made up of a sequence of up to seven components, _atom_site_label_component_0 to *_6, which may be specified as separate data items. Component 0 usually matches one of the specified _atom_type_symbol codes. This is not mandatory if an _atom_site_type_symbol item is included in the atom-site list. The _atom_site_type_symbol always takes precedence over an _atom_site_label in the identification of the atom type. The label components 1 to 6 are optional, and normally only components 0 and 1 are used. Note that components 0 and 1 are concatenated, while all other components, if specified, are separated by an underscore. Underscores are only used if higher-order components exist. If an intermediate component is not used, it may be omitted provided the underscore separators are inserted. For example, the label 'C233__ggg' is acceptable and represents the components C, 233, '' and ggg. Different labels may have a different number of components. ; data_atom_site_label_component_ loop_ _name '_atom_site_label_component_0' '_atom_site_label_component_1' '_atom_site_label_component_2' '_atom_site_label_component_3' '_atom_site_label_component_4' '_atom_site_label_component_5' '_atom_site_label_component_6' _category atom_site _type char _list yes _list_reference '_atom_site_label' _definition ; Component 0 is normally a code which matches identically with one of the _atom_type_symbol codes. If this is the case, then the rules governing the _atom_type_symbol code apply. If, however, the data item _atom_site_type_symbol is also specified in the atom-site list, component 0 need not match this symbol or adhere to any of the _atom_type_symbol rules. Component 1 is referred to as the "atom number". When component 0 is the atom-type code, it is used to number the sites with the same atom type. This component code must start with at least one digit which is not followed by a + or - sign (to distinguish it from the component 0 rules). Components 2 to 6 contain the identifier, residue, sequence, asymmetry identifier and alternate codes, respectively. These codes may be composed of any characters except an underscore. ; data_atom_site_occupancy _name '_atom_site_occupancy' _category atom_site _type numb _type_conditions esd _list yes _list_reference '_atom_site_label' _enumeration_range 0.0:1.0 _enumeration_default 1.0 _definition ; The fraction of the atom type present at this site. The sum of the occupancies of all the atom types at this site may not significantly exceed 1.0 unless it is a dummy site. The value must lie in the 99.97% Gaussian confidence interval -3u =< x =< 1 + 3u. The _enumeration_range of 0.0:1.0 is thus correctly interpreted as meaning (0.0 - 3u) =< x =< (1.0 + 3u). ; data_atom_site_refinement_flags _name '_atom_site_refinement_flags' _category atom_site _type char _list yes _list_reference '_atom_site_label' loop_ _related_item _related_function '_atom_site_refinement_flags_posn' replace '_atom_site_refinement_flags_adp' replace '_atom_site_refinement_flags_occupancy' replace loop_ _enumeration _enumeration_detail . 'no refinement constraints' S 'special-position constraint on site' G 'rigid-group refinement of site' R 'riding-atom site attached to non-riding atom' D 'distance or angle restraint on site' T 'thermal displacement constraints' U 'Uiso or Uij restraint (rigid bond)' P 'partial occupancy constraint' _definition ; A concatenated series of single-letter codes which indicate the refinement restraints or constraints applied to this site. This item should not be used. It has been replaced by _atom_site_refinement_flags_posn, *_adp and *_occupancy. It is retained in this dictionary only to provide compatibility with legacy CIFs. ; data_atom_site_refinement_flags_adp _name '_atom_site_refinement_flags_adp' _category atom_site _type char _list yes _list_reference '_atom_site_label' _related_item '_atom_site_refinement_flags' _related_function alternate loop_ _enumeration _enumeration_detail . 'no constraints on atomic displacement parameters' T 'special-position constraints on atomic displacement parameters' U 'Uiso or Uij restraint (rigid bond)' TU 'both constraints applied' _definition ; A code which indicates the refinement restraints or constraints applied to the atomic displacement parameters of this site. ; data_atom_site_refinement_flags_occupancy _name '_atom_site_refinement_flags_occupancy' _category atom_site _type char _list yes _list_reference '_atom_site_label' _related_item '_atom_site_refinement_flags' _related_function alternate loop_ _enumeration _enumeration_detail . 'no constraints on site-occupancy parameters' P 'site-occupancy constraint' _definition ; A code which indicates that refinement restraints or constraints were applied to the occupancy of this site. ; data_atom_site_refinement_flags_posn _name '_atom_site_refinement_flags_posn' _category atom_site _type char _list yes _list_reference '_atom_site_label' _related_item '_atom_site_refinement_flags' _related_function alternate loop_ _enumeration _enumeration_detail . 'no constraints on positional coordinates' D 'distance or angle restraint on positional coordinates' G 'rigid-group refinement of positional coordinates' R 'riding-atom site attached to non-riding atom' S 'special-position constraint on positional coordinates' DG 'combination of the above constraints' DR 'combination of the above constraints' DS 'combination of the above constraints' GR 'combination of the above constraints' GS 'combination of the above constraints' RS 'combination of the above constraints' DGR 'combination of the above constraints' DGS 'combination of the above constraints' DRS 'combination of the above constraints' GRS 'combination of the above constraints' DGRS 'combination of the above constraints' _definition ; A code which indicates the refinement restraints or constraints applied to the positional coordinates of this site. ; data_atom_site_restraints _name '_atom_site_restraints' _category atom_site _type char _list yes _list_reference '_atom_site_label' _example 'restrained to planar ring' _definition ; A description of restraints applied to specific parameters at this site during refinement. See also _atom_site_refinement_flags and _refine_ls_number_restraints. ; data_atom_site_symmetry_multiplicity _name '_atom_site_symmetry_multiplicity' _category atom_site _type numb _list yes _list_reference '_atom_site_label' _enumeration_range 1:192 _definition ; The multiplicity of a site due to the space-group symmetry as given in International Tables for Crystallography Vol. A (2002). ; data_atom_site_thermal_displace_type _name '_atom_site_thermal_displace_type' _category atom_site _type char _related_item '_atom_site_adp_type' _related_function replace _list yes _list_reference '_atom_site_label' loop_ _enumeration _enumeration_detail Uani 'anisotropic Uij' Uiso 'isotropic U' Uovl 'overall U' Umpe 'multipole expansion U' Bani 'anisotropic Bij' Biso 'isotropic B' Bovl 'overall B' _definition ; A standard code used to describe the type of atomic displacement parameters used for the site. ; data_atom_site_type_symbol _name '_atom_site_type_symbol' _category atom_site _type char _list yes _list_reference '_atom_site_label' _list_link_parent '_atom_type_symbol' _list_link_child '_atom_site_aniso_type_symbol' loop_ _example Cu Cu2+ dummy Fe3+Ni2+ S- H* H(SDS) _definition ; A code to identify the atom species (singular or plural) occupying this site. This code must match a corresponding _atom_type_symbol. The specification of this code is optional if component 0 of the _atom_site_label is used for this purpose. See _atom_type_symbol. ; data_atom_site_U_equiv_geom_mean _name '_atom_site_U_equiv_geom_mean' _category atom_site _type numb _type_conditions esd _list yes _list_reference '_atom_site_label' _enumeration_range 0.0: loop_ _related_item _related_function '_atom_site_U_iso_or_equiv' alternate '_atom_site_B_equiv_geom_mean' conversion _units A^2^ _units_detail 'angstroms squared' _definition ; Equivalent isotropic atomic displacement parameter, U(equiv), in angstroms squared, calculated as the geometric mean of the anisotropic atomic displacement parameters. U(equiv) = (U~i~ U~j~ U~k~)^1/3^ U~n~ = the principal components of the orthogonalized U^ij^ ; data_atom_site_U_iso_or_equiv _name '_atom_site_U_iso_or_equiv' _category atom_site _type numb _type_conditions esd _list yes _list_reference '_atom_site_label' _enumeration_range 0.0: loop_ _related_item _related_function '_atom_site_U_equiv_geom_mean' alternate '_atom_site_B_iso_or_equiv' conversion _units A^2^ _units_detail 'angstroms squared' _definition ; Isotropic atomic displacement parameter, or equivalent isotropic atomic displacement parameter, U(equiv), in angstroms squared, calculated from anisotropic atomic displacement parameters. U(equiv) = (1/3) sum~i~[sum~j~(U^ij^ a*~i~ a*~j~ a~i~ a~j~)] a = the real-space cell lengths a* = the reciprocal-space cell lengths Ref: Fischer, R. X. & Tillmanns, E. (1988). Acta Cryst. C44, 775-776. ; data_atom_site_Wyckoff_symbol _name '_atom_site_Wyckoff_symbol' _category atom_site _type char _list yes _list_reference '_atom_site_label' _definition ; The Wyckoff symbol (letter) as listed in the space-group tables of International Tables for Crystallography Vol. A (2002). ; ################ ## ATOM_SITES ## ################ data_atom_sites_[] _name '_atom_sites_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _atom_sites_Cartn_transform_axes 'c along z, astar along x, b along y' _atom_sites_Cartn_tran_matrix_11 58.39 _atom_sites_Cartn_tran_matrix_12 0.00 _atom_sites_Cartn_tran_matrix_13 0.00 _atom_sites_Cartn_tran_matrix_21 0.00 _atom_sites_Cartn_tran_matrix_22 86.70 _atom_sites_Cartn_tran_matrix_23 0.00 _atom_sites_Cartn_tran_matrix_31 0.00 _atom_sites_Cartn_tran_matrix_32 0.00 _atom_sites_Cartn_tran_matrix_33 46.27 ; ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the ATOM_SITES category record details about the crystallographic cell and cell transformations, which are common to all atom sites. ; data_atom_sites_Cartn_tran_matrix_ loop_ _name '_atom_sites_Cartn_tran_matrix_11' '_atom_sites_Cartn_tran_matrix_12' '_atom_sites_Cartn_tran_matrix_13' '_atom_sites_Cartn_tran_matrix_21' '_atom_sites_Cartn_tran_matrix_22' '_atom_sites_Cartn_tran_matrix_23' '_atom_sites_Cartn_tran_matrix_31' '_atom_sites_Cartn_tran_matrix_32' '_atom_sites_Cartn_tran_matrix_33' _category atom_sites _type numb _definition ; Matrix elements used to transform fractional coordinates in the ATOM_SITE category to Cartesian coordinates. The axial alignments of this transformation are described in _atom_sites_Cartn_transform_axes. The 3 x 1 translation is defined in _atom_sites_Cartn_tran_vector_. x' |11 12 13| x | 1 | ( y' ) Cartesian = |21 22 23| ( y ) fractional + | 2 | z' |31 32 33| z | 3 | ; data_atom_sites_Cartn_transform_axes _name '_atom_sites_Cartn_transform_axes' _category atom_sites _type char _example 'a parallel to x; b in the plane of y and z' _definition ; A description of the relative alignment of the crystal cell axes to the Cartesian orthogonal axes as applied in the transformation matrix _atom_sites_Cartn_tran_matrix_. ; data_atom_sites_Cartn_tran_vector_ loop_ _name '_atom_sites_Cartn_tran_vector_1' '_atom_sites_Cartn_tran_vector_2' '_atom_sites_Cartn_tran_vector_3' _category atom_sites _type numb _definition ; Elements of a 3 x 1 translation vector used in the transformation of fractional coordinates in the ATOM_SITE category to Cartesian coordinates. The axial alignments of this transformation are described in _atom_sites_Cartn_transform_axes. x' |11 12 13| x | 1 | ( y' ) Cartesian = |21 22 23| ( y ) fractional + | 2 | z' |31 32 33| z | 3 | ; data_atom_sites_fract_tran_matrix_ loop_ _name '_atom_sites_fract_tran_matrix_11' '_atom_sites_fract_tran_matrix_12' '_atom_sites_fract_tran_matrix_13' '_atom_sites_fract_tran_matrix_21' '_atom_sites_fract_tran_matrix_22' '_atom_sites_fract_tran_matrix_23' '_atom_sites_fract_tran_matrix_31' '_atom_sites_fract_tran_matrix_32' '_atom_sites_fract_tran_matrix_33' _category atom_sites _type numb _definition ; Matrix elements used to transform Cartesian coordinates in the ATOM_SITE category to fractional coordinates. The axial alignments of this transformation are described in _atom_sites_Cartn_transform_axes. The 3 x 1 translation is defined in _atom_sites_fract_tran_vector_. x' |11 12 13| x | 1 | ( y' ) fractional = |21 22 23| ( y ) Cartesian + | 2 | z' |31 32 33| z | 3 | ; data_atom_sites_fract_tran_vector_ loop_ _name '_atom_sites_fract_tran_vector_1' '_atom_sites_fract_tran_vector_2' '_atom_sites_fract_tran_vector_3' _category atom_sites _type numb _definition ; Elements of a 3 x 1 translation vector used in the transformation of Cartesian coordinates in the ATOM_SITE category to fractional coordinates. The axial alignments of this transformation are described in _atom_sites_Cartn_transform_axes. x' |11 12 13| x | 1 | ( y' ) fractional = |21 22 23| ( y ) Cartesian + | 2 | z' |31 32 33| z | 3 | ; data_atom_sites_solution_ loop_ _name '_atom_sites_solution_primary' '_atom_sites_solution_secondary' '_atom_sites_solution_hydrogens' _category atom_sites _type char loop_ _enumeration _enumeration_detail difmap 'difference Fourier map' vecmap 'real-space vector search' heavy 'heavy-atom method' direct 'structure-invariant direct methods' geom 'inferred from neighbouring sites' disper 'anomalous-dispersion techniques' isomor 'isomorphous structure methods' _definition ; Codes which identify the methods used to locate the initial atom sites. The *_primary code identifies how the first atom sites were determined; the *_secondary code identifies how the remaining non-hydrogen sites were located; and the *_hydrogens code identifies how the hydrogen sites were located. ; data_atom_sites_special_details _name '_atom_sites_special_details' _category atom_sites _type char _definition ; Additional information about the atomic coordinates not coded elsewhere in the CIF. ; ############### ## ATOM_TYPE ## ############### data_atom_type_[] _name '_atom_type_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _atom_type_symbol _atom_type_oxidation_number _atom_type_number_in_cell _atom_type_scat_dispersion_real _atom_type_scat_dispersion_imag _atom_type_scat_source C 0 72 .017 .009 International_Tables_Vol_IV_Table_2.2B H 0 100 0 0 International_Tables_Vol_IV_Table_2.2B O 0 12 .047 .032 International_Tables_Vol_IV_Table_2.2B N 0 4 .029 .018 International_Tables_Vol_IV_Table_2.2B ; ; Example 1 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the ATOM_TYPE category record details about properties of the atoms that occupy the atom sites, such as the atomic scattering factors. ; data_atom_type_analytical_mass_% _name '_atom_type_analytical_mass_%' _category atom_type _type numb _list yes _list_reference '_atom_type_symbol' _enumeration_range 0.0:100.0 _definition ; Mass percentage of this atom type derived from chemical analysis. ; data_atom_type_description _name '_atom_type_description' _category atom_type _type char _list yes _list_reference '_atom_type_symbol' loop_ _example deuterium 0.34Fe+0.66Ni _definition ; A description of the atom(s) designated by this atom type. In most cases, this will be the element name and oxidation state of a single atom species. For disordered or nonstoichiometric structures it will describe a combination of atom species. ; data_atom_type_number_in_cell _name '_atom_type_number_in_cell' _category atom_type _type numb _list yes _list_reference '_atom_type_symbol' _enumeration_range 0: _definition ; Total number of atoms of this atom type in the unit cell. ; data_atom_type_oxidation_number _name '_atom_type_oxidation_number' _category atom_type _type numb _list yes _list_reference '_atom_type_symbol' _enumeration_range -8:8 _enumeration_default 0 _definition ; Formal oxidation state of this atom type in the structure. ; data_atom_type_radius_ loop_ _name '_atom_type_radius_bond' '_atom_type_radius_contact' _category atom_type _type numb _list yes _list_reference '_atom_type_symbol' _enumeration_range 0.0:5.0 _units A _units_detail 'angstroms' _definition ; The effective intra- and intermolecular bonding radii in angstroms of this atom type. ; data_atom_type_scat_Cromer_Mann_ loop_ _name '_atom_type_scat_Cromer_Mann_a1' '_atom_type_scat_Cromer_Mann_a2' '_atom_type_scat_Cromer_Mann_a3' '_atom_type_scat_Cromer_Mann_a4' '_atom_type_scat_Cromer_Mann_b1' '_atom_type_scat_Cromer_Mann_b2' '_atom_type_scat_Cromer_Mann_b3' '_atom_type_scat_Cromer_Mann_b4' '_atom_type_scat_Cromer_Mann_c' _category atom_type _type numb _list yes _list_reference '_atom_type_symbol' _definition ; The Cromer-Mann scattering-factor coefficients used to calculate the scattering factors for this atom type. Ref: International Tables for X-ray Crystallography (1974). Vol. IV, Table 2.2B or International Tables for Crystallography (2004). Vol. C, Tables 6.1.1.4 and 6.1.1.5 ; data_atom_type_scat_dispersion_ loop_ _name '_atom_type_scat_dispersion_imag' '_atom_type_scat_dispersion_real' _category atom_type _type numb _list yes _list_reference '_atom_type_symbol' _enumeration_default 0.0 _definition ; The imaginary and real components of the anomalous-dispersion scattering factor, f'' and f', in electrons for this atom type and the radiation given in _diffrn_radiation_wavelength. ; data_atom_type_scat_dispersion_source _name '_atom_type_scat_dispersion_source' _category atom_type _type char _list yes _list_reference '_atom_type_symbol' _example 'International Tables Vol. IV Table 2.3.1' _definition ; Reference to source of real and imaginary dispersion corrections for scattering factors used for this atom type. ; data_atom_type_scat_length_neutron _name '_atom_type_scat_length_neutron' _category atom_type _type numb _list yes _list_reference '_atom_type_symbol' _enumeration_default 0.0 _units fm _units_detail 'femtometres' _definition ; The bound coherent scattering length in femtometres for the atom type at the isotopic composition used for the diffraction experiment. ; data_atom_type_scat_source _name '_atom_type_scat_source' _category atom_type _type char _list yes _list_reference '_atom_type_symbol' _example 'International Tables Vol. IV Table 2.4.6B' _definition ; Reference to source of scattering factors or scattering lengths used for this atom type. ; data_atom_type_scat_versus_stol_list _name '_atom_type_scat_versus_stol_list' _category atom_type _type char _list yes _list_reference '_atom_type_symbol' _definition ; A table of scattering factors as a function of sin theta over lambda. This table should be well commented to indicate the items present. Regularly formatted lists are strongly recommended. ; data_atom_type_symbol _name '_atom_type_symbol' _category atom_type _type char _list yes _list_mandatory yes _list_link_child '_atom_site_type_symbol' loop_ _example C Cu2+ H(SDS) dummy FeNi _definition ; The code used to identify the atom species (singular or plural) representing this atom type. Normally this code is the element symbol. The code may be composed of any character except an underscore with the additional proviso that digits designate an oxidation state and must be followed by a + or - character. ; ########### ## AUDIT ## ########### data_audit_[] _name '_audit_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _audit_block_code TOZ_1991-03-20 _audit_creation_date 1991-03-20 _audit_creation_method from_xtal_archive_file_using_CIFIO _audit_update_record ; 1991-04-09 text and data added by Tony Willis. 1991-04-15 rec'd by co-editor as manuscript HL0007. 1991-04-17 adjustments based on first referee report. 1991-04-18 adjustments based on second referee report. ; ; ; Example 1 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the AUDIT category record details about the creation and subsequent updating of the data block. ; data_audit_block_code _name '_audit_block_code' _category audit _type char _example TOZ_1991-03-20 _definition ; A code intended to identify uniquely the current data block. ; data_audit_creation_date _name '_audit_creation_date' _category audit _type char _example 1990-07-12 _definition ; The date that the data block was created. The date format is yyyy-mm-dd. ; data_audit_creation_method _name '_audit_creation_method' _category audit _type char _example 'spawned by the program QBEE' _definition ; A description of how data were entered into the data block. ; data_audit_update_record _name '_audit_update_record' _category audit _type char _example '1990-07-15 Updated by the Co-editor' _definition ; A record of any changes to the data block. The update format is a date (yyyy-mm-dd) followed by a description of the changes. The latest update entry is added to the bottom of this record. ; ################## ## AUDIT_AUTHOR ## ################## data_audit_author_[] _name '_audit_author_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _audit_author_name _audit_author_address 'Fitzgerald, Paula M. D.' ; Department of Biophysical Chemistry Merck Research Laboratories PO Box 2000, Ry80M203 Rahway New Jersey 07065 USA ; 'Van Middlesworth, J. F.' ; Department of Biophysical Chemistry Merck Research Laboratories PO Box 2000, Ry80M203 Rahway New Jersey 07065 USA ; ; ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the AUDIT_AUTHOR category record details about the author(s) of the data block. ; data_audit_author_address _name '_audit_author_address' _category audit_author _type char _list yes _list_reference '_audit_author_name' _example ; Department Institute Street City and postcode COUNTRY ; _definition ; The address of an author of this data block. If there are multiple authors, _audit_author_address is looped with _audit_author_name. ; data_audit_author_name _name '_audit_author_name' _category audit_author _type char _list yes _list_mandatory yes loop_ _example 'Bleary, Percival R.' "O'Neil, F.K." 'Van den Bossche, G.' 'Yang, D.-L.' 'Simonov, Yu.A.' 'M\"uller, H.A.' 'Ross II, C.R.' _definition ; The name of an author of this data block. If there are multiple authors, _audit_author_name is looped with _audit_author_address. The family name(s), followed by a comma and including any dynastic components, precedes the first name(s) or initial(s). ; ################### ## AUDIT_CONFORM ## ################### data_audit_conform_[] _name '_audit_conform_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _audit_conform_dict_name cif_core.dic _audit_conform_dict_version 2.3.1 _audit_conform_dict_location ftp://ftp.iucr.org/pub/cif_core.2.3.1.dic ; ; Example 1 - any file conforming to the current CIF core dictionary. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the AUDIT_CONFORM category describe the dictionary versions against which the data names appearing in the current data block are conformant. ; data_audit_conform_dict_location _name '_audit_conform_dict_location' _category audit_conform _type char _list both _list_reference '_audit_conform_dict_name' _definition ; A file name or uniform resource locator (URL) for the dictionary to which the current data block conforms. ; data_audit_conform_dict_name _name '_audit_conform_dict_name' _category audit_conform _type char _list both _list_mandatory yes _definition ; The string identifying the highest-level dictionary defining data names used in this file. ; data_audit_conform_dict_version _name '_audit_conform_dict_version' _category audit_conform _type char _list both _list_reference '_audit_conform_dict_name' _definition ; The version number of the dictionary to which the current data block conforms. ; ########################## ## AUDIT_CONTACT_AUTHOR ## ########################## data_audit_contact_author_[] _name '_audit_contact_author_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _audit_contact_author_name _audit_contact_author_address _audit_contact_author_email _audit_contact_author_fax _audit_contact_author_phone 'Fitzgerald, Paula M. D.' ; Department of Biophysical Chemistry Merck Research Laboratories PO Box 2000, Ry80M203 Rahway New Jersey 07065 USA ; 'paula_fitzgerald@merck.com' '1(908)5945510' '1(908)5945510' ; ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the AUDIT_CONTACT_AUTHOR category record details about the name and address of the author to be contacted concerning the contents of this data block. ; data_audit_contact_author_address _name '_audit_contact_author_address' _category audit_contact_author _type char _example ; Department Institute Street City and postcode COUNTRY ; _definition ; The mailing address of the author of the data block to whom correspondence should be addressed. ; data_audit_contact_author_email _name '_audit_contact_author_email' _category audit_contact_author _type char loop_ _example name@host.domain.country bm@iucr.org _definition ; The electronic mail address of the author of the data block to whom correspondence should be addressed, in a form recognizable to international networks. The format of e-mail addresses is given in Section 3.4, Address Specification, of Internet Message Format, RFC 2822, P. Resnick (Editor), Network Standards Group, April 2001. ; data_audit_contact_author_fax _name '_audit_contact_author_fax' _category audit_contact_author _type char loop_ _example '12(34)9477334' '12()349477334' _definition ; The facsimile telephone number of the author of the data block to whom correspondence should be addressed. The recommended style starts with the international dialing prefix, followed by the area code in parentheses, followed by the local number with no spaces. ; data_audit_contact_author_name _name '_audit_contact_author_name' _category audit_contact_author _type char loop_ _example 'Bleary, Percival R.' "O'Neil, F.K." 'Van den Bossche, G.' 'Yang, D.-L.' 'Simonov, Yu.A.' 'M\"uller, H.A.' 'Ross II, C.R.' _definition ; The name of the author of the data block to whom correspondence should be addressed. The family name(s), followed by a comma and including any dynastic components, precedes the first name(s) or initial(s). ; data_audit_contact_author_phone _name '_audit_contact_author_phone' _category audit_contact_author _type char loop_ _example '12(34)9477330' '12()349477330' '12(34)9477330x5543' _definition ; The telephone number of the author of the data block to whom correspondence should be addressed. The recommended style starts with the international dialing prefix, followed by the area code in parentheses, followed by the local number and any extension number prefixed by 'x', with no spaces. ; ################ ## AUDIT_LINK ## ################ data_audit_link_[] _name '_audit_link_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _audit_link_block_code _audit_link_block_description . 'discursive text of paper with two structures' morA_(1) 'structure 1 of 2' morA_(2) 'structure 2 of 2' ; ; Example 1 - multiple structure paper, as illustrated in A Guide to CIF for Authors (1995). IUCr: Chester. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _audit_link_block_code _audit_link_block_description . 'publication details' KSE_COM 'experimental data common to ref./mod. structures' KSE_REF 'reference structure' KSE_MOD 'modulated structure' ; ; Example 2 - example file for the one-dimensional incommensurately modulated structure of K~2~SeO~4~. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the AUDIT_LINK category record details about the relationships between data blocks in the current CIF. ; data_audit_link_block_code _name '_audit_link_block_code' _category audit_link _type char _list yes _list_mandatory yes _definition ; The value of _audit_block_code associated with a data block in the current file related to the current data block. The special value '.' may be used to refer to the current data block for completeness. ; data_audit_link_block_description _name '_audit_link_block_description' _category audit_link _type char _list yes _list_reference '_audit_link_block_code' _definition ; A textual description of the relationship of the referenced data block to the current one. ; ########## ## CELL ## ########## data_cell_[] _name '_cell_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _cell_length_a 5.959(1) _cell_length_b 14.956(1) _cell_length_c 19.737(3) _cell_angle_alpha 90 _cell_angle_beta 90 _cell_angle_gamma 90 _cell_volume 1759.0(3) _cell_measurement_temperature 293 _cell_measurement_reflns_used 25 _cell_measurement_theta_min 25 _cell_measurement_theta_max 31 ; ; Example 1 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the CELL category record details about the crystallographic cell parameters and their measurement. ; data_cell_angle_ loop_ _name '_cell_angle_alpha' '_cell_angle_beta' '_cell_angle_gamma' _category cell _type numb _type_conditions esd _enumeration_range 0.0:180.0 _enumeration_default 90.0 _units deg _units_detail 'degrees' _definition ; Unit-cell angles of the reported structure in degrees. The values of _refln_index_h, *_k, *_l must correspond to the cell defined by these values and _cell_length_a, *_b and *_c. The values of _diffrn_refln_index_h, *_k, *_l may not correspond to these values if a cell transformation took place following the measurement of the diffraction intensities. See also _diffrn_reflns_transf_matrix_. ; data_cell_formula_units_Z _name '_cell_formula_units_Z' _category cell _type numb _enumeration_range 1: _definition ; The number of the formula units in the unit cell as specified by _chemical_formula_structural, _chemical_formula_moiety or _chemical_formula_sum. ; data_cell_length_ loop_ _name '_cell_length_a' '_cell_length_b' '_cell_length_c' _category cell _type numb _type_conditions esd _enumeration_range 0.0: _units A _units_detail 'angstroms' _definition ; Unit-cell lengths in angstroms corresponding to the structure reported. The values of _refln_index_h, *_k, *_l must correspond to the cell defined by these values and _cell_angle_ values. The values of _diffrn_refln_index_h, *_k, *_l may not correspond to these values if a cell transformation took place following the measurement of the diffraction intensities. See also _diffrn_reflns_transf_matrix_. ; data_cell_measurement_pressure _name '_cell_measurement_pressure' _category cell _type numb _type_conditions esd _enumeration_range 0.0: _units kPa _units_detail 'kilopascals' _definition ; The pressure in kilopascals at which the unit-cell parameters were measured (not the pressure at which the sample was synthesized). ; data_cell_measurement_radiation _name '_cell_measurement_radiation' _category cell _type char loop_ _example 'neutron' 'Cu K\a' 'synchrotron' _definition ; Description of the radiation used to measure the unit-cell data. See also _cell_measurement_wavelength. ; data_cell_measurement_reflns_used _name '_cell_measurement_reflns_used' _category cell _type numb _definition ; The total number of reflections used to determine the unit cell. These reflections may be specified as _cell_measurement_refln_ data items. ; data_cell_measurement_temperature _name '_cell_measurement_temperature' _category cell _type numb _type_conditions esd _enumeration_range 0.0: _units K _units_detail kelvin _definition ; The temperature in kelvins at which the unit-cell parameters were measured (not the temperature of synthesis). ; data_cell_measurement_theta_ loop_ _name '_cell_measurement_theta_max' '_cell_measurement_theta_min' _category cell _type numb _enumeration_range 0.0:90.0 _units deg _units_detail 'degrees' _definition ; The maximum and minimum theta angles of reflections used to measure the unit cell in degrees. ; data_cell_measurement_wavelength _name '_cell_measurement_wavelength' _category cell _type numb _enumeration_range 0.0: _units A _units_detail 'angstroms' _definition ; The wavelength in angstroms of the radiation used to measure the unit cell. If this is not specified, the wavelength is assumed to be the same as that given in _diffrn_radiation_wavelength. ; data_cell_reciprocal_angle_ loop_ _name '_cell_reciprocal_angle_alpha' '_cell_reciprocal_angle_beta' '_cell_reciprocal_angle_gamma' _category cell _type numb _type_conditions esd _enumeration_range 0.0:180.0 _enumeration_default 90.0 _units deg _units_detail 'degrees' _definition ; The angles defining the reciprocal cell in degrees. These are related to those in the real cell by: cos(recip-alpha) = [cos(beta)*cos(gamma) - cos(alpha)]/[sin(beta)*sin(gamma)] cos(recip-beta) = [cos(gamma)*cos(alpha) - cos(beta)]/[sin(gamma)*sin(alpha)] cos(recip-gamma) = [cos(alpha)*cos(beta) - cos(gamma)]/[sin(alpha)*sin(beta)] Ref: Buerger, M. J. (1942). X-ray Crystallography, p. 360. New York: John Wiley & Sons Inc. ; data_cell_reciprocal_length_ loop_ _name '_cell_reciprocal_length_a' '_cell_reciprocal_length_b' '_cell_reciprocal_length_c' _category cell _type numb _type_conditions esd _enumeration_range 0.0: _units A^-1^ _units_detail 'reciprocal angstroms' _definition ; The reciprocal-cell lengths in inverse angstroms. These are related to the real cell by: recip-a = b*c*sin(alpha)/V recip-b = c*a*sin(beta)/V recip-c = a*b*sin(gamma)/V where V is the cell volume. Ref: Buerger, M. J. (1942). X-ray Crystallography, p. 360. New York: John Wiley & Sons Inc. ; data_cell_special_details _name '_cell_special_details' _category cell _type char loop_ _example 'pseudo-orthorhombic' 'standard setting from 45 deg rotation around c' _definition ; A description of special aspects of the cell choice, noting possible alternative settings. ; data_cell_volume _name '_cell_volume' _category cell _type numb _type_conditions esd _enumeration_range 0.0: _units A^3^ _units_detail 'cubic angstroms' _definition ; Cell volume V in angstroms cubed. V = a b c [1 - cos^2^(alpha) - cos^2^(beta) - cos^2^(gamma) + 2 cos(alpha) cos(beta) cos(gamma) ] ^1/2^ a = _cell_length_a b = _cell_length_b c = _cell_length_c alpha = _cell_angle_alpha beta = _cell_angle_beta gamma = _cell_angle_gamma ; ############################ ## CELL_MEASUREMENT_REFLN ## ############################ data_cell_measurement_refln_[] _name '_cell_measurement_refln_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _cell_measurement_refln_index_h _cell_measurement_refln_index_k _cell_measurement_refln_index_l _cell_measurement_refln_theta -2 4 1 8.67 0 3 2 9.45 3 0 2 9.46 -3 4 1 8.93 -2 1 -2 7.53 10 0 0 23.77 0 10 0 23.78 -5 4 1 11.14 # - - - - data truncated for brevity - - - - ; ; Example 1 - extracted from the CAD-4 listing for Rb~2~S~2~O~6~ at room temperature (unpublished). ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the CELL_MEASUREMENT_REFLN category record details about the reflections used in the determination of the crystallographic cell parameters. The _cell_measurement_refln_ data items would in general be used only for diffractometer measurements. ; data_cell_measurement_refln_index_ loop_ _name '_cell_measurement_refln_index_h' '_cell_measurement_refln_index_k' '_cell_measurement_refln_index_l' _category cell_measurement_refln _type numb _list yes _list_mandatory yes _definition ; Miller indices of a reflection used for measurement of the unit cell. ; data_cell_measurement_refln_theta _name '_cell_measurement_refln_theta' _category cell_measurement_refln _type numb _list yes _list_reference '_cell_measurement_refln_index_' _enumeration_range 0.0:90.0 _units deg _units_detail 'degrees' _definition ; Theta angle in degrees for the reflection used for measurement of the unit cell with the indices _cell_measurement_refln_index_. ; ############## ## CHEMICAL ## ############## data_chemical_[] _name '_chemical_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _chemical_name_systematic trans-bis(tricyclohexylphosphine)tetracarbonylmolybdenum(0) ; ; Example 1 - based on data set 9597gaus of Alyea, Ferguson & Kannan [Acta Cryst. (1996), C52, 765-767]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the CHEMICAL category record details about the composition and chemical properties of the compound. The formula data items must agree with those that specify the density, unit-cell and Z values. ; data_chemical_absolute_configuration _name '_chemical_absolute_configuration' _category chemical _type char loop_ _enumeration _enumeration_detail rm ; absolute configuration established by the structure determination of a compound containing a chiral reference molecule of known absolute configuration ; ad ; absolute configuration established by anomalous-dispersion effects in diffraction measurements on the crystal ; rmad ; absolute configuration established by the structure determination of a compound containing a chiral reference molecule of known absolute configuration and confirmed by anomalous-dispersion effects in diffraction measurements on the crystal ; syn ; absolute configuration has not been established by anomalous-dispersion effects in diffraction measurements on the crystal. The enantiomer has been assigned by reference to an unchanging chiral centre in the synthetic procedure ; unk ; absolute configuration is unknown, there being no firm chemical evidence for its assignment to hand and it having not been established by anomalous-dispersion effects in diffraction measurements on the crystal. An arbitrary choice of enantiomer has been made ; . 'inapplicable' _definition ; Necessary conditions for the assignment of _chemical_absolute_configuration are given by H. D. Flack and G. Bernardinelli (1999, 2000). Ref: Flack, H. D. & Bernardinelli, G. (1999). Acta Cryst. A55, 908-915. (http://www.iucr.org/paper?sh0129) Flack, H. D. & Bernardinelli, G. (2000). J. Appl. Cryst. 33, 1143-1148. (http://www.iucr.org/paper?ks0021) ; data_chemical_compound_source _name '_chemical_compound_source' _category chemical _type char loop_ _example 'From Norilsk (USSR)' 'Extracted from the bark of Cinchona Naturalis' _definition ; Description of the source of the compound under study, or of the parent molecule if a simple derivative is studied. This includes the place of discovery for minerals or the actual source of a natural product. ; data_chemical_melting_point _name '_chemical_melting_point' _category chemical _type numb _type_conditions esd _enumeration_range 0.0: _units K _units_detail kelvin _definition ; The temperature in kelvins at which the crystalline solid changes to a liquid. ; data_chemical_melting_point_ loop_ _name '_chemical_melting_point_gt' '_chemical_melting_point_lt' _category chemical _type numb _related_item '_chemical_melting_point' _related_function alternate _enumeration_range 0.0: _units K _units_detail kelvin _definition ; A temperature in kelvins below which (*_lt) or above which (*_gt) the melting point (the temperature at which the crystalline solid changes to a liquid) lies. These items allow a range of temperatures to be given. _chemical_melting_point should always be used in preference to these items whenever possible. ; data_chemical_name_common _name '_chemical_name_common' _category chemical _type char _example '1-bromoestradiol' _definition ; Trivial name by which the compound is commonly known. ; data_chemical_name_mineral _name '_chemical_name_mineral' _category chemical _type char _example chalcopyrite _definition ; Mineral name accepted by the International Mineralogical Association. Use only for natural minerals. See also _chemical_compound_source. ; data_chemical_name_structure_type _name '_chemical_name_structure_type' _category chemical _type char loop_ _example perovskite sphalerite A15 _definition ; Commonly used structure-type name. Usually only applied to minerals or inorganic compounds. ; data_chemical_name_systematic _name '_chemical_name_systematic' _category chemical _type char _example '1-bromoestra-1,3,5(10)-triene-3,17\b-diol' _definition ; IUPAC or Chemical Abstracts full name of the compound. ; data_chemical_optical_rotation _name '_chemical_optical_rotation' _category chemical _type char _example '[\a]^25^~D~ = +108 (c = 3.42, CHCl~3~)' _definition ; The optical rotation in solution of the compound is specified in the following format: '[\a]^TEMP^~WAVE~ = SORT (c = CONC, SOLV)' where: TEMP is the temperature of the measurement in degrees Celsius, WAVE is an indication of the wavelength of the light used for the measurement, CONC is the concentration of the solution given as the mass of the substance in g per 100 ml of solution, SORT is the signed value (preceded by a + or a - sign) of 100.\a/(l.c), where \a is the signed optical rotation in degrees measured in a cell of length l in dm and c is the value of CONC as defined above, and SOLV is the chemical formula of the solvent. ; data_chemical_properties_biological _name '_chemical_properties_biological' _category chemical _type char loop_ _example ; diverse biological activities including use as a laxative and strong antibacterial activity against S. aureus and weak activity against cyclooxygenase-1 (COX-1) ; ; antibiotic activity against Bacillus subtilis (ATCC 6051) but no significant activity against Candida albicans (ATCC 14053), Aspergillus flavus (NRRL 6541) and Fusarium verticillioides (NRRL 25457) ; ; weakly potent lipoxygenase nonredox inhibitor ; ; no influenza A virus sialidase inhibitory and plaque reduction activities ; ; low toxicity against Drosophila melanogaster ; _definition ; A free-text description of the biological properties of the material. ; data_chemical_properties_physical _name '_chemical_properties_physical' _category chemical _type char loop_ _example air-sensitive moisture-sensitive hygroscopic deliquescent oxygen-sensitive photo-sensitive pyrophoric semiconductor 'ferromagnetic at low temperature' 'paramagnetic and thermochromic' _definition ; A free-text description of the physical properties of the material. ; data_chemical_temperature_decomposition _name '_chemical_temperature_decomposition' _category chemical _type numb _type_conditions esd _enumeration_range 0.0: _units K _units_detail kelvin _example 350 _definition ; The temperature in kelvins at which the solid decomposes. ; data_chemical_temperature_decomposition_ loop_ _name '_chemical_temperature_decomposition_gt' '_chemical_temperature_decomposition_lt' _category chemical _type numb _enumeration_range 0.0: _units K _units_detail kelvin _related_item '_chemical_temperature_decomposition' _related_function alternate _example 350 _definition ; A temperature in kelvins below which (*_lt) or above which (*_gt) the solid is known to decompose. These items allow a range of temperatures to be given. _chemical_temperature_decomposition should always be used in preference to these items whenever possible. ; data_chemical_temperature_sublimation _name '_chemical_temperature_sublimation' _category chemical _type numb _type_conditions esd _enumeration_range 0.0: _units K _units_detail kelvin _example 350 _definition ; The temperature in kelvins at which the solid sublimes. ; data_chemical_temperature_sublimation_ loop_ _name '_chemical_temperature_sublimation_gt' '_chemical_temperature_sublimation_lt' _category chemical _type numb _enumeration_range 0.0: _units K _units_detail kelvin _related_item '_chemical_temperature_sublimation' _related_function alternate _example 350 _definition ; A temperature in kelvins below which (*_lt) or above which (*_gt) the solid is known to sublime. These items allow a range of temperatures to be given. _chemical_temperature_sublimation should always be used in preference to these items whenever possible. ; ######################## ## CHEMICAL_CONN_ATOM ## ######################## data_chemical_conn_atom_[] _name '_chemical_conn_atom_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _chemical_conn_atom_number _chemical_conn_atom_type_symbol _chemical_conn_atom_display_x _chemical_conn_atom_display_y _chemical_conn_atom_NCA _chemical_conn_atom_NH 1 S .39 .81 1 0 2 S .39 .96 2 0 3 N .14 .88 3 0 4 C .33 .88 3 0 5 C .11 .96 2 2 6 C .03 .96 2 2 7 C .03 .80 2 2 8 C .11 .80 2 2 9 S .54 .81 1 0 10 S .54 .96 2 0 11 N .80 .88 3 0 12 C .60 .88 3 0 13 C .84 .96 2 2 14 C .91 .96 2 2 15 C .91 .80 2 2 16 C .84 .80 2 2 ; ; Example 1 - based on data set DPTD of Yamin, Suwandi, Fun, Sivakumar & bin Shawkataly [Acta Cryst. (1996), C52, 951-953]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the _chemical_conn_atom_ and _chemical_conn_bond_ categories record details about the two-dimensional (2D) chemical structure of the molecular species. They allow a 2D chemical diagram to be reconstructed for use in a publication or in a database search for structural and substructural relationships. The _chemical_conn_atom_ data items provide information about the chemical properties of the atoms in the structure. In cases where crystallographic and molecular symmetry elements coincide, they must also contain symmetry-generated atoms, so that the _chemical_conn_atom_ and _chemical_conn_bond_ data items will always describe a complete chemical entity. ; data_chemical_conn_atom_charge _name '_chemical_conn_atom_charge' _category chemical_conn_atom _type numb _list yes _list_reference '_chemical_conn_atom_type_symbol' _enumeration_range -6:6 _enumeration_default 0 loop_ _example _example_detail 1 'for an ammonium nitrogen' -1 'for a chloride ion' _definition ; The net integer charge assigned to this atom. This is the formal charge assignment normally found in chemical diagrams. ; data_chemical_conn_atom_display_ loop_ _name '_chemical_conn_atom_display_x' '_chemical_conn_atom_display_y' _category chemical_conn_atom _type numb _list yes _list_reference '_chemical_conn_atom_type_symbol' _enumeration_range 0.0:1.0 _definition ; The 2D Cartesian coordinates (x,y) of the position of this atom in a recognizable chemical diagram. The coordinate origin is at the lower left corner, the x axis is horizontal and the y axis is vertical. The coordinates must lie in the range 0.0 to 1.0. These coordinates can be obtained from projections of a suitable uncluttered view of the molecular structure. ; data_chemical_conn_atom_NCA _name '_chemical_conn_atom_NCA' _category chemical_conn_atom _type numb _list yes _list_reference '_chemical_conn_atom_type_symbol' _enumeration_range 0: _definition ; The number of connected atoms excluding terminal hydrogen atoms. ; data_chemical_conn_atom_NH _name '_chemical_conn_atom_NH' _category chemical_conn_atom _type numb _list yes _list_reference '_chemical_conn_atom_type_symbol' _enumeration_range 0: _definition ; The total number of hydrogen atoms attached to this atom, regardless of whether they are included in the refinement or the _atom_site_ list. This number will be the same as _atom_site_attached_hydrogens only if none of the hydrogen atoms appear in the _atom_site_ list. ; data_chemical_conn_atom_number _name '_chemical_conn_atom_number' _category chemical_conn_atom _type numb _list yes loop_ _list_link_child '_atom_site_chemical_conn_number' '_chemical_conn_bond_atom_1' '_chemical_conn_bond_atom_2' _list_reference '_chemical_conn_atom_type_symbol' _enumeration_range 1: _definition ; The chemical sequence number to be associated with this atom. ; data_chemical_conn_atom_type_symbol _name '_chemical_conn_atom_type_symbol' _category chemical_conn_atom _type char _list yes _list_mandatory yes _definition ; A code identifying the atom type. This code must match an _atom_type_symbol code in the _atom_type_ list or be a recognizable element symbol. ; ######################## ## CHEMICAL_CONN_BOND ## ######################## data_chemical_conn_bond_[] _name '_chemical_conn_bond_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _chemical_conn_bond_atom_1 _chemical_conn_bond_atom_2 _chemical_conn_bond_type 4 1 doub 4 3 sing 4 2 sing 5 3 sing 6 5 sing 7 6 sing 8 7 sing 8 3 sing 10 2 sing 12 9 doub 12 11 sing 12 10 sing 13 11 sing 14 13 sing 15 14 sing 16 15 sing 16 11 sing 17 5 sing 18 5 sing 19 6 sing 20 6 sing 21 7 sing 22 7 sing 23 8 sing 24 8 sing 25 13 sing 26 13 sing 27 14 sing 28 14 sing 29 15 sing 30 15 sing 31 16 sing 32 16 sing ; ; Example 1 - based on data set DPTD of Yamin, Suwandi, Fun, Sivakumar & bin Shawkataly [Acta Cryst. (1996), C52, 951-953]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the _chemical_conn_atom_ and _chemical_conn_bond_ categories record details about the two-dimensional (2D) chemical structure of the molecular species. They allow a 2D chemical diagram to be reconstructed for use in a publication or in a database search for structural and substructural relationships. The _chemical_conn_bond_ data items specify the connections between the atoms in the _chemical_conn_atom_ list and the nature of the chemical bond between these atoms. ; data_chemical_conn_bond_atom_ loop_ _name '_chemical_conn_bond_atom_1' '_chemical_conn_bond_atom_2' _category chemical_conn_bond _type numb _list yes _list_link_parent '_chemical_conn_atom_number' _enumeration_range 1: _definition ; Atom numbers which must match with chemical sequence numbers specified as _chemical_conn_atom_number values. These link the bond connection to the chemical numbering and atom sites. ; data_chemical_conn_bond_type _name '_chemical_conn_bond_type' _category chemical_conn_bond _type char _list yes _list_reference '_chemical_conn_bond_atom_' loop_ _enumeration _enumeration_detail sing 'single bond' doub 'double bond' trip 'triple bond' quad 'quadruple bond' arom 'aromatic bond' poly 'polymeric bond' delo 'delocalized double bond' pi 'pi bond' _enumeration_default sing _definition ; The chemical bond type associated with the connection between the two sites _chemical_conn_bond_atom_1 and *_2. ; ###################### ## CHEMICAL_FORMULA ## ###################### data_chemical_formula_[] _name '_chemical_formula_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _chemical_formula_moiety 'C18 H25 N O3' _chemical_formula_sum 'C18 H25 N O3' _chemical_formula_weight 303.40 ; ; Example 1 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _chemical_formula_iupac '[Mo (C O)4 (C18 H33 P)2]' _chemical_formula_moiety 'C40 H66 Mo O4 P2' _chemical_formula_structural '((C O)4 (P (C6 H11)3)2)Mo' _chemical_formula_sum 'C40 H66 Mo O4 P2' _chemical_formula_weight 768.81 ; ; Example 2 - based on data set 9597gaus of Alyea, Ferguson & Kannan [Acta Cryst. (1996), C52, 765-767]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; _chemical_formula_ items specify the composition and chemical properties of the compound. The formula data items must agree with those that specify the density, unit-cell and Z values. The following rules apply to the construction of the data items _chemical_formula_analytical, *_structural and *_sum. For the data item *_moiety, the formula construction is broken up into residues or moieties, i.e. groups of atoms that form a molecular unit or molecular ion. The rules given below apply within each moiety but different requirements apply to the way that moieties are connected (see _chemical_formula_moiety). (1) Only recognized element symbols may be used. (2) Each element symbol is followed by a 'count' number. A count of '1' may be omitted. (3) A space or parenthesis must separate each cluster of (element symbol + count). (4) Where a group of elements is enclosed in parentheses, the multiplier for the group must follow the closing parenthesis. That is, all element and group multipliers are assumed to be printed as subscripted numbers. (An exception to this rule exists for *_moiety formulae where pre- and post-multipliers are permitted for molecular units.) (5) Unless the elements are ordered in a manner that corresponds to their chemical structure, as in _chemical_formula_structural, the order of the elements within any group or moiety depends on whether carbon is present or not. If carbon is present, the order should be: C, then H, then the other elements in alphabetical order of their symbol. If carbon is not present, the elements are listed purely in alphabetical order of their symbol. This is the 'Hill' system used by Chemical Abstracts. This ordering is used in _chemical_formula_moiety and _chemical_formula_sum. ; data_chemical_formula_analytical _name '_chemical_formula_analytical' _category chemical_formula _type char _example 'Fe2.45(2) Ni1.60(3) S4' _definition ; Formula determined by standard chemical analysis including trace elements. See the _chemical_formula_[] category description for rules for writing chemical formulae. Parentheses are used only for standard uncertainties (e.s.d.'s). ; data_chemical_formula_iupac _name '_chemical_formula_iupac' _category chemical_formula _type char _example '[Co Re (C12 H22 P)2 (C O)6].0.5C H3 O H' _definition ; Formula expressed in conformance with IUPAC rules for inorganic and metal-organic compounds where these conflict with the rules for any other _chemical_formula_ entries. Typically used for formatting a formula in accordance with journal rules. This should appear in the data block in addition to the most appropriate of the other _chemical_formula_ data names. Ref: IUPAC (1990). Nomenclature of Inorganic Chemistry. Oxford: Blackwell Scientific Publications. ; data_chemical_formula_moiety _name '_chemical_formula_moiety' _category chemical_formula _type char loop_ _example 'C7 H4 Cl Hg N O3 S' 'C12 H17 N4 O S 1+, C6 H2 N3 O7 1-' 'C12 H16 N2 O6, 5(H2 O1)' "(Cd 2+)3, (C6 N6 Cr 3-)2, 2(H2 O)" _definition ; Formula with each discrete bonded residue or ion shown as a separate moiety. See the _chemical_formula_[] category description for rules for writing chemical formulae. In addition to the general formulae requirements, the following rules apply: (1) Moieties are separated by commas ','. (2) The order of elements within a moiety follows general rule (5) in the _chemical_formula_[] category description. (3) Parentheses are not used within moieties but may surround a moiety. Parentheses may not be nested. (4) Charges should be placed at the end of the moiety. The charge '+' or '-' may be preceded by a numerical multiplier and should be separated from the last (element symbol + count) by a space. Pre- or post-multipliers may be used for individual moieties. ; data_chemical_formula_structural _name '_chemical_formula_structural' _category chemical_formula _type char loop_ _example 'Ca ((Cl O3)2 O)2 (H2 O)6' '(Pt (N H3)2 (C5 H7 N3 O)2) (Cl O4)2' _definition ; See the _chemical_formula_[] category description for the rules for writing chemical formulae for inorganics, organometallics, metal complexes etc., in which bonded groups are preserved as discrete entities within parentheses, with post-multipliers as required. The order of the elements should give as much information as possible about the chemical structure. Parentheses may be used and nested as required. This formula should correspond to the structure as actually reported, i.e. trace elements not included in atom-type and atom-site lists should not be included in this formula (see also _chemical_formula_analytical). ; data_chemical_formula_sum _name '_chemical_formula_sum' _category chemical_formula _type char loop_ _example 'C18 H19 N7 O8 S' _definition ; See the _chemical_formula_[] category description for the rules for writing chemical formulae in which all discrete bonded residues and ions are summed over the constituent elements, following the ordering given in general rule (5) in the _chemical_formula_[] category description. Parentheses are not normally used. ; data_chemical_formula_weight _name '_chemical_formula_weight' _category chemical_formula _type numb _enumeration_range 1.0: _units Da _units_detail 'daltons' _definition ; Formula mass in daltons. This mass should correspond to the formulae given under _chemical_formula_structural, *_iupac, *_moiety or *_sum and, together with the Z value and cell parameters, should yield the density given as _exptl_crystal_density_diffrn. ; data_chemical_formula_weight_meas _name '_chemical_formula_weight_meas' _category chemical_formula _type numb _enumeration_range 1.0: _units Da _units_detail 'daltons' _definition ; Formula mass in daltons measured by a non-diffraction experiment. ; ############## ## CITATION ## ############## data_citation_[] _name '_citation_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _citation_id _citation_coordinate_linkage _citation_title _citation_country _citation_page_first _citation_page_last _citation_year _citation_journal_abbrev _citation_journal_volume _citation_journal_issue _citation_journal_id_ASTM _citation_journal_id_ISSN _citation_book_title _citation_book_publisher _citation_book_id_ISBN _citation_special_details primary yes ; Crystallographic analysis of a complex between human immunodeficiency virus type 1 protease and acetyl-pepstatin at 2.0-Angstroms resolution. ; US 14209 14219 1990 'J. Biol. Chem.' 265 . HBCHA3 0021-9258 . . . ; The publication that directly relates to this coordinate set. ; 2 no ; Three-dimensional structure of aspartyl-protease from human immunodeficiency virus HIV-1. ; UK 615 619 1989 'Nature' 337 . NATUAS 0028-0836 . . . ; Determination of the structure of the unliganded enzyme. ; 3 no ; Crystallization of the aspartylprotease from human immunodeficiency virus, HIV-1. ; US 1919 1921 1989 'J. Biol. Chem.' 264 . HBCHA3 0021-9258 . . . ; Crystallization of the unliganded enzyme. ; ; ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the CITATION category record details about the literature cited as being relevant to the contents of the data block. ; data_citation_abstract _name '_citation_abstract' _category citation _type char _list yes _list_reference '_citation_id' _definition ; Abstract for the citation. This is used most when the citation is extracted from a bibliographic database that contains full text or abstract information. ; data_citation_abstract_id_CAS _name '_citation_abstract_id_CAS' _category citation _type char _list yes _list_reference '_citation_id' _definition ; The Chemical Abstracts Service (CAS) abstract identifier; relevant for journal articles. ; data_citation_book_id_ISBN _name '_citation_book_id_ISBN' _category citation _type char _list yes _list_reference '_citation_id' _definition ; The International Standard Book Number (ISBN) code assigned to the book cited; relevant for books or book chapters. ; data_citation_book_publisher _name '_citation_book_publisher' _category citation _type char _list yes _list_reference '_citation_id' _example 'John Wiley' _definition ; The name of the publisher of the citation; relevant for books or book chapters. ; data_citation_book_publisher_city _name '_citation_book_publisher_city' _category citation _type char _list yes _list_reference '_citation_id' _example 'New York' _definition ; The location of the publisher of the citation; relevant for books or book chapters. ; data_citation_book_title _name '_citation_book_title' _category citation _type char _list yes _list_reference '_citation_id' _definition ; The title of the book in which the citation appeared; relevant for books or book chapters. ; data_citation_coordinate_linkage _name '_citation_coordinate_linkage' _category citation _type char _list yes _list_reference '_citation_id' loop_ _enumeration _enumeration_detail no 'citation unrelated to current coordinates' n 'abbreviation for "no"' yes 'citation related to current coordinates' y 'abbreviation for "yes"' _definition ; _citation_coordinate_linkage states whether or not this citation is concerned with precisely the set of coordinates given in the data block. If, for instance, the publication described the same structure, but the coordinates had undergone further refinement prior to creation of the data block, the value of this data item would be 'no'. ; data_citation_country _name '_citation_country' _category citation _type char _list yes _list_reference '_citation_id' _definition ; The country of publication; relevant for books and book chapters. ; data_citation_database_id_CSD _name '_citation_database_id_CSD' _category citation _type char _list yes _list_reference '_citation_id' _example LEKKUH _definition ; Identifier ('refcode') of the database record in the Cambridge Structural Database that contains details of the cited structure. ; data_citation_database_id_Medline _name '_citation_database_id_Medline' _category citation _type numb _list yes _list_reference '_citation_id' _enumeration_range 1: _example 89064067 _definition ; Accession number used by Medline to categorize a specific bibliographic entry. ; data_citation_id _name '_citation_id' _category citation _type char _list yes _list_mandatory yes loop_ _list_link_child '_citation_author_citation_id' '_citation_editor_citation_id' loop_ _example primary 1 2 3 _definition ; The value of _citation_id must uniquely identify a record in the _citation_ list. The _citation_id 'primary' should be used to indicate the citation that the author(s) consider to be the most pertinent to the contents of the data block. Note that this item need not be a number; it can be any unique identifier. ; data_citation_journal_abbrev _name '_citation_journal_abbrev' _category citation _type char _list yes _list_reference '_citation_id' _example 'J. Mol. Biol.' _definition ; Abbreviated name of the journal cited as given in the Chemical Abstracts Service Source Index. ; data_citation_journal_id_ASTM _name '_citation_journal_id_ASTM' _category citation _type char _list yes _list_reference '_citation_id' _definition ; The American Society for Testing and Materials (ASTM) code assigned to the journal cited (also referred to as the CODEN designator of the Chemical Abstracts Service); relevant for journal articles. ; data_citation_journal_id_CSD _name '_citation_journal_id_CSD' _category citation _type char _list yes _list_reference '_citation_id' _example '0070' _definition ; The Cambridge Structural Database (CSD) code assigned to the journal cited; relevant for journal articles. This is also the system used at the Protein Data Bank (PDB). ; data_citation_journal_id_ISSN _name '_citation_journal_id_ISSN' _category citation _type char _list yes _list_reference '_citation_id' _definition ; The International Standard Serial Number (ISSN) code assigned to the journal cited; relevant for journal articles. ; data_citation_journal_full _name '_citation_journal_full' _category citation _type char _list yes _list_reference '_citation_id' _example 'Journal of Molecular Biology' _definition ; Full name of the journal cited; relevant for journal articles. ; data_citation_journal_issue _name '_citation_journal_issue' _category citation _type char _list yes _list_reference '_citation_id' _example 2 _definition ; Issue number of the journal cited; relevant for journal articles. ; data_citation_journal_volume _name '_citation_journal_volume' _category citation _type char _list yes _list_reference '_citation_id' _example 174 _definition ; Volume number of the journal cited; relevant for journal articles. ; data_citation_language _name '_citation_language' _category citation _type char _list yes _list_reference '_citation_id' _example German _definition ; Language in which the cited article is written. ; data_citation_page_ loop_ _name '_citation_page_first' '_citation_page_last' _category citation _type char _list yes _list_reference '_citation_id' _definition ; The first and last pages of the citation; relevant for journal articles, books and book chapters. ; data_citation_special_details _name '_citation_special_details' _category citation _type char _list yes _list_reference '_citation_id' loop_ _example ; citation relates to this precise coordinate set ; ; citation relates to earlier low-resolution structure ; ; citation relates to further refinement of structure reported in citation 2 ; _definition ; A description of special aspects of the relationship of the contents of the data block to the literature item cited. ; data_citation_title _name '_citation_title' _category citation _type char _list yes _list_reference '_citation_id' _example ; Structure of diferric duck ovotransferrin at 2.35 \%A resolution. ; _definition ; The title of the citation; relevant for journal articles, books and book chapters. ; data_citation_year _name '_citation_year' _category citation _type numb _list yes _list_reference '_citation_id' _example 1984 _definition ; The year of the citation; relevant for journal articles, books and book chapters. ; ##################### ## CITATION_AUTHOR ## ##################### data_citation_author_[] _name '_citation_author_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _citation_author_citation_id _citation_author_name primary 'Fitzgerald, P.M.D.' primary 'McKeever, B.M.' primary 'Van Middlesworth, J.F.' primary 'Springer, J.P.' primary 'Heimbach, J.C.' primary 'Leu, C.-T.' primary 'Herber, W.K.' primary 'Dixon, R.A.F.' primary 'Darke, P.L.' 2 'Navia, M.A.' 2 'Fitzgerald, P.M.D.' 2 'McKeever, B.M.' 2 'Leu, C.-T.' 2 'Heimbach, J.C.' 2 'Herber, W.K.' 2 'Sigal, I.S.' 2 'Darke, P.L.' 2 'Springer, J.P.' 3 'McKeever, B.M.' 3 'Navia, M.A.' 3 'Fitzgerald, P.M.D.' 3 'Springer, J.P.' 3 'Leu, C.-T.' 3 'Heimbach, J.C.' 3 'Herber, W.K.' 3 'Sigal, I.S.' 3 'Darke, P.L.' ; ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the CITATION_AUTHOR category record details about the authors associated with the citations in the _citation_ list. ; data_citation_author_citation_id _name '_citation_author_citation_id' _category citation_author _type char _list yes _list_mandatory yes _list_link_parent '_citation_id' _definition ; The value of _citation_author_citation_id must match an identifier specified by _citation_id in the _citation_ list. ; data_citation_author_name _name '_citation_author_name' _category citation_author _type char _list yes _list_mandatory yes loop_ _example 'Bleary, Percival R.' "O'Neil, F.K." 'Van den Bossche, G.' 'Yang, D.-L.' 'Simonov, Yu.A.' 'M\"uller, H.A.' 'Ross II, C.R.' _definition ; Name of an author of the citation; relevant for journal articles, books and book chapters. The family name(s), followed by a comma and including any dynastic components, precedes the first name(s) or initial(s). ; data_citation_author_ordinal _name '_citation_author_ordinal' _category citation_author _type char _list yes _definition ; This data name defines the order of the author's name in the list of authors of a citation. ; ##################### ## CITATION_EDITOR ## ##################### data_citation_editor_[] _name '_citation_editor_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _citation_editor_citation_id _citation_editor_name 5 'McKeever, B.M.' 5 'Navia, M.A.' 5 'Fitzgerald, P.M.D.' 5 'Springer, J.P.' ; ; Example 1 - hypothetical example. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the CITATION_EDITOR category record details about the editor associated with the book or book chapter citations in the _citation_ list. ; data_citation_editor_citation_id _name '_citation_editor_citation_id' _category citation_editor _type char _list yes _list_mandatory yes _list_link_parent '_citation_id' _definition ; The value of _citation_editor_citation_id must match an identifier specified by _citation_id in the _citation_ list. ; data_citation_editor_name _name '_citation_editor_name' _category citation_editor _type char _list yes _list_mandatory yes loop_ _example 'Bleary, Percival R.' "O'Neil, F.K." 'Van den Bossche, G.' 'Yang, D.-L.' 'Simonov, Yu.A.' 'M\"uller, H.A.' 'Ross II, C.R.' _definition ; Name of an editor of the citation; relevant for books and book chapters. The family name(s), followed by a comma and including any dynastic components, precedes the first name(s) or initial(s). ; data_citation_editor_ordinal _name '_citation_editor_ordinal' _category citation_editor _type char _list yes _definition ; This data name defines the order of the editor's name in the list of editors of a citation. ; ############### ## COMPUTING ## ############### data_computing_[] _name '_computing_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _computing_data_collection 'CAD-4 (Enraf-Nonius, 1989)' _computing_cell_refinement 'CAD-4 (Enraf-Nonius, 1989)' _computing_data_reduction 'CFEO (Solans, 1978)' _computing_structure_solution 'SHELXS86 (Sheldrick, 1990)' _computing_structure_refinement 'SHELXL93 (Sheldrick, 1993)' _computing_molecular_graphics 'ORTEPII (Johnson, 1976)' _computing_publication_material 'PARST (Nardelli, 1983)' ; ; Example 1 - Rodr\'iguez-Romero, Ruiz-P\'erez & Solans [Acta Cryst. (1996), C52, 1415-1417]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the COMPUTING category record details about the computer programs used in the crystal structure analysis. ; data_computing_ loop_ _name '_computing_cell_refinement' '_computing_data_collection' '_computing_data_reduction' '_computing_molecular_graphics' '_computing_publication_material' '_computing_structure_refinement' '_computing_structure_solution' _category computing _type char loop_ _example 'CAD-4 (Enraf-Nonius, 1989)' 'DIFDAT, SORTRF, ADDREF (Hall & Stewart, 1990)' 'FRODO (Jones, 1986), ORTEP (Johnson, 1965)' 'CRYSTALS (Watkin, 1988)' 'SHELX85 (Sheldrick, 1985)' _definition ; Software used in the processing of the data. Give the program or package name and a brief reference. ; ############## ## DATABASE ## ############## data_database_[] _name '_database_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _database_code_CSD 'VOBYUG' ; ; Example 1 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the DATABASE category record details about the database identifiers of the data block. These data items are assigned by database managers and should only appear in a CIF if they originate from that source. ; data_database_code_ loop_ _name '_database_code_CAS' '_database_code_CSD' '_database_code_ICSD' '_database_code_MDF' '_database_code_NBS' '_database_code_PDB' '_database_code_PDF' _category database _type char _definition ; The codes are assigned by databases: Chemical Abstracts; Cambridge Structural Database (organic and metal-organic compounds); Inorganic Crystal Structure Database; Metals Data File (metal structures); NBS (NIST) Crystal Data Database (lattice parameters); Protein Data Bank; and the Powder Diffraction File (JCPDS/ICDD). ; data_database_code_depnum_ccdc_fiz _name '_database_code_depnum_ccdc_fiz' _category database _type char _definition ; Deposition numbers assigned by the Fachinformationszentrum Karlsruhe (FIZ) to files containing structural information archived by the Cambridge Crystallographic Data Centre (CCDC). ; data_database_code_depnum_ccdc_journal _name '_database_code_depnum_ccdc_journal' _category database _type char _definition ; Deposition numbers assigned by various journals to files containing structural information archived by the Cambridge Crystallographic Data Centre (CCDC). ; data_database_code_depnum_ccdc_archive _name '_database_code_depnum_ccdc_archive' _category database _type char _definition ; Deposition numbers assigned by the Cambridge Crystallographic Data Centre (CCDC) to files containing structural information archived by the CCDC. ; data_database_CSD_history _name '_database_CSD_history' _category database _type char _definition ; A history of changes made by the Cambridge Crystallographic Data Centre and incorporated into the Cambridge Structural Database (CSD). ; data_database_journal_ loop_ _name '_database_journal_ASTM' '_database_journal_CSD' _category database _type char _definition ; The ASTM CODEN designator for a journal as given in the Chemical Source List maintained by the Chemical Abstracts Service, and the journal code used in the Cambridge Structural Database. ; ############ ## DIFFRN ## ############ data_diffrn_[] _name '_diffrn_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _diffrn_special_details ; \q scan width (1.0 + 0.14tan\q)\%, \q scan rate 1.2\% min^-1^. Background counts for 5 s on each side every scan. ; _diffrn_ambient_temperature 293 ; ; Example 1 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the DIFFRN category record details about the intensity measurements. ; data_diffrn_ambient_environment _name '_diffrn_ambient_environment' _category diffrn _type char loop_ _example He vacuum 'mother liquor' _definition ; The gas or liquid surrounding the sample, if not air. ; data_diffrn_ambient_pressure _name '_diffrn_ambient_pressure' _category diffrn _type numb _type_conditions esd _enumeration_range 0.0: _units kPa _units_detail 'kilopascals' _definition ; The mean hydrostatic pressure in kilopascals at which the intensities were measured. ; data_diffrn_ambient_pressure_ loop_ _name '_diffrn_ambient_pressure_gt' '_diffrn_ambient_pressure_lt' _category diffrn _type numb _related_item '_diffrn_ambient_pressure' _related_function alternate _enumeration_range 0.0: _units kPa _units_detail 'kilopascals' _definition ; The mean hydrostatic pressure in kilopascals above which (*_gt) or below which (*_lt) the intensities were measured. These items allow for a pressure range to be given. _diffrn_ambient_pressure should always be used in preference to these items whenever possible. ; data_diffrn_ambient_temperature _name '_diffrn_ambient_temperature' _category diffrn _type numb _type_conditions esd _enumeration_range 0.0: _units K _units_detail kelvin _definition ; The mean temperature in kelvins at which the intensities were measured. ; data_diffrn_ambient_temperature_ loop_ _name '_diffrn_ambient_temperature_gt' '_diffrn_ambient_temperature_lt' _category diffrn _type numb _related_item '_diffrn_ambient_temperature' _related_function alternate _enumeration_range 0.0: _units K _units_detail kelvin _definition ; The mean temperature in kelvins above which (*_gt) or below which (*_lt) the intensities were measured. These items allow a range of temperatures to be given. _diffrn_ambient_temperature should always be used in preference to these items whenever possible. ; data_diffrn_crystal_treatment _name '_diffrn_crystal_treatment' _category diffrn _type char loop_ _example 'equilibrated in hutch for 24 hours' 'flash frozen in liquid nitrogen' 'slow cooled with direct air stream' _definition ; Remarks about how the crystal was treated prior to the intensity measurements. Particularly relevant when intensities were measured at low temperature. ; data_diffrn_measured_fraction_theta_full _name '_diffrn_measured_fraction_theta_full' _category diffrn _type numb _enumeration_range 0:1.0 _definition ; Fraction of unique (symmetry-independent) reflections measured out to _diffrn_reflns_theta_full. ; data_diffrn_measured_fraction_theta_max _name '_diffrn_measured_fraction_theta_max' _category diffrn _type numb _enumeration_range 0:1.0 _definition ; Fraction of unique (symmetry-independent) reflections measured out to _diffrn_reflns_theta_max. ; data_diffrn_special_details _name '_diffrn_special_details' _category diffrn _type char _example ; The results may not be entirely reliable as the measurement was made during a heat wave when the air-conditioning had failed. ; _definition ; Special details of the intensity-measurement process. Should include information about source instability, crystal motion, degradation and so on. ; data_diffrn_symmetry_description _name '_diffrn_symmetry_description' _category diffrn _type char _definition ; Observed diffraction point symmetry, systematic absences and possible space group(s) or superspace group(s) compatible with these. ; ####################### ## DIFFRN_ATTENUATOR ## ####################### data_diffrn_attenuator_[] _name '_diffrn_attenuator_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _diffrn_attenuator_code _diffrn_attenuator_scale 0 1.00 1 16.97 2 33.89 ; ; Example 1 - hypothetical example. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the DIFFRN_ATTENUATOR category record details about the diffraction attenuator scales employed. ; data_diffrn_attenuator_code _name '_diffrn_attenuator_code' _category diffrn_attenuator _type char _list yes _list_mandatory yes _list_link_child '_diffrn_refln_attenuator_code' _definition ; A code associated with a particular attenuator setting. This code is referenced by the _diffrn_refln_attenuator_code which is stored with the intensities. See _diffrn_attenuator_scale. ; data_diffrn_attenuator_material _name '_diffrn_attenuator_material' _category diffrn_attenuator _type char _list yes _list_reference '_diffrn_attenuator_code' _definition ; Material from which the attenuator is made. ; data_diffrn_attenuator_scale _name '_diffrn_attenuator_scale' _category diffrn_attenuator _type numb _list yes _list_reference '_diffrn_attenuator_code' _enumeration_range 1.0: _definition ; The scale factor applied when an intensity measurement is reduced by an attenuator identified by _diffrn_attenuator_code. The measured intensity must be multiplied by this scale to convert it to the same scale as unattenuated intensities. ; ##################### ## DIFFRN_DETECTOR ## ##################### data_diffrn_detector_[] _name '_diffrn_detector_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _diffrn_detector 'multiwire' _diffrn_detector_type 'Siemens' ; ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the DIFFRN_DETECTOR category describe the detector used to measure the scattered radiation, including any analyser and post-sample collimation. ; data_diffrn_detector _name '_diffrn_detector' _category diffrn_detector _type char _related_item '_diffrn_radiation_detector' _related_function alternate loop_ _example 'photographic film' 'scintillation counter' 'CCD plate' 'BF~3~ counter' _definition ; The general class of the radiation detector. ; data_diffrn_detector_area_resol_mean _name '_diffrn_detector_area_resol_mean' _category diffrn_detector _type numb _enumeration_range 0.0: _units mm^-1^ _units_detail 'pixels per millimetre' _definition ; The resolution of an area detector, in pixels/mm. ; data_diffrn_detector_details _name '_diffrn_detector_details' _category diffrn_detector _type char _definition ; A description of special aspects of the radiation detector. ; data_diffrn_detector_dtime _name '_diffrn_detector_dtime' _category diffrn_detector _related_item '_diffrn_radiation_detector_dtime' _related_function alternate _type numb _enumeration_range 0.0: _definition ; The deadtime in microseconds of the detector used to measure the diffraction intensities. ; data_diffrn_detector_type _name '_diffrn_detector_type' _category diffrn_detector _type char _definition ; The make, model or name of the detector device used. ; data_diffrn_radiation_detector _name '_diffrn_radiation_detector' _category diffrn_detector _type char _related_item '_diffrn_detector' _related_function replace _definition ; The detector used to measure the diffraction intensities. ; data_diffrn_radiation_detector_dtime _name '_diffrn_radiation_detector_dtime' _category diffrn_detector _type numb _enumeration_range 0.0: _related_item '_diffrn_detector_dtime' _related_function replace _definition ; The deadtime in microseconds of the detector used to measure the diffraction intensities. ; ######################## ## DIFFRN_MEASUREMENT ## ######################## data_diffrn_measurement_[] _name '_diffrn_measurement_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _diffrn_measurement_device_type 'Philips PW1100/20 diffractometer' _diffrn_measurement_method \q/2\q ; ; Example 1 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the DIFFRN_MEASUREMENT category refer to the mounting of the sample and to the goniometer on which it is mounted. ; data_diffrn_measurement_details _name '_diffrn_measurement_details' _category diffrn_measurement _type char _example '440 frames of 0.25\%' _definition ; A description of special aspects of the intensity measurement. ; data_diffrn_measurement_device _name '_diffrn_measurement_device' _category diffrn_measurement _type char loop_ _example 'three-circle diffractometer' 'four-circle diffractometer' '\k-geometry diffractometer' 'oscillation camera' 'precession camera' _definition ; The general class of goniometer or device used to support and orient the specimen. ; data_diffrn_measurement_device_details _name '_diffrn_measurement_device_details' _category diffrn_measurement _type char _example ; commercial goniometer modified locally to allow for 90\% \t arc ; _definition ; A description of special aspects of the device used to measure the diffraction intensities. ; data_diffrn_measurement_device_type _name '_diffrn_measurement_device_type' _category diffrn_measurement _type char _definition ; The make, model or name of the measurement device (goniometer) used. ; data_diffrn_measurement_method _name '_diffrn_measurement_method' _category diffrn_measurement _type char _example 'profile data from \q/2\q scans' _definition ; Method used to measure the intensities. ; data_diffrn_measurement_specimen_support _name '_diffrn_measurement_specimen_support' _category diffrn_measurement _type char loop_ _example 'glass capillary' 'quartz capillary' 'fiber' 'metal loop' _definition ; The physical device used to support the crystal during data collection. ; ########################## ## DIFFRN_ORIENT_MATRIX ## ########################## data_diffrn_orient_matrix_[] _name '_diffrn_orient_matrix_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _diffrn_orient_matrix_UB_11 -0.04170 _diffrn_orient_matrix_UB_12 -0.01429 _diffrn_orient_matrix_UB_13 -0.02226 _diffrn_orient_matrix_UB_21 -0.00380 _diffrn_orient_matrix_UB_22 -0.05578 _diffrn_orient_matrix_UB_23 -0.05048 _diffrn_orient_matrix_UB_31 0.00587 _diffrn_orient_matrix_UB_32 -0.13766 _diffrn_orient_matrix_UB_33 0.02277 _diffrn_orient_matrix_type 'TEXSAN convention (MSC, 1989)' ; ; Example 1 - data set n-alkylation_C-4 of Hussain, Fleming, Norman & Chang [Acta Cryst. (1996), C52, 1010-1012]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the DIFFRN_ORIENT_MATRIX category record details about the orientation matrix used in the measurement of the diffraction intensities. ; data_diffrn_orient_matrix_type _name '_diffrn_orient_matrix_type' _category diffrn_orient_matrix _type char _definition ; A description of the orientation matrix type and how it should be applied to define the orientation of the crystal precisely with respect to the diffractometer axes. ; data_diffrn_orient_matrix_UB_ loop_ _name '_diffrn_orient_matrix_UB_11' '_diffrn_orient_matrix_UB_12' '_diffrn_orient_matrix_UB_13' '_diffrn_orient_matrix_UB_21' '_diffrn_orient_matrix_UB_22' '_diffrn_orient_matrix_UB_23' '_diffrn_orient_matrix_UB_31' '_diffrn_orient_matrix_UB_32' '_diffrn_orient_matrix_UB_33' _category diffrn_orient_matrix _type numb _definition ; The elements of the diffractometer orientation matrix. These define the dimensions of the reciprocal cell and its orientation to the local diffractometer axes. See _diffrn_orient_matrix_type. ; ######################### ## DIFFRN_ORIENT_REFLN ## ######################### data_diffrn_orient_refln_[] _name '_diffrn_orient_refln_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _diffrn_orient_refln_index_h _diffrn_orient_refln_index_k _diffrn_orient_refln_index_l _diffrn_orient_refln_angle_theta _diffrn_orient_refln_angle_phi _diffrn_orient_refln_angle_omega _diffrn_orient_refln_angle_kappa -3 2 3 7.35 44.74 2.62 17.53 -4 1 0 9.26 83.27 8.06 5.79 0 0 6 5.85 -43.93 -25.36 86.20 2 1 3 7.36 -57.87 6.26 5.42 0 0 -6 5.85 -161.59 36.96 -86.79 -3 1 0 6.74 80.28 5.87 2.60 2 0 3 5.86 -76.86 -0.17 21.34 0 0 12 11.78 -44.02 -19.51 86.41 0 0 -12 11.78 -161.67 42.81 -86.61 -5 1 0 11.75 86.24 9.16 7.44 0 4 6 11.82 -19.82 10.45 4.19 5 0 6 14.13 -77.28 10.17 15.34 8 0 0 20.79 -77.08 25.30 -13.96 ; ; Example 1 - typical output listing from an Enraf-Nonius CAD-4 diffractometer. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the DIFFRN_ORIENT_REFLN category record details about the reflections that define the orientation matrix used in the measurement of the diffraction intensities. ; data_diffrn_orient_refln_angle_ loop_ _name '_diffrn_orient_refln_angle_chi' '_diffrn_orient_refln_angle_kappa' '_diffrn_orient_refln_angle_omega' '_diffrn_orient_refln_angle_phi' '_diffrn_orient_refln_angle_psi' '_diffrn_orient_refln_angle_theta' _category diffrn_orient_refln _type numb _list yes _list_reference '_diffrn_orient_refln_index_' _units deg _units_detail 'degrees' _definition ; Diffractometer angles of a reflection used to define the orientation matrix in degrees. See _diffrn_orient_matrix_UB_ and _diffrn_orient_refln_index_h, *_k and *_l. ; data_diffrn_orient_refln_index_ loop_ _name '_diffrn_orient_refln_index_h' '_diffrn_orient_refln_index_k' '_diffrn_orient_refln_index_l' _category diffrn_orient_refln _type numb _list yes _list_mandatory yes _definition ; The indices of a reflection used to define the orientation matrix. See _diffrn_orient_matrix_. ; ###################### ## DIFFRN_RADIATION ## ###################### data_diffrn_radiation_[] _name '_diffrn_radiation_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _diffrn_radiation_type 'Cu K\a' _diffrn_radiation_monochromator 'graphite' ; ; Example 1 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the DIFFRN_RADIATION category describe the radiation used in measuring the diffraction intensities, its collimation and monochromatization before the sample. Post-sample treatment of the beam is described by data items in the DIFFRN_DETECTOR category. ; data_diffrn_radiation_collimation _name '_diffrn_radiation_collimation' _category diffrn_radiation _type char loop_ _example '0.3 mm double-pinhole' '0.5 mm' 'focusing mirrors' _definition ; The collimation or focusing applied to the radiation. ; data_diffrn_radiation_filter_edge _name '_diffrn_radiation_filter_edge' _category diffrn_radiation _type numb _enumeration_range 0.0: _units A _units_detail 'angstroms' _definition ; Absorption edge in angstroms of the radiation filter used. ; data_diffrn_radiation_inhomogeneity _name '_diffrn_radiation_inhomogeneity' _category diffrn_radiation _type numb _enumeration_range 0.0: _definition ; Half-width in millimetres of the incident beam in the direction perpendicular to the diffraction plane. ; data_diffrn_radiation_monochromator _name '_diffrn_radiation_monochromator' _category diffrn_radiation _type char loop_ _example 'Zr filter' 'Ge 220' 'none' 'equatorial mounted graphite' _definition ; The method used to obtain monochromatic radiation. If a mono- chromator crystal is used, the material and the indices of the Bragg reflection are specified. ; data_diffrn_radiation_polarisn_norm _name '_diffrn_radiation_polarisn_norm' _category diffrn_radiation _type numb _enumeration_range -180.0:180.0 _units deg _units_detail 'degrees' _definition ; The angle in degrees, as viewed from the specimen, between the perpendicular component of the polarization and the diffraction plane. See _diffrn_radiation_polarisn_ratio. ; data_diffrn_radiation_polarisn_ratio _name '_diffrn_radiation_polarisn_ratio' _category diffrn_radiation _type numb _enumeration_range 0.0: _definition ; Polarization ratio of the diffraction beam incident on the crystal. It is the ratio of the perpendicularly polarized to the parallel polarized components of the radiation. The perpendicular component forms an angle of _diffrn_radiation_polarisn_norm to the normal to the diffraction plane of the sample (i.e. the plane containing the incident and reflected beams). ; data_diffrn_radiation_probe _name '_diffrn_radiation_probe' _category diffrn_radiation _type char loop_ _enumeration x-ray neutron electron gamma _definition ; The nature of the radiation used (i.e. the name of the subatomic particle or the region of the electromagnetic spectrum). It is strongly recommended that this information be given, so that the probe radiation can be simply determined. ; data_diffrn_radiation_type _name '_diffrn_radiation_type' _category diffrn_radiation _type char loop_ _example 'Cu K\a' 'Cu K\a~1~' 'Cu K-L~2,3~' white-beam _definition ; The type of the radiation. This is used to give a more detailed description than _diffrn_radiation_probe and is typically a description of the X-ray wavelength in Siegbahn notation. ; data_diffrn_radiation_xray_symbol _name '_diffrn_radiation_xray_symbol' _category diffrn_radiation _type char loop_ _enumeration _enumeration_detail K-L~3~ 'K\a~1~ in older Siegbahn notation' K-L~2~ 'K\a~2~ in older Siegbahn notation' K-M~3~ 'K\b~1~ in older Siegbahn notation' K-L~2,3~ 'use where K-L~3~ and K-L~2~ are not resolved' _definition ; The IUPAC symbol for the X-ray wavelength for the probe radiation. ; ################################### ### DIFFRN_RADIATION_WAVELENGTH ### ################################### data_diffrn_radiation_wavelength_[] _name '_diffrn_radiation_wavelength_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _diffrn_radiation_wavelength 1.5418 ; ; Example 1 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the DIFFRN_RADIATION_WAVELENGTH category describe the wavelength of the radiation used in measuring the diffraction intensities. Items may be looped to identify and assign weights to distinct wavelength components from a polychromatic beam. ; data_diffrn_radiation_wavelength _name '_diffrn_radiation_wavelength' _category diffrn_radiation_wavelength _type numb _list both _list_reference '_diffrn_radiation_wavelength_id' _enumeration_range 0.0: _units A _units_detail 'angstroms' _definition ; The radiation wavelength in angstroms. ; data_diffrn_radiation_wavelength_id _name '_diffrn_radiation_wavelength_id' _category diffrn_radiation_wavelength _type char _list yes _list_mandatory yes _list_link_child '_diffrn_refln_wavelength_id' loop_ _example x1 x2 neut _definition ; An arbitrary code identifying each value of _diffrn_radiation_wavelength. Items in the DIFFRN_RADIATION category are looped when multiple wavelengths are used. This code is used to link with the _diffrn_refln_ list. It must match with one of the _diffrn_refln_wavelength_id codes. ; data_diffrn_radiation_wavelength_wt _name '_diffrn_radiation_wavelength_wt' _category diffrn_radiation_wavelength _type numb _list yes _list_reference '_diffrn_radiation_wavelength_id' _enumeration_range 0.0:1.0 _enumeration_default 1.0 _definition ; The relative weight of a wavelength identified by the code _diffrn_radiation_wavelength_id in the list of wavelengths. ; ################## ## DIFFRN_REFLN ## ################## data_diffrn_refln_[] _name '_diffrn_refln_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _diffrn_refln_index_h _diffrn_refln_index_k _diffrn_refln_index_l _diffrn_refln_angle_chi _diffrn_refln_scan_rate _diffrn_refln_counts_bg_1 _diffrn_refln_counts_total _diffrn_refln_counts_bg_2 _diffrn_refln_angle_theta _diffrn_refln_angle_phi _diffrn_refln_angle_omega _diffrn_refln_angle_kappa _diffrn_refln_scan_width _diffrn_refln_elapsed_time 0 0 -16 0. 4.12 28 127 36 33.157 -75.846 16.404 50.170 1.516 19.43 0 0 -15 0. 4.12 38 143 28 30.847 -75.846 14.094 50.170 1.516 19.82 0 0 -14 0. 1.03 142 742 130 28.592 -75.846 11.839 50.170 1.516 21.32 0 0 -13 0. 4.12 26 120 37 26.384 -75.846 9.631 50.170 1.450 21.68 0 0 -12 0. 0.97 129 618 153 24.218 -75.846 7.464 50.170 1.450 23.20 0 0 -11 0. 4.12 33 107 38 22.087 -75.846 5.334 50.170 1.384 23.55 0 0 -10 0. 4.12 37 146 33 19.989 -75.846 3.235 50.170 1.384 23.90 0 0 -9 0. 4.12 50 179 49 17.918 -75.846 1.164 50.170 1.384 24.25 # - - - - data truncated for brevity - - - - 3 4 -4 0. 1.03 69 459 73 30.726 -53.744 46.543 -47.552 1.516 2082.58 3 4 -5 0. 1.03 91 465 75 31.407 -54.811 45.519 -42.705 1.516 2084.07 3 14 -6 0. 1.03 84 560 79 32.228 -55.841 44.745 -38.092 1.516 2085.57 # - - - - data truncated for brevity - - - - ; ; Example 1 - extracted from the CAD-4 listing for Tl~2~Cd~2~(SO~4~)~3~ at 85 K (unpublished). ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the DIFFRN_REFLN category record details about the intensities measured in the diffraction experiment. The DIFFRN_REFLN data items refer to individual intensity measurements and must be included in looped lists. (The DIFFRN_REFLNS data items specify the parameters that apply to all intensity measurements. The DIFFRN_REFLNS data items are not looped.) ; data_diffrn_refln_angle_ loop_ _name '_diffrn_refln_angle_chi' '_diffrn_refln_angle_kappa' '_diffrn_refln_angle_omega' '_diffrn_refln_angle_phi' '_diffrn_refln_angle_psi' '_diffrn_refln_angle_theta' _category diffrn_refln _type numb _list yes _list_reference '_diffrn_refln_index_' _units deg _units_detail 'degrees' _definition ; The diffractometer angles of a reflection in degrees. These correspond to the specified orientation matrix and the original measured cell before any subsequent cell transformations. ; data_diffrn_refln_attenuator_code _name '_diffrn_refln_attenuator_code' _category diffrn_refln _type char _list yes _list_reference '_diffrn_refln_index_' _list_link_parent '_diffrn_attenuator_code' _definition ; The code identifying the attenuator setting for this reflection. This code must match one of the _diffrn_attenuator_code values. ; data_diffrn_refln_class_code _name '_diffrn_refln_class_code' _category diffrn_refln _type char _list yes _list_reference '_diffrn_refln_index_' _list_link_parent '_diffrn_reflns_class_code' _definition ; The code identifying the class to which this reflection has been assigned. This code must match a value of _diffrn_reflns_class_code. Reflections may be grouped into classes for a variety of purposes. For example, for modulated structures each reflection class may be defined by the number m=sum|m~i~|, where the m~i~ are the integer coefficients that, in addition to h,k,l, index the corresponding diffraction vector in the basis defined for the reciprocal lattice. ; data_diffrn_refln_counts_ loop_ _name '_diffrn_refln_counts_bg_1' '_diffrn_refln_counts_bg_2' '_diffrn_refln_counts_net' '_diffrn_refln_counts_peak' '_diffrn_refln_counts_total' _category diffrn_refln _type numb _list yes _list_reference '_diffrn_refln_index_' _definition ; The diffractometer counts for the measurements: background before the peak, background after the peak, net counts after background removed, counts for peak scan or position, and the total counts (background plus peak). ; data_diffrn_refln_crystal_id _name '_diffrn_refln_crystal_id' _category diffrn_refln _type char _list yes _list_reference '_diffrn_refln_index_' _list_link_parent '_exptl_crystal_id' _definition ; Code identifying each crystal if multiple crystals are used. Is used to link with _exptl_crystal_id in the _exptl_crystal_ list. ; data_diffrn_refln_detect_slit_ loop_ _name '_diffrn_refln_detect_slit_horiz' '_diffrn_refln_detect_slit_vert' _category diffrn_refln _type numb _list yes _list_reference '_diffrn_refln_index_' _enumeration_range 0.0:90.0 _units deg _units_detail 'degrees' _definition ; Total slit apertures in degrees in the diffraction plane (*_horiz) and perpendicular to the diffraction plane (*_vert). ; data_diffrn_refln_elapsed_time _name '_diffrn_refln_elapsed_time' _category diffrn_refln _type numb _list yes _list_reference '_diffrn_refln_index_' _enumeration_range 0.0: _units min _units_detail 'minutes' _definition ; Elapsed time in minutes from the start of the diffraction experiment to the measurement of this intensity. ; data_diffrn_refln_index_ loop_ _name '_diffrn_refln_index_h' '_diffrn_refln_index_k' '_diffrn_refln_index_l' _category diffrn_refln _type numb _list yes _list_mandatory yes _definition ; Miller indices of a measured reflection. These need not match the _refln_index_h, *_k, *_l values if a transformation of the original measured cell has taken place. Details of the cell transformation are given in _diffrn_reflns_reduction_process. See also _diffrn_reflns_transf_matrix_. ; data_diffrn_refln_intensity_net _name '_diffrn_refln_intensity_net' _category diffrn_refln _type numb _list yes _list_reference '_diffrn_refln_index_' _enumeration_range 0: _definition ; Net intensity calculated from the diffraction counts after the attenuator and standard scales have been applied. ; data_diffrn_refln_intensity_sigma _name '_diffrn_refln_intensity_sigma' _category diffrn_refln _type numb _related_item '_diffrn_refln_intensity_u' _related_function replace _list yes _list_reference '_diffrn_refln_index_' _enumeration_range 0: _definition ; Standard uncertainty (e.s.d.) of the net intensity calculated from the diffraction counts after the attenuator and standard scales have been applied. ; data_diffrn_refln_intensity_u _name '_diffrn_refln_intensity_u' _category diffrn_refln _type numb _related_item '_diffrn_refln_intensity_sigma' _related_function alternate _list yes _list_reference '_diffrn_refln_index_' _enumeration_range 0: _definition ; Standard uncertainty of the net intensity calculated from the diffraction counts after the attenuator and standard scales have been applied. ; data_diffrn_refln_scale_group_code _name '_diffrn_refln_scale_group_code' _category diffrn_refln _type char _list yes _list_link_parent '_diffrn_scale_group_code' _list_reference '_diffrn_refln_index_' _definition ; The code identifying the scale applicable to this reflection. This code must match with a specified _diffrn_scale_group_code value. ; data_diffrn_refln_scan_mode _name '_diffrn_refln_scan_mode' _category diffrn_refln _type char _list yes _list_reference '_diffrn_refln_index_' loop_ _enumeration _enumeration_detail om 'omega scan' ot 'omega/2theta scan' q 'Q scans (arbitrary reciprocal directions)' _definition ; The code identifying the mode of scanning for measurements using a diffractometer. See _diffrn_refln_scan_width and _diffrn_refln_scan_mode_backgd. ; data_diffrn_refln_scan_mode_backgd _name '_diffrn_refln_scan_mode_backgd' _category diffrn_refln _type char _list yes _list_reference '_diffrn_refln_index_' loop_ _enumeration _enumeration_detail st 'stationary counter background' mo 'moving counter background' _definition ; The code identifying the mode of scanning a reflection to measure the background intensity. ; data_diffrn_refln_scan_rate _name '_diffrn_refln_scan_rate' _category diffrn_refln _type numb _list yes _list_reference '_diffrn_refln_index_' _enumeration_range 0.0: _units deg/min _units_detail 'degrees per minute' _definition ; The rate of scanning a reflection in degrees per minute to measure the intensity. ; data_diffrn_refln_scan_time_backgd _name '_diffrn_refln_scan_time_backgd' _category diffrn_refln _type numb _list yes _list_reference '_diffrn_refln_index_' _enumeration_range 0.0: _units sec _units_detail 'seconds' _definition ; The time spent measuring each background in seconds. ; data_diffrn_refln_scan_width _name '_diffrn_refln_scan_width' _category diffrn_refln _type numb _list yes _list_reference '_diffrn_refln_index_' _enumeration_range 0.0:90.0 _units deg _units_detail 'degrees' _definition ; The scan width in degrees of the scan mode defined by the code _diffrn_refln_scan_mode. ; data_diffrn_refln_sint/lambda _name '_diffrn_refln_sint/lambda' _category diffrn_refln _type numb _list yes _list_reference '_diffrn_refln_index_' _enumeration_range 0.0: _units A^-1^ _units_detail 'reciprocal angstroms' _definition ; The (sin theta)/lambda value in reciprocal angstroms for this reflection. ; data_diffrn_refln_standard_code _name '_diffrn_refln_standard_code' _category diffrn_refln _type char _list yes _list_link_parent '_diffrn_standard_refln_code' _list_reference '_diffrn_refln_index_' loop_ _example 1 2 3 s1 s2 s3 A B C _definition ; A code indicating that this reflection was measured as a standard reflection. The value must be '.' or match one of the _diffrn_standard_refln_code values. ; data_diffrn_refln_wavelength _name '_diffrn_refln_wavelength' _category diffrn_refln _type numb _list yes _list_reference '_diffrn_refln_index_' _enumeration_range 0.0: _units A _units_detail 'angstroms' _definition ; The mean wavelength in angstroms of the radiation used to measure the intensity of this reflection. This is an important parameter for reflections measured using energy-dispersive detectors or the Laue method. ; data_diffrn_refln_wavelength_id _name '_diffrn_refln_wavelength_id' _category diffrn_refln _type char _list yes _list_link_parent '_diffrn_radiation_wavelength_id' _list_reference '_diffrn_refln_index_' loop_ _example x1 x2 neut _definition ; Code identifying the wavelength in the _diffrn_radiation_ list. ; ################### ## DIFFRN_REFLNS ## ################### data_diffrn_reflns_[] _name '_diffrn_reflns_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _diffrn_reflns_number 1592 _diffrn_reflns_av_R_equivalents 0 _diffrn_reflns_av_unetI/netI .027 _diffrn_reflns_limit_h_min 0 _diffrn_reflns_limit_h_max 6 _diffrn_reflns_limit_k_min -17 _diffrn_reflns_limit_k_max 0 _diffrn_reflns_limit_l_min 0 _diffrn_reflns_limit_l_max 22 _diffrn_reflns_theta_min 3.71 _diffrn_reflns_theta_max 61.97 ; ; Example 1 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the DIFFRN_REFLNS category record details about the set of intensities measured in the diffraction experiment. The DIFFRN_REFLNS data items specify the parameters that apply to all intensity measurements. The DIFFRN_REFLNS data items are not looped. (The DIFFRN_REFLN data items refer to individual intensity measurements and must be included in looped lists.) ; data_diffrn_reflns_av_R_equivalents _name '_diffrn_reflns_av_R_equivalents' _category diffrn_reflns _type numb _enumeration_range 0.0: _definition ; The residual [sum av|del(I)| / sum |av(I)|] for symmetry-equivalent reflections used to calculate the average intensity av(I). The av|del(I)| term is the average absolute difference between av(I) and the individual symmetry-equivalent intensities. ; data_diffrn_reflns_av_sigmaI/netI _name '_diffrn_reflns_av_sigmaI/netI' _category diffrn_reflns _type numb _related_item '_diffrn_reflns_av_unetI/netI' _related_function replace _enumeration_range 0.0: _definition ; Measure [sum u(net I)|/sum|net I|] for all measured reflections. ; data_diffrn_reflns_av_unetI/netI _name '_diffrn_reflns_av_unetI/netI' _category diffrn_reflns _type numb _related_item '_diffrn_reflns_av_sigmaI/netI' _related_function alternate _enumeration_range 0.0: _definition ; Measure [sum u(net I)|/sum|net I|] for all measured reflections. ; data_diffrn_reflns_limit_ loop_ _name '_diffrn_reflns_limit_h_max' '_diffrn_reflns_limit_h_min' '_diffrn_reflns_limit_k_max' '_diffrn_reflns_limit_k_min' '_diffrn_reflns_limit_l_max' '_diffrn_reflns_limit_l_min' _category diffrn_reflns _type numb _definition ; The limits on the Miller indices of the intensities specified by _diffrn_refln_index_h, *_k, *_l. ; data_diffrn_reflns_number _name '_diffrn_reflns_number' _category diffrn_reflns _type numb _enumeration_range 0: _definition ; The total number of measured intensities, excluding reflections that are classed as systematically absent arising from translational symmetry in the crystal unit cell. ; data_diffrn_reflns_reduction_process _name '_diffrn_reflns_reduction_process' _category diffrn_reflns _type char _example 'data averaged using Fisher test' _definition ; A description of the process used to reduce the intensities into structure-factor magnitudes. ; data_diffrn_reflns_resolution_full _name '_diffrn_reflns_resolution_full' _category diffrn_reflns _type numb _enumeration_range 0.0: _units A^-1^ _units_detail 'reciprocal angstroms' _related_item '_diffrn_reflns_theta_full' _related_function alternate _definition ; The resolution in reciprocal angstroms at which the measured reflection count is close to complete. ; data_diffrn_reflns_resolution_max _name '_diffrn_reflns_resolution_max' _category diffrn_reflns _type numb _enumeration_range 0.0: _units A^-1^ _units_detail 'reciprocal angstroms' _related_item '_diffrn_reflns_theta_max' _related_function alternate _definition ; Maximum resolution in reciprocal angstroms of the measured diffraction pattern. ; data_diffrn_reflns_theta_full _name '_diffrn_reflns_theta_full' _category diffrn_reflns _type numb _enumeration_range 0.0:90.0 _units deg _units_detail 'degrees' _definition ; The theta angle (in degrees) at which the measured reflection count is close to complete. The fraction of unique reflections measured out to this angle is given by _diffrn_measured_fraction_theta_full. ; data_diffrn_reflns_theta_max _name '_diffrn_reflns_theta_max' _category diffrn_reflns _type numb _enumeration_range 0.0:90.0 _units deg _units_detail 'degrees' _definition ; Maximum theta angle in degrees for the measured intensities. ; data_diffrn_reflns_theta_min _name '_diffrn_reflns_theta_min' _category diffrn_reflns _type numb _enumeration_range 0.0:90.0 _units deg _units_detail 'degrees' _definition ; Minimum theta angle in degrees for the measured intensities. ; data_diffrn_reflns_transf_matrix_ loop_ _name '_diffrn_reflns_transf_matrix_11' '_diffrn_reflns_transf_matrix_12' '_diffrn_reflns_transf_matrix_13' '_diffrn_reflns_transf_matrix_21' '_diffrn_reflns_transf_matrix_22' '_diffrn_reflns_transf_matrix_23' '_diffrn_reflns_transf_matrix_31' '_diffrn_reflns_transf_matrix_32' '_diffrn_reflns_transf_matrix_33' _category diffrn_reflns _type numb _definition ; Elements of the matrix used to transform the diffraction reflection indices _diffrn_refln_index_h, *_k, *_l into the _refln_index_h, *_k, *_l indices. |11 12 13| (h k l) diffraction |21 22 23| = (h' k' l') |31 32 33| ; ######################### ## DIFFRN_REFLNS_CLASS ## ######################### data_diffrn_reflns_class_[] _name '_diffrn_reflns_class_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _diffrn_reflns_class_number _diffrn_reflns_class_d_res_high _diffrn_reflns_class_d_res_low _diffrn_reflns_class_av_R_eq _diffrn_reflns_class_code _diffrn_reflns_class_description 1580 0.551 6.136 0.015 'Main' 'm=0; main reflections' 1045 0.551 6.136 0.010 'Sat1' 'm=1; first-order satellites' ; ; Example 1 - example corresponding to the one-dimensional incommensurately modulated structure of K~2~SeO~4~. Each reflection class is defined by the number m=sum|m~i~|, where the m~i~ are the integer coefficients that, in addition to h,k,l, index the corresponding diffraction vector in the basis defined for the reciprocal lattice. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the DIFFRN_REFLNS_CLASS category record details about the classes of reflections measured in the diffraction experiment. ; data_diffrn_reflns_class_av_R_eq _name '_diffrn_reflns_class_av_R_eq' _category diffrn_reflns_class _type numb _list yes _list_reference '_diffrn_reflns_class_code' _enumeration_range 0.0: _definition ; For each reflection class, the residual [sum av|del(I)|/sum|av(I)|] for symmetry-equivalent reflections used to calculate the average intensity av(I). The av|del(I)| term is the average absolute difference between av(I) and the individual intensities. ; data_diffrn_reflns_class_av_sgI/I _name '_diffrn_reflns_class_av_sgI/I' _category diffrn_reflns_class _type numb _related_item '_diffrn_reflns_class_av_uI/I' _related_function replace _list yes _list_reference '_diffrn_reflns_class_code' _enumeration_range 0.0: _definition ; Measure [sum|u(net I)|/sum|net I|] for all measured intensities in a reflection class. ; data_diffrn_reflns_class_av_uI/I _name '_diffrn_reflns_class_av_uI/I' _category diffrn_reflns_class _type numb _related_item '_diffrn_reflns_class_av_sgI/I' _related_function alternate _list yes _list_reference '_diffrn_reflns_class_code' _enumeration_range 0.0: _definition ; Measure [sum|u(net I)|/sum|net I|] for all measured intensities in a reflection class. ; data_diffrn_reflns_class_code _name '_diffrn_reflns_class_code' _category diffrn_reflns_class _type char _list yes _list_mandatory yes _list_link_child '_diffrn_refln_class_code' loop_ _example '1' 'm1' 's2' _definition ; The code identifying a certain reflection class. ; data_diffrn_reflns_class_description _name '_diffrn_reflns_class_description' _category diffrn_reflns_class _type char _list yes _list_reference '_diffrn_reflns_class_code' loop_ _example 'm=1 first order satellites' 'H0L0 common projection reflections' _definition ; Description of each reflection class. ; data_diffrn_reflns_class_d_res_high _name '_diffrn_reflns_class_d_res_high' _category diffrn_reflns_class _type numb _list yes _list_reference '_diffrn_reflns_class_code' _enumeration_range 0.0: _units A _units_detail 'Angstroms' _definition ; The smallest value in angstroms of the interplanar spacings of the reflections in each reflection class. This is called the highest resolution for this reflection class. ; data_diffrn_reflns_class_d_res_low _name '_diffrn_reflns_class_d_res_low' _category diffrn_reflns_class _type numb _list yes _list_reference '_diffrn_reflns_class_code' _enumeration_range 0.0: _units A _units_detail 'Angstroms' _definition ; The highest value in angstroms of the interplanar spacings of the reflections in each reflection class. This is called the lowest resolution for this reflection class. ; data_diffrn_reflns_class_number _name '_diffrn_reflns_class_number' _category diffrn_reflns_class _type numb _list yes _list_reference '_diffrn_reflns_class_code' _enumeration_range 0: _definition ; The total number of measured intensities for each reflection class, excluding the systematic absences arising from centring translations. ; ######################## ## DIFFRN_SCALE_GROUP ## ######################## data_diffrn_scale_group_[] _name '_diffrn_scale_group_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _diffrn_scale_group_code _diffrn_scale_group_I_net 1 .86473 2 1.0654 ; ; Example 1 - hypothetical example. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the DIFFRN_SCALE_GROUP category record details of the scaling factors applied to place all intensities in the reflection lists on a common scale. Scaling groups might, for instance, correspond to each film in a multi-film data set or each crystal in a multi-crystal data set. ; data_diffrn_scale_group_code _name '_diffrn_scale_group_code' _category diffrn_scale_group _type char _list yes _list_mandatory yes _list_link_child '_diffrn_refln_scale_group_code' loop_ _example 1 2 3 s1 A B c1 c2 c3 _definition ; The code identifying a specific measurement group (e.g. for multi-film or multi-crystal data). The code must match a _diffrn_refln_scale_group_code in the reflection list. ; data_diffrn_scale_group_I_net _name '_diffrn_scale_group_I_net' _category diffrn_scale_group _type numb _list yes _list_reference '_diffrn_scale_group_code' _enumeration_range 0.0: _definition ; The scale for a specific measurement group which is to be multiplied with the net intensity to place all intensities in the _diffrn_refln_ or _refln_ list on a common scale. ; ################### ## DIFFRN_SOURCE ## ################### data_diffrn_source_[] _name '_diffrn_source_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _diffrn_source 'rotating anode X-ray tube' _diffrn_source_type 'Rigaku RU-200' _diffrn_source_power 50 _diffrn_source_current 180 _diffrn_source_size '8 mm x 0.4 mm broad focus' ; ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the DIFFRN_SOURCE category record details of the source of radiation used in the diffraction experiment. ; data_diffrn_radiation_source _name '_diffrn_radiation_source' _category diffrn_source _type char _related_item '_diffrn_source' _related_function replace _definition ; The source of radiation. ; data_diffrn_source _name '_diffrn_source' _category diffrn_source _type char _related_item '_diffrn_radiation_source' _related_function alternate loop_ _example 'sealed X-ray tube' 'nuclear reactor' 'spallation source' 'electron microscope' 'rotating-anode X-ray tube' 'synchrotron' _definition ; The general class of the source of radiation. ; data_diffrn_source_current _name '_diffrn_source_current' _category diffrn_source _type numb _enumeration_range 0.0: _units mA _units_detail 'milliamperes' _definition ; The current in milliamperes at which the radiation source was operated. ; data_diffrn_source_details _name '_diffrn_source_details' _category diffrn_source _type char _definition ; A description of special aspects of the source. ; data_diffrn_source_power _name '_diffrn_source_power' _category diffrn_source _type numb _enumeration_range 0.0: _units kW _units_detail 'kilowatts' _definition ; The power in kilowatts at which the radiation source was operated. ; data_diffrn_source_size _name '_diffrn_source_size' _category diffrn_source _type char loop_ _example '8mm x 0.4 mm fine-focus' 'broad focus' _definition ; The dimensions of the source as viewed from the sample. ; data_diffrn_source_take-off_angle _name '_diffrn_source_take-off_angle' _category diffrn_source _type numb _enumeration_range 0:90 _units degrees _example 1.53 _definition ; The complement of the angle in degrees between the normal to the surface of the X-ray tube target and the primary X-ray beam for beams generated by traditional X-ray tubes. ; data_diffrn_source_target _name '_diffrn_source_target' _category diffrn_source _type char loop_ _enumeration H He Li Be B C N O F Ne Na Mg Al Si P S Cl Ar K Ca Sc Ti V Cr Mn Fe Co Ni Cu Zn Ga Ge As Se Br Kr Rb Sr Y Zr Nb Mo Tc Ru Rh Pd Ag Cd In Sn Sb Te I Xe Cs Ba La Ce Pr Nd Pm Sm Eu Gd Tb Dy Ho Er Tm Yb Lu Hf Ta W Re Os Ir Pt Au Hg Tl Pb Bi Po At Rn Fr Ra Ac Th Pa U Np Pu Am Cm Bk Cf Es Fm Md No Lr _definition ; The chemical element symbol for the X-ray target (usually the anode) used to generate X-rays. This can also be used for spallation sources. ; data_diffrn_source_type _name '_diffrn_source_type' _category diffrn_source _type char loop_ _example 'NSLS beamline X8C' 'Rigaku RU200' _definition ; The make, model or name of the source of radiation. ; data_diffrn_source_voltage _name '_diffrn_source_voltage' _category diffrn_source _type numb _enumeration_range 0.0: _units kV _units_detail 'kilovolts' _definition ; The voltage in kilovolts at which the radiation source was operated. ; ########################### ## DIFFRN_STANDARD_REFLN ## ########################### data_diffrn_standard_refln_[] _name '_diffrn_standard_refln_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _diffrn_standard_refln_index_h _diffrn_standard_refln_index_k _diffrn_standard_refln_index_l 3 2 4 1 9 1 3 0 10 ; ; Example 1 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the DIFFRN_STANDARD_REFLN category record details about the reflections treated as standards during the measurement of the diffraction intensities. Note that these are the individual standard reflections, not the results of the analysis of the standard reflections. ; data_diffrn_standard_refln_code _name '_diffrn_standard_refln_code' _category diffrn_standard_refln _type char _list yes _list_link_child '_diffrn_refln_standard_code' _list_reference '_diffrn_standard_refln_index_' loop_ _example 1 2 3 s1 A B _definition ; The code identifying a reflection measured as a standard reflection with the indices _diffrn_standard_refln_index_. This is the same code as the _diffrn_refln_standard_code in the _diffrn_refln_ list. ; data_diffrn_standard_refln_index_ loop_ _name '_diffrn_standard_refln_index_h' '_diffrn_standard_refln_index_k' '_diffrn_standard_refln_index_l' _category diffrn_standard_refln _type numb _list yes _list_mandatory yes _definition ; Miller indices of standard reflections used in the diffraction measurement process. ; ###################### ## DIFFRN_STANDARDS ## ###################### data_diffrn_standards_[] _name '_diffrn_standards_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _diffrn_standards_number 3 _diffrn_standards_interval_time 120 _diffrn_standards_decay_% 0 ; ; Example 1 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the DIFFRN_STANDARDS category record details about the set of standard reflections used to monitor intensity stability during the measurement of diffraction intensities. Note that these records describe properties common to the set of standard reflections, not the standard reflections themselves. ; data_diffrn_standards_decay_% _name '_diffrn_standards_decay_%' _category diffrn_standards _type numb _type_conditions esd _enumeration_range :100 _definition ; The percentage decrease in the mean of the intensities for the set of standard reflections from the start of the measurement process to the end. This value usually affords a measure of the overall decay in crystal quality during the diffraction measurement process. Negative values are used in exceptional instances where the final intensities are greater than the initial ones. ; data_diffrn_standards_interval_ loop_ _name '_diffrn_standards_interval_count' '_diffrn_standards_interval_time' _category diffrn_standards _type numb _enumeration_range 0: _definition ; The number of reflection intensities, or the time in minutes, between the measurement of standard reflection intensities. ; data_diffrn_standards_number _name '_diffrn_standards_number' _category diffrn_standards _type numb _enumeration_range 0: _definition ; The number of unique standard reflections used during the measurement of the diffraction intensities. ; data_diffrn_standards_scale_sigma _name '_diffrn_standards_scale_sigma' _category diffrn_standards _type numb _related_item '_diffrn_standards_scale_u' _related_function replace _enumeration_range 0.0: _definition ; The standard uncertainty (e.s.d.) of the individual mean standard scales applied to the intensity data. ; data_diffrn_standards_scale_u _name '_diffrn_standards_scale_u' _category diffrn_standards _type numb _related_item '_diffrn_standards_scale_sigma' _related_function alternate _enumeration_range 0.0: _definition ; The standard uncertainty of the individual mean standard scales applied to the intensity data. ; ########### ## EXPTL ## ########### data_exptl_[] _name '_exptl_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _exptl_absorpt_coefficient_mu 0.962 _exptl_absorpt_correction_type psi-scan _exptl_absorpt_process_details 'North, Phillips & Mathews (1968)' _exptl_absorpt_correction_T_min 0.929 _exptl_absorpt_correction_T_max 0.997 ; ; Example 1 - based on a paper by Steiner [Acta Cryst. (1996), C52, 2554-2556]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the EXPTL category record details about the experimental work prior to the intensity measurements and details about the absorption-correction technique employed. ; data_exptl_absorpt_coefficient_mu _name '_exptl_absorpt_coefficient_mu' _category exptl _type numb _enumeration_range 0.0: _units mm^-1^ _units_detail 'reciprocal millimetres' _definition ; The absorption coefficient mu in reciprocal millimetres calculated from the atomic content of the cell, the density and the radiation wavelength. ; data_exptl_absorpt_correction_T_ loop_ _name '_exptl_absorpt_correction_T_max' '_exptl_absorpt_correction_T_min' _category exptl _type numb _enumeration_range 0.0:1.0 _definition ; The maximum and minimum transmission factors for the crystal and radiation. These factors are also referred to as the absorption correction A or 1/A*. ; data_exptl_absorpt_correction_type _name '_exptl_absorpt_correction_type' _category exptl _type char loop_ _enumeration _enumeration_detail analytical 'analytical from crystal shape' cylinder 'cylindrical' empirical 'empirical from intensities' gaussian 'Gaussian from crystal shape' integration 'integration from crystal shape' multi-scan 'symmetry-related measurements' none 'no absorption correction applied' numerical 'numerical from crystal shape' psi-scan 'psi-scan corrections' refdelf 'refined from delta-F' sphere 'spherical' _definition ; The absorption-correction type and method. The value 'empirical' should NOT be used unless more detailed information is not available. ; data_exptl_absorpt_process_details _name '_exptl_absorpt_process_details' _category exptl _type char loop_ _example 'Tompa analytical' 'MolEN (Fair, 1990)' '(North, Phillips & Mathews, 1968)' _definition ; Description of the absorption process applied to the intensities. A literature reference should be supplied for psi-scan techniques. ; data_exptl_crystals_number _name '_exptl_crystals_number' _category exptl _type numb _enumeration_range 1: _definition ; The total number of crystals used for the measurement of intensities. ; data_exptl_special_details _name '_exptl_special_details' _category exptl _type char _definition ; Any special information about the experimental work prior to the intensity measurements. See also _exptl_crystal_preparation. ; ################### ## EXPTL_CRYSTAL ## ################### data_exptl_crystal_[] _name '_exptl_crystal_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _exptl_crystal_description prism _exptl_crystal_colour colourless _exptl_crystal_size_max 0.32 _exptl_crystal_size_mid 0.27 _exptl_crystal_size_min 0.10 _exptl_crystal_density_diffrn 1.146 _exptl_crystal_density_meas ? _exptl_crystal_density_method 'not measured' _exptl_crystal_F_000 656 ; ; Example 1 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _exptl_crystal_density_meas_gt 2.5 _exptl_crystal_density_meas_lt 5.0 ; ; Example 2 - using separate items to define upper and lower limits for a value. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _exptl_crystal_density_meas_temp_lt 300 ; ; Example 3 - here the density was measured at some unspecified temperature below room temperature. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the EXPTL_CRYSTAL category record details about experimental measurements on the crystal or crystals used, such as shape, size or density. ; data_exptl_crystal_colour _name '_exptl_crystal_colour' _category exptl_crystal _type char _list both _list_reference '_exptl_crystal_id' loop_ _related_item _related_function '_exptl_crystal_colour_lustre' alternate '_exptl_crystal_colour_modifier' alternate '_exptl_crystal_colour_primary' alternate _example 'dark green' _definition ; The colour of the crystal. ; data_exptl_crystal_colour_lustre _name '_exptl_crystal_colour_lustre' _category exptl_crystal _type char _list both _list_reference '_exptl_crystal_id' loop_ _enumeration metallic dull clear _related_item '_exptl_crystal_colour' _related_function alternate _definition ; The enumeration list of standardized names developed for the International Centre for Diffraction Data. The colour of a crystal is given by the combination of _exptl_crystal_colour_modifier with _exptl_crystal_colour_primary, as in 'dark-green' or 'bluish-violet', if necessary combined with _exptl_crystal_colour_lustre, as in 'metallic-green'. ; data_exptl_crystal_colour_modifier _name '_exptl_crystal_colour_modifier' _category exptl_crystal _type char _list both _list_reference '_exptl_crystal_id' loop_ _enumeration light dark whitish blackish grayish brownish reddish pinkish orangish yellowish greenish bluish _related_item '_exptl_crystal_colour' _related_function alternate _definition ; The enumeration list of standardized names developed for the International Centre for Diffraction Data. The colour of a crystal is given by the combination of _exptl_crystal_colour_modifier with _exptl_crystal_colour_primary, as in 'dark-green' or 'bluish-violet', if necessary combined with _exptl_crystal_colour_lustre, as in 'metallic-green'. ; data_exptl_crystal_colour_primary _name '_exptl_crystal_colour_primary' _category exptl_crystal _type char _list both _list_reference '_exptl_crystal_id' loop_ _enumeration colourless white black gray brown red pink orange yellow green blue violet _related_item '_exptl_crystal_colour' _related_function alternate _definition ; The enumeration list of standardized names developed for the International Centre for Diffraction Data. The colour of a crystal is given by the combination of _exptl_crystal_colour_modifier with _exptl_crystal_colour_primary, as in 'dark-green' or 'bluish-violet', if necessary combined with _exptl_crystal_colour_lustre, as in 'metallic-green'. ; data_exptl_crystal_density_diffrn _name '_exptl_crystal_density_diffrn' _category exptl_crystal _type numb _list both _list_reference '_exptl_crystal_id' _enumeration_range 0.0: _units Mgm^-3^ _units_detail 'megagrams per cubic metre' _definition ; Density values calculated from the crystal cell and contents. The units are megagrams per cubic metre (grams per cubic centimetre). ; data_exptl_crystal_density_meas _name '_exptl_crystal_density_meas' _category exptl_crystal _type numb _type_conditions esd _list both _list_reference '_exptl_crystal_id' _enumeration_range 0.0: _units Mgm^-3^ _units_detail 'megagrams per cubic metre' _definition ; Density values measured using standard chemical and physical methods. The units are megagrams per cubic metre (grams per cubic centimetre). ; data_exptl_crystal_density_meas_gt _name '_exptl_crystal_density_meas_gt' _category exptl_crystal _type numb _list both _list_reference '_exptl_crystal_id' _enumeration_range 0.0: _units Mg^-3^ _units_detail 'megagrams per cubic metre' _related_item '_exptl_crystal_density_meas' _related_function alternate loop_ _example _example_detail 2.5 ; lower limit for the density (only the range within which the density lies was given in the original paper) ; _definition ; The value above which the density measured using standard chemical and physical methods lies. The units are megagrams per cubic metre (grams per cubic centimetre). _exptl_crystal_density_meas_gt and _exptl_crystal_density_meas_lt should not be used to report new experimental work, for which _exptl_crystal_density_meas should be used. These items are intended for use in reporting information in existing databases and archives which would be misleading if reported under _exptl_crystal_density_meas. ; data_exptl_crystal_density_meas_lt _name '_exptl_crystal_density_meas_lt' _category exptl_crystal _type numb _list both _list_reference '_exptl_crystal_id' _enumeration_range 0.0: _units Mg^-3^ _units_detail 'megagrams per cubic metre' _related_item '_exptl_crystal_density_meas' _related_function alternate loop_ _example _example_detail 1.0 'specimen floats in water' 5.0 ; upper limit for the density (only the range within which the density lies was given in the original paper) ; _definition ; The value below which the density measured using standard chemical and physical methods lies. The units are megagrams per cubic metre (grams per cubic centimetre). _exptl_crystal_density_meas_gt and _exptl_crystal_density_meas_lt should not be used to report new experimental work, for which _exptl_crystal_density_meas should be used. These items are intended for use in reporting information in existing databases and archives which would be misleading if reported under _exptl_crystal_density_meas. ; data_exptl_crystal_density_meas_temp _name '_exptl_crystal_density_meas_temp' _category exptl_crystal _type numb _type_conditions esd _list both _list_reference '_exptl_crystal_id' _enumeration_range 0.0: _units K _units_detail kelvin _definition ; Temperature in kelvins at which _exptl_crystal_density_meas was determined. ; data_exptl_crystal_density_meas_temp_gt _name '_exptl_crystal_density_meas_temp_gt' _category exptl_crystal _type numb _list both _list_reference '_exptl_crystal_id' _enumeration_range 0.0: _units K _units_detail kelvin _related_item '_exptl_crystal_density_meas_temp' _related_function alternate _definition ; Temperature in kelvins above which _exptl_crystal_density_meas was determined. _exptl_crystal_density_meas_temp_gt and _exptl_crystal_density_meas_temp_lt should not be used for reporting new work, for which the correct temperature of measurement should be given. These items are intended for use in reporting information stored in databases or archives which would be misleading if reported under _exptl_crystal_density_meas_temp. ; data_exptl_crystal_density_meas_temp_lt _name '_exptl_crystal_density_meas_temp_lt' _category exptl_crystal _type numb _list both _list_reference '_exptl_crystal_id' _enumeration_range 0.0: _units K _units_detail kelvin _related_item '_exptl_crystal_density_meas_temp' _related_function alternate loop_ _example _example_detail 300 ; The density was measured at some unspecified temperature below room temperature. ; _definition ; Temperature in kelvins below which _exptl_crystal_density_meas was determined. _exptl_crystal_density_meas_temp_gt and _exptl_crystal_density_meas_temp_lt should not be used for reporting new work, for which the correct temperature of measurement should be given. These items are intended for use in reporting information stored in databases or archives which would be misleading if reported under _exptl_crystal_density_meas_temp. ; data_exptl_crystal_density_method _name '_exptl_crystal_density_method' _category exptl_crystal _type char _list both _list_reference '_exptl_crystal_id' loop_ _example 'flotation in aqueous KI' 'not measured' 'Berman density torsion balance' _definition ; The method used to measure _exptl_crystal_density_meas. ; data_exptl_crystal_description _name '_exptl_crystal_description' _category exptl_crystal _type char _list both _list_reference '_exptl_crystal_id' _definition ; A description of the quality and habit of the crystal. The crystal dimensions should not normally be reported here; use instead _exptl_crystal_size_ for the gross dimensions of the crystal and _exptl_crystal_face_ to describe the relationship between individual faces. ; data_exptl_crystal_F_000 _name '_exptl_crystal_F_000' _category exptl_crystal _type numb _list both _list_reference '_exptl_crystal_id' _enumeration_range 0.0: _definition ; The effective number of electrons in the crystal unit cell contributing to F(000). This may contain dispersion contributions and is calculated as F(000) = [ (sum f~r~)^2^ + (sum f~i~)^2^ ]^1/2^ f~r~ = real part of the scattering factors at theta = 0 f~i~ = imaginary part of the scattering factors at theta = 0 the sum is taken over each atom in the unit cell ; data_exptl_crystal_id _name '_exptl_crystal_id' _category exptl_crystal _type char _list yes _list_mandatory yes loop_ _list_link_child '_diffrn_refln_crystal_id' '_refln_crystal_id' _definition ; Code identifying each crystal if multiple crystals are used. It is used to link with _diffrn_refln_crystal_id in the intensity measurements and with _refln_crystal_id in the _refln_ list. ; data_exptl_crystal_preparation _name '_exptl_crystal_preparation' _category exptl_crystal _type char _list both _list_reference '_exptl_crystal_id' _example 'mounted in an argon-filled quartz capillary' _definition ; Details of crystal growth and preparation of the crystal (e.g. mounting) prior to the intensity measurements. ; data_exptl_crystal_pressure_history _name '_exptl_crystal_pressure_history' _category exptl_crystal _type char _list both _list_reference '_exptl_crystal_id' _definition ; Relevant details concerning the pressure history of the sample. ; data_exptl_crystal_recrystallization_method _name '_exptl_crystal_recrystallization_method' _category exptl_crystal _type char _definition ; Describes the method used to recrystallize the sample. Sufficient details should be given for the procedure to be repeated. The temperature or temperatures should be given as well as details of the solvent, flux or carrier gas with concentrations or pressures and ambient atmosphere. ; data_exptl_crystal_size_ loop_ _name '_exptl_crystal_size_length' '_exptl_crystal_size_max' '_exptl_crystal_size_mid' '_exptl_crystal_size_min' '_exptl_crystal_size_rad' _category exptl_crystal _type numb _list both _list_reference '_exptl_crystal_id' _enumeration_range 0.0: _units mm _units_detail 'millimetres' _definition ; The maximum, medial and minimum dimensions in millimetres of the crystal. If the crystal is a sphere, then the *_rad item is its radius. If the crystal is a cylinder, then the *_rad item is its radius and the *_length item is its length. These may appear in a list with _exptl_crystal_id if multiple crystals are used in the experiment. ; data_exptl_crystal_thermal_history _name '_exptl_crystal_thermal_history' _category exptl_crystal _type char _list both _list_reference '_exptl_crystal_id' _definition ; Relevant details concerning the thermal history of the sample. ; ######################## ## EXPTL_CRYSTAL_FACE ## ######################## data_exptl_crystal_face_[] _name '_exptl_crystal_face_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _exptl_crystal_face_index_h _exptl_crystal_face_index_k _exptl_crystal_face_index_l _exptl_crystal_face_perp_dist 0 -1 -2 .18274 1 0 -2 .17571 -1 1 -2 .17845 -2 1 0 .21010 -1 0 2 .18849 1 -1 2 .20605 2 -1 0 .24680 -1 2 0 .19688 0 1 2 .15206 ; ; Example 1 - based on structure PAWD2 of Vittal & Dean [Acta Cryst. (1996), C52, 1180-1182]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the EXPTL_CRYSTAL_FACE category record details of the crystal faces. ; data_exptl_crystal_face_diffr_ loop_ _name '_exptl_crystal_face_diffr_chi' '_exptl_crystal_face_diffr_kappa' '_exptl_crystal_face_diffr_phi' '_exptl_crystal_face_diffr_psi' _category exptl_crystal_face _type numb _list yes _list_reference '_exptl_crystal_face_index_' _units deg _units_detail 'degrees' _definition ; The goniometer angle settings in degrees when the perpendicular to the specified crystal face is aligned along a specified direction (e.g. the bisector of the incident and reflected beams in an optical goniometer). ; data_exptl_crystal_face_index_ loop_ _name '_exptl_crystal_face_index_h' '_exptl_crystal_face_index_k' '_exptl_crystal_face_index_l' _category exptl_crystal_face _type numb _list yes _list_mandatory yes _definition ; Miller indices of the crystal face associated with the value _exptl_crystal_face_perp_dist. ; data_exptl_crystal_face_perp_dist _name '_exptl_crystal_face_perp_dist' _category exptl_crystal_face _type numb _list yes _list_reference '_exptl_crystal_face_index_' _enumeration_range 0.0: _units mm _units_detail 'millimetres' _definition ; The perpendicular distance in millimetres from the face to the centre of rotation of the crystal. ; ########## ## GEOM ## ########## data_geom_[] _name '_geom_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _geom_special_details ; All esds (except the esd in the dihedral angle between two l.s. planes) are estimated using the full covariance matrix. The cell esds are taken into account individually in the estimation of esds in distances, angles and torsion angles; correlations between esds in cell parameters are only used when they are defined by crystal symmetry. An approximate (isotropic) treatment of cell esds is used for estimating esds involving l.s. planes. ; ; ; Example 1 - based on data set bagan of Yamane & DiSalvo [Acta Cryst. (1996), C52, 760-761]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the GEOM and related (GEOM_ANGLE, GEOM_BOND, GEOM_CONTACT, GEOM_HBOND and GEOM_TORSION) categories record details about the molecular and crystal geometry as calculated from the ATOM, CELL and SYMMETRY data. Geometry data are usually redundant, in that they can be calculated from other more fundamental quantities in the data block. However, they serve the dual purposes of providing a check on the correctness of both sets of data and of enabling the most important geometric data to be identified for publication by setting the appropriate publication flag. ; data_geom_special_details _name '_geom_special_details' _category geom _type char _definition ; The description of geometrical information not covered by the existing data names in the geometry categories, such as least-squares planes. ; ################ ## GEOM_ANGLE ## ################ data_geom_angle_[] _name '_geom_angle_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _geom_angle_atom_site_label_1 _geom_angle_atom_site_label_2 _geom_angle_atom_site_label_3 _geom_angle _geom_angle_site_symmetry_1 _geom_angle_site_symmetry_2 _geom_angle_site_symmetry_3 _geom_angle_publ_flag C2 O1 C5 111.6(2) 1_555 1_555 1_555 yes O1 C2 C3 110.9(2) 1_555 1_555 1_555 yes O1 C2 O21 122.2(3) 1_555 1_555 1_555 yes C3 C2 O21 127.0(3) 1_555 1_555 1_555 yes C2 C3 N4 101.3(2) 1_555 1_555 1_555 yes C2 C3 C31 111.3(2) 1_555 1_555 1_555 yes C2 C3 H3 107(1) 1_555 1_555 1_555 no N4 C3 C31 116.7(2) 1_555 1_555 1_555 yes # - - - - data truncated for brevity - - - - ; ; Example 1 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the GEOM_ANGLE category record details about the bond angles as calculated from the ATOM, CELL and SYMMETRY data. ; data_geom_angle _name '_geom_angle' _category geom_angle _type numb _type_conditions esd _list yes _list_reference '_geom_angle_atom_site_label_' _units deg _units_detail 'degrees' _definition ; Angle in degrees defined by the three sites _geom_angle_atom_site_label_1, *_2 and *_3. The site at *_2 is at the apex of the angle. ; data_geom_angle_atom_site_label_ loop_ _name '_geom_angle_atom_site_label_1' '_geom_angle_atom_site_label_2' '_geom_angle_atom_site_label_3' _category geom_angle _type char _list yes _list_mandatory yes _list_link_parent '_atom_site_label' _definition ; The labels of the three atom sites which define the angle given by _geom_angle. These must match labels specified as _atom_site_label in the atom list. Label 2 identifies the site at the apex of the angle. ; data_geom_angle_publ_flag _name '_geom_angle_publ_flag' _category geom_angle _type char _list yes _list_reference '_geom_angle_atom_site_label_' loop_ _enumeration _enumeration_detail no 'do not include angle in special list' n 'abbreviation for "no"' yes 'do include angle in special list' y 'abbreviation for "yes"' _enumeration_default no _definition ; This code signals whether the angle is referred to in a publication or should be placed in a table of significant angles. ; data_geom_angle_site_symmetry_ loop_ _name '_geom_angle_site_symmetry_1' '_geom_angle_site_symmetry_2' '_geom_angle_site_symmetry_3' _category geom_angle _type char _list yes _list_reference '_geom_angle_atom_site_label_' loop_ _example _example_detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' _definition ; The symmetry code of each atom site as the symmetry-equivalent position number 'n' and the cell translation number 'klm'. These numbers are combined to form the code 'n klm' or n_klm. The character string n_klm is composed as follows: n refers to the symmetry operation that is applied to the coordinates stored in _atom_site_fract_x, _atom_site_fract_y and _atom_site_fract_z. It must match a number given in _space_group_symop_id. k, l and m refer to the translations that are subsequently applied to the symmetry-transformed coordinates to generate the atom used in calculating the angle. These translations (x,y,z) are related to (k,l,m) by the relations k = 5 + x l = 5 + y m = 5 + z By adding 5 to the translations, the use of negative numbers is avoided. ; ############### ## GEOM_BOND ## ############### data_geom_bond_[] _name '_geom_bond_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _geom_bond_atom_site_label_1 _geom_bond_atom_site_label_2 _geom_bond_distance _geom_bond_site_symmetry_1 _geom_bond_site_symmetry_2 _geom_bond_publ_flag O1 C2 1.342(4) 1_555 1_555 yes O1 C5 1.439(3) 1_555 1_555 yes C2 C3 1.512(4) 1_555 1_555 yes C2 O21 1.199(4) 1_555 1_555 yes C3 N4 1.465(3) 1_555 1_555 yes C3 C31 1.537(4) 1_555 1_555 yes C3 H3 1.00(3) 1_555 1_555 no N4 C5 1.472(3) 1_555 1_555 yes # - - - - data truncated for brevity - - - - ; ; Example 1 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the GEOM_BOND category record details about bonds as calculated from the ATOM, CELL and SYMMETRY data. ; data_geom_bond_atom_site_label_ loop_ _name '_geom_bond_atom_site_label_1' '_geom_bond_atom_site_label_2' _category geom_bond _type char _list yes _list_mandatory yes _list_link_parent '_atom_site_label' _definition ; The labels of two atom sites that form a bond. These must match labels specified as _atom_site_label in the atom list. ; data_geom_bond_distance _name '_geom_bond_distance' _category geom_bond _type numb _type_conditions esd _list yes _list_reference '_geom_bond_atom_site_label_' _enumeration_range 0.0: _units A _units_detail 'angstroms' _definition ; The intramolecular bond distance in angstroms. ; data_geom_bond_publ_flag _name '_geom_bond_publ_flag' _category geom_bond _type char _list yes _list_reference '_geom_bond_atom_site_label_' loop_ _enumeration _enumeration_detail no 'do not include bond in special list' n 'abbreviation for "no"' yes 'do include bond in special list' y 'abbreviation for "yes"' _enumeration_default no _definition ; This code signals whether the bond distance is referred to in a publication or should be placed in a list of significant bond distances. ; data_geom_bond_site_symmetry_ loop_ _name '_geom_bond_site_symmetry_1' '_geom_bond_site_symmetry_2' _category geom_bond _type char _list yes _list_reference '_geom_bond_atom_site_label_' loop_ _example _example_detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' _definition ; The symmetry code of each atom site as the symmetry-equivalent position number 'n' and the cell translation number 'klm'. These numbers are combined to form the code 'n klm' or n_klm. The character string n_klm is composed as follows: n refers to the symmetry operation that is applied to the coordinates stored in _atom_site_fract_x, _atom_site_fract_y and _atom_site_fract_z. It must match a number given in _space_group_symop_id. k, l and m refer to the translations that are subsequently applied to the symmetry-transformed coordinates to generate the atom used in calculating the bond. These translations (x,y,z) are related to (k,l,m) by the relations k = 5 + x l = 5 + y m = 5 + z By adding 5 to the translations, the use of negative numbers is avoided. ; data_geom_bond_valence _name '_geom_bond_valence' _category geom_bond _type numb _list yes _list_reference '_geom_bond_atom_site_label_' _definition ; The bond valence calculated from _geom_bond_distance. ; ################## ## GEOM_CONTACT ## ################## data_geom_contact_[] _name '_geom_contact_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _geom_contact_atom_site_label_1 _geom_contact_atom_site_label_2 _geom_contact_distance _geom_contact_site_symmetry_1 _geom_contact_site_symmetry_2 _geom_contact_publ_flag O(1) O(2) 2.735(3) . . yes H(O1) O(2) 1.82 . . no ; ; Example 1 - based on data set CLPHO6 of Ferguson, Ruhl, McKervey & Browne [Acta Cryst. (1992), C48, 2262-2264]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the GEOM_CONTACT category record details about interatomic contacts as calculated from the ATOM, CELL and SYMMETRY data. ; data_geom_contact_atom_site_label_ loop_ _name '_geom_contact_atom_site_label_1' '_geom_contact_atom_site_label_2' _category geom_contact _type char _list yes _list_mandatory yes _list_link_parent '_atom_site_label' _definition ; The labels of two atom sites that are within contact distance. The labels must match _atom_site_label codes in the atom list. ; data_geom_contact_distance _name '_geom_contact_distance' _category geom_contact _type numb _type_conditions esd _list yes _list_reference '_geom_contact_atom_site_label_' _enumeration_range 0.0: _units A _units_detail 'angstroms' _definition ; The interatomic contact distance in angstroms. ; data_geom_contact_publ_flag _name '_geom_contact_publ_flag' _category geom_contact _type char _list yes _list_reference '_geom_contact_atom_site_label_' loop_ _enumeration _enumeration_detail no 'do not include distance in special list' n 'abbreviation for "no"' yes 'do include distance in special list' y 'abbreviation for "yes"' _enumeration_default no _definition ; This code signals whether the contact distance is referred to in a publication or should be placed in a list of significant contact distances. ; data_geom_contact_site_symmetry_ loop_ _name '_geom_contact_site_symmetry_1' '_geom_contact_site_symmetry_2' _category geom_contact _type char _list yes _list_reference '_geom_contact_atom_site_label_' loop_ _example _example_detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' _definition ; The symmetry code of each atom site as the symmetry-equivalent position number 'n' and the cell translation number 'klm'. These numbers are combined to form the code 'n klm' or n_klm. The character string n_klm is composed as follows: n refers to the symmetry operation that is applied to the coordinates stored in _atom_site_fract_x, _atom_site_fract_y and _atom_site_fract_z. It must match a number given in _space_group_symop_id. k, l and m refer to the translations that are subsequently applied to the symmetry-transformed coordinates to generate the atom used in calculating the contact. These translations (x,y,z) are related to (k,l,m) by the relations k = 5 + x l = 5 + y m = 5 + z By adding 5 to the translations, the use of negative numbers is avoided. ; ################ ## GEOM_HBOND ## ################ data_geom_hbond_[] _name '_geom_hbond_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _geom_hbond_atom_site_label_D _geom_hbond_atom_site_label_H _geom_hbond_atom_site_label_A _geom_hbond_distance_DH _geom_hbond_distance_HA _geom_hbond_distance_DA _geom_hbond_angle_DHA _geom_hbond_publ_flag N6 HN6 OW 0.888(8) 1.921(12) 2.801(8) 169.6(8) yes OW HO2 O7 0.917(6) 1.923(12) 2.793(8) 153.5(8) yes OW HO1 N10 0.894(8) 1.886(11) 2.842(8) 179.7(9) yes ; ; Example 1 - based on C~14~H~13~ClN~2~O.H~2~O, reported by Palmer, Puddle & Lisgarten [Acta Cryst. (1993), C49, 1777-1779]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the GEOM_HBOND category record details about hydrogen bonds as calculated from the ATOM, CELL and SYMMETRY data. ; data_geom_hbond_angle_DHA _name '_geom_hbond_angle_DHA' _category geom_hbond _type numb _type_conditions esd _list yes _list_reference '_geom_hbond_atom_site_label_' _units deg _units_detail 'degrees' _definition ; Angle in degrees defined by the three sites _geom_hbond_atom_site_label_D, *_H and *_A. The site at *_H (the hydrogen atom participating in the interaction) is at the apex of the angle. ; data_geom_hbond_atom_site_label_ loop_ _name '_geom_hbond_atom_site_label_D' '_geom_hbond_atom_site_label_H' '_geom_hbond_atom_site_label_A' _category geom_hbond _type char _list yes _list_mandatory yes _list_link_parent '_atom_site_label' _definition ; The labels of three atom sites (respectively, the donor atom, hydrogen atom and acceptor atom) participating in a hydrogen bond. These must match labels specified as _atom_site_label in the atom list. ; data_geom_hbond_distance_ loop_ _name '_geom_hbond_distance_DH' '_geom_hbond_distance_HA' '_geom_hbond_distance_DA' _category geom_hbond _type numb _type_conditions esd _list yes _list_reference '_geom_hbond_atom_site_label_' _enumeration_range 0.0: _units A _units_detail 'angstroms' _definition ; Distances in angstroms between the donor and hydrogen (*_DH), hydrogen and acceptor (*_HA) and donor and acceptor (*_DA) sites in a hydrogen bond. ; data_geom_hbond_publ_flag _name '_geom_hbond_publ_flag' _category geom_hbond _type char _list yes _list_reference '_geom_hbond_atom_site_label_' loop_ _enumeration _enumeration_detail no 'do not include bond in special list' n 'abbreviation for "no"' yes 'do include bond in special list' y 'abbreviation for "yes"' _enumeration_default no _definition ; This code signals whether the hydrogen-bond information is referred to in a publication or should be placed in a table of significant hydrogen-bond geometry. ; data_geom_hbond_site_symmetry_ loop_ _name '_geom_hbond_site_symmetry_D' '_geom_hbond_site_symmetry_H' '_geom_hbond_site_symmetry_A' _category geom_hbond _type char _list yes _list_reference '_geom_hbond_atom_site_label_' loop_ _example _example_detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' _definition ; The symmetry code of each atom site as the symmetry-equivalent position number 'n' and the cell translation number 'klm'. These numbers are combined to form the code 'n klm' or n_klm. The character string n_klm is composed as follows: n refers to the symmetry operation that is applied to the coordinates stored in _atom_site_fract_x, _atom_site_fract_y and _atom_site_fract_z. It must match a number given in _space_group_symop_id. k, l and m refer to the translations that are subsequently applied to the symmetry-transformed coordinates to generate the atom used in calculating the hydrogen bond. These translations (x,y,z) are related to (k,l,m) by the relations k = 5 + x l = 5 + y m = 5 + z By adding 5 to the translations, the use of negative numbers is avoided. ; ################## ## GEOM_TORSION ## ################## data_geom_torsion_[] _name '_geom_torsion_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _geom_torsion_atom_site_label_1 _geom_torsion_atom_site_label_2 _geom_torsion_atom_site_label_3 _geom_torsion_atom_site_label_4 _geom_torsion _geom_torsion_site_symmetry_1 _geom_torsion_site_symmetry_2 _geom_torsion_site_symmetry_3 _geom_torsion_site_symmetry_4 _geom_torsion_publ_flag C(9) O(2) C(7) C(2) 71.8(2) . . . . yes C(7) O(2) C(9) C(10) -168.0(3) . . . 2_666 yes C(10) O(3) C(8) C(6) -167.7(3) . . . . yes C(8) O(3) C(10) C(9) -69.7(2) . . . 2_666 yes O(1) C(1) C(2) C(3) -179.5(4) . . . . no O(1) C(1) C(2) C(7) -0.6(1) . . . . no ; ; Example 1 - based on data set CLPHO6 of Ferguson, Ruhl, McKervey & Browne [Acta Cryst. (1992), C48, 2262-2264]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the GEOM_TORSION category record details about interatomic torsion angles as calculated from the ATOM, CELL and SYMMETRY data. ; data_geom_torsion _name '_geom_torsion' _category geom_torsion _type numb _type_conditions esd _list yes _list_reference '_geom_torsion_atom_site_label_' _units deg _units_detail 'degrees' _definition ; The torsion angle in degrees bounded by the four atom sites identified by the _geom_torsion_atom_site_label_ codes. These must match labels specified as _atom_site_label in the atom list. The torsion-angle definition should be that of Klyne and Prelog. Ref: Klyne, W. & Prelog, V. (1960). Experientia, 16, 521-523. ; data_geom_torsion_atom_site_label_ loop_ _name '_geom_torsion_atom_site_label_1' '_geom_torsion_atom_site_label_2' '_geom_torsion_atom_site_label_3' '_geom_torsion_atom_site_label_4' _category geom_torsion _type char _list yes _list_mandatory yes _list_link_parent '_atom_site_label' _definition ; The labels of the four atom sites which define the torsion angle specified by _geom_torsion. These must match codes specified as _atom_site_label in the atom list. The torsion-angle definition should be that of Klyne and Prelog. The vector direction *_label_2 to *_label_3 is the viewing direction, and the torsion angle is the angle of twist required to superimpose the projection of the vector between site 2 and site 1 onto the projection of the vector between site 3 and site 4. Clockwise torsions are positive, anticlockwise torsions are negative. Ref: Klyne, W. & Prelog, V. (1960). Experientia, 16, 521-523. ; data_geom_torsion_publ_flag _name '_geom_torsion_publ_flag' _category geom_torsion _type char _list yes _list_reference '_geom_torsion_atom_site_label_' loop_ _enumeration _enumeration_detail no 'do not include angle in special list' n 'abbreviation for "no"' yes 'do include angle in special list' y 'abbreviation for "yes"' _enumeration_default no _definition ; This code signals whether the torsion angle is referred to in a publication or should be placed in a table of significant torsion angles. ; data_geom_torsion_site_symmetry_ loop_ _name '_geom_torsion_site_symmetry_1' '_geom_torsion_site_symmetry_2' '_geom_torsion_site_symmetry_3' '_geom_torsion_site_symmetry_4' _category geom_torsion _type char _list yes _list_reference '_geom_torsion_atom_site_label_' loop_ _example _example_detail . 'no symmetry or translation to site' 4 '4th symmetry operation applied' 7_645 '7th symm. posn.; +a on x; -b on y' _definition ; The symmetry code of each atom site as the symmetry-equivalent position number 'n' and the cell translation number 'klm'. These numbers are combined to form the code 'n klm' or n_klm. The character string n_klm is composed as follows: n refers to the symmetry operation that is applied to the coordinates stored in _atom_site_fract_x, _atom_site_fract_y and _atom_site_fract_z. It must match a number given in _space_group_symop_id. k, l and m refer to the translations that are subsequently applied to the symmetry-transformed coordinates to generate the atom used in calculating the angle. These translations (x,y,z) are related to (k,l,m) by the relations k = 5 + x l = 5 + y m = 5 + z By adding 5 to the translations, the use of negative numbers is avoided. ; ############# ## JOURNAL ## ############# data_journal_[] _name '_journal_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _journal_date_recd_electronic 91-04-15 _journal_date_from_coeditor 91-04-18 _journal_date_accepted 91-04-18 _journal_date_printers_first 91-08-07 _journal_date_proofs_out 91-08-07 _journal_coeditor_code HL0007 _journal_techeditor_code C910963 _journal_coden_ASTM ACSCEE _journal_name_full 'Acta Crystallographica Section C' _journal_year 1991 _journal_volume 47 _journal_issue NOV91 _journal_page_first 2276 _journal_page_last 2277 ; ; Example 1 - based on Acta Cryst. file for entry HL0007 [Willis, Beckwith & Tozer (1991). Acta Cryst. C47, 2276-2277]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the JOURNAL category record details about the book-keeping by the journal staff when processing a CIF submitted for publication. The creator of a CIF will not normally specify these data items. The data names are not defined in the dictionary because they are for journal use only. ; data_journal_ loop_ _name '_journal_coden_ASTM' '_journal_coden_Cambridge' '_journal_coeditor_address' '_journal_coeditor_code' '_journal_coeditor_email' '_journal_coeditor_fax' '_journal_coeditor_name' '_journal_coeditor_notes' '_journal_coeditor_phone' '_journal_data_validation_number' '_journal_date_accepted' '_journal_date_from_coeditor' '_journal_date_to_coeditor' '_journal_date_printers_final' '_journal_date_printers_first' '_journal_date_proofs_in' '_journal_date_proofs_out' '_journal_date_recd_copyright' '_journal_date_recd_electronic' '_journal_date_recd_hard_copy' '_journal_issue' '_journal_language' '_journal_name_full' '_journal_page_first' '_journal_page_last' '_journal_paper_category' '_journal_suppl_publ_number' '_journal_suppl_publ_pages' '_journal_techeditor_address' '_journal_techeditor_code' '_journal_techeditor_email' '_journal_techeditor_fax' '_journal_techeditor_name' '_journal_techeditor_notes' '_journal_techeditor_phone' '_journal_volume' '_journal_year' _category journal _type char _definition ; Data items specified by the journal staff. ; ################### ## JOURNAL_INDEX ## ################### data_journal_index_[] _name '_journal_index_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _journal_index_type _journal_index_term _journal_index_subterm O C16H19NO4 . S alkaloids (-)-norcocaine S (-)-norcocaine . S ; [2R,3S-(2\b,3\b)]-methyl 3-(benzoyloxy)-8-azabicyclo[3.2.1]octane-2-carboxylate ; . ; ; Example 1 - based on a paper by Zhu, Reynolds, Klein & Trudell [Acta Cryst. (1994), C50, 2067-2069]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the JOURNAL_INDEX category are used to list terms used to generate the journal indexes. The creator of a CIF will not normally specify these data items. ; data_journal_index_ loop_ _name '_journal_index_subterm' '_journal_index_term' '_journal_index_type' _category journal_index _type char _definition ; Indexing terms supplied by the journal staff. ; ########## ## PUBL ## ########## data_publ_[] _name '_publ_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _publ_section_title ; trans-3-Benzoyl-2-(tert-butyl)-4-(iso-butyl)- 1,3-oxazolidin-5-one ; _publ_section_abstract ; The oxazolidinone ring is a shallow envelope conformation with the tert-butyl and iso-butyl groups occupying trans-positions with respect to the ring. The angles at the N atom sum to 356.2\%, indicating a very small degree of pyramidalization at this atom. This is consistent with electron delocalization between the N atom and the carbonyl centre [N-C=O = 1.374(3)\%A]. ; ; ; Example 1 - based on Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _publ_section_title ; Hemiasterlin methyl ester ; _publ_section_title_footnote ; IUPAC name: methyl 2,5-dimethyl-4-{2-[3-methyl- 2-methylamino-3-(N-methylbenzo[b]pyrrol- 3-yl)butanamido]-3,3-dimethyl-N-methyl- butanamido}-2-hexenoate. ; ; ; Example 2 - based on C~31~H~48~N~4~O~4~, reported by Coleman, Patrick, Andersen & Rettig [Acta Cryst. (1996), C52, 1525-1527]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the PUBL category are used when submitting a manuscript for publication. They refer either to the paper as a whole, or to specific named elements within a paper (such as the title and abstract, or the Comment and Experimental sections of Acta Crystallographica Section C). The data items in the PUBL_BODY category should be used for the text of other submissions. Typically, each journal will supply a list of the specific items it requires in its Notes for Authors. ; data_publ_contact_author _name '_publ_contact_author' _category publ _type char loop_ _example ; Professor George Ferguson Department of Chemistry and Biochemistry University of Guelph Ontario Canada N1G 2W1 ; _definition ; The name and address of the author submitting the manuscript and data block. This is the person contacted by the journal editorial staff. It is preferable to use the separate data items _publ_contact_author_name and _publ_contact_author_address. ; data_publ_contact_author_address _name '_publ_contact_author_address' _category publ _type char _example ; Department of Chemistry and Biochemistry University of Guelph Ontario Canada N1G 2W1 ; _definition ; The address of the author submitting the manuscript and data block. This is the person contacted by the journal editorial staff. ; data_publ_contact_author_email _name '_publ_contact_author_email' _category publ _type char loop_ _example name@host.domain.country bm@iucr.org _definition ; E-mail address in a form recognizable to international networks. The format of e-mail addresses is given in Section 3.4, Address Specification, of Internet Message Format, RFC 2822, P. Resnick (Editor), Network Standards Group, April 2001. ; data_publ_contact_author_fax _name '_publ_contact_author_fax' _category publ _type char loop_ _example '12(34)9477334' '12()349477334' _definition ; Facsimile telephone number of the author submitting the manuscript and data block. The recommended style is the international dialing prefix, followed by the area code in parentheses, followed by the local number with no spaces. The earlier convention of including the international dialing prefix in parentheses is no longer recommended. ; data_publ_contact_author_id_iucr _name '_publ_contact_author_id_iucr' _category publ _type char _example 2985 _definition ; Identifier in the IUCr contact database of the author submitting the manuscript and data block. This identifier may be available from the World Directory of Crystallographers (http://wdc.iucr.org). ; data_publ_contact_author_name _name '_publ_contact_author_name' _category publ _type char _example 'Professor George Ferguson' _definition ; The name of the author submitting the manuscript and data block. This is the person contacted by the journal editorial staff. ; data_publ_contact_author_phone _name '_publ_contact_author_phone' _category publ _type char loop_ _example '12(34)9477330' '12()349477330' '12(34)9477330x5543' _definition ; Telephone number of the author submitting the manuscript and data block. The recommended style is the international dialing prefix, followed by the area code in parentheses, followed by the local number and any extension number prefixed by 'x', with no spaces. The earlier convention of including the international dialing prefix in parentheses is no longer recommended. ; data_publ_contact_letter _name '_publ_contact_letter' _category publ _type char _definition ; A letter submitted to the journal editor by the contact author. ; data_publ_manuscript_creation _name '_publ_manuscript_creation' _category publ _type char _example 'Tex file created by FrameMaker on a Sun 3/280' _definition ; A description of the word-processor package and computer used to create the word-processed manuscript stored as _publ_manuscript_processed. ; data_publ_manuscript_processed _name '_publ_manuscript_processed' _category publ _type char _definition ; The full manuscript of a paper (excluding possibly the figures and the tables) output in ASCII characters from a word processor. Information about the generation of this data item must be specified in the data item _publ_manuscript_creation. ; data_publ_manuscript_text _name '_publ_manuscript_text' _category publ _type char _definition ; The full manuscript of a paper (excluding figures and possibly the tables) output as standard ASCII text. ; data_publ_requested_category _name '_publ_requested_category' _category publ _type char loop_ _enumeration _enumeration_detail FA 'Full article' FI 'Full submission - inorganic (Acta C)' FO 'Full submission - organic (Acta C)' FM 'Full submission - metal-organic (Acta C)' CI 'CIF-access paper - inorganic (Acta C) (no longer in use)' CO 'CIF-access paper - organic (Acta C) (no longer in use)' CM 'CIF-access paper - metal-organic (Acta C) (no longer in use)' EI 'Electronic submission - inorganic (Acta E)' EO 'Electronic submission - organic (Acta E)' EM 'Electronic submission - metal-organic (Acta E)' AD 'Addenda and Errata (Acta C, Acta E)' SC 'Short communication' _enumeration_default FA _definition ; The category of paper submitted. For submission to Acta Crystallographica Section C or Acta Crystallographica Section E, ONLY those codes indicated for use with those journals should be used. ; data_publ_requested_coeditor_name _name '_publ_requested_coeditor_name' _category publ _type char _definition ; The name of the co-editor whom the authors would like to handle the submitted manuscript. ; data_publ_requested_journal _name '_publ_requested_journal' _category publ _type char _definition ; The name of the journal to which the manuscript is being submitted. ; data_publ_section_ loop_ _name '_publ_section_title' '_publ_section_title_footnote' '_publ_section_synopsis' '_publ_section_abstract' '_publ_section_comment' '_publ_section_introduction' '_publ_section_experimental' '_publ_section_exptl_prep' '_publ_section_exptl_refinement' '_publ_section_exptl_solution' '_publ_section_discussion' '_publ_section_acknowledgements' '_publ_section_references' '_publ_section_figure_captions' '_publ_section_table_legends' _category publ _type char _definition ; The sections of a manuscript if submitted in parts. As an alternative, see _publ_manuscript_text and _publ_manuscript_processed. The _publ_section_exptl_prep, _publ_section_exptl_refinement and _publ_section_exptl_solution items are preferred for separating the chemical preparation, refinement and structure solution aspects of the experimental description. ; ################# ## PUBL_AUTHOR ## ################# data_publ_author_[] _name '_publ_author_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _publ_author_name _publ_author_address 'Willis, Anthony C.' ; Research School of Chemistry Australian National University GPO Box 4 Canberra, ACT Australia 2601 ; ; ; Example 1 - based on Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the PUBL_AUTHOR category record details of the authors of a manuscript submitted for publication. ; data_publ_author_address _name '_publ_author_address' _category publ_author _type char _list both _list_reference '_publ_author_name' _example ; Department Institute Street City and postcode COUNTRY ; _definition ; The address of a publication author. If there is more than one author, this will be looped with _publ_author_name. ; data_publ_author_footnote _name '_publ_author_footnote' _category publ_author _type char _list both _list_reference '_publ_author_name' loop_ _example 'On leave from U. Western Australia' 'Also at Department of Biophysics' _definition ; A footnote accompanying an author's name in the list of authors of a paper. Typically indicates sabbatical address, additional affiliations or date of decease. ; data_publ_author_email _name '_publ_author_email' _category publ_author _type char _list both _list_reference '_publ_author_name' loop_ _example name@host.domain.country bm@iucr.org _definition ; The e-mail address of a publication author. If there is more than one author, this will be looped with _publ_author_name. The format of e-mail addresses is given in Section 3.4, Address Specification, of Internet Message Format, RFC 2822, P. Resnick (Editor), Network Standards Group, April 2001. ; data_publ_author_id_iucr _name '_publ_author_id_iucr' _category publ_author _type char _list both _example 2985 _definition ; Identifier in the IUCr contact database of a publication author. This identifier may be available from the World Directory of Crystallographers (http://wdc.iucr.org). ; data_publ_author_name _name '_publ_author_name' _category publ_author _type char _list both _list_mandatory yes loop_ _example 'Bleary, Percival R.' "O'Neil, F.K." 'Van den Bossche, G.' 'Yang, D.-L.' 'Simonov, Yu.A.' 'M\"uller, H.A.' 'Ross II, C.R.' _definition ; The name of a publication author. If there are multiple authors, this will be looped with _publ_author_address. The family name(s), followed by a comma and including any dynastic components, precedes the first names or initials. ; ############### ## PUBL_BODY ## ############### data_publ_body_[] _name '_publ_body_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _publ_body_element _publ_body_label _publ_body_title _publ_body_format _publ_body_contents section 1 Introduction cif ; X-ray diffraction from a crystalline material provides information on the thermally and spatially averaged electron density in the crystal... ; section 2 Theory tex ; In the rigid-atom approximation, the dynamic electron density of an atom is described by the convolution product of the static atomic density and a probability density function, $\rho_{dyn}(\bf r) = \rho_{stat}(\bf r) * P(\bf r). \eqno(1)$ ; ; ; Example 1 - based on a paper by R. Restori & D. Schwarzenbach [Acta Cryst. (1996), A52, 369-378]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _publ_body_element _publ_body_label _publ_body_title _publ_body_contents section 3 ; The two-channel method for retrieval of the deformation electron density ; . subsection 3.1 'The two-channel entropy S[\D\r(r)]' ; As the wide dynamic range involved in the total electron density... ; subsection 3.2 'Uniform vs informative prior model densities' . subsubsection 3.2.1 'Use of uniform models' ; Straightforward algebra leads to expressions analogous to... ; ; ; Example 2 - based on a paper by R. J. Papoular, Y. Vekhter & P. Coppens [Acta Cryst. (1996), A52, 397-407]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the PUBL_BODY category permit the labelling of different text sections within the body of a paper. Note that these should not be used in a paper which has a standard format with sections tagged by specific data names (such as in Acta Crystallographica Section C). Typically, each journal will supply a list of the specific items it requires in its Notes for Authors. ; data_publ_body_contents _name '_publ_body_contents' _category publ_body _type char _list yes _list_reference '_publ_body_label' _definition ; A text section of a paper. ; data_publ_body_element _name '_publ_body_element' _category publ_body _type char _list yes _list_reference '_publ_body_label' loop_ _enumeration section subsection subsubsection appendix footnote _definition ; The functional role of the associated text section. ; data_publ_body_format _name '_publ_body_format' _category publ_body _type char _list yes _list_reference '_publ_body_label' loop_ _enumeration _enumeration_detail ascii 'no coding for special symbols' cif 'CIF convention' latex 'LaTeX' rtf 'Rich Text Format' sgml 'SGML (ISO 8879)' tex 'TeX' troff 'troff or nroff' _enumeration_default cif _definition ; Code indicating the appropriate typesetting conventions for accented characters and special symbols in the text section. ; data_publ_body_label _name '_publ_body_label' _category publ_body _type char _list yes _list_mandatory yes _list_uniqueness '_publ_body_element' loop_ _example 1 1.1 2.1.3 _definition ; Code identifying the section of text. The combination of this with _publ_body_element must be unique. ; data_publ_body_title _name '_publ_body_title' _category publ_body _type char _list yes _list_reference '_publ_body_label' _definition ; Title of the associated section of text. ; ########################## ## PUBL_MANUSCRIPT_INCL ## ########################## data_publ_manuscript_incl_[] _name '_publ_manuscript_incl_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _publ_manuscript_incl_extra_item _publ_manuscript_incl_extra_info _publ_manuscript_incl_extra_defn # # Include Hydrogen Bonding Geometry Description # ============================================= # Name explanation standard? # ---- ----------- --------- '_geom_hbond_atom_site_label_D' 'H-bond donor' yes '_geom_hbond_atom_site_label_H' 'H-bond hydrogen' yes '_geom_hbond_atom_site_label_A' 'H-bond acceptor' yes '_geom_hbond_distance_DH' 'H-bond D-H' yes '_geom_hbond_distance_HA' 'H-bond H...A' yes '_geom_hbond_distance_DA' 'H-bond D...A' yes '_geom_hbond_angle_DHA' 'H-bond D-H...A' yes ; ; Example 1 - directive to include a hydrogen-bonding table, including cosmetic headings in comments. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _publ_manuscript_incl_extra_item _publ_manuscript_incl_extra_info _publ_manuscript_incl_extra_defn '_atom_site_symmetry_multiplicity' 'to emphasise special sites' yes '_chemical_compound_source' 'rare material, unusual source' yes '_reflns_d_resolution_high' 'limited data is a problem here' yes '_crystal_magnetic_permeability' 'unusual value for this material' no ; ; Example 2 - hypothetical example including both standard CIF data items and a non-CIF quantity which the author wishes to list. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the PUBL_MANUSCRIPT_INCL category allow the authors of a manuscript submitted for publication to list data names that should be added to the standard request list used by the journal printing software. Although these fields are primarily intended to identify CIF data items that the author wishes to include in a published paper, they can also be used to identify data names created so that non-CIF items can be included in the publication. Note that *_item names MUST be enclosed in single quotes. ; data_publ_manuscript_incl_extra_defn _name '_publ_manuscript_incl_extra_defn' _category publ_manuscript_incl _type char _list yes _list_reference '_publ_manuscript_incl_extra_item' loop_ _enumeration _enumeration_detail no 'not a standard CIF data name' n 'abbreviation for "no"' yes 'a standard CIF data name' y 'abbreviation for "yes"' _enumeration_default yes _definition ; Flags whether the corresponding data item marked for inclusion in a journal request list is a standard CIF definition or not. ; data_publ_manuscript_incl_extra_info _name '_publ_manuscript_incl_extra_info' _category publ_manuscript_incl _type char _list yes _list_reference '_publ_manuscript_incl_extra_item' _definition ; A short note indicating the reason why the author wishes the corresponding data item marked for inclusion in the journal request list to be published. ; data_publ_manuscript_incl_extra_item _name '_publ_manuscript_incl_extra_item' _category publ_manuscript_incl _type char _list yes _list_mandatory yes _definition ; Specifies the inclusion of specific data into a manuscript which are not normally requested by the journal. The values of this item are the extra data names (which MUST be enclosed in single quotes) that will be added to the journal request list. ; ############ ## REFINE ## ############ data_refine_[] _name '_refine_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _refine_special_details sfls:_F_calc_weight_full_matrix _refine_ls_structure_factor_coef F _refine_ls_matrix_type full _refine_ls_weighting_scheme calc _refine_ls_weighting_details 'w=1/(u^2^(F)+0.0004F^2^)' _refine_ls_hydrogen_treatment refxyz _refine_ls_extinction_method Zachariasen _refine_ls_extinction_coef 3514(42) _refine_ls_extinction_expression ; Larson, A. C. (1970). "Crystallographic Computing", edited by F. R. Ahmed. Eq. (22) p. 292. Copenhagen: Munksgaard. ; _refine_ls_abs_structure_details ; The absolute configuration was assigned to agree with that of its precursor l-leucine at the chiral centre C3. ; _refine_ls_number_reflns 1408 _refine_ls_number_parameters 272 _refine_ls_number_restraints 0 _refine_ls_number_constraints 0 _refine_ls_R_factor_all .038 _refine_ls_R_factor_gt .034 _refine_ls_wR_factor_all .044 _refine_ls_wR_factor_gt .042 _refine_ls_goodness_of_fit_all 1.462 _refine_ls_goodness_of_fit_gt 1.515 _refine_ls_shift/su_max .535 _refine_ls_shift/su_mean .044 _refine_diff_density_min -.108 _refine_diff_density_max .131 ; ; Example 1 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the REFINE category record details about the structure-refinement parameters. ; data_refine_diff_density_ loop_ _name '_refine_diff_density_max' '_refine_diff_density_min' '_refine_diff_density_rms' _category refine _type numb _type_conditions esd _units e_A^-3^ _units_detail 'electrons per cubic angstrom' _definition ; The largest and smallest values and the root-mean-square deviation, in electrons per angstrom cubed, of the final difference electron density. The *_rms value is measured with respect to the arithmetic mean density and is derived from summations over each grid point in the asymmetric unit of the cell. This quantity is useful for assessing the significance of *_min and *_max values, and also for defining suitable contour levels. ; data_refine_ls_abs_structure_details _name '_refine_ls_abs_structure_details' _category refine _type char _definition ; The nature of the absolute structure and how it was determined. ; data_refine_ls_abs_structure_Flack _name '_refine_ls_abs_structure_Flack' _category refine _type numb _type_conditions esd _enumeration_range 0.0:1.0 _definition ; The measure of absolute structure as defined by Flack (1983). For centrosymmetric structures, the only permitted value, if the data name is present, is 'inapplicable', represented by '.' . For noncentrosymmetric structures, the value must lie in the 99.97% Gaussian confidence interval -3u =< x =< 1 + 3u and a standard uncertainty (e.s.d.) u must be supplied. The _enumeration_range of 0.0:1.0 is correctly interpreted as meaning (0.0 - 3u) =< x =< (1.0 + 3u). Ref: Flack, H. D. (1983). Acta Cryst. A39, 876-881. ; data_refine_ls_abs_structure_Rogers _name '_refine_ls_abs_structure_Rogers' _category refine _type numb _type_conditions esd _enumeration_range -1.0:1.0 _definition ; The measure of absolute structure as defined by Rogers (1981). The value must lie in the 99.97% Gaussian confidence interval -1 -3u =< \h =< 1 + 3u and a standard uncertainty (e.s.d.) u must be supplied. The _enumeration_range of -1.0:1.0 is correctly interpreted as meaning (-1.0 - 3u) =< \h =< (1.0 + 3u). Ref: Rogers, D. (1981). Acta Cryst. A37, 734-741. ; data_refine_ls_d_res_high _name '_refine_ls_d_res_high' _category refine _type numb _enumeration_range 0.0: _units A _units_detail 'angstroms' _definition ; The smallest value in angstroms of the interplanar spacings of the reflections used in the refinement. This is called the highest resolution. ; data_refine_ls_d_res_low _name '_refine_ls_d_res_low' _category refine _type numb _enumeration_range 0.0: _units A _units_detail 'angstroms' _definition ; The largest value in angstroms of the interplanar spacings of the reflections used in the refinement. This is called the lowest resolution. ; data_refine_ls_extinction_coef _name '_refine_ls_extinction_coef' _category refine _type numb _type_conditions esd _example 3472(52) _example_detail 'Zachariasen coefficient r* = 0.347(5) E04' _definition ; The extinction coefficient used to calculate the correction factor applied to the structure-factor data. The nature of the extinction coefficient is given in the definitions of _refine_ls_extinction_expression and _refine_ls_extinction_method. For the 'Zachariasen' method it is the r* value; for the 'Becker-Coppens type 1 isotropic' method it is the 'g' value and for 'Becker-Coppens type 2 isotropic' corrections it is the 'rho' value. Note that the magnitude of these values is usually of the order of 10000. Ref: Becker, P. J. & Coppens, P. (1974). Acta Cryst. A30, 129-147, 148-153. Zachariasen, W. H. (1967). Acta Cryst. 23, 558-564. Larson, A. C. (1967). Acta Cryst. 23, 664-665. ; data_refine_ls_extinction_expression _name '_refine_ls_extinction_expression' _category refine _type char _example ; Larson, A. C. (1970). "Crystallographic Computing", edited by F. R. Ahmed. Eq. (22), p. 292. Copenhagen: Munksgaard. ; _definition ; A description of or reference to the extinction-correction equation used to apply the data item _refine_ls_extinction_coef. This information must be sufficient to reproduce the extinction-correction factors applied to the structure factors. ; data_refine_ls_extinction_method _name '_refine_ls_extinction_method' _category refine _type char _enumeration_default 'Zachariasen' loop_ _example 'B-C type 2 Gaussian isotropic' 'none' _definition ; A description of the extinction-correction method applied. This description should include information about the correction method, either 'Becker-Coppens' or 'Zachariasen'. The latter is sometimes referred to as the 'Larson' method even though it employs Zachariasen's formula. The Becker-Coppens procedure is referred to as 'type 1' when correcting secondary extinction dominated by the mosaic spread; as 'type 2' when secondary extinction is dominated by particle size and includes a primary extinction component; and as 'mixed' when there is a mixture of types 1 and 2. For the Becker-Coppens method, it is also necessary to set the mosaic distribution as either 'Gaussian' or 'Lorentzian' and the nature of the extinction as 'isotropic' or 'anisotropic'. Note that if either the 'mixed' or 'anisotropic' corrections are applied, the multiple coefficients cannot be contained in *_extinction_coef and must be listed in _refine_special_details. Ref: Becker, P. J. & Coppens, P. (1974). Acta Cryst. A30, 129-147, 148-153. Zachariasen, W. H. (1967). Acta Cryst. 23, 558-564. Larson, A. C. (1967). Acta Cryst. 23, 664-665. ; data_refine_ls_goodness_of_fit_all _name '_refine_ls_goodness_of_fit_all' _category refine _type numb _type_conditions esd _enumeration_range 0.0: _definition ; The least-squares goodness-of-fit parameter S for all reflections after the final cycle of refinement. Ideally, account should be taken of parameters restrained in the least-squares refinement. See also _refine_ls_restrained_S_ definitions. { sum { w [ Y(obs) - Y(calc) ]^2^ } }^1/2^ S = { ----------------------------------- } { Nref - Nparam } Y(obs) = the observed coefficients (see _refine_ls_structure_factor_coef) Y(calc) = the calculated coefficients (see _refine_ls_structure_factor_coef) w = the least-squares reflection weight [1/(u^2^)] u = the standard uncertainty Nref = the number of reflections used in the refinement Nparam = the number of refined parameters and the sum is taken over the specified reflections ; data_refine_ls_goodness_of_fit_gt _name '_refine_ls_goodness_of_fit_gt' _category refine _type numb _type_conditions esd _related_item '_refine_ls_goodness_of_fit_obs' _related_function alternate _enumeration_range 0.0: _definition ; The least-squares goodness-of-fit parameter S for significantly intense reflections (see _reflns_threshold_expression) after the final cycle of refinement. Ideally, account should be taken of parameters restrained in the least-squares refinement. See also _refine_ls_restrained_S_ definitions. { sum { w [ Y(obs) - Y(calc) ]^2^ } }^1/2^ S = { ----------------------------------- } { Nref - Nparam } Y(obs) = the observed coefficients (see _refine_ls_structure_factor_coef) Y(calc) = the calculated coefficients (see _refine_ls_structure_factor_coef) w = the least-squares reflection weight [1/(u^2^)] u = standard uncertainty Nref = the number of reflections used in the refinement Nparam = the number of refined parameters and the sum is taken over the specified reflections ; data_refine_ls_goodness_of_fit_obs _name '_refine_ls_goodness_of_fit_obs' _category refine _type numb _type_conditions esd _related_item '_refine_ls_goodness_of_fit_gt' _related_function replace _enumeration_range 0.0: _definition ; The least-squares goodness-of-fit parameter S for observed reflections (see _reflns_observed_criterion) after the final cycle of refinement. Ideally, account should be taken of parameters restrained in the least-squares refinement. See also _refine_ls_restrained_S_ definitions. { sum { w [ Y(obs) - Y(calc) ]^2^ } }^1/2^ S = { ----------------------------------- } { Nref - Nparam } Y(obs) = the observed coefficients (see _refine_ls_structure_factor_coef) Y(calc) = the calculated coefficients (see _refine_ls_structure_factor_coef) w = the least-squares reflection weight [1/(u^2^)] u = standard uncertainty (e.s.d.) Nref = the number of reflections used in the refinement Nparam = the number of refined parameters and the sum is taken over the specified reflections ; data_refine_ls_goodness_of_fit_ref _name '_refine_ls_goodness_of_fit_ref' _category refine _type numb _type_conditions esd _enumeration_range 0.0: _definition ; The least-squares goodness-of-fit parameter S for all reflections included in the refinement after the final cycle of refinement. Ideally, account should be taken of parameters restrained in the least-squares refinement. See also _refine_ls_restrained_S_ definitions. { sum | w | Y(obs) - Y(calc) |^2^ | }^1/2^ S = { ----------------------------------- } { Nref - Nparam } Y(obs) = the observed coefficients (see _refine_ls_structure_factor_coef) Y(calc) = the calculated coefficients (see _refine_ls_structure_factor_coef) w = the least-squares reflection weight [1/(u^2^)] u = standard uncertainty Nref = the number of reflections used in the refinement Nparam = the number of refined parameters and the sum is taken over the specified reflections ; data_refine_ls_hydrogen_treatment _name '_refine_ls_hydrogen_treatment' _category refine _type char loop_ _enumeration _enumeration_detail refall 'refined all H-atom parameters' refxyz 'refined H-atom coordinates only' refU 'refined H-atom U's only' noref 'no refinement of H-atom parameters' constr 'H-atom parameters constrained' mixed 'some constrained, some independent' undef 'H-atom parameters not defined' _enumeration_default undef _definition ; Treatment of hydrogen atoms in the least-squares refinement. ; data_refine_ls_matrix_type _name '_refine_ls_matrix_type' _category refine _type char loop_ _enumeration _enumeration_detail full 'full' fullcycle 'full with fixed elements per cycle' atomblock 'block diagonal per atom' userblock 'user-defined blocks' diagonal 'diagonal elements only' sparse 'selected elements only' _enumeration_default full _definition ; Type of matrix used to accumulate the least-squares derivatives. ; data_refine_ls_number_constraints _name '_refine_ls_number_constraints' _category refine _type numb _enumeration_range 0: _enumeration_default 0 _definition ; The number of constrained (non-refined or dependent) parameters in the least-squares process. These may be due to symmetry or any other constraint process (e.g. rigid-body refinement). See also _atom_site_constraints and _atom_site_refinement_flags. A general description of constraints may appear in _refine_special_details. ; data_refine_ls_number_parameters _name '_refine_ls_number_parameters' _category refine _type numb _enumeration_range 0: _definition ; The number of parameters refined in the least-squares process. If possible, this number should include some contribution from the restrained parameters. The restrained parameters are distinct from the constrained parameters (where one or more parameters are linearly dependent on the refined value of another). Least-squares restraints often depend on geometry or energy considerations and this makes their direct contribution to this number, and to the goodness-of-fit calculation, difficult to assess. ; data_refine_ls_number_reflns _name '_refine_ls_number_reflns' _category refine _type numb _enumeration_range 0: _definition ; The number of unique reflections contributing to the least-squares refinement calculation. ; data_refine_ls_number_restraints _name '_refine_ls_number_restraints' _category refine _type numb _enumeration_range 0: _definition ; The number of restrained parameters. These are parameters which are not directly dependent on another refined parameter. Restrained parameters often involve geometry or energy dependencies. See also _atom_site_constraints and _atom_site_refinement_flags. A general description of refinement constraints may appear in _refine_special_details. ; data_refine_ls_R_factor_all _name '_refine_ls_R_factor_all' _category refine _type numb _enumeration_range 0.0: _definition ; Residual factor for all reflections satisfying the resolution limits established by _refine_ls_d_res_high and _refine_ls_d_res_low. This is the conventional R factor. See also _refine_ls_wR_factor_ definitions. sum | F(obs) - F(calc) | R = ------------------------ sum | F(obs) | F(obs) = the observed structure-factor amplitudes F(calc) = the calculated structure-factor amplitudes and the sum is taken over the specified reflections ; data_refine_ls_R_factor_gt _name '_refine_ls_R_factor_gt' _category refine _type numb _related_item '_refine_ls_R_factor_obs' _related_function alternate _enumeration_range 0.0: _definition ; Residual factor for the reflections (with number given by _reflns_number_gt) judged significantly intense (i.e. satisfying the threshold specified by _reflns_threshold_expression) and included in the refinement. The reflections also satisfy the resolution limits established by _refine_ls_d_res_high and _refine_ls_d_res_low. This is the conventional R factor. See also _refine_ls_wR_factor_ definitions. sum | F(obs) - F(calc) | R = ------------------------ sum | F(obs) | F(obs) = the observed structure-factor amplitudes F(calc) = the calculated structure-factor amplitudes and the sum is taken over the specified reflections ; data_refine_ls_R_factor_obs _name '_refine_ls_R_factor_obs' _category refine _type numb _related_item '_refine_ls_R_factor_gt' _related_function replace _enumeration_range 0.0: _definition ; Residual factor for the reflections classified as 'observed' (see _reflns_observed_criterion) and included in the refinement. The reflections also satisfy the resolution limits established by _refine_ls_d_res_high and _refine_ls_d_res_low. This is the conventional R factor. See also _refine_ls_wR_factor_ definitions. sum | F(obs) - F(calc) | R = ------------------------ sum | F(obs) | F(obs) = the observed structure-factor amplitudes F(calc) = the calculated structure-factor amplitudes and the sum is taken over the specified reflections ; data_refine_ls_R_Fsqd_factor _name '_refine_ls_R_Fsqd_factor' _category refine _type numb _enumeration_range 0.0: _definition ; Residual factor R(Fsqd), calculated on the squared amplitudes of the observed and calculated structure factors, for significantly intense reflections (satisfying _reflns_threshold_expression) and included in the refinement. The reflections also satisfy the resolution limits established by _refine_ls_d_res_high and _refine_ls_d_res_low. sum | F(obs)^2^ - F(calc)^2^ | R(Fsqd) = ------------------------------- sum F(obs)^2^ F(obs)^2^ = squares of the observed structure-factor amplitudes F(calc)^2^ = squares of the calculated structure-factor amplitudes and the sum is taken over the specified reflections ; data_refine_ls_R_I_factor _name '_refine_ls_R_I_factor' _category refine _type numb _enumeration_range 0.0: _definition ; Residual factor R(I) for significantly intense reflections (satisfying _reflns_threshold_expression) and included in the refinement. This is most often calculated in Rietveld refinements against powder data, where it is referred to as R~B~ or R~Bragg~. sum | I(obs) - I(calc) | R(I) = ------------------------ sum | I(obs) | I(obs) = the net observed intensities I(calc) = the net calculated intensities and the sum is taken over the specified reflections ; data_refine_ls_restrained_S_all _name '_refine_ls_restrained_S_all' _category refine _type numb _enumeration_range 0.0: _definition ; The least-squares goodness-of-fit parameter S' for all reflections after the final cycle of least-squares refinement. This parameter explicitly includes the restraints applied in the least-squares process. See also _refine_ls_goodness_of_fit_ definitions. {sum { w [ Y(obs) - Y(calc) ]^2^ } }^1/2^ { + sum~r~ { w~r~ [ P(calc) - P(targ) ]^2^ } } S' = { -------------------------------------------------- } { N~ref~ + N~restr~ - N~param~ } Y(obs) = the observed coefficients (see _refine_ls_structure_factor_coef) Y(calc) = the calculated coefficients (see _refine_ls_structure_factor_coef) w = the least-squares reflection weight [1/square of standard uncertainty (e.s.d.)] P(calc) = the calculated restraint values P(targ) = the target restraint values w~r~ = the restraint weight N~ref~ = the number of reflections used in the refinement (see _refine_ls_number_reflns) N~restr~ = the number of restraints (see _refine_ls_number_restraints) N~param~ = the number of refined parameters (see _refine_ls_number_parameters) sum is taken over the specified reflections sum~r~ is taken over the restraints ; data_refine_ls_restrained_S_gt _name '_refine_ls_restrained_S_gt' _category refine _type numb _related_item '_refine_ls_restrained_S_obs' _related_function alternate _enumeration_range 0.0: _definition ; The least-squares goodness-of-fit parameter S' for significantly intense reflections (satisfying _reflns_threshold_expression) after the final cycle of least-squares refinement. This parameter explicitly includes the restraints applied in the least-squares process. See also _refine_ls_goodness_of_fit_ definitions. {sum { w [ Y(obs) - Y(calc) ]^2^ } }^1/2^ { + sum~r~ { w~r~ [ P(calc) - P(targ) ]^2^ } } S' = { -------------------------------------------------- } { N~ref~ + N~restr~ - N~param~ } Y(obs) = the observed coefficients (see _refine_ls_structure_factor_coef) Y(calc) = the calculated coefficients (see _refine_ls_structure_factor_coef) w = the least-squares reflection weight [1/square of standard uncertainty (e.s.d.)] P(calc) = the calculated restraint values P(targ) = the target restraint values w~r~ = the restraint weight N~ref~ = the number of reflections used in the refinement (see _refine_ls_number_reflns) N~restr~ = the number of restraints (see _refine_ls_number_restraints) N~param~ = the number of refined parameters (see _refine_ls_number_parameters) sum is taken over the specified reflections sum~r~ is taken over the restraints ; data_refine_ls_restrained_S_obs _name '_refine_ls_restrained_S_obs' _category refine _type numb _related_item '_refine_ls_restrained_S_gt' _related_function replace _enumeration_range 0.0: _definition ; The least-squares goodness-of-fit parameter S' for observed reflections after the final cycle of least-squares refinement. This parameter explicitly includes the restraints applied in the least-squares process. See also _refine_ls_goodness_of_fit_ definitions. {sum { w [ Y(obs) - Y(calc) ]^2^ } }^1/2^ { + sum~r~ { w~r~ [ P(calc) - P(targ) ]^2^ } } S' = { -------------------------------------------------- } { N~ref~ + N~restr~ - N~param~ } Y(obs) = the observed coefficients (see _refine_ls_structure_factor_coef) Y(calc) = the calculated coefficients (see _refine_ls_structure_factor_coef) w = the least-squares reflection weight [1/square of standard uncertainty (e.s.d.)] P(calc) = the calculated restraint values P(targ) = the target restraint values w~r~ = the restraint weight N~ref~ = the number of reflections used in the refinement (see _refine_ls_number_reflns) N~restr~ = the number of restraints (see _refine_ls_number_restraints) N~param~ = the number of refined parameters (see _refine_ls_number_parameters) sum is taken over the specified reflections sum~r~ is taken over the restraints ; data_refine_ls_shift/esd_max _name '_refine_ls_shift/esd_max' _category refine _type numb _related_item '_refine_ls_shift/su_max' _related_function replace _enumeration_range 0.0: _definition ; The largest ratio of the final least-squares parameter shift to the final standard uncertainty (s.u., formerly described as estimated standard deviation, e.s.d.). ; data_refine_ls_shift/esd_mean _name '_refine_ls_shift/esd_mean' _category refine _type numb _related_item '_refine_ls_shift/su_mean' _related_function replace _enumeration_range 0.0: _definition ; The average ratio of the final least-squares parameter shift to the final standard uncertainty (s.u., formerly described as estimated standard deviation, e.s.d.). ; data_refine_ls_shift/su_max _name '_refine_ls_shift/su_max' _category refine _type numb _related_item '_refine_ls_shift/esd_max' _related_function alternate _enumeration_range 0.0: _definition ; The largest ratio of the final least-squares parameter shift to the final standard uncertainty. ; data_refine_ls_shift/su_max_lt _name '_refine_ls_shift/su_max_lt' _category refine _type numb _related_item '_refine_ls_shift/su_max' _related_function alternate _enumeration_range 0.0: _definition ; An upper limit for the largest ratio of the final least-squares parameter shift to the final standard uncertainty. This item is used when the largest value of the shift divided by the final standard uncertainty is too small to measure. ; data_refine_ls_shift/su_mean _name '_refine_ls_shift/su_mean' _category refine _type numb _related_item '_refine_ls_shift/esd_mean' _related_function alternate _enumeration_range 0.0: _definition ; The average ratio of the final least-squares parameter shift to the final standard uncertainty. ; data_refine_ls_shift/su_mean_lt _name '_refine_ls_shift/su_mean_lt' _category refine _type numb _related_item '_refine_ls_shift/su_mean' _related_function alternate _enumeration_range 0.0: _definition ; An upper limit for the average ratio of the final least-squares parameter shift to the final standard uncertainty. This item is used when the average value of the shift divided by the final standard uncertainty is too small to measure. ; data_refine_ls_structure_factor_coef _name '_refine_ls_structure_factor_coef' _category refine _type char loop_ _enumeration _enumeration_detail F 'structure-factor magnitude' Fsqd 'structure factor squared' Inet 'net intensity' _enumeration_default F _definition ; Structure-factor coefficient |F|, F^2^ or I used in the least-squares refinement process. ; data_refine_ls_weighting_details _name '_refine_ls_weighting_details' _category refine _type char _example ; Sigdel model of Konnert-Hendrickson: Sigdel = Afsig + Bfsig*(sin(\q)/\l - 1/6) Afsig = 22.0, Bfsig = 150.0 at the beginning of refinement. Afsig = 16.0, Bfsig = 60.0 at the end of refinement. ; _definition ; A description of special aspects of the weighting scheme used in the least-squares refinement. Used to describe the weighting when the value of _refine_ls_weighting_scheme is specified as 'calc'. ; data_refine_ls_weighting_scheme _name '_refine_ls_weighting_scheme' _category refine _type char loop_ _enumeration _enumeration_detail sigma "based on measured s.u.'s" unit 'unit or no weights applied' calc 'calculated weights applied' _enumeration_default sigma _definition ; The weighting scheme applied in the least-squares process. The standard code may be followed by a description of the weight (but see _refine_ls_weighting_details for a preferred approach). ; data_refine_ls_wR_factor_all _name '_refine_ls_wR_factor_all' _category refine _type numb _enumeration_range 0.0: _definition ; Weighted residual factors for all reflections. The reflections also satisfy the resolution limits established by _refine_ls_d_res_high and _refine_ls_d_res_low. See also the _refine_ls_R_factor_ definitions. ( sum w [ Y(obs) - Y(calc) ]^2^ )^1/2^ wR = ( ------------------------------ ) ( sum w Y(obs)^2^ ) Y(obs) = the observed amplitude specified by _refine_ls_structure_factor_coef Y(calc) = the calculated amplitude specified by _refine_ls_structure_factor_coef w = the least-squares weight and the sum is taken over the specified reflections ; data_refine_ls_wR_factor_gt _name '_refine_ls_wR_factor_gt' _category refine _type numb _related_item '_refine_ls_wR_factor_obs' _related_function alternate _enumeration_range 0.0: _definition ; Weighted residual factors for significantly intense reflections (satisfying _reflns_threshold_expression) included in the refinement. The reflections also satisfy the resolution limits established by _refine_ls_d_res_high and _refine_ls_d_res_low. See also the _refine_ls_R_factor_ definitions. ( sum w [ Y(obs) - Y(calc) ]^2^ )^1/2^ wR = ( ------------------------------ ) ( sum w Y(obs)^2^ ) Y(obs) = the observed amplitude specified by _refine_ls_structure_factor_coef Y(calc) = the calculated amplitude specified by _refine_ls_structure_factor_coef w = the least-squares weight and the sum is taken over the specified reflections ; data_refine_ls_wR_factor_obs _name '_refine_ls_wR_factor_obs' _category refine _type numb _related_item '_refine_ls_wR_factor_gt' _related_function replace _enumeration_range 0.0: _definition ; Weighted residual factors for the reflections classified as 'observed' (see _reflns_observed_criterion) and included in the refinement. The reflections also satisfy the resolution limits established by _refine_ls_d_res_high and _refine_ls_d_res_low. See also the _refine_ls_R_factor_ definitions. ( sum w [ Y(obs) - Y(calc) ]^2^ )^1/2^ wR = ( ------------------------------ ) ( sum w Y(obs)^2^ ) Y(obs) = the observed amplitude specified by _refine_ls_structure_factor_coef Y(calc) = the calculated amplitude specified by _refine_ls_structure_factor_coef w = the least-squares weight and the sum is taken over the specified reflections ; data_refine_ls_wR_factor_ref _name '_refine_ls_wR_factor_ref' _category refine _type numb _enumeration_range 0.0: _definition ; Weighted residual factors for all reflections included in the refinement. The reflections also satisfy the resolution limits established by _refine_ls_d_res_high and _refine_ls_d_res_low. See also the _refine_ls_R_factor_ definitions. ( sum w [ Y(obs) - Y(calc) ]^2^ )^1/2^ wR = ( ------------------------------ ) ( sum w Y(obs)^2^ ) Y(obs) = the observed amplitude specified by _refine_ls_structure_factor_coef Y(calc) = the calculated amplitude specified by _refine_ls_structure_factor_coef w = the least-squares weight and the sum is taken over the specified reflections ; data_refine_special_details _name '_refine_special_details' _category refine _type char _definition ; Description of special aspects of the refinement process. ; ##################### ## REFINE_LS_CLASS ## ##################### data_refine_ls_class_[] _name '_refine_ls_class_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _refine_ls_class_R_factor_gt _refine_ls_class_code 0.057 'Main' 0.074 'Com' 0.064 'NbRefls' 0.046 'LaRefls' 0.112 'Sat1' 0.177 'Sat2' ; ; Example 1 - example for a modulated structure extracted from van Smaalen [J. Phys. Condens. Matter (1991), 3, 1247-1263.] ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the REFINE_LS_CLASS category record details (for each reflection class separately) about the reflections used for the structure refinement. ; data_refine_ls_class_code _name '_refine_ls_class_code' _category refine_ls_class _type char _list yes _list_link_parent '_reflns_class_code' loop_ _example '1' 'm1' 's2' _definition ; The code identifying a certain reflection class. This code must match a _reflns_class_code. ; data_refine_ls_class_d_res_high _name '_refine_ls_class_d_res_high' _category refine_ls_class _type numb _list yes _list_reference '_refine_ls_class_code' _enumeration_range 0.0: _units A _units_detail 'Angstroms' _definition ; For each reflection class, the highest resolution in angstroms for the reflections used in the refinement. This is the lowest d value in a reflection class. ; data_refine_ls_class_d_res_low _name '_refine_ls_class_d_res_low' _category refine_ls_class _type numb _list yes _list_reference '_refine_ls_class_code' _enumeration_range 0.0: _units A _units_detail 'Angstroms' _definition ; For each reflection class, the lowest resolution in angstroms for the reflections used in the refinement. This is the highest d value in a reflection class. ; data_refine_ls_class_R_factor_ loop_ _name '_refine_ls_class_R_factor_all' '_refine_ls_class_R_factor_gt' _category refine_ls_class _type numb _list yes _list_reference '_refine_ls_class_code' _enumeration_range 0.0: _definition ; For each reflection class, the residual factors for all reflections, and for significantly intense reflections (see _reflns_threshold_expression), included in the refinement. The reflections also satisfy the resolution limits established by _refine_ls_class_d_res_high and _refine_ls_class_d_res_low. This is the conventional R factor. sum | F(obs) - F(calc) | R = ------------------------ sum | F(obs) | F(obs) = the observed structure-factor amplitudes F(calc) = the calculated structure-factor amplitudes and the sum is taken over the reflections of this class. See also _refine_ls_class_wR_factor_all definitions. ; data_refine_ls_class_R_Fsqd_factor _name '_refine_ls_class_R_Fsqd_factor' _category refine_ls_class _type numb _list yes _list_reference '_refine_ls_class_code' _enumeration_range 0.0: _definition ; For each reflection class, the residual factor R(F^2^) calculated on the squared amplitudes of the observed and calculated structure factors for the reflections judged significantly intense (i.e. satisfying the threshold specified by _reflns_threshold_expression) and included in the refinement. The reflections also satisfy the resolution limits established by _refine_ls_class_d_res_high and _refine_ls_class_d_res_low. sum | F(obs)^2^ - F(calc)^2^ | R(Fsqd) = ------------------------------- sum F(obs)^2^ F(obs)^2^ = squares of the observed structure-factor amplitudes F(calc)^2^ = squares of the calculated structure-factor amplitudes and the sum is taken over the reflections of this class. ; data_refine_ls_class_R_I_factor _name '_refine_ls_class_R_I_factor' _category refine_ls_class _type numb _list yes _list_reference '_refine_ls_class_code' _enumeration_range 0.0: _definition ; For each reflection class, the residual factor R(I) for the reflections judged significantly intense (i.e. satisfying the threshold specified by _reflns_threshold_expression) and included in the refinement. This is most often calculated in Rietveld refinements against powder data, where it is referred to as R~B~ or R~Bragg~. sum | I(obs) - I(calc) | R(I) = ------------------------ sum | I(obs) | I(obs) = the net observed intensities I(calc) = the net calculated intensities and the sum is taken over the reflections of this class. ; data_refine_ls_class_wR_factor_all _name '_refine_ls_class_wR_factor_all' _category refine_ls_class _type numb _list yes _list_reference '_refine_ls_class_code' _enumeration_range 0.0: _definition ; For each reflection class, the weighted residual factors for all reflections included in the refinement. The reflections also satisfy the resolution limits established by _refine_ls_class_d_res_high and _refine_ls_class_d_res_low. ( sum w [ Y(obs) - Y(calc) ]^2^ )^1/2^ wR = ( ------------------------------ ) ( sum w Y(obs)^2^ ) Y(obs) = the observed amplitudes specified by _refine_ls_structure_factor_coef Y(calc) = the calculated amplitudes specified by _refine_ls_structure_factor_coef w = the least-squares weights and the sum is taken over the reflections of this class. See also _refine_ls_class_R_factor_ definitions. ; ########### ## REFLN ## ########### data_refln_[] _name '_refln_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _refln_index_h _refln_index_k _refln_index_l _refln_F_squared_calc _refln_F_squared_meas _refln_F_squared_sigma _refln_include_status 2 0 0 85.57 58.90 1.45 o 3 0 0 15718.18 15631.06 30.40 o 4 0 0 55613.11 49840.09 61.86 o 5 0 0 246.85 241.86 10.02 o 6 0 0 82.16 69.97 1.93 o 7 0 0 1133.62 947.79 11.78 o 8 0 0 2558.04 2453.33 20.44 o 9 0 0 283.88 393.66 7.79 o 10 0 0 283.70 171.98 4.26 o ; ; Example 1 - based on data set fetod of Todres, Yanovsky, Ermekov & Struchkov [Acta Cryst. (1993), C49, 1352-1354]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _refln_index_h _refln_index_k _refln_index_l _refln_F_meas _refln_F_calc _refln_F_sigma _refln_include_status _refln_scale_group_code 0 0 6 34.935 36.034 3.143 o 1 0 0 12 42.599 40.855 2.131 o 1 0 1 0 42.500 42.507 4.719 o 1 0 1 1 59.172 57.976 4.719 o 1 0 1 2 89.694 94.741 4.325 o 1 0 1 3 51.743 52.241 3.850 o 1 0 1 4 9.294 10.318 2.346 o 1 0 1 5 41.160 39.951 3.313 o 1 0 1 6 6.755 7.102 .895 < 1 0 1 7 30.693 31.171 2.668 o 1 0 1 8 12.324 12.085 2.391 o 1 0 1 9 15.348 15.122 2.239 o 1 0 1 10 17.622 19.605 1.997 o 1 ; ; Example 2 - based on standard test data set p6122 of the Xtal distribution [Hall, King & Stewart (1995). Xtal3.4 User's Manual. University of Western Australia]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the REFLN category record details about the reflections used to determine the ATOM_SITE data items. The REFLN data items refer to individual reflections and must be included in looped lists. The REFLNS data items specify the parameters that apply to all reflections. The REFLNS data items are not looped. ; data_refln_A_ loop_ _name '_refln_A_calc' '_refln_A_meas' _category refln _type numb _list yes _list_reference '_refln_index_' _definition ; The calculated and measured structure-factor component A (in electrons for X-ray diffraction). A =|F|cos(phase) ; data_refln_B_ loop_ _name '_refln_B_calc' '_refln_B_meas' _category refln _type numb _list yes _list_reference '_refln_index_' _definition ; The calculated and measured structure-factor component B (in electrons for X-ray diffraction). B =|F|sin(phase) ; data_refln_class_code _name '_refln_class_code' _category refln _type char _list yes _list_reference '_refln_index_' _list_link_parent '_reflns_class_code' _definition ; The code identifying the class to which this reflection has been assigned. This code must match a value of _reflns_class_code. Reflections may be grouped into classes for a variety of purposes. For example, for modulated structures each reflection class may be defined by the number m=sum|m~i~|, where the m~i~ are the integer coefficients that, in addition to h,k,l, index the corresponding diffraction vector in the basis defined for the reciprocal lattice. ; data_refln_d_spacing _name '_refln_d_spacing' _category refln _type numb _list yes _list_reference '_refln_index_' _enumeration_range 0.0: _units A _units_detail 'angstroms' _definition ; The d spacing in angstroms for this reflection. This is related to the (sin theta)/lambda value by the expression _refln_d_spacing = 2/(_refln_sint/lambda) ; data_refln_crystal_id _name '_refln_crystal_id' _category refln _type char _list yes _list_link_parent '_exptl_crystal_id' _list_reference '_refln_index_' _definition ; Code identifying each crystal if multiple crystals are used. Is used to link with _exptl_crystal_id in the _exptl_crystal_ list. ; data_refln_F_ loop_ _name '_refln_F_calc' '_refln_F_meas' '_refln_F_sigma' _category refln _type numb _list yes _list_reference '_refln_index_' _definition ; The calculated, measured and standard uncertainty (derived from measurement) of the structure factors (in electrons for X-ray diffraction). ; data_refln_F_squared_ loop_ _name '_refln_F_squared_calc' '_refln_F_squared_meas' '_refln_F_squared_sigma' _category refln _type numb _list yes _list_reference '_refln_index_' _definition ; Calculated, measured and estimated standard uncertainty (derived from measurement) of the squared structure factors (in electrons squared for X-ray diffraction). ; data_refln_include_status _name '_refln_include_status' _category refln _type char _related_item '_refln_observed_status' _related_function alternate _list yes _list_reference '_refln_index_' loop_ _enumeration _enumeration_detail o ; (lower-case letter o for 'observed') satisfies _refine_ls_d_res_high satisfies _refine_ls_d_res_low exceeds _reflns_threshold_expression ; < ; satisfies _refine_ls_d_res_high satisfies _refine_ls_d_res_low does not exceed _reflns_threshold_expression ; - 'systematically absent reflection' x 'unreliable measurement -- not used' h 'does not satisfy _refine_ls_d_res_high' l 'does not satisfy _refine_ls_d_res_low' _enumeration_default o _definition ; Classification of a reflection indicating its status with respect to inclusion in the refinement and the calculation of R factors. ; data_refln_index_ loop_ _name '_refln_index_h' '_refln_index_k' '_refln_index_l' _category refln _type numb _list yes _list_mandatory yes _definition ; Miller indices of the reflection. The values of the Miller indices in the REFLN category must correspond to the cell defined by the cell lengths and cell angles in the CELL category. ; data_refln_intensity_ loop_ _name '_refln_intensity_calc' '_refln_intensity_meas' '_refln_intensity_sigma' _category refln _type numb _list yes _list_reference '_refln_index_' _definition ; The calculated, measured and standard uncertainty (derived from measurement) of the intensity, all in the same arbitrary units as _refln_intensity_meas. ; data_refln_mean_path_length_tbar _name '_refln_mean_path_length_tbar' _category refln _type numb _list yes _list_reference '_refln_index_' _enumeration_range 0.0: _units mm _units_detail 'millimetres' _definition ; Mean path length in millimetres through the crystal for this reflection. ; data_refln_observed_status _name '_refln_observed_status' _category refln _type char _related_item '_refln_include_status' _related_function replace _list yes _list_reference '_refln_index_' loop_ _enumeration _enumeration_detail o ; satisfies _refine_ls_d_res_high satisfies _refine_ls_d_res_low observed by _reflns_observed_criterion ; < ; satisfies _refine_ls_d_res_high satisfies _refine_ls_d_res_low unobserved by _reflns_observed_criterion ; - 'systematically absent reflection' x 'unreliable measurement -- not used' h 'does not satisfy _refine_ls_d_res_high' l 'does not satisfy _refine_ls_d_res_low' _enumeration_default o _definition ; Classification of a reflection indicating its status with respect to inclusion in the refinement and the calculation of R factors. ; data_refln_phase_calc _name '_refln_phase_calc' _category refln _type numb _list yes _list_reference '_refln_index_' _units deg _units_detail 'degrees' _definition ; The calculated structure-factor phase in degrees. ; data_refln_phase_meas _name '_refln_phase_meas' _category refln _type numb _type_conditions esd _list yes _list_reference '_refln_index_' _units deg _units_detail 'degrees' _definition ; The measured structure-factor phase in degrees. ; data_refln_refinement_status _name '_refln_refinement_status' _category refln _type char _list yes _list_reference '_refln_index_' loop_ _enumeration _enumeration_detail incl 'included in ls process' excl 'excluded from ls process' extn 'excluded due to extinction' _enumeration_default incl _definition ; Status of a reflection in the structure-refinement process. ; data_refln_scale_group_code _name '_refln_scale_group_code' _category refln _type char _list yes _list_link_parent '_reflns_scale_group_code' _list_reference '_refln_index_' loop_ _example 1 2 3 s1 A B c1 c2 c3 _definition ; Code identifying the structure-factor scale. This code must correspond to one of the _reflns_scale_group_code values. ; data_refln_sint/lambda _name '_refln_sint/lambda' _category refln _type numb _list yes _list_reference '_refln_index_' _enumeration_range 0.0: _units A^-1^ _units_detail 'reciprocal angstroms' _definition ; The (sin theta)/lambda value in reciprocal angstroms for this reflection. ; data_refln_symmetry_epsilon _name '_refln_symmetry_epsilon' _category refln _type numb _list yes _list_reference '_refln_index_' _enumeration_range 1:48 _definition ; The symmetry reinforcement factor corresponding to the number of times the reflection indices are generated identically from the space-group symmetry operations. ; data_refln_symmetry_multiplicity _name '_refln_symmetry_multiplicity' _category refln _type numb _list yes _list_reference '_refln_index_' _enumeration_range 1:48 _definition ; The number of reflections symmetry-equivalent under the Laue symmetry to the present reflection. In the Laue symmetry, Friedel opposites (h k l and -h -k -l) are equivalent. Tables of symmetry-equivalent reflections are available in International Tables for Crystallography Volume A (2002), Chapter 10.1. ; data_refln_wavelength _name '_refln_wavelength' _category refln _type numb _list yes _list_reference '_refln_index_' _enumeration_range 0.0: _units A _units_detail 'angstroms' _definition ; The mean wavelength in angstroms of the radiation used to measure this reflection. This is an important parameter for data collected using energy-dispersive detectors or the Laue method. ; data_refln_wavelength_id _name '_refln_wavelength_id' _category refln _type char _list yes _list_link_parent '_diffrn_radiation_wavelength_id' _list_reference '_refln_index_' _definition ; Code identifying the wavelength in the _diffrn_radiation_ list. See _diffrn_radiation_wavelength_id. ; ############ ## REFLNS ## ############ data_reflns_[] _name '_reflns_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _reflns_limit_h_min 0 _reflns_limit_h_max 6 _reflns_limit_k_min 0 _reflns_limit_k_max 17 _reflns_limit_l_min 0 _reflns_limit_l_max 22 _reflns_number_total 1592 _reflns_number_gt 1408 _reflns_threshold_expression 'F > 6.0u(F)' _reflns_d_resolution_high 0.8733 _reflns_d_resolution_low 11.9202 ; ; Example 1 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the REFLNS category record details about the reflections used to determine the ATOM_SITE data items. The REFLN data items refer to individual reflections and must be included in looped lists. The REFLNS data items specify the parameters that apply to all reflections. The REFLNS data items are not looped. ; data_reflns_d_resolution_ loop_ _name '_reflns_d_resolution_high' '_reflns_d_resolution_low' _category reflns _type numb _enumeration_range 0.0: _units A _units_detail 'angstroms' _definition ; The highest and lowest resolution in angstroms for the reflections. These are the smallest and largest d values. ; data_reflns_Friedel_coverage _name '_reflns_Friedel_coverage' _category reflns _type numb _enumeration_range 0.0:1.0 _definition ; The proportion of Friedel-related reflections present in the number of 'independent' reflections specified by the item _reflns_number_total. This proportion is calculated as the ratio: [N(crystal class) - N(Laue symmetry)] / N(Laue symmetry) where, working from the _diffrn_refln_ list, N(crystal class) is the number of reflections obtained on averaging under the symmetry of the crystal class N(Laue symmetry) is the number of reflections obtained on averaging under the Laue symmetry. Examples: (a) For centrosymmetric structures, _reflns_Friedel_coverage is necessarily equal to 0.0 as the crystal class is identical to the Laue symmetry. (b) For whole-sphere data for a crystal in the space group P1, _reflns_Friedel_coverage is equal to 1.0, as no reflection h k l is equivalent to -h -k -l in the crystal class and all Friedel pairs {h k l; -h -k -l} have been measured. (c) For whole-sphere data in space group Pmm2, _reflns_Friedel_coverage will be < 1.0 because although reflections h k l and -h -k -l are not equivalent when h k l indices are nonzero, they are when l=0. (d) For a crystal in the space group Pmm2, measurements of the two inequivalent octants h >= 0, k >=0, l lead to the same value as in (c), whereas measurements of the two equivalent octants h >= 0, k, l >= 0 will lead to a value of zero for _reflns_Friedel_coverage. ; data_reflns_limit_ loop_ _name '_reflns_limit_h_max' '_reflns_limit_h_min' '_reflns_limit_k_max' '_reflns_limit_k_min' '_reflns_limit_l_max' '_reflns_limit_l_min' _category reflns _type numb _definition ; Miller indices limits for the reported reflections. These need not be the same as the _diffrn_reflns_limit_ values. ; data_reflns_number_gt _name '_reflns_number_gt' _category reflns _type numb _related_item '_reflns_number_observed' _related_function alternate _enumeration_range 0: _definition ; The number of reflections in the _refln_ list (not the _diffrn_refln_ list) that are significantly intense, satisfying the criterion specified by _reflns_threshold_expression. This may include Friedel-equivalent reflections (i.e. those which are symmetry-equivalent under the Laue symmetry but inequivalent under the crystal class) according to the nature of the structure and the procedures used. Special characteristics of the reflections included in the _refln_ list should be given in the item _reflns_special_details. ; data_reflns_number_observed _name '_reflns_number_observed' _category reflns _type numb _related_item '_reflns_number_gt' _related_function replace _enumeration_range 0: _definition ; The number of 'observed' reflections in the _refln_ list (not the _diffrn_refln_ list). The observed reflections satisfy the threshold criterion specified by _reflns_threshold_expression (or the deprecated item _reflns_observed_criterion). They may include Friedel-equivalent reflections according to the nature of the structure and the procedures used. Special characteristics of the reflections included in the _refln_ list should be given in the item _reflns_special_details. ; data_reflns_number_total _name '_reflns_number_total' _category reflns _type numb _enumeration_range 0: _definition ; The total number of reflections in the _refln_ list (not the _diffrn_refln_ list). This may include Friedel-equivalent reflections (i.e. those which are symmetry-equivalent under the Laue symmetry but inequivalent under the crystal class) according to the nature of the structure and the procedures used. Special characteristics of the reflections included in the _refln_ list should be given in the item _reflns_special_details. ; data_reflns_observed_criterion _name '_reflns_observed_criterion' _category reflns _type char _related_item '_reflns_threshold_expression' _related_function replace _example 'I>2u(I)' _definition ; The criterion used to classify a reflection as 'observed'. This criterion is usually expressed in terms of a sigma(I) or sigma(F) threshold. ; data_reflns_special_details _name '_reflns_special_details' _category reflns _type char _definition ; Description of the properties of the reported reflection list that are not given in other data items. In particular, this should include information about the averaging (or not) of symmetry-equivalent reflections including Friedel pairs. ; data_reflns_threshold_expression _name '_reflns_threshold_expression' _category reflns _type char _related_item '_reflns_observed_criterion' _related_function alternate _example 'I>2u(I)' _definition ; The threshold, usually based on multiples of u(I), u(F^2^) or u(F), that serves to identify significantly intense reflections, the number of which is given by _reflns_number_gt. These reflections are used in the calculation of _refine_ls_R_factor_gt. ; ################## ## REFLNS_CLASS ## ################## data_reflns_class_[] _name '_reflns_class_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _reflns_class_number_gt _reflns_class_code 584 'Main' 226 'Sat1' 50 'Sat2' ; ; Example 1 - corresponding to the one-dimensional incommensurately modulated structure of K~2~SeO~4~. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the REFLNS_CLASS category record details, for each reflection class, about the reflections used to determine the structural parameters. ; data_reflns_class_code _name '_reflns_class_code' _category reflns_class _type char _list yes loop_ _list_link_child '_refln_class_code' '_refine_ls_class_code' loop_ _example '1' 'm1' 's2' _definition ; The code identifying a certain reflection class. ; data_reflns_class_description _name '_reflns_class_description' _category reflns_class _type char _list yes _list_reference '_reflns_class_code' loop_ _example 'm=1 first order satellites' 'H0L0 common projection reflections' _definition ; Description of each reflection class. ; data_reflns_class_d_res_high _name '_reflns_class_d_res_high' _category reflns_class _type numb _list yes _list_reference '_reflns_class_code' _enumeration_range 0.0: _units A _units_detail 'Angstroms' _definition ; For each reflection class, the highest resolution in angstroms for the reflections used in the refinement. This is the smallest d value. ; data_reflns_class_d_res_low _name '_reflns_class_d_res_low' _category reflns_class _type numb _list yes _list_reference '_reflns_class_code' _enumeration_range 0.0: _units A _units_detail 'Angstroms' _definition ; For each reflection class, the lowest resolution in angstroms for the reflections used in the refinement. This is the largest d value. ; data_reflns_class_number_gt _name '_reflns_class_number_gt' _category reflns_class _type numb _list yes _list_reference '_reflns_class_code' _enumeration_range 0.0: _definition ; For each reflection class, the number of significantly intense reflections (see _reflns_threshold_expression) in the _refln_ list (not the _diffrn_refln_ list). This may include Friedel- equivalent reflections (i.e. those which are symmetry-equivalent under the Laue symmetry but inequivalent under the crystal class) according to the nature of the structure and the procedures used. Special characteristics of the reflections included in the _refln_ list should be given in the item _reflns_special_details. ; data_reflns_class_number_total _name '_reflns_class_number_total' _category reflns_class _type numb _list yes _list_reference '_reflns_class_code' _enumeration_range 0.0: _definition ; For each reflection class, the total number of reflections in the _refln_ list (not the _diffrn_refln_ list). This may include Friedel-equivalent reflections (i.e. those which are symmetry-equivalent under the Laue symmetry but inequivalent under the crystal class) according to the nature of the structure and the procedures used. Special characteristics of the reflections included in the _refln_ list should be given in the item _reflns_special_details. ; data_reflns_class_R_factor_ loop_ _name '_reflns_class_R_factor_all' '_reflns_class_R_factor_gt' _category reflns_class _type numb _list yes _list_reference '_reflns_class_code' _enumeration_range 0.0: _definition ; For each reflection class, the residual factors for all reflections, and for significantly intense reflections (see _reflns_threshold_expression), included in the refinement. The reflections also satisfy the resolution limits established by _reflns_class_d_res_high and _reflns_class_d_res_low. This is the conventional R factor. sum | F(obs) - F(calc) | R = ------------------------ sum | F(obs) | F(obs) = the observed structure-factor amplitudes F(calc) = the calculated structure-factor amplitudes and the sum is taken over the reflections of this class. See also _reflns_class_wR_factor_all definitions. ; data_reflns_class_R_Fsqd_factor _name '_reflns_class_R_Fsqd_factor' _category reflns_class _type numb _list yes _list_reference '_reflns_class_code' _enumeration_range 0.0: _definition ; For each reflection class, the residual factor R(F^2^) calculated on the squared amplitudes of the observed and calculated structure factors, for the reflections judged significantly intense (i.e. satisfying the threshold specified by _reflns_threshold_expression) and included in the refinement. The reflections also satisfy the resolution limits established by _reflns_class_d_res_high and _reflns_class_d_res_low. sum | F(obs)^2^ - F(calc)^2^ | R(Fsqd) = ------------------------------- sum F(obs)^2^ F(obs)^2^ = squares of the observed structure-factor amplitudes F(calc)^2^ = squares of the calculated structure-factor amplitudes and the sum is taken over the reflections of this class. ; data_reflns_class_R_I_factor _name '_reflns_class_R_I_factor' _category reflns_class _type numb _list yes _list_reference '_reflns_class_code' _enumeration_range 0.0: _definition ; For each reflection class, the residual factor R(I) for the reflections judged significantly intense (i.e. satisfying the threshold specified by _reflns_threshold_expression) and included in the refinement. This is most often calculated in Rietveld refinements against powder data, where it is referred to as R~B~ or R~Bragg~. sum | I(obs) - I(calc) | R(I) = ------------------------ sum | I(obs) | I(obs) = the net observed intensities I(calc) = the net calculated intensities and the sum is taken over the reflections of this class. ; data_reflns_class_wR_factor_all _name '_reflns_class_wR_factor_all' _category reflns_class _type numb _list yes _list_reference '_reflns_class_code' _enumeration_range 0.0: _definition ; For each reflection class, the weighted residual factors for all reflections included in the refinement. The reflections also satisfy the resolution limits established by _reflns_class_d_res_high and _reflns_class_d_res_low. ( sum w [ Y(obs) - Y(calc) ]^2^ )^1/2^ wR = ( ------------------------------ ) ( sum w Y(obs)^2^ ) Y(obs) = the observed amplitudes specified by _refine_ls_structure_factor_coef Y(calc) = the calculated amplitudes specified by _refine_ls_structure_factor_coef w = the least-squares weights and the sum is taken over the reflections of this class. See also _reflns_class_R_factor_ definitions. ; ################## ## REFLNS_SCALE ## ################## data_reflns_scale_[] _name '_reflns_scale_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _reflns_scale_group_code _reflns_scale_meas_F 1 .895447 2 .912743 ; ; Example 1 - based on standard test data set p6122 of the Xtal distribution [Hall, King & Stewart (1995). Xtal3.4 User's Manual. University of Western Australia]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the REFLNS_SCALE category record details about the structure-factor scales. They are referenced from within the REFLN list through _refln_scale_group_code. ; data_reflns_scale_group_code _name '_reflns_scale_group_code' _category reflns_scale _type char _list yes _list_mandatory yes _list_link_child '_refln_scale_group_code' _definition ; The code identifying a scale _reflns_scale_meas_. These are linked to the _refln_ list by the _refln_scale_group_code. These codes need not correspond to those in the _diffrn_scale_ list. ; data_reflns_scale_meas_ loop_ _name '_reflns_scale_meas_F' '_reflns_scale_meas_F_squared' '_reflns_scale_meas_intensity' _category reflns_scale _type numb _type_conditions esd _enumeration_range 0.0: _list yes _list_reference '_reflns_scale_group_code' _definition ; Scales associated with _reflns_scale_group_code. ; ################## ## REFLNS_SHELL ## ################## data_reflns_shell_[] _name '_reflns_shell_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _reflns_shell_d_res_high _reflns_shell_d_res_low _reflns_shell_meanI_over_uI_gt _reflns_shell_number_measured_gt _reflns_shell_number_unique_gt _reflns_shell_percent_possible_gt _reflns_shell_Rmerge_F_gt 31.38 3.82 69.8 9024 2540 96.8 1.98 3.82 3.03 26.1 7413 2364 95.1 3.85 3.03 2.65 10.5 5640 2123 86.2 6.37 2.65 2.41 6.4 4322 1882 76.8 8.01 2.41 2.23 4.3 3247 1714 70.4 9.86 2.23 2.10 3.1 1140 812 33.3 13.99 ; ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the REFLNS_SHELL category record details about the reflections used to determine the ATOM_SITE data items, as broken down by shells of resolution. ; data_reflns_shell_d_res_high _name '_reflns_shell_d_res_high' _category reflns_shell _type numb _list yes _enumeration_range 0.0: _units A _units_detail 'angstroms' _definition ; The highest resolution in angstroms for the reflections in this shell. This is the smallest d value. ; data_reflns_shell_d_res_low _name '_reflns_shell_d_res_low' _category reflns_shell _type numb _list yes _enumeration_range 0.0: _units A _units_detail 'angstroms' _definition ; The lowest resolution in angstroms for the reflections in this shell. This is the largest d value. ; data_reflns_shell_meanI_over_sigI_all _name '_reflns_shell_meanI_over_sigI_all' _category reflns_shell _type numb _related_item '_reflns_shell_meanI_over_uI_all' _related_function replace _list yes _definition ; The ratio of the mean of the intensities of all reflections in this shell to the mean of the standard uncertainties of the intensities of all reflections in the resolution shell. ; data_reflns_shell_meanI_over_sigI_gt _name '_reflns_shell_meanI_over_sigI_gt' _category reflns_shell _type numb _related_item '_reflns_shell_meanI_over_uI_gt' _related_function replace _list yes _definition ; The ratio of the mean of the intensities of the significantly intense reflections (see _reflns_threshold_expression) in this shell to the mean of the standard uncertainties of the intensities of the significantly intense reflections in the resolution shell. ; data_reflns_shell_meanI_over_sigI_obs _name '_reflns_shell_meanI_over_sigI_obs' _category reflns_shell _type numb _related_item '_reflns_shell_meanI_over_sigI_gt' _related_function replace _list yes _definition ; The ratio of the mean of the intensities of the reflections classified as 'observed' (see _reflns_observed_criterion) in this shell to the mean of the standard uncertainties of the intensities of the 'observed' reflections in the resolution shell. ; data_reflns_shell_meanI_over_uI_all _name '_reflns_shell_meanI_over_uI_all' _category reflns_shell _type numb _related_item '_reflns_shell_meanI_over_sigI_all' _related_function alternate _list yes _definition ; The ratio of the mean of the intensities of all reflections in this shell to the mean of the standard uncertainties of the intensities of all reflections in the resolution shell. ; data_reflns_shell_meanI_over_uI_gt _name '_reflns_shell_meanI_over_uI_gt' _category reflns_shell _type numb loop_ _related_item _related_function '_reflns_shell_meanI_over_sigI_gt' alternate '_reflns_shell_meanI_over_sigI_obs' alternate _list yes _definition ; The ratio of the mean of the intensities of the significantly intense reflections (see _reflns_threshold_expression) in this shell to the mean of the standard uncertainties of the intensities of the significantly intense reflections in the resolution shell. ; data_reflns_shell_number_measured_all _name '_reflns_shell_number_measured_all' _category reflns_shell _type numb _list yes _enumeration_range 0.0: _definition ; The total number of reflections measured for this resolution shell. ; data_reflns_shell_number_measured_gt _name '_reflns_shell_number_measured_gt' _category reflns_shell _type numb _related_item '_reflns_shell_number_measured_obs' _related_function alternate _list yes _enumeration_range 0.0: _definition ; The number of significantly intense reflections (see _reflns_threshold_expression) measured for this resolution shell. ; data_reflns_shell_number_measured_obs _name '_reflns_shell_number_measured_obs' _category reflns_shell _type numb _related_item '_reflns_shell_number_measured_gt' _related_function replace _list yes _enumeration_range 0.0: _definition ; The number of reflections classified as 'observed' (see _reflns_observed_criterion) measured for this resolution shell. ; data_reflns_shell_number_possible _name '_reflns_shell_number_possible' _category reflns_shell _type numb _list yes _enumeration_range 0: _definition ; The number of unique reflections it is possible to measure in this reflection shell. ; data_reflns_shell_number_unique_all _name '_reflns_shell_number_unique_all' _category reflns_shell _type numb _list yes _enumeration_range 0: _definition ; The total number of measured reflections resulting from merging measured symmetry-equivalent reflections for this resolution shell. ; data_reflns_shell_number_unique_gt _name '_reflns_shell_number_unique_gt' _category reflns_shell _type numb _related_item '_reflns_shell_number_unique_obs' _related_function alternate _list yes _enumeration_range 0: _definition ; The total number of significantly intense reflections (see _reflns_threshold_expression) resulting from merging measured symmetry-equivalent reflections for this resolution shell. ; data_reflns_shell_number_unique_obs _name '_reflns_shell_number_unique_obs' _category reflns_shell _type numb _related_item '_reflns_shell_number_unique_gt' _related_function replace _list yes _enumeration_range 0: _definition ; The total number of reflections classified as 'observed' (see _reflns_observed_criterion) resulting from merging measured symmetry-equivalent reflections for this resolution shell. ; data_reflns_shell_percent_possible_all _name '_reflns_shell_percent_possible_all' _category reflns_shell _type numb _list yes _enumeration_range 0.0:100.0 _definition ; The percentage of geometrically possible reflections represented by all reflections measured for this resolution shell. ; data_reflns_shell_percent_possible_gt _name '_reflns_shell_percent_possible_gt' _category reflns_shell _type numb _related_item '_reflns_shell_percent_possible_obs' _related_function alternate _list yes _enumeration_range 0.0:100.0 _definition ; The percentage of geometrically possible reflections represented by significantly intense reflections (see _reflns_threshold_expression) measured for this resolution shell. ; data_reflns_shell_percent_possible_obs _name '_reflns_shell_percent_possible_obs' _category reflns_shell _type numb _related_item '_reflns_shell_percent_possible_gt' _related_function replace _list yes _enumeration_range 0.0:100.0 _definition ; The percentage of geometrically possible reflections represented by reflections classified as 'observed' (see _reflns_observed_criterion) measured for this resolution shell. ; data_reflns_shell_Rmerge_F_all _name '_reflns_shell_Rmerge_F_all' _category reflns_shell _type numb _list yes _enumeration_range 0.0: _definition ; The value of Rmerge(F) for all reflections in a given shell. sum~i~ ( sum~j~ | F~j~ - | ) Rmerge(F) = -------------------------------- sum~i~ ( sum~j~ ) F~j~ = the amplitude of the jth observation of reflection i = the mean of the amplitudes of all observations of reflection i sum~i~ is taken over all reflections sum~j~ is taken over all observations of each reflection. ; data_reflns_shell_Rmerge_F_gt _name '_reflns_shell_Rmerge_F_gt' _category reflns_shell _type numb _related_item '_reflns_shell_Rmerge_F_obs' _related_function alternate _list yes _enumeration_range 0.0: _definition ; The value of Rmerge(F) for significantly intense reflections (see _reflns_threshold_expression) in a given shell. sum~i~ ( sum~j~ | F~j~ - | ) Rmerge(F) = -------------------------------- sum~i~ ( sum~j~ ) F~j~ = the amplitude of the jth observation of reflection i = the mean of the amplitudes of all observations of reflection i sum~i~ is taken over all reflections sum~j~ is taken over all observations of each reflection. ; data_reflns_shell_Rmerge_F_obs _name '_reflns_shell_Rmerge_F_obs' _category reflns_shell _type numb _related_item '_reflns_shell_Rmerge_F_gt' _related_function replace _list yes _enumeration_range 0.0: _definition ; The value of Rmerge(F) for reflections classified as 'observed' (see _reflns_observed_criterion) in a given shell. sum~i~ ( sum~j~ | F~j~ - | ) Rmerge(F) = -------------------------------- sum~i~ ( sum~j~ ) F~j~ = the amplitude of the jth observation of reflection i = the mean of the amplitudes of all observations of reflection i sum~i~ is taken over all reflections sum~j~ is taken over all observations of each reflection. ; data_reflns_shell_Rmerge_I_all _name '_reflns_shell_Rmerge_I_all' _category reflns_shell _type numb _list yes _enumeration_range 0.0: _definition ; The value of Rmerge(I) for all reflections in a given shell. sum~i~ ( sum~j~ | I~j~ - | ) Rmerge(I) = -------------------------------- sum~i~ ( sum~j~ ) I~j~ = the intensity of the jth observation of reflection i = the mean of the intensities of all observations of reflection i sum~i~ is taken over all reflections sum~j~ is taken over all observations of each reflection. ; data_reflns_shell_Rmerge_I_gt _name '_reflns_shell_Rmerge_I_gt' _category reflns_shell _type numb _related_item '_reflns_shell_Rmerge_I_obs' _related_function alternate _list yes _enumeration_range 0.0: _definition ; The value of Rmerge(I) for significantly intense reflections (see _reflns_threshold_expression) in a given shell. sum~i~ ( sum~j~ | I~j~ - | ) Rmerge(I) = -------------------------------- sum~i~ ( sum~j~ ) I~j~ = the intensity of the jth observation of reflection i = the mean of the intensities of all observations of reflection i sum~i~ is taken over all reflections sum~j~ is taken over all observations of each reflection. ; data_reflns_shell_Rmerge_I_obs _name '_reflns_shell_Rmerge_I_obs' _category reflns_shell _type numb _related_item '_reflns_shell_Rmerge_I_gt' _related_function replace _list yes _enumeration_range 0.0: _definition ; The value of Rmerge(I) for reflections classified as 'observed' (see _reflns_observed_criterion) in a given shell. sum~i~ ( sum~j~ | I~j~ - | ) Rmerge(I) = -------------------------------- sum~i~ ( sum~j~ ) I~j~ = the intensity of the jth observation of reflection i = the mean of the intensities of all observations of reflection i sum~i~ is taken over all reflections sum~j~ is taken over all observations of each reflection. ; ################# ## SPACE_GROUP ## ################# data_space_group_[] _name '_space_group_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _space_group_id 1 _space_group_name_H-M_alt 'C 2/c' _space_group_IT_number 15 _space_group_name_Hall '-C 2yc' _space_group_crystal_system monoclinic ; ; Example 1 - the monoclinic space group No. 15 with unique axis b. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Contains all the data items that refer to the space group as a whole, such as its name or crystal system. They may be looped, for example, in a list of space groups and their properties. Only a subset of the SPACE_GROUP category items appear in the core dictionary. The remainder are found in the symmetry CIF dictionary. Space-group types are identified by their number as given in International Tables for Crystallography Vol. A. Specific settings of the space groups can be identified either by their Hall symbol or by specifying their symmetry operations. The commonly used Hermann-Mauguin symbol determines the space-group type uniquely but several different Hermann-Mauguin symbols may refer to the same space-group type. A Hermann-Mauguin symbol contains information on the choice of the basis, but not on the choice of origin. Different formats for the Hermann-Mauguin symbol are found in the symmetry CIF dictionary. ; data_space_group_crystal_system _name '_space_group_crystal_system' _category space_group _type char _list both _list_reference '_space_group_id' _related_item '_symmetry_cell_setting' _related_function alternate loop_ _enumeration triclinic monoclinic orthorhombic tetragonal trigonal hexagonal cubic _definition ; The name of the system of geometric crystal classes of space groups (crystal system) to which the space group belongs. Note that rhombohedral space groups belong to the trigonal system. ; data_space_group_id _name '_space_group_id' _category space_group _type char _list yes _list_mandatory yes _list_link_child '_space_group_symop_sg_id' _definition ; This is an identifier needed if _space_group_ items are looped. ; data_space_group_IT_number _name '_space_group_IT_number' _category space_group _type numb _list both _list_reference '_space_group_id' _related_item '_symmetry_Int_Tables_number' _related_function alternate _enumeration_range 1:230 _definition ; The number as assigned in International Tables for Crystallography Vol. A, specifying the proper affine class (i.e. the orientation-preserving affine class) of space groups (crystallographic space-group type) to which the space group belongs. This number defines the space-group type but not the coordinate system in which it is expressed. ; data_space_group_name_Hall _name '_space_group_name_Hall' _category space_group _type char _list both _list_reference '_space_group_id' _related_item '_symmetry_space_group_name_Hall' _related_function alternate loop_ _example _example_detail 'P 2c -2ac' 'equivalent to Pca21' '-I 4bd 2ab 3' 'equivalent to Ia-3d' _definition ; Space-group symbol defined by Hall. Each component of the space-group name is separated by a space or an underscore. The use of a space is strongly recommended. The underscore is only retained because it was used in older files. It should not be used in new CIFs. _space_group_name_Hall uniquely defines the space group and its reference to a particular coordinate system. Ref: Hall, S. R. (1981). Acta Cryst. A37, 517-525; erratum (1981), A37, 921. [See also International Tables for Crystallography, Vol. B (2001), Chapter 1.4, Appendix 1.4.2] ; data_space_group_name_H-M_alt _name '_space_group_name_H-M_alt' _category space_group _type char _list both _list_reference '_space_group_id' _related_item '_symmetry_space_group_name_H-M' _related_function alternate loop_ _example _example_detail ; loop_ _space_group_id _space_group_name_H-M_alt 1 'C m c m' 2 'C 2/c 2/m 21/m' 3 'A m a m' ; 'three examples for space group No. 63' _definition ; _space_group_name_H-M_alt allows any Hermann-Mauguin symbol to be given. The way in which this item is used is determined by the user and in general is not intended to be interpreted by computer. It may, for example, be used to give one of the extended Hermann-Mauguin symbols given in Table 4.3.2.1 of International Tables for Crystallography Vol. A (2002) or a Hermann-Mauguin symbol for a conventional or unconventional setting. Each component of the space-group name is separated by a space or an underscore. The use of a space is strongly recommended. The underscore is only retained because it was used in older files. It should not be used in new CIFs. Subscripts should appear without special symbols. Bars should be given as negative signs before the numbers to which they apply. The commonly used Hermann-Mauguin symbol determines the space- group type uniquely but a given space-group type may be described by more than one Hermann-Mauguin symbol. The space- group type is best described using _space_group_IT_number. The Hermann-Mauguin symbol may contain information on the choice of basis, but not on the choice of origin. To define the setting uniquely, use _space_group_name_Hall or list the symmetry operations. ; ####################### ## SPACE_GROUP_SYMOP ## ####################### data_space_group_symop_[] _name '_space_group_symop_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _space_group_symop_id _space_group_symop_operation_xyz 1 x,y,z 2 -x,-y,-z 3 -x,1/2+y,1/2-z 4 x,1/2-y,1/2+z ; ; Example 1 - the symmetry operations for the space group P21/c. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Contains information about the symmetry operations of the space group. ; data_space_group_symop_id _name '_space_group_symop_id' _type char _category space_group_symop _list yes _list_mandatory yes _related_item '_symmetry_equiv_pos_site_id' _related_function alternate _definition ; An arbitrary identifier that uniquely labels each symmetry operation in the list. ; data_space_group_symop_operation_xyz _name '_space_group_symop_operation_xyz' _category space_group_symop _type char _list both _list_reference '_space_group_symop_id' _enumeration_default 'x,y,z' _related_item '_symmetry_equiv_pos_as_xyz' _related_function alternate loop_ _example _example_detail 'x,1/2-y,1/2+z' ; glide reflection through the plane (x,1/4,z), with glide vector (1/2)c ; _definition ; A parsable string giving one of the symmetry operations of the space group in algebraic form. If W is a matrix representation of the rotational part of the symmetry operation defined by the positions and signs of x, y and z, and w is a column of translations defined by fractions, an equivalent position X' is generated from a given position X by the equation X' = WX + w (Note: X is used to represent bold_italics_x in International Tables for Crystallography Vol. A, Part 5) When a list of symmetry operations is given, it must contain a complete set of coordinate representatives which generates all the operations of the space group by the addition of all primitive translations of the space group. Such representatives are to be found as the coordinates of the general-equivalent position in International Tables for Crystallography Vol. A (2002), to which it is necessary to add any centring translations shown above the general-equivalent position. That is to say, it is necessary to list explicitly all the symmetry operations required to generate all the atoms in the unit cell defined by the setting used. ; data_space_group_symop_sg_id _name '_space_group_symop_sg_id' _category space_group_symop _type numb _list both _list_mandatory no _list_reference '_space_group_symop_id' _list_link_parent '_space_group_id' _definition ; This must match a particular value of _space_group_id, allowing the symmetry operation to be identified with a particular space group. ; ############## ## SYMMETRY ## ############## data_symmetry_[] _name '_symmetry_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; _symmetry_cell_setting orthorhombic _symmetry_space_group_name_H-M 'P 21 21 21' _symmetry_space_group_name_Hall 'P 2ac 2ab' ; ; Example 1 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the SYMMETRY category record details about the space-group symmetry. ; data_symmetry_cell_setting _name '_symmetry_cell_setting' _category symmetry _type char loop_ _enumeration triclinic monoclinic orthorhombic tetragonal rhombohedral trigonal hexagonal cubic _related_item '_space_group_crystal_system' _related_function replace _definition ; The cell settings for this space-group symmetry. ; data_symmetry_Int_Tables_number _name '_symmetry_Int_Tables_number' _category symmetry _type numb _enumeration_range 1:230 _related_item '_space_group_IT_number' _related_function replace _definition ; Space-group number from International Tables for Crystallography Vol. A (2002). ; data_symmetry_space_group_name_Hall _name '_symmetry_space_group_name_Hall' _category symmetry _type char _related_item '_space_group_name_Hall' _related_function replace loop_ _example '-P 2ac 2n' '-R 3 2"' 'P 61 2 2 (0 0 -1)' _definition ; Space-group symbol as described by Hall. This symbol gives the space-group setting explicitly. Leave spaces between the separate components of the symbol. Ref: Hall, S. R. (1981). Acta Cryst. A37, 517-525; erratum (1981), A37, 921. ; data_symmetry_space_group_name_H-M _name '_symmetry_space_group_name_H-M' _category symmetry _type char _related_item '_space_group_name_H-M_alt' _related_function replace loop_ _example 'P 1 21/m 1' 'P 2/n 2/n 2/n (origin at -1)' 'R -3 2/m' _definition ; Hermann-Mauguin space-group symbol. Note that the Hermann-Mauguin symbol does not necessarily contain complete information about the symmetry and the space-group origin. If used, always supply the FULL symbol from International Tables for Crystallography Vol. A (2002) and indicate the origin and the setting if it is not implicit. If there is any doubt that the equivalent positions can be uniquely deduced from this symbol, specify the _symmetry_equiv_pos_as_xyz or *_Hall data items as well. Leave spaces between symbols referring to different axes. ; #################### ## SYMMETRY_EQUIV ## #################### data_symmetry_equiv_[] _name '_symmetry_equiv_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _symmetry_equiv_pos_as_xyz +x,+y,+z 1/2-x,-y,1/2+z 1/2+x,1/2-y,-z -x,1/2+y,1/2-z ; ; Example 1 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _symmetry_equiv_pos_site_id _symmetry_equiv_pos_as_xyz 1 x,y,z 2 1/2-x,-y,1/2+z 3 1/2+x,1/2-y,-z 4 -x,1/2+y,1/2-z ; ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. Formally, the value of _symmetry_equiv_pos_site_id can be any unique character string; it is recommended that it be assigned the sequence number of the list of equivalent positions for compatibility with older files in which it did not appear. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the SYMMETRY_EQUIV category list the symmetry-equivalent positions for the space group. ; data_symmetry_equiv_pos_as_xyz _name '_symmetry_equiv_pos_as_xyz' _category symmetry_equiv _type char _list both _example -y+x,-y,1/3+z _related_item '_space_group_symop_operation_xyz' _related_function replace _definition ; Symmetry-equivalent position in the 'xyz' representation. Except for the space group P1, these data will be repeated in a loop. The format of the data item is as per International Tables for Crystallography Vol. A. (2002). All equivalent positions should be entered, including those for lattice centring and a centre of symmetry, if present. ; data_symmetry_equiv_pos_site_id _name '_symmetry_equiv_pos_site_id' _category symmetry_equiv _type numb _list yes _list_reference '_symmetry_equiv_pos_as_xyz' _related_item '_space_group_symop_id' _related_function replace _definition ; A code identifying each entry in the _symmetry_equiv_pos_as_xyz list. It is normally the sequence number of the entry in that list, and should be identified with the code 'n' in _geom_*_symmetry_ codes of the form 'n_klm'. ; ################### ## VALENCE_PARAM ## ################### data_valence_param_[] _name '_valence_param_[]' _category category_overview _type null loop_ _example _example_detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; loop_ _valence_param_id _valence_param_atom_1 _valence_param_atom_1_valence _valence_param_atom_2 _valence_param_atom_2_valence _valence_param_Ro _valence_param_B _valence_param_ref_id _valence_param_details 1 Cu 2 O -2 1.679 0.37 a . 2 Cu 2 O -2 1.649 0.37 j . 3 Cu 2 N -3 1.64 0.37 m '2-coordinate N' 4 Cu 2 N -3 1.76 0.37 m '3-coordinate N' loop_ _valence_ref_id _valence_ref_reference a 'Brown & Altermatt (1985), Acta Cryst. B41, 244-247' j 'Liu & Thorp (1993), Inorg. Chem. 32, 4102-4205' m 'See, Krause & Strub (1998), Inorg. Chem. 37, 5369-5375' ; ; Example 1 - a bond-valence parameter list with accompanying references. ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - _definition ; Data items in the VALENCE_PARAM category define the parameters used for calculating bond valences from bond lengths. In addition to the parameters, a pointer is given to the reference (in VALENCE_REF) from which the bond-valence parameters were taken. ; data_valence_param_atom_1 _name '_valence_param_atom_1' _category valence_param _type char _list yes _list_reference '_valence_param_id' _definition ; The element symbol of the first atom forming the bond whose bond-valence parameters are given in this category. ; data_valence_param_atom_1_valence _name '_valence_param_atom_1_valence' _category valence_param _type numb _list yes _list_reference '_valence_param_id' _definition ; The valence (formal charge) of the first atom whose bond-valence parameters are given in this category. ; data_valence_param_atom_2 _name '_valence_param_atom_2' _category valence_param _type char _list yes _list_reference '_valence_param_id' _definition ; The element symbol of the second atom forming the bond whose bond-valence parameters are given in this category. ; data_valence_param_atom_2_valence _name '_valence_param_atom_2_valence' _category valence_param _type numb _list yes _list_reference '_valence_param_id' _definition ; The valence (formal charge) of the second atom whose bond-valence parameters are given in this category. ; data_valence_param_B _name '_valence_param_B' _category valence_param _type numb _list yes _list_reference '_valence_param_id' _units A _units_detail Angstrom _definition ; The bond-valence parameter B used in the expression s = exp[(Ro - R)/B] where s is the valence of a bond of length R. ; data_valence_param_details _name '_valence_param_details' _category valence_param _type char _list yes _list_reference '_valence_param_id' _definition ; Details of or comments on the bond-valence parameters. ; data_valence_param_id _name '_valence_param_id' _category valence_param _type char _list yes _definition ; An identifier for the valence parameters of a bond between the given atoms. ; data_valence_param_ref_id _name '_valence_param_ref_id' _category valence_param _type char _list yes _list_reference '_valence_param_id' _list_link_parent '_valence_ref_id' _definition ; An identifier which links to the reference to the source from which the bond-valence parameters are taken. A child of _valence_ref_id, which it must match. ; data_valence_param_Ro _name '_valence_param_Ro' _category valence_param _type numb _list yes _list_reference '_valence_param_id' _units A _units_detail Angstrom _definition ; The bond-valence parameter Ro used in the expression s = exp[(Ro - R)/B] where s is the valence of a bond of length R. ; ################# ## VALENCE_REF ## ################# data_valence_ref_[] _name '_valence_ref_[]' _category category_overview _type null _definition ; Data items in the VALENCE_REF category list the references from which the bond-valence parameters have been taken. ; data_valence_ref_id _name '_valence_ref_id' _category valence_ref _type char _list yes _list_reference '_valence_ref_id' _list_link_child '_valence_param_ref_id' _definition ; An identifier for items in this category. Parent of _valence_param_ref_id, which must have the same value. ; data_valence_ref_reference _name '_valence_ref_reference' _type char _category valence_ref _list yes _list_reference '_valence_ref_id' _definition ; Literature reference from which the valence parameters identified by _valence_param_id were taken. ; #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof ./CBFlib-0.9.2.2/doc/Idiffrn_scan_frame_axis.displacement_increment.html0000644000076500007650000000603711603702115024535 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan_frame_axis.displacement_increment

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_scan_frame_axis.displacement_increment

Name:
'_diffrn_scan_frame_axis.displacement_increment'

Definition:

        The increment for this frame for the displacement setting of
               the specified axis in millimetres.  The sum of the values
               of _diffrn_scan_frame_axis.displacement and
               _diffrn_scan_frame_axis.displacement_increment is the
               angular setting of the axis at the end of the integration
               time for this frame.

Type: float

Mandatory item: no


Enumeration default: 0.0

Category: diffrn_scan_frame_axis

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_detector.diffrn_id.html0000644000076500007650000000475411603702115020440 0ustar yayayaya (IUCr) CIF Definition save__diffrn_detector.diffrn_id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_detector.diffrn_id

Name:
'_diffrn_detector.diffrn_id'

Definition:

        This data item is a pointer to _diffrn.id in the DIFFRN
               category.

               The value of _diffrn.id uniquely defines a set of
               diffraction data.

Type: code

Mandatory item: yes

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_scan_frame_axis.angle.html0000644000076500007650000000514311603702115021104 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan_frame_axis.angle

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_scan_frame_axis.angle

Name:
'_diffrn_scan_frame_axis.angle'

Definition:

        The setting of the specified axis in degrees for this frame.
               This is the setting at the start of the integration time.

Type: float

Mandatory item: no


Enumeration default: 0.0

Category: diffrn_scan_frame_axis

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_detector.dtime.html0000644000076500007650000000534111603702115017607 0ustar yayayaya (IUCr) CIF Definition save__diffrn_detector.dtime

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_detector.dtime

Name:
'_diffrn_detector.dtime'

Definition:

        The deadtime in microseconds of the detector(s) used to
               measure the diffraction intensities.

Type: float

Mandatory item: no

Aliases:


_diffrn_radiation_detector_dtime (cifdic.c91 version 1.0)
_diffrn_detector_dtime (cif_core.dic version 2.0)
The permitted range is [0.0, infinity)

Category: diffrn_detector

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Carray_structure.html0000644000076500007650000000614211603702115016575 0ustar yayayaya (IUCr) CIF Definition save_array_structure

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

Category ARRAY_STRUCTURE

Name:
'array_structure'

Description:

    Data items in the ARRAY_STRUCTURE category record the organization and
     encoding of array data that may be stored in the ARRAY_DATA category.

Example:

Example 1 -
 
     loop_
    _array_structure.id
    _array_structure.encoding_type
    _array_structure.compression_type
    _array_structure.byte_order
     image_1       "unsigned 16-bit integer"  none  little_endian



Category groups:
    inclusive_group
    array_data_group
Category key:
    _array_structure.id

Mandatory category: no

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_scan_frame.date.html0000644000076500007650000000473511603702115017715 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan_frame.date

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_scan_frame.date

Name:
'_diffrn_scan_frame.date'

Definition:

        The date and time of the start of the frame being scanned.

Type: yyyy-mm-dd

Mandatory item: no

Category: diffrn_scan_frame

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/index.html0000644000076500007650000005560111603702115014347 0ustar yayayaya (IUCr) Image dictionary (imgCIF) definitions

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Image dictionary (imgCIF) version 1.5.4 definitions

##############################################################################
#                                                                            #
#                       Image CIF Dictionary (imgCIF)                        #
#             and Crystallographic Binary File Dictionary (CBF)              #
#            Extending the Macromolecular CIF Dictionary (mmCIF)             #
#                                                                            #
#                              Version 1.5.4                                 #
#                              of 2007-07-28                                 #
#    ###################################################################     #
#    # *** WARNING *** THIS IS A DRAFT FOR DISCUSSSION *** WARNING *** #     #
#    #                 SUBJECT TO CHANGE WITHOUT NOTICE                #     #
#    #       SEND COMMENTS TO imgcif-l@iucr.org CITING THE VERSION     #     #
#    ###################################################################     #
#                  This draft edited by H. J. Bernstein                      #
#                                                                            #
#     by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook    #
#                                                                            #
# This dictionary was adapted from format discussed at the imgCIF Workshop,  #
# held at BNL Oct 1997 and the Crystallographic Binary File Format Draft     #
# Proposal by Andrew Hammersley.  The first DDL 2.1 Version was created by   #
# John Westbrook.  This version was drafted by Herbert J. Bernstein and      #
# incorporates comments by I. David Brown, John Westbrook, Brian McMahon,    #
# Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li, Gotzon Madariaga,         #
# Frances C. Bernstein, Chris Nielsen, Nicola Ashcroft and others.           #
##############################################################################

Definitions are arranged alphabetically by category and within category.

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/cif_img_1.6.4_2Jul11.html0000644000076500007650000140052111603745600016423 0ustar yayayaya cif_img.dic v1.6.4

# [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib] #

# imgCIF/CBF #

# Extensions Dictionary #

data_cif_img.dic

    _datablock.id               cif_img.dic
    _datablock.description
;
##############################################################################
#                                                                            #
#                       Image CIF Dictionary (imgCIF)                        #
#             and Crystallographic Binary File Dictionary (CBF)              #
#            Extending the Macromolecular CIF Dictionary (mmCIF)             #
#                                                                            #
#                              Version 1.6.4                                 #
#                              of 2011-07-02                                 #
#    ###################################################################     #
#    # *** WARNING *** THIS IS A DRAFT FOR DISCUSSSION *** WARNING *** #     #
#    #                 SUBJECT TO CHANGE WITHOUT NOTICE                #     #
#    #       SEND COMMENTS TO imgcif-l@iucr.org CITING THE VERSION     #     #
#    ###################################################################     #
#                  This draft edited by H. J. Bernstein                      #
#                                                                            #
#     by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook    #
#                                                                            #
# This dictionary was adapted from format discussed at the imgCIF Workshop,  #
# held at BNL Oct 1997 and the Crystallographic Binary File Format Draft     #
# Proposal by Andrew Hammersley.  The first DDL 2.1 Version was created by   #
# John Westbrook.  This version was drafted by Herbert J. Bernstein and      #
# incorporates comments by I. David Brown, John Westbrook, Brian McMahon,    #
# Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li, Gotzon Madariaga,         #
# Frances C. Bernstein, Chris Nielsen, Nicola Ashcroft and others.           #
##############################################################################

##############################################################################
#    CONTENTS
#
#        CATEGORY_GROUP_LIST
#        SUB_CATEGORY
#
#        category  ARRAY_DATA
#
#                  _array_data.array_id
#                  _array_data.binary_id
#                  _array_data.data
#                  _array_data.header_contents
#                  _array_data.header_convention
#                  _array_data.variant
#
#        category  ARRAY_ELEMENT_SIZE
#
#                  _array_element_size.array_id
#                  _array_element_size.index
#                  _array_element_size.size
#                  _array_element_size.variant
#
#        category  ARRAY_INTENSITIES
#
#                  _array_intensities.array_id
#                  _array_intensities.binary_id
#                  _array_intensities.gain
#                  _array_intensities.gain_esd
#                  _array_intensities.linearity
#                  _array_intensities.offset
#                  _array_intensities.scaling
#                  _array_intensities.overload
#                  _array_intensities.undefined_value
#                  _array_intensities.pixel_fast_bin_size
#                  _array_intensities.pixel_slow_bin_size
#                  _array_intensities.pixel_binning_method
#                  _array_intensities.variant
#
#        category  ARRAY_STRUCTURE
#
#                  _array_structure.byte_order
#                  _array_structure.compression_type
#                  _array_structure.compression_type_flag
#                  _array_structure.encoding_type
#                  _array_structure.id
#                  _array_structure.variant
#
#        category  ARRAY_STRUCTURE_LIST
#
#                  _array_structure_list.axis_set_id
#                  _array_structure_list.array_id
#                  _array_structure_list.dimension
#                  _array_structure_list.direction
#                  _array_structure_list.index
#                  _array_structure_list.precedence
#                  _array_structure_list.variant
#
#        category  ARRAY_STRUCTURE_LIST_AXIS
#
#                  _array_structure_list_axis.axis_id
#                  _array_structure_list_axis.axis_set_id
#                  _array_structure_list_axis.angle
#                  _array_structure_list_axis.angle_increment
#                  _array_structure_list_axis.displacement
#                  _array_structure_list_axis.fract_displacement
#                  _array_structure_list_axis.displacement_increment
#                  _array_structure_list_axis.fract_displacement_increment
#                  _array_structure_list_axis.angular_pitch
#                  _array_structure_list_axis.radial_pitch
#                  _array_structure_list_axis.reference_angle
#                  _array_structure_list_axis.reference_displacement
#                  _array_structure_list_axis.variant
#
#        category  AXIS
#
#                  _axis.depends_on
#                  _axis.equipment
#                  _axis.id
#                  _axis.offset[1]
#                  _axis.offset[2]
#                  _axis.offset[3]
#                  _axis.type
#                  _axis.system
#                  _axis.vector[1]
#                  _axis.vector[2]
#                  _axis.vector[3]
#                  _axis.variant
#
#        category  DIFFRN_DATA_FRAME
#
#                  _diffrn_data_frame.array_id
#                  _diffrn_data_frame.binary_id
#                  _diffrn_data_frame.center_fast
#                  _diffrn_data_frame.center_slow
#                  _diffrn_data_frame.center_units
#                  _diffrn_data_frame.detector_element_id
#                  _diffrn_data_frame.id
#                  _diffrn_data_frame.details
#                  _diffrn_data_frame.variant
#
#        category  DIFFRN_DETECTOR
#
#                  _diffrn_detector.details
#                  _diffrn_detector.detector
#                  _diffrn_detector.diffrn_id
#                  _diffrn_detector.dtime
#                  _diffrn_detector.id
#                  _diffrn_detector.number_of_axes
#                  _diffrn_detector.type
#                  _diffrn_detector.variant
#
#        category  DIFFRN_DETECTOR_AXIS
#
#                  _diffrn_detector_axis.axis_id
#                  _diffrn_detector_axis.detector_id
#                  _diffrn_detector_axis.variant
#
#        category  DIFFRN_DETECTOR_ELEMENT
#
#                  _diffrn_detector_element.id
#                  _diffrn_detector_element.detector_id
#                  _diffrn_detector_element.reference_center_fast
#                  _diffrn_detector_element.reference_center_slow
#                  _diffrn_detector_element.reference_center_units
#                  _diffrn_detector_element.variant
#
#        category  DIFFRN_MEASUREMENT
#
#                  _diffrn_measurement.diffrn_id
#                  _diffrn_measurement.details
#                  _diffrn_measurement.device
#                  _diffrn_measurement.device_details
#                  _diffrn_measurement.device_type
#                  _diffrn_measurement.id
#                  _diffrn_measurement.method
#                  _diffrn_measurement.number_of_axes
#                  _diffrn_measurement.sample_detector_distance
#                  _diffrn_measurement.sample_detector_voffset
#                  _diffrn_measurement.specimen_support
#                  _diffrn_measurement.variant
#
#        category  DIFFRN_MEASUREMENT_AXIS
#
#                  _diffrn_measurement_axis.axis_id
#                  _diffrn_measurement_axis.measurement_device
#                  _diffrn_measurement_axis.measurement_id
#                  _diffrn_measurement_axis.variant
#
#        category  DIFFRN_RADIATION
#
#                  _diffrn_radiation.collimation
#                  _diffrn_radiation.diffrn_id
#                  _diffrn_radiation.div_x_source
#                  _diffrn_radiation.div_y_source
#                  _diffrn_radiation.div_x_y_source
#                  _diffrn_radiation.filter_edge'
#                  _diffrn_radiation.inhomogeneity
#                  _diffrn_radiation.monochromator
#                  _diffrn_radiation.polarisn_norm
#                  _diffrn_radiation.polarisn_ratio
#                  _diffrn_radiation.polarizn_source_norm
#                  _diffrn_radiation.polarizn_source_ratio
#                  _diffrn_radiation.probe
#                  _diffrn_radiation.type
#                  _diffrn_radiation.xray_symbol
#                  _diffrn_radiation.wavelength_id
#                  _diffrn_radiation.variant
#
#        category  DIFFRN_REFLN
#
#                  _diffrn_refln.frame_id
#                  _diffrn_refln.variant
#
#        category  DIFFRN_SCAN
#
#                  _diffrn_scan.id
#                  _diffrn_scan.date_end
#                  _diffrn_scan.date_start
#                  _diffrn_scan.integration_time
#                  _diffrn_scan.frame_id_start
#                  _diffrn_scan.frame_id_end
#                  _diffrn_scan.frames
#                  _diffrn_scan.time_period
#                  _diffrn_scan.time_rstrt_incr
#                  _diffrn_scan.variant
#
#        category  DIFFRN_SCAN_AXIS
#
#                  _diffrn_scan_axis.axis_id
#                  _diffrn_scan_axis.angle_start
#                  _diffrn_scan_axis.angle_range
#                  _diffrn_scan_axis.angle_increment
#                  _diffrn_scan_axis.angle_rstrt_incr
#                  _diffrn_scan_axis.displacement_start
#                  _diffrn_scan_axis.displacement_range
#                  _diffrn_scan_axis.displacement_increment
#                  _diffrn_scan_axis.displacement_rstrt_incr
#                  _diffrn_scan_axis.reference_angle
#                  _diffrn_scan_axis.reference_displacement
#                  _diffrn_scan_axis.scan_id
#                  _diffrn_scan_axis.variant
#
#        category  DIFFRN_SCAN_FRAME
#
#                  _diffrn_scan_frame.date
#                  _diffrn_scan_frame.frame_id
#                  _diffrn_scan_frame.frame_number
#                  _diffrn_scan_frame.integration_time
#                  _diffrn_scan_frame.scan_id
#                  _diffrn_scan_frame.time_period
#                  _diffrn_scan_frame.time_rstrt_incr
#                  _diffrn_scan_frame.variant
#
#        category  DIFFRN_SCAN_FRAME_AXIS
#
#                  _diffrn_scan_frame_axis.axis_id
#                  _diffrn_scan_frame_axis.angle
#                  _diffrn_scan_frame_axis.angle_increment
#                  _diffrn_scan_frame_axis.angle_rstrt_incr
#                  _diffrn_scan_frame_axis.displacement
#                  _diffrn_scan_frame_axis.displacement_increment
#                  _diffrn_scan_frame_axis.displacement_rstrt_incr
#                  _diffrn_scan_frame_axis.reference_angle
#                  _diffrn_scan_frame_axis.reference_displacement
#                  _diffrn_scan_frame_axis.frame_id
#                  _diffrn_scan_frame_axis.variant
#
#        category  DIFFRN_SCAN_FRAME_MONITOR
#
#                  _diffrn_scan_frame_monitor.id
#                  _diffrn_scan_frame_monitor.detector_id
#                  _diffrn_scan_frame_monitor.scan_id
#                  _diffrn_data_frame_monitor.frame_id
#                  _diffrn_data_frame_monitor.integration_time
#                  _diffrn_data_frame_monitor.monitor_value
#                  _diffrn_data_frame_monitor.variant
#
#        category  MAP
#
#                  _map.details
#                  _map.diffrn_id
#                  _map.entry_id
#                  _map.id
#                  _map.variant
#
#       category   MAP_SEGMENT
#
#                  _map_segment.array_id
#                  _map_segment.binary_id
#                  _map_segment.mask_array_id
#                  _map_segment.mask_binary_id
#                  _map_segment.id
#                  _map_segment.map_id
#                  _map_segment.details
#                  _map_segment.variant
#
#       category   VARIANT
#
#                  _variant.details
#                  _variant.role
#                  _variant.timestamp
#                  _variant.variant
#                  _variant.variant_of
#
#       ***DEPRECATED*** data items
#
#                  _diffrn_detector_axis.id
#                  _diffrn_detector_element.center[1]
#                  _diffrn_detector_element.center[2]
#                  _diffrn_measurement_axis.id
#
#       ***DEPRECATED*** category  DIFFRN_FRAME_DATA
#
#                  _diffrn_frame_data.array_id
#                  _diffrn_frame_data.binary_id
#                  _diffrn_frame_data.detector_element_id
#                  _diffrn_frame_data.id
#                  _diffrn_frame_data.details
#
#
#        ITEM_TYPE_LIST
#        ITEM_UNITS_LIST
#        DICTIONARY_HISTORY
#
##############################################################################


ARRAY_DATA_GROUP Categories that describe array data.
ARRAY_DATA Data items in the ARRAY_DATA category are the containers for the array data items described in the category ARRAY_STRUCTURE.

It is recognized that the data in this category needs to be used in two distinct ways. During a data collection the lack of ancillary data and timing constraints in processing data may dictate the need to make a 'miniCBF' nothing more than an essential minimum of information to record the results of the data collection. In that case it is proper to use the ARRAY_DATA category as a container for just a single image and a compacted, beam-line dependent list of data collection parameter values. In such a case, only the tags '_array_data.header_convention', '_array_data.header_contents' and '_array_data.data' need be populated.

For full processing and archiving, most of the tags in this dictionary will need to be populated.

ARRAY_ELEMENT_SIZE Data items in the ARRAY_ELEMENT_SIZE category record the physical size of array elements along each array dimension.
ARRAY_INTENSITIES Data items in the ARRAY_INTENSITIES category record the information required to recover the intensity data from the set of data values stored in the ARRAY_DATA category.

The detector may have a complex relationship between the raw intensity values and the number of incident photons. In most cases, the number stored in the final array will have a simple linear relationship to the actual number of incident photons, given by _array_intensities.gain. If raw, uncorrected values are presented (e.g. for calibration experiments), the value of _array_intensities.linearity will be 'raw' and _array_intensities.gain will not be used.

ARRAY_STRUCTURE Data items in the ARRAY_STRUCTURE category record the organization and encoding of array data that may be stored in the ARRAY_DATA category.
  ARRAY_STRUCTURE_LIST Data items in the ARRAY_STRUCTURE_LIST category record the size and organization of each array dimension.

The relationship to physical axes may be given.

  ARRAY_STRUCTURE_LIST_AXIS Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe the physical settings of sets of axes for the centres of pixels that correspond to data points described in the ARRAY_STRUCTURE_LIST category.

In the simplest cases, the physical increments of a single axis correspond to the increments of a single array index. More complex organizations, e.g. spiral scans, may require coupled motions along multiple axes.

Note that a spiral scan uses two coupled axes: one for the angular direction and one for the radial direction. This differs from a cylindrical scan for which the two axes are not coupled into one set.

AXIS_GROUP Categories that describe axes.
AXIS Data items in the AXIS category record the information required to describe the various goniometer, detector, source and other axes needed to specify a data collection or the axes defining the coordinate system of an image.

The location of each axis is specified by two vectors: the axis itself, given by a unit vector in the direction of the axis, and an offset to the base of the unit vector.

The vectors defining an axis are referenced to an appropriate coordinate system. The axis vector, itself, is a dimensionless unit vector. Where meaningful, the offset vector is given in millimetres. In coordinate systems not measured in metres, the offset is not specified and is taken as zero.

The available coordinate systems are:

The imgCIF standard laboratory coordinate system
The direct lattice (fractional atomic coordinates)
The orthogonal Cartesian coordinate system (real space)
The reciprocal lattice
An abstract orthogonal Cartesian coordinate frame

DIFFRN_GROUP Categories that describe details of the diffraction experiment.
DIFFRN_DATA_FRAME Data items in the DIFFRN_DATA_FRAME category record the details about each frame of data.

The items in this category were previously in a DIFFRN_FRAME_DATA category, which is now deprecated. The items from the old category are provided as aliases but should not be used for new work.

DIFFRN_DETECTOR Data items in the DIFFRN_DETECTOR category describe the detector used to measure the scattered radiation, including any analyser and post-sample collimation.
  DIFFRN_DETECTOR_AXIS Data items in the DIFFRN_DETECTOR_AXIS category associate axes with detectors.
  DIFFRN_DETECTOR_ELEMENT Data items in the DIFFRN_DETECTOR_ELEMENT category record the details about spatial layout and other characteristics of each element of a detector which may have multiple elements.

In most cases, giving more detailed information in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS is preferable to simply providing the centre of the detector element.

DIFFRN_MEASUREMENT Data items in the DIFFRN_MEASUREMENT category record details about the device used to orient and/or position the crystal during data measurement and the manner in which the diffraction data were measured.
  DIFFRN_MEASUREMENT_AXIS Data items in the DIFFRN_MEASUREMENT_AXIS category associate axes with goniometers.
DIFFRN_RADIATION Data items in the DIFFRN_RADIATION category describe the radiation used for measuring diffraction intensities, its collimation and monochromatization before the sample.

Post-sample treatment of the beam is described by data items in the DIFFRN_DETECTOR category.

DIFFRN_REFLN This category redefinition has been added to extend the key of the standard DIFFRN_REFLN category.

Data items in the DIFFRN_REFLN category record details about the intensities in the diffraction data set identified by _diffrn_refln.diffrn_id.

The DIFFRN_REFLN data items refer to individual intensity measurements and must be included in looped lists.

The DIFFRN_REFLNS data items specify the parameters that apply to all intensity measurements in the particular diffraction data set identified by _diffrn_reflns.diffrn_id and _diffrn_refln.frame_id

DIFFRN_SCAN Data items in the DIFFRN_SCAN category describe the parameters of one or more scans, relating axis positions to frames.
  DIFFRN_SCAN_AXIS Data items in the DIFFRN_SCAN_AXIS category describe the settings of axes for particular scans. Unspecified axes are assumed to be at their zero points.
  DIFFRN_SCAN_FRAME Data items in the DIFFRN_SCAN_FRAME category describe the relationships of particular frames to scans.
 
  DIFFRN_SCAN_FRAME_AXIS Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the settings of axes for particular frames. Unspecified axes are assumed to be at their zero points. If, for any given frame, nonzero values apply for any of the data items in this category, those values should be given explicitly in this category and not simply inferred from values in DIFFRN_SCAN_AXIS.
 
  DIFFRN_SCAN_FRAME_MONITOR Data items in the DIFFRN_SCAN_FRAME_MONITOR category record the values and details about each monitor for each frame of data during a scan.

Each monitor value is uniquely identified by the combination of the scan_id given by _diffrn_scan_frame.scan_id the frame_id given by _diffrn_scan_frame_monitor.frame_id, the monitor's detector_id given by _diffrn_scan_frame_monitor.monitor_id, and a 1-based ordinal given by _diffrn_scan_frame_monitor.id.

If there is only one frame for the scan, the value of _diffrn_scan_frame_monitor.frame_id may be omitted.

A single frame may have more than one monitor value, and each monitor value may be the result of integration over the entire frame integration time given by the value of _diffrn_scan_frame.integration_time or many monitor values may be reported over shorter times given by the value of _diffrn_scan_frame_monitor.integration_time. If only one monitor value for a given monitor is collected during the integration time of the frame, the value of _diffrn_scan_frame_monitor.id may be omitted.

MAP_GROUP Categories that describe maps.
MAP Data items in the MAP category record the details of a maps. Maps record values of parameters, such as density, that are functions of position within a cell or are functions of orthogonal coordinates in three space.

A map may is composed of one or more map segments specified in the MAP_SEGMENT category.

Examples are given in the MAP_SEGMENT category.

  MAP_SEGMENT Data items in the MAP_SEGMENT category record the details about each segment (section or brick) of a map.
VARIANT_GROUP Categories that describe variants
VARIANT Data items in the VARIANT category record the details about sets of variants of data items.

There is sometimes a need to allow for multiple versions of the same data items in order to allow for refinements and corrections to earlier assumptions, observations and calculations. In order to allow data sets to contain more than one variant of the same information, an optional ...variant data item as a pointer to _variant.variant has been added to the key of every category, as an implicit data item with a null (empty) default value.

All rows in a category with the same variant value are considered to be related to one another and to all rows in other categories with the same variant value. For a given variant, all such rows are also considered to be related to all rows with a null variant value, except that a row with a null variant value is for which all other components of its key are identical to those entries in another row with a non-null variant value is not related the the rows with that non-null variant value. This behavior is similar to the convention for identifying alternate conformers in an atom list.

An optional role may be specified for a variant as the value of _variant.role. Possible roles are null, "preferred", "raw data", "unsuccessful trial".

Variants may carry an optional timestamp as the value of _variant.timestamp.

Variants may be related to other variants from which they were derived by the value of _variant.variant_of

Further details about the variant may be specified as the value of _variant.details.

In order to allow variant information from multiple datasets to be combined, _variant.diffrn_id and/or _variant.entry_id may be used.

; _dictionary.title cif_img.dic _dictionary.version 1.6.4 _dictionary.datablock_id cif_img.dic ######################### ## CATEGORY_GROUP_LIST ## ######################### loop_ _category_group_list.id _category_group_list.parent_id _category_group_list.description 'inclusive_group' . ; Categories that belong to the dictionary extension. ; 'array_data_group' 'inclusive_group' ; Categories that describe array data. ; 'axis_group' 'inclusive_group' ; Categories that describe axes. ; 'diffrn_group' 'inclusive_group' ; Categories that describe details of the diffraction experiment. ; 'map_group' 'inclusive_group' ; Categories that describe details of map data. ; 'variant_group' 'inclusive_group' ; Categories that describe details of map data. ; ################## ## SUB_CATEGORY ## ################## loop_ _sub_category.id _sub_category.description 'matrix' ; The collection of elements of a matrix. ; 'vector' ; The collection of elements of a vector. ; ############## # ARRAY_DATA # ############## save_ARRAY_DATA _category.description ; Data items in the ARRAY_DATA category are the containers for the array data items described in the category ARRAY_STRUCTURE. It is recognized that the data in this category needs to be used in two distinct ways. During a data collection the lack of ancillary data and timing constraints in processing data may dictate the need to make a 'miniCBF' nothing more than an essential minimum of information to record the results of the data collection. In that case it is proper to use the ARRAY_DATA category as a container for just a single image and a compacted, beam-line dependent list of data collection parameter values. In such a case, only the tags '_array_data.header_convention', '_array_data.header_contents' and '_array_data.data' need be populated. For full processing and archiving, most of the tags in this dictionary will need to be populated. ; _category.id array_data _category.mandatory_code no loop_ _category_key.name '_array_data.array_id' '_array_data.binary_id' '_array_data.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows two binary data blocks. The first one was compressed by the CBF_CANONICAL compression algorithm and is presented as hexadecimal data. The first character 'H' on the data lines means hexadecimal. It could have been 'O' for octal or 'D' for decimal. The second character on the line shows the number of bytes in each word (in this case '4'), which then requires eight hexadecimal digits per word. The third character gives the order of octets within a word, in this case '<' for the ordering 4321 (i.e. 'big-endian'). Alternatively, the character '>' could have been used for the ordering 1234 (i.e. 'little-endian'). The block has a 'message digest' to check the integrity of the data. The second block is similar, but uses CBF_PACKED compression and BASE64 encoding. Note that the size and the digest are different. ; ; loop_ _array_data.array_id _array_data.binary_id _array_data.data image_1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF_CANONICAL" Content-Transfer-Encoding: X-BASE16 X-Binary-Size: 3927126 X-Binary-ID: 1 Content-MD5: u2sTJEovAHkmkDjPi+gWsg== # Hexadecimal encoding, byte 0, byte order ...21 # H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ... .... --CIF-BINARY-FORMAT-SECTION---- ; image_2 2 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF-PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3745758 X-Binary-ID: 2 Content-MD5: 1zsJjWPfol2GYl2V+QSXrw== ELhQAAAAAAAA... ... --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - This example shows a single image in a miniCBF, provided by E. Eikenberry. The entire CBF consists of one data block containing one category and three tags. The CBFlib program convert_miniCBF and a suitable template file can be used to convert this miniCBF to a full imgCIF file. ; ; ###CBF: VERSION 1.5 # CBF file written by CBFlib v0.7.8 data_insulin_pilatus6m _array_data.header_convention SLS_1.0 _array_data.header_contents ; # Detector: PILATUS 6M SN: 60-0001 # 2007/Jun/17 15:12:36.928 # Pixel_size 172e-6 m x 172e-6 m # Silicon sensor, thickness 0.000320 m # Exposure_time 0.995000 s # Exposure_period 1.000000 s # Tau = 194.0e-09 s # Count_cutoff 1048575 counts # Threshold_setting 5000 eV # Wavelength 1.2398 A # Energy_range (0, 0) eV # Detector_distance 0.15500 m # Detector_Voffset -0.01003 m # Beam_xy (1231.00, 1277.00) pixels # Flux 22487563295 ph/s # Filter_transmission 0.0008 # Start_angle 13.0000 deg. # Angle_increment 1.0000 deg. # Detector_2theta 0.0000 deg. # Polarization 0.990 # Alpha 0.0000 deg. # Kappa 0.0000 deg. # Phi 0.0000 deg. # Chi 0.0000 deg. # Oscillation_axis X, CW # N_oscillations 1 ; _array_data.data ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_BYTE_OFFSET" Content-Transfer-Encoding: BINARY X-Binary-Size: 6247567 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" X-Binary-Element-Byte-Order: LITTLE_ENDIAN Content-MD5: 8wO6i2+899lf5iO8QPdgrw== X-Binary-Number-of-Elements: 6224001 X-Binary-Size-Fastest-Dimension: 2463 X-Binary-Size-Second-Dimension: 2527 X-Binary-Size-Padding: 4095 ... --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_data.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. If not given, it defaults to 1. ; _item.name '_array_data.array_id' _item.category_id array_data _item.mandatory_code implicit _item_default.value 1 _item_type.code code save_ save__array_data.binary_id _item_description.description ; This item is an integer identifier which, along with _array_data.array_id, should uniquely identify the particular block of array data. If _array_data.binary_id is not explicitly given, it defaults to 1. The value of _array_data.binary_id distinguishes among multiple sets of data with the same array structure. If the MIME header of the data array specifies a value for X-Binary-ID, the value of _array_data.binary_id should be equal to the value given for X-Binary-ID. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_data.binary_id' array_data implicit '_diffrn_data_frame.binary_id' diffrn_data_frame implicit '_array_intensities.binary_id' array_intensities implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.binary_id' '_array_data.binary_id' '_array_intensities.binary_id' '_array_data.binary_id' _item_default.value 1 _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_data.data _item_description.description ; The value of _array_data.data contains the array data encapsulated in a STAR string. The representation used is a variant on the Multipurpose Internet Mail Extensions (MIME) specified in RFC 2045-2049 by N. Freed et al. The boundary delimiter used in writing an imgCIF or CBF is '\n--CIF-BINARY-FORMAT-SECTION--' (including the required initial '\n--'). The Content-Type may be any of the discrete types permitted in RFC 2045; 'application/octet-stream' is recommended for diffraction images in the ARRAY_DATA category. Note: When appropriate in other categories, e.g. for photographs of crystals, more precise types, such as 'image/jpeg', 'image/tiff', 'image/png', etc. should be used. If an octet stream was compressed, the compression should be specified by the parameter 'conversions="X-CBF_PACKED"' or the parameter 'conversions="X-CBF_CANONICAL"' or the parameter 'conversions="X-CBF_BYTE_OFFSET"' or the parameter 'conversions="X-CBF_BACKGROUND_OFFSET_DELTA"' If the parameter 'conversions="X-CBF_PACKED"' is given it may be further modified with the parameters '"uncorrelated_sections"' or '"flat"' If the '"uncorrelated_sections"' parameter is given, each section will be compressed without using the prior section for averaging. If the '"flat"' parameter is given, each the image will be treated as one long row. Note that the X-CBF_CANONICAL and X-CBF_PACKED are slower but more efficient compressions that the others. The X-CBF_BYTE_OFFSET compression is a good compromise between speed and efficiency for ordinary diffraction images. The X-CBF_BACKGROUND_OFFSET_DELTA compression is oriented towards sparse data, such as masks and tables of replacement pixel values for images with overloaded spots. The Content-Transfer-Encoding may be 'BASE64', 'Quoted-Printable', 'X-BASE8', 'X-BASE10', 'X-BASE16' or 'X-BASE32K', for an imgCIF or 'BINARY' for a CBF. The octal, decimal and hexadecimal transfer encodings are provided for convenience in debugging and are not recommended for archiving and data interchange. In a CIF, one of the parameters 'charset=us-ascii', 'charset=utf-8' or 'charset=utf-16' may be used on the Content-Transfer-Encoding to specify the character set used for the external presentation of the encoded data. If no charset parameter is given, the character set of the enclosing CIF is assumed. In any case, if a BOM flag is detected (FE FF for big-endian UTF-16, FF FE for little-endian UTF-16 or EF BB BF for UTF-8) is detected, the indicated charset will be assumed until the end of the encoded data or the detection of a different BOM. The charset of the Content-Transfer-Encoding is not the character set of the encoded data, only the character set of the presentation of the encoded data and should be respecified for each distinct STAR string. In an imgCIF file, the encoded binary data begins after the empty line terminating the header. In an imgCIF file, the encoded binary data ends with the terminating boundary delimiter '\n--CIF-BINARY-FORMAT-SECTION----' in the currently effective charset or with the '\n; ' that terminates the STAR string. In a CBF, the raw binary data begins after an empty line terminating the header and after the sequence: Octet Hex Decimal Purpose 0 0C 12 (ctrl-L) Page break 1 1A 26 (ctrl-Z) Stop listings in MS-DOS 2 04 04 (Ctrl-D) Stop listings in UNIX 3 D5 213 Binary section begins None of these octets are included in the calculation of the message size or in the calculation of the message digest. The X-Binary-Size header specifies the size of the equivalent binary data in octets. If compression was used, this size is the size after compression, including any book-keeping fields. An adjustment is made for the deprecated binary formats in which eight bytes of binary header are used for the compression type. In this case, the eight bytes used for the compression type are subtracted from the size, so that the same size will be reported if the compression type is supplied in the MIME header. Use of the MIME header is the recommended way to supply the compression type. In general, no portion of the binary header is included in the calculation of the size. The X-Binary-Element-Type header specifies the type of binary data in the octets, using the same descriptive phrases as in _array_structure.encoding_type. The default value is 'unsigned 32-bit integer'. An MD5 message digest may, optionally, be used. The 'RSA Data Security, Inc. MD5 Message-Digest Algorithm' should be used. No portion of the header is included in the calculation of the message digest. If the Transfer Encoding is 'X-BASE8', 'X-BASE10' or 'X-BASE16', the data are presented as octal, decimal or hexadecimal data organized into lines or words. Each word is created by composing octets of data in fixed groups of 2, 3, 4, 6 or 8 octets, either in the order ...4321 ('big- endian') or 1234... ('little-endian'). If there are fewer than the specified number of octets to fill the last word, then the missing octets are presented as '==' for each missing octet. Exactly two equal signs are used for each missing octet even for octal and decimal encoding. The format of lines is: rnd xxxxxx xxxxxx xxxxxx where r is 'H', 'O' or 'D' for hexadecimal, octal or decimal, n is the number of octets per word and d is '<' or '>' for the '...4321' and '1234...' octet orderings, respectively. The '==' padding for the last word should be on the appropriate side to correspond to the missing octets, e.g. H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000 or H3> FF0700 00==== For these hexadecimal, octal and decimal formats only, comments beginning with '#' are permitted to improve readability. BASE64 encoding follows MIME conventions. Octets are in groups of three: c1, c2, c3. The resulting 24 bits are broken into four six-bit quantities, starting with the high-order six bits (c1 >> 2) of the first octet, then the low-order two bits of the first octet followed by the high-order four bits of the second octet [(c1 & 3)<<4 | (c2>>4)], then the bottom four bits of the second octet followed by the high-order two bits of the last octet [(c2 & 15)<<2 | (c3>>6)], then the bottom six bits of the last octet (c3 & 63). Each of these four quantities is translated into an ASCII character using the mapping: 1 2 3 4 5 6 0123456789012345678901234567890123456789012345678901234567890123 | | | | | | | ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/ With short groups of octets padded on the right with one '=' if c3 is missing, and with '==' if both c2 and c3 are missing. X-BASE32K encoding is similar to BASE64 encoding, except that sets of 15 octets are encoded as sets of 8 16-bit unicode characters, by breaking the 120 bits into 8 15-bit quantities. 256 is added to each 15 bit quantity to bring it into a printable uncode range. When encoding, zero padding is used to fill out the last 15 bit quantity. If 8 or more bits of padding are used, a single equals sign (hexadecimal 003D) is appended. Embedded whitespace and newlines are introduced to produce lines of no more than 80 characters each. On decoding, all printable ascii characters and ascii whitespace characters are ignored except for any trailing equals signs. The number of trailing equals signs indicated the number of trailing octets to be trimmed from the end of the decoded data. (see Georgi Darakev, Vassil Litchev, Kostadin Z. Mitev, Herbert J. Bernstein, 'Efficient Support of Binary Data in the XML Implementation of the NeXus File Format',absract W0165, ACA Summer Meeting, Honolulu, HI, July 2006). QUOTED-PRINTABLE encoding also follows MIME conventions, copying octets without translation if their ASCII values are 32...38, 42, 48...57, 59, 60, 62, 64...126 and the octet is not a ';' in column 1. All other characters are translated to =nn, where nn is the hexadecimal encoding of the octet. All lines are 'wrapped' with a terminating '=' (i.e. the MIME conventions for an implicit line terminator are never used). The "X-Binary-Element-Byte-Order" can specify either '"BIG_ENDIAN"' or '"LITTLE_ENDIAN"' byte order of the imaage data. Only LITTLE_ENDIAN is recommended. Processors may treat BIG_ENDIAN as a warning of data that can only be processed by special software. The "X-Binary-Number-of-Elements" specifies the number of elements (not the number of octets) in the decompressed, decoded image. The optional "X-Binary-Size-Fastest-Dimension" specifies the number of elements (not the number of octets) in one row of the fastest changing dimension of the binary data array. This information must be in the MIME header for proper operation of some of the decompression algorithms. The optional "X-Binary-Size-Second-Dimension" specifies the number of elements (not the number of octets) in one column of the second-fastest changing dimension of the binary data array. This information must be in the MIME header for proper operation of some of the decompression algorithms. The optional "X-Binary-Size-Third-Dimension" specifies the number of sections for the third-fastest changing dimension of the binary data array. The optional "X-Binary-Size-Padding" specifies the size in octets of an optional padding after the binary array data and before the closing flags for a binary section. ; _item.name '_array_data.data' _item.category_id array_data _item.mandatory_code yes _item_type.code binary save_ save__array_data.header_contents _item_description.description ; This item is an text field for use in minimal CBF files to carry essential header information to be kept with image data in _array_data.data when the tags that normally carry the structured metadata for the image have not been populated. Normally this data item should not appear when the full set of tags have been populated and _diffrn_data_frame.details appears. ; _item.name '_array_data.header_contents' _item.category_id array_data _item.mandatory_code no _item_type.code text save_ save__array_data.header_convention _item_description.description ; This item is an identifier for the convention followed in constructing the contents of _array_data.header_contents The permitted values are of the of an image creator identifier followed by an underscore and a version string. To avoid confusion about conventions, all creator identifiers should be registered with the IUCr and the conventions for all identifiers and versions should be posted on the MEDSBIO.org web site. ; _item.name '_array_data.header_convention' _item.category_id array_data _item.mandatory_code no _item_type.code code save_ save__array_data.variant _item_description.description ; The value of _array_data.variant gives the variant to which the given array_data row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_array_data.variant' _item.category_id array_data _item.mandatory_code no _item_type.code code save_ ###################### # ARRAY_ELEMENT_SIZE # ###################### save_ARRAY_ELEMENT_SIZE _category.description ; Data items in the ARRAY_ELEMENT_SIZE category record the physical size of array elements along each array dimension. ; _category.id array_element_size _category.mandatory_code no loop_ _category_key.name '_array_element_size.array_id' '_array_element_size.index' '_array_element_size.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A regular 2D array with a uniform element dimension of 1220 nanometres. ; ; loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size image_1 1 1.22e-6 image_1 2 1.22e-6 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_element_size.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_element_size.array_id' _item.category_id array_element_size _item.mandatory_code implicit _item_type.code code save_ save__array_element_size.index _item_description.description ; This item is a pointer to _array_structure_list.index in the ARRAY_STRUCTURE_LIST category. ; _item.name '_array_element_size.index' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.size _item_description.description ; The size in metres of an image element in this dimension. This supposes that the elements are arranged on a regular grid. ; _item.name '_array_element_size.size' _item.category_id array_element_size _item.mandatory_code yes _item_type.code float _item_units.code 'metres' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__array_element_size.variant _item_description.description ; The value of _array_element_size.variant gives the variant to which the given array_element_size row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_array_element_size.variant' _item.category_id array_element_size _item.mandatory_code no _item_type.code code save_ ##################### # ARRAY_INTENSITIES # ##################### save_ARRAY_INTENSITIES _category.description ; Data items in the ARRAY_INTENSITIES category record the information required to recover the intensity data from the set of data values stored in the ARRAY_DATA category. The detector may have a complex relationship between the raw intensity values and the number of incident photons. In most cases, the number stored in the final array will have a simple linear relationship to the actual number of incident photons, given by _array_intensities.gain. If raw, uncorrected values are presented (e.g. for calibration experiments), the value of _array_intensities.linearity will be 'raw' and _array_intensities.gain will not be used. ; _category.id array_intensities _category.mandatory_code no loop_ _category_key.name '_array_intensities.array_id' '_array_intensities.binary_id' '_array_intensities.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 ; ; loop_ _array_intensities.array_id _array_intensities.linearity _array_intensities.gain _array_intensities.overload _array_intensities.undefined_value _array_intensities.pixel_fast_bin_size _array_intensities.pixel_slow_bin_size _array_intensities.pixel_binning_method image_1 linear 1.2 655535 0 2 2 hardware ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_intensities.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_intensities.array_id' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code code save_ save__array_intensities.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_array_intensities.binary_id' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code int save_ save__array_intensities.gain _item_description.description ; Detector 'gain'. The factor by which linearized intensity count values should be divided to produce true photon counts. ; _item.name '_array_intensities.gain' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain_esd' 'associated_value' save_ save__array_intensities.gain_esd _item_description.description ; The estimated standard deviation in detector 'gain'. ; _item.name '_array_intensities.gain_esd' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain' 'associated_esd' save_ save__array_intensities.linearity _item_description.description ; The intensity linearity scaling method used to convert from the raw intensity to the stored element value: 'linear' is linear. 'offset' means that the value defined by _array_intensities.offset should be added to each element value. 'scaling' means that the value defined by _array_intensities.scaling should be multiplied with each element value. 'scaling_offset' is the combination of the two previous cases, with the scale factor applied before the offset value. 'sqrt_scaled' means that the square root of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and squaring the result. 'logarithmic_scaled' means that the logarithm base 10 of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and calculating 10 to the power of this number. 'raw' means that the data are a set of raw values straight from the detector. ; _item.name '_array_intensities.linearity' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'linear' . 'offset' ; The value defined by _array_intensities.offset should be added to each element value. ; 'scaling' ; The value defined by _array_intensities.scaling should be multiplied with each element value. ; 'scaling_offset' ; The combination of the scaling and offset with the scale factor applied before the offset value. ; 'sqrt_scaled' ; The square root of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and squaring the result. ; 'logarithmic_scaled' ; The logarithm base 10 of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and calculating 10 to the power of this number. ; 'raw' ; The array consists of raw values to which no corrections have been applied. While the handling of the data is similar to that given for 'linear' data with no offset, the meaning of the data differs in that the number of incident photons is not necessarily linearly related to the number of counts reported. This value is intended for use either in calibration experiments or to allow for handling more complex data-fitting algorithms than are allowed for by this data item. ; save_ save__array_intensities.offset _item_description.description ; Offset value to add to array element values in the manner described by the item _array_intensities.linearity. ; _item.name '_array_intensities.offset' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.overload _item_description.description ; The saturation intensity level for this data array. ; _item.name '_array_intensities.overload' _item.category_id array_intensities _item.mandatory_code no _item_type.code float _item_units.code 'counts' save_ save__array_intensities.pixel_fast_bin_size _item_description.description ; The value of _array_intensities.pixel_fast_bin_size specifies the number of pixels that compose one element in the direction of the most rapidly varying array dimension. Typical values are 1, 2, 4 or 8. When there is 1 pixel per array element in both directions, the value given for _array_intensities.pixel_binning_method normally should be 'none'. It is specified as a float to allow for binning algorithms that create array elements that are not integer multiples of the detector pixel size. ; _item.name '_array_intensities.pixel_fast_bin_size' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code float _item_default.value 1. loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'pixels_per_element' save_ save__array_intensities.pixel_slow_bin_size _item_description.description ; The value of _array_intensities.pixel_slow_bin_size specifies the number of pixels that compose one element in the direction of the second most rapidly varying array dimension. Typical values are 1, 2, 4 or 8. When there is 1 pixel per array element in both directions, the value given for _array_intensities.pixel_binning_method normally should be 'none'. It is specified as a float to allow for binning algorithms that create array elements that are not integer multiples of the detector pixel size. ; _item.name '_array_intensities.pixel_slow_bin_size' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code float _item_default.value 1. loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'pixels_per_element' save_ save__array_intensities.pixel_binning_method _item_description.description ; The value of _array_intensities.pixel_binning_method specifies the method used to derive array elements from multiple pixels. ; _item.name '_array_intensities.pixel_binning_method' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'hardware' ; The element intensities were derived from the raw data of one or more pixels by used of hardware in the detector, e.g. by use of shift registers in a CCD to combine pixels into super-pixels. ; 'software' ; The element intensities were derived from the raw data of more than one pixel by use of software. ; 'combined' ; The element intensities were derived from the raw data of more than one pixel by use of both hardware and software, as when hardware binning is used in one direction and software in the other. ; 'none' ; In the both directions, the data has not been binned. The number of pixels is equal to the number of elements. When the value of _array_intensities.pixel_binning_method is 'none' the values of _array_intensities.pixel_fast_bin_size and _array_intensities.pixel_slow_bin_size both must be 1. ; 'unspecified' ; The method used to derive element intensities is not specified. ; _item_default.value 'unspecified' save_ save__array_intensities.scaling _item_description.description ; Multiplicative scaling value to be applied to array data in the manner described by item _array_intensities.linearity. ; _item.name '_array_intensities.scaling' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.undefined_value _item_description.description ; A value to be substituted for undefined values in the data array. ; _item.name '_array_intensities.undefined_value' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.variant _item_description.description ; The value of _array_intensities.variant gives the variant to which the given array_intensities row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_array_intensities.variant' _item.category_id array_intensities _item.mandatory_code no _item_type.code code save_ ################### # ARRAY_STRUCTURE # ################### save_ARRAY_STRUCTURE _category.description ; Data items in the ARRAY_STRUCTURE category record the organization and encoding of array data that may be stored in the ARRAY_DATA category. ; _category.id array_structure _category.mandatory_code no loop_ _category_key.name '_array_structure.id' '_array_structure.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order image_1 "unsigned 16-bit integer" none little_endian ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure.byte_order _item_description.description ; The order of bytes for integer values which require more than 1 byte. (IBM-PC's and compatibles and DEC VAXs use low-byte-first ordered integers, whereas Hewlett Packard 700 series, Sun-4 and Silicon Graphics use high-byte-first ordered integers. DEC Alphas can produce/use either depending on a compiler switch.) ; _item.name '_array_structure.byte_order' _item.category_id array_structure _item.mandatory_code yes _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail 'big_endian' ; The first byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; 'little_endian' ; The last byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; save_ save__array_structure.compression_type _item_description.description ; Type of data-compression method used to compress the array data. ; _item.name '_array_structure.compression_type' _item.category_id array_structure _item.mandatory_code no _item_type.code ucode _item_default.value 'none' loop_ _item_enumeration.value _item_enumeration.detail 'byte_offset' ; Using the 'byte_offset' compression scheme as per A. Hammersley and the CBFlib manual, section 3.3.3 ; 'canonical' ; Using the 'canonical' compression scheme (International Tables for Crystallography Volume G, Section 5.6.3.1) and CBFlib manual section 3.3.1 ; 'none' ; Data are stored in normal format as defined by _array_structure.encoding_type and _array_structure.byte_order. ; 'packed' ; Using the 'packed' compression scheme, a CCP4-style packing as per J. P. Abrahams pack_c.c and CBFlib manual, section 3.3.2. ; 'packed_v2' ; Using the 'packed' compression scheme, version 2, as per J. P. Abrahams pack_c.c and CBFlib manual, section 3.3.2. ; save_ save__array_structure.compression_type_flag _item_description.description ; Flags modifying the type of data-compression method used to compress the arraydata. ; _item.name '_array_structure.compression_type_flag' _item.category_id array_structure _item.mandatory_code no _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail 'uncorrelated_sections' ; When applying packed or packed_v2 compression on an array with uncorrelated sections, do not average in points from the prior section. ; 'flat' ; When applying packed or packed_v2 compression on an array with treat the entire image as a single line set the maximum number of bits for an offset to 65 bits. The flag is included for compatibility with software prior to CBFlib_0.7.7, and should not be used for new data sets. ; save_ save__array_structure.encoding_type _item_description.description ; Data encoding of a single element of array data. The type 'unsigned 1-bit integer' is used for packed Booleans arrays for masks. Each element of the array corresponds to a single bit packed in unsigned 8-bit data. In several cases, the IEEE format is referenced. See IEEE Standard 754-1985 (IEEE, 1985). Ref: IEEE (1985). IEEE Standard for Binary Floating-Point Arithmetic. ANSI/IEEE Std 754-1985. New York: Institute of Electrical and Electronics Engineers. ; _item.name '_array_structure.encoding_type' _item.category_id array_structure _item.mandatory_code yes _item_type.code uline loop_ _item_enumeration.value 'unsigned 1-bit integer' 'unsigned 8-bit integer' 'signed 8-bit integer' 'unsigned 16-bit integer' 'signed 16-bit integer' 'unsigned 32-bit integer' 'signed 32-bit integer' 'signed 32-bit real IEEE' 'signed 64-bit real IEEE' 'signed 32-bit complex IEEE' save_ save__array_structure.id _item_description.description ; The value of _array_structure.id must uniquely identify each item of array data. This item has been made implicit and given a default value of 1 as a convenience in writing miniCBF files. Normally an explicit name with useful content should be used. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure.id' array_structure implicit '_array_data.array_id' array_data implicit '_array_structure_list.array_id' array_structure_list implicit '_array_intensities.array_id' array_intensities implicit '_diffrn_data_frame.array_id' diffrn_data_frame implicit _item_default.value 1 _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_data.array_id' '_array_structure.id' '_array_structure_list.array_id' '_array_structure.id' '_array_intensities.array_id' '_array_structure.id' '_diffrn_data_frame.array_id' '_array_structure.id' save_ save__array_structure.variant _item_description.description ; The value of _array_structure.variant gives the variant to which the given array_structure row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_array_structure.variant' _item.category_id array_structure _item.mandatory_code no _item_type.code code save_ ######################## # ARRAY_STRUCTURE_LIST # ######################## save_ARRAY_STRUCTURE_LIST _category.description ; Data items in the ARRAY_STRUCTURE_LIST category record the size and organization of each array dimension. The relationship to physical axes may be given. ; _category.id array_structure_list _category.mandatory_code no loop_ _category_key.name '_array_structure_list.array_id' '_array_structure_list.index' '_array_structure_list.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - An image array of 1300 x 1200 elements. The raster order of the image is left to right (increasing) in the first dimension and bottom to top (decreasing) in the second dimension. ; ; loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id image_1 1 1300 1 increasing ELEMENT_X image_1 2 1200 2 decreasing ELEMENY_Y ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure_list.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_structure_list.array_id' _item.category_id array_structure_list _item.mandatory_code implicit _item_type.code code save_ save__array_structure_list.axis_set_id _item_description.description ; This is a descriptor for the physical axis or set of axes corresponding to an array index. This data item is related to the axes of the detector itself given in DIFFRN_DETECTOR_AXIS, but usually differs in that the axes in this category are the axes of the coordinate system of reported data points, while the axes in DIFFRN_DETECTOR_AXIS are the physical axes of the detector describing the 'poise' of the detector as an overall physical object. If there is only one axis in the set, the identifier of that axis should be used as the identifier of the set. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.axis_set_id' array_structure_list yes '_array_structure_list_axis.axis_set_id' array_structure_list_axis implicit _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_structure_list_axis.axis_set_id' '_array_structure_list.axis_set_id' save_ save__array_structure_list.dimension _item_description.description ; The number of elements stored in the array structure in this dimension. ; _item.name '_array_structure_list.dimension' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.direction _item_description.description ; Identifies the direction in which this array index changes. ; _item.name '_array_structure_list.direction' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'increasing' ; Indicates the index changes from 1 to the maximum dimension. ; 'decreasing' ; Indicates the index changes from the maximum dimension to 1. ; save_ save__array_structure_list.index _item_description.description ; Identifies the one-based index of the row or column in the array structure. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.index' array_structure_list yes '_array_structure_list.precedence' array_structure_list yes '_array_element_size.index' array_element_size yes _item_type.code int loop_ _item_linked.child_name _item_linked.parent_name '_array_element_size.index' '_array_structure_list.index' loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.precedence _item_description.description ; Identifies the rank order in which this array index changes with respect to other array indices. The precedence of 1 indicates the index which changes fastest. ; _item.name '_array_structure_list.precedence' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.variant _item_description.description ; The value of _array_structure_list.variant gives the variant to which the given array_structure_list row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_array_structure_list.variant' _item.category_id array_structure_list _item.mandatory_code no _item_type.code code save_ ############################# # ARRAY_STRUCTURE_LIST_AXIS # ############################# save_ARRAY_STRUCTURE_LIST_AXIS _category.description ; Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe the physical settings of sets of axes for the centres of pixels that correspond to data points described in the ARRAY_STRUCTURE_LIST category. In the simplest cases, the physical increments of a single axis correspond to the increments of a single array index. More complex organizations, e.g. spiral scans, may require coupled motions along multiple axes. Note that a spiral scan uses two coupled axes: one for the angular direction and one for the radial direction. This differs from a cylindrical scan for which the two axes are not coupled into one set. ; _category.id array_structure_list_axis _category.mandatory_code no loop_ _category_key.name '_array_structure_list_axis.axis_set_id' '_array_structure_list_axis.axis_id' '_array_structure_list_axis.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' save_ save__array_structure_list_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes in the set of axes for which settings are being specified. Multiple axes may be specified for the same value of _array_structure_list_axis.axis_set_id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_array_structure_list_axis.axis_id' _item.category_id array_structure_list_axis _item.mandatory_code yes _item_type.code code save_ save__array_structure_list_axis.axis_set_id _item_description.description ; The value of this data item is the identifier of the set of axes for which axis settings are being specified. Multiple axes may be specified for the same value of _array_structure_list_axis.axis_set_id. This item is a pointer to _array_structure_list.axis_set_id in the ARRAY_STRUCTURE_LIST category. If this item is not specified, it defaults to the corresponding axis identifier. ; _item.name '_array_structure_list_axis.axis_set_id' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_type.code code save_ save__array_structure_list_axis.angle _item_description.description ; The setting of the specified axis in degrees for the first data point of the array index with the corresponding value of _array_structure_list.axis_set_id. If the index is specified as 'increasing', this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing', this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.angle' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.angle_increment _item_description.description ; The pixel-centre-to-pixel-centre increment in the angular setting of the specified axis in degrees. This is not meaningful in the case of 'constant velocity' spiral scans and should not be specified for this case. See _array_structure_list_axis.angular_pitch. ; _item.name '_array_structure_list_axis.angle_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for the first data point of the array index with the corresponding value of _array_structure_list.axis_set_id. If the index is specified as 'increasing', this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing', this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.displacement' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.fract_displacement _item_description.description ; The setting of the specified axis as a decimal fraction of the axis unit vector for the first data point of the array index with the corresponding value of _array_structure_list.axis_set_id. If the index is specified as 'increasing', this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing', this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.fract_displacement' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float save_ save__array_structure_list_axis.displacement_increment _item_description.description ; The pixel-centre-to-pixel-centre increment for the displacement setting of the specified axis in millimetres. ; _item.name '_array_structure_list_axis.displacement_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.fract_displacement_increment _item_description.description ; The pixel-centre-to-pixel-centre increment for the displacement setting of the specified axis as a decimal fraction of the axis unit vector. ; _item.name '_array_structure_list_axis.fract_displacement_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.angular_pitch _item_description.description ; The pixel-centre-to-pixel-centre distance for a one-step change in the setting of the specified axis in millimetres. This is meaningful only for 'constant velocity' spiral scans or for uncoupled angular scans at a constant radius (cylindrical scans) and should not be specified for cases in which the angle between pixels (rather than the distance between pixels) is uniform. See _array_structure_list_axis.angle_increment. ; _item.name '_array_structure_list_axis.angular_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.radial_pitch _item_description.description ; The radial distance from one 'cylinder' of pixels to the next in millimetres. If the scan is a 'constant velocity' scan with differing angular displacements between pixels, the value of this item may differ significantly from the value of _array_structure_list_axis.displacement_increment. ; _item.name '_array_structure_list_axis.radial_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.reference_angle _item_description.description ; The value of _array_structure_list_axis.reference_angle specifies the setting of the angle of this axis used for determining a reference beam center and a reference detector distance. It is normally expected to be identical to the value of _array_structure_list.angle. ; _item.name '_array_structure_list_axis.reference_angle' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.reference_displacement _item_description.description ; The value of _array_structure_list_axis.reference_displacement specifies the setting of the displacement of this axis used for determining a reference beam center and a reference detector distance. It is normally expected to be identical to the value of _array_structure_list.displacement. ; _item.name '_array_structure_list_axis.reference_displacement' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.variant _item_description.description ; The value of _array_structure_list_axis.variant gives the variant to which the given array_structure_list_axis row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_array_structure_list_axis.variant' _item.category_id array_structure_list_axis _item.mandatory_code no _item_type.code code save_ ######## # AXIS # ######## save_AXIS _category.description ; Data items in the AXIS category record the information required to describe the various goniometer, detector, source and other axes needed to specify a data collection or the axes defining the coordinate system of an image. The location of each axis is specified by two vectors: the axis itself, given by a unit vector in the direction of the axis, and an offset to the base of the unit vector. The vectors defining an axis are referenced to an appropriate coordinate system. The axis vector, itself, is a dimensionless unit vector. Where meaningful, the offset vector is given in millimetres. In coordinate systems not measured in metres, the offset is not specified and is taken as zero. The available coordinate systems are: The imgCIF standard laboratory coordinate system The direct lattice (fractional atomic coordinates) The orthogonal Cartesian coordinate system (real space) The reciprocal lattice An abstract orthogonal Cartesian coordinate frame For consistency in this discussion, we call the three coordinate system axes X, Y and Z. This is appropriate for the imgCIF standard laboratory coordinate system, and last two Cartesian coordinate systems, but for the direct lattice, X corresponds to a, Y to b and Z to c, while for the reciprocal lattice, X corresponds to a*, Y to b* and Z to c*. For purposes of visualization, all the coordinate systems are taken as right-handed, i.e., using the convention that the extended thumb of a right hand could point along the first (X) axis, the straightened pointer finger could point along the second (Y) axis and the middle finger folded inward could point along the third (Z) axis. THE IMGCIF STANDARD LABORATORY COORDINATE SYSTEM The imgCIF standard laboratory coordinate system is a right-handed orthogonal coordinate similar to the MOSFLM coordinate system, but imgCIF puts Z along the X-ray beam, rather than putting X along the X-ray beam as in MOSFLM. The vectors for the imgCIF standard laboratory coordinate system form a right-handed Cartesian coordinate system with its origin in the sample or specimen. The origin of the axis system should, if possible, be defined in terms of mechanically stable axes to be be both in the sample and in the beam. If the sample goniometer or other sample positioner has two axes the intersection of which defines a unique point at which the sample should be mounted to be bathed by the beam, that will be the origin of the axis system. If no such point is defined, then the midpoint of the line of intersection between the sample and the center of the beam will define the origin. For this definition the sample positioning system will be set at its initial reference position for the experiment. | Y (to complete right-handed system) | | | | | |________________X / principal goniometer axis / / / / /Z (to source) Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from the sample or specimen along the principal axis of the goniometer or sample positioning system if the sample positioning system has an axis that intersects the origin and which form an angle of more than 22.5 degrees with the beam axis. Axis 2 (Y): The Y-axis completes an orthogonal right-handed system defined by the X-axis and the Z-axis (see below). Axis 3 (Z): The Z-axis is derived from the source axis which goes from the sample to the source. The Z-axis is the component of the source axis in the direction of the source orthogonal to the X-axis in the plane defined by the X-axis and the source axis. If the conditions for the X-axis can be met, the coordinate system will be based on the goniometer or other sample positioning system and the beam and not on the orientation of the detector, gravity etc. The vectors necessary to specify all other axes are given by sets of three components in the order (X, Y, Z). If the axis involved is a rotation axis, it is right-handed, i.e. as one views the object to be rotated from the origin (the tail) of the unit vector, the rotation is clockwise. If a translation axis is specified, the direction of the unit vector specifies the sense of positive translation. Note: This choice of coordinate system is similar to but significantly different from the choice in MOSFLM (Leslie & Powell, 2004). In MOSFLM, X is along the X-ray beam (the CBF/imgCIF Z axis) and Z is along the rotation axis. In some experimental techniques, there is no goniometer or the principal axis of the goniometer is at a small acute angle with respect to the source axis. In such cases, other reference axes are needed to define a useful coordinate system. The order of priority in defining directions in such cases is to use the detector, then gravity, then north. If the X-axis cannot be defined as above, then the direction (not the origin) of the X-axis should be parallel to the axis of the primary detector element corresponding to the most rapidly varying dimension of that detector element's data array, with its positive sense corresponding to increasing values of the index for that dimension. If the detector is such that such a direction cannot be defined (as with a point detector) or that direction forms an angle of less than 22.5 degrees with respect to the source axis, then the X-axis should be chosen so that if the Y-axis is chosen in the direction of gravity, and the Z-axis is chosen to be along the source axis, a right-handed orthogonal coordinate system is chosen. In the case of a vertical source axis, as a last resort, the X-axis should be chosen to point North. All rotations are given in degrees and all translations are given in mm. Axes may be dependent on one another. The X-axis is the only goniometer axis the direction of which is strictly connected to the hardware. All other axes are specified by the positions they would assume when the axes upon which they depend are at their zero points. When specifying detector axes, the axis is given to the beam centre. The location of the beam centre on the detector should be given in the DIFFRN_DETECTOR category in distortion-corrected millimetres from the (0,0) corner of the detector. It should be noted that many different origins arise in the definition of an experiment. In particular, as noted above, it is necessary to specify the location of the beam centre on the detector in terms of the origin of the detector, which is, of course, not coincident with the centre of the sample. The unit cell, reciprocal cell and crystallographic orthogonal Cartesian coordinate system are defined by the CELL and the matrices in the ATOM_SITES category. THE DIRECT LATTICE (FRACTIONAL COORDINATES) The direct lattice coordinate system is a system of fractional coordinates aligned to the crystal, rather than to the laboratory. This is a natural coordinate system for maps and atomic coordinates. It is the simplest coordinate system in which to apply symmetry. The axes are determined by the cell edges, and are not necessarily othogonal. This coordinate system is not uniquely defined and depends on the cell parameters in the CELL category and the settings chosen to index the crystal. Molecules in a crystal studied by X-ray diffracraction are organized into a repeating regular array of unit cells. Each unit cell is defined by three vectors, a, b and c. To quote from Drenth, "The choice of the unit cell is not unique and therefore, guidelines have been established for selecting the standard basis vectors and the origin. They are based on symmetry and metric considerations: "(1) The axial system should be right handed. (2) The basis vectors should coincide as much as possible with directions of highest symmetry." (3) The cell taken should be the smallest one that satisfies condition (2) (4) Of all the lattice vectors, none is shorter than a. (5) Of those not directed along a, none is shorter than b. (6) Of those not lying in the ab plane, none is shorter than c. (7) The three angles between the basis vectors a, b and c are either all acute (<90\%) or all obtuse (≥90\%)." These rules do not produce a unique result that is stable under the assumption of experimental errors, and the the resulting cell may not be primitive. In this coordinate system, the vector (.5, .5, .5) is in the middle of the given unit cell. Grid coordinates are an important variation on fractional coordinates used when working with maps. In imgCIF, the conversion from fractional to grid coordinates is implicit in the array indexing specified by _array_structure_list.dimension. Note that this implicit grid-coordinate scheme is 1-based, not zero-based, i.e. the origin of the cell for axes along the cell edges with no specified _array_structure_list_axis.displacement will have grid coordinates of (1,1,1), i.e. array indices of (1,1,1). THE ORTHOGONAL CARTESIAN COORDINATE SYSTEM (REAL SPACE) The orthogonal Cartesian coordinate system is a transformation of the direct lattice to the actual physical coordinates of atoms in space. It is similar to the laboratory coordinate system, but is anchored to and moves with the crystal, rather than being schored to the laboratory. The transformation from fractional to orthogonal cartesian coordinates is given by the _atom_sites.Cartn_transf_matrix[i][j] and _atom_sites.Cartn_transf_vector[i] tags. A common choice for the matrix of the transformation is given in the 1992 PDB format document | a b cos(\g) c cos(\b) | | 0 b sin(\g) c (cos(\a) - cos(\b)cos(\g))/sin(\g) | | 0 0 V/(a b sin(\g)) | This is a convenient coordinate system in which to do fitting of models to maps and in which to understand the chemistry of a molecule. THE RECIPROCAL LATTICE The reciprocal lattice coordinate system is used for diffraction intensitities. It is based on the reciprocal cell, the dual of the cell, in which reciprocal cell edges are derived from direct cell faces: a* = bc sin(\a)/V b* = ac sin(\b)/V c* = ab sin(\g)/V cos(\a*) = (cos(\b) cos(\g) - cos(\a))/(sin(\b) sin(\g)) cos(\b*) = (cos(\a) cos(\g) - cos(\b))/(sin(\a) sin(\g)) cos(\g*) = (cos(\a) cos(\b) - cos(\g))/(sin(\a) sin(\b)) V = abc SQRT(1 - cos(\a)^2^ - cos(\b)^2^ - cos(\g)^2^ + 2 cos(\a) cos(\b) cos(\g) ) In this form the dimensions of the reciprocal lattice are in reciprocal \%Angstroms (\%A^-1^). A dimensionless form can be obtained by multiplying by the wavelength. Reflections are commonly indexed against this coordinate system as (h, k, l) triples. References: Drenth, J., "Introduction to basic crystallography." chapter 2.1 in Rossmann, M. G. and Arnold, E. "Crystallography of biological macromolecules", Volume F of the IUCr's "International tables for crystallography", Kluwer, Dordrecht 2001, pp 44 -- 63 Leslie, A. G. W. and Powell, H. (2004). MOSFLM v6.11. MRC Laboratory of Molecular Biology, Hills Road, Cambridge, England. http://www.CCP4.ac.uk/dist/X-windows/Mosflm/. Stout, G. H. and Jensen, L. H., "X-ray structure determination", 2nd ed., Wiley, New York, 1989, 453 pp. __, "PROTEIN DATA BANK ATOMIC COORDINATE AND BIBLIOGRAPHIC ENTRY FORMAT DESCRIPTION," Brookhaven National Laboratory, February 1992. ; _category.id axis _category.mandatory_code no loop_ _category_key.name '_axis.id' '_axis.equipment' '_axis.variant' loop_ _category_group.id 'inclusive_group' 'axis_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows the axis specification of the axes of a kappa- geometry goniometer [see Stout, G. H. & Jensen, L. H. (1989). X-ray structure determination. A practical guide, 2nd ed. p. 134. New York: Wiley Interscience]. There are three axes specified, and no offsets. The outermost axis, omega, is pointed along the X axis. The next innermost axis, kappa, is at a 50 degree angle to the X axis, pointed away from the source. The innermost axis, phi, aligns with the X axis when omega and phi are at their zero points. If T-omega, T-kappa and T-phi are the transformation matrices derived from the axis settings, the complete transformation would be: X' = (T-omega) (T-kappa) (T-phi) X ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] omega rotation goniometer . 1 0 0 kappa rotation goniometer omega -.64279 0 -.76604 phi rotation goniometer kappa 1 0 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - This example shows the axis specification of the axes of a detector, source and gravity. The order has been changed as a reminder that the ordering of presentation of tokens is not significant. The centre of rotation of the detector has been taken to be 68 millimetres in the direction away from the source. ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] source . source . 0 0 1 . . . gravity . gravity . 0 -1 0 . . . tranz translation detector rotz 0 0 1 0 0 -68 twotheta rotation detector . 1 0 0 . . . roty rotation detector twotheta 0 1 0 0 0 -68 rotz rotation detector roty 0 0 1 0 0 -68 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 3 - This example show the axis specification of the axes for a map, using fractional coordinates. Each cell edge has been divided into a grid of 50 divisions in the ARRAY_STRUCTURE_LIST_AXIS category. The map is using only the first octant of the grid in the ARRAY_STRUCTURE_LIST category. The fastest changing axis is the gris along A, then along B, and the slowest is along C. The map sampling is being done in the middle of each grid division ; ; loop_ _axis.id _axis.system _axis.vector[1] _axis.vector[2] _axis.vector[3] CELL_A_AXIS fractional 1 0 0 CELL_B_AXIS fractional 0 1 0 CELL_C_AXIS fractional 0 0 1 loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_id MAP 1 25 1 increasing CELL_A_AXIS MAP 1 25 2 increasing CELL_B_AXIS MAP 1 25 3 increasing CELL_C_AXIS loop_ _array_structure_list_axis.axis_id _array_structure_list_axis.fract_displacement _array_structure_list_axis.fract_displacement_increment CELL_A_AXIS 0.01 0.02 CELL_B_AXIS 0.01 0.02 CELL_C_AXIS 0.01 0.02 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 4 - This example show the axis specification of the axes for a map, this time as orthogonal \%Angstroms, using the same coordinate system as for the atomic coordinates. The map is sampling every 1.5 \%Angstroms (1.5e-7 millimeters) in a map segment 37.5 \%Angstroms on a side. ; ; loop_ _axis.id _axis.system _axis.vector[1] _axis.vector[2] _axis.vector[3] X orthogonal 1 0 0 Y orthogonal 0 1 0 Z orthogonal 0 0 1 loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_id MAP 1 25 1 increasing X MAP 2 25 2 increasing Y MAP 3 25 3 increasing Z loop_ _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment X 7.5e-8 1.5e-7 Y 7.5e-8 1.5e-7 Z 7.5e-8 1.5e-7 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__axis.depends_on _item_description.description ; The value of _axis.depends_on specifies the next outermost axis upon which this axis depends. This item is a pointer to _axis.id in the same category. ; _item.name '_axis.depends_on' _item.category_id axis _item.mandatory_code no save_ save__axis.equipment _item_description.description ; The value of _axis.equipment specifies the type of equipment using the axis: 'goniometer', 'detector', 'gravity', 'source' or 'general'. ; _item.name '_axis.equipment' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail goniometer 'equipment used to orient or position samples' detector 'equipment used to detect reflections' general 'equipment used for general purposes' gravity 'axis specifying the downward direction' source 'axis specifying the direction sample to source' save_ save__axis.offset[1] _item_description.description ; The [1] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[2] _item_description.description ; The [2] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[3] _item_description.description ; The [3] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.id _item_description.description ; The value of _axis.id must uniquely identify each axis relevant to the experiment. Note that multiple pieces of equipment may share the same axis (e.g. a twotheta arm), so the category key for AXIS also includes the equipment. ; loop_ _item.name _item.category_id _item.mandatory_code '_axis.id' axis yes '_array_structure_list_axis.axis_id' array_structure_list_axis yes '_diffrn_detector_axis.axis_id' diffrn_detector_axis yes '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes '_diffrn_scan_axis.axis_id' diffrn_scan_axis yes '_diffrn_scan_frame_axis.axis_id' diffrn_scan_frame_axis yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_axis.depends_on' '_axis.id' '_array_structure_list_axis.axis_id' '_axis.id' '_diffrn_detector_axis.axis_id' '_axis.id' '_diffrn_measurement_axis.axis_id' '_axis.id' '_diffrn_scan_axis.axis_id' '_axis.id' '_diffrn_scan_frame_axis.axis_id' '_axis.id' save_ save__axis.system _item_description.description ; The value of _axis.system specifies the coordinate system used to define the axis: 'laboratory', 'direct', 'orthogonal', 'reciprocal' or 'abstract'. ; _item.name '_axis.system' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value laboratory loop_ _item_enumeration.value _item_enumeration.detail laboratory ; the axis is referenced to the imgCIF standard laboratory Cartesian coordinate system ; direct ; the axis is referenced to the direct lattice ; orthogonal ; the axis is referenced to the cell Cartesian orthogonal coordinates ; reciprocal ; the axis is referenced to the reciprocal lattice ; abstract ; the axis is referenced to abstract Cartesian cooridinate system ; save_ save__axis.type _item_description.description ; The value of _axis.type specifies the type of axis: 'rotation' or 'translation' (or 'general' when the type is not relevant, as for gravity). ; _item.name '_axis.type' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail rotation 'right-handed axis of rotation' translation 'translation in the direction of the axis' general 'axis for which the type is not relevant' save_ save__axis.vector[1] _item_description.description ; The [1] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[2] _item_description.description ; The [2] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[3] _item_description.description ; The [3] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.variant _item_description.description ; The value of _axis.variant gives the variant to which the given axis row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_axis.variant' _item.category_id axis _item.mandatory_code no _item_type.code code save_ ##################### # DIFFRN_DATA_FRAME # ##################### save_DIFFRN_DATA_FRAME _category.description ; Data items in the DIFFRN_DATA_FRAME category record the details about each frame of data. The items in this category were previously in a DIFFRN_FRAME_DATA category, which is now deprecated. The items from the old category are provided as aliases but should not be used for new work. ; _category.id diffrn_data_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_data_frame.id' '_diffrn_data_frame.detector_element_id' '_diffrn_data_frame.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A frame containing data from 4 frame elements. Each frame element has a common array configuration 'array_1' described in ARRAY_STRUCTURE and related categories. The data for each detector element are stored in four groups of binary data in the ARRAY_DATA category, linked by the array_id and binary_id. ; ; loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id frame_1 d1_ccd_1 array_1 1 frame_1 d1_ccd_2 array_1 2 frame_1 d1_ccd_3 array_1 3 frame_1 d1_ccd_4 array_1 4 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_data_frame.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_diffrn_data_frame.array_id' _item.category_id diffrn_data_frame _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_frame_data.array_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_diffrn_data_frame.binary_id' _item.category_id diffrn_data_frame _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_frame_data.binary_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code int save_ save__diffrn_data_frame.center_fast _item_description.description ; The value of _diffrn_data_frame.center_fast is the fast index axis beam center position relative to the detector element face in the units specified in the data item '_diffrn_data_frame.center_units' along the fast axis of the detector from the center of the first pixel to the point at which the Z-axis (which should be colinear with the beam) intersects the face of the detector, if in fact is does. At the time of the measurement the current setting of detector positioner given frame are used. It is important to note that for measurements in millimetres, the sense of the axis is used, rather than the sign of the pixel-to-pixel increments. ; _item.name '_diffrn_data_frame.center_fast' _item.category_id diffrn_data_frame _item.mandatory_code no _item_type.code float save_ save__diffrn_data_frame.center_slow _item_description.description ; The value of _diffrn_data_frame.center_slow is the slow index axis beam center position relative to the detector element face in the units specified in the data item '_diffrn_data_frame.center_units' along the slow axis of the detector from the center of the first pixel to the point at which the Z-axis (which should be colinear with the beam) intersects the face of the detector, if in fact is does. At the time of the measurement the current setting of detector positioner given frame are used. It is important to note that the sense of the axis is used, rather than the sign of the pixel-to-pixel increments. ; _item.name '_diffrn_data_frame.center_slow' _item.category_id diffrn_data_frame _item.mandatory_code no _item_type.code float save_ save__diffrn_data_frame.center_units _item_description.description ; The value of _diffrn_data_frame.center_units specifies the units in which the values of '_diffrn_data_frame.center_fast' and '_diffrn_data_frame.center_slow' are presented. The default is 'mm' for millimetres. The alternatives are 'pixels' and 'bins'. In all cases the center distances are measured from the center of the first pixel, i.e. in a 2x2 binning, the measuring origin is offset from the centers of the bins by one half pixel towards the first pixel. If 'bins' is specified, the data in '_array_intensities.pixel_fast_bin_size', '_array_intensities.pixel_slow_bin_size', and '_array_intensities.pixel_binning_method' is used to define the binning scheme. ; _item.name '_diffrn_data_frame.center_units' _item.category_id diffrn_data_frame _item.mandatory_code no _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail mm 'millimetres' pixels 'detector pixels' bins 'detector bins' save_ save__diffrn_data_frame.detector_element_id _item_description.description ; This item is a pointer to _diffrn_detector_element.id in the DIFFRN_DETECTOR_ELEMENT category. ; _item.name '_diffrn_data_frame.detector_element_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.detector_element_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.id _item_description.description ; The value of _diffrn_data_frame.id must uniquely identify each complete frame of data. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_data_frame.id' diffrn_data_frame yes '_diffrn_refln.frame_id' diffrn_refln yes '_diffrn_scan.frame_id_start' diffrn_scan yes '_diffrn_scan.frame_id_end' diffrn_scan yes '_diffrn_scan_frame.frame_id' diffrn_scan_frame yes '_diffrn_scan_frame_axis.frame_id' diffrn_scan_frame_axis yes '_diffrn_scan_frame_monitor.frame_id' diffrn_scan_frame_monitor implicit _item_aliases.alias_name '_diffrn_frame_data.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_refln.frame_id' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_start' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_end' '_diffrn_data_frame.id' '_diffrn_scan_frame.frame_id' '_diffrn_data_frame.id' '_diffrn_scan_frame_axis.frame_id' '_diffrn_data_frame.id' '_diffrn_scan_frame_monitor.frame_id' '_diffrn_data_frame.id' save_ save__diffrn_data_frame.details _item_description.description ; The value of _diffrn_data_frame.details should give a description of special aspects of each frame of data. This is an appropriate location in which to record information from vendor headers as presented in those headers, but it should never be used as a substitute for providing the fully parsed information within the appropriate imgCIF/CBF categories. Normally, when a conversion from a miniCBF has been done the data from '_array_data.header_convention' should be transferred to this data item and '_array_data.header_convention' should be removed. ; _item.name '_diffrn_data_frame.details' _item.category_id diffrn_data_frame _item.mandatory_code no _item_aliases.alias_name '_diffrn_frame_data.details' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.4 _item_type.code text loop_ _item_examples.case _item_examples.detail ; HEADER_BYTES = 512; DIM = 2; BYTE_ORDER = big_endian; TYPE = unsigned_short; SIZE1 = 3072; SIZE2 = 3072; PIXEL_SIZE = 0.102588; BIN = 2x2; DETECTOR_SN = 901; TIME = 29.945155; DISTANCE = 200.000000; PHI = 85.000000; OSC_START = 85.000000; OSC_RANGE = 1.000000; WAVELENGTH = 0.979381; BEAM_CENTER_X = 157.500000; BEAM_CENTER_Y = 157.500000; PIXEL SIZE = 0.102588; OSCILLATION RANGE = 1; EXPOSURE TIME = 29.9452; TWO THETA = 0; BEAM CENTRE = 157.5 157.5; ; ; Example of header information extracted from an ADSC Quantum 315 detector header by CBFlib_0.7.6. Image provided by Chris Nielsen of ADSC from a data collection at SSRL beamline 1-5. ; save_ save__diffrn_data_frame.variant _item_description.description ; The value of _diffrn_data_frame.variant gives the variant to which the given diffrn_data_frame row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_data_frame.variant' _item.category_id diffrn_data_frame _item.mandatory_code no _item_type.code code save_ ########################################################################## # The following is a restatement of the mmCIF DIFFRN_DETECTOR, # # DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for # # the CBF/imgCIF extensions # ########################################################################## ################### # DIFFRN_DETECTOR # ################### save_DIFFRN_DETECTOR _category.description ; Data items in the DIFFRN_DETECTOR category describe the detector used to measure the scattered radiation, including any analyser and post-sample collimation. ; _category.id diffrn_detector _category.mandatory_code no loop_ _category_key.name '_diffrn_detector.diffrn_id' '_diffrn_detector.id' '_diffrn_detector.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _diffrn_detector.diffrn_id 'd1' _diffrn_detector.detector 'multiwire' _diffrn_detector.type 'Siemens' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector.details _item_description.description ; A description of special aspects of the radiation detector. ; _item.name '_diffrn_detector.details' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'slow mode' save_ save__diffrn_detector.detector _item_description.description ; The general class of the radiation detector. ; _item.name '_diffrn_detector.detector' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector' cifdic.c91 1.0 '_diffrn_detector' cif_core.dic 2.0 _item_type.code text loop_ _item_examples.case 'photographic film' 'scintillation counter' 'CCD plate' 'BF~3~ counter' save_ save__diffrn_detector.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. The value of _diffrn.id uniquely defines a set of diffraction data. ; _item.name '_diffrn_detector.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector.dtime _item_description.description ; The deadtime in microseconds of the detector(s) used to measure the diffraction intensities. ; _item.name '_diffrn_detector.dtime' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector_dtime' cifdic.c91 1.0 '_diffrn_detector_dtime' cif_core.dic 2.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code microseconds save_ save__diffrn_detector.id _item_description.description ; The value of _diffrn_detector.id must uniquely identify each detector used to collect each diffraction data set. If the value of _diffrn_detector.id is not given, it is implicitly equal to the value of _diffrn_detector.diffrn_id. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector.id' diffrn_detector implicit '_diffrn_detector_axis.detector_id' diffrn_detector_axis yes '_diffrn_scan_frame_monitor.detector_id' diffrn_scan_frame_monitor yes loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_detector_axis.detector_id' '_diffrn_detector.id' '_diffrn_scan_frame_monitor.detector_id' '_diffrn_detector.id' _item_type.code code save_ save__diffrn_detector.number_of_axes _item_description.description ; The value of _diffrn_detector.number_of_axes gives the number of axes of the positioner for the detector identified by _diffrn_detector.id. The word 'positioner' is a general term used in instrumentation design for devices that are used to change the positions of portions of apparatus by linear translation, rotation or combinations of such motions. Axes which are used to provide a coordinate system for the face of an area detetctor should not be counted for this data item. The description of each axis should be provided by entries in DIFFRN_DETECTOR_AXIS. ; _item.name '_diffrn_detector.number_of_axes' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_detector.type _item_description.description ; The make, model or name of the detector device used. ; _item.name '_diffrn_detector.type' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__diffrn_detector.variant _item_description.description ; The value of _diffrn_detector.variant gives the variant to which the given diffrn_detector row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_detector.variant' _item.category_id diffrn_detector _item.mandatory_code no _item_type.code code save_ ######################## # DIFFRN_DETECTOR_AXIS # ######################## save_DIFFRN_DETECTOR_AXIS _category.description ; Data items in the DIFFRN_DETECTOR_AXIS category associate axes with detectors. ; _category.id diffrn_detector_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_axis.detector_id' '_diffrn_detector_axis.axis_id' '_diffrn_detector_axis.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_detector_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_detector_axis.axis_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_axis.detector_id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. This item was previously named _diffrn_detector_axis.id which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_detector_axis.detector_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_aliases.alias_name '_diffrn_detector_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_detector_axis.variant _item_description.description ; The value of _diffrn_detector_axis.variant gives the variant to which the given diffrn_detector_axis row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_detector_axis.variant' _item.category_id diffrn_detector_axis _item.mandatory_code no _item_type.code code save_ ########################### # DIFFRN_DETECTOR_ELEMENT # ########################### save_DIFFRN_DETECTOR_ELEMENT _category.description ; Data items in the DIFFRN_DETECTOR_ELEMENT category record the details about spatial layout and other characteristics of each element of a detector which may have multiple elements. In most cases, giving more detailed information in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS is preferable to simply providing the centre of the detector element. ; _category.id diffrn_detector_element _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_element.id' '_diffrn_detector_element.detector_id' '_diffrn_detector_element.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Detector d1 is composed of four CCD detector elements, each 200 mm by 200 mm, arranged in a square, in the pattern 1 2 * 3 4 Note that the beam centre is slightly displaced from each of the detector elements, just beyond the lower right corner of 1, the lower left corner of 2, the upper right corner of 3 and the upper left corner of 4. For each element, the detector face coordiate system, is assumed to have the fast axis running from left to right and the slow axis running from top to bottom with the origin at the top left corner. ; ; loop_ _diffrn_detector_element.detector_id _diffrn_detector_element.id _diffrn_detector_element.reference_center_fast _diffrn_detector_element.reference_center_slow _diffrn_detector_element.reference_center_units d1 d1_ccd_1 201.5 201.5 mm d1 d1_ccd_2 -1.8 201.5 mm d1 d1_ccd_3 201.6 -1.4 mm d1 d1_ccd_4 -1.7 -1.5 mm ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector_element.id _item_description.description ; The value of _diffrn_detector_element.id must uniquely identify each element of a detector. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector_element.id' diffrn_detector_element yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.detector_element_id' '_diffrn_detector_element.id' save_ save__diffrn_detector_element.detector_id _item_description.description ; This item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. ; _item.name '_diffrn_detector_element.detector_id' _item.category_id diffrn_detector_element _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_element.reference_center_fast _item_description.description ; The value of _diffrn_detector_element.reference_center_fast is the fast index axis beam center position relative to the detector element face in the units specified in the data item '_diffrn_detector_element.reference_center_units' along the fast axis of the detector from the center of the first pixel to the point at which the Z-axis (which should be colinear with the beam) intersects the face of the detector, if in fact is does. At the time of the measurement all settings of the detector positioner should be at their reference settings. If more than one reference setting has been used the value given whould be representive of the beam center as determined from the ensemble of settings. It is important to note that for measurements in millimetres, the sense of the axis is used, rather than the sign of the pixel-to-pixel increments. ; _item.name '_diffrn_detector_element.reference_center_fast' _item.category_id diffrn_detector_element _item.mandatory_code no _item_type.code float save_ save__diffrn_detector_element.reference_center_slow _item_description.description ; The value of _diffrn_detector_element.reference_center_slow is the slow index axis beam center position relative to the detector element face in the units specified in the data item '_diffrn_detector_element.reference_center_units' along the slow axis of the detector from the center of the first pixel to the point at which the Z-axis (which should be colinear with the beam) intersects the face of the detector, if in fact is does. At the time of the measurement all settings of the detector positioner should be at their reference settings. If more than one reference setting has been used the value givien whould be representive of the beam center as determined from the ensemble of settings. It is important to note that the sense of the axis is used, rather than the sign of the pixel-to-pixel increments. ; _item.name '_diffrn_detector_element.reference_center_slow' _item.category_id diffrn_detector_element _item.mandatory_code no _item_type.code float save_ save__diffrn_detector_element.reference_center_units _item_description.description ; The value of _diffrn_detector_element.reference_center_units specifies the units in which the values of '_diffrn_detector_element.reference_center_fast' and '_diffrn_detector_element.reference_center_slow' are presented. The default is 'mm' for millimetres. The alternatives are 'pixels' and 'bins'. In all cases the center distances are measured from the center of the first pixel, i.e. in a 2x2 binning, the measuring origin is offset from the centers of the bins by one half pixel towards the first pixel. If 'bins' is specified, the data in '_array_intensities.pixel_fast_bin_size', '_array_intensities.pixel_slow_bin_size', and '_array_intensities.pixel_binning_method' is used to define the binning scheme. ; _item.name '_diffrn_detector_element.reference_center_units' _item.category_id diffrn_detector_element _item.mandatory_code no _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail mm 'millimetres' pixels 'detector pixels' bins 'detector bins' save_ save__diffrn_detector_element.variant _item_description.description ; The value of _diffrn_detector_element.variant gives the variant to which the given diffrn_detector_element row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_detector_element.variant' _item.category_id diffrn_detector_element _item.mandatory_code no _item_type.code code save_ ######################## ## DIFFRN_MEASUREMENT ## ######################## save_DIFFRN_MEASUREMENT _category.description ; Data items in the DIFFRN_MEASUREMENT category record details about the device used to orient and/or position the crystal during data measurement and the manner in which the diffraction data were measured. ; _category.id diffrn_measurement _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement.device' '_diffrn_measurement.diffrn_id' '_diffrn_measurement.id' '_diffrn_measurement.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_measurement.diffrn_id 'd1' _diffrn_measurement.device '3-circle camera' _diffrn_measurement.device_type 'Supper model X' _diffrn_measurement.device_details 'none' _diffrn_measurement.method 'omega scan' _diffrn_measurement.details ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _diffrn_measurement.diffrn_id 's1' _diffrn_measurement.device_type 'Philips PW1100/20 diffractometer' _diffrn_measurement.method 'theta/2theta (\q/2\q)' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_measurement.device _item_description.description ; The general class of goniometer or device used to support and orient the specimen. If the value of _diffrn_measurement.device is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id. Either _diffrn_measurement.device or _diffrn_measurement.id may be used to link to other categories. If the experimental setup admits multiple devices, then _diffrn_measurement.id is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.device' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_device' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement.device' _item_aliases.alias_name '_diffrn_measurement_device' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '3-circle camera' '4-circle camera' 'kappa-geometry camera' 'oscillation camera' 'precession camera' save_ save__diffrn_measurement.device_details _item_description.description ; A description of special aspects of the device used to measure the diffraction intensities. ; _item.name '_diffrn_measurement.device_details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; commercial goniometer modified locally to allow for 90\% \t arc ; save_ save__diffrn_measurement.device_type _item_description.description ; The make, model or name of the measurement device (goniometer) used. ; _item.name '_diffrn_measurement.device_type' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Supper model q' 'Huber model r' 'Enraf-Nonius model s' 'home-made' save_ save__diffrn_measurement.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_measurement.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement.details _item_description.description ; A description of special aspects of the intensity measurement. ; _item.name '_diffrn_measurement.details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; save_ save__diffrn_measurement.id _item_description.description ; The value of _diffrn_measurement.id must uniquely identify the set of mechanical characteristics of the device used to orient and/or position the sample used during the collection of each diffraction data set. If the value of _diffrn_measurement.id is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id. Either _diffrn_measurement.device or _diffrn_measurement.id may be used to link to other categories. If the experimental setup admits multiple devices, then _diffrn_measurement.id is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.id' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_id' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement.id' _item_type.code code save_ save__diffrn_measurement.method _item_description.description ; Method used to measure intensities. ; _item.name '_diffrn_measurement.method' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_method' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'profile data from theta/2theta (\q/2\q) scans' save_ save__diffrn_measurement.number_of_axes _item_description.description ; The value of _diffrn_measurement.number_of_axes gives the number of axes of the positioner for the goniometer or other sample orientation or positioning device identified by _diffrn_measurement.id. The description of the axes should be provided by entries in DIFFRN_MEASUREMENT_AXIS. ; _item.name '_diffrn_measurement.number_of_axes' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ # _diffrn_measurement.sample_detector_distance # _diffrn_measurement.sample_detector_voffset save__diffrn_measurement.sample_detector_distance _item_description.description ; The value of _diffrn_measurement.sample_detector_distance gives the unsigned distance in millimetres from the sample to the detector along the beam. ; _item.name '_diffrn_measurement.sample_detector_distance' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 _item_type.code float _item_units.code mm save_ save__diffrn_measurement.sample_detector_voffset _item_description.description ; The value of _diffrn_measurement.sample_detector_voffset gives the signed distance in millimetres in the vertical direction (positive for up) from the center of the beam to the center of the detector. ; _item.name '_diffrn_measurement.sample_detector_voffset' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . . . . _item_type.code float _item_units.code mm save_ save__diffrn_measurement.specimen_support _item_description.description ; The physical device used to support the crystal during data collection. ; _item.name '_diffrn_measurement.specimen_support' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_specimen_support' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'glass capillary' 'quartz capillary' 'fiber' 'metal loop' save_ save__diffrn_measurement.variant _item_description.description ; The value of _diffrn_measurement.variant gives the variant to which the given diffrn_measurement row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_measurement.variant' _item.category_id diffrn_measurement _item.mandatory_code no _item_type.code code save_ ########################### # DIFFRN_MEASUREMENT_AXIS # ########################### save_DIFFRN_MEASUREMENT_AXIS _category.description ; Data items in the DIFFRN_MEASUREMENT_AXIS category associate axes with goniometers. ; _category.id diffrn_measurement_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement_axis.axis_id' '_diffrn_measurement_axis.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_measurement_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_measurement_axis.axis_id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.measurement_device _item_description.description ; This data item is a pointer to _diffrn_measurement.device in the DIFFRN_MEASUREMENT category. ; _item.name '_diffrn_measurement_axis.measurement_device' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit _item_type.code text save_ save__diffrn_measurement_axis.measurement_id _item_description.description ; This data item is a pointer to _diffrn_measurement.id in the DIFFRN_MEASUREMENT category. This item was previously named _diffrn_measurement_axis.id, which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_measurement_axis.measurement_id' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_measurement_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_measurement_axis.variant _item_description.description ; The value of _diffrn_measurement_axis.variant gives the variant to which the given diffrn_measurement_axis row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_measurement_axis.variant' _item.category_id diffrn_measurement_axis _item.mandatory_code no _item_type.code code save_ #################### # DIFFRN_RADIATION # #################### save_DIFFRN_RADIATION _category.description ; Data items in the DIFFRN_RADIATION category describe the radiation used for measuring diffraction intensities, its collimation and monochromatization before the sample. Post-sample treatment of the beam is described by data items in the DIFFRN_DETECTOR category. ; _category.id diffrn_radiation _category.mandatory_code no loop_ _category_key.name '_diffrn_radiation.diffrn_id' '_diffrn_radiation.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_radiation.diffrn_id 'set1' _diffrn_radiation.collimation '0.3 mm double pinhole' _diffrn_radiation.monochromator 'graphite' _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.wavelength_id 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _diffrn_radiation.wavelength_id 1 _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.monochromator 'graphite' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_radiation.collimation _item_description.description ; The collimation or focusing applied to the radiation. ; _item.name '_diffrn_radiation.collimation' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_collimation' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '0.3 mm double-pinhole' '0.5 mm' 'focusing mirrors' save_ save__diffrn_radiation.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_radiation.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_radiation.div_x_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory X axis (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the standard uncertainty (e.s.d.) of the directions of photons in the XZ plane around the mean source beam direction. Note that for some synchrotrons this value is specified in milliradians, in which case a conversion is needed. To convert a value in milliradians to a value in degrees, multiply by 0.180 and divide by \p. ; _item.name '_diffrn_radiation.div_x_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.div_y_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory Y axis (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the standard uncertainty (e.s.d.) of the directions of photons in the YZ plane around the mean source beam direction. Note that for some synchrotrons this value is specified in milliradians, in which case a conversion is needed. To convert a value in milliradians to a value in degrees, multiply by 0.180 and divide by \p. ; _item.name '_diffrn_radiation.div_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.div_x_y_source _item_description.description ; Beam crossfire correlation degrees^2^ between the crossfire laboratory X-axis component and the crossfire laboratory Y-axis component (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the mean of the products of the deviations of the direction of each photon in XZ plane times the deviations of the direction of the same photon in the YZ plane around the mean source beam direction. This will be zero for uncorrelated crossfire. Note that some synchrotrons, this value is specified in milliradians^2^, in which case a conversion would be needed. To go from a value in milliradians^2^ to a value in degrees^2^, multiply by 0.180^2^ and divide by \p^2^. ; _item.name '_diffrn_radiation.div_x_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees_squared _item_default.value 0.0 save_ save__diffrn_radiation.filter_edge _item_description.description ; Absorption edge in \%Angstroms of the radiation filter used. ; _item.name '_diffrn_radiation.filter_edge' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_filter_edge' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__diffrn_radiation.inhomogeneity _item_description.description ; Half-width in millimetres of the incident beam in the direction perpendicular to the diffraction plane. ; _item.name '_diffrn_radiation.inhomogeneity' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_inhomogeneity' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code millimetres save_ save__diffrn_radiation.monochromator _item_description.description ; The method used to obtain monochromatic radiation. If a monochromator crystal is used, the material and the indices of the Bragg reflection are specified. ; _item.name '_diffrn_radiation.monochromator' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_monochromator' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Zr filter' 'Ge 220' 'none' 'equatorial mounted graphite' save_ save__diffrn_radiation.polarisn_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the perpendicular component of the polarization and the diffraction plane. See _diffrn_radiation_polarisn_ratio. ; _item.name '_diffrn_radiation.polarisn_norm' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_norm' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.polarisn_ratio _item_description.description ; Polarization ratio of the diffraction beam incident on the crystal. This is the ratio of the perpendicularly polarized to the parallel polarized component of the radiation. The perpendicular component forms an angle of _diffrn_radiation.polarisn_norm to the normal to the diffraction plane of the sample (i.e. the plane containing the incident and reflected beams). ; _item.name '_diffrn_radiation.polarisn_ratio' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_ratio' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__diffrn_radiation.polarizn_source_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the normal to the polarization plane and the laboratory Y axis as defined in the AXIS category. Note that this is the angle of polarization of the source photons, either directly from a synchrotron beamline or from a monochromater. This differs from the value of _diffrn_radiation.polarisn_norm in that _diffrn_radiation.polarisn_norm refers to polarization relative to the diffraction plane rather than to the laboratory axis system. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane should be taken as the XZ plane and the angle as 0. See _diffrn_radiation.polarizn_source_ratio. ; _item.name '_diffrn_radiation.polarizn_source_norm' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.polarizn_source_ratio _item_description.description ; (Ip-In)/(Ip+In), where Ip is the intensity (amplitude squared) of the electric vector in the plane of polarization and In is the intensity (amplitude squared) of the electric vector in the plane of the normal to the plane of polarization. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane is to be taken as the XZ plane and the normal is parallel to the Y axis. Thus, if there was complete polarization in the plane of polarization, the value of _diffrn_radiation.polarizn_source_ratio would be 1, and for an unpolarized beam _diffrn_radiation.polarizn_source_ratio would have a value of 0. If the X axis has been chosen to lie in the plane of polarization, this definition will agree with the definition of 'MONOCHROMATOR' in the Denzo glossary, and values of near 1 should be expected for a bending-magnet source. However, if the X axis were perpendicular to the polarization plane (not a common choice), then the Denzo value would be the negative of _diffrn_radiation.polarizn_source_ratio. See http://www.hkl-xray.com for information on Denzo and Otwinowski & Minor (1997). This differs both in the choice of ratio and choice of orientation from _diffrn_radiation.polarisn_ratio, which, unlike _diffrn_radiation.polarizn_source_ratio, is unbounded. Reference: Otwinowski, Z. & Minor, W. (1997). 'Processing of X-ray diffraction data collected in oscillation mode.' Methods Enzymol. 276, 307-326. ; _item.name '_diffrn_radiation.polarizn_source_ratio' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 -1.0 -1.0 -1.0 _item_type.code float save_ save__diffrn_radiation.probe _item_description.description ; Name of the type of radiation used. It is strongly recommended that this be given so that the probe radiation is clearly specified. ; _item.name '_diffrn_radiation.probe' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_probe' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value 'X-ray' 'neutron' 'electron' 'gamma' save_ save__diffrn_radiation.type _item_description.description ; The nature of the radiation. This is typically a description of the X-ray wavelength in Siegbahn notation. ; _item.name '_diffrn_radiation.type' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'CuK\a' 'Cu K\a~1~' 'Cu K-L~2,3~' 'white-beam' save_ save__diffrn_radiation.xray_symbol _item_description.description ; The IUPAC symbol for the X-ray wavelength for the probe radiation. ; _item.name '_diffrn_radiation.xray_symbol' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_xray_symbol' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value _item_enumeration.detail 'K-L~3~' 'K\a~1~ in older Siegbahn notation' 'K-L~2~' 'K\a~2~ in older Siegbahn notation' 'K-M~3~' 'K\b~1~ in older Siegbahn notation' 'K-L~2,3~' 'use where K-L~3~ and K-L~2~ are not resolved' save_ save__diffrn_radiation.wavelength_id _item_description.description ; This data item is a pointer to _diffrn_radiation_wavelength.id in the DIFFRN_RADIATION_WAVELENGTH category. ; _item.name '_diffrn_radiation.wavelength_id' _item.category_id diffrn_radiation _item.mandatory_code yes _item_type.code code save_ save__diffrn_radiation.variant _item_description.description ; The value of _diffrn_radiation.variant gives the variant to which the given diffrn_radiation row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_radiation.variant' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code code save_ ################ # DIFFRN_REFLN # ################ save_DIFFRN_REFLN _category.description ; This category redefinition has been added to extend the key of the standard DIFFRN_REFLN category. Data items in the DIFFRN_REFLN category record details about the intensities in the diffraction data set identified by _diffrn_refln.diffrn_id. The DIFFRN_REFLN data items refer to individual intensity measurements and must be included in looped lists. The DIFFRN_REFLNS data items specify the parameters that apply to all intensity measurements in the particular diffraction data set identified by _diffrn_reflns.diffrn_id and _diffrn_refln.frame_id ; _category.id diffrn_refln _category.mandatory_code no loop_ _category_key.name '_diffrn_refln.diffrn_id' '_diffrn_refln.id' '_diffrn_refln.frame_id' '_diffrn_refln.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_refln.frame_id _item_description.description ; This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_refln.frame_id' _item.category_id diffrn_refln _item.mandatory_code yes _item_type.code code save_ save__diffrn_refln.variant _item_description.description ; The value of _diffrn_refln.variant gives the variant to which the given diffrn_refln row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_refln.variant' _item.category_id diffrn_refln _item.mandatory_code no _item_type.code code save_ ############### # DIFFRN_SCAN # ############### save_DIFFRN_SCAN _category.description ; Data items in the DIFFRN_SCAN category describe the parameters of one or more scans, relating axis positions to frames. ; _category.id diffrn_scan _category.mandatory_code no loop_ _category_key.name '_diffrn_scan.id' '_diffrn_scan.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - derived from a suggestion by R. M. Sweet. The vector of each axis is not given here, because it is provided in the AXIS category. By making _diffrn_scan_axis.scan_id and _diffrn_scan_axis.axis_id keys of the DIFFRN_SCAN_AXIS category, an arbitrary number of scanning and fixed axes can be specified for a scan. In this example, three rotation axes and one translation axis at nonzero values are specified, with one axis stepping. There is no reason why more axes could not have been specified to step. Range information has been specified, but note that it can be calculated from the number of frames and the increment, so the data item _diffrn_scan_axis.angle_range could be dropped. Both the sweep data and the data for a single frame are specified. Note that the information on how the axes are stepped is given twice, once in terms of the overall averages in the value of _diffrn_scan.integration_time and the values for DIFFRN_SCAN_AXIS, and precisely for the given frame in the value for _diffrn_scan_frame.integration_time and the values for DIFFRN_SCAN_FRAME_AXIS. If dose-related adjustments are made to scan times and nonlinear stepping is done, these values may differ. Therefore, in interpreting the data for a particular frame it is important to use the frame-specific data. ; ; _diffrn_scan.id 1 _diffrn_scan.date_start '2001-11-18T03:26:42' _diffrn_scan.date_end '2001-11-18T03:36:45' _diffrn_scan.integration_time 3.0 _diffrn_scan.frame_id_start mad_L2_000 _diffrn_scan.frame_id_end mad_L2_200 _diffrn_scan.frames 201 loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment 1 omega 200.0 20.0 0.1 . . . 1 kappa -40.0 0.0 0.0 . . . 1 phi 127.5 0.0 0.0 . . . 1 tranz . . . 2.3 0.0 0.0 _diffrn_scan_frame.scan_id 1 _diffrn_scan_frame.date '2001-11-18T03:27:33' _diffrn_scan_frame.integration_time 3.0 _diffrn_scan_frame.frame_id mad_L2_018 _diffrn_scan_frame.frame_number 18 loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.angle_increment _diffrn_scan_frame_axis.displacement _diffrn_scan_frame_axis.displacement_increment mad_L2_018 omega 201.8 0.1 . . mad_L2_018 kappa -40.0 0.0 . . mad_L2_018 phi 127.5 0.0 . . mad_L2_018 tranz . . 2.3 0.0 ; ; Example 2 - a more extensive example (R. M. Sweet, P. J. Ellis & H. J. Bernstein). A detector is placed 240 mm along the Z axis from the goniometer. This leads to a choice: either the axes of the detector are defined at the origin, and then a Z setting of -240 is entered, or the axes are defined with the necessary Z offset. In this case, the setting is used and the offset is left as zero. This axis is called DETECTOR_Z. The axis for positioning the detector in the Y direction depends on the detector Z axis. This axis is called DETECTOR_Y. The axis for positioning the detector in the X direction depends on the detector Y axis (and therefore on the detector Z axis). This axis is called DETECTOR_X. This detector may be rotated around the Y axis. This rotation axis depends on the three translation axes. It is called DETECTOR_PITCH. A coordinate system is defined on the face of the detector in terms of 2300 0.150 mm pixels in each direction. The ELEMENT_X axis is used to index the first array index of the data array and the ELEMENT_Y axis is used to index the second array index. Because the pixels are 0.150mm X 0.150mm, the centre of the first pixel is at (0.075, 0.075) in this coordinate system. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 172.43 -172.43 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 2300 1 increasing ELEMENT_X ARRAY1 2 2300 2 increasing ELEMENT_Y # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.075 0.150 ELEMENT_Y ELEMENT_Y 0.075 0.150 # category ARRAY_ELEMENT_SIZE loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 ARRAY1 2 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; ; Example 3 - Example 2 revised for a spiral scan (R. M. Sweet, P. J. Ellis & H. J. Bernstein). A detector is placed 240 mm along the Z axis from the goniometer, as in Example 2 above, but in this example the image plate is scanned in a spiral pattern from the outside edge in. The axis for positioning the detector in the Y direction depends on the detector Z axis. This axis is called DETECTOR_Y. The axis for positioning the detector in the X direction depends on the detector Y axis (and therefore on the detector Z axis). This axis is called DETECTOR_X. This detector may be rotated around the Y axis. This rotation axis depends on the three translation axes. It is called DETECTOR_PITCH. A coordinate system is defined on the face of the detector in terms of a coupled rotation axis and radial scan axis to form a spiral scan. The rotation axis is called ELEMENT_ROT and the radial axis is called ELEMENT_RAD. A 150 micrometre radial pitch and a 75 micrometre 'constant velocity' angular pitch are assumed. Indexing is carried out first on the rotation axis and the radial axis is made to be dependent on it. The two axes are coupled to form an axis set ELEMENT_SPIRAL. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_ROT translation detector DETECTOR_PITCH 0 0 1 0 0 0 ELEMENT_RAD translation detector ELEMENT_ROT 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.angle _array_structure_list_axis.displacement _array_structure_list_axis.angular_pitch _array_structure_list_axis.radial_pitch ELEMENT_SPIRAL ELEMENT_ROT 0 . 0.075 . ELEMENT_SPIRAL ELEMENT_RAD . 172.5 . -0.150 # category ARRAY_ELEMENT_SIZE # the actual pixels are 0.075 by 0.150 mm # We give the coarser dimension here. loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_scan.id _item_description.description ; The value of _diffrn_scan.id uniquely identifies each scan. The identifier is used to tie together all the information about the scan. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_scan.id' diffrn_scan yes '_diffrn_scan_axis.scan_id' diffrn_scan_axis yes '_diffrn_scan_frame.scan_id' diffrn_scan_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_scan_axis.scan_id' '_diffrn_scan.id' '_diffrn_scan_frame.scan_id' '_diffrn_scan.id' save_ save__diffrn_scan.date_end _item_description.description ; The date and time of the end of the scan. Note that this may be an estimate generated during the scan, before the precise time of the end of the scan is known. ; _item.name '_diffrn_scan.date_end' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.date_start _item_description.description ; The date and time of the start of the scan. ; _item.name '_diffrn_scan.date_start' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.integration_time _item_description.description ; Approximate average time in seconds to integrate each step of the scan. The precise time for integration of each particular step must be provided in _diffrn_scan_frame.integration_time, even if all steps have the same integration time. ; _item.name '_diffrn_scan.integration_time' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan.frame_id_start _item_description.description ; The value of this data item is the identifier of the first frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_start' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frame_id_end _item_description.description ; The value of this data item is the identifier of the last frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_end' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frames _item_description.description ; The value of this data item is the number of frames in the scan. ; _item.name '_diffrn_scan.frames' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 1 1 1 save_ save__diffrn_scan.time_period _item_description.description ; Approximate average time in seconds between the start of each step of the scan. The precise start-to-start time increment of each particular step may be provided in _diffrn_scan_frame.time_period. ; _item.name '_diffrn_scan.time_period' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan.time_rstrt_incr _item_description.description ; Approximate average time in seconds between the end of integration of each step of the scan than the start of integration of the next step. In general, this will agree with _diffrn_scan_frame.time_rstrt_incr. The sum of the values of _diffrn_scan_frame.integration_time and _diffrn_scan_frame.time_rstrt_incr is the time from the start of integration of one frame and the start of integration for the next frame and should equal the value of _diffrn_scan_frame.time_period for this frame. If the individual frame values vary, then the value of _diffrn_scan.time_rstrt_incr will be representative of the ensemble of values of _diffrn_scan_frame_axis.time_rstrt_incr (e.g. the mean). ; _item.name '_diffrn_scan.time_period' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan.variant _item_description.description ; The value of _diffrn_scan.variant gives the variant to which the given diffrn_scan row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_scan.variant' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code code save_ #################### # DIFFRN_SCAN_AXIS # #################### save_DIFFRN_SCAN_AXIS _category.description ; Data items in the DIFFRN_SCAN_AXIS category describe the settings of axes for particular scans. Unspecified axes are assumed to be at their zero points. ; _category.id diffrn_scan_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_axis.scan_id' '_diffrn_scan_axis.axis_id' '_diffrn_scan_axis.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_axis.scan_id _item_description.description ; The value of this data item is the identifier of the scan for which axis settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan.id. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_axis.scan_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the scan for which settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan.id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_axis.axis_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.angle_start _item_description.description ; The starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_range _item_description.description ; The range from the starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_increment _item_description.description ; The increment for each step for the specified axis in degrees. In general, this will agree with _diffrn_scan_frame_axis.angle_increment. The sum of the values of _diffrn_scan_frame_axis.angle and _diffrn_scan_frame_axis.angle_increment is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of _diffrn_scan_axis.angle_increment will be representative of the ensemble of values of _diffrn_scan_frame_axis.angle_increment (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_rstrt_incr _item_description.description ; The increment after each step for the specified axis in degrees. In general, this will agree with _diffrn_scan_frame_axis.angle_rstrt_incr. The sum of the values of _diffrn_scan_frame_axis.angle, _diffrn_scan_frame_axis.angle_increment and _diffrn_scan_frame_axis.angle_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame and should equal _diffrn_scan_frame_axis.angle for this next frame. If the individual frame values vary, then the value of _diffrn_scan_axis.angle_rstrt_incr will be representative of the ensemble of values of _diffrn_scan_frame_axis.angle_rstrt_incr (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.displacement_start _item_description.description ; The starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_range _item_description.description ; The range from the starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_increment _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with _diffrn_scan_frame_axis.displacement_increment. The sum of the values of _diffrn_scan_frame_axis.displacement and _diffrn_scan_frame_axis.displacement_increment is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of _diffrn_scan_axis.displacement_increment will be representative of the ensemble of values of _diffrn_scan_frame_axis.displacement_increment (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_rstrt_incr _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with _diffrn_scan_frame_axis.displacement_rstrt_incr. The sum of the values of _diffrn_scan_frame_axis.displacement, _diffrn_scan_frame_axis.displacement_increment and _diffrn_scan_frame_axis.displacement_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame and should equal _diffrn_scan_frame_axis.displacement for this next frame. If the individual frame values vary, then the value of _diffrn_scan_axis.displacement_rstrt_incr will be representative of the ensemble of values of _diffrn_scan_frame_axis.displacement_rstrt_incr (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.reference_angle _item_description.description ; The setting of the specified axis in degrees against which measurements of the reference beam center and reference detector distance should be made. In general, this will agree with _diffrn_scan_frame_axis.reference_angle. If the individual frame values vary, then the value of _diffrn_scan_axis.reference_angle will be representative of the ensemble of values of _diffrn_scan_frame_axis.reference_angle (e.g. the mean). If not specified, the value defaults to zero. ; _item.name '_diffrn_scan_axis.reference_angle' _item.category_id diffrn_scan_axis _item.mandatory_code implicit _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.reference_displacement _item_description.description ; The setting of the specified axis in millimetres against which measurements of the reference beam center and reference detector distance should be made. In general, this will agree with _diffrn_scan_frame_axis.reference_displacement. If the individual frame values vary, then the value of _diffrn_scan_axis.reference_displacement will be representative of the ensemble of values of _diffrn_scan_frame_axis.reference_displacement (e.g. the mean). If not specified, the value defaults to to the value of _diffrn_scan_axis.displacement. ; _item.name '_diffrn_scan_axis.reference_displacement' _item.category_id diffrn_scan_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.variant _item_description.description ; The value of _diffrn_scan_axis.variant gives the variant to which the given diffrn_scan_axis row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_scan_axis.variant' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_type.code code save_ ##################### # DIFFRN_SCAN_FRAME # ##################### save_DIFFRN_SCAN_FRAME _category.description ; Data items in the DIFFRN_SCAN_FRAME category describe the relationships of particular frames to scans. ; _category.id diffrn_scan_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame.scan_id' '_diffrn_scan_frame.frame_id' '_diffrn_scan_frame.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame.date _item_description.description ; The date and time of the start of the frame being scanned. ; _item.name '_diffrn_scan_frame.date' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan_frame.frame_id _item_description.description ; The value of this data item is the identifier of the frame being examined. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame.frame_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame.frame_number _item_description.description ; The value of this data item is the number of the frame within the scan, starting with 1. It is not necessarily the same as the value of _diffrn_scan_frame.frame_id, but it may be. ; _item.name '_diffrn_scan_frame.frame_number' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 0 0 0 save_ save__diffrn_scan_frame.integration_time _item_description.description ; The time in seconds to integrate this step of the scan. This should be the precise time of integration of each particular frame. The value of this data item should be given explicitly for each frame and not inferred from the value of _diffrn_scan.integration_time. ; _item.name '_diffrn_scan_frame.integration_time' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame.scan_id _item_description.description ; The value of _diffrn_scan_frame.scan_id identifies the scan containing this frame. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_frame.scan_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame.time_period _item_description.description ; The time in seconds between the start of this frame and the start of the next frame, if any. If there is no next frame, a null value should be given. ; _item.name '_diffrn_scan_frame.time_period' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame.time_rstrt_incr _item_description.description ; The time in seconds between the end of integration of this step of the scan and the start of integration of the next step. The sum of the values of _diffrn_scan_frame.integration_time and _diffrn_scan_frame.time_rstrt_incr is the time from the start of integration of one frame and the start of integration for the next frame and should equal the value of _diffrn_scan_frame.time_period for this frame. The value of _diffrn_scan.time_rstrt_incr will be representative of the ensemble of values of _diffrn_scan_frame_axis.time_rstrt_incr (e.g. the mean). If there is no next frame, a null value should be given. ; _item.name '_diffrn_scan.time_period' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame.variant _item_description.description ; The value of _diffrn_scan_frame.variant gives the variant to which the given diffrn_scan_frame row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_scan_frame.variant' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code code save_ ########################## # DIFFRN_SCAN_FRAME_AXIS # ########################## save_DIFFRN_SCAN_FRAME_AXIS _category.description ; Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the settings of axes for particular frames. Unspecified axes are assumed to be at their zero points. If, for any given frame, nonzero values apply for any of the data items in this category, those values should be given explicitly in this category and not simply inferred from values in DIFFRN_SCAN_AXIS. ; _category.id diffrn_scan_frame_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame_axis.frame_id' '_diffrn_scan_frame_axis.axis_id' '_diffrn_scan_frame_axis.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the frame for which settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_frame_axis.axis_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_axis.angle _item_description.description ; The setting of the specified axis in degrees for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.angle' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_increment _item_description.description ; The increment for this frame for the angular setting of the specified axis in degrees. The sum of the values of _diffrn_scan_frame_axis.angle and _diffrn_scan_frame_axis.angle_increment is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.angle_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_rstrt_incr _item_description.description ; The increment after this frame for the angular setting of the specified axis in degrees. The sum of the values of _diffrn_scan_frame_axis.angle, _diffrn_scan_frame_axis.angle_increment and _diffrn_scan_frame_axis.angle_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame and should equal _diffrn_scan_frame_axis.angle for this next frame. ; _item.name '_diffrn_scan_frame_axis.angle_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.displacement' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_increment _item_description.description ; The increment for this frame for the displacement setting of the specified axis in millimetres. The sum of the values of _diffrn_scan_frame_axis.displacement and _diffrn_scan_frame_axis.displacement_increment is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.displacement_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_rstrt_incr _item_description.description ; The increment for this frame for the displacement setting of the specified axis in millimetres. The sum of the values of _diffrn_scan_frame_axis.displacement, _diffrn_scan_frame_axis.displacement_increment and _diffrn_scan_frame_axis.displacement_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame and should equal _diffrn_scan_frame_axis.displacement for this next frame. ; _item.name '_diffrn_scan_frame_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.frame_id _item_description.description ; The value of this data item is the identifier of the frame for which axis settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame_axis.frame_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_axis.reference_angle _item_description.description ; The setting of the specified axis in degrees against which measurements of the reference beam center and reference detector distance should be made. This is normally the same for all frames, but the option is provided here of making changes when needed. If not provided, it is assumed to be zero. ; _item.name '_diffrn_scan_frame_axis.reference_angle' _item.category_id diffrn_scan_frame_axis _item.mandatory_code implicit _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.reference_displacement _item_description.description ; The setting of the specified axis in millimetres for this frame against which measurements of the reference beam center and reference detector distance should be made. This is normally the same for all frames, but the option is provided here of making changes when needed. If not provided, it is assumed to be equal to _diffrn_scan_frame_axis.displacement. ; _item.name '_diffrn_scan_frame_axis.reference_displacement' _item.category_id diffrn_scan_frame_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.variant _item_description.description ; The value of _diffrn_scan_frame_axis.variant gives the variant to which the given diffrn_scan_frame_axis row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_scan_frame_axis.variant' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_type.code code save_ ############################# # DIFFRN_SCAN_FRAME_MONITOR # ############################# save_DIFFRN_SCAN_FRAME_MONITOR _category.description ; Data items in the DIFFRN_SCAN_FRAME_MONITOR category record the values and details about each monitor for each frame of data during a scan. Each monitor value is uniquely identified by the combination of the scan_id given by _diffrn_scan_frame.scan_id the frame_id given by _diffrn_scan_frame_monitor.frame_id, the monitor's detector_id given by _diffrn_scan_frame_monitor.monitor_id, and a 1-based ordinal given by _diffrn_scan_frame_monitor.id. If there is only one frame for the scan, the value of _diffrn_scan_frame_monitor.frame_id may be omitted. A single frame may have more than one monitor value, and each monitor value may be the result of integration over the entire frame integration time given by the value of _diffrn_scan_frame.integration_time or many monitor values may be reported over shorter times given by the value of _diffrn_scan_frame_monitor.integration_time. If only one monitor value for a given monitor is collected during the integration time of the frame, the value of _diffrn_scan_frame_monitor.id may be omitted. ; _category.id diffrn_data_frame_monitor _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame_monitor.id' '_diffrn_scan_frame_monitor.detector_id' '_diffrn_scan_frame_monitor.scan_id' '_diffrn_data_frame_monitor.frame_id' '_diffrn_data_frame_monitor.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - The beam intensity for frame FRAME1 is being tracked by a beamstop monitor detector BSM01, made from metal foil and a PIN diode, locate 20 mm in front of a MAR345 detector and being sampled every 2 seconds in a 20 second scan. ; ; # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 P6MB BSM01 'metal foil and PIN diode' 1 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH BSM01 MONITOR_Z # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 MONITOR_Z 0.0 0.0 0.0 -220.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_MONITOR loop_ _diffrn_scan_frame_monitor.id _diffrn_scan_frame_monitor.detector_id _diffrn_scan_frame_monitor.scan_id _diffrn_data_frame_monitor.frame_id _diffrn_data_frame_monitor.integration_time _diffrn_data_frame_monitor.monitor_value 1 BSM01 SCAN1 FRAME1 2.0 23838345642 2 BSM01 SCAN1 FRAME1 2.0 23843170669 3 BSM01 SCAN1 FRAME1 2.0 23839478690 4 BSM01 SCAN1 FRAME1 2.0 23856642085 5 BSM01 SCAN1 FRAME1 2.0 23781717656 6 BSM01 SCAN1 FRAME1 2.0 23788850775 7 BSM01 SCAN1 FRAME1 2.0 23815576677 8 BSM01 SCAN1 FRAME1 2.0 23789299964 9 BSM01 SCAN1 FRAME1 2.0 23830195536 10 BSM01 SCAN1 FRAME1 2.0 23673082270 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 FRAME1 MONITOR_Z 0.0 -220.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 172.43 -172.43 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 MONITOR_Z translation detector . 0 0 1 0 0 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_scan_frame_monitor.id _item_description.description ; This item is an integer identifier which, along with _diffrn_scan_frame_monitor.detector_id, _diffrn_scan_frame_monitor.scan_id, and _diffrn_data_frame_monitor.frame_id should uniquely identify the monitor value being recorded If _array_data.binary_id is not explicitly given, it defaults to 1. ; loop_ _item.name '_diffrn_scan_frame_monitor.id' _item.category_id diffrn_scan_frame_monitor _item.mandatory_code implicit _item_default.value 1 _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__diffrn_scan_frame_monitor.detector_id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. ; _item.name '_diffrn_scan_frame_monitor.detector_id' _item.category_id diffrn_scan_frame_monitor _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_monitor.frame_id _item_description.description ; This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame_monitor.frame_id' _item.category_id diffrn_scan_frame_monitor _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_monitor.integration_time _item_description.description ; The precise time for integration of the monitor value given in _diffrn_scan_frame_monitor.value must be given in _diffrn_scan_frame_monitor.integration_time. ; _item.name '_diffrn_scan_frame_monitor.integration_time' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame_monitor.value _item_description.description ; The value reported by the monitor detector should be given in _diffrn_scan_frame_monitor.value. The value is typed as float to allow of monitors for very intense beams that cannot report all digits, but when available, all digits of the monitor should be recorded. ; _item.name '_diffrn_scan_frame_monitor.value' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame_monitor.variant _item_description.description ; The value of _diffrn_scan_frame_monitor.variant gives the variant to which the given diffrn_scan_frame_monitor row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_scan_frame_monitor.variant' _item.category_id diffrn_scan_frame_monitor _item.mandatory_code no _item_type.code code save_ ####### # MAP # ####### save_MAP _category.description ; Data items in the MAP category record the details of a maps. Maps record values of parameters, such as density, that are functions of position within a cell or are functions of orthogonal coordinates in three space. A map may is composed of one or more map segments specified in the MAP_SEGMENT category. Examples are given in the MAP_SEGMENT category. ; _category.id map _category.mandatory_code no loop_ _category_key.name '_map.id' '_map.diffrn_id' '_map.entry_id' '_map.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' 'map_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Identifying an observed density map and a calculated density map ; ; loop_ _map.id _map.details rho_calc ; density calculated from F_calc derived from the ATOM_SITE list ; rho_obs ; density combining the observed structure factors with the calculated phases ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__map.details _item_description.description ; The value of _map.details should give a description of special aspects of each map. ; _item.name '_map.details' _item.category_id map _item.mandatory_code no _item_type.code text loop_ _item_examples.case _item_examples.detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Identifying an observed density map and a calculated density map ; ; loop_ _map.id _map.details rho_calc ; density calculated from F_calc derived from the ATOM_SITE list ; rho_obs ; density combining the observed structure factors with the calculated phases ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__map.diffrn_id _item_description.description ; This item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_map.diffrn_id' _item.category_id map _item.mandatory_code implicit _item_type.code code save_ save__map.entry_id _item_description.description ; This item is a pointer to _entry.id in the ENTRY category. ; _item.name '_map.entry_id' _item.category_id map _item.mandatory_code implicit _item_type.code code save_ save__map.id _item_description.description ; The value of _map.id must uniquely identify each map for the given diffrn.id or entry.id. ; loop_ _item.name _item.category_id _item.mandatory_code '_map.id' map yes '_map_segment.id' map_segment yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_map_segment.id' '_map.id' save_ save__map.variant _item_description.description ; The value of _map.variant gives the variant to which the given map row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_map.variant' _item.category_id map _item.mandatory_code no _item_type.code code save_ ############### # MAP_SEGMENT # ############### save_MAP_SEGMENT _category.description ; Data items in the MAP_SEGMENT category record the details about each segment (section or brick) of a map. ; _category.id map_segment _category.mandatory_code no loop_ _category_key.name '_map_segment.id' '_map_segment.map_id' '_map_segment.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' 'map_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Identifying an observed density map and a calculated density map, each consisting of one segment, both using the same array structure and mask. ; ; loop_ _map.id _map.details rho_calc ; density calculated from F_calc derived from the ATOM_SITE list ; rho_obs ; density combining the observed structure factors with the calculated phases ; loop_ _map_segment.map_id _map_segment.id _map_segment.array_id _map_segment.binary_id _map_segment.mask_array_id _map_segment.mask_binary_id rho_calc rho_calc map_structure 1 mask_structure 1 rho_obs rho_obs map_structure 2 mask_structure 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__map_segment.array_id _item_description.description ; The value of _map_segment.array_id identifies the array structure into which the map is organized. This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_map_segment.array_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code code save_ save__map_segment.binary_id _item_description.description ; The value of _map_segment.binary_id distinguishes the particular set of data organized according to _map_segment.array_id in which the data values of the map are stored. This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_map_segment.binary_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code int save_ save__map_segment.mask_array_id _item_description.description ; The value of _map_segment.mask_array_id, if given, the array structure into which the mask for the map is organized. If no value is given, then all elements of the map are valid. If a value is given, then only elements of the map for which the corresponding element of the mask is non-zero are valid. The value of _map_segment.mask_array_id differs from the value of _map_segment.array_id in order to permit the mask to be given as, say, unsigned 8-bit integers, while the map is given as a data type with more range. However, the two array structures must be aligned, using the same axes in the same order with the same displacements and increments This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_map_segment.mask_array_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code code save_ save__map_segment.mask_binary_id _item_description.description ; The value of _map_segment.mask_binary_id identifies the particular set of data organized according to _map_segment.mask_array_id specifying the mask for the map. This item is a pointer to _array_data.mask_binary_id in the ARRAY_DATA category. ; _item.name '_map_segment.mask_binary_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code int save_ save__map_segment.id _item_description.description ; The value of _map_segment.id must uniquely identify each segment of a map. ; loop_ _item.name _item.category_id _item.mandatory_code '_map_segment.id' map_segment yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_map_data_frame.map_segment_id' '_map_segment.id' save_ save__map_segment.map_id _item_description.description ; This item is a pointer to _map.id in the MAP category. ; _item.name '_map_segment.map_id' _item.category_id map_segment _item.mandatory_code yes _item_type.code code save_ save__map_segment.details _item_description.description ; The value of _map_segment.details should give a description of special aspects of each segment of a map. ; _item.name '_map_segment.details' _item.category_id map_segment _item.mandatory_code no _item_type.code text loop_ _item_examples.case _item_examples.detail ; Example to be provided ; ; ; save_ save__map_segment.variant _item_description.description ; The value of _map_segment.variant gives the variant to which the given map segment is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_map_segment.variant' _item.category_id map_segment _item.mandatory_code no _item_type.code code save_ ########### # VARIANT # ########### save_VARIANT _category.description ; Data items in the VARIANT category record the details about sets of variants of data items. There is sometimes a need to allow for multiple versions of the same data items in order to allow for refinements and corrections to earlier assumptions, observations and calculations. In order to allow data sets to contain more than one variant of the same information, an optional ...variant data item as a pointer to _variant.variant has been added to the key of every category, as an implicit data item with a null (empty) default value. All rows in a category with the same variant value are considered to be related to one another and to all rows in other categories with the same variant value. For a given variant, all such rows are also considered to be related to all rows with a null variant value, except that a row with a null variant value is for which all other components of its key are identical to those entries in another row with a non-null variant value is not related the the rows with that non-null variant value. This behavior is similar to the convention for identifying alternate conformers in an atom list. An optional role may be specified for a variant as the value of _variant.role. Possible roles are null, "preferred", "raw data", "unsuccessful trial". Variants may carry an optional timestamp as the value of _variant.timestamp. Variants may be related to other variants from which they were derived by the value of _variant.variant_of Further details about the variant may be specified as the value of _variant.details. In order to allow variant information from multiple datasets to be combined, _variant.diffrn_id and/or _variant.entry_id may be used. ; _category.id variant _category.mandatory_code no loop_ _category_key.name '_variant.variant' '_variant.diffrn_id' '_variant.entry_id' loop_ _category_group.id 'inclusive_group' 'variant_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Distinguishing between a raw beam center and a refined beam center inferred after indexing. Detector d1 is composed of four CCD detector elements, each 200 mm by 200 mm, arranged in a square, in the pattern 1 2 * 3 4 Note that the beam centre is slightly displaced from each of the detector elements, just beyond the lower right corner of 1, the lower left corner of 2, the upper right corner of 3 and the upper left corner of 4. For each element, the detector face coordiate system, is assumed to have the fast axis running from left to right and the slow axis running from top to bottom with the origin at the top left corner. After indexing and refinement, the center is shifted by .2 mm left and .1 mm down. ; ; loop_ _variant.variant _variant.role _variant.timestamp _variant.variant_of _variant.details . "raw data" 2007-08-03T23:20:00 . . indexed "preferred" 2007-08-04T01:17:28 . "indexed cell and refined beam center" loop_ _diffrn_detector_element.detector_id _diffrn_detector_element.id _diffrn_detector_element.reference_center_fast _diffrn_detector_element.reference_center_slow _diffrn_detector_element.reference_center_units _diffrn_detector_element.variant d1 d1_ccd_1 201.5 201.5 mm . d1 d1_ccd_2 -1.8 201.5 mm . d1 d1_ccd_3 201.6 -1.4 mm . d1 d1_ccd_4 -1.7 -1.5 mm . d1 d1_ccd_1 201.3 201.6 mm indexed d1 d1_ccd_2 -2.0 201.6 mm indexed d1 d1_ccd_3 201.3 -1.5 mm indexed d1 d1_ccd_4 -1.9 -1.6 mm indexed ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__variant.details _item_description.description ; A description of special aspects of the variant. ; _item.name '_variant.details' _item.category_id variant _item.mandatory_code no _item_type.code text _item_examples.case ; indexed cell and refined beam center ; save_ save__variant.role _item_description.description ; The value of _variant.role specified a role for this variant. Possible roles are null, "preferred", "raw data", and "unsuccessful trial". ; _item.name '_variant.role' _item.category_id variant _item.mandatory_code no _item_type.code uline loop_ _item_enumeration.value _item_enumeration.detail . ; A null value for _variant.role leaves the precise role of the variant unspecified. No inference should be made that the variant with the latest time stamp is preferred. ; "preferred" ; A value of "preferred" indicates that rows of any categories specifying this variant should be used in preference to rows with the same key specifying other variants or the null variant. It is an error to specify two variants that appear in the same category with the same key as being preferred, but it is not an error to specify more than one variant as preferred in other cases. ; "raw data" ; A value of "raw data" indicates data prior to any corrections, calculations or refinements. It is not necessarily an error for raw data to also be a variant of an earlier variant. It may be replacement raw data for earlier data believed to be erroneous. ; "unsuccessful trial" ; A value of "unsuccessful trial" indicates data that should not be used for further calculation. ; save_ save__variant.timestamp _item_description.description ; The date and time identifying a variant. This is not necessarily the precise time of the measurement or calculation of the individual related data items, but a timestamp that reflects the order in which the variants were defined. ; _item.name '_variant.timestamp' _item.category_id variant _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__variant.variant _item_description.description ; The value of _variant.variant must uniquely identify each variant for the given diffraction experiment and/or entry This item has been made implicit and given a default value of null. ; loop_ _item.name _item.category_id _item.mandatory_code '_variant.variant' variant implicit '_variant.variant_of' variant implicit '_array_data.variant' array_data implicit '_array_element_size.variant' array_element_size implicit '_array_intensities.variant' array_intensities implicit '_array_structure.variant' array_structure implicit '_array_structure_list.variant' array_structure_list implicit '_array_structure_list_axis.variant' array_structure_list_axis implicit '_axis.variant' axis implicit '_diffrn_data_frame.variant' diffrn_data_frame implicit '_diffrn_detector.variant' diffrn_detector implicit '_diffrn_detector_axis.variant' diffrn_detector_axis implicit '_diffrn_detector_element.variant' diffrn_detector_element implicit '_diffrn_measurement.variant' diffrn_measurement implicit '_diffrn_measurement_axis.variant' diffrn_measurement_axis implicit '_diffrn_radiation.variant' diffrn_radiation implicit '_diffrn_refln.variant' diffrn_refln implicit '_diffrn_scan.variant' diffrn_scan implicit '_diffrn_scan_axis.variant' diffrn_scan_axis implicit '_diffrn_scan_frame.variant' diffrn_scan_frame implicit '_diffrn_scan_frame_axis.variant' diffrn_scan_frame_axis implicit '_diffrn_scan_frame_monitor.variant' diffrn_scan_frame_monitor implicit '_map.variant' map implicit '_map_segment.variant' map_segment implicit _item_default.value . _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_data.variant' '_variant.variant' '_array_data.variant_of' '_variant.variant' '_array_element_size.variant' '_variant.variant' '_array_intensities.variant' '_variant.variant' '_array_structure.variant' '_variant.variant' '_array_structure_list.variant' '_variant.variant' '_array_structure_list_axis.variant' '_variant.variant' '_axis.variant' '_variant.variant' '_diffrn_data_frame.variant' '_variant.variant' '_diffrn_detector.variant' '_variant.variant' '_diffrn_detector_axis.variant' '_variant.variant' '_diffrn_detector_element.variant' '_variant.variant' '_diffrn_measurement.variant' '_variant.variant' '_diffrn_measurement_axis.variant' '_variant.variant' '_diffrn_radiation.variant' '_variant.variant' '_diffrn_refln.variant' '_variant.variant' '_diffrn_scan.variant' '_variant.variant' '_diffrn_scan_axis.variant' '_variant.variant' '_diffrn_scan_frame.variant' '_variant.variant' '_diffrn_scan_frame_axis.variant' '_variant.variant' '_diffrn_scan_frame_monitor.variant' '_variant.variant' '_map.variant' '_variant.variant' '_map_segment.variant' '_variant.variant' save_ save__variant.variant_of _item_description.description ; The value of _variant.variant_of gives the variant from which this variant was derived. If this value is not given, the variant is assumed to be derived from the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_variant.variant_of' _item.category_id variant _item.mandatory_code no _item_type.code code save_ ######################## DEPRECATED DATA ITEMS ######################## save__diffrn_detector_axis.id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_detector_axis.id' _item.category_id diffrn_detector_axis _item.mandatory_code no _item_type.code code save_ save__diffrn_detector_element.center[1] _item_description.description ; The value of _diffrn_detector_element.center[1] is the X component of the distortion-corrected beam centre in millimetres from the (0, 0) (lower-left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. Because of ambiguity about the setting used to determine this center, use of this data item is deprecated. The data item _diffrn_data_frame.center_fast which is referenced to the detector coordinate system and not directly to the laboratory coordinate system should be used instead. ; _item.name '_diffrn_detector_element.center[1]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.center[2] _item_description.description ; The value of _diffrn_detector_element.center[2] is the Y component of the distortion-corrected beam centre in millimetres from the (0, 0) (lower-left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. Because of ambiguity about the setting used to determine this center, use of this data item is deprecated. The data item _diffrn_data_frame.center_slow which is referenced to the detector coordinate system and not directly to the laboratory coordinate system should be used instead. ; _item.name '_diffrn_detector_element.center[2]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_measurement_axis.id _item_description.description ; This data item is a pointer to _diffrn_measurement.id in the DIFFRN_MEASUREMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_measurement_axis.id' _item.category_id diffrn_measurement_axis _item.mandatory_code no _item_type.code code save_ ######################### DEPRECATED CATEGORY ######################### ##################### # DIFFRN_FRAME_DATA # ##################### save_DIFFRN_FRAME_DATA _category.description ; Data items in the DIFFRN_FRAME_DATA category record the details about each frame of data. The items in this category are now in the DIFFRN_DATA_FRAME category. The items in the DIFFRN_FRAME_DATA category are now deprecated. The items from this category are provided as aliases in the 1.0 dictionary or, in the case of _diffrn_frame_data.details, in the 1.4 dictionary. THESE ITEMS SHOULD NOT BE USED FOR NEW WORK. The items from the old category are provided in this dictionary for completeness but should not be used or cited. To avoid confusion, the example has been removed and the redundant parent-child links to other categories have been removed. All _item.mandatory_code values have been changed to no ; _category.id diffrn_frame_data _category.mandatory_code no loop_ _category_key.name '_diffrn_frame_data.id' '_diffrn_frame_data.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; THE DIFFRN_FRAME_DATA category is deprecated and should not be used. ; ; # EXAMPLE REMOVED # ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_frame_data.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.array_id' _item.category_id diffrn_frame_data _item.mandatory_code no _item_type.code code save_ save__diffrn_frame_data.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.binary_id' _item.category_id diffrn_frame_data _item.mandatory_code no _item_type.code int save_ save__diffrn_frame_data.detector_element_id _item_description.description ; This item is a pointer to _diffrn_detector_element.id in the DIFFRN_DETECTOR_ELEMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.detector_element_id' _item.category_id diffrn_frame_data _item.mandatory_code no _item_type.code code save_ save__diffrn_frame_data.id _item_description.description ; The value of _diffrn_frame_data.id must uniquely identify each complete frame of data. DEPRECATED -- DO NOT USE ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_frame_data.id' diffrn_frame_data yes _item_type.code code save_ save__diffrn_frame_data.details _item_description.description ; The value of _diffrn_data_frame.details should give a description of special aspects of each frame of data. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.details' _item.category_id diffrn_frame_data _item.mandatory_code no _item_type.code text save_ ################ END DEPRECATED SECTION ########### #################### ## ITEM_TYPE_LIST ## #################### # # # The regular expressions defined here are not compliant # with the POSIX 1003.2 standard as they include the # '\n' and '\t' special characters. These regular expressions # have been tested using version 0.12 of Richard Stallman's # GNU regular expression library in POSIX mode. # In order to allow presentation of a regular expression # in a text field concatenate any line ending in a backslash # with the following line, after discarding the backslash. # # A formal definition of the '\n' and '\t' special characters # is most properly done in the DDL, but for completeness, please # note that '\n' is the line termination character ('newline') # and '\t' is the horizontal tab character. There is a formal # ambiguity in the use of '\n' for line termination, in that # the intention is that the equivalent machine/OS-dependent line # termination character sequence should be accepted as a match, e.g. # # '\r' (control-M) under MacOS # '\n' (control-J) under Unix # '\r\n' (control-M control-J) under DOS and MS Windows # loop_ _item_type_list.code _item_type_list.primitive_code _item_type_list.construct _item_type_list.detail code char '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words ... ; ucode uchar '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words (case insensitive) ... ; line char '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; char item types / multi-word items ... ; uline uchar '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; char item types / multi-word items (case insensitive)... ; text char '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; text item types / multi-line text ... ; binary char ;\n--CIF-BINARY-FORMAT-SECTION--\n\ [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\ \n--CIF-BINARY-FORMAT-SECTION---- ; ; binary items are presented as MIME-like ascii-encoded sections in an imgCIF. In a CBF, raw octet streams are used to convey the same information. ; int numb '-?[0-9]+' ; int item types are the subset of numbers that are the negative or positive integers. ; float numb '-?(([0-9]+)[.]?|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?' ; float item types are the subset of numbers that are the floating point numbers. ; any char '.*' ; A catch all for items that may take any form... ; yyyy-mm-dd char ;\ [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9]?[0-9]\ ((T[0-2][0-9](:[0-5][0-9](:[0-5][0-9](.[0-9]+)?)?)?)?\ ([+-][0-5][0-9]:[0-5][0-9]))? ; ; Standard format for CIF date and time strings (see http://www.iucr.org/iucr-top/cif/spec/datetime.html), consisting of a yyyy-mm-dd date optionally followed by the character 'T' followed by a 24-hour clock time, optionally followed by a signed time-zone offset. The IUCr standard has been extended to allow for an optional decimal fraction on the seconds of time. Time is local time if no time-zone offset is given. Note that this type extends the mmCIF yyyy-mm-dd type but does not conform to the mmCIF yyyy-mm-dd:hh:mm type that uses a ':' in place if the 'T' specified by the IUCr standard. For reading, both forms should be accepted, but for writing, only the IUCr form should be used. For maximal compatibility, the special time zone indicator 'Z' (for 'zulu') should be accepted on reading in place of '+00:00' for GMT. ; ##################### ## ITEM_UNITS_LIST ## ##################### loop_ _item_units_list.code _item_units_list.detail # 'metres' 'metres' 'centimetres' 'centimetres (metres * 10^( -2)^)' 'millimetres' 'millimetres (metres * 10^( -3)^)' 'nanometres' 'nanometres (metres * 10^( -9)^)' 'angstroms' '\%Angstroms (metres * 10^(-10)^)' 'picometres' 'picometres (metres * 10^(-12)^)' 'femtometres' 'femtometres (metres * 10^(-15)^)' # 'reciprocal_metres' 'reciprocal metres (metres^(-1)^)' 'reciprocal_centimetres' 'reciprocal centimetres ((metres * 10^( -2)^)^(-1)^)' 'reciprocal_millimetres' 'reciprocal millimetres ((metres * 10^( -3)^)^(-1)^)' 'reciprocal_nanometres' 'reciprocal nanometres ((metres * 10^( -9)^)^(-1)^)' 'reciprocal_angstroms' 'reciprocal \%Angstroms ((metres * 10^(-10)^)^(-1)^)' 'reciprocal_picometres' 'reciprocal picometres ((metres * 10^(-12)^)^(-1)^)' # 'nanometres_squared' 'nanometres squared (metres * 10^( -9)^)^2^' 'angstroms_squared' '\%Angstroms squared (metres * 10^(-10)^)^2^' '8pi2_angstroms_squared' '8\p^2^ * \%Angstroms squared (metres * 10^(-10)^)^2^' 'picometres_squared' 'picometres squared (metres * 10^(-12)^)^2^' # 'nanometres_cubed' 'nanometres cubed (metres * 10^( -9)^)^3^' 'angstroms_cubed' '\%Angstroms cubed (metres * 10^(-10)^)^3^' 'picometres_cubed' 'picometres cubed (metres * 10^(-12)^)^3^' # 'kilopascals' 'kilopascals' 'gigapascals' 'gigapascals' # 'hours' 'hours' 'minutes' 'minutes' 'seconds' 'seconds' 'microseconds' 'microseconds' # 'degrees' 'degrees (of arc)' 'degrees_squared' 'degrees (of arc) squared' # 'degrees_per_minute' 'degrees (of arc) per minute' # 'celsius' 'degrees (of temperature) Celsius' 'kelvins' 'degrees (of temperature) Kelvin' # 'counts' 'counts' 'counts_per_photon' 'counts per photon' # 'electrons' 'electrons' # 'electrons_squared' 'electrons squared' # 'electrons_per_nanometres_cubed' ; electrons per nanometres cubed (electrons/(metres * 10^( -9)^)^(-3)^) ; 'electrons_per_angstroms_cubed' ; electrons per \%Angstroms cubed (electrons/(metres * 10^(-10)^)^(-3)^) ; 'electrons_per_picometres_cubed' ; electrons per picometres cubed (electrons/(metres * 10^(-12)^)^(-3)^) ; 'kilowatts' 'kilowatts' 'milliamperes' 'milliamperes' 'kilovolts' 'kilovolts' # 'pixels_per_element' '(image) pixels per (array) element' # 'arbitrary' ; arbitrary system of units. ; # loop_ _item_units_conversion.from_code _item_units_conversion.to_code _item_units_conversion.operator _item_units_conversion.factor ### 'metres' 'centimetres' '*' 1.0E+02 'metres' 'millimetres' '*' 1.0E+03 'metres' 'nanometres' '*' 1.0E+09 'metres' 'angstroms' '*' 1.0E+10 'metres' 'picometres' '*' 1.0E+12 'metres' 'femtometres' '*' 1.0E+15 # 'centimetres' 'metres' '*' 1.0E-02 'centimetres' 'millimetres' '*' 1.0E+01 'centimetres' 'nanometres' '*' 1.0E+07 'centimetres' 'angstroms' '*' 1.0E+08 'centimetres' 'picometres' '*' 1.0E+10 'centimetres' 'femtometres' '*' 1.0E+13 # 'millimetres' 'metres' '*' 1.0E-03 'millimetres' 'centimetres' '*' 1.0E-01 'millimetres' 'nanometres' '*' 1.0E+06 'millimetres' 'angstroms' '*' 1.0E+07 'millimetres' 'picometres' '*' 1.0E+09 'millimetres' 'femtometres' '*' 1.0E+12 # 'nanometres' 'metres' '*' 1.0E-09 'nanometres' 'centimetres' '*' 1.0E-07 'nanometres' 'millimetres' '*' 1.0E-06 'nanometres' 'angstroms' '*' 1.0E+01 'nanometres' 'picometres' '*' 1.0E+03 'nanometres' 'femtometres' '*' 1.0E+06 # 'angstroms' 'metres' '*' 1.0E-10 'angstroms' 'centimetres' '*' 1.0E-08 'angstroms' 'millimetres' '*' 1.0E-07 'angstroms' 'nanometres' '*' 1.0E-01 'angstroms' 'picometres' '*' 1.0E+02 'angstroms' 'femtometres' '*' 1.0E+05 # 'picometres' 'metres' '*' 1.0E-12 'picometres' 'centimetres' '*' 1.0E-10 'picometres' 'millimetres' '*' 1.0E-09 'picometres' 'nanometres' '*' 1.0E-03 'picometres' 'angstroms' '*' 1.0E-02 'picometres' 'femtometres' '*' 1.0E+03 # 'femtometres' 'metres' '*' 1.0E-15 'femtometres' 'centimetres' '*' 1.0E-13 'femtometres' 'millimetres' '*' 1.0E-12 'femtometres' 'nanometres' '*' 1.0E-06 'femtometres' 'angstroms' '*' 1.0E-05 'femtometres' 'picometres' '*' 1.0E-03 ### 'reciprocal_centimetres' 'reciprocal_metres' '*' 1.0E+02 'reciprocal_centimetres' 'reciprocal_millimetres' '*' 1.0E-01 'reciprocal_centimetres' 'reciprocal_nanometres' '*' 1.0E-07 'reciprocal_centimetres' 'reciprocal_angstroms' '*' 1.0E-08 'reciprocal_centimetres' 'reciprocal_picometres' '*' 1.0E-10 # 'reciprocal_millimetres' 'reciprocal_metres' '*' 1.0E+03 'reciprocal_millimetres' 'reciprocal_centimetres' '*' 1.0E+01 'reciprocal_millimetres' 'reciprocal_nanometres' '*' 1.0E-06 'reciprocal_millimetres' 'reciprocal_angstroms' '*' 1.0E-07 'reciprocal_millimetres' 'reciprocal_picometres' '*' 1.0E-09 # 'reciprocal_nanometres' 'reciprocal_metres' '*' 1.0E+09 'reciprocal_nanometres' 'reciprocal_centimetres' '*' 1.0E+07 'reciprocal_nanometres' 'reciprocal_millimetres' '*' 1.0E+06 'reciprocal_nanometres' 'reciprocal_angstroms' '*' 1.0E-01 'reciprocal_nanometres' 'reciprocal_picometres' '*' 1.0E-03 # 'reciprocal_angstroms' 'reciprocal_metres' '*' 1.0E+10 'reciprocal_angstroms' 'reciprocal_centimetres' '*' 1.0E+08 'reciprocal_angstroms' 'reciprocal_millimetres' '*' 1.0E+07 'reciprocal_angstroms' 'reciprocal_nanometres' '*' 1.0E+01 'reciprocal_angstroms' 'reciprocal_picometres' '*' 1.0E-02 # 'reciprocal_picometres' 'reciprocal_metres' '*' 1.0E+12 'reciprocal_picometres' 'reciprocal_centimetres' '*' 1.0E+10 'reciprocal_picometres' 'reciprocal_millimetres' '*' 1.0E+09 'reciprocal_picometres' 'reciprocal_nanometres' '*' 1.0E+03 'reciprocal_picometres' 'reciprocal_angstroms' '*' 1.0E+01 ### 'nanometres_squared' 'angstroms_squared' '*' 1.0E+02 'nanometres_squared' 'picometres_squared' '*' 1.0E+06 # 'angstroms_squared' 'nanometres_squared' '*' 1.0E-02 'angstroms_squared' 'picometres_squared' '*' 1.0E+04 'angstroms_squared' '8pi2_angstroms_squared' '*' 78.9568 # 'picometres_squared' 'nanometres_squared' '*' 1.0E-06 'picometres_squared' 'angstroms_squared' '*' 1.0E-04 ### 'nanometres_cubed' 'angstroms_cubed' '*' 1.0E+03 'nanometres_cubed' 'picometres_cubed' '*' 1.0E+09 # 'angstroms_cubed' 'nanometres_cubed' '*' 1.0E-03 'angstroms_cubed' 'picometres_cubed' '*' 1.0E+06 # 'picometres_cubed' 'nanometres_cubed' '*' 1.0E-09 'picometres_cubed' 'angstroms_cubed' '*' 1.0E-06 ### 'kilopascals' 'gigapascals' '*' 1.0E-06 'gigapascals' 'kilopascals' '*' 1.0E+06 ### 'hours' 'minutes' '*' 6.0E+01 'hours' 'seconds' '*' 3.6E+03 'hours' 'microseconds' '*' 3.6E+09 # 'minutes' 'hours' '/' 6.0E+01 'minutes' 'seconds' '*' 6.0E+01 'minutes' 'microseconds' '*' 6.0E+07 # 'seconds' 'hours' '/' 3.6E+03 'seconds' 'minutes' '/' 6.0E+01 'seconds' 'microseconds' '*' 1.0E+06 # 'microseconds' 'hours' '/' 3.6E+09 'microseconds' 'minutes' '/' 6.0E+07 'microseconds' 'seconds' '/' 1.0E+06 ### 'celsius' 'kelvins' '-' 273.0 'kelvins' 'celsius' '+' 273.0 ### 'electrons_per_nanometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E+03 'electrons_per_nanometres_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+09 # 'electrons_per_angstroms_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-03 'electrons_per_angstroms_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+06 # 'electrons_per_picometres_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-09 'electrons_per_picometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E-06 ### ######################## ## DICTIONARY_HISTORY ## ######################## loop_ _dictionary_history.version _dictionary_history.update _dictionary_history.revision 1.6.4 2011-07-02 ; Corrections to support DLS Dectris header as per G. Winter (HJB) + Define new tags _diffrn_scan.time_period, _diffrn_scan.time_rstrt_incr, _diffrn_scan_frame.time_period, _diffrn_scan_frame.time_rstrt_incr + fix bad category name in loop in _diffrn_detector.id + remove stray text field terminator at line 4642 + fix unquoted tag as a value in _diffrn_scan_frame_monitor.id + make formerly mandatory and implicit deprecated items non-mandatory ; 1.6.3 2010-08-26 ; Cummulative corrections from 1.6.0, 1, 2 drafts (HJB) + Move descriptive dictionary comments into _datablock.description with catgeory tree described + add default _array_data.array_id value of 1 + add option of CBF_BACKGROUND_OFFSET_DELTA compression + add VARIANT catgeory and tags + add DIFFRN_SCAN_FRAME_MONITOR category ; 1.5.4 2007-07-28 ; Typographics corrections (HJB) + Corrected embedded degree characters to \% + Corrected embedded Aring to \%A + Added trailing ^ for a power + Removed 2 cases of a space after an underscore in tag name. ; 1.5.3 2007-07-08 ; Changes to support SLS miniCBF and suggestions from the 24 May 07 BNL imgCIF workshop (HJB) + Added new data items '_array_data.header_contents', '_array_data.header_convention', '_diffrn_data_frame.center_fast', '_diffrn_data_frame.center_slow', '_diffrn_data_frame.center_units', '_diffrn_measurement.sample_detector_distance', '_diffrn_measurement.sample_detector_voffset + Deprecated data items '_diffrn_detector_element.center[1]', '_diffrn_detector_element.center[2]' + Added comments and example on miniCBF + Changed all array_id data items to implicit ; 1.5.2 2007-05-06 ; Further clarifications of the coordinate system. (HJB) ; 1.5.1 2007-04-26 ; Improve defintion of X-axis to cover the case of no goniometer and clean up more line folds (HJB) ; 1.5 2007-07-25 ; This is a cummulative list of the changes proposed since the imgCIF workshop in Hawaii in July 2006. It is the result of contributions by H. J. Bernstein, A. Hammersley, J. Wright and W. Kabsch. 2007-02-19 Consolidated changes (edited by HJB) + Added new data items '_array_structure.compression_type_flag', '_array_structure_list_axis.fract_displacement', '_array_structure_list_axis.displacement_increment', '_array_structure_list_axis.reference_angle', '_array_structure_list_axis.reference_displacement', '_axis.system', '_diffrn_detector_element.reference_center_fast', '_diffrn_detector_element.reference_center_slow', '_diffrn_scan_axis.reference_angle', '_diffrn_scan_axis.reference_displacement', '_map.details', '_map.diffrn_id', '_map.entry_id', '_map.id', '_map_segment.array_id', '_map_segment.binary_id', '_map_segment.mask_array_id', '_map_segment.mask_binary_id', '_map_segment.id', '_map_segment.map_id', '_map_segment.details. + Change type of '_array_structure.byte_order' and '_array_structure.compression_type' to ucode to make these values case-insensitive + Add values 'packed_v2' and 'byte_offset' to enumeration of values for '_array_structure.compression_type' + Add to definitions for the binary data type to handle new compression types, maps, and a variety of new axis types. 2007-07-25 Cleanup of typos for formal release (HJB) + Corrected text fields for reference_ tag descriptions that were off by one column + Fix typos in comments listing fract_ tags + Changed name of release from 1.5_DRAFT to 1.5 + Fix unclosed text fields in various map definitions ; 1.4 2006-07-04 ; This is a change to reintegrate all changes made in the course of publication of ITVG, by the RCSB from April 2005 through August 2008 and changes for the 2006 imgCIF workshop in Hawaii. 2006-07-04 Consolidated changes for the 2006 imgCIF workshop (edited by HJB) + Correct type of '_array_structure_list.direction' from 'int' to 'code'. + Added new data items suggested by CN '_diffrn_data_frame.details' '_array_intensities.pixel_fast_bin_size', '_array_intensities.pixel_slow_bin_size and '_array_intensities.pixel_binning_method + Added deprecated item for completeness '_diffrn_frame_data.details' + Added entry for missing item in contents list '_array_structure_list_axis.displacement' + Added new MIME type X-BASE32K based on work by VL, KM, GD, HJB + Correct description of MIME boundary delimiter to start in column 1. + General cleanup of text fields to conform to changes for ITVG by removing empty lines at start and finish of text field. + Amend example for ARRAY_INTENSITIES to include binning. + Add local copy of type specification (as 'code') for all children of '_diffrn.id'. + For consistency, change all references to 'pi' to '\p' and all references to 'Angstroms' to '\%Angstroms'. + Clean up all powers to use IUCr convention of '^power^', as in '10^3^' for '10**3'. + Update 'yyyy-mm-dd' type regex to allow truncation from the right and improve comments to explain handling of related mmCIF 'yyyy-mm-dd:hh:mm' type, and use of 'Z' for GMT time zone. 2005-03-08 and 2004-08-08 fixed cases where _item_units.code used instead of _item_type.code (JDW) 2004-04-15 fixed item ordering in _diffrn_measurement_axis.measurement_id added sub_category 'vector' (JDW) ; 1.3.2 2005-06-25 ; 2005-06-25 ITEM_TYPE_LIST: code, ucode, line, uline regexps updated to those of current mmCIF; float modified by allowing integers terminated by a point as valid. The 'time' part of yyyy-mm-dd types made optional in the regexp. (BM) 2005-06-17 Minor corrections as for proofs for IT G Chapter 4.6 (NJA) 2005-02-21 Minor corrections to spelling and punctuation (NJA) 2005-01-08 Changes as per Nicola Ashcroft. + Updated example 1 for DIFFRN_MEASUREMENT to agree with mmCIF. + Spelled out "micrometres" for "um" and "millimetres" for "mm". + Removed phrase "which may be stored" from ARRAY_STRUCTURE description. + Removed unused 'byte-offsets' compressions and updated cites to ITVG for '_array_structure.compression_type'. (HJB) ; 1.3.1 2003-08-13 ; Changes as per Frances C. Bernstein. + Identify initials. + Adopt British spelling for centre in text. + Set \p and \%Angstrom and powers. + Clean up commas and unclear wordings. + Clean up tenses in history. Changes as per Gotzon Madariaga. + Fix the ARRAY_DATA example to align '_array_data.binary_id' and X-Binary-ID. + Add a range to '_array_intensities.gain_esd'. + In the example of DIFFRN_DETECTOR_ELEMENT, '_diffrn_detector_element.id' and '_diffrn_detector_element.detector_id' interchanged. + Fix typos for direction, detector and axes. + Clarify description of polarisation. + Clarify axes in '_diffrn_detector_element.center[1]' '_diffrn_detector_element.center[2]'. + Add local item types for items that are pointers. (HJB) ; 1.3.0 2003-07-24 ; Changes as per Brian McMahon. + Consistently quote tags embedded in text. + Clean up introductory comments. + Adjust line lengths to fit in 80 character window. + Fix several descriptions in AXIS category which referred to '_axis.type' instead of the current item. + Fix erroneous use of deprecated item '_diffrn_detector_axis.id' in examples for DIFFRN_SCAN_AXIS. + Add deprecated items '_diffrn_detector_axis.id' and '_diffrn_measurement_axis.id'. (HJB) ; 1.2.4 2003-07-14 ; Changes as per I. David Brown. + Enhance descriptions in DIFFRN_SCAN_AXIS to make them less dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS. + Provide a copy of the deprecated DIFFRN_FRAME_DATA category for completeness. (HJB) ; 1.2.3 2003-07-03 ; Cleanup to conform to ITVG. + Correct sign error in ..._cubed units. + Correct '_diffrn_radiation.polarisn_norm' range. (HJB) ; 1.2.2 2003-03-10 ; Correction of typos in various DIFFRN_SCAN_AXIS descriptions. (HJB) ; 1.2.1 2003-02-22 ; Correction of ATOM_ for ARRAY_ typos in various descriptions. (HJB) ; 1.2 2003-02-07 ; Corrections to encodings (remove extraneous hyphens) remove extraneous underscore in '_array_structure.encoding_type' enumeration. Correct typos in items units list. (HJB) ; 1.1.3 2001-04-19 ; Another typo corrections by Wilfred Li, and cleanup by HJB. ; 1.1.2 2001-03-06 ; Several typo corrections by Wilfred Li. ; 1.1.1 2001-02-16 ; Several typo corrections by JW. ; 1.1 2001-02-06 ; Draft resulting from discussions on header for use at NSLS. (HJB) + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME. + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'. + Add '_diffrn_measurement_axis.measurement_device' and change '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'. + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source', '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm', '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end', '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr', '_diffrn_scan_axis.displacement_rstrt_incr', '_diffrn_scan_frame_axis.angle_increment', '_diffrn_scan_frame_axis.angle_rstrt_incr', '_diffrn_scan_frame_axis.displacement', '_diffrn_scan_frame_axis.displacement_increment',and '_diffrn_scan_frame_axis.displacement_rstrt_incr'. + Add '_diffrn_measurement.device' to category key. + Update yyyy-mm-dd to allow optional time with fractional seconds for time stamps. + Fix typos caught by RS. + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to allow for coupled axes, as in spiral scans. + Add examples for fairly complete headers thanks to R. Sweet and P. Ellis. ; 1.0 2000-12-21 ; Release version - few typos and tidying up. (BM & HJB) + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end of dictionary. + Alphabetize dictionary. ; 0.7.1 2000-09-29 ; Cleanup fixes. (JW) + Correct spelling of diffrn_measurement_axis in '_axis.id' + Correct ordering of uses of '_item.mandatory_code' and '_item_default.value'. ; 0.7.0 2000-09-09 ; Respond to comments by I. David Brown. (HJB) + Add further comments on '\n' and '\t'. + Update ITEM_UNITS_LIST by taking section from mmCIF dictionary and adding metres. Change 'meter' to 'metre' throughout. + Add missing enumerations to '_array_structure.compression_type' and make 'none' the default. + Remove parent-child relationship between '_array_structure_list.index' and '_array_structure_list.precedence'. + Improve alphabetization. + Fix '_array_intensities_gain.esd' related function. + Improve comments in AXIS. + Fix DIFFRN_FRAME_DATA example. + Remove erroneous DIFFRN_MEASUREMENT example. + Add '_diffrn_measurement_axis.id' to the category key. ; 0.6.0 1999-01-14 ; Remove redundant information for ENC_NONE data. (HJB) + After the D5 remove binary section identifier, size and compression type. + Add Control-L to header. ; 0.5.1 1999-01-03 ; Cleanup of typos and syntax errors. (HJB) + Cleanup example details for DIFFRN_SCAN category. + Add missing quote marks for '_diffrn_scan.id' definition. ; 0.5 1999-01-01 ; Modifications for axis definitions and reduction of binary header. (HJB) + Restore '_diffrn_detector.diffrn_id' to DIFFRN_DETECTOR KEY. + Add AXIS category. + Bring in complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories from cif_mm.dic for clarity. + Change '_array_structure.encoding_type' from type code to uline and added X-Binary-Element-Type to MIME header. + Add detector beam centre '_diffrn_detector_element.center[1]' and '_diffrn_detector_element.center[2]'. + Correct item name of '_diffrn_refln.frame_id'. + Replace reference to '_array_intensities.undefined' by '_array_intensities.undefined_value'. + Replace references to '_array_intensity.scaling' with '_array_intensities.scaling'. + Add DIFFRN_SCAN... categories. ; 0.4 1998-08-11 ; Modifications to the 0.3 imgCIF draft. (HJB) + Reflow comment lines over 80 characters and corrected typos. + Update examples and descriptions of MIME encoded data. + Change name to cbfext98.dic. ; 0.3 1998-07-04 ; Modifications for imgCIF. (HJB) + Add binary type, which is a text field containing a variant on MIME encoded data. + Change type of '_array_data.data' to binary and specify internal structure of raw binary data. + Add '_array_data.binary_id', and make '_diffrn_frame_data.binary_id' and '_array_intensities.binary_id' into pointers to this item. ; 0.2 1997-12-02 ; Modifications to the CBF draft. (JW) + Add category hierarchy for describing frame data developed from discussions at the BNL imgCIF Workshop Oct 1997. The following changes are made in implementing the workshop draft. Category DIFFRN_ARRAY_DATA is renamed to DIFFRN_FRAME_DATA. Category DIFFRN_FRAME_TYPE is renamed to DIFFRN_DETECTOR_ELEMENT. The parent item for '_diffrn_frame_data.array_id' is changed from '_array_structure_list.array_id' to '_array_structure.id'. Item '_diffrn_detector.array_id' is deleted. + Add data item '_diffrn_frame_data.binary_id' to identify data groups within a binary section. The formal identification of the binary section is still fuzzy. ; 0.1 1997-01-24 ; First draft of this dictionary in DDL 2.1 compliant format by John Westbrook (JW). This version is adapted from the Crystallographic Binary File (CBF) Format Draft Proposal provided by Andy Hammersley (AH). Modifications to the CBF draft. (JW) + In this version the array description has been cast in the categories ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. These categories have been generalized to describe array data of arbitrary dimension. + Array data in this description are contained in the category ARRAY_DATA. This departs from the CBF notion of data existing in some special comment. In this description, data are handled as an ordinary data item encapsulated in a character data type. Although data this manner deviates from CIF conventions, it does not violate any DDL 2.1 rules. DDL 2.1 regular expressions can be used to define the binary representation which will permit some level of data validation. In this version, the placeholder type code "any" has been used. This translates to a regular expression which will match any pattern. It should be noted that DDL 2.1 already supports array data objects although these have not been used in the current mmCIF dictionary. It may be possible to use the DDL 2.1 ITEM_STRUCTURE and ITEM_STRUCTURE_LIST categories to provide the information that is carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. By moving the array structure to the DDL level it would be possible to define an array type as well as a regular expression defining the data format. + Multiple array sections can be properly handled within a single datablock. ; #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof
./CBFlib-0.9.2.2/doc/Cdiffrn_data_frame.html0000644000076500007650000000763211603702115016757 0ustar yayayaya (IUCr) CIF Definition save_diffrn_data_frame

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

Category DIFFRN_DATA_FRAME

Name:
'diffrn_data_frame'

Description:

       Data items in the DIFFRN_DATA_FRAME category record
              the details about each frame of data.

              The items in this category were previously in a
              DIFFRN_FRAME_DATA category, which is now deprecated.
              The items from the old category are provided
              as aliases but should not be used for new work.

Example:

Example 1 - A frame containing data from 4 frame elements. Each frame element has a common array configuration 'array_1' described in ARRAY_STRUCTURE and related categories. The data for each detector element are stored in four groups of binary data in the ARRAY_DATA category, linked by the array_id and binary_id.
 
        loop_
        _diffrn_data_frame.id
        _diffrn_data_frame.detector_element_id
        _diffrn_data_frame.array_id
        _diffrn_data_frame.binary_id
        frame_1   d1_ccd_1  array_1  1
        frame_1   d1_ccd_2  array_1  2
        frame_1   d1_ccd_3  array_1  3
        frame_1   d1_ccd_4  array_1  4



Category groups:
    inclusive_group
    array_data_group
Category keys:
    _diffrn_data_frame.id
    _diffrn_data_frame.detector_element_id

Mandatory category: no

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/ddl2.dic0000644000076500007650000031435211603702115013661 0ustar yayayaya########################################################################### # # File: mmcif_ddl.dic # Date: Mon Aug 9 02:48:08 EDT 2004 # # Created from files in CVS module dict-mmcif_ddl.dic unless noted: # mmcif_ddl-header.dic # mmcif_ddl-data.dic # mmcif_ddl-def-1.dic # mmcif_ddl-def-2.dic # ########################################################################### ########################################################################### # # File: mmcif_ddl-header.dic # # mmCIF DDL Core Dictionary with NDB extensions # # This DDL dictionary is a mirror of ddl_core.dic-org with all implicit # data items fully expanded and with NDB extensions added. # # Header Section # # ########################################################################### data_mmcif_ddl.dic _datablock.id mmcif_ddl.dic _datablock.description ; This data block holds the core DDL. ; _dictionary.datablock_id mmcif_ddl.dic _dictionary.title mmcif_ddl.dic _dictionary.version 2.1.6 loop_ _dictionary_history.version _dictionary_history.update _dictionary_history.revision 1.1 1994-07-25 ; DDL 1.1 from Syd Hall et. al. ; 1.2.1 1994-09-18 ; Changes:.........etc. etc. John Westbrook ; 1.2.9 1994-10-05 ; Reflect the results of the Treaty of Brussels. JW. ; 2.0.1 1994-10-15 ; Adapted for closer mapping to DDL1.3 and clearer presentation. SRH/NS. ; 2.0.2 1994-10-16 ; Even closer................... SRH/NS. ; 2.0.3 1994-10-17 ; Coming to grips with the links and dependencies..... SRH/NS. ; 2.0.4 1994-10-20 ; Backed in changes from mm-ddl 1.2.12 Many other changes ... (JW) ; 2.0.5 1994-10-20 ; Some small adjustments..........SRH. ; 2.0.6 1994-10-20 ; More small adjustments..........JW. ; 2.0.7 1994-11-03 ; Changes: (JW) + Place all item and item_linked category definitions with the parent item. + Fixed a number of not so trivial typos. + Corrected errors in the data type conversion table. + Corrected key item inconsistencies. + Added the item_aliases category. ; 2.0.8 1994-11-10 ; Miscellaneous corrections: (JW) + defined sub_category_group + corrected typo in category_examples.id definition + added _item_type_conditions.name in item category + added _item_structure.name in item category + corrected typo in item_aliases category definition + corrected typo in sub_category.method_id definition ; 2.0.9 1994-11-14 ; Changes: (JW) + added ITEM_UNITS, ITEM_UNITS_LIST, and UNITS_CONVERSION categories. + added an additional primitive type for character type items for which comparisons must be case insensitive. Since it is customary to permit item names and category identifiers to be specified in mixed case, it is necessary to declare that case should NOT be considered in any comparisons of these items. ; 2.0.10 1994-11-23 ; Changes: (JW) + Several name category changes for the sake of consistency: enumeration -> item_enumeration enumeration_default -> item_enumeration_default enumeration_limit -> item_enumeration_limit units_conversion -> item_units_conversion + Added _item_related.function_code alternate_exclusive to identify mutually exclusive alternative declarations of the same item. + Added structure options for real symmetric matrices. + Changed from zero based indices to one based indices for compatibility with existing matrix component definitions. + Add _item_linked.parent_name to the key of the item_linked category. + Reorder items in the DDL so be alphabetical within category groups. ; 2.0.11 1994-11-28 ; Changes: (JW) + Corrected spelling error for the data type code in the DICTIONARY_HISTORY category. + Add category BLOCK to hold the data block name and data block description. The block identifier was also added to the key of the item category. The block identifier can be implicitly derived from the STAR "data_" delimiter. This identifier is required to form the key for categories which are conceptually related to the data block as a whole. ; 2.0.12 1994-11-30 ; Changes: (JW) + Added a data item _block.scope to indicate the scope of data item names defined within included data blocks. ; 2.0.13 1994-12-12 ; Changes: (JW) + Deleted data item _block.scope. + Changed DICTIONARY category key to _dictionary.block_id to guarantee only one dictionary definition per block. + Deleted data item _item.block_id as this will be replaced by an item address syntax that will include block, save frame, and url. ; 2.0.14 1994-12-15 ; Changes: (JW) + Made some terminology changes suggested by PMDF _item_enumeration.code -> _item_enumeration.value ITEM_ENUMERATION_DEFAULT -> ITEM_DEFAULT ITEM_ENUMERATION_LIMIT -> ITEM_RANGE + Added item _item_type_list.detail + Version 2.0.14 is being frozen and exported. ; 2.0.15 1995-02-13 ; Changes: (JW) + Added '_' prefix to all data item save frame names. References to data item names now always include a leading underscore independent of the usage context. + A few miscellaneous corrections. ; 2.0.16 1995-06-18 ; Changes: (JW) + Revised the block level categories in the following ways: Changed category BLOCK to DATA_BLOCK. Added connection from _data_block.id to _category.implicit_key in order to provide a formal means of merging the contents of categories between data blocks. + Moved ennumerations for _method_list.code and method_list.language to examples. + Removed symmetric matrix options from the ennumerations for _item_structure.organization. + Added _item_related.function codes for 'associated_value', 'associated_esd', 'replaces' and 'replacedby' + Added data items _item_aliases.dictionary and _item_aliases.dictionary_version. + Reorganized method categories such that multiple methods can be applied at each level of data structure. Introduced a consistent set of categories to hold method associations: ITEM_METHODS, CATEGORY_METHODS, SUB_CATEGORY_METHODS, and DATA_BLOCK_METHODS. Removed data items _category.method_id _sub_category.method_id. ; 2.0.17 1995-06-22 ; Changes: (JW) + Quoted data vaules containing the leading string 'data_'. ; 2.1.0 1995-07-20 ; Changes: (JW) Final adjustments before the first release of the mmCIF dictionary: + changed data_block to datablock to avoid any problems with the STAR data_ reserved token. + created new category to hold item subcategory associations and deleted the subcategory attribute from ITEM category. + modified regular expressions to reflect limitations observed on several platforms. + expanded the ennumeration of _item_related.function_code. + removed default value from _item.manadatory_code. + removed type construct for date and changed date data type to yyyy-mm-dd + added less restrictive data type for alias names. ; 2.1.1 1995-09-26 ; Changes: (JW) + Changed regular expressions for type code to permit single quote. + Corrected regular expression syntax for type name and type date. + Corrected lower bound description for item_range.minimum. The incorrect <= condition is changed to <. + _item_mandatory.code has been now a mandatory item. + _item_aliases.dictionary and _item_aliases.dictionary_version are added to the composite key for category ITEM_ALIASES. + _datablock.id data type changes to type code. + Shortened the name _item_aliases.dictionary_version to _item_aliases.version ; 2.1.2 1997-01-24 ; Changes: (JW) + Added associated_error to the enumeration list of _item_related.function_code. ; 2.1.3 2000-10-16 ; Changes: (JW) + Changed data type for regular expression in _item_type_list.construct to type text. ; 2.1.5 2003-06-23 ; Changes: (JW) + NDB extensions adopted into ddl_core + New partitioning scheme implemented ; 2.1.6 2004-04-15 ; Changes: (JW) + Name changed to mmcif_ddl.dic ; ### EOF mmcif_ddl-header.dic #### ########################################################################### # # File: mmcif_ddl-data.dic # # mmCIF DDL Core Dictionary with NDB extensions # # This DDL dictionary is a mirror of ddl_core.dic-org with all implicit # data items fully expanded and with NDB extensions added. # # Data Section # # ########################################################################### # DATA TYPE CONVERSION TABLE # -------------------------- loop_ _item_type_list.code _item_type_list.primitive_code _item_type_list.detail _item_type_list.construct code char 'A single word' '[^\t\n "]*' char char 'A single line of text' '[^\n]*' text char 'Text which may span lines' '.*' int numb 'Unsigned integer data' '[0-9]+' name uchar 'A data item name (restrictive type)' '_[_A-Za-z0-9]+[.][][_A-Za-z0-9\<\>%/-]+' aliasname uchar 'A DDL 1.4 data item name (less restrictive type)' '_[^\t\n "]+' idname uchar 'A data item name component or identifier' '[_A-Za-z0-9]+' any char 'Any data type' '.*' yyyy-mm-dd char 'A date format' '[0-9][0-9][0-9][0-9]-[0-9]?[0-9]-[0-9][0-9]' # loop_ _category_group_list.id _category_group_list.parent_id _category_group_list.description 'ddl_group' . ; Component categories of the macromolecular DDL ; 'datablock_group' 'ddl_group' ; Categories that describe the characteristics of data blocks. ; 'category_group' 'ddl_group' ; Categories that describe the characteristics of categories. ; 'sub_category_group' 'ddl_group' ; Categories that describe the characteristics of subcategories. ; 'item_group' 'ddl_group' ; Categories that describe the characteristics of data items. ; 'dictionary_group' 'ddl_group' ; Categories that describe the dictionary. ; 'compliance_group' 'ddl_group' ; Categories that are retained specifically for compliance with older versions of the DDL. ; ### EOF mmcif_ddl-data.dic ########################################################################### # # File: mmcif_ddl-def-1.dic # # mmCIF DDL Core Dictionary with NDB extensions # # This DDL dictionary is a mirror of ddl_core.dic-org with all implicit # data items fully expanded and with NDB extensions added. # # Definition Section 1. # (Core Definitions) # # ########################################################################### # ---------------------------------------------------------------------------- save_DATABLOCK _category.description ; Attributes defining the characteristics of a data block. ; _category.id datablock _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id datablock _category_key.name '_datablock.id' loop_ _category_group.id _category_group.category_id 'ddl_group' datablock 'datablock_group' datablock save_ save__datablock.id _item_description.name '_datablock.id' _item_description.description ; The identity of the data block. ; _item.name '_datablock.id' _item.category_id datablock _item.mandatory_code implicit _item_type.name '_datablock.id' _item_type.code code loop_ _item_linked.parent_name _item_linked.child_name '_datablock.id' '_datablock_methods.datablock_id' '_datablock.id' '_dictionary.datablock_id' '_datablock.id' '_category.implicit_key' save_ save__datablock.description _item_description.name '_datablock.description' _item_description.description ; Text description of the data block. ; _item.name '_datablock.description' _item.category_id datablock _item.mandatory_code yes _item_type.name '_datablock.description' _item_type.code text save_ # ---------------------------------------------------------------------------- save_DATABLOCK_METHODS _category.description ; Attributes specifying the association between data blocks and methods. ; _category.id datablock_methods _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name datablock_methods '_datablock_methods.method_id' datablock_methods '_datablock_methods.datablock_id' loop_ _category_group.id _category_group.category_id 'ddl_group' datablock_methods 'datablock_group' datablock_methods save_ save__datablock_methods.datablock_id _item_description.name '_datablock_methods.datablock_id' _item_description.description ; Identifier of data block. ; _item.name '_datablock_methods.datablock_id' _item.category_id datablock_methods _item.mandatory_code implicit _item_type.name '_datablock_methods.datablock_id' _item_type.code code save_ save__datablock_methods.method_id _item_description.name '_datablock_methods.method_id' _item_description.description ; Unique method identifier associated with a data block. ; _item.name '_datablock_methods.method_id' _item.category_id datablock_methods _item.mandatory_code yes _item_type.name '_datablock_methods.method_id' _item_type.code idname save_ # ---------------------------------------------------------------------------- save_CATEGORY _category.description ; Attributes defining the functionality for the entire category. ; _category.id category _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id category _category_key.name '_category.id' loop_ _category_group.id _category_group.category_id 'ddl_group' category 'category_group' category save_ save__category.id _item_description.name '_category.id' _item_description.description ; The identity of the data category. Data items may only be looped with items of the same category. ; _item.name '_category.id' _item.category_id category _item.mandatory_code yes _item_type.name '_category.id' _item_type.code idname loop_ _item_linked.child_name _item_linked.parent_name '_category_examples.id' '_category.id' '_category_group.category_id' '_category.id' '_category_key.id' '_category.id' '_category_methods.category_id' '_category.id' '_item.category_id' '_category.id' save_ save__category.description _item_description.name '_category.description' _item_description.description ; Text description of a category. ; _item.name '_category.description' _item.category_id category _item.mandatory_code yes _item_type.name '_category.description' _item_type.code text save_ save__category.implicit_key _item_description.name '_category.implicit_key' _item_description.description ; An identifier that may be used to distinguish the contents of like categories between data blocks. ; _item.name '_category.implicit_key' _item.category_id category _item.mandatory_code implicit _item_type.name '_category.implicit_key' _item_type.code code save_ save__category.mandatory_code _item_description.name '_category.mandatory_code' _item_description.description ; Whether the category must be specified in a dictionary. ; _item.name '_category.mandatory_code' _item.category_id category _item.mandatory_code yes _item_type.name '_category.mandatory_code' _item_type.code code save_ # ---------------------------------------------------------------------------- save_CATEGORY_EXAMPLES _category.description ; Example applications and descriptions of data items in this category. ; _category.id category_examples _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name category_examples '_category_examples.id' category_examples '_category_examples.case' save_ save__category_examples.id _item_description.name '_category_examples.id' _item_description.description ; The name of category. ; _item.name '_category_examples.id' _item.category_id category_examples _item.mandatory_code implicit _item_type.name '_category_examples.id' _item_type.code idname save_ save__category_examples.case _item_description.name '_category_examples.case' _item_description.description ; A case of examples involving items in this category. ; _item.name '_category_examples.case' _item.category_id category_examples _item.mandatory_code yes _item_type.name '_category_examples.case' _item_type.code text save_ save__category_examples.detail _item_description.name '_category_examples.detail' _item_description.description ; A description of an example _category_examples.case ; _item.name '_category_examples.detail' _item.category_id category_examples _item.mandatory_code no _item_type.name '_category_examples.detail' _item_type.code text save_ # ---------------------------------------------------------------------------- save_CATEGORY_KEY _category.description ; This category holds a list of the item names that uniquely identify the elements of the category. ; _category.id category_key _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name category_key '_category_key.name' category_key '_category_key.id' loop_ _category_group.id _category_group.category_id 'ddl_group' category_key 'category_group' category_key save_ save__category_key.name _item_description.name '_category_key.name' _item_description.description ; The name of a data item that serves as a key identifier for the category (eg. a component of the primary key). ; _item.name '_category_key.name' _item.category_id category_key _item.mandatory_code yes _item_type.name '_category_key.name' _item_type.code name save_ save__category_key.id _item_description.name '_category_key.id' _item_description.description ; The identifier of the category (eg. a component of the primary key). ; _item.name '_category_key.id' _item.category_id category_key _item.mandatory_code implicit _item_type.name '_category_key.id' _item_type.code idname save_ # ---------------------------------------------------------------------------- save_CATEGORY_GROUP _category.description ; Provides a list of category groups to which the base category belongs. ; _category.id category_group _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name category_group '_category_group.id' category_group '_category_group.category_id' loop_ _category_group.id _category_group.category_id 'ddl_group' category_group 'category_group' category_group save_ save__category_group.id _item_description.name '_category_group.id' _item_description.description ; The name of a category group ... ; _item.name '_category_group.id' _item.category_id category_group _item.mandatory_code yes _item_type.name '_category_group.id' _item_type.code idname save_ save__category_group.category_id _item_description.name '_category_group.category_id' _item_description.description ; The name of a category ... ; _item.name '_category_group.category_id' _item.category_id category_group _item.mandatory_code implicit _item_type.name '_category_group.category_id' _item_type.code idname save_ # ---------------------------------------------------------------------------- save_CATEGORY_GROUP_LIST _category.description ; This category provides the definition of each category group. A category group is a collection of related categories. ; _category.id category_group_list _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id category_group_list _category_key.name '_category_group_list.id' loop_ _category_group.id _category_group.category_id 'ddl_group' category_group_list 'category_group' category_group_list save_ save__category_group_list.id _item_description.name '_category_group_list.id' _item_description.description ; The name of a category group ... ; _item.name '_category_group_list.id' _item.category_id category_group_list _item.mandatory_code yes _item_type.name '_category_group_list.id' _item_type.code idname loop_ _item_linked.child_name _item_linked.parent_name '_category_group.id' '_category_group_list.id' '_category_group_list.parent_id' '_category_group_list.id' save_ save__category_group_list.description _item_description.name '_category_group_list.description' _item_description.description ; Text description of a category group... ; _item.name '_category_group_list.description' _item.category_id category_group_list _item.mandatory_code yes _item_type.name '_category_group_list.description' _item_type.code text save_ save__category_group_list.parent_id _item_description.name '_category_group_list.parent_id' _item_description.description ; The name of the optional parent category group. ; _item.name '_category_group_list.parent_id' _item.category_id category_group_list _item.mandatory_code no _item_type.name '_category_group_list.parent_id' _item_type.code idname save_ # ---------------------------------------------------------------------------- save_CATEGORY_METHODS _category.description ; Attributes specifying the association between categories and methods. ; _category.id category_methods _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name category_methods '_category_methods.method_id' category_methods '_category_methods.category_id' loop_ _category_group.id _category_group.category_id 'ddl_group' category_methods 'category_group' category_methods save_ save__category_methods.category_id _item_description.name '_category_methods.category_id' _item_description.description ; The name of the category ; _item.name '_category_methods.category_id' _item.category_id category_methods _item.mandatory_code implicit _item_type.name '_category_methods.category_id' _item_type.code idname save_ save__category_methods.method_id _item_description.name '_category_methods.method_id' _item_description.description ; The name of the method ; _item.name '_category_methods.method_id' _item.category_id category_methods _item.mandatory_code yes _item_type.name '_category_methods.method_id' _item_type.code idname save_ # ---------------------------------------------------------------------------- save_SUB_CATEGORY _category.description ; The purpose of a sub-category is to define an association between data items within a category and optionally provide a method to validate the collection of items. The sub-category named 'cartesian' might be applied to the data items for the coordinates x, y, and z. ; _category.id sub_category _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id sub_category _category_key.name '_sub_category.id' loop_ _category_group.id _category_group.category_id 'ddl_group' sub_category 'sub_category_group' sub_category save_ save__sub_category.id _item_description.name '_sub_category.id' _item_description.description ; The identity of the sub-category. ; _item.name '_sub_category.id' _item.category_id sub_category _item.mandatory_code yes _item_type.name '_sub_category.id' _item_type.code idname loop_ _item_linked.child_name _item_linked.parent_name '_sub_category_examples.id' '_sub_category.id' '_sub_category_methods.sub_category_id' '_sub_category.id' '_item_sub_category.id' '_sub_category.id' save_ save__sub_category.description _item_description.name '_sub_category.description' _item_description.description ; Description of the sub-category. ; _item.name '_sub_category.description' _item.category_id sub_category _item.mandatory_code yes _item_type.name '_sub_category.description' _item_type.code text save_ # ---------------------------------------------------------------------------- save_SUB_CATEGORY_EXAMPLES _category.description ; Example applications and descriptions of data items in this subcategory. ; _category.id sub_category_examples _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name sub_category_examples '_sub_category_examples.id' sub_category_examples '_sub_category_examples.case' loop_ _category_group.id _category_group.category_id 'ddl_group' sub_category_examples 'sub_category_group' sub_category_examples save_ save__sub_category_examples.id _item_description.name '_sub_category_examples.id' _item_description.description ; The name for the subcategory. ; _item.name '_sub_category_examples.id' _item.category_id sub_category_examples _item.mandatory_code yes _item_type.name '_sub_category_examples.id' _item_type.code idname save_ save__sub_category_examples.case _item_description.name '_sub_category_examples.case' _item_description.description ; An example involving items in this subcategory. ; _item.name '_sub_category_examples.case' _item.category_id sub_category_examples _item.mandatory_code yes _item_type.name '_sub_category_examples.case' _item_type.code text save_ save__sub_category_examples.detail _item_description.name '_sub_category_examples.detail' _item_description.description ; A description of an example _sub_category_examples.case ; _item.name '_sub_category_examples.detail' _item.category_id sub_category_examples _item.mandatory_code no _item_type.name '_sub_category_examples.detail' _item_type.code text save_ # ---------------------------------------------------------------------------- save_SUB_CATEGORY_METHODS _category.description ; Attributes specifying the association between subcategories and methods. ; _category.id sub_category_methods _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name sub_category_methods '_sub_category_methods.method_id' sub_category_methods '_sub_category_methods.sub_category_id' loop_ _category_group.id _category_group.category_id 'ddl_group' sub_category_methods 'sub_category_group' sub_category_methods save_ save__sub_category_methods.sub_category_id _item_description.name '_sub_category_methods.sub_category_id' _item_description.description ; The name of the subcategory ; _item.name '_sub_category_methods.sub_category_id' _item.category_id sub_category_methods _item.mandatory_code yes _item_type.name '_sub_category_methods.sub_category_id' _item_type.code idname save_ save__sub_category_methods.method_id _item_description.name '_sub_category_methods.method_id' _item_description.description ; The name of the method ; _item.name '_sub_category_methods.method_id' _item.category_id sub_category_methods _item.mandatory_code yes _item_type.name '_sub_category_methods.method_id' _item_type.code idname save_ # ---------------------------------------------------------------------------- save_ITEM _category.description ; Attributes which describe the characteristics of a data item. ; _category.id item _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id item _category_key.name '_item.name' loop_ _category_group.id _category_group.category_id 'ddl_group' item 'item_group' item save_ save__item.name _item_description.name '_item.name' _item_description.description ; Data name of the defined item. ; _item_type.name '_item.name' _item_type.code name _item.name '_item.name' _item.category_id item _item.mandatory_code implicit loop_ _item_linked.child_name _item_linked.parent_name '_category_key.name' '_item.name' '_item_aliases.name' '_item.name' '_item_default.name' '_item.name' '_item_dependent.name' '_item.name' '_item_dependent.dependent_name' '_item.name' '_item_description.name' '_item.name' '_item_enumeration.name' '_item.name' '_item_examples.name' '_item.name' '_item_linked.child_name' '_item.name' '_item_linked.parent_name' '_item.name' '_item_methods.name' '_item.name' '_item_range.name' '_item.name' '_item_related.name' '_item.name' '_item_related.related_name' '_item.name' '_item_type.name' '_item.name' '_item_type_conditions.name' '_item.name' '_item_structure.name' '_item.name' '_item_sub_category.name' '_item.name' '_item_units.name' '_item.name' save_ save__item.mandatory_code _item_description.name '_item.mandatory_code' _item_description.description ; Signals if the defined item is mandatory for the proper description of its category. ; _item.name '_item.mandatory_code' _item.category_id item _item.mandatory_code yes _item_type.name '_item.mandatory_code' _item_type.code code loop_ _item_enumeration.name _item_enumeration.value _item_enumeration.detail '_item.mandatory_code' yes 'required item in this category' '_item.mandatory_code' no 'optional item in this category' '_item.mandatory_code' implicit 'required item but may be determined from context' save_ save__item.category_id _item_description.name '_item.category_id' _item_description.description ; This is category id of the item. ; _item.name '_item.category_id' _item.category_id item _item.mandatory_code implicit _item_type.name '_item.category_id' _item_type.code idname save_ # ---------------------------------------------------------------------------- save_ITEM_ALIASES _category.description ; This category holds a list of possible alias names or synonyms for each data item. Each alias name is identified by the name and version of the dictionary to which it belongs. ; _category.id item_aliases _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name item_aliases '_item_aliases.alias_name' item_aliases '_item_aliases.dictionary' item_aliases '_item_aliases.version' save_ save__item_aliases.name _item_description.name '_item_aliases.name' _item_description.description ; Name for the data item. ; _item.name '_item_aliases.name' _item.category_id item_aliases _item.mandatory_code implicit _item_type.name '_item_aliases.name' _item_type.code name save_ save__item_aliases.alias_name _item_description.name '_item_aliases.alias_name' _item_description.description ; Alias name for the data item. ; _item.name '_item_aliases.alias_name' _item.category_id item_aliases _item.mandatory_code yes _item_type.name '_item_aliases.alias_name' _item_type.code aliasname save_ save__item_aliases.dictionary _item_description.name '_item_aliases.dictionary' _item_description.description ; The dictionary in which the alias name is defined. ; _item.name '_item_aliases.dictionary' _item.category_id item_aliases _item.mandatory_code yes _item_type.name '_item_aliases.dictionary' _item_type.code char save_ save__item_aliases.version _item_description.name '_item_aliases.version' _item_description.description ; The version of the dictionary in which the alias name is defined. ; _item.name '_item_aliases.version' _item.category_id item_aliases _item.mandatory_code yes _item_type.name '_item_aliases.version' _item_type.code char save_ # ---------------------------------------------------------------------------- save_ITEM_DEFAULT _category.description ; Attributes specifying the default value for a data item. ; _category.id item_default _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id item_default _category_key.name '_item_default.name' loop_ _category_group.id _category_group.category_id 'ddl_group' item_default 'item_group' item_default save_ save__item_default.name _item_description.name '_item_default.name' _item_description.description ; The name of item for which the default value is defined ; _item.name '_item_default.name' _item.category_id item_default _item.mandatory_code implicit _item_type.name '_item_default.name' _item_type.code name save_ save__item_default.value _item_description.name '_item_default.value' _item_description.description ; The default value for the defined item if it is not specified explicitly. If a data value is not declared, the default is assumed to be the most likely or natural value. ; _item.name '_item_default.value' _item.category_id item_default _item.mandatory_code no _item_type.name '_item_default.value' _item_type.code any save_ # ---------------------------------------------------------------------------- save_ITEM_DEPENDENT _category.description ; Attributes which identify other data items that must be specified for the defined data item to be valid. ; _category.id item_dependent _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name item_dependent '_item_dependent.name' item_dependent '_item_dependent.dependent_name' save_ save__item_dependent.name _item_description.name '_item_dependent.name' _item_description.description ; Item name of a dependent item. ; _item.name '_item_dependent.name' _item.category_id item_dependent _item.mandatory_code implicit _item_type.name '_item_dependent.name' _item_type.code name save_ save__item_dependent.dependent_name _item_description.name '_item_dependent.dependent_name' _item_description.description ; Data name of a dependent item. ; _item.name '_item_dependent.dependent_name' _item.category_id item_dependent _item.mandatory_code yes _item_type.name '_item_dependent.dependent_name' _item_type.code name save_ # ---------------------------------------------------------------------------- save_ITEM_DESCRIPTION _category.description ; This category holds the descriptions of each data item. ; _category.id item_description _category.mandatory_code yes _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name item_description '_item_description.name' item_description '_item_description.description' loop_ _category_group.id _category_group.category_id 'ddl_group' item_description 'item_group' item_description save_ save__item_description.name _item_description.name '_item_description.name' _item_description.description ; Tne name of data item. ; _item.name '_item_description.name' _item.category_id item_description _item.mandatory_code implicit _item_type.name '_item_description.name' _item_type.code name save_ save__item_description.description _item_description.name '_item_description.description' _item_description.description ; Text decription of the defined data item. ; _item.name '_item_description.description' _item.category_id item_description _item.mandatory_code yes _item_type.name '_item_description.description' _item_type.code text save_ # ---------------------------------------------------------------------------- save_ITEM_ENUMERATION _category.description ; Attributes which specify the permitted enumeration of the items. ; _category.id item_enumeration _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name item_enumeration '_item_enumeration.name' item_enumeration '_item_enumeration.value' loop_ _category_group.id _category_group.category_id 'ddl_group' item_enumeration 'item_group' item_enumeration save_ save__item_enumeration.name _item_description.name '_item_enumeration.name' _item_description.description ; Name of data item. ; _item.name '_item_enumeration.name' _item.category_id item_enumeration _item.mandatory_code implicit _item_type.name '_item_enumeration.name' _item_type.code name save_ save__item_enumeration.value _item_description.name '_item_enumeration.value' _item_description.description ; A permissible value, character or number, for the defined item. ; _item.name '_item_enumeration.value' _item.category_id item_enumeration _item.mandatory_code yes _item_type.name '_item_enumeration.value' _item_type.code any save_ save__item_enumeration.detail _item_description.name '_item_enumeration.detail' _item_description.description ; A description of a permissible value for the defined item. ; _item.name '_item_enumeration.detail' _item.category_id item_enumeration _item.mandatory_code no _item_type.name '_item_enumeration.detail' _item_type.code text save_ # ---------------------------------------------------------------------------- save_ITEM_EXAMPLES _category.description ; Attributes for describing application examples of the data item. ; _category.id item_examples _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name item_examples '_item_examples.name' item_examples '_item_examples.case' loop_ _category_group.id _category_group.category_id 'ddl_group' item_examples 'item_group' item_examples save_ save__item_examples.name _item_description.name '_item_examples.name' _item_description.description ; The name of data item for the example. ; _item.name '_item_examples.name' _item.category_id item_examples _item.mandatory_code implicit _item_type.name '_item_examples.name' _item_type.code name save_ save__item_examples.case _item_description.name '_item_examples.case' _item_description.description ; An example application of the defined data item. ; _item.name '_item_examples.case' _item.category_id item_examples _item.mandatory_code no _item_type.name '_item_examples.case' _item_type.code text save_ save__item_examples.detail _item_description.name '_item_examples.detail' _item_description.description ; A description of an example specified in _item_example.case ; _item.name '_item_examples.detail' _item.category_id item_examples _item.mandatory_code no _item_type.name '_item_examples.detail' _item_type.code text save_ # ---------------------------------------------------------------------------- save_ITEM_LINKED _category.description ; Attributes which describe how equivalent data items are linked within categories and across different categories. ; _category.id item_linked _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name item_linked '_item_linked.child_name' item_linked '_item_linked.parent_name' loop_ _category_group.id _category_group.category_id 'ddl_group' item_linked 'item_group' item_linked save_ save__item_linked.child_name _item_description.name '_item_linked.child_name' _item_description.description ; Name of the child data item. ; _item.name '_item_linked.child_name' _item.category_id item_linked _item.mandatory_code yes _item_type.name '_item_linked.child_name' _item_type.code name save_ save__item_linked.parent_name _item_description.name '_item_linked.parent_name' _item_description.description ; Name of the parent data item. ; _item.name '_item_linked.parent_name' _item.category_id item_linked _item.mandatory_code implicit _item_type.name '_item_linked.parent_name' _item_type.code name save_ # ---------------------------------------------------------------------------- save_ITEM_METHODS _category.description ; Attributes specifying the association between data items and methods. ; _category.id item_methods _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name item_methods '_item_methods.method_id' item_methods '_item_methods.name' loop_ _category_group.id _category_group.category_id 'ddl_group' item_methods 'item_group' item_methods save_ save__item_methods.name _item_description.name '_item_methods.name' _item_description.description ; The name of the item ; _item.name '_item_methods.name' _item.category_id item_methods _item.mandatory_code implicit _item_type.name '_item_methods.name' _item_type.code name save_ save__item_methods.method_id _item_description.name '_item_methods.method_id' _item_description.description ; The name of itemthe method ; _item.name '_item_methods.method_id' _item.category_id item_methods _item.mandatory_code yes _item_type.name '_item_methods.method_id' _item_type.code idname save_ # ---------------------------------------------------------------------------- save_ITEM_RANGE _category.description ; The range of permissible values of a data item. When multiple ranges are specified they are interpreted sequentially using a logical OR. To specify that an item value may be equal to a boundary value, specify an item range where the maximum and mimimum values equal the boundary value. ; _category.id item_range _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name item_range '_item_range.name' item_range '_item_range.minimum' item_range '_item_range.maximum' loop_ _category_group.id _category_group.category_id 'ddl_group' item_range 'item_group' item_range save_ save__item_range.name _item_description.name '_item_range.name' _item_description.description ; Name of data item ... ; _item.name '_item_range.name' _item.category_id item_range _item.mandatory_code implicit _item_type.name '_item_range.name' _item_type.code name save_ save__item_range.minimum _item_description.name '_item_range.minimum' _item_description.description ; Minimum permissible value of a data item or the lower bound of a permissible range. ( minimum value < data value) ; _item.name '_item_range.minimum' _item.category_id item_range _item.mandatory_code no _item_type.name '_item_range.minimum' _item_type.code any save_ save__item_range.maximum _item_description.name '_item_range.maximum' _item_description.description ; Maximum permissible value of a data item or the upper bound of a permissible range. ( maximum value > data value) ; _item.name '_item_range.maximum' _item.category_id item_range _item.mandatory_code no _item_type.name '_item_range.maximum' _item_type.code any save_ # ---------------------------------------------------------------------------- save_ITEM_RELATED _category.description ; Attributes which specify recognized relationships between data items. ; _category.id item_related _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name item_related '_item_related.name' item_related '_item_related.related_name' item_related '_item_related.function_code' loop_ _category_group.id _category_group.category_id 'ddl_group' item_related 'item_group' item_related save_ save__item_related.name _item_description.name '_item_related.name' _item_description.description ; Identifies a defined data item ... ; _item.name '_item_related.name' _item.category_id item_related _item.mandatory_code implicit _item_type.name '_item_related.name' _item_type.code name save_ save__item_related.related_name _item_description.name '_item_related.related_name' _item_description.description ; Identifies a data item by name which is closely related to the defined data item by the manner described by _item_related.function_code ; _item.name '_item_related.related_name' _item.category_id item_related _item.mandatory_code yes _item_type.name '_item_related.related_name' _item_type.code name save_ save__item_related.function_code _item_description.name '_item_related.function_code' _item_description.description ; The code for the type of relationship of the item identified by _item_related.name and the defined item. ALTERNATE indicates that the item identified in _item_related.related_name is an alternative expression in terms of its application and attributes to the item in this definition. ALTERNATE_EXCLUSIVE indicates that the item identified in _item_related.related_name is an alternative expression in terms of its application and attributes to the item in this definition. Only one of the alternative forms may be specified. CONVENTION indicates that the item identified in _item_related.related_name differs from the defined item only in terms of a convention in its expression. CONVERSION_CONSTANT indicates that the item identified in _item_related.related_name differs from the defined item only by a known constant. CONVERSION_ARBITRARY indicates that the item identified in _item_related.related_name differs from the defined item only by a arbitrary constant. REPLACES indicates that the defined item replaces the item identified in _item_related.related_name. REPLACEDBY indicates that the defined item is replaced by the item identified in _item_related.related_name. ASSOCIATED_VALUE indicates that the item identified in _item_related.related_name is meaningful when associated with the defined item. ASSOCIATED_ESD indicates that the item identified in _item_related.related_name is the estimated standard deviation of of the defined item. ; _item.name '_item_related.function_code' _item.category_id item_related _item.mandatory_code yes _item_type.name '_item_related.function_code' _item_type.code code loop_ _item_enumeration.name _item_enumeration.value _item_enumeration.detail '_item_related.function_code' alternate 'alternate form of the item' '_item_related.function_code' alternate_exclusive 'mutually exclusive alternate form of the item' '_item_related.function_code' convention 'depends on defined convention' '_item_related.function_code' conversion_constant 'related by a known conversion factor' '_item_related.function_code' conversion_arbitrary 'related by a arbitrary conversion factor' '_item_related.function_code' replaces 'a replacement definition' '_item_related.function_code' replacedby 'an obsolete definition' '_item_related.function_code' associated_value 'a meaningful value when related to the item' '_item_related.function_code' associated_esd 'an estimated standard deviation of the item' '_item_related.function_code' associated_error 'an estimated error of the item' save_ # ---------------------------------------------------------------------------- save_ITEM_STRUCTURE _category.description ; This category holds the association between data items and named vector/matrix declarations. ; _category.id item_structure _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id item_structure _category_key.name '_item_structure.name' loop_ _category_group.id _category_group.category_id 'ddl_group' item_structure 'item_group' item_structure save_ save__item_structure.name _item_description.name '_item_structure.name' _item_description.description ; The name of data item ; _item.name '_item_structure.name' _item.category_id item_structure _item.mandatory_code implicit _item_type.name '_item_structure.name' _item_type.code name save_ save__item_structure.code _item_description.name '_item_structure.code' _item_description.description ; Provides an indirect reference into the list of structure type definition in category item_structure_list. ; _item.name '_item_structure.code' _item.category_id item_structure _item.mandatory_code yes _item_type.name '_item_structure.code' _item_type.code code save_ save__item_structure.organization _item_description.name '_item_structure.organization' _item_description.description ; Identifies if the struct is defined in column or row major order. Only the unique elements of symmetric matrices are specified. ; _item.name '_item_structure.organization' _item.category_id item_structure _item.mandatory_code yes _item_type.name '_item_structure.organization' _item_type.code code loop_ _item_enumeration.name _item_enumeration.value _item_enumeration.detail '_item_structure.organization' 'columnwise' 'column major order' '_item_structure.organization' 'rowwise' 'row major order' save_ # ---------------------------------------------------------------------------- save_ITEM_STRUCTURE_LIST _category.description ; This category holds a description for each structure type. ; _category.id item_structure_list _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name item_structure_list '_item_structure_list.code' item_structure_list '_item_structure_list.index' loop_ _category_group.id _category_group.category_id 'ddl_group' item_structure_list 'item_group' item_structure_list save_ save__item_structure_list.code _item_description.name '_item_structure_list.code' _item_description.description ; The name of the matrix/vector structure declaration. ; _item.name '_item_structure_list.code' _item.category_id item_structure_list _item.mandatory_code yes _item_linked.parent_name '_item_structure_list.code' _item_linked.child_name '_item_structure.code' _item_type.name '_item_structure_list.code' _item_type.code code save_ save__item_structure_list.index _item_description.name '_item_structure_list.index' _item_description.description ; Identifies the one based index of a row/column of the structure. ; _item.name '_item_structure_list.index' _item.category_id item_structure_list _item.mandatory_code yes loop_ _item_range.name _item_range.minimum _item_range.maximum '_item_structure_list.index' 1 1 '_item_structure_list.index' 1 . _item_type.name '_item_structure_list.index' _item_type.code int save_ save__item_structure_list.dimension _item_description.name '_item_structure_list.dimension' _item_description.description ; Identifies the length of this row/column of the structure. ; _item.name '_item_structure_list.dimension' _item.category_id item_structure_list _item.mandatory_code yes loop_ _item_range.name _item_range.minimum _item_range.maximum '_item_structure_list.dimension' 1 1 '_item_structure_list.dimension' 1 . _item_type.name '_item_structure_list.dimension' _item_type.code int save_ # ---------------------------------------------------------------------------- save_ITEM_SUB_CATEGORY _category.description ; This category assigns data items to subcategories. ; _category.id item_sub_category _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name item_sub_category '_item_sub_category.id' item_sub_category '_item_sub_category.name' loop_ _category_group.id _category_group.category_id 'sub_category_group' item_sub_category 'item_group' item_sub_category save_ save__item_sub_category.name _item_description.name '_item_sub_category.name' _item_description.description ; The name of data item ; _item.name '_item_sub_category.name' _item.category_id item_sub_category _item.mandatory_code implicit _item_type.name '_item_sub_category.name' _item_type.code name save_ save__item_sub_category.id _item_description.name '_item_sub_category.id' _item_description.description ; The identifier of subcategory ; _item.name '_item_sub_category.id' _item.category_id item_sub_category _item.mandatory_code yes _item_type.name '_item_sub_category.id' _item_type.code idname save_ # ---------------------------------------------------------------------------- save_ITEM_TYPE _category.description ; Attributes for specifying the data type code for each data item. ; _category.id item_type _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id item_type _category_key.name '_item_type.name' loop_ _category_group.id _category_group.category_id 'ddl_group' item_type 'item_group' item_type save_ save__item_type.name _item_description.name '_item_type.name' _item_description.description ; The name of data item ; _item.name '_item_type.name' _item.category_id item_type _item.mandatory_code implicit _item_type.name '_item_type.name' _item_type.code name save_ save__item_type.code _item_description.name '_item_type.code' _item_description.description ; Data type of defined data item ; _item.name '_item_type.code' _item.category_id item_type _item.mandatory_code yes _item_type.name '_item_type.code' _item_type.code code save_ # ---------------------------------------------------------------------------- save_ITEM_TYPE_CONDITIONS _category.description ; Attributes for specifying additional conditions associated with the data type of the item. ; _category.id item_type_conditions _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id item_type_conditions _category_key.name '_item_type_conditions.name' loop_ _category_group.id _category_group.category_id 'ddl_group' item_type_conditions 'item_group' item_type_conditions 'compliance_group' item_type_conditions save_ save__item_type_conditions.name _item_description.name '_item_type_conditions.name' _item_description.description ; The name of data item ; _item.name '_item_type_conditions.name' _item.category_id item_type_conditions _item.mandatory_code implicit _item_type.name '_item_type_conditions.name' _item_type.code name save_ save__item_type_conditions.code _item_description.name '_item_type_conditions.code' _item_description.description ; Codes defining conditions on the _item_type.code specification. 'esd' permits a number string to contain an appended standard deviation number enclosed within parentheses. E.g. 4.37(5) 'seq' permits data to be declared as a sequence of values separated by a comma <,> or a colon <:>. * The sequence v1,v2,v3,. signals that v1, v2, v3, etc. are alternative values or the data item. * The sequence v1:v2 signals that v1 and v2 are the boundary values of a continuous range of values. This mechanism was used to specify permitted ranges of an item in previous DDL versions. Combinations of alternate and range sequences are permitted. ; _item.name '_item_type_conditions.code' _item.category_id item_type_conditions _item.mandatory_code yes _item_type.name '_item_type_conditions.code' _item_type.code code loop_ _item_enumeration.name _item_enumeration.value _item_enumeration.detail '_item_type_conditions.code' none 'no extra conditions apply to this data item' '_item_type_conditions.code' esd 'numbers may have esd values appended within ()' '_item_type_conditions.code' seq 'data may be declared as a comma or colon separated sequence' save_ # ---------------------------------------------------------------------------- save_ITEM_TYPE_LIST _category.description ; Attributes which define each type code. ; _category.id item_type_list _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id item_type_list _category_key.name '_item_type_list.code' loop_ _category_group.id _category_group.category_id 'ddl_group' item_type_list 'item_group' item_type_list save_ save__item_type_list.code _item_description.name '_item_type_list.code' _item_description.description ; The codes specifying the nature of the data value. ; _item.name '_item_type_list.code' _item.category_id item_type_list _item.mandatory_code yes _item_type.name '_item_type_list.code' _item_type.code code _item_linked.child_name '_item_type.code' _item_linked.parent_name '_item_type_list.code' save_ save__item_type_list.primitive_code _item_description.name '_item_type_list.primitive_code' _item_description.description ; The codes specifying the primitive type of the data value. ; _item.name '_item_type_list.primitive_code' _item.category_id item_type_list _item.mandatory_code yes _item_type.name '_item_type_list.primitive_code' _item_type.code code loop_ _item_enumeration.name _item_enumeration.value _item_enumeration.detail '_item_type_list.primitive_code' numb 'numerically-interpretable string' '_item_type_list.primitive_code' char 'character or text string (case-sensitive)' '_item_type_list.primitive_code' uchar 'character or text string (case-insensitive)' '_item_type_list.primitive_code' null 'for dictionary purposes only' save_ save__item_type_list.construct _item_description.name '_item_type_list.construct' _item_description.description ; When a data value can be defined as a pre-determined sequence of characters, or optional characters, or data names (for which the definition is also available), it is specified as a construction. The rules of construction conform to the the regular expression (REGEX) specificatiopns detailed in the IEEE document P1003.2 Draft 11.2 Sept 1991 (ftp file '/doc/POSIX/1003.2/p121-140'). Resolved data names for which _item_type_list.construct specifications exist are replaced by these constructions, otherwise the data name string is not replaced. ; _item.name '_item_type_list.construct' _item.category_id item_type_list _item.mandatory_code no _item_type.name '_item_type_list.construct' _item_type.code text _item_examples.name '_item_type_list.construct' _item_examples.case '{_year}-{_month}-{_day}' _item_examples.detail 'typical construction for _date' save_ save__item_type_list.detail _item_description.name '_item_type_list.detail' _item_description.description ; An optional description of the data type ; _item.name '_item_type_list.detail' _item.category_id item_type_list _item.mandatory_code no _item_type.name '_item_type_list.detail' _item_type.code text save_ # ---------------------------------------------------------------------------- save_ITEM_UNITS _category.description ; Specifies the physical units in which data items are expressed. ; _category.id item_units _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id item_units _category_key.name '_item_units.name' loop_ _category_group.id _category_group.category_id 'ddl_group' item_units 'item_group' item_units save_ save__item_units.name _item_description.name '_item_units.name' _item_description.description ; The name of data item ; _item.name '_item_units.name' _item.category_id item_units _item.mandatory_code implicit _item_type.name '_item_units.name' _item_type.code name save_ save__item_units.code _item_description.name '_item_units.code' _item_description.description ; The identifier of unit in which the data item is expressed. ; _item.name '_item_units.code' _item.category_id item_units _item.mandatory_code yes _item_type.name '_item_units.code' _item_type.code code save_ # ---------------------------------------------------------------------------- save_ITEM_UNITS_CONVERSION _category.description ; Conversion factors between the various units of measure defined in the ITEM_UNITS_LIST category. ; _category.id item_units_conversion _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name item_units_conversion '_item_units_conversion.from_code' item_units_conversion '_item_units_conversion.to_code' loop_ _category_group.id _category_group.category_id 'ddl_group' item_units_conversion 'item_group' item_units_conversion save_ save__item_units_conversion.from_code _item_description.name '_item_units_conversion.from_code' _item_description.description ; The unit system on which the conversion operation is applied to produce the unit system specified in _item_units_conversion.to_code. = ; _item.name '_item_units_conversion.from_code' _item.category_id item_units_conversion _item.mandatory_code yes _item_type.name '_item_units_conversion.from_code' _item_type.code code save_ save__item_units_conversion.to_code _item_description.name '_item_units_conversion.to_code' _item_description.description ; The unit system produced after an operation is applied to the unit system specified by _item_units_conversion.from_code. = ; _item.name '_item_units_conversion.to_code' _item.category_id item_units_conversion _item.mandatory_code yes _item_type.name '_item_units_conversion.to_code' _item_type.code code save_ save__item_units_conversion.operator _item_description.name '_item_units_conversion.operator' _item_description.description ; The arithmetic operator required to convert between the unit systems: = ; _item.name '_item_units_conversion.operator' _item.category_id item_units_conversion _item.mandatory_code yes _item_type.name '_item_units_conversion.operator' _item_type.code code loop_ _item_enumeration.name _item_enumeration.value _item_enumeration.detail '_item_units_conversion.operator' '+' 'addition' '_item_units_conversion.operator' '-' 'subtraction' '_item_units_conversion.operator' '*' 'multiplication' '_item_units_conversion.operator' '/' 'division' save_ save__item_units_conversion.factor _item_description.name '_item_units_conversion.factor' _item_description.description ; The arithmetic operation required to convert between the unit systems: = ; _item.name '_item_units_conversion.factor' _item.category_id item_units_conversion _item.mandatory_code yes _item_type.name '_item_units_conversion.factor' _item_type.code any save_ # ---------------------------------------------------------------------------- save_ITEM_UNITS_LIST _category.description ; Attributes which describe the physical units of measure in which data items may be expressed. ; _category.id item_units_list _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id item_units_list _category_key.name '_item_units_list.code' loop_ _category_group.id _category_group.category_id 'ddl_group' item_units_list 'item_group' item_units_list save_ save__item_units_list.code _item_description.name '_item_units_list.code' _item_description.description ; The code specifying the name of the unit of measure. ; _item.name '_item_units_list.code' _item.category_id item_units_list _item.mandatory_code yes _item_type.name '_item_units_list.code' _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_item_units.code' '_item_units_list.code' '_item_units_conversion.from_code' '_item_units_list.code' '_item_units_conversion.to_code' '_item_units_list.code' save_ save__item_units_list.detail _item_description.name '_item_units_list.detail' _item_description.description ; A description of the unit of measure. ; _item.name '_item_units_list.detail' _item.category_id item_units_list _item.mandatory_code no _item_type.name '_item_units_list.detail' _item_type.code text save_ # ---------------------------------------------------------------------------- save_METHOD_LIST _category.description ; Attributes specifying the list of methods applicable to data items, sub-categories, and categories. ; _category.id method_list _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id method_list _category_key.name '_method_list.id' loop_ _category_group.id _category_group.category_id 'ddl_group' method_list 'item_group' method_list 'category_group' method_list save_ save__method_list.id _item_description.name '_method_list.id' _item_description.description ; Identity of method in the list referenced by _method.id ; _item.name '_method_list.id' _item.category_id method_list _item.mandatory_code yes _item_type.name '_method_list.id' _item_type.code idname loop_ _item_linked.child_name _item_linked.parent_name '_item_methods.method_id' '_method_list.id' '_category_methods.method_id' '_method_list.id' '_sub_category_methods.method_id' '_method_list.id' '_datablock_methods.method_id' '_method_list.id' save_ save__method_list.detail _item_description.name '_method_list.detail' _item_description.description ; Description of application method in _method_list.id ; _item.name '_method_list.detail' _item.category_id method_list _item.mandatory_code no _item_type.name '_method_list.detail' _item_type.code text save_ save__method_list.inline _item_description.name '_method_list.inline' _item_description.description ; Inline text of a method associated with the data item. ; _item.name '_method_list.inline' _item.category_id method_list _item.mandatory_code yes _item_type.name '_method_list.inline' _item_type.code text save_ save__method_list.code _item_description.name '_method_list.code' _item_description.description ; A code that describes the function of the method. ; _item.name '_method_list.code' _item.category_id method_list _item.mandatory_code yes _item_type.name '_method_list.code' _item_type.code code loop_ _item_examples.name _item_examples.case _item_examples.detail '_method_list.code' calculation 'method to calculate the item ' '_method_list.code' verification 'method to verify the data item ' '_method_list.code' cast 'method to provide cast conversion ' '_method_list.code' addition 'method to define item + item ' '_method_list.code' division 'method to define item / item ' '_method_list.code' multiplication 'method to define item * item ' '_method_list.code' equivalence 'method to define item = item ' '_method_list.code' other 'miscellaneous method ' save_ save__method_list.language _item_description.name '_method_list.language' _item_description.description ; Language in which the method is expressed. ; _item.name '_method_list.language' _item.category_id method_list _item.mandatory_code yes _item_type.name '_method_list.language' _item_type.code code loop_ _item_examples.name _item_examples.case _item_examples.detail '_method_list.language' BNF ? '_method_list.language' C ? '_method_list.language' C++ ? '_method_list.language' FORTRAN ? '_method_list.language' LISP ? '_method_list.language' PASCAL ? '_method_list.language' PEARL ? '_method_list.language' TCL ? '_method_list.language' OTHER ? save_ # ---------------------------------------------------------------------------- save_DICTIONARY _category.description ; Attributes for specifying the dictionary title, version and data block identifier. ; _category.id dictionary _category.mandatory_code yes _category.implicit_key mmcif_ddl.dic _category_key.id dictionary _category_key.name '_dictionary.datablock_id' loop_ _category_group.id _category_group.category_id 'ddl_group' dictionary 'datablock_group' dictionary 'dictionary_group' dictionary save_ save__dictionary.datablock_id _item_description.name '_dictionary.datablock_id' _item_description.description ; The identifier for the data block containing the dictionary. ; _item.name '_dictionary.datablock_id' _item.category_id dictionary _item.mandatory_code implicit _item_type.name '_dictionary.datablock_id' _item_type.code code save_ save__dictionary.title _item_description.name '_dictionary.title' _item_description.description ; Title identification of the dictionary. ; _item.name '_dictionary.title' _item.category_id dictionary _item.mandatory_code yes _item_type.name '_dictionary.title' _item_type.code char save_ save__dictionary.version _item_description.name '_dictionary.version' _item_description.description ; A unique version identifier for the dictionary. ; _item.name '_dictionary.version' _item.category_id dictionary _item.mandatory_code yes _item_type.name '_dictionary.version' _item_type.code char save_ # ---------------------------------------------------------------------------- save_DICTIONARY_HISTORY _category.description ; Attributes for specifying the revision history of the dictionary. ; _category.id dictionary_history _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id dictionary_history _category_key.name '_dictionary_history.version' loop_ _category_group.id _category_group.category_id 'ddl_group' dictionary_history 'dictionary_group' dictionary_history save_ save__dictionary_history.version _item_description.name '_dictionary_history.version' _item_description.description ; A unique version identifier for the dictionary revision. ; _item.name '_dictionary_history.version' _item.category_id dictionary_history _item.mandatory_code yes _item_type.name '_dictionary_history.version' _item_type.code char _item_linked.child_name '_dictionary.version' _item_linked.parent_name '_dictionary_history.version' save_ save__dictionary_history.update _item_description.name '_dictionary_history.update' _item_description.description ; The date that the last dictionary revision took place. ; _item.name '_dictionary_history.update' _item.category_id dictionary_history _item.mandatory_code yes _item_type.name '_dictionary_history.update' _item_type.code yyyy-mm-dd save_ save__dictionary_history.revision _item_description.name '_dictionary_history.revision' _item_description.description ; Text description of the dictionary revision. ; _item.name '_dictionary_history.revision' _item.category_id dictionary_history _item.mandatory_code yes _item_type.name '_dictionary_history.revision' _item_type.code text save_ ### EOF mmcif_ddl-def-1.dic ########################################################################### # # File: mmcif_ddl-def-1.dic # # mmCIF DDL Core Dictionary with NDB extensions # # This DDL dictionary is a mirror of ddl_core.dic-org with all implicit # data items fully expanded and with NDB extensions added. # # Definition Section 2. # (NDB Extension Definitions) # # ########################################################################### save_NDB_CATEGORY_DESCRIPTION _category.description ; NDB description of data items in this category. ; _category.id ndb_category_description _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name ndb_category_description '_ndb_category_description.id' ndb_category_description '_ndb_category_description.description' save_ save__ndb_category_description.id _item.name '_ndb_category_description.id' _item.category_id ndb_category_description _item.mandatory_code implicit _item_type.name '_ndb_category_description.id' _item_type.code idname _item_linked.child_name '_ndb_category_description.id' _item_linked.parent_name '_category.id' save_ save__ndb_category_description.description _item_description.name '_ndb_category_description.description' _item_description.description ; NDB text description of a category. ; _item.name '_ndb_category_description.description' _item.category_id ndb_category_description _item.mandatory_code yes _item_type.name '_ndb_category_description.description' _item_type.code text save_ # -------------------------------------------------------------------------- save_NDB_CATEGORY_EXAMPLES _category.description ; NDB example applications and descriptions of data items in this category. ; _category.id ndb_category_examples _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name ndb_category_examples '_ndb_category_examples.id' ndb_category_examples '_ndb_category_examples.case' save_ save__ndb_category_examples.id _item.name '_ndb_category_examples.id' _item.category_id ndb_category_examples _item.mandatory_code implicit _item_type.name '_ndb_category_examples.id' _item_type.code idname _item_linked.child_name '_ndb_category_examples.id' _item_linked.parent_name '_category.id' save_ save__ndb_category_examples.case _item_description.name '_ndb_category_examples.case' _item_description.description ; NDB case of examples involving items in this category. ; _item.name '_ndb_category_examples.case' _item.category_id ndb_category_examples _item.mandatory_code yes _item_type.name '_ndb_category_examples.case' _item_type.code text save_ save__ndb_category_examples.detail _item_description.name '_ndb_category_examples.detail' _item_description.description ; NDB description of an example _category_examples.case ; _item.name '_ndb_category_examples.detail' _item.category_id ndb_category_examples _item.mandatory_code no _item_type.name '_ndb_category_examples.detail' _item_type.code text save_ #-------------------------------------------------------------------------- save_NDB_ITEM_DESCRIPTION _category.description ; This category holds the NDB descriptions of each data item. ; _category.id ndb_item_description _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name ndb_item_description '_ndb_item_description.name' ndb_item_description '_ndb_item_description.description' loop_ _category_group.id _category_group.category_id 'ddl_group' ndb_item_description 'item_group' ndb_item_description save_ save__ndb_item_description.name _item_description.name '_ndb_item_description.name' _item_description.description ; Data name of the defined item. ; _item.name '_ndb_item_description.name' _item.category_id ndb_item_description _item.mandatory_code implicit _item_type.name '_ndb_item_description.name' _item_type.code name _item_linked.child_name '_ndb_item_description.name' _item_linked.parent_name '_item.name' save_ save__ndb_item_description.description _item_description.name '_ndb_item_description.description' _item_description.description ; NDB text description of the defined data item. ; _item.name '_ndb_item_description.description' _item.category_id ndb_item_description _item.mandatory_code yes _item_type.name '_ndb_item_description.description' _item_type.code text save_ # -------------------------------------------------------------------------- save_NDB_ITEM_ENUMERATION _category.description ; Attributes which specify the permitted enumeration of the items. ; _category.id ndb_item_enumeration _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name ndb_item_enumeration '_ndb_item_enumeration.name' ndb_item_enumeration '_ndb_item_enumeration.value' loop_ _category_group.category_id _category_group.id ndb_item_enumeration 'ddl_group' ndb_item_enumeration 'item_group' save_ save__ndb_item_enumeration.name _item.name '_ndb_item_enumeration.name' _item.category_id ndb_item_enumeration _item.mandatory_code implicit _item_type.name '_ndb_item_enumeration.name' _item_type.code name _item_linked.child_name '_ndb_item_enumeration.name' _item_linked.parent_name '_item.name' save_ save__ndb_item_enumeration.value _item_description.name '_ndb_item_enumeration.value' _item_description.description ; A permissible value, character or number, for the defined item. ; _item.name '_ndb_item_enumeration.value' _item.category_id ndb_item_enumeration _item.mandatory_code yes _item_type.name '_ndb_item_enumeration.value' _item_type.code any save_ save__ndb_item_enumeration.detail _item_description.name '_ndb_item_enumeration.detail' _item_description.description ; A description of a permissible value for the defined item. ; _item.name '_ndb_item_enumeration.detail' _item.category_id ndb_item_enumeration _item.mandatory_code no _item_type.name '_ndb_item_enumeration.detail' _item_type.code text save_ # -------------------------------------------------------------------------- save_NDB_ITEM_EXAMPLES _category.description ; Attributes for describing application examples of the data item. ; _category.id ndb_item_examples _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name ndb_item_examples '_ndb_item_examples.name' ndb_item_examples '_ndb_item_examples.case' loop_ _category_group.id _category_group.category_id 'ddl_group' ndb_item_examples 'item_group' ndb_item_examples save_ save__ndb_item_examples.case _item_description.name '_ndb_item_examples.case' _item_description.description ; NDB example application of the defined data item. ; _item.name '_ndb_item_examples.case' _item.category_id ndb_item_examples _item.mandatory_code yes _item_type.name '_ndb_item_examples.case' _item_type.code text save_ save__ndb_item_examples.detail _item_description.name '_ndb_item_examples.detail' _item_description.description ; NDB description of an example specified in _ndb_item_example.case ; _item.name '_ndb_item_examples.detail' _item.category_id ndb_item_examples _item.mandatory_code yes _item_type.name '_ndb_item_examples.detail' _item_type.code text save_ save__ndb_item_examples.name _item.name '_ndb_item_examples.name' _item.category_id ndb_item_examples _item.mandatory_code implicit _item_type.name '_ndb_item_examples.name' _item_type.code name _item_linked.child_name '_ndb_item_examples.name' _item_linked.parent_name '_item.name' save_ #### EOF mmcif_ddl-def-2.dic ./CBFlib-0.9.2.2/doc/Idiffrn_radiation.xray_symbol.html0000644000076500007650000000644111603702115021220 0ustar yayayaya (IUCr) CIF Definition save__diffrn_radiation.xray_symbol

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_radiation.xray_symbol

Name:
'_diffrn_radiation.xray_symbol'

Definition:

        The IUPAC symbol for the X-ray wavelength for the probe
               radiation.

Type: line

Mandatory item: no

Alias:
_diffrn_radiation_xray_symbol (cif_core.dic version 2.0.1)
The data value must be one of the following:


K-L~3~
K\a~1~ in older Siegbahn notation

K-L~2~
K\a~2~ in older Siegbahn notation

K-M~3~
K\b~1~ in older Siegbahn notation

K-L~2,3~
use where K-L~3~ and K-L~2~ are not resolved

Category: diffrn_radiation

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_detector_element.reference_center_units.html0000644000076500007650000001050611603702115024735 0ustar yayayaya (IUCr) CIF Definition save__diffrn_detector_element.reference_center_units

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_detector_element.reference_center_units

Name:
'_diffrn_detector_element.reference_center_units'

Definition:

       The value of _diffrn_detector_element.reference_center_units
              specifies the units in which the values of
              '_diffrn_detector_element.reference_center_fast' and
              '_diffrn_detector_element.reference_center_slow'
              are presented.  The default is 'mm' for millimetres.  The
              alternatives are 'pixels' and 'bins'.  In all cases the
              center distances are measured from the center of the
              first pixel, i.e. in a 2x2 binning, the measuring origin
              is offset from the centers of the bins by one half pixel
              towards the first pixel.

              If 'bins' is specified, the data in
                  '_array_intensities.pixel_fast_bin_size',
                  '_array_intensities.pixel_slow_bin_size', and
                  '_array_intensities.pixel_binning_method'
              is used to define the binning scheme.



Type: code

Mandatory item: no


The data value must be one of the following:


mm
millimetres

pixels
detector pixels

bins
detector bins

Category: diffrn_detector_element

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/cif_img_1.5.3_8Jul07.dic0000644000076500007650000074665211603702115016242 0ustar yayayaya############################################################################## # # # Image CIF Dictionary (imgCIF) # # and Crystallographic Binary File Dictionary (CBF) # # Extending the Macromolecular CIF Dictionary (mmCIF) # # # # Version 1.5.3 # # of 2007-07-08 # # ################################################################### # # # *** WARNING *** THIS IS A DRAFT FOR DISCUSSSION *** WARNING *** # # # # SUBJECT TO CHANGE WITHOUT NOTICE # # # # SEND COMMENTS TO imgcif-l@iucr.org CITING THE VERSION # # # ################################################################### # # This draft edited by H. J. Bernstein # # # # by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook # # # # This dictionary was adapted from format discussed at the imgCIF Workshop, # # held at BNL Oct 1997 and the Crystallographic Binary File Format Draft # # Proposal by Andrew Hammersley. The first DDL 2.1 Version was created by # # John Westbrook. This version was drafted by Herbert J. Bernstein and # # incorporates comments by I. David Brown, John Westbrook, Brian McMahon, # # Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li, Gotzon Madariaga, # # Frances C. Bernstein, Chris Nielsen, Nicola Ashcroft and others. # ############################################################################## data_cif_img.dic _dictionary.title cif_img.dic _dictionary.version 1.5.3 _dictionary.datablock_id cif_img.dic ############################################################################## # CONTENTS # # CATEGORY_GROUP_LIST # SUB_CATEGORY # # category ARRAY_DATA # # _array_data.array_id # _array_data.binary_id # _array_data.data # _array_data.header_contents # _array_data.header_convention # # category ARRAY_ELEMENT_SIZE # # _array_element_size.array_id # _array_element_size.index # _array_element_size.size # # category ARRAY_INTENSITIES # # _array_intensities.array_id # _array_intensities.binary_id # _array_intensities.gain # _array_intensities.gain_esd # _array_intensities.linearity # _array_intensities.offset # _array_intensities.scaling # _array_intensities.overload # _array_intensities.undefined_value # _array_intensities.pixel_fast_bin_size # _array_intensities.pixel_slow_bin_size # _array_intensities.pixel_binning_method # # category ARRAY_STRUCTURE # # _array_structure.byte_order # _array_structure.compression_type # _array_structure.compression_type_flag # _array_structure.encoding_type # _array_structure.id # # category ARRAY_STRUCTURE_LIST # # _array_structure_list.axis_set_id # _array_structure_list.array_id # _array_structure_list.dimension # _array_structure_list.direction # _array_structure_list.index # _array_structure_list.precedence # # category ARRAY_STRUCTURE_LIST_AXIS # # _array_structure_list_axis.axis_id # _array_structure_list_axis.axis_set_id # _array_structure_list_axis.angle # _array_structure_list_axis.angle_increment # _array_structure_list_axis.displacement # _array_structure_list_axis.fract_displacement # _array_structure_list_axis.displacement_increment # _array_structure_list_axis.fract_displacement_increment # _array_structure_list_axis.angular_pitch # _array_structure_list_axis.radial_pitch # _array_structure_list_axis.reference_angle # _array_structure_list_axis.reference_displacement # # category AXIS # # _axis.depends_on # _axis.equipment # _axis.id # _axis.offset[1] # _axis.offset[2] # _axis.offset[3] # _axis.type # _axis.system # _axis.vector[1] # _axis.vector[2] # _axis.vector[3] # # category DIFFRN_DATA_FRAME # # _diffrn_data_frame.array_id # _diffrn_data_frame.binary_id # _diffrn_data_frame.center_fast # _diffrn_data_frame.center_slow # _diffrn_data_frame.center_units # _diffrn_data_frame.detector_element_id # _diffrn_data_frame.id # _diffrn_data_frame.details # # category DIFFRN_DETECTOR # # _diffrn_detector.details # _diffrn_detector.detector # _diffrn_detector.diffrn_id # _diffrn_detector.dtime # _diffrn_detector.id # _diffrn_detector.number_of_axes # _diffrn_detector.type # # category DIFFRN_DETECTOR_AXIS # # _diffrn_detector_axis.axis_id # _diffrn_detector_axis.detector_id # # category DIFFRN_DETECTOR_ELEMENT # # _diffrn_detector_element.id # _diffrn_detector_element.detector_id # _diffrn_detector_element.reference_center_fast # _diffrn_detector_element.reference_center_slow # _diffrn_detector_element.reference_center_units # # category DIFFRN_MEASUREMENT # # _diffrn_measurement.diffrn_id # _diffrn_measurement.details # _diffrn_measurement.device # _diffrn_measurement.device_details # _diffrn_measurement.device_type # _diffrn_measurement.id # _diffrn_measurement.method # _diffrn_measurement.number_of_axes # _diffrn_measurement.sample_detector_distance # _diffrn_measurement.sample_detector_voffset # _diffrn_measurement.specimen_support # # category DIFFRN_MEASUREMENT_AXIS # # _diffrn_measurement_axis.axis_id # _diffrn_measurement_axis.measurement_device # _diffrn_measurement_axis.measurement_id # # category DIFFRN_RADIATION # # _diffrn_radiation.collimation # _diffrn_radiation.diffrn_id # _diffrn_radiation.div_x_source # _diffrn_radiation.div_y_source # _diffrn_radiation.div_x_y_source # _diffrn_radiation.filter_edge' # _diffrn_radiation.inhomogeneity # _diffrn_radiation.monochromator # _diffrn_radiation.polarisn_norm # _diffrn_radiation.polarisn_ratio # _diffrn_radiation.polarizn_source_norm # _diffrn_radiation.polarizn_source_ratio # _diffrn_radiation.probe # _diffrn_radiation.type # _diffrn_radiation.xray_symbol # _diffrn_radiation.wavelength_id # # category DIFFRN_REFLN # # _diffrn_refln.frame_id # # category DIFFRN_SCAN # # _diffrn_scan.id # _diffrn_scan.date_end # _diffrn_scan.date_start # _diffrn_scan.integration_time # _diffrn_scan.frame_id_start # _diffrn_scan.frame_id_end # _diffrn_scan.frames # # category DIFFRN_SCAN_AXIS # # _diffrn_scan_axis.axis_id # _diffrn_scan_axis.angle_start # _diffrn_scan_axis.angle_range # _diffrn_scan_axis.angle_increment # _diffrn_scan_axis.angle_rstrt_incr # _diffrn_scan_axis.displacement_start # _diffrn_scan_axis.displacement_range # _diffrn_scan_axis.displacement_increment # _diffrn_scan_axis.displacement_rstrt_incr # _diffrn_scan_axis.reference_angle # _diffrn_scan_axis.reference_displacement # _diffrn_scan_axis.scan_id # # category DIFFRN_SCAN_FRAME # # _diffrn_scan_frame.date # _diffrn_scan_frame.frame_id # _diffrn_scan_frame.frame_number # _diffrn_scan_frame.integration_time # _diffrn_scan_frame.scan_id # # category DIFFRN_SCAN_FRAME_AXIS # # _diffrn_scan_frame_axis.axis_id # _diffrn_scan_frame_axis.angle # _diffrn_scan_frame_axis.angle_increment # _diffrn_scan_frame_axis.angle_rstrt_incr # _diffrn_scan_frame_axis.displacement # _diffrn_scan_frame_axis.displacement_increment # _diffrn_scan_frame_axis.displacement_rstrt_incr # _diffrn_scan_frame_axis.reference_angle # _diffrn_scan_frame_axis.reference_displacement # _diffrn_scan_frame_axis.frame_id # # categor MAP # # _map.details # _map.diffrn_id # _map.entry_id # _map.id # # categor MAP_SEGMENT # # _map_segment.array_id # _map_segment.binary_id # _map_segment.mask_array_id # _map_segment.mask_binary_id # _map_segment.id # _map_segment.map_id # _map_segment.details # # ***DEPRECATED*** data items # # _diffrn_detector_axis.id # _diffrn_detector_element.center[1] # _diffrn_detector_element.center[2] # _diffrn_measurement_axis.id # # ***DEPRECATED*** category DIFFRN_FRAME_DATA # # _diffrn_frame_data.array_id # _diffrn_frame_data.binary_id # _diffrn_frame_data.detector_element_id # _diffrn_frame_data.id # _diffrn_frame_data.details # # # ITEM_TYPE_LIST # ITEM_UNITS_LIST # DICTIONARY_HISTORY # ############################################################################## ######################### ## CATEGORY_GROUP_LIST ## ######################### loop_ _category_group_list.id _category_group_list.parent_id _category_group_list.description 'inclusive_group' . ; Categories that belong to the dictionary extension. ; 'array_data_group' 'inclusive_group' ; Categories that describe array data. ; 'axis_group' 'inclusive_group' ; Categories that describe axes. ; 'diffrn_group' 'inclusive_group' ; Categories that describe details of the diffraction experiment. ; ################## ## SUB_CATEGORY ## ################## loop_ _sub_category.id _sub_category.description 'matrix' ; The collection of elements of a matrix. ; 'vector' ; The collection of elements of a vector. ; ############## # ARRAY_DATA # ############## save_ARRAY_DATA _category.description ; Data items in the ARRAY_DATA category are the containers for the array data items described in the category ARRAY_STRUCTURE. It is recognized that the data in this category needs to be used in two distinct ways. During a data collection the lack of ancillary data and timing constraints in processing data may dictate the need to make a 'miniCBF' nothing more than an essential minimum of information to record the results of the data collection. In that case it is proper to use the ARRAY_DATA category as a container for just a single image and a compacted, beam-line dependent list of data collection parameter values. In such a case, only the tags '_array_data.header_convention', '_array_data.header_contents' and '_array_data.data' need be populated. For full processing and archiving, most of the tags in this dictionary will need to be populated. ; _category.id array_data _category.mandatory_code no loop_ _category_key.name '_array_data.array_id' '_array_data.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows two binary data blocks. The first one was compressed by the CBF_CANONICAL compression algorithm and is presented as hexadecimal data. The first character 'H' on the data lines means hexadecimal. It could have been 'O' for octal or 'D' for decimal. The second character on the line shows the number of bytes in each word (in this case '4'), which then requires eight hexadecimal digits per word. The third character gives the order of octets within a word, in this case '<' for the ordering 4321 (i.e. 'big-endian'). Alternatively, the character '>' could have been used for the ordering 1234 (i.e. 'little-endian'). The block has a 'message digest' to check the integrity of the data. The second block is similar, but uses CBF_PACKED compression and BASE64 encoding. Note that the size and the digest are different. ; ; loop_ _array_data.array_id _array_data.binary_id _array_data.data image_1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF_CANONICAL" Content-Transfer-Encoding: X-BASE16 X-Binary-Size: 3927126 X-Binary-ID: 1 Content-MD5: u2sTJEovAHkmkDjPi+gWsg== # Hexadecimal encoding, byte 0, byte order ...21 # H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ... .... --CIF-BINARY-FORMAT-SECTION---- ; image_2 2 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF-PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3745758 X-Binary-ID: 2 Content-MD5: 1zsJjWPfol2GYl2V+QSXrw== ELhQAAAAAAAA... ... --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - This example shows a single image in a miniCBF, provided by E. Eikenberry. The entire CBF consists of one data block containing one category and three tags. The CBFlib program convert_miniCBF and a suitable template file can be used to convert this miniCBF to a full imgCIF file. ; ; ###CBF: VERSION 1.5 # CBF file written by CBFlib v0.7.8 data_insulin_pilatus6m _array_data.header_convention SLS_1.0 _array_data.header_contents ; # Detector: PILATUS 6M SN: 60-0001 # 2007/Jun/17 15:12:36.928 # Pixel_size 172e-6 m x 172e-6 m # Silicon sensor, thickness 0.000320 m # Exposure_time 0.995000 s # Exposure_period 1.000000 s # Tau = 194.0e-09 s # Count_cutoff 1048575 counts # Threshold_setting 5000 eV # Wavelength 1.2398 A # Energy_range (0, 0) eV # Detector_distance 0.15500 m # Detector_Voffset -0.01003 m # Beam_xy (1231.00, 1277.00) pixels # Flux 22487563295 ph/s # Filter_transmission 0.0008 # Start_angle 13.0000 deg. # Angle_increment 1.0000 deg. # Detector_2theta 0.0000 deg. # Polarization 0.990 # Alpha 0.0000 deg. # Kappa 0.0000 deg. # Phi 0.0000 deg. # Chi 0.0000 deg. # Oscillation_axis X, CW # N_oscillations 1 ; _array_data.data ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_BYTE_OFFSET" Content-Transfer-Encoding: BINARY X-Binary-Size: 6247567 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" X-Binary-Element-Byte-Order: LITTLE_ENDIAN Content-MD5: 8wO6i2+899lf5iO8QPdgrw== X-Binary-Number-of-Elements: 6224001 X-Binary-Size-Fastest-Dimension: 2463 X-Binary-Size-Second-Dimension: 2527 X-Binary-Size-Padding: 4095 ... --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_data.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. If not given, it defaults to 1. ; _item.name '_array_data.array_id' _item.category_id array_data _item.mandatory_code implicit _item_type.code code save_ save__array_data.binary_id _item_description.description ; This item is an integer identifier which, along with _array_data.array_id, should uniquely identify the particular block of array data. If _array_data.binary_id is not explicitly given, it defaults to 1. The value of _array_data.binary_id distinguishes among multiple sets of data with the same array structure. If the MIME header of the data array specifies a value for X-Binary-ID, the value of _array_data.binary_id should be equal to the value given for X-Binary-ID. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_data.binary_id' array_data implicit '_diffrn_data_frame.binary_id' diffrn_data_frame implicit '_array_intensities.binary_id' array_intensities implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.binary_id' '_array_data.binary_id' '_array_intensities.binary_id' '_array_data.binary_id' _item_default.value 1 _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_data.data _item_description.description ; The value of _array_data.data contains the array data encapsulated in a STAR string. The representation used is a variant on the Multipurpose Internet Mail Extensions (MIME) specified in RFC 2045-2049 by N. Freed et al. The boundary delimiter used in writing an imgCIF or CBF is '\n--CIF-BINARY-FORMAT-SECTION--' (including the required initial '\n--'). The Content-Type may be any of the discrete types permitted in RFC 2045; 'application/octet-stream' is recommended for diffraction images in the ARRAY_DATA category. Note: When appropriate in other categories, e.g. for photographs of crystals, more precise types, such as 'image/jpeg', 'image/tiff', 'image/png', etc. should be used. If an octet stream was compressed, the compression should be specified by the parameter 'conversions="X-CBF_PACKED"' or the parameter 'conversions="X-CBF_CANONICAL"' or the parameter 'conversions="X-CBF_BYTE_OFFSET"' If the parameter 'conversions="X-CBF_PACKED"' is given it may be further modified with the parameters '"uncorrelated_sections"' or '"flat"' If the '"uncorrelated_sections"' parameter is given, each section will be compressed without using the prior section for averaging. If the '"flat"' parameter is given, each the image will be treated as one long row. The Content-Transfer-Encoding may be 'BASE64', 'Quoted-Printable', 'X-BASE8', 'X-BASE10', 'X-BASE16' or 'X-BASE32K', for an imgCIF or 'BINARY' for a CBF. The octal, decimal and hexadecimal transfer encodings are provided for convenience in debugging and are not recommended for archiving and data interchange. In a CIF, one of the parameters 'charset=us-ascii', 'charset=utf-8' or 'charset=utf-16' may be used on the Content-Transfer-Encoding to specify the character set used for the external presentation of the encoded data. If no charset parameter is given, the character set of the enclosing CIF is assumed. In any case, if a BOM flag is detected (FE FF for big-endian UTF-16, FF FE for little-endian UTF-16 or EF BB BF for UTF-8) is detected, the indicated charset will be assumed until the end of the encoded data or the detection of a different BOM. The charset of the Content-Transfer-Encoding is not the character set of the encoded data, only the character set of the presentation of the encoded data and should be respecified for each distinct STAR string. In an imgCIF file, the encoded binary data begins after the empty line terminating the header. In an imgCIF file, the encoded binary data ends with the terminating boundary delimiter '\n--CIF-BINARY-FORMAT-SECTION----' in the currently effective charset or with the '\n; ' that terminates the STAR string. In a CBF, the raw binary data begins after an empty line terminating the header and after the sequence: Octet Hex Decimal Purpose 0 0C 12 (ctrl-L) Page break 1 1A 26 (ctrl-Z) Stop listings in MS-DOS 2 04 04 (Ctrl-D) Stop listings in UNIX 3 D5 213 Binary section begins None of these octets are included in the calculation of the message size or in the calculation of the message digest. The X-Binary-Size header specifies the size of the equivalent binary data in octets. If compression was used, this size is the size after compression, including any book-keeping fields. An adjustment is made for the deprecated binary formats in which eight bytes of binary header are used for the compression type. In this case, the eight bytes used for the compression type are subtracted from the size, so that the same size will be reported if the compression type is supplied in the MIME header. Use of the MIME header is the recommended way to supply the compression type. In general, no portion of the binary header is included in the calculation of the size. The X-Binary-Element-Type header specifies the type of binary data in the octets, using the same descriptive phrases as in _array_structure.encoding_type. The default value is 'unsigned 32-bit integer'. An MD5 message digest may, optionally, be used. The 'RSA Data Security, Inc. MD5 Message-Digest Algorithm' should be used. No portion of the header is included in the calculation of the message digest. If the Transfer Encoding is 'X-BASE8', 'X-BASE10' or 'X-BASE16', the data are presented as octal, decimal or hexadecimal data organized into lines or words. Each word is created by composing octets of data in fixed groups of 2, 3, 4, 6 or 8 octets, either in the order ...4321 ('big- endian') or 1234... ('little-endian'). If there are fewer than the specified number of octets to fill the last word, then the missing octets are presented as '==' for each missing octet. Exactly two equal signs are used for each missing octet even for octal and decimal encoding. The format of lines is: rnd xxxxxx xxxxxx xxxxxx where r is 'H', 'O' or 'D' for hexadecimal, octal or decimal, n is the number of octets per word and d is '<' or '>' for the '...4321' and '1234...' octet orderings, respectively. The '==' padding for the last word should be on the appropriate side to correspond to the missing octets, e.g. H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000 or H3> FF0700 00==== For these hexadecimal, octal and decimal formats only, comments beginning with '#' are permitted to improve readability. BASE64 encoding follows MIME conventions. Octets are in groups of three: c1, c2, c3. The resulting 24 bits are broken into four six-bit quantities, starting with the high-order six bits (c1 >> 2) of the first octet, then the low-order two bits of the first octet followed by the high-order four bits of the second octet [(c1 & 3)<<4 | (c2>>4)], then the bottom four bits of the second octet followed by the high-order two bits of the last octet [(c2 & 15)<<2 | (c3>>6)], then the bottom six bits of the last octet (c3 & 63). Each of these four quantities is translated into an ASCII character using the mapping: 1 2 3 4 5 6 0123456789012345678901234567890123456789012345678901234567890123 | | | | | | | ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/ With short groups of octets padded on the right with one '=' if c3 is missing, and with '==' if both c2 and c3 are missing. X-BASE32K encoding is similar to BASE64 encoding, except that sets of 15 octets are encoded as sets of 8 16-bit unicode characters, by breaking the 120 bits into 8 15-bit quantities. 256 is added to each 15 bit quantity to bring it into a printable uncode range. When encoding, zero padding is used to fill out the last 15 bit quantity. If 8 or more bits of padding are used, a single equals sign (hexadecimal 003D) is appended. Embedded whitespace and newlines are introduced to produce lines of no more than 80 characters each. On decoding, all printable ascii characters and ascii whitespace characters are ignored except for any trailing equals signs. The number of trailing equals signs indicated the number of trailing octets to be trimmed from the end of the decoded data. (see Georgi Darakev, Vassil Litchev, Kostadin Z. Mitev, Herbert J. Bernstein, 'Efficient Support of Binary Data in the XML Implementation of the NeXus File Format',absract W0165, ACA Summer Meeting, Honolulu, HI, July 2006). QUOTED-PRINTABLE encoding also follows MIME conventions, copying octets without translation if their ASCII values are 32...38, 42, 48...57, 59, 60, 62, 64...126 and the octet is not a ';' in column 1. All other characters are translated to =nn, where nn is the hexadecimal encoding of the octet. All lines are 'wrapped' with a terminating '=' (i.e. the MIME conventions for an implicit line terminator are never used). The "X-Binary-Element-Byte-Order" can specify either '"BIG_ENDIAN"' or '"LITTLE_ENDIAN"' byte order of the imaage data. Only LITTLE_ENDIAN is recommended. Processors may treat BIG_ENDIAN as a warning of data that can only be processed by special software. The "X-Binary-Number-of-Elements" specifies the number of elements (not the number of octets) in the decompressed, decoded image. The optional "X-Binary-Size-Fastest-Dimension" specifies the number of elements (not the number of octets) in one row of the fastest changing dimension of the binary data array. This information must be in the MIME header for proper operation of some of the decompression algorithms. The optional "X-Binary-Size-Second-Dimension" specifies the number of elements (not the number of octets) in one column of the second-fastest changing dimension of the binary data array. This information must be in the MIME header for proper operation of some of the decompression algorithms. The optional "X-Binary-Size-Third-Dimension" specifies the number of sections for the third-fastest changing dimension of the binary data array. The optional "X-Binary-Size-Padding" specifies the size in octets of an optional padding after the binary array data and before the closing flags for a binary section. ; _item.name '_array_data.data' _item.category_id array_data _item.mandatory_code yes _item_type.code binary save_ save__array_data.header_contents _item_description.description ; This item is an text field for use in minimal CBF files to carry essential header information to be kept with image data in _array_data.data when the tags that normally carry the structured metadata for the image have not been populated. Normally this data item should not appear when the full set of tags have been populated and _diffrn_data_frame.details appears. ; _item.name '_array_data.header_contents' _item.category_id array_data _item.mandatory_code no _item_type.code text save_ save__array_data.header_convention _item_description.description ; This item is an identifier for the convention followed in constructing the contents of _array_data.header_contents The permitted values are of the of an image creator identifier followed by an underscore and a version string. To avoid confusion about conventions, all creator identifiers should be registered with the IUCr and the conventions for all identifiers and versions should be posted on the MEDSBIO.org web site. ; _item.name '_array_data.header_convention' _item.category_id array_data _item.mandatory_code no _item_type.code code save_ ###################### # ARRAY_ELEMENT_SIZE # ###################### save_ARRAY_ELEMENT_SIZE _category.description ; Data items in the ARRAY_ELEMENT_SIZE category record the physical size of array elements along each array dimension. ; _category.id array_element_size _category.mandatory_code no loop_ _category_key.name '_array_element_size.array_id' '_array_element_size.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A regular 2D array with a uniform element dimension of 1220 nanometres. ; ; loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size image_1 1 1.22e-6 image_1 2 1.22e-6 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_element_size.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_element_size.array_id' _item.category_id array_element_size _item.mandatory_code implicit _item_type.code code save_ save__array_element_size.index _item_description.description ; This item is a pointer to _array_structure_list.index in the ARRAY_STRUCTURE_LIST category. ; _item.name '_array_element_size.index' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.size _item_description.description ; The size in metres of an image element in this dimension. This supposes that the elements are arranged on a regular grid. ; _item.name '_array_element_size.size' _item.category_id array_element_size _item.mandatory_code yes _item_type.code float _item_units.code 'metres' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ ##################### # ARRAY_INTENSITIES # ##################### save_ARRAY_INTENSITIES _category.description ; Data items in the ARRAY_INTENSITIES category record the information required to recover the intensity data from the set of data values stored in the ARRAY_DATA category. The detector may have a complex relationship between the raw intensity values and the number of incident photons. In most cases, the number stored in the final array will have a simple linear relationship to the actual number of incident photons, given by _array_intensities.gain. If raw, uncorrected values are presented (e.g. for calibration experiments), the value of _array_intensities.linearity will be 'raw' and _array_intensities.gain will not be used. ; _category.id array_intensities _category.mandatory_code no loop_ _category_key.name '_array_intensities.array_id' '_array_intensities.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 ; ; loop_ _array_intensities.array_id _array_intensities.linearity _array_intensities.gain _array_intensities.overload _array_intensities.undefined_value _array_intensities.pixel_fast_bin_size _array_intensities.pixel_slow_bin_size _array_intensities.pixel_binning_method image_1 linear 1.2 655535 0 2 2 hardware ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_intensities.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_intensities.array_id' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code code save_ save__array_intensities.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_array_intensities.binary_id' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code int save_ save__array_intensities.gain _item_description.description ; Detector 'gain'. The factor by which linearized intensity count values should be divided to produce true photon counts. ; _item.name '_array_intensities.gain' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain_esd' 'associated_value' save_ save__array_intensities.gain_esd _item_description.description ; The estimated standard deviation in detector 'gain'. ; _item.name '_array_intensities.gain_esd' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain' 'associated_esd' save_ save__array_intensities.linearity _item_description.description ; The intensity linearity scaling method used to convert from the raw intensity to the stored element value: 'linear' is linear. 'offset' means that the value defined by _array_intensities.offset should be added to each element value. 'scaling' means that the value defined by _array_intensities.scaling should be multiplied with each element value. 'scaling_offset' is the combination of the two previous cases, with the scale factor applied before the offset value. 'sqrt_scaled' means that the square root of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and squaring the result. 'logarithmic_scaled' means that the logarithm base 10 of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and calculating 10 to the power of this number. 'raw' means that the data are a set of raw values straight from the detector. ; _item.name '_array_intensities.linearity' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'linear' . 'offset' ; The value defined by _array_intensities.offset should be added to each element value. ; 'scaling' ; The value defined by _array_intensities.scaling should be multiplied with each element value. ; 'scaling_offset' ; The combination of the scaling and offset with the scale factor applied before the offset value. ; 'sqrt_scaled' ; The square root of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and squaring the result. ; 'logarithmic_scaled' ; The logarithm base 10 of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and calculating 10 to the power of this number. ; 'raw' ; The array consists of raw values to which no corrections have been applied. While the handling of the data is similar to that given for 'linear' data with no offset, the meaning of the data differs in that the number of incident photons is not necessarily linearly related to the number of counts reported. This value is intended for use either in calibration experiments or to allow for handling more complex data-fitting algorithms than are allowed for by this data item. ; save_ save__array_intensities.offset _item_description.description ; Offset value to add to array element values in the manner described by the item _array_intensities.linearity. ; _item.name '_array_intensities.offset' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.overload _item_description.description ; The saturation intensity level for this data array. ; _item.name '_array_intensities.overload' _item.category_id array_intensities _item.mandatory_code no _item_type.code float _item_units.code 'counts' save_ save__array_intensities.pixel_fast_bin_size _item_description.description ; The value of _array_intensities.pixel_fast_bin_size specifies the number of pixels that compose one element in the direction of the most rapidly varying array dimension. Typical values are 1, 2, 4 or 8. When there is 1 pixel per array element in both directions, the value given for _array_intensities.pixel_binning_method normally should be 'none'. It is specified as a float to allow for binning algorithms that create array elements that are not integer multiples of the detector pixel size. ; _item.name '_array_intensities.pixel_fast_bin_size' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code float _item_default.value 1. loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'pixels_per_element' save_ save__array_intensities.pixel_slow_bin_size _item_description.description ; The value of _array_intensities.pixel_slow_bin_size specifies the number of pixels that compose one element in the direction of the second most rapidly varying array dimension. Typical values are 1, 2, 4 or 8. When there is 1 pixel per array element in both directions, the value given for _array_intensities.pixel_binning_method normally should be 'none'. It is specified as a float to allow for binning algorithms that create array elements that are not integer multiples of the detector pixel size. ; _item.name '_array_intensities.pixel_slow_bin_size' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code float _item_default.value 1. loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'pixels_per_element' save_ save__array_intensities.pixel_binning_method _item_description.description ; The value of _array_intensities.pixel_binning_method specifies the method used to derive array elements from multiple pixels. ; _item.name '_array_intensities.pixel_binning_method' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'hardware' ; The element intensities were derived from the raw data of one or more pixels by used of hardware in the detector, e.g. by use of shift registers in a CCD to combine pixels into super-pixels. ; 'software' ; The element intensities were derived from the raw data of more than one pixel by use of software. ; 'combined' ; The element intensities were derived from the raw data of more than one pixel by use of both hardware and software, as when hardware binning is used in one direction and software in the other. ; 'none' ; In the both directions, the data has not been binned. The number of pixels is equal to the number of elements. When the value of _array_intensities.pixel_binning_method is 'none' the values of _array_intensities.pixel_fast_bin_size and _array_intensities.pixel_slow_bin_size both must be 1. ; 'unspecified' ; The method used to derive element intensities is not specified. ; _item_default.value 'unspecified' save_ save__array_intensities.scaling _item_description.description ; Multiplicative scaling value to be applied to array data in the manner described by item _array_intensities.linearity. ; _item.name '_array_intensities.scaling' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.undefined_value _item_description.description ; A value to be substituted for undefined values in the data array. ; _item.name '_array_intensities.undefined_value' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ ################### # ARRAY_STRUCTURE # ################### save_ARRAY_STRUCTURE _category.description ; Data items in the ARRAY_STRUCTURE category record the organization and encoding of array data that may be stored in the ARRAY_DATA category. ; _category.id array_structure _category.mandatory_code no _category_key.name '_array_structure.id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order image_1 "unsigned 16-bit integer" none little_endian ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure.byte_order _item_description.description ; The order of bytes for integer values which require more than 1 byte. (IBM-PC's and compatibles and DEC VAXs use low-byte-first ordered integers, whereas Hewlett Packard 700 series, Sun-4 and Silicon Graphics use high-byte-first ordered integers. DEC Alphas can produce/use either depending on a compiler switch.) ; _item.name '_array_structure.byte_order' _item.category_id array_structure _item.mandatory_code yes _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail 'big_endian' ; The first byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; 'little_endian' ; The last byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; save_ save__array_structure.compression_type _item_description.description ; Type of data-compression method used to compress the array data. ; _item.name '_array_structure.compression_type' _item.category_id array_structure _item.mandatory_code no _item_type.code ucode _item_default.value 'none' loop_ _item_enumeration.value _item_enumeration.detail 'byte_offset' ; Using the 'byte_offset' compression scheme as per A. Hammersley and the CBFlib manual, section 3.3.3 ; 'canonical' ; Using the 'canonical' compression scheme (International Tables for Crystallography Volume G, Section 5.6.3.1) and CBFlib manual section 3.3.1 ; 'none' ; Data are stored in normal format as defined by _array_structure.encoding_type and _array_structure.byte_order. ; 'packed' ; Using the 'packed' compression scheme, a CCP4-style packing as per J. P. Abrahams pack_c.c and CBFlib manual, section 3.3.2. ; 'packed_v2' ; Using the 'packed' compression scheme, version 2, as per J. P. Abrahams pack_c.c and CBFlib manual, section 3.3.2. ; save_ save__array_structure.compression_type_flag _item_description.description ; Flags modifying the type of data-compression method used to compress the arraydata. ; _item.name '_array_structure.compression_type_flag' _item.category_id array_structure _item.mandatory_code no _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail 'uncorrelated_sections' ; When applying packed or packed_v2 compression on an array with uncorrelated sections, do not average in points from the prior section. ; 'flat' ; When applying packed or packed_v2 compression on an array with treat the entire image as a single line set the maximum number of bits for an offset to 65 bits. The flag is included for compatibility with software prior to CBFlib_0.7.7, and should not be used for new data sets. ; save_ save__array_structure.encoding_type _item_description.description ; Data encoding of a single element of array data. The type 'unsigned 1-bit integer' is used for packed Booleans arrays for masks. Each element of the array corresponds to a single bit packed in unsigned 8-bit data. In several cases, the IEEE format is referenced. See IEEE Standard 754-1985 (IEEE, 1985). Ref: IEEE (1985). IEEE Standard for Binary Floating-Point Arithmetic. ANSI/IEEE Std 754-1985. New York: Institute of Electrical and Electronics Engineers. ; _item.name '_array_structure.encoding_type' _item.category_id array_structure _item.mandatory_code yes _item_type.code uline loop_ _item_enumeration.value 'unsigned 1-bit integer' 'unsigned 8-bit integer' 'signed 8-bit integer' 'unsigned 16-bit integer' 'signed 16-bit integer' 'unsigned 32-bit integer' 'signed 32-bit integer' 'signed 32-bit real IEEE' 'signed 64-bit real IEEE' 'signed 32-bit complex IEEE' save_ save__array_structure.id _item_description.description ; The value of _array_structure.id must uniquely identify each item of array data. This item has been made implicit and given a default value of 1 as a convenience in writing miniCBF files. Normally an explicit name with useful content should be used. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure.id' array_structure implicit '_array_data.array_id' array_data implicit '_array_structure_list.array_id' array_structure_list implicit '_array_intensities.array_id' array_intensities implicit '_diffrn_data_frame.array_id' diffrn_data_frame implicit _item_default.value 1 _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_data.array_id' '_array_structure.id' '_array_structure_list.array_id' '_array_structure.id' '_array_intensities.array_id' '_array_structure.id' '_diffrn_data_frame.array_id' '_array_structure.id' save_ ######################## # ARRAY_STRUCTURE_LIST # ######################## save_ARRAY_STRUCTURE_LIST _category.description ; Data items in the ARRAY_STRUCTURE_LIST category record the size and organization of each array dimension. The relationship to physical axes may be given. ; _category.id array_structure_list _category.mandatory_code no loop_ _category_key.name '_array_structure_list.array_id' '_array_structure_list.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - An image array of 1300 x 1200 elements. The raster order of the image is left to right (increasing) in the first dimension and bottom to top (decreasing) in the second dimension. ; ; loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id image_1 1 1300 1 increasing ELEMENT_X image_1 2 1200 2 decreasing ELEMENY_Y ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure_list.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_structure_list.array_id' _item.category_id array_structure_list _item.mandatory_code implicit _item_type.code code save_ save__array_structure_list.axis_set_id _item_description.description ; This is a descriptor for the physical axis or set of axes corresponding to an array index. This data item is related to the axes of the detector itself given in DIFFRN_DETECTOR_AXIS, but usually differs in that the axes in this category are the axes of the coordinate system of reported data points, while the axes in DIFFRN_DETECTOR_AXIS are the physical axes of the detector describing the 'poise' of the detector as an overall physical object. If there is only one axis in the set, the identifier of that axis should be used as the identifier of the set. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.axis_set_id' array_structure_list yes '_array_structure_list_axis.axis_set_id' array_structure_list_axis implicit _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_structure_list_axis.axis_set_id' '_array_structure_list.axis_set_id' save_ save__array_structure_list.dimension _item_description.description ; The number of elements stored in the array structure in this dimension. ; _item.name '_array_structure_list.dimension' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.direction _item_description.description ; Identifies the direction in which this array index changes. ; _item.name '_array_structure_list.direction' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'increasing' ; Indicates the index changes from 1 to the maximum dimension. ; 'decreasing' ; Indicates the index changes from the maximum dimension to 1. ; save_ save__array_structure_list.index _item_description.description ; Identifies the one-based index of the row or column in the array structure. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.index' array_structure_list yes '_array_structure_list.precedence' array_structure_list yes '_array_element_size.index' array_element_size yes _item_type.code int loop_ _item_linked.child_name _item_linked.parent_name '_array_element_size.index' '_array_structure_list.index' loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.precedence _item_description.description ; Identifies the rank order in which this array index changes with respect to other array indices. The precedence of 1 indicates the index which changes fastest. ; _item.name '_array_structure_list.precedence' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ ############################# # ARRAY_STRUCTURE_LIST_AXIS # ############################# save_ARRAY_STRUCTURE_LIST_AXIS _category.description ; Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe the physical settings of sets of axes for the centres of pixels that correspond to data points described in the ARRAY_STRUCTURE_LIST category. In the simplest cases, the physical increments of a single axis correspond to the increments of a single array index. More complex organizations, e.g. spiral scans, may require coupled motions along multiple axes. Note that a spiral scan uses two coupled axes: one for the angular direction and one for the radial direction. This differs from a cylindrical scan for which the two axes are not coupled into one set. ; _category.id array_structure_list_axis _category.mandatory_code no loop_ _category_key.name '_array_structure_list_axis.axis_set_id' '_array_structure_list_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' save_ save__array_structure_list_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes in the set of axes for which settings are being specified. Multiple axes may be specified for the same value of _array_structure_list_axis.axis_set_id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_array_structure_list_axis.axis_id' _item.category_id array_structure_list_axis _item.mandatory_code yes _item_type.code code save_ save__array_structure_list_axis.axis_set_id _item_description.description ; The value of this data item is the identifier of the set of axes for which axis settings are being specified. Multiple axes may be specified for the same value of _array_structure_list_axis.axis_set_id. This item is a pointer to _array_structure_list.axis_set_id in the ARRAY_STRUCTURE_LIST category. If this item is not specified, it defaults to the corresponding axis identifier. ; _item.name '_array_structure_list_axis.axis_set_id' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_type.code code save_ save__array_structure_list_axis.angle _item_description.description ; The setting of the specified axis in degrees for the first data point of the array index with the corresponding value of _array_structure_list.axis_set_id. If the index is specified as 'increasing', this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing', this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.angle' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.angle_increment _item_description.description ; The pixel-centre-to-pixel-centre increment in the angular setting of the specified axis in degrees. This is not meaningful in the case of 'constant velocity' spiral scans and should not be specified for this case. See _array_structure_list_axis.angular_pitch. ; _item.name '_array_structure_list_axis.angle_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for the first data point of the array index with the corresponding value of _array_structure_list.axis_set_id. If the index is specified as 'increasing', this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing', this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.displacement' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.fract_displacement _item_description.description ; The setting of the specified axis as a decimal fraction of the axis unit vector for the first data point of the array index with the corresponding value of _array_structure_list.axis_set_id. If the index is specified as 'increasing', this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing', this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.fract_displacement' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float save_ save__array_structure_list_axis.displacement_increment _item_description.description ; The pixel-centre-to-pixel-centre increment for the displacement setting of the specified axis in millimetres. ; _item.name '_array_structure_list_axis.displacement_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.fract_displacement_increment _item_description.description ; The pixel-centre-to-pixel-centre increment for the displacement setting of the specified axis as a decimal fraction of the axis unit vector. ; _item.name '_array_structure_list_axis.fract_displacement_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.angular_pitch _item_description.description ; The pixel-centre-to-pixel-centre distance for a one-step change in the setting of the specified axis in millimetres. This is meaningful only for 'constant velocity' spiral scans or for uncoupled angular scans at a constant radius (cylindrical scans) and should not be specified for cases in which the angle between pixels (rather than the distance between pixels) is uniform. See _array_structure_list_axis.angle_increment. ; _item.name '_array_structure_list_axis.angular_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.radial_pitch _item_description.description ; The radial distance from one 'cylinder' of pixels to the next in millimetres. If the scan is a 'constant velocity' scan with differing angular displacements between pixels, the value of this item may differ significantly from the value of _array_structure_list_axis.displacement_increment. ; _item.name '_array_structure_list_axis.radial_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.reference_angle _item_description.description ; The value of _array_structure_list_axis.reference_angle specifies the setting of the angle of this axis used for determining a reference beam center and a reference detector distance. It is normally expected to be identical to the value of _array_structure_list.angle. ; _item.name '_array_structure_list_axis.reference_angle' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.reference_displacement _item_description.description ; The value of _array_structure_list_axis.reference_displacement specifies the setting of the displacement of this axis used for determining a reference beam center and a reference detector distance. It is normally expected to be identical to the value of _array_structure_list.displacement. ; _item.name '_array_structure_list_axis.reference_displacement' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'millimetres' save_ ######## # AXIS # ######## save_AXIS _category.description ; Data items in the AXIS category record the information required to describe the various goniometer, detector, source and other axes needed to specify a data collection or the axes defining the coordinate system of an image. The location of each axis is specified by two vectors: the axis itself, given by a unit vector in the direction of the axis, and an offset to the base of the unit vector. The vectors defining an axis are referenced to an appropriate coordinate system. The axis vector, itself, is a dimensionless unit vector. Where meaningful, the offset vector is given in millimetres. In coordinate systems not measured in metres, the offset is not specified and is taken as zero. The available coordinate systems are: The imgCIF standard laboratory coordinate system The direct lattice (fractional atomic coordinates) The orthogonal Cartesian coordinate system (real space) The reciprocal lattice An abstract orthogonal Cartesian coordinate frame For consistency in this discussion, we call the three coordinate system axes X, Y and Z. This is appropriate for the imgCIF standard laboratory coordinate system, and last two Cartesian coordinate systems, but for the direct lattice, X corresponds to a, Y to b and Z to c, while for the reciprocal lattice, X corresponds to a*, Y to b* and Z to c*. For purposes of visualization, all the coordinate systems are taken as right-handed, i.e., using the convention that the extended thumb of a right hand could point along the first (X) axis, the straightened pointer finger could point along the second (Y) axis and the middle finger folded inward could point along the third (Z) axis. THE IMGCIF STANDARD LABORATORY COORDINATE SYSTEM The imgCIF standard laboratory coordinate system is a right-handed orthogonal coordinate similar to the MOSFLM coordinate system, but imgCIF puts Z along the X-ray beam, rather than putting X along the X-ray beam as in MOSFLM. The vectors for the imgCIF standard laboratory coordinate system form a right-handed Cartesian coordinate system with its origin in the sample or specimen. The origin of the axis system should, if possible, be defined in terms of mechanically stable axes to be be both in the sample and in the beam. If the sample goniometer or other sample positioner has two axes the intersection of which defines a unique point at which the sample should be mounted to be bathed by the beam, that will be the origin of the axis system. If no such point is defined, then the midpoint of the line of intersection between the sample and the center of the beam will define the origin. For this definition the sample positioning system will be set at its initial reference position for the experiment. | Y (to complete right-handed system) | | | | | |________________X / principal goniometer axis / / / / /Z (to source) Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from the sample or specimen along the principal axis of the goniometer or sample positioning system if the sample positioning system has an axis that intersects the origin and which form an angle of more than 22.5 degrees with the beam axis. Axis 2 (Y): The Y-axis completes an orthogonal right-handed system defined by the X-axis and the Z-axis (see below). Axis 3 (Z): The Z-axis is derived from the source axis which goes from the sample to the source. The Z-axis is the component of the source axis in the direction of the source orthogonal to the X-axis in the plane defined by the X-axis and the source axis. If the conditions for the X-axis can be met, the coordinate system will be based on the goniometer or other sample positioning system and the beam and not on the orientation of the detector, gravity etc. The vectors necessary to specify all other axes are given by sets of three components in the order (X, Y, Z). If the axis involved is a rotation axis, it is right-handed, i.e. as one views the object to be rotated from the origin (the tail) of the unit vector, the rotation is clockwise. If a translation axis is specified, the direction of the unit vector specifies the sense of positive translation. Note: This choice of coordinate system is similar to but significantly different from the choice in MOSFLM (Leslie & Powell, 2004). In MOSFLM, X is along the X-ray beam (the CBF/imgCIF Z axis) and Z is along the rotation axis. In some experimental techniques, there is no goniometer or the principal axis of the goniometer is at a small acute angle with respect to the source axis. In such cases, other reference axes are needed to define a useful coordinate system. The order of priority in defining directions in such cases is to use the detector, then gravity, then north. If the X-axis cannot be defined as above, then the direction (not the origin) of the X-axis should be parallel to the axis of the primary detector element corresponding to the most rapidly varying dimension of that detector element's data array, with its positive sense corresponding to increasing values of the index for that dimension. If the detector is such that such a direction cannot be defined (as with a point detector) or that direction forms an angle of less than 22.5 degrees with respect to the source axis, then the X-axis should be chosen so that if the Y-axis is chosen in the direction of gravity, and the Z-axis is chosen to be along the source axis, a right-handed orthogonal coordinate system is chosen. In the case of a vertical source axis, as a last resort, the X-axis should be chosen to point North. All rotations are given in degrees and all translations are given in mm. Axes may be dependent on one another. The X-axis is the only goniometer axis the direction of which is strictly connected to the hardware. All other axes are specified by the positions they would assume when the axes upon which they depend are at their zero points. When specifying detector axes, the axis is given to the beam centre. The location of the beam centre on the detector should be given in the DIFFRN_DETECTOR category in distortion-corrected millimetres from the (0,0) corner of the detector. It should be noted that many different origins arise in the definition of an experiment. In particular, as noted above, it is necessary to specify the location of the beam centre on the detector in terms of the origin of the detector, which is, of course, not coincident with the centre of the sample. The unit cell, reciprocal cell and crystallographic orthogonal Cartesian coordinate system are defined by the CELL and the matrices in the ATOM_SITES category. THE DIRECT LATTICE (FRACTIONAL COORDINATES) The direct lattice coordinate system is a system of fractional coordinates aligned to the crystal, rather than to the laboratory. This is a natural coordinate system for maps and atomic coordinates. It is the simplest coordinate system in which to apply symmetry. The axes are determined by the cell edges, and are not necessarily othogonal. This coordinate system is not uniquely defined and depends on the cell parameters in the CELL category and the settings chosen to index the crystal. Molecules in a crystal studied by X-ray diffracraction are organized into a repeating regular array of unit cells. Each unit cell is defined by three vectors, a, b and c. To quote from Drenth, "The choice of the unit cell is not unique and therefore, guidelines have been established for selecting the standard basis vectors and the origin. They are based on symmetry and metric considerations: "(1) The axial system should be right handed. (2) The basis vectors should coincide as much as possible with directions of highest symmetry." (3) The cell taken should be the smallest one that satisfies condition (2) (4) Of all the lattice vectors, none is shorter than a. (5) Of those not directed along a, none is shorter than b. (6) Of those not lying in the ab plane, none is shorter than c. (7) The three angles between the basis vectors a, b and c are either all acute (<90°) or all obtuse (>=90°)." These rules do not produce a unique result that is stable under the assumption of experimental errors, and the the resulting cell may not be primitive. In this coordinate system, the vector (.5, .5, .5) is in the middle of the given unit cell. Grid coordinates are an important variation on fractional coordinates used when working with maps. In imgCIF, the conversion from fractional to grid coordinates is implicit in the array indexing specified by _array_structure_list.dimension. Note that this implicit grid-coordinate scheme is 1-based, not zero-based, i.e. the origin of the cell for axes along the cell edges with no specified _array_structure_list_axis.displacement will have grid coordinates of (1,1,1), i.e. array indices of (1,1,1). THE ORTHOGONAL CARTESIAN COORDINATE SYSTEM (REAL SPACE) The orthogonal Cartesian coordinate system is a transformation of the direct lattice to the actual physical coordinates of atoms in space. It is similar to the laboratory coordinate system, but is anchored to and moves with the crystal, rather than being schored to the laboratory. The transformation from fractional to orthogonal cartesian coordinates is given by the _atom_sites.Cartn_transf_matrix[i][j] and _atom_sites.Cartn_transf_vector[i] tags. A common choice for the matrix of the transformation is given in the 1992 PDB format document | a b cos(g) c cos(b) | | 0 b sin(g) c (cos(a) - cos(b)cos(g))/sin(g) | | 0 0 V/(a b sin(g)) | This is a convenient coordinate system in which to do fitting of models to maps and in which to understand the chemistry of a molecule. THE RECIPROCAL LATTICE The reciprocal lattice coordinate system is used for diffraction intensitities. It is based on the reciprocal cell, the dual of the cell, in which reciprocal cell edges are derived from direct cell faces: a* = bc sin(a)/V b* = ac sin(b)/V c* = ab sin(g)/V cos(a*) = (cos(b) cos(g) - cos(a))/(sin(b) sin(g)) cos(b*) = (cos(g) cos(g) - cos(b) )/(sin(a) sin(g)) cos(g*) = (cos(a) cos(b) - cos(g))/(sin(a) sin(b)) V = abc SQRT (1 - cos(a)2 - cos(b)2 - cos(g)2 + 2 cos(a) cos(b) cos(g) ) In this form the dimensions of the reciprocal lattice are in reciprocal Ångstroms (&A^-1). A dimensionless form can be obtained by multiplying by the wavelength. Reflections are commonly indexed against this coordinate system as (h, k, l) triples. References: Drenth, J., "Introduction to basic crystallography." chapter 2.1 in Rossmann, M. G. and Arnold, E. "Crystallography of biological macromolecules", Volume F of the IUCr's "International tables for crystallography", Kluwer, Dordrecht 2001, pp 44 -- 63 Leslie, A. G. W. and Powell, H. (2004). MOSFLM v6.11. MRC Laboratory of Molecular Biology, Hills Road, Cambridge, England. http://www.CCP4.ac.uk/dist/X-windows/Mosflm/. Stout, G. H. and Jensen, L. H., "X-ray structure determination", 2nd ed., Wiley, New York, 1989, 453 pp. __, "PROTEIN DATA BANK ATOMIC COORDINATE AND BIBLIOGRAPHIC ENTRY FORMAT DESCRIPTION," Brookhaven National Laboratory, February 1992. ; _category.id axis _category.mandatory_code no loop_ _category_key.name '_axis.id' '_axis.equipment' loop_ _category_group.id 'inclusive_group' 'axis_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows the axis specification of the axes of a kappa- geometry goniometer [see Stout, G. H. & Jensen, L. H. (1989). X-ray structure determination. A practical guide, 2nd ed. p. 134. New York: Wiley Interscience]. There are three axes specified, and no offsets. The outermost axis, omega, is pointed along the X axis. The next innermost axis, kappa, is at a 50 degree angle to the X axis, pointed away from the source. The innermost axis, phi, aligns with the X axis when omega and phi are at their zero points. If T-omega, T-kappa and T-phi are the transformation matrices derived from the axis settings, the complete transformation would be: X' = (T-omega) (T-kappa) (T-phi) X ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] omega rotation goniometer . 1 0 0 kappa rotation goniometer omega -.64279 0 -.76604 phi rotation goniometer kappa 1 0 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - This example shows the axis specification of the axes of a detector, source and gravity. The order has been changed as a reminder that the ordering of presentation of tokens is not significant. The centre of rotation of the detector has been taken to be 68 millimetres in the direction away from the source. ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] source . source . 0 0 1 . . . gravity . gravity . 0 -1 0 . . . tranz translation detector rotz 0 0 1 0 0 -68 twotheta rotation detector . 1 0 0 . . . roty rotation detector twotheta 0 1 0 0 0 -68 rotz rotation detector roty 0 0 1 0 0 -68 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 3 - This example show the axis specification of the axes for a map, using fractional coordinates. Each cell edge has been divided into a grid of 50 divisions in the ARRAY_STRUCTURE_LIST_AXIS category. The map is using only the first octant of the grid in the ARRAY_STRUCTURE_LIST category. The fastest changing axis is the gris along A, then along B, and the slowest is along C. The map sampling is being done in the middle of each grid division ; ; loop_ _axis.id _axis.system _axis.vector[1] _axis.vector[2] _axis.vector[3] CELL_A_AXIS fractional 1 0 0 CELL_B_AXIS fractional 0 1 0 CELL_C_AXIS fractional 0 0 1 loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_id MAP 1 25 1 increasing CELL_A_AXIS MAP 1 25 2 increasing CELL_B_AXIS MAP 1 25 3 increasing CELL_C_AXIS loop_ _array_structure_list_axis.axis_id _array_structure_list_axis.fract_displacement _array_structure_list_axis.fract_displacement_increment CELL_A_AXIS 0.01 0.02 CELL_B_AXIS 0.01 0.02 CELL_C_AXIS 0.01 0.02 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 4 - This example show the axis specification of the axes for a map, this time as orthogonal Angstroms, using the same coordinate system as for the atomic coordinates. The map is sampling every 1.5 Angstroms (1.5e-7 millimeters) in a map segment 37.5 Angstroms on a side. ; ; loop_ _axis.id _axis.system _axis.vector[1] _axis.vector[2] _axis.vector[3] X orthogonal 1 0 0 Y orthogonal 0 1 0 Z orthogonal 0 0 1 loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_id MAP 1 25 1 increasing X MAP 2 25 2 increasing Y MAP 3 25 3 increasing Z loop_ _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment X 7.5e-8 1.5e-7 Y 7.5e-8 1.5e-7 Z 7.5e-8 1.5e-7 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__axis.depends_on _item_description.description ; The value of _axis.depends_on specifies the next outermost axis upon which this axis depends. This item is a pointer to _axis.id in the same category. ; _item.name '_axis.depends_on' _item.category_id axis _item.mandatory_code no save_ save__axis.equipment _item_description.description ; The value of _axis.equipment specifies the type of equipment using the axis: 'goniometer', 'detector', 'gravity', 'source' or 'general'. ; _item.name '_axis.equipment' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail goniometer 'equipment used to orient or position samples' detector 'equipment used to detect reflections' general 'equipment used for general purposes' gravity 'axis specifying the downward direction' source 'axis specifying the direction sample to source' save_ save__axis.offset[1] _item_description.description ; The [1] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[2] _item_description.description ; The [2] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[3] _item_description.description ; The [3] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.id _item_description.description ; The value of _axis.id must uniquely identify each axis relevant to the experiment. Note that multiple pieces of equipment may share the same axis (e.g. a twotheta arm), so the category key for AXIS also includes the equipment. ; loop_ _item.name _item.category_id _item.mandatory_code '_axis.id' axis yes '_array_structure_list_axis.axis_id' array_structure_list_axis yes '_diffrn_detector_axis.axis_id' diffrn_detector_axis yes '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes '_diffrn_scan_axis.axis_id' diffrn_scan_axis yes '_diffrn_scan_frame_axis.axis_id' diffrn_scan_frame_axis yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_axis.depends_on' '_axis.id' '_array_structure_list_axis.axis_id' '_axis.id' '_diffrn_detector_axis.axis_id' '_axis.id' '_diffrn_measurement_axis.axis_id' '_axis.id' '_diffrn_scan_axis.axis_id' '_axis.id' '_diffrn_scan_frame_axis.axis_id' '_axis.id' save_ save__axis.system _item_description.description ; The value of _axis.system specifies the coordinate system used to define the axis: 'laboratory', 'direct', 'orthogonal', 'reciprocal' or 'abstract'. ; _item.name '_axis.system' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value laboratory loop_ _item_enumeration.value _item_enumeration.detail laboratory ; the axis is referenced to the imgCIF standard laboratory Cartesian coordinate system ; direct ; the axis is referenced to the direct lattice ; orthogonal ; the axis is referenced to the cell Cartesian orthogonal coordinates ; reciprocal ; the axis is referenced to the reciprocal lattice ; abstract ; the axis is referenced to abstract Cartesian cooridinate system ; save_ save__axis.type _item_description.description ; The value of _axis.type specifies the type of axis: 'rotation' or 'translation' (or 'general' when the type is not relevant, as for gravity). ; _item.name '_axis.type' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail rotation 'right-handed axis of rotation' translation 'translation in the direction of the axis' general 'axis for which the type is not relevant' save_ save__axis.vector[1] _item_description.description ; The [1] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[2] _item_description.description ; The [2] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[3] _item_description.description ; The [3] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ ##################### # DIFFRN_DATA_FRAME # ##################### save_DIFFRN_DATA_FRAME _category.description ; Data items in the DIFFRN_DATA_FRAME category record the details about each frame of data. The items in this category were previously in a DIFFRN_FRAME_DATA category, which is now deprecated. The items from the old category are provided as aliases but should not be used for new work. ; _category.id diffrn_data_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_data_frame.id' '_diffrn_data_frame.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A frame containing data from 4 frame elements. Each frame element has a common array configuration 'array_1' described in ARRAY_STRUCTURE and related categories. The data for each detector element are stored in four groups of binary data in the ARRAY_DATA category, linked by the array_id and binary_id. ; ; loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id frame_1 d1_ccd_1 array_1 1 frame_1 d1_ccd_2 array_1 2 frame_1 d1_ccd_3 array_1 3 frame_1 d1_ccd_4 array_1 4 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_data_frame.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_diffrn_data_frame.array_id' _item.category_id diffrn_data_frame _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_frame_data.array_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_diffrn_data_frame.binary_id' _item.category_id diffrn_data_frame _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_frame_data.binary_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code int save_ save__diffrn_data_frame.center_fast _item_description.description ; The value of _diffrn_data_frame.center_fast is the fast index axis beam center position relative to the detector element face in the units specified in the data item '_diffrn_data_frame.center_units' along the fast axis of the detector from the center of the first pixel to the point at which the Z-axis (which should be colinear with the beam) intersects the face of the detector, if in fact is does. At the time of the measurement the current setting of detector positioner given frame are used. It is important to note that for measurements in millimetres, the sense of the axis is used, rather than the sign of the pixel-to-pixel increments. ; _item.name '_diffrn_data_frame.center_fast' _item.category_id diffrn_data_frame _item.mandatory_code no _item_type.code float save_ save__diffrn_data_frame.center_slow _item_description.description ; The value of _diffrn_data_frame.center_slow is the slow index axis beam center position relative to the detector element face in the units specified in the data item '_diffrn_data_frame.center_units' along the slow axis of the detector from the center of the first pixel to the point at which the Z-axis (which should be colinear with the beam) intersects the face of the detector, if in fact is does. At the time of the measurement the current setting of detector positioner given frame are used. It is important to note that the sense of the axis is used, rather than the sign of the pixel-to-pixel increments. ; _item.name '_diffrn_data_frame.center_slow' _item.category_id diffrn_data_frame _item.mandatory_code no _item_type.code float save_ save__diffrn_data_frame.center_units _item_description.description ; The value of _diffrn_data_frame.center_units specifies the units in which the values of '_diffrn_data_frame.center_fast' and '_diffrn_data_frame.center_slow' are presented. The default is 'mm' for millimetres. The alternatives are 'pixels' and 'bins'. In all cases the center distances are measured from the center of the first pixel, i.e. in a 2x2 binning, the measuring origin is offset from the centers of the bins by one half pixel towards the first pixel. If 'bins' is specified, the data in '_array_intensities.pixel_fast_bin_size', '_array_intensities.pixel_slow_bin_size', and '_array_intensities.pixel_binning_method' is used to define the binning scheme. ; _item.name '_diffrn_data_frame.center_units' _item.category_id diffrn_data_frame _item.mandatory_code no _item_type.code code loop_ _ item_enumeration.value _ item_enumeration.detail mm 'millimetres' pixels 'detector pixels' bins 'detector bins' save_ save__diffrn_data_frame.detector_element_id _item_description.description ; This item is a pointer to _diffrn_detector_element.id in the DIFFRN_DETECTOR_ELEMENT category. ; _item.name '_diffrn_data_frame.detector_element_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.detector_element_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.id _item_description.description ; The value of _diffrn_data_frame.id must uniquely identify each complete frame of data. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_data_frame.id' diffrn_data_frame yes '_diffrn_refln.frame_id' diffrn_refln yes '_diffrn_scan.frame_id_start' diffrn_scan yes '_diffrn_scan.frame_id_end' diffrn_scan yes '_diffrn_scan_frame.frame_id' diffrn_scan_frame yes '_diffrn_scan_frame_axis.frame_id' diffrn_scan_frame_axis yes _item_aliases.alias_name '_diffrn_frame_data.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_refln.frame_id' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_start' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_end' '_diffrn_data_frame.id' '_diffrn_scan_frame.frame_id' '_diffrn_data_frame.id' '_diffrn_scan_frame_axis.frame_id' '_diffrn_data_frame.id' save_ save__diffrn_data_frame.details _item_description.description ; The value of _diffrn_data_frame.details should give a description of special aspects of each frame of data. This is an appropriate location in which to record information from vendor headers as presented in those headers, but it should never be used as a substitute for providing the fully parsed information within the appropriate imgCIF/CBF categories. Normally, when a conversion from a miniCBF has been done the data from '_array_data.header_convention' should be transferred to this data item and '_array_data.header_convention' should be removed. ; _item.name '_diffrn_data_frame.details' _item.category_id diffrn_data_frame _item.mandatory_code no _item_aliases.alias_name '_diffrn_frame_data.details' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.4 _item_type.code text loop_ _item_examples.case _item_examples.detail ; HEADER_BYTES = 512; DIM = 2; BYTE_ORDER = big_endian; TYPE = unsigned_short; SIZE1 = 3072; SIZE2 = 3072; PIXEL_SIZE = 0.102588; BIN = 2x2; DETECTOR_SN = 901; TIME = 29.945155; DISTANCE = 200.000000; PHI = 85.000000; OSC_START = 85.000000; OSC_RANGE = 1.000000; WAVELENGTH = 0.979381; BEAM_CENTER_X = 157.500000; BEAM_CENTER_Y = 157.500000; PIXEL SIZE = 0.102588; OSCILLATION RANGE = 1; EXPOSURE TIME = 29.9452; TWO THETA = 0; BEAM CENTRE = 157.5 157.5; ; ; Example of header information extracted from an ADSC Quantum 315 detector header by CBFlib_0.7.6. Image provided by Chris Nielsen of ADSC from a data collection at SSRL beamline 1-5. ; save_ ########################################################################## # The following is a restatement of the mmCIF DIFFRN_DETECTOR, # # DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for # # the CBF/imgCIF extensions # ########################################################################## ################### # DIFFRN_DETECTOR # ################### save_DIFFRN_DETECTOR _category.description ; Data items in the DIFFRN_DETECTOR category describe the detector used to measure the scattered radiation, including any analyser and post-sample collimation. ; _category.id diffrn_detector _category.mandatory_code no loop_ _category_key.name '_diffrn_detector.diffrn_id' '_diffrn_detector.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _diffrn_detector.diffrn_id 'd1' _diffrn_detector.detector 'multiwire' _diffrn_detector.type 'Siemens' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector.details _item_description.description ; A description of special aspects of the radiation detector. ; _item.name '_diffrn_detector.details' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'slow mode' save_ save__diffrn_detector.detector _item_description.description ; The general class of the radiation detector. ; _item.name '_diffrn_detector.detector' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector' cifdic.c91 1.0 '_diffrn_detector' cif_core.dic 2.0 _item_type.code text loop_ _item_examples.case 'photographic film' 'scintillation counter' 'CCD plate' 'BF~3~ counter' save_ save__diffrn_detector.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. The value of _diffrn.id uniquely defines a set of diffraction data. ; _item.name '_diffrn_detector.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector.dtime _item_description.description ; The deadtime in microseconds of the detector(s) used to measure the diffraction intensities. ; _item.name '_diffrn_detector.dtime' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector_dtime' cifdic.c91 1.0 '_diffrn_detector_dtime' cif_core.dic 2.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code microseconds save_ save__diffrn_detector.id _item_description.description ; The value of _diffrn_detector.id must uniquely identify each detector used to collect each diffraction data set. If the value of _diffrn_detector.id is not given, it is implicitly equal to the value of _diffrn_detector.diffrn_id. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector.id' diffrn_detector implicit '_diffrn_detector_axis.detector_id' diffrn_detector_axis yes loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_detector_axis.detector_id' '_diffrn_detector.id' _item_type.code code save_ save__diffrn_detector.number_of_axes _item_description.description ; The value of _diffrn_detector.number_of_axes gives the number of axes of the positioner for the detector identified by _diffrn_detector.id. The word 'positioner' is a general term used in instrumentation design for devices that are used to change the positions of portions of apparatus by linear translation, rotation or combinations of such motions. Axes which are used to provide a coordinate system for the face of an area detetctor should not be counted for this data item. The description of each axis should be provided by entries in DIFFRN_DETECTOR_AXIS. ; _item.name '_diffrn_detector.number_of_axes' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_detector.type _item_description.description ; The make, model or name of the detector device used. ; _item.name '_diffrn_detector.type' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ ######################## # DIFFRN_DETECTOR_AXIS # ######################## save_DIFFRN_DETECTOR_AXIS _category.description ; Data items in the DIFFRN_DETECTOR_AXIS category associate axes with detectors. ; _category.id diffrn_detector_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_axis.detector_id' '_diffrn_detector_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_detector_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_detector_axis.axis_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_axis.detector_id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. This item was previously named _diffrn_detector_axis.id which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_detector_axis.detector_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_aliases.alias_name '_diffrn_detector_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ ########################### # DIFFRN_DETECTOR_ELEMENT # ########################### save_DIFFRN_DETECTOR_ELEMENT _category.description ; Data items in the DIFFRN_DETECTOR_ELEMENT category record the details about spatial layout and other characteristics of each element of a detector which may have multiple elements. In most cases, giving more detailed information in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS is preferable to simply providing the centre of the detector element. ; _category.id diffrn_detector_element _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_element.id' '_diffrn_detector_element.detector_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Detector d1 is composed of four CCD detector elements, each 200 mm by 200 mm, arranged in a square, in the pattern 1 2 * 3 4 Note that the beam centre is slightly displaced from each of the detector elements, just beyond the lower right corner of 1, the lower left corner of 2, the upper right corner of 3 and the upper left corner of 4. For each element, the detector face coordiate system, is assumed to have the fast axis running from left to right and the slow axis running from top to bottom with the origin at the top left corner. ; ; loop_ _diffrn_detector_element.detector_id _diffrn_detector_element.id _diffrn_detector_element.reference_center_fast _diffrn_detector_element.reference_center_slow _diffrn_detector_element.reference_center_units d1 d1_ccd_1 201.5 201.5 mm d1 d1_ccd_2 -1.8 201.5 mm d1 d1_ccd_3 201.6 -1.4 mm d1 d1_ccd_4 -1.7 -1.5 mm ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector_element.id _item_description.description ; The value of _diffrn_detector_element.id must uniquely identify each element of a detector. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector_element.id' diffrn_detector_element yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.detector_element_id' '_diffrn_detector_element.id' save_ save__diffrn_detector_element.detector_id _item_description.description ; This item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. ; _item.name '_diffrn_detector_element.detector_id' _item.category_id diffrn_detector_element _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_element.reference_center_fast _item_description.description ; The value of _diffrn_detector_element.reference_center_fast is the fast index axis beam center position relative to the detector element face in the units specified in the data item '_diffrn_detector_element.reference_center_units' along the fast axis of the detector from the center of the first pixel to the point at which the Z-axis (which should be colinear with the beam) intersects the face of the detector, if in fact is does. At the time of the measurement all settings of the detector positioner should be at their reference settings. If more than one reference setting has been used the value given whould be representive of the beam center as determined from the ensemble of settings. It is important to note that for measurements in millimetres, the sense of the axis is used, rather than the sign of the pixel-to-pixel increments. ; _item.name '_diffrn_detector_element.reference_center_fast' _item.category_id diffrn_detector_element _item.mandatory_code no _item_type.code float save_ save__diffrn_detector_element.reference_center_slow _item_description.description ; The value of _diffrn_detector_element.reference_center_slow is the slow index axis beam center position relative to the detector element face in the units specified in the data item '_diffrn_detector_element.reference_center_units' along the slow axis of the detector from the center of the first pixel to the point at which the Z-axis (which should be colinear with the beam) intersects the face of the detector, if in fact is does. At the time of the measurement all settings of the detector positioner should be at their reference settings. If more than one reference setting has been used the value givien whould be representive of the beam center as determined from the ensemble of settings. It is important to note that the sense of the axis is used, rather than the sign of the pixel-to-pixel increments. ; _item.name '_diffrn_detector_element.reference_center_slow' _item.category_id diffrn_detector_element _item.mandatory_code no _item_type.code float save_ save__diffrn_detector_element.reference_center_units _item_description.description ; The value of _diffrn_detector_element.reference_center_units specifies the units in which the values of '_diffrn_detector_element.reference_center_fast' and '_diffrn_detector_element.reference_center_slow' are presented. The default is 'mm' for millimetres. The alternatives are 'pixels' and 'bins'. In all cases the center distances are measured from the center of the first pixel, i.e. in a 2x2 binning, the measuring origin is offset from the centers of the bins by one half pixel towards the first pixel. If 'bins' is specified, the data in '_array_intensities.pixel_fast_bin_size', '_array_intensities.pixel_slow_bin_size', and '_array_intensities.pixel_binning_method' is used to define the binning scheme. ; _item.name '_diffrn_detector_element.reference_center_units' _item.category_id diffrn_detector_element _item.mandatory_code no _item_type.code code loop_ _ item_enumeration.value _ item_enumeration.detail mm 'millimetres' pixels 'detector pixels' bins 'detector bins' save_ ######################## ## DIFFRN_MEASUREMENT ## ######################## save_DIFFRN_MEASUREMENT _category.description ; Data items in the DIFFRN_MEASUREMENT category record details about the device used to orient and/or position the crystal during data measurement and the manner in which the diffraction data were measured. ; _category.id diffrn_measurement _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement.device' '_diffrn_measurement.diffrn_id' '_diffrn_measurement.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_measurement.diffrn_id 'd1' _diffrn_measurement.device '3-circle camera' _diffrn_measurement.device_type 'Supper model X' _diffrn_measurement.device_details 'none' _diffrn_measurement.method 'omega scan' _diffrn_measurement.details ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _diffrn_measurement.diffrn_id 's1' _diffrn_measurement.device_type 'Philips PW1100/20 diffractometer' _diffrn_measurement.method 'theta/2theta (\q/2\q)' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_measurement.device _item_description.description ; The general class of goniometer or device used to support and orient the specimen. If the value of _diffrn_measurement.device is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id. Either _diffrn_measurement.device or _diffrn_measurement.id may be used to link to other categories. If the experimental setup admits multiple devices, then _diffrn_measurement.id is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.device' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_device' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement.device' _item_aliases.alias_name '_diffrn_measurement_device' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '3-circle camera' '4-circle camera' 'kappa-geometry camera' 'oscillation camera' 'precession camera' save_ save__diffrn_measurement.device_details _item_description.description ; A description of special aspects of the device used to measure the diffraction intensities. ; _item.name '_diffrn_measurement.device_details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; commercial goniometer modified locally to allow for 90\% \t arc ; save_ save__diffrn_measurement.device_type _item_description.description ; The make, model or name of the measurement device (goniometer) used. ; _item.name '_diffrn_measurement.device_type' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Supper model q' 'Huber model r' 'Enraf-Nonius model s' 'home-made' save_ save__diffrn_measurement.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_measurement.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement.details _item_description.description ; A description of special aspects of the intensity measurement. ; _item.name '_diffrn_measurement.details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; save_ save__diffrn_measurement.id _item_description.description ; The value of _diffrn_measurement.id must uniquely identify the set of mechanical characteristics of the device used to orient and/or position the sample used during the collection of each diffraction data set. If the value of _diffrn_measurement.id is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id. Either _diffrn_measurement.device or _diffrn_measurement.id may be used to link to other categories. If the experimental setup admits multiple devices, then _diffrn_measurement.id is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.id' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_id' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement.id' _item_type.code code save_ save__diffrn_measurement.method _item_description.description ; Method used to measure intensities. ; _item.name '_diffrn_measurement.method' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_method' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'profile data from theta/2theta (\q/2\q) scans' save_ save__diffrn_measurement.number_of_axes _item_description.description ; The value of _diffrn_measurement.number_of_axes gives the number of axes of the positioner for the goniometer or other sample orientation or positioning device identified by _diffrn_measurement.id. The description of the axes should be provided by entries in DIFFRN_MEASUREMENT_AXIS. ; _item.name '_diffrn_measurement.number_of_axes' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ # _diffrn_measurement.sample_detector_distance # _diffrn_measurement.sample_detector_voffset save__diffrn_measurement.sample_detector_distance _item_description.description ; The value of _diffrn_measurement.sample_detector_distance gives the unsigned distance in millimetres from the sample to the detector along the beam. ; _item.name '_diffrn_measurement.sample_detector_distance' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 _item_type.code float _item_units.code mm save_ save__diffrn_measurement.sample_detector_voffset _item_description.description ; The value of _diffrn_measurement.sample_detector_voffset gives the signed distance in millimetres in the vertical direction (positive for up) from the center of the beam to the center of the detector. ; _item.name '_diffrn_measurement.sample_detector_voffset' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . . . . _item_type.code float _item_units.code mm save_ save__diffrn_measurement.specimen_support _item_description.description ; The physical device used to support the crystal during data collection. ; _item.name '_diffrn_measurement.specimen_support' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_specimen_support' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'glass capillary' 'quartz capillary' 'fiber' 'metal loop' save_ ########################### # DIFFRN_MEASUREMENT_AXIS # ########################### save_DIFFRN_MEASUREMENT_AXIS _category.description ; Data items in the DIFFRN_MEASUREMENT_AXIS category associate axes with goniometers. ; _category.id diffrn_measurement_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_measurement_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_measurement_axis.axis_id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.measurement_device _item_description.description ; This data item is a pointer to _diffrn_measurement.device in the DIFFRN_MEASUREMENT category. ; _item.name '_diffrn_measurement_axis.measurement_device' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit _item_type.code text save_ save__diffrn_measurement_axis.measurement_id _item_description.description ; This data item is a pointer to _diffrn_measurement.id in the DIFFRN_MEASUREMENT category. This item was previously named _diffrn_measurement_axis.id, which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_measurement_axis.measurement_id' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_measurement_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ #################### # DIFFRN_RADIATION # #################### save_DIFFRN_RADIATION _category.description ; Data items in the DIFFRN_RADIATION category describe the radiation used for measuring diffraction intensities, its collimation and monochromatization before the sample. Post-sample treatment of the beam is described by data items in the DIFFRN_DETECTOR category. ; _category.id diffrn_radiation _category.mandatory_code no _category_key.name '_diffrn_radiation.diffrn_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_radiation.diffrn_id 'set1' _diffrn_radiation.collimation '0.3 mm double pinhole' _diffrn_radiation.monochromator 'graphite' _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.wavelength_id 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _diffrn_radiation.wavelength_id 1 _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.monochromator 'graphite' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_radiation.collimation _item_description.description ; The collimation or focusing applied to the radiation. ; _item.name '_diffrn_radiation.collimation' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_collimation' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '0.3 mm double-pinhole' '0.5 mm' 'focusing mirrors' save_ save__diffrn_radiation.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_radiation.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_radiation.div_x_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory X axis (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the standard uncertainty (e.s.d.) of the directions of photons in the XZ plane around the mean source beam direction. Note that for some synchrotrons this value is specified in milliradians, in which case a conversion is needed. To convert a value in milliradians to a value in degrees, multiply by 0.180 and divide by \p. ; _item.name '_diffrn_radiation.div_x_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.div_y_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory Y axis (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the standard uncertainty (e.s.d.) of the directions of photons in the YZ plane around the mean source beam direction. Note that for some synchrotrons this value is specified in milliradians, in which case a conversion is needed. To convert a value in milliradians to a value in degrees, multiply by 0.180 and divide by \p. ; _item.name '_diffrn_radiation.div_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.div_x_y_source _item_description.description ; Beam crossfire correlation degrees^2^ between the crossfire laboratory X-axis component and the crossfire laboratory Y-axis component (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the mean of the products of the deviations of the direction of each photon in XZ plane times the deviations of the direction of the same photon in the YZ plane around the mean source beam direction. This will be zero for uncorrelated crossfire. Note that some synchrotrons, this value is specified in milliradians^2^, in which case a conversion would be needed. To go from a value in milliradians^2^ to a value in degrees^2^, multiply by 0.180^2^ and divide by \p^2^. ; _item.name '_diffrn_radiation.div_x_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees_squared _item_default.value 0.0 save_ save__diffrn_radiation.filter_edge _item_description.description ; Absorption edge in \%Angstroms of the radiation filter used. ; _item.name '_diffrn_radiation.filter_edge' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_filter_edge' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__diffrn_radiation.inhomogeneity _item_description.description ; Half-width in millimetres of the incident beam in the direction perpendicular to the diffraction plane. ; _item.name '_diffrn_radiation.inhomogeneity' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_inhomogeneity' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code millimetres save_ save__diffrn_radiation.monochromator _item_description.description ; The method used to obtain monochromatic radiation. If a monochromator crystal is used, the material and the indices of the Bragg reflection are specified. ; _item.name '_diffrn_radiation.monochromator' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_monochromator' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Zr filter' 'Ge 220' 'none' 'equatorial mounted graphite' save_ save__diffrn_radiation.polarisn_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the perpendicular component of the polarization and the diffraction plane. See _diffrn_radiation_polarisn_ratio. ; _item.name '_diffrn_radiation.polarisn_norm' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_norm' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.polarisn_ratio _item_description.description ; Polarization ratio of the diffraction beam incident on the crystal. This is the ratio of the perpendicularly polarized to the parallel polarized component of the radiation. The perpendicular component forms an angle of _diffrn_radiation.polarisn_norm to the normal to the diffraction plane of the sample (i.e. the plane containing the incident and reflected beams). ; _item.name '_diffrn_radiation.polarisn_ratio' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_ratio' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__diffrn_radiation.polarizn_source_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the normal to the polarization plane and the laboratory Y axis as defined in the AXIS category. Note that this is the angle of polarization of the source photons, either directly from a synchrotron beamline or from a monochromater. This differs from the value of _diffrn_radiation.polarisn_norm in that _diffrn_radiation.polarisn_norm refers to polarization relative to the diffraction plane rather than to the laboratory axis system. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane should be taken as the XZ plane and the angle as 0. See _diffrn_radiation.polarizn_source_ratio. ; _item.name '_diffrn_radiation.polarizn_source_norm' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.polarizn_source_ratio _item_description.description ; (Ip-In)/(Ip+In), where Ip is the intensity (amplitude squared) of the electric vector in the plane of polarization and In is the intensity (amplitude squared) of the electric vector in the plane of the normal to the plane of polarization. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane is to be taken as the XZ plane and the normal is parallel to the Y axis. Thus, if there was complete polarization in the plane of polarization, the value of _diffrn_radiation.polarizn_source_ratio would be 1, and for an unpolarized beam _diffrn_radiation.polarizn_source_ratio would have a value of 0. If the X axis has been chosen to lie in the plane of polarization, this definition will agree with the definition of 'MONOCHROMATOR' in the Denzo glossary, and values of near 1 should be expected for a bending-magnet source. However, if the X axis were perpendicular to the polarization plane (not a common choice), then the Denzo value would be the negative of _diffrn_radiation.polarizn_source_ratio. See http://www.hkl-xray.com for information on Denzo and Otwinowski & Minor (1997). This differs both in the choice of ratio and choice of orientation from _diffrn_radiation.polarisn_ratio, which, unlike _diffrn_radiation.polarizn_source_ratio, is unbounded. Reference: Otwinowski, Z. & Minor, W. (1997). 'Processing of X-ray diffraction data collected in oscillation mode.' Methods Enzymol. 276, 307-326. ; _item.name '_diffrn_radiation.polarizn_source_ratio' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 -1.0 -1.0 -1.0 _item_type.code float save_ save__diffrn_radiation.probe _item_description.description ; Name of the type of radiation used. It is strongly recommended that this be given so that the probe radiation is clearly specified. ; _item.name '_diffrn_radiation.probe' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_probe' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value 'X-ray' 'neutron' 'electron' 'gamma' save_ save__diffrn_radiation.type _item_description.description ; The nature of the radiation. This is typically a description of the X-ray wavelength in Siegbahn notation. ; _item.name '_diffrn_radiation.type' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'CuK\a' 'Cu K\a~1~' 'Cu K-L~2,3~' 'white-beam' save_ save__diffrn_radiation.xray_symbol _item_description.description ; The IUPAC symbol for the X-ray wavelength for the probe radiation. ; _item.name '_diffrn_radiation.xray_symbol' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_xray_symbol' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value _item_enumeration.detail 'K-L~3~' 'K\a~1~ in older Siegbahn notation' 'K-L~2~' 'K\a~2~ in older Siegbahn notation' 'K-M~3~' 'K\b~1~ in older Siegbahn notation' 'K-L~2,3~' 'use where K-L~3~ and K-L~2~ are not resolved' save_ save__diffrn_radiation.wavelength_id _item_description.description ; This data item is a pointer to _diffrn_radiation_wavelength.id in the DIFFRN_RADIATION_WAVELENGTH category. ; _item.name '_diffrn_radiation.wavelength_id' _item.category_id diffrn_radiation _item.mandatory_code yes _item_type.code code save_ ################ # DIFFRN_REFLN # ################ save_DIFFRN_REFLN _category.description ; This category redefinition has been added to extend the key of the standard DIFFRN_REFLN category. ; _category.id diffrn_refln _category.mandatory_code no _category_key.name '_diffrn_refln.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_refln.frame_id _item_description.description ; This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_refln.frame_id' _item.category_id diffrn_refln _item.mandatory_code yes _item_type.code code save_ ############### # DIFFRN_SCAN # ############### save_DIFFRN_SCAN _category.description ; Data items in the DIFFRN_SCAN category describe the parameters of one or more scans, relating axis positions to frames. ; _category.id diffrn_scan _category.mandatory_code no _category_key.name '_diffrn_scan.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - derived from a suggestion by R. M. Sweet. The vector of each axis is not given here, because it is provided in the AXIS category. By making _diffrn_scan_axis.scan_id and _diffrn_scan_axis.axis_id keys of the DIFFRN_SCAN_AXIS category, an arbitrary number of scanning and fixed axes can be specified for a scan. In this example, three rotation axes and one translation axis at nonzero values are specified, with one axis stepping. There is no reason why more axes could not have been specified to step. Range information has been specified, but note that it can be calculated from the number of frames and the increment, so the data item _diffrn_scan_axis.angle_range could be dropped. Both the sweep data and the data for a single frame are specified. Note that the information on how the axes are stepped is given twice, once in terms of the overall averages in the value of _diffrn_scan.integration_time and the values for DIFFRN_SCAN_AXIS, and precisely for the given frame in the value for _diffrn_scan_frame.integration_time and the values for DIFFRN_SCAN_FRAME_AXIS. If dose-related adjustments are made to scan times and nonlinear stepping is done, these values may differ. Therefore, in interpreting the data for a particular frame it is important to use the frame-specific data. ; ; _diffrn_scan.id 1 _diffrn_scan.date_start '2001-11-18T03:26:42' _diffrn_scan.date_end '2001-11-18T03:36:45' _diffrn_scan.integration_time 3.0 _diffrn_scan.frame_id_start mad_L2_000 _diffrn_scan.frame_id_end mad_L2_200 _diffrn_scan.frames 201 loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment 1 omega 200.0 20.0 0.1 . . . 1 kappa -40.0 0.0 0.0 . . . 1 phi 127.5 0.0 0.0 . . . 1 tranz . . . 2.3 0.0 0.0 _diffrn_scan_frame.scan_id 1 _diffrn_scan_frame.date '2001-11-18T03:27:33' _diffrn_scan_frame.integration_time 3.0 _diffrn_scan_frame.frame_id mad_L2_018 _diffrn_scan_frame.frame_number 18 loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.angle_increment _diffrn_scan_frame_axis.displacement _diffrn_scan_frame_axis.displacement_increment mad_L2_018 omega 201.8 0.1 . . mad_L2_018 kappa -40.0 0.0 . . mad_L2_018 phi 127.5 0.0 . . mad_L2_018 tranz . . 2.3 0.0 ; ; Example 2 - a more extensive example (R. M. Sweet, P. J. Ellis & H. J. Bernstein). A detector is placed 240 mm along the Z axis from the goniometer. This leads to a choice: either the axes of the detector are defined at the origin, and then a Z setting of -240 is entered, or the axes are defined with the necessary Z offset. In this case, the setting is used and the offset is left as zero. This axis is called DETECTOR_Z. The axis for positioning the detector in the Y direction depends on the detector Z axis. This axis is called DETECTOR_Y. The axis for positioning the detector in the X direction depends on the detector Y axis (and therefore on the detector Z axis). This axis is called DETECTOR_X. This detector may be rotated around the Y axis. This rotation axis depends on the three translation axes. It is called DETECTOR_PITCH. A coordinate system is defined on the face of the detector in terms of 2300 0.150 mm pixels in each direction. The ELEMENT_X axis is used to index the first array index of the data array and the ELEMENT_Y axis is used to index the second array index. Because the pixels are 0.150mm X 0.150mm, the centre of the first pixel is at (0.075, 0.075) in this coordinate system. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 172.43 -172.43 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 2300 1 increasing ELEMENT_X ARRAY1 2 2300 2 increasing ELEMENT_Y # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.075 0.150 ELEMENT_Y ELEMENT_Y 0.075 0.150 # category ARRAY_ELEMENT_SIZE loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 ARRAY1 2 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; ; Example 3 - Example 2 revised for a spiral scan (R. M. Sweet, P. J. Ellis & H. J. Bernstein). A detector is placed 240 mm along the Z axis from the goniometer, as in Example 2 above, but in this example the image plate is scanned in a spiral pattern from the outside edge in. The axis for positioning the detector in the Y direction depends on the detector Z axis. This axis is called DETECTOR_Y. The axis for positioning the detector in the X direction depends on the detector Y axis (and therefore on the detector Z axis). This axis is called DETECTOR_X. This detector may be rotated around the Y axis. This rotation axis depends on the three translation axes. It is called DETECTOR_PITCH. A coordinate system is defined on the face of the detector in terms of a coupled rotation axis and radial scan axis to form a spiral scan. The rotation axis is called ELEMENT_ROT and the radial axis is called ELEMENT_RAD. A 150 micrometre radial pitch and a 75 micrometre 'constant velocity' angular pitch are assumed. Indexing is carried out first on the rotation axis and the radial axis is made to be dependent on it. The two axes are coupled to form an axis set ELEMENT_SPIRAL. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_ROT translation detector DETECTOR_PITCH 0 0 1 0 0 0 ELEMENT_RAD translation detector ELEMENT_ROT 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.angle _array_structure_list_axis.displacement _array_structure_list_axis.angular_pitch _array_structure_list_axis.radial_pitch ELEMENT_SPIRAL ELEMENT_ROT 0 . 0.075 . ELEMENT_SPIRAL ELEMENT_RAD . 172.5 . -0.150 # category ARRAY_ELEMENT_SIZE # the actual pixels are 0.075 by 0.150 mm # We give the coarser dimension here. loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_scan.id _item_description.description ; The value of _diffrn_scan.id uniquely identifies each scan. The identifier is used to tie together all the information about the scan. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_scan.id' diffrn_scan yes '_diffrn_scan_axis.scan_id' diffrn_scan_axis yes '_diffrn_scan_frame.scan_id' diffrn_scan_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_scan_axis.scan_id' '_diffrn_scan.id' '_diffrn_scan_frame.scan_id' '_diffrn_scan.id' save_ save__diffrn_scan.date_end _item_description.description ; The date and time of the end of the scan. Note that this may be an estimate generated during the scan, before the precise time of the end of the scan is known. ; _item.name '_diffrn_scan.date_end' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.date_start _item_description.description ; The date and time of the start of the scan. ; _item.name '_diffrn_scan.date_start' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.integration_time _item_description.description ; Approximate average time in seconds to integrate each step of the scan. The precise time for integration of each particular step must be provided in _diffrn_scan_frame.integration_time, even if all steps have the same integration time. ; _item.name '_diffrn_scan.integration_time' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan.frame_id_start _item_description.description ; The value of this data item is the identifier of the first frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_start' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frame_id_end _item_description.description ; The value of this data item is the identifier of the last frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_end' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frames _item_description.description ; The value of this data item is the number of frames in the scan. ; _item.name '_diffrn_scan.frames' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 1 1 1 save_ #################### # DIFFRN_SCAN_AXIS # #################### save_DIFFRN_SCAN_AXIS _category.description ; Data items in the DIFFRN_SCAN_AXIS category describe the settings of axes for particular scans. Unspecified axes are assumed to be at their zero points. ; _category.id diffrn_scan_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_axis.scan_id' '_diffrn_scan_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_axis.scan_id _item_description.description ; The value of this data item is the identifier of the scan for which axis settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan.id. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_axis.scan_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the scan for which settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan.id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_axis.axis_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.angle_start _item_description.description ; The starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_range _item_description.description ; The range from the starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_increment _item_description.description ; The increment for each step for the specified axis in degrees. In general, this will agree with _diffrn_scan_frame_axis.angle_increment. The sum of the values of _diffrn_scan_frame_axis.angle and _diffrn_scan_frame_axis.angle_increment is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of _diffrn_scan_axis.angle_increment will be representative of the ensemble of values of _diffrn_scan_frame_axis.angle_increment (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_rstrt_incr _item_description.description ; The increment after each step for the specified axis in degrees. In general, this will agree with _diffrn_scan_frame_axis.angle_rstrt_incr. The sum of the values of _diffrn_scan_frame_axis.angle, _diffrn_scan_frame_axis.angle_increment and _diffrn_scan_frame_axis.angle_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame and should equal _diffrn_scan_frame_axis.angle for this next frame. If the individual frame values vary, then the value of _diffrn_scan_axis.angle_rstrt_incr will be representative of the ensemble of values of _diffrn_scan_frame_axis.angle_rstrt_incr (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.displacement_start _item_description.description ; The starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_range _item_description.description ; The range from the starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_increment _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with _diffrn_scan_frame_axis.displacement_increment. The sum of the values of _diffrn_scan_frame_axis.displacement and _diffrn_scan_frame_axis.displacement_increment is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of _diffrn_scan_axis.displacement_increment will be representative of the ensemble of values of _diffrn_scan_frame_axis.displacement_increment (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_rstrt_incr _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with _diffrn_scan_frame_axis.displacement_rstrt_incr. The sum of the values of _diffrn_scan_frame_axis.displacement, _diffrn_scan_frame_axis.displacement_increment and _diffrn_scan_frame_axis.displacement_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame and should equal _diffrn_scan_frame_axis.displacement for this next frame. If the individual frame values vary, then the value of _diffrn_scan_axis.displacement_rstrt_incr will be representative of the ensemble of values of _diffrn_scan_frame_axis.displacement_rstrt_incr (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.reference_angle _item_description.description ; The setting of the specified axis in degrees against which measurements of the reference beam center and reference detector distance should be made. In general, this will agree with _diffrn_scan_frame_axis.reference_angle. If the individual frame values vary, then the value of _diffrn_scan_axis.reference_angle will be representative of the ensemble of values of _diffrn_scan_frame_axis.reference_angle (e.g. the mean). If not specified, the value defaults to zero. ; _item.name '_diffrn_scan_axis.reference_angle' _item.category_id diffrn_scan_axis _item.mandatory_code implicit _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.reference_displacement _item_description.description ; The setting of the specified axis in millimetres against which measurements of the reference beam center and reference detector distance should be made. In general, this will agree with _diffrn_scan_frame_axis.reference_displacement. If the individual frame values vary, then the value of _diffrn_scan_axis.reference_displacement will be representative of the ensemble of values of _diffrn_scan_frame_axis.reference_displacement (e.g. the mean). If not specified, the value defaults to to the value of _diffrn_scan_axis.displacement. ; _item.name '_diffrn_scan_axis.reference_displacement' _item.category_id diffrn_scan_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'millimetres' save_ ##################### # DIFFRN_SCAN_FRAME # ##################### save_DIFFRN_SCAN_FRAME _category.description ; Data items in the DIFFRN_SCAN_FRAME category describe the relationships of particular frames to scans. ; _category.id diffrn_scan_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame.scan_id' '_diffrn_scan_frame.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame.date _item_description.description ; The date and time of the start of the frame being scanned. ; _item.name '_diffrn_scan_frame.date' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan_frame.frame_id _item_description.description ; The value of this data item is the identifier of the frame being examined. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame.frame_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame.frame_number _item_description.description ; The value of this data item is the number of the frame within the scan, starting with 1. It is not necessarily the same as the value of _diffrn_scan_frame.frame_id, but it may be. ; _item.name '_diffrn_scan_frame.frame_number' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 0 0 0 save_ save__diffrn_scan_frame.integration_time _item_description.description ; The time in seconds to integrate this step of the scan. This should be the precise time of integration of each particular frame. The value of this data item should be given explicitly for each frame and not inferred from the value of _diffrn_scan.integration_time. ; _item.name '_diffrn_scan_frame.integration_time' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame.scan_id _item_description.description ; The value of _diffrn_scan_frame.scan_id identifies the scan containing this frame. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_frame.scan_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ ########################## # DIFFRN_SCAN_FRAME_AXIS # ########################## save_DIFFRN_SCAN_FRAME_AXIS _category.description ; Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the settings of axes for particular frames. Unspecified axes are assumed to be at their zero points. If, for any given frame, nonzero values apply for any of the data items in this category, those values should be given explicitly in this category and not simply inferred from values in DIFFRN_SCAN_AXIS. ; _category.id diffrn_scan_frame_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame_axis.frame_id' '_diffrn_scan_frame_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the frame for which settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_frame_axis.axis_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_axis.angle _item_description.description ; The setting of the specified axis in degrees for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.angle' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_increment _item_description.description ; The increment for this frame for the angular setting of the specified axis in degrees. The sum of the values of _diffrn_scan_frame_axis.angle and _diffrn_scan_frame_axis.angle_increment is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.angle_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_rstrt_incr _item_description.description ; The increment after this frame for the angular setting of the specified axis in degrees. The sum of the values of _diffrn_scan_frame_axis.angle, _diffrn_scan_frame_axis.angle_increment and _diffrn_scan_frame_axis.angle_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame and should equal _diffrn_scan_frame_axis.angle for this next frame. ; _item.name '_diffrn_scan_frame_axis.angle_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.displacement' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_increment _item_description.description ; The increment for this frame for the displacement setting of the specified axis in millimetres. The sum of the values of _diffrn_scan_frame_axis.displacement and _diffrn_scan_frame_axis.displacement_increment is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.displacement_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_rstrt_incr _item_description.description ; The increment for this frame for the displacement setting of the specified axis in millimetres. The sum of the values of _diffrn_scan_frame_axis.displacement, _diffrn_scan_frame_axis.displacement_increment and _diffrn_scan_frame_axis.displacement_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame and should equal _diffrn_scan_frame_axis.displacement for this next frame. ; _item.name '_diffrn_scan_frame_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.frame_id _item_description.description ; The value of this data item is the identifier of the frame for which axis settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame_axis.frame_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_axis.reference_angle _item_description.description ; The setting of the specified axis in degrees against which measurements of the reference beam center and reference detector distance should be made. This is normally the same for all frames, but the option is provided here of making changes when needed. If not provided, it is assumed to be zero. ; _item.name '_diffrn_scan_frame_axis.reference_angle' _item.category_id diffrn_scan_frame_axis _item.mandatory_code implicit _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.reference_displacement _item_description.description ; The setting of the specified axis in millimetres for this frame against which measurements of the reference beam center and reference detector distance should be made. This is normally the same for all frames, but the option is provided here of making changes when needed. If not provided, it is assumed to be equal to _diffrn_scan_frame_axis.displacement. ; _item.name '_diffrn_scan_frame_axis.reference_displacement' _item.category_id diffrn_scan_frame_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'millimetres' save_ ####### # MAP # ####### save_MAP _category.description ; Data items in the MAP category record the details of a maps. Maps record values of parameters, such as density, that are functions of position within a cell or are functions of orthogonal coordinates in three space. A map may is composed of one or more map segments specified in the MAP_SEGMENT category. Examples are given in the MAP_SEGMENT category. ; _category.id map _category.mandatory_code no loop_ _category_key.name '_map.id' '_map.diffrn_id' '_map.entry_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Identifying an observed density map and a calculated density map ; ; loop_ _map.id _map.details rho_calc ; density calculated from F_calc derived from the ATOM_SITE list ; rho_obs ; density combining the observed structure factors with the calculated phases ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__map.details _item_description.description ; The value of _map.details should give a description of special aspects of each map. ; _item.name '_map.details' _item.category_id map _item.mandatory_code no _item_type.code text loop_ _item_examples.case _item_examples.detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Identifying an observed density map and a calculated density map ; ; loop_ _map.id _map.details rho_calc ; density calculated from F_calc derived from the ATOM_SITE list ; rho_obs ; density combining the observed structure factors with the calculated phases ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__map.diffrn_id _item_description.description ; This item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_map.diffrn_id' _item.category_id map _item.mandatory_code implicit _item_type.code code save_ save__map.entry_id _item_description.description ; This item is a pointer to _entry.id in the ENTRY category. ; _item.name '_map.entry_id' _item.category_id map _item.mandatory_code implicit _item_type.code code save_ save__map.id _item_description.description ; The value of _map.id must uniquely identify each map for the given diffrn.id or entry.id. ; loop_ _item.name _item.category_id _item.mandatory_code '_map.id' map yes '_map_segment.id' map_segment yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_map_segment.id' '_map.id' save_ ########################### # MAP_SEGMENT # ########################### save_MAP_SEGMENT _category.description ; Data items in the MAP_SEGMENT category record the details about each segment (section or brick) of a map. ; _category.id map_segment _category.mandatory_code no loop_ _category_key.name '_map_segment.id' '_map_segment.map_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Identifying an observed density map and a calculated density map, each consisting of one segment, both using the same array structure and mask. ; ; loop_ _map.id _map.details rho_calc ; density calculated from F_calc derived from the ATOM_SITE list ; rho_obs ; density combining the observed structure factors with the calculated phases ; loop_ _map_segment.map_id _map_segment.id _map_segment.array_id _map_segment.binary_id _map_segment.mask_array_id _map_segment.mask_binary_id rho_calc rho_calc map_structure 1 mask_structure 1 rho_obs rho_obs map_structure 2 mask_structure 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__map_segment.array_id _item_description.description ; The value of _map_segment.array_id identifies the array structure into which the map is organized. This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_map_segment.array_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code code save_ save__map_segment.binary_id _item_description.description ; The value of _map_segment.binary_id distinguishes the particular set of data organized according to _map_segment.array_id in which the data values of the map are stored. This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_map_segment.binary_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code int save_ save__map_segment.mask_array_id _item_description.description ; The value of _map_segment.mask_array_id, if given, the array structure into which the mask for the map is organized. If no value is given, then all elements of the map are valid. If a value is given, then only elements of the map for which the corresponding element of the mask is non-zero are valid. The value of _map_segment.mask_array_id differs from the value of _map_segment.array_id in order to permit the mask to be given as, say, unsigned 8-bit integers, while the map is given as a data type with more range. However, the two array structures must be aligned, using the same axes in the same order with the same displacements and increments This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_map_segment.mask_array_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code code save_ save__map_segment.mask_binary_id _item_description.description ; The value of _map_segment.mask_binary_id identifies the particular set of data organized according to _map_segment.mask_array_id specifying the mask for the map. This item is a pointer to _array_data.mask_binary_id in the ARRAY_DATA category. ; _item.name '_map_segment.mask_binary_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code int save_ save__map_segment.id _item_description.description ; The value of _map_segment.id must uniquely identify each segment of a map. ; loop_ _item.name _item.category_id _item.mandatory_code '_map_segment.id' map_segment yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_map_data_frame.map_segment_id' '_map_segment.id' save_ save__map_segment.map_id _item_description.description ; This item is a pointer to _map.id in the MAP category. ; _item.name '_map_segment.map_id' _item.category_id map_segment _item.mandatory_code yes _item_type.code code save_ save__map_segment.details _item_description.description ; The value of _map_segment.details should give a description of special aspects of each segment of a map. ; _item.name '_map_segment.details' _item.category_id map_segment _item.mandatory_code no _item_type.code text loop_ _item_examples.case _item_examples.detail ; Example to be provided ; ; ; save_ ######################## DEPRECATED DATA ITEMS ######################## save__diffrn_detector_axis.id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_detector_axis.id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_element.center[1] _item_description.description ; The value of _diffrn_detector_element.center[1] is the X component of the distortion-corrected beam centre in millimetres from the (0, 0) (lower-left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. Because of ambiguity about the setting used to determine this center, use of this data item is deprecated. The data item _diffrn_data_frame.center_fast which is referenced to the detector coordinate system and not directly to the laboratory coordinate system should be used instead. ; _item.name '_diffrn_detector_element.center[1]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.center[2] _item_description.description ; The value of _diffrn_detector_element.center[2] is the Y component of the distortion-corrected beam centre in millimetres from the (0, 0) (lower-left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. Because of ambiguity about the setting used to determine this center, use of this data item is deprecated. The data item _diffrn_data_frame.center_slow which is referenced to the detector coordinate system and not directly to the laboratory coordinate system should be used instead. ; _item.name '_diffrn_detector_element.center[2]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_measurement_axis.id _item_description.description ; This data item is a pointer to _diffrn_measurement.id in the DIFFRN_MEASUREMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_measurement_axis.id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ ######################### DEPRECATED CATEGORY ######################### ##################### # DIFFRN_FRAME_DATA # ##################### save_DIFFRN_FRAME_DATA _category.description ; Data items in the DIFFRN_FRAME_DATA category record the details about each frame of data. The items in this category are now in the DIFFRN_DATA_FRAME category. The items in the DIFFRN_FRAME_DATA category are now deprecated. The items from this category are provided as aliases in the 1.0 dictionary or, in the case of _diffrn_frame_data.details, in the 1.4 dictionary. THESE ITEMS SHOULD NOT BE USED FOR NEW WORK. The items from the old category are provided in this dictionary for completeness but should not be used or cited. To avoid confusion, the example has been removed and the redundant parent-child links to other categories have been removed. ; _category.id diffrn_frame_data _category.mandatory_code no loop_ _category_key.name '_diffrn_frame_data.id' '_diffrn_frame_data.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; THE DIFFRN_FRAME_DATA category is deprecated and should not be used. ; ; # EXAMPLE REMOVED # ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_frame_data.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.array_id' _item.category_id diffrn_frame_data _item.mandatory_code implicit _item_type.code code save_ save__diffrn_frame_data.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.binary_id' _item.category_id diffrn_frame_data _item.mandatory_code implicit _item_type.code int save_ save__diffrn_frame_data.detector_element_id _item_description.description ; This item is a pointer to _diffrn_detector_element.id in the DIFFRN_DETECTOR_ELEMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.detector_element_id' _item.category_id diffrn_frame_data _item.mandatory_code yes _item_type.code code save_ save__diffrn_frame_data.id _item_description.description ; The value of _diffrn_frame_data.id must uniquely identify each complete frame of data. DEPRECATED -- DO NOT USE ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_frame_data.id' diffrn_frame_data yes _item_type.code code save_ save__diffrn_frame_data.details _item_description.description ; The value of _diffrn_data_frame.details should give a description of special aspects of each frame of data. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.details' _item.category_id diffrn_frame_data _item.mandatory_code no _item_type.code text save_ ################ END DEPRECATED SECTION ########### #################### ## ITEM_TYPE_LIST ## #################### # # # The regular expressions defined here are not compliant # with the POSIX 1003.2 standard as they include the # '\n' and '\t' special characters. These regular expressions # have been tested using version 0.12 of Richard Stallman's # GNU regular expression library in POSIX mode. # In order to allow presentation of a regular expression # in a text field concatenate any line ending in a backslash # with the following line, after discarding the backslash. # # A formal definition of the '\n' and '\t' special characters # is most properly done in the DDL, but for completeness, please # note that '\n' is the line termination character ('newline') # and '\t' is the horizontal tab character. There is a formal # ambiguity in the use of '\n' for line termination, in that # the intention is that the equivalent machine/OS-dependent line # termination character sequence should be accepted as a match, e.g. # # '\r' (control-M) under MacOS # '\n' (control-J) under Unix # '\r\n' (control-M control-J) under DOS and MS Windows # loop_ _item_type_list.code _item_type_list.primitive_code _item_type_list.construct _item_type_list.detail code char '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words ... ; ucode uchar '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words (case insensitive) ... ; line char '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; char item types / multi-word items ... ; uline uchar '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; char item types / multi-word items (case insensitive)... ; text char '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; text item types / multi-line text ... ; binary char ;\n--CIF-BINARY-FORMAT-SECTION--\n\ [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\ \n--CIF-BINARY-FORMAT-SECTION---- ; ; binary items are presented as MIME-like ascii-encoded sections in an imgCIF. In a CBF, raw octet streams are used to convey the same information. ; int numb '-?[0-9]+' ; int item types are the subset of numbers that are the negative or positive integers. ; float numb '-?(([0-9]+)[.]?|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?' ; float item types are the subset of numbers that are the floating point numbers. ; any char '.*' ; A catch all for items that may take any form... ; yyyy-mm-dd char ;\ [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9]?[0-9]\ ((T[0-2][0-9](:[0-5][0-9](:[0-5][0-9](.[0-9]+)?)?)?)?\ ([+-][0-5][0-9]:[0-5][0-9]))? ; ; Standard format for CIF date and time strings (see http://www.iucr.org/iucr-top/cif/spec/datetime.html), consisting of a yyyy-mm-dd date optionally followed by the character 'T' followed by a 24-hour clock time, optionally followed by a signed time-zone offset. The IUCr standard has been extended to allow for an optional decimal fraction on the seconds of time. Time is local time if no time-zone offset is given. Note that this type extends the mmCIF yyyy-mm-dd type but does not conform to the mmCIF yyyy-mm-dd:hh:mm type that uses a ':' in place if the 'T' specified by the IUCr standard. For reading, both forms should be accepted, but for writing, only the IUCr form should be used. For maximal compatibility, the special time zone indicator 'Z' (for 'zulu') should be accepted on reading in place of '+00:00' for GMT. ; ##################### ## ITEM_UNITS_LIST ## ##################### loop_ _item_units_list.code _item_units_list.detail # 'metres' 'metres' 'centimetres' 'centimetres (metres * 10^( -2)^)' 'millimetres' 'millimetres (metres * 10^( -3)^)' 'nanometres' 'nanometres (metres * 10^( -9)^)' 'angstroms' '\%Angstroms (metres * 10^(-10)^)' 'picometres' 'picometres (metres * 10^(-12)^)' 'femtometres' 'femtometres (metres * 10^(-15)^)' # 'reciprocal_metres' 'reciprocal metres (metres^(-1)^)' 'reciprocal_centimetres' 'reciprocal centimetres ((metres * 10^( -2)^)^(-1)^)' 'reciprocal_millimetres' 'reciprocal millimetres ((metres * 10^( -3)^)^(-1)^)' 'reciprocal_nanometres' 'reciprocal nanometres ((metres * 10^( -9)^)^(-1)^)' 'reciprocal_angstroms' 'reciprocal \%Angstroms ((metres * 10^(-10)^)^(-1)^)' 'reciprocal_picometres' 'reciprocal picometres ((metres * 10^(-12)^)^(-1)^)' # 'nanometres_squared' 'nanometres squared (metres * 10^( -9)^)^2^' 'angstroms_squared' '\%Angstroms squared (metres * 10^(-10)^)^2^' '8pi2_angstroms_squared' '8\p^2^ * \%Angstroms squared (metres * 10^(-10)^)^2^' 'picometres_squared' 'picometres squared (metres * 10^(-12)^)^2^' # 'nanometres_cubed' 'nanometres cubed (metres * 10^( -9)^)^3^' 'angstroms_cubed' '\%Angstroms cubed (metres * 10^(-10)^)^3^' 'picometres_cubed' 'picometres cubed (metres * 10^(-12)^)^3^' # 'kilopascals' 'kilopascals' 'gigapascals' 'gigapascals' # 'hours' 'hours' 'minutes' 'minutes' 'seconds' 'seconds' 'microseconds' 'microseconds' # 'degrees' 'degrees (of arc)' 'degrees_squared' 'degrees (of arc) squared' # 'degrees_per_minute' 'degrees (of arc) per minute' # 'celsius' 'degrees (of temperature) Celsius' 'kelvins' 'degrees (of temperature) Kelvin' # 'counts' 'counts' 'counts_per_photon' 'counts per photon' # 'electrons' 'electrons' # 'electrons_squared' 'electrons squared' # 'electrons_per_nanometres_cubed' ; electrons per nanometres cubed (electrons/(metres * 10^( -9)^)^(-3)^) ; 'electrons_per_angstroms_cubed' ; electrons per \%Angstroms cubed (electrons/(metres * 10^(-10)^)^(-3)^) ; 'electrons_per_picometres_cubed' ; electrons per picometres cubed (electrons/(metres * 10^(-12)^)^(-3)^) ; 'kilowatts' 'kilowatts' 'milliamperes' 'milliamperes' 'kilovolts' 'kilovolts' # 'pixels_per_element' '(image) pixels per (array) element' # 'arbitrary' ; arbitrary system of units. ; # loop_ _item_units_conversion.from_code _item_units_conversion.to_code _item_units_conversion.operator _item_units_conversion.factor ### 'metres' 'centimetres' '*' 1.0E+02 'metres' 'millimetres' '*' 1.0E+03 'metres' 'nanometres' '*' 1.0E+09 'metres' 'angstroms' '*' 1.0E+10 'metres' 'picometres' '*' 1.0E+12 'metres' 'femtometres' '*' 1.0E+15 # 'centimetres' 'metres' '*' 1.0E-02 'centimetres' 'millimetres' '*' 1.0E+01 'centimetres' 'nanometres' '*' 1.0E+07 'centimetres' 'angstroms' '*' 1.0E+08 'centimetres' 'picometres' '*' 1.0E+10 'centimetres' 'femtometres' '*' 1.0E+13 # 'millimetres' 'metres' '*' 1.0E-03 'millimetres' 'centimetres' '*' 1.0E-01 'millimetres' 'nanometres' '*' 1.0E+06 'millimetres' 'angstroms' '*' 1.0E+07 'millimetres' 'picometres' '*' 1.0E+09 'millimetres' 'femtometres' '*' 1.0E+12 # 'nanometres' 'metres' '*' 1.0E-09 'nanometres' 'centimetres' '*' 1.0E-07 'nanometres' 'millimetres' '*' 1.0E-06 'nanometres' 'angstroms' '*' 1.0E+01 'nanometres' 'picometres' '*' 1.0E+03 'nanometres' 'femtometres' '*' 1.0E+06 # 'angstroms' 'metres' '*' 1.0E-10 'angstroms' 'centimetres' '*' 1.0E-08 'angstroms' 'millimetres' '*' 1.0E-07 'angstroms' 'nanometres' '*' 1.0E-01 'angstroms' 'picometres' '*' 1.0E+02 'angstroms' 'femtometres' '*' 1.0E+05 # 'picometres' 'metres' '*' 1.0E-12 'picometres' 'centimetres' '*' 1.0E-10 'picometres' 'millimetres' '*' 1.0E-09 'picometres' 'nanometres' '*' 1.0E-03 'picometres' 'angstroms' '*' 1.0E-02 'picometres' 'femtometres' '*' 1.0E+03 # 'femtometres' 'metres' '*' 1.0E-15 'femtometres' 'centimetres' '*' 1.0E-13 'femtometres' 'millimetres' '*' 1.0E-12 'femtometres' 'nanometres' '*' 1.0E-06 'femtometres' 'angstroms' '*' 1.0E-05 'femtometres' 'picometres' '*' 1.0E-03 ### 'reciprocal_centimetres' 'reciprocal_metres' '*' 1.0E+02 'reciprocal_centimetres' 'reciprocal_millimetres' '*' 1.0E-01 'reciprocal_centimetres' 'reciprocal_nanometres' '*' 1.0E-07 'reciprocal_centimetres' 'reciprocal_angstroms' '*' 1.0E-08 'reciprocal_centimetres' 'reciprocal_picometres' '*' 1.0E-10 # 'reciprocal_millimetres' 'reciprocal_metres' '*' 1.0E+03 'reciprocal_millimetres' 'reciprocal_centimetres' '*' 1.0E+01 'reciprocal_millimetres' 'reciprocal_nanometres' '*' 1.0E-06 'reciprocal_millimetres' 'reciprocal_angstroms' '*' 1.0E-07 'reciprocal_millimetres' 'reciprocal_picometres' '*' 1.0E-09 # 'reciprocal_nanometres' 'reciprocal_metres' '*' 1.0E+09 'reciprocal_nanometres' 'reciprocal_centimetres' '*' 1.0E+07 'reciprocal_nanometres' 'reciprocal_millimetres' '*' 1.0E+06 'reciprocal_nanometres' 'reciprocal_angstroms' '*' 1.0E-01 'reciprocal_nanometres' 'reciprocal_picometres' '*' 1.0E-03 # 'reciprocal_angstroms' 'reciprocal_metres' '*' 1.0E+10 'reciprocal_angstroms' 'reciprocal_centimetres' '*' 1.0E+08 'reciprocal_angstroms' 'reciprocal_millimetres' '*' 1.0E+07 'reciprocal_angstroms' 'reciprocal_nanometres' '*' 1.0E+01 'reciprocal_angstroms' 'reciprocal_picometres' '*' 1.0E-02 # 'reciprocal_picometres' 'reciprocal_metres' '*' 1.0E+12 'reciprocal_picometres' 'reciprocal_centimetres' '*' 1.0E+10 'reciprocal_picometres' 'reciprocal_millimetres' '*' 1.0E+09 'reciprocal_picometres' 'reciprocal_nanometres' '*' 1.0E+03 'reciprocal_picometres' 'reciprocal_angstroms' '*' 1.0E+01 ### 'nanometres_squared' 'angstroms_squared' '*' 1.0E+02 'nanometres_squared' 'picometres_squared' '*' 1.0E+06 # 'angstroms_squared' 'nanometres_squared' '*' 1.0E-02 'angstroms_squared' 'picometres_squared' '*' 1.0E+04 'angstroms_squared' '8pi2_angstroms_squared' '*' 78.9568 # 'picometres_squared' 'nanometres_squared' '*' 1.0E-06 'picometres_squared' 'angstroms_squared' '*' 1.0E-04 ### 'nanometres_cubed' 'angstroms_cubed' '*' 1.0E+03 'nanometres_cubed' 'picometres_cubed' '*' 1.0E+09 # 'angstroms_cubed' 'nanometres_cubed' '*' 1.0E-03 'angstroms_cubed' 'picometres_cubed' '*' 1.0E+06 # 'picometres_cubed' 'nanometres_cubed' '*' 1.0E-09 'picometres_cubed' 'angstroms_cubed' '*' 1.0E-06 ### 'kilopascals' 'gigapascals' '*' 1.0E-06 'gigapascals' 'kilopascals' '*' 1.0E+06 ### 'hours' 'minutes' '*' 6.0E+01 'hours' 'seconds' '*' 3.6E+03 'hours' 'microseconds' '*' 3.6E+09 # 'minutes' 'hours' '/' 6.0E+01 'minutes' 'seconds' '*' 6.0E+01 'minutes' 'microseconds' '*' 6.0E+07 # 'seconds' 'hours' '/' 3.6E+03 'seconds' 'minutes' '/' 6.0E+01 'seconds' 'microseconds' '*' 1.0E+06 # 'microseconds' 'hours' '/' 3.6E+09 'microseconds' 'minutes' '/' 6.0E+07 'microseconds' 'seconds' '/' 1.0E+06 ### 'celsius' 'kelvins' '-' 273.0 'kelvins' 'celsius' '+' 273.0 ### 'electrons_per_nanometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E+03 'electrons_per_nanometres_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+09 # 'electrons_per_angstroms_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-03 'electrons_per_angstroms_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+06 # 'electrons_per_picometres_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-09 'electrons_per_picometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E-06 ### ######################## ## DICTIONARY_HISTORY ## ######################## loop_ _dictionary_history.version _dictionary_history.update _dictionary_history.revision 1.5.3 2007-07-08 ; Changes to support SLS miniCBF and suggestions from the 24 May 07 BNL imgCIF workshop (HJB) + Added new data items '_array_data.header_contents', '_array_data.header_convention', '_diffrn_data_frame.center_fast', '_diffrn_data_frame.center_slow', '_diffrn_data_frame.center_units', '_diffrn_measurement.sample_detector_distance', '_diffrn_measurement.sample_detector_voffset + Deprecated data items '_diffrn_detector_element.center[1]', '_diffrn_detector_element.center[2]' + Added comments and example on miniCBF + Changed all array_id data items to implicit ; 1.5.2 2007-05-06 ; Further clarifications of the coordinate system. (HJB) ; 1.5.1 2007-04-26 ; Improve defintion of X-axis to cover the case of no goniometer and clean up more line folds (HJB) ; 1.5 2007-07-25 ; This is a cummulative list of the changes proposed since the imgCIF workshop in Hawaii in July 2006. It is the result of contributions by H. J. Bernstein, A. Hammersley, J. Wright and W. Kabsch. 2007-02-19 Consolidated changes (edited by HJB) + Added new data items '_array_structure.compression_type_flag', '_array_structure_list_axis.fract_displacement', '_array_structure_list_axis.displacement_increment', '_array_structure_list_axis.reference_angle', '_array_structure_list_axis.reference_displacement', '_axis.system', '_diffrn_detector_element.reference_center_fast', '_diffrn_detector_element.reference_center_slow', '_diffrn_scan_axis.reference_angle', '_diffrn_scan_axis.reference_displacement', '_map.details', '_map.diffrn_id', '_map.entry_id', '_map.id', '_map_segment.array_id', '_map_segment.binary_id', '_map_segment.mask_array_id', '_map_segment.mask_binary_id', '_map_segment.id', '_map_segment.map_id', '_map_segment.details. + Change type of '_array_structure.byte_order' and '_array_structure.compression_type' to ucode to make these values case-insensitive + Add values 'packed_v2' and 'byte_offset' to enumeration of values for '_array_structure.compression_type' + Add to defintions for the binary data type to handle new compression types, maps, and a variety of new axis types. 2007-07-25 Cleanup of typos for formal release (HJB) + Corrected text fields for reference_ tag descriptions that were off by one column + Fix typos in comments listing fract_ tags + Changed name of release from 1.5_DRAFT to 1.5 + Fix unclosed text fields in various map definitions ; 1.4 2006-07-04 ; This is a change to reintegrate all changes made in the course of publication of ITVG, by the RCSB from April 2005 through August 2008 and changes for the 2006 imgCIF workshop in Hawaii. 2006-07-04 Consolidated changes for the 2006 imgCIF workshop (edited by HJB) + Correct type of '_array_structure_list.direction' from 'int' to 'code'. + Added new data items suggested by CN '_diffrn_data_frame.details' '_array_intensities.pixel_fast_bin_size', '_array_intensities.pixel_slow_bin_size and '_array_intensities.pixel_binning_method + Added deprecated item for completeness '_diffrn_frame_data.details' + Added entry for missing item in contents list '_array_structure_list_axis.displacement' + Added new MIME type X-BASE32K based on work by VL, KM, GD, HJB + Correct description of MIME boundary delimiter to start in column 1. + General cleanup of text fields to conform to changes for ITVG by removing empty lines at start and finish of text field. + Amend example for ARRAY_INTENSITIES to include binning. + Add local copy of type specification (as 'code') for all children of '_diffrn.id'. + For consistency, change all references to 'pi' to '\p' and all references to 'Angstroms' to '\%Angstroms'. + Clean up all powers to use IUCr convention of '^power^', as in '10^3^' for '10**3'. + Update 'yyyy-mm-dd' type regex to allow truncation from the right and improve comments to explain handling of related mmCIF 'yyyy-mm-dd:hh:mm' type, and use of 'Z' for GMT time zone. 2005-03-08 and 2004-08-08 fixed cases where _item_units.code used instead of _item_type.code (JDW) 2004-04-15 fixed item ordering in _diffrn_measurement_axis.measurement_id added sub_category 'vector' (JDW) ; 1.3.2 2005-06-25 ; 2005-06-25 ITEM_TYPE_LIST: code, ucode, line, uline regexps updated to those of current mmCIF; float modified by allowing integers terminated by a point as valid. The 'time' part of yyyy-mm-dd types made optional in the regexp. (BM) 2005-06-17 Minor corrections as for proofs for IT G Chapter 4.6 (NJA) 2005-02-21 Minor corrections to spelling and punctuation (NJA) 2005-01-08 Changes as per Nicola Ashcroft. + Updated example 1 for DIFFRN_MEASUREMENT to agree with mmCIF. + Spelled out "micrometres" for "um" and "millimetres" for "mm". + Removed phrase "which may be stored" from ARRAY_STRUCTURE description. + Removed unused 'byte-offsets' compressions and updated cites to ITVG for '_array_structure.compression_type'. (HJB) ; 1.3.1 2003-08-13 ; Changes as per Frances C. Bernstein. + Identify initials. + Adopt British spelling for centre in text. + Set \p and \%Angstrom and powers. + Clean up commas and unclear wordings. + Clean up tenses in history. Changes as per Gotzon Madariaga. + Fix the ARRAY_DATA example to align '_array_data.binary_id' and X-Binary-ID. + Add a range to '_array_intensities.gain_esd'. + In the example of DIFFRN_DETECTOR_ELEMENT, '_diffrn_detector_element.id' and '_diffrn_detector_element.detector_id' interchanged. + Fix typos for direction, detector and axes. + Clarify description of polarisation. + Clarify axes in '_diffrn_detector_element.center[1]' '_diffrn_detector_element.center[2]'. + Add local item types for items that are pointers. (HJB) ; 1.3.0 2003-07-24 ; Changes as per Brian McMahon. + Consistently quote tags embedded in text. + Clean up introductory comments. + Adjust line lengths to fit in 80 character window. + Fix several descriptions in AXIS category which referred to '_axis.type' instead of the current item. + Fix erroneous use of deprecated item '_diffrn_detector_axis.id' in examples for DIFFRN_SCAN_AXIS. + Add deprecated items '_diffrn_detector_axis.id' and '_diffrn_measurement_axis.id'. (HJB) ; 1.2.4 2003-07-14 ; Changes as per I. David Brown. + Enhance descriptions in DIFFRN_SCAN_AXIS to make them less dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS. + Provide a copy of the deprecated DIFFRN_FRAME_DATA category for completeness. (HJB) ; 1.2.3 2003-07-03 ; Cleanup to conform to ITVG. + Correct sign error in ..._cubed units. + Correct '_diffrn_radiation.polarisn_norm' range. (HJB) ; 1.2.2 2003-03-10 ; Correction of typos in various DIFFRN_SCAN_AXIS descriptions. (HJB) ; 1.2.1 2003-02-22 ; Correction of ATOM_ for ARRAY_ typos in various descriptions. (HJB) ; 1.2 2003-02-07 ; Corrections to encodings (remove extraneous hyphens) remove extraneous underscore in '_array_structure.encoding_type' enumeration. Correct typos in items units list. (HJB) ; 1.1.3 2001-04-19 ; Another typo corrections by Wilfred Li, and cleanup by HJB. ; 1.1.2 2001-03-06 ; Several typo corrections by Wilfred Li. ; 1.1.1 2001-02-16 ; Several typo corrections by JW. ; 1.1 2001-02-06 ; Draft resulting from discussions on header for use at NSLS. (HJB) + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME. + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'. + Add '_diffrn_measurement_axis.measurement_device' and change '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'. + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source', '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm', '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end', '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr', '_diffrn_scan_axis.displacement_rstrt_incr', '_diffrn_scan_frame_axis.angle_increment', '_diffrn_scan_frame_axis.angle_rstrt_incr', '_diffrn_scan_frame_axis.displacement', '_diffrn_scan_frame_axis.displacement_increment',and '_diffrn_scan_frame_axis.displacement_rstrt_incr'. + Add '_diffrn_measurement.device' to category key. + Update yyyy-mm-dd to allow optional time with fractional seconds for time stamps. + Fix typos caught by RS. + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to allow for coupled axes, as in spiral scans. + Add examples for fairly complete headers thanks to R. Sweet and P. Ellis. ; 1.0 2000-12-21 ; Release version - few typos and tidying up. (BM & HJB) + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end of dictionary. + Alphabetize dictionary. ; 0.7.1 2000-09-29 ; Cleanup fixes. (JW) + Correct spelling of diffrn_measurement_axis in '_axis.id' + Correct ordering of uses of '_item.mandatory_code' and '_item_default.value'. ; 0.7.0 2000-09-09 ; Respond to comments by I. David Brown. (HJB) + Add further comments on '\n' and '\t'. + Update ITEM_UNITS_LIST by taking section from mmCIF dictionary and adding metres. Change 'meter' to 'metre' throughout. + Add missing enumerations to '_array_structure.compression_type' and make 'none' the default. + Remove parent-child relationship between '_array_structure_list.index' and '_array_structure_list.precedence'. + Improve alphabetization. + Fix '_array_intensities_gain.esd' related function. + Improve comments in AXIS. + Fix DIFFRN_FRAME_DATA example. + Remove erroneous DIFFRN_MEASUREMENT example. + Add '_diffrn_measurement_axis.id' to the category key. ; 0.6.0 1999-01-14 ; Remove redundant information for ENC_NONE data. (HJB) + After the D5 remove binary section identifier, size and compression type. + Add Control-L to header. ; 0.5.1 1999-01-03 ; Cleanup of typos and syntax errors. (HJB) + Cleanup example details for DIFFRN_SCAN category. + Add missing quote marks for '_diffrn_scan.id' definition. ; 0.5 1999-01-01 ; Modifications for axis definitions and reduction of binary header. (HJB) + Restore '_diffrn_detector.diffrn_id' to DIFFRN_DETECTOR KEY. + Add AXIS category. + Bring in complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories from cif_mm.dic for clarity. + Change '_array_structure.encoding_type' from type code to uline and added X-Binary-Element-Type to MIME header. + Add detector beam centre '_diffrn_detector_element.center[1]' and '_diffrn_detector_element.center[2]'. + Correct item name of '_diffrn_refln.frame_id'. + Replace reference to '_array_intensities.undefined' by '_array_intensities.undefined_value'. + Replace references to '_array_intensity.scaling' with '_array_intensities.scaling'. + Add DIFFRN_SCAN... categories. ; 0.4 1998-08-11 ; Modifications to the 0.3 imgCIF draft. (HJB) + Reflow comment lines over 80 characters and corrected typos. + Update examples and descriptions of MIME encoded data. + Change name to cbfext98.dic. ; 0.3 1998-07-04 ; Modifications for imgCIF. (HJB) + Add binary type, which is a text field containing a variant on MIME encoded data. + Change type of '_array_data.data' to binary and specify internal structure of raw binary data. + Add '_array_data.binary_id', and make '_diffrn_frame_data.binary_id' and '_array_intensities.binary_id' into pointers to this item. ; 0.2 1997-12-02 ; Modifications to the CBF draft. (JW) + Add category hierarchy for describing frame data developed from discussions at the BNL imgCIF Workshop Oct 1997. The following changes are made in implementing the workshop draft. Category DIFFRN_ARRAY_DATA is renamed to DIFFRN_FRAME_DATA. Category DIFFRN_FRAME_TYPE is renamed to DIFFRN_DETECTOR_ELEMENT. The parent item for '_diffrn_frame_data.array_id' is changed from '_array_structure_list.array_id' to '_array_structure.id'. Item '_diffrn_detector.array_id' is deleted. + Add data item '_diffrn_frame_data.binary_id' to identify data groups within a binary section. The formal identification of the binary section is still fuzzy. ; 0.1 1997-01-24 ; First draft of this dictionary in DDL 2.1 compliant format by John Westbrook (JW). This version is adapted from the Crystallographic Binary File (CBF) Format Draft Proposal provided by Andy Hammersley (AH). Modifications to the CBF draft. (JW) + In this version the array description has been cast in the categories ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. These categories have been generalized to describe array data of arbitrary dimension. + Array data in this description are contained in the category ARRAY_DATA. This departs from the CBF notion of data existing in some special comment. In this description, data are handled as an ordinary data item encapsulated in a character data type. Although data this manner deviates from CIF conventions, it does not violate any DDL 2.1 rules. DDL 2.1 regular expressions can be used to define the binary representation which will permit some level of data validation. In this version, the placeholder type code "any" has been used. This translates to a regular expression which will match any pattern. It should be noted that DDL 2.1 already supports array data objects although these have not been used in the current mmCIF dictionary. It may be possible to use the DDL 2.1 ITEM_STRUCTURE and ITEM_STRUCTURE_LIST categories to provide the information that is carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. By moving the array structure to the DDL level it would be possible to define an array type as well as a regular expression defining the data format. + Multiple array sections can be properly handled within a single datablock. ; #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof ./CBFlib-0.9.2.2/doc/Imap.diffrn_id.html0000644000076500007650000000466511603702115016055 0ustar yayayaya (IUCr) CIF Definition save__map.diffrn_id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_map.diffrn_id

Name:
'_map.diffrn_id'

Definition:

       This item is a pointer to _diffrn.id in the
              DIFFRN category.

Type: code

Mandatory item: implicit

Category: map

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Iarray_structure.encoding_type.html0000644000076500007650000001073411603702115021433 0ustar yayayaya (IUCr) CIF Definition save__array_structure.encoding_type

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_array_structure.encoding_type

Name:
'_array_structure.encoding_type'

Definition:

        Data encoding of a single element of array data.

               The type 'unsigned 1-bit integer' is used for
               packed Booleans arrays for masks.  Each element
               of the array corresponds to a single bit
               packed in unsigned 8-bit data.

               In several cases, the IEEE format is referenced.
               See IEEE Standard 754-1985 (IEEE, 1985).

               Ref: IEEE (1985). IEEE Standard for Binary Floating-Point
               Arithmetic. ANSI/IEEE Std 754-1985. New York: Institute of
               Electrical and Electronics Engineers.

Type: uline

Mandatory item: yes


The data value must be one of the following:


'unsigned 1-bit integer'

'unsigned 8-bit integer'

'signed 8-bit integer'

'unsigned 16-bit integer'

'signed 16-bit integer'

'unsigned 32-bit integer'

'signed 32-bit integer'

'signed 32-bit real IEEE'

'signed 64-bit real IEEE'

'signed 32-bit complex IEEE'

Category: array_structure

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_scan.integration_time.html0000644000076500007650000000551011603702115021157 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan.integration_time

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_scan.integration_time

Name:
'_diffrn_scan.integration_time'

Definition:

        Approximate average time in seconds to integrate each
               step of the scan.  The precise time for integration
               of each particular step must be provided in
               _diffrn_scan_frame.integration_time, even
               if all steps have the same integration time.

Type: float

Mandatory item: no


The permitted range is [0.0, infinity)

Category: diffrn_scan

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_data_frame.center_units.html0000644000076500007650000001025211603702115021456 0ustar yayayaya (IUCr) CIF Definition save__diffrn_data_frame.center_units

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_data_frame.center_units

Name:
'_diffrn_data_frame.center_units'

Definition:

       The value of _diffrn_data_frame.center_units
              specifies the units in which the values of
              '_diffrn_data_frame.center_fast' and
              '_diffrn_data_frame.center_slow'
              are presented.  The default is 'mm' for millimetres.  The
              alternatives are 'pixels' and 'bins'.  In all cases the
              center distances are measured from the center of the
              first pixel, i.e. in a 2x2 binning, the measuring origin
              is offset from the centers of the bins by one half pixel
              towards the first pixel.

              If 'bins' is specified, the data in
                  '_array_intensities.pixel_fast_bin_size',
                  '_array_intensities.pixel_slow_bin_size', and
                  '_array_intensities.pixel_binning_method'
              is used to define the binning scheme.



Type: code

Mandatory item: no


The data value must be one of the following:


mm
millimetres

pixels
detector pixels

bins
detector bins

Category: diffrn_data_frame

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/cif_img.dic0000777000076500007650000000000011603751102020260 2cif_img_1.6.4_2Jul11.dicustar yayayaya./CBFlib-0.9.2.2/doc/Idiffrn_radiation.div_x_y_source.html0000644000076500007650000000665011603702115021673 0ustar yayayaya (IUCr) CIF Definition save__diffrn_radiation.div_x_y_source

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_radiation.div_x_y_source

Name:
'_diffrn_radiation.div_x_y_source'

Definition:

        Beam crossfire correlation degrees^2^ between the
               crossfire laboratory X-axis component and the crossfire
               laboratory Y-axis component (see AXIS category).

               This is a characteristic of the X-ray beam as it illuminates
               the sample (or specimen) after all monochromation and
               collimation.

               This is the mean of the products of the deviations of the
               direction of each photon in XZ plane times the deviations
               of the direction of the same photon in the YZ plane
               around the mean source beam direction.  This will be zero
               for uncorrelated crossfire.

               Note that some synchrotrons, this value is specified in
               milliradians^2^, in which case a conversion would be needed.
               To go from a value in milliradians^2^ to a value in
               degrees^2^, multiply by 0.180^2^ and divide by \p^2^.


Type: float

Mandatory item: no


Enumeration default: 0.0

Category: diffrn_radiation

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Iarray_intensities.overload.html0000644000076500007650000000473511603702115020721 0ustar yayayaya (IUCr) CIF Definition save__array_intensities.overload

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_array_intensities.overload

Name:
'_array_intensities.overload'

Definition:

        The saturation intensity level for this data array.

Type: float

Mandatory item: no

Category: array_intensities

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_measurement.diffrn_id.html0000644000076500007650000000462211603702115021146 0ustar yayayaya (IUCr) CIF Definition save__diffrn_measurement.diffrn_id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_measurement.diffrn_id

Name:
'_diffrn_measurement.diffrn_id'

Definition:

        This data item is a pointer to _diffrn.id in the DIFFRN
               category.

Type: code

Mandatory item: yes

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_radiation.inhomogeneity.html0000644000076500007650000000527311603702115021530 0ustar yayayaya (IUCr) CIF Definition save__diffrn_radiation.inhomogeneity

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_radiation.inhomogeneity

Name:
'_diffrn_radiation.inhomogeneity'

Definition:

        Half-width in millimetres of the incident beam in the
               direction perpendicular to the diffraction plane.

Type: float

Mandatory item: no

Alias:
_diffrn_radiation_inhomogeneity (cif_core.dic version 2.0.1)
The permitted range is [0.0, infinity)

Category: diffrn_radiation

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/cif_img_1.6.3.html0000777000076500007650000000000011603745056021500 2cif_img_1.6.3_26Aug10.htmlustar yayayaya./CBFlib-0.9.2.2/doc/Iarray_structure_list_axis.fract_displacement.html0000644000076500007650000000612011603702115024504 0ustar yayayaya (IUCr) CIF Definition save__array_structure_list_axis.fract_displacement

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_array_structure_list_axis.fract_displacement

Name:
'_array_structure_list_axis.fract_displacement'

Definition:

        The setting of the specified axis as a decimal fraction of
               the axis unit vector for the first data point of the array
               index with the corresponding value of
               _array_structure_list.axis_set_id.
               If the index is specified as 'increasing', this will be the
               centre of the pixel with index value 1.  If the index is
               specified as 'decreasing', this will be the centre of the
               pixel with maximum index value.

Type: float

Mandatory item: no


Enumeration default: 0.0

Category: array_structure_list_axis

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_scan_frame_axis.axis_id.html0000644000076500007650000000557311603702115021445 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan_frame_axis.axis_id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_scan_frame_axis.axis_id

Name:
'_diffrn_scan_frame_axis.axis_id'

Definition:

        The value of this data item is the identifier of one of
               the axes for the frame for which settings are being specified.

               Multiple axes may be specified for the same value of
               _diffrn_scan_frame.frame_id.

               This item is a pointer to _axis.id in the
               AXIS category.

Type: code

Mandatory item: yes

Category: diffrn_scan_frame_axis

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/cif_img.html0000777000076500007650000000000011603751102020672 2cif_img_1.6.4_2Jul11.htmlustar yayayaya./CBFlib-0.9.2.2/doc/Imap_segment.mask_binary_id.html0000644000076500007650000000557211603702115020624 0ustar yayayaya (IUCr) CIF Definition save__map_segment.mask_binary_id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_map_segment.mask_binary_id

Name:
'_map_segment.mask_binary_id'

Definition:

       The value of _map_segment.mask_binary_id identifies the
              particular set of data organized according to
              _map_segment.mask_array_id specifying the mask for the map.

              This item is a pointer to _array_data.mask_binary_id in the
              ARRAY_DATA category.

Type: int

Mandatory item: implicit

Category: map_segment

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_detector.number_of_axes.html0000644000076500007650000000656011603702115021505 0ustar yayayaya (IUCr) CIF Definition save__diffrn_detector.number_of_axes

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_detector.number_of_axes

Name:
'_diffrn_detector.number_of_axes'

Definition:

        The value of _diffrn_detector.number_of_axes gives the
               number of axes of the positioner for the detector identified
               by _diffrn_detector.id.

               The word 'positioner' is a general term used in
               instrumentation design for devices that are used to change
               the positions of portions of apparatus by linear
               translation, rotation or combinations of such motions.

               Axes which are used to provide a coordinate system for the
               face of an area detetctor should not be counted for this
               data item.

               The description of each axis should be provided by entries
               in DIFFRN_DETECTOR_AXIS.

Type: int

Mandatory item: no


The permitted range is [1, infinity)

Category: diffrn_detector

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Iarray_structure.compression_type_flag.html0000644000076500007650000000652011603702115023175 0ustar yayayaya (IUCr) CIF Definition save__array_structure.compression_type_flag

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_array_structure.compression_type_flag

Name:
'_array_structure.compression_type_flag'

Definition:

       Flags modifying the type of data-compression method used to
              compress the arraydata.

Type: ucode

Mandatory item: no


The data value must be one of the following:


uncorrelated_sections
When applying packed or packed_v2 compression on an array with uncorrelated sections, do not average in points from the prior section.

flat
When applying packed or packed_v2 compression on an array with treat the entire image as a single line set the maximum number of bits for an offset to 65 bits. The flag is included for compatibility with software prior to CBFlib_0.7.7, and should not be used for new data sets.

Category: array_structure

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/cif_img_1.6.4.html0000777000076500007650000000000011603751102021420 2cif_img_1.6.4_2Jul11.htmlustar yayayaya./CBFlib-0.9.2.2/doc/cif_img_1.1.3.html0000644000076500007650000065524611603702115015370 0ustar yayayaya cif_img.dic v1.1.3

# [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib] #

# imgCIF/CBF #

# Extensions Dictionary #

##############################################################################
#                                                                            #
#                       Image CIF Dictionary (imgCIF)                        #
#             and Crystallographic Binary File Dictionary (CBF)              #
#            Extending the Macromolecular CIF Dictionary (mmCIF)             #
#                                                                            #
#                              Version 1.1.3                                 #
#                              of 2001-04-19                                 #
#                                                                            #
#                             Adapted from the                               #
#                       imgCIF Workshop, BNL Oct 1997                        #
#                                    and                                     #
#               Crystallographic Binary File Format Draft Proposal           #
#                            by Andy Hammersley                              #
#                                                                            #
##############################################################################
#                                                                            #
#                           First DDL 2.1 Version                            #
#                                    by                                      # 
#                               John Westbrook                               #
#                           Nucleic Acid Database                            #
#                             Rutgers University                             #
#                                                                            #
##############################################################################
# These revisions by:  Herbert J. Bernstein, yaya@bernstein-plus-sons.com    #
# Incorporating comments by I. David Brown, John Westbrook, Brian McMahon.   #
# Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li and others                 #
##############################################################################

                                                                            
data_cif_img.dic


    _dictionary.title           cif_img.dic
    _dictionary.version         1.1.3
    _dictionary.datablock_id    cif_img.dic

##############################################################################
#    CONTENTS
#
#        CATEGORY_GROUP_LIST
#
#        category  ARRAY_DATA
#
#                  _array_data.array_id
#                  _array_data.binary_id
#                  _array_data.data
#
#        category  ARRAY_ELEMENT_SIZE
#        
#                  _array_element_size.array_id
#                  _array_element_size.index
#                  _array_element_size.size
#        
#        category  ARRAY_INTENSITIES
#        
#                  _array_intensities.array_id
#                  _array_intensities.binary_id
#                  _array_intensities.gain
#                  _array_intensities.gain_esd
#                  _array_intensities.linearity
#                  _array_intensities.offset
#                  _array_intensities.scaling
#                  _array_intensities.overload
#                  _array_intensities.undefined_value
#        
#        category  ARRAY_STRUCTURE
#        
#                  _array_structure.byte_order
#                  _array_structure.compression_type
#                  _array_structure.encoding_type
#                  _array_structure.id
#        
#        category  ARRAY_STRUCTURE_LIST
#        
#                  _array_structure_list.axis_set_id
#                  _array_structure_list.array_id
#                  _array_structure_list.dimension
#                  _array_structure_list.direction
#                  _array_structure_list.index
#                  _array_structure_list.precedence
#
#        category  ARRAY_STRUCTURE_LIST_AXIS
#        
#                  _array_structure_list_axis.axis_id
#                  _array_structure_list_axis.axis_set_id
#                  _array_structure_list_axis.angle
#                  _array_structure_list_axis.angle_increment
#                  _array_structure_list_axis.displacement_increment
#                  _array_structure_list_axis.angular_pitch
#                  _array_structure_list_axis.radial_pitch
#
#        category  AXIS
#        
#                  _axis.depends_on
#                  _axis.equipment
#                  _axis.id
#                  _axis.offset[1]
#                  _axis.offset[2]
#                  _axis.offset[3]
#                  _axis.type
#                  _axis.vector[1]
#                  _axis.vector[2]
#                  _axis.vector[3]
#
#        category  DIFFRN_DATA_FRAME
#
#                  _diffrn_data_frame.array_id
#                  _diffrn_data_frame.binary_id
#                  _diffrn_data_frame.detector_element_id
#                  _diffrn_data_frame.id
#
#        category  DIFFRN_DETECTOR
#        
#                  _diffrn_detector.details
#                  _diffrn_detector.detector
#                  _diffrn_detector.diffrn_id
#                  _diffrn_detector.dtime
#                  _diffrn_detector.id
#                  _diffrn_detector.number_of_axes
#                  _diffrn_detector.type
#
#        category  DIFFRN_DETECTOR_AXIS
#        
#                  _diffrn_detector_axis.axis_id
#                  _diffrn_detector_axis.detector_id    
#        
#        category  DIFFRN_DETECTOR_ELEMENT
#
#                  _diffrn_detector_element.center[1]
#                  _diffrn_detector_element.center[2]
#                  _diffrn_detector_element.id
#                  _diffrn_detector_element.detector_id
#        
#        category  DIFFRN_MEASUREMENT
#        
#                  _diffrn_measurement.diffrn_id
#                  _diffrn_measurement.details
#                  _diffrn_measurement.device
#                  _diffrn_measurement.device_details
#                  _diffrn_measurement.device_type
#                  _diffrn_measurement.id
#                  _diffrn_measurement.method
#                  _diffrn_measurement.number_of_axes
#                  _diffrn_measurement.specimen_support
#
#        category  DIFFRN_MEASUREMENT_AXIS
#        
#                  _diffrn_measurement_axis.axis_id
#                  _diffrn_measurement_axis.measurement_device
#                  _diffrn_measurement_axis.measurement_id
#
#        category  DIFFRN_RADIATION
#
#                  _diffrn_radiation.collimation
#                  _diffrn_radiation.diffrn_id
#                  _diffrn_radiation.div_x_source
#                  _diffrn_radiation.div_y_source
#                  _diffrn_radiation.div_x_y_source
#                  _diffrn_radiation.filter_edge'
#                  _diffrn_radiation.inhomogeneity
#                  _diffrn_radiation.monochromator
#                  _diffrn_radiation.polarisn_norm
#                  _diffrn_radiation.polarisn_ratio
#                  _diffrn_radiation.polarizn_source_norm
#                  _diffrn_radiation.polarizn_source_ratio
#                  _diffrn_radiation.probe
#                  _diffrn_radiation.type
#                  _diffrn_radiation.xray_symbol
#                  _diffrn_radiation.wavelength_id
#        
#        category  DIFFRN_REFLN
#        
#                  _diffrn_refln.frame_id
#
#        category  DIFFRN_SCAN
#        
#                  _diffrn_scan.id
#                  _diffrn_scan.date_end
#                  _diffrn_scan.date_start
#                  _diffrn_scan.integration_time
#                  _diffrn_scan.frame_id_start
#                  _diffrn_scan.frame_id_end
#                  _diffrn_scan.frames
#
#        category  DIFFRN_SCAN_AXIS
#        
#                  _diffrn_scan_axis.axis_id
#                  _diffrn_scan_axis.angle_start
#                  _diffrn_scan_axis.angle_range
#                  _diffrn_scan_axis.angle_increment
#                  _diffrn_scan_axis.angle_rstrt_incr
#                  _diffrn_scan_axis.displacement_start
#                  _diffrn_scan_axis.displacement_range
#                  _diffrn_scan_axis.displacement_increment
#                  _diffrn_scan_axis.displacement_rstrt_incr
#                  _diffrn_scan_axis.scan_id
#
#        category  DIFFRN_SCAN_FRAME
#        
#                  _diffrn_scan_frame.date
#                  _diffrn_scan_frame.frame_id
#                  _diffrn_scan_frame.frame_number
#                  _diffrn_scan_frame.integration_time
#                  _diffrn_scan_frame.scan_id
#
#        category  DIFFRN_SCAN_FRAME_AXIS
#        
#                  _diffrn_scan_frame_axis.axis_id
#                  _diffrn_scan_frame_axis.angle
#                  _diffrn_scan_frame_axis.angle_increment
#                  _diffrn_scan_frame_axis.angle_rstrt_incr
#                  _diffrn_scan_frame_axis.displacement
#                  _diffrn_scan_frame_axis.displacement_increment
#                  _diffrn_scan_frame_axis.displacement_rstrt_incr
#                  _diffrn_scan_frame_axis.frame_id
#
#        ITEM_TYPE_LIST
#        ITEM_UNITS_LIST
#        DICTIONARY_HISTORY
#
##############################################################################


#########################
## CATEGORY_GROUP_LIST ##
#########################

     loop_
    _category_group_list.id
    _category_group_list.parent_id
    _category_group_list.description
             'inclusive_group'   .
;             Categories that belong to the dictionary extension.
;
             'array_data_group'
             'inclusive_group'
;             Categories that describe array data.
;
             'axis_group'
             'inclusive_group'
;             Categories that describe axes.
;
             'diffrn_group'
             'inclusive_group'
;            Categories that describe details of the diffraction experiment.
;
 
 
 
 
##############
# ARRAY_DATA #
##############
 
  
save_ARRAY_DATA
    _category.description
;
     Data items in the ARRAY_DATA category are the containers for
     the array data items described in category ARRAY_STRUCTURE.
;
    _category.id                   array_data
    _category.mandatory_code       no
     loop_
    _category_key.name             '_array_data.array_id'
                                   '_array_data.binary_id'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
        Example 1 -

        This example shows two binary data blocks.  The first one
        was compressed by the CBF_CANONICAL compression algorithm and
        presented as hexadecimal data.  The first character "H" on the
        data lines means hexadecimal.  It could have been "O" for octal
        or "D" for decimal.  The second character on the line shows
        the number of bytes in each word (in this case "4"), which then
        requires 8 hexadecimal digits per word.  The third character
        gives the order of octets within a word, in this case "<"
        for the ordering 4321 (i.e. "big-endian").  Alternatively the
        character ">" could have been used for the ordering 1234
        (i.e. "little-endian").  The block has a "message digest"
        to check the integrity of the data.

        The second block is similar, but uses CBF_PACKED compression
        and BASE64 encoding.  Note that the size and the digest are
        different.
;
;

        loop_
        _array_data.array_id
        _array_data.binary_id
        _array_data.data
        image_1 1
        ;
        --CIF-BINARY-FORMAT-SECTION--
        Content-Type: application/octet-stream;
             conversions="x-CBF_CANONICAL"
        Content-Transfer-Encoding: X-BASE16
        X-Binary-Size: 3927126
        X-Binary-ID: 1
        Content-MD5: u2sTJEovAHkmkDjPi+gWsg==

        # Hexadecimal encoding, byte 0, byte order ...21
        #
        H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ...
        ....
        --CIF-BINARY-FORMAT-SECTION----
        ;
        image_2 2
        ;
        --CIF-BINARY-FORMAT-SECTION--
        Content-Type: application/octet-stream;
             conversions="x-CBF-PACKED"
        Content-Transfer-Encoding: BASE64
        X-Binary-Size: 3745758
        X-Binary-ID: 1
        Content-MD5: 1zsJjWPfol2GYl2V+QSXrw==

        ELhQAAAAAAAA...
        ...
        --CIF-BINARY-FORMAT-SECTION----
        ;
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
save_
 
 
save__array_data.array_id
    _item_description.description
;             This item is a pointer to _array_structure.id in the
              ARRAY_STRUCTURE category. 
;
    _item.name                  '_array_data.array_id'
    _item.category_id             array_data
    _item.mandatory_code          yes
    _item_type.code               code
     save_
 
 
save__array_data.binary_id
    _item_description.description
;             This item is an integer identifier which, along with
              _array_data.array_id should uniquely identify the 
              particular block of array data.
              
              If _array_data.binary_id is not explicitly given,
              it defaults to 1.
              
              The value of _array_data.binary_id distinguishes
              among multiple sets of data with the same array
              structure.
              
              If the MIME header of the data array specifies a 
              value for X-Binary-Id, these values should be equal.
;
     loop_
    _item.name                  
    _item.category_id             
    _item.mandatory_code          
             '_array_data.binary_id'            array_data      
                                                                implicit
             '_diffrn_data_frame.binary_id'     diffrn_data_frame
                                                                implicit
             '_array_intensities.binary_id'     array_intensities
                                                                implicit
     loop_
    _item_linked.child_name
    _item_linked.parent_name
             '_diffrn_data_frame.binary_id'     '_array_data.binary_id'
             '_array_intensities.binary_id'     '_array_data.binary_id'

    _item_default.value           1
    _item_type.code               int
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            1  1
                            .  1
     save_
 
 
save__array_data.data
    _item_description.description
;             The value of _array_data.data contains the array data 
              encapsulated in a STAR string.
              
              The representation used is a variant on the
              Multipurpose Internet Mail Extensions (MIME) specified
              in RFC 2045-2049 by N. Freed et al.  The boundary
              delimiter used in writing an imgCIF or CBF is
              "--CIF-BINARY-FORMAT-SECTION--" (including the
              required initial "--").

              The Content-Type may be any of the discrete types permitted
              in RFC 2045; "application/octet-stream" is recommended.  
              If an octet stream was compressed, the compression should 
              be specified by the parameter 'conversions="x-CBF_PACKED"' 
              or the parameter 'conversions="x-CBF_CANONICAL"'.
              
              The Content-Transfer-Encoding may be "BASE-64",
              "Quoted-Printable", "X-BASE-8", "X-BASE-10", or
              "X-BASE-16" for an imgCIF or "BINARY" for a CBF.  The
              octal, decimal and hexadecimal transfer encodings are
              for convenience in debugging, and are not recommended
              for archiving and data interchange.
              
              In an imgCIF file, the encoded binary data begins after
              the empty line terminating the header.  In a CBF, the
              raw binary data begins after an empty line terminating
              the header and after the sequence:
                    
              Octet   Hex   Decimal  Purpose
                0     0C       12    (ctrl-L) Page break
                1     1A       26    (ctrl-Z) Stop listings in MS-DOS
                2     04       04    (Ctrl-D) Stop listings in UNIX
                3     D5      213    Binary section begins

              None of these octets are included in the calculation of
              the message size, nor in the calculation of the
              message digest.
                             
              The X-Binary-Size header specifies the size of the
              equivalent binary data in octets.  If compression was
              used, this size is the size after compression, including
              any book-keeping fields.  And adjustment is made for
              the deprecated binary formats in which 8 bytes of binary
              header are used for the compression type.  In that case,
              the 8 bytes used for the compression type is subtracted
              from the size, so that the same size will be reported
              if the compression type is supplied in the MIME header.
              Use of the MIME header is the recommended way to
              supply the compression type.  In general, no portion of
              the  binary header is included in the calculation of the size.

              The X-Binary-Element-Type header specifies the type of
              binary data in the octets, using the same descriptive
              phrases as in _array_structure.encoding_type.  The default
              value is "unsigned 32-bit integer".
              
              An MD5 message digest may, optionally, be used. The "RSA Data
              Security, Inc. MD5 Message-Digest Algorithm" should be used.
              No portion of the header is included in the calculation of the
              message digest.

              If the Transfer Encoding is "X-BASE-8", "X-BASE-10", or
              "X-BASE-16", the data is presented as octal, decimal or
              hexadecimal data organized into lines or words.  Each word
              is created by composing octets of data in fixed groups of
              2, 3, 4, 6 or 8 octets, either in the order ...4321 ("big-
              endian") or 1234... (little-endian).  If there are fewer
              than the specified number of octets to fill the last word,
              then the missing octets are presented as "==" for each
              missing octet.  Exactly two equal signs are used for each
              missing octet even for octal and decimal encoding.
              The format of lines is:

              rnd xxxxxx xxxxxx xxxxxx

              where r is "H", "O", or "D" for hexadecimal, octal or
              decimal, n is the number of octets per word. and d is "<"
              for ">" for the "...4321" and "1234..." octet orderings
              respectively.  The "==" padding for the last word should
              be on the appropriate side to correspond to the missing
              octets, e.g.

              H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000

              or

              H3> FF0700 00====

              For these hex, octal and decimal formats, only, comments
              beginning with "#" are permitted to improve readability.

              BASE64 encoding follows MIME conventions.  Octets are
              in groups of three, c1, c2, c3.  The resulting 24 bits 
              are broken into four 6-bit quantities, starting with 
              the high-order six bits (c1 >> 2) of the first octet, then
              the low-order two bits of the first octet followed by the
              high-order 4 bits of the second octet ((c1 & 3)<<4 | (c2>>4)),
              then the bottom 4 bits of the second octet followed by the
              high order two bits of the last octet ((c2 & 15)<<2 | (c3>>6)),
              then the bottom six bits of the last octet (c3 & 63).  Each
              of these four quantities is translated into an ASCII character
              using the mapping:

                        1         2         3         4         5         6
              0123456789012345678901234567890123456789012345678901234567890123
              |         |         |         |         |         |         |
              ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/

              With short groups of octets padded on the right with one "="
              if c3 is missing, and with "==" if both c2 and c3 are missing.

              QUOTED-PRINTABLE encoding also follows MIME conventions, copying
              octets without translation if their ASCII values are 32..38,
              42, 48..57, 59..60, 62, 64..126 and the octet is not a ";"
              in column 1.  All other characters are translated to =nn, where
              nn is the hexadecimal encoding of the octet.  All lines are
              "wrapped" with a terminating "=" (i.e. the MIME conventions
              for an implicit line terminator are never used).
;
    _item.name                  '_array_data.data'
    _item.category_id             array_data
    _item.mandatory_code          yes
    _item_type.code               binary
save_
 
 
######################
# ARRAY_ELEMENT_SIZE #
######################
 
 
save_ARRAY_ELEMENT_SIZE
    _category.description
;
     Data items in the ARRAY_ELEMENT_SIZE category record the physical 
     size of array elements along each array dimension.
;
    _category.id                   array_element_size
    _category.mandatory_code       no
     loop_
    _category_key.name             '_array_element_size.array_id'
                                   '_array_element_size.index'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
        Example 1 - A regular 2D array with a uniform element dimension
                    of 1220 nanometres.
;
;
        loop_
       _array_element_size.array_id  
       _array_element_size.index
       _array_element_size.size
        image_1   1    1.22e-6
        image_1   2    1.22e-6
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_
 
 
save__array_element_size.array_id
    _item_description.description
;             
              This item is a pointer to _array_structure.id in the
              ATOM_STRUCTURE category. 
;
    _item.name                  '_array_element_size.array_id'
    _item.category_id             array_element_size
    _item.mandatory_code          yes
    _item_type.code               code
     save_
 
 
save__array_element_size.index
    _item_description.description
;             
              This item is a pointer to _array_structure_list.index in the
              ATOM_STRUCTURE_LIST category. 
;
    _item.name                  '_array_element_size.index'
    _item.category_id             array_element_size
    _item.mandatory_code          yes
    _item_type.code               code
     save_
 
 
save__array_element_size.size
    _item_description.description
;
               The size in metres of an image element in this 
               dimension. This supposes that the elements are arranged
               on a regular grid.
;
    _item.name               '_array_element_size.size'
    _item.category_id          array_element_size
    _item.mandatory_code       yes 
    _item_type.code            float
    _item_units.code           'metres'
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            .   0.0
     save_
 
 
#####################
# ARRAY_INTENSITIES #
#####################
 
 
save_ARRAY_INTENSITIES
    _category.description
;
              Data items in the ARRAY_INTENSITIES category record the
              information required to recover the intensity data from 
              the set of data values stored in the ARRAY_DATA category.

              The actual detector may have a complex relationship
              between the raw intensity values and the number of
              incident photons.  In most cases, the number stored
              in the final array will have a simple linear relationship
              to the actual number of incident photons, given by
              '_array_intensities.gain'.  If raw, uncorrected values
              are presented (e.g for calibration experiments), the
              value of '_array_intensities.linearity' will be 'raw'
              and '_array_intensities.gain' will not be used.

;
    _category.id                   array_intensities
    _category.mandatory_code       no
    loop_
    _category_key.name             '_array_intensities.array_id'
                                   '_array_intensities.binary_id'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
        Example 1
;
;
        loop_
        _array_intensities.array_id
        _array_intensities.linearity 
        _array_intensities.gain      
        _array_intensities.overload  
        _array_intensities.undefined_value 
        image_1   linear  1.2    655535   0
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_
 
 
save__array_intensities.array_id
    _item_description.description
;             
              This item is a pointer to _array_structure.id in the
              ATOM_STRUCTURE category. 
;
    _item.name                  '_array_intensities.array_id'
    _item.category_id             array_intensities
    _item.mandatory_code          yes
    _item_type.code               code
     save_
 
 
save__array_intensities.binary_id
    _item_description.description
;             This item is a pointer to _array_data.binary_id in the
              ARRAY_STRUCTURE category. 
;
    _item.name                  '_array_intensities.binary_id'
    _item.category_id             array_intensities
    _item.mandatory_code          implicit
    _item_type.code               int
     save_
 
 
save__array_intensities.gain
    _item_description.description
;              
               Detector "gain". The factor by which linearized 
               intensity count values should be divided to produce
               true photon counts.
;
    _item.name              '_array_intensities.gain'
    _item.category_id          array_intensities
    _item.mandatory_code       yes
    _item_type.code            float
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            .   0.0
    _item_units.code           'counts_per_photon'
     loop_
    _item_related.related_name
    _item_related.function_code  '_array_intensities.gain_esd'
                                 'associated_value'
    save_
 
  
save__array_intensities.gain_esd
    _item_description.description
;              
              The estimated standard deviation in detector "gain".
;
    _item.name              '_array_intensities.gain_esd'
    _item.category_id          array_intensities
    _item.mandatory_code       yes
    _item_type.code            float

    _item_units.code          'counts_per_photon'
     loop_
    _item_related.related_name
    _item_related.function_code  '_array_intensities.gain'
                                 'associated_esd'
    save_
 
 
save__array_intensities.linearity
    _item_description.description
;
               The intensity linearity scaling used from raw intensity
               to the stored element value:

               'linear' is obvious

               'offset'  means that the value defined by 
               '_array_intensities.offset' should be added to each
                element value.  

               'scaling' means that the value defined by 
               '_array_intensities.scaling' should be multiplied with each 
               element value.  

               'scaling_offset' is the combination of the two previous cases, 
               with the scale factor applied before the offset value.

               'sqrt_scaled' means that the square root of raw 
               intensities multiplied by '_array_intensities.scaling' is
               calculated and stored, perhaps rounded to the nearest 
               integer. Thus, linearization involves dividing the stored
               values by '_array_intensities.scaling' and squaring the 
               result. 

               'logarithmic_scaled' means that the logarithm based 10 of
               raw intensities multiplied by '_array_intensities.scaling' 
               is calculated and stored, perhaps rounded to the nearest 
               integer. Thus, linearization involves dividing the stored
               values by '_array_intensities.scaling' and calculating 10
               to the power of this number.

               'raw' means that the data is the raw is a set of raw values
               straight from the detector.
;

    _item.name               '_array_intensities.linearity'
    _item.category_id          array_intensities
    _item.mandatory_code       yes
    _item_type.code            code
     loop_
    _item_enumeration.value   
    _item_enumeration.detail   
                              'linear' .
                              'offset'           
;
               The value defined by  '_array_intensities.offset' should 
               be added to each element value.  
;
                              'scaling'
;
               The value defined by '_array_intensities.scaling' should be 
               multiplied with each element value.  
;
                              'scaling_offset'   
;
               The combination of the scaling and offset 
               with the scale factor applied before the offset value.
;
                              'sqrt_scaled'      
;
               The square root of raw intensities multiplied by 
               '_array_intensities.scaling' is calculated and stored, 
               perhaps rounded to the nearest integer. Thus, 
               linearization involves dividing the stored
               values by '_array_intensities.scaling' and squaring the 
               result. 
;
                              'logarithmic_scaled'
;
               The logarithm based 10 of raw intensities multiplied by 
               '_array_intensities.scaling'  is calculated and stored, 
               perhaps rounded to the nearest integer. Thus, 
               linearization involves dividing the stored values by 
               '_array_intensities.scaling' and calculating 10 to the 
               power of this number.
;
                              'raw'
;
               The array consists of raw values to which no corrections have
               been applied.  While the handling of the data is similar to 
               that given for 'linear' data with no offset, the meaning of 
               the data differs in that the number of incident photons is 
               not necessarily linearly related to the number of counts 
               reported.  This value is intended for use either in 
               calibration experiments or to allow for handling more 
               complex data fitting algorithms than are allowed for by 
               this data item.
;

    save_
  
  
save__array_intensities.offset
    _item_description.description
;
               Offset value to add to array element values in the manner
               described by item _array_intensities.linearity.
;
    _item.name                 '_array_intensities.offset'
    _item.category_id          array_intensities
    _item.mandatory_code       no
    _item_type.code            float
    save_
 
 
save__array_intensities.scaling
    _item_description.description
;
               Multiplicative scaling value to be applied to array data
               in the manner described by item _array_intensities.linearity.
;
    _item.name                 '_array_intensities.scaling'
    _item.category_id          array_intensities
    _item.mandatory_code       no
    _item_type.code            float
    save_
 
 
save__array_intensities.overload
    _item_description.description
;
               The saturation intensity level for this data array.
;
    _item.name                 '_array_intensities.overload'
    _item.category_id          array_intensities
    _item.mandatory_code       no
    _item_type.code            float
    _item_units.code          'counts'
    save_
 
  
save__array_intensities.undefined_value
    _item_description.description
;
               A value to be substituted for undefined values in 
               the data array.
;
    _item.name                 '_array_intensities.undefined_value'
    _item.category_id          array_intensities
    _item.mandatory_code       no
    _item_type.code            float
    save_
 
 
###################
# ARRAY_STRUCTURE #
###################
 
 
save_ARRAY_STRUCTURE
    _category.description
;
     Data items in the ARRAY_STRUCTURE category record the organization and 
     encoding of array data which may be stored in the ARRAY_DATA category.
;
    _category.id                   array_structure
    _category.mandatory_code       no
    _category_key.name             '_array_structure.id'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
    Example 1 -
;
;
     loop_
    _array_structure.id 
    _array_structure.encoding_type        
    _array_structure.compression_type     
    _array_structure.byte_order           
     image_1       "unsigned 16-bit integer"  none  little_endian
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_
 
 
save__array_structure.byte_order
    _item_description.description
;
               The order of bytes for integer values which require more
               than 1-byte. 

               (IBM-PC's and compatibles, and Dec-Vaxes use low-byte-first
               ordered integers, whereas Hewlett Packard 700 
               series, Sun-4 and Silicon Graphics use high-byte-first
               ordered integers.  Dec-Alphas can produce/use either
               depending on a compiler switch.)
;

    _item.name                     '_array_structure.byte_order'
    _item.category_id               array_structure
    _item.mandatory_code            yes 
    _item_type.code                 code
     loop_
    _item_enumeration.value        
    _item_enumeration.detail        
                                   'big_endian'
;
        The first byte in the byte stream of the bytes which make up an 
        integer value is the most significant byte of an integer. 
;
                                   'little_endian'
;
        The last byte in the byte stream of the bytes which make up an 
        integer value is the most significant byte of an integer.
;
     save_
 
 
save__array_structure.compression_type 
    _item_description.description
;
              Type of data compression method used to compress the array
              data. 
;
    _item.name                   '_array_structure.compression_type'
    _item.category_id             array_structure
    _item.mandatory_code          no 
    _item_type.code               code
    _item_default.value           'none'
     loop_
    _item_enumeration.value       
    _item_enumeration.detail
                                  'none'
;
        Data are stored in normal format as defined by 
        '_array_structure.encoding_type' and 
        '_array_structure.byte_order'.
;
                                  'byte_offsets'
;
        Using the compression scheme defined in CBF definition
        Section 5.0.
;
                                  'packed'
;
        Using the 'packed' compression scheme, a CCP4-style packing
        (CBFlib section 3.3.2)
;
                                  'canonical'
;
        Using the 'canonical' compression scheme (CBFlib section
        3.3.1)
;
    save_
 
 
save__array_structure.encoding_type
    _item_description.description
;
               Data encoding of a single element of array data. 
               
               In several cases, the IEEE format is referenced.
               See "IEEE Standard for Binary Floating-Point Arithmetic",
               ANSI/IEEE Std 754-1985, the Institute of Electrical and
               Electronics Engineers, Inc., NY 1985.  
;

    _item.name                '_array_structure.encoding_type'
    _item.category_id          array_structure
    _item.mandatory_code       yes 
    _item_type.code            uline
     loop_
    _item_enumeration.value   
                              'unsigned 8-bit integer'
                              'signed 8-bit integer'
                              'unsigned 16-bit integer'
                              'signed 16-bit_integer'
                              'unsigned 32-bit integer'
                              'signed 32-bit integer'
                              'signed 32-bit real IEEE'
                              'signed 64-bit real IEEE'
                              'signed 32-bit complex IEEE'
     save_
 
 
save__array_structure.id
    _item_description.description
;             The value of _array_structure.id must uniquely identify 
              each item of array data. 
;
    loop_
    _item.name                  
    _item.category_id             
    _item.mandatory_code          
             '_array_structure.id'              array_structure      yes
             '_array_data.array_id'             array_data           yes
             '_array_structure_list.array_id'   array_structure_list yes
             '_array_intensities.array_id'      array_intensities    yes
             '_diffrn_data_frame.array_id'      diffrn_data_frame    yes
 

    _item_type.code               code
     loop_
    _item_linked.child_name
    _item_linked.parent_name
             '_array_data.array_id'             '_array_structure.id'
             '_array_structure_list.array_id'   '_array_structure.id'
             '_array_intensities.array_id'      '_array_structure.id'
             '_diffrn_data_frame.array_id'      '_array_structure.id'

     save_
 
 
########################
# ARRAY_STRUCTURE_LIST #
########################
 
 
save_ARRAY_STRUCTURE_LIST
    _category.description
;
     Data items in the ARRAY_STRUCTURE_LIST category record the size 
     and organization of each array dimension.

     The relationship to physical axes may be given.
;
    _category.id                   array_structure_list
    _category.mandatory_code       no
     loop_
    _category_key.name             '_array_structure_list.array_id'
                                   '_array_structure_list.index'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
        Example 1 - An image array of 1300 x 1200 elements.  The raster 
                    order of the image is left-to-right (increasing) in 
                    first dimension and bottom-to-top (decreasing) in 
                    the second dimension.
;
;
        loop_
       _array_structure_list.array_id  
       _array_structure_list.index
       _array_structure_list.dimension 
       _array_structure_list.precedence 
       _array_structure_list.direction
       _array_structure_list.axis_set_id
        image_1   1    1300    1     increasing  ELEMENT_X
        image_1   2    1200    2     decreasing  ELEMENY_Y
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_
 
 
save__array_structure_list.array_id
    _item_description.description
;             
              This item is a pointer to _array_structure.id in the
              ARRAY_STRUCTURE category. 
;
    _item.name                  '_array_structure_list.array_id'
    _item.category_id             array_structure_list
    _item.mandatory_code          yes
    _item_type.code               code
save_
 
 
save__array_structure_list.axis_set_id
    _item_description.description
;              This is a descriptor for the physical axis or set of axes 
               corresponding to an array index.
               
               This data item is related to the axes of the detector 
               itself given in DIFFRN_DETECTOR_AXIS, but usually differ
               in that the axes in this category are the axes of the
               coordinate system of reported data points, while the axes in
               DIFFRN_DETECTOR_AXIS are the physical axes 
               of the detector describing the "poise" of the detector as an
               overall physical object.
               
               If there is only one axis in the set, the identifier of 
               that axis should be used as the identifier of the set.
               
;
     loop_
    _item.name                
    _item.category_id          
    _item.mandatory_code       
           '_array_structure_list.axis_set_id'
                                  array_structure_list            yes
           '_array_structure_list_axis.axis_set_id'
                                  array_structure_list_axis       implicit
    _item_type.code               code
     loop_
    _item_linked.child_name
    _item_linked.parent_name
           '_array_structure_list_axis.axis_set_id'
                               '_array_structure_list.axis_set_id'


     save_
 
 
save__array_structure_list.dimension
    _item_description.description
;              
               The number of elements stored in the array structure in this 
               dimension.
;
    _item.name                '_array_structure_list.dimension'
    _item.category_id          array_structure_list
    _item.mandatory_code       yes 
    _item_type.code            int
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            1  1
                            .  1
     save_
 
 
save__array_structure_list.direction
    _item_description.description
;
              Identifies the direction in which this array index changes.
;
    _item.name                '_array_structure_list.direction'
    _item.category_id          array_structure_list
    _item.mandatory_code       yes 
    _item_type.code            int
     loop_
    _item_enumeration.value
    _item_enumeration.detail        

                              'increasing'
;
         Indicates the index changes from 1 to the maximum dimension.
;
                              'decreasing'
;
         Indicates the index changes from the maximum dimension to 1.
;
     save_
 
 
save__array_structure_list.index
    _item_description.description
;              
               Identifies the one-based index of the row or column in the
               array structure.
;
     loop_
    _item.name                
    _item.category_id          
    _item.mandatory_code       
           '_array_structure_list.index'        array_structure_list   yes
           '_array_structure_list.precedence'   array_structure_list   yes
           '_array_element_size.index'          array_element_size     yes

    _item_type.code            int

     loop_
    _item_linked.child_name
    _item_linked.parent_name
          '_array_element_size.index'         '_array_structure_list.index'
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            1  1
                            .  1
     save_
 
 
save__array_structure_list.precedence
    _item_description.description
;
               Identifies the rank order in which this array index changes 
               with respect to other array indices.  The precedence of 1  
               indicates the index which changes fastest.
;
    _item.name                '_array_structure_list.precedence'
    _item.category_id          array_structure_list
    _item.mandatory_code       yes 
    _item_type.code            int
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            1  1
                            .  1
     save_
 
 
#############################
# ARRAY_STRUCTURE_LIST_AXIS #
#############################
 
save_ARRAY_STRUCTURE_LIST_AXIS
    _category.description
;
     Data items in the ARRAY_STRUCTURE_LIST_AXIS category describes
     the physical settings of sets axes for the centres of pixels that 
     correspond to data points described in the 
     ARRAY_STRUCTURE_LIST category. 
     
     In the simplest cases, the physical increments of a single axis correspond
     to the increments of a single array index.  More complex organizations,
     e.g. spiral scans, may require coupled motions along multiple axes.
     
     Note that a spiral scan uses two coupled axis, one for the angular 
     direction, one for the radial direction.  This differs from a 
     cylindrical scan for which the two axes are not coupled into one set.
     
;
    _category.id                   array_structure_list_axis
    _category.mandatory_code       no
     loop_
    _category_key.name
                                  '_array_structure_list_axis.axis_set_id'
                                  '_array_structure_list_axis.axis_id'
     loop_
    _category_group.id           'inclusive_group'
                                 'array_data_group'
     save_
 
 
save__array_structure_list_axis.axis_id
    _item_description.description
;
               The value of this data item is the identifier of one of
               the axes for the set of axes for which settings are being 
               specified.

               Multiple axes may be specified for the same value of
               '_array_structure_list_axis.axis_set_id'

               This item is a pointer to _axis.id in the
               AXIS category.
;
    _item.name                 '_array_structure_list_axis.axis_id'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       yes
     save_
 
 
save__array_structure_list_axis.axis_set_id
    _item_description.description
;
               The value of this data item is the identifier of the
               set of axes for which axis settings are being specified.

               Multiple axes may be specified for the same value of
               _array_structure_list_axis.axis_set_id .

               This item is a pointer to _array_structure_list.axis_set_id
               in the ARRAY_STRUCTURE_LIST category.
               
               If this item is not specified, it defaults to the corresponding
               axis identifier.
;
    _item.name                 '_array_structure_list_axis.axis_set_id'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       implicit
     save_
 
 
save__array_structure_list_axis.angle
    _item_description.description
;
               The setting of the specified axis in degrees for the first
               data point of the array index with the corresponding value
               of '_array_structure_list.axis_set_id'.  If the index is
               specified as 'increasing' this will be the center of the
               pixel with index value 1.  If the index is specified as
               'decreasing' this will be the center of the pixel with
               maximum index value. 
;
    _item.name                 '_array_structure_list_axis.angle'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       no 
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_
 
 
save__array_structure_list_axis.angle_increment
    _item_description.description
;
               The pixel-center-to-pixel-center increment in the angular 
               setting of the specified axis in degrees.  This is not 
               meaningful in the case of 'constant velocity' spiral scans  
               and should not be specified in that case.  

               See '_array_structure_list_axis.angular_pitch'.
               
;
    _item.name                 '_array_structure_list_axis.angle_increment'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_
 
 
save__array_structure_list_axis.displacement
    _item_description.description
;
               The setting of the specified axis in millimetres for the first
               data point of the array index with the corresponding value
               of '_array_structure_list.axis_set_id'.  If the index is
               specified as 'increasing' this will be the center of the
               pixel with index value 1.  If the index is specified as
               'decreasing' this will be the center of the pixel with
               maximum index value. 

;
    _item.name               '_array_structure_list_axis.displacement'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
 
 
save__array_structure_list_axis.displacement_increment
    _item_description.description
;
               The pixel-center-to-pixel-center increment for the displacement 
               setting of the specified axis in millimetres.
               
;
    _item.name                 
        '_array_structure_list_axis.displacement_increment'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
  
 
save__array_structure_list_axis.angular_pitch
    _item_description.description
;
               The pixel-center-to-pixel-center distance for a one step 
               change in the setting of the specified axis in millimetres.
               
               This is meaningful only for 'constant velocity' spiral scans,
               or for uncoupled angular scans at a constant radius
               (cylindrical scan) and should not be specified for cases
               in which the angle between pixels, rather than the distance
               between pixels is uniform.
               
               See '_array_structure_list_axis.angle_increment'.
               
;
    _item.name               '_array_structure_list_axis.angular_pitch'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
   
 
save__array_structure_list_axis.radial_pitch
    _item_description.description
;
               The radial distance from one "cylinder" of pixels to the
               next in millimetres.  If the scan is a 'constant velocity'
               scan with differing angular displacements between pixels,
               the value of this item may differ significantly from the
               value of '_array_structure_list_axis.displacement_increment'.
               
;
    _item.name               '_array_structure_list_axis.radial_pitch'
    _item.category_id          array_structure_list_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
  

 
########
# AXIS #
########

save_AXIS
    _category.description
;
     Data items in the AXIS category record the information required
     to describe the various goniometer, detector, source and other
     axes needed to specify a data collection.  The location of each
     axis is specified by two vectors: the axis itself, given as a unit
     vector, and an offset to the base of the unit vector.  These vectors
     are referenced to a right-handed laboratory coordinate system with
     its origin in the sample or specimen:
     
                             | Y (to complete right-handed system)
                             |
                             |
                             |
                             |
                             |
                             |________________X
                            /       principal goniometer axis
                           /
                          /
                         /
                        /
                       /Z (to source)
 
 
                                                      
     Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from
     the sample or specimen along the  principal axis of the goniometer.
     
     Axis 2 (Y): The Y-axis completes an orthogonal right-handed system
     defined by the X-axis and the Z-axis (see below).
     
     Axis 3 (Z): The Z-axis is derived from the source axis which goes from 
     the sample to the source.  The Z-axis is the component of the source axis
     in the direction of the source orthogonal to the X-axis in the plane 
     defined by the X-axis and the source axis.
          
     These axes are based on the goniometer, not on the orientation of the 
     detector, gravity, etc.  The vectors necessary to specify all other
     axes are given by sets of three components in the order (X, Y, Z).
     If the axis involved is a rotation axis, it is right handed, i.e. as
     one views the object to be rotated from the origin (the tail) of the 
     unit vector, the rotation is clockwise.  If a translation axis is
     specified, the direction of the unit vector specifies the sense of
     positive translation.
     
     Note:  This choice of coordinate system is similar to, but significantly
     different from the choice in MOSFLM (Andrew G.W. Leslie, Harry Powell,
     MRC Laboratory of Molecular Biology, Hills Road, Cambridge CB2 2QH,UK
     http://www.dl.ac.uk/CCP/CCP4/dist/x-windows/Mosflm/).  In MOSFLM,
     X is along the X-ray beam (our Z axis) and Z is along the rotation axis.

     All rotations are given in degrees and all translations are given in mm.
     
     Axes may be dependent on one another.  The X-axis is the only goniometer
     axis the direction of which is strictly connected to the hardware.  All
     other axes are specified by the positions they would assume when the
     axes upon which they depend are at their zero points.
     
     When specifying detector axes, the axis is given to the beam center.
     The location of the beam center on the detector should be given in the
     DIFFRN_DETECTOR category in distortion-corrected mm from the (0,0) corner
     of the detector.
     
     It should be noted that many different origins arise in the definition
     of an experiment.  In particular, as noted above, we need to specify the
     location of the beam center on the detector in terms of the origin of the
     detector, which is, of course, not coincident with the center of the
     sample.  
;
    _category.id                   axis
    _category.mandatory_code       no
     loop_
    _category_key.name          '_axis.id' 
                                '_axis.equipment'               
     loop_
    _category_group.id           'inclusive_group'
                                 'axis_group'
                                 'diffrn_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
        Example 1 -
        
        This example shows the axis specification of the axes of a kappa
        geometry goniometer (See "X-Ray Structure Determination, A Practical
        Guide", 2nd ed. by  G. H. Stout, L. H. Jensen, Wiley Interscience,
        1989, 453 pp, p 134.).
        
        There are three axes specified, and no offsets.  The outermost axis,
        omega, is pointed along the X-axis.  The next innermost axis, kappa,
        is at a 50 degree angle to the X-axis, pointed away from the source.
        The innermost axis, phi, aligns with the X-axis when omega and
        phi are at their zero-points.  If T-omega, T-kappa and T-phi
        are the transformation matrices derived from the axis settings,
        the complete transformation would be:
            x' = (T-omega) (T-kappa) (T-phi) x
;
;
         loop_
        _axis.id
        _axis.type
        _axis.equipment
        _axis.depends_on
        _axis.vector[1] _axis.vector[2] _axis.vector[3]
        omega rotation goniometer     .    1        0        0
        kappa rotation goniometer omega    -.64279  0       -.76604
        phi   rotation goniometer kappa    1        0        0   
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
        Example 2 -
        
        This example show the axis specification of the axes of a
        detector, source and gravity.  We have juggled the order as a
        reminder that the ordering of presentation of tokens is not
        significant.  We have taken the center of rotation of the detector
        to be 68 millimetres in the direction away from the source.
;
;
        loop_
        _axis.id
        _axis.type
        _axis.equipment
        _axis.depends_on
        _axis.vector[1] _axis.vector[2] _axis.vector[3]
        _axis.offset[1] _axis.offset[2] _axis.offset[3]
        source       .        source     .       0     0     1   . . .
        gravity      .        gravity    .       0    -1     0   . . .
        tranz     translation detector rotz      0     0     1   0 0 -68
        twotheta  rotation    detector   .       1     0     0   . . .
        roty      rotation    detector twotheta  0     1     0   0 0 -68
        rotz      rotation    detector roty      0     0     1   0 0 -68
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_
 
 
save__axis.depends_on
    _item_description.description
;             The value of  _axis.type specifies the next outermost
              axis upon which this axis depends.
              
              This item is a pointer to axis.id in the same category.
;
    _item.name                      '_axis.depends_on'
    _item.category_id                 axis
    _item.mandatory_code              no

     save_
 
 
save__axis.equipment
    _item_description.description
;             The value of  _axis.type specifies the type of equipment
              using the axis:  goniometer, detector, gravity, source
              or general
;
    _item.name                      '_axis.equipment'
    _item.category_id                 axis
    _item.mandatory_code              no
    _item_type.code                   ucode
    _item_default.value               general
     loop_
    _item_enumeration.value
    _item_enumeration.detail   goniometer
                              'equipment used to orient or position samples'
                               detector
                              'equipment used to detect reflections'
                               general
                              'equipment used for general purposes'
                               gravity
                              'axis specifying the downward direction'
                               source
                              'axis specifying the direction sample to source'

     save_
 
 
save__axis.offset[1]
    _item_description.description
;              The [1] element of the 3-element vector used to specify
               the offset to the base of a rotation or translation axis.
               
               The vector is specified in millimetres
;
    _item.name                  '_axis.offset[1]'
    _item.category_id             axis
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
    _item_units.code              millimetres
     save_
 
 
save__axis.offset[2]
    _item_description.description
;              The [2] element of the 3-element vector used to specify
               the offset to the base of a rotation or translation axis.
               
               The vector is specified in millimetres
;
    _item.name                  '_axis.offset[2]'
    _item.category_id             axis
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
    _item_units.code              millimetres
     save_
 
 
save__axis.offset[3]
    _item_description.description
;              The [3] element of the 3-element vector used to specify
               the offset to the base of a rotation or translation axis.
               
               The vector is specified in millimetres
;
    _item.name                  '_axis.offset[3]'
    _item.category_id             axis
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
    _item_units.code              millimetres
     save_
 
 
save__axis.id
    _item_description.description
;             The value of _axis.id must uniquely identify
              each axis relevant to the experiment.  Note that multiple
              pieces of equipment may share the same axis (e.g. a twotheta
              arm), so that the category key for AXIS also includes the
              equipment.
;
    loop_
    _item.name
    _item.category_id
    _item.mandatory_code
         '_axis.id'                         axis                    yes
         '_array_structure_list_axis.axis_id'
                                            array_structure_list_axis
                                                                    yes
         '_diffrn_detector_axis.axis_id'    diffrn_detector_axis    yes
         '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes
         '_diffrn_scan_axis.axis_id'        diffrn_scan_axis        yes
         '_diffrn_scan_frame_axis.axis_id'  diffrn_scan_frame_axis  yes

    _item_type.code               code
     loop_
    _item_linked.child_name
    _item_linked.parent_name
         '_axis.depends_on'                   '_axis.id'
         '_array_structure_list_axis.axis_id' '_axis.id'
         '_diffrn_detector_axis.axis_id'      '_axis.id'
         '_diffrn_measurement_axis.axis_id'   '_axis.id'
         '_diffrn_scan_axis.axis_id'          '_axis.id'      
         '_diffrn_scan_frame_axis.axis_id'    '_axis.id'

     save_
 
 
save__axis.type
    _item_description.description
;             The value of _axis.type specifies the type of
              axis:  rotation, translation (or general when the type is
              not relevant, as for gravity)
;
    _item.name                      '_axis.type'
    _item.category_id                 axis
    _item.mandatory_code              no
    _item_type.code                   ucode
    _item_default.value               general
     loop_
    _item_enumeration.value
    _item_enumeration.detail      rotation
                                 'right-handed axis of rotation'
                                  translation
                                 'translation in the direction of the axis'
                                  general
                                 'axis for which the type is not relevant'

     save_


save__axis.vector[1]
    _item_description.description
;              The [1] element of the 3-element vector used to specify
               the direction of a rotation or translation axis.
               The vector should be normalized to be a unit vector, and
               is dimensionless.
;
    _item.name                  '_axis.vector[1]'
    _item.category_id             axis
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
     save_

save__axis.vector[2]
    _item_description.description
;              The [2] element of the 3-element vector used to specify
               the direction of a rotation or translation axis.
               The vector should be normalized to be a unit vector, and
               is dimensionless.
;
    _item.name                  '_axis.vector[2]'
    _item.category_id             axis
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
     save_

save__axis.vector[3]
    _item_description.description
;              The [3] element of the 3-element vector used to specify
               the direction of a rotation or translation axis.
               The vector should be normalized to be a unit vector, and
               is dimensionless.
;
    _item.name                  '_axis.vector[3]'
    _item.category_id             axis
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
     save_
 

 
#####################
# DIFFRN_DATA_FRAME #
#####################
 
 
save_DIFFRN_DATA_FRAME
    _category.description
;
              Data items in the DIFFRN_DATA_FRAME category record
              the details about each frame of data. 
              
              The items in this category were previously in a
              DIFFRN_FRAME_DATA category, which is now deprecated.
              The items from the old category are provided
              as aliases, but should not be used for new work.
;
    _category.id                   diffrn_data_frame
    _category.mandatory_code       no
     loop_
    _category_key.name             '_diffrn_data_frame.id'
                                   '_diffrn_data_frame.detector_element_id'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
    Example 1 - A frame containing data from 4 frame elements.
                Each frame element has a common array configuration
                'array_1' described in ARRAY_STRUCTURE and related
                categories.  The data for each detector element is 
                stored in four groups of binary data in the
                ARRAY_DATA category, linked by the array_id and
                binary_id
;
;
        loop_
        _diffrn_data_frame.id
        _diffrn_data_frame.detector_element_id
        _diffrn_data_frame.array_id
        _diffrn_data_frame.binary_id
        frame_1   d1_ccd_1  array_1  1  
        frame_1   d1_ccd_2  array_1  2 
        frame_1   d1_ccd_3  array_1  3 
        frame_1   d1_ccd_4  array_1  4 
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    save_
 
 
save__diffrn_data_frame.array_id
    _item_description.description
;             
              This item is a pointer to _array_structure.id in the
              ARRAY_STRUCTURE category. 
;
    _item.name                  '_diffrn_data_frame.array_id'
    _item.category_id             diffrn_data_frame
    _item.mandatory_code          yes
    _item_aliases.alias_name    '_diffrn_frame_data.array_id'
    _item_aliases.dictionary      cif_img.dic
    _item_aliases.version         1.0.00
    _item_type.code               code
     save_
 
 
save__diffrn_data_frame.binary_id
    _item_description.description
;             This item is a pointer to _array_data.binary_id in the
              ARRAY_DATA category. 
;
    _item.name                  '_diffrn_data_frame.binary_id'
    _item.category_id             diffrn_data_frame
    _item.mandatory_code          implicit
    _item_aliases.alias_name    '_diffrn_frame_data.binary_id'
    _item_aliases.dictionary      cif_img.dic
    _item_aliases.version         1.0
    _item_type.code               int
     save_
 
 
save__diffrn_data_frame.detector_element_id
    _item_description.description
;             
               This item is a pointer to _diffrn_detector_element.id
               in the DIFFRN_DETECTOR_ELEMENT category. 
;
    _item.name                  '_diffrn_data_frame.detector_element_id'
    _item.category_id             diffrn_data_frame
    _item.mandatory_code          yes
    _item_aliases.alias_name    '_diffrn_frame_data.detector_element_id'
    _item_aliases.dictionary      cif_img.dic
    _item_aliases.version         1.0
    _item_type.code               code
     save_
 
 
save__diffrn_data_frame.id
    _item_description.description
;             
              The value of _diffrn_data_frame.id must uniquely identify
              each complete frame of data.
;
     loop_
    _item.name                
    _item.category_id          
    _item.mandatory_code       
           '_diffrn_data_frame.id'        diffrn_data_frame  yes
           '_diffrn_refln.frame_id'       diffrn_refln       yes
           '_diffrn_scan.frame_id_start'  diffrn_scan        yes
           '_diffrn_scan.frame_id_end'    diffrn_scan        yes
           '_diffrn_scan_frame.frame_id'  diffrn_scan_frame  yes
           '_diffrn_scan_frame_axis.frame_id'  
                                          diffrn_scan_frame_axis
                                                             yes
    _item_aliases.alias_name    '_diffrn_frame_data.id'
    _item_aliases.dictionary      cif_img.dic
    _item_aliases.version         1.0
    _item_type.code               code
     loop_
    _item_linked.child_name
    _item_linked.parent_name
           '_diffrn_refln.frame_id'        '_diffrn_data_frame.id'
           '_diffrn_scan.frame_id_start'   '_diffrn_data_frame.id'
           '_diffrn_scan.frame_id_end'     '_diffrn_data_frame.id'
           '_diffrn_scan_frame.frame_id'   '_diffrn_data_frame.id'
           '_diffrn_scan_frame_axis.frame_id'
                                           '_diffrn_data_frame.id'
     save_
 

##########################################################################
#  The following is a restatement of the mmCIF DIFFRN_DETECTOR,          #
#  DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for      #
#  the CBF/imgCIF extensions                                             #
##########################################################################

###################
# DIFFRN_DETECTOR #
###################
 
 
save_DIFFRN_DETECTOR
    _category.description
;              Data items in the DIFFRN_DETECTOR category describe the 
               detector used to measure the scattered radiation, including
               any analyser and post-sample collimation.
;
    _category.id                  diffrn_detector
    _category.mandatory_code      no
     loop_
    _category_key.name          '_diffrn_detector.diffrn_id'
                                '_diffrn_detector.id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
    Example 1 - based on PDB entry 5HVP and laboratory records for the
                structure corresponding to PDB entry 5HVP
;
;
    _diffrn_detector.diffrn_id             'd1'
    _diffrn_detector.detector              'multiwire'
    _diffrn_detector.type                  'Siemens'
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_
 
 
save__diffrn_detector.details
    _item_description.description
;              A description of special aspects of the radiation detector.
;
    _item.name                  '_diffrn_detector.details'
    _item.category_id             diffrn_detector
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_detector_details'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
    _item_examples.case
;                                 Need new example here.
;
     save_
 
 
save__diffrn_detector.detector
    _item_description.description
;              The general class of the radiation detector.
;
    _item.name                  '_diffrn_detector.detector'
    _item.category_id             diffrn_detector
    _item.mandatory_code          no
     loop_
    _item_aliases.alias_name
    _item_aliases.dictionary
    _item_aliases.version       '_diffrn_radiation_detector'
                                  cifdic.c91
                                  1.0
                                '_diffrn_detector'
                                  cif_core.dic
                                  2.0
    _item_type.code               text
     loop_
    _item_examples.case          'photographic film'
                                 'scintillation counter'
                                 'CCD plate'
                                 'BF~3~ counter'
     save_
 
 
save__diffrn_detector.diffrn_id
    _item_description.description
;              This data item is a pointer to _diffrn.id in the DIFFRN
               category.

               The value of _diffrn.id uniquely defines a set of
               diffraction data.
;
    _item.name                  '_diffrn_detector.diffrn_id'
    _item.mandatory_code          yes
     save_
 
 
save__diffrn_detector.dtime
    _item_description.description
;              The deadtime in microseconds of the detectors used to measure
               the diffraction intensities.
;
    _item.name                  '_diffrn_detector.dtime'
    _item.category_id             diffrn_detector
    _item.mandatory_code          no
     loop_
    _item_aliases.alias_name
    _item_aliases.dictionary
    _item_aliases.version       '_diffrn_radiation_detector_dtime'
                                  cifdic.c91
                                  1.0
                                '_diffrn_detector_dtime'
                                  cif_core.dic
                                  2.0
     loop_  
    _item_range.maximum           
    _item_range.minimum            .    0.0
                                  0.0   0.0
    _item_type.code               float
    _item_units.code              microseconds
     save_
 
 
save__diffrn_detector.id
    _item_description.description
;             
               The value of _diffrn_detector.id must uniquely identify
               each detector used to collect each diffraction data set.

               If the value of _diffrn_detector.id is not given, it is
               implicitly equal to the value of _diffrn_detector.diffrn_id
;
     loop_
    _item.name                 
    _item.category_id
    _item.mandatory_code
             '_diffrn_detector.id'         diffrn_detector       implicit
             '_diffrn_detector_axis.detector_id'
                                           diffrn_detector_axis       yes
     loop_
    _item_linked.child_name
    _item_linked.parent_name
             '_diffrn_detector_axis.detector_id'
                                         '_diffrn_detector.id'

    _item_type.code               code
     save_
 
 
save__diffrn_detector.number_of_axes
    _item_description.description
;             
               The value of _diffrn_detector.number_of_axes gives the 
               number of axes of the positioner for the detector identified 
               by _diffrn_detector.id
               
               The word "positioner" is a general term used in instrumentation
               design for devices that are used to change the positions of 
               portions of apparatus by linear translation, rotation, or 
               combinations of such motions.
               
               Axes which are used to provide a coordinate system for the
               face of an area detetctor should not be counted for this
               data item.

               The description of each axis should be provided by entries 
               in DIFFRN_DETECTOR_AXIS.
;
    _item.name                  '_diffrn_detector.number_of_axes'
    _item.category_id             diffrn_detector
    _item.mandatory_code          no
     loop_
    _item_range.maximum
    _item_range.minimum           .   1
                                  1   1
    _item_type.code               int
     save_
 
 
save__diffrn_detector.type
    _item_description.description
;              The make, model or name of the detector device used.
;
    _item.name                  '_diffrn_detector.type'
    _item.category_id             diffrn_detector
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_detector_type'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
     save_
 
 
########################
# DIFFRN_DETECTOR_AXIS #
########################
 
 
save_DIFFRN_DETECTOR_AXIS
    _category.description
;
     Data items in the DIFFRN_DETECTOR_AXIS category associate
     axes with detectors.
;
    _category.id                   diffrn_detector_axis
    _category.mandatory_code       no
     loop_
    _category_key.name          '_diffrn_detector_axis.detector_id'
                                '_diffrn_detector_axis.axis_id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     save_
 
 
save__diffrn_detector_axis.axis_id
    _item_description.description
;
               This data item is a pointer to _axis.id in
               the AXIS category.
;
    _item.name                  '_diffrn_detector_axis.axis_id'
    _item.category_id             diffrn_detector_axis
    _item.mandatory_code          yes
    _item_type.code               code
     save_
 
 
save__diffrn_detector_axis.detector_id
    _item_description.description
;
               This data item is a pointer to _diffrn_detector.id in
               the DIFFRN_DETECTOR category.

               This item was previously named '_diffrn_detector_axis.id'
               which is now a deprecated name.  The old name is
               provided as an alias, but should not be used for new work.

;
    _item.name                  '_diffrn_detector_axis.detector_id'
    _item.category_id             diffrn_detector_axis
    _item.mandatory_code          yes
    _item_aliases.alias_name    '_diffrn_detector_axis.id'
    _item_aliases.dictionary      cif_img.dic
    _item_aliases.version         1.0
     save_
 
 
###########################
# DIFFRN_DETECTOR_ELEMENT #
###########################
 
 
save_DIFFRN_DETECTOR_ELEMENT
    _category.description
;
              Data items in the DIFFRN_DETECTOR_ELEMENT category record
              the details about spatial layout and other characteristics
              of each element of a detector which may have multiple elements.
              
              In most cases, the more detailed information provided
              in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS
              are preferable to simply providing the centre.

;
    _category.id                   diffrn_detector_element
    _category.mandatory_code       no
     loop_
    _category_key.name             '_diffrn_detector_element.id'
                                   '_diffrn_detector_element.detector_id'
    loop_
    _category_group.id             'inclusive_group'
                                   'array_data_group'
    loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
        Example 1 - Detector d1 is composed of four CCD detector elements,
        each 200 mm by 200 mm, arranged in a square. in the pattern
                    
                   1     2
                      *
                   3     4

        Note that the beam center is slightly off of each of the
        detector elements, just beyond the lower right corner of 1,
        the lower left corner of 2, the upper right corner of 3 and
        the upper left corner of 4.
;
;
        loop_
        _diffrn_detector_element.id
        _diffrn_detector_element.detector_id
        _diffrn_detector_element.center[1]
        _diffrn_detector_element.center[2]
        d1     d1_ccd_1  201.5 -1.5
        d1     d1_ccd_2  -1.8  -1.5
        d1     d1_ccd_3  201.6 201.4  
        d1     d1_ccd_4  -1.7  201.5
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    save_
 
 
save__diffrn_detector_element.center[1]
    _item_description.description
;             
              The value of _diffrn_detector_element.center[1] is the X
              component of the distortion-corrected beam-center in mm from the
              (0, 0) (lower left) corner of the detector element viewed from 
              the sample side.
;
    _item.name                  '_diffrn_detector_element.center[1]'
    _item.category_id             diffrn_detector_element
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
    _item_units.code              millimetres

    save_
 
 
save__diffrn_detector_element.center[2]
    _item_description.description
;             
              The value of _diffrn_detector_element.center[2] is the Y
              component of the distortion-corrected beam-center in mm from the
              (0, 0) (lower left) corner of the detector element viewed from 
              the sample side.
;
    _item.name                  '_diffrn_detector_element.center[2]'
    _item.category_id             diffrn_detector_element
    _item.mandatory_code          no
    _item_default.value           0.0
    _item_sub_category.id         vector
    _item_type.code               float
    _item_units.code              millimetres

    save_
 
 
save__diffrn_detector_element.id
    _item_description.description
;             
              The value of _diffrn_detector_element.id must uniquely identify
              each element of a detector.
;
     loop_
    _item.name                
    _item.category_id          
    _item.mandatory_code       
           '_diffrn_detector_element.id'
           diffrn_detector_element
           yes
    _item_type.code               code
     loop_
    _item_linked.child_name
    _item_linked.parent_name
           '_diffrn_data_frame.detector_element_id'
           '_diffrn_detector_element.id'

     save_
 
 
save__diffrn_detector_element.detector_id
    _item_description.description
;             
               This item is a pointer to _diffrn_detector.id
               in the DIFFRN_DETECTOR category. 
;
    _item.name                  '_diffrn_detector_element.detector_id'
    _item.category_id             diffrn_detector_element
    _item.mandatory_code          yes
    _item_type.code               code
     save_
 
 
 
########################
## DIFFRN_MEASUREMENT ##
########################
 
 
save_DIFFRN_MEASUREMENT
    _category.description
;              Data items in the DIFFRN_MEASUREMENT category record details
               about the device used to orient and/or position the crystal
               during data measurement and the manner in which the diffraction
               data were measured.
;
    _category.id                  diffrn_measurement
    _category.mandatory_code      no
     loop_
    _category_key.name          '_diffrn_measurement.device'
                                '_diffrn_measurement.diffrn_id'
                                '_diffrn_measurement.id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
    Example 1 - based on PDB entry 5HVP and laboratory records for the
                structure corresponding to PDB entry 5HVP
;
;
    _diffrn_measurement.diffrn_id          'd1'
    _diffrn_measurement.device             '3-circle camera'
    _diffrn_measurement.device_type        'Supper model x'
    _diffrn_measurement.device_details     'none'
    _diffrn_measurement.method             'omega scan'
    _diffrn_measurement.details
    ; Need new example here
    ;
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
    Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991).
                Acta Cryst. C47, 2276-2277].
;
;
    _diffrn_measurement.diffrn_id       's1'
    _diffrn_measurement.device_type     'Philips PW1100/20 diffractometer'
    _diffrn_measurement.method          'theta/2theta (\q/2\q)'
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_
 
 
save__diffrn_measurement.device
    _item_description.description
;              The general class of goniometer or device used to support and
               orient the specimen.
               
               If the value of _diffrn_measurement.device is not given, it is
               implicitly equal to the value of _diffrn_measurement.diffrn_id

               Either '_diffrn_measurement.device' or '_diffrn_measurement.id'
               may be used to link to other categories.  If the experimental
               setup admits multiple devices, then '_diffrn_measurement.id'
               is used to provide a unique link.
               
;
     loop_
    _item.name
    _item.category_id
    _item.mandatory_code
             '_diffrn_measurement.device'  diffrn_measurement      implicit
             '_diffrn_measurement_axis.measurement_device' 
                                           diffrn_measurement_axis implicit
     loop_
    _item_linked.child_name
    _item_linked.parent_name
             '_diffrn_measurement_axis.measurement_device'  
                                         '_diffrn_measurement.device'
    _item_aliases.alias_name    '_diffrn_measurement_device'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
     loop_
    _item_examples.case          '3-circle camera'
                                 '4-circle camera'
                                 'kappa-geometry camera'
                                 'oscillation camera'
                                 'precession camera'
     save_
 
 
save__diffrn_measurement.device_details
    _item_description.description
;              A description of special aspects of the device used to measure
               the diffraction intensities.
;
    _item.name                  '_diffrn_measurement.device_details'
    _item.category_id             diffrn_measurement
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_measurement_device_details'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
    _item_examples.case
;                                 commercial goniometer modified locally to
                                  allow for 90\% \t arc
;
     save_
 
 
save__diffrn_measurement.device_type
    _item_description.description
;              The make, model or name of the measurement device
               (goniometer) used.
;
    _item.name                  '_diffrn_measurement.device_type'
    _item.category_id             diffrn_measurement
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_measurement_device_type'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
     loop_
    _item_examples.case          'Supper model q'
                                 'Huber model r'
                                 'Enraf-Nonius model s'
                                 'homemade'
     save_
 
 
save__diffrn_measurement.diffrn_id
    _item_description.description
;              This data item is a pointer to _diffrn.id in the DIFFRN 
               category.
;
    _item.name                  '_diffrn_measurement.diffrn_id'
    _item.mandatory_code          yes
     save_
 
 
save__diffrn_measurement.details
    _item_description.description
;              A description of special aspects of the intensity measurement.
;
    _item.name                  '_diffrn_measurement.details'
    _item.category_id             diffrn_measurement
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_measurement_details'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
    _item_examples.case
;                                 440 frames, 0.20 degrees, 150 sec, detector
                                  distance 12 cm, detector angle 22.5 degrees
;
     save_
 
 
save__diffrn_measurement.id
    _item_description.description
;             
               The value of _diffrn_measurement.id must uniquely identify
               the set of mechanical characteristics of the device used to 
               orient and/or position the sample used during collection 
               of each diffraction data set.

               If the value of _diffrn_measurement.id is not given, it is
               implicitly equal to the value of _diffrn_measurement.diffrn_id

               Either '_diffrn_measurement.device' or '_diffrn_measurement.id'
               may be used to link to other categories.  If the experimental
               setup admits multiple devices, then '_diffrn_measurement.id'
               is used to provide a unique link.
;
     loop_
    _item.name                 
    _item.category_id
    _item.mandatory_code
             '_diffrn_measurement.id'      diffrn_measurement      implicit
             '_diffrn_measurement_axis.measurement_id'
                                           diffrn_measurement_axis implicit
     loop_
    _item_linked.child_name
    _item_linked.parent_name
             '_diffrn_measurement_axis.measurement_id'
                                         '_diffrn_measurement.id'

    _item_type.code               code
     save_
 
 
save__diffrn_measurement.method
    _item_description.description
;              Method used to measure intensities.
;
    _item.name                  '_diffrn_measurement.method'
    _item.category_id             diffrn_measurement
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_measurement_method'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
    _item_examples.case         'profile data from theta/2theta (\q/2\q) scans'
     save_
 
 
save__diffrn_measurement.number_of_axes
    _item_description.description
;             
               The value of _diffrn_measurement.number_of_axes gives the 
               number of axes of the positioner for the goniometer or
               other sample orientation or positioning device identified 
               by _diffrn_measurement.id

               The description of the axes should be provided by entries in 
               DIFFRN_MEASUREMENT_AXIS.
;
    _item.name                  '_diffrn_measurement.number_of_axes'
    _item.category_id             diffrn_measurement
    _item.mandatory_code          no
     loop_
    _item_range.maximum
    _item_range.minimum           .   1
                                  1   1
    _item_type.code               int
     save_
 
 
save__diffrn_measurement.specimen_support
    _item_description.description
;              The physical device used to support the crystal during data
               collection.
;
    _item.name                  '_diffrn_measurement.specimen_support'
    _item.category_id             diffrn_measurement
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_measurement_specimen_support'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
     loop_
    _item_examples.case          'glass capillary'
                                 'quartz capillary'
                                 'fiber'
                                 'metal loop'
     save_
 
 
###########################
# DIFFRN_MEASUREMENT_AXIS #
###########################
 
 
save_DIFFRN_MEASUREMENT_AXIS
    _category.description
;
     Data items in the DIFFRN_MEASUREMENT_AXIS category associate
     axes with goniometers.
;
    _category.id                   diffrn_measurement_axis
    _category.mandatory_code       no
     loop_
    _category_key.name          '_diffrn_measurement_axis.measurement_device'
                                '_diffrn_measurement_axis.measurement_id'
                                '_diffrn_measurement_axis.axis_id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     save_
 
 
save__diffrn_measurement_axis.axis_id
    _item_description.description
;
               This data item is a pointer to _axis.id in
               the AXIS category.
;
    _item.name                  '_diffrn_measurement_axis.axis_id'
    _item.category_id             diffrn_measurement_axis
    _item.mandatory_code          yes
    _item_type.code               code
     save_
 
 
save__diffrn_measurement_axis.measurement_device
    _item_description.description
;
               This data item is a pointer to _diffrn_measurement.device in
               the DIFFRN_MEASUREMENT category.

;
    _item.name                  '_diffrn_measurement_axis.measurement_device'
    _item.category_id             diffrn_measurement_axis
    _item.mandatory_code          implicit
     save_
 
 
save__diffrn_measurement_axis.measurement_id
    _item_description.description
;
               This data item is a pointer to _diffrn_measurement.id in
               the DIFFRN_MEASUREMENT category.
              
               This item was previously named '_diffrn_measurement_axis.id'
               which is now a deprecated name.  The old name is
               provided as an alias, but should not be used for new work.

;
    _item.name                  '_diffrn_measurement_axis.measurement_id'
    _item.category_id             diffrn_measurement_axis
    _item_aliases.alias_name    '_diffrn_measurement_axis.id'
    _item_aliases.dictionary      cif_img.dic
    _item_aliases.version         1.0.00
    _item.mandatory_code          implicit
     save_

 
####################
# DIFFRN_RADIATION #
####################
 
 
save_DIFFRN_RADIATION
    _category.description
;              Data items in the DIFFRN_RADIATION category describe
               the radiation used in measuring diffraction intensities,
               its collimation and monochromatisation before the sample.

               Post-sample treatment of the beam is described by data
               items in the DIFFRN_DETECTOR category.

;
    _category.id                  diffrn_radiation
    _category.mandatory_code      no
    _category_key.name          '_diffrn_radiation.diffrn_id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
    Example 1 - based on PDB entry 5HVP and laboratory records for the
                structure corresponding to PDB entry 5HVP
;
;
    _diffrn_radiation.diffrn_id            'set1'

    _diffrn_radiation.collimation          '0.3 mm double pinhole'
    _diffrn_radiation.monochromator        'graphite'
    _diffrn_radiation.type                 'Cu K\a'
    _diffrn_radiation.wavelength_id         1
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
    Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991).
                Acta Cryst. C47, 2276-2277].
;
;
    _diffrn_radiation.wavelength_id    1
    _diffrn_radiation.type             'Cu K\a'
    _diffrn_radiation.monochromator    'graphite'
;
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
     save_

save__diffrn_radiation.collimation
    _item_description.description
;              The collimation or focusing applied to the radiation.
;
    _item.name                  '_diffrn_radiation.collimation'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_collimation'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
     loop_
    _item_examples.case          '0.3 mm double-pinhole'
                                 '0.5 mm'
                                 'focusing mirrors'
     save_


save__diffrn_radiation.diffrn_id
    _item_description.description
;              This data item is a pointer to _diffrn.id in the DIFFRN
               category.
;
    _item.name                  '_diffrn_radiation.diffrn_id'
    _item.mandatory_code          yes
     save_

 
 
save__diffrn_radiation.div_x_source
    _item_description.description
;              Beam crossfire in degrees parallel to the laboratory X axis
               (see AXIS category).
               
               This is a characteristic of the xray beam as it illuminates
               the sample (or specimen) after all monochromation and 
               collimation.
               
               This is the esd of the directions of photons in the X-Z plane
               around the mean source beam direction.
               
               Note that some synchrotrons specify this value in milliradians,
               in which case a conversion would be needed.  To go from a
               value in milliradians to a value in degrees, multiply by 0.180
               and divide by Pi.

;
    _item.name                  '_diffrn_radiation.div_x_source'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_type.code               float
    _item_units.code              degrees
     save_
 
 
save__diffrn_radiation.div_y_source
    _item_description.description
;              Beam crossfire in degrees parallel to the laboratory Y axis
               (see AXIS category).
               
               This is a characteristic of the xray beam as it illuminates
               the sample (or specimen) after all monochromation and 
               collimation.
               
               This is the esd of the directions of photons in the Y-Z plane
               around the mean source beam direction.

               Note that some synchrotrons specify this value in milliradians,
               in which case a conversion would be needed.  To go from a
               value in milliradians to a value in degrees, multiply by 0.180
               and divide by Pi.

;
    _item.name                  '_diffrn_radiation.div_y_source'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_type.code               float
    _item_units.code              degrees
    _item_default.value           0.0
     save_
 
 
save__diffrn_radiation.div_x_y_source
    _item_description.description
;              Beam crossfire correlation degrees**2 between the
               crossfire laboratory X-axis component and the crossfire
               laboratory Y-axis component (see AXIS category).
               
               This is a characteristic of the xray beam as it illuminates
               the sample (or specimen) after all monochromation and 
               collimation.
               
               This is the mean of the products of the deviations of the
               directin of each photons in X-Z plane times the deviations
               of the direction of the same photon in the Y-Z plane
               around the mean source beam direction.  This will be zero
               for uncorrelated crossfire.
               
               Note that some synchrotrons specify this value in 
               milliradians**2, in which case a conversion would be needed.  
               To go from a value in milliradians**2 to a value in
               degrees**2, multiply by 0.180**2 and divide by Pi**2.

;
    _item.name                  '_diffrn_radiation.div_x_y_source'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_type.code               float
    _item_units.code              degrees_squared
    _item_default.value           0.0
     save_

save__diffrn_radiation.filter_edge
    _item_description.description
;              Absorption edge in angstroms of the radiation filter used.
;
    _item.name                  '_diffrn_radiation.filter_edge'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_filter_edge'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
     loop_
    _item_range.maximum           
    _item_range.minimum            .    0.0
                                  0.0   0.0
    _item_type.code               float
    _item_units.code              angstroms
     save_

save__diffrn_radiation.inhomogeneity
    _item_description.description
;              Half-width in millimetres of the incident beam in the
               direction perpendicular to the diffraction plane.
;
    _item.name                  '_diffrn_radiation.inhomogeneity'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_inhomogeneity'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
     loop_
    _item_range.maximum           
    _item_range.minimum            .    0.0
                                  0.0   0.0
    _item_type.code               float
    _item_units.code              millimetres
     save_

save__diffrn_radiation.monochromator
    _item_description.description
;              The method used to obtain monochromatic radiation. If a mono-
               chromator crystal is used the material and the indices of the
               Bragg reflection are specified.
;
    _item.name                  '_diffrn_radiation.monochromator'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_monochromator'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               text
     loop_
    _item_examples.case          'Zr filter'
                                 'Ge 220'
                                 'none'
                                 'equatorial mounted graphite'
     save_

save__diffrn_radiation.polarisn_norm
    _item_description.description
;              The angle in degrees, as viewed from the specimen, between the
               perpendicular component of the polarisation and the diffraction
               plane. See _diffrn_radiation_polarisn_ratio.
;
    _item.name                  '_diffrn_radiation.polarisn_norm'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_polarisn_norm'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
     loop_
    _item_range.maximum           
    _item_range.minimum            .    0.0
                                  0.0   0.0
    _item_type.code               float
    _item_units.code              degrees
     save_

save__diffrn_radiation.polarisn_ratio
    _item_description.description
;              Polarisation ratio of the diffraction beam incident on the
               crystal. It is the ratio of the perpendicularly polarised to the
               parallel polarised component of the radiation. The perpendicular
               component forms an angle of _diffrn_radiation.polarisn_norm to
               the normal to the diffraction plane of the sample (i.e. the
               plane containing the incident and reflected beams).
;
    _item.name                  '_diffrn_radiation.polarisn_ratio'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_polarisn_ratio'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
     loop_
    _item_range.maximum           
    _item_range.minimum            .    0.0
                                  0.0   0.0
    _item_type.code               float
     save_

 
 
save__diffrn_radiation.polarizn_source_norm
    _item_description.description
;              The angle in degrees, as viewed from the specimen, between the
               normal to the polarization plane and the laboratory Y axis as
               defined in the AXIS category.
               
               Note that this is the angle of polarization of the source 
               photons, either directly from a synchrotron beamline or
               from a monchromater.
               
               This differs from the value of '_diffrn_radiation.polarisn_norm'
               in that '_diffrn_radiation.polarisn_norm' refers to polarization
               relative to the diffraction plane rather than to the laboratory
               axis system.
               
               In the case of an unpolarized beam, or a beam with true circular
               polarization, in which no single plane of polarization can be
               determined, the plane should be taken as the X-Z plane, and the
               angle as 0.
               
               See '_diffrn_radiation.polarizn_source_ratio'.
;
    _item.name                  '_diffrn_radiation.polarizn_source_norm'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
     loop_
    _item_range.maximum           
    _item_range.minimum           90.0   90.0
                                  90.0  -90.0
                                 -90.0  -90.0
    _item_type.code               float
    _item_units.code              degrees
    _item_default.value           0.0
     save_
 
 
save__diffrn_radiation.polarizn_source_ratio
    _item_description.description
;              (Ip-In)/(Ip+In), where Ip is the intensity (amplitude squared)
               of the electric vector in the plane of polarization and In is
               the intensity (amplitude squared) of the electric vector
               in plane of the normal to the plane of polarization.
               
               Thus, if we had complete polarization in the plane of
               polarization, the value of 
               '_diffrn_radiation.polarizn_source_ratio' would
               be 1, and an unpolarized beam would have a value of 0.
               
               If the X-axis has been chosen to lie in the plane of
               polarization, this definition will agree with the definition
               of "MONOCHROMATOR" in the Denzo glossary, and values of near
               1 should be expected for a bending magnet source.  However,
               if the X-axis were, for some reason to be, say, perpendicular
               to the polarization plane (not a common choice), then the
               Denzo value would be the negative of
               '_diffrn_radiation.polarizn_source_ratio'.
               
               See http://www.hkl-xray.com for information on Denzo, and
               Z. Otwinowski and W. Minor, " Processing of X-ray Diffraction
               Data Collected in Oscillation Mode ", Methods in Enzymology, 
               Volume 276: Macromolecular Crystallography, part A, p.307-326,
               1997,C.W. Carter, Jr. & R. M. Sweet, Eds., Academic Press.

               This differs both in the choice of ratio and choice of
               orientation from '_diffrn_radiation.polarisn_ratio', which,
               unlike '_diffrn_radiation.polarizn_source_ratio', is unbounded.

;
    _item.name                  '_diffrn_radiation.polarizn_source_ratio'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
     loop_
    _item_range.maximum           
    _item_range.minimum           1.0    1.0
                                  1.0   -1.0
                                 -1.0   -1.0
    _item_type.code               float
     save_


save__diffrn_radiation.probe
    _item_description.description
;              Name of the type of radiation used. It is strongly encouraged
               that this field be specified so that the probe radiation
               can be simply determined.
;
    _item.name                  '_diffrn_radiation.probe'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_probe'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               line
     loop_
    _item_enumeration.value      'x-ray'
                                 'neutron'
                                 'electron'
                                 'gamma'
     save_

save__diffrn_radiation.type
    _item_description.description
;              The nature of the radiation. This is typically a description
               of the X-ray wavelength in Siegbahn notation.
;
    _item.name                  '_diffrn_radiation.type'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_type'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               line
     loop_
    _item_examples.case          'CuK\a'
                                 'Cu K\a~1~'
                                 'Cu K-L~2,3~' 
                                 'white-beam'

     save_

save__diffrn_radiation.xray_symbol
    _item_description.description
;              The IUPAC symbol for the X-ray wavelength for probe radiation.
;
    _item.name                  '_diffrn_radiation.xray_symbol'
    _item.category_id             diffrn_radiation
    _item.mandatory_code          no
    _item_aliases.alias_name    '_diffrn_radiation_xray_symbol'
    _item_aliases.dictionary      cif_core.dic
    _item_aliases.version         2.0.1
    _item_type.code               line
     loop_
    _item_enumeration.value
    _item_enumeration.detail     'K-L~3~'
                                 'K\a~1~ in older Siegbahn notation'
                                 'K-L~2~'
                                 'K\a~2~ in older Siegbahn notation'
                                 'K-M~3~'
                                 'K\b~1~ in older Siegbahn notation'
                                 'K-L~2,3~'
                                 'use where K-L~3~ and K-L~2~ are not resolved'
     save_

save__diffrn_radiation.wavelength_id
    _item_description.description
;              This data item is a pointer to _diffrn_radiation_wavelength.id
               in the DIFFRN_RADIATION_WAVELENGTH category.
;
    _item.name                  '_diffrn_radiation.wavelength_id'
    _item.mandatory_code          yes
     save_


 
################
# DIFFRN_REFLN #
################
 
 
save_DIFFRN_REFLN
    _category.description 
;
     This category redefinition has been added to extend the key of 
     the standard DIFFRN_REFLN category.
;
    _category.id                   diffrn_refln
    _category.mandatory_code       no
    _category_key.name             '_diffrn_refln.frame_id'
     loop_
    _category_group.id             'inclusive_group'
                                   'diffrn_group'
     save_
 
 
save__diffrn_refln.frame_id
    _item_description.description
;             
               This item is a pointer to _diffrn_data_frame.id
               in the DIFFRN_DATA_FRAME category. 
;
    _item.name                  '_diffrn_refln.frame_id'
    _item.category_id             diffrn_refln
    _item.mandatory_code          yes
    _item_type.code               code
     save_
 
 
###############
# DIFFRN_SCAN #
###############

save_DIFFRN_SCAN
    _category.description 
;
     Data items in the DIFFRN_SCAN category describe the parameters of one
     or more scans, relating axis positions to frames.

;
    _category.id                   diffrn_scan
    _category.mandatory_code       no
    _category_key.name            '_diffrn_scan.id'
     loop_
    _category_group.id            'inclusive_group'
                                  'diffrn_group'
     loop_
    _category_examples.detail
    _category_examples.case
# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
;
    Example 1 - derived from a suggestion by R. M. Sweet.

   The vector of each axis is not given here, because it is provided in
   the AXIS category.  By making _diffrn_scan_axis.scan_id and
   _diffrn_scan_axis.axis_id keys of the DIFFRN_SCAN_AXIS category,
   an arbitrary number of scanning and fixed axes can be specified for a 
   scan.  We have specified three rotation axes and one translation axis 
   at non-zero values, with one axis stepping.  There is no reason why 
   more axes could not have been specified to step.   We have specified
   range information, but note that it is redundant from the  number of 
   frames and the increment, so we could drop the data item
   _diffrn_scan_axis.angle_range .
   
   We have specified both the sweep data and the data for a single frame.
 
   Note that the information on how the axes are stepped is given twice,
   once in terms of the overall averages in the value of
   '_diffrn_scan.integration_time' and the values for DIFFRN_SCAN_AXIS,
   and precisely for the given frame in the value for 
   '_diffrn_scan_frame.integration_time' and the values for
   DIFFRN_SCAN_FRAME_AXIS.  If dose-related adjustements are made to
   scan times and non-linear stepping is done, these values may differ.
   Therefore, in interpreting the data for a particular frame it is
   important to use the frame-specific data.
 
;
;
      _diffrn_scan.id                   1
      _diffrn_scan.date_start         '2001-11-18T03:26:42'
      _diffrn_scan.date_end           '2001-11-18T03:36:45'
      _diffrn_scan.integration_time    3.0
      _diffrn_scan.frame_id_start      mad_L2_000
      _diffrn_scan.frame_id_end        mad_L2_200
      _diffrn_scan.frames              201

       loop_
      _diffrn_scan_axis.scan_id
      _diffrn_scan_axis.axis_id
      _diffrn_scan_axis.angle_start
      _diffrn_scan_axis.angle_range
      _diffrn_scan_axis.angle_increment
      _diffrn_scan_axis.displacement_start
      _diffrn_scan_axis.displacement_range
      _diffrn_scan_axis.displacement_increment

       1 omega 200.0 20.0 0.1 . . . 
       1 kappa -40.0  0.0 0.0 . . . 
       1 phi   127.5  0.0 0.0 . . . 
       1 tranz  . . .   2.3 0.0 0.0 

      _diffrn_scan_frame.scan_id                   1
      _diffrn_scan_frame.date               '2001-11-18T03:27:33'
      _diffrn_scan_frame.integration_time    3.0
      _diffrn_scan_frame.frame_id            mad_L2_018
      _diffrn_scan_frame.frame_number        18

      loop_
      _diffrn_scan_frame_axis.frame_id
      _diffrn_scan_frame_axis.axis_id
      _diffrn_scan_frame_axis.angle
      _diffrn_scan_frame_axis.angle_increment
      _diffrn_scan_frame_axis.displacement
      _diffrn_scan_frame_axis.displacement_increment

       mad_L2_018 omega 201.8  0.1 . .
       mad_L2_018 kappa -40.0  0.0 . .
       mad_L2_018 phi   127.5  0.0 . .
       mad_L2_018 tranz  .     .  2.3 0.0

;

;
    Example 2 - a more extensive example, R. M. Sweet, P. Ellis, H. Bernstein.
    
   We place a detector 240 mm along the Z axis from the goniometer.
   This presents us with a choice -- either we define the axes of
   the detector at the origin, and then put a Z setting of -240 in
   for the actual use, or we define the axes with the necessary Z-offset.
   In this case we use the setting, and leave the offset as zero.
   We call this axis DETECTOR_Z.
   
   The axis for positioning the detector in the Y-direction depends
   on the detector Z-axis.  We call this axis, DETECTOR_Y.
   
   The axis for positioning the dector in the X-direction depends
   on the detector Y-axis (and therefore on the detector Z-axis).
   We call this axis DETECTOR_X.
   
   This detector may be rotated around the Y-axis.  This rotation axis
   depends on the three translation axies.  We call it DETECTOR_PITCH.
   
   We define a coordinate system on the face of the detector in terms of
   2300 0.150 mm pixels in each direction.  The ELEMENT_X axis is used to
   index the first array index of the data array and the ELEMENT_Y
   axis is used to index the second array index.  Because the pixels
   are 0.150mm x 0.150mm, the center of the first pixel is at (0.075, 
   0.075) in this coordinate system.
 
;
;
     ###CBF: VERSION 1.1 

     data_image_1 
 

     # category DIFFRN 

     _diffrn.id P6MB 
     _diffrn.crystal_id P6MB_CRYSTAL7 
 

     # category DIFFRN_SOURCE 

     loop_ 
     _diffrn_source.diffrn_id 
     _diffrn_source.source 
     _diffrn_source.type 
      P6MB synchrotron 'SSRL beamline 9-1' 
 

     # category DIFFRN_RADIATION 

          loop_ 
     _diffrn_radiation.diffrn_id 
     _diffrn_radiation.wavelength_id 
     _diffrn_radiation.monochromator 
     _diffrn_radiation.polarizn_source_ratio 
     _diffrn_radiation.polarizn_source_norm 
     _diffrn_radiation.div_x_source 
     _diffrn_radiation.div_y_source 
     _diffrn_radiation.div_x_y_source 
      P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08
     0.01 0.00 
 

     # category DIFFRN_RADIATION_WAVELENGTH 

     loop_ 
     _diffrn_radiation_wavelength.id 
     _diffrn_radiation_wavelength.wavelength 
     _diffrn_radiation_wavelength.wt 
      WAVELENGTH1 0.98 1.0 
 

     # category DIFFRN_DETECTOR 

     loop_ 
     _diffrn_detector.diffrn_id 
     _diffrn_detector.id 
     _diffrn_detector.type 
     _diffrn_detector.number_of_axes 
      P6MB MAR345-SN26 'MAR 345' 4 
 

     # category DIFFRN_DETECTOR_AXIS 

     loop_ 
     _diffrn_detector_axis.id 
     _diffrn_detector_axis.axis_id 
      MAR345-SN26 DETECTOR_X 
      MAR345-SN26 DETECTOR_Y 
      MAR345-SN26 DETECTOR_Z 
      MAR345-SN26 DETECTOR_PITCH 
 

     # category DIFFRN_DETECTOR_ELEMENT 

     loop_ 
     _diffrn_detector_element.id 
     _diffrn_detector_element.detector_id 
      ELEMENT1 MAR345-SN26 
 

     # category DIFFRN_DATA_FRAME 

     loop_ 
     _diffrn_data_frame.id 
     _diffrn_data_frame.detector_element_id 
     _diffrn_data_frame.array_id 
     _diffrn_data_frame.binary_id 
      FRAME1 ELEMENT1 ARRAY1 1 
 

     # category DIFFRN_MEASUREMENT 

     loop_ 
     _diffrn_measurement.diffrn_id 
     _diffrn_measurement.id 
     _diffrn_measurement.number_of_axes 
     _diffrn_measurement.method 
      P6MB GONIOMETER 3 rotation 
 

     # category DIFFRN_MEASUREMENT_AXIS 

     loop_ 
     _diffrn_measurement_axis.measurement_id 
     _diffrn_measurement_axis.axis_id 
      GONIOMETER GONIOMETER_PHI 
      GONIOMETER GONIOMETER_KAPPA 
      GONIOMETER GONIOMETER_OMEGA 
 

     # category DIFFRN_SCAN 

     loop_ 
     _diffrn_scan.id 
     _diffrn_scan.frame_id_start 
     _diffrn_scan.frame_id_end 
     _diffrn_scan.frames 
      SCAN1 FRAME1 FRAME1 1 
 

     # category DIFFRN_SCAN_AXIS 

     loop_ 
     _diffrn_scan_axis.scan_id 
     _diffrn_scan_axis.axis_id 
     _diffrn_scan_axis.angle_start 
     _diffrn_scan_axis.angle_range 
     _diffrn_scan_axis.angle_increment 
     _diffrn_scan_axis.displacement_start 
     _diffrn_scan_axis.displacement_range 
     _diffrn_scan_axis.displacement_increment 
      SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 
      SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 
      SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 
      SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 
      SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 
      SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 
      SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 
 

     # category DIFFRN_SCAN_FRAME 

     loop_ 
     _diffrn_scan_frame.frame_id 
     _diffrn_scan_frame.frame_number 
     _diffrn_scan_frame.integration_time 
     _diffrn_scan_frame.scan_id 
     _diffrn_scan_frame.date 
      FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 
 

     # category DIFFRN_SCAN_FRAME_AXIS 

     loop_ 
     _diffrn_scan_frame_axis.frame_id 
     _diffrn_scan_frame_axis.axis_id 
     _diffrn_scan_frame_axis.angle 
     _diffrn_scan_frame_axis.displacement 
      FRAME1 GONIOMETER_OMEGA 12.0 0.0 
      FRAME1 GONIOMETER_KAPPA 23.3 0.0 
      FRAME1 GONIOMETER_PHI -165.8 0.0 
      FRAME1 DETECTOR_Z 0.0 -240.0 
      FRAME1 DETECTOR_Y 0.0 0.6 
      FRAME1 DETECTOR_X 0.0 -0.5 
      FRAME1 DETECTOR_PITCH 0.0 0.0 
 

     # category AXIS 

     loop_ 
     _axis.id 
     _axis.type 
     _axis.equipment 
     _axis.depends_on 
     _axis.vector[1] _axis.vector[2] _axis.vector[3] 
     _axis.offset[1] _axis.offset[2] _axis.offset[3] 
      GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . 
      GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279
      0 0.76604 . . . 
      GONIOMETER_PHI   rotation goniometer GONIOMETER_KAPPA 1 0 0
     . . . 
      SOURCE           general source . 0 0 1 . . . 
      GRAVITY          general gravity . 0 -1 0 . . . 
      DETECTOR_Z       translation detector . 0 0 1 0 0 0
      DETECTOR_Y       translation detector DETECTOR_Z 0 1 0 0 0 0 
      DETECTOR_X       translation detector DETECTOR_Y 1 0 0 0 0 0 
      DETECTOR_PITCH   rotation    detector DETECTOR_X 0 1 0 0 0 0 
      ELEMENT_X        translation detector DETECTOR_PITCH
     1 0 0 172.43 -172.43 0
      ELEMENT_Y        translation detector ELEMENT_X
     0 1 0 0 0 0 
 
     # category ARRAY_STRUCTURE_LIST 

     loop_ 
     _array_structure_list.array_id 
     _array_structure_list.index 
     _array_structure_list.dimension 
     _array_structure_list.precedence 
     _array_structure_list.direction 
     _array_structure_list.axis_set_id 
      ARRAY1 1 2300 1 increasing ELEMENT_X 
      ARRAY1 2 2300 2 increasing ELEMENT_Y 
 
 
     # category ARRAY_STRUCTURE_LIST_AXIS 

     loop_
     _array_structure_list_axis.axis_set_id
     _array_structure_list_axis.axis_id
     _array_structure_list_axis.displacement
     _array_structure_list_axis.displacement_increment
      ELEMENT_X ELEMENT_X 0.075 0.150
      ELEMENT_Y ELEMENT_Y 0.075 0.150

     # category ARRAY_ELEMENT_SIZE 

     loop_ 
     _array_element_size.array_id 
     _array_element_size.index 
     _array_element_size.size 
      ARRAY1 1 150e-6 
      ARRAY1 2 150e-6 
 

     # category ARRAY_INTENSITIES 

     loop_ 
     _array_intensities.array_id 
     _array_intensities.binary_id 
     _array_intensities.linearity 
     _array_intensities.gain 
     _array_intensities.gain_esd 
     _array_intensities.overload
     _array_intensities.undefined_value 
      ARRAY1 1 linear 1.15 0.2 240000 0 
 

      # category ARRAY_STRUCTURE 

      loop_ 
      _array_structure.id 
      _array_structure.encoding_type 
      _array_structure.compression_type 
      _array_structure.byte_order 
      ARRAY1 "signed 32-bit integer" packed little_endian 
 

     # category ARRAY_DATA         

     loop_ 
     _array_data.array_id 
     _array_data.binary_id 
     _array_data.data 
      ARRAY1 1 
     ; 
     --CIF-BINARY-FORMAT-SECTION-- 
     Content-Type: application/octet-stream; 
         conversions="x-CBF_PACKED" 
     Content-Transfer-Encoding: BASE64 
     X-Binary-Size: 3801324 
     X-Binary-ID: 1 
     X-Binary-Element-Type: "signed 32-bit integer" 
     Content-MD5: 07lZFvF+aOcW85IN7usl8A== 

     AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg 
     ... 
     8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE 

     --CIF-BINARY-FORMAT-SECTION---- 
     ; 
;

;
    Example 3 - Example 2 revised for a spiral scan, R. M. Sweet, 
    P. Ellis, H. Bernstein.
    
   We place a detector 240 mm along the Z axis from the goniometer,
   as in Example 2, above, but in this example, the image plate is
   scanned in a spiral pattern outside edge in.
   
   The axis for positioning the detector in the Y-direction depends
   on the detector Z-axis.  We call this axis, DETECTOR_Y.
   
   The axis for positioning the dector in the X-direction depends
   on the detector Y-axis (and therefore on the detector Z-axis).
   We call this axis DETECTOR_X.
   
   This detector may be rotated around the Y-axis.  This rotation axis
   depends on the three translation axies.  We call it DETECTOR_PITCH.
 
   We define a coordinate system on the face of the detector in
   terms of a coupled rotation axis and radial scan axis to form 
   a spiral scan.  Let us call rotation axis ELEMENT_ROT, and the
   radial axis ELEMENT_RAD.   We assume 150 um radial pitch and 75 um 
   'constant velocity' angular pitch. 

   We index first on the rotation axis and make the radial axis
   dependent on 
   it. 

   The two axes are coupled to form an axis set ELEMENT_SPIRAL. 
 
;
;
     ###CBF: VERSION 1.1 

     data_image_1 
 

     # category DIFFRN 

     _diffrn.id P6MB 
     _diffrn.crystal_id P6MB_CRYSTAL7 
 

     # category DIFFRN_SOURCE 

     loop_ 
     _diffrn_source.diffrn_id 
     _diffrn_source.source 
     _diffrn_source.type 
      P6MB synchrotron 'SSRL beamline 9-1' 
 

     # category DIFFRN_RADIATION 

          loop_ 
     _diffrn_radiation.diffrn_id 
     _diffrn_radiation.wavelength_id 
     _diffrn_radiation.monochromator 
     _diffrn_radiation.polarizn_source_ratio 
     _diffrn_radiation.polarizn_source_norm 
     _diffrn_radiation.div_x_source 
     _diffrn_radiation.div_y_source 
     _diffrn_radiation.div_x_y_source 
      P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08
     0.01 0.00 
 

     # category DIFFRN_RADIATION_WAVELENGTH 

     loop_ 
     _diffrn_radiation_wavelength.id 
     _diffrn_radiation_wavelength.wavelength 
     _diffrn_radiation_wavelength.wt 
      WAVELENGTH1 0.98 1.0 
 

     # category DIFFRN_DETECTOR 

     loop_ 
     _diffrn_detector.diffrn_id 
     _diffrn_detector.id 
     _diffrn_detector.type 
     _diffrn_detector.number_of_axes 
      P6MB MAR345-SN26 'MAR 345' 4 
 

     # category DIFFRN_DETECTOR_AXIS 

     loop_ 
     _diffrn_detector_axis.id 
     _diffrn_detector_axis.axis_id 
      MAR345-SN26 DETECTOR_X 
      MAR345-SN26 DETECTOR_Y 
      MAR345-SN26 DETECTOR_Z 
      MAR345-SN26 DETECTOR_PITCH 
 

     # category DIFFRN_DETECTOR_ELEMENT 

     loop_ 
     _diffrn_detector_element.id 
     _diffrn_detector_element.detector_id 
      ELEMENT1 MAR345-SN26 
 

     # category DIFFRN_DATA_FRAME 

     loop_ 
     _diffrn_data_frame.id 
     _diffrn_data_frame.detector_element_id 
     _diffrn_data_frame.array_id 
     _diffrn_data_frame.binary_id 
      FRAME1 ELEMENT1 ARRAY1 1 
 

     # category DIFFRN_MEASUREMENT 

     loop_ 
     _diffrn_measurement.diffrn_id 
     _diffrn_measurement.id 
     _diffrn_measurement.number_of_axes 
     _diffrn_measurement.method 
      P6MB GONIOMETER 3 rotation 
 

     # category DIFFRN_MEASUREMENT_AXIS 

     loop_ 
     _diffrn_measurement_axis.measurement_id 
     _diffrn_measurement_axis.axis_id 
      GONIOMETER GONIOMETER_PHI 
      GONIOMETER GONIOMETER_KAPPA 
      GONIOMETER GONIOMETER_OMEGA 
 

     # category DIFFRN_SCAN 

     loop_ 
     _diffrn_scan.id 
     _diffrn_scan.frame_id_start 
     _diffrn_scan.frame_id_end 
     _diffrn_scan.frames 
      SCAN1 FRAME1 FRAME1 1 
 

     # category DIFFRN_SCAN_AXIS 

     loop_ 
     _diffrn_scan_axis.scan_id 
     _diffrn_scan_axis.axis_id 
     _diffrn_scan_axis.angle_start 
     _diffrn_scan_axis.angle_range 
     _diffrn_scan_axis.angle_increment 
     _diffrn_scan_axis.displacement_start 
     _diffrn_scan_axis.displacement_range 
     _diffrn_scan_axis.displacement_increment 
      SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 
      SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 
      SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 
      SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 
      SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 
      SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 
      SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 
 

     # category DIFFRN_SCAN_FRAME 

     loop_ 
     _diffrn_scan_frame.frame_id 
     _diffrn_scan_frame.frame_number 
     _diffrn_scan_frame.integration_time 
     _diffrn_scan_frame.scan_id 
     _diffrn_scan_frame.date 
      FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 
 

     # category DIFFRN_SCAN_FRAME_AXIS 

     loop_ 
     _diffrn_scan_frame_axis.frame_id 
     _diffrn_scan_frame_axis.axis_id 
     _diffrn_scan_frame_axis.angle 
     _diffrn_scan_frame_axis.displacement 
      FRAME1 GONIOMETER_OMEGA 12.0 0.0 
      FRAME1 GONIOMETER_KAPPA 23.3 0.0 
      FRAME1 GONIOMETER_PHI -165.8 0.0 
      FRAME1 DETECTOR_Z 0.0 -240.0 
      FRAME1 DETECTOR_Y 0.0 0.6 
      FRAME1 DETECTOR_X 0.0 -0.5 
      FRAME1 DETECTOR_PITCH 0.0 0.0 
 

     # category AXIS 

     loop_ 
     _axis.id 
     _axis.type 
     _axis.equipment 
     _axis.depends_on 
     _axis.vector[1] _axis.vector[2] _axis.vector[3] 
     _axis.offset[1] _axis.offset[2] _axis.offset[3] 
      GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . 
      GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279
      0 0.76604 . . . 
      GONIOMETER_PHI   rotation goniometer GONIOMETER_KAPPA 1 0 0
     . . . 
      SOURCE           general source . 0 0 1 . . . 
      GRAVITY          general gravity . 0 -1 0 . . . 
      DETECTOR_Z       translation detector . 0 0 1 0 0 0
      DETECTOR_Y       translation detector DETECTOR_Z 0 1 0 0 0 0 
      DETECTOR_X       translation detector DETECTOR_Y 1 0 0 0 0 0 
      DETECTOR_PITCH   rotation    detector DETECTOR_X 0 1 0 0 0 0 
      ELEMENT_ROT      translation detector DETECTOR_PITCH 0 0 1 0 0 0
      ELEMENT_RAD      translation detector ELEMENT_ROT 0 1 0 0 0 0 
 
     # category ARRAY_STRUCTURE_LIST 

     loop_ 
     _array_structure_list.array_id 
     _array_structure_list.index 
     _array_structure_list.dimension 
     _array_structure_list.precedence 
     _array_structure_list.direction 
     _array_structure_list.axis_set_id 
      ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL
 
 
     # category ARRAY_STRUCTURE_LIST_AXIS 

     loop_
     _array_structure_list_axis.axis_set_id
     _array_structure_list_axis.axis_id
     _array_structure_list_axis.angle
     _array_structure_list_axis.displacement
     _array_structure_list_axis.angular_pitch
     _array_structure_list_axis.radial_pitch
      ELEMENT_SPIRAL ELEMENT_ROT 0    .  0.075   .
      ELEMENT_SPIRAL ELEMENT_RAD . 172.5  .    -0.150

     # category ARRAY_ELEMENT_SIZE 
     # the actual pixels are 0.075 by 0.150 mm
     # We give the coarser dimension here.

     loop_ 
     _array_element_size.array_id 
     _array_element_size.index 
     _array_element_size.size 
      ARRAY1 1 150e-6 
 

     # category ARRAY_INTENSITIES 

     loop_ 
     _array_intensities.array_id 
     _array_intensities.binary_id 
     _array_intensities.linearity 
     _array_intensities.gain 
     _array_intensities.gain_esd 
     _array_intensities.overload
     _array_intensities.undefined_value 
      ARRAY1 1 linear 1.15 0.2 240000 0 
 

      # category ARRAY_STRUCTURE 

      loop_ 
      _array_structure.id 
      _array_structure.encoding_type 
      _array_structure.compression_type 
      _array_structure.byte_order 
      ARRAY1 "signed 32-bit integer" packed little_endian 
 

     # category ARRAY_DATA         

     loop_ 
     _array_data.array_id 
     _array_data.binary_id 
     _array_data.data 
      ARRAY1 1 
     ; 
     --CIF-BINARY-FORMAT-SECTION-- 
     Content-Type: application/octet-stream; 
         conversions="x-CBF_PACKED" 
     Content-Transfer-Encoding: BASE64 
     X-Binary-Size: 3801324 
     X-Binary-ID: 1 
     X-Binary-Element-Type: "signed 32-bit integer" 
     Content-MD5: 07lZFvF+aOcW85IN7usl8A== 

     AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg 
     ... 
     8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE 

     --CIF-BINARY-FORMAT-SECTION---- 
     ; 
;


# - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
       save_
 
 
save__diffrn_scan.id
    _item_description.description
;             The value of _diffrn_scan.id uniquely identifies each
              scan.  The identifier is used to tie together all the 
              information about the scan.
;
     loop_
    _item.name                
    _item.category_id          
    _item.mandatory_code       
       '_diffrn_scan.id'                 diffrn_scan             yes
       '_diffrn_scan_axis.scan_id'       diffrn_scan_axis        yes
       '_diffrn_scan_frame.scan_id'      diffrn_scan_frame       yes
    _item_type.code               code
     loop_
    _item_linked.child_name
    _item_linked.parent_name
       '_diffrn_scan_axis.scan_id'          '_diffrn_scan.id'
       '_diffrn_scan_frame.scan_id'         '_diffrn_scan.id'
     save_
 
 
save__diffrn_scan.date_end
    _item_description.description
;
               The date and time of the end of the scan.  Note that this
               may be an estimate generated during the scan, before the
               precise time of the end of the scan is known.
;
    _item.name                 '_diffrn_scan.date_end'
    _item.category_id          diffrn_scan
    _item.mandatory_code       no
    _item_type.code            yyyy-mm-dd
     save_
 
 
save__diffrn_scan.date_start
    _item_description.description
;
               The date and time of the start of the scan.
;
    _item.name                 '_diffrn_scan.date_start'
    _item.category_id          diffrn_scan
    _item.mandatory_code       no
    _item_type.code            yyyy-mm-dd
     save_
 
 
save__diffrn_scan.integration_time
    _item_description.description
;
               Approximate average time in seconds to integrate each 
               step of the scan.  The precise time for integration
               of each particular step must be provided in
               '_diffrn_scan_frame.integration_time', even
               if all steps have the same integration time.
;
    _item.name                 '_diffrn_scan.integration_time'
    _item.category_id          diffrn_scan
    _item.mandatory_code       no
    _item_type.code            float
    _item_units.code           'seconds'
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            .   0.0
     save_
 
 
save__diffrn_scan.frame_id_start
    _item_description.description
;
               The value of this data item is the identifier of the
               first frame in the scan.

               This item is a pointer to _diffrn_data_frame.id in the
               DIFFRN_DATA_FRAME category.
;
    _item.name                 '_diffrn_scan.frame_id_start'
    _item.category_id          diffrn_scan
    _item.mandatory_code       yes
     save_
 
 
save__diffrn_scan.frame_id_end
    _item_description.description
;
               The value of this data item is the identifier of the
               last frame in the scan.

               This item is a pointer to _diffrn_data_frame.id in the
               DIFFRN_DATA_FRAME category.
;
    _item.name                 '_diffrn_scan.frame_id_end'
    _item.category_id          diffrn_scan
    _item.mandatory_code       yes 
     save_
 
 
save__diffrn_scan.frames
    _item_description.description
;
               The value of this data item is the number of frames in
               the scan.

;
    _item.name                 '_diffrn_scan.frames'
    _item.category_id          diffrn_scan
    _item.mandatory_code       no 
    _item_type.code            int
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            .   1
                            1   1
     save_
 
 
####################
# DIFFRN_SCAN_AXIS #
####################

save_DIFFRN_SCAN_AXIS
    _category.description 
;
     Data items in the DIFFRN_SCAN_AXIS category describe the settings of
     axes for particular scans.  Unspecified axes are assumed to be at
     their zero points.

;
    _category.id                   diffrn_scan_axis
    _category.mandatory_code       no
     loop_
    _category_key.name            
                                  '_diffrn_scan_axis.scan_id'
                                  '_diffrn_scan_axis.axis_id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     save_
 
 
save__diffrn_scan_axis.scan_id
    _item_description.description
;
               The value of this data item is the identifier of the
               scan for which axis settings are being specified.

               Multiple axes may be specified for the same value of
               '_diffrn_scan.id'.

               This item is a pointer to _diffrn_scan.id in the
               DIFFRN_SCAN category.
;
    _item.name                 '_diffrn_scan_axis.scan_id'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       yes
     save_
 
 
save__diffrn_scan_axis.axis_id
    _item_description.description
;
               The value of this data item is the identifier of one of
               the axes for the scan for which settings are being specified.

               Multiple axes may be specified for the same value of
               '_diffrn_scan.id'.

               This item is a pointer to _axis.id in the
               AXIS category.
;
    _item.name                 '_diffrn_scan_axis.axis_id'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       yes
     save_
 
 
save__diffrn_scan_axis.angle_start
    _item_description.description
;
               The starting position for the specified axis in degrees.
;
    _item.name                 '_diffrn_scan_axis.angle_start'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no 
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_
 
 
save__diffrn_scan_axis.angle_range
    _item_description.description
;
               The range from the starting position for the specified axis 
               in degrees.
;
    _item.name                 '_diffrn_scan_axis.angle_range'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no 
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_
 
 
save__diffrn_scan_axis.angle_increment
    _item_description.description
;
               The increment for each step for the specified axis
               in degrees.  In general, this will agree with
               '_array_structure_list_axis.angle_increment', which
               see for a precise description.
;
    _item.name                 '_diffrn_scan_axis.angle_increment'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no 
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_
 
 
save__diffrn_scan_axis.angle_rstrt_incr
    _item_description.description
;
               The increment after each step for the specified axis
               in degrees.  In general, this will agree with
               '_array_structure_list_axis.angle_increment', which
               see for a precise description.
;
    _item.name                 '_diffrn_scan_axis.angle_rstrt_incr'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_
 
 
save__diffrn_scan_axis.displacement_start
    _item_description.description
;
               The starting position for the specified axis in millimetres.
;
    _item.name                 '_diffrn_scan_axis.displacement_start'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no 
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
 
 
save__diffrn_scan_axis.displacement_range
    _item_description.description
;
               The range from the starting position for the specified axis 
               in millimetres.
;
    _item.name                 '_diffrn_scan_axis.displacement_range'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no 
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
 
 
save__diffrn_scan_axis.displacement_increment
    _item_description.description
;
               The increment for each step for the specified axis
               in millimetres.  In general, this will agree with
               '_diffrn_scan_frame_axis.displacement_increment', which
               see for a precise description.
;
    _item.name                 '_diffrn_scan_axis.displacement_increment'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no 
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
 
 
save__diffrn_scan_axis.displacement_rstrt_incr
    _item_description.description
;
               The increment for each step for the specified axis
               in millimetres.  In general, this will agree with
               '_diffrn_scan_frame_axis.displacement_rstrt_incr', which
               see for a precise description.
;
    _item.name                 '_diffrn_scan_axis.displacement_rstrt_incr'
    _item.category_id          diffrn_scan_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
 
 
#####################
# DIFFRN_SCAN_FRAME #
#####################

save_DIFFRN_SCAN_FRAME
    _category.description 
;
     Data items in the DIFFRN_SCAN_FRAME category describe the settings of
     axes for particular frames.  Unspecified axes are assumed to be at
     their zero points.

;
    _category.id                   diffrn_scan_frame
    _category.mandatory_code       no
     loop_
    _category_key.name     
                                  '_diffrn_scan_frame.scan_id'
                                  '_diffrn_scan_frame.frame_id'
     loop_
    _category_group.id            'inclusive_group'
                                  'diffrn_group'
     save_
 
 
save__diffrn_scan_frame.date
    _item_description.description
;
               The date and time of the start of the frame being scanned.
;
    _item.name                 '_diffrn_scan_frame.date'
    _item.category_id          diffrn_scan_frame
    _item.mandatory_code       no
    _item_type.code            yyyy-mm-dd
     save_
 
 
save__diffrn_scan_frame.frame_id
    _item_description.description
;
               The value of this data item is the identifier of the
               frame being examined.

               This item is a pointer to _diffrn_data_frame.id in the
               DIFFRN_DATA_FRAME category.
;
    _item.name                 '_diffrn_scan_frame.frame_id'
    _item.category_id          diffrn_scan_frame
    _item.mandatory_code       yes
     save_
 
 
save__diffrn_scan_frame.frame_number
    _item_description.description
;
               The value of this data item is the number of the frame within
               the scan, starting with 1.  It is not necessarily the same as
               the value of _diffrn_scan_frame.frame_id, but may
               be.

;
    _item.name                 '_diffrn_scan_frame.frame_number'
    _item.category_id          diffrn_scan_frame
    _item.mandatory_code       no 
    _item_type.code            int
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            .   0
                            0   0
     save_
 
 
save__diffrn_scan_frame.integration_time
    _item_description.description
;
               The time in seconds to integrate this step of the scan.
               This should be the precise time of integration of each
               particular frame.  The value of this data item should
               be given explicitly for each frame and not inferred
               from the value of '_diffrn_scan.integration_time'.
;
    _item.name                 '_diffrn_scan_frame.integration_time'
    _item.category_id          diffrn_scan_frame
    _item.mandatory_code       yes 
    _item_type.code            float
    _item_units.code           'seconds'
     loop_
    _item_range.maximum           
    _item_range.minimum           
                            .   0.0
     save_
 
 
save__diffrn_scan_frame.scan_id
    _item_description.description
;             The value of _diffrn_scan_frame.scan_id identifies the scan
              containing this frame.

              This item is a pointer to _diffrn_scan.id in the
              DIFFRN_SCAN category.
;
    _item.name             '_diffrn_scan_frame.scan_id'    
    _item.category_id        diffrn_scan_frame        
    _item.mandatory_code     yes     
     save_
 
 
##########################
# DIFFRN_SCAN_FRAME_AXIS #
##########################

save_DIFFRN_SCAN_FRAME_AXIS
    _category.description
;
     Data items in the DIFFRN_SCAN_FRAME_AXIS category describes the settings
     of axes for particular frames.  Unspecified axes are assumed to be at
     their zero points.  If, for any given frame, non-zero values apply
     for any of the data items in this category, those values should be
     given explicitly in this category and not simply inferred from values
     in DIFFRN_SCAN_AXIS.

;
    _category.id                   diffrn_scan_frame_axis
    _category.mandatory_code       no
     loop_
    _category_key.name
                                  '_diffrn_scan_frame_axis.frame_id'
                                  '_diffrn_scan_frame_axis.axis_id'
     loop_
    _category_group.id           'inclusive_group'
                                 'diffrn_group'
     save_
 
 
save__diffrn_scan_frame_axis.axis_id
    _item_description.description
;
               The value of this data item is the identifier of one of
               the axes for the frame for which settings are being specified.

               Multiple axes may be specified for the same value of
               _diffrn_scan_frame.frame_id

               This item is a pointer to _axis.id in the
               AXIS category.
;
    _item.name                 '_diffrn_scan_frame_axis.axis_id'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       yes
     save_
 
 
save__diffrn_scan_frame_axis.angle
    _item_description.description
;
               The setting of the specified axis in degrees for this frame.
               This is the setting at the start of the integration time.
;
    _item.name                 '_diffrn_scan_frame_axis.angle'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       no 
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_
 
 
save__diffrn_scan_frame_axis.angle_increment
    _item_description.description
;
               The increment for this frame for angular setting of
               the specified axis in degrees.  The sum of the values
               of '_diffrn_scan_frame_axis.angle' and
               '_diffrn_scan_frame_axis.angle_increment' is the
               angular setting of the axis at the end of the integration
               time for this frame.
;
    _item.name                 '_diffrn_scan_frame_axis.angle_increment'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_
 
 
save__diffrn_scan_frame_axis.angle_rstrt_incr
    _item_description.description
;
               The increment after this frame for angular setting of
               the specified axis in degrees.  The sum of the values
               of '_diffrn_scan_frame_axis.angle' and
               '_diffrn_scan_frame_axis.angle_increment' and
               '_diffrn_scan_frame_axis.angle_rstrt_incr' is the
               angular setting of the axis at the start of the integration
               time for the next frame, and should equal
               '_diffrn_scan_frame_axis.angle' for that next frame.
;
    _item.name               '_diffrn_scan_frame_axis.angle_rstrt_incr'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'degrees'
     save_
 
 
save__diffrn_scan_frame_axis.displacement
    _item_description.description
;
               The setting of the specified axis in millimetres for this
               frame.  This is the setting at the start of the integration
               time.

;
    _item.name               '_diffrn_scan_frame_axis.displacement'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
 
 
save__diffrn_scan_frame_axis.displacement_increment
    _item_description.description
;
               The increment for this frame for displacement setting of
               the specified axis in millimetres.  The sum of the values
               of '_diffrn_scan_frame_axis.displacement' and
               '_diffrn_scan_frame_axis.displacement_increment' is the
               angular setting of the axis at the end of the integration
               time for this frame.
;
    _item.name               '_diffrn_scan_frame_axis.displacement_increment'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_
 
 
save__diffrn_scan_frame_axis.displacement_rstrt_incr
    _item_description.description
;
               The increment for this frame for displacement setting of
               the specified axis in millimetres.  The sum of the values
               of '_diffrn_scan_frame_axis.displacement' and
               '_diffrn_scan_frame_axis.displacement_increment' and
               '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the
               angular setting of the axis at the start of the integration
               time for the next frame, and should equal
               '_diffrn_scan_frame_axis.displacement' for that next frame.
;
    _item.name               '_diffrn_scan_frame_axis.displacement_rstrt_incr'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       no
    _item_default.value        0.0
    _item_type.code            float
    _item_units.code           'millimetres'
     save_

save__diffrn_scan_frame_axis.frame_id
    _item_description.description
;
               The value of this data item is the identifier of the
               frame for which axis settings are being specified.

               Multiple axes may be specified for the same value of
               _diffrn_scan_frame.frame_id .

               This item is a pointer to _diffrn_data_frame.id in the
               DIFFRN_DATA_FRAME category.
;
    _item.name               '_diffrn_scan_frame_axis.frame_id'
    _item.category_id          diffrn_scan_frame_axis
    _item.mandatory_code       yes
     save_
 
 
####################
## ITEM_TYPE_LIST ##
####################
#
#
#  The regular expressions defined here are not compliant
#  with the POSIX 1003.2 standard as they include the
#  '\n' and '\t' special characters.  These regular expressions
#  have been tested using version 0.12 of Richard Stallman's
#  GNU regular expression library in POSIX mode.
#  In order to allow presentation of a regular expression
#  in a text field concatenate any line ending in a backslash
#  with the following line, after discarding the backslash.
#
#  A formal definition of the '\n' and '\t' special characters
#  is most properly done in the DDL, but for completeness, please
#  note that '\n' is the line termination character ('newline')
#  and '\t' is the horizontal tab character.  There is a formal
#  ambiguity in the use of '\n' for line termination, in that
#  the intention is that the equivalent machine/OS-dependent line
#  termination character sequence should be accepted as a match, e.g.
#
#      '\r' (control-M) under MacOS
#      '\n' (control-J) under Unix
#      '\r\n' (control-M control-J) under DOS and MS Windows
#
     loop_
    _item_type_list.code
    _item_type_list.primitive_code
    _item_type_list.construct
    _item_type_list.detail
               code      char
'[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
;              code item types/single words ...
;
               ucode      uchar
'[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
;              code item types/single words (case insensitive)
;
               line      char
'[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
;              code item types / multi-word items  ...
;
               uline     uchar
'[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
;              code item types / multi-word items (case insensitive)
;
               text      char
'[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*'
;              text item types / multi-line text ...
;
               binary    char
;\n--CIF-BINARY-FORMAT-SECTION--\n\
[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*}\
\n--CIF-BINARY-FORMAT-SECTION----
;
;              binary items are presented as MIME-like ascii-encoded
               sections in an imgCIF.  In a CBF, raw octet streams
               are used to convey the same information.
;
               int       numb
'-?[0-9]+'
;              int item types are the subset of numbers that are the negative
               or positive integers.
;
               float     numb
'-?(([0-9]+)|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?'
;              float item types are the subset of numbers that are the floating
               numbers.
;
               any       char
'.*'
;              A catch all for items that may take any form...
;
               yyyy-mm-dd  char
;\
[0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9][0-9]\
(T[0-2][0-9]:[0-5][0-9]:[0-5][0-9](.[0-9]+)([+-][0-5][0-9]:[0-5][0-9]))
;
;
               Standard format for CIF date and time strings (see
               http://www.iucr.orgiucr-top/cif/spec/datetime.html),
               consisting of a yyyy-mm-dd date optionally followed by
               the character "T" followed by a 24-hour clock time,
               optionally followed by a signed time-zone offset.
               
               The IUCr standard has been extended to allow for an optional
               deciaml fraction on the seconds of time.
               
               Time is local time if no time-zone offset is given.
;
 
 
#####################
## ITEM_UNITS_LIST ##
#####################

     loop_
    _item_units_list.code
    _item_units_list.detail
#
     'metres'                 'metres'
     'centimetres'            'centimetres (metres * 10^( -2))'
     'millimetres'            'millimetres (metres * 10^( -3))'
     'nanometres'             'nanometres  (metres * 10^( -9))'
     'angstroms'              'angstroms   (metres * 10^(-10))'
     'picometres'             'picometres  (metres * 10^(-12))'
     'femtometres'            'femtometres (metres * 10^(-15))'
#
     'reciprocal_metres'      'reciprocal metres (metres * 10^-1)'
     'reciprocal_centimetres' 'reciprocal centimetres (metres * 10^( -2)^-1)'
     'reciprocal_millimetres' 'reciprocal millimetres (metres * 10^( -3)^-1)'
     'reciprocal_nanometres'  'reciprocal nanometres  (metres * 10^( -9)^-1)'
     'reciprocal_angstroms'   'reciprocal angstroms   (metres * 10^(-10)^-1)'
     'reciprocal_picometres'  'reciprocal picometres  (metres * 10^(-12)^-1)'
#
     'nanometres_squared'     'nanometres squared (metres * 10^( -9))^2'
     'angstroms_squared'      'angstroms squared  (metres * 10^(-10))^2'
     '8pi2_angstroms_squared' '8pi^2 * angstroms squared (metres * 10^(-10))^2'
     'picometres_squared'     'picometres squared (metres * 10^(-12))^2'
#
     'nanometres_cubed'       'nanometres cubed (metres * 10^( -9))^3'
     'angstroms_cubed'        'angstroms cubed  (metres * 10^(-10))^3'
     'picometres_cubed'       'picometres cubed (metres * 10^(-12))^3'
#
     'kilopascals'            'kilopascals'
     'gigapascals'            'gigapascals'
#
     'hours'                  'hours'
     'minutes'                'minutes'
     'seconds'                'seconds'
     'microseconds'           'microseconds'
#
     'degrees'                'degrees (of arc)'
     'degrees_squared'        'degrees (of arc) squared'
#
     'degrees_per_minute'     'degrees (of arc) per minute'
#
     'celsius'                'degrees (of temperature) Celsius'
     'kelvins'                'degrees (of temperature) Kelvin'
#
     'counts'                 'counts'
     'counts_per_photon'      'counts per photon'
#
     'electrons'              'electrons'
#
     'electrons_squared'      'electrons squared'
#
     'electrons_per_nanometres_cubed'
; electrons per nanometres cubed (metres * 10^( -9))^3
;
     'electrons_per_angstroms_cubed'
; electrons per angstroms  cubed (metres * 10^(-10))^3
;
     'electrons_per_picometres_cubed'
; electrons per picometres cubed (metres * 10^(-12))^3
;
     'kilowatts'              'kilowatts'
     'milliamperes'           'milliamperes'
     'kilovolts'              'kilovolts'
#
     'arbitrary'
; arbitrary system of units.
;
#

     loop_
    _item_units_conversion.from_code
    _item_units_conversion.to_code
    _item_units_conversion.operator
    _item_units_conversion.factor
###
     'metres'                   'centimetres'              '*'   1.0E+02
     'metres'                   'millimetres'              '*'   1.0E+03
     'metres'                   'nanometres'               '*'   1.0E+09
     'metres'                   'angstroms'                '*'   1.0E+10
     'metres'                   'picometres'               '*'   1.0E+12
     'metres'                   'femtometres'              '*'   1.0E+15
#
     'centimetres'              'metres'                   '*'   1.0E-02
     'centimetres'              'millimetres'              '*'   1.0E+01
     'centimetres'              'nanometres'               '*'   1.0E+07
     'centimetres'              'angstroms'                '*'   1.0E+08
     'centimetres'              'picometres'               '*'   1.0E+10
     'centimetres'              'femtometres'              '*'   1.0E+13
#
     'millimetres'              'metres'                   '*'   1.0E-03
     'millimetres'              'centimetres'              '*'   1.0E-01
     'millimetres'              'nanometres'               '*'   1.0E+06
     'millimetres'              'angstroms'                '*'   1.0E+07
     'millimetres'              'picometres'               '*'   1.0E+09
     'millimetres'              'femtometres'              '*'   1.0E+12
#
     'nanometres'               'metres'                   '*'   1.0E-09
     'nanometres'               'centimetres'              '*'   1.0E-07
     'nanometres'               'millimetres'              '*'   1.0E-06
     'nanometres'               'angstroms'                '*'   1.0E+01
     'nanometres'               'picometres'               '*'   1.0E+03
     'nanometres'               'femtometres'              '*'   1.0E+06
#
     'angstroms'                'metres'                   '*'   1.0E-10
     'angstroms'                'centimetres'              '*'   1.0E-08
     'angstroms'                'millimetres'              '*'   1.0E-07
     'angstroms'                'nanometres'               '*'   1.0E-01
     'angstroms'                'picometres'               '*'   1.0E+02
     'angstroms'                'femtometres'              '*'   1.0E+05
#
     'picometres'               'metres'                   '*'   1.0E-12
     'picometres'               'centimetres'              '*'   1.0E-10
     'picometres'               'millimetres'              '*'   1.0E-09
     'picometres'               'nanometres'               '*'   1.0E-03
     'picometres'               'angstroms'                '*'   1.0E-02
     'picometres'               'femtometres'              '*'   1.0E+03
#
     'femtometres'              'metres'                   '*'   1.0E-15
     'femtometres'              'centimetres'              '*'   1.0E-13
     'femtometres'              'millimetres'              '*'   1.0E-12
     'femtometres'              'nanometres'               '*'   1.0E-06
     'femtometres'              'angstroms'                '*'   1.0E-05
     'femtometres'              'picometres'               '*'   1.0E-03
###
     'reciprocal_centimetres'   'reciprocal_metres'        '*'   1.0E+02
     'reciprocal_centimetres'   'reciprocal_millimetres'   '*'   1.0E-01
     'reciprocal_centimetres'   'reciprocal_nanometres'    '*'   1.0E-07
     'reciprocal_centimetres'   'reciprocal_angstroms'     '*'   1.0E-08
     'reciprocal_centimetres'   'reciprocal_picometres'    '*'   1.0E-10
#
     'reciprocal_millimetres'   'reciprocal_metres'        '*'   1.0E+03
     'reciprocal_millimetres'   'reciprocal_centimetres'   '*'   1.0E+01
     'reciprocal_millimetres'   'reciprocal_nanometres'    '*'   1.0E-06
     'reciprocal_millimetres'   'reciprocal_angstroms'     '*'   1.0E-07
     'reciprocal_millimetres'   'reciprocal_picometres'    '*'   1.0E-09
#
     'reciprocal_nanometres'    'reciprocal_metres'        '*'   1.0E+09
     'reciprocal_nanometres'    'reciprocal_centimetres'   '*'   1.0E+07
     'reciprocal_nanometres'    'reciprocal_millimetres'   '*'   1.0E+06
     'reciprocal_nanometres'    'reciprocal_angstroms'     '*'   1.0E-01
     'reciprocal_nanometres'    'reciprocal_picometres'    '*'   1.0E-03
#
     'reciprocal_angstroms'     'reciprocal_metres'        '*'   1.0E+10
     'reciprocal_angstroms'     'reciprocal_centimetres'   '*'   1.0E+08
     'reciprocal_angstroms'     'reciprocal_millimetres'   '*'   1.0E+07
     'reciprocal_angstroms'     'reciprocal_nanometres'    '*'   1.0E+01
     'reciprocal_angstroms'     'reciprocal_picometres'    '*'   1.0E-02
#
     'reciprocal_picometres'    'reciprocal_metres'        '*'   1.0E+12
     'reciprocal_picometres'    'reciprocal_centimetres'   '*'   1.0E+10
     'reciprocal_picometres'    'reciprocal_millimetres'   '*'   1.0E+09
     'reciprocal_picometres'    'reciprocal_nanometres'    '*'   1.0E+03
     'reciprocal_picometres'    'reciprocal_angstroms'     '*'   1.0E+01
###
     'nanometres_squared'       'angstroms_squared'        '*'   1.0E+02
     'nanometres_squared'       'picometres_squared'       '*'   1.0E+06
#
     'angstroms_squared'        'nanometres_squared'       '*'   1.0E-02
     'angstroms_squared'        'picometres_squared'       '*'   1.0E+04
     'angstroms_squared'        '8pi2_angstroms_squared'   '*'   78.9568

#
     'picometres_squared'       'nanometres_squared'       '*'   1.0E-06
     'picometres_squared'       'angstroms_squared'        '*'   1.0E-04
###
     'nanometres_cubed'         'angstroms_cubed'          '*'   1.0E+03
     'nanometres_cubed'         'picometres_cubed'         '*'   1.0E+09
#
     'angstroms_cubed'          'nanometres_cubed'         '*'   1.0E-03
     'angstroms_cubed'          'picometres_cubed'         '*'   1.0E+06
#
     'picometres_cubed'         'nanometres_cubed'         '*'   1.0E-09
     'picometres_cubed'         'angstroms_cubed'          '*'   1.0E-06
###
     'kilopascals'              'gigapascals'              '*'   1.0E-06
     'gigapascals'              'kilopascals'              '*'   1.0E+06
###
     'hours'                    'minutes'                  '*'   6.0E+01
     'hours'                    'seconds'                  '*'   3.6E+03
     'hours'                    'microseconds'             '*'   3.6E+09
#
     'minutes'                  'hours'                    '/'   6.0E+01
     'minutes'                  'seconds'                  '*'   6.0E+01
     'minutes'                  'microseconds'             '*'   6.0E+07
#
     'seconds'                  'hours'                    '/'   3.6E+03
     'seconds'                  'minutes'                  '/'   6.0E+01
     'seconds'                  'microseconds'             '*'   1.0E+06
#
     'microseconds'             'hours'                    '/'   3.6E+09
     'microseconds'             'minutes'                  '/'   6.0E+07
     'microseconds'             'seconds'                  '/'   1.0E+06
###
     'celsius'                  'kelvins'                  '-'     273.0
     'kelvins'                  'celsius'                  '+'     273.0
###
     'electrons_per_nanometres_cubed'
     'electrons_per_angstroms_cubed'                       '*'   1.0E-03
     'electrons_per_nanometres_cubed'
     'electrons_per_picometres_cubed'                      '*'   1.0E-09
#
     'electrons_per_angstroms_cubed'
     'electrons_per_nanometres_cubed'                      '*'   1.0E+03
     'electrons_per_angstroms_cubed'
     'electrons_per_picometres_cubed'                      '*'   1.0E-06
#
     'electrons_per_picometres_cubed'
     'electrons_per_nanometres_cubed'                      '*'   1.0E+09
     'electrons_per_picometres_cubed'
     'electrons_per_angstroms_cubed'                       '*'   1.0E+06
###
 
 
########################
## DICTIONARY_HISTORY ##
########################

     loop_
    _dictionary_history.version
    _dictionary_history.update
    _dictionary_history.revision

   1.1.3   2001-04-19
;
   Another typo corrections by Wilfred Li, and cleanup by HJB
;

   1.1.2   2001-03-06
;
   Several typo corrections by Wilfred Li
;


   1.1.1   2001-02-16
;
   Several typo corrections by JW
;


   1.1     2001-02-06
;
   Draft resulting from discussions on header for use at NSLS (HJB)
   
   + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME
   
   + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'.
   
   + Add '_diffrn_measurement_axis.measurement_device' and change
   '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'.
   
   + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source',
   '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm',
   '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end',
   '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr',
   '_diffrn_scan_axis.displacement_rstrt_incr', 
   '_diffrn_scan_frame_axis.angle_increment',
   '_diffrn_scan_frame_axis.angle_rstrt_incr',
   '_diffrn_scan_frame_axis.displacement',
   '_diffrn_scan_frame_axis.displacement_increment',and
   '_diffrn_scan_frame_axis.displacement_rstrt_incr'.
   
   + Add _diffrn_measurement.device to category key
   
   + Update yyyy-mm-dd to allow optional time with fractional seconds
   for time stamps.

   + Fix typos caught by RS.
   
   + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to allow
   for coupled axes, as in spiral scans.

   + Add examples for fairly complete headers thanks to R. Sweet and P. 
   Ellis.
;


   1.0     2000-12-21
;
   Release version - few typos and tidying up (BM & HJB)
   
   + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end
   of dictionary.
   
   + Alphabetize dictionary.
;

   0.7.1   2000-09-29
;
   Cleanup fixes (JW)

   + Correct spelling of diffrn_measurement_axis in _axis.id

   + Correct ordering of uses of _item.mandatory_code and _item_default.value
;

   0.7.0   2000-09-09
;
   Respond to comments by I. David Brown (HJB)

   + Added further comments on '\n' and '\t'

   + Updated ITEM_UNITS_LIST by taking section from mmCIF dictionary
 and adding metres.  Changed all spelling 'meter' to 'metre' throughout.

   + Added missing enumerations to _array_structure.compression_type
 and made 'none' the default.

   + Removed parent-child relationship between _array_structure_list.index
 and _array_structure_list.precedence .

   + Improve alphabetization.

   + Fix _array_intensities_gain.esd related function.

   + Improved comments in AXIS.

   + Fixed DIFFRN_FRAME_DATA example.

   + Removed erroneous DIFFRN_MEASUREMENT example.

   + Added _diffrn_measurement_axis.id to the category key.
;

   0.6.0   1999-01-14
;
   Remove redundant information for ENC_NONE data (HJB)

   + After the D5 remove binary section identifier, size and
 compression type.

   + Add Control-L to header.
;
   0.5.1   1999-01-03
;
   Cleanup of typos and syntax errors (HJB)

   + Cleanup example details for DIFFRN_SCAN category.

   + Add missing quote marks for _diffrn_scan.id definition.
;

   0.5   1999-01-01
;
   Modifications for axis definitions and reduction of binary header (HJB)

   + Restored _diffrn_detector.diffrn_id to DIFFRN_DETECTOR KEY.

   + Added AXIS category.

   + Brought complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories
 in from cif_mm.dic for clarity.

   + changed _array_structure.encoding_type from type code to uline and
 added X-Binary-Element-Type to MIME header.

   + added detector beam center _diffrn_detector_element.center[1] and 
_diffrn_detector_element.center[2]

   + corrected item name of _diffrn_refln.frame_id

   + replace reference to _array_intensities.undefined by
 _array_intensities.undefined_value

   + replace references to _array_intensity.scaling with
 _array_intensities.scaling

   + added DIFFRN_SCAN... categories
;

   0.4   1998-08-11
;
   Modifications to the 0.3 imgCIF draft (HJB)

   +  Reflowed comment lines over 80 characters and corrected typos.

   +  Updated examples and descriptions of MIME encoded data.

   +  Change name to cbfext98.dic.
;

   0.3   1998-07-04
;
   Modifications for imgCIF (HJB)

   +  Added binary type, which is a text field containing a variant on
      MIME encoded data.
      
   +  Changed type of _array_data.data to binary and specified internal
      structure of raw binary data.
      
   +  Added _array_data.binary_id, and made 
      _diffrn_frame_data.binary_id and _array_intensities.binary_id
      into pointers to this item.
;

   0.2   1997-12-02
;
   Modifications to the CBF draft (JW):  

   +  Added category hierarchy for describing frame data developed from
      discussions at the BNL imgCIF Workshop Oct 1997.   The following
      changes were made in implementing the workshop draft.  Category
      DIFFRN_ARRAY_DATA was renamed to DIFFRN_FRAME_DATA.  Category
      DIFFRN_FRAME_TYPE was renamed to DIFFRN_DETECTOR_ELEMENT.   The
      parent item for _diffrn_frame_data.array_id was changed from
      array_structure_list.array_id to array_structure.id. Item 
      _diffrn_detector.array_id was deleted.  
   +  Added data item _diffrn_frame_data.binary_id to identify data groups
      within a binary section.  The formal identification of the binary section
      is still fuzzy.  
;

   0.1   1997-01-24
;
   First draft of this dictionary in DDL 2.1 compliant format by John 
   Westbrook (JW).  This version was adapted from the Crystallographic 
   Binary File (CBF) Format Draft Proposal provided by Andy Hammersley (AH).  
 
   Modifications to the CBF draft (JW):  
 
   + In this version the array description has been cast in the categories 
     ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST.  These categories have been 
     generalized to describe array data  of arbitrary dimension.  

   + Array data in this description are contained in the category ARRAY_DATA        .
     This departs from the CBF notion of data existing in some special comment.
     In this description, data is handled as an ordinary data item encapsulated
     in a character data type.   Although handling binary data this manner
     deviates from CIF conventions, it does not violate any DDL 2.1 rules.
     DDL 2.1 regular expressions can be used to define the binary 
     representation which will permit some level of data validation.  In 
     this version, the placeholder type code "any" has been used.
     This translates to a regular expression which will match any pattern.  

     It should be noted that DDL 2.1 already supports array data objects 
     although these have not been used in the current mmCIF dictionary.  It 
     may be possible to use the DDL 2.1 ITEM_STRUCTURE and ITEM_STRUCTURE_LIST
     categories to provide the information that is carried in by the 
     ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST.  By moving the array 
     structure to the DDL level it would be possible to define an array 
     type as well as a regular expression defining the data format. 

   + Multiple array sections can be properly handled within a single datablock.
;
 
 
#-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof
./CBFlib-0.9.2.2/doc/Iaxis.depends_on.html0000644000076500007650000000515011603702115016424 0ustar yayayaya (IUCr) CIF Definition save__axis.depends_on

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_axis.depends_on

Name:
'_axis.depends_on'

Definition:

       The value of _axis.depends_on specifies the next outermost
              axis upon which this axis depends.

              This item is a pointer to _axis.id in the same category.

Mandatory item: no

Category: axis

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Carray_intensities.html0000644000076500007650000001030011603702115017062 0ustar yayayaya (IUCr) CIF Definition save_array_intensities

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

Category ARRAY_INTENSITIES

Name:
'array_intensities'

Description:

       Data items in the ARRAY_INTENSITIES category record the
              information required to recover the intensity data from
              the set of data values stored in the ARRAY_DATA category.

              The detector may have a complex relationship
              between the raw intensity values and the number of
              incident photons.  In most cases, the number stored
              in the final array will have a simple linear relationship
              to the actual number of incident photons, given by
              _array_intensities.gain.  If raw, uncorrected values
              are presented (e.g. for calibration experiments), the
              value of _array_intensities.linearity will be 'raw'
              and _array_intensities.gain will not be used.


Example:

Example 1
 
        loop_
        _array_intensities.array_id
        _array_intensities.linearity
        _array_intensities.gain
        _array_intensities.overload
        _array_intensities.undefined_value
        _array_intensities.pixel_fast_bin_size
        _array_intensities.pixel_slow_bin_size
        _array_intensities.pixel_binning_method
        image_1   linear  1.2    655535   0   2   2    hardware



Category groups:
    inclusive_group
    array_data_group
Category keys:
    _array_intensities.array_id
    _array_intensities.binary_id

Mandatory category: no

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_scan_frame_axis.reference_angle.html0000644000076500007650000000560611603702115023126 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan_frame_axis.reference_angle

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_scan_frame_axis.reference_angle

Name:
'_diffrn_scan_frame_axis.reference_angle'

Definition:

        The setting of the specified axis in degrees
               against which measurements of the reference beam center
               and reference detector distance should be made.

               This is normally the same for all frames, but the
               option is provided here of making changes when
               needed.

               If not provided, it is assumed to be zero.

Type: float

Mandatory item: implicit


Enumeration default: 0.0

Category: diffrn_scan_frame_axis

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_data_frame.center_slow.html0000644000076500007650000000645311603702115021310 0ustar yayayaya (IUCr) CIF Definition save__diffrn_data_frame.center_slow

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_data_frame.center_slow

Name:
'_diffrn_data_frame.center_slow'

Definition:

       The value of _diffrn_data_frame.center_slow is
              the slow index axis beam center position relative to the detector
              element face in the units specified in the data item
              '_diffrn_data_frame.center_units' along the slow
              axis of the detector from the center of the first pixel to
              the point at which the Z-axis (which should be colinear with the
              beam) intersects the face of the detector, if in fact is does.
              At the time of the measurement the current setting of detector
              positioner given frame are used.

              It is important to note that the sense of the axis is used,
              rather than the sign of the pixel-to-pixel increments.


Type: float

Mandatory item: no

Category: diffrn_data_frame

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Iarray_structure_list_axis.fract_displacement_increment.html0000644000076500007650000000533411603702115026556 0ustar yayayaya (IUCr) CIF Definition save__array_structure_list_axis.fract_displacement_increment

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_array_structure_list_axis.fract_displacement_increment

Name:
'_array_structure_list_axis.fract_displacement_increment'

Definition:

        The pixel-centre-to-pixel-centre increment for the displacement
               setting of the specified axis as a decimal fraction of the
               axis unit vector.

Type: float

Mandatory item: no


Enumeration default: 0.0

Category: array_structure_list_axis

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_scan_frame.frame_id.html0000644000076500007650000000534511603702115020544 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan_frame.frame_id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_scan_frame.frame_id

Name:
'_diffrn_scan_frame.frame_id'

Definition:

        The value of this data item is the identifier of the
               frame being examined.

               This item is a pointer to _diffrn_data_frame.id in the
               DIFFRN_DATA_FRAME category.

Type: code

Mandatory item: yes

Category: diffrn_scan_frame

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_radiation.div_y_source.html0000644000076500007650000000623011603702115021336 0ustar yayayaya (IUCr) CIF Definition save__diffrn_radiation.div_y_source

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_radiation.div_y_source

Name:
'_diffrn_radiation.div_y_source'

Definition:

        Beam crossfire in degrees parallel to the laboratory Y axis
               (see AXIS category).

               This is a characteristic of the X-ray beam as it illuminates
               the sample (or specimen) after all monochromation and
               collimation.

               This is the standard uncertainty (e.s.d.) of the directions
               of photons in the YZ plane around the mean source beam
               direction.

               Note that for some synchrotrons this value is specified
               in milliradians, in which case a conversion is needed.
               To convert a value in milliradians to a value in degrees,
               multiply by 0.180 and divide by \p.

Type: float

Mandatory item: no


Enumeration default: 0.0

Category: diffrn_radiation

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/mmcif_ddl_2.1.6.dic0000644000076500007650000031435211603702115015476 0ustar yayayaya########################################################################### # # File: mmcif_ddl.dic # Date: Mon Aug 9 02:48:08 EDT 2004 # # Created from files in CVS module dict-mmcif_ddl.dic unless noted: # mmcif_ddl-header.dic # mmcif_ddl-data.dic # mmcif_ddl-def-1.dic # mmcif_ddl-def-2.dic # ########################################################################### ########################################################################### # # File: mmcif_ddl-header.dic # # mmCIF DDL Core Dictionary with NDB extensions # # This DDL dictionary is a mirror of ddl_core.dic-org with all implicit # data items fully expanded and with NDB extensions added. # # Header Section # # ########################################################################### data_mmcif_ddl.dic _datablock.id mmcif_ddl.dic _datablock.description ; This data block holds the core DDL. ; _dictionary.datablock_id mmcif_ddl.dic _dictionary.title mmcif_ddl.dic _dictionary.version 2.1.6 loop_ _dictionary_history.version _dictionary_history.update _dictionary_history.revision 1.1 1994-07-25 ; DDL 1.1 from Syd Hall et. al. ; 1.2.1 1994-09-18 ; Changes:.........etc. etc. John Westbrook ; 1.2.9 1994-10-05 ; Reflect the results of the Treaty of Brussels. JW. ; 2.0.1 1994-10-15 ; Adapted for closer mapping to DDL1.3 and clearer presentation. SRH/NS. ; 2.0.2 1994-10-16 ; Even closer................... SRH/NS. ; 2.0.3 1994-10-17 ; Coming to grips with the links and dependencies..... SRH/NS. ; 2.0.4 1994-10-20 ; Backed in changes from mm-ddl 1.2.12 Many other changes ... (JW) ; 2.0.5 1994-10-20 ; Some small adjustments..........SRH. ; 2.0.6 1994-10-20 ; More small adjustments..........JW. ; 2.0.7 1994-11-03 ; Changes: (JW) + Place all item and item_linked category definitions with the parent item. + Fixed a number of not so trivial typos. + Corrected errors in the data type conversion table. + Corrected key item inconsistencies. + Added the item_aliases category. ; 2.0.8 1994-11-10 ; Miscellaneous corrections: (JW) + defined sub_category_group + corrected typo in category_examples.id definition + added _item_type_conditions.name in item category + added _item_structure.name in item category + corrected typo in item_aliases category definition + corrected typo in sub_category.method_id definition ; 2.0.9 1994-11-14 ; Changes: (JW) + added ITEM_UNITS, ITEM_UNITS_LIST, and UNITS_CONVERSION categories. + added an additional primitive type for character type items for which comparisons must be case insensitive. Since it is customary to permit item names and category identifiers to be specified in mixed case, it is necessary to declare that case should NOT be considered in any comparisons of these items. ; 2.0.10 1994-11-23 ; Changes: (JW) + Several name category changes for the sake of consistency: enumeration -> item_enumeration enumeration_default -> item_enumeration_default enumeration_limit -> item_enumeration_limit units_conversion -> item_units_conversion + Added _item_related.function_code alternate_exclusive to identify mutually exclusive alternative declarations of the same item. + Added structure options for real symmetric matrices. + Changed from zero based indices to one based indices for compatibility with existing matrix component definitions. + Add _item_linked.parent_name to the key of the item_linked category. + Reorder items in the DDL so be alphabetical within category groups. ; 2.0.11 1994-11-28 ; Changes: (JW) + Corrected spelling error for the data type code in the DICTIONARY_HISTORY category. + Add category BLOCK to hold the data block name and data block description. The block identifier was also added to the key of the item category. The block identifier can be implicitly derived from the STAR "data_" delimiter. This identifier is required to form the key for categories which are conceptually related to the data block as a whole. ; 2.0.12 1994-11-30 ; Changes: (JW) + Added a data item _block.scope to indicate the scope of data item names defined within included data blocks. ; 2.0.13 1994-12-12 ; Changes: (JW) + Deleted data item _block.scope. + Changed DICTIONARY category key to _dictionary.block_id to guarantee only one dictionary definition per block. + Deleted data item _item.block_id as this will be replaced by an item address syntax that will include block, save frame, and url. ; 2.0.14 1994-12-15 ; Changes: (JW) + Made some terminology changes suggested by PMDF _item_enumeration.code -> _item_enumeration.value ITEM_ENUMERATION_DEFAULT -> ITEM_DEFAULT ITEM_ENUMERATION_LIMIT -> ITEM_RANGE + Added item _item_type_list.detail + Version 2.0.14 is being frozen and exported. ; 2.0.15 1995-02-13 ; Changes: (JW) + Added '_' prefix to all data item save frame names. References to data item names now always include a leading underscore independent of the usage context. + A few miscellaneous corrections. ; 2.0.16 1995-06-18 ; Changes: (JW) + Revised the block level categories in the following ways: Changed category BLOCK to DATA_BLOCK. Added connection from _data_block.id to _category.implicit_key in order to provide a formal means of merging the contents of categories between data blocks. + Moved ennumerations for _method_list.code and method_list.language to examples. + Removed symmetric matrix options from the ennumerations for _item_structure.organization. + Added _item_related.function codes for 'associated_value', 'associated_esd', 'replaces' and 'replacedby' + Added data items _item_aliases.dictionary and _item_aliases.dictionary_version. + Reorganized method categories such that multiple methods can be applied at each level of data structure. Introduced a consistent set of categories to hold method associations: ITEM_METHODS, CATEGORY_METHODS, SUB_CATEGORY_METHODS, and DATA_BLOCK_METHODS. Removed data items _category.method_id _sub_category.method_id. ; 2.0.17 1995-06-22 ; Changes: (JW) + Quoted data vaules containing the leading string 'data_'. ; 2.1.0 1995-07-20 ; Changes: (JW) Final adjustments before the first release of the mmCIF dictionary: + changed data_block to datablock to avoid any problems with the STAR data_ reserved token. + created new category to hold item subcategory associations and deleted the subcategory attribute from ITEM category. + modified regular expressions to reflect limitations observed on several platforms. + expanded the ennumeration of _item_related.function_code. + removed default value from _item.manadatory_code. + removed type construct for date and changed date data type to yyyy-mm-dd + added less restrictive data type for alias names. ; 2.1.1 1995-09-26 ; Changes: (JW) + Changed regular expressions for type code to permit single quote. + Corrected regular expression syntax for type name and type date. + Corrected lower bound description for item_range.minimum. The incorrect <= condition is changed to <. + _item_mandatory.code has been now a mandatory item. + _item_aliases.dictionary and _item_aliases.dictionary_version are added to the composite key for category ITEM_ALIASES. + _datablock.id data type changes to type code. + Shortened the name _item_aliases.dictionary_version to _item_aliases.version ; 2.1.2 1997-01-24 ; Changes: (JW) + Added associated_error to the enumeration list of _item_related.function_code. ; 2.1.3 2000-10-16 ; Changes: (JW) + Changed data type for regular expression in _item_type_list.construct to type text. ; 2.1.5 2003-06-23 ; Changes: (JW) + NDB extensions adopted into ddl_core + New partitioning scheme implemented ; 2.1.6 2004-04-15 ; Changes: (JW) + Name changed to mmcif_ddl.dic ; ### EOF mmcif_ddl-header.dic #### ########################################################################### # # File: mmcif_ddl-data.dic # # mmCIF DDL Core Dictionary with NDB extensions # # This DDL dictionary is a mirror of ddl_core.dic-org with all implicit # data items fully expanded and with NDB extensions added. # # Data Section # # ########################################################################### # DATA TYPE CONVERSION TABLE # -------------------------- loop_ _item_type_list.code _item_type_list.primitive_code _item_type_list.detail _item_type_list.construct code char 'A single word' '[^\t\n "]*' char char 'A single line of text' '[^\n]*' text char 'Text which may span lines' '.*' int numb 'Unsigned integer data' '[0-9]+' name uchar 'A data item name (restrictive type)' '_[_A-Za-z0-9]+[.][][_A-Za-z0-9\<\>%/-]+' aliasname uchar 'A DDL 1.4 data item name (less restrictive type)' '_[^\t\n "]+' idname uchar 'A data item name component or identifier' '[_A-Za-z0-9]+' any char 'Any data type' '.*' yyyy-mm-dd char 'A date format' '[0-9][0-9][0-9][0-9]-[0-9]?[0-9]-[0-9][0-9]' # loop_ _category_group_list.id _category_group_list.parent_id _category_group_list.description 'ddl_group' . ; Component categories of the macromolecular DDL ; 'datablock_group' 'ddl_group' ; Categories that describe the characteristics of data blocks. ; 'category_group' 'ddl_group' ; Categories that describe the characteristics of categories. ; 'sub_category_group' 'ddl_group' ; Categories that describe the characteristics of subcategories. ; 'item_group' 'ddl_group' ; Categories that describe the characteristics of data items. ; 'dictionary_group' 'ddl_group' ; Categories that describe the dictionary. ; 'compliance_group' 'ddl_group' ; Categories that are retained specifically for compliance with older versions of the DDL. ; ### EOF mmcif_ddl-data.dic ########################################################################### # # File: mmcif_ddl-def-1.dic # # mmCIF DDL Core Dictionary with NDB extensions # # This DDL dictionary is a mirror of ddl_core.dic-org with all implicit # data items fully expanded and with NDB extensions added. # # Definition Section 1. # (Core Definitions) # # ########################################################################### # ---------------------------------------------------------------------------- save_DATABLOCK _category.description ; Attributes defining the characteristics of a data block. ; _category.id datablock _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id datablock _category_key.name '_datablock.id' loop_ _category_group.id _category_group.category_id 'ddl_group' datablock 'datablock_group' datablock save_ save__datablock.id _item_description.name '_datablock.id' _item_description.description ; The identity of the data block. ; _item.name '_datablock.id' _item.category_id datablock _item.mandatory_code implicit _item_type.name '_datablock.id' _item_type.code code loop_ _item_linked.parent_name _item_linked.child_name '_datablock.id' '_datablock_methods.datablock_id' '_datablock.id' '_dictionary.datablock_id' '_datablock.id' '_category.implicit_key' save_ save__datablock.description _item_description.name '_datablock.description' _item_description.description ; Text description of the data block. ; _item.name '_datablock.description' _item.category_id datablock _item.mandatory_code yes _item_type.name '_datablock.description' _item_type.code text save_ # ---------------------------------------------------------------------------- save_DATABLOCK_METHODS _category.description ; Attributes specifying the association between data blocks and methods. ; _category.id datablock_methods _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name datablock_methods '_datablock_methods.method_id' datablock_methods '_datablock_methods.datablock_id' loop_ _category_group.id _category_group.category_id 'ddl_group' datablock_methods 'datablock_group' datablock_methods save_ save__datablock_methods.datablock_id _item_description.name '_datablock_methods.datablock_id' _item_description.description ; Identifier of data block. ; _item.name '_datablock_methods.datablock_id' _item.category_id datablock_methods _item.mandatory_code implicit _item_type.name '_datablock_methods.datablock_id' _item_type.code code save_ save__datablock_methods.method_id _item_description.name '_datablock_methods.method_id' _item_description.description ; Unique method identifier associated with a data block. ; _item.name '_datablock_methods.method_id' _item.category_id datablock_methods _item.mandatory_code yes _item_type.name '_datablock_methods.method_id' _item_type.code idname save_ # ---------------------------------------------------------------------------- save_CATEGORY _category.description ; Attributes defining the functionality for the entire category. ; _category.id category _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id category _category_key.name '_category.id' loop_ _category_group.id _category_group.category_id 'ddl_group' category 'category_group' category save_ save__category.id _item_description.name '_category.id' _item_description.description ; The identity of the data category. Data items may only be looped with items of the same category. ; _item.name '_category.id' _item.category_id category _item.mandatory_code yes _item_type.name '_category.id' _item_type.code idname loop_ _item_linked.child_name _item_linked.parent_name '_category_examples.id' '_category.id' '_category_group.category_id' '_category.id' '_category_key.id' '_category.id' '_category_methods.category_id' '_category.id' '_item.category_id' '_category.id' save_ save__category.description _item_description.name '_category.description' _item_description.description ; Text description of a category. ; _item.name '_category.description' _item.category_id category _item.mandatory_code yes _item_type.name '_category.description' _item_type.code text save_ save__category.implicit_key _item_description.name '_category.implicit_key' _item_description.description ; An identifier that may be used to distinguish the contents of like categories between data blocks. ; _item.name '_category.implicit_key' _item.category_id category _item.mandatory_code implicit _item_type.name '_category.implicit_key' _item_type.code code save_ save__category.mandatory_code _item_description.name '_category.mandatory_code' _item_description.description ; Whether the category must be specified in a dictionary. ; _item.name '_category.mandatory_code' _item.category_id category _item.mandatory_code yes _item_type.name '_category.mandatory_code' _item_type.code code save_ # ---------------------------------------------------------------------------- save_CATEGORY_EXAMPLES _category.description ; Example applications and descriptions of data items in this category. ; _category.id category_examples _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name category_examples '_category_examples.id' category_examples '_category_examples.case' save_ save__category_examples.id _item_description.name '_category_examples.id' _item_description.description ; The name of category. ; _item.name '_category_examples.id' _item.category_id category_examples _item.mandatory_code implicit _item_type.name '_category_examples.id' _item_type.code idname save_ save__category_examples.case _item_description.name '_category_examples.case' _item_description.description ; A case of examples involving items in this category. ; _item.name '_category_examples.case' _item.category_id category_examples _item.mandatory_code yes _item_type.name '_category_examples.case' _item_type.code text save_ save__category_examples.detail _item_description.name '_category_examples.detail' _item_description.description ; A description of an example _category_examples.case ; _item.name '_category_examples.detail' _item.category_id category_examples _item.mandatory_code no _item_type.name '_category_examples.detail' _item_type.code text save_ # ---------------------------------------------------------------------------- save_CATEGORY_KEY _category.description ; This category holds a list of the item names that uniquely identify the elements of the category. ; _category.id category_key _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name category_key '_category_key.name' category_key '_category_key.id' loop_ _category_group.id _category_group.category_id 'ddl_group' category_key 'category_group' category_key save_ save__category_key.name _item_description.name '_category_key.name' _item_description.description ; The name of a data item that serves as a key identifier for the category (eg. a component of the primary key). ; _item.name '_category_key.name' _item.category_id category_key _item.mandatory_code yes _item_type.name '_category_key.name' _item_type.code name save_ save__category_key.id _item_description.name '_category_key.id' _item_description.description ; The identifier of the category (eg. a component of the primary key). ; _item.name '_category_key.id' _item.category_id category_key _item.mandatory_code implicit _item_type.name '_category_key.id' _item_type.code idname save_ # ---------------------------------------------------------------------------- save_CATEGORY_GROUP _category.description ; Provides a list of category groups to which the base category belongs. ; _category.id category_group _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name category_group '_category_group.id' category_group '_category_group.category_id' loop_ _category_group.id _category_group.category_id 'ddl_group' category_group 'category_group' category_group save_ save__category_group.id _item_description.name '_category_group.id' _item_description.description ; The name of a category group ... ; _item.name '_category_group.id' _item.category_id category_group _item.mandatory_code yes _item_type.name '_category_group.id' _item_type.code idname save_ save__category_group.category_id _item_description.name '_category_group.category_id' _item_description.description ; The name of a category ... ; _item.name '_category_group.category_id' _item.category_id category_group _item.mandatory_code implicit _item_type.name '_category_group.category_id' _item_type.code idname save_ # ---------------------------------------------------------------------------- save_CATEGORY_GROUP_LIST _category.description ; This category provides the definition of each category group. A category group is a collection of related categories. ; _category.id category_group_list _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id category_group_list _category_key.name '_category_group_list.id' loop_ _category_group.id _category_group.category_id 'ddl_group' category_group_list 'category_group' category_group_list save_ save__category_group_list.id _item_description.name '_category_group_list.id' _item_description.description ; The name of a category group ... ; _item.name '_category_group_list.id' _item.category_id category_group_list _item.mandatory_code yes _item_type.name '_category_group_list.id' _item_type.code idname loop_ _item_linked.child_name _item_linked.parent_name '_category_group.id' '_category_group_list.id' '_category_group_list.parent_id' '_category_group_list.id' save_ save__category_group_list.description _item_description.name '_category_group_list.description' _item_description.description ; Text description of a category group... ; _item.name '_category_group_list.description' _item.category_id category_group_list _item.mandatory_code yes _item_type.name '_category_group_list.description' _item_type.code text save_ save__category_group_list.parent_id _item_description.name '_category_group_list.parent_id' _item_description.description ; The name of the optional parent category group. ; _item.name '_category_group_list.parent_id' _item.category_id category_group_list _item.mandatory_code no _item_type.name '_category_group_list.parent_id' _item_type.code idname save_ # ---------------------------------------------------------------------------- save_CATEGORY_METHODS _category.description ; Attributes specifying the association between categories and methods. ; _category.id category_methods _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name category_methods '_category_methods.method_id' category_methods '_category_methods.category_id' loop_ _category_group.id _category_group.category_id 'ddl_group' category_methods 'category_group' category_methods save_ save__category_methods.category_id _item_description.name '_category_methods.category_id' _item_description.description ; The name of the category ; _item.name '_category_methods.category_id' _item.category_id category_methods _item.mandatory_code implicit _item_type.name '_category_methods.category_id' _item_type.code idname save_ save__category_methods.method_id _item_description.name '_category_methods.method_id' _item_description.description ; The name of the method ; _item.name '_category_methods.method_id' _item.category_id category_methods _item.mandatory_code yes _item_type.name '_category_methods.method_id' _item_type.code idname save_ # ---------------------------------------------------------------------------- save_SUB_CATEGORY _category.description ; The purpose of a sub-category is to define an association between data items within a category and optionally provide a method to validate the collection of items. The sub-category named 'cartesian' might be applied to the data items for the coordinates x, y, and z. ; _category.id sub_category _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id sub_category _category_key.name '_sub_category.id' loop_ _category_group.id _category_group.category_id 'ddl_group' sub_category 'sub_category_group' sub_category save_ save__sub_category.id _item_description.name '_sub_category.id' _item_description.description ; The identity of the sub-category. ; _item.name '_sub_category.id' _item.category_id sub_category _item.mandatory_code yes _item_type.name '_sub_category.id' _item_type.code idname loop_ _item_linked.child_name _item_linked.parent_name '_sub_category_examples.id' '_sub_category.id' '_sub_category_methods.sub_category_id' '_sub_category.id' '_item_sub_category.id' '_sub_category.id' save_ save__sub_category.description _item_description.name '_sub_category.description' _item_description.description ; Description of the sub-category. ; _item.name '_sub_category.description' _item.category_id sub_category _item.mandatory_code yes _item_type.name '_sub_category.description' _item_type.code text save_ # ---------------------------------------------------------------------------- save_SUB_CATEGORY_EXAMPLES _category.description ; Example applications and descriptions of data items in this subcategory. ; _category.id sub_category_examples _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name sub_category_examples '_sub_category_examples.id' sub_category_examples '_sub_category_examples.case' loop_ _category_group.id _category_group.category_id 'ddl_group' sub_category_examples 'sub_category_group' sub_category_examples save_ save__sub_category_examples.id _item_description.name '_sub_category_examples.id' _item_description.description ; The name for the subcategory. ; _item.name '_sub_category_examples.id' _item.category_id sub_category_examples _item.mandatory_code yes _item_type.name '_sub_category_examples.id' _item_type.code idname save_ save__sub_category_examples.case _item_description.name '_sub_category_examples.case' _item_description.description ; An example involving items in this subcategory. ; _item.name '_sub_category_examples.case' _item.category_id sub_category_examples _item.mandatory_code yes _item_type.name '_sub_category_examples.case' _item_type.code text save_ save__sub_category_examples.detail _item_description.name '_sub_category_examples.detail' _item_description.description ; A description of an example _sub_category_examples.case ; _item.name '_sub_category_examples.detail' _item.category_id sub_category_examples _item.mandatory_code no _item_type.name '_sub_category_examples.detail' _item_type.code text save_ # ---------------------------------------------------------------------------- save_SUB_CATEGORY_METHODS _category.description ; Attributes specifying the association between subcategories and methods. ; _category.id sub_category_methods _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name sub_category_methods '_sub_category_methods.method_id' sub_category_methods '_sub_category_methods.sub_category_id' loop_ _category_group.id _category_group.category_id 'ddl_group' sub_category_methods 'sub_category_group' sub_category_methods save_ save__sub_category_methods.sub_category_id _item_description.name '_sub_category_methods.sub_category_id' _item_description.description ; The name of the subcategory ; _item.name '_sub_category_methods.sub_category_id' _item.category_id sub_category_methods _item.mandatory_code yes _item_type.name '_sub_category_methods.sub_category_id' _item_type.code idname save_ save__sub_category_methods.method_id _item_description.name '_sub_category_methods.method_id' _item_description.description ; The name of the method ; _item.name '_sub_category_methods.method_id' _item.category_id sub_category_methods _item.mandatory_code yes _item_type.name '_sub_category_methods.method_id' _item_type.code idname save_ # ---------------------------------------------------------------------------- save_ITEM _category.description ; Attributes which describe the characteristics of a data item. ; _category.id item _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id item _category_key.name '_item.name' loop_ _category_group.id _category_group.category_id 'ddl_group' item 'item_group' item save_ save__item.name _item_description.name '_item.name' _item_description.description ; Data name of the defined item. ; _item_type.name '_item.name' _item_type.code name _item.name '_item.name' _item.category_id item _item.mandatory_code implicit loop_ _item_linked.child_name _item_linked.parent_name '_category_key.name' '_item.name' '_item_aliases.name' '_item.name' '_item_default.name' '_item.name' '_item_dependent.name' '_item.name' '_item_dependent.dependent_name' '_item.name' '_item_description.name' '_item.name' '_item_enumeration.name' '_item.name' '_item_examples.name' '_item.name' '_item_linked.child_name' '_item.name' '_item_linked.parent_name' '_item.name' '_item_methods.name' '_item.name' '_item_range.name' '_item.name' '_item_related.name' '_item.name' '_item_related.related_name' '_item.name' '_item_type.name' '_item.name' '_item_type_conditions.name' '_item.name' '_item_structure.name' '_item.name' '_item_sub_category.name' '_item.name' '_item_units.name' '_item.name' save_ save__item.mandatory_code _item_description.name '_item.mandatory_code' _item_description.description ; Signals if the defined item is mandatory for the proper description of its category. ; _item.name '_item.mandatory_code' _item.category_id item _item.mandatory_code yes _item_type.name '_item.mandatory_code' _item_type.code code loop_ _item_enumeration.name _item_enumeration.value _item_enumeration.detail '_item.mandatory_code' yes 'required item in this category' '_item.mandatory_code' no 'optional item in this category' '_item.mandatory_code' implicit 'required item but may be determined from context' save_ save__item.category_id _item_description.name '_item.category_id' _item_description.description ; This is category id of the item. ; _item.name '_item.category_id' _item.category_id item _item.mandatory_code implicit _item_type.name '_item.category_id' _item_type.code idname save_ # ---------------------------------------------------------------------------- save_ITEM_ALIASES _category.description ; This category holds a list of possible alias names or synonyms for each data item. Each alias name is identified by the name and version of the dictionary to which it belongs. ; _category.id item_aliases _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name item_aliases '_item_aliases.alias_name' item_aliases '_item_aliases.dictionary' item_aliases '_item_aliases.version' save_ save__item_aliases.name _item_description.name '_item_aliases.name' _item_description.description ; Name for the data item. ; _item.name '_item_aliases.name' _item.category_id item_aliases _item.mandatory_code implicit _item_type.name '_item_aliases.name' _item_type.code name save_ save__item_aliases.alias_name _item_description.name '_item_aliases.alias_name' _item_description.description ; Alias name for the data item. ; _item.name '_item_aliases.alias_name' _item.category_id item_aliases _item.mandatory_code yes _item_type.name '_item_aliases.alias_name' _item_type.code aliasname save_ save__item_aliases.dictionary _item_description.name '_item_aliases.dictionary' _item_description.description ; The dictionary in which the alias name is defined. ; _item.name '_item_aliases.dictionary' _item.category_id item_aliases _item.mandatory_code yes _item_type.name '_item_aliases.dictionary' _item_type.code char save_ save__item_aliases.version _item_description.name '_item_aliases.version' _item_description.description ; The version of the dictionary in which the alias name is defined. ; _item.name '_item_aliases.version' _item.category_id item_aliases _item.mandatory_code yes _item_type.name '_item_aliases.version' _item_type.code char save_ # ---------------------------------------------------------------------------- save_ITEM_DEFAULT _category.description ; Attributes specifying the default value for a data item. ; _category.id item_default _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id item_default _category_key.name '_item_default.name' loop_ _category_group.id _category_group.category_id 'ddl_group' item_default 'item_group' item_default save_ save__item_default.name _item_description.name '_item_default.name' _item_description.description ; The name of item for which the default value is defined ; _item.name '_item_default.name' _item.category_id item_default _item.mandatory_code implicit _item_type.name '_item_default.name' _item_type.code name save_ save__item_default.value _item_description.name '_item_default.value' _item_description.description ; The default value for the defined item if it is not specified explicitly. If a data value is not declared, the default is assumed to be the most likely or natural value. ; _item.name '_item_default.value' _item.category_id item_default _item.mandatory_code no _item_type.name '_item_default.value' _item_type.code any save_ # ---------------------------------------------------------------------------- save_ITEM_DEPENDENT _category.description ; Attributes which identify other data items that must be specified for the defined data item to be valid. ; _category.id item_dependent _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name item_dependent '_item_dependent.name' item_dependent '_item_dependent.dependent_name' save_ save__item_dependent.name _item_description.name '_item_dependent.name' _item_description.description ; Item name of a dependent item. ; _item.name '_item_dependent.name' _item.category_id item_dependent _item.mandatory_code implicit _item_type.name '_item_dependent.name' _item_type.code name save_ save__item_dependent.dependent_name _item_description.name '_item_dependent.dependent_name' _item_description.description ; Data name of a dependent item. ; _item.name '_item_dependent.dependent_name' _item.category_id item_dependent _item.mandatory_code yes _item_type.name '_item_dependent.dependent_name' _item_type.code name save_ # ---------------------------------------------------------------------------- save_ITEM_DESCRIPTION _category.description ; This category holds the descriptions of each data item. ; _category.id item_description _category.mandatory_code yes _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name item_description '_item_description.name' item_description '_item_description.description' loop_ _category_group.id _category_group.category_id 'ddl_group' item_description 'item_group' item_description save_ save__item_description.name _item_description.name '_item_description.name' _item_description.description ; Tne name of data item. ; _item.name '_item_description.name' _item.category_id item_description _item.mandatory_code implicit _item_type.name '_item_description.name' _item_type.code name save_ save__item_description.description _item_description.name '_item_description.description' _item_description.description ; Text decription of the defined data item. ; _item.name '_item_description.description' _item.category_id item_description _item.mandatory_code yes _item_type.name '_item_description.description' _item_type.code text save_ # ---------------------------------------------------------------------------- save_ITEM_ENUMERATION _category.description ; Attributes which specify the permitted enumeration of the items. ; _category.id item_enumeration _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name item_enumeration '_item_enumeration.name' item_enumeration '_item_enumeration.value' loop_ _category_group.id _category_group.category_id 'ddl_group' item_enumeration 'item_group' item_enumeration save_ save__item_enumeration.name _item_description.name '_item_enumeration.name' _item_description.description ; Name of data item. ; _item.name '_item_enumeration.name' _item.category_id item_enumeration _item.mandatory_code implicit _item_type.name '_item_enumeration.name' _item_type.code name save_ save__item_enumeration.value _item_description.name '_item_enumeration.value' _item_description.description ; A permissible value, character or number, for the defined item. ; _item.name '_item_enumeration.value' _item.category_id item_enumeration _item.mandatory_code yes _item_type.name '_item_enumeration.value' _item_type.code any save_ save__item_enumeration.detail _item_description.name '_item_enumeration.detail' _item_description.description ; A description of a permissible value for the defined item. ; _item.name '_item_enumeration.detail' _item.category_id item_enumeration _item.mandatory_code no _item_type.name '_item_enumeration.detail' _item_type.code text save_ # ---------------------------------------------------------------------------- save_ITEM_EXAMPLES _category.description ; Attributes for describing application examples of the data item. ; _category.id item_examples _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name item_examples '_item_examples.name' item_examples '_item_examples.case' loop_ _category_group.id _category_group.category_id 'ddl_group' item_examples 'item_group' item_examples save_ save__item_examples.name _item_description.name '_item_examples.name' _item_description.description ; The name of data item for the example. ; _item.name '_item_examples.name' _item.category_id item_examples _item.mandatory_code implicit _item_type.name '_item_examples.name' _item_type.code name save_ save__item_examples.case _item_description.name '_item_examples.case' _item_description.description ; An example application of the defined data item. ; _item.name '_item_examples.case' _item.category_id item_examples _item.mandatory_code no _item_type.name '_item_examples.case' _item_type.code text save_ save__item_examples.detail _item_description.name '_item_examples.detail' _item_description.description ; A description of an example specified in _item_example.case ; _item.name '_item_examples.detail' _item.category_id item_examples _item.mandatory_code no _item_type.name '_item_examples.detail' _item_type.code text save_ # ---------------------------------------------------------------------------- save_ITEM_LINKED _category.description ; Attributes which describe how equivalent data items are linked within categories and across different categories. ; _category.id item_linked _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name item_linked '_item_linked.child_name' item_linked '_item_linked.parent_name' loop_ _category_group.id _category_group.category_id 'ddl_group' item_linked 'item_group' item_linked save_ save__item_linked.child_name _item_description.name '_item_linked.child_name' _item_description.description ; Name of the child data item. ; _item.name '_item_linked.child_name' _item.category_id item_linked _item.mandatory_code yes _item_type.name '_item_linked.child_name' _item_type.code name save_ save__item_linked.parent_name _item_description.name '_item_linked.parent_name' _item_description.description ; Name of the parent data item. ; _item.name '_item_linked.parent_name' _item.category_id item_linked _item.mandatory_code implicit _item_type.name '_item_linked.parent_name' _item_type.code name save_ # ---------------------------------------------------------------------------- save_ITEM_METHODS _category.description ; Attributes specifying the association between data items and methods. ; _category.id item_methods _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name item_methods '_item_methods.method_id' item_methods '_item_methods.name' loop_ _category_group.id _category_group.category_id 'ddl_group' item_methods 'item_group' item_methods save_ save__item_methods.name _item_description.name '_item_methods.name' _item_description.description ; The name of the item ; _item.name '_item_methods.name' _item.category_id item_methods _item.mandatory_code implicit _item_type.name '_item_methods.name' _item_type.code name save_ save__item_methods.method_id _item_description.name '_item_methods.method_id' _item_description.description ; The name of itemthe method ; _item.name '_item_methods.method_id' _item.category_id item_methods _item.mandatory_code yes _item_type.name '_item_methods.method_id' _item_type.code idname save_ # ---------------------------------------------------------------------------- save_ITEM_RANGE _category.description ; The range of permissible values of a data item. When multiple ranges are specified they are interpreted sequentially using a logical OR. To specify that an item value may be equal to a boundary value, specify an item range where the maximum and mimimum values equal the boundary value. ; _category.id item_range _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name item_range '_item_range.name' item_range '_item_range.minimum' item_range '_item_range.maximum' loop_ _category_group.id _category_group.category_id 'ddl_group' item_range 'item_group' item_range save_ save__item_range.name _item_description.name '_item_range.name' _item_description.description ; Name of data item ... ; _item.name '_item_range.name' _item.category_id item_range _item.mandatory_code implicit _item_type.name '_item_range.name' _item_type.code name save_ save__item_range.minimum _item_description.name '_item_range.minimum' _item_description.description ; Minimum permissible value of a data item or the lower bound of a permissible range. ( minimum value < data value) ; _item.name '_item_range.minimum' _item.category_id item_range _item.mandatory_code no _item_type.name '_item_range.minimum' _item_type.code any save_ save__item_range.maximum _item_description.name '_item_range.maximum' _item_description.description ; Maximum permissible value of a data item or the upper bound of a permissible range. ( maximum value > data value) ; _item.name '_item_range.maximum' _item.category_id item_range _item.mandatory_code no _item_type.name '_item_range.maximum' _item_type.code any save_ # ---------------------------------------------------------------------------- save_ITEM_RELATED _category.description ; Attributes which specify recognized relationships between data items. ; _category.id item_related _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name item_related '_item_related.name' item_related '_item_related.related_name' item_related '_item_related.function_code' loop_ _category_group.id _category_group.category_id 'ddl_group' item_related 'item_group' item_related save_ save__item_related.name _item_description.name '_item_related.name' _item_description.description ; Identifies a defined data item ... ; _item.name '_item_related.name' _item.category_id item_related _item.mandatory_code implicit _item_type.name '_item_related.name' _item_type.code name save_ save__item_related.related_name _item_description.name '_item_related.related_name' _item_description.description ; Identifies a data item by name which is closely related to the defined data item by the manner described by _item_related.function_code ; _item.name '_item_related.related_name' _item.category_id item_related _item.mandatory_code yes _item_type.name '_item_related.related_name' _item_type.code name save_ save__item_related.function_code _item_description.name '_item_related.function_code' _item_description.description ; The code for the type of relationship of the item identified by _item_related.name and the defined item. ALTERNATE indicates that the item identified in _item_related.related_name is an alternative expression in terms of its application and attributes to the item in this definition. ALTERNATE_EXCLUSIVE indicates that the item identified in _item_related.related_name is an alternative expression in terms of its application and attributes to the item in this definition. Only one of the alternative forms may be specified. CONVENTION indicates that the item identified in _item_related.related_name differs from the defined item only in terms of a convention in its expression. CONVERSION_CONSTANT indicates that the item identified in _item_related.related_name differs from the defined item only by a known constant. CONVERSION_ARBITRARY indicates that the item identified in _item_related.related_name differs from the defined item only by a arbitrary constant. REPLACES indicates that the defined item replaces the item identified in _item_related.related_name. REPLACEDBY indicates that the defined item is replaced by the item identified in _item_related.related_name. ASSOCIATED_VALUE indicates that the item identified in _item_related.related_name is meaningful when associated with the defined item. ASSOCIATED_ESD indicates that the item identified in _item_related.related_name is the estimated standard deviation of of the defined item. ; _item.name '_item_related.function_code' _item.category_id item_related _item.mandatory_code yes _item_type.name '_item_related.function_code' _item_type.code code loop_ _item_enumeration.name _item_enumeration.value _item_enumeration.detail '_item_related.function_code' alternate 'alternate form of the item' '_item_related.function_code' alternate_exclusive 'mutually exclusive alternate form of the item' '_item_related.function_code' convention 'depends on defined convention' '_item_related.function_code' conversion_constant 'related by a known conversion factor' '_item_related.function_code' conversion_arbitrary 'related by a arbitrary conversion factor' '_item_related.function_code' replaces 'a replacement definition' '_item_related.function_code' replacedby 'an obsolete definition' '_item_related.function_code' associated_value 'a meaningful value when related to the item' '_item_related.function_code' associated_esd 'an estimated standard deviation of the item' '_item_related.function_code' associated_error 'an estimated error of the item' save_ # ---------------------------------------------------------------------------- save_ITEM_STRUCTURE _category.description ; This category holds the association between data items and named vector/matrix declarations. ; _category.id item_structure _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id item_structure _category_key.name '_item_structure.name' loop_ _category_group.id _category_group.category_id 'ddl_group' item_structure 'item_group' item_structure save_ save__item_structure.name _item_description.name '_item_structure.name' _item_description.description ; The name of data item ; _item.name '_item_structure.name' _item.category_id item_structure _item.mandatory_code implicit _item_type.name '_item_structure.name' _item_type.code name save_ save__item_structure.code _item_description.name '_item_structure.code' _item_description.description ; Provides an indirect reference into the list of structure type definition in category item_structure_list. ; _item.name '_item_structure.code' _item.category_id item_structure _item.mandatory_code yes _item_type.name '_item_structure.code' _item_type.code code save_ save__item_structure.organization _item_description.name '_item_structure.organization' _item_description.description ; Identifies if the struct is defined in column or row major order. Only the unique elements of symmetric matrices are specified. ; _item.name '_item_structure.organization' _item.category_id item_structure _item.mandatory_code yes _item_type.name '_item_structure.organization' _item_type.code code loop_ _item_enumeration.name _item_enumeration.value _item_enumeration.detail '_item_structure.organization' 'columnwise' 'column major order' '_item_structure.organization' 'rowwise' 'row major order' save_ # ---------------------------------------------------------------------------- save_ITEM_STRUCTURE_LIST _category.description ; This category holds a description for each structure type. ; _category.id item_structure_list _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name item_structure_list '_item_structure_list.code' item_structure_list '_item_structure_list.index' loop_ _category_group.id _category_group.category_id 'ddl_group' item_structure_list 'item_group' item_structure_list save_ save__item_structure_list.code _item_description.name '_item_structure_list.code' _item_description.description ; The name of the matrix/vector structure declaration. ; _item.name '_item_structure_list.code' _item.category_id item_structure_list _item.mandatory_code yes _item_linked.parent_name '_item_structure_list.code' _item_linked.child_name '_item_structure.code' _item_type.name '_item_structure_list.code' _item_type.code code save_ save__item_structure_list.index _item_description.name '_item_structure_list.index' _item_description.description ; Identifies the one based index of a row/column of the structure. ; _item.name '_item_structure_list.index' _item.category_id item_structure_list _item.mandatory_code yes loop_ _item_range.name _item_range.minimum _item_range.maximum '_item_structure_list.index' 1 1 '_item_structure_list.index' 1 . _item_type.name '_item_structure_list.index' _item_type.code int save_ save__item_structure_list.dimension _item_description.name '_item_structure_list.dimension' _item_description.description ; Identifies the length of this row/column of the structure. ; _item.name '_item_structure_list.dimension' _item.category_id item_structure_list _item.mandatory_code yes loop_ _item_range.name _item_range.minimum _item_range.maximum '_item_structure_list.dimension' 1 1 '_item_structure_list.dimension' 1 . _item_type.name '_item_structure_list.dimension' _item_type.code int save_ # ---------------------------------------------------------------------------- save_ITEM_SUB_CATEGORY _category.description ; This category assigns data items to subcategories. ; _category.id item_sub_category _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name item_sub_category '_item_sub_category.id' item_sub_category '_item_sub_category.name' loop_ _category_group.id _category_group.category_id 'sub_category_group' item_sub_category 'item_group' item_sub_category save_ save__item_sub_category.name _item_description.name '_item_sub_category.name' _item_description.description ; The name of data item ; _item.name '_item_sub_category.name' _item.category_id item_sub_category _item.mandatory_code implicit _item_type.name '_item_sub_category.name' _item_type.code name save_ save__item_sub_category.id _item_description.name '_item_sub_category.id' _item_description.description ; The identifier of subcategory ; _item.name '_item_sub_category.id' _item.category_id item_sub_category _item.mandatory_code yes _item_type.name '_item_sub_category.id' _item_type.code idname save_ # ---------------------------------------------------------------------------- save_ITEM_TYPE _category.description ; Attributes for specifying the data type code for each data item. ; _category.id item_type _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id item_type _category_key.name '_item_type.name' loop_ _category_group.id _category_group.category_id 'ddl_group' item_type 'item_group' item_type save_ save__item_type.name _item_description.name '_item_type.name' _item_description.description ; The name of data item ; _item.name '_item_type.name' _item.category_id item_type _item.mandatory_code implicit _item_type.name '_item_type.name' _item_type.code name save_ save__item_type.code _item_description.name '_item_type.code' _item_description.description ; Data type of defined data item ; _item.name '_item_type.code' _item.category_id item_type _item.mandatory_code yes _item_type.name '_item_type.code' _item_type.code code save_ # ---------------------------------------------------------------------------- save_ITEM_TYPE_CONDITIONS _category.description ; Attributes for specifying additional conditions associated with the data type of the item. ; _category.id item_type_conditions _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id item_type_conditions _category_key.name '_item_type_conditions.name' loop_ _category_group.id _category_group.category_id 'ddl_group' item_type_conditions 'item_group' item_type_conditions 'compliance_group' item_type_conditions save_ save__item_type_conditions.name _item_description.name '_item_type_conditions.name' _item_description.description ; The name of data item ; _item.name '_item_type_conditions.name' _item.category_id item_type_conditions _item.mandatory_code implicit _item_type.name '_item_type_conditions.name' _item_type.code name save_ save__item_type_conditions.code _item_description.name '_item_type_conditions.code' _item_description.description ; Codes defining conditions on the _item_type.code specification. 'esd' permits a number string to contain an appended standard deviation number enclosed within parentheses. E.g. 4.37(5) 'seq' permits data to be declared as a sequence of values separated by a comma <,> or a colon <:>. * The sequence v1,v2,v3,. signals that v1, v2, v3, etc. are alternative values or the data item. * The sequence v1:v2 signals that v1 and v2 are the boundary values of a continuous range of values. This mechanism was used to specify permitted ranges of an item in previous DDL versions. Combinations of alternate and range sequences are permitted. ; _item.name '_item_type_conditions.code' _item.category_id item_type_conditions _item.mandatory_code yes _item_type.name '_item_type_conditions.code' _item_type.code code loop_ _item_enumeration.name _item_enumeration.value _item_enumeration.detail '_item_type_conditions.code' none 'no extra conditions apply to this data item' '_item_type_conditions.code' esd 'numbers may have esd values appended within ()' '_item_type_conditions.code' seq 'data may be declared as a comma or colon separated sequence' save_ # ---------------------------------------------------------------------------- save_ITEM_TYPE_LIST _category.description ; Attributes which define each type code. ; _category.id item_type_list _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id item_type_list _category_key.name '_item_type_list.code' loop_ _category_group.id _category_group.category_id 'ddl_group' item_type_list 'item_group' item_type_list save_ save__item_type_list.code _item_description.name '_item_type_list.code' _item_description.description ; The codes specifying the nature of the data value. ; _item.name '_item_type_list.code' _item.category_id item_type_list _item.mandatory_code yes _item_type.name '_item_type_list.code' _item_type.code code _item_linked.child_name '_item_type.code' _item_linked.parent_name '_item_type_list.code' save_ save__item_type_list.primitive_code _item_description.name '_item_type_list.primitive_code' _item_description.description ; The codes specifying the primitive type of the data value. ; _item.name '_item_type_list.primitive_code' _item.category_id item_type_list _item.mandatory_code yes _item_type.name '_item_type_list.primitive_code' _item_type.code code loop_ _item_enumeration.name _item_enumeration.value _item_enumeration.detail '_item_type_list.primitive_code' numb 'numerically-interpretable string' '_item_type_list.primitive_code' char 'character or text string (case-sensitive)' '_item_type_list.primitive_code' uchar 'character or text string (case-insensitive)' '_item_type_list.primitive_code' null 'for dictionary purposes only' save_ save__item_type_list.construct _item_description.name '_item_type_list.construct' _item_description.description ; When a data value can be defined as a pre-determined sequence of characters, or optional characters, or data names (for which the definition is also available), it is specified as a construction. The rules of construction conform to the the regular expression (REGEX) specificatiopns detailed in the IEEE document P1003.2 Draft 11.2 Sept 1991 (ftp file '/doc/POSIX/1003.2/p121-140'). Resolved data names for which _item_type_list.construct specifications exist are replaced by these constructions, otherwise the data name string is not replaced. ; _item.name '_item_type_list.construct' _item.category_id item_type_list _item.mandatory_code no _item_type.name '_item_type_list.construct' _item_type.code text _item_examples.name '_item_type_list.construct' _item_examples.case '{_year}-{_month}-{_day}' _item_examples.detail 'typical construction for _date' save_ save__item_type_list.detail _item_description.name '_item_type_list.detail' _item_description.description ; An optional description of the data type ; _item.name '_item_type_list.detail' _item.category_id item_type_list _item.mandatory_code no _item_type.name '_item_type_list.detail' _item_type.code text save_ # ---------------------------------------------------------------------------- save_ITEM_UNITS _category.description ; Specifies the physical units in which data items are expressed. ; _category.id item_units _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id item_units _category_key.name '_item_units.name' loop_ _category_group.id _category_group.category_id 'ddl_group' item_units 'item_group' item_units save_ save__item_units.name _item_description.name '_item_units.name' _item_description.description ; The name of data item ; _item.name '_item_units.name' _item.category_id item_units _item.mandatory_code implicit _item_type.name '_item_units.name' _item_type.code name save_ save__item_units.code _item_description.name '_item_units.code' _item_description.description ; The identifier of unit in which the data item is expressed. ; _item.name '_item_units.code' _item.category_id item_units _item.mandatory_code yes _item_type.name '_item_units.code' _item_type.code code save_ # ---------------------------------------------------------------------------- save_ITEM_UNITS_CONVERSION _category.description ; Conversion factors between the various units of measure defined in the ITEM_UNITS_LIST category. ; _category.id item_units_conversion _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name item_units_conversion '_item_units_conversion.from_code' item_units_conversion '_item_units_conversion.to_code' loop_ _category_group.id _category_group.category_id 'ddl_group' item_units_conversion 'item_group' item_units_conversion save_ save__item_units_conversion.from_code _item_description.name '_item_units_conversion.from_code' _item_description.description ; The unit system on which the conversion operation is applied to produce the unit system specified in _item_units_conversion.to_code. = ; _item.name '_item_units_conversion.from_code' _item.category_id item_units_conversion _item.mandatory_code yes _item_type.name '_item_units_conversion.from_code' _item_type.code code save_ save__item_units_conversion.to_code _item_description.name '_item_units_conversion.to_code' _item_description.description ; The unit system produced after an operation is applied to the unit system specified by _item_units_conversion.from_code. = ; _item.name '_item_units_conversion.to_code' _item.category_id item_units_conversion _item.mandatory_code yes _item_type.name '_item_units_conversion.to_code' _item_type.code code save_ save__item_units_conversion.operator _item_description.name '_item_units_conversion.operator' _item_description.description ; The arithmetic operator required to convert between the unit systems: = ; _item.name '_item_units_conversion.operator' _item.category_id item_units_conversion _item.mandatory_code yes _item_type.name '_item_units_conversion.operator' _item_type.code code loop_ _item_enumeration.name _item_enumeration.value _item_enumeration.detail '_item_units_conversion.operator' '+' 'addition' '_item_units_conversion.operator' '-' 'subtraction' '_item_units_conversion.operator' '*' 'multiplication' '_item_units_conversion.operator' '/' 'division' save_ save__item_units_conversion.factor _item_description.name '_item_units_conversion.factor' _item_description.description ; The arithmetic operation required to convert between the unit systems: = ; _item.name '_item_units_conversion.factor' _item.category_id item_units_conversion _item.mandatory_code yes _item_type.name '_item_units_conversion.factor' _item_type.code any save_ # ---------------------------------------------------------------------------- save_ITEM_UNITS_LIST _category.description ; Attributes which describe the physical units of measure in which data items may be expressed. ; _category.id item_units_list _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id item_units_list _category_key.name '_item_units_list.code' loop_ _category_group.id _category_group.category_id 'ddl_group' item_units_list 'item_group' item_units_list save_ save__item_units_list.code _item_description.name '_item_units_list.code' _item_description.description ; The code specifying the name of the unit of measure. ; _item.name '_item_units_list.code' _item.category_id item_units_list _item.mandatory_code yes _item_type.name '_item_units_list.code' _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_item_units.code' '_item_units_list.code' '_item_units_conversion.from_code' '_item_units_list.code' '_item_units_conversion.to_code' '_item_units_list.code' save_ save__item_units_list.detail _item_description.name '_item_units_list.detail' _item_description.description ; A description of the unit of measure. ; _item.name '_item_units_list.detail' _item.category_id item_units_list _item.mandatory_code no _item_type.name '_item_units_list.detail' _item_type.code text save_ # ---------------------------------------------------------------------------- save_METHOD_LIST _category.description ; Attributes specifying the list of methods applicable to data items, sub-categories, and categories. ; _category.id method_list _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id method_list _category_key.name '_method_list.id' loop_ _category_group.id _category_group.category_id 'ddl_group' method_list 'item_group' method_list 'category_group' method_list save_ save__method_list.id _item_description.name '_method_list.id' _item_description.description ; Identity of method in the list referenced by _method.id ; _item.name '_method_list.id' _item.category_id method_list _item.mandatory_code yes _item_type.name '_method_list.id' _item_type.code idname loop_ _item_linked.child_name _item_linked.parent_name '_item_methods.method_id' '_method_list.id' '_category_methods.method_id' '_method_list.id' '_sub_category_methods.method_id' '_method_list.id' '_datablock_methods.method_id' '_method_list.id' save_ save__method_list.detail _item_description.name '_method_list.detail' _item_description.description ; Description of application method in _method_list.id ; _item.name '_method_list.detail' _item.category_id method_list _item.mandatory_code no _item_type.name '_method_list.detail' _item_type.code text save_ save__method_list.inline _item_description.name '_method_list.inline' _item_description.description ; Inline text of a method associated with the data item. ; _item.name '_method_list.inline' _item.category_id method_list _item.mandatory_code yes _item_type.name '_method_list.inline' _item_type.code text save_ save__method_list.code _item_description.name '_method_list.code' _item_description.description ; A code that describes the function of the method. ; _item.name '_method_list.code' _item.category_id method_list _item.mandatory_code yes _item_type.name '_method_list.code' _item_type.code code loop_ _item_examples.name _item_examples.case _item_examples.detail '_method_list.code' calculation 'method to calculate the item ' '_method_list.code' verification 'method to verify the data item ' '_method_list.code' cast 'method to provide cast conversion ' '_method_list.code' addition 'method to define item + item ' '_method_list.code' division 'method to define item / item ' '_method_list.code' multiplication 'method to define item * item ' '_method_list.code' equivalence 'method to define item = item ' '_method_list.code' other 'miscellaneous method ' save_ save__method_list.language _item_description.name '_method_list.language' _item_description.description ; Language in which the method is expressed. ; _item.name '_method_list.language' _item.category_id method_list _item.mandatory_code yes _item_type.name '_method_list.language' _item_type.code code loop_ _item_examples.name _item_examples.case _item_examples.detail '_method_list.language' BNF ? '_method_list.language' C ? '_method_list.language' C++ ? '_method_list.language' FORTRAN ? '_method_list.language' LISP ? '_method_list.language' PASCAL ? '_method_list.language' PEARL ? '_method_list.language' TCL ? '_method_list.language' OTHER ? save_ # ---------------------------------------------------------------------------- save_DICTIONARY _category.description ; Attributes for specifying the dictionary title, version and data block identifier. ; _category.id dictionary _category.mandatory_code yes _category.implicit_key mmcif_ddl.dic _category_key.id dictionary _category_key.name '_dictionary.datablock_id' loop_ _category_group.id _category_group.category_id 'ddl_group' dictionary 'datablock_group' dictionary 'dictionary_group' dictionary save_ save__dictionary.datablock_id _item_description.name '_dictionary.datablock_id' _item_description.description ; The identifier for the data block containing the dictionary. ; _item.name '_dictionary.datablock_id' _item.category_id dictionary _item.mandatory_code implicit _item_type.name '_dictionary.datablock_id' _item_type.code code save_ save__dictionary.title _item_description.name '_dictionary.title' _item_description.description ; Title identification of the dictionary. ; _item.name '_dictionary.title' _item.category_id dictionary _item.mandatory_code yes _item_type.name '_dictionary.title' _item_type.code char save_ save__dictionary.version _item_description.name '_dictionary.version' _item_description.description ; A unique version identifier for the dictionary. ; _item.name '_dictionary.version' _item.category_id dictionary _item.mandatory_code yes _item_type.name '_dictionary.version' _item_type.code char save_ # ---------------------------------------------------------------------------- save_DICTIONARY_HISTORY _category.description ; Attributes for specifying the revision history of the dictionary. ; _category.id dictionary_history _category.mandatory_code no _category.implicit_key mmcif_ddl.dic _category_key.id dictionary_history _category_key.name '_dictionary_history.version' loop_ _category_group.id _category_group.category_id 'ddl_group' dictionary_history 'dictionary_group' dictionary_history save_ save__dictionary_history.version _item_description.name '_dictionary_history.version' _item_description.description ; A unique version identifier for the dictionary revision. ; _item.name '_dictionary_history.version' _item.category_id dictionary_history _item.mandatory_code yes _item_type.name '_dictionary_history.version' _item_type.code char _item_linked.child_name '_dictionary.version' _item_linked.parent_name '_dictionary_history.version' save_ save__dictionary_history.update _item_description.name '_dictionary_history.update' _item_description.description ; The date that the last dictionary revision took place. ; _item.name '_dictionary_history.update' _item.category_id dictionary_history _item.mandatory_code yes _item_type.name '_dictionary_history.update' _item_type.code yyyy-mm-dd save_ save__dictionary_history.revision _item_description.name '_dictionary_history.revision' _item_description.description ; Text description of the dictionary revision. ; _item.name '_dictionary_history.revision' _item.category_id dictionary_history _item.mandatory_code yes _item_type.name '_dictionary_history.revision' _item_type.code text save_ ### EOF mmcif_ddl-def-1.dic ########################################################################### # # File: mmcif_ddl-def-1.dic # # mmCIF DDL Core Dictionary with NDB extensions # # This DDL dictionary is a mirror of ddl_core.dic-org with all implicit # data items fully expanded and with NDB extensions added. # # Definition Section 2. # (NDB Extension Definitions) # # ########################################################################### save_NDB_CATEGORY_DESCRIPTION _category.description ; NDB description of data items in this category. ; _category.id ndb_category_description _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name ndb_category_description '_ndb_category_description.id' ndb_category_description '_ndb_category_description.description' save_ save__ndb_category_description.id _item.name '_ndb_category_description.id' _item.category_id ndb_category_description _item.mandatory_code implicit _item_type.name '_ndb_category_description.id' _item_type.code idname _item_linked.child_name '_ndb_category_description.id' _item_linked.parent_name '_category.id' save_ save__ndb_category_description.description _item_description.name '_ndb_category_description.description' _item_description.description ; NDB text description of a category. ; _item.name '_ndb_category_description.description' _item.category_id ndb_category_description _item.mandatory_code yes _item_type.name '_ndb_category_description.description' _item_type.code text save_ # -------------------------------------------------------------------------- save_NDB_CATEGORY_EXAMPLES _category.description ; NDB example applications and descriptions of data items in this category. ; _category.id ndb_category_examples _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name ndb_category_examples '_ndb_category_examples.id' ndb_category_examples '_ndb_category_examples.case' save_ save__ndb_category_examples.id _item.name '_ndb_category_examples.id' _item.category_id ndb_category_examples _item.mandatory_code implicit _item_type.name '_ndb_category_examples.id' _item_type.code idname _item_linked.child_name '_ndb_category_examples.id' _item_linked.parent_name '_category.id' save_ save__ndb_category_examples.case _item_description.name '_ndb_category_examples.case' _item_description.description ; NDB case of examples involving items in this category. ; _item.name '_ndb_category_examples.case' _item.category_id ndb_category_examples _item.mandatory_code yes _item_type.name '_ndb_category_examples.case' _item_type.code text save_ save__ndb_category_examples.detail _item_description.name '_ndb_category_examples.detail' _item_description.description ; NDB description of an example _category_examples.case ; _item.name '_ndb_category_examples.detail' _item.category_id ndb_category_examples _item.mandatory_code no _item_type.name '_ndb_category_examples.detail' _item_type.code text save_ #-------------------------------------------------------------------------- save_NDB_ITEM_DESCRIPTION _category.description ; This category holds the NDB descriptions of each data item. ; _category.id ndb_item_description _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name ndb_item_description '_ndb_item_description.name' ndb_item_description '_ndb_item_description.description' loop_ _category_group.id _category_group.category_id 'ddl_group' ndb_item_description 'item_group' ndb_item_description save_ save__ndb_item_description.name _item_description.name '_ndb_item_description.name' _item_description.description ; Data name of the defined item. ; _item.name '_ndb_item_description.name' _item.category_id ndb_item_description _item.mandatory_code implicit _item_type.name '_ndb_item_description.name' _item_type.code name _item_linked.child_name '_ndb_item_description.name' _item_linked.parent_name '_item.name' save_ save__ndb_item_description.description _item_description.name '_ndb_item_description.description' _item_description.description ; NDB text description of the defined data item. ; _item.name '_ndb_item_description.description' _item.category_id ndb_item_description _item.mandatory_code yes _item_type.name '_ndb_item_description.description' _item_type.code text save_ # -------------------------------------------------------------------------- save_NDB_ITEM_ENUMERATION _category.description ; Attributes which specify the permitted enumeration of the items. ; _category.id ndb_item_enumeration _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name ndb_item_enumeration '_ndb_item_enumeration.name' ndb_item_enumeration '_ndb_item_enumeration.value' loop_ _category_group.category_id _category_group.id ndb_item_enumeration 'ddl_group' ndb_item_enumeration 'item_group' save_ save__ndb_item_enumeration.name _item.name '_ndb_item_enumeration.name' _item.category_id ndb_item_enumeration _item.mandatory_code implicit _item_type.name '_ndb_item_enumeration.name' _item_type.code name _item_linked.child_name '_ndb_item_enumeration.name' _item_linked.parent_name '_item.name' save_ save__ndb_item_enumeration.value _item_description.name '_ndb_item_enumeration.value' _item_description.description ; A permissible value, character or number, for the defined item. ; _item.name '_ndb_item_enumeration.value' _item.category_id ndb_item_enumeration _item.mandatory_code yes _item_type.name '_ndb_item_enumeration.value' _item_type.code any save_ save__ndb_item_enumeration.detail _item_description.name '_ndb_item_enumeration.detail' _item_description.description ; A description of a permissible value for the defined item. ; _item.name '_ndb_item_enumeration.detail' _item.category_id ndb_item_enumeration _item.mandatory_code no _item_type.name '_ndb_item_enumeration.detail' _item_type.code text save_ # -------------------------------------------------------------------------- save_NDB_ITEM_EXAMPLES _category.description ; Attributes for describing application examples of the data item. ; _category.id ndb_item_examples _category.mandatory_code no _category.implicit_key mmcif_ddl.dic loop_ _category_key.id _category_key.name ndb_item_examples '_ndb_item_examples.name' ndb_item_examples '_ndb_item_examples.case' loop_ _category_group.id _category_group.category_id 'ddl_group' ndb_item_examples 'item_group' ndb_item_examples save_ save__ndb_item_examples.case _item_description.name '_ndb_item_examples.case' _item_description.description ; NDB example application of the defined data item. ; _item.name '_ndb_item_examples.case' _item.category_id ndb_item_examples _item.mandatory_code yes _item_type.name '_ndb_item_examples.case' _item_type.code text save_ save__ndb_item_examples.detail _item_description.name '_ndb_item_examples.detail' _item_description.description ; NDB description of an example specified in _ndb_item_example.case ; _item.name '_ndb_item_examples.detail' _item.category_id ndb_item_examples _item.mandatory_code yes _item_type.name '_ndb_item_examples.detail' _item_type.code text save_ save__ndb_item_examples.name _item.name '_ndb_item_examples.name' _item.category_id ndb_item_examples _item.mandatory_code implicit _item_type.name '_ndb_item_examples.name' _item_type.code name _item_linked.child_name '_ndb_item_examples.name' _item_linked.parent_name '_item.name' save_ #### EOF mmcif_ddl-def-2.dic ./CBFlib-0.9.2.2/doc/Idiffrn_scan_axis.scan_id.html0000644000076500007650000000557211603702115020252 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan_axis.scan_id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_scan_axis.scan_id

Name:
'_diffrn_scan_axis.scan_id'

Definition:

        The value of this data item is the identifier of the
               scan for which axis settings are being specified.

               Multiple axes may be specified for the same value of
               _diffrn_scan.id.

               This item is a pointer to _diffrn_scan.id in the
               DIFFRN_SCAN category.

Type: code

Mandatory item: yes

Category: diffrn_scan_axis

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_detector_axis.id.html0000644000076500007650000000523611603702115020130 0ustar yayayaya (IUCr) CIF Definition save__diffrn_detector_axis.id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_detector_axis.id

Name:
'_diffrn_detector_axis.id'

Definition:

        This data item is a pointer to _diffrn_detector.id in
               the DIFFRN_DETECTOR category.

               DEPRECATED -- DO NOT USE

Type: code

Mandatory item: yes

Category: diffrn_detector_axis

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Iaxis.offset[1].html0000644000076500007650000000511411603702115016145 0ustar yayayaya (IUCr) CIF Definition save__axis.offset[1]

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_axis.offset[1]

Name:
'_axis.offset[1]'

Definition:

        The [1] element of the three-element vector used to specify
               the offset to the base of a rotation or translation axis.

               The vector is specified in millimetres.

Type: float

Mandatory item: no


Enumeration default: 0.0

Category: axis

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_scan_frame.integration_time.html0000644000076500007650000000557611603702115022345 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan_frame.integration_time

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_scan_frame.integration_time

Name:
'_diffrn_scan_frame.integration_time'

Definition:

        The time in seconds to integrate this step of the scan.
               This should be the precise time of integration of each
               particular frame.  The value of this data item should
               be given explicitly for each frame and not inferred
               from the value of _diffrn_scan.integration_time.

Type: float

Mandatory item: yes


The permitted range is [0.0, infinity)

Category: diffrn_scan_frame

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_measurement_axis.id.html0000644000076500007650000000527111603702115020643 0ustar yayayaya (IUCr) CIF Definition save__diffrn_measurement_axis.id

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_measurement_axis.id

Name:
'_diffrn_measurement_axis.id'

Definition:

        This data item is a pointer to _diffrn_measurement.id in
               the DIFFRN_MEASUREMENT category.

               DEPRECATED -- DO NOT USE

Type: code

Mandatory item: yes

Category: diffrn_measurement_axis

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_radiation.collimation.html0000644000076500007650000000604411603702115021161 0ustar yayayaya (IUCr) CIF Definition save__diffrn_radiation.collimation

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_radiation.collimation

Name:
'_diffrn_radiation.collimation'

Definition:

        The collimation or focusing applied to the radiation.

Examples:

'0.3 mm double-pinhole'
'0.5 mm'
'focusing mirrors'

Type: text

Mandatory item: no

Alias:
_diffrn_radiation_collimation (cif_core.dic version 2.0.1)

Category: diffrn_radiation

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/Idiffrn_radiation.polarizn_source_ratio.html0000644000076500007650000001143411603702115023262 0ustar yayayaya (IUCr) CIF Definition save__diffrn_radiation.polarizn_source_ratio

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

_diffrn_radiation.polarizn_source_ratio

Name:
'_diffrn_radiation.polarizn_source_ratio'

Definition:

        (Ip-In)/(Ip+In), where Ip is the intensity
               (amplitude squared) of the electric vector in the plane of
               polarization and In is the intensity (amplitude squared)
               of the electric vector in the plane of the normal to the
               plane of polarization.

               In the case of an unpolarized beam, or a beam with true
               circular polarization, in which no single plane of
               polarization can be determined, the plane is to be taken
               as the XZ plane and the normal is parallel to the Y axis.

               Thus, if there was complete polarization in the plane of
               polarization, the value of
               _diffrn_radiation.polarizn_source_ratio would be 1, and
               for an unpolarized beam
               _diffrn_radiation.polarizn_source_ratio would have a
               value of 0.

               If the X axis has been chosen to lie in the plane of
               polarization, this definition will agree with the definition
               of 'MONOCHROMATOR' in the Denzo glossary, and values of near
               1 should be expected for a bending-magnet source.  However,
               if the X axis were perpendicular to the polarization plane
               (not a common choice), then the Denzo value would be the
               negative of _diffrn_radiation.polarizn_source_ratio.

               See http://www.hkl-xray.com for information on Denzo and
               Otwinowski & Minor (1997).

               This differs both in the choice of ratio and choice of
               orientation from _diffrn_radiation.polarisn_ratio, which,
               unlike _diffrn_radiation.polarizn_source_ratio, is
               unbounded.

               Reference: Otwinowski, Z. & Minor, W. (1997). 'Processing of
               X-ray diffraction data collected in oscillation mode.' Methods
               Enzymol. 276, 307-326.

Type: float

Mandatory item: no


The permitted range is [-1.0, 1.0]

Category: diffrn_radiation

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/cif_img_1.1.3.dic0000644000076500007650000051754211603702115015157 0ustar yayayaya############################################################################## # # # Image CIF Dictionary (imgCIF) # # and Crystallographic Binary File Dictionary (CBF) # # Extending the Macromolecular CIF Dictionary (mmCIF) # # # # Version 1.1.3 # # of 2001-04-19 # # # # Adapted from the # # imgCIF Workshop, BNL Oct 1997 # # and # # Crystallographic Binary File Format Draft Proposal # # by Andy Hammersley # # # ############################################################################## # # # First DDL 2.1 Version # # by # # John Westbrook # # Nucleic Acid Database # # Rutgers University # # # ############################################################################## # These revisions by: Herbert J. Bernstein, yaya@bernstein-plus-sons.com # # Incorporating comments by I. David Brown, John Westbrook, Brian McMahon. # # Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li and others # ############################################################################## data_cif_img.dic _dictionary.title cif_img.dic _dictionary.version 1.1.3 _dictionary.datablock_id cif_img.dic ############################################################################## # CONTENTS # # CATEGORY_GROUP_LIST # # category ARRAY_DATA # # _array_data.array_id # _array_data.binary_id # _array_data.data # # category ARRAY_ELEMENT_SIZE # # _array_element_size.array_id # _array_element_size.index # _array_element_size.size # # category ARRAY_INTENSITIES # # _array_intensities.array_id # _array_intensities.binary_id # _array_intensities.gain # _array_intensities.gain_esd # _array_intensities.linearity # _array_intensities.offset # _array_intensities.scaling # _array_intensities.overload # _array_intensities.undefined_value # # category ARRAY_STRUCTURE # # _array_structure.byte_order # _array_structure.compression_type # _array_structure.encoding_type # _array_structure.id # # category ARRAY_STRUCTURE_LIST # # _array_structure_list.axis_set_id # _array_structure_list.array_id # _array_structure_list.dimension # _array_structure_list.direction # _array_structure_list.index # _array_structure_list.precedence # # category ARRAY_STRUCTURE_LIST_AXIS # # _array_structure_list_axis.axis_id # _array_structure_list_axis.axis_set_id # _array_structure_list_axis.angle # _array_structure_list_axis.angle_increment # _array_structure_list_axis.displacement_increment # _array_structure_list_axis.angular_pitch # _array_structure_list_axis.radial_pitch # # category AXIS # # _axis.depends_on # _axis.equipment # _axis.id # _axis.offset[1] # _axis.offset[2] # _axis.offset[3] # _axis.type # _axis.vector[1] # _axis.vector[2] # _axis.vector[3] # # category DIFFRN_DATA_FRAME # # _diffrn_data_frame.array_id # _diffrn_data_frame.binary_id # _diffrn_data_frame.detector_element_id # _diffrn_data_frame.id # # category DIFFRN_DETECTOR # # _diffrn_detector.details # _diffrn_detector.detector # _diffrn_detector.diffrn_id # _diffrn_detector.dtime # _diffrn_detector.id # _diffrn_detector.number_of_axes # _diffrn_detector.type # # category DIFFRN_DETECTOR_AXIS # # _diffrn_detector_axis.axis_id # _diffrn_detector_axis.detector_id # # category DIFFRN_DETECTOR_ELEMENT # # _diffrn_detector_element.center[1] # _diffrn_detector_element.center[2] # _diffrn_detector_element.id # _diffrn_detector_element.detector_id # # category DIFFRN_MEASUREMENT # # _diffrn_measurement.diffrn_id # _diffrn_measurement.details # _diffrn_measurement.device # _diffrn_measurement.device_details # _diffrn_measurement.device_type # _diffrn_measurement.id # _diffrn_measurement.method # _diffrn_measurement.number_of_axes # _diffrn_measurement.specimen_support # # category DIFFRN_MEASUREMENT_AXIS # # _diffrn_measurement_axis.axis_id # _diffrn_measurement_axis.measurement_device # _diffrn_measurement_axis.measurement_id # # category DIFFRN_RADIATION # # _diffrn_radiation.collimation # _diffrn_radiation.diffrn_id # _diffrn_radiation.div_x_source # _diffrn_radiation.div_y_source # _diffrn_radiation.div_x_y_source # _diffrn_radiation.filter_edge' # _diffrn_radiation.inhomogeneity # _diffrn_radiation.monochromator # _diffrn_radiation.polarisn_norm # _diffrn_radiation.polarisn_ratio # _diffrn_radiation.polarizn_source_norm # _diffrn_radiation.polarizn_source_ratio # _diffrn_radiation.probe # _diffrn_radiation.type # _diffrn_radiation.xray_symbol # _diffrn_radiation.wavelength_id # # category DIFFRN_REFLN # # _diffrn_refln.frame_id # # category DIFFRN_SCAN # # _diffrn_scan.id # _diffrn_scan.date_end # _diffrn_scan.date_start # _diffrn_scan.integration_time # _diffrn_scan.frame_id_start # _diffrn_scan.frame_id_end # _diffrn_scan.frames # # category DIFFRN_SCAN_AXIS # # _diffrn_scan_axis.axis_id # _diffrn_scan_axis.angle_start # _diffrn_scan_axis.angle_range # _diffrn_scan_axis.angle_increment # _diffrn_scan_axis.angle_rstrt_incr # _diffrn_scan_axis.displacement_start # _diffrn_scan_axis.displacement_range # _diffrn_scan_axis.displacement_increment # _diffrn_scan_axis.displacement_rstrt_incr # _diffrn_scan_axis.scan_id # # category DIFFRN_SCAN_FRAME # # _diffrn_scan_frame.date # _diffrn_scan_frame.frame_id # _diffrn_scan_frame.frame_number # _diffrn_scan_frame.integration_time # _diffrn_scan_frame.scan_id # # category DIFFRN_SCAN_FRAME_AXIS # # _diffrn_scan_frame_axis.axis_id # _diffrn_scan_frame_axis.angle # _diffrn_scan_frame_axis.angle_increment # _diffrn_scan_frame_axis.angle_rstrt_incr # _diffrn_scan_frame_axis.displacement # _diffrn_scan_frame_axis.displacement_increment # _diffrn_scan_frame_axis.displacement_rstrt_incr # _diffrn_scan_frame_axis.frame_id # # ITEM_TYPE_LIST # ITEM_UNITS_LIST # DICTIONARY_HISTORY # ############################################################################## ######################### ## CATEGORY_GROUP_LIST ## ######################### loop_ _category_group_list.id _category_group_list.parent_id _category_group_list.description 'inclusive_group' . ; Categories that belong to the dictionary extension. ; 'array_data_group' 'inclusive_group' ; Categories that describe array data. ; 'axis_group' 'inclusive_group' ; Categories that describe axes. ; 'diffrn_group' 'inclusive_group' ; Categories that describe details of the diffraction experiment. ; ############## # ARRAY_DATA # ############## save_ARRAY_DATA _category.description ; Data items in the ARRAY_DATA category are the containers for the array data items described in category ARRAY_STRUCTURE. ; _category.id array_data _category.mandatory_code no loop_ _category_key.name '_array_data.array_id' '_array_data.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows two binary data blocks. The first one was compressed by the CBF_CANONICAL compression algorithm and presented as hexadecimal data. The first character "H" on the data lines means hexadecimal. It could have been "O" for octal or "D" for decimal. The second character on the line shows the number of bytes in each word (in this case "4"), which then requires 8 hexadecimal digits per word. The third character gives the order of octets within a word, in this case "<" for the ordering 4321 (i.e. "big-endian"). Alternatively the character ">" could have been used for the ordering 1234 (i.e. "little-endian"). The block has a "message digest" to check the integrity of the data. The second block is similar, but uses CBF_PACKED compression and BASE64 encoding. Note that the size and the digest are different. ; ; loop_ _array_data.array_id _array_data.binary_id _array_data.data image_1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_CANONICAL" Content-Transfer-Encoding: X-BASE16 X-Binary-Size: 3927126 X-Binary-ID: 1 Content-MD5: u2sTJEovAHkmkDjPi+gWsg== # Hexadecimal encoding, byte 0, byte order ...21 # H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ... .... --CIF-BINARY-FORMAT-SECTION---- ; image_2 2 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF-PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3745758 X-Binary-ID: 1 Content-MD5: 1zsJjWPfol2GYl2V+QSXrw== ELhQAAAAAAAA... ... --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_data.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_data.array_id' _item.category_id array_data _item.mandatory_code yes _item_type.code code save_ save__array_data.binary_id _item_description.description ; This item is an integer identifier which, along with _array_data.array_id should uniquely identify the particular block of array data. If _array_data.binary_id is not explicitly given, it defaults to 1. The value of _array_data.binary_id distinguishes among multiple sets of data with the same array structure. If the MIME header of the data array specifies a value for X-Binary-Id, these values should be equal. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_data.binary_id' array_data implicit '_diffrn_data_frame.binary_id' diffrn_data_frame implicit '_array_intensities.binary_id' array_intensities implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.binary_id' '_array_data.binary_id' '_array_intensities.binary_id' '_array_data.binary_id' _item_default.value 1 _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_data.data _item_description.description ; The value of _array_data.data contains the array data encapsulated in a STAR string. The representation used is a variant on the Multipurpose Internet Mail Extensions (MIME) specified in RFC 2045-2049 by N. Freed et al. The boundary delimiter used in writing an imgCIF or CBF is "--CIF-BINARY-FORMAT-SECTION--" (including the required initial "--"). The Content-Type may be any of the discrete types permitted in RFC 2045; "application/octet-stream" is recommended. If an octet stream was compressed, the compression should be specified by the parameter 'conversions="x-CBF_PACKED"' or the parameter 'conversions="x-CBF_CANONICAL"'. The Content-Transfer-Encoding may be "BASE-64", "Quoted-Printable", "X-BASE-8", "X-BASE-10", or "X-BASE-16" for an imgCIF or "BINARY" for a CBF. The octal, decimal and hexadecimal transfer encodings are for convenience in debugging, and are not recommended for archiving and data interchange. In an imgCIF file, the encoded binary data begins after the empty line terminating the header. In a CBF, the raw binary data begins after an empty line terminating the header and after the sequence: Octet Hex Decimal Purpose 0 0C 12 (ctrl-L) Page break 1 1A 26 (ctrl-Z) Stop listings in MS-DOS 2 04 04 (Ctrl-D) Stop listings in UNIX 3 D5 213 Binary section begins None of these octets are included in the calculation of the message size, nor in the calculation of the message digest. The X-Binary-Size header specifies the size of the equivalent binary data in octets. If compression was used, this size is the size after compression, including any book-keeping fields. And adjustment is made for the deprecated binary formats in which 8 bytes of binary header are used for the compression type. In that case, the 8 bytes used for the compression type is subtracted from the size, so that the same size will be reported if the compression type is supplied in the MIME header. Use of the MIME header is the recommended way to supply the compression type. In general, no portion of the binary header is included in the calculation of the size. The X-Binary-Element-Type header specifies the type of binary data in the octets, using the same descriptive phrases as in _array_structure.encoding_type. The default value is "unsigned 32-bit integer". An MD5 message digest may, optionally, be used. The "RSA Data Security, Inc. MD5 Message-Digest Algorithm" should be used. No portion of the header is included in the calculation of the message digest. If the Transfer Encoding is "X-BASE-8", "X-BASE-10", or "X-BASE-16", the data is presented as octal, decimal or hexadecimal data organized into lines or words. Each word is created by composing octets of data in fixed groups of 2, 3, 4, 6 or 8 octets, either in the order ...4321 ("big- endian") or 1234... (little-endian). If there are fewer than the specified number of octets to fill the last word, then the missing octets are presented as "==" for each missing octet. Exactly two equal signs are used for each missing octet even for octal and decimal encoding. The format of lines is: rnd xxxxxx xxxxxx xxxxxx where r is "H", "O", or "D" for hexadecimal, octal or decimal, n is the number of octets per word. and d is "<" for ">" for the "...4321" and "1234..." octet orderings respectively. The "==" padding for the last word should be on the appropriate side to correspond to the missing octets, e.g. H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000 or H3> FF0700 00==== For these hex, octal and decimal formats, only, comments beginning with "#" are permitted to improve readability. BASE64 encoding follows MIME conventions. Octets are in groups of three, c1, c2, c3. The resulting 24 bits are broken into four 6-bit quantities, starting with the high-order six bits (c1 >> 2) of the first octet, then the low-order two bits of the first octet followed by the high-order 4 bits of the second octet ((c1 & 3)<<4 | (c2>>4)), then the bottom 4 bits of the second octet followed by the high order two bits of the last octet ((c2 & 15)<<2 | (c3>>6)), then the bottom six bits of the last octet (c3 & 63). Each of these four quantities is translated into an ASCII character using the mapping: 1 2 3 4 5 6 0123456789012345678901234567890123456789012345678901234567890123 | | | | | | | ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/ With short groups of octets padded on the right with one "=" if c3 is missing, and with "==" if both c2 and c3 are missing. QUOTED-PRINTABLE encoding also follows MIME conventions, copying octets without translation if their ASCII values are 32..38, 42, 48..57, 59..60, 62, 64..126 and the octet is not a ";" in column 1. All other characters are translated to =nn, where nn is the hexadecimal encoding of the octet. All lines are "wrapped" with a terminating "=" (i.e. the MIME conventions for an implicit line terminator are never used). ; _item.name '_array_data.data' _item.category_id array_data _item.mandatory_code yes _item_type.code binary save_ ###################### # ARRAY_ELEMENT_SIZE # ###################### save_ARRAY_ELEMENT_SIZE _category.description ; Data items in the ARRAY_ELEMENT_SIZE category record the physical size of array elements along each array dimension. ; _category.id array_element_size _category.mandatory_code no loop_ _category_key.name '_array_element_size.array_id' '_array_element_size.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A regular 2D array with a uniform element dimension of 1220 nanometres. ; ; loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size image_1 1 1.22e-6 image_1 2 1.22e-6 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_element_size.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ATOM_STRUCTURE category. ; _item.name '_array_element_size.array_id' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.index _item_description.description ; This item is a pointer to _array_structure_list.index in the ATOM_STRUCTURE_LIST category. ; _item.name '_array_element_size.index' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.size _item_description.description ; The size in metres of an image element in this dimension. This supposes that the elements are arranged on a regular grid. ; _item.name '_array_element_size.size' _item.category_id array_element_size _item.mandatory_code yes _item_type.code float _item_units.code 'metres' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ ##################### # ARRAY_INTENSITIES # ##################### save_ARRAY_INTENSITIES _category.description ; Data items in the ARRAY_INTENSITIES category record the information required to recover the intensity data from the set of data values stored in the ARRAY_DATA category. The actual detector may have a complex relationship between the raw intensity values and the number of incident photons. In most cases, the number stored in the final array will have a simple linear relationship to the actual number of incident photons, given by '_array_intensities.gain'. If raw, uncorrected values are presented (e.g for calibration experiments), the value of '_array_intensities.linearity' will be 'raw' and '_array_intensities.gain' will not be used. ; _category.id array_intensities _category.mandatory_code no loop_ _category_key.name '_array_intensities.array_id' '_array_intensities.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 ; ; loop_ _array_intensities.array_id _array_intensities.linearity _array_intensities.gain _array_intensities.overload _array_intensities.undefined_value image_1 linear 1.2 655535 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_intensities.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ATOM_STRUCTURE category. ; _item.name '_array_intensities.array_id' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code save_ save__array_intensities.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_STRUCTURE category. ; _item.name '_array_intensities.binary_id' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code int save_ save__array_intensities.gain _item_description.description ; Detector "gain". The factor by which linearized intensity count values should be divided to produce true photon counts. ; _item.name '_array_intensities.gain' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain_esd' 'associated_value' save_ save__array_intensities.gain_esd _item_description.description ; The estimated standard deviation in detector "gain". ; _item.name '_array_intensities.gain_esd' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain' 'associated_esd' save_ save__array_intensities.linearity _item_description.description ; The intensity linearity scaling used from raw intensity to the stored element value: 'linear' is obvious 'offset' means that the value defined by '_array_intensities.offset' should be added to each element value. 'scaling' means that the value defined by '_array_intensities.scaling' should be multiplied with each element value. 'scaling_offset' is the combination of the two previous cases, with the scale factor applied before the offset value. 'sqrt_scaled' means that the square root of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and squaring the result. 'logarithmic_scaled' means that the logarithm based 10 of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and calculating 10 to the power of this number. 'raw' means that the data is the raw is a set of raw values straight from the detector. ; _item.name '_array_intensities.linearity' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'linear' . 'offset' ; The value defined by '_array_intensities.offset' should be added to each element value. ; 'scaling' ; The value defined by '_array_intensities.scaling' should be multiplied with each element value. ; 'scaling_offset' ; The combination of the scaling and offset with the scale factor applied before the offset value. ; 'sqrt_scaled' ; The square root of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and squaring the result. ; 'logarithmic_scaled' ; The logarithm based 10 of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and calculating 10 to the power of this number. ; 'raw' ; The array consists of raw values to which no corrections have been applied. While the handling of the data is similar to that given for 'linear' data with no offset, the meaning of the data differs in that the number of incident photons is not necessarily linearly related to the number of counts reported. This value is intended for use either in calibration experiments or to allow for handling more complex data fitting algorithms than are allowed for by this data item. ; save_ save__array_intensities.offset _item_description.description ; Offset value to add to array element values in the manner described by item _array_intensities.linearity. ; _item.name '_array_intensities.offset' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.scaling _item_description.description ; Multiplicative scaling value to be applied to array data in the manner described by item _array_intensities.linearity. ; _item.name '_array_intensities.scaling' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.overload _item_description.description ; The saturation intensity level for this data array. ; _item.name '_array_intensities.overload' _item.category_id array_intensities _item.mandatory_code no _item_type.code float _item_units.code 'counts' save_ save__array_intensities.undefined_value _item_description.description ; A value to be substituted for undefined values in the data array. ; _item.name '_array_intensities.undefined_value' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ ################### # ARRAY_STRUCTURE # ################### save_ARRAY_STRUCTURE _category.description ; Data items in the ARRAY_STRUCTURE category record the organization and encoding of array data which may be stored in the ARRAY_DATA category. ; _category.id array_structure _category.mandatory_code no _category_key.name '_array_structure.id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order image_1 "unsigned 16-bit integer" none little_endian ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure.byte_order _item_description.description ; The order of bytes for integer values which require more than 1-byte. (IBM-PC's and compatibles, and Dec-Vaxes use low-byte-first ordered integers, whereas Hewlett Packard 700 series, Sun-4 and Silicon Graphics use high-byte-first ordered integers. Dec-Alphas can produce/use either depending on a compiler switch.) ; _item.name '_array_structure.byte_order' _item.category_id array_structure _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'big_endian' ; The first byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; 'little_endian' ; The last byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; save_ save__array_structure.compression_type _item_description.description ; Type of data compression method used to compress the array data. ; _item.name '_array_structure.compression_type' _item.category_id array_structure _item.mandatory_code no _item_type.code code _item_default.value 'none' loop_ _item_enumeration.value _item_enumeration.detail 'none' ; Data are stored in normal format as defined by '_array_structure.encoding_type' and '_array_structure.byte_order'. ; 'byte_offsets' ; Using the compression scheme defined in CBF definition Section 5.0. ; 'packed' ; Using the 'packed' compression scheme, a CCP4-style packing (CBFlib section 3.3.2) ; 'canonical' ; Using the 'canonical' compression scheme (CBFlib section 3.3.1) ; save_ save__array_structure.encoding_type _item_description.description ; Data encoding of a single element of array data. In several cases, the IEEE format is referenced. See "IEEE Standard for Binary Floating-Point Arithmetic", ANSI/IEEE Std 754-1985, the Institute of Electrical and Electronics Engineers, Inc., NY 1985. ; _item.name '_array_structure.encoding_type' _item.category_id array_structure _item.mandatory_code yes _item_type.code uline loop_ _item_enumeration.value 'unsigned 8-bit integer' 'signed 8-bit integer' 'unsigned 16-bit integer' 'signed 16-bit_integer' 'unsigned 32-bit integer' 'signed 32-bit integer' 'signed 32-bit real IEEE' 'signed 64-bit real IEEE' 'signed 32-bit complex IEEE' save_ save__array_structure.id _item_description.description ; The value of _array_structure.id must uniquely identify each item of array data. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure.id' array_structure yes '_array_data.array_id' array_data yes '_array_structure_list.array_id' array_structure_list yes '_array_intensities.array_id' array_intensities yes '_diffrn_data_frame.array_id' diffrn_data_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_data.array_id' '_array_structure.id' '_array_structure_list.array_id' '_array_structure.id' '_array_intensities.array_id' '_array_structure.id' '_diffrn_data_frame.array_id' '_array_structure.id' save_ ######################## # ARRAY_STRUCTURE_LIST # ######################## save_ARRAY_STRUCTURE_LIST _category.description ; Data items in the ARRAY_STRUCTURE_LIST category record the size and organization of each array dimension. The relationship to physical axes may be given. ; _category.id array_structure_list _category.mandatory_code no loop_ _category_key.name '_array_structure_list.array_id' '_array_structure_list.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - An image array of 1300 x 1200 elements. The raster order of the image is left-to-right (increasing) in first dimension and bottom-to-top (decreasing) in the second dimension. ; ; loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id image_1 1 1300 1 increasing ELEMENT_X image_1 2 1200 2 decreasing ELEMENY_Y ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure_list.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_structure_list.array_id' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code code save_ save__array_structure_list.axis_set_id _item_description.description ; This is a descriptor for the physical axis or set of axes corresponding to an array index. This data item is related to the axes of the detector itself given in DIFFRN_DETECTOR_AXIS, but usually differ in that the axes in this category are the axes of the coordinate system of reported data points, while the axes in DIFFRN_DETECTOR_AXIS are the physical axes of the detector describing the "poise" of the detector as an overall physical object. If there is only one axis in the set, the identifier of that axis should be used as the identifier of the set. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.axis_set_id' array_structure_list yes '_array_structure_list_axis.axis_set_id' array_structure_list_axis implicit _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_structure_list_axis.axis_set_id' '_array_structure_list.axis_set_id' save_ save__array_structure_list.dimension _item_description.description ; The number of elements stored in the array structure in this dimension. ; _item.name '_array_structure_list.dimension' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.direction _item_description.description ; Identifies the direction in which this array index changes. ; _item.name '_array_structure_list.direction' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_enumeration.value _item_enumeration.detail 'increasing' ; Indicates the index changes from 1 to the maximum dimension. ; 'decreasing' ; Indicates the index changes from the maximum dimension to 1. ; save_ save__array_structure_list.index _item_description.description ; Identifies the one-based index of the row or column in the array structure. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.index' array_structure_list yes '_array_structure_list.precedence' array_structure_list yes '_array_element_size.index' array_element_size yes _item_type.code int loop_ _item_linked.child_name _item_linked.parent_name '_array_element_size.index' '_array_structure_list.index' loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.precedence _item_description.description ; Identifies the rank order in which this array index changes with respect to other array indices. The precedence of 1 indicates the index which changes fastest. ; _item.name '_array_structure_list.precedence' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ ############################# # ARRAY_STRUCTURE_LIST_AXIS # ############################# save_ARRAY_STRUCTURE_LIST_AXIS _category.description ; Data items in the ARRAY_STRUCTURE_LIST_AXIS category describes the physical settings of sets axes for the centres of pixels that correspond to data points described in the ARRAY_STRUCTURE_LIST category. In the simplest cases, the physical increments of a single axis correspond to the increments of a single array index. More complex organizations, e.g. spiral scans, may require coupled motions along multiple axes. Note that a spiral scan uses two coupled axis, one for the angular direction, one for the radial direction. This differs from a cylindrical scan for which the two axes are not coupled into one set. ; _category.id array_structure_list_axis _category.mandatory_code no loop_ _category_key.name '_array_structure_list_axis.axis_set_id' '_array_structure_list_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' save_ save__array_structure_list_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the set of axes for which settings are being specified. Multiple axes may be specified for the same value of '_array_structure_list_axis.axis_set_id' This item is a pointer to _axis.id in the AXIS category. ; _item.name '_array_structure_list_axis.axis_id' _item.category_id array_structure_list_axis _item.mandatory_code yes save_ save__array_structure_list_axis.axis_set_id _item_description.description ; The value of this data item is the identifier of the set of axes for which axis settings are being specified. Multiple axes may be specified for the same value of _array_structure_list_axis.axis_set_id . This item is a pointer to _array_structure_list.axis_set_id in the ARRAY_STRUCTURE_LIST category. If this item is not specified, it defaults to the corresponding axis identifier. ; _item.name '_array_structure_list_axis.axis_set_id' _item.category_id array_structure_list_axis _item.mandatory_code implicit save_ save__array_structure_list_axis.angle _item_description.description ; The setting of the specified axis in degrees for the first data point of the array index with the corresponding value of '_array_structure_list.axis_set_id'. If the index is specified as 'increasing' this will be the center of the pixel with index value 1. If the index is specified as 'decreasing' this will be the center of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.angle' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.angle_increment _item_description.description ; The pixel-center-to-pixel-center increment in the angular setting of the specified axis in degrees. This is not meaningful in the case of 'constant velocity' spiral scans and should not be specified in that case. See '_array_structure_list_axis.angular_pitch'. ; _item.name '_array_structure_list_axis.angle_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for the first data point of the array index with the corresponding value of '_array_structure_list.axis_set_id'. If the index is specified as 'increasing' this will be the center of the pixel with index value 1. If the index is specified as 'decreasing' this will be the center of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.displacement' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.displacement_increment _item_description.description ; The pixel-center-to-pixel-center increment for the displacement setting of the specified axis in millimetres. ; _item.name '_array_structure_list_axis.displacement_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.angular_pitch _item_description.description ; The pixel-center-to-pixel-center distance for a one step change in the setting of the specified axis in millimetres. This is meaningful only for 'constant velocity' spiral scans, or for uncoupled angular scans at a constant radius (cylindrical scan) and should not be specified for cases in which the angle between pixels, rather than the distance between pixels is uniform. See '_array_structure_list_axis.angle_increment'. ; _item.name '_array_structure_list_axis.angular_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.radial_pitch _item_description.description ; The radial distance from one "cylinder" of pixels to the next in millimetres. If the scan is a 'constant velocity' scan with differing angular displacements between pixels, the value of this item may differ significantly from the value of '_array_structure_list_axis.displacement_increment'. ; _item.name '_array_structure_list_axis.radial_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ ######## # AXIS # ######## save_AXIS _category.description ; Data items in the AXIS category record the information required to describe the various goniometer, detector, source and other axes needed to specify a data collection. The location of each axis is specified by two vectors: the axis itself, given as a unit vector, and an offset to the base of the unit vector. These vectors are referenced to a right-handed laboratory coordinate system with its origin in the sample or specimen: | Y (to complete right-handed system) | | | | | |________________X / principal goniometer axis / / / / /Z (to source) Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from the sample or specimen along the principal axis of the goniometer. Axis 2 (Y): The Y-axis completes an orthogonal right-handed system defined by the X-axis and the Z-axis (see below). Axis 3 (Z): The Z-axis is derived from the source axis which goes from the sample to the source. The Z-axis is the component of the source axis in the direction of the source orthogonal to the X-axis in the plane defined by the X-axis and the source axis. These axes are based on the goniometer, not on the orientation of the detector, gravity, etc. The vectors necessary to specify all other axes are given by sets of three components in the order (X, Y, Z). If the axis involved is a rotation axis, it is right handed, i.e. as one views the object to be rotated from the origin (the tail) of the unit vector, the rotation is clockwise. If a translation axis is specified, the direction of the unit vector specifies the sense of positive translation. Note: This choice of coordinate system is similar to, but significantly different from the choice in MOSFLM (Andrew G.W. Leslie, Harry Powell, MRC Laboratory of Molecular Biology, Hills Road, Cambridge CB2 2QH,UK http://www.dl.ac.uk/CCP/CCP4/dist/x-windows/Mosflm/). In MOSFLM, X is along the X-ray beam (our Z axis) and Z is along the rotation axis. All rotations are given in degrees and all translations are given in mm. Axes may be dependent on one another. The X-axis is the only goniometer axis the direction of which is strictly connected to the hardware. All other axes are specified by the positions they would assume when the axes upon which they depend are at their zero points. When specifying detector axes, the axis is given to the beam center. The location of the beam center on the detector should be given in the DIFFRN_DETECTOR category in distortion-corrected mm from the (0,0) corner of the detector. It should be noted that many different origins arise in the definition of an experiment. In particular, as noted above, we need to specify the location of the beam center on the detector in terms of the origin of the detector, which is, of course, not coincident with the center of the sample. ; _category.id axis _category.mandatory_code no loop_ _category_key.name '_axis.id' '_axis.equipment' loop_ _category_group.id 'inclusive_group' 'axis_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows the axis specification of the axes of a kappa geometry goniometer (See "X-Ray Structure Determination, A Practical Guide", 2nd ed. by G. H. Stout, L. H. Jensen, Wiley Interscience, 1989, 453 pp, p 134.). There are three axes specified, and no offsets. The outermost axis, omega, is pointed along the X-axis. The next innermost axis, kappa, is at a 50 degree angle to the X-axis, pointed away from the source. The innermost axis, phi, aligns with the X-axis when omega and phi are at their zero-points. If T-omega, T-kappa and T-phi are the transformation matrices derived from the axis settings, the complete transformation would be: x' = (T-omega) (T-kappa) (T-phi) x ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] omega rotation goniometer . 1 0 0 kappa rotation goniometer omega -.64279 0 -.76604 phi rotation goniometer kappa 1 0 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - This example show the axis specification of the axes of a detector, source and gravity. We have juggled the order as a reminder that the ordering of presentation of tokens is not significant. We have taken the center of rotation of the detector to be 68 millimetres in the direction away from the source. ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] source . source . 0 0 1 . . . gravity . gravity . 0 -1 0 . . . tranz translation detector rotz 0 0 1 0 0 -68 twotheta rotation detector . 1 0 0 . . . roty rotation detector twotheta 0 1 0 0 0 -68 rotz rotation detector roty 0 0 1 0 0 -68 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__axis.depends_on _item_description.description ; The value of _axis.type specifies the next outermost axis upon which this axis depends. This item is a pointer to axis.id in the same category. ; _item.name '_axis.depends_on' _item.category_id axis _item.mandatory_code no save_ save__axis.equipment _item_description.description ; The value of _axis.type specifies the type of equipment using the axis: goniometer, detector, gravity, source or general ; _item.name '_axis.equipment' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail goniometer 'equipment used to orient or position samples' detector 'equipment used to detect reflections' general 'equipment used for general purposes' gravity 'axis specifying the downward direction' source 'axis specifying the direction sample to source' save_ save__axis.offset[1] _item_description.description ; The [1] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[2] _item_description.description ; The [2] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[3] _item_description.description ; The [3] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.id _item_description.description ; The value of _axis.id must uniquely identify each axis relevant to the experiment. Note that multiple pieces of equipment may share the same axis (e.g. a twotheta arm), so that the category key for AXIS also includes the equipment. ; loop_ _item.name _item.category_id _item.mandatory_code '_axis.id' axis yes '_array_structure_list_axis.axis_id' array_structure_list_axis yes '_diffrn_detector_axis.axis_id' diffrn_detector_axis yes '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes '_diffrn_scan_axis.axis_id' diffrn_scan_axis yes '_diffrn_scan_frame_axis.axis_id' diffrn_scan_frame_axis yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_axis.depends_on' '_axis.id' '_array_structure_list_axis.axis_id' '_axis.id' '_diffrn_detector_axis.axis_id' '_axis.id' '_diffrn_measurement_axis.axis_id' '_axis.id' '_diffrn_scan_axis.axis_id' '_axis.id' '_diffrn_scan_frame_axis.axis_id' '_axis.id' save_ save__axis.type _item_description.description ; The value of _axis.type specifies the type of axis: rotation, translation (or general when the type is not relevant, as for gravity) ; _item.name '_axis.type' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail rotation 'right-handed axis of rotation' translation 'translation in the direction of the axis' general 'axis for which the type is not relevant' save_ save__axis.vector[1] _item_description.description ; The [1] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector, and is dimensionless. ; _item.name '_axis.vector[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[2] _item_description.description ; The [2] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector, and is dimensionless. ; _item.name '_axis.vector[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[3] _item_description.description ; The [3] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector, and is dimensionless. ; _item.name '_axis.vector[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ ##################### # DIFFRN_DATA_FRAME # ##################### save_DIFFRN_DATA_FRAME _category.description ; Data items in the DIFFRN_DATA_FRAME category record the details about each frame of data. The items in this category were previously in a DIFFRN_FRAME_DATA category, which is now deprecated. The items from the old category are provided as aliases, but should not be used for new work. ; _category.id diffrn_data_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_data_frame.id' '_diffrn_data_frame.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A frame containing data from 4 frame elements. Each frame element has a common array configuration 'array_1' described in ARRAY_STRUCTURE and related categories. The data for each detector element is stored in four groups of binary data in the ARRAY_DATA category, linked by the array_id and binary_id ; ; loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id frame_1 d1_ccd_1 array_1 1 frame_1 d1_ccd_2 array_1 2 frame_1 d1_ccd_3 array_1 3 frame_1 d1_ccd_4 array_1 4 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_data_frame.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_diffrn_data_frame.array_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.array_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0.00 _item_type.code code save_ save__diffrn_data_frame.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_diffrn_data_frame.binary_id' _item.category_id diffrn_data_frame _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_frame_data.binary_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code int save_ save__diffrn_data_frame.detector_element_id _item_description.description ; This item is a pointer to _diffrn_detector_element.id in the DIFFRN_DETECTOR_ELEMENT category. ; _item.name '_diffrn_data_frame.detector_element_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.detector_element_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.id _item_description.description ; The value of _diffrn_data_frame.id must uniquely identify each complete frame of data. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_data_frame.id' diffrn_data_frame yes '_diffrn_refln.frame_id' diffrn_refln yes '_diffrn_scan.frame_id_start' diffrn_scan yes '_diffrn_scan.frame_id_end' diffrn_scan yes '_diffrn_scan_frame.frame_id' diffrn_scan_frame yes '_diffrn_scan_frame_axis.frame_id' diffrn_scan_frame_axis yes _item_aliases.alias_name '_diffrn_frame_data.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_refln.frame_id' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_start' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_end' '_diffrn_data_frame.id' '_diffrn_scan_frame.frame_id' '_diffrn_data_frame.id' '_diffrn_scan_frame_axis.frame_id' '_diffrn_data_frame.id' save_ ########################################################################## # The following is a restatement of the mmCIF DIFFRN_DETECTOR, # # DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for # # the CBF/imgCIF extensions # ########################################################################## ################### # DIFFRN_DETECTOR # ################### save_DIFFRN_DETECTOR _category.description ; Data items in the DIFFRN_DETECTOR category describe the detector used to measure the scattered radiation, including any analyser and post-sample collimation. ; _category.id diffrn_detector _category.mandatory_code no loop_ _category_key.name '_diffrn_detector.diffrn_id' '_diffrn_detector.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_detector.diffrn_id 'd1' _diffrn_detector.detector 'multiwire' _diffrn_detector.type 'Siemens' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector.details _item_description.description ; A description of special aspects of the radiation detector. ; _item.name '_diffrn_detector.details' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; Need new example here. ; save_ save__diffrn_detector.detector _item_description.description ; The general class of the radiation detector. ; _item.name '_diffrn_detector.detector' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector' cifdic.c91 1.0 '_diffrn_detector' cif_core.dic 2.0 _item_type.code text loop_ _item_examples.case 'photographic film' 'scintillation counter' 'CCD plate' 'BF~3~ counter' save_ save__diffrn_detector.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. The value of _diffrn.id uniquely defines a set of diffraction data. ; _item.name '_diffrn_detector.diffrn_id' _item.mandatory_code yes save_ save__diffrn_detector.dtime _item_description.description ; The deadtime in microseconds of the detectors used to measure the diffraction intensities. ; _item.name '_diffrn_detector.dtime' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector_dtime' cifdic.c91 1.0 '_diffrn_detector_dtime' cif_core.dic 2.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code microseconds save_ save__diffrn_detector.id _item_description.description ; The value of _diffrn_detector.id must uniquely identify each detector used to collect each diffraction data set. If the value of _diffrn_detector.id is not given, it is implicitly equal to the value of _diffrn_detector.diffrn_id ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector.id' diffrn_detector implicit '_diffrn_detector_axis.detector_id' diffrn_detector_axis yes loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_detector_axis.detector_id' '_diffrn_detector.id' _item_type.code code save_ save__diffrn_detector.number_of_axes _item_description.description ; The value of _diffrn_detector.number_of_axes gives the number of axes of the positioner for the detector identified by _diffrn_detector.id The word "positioner" is a general term used in instrumentation design for devices that are used to change the positions of portions of apparatus by linear translation, rotation, or combinations of such motions. Axes which are used to provide a coordinate system for the face of an area detetctor should not be counted for this data item. The description of each axis should be provided by entries in DIFFRN_DETECTOR_AXIS. ; _item.name '_diffrn_detector.number_of_axes' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_detector.type _item_description.description ; The make, model or name of the detector device used. ; _item.name '_diffrn_detector.type' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ ######################## # DIFFRN_DETECTOR_AXIS # ######################## save_DIFFRN_DETECTOR_AXIS _category.description ; Data items in the DIFFRN_DETECTOR_AXIS category associate axes with detectors. ; _category.id diffrn_detector_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_axis.detector_id' '_diffrn_detector_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_detector_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_detector_axis.axis_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_axis.detector_id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. This item was previously named '_diffrn_detector_axis.id' which is now a deprecated name. The old name is provided as an alias, but should not be used for new work. ; _item.name '_diffrn_detector_axis.detector_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_aliases.alias_name '_diffrn_detector_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 save_ ########################### # DIFFRN_DETECTOR_ELEMENT # ########################### save_DIFFRN_DETECTOR_ELEMENT _category.description ; Data items in the DIFFRN_DETECTOR_ELEMENT category record the details about spatial layout and other characteristics of each element of a detector which may have multiple elements. In most cases, the more detailed information provided in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS are preferable to simply providing the centre. ; _category.id diffrn_detector_element _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_element.id' '_diffrn_detector_element.detector_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Detector d1 is composed of four CCD detector elements, each 200 mm by 200 mm, arranged in a square. in the pattern 1 2 * 3 4 Note that the beam center is slightly off of each of the detector elements, just beyond the lower right corner of 1, the lower left corner of 2, the upper right corner of 3 and the upper left corner of 4. ; ; loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id _diffrn_detector_element.center[1] _diffrn_detector_element.center[2] d1 d1_ccd_1 201.5 -1.5 d1 d1_ccd_2 -1.8 -1.5 d1 d1_ccd_3 201.6 201.4 d1 d1_ccd_4 -1.7 201.5 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector_element.center[1] _item_description.description ; The value of _diffrn_detector_element.center[1] is the X component of the distortion-corrected beam-center in mm from the (0, 0) (lower left) corner of the detector element viewed from the sample side. ; _item.name '_diffrn_detector_element.center[1]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.center[2] _item_description.description ; The value of _diffrn_detector_element.center[2] is the Y component of the distortion-corrected beam-center in mm from the (0, 0) (lower left) corner of the detector element viewed from the sample side. ; _item.name '_diffrn_detector_element.center[2]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.id _item_description.description ; The value of _diffrn_detector_element.id must uniquely identify each element of a detector. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector_element.id' diffrn_detector_element yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.detector_element_id' '_diffrn_detector_element.id' save_ save__diffrn_detector_element.detector_id _item_description.description ; This item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. ; _item.name '_diffrn_detector_element.detector_id' _item.category_id diffrn_detector_element _item.mandatory_code yes _item_type.code code save_ ######################## ## DIFFRN_MEASUREMENT ## ######################## save_DIFFRN_MEASUREMENT _category.description ; Data items in the DIFFRN_MEASUREMENT category record details about the device used to orient and/or position the crystal during data measurement and the manner in which the diffraction data were measured. ; _category.id diffrn_measurement _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement.device' '_diffrn_measurement.diffrn_id' '_diffrn_measurement.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_measurement.diffrn_id 'd1' _diffrn_measurement.device '3-circle camera' _diffrn_measurement.device_type 'Supper model x' _diffrn_measurement.device_details 'none' _diffrn_measurement.method 'omega scan' _diffrn_measurement.details ; Need new example here ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991). Acta Cryst. C47, 2276-2277]. ; ; _diffrn_measurement.diffrn_id 's1' _diffrn_measurement.device_type 'Philips PW1100/20 diffractometer' _diffrn_measurement.method 'theta/2theta (\q/2\q)' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_measurement.device _item_description.description ; The general class of goniometer or device used to support and orient the specimen. If the value of _diffrn_measurement.device is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id Either '_diffrn_measurement.device' or '_diffrn_measurement.id' may be used to link to other categories. If the experimental setup admits multiple devices, then '_diffrn_measurement.id' is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.device' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_device' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement.device' _item_aliases.alias_name '_diffrn_measurement_device' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '3-circle camera' '4-circle camera' 'kappa-geometry camera' 'oscillation camera' 'precession camera' save_ save__diffrn_measurement.device_details _item_description.description ; A description of special aspects of the device used to measure the diffraction intensities. ; _item.name '_diffrn_measurement.device_details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; commercial goniometer modified locally to allow for 90\% \t arc ; save_ save__diffrn_measurement.device_type _item_description.description ; The make, model or name of the measurement device (goniometer) used. ; _item.name '_diffrn_measurement.device_type' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Supper model q' 'Huber model r' 'Enraf-Nonius model s' 'homemade' save_ save__diffrn_measurement.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_measurement.diffrn_id' _item.mandatory_code yes save_ save__diffrn_measurement.details _item_description.description ; A description of special aspects of the intensity measurement. ; _item.name '_diffrn_measurement.details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; save_ save__diffrn_measurement.id _item_description.description ; The value of _diffrn_measurement.id must uniquely identify the set of mechanical characteristics of the device used to orient and/or position the sample used during collection of each diffraction data set. If the value of _diffrn_measurement.id is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id Either '_diffrn_measurement.device' or '_diffrn_measurement.id' may be used to link to other categories. If the experimental setup admits multiple devices, then '_diffrn_measurement.id' is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.id' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_id' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement.id' _item_type.code code save_ save__diffrn_measurement.method _item_description.description ; Method used to measure intensities. ; _item.name '_diffrn_measurement.method' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_method' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'profile data from theta/2theta (\q/2\q) scans' save_ save__diffrn_measurement.number_of_axes _item_description.description ; The value of _diffrn_measurement.number_of_axes gives the number of axes of the positioner for the goniometer or other sample orientation or positioning device identified by _diffrn_measurement.id The description of the axes should be provided by entries in DIFFRN_MEASUREMENT_AXIS. ; _item.name '_diffrn_measurement.number_of_axes' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_measurement.specimen_support _item_description.description ; The physical device used to support the crystal during data collection. ; _item.name '_diffrn_measurement.specimen_support' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_specimen_support' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'glass capillary' 'quartz capillary' 'fiber' 'metal loop' save_ ########################### # DIFFRN_MEASUREMENT_AXIS # ########################### save_DIFFRN_MEASUREMENT_AXIS _category.description ; Data items in the DIFFRN_MEASUREMENT_AXIS category associate axes with goniometers. ; _category.id diffrn_measurement_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_measurement_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_measurement_axis.axis_id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.measurement_device _item_description.description ; This data item is a pointer to _diffrn_measurement.device in the DIFFRN_MEASUREMENT category. ; _item.name '_diffrn_measurement_axis.measurement_device' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit save_ save__diffrn_measurement_axis.measurement_id _item_description.description ; This data item is a pointer to _diffrn_measurement.id in the DIFFRN_MEASUREMENT category. This item was previously named '_diffrn_measurement_axis.id' which is now a deprecated name. The old name is provided as an alias, but should not be used for new work. ; _item.name '_diffrn_measurement_axis.measurement_id' _item.category_id diffrn_measurement_axis _item_aliases.alias_name '_diffrn_measurement_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0.00 _item.mandatory_code implicit save_ #################### # DIFFRN_RADIATION # #################### save_DIFFRN_RADIATION _category.description ; Data items in the DIFFRN_RADIATION category describe the radiation used in measuring diffraction intensities, its collimation and monochromatisation before the sample. Post-sample treatment of the beam is described by data items in the DIFFRN_DETECTOR category. ; _category.id diffrn_radiation _category.mandatory_code no _category_key.name '_diffrn_radiation.diffrn_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_radiation.diffrn_id 'set1' _diffrn_radiation.collimation '0.3 mm double pinhole' _diffrn_radiation.monochromator 'graphite' _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.wavelength_id 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991). Acta Cryst. C47, 2276-2277]. ; ; _diffrn_radiation.wavelength_id 1 _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.monochromator 'graphite' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_radiation.collimation _item_description.description ; The collimation or focusing applied to the radiation. ; _item.name '_diffrn_radiation.collimation' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_collimation' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '0.3 mm double-pinhole' '0.5 mm' 'focusing mirrors' save_ save__diffrn_radiation.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_radiation.diffrn_id' _item.mandatory_code yes save_ save__diffrn_radiation.div_x_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory X axis (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the esd of the directions of photons in the X-Z plane around the mean source beam direction. Note that some synchrotrons specify this value in milliradians, in which case a conversion would be needed. To go from a value in milliradians to a value in degrees, multiply by 0.180 and divide by Pi. ; _item.name '_diffrn_radiation.div_x_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.div_y_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory Y axis (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the esd of the directions of photons in the Y-Z plane around the mean source beam direction. Note that some synchrotrons specify this value in milliradians, in which case a conversion would be needed. To go from a value in milliradians to a value in degrees, multiply by 0.180 and divide by Pi. ; _item.name '_diffrn_radiation.div_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.div_x_y_source _item_description.description ; Beam crossfire correlation degrees**2 between the crossfire laboratory X-axis component and the crossfire laboratory Y-axis component (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the mean of the products of the deviations of the directin of each photons in X-Z plane times the deviations of the direction of the same photon in the Y-Z plane around the mean source beam direction. This will be zero for uncorrelated crossfire. Note that some synchrotrons specify this value in milliradians**2, in which case a conversion would be needed. To go from a value in milliradians**2 to a value in degrees**2, multiply by 0.180**2 and divide by Pi**2. ; _item.name '_diffrn_radiation.div_x_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees_squared _item_default.value 0.0 save_ save__diffrn_radiation.filter_edge _item_description.description ; Absorption edge in angstroms of the radiation filter used. ; _item.name '_diffrn_radiation.filter_edge' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_filter_edge' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__diffrn_radiation.inhomogeneity _item_description.description ; Half-width in millimetres of the incident beam in the direction perpendicular to the diffraction plane. ; _item.name '_diffrn_radiation.inhomogeneity' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_inhomogeneity' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code millimetres save_ save__diffrn_radiation.monochromator _item_description.description ; The method used to obtain monochromatic radiation. If a mono- chromator crystal is used the material and the indices of the Bragg reflection are specified. ; _item.name '_diffrn_radiation.monochromator' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_monochromator' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Zr filter' 'Ge 220' 'none' 'equatorial mounted graphite' save_ save__diffrn_radiation.polarisn_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the perpendicular component of the polarisation and the diffraction plane. See _diffrn_radiation_polarisn_ratio. ; _item.name '_diffrn_radiation.polarisn_norm' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_norm' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.polarisn_ratio _item_description.description ; Polarisation ratio of the diffraction beam incident on the crystal. It is the ratio of the perpendicularly polarised to the parallel polarised component of the radiation. The perpendicular component forms an angle of _diffrn_radiation.polarisn_norm to the normal to the diffraction plane of the sample (i.e. the plane containing the incident and reflected beams). ; _item.name '_diffrn_radiation.polarisn_ratio' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_ratio' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__diffrn_radiation.polarizn_source_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the normal to the polarization plane and the laboratory Y axis as defined in the AXIS category. Note that this is the angle of polarization of the source photons, either directly from a synchrotron beamline or from a monchromater. This differs from the value of '_diffrn_radiation.polarisn_norm' in that '_diffrn_radiation.polarisn_norm' refers to polarization relative to the diffraction plane rather than to the laboratory axis system. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane should be taken as the X-Z plane, and the angle as 0. See '_diffrn_radiation.polarizn_source_ratio'. ; _item.name '_diffrn_radiation.polarizn_source_norm' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.polarizn_source_ratio _item_description.description ; (Ip-In)/(Ip+In), where Ip is the intensity (amplitude squared) of the electric vector in the plane of polarization and In is the intensity (amplitude squared) of the electric vector in plane of the normal to the plane of polarization. Thus, if we had complete polarization in the plane of polarization, the value of '_diffrn_radiation.polarizn_source_ratio' would be 1, and an unpolarized beam would have a value of 0. If the X-axis has been chosen to lie in the plane of polarization, this definition will agree with the definition of "MONOCHROMATOR" in the Denzo glossary, and values of near 1 should be expected for a bending magnet source. However, if the X-axis were, for some reason to be, say, perpendicular to the polarization plane (not a common choice), then the Denzo value would be the negative of '_diffrn_radiation.polarizn_source_ratio'. See http://www.hkl-xray.com for information on Denzo, and Z. Otwinowski and W. Minor, " Processing of X-ray Diffraction Data Collected in Oscillation Mode ", Methods in Enzymology, Volume 276: Macromolecular Crystallography, part A, p.307-326, 1997,C.W. Carter, Jr. & R. M. Sweet, Eds., Academic Press. This differs both in the choice of ratio and choice of orientation from '_diffrn_radiation.polarisn_ratio', which, unlike '_diffrn_radiation.polarizn_source_ratio', is unbounded. ; _item.name '_diffrn_radiation.polarizn_source_ratio' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 -1.0 -1.0 -1.0 _item_type.code float save_ save__diffrn_radiation.probe _item_description.description ; Name of the type of radiation used. It is strongly encouraged that this field be specified so that the probe radiation can be simply determined. ; _item.name '_diffrn_radiation.probe' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_probe' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value 'x-ray' 'neutron' 'electron' 'gamma' save_ save__diffrn_radiation.type _item_description.description ; The nature of the radiation. This is typically a description of the X-ray wavelength in Siegbahn notation. ; _item.name '_diffrn_radiation.type' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'CuK\a' 'Cu K\a~1~' 'Cu K-L~2,3~' 'white-beam' save_ save__diffrn_radiation.xray_symbol _item_description.description ; The IUPAC symbol for the X-ray wavelength for probe radiation. ; _item.name '_diffrn_radiation.xray_symbol' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_xray_symbol' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value _item_enumeration.detail 'K-L~3~' 'K\a~1~ in older Siegbahn notation' 'K-L~2~' 'K\a~2~ in older Siegbahn notation' 'K-M~3~' 'K\b~1~ in older Siegbahn notation' 'K-L~2,3~' 'use where K-L~3~ and K-L~2~ are not resolved' save_ save__diffrn_radiation.wavelength_id _item_description.description ; This data item is a pointer to _diffrn_radiation_wavelength.id in the DIFFRN_RADIATION_WAVELENGTH category. ; _item.name '_diffrn_radiation.wavelength_id' _item.mandatory_code yes save_ ################ # DIFFRN_REFLN # ################ save_DIFFRN_REFLN _category.description ; This category redefinition has been added to extend the key of the standard DIFFRN_REFLN category. ; _category.id diffrn_refln _category.mandatory_code no _category_key.name '_diffrn_refln.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_refln.frame_id _item_description.description ; This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_refln.frame_id' _item.category_id diffrn_refln _item.mandatory_code yes _item_type.code code save_ ############### # DIFFRN_SCAN # ############### save_DIFFRN_SCAN _category.description ; Data items in the DIFFRN_SCAN category describe the parameters of one or more scans, relating axis positions to frames. ; _category.id diffrn_scan _category.mandatory_code no _category_key.name '_diffrn_scan.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - derived from a suggestion by R. M. Sweet. The vector of each axis is not given here, because it is provided in the AXIS category. By making _diffrn_scan_axis.scan_id and _diffrn_scan_axis.axis_id keys of the DIFFRN_SCAN_AXIS category, an arbitrary number of scanning and fixed axes can be specified for a scan. We have specified three rotation axes and one translation axis at non-zero values, with one axis stepping. There is no reason why more axes could not have been specified to step. We have specified range information, but note that it is redundant from the number of frames and the increment, so we could drop the data item _diffrn_scan_axis.angle_range . We have specified both the sweep data and the data for a single frame. Note that the information on how the axes are stepped is given twice, once in terms of the overall averages in the value of '_diffrn_scan.integration_time' and the values for DIFFRN_SCAN_AXIS, and precisely for the given frame in the value for '_diffrn_scan_frame.integration_time' and the values for DIFFRN_SCAN_FRAME_AXIS. If dose-related adjustements are made to scan times and non-linear stepping is done, these values may differ. Therefore, in interpreting the data for a particular frame it is important to use the frame-specific data. ; ; _diffrn_scan.id 1 _diffrn_scan.date_start '2001-11-18T03:26:42' _diffrn_scan.date_end '2001-11-18T03:36:45' _diffrn_scan.integration_time 3.0 _diffrn_scan.frame_id_start mad_L2_000 _diffrn_scan.frame_id_end mad_L2_200 _diffrn_scan.frames 201 loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment 1 omega 200.0 20.0 0.1 . . . 1 kappa -40.0 0.0 0.0 . . . 1 phi 127.5 0.0 0.0 . . . 1 tranz . . . 2.3 0.0 0.0 _diffrn_scan_frame.scan_id 1 _diffrn_scan_frame.date '2001-11-18T03:27:33' _diffrn_scan_frame.integration_time 3.0 _diffrn_scan_frame.frame_id mad_L2_018 _diffrn_scan_frame.frame_number 18 loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.angle_increment _diffrn_scan_frame_axis.displacement _diffrn_scan_frame_axis.displacement_increment mad_L2_018 omega 201.8 0.1 . . mad_L2_018 kappa -40.0 0.0 . . mad_L2_018 phi 127.5 0.0 . . mad_L2_018 tranz . . 2.3 0.0 ; ; Example 2 - a more extensive example, R. M. Sweet, P. Ellis, H. Bernstein. We place a detector 240 mm along the Z axis from the goniometer. This presents us with a choice -- either we define the axes of the detector at the origin, and then put a Z setting of -240 in for the actual use, or we define the axes with the necessary Z-offset. In this case we use the setting, and leave the offset as zero. We call this axis DETECTOR_Z. The axis for positioning the detector in the Y-direction depends on the detector Z-axis. We call this axis, DETECTOR_Y. The axis for positioning the dector in the X-direction depends on the detector Y-axis (and therefore on the detector Z-axis). We call this axis DETECTOR_X. This detector may be rotated around the Y-axis. This rotation axis depends on the three translation axies. We call it DETECTOR_PITCH. We define a coordinate system on the face of the detector in terms of 2300 0.150 mm pixels in each direction. The ELEMENT_X axis is used to index the first array index of the data array and the ELEMENT_Y axis is used to index the second array index. Because the pixels are 0.150mm x 0.150mm, the center of the first pixel is at (0.075, 0.075) in this coordinate system. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 172.43 -172.43 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 2300 1 increasing ELEMENT_X ARRAY1 2 2300 2 increasing ELEMENT_Y # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.075 0.150 ELEMENT_Y ELEMENT_Y 0.075 0.150 # category ARRAY_ELEMENT_SIZE loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 ARRAY1 2 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; ; Example 3 - Example 2 revised for a spiral scan, R. M. Sweet, P. Ellis, H. Bernstein. We place a detector 240 mm along the Z axis from the goniometer, as in Example 2, above, but in this example, the image plate is scanned in a spiral pattern outside edge in. The axis for positioning the detector in the Y-direction depends on the detector Z-axis. We call this axis, DETECTOR_Y. The axis for positioning the dector in the X-direction depends on the detector Y-axis (and therefore on the detector Z-axis). We call this axis DETECTOR_X. This detector may be rotated around the Y-axis. This rotation axis depends on the three translation axies. We call it DETECTOR_PITCH. We define a coordinate system on the face of the detector in terms of a coupled rotation axis and radial scan axis to form a spiral scan. Let us call rotation axis ELEMENT_ROT, and the radial axis ELEMENT_RAD. We assume 150 um radial pitch and 75 um 'constant velocity' angular pitch. We index first on the rotation axis and make the radial axis dependent on it. The two axes are coupled to form an axis set ELEMENT_SPIRAL. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_ROT translation detector DETECTOR_PITCH 0 0 1 0 0 0 ELEMENT_RAD translation detector ELEMENT_ROT 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.angle _array_structure_list_axis.displacement _array_structure_list_axis.angular_pitch _array_structure_list_axis.radial_pitch ELEMENT_SPIRAL ELEMENT_ROT 0 . 0.075 . ELEMENT_SPIRAL ELEMENT_RAD . 172.5 . -0.150 # category ARRAY_ELEMENT_SIZE # the actual pixels are 0.075 by 0.150 mm # We give the coarser dimension here. loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_scan.id _item_description.description ; The value of _diffrn_scan.id uniquely identifies each scan. The identifier is used to tie together all the information about the scan. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_scan.id' diffrn_scan yes '_diffrn_scan_axis.scan_id' diffrn_scan_axis yes '_diffrn_scan_frame.scan_id' diffrn_scan_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_scan_axis.scan_id' '_diffrn_scan.id' '_diffrn_scan_frame.scan_id' '_diffrn_scan.id' save_ save__diffrn_scan.date_end _item_description.description ; The date and time of the end of the scan. Note that this may be an estimate generated during the scan, before the precise time of the end of the scan is known. ; _item.name '_diffrn_scan.date_end' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.date_start _item_description.description ; The date and time of the start of the scan. ; _item.name '_diffrn_scan.date_start' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.integration_time _item_description.description ; Approximate average time in seconds to integrate each step of the scan. The precise time for integration of each particular step must be provided in '_diffrn_scan_frame.integration_time', even if all steps have the same integration time. ; _item.name '_diffrn_scan.integration_time' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan.frame_id_start _item_description.description ; The value of this data item is the identifier of the first frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_start' _item.category_id diffrn_scan _item.mandatory_code yes save_ save__diffrn_scan.frame_id_end _item_description.description ; The value of this data item is the identifier of the last frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_end' _item.category_id diffrn_scan _item.mandatory_code yes save_ save__diffrn_scan.frames _item_description.description ; The value of this data item is the number of frames in the scan. ; _item.name '_diffrn_scan.frames' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 1 1 1 save_ #################### # DIFFRN_SCAN_AXIS # #################### save_DIFFRN_SCAN_AXIS _category.description ; Data items in the DIFFRN_SCAN_AXIS category describe the settings of axes for particular scans. Unspecified axes are assumed to be at their zero points. ; _category.id diffrn_scan_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_axis.scan_id' '_diffrn_scan_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_axis.scan_id _item_description.description ; The value of this data item is the identifier of the scan for which axis settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan.id'. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_axis.scan_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes save_ save__diffrn_scan_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the scan for which settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan.id'. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_axis.axis_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes save_ save__diffrn_scan_axis.angle_start _item_description.description ; The starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_range _item_description.description ; The range from the starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_increment _item_description.description ; The increment for each step for the specified axis in degrees. In general, this will agree with '_array_structure_list_axis.angle_increment', which see for a precise description. ; _item.name '_diffrn_scan_axis.angle_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_rstrt_incr _item_description.description ; The increment after each step for the specified axis in degrees. In general, this will agree with '_array_structure_list_axis.angle_increment', which see for a precise description. ; _item.name '_diffrn_scan_axis.angle_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.displacement_start _item_description.description ; The starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_range _item_description.description ; The range from the starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_increment _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with '_diffrn_scan_frame_axis.displacement_increment', which see for a precise description. ; _item.name '_diffrn_scan_axis.displacement_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_rstrt_incr _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with '_diffrn_scan_frame_axis.displacement_rstrt_incr', which see for a precise description. ; _item.name '_diffrn_scan_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ ##################### # DIFFRN_SCAN_FRAME # ##################### save_DIFFRN_SCAN_FRAME _category.description ; Data items in the DIFFRN_SCAN_FRAME category describe the settings of axes for particular frames. Unspecified axes are assumed to be at their zero points. ; _category.id diffrn_scan_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame.scan_id' '_diffrn_scan_frame.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame.date _item_description.description ; The date and time of the start of the frame being scanned. ; _item.name '_diffrn_scan_frame.date' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan_frame.frame_id _item_description.description ; The value of this data item is the identifier of the frame being examined. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame.frame_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes save_ save__diffrn_scan_frame.frame_number _item_description.description ; The value of this data item is the number of the frame within the scan, starting with 1. It is not necessarily the same as the value of _diffrn_scan_frame.frame_id, but may be. ; _item.name '_diffrn_scan_frame.frame_number' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 0 0 0 save_ save__diffrn_scan_frame.integration_time _item_description.description ; The time in seconds to integrate this step of the scan. This should be the precise time of integration of each particular frame. The value of this data item should be given explicitly for each frame and not inferred from the value of '_diffrn_scan.integration_time'. ; _item.name '_diffrn_scan_frame.integration_time' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame.scan_id _item_description.description ; The value of _diffrn_scan_frame.scan_id identifies the scan containing this frame. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_frame.scan_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes save_ ########################## # DIFFRN_SCAN_FRAME_AXIS # ########################## save_DIFFRN_SCAN_FRAME_AXIS _category.description ; Data items in the DIFFRN_SCAN_FRAME_AXIS category describes the settings of axes for particular frames. Unspecified axes are assumed to be at their zero points. If, for any given frame, non-zero values apply for any of the data items in this category, those values should be given explicitly in this category and not simply inferred from values in DIFFRN_SCAN_AXIS. ; _category.id diffrn_scan_frame_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame_axis.frame_id' '_diffrn_scan_frame_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the frame for which settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_frame_axis.axis_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes save_ save__diffrn_scan_frame_axis.angle _item_description.description ; The setting of the specified axis in degrees for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.angle' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_increment _item_description.description ; The increment for this frame for angular setting of the specified axis in degrees. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.angle_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_rstrt_incr _item_description.description ; The increment after this frame for angular setting of the specified axis in degrees. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' and '_diffrn_scan_frame_axis.angle_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame, and should equal '_diffrn_scan_frame_axis.angle' for that next frame. ; _item.name '_diffrn_scan_frame_axis.angle_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.displacement' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_increment _item_description.description ; The increment for this frame for displacement setting of the specified axis in millimetres. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.displacement_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_rstrt_incr _item_description.description ; The increment for this frame for displacement setting of the specified axis in millimetres. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' and '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame, and should equal '_diffrn_scan_frame_axis.displacement' for that next frame. ; _item.name '_diffrn_scan_frame_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.frame_id _item_description.description ; The value of this data item is the identifier of the frame for which axis settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id . This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame_axis.frame_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes save_ #################### ## ITEM_TYPE_LIST ## #################### # # # The regular expressions defined here are not compliant # with the POSIX 1003.2 standard as they include the # '\n' and '\t' special characters. These regular expressions # have been tested using version 0.12 of Richard Stallman's # GNU regular expression library in POSIX mode. # In order to allow presentation of a regular expression # in a text field concatenate any line ending in a backslash # with the following line, after discarding the backslash. # # A formal definition of the '\n' and '\t' special characters # is most properly done in the DDL, but for completeness, please # note that '\n' is the line termination character ('newline') # and '\t' is the horizontal tab character. There is a formal # ambiguity in the use of '\n' for line termination, in that # the intention is that the equivalent machine/OS-dependent line # termination character sequence should be accepted as a match, e.g. # # '\r' (control-M) under MacOS # '\n' (control-J) under Unix # '\r\n' (control-M control-J) under DOS and MS Windows # loop_ _item_type_list.code _item_type_list.primitive_code _item_type_list.construct _item_type_list.detail code char '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words ... ; ucode uchar '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words (case insensitive) ; line char '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types / multi-word items ... ; uline uchar '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types / multi-word items (case insensitive) ; text char '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; text item types / multi-line text ... ; binary char ;\n--CIF-BINARY-FORMAT-SECTION--\n\ [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*}\ \n--CIF-BINARY-FORMAT-SECTION---- ; ; binary items are presented as MIME-like ascii-encoded sections in an imgCIF. In a CBF, raw octet streams are used to convey the same information. ; int numb '-?[0-9]+' ; int item types are the subset of numbers that are the negative or positive integers. ; float numb '-?(([0-9]+)|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?' ; float item types are the subset of numbers that are the floating numbers. ; any char '.*' ; A catch all for items that may take any form... ; yyyy-mm-dd char ;\ [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9][0-9]\ (T[0-2][0-9]:[0-5][0-9]:[0-5][0-9](.[0-9]+)([+-][0-5][0-9]:[0-5][0-9])) ; ; Standard format for CIF date and time strings (see http://www.iucr.orgiucr-top/cif/spec/datetime.html), consisting of a yyyy-mm-dd date optionally followed by the character "T" followed by a 24-hour clock time, optionally followed by a signed time-zone offset. The IUCr standard has been extended to allow for an optional deciaml fraction on the seconds of time. Time is local time if no time-zone offset is given. ; ##################### ## ITEM_UNITS_LIST ## ##################### loop_ _item_units_list.code _item_units_list.detail # 'metres' 'metres' 'centimetres' 'centimetres (metres * 10^( -2))' 'millimetres' 'millimetres (metres * 10^( -3))' 'nanometres' 'nanometres (metres * 10^( -9))' 'angstroms' 'angstroms (metres * 10^(-10))' 'picometres' 'picometres (metres * 10^(-12))' 'femtometres' 'femtometres (metres * 10^(-15))' # 'reciprocal_metres' 'reciprocal metres (metres * 10^-1)' 'reciprocal_centimetres' 'reciprocal centimetres (metres * 10^( -2)^-1)' 'reciprocal_millimetres' 'reciprocal millimetres (metres * 10^( -3)^-1)' 'reciprocal_nanometres' 'reciprocal nanometres (metres * 10^( -9)^-1)' 'reciprocal_angstroms' 'reciprocal angstroms (metres * 10^(-10)^-1)' 'reciprocal_picometres' 'reciprocal picometres (metres * 10^(-12)^-1)' # 'nanometres_squared' 'nanometres squared (metres * 10^( -9))^2' 'angstroms_squared' 'angstroms squared (metres * 10^(-10))^2' '8pi2_angstroms_squared' '8pi^2 * angstroms squared (metres * 10^(-10))^2' 'picometres_squared' 'picometres squared (metres * 10^(-12))^2' # 'nanometres_cubed' 'nanometres cubed (metres * 10^( -9))^3' 'angstroms_cubed' 'angstroms cubed (metres * 10^(-10))^3' 'picometres_cubed' 'picometres cubed (metres * 10^(-12))^3' # 'kilopascals' 'kilopascals' 'gigapascals' 'gigapascals' # 'hours' 'hours' 'minutes' 'minutes' 'seconds' 'seconds' 'microseconds' 'microseconds' # 'degrees' 'degrees (of arc)' 'degrees_squared' 'degrees (of arc) squared' # 'degrees_per_minute' 'degrees (of arc) per minute' # 'celsius' 'degrees (of temperature) Celsius' 'kelvins' 'degrees (of temperature) Kelvin' # 'counts' 'counts' 'counts_per_photon' 'counts per photon' # 'electrons' 'electrons' # 'electrons_squared' 'electrons squared' # 'electrons_per_nanometres_cubed' ; electrons per nanometres cubed (metres * 10^( -9))^3 ; 'electrons_per_angstroms_cubed' ; electrons per angstroms cubed (metres * 10^(-10))^3 ; 'electrons_per_picometres_cubed' ; electrons per picometres cubed (metres * 10^(-12))^3 ; 'kilowatts' 'kilowatts' 'milliamperes' 'milliamperes' 'kilovolts' 'kilovolts' # 'arbitrary' ; arbitrary system of units. ; # loop_ _item_units_conversion.from_code _item_units_conversion.to_code _item_units_conversion.operator _item_units_conversion.factor ### 'metres' 'centimetres' '*' 1.0E+02 'metres' 'millimetres' '*' 1.0E+03 'metres' 'nanometres' '*' 1.0E+09 'metres' 'angstroms' '*' 1.0E+10 'metres' 'picometres' '*' 1.0E+12 'metres' 'femtometres' '*' 1.0E+15 # 'centimetres' 'metres' '*' 1.0E-02 'centimetres' 'millimetres' '*' 1.0E+01 'centimetres' 'nanometres' '*' 1.0E+07 'centimetres' 'angstroms' '*' 1.0E+08 'centimetres' 'picometres' '*' 1.0E+10 'centimetres' 'femtometres' '*' 1.0E+13 # 'millimetres' 'metres' '*' 1.0E-03 'millimetres' 'centimetres' '*' 1.0E-01 'millimetres' 'nanometres' '*' 1.0E+06 'millimetres' 'angstroms' '*' 1.0E+07 'millimetres' 'picometres' '*' 1.0E+09 'millimetres' 'femtometres' '*' 1.0E+12 # 'nanometres' 'metres' '*' 1.0E-09 'nanometres' 'centimetres' '*' 1.0E-07 'nanometres' 'millimetres' '*' 1.0E-06 'nanometres' 'angstroms' '*' 1.0E+01 'nanometres' 'picometres' '*' 1.0E+03 'nanometres' 'femtometres' '*' 1.0E+06 # 'angstroms' 'metres' '*' 1.0E-10 'angstroms' 'centimetres' '*' 1.0E-08 'angstroms' 'millimetres' '*' 1.0E-07 'angstroms' 'nanometres' '*' 1.0E-01 'angstroms' 'picometres' '*' 1.0E+02 'angstroms' 'femtometres' '*' 1.0E+05 # 'picometres' 'metres' '*' 1.0E-12 'picometres' 'centimetres' '*' 1.0E-10 'picometres' 'millimetres' '*' 1.0E-09 'picometres' 'nanometres' '*' 1.0E-03 'picometres' 'angstroms' '*' 1.0E-02 'picometres' 'femtometres' '*' 1.0E+03 # 'femtometres' 'metres' '*' 1.0E-15 'femtometres' 'centimetres' '*' 1.0E-13 'femtometres' 'millimetres' '*' 1.0E-12 'femtometres' 'nanometres' '*' 1.0E-06 'femtometres' 'angstroms' '*' 1.0E-05 'femtometres' 'picometres' '*' 1.0E-03 ### 'reciprocal_centimetres' 'reciprocal_metres' '*' 1.0E+02 'reciprocal_centimetres' 'reciprocal_millimetres' '*' 1.0E-01 'reciprocal_centimetres' 'reciprocal_nanometres' '*' 1.0E-07 'reciprocal_centimetres' 'reciprocal_angstroms' '*' 1.0E-08 'reciprocal_centimetres' 'reciprocal_picometres' '*' 1.0E-10 # 'reciprocal_millimetres' 'reciprocal_metres' '*' 1.0E+03 'reciprocal_millimetres' 'reciprocal_centimetres' '*' 1.0E+01 'reciprocal_millimetres' 'reciprocal_nanometres' '*' 1.0E-06 'reciprocal_millimetres' 'reciprocal_angstroms' '*' 1.0E-07 'reciprocal_millimetres' 'reciprocal_picometres' '*' 1.0E-09 # 'reciprocal_nanometres' 'reciprocal_metres' '*' 1.0E+09 'reciprocal_nanometres' 'reciprocal_centimetres' '*' 1.0E+07 'reciprocal_nanometres' 'reciprocal_millimetres' '*' 1.0E+06 'reciprocal_nanometres' 'reciprocal_angstroms' '*' 1.0E-01 'reciprocal_nanometres' 'reciprocal_picometres' '*' 1.0E-03 # 'reciprocal_angstroms' 'reciprocal_metres' '*' 1.0E+10 'reciprocal_angstroms' 'reciprocal_centimetres' '*' 1.0E+08 'reciprocal_angstroms' 'reciprocal_millimetres' '*' 1.0E+07 'reciprocal_angstroms' 'reciprocal_nanometres' '*' 1.0E+01 'reciprocal_angstroms' 'reciprocal_picometres' '*' 1.0E-02 # 'reciprocal_picometres' 'reciprocal_metres' '*' 1.0E+12 'reciprocal_picometres' 'reciprocal_centimetres' '*' 1.0E+10 'reciprocal_picometres' 'reciprocal_millimetres' '*' 1.0E+09 'reciprocal_picometres' 'reciprocal_nanometres' '*' 1.0E+03 'reciprocal_picometres' 'reciprocal_angstroms' '*' 1.0E+01 ### 'nanometres_squared' 'angstroms_squared' '*' 1.0E+02 'nanometres_squared' 'picometres_squared' '*' 1.0E+06 # 'angstroms_squared' 'nanometres_squared' '*' 1.0E-02 'angstroms_squared' 'picometres_squared' '*' 1.0E+04 'angstroms_squared' '8pi2_angstroms_squared' '*' 78.9568 # 'picometres_squared' 'nanometres_squared' '*' 1.0E-06 'picometres_squared' 'angstroms_squared' '*' 1.0E-04 ### 'nanometres_cubed' 'angstroms_cubed' '*' 1.0E+03 'nanometres_cubed' 'picometres_cubed' '*' 1.0E+09 # 'angstroms_cubed' 'nanometres_cubed' '*' 1.0E-03 'angstroms_cubed' 'picometres_cubed' '*' 1.0E+06 # 'picometres_cubed' 'nanometres_cubed' '*' 1.0E-09 'picometres_cubed' 'angstroms_cubed' '*' 1.0E-06 ### 'kilopascals' 'gigapascals' '*' 1.0E-06 'gigapascals' 'kilopascals' '*' 1.0E+06 ### 'hours' 'minutes' '*' 6.0E+01 'hours' 'seconds' '*' 3.6E+03 'hours' 'microseconds' '*' 3.6E+09 # 'minutes' 'hours' '/' 6.0E+01 'minutes' 'seconds' '*' 6.0E+01 'minutes' 'microseconds' '*' 6.0E+07 # 'seconds' 'hours' '/' 3.6E+03 'seconds' 'minutes' '/' 6.0E+01 'seconds' 'microseconds' '*' 1.0E+06 # 'microseconds' 'hours' '/' 3.6E+09 'microseconds' 'minutes' '/' 6.0E+07 'microseconds' 'seconds' '/' 1.0E+06 ### 'celsius' 'kelvins' '-' 273.0 'kelvins' 'celsius' '+' 273.0 ### 'electrons_per_nanometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E-03 'electrons_per_nanometres_cubed' 'electrons_per_picometres_cubed' '*' 1.0E-09 # 'electrons_per_angstroms_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E+03 'electrons_per_angstroms_cubed' 'electrons_per_picometres_cubed' '*' 1.0E-06 # 'electrons_per_picometres_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E+09 'electrons_per_picometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E+06 ### ######################## ## DICTIONARY_HISTORY ## ######################## loop_ _dictionary_history.version _dictionary_history.update _dictionary_history.revision 1.1.3 2001-04-19 ; Another typo corrections by Wilfred Li, and cleanup by HJB ; 1.1.2 2001-03-06 ; Several typo corrections by Wilfred Li ; 1.1.1 2001-02-16 ; Several typo corrections by JW ; 1.1 2001-02-06 ; Draft resulting from discussions on header for use at NSLS (HJB) + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'. + Add '_diffrn_measurement_axis.measurement_device' and change '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'. + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source', '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm' , '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end', '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr', '_diffrn_scan_axis.displacement_rstrt_incr', '_diffrn_scan_frame_axis.angle_increment', '_diffrn_scan_frame_axis.angle_rstrt_incr', '_diffrn_scan_frame_axis.displacement', '_diffrn_scan_frame_axis.displacement_increment',and '_diffrn_scan_frame_axis.displacement_rstrt_incr'. + Add _diffrn_measurement.device to category key + Update yyyy-mm-dd to allow optional time with fractional seconds for time stamps. + Fix typos caught by RS. + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to al low for coupled axes, as in spiral scans. + Add examples for fairly complete headers thanks to R. Sweet and P. Ellis. ; 1.0 2000-12-21 ; Release version - few typos and tidying up (BM & HJB) + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end of dictionary. + Alphabetize dictionary. ; 0.7.1 2000-09-29 ; Cleanup fixes (JW) + Correct spelling of diffrn_measurement_axis in _axis.id + Correct ordering of uses of _item.mandatory_code and _item_default.value ; 0.7.0 2000-09-09 ; Respond to comments by I. David Brown (HJB) + Added further comments on '\n' and '\t' + Updated ITEM_UNITS_LIST by taking section from mmCIF dictionary and adding metres. Changed all spelling 'meter' to 'metre' throughout. + Added missing enumerations to _array_structure.compression_type and made 'none' the default. + Removed parent-child relationship between _array_structure_list.index and _array_structure_list.precedence . + Improve alphabetization. + Fix _array_intensities_gain.esd related function. + Improved comments in AXIS. + Fixed DIFFRN_FRAME_DATA example. + Removed erroneous DIFFRN_MEASUREMENT example. + Added _diffrn_measurement_axis.id to the category key. ; 0.6.0 1999-01-14 ; Remove redundant information for ENC_NONE data (HJB) + After the D5 remove binary section identifier, size and compression type. + Add Control-L to header. ; 0.5.1 1999-01-03 ; Cleanup of typos and syntax errors (HJB) + Cleanup example details for DIFFRN_SCAN category. + Add missing quote marks for _diffrn_scan.id definition. ; 0.5 1999-01-01 ; Modifications for axis definitions and reduction of binary header (HJB) + Restored _diffrn_detector.diffrn_id to DIFFRN_DETECTOR KEY. + Added AXIS category. + Brought complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories in from cif_mm.dic for clarity. + changed _array_structure.encoding_type from type code to uline and added X-Binary-Element-Type to MIME header. + added detector beam center _diffrn_detector_element.center[1] and _diffrn_detector_element.center[2] + corrected item name of _diffrn_refln.frame_id + replace reference to _array_intensities.undefined by _array_intensities.undefined_value + replace references to _array_intensity.scaling with _array_intensities.scaling + added DIFFRN_SCAN... categories ; 0.4 1998-08-11 ; Modifications to the 0.3 imgCIF draft (HJB) + Reflowed comment lines over 80 characters and corrected typos. + Updated examples and descriptions of MIME encoded data. + Change name to cbfext98.dic. ; 0.3 1998-07-04 ; Modifications for imgCIF (HJB) + Added binary type, which is a text field containing a variant on MIME encoded data. + Changed type of _array_data.data to binary and specified internal structure of raw binary data. + Added _array_data.binary_id, and made _diffrn_frame_data.binary_id and _array_intensities.binary_id into pointers to this item. ; 0.2 1997-12-02 ; Modifications to the CBF draft (JW): + Added category hierarchy for describing frame data developed from discussions at the BNL imgCIF Workshop Oct 1997. The following changes were made in implementing the workshop draft. Category DIFFRN_ARRAY_DATA was renamed to DIFFRN_FRAME_DATA. Category DIFFRN_FRAME_TYPE was renamed to DIFFRN_DETECTOR_ELEMENT. The parent item for _diffrn_frame_data.array_id was changed from array_structure_list.array_id to array_structure.id. Item _diffrn_detector.array_id was deleted. + Added data item _diffrn_frame_data.binary_id to identify data groups within a binary section. The formal identification of the binary section is still fuzzy. ; 0.1 1997-01-24 ; First draft of this dictionary in DDL 2.1 compliant format by John Westbrook (JW). This version was adapted from the Crystallographic Binary File (CBF) Format Draft Proposal provided by Andy Hammersley (AH). Modifications to the CBF draft (JW): + In this version the array description has been cast in the categories ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. These categories have been generalized to describe array data of arbitrary dimension. + Array data in this description are contained in the category ARRAY_DATA . This departs from the CBF notion of data existing in some special comment. In this description, data is handled as an ordinary data item encapsulated in a character data type. Although handling binary data this manner deviates from CIF conventions, it does not violate any DDL 2.1 rules. DDL 2.1 regular expressions can be used to define the binary representation which will permit some level of data validation. In this version, the placeholder type code "any" has been used. This translates to a regular expression which will match any pattern. It should be noted that DDL 2.1 already supports array data objects although these have not been used in the current mmCIF dictionary. It may be possible to use the DDL 2.1 ITEM_STRUCTURE and ITEM_STRUCTURE_LIST categories to provide the information that is carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. By moving the array structure to the DDL level it would be possible to define an array type as well as a regular expression defining the data format. + Multiple array sections can be properly handled within a single datablock. ; #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof ./CBFlib-0.9.2.2/doc/cif_img_1.1.3.txt0000644000076500007650000051754211603702115015237 0ustar yayayaya############################################################################## # # # Image CIF Dictionary (imgCIF) # # and Crystallographic Binary File Dictionary (CBF) # # Extending the Macromolecular CIF Dictionary (mmCIF) # # # # Version 1.1.3 # # of 2001-04-19 # # # # Adapted from the # # imgCIF Workshop, BNL Oct 1997 # # and # # Crystallographic Binary File Format Draft Proposal # # by Andy Hammersley # # # ############################################################################## # # # First DDL 2.1 Version # # by # # John Westbrook # # Nucleic Acid Database # # Rutgers University # # # ############################################################################## # These revisions by: Herbert J. Bernstein, yaya@bernstein-plus-sons.com # # Incorporating comments by I. David Brown, John Westbrook, Brian McMahon. # # Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li and others # ############################################################################## data_cif_img.dic _dictionary.title cif_img.dic _dictionary.version 1.1.3 _dictionary.datablock_id cif_img.dic ############################################################################## # CONTENTS # # CATEGORY_GROUP_LIST # # category ARRAY_DATA # # _array_data.array_id # _array_data.binary_id # _array_data.data # # category ARRAY_ELEMENT_SIZE # # _array_element_size.array_id # _array_element_size.index # _array_element_size.size # # category ARRAY_INTENSITIES # # _array_intensities.array_id # _array_intensities.binary_id # _array_intensities.gain # _array_intensities.gain_esd # _array_intensities.linearity # _array_intensities.offset # _array_intensities.scaling # _array_intensities.overload # _array_intensities.undefined_value # # category ARRAY_STRUCTURE # # _array_structure.byte_order # _array_structure.compression_type # _array_structure.encoding_type # _array_structure.id # # category ARRAY_STRUCTURE_LIST # # _array_structure_list.axis_set_id # _array_structure_list.array_id # _array_structure_list.dimension # _array_structure_list.direction # _array_structure_list.index # _array_structure_list.precedence # # category ARRAY_STRUCTURE_LIST_AXIS # # _array_structure_list_axis.axis_id # _array_structure_list_axis.axis_set_id # _array_structure_list_axis.angle # _array_structure_list_axis.angle_increment # _array_structure_list_axis.displacement_increment # _array_structure_list_axis.angular_pitch # _array_structure_list_axis.radial_pitch # # category AXIS # # _axis.depends_on # _axis.equipment # _axis.id # _axis.offset[1] # _axis.offset[2] # _axis.offset[3] # _axis.type # _axis.vector[1] # _axis.vector[2] # _axis.vector[3] # # category DIFFRN_DATA_FRAME # # _diffrn_data_frame.array_id # _diffrn_data_frame.binary_id # _diffrn_data_frame.detector_element_id # _diffrn_data_frame.id # # category DIFFRN_DETECTOR # # _diffrn_detector.details # _diffrn_detector.detector # _diffrn_detector.diffrn_id # _diffrn_detector.dtime # _diffrn_detector.id # _diffrn_detector.number_of_axes # _diffrn_detector.type # # category DIFFRN_DETECTOR_AXIS # # _diffrn_detector_axis.axis_id # _diffrn_detector_axis.detector_id # # category DIFFRN_DETECTOR_ELEMENT # # _diffrn_detector_element.center[1] # _diffrn_detector_element.center[2] # _diffrn_detector_element.id # _diffrn_detector_element.detector_id # # category DIFFRN_MEASUREMENT # # _diffrn_measurement.diffrn_id # _diffrn_measurement.details # _diffrn_measurement.device # _diffrn_measurement.device_details # _diffrn_measurement.device_type # _diffrn_measurement.id # _diffrn_measurement.method # _diffrn_measurement.number_of_axes # _diffrn_measurement.specimen_support # # category DIFFRN_MEASUREMENT_AXIS # # _diffrn_measurement_axis.axis_id # _diffrn_measurement_axis.measurement_device # _diffrn_measurement_axis.measurement_id # # category DIFFRN_RADIATION # # _diffrn_radiation.collimation # _diffrn_radiation.diffrn_id # _diffrn_radiation.div_x_source # _diffrn_radiation.div_y_source # _diffrn_radiation.div_x_y_source # _diffrn_radiation.filter_edge' # _diffrn_radiation.inhomogeneity # _diffrn_radiation.monochromator # _diffrn_radiation.polarisn_norm # _diffrn_radiation.polarisn_ratio # _diffrn_radiation.polarizn_source_norm # _diffrn_radiation.polarizn_source_ratio # _diffrn_radiation.probe # _diffrn_radiation.type # _diffrn_radiation.xray_symbol # _diffrn_radiation.wavelength_id # # category DIFFRN_REFLN # # _diffrn_refln.frame_id # # category DIFFRN_SCAN # # _diffrn_scan.id # _diffrn_scan.date_end # _diffrn_scan.date_start # _diffrn_scan.integration_time # _diffrn_scan.frame_id_start # _diffrn_scan.frame_id_end # _diffrn_scan.frames # # category DIFFRN_SCAN_AXIS # # _diffrn_scan_axis.axis_id # _diffrn_scan_axis.angle_start # _diffrn_scan_axis.angle_range # _diffrn_scan_axis.angle_increment # _diffrn_scan_axis.angle_rstrt_incr # _diffrn_scan_axis.displacement_start # _diffrn_scan_axis.displacement_range # _diffrn_scan_axis.displacement_increment # _diffrn_scan_axis.displacement_rstrt_incr # _diffrn_scan_axis.scan_id # # category DIFFRN_SCAN_FRAME # # _diffrn_scan_frame.date # _diffrn_scan_frame.frame_id # _diffrn_scan_frame.frame_number # _diffrn_scan_frame.integration_time # _diffrn_scan_frame.scan_id # # category DIFFRN_SCAN_FRAME_AXIS # # _diffrn_scan_frame_axis.axis_id # _diffrn_scan_frame_axis.angle # _diffrn_scan_frame_axis.angle_increment # _diffrn_scan_frame_axis.angle_rstrt_incr # _diffrn_scan_frame_axis.displacement # _diffrn_scan_frame_axis.displacement_increment # _diffrn_scan_frame_axis.displacement_rstrt_incr # _diffrn_scan_frame_axis.frame_id # # ITEM_TYPE_LIST # ITEM_UNITS_LIST # DICTIONARY_HISTORY # ############################################################################## ######################### ## CATEGORY_GROUP_LIST ## ######################### loop_ _category_group_list.id _category_group_list.parent_id _category_group_list.description 'inclusive_group' . ; Categories that belong to the dictionary extension. ; 'array_data_group' 'inclusive_group' ; Categories that describe array data. ; 'axis_group' 'inclusive_group' ; Categories that describe axes. ; 'diffrn_group' 'inclusive_group' ; Categories that describe details of the diffraction experiment. ; ############## # ARRAY_DATA # ############## save_ARRAY_DATA _category.description ; Data items in the ARRAY_DATA category are the containers for the array data items described in category ARRAY_STRUCTURE. ; _category.id array_data _category.mandatory_code no loop_ _category_key.name '_array_data.array_id' '_array_data.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows two binary data blocks. The first one was compressed by the CBF_CANONICAL compression algorithm and presented as hexadecimal data. The first character "H" on the data lines means hexadecimal. It could have been "O" for octal or "D" for decimal. The second character on the line shows the number of bytes in each word (in this case "4"), which then requires 8 hexadecimal digits per word. The third character gives the order of octets within a word, in this case "<" for the ordering 4321 (i.e. "big-endian"). Alternatively the character ">" could have been used for the ordering 1234 (i.e. "little-endian"). The block has a "message digest" to check the integrity of the data. The second block is similar, but uses CBF_PACKED compression and BASE64 encoding. Note that the size and the digest are different. ; ; loop_ _array_data.array_id _array_data.binary_id _array_data.data image_1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_CANONICAL" Content-Transfer-Encoding: X-BASE16 X-Binary-Size: 3927126 X-Binary-ID: 1 Content-MD5: u2sTJEovAHkmkDjPi+gWsg== # Hexadecimal encoding, byte 0, byte order ...21 # H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ... .... --CIF-BINARY-FORMAT-SECTION---- ; image_2 2 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF-PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3745758 X-Binary-ID: 1 Content-MD5: 1zsJjWPfol2GYl2V+QSXrw== ELhQAAAAAAAA... ... --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_data.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_data.array_id' _item.category_id array_data _item.mandatory_code yes _item_type.code code save_ save__array_data.binary_id _item_description.description ; This item is an integer identifier which, along with _array_data.array_id should uniquely identify the particular block of array data. If _array_data.binary_id is not explicitly given, it defaults to 1. The value of _array_data.binary_id distinguishes among multiple sets of data with the same array structure. If the MIME header of the data array specifies a value for X-Binary-Id, these values should be equal. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_data.binary_id' array_data implicit '_diffrn_data_frame.binary_id' diffrn_data_frame implicit '_array_intensities.binary_id' array_intensities implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.binary_id' '_array_data.binary_id' '_array_intensities.binary_id' '_array_data.binary_id' _item_default.value 1 _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_data.data _item_description.description ; The value of _array_data.data contains the array data encapsulated in a STAR string. The representation used is a variant on the Multipurpose Internet Mail Extensions (MIME) specified in RFC 2045-2049 by N. Freed et al. The boundary delimiter used in writing an imgCIF or CBF is "--CIF-BINARY-FORMAT-SECTION--" (including the required initial "--"). The Content-Type may be any of the discrete types permitted in RFC 2045; "application/octet-stream" is recommended. If an octet stream was compressed, the compression should be specified by the parameter 'conversions="x-CBF_PACKED"' or the parameter 'conversions="x-CBF_CANONICAL"'. The Content-Transfer-Encoding may be "BASE-64", "Quoted-Printable", "X-BASE-8", "X-BASE-10", or "X-BASE-16" for an imgCIF or "BINARY" for a CBF. The octal, decimal and hexadecimal transfer encodings are for convenience in debugging, and are not recommended for archiving and data interchange. In an imgCIF file, the encoded binary data begins after the empty line terminating the header. In a CBF, the raw binary data begins after an empty line terminating the header and after the sequence: Octet Hex Decimal Purpose 0 0C 12 (ctrl-L) Page break 1 1A 26 (ctrl-Z) Stop listings in MS-DOS 2 04 04 (Ctrl-D) Stop listings in UNIX 3 D5 213 Binary section begins None of these octets are included in the calculation of the message size, nor in the calculation of the message digest. The X-Binary-Size header specifies the size of the equivalent binary data in octets. If compression was used, this size is the size after compression, including any book-keeping fields. And adjustment is made for the deprecated binary formats in which 8 bytes of binary header are used for the compression type. In that case, the 8 bytes used for the compression type is subtracted from the size, so that the same size will be reported if the compression type is supplied in the MIME header. Use of the MIME header is the recommended way to supply the compression type. In general, no portion of the binary header is included in the calculation of the size. The X-Binary-Element-Type header specifies the type of binary data in the octets, using the same descriptive phrases as in _array_structure.encoding_type. The default value is "unsigned 32-bit integer". An MD5 message digest may, optionally, be used. The "RSA Data Security, Inc. MD5 Message-Digest Algorithm" should be used. No portion of the header is included in the calculation of the message digest. If the Transfer Encoding is "X-BASE-8", "X-BASE-10", or "X-BASE-16", the data is presented as octal, decimal or hexadecimal data organized into lines or words. Each word is created by composing octets of data in fixed groups of 2, 3, 4, 6 or 8 octets, either in the order ...4321 ("big- endian") or 1234... (little-endian). If there are fewer than the specified number of octets to fill the last word, then the missing octets are presented as "==" for each missing octet. Exactly two equal signs are used for each missing octet even for octal and decimal encoding. The format of lines is: rnd xxxxxx xxxxxx xxxxxx where r is "H", "O", or "D" for hexadecimal, octal or decimal, n is the number of octets per word. and d is "<" for ">" for the "...4321" and "1234..." octet orderings respectively. The "==" padding for the last word should be on the appropriate side to correspond to the missing octets, e.g. H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000 or H3> FF0700 00==== For these hex, octal and decimal formats, only, comments beginning with "#" are permitted to improve readability. BASE64 encoding follows MIME conventions. Octets are in groups of three, c1, c2, c3. The resulting 24 bits are broken into four 6-bit quantities, starting with the high-order six bits (c1 >> 2) of the first octet, then the low-order two bits of the first octet followed by the high-order 4 bits of the second octet ((c1 & 3)<<4 | (c2>>4)), then the bottom 4 bits of the second octet followed by the high order two bits of the last octet ((c2 & 15)<<2 | (c3>>6)), then the bottom six bits of the last octet (c3 & 63). Each of these four quantities is translated into an ASCII character using the mapping: 1 2 3 4 5 6 0123456789012345678901234567890123456789012345678901234567890123 | | | | | | | ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/ With short groups of octets padded on the right with one "=" if c3 is missing, and with "==" if both c2 and c3 are missing. QUOTED-PRINTABLE encoding also follows MIME conventions, copying octets without translation if their ASCII values are 32..38, 42, 48..57, 59..60, 62, 64..126 and the octet is not a ";" in column 1. All other characters are translated to =nn, where nn is the hexadecimal encoding of the octet. All lines are "wrapped" with a terminating "=" (i.e. the MIME conventions for an implicit line terminator are never used). ; _item.name '_array_data.data' _item.category_id array_data _item.mandatory_code yes _item_type.code binary save_ ###################### # ARRAY_ELEMENT_SIZE # ###################### save_ARRAY_ELEMENT_SIZE _category.description ; Data items in the ARRAY_ELEMENT_SIZE category record the physical size of array elements along each array dimension. ; _category.id array_element_size _category.mandatory_code no loop_ _category_key.name '_array_element_size.array_id' '_array_element_size.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A regular 2D array with a uniform element dimension of 1220 nanometres. ; ; loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size image_1 1 1.22e-6 image_1 2 1.22e-6 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_element_size.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ATOM_STRUCTURE category. ; _item.name '_array_element_size.array_id' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.index _item_description.description ; This item is a pointer to _array_structure_list.index in the ATOM_STRUCTURE_LIST category. ; _item.name '_array_element_size.index' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.size _item_description.description ; The size in metres of an image element in this dimension. This supposes that the elements are arranged on a regular grid. ; _item.name '_array_element_size.size' _item.category_id array_element_size _item.mandatory_code yes _item_type.code float _item_units.code 'metres' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ ##################### # ARRAY_INTENSITIES # ##################### save_ARRAY_INTENSITIES _category.description ; Data items in the ARRAY_INTENSITIES category record the information required to recover the intensity data from the set of data values stored in the ARRAY_DATA category. The actual detector may have a complex relationship between the raw intensity values and the number of incident photons. In most cases, the number stored in the final array will have a simple linear relationship to the actual number of incident photons, given by '_array_intensities.gain'. If raw, uncorrected values are presented (e.g for calibration experiments), the value of '_array_intensities.linearity' will be 'raw' and '_array_intensities.gain' will not be used. ; _category.id array_intensities _category.mandatory_code no loop_ _category_key.name '_array_intensities.array_id' '_array_intensities.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 ; ; loop_ _array_intensities.array_id _array_intensities.linearity _array_intensities.gain _array_intensities.overload _array_intensities.undefined_value image_1 linear 1.2 655535 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_intensities.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ATOM_STRUCTURE category. ; _item.name '_array_intensities.array_id' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code save_ save__array_intensities.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_STRUCTURE category. ; _item.name '_array_intensities.binary_id' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code int save_ save__array_intensities.gain _item_description.description ; Detector "gain". The factor by which linearized intensity count values should be divided to produce true photon counts. ; _item.name '_array_intensities.gain' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain_esd' 'associated_value' save_ save__array_intensities.gain_esd _item_description.description ; The estimated standard deviation in detector "gain". ; _item.name '_array_intensities.gain_esd' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain' 'associated_esd' save_ save__array_intensities.linearity _item_description.description ; The intensity linearity scaling used from raw intensity to the stored element value: 'linear' is obvious 'offset' means that the value defined by '_array_intensities.offset' should be added to each element value. 'scaling' means that the value defined by '_array_intensities.scaling' should be multiplied with each element value. 'scaling_offset' is the combination of the two previous cases, with the scale factor applied before the offset value. 'sqrt_scaled' means that the square root of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and squaring the result. 'logarithmic_scaled' means that the logarithm based 10 of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and calculating 10 to the power of this number. 'raw' means that the data is the raw is a set of raw values straight from the detector. ; _item.name '_array_intensities.linearity' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'linear' . 'offset' ; The value defined by '_array_intensities.offset' should be added to each element value. ; 'scaling' ; The value defined by '_array_intensities.scaling' should be multiplied with each element value. ; 'scaling_offset' ; The combination of the scaling and offset with the scale factor applied before the offset value. ; 'sqrt_scaled' ; The square root of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and squaring the result. ; 'logarithmic_scaled' ; The logarithm based 10 of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and calculating 10 to the power of this number. ; 'raw' ; The array consists of raw values to which no corrections have been applied. While the handling of the data is similar to that given for 'linear' data with no offset, the meaning of the data differs in that the number of incident photons is not necessarily linearly related to the number of counts reported. This value is intended for use either in calibration experiments or to allow for handling more complex data fitting algorithms than are allowed for by this data item. ; save_ save__array_intensities.offset _item_description.description ; Offset value to add to array element values in the manner described by item _array_intensities.linearity. ; _item.name '_array_intensities.offset' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.scaling _item_description.description ; Multiplicative scaling value to be applied to array data in the manner described by item _array_intensities.linearity. ; _item.name '_array_intensities.scaling' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.overload _item_description.description ; The saturation intensity level for this data array. ; _item.name '_array_intensities.overload' _item.category_id array_intensities _item.mandatory_code no _item_type.code float _item_units.code 'counts' save_ save__array_intensities.undefined_value _item_description.description ; A value to be substituted for undefined values in the data array. ; _item.name '_array_intensities.undefined_value' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ ################### # ARRAY_STRUCTURE # ################### save_ARRAY_STRUCTURE _category.description ; Data items in the ARRAY_STRUCTURE category record the organization and encoding of array data which may be stored in the ARRAY_DATA category. ; _category.id array_structure _category.mandatory_code no _category_key.name '_array_structure.id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order image_1 "unsigned 16-bit integer" none little_endian ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure.byte_order _item_description.description ; The order of bytes for integer values which require more than 1-byte. (IBM-PC's and compatibles, and Dec-Vaxes use low-byte-first ordered integers, whereas Hewlett Packard 700 series, Sun-4 and Silicon Graphics use high-byte-first ordered integers. Dec-Alphas can produce/use either depending on a compiler switch.) ; _item.name '_array_structure.byte_order' _item.category_id array_structure _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'big_endian' ; The first byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; 'little_endian' ; The last byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; save_ save__array_structure.compression_type _item_description.description ; Type of data compression method used to compress the array data. ; _item.name '_array_structure.compression_type' _item.category_id array_structure _item.mandatory_code no _item_type.code code _item_default.value 'none' loop_ _item_enumeration.value _item_enumeration.detail 'none' ; Data are stored in normal format as defined by '_array_structure.encoding_type' and '_array_structure.byte_order'. ; 'byte_offsets' ; Using the compression scheme defined in CBF definition Section 5.0. ; 'packed' ; Using the 'packed' compression scheme, a CCP4-style packing (CBFlib section 3.3.2) ; 'canonical' ; Using the 'canonical' compression scheme (CBFlib section 3.3.1) ; save_ save__array_structure.encoding_type _item_description.description ; Data encoding of a single element of array data. In several cases, the IEEE format is referenced. See "IEEE Standard for Binary Floating-Point Arithmetic", ANSI/IEEE Std 754-1985, the Institute of Electrical and Electronics Engineers, Inc., NY 1985. ; _item.name '_array_structure.encoding_type' _item.category_id array_structure _item.mandatory_code yes _item_type.code uline loop_ _item_enumeration.value 'unsigned 8-bit integer' 'signed 8-bit integer' 'unsigned 16-bit integer' 'signed 16-bit_integer' 'unsigned 32-bit integer' 'signed 32-bit integer' 'signed 32-bit real IEEE' 'signed 64-bit real IEEE' 'signed 32-bit complex IEEE' save_ save__array_structure.id _item_description.description ; The value of _array_structure.id must uniquely identify each item of array data. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure.id' array_structure yes '_array_data.array_id' array_data yes '_array_structure_list.array_id' array_structure_list yes '_array_intensities.array_id' array_intensities yes '_diffrn_data_frame.array_id' diffrn_data_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_data.array_id' '_array_structure.id' '_array_structure_list.array_id' '_array_structure.id' '_array_intensities.array_id' '_array_structure.id' '_diffrn_data_frame.array_id' '_array_structure.id' save_ ######################## # ARRAY_STRUCTURE_LIST # ######################## save_ARRAY_STRUCTURE_LIST _category.description ; Data items in the ARRAY_STRUCTURE_LIST category record the size and organization of each array dimension. The relationship to physical axes may be given. ; _category.id array_structure_list _category.mandatory_code no loop_ _category_key.name '_array_structure_list.array_id' '_array_structure_list.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - An image array of 1300 x 1200 elements. The raster order of the image is left-to-right (increasing) in first dimension and bottom-to-top (decreasing) in the second dimension. ; ; loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id image_1 1 1300 1 increasing ELEMENT_X image_1 2 1200 2 decreasing ELEMENY_Y ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure_list.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_structure_list.array_id' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code code save_ save__array_structure_list.axis_set_id _item_description.description ; This is a descriptor for the physical axis or set of axes corresponding to an array index. This data item is related to the axes of the detector itself given in DIFFRN_DETECTOR_AXIS, but usually differ in that the axes in this category are the axes of the coordinate system of reported data points, while the axes in DIFFRN_DETECTOR_AXIS are the physical axes of the detector describing the "poise" of the detector as an overall physical object. If there is only one axis in the set, the identifier of that axis should be used as the identifier of the set. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.axis_set_id' array_structure_list yes '_array_structure_list_axis.axis_set_id' array_structure_list_axis implicit _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_structure_list_axis.axis_set_id' '_array_structure_list.axis_set_id' save_ save__array_structure_list.dimension _item_description.description ; The number of elements stored in the array structure in this dimension. ; _item.name '_array_structure_list.dimension' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.direction _item_description.description ; Identifies the direction in which this array index changes. ; _item.name '_array_structure_list.direction' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_enumeration.value _item_enumeration.detail 'increasing' ; Indicates the index changes from 1 to the maximum dimension. ; 'decreasing' ; Indicates the index changes from the maximum dimension to 1. ; save_ save__array_structure_list.index _item_description.description ; Identifies the one-based index of the row or column in the array structure. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.index' array_structure_list yes '_array_structure_list.precedence' array_structure_list yes '_array_element_size.index' array_element_size yes _item_type.code int loop_ _item_linked.child_name _item_linked.parent_name '_array_element_size.index' '_array_structure_list.index' loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.precedence _item_description.description ; Identifies the rank order in which this array index changes with respect to other array indices. The precedence of 1 indicates the index which changes fastest. ; _item.name '_array_structure_list.precedence' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ ############################# # ARRAY_STRUCTURE_LIST_AXIS # ############################# save_ARRAY_STRUCTURE_LIST_AXIS _category.description ; Data items in the ARRAY_STRUCTURE_LIST_AXIS category describes the physical settings of sets axes for the centres of pixels that correspond to data points described in the ARRAY_STRUCTURE_LIST category. In the simplest cases, the physical increments of a single axis correspond to the increments of a single array index. More complex organizations, e.g. spiral scans, may require coupled motions along multiple axes. Note that a spiral scan uses two coupled axis, one for the angular direction, one for the radial direction. This differs from a cylindrical scan for which the two axes are not coupled into one set. ; _category.id array_structure_list_axis _category.mandatory_code no loop_ _category_key.name '_array_structure_list_axis.axis_set_id' '_array_structure_list_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' save_ save__array_structure_list_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the set of axes for which settings are being specified. Multiple axes may be specified for the same value of '_array_structure_list_axis.axis_set_id' This item is a pointer to _axis.id in the AXIS category. ; _item.name '_array_structure_list_axis.axis_id' _item.category_id array_structure_list_axis _item.mandatory_code yes save_ save__array_structure_list_axis.axis_set_id _item_description.description ; The value of this data item is the identifier of the set of axes for which axis settings are being specified. Multiple axes may be specified for the same value of _array_structure_list_axis.axis_set_id . This item is a pointer to _array_structure_list.axis_set_id in the ARRAY_STRUCTURE_LIST category. If this item is not specified, it defaults to the corresponding axis identifier. ; _item.name '_array_structure_list_axis.axis_set_id' _item.category_id array_structure_list_axis _item.mandatory_code implicit save_ save__array_structure_list_axis.angle _item_description.description ; The setting of the specified axis in degrees for the first data point of the array index with the corresponding value of '_array_structure_list.axis_set_id'. If the index is specified as 'increasing' this will be the center of the pixel with index value 1. If the index is specified as 'decreasing' this will be the center of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.angle' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.angle_increment _item_description.description ; The pixel-center-to-pixel-center increment in the angular setting of the specified axis in degrees. This is not meaningful in the case of 'constant velocity' spiral scans and should not be specified in that case. See '_array_structure_list_axis.angular_pitch'. ; _item.name '_array_structure_list_axis.angle_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for the first data point of the array index with the corresponding value of '_array_structure_list.axis_set_id'. If the index is specified as 'increasing' this will be the center of the pixel with index value 1. If the index is specified as 'decreasing' this will be the center of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.displacement' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.displacement_increment _item_description.description ; The pixel-center-to-pixel-center increment for the displacement setting of the specified axis in millimetres. ; _item.name '_array_structure_list_axis.displacement_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.angular_pitch _item_description.description ; The pixel-center-to-pixel-center distance for a one step change in the setting of the specified axis in millimetres. This is meaningful only for 'constant velocity' spiral scans, or for uncoupled angular scans at a constant radius (cylindrical scan) and should not be specified for cases in which the angle between pixels, rather than the distance between pixels is uniform. See '_array_structure_list_axis.angle_increment'. ; _item.name '_array_structure_list_axis.angular_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.radial_pitch _item_description.description ; The radial distance from one "cylinder" of pixels to the next in millimetres. If the scan is a 'constant velocity' scan with differing angular displacements between pixels, the value of this item may differ significantly from the value of '_array_structure_list_axis.displacement_increment'. ; _item.name '_array_structure_list_axis.radial_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ ######## # AXIS # ######## save_AXIS _category.description ; Data items in the AXIS category record the information required to describe the various goniometer, detector, source and other axes needed to specify a data collection. The location of each axis is specified by two vectors: the axis itself, given as a unit vector, and an offset to the base of the unit vector. These vectors are referenced to a right-handed laboratory coordinate system with its origin in the sample or specimen: | Y (to complete right-handed system) | | | | | |________________X / principal goniometer axis / / / / /Z (to source) Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from the sample or specimen along the principal axis of the goniometer. Axis 2 (Y): The Y-axis completes an orthogonal right-handed system defined by the X-axis and the Z-axis (see below). Axis 3 (Z): The Z-axis is derived from the source axis which goes from the sample to the source. The Z-axis is the component of the source axis in the direction of the source orthogonal to the X-axis in the plane defined by the X-axis and the source axis. These axes are based on the goniometer, not on the orientation of the detector, gravity, etc. The vectors necessary to specify all other axes are given by sets of three components in the order (X, Y, Z). If the axis involved is a rotation axis, it is right handed, i.e. as one views the object to be rotated from the origin (the tail) of the unit vector, the rotation is clockwise. If a translation axis is specified, the direction of the unit vector specifies the sense of positive translation. Note: This choice of coordinate system is similar to, but significantly different from the choice in MOSFLM (Andrew G.W. Leslie, Harry Powell, MRC Laboratory of Molecular Biology, Hills Road, Cambridge CB2 2QH,UK http://www.dl.ac.uk/CCP/CCP4/dist/x-windows/Mosflm/). In MOSFLM, X is along the X-ray beam (our Z axis) and Z is along the rotation axis. All rotations are given in degrees and all translations are given in mm. Axes may be dependent on one another. The X-axis is the only goniometer axis the direction of which is strictly connected to the hardware. All other axes are specified by the positions they would assume when the axes upon which they depend are at their zero points. When specifying detector axes, the axis is given to the beam center. The location of the beam center on the detector should be given in the DIFFRN_DETECTOR category in distortion-corrected mm from the (0,0) corner of the detector. It should be noted that many different origins arise in the definition of an experiment. In particular, as noted above, we need to specify the location of the beam center on the detector in terms of the origin of the detector, which is, of course, not coincident with the center of the sample. ; _category.id axis _category.mandatory_code no loop_ _category_key.name '_axis.id' '_axis.equipment' loop_ _category_group.id 'inclusive_group' 'axis_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows the axis specification of the axes of a kappa geometry goniometer (See "X-Ray Structure Determination, A Practical Guide", 2nd ed. by G. H. Stout, L. H. Jensen, Wiley Interscience, 1989, 453 pp, p 134.). There are three axes specified, and no offsets. The outermost axis, omega, is pointed along the X-axis. The next innermost axis, kappa, is at a 50 degree angle to the X-axis, pointed away from the source. The innermost axis, phi, aligns with the X-axis when omega and phi are at their zero-points. If T-omega, T-kappa and T-phi are the transformation matrices derived from the axis settings, the complete transformation would be: x' = (T-omega) (T-kappa) (T-phi) x ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] omega rotation goniometer . 1 0 0 kappa rotation goniometer omega -.64279 0 -.76604 phi rotation goniometer kappa 1 0 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - This example show the axis specification of the axes of a detector, source and gravity. We have juggled the order as a reminder that the ordering of presentation of tokens is not significant. We have taken the center of rotation of the detector to be 68 millimetres in the direction away from the source. ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] source . source . 0 0 1 . . . gravity . gravity . 0 -1 0 . . . tranz translation detector rotz 0 0 1 0 0 -68 twotheta rotation detector . 1 0 0 . . . roty rotation detector twotheta 0 1 0 0 0 -68 rotz rotation detector roty 0 0 1 0 0 -68 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__axis.depends_on _item_description.description ; The value of _axis.type specifies the next outermost axis upon which this axis depends. This item is a pointer to axis.id in the same category. ; _item.name '_axis.depends_on' _item.category_id axis _item.mandatory_code no save_ save__axis.equipment _item_description.description ; The value of _axis.type specifies the type of equipment using the axis: goniometer, detector, gravity, source or general ; _item.name '_axis.equipment' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail goniometer 'equipment used to orient or position samples' detector 'equipment used to detect reflections' general 'equipment used for general purposes' gravity 'axis specifying the downward direction' source 'axis specifying the direction sample to source' save_ save__axis.offset[1] _item_description.description ; The [1] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[2] _item_description.description ; The [2] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[3] _item_description.description ; The [3] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.id _item_description.description ; The value of _axis.id must uniquely identify each axis relevant to the experiment. Note that multiple pieces of equipment may share the same axis (e.g. a twotheta arm), so that the category key for AXIS also includes the equipment. ; loop_ _item.name _item.category_id _item.mandatory_code '_axis.id' axis yes '_array_structure_list_axis.axis_id' array_structure_list_axis yes '_diffrn_detector_axis.axis_id' diffrn_detector_axis yes '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes '_diffrn_scan_axis.axis_id' diffrn_scan_axis yes '_diffrn_scan_frame_axis.axis_id' diffrn_scan_frame_axis yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_axis.depends_on' '_axis.id' '_array_structure_list_axis.axis_id' '_axis.id' '_diffrn_detector_axis.axis_id' '_axis.id' '_diffrn_measurement_axis.axis_id' '_axis.id' '_diffrn_scan_axis.axis_id' '_axis.id' '_diffrn_scan_frame_axis.axis_id' '_axis.id' save_ save__axis.type _item_description.description ; The value of _axis.type specifies the type of axis: rotation, translation (or general when the type is not relevant, as for gravity) ; _item.name '_axis.type' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail rotation 'right-handed axis of rotation' translation 'translation in the direction of the axis' general 'axis for which the type is not relevant' save_ save__axis.vector[1] _item_description.description ; The [1] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector, and is dimensionless. ; _item.name '_axis.vector[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[2] _item_description.description ; The [2] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector, and is dimensionless. ; _item.name '_axis.vector[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[3] _item_description.description ; The [3] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector, and is dimensionless. ; _item.name '_axis.vector[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ ##################### # DIFFRN_DATA_FRAME # ##################### save_DIFFRN_DATA_FRAME _category.description ; Data items in the DIFFRN_DATA_FRAME category record the details about each frame of data. The items in this category were previously in a DIFFRN_FRAME_DATA category, which is now deprecated. The items from the old category are provided as aliases, but should not be used for new work. ; _category.id diffrn_data_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_data_frame.id' '_diffrn_data_frame.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A frame containing data from 4 frame elements. Each frame element has a common array configuration 'array_1' described in ARRAY_STRUCTURE and related categories. The data for each detector element is stored in four groups of binary data in the ARRAY_DATA category, linked by the array_id and binary_id ; ; loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id frame_1 d1_ccd_1 array_1 1 frame_1 d1_ccd_2 array_1 2 frame_1 d1_ccd_3 array_1 3 frame_1 d1_ccd_4 array_1 4 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_data_frame.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_diffrn_data_frame.array_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.array_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0.00 _item_type.code code save_ save__diffrn_data_frame.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_diffrn_data_frame.binary_id' _item.category_id diffrn_data_frame _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_frame_data.binary_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code int save_ save__diffrn_data_frame.detector_element_id _item_description.description ; This item is a pointer to _diffrn_detector_element.id in the DIFFRN_DETECTOR_ELEMENT category. ; _item.name '_diffrn_data_frame.detector_element_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.detector_element_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.id _item_description.description ; The value of _diffrn_data_frame.id must uniquely identify each complete frame of data. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_data_frame.id' diffrn_data_frame yes '_diffrn_refln.frame_id' diffrn_refln yes '_diffrn_scan.frame_id_start' diffrn_scan yes '_diffrn_scan.frame_id_end' diffrn_scan yes '_diffrn_scan_frame.frame_id' diffrn_scan_frame yes '_diffrn_scan_frame_axis.frame_id' diffrn_scan_frame_axis yes _item_aliases.alias_name '_diffrn_frame_data.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_refln.frame_id' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_start' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_end' '_diffrn_data_frame.id' '_diffrn_scan_frame.frame_id' '_diffrn_data_frame.id' '_diffrn_scan_frame_axis.frame_id' '_diffrn_data_frame.id' save_ ########################################################################## # The following is a restatement of the mmCIF DIFFRN_DETECTOR, # # DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for # # the CBF/imgCIF extensions # ########################################################################## ################### # DIFFRN_DETECTOR # ################### save_DIFFRN_DETECTOR _category.description ; Data items in the DIFFRN_DETECTOR category describe the detector used to measure the scattered radiation, including any analyser and post-sample collimation. ; _category.id diffrn_detector _category.mandatory_code no loop_ _category_key.name '_diffrn_detector.diffrn_id' '_diffrn_detector.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_detector.diffrn_id 'd1' _diffrn_detector.detector 'multiwire' _diffrn_detector.type 'Siemens' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector.details _item_description.description ; A description of special aspects of the radiation detector. ; _item.name '_diffrn_detector.details' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; Need new example here. ; save_ save__diffrn_detector.detector _item_description.description ; The general class of the radiation detector. ; _item.name '_diffrn_detector.detector' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector' cifdic.c91 1.0 '_diffrn_detector' cif_core.dic 2.0 _item_type.code text loop_ _item_examples.case 'photographic film' 'scintillation counter' 'CCD plate' 'BF~3~ counter' save_ save__diffrn_detector.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. The value of _diffrn.id uniquely defines a set of diffraction data. ; _item.name '_diffrn_detector.diffrn_id' _item.mandatory_code yes save_ save__diffrn_detector.dtime _item_description.description ; The deadtime in microseconds of the detectors used to measure the diffraction intensities. ; _item.name '_diffrn_detector.dtime' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector_dtime' cifdic.c91 1.0 '_diffrn_detector_dtime' cif_core.dic 2.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code microseconds save_ save__diffrn_detector.id _item_description.description ; The value of _diffrn_detector.id must uniquely identify each detector used to collect each diffraction data set. If the value of _diffrn_detector.id is not given, it is implicitly equal to the value of _diffrn_detector.diffrn_id ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector.id' diffrn_detector implicit '_diffrn_detector_axis.detector_id' diffrn_detector_axis yes loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_detector_axis.detector_id' '_diffrn_detector.id' _item_type.code code save_ save__diffrn_detector.number_of_axes _item_description.description ; The value of _diffrn_detector.number_of_axes gives the number of axes of the positioner for the detector identified by _diffrn_detector.id The word "positioner" is a general term used in instrumentation design for devices that are used to change the positions of portions of apparatus by linear translation, rotation, or combinations of such motions. Axes which are used to provide a coordinate system for the face of an area detetctor should not be counted for this data item. The description of each axis should be provided by entries in DIFFRN_DETECTOR_AXIS. ; _item.name '_diffrn_detector.number_of_axes' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_detector.type _item_description.description ; The make, model or name of the detector device used. ; _item.name '_diffrn_detector.type' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ ######################## # DIFFRN_DETECTOR_AXIS # ######################## save_DIFFRN_DETECTOR_AXIS _category.description ; Data items in the DIFFRN_DETECTOR_AXIS category associate axes with detectors. ; _category.id diffrn_detector_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_axis.detector_id' '_diffrn_detector_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_detector_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_detector_axis.axis_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_axis.detector_id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. This item was previously named '_diffrn_detector_axis.id' which is now a deprecated name. The old name is provided as an alias, but should not be used for new work. ; _item.name '_diffrn_detector_axis.detector_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_aliases.alias_name '_diffrn_detector_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 save_ ########################### # DIFFRN_DETECTOR_ELEMENT # ########################### save_DIFFRN_DETECTOR_ELEMENT _category.description ; Data items in the DIFFRN_DETECTOR_ELEMENT category record the details about spatial layout and other characteristics of each element of a detector which may have multiple elements. In most cases, the more detailed information provided in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS are preferable to simply providing the centre. ; _category.id diffrn_detector_element _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_element.id' '_diffrn_detector_element.detector_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Detector d1 is composed of four CCD detector elements, each 200 mm by 200 mm, arranged in a square. in the pattern 1 2 * 3 4 Note that the beam center is slightly off of each of the detector elements, just beyond the lower right corner of 1, the lower left corner of 2, the upper right corner of 3 and the upper left corner of 4. ; ; loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id _diffrn_detector_element.center[1] _diffrn_detector_element.center[2] d1 d1_ccd_1 201.5 -1.5 d1 d1_ccd_2 -1.8 -1.5 d1 d1_ccd_3 201.6 201.4 d1 d1_ccd_4 -1.7 201.5 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector_element.center[1] _item_description.description ; The value of _diffrn_detector_element.center[1] is the X component of the distortion-corrected beam-center in mm from the (0, 0) (lower left) corner of the detector element viewed from the sample side. ; _item.name '_diffrn_detector_element.center[1]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.center[2] _item_description.description ; The value of _diffrn_detector_element.center[2] is the Y component of the distortion-corrected beam-center in mm from the (0, 0) (lower left) corner of the detector element viewed from the sample side. ; _item.name '_diffrn_detector_element.center[2]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.id _item_description.description ; The value of _diffrn_detector_element.id must uniquely identify each element of a detector. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector_element.id' diffrn_detector_element yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.detector_element_id' '_diffrn_detector_element.id' save_ save__diffrn_detector_element.detector_id _item_description.description ; This item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. ; _item.name '_diffrn_detector_element.detector_id' _item.category_id diffrn_detector_element _item.mandatory_code yes _item_type.code code save_ ######################## ## DIFFRN_MEASUREMENT ## ######################## save_DIFFRN_MEASUREMENT _category.description ; Data items in the DIFFRN_MEASUREMENT category record details about the device used to orient and/or position the crystal during data measurement and the manner in which the diffraction data were measured. ; _category.id diffrn_measurement _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement.device' '_diffrn_measurement.diffrn_id' '_diffrn_measurement.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_measurement.diffrn_id 'd1' _diffrn_measurement.device '3-circle camera' _diffrn_measurement.device_type 'Supper model x' _diffrn_measurement.device_details 'none' _diffrn_measurement.method 'omega scan' _diffrn_measurement.details ; Need new example here ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991). Acta Cryst. C47, 2276-2277]. ; ; _diffrn_measurement.diffrn_id 's1' _diffrn_measurement.device_type 'Philips PW1100/20 diffractometer' _diffrn_measurement.method 'theta/2theta (\q/2\q)' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_measurement.device _item_description.description ; The general class of goniometer or device used to support and orient the specimen. If the value of _diffrn_measurement.device is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id Either '_diffrn_measurement.device' or '_diffrn_measurement.id' may be used to link to other categories. If the experimental setup admits multiple devices, then '_diffrn_measurement.id' is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.device' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_device' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement.device' _item_aliases.alias_name '_diffrn_measurement_device' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '3-circle camera' '4-circle camera' 'kappa-geometry camera' 'oscillation camera' 'precession camera' save_ save__diffrn_measurement.device_details _item_description.description ; A description of special aspects of the device used to measure the diffraction intensities. ; _item.name '_diffrn_measurement.device_details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; commercial goniometer modified locally to allow for 90\% \t arc ; save_ save__diffrn_measurement.device_type _item_description.description ; The make, model or name of the measurement device (goniometer) used. ; _item.name '_diffrn_measurement.device_type' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Supper model q' 'Huber model r' 'Enraf-Nonius model s' 'homemade' save_ save__diffrn_measurement.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_measurement.diffrn_id' _item.mandatory_code yes save_ save__diffrn_measurement.details _item_description.description ; A description of special aspects of the intensity measurement. ; _item.name '_diffrn_measurement.details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; save_ save__diffrn_measurement.id _item_description.description ; The value of _diffrn_measurement.id must uniquely identify the set of mechanical characteristics of the device used to orient and/or position the sample used during collection of each diffraction data set. If the value of _diffrn_measurement.id is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id Either '_diffrn_measurement.device' or '_diffrn_measurement.id' may be used to link to other categories. If the experimental setup admits multiple devices, then '_diffrn_measurement.id' is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.id' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_id' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement.id' _item_type.code code save_ save__diffrn_measurement.method _item_description.description ; Method used to measure intensities. ; _item.name '_diffrn_measurement.method' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_method' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'profile data from theta/2theta (\q/2\q) scans' save_ save__diffrn_measurement.number_of_axes _item_description.description ; The value of _diffrn_measurement.number_of_axes gives the number of axes of the positioner for the goniometer or other sample orientation or positioning device identified by _diffrn_measurement.id The description of the axes should be provided by entries in DIFFRN_MEASUREMENT_AXIS. ; _item.name '_diffrn_measurement.number_of_axes' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_measurement.specimen_support _item_description.description ; The physical device used to support the crystal during data collection. ; _item.name '_diffrn_measurement.specimen_support' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_specimen_support' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'glass capillary' 'quartz capillary' 'fiber' 'metal loop' save_ ########################### # DIFFRN_MEASUREMENT_AXIS # ########################### save_DIFFRN_MEASUREMENT_AXIS _category.description ; Data items in the DIFFRN_MEASUREMENT_AXIS category associate axes with goniometers. ; _category.id diffrn_measurement_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_measurement_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_measurement_axis.axis_id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.measurement_device _item_description.description ; This data item is a pointer to _diffrn_measurement.device in the DIFFRN_MEASUREMENT category. ; _item.name '_diffrn_measurement_axis.measurement_device' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit save_ save__diffrn_measurement_axis.measurement_id _item_description.description ; This data item is a pointer to _diffrn_measurement.id in the DIFFRN_MEASUREMENT category. This item was previously named '_diffrn_measurement_axis.id' which is now a deprecated name. The old name is provided as an alias, but should not be used for new work. ; _item.name '_diffrn_measurement_axis.measurement_id' _item.category_id diffrn_measurement_axis _item_aliases.alias_name '_diffrn_measurement_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0.00 _item.mandatory_code implicit save_ #################### # DIFFRN_RADIATION # #################### save_DIFFRN_RADIATION _category.description ; Data items in the DIFFRN_RADIATION category describe the radiation used in measuring diffraction intensities, its collimation and monochromatisation before the sample. Post-sample treatment of the beam is described by data items in the DIFFRN_DETECTOR category. ; _category.id diffrn_radiation _category.mandatory_code no _category_key.name '_diffrn_radiation.diffrn_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_radiation.diffrn_id 'set1' _diffrn_radiation.collimation '0.3 mm double pinhole' _diffrn_radiation.monochromator 'graphite' _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.wavelength_id 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991). Acta Cryst. C47, 2276-2277]. ; ; _diffrn_radiation.wavelength_id 1 _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.monochromator 'graphite' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_radiation.collimation _item_description.description ; The collimation or focusing applied to the radiation. ; _item.name '_diffrn_radiation.collimation' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_collimation' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '0.3 mm double-pinhole' '0.5 mm' 'focusing mirrors' save_ save__diffrn_radiation.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_radiation.diffrn_id' _item.mandatory_code yes save_ save__diffrn_radiation.div_x_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory X axis (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the esd of the directions of photons in the X-Z plane around the mean source beam direction. Note that some synchrotrons specify this value in milliradians, in which case a conversion would be needed. To go from a value in milliradians to a value in degrees, multiply by 0.180 and divide by Pi. ; _item.name '_diffrn_radiation.div_x_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.div_y_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory Y axis (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the esd of the directions of photons in the Y-Z plane around the mean source beam direction. Note that some synchrotrons specify this value in milliradians, in which case a conversion would be needed. To go from a value in milliradians to a value in degrees, multiply by 0.180 and divide by Pi. ; _item.name '_diffrn_radiation.div_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.div_x_y_source _item_description.description ; Beam crossfire correlation degrees**2 between the crossfire laboratory X-axis component and the crossfire laboratory Y-axis component (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the mean of the products of the deviations of the directin of each photons in X-Z plane times the deviations of the direction of the same photon in the Y-Z plane around the mean source beam direction. This will be zero for uncorrelated crossfire. Note that some synchrotrons specify this value in milliradians**2, in which case a conversion would be needed. To go from a value in milliradians**2 to a value in degrees**2, multiply by 0.180**2 and divide by Pi**2. ; _item.name '_diffrn_radiation.div_x_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees_squared _item_default.value 0.0 save_ save__diffrn_radiation.filter_edge _item_description.description ; Absorption edge in angstroms of the radiation filter used. ; _item.name '_diffrn_radiation.filter_edge' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_filter_edge' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__diffrn_radiation.inhomogeneity _item_description.description ; Half-width in millimetres of the incident beam in the direction perpendicular to the diffraction plane. ; _item.name '_diffrn_radiation.inhomogeneity' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_inhomogeneity' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code millimetres save_ save__diffrn_radiation.monochromator _item_description.description ; The method used to obtain monochromatic radiation. If a mono- chromator crystal is used the material and the indices of the Bragg reflection are specified. ; _item.name '_diffrn_radiation.monochromator' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_monochromator' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Zr filter' 'Ge 220' 'none' 'equatorial mounted graphite' save_ save__diffrn_radiation.polarisn_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the perpendicular component of the polarisation and the diffraction plane. See _diffrn_radiation_polarisn_ratio. ; _item.name '_diffrn_radiation.polarisn_norm' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_norm' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.polarisn_ratio _item_description.description ; Polarisation ratio of the diffraction beam incident on the crystal. It is the ratio of the perpendicularly polarised to the parallel polarised component of the radiation. The perpendicular component forms an angle of _diffrn_radiation.polarisn_norm to the normal to the diffraction plane of the sample (i.e. the plane containing the incident and reflected beams). ; _item.name '_diffrn_radiation.polarisn_ratio' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_ratio' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__diffrn_radiation.polarizn_source_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the normal to the polarization plane and the laboratory Y axis as defined in the AXIS category. Note that this is the angle of polarization of the source photons, either directly from a synchrotron beamline or from a monchromater. This differs from the value of '_diffrn_radiation.polarisn_norm' in that '_diffrn_radiation.polarisn_norm' refers to polarization relative to the diffraction plane rather than to the laboratory axis system. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane should be taken as the X-Z plane, and the angle as 0. See '_diffrn_radiation.polarizn_source_ratio'. ; _item.name '_diffrn_radiation.polarizn_source_norm' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.polarizn_source_ratio _item_description.description ; (Ip-In)/(Ip+In), where Ip is the intensity (amplitude squared) of the electric vector in the plane of polarization and In is the intensity (amplitude squared) of the electric vector in plane of the normal to the plane of polarization. Thus, if we had complete polarization in the plane of polarization, the value of '_diffrn_radiation.polarizn_source_ratio' would be 1, and an unpolarized beam would have a value of 0. If the X-axis has been chosen to lie in the plane of polarization, this definition will agree with the definition of "MONOCHROMATOR" in the Denzo glossary, and values of near 1 should be expected for a bending magnet source. However, if the X-axis were, for some reason to be, say, perpendicular to the polarization plane (not a common choice), then the Denzo value would be the negative of '_diffrn_radiation.polarizn_source_ratio'. See http://www.hkl-xray.com for information on Denzo, and Z. Otwinowski and W. Minor, " Processing of X-ray Diffraction Data Collected in Oscillation Mode ", Methods in Enzymology, Volume 276: Macromolecular Crystallography, part A, p.307-326, 1997,C.W. Carter, Jr. & R. M. Sweet, Eds., Academic Press. This differs both in the choice of ratio and choice of orientation from '_diffrn_radiation.polarisn_ratio', which, unlike '_diffrn_radiation.polarizn_source_ratio', is unbounded. ; _item.name '_diffrn_radiation.polarizn_source_ratio' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 -1.0 -1.0 -1.0 _item_type.code float save_ save__diffrn_radiation.probe _item_description.description ; Name of the type of radiation used. It is strongly encouraged that this field be specified so that the probe radiation can be simply determined. ; _item.name '_diffrn_radiation.probe' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_probe' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value 'x-ray' 'neutron' 'electron' 'gamma' save_ save__diffrn_radiation.type _item_description.description ; The nature of the radiation. This is typically a description of the X-ray wavelength in Siegbahn notation. ; _item.name '_diffrn_radiation.type' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'CuK\a' 'Cu K\a~1~' 'Cu K-L~2,3~' 'white-beam' save_ save__diffrn_radiation.xray_symbol _item_description.description ; The IUPAC symbol for the X-ray wavelength for probe radiation. ; _item.name '_diffrn_radiation.xray_symbol' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_xray_symbol' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value _item_enumeration.detail 'K-L~3~' 'K\a~1~ in older Siegbahn notation' 'K-L~2~' 'K\a~2~ in older Siegbahn notation' 'K-M~3~' 'K\b~1~ in older Siegbahn notation' 'K-L~2,3~' 'use where K-L~3~ and K-L~2~ are not resolved' save_ save__diffrn_radiation.wavelength_id _item_description.description ; This data item is a pointer to _diffrn_radiation_wavelength.id in the DIFFRN_RADIATION_WAVELENGTH category. ; _item.name '_diffrn_radiation.wavelength_id' _item.mandatory_code yes save_ ################ # DIFFRN_REFLN # ################ save_DIFFRN_REFLN _category.description ; This category redefinition has been added to extend the key of the standard DIFFRN_REFLN category. ; _category.id diffrn_refln _category.mandatory_code no _category_key.name '_diffrn_refln.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_refln.frame_id _item_description.description ; This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_refln.frame_id' _item.category_id diffrn_refln _item.mandatory_code yes _item_type.code code save_ ############### # DIFFRN_SCAN # ############### save_DIFFRN_SCAN _category.description ; Data items in the DIFFRN_SCAN category describe the parameters of one or more scans, relating axis positions to frames. ; _category.id diffrn_scan _category.mandatory_code no _category_key.name '_diffrn_scan.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - derived from a suggestion by R. M. Sweet. The vector of each axis is not given here, because it is provided in the AXIS category. By making _diffrn_scan_axis.scan_id and _diffrn_scan_axis.axis_id keys of the DIFFRN_SCAN_AXIS category, an arbitrary number of scanning and fixed axes can be specified for a scan. We have specified three rotation axes and one translation axis at non-zero values, with one axis stepping. There is no reason why more axes could not have been specified to step. We have specified range information, but note that it is redundant from the number of frames and the increment, so we could drop the data item _diffrn_scan_axis.angle_range . We have specified both the sweep data and the data for a single frame. Note that the information on how the axes are stepped is given twice, once in terms of the overall averages in the value of '_diffrn_scan.integration_time' and the values for DIFFRN_SCAN_AXIS, and precisely for the given frame in the value for '_diffrn_scan_frame.integration_time' and the values for DIFFRN_SCAN_FRAME_AXIS. If dose-related adjustements are made to scan times and non-linear stepping is done, these values may differ. Therefore, in interpreting the data for a particular frame it is important to use the frame-specific data. ; ; _diffrn_scan.id 1 _diffrn_scan.date_start '2001-11-18T03:26:42' _diffrn_scan.date_end '2001-11-18T03:36:45' _diffrn_scan.integration_time 3.0 _diffrn_scan.frame_id_start mad_L2_000 _diffrn_scan.frame_id_end mad_L2_200 _diffrn_scan.frames 201 loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment 1 omega 200.0 20.0 0.1 . . . 1 kappa -40.0 0.0 0.0 . . . 1 phi 127.5 0.0 0.0 . . . 1 tranz . . . 2.3 0.0 0.0 _diffrn_scan_frame.scan_id 1 _diffrn_scan_frame.date '2001-11-18T03:27:33' _diffrn_scan_frame.integration_time 3.0 _diffrn_scan_frame.frame_id mad_L2_018 _diffrn_scan_frame.frame_number 18 loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.angle_increment _diffrn_scan_frame_axis.displacement _diffrn_scan_frame_axis.displacement_increment mad_L2_018 omega 201.8 0.1 . . mad_L2_018 kappa -40.0 0.0 . . mad_L2_018 phi 127.5 0.0 . . mad_L2_018 tranz . . 2.3 0.0 ; ; Example 2 - a more extensive example, R. M. Sweet, P. Ellis, H. Bernstein. We place a detector 240 mm along the Z axis from the goniometer. This presents us with a choice -- either we define the axes of the detector at the origin, and then put a Z setting of -240 in for the actual use, or we define the axes with the necessary Z-offset. In this case we use the setting, and leave the offset as zero. We call this axis DETECTOR_Z. The axis for positioning the detector in the Y-direction depends on the detector Z-axis. We call this axis, DETECTOR_Y. The axis for positioning the dector in the X-direction depends on the detector Y-axis (and therefore on the detector Z-axis). We call this axis DETECTOR_X. This detector may be rotated around the Y-axis. This rotation axis depends on the three translation axies. We call it DETECTOR_PITCH. We define a coordinate system on the face of the detector in terms of 2300 0.150 mm pixels in each direction. The ELEMENT_X axis is used to index the first array index of the data array and the ELEMENT_Y axis is used to index the second array index. Because the pixels are 0.150mm x 0.150mm, the center of the first pixel is at (0.075, 0.075) in this coordinate system. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 172.43 -172.43 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 2300 1 increasing ELEMENT_X ARRAY1 2 2300 2 increasing ELEMENT_Y # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.075 0.150 ELEMENT_Y ELEMENT_Y 0.075 0.150 # category ARRAY_ELEMENT_SIZE loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 ARRAY1 2 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; ; Example 3 - Example 2 revised for a spiral scan, R. M. Sweet, P. Ellis, H. Bernstein. We place a detector 240 mm along the Z axis from the goniometer, as in Example 2, above, but in this example, the image plate is scanned in a spiral pattern outside edge in. The axis for positioning the detector in the Y-direction depends on the detector Z-axis. We call this axis, DETECTOR_Y. The axis for positioning the dector in the X-direction depends on the detector Y-axis (and therefore on the detector Z-axis). We call this axis DETECTOR_X. This detector may be rotated around the Y-axis. This rotation axis depends on the three translation axies. We call it DETECTOR_PITCH. We define a coordinate system on the face of the detector in terms of a coupled rotation axis and radial scan axis to form a spiral scan. Let us call rotation axis ELEMENT_ROT, and the radial axis ELEMENT_RAD. We assume 150 um radial pitch and 75 um 'constant velocity' angular pitch. We index first on the rotation axis and make the radial axis dependent on it. The two axes are coupled to form an axis set ELEMENT_SPIRAL. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_ROT translation detector DETECTOR_PITCH 0 0 1 0 0 0 ELEMENT_RAD translation detector ELEMENT_ROT 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.angle _array_structure_list_axis.displacement _array_structure_list_axis.angular_pitch _array_structure_list_axis.radial_pitch ELEMENT_SPIRAL ELEMENT_ROT 0 . 0.075 . ELEMENT_SPIRAL ELEMENT_RAD . 172.5 . -0.150 # category ARRAY_ELEMENT_SIZE # the actual pixels are 0.075 by 0.150 mm # We give the coarser dimension here. loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_scan.id _item_description.description ; The value of _diffrn_scan.id uniquely identifies each scan. The identifier is used to tie together all the information about the scan. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_scan.id' diffrn_scan yes '_diffrn_scan_axis.scan_id' diffrn_scan_axis yes '_diffrn_scan_frame.scan_id' diffrn_scan_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_scan_axis.scan_id' '_diffrn_scan.id' '_diffrn_scan_frame.scan_id' '_diffrn_scan.id' save_ save__diffrn_scan.date_end _item_description.description ; The date and time of the end of the scan. Note that this may be an estimate generated during the scan, before the precise time of the end of the scan is known. ; _item.name '_diffrn_scan.date_end' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.date_start _item_description.description ; The date and time of the start of the scan. ; _item.name '_diffrn_scan.date_start' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.integration_time _item_description.description ; Approximate average time in seconds to integrate each step of the scan. The precise time for integration of each particular step must be provided in '_diffrn_scan_frame.integration_time', even if all steps have the same integration time. ; _item.name '_diffrn_scan.integration_time' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan.frame_id_start _item_description.description ; The value of this data item is the identifier of the first frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_start' _item.category_id diffrn_scan _item.mandatory_code yes save_ save__diffrn_scan.frame_id_end _item_description.description ; The value of this data item is the identifier of the last frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_end' _item.category_id diffrn_scan _item.mandatory_code yes save_ save__diffrn_scan.frames _item_description.description ; The value of this data item is the number of frames in the scan. ; _item.name '_diffrn_scan.frames' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 1 1 1 save_ #################### # DIFFRN_SCAN_AXIS # #################### save_DIFFRN_SCAN_AXIS _category.description ; Data items in the DIFFRN_SCAN_AXIS category describe the settings of axes for particular scans. Unspecified axes are assumed to be at their zero points. ; _category.id diffrn_scan_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_axis.scan_id' '_diffrn_scan_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_axis.scan_id _item_description.description ; The value of this data item is the identifier of the scan for which axis settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan.id'. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_axis.scan_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes save_ save__diffrn_scan_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the scan for which settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan.id'. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_axis.axis_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes save_ save__diffrn_scan_axis.angle_start _item_description.description ; The starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_range _item_description.description ; The range from the starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_increment _item_description.description ; The increment for each step for the specified axis in degrees. In general, this will agree with '_array_structure_list_axis.angle_increment', which see for a precise description. ; _item.name '_diffrn_scan_axis.angle_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_rstrt_incr _item_description.description ; The increment after each step for the specified axis in degrees. In general, this will agree with '_array_structure_list_axis.angle_increment', which see for a precise description. ; _item.name '_diffrn_scan_axis.angle_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.displacement_start _item_description.description ; The starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_range _item_description.description ; The range from the starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_increment _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with '_diffrn_scan_frame_axis.displacement_increment', which see for a precise description. ; _item.name '_diffrn_scan_axis.displacement_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_rstrt_incr _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with '_diffrn_scan_frame_axis.displacement_rstrt_incr', which see for a precise description. ; _item.name '_diffrn_scan_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ ##################### # DIFFRN_SCAN_FRAME # ##################### save_DIFFRN_SCAN_FRAME _category.description ; Data items in the DIFFRN_SCAN_FRAME category describe the settings of axes for particular frames. Unspecified axes are assumed to be at their zero points. ; _category.id diffrn_scan_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame.scan_id' '_diffrn_scan_frame.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame.date _item_description.description ; The date and time of the start of the frame being scanned. ; _item.name '_diffrn_scan_frame.date' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan_frame.frame_id _item_description.description ; The value of this data item is the identifier of the frame being examined. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame.frame_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes save_ save__diffrn_scan_frame.frame_number _item_description.description ; The value of this data item is the number of the frame within the scan, starting with 1. It is not necessarily the same as the value of _diffrn_scan_frame.frame_id, but may be. ; _item.name '_diffrn_scan_frame.frame_number' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 0 0 0 save_ save__diffrn_scan_frame.integration_time _item_description.description ; The time in seconds to integrate this step of the scan. This should be the precise time of integration of each particular frame. The value of this data item should be given explicitly for each frame and not inferred from the value of '_diffrn_scan.integration_time'. ; _item.name '_diffrn_scan_frame.integration_time' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame.scan_id _item_description.description ; The value of _diffrn_scan_frame.scan_id identifies the scan containing this frame. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_frame.scan_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes save_ ########################## # DIFFRN_SCAN_FRAME_AXIS # ########################## save_DIFFRN_SCAN_FRAME_AXIS _category.description ; Data items in the DIFFRN_SCAN_FRAME_AXIS category describes the settings of axes for particular frames. Unspecified axes are assumed to be at their zero points. If, for any given frame, non-zero values apply for any of the data items in this category, those values should be given explicitly in this category and not simply inferred from values in DIFFRN_SCAN_AXIS. ; _category.id diffrn_scan_frame_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame_axis.frame_id' '_diffrn_scan_frame_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the frame for which settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_frame_axis.axis_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes save_ save__diffrn_scan_frame_axis.angle _item_description.description ; The setting of the specified axis in degrees for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.angle' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_increment _item_description.description ; The increment for this frame for angular setting of the specified axis in degrees. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.angle_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_rstrt_incr _item_description.description ; The increment after this frame for angular setting of the specified axis in degrees. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' and '_diffrn_scan_frame_axis.angle_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame, and should equal '_diffrn_scan_frame_axis.angle' for that next frame. ; _item.name '_diffrn_scan_frame_axis.angle_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.displacement' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_increment _item_description.description ; The increment for this frame for displacement setting of the specified axis in millimetres. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.displacement_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_rstrt_incr _item_description.description ; The increment for this frame for displacement setting of the specified axis in millimetres. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' and '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame, and should equal '_diffrn_scan_frame_axis.displacement' for that next frame. ; _item.name '_diffrn_scan_frame_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.frame_id _item_description.description ; The value of this data item is the identifier of the frame for which axis settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id . This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame_axis.frame_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes save_ #################### ## ITEM_TYPE_LIST ## #################### # # # The regular expressions defined here are not compliant # with the POSIX 1003.2 standard as they include the # '\n' and '\t' special characters. These regular expressions # have been tested using version 0.12 of Richard Stallman's # GNU regular expression library in POSIX mode. # In order to allow presentation of a regular expression # in a text field concatenate any line ending in a backslash # with the following line, after discarding the backslash. # # A formal definition of the '\n' and '\t' special characters # is most properly done in the DDL, but for completeness, please # note that '\n' is the line termination character ('newline') # and '\t' is the horizontal tab character. There is a formal # ambiguity in the use of '\n' for line termination, in that # the intention is that the equivalent machine/OS-dependent line # termination character sequence should be accepted as a match, e.g. # # '\r' (control-M) under MacOS # '\n' (control-J) under Unix # '\r\n' (control-M control-J) under DOS and MS Windows # loop_ _item_type_list.code _item_type_list.primitive_code _item_type_list.construct _item_type_list.detail code char '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words ... ; ucode uchar '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words (case insensitive) ; line char '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types / multi-word items ... ; uline uchar '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types / multi-word items (case insensitive) ; text char '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; text item types / multi-line text ... ; binary char ;\n--CIF-BINARY-FORMAT-SECTION--\n\ [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*}\ \n--CIF-BINARY-FORMAT-SECTION---- ; ; binary items are presented as MIME-like ascii-encoded sections in an imgCIF. In a CBF, raw octet streams are used to convey the same information. ; int numb '-?[0-9]+' ; int item types are the subset of numbers that are the negative or positive integers. ; float numb '-?(([0-9]+)|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?' ; float item types are the subset of numbers that are the floating numbers. ; any char '.*' ; A catch all for items that may take any form... ; yyyy-mm-dd char ;\ [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9][0-9]\ (T[0-2][0-9]:[0-5][0-9]:[0-5][0-9](.[0-9]+)([+-][0-5][0-9]:[0-5][0-9])) ; ; Standard format for CIF date and time strings (see http://www.iucr.orgiucr-top/cif/spec/datetime.html), consisting of a yyyy-mm-dd date optionally followed by the character "T" followed by a 24-hour clock time, optionally followed by a signed time-zone offset. The IUCr standard has been extended to allow for an optional deciaml fraction on the seconds of time. Time is local time if no time-zone offset is given. ; ##################### ## ITEM_UNITS_LIST ## ##################### loop_ _item_units_list.code _item_units_list.detail # 'metres' 'metres' 'centimetres' 'centimetres (metres * 10^( -2))' 'millimetres' 'millimetres (metres * 10^( -3))' 'nanometres' 'nanometres (metres * 10^( -9))' 'angstroms' 'angstroms (metres * 10^(-10))' 'picometres' 'picometres (metres * 10^(-12))' 'femtometres' 'femtometres (metres * 10^(-15))' # 'reciprocal_metres' 'reciprocal metres (metres * 10^-1)' 'reciprocal_centimetres' 'reciprocal centimetres (metres * 10^( -2)^-1)' 'reciprocal_millimetres' 'reciprocal millimetres (metres * 10^( -3)^-1)' 'reciprocal_nanometres' 'reciprocal nanometres (metres * 10^( -9)^-1)' 'reciprocal_angstroms' 'reciprocal angstroms (metres * 10^(-10)^-1)' 'reciprocal_picometres' 'reciprocal picometres (metres * 10^(-12)^-1)' # 'nanometres_squared' 'nanometres squared (metres * 10^( -9))^2' 'angstroms_squared' 'angstroms squared (metres * 10^(-10))^2' '8pi2_angstroms_squared' '8pi^2 * angstroms squared (metres * 10^(-10))^2' 'picometres_squared' 'picometres squared (metres * 10^(-12))^2' # 'nanometres_cubed' 'nanometres cubed (metres * 10^( -9))^3' 'angstroms_cubed' 'angstroms cubed (metres * 10^(-10))^3' 'picometres_cubed' 'picometres cubed (metres * 10^(-12))^3' # 'kilopascals' 'kilopascals' 'gigapascals' 'gigapascals' # 'hours' 'hours' 'minutes' 'minutes' 'seconds' 'seconds' 'microseconds' 'microseconds' # 'degrees' 'degrees (of arc)' 'degrees_squared' 'degrees (of arc) squared' # 'degrees_per_minute' 'degrees (of arc) per minute' # 'celsius' 'degrees (of temperature) Celsius' 'kelvins' 'degrees (of temperature) Kelvin' # 'counts' 'counts' 'counts_per_photon' 'counts per photon' # 'electrons' 'electrons' # 'electrons_squared' 'electrons squared' # 'electrons_per_nanometres_cubed' ; electrons per nanometres cubed (metres * 10^( -9))^3 ; 'electrons_per_angstroms_cubed' ; electrons per angstroms cubed (metres * 10^(-10))^3 ; 'electrons_per_picometres_cubed' ; electrons per picometres cubed (metres * 10^(-12))^3 ; 'kilowatts' 'kilowatts' 'milliamperes' 'milliamperes' 'kilovolts' 'kilovolts' # 'arbitrary' ; arbitrary system of units. ; # loop_ _item_units_conversion.from_code _item_units_conversion.to_code _item_units_conversion.operator _item_units_conversion.factor ### 'metres' 'centimetres' '*' 1.0E+02 'metres' 'millimetres' '*' 1.0E+03 'metres' 'nanometres' '*' 1.0E+09 'metres' 'angstroms' '*' 1.0E+10 'metres' 'picometres' '*' 1.0E+12 'metres' 'femtometres' '*' 1.0E+15 # 'centimetres' 'metres' '*' 1.0E-02 'centimetres' 'millimetres' '*' 1.0E+01 'centimetres' 'nanometres' '*' 1.0E+07 'centimetres' 'angstroms' '*' 1.0E+08 'centimetres' 'picometres' '*' 1.0E+10 'centimetres' 'femtometres' '*' 1.0E+13 # 'millimetres' 'metres' '*' 1.0E-03 'millimetres' 'centimetres' '*' 1.0E-01 'millimetres' 'nanometres' '*' 1.0E+06 'millimetres' 'angstroms' '*' 1.0E+07 'millimetres' 'picometres' '*' 1.0E+09 'millimetres' 'femtometres' '*' 1.0E+12 # 'nanometres' 'metres' '*' 1.0E-09 'nanometres' 'centimetres' '*' 1.0E-07 'nanometres' 'millimetres' '*' 1.0E-06 'nanometres' 'angstroms' '*' 1.0E+01 'nanometres' 'picometres' '*' 1.0E+03 'nanometres' 'femtometres' '*' 1.0E+06 # 'angstroms' 'metres' '*' 1.0E-10 'angstroms' 'centimetres' '*' 1.0E-08 'angstroms' 'millimetres' '*' 1.0E-07 'angstroms' 'nanometres' '*' 1.0E-01 'angstroms' 'picometres' '*' 1.0E+02 'angstroms' 'femtometres' '*' 1.0E+05 # 'picometres' 'metres' '*' 1.0E-12 'picometres' 'centimetres' '*' 1.0E-10 'picometres' 'millimetres' '*' 1.0E-09 'picometres' 'nanometres' '*' 1.0E-03 'picometres' 'angstroms' '*' 1.0E-02 'picometres' 'femtometres' '*' 1.0E+03 # 'femtometres' 'metres' '*' 1.0E-15 'femtometres' 'centimetres' '*' 1.0E-13 'femtometres' 'millimetres' '*' 1.0E-12 'femtometres' 'nanometres' '*' 1.0E-06 'femtometres' 'angstroms' '*' 1.0E-05 'femtometres' 'picometres' '*' 1.0E-03 ### 'reciprocal_centimetres' 'reciprocal_metres' '*' 1.0E+02 'reciprocal_centimetres' 'reciprocal_millimetres' '*' 1.0E-01 'reciprocal_centimetres' 'reciprocal_nanometres' '*' 1.0E-07 'reciprocal_centimetres' 'reciprocal_angstroms' '*' 1.0E-08 'reciprocal_centimetres' 'reciprocal_picometres' '*' 1.0E-10 # 'reciprocal_millimetres' 'reciprocal_metres' '*' 1.0E+03 'reciprocal_millimetres' 'reciprocal_centimetres' '*' 1.0E+01 'reciprocal_millimetres' 'reciprocal_nanometres' '*' 1.0E-06 'reciprocal_millimetres' 'reciprocal_angstroms' '*' 1.0E-07 'reciprocal_millimetres' 'reciprocal_picometres' '*' 1.0E-09 # 'reciprocal_nanometres' 'reciprocal_metres' '*' 1.0E+09 'reciprocal_nanometres' 'reciprocal_centimetres' '*' 1.0E+07 'reciprocal_nanometres' 'reciprocal_millimetres' '*' 1.0E+06 'reciprocal_nanometres' 'reciprocal_angstroms' '*' 1.0E-01 'reciprocal_nanometres' 'reciprocal_picometres' '*' 1.0E-03 # 'reciprocal_angstroms' 'reciprocal_metres' '*' 1.0E+10 'reciprocal_angstroms' 'reciprocal_centimetres' '*' 1.0E+08 'reciprocal_angstroms' 'reciprocal_millimetres' '*' 1.0E+07 'reciprocal_angstroms' 'reciprocal_nanometres' '*' 1.0E+01 'reciprocal_angstroms' 'reciprocal_picometres' '*' 1.0E-02 # 'reciprocal_picometres' 'reciprocal_metres' '*' 1.0E+12 'reciprocal_picometres' 'reciprocal_centimetres' '*' 1.0E+10 'reciprocal_picometres' 'reciprocal_millimetres' '*' 1.0E+09 'reciprocal_picometres' 'reciprocal_nanometres' '*' 1.0E+03 'reciprocal_picometres' 'reciprocal_angstroms' '*' 1.0E+01 ### 'nanometres_squared' 'angstroms_squared' '*' 1.0E+02 'nanometres_squared' 'picometres_squared' '*' 1.0E+06 # 'angstroms_squared' 'nanometres_squared' '*' 1.0E-02 'angstroms_squared' 'picometres_squared' '*' 1.0E+04 'angstroms_squared' '8pi2_angstroms_squared' '*' 78.9568 # 'picometres_squared' 'nanometres_squared' '*' 1.0E-06 'picometres_squared' 'angstroms_squared' '*' 1.0E-04 ### 'nanometres_cubed' 'angstroms_cubed' '*' 1.0E+03 'nanometres_cubed' 'picometres_cubed' '*' 1.0E+09 # 'angstroms_cubed' 'nanometres_cubed' '*' 1.0E-03 'angstroms_cubed' 'picometres_cubed' '*' 1.0E+06 # 'picometres_cubed' 'nanometres_cubed' '*' 1.0E-09 'picometres_cubed' 'angstroms_cubed' '*' 1.0E-06 ### 'kilopascals' 'gigapascals' '*' 1.0E-06 'gigapascals' 'kilopascals' '*' 1.0E+06 ### 'hours' 'minutes' '*' 6.0E+01 'hours' 'seconds' '*' 3.6E+03 'hours' 'microseconds' '*' 3.6E+09 # 'minutes' 'hours' '/' 6.0E+01 'minutes' 'seconds' '*' 6.0E+01 'minutes' 'microseconds' '*' 6.0E+07 # 'seconds' 'hours' '/' 3.6E+03 'seconds' 'minutes' '/' 6.0E+01 'seconds' 'microseconds' '*' 1.0E+06 # 'microseconds' 'hours' '/' 3.6E+09 'microseconds' 'minutes' '/' 6.0E+07 'microseconds' 'seconds' '/' 1.0E+06 ### 'celsius' 'kelvins' '-' 273.0 'kelvins' 'celsius' '+' 273.0 ### 'electrons_per_nanometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E-03 'electrons_per_nanometres_cubed' 'electrons_per_picometres_cubed' '*' 1.0E-09 # 'electrons_per_angstroms_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E+03 'electrons_per_angstroms_cubed' 'electrons_per_picometres_cubed' '*' 1.0E-06 # 'electrons_per_picometres_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E+09 'electrons_per_picometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E+06 ### ######################## ## DICTIONARY_HISTORY ## ######################## loop_ _dictionary_history.version _dictionary_history.update _dictionary_history.revision 1.1.3 2001-04-19 ; Another typo corrections by Wilfred Li, and cleanup by HJB ; 1.1.2 2001-03-06 ; Several typo corrections by Wilfred Li ; 1.1.1 2001-02-16 ; Several typo corrections by JW ; 1.1 2001-02-06 ; Draft resulting from discussions on header for use at NSLS (HJB) + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'. + Add '_diffrn_measurement_axis.measurement_device' and change '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'. + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source', '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm' , '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end', '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr', '_diffrn_scan_axis.displacement_rstrt_incr', '_diffrn_scan_frame_axis.angle_increment', '_diffrn_scan_frame_axis.angle_rstrt_incr', '_diffrn_scan_frame_axis.displacement', '_diffrn_scan_frame_axis.displacement_increment',and '_diffrn_scan_frame_axis.displacement_rstrt_incr'. + Add _diffrn_measurement.device to category key + Update yyyy-mm-dd to allow optional time with fractional seconds for time stamps. + Fix typos caught by RS. + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to al low for coupled axes, as in spiral scans. + Add examples for fairly complete headers thanks to R. Sweet and P. Ellis. ; 1.0 2000-12-21 ; Release version - few typos and tidying up (BM & HJB) + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end of dictionary. + Alphabetize dictionary. ; 0.7.1 2000-09-29 ; Cleanup fixes (JW) + Correct spelling of diffrn_measurement_axis in _axis.id + Correct ordering of uses of _item.mandatory_code and _item_default.value ; 0.7.0 2000-09-09 ; Respond to comments by I. David Brown (HJB) + Added further comments on '\n' and '\t' + Updated ITEM_UNITS_LIST by taking section from mmCIF dictionary and adding metres. Changed all spelling 'meter' to 'metre' throughout. + Added missing enumerations to _array_structure.compression_type and made 'none' the default. + Removed parent-child relationship between _array_structure_list.index and _array_structure_list.precedence . + Improve alphabetization. + Fix _array_intensities_gain.esd related function. + Improved comments in AXIS. + Fixed DIFFRN_FRAME_DATA example. + Removed erroneous DIFFRN_MEASUREMENT example. + Added _diffrn_measurement_axis.id to the category key. ; 0.6.0 1999-01-14 ; Remove redundant information for ENC_NONE data (HJB) + After the D5 remove binary section identifier, size and compression type. + Add Control-L to header. ; 0.5.1 1999-01-03 ; Cleanup of typos and syntax errors (HJB) + Cleanup example details for DIFFRN_SCAN category. + Add missing quote marks for _diffrn_scan.id definition. ; 0.5 1999-01-01 ; Modifications for axis definitions and reduction of binary header (HJB) + Restored _diffrn_detector.diffrn_id to DIFFRN_DETECTOR KEY. + Added AXIS category. + Brought complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories in from cif_mm.dic for clarity. + changed _array_structure.encoding_type from type code to uline and added X-Binary-Element-Type to MIME header. + added detector beam center _diffrn_detector_element.center[1] and _diffrn_detector_element.center[2] + corrected item name of _diffrn_refln.frame_id + replace reference to _array_intensities.undefined by _array_intensities.undefined_value + replace references to _array_intensity.scaling with _array_intensities.scaling + added DIFFRN_SCAN... categories ; 0.4 1998-08-11 ; Modifications to the 0.3 imgCIF draft (HJB) + Reflowed comment lines over 80 characters and corrected typos. + Updated examples and descriptions of MIME encoded data. + Change name to cbfext98.dic. ; 0.3 1998-07-04 ; Modifications for imgCIF (HJB) + Added binary type, which is a text field containing a variant on MIME encoded data. + Changed type of _array_data.data to binary and specified internal structure of raw binary data. + Added _array_data.binary_id, and made _diffrn_frame_data.binary_id and _array_intensities.binary_id into pointers to this item. ; 0.2 1997-12-02 ; Modifications to the CBF draft (JW): + Added category hierarchy for describing frame data developed from discussions at the BNL imgCIF Workshop Oct 1997. The following changes were made in implementing the workshop draft. Category DIFFRN_ARRAY_DATA was renamed to DIFFRN_FRAME_DATA. Category DIFFRN_FRAME_TYPE was renamed to DIFFRN_DETECTOR_ELEMENT. The parent item for _diffrn_frame_data.array_id was changed from array_structure_list.array_id to array_structure.id. Item _diffrn_detector.array_id was deleted. + Added data item _diffrn_frame_data.binary_id to identify data groups within a binary section. The formal identification of the binary section is still fuzzy. ; 0.1 1997-01-24 ; First draft of this dictionary in DDL 2.1 compliant format by John Westbrook (JW). This version was adapted from the Crystallographic Binary File (CBF) Format Draft Proposal provided by Andy Hammersley (AH). Modifications to the CBF draft (JW): + In this version the array description has been cast in the categories ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. These categories have been generalized to describe array data of arbitrary dimension. + Array data in this description are contained in the category ARRAY_DATA . This departs from the CBF notion of data existing in some special comment. In this description, data is handled as an ordinary data item encapsulated in a character data type. Although handling binary data this manner deviates from CIF conventions, it does not violate any DDL 2.1 rules. DDL 2.1 regular expressions can be used to define the binary representation which will permit some level of data validation. In this version, the placeholder type code "any" has been used. This translates to a regular expression which will match any pattern. It should be noted that DDL 2.1 already supports array data objects although these have not been used in the current mmCIF dictionary. It may be possible to use the DDL 2.1 ITEM_STRUCTURE and ITEM_STRUCTURE_LIST categories to provide the information that is carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. By moving the array structure to the DDL level it would be possible to define an array type as well as a regular expression defining the data format. + Multiple array sections can be properly handled within a single datablock. ; #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof ./CBFlib-0.9.2.2/doc/Carray_structure_list.html0000644000076500007650000000707411603702115017635 0ustar yayayaya (IUCr) CIF Definition save_array_structure_list

DRAFT DICTIONARY

CBF/imgCIF Extensions Dictionary

Draft version 1.5 for comment


[IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


Index

Image dictionary (imgCIF) version 1.5.4

Category ARRAY_STRUCTURE_LIST

Name:
'array_structure_list'

Description:

    Data items in the ARRAY_STRUCTURE_LIST category record the size
     and organization of each array dimension.

     The relationship to physical axes may be given.

Example:

Example 1 - An image array of 1300 x 1200 elements. The raster order of the image is left to right (increasing) in the first dimension and bottom to top (decreasing) in the second dimension.
 
        loop_
       _array_structure_list.array_id
       _array_structure_list.index
       _array_structure_list.dimension
       _array_structure_list.precedence
       _array_structure_list.direction
       _array_structure_list.axis_set_id
        image_1   1    1300    1     increasing  ELEMENT_X
        image_1   2    1200    2     decreasing  ELEMENY_Y



Category groups:
    inclusive_group
    array_data_group
Category keys:
    _array_structure_list.array_id
    _array_structure_list.index

Mandatory category: no

HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

./CBFlib-0.9.2.2/doc/CBFlib.html0000644000076500007650000135242511603702115014326 0ustar yayayaya CBFlib Manual [IUCr Home Page] [CIF Home Page] [CBF/imgCIF]
| IUCr Home Page | CIF Home Page | CBF/imgCIF | CBFlib |
| NOTICE | GPL | LGPL | imgCIF dictionary |
| Click Here to Make a Donation |

CBFlib

An API for CBF/imgCIF
Crystallographic Binary Files with ASCII Support

Version 0.9.2
12 February 2011

by
Paul J. Ellis
Stanford Synchrotron Radiation Laboratory

and
Herbert J. Bernstein
Bernstein + Sons

© Copyright 2006, 2007, 2008, 2011 Herbert J. Bernstein


YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL.

ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS OF THE LGPL.


Before using this software, please read the
NOTICE
for important disclaimers and the IUCr Policy on the Use of the Crystallographic Information File (CIF) and for other important information.

Work on imgCIF and CBFlib supported in part by the U. S. Department of Energy (DOE) under grants ER63601-1021466-0009501 and ER64212-1027708-0011962, by the U. S. National Science Foundation (NSF) under grants DBI-0610407, DBI-0315281 and EF-0312612, the U. S. National Institutes of Health (NIH) under grants 1R15GM078077 from NIGMS and 1R13RR023192 from NCRR and funding from the International Union for Crystallographyn (IUCr). The content is solely the responsibility of the authors and does not necessarily represent the official views of DOE, NSF, NIH, NIGMS, NCRR or IUCr.


Version History

Version DateByDescription
  0.1  Apr. 1998   PJE   This was the first CBFlib release. It supported binary CBF files using binary strings.
  0.2   Aug. 1998   HJB  This release added ascii imgCIF support using MIME-encoded binary sections, added the option of MIME headers for the binary strings was well. MIME code adapted from mpack 1.5. Added hooks needed for DDL1-style names without categories.
  0.3   Sep. 1998   PJE  This release cleaned up the changes made for version 0.2, allowing multi-threaded use of the code, and removing dependence on the mpack package.
  0.4   Nov. 1998   HJB   This release merged much of the message digest code into the general file reading and writing to reduce the number of passes. More consistency checking between the MIME header and the binary header was introduced. The size in the MIME header was adjusted to agree with the version 0.2 documentation.
  0.5   Dec. 1998   PJE  This release greatly increased the speed of processing by allowing for deferred digest evaluation.
  0.6   Jan. 1999   HJB   This release removed the redundant information (binary id, size, compression id) from a binary header when there is a MIME header, removed the unused repeat argument, and made the memory allocation for buffering and tables with many rows sensitive to the current memory allocation already used.
  0.6.1   Feb. 2001   HP (per HJB)   This release fixed a memory leak due to misallocation by size of cbf_handle instead of cbf_handle_struct
  0.7   Mar. 2001   PJE   This release added high-level instructions based on the imgCIF dictionary version 1.1.
  0.7.1   Mar. 2001   PJE   The high-level functions were revised to permit future expansion to files with multiple images.
  0.7.2   Apr. 2001   HJB   This release adjusted cbf_cimple.c to conform to cif_img.dic version 1.1.3
  0.7.2.1   May 2001   PJE   This release corrected an if nesting error in the prior mod to cbf_cimple.c.
  0.7.3   Oct. 2002   PJE   This release modified cbf_simple.c to reorder image data on read so that the indices are always increasing in memory (this behavior was undefined previously).
  0.7.4   Jan 2004   HJB   This release fixes a parse error for quoted strings, adds code to get and set character string types, and removes compiler warnings
  0.7.5   Apr 2006   HJB   This release cleans up some compiler warnings, corrects a parse error on quoted strings with a leading blank as adds the new routines for support of aliases, dictionaries and real arrays, higher level routines to get and set pixel sizes, do cell computations, and to set beam centers, improves support for conversion of images, picking up more data from headers.
  0.7.6   Jul 2006   HJB   This release reorganizes the kit into two pieces: CBFlib_0.7.6_Data_Files and CBFlib_0.7.6. An optional local copy of getopt is added. The 1.4 draft dictionary has been added. cif2cbf updated to support vcif2 validation. convert_image and cif2cbf updated to report text of error messages. convert_image updated to support tag and category aliases, default to adxv images. convert_image and img updated to support row-major images. Support added for binning. API Support added for validation, wide files and line folding. Logic changed for beam center reporting. Added new routines: cbf_validate, cbf_get_bin_sizes, cbf_set_bin_sizes, cbf_find_last_typed_child, cbf_compose_itemname, cbf_set_cbf_logfile, cbf_make_widefile, cbf_read_anyfile, cbf_read_widefile, cbf_write_local_file, cbf_write_widefile, cbf_column_number, cbf_blockitem_number, cbf_log, cbf_check_category_tags, cbf_set_beam_center
  0.7.7   February 2007   HJB   This release reflects changes for base 32K support developed by G. Darakev, and changes for support of reals, 3d arrays, byte_offset compression and J. P. Abrahams packed compression made in consultation with (in alphabetic order) E. Eikenberry, A. Hammerley, W. Kabsch, M. Kobas, J. Wright and others at PSI and ESRF in January 2007, as well accumulated changes fixing problems in release 0.7.6.
  0.7.7.1   February 2007   HJB   This release is a patch to 0.7.7 to change the treatment of the byteorder parameter from strcpy semantics to return of a pointer to a string constant. Our thanks to E. Eikenberry for pointing out the problem.
  0.7.7.2   February 2007   HJB   This release is a patch to 0.7.7.1 to add testing for JPA packed compression and to respect signs declared in the MIME header.
  0.7.7.3   April 2007   HJB   This release is a patch to 0.7.7.3 to add f90 support for reading of CBF byte-offset and packed compression, to fix problems with gcc 4.4.1 and to correct errors in multidimensional packed compression.
  0.7.7.4   May 2007   HJB   Corrects in handling SLS detector mincbfs and reorder dimensions versus arrays for some f90 compilers as per H. Powell.
  0.7.7.5   May 2007   HJB   Fix to cbf_get_image for bug reported by F. Remacle, fixes for windows builds as per J. Wright and F. Remacle.
  0.7.7.6   Jun 2007   HJB   Fix to CBF byte-offset compression writes, fix to Makefiles and m4 for f90 test programs to allow adjustable record length.
  0.7.8   Jul 2007   HJB  Release for full support of SLS data files with updated convert_minicbf, and support for gfortran from gcc 4.2.
  0.7.8.1  Jul 2007  HJB  Update to 0.7.8 release to fix memory leaks reported by N. Sauter and to update validation checks for recent changes.
  0.7.8.2  Dec 2007  CN, HJB  Update to 0.7.8.1 to add ADSC jiffie by Chris Nielsen, and to add ..._fs and ..._sf macros.
  0.7.9  Dec 2007  CN, HJBIdentical to 0.7.8.2 except for a cleanup of deprecated examples, e.g. diffrn_frame_data
  0.7.9.1  Jan 2008  CN, HJB  Update to 0.7.8.2 to add inverse ADSC jiffie by Chris Nielsen, to clean up problems in handling maps for RasMol.
  0.8.0  Jul 2008  GT, HJB  Cleanup of 0.7.9.1 to start 0.8 series.
  0.8.1   Jul 2009   EZ, CN, PC, GW, JH, HJB    Release with EZ's 2008 DDLm support using JH's PyCifRW, also cbff f95 wrapper code, PC's java bindings.
  0.9.1  Aug 2010  PC, EE, JLM, NS, EZ, HJB   Release with EE's Dectris template software, also with vcif3, new arvai_test, sequence_match.
  0.9.2   Feb 2011   PC, EE, JLM, NS, EZ, HJB   New default release with updated pycbf, tiff support, removal of default use of PyCifRW to avoid Fedora license issue.


Known Problems

The example program tiff2cbf needs the enviroment variable LD_LIBRARY_PATH set to the location of the lib directory in CBFlib_0.9.2, unless a system install of tiff-3.9.4-rev-6Feb11 has been done.

Due to license issues, PyCifRW is not included with default releases of CBFlib. Users can download PyCifRW separately.

There are some issues with Peter Chang's lastest java wrapper under the CBFlib 0.9.2 release. Until they are resolved, the CBFlib 0.8.1 release should be used for Java applications.

This version does not have support for predictor compression.

Code is needed to support array sub-sections.

Foreword

In order to work with CBFlib, you need:

If your system has the program wget, you only need the source code. The download of the other tar balls will be handled automatically.

Be careful about space. A full build and test can use 350 MB or more. If space is tight, be sure to read the instructions below on using only the signatures of the test files.

Uncompress and unpack :

  • gunzip < CBFlib_0.9.2.tar.gz | tar xvf -

To run the test programs, you will also need Paul Ellis's sample MAR345 image, example.mar2300, Chris Nielsen's sample ADSC Quantum 315 image, mb_LP_1_001.img, and Eric Eikenberry's SLS sample Pilatus 6m image, insulin_pilatus6m, as sample data. In addition there are is a PDB mmCIF file, 9ins.cif, and 3 special test files testflatin.cbf, testflatpackedin.cbf and testrealin.cbf. All these files will be dowloaded and extracted by the Makefile from CBFlib_0.9.2_Data_Files_Input. Do not download copies into the top level directory.

Thare are various sample Makefiles for common configurations. The Makefile_OSX samples is for systems with gfortran from prior to the release of gcc 4.2. For the most recent gfortran, use Makefile_OSX_gcc42. All the Makefiles are generated from m4/Makefile.m4.

The Makefiles use GNU make constructs, such as ifeq and ifneq. If you need to use a different version of make, you will need to edit out the conditionals

The operation of the Makefiles is sensitive to the following environment variables:

  • CBFLIB_USE_PYCIFRW If you define this environment variable, you may rebuild the Makefiles to include James Hester's PyCifRW. The process under bash is:

    export CBFLIB_USE_PYCIFRW=yes
    cd CBFlib_0.9.2
    touch m4/Makefile.m4
    make Makefiles
    
  • CBF_DONT_USE_LONG_LONG If you define this environment variable, use of the long long data type in CBFlib is replaced by use of a struct. The Makefiles do not need to be rebuilt. Makefile_MINGW does not use the long long data type even without defining this variable.
  • NOFORTRAN If you define this environment variable, use of the fortran compiler is suppressed.

If necessary, adjust the definition of CC and C++ and other defintions in Makefile to point to your compilers. Set the definition of CFLAGS to an appropriate value for your C and C++ compilers, the definition of F90C to point to your Fortan-90/95 compiler, and the definitions of F90FLAGS and F90LDFLAGS to approriate values for your Fortan-90/95 compilers, and then

make all
make tests

or, if space is at a premium:

make all
make tests_sigs_only

If you do not have a fortran compiler, you will need edit the Makefile or to define the variable NOFORTRAN, either in the Makefile or in the environment

We have included examples of CBF/imgCIF files produced by CBFlib in the test data CBFlib_0.9.2_Data_Files_Output.tar.gz, the current best draft of the CBF Extensions Dictionary, and of Andy Hammersley's CBF definition, updated to become a DRAFT CBF/ImgCIF DEFINITION.

CBFlib 0.9.2 includes a program, tiff2cbf, to convert from tiff files to CBF files, that requires an augmented version of tiff-3.9.4 called tiff-3.9.4-rev-6Feb11, that installs into the CBFlib_0.9.2 directory. If a system copy is desired, download and install http://downloads.sf.net/cbflib/tiff-3.9.4-rev-6Feb11.tar.gz


Contents

1. Introduction

CBFlib (Crystallographic Binary File library) is a library of ANSI-C functions providing a simple mechanism for accessing Crystallographic Binary Files (CBF files) and Image-supporting CIF (imgCIF) files. The CBFlib API is loosely based on the CIFPARSE API for mmCIF files. Like CIFPARSE, CBFlib does not perform any semantic integrity checks; rather it simply provides functions to create, read, modify and write CBF binary data files and imgCIF ASCII data files.

Starting with version 0.7.7, an envolving FCBlib (Fortran Crystallographic Binary library) has been added. As of this release it includes code for reading byte-offset and packed compression image files created by CBFlib.

2. Function descriptions

2.1 General description

Almost all of the CBFlib functions receive a value of type cbf_handle (a CBF handle) as the first argument. Several of the high-level CBFlib functions dealing with geometry receive a value of type cbf_goniometer (a handle for a CBF goniometer object) or cbf_detector (a handle for a CBF detector object).

All functions return an integer equal to 0 for success or an error code for failure.

2.1.1 CBF handles

CBFlib permits a program to use multiple CBF objects simultaneously. To identify the CBF object on which a function will operate, CBFlib uses a value of type cbf_handle.

All functions in the library except cbf_make_handle expect a value of type cbf_handle as the first argument.

The function cbf_make_handle creates and initializes a new CBF handle.

The function cbf_free_handle destroys a handle and frees all memory associated with the corresponding CBF object.

2.1.2 CBF goniometer handles

To represent the goniometer used to orient a sample, CBFlib uses a value of type cbf_goniometer.

A goniometer object is created and initialized from a CBF object using the function cbf_construct_goniometer.

The function cbf_free_goniometer destroys a goniometer handle and frees all memory associated with the corresponding object.

2.1.3 CBF detector handles

To represent a detector surface mounted on a positioning system, CBFlib uses a value of type cbf_detector.

A goniometer object is created and initialized from a CBF object using one of the functions cbf_construct_detector, cbf_construct_reference_detector or cbf_require_reference_detector.

The function cbf_free_detector destroys a detector handle and frees all memory associated with the corresponding object.

2.1.4 Return values

All of the CBFlib functions return 0 on success and an error code on failure. The error codes are:

  CBF_FORMAT  The file format is invalid
  CBF_ALLOC  Memory allocation failed
  CBF_ARGUMENT  Invalid function argument
  CBF_ASCII  The value is ASCII (not binary)
  CBF_BINARY  The value is binary (not ASCII)
  CBF_BITCOUNT  The expected number of bits does
not match the actual number written
  CBF_ENDOFDATA  The end of the data was reached
before the end of the array
  CBF_FILECLOSE  File close error
  CBF_FILEOPEN  File open error
  CBF_FILEREAD  File read error
  CBF_FILESEEK  File seek error
  CBF_FILETELL  File tell error
  CBF_FILEWRITE  File write error
  CBF_IDENTICAL  A data block with the new name
already exists
  CBF_NOTFOUND  The data block, category, column or
row does not exist
  CBF_OVERFLOW  The number read cannot fit into the
destination argument. The destination has
been set to the nearest value.
  CBF_UNDEFINED  The requested number is not defined (e.g. 0/0; new for version 0.7).
  CBF_NOTIMPLEMENTED  The requested functionality is not yet implemented (New for version 0.7).

If more than one error has occurred, the error code is the logical OR of the individual error codes.

2.2 Reading and writing files containing binary sections

2.2.1 Reading binary sections

The current version of CBFlib only decompresses a binary section from disk when requested by the program.

When a file containing one or more binary sections is read, CBFlib saves the file pointer and the position of the binary section within the file and then jumps past the binary section. When the program attempts to access the binary data, CBFlib sets the file position back to the start of the binary section and then reads the data.

For this scheme to work:

1. The file must be a random-access file opened in binary mode (fopen ( ," rb")).
2. The program must not close the file. CBFlib will close the file using fclose ( ) when it is no longer needed.

At present, this also means that a program cant read a file and then write back to the same file. This restriction will be eliminated in a future version.

When reading an imgCIF vs a CBF, the difference is detected automatically.

2.2.2 Writing binary sections

When a program passes CBFlib a binary value, the data is compressed to a temporary file. If the CBF object is subsequently written to a file, the data is simply copied from the temporary file to the output file.

The output file can be of any type. If the program indicates to CBFlib that the file is a random-access and readable, CBFlib will conserve disk space by closing the temporary file and using the output file as the location at which the binary value is stored.

For this option to work:

1. The file must be a random-access file opened in binary update mode (fopen ( , "w+b")).
2. The program must not close the file. CBFlib will close the file using fclose ( ) when it is no longer needed.

If this option is not used:

1. CBFlib will continue using the temporary file.
2. CBFlib will not close the file. This is the responsibility of the main program.

2.2.3 Summary of reading and writing files containing binary sections

1. Open disk files to read using the mode "rb".
2. If possible, open disk files to write using the mode "w+b" and tell CBFlib that it can use the file as a buffer.
3. Do not close any files read by CBFlib or written by CBFlib with buffering turned on.
4. Do not attempt to read from a file, then write to the same file.

2.2.4 Ordering of array indices

There are two major conventions in the ordering of array indices:

  • fs: Fast to slow. The first array index (the one numbered "1") is the one for which the values of that index change "fastest". That is, as we move forward in memory, the value of this index changes more rapidly than any other.
  • sf: Slow to fast. The first array index (the one numbered "1") is the one for which the values of that index change "slowest". That is as we move forward in memory, the value of this index changes more slowly than any other.

During the development of CBFlib, both conventions have been used. In order to avoid confusion, the functions for which array indices are used are available in three forms: a default version which may used either one convention or the other, a form in which the name of the function has an "_fs" suffix for the fast to slow convention and a form in which the name of the function has a "_sf" suffix for the slow to fast convention. Designers of applications are advised to use one of the two suffix conventions. There is no burden on performance for using one convention or the other. The differences are resolved at compile time by use of preprocessor macros.



2.3 Low-level function prototypes

2.3.1 cbf_make_handle

PROTOTYPE

#include "cbf.h"

int cbf_make_handle (cbf_handle *handle);

DESCRIPTION

cbf_make_handle creates and initializes a new internal CBF object. All other CBFlib functions operating on this object receive the CBF handle as the first argument.

ARGUMENTS
  handle  Pointer to a CBF handle.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.2 cbf_free_handle


2.3.2 cbf_free_handle

PROTOTYPE

#include "cbf.h"

int cbf_free_handle (cbf_handle handle);

DESCRIPTION

cbf_free_handle destroys the CBF object specified by the handle and frees all associated memory.

ARGUMENTS
  handle  CBF handle to free.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.1 cbf_make_handle


2.3.3 cbf_read_file, cbf_read_widefile

PROTOTYPE

#include "cbf.h"

int cbf_read_file (cbf_handle handle, FILE *file, int flags);
int cbf_read_widefile (cbf_handle handle, FILE *file, int flags);

DESCRIPTION

cbf_read_file reads the CBF or CIF file file into the CBF object specified by handle, using the CIF 1.0 convention of 80 character lines. cbf_read_widefile reads the CBF or CIF file file into the CBF object specified by handle, using the CIF 1.1 convention of 2048 character lines. A warning is issued to stderr for ascii lines over the limit. No test is performed on binary sections.

Validation is performed in three ways levels: during the lexical scan, during the parse, and, if a dictionary was converted, against the value types, value enumerations, categories and parent-child relationships specified in the dictionary.

flags controls the interpretation of binary section headers, the parsing of brackets constructs and the parsing of treble-quoted strings.
  MSG_DIGEST:   Instructs CBFlib to check that the digest of the binary section matches any header digest value. If the digests do not match, the call will return CBF_FORMAT. This evaluation and comparison is delayed (a "lazy" evaluation) to ensure maximal processing efficiency. If an immediately evaluation is required, see MSG_DIGESTNOW, below.
  MSG_DIGESTNOW:   Instructs CBFlib to check that the digest of the binary section matches any header digeste value. If the digests do not match, the call will return CBF_FORMAT. This evaluation and comparison is performed during initial parsing of the section to ensure timely error reporting at the expense of processing efficiency. If a more efficient delayed ("lazy") evaluation is required, see MSG_DIGEST, above.
  MSG_DIGESTWARN:   Instructs CBFlib to check that the digest of the binary section matches any header digeste value. If the digests do not match, a warning message will be sent to stderr, but processing will attempt to continue. This evaluation and comparison is first performed during initial parsing of the section to ensure timely error reporting at the expense of processing efficiency. An mismatch of the message digest usually indicates a serious error, but it is sometimes worth continuing processing to try to isolate the cause of the error. Use this option with caution.
  MSG_NODIGEST:   Do not check the digest (default).
  PARSE_BRACKETS:   Accept DDLm bracket-delimited [item,item,...item] or {item,item,...item} or (item,item,...item) constructs as valid, stripping non-quoted embedded whitespace and comments. These constructs may span multiple lines.
  PARSE_LIBERAL_BRACKETS:   Accept DDLm bracket-delimited [item,item,...item] or {item,item,...item} or (item,item,...item) constructs as valid, stripping embedded non-quoted, non-separating whitespace and comments. These constructs may span multiple lines. In this case, whitespace may be used as an alternative to the comma.
  PARSE_TRIPLE_QUOTES:   Accept DDLm triple-quoted """item,item,...item""" or '''item,item,...item''' constructs as valid, stripping embedded whitespace and comments. These constructs may span multiple lines. If this flag is set, then ''' will not be interpreted as a quoted apoptrophe and """ will not be interpreted as a quoted double quote mark and
  PARSE_NOBRACKETS:   Do not accept DDLm bracket-delimited [item,item,...item] or {item,item,...item} or (item,item,...item) constructs as valid, stripping non-quoted embedded whitespace and comments. These constructs may span multiple lines.
  PARSE_NOTRIPLE_QUOTES:   No not accept DDLm triple-quoted """item,item,...item""" or '''item,item,...item''' constructs as valid, stripping embedded whitespace and comments. These constructs may span multiple lines. If this flag is set, then ''' will be interpreted as a quoted apostrophe and """ will be interpreted as a quoted double quote mark.

CBFlib defers reading binary sections as long as possible. In the current version of CBFlib, this means that:

1. The file must be a random-access file opened in binary mode (fopen ( , "rb")).
2. The program must not close the file. CBFlib will close the file using fclose ( ) when it is no longer needed.

These restrictions may change in a future release.

ARGUMENTS
  handle  CBF handle.
  file  Pointer to a file descriptor.
  headers  Controls interprestation of binary section headers.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.4 cbf_write_file


2.3.4 cbf_write_file

PROTOTYPE

#include "cbf.h"

int cbf_write_file (cbf_handle handle, FILE *file, int readable, int ciforcbf, int flags, int encoding);
int cbf_write_widefile (cbf_handle handle, FILE *file, int readable, int ciforcbf, int flags, int encoding);

DESCRIPTION

cbf_write_file writes the CBF object specified by handle into the file file, following CIF 1.0 conventions of 80 character lines. cbf_write_widefile writes the CBF object specified by handle into the file file, following CIF 1.1 conventions of 2048 character lines. A warning is issued to stderr for ascii lines over the limit, and an attempt is made to fold lines to fit. No test is performed on binary sections.

If a dictionary has been provided, aliases will be applied on output.

Unlike cbf_read_file, the file does not have to be random-access.

If the file is random-access and readable, readable can be set to non-0 to indicate to CBFlib that the file can be used as a buffer to conserve disk space. If the file is not random-access or not readable, readable must be 0.

If readable is non-0, CBFlib will close the file when it is no longer required, otherwise this is the responsibility of the program.

ciforcbf selects the format in which the binary sections are written:
  CIF  Write an imgCIF file.
  CBF  Write a CBF file (default).
flags selects the type of header used in CBF binary sections, selects whether message digests are generated, and controls the style of output. The value of flags can be a logical OR of any of:
  MIME_HEADERS  Use MIME-type headers (default).
  MIME_NOHEADERS  Use a simple ASCII headers.
  MSG_DIGEST  Generate message digests for binary data validation.
  MSG_NODIGEST  Do not generate message digests (default).
  PARSE_BRACKETS  Do not convert bracketed strings to text fields (default).
  PARSE_LIBERAL_BRACKETS  Do not convert bracketed strings to text fields (default).
  PARSE_NOBRACKETS  Convert bracketed strings to text fields (default).
  PARSE_TRIPLE_QUOTES  Do not convert triple-quoted strings to text fields (default).
  PARSE_NOTRIPLE_QUOTES  Convert triple-quoted strings to text fields (default).
  PAD_1K  Pad binary sections with 1023 nulls.
  PAD_2K  Pad binary sections with 2047 nulls.
  PAD_4K  Pad binary sections with 4095 nulls.

Note that on output, the types "prns&, "brcs" and "bkts" will be converted to "text" fields if PARSE_NOBRACKETS has been set flags, and that the types "tsqs" and "tdqs" will be converted to "text" fields if the flag PARSE_NOTRIPLE_QUOTES has been set in the flags. It is an error to set PARSE_NOBRACKETS and to set either PARSE_BRACKETS or PARSE_LIBERAL_BRACKETS. It is an error to set both PARSE_NOTRIPLE_QUOTES and PARSE_TRIPLE_QUOTES.

encoding selects the type of encoding used for binary sections and the type of line-termination in imgCIF files. The value can be a logical OR of any of:
  ENC_BASE64  Use BASE64 encoding (default).
  ENC_QP  Use QUOTED-PRINTABLE encoding.
  ENC_BASE8  Use BASE8 (octal) encoding.
  ENC_BASE10  Use BASE10 (decimal) encoding.
  ENC_BASE16  Use BASE16 (hexadecimal) encoding.
  ENC_FORWARD  For BASE8, BASE10 or BASE16 encoding, map bytes to words forward (1234) (default on little-endian machines).
  ENC_BACKWARD  Map bytes to words backward (4321) (default on big-endian machines).
  ENC_CRTERM  Terminate lines with CR.
  ENC_LFTERM  Terminate lines with LF (default).

ARGUMENTS
  handle  CBF handle.
  file  Pointer to a file descriptor.
  readable  If non-0: this file is random-access and readable and can be used as a buffer.
  ciforcbf  Selects the format in which the binary sections are written (CIF/CBF).
  headers  Selects the type of header in CBF binary sections and message digest generation.
  encoding  Selects the type of encoding used for binary sections and the type of line-termination in imgCIF files.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.3 cbf_read_file


2.3.5 cbf_new_datablock, cbf_new_saveframe

PROTOTYPE

#include "cbf.h"

int cbf_new_datablock (cbf_handle handle, const char *datablockname);
int cbf_new_saveframe (cbf_handle handle, const char *saveframename);

DESCRIPTION

cbf_new_datablock creates a new data block with name datablockname and makes it the current data block. cbf_new_saveframe creates a new save frame with name saveframename within the current data block and makes the new save frame the current save frame.

If a data block or save frame with this name already exists, the existing data block or save frame becomes the current data block or save frame.

ARGUMENTS
  handle  CBF handle.
  datablockname  The name of the new data block.
  saveframename  The name of the new save frame.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.6 cbf_force_new_datablock, cbf_force_new_saveframe
2.3.7 cbf_new_category
2.3.8 cbf_force_new_category
2.3.9 cbf_new_column
2.3.10 cbf_new_row
2.3.11 cbf_insert_row
2.3.12 cbf_set_datablockname, cbf_set_saveframename
2.3.17 cbf_remove_datablock, cbf_remove_saveframe
2.3.59 cbf_require_datablock
2.3.60 cbf_require_category
2.3.61 cbf_require_column


2.3.6 cbf_force_new_datablock, cbf_force_new_saveframe

PROTOTYPE

#include "cbf.h"

int cbf_force_new_datablock (cbf_handle handle, const char *datablockname);
int cbf_force_new_saveframe (cbf_handle handle, const char *saveframename);

DESCRIPTION

cbf_force_new_datablock creates a new data block with name datablockname and makes it the current data block. Duplicate data block names are allowed. cbf_force_new_saveframe creates a new savew frame with name saveframename and makes it the current save frame. Duplicate save frame names are allowed.

Even if a save frame with this name already exists, a new save frame is created and becomes the current save frame.

ARGUMENTS
  handle  CBF handle.
  datablockname  The name of the new data block.
  saveframename  The name of the new save frame.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.5 cbf_new_datablock, cbf_new_saveframe
2.3.7 cbf_new_category
2.3.8 cbf_force_new_category
2.3.9 cbf_new_column
2.3.10 cbf_new_row
2.3.11 cbf_insert_row
2.3.12 cbf_set_datablockname, cbf_set_saveframename
2.3.17 cbf_remove_datablock, cbf_remove_saveframe
2.3.59 cbf_require_datablock
2.3.60 cbf_require_category
2.3.61 cbf_require_column


2.3.7 cbf_new_category

PROTOTYPE

#include "cbf.h"

int cbf_new_category (cbf_handle handle, const char *categoryname);

DESCRIPTION

cbf_new_category creates a new category in the current data block with name categoryname and makes it the current category.

If a category with this name already exists, the existing category becomes the current category.

ARGUMENTS
  handle  CBF handle.
  categoryname  The name of the new category.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.5 cbf_new_datablock, cbf_new_saveframe
2.3.6 cbf_force_new_datablock, cbf_force_new_saveframe
2.3.8 cbf_force_new_category
2.3.9 cbf_new_column
2.3.10 cbf_new_row
2.3.11 cbf_insert_row
2.3.18 cbf_remove_category
2.3.59 cbf_require_datablock
2.3.60 cbf_require_category
2.3.61 cbf_require_column


2.3.8 cbf_force_new_category

PROTOTYPE

#include "cbf.h"

int cbf_force_new_category (cbf_handle handle, const char *categoryname);

DESCRIPTION

cbf_force_new_category creates a new category in the current data block with name categoryname and makes it the current category. Duplicate category names are allowed.

Even if a category with this name already exists, a new category of the same name is created and becomes the current category. The allows for the creation of unlooped tag/value lists drawn from the same category.

ARGUMENTS
  handle  CBF handle.
  categoryname  The name of the new category.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.5 cbf_new_datablock, cbf_new_saveframe
2.3.6 cbf_force_new_datablock, cbf_force_new_saveframe
2.3.7 cbf_new_category
2.3.9 cbf_new_column
2.3.10 cbf_new_row
2.3.11 cbf_insert_row
2.3.18 cbf_remove_category
2.3.59 cbf_require_datablock
2.3.60 cbf_require_category
2.3.61 cbf_require_column


2.3.9 cbf_new_column

PROTOTYPE

#include "cbf.h"

int cbf_new_column (cbf_handle handle, const char *columnname);

DESCRIPTION

cbf_new_column creates a new column in the current category with name columnname and makes it the current column.

If a column with this name already exists, the existing column becomes the current category.

ARGUMENTS
  handle  CBF handle.
  columnname  The name of the new column.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.5 cbf_new_datablock, cbf_new_saveframe
2.3.6 cbf_force_new_datablock, cbf_force_new_saveframe
2.3.7 cbf_new_category
2.3.8 cbf_force_new_category
2.3.10 cbf_new_row
2.3.11 cbf_insert_row
2.3.19 cbf_remove_column
2.3.59 cbf_require_datablock
2.3.60 cbf_require_category
2.3.61 cbf_require_column


2.3.10 cbf_new_row

PROTOTYPE

#include "cbf.h"

int cbf_new_row (cbf_handle handle);

DESCRIPTION

cbf_new_row adds a new row to the current category and makes it the current row.

ARGUMENTS
  handle  CBF handle.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.5 cbf_new_datablock, cbf_new_saveframe
2.3.6 cbf_force_new_datablock, cbf_force_new_saveframe
2.3.7 cbf_new_category
2.3.8 cbf_force_new_category
2.3.9 cbf_new_column
2.3.11 cbf_insert_row
2.3.12 cbf_delete_row
2.3.20 cbf_remove_row
2.3.59 cbf_require_datablock
2.3.60 cbf_require_category
2.3.61 cbf_require_column


2.3.11 cbf_insert_row

PROTOTYPE

#include "cbf.h"

int cbf_insert_row (cbf_handle handle, unsigned int rownumber);

DESCRIPTION

cbf_insert_row adds a new row to the current category. The new row is inserted as row rownumber and existing rows starting from rownumber are moved up by 1. The new row becomes the current row.

If the category has fewer than rownumber rows, the function returns CBF_NOTFOUND.

The row numbers start from 0.

ARGUMENTS
  handle  CBF handle.
  rownumber  The row number of the new row.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.5 cbf_new_datablock, cbf_new_saveframe
2.3.6 cbf_force_new_datablock, cbf_force_new_saveframe
2.3.7 cbf_new_category
2.3.8 cbf_force_new_category
2.3.9 cbf_new_column
2.3.10 cbf_new_row
2.3.12 cbf_delete_row
2.3.20 cbf_remove_row
2.3.59 cbf_require_datablock
2.3.60 cbf_require_category
2.3.61 cbf_require_column


2.3.12 cbf_delete_row

PROTOTYPE

#include "cbf.h"

int cbf_delete_row (cbf_handle handle, unsigned int rownumber);

DESCRIPTION

cbf_delete_row deletes a row from the current category. Rows starting from rownumber +1 are moved down by 1. If the current row was higher than rownumber, or if the current row is the last row, it will also move down by 1.

The row numbers start from 0.

ARGUMENTS
  handle  CBF handle.
  rownumber  The number of the row to delete.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.10 cbf_new_row
2.3.11 cbf_insert_row
2.3.17 cbf_remove_datablock, cbf_remove_saveframe
2.3.18 cbf_remove_category
2.3.19 cbf_remove_column
2.3.20 cbf_remove_row
2.3.59 cbf_require_datablock
2.3.60 cbf_require_category
2.3.61 cbf_require_column


2.3.13 cbf_set_datablockname, cbf_set_saveframename

PROTOTYPE

#include "cbf.h"

int cbf_set_datablockname (cbf_handle handle, const char *datablockname);
int cbf_set_saveframename (cbf_handle handle, const char *saveframename);

DESCRIPTION

cbf_set_datablockname changes the name of the current data block to datablockname. cbf_set_saveframename changes the name of the current save frame to saveframename.

If a data block or save frame with this name already exists (comparison is case-insensitive), the function returns CBF_IDENTICAL.

ARGUMENTS
  handle  CBF handle.
  datablockname  The new data block name.
  datablockname  The new save frame name.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.5 cbf_new_datablock, cbf_new_saveframe
2.3.14 cbf_reset_datablocks
2.3.15 cbf_reset_datablock, cbf_reset_saveframe
2.3.17 cbf_remove_datablock, cbf_remove_saveframe
2.3.42 cbf_datablock_name


2.3.14 cbf_reset_datablocks

PROTOTYPE

#include "cbf.h"

int cbf_reset_datablocks (cbf_handle handle);

DESCRIPTION

cbf_reset_datablocks deletes all categories from all data blocks.

The current data block does not change.

ARGUMENTS
  handle  CBF handle.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.15 cbf_reset_datablock, cbf_reset_saveframe
2.3.18 cbf_remove_category


2.3.15 cbf_reset_datablock, cbf_reset_datablock

PROTOTYPE

#include "cbf.h"

int cbf_reset_datablock (cbf_handle handle);
int cbf_reset_saveframe (cbf_handle handle);

DESCRIPTION

cbf_reset_datablock deletes all categories from the current data block. cbf_reset_saveframe deletes all categories from the current save frame.

ARGUMENTS
  handle  CBF handle.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.14 cbf_reset_datablocks
2.3.18 cbf_remove_category


2.3.16 cbf_reset_category

PROTOTYPE

#include "cbf.h"

int cbf_reset_category (cbf_handle handle);

DESCRIPTION

cbf_reset_category deletes all columns and rows from current category.

ARGUMENTS
  handle  CBF handle.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.16 cbf_reset_category
2.3.19 cbf_remove_column
2.3.20 cbf_remove_row


2.3.17 cbf_remove_datablock, cbf_remove_saveframe

PROTOTYPE

#include "cbf.h"

int cbf_remove_datablock (cbf_handle handle);
int cbf_remove_saveframe (cbf_handle handle);

DESCRIPTION

cbf_remove_datablock deletes the current data block. cbf_remove_saveframe deletes the current save frame.

The current data block becomes undefined.

ARGUMENTS
  handle  CBF handle.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.5 cbf_new_datablock, cbf_new_saveframe
2.3.6 cbf_force_new_datablock, cbf_force_new_saveframe
2.3.18 cbf_remove_category
2.3.19 cbf_remove_column
2.3.20 cbf_remove_row
2.3.59 cbf_require_datablock
2.3.60 cbf_require_category
2.3.61 cbf_require_column


2.3.18 cbf_remove_category

PROTOTYPE

#include "cbf.h"

int cbf_remove_category (cbf_handle handle);

DESCRIPTION

cbf_remove_category deletes the current category.

The current category becomes undefined.

ARGUMENTS
  handle  CBF handle.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.7 cbf_new_category
2.3.8 cbf_force_new_category
2.3.17 cbf_remove_datablock, cbf_remove_saveframe
2.3.19 cbf_remove_column
2.3.20 cbf_remove_row
2.3.59 cbf_require_datablock
2.3.60 cbf_require_category
2.3.61 cbf_require_column


2.3.19 cbf_remove_column

PROTOTYPE

#include "cbf.h"

int cbf_remove_column (cbf_handle handle);

DESCRIPTION

cbf_remove_column deletes the current column.

The current column becomes undefined.

ARGUMENTS
  handle  CBF handle.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.9 cbf_new_column
2.3.17 cbf_remove_datablock, cbf_remove_saveframe
2.3.18 cbf_remove_category
2.3.20 cbf_remove_row
2.3.59 cbf_require_datablock
2.3.60 cbf_require_category
2.3.61 cbf_require_column


2.3.20 cbf_remove_row

PROTOTYPE

#include "cbf.h"

int cbf_remove_row (cbf_handle handle);

DESCRIPTION

cbf_remove_row deletes the current row in the current category.

If the current row was the last row, it will move down by 1, otherwise, it will remain the same.

ARGUMENTS
  handle  CBF handle.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.10 cbf_new_row
2.3.11 cbf_insert_row
2.3.17 cbf_remove_datablock, cbf_remove_saveframe
2.3.18 cbf_remove_category
2.3.19 cbf_remove_column
2.3.12 cbf_delete_row
2.3.59 cbf_require_datablock
2.3.60 cbf_require_category
2.3.61 cbf_require_column


2.3.21 cbf_rewind_datablock

PROTOTYPE

#include "cbf.h"

int cbf_rewind_datablock (cbf_handle handle);

DESCRIPTION

cbf_rewind_datablock makes the first data block the current data block.

If there are no data blocks, the function returns CBF_NOTFOUND.

The current category becomes undefined.

ARGUMENTS
  handle  CBF handle.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.22 cbf_rewind_category, cbf_rewind_saveframe, cbf_rewind_blockitem
2.3.19 cbf_rewind_column
2.3.24 cbf_rewind_row
2.3.25 cbf_next_datablock


2.3.22 cbf_rewind_category, cbf_rewind_saveframe, cbf_rewind_blockitem

PROTOTYPE

#include "cbf.h"

int cbf_rewind_category (cbf_handle handle);
int cbf_rewind_saveframe (cbf_handle handle);
int cbf_rewind_blockitem (cbf_handle handle, CBF_NODETYPE * type);

DESCRIPTION

cbf_rewind_category makes the first category in the current data block the current category. cbf_rewind_saveframe makes the first saveframe in the current data block the current saveframe. cbf_rewind_blockitem makes the first blockitem (category or saveframe) in the current data block the current blockitem. The type of the blockitem (CBF_CATEGORY or CBF_SAVEFRAME) is returned in type.

If there are no categories, saveframes or blockitems the function returns CBF_NOTFOUND.

The current column and row become undefined.

ARGUMENTS
  handle  CBF handle.
  type  CBF handle.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.21 cbf_rewind_datablock
2.3.19 cbf_rewind_column
2.3.24 cbf_rewind_row
2.3.26 cbf_next_category, cbf_next_saveframe, cbf_next_blockitem


2.3.23 cbf_rewind_column

PROTOTYPE

#include "cbf.h"

int cbf_rewind_column (cbf_handle handle);

DESCRIPTION

cbf_rewind_column makes the first column in the current category the current column.

If there are no columns, the function returns CBF_NOTFOUND.

The current row is not affected.

ARGUMENTS
  handle  CBF handle.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.21 cbf_rewind_datablock
2.3.22 cbf_rewind_category, cbf_rewind_saveframe, cbf_rewind_blockitem
2.3.24 cbf_rewind_row
2.3.27 cbf_next_column


2.3.24 cbf_rewind_row

PROTOTYPE

#include "cbf.h"

int cbf_rewind_row (cbf_handle handle);

DESCRIPTION

cbf_rewind_row makes the first row in the current category the current row.

If there are no rows, the function returns CBF_NOTFOUND.

The current column is not affected.

ARGUMENTS
  handle  CBF handle.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.21 cbf_rewind_datablock
2.3.22 cbf_rewind_category, cbf_rewind_saveframe, cbf_rewind_blockitem
2.3.19 cbf_rewind_column
2.3.28 cbf_next_row


2.3.25 cbf_next_datablock

PROTOTYPE

#include "cbf.h"

int cbf_next_datablock (cbf_handle handle);

DESCRIPTION

cbf_next_datablock makes the data block following the current data block the current data block.

If there are no more data blocks, the function returns CBF_NOTFOUND.

The current category becomes undefined.

ARGUMENTS
  handle  CBF handle.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.21 cbf_rewind_datablock
2.3.26 cbf_next_category, cbf_next_saveframe, cbf_next_blockitem
2.3.27 cbf_next_column
2.3.28 cbf_next_row


2.3.26 cbf_next_category

PROTOTYPE

#include "cbf.h"

int cbf_next_category (cbf_handle handle);

DESCRIPTION

cbf_next_category makes the category following the current category in the current data block the current category.

If there are no more categories, the function returns CBF_NOTFOUND.

The current column and row become undefined.

ARGUMENTS
  handle  CBF handle.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.22 cbf_rewind_category, cbf_rewind_saveframe, cbf_rewind_blockitem
2.3.25 cbf_next_datablock
2.3.27 cbf_next_column
2.3.27 cbf_next_row


2.3.27 cbf_next_column

PROTOTYPE

#include "cbf.h"

int cbf_next_column (cbf_handle handle);

DESCRIPTION

cbf_next_column makes the column following the current column in the current category the current column.

If there are no more columns, the function returns CBF_NOTFOUND.

The current row is not affected.

ARGUMENTS
  handle  CBF handle.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.19 cbf_rewind_column
2.3.25 cbf_next_datablock
2.3.26 cbf_next_category, cbf_next_saveframe, cbf_next_blockitem
2.3.28 cbf_next_row


2.3.28 cbf_next_row

PROTOTYPE

#include "cbf.h"

int cbf_next_row (cbf_handle handle);

DESCRIPTION

cbf_next_row makes the row following the current row in the current category the current row.

If there are no more rows, the function returns CBF_NOTFOUND.

The current column is not affected.

ARGUMENTS
  handle  CBF handle.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.24 cbf_rewind_row
2.3.25 cbf_next_datablock
2.3.26 cbf_next_category, cbf_next_saveframe, cbf_next_blockitem
2.3.27 cbf_next_column


2.3.29 cbf_find_datablock

PROTOTYPE

#include "cbf.h"

int cbf_find_datablock (cbf_handle handle, const char *datablockname);

DESCRIPTION

cbf_find_datablock makes the data block with name datablockname the current data block.

The comparison is case-insensitive.

If the data block does not exist, the function returns CBF_NOTFOUND.

The current category becomes undefined.

ARGUMENTS
  handle  CBF handle.
  datablockname  The name of the data block to find.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.21 cbf_rewind_datablock
2.3.25 cbf_next_datablock
2.3.30 cbf_find_category, cbf_find_saveframe, cbf_find_blockitem
2.3.31 cbf_find_column
2.3.32 cbf_find_row
2.3.42 cbf_datablock_name
2.3.59 cbf_require_datablock
2.3.60 cbf_require_category
2.3.61 cbf_require_column


2.3.30 cbf_find_category

PROTOTYPE

#include "cbf.h"

int cbf_find_category (cbf_handle handle, const char *categoryname);

DESCRIPTION

cbf_find_category makes the category in the current data block with name categoryname the current category.

The comparison is case-insensitive.

If the category does not exist, the function returns CBF_NOTFOUND.

The current column and row become undefined.

ARGUMENTS
  handle  CBF handle.
  categoryname  The name of the category to find.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.22 cbf_rewind_category, cbf_rewind_saveframe, cbf_rewind_blockitem
2.3.26 cbf_next_category, cbf_next_saveframe, cbf_next_blockitem
2.3.29 cbf_find_datablock
2.3.31 cbf_find_column
2.3.32 cbf_find_row
2.3.43 cbf_category_name
2.3.59 cbf_require_datablock
2.3.60 cbf_require_category
2.3.61 cbf_require_column


2.3.31 cbf_find_column

PROTOTYPE

#include "cbf.h"

int cbf_find_column (cbf_handle handle, const char *columnname);

DESCRIPTION

cbf_find_column makes the columns in the current category with name columnname the current column.

The comparison is case-insensitive.

If the column does not exist, the function returns CBF_NOTFOUND.

The current row is not affected.

ARGUMENTS
  handle  CBF handle.
  columnname  The name of column to find.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.19 cbf_rewind_column
2.3.27 cbf_next_column
2.3.29 cbf_find_datablock
2.3.30 cbf_find_category, cbf_find_saveframe, cbf_find_blockitem
2.3.32 cbf_find_row
2.3.44 cbf_column_name
2.3.59 cbf_require_datablock
2.3.60 cbf_require_category
2.3.61 cbf_require_column


2.3.32 cbf_find_row

PROTOTYPE

#include "cbf.h"

int cbf_find_row (cbf_handle handle, const char *value);

DESCRIPTION

cbf_find_row makes the first row in the current column with value value the current row.

The comparison is case-sensitive.

If a matching row does not exist, the function returns CBF_NOTFOUND.

The current column is not affected.

ARGUMENTS
  handle  CBF handle.
  value  The value of the row to find.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.24 cbf_rewind_row
2.3.28 cbf_next_row
2.3.29 cbf_find_datablock
2.3.30 cbf_find_category, cbf_find_saveframe, cbf_find_blockitem
2.3.31 cbf_find_column
2.3.33 cbf_find_nextrow
2.3.46 cbf_get_value, cbf_require_value
2.3.48 cbf_get_typeofvalue

2.3.33 cbf_find_nextrow

PROTOTYPE

#include "cbf.h"

int cbf_find_nextrow (cbf_handle handle, const char *value);

DESCRIPTION

cbf_find_nextrow makes the makes the next row in the current column with value value the current row. The search starts from the row following the last row found with cbf_find_row or cbf_find_nextrow, or from the current row if the current row was defined using any other function.

The comparison is case-sensitive.

If no more matching rows exist, the function returns CBF_NOTFOUND.

The current column is not affected.

ARGUMENTS
  handle  CBF handle.
  value  the value to search for.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.24 cbf_rewind_row
2.3.28 cbf_next_row
2.3.29 cbf_find_datablock
2.3.30 cbf_find_category, cbf_find_saveframe, cbf_find_blockitem
2.3.31 cbf_find_column
2.3.32 cbf_find_row
2.3.46 cbf_get_value, cbf_require_value
2.3.48 cbf_get_typeofvalue


2.3.34 cbf_count_datablocks

PROTOTYPE

#include "cbf.h"

int cbf_count_datablocks (cbf_handle handle, unsigned int *datablocks);

DESCRIPTION

cbf_count_datablocks puts the number of data blocks in *datablocks .

ARGUMENTS
  handle  CBF handle.
  datablocks  Pointer to the destination data block count.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.35 cbf_count_categories, cbf_count_saveframes, cbf_count_blockitems
2.3.36 cbf_count_columns
2.3.37 cbf_count_rows
2.3.38 cbf_select_datablock


2.3.35 cbf_count_categories

PROTOTYPE

#include "cbf.h"

int cbf_count_categories (cbf_handle handle, unsigned int *categories);

DESCRIPTION

cbf_count_categories puts the number of categories in the current data block in *categories.

ARGUMENTS
  handle  CBF handle.
  categories  Pointer to the destination category count.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.34 cbf_count_datablocks
2.3.36 cbf_count_columns
2.3.37 cbf_count_rows
2.3.39 cbf_select_category, cbf_select_saveframe, cbf_select_blockitem


2.3.36 cbf_count_columns

PROTOTYPE

#include "cbf.h"

int cbf_count_columns (cbf_handle handle, unsigned int *columns);

DESCRIPTION

cbf_count_columns puts the number of columns in the current category in *columns.

ARGUMENTS
  handle  CBF handle.
  columns  Pointer to the destination column count.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.34 cbf_count_datablocks
2.3.35 cbf_count_categories, cbf_count_saveframes, cbf_count_blockitems
2.3.37 cbf_count_rows
2.3.40 cbf_select_column


2.3.37 cbf_count_rows

PROTOTYPE

#include "cbf.h"

int cbf_count_rows (cbf_handle handle, unsigned int *rows);

DESCRIPTION

cbf_count_rows puts the number of rows in the current category in *rows .

ARGUMENTS
  handle  CBF handle.
  rows  Pointer to the destination row count.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.34 cbf_count_datablocks
2.3.35 cbf_count_categories, cbf_count_saveframes, cbf_count_blockitems
2.3.36 cbf_count_columns
2.3.41 cbf_select_row


2.3.38 cbf_select_datablock

PROTOTYPE

#include "cbf.h"

int cbf_select_datablock (cbf_handle handle, unsigned int datablock);

DESCRIPTION

cbf_select_datablock selects data block number datablock as the current data block.

The first data block is number 0.

If the data block does not exist, the function returns CBF_NOTFOUND.

ARGUMENTS
  handle  CBF handle.
  datablock  Number of the data block to select.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.34 cbf_count_datablocks
2.3.39 cbf_select_category, cbf_select_saveframe, cbf_select_blockitem
2.3.40 cbf_select_column
2.3.41 cbf_select_row


2.3.39 cbf_select_category

PROTOTYPE

#include "cbf.h"

int cbf_select_category (cbf_handle handle, unsigned int category);

DESCRIPTION

cbf_select_category selects category number category in the current data block as the current category.

The first category is number 0.

The current column and row become undefined.

If the category does not exist, the function returns CBF_NOTFOUND.

ARGUMENTS
  handle  CBF handle.
  category  Number of the category to select.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.35 cbf_count_categories, cbf_count_saveframes, cbf_count_blockitems
2.3.38 cbf_select_datablock
2.3.40 cbf_select_column
2.3.41 cbf_select_row


2.3.40 cbf_select_column

PROTOTYPE

#include "cbf.h"

int cbf_select_column (cbf_handle handle, unsigned int column);

DESCRIPTION

cbf_select_column selects column number column in the current category as the current column.

The first column is number 0.

The current row is not affected

If the column does not exist, the function returns CBF_NOTFOUND.

ARGUMENTS
  handle  CBF handle.
  column  Number of the column to select.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.36 cbf_count_columns
2.3.38 cbf_select_datablock
2.3.39 cbf_select_category, cbf_select_saveframe, cbf_select_blockitem
2.3.41 cbf_select_row


2.3.41 cbf_select_row

PROTOTYPE

#include "cbf.h"

int cbf_select_row (cbf_handle handle, unsigned int row);

DESCRIPTION

cbf_select_row selects row number row in the current category as the current row.

The first row is number 0.

The current column is not affected

If the row does not exist, the function returns CBF_NOTFOUND.

ARGUMENTS
  handle  CBF handle.
  row  Number of the row to select.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.37 cbf_count_rows
2.3.38 cbf_select_datablock
2.3.39 cbf_select_category, cbf_select_saveframe, cbf_select_blockitem
2.3.40 cbf_select_column


2.3.42 cbf_datablock_name

PROTOTYPE

#include "cbf.h"

int cbf_datablock_name (cbf_handle handle, const char **datablockname);

DESCRIPTION

cbf_datablock_name sets *datablockname to point to the name of the current data block.

The data block name will be valid as long as the data block exists and has not been renamed.

The name must not be modified by the program in any way.

ARGUMENTS
  handle  CBF handle.
  datablockname  Pointer to the destination data block name pointer.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.29 cbf_find_datablock


2.3.43 cbf_category_name

PROTOTYPE

#include "cbf.h"

int cbf_category_name (cbf_handle handle, const char **categoryname);

DESCRIPTION

cbf_category_name sets *categoryname to point to the name of the current category of the current data block.

The category name will be valid as long as the category exists.

The name must not be modified by the program in any way.

ARGUMENTS
  handle  CBF handle.
  categoryname  Pointer to the destination category name pointer.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.30 cbf_find_category, cbf_find_saveframe, cbf_find_blockitem


2.3.44 cbf_column_name, cbf_set_column_name

PROTOTYPE

#include "cbf.h"

int cbf_column_name (cbf_handle handle, const char **columnname);
int cbf_set_column_name (cbf_handle handle, const char *newcolumnname)

DESCRIPTION

cbf_column_name sets *columnname to point to the name of the current column of the current category.

The column name will be valid as long as the column exists.

The name must not be modified by the program in any way.

cbf_set_column_name sets the name of the current column to newcolumnname

ARGUMENTS
  handle  CBF handle.
  columnname  Pointer to the destination column name pointer.
  newcolumnname  New column name pointer.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.31 cbf_find_column


2.3.45 cbf_row_number

PROTOTYPE

#include "cbf.h"

int cbf_row_number (cbf_handle handle, unsigned int *row);

DESCRIPTION

cbf_row_number sets *row to the number of the current row of the current category.

ARGUMENTS
  handle  CBF handle.
  row  Pointer to the destination row number.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.41 cbf_select_row


2.3.46 cbf_get_value, cbf_require_value

PROTOTYPE

#include "cbf.h"

int cbf_get_value (cbf_handle handle, const char **value);
int cbf_require_value (cbf_handle handle, const char **value, const char *defaultvalue );

DESCRIPTION

cbf_get_value sets *value to point to the ASCII value of the item at the current column and row. cbf_require_value sets *value to point to the ASCII value of the item at the current column and row, creating the data item if necessary and initializing it to a copy of defaultvalue.

If the value is not ASCII, the function returns CBF_BINARY.

The value will be valid as long as the item exists and has not been set to a new value.

The value must not be modified by the program in any way.

ARGUMENTS
  handle  CBF handle.
  value  Pointer to the destination value pointer.
  defaultvalue  Default value character string.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.47 cbf_set_value
2.3.48 cbf_get_typeofvalue
2.3.49 cbf_set_typeofvalue
2.3.50 cbf_get_integervalue, cbf_require_integervalue
2.3.52 cbf_get_doublevalue, cbf_require_doublevalue
2.3.54 cbf_get_integerarrayparameters, cbf_get_integerarrayparameters_wdims, cbf_get_realarrayparameters, cbf_get_realarrayparameters_wdims
2.3.55 cbf_get_integerarray, cbf_get_realarray
2.3.62 cbf_require_column_value
2.3.63 cbf_require_column_integervalue
2.3.64 cbf_require_column_doublevalue


2.3.47 cbf_set_value

PROTOTYPE

#include "cbf.h"

int cbf_set_value (cbf_handle handle, const char *value);

DESCRIPTION

cbf_set_value sets the item at the current column and row to the ASCII value value.

ARGUMENTS
  handle  CBF handle.
  value  ASCII value.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.46 cbf_get_value, cbf_require_value
2.3.48 cbf_get_typeofvalue
2.3.49 cbf_set_typeofvalue
2.3.51 cbf_set_integervalue
2.3.53 cbf_set_doublevalue
2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_realarray, cbf_set_realarray_wdims
2.3.62 cbf_require_column_value
2.3.63 cbf_require_column_integervalue
2.3.64 cbf_require_column_doublevalue


2.3.48 cbf_get_typeofvalue

PROTOTYPE

#include "cbf.h"

int cbf_get_typeofvalue (cbf_handle handle, const char **typeofvalue);

DESCRIPTION

cbf_get_value sets *typeofvalue to point an ASCII descriptor of the value of the item at the current column and row. The strings that may be returned are:

"null"for a null value indicated by a "." or a "?"
"bnry"for a binary value
"word"for an unquoted string
"dblq"for a double-quoted string
"sglq"for a single-quoted string
"text"for a semicolon-quoted string (multiline text field)
"prns"for a parenthesis-bracketed string (multiline text field)
"brcs"for a brace-bracketed string (multiline text field)
"bkts"for a square-bracket-bracketed string (multiline text field)
"tsqs"for a treble-single-quote quoted string (multiline text field)
"tdqs"for a treble-double-quote quoted string (multiline text field)

Not all types are valid for all type of CIF files. In partcular the types "prns", "brcs", "bkts" were introduced with DDLm and are not valid in DDL1 or DDL2 CIFS. The types "tsqs" and "tdqs" are not formally part of the CIF syntax. A field for which no value has been set sets *typeofvalue to NULL rather than to the string "null".

The typeofvalue must not be modified by the program in any way.

ARGUMENTS
  handle  CBF handle.
  typeofvalue  Pointer to the destination type-of-value string pointer.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.46 cbf_get_value, cbf_require_value
2.3.47 cbf_set_value
2.3.49 cbf_set_typeofvalue
2.3.50 cbf_get_integervalue, cbf_require_integervalue
2.3.52 cbf_get_doublevalue, cbf_require_doublevalue
2.3.54 cbf_get_integerarrayparameters, cbf_get_integerarrayparameters_wdims, cbf_get_realarrayparameters, cbf_get_realarrayparameters_wdims
2.3.55 cbf_get_integerarray, cbf_get_realarray
2.3.62 cbf_require_column_value
2.3.63 cbf_require_column_integervalue
2.3.64 cbf_require_column_doublevalue


2.3.49 cbf_set_typeofvalue

PROTOTYPE

#include "cbf.h"

int cbf_set_typeofvalue (cbf_handle handle, const char *typeofvalue);

DESCRIPTION

cbf_set_typeofvalue sets the type of the item at the current column and row to the type specified by the ASCII character string given by typeofvalue. The strings that may be used are:

"null"for a null value indicated by a "." or a "?"
"bnry"for a binary value
"word"for an unquoted string
"dblq"for a double-quoted string
"sglq"for a single-quoted string
"text"for a semicolon-quoted string (multiline text field)
"prns"for a parenthesis-bracketed string (multiline text field)
"brcs"for a brace-bracketed string (multiline text field)
"bkts"for a square-bracket-bracketed string (multiline text field)
"tsqs"for a treble-single-quote quoted string (multiline text field)
"tdqs"for a treble-double-quote quoted string (multiline text field)
Not all types may be used for all values. Not all types are valid for all type of CIF files. In partcular the types "prns", "brcs", "bkts" were introduced with DDLm and are not valid in DDL1 or DDL2 CIFS. The types "tsqs" and "tdqs" are not formally part of the CIF syntax. No changes may be made to the type of binary values. You may not set the type of a string that contains a single quote followed by a blank or a tab or which contains multiple lines to "sglq". You may not set the type of a string that contains a double quote followed by a blank or a tab or which contains multiple lines to "dblq".

ARGUMENTS
  handle  CBF handle.
  typeofvalue  ASCII string for desired type of value.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.46 cbf_get_value, cbf_require_value
2.3.47 cbf_set_value
2.3.48 cbf_get_typeofvalue
2.3.51 cbf_set_integervalue
2.3.53 cbf_set_doublevalue
2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_realarray, cbf_set_realarray_wdims
2.3.62 cbf_require_column_value
2.3.63 cbf_require_column_integervalue
2.3.64 cbf_require_column_doublevalue


2.3.50 cbf_get_integervalue, cbf_require_integervalue

PROTOTYPE

#include "cbf.h"

int cbf_get_integervalue (cbf_handle handle, int *number);
int cbf_require_integervalue (cbf_handle handle, int *number, int defaultvalue);

DESCRIPTION

cbf_get_integervalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal integer. cbf_require_integervalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal integer, setting it to defaultvalue if necessary.

If the value is not ASCII, the function returns CBF_BINARY.

ARGUMENTS
  handle  CBF handle.
  number  pointer to the number.
  defaultvalue  default number value.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.46 cbf_get_value, cbf_require_value
2.3.48 cbf_get_typeofvalue
2.3.51 cbf_set_integervalue
2.3.52 cbf_get_doublevalue, cbf_require_doublevalue
2.3.54 cbf_get_integerarrayparameters, cbf_get_integerarrayparameters_wdims, cbf_get_realarrayparameters, cbf_get_realarrayparameters_wdims
2.3.55 cbf_get_integerarray, cbf_get_realarray
2.3.62 cbf_require_column_value
2.3.63 cbf_require_column_integervalue
2.3.64 cbf_require_column_doublevalue


2.3.51 cbf_set_integervalue

PROTOTYPE

#include "cbf.h"

int cbf_set_integervalue (cbf_handle handle, int number);

DESCRIPTION

cbf_set_integervalue sets the item at the current column and row to the integer value number written as a decimal ASCII string.

ARGUMENTS
  handle  CBF handle.
  number  Integer value.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.46 cbf_get_value, cbf_require_value
2.3.47 cbf_set_value
2.3.48 cbf_get_typeofvalue
2.3.49 cbf_set_typeofvalue
2.3.50 cbf_get_integervalue, cbf_require_integervalue
2.3.51 cbf_set_integervalue
2.3.53 cbf_set_doublevalue
2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_realarray, cbf_set_realarray_wdims
2.3.62 cbf_require_column_value
2.3.63 cbf_require_column_integervalue
2.3.64 cbf_require_column_doublevalue


2.3.52 cbf_get_doublevalue, cbf_require_doublevalue

PROTOTYPE

#include "cbf.h"

int cbf_get_doublevalue (cbf_handle handle, double *number);
int cbf_require_doublevalue (cbf_handle handle, double *number, double defaultvalue);

DESCRIPTION

cbf_get_doublevalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal floating-point number. cbf_require_doublevalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal floating-point number, setting it to defaultvalue if necessary.

If the value is not ASCII, the function returns CBF_BINARY.

ARGUMENTS
  handle  CBF handle.
  number  Pointer to the destination number.
  defaultvalue  default number value.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.46 cbf_get_value, cbf_require_value
2.3.48 cbf_get_typeofvalue
2.3.49 cbf_set_typeofvalue
2.3.50 cbf_get_integervalue, cbf_require_integervalue
2.3.53 cbf_set_doublevalue
2.3.54 cbf_get_integerarrayparameters, cbf_get_integerarrayparameters_wdims, cbf_get_realarrayparameters, cbf_get_realarrayparameters_wdims
2.3.55 cbf_get_integerarray, cbf_get_realarray
2.3.62 cbf_require_column_value
2.3.63 cbf_require_column_integervalue
2.3.64 cbf_require_column_doublevalue


2.3.53 cbf_set_doublevalue

PROTOTYPE

#include "cbf.h"

int cbf_set_doublevalue (cbf_handle handle, const char *format, double number);

DESCRIPTION

cbf_set_doublevalue sets the item at the current column and row to the floating-point value number written as an ASCII string with the format specified by format as appropriate for the printf function.

ARGUMENTS
  handle  CBF handle.
  format  Format for the number.
  number  Floating-point value.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.46 cbf_get_value, cbf_require_value
2.3.47 cbf_set_value
2.3.48 cbf_get_typeofvalue
2.3.49 cbf_set_typeofvalue
2.3.51 cbf_set_integervalue
2.3.52 cbf_get_doublevalue, cbf_require_doublevalue
2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_realarray, cbf_set_realarray_wdims
2.3.62 cbf_require_column_value
2.3.63 cbf_require_column_integervalue
2.3.64 cbf_require_column_doublevalue


2.3.54 cbf_get_integerarrayparameters,
      cbf_get_integerarrayparameters_wdims, cbf_get_integerarrayparameters_wdims_fs, cbf_get_integerarrayparameters_wdims_sf,       cbf_get_realarrayparameters,
      cbf_get_realarrayparameters_wdims, cbf_get_realarrayparameters_wdims_fs, cbf_get_realarrayparameters_wdims_sf

PROTOTYPE

#include "cbf.h"

int cbf_get_integerarrayparameters (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, int *elsigned, int *elunsigned, size_t *elements, int *minelement, int *maxelement);
 
int cbf_get_integerarrayparameters_wdims (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, int *elsigned, int *elunsigned, size_t *elements, int *minelement, int *maxelement, const char **byteorder, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding);
int cbf_get_integerarrayparameters_wdims_fs (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, int *elsigned, int *elunsigned, size_t *elements, int *minelement, int *maxelement, const char **byteorder, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding);
int cbf_get_integerarrayparameters_wdims_sf (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, int *elsigned, int *elunsigned, size_t *elements, int *minelement, int *maxelement, const char **byteorder, size_t *dimslow, size_t *dimmid, size_t *dimfast, size_t *padding);
 
int cbf_get_realarrayparameters (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, size_t *elements);
 
int cbf_get_realarrayparameters_wdims (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, size_t *elements, const char **byteorder, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding);
int cbf_get_realarrayparameters_wdims_fs (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, size_t *elements, const char **byteorder, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding);
int cbf_get_realarrayparameters_wdims_sf (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, size_t *elements, const char **byteorder, size_t *dimslow, size_t *dimmid, size_t *dimfast, size_t *padding);

DESCRIPTION

cbf_get_integerarrayparameters sets *compression, *binary_id, *elsize, *elsigned, *elunsigned, *elements, *minelement and *maxelement to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_integerarray, if a copy of the array is to be made into another CIF or CBF. cbf_get_realarrayparameters sets *compression, *binary_id, *elsize, *elements to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_realarray, if a copy of the arry is to be made into another CIF or CBF.

The variants cbf_get_integerarrayparameters_wdims, cbf_get_integerarrayparameters_wdims_fs, cbf_get_integerarrayparameters_wdims_sf, cbf_get_realarrayparameters_wdims, cbf_get_realarrayparameters_wdims_fs, cbf_get_realarrayparameters_wdims_sf set **byteorder, *dimfast, *dimmid, *dimslow, and *padding as well, providing the additional parameters needed for a subsequent call to cbf_set_integerarray_wdims or cbf_set_realarray_wdims.

The value returned in *byteorder is a pointer either to the string "little_endian" or to the string "big_endian". This should be the byte order of the data, not necessarily of the host machine. No attempt should be made to modify this string. At this time only "little_endian" will be returned.

The values returned in *dimfast, *dimmid and *dimslow are the sizes of the fastest changing, second fastest changing and third fastest changing dimensions of the array, if specified, or zero, if not specified.

The value returned in *padding is the size of the post-data padding, if any and if specified in the data header. The value is given as a count of octets.

If the value is not binary, the function returns CBF_ASCII.

ARGUMENTS
  handle  CBF handle.
  compression  Compression method used.
  elsize  Size in bytes of each array element.
  binary_id  Pointer to the destination integer binary identifier.
  elsigned  Pointer to an integer. Set to 1 if the elements can be read as signed integers.
  elunsigned  Pointer to an integer. Set to 1 if the elements can be read as unsigned integers.
  elements  Pointer to the destination number of elements.
  minelement  Pointer to the destination smallest element.
  maxelement  Pointer to the destination largest element.
  byteorder  Pointer to the destination byte order.
  dimfast  Pointer to the destination fastest dimension.
  dimmid  Pointer to the destination second fastest dimension.
  dimslow  Pointer to the destination third fastest dimension.
  padding  Pointer to the destination padding size.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.46 cbf_get_value, cbf_require_value
2.3.48 cbf_get_typeofvalue
2.3.49 cbf_set_typeofvalue
2.3.50 cbf_get_integervalue, cbf_require_integervalue
2.3.52 cbf_get_doublevalue, cbf_require_doublevalue
2.3.55 cbf_get_integerarray, cbf_get_realarray
2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_realarray, cbf_set_realarray_wdims
2.3.62 cbf_require_column_value
2.3.63 cbf_require_column_integervalue
2.3.64 cbf_require_column_doublevalue


2.3.55 cbf_get_integerarray, cbf_get_realarray

PROTOTYPE

#include "cbf.h"

int cbf_get_integerarray (cbf_handle handle, int *binary_id, void *array, size_t elsize, int elsigned, size_t elements, size_t *elements_read);
int cbf_get_realarray (cbf_handle handle, int *binary_id, void *array, size_t elsize, size_t elements, size_t *elements_read);

DESCRIPTION

cbf_get_integerarray reads the binary value of the item at the current column and row into an integer array. The array consists of elements elements of elsize bytes each, starting at array. The elements are signed if elsigned is non-0 and unsigned otherwise. *binary_id is set to the binary section identifier and *elements_read to the number of elements actually read. cbf_get_realarray reads the binary value of the item at the current column and row into a real array. The array consists of elements elements of elsize bytes each, starting at array. *binary_id is set to the binary section identifier and *elements_read to the number of elements actually read.

If any element in the integer binary data cant fit into the destination element, the destination is set the nearest possible value.

If the value is not binary, the function returns CBF_ASCII.

If the requested number of elements cant be read, the function will read as many as it can and then return CBF_ENDOFDATA.

Currently, the destination array must consist of chars, shorts or ints (signed or unsigned). If elsize is not equal to sizeof (char), sizeof (short) or sizeof (int), for cbf_get_integerarray, or sizeof(double) or sizeof(float), for cbf_get_realarray the function returns CBF_ARGUMENT.

An additional restriction in the current version of CBFlib is that values too large to fit in an int are not correctly decompressed. As an example, if the machine with 32-bit ints is reading an array containing a value outside the range 0 .. 2^32-1 (unsigned) or -2^31 .. 2^31-1 (signed), the array will not be correctly decompressed. This restriction will be removed in a future release. For cbf_get_realarray, only IEEE format is supported. No conversion to other floating point formats is done at this time.

ARGUMENTS
  handle  CBF handle.
  binary_id  Pointer to the destination integer binary identifier.
  array  Pointer to the destination array.
  elsize  Size in bytes of each destination array element.
  elsigned  Set to non-0 if the destination array elements are signed.
  elements  The number of elements to read.
  elements_read  Pointer to the destination number of elements actually read.

RETURN VALUE

Returns an error code on failure or 0 for success.
SEE ALSO

2.3.46 cbf_get_value, cbf_require_value
2.3.48 cbf_get_typeofvalue
2.3.49 cbf_set_typeofvalue
2.3.50 cbf_get_integervalue, cbf_require_integervalue
2.3.52 cbf_get_doublevalue, cbf_require_doublevalue
2.3.54 cbf_get_integerarrayparameters, cbf_get_integerarrayparameters_wdims, cbf_get_realarrayparameters, cbf_get_realarrayparameters_wdims
2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_realarray, cbf_set_realarray_wdims
2.3.62 cbf_require_column_value
2.3.63 cbf_require_column_integervalue
2.3.64 cbf_require_column_doublevalue


2.3.56 cbf_set_integerarray,
      cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, cbf_set_integerarray_wdims_sf,
      cbf_set_realarray,
      cbf_set_realarray_wdims, cbf_set_realarray_wdims_fs, cbf_set_realarray_wdims_sf

PROTOTYPE

#include "cbf.h"

int cbf_set_integerarray (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, int elsigned, size_t elements);
 
int cbf_set_integerarray_wdims (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, int elsigned, size_t elements, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding);
int cbf_set_integerarray_wdims_fs (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, int elsigned, size_t elements, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding);
int cbf_set_integerarray_wdims_sf (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, int elsigned, size_t elements, const char *byteorder, size_t dimslow, size_t dimmid, size_t dimfast, size_t padding);
 
int cbf_set_realarray (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, size_t elements);
 
int cbf_set_realarray_wdims (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, size_t elements, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding);
int cbf_set_realarray_wdims_fs (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, size_t elements, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding);
int cbf_set_realarray_wdims_sf (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, size_t elements, const char *byteorder, size_t dimslow, size_t dimmid, size_t dimfast, size_t padding);

DESCRIPTION

cbf_set_integerarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. The elements are signed if elsigned is non-0 and unsigned otherwise. binary_id is the binary section identifier. cbf_set_realarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. binary_id is the binary section identifier.

The cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, cbf_set_integerarray_wdims_sf, cbf_set_realarray_wdims, cbf_set_realarray_wdims_fs and cbf_set_realarray_wdims_sf variants allow the data header values of byteorder, dimfast, dimmid, dimslow and padding to be set to the data byte order, the fastest, second fastest and third fastest array dimensions and the size in byte of the post data padding to be used.

The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are:

  CBF_CANONICAL  Canonical-code compression (section 3.3.1)
  CBF_PACKED  CCP4-style packing (section 3.3.2)
  CBF_PACKED_V2  CCP4-style packing, version 2 (section 3.3.2)
  CBF_BYTE_OFFSET  Simple "byte_offset" compression.
  CBF_NONE  No compression. NOTE: This scheme is by far the slowest of the four and uses much more disk space. It is intended for routine use with small arrays only. With large arrays (like images) it should be used only for debugging.

The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value.

Currently, the source array must consist of chars, shorts or ints (signed or unsigned), for cbf_set_integerarray, or IEEE doubles or floats for cbf_set_realarray. If elsize is not equal to sizeof (char), sizeof (short) or sizeof (int), the function returns CBF_ARGUMENT.

ARGUMENTS
  handle  CBF handle.
  compression  Compression method to use.
  binary_id  Integer binary identifier.
  array  Pointer to the source array.
  elsize  Size in bytes of each source array element.
  elsigned  Set to non-0 if the source array elements are signed.
elements: The number of elements in the array.

RETURN VALUE

Returns an error code on failure or 0 for success.

SEE ALSO

2.3.47 cbf_set_value
2.3.48 cbf_get_typeofvalue
2.3.49 cbf_set_typeofvalue
2.3.51 cbf_set_integervalue
2.3.53 cbf_set_doublevalue
2.3.54 cbf_get_integerarrayparameters, cbf_get_integerarrayparameters_wdims, cbf_get_realarrayparameters, cbf_get_realarrayparameters_wdims
2.3.55 cbf_get_integerarray, cbf_get_realarray
2.3.62 cbf_require_column_value
2.3.63 cbf_require_column_integervalue
2.3.64 cbf_require_column_doublevalue


2.3.57 cbf_failnez

DEFINITION

#include "cbf.h"

#define cbf_failnez(f) {int err; err = (f); if (err) return err; }

DESCRIPTION

cbf_failnez is a macro used for error propagation throughout CBFlib. cbf_failnez executes the function f and saves the returned error value. If the error value is non-0, cbf_failnez executes a return with the error value as argument. If CBFDEBUG is defined, then a report of the error is also printed to the standard error stream, stderr, in the form

CBFlib error f in "symbol"

where f is the decimal value of the error and symbol is the symbolic form.

ARGUMENTS
  f  Integer error value.

SEE ALSO

2.3.58 cbf_onfailnez


2.3.58 cbf_onfailnez

DEFINITION

#include "cbf.h"

#define cbf_onfailnez(f,c) {int err; err = (f); if (err) {{c; }return err; }}

DESCRIPTION

cbf_onfailnez is a macro used for error propagation throughout CBFlib. cbf_onfailnez executes the function f and saves the returned error value. If the error value is non-0, cbf_failnez executes first the statement c and then a return with the error value as argument. If CBFDEBUG is defined, then a report of the error is also printed to the standard error stream, stderr, in the form

CBFlib error f in "symbol"

where f is the decimal value of the error and symbol is the symbolic form.

ARGUMENTS
  f  integer function to execute.
  c  statement to execute on failure.

SEE ALSO

  • 2.3.57 cbf_failnez


    2.3.59 cbf_require_datablock

    PROTOTYPE

    #include "cbf.h"

    int cbf_require_datablock (cbf_handle handle, const char *datablockname);

    DESCRIPTION

    cbf_require_datablock makes the data block with name datablockname the current data block, if it exists, or creates it if it does not.

    The comparison is case-insensitive.

    The current category becomes undefined.

    ARGUMENTS
      handle  CBF handle.
      datablockname  The name of the data block to find or create.

    RETURN VALUE

    Returns an error code on failure or 0 for success.

    SEE ALSO

    2.3.21 cbf_rewind_datablock
    2.3.25 cbf_next_datablock
    2.3.29 cbf_find_datablock
    2.3.30 cbf_find_category, cbf_find_saveframe, cbf_find_blockitem
    2.3.31 cbf_find_column
    2.3.32 cbf_find_row
    2.3.42 cbf_datablock_name
    2.3.60 cbf_require_category
    2.3.61 cbf_require_column


    2.3.60 cbf_require_category

    PROTOTYPE

    #include "cbf.h"

    int cbf_require_category (cbf_handle handle, const char *categoryname);

    DESCRIPTION

    cbf_rewuire_category makes the category in the current data block with name categoryname the current category, if it exists, or creates the catagory if it does not exist.

    The comparison is case-insensitive.

    The current column and row become undefined.

    ARGUMENTS
      handle  CBF handle.
      categoryname  The name of the category to find.

    RETURN VALUE

    Returns an error code on failure or 0 for success.

    SEE ALSO

    2.3.22 cbf_rewind_category, cbf_rewind_saveframe, cbf_rewind_blockitem
    2.3.26 cbf_next_category, cbf_next_saveframe, cbf_next_blockitem
    2.3.29 cbf_find_datablock
    2.3.31 cbf_find_column
    2.3.32 cbf_find_row
    2.3.43 cbf_category_name
    2.3.59 cbf_require_datablock
    2.3.61 cbf_require_column


    2.3.61 cbf_require_column

    PROTOTYPE

    #include "cbf.h"

    int cbf_require_column (cbf_handle handle, const char *columnname);

    DESCRIPTION

    cbf_require_column makes the columns in the current category with name columnname the current column, if it exists, or creates it if it does not.

    The comparison is case-insensitive.

    The current row is not affected.

    ARGUMENTS
      handle  CBF handle.
      columnname  The name of column to find.

    RETURN VALUE

    Returns an error code on failure or 0 for success.

    SEE ALSO

    2.3.19 cbf_rewind_column
    2.3.27 cbf_next_column
    2.3.29 cbf_find_datablock
    2.3.30 cbf_find_category, cbf_find_saveframe, cbf_find_blockitem
    2.3.32 cbf_find_row
    2.3.44 cbf_column_name, cbf_set_column_name
    2.3.59 cbf_require_datablock
    2.3.60 cbf_require_category


    2.3.62 cbf_require_column_value

    PROTOTYPE

    #include "cbf.h"

    int cbf_require_column_value (cbf_handle handle, const char *columnname, const char **value, const char *defaultvalue);

    DESCRIPTION

    cbf_require_column_doublevalue sets *value to the ASCII item at the current row for the column given with the name given by *columnname, or to the string given by defaultvalue if the item cannot be found.

    ARGUMENTS
      handle  CBF handle.
      columnname  Name of the column containing the number.
      value  pointer to the location to receive the value.
      defaultvalue  Value to use if the requested column and value cannot be found.

    RETURN VALUE

    Returns an error code on failure or 0 for success.

    SEE ALSO

    2.3.46 cbf_get_value, cbf_require_value
    2.3.47 cbf_set_value
    2.3.48 cbf_get_typeofvalue
    2.3.49 cbf_set_typeofvalue
    2.3.51 cbf_set_integervalue
    2.3.52 cbf_get_doublevalue, cbf_require_doublevalue
    2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_realarray, cbf_set_realarray_wdims
    2.3.63 cbf_require_column_integervalue
    2.3.64 cbf_require_column_doublevalue


    2.3.63 cbf_require_column_integervalue

    PROTOTYPE

    #include "cbf.h"

    int cbf_require_column_integervalue (cbf_handle handle, const char *columnname, int *number, const int defaultvalue);

    DESCRIPTION

    cbf_require_column_doublevalue sets *number to the value of the ASCII item at the current row for the column given with the name given by *columnname, with the value interpreted as an integer number, or to the number given by defaultvalue if the item cannot be found.

    ARGUMENTS
      handle  CBF handle.
      columnname  Name of the column containing the number.
      number  pointer to the location to receive the integer value.
      defaultvalue  Value to use if the requested column and value cannot be found.

    RETURN VALUE

    Returns an error code on failure or 0 for success.

    SEE ALSO

    2.3.46 cbf_get_value, cbf_require_value
    2.3.47 cbf_set_value
    2.3.48 cbf_get_typeofvalue
    2.3.49 cbf_set_typeofvalue
    2.3.51 cbf_set_integervalue
    2.3.52 cbf_get_doublevalue, cbf_require_doublevalue
    2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_realarray, cbf_set_realarray_wdims
    2.3.62 cbf_require_column_value
    2.3.64 cbf_require_column_doublevalue


    2.3.64 cbf_require_column_doublevalue

    PROTOTYPE

    #include "cbf.h"

    int cbf_require_column_doublevalue (cbf_handle handle, const char *columnname, double *number, const double defaultvalue);

    DESCRIPTION

    cbf_require_column_doublevalue sets *number to the value of the ASCII item at the current row for the column given with the name given by *columnname, with the value interpreted as a decimal floating-point number, or to the number given by defaultvalue if the item cannot be found.

    ARGUMENTS
      handle  CBF handle.
      columnname  Name of the column containing the number.
      number  pointer to the location to receive the floating-point value.
      defaultvalue  Value to use if the requested column and value cannot be found.

    RETURN VALUE

    Returns an error code on failure or 0 for success.

    SEE ALSO

    2.3.46 cbf_get_value, cbf_require_value
    2.3.47 cbf_set_value
    2.3.48 cbf_get_typeofvalue
    2.3.49 cbf_set_typeofvalue
    2.3.51 cbf_set_integervalue
    2.3.52 cbf_get_doublevalue, cbf_require_doublevalue
    2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_realarray, cbf_set_realarray_wdims
    2.3.62 cbf_require_column_value
    2.3.63 cbf_require_column_integervalue


    2.3.65 cbf_get_local_integer_byte_order, cbf_get_local_real_byte_order, cbf_get_local_real_format

    PROTOTYPE

    #include "cbf.h"

    int cbf_get_local_integer_byte_order (char ** byte_order);
    int cbf_get_local_real_byte_order (char ** byte_order);
    int cbf_get_local_real_format (char ** real_format );

    DESCRIPTION

    cbf_get_local_integer_byte_order returns the byte order of integers on the machine on which the API is being run in the form of a character string returned as the value pointed to by byte_order. cbf_get_local_real_byte_order returns the byte order of reals on the machine on which the API is being run in the form of a character string returned as the value pointed to by byte_order. cbf_get_local_real_format returns the format of floats on the machine on which the API is being run in the form of a character string returned as the value pointed to by real_format. The strings returned must not be modified in any way.

    The values returned in byte_order may be the strings "little_endian" or "big-endian". The values returned in real_format may be the strings "ieee 754-1985" or "other". Additional values may be returned by future versions of the API.

    ARGUMENTS
      byte_order  pointer to the returned string
      real_format  pointer to the returned string

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.3.66 cbf_get_dictionary, cbf_set_dictionary, cbf_require_dictionary

    PROTOTYPE

    #include "cbf.h"

    int cbf_get_dictionary (cbf_handle handle, cbf_handle * dictionary);
    int cbf_set_dictionary (cbf_handle handle, cbf_handle dictionary_in);
    int cbf_require_dictionary (cbf_handle handle, cbf_handle * dictionary)

    DESCRIPTION

    cbf_get_dictionary sets *dictionary to the handle of a CBF which has been associated with the CBF handle by cbf_set_dictionary. cbf_set_dictionary associates the CBF handle dictionary_in with handle as its dictionary. cbf_require_dictionary sets *dictionary to the handle of a CBF which has been associated with the CBF handle by cbf_set_dictionary or creates a new empty CBF and associates it with handle, returning the new handle in *dictionary.

    ARGUMENTS
      handle  CBF handle.
      dictionary  Pointer to CBF handle of dictionary.
      dictionary_in  CBF handle of dcitionary.
    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.3.67 cbf_convert_dictionary

    PROTOTYPE

    #include "cbf.h"

    int cbf_convert_dictionary (cbf_handle handle, cbf_handle dictionary )

    DESCRIPTION

    cbf_convert_dictionary converts dictionary as a DDL1 or DDL2 dictionary to a CBF dictionary of category and item properties for handle, creating a new dictionary if none exists or layering the definitions in dictionary onto the existing dictionary of handle if one exists.

    If a CBF is read into handle after calling cbf_convert_dictionary, then the dictionary will be used for validation of the CBF as it is read.

    ARGUMENTS
      handle  CBF handle.
      dictionary  CBF handle of dictionary.
    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.3.68 cbf_find_tag, cbf_find_local_tag

    PROTOTYPE

    #include "cbf.h"

    int cbf_find_tag (cbf_handle handle, const char *tag)
    int cbf_find_local_tag (cbf_handle handle, const char *tag)

    DESCRIPTION

    cbf_find_tag searches all of the CBF handle for the CIF tag given by the string tag and makes it the current tag. The search does not include the dictionary, but does include save frames as well as categories.

    The string tag is the complete tag in either DDL1 or DDL2 format, starting with the leading underscore, not just a category or column.

    ARGUMENTS
      handle  CBF handle.
      tag  CIF tag.
    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.3.69 cbf_find_category_root, cbf_set_category_root, cbf_require_category_root

    PROTOTYPE

    #include "cbf.h"

    int cbf_find_category_root (cbf_handle handle, const char* categoryname, const char** categoryroot);
    int cbf_set_category_root (cbf_handle handle, const char* categoryname_in, const char*categoryroot);
    int cbf_require_category_root (cbf_handle handle, const char* categoryname, const char** categoryroot);

    DESCRIPTION

    cbf_find_category_root sets *categoryroot to the root category of which categoryname is an alias. cbf_set_category_root sets categoryname_in as an alias of categoryroot in the dictionary associated with handle, creating the dictionary if necessary. cbf_require_category_root sets *categoryroot to the root category of which categoryname is an alias, if there is one, or to the value of categoryname, if categoryname is not an alias.

    A returned categoryroot string must not be modified in any way.

    ARGUMENTS
      handle  CBF handle.
      categoryname  category name which may be an alias.
      categoryroot  pointer to a returned category root name.
      categoryroot_in  input category root name.
    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.3.70 cbf_find_tag_root, cbf_set_tag_root, cbf_require_tag_root

    PROTOTYPE

    #include "cbf.h"

    int cbf_find_tag_root (cbf_handle handle, const char* tagname, const char** tagroot);
    int cbf_set_tag_root (cbf_handle handle, const char* tagname, const char*tagroot_in);
    int cbf_require_tag_root (cbf_handle handle, const char* tagname, const char** tagroot);

    DESCRIPTION

    cbf_find_tag_root sets *tagroot to the root tag of which tagname is an alias. cbf_set_tag_root sets tagname as an alias of tagroot_in in the dictionary associated with handle, creating the dictionary if necessary. cbf_require_tag_root sets *tagroot to the root tag of which tagname is an alias, if there is one, or to the value of tagname, if tagname is not an alias.

    A returned tagroot string must not be modified in any way.

    ARGUMENTS
      handle  CBF handle.
      tagname  tag name which may be an alias.
      tagroot  pointer to a returned tag root name.
      tagroot_in  input tag root name.
    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.3.71 cbf_find_tag_category, cbf_set_tag_category

    PROTOTYPE

    #include "cbf.h"

    int cbf_find_tag_category (cbf_handle handle, const char* tagname, const char** categoryname);
    int cbf_set_tag_category (cbf_handle handle, const char* tagname, const char* categoryname_in);

    DESCRIPTION

    cbf_find_tag_category sets categoryname to the category associated with tagname in the dictionary associated with handle. cbf_set_tag_category upddates the dictionary associated with handle to indicated that tagname is in category categoryname_in.

    ARGUMENTS
      handle  CBF handle.
      tagname  tag name.
      categoryname  pointer to a returned category name.
      categoryname_in  input category name.
    RETURN VALUE

    Returns an error code on failure or 0 for success.



    2.4 High-level function prototypes

    2.4.1 cbf_read_template

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_read_template (cbf_handle handle, FILE *file);

    DESCRIPTION

    cbf_read_template reads the CBF or CIF file file into the CBF object specified by handle and selects the first datablock as the current datablock.

    ARGUMENTS
      handle  Pointer to a CBF handle.
      file  Pointer to a file descriptor.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.2 cbf_get_diffrn_id, cbf_require_diffrn_id

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_diffrn_id (cbf_handle handle, const char **diffrn_id);
    int cbf_require_diffrn_id (cbf_handle handle, const char **diffrn_id, const char *default_id)

    DESCRIPTION

    cbf_get_diffrn_id sets *diffrn_id to point to the ASCII value of the "diffrn.id" entry. cbf_require_diffrn_id also sets *diffrn_id to point to the ASCII value of the "diffrn.id" entry, but, if the "diffrn.id" entry does not exist, it sets the value in the CBF and in*diffrn_id to the character string given by default_id, creating the category and column is necessary.

    The diffrn_id will be valid as long as the item exists and has not been set to a new value.

    The diffrn_id must not be modified by the program in any way.

    ARGUMENTS
      handle  CBF handle.
      diffrn_id  Pointer to the destination value pointer.
      default_id  Character string default value.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.3 cbf_set_diffrn_id

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_set_diffrn_id (cbf_handle handle, const char *diffrn_id);

    DESCRIPTION

    cbf_set_diffrn_id sets the "diffrn.id" entry of the current datablock to the ASCII value diffrn_id.

    This function also changes corresponding "diffrn_id" entries in the "diffrn_source", "diffrn_radiation", "diffrn_detector" and "diffrn_measurement" categories.

    ARGUMENTS
      handle  CBF handle.
      diffrn_id  ASCII value.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.4 cbf_get_crystal_id

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_crystal_id (cbf_handle handle, const char **crystal_id);

    DESCRIPTION

    cbf_get_crystal_id sets *crystal_id to point to the ASCII value of the "diffrn.crystal_id" entry.

    If the value is not ASCII, the function returns CBF_BINARY.

    The value will be valid as long as the item exists and has not been set to a new value.

    The value must not be modified by the program in any way.

    ARGUMENTS
      handle  CBF handle.
      crystal_id  Pointer to the destination value pointer.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.5 cbf_set_crystal_id

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_set_crystal_id (cbf_handle handle, const char *crystal_id);

    DESCRIPTION

    cbf_set_crystal_id sets the "diffrn.crystal_id" entry to the ASCII value crystal_id.

    ARGUMENTS
      handle  CBF handle.
      crystal_id  ASCII value.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.6 cbf_get_wavelength

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_wavelength (cbf_handle handle, double *wavelength);

    DESCRIPTION

    cbf_get_wavelength sets *wavelength to the current wavelength in Å.

    ARGUMENTS
      handle  CBF handle.
      wavelength  Pointer to the destination.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.7 cbf_set_wavelength

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_set_wavelength (cbf_handle handle, double wavelength);

    DESCRIPTION

    cbf_set_wavelength sets the current wavelength in Å to wavelength.

    ARGUMENTS
      handle  CBF handle.
      wavelength  Wavelength in Å.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.8 cbf_get_polarization

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_polarization (cbf_handle handle, double *polarizn_source_ratio, double *polarizn_source_norm);

    DESCRIPTION

    cbf_get_polarization sets *polarizn_source_ratio and *polarizn_source_norm to the corresponding source polarization parameters.

    Either destination pointer may be NULL.

    ARGUMENTS
      handle  CBF handle.
      polarizn_source_ratio  Pointer to the destination polarizn_source_ratio.
      polarizn_source_norm  Pointer to the destination polarizn_source_norm.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.9 cbf_set_polarization

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_set_polarization (cbf_handle handle, double polarizn_source_ratio, double polarizn_source_norm);

    DESCRIPTION

    cbf_set_polarization sets the source polarization to the values specified by polarizn_source_ratio and polarizn_source_norm.

    ARGUMENTS
      handle  CBF handle.
      polarizn_source_ratio  New value of polarizn_source_ratio.
      polarizn_source_norm  New value of polarizn_source_norm.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.10 cbf_get_divergence

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_divergence (cbf_handle handle, double *div_x_source, double *div_y_source, double *div_x_y_source);

    DESCRIPTION

    cbf_get_divergence sets *div_x_source, *div_y_source and *div_x_y_source to the corresponding source divergence parameters.

    Any of the destination pointers may be NULL.

    ARGUMENTS
      handle  CBF handle.
      div_x_source  Pointer to the destination div_x_source.
      div_y_source  Pointer to the destination div_y_source.
      div_x_y_source  Pointer to the destination div_x_y_source.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.11 cbf_ set_divergence

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_set_divergence (cbf_handle handle, double div_x_source, double div_y_source, double div_x_y_source);

    DESCRIPTION

    cbf_set_divergence sets the source divergence parameters to the values specified by div_x_source, div_y_source and div_x_y_source.

    ARGUMENTS
      handle  CBF handle.
      div_x_source  New value of div_x_source.
      div_y_source  New value of div_y_source.
      div_x_y_source  New value of div_x_y_source.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.12 cbf_count_elements

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_count_elements (cbf_handle handle, unsigned int *elements);

    DESCRIPTION

    cbf_count_elements sets *elements to the number of detector elements.

    ARGUMENTS
      handle  CBF handle.
      elements  Pointer to the destination count.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.13 cbf_get_element_id

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_element_id (cbf_handle handle, unsigned int element_number, const char **element_id);

    DESCRIPTION

    cbf_get_element_id sets *element_id to point to the ASCII value of the element_number'th "diffrn_data_frame.detector_element_id" entry, counting from 0.

    If the detector element does not exist, the function returns CBF_NOTFOUND.

    The element_id will be valid as long as the item exists and has not been set to a new value.

    The element_id must not be modified by the program in any way.

    ARGUMENTS
      handle  CBF handle.
      element_number  The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category.
      element_id  Pointer to the destination.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.14 cbf_get_gain

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_gain (cbf_handle handle, unsigned int element_number, double *gain, double *gain_esd);

    DESCRIPTION

    cbf_get_gain sets *gain and *gain_esd to the corresponding gain parameters for element number element_number.

    Either of the destination pointers may be NULL.

    ARGUMENTS
      handle  CBF handle.
      element_number  The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category.
      gain  Pointer to the destination gain.
      gain_esd  Pointer to the destination gain_esd.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.15 cbf_ set_gain

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_set_gain (cbf_handle handle, unsigned int element_number, double gain, double gain_esd);

    DESCRIPTION

    cbf_set_gain sets the gain of element number element_number to the values specified by gain and gain_esd.

    ARGUMENTS
      handle  CBF handle.
      element_number  The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category.
      gain  New gain value.
      gain_esd  New gain_esd value.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.16 cbf_get_overload

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_overload (cbf_handle handle, unsigned int element_number, double *overload);

    DESCRIPTION

    cbf_get_overload sets *overload to the overload value for element number element_number.

    ARGUMENTS
      handle  CBF handle.
      element_number  The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category.
      overload  Pointer to the destination overload.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.17 cbf_ set_overload

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_set_overload (cbf_handle handle, unsigned int element_number, double overload);

    DESCRIPTION

    cbf_set_overload sets the overload value of element number element_number to overload.

    ARGUMENTS
      handle  CBF handle.
      element_number  The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category.
      overload  New overload value.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.18 cbf_get_integration_time

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_integration_time (cbf_handle handle, unsigned int reserved, double *time);

    DESCRIPTION

    cbf_get_integration_time sets *time to the integration time in seconds. The parameter reserved is presently unused and should be set to 0.

    ARGUMENTS
      handle  CBF handle.
      reserved  Unused. Any value other than 0 is invalid.
      time  Pointer to the destination time.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.19 cbf_set_integration_time

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_set_integration_time (cbf_handle handle, unsigned int reserved, double time);

    DESCRIPTION

    cbf_set_integration_time sets the integration time in seconds to the value specified by time. The parameter reserved is presently unused and should be set to 0.

    ARGUMENTS
      handle  CBF handle.
      reserved  Unused. Any value other than 0 is invalid.
      time Integration  time in seconds.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.20 cbf_get_timestamp

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_timestamp (cbf_handle handle, unsigned int reserved, double *time, int *timezone);

    DESCRIPTION

    cbf_get_timestamp sets *time to the collection timestamp in seconds since January 1 1970. *timezone is set to timezone difference from UTC in minutes. The parameter reserved is presently unused and should be set to 0.

    Either of the destination pointers may be NULL.

    ARGUMENTS
      handle  CBF handle.
      reserved  Unused. Any value other than 0 is invalid.
      time  Pointer to the destination collection timestamp.
      timezone  Pointer to the destination timezone difference.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.21 cbf_set_timestamp

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_set_timestamp (cbf_handle handle, unsigned int reserved, double time, int timezone, double precision);

    DESCRIPTION

    cbf_set_timestamp sets the collection timestamp in seconds since January 1 1970 to the value specified by time. The timezone difference from UTC in minutes is set to timezone. If no timezone is desired, timezone should be CBF_NOTIM EZONE. The parameter reserved is presently unused and should be set to 0.

    The precision of the new timestamp is specified by the value precision in seconds. If precision is 0, the saved timestamp is assumed accurate to 1 second.

    ARGUMENTS
      handle  CBF handle.
      reserved  Unused. Any value other than 0 is invalid.
      time  Timestamp in seconds since January 1 1970.
      timezone  Timezone difference from UTC in minutes or CBF_NOTIMEZONE.
      precision  Timestamp precision in seconds.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.22 cbf_get_datestamp

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_datestamp (cbf_handle handle, unsigned int reserved, int *year, int *month, int *day, int *hour, int *minute, double *second, int *timezone);

    DESCRIPTION

    cbf_get_datestamp sets *year, *month, *day, *hour, *minute and *second to the corresponding values of the collection timestamp. *timezone is set to timezone difference from UTC in minutes. The parameter < i>reserved is presently unused and should be set to 0.

    Any of the destination pointers may be NULL.

    ARGUMENTS
      handle  CBF handle.
      reserved  Unused. Any value other than 0 is invalid.
      year  Pointer to the destination timestamp year.
      month  Pointer to the destination timestamp month (1-12).
      day  Pointer to the destination timestamp day (1-31).
      hour  Pointer to the destination timestamp hour (0-23).
      minute  Pointer to the destination timestamp minute (0-59).
      second  Pointer to the destination timestamp second (0-60.0).
      timezone  Pointer to the destination timezone difference from UTC in minutes.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.23 cbf_set_datestamp

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_set_datestamp (cbf_handle handle, unsigned int reserved, int year, int month, int day, int hour, int minute, double second, int timezone, double precision);

    DESCRIPTION

    cbf_set_datestamp sets the collection timestamp in seconds since January 1 1970 to the value specified by time. The timezone difference from UTC in minutes is set to timezone. If no timezone is desired, timezone should be CBF_NOTIM EZONE. The parameter reserved is presently unused and should be set to 0.

    The precision of the new timestamp is specified by the value precision in seconds. If precision is 0, the saved timestamp is assumed accurate to 1 second.

    ARGUMENTS
      handleCBF handle.
      reservedUnused. Any value other than 0 is invalid.
      timeTimestamp in seconds since January 1 1970.
      timezoneTimezone difference from UTC in minutes or CBF_NOTIMEZONE.
      precisionTimestamp precision in seconds.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.24 cbf_set_current_timestamp

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_set_current_timestamp (cbf_handle handle, unsigned int reserved, int timezone);

    DESCRIPTION

    cbf_set_current_timestamp sets the collection timestamp to the current time. The timezone difference from UTC in minutes is set to timezone. If no timezone is desired, timezone should be CBF_NOTIMEZONE. If no timezone is used, the timest amp will be UTC. The parameter reserved is presently unused and should be set to 0.

    The new timestamp will have a precision of 1 second.

    ARGUMENTS
      handle  CBF handle.
      reserved  Unused.   Any value other than 0 is invalid.
      timezone  Timezone difference from UTC in minutes or CBF_NOTIMEZONE.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.25 cbf_get_image_size, cbf_get_image_size_fs, cbf_get_image_size_sf,
          cbf_get_3d_image_size, cbf_get_3d_image_size_fs, cbf_get_3d_image_size_sf

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_image_size (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimslow, size_t *ndimfast);
    int cbf_get_image_size_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimfast, size_t *ndimslow);
    int cbf_get_image_size_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimslow, size_t *ndimfast);
     
    int cbf_get_3d_image_size (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimslow, size_t *ndimmid, size_t *ndimfast);
    int cbf_get_3d_image_size_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimfast, size_t *ndimmid, size_t *ndimslow);
    int cbf_get_3d_image_size_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimslow, size_t *ndimmid, size_t *ndimfast);

    DESCRIPTION

    cbf_get_image_size, cbf_get_image_size_fs and cbf_get_image_size_sf set *ndimslow and *ndimfast to the slow and fast dimensions of the image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimfast will be set to 1. If the array is 3-dimensional an error code will be returned. cbf_get_3d_image_size, cbf_get_3d_image_size_fs and cbf_get_3d_image_size_sf set *ndimslow, *ndimmid and *ndimfast to the slowest, next fastest and fastest dimensions, respectively, of the 3D image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimmid and *ndimfast will be set to 1. If the array is 2-dimensional *ndimslow and *ndimmid will be set as for a call to cbf_get_image_size and *ndimfast will be set to 1.

    The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order

    Note that the ordering of dimensions is specified by values of the tag _array_structure_list.precedence with a precedence of 1 for the fastest dimension, 2 for the next slower, etc., which is opposite to the ordering of the dimension arguments for these functions, except for the ones with the _fs suffix..

    Any of the destination pointers may be NULL.

    The parameter reserved is presently unused and should be set to 0.

    ARGUMENTS
      handle  CBF handle.
      reserved  Unused. Any value other than 0 is invalid.
      element_number  The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category.
      ndimslow  Pointer to the destination slowest dimension.
      ndimmid  Pointer to the destination next faster dimension.
      ndimfast  Pointer to the destination fastest dimension.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.26 cbf_get_image, cbf_get_image_fs, cbf_get_image_sf,
          cbf_get_real_image, cbf_get_real_image_fs, cbf_get_real_image_sf,
          cbf_get_3d_image, cbf_get_3d_image_fs, cbf_get_3d_image_sf,
          cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast);
    int cbf_get_image_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimfast, size_t ndimslow);
    int cbf_get_image_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast);
     
    int cbf_get_real_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimslow, size_t ndimfast);
    int cbf_get_real_image_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimfast, size_t ndimslow);
    int cbf_get_real_image_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimslow, size_t ndimfast);
     
    int cbf_get_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast);
    int cbf_get_3d_image_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimfast, size_t ndimmid, size_t ndimslow);
    int cbf_get_3d_image_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast);
     
    int cbf_get_real_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast);
    int cbf_get_real_3d_image_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimfast, size_t ndimmid, size_t ndimslow);
    int cbf_get_real_3d_image_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast);

    DESCRIPTION

    cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image array for element number element_number into an array. The array consists of ndimslow×ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and cbf_get_real_image_sf read the image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. cbf_get_3d_image, cbf_get_3d_image_fs and cbf_get_3d_image_sf read the 3D image array for element number element_number into an array. The array consists of ndimslow×ndimmid×ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed.

    The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order

    The structure of the array as a 1-, 2- or 3-dimensional array should agree with the structure of the array given in the ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1 both in the call and in the imgCIF data being processed. If the array is 2-dimensional and a 3D call is used, ndimslow and ndimmid should be the array dimensions and ndimfast should be set to 1 both in the call and in the imgCIF data being processed.

    If any element in the binary data canÕt fit into the destination element, the destination is set the nearest possible value.

    If the value is not binary, the function returns CBF_ASCII.

    If the requested number of elements canÕt be read, the function will read as many as it can and then return CBF_ENDOFDATA.

    Currently, the destination array must consist of chars, shorts or ints (signed or unsigned) for cbf_get_image, or IEEE doubles or floats for cbf_get_real_image. If elsize is not equal to sizeof (char), sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT.

    The parameter reserved is presently unused and should be set to 0.

    ARGUMENTS
      handle  CBF handle.
      reserved  Unused. Any value other than 0 is invalid.
      element_number  The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category.
      array  Pointer to the destination array.
      elsize  Size in bytes of each destination array element.
      elsigned  Set to non-0 if the destination array elements are signed.
      ndimslow  Slowest array dimension.
      ndimmid  Next faster array dimension.
      ndimfast  Fastest array dimension.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.27 cbf_set_image, cbf_set_image_fs, cbf_set_image_sf,
          cbf_set_real_image, cbf_set_real_image_fs, cbf_set_real_image_sf,
          cbf_set_3d_image, cbf_set_3d_image, cbf_set_3d_image,
          cbf_set_real_3d_image, cbf_set_real_3d_image_fs, cbf_set_real_3d_image_sf

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_set_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast);
    int cbf_set_image_fs(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimfast, size_t ndimslow);
    int cbf_set_image_sf(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast);
     
    int cbf_set_real_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimslow, size_t ndimfast);
    int cbf_set_real_image_fs(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimfast, size_t ndimslow);
    int cbf_set_real_image_sf(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimslow, size_t ndimfast);
     
    int cbf_set_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast);
    int cbf_set_3d_image_fs(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimfast, size_t ndimmid, size_t ndimslow);
    int cbf_set_3d_image_sf(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast);
     
    int cbf_set_real_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast);
    int cbf_set_real_3d_image_fs(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimfast, size_t ndimmid, size_t ndimslow);
    int cbf_set_real_3d_image_sf(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast);

    DESCRIPTION

    cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image array for element number element_number. The array consists of ndimfast×ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-zero and unsigned otherwise. cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf write the image array for element number element_number. The array consists of ndimfast×ndimslow IEEE double or float elements of elsize bytes each, starting at array. cbf_set_3d_image, cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array for element number element_number. The array consists of ndimfast×ndimmid×ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_set_real_3d_image, cbf_set_real_3d_image_fs and cbf_set_real_3d_image_sf writes the 3D image array for element number element_number. The array consists of ndimfast×ndimmid×ndimslow IEEE double or float elements of elsize bytes each, starting at array.

    The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order

    If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the array is 2-dimensional and the 3D calls are used, ndimslow and ndimmid should be used for the array dimensions and ndimfast should be set to 1.

    The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are:

    CBF_CANONICALCanonical-code compression (section 3.3.1)
    CBF_PACKEDCCP4-style packing (section 3.3.2)
    CBF_PACKED_V2  CCP4-style packing, version 2 (section 3.3.2)
    CBF_BYTE_OFFSET  Simple "byte_offset" compression.
    CBF_NONENo compression.

    The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value.

    Currently, the source array must consist of chars, shorts or ints (signed or unsigned)for cbf_set_image, or IEEE doubles or floats for cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT.

    The parameter reserved is presently unused and should be set to 0.

    ARGUMENTS
      handle  CBF handle.
      reserved  Unused. Any value other than 0 is invalid.
      element_number  The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category.
      compression  Compression type.
      array  Pointer to the image array.
      elsize  Size in bytes of each image array element.
      elsigned  Set to non-0 if the image array elements are signed.
      ndimslow  Slowest array dimension.
      ndimmid  Second slowest array dimension.
      ndimfast  Fastest array dimension.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.28 cbf_get_axis_setting

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_axis_setting (cbf_handle handle, unsigned int reserved, const char *axis_id, double *start, double *increment);

    DESCRIPTION

    cbf_get_axis_setting sets *start and *increment to the corresponding values of the axis axis_id.

    Either of the destination pointers may be NULL.

    The parameter reserved is presently unused and should be set to 0.

    ARGUMENTS
      handle  CBF handle.
      reserved  Unused. Any value other than 0 is invalid.
      axis_id  Axis id.
      start  Pointer to the destination start value.
      increment  Pointer to the destination increment value.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.29 cbf_set_axis_setting

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_set_axis_setting (cbf_handle handle, unsigned int reserved, const char *axis_id, double start, double increment);

    DESCRIPTION

    cbf_set_axis_setting sets the starting and increment values of the axis axis_id to start and increment.

    The parameter reserved is presently unused and should be set to 0.

    ARGUMENTS
      handle  CBF handle.
      reserved  Unused. Any value other than 0 is invalid.
      axis_id  Axis id.
      start  Start value.
      increment  Increment value.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.30 cbf_construct_goniometer

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_construct_goniometer (cbf_handle handle, cbf_goniometer *goniometer);

    DESCRIPTION

    cbf_construct_goniometer constructs a goniometer object using the description in the CBF object handle and initialises the goniometer handle *goniometer.

    ARGUMENTS
      handle  CBF handle.
      goniometer  Pointer to the destination goniometer handle.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.31 cbf_free_goniometer

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_free_goniometer (cbf_goniometer goniometer);

    DESCRIPTION

    cbf_free_goniometer destroys the goniometer object specified by goniometer and frees all associated memory.

    ARGUMENTS
      goniometer  Goniometer handle to free.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.32 cbf_get_rotation_axis

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_rotation_axis (cbf_goniometer goniometer, unsigned int reserved, double *vector1, double *vector2, double *vector3);

    DESCRIPTION

    cbf_get_rotation_axis sets *vector1, *vector2, and *vector3 to the 3 components of the goniometer rotation axis used for the exposure.

    Any of the destination pointers may be NULL.

    The parameter reserved is presently unused and should be set to 0.

    ARGUMENTS
      goniometer  Goniometer handle.
      reserved  Unused. Any value other than 0 is invalid.
      vector1  Pointer to the destination x component of the rotation axis.
      vector2  Pointer to the destination y component of the rotation axis.
      vector3  Pointer to the destination z component of the rotation axis.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.33 cbf_get_rotation_range

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_rotation_range (cbf_goniometer goniometer, unsigned int reserved, double *start, double *increment);

    DESCRIPTION

    cbf_get_rotation_range sets *start and *increment to the corresponding values of the goniometer rotation axis used for the exposure.

    Either of the destination pointers may be NULL.

    The parameter reserved is presently unused and should be set to 0.

    ARGUMENTS
      goniometer  Goniometer handle.
      reserved  Unused. Any value other than 0 is invalid.
      start  Pointer to the destination start value.
      increment  Pointer to the destination increment value.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.34 cbf_rotate_vector

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_rotate_vector (cbf_goniometer goniometer, unsigned int reserved, double ratio, double initial1, double initial2, double initial3, double *final1, double *final2, double *final3);

    DESCRIPTION

    cbf_rotate_vector sets *final1, *final2, and *final3 to the 3 components of the of the vector (initial1, initial2, initial3) after reorientation by applying the goniometer rotations. The value ratio specif ies the goniometer setting and varies from 0.0 at the beginning of the exposure to 1.0 at the end, irrespective of the actual rotation range.

    Any of the destination pointers may be NULL.

    The parameter reserved is presently unused and should be set to 0.

    ARGUMENTS
      goniometer  Goniometer handle.
      reserved  Unused. Any value other than 0 is invalid.
      ratio  Goniometer setting. 0 = beginning of exposure, 1 = end.
      initial1  x component of the initial vector.
      initial2  y component of the initial vector.
      initial3  z component of the initial vector.
      vector1  Pointer to the destination x component of the final vector.
      vector2  Pointer to the destination y component of the final vector.
      vector3  Pointer to the destination z component of the final vector.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.35 cbf_get_reciprocal

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_reciprocal (cbf_goniometer goniometer, unsigned int reserved, double ratio, double wavelength, double real1, double real2, double real3, double *reciprocal1, double *reciprocal2, double *reciprocal3);

    DESCRIPTION

    cbf_get_reciprocal sets *reciprocal1, * reciprocal2, and * reciprocal3 to the 3 components of the of the reciprocal-space vector corresponding to the real-space vector (real1, real2, real3). The reciprocal-space vector is oriented to correspond to the goniometer setting with all axes at 0. The value wavelength is the wavlength in Å and the value ratio specifies the current goniometer setting and varies from 0.0 at the beginning of the exposur e to 1.0 at the end, irrespective of the actual rotation range.

    Any of the destination pointers may be NULL.

    The parameter reserved is presently unused and should be set to 0.

    ARGUMENTS
      goniometer  Goniometer handle.
      reserved  Unused. Any value other than 0 is invalid.
      ratio  Goniometer setting. 0 = beginning of exposure, 1 = end.
      wavelength  Wavelength in Å.
      real1  x component of the real-space vector.
      real2  y component of the real-space vector.
      real3  z component of the real-space vector.
      reciprocal1  Pointer to the destination x component of the reciprocal-space vector.
      reciprocal2  Pointer to the destination y component of the reciprocal-space vector.
      reciprocal3  Pointer to the destination z component of the reciprocal-space vector.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.36 cbf_construct_detector, cbf_construct_reference_detector, cbf_require_reference_detector

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_construct_detector (cbf_handle handle, cbf_detector *detector, unsigned int element_number);

    int cbf_construct_reference_detector (cbf_handle handle, cbf_detector *detector, unsigned int element_number);

    int cbf_require_reference_detector (cbf_handle handle, cbf_detector *detector, unsigned int element_number);

    DESCRIPTION

    cbf_construct_detector constructs a detector object for detector element number element_number using the description in the CBF object handle and initialises the detector handle *detector.

    cbf_construct_reference_detector constructs a detector object for detector element number element_number using the description in the CBF object handle and initialises the detector handle *detector using the reference settings of the axes. cbf_require_reference_detector is similar, but try to force the creations of missing intermediate categories needed to construct a detector object.

    ARGUMENTS
      handle  CBF handle.
      detector  Pointer to the destination detector handle.
      element_number  The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.37 cbf_free_detector

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_free_detector (cbf_detector detector);

    DESCRIPTION

    cbf_free_detector destroys the detector object specified by detector and frees all associated memory.

    ARGUMENTS
      detector  Detector handle to free.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.38 cbf_get_beam_center, cbf_get_beam_center_fs, cbf_get_beam_center_sf,
          cbf_set_beam_center, cbf_set_beam_center_fs, cbf_set_beam_center_sf,
          set_reference_beam_center, set_reference_beam_center_fs, set_reference_beam_center_fs

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_beam_center (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast);
    int cbf_get_beam_center_fs (cbf_detector detector, double *indexfast, double *indexslow, double *centerfast, double *centerslow);
    int cbf_get_beam_center_sf (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast);

    int cbf_set_beam_center (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast);
    int cbf_set_beam_center_fs (cbf_detector detector, double *indexfast, double *indexslow, double *centerfast, double *centerslow);
    int cbf_set_beam_center_sf (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast);

    int cbf_set_reference_beam_center (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast);
    int cbf_set_reference_beam_center_fs (cbf_detector detector, double *indexfast, double *indexslow, double *centerfast, double *centerslow);
    int cbf_set_reference_beam_center_sf (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast);

    DESCRIPTION

    cbf_get_beam_center sets *centerfast and *centerslow to the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector and *indexfast and *indexslow to the corresponding indices. cbf_set_beam_center sets the offsets in the axis category for the detector element axis with precedence 1 to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given *indexfast and *indexslow. cbf_set_reference_beam_center sets the displacments in the array_structure_list_axis category to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given by *indexfast and *indexslow. In order to achieve consistent results, a reference detector should be used for detector to have all axes at their reference settings.

    Note that the precedence 1 axis is the fastest axis, so that *centerfast and *indexfast are the fast axis components of the center and *centerslow and *indexslow are the slow axis components of the center.

    The _fs calls give the displacments in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the displacements in slow-to-fast order

    Any of the destination pointers may be NULL for getting the beam center. For setting the beam axis, either the indices of the center must not be NULL.

    The indices are non-negative for beam centers within the detector surface, but the center for an axis with a negative increment will be negative for a beam center within the detector surface.

    For cbf_set_beam_center if the diffrn_data_frame category exists with a row for the corresponding element id, the values will be set for _diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in millimetres and the value of _diffrn_data_frame.center_units will be set to 'mm'.

    For cbf_set_reference_beam_center if the diffrn_detector_element category exists with a row for the corresponding element id, the values will be set for _diffrn_detector_element.reference_center_fast and _diffrn_detector_element.reference_center_slow in millimetres and the value of _diffrn_detector_element.reference_units will be set to 'mm'.

    ARGUMENTS
      detector  Detector handle.
      indexfast  Pointer to the destination fast index.
      indexslow  Pointer to the destination slow index.
      centerfast  Pointer to the destination displacement along the fast axis.
      centerslow  Pointer to the destination displacement along the slow axis.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.39 cbf_get_detector_distance

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_detector_distance (cbf_detector detector, double *distance);

    DESCRIPTION

    cbf_get_detector_distance sets *distance to the nearest distance from the sample position to the detector plane.

    ARGUMENTS
      detector  Detector handle.
      distance  Pointer to the destination distance.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.40 cbf_get_detector_normal

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_detector_normal (cbf_detector detector, double *normal1, double *normal2, double *normal3);

    DESCRIPTION

    cbf_get_detector_normal sets *normal1, *normal2, and *normal3 to the 3 components of the of the normal vector to the detector plane. The vector is normalized.

    Any of the destination pointers may be NULL.

    ARGUMENTS
      detector  Detector handle.
      normal1  Pointer to the destination x component of the normal vector.
      normal2  Pointer to the destination y component of the normal vector.
      normal3  Pointer to the destination z component of the normal vector.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.41 cbf_get_detector_axis_slow, cbf_get_detector_axis_slow, cbf_get_detector_axes, cbf_get_detector_axes_fs, cbf_get_detector_axes_sf

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_detector_axis_slow (cbf_detector detector, double *slowaxis1, double *slowaxis2, double *slowaxis3);
    int cbf_get_detector_axis_fast (cbf_detector detector, double *fastaxis1, double *fastaxis2, double *fastaxis3);
    int cbf_get_detector_axes (cbf_detector detector, double *slowaxis1, double *slowaxis2, double *slowaxis3, double *fastaxis1, double *fastaxis2, double *fastaxis3);
    int cbf_get_detector_axes_fs (cbf_detector detector, double *fastaxis1, double *fastaxis2, double *fastaxis3, double *slowaxis1, double *slowaxis2, double *slowaxis3);
    int cbf_get_detector_axes_sf (cbf_detector detector, double *slowaxis1, double *slowaxis2, double *slowaxis3, double *fastaxis1, double *fastaxis2, double *fastaxis3);

    DESCRIPTION

    cbf_get_detector_axis_slow sets *slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the slow axis of the specified detector at the current settings of all axes. cbf_get_detector_axis_slow sets *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 components of the fast axis of the specified detector at the current settings of all axes. cbf_get_detector_axes, cbf_get_detector_axes_fs and int cbf_get_detector_axes_sf set *slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the slow axis and *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 components of the fast axis of the specified detector at the current settings of all axes.

    Any of the destination pointers may be NULL.

    ARGUMENTS
      detector  Detector handle.
      slowaxis1  Pointer to the destination x component of the slow axis vector.
      slowaxis2  Pointer to the destination y component of the slow axis vector.
      slowaxis3  Pointer to the destination z component of the slow axis vector.
      fastaxis1  Pointer to the destination x component of the fast axis vector.
      fastaxis2  Pointer to the destination y component of the fast axis vector.
      fastaxis3  Pointer to the destination z component of the fast axis vector.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.42 cbf_get_pixel_coordinates, cbf_get_pixel_coordinates_fs, cbf_get_pixel_coordinates_sf

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_pixel_coordinates (cbf_detector detector, double indexslow, double indexfast, double *coordinate1, double *coordinate2, double *coordinate3);
    int cbf_get_pixel_coordinates_fs (cbf_detector detector, double indexfast, double indexslow, double *coordinate1, double *coordinate2, double *coordinate3);
    int cbf_get_pixel_coordinates_sf (cbf_detector detector, double indexslow, double indexfast, double *coordinate1, double *coordinate2, double *coordinate3);

    DESCRIPTION

    cbf_get_pixel_coordinates, cbf_get_pixel_coordinates_fs and cbf_get_pixel_coordinates_sf ses *coordinate1, *coordinate2, and *coordinate3 to the vector position of pixel (indexfast, indexslow) on the detector surface. If indexslow and indexfast are integers then the coordinates correspond to the center of a pixel.

    Any of the destination pointers may be NULL.

    ARGUMENTS
      detector  Detector handle.
      indexslow  Slow index.
      indexfast  Fast index.
      coordinate1  Pointer to the destination x component.
      coordinate2  Pointer to the destination y component.
      coordinate3  Pointer to the destination z component.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.43 cbf_get_pixel_normal, cbf_get_pixel_normal_fs, cbf_get_pixel_normal_sf

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_pixel_normal (cbf_detector detector, double indexslow, double indexfast, double *normal1, double *normal2, double *normal3);
    int cbf_get_pixel_normal_fs (cbf_detector detector, double indexfast, double indexslow, double *normal1, double *normal2, double *normal3);
    int cbf_get_pixel_normal (cbf_detector detector, double indexslow, double indexfast, double *normal1, double *normal2, double *normal3);

    DESCRIPTION

    cbf_get_detector_normal, cbf_get_pixel_normal_fs and cbf_get_pixel_normal_sf set *normal1, *normal2, and *normal3 to the 3 components of the of the normal vector to the pixel at (indexfast, indexslow). The vector is normalized.

    Any of the destination pointers may be NULL.

    ARGUMENTS
      detector  Detector handle.
      indexslow  Slow index.
      indexfast  Fast index.
      normal1  Pointer to the destination x component of the normal vector.
      normal2  Pointer to the destination y component of the normal vector.
      normal3  Pointer to the destination z component of the normal vector.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.44 cbf_get_pixel_area, cbf_get_pixel_area_fs, cbf_get_pixel_area_sf

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_pixel_area (cbf_detector detector, double indexslow, double indexfast, double *area, double *projected_area);
    int cbf_get_pixel_area_fs(cbf_detector detector, double indexfast, double indexslow, double *area, double *projected_area);
    int cbf_get_pixel_area_sf(cbf_detector detector, double indexslow, double indexfast, double *area, double *projected_area);

    DESCRIPTION

    cbf_get_pixel_area, cbf_get_pixel_area_fs and cbf_get_pixel_area_sf set *area to the area of the pixel at (indexfast, indexslow) on the detector surface and *projected_area to the apparent area of the pixel as viewed from the sample position, with indexslow being the slow axis and indexfast being the fast axis.

    Either of the destination pointers may be NULL.

    ARGUMENTS
      detector  Detector handle.
      indexfast  Fast index.
      indexslow  Slow index.
      area  Pointer to the destination area in mm2.
      projected_area  Pointer to the destination apparent area in mm2.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.45 cbf_get_pixel_size, cbf_get_pixel_size_fs, cbf_get_pixel_size_sf

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_pixel_size (cbf_handle handle, unsigned int element_number, int axis_number, double *psize);
    int cbf_get_pixel_size_fs(cbf_handle handle, unsigned int element_number, int axis_number, double *psize);
    int cbf_get_pixel_size_sf(cbf_handle handle, unsigned int element_number, int axis_number, double *psize);

    DESCRIPTION

    cbf_get_pixel_size and cbf_get_pixel_size_sf set *psize to point to the double value in millimeters of the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the slowest axis. cbf_get_pixel_size_fs sets *psize to point to the double value in millimeters of the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the fastest axis.

    If a negative axis number is given, the order of axes is reversed, so that -1 specifies the slowest axis for cbf_get_pixel_size_fs and the fastest axis for cbf_get_pixel_size_sf.

    If the pixel size is not given explcitly in the "array_element_size" category, the function returns CBF_NOTFOUND.

    ARGUMENTS
      handle  CBF handle.
      element_number  The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category.
      axis_number  The number of the axis, starting from 1 for the fastest for cbf_get_pixel_size and cbf_get_pixel_size_fs and the slowest for cbf_get_pixel_size_sf.
      psize  Pointer to the destination pixel size.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.46 cbf_set_pixel_size, cbf_set_pixel_size_fs, cbf_set_pixel_size_sf

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_set_pixel_size (cbf_handle handle, unsigned int element_number, int axis_number, double psize);
    int cbf_set_pixel_size_fs(cbf_handle handle, unsigned int element_number, int axis_number, double psize);
    int cbf_set_pixel_size_sf(cbf_handle handle, unsigned int element_number, int axis_number, double psize);

    DESCRIPTION

    cbf_set_pixel_size and cbf_set_pixel_size_sf set the item in the "e;size"e; column of the "array_structure_list" category at the row which matches axis axis_number of the detector element element_number converting the double pixel size psize from meters to millimeters in storing it in the "size" column for the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the slowest axis. cbf_set_pixel_size_fs sets the item in the "e;size"e; column of the "array_structure_list" category at the row which matches axis axis_number of the detector element element_number converting the double pixel size psize from meters to millimeters in storing it in the "size" column for the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the fastest axis.

    If a negative axis number is given, the order of axes is reversed, so that -1 specifies the slowest axis for cbf_get_pixel_size_fs and the fastest axis for cbf_get_pixel_size_sf.

    If the "array_structure_list" category does not already exist, it is created.

    If the appropriate row in the "array_structure_list" catgeory does not already exist, it is created.

    If the pixel size is not given explcitly in the "array_element_size category", the function returns CBF_NOTFOUND.

    ARGUMENTS
      handle  CBF handle.
      element_number  The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category.
      axis_number  The number of the axis, fastest first, starting from 1.
      psize  The pixel size in millimeters.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.47 cbf_get_inferred_pixel_size, cbf_get_inferred_pixel_size_fs, cbf_get_inferred_pixel_size_sf

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_inferred_pixel_size (cbf_detector detector, int axis_number, double *psize);
    int cbf_get_inferred_pixel_size_fs(cbf_detector detector, int axis_number, double *psize);
    int cbf_get_inferred_pixel_size_sf(cbf_detector detector, int axis_number, double *psize);

    DESCRIPTION

    cbf_get_inferred_pixel_size, cbf_get_inferred_pixel_size_sf set *psize to point to the double value in millimeters of the pixel size for the axis axis_number value. The slow index is treated as axis 1 and the next faster index is treated as axis 2. cbf_get_inferred_pixel_size_fs sets *psize to point to the double value in millimeters of the pixel size for the axis axis_number value. The fast index is treated as axis 1 and the next slower index is treated as axis 2.

    If the axis number is negative, the axes are used in the reverse order so that an axis_number of -1 indicates the fast axes in a call to cbf_get_inferred_pixel_size or cbf_get_inferred_pixel_size_sf and indicates the fast axis in a call to cbf_get_inferred_pixel_size_fs.

    ARGUMENTS
      detector  Detector handle.
      axis_number  The number of the axis.
      area  Pointer to the destination pizel size in mm.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.48 cbf_get_unit_cell

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_unit_cell (cbf_handle handle, double cell[6], double cell_esd[6] );

    DESCRIPTION

    cbf_get_unit_cell sets cell[0:2] to the double values of the cell edge lengths a, b and c in Ångstroms, cell[3:5] to the double values of the cell angles α, β and γ in degrees, cell_esd[0:2] to the double values of the estimated strandard deviations of the cell edge lengths a, b and c in Ångstroms, cell_esd[3:5] to the double values of the estimated standard deviations of the the cell angles α, β and γ in degrees.

    The values returned are retrieved from the first row of the "cell" category. The value of "_cell.entry_id" is ignored.

    cell or cell_esd may be NULL.

    If cell is NULL, the cell parameters are not retrieved.

    If cell_esd is NULL, the cell parameter esds are not retrieved.

    If the "cell" category is present, but some of the values are missing, zeros are returned for the missing values.

    ARGUMENTS
      handle  CBF handle.
      cell  Pointer to the destination array of 6 doubles for the cell parameters.
      cell_esd  Pointer to the destination array of 6 doubles for the cell parameter esds.

    RETURN VALUE

    Returns an error code on failure or 0 for success. No errors is returned for missing values if the "cell" category exists.

    SEE ALSO

    2.4.49 cbf_set_unit_cell
    2.4.50 cbf_get_reciprocal_cell
    2.4.51 cbf_set_reciprocal_cell
    2.4.52 cbf_compute_cell_volume
    2.4.53 cbf_compute_reciprocal_cell


    2.4.49 cbf_set_unit_cell

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_set_unit_cell (cbf_handle handle, double cell[6], double cell_esd[6] );

    DESCRIPTION

    cbf_set_unit_cell sets the cell parameters to the double values given in cell[0:2] for the cell edge lengths a, b and c in Ångstroms, the double values given in cell[3:5] for the cell angles α, β and γ in degrees, the double values given in cell_esd[0:2] for the estimated strandard deviations of the cell edge lengths a, b and c in Ångstroms, and the double values given in cell_esd[3:5] for the estimated standard deviations of the the cell angles α, β and γ in degrees.

    The values are placed in the first row of the "cell" category. If no value has been given for "_cell.entry_id", it is set to the value of the "diffrn.id" entry of the current data block.

    cell or cell_esd may be NULL.

    If cell is NULL, the cell parameters are not set.

    If cell_esd is NULL, the cell parameter esds are not set.

    If the "cell" category is not present, it is created. If any of the necessary columns are not present, they are created.

    ARGUMENTS
      handle  CBF handle.
      cell  Pointer to the array of 6 doubles for the cell parameters.
      cell_esd  Pointer to the array of 6 doubles for the cell parameter esds.

    RETURN VALUE

    Returns an error code on failure or 0 for success.

    SEE ALSO

    2.4.48 cbf_get_unit_cell
    2.4.50 cbf_get_reciprocal_cell
    2.4.51 cbf_set_reciprocal_cell
    2.4.52 cbf_compute_cell_volume
    2.4.53 cbf_compute_reciprocal_cell


    SEE ALSO

    2.4.50 cbf_get_reciprocal_cell

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_reciprocal_cell (cbf_handle handle, double cell[6], double cell_esd[6] );

    DESCRIPTION

    cbf_get_reciprocal_cell sets cell[0:2] to the double values of the reciprocal cell edge lengths a*, b* and c* in Ångstroms-1, cell[3:5] to the double values of the reciprocal cell angles α*, β* and γ* in degrees, cell_esd[0:2] to the double values of the estimated strandard deviations of the reciprocal cell edge lengths a*, b* and c* in Ångstroms-1, cell_esd[3:5] to the double values of the estimated standard deviations of the the reciprocal cell angles α*, β* and γ* in degrees.

    The values returned are retrieved from the first row of the "cell" category. The value of "_cell.entry_id" is ignored.

    cell or cell_esd may be NULL.

    If cell is NULL, the reciprocal cell parameters are not retrieved.

    If cell_esd is NULL, the reciprocal cell parameter esds are not retrieved.

    If the "cell" category is present, but some of the values are missing, zeros are returned for the missing values.

    ARGUMENTS
      handle  CBF handle.
      cell  Pointer to the destination array of 6 doubles for the reciprocal cell parameters.
      cell_esd  Pointer to the destination array of 6 doubles for the reciprocal cell parameter esds.

    RETURN VALUE

    Returns an error code on failure or 0 for success. No errors is returned for missing values if the "cell" category exists.

    SEE ALSO

    2.4.48 cbf_get_unit_cell
    2.4.49 cbf_set_unit_cell
    2.4.51 cbf_set_reciprocal_cell
    2.4.52 cbf_compute_cell_volume
    2.4.53 cbf_compute_reciprocal_cell


    2.4.51 cbf_set_reciprocal_cell

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_set_reciprocal_cell (cbf_handle handle, double cell[6], double cell_esd[6] );

    DESCRIPTION

    cbf_set_reciprocal_cell sets the reciprocal cell parameters to the double values given in cell[0:2] for the reciprocal cell edge lengths a*, b* and c* in Ångstroms-1, the double values given in cell[3:5] for the reciprocal cell angles α*, β* and γ* in degrees, the double values given in cell_esd[0:2] for the estimated strandard deviations of the reciprocal cell edge lengths a*, b* and c* in Ångstroms, and the double values given in cell_esd[3:5] for the estimated standard deviations of the reciprocal cell angles α*, β* and γ* in degrees.

    The values are placed in the first row of the "cell" category. If no value has been given for "_cell.entry_id", it is set to the value of the "diffrn.id" entry of the current data block.

    cell or cell_esd may be NULL.

    If cell is NULL, the reciprocal cell parameters are not set.

    If cell_esd is NULL, the reciprocal cell parameter esds are not set.

    If the "cell" category is not present, it is created. If any of the necessary columns are not present, they are created.

    ARGUMENTS
      handle  CBF handle.
      cell  Pointer to the array of 6 doubles for the reciprocal cell parameters.
      cell_esd  Pointer to the array of 6 doubles for the reciprocal cell parameter esds.

    RETURN VALUE

    Returns an error code on failure or 0 for success.

    SEE ALSO

    2.4.48 cbf_get_unit_cell
    2.4.49 cbf_set_unit_cell
    2.4.50 cbf_get_reciprocal_cell
    2.4.52 cbf_compute_cell_volume
    2.4.53 cbf_compute_reciprocal_cell


    2.4.52 cbf_compute_cell_volume

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_compute_cell_volume ( double cell[6], double *volume );

    DESCRIPTION

    cbf_compute_cell_volume sets *volume to point to the volume of the unit cell computed from the double values in cell[0:2] for the cell edge lengths a, b and c in Ångstroms and the double values given in cell[3:5] for the cell angles α, β and γ in degrees.

    ARGUMENTS
      cell  Pointer to the array of 6 doubles giving the cell parameters.
      volume  Pointer to the doubles for cell volume.

    RETURN VALUE

    Returns an error code on failure or 0 for success.

    SEE ALSO

    2.4.48 cbf_get_unit_cell
    2.4.49 cbf_set_unit_cell
    2.4.50 cbf_get_reciprocal_cell
    2.4.51 cbf_set_reciprocal_cell
    2.4.53 cbf_compute_reciprocal_cell


    2.4.53 cbf_compute_reciprocal_cell

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_compute_reciprocal_cell ( double cell[6], double rcell[6] );

    DESCRIPTION

    cbf_compute_reciprocal_cell sets rcell to point to the array of reciprocal cell parameters computed from the double values cell[0:2] giving the cell edge lengths a, b and c in Ångstroms, and the double values cell[3:5] giving the cell angles α, β and γ in degrees. The double values rcell[0:2] will be set to the reciprocal cell lengths a*, b* and c* in Ångstroms-1 and the double values rcell[3:5] will be set to the reciprocal cell angles α*, β* and γ* in degrees.

    ARGUMENTS
      cell  Pointer to the array of 6 doubles giving the cell parameters.
      rcell  Pointer to the destination array of 6 doubles giving the reciprocal cell parameters.
      volume  Pointer to the doubles for cell volume.

    RETURN VALUE

    Returns an error code on failure or 0 for success.

    SEE ALSO

    2.4.48 cbf_get_unit_cell
    2.4.49 cbf_set_unit_cell
    2.4.50 cbf_get_reciprocal_cell
    2.4.51 cbf_set_reciprocal_cell
    2.4.52 cbf_compute_cell_volume


    2.4.54 cbf_get_orientation_matrix, cbf_set_orientation_matrix

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_orientation_matrix (cbf_handle handle, double ub_matrix[9]);
    int cbf_set_orientation_matrix (cbf_handle handle, double ub_matrix[9]);

    DESCRIPTION

    cbf_get_orientation_matrix sets ub_matrix to point to the array of orientation matrix entries in the "diffrn" category in the order of columns:

    "UB[1][1]" "UB[1][2]" "UB[1][3]"
    "UB[2][1]" "UB[2][2]" "UB[2][3]"
    "UB[3][1]" "UB[3][2]" "UB[3][3]"

    cbf_set_orientation_matrix sets the values in the "diffrn" category to the values pointed to by ub_matrix.

    ARGUMENTS
      handle  CBF handle.
      ubmatric  Source or destination array of 9 doubles giving the orientation matrix parameters.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.4.55 cbf_get_bin_sizes, cbf_set_bin_sizes

    PROTOTYPE

    #include "cbf_simple.h"

    int cbf_get_bin_sizes(cbf_handle handle, unsigned int element_number, double * slowbinsize, double * fastbinsize);
    int cbf_set_bin_sizes(cbf_handle handle, unsigned int element_number, double slowbinsize_in,double fastbinsize_in);

    DESCRIPTION

    cbf_get_bin_sizes sets slowbinsize to point to the value of the number of pixels composing one array element in the dimension that changes at the second-fastest rate and fastbinsize to point to the value of the number of pixels composing one array element in the dimension that changes at the fastest rate for the dectector element with the ordinal element_number. cbf_set_bin_sizes sets the the pixel bin sizes in the "array_intensities" category to the values of slowbinsize_in for the number of pixels composing one array element in the dimension that changes at the second-fastest rate and fastbinsize_in for the number of pixels composing one array element in the dimension that changes at the fastest rate for the dectector element with the ordinal element_number.

    In order to allow for software binning involving fractions of pixels, the bin sizes are doubles rather than ints.

    ARGUMENTS
      handle  CBF handle.
      element_number  The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category.
      slowbinsize  Pointer to the returned number of pixels composing one array element in the dimension that changes at the second-fastest rate.
      fastbinsize  Pointer to the returned number of pixels composing one array element in the dimension that changes at the fastest rate.
      slowbinsize_in  The number of pixels composing one array element in the dimension that changes at the second-fastest rate.
      fastbinsize_in  The number of pixels composing one array element in the dimension that changes at the fastest rate.

    RETURN VALUE

    Returns an error code on failure or 0 for success.


    2.5 F90 function interfaces

    At the suggestion of W. Kabsch, Fortran 90/95 routines have been added to CBFlib. As of this writing code has been written to allow the reading of CBF_BYTE_OFFSET, CBF_PACKED and CBF_PACKED_V2 binary images. This code has been gather into FCBlib (Fortran Crystallographic Binary library) as lib/libfcb.

    In general, most of the FCBlib functions return 0 for normal completion and a non-zero value in case of an error. In a few cases, such as FCB_ATOL_WCNT and FCB_NBLEN_ARRAY in order to conform to the conventions for commonly used C-equivalent functions, the function return is the value being computed.

    For each function, an interface is given to be included in the declarations of your Fortran 90/95 code. Some functions in FCBlIB are not intended for external use and are subject to change: FCB_UPDATE_JPA_POINTERS_I2, FCB_UPDATE_JPA_POINTERS_I4, FCB_UPDATE_JPA_POINTERS_3D_I2, FCB_UPDATE_JPA_POINTERS_3D_I4 and CNT2PIX. These names should not be used for user routines.

    The functions involving reading of a CBF have been done strictly in Fortran without the use of C code. This has required some compromises and the use of direct access I/O. Rather than putting the buffer and its control variables into COMMON these are passed as local arguments to make the routines inherently 'threadsafe' in a parallel programming environment. Note also, that a reading error could occur for the last record if it does not fill a full block. The code is written to recover from end-of-record and end-of-file errors, if possible. On many modern system, no special action is required, but on some systems it may be necessary to make use of the padding between the end of binary data and the terminal MIME boundary marker in binary sections. To ensure maximum portability of CBF files, a padding of 4095 bytes is recommended. Existing files without padding can be converted to files with padding by use of the new -p4 option for cif2cbf.

    2.5.1 FCB_ATOL_WCNT

          INTERFACE
          INTEGER(8) FUNCTION FCB_ATOL_WCNT(ARRAY, N, CNT)
          INTEGER(1),INTENT(IN):: ARRAY(N)
          INTEGER,   INTENT(IN):: N
          INTEGER,  INTENT(OUT):: CNT
          END FUNCTION
          END INTERFACE

    FCB_ATOL_WCNT converts INTEGER(1) bytes in ARRAY of N bytes to an INTEGER(8) value returned as the function value. The number of bytes of ARRAY actually used before encountering a character not used to form the number is returned in CNT.

    The scan stops at the first byte in ARRAY that cannot be properly parsed as part of the integer result.

    ARGUMENTS
      ARRAY  The array of INTEGER(1) bytes to be scanned
      N  The INTEGER size of ARRAY
      CNT  The INTEGER size of the portion of ARRAY scanned.

    RETURN VALUE

    Returns the INTEGER(8) value derived from the characters ARRAY(1:CNT) scanned.


    2.5.2 FCB_CI_STRNCMPARR

          INTERFACE
          INTEGER FUNCTION FCB_CI_STRNCMPARR(STRING>, ARRAY, N, LIMIT)
          CHARACTER(LEN=*),INTENT(IN):: STRING>
          INTEGER,         INTENT(IN):: N, LIMIT
          INTEGER(1),      INTENT(IN):: ARRAY(N)
          END FUNCTION
          END INTERFACE

    The function FCB_CI_STRNCMPARR compares up to LIMIT characters of character string STRING and INTEGER(1) byte array ARRAY of dimension N in a case-insensitive manner, returning 0 for a match.

    ARGUMENTS
      STRING  A character string
      ARRAY  The array of INTEGER(1) bytes to be scanned
      N  The INTEGER size of ARRAY
      N  The INTEGER limit on the number of characters to consider in the comparison

    RETURN VALUE

    Returns 0 if the string and array match, a non-zero value otherwise.


    2.5.3 FCB_EXIT_BINARY

          INTERFACE
          INTEGER FUNCTION FCB_EXIT_BINARY(TAPIN,LAST_CHAR,FCB_BYTES_IN_REC,&
                                          BYTE_IN_FILE,REC_IN_FILE,BUFFER,  &
                                          PADDING )
          INTEGER,   INTENT(IN)   :: TAPIN,FCB_BYTES_IN_REC
          INTEGER,   INTENT(INOUT):: BYTE_IN_FILE,REC_IN_FILE
          INTEGER(1),INTENT(INOUT):: LAST_CHAR,BUFFER(FCB_BYTES_IN_REC)
          INTEGER(8),INTENT(IN)   :: PADDING
          END FUNCTION
          END INTERFACE

    The function FCB_EXIT_BINARY is used to skip from the end of a binary section past any padding to the end of the text section that encloses the binary section. The values of the arguments must be consistent with those in the last call to FCB_NEXT_BINARY

    ARGUMENTS
      TAPIN  The INTEGER Fortran device unit number assigned to image file.
      LAST_CHAR  The last character (as an INTEGER(1) byte) read.
      FCB_BYTES_IN_REC  The INTEGER number of bytes in a record.
      BYTE_IN_FILE  The INTEGER byte (counting from 1) of the byte to read.
      REC_IN_FILE  The INTEGER record number (counting from 1) of next record to read.
      BUFFER  The INTEGER(1) array of length FCB_BYTES_IN_REC to hold the appropriate record from TAPIN
      PADDING  The INTEGER(8) number of bytes of padding after the binary data and before the closing MIME boundary.

    RETURN VALUE

    Returns 0 if the function is successful. Returns whatever non-zero error value is reported by FCB_READ_LINE if a necessary next line cannot be read.

    SEE ALSO

    2.5.5 FCB_NEXT_BINARY
    2.5.6 FCB_OPEN_CIFIN
    2.5.9 FCB_READ_BYTE
    2.5.11 FCB_READ_LINE


    2.5.4 FCB_NBLEN_ARRAY

          INTERFACE
          INTEGER FUNCTION FCB_NBLEN_ARRAY(ARRAY, ARRAYLEN)
          INTEGER,    INTENT(IN):: ARRAYLEN
          INTEGER(1), INTENT(IN):: ARRAY(ARRAYLEN)
          END FUNCTION
          END INTERFACE

    The function FCB_NBLEN_ARRAY returns the trimmed length of the INTEGER(1) byte array ARRAY of dimension ARRAYLEN after removal of trailing ASCII blanks, horizontal tabs (Z'09'), newlines (Z'0A') and carriage returns (Z'0D'). The resulting length may be zero.

    The INTEGER trimmed length is returned as the function value.

    ARGUMENTS
      ARRAY  The array of bytes for which the trimmed length is required.
      ARRAYLEN  The dimension of the array of bytes to be scanned.

    RETURN VALUE

    Returns the trimmed length of the array ARRAY.


    2.5.5 FCB_NEXT_BINARY

          INTERFACE
          INTEGER FUNCTION FCB_NEXT_BINARY(TAPIN,LAST_CHAR,FCB_BYTES_IN_REC,&
                                          BYTE_IN_FILE,REC_IN_FILE,BUFFER,  &
                                          ENCODING,SIZE,ID,DIGEST,          &
                                          COMPRESSION,BITS,VORZEICHEN,REELL,&
                                          BYTEORDER,DIMOVER,DIM1,DIM2,DIM3, &
                                          PADDING )
          INTEGER,   INTENT(IN)   :: TAPIN,FCB_BYTES_IN_REC
          INTEGER,   INTENT(INOUT):: BYTE_IN_FILE,REC_IN_FILE
          INTEGER(1),INTENT(INOUT):: LAST_CHAR,BUFFER(FCB_BYTES_IN_REC)
          INTEGER,   INTENT(OUT)  :: ENCODING
          INTEGER, INTENT(OUT)        :: SIZE    !Binary size
          INTEGER, INTENT(OUT)        :: ID      !Binary ID
          CHARACTER(len=*),INTENT(OUT):: DIGEST  !Message digest
          INTEGER,         INTENT(OUT):: COMPRESSION
          INTEGER,         INTENT(OUT):: BITS,VORZEICHEN,REELL
          CHARACTER(len=*),INTENT(OUT):: BYTEORDER
          INTEGER(8),      INTENT(OUT):: DIMOVER
          INTEGER(8),      INTENT(OUT):: DIM1
          INTEGER(8),      INTENT(OUT):: DIM2
          INTEGER(8),      INTENT(OUT):: DIM3
          INTEGER(8),      INTENT(OUT):: PADDING
          END FUNCTION
          END INTERFACE

    The function FCB_NEXT_BINARY skips to the start of the next binary section in the image file on unit TAPIN leaving the file positioned for a subsequent read of the image data. The skip may prior to the text field that contains the binary section. When the text filed is reached, it will be scanned for a MIME boundary marker, and, if it is found the subsequence MIME headers will be used to populate the arguments ENCODING, SIZE, ID, DIGEST, COMPRESSION, BITS, VORZEICHEN,REELL, BYTEORDER, DIMOVER, DIM1, DIM2,DIM3, PADDING.

    The value returned in ENCODING is taken from the MIME header Content-Transfer-Encoding as an INTEGER. It is returned as 0 if not specified. The reported value is one of the integer values ENC_NONE (Z'0001') for BINARY encoding, ENC_BASE64 (Z'0002') for BASE64 encoding, ENC_BASE32K (Z'0004') for X-BASE32K encoding, ENC_QP (Z'0008') for QUOTED-PRINTABLE encoding, ENC_BASE10 (Z'0010') for BASE10 encoding, ENC_BASE16 (Z'0020') for BASE16 encoding or ENC_BASE8 (Z'0040') for BASE8 encoding. At this time FCBlib only supports ENC_NONE BINARY encoding.

    The value returned in SIZE is taken from the MIME header X-Binary-Size as an INTEGER. It is returned as 0 if not specified.

    The value returned in ID is taken from the MIME header X-Binary-ID as an INTEGER. It is returned as 0 if not specified.

    The value returned in DIGEST is taken from the MIME header Content-MD5. It is returned as a character string. If no digest is given, an empty string is returned.

    The value returned in COMPRESSION is taken from the MIME header Content-Type in the conversions parameter. The reported value is one of the INTEGER values CBF_CANONICAL (Z'0050'), CBF_PACKED (Z'0060'), CBF_PACKED_V2 (Z'0090'), CBF_BYTE_OFFSET (Z'0070'), CBF_PREDICTOR (Z'0080'), CBF_NONE (Z'0040'). Two flags may be combined with CBF_PACKED or CBF_PACKED_V2: CBF_UNCORRELATED_SECTIONS (Z'0100') or CBF_FLAT_IMAGE (Z'0200'). At this time FCBlib does not support CBF_PREDICTOR or CBF_NONE compression.

    The values returned in BITS, VORZEICHEN and REELL are the parameters of the data types of the elements. These values are taken from the MIME header X-Binary-Element-Type, which has values of the form "signed BITS-bit integer", "unsigned BITS-bit integer", "signed BITS-bit real IEEE" or "signed BITS-bit complex IEEE". If no value is given, REELL is reported as -1. If the value in one of the integer types, REELL is reported as 0. If the value is one of the real or complex types, REELL is reported as 1. In the current release of FCBlib only the integer types for BITS equal to 16 or 32 are supported.

    The value returned in BYTEORDER is the byte order of the data in the image file as reported in the MIME header. The value, if specified, will be either the character string "LITTLE_ENDIAN" or the character string "BIG_ENDIAN". If no byte order is specified, "LITTLE_ENDIAN" is reported. This value is taken from the MIME header X-Binary-Element-Byte-Order. As of this writing, CBFlib will not generate "BIG_ENDIAN" byte-order files. However, both CBFlib and FCBlib read "LITTLE_ENDIAN" byte-order files, even on big-endian machines.

    The value returned in DIMOVER is the overall number of elements in the image array, if specified, or zero, if not specified. This value is taken from the MIME header X-Binary-Number-of-Elements. The values returned in DIM1, DIM2 and DIM3 are the sizes of the fastest changing, second fastest changing and third fastest changing dimensions of the array, if specified, or zero, if not specified. These values are taken from the MIME header X-Binary-Size-Fastest-Dimension, X-Binary-Size-Second-Dimension and X-Binary-Size-Third-Dimension respectively.

    The value returned in PADDING is the size of the post-data padding, if any, if specified or zero, if not specified. The value is given as a count of octets. This value is taken from the MIME header X-Binary-Size-Padding.

    ARGUMENTS
      TAPIN  The INTEGER Fortran device unit number assigned to image file.
      LAST_CHAR  The last character (as an INTEGER(1) byte) read.
      FCB_BYTES_IN_REC  The INTEGER number of bytes in a record.
      BYTE_IN_FILE  The INTEGER byte (counting from 1) of the byte to read.
      REC_IN_FILE  The INTEGER record number (counting from 1) of next record to read.
      BUFFER  The INTEGER(1) array of length FCB_BYTES_IN_REC to hold the appropriate record from TAPIN
      ENCODING  INTEGER type of encoding for the binary section as reported in the MIME header.
      ID  INTEGER binary identifier as reported in the MIME header.
      SIZE  INTEGER size of compressed binary section as reported in the MIME header.
      DIGEST  The MD5 message digest as reported in the MIME header.
      COMPRESSION  INTEGER compression method as reported in the MIME header.
      BITS  INTEGER number of bits in each element as reported in the MIME header.
      VORZEICHEN  INTEGER flag for signed or unsigned elements as reported in the MIME header. Set to 1 if the elements can be read as signed values, 0 otherwise.
      REELL  INTEGER flag for real elements as reported in the MIME header. Set to 1 if the elements can be read as REAL
      BYTEORDER  The byte order as reported in the MIME header.
      DIM1  Pointer to the destination fastest dimension.
      DIM2  Pointer to the destination second fastest dimension.
      DIM3  Pointer to the destination third fastest dimension.
      PADDING  Pointer to the destination padding size.

    RETURN VALUE

    Returns 0 if the function is successful. SEE ALSO

    2.5.3 FCB_EXIT_BINARY
    2.5.6 FCB_OPEN_CIFIN
    2.5.9 FCB_READ_BYTE
    2.5.11 FCB_READ_LINE


    2.5.6 FCB_OPEN_CIFIN

          INTERFACE
          INTEGER FUNCTION FCB_OPEN_CIFIN(FILNAM,TAPIN,LAST_CHAR,                &
          FCB_BYTES_IN_REC,BYTE_IN_FILE,REC_IN_FILE,BUFFER)
          CHARACTER(len=*),INTENT(IN) :: FILNAM
          INTEGER,         INTENT(IN) :: TAPIN,FCB_BYTES_IN_REC
          INTEGER(1),      INTENT(OUT):: LAST_CHAR
          INTEGER,         INTENT(OUT):: BYTE_IN_FILE,REC_IN_FILE
          INTEGER(1),    INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC)
          INTEGER                        FCB_RECORD_SIZE
          END FUNCTION
          END INTERFACE

    The function FCB_OPEN_CIFIN opens the CBF image file given by the file name in the character string FILNAM on the logical unit TAPIN. The calling routine must provide an INTEGER(1) byte buffer BUFFER of some appropriate INTEGER size FCB_BYTES_IN_REC. The size must be chosen to suit the machine, but in most cases, 4096 will work. The values returned in LAST_CHAR, BYTE_IN_FILE, and REC_IN_FILE are for use in subsequent FCBlib I/O routines.

    The image file will be checked for the initial characters "###CBF: ". If there is no match the error value CBF_FILEREAD is returned.

    ARGUMENTS
      FILNAM  The character string name of the image file to be opened.
      TAPIN  The INTEGER Fortran device unit number assigned to image file.
      LAST_CHAR  The last character (as an INTEGER(1) byte) read.
      FCB_BYTES_IN_REC  The INTEGER number of bytes in a record.
      BYTE_IN_FILE  The INTEGER byte (counting from 1) of the byte to read.
      REC_IN_FILE  The INTEGER record number (counting from 1) of next record to read.
      BUFFER  The INTEGER(1) array of length FCB_BYTES_IN_REC to hold the appropriate record from TAPIN

    RETURN VALUE

    Returns 0 if the function is successful. SEE ALSO

    2.5.3 FCB_EXIT_BINARY
    2.5.5 FCB_NEXT_BINARY
    2.5.9 FCB_READ_BYTE
    2.5.11 FCB_READ_LINE


    2.5.7 FCB_PACKED: FCB_DECOMPRESS_PACKED_I2, FCB_DECOMPRESS_PACKED_I4, FCB_DECOMPRESS_PACKED_3D_I2, FCB_DECOMPRESS_PACKED_3D_I4

          INTERFACE
          INTEGER FUNCTION FCB_DECOMPRESS_PACKED_I2 (ARRAY,NELEM,NELEM_READ, &
            ELSIGN, COMPRESSION, DIM1, DIM2,  &
            TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE,                   &
            REC_IN_FILE,BUFFER)
          INTEGER(2),  INTENT(OUT):: ARRAY(DIM1,DIM2)
          INTEGER(8),  INTENT(OUT):: NELEM_READ
          INTEGER(8),   INTENT(IN):: NELEM
          INTEGER,      INTENT(IN):: ELSIGN, COMPRESSION
          INTEGER(8),   INTENT(IN):: DIM1,DIM2 
          INTEGER,      INTENT(IN):: TAPIN,FCB_BYTES_IN_REC
          INTEGER,   INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE
          INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC)
          END FUNCTION
          END INTERFACE

          INTERFACE
          INTEGER FUNCTION FCB_DECOMPRESS_PACKED_I4 (ARRAY,NELEM,NELEM_READ, &
            ELSIGN, COMPRESSION, DIM1, DIM2,  &
            TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE,                   &
            REC_IN_FILE,BUFFER)
            
          INTEGER(4),  INTENT(OUT):: ARRAY(DIM1,DIM2)
          INTEGER(8),  INTENT(OUT):: NELEM_READ
          INTEGER(8),   INTENT(IN):: NELEM
          INTEGER,      INTENT(IN):: ELSIGN, COMPRESSION
          INTEGER(8),   INTENT(IN):: DIM1,DIM2 
          INTEGER,      INTENT(IN):: TAPIN,FCB_BYTES_IN_REC
          INTEGER,   INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE
          INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC)
          END FUNCTION
          END INTERFACE

          INTERFACE
          INTEGER FUNCTION FCB_DECOMPRESS_PACKED_3D_I2 (ARRAY,NELEM,NELEM_READ, &
            ELSIGN, COMPRESSION, DIM1, DIM2, DIM3,  &
            TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE,                   &
            REC_IN_FILE,BUFFER)
          INTEGER(2),  INTENT(OUT):: ARRAY(DIM1,DIM2,DIM3)
          INTEGER(8),  INTENT(OUT):: NELEM_READ
          INTEGER(8),   INTENT(IN):: NELEM
          INTEGER,      INTENT(IN):: ELSIGN, COMPRESSION
          INTEGER(8),   INTENT(IN):: DIM1,DIM2,DIM3 
          INTEGER,      INTENT(IN):: TAPIN,FCB_BYTES_IN_REC
          INTEGER,   INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE
          INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC)
          END FUNCTION
          END INTERFACE

          INTERFACE
          INTEGER FUNCTION FCB_DECOMPRESS_PACKED_3D_I4 (ARRAY,NELEM,NELEM_READ, &
            ELSIGN, COMPRESSION, DIM1, DIM2, DIM3,  &
            TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE,                   &
            REC_IN_FILE,BUFFER)
          INTEGER(4),  INTENT(OUT):: ARRAY(DIM1,DIM2,DIM3)
          INTEGER(8),  INTENT(OUT):: NELEM_READ
          INTEGER(8),   INTENT(IN):: NELEM
          INTEGER,      INTENT(IN):: ELSIGN, COMPRESSION
          INTEGER(8),   INTENT(IN):: DIM1,DIM2,DIM3 
          INTEGER,      INTENT(IN):: TAPIN,FCB_BYTES_IN_REC
          INTEGER,   INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE
          INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC)
          END FUNCTION
          END INTERFACE

    The functions FCB_DECOMPRESS_PACKED_I2, FCB_DECOMPRESS_PACKED_I4, FCB_DECOMPRESS_PACKED_3D_I2 and FCB_DECOMPRESS_PACKED_3D_I4, decompress images compress according the the CBF_PACKED or CBF_PACKED_V2 compression described in section 3.3.2 on J. P. Abrahams CCP4 packed compression.

    The relevant function should be called immediately after a call to FCB_NEXT_BINARY, using the values returned by FCB_NEXT_BINARY to select the appropriate version of the function.

    ARGUMENTS
      ARRAY  The array to receive the image
      NELEM  The INTEGER(8) number of elements to be read
      NELEM_READ  The INTEGER(8) returned value of the number of elements actually read
      ELSIGN  The INTEGER value of the flag for signed (1) OR unsigned (0) data
      COMPRESSION  The compression of the image
      DIM1  The INTEGER(8) value of the fastest dimension of ARRAY
      DIM2  The INTEGER(8) value of the second fastest dimension
      DIM3  The INTEGER(8) value of the third fastest dimension
      TAPIN  The INTEGER Fortran device unit number assigned to image file.
      FCB_BYTES_IN_REC  The INTEGER number of bytes in a record.
      BYTE_IN_FILE  The INTEGER byte (counting from 1) of the byte to read.
      REC_IN_FILE  The INTEGER record number (counting from 1) of next record to read.
      BUFFER  The INTEGER(1) array of length FCB_BYTES_IN_REC to hold the appropriate record from TAPIN

    RETURN VALUE

    Returns 0 if the function is successful.

    SEE ALSO

    2.5.3 FCB_EXIT_BINARY
    2.5.5 FCB_NEXT_BINARY
    2.5.6 FCB_OPEN_CIFIN
    2.5.9 FCB_READ_BYTE
    2.5.11 FCB_READ_LINE


    2.5.8 FCB_READ_BITS

          INTERFACE
          INTEGER FUNCTION FCB_READ_BITS(TAPIN,FCB_BYTES_IN_REC,BUFFER,     &
                         REC_IN_FILE,BYTE_IN_FILE,BCOUNT,BBYTE,             &
                         BITCOUNT,IINT,LINT)
          INTEGER,      INTENT(IN):: TAPIN,FCB_BYTES_IN_REC
          INTEGER,   INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE
          INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC)
          INTEGER,   INTENT(INOUT):: BCOUNT
          INTEGER(1),INTENT(INOUT):: BBYTE
          INTEGER,      INTENT(IN):: BITCOUNT
          INTEGER,      INTENT(IN):: LINT
          INTEGER(4),  INTENT(OUT):: IINT(LINT)
          END FUNCTION
          END INTERFACE

    The function FCB_READ_BITS gets the integer value starting at BYTE_IN_FILE from file TAPIN continuing through BITCOUNT bits, with sign extension. BYTE_IN_FILE is left at the entry value and not incremented. The resulting, sign-extended integer value is stored in the INTEGER(4) array IINT of dimension LINT with the least significant portion in IINT(1).

    ARGUMENTS
      TAPIN  The INTEGER Fortran device unit number assigned to image file.
      FCB_BYTES_IN_REC  The INTEGER number of bytes in a record.
      BUFFER  The INTEGER(1) array of length FCB_BYTES_IN_REC to hold the appropriate record from TAPIN
      REC_IN_FILE  The INTEGER record number (counting from 1) of next record to read.
      BYTE_IN_FILE  The INTEGER byte (counting from 1) of the byte to read.
      BCOUNT  The INTEGER count of bits remaining unused from the last call to FCB_READ_BITS.
      BBYTE  The INTEGER(1) byte containing the unused bits from the last call to FCB_READ_BITS.
      BITCOUNT  The INTEGER count of the number of bits to be extracted from the image file.
      IINT  The INTEGER(4) array into which to store the value extracted from the image file.
      LINT  The INTEGER length of the array IINT.

    RETURN VALUE

    Returns 0 if the function is successful. Because of the use of direct access I/O in blocks of size FCB_BYTES_IN_REC the precise location of the end of file may not be detected.

    SEE ALSO

    2.5.3 FCB_EXIT_BINARY
    2.5.5 FCB_NEXT_BINARY
    2.5.6 FCB_OPEN_CIFIN
    2.5.9 FCB_READ_BYTE
    2.5.11 FCB_READ_LINE


    2.5.9 FCB_READ_BYTE

          INTERFACE
          INTEGER FUNCTION FCB_READ_BYTE(TAPIN,FCB_BYTES_IN_REC,BUFFER,     &
                                 REC_IN_FILE,BYTE_IN_FILE,IBYTE)
          INTEGER,      INTENT(IN):: TAPIN,FCB_BYTES_IN_REC
          INTEGER,   INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE
          INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC)
          INTEGER(1),  INTENT(OUT):: IBYTE
          END FUNCTION
          END INTERFACE

    The function FCB_READ_BYTE reads the byte at the position BYTE_IN_FILE in the image file TAPIN. The first byte in the file is at BYTE_IN_FILE = 1. BYTE_IN_FILE should be set to the desired value before the call to the function and is not incremented within the function.

    The function attempts to suppress the error caused by a read of a short last record, and in most systems cannot determine the exact location of the end of the image file, returning zero bytes until the equivalent of a full final record has been read.

    ARGUMENTS
      TAPIN  The INTEGER Fortran device unit number assigned to image file.
      FCB_BYTES_IN_REC  The INTEGER number of bytes in a record.
      BUFFER  The INTEGER(1) array of length FCB_BYTES_IN_REC to hold the appropriate record from TAPIN
      REC_IN_FILE  The INTEGER record number (counting from 1) of next record to read.
      BYTE_IN_FILE  The INTEGER byte (counting from 1) of the byte to read.
      IBYTE  The INTEGER(1) byte found in the image file at the byte position BYTE_IN_FILE.

    RETURN VALUE

    Returns 0 if the function is successful. Because of the use of direct access I/O in blocks of size FCB_BYTES_IN_REC the precise location of the end of file may not be detected.

    SEE ALSO

    2.5.3 FCB_EXIT_BINARY
    2.5.5 FCB_NEXT_BINARY
    2.5.6 FCB_OPEN_CIFIN
    2.5.9 FCB_READ_BITS
    2.5.11 FCB_READ_LINE


    2.5.10 FCB_READ_IMAGE_I2, FCB_READ_IMAGE_I4, FCB_READ_IMAGE_3D_I2, FCB_READ_IMAGE_3D_I4

          INTERFACE
          INTEGER FUNCTION FCB_READ_IMAGE_I2(ARRAY,NELEM,NELEM_READ, &
            ELSIGN, COMPRESSION, DIM1, DIM2,                         &
            PADDING,TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE,             &
            REC_IN_FILE,BUFFER)
          
          INTEGER(2),  INTENT(OUT):: ARRAY(DIM1,DIM2)
          INTEGER(8),  INTENT(OUT):: NELEM_READ
          INTEGER(8),   INTENT(IN):: NELEM
          INTEGER,      INTENT(IN):: ELSIGN
          INTEGER,     INTENT(OUT):: COMPRESSION
          INTEGER(8),   INTENT(IN):: DIM1,DIM2 
          INTEGER(8),  INTENT(OUT):: PADDING
          INTEGER,      INTENT(IN):: TAPIN,FCB_BYTES_IN_REC
          INTEGER,   INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE
          INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC)
          END FUNCTION
          END INTERFACE

          INTERFACE
          INTEGER FUNCTION FCB_READ_IMAGE_I4(ARRAY,NELEM,NELEM_READ, &
            ELSIGN, COMPRESSION, DIM1, DIM2,                         &
            PADDING,TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE,             &
            REC_IN_FILE,BUFFER)
          INTEGER(4),  INTENT(OUT):: ARRAY(DIM1,DIM2)
          INTEGER(8),  INTENT(OUT):: NELEM_READ
          INTEGER(8),   INTENT(IN):: NELEM
          INTEGER,      INTENT(IN):: ELSIGN
          INTEGER,     INTENT(OUT):: COMPRESSION
          INTEGER(8),   INTENT(IN):: DIM1,DIM2 
          INTEGER(8),  INTENT(OUT):: PADDING
          INTEGER,      INTENT(IN):: TAPIN,FCB_BYTES_IN_REC
          INTEGER,   INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE
          INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC)
          END FUNCTION
          END INTERFACE

          INTERFACE
          INTEGER FUNCTION FCB_READ_IMAGE_3D_I2(ARRAY,NELEM,NELEM_READ, &
            ELSIGN, COMPRESSION, DIM1, DIM2, DIM3,                      &
            PADDING,TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE,                &
            REC_IN_FILE,BUFFER)
          INTEGER(2),  INTENT(OUT):: ARRAY(DIM1,DIM2,DIM3)
          INTEGER(8),  INTENT(OUT):: NELEM_READ
          INTEGER(8),   INTENT(IN):: NELEM
          INTEGER,      INTENT(IN):: ELSIGN
          INTEGER,     INTENT(OUT):: COMPRESSION
          INTEGER(8),   INTENT(IN):: DIM1,DIM2,DIM3 
          INTEGER(8),  INTENT(OUT):: PADDING
          INTEGER,      INTENT(IN):: TAPIN,FCB_BYTES_IN_REC
          INTEGER,   INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE
          INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC)
          END FUNCTION
          END INTERFACE

          INTERFACE
          INTEGER FUNCTION FCB_READ_IMAGE_3D_I4(ARRAY,NELEM,NELEM_READ, &
            ELSIGN, COMPRESSION, DIM1, DIM2, DIM3,                      &
            PADDING,TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE,                &
            REC_IN_FILE,BUFFER)
          INTEGER(4),  INTENT(OUT):: ARRAY(DIM1,DIM2,DIM3)
          INTEGER(8),  INTENT(OUT):: NELEM_READ
          INTEGER(8),   INTENT(IN):: NELEM
          INTEGER,      INTENT(IN):: ELSIGN
          INTEGER,     INTENT(OUT):: COMPRESSION
          INTEGER(8),   INTENT(IN):: DIM1,DIM2,DIM3 
          INTEGER(8),  INTENT(OUT):: PADDING
          INTEGER,      INTENT(IN):: TAPIN,FCB_BYTES_IN_REC
          INTEGER,   INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE
          INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC)
          END FUNCTION
          END INTERFACE

    The function FCB_READ_IMAGE_I2 reads a 16-bit twos complement INTEGER(2) 2D image. The function FCB_READ_IMAGE_I4 read a 32-bit twos complement INTEGER(4) 2D image. The function FCB_READ_IMAGE_3D_I2 reads a 16-bit twos complement INTEGER(2) 3D image. The function FCB_READ_IMAGE_3D_I4 reads a 32-bit twos complement INTEGER(4) 3D image. In each case the image is compressed either by a BYTE_OFFSET algorithm by W. Kabsch based on a proposal by A. Hammersley or by a PACKED algorithm by J. P. Abrahams as used in CCP4, with modifications by P. Ellis and H. J. Bernstein.

    The relevant function automatically first calls FCB_NEXT_BINARY to skip to the next binary section and then starts to read. An error return will result if the parameters of this call are inconsistent with the values in MIME header.

    ARGUMENTS
      ARRAY  The array to receive the image
      NELEM  The INTEGER(8) number of elements to be read
      NELEM_READ  The INTEGER(8) returned value of the number of elements actually read
      ELSIGN  The INTEGER value of the flag for signed (1) OR unsigned (0) data
      COMPRESSION  The actual compression of the image
      DIM1  The INTEGER(8) value of the fastest dimension of ARRAY
      DIM2  The INTEGER(8) value of the second fastest dimension
      DIM3  The INTEGER(8) value of the third fastest dimension
      TAPIN  The INTEGER Fortran device unit number assigned to image file.
      FCB_BYTES_IN_REC  The INTEGER number of bytes in a record.
      BYTE_IN_FILE  The INTEGER byte (counting from 1) of the byte to read.
      REC_IN_FILE  The INTEGER record number (counting from 1) of next record to read.
      BUFFER  The INTEGER(1) array of length FCB_BYTES_IN_REC to hold the appropriate record from TAPIN

    RETURN VALUE

    Returns 0 if the function is successful.

    SEE ALSO

    2.5.3 FCB_EXIT_BINARY
    2.5.5 FCB_NEXT_BINARY
    2.5.6 FCB_OPEN_CIFIN
    2.5.7 FCB_DECOMPRESS: FCB_DECOMPRESS_PACKED_I2, FCB_DECOMPRESS_PACKED_I4, FCB_DECOMPRESS_PACKED_3D_I2, FCB_DECOMPRESS_PACKED_3D_I4
    2.5.9 FCB_READ_BYTE
    2.5.11 FCB_READ_LINE


    2.5.11 FCB_READ_LINE

          INTERFACE
          INTEGER FUNCTION FCB_READ_LINE(TAPIN,LAST_CHAR,FCB_BYTES_IN_REC,  &
    			 BYTE_IN_FILE,REC_IN_FILE,BUFFER,LINE,N,LINELEN)
          INTEGER,      INTENT(IN):: TAPIN,FCB_BYTES_IN_REC,N
          INTEGER,   INTENT(INOUT):: BYTE_IN_FILE,REC_IN_FILE
          INTEGER,     INTENT(OUT):: LINELEN
          INTEGER(1),INTENT(INOUT):: LAST_CHAR,BUFFER,(FCB_BYTES_IN_REC)
          INTEGER(1),  INTENT(OUT):: LINE(N)
          END FUNCTION
          END INTERFACE

    The function FCB_READ_LINE reads successive bytes into the INTEGER(1) byte array LINE of dimension N), stopping at N bytes or the first error or the first CR (Z'0D') or LF (Z'0A'), whichever comes first. It discards an LF after a CR. The variable LAST_CHAR is checked for the last character from the previous line to make this determination.

    The actual number of bytes read into the line, not including any terminal CR or LF is stored in LINELEN.

    ARGUMENTS
      TAPIN  The INTEGER Fortran device unit number assigned to image file.
      LAST_CHAR  The INTEGER(1) byte holding the ASCII value of the last character read for each line read.
      FCB_BYTES_IN_REC  The INTEGER number of bytes in a record.
      BYTE_IN_FILE  The INTEGER byte (counting from 1) of the byte to read.
      REC_IN_FILE  The INTEGER record number (counting from 1) of next record to read.
      BUFFER  The INTEGER(1) array of length FCB_BYTES_IN_REC to hold the appropriate record from TAPIN.
      LINE  The INTEGER(1) array of length N to hold the line to be read from TAPIN.
      N  The INTEGER dimension of LINE.
      LINELEN  The INTEGER number of characters read into LINE.

    RETURN VALUE

    Returns 0 if the function is successful.

    SEE ALSO

    2.5.3 FCB_EXIT_BINARY
    2.5.5 FCB_NEXT_BINARY
    2.5.6 FCB_OPEN_CIFIN
    2.5.7 FCB_DECOMPRESS: FCB_DECOMPRESS_PACKED_I2, FCB_DECOMPRESS_PACKED_I4, FCB_DECOMPRESS_PACKED_3D_I2, FCB_DECOMPRESS_PACKED_3D_I4
    2.5.9 FCB_READ_BYTE

    2.5.12 FCB_READ_XDS_I2

          INTERFACE
          INTEGER FUNCTION FCB_READ_XDS_I2(FILNAM,TAPIN,NX,NY,IFRAME,JFRAME)
          CHARACTER(len=*),INTENT(IN) :: FILNAM
          INTEGER,         INTENT(IN) :: TAPIN,NX,NY
          INTEGER(2),      INTENT(OUT):: IFRAME(NX*NY)
          INTEGER(4),      INTENT(OUT):: JFRAME(NX,NY)
          END FUNCTION
          END INTERFACE

    The function FCB_READ_XDS_I2 read a 32-bit integer twos complement image into a 16-bit INTEGER(2) XDS image using the CBF_BYTE_OFFSET, CBF_PACKED or CBF_PACKED_V2 compressions for the 32-bit data. The BYTE_OFFSET algorithm is a variant of the September 2006 version by W. Kabsch which was based on a suggestion by A. Hammersley and which was further modified by H. Bernstein.

    The file named FILNAM is opened on the logical unit TAPIN and FCB_NEXT_BINARY is used to skip to the next binary image. The binary image is then decompressed to produce an XDS 16-bit integer image array IFRAME which is NX by NY. The dimensions must agree with the dimensions specified in MIME header.

    The conversion from a 32-bit integer I32 to 16-bit XDS pixel I16 is done as per W. Kabsch as follows: The value I32 is limited to the range -1023 ≤ I32 ≤ 1048576. If I32 is outside that range it is truncated to the closer boundary. The generate I16, the 16-bit result, if I32 > 32767, it is divided by 32 (producing a number between 1024 and 32768), and then negated (producing a number between -1024 and -32768).

    For CBF_BYTE_OFFSET this conversion can be done on the fly directly into the target array IFRAME, but for the CBF_PACKED or CBF_PACKED_V2, the full 32 bit precision is needed during the decompression, forcing the use of an intermediate INTEGER(4) array JFRAME to hold the 32-bit image in that case.

    The image file is closed after reading one image.

    ARGUMENTS
      FILNAM  The character string name of the image file to be opened.
      TAPIN  The INTEGER Fortran device unit number assigned to image file.
      NX  The INTEGER fast dimension of the image array.
      NY  The INTEGER slow dimension of the image array.
      IFRAME  The INTEGER(2) XDS image array.
      JFRAME  The INTEGER(4) 32-bit image scratch array needed for CBF_PACKED or CBF_PACKED_V2 images.

    RETURN VALUE

    Returns 0 if the function is successful, CBF_FORMAT (=1) if it cannot handle this CBF format (not implemented), -1 if it cannot determine endian architecture of this machine, -2: if it cannot open the image file, -3: if it finds the wrong image format and -4 if it cannot read the image.


    2.5.13 FCB_SKIP_WHITESPACE

          INTERFACE
          INTEGER FUNCTION FCB_SKIP_WHITESPACE(TAPIN,LAST_CHAR,             &
    		       FCB_BYTES_IN_REC,BYTE_IN_FILE,REC_IN_FILE,BUFFER,&
    		       LINE,N,LINELEN,ICUR,FRESH_LINE)
          INTEGER,      INTENT(IN):: TAPIN,FCB_BYTES_IN_REC,N
          INTEGER,   INTENT(INOUT):: BYTE_IN_FILE,REC_IN_FILE,LINELEN,ICUR, &
    				 FRESH_LINE
          INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC),LINE(N),      &
    				 LAST_CHAR
          END INTERFACE

    The function FCB_SKIP_WHITESPACE skips forward on the current INTEGER(1) byte array LINE of size N with valid data in LINE(1:LINELEN) from the current position ICUR moving over MIME header whitespace and comments, reading new lines into LINE if needed. The flag FRESH_LINE indicates that a fresh line should be read on entry.

    ARGUMENTS
      TAPIN  The INTEGER Fortran device unit number assigned to image file.
      LAST_CHAR  The INTEGER(1) byte holding the ASCII value of the last character read for each line read.
      FCB_BYTES_IN_REC  The INTEGER number of bytes in a record.
      BYTE_IN_FILE  The INTEGER byte (counting from 1) of the byte to read.
      REC_IN_FILE  The INTEGER record number (counting from 1) of next record to read.
      BUFFER  The INTEGER(1) array of length FCB_BYTES_IN_REC to hold the appropriate record from TAPIN.
      LINE  The INTEGER(1) array of length N to hold the line to be read from TAPIN.
      N  The INTEGER dimension of LINE.
      LINELEN  The INTEGER number of characters read into LINE.
      ICUR  The INTEGER position within the line.
      FRESH_LINE  The INTEGER flag that a fresh line is needed.

    RETURN VALUE

    Returns 0 if the function is successful.

    SEE ALSO

    2.5.3 FCB_EXIT_BINARY
    2.5.5 FCB_NEXT_BINARY
    2.5.6 FCB_OPEN_CIFIN
    2.5.7 FCB_DECOMPRESS: FCB_DECOMPRESS_PACKED_I2, FCB_DECOMPRESS_PACKED_I4, FCB_DECOMPRESS_PACKED_3D_I2, FCB_DECOMPRESS_PACKED_3D_I4
    2.5.9 FCB_READ_BYTE


    3. File format

    3.1 General description

    With the exception of the binary sections, a CBF file is an mmCIF-format ASCII file, so a CBF file with no binary sections is a CIF file. An imgCIF file has any binary sections encoded as CIF-format ASCII strings and is a CIF file whether or not it contains binary sections. In most cases, CBFlib can also be used to access normal CIF files as well as CBF and imgCIF files.

    3.2 Format of the binary sections

    Before getting to the binary data itself, there are some preliminaries to allow a smooth transition from the conventions of CIF to those of raw or encoded streams of "octets" (8-bit bytes). The binary data is given as the essential part of a specially formatted semicolon-delimited CIF multi-line text string. This text string is the value associated with the tag "_array_data.data".

    The specific format of the binary sections differs between an imgCIF and a CBF file.

    3.2.1 Format of imgCIF binary sections

    Each binary section is encoded as a semicolon-delimited string. Within the text string, the conventions developed for transmitting email messages including binary attachments are followed. There is secondary ASCII header information, formatted as Multipurpose Internet Mail Extensions (MIME) headers (see RFCs 2045-49 by Freed, et al.). The boundary marker for the beginning of all this is the special string

    --CIF-BINARY-FORMAT-SECTION--
    

    at the beginning of a line. The initial "--" says that this is a MIME boundary. We cannot put "###" in front of it and conform to MIME conventions. Immediately after the boundary marker are MIME headers, describing some useful information we will need to process the binary section. MIME headers can appear in different orders, and can be very confusing (look at the raw contents of a email message with attachments), but there is only one header which is has to be understood to process an imgCIF: "Content-Transfer-Encoding". If the value given on this header is "BINARY", this is a CBF and the data will be presented as raw binary, containing a count (in the header described in 3.2.2 Format of CBF binary sections) so that we'll know when to start looking for more information.

    If the value given for "Content-Transfer-Encoding" is one of the real encodings: "BASE64", "QUOTED-PRINTABLE", "X-BASE8", "X-BASE10" or "X-BASE16", the file is an imgCIF, and we'll need some other headers to process the encoded binary data properly. It is a good practice to give headers in all cases. The meanings of various encodings is given in the CBF extensions dictionary, cif_img_1.5.4.dic, as one html file, or as separate pages for each defintion.

    For certain compressions (e.g. CBF_PACKED) MIME headers are essential to determine the parameters of the compression. The full list of MIME headers recognized by and generated by CBFlib is:

    • Content-Type:
    • Content-Transfer-Encoding:
    • Content-MD5:
    • X-Binary-Size:
    • X-Binary-ID:
    • X-Binary-Element-Type:
    • X-Binary-Element-Byte-Order:
    • X-Binary-Number-of-Elements:
    • X-Binary-Size-Fastest-Dimension:
    • X-Binary-Size-Second-Dimension:
    • X-Binary-Size-Third-Dimension:
    • X-Binary-Size-Padding:

    • Content-Type:

      The "Content-Type" header tells us what sort of data we have (currently always "application/octet-stream" for a miscellaneous stream of binary data) and, optionally, the conversions that were applied to the original data. The default is to compress the data with the "CBF-PACKED" algorithm. The Content-Type may be any of the discrete types permitted in RFC 2045; 'application/octet-stream' is recommended. If an octet stream was compressed, the compression should be specified by the parameter 'conversions="X-CBF_PACKED"' or the parameter 'conversions="X-CBF_PACKED_V2"' or the parameter 'conversions="X-CBF_CANONICAL"' or the parameter 'conversions="X-CBF_BYTE_OFFSET"'

      If the parameter 'conversions="X-CBF_PACKED"' or 'conversions="X-CBF_PACKED_V2"' is given it may be further modified with the parameters '"uncorrelated_sections"' or '"flat"'

      If the '"uncorrelated_sections"' parameter is given, each section will be compressed without using the prior section for averaging. If the '"flat"' parameter is given, each the image will be treated as one long row.

    • Content-Transfer-Encoding:

      The "Content-Transfer-Encoding" may be 'BASE64', 'Quoted-Printable', 'X-BASE8', 'X-BASE10', 'X-BASE16' or 'X-BASE32K', for an imgCIF or 'BINARY' for a CBF. The octal, decimal and hexadecimal transfer encodings are provided for convenience in debugging and are not recommended for archiving and data interchange.

      In a CIF, one of the parameters 'charset=us-ascii', 'charset=utf-8' or 'charset=utf-16' may be used on the Content-Transfer-Encoding to specify the character set used for the external presentation of the encoded data. If no charset parameter is given, the character set of the enclosing CIF is assumed. In any case, if a BOM flag is detected (FE FF for big-endian UTF-16, FF FE for little-endian UTF-16 or EF BB BF for UTF-8) is detected, the indicated charset will be assumed until the end of the encoded data or the detection of a different BOM. The charset of the Content-Transfer-Encoding is not the character set of the encoded data, only the character set of the presentation of the encoded data and should be respecified for each distinct STAR string.

      In an imgCIF file, the encoded binary data begins after the empty line terminating the header. In an imgCIF file, the encoded binary data ends with the terminating boundary delimiter '\n--CIF-BINARY-FORMAT-SECTION----' in the currently effective charset or with the '\n; ' that terminates the STAR string.

      In a CBF, the raw binary data begins after an empty line terminating the header and after the sequence:

                    Octet   Hex   Decimal  Purpose
                      0     0C       12    (ctrl-L) Page break
                      1     1A       26    (ctrl-Z) Stop listings in MS-DOS
                      2     04       04    (Ctrl-D) Stop listings in UNIX
                      3     D5      213    Binary section begins
      
      None of these octets are included in the calculation of the message size or in the calculation of the message digest.

    • Content-MD5:

      An MD5 message digest may, optionally, be used. The 'RSA Data Security, Inc. MD5 Message-Digest Algorithm' should be used. No portion of the header is included in the calculation of the message digest. The optional "Content-MD5" header provides a much more sophisticated check on the integrity of the binary data than size checks alone can provide.

    • X-Binary-Size:

      The "X-Binary-Size" header specifies the size of the equivalent binary data in octets. This is the size after any compressions, but before any ascii encodings. This is useful in making a simple check for a missing portion of this file. The 8 bytes for the Compression type (see below) are not counted in this field, so the value of "X-Binary-Size" is 8 less than the quantity in bytes 12-19 of the raw binary data ( 3.2.2 Format of CBF binary sections).

    • X-Binary-ID:

      The "X-Binary-ID" header should contain the same value as was given for "_array_data.binary_id".

    • X-Binary-Element-Type:

      The "X-Binary-Element-Type" header specifies the type of binary data in the octets, using the same descriptive phrases as in _array_structure.encoding_type. The default value is 'unsigned 32-bit integer'.

    • X-Binary-Element-Byte-Order:

      The "X-Binary-Element-Byte-Order" can specify either '"BIG_ENDIAN"' or '"LITTLE_ENDIAN"' byte order of the image data. CBFlib only writes '"LITTLE_ENDIAN"', and in general can only process LITTLE_ENDIAN even on machines that are BIG_ENDIAN.

    • X-Binary-Number-of-Elements:

      The "X-Binary-Number-of-Elements" specifies the number of elements (not the number of octets) in the decompressed, decoded image.

    • X-Binary-Size-Fastest-Dimension:

      The optional "X-Binary-Size-Fastest-Dimension" specifies the number of elements (not the number of octets) in one row of the fastest changing dimension of the binary data array. This information must be in the MIME header for proper operation of some of the decompression algorithms.

    • X-Binary-Size-Second-Dimension:

      The optional "X-Binary-Size-Second-Dimension" specifies the number of elements (not the number of octets) in one column of the second-fastest changing dimension of the binary data array. This information must be in the MIME header for proper operation of some of the decompression algorithms.

    • X-Binary-Size-Third-Dimension:

      The optional "X-Binary-Size-Third-Dimension" specifies the number of sections for the third-fastest changing dimension of the binary data array.

    • X-Binary-Size-Padding:

      The optional "X-Binary-Size-Padding" specifies the size in octets of an optional padding after the binary array data and before the closing flags for a binary section. CBFlib always writes this padding as zeros, but this information should be in the MIME header for a binary section that uses padding, especially if non-zero padding is used.

    A blank line separator immediately precedes the start of the encoded binary data. Blank spaces may be added prior to the preceding "line separator" if desired (e.g. to force word or block alignment).

    Because CBFLIB may jump forward in the file from the MIME header, the length of encoded data cannot be greater than the value defined by "X-Binary-Size" (except when "X-Binary-Size" is zero, which means that the size is unknown), unless "X-Binary-Size-Padding" is specified to allow for the padding. At exactly the byte following the full binary section as defined by the length and padding values is the end of binary section identifier. This consists of the line-termination sequence followed by:

    --CIF-BINARY-FORMAT-SECTION----
    ;
    

    with each of these lines followed by a line-termination sequence. This brings us back into a normal CIF environment. This identifier is, in a sense, redundant because the binary data length value tells the a program how many bytes to jump over to the end of the binary data. This redundancy has been deliberately added for error checking, and for possible file recovery in the case of a corrupted file and this identifier must be present at the end of every block of binary data.

    3.2.2 Format of CBF binary sections

    In a CBF file, each binary section is encoded as a ;-delimited string, starting with an arbitrary number of pure-ASCII characters.

    Note: For historical reasons, CIFlib has the option of writing simple header and footer sections: "START OF BINARY SECTION" at the start of a binary section and "END OF BINARY SECTION" at the end of a binary section, or writing MIME-type header and footer sections (3.2.1 Format of imgCIF binary sections). If the simple header is used, the actual ASCII text is ignored when the binary section is read. Use of the simple binary header is deprecated.

    The MIME header is recommended.

    Between the ASCII header and the actual CBF binary data is a series of bytes ("octets") to try to stop the listing of the header, bytes which define the binary identifier which should match the "binary_id" defined in the header, and bytes which define the length of the binary section.


    Octet Hex Decimal Purpose
       1   0C   12   (ctrl-L) End of Page
       2   1A   26   (ctrl-Z) Stop listings in MS-DOS
       3   04   04   (Ctrl-D) Stop listings in UNIX
       4   D5   213   Binary section begins
       5..5+n-1         Binary data (n octets)

    NOTE: When a MIME header is used, only bytes 5 through 5+n-1 are considered in computing the size and the message digest, and only these bytes are encoded for the equivalent imgCIF file using the indicated Content-Transfer-Encoding.

    If no MIME header has been requested (a deprecated use), then bytes 5 through 28 are used for three 8-byte words to hold the binary_id, the size and the compression type:

       5..12          Binary Section Identifier
    (See _array_data.binary_id)
    64-bit, little endian
       13..20          The size (n) of the
    binary section in octets
    (i.e. the offset from octet
    29 to the first byte following
    the data)
       21..28         Compression type:
      CBF_NONE   0x0040 (64)
      CBF_CANONICAL   0x0050 (80)
      CBF_PACKED   0x0060 (96)
      CBF_BYTE_OFFSET   0x0070 (112)
      CBF_PREDICTOR   0x0080 (128)
      ...    

    The binary data then follows in bytes 29 through 29+n-1.

    The binary characters serve specific purposes:

    • The Control-L (from-feed) will terminate printing of the current page on most operating systems.

    • The Control-Z will stop the listing of the file on MS-DOS type operating systems.

    • The Control-D will stop the listing of the file on Unix type operating systems.

    • The unsigned byte value 213 (decimal) is binary 11010101. (Octal 325, and hexadecimal D5). This has the eighth bit set so can be used for error checking on 7-bit transmission. It is also asymmetric, but with the first bit also set in the case that the bit order could be reversed (which is not a known concern).

    • (The carriage return, line-feed pair before the START_OF_BIN and other lines can also be used to check that the file has not been corrupted e.g. by being sent by ftp in ASCII mode.)


      At present four compression schemes are implemented are defined: CBF_NONE (for no compression), CBF_CANONICAL (for and entropy-coding scheme based on the canonical-code algorithm described by Moffat, et al. (International Journal of High Speed Electronics and Systems, Vol 8, No 1 (1997) 179-231)), CBF_PACKED or CBF_PACKED_V2 for J. P. Abrahams CCP4-style packing schemes and CBF_BYTE_OFFSET for a simple byte_offset compression scheme.. Other compression schemes will be added to this list in the future.

    For historical reasons, CBFlib can read or write a binary string without a MIME header. The structure of a binary string with simple headers is:

    ByteASCII
    symbol
    Decimal 
    value
    Description
      1  ;  59  Initial ; delimiter
      2  carriage-return  13  
      3  line-feed  10  The CBF new-line code is carriage-return, line-feed
      4  S  83  
      5  T  84  
      6  A  65  
      7  R  83  
      8  T  84  
      9    32  
      10  O  79  
      11  F  70  
      12    32  
      13  B  66  
      14  I  73  
      15  N  78  
      16  A  65  
      17  R  83  
      18  Y  89  
      19    32  
      20  S  83  
      21  E  69  
      22  C  67  
      23  T  84  
      24  I  73  
      25  O  79  
      26  N  78  
      27  carriage-return  13  
      28  line-feed  10  
      29  form-feed  12  
      30  substitute  26  Stop the listing of the file in MS-DOS
      31  end-of-transmission  4  Stop the listing of the file in unix
      32    213  First non-ASCII value
      33 .. 40      Binary section identifier (64-bit little-endien)
      41 .. 48      Offset from byte 57 to the first ASCII character following the binary data
      49 .. 56      Compression type
    57 .. 57 + n-1    Binary data (nbytes)
      57 + n   carriage-return  13  
      58 + n   line-feed  10  
      59 + n   E  69  
      60 + n   N  78  
      61 + n   D  68  
      62 + n     32  
      63 + n   O  79  
      64 + n   F  70  
      65 + n     32  
      66 + n   B  66  
      67 + n   I  73  
      68 + n   N  78  
      69 + n   A  65  
      70 + n   R  83  
      71 + n   Y  89  
      72 + n     32  
      73 + n   S  83  
      74 + n   E  69  
      75 + n   C  67  
      76 + n   T  84  
      77 + n   I  73  
      78 + n   O  79  
      79 + n   N  78  
      80 + n   carriage-return  13  
      81 + n   line-feed  10  
      82 + n   ;  59  Final ; delimiter

    3.3 Compression schemes

    Two schemes for lossless compression of integer arrays (such as images) have been implemented in this version of CBFlib:

    1. An entropy-encoding scheme using canonical coding
    2. A CCP4-style packing scheme.

    Both encode the difference (or error) between the current element in the array and the prior element. Parameters required for more sophisticated predictors have been included in the compression functions and will be used in a future version of the library.

    3.3.1 Canonical-code compression

    The canonical-code compression scheme encodes errors in two ways: directly or indirectly. Errors are coded directly using a symbol corresponding to the error value. Errors are coded indirectly using a symbol for the number of bits in the (signed) error, followed by the error iteslf.

    At the start of the compression, CBFlib constructs a table containing a set of symbols, one for each of the 2^n direct codes from -2^(n-1) .. 2^(n-1)-1, one for a stop code, and one for each of the maxbits -n indirect codes, where n is chosen at compress time and maxbits is the maximum number of bits in an error. CBFlib then assigns to each symbol a bit-code, using a shorter bit code for the more common symbols and a longer bit code for the less common symbols. The bit-code lengths are calculated using a Huffman-type algorithm, and the actual bit-codes are constructed using the canonical-code algorithm described by Moffat, et al. (International Journal of High Speed Electronics and Systems, Vol 8, No 1 (1997) 179-231).

    The structure of the compressed data is:

    ByteValue
      1 .. 8  Number of elements (64-bit little-endian number)
      9 .. 16  Minimum element
      17 .. 24  Maximum element
      25 .. 32  (reserved for future use)
      33  Number of bits directly coded, n
      34  Maximum number of bits encoded, maxbits
      35 .. 35+2^n-1  Number of bits in each direct code
      35+2^n  Number of bits in the stop code
      35+2^n+1 .. 35+2^n+maxbits-n   Number of bits in each indirect code
      35+2^n+maxbits-n+1 ..   Coded data

    3.3.2 CCP4-style compression

    Starting with CBFlib 0.7.7, CBFlib supports three variations on CCP4-style compression: the "flat" version supported in versions of CBFlib prior to release 0.7.7, as well as both version 1 and version 2 of J. P. Abrahams "pack_c" compression.

    The CBF_PACKED and CBF_PACKED_V2 compression and decompression code incorporated in CBFlib is derived in large part from the J. P. Abrahams pack_c.c compression code in CCP4. This code is incorporated in CBFlib under the GPL and the LGPL with both the permission Jan Pieter Abrahams, the original author of pack_c.c (email from Jan Pieter Abrahams of 15 January 2007) and of the CCP4 project (email from Martyn Winn on 12 January 2007). The cooperation of J. P. Abrahams and of the CCP4 project is gratefully acknowledged.

    The basis for all three versions is a scheme to pack offsets (differences from a base value) into a small-endian bit stream. The stream is organized into blocks. Each block begins with a header of 6 bits in the flat packed version and version 1 of J. P. Abrahams compression, and 7 bits in version 2 of J. P. Abrahams compression. The header gives the number of offsets that follow and the number of bits in each offset. Each offset is a signed, 2's complement integer.

    The first 3 bits in the header gives the logarithm base 2 of the numer of offsets that follow the header. For example, if a header has a zero in bits, only one offset follows the header. If those same bits contain the number n, the number of offsets in the block is 2n.

    The following 3 bits (flat and version 1) or 4 bits (version 2) contains a number giving an index into a table of bit-lengths for the offsets. All offsets in a given block are of the same length.

    Bits 3 .. 5 (flat and version 1) or bits 3 .. 6 (version 2) encode the number of bits in each offset as follows:
    Value in
    bits 3 .. 5
    Number of bits
    in each V1 offset

    Number of bits
    in each V2 offset

    000
    143
    254
    365
    476
    587
    6168
    7max9
    8 10
    9 11
    10 12
    11 13
    12 14
    13 15
    14 16
    15 max

    The value "max" is determined by the compression version and the element size. If the compression used is "flat", then "max" is 65. If the compression is version 1 or version 2 of the JPA compression, then "max" is the number of bits in each element, i.e. 8, 16, 32 or 64 bits.

    The major difference between the three variants of packed compression is the choice of the base value from which the offset is measured. In all cases the first offset is measured from zero, i.e. the first offset is the value of the first pixel of the image. If "flat" is chosen or if the dimensions of the data array are not given, then the remaining offset are measure against the prior value, making it similar in approach to the "byte offset" compression described in section 3.3.3 Byte offset compression, but with a more efficient representation of the offsets.

    In version 1 and version 2 of the J. P. Abrahams compression, the offsets are measured against an average of earlier pixels. If there is only one row only the prior pxiel is used, starting with the same offsets for that row as for "flat". After the first row, three pixels from the prior row are used in addition to using the immediately prior pixel. If there are multiple sections, and the sections are marked as correlated, after the first section, 4 pixels from the prior section are included in the average. The CBFlib code differs from the pack_c code in the handling of the beginnings and ends of rows and sections. The pack_c code will use pixels from the other side of the image in doing the averaging. The CBFlib code drops pixels from the other side of the image from the pool. The details follow.

    After dealing with the special case of the first pixel, The algorithm uses an array of pointers, trail_char_data. The assignment of pixels to the pool to be averaged begins with trail_char_data[0] points to the pixel immediately prior to the next pixel to be processed, either in the same row (fastest index) or, at the end of the prior row if the next data element to be processed is at the end of a row. The location of the pixel pointed to by trail_char_data[0] is used to compute the locations of the other pixels in the pool. It will be dropped from the pool before averaging if it is on the opposite side of the image. The pool will consist of 1, 2, 4 or 8 pixels.

    Assume ndim1, ndim2, ndim3 are the indices of the same pixel as trail_char_data[0] points to. These indices are incremented to be the indices of the next pixel to be processed before populating trail_char_data.

    On exit, trail_char_data[0 .. 7] will have been populated with pointers to the pixels to be used in forming the average. Pixels that will not be used will be set to NULL. Note that trail_char_data[0] may be set to NULL.

    If we mark the next element to be processed with a "*" and the entries in trail_char_data with their array indices 0 .. 7, the possible patterns of settings in the general case are:

    current section:

    
        
             - - - - 0 * - - - -
             - - - - 3 2 1 - - - 
             - - - - - - - - - -
    
    

    prior section:

    
        
             - - - - - 4 - - - -
             - - - - 7 6 5 - - - 
             - - - - - - - - - -
    
    

    If there is no prior section (i.e. ndim3 is 0, or the CBF_UNCORRELATED_SECTIONS flag is set to indicate discontinuous sections), the values for trail_char_data[4 .. 7] will all be NULL. When there is a prior section, trail_char_data[5..7] are pointers to the pixels immediately below the elements pointed to by trail_char_data[1..3], except trail_char_data[4] is one element further along its row to be directly below the next element to be processed.

    The first element of the first row of the first section is a special case, with no averaging.

    In the first row of the first section (ndim2 == 0, and ndim3 == 0), after the first element (ndim1 > 0), only trail_char_data[0] is used

    current section:

    
            
             - - - - 0 * - - - -
    
    

    For subsequent rows of the first section (ndim2 > 0, and ndim3 == 0), for the first element (ndim1 == 0), two elements from the prior row are used:

    current section:

    
        
             * - - - - - - - - -
             2 1 - - - - - - - -
             - - - - - - - - - -
    
    

    while for element after the first element, but before the last element of the row, a full set of 4 elements is used:

    current section:

    
        
             - - - - 0 * - - - -
             - - - - 3 2 1 - - - 
             - - - - - - - - - -
    
    

    For the last element of a row (ndim1 == dim1-1), two elements are used

    current section:

    
       
             - - - - - - - - 0 *
             - - - - - - - - - 2 
             - - - - - - - - - -
    
    

    For sections after the first section, provided the CBF_UNCORRELATED_SECTIONS flag is not set in the compression, for each non-NULL entry in trail_char_data [0..3] an entry is made in trail_char_data [4..7], except for the first element of the first row of a section. In that case an entry is made in trail_char_data[4].

    The structure of the compressed data is:

    ByteValue
      1 .. 8  Number of elements (64-bit little-endian number)
      9 .. 16  Minumum element (currently unused)
      17 .. 24  Maximum element (currently unused)
      25 .. 32  (reserved for future use)
      33 ..  Coded data

    3.3.3 Byte_offset compression

    Starting with CBFlib 0.7.7, CBFlib supports a simple and efficient "byte_offset" algorithm originally proposed by Andy Hammerley and modified by Wolgang Kabsch and Herbert Bernstein. The original proposal was called "byte_offsets". We distinguish this variant by calling it "byte_offset". The major differences are that the "byte_offsets" algorithm started with explicit storage of the first element of the array as a 4-byte signed two's integer, and checked for image edges to changes the selection of prior pixel. The CBFlib "byte_offset" alogorithm starts with an assumed zero before the first pixel and represents the value of the first pixel as an offset of whatever number of size is needed to hold the value, and for speed, treats the entire image as a simple linear array, allowing use of the last pixel of one row as the base against which to compute the offset for the first element of the next row.

    The algorithm is simple and easily implemented. This algorithm can never achieve better than a factor of two compression relative to 16-bit raw data or 4 relative to 32-bit raw data, but for most diffraction data the compression will indeed be very close to these ideal values. It also has the advantage that integer values up to 32 bits (or 31 bits and sign) may be stored efficiently without the need for special over-load tables. It is a fixed algorithm which does not need to calculate any image statistics, so is fast.

    The algorithm works because of the following property of almost all diffraction data and much other image data: The value of one element tends to be close to the value of the adjacent elements, and the vast majority of the differences use little of the full dynamic range. However, noise in experimental data means that run-length encoding is not useful (unless the image is separated into different bit-planes). If a variable length code is used to store the differences, with the number of bits used being inversely proportional to the probability of occurrence, then compression ratios of 2.5 to 3.0 may be achieved. However, the optimum encoding becomes dependent of the exact properties of the image, and in particular on the noise. Here a lower compression ratio is achieved, but the resulting algorithm is much simpler and more robust.

    The "byte_offset" compression algorithm is the following:

    1. Start with a base pixel value of 0.
    2. Compute the difference delta between the next pixel value and the base pixel value.
    3. If -127 ≤ delta ≤ 127, output delta as one byte, make the current pixel value the base pixel value and return to step 2.
    4. Otherwise output -128 (80 hex).
    5. We still have to output delta. If -32767 ≤ delta ≤ 32767, output delta as a little_endian 16-bit quantity, make the current pixel value the base pixel value and return to step 2.
    6. Otherwise output -32768 (8000 hex, little_endian, i.e. 00 then 80)
    7. We still have to output delta. If -2147483647 ≤ delta ≤ 2147483647, output delta as a little_endian 32 bit quantity, make the current pixel value the base pixel value and return to step 2.
    8. Otherwise output -2147483648 (80000000 hex, little_endian, i.e. 00, then 00, then 00, then 80) and then output the pixel value as a little-endian 64 bit quantity, make the current pixel value the base pixel value and return to step 2.

    The "byte_offset" decompression algorithm is the following:

    1. Start with a base pixel value of 0.
    2. Read the next byte as delta
    3. If -127 ≤ delta ≤ 127, add delta to the base pixel value, make that the new base pixel value, place it on the output array and return to step 2.
    4. If delta is 80 hex, read the next two bytes as a little_endian 16-bit number and make that delta.
    5. If -32767 ≤ delta ≤ 32767, add delta to the base pixel value, make that the new base pixel value, place it on the output array and return to step 2.
    6. If delta is 8000 hex, read the next 4 bytes as a little_endian 32-bit number and make that delta
    7. If -2147483647 ≤ delta ≤ 2147483647, add delta to the base pixel value, make that the new base pixel value, place it on the output array and return to step 2.
    8. If delta is 80000000 hex, read the next 8 bytes as a little_endian 64-bit number and make that delta, add delta to the base pixel value, make that the new base pixel value, place it on the output array and return to step 2.

    Let us look at an example, of two 1000 x 1000 flat field images presented as a mimimal imgCIF file. The first image uses 32-bit unsigned integers and the second image uses 16-bit unsigned integers.

    The imgCIF file begins with some identifying comments (magic numbers) to track the version of the dictionary and library:

    ###CBF: VERSION 1.5
    # CBF file written by CBFlib v0.7.7
    

    This is followed by the necessary syntax to start a CIF data block and by whatever tags and values are appropriate to describe the experiment. The minimum is something like

    data_testflat
    

    eventually we come to the actual binary data, which begins the loop header for the array_data category

    loop_
    _array_data.data
    

    with any additional tags needed, and then the data itself, which starts with the mini-header:

    ;
    --CIF-BINARY-FORMAT-SECTION--
    Content-Type: application/octet-stream;
         conversions="x-CBF_BYTE_OFFSET"
    Content-Transfer-Encoding: BINARY
    X-Binary-Size: 1000002
    X-Binary-ID: 1
    X-Binary-Element-Type: "unsigned 32-bit integer"
    X-Binary-Element-Byte-Order: LITTLE_ENDIAN
    Content-MD5: +FqUJGxXhvCijXMFHC0kaA==
    X-Binary-Number-of-Elements: 1000000
    X-Binary-Size-Fastest-Dimension: 1000
    X-Binary-Size-Second-Dimension: 1000
    X-Binary-Size-Padding: 4095
    

    followed by an empty line and then the sequence of characters:

    ^L^Z^D<D5>
    

    followed immediately by the compressed data.

    The binary data begins with the hex byte 80 to flag the need for a value that will not fit in one byte. That is followed by the small_endian hex value 3E8 saying that the first delta is 1000. Then 999,999 bytes of zero follow, since this is a flat field, with all values equal to zero. That gives us our entire 1000x1000 compressed flat field. However, because we asked for 4095 bytes of padding, there is an additional 4095 bytes of zero that are not part of the compressed field. They are just pad and can be ignored. Finally, after the pad, the CIF text field that began with

    ;
    --CIF-BINARY-FORMAT-SECTION--
    

    is completed with

    --CIF-BINARY-FORMAT-SECTION----
    ;
    

    notice the extra --

    The second flat field then follows, with a very similar mini-header:

    ;
    --CIF-BINARY-FORMAT-SECTION--
    Content-Type: application/octet-stream;
         conversions="x-CBF_BYTE_OFFSET"
    Content-Transfer-Encoding: BINARY
    X-Binary-Size: 1000002
    X-Binary-ID: 2
    X-Binary-Element-Type: "unsigned 16-bit integer"
    X-Binary-Element-Byte-Order: LITTLE_ENDIAN
    Content-MD5: +FqUJGxXhvCijXMFHC0kaA==
    X-Binary-Number-of-Elements: 1000000
    X-Binary-Size-Fastest-Dimension: 1000
    X-Binary-Size-Second-Dimension: 1000
    X-Binary-Size-Padding: 4095
    
    ^L^Z^D<D5>
    

    The only difference is that we have declared this array to be 16-bit and have chosen a different binary id (2 instead of 1). Even the checksum is the same.

    4. Installation

    CBFlib should be built on a disk with at least 200 megabytes of free space. CBFlib.tar.gz is a "gzipped" tar of the code as it now stands. Place the gzipped tar in the directory that is intended to contain a new directory, named CBFlib_0.7.5 (the "top-level" directory) and uncompress it with gunzip and unpack it with tar:

         gunzip CBFlib.tar.gz
         tar xvf CBFLIB.tar
    

    As with prior releases, to run the test programs, you will also need Paul Ellis's sample MAR345 image, example.mar2300, and Chris Nielsen's sample ADSC Quantum 315 image, mb_LP_1_001.img as sample data. Both these files will be extracted by the Makefile from CBFlib_0.7.7_Data_Files. Do not download copies into the top level directory.

    After unpacking the archive, the top-level directory should contain a makefile:

      Makefile  Makefile for unix

    and the subdirectories:

      src/  CBFLIB source files
      include/  CBFLIB header files
      m4/  CBFLIB m4 macro files (used to build .f90 files)
      examples/  Example program source files
      doc/  Documentation
      lib/  Compiled CBFLIB library
      bin/  Executable example programs
      html_images/  JPEG images used in rendering the HTML files

    For instructions on compiling and testing the library, go to the top-level directory and type:

         make
    

    The CBFLIB source and header files are in the "src" and "include" subdirectories. The FCBLIB source and m4 files are in the "src" and "m4" subdirectories. The files are:
    src/include/m4/ Description
      cbf.c  cbf.h   CBFLIB API functions
      cbf_alloc.c  cbf_alloc.h   Memory allocation functions
      cbf_ascii.c  cbf_ascii.h   Function for writing ASCII values
      cbf_binary.c  cbf_binary.h   Functions for binary values
      cbf_byte_offset.c  cbf_byte_offset.h   Byte-offset compression
      cbf_canonical.c  cbf_canonical.h   Canonical-code compression
      cbf_codes.c  cbf_codes.h   Encoding and message digest functions
      cbf_compress.c  cbf_compress.h   General compression routines
      cbf_context.c  cbf_context.h   Control of temporary files
      cbf_file.c  cbf_file.h   File in/out functions
      cbf_lex.c  cbf_lex.h   Lexical analyser
      cbf_packed.c  cbf_packed.h   CCP4-style packing compression
      cbf_predictor.c  cbf_predictor.h   Predictor-Huffman compression (not implemented)
      cbf_read_binary.c  cbf_read_binary.h   Read binary headers
      cbf_read_mime.c  cbf_read_mime.h   Read MIME-encoded binary sections
      cbf_simple.c  cbf_simple.h   Higher-level CBFlib functions
      cbf_string.c  cbf_string.h   Case-insensitive string comparisons
      cbf_stx.c  cbf_stx.h   Parser (generated from cbf.stx.y)
      cbf_tree.c  cbf_tree.h   CBF tree-structure functions
      cbf_uncompressed.c  cbf_uncompressed.h   Uncompressed binary sections
      cbf_write.c  cbf_write.h   Functions for writing
      cbf_write_binary.c  cbf_write_binary.h   Write binary sections
      cbf.stx.y      bison grammar to define cbf_stx.c (see WARNING)
      md5c.c  md5.h   RSA message digest software from mpack
         global.h    
      fcb_atol_wcnt.f90      Function to convert a string to an integer
      fcb_ci_strncmparr.f90      Function to do a case-insensitive comparison of a string to a byte array
      fcb_nblen_array.f90      Function to determine the non-blank length of a byte array
      fcb_read_byte.f90      Function to read a single byte
      fcb_read_line.f90      Function to read a line into a byte array
      fcb_skip_whitespace.f90      Function to skip whitespace and comments in a MIME header
          fcb_exit_binary.m4   Function to skip past the end of the current binary text field
          fcb_next_binary.m4   Function to skip to the next binary
          fcb_open_cifin.m4   Function to open a CBF file for reading
          fcb_packed.m4   Functions to read a JPA CCP4 compressed image
          fcb_read_bits.m4   Functions to read nay number of bits as an integer
          fcb_read_image.m4   Functions to read the next image in I2, I4, 3D_I2 and 3D_I4 format
          fcb_read_xds_i2.m4   Function to read a single xds image.
          fcblib_defines.m4   General m4 macro file for FCBLIB routines.

    In the "examples" subdirectory, there are 2 additional files used by the example programs (section 5) for reading MAR300, MAR345 or ADSC CCD images:

      img.c  img.h  Simple image library

    and the example programs themselves:

      makecbf.c  Make a CBF file from an image
      img2cif.c  Make an imgCIF or CBF from an image
      cif2cbf.c  Copy a CIF/CBF to a CIF/CBF
      convert_image.c  Convert an image file to a cbf using a template file
      cif2c.c  Convert a template cbf file into a function to produce the same template in an internal cbf data structure
      testcell.C  Exercise the cell functions

    as well as three template files: template_adscquantum4_2304x2304.cbf, template_mar345_2300x2300.cbf, and template_adscquantum315_3072x3072.cbf.

    Two additional examples (test_fcb_read_image.f90 and test_xds_binary.f90) are created from two files (test_fcb_read_image.m4 and test_xds_binary.m4) in the m4 directory.

    The documentation files are in the "doc" subdirectory:

      CBFlib.html  This document (HTML)
      CBFlib.txt  This document (ASCII)
      CBFlib_NOTICES.html  Important NOTICES -- PLEASE READ
      CBFlib_NOTICES.txt  Important NOTICES -- PLEASE READ
      gpl.txt  GPL -- PLEASE READ
      lgpl.txt  LGPL -- PLEASE READ
      cbf_definition_rev.txt  Draft CBF/ImgCIF definition (ASCII)
      cbf_definition_rev.html  Draft CBF/ImgCIF definition (HTML)
      cif_img.html  CBF/ImgCIF extensions dictionary (HTML)
      cif_img.dic  CBF/ImgCIF extensions dictionary (ASCII)
      ChangeLog,html  Summary of change history (HTML)
      ChangeLog  Summary of change history (ASCII)

    5. Example programs

    The example programs makecbf.c, img2cif.c and convert_image.c read an image file from a MAR300, MAR345 or ADSC CCD detector and then uses CBFlib to convert it to CBF format (makecbf) or either imgCIF or CBF format (img2cif). makecbf writes the CBF-format image to disk, reads it in again, and then compares it to the original. img2cif just writes the desired file. makecbf works only from stated files on disk, so that random I/O can be used. img2cif includes code to process files from stdin and to stdout. convert_image reads a template as well as the image file and produces a complete CBF. The program convert_minicbf reads a minimal CBF file with just and image and some lines of text specifying the parameters of the data collection as done at SLS and combines the result with a template to produce a full CBF. The program cif2cbf can be used to convert among carious compression and encoding schemes. The program sauter_test.C is a C++ test program contributed by Nick Sauter to help in resolving a memory leak he found. The programs adscimg2cbf and cbf2adscimg are a "jiffies" contributed by Chris Nielsen of ADSC to convert ADSC images to imgCIF/CBF format and vice versa.

    makecbf.c is a good example of how many of the CBFlib functions can be used. To compile makecbf and the other example programs use the Makefile in the top-level directory:

         make all
    
    This will place the programs in the bin directory.

    makecbf

    To run makecbf with the example image, type:

         ./bin/makecbf example.mar2300 test.cbf
    

    The program img2cif has the following command line interface:

     img2cif     [-i  input_image]                               \
                 [-o  output_cif]                                \
                 [-c  {p[acked]|c[annonical]|[n[one]}]           \
                 [-m  {h[eaders]|n[oheaders]}]                   \
                 [-d  {d[igest]|n[odigest]}]                     \
                 [-e  {b[ase64]|q[uoted-printable]|              \
                       d[ecimal]|h[exadecimal]|o[ctal]|n[one]}]  \
                 [-b  {f[orward]|b[ackwards]}]                   \
                 [input_image] [output_cif]
    
     the options are:
    
     -i  input_image (default: stdin)
         the input_image file in MAR300, MAR345 or ADSC CCD detector
         format is given.  If no input_image file is specified or is
         given as "-", an image is copied from stdin to a temporary file.
    
     -o  output_cif (default: stdout)
         the output cif (if base64 or quoted-printable encoding is used)
         or cbf (if no encoding is used).  if no output_cif is specified
         or is given as "-", the output is written to stdout
    
     -c  compression_scheme (packed, canonical or none, default packed)
    
     -m  [no]headers (default headers for cifs, noheaders for cbfs)
         selects MIME (N. Freed, N. Borenstein, RFC 2045, November 1996)
         headers within binary data value text fields.
    
     -d  [no]digest  (default md5 digest [R. Rivest, RFC 1321, April
         1992 using"RSA Data Security, Inc. MD5 Message-Digest
         Algorithm"] when MIME headers are selected)
    
     -e  encoding (base64, quoted-printable, decimal, hexadecimal,
         octal or none, default: base64) specifies one of the standard
         MIME encodings (base64 or quoted-printable) or a non-standard
         decimal, hexamdecimal or octal encoding for an ascii cif
         or "none" for a binary cbf
    
     -b  direction (forward or backwards, default: backwards)
         specifies the direction of mapping of bytes into words
         for decimal, hexadecimal or octal output, marked by '>' for
         forward or '<' for backwards as the second character of each
         line of output, and in '#' comment lines.
    
    

    cif2cbf

    The test program cif2cbf uses many of the same command line options as img2cif, but accepts either a CIF or a CBF as input instead of an image file:

      cif2cbf [-i input_cif] [-o output_cbf] \
        [-u update_cif] \
        [-c {p[acked]|c[annonical]|{b[yte_offset]}|\
            {v[2packed}|{f[latpacked}[n[one]}] \
        [-C highclipvalue] \
        [-D ] \
        [-I {0|2|4|8}] \
        [-R {0|4|8}] \
        [-L {0|4|8}] \
        [-m {h[eaders]|noh[eaders]}] \
        [-m {d[imensions]|nod[imensions}] \
        [-d {d[igest]|n[odigest]|w[arndigest]}] \
        [-B {read|liberal|noread}] [-B {write|nowrite}] \
        [-S {read|noread}] [-S {write|nowrite}] \
        [-T {read|noread}] [-T {write|nowrite}] \
        [-e {b[ase64]|q[uoted-printable]|\
                      d[ecimal]|h[examdecimal|o[ctal]|n[one]}] \
        [-b {f[orward]|b[ackwards]}\
        [-p {1|2|4}\
        [-v dictionary]* [-w] [-W]\
        [input_cif] [output_cbf] 
    
      the options are:
    
        -i input_cif (default: stdin)
          the input  file in CIF or CBF  format.  If input_cif is not
          specified or is given as "-", it is copied from stdin to a
          temporary file.
    
        -o output_cbf (default: stdout)
          the output cif (if base64 or quoted-printable encoding is used)
          or cbf (if no encoding is used).  if no output_cif is specified
          or is given as "-", the output is written to stdout
          if the output_cbf is /dev/null, no output is written.
    
        -u update_cif (no default)
          and optional second input file in CIF or CBF format containing
          data blocks to be merged with data blocks from the primary
          input CIF or CBF
    
        The remaining options specify the characteristics of the
        output cbf.  Most of the characteristics of the input cif are
        derived from context, except when modified by the -B, -S, -T, -v
        and -w flags.
    
        -b byte_order (forward or backwards, default forward (1234) on
          little-endian machines, backwards (4321) on big-endian machines
    
        -B [no]read or liberal (default noread)
          read to enable reading of DDLm style brackets
          liberal to accept whitespace for commas
    
        -B [no]write (default write)
          write to enable writing of DDLm style brackets
    
        -c compression_scheme (packed, canonical, byte_offset,
          v2packed, flatpacked or none,
          default packed)
    
        -C highclipvalue
          specifies a double precision value to which to clip the data
    
        -d [no]digest or warndigest  (default md5 digest [R. Rivest,
          RFC 1321, April 1992 using"RSA Data Security, Inc. MD5
          Message-Digest Algorithm"] when MIME headers are selected)
    
        -D test cbf_construct_detector
    
        -e encoding (base64, k, quoted-printable or none, default base64)
          specifies one of the standard MIME encodings for an ascii cif
          or "none" for a binary cbf
    
        -I 0 or integer element size
          specifies integer conversion of the data, 0 to use the input
          number of bytes, 2, 4 or 8 for short, long or long long
          output integers
    
        -L lowclipvalue
          specifies a double precision value to cut off the data from
          below
    
        -m [no]headers (default headers)
          selects MIME (N. Freed, N. Borenstein, RFC 2045, November 1996)
          headers within binary data value text fields.
    
        -m [nod]imensions (default dimensions)
          selects detailed recovery of dimensions from the input CIF
          for use in the MIME header of the output CIF
    
        -p K_of_padding (0, 1, 2, 4) for no padding after binary data
          1023, 2047 or 4095 bytes of padding after binary data
    
        -R 0 or integer element size
          specifies real conversion of the data, 0 to use the input
          number of bytes,  4 or 8 for float or double output reals 
    
        -S [no]read or (default noread)
          read to enable reading of whitespace and comments
    
        -S [no]write (default write)
          write to enable writing of whitespace and comments
    
        -T [no]read or (default noread)
          read to enable reading of DDLm style triple quotes
    
        -T [no]write (default write)
          write to enable writing of DDLm style triple quotes
    
        -v dictionary specifies a dictionary to be used to validate
          the input cif and to apply aliases to the output cif.
          This option may be specified multiple times, with dictionaries
          layered in the order given.
    
        -w process wide (2048 character) lines
    
        -W write wide (2048 character) lines
    
    

    convert_image

    The program convert_image requires two arguments: imagefile and cbffile. Those are the primary input and output. The detector type is extracted from the image file or from the command line, converted to lower case and used to construct the name of a template cbf file to use for the copy. The template file name is of the form template_name_columnsxrows. The full set of options is:

    
      convert_image [-i input_img] [-o output_cbf] [-p template_cbf]\
        [-d detector name]  -m [x|y|x=y] [-z distance]              \
        [-c category_alias=category_root]*                          \
        [-t tag_alias=tag_root]* [-F] [-R]                          \
        [input_img] [output_cbf]
    
      the options are:
    
      -i input_img (default: stdin)
        the input file as an image in smv, mar300, or mar345  format.
        If input_img is not specified or is given as "-", it is copied
        from stdin to a temporary file.
    
      -p template_cbf
        the template for the final cbf to be produced.  If template_cbf
        is not specified the name is constructed from the first token
        of the detector name and the image size as
           template_<type>_<columns>x<rows>.cbf
    
      -o output_cbf (default: stdout )
        the output cbf combining the image and the template.  If the
        output_cbf is not specified or is given as "-", it is written
        to stdout.
    
      -d detectorname
        a detector name to be used if none is provided in the image
        header.
    
      -F
        when writing packed compression, treat the entire image as
        one line with no averaging
    
      -m [x|y|x=y] (default x=y, square arrays only)
        mirror the array in the x-axis (y -> -y)
                         in the y-axis (x -> -x)
                      or in x=y ( x -> y, y-> x)
    
      -r n
        rotate the array n times 90 degrees counter clockwise
        x -> y, y -> -x for each rotation, n = 1, 2 or 3
    
      -R
        if setting a beam center, set reference values of
        axis settings as well as standard settings
    
      -z distance
        detector distance along Z-axis
    
      -c category_alias=category_root
      -t tag_alias=tagroot
        map the given alias to the given root, so that instead
        of outputting the alias, the root will be presented in the
        output cbf instead.  These options may be repeated as many
        times as needed.
    

    convert_minicbf

    The program convert_minicbf requires two arguments: minicbf and cbffile. Those are the primary input and output. The detector type is extracted from the image file or from the command line, converted to lower case and used to construct the name of a template cbf file to use for the copy. The template file name is of the form template_name_columnsxrows. The full set of options is:

    
      convert_minicbf [-i input_cbf] [-o output_cbf] [-p template_cbf]\
        [-q] [-C convention]                                        \
        [-d detector name]  -m [x|y|x=y] [-z distance]              \
        [-c category_alias=category_root]*                          \
        [-t tag_alias=tag_root]* [-F] [-R]                          \
        [input_cbf] [output_cbf]
    
      the options are:
    
      -i input_cbf (default: stdin)
        the input file as a CBF with at least an image.
    
      -p template_cbf
        the template for the final cbf to be produced.  If template_cbf
        is not specified the name is constructed from the first token
        of the detector name and the image size as
           template_<type>_<columns>x<rows>.cbf
    
      -o output_cbf (default: stdout )
        the output cbf combining the image and the template.  If the
        output_cbf is not specified or is given as "-", it is written
        to stdout.
    
      -q
        exit quickly with just the miniheader expanded
        after the data.  No template is used.
    
      -Q
        exit quickly with just the miniheader unexpanded
        before the data.  No template is used.
    
      -C convention
        convert the comment form of miniheader into the
            _array_data.header_convention convention
            _array_data.header_contents
        overriding any existing values
    
      -d detectorname
        a detector name to be used if none is provided in the image
        header.
    
      -F
        when writing packed compression, treat the entire image as
        one line with no averaging
    
      -m [x|y|x=y] (default x=y, square arrays only)
        mirror the array in the x-axis (y -> -y)
                         in the y-axis (x -> -x)
                      or in x=y ( x -> y, y-> x)
    
      -r n
        rotate the array n times 90 degrees counter clockwise
        x -> y, y -> -x for each rotation, n = 1, 2 or 3
    
      -R
        if setting a beam center, set reference values of
        axis settings as well as standard settings
    
      -z distance
        detector distance along Z-axis
    
      -c category_alias=category_root
      -t tag_alias=tagroot
        map the given alias to the given root, so that instead
        of outputting the alias, the root will be presented in the
        output cbf instead.  These options may be repeated as many
        times as needed.
    
    

    testreals, testflat and testflatpacked

    The example programs testreals, testflat and testflatpacked exercise the handling of reals, byte_offset compression and packed compression. Each is run without any arguments. testreals will read real images from the data file testrealin.cbf and write a file with real images in testrealout.cbf, which should be identical to testrealin.cbf. testflat and testflatpacked read 4 1000x1000 2D images and one 50x60x70 3D image and produce an output file that should be identical to the input. testflat reads testflatin.cbf and produces testflatout.cbf using CBF_BYTE_OFFSET compression. testflatpacked reads testflatpackedin.cbf and produces testflatpackedout.cbf. The images are:

    • A 1000 x 1000 array of 32-bit integers forming a flat field with all pixels set to 1000.
    • A 1000 x 1000 array of 16-bit integers forming a flat field with all pixels set to 1000.
    • A 1000 x 1000 array of 32-bit integers forming a flat field with all pixels set to 1000, except for -3 along the main diagonal and its transpose.
    • A 1000 x 1000 array of 16-bit integers forming a flat field with all pixels set to 1000, except for -3 along the main diagonal and its transpose.
    • A 50 x 60 x 70 array of 32-bit integers in a flat field of 1000, except for -3 along the main diagonal and the values i+j+k (counting from zero) every 1000th pixel

    test_fcb_read_image, test_xds_binary

    The example programs test_fcb_read_image and test_xds_binary are designed read the output of testflat and testflatpacked using the FCBlib routines in lib/libfcb. test_xds_binary reads only the first image and closes the file immediately. test_fcb_read_image reads all 5 images from the input file. The name of the input file should be provided on stdin, as in:

    • echo testflatout.cbf | bin/test_xds_binary
    • echo testflatpackedout.cbf | bin/test_xds_binary
    • echo testflatout.cbf | bin/test_fcb_read_image
    • echo testflatpackedout.cbf | bin/test_fcb_read_image

    In order to compile these programs correctly for the G95 compiler it is important to set the record size for reading to be no larger than the padding after binary images. This in controlled in Makefile by the line M4FLAGS = -Dfcb_bytes_in_rec=131072 which provides good performance for gfortran. For g95, this line must be changed to M4FLAGS = -Dfcb_bytes_in_rec=4096

    sauter_test

    The program sauter_test.C is a C++ test program contributed by Nick Sauter to help in resolving a memory leak he found. The program is run as bin/sauter_test and should run long enough to allow a check with top to ensure that it has constant memory demands. In addition, starting with release 0.7.8.1, the addition of -DCBFLIB_MEM_DEBUG to the compiler flags will cause detailed reports on memory use to stderr to be reported.

    adscimg2cbf

    The example program adscimg2cbf accepts any number of raw or compressed ADSC images with .img, .img.gz, .img.bz2 or .img.Z extensions and converts each of them to an imgCIF/CBF file with a .cbf extension.

    
      adscimg2cbf [--flag[,modifier]] file1.img ... filen.img     (creates file1.cbf ... filen.cbf)
             Image files may also be compressed (.gz, .bz2, .Z)
    
      Flags:
        --cbf_byte_offset   Use BYTE_OFFSET compression (DEFAULT)
        --cbf_packed        Use CCP4 packing (JPA) compression.
        --cbf_packed_v2     Use CCP4 packing version 2 (JPA) compression.
        --no_compression    No compression.
    
      The following two modifiers can be appended to the flags (syntax: --flag,modifier):
        flat            Flat (linear) images.
        uncorrelated    Uncorrelated sections.
    

    adscimg2cbf

    The example program cbf2adscimg accepts any number of cbfs of ADSC images created by adscimg1cbf or convert_image and produces raw or compressed adsc image files with .img, .img.gz or .img.bz2 extensions.

    
      cbf2adscimg [--flag] file1.cbf ... filen.cbf     (creates file1.img ... filen.img)
             Image files may be compressed on output: (.gz, .bz2) by using the flags below.\n");
    
      Flags:
        --gz    Output a .gz file  (e.g., filen.img.gz).
        --bz2   Output a .bz2 file (e.g., filen.img.bz2).
    

    tiff2cbf

    The test program tiff2cbf converts a tiff data file to a cbf data file. The program converts the tiff data samples directly into a minicbf with the tiff header stored at the value of _array_data.header_contents. This conversion is supported for the sample formats SAMPLEFORMAT_UINT (unsigned integer data), SAMPLEFORMAT_INT (unsigned integer data), SAMPLEFORMAT_INT (signed integer data), SAMPLEFORMAT_IEEEFP (IEEE floating point data), SAMPLEFORMAT_COMPLEXINT (complex signed int) and SAMPLEFORMAT_COMPLEXIEEEFP (complex ieee floating). Conversions from these formats to other CBF formats can be handled by cif2cbf. If you wish to convert and xxx.tif written with IEEE floating point samples into a CBF with integer values compressed by byte-offset compression for use by XDS, creating an xxx_view.cbf with values clipped between 0 and 100, and an xxx_xds.cbf with unclipped values for processing:

    
      tiff2cbf xxx.tif xxx.cbf
      cif2cbf -I 4 -C 100. -L 0. -e n -c b -i xxx.cbf -o xxx_view.cbf
      cif2cbf -I 4 -e n -c b -i xxx.cbf -o xxx_xds.cbf
      
    



    Updated 29 March 2011. Contact:
    ./CBFlib-0.9.2.2/doc/Dhistory.html0000644000076500007650000007023311603702115015043 0ustar yayayaya (IUCr) CIF dictionary cif_img.dic revision history

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    Revision history

    ========================================================================
    Version 1.5.4 (2007-07-28)
    ------------------------------------------------------------------------
      Typographics corrections (HJB)
    
         + Corrected embedded degree characters to \%
         + Corrected embedded Aring to \%A
         + Added trailing ^ for a power
         + Removed 2 cases of a space after an underscore
           in tag name.
    
    ========================================================================
    Version 1.5.3 (2007-07-08)
    ------------------------------------------------------------------------
      Changes to support SLS miniCBF and suggestions
       from the 24 May 07 BNL imgCIF workshop (HJB)
    
         + Added new data items
           '_array_data.header_contents',
           '_array_data.header_convention',
           '_diffrn_data_frame.center_fast',
           '_diffrn_data_frame.center_slow',
           '_diffrn_data_frame.center_units',
           '_diffrn_measurement.sample_detector_distance',
           '_diffrn_measurement.sample_detector_voffset
         + Deprecated data items
           '_diffrn_detector_element.center[1]',
           '_diffrn_detector_element.center[2]'
         + Added comments and example on miniCBF
         + Changed all array_id data items to implicit
    
    ========================================================================
    Version 1.5.2 (2007-05-06)
    ------------------------------------------------------------------------
      Further clarifications of the coordinate system. (HJB)
    
    ========================================================================
    Version 1.5.1 (2007-04-26)
    ------------------------------------------------------------------------
      Improve defintion of X-axis to cover the case of no goniometer
       and clean up more line folds (HJB)
    
    ========================================================================
    Version 1.5 (2007-07-25)
    ------------------------------------------------------------------------
      This is a cummulative list of the changes proposed since the
       imgCIF workshop in Hawaii in July 2006.  It is the result
       of contributions by H. J. Bernstein, A. Hammersley,
       J. Wright and W. Kabsch.
    
       2007-02-19 Consolidated changes (edited by HJB)
         + Added new data items
           '_array_structure.compression_type_flag',
           '_array_structure_list_axis.fract_displacement',
           '_array_structure_list_axis.displacement_increment',
           '_array_structure_list_axis.reference_angle',
           '_array_structure_list_axis.reference_displacement',
           '_axis.system',
           '_diffrn_detector_element.reference_center_fast',
           '_diffrn_detector_element.reference_center_slow',
           '_diffrn_scan_axis.reference_angle',
           '_diffrn_scan_axis.reference_displacement',
           '_map.details', '_map.diffrn_id',
           '_map.entry_id', '_map.id',
           '_map_segment.array_id', '_map_segment.binary_id',
           '_map_segment.mask_array_id', '_map_segment.mask_binary_id',
           '_map_segment.id', '_map_segment.map_id',
           '_map_segment.details.
         + Change type of
           '_array_structure.byte_order' and
           '_array_structure.compression_type'
           to ucode to make these values case-insensitive
         + Add values 'packed_v2' and 'byte_offset' to enumeration of values for
           '_array_structure.compression_type'
         + Add to definitions for the binary data type to handle new compression 
           types, maps, and a variety of new axis types.
        2007-07-25 Cleanup of typos for formal release (HJB)
         + Corrected text fields for reference_ tag descriptions that
           were off by one column
         + Fix typos in comments listing fract_ tags
         + Changed name of release from 1.5_DRAFT to 1.5
         + Fix unclosed text fields in various map definitions
    
    
    ========================================================================
    Version 1.4 (2006-07-04)
    ------------------------------------------------------------------------
      This is a change to reintegrate all changes made in the course of
       publication of ITVG, by the RCSB from April 2005 through
       August 2008 and changes for the 2006 imgCIF workshop in
       Hawaii.
    
       2006-07-04 Consolidated changes for the 2006 imgCIF workshop (edited by HJB)
         + Correct type of '_array_structure_list.direction' from 'int' to 'code'.
         + Added new data items suggested by CN
           '_diffrn_data_frame.details'
           '_array_intensities.pixel_fast_bin_size',
           '_array_intensities.pixel_slow_bin_size and
           '_array_intensities.pixel_binning_method
         + Added deprecated item for completeness
           '_diffrn_frame_data.details'
         + Added entry for missing item in contents list
           '_array_structure_list_axis.displacement'
         + Added new MIME type X-BASE32K based on work by VL, KM, GD, HJB
         + Correct description of MIME boundary delimiter to start in
           column 1.
         + General cleanup of text fields to conform to changes for ITVG
           by removing empty lines at start and finish of text field.
         + Amend example for ARRAY_INTENSITIES to include binning.
         + Add local copy of type specification (as 'code') for all children
           of '_diffrn.id'.
         + For consistency, change all references to 'pi' to '\p' and all
           references to 'Angstroms' to '\%Angstroms'.
         + Clean up all powers to use IUCr convention of '^power^', as in
           '10^3^' for '10**3'.
         + Update 'yyyy-mm-dd' type regex to allow truncation from the right
           and improve comments to explain handling of related mmCIF
           'yyyy-mm-dd:hh:mm' type, and use of 'Z' for GMT time zone.
    
       2005-03-08 and
       2004-08-08 fixed cases where _item_units.code  used
                  instead of _item_type.code (JDW)
       2004-04-15 fixed item ordering in
                   _diffrn_measurement_axis.measurement_id
                   added sub_category 'vector' (JDW)
    
    ========================================================================
    Version 1.3.2 (2005-06-25)
    ------------------------------------------------------------------------
      2005-06-25 ITEM_TYPE_LIST: code, ucode, line, uline regexps updated
                  to those of current mmCIF; float modified by allowing integers
                  terminated by a point as valid. The 'time' part of
                  yyyy-mm-dd types made optional in the regexp. (BM)
    
       2005-06-17 Minor corrections as for proofs for IT G Chapter 4.6
       (NJA)
    
       2005-02-21  Minor corrections to spelling and punctuation
       (NJA)
    
       2005-01-08 Changes as per Nicola Ashcroft.
       + Updated example 1 for DIFFRN_MEASUREMENT to agree with mmCIF.
       + Spelled out "micrometres" for "um" and "millimetres" for "mm".
       + Removed phrase "which may be stored" from ARRAY_STRUCTURE
         description.
       + Removed unused 'byte-offsets' compressions and updated
         cites to ITVG for '_array_structure.compression_type'.
       (HJB)
    
    ========================================================================
    Version 1.3.1 (2003-08-13)
    ------------------------------------------------------------------------
    
       Changes as per Frances C. Bernstein.
       + Identify initials.
       + Adopt British spelling for centre in text.
       + Set \p and \%Angstrom and powers.
       + Clean up commas and unclear wordings.
       + Clean up tenses in history.
       Changes as per Gotzon Madariaga.
       + Fix the ARRAY_DATA example to align '_array_data.binary_id'
       and X-Binary-ID.
       + Add a range to '_array_intensities.gain_esd'.
       + In the example of DIFFRN_DETECTOR_ELEMENT,
       '_diffrn_detector_element.id' and
       '_diffrn_detector_element.detector_id' interchanged.
       + Fix typos for direction, detector and axes.
       + Clarify description of polarisation.
       + Clarify axes in '_diffrn_detector_element.center[1]'
        '_diffrn_detector_element.center[2]'.
       + Add local item types for items that are pointers.
       (HJB)
    
    ========================================================================
    Version 1.3.0 (2003-07-24)
    ------------------------------------------------------------------------
    
       Changes as per Brian McMahon.
       + Consistently quote tags embedded in text.
       + Clean up introductory comments.
       + Adjust line lengths to fit in 80 character window.
       + Fix several descriptions in AXIS category which
         referred to '_axis.type' instead of the current item.
       + Fix erroneous use of deprecated item
         '_diffrn_detector_axis.id' in examples for
         DIFFRN_SCAN_AXIS.
       + Add deprecated items '_diffrn_detector_axis.id'
         and '_diffrn_measurement_axis.id'.
       (HJB)
    
    ========================================================================
    Version 1.2.4 (2003-07-14)
    ------------------------------------------------------------------------
    
       Changes as per I. David Brown.
       + Enhance descriptions in DIFFRN_SCAN_AXIS to make them less
         dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS.
       + Provide a copy of the deprecated DIFFRN_FRAME_DATA
         category for completeness.
       (HJB)
    
    ========================================================================
    Version 1.2.3 (2003-07-03)
    ------------------------------------------------------------------------
    
       Cleanup to conform to ITVG.
       + Correct sign error in ..._cubed units.
       + Correct '_diffrn_radiation.polarisn_norm' range.
       (HJB)
    
    ========================================================================
    Version 1.2.2 (2003-03-10)
    ------------------------------------------------------------------------
    
       Correction of typos in various DIFFRN_SCAN_AXIS descriptions.
       (HJB)
    
    ========================================================================
    Version 1.2.1 (2003-02-22)
    ------------------------------------------------------------------------
    
       Correction of ATOM_ for ARRAY_ typos in various descriptions.
       (HJB)
    
    ========================================================================
    Version 1.2 (2003-02-07)
    ------------------------------------------------------------------------
    
       Corrections to encodings (remove extraneous hyphens) remove
       extraneous underscore in '_array_structure.encoding_type'
       enumeration.  Correct typos in items units list.  (HJB)
    
    ========================================================================
    Version 1.1.3 (2001-04-19)
    ------------------------------------------------------------------------
    
       Another typo corrections by Wilfred Li, and cleanup by HJB.
    
    ========================================================================
    Version 1.1.2 (2001-03-06)
    ------------------------------------------------------------------------
    
       Several typo corrections by Wilfred Li.
    
    ========================================================================
    Version 1.1.1 (2001-02-16)
    ------------------------------------------------------------------------
    
       Several typo corrections by JW.
    
    ========================================================================
    Version 1.1 (2001-02-06)
    ------------------------------------------------------------------------
    
       Draft resulting from discussions on header for use at NSLS.  (HJB)
    
       + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME.
    
       + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'.
    
       + Add '_diffrn_measurement_axis.measurement_device' and change
         '_diffrn_measurement_axis.id' to
         '_diffrn_measurement_axis.measurement_id'.
    
       + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source',
        '_diffrn_radiation.div_x_y_source',
        '_diffrn_radiation.polarizn_source_norm',
       '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end',
       '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr',
       '_diffrn_scan_axis.displacement_rstrt_incr',
       '_diffrn_scan_frame_axis.angle_increment',
       '_diffrn_scan_frame_axis.angle_rstrt_incr',
       '_diffrn_scan_frame_axis.displacement',
       '_diffrn_scan_frame_axis.displacement_increment',and
       '_diffrn_scan_frame_axis.displacement_rstrt_incr'.
    
       + Add '_diffrn_measurement.device' to category key.
    
       + Update yyyy-mm-dd to allow optional time with fractional seconds
         for time stamps.
    
       + Fix typos caught by RS.
    
       + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to
         allow for coupled axes, as in spiral scans.
    
       + Add examples for fairly complete headers thanks to R. Sweet and P.
         Ellis.
    
    ========================================================================
    Version 1.0 (2000-12-21)
    ------------------------------------------------------------------------
    
       Release version - few typos and tidying up.  (BM & HJB)
    
       + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end
       of dictionary.
    
       + Alphabetize dictionary.
    
    ========================================================================
    Version 0.7.1 (2000-09-29)
    ------------------------------------------------------------------------
    
       Cleanup fixes.  (JW)
    
       + Correct spelling of diffrn_measurement_axis in '_axis.id'
    
       + Correct ordering of uses of '_item.mandatory_code' and
       '_item_default.value'.
    
    ========================================================================
    Version 0.7.0 (2000-09-09)
    ------------------------------------------------------------------------
    
       Respond to comments by I. David Brown.  (HJB)
    
       + Add further comments on '\n' and '\t'.
    
       + Update ITEM_UNITS_LIST by taking section from mmCIF dictionary
         and adding metres.  Change 'meter' to 'metre' throughout.
    
       + Add missing enumerations to '_array_structure.compression_type'
         and make 'none' the default.
    
       + Remove parent-child relationship between
         '_array_structure_list.index' and '_array_structure_list.precedence'.
    
       + Improve alphabetization.
    
       + Fix '_array_intensities_gain.esd' related function.
    
       + Improve comments in AXIS.
    
       + Fix DIFFRN_FRAME_DATA example.
    
       + Remove erroneous DIFFRN_MEASUREMENT example.
    
       + Add '_diffrn_measurement_axis.id' to the category key.
    
    ========================================================================
    Version 0.6.0 (1999-01-14)
    ------------------------------------------------------------------------
    
       Remove redundant information for ENC_NONE data.  (HJB)
    
       + After the D5 remove binary section identifier, size and
         compression type.
    
       + Add Control-L to header.
    
    ========================================================================
    Version 0.5.1 (1999-01-03)
    ------------------------------------------------------------------------
    
       Cleanup of typos and syntax errors.  (HJB)
    
       + Cleanup example details for DIFFRN_SCAN category.
    
       + Add missing quote marks for '_diffrn_scan.id' definition.
    
    ========================================================================
    Version 0.5 (1999-01-01)
    ------------------------------------------------------------------------
    
       Modifications for axis definitions and reduction of binary header.  (HJB)
    
       + Restore '_diffrn_detector.diffrn_id' to DIFFRN_DETECTOR KEY.
    
       + Add AXIS category.
    
       + Bring in complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories
         from cif_mm.dic for clarity.
    
       + Change '_array_structure.encoding_type' from type code to uline and
         added X-Binary-Element-Type to MIME header.
    
       + Add detector beam centre '_diffrn_detector_element.center[1]' and
         '_diffrn_detector_element.center[2]'.
    
       + Correct item name of '_diffrn_refln.frame_id'.
    
       + Replace reference to '_array_intensities.undefined' by
         '_array_intensities.undefined_value'.
    
       + Replace references to '_array_intensity.scaling' with
         '_array_intensities.scaling'.
    
       + Add DIFFRN_SCAN... categories.
    
    ========================================================================
    Version 0.4 (1998-08-11)
    ------------------------------------------------------------------------
    
       Modifications to the 0.3 imgCIF draft.  (HJB)
    
       + Reflow comment lines over 80 characters and corrected typos.
    
       + Update examples and descriptions of MIME encoded data.
    
       + Change name to cbfext98.dic.
    
    ========================================================================
    Version 0.3 (1998-07-04)
    ------------------------------------------------------------------------
    
       Modifications for imgCIF.  (HJB)
    
       + Add binary type, which is a text field containing a variant on
         MIME encoded data.
    
       + Change type of '_array_data.data' to binary and specify internal
         structure of raw binary data.
    
       + Add '_array_data.binary_id', and make
         '_diffrn_frame_data.binary_id' and '_array_intensities.binary_id'
         into pointers to this item.
    
    ========================================================================
    Version 0.2 (1997-12-02)
    ------------------------------------------------------------------------
    
       Modifications to the CBF draft.  (JW)
    
       + Add category hierarchy for describing frame data developed from
         discussions at the BNL imgCIF Workshop Oct 1997.   The following
         changes are made in implementing the workshop draft.  Category
         DIFFRN_ARRAY_DATA is renamed to DIFFRN_FRAME_DATA.  Category
         DIFFRN_FRAME_TYPE is renamed to DIFFRN_DETECTOR_ELEMENT.   The
         parent item for '_diffrn_frame_data.array_id' is changed from
         '_array_structure_list.array_id' to '_array_structure.id'. Item
         '_diffrn_detector.array_id' is deleted.
       + Add data item '_diffrn_frame_data.binary_id' to identify data
         groups within a binary section.  The formal identification of the
         binary section is still fuzzy.
    
    ========================================================================
    Version 0.1 (1997-01-24)
    ------------------------------------------------------------------------
    
       First draft of this dictionary in DDL 2.1 compliant format by John
       Westbrook (JW).  This version is adapted from the Crystallographic
       Binary File (CBF) Format Draft Proposal provided by Andy Hammersley
       (AH).
    
       Modifications to the CBF draft.  (JW)
    
       + In this version the array description has been cast in the categories
         ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST.  These categories
         have been generalized to describe array data  of arbitrary dimension.
    
       + Array data in this description are contained in the category
         ARRAY_DATA.  This departs from the CBF notion of data existing
         in some special comment. In this description, data are handled as an
         ordinary data item encapsulated in a character data type.   Although
         data this manner deviates from CIF conventions, it does not violate
         any DDL 2.1 rules.  DDL 2.1 regular expressions can be used to define
         the binary representation which will permit some level of data
         validation.  In this version, the placeholder type code "any" has
         been used. This translates to a regular expression which will match
         any pattern.
    
         It should be noted that DDL 2.1 already supports array data objects
         although these have not been used in the current mmCIF dictionary.
         It may be possible to use the DDL 2.1 ITEM_STRUCTURE and
         ITEM_STRUCTURE_LIST categories to provide the information that is
         carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST.  By
         moving the array structure to the DDL level it would be possible to
         define an array type as well as a regular expression defining the
         data format.
    
       + Multiple array sections can be properly handled within a single
         datablock.
    
    ========================================================================
    

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Iarray_structure_list_axis.axis_set_id.html0000644000076500007650000000624211603702115023155 0ustar yayayaya (IUCr) CIF Definition save__array_structure_list_axis.axis_set_id

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _array_structure_list_axis.axis_set_id

    Name:
    '_array_structure_list_axis.axis_set_id'

    Definition:

            The value of this data item is the identifier of the
                   set of axes for which axis settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   _array_structure_list_axis.axis_set_id.
    
                   This item is a pointer to
                   _array_structure_list.axis_set_id
                   in the ARRAY_STRUCTURE_LIST category.
    
                   If this item is not specified, it defaults to the corresponding
                   axis identifier.
    
    

    Type: code

    Mandatory item: implicit

    Category: array_structure_list_axis

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_detector.detector.html0000644000076500007650000000635411603702115020323 0ustar yayayaya (IUCr) CIF Definition save__diffrn_detector.detector

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_detector.detector

    Name:
    '_diffrn_detector.detector'

    Definition:

            The general class of the radiation detector.
    
    
    Examples:

    'photographic film'
    'scintillation counter'
    'CCD plate'
    'BF~3~ counter'

    Type: text

    Mandatory item: no

    Aliases:


    _diffrn_radiation_detector (cifdic.c91 version 1.0)
    _diffrn_detector (cif_core.dic version 2.0)

    Category: diffrn_detector

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/.undosymlinks0000755000076500007650000001053511603747624015130 0ustar yayayaya#!/bin/sh ###################################################################### # # # .undosymlinks for CBFlib/doc directory # # # # # # Version 0.7.8.2 25 Jun 2007 # # # # Paul Ellis and # # Herbert J. Bernstein (yaya@bernstein-plus-sons.com) # # # # (C) Copyright 2006 - 2007 Herbert J. Bernstein # # # ###################################################################### ###################################################################### # # # YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL # # # # ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS # # OF THE LGPL # # # ###################################################################### ########################### GPL NOTICES ############################## # # # This program is free software; you can redistribute it and/or # # modify it under the terms of the GNU General Public License as # # published by the Free Software Foundation; either version 2 of # # (the License, or (at your option) any later version. # # # # This program is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # # GNU General Public License for more details. # # # # You should have received a copy of the GNU General Public License # # along with this program; if not, write to the Free Software # # Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA # # 02111-1307 USA # # # ###################################################################### ######################### LGPL NOTICES ############################### # # # This library is free software; you can redistribute it and/or # # modify it under the terms of the GNU Lesser General Public # # License as published by the Free Software Foundation; either # # version 2.1 of the License, or (at your option) any later version. # # # # This library is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # # Lesser General Public License for more details. # # # # You should have received a copy of the GNU Lesser General Public # # License along with this library; if not, write to the Free # # Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, # # MA 02110-1301 USA # # # ###################################################################### # Usage ./.undosymlinks for file in cif_img.dic cif_img.html cif_img_1_3_2.html \ cif_img_1.5.dic cif_img_1.5.html cif_img_1.5.4.html \ cif_img_1.6.dic cif_img_1.6.html cif_img_1.6.4.dic cif_img_1.6.4.html do rm -rf $file done for file in * do if [ -d "$file" ] ; then if [ -e "$file/.undosymlinks" ] ; then (cd "$file"; sh -c "./.undosymlinks") fi fi done ./CBFlib-0.9.2.2/doc/Idiffrn_data_frame.array_id.html0000644000076500007650000000544011603702115020551 0ustar yayayaya (IUCr) CIF Definition save__diffrn_data_frame.array_id

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_data_frame.array_id

    Name:
    '_diffrn_data_frame.array_id'

    Definition:

           This item is a pointer to _array_structure.id in the
                  ARRAY_STRUCTURE category.
    
    

    Type: code

    Mandatory item: implicit

    Alias:
    _diffrn_frame_data.array_id (cif_img.dic version 1.0)

    Category: diffrn_data_frame

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Imap_segment.map_id.html0000644000076500007650000000476711603702115017107 0ustar yayayaya (IUCr) CIF Definition save__map_segment.map_id

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _map_segment.map_id

    Name:
    '_map_segment.map_id'

    Definition:

            This item is a pointer to _map.id
                   in the MAP category.
    
    

    Type: code

    Mandatory item: yes

    Category: map_segment

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Iarray_data.binary_id.html0000644000076500007650000000676611603702115017427 0ustar yayayaya (IUCr) CIF Definition save__array_data.binary_id

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _array_data.binary_id

    Name:
    '_array_data.binary_id'

    Definition:

           This item is an integer identifier which, along with
                  _array_data.array_id, should uniquely identify the
                  particular block of array data.
    
                  If _array_data.binary_id is not explicitly given,
                  it defaults to 1.
    
                  The value of _array_data.binary_id distinguishes
                  among multiple sets of data with the same array
                  structure.
    
                  If the MIME header of the data array specifies a
                  value for X-Binary-ID, the value of  _array_data.binary_id
                  should be equal to the value given for X-Binary-ID.
    
    

    Type: int

    Mandatory item: implicit

    _diffrn_data_frame.binary_id
    _array_intensities.binary_id

    The permitted range is [1, infinity)

    Enumeration default: 1

    Category: array_data

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_measurement.specimen_support.html0000644000076500007650000000636011603702115022622 0ustar yayayaya (IUCr) CIF Definition save__diffrn_measurement.specimen_support

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_measurement.specimen_support

    Name:
    '_diffrn_measurement.specimen_support'

    Definition:

            The physical device used to support the crystal during data
                   collection.
    
    
    Examples:

    'glass capillary'
    'quartz capillary'
    fiber
    'metal loop'

    Type: text

    Mandatory item: no

    Alias:
    _diffrn_measurement_specimen_support (cif_core.dic version 2.0.1)

    Category: diffrn_measurement

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_radiation.type.html0000644000076500007650000000631211603702115017626 0ustar yayayaya (IUCr) CIF Definition save__diffrn_radiation.type

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_radiation.type

    Name:
    '_diffrn_radiation.type'

    Definition:

            The nature of the radiation. This is typically a description
                   of the X-ray wavelength in Siegbahn notation.
    
    
    Examples:

    CuK\a
    'Cu K\a~1~'
    'Cu K-L~2,3~'
    white-beam

    Type: line

    Mandatory item: no

    Alias:
    _diffrn_radiation_type (cif_core.dic version 2.0.1)

    Category: diffrn_radiation

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_detector.id.html0000644000076500007650000000572211603702115017104 0ustar yayayaya (IUCr) CIF Definition save__diffrn_detector.id

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_detector.id

    Name:
    '_diffrn_detector.id'

    Definition:

            The value of _diffrn_detector.id must uniquely identify
                   each detector used to collect each diffraction data set.
    
                   If the value of _diffrn_detector.id is not given, it is
                   implicitly equal to the value of
                   _diffrn_detector.diffrn_id.
    
    

    Type: code

    Mandatory item: implicit

    _diffrn_detector_axis.detector_id

    Category: diffrn_detector

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Dunitcodes.html0000644000076500007650000001243411603702115015336 0ustar yayayaya (IUCr) CIF dictionary cif_img.dic Unit codes

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF)

    Unit codes

    The following unit codes are defined in this dictionary:

    metres metres
    centimetres centimetres (metres * 10^( -2)^)
    millimetres millimetres (metres * 10^( -3)^)
    nanometres nanometres (metres * 10^( -9)^)
    angstroms \%Angstroms (metres * 10^(-10)^)
    picometres picometres (metres * 10^(-12)^)
    femtometres femtometres (metres * 10^(-15)^)
    reciprocal_metres reciprocal metres (metres^(-1)^)
    reciprocal_centimetres reciprocal centimetres ((metres * 10^( -2)^)^(-1)^)
    reciprocal_millimetres reciprocal millimetres ((metres * 10^( -3)^)^(-1)^)
    reciprocal_nanometres reciprocal nanometres ((metres * 10^( -9)^)^(-1)^)
    reciprocal_angstroms reciprocal \%Angstroms ((metres * 10^(-10)^)^(-1)^)
    reciprocal_picometres reciprocal picometres ((metres * 10^(-12)^)^(-1)^)
    nanometres_squared nanometres squared (metres * 10^( -9)^)^2^
    angstroms_squared \%Angstroms squared (metres * 10^(-10)^)^2^
    8pi2_angstroms_squared 8\p^2^ * \%Angstroms squared (metres * 10^(-10)^)^2^
    picometres_squared picometres squared (metres * 10^(-12)^)^2^
    nanometres_cubed nanometres cubed (metres * 10^( -9)^)^3^
    angstroms_cubed \%Angstroms cubed (metres * 10^(-10)^)^3^
    picometres_cubed picometres cubed (metres * 10^(-12)^)^3^
    kilopascals kilopascals
    gigapascals gigapascals
    hours hours
    minutes minutes
    seconds seconds
    microseconds microseconds
    degrees degrees (of arc)
    degrees_squared degrees (of arc) squared
    degrees_per_minute degrees (of arc) per minute
    celsius degrees (of temperature) Celsius
    kelvins degrees (of temperature) Kelvin
    counts counts
    counts_per_photon counts per photon
    electrons electrons
    electrons_squared electrons squared
    electrons_per_nanometres_cubed electrons per nanometres cubed (electrons/(metres * 10^( -9)^)^(-3)^)
    electrons_per_angstroms_cubed electrons per \%Angstroms cubed (electrons/(metres * 10^(-10)^)^(-3)^)
    electrons_per_picometres_cubed electrons per picometres cubed (electrons/(metres * 10^(-12)^)^(-3)^)
    kilowatts kilowatts
    milliamperes milliamperes
    kilovolts kilovolts
    pixels_per_element (image) pixels per (array) element
    arbitrary arbitrary system of units.

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_scan.frame_id_end.html0000644000076500007650000000532511603702115020216 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan.frame_id_end

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_scan.frame_id_end

    Name:
    '_diffrn_scan.frame_id_end'

    Definition:

            The value of this data item is the identifier of the
                   last frame in the scan.
    
                   This item is a pointer to _diffrn_data_frame.id in the
                   DIFFRN_DATA_FRAME category.
    
    

    Type: code

    Mandatory item: yes

    Category: diffrn_scan

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Iarray_intensities.pixel_fast_bin_size.html0000644000076500007650000000646711603702115023132 0ustar yayayaya (IUCr) CIF Definition save__array_intensities.pixel_fast_bin_size

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _array_intensities.pixel_fast_bin_size

    Name:
    '_array_intensities.pixel_fast_bin_size'

    Definition:

            The value of _array_intensities.pixel_fast_bin_size specifies
                   the number of pixels that compose one element in the direction
                   of the most rapidly varying array dimension.
    
                   Typical values are 1, 2, 4 or 8.  When there is 1 pixel per
                   array element in both directions, the value given for
                   _array_intensities.pixel_binning_method normally should be
                   'none'.
    
                   It is specified as a float to allow for binning algorithms that
                   create array elements that are not integer multiples of the
                   detector pixel size.
    
    

    Type: float

    Mandatory item: implicit


    The permitted range is [0.0, infinity)

    Enumeration default: 1.

    Category: array_intensities

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_radiation.probe.html0000644000076500007650000000631111603702115017753 0ustar yayayaya (IUCr) CIF Definition save__diffrn_radiation.probe

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_radiation.probe

    Name:
    '_diffrn_radiation.probe'

    Definition:

            Name of the type of radiation used. It is strongly
                   recommended that this be given so that the
                   probe radiation is clearly specified.
    
    

    Type: line

    Mandatory item: no

    Alias:
    _diffrn_radiation_probe (cif_core.dic version 2.0.1)
    The data value must be one of the following:


    X-ray

    neutron

    electron

    gamma

    Category: diffrn_radiation

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/cif_img_1.5.html0000777000076500007650000000000011603751102021351 2cif_img_1.5.4_28Jul07.htmlustar yayayaya./CBFlib-0.9.2.2/doc/Cdiffrn_scan.html0000644000076500007650000005333611603702115015622 0ustar yayayaya (IUCr) CIF Definition save_diffrn_scan

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    Category DIFFRN_SCAN

    Name:
    'diffrn_scan'

    Description:

        Data items in the DIFFRN_SCAN category describe the parameters of one
         or more scans, relating axis positions to frames.
    
    
    
    Examples:

    Example 1 - derived from a suggestion by R. M. Sweet. The vector of each axis is not given here, because it is provided in the AXIS category. By making _diffrn_scan_axis.scan_id and _diffrn_scan_axis.axis_id keys of the DIFFRN_SCAN_AXIS category, an arbitrary number of scanning and fixed axes can be specified for a scan. In this example, three rotation axes and one translation axis at nonzero values are specified, with one axis stepping. There is no reason why more axes could not have been specified to step. Range information has been specified, but note that it can be calculated from the number of frames and the increment, so the data item _diffrn_scan_axis.angle_range could be dropped. Both the sweep data and the data for a single frame are specified. Note that the information on how the axes are stepped is given twice, once in terms of the overall averages in the value of _diffrn_scan.integration_time and the values for DIFFRN_SCAN_AXIS, and precisely for the given frame in the value for _diffrn_scan_frame.integration_time and the values for DIFFRN_SCAN_FRAME_AXIS. If dose-related adjustments are made to scan times and nonlinear stepping is done, these values may differ. Therefore, in interpreting the data for a particular frame it is important to use the frame-specific data.
     
          _diffrn_scan.id                   1
          _diffrn_scan.date_start         '2001-11-18T03:26:42'
          _diffrn_scan.date_end           '2001-11-18T03:36:45'
          _diffrn_scan.integration_time    3.0
          _diffrn_scan.frame_id_start      mad_L2_000
          _diffrn_scan.frame_id_end        mad_L2_200
          _diffrn_scan.frames              201
    
           loop_
          _diffrn_scan_axis.scan_id
          _diffrn_scan_axis.axis_id
          _diffrn_scan_axis.angle_start
          _diffrn_scan_axis.angle_range
          _diffrn_scan_axis.angle_increment
          _diffrn_scan_axis.displacement_start
          _diffrn_scan_axis.displacement_range
          _diffrn_scan_axis.displacement_increment
    
           1 omega 200.0 20.0 0.1 . . .
           1 kappa -40.0  0.0 0.0 . . .
           1 phi   127.5  0.0 0.0 . . .
           1 tranz  . . .   2.3 0.0 0.0
    
          _diffrn_scan_frame.scan_id                   1
          _diffrn_scan_frame.date               '2001-11-18T03:27:33'
          _diffrn_scan_frame.integration_time    3.0
          _diffrn_scan_frame.frame_id            mad_L2_018
          _diffrn_scan_frame.frame_number        18
    
          loop_
          _diffrn_scan_frame_axis.frame_id
          _diffrn_scan_frame_axis.axis_id
          _diffrn_scan_frame_axis.angle
          _diffrn_scan_frame_axis.angle_increment
          _diffrn_scan_frame_axis.displacement
          _diffrn_scan_frame_axis.displacement_increment
    
           mad_L2_018 omega 201.8  0.1 . .
           mad_L2_018 kappa -40.0  0.0 . .
           mad_L2_018 phi   127.5  0.0 . .
           mad_L2_018 tranz  .     .  2.3 0.0
    
    


    Example 2 - a more extensive example (R. M. Sweet, P. J. Ellis & H. J. Bernstein). A detector is placed 240 mm along the Z axis from the goniometer. This leads to a choice: either the axes of the detector are defined at the origin, and then a Z setting of -240 is entered, or the axes are defined with the necessary Z offset. In this case, the setting is used and the offset is left as zero. This axis is called DETECTOR_Z. The axis for positioning the detector in the Y direction depends on the detector Z axis. This axis is called DETECTOR_Y. The axis for positioning the detector in the X direction depends on the detector Y axis (and therefore on the detector Z axis). This axis is called DETECTOR_X. This detector may be rotated around the Y axis. This rotation axis depends on the three translation axes. It is called DETECTOR_PITCH. A coordinate system is defined on the face of the detector in terms of 2300 0.150 mm pixels in each direction. The ELEMENT_X axis is used to index the first array index of the data array and the ELEMENT_Y axis is used to index the second array index. Because the pixels are 0.150mm X 0.150mm, the centre of the first pixel is at (0.075, 0.075) in this coordinate system.
         ###CBF: VERSION 1.1
    
         data_image_1
    
         # category DIFFRN
         _diffrn.id P6MB
         _diffrn.crystal_id P6MB_CRYSTAL7
    
         # category DIFFRN_SOURCE
         loop_
         _diffrn_source.diffrn_id
         _diffrn_source.source
         _diffrn_source.type
          P6MB synchrotron 'SSRL beamline 9-1'
    
         # category DIFFRN_RADIATION
         loop_
         _diffrn_radiation.diffrn_id
         _diffrn_radiation.wavelength_id
         _diffrn_radiation.monochromator
         _diffrn_radiation.polarizn_source_ratio
         _diffrn_radiation.polarizn_source_norm
         _diffrn_radiation.div_x_source
         _diffrn_radiation.div_y_source
         _diffrn_radiation.div_x_y_source
          P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08
         0.01 0.00
    
         # category DIFFRN_RADIATION_WAVELENGTH
         loop_
         _diffrn_radiation_wavelength.id
         _diffrn_radiation_wavelength.wavelength
         _diffrn_radiation_wavelength.wt
          WAVELENGTH1 0.98 1.0
    
         # category DIFFRN_DETECTOR
         loop_
         _diffrn_detector.diffrn_id
         _diffrn_detector.id
         _diffrn_detector.type
         _diffrn_detector.number_of_axes
          P6MB MAR345-SN26 'MAR 345' 4
    
         # category DIFFRN_DETECTOR_AXIS
         loop_
         _diffrn_detector_axis.detector_id
         _diffrn_detector_axis.axis_id
          MAR345-SN26 DETECTOR_X
          MAR345-SN26 DETECTOR_Y
          MAR345-SN26 DETECTOR_Z
          MAR345-SN26 DETECTOR_PITCH
    
         # category DIFFRN_DETECTOR_ELEMENT
         loop_
         _diffrn_detector_element.id
         _diffrn_detector_element.detector_id
          ELEMENT1 MAR345-SN26
    
         # category DIFFRN_DATA_FRAME
         loop_
         _diffrn_data_frame.id
         _diffrn_data_frame.detector_element_id
         _diffrn_data_frame.array_id
         _diffrn_data_frame.binary_id
          FRAME1 ELEMENT1 ARRAY1 1
    
         # category DIFFRN_MEASUREMENT
         loop_
         _diffrn_measurement.diffrn_id
         _diffrn_measurement.id
         _diffrn_measurement.number_of_axes
         _diffrn_measurement.method
          P6MB GONIOMETER 3 rotation
    
         # category DIFFRN_MEASUREMENT_AXIS
         loop_
         _diffrn_measurement_axis.measurement_id
         _diffrn_measurement_axis.axis_id
          GONIOMETER GONIOMETER_PHI
          GONIOMETER GONIOMETER_KAPPA
          GONIOMETER GONIOMETER_OMEGA
    
         # category DIFFRN_SCAN
         loop_
         _diffrn_scan.id
         _diffrn_scan.frame_id_start
         _diffrn_scan.frame_id_end
         _diffrn_scan.frames
          SCAN1 FRAME1 FRAME1 1
    
         # category DIFFRN_SCAN_AXIS
         loop_
         _diffrn_scan_axis.scan_id
         _diffrn_scan_axis.axis_id
         _diffrn_scan_axis.angle_start
         _diffrn_scan_axis.angle_range
         _diffrn_scan_axis.angle_increment
         _diffrn_scan_axis.displacement_start
         _diffrn_scan_axis.displacement_range
         _diffrn_scan_axis.displacement_increment
          SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0
          SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0
          SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0
          SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0
          SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0
          SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0
          SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0
    
         # category DIFFRN_SCAN_FRAME
         loop_
         _diffrn_scan_frame.frame_id
         _diffrn_scan_frame.frame_number
         _diffrn_scan_frame.integration_time
         _diffrn_scan_frame.scan_id
         _diffrn_scan_frame.date
          FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48
    
         # category DIFFRN_SCAN_FRAME_AXIS
         loop_
         _diffrn_scan_frame_axis.frame_id
         _diffrn_scan_frame_axis.axis_id
         _diffrn_scan_frame_axis.angle
         _diffrn_scan_frame_axis.displacement
          FRAME1 GONIOMETER_OMEGA 12.0 0.0
          FRAME1 GONIOMETER_KAPPA 23.3 0.0
          FRAME1 GONIOMETER_PHI -165.8 0.0
          FRAME1 DETECTOR_Z 0.0 -240.0
          FRAME1 DETECTOR_Y 0.0 0.6
          FRAME1 DETECTOR_X 0.0 -0.5
          FRAME1 DETECTOR_PITCH 0.0 0.0
    
         # category AXIS
         loop_
         _axis.id
         _axis.type
         _axis.equipment
         _axis.depends_on
         _axis.vector[1] _axis.vector[2] _axis.vector[3]
         _axis.offset[1] _axis.offset[2] _axis.offset[3]
          GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . .
          GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279
          0 0.76604 . . .
          GONIOMETER_PHI   rotation goniometer GONIOMETER_KAPPA 1 0 0
         . . .
          SOURCE           general source . 0 0 1 . . .
          GRAVITY          general gravity . 0 -1 0 . . .
          DETECTOR_Z       translation detector . 0 0 1 0 0 0
          DETECTOR_Y       translation detector DETECTOR_Z 0 1 0 0 0 0
          DETECTOR_X       translation detector DETECTOR_Y 1 0 0 0 0 0
          DETECTOR_PITCH   rotation    detector DETECTOR_X 0 1 0 0 0 0
          ELEMENT_X        translation detector DETECTOR_PITCH
         1 0 0 172.43 -172.43 0
          ELEMENT_Y        translation detector ELEMENT_X
         0 1 0 0 0 0
    
         # category ARRAY_STRUCTURE_LIST
         loop_
         _array_structure_list.array_id
         _array_structure_list.index
         _array_structure_list.dimension
         _array_structure_list.precedence
         _array_structure_list.direction
         _array_structure_list.axis_set_id
          ARRAY1 1 2300 1 increasing ELEMENT_X
          ARRAY1 2 2300 2 increasing ELEMENT_Y
    
         # category ARRAY_STRUCTURE_LIST_AXIS
         loop_
         _array_structure_list_axis.axis_set_id
         _array_structure_list_axis.axis_id
         _array_structure_list_axis.displacement
         _array_structure_list_axis.displacement_increment
          ELEMENT_X ELEMENT_X 0.075 0.150
          ELEMENT_Y ELEMENT_Y 0.075 0.150
    
         # category ARRAY_ELEMENT_SIZE
         loop_
         _array_element_size.array_id
         _array_element_size.index
         _array_element_size.size
          ARRAY1 1 150e-6
          ARRAY1 2 150e-6
    
         # category ARRAY_INTENSITIES
         loop_
         _array_intensities.array_id
         _array_intensities.binary_id
         _array_intensities.linearity
         _array_intensities.gain
         _array_intensities.gain_esd
         _array_intensities.overload
         _array_intensities.undefined_value
          ARRAY1 1 linear 1.15 0.2 240000 0
    
          # category ARRAY_STRUCTURE
          loop_
          _array_structure.id
          _array_structure.encoding_type
          _array_structure.compression_type
          _array_structure.byte_order
          ARRAY1 "signed 32-bit integer" packed little_endian
    
         # category ARRAY_DATA
         loop_
         _array_data.array_id
         _array_data.binary_id
         _array_data.data
          ARRAY1 1
         ;
         --CIF-BINARY-FORMAT-SECTION--
         Content-Type: application/octet-stream;
             conversions="X-CBF_PACKED"
         Content-Transfer-Encoding: BASE64
         X-Binary-Size: 3801324
         X-Binary-ID: 1
         X-Binary-Element-Type: "signed 32-bit integer"
         Content-MD5: 07lZFvF+aOcW85IN7usl8A==
    
         AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg
         ...
         8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE
    
         --CIF-BINARY-FORMAT-SECTION----
         ;
    
    


    Example 3 - Example 2 revised for a spiral scan (R. M. Sweet, P. J. Ellis & H. J. Bernstein). A detector is placed 240 mm along the Z axis from the goniometer, as in Example 2 above, but in this example the image plate is scanned in a spiral pattern from the outside edge in. The axis for positioning the detector in the Y direction depends on the detector Z axis. This axis is called DETECTOR_Y. The axis for positioning the detector in the X direction depends on the detector Y axis (and therefore on the detector Z axis). This axis is called DETECTOR_X. This detector may be rotated around the Y axis. This rotation axis depends on the three translation axes. It is called DETECTOR_PITCH. A coordinate system is defined on the face of the detector in terms of a coupled rotation axis and radial scan axis to form a spiral scan. The rotation axis is called ELEMENT_ROT and the radial axis is called ELEMENT_RAD. A 150 micrometre radial pitch and a 75 micrometre 'constant velocity' angular pitch are assumed. Indexing is carried out first on the rotation axis and the radial axis is made to be dependent on it. The two axes are coupled to form an axis set ELEMENT_SPIRAL.
         ###CBF: VERSION 1.1
    
         data_image_1
    
         # category DIFFRN
         _diffrn.id P6MB
         _diffrn.crystal_id P6MB_CRYSTAL7
    
         # category DIFFRN_SOURCE
         loop_
         _diffrn_source.diffrn_id
         _diffrn_source.source
         _diffrn_source.type
          P6MB synchrotron 'SSRL beamline 9-1'
    
         # category DIFFRN_RADIATION
              loop_
         _diffrn_radiation.diffrn_id
         _diffrn_radiation.wavelength_id
         _diffrn_radiation.monochromator
         _diffrn_radiation.polarizn_source_ratio
         _diffrn_radiation.polarizn_source_norm
         _diffrn_radiation.div_x_source
         _diffrn_radiation.div_y_source
         _diffrn_radiation.div_x_y_source
          P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08
         0.01 0.00
    
         # category DIFFRN_RADIATION_WAVELENGTH
         loop_
         _diffrn_radiation_wavelength.id
         _diffrn_radiation_wavelength.wavelength
         _diffrn_radiation_wavelength.wt
          WAVELENGTH1 0.98 1.0
    
         # category DIFFRN_DETECTOR
         loop_
         _diffrn_detector.diffrn_id
         _diffrn_detector.id
         _diffrn_detector.type
         _diffrn_detector.number_of_axes
          P6MB MAR345-SN26 'MAR 345' 4
    
         # category DIFFRN_DETECTOR_AXIS
         loop_
         _diffrn_detector_axis.detector_id
         _diffrn_detector_axis.axis_id
          MAR345-SN26 DETECTOR_X
          MAR345-SN26 DETECTOR_Y
          MAR345-SN26 DETECTOR_Z
          MAR345-SN26 DETECTOR_PITCH
    
         # category DIFFRN_DETECTOR_ELEMENT
         loop_
         _diffrn_detector_element.id
         _diffrn_detector_element.detector_id
          ELEMENT1 MAR345-SN26
    
         # category DIFFRN_DATA_FRAME
         loop_
         _diffrn_data_frame.id
         _diffrn_data_frame.detector_element_id
         _diffrn_data_frame.array_id
         _diffrn_data_frame.binary_id
          FRAME1 ELEMENT1 ARRAY1 1
    
         # category DIFFRN_MEASUREMENT
         loop_
         _diffrn_measurement.diffrn_id
         _diffrn_measurement.id
         _diffrn_measurement.number_of_axes
         _diffrn_measurement.method
          P6MB GONIOMETER 3 rotation
    
         # category DIFFRN_MEASUREMENT_AXIS
         loop_
         _diffrn_measurement_axis.measurement_id
         _diffrn_measurement_axis.axis_id
          GONIOMETER GONIOMETER_PHI
          GONIOMETER GONIOMETER_KAPPA
          GONIOMETER GONIOMETER_OMEGA
    
         # category DIFFRN_SCAN
         loop_
         _diffrn_scan.id
         _diffrn_scan.frame_id_start
         _diffrn_scan.frame_id_end
         _diffrn_scan.frames
          SCAN1 FRAME1 FRAME1 1
    
         # category DIFFRN_SCAN_AXIS
         loop_
         _diffrn_scan_axis.scan_id
         _diffrn_scan_axis.axis_id
         _diffrn_scan_axis.angle_start
         _diffrn_scan_axis.angle_range
         _diffrn_scan_axis.angle_increment
         _diffrn_scan_axis.displacement_start
         _diffrn_scan_axis.displacement_range
         _diffrn_scan_axis.displacement_increment
          SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0
          SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0
          SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0
          SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0
          SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0
          SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0
          SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0
    
         # category DIFFRN_SCAN_FRAME
         loop_
         _diffrn_scan_frame.frame_id
         _diffrn_scan_frame.frame_number
         _diffrn_scan_frame.integration_time
         _diffrn_scan_frame.scan_id
         _diffrn_scan_frame.date
          FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48
    
         # category DIFFRN_SCAN_FRAME_AXIS
         loop_
         _diffrn_scan_frame_axis.frame_id
         _diffrn_scan_frame_axis.axis_id
         _diffrn_scan_frame_axis.angle
         _diffrn_scan_frame_axis.displacement
          FRAME1 GONIOMETER_OMEGA 12.0 0.0
          FRAME1 GONIOMETER_KAPPA 23.3 0.0
          FRAME1 GONIOMETER_PHI -165.8 0.0
          FRAME1 DETECTOR_Z 0.0 -240.0
          FRAME1 DETECTOR_Y 0.0 0.6
          FRAME1 DETECTOR_X 0.0 -0.5
          FRAME1 DETECTOR_PITCH 0.0 0.0
    
         # category AXIS
         loop_
         _axis.id
         _axis.type
         _axis.equipment
         _axis.depends_on
         _axis.vector[1] _axis.vector[2] _axis.vector[3]
         _axis.offset[1] _axis.offset[2] _axis.offset[3]
          GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . .
          GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279
          0 0.76604 . . .
          GONIOMETER_PHI   rotation goniometer GONIOMETER_KAPPA 1 0 0
         . . .
          SOURCE           general source . 0 0 1 . . .
          GRAVITY          general gravity . 0 -1 0 . . .
          DETECTOR_Z       translation detector . 0 0 1 0 0 0
          DETECTOR_Y       translation detector DETECTOR_Z 0 1 0 0 0 0
          DETECTOR_X       translation detector DETECTOR_Y 1 0 0 0 0 0
          DETECTOR_PITCH   rotation    detector DETECTOR_X 0 1 0 0 0 0
          ELEMENT_ROT      translation detector DETECTOR_PITCH 0 0 1 0 0 0
          ELEMENT_RAD      translation detector ELEMENT_ROT 0 1 0 0 0 0
    
         # category ARRAY_STRUCTURE_LIST
         loop_
         _array_structure_list.array_id
         _array_structure_list.index
         _array_structure_list.dimension
         _array_structure_list.precedence
         _array_structure_list.direction
         _array_structure_list.axis_set_id
          ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL
    
         # category ARRAY_STRUCTURE_LIST_AXIS
         loop_
         _array_structure_list_axis.axis_set_id
         _array_structure_list_axis.axis_id
         _array_structure_list_axis.angle
         _array_structure_list_axis.displacement
         _array_structure_list_axis.angular_pitch
         _array_structure_list_axis.radial_pitch
          ELEMENT_SPIRAL ELEMENT_ROT 0    .  0.075   .
          ELEMENT_SPIRAL ELEMENT_RAD . 172.5  .    -0.150
    
         # category ARRAY_ELEMENT_SIZE
         # the actual pixels are 0.075 by 0.150 mm
         # We give the coarser dimension here.
         loop_
         _array_element_size.array_id
         _array_element_size.index
         _array_element_size.size
          ARRAY1 1 150e-6
    
         # category ARRAY_INTENSITIES
         loop_
         _array_intensities.array_id
         _array_intensities.binary_id
         _array_intensities.linearity
         _array_intensities.gain
         _array_intensities.gain_esd
         _array_intensities.overload
         _array_intensities.undefined_value
          ARRAY1 1 linear 1.15 0.2 240000 0
    
          # category ARRAY_STRUCTURE
          loop_
          _array_structure.id
          _array_structure.encoding_type
          _array_structure.compression_type
          _array_structure.byte_order
          ARRAY1 "signed 32-bit integer" packed little_endian
    
         # category ARRAY_DATA
         loop_
         _array_data.array_id
         _array_data.binary_id
         _array_data.data
          ARRAY1 1
         ;
         --CIF-BINARY-FORMAT-SECTION--
         Content-Type: application/octet-stream;
             conversions="X-CBF_PACKED"
         Content-Transfer-Encoding: BASE64
         X-Binary-Size: 3801324
         X-Binary-ID: 1
         X-Binary-Element-Type: "signed 32-bit integer"
         Content-MD5: 07lZFvF+aOcW85IN7usl8A==
    
         AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg
         ...
         8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE
    
         --CIF-BINARY-FORMAT-SECTION----
         ;
    
    


    Category groups:
        inclusive_group
        diffrn_group
    Category key:
        _diffrn_scan.id

    Mandatory category: no

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_measurement.id.html0000644000076500007650000000712311603702115017615 0ustar yayayaya (IUCr) CIF Definition save__diffrn_measurement.id

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_measurement.id

    Name:
    '_diffrn_measurement.id'

    Definition:

            The value of _diffrn_measurement.id must uniquely identify
                   the set of mechanical characteristics of the device used to
                   orient and/or position the sample used during the collection
                   of each diffraction data set.
    
                   If the value of _diffrn_measurement.id is not given, it is
                   implicitly equal to the value of
                   _diffrn_measurement.diffrn_id.
    
                   Either _diffrn_measurement.device or
                   _diffrn_measurement.id may be used to link to other
                   categories.  If the experimental setup admits multiple
                   devices, then _diffrn_measurement.id is used to provide
                   a unique link.
    
    

    Type: code

    Mandatory item: implicit

    _diffrn_measurement_axis.measurement_id

    Category: diffrn_measurement

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/ChangeLog.html0000644000076500007650000035436411603702115015077 0ustar yayayaya CBFlib ChangeLog [IUCr Home Page] [CIF Home Page] [CBF/imgCIF]
    | IUCr Home Page | CIF Home Page | CBF/imgCIF | CBFlib |
    | NOTICE | GPL | LGPL | imgCIF dictionary |
    | Click Here to Make a Donation |

    CBFlib ChangeLog

    An API for CBF/imgCIF
    Crystallographic Binary Files with ASCII Support

    Version 0.9.2
    12 February 2011

    by
    Paul J. Ellis
    Stanford Synchrotron Radiation Laboratory

    and
    Herbert J. Bernstein
    Bernstein + Sons

    © Copyright 2006, 2007, 2008, 2011 Herbert J. Bernstein


    YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL.

    ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS OF THE LGPL.


    Before using this software, please read the
    NOTICE
    for important disclaimers and the IUCr Policy on the Use of the Crystallographic Information File (CIF) and for other important information.

    Work on imgCIF and CBFlib supported in part by the U. S. Department of Energy (DOE) under grants ER63601-1021466-0009501 and ER64212-1027708-0011962, by the U. S. National Science Foundation (NSF) under grants DBI-0610407, DBI-0315281 and EF-0312612, the U. S. National Institutes of Health (NIH) under grants 1R15GM078077 from NIGMS and 1R13RR023192 from NCRR and funding from the International Union for Crystallographyn (IUCr). The content is solely the responsibility of the authors and does not necessarily represent the official views of DOE, NSF, NIH, NIGMS, NCRR or IUCr.


    Version History

    Version DateByDescription
      0.1  Apr. 1998   PJE   This was the first CBFlib release. It supported binary CBF files using binary strings.
      0.2   Aug. 1998   HJB  This release added ascii imgCIF support using MIME-encoded binary sections, added the option of MIME headers for the binary strings was well. MIME code adapted from mpack 1.5. Added hooks needed for DDL1-style names without categories.
      0.3   Sep. 1998   PJE  This release cleaned up the changes made for version 0.2, allowing multi-threaded use of the code, and removing dependence on the mpack package.
      0.4   Nov. 1998   HJB   This release merged much of the message digest code into the general file reading and writing to reduce the number of passes. More consistency checking between the MIME header and the binary header was introduced. The size in the MIME header was adjusted to agree with the version 0.2 documentation.
      0.5   Dec. 1998   PJE  This release greatly increased the speed of processing by allowing for deferred digest evaluation.
      0.6   Jan. 1999   HJB   This release removed the redundant information (binary id, size, compression id) from a binary header when there is a MIME header, removed the unused repeat argument, and made the memory allocation for buffering and tables with many rows sensitive to the current memory allocation already used.
      0.6.1   Feb. 2001   HP (per HJB)   This release fixed a memory leak due to misallocation by size of cbf_handle instead of cbf_handle_struct
      0.7   Mar. 2001   PJE   This release added high-level instructions based on the imgCIF dictionary version 1.1.
      0.7.1   Mar. 2001   PJE   The high-level functions were revised to permit future expansion to files with multiple images.
      0.7.2   Apr. 2001   HJB   This release adjusted cbf_cimple.c to conform to cif_img.dic version 1.1.3
      0.7.2.1   May 2001   PJE   This release corrected an if nesting error in the prior mod to cbf_cimple.c.
      0.7.3   Oct. 2002   PJE   This release modified cbf_simple.c to reorder image data on read so that the indices are always increasing in memory (this behavior was undefined previously).
      0.7.4   Jan 2004   HJB   This release fixes a parse error for quoted strings, adds code to get and set character string types, and removes compiler warnings
      0.7.5   Apr 2006   HJB   This release cleans up some compiler warnings, corrects a parse error on quoted strings with a leading blank as adds the new routines for support of aliases, dictionaries and real arrays, higher level routines to get and set pixel sizes, do cell computations, and to set beam centers, improves support for conversion of images, picking up more data from headers.
      0.7.6   Jul 2006   HJB   This release reorganizes the kit into two pieces: CBFlib_0.7.6_Data_Files and CBFlib_0.7.6. An optional local copy of getopt is added. The 1.4 draft dictionary has been added. cif2cbf updated to support vcif2 validation. convert_image and cif2cbf updated to report text of error messages. convert_image updated to support tag and category aliases, default to adxv images. convert_image and img updated to support row-major images. Support added for binning. API Support added for validation, wide files and line folding. Logic changed for beam center reporting. Added new routines: cbf_validate, cbf_get_bin_sizes, cbf_set_bin_sizes, cbf_find_last_typed_child, cbf_compose_itemname, cbf_set_cbf_logfile, cbf_make_widefile, cbf_read_anyfile, cbf_read_widefile, cbf_write_local_file, cbf_write_widefile, cbf_column_number, cbf_blockitem_number, cbf_log, cbf_check_category_tags, cbf_set_beam_center
      0.7.7   February 2007   HJB   This release reflects changes for base 32K support developed by G. Darakev, and changes for support of reals, 3d arrays, byte_offset compression and J. P. Abrahams packed compression made in consultation with (in alphabetic order) E. Eikenberry, A. Hammerley, W. Kabsch, M. Kobas, J. Wright and others at PSI and ESRF in January 2007, as well accumulated changes fixing problems in release 0.7.6.
      0.7.7.1   February 2007   HJB   This release is a patch to 0.7.7 to change the treatment of the byteorder parameter from strcpy semantics to return of a pointer to a string constant. Our thanks to E. Eikenberry for pointing out the problem.
      0.7.7.2   February 2007   HJB   This release is a patch to 0.7.7.1 to add testing for JPA packed compression and to respect signs declared in the MIME header.
      0.7.7.3   April 2007   HJB   This release is a patch to 0.7.7.3 to add f90 support for reading of CBF byte-offset and packed compression, to fix problems with gcc 4.4.1 and to correct errors in multidimensional packed compression.
      0.7.7.4   May 2007   HJB   Corrects in handling SLS detector mincbfs and reorder dimensions versus arrays for some f90 compilers as per H. Powell.
      0.7.7.5   May 2007   HJB   Fix to cbf_get_image for bug reported by F. Remacle, fixes for windows builds as per J. Wright and F. Remacle.
      0.7.7.6   Jun 2007   HJB   Fix to CBF byte-offset compression writes, fix to Makefiles and m4 for f90 test programs to allow adjustable record length.
      0.7.8   Jul 2007   HJB  Release for full support of SLS data files with updated convert_minicbf, and support for gfortran from gcc 4.2.
      0.7.8.1  Jul 2007  HJB  Update to 0.7.8 release to fix memory leaks reported by N. Sauter and to update validation checks for recent changes.
      0.7.8.2  Dec 2007  CN, HJB  Update to 0.7.8.1 to add ADSC jiffie by Chris Nielsen, and to add ..._fs and ..._sf macros.
      0.7.9  Dec 2007  CN, HJBIdentical to 0.7.8.2 except for a cleanup of deprecated examples, e.g. diffrn_frame_data
      0.7.9.1  Jan 2008  CN, HJB  Update to 0.7.8.2 to add inverse ADSC jiffie by Chris Nielsen, to clean up problems in handling maps for RasMol.
      0.8.0  Jul 2008  GT, HJB  Cleanup of 0.7.9.1 to start 0.8 series.
      0.8.1   Jul 2009   EZ, CN, PC, GW, JH, HJB    Release with EZ's 2008 DDLm support using JH's PyCifRW, also cbff f95 wrapper code, PC's java bindings.
      0.9.1  Aug 2010  PC, EE, JLM, NS, EZ, HJB   Release with EE's Dectris template software, also with vcif3, new arvai_test, sequence_match.
      0.9.2   Feb 2011   PC, EE, JLM, NS, EZ, HJB   New default release with updated pycbf, tiff support, removal of default use of PyCifRW to avoid Fedora license issue.


    Release 0.9.2, Herbert J. Bernstein, 12 February 2011

    Source FileChange
    Makefile.m4, Makefiles   Changes for libtiff and tiff2cbf. Create a separate setup.py for MINGW. Allow CBF_DONT_USE_LONG_LONG variable to control Makefiles. Disable default use of PyCifRW because of Fedora concerns about PyCifRW license issues. Force use of long long for SWIG. Update Makefiles to run changtestcompression. Update pycbf build.
    cbf_template_t.c   Don't use /tmp for dectris template code. Add EE's change for DLS signs
    cbf_copy.c   Fix cbf_copy.c to handle not using long long correctly
    jcbf.i   Move cbf.i to jcbf directory.
    cbf_byte_offset.h, cbf_canonical.h, cbf_compress.h, cbf_packed.h, cbf_predictor.h, cbf_uncompressed.h, cbf.c, cbf_binary.c, cbf_byte_offset.c, cbf_canonical.c, cbf_compress.c, cbf_packed.c, cbf_predictor.c, cbf_uncompressed.c, cbff.c   Implement P. Chang's fast byte-offset decompress, but with hooks to run on machines without long long support. Fix bad mask, fix sign extension for MINGW and other systems in which long long is not used. Fix error in mpint_shift logic causing erroneous sign Add changes in the compression infrastructure by P. Chang to make the compressed size available on decompression. Extend cbf_canonical to support long long and double. Correct cbf_packed for elsize 8 data.
    cbfdetectorwrappers.i, cbfgenericwrappers.i, cbfgoniometerwrappers.i, cbfhandlewrappers.i, make_pycbf.py, pycbf.py, pycbf_test2.py, pycbf_wrap.c, cbf_simple.c   Update pycbf for 0.9 release Add cbf_get_detector_axis_slow, cbf_get_detector_axis_fast, cbf_get_detector_axes, cbf_get_detector_axes_fs, cbf_get_detector_sf, and changes for pycbf wrapper
    cbf2adscimg_sub.c   Fix buffer overflow
    cif_img_1.6.3_26Aug10.dic, cif_img_1.6.3_26Aug10.html Add variant category and tags and diffrn_scan_frame_monitor


    Release 0.9.1, P. Chang, E. Eikenberry, J. Lewis Muir, N. Sauter, E. Zlateva, Herbert J. Bernstein, 15 August 2010

    Source FileChange
    cbf_simple.c   Fix nested axis handling.
    cbf_template_t.c   Add E.E.'s Dectris template software. Change to C-style comments.
    Makefile.m4, Makefiles   Add DMALLOC hooks.
    arvai_test.c, seqmatchsub.c, seqmatchsub.h, sequence_match.c, cbf_copy.h, Makefile.m4, cbf_ascii.c, cbf_copy.c   Add arvai_test and sequence_match examples. Transfer copy logic from cib2cbf into cbf_copy.c
    cbf.h, cbf_ascii.h, cbf_file.h, cbf_write.h, cbff.h, cbf.c, cbf_ascii.c, cbf_file.c, cbf_lex.c, cbf_write.c   As per request by J. Lewis Muir, direct all warning messages through cbf_log or new cbf_flog, so such messages can all be suppressed by setting the logfile to NULL
    cbf_byte_offset.c, cbf_file.c   Fix to byte-offset compression for 16 bit data with a delta that looks like a flag. Fix to setting/getting file position when there is no stream. Fix incorrect sign extension test as per N. Sauter.
    convert_minicbf.c   Allow for changes in miniheader and report unrecognized lines but continue. Also allow S/N instead of SN
    Makefile.m4, Makefiles, Java.txt, testcbf.java, cbf.c   As per P. Chang, decouple CBF_UNDEFINED error return from CBF_UNDEFINED node type by defining CBF_UNDEFNODE (rather than PC's CBF_UNDEFINEDNODE)
    drel_prep.py, drel_yacc.py, cif2cbf.c, cbf.h, cbf.c, cbf_ascii.c, cbf_lex.c, cbf.stx.y, cbf_getopt.c, cbf_stx.c   vcif 3 release.
    cbf.h, cbf.c   Add function cbf_set_column_name


    Release 0.8.1, E. Zlateva, C. Neilsen, P. Chang, G. Winter, J. Hester, Herbert J. Bernstein, 24 July 2009

    Source FileChange
    cbf.h, cbf_stx.h, cbf_tree.h, cbf.c, cbf.stx.y, cbf_lex.c, cbf_stx.c, Makefile.m4, Makefiles   As per EZ, Add DDLm support, parsing of function definitions. Add auto download of J. Hester's PyCifRW and PLY
    cbf_getopt.c   Correct a memory leak and ensure correct handling of unspecified options when a '-' is given on the option string.
    CBFlib.html, CBFlib.txt   As per G. Winter correct documentation of byte-offset algorithm to refer to hex 80 not hex F0.
    cbf_getopt.h, cbf_getopt.c, Makefile.m4, Makefiles, cif2cbf.c, convert_image.c, convert_minicbf.c, img2cif.c   Introduce cbf_getopt.h, cbf_getopt.c, remove use of getopt
    Java.txt, testcbf.c, testcbf.java, Makefile.m4, cbf.i   P. Chang's java bindings
    libtool directory   Add a libtool build directory for future use of shared libraries.
    cif2cbf.c   Add test for construct_detector to cif2cbf. Fix getopt option string.
    cif_tree.h   Add DDLm bracket types for nodes
    adscimg2cbf.c, adscimg2cbf_sub.c   Apply mods to adscimg2cbf by C. Nielsen: Add new command line options: --beam_center_from_header, Figure out beam center from ADSC header information (default); --beam_center_mosflm, Beam center in ADSC header: MOSFLM coordinates; --beam_center_ulhc, Beam center in ADSC header: origin: upper left hand corner of image.(HKL mm); --beam_center_llhc, Beam center in ADSC header: origin: lower left hand corner of image.(adxv mm)
    cbff.h, cbff.c   Add src/cbff.c and include/cbff.h as start of full f95 wrapper for C code


    Release 0.8.0, G. Todorov, Herbert J. Bernstein, 21 July 2008

    Source FileChange
    adscimg2cbf_sub.c, adscimg2cbf_sub.c   Patch to deal with gcc 4 optimization error in get_bo Replaced with call to cbf_get_local_integer_byte_order.
    cbf.c, cbf.h, cbf_ascii.c, cbf_file.c, cbf_lex.c, cbf_write.c   Clean up spacing; trim trailing blanks in text fields; validate DDLm types. Add MSG_DIGESTWARN. Update spacing. Fix includes for regex use. Fixes on achar and anchar and element. Added cbf_check_type_contents function that will verify ddlm types based on regular expressions. Fix handling for bracketed unquoted words and handle more DDLm tags. Fix scan of DDLm bracketed constructs with embedded quotes. Pick up item names in DDLm save frames. Fix cif2cbf handling of bracketed constructs in dictionaries. Updates to bracketed construct parse and output logic. Update write logic for bracketed constructs with folding. cbf_set_tag_category() code fixed. Change internal routine cbf_read_anyfile and add new user routine cbf_read_buffered_file to support pre-read of input files and memory-only files. Add new routines cbf_io_buffersize and cbf_reset_in_bits and change read logic to allow buffered reads.


    Release 0.7.9.1, Chris Nielsen, Herbert J. Bernstein, 24 January 2008

    Source FileChange
    cbf2adscimg.c cbf2adscimg_sub.c   Last minutes fixes on release: Put missing byte swap in cbf2adscimg.c for when byte orders differ. Bypass problems with gcc optimization, and handle case then array header is there but invalid.
    .symlinks .undosymlinks   Update version to 0.7.9
    Makefile.m4 Makefile, Makefile_AIX ...   Update for CN's jiffies, and testing with MD5 signatures only
    cbf2adscimg.c cbf2adscimg_sub.c   New inverse jiffie by Chris Nielsen of ADSC to convert CBF files created by convert_image or adscimg2cbf to ADSC detector images. This version depends on the header extract planted by convert_image or adscimg2cbf.
    cbf_byte_offset.c   Fix handling of byte offset compression when the data does not compress.
    cbf_codes.c   Fix 32K encoding big-endian test as per Ladislav Michnovic .
    cbf_packed.c   Correct mishandling of 64 bit data.
    cbf_uncompressed.c   Remove redundant initialization of unsigned_char_data.
    cbf_write.c.c   Fix conflicting uses of variable column by introducing separate variable xcol.
    README.html README   Update to version 0.7.9 directory structure and programs.
    cbf.c   Fix local sensitivity of cbf_get_doublevalue and cbf_set_doublevalue so "." will be accepted and written as the decimal point in locales that use ",".


    Release 0.7.9, Chris Nielsen, Herbert J. Bernstein, 30 December 2007

    Source FileChange
    Makefiles and test data   Change test cases to avoid deprecated features.


    Release 0.7.8.2, Chris Nielsen, Herbert J. Bernstein, 25 December 2007

    Source FileChange
    adscimg2cbf.c adscimg2cbf_sub.c   New jiffie by Chris Nielsen of ADSC to convert ADSC detector images to CBF.
    cbf.h cbf_byte_offset.h, cbf_compress.h, cbf_read_mime.h, cbf_simple.h   Add _fs and _sf versions of cbf_get_arrayparameters_wdims, cbf_get_integerarrayparameters_wdims, cbf_get_realarrayparameters_wdims, cbf_set_integerarray_wdims, cbf_set_realarray_wdims, cbf_compress_byte_offset, cbf_compress, cbf_decompress, cbf_parse_mimeheader, cbf_get_pixel_size, cbf_set_pixel_size, cbf_get_image_size, cbf_get_image, cbf_get_real_image, cbf_get_3d_image_size, cbf_get_3d_image, cbf_get_real_3d_image, cbf_set_image, cbf_set_real_image, cbf_set_3d_image, cbf_set_real_3d_image, cbf_get_map_array_id, cbf_get_map_segment_size, cbf_get_map_segment, cbf_get_map_segment_mask, cbf_get_real_map_segment, cbf_get_real_map_segment_mask, cbf_set_map_segment, cbf_set_map_segment_mask, cbf_set_real_map_segment, cbf_set_real_map_segment_mask, cbf_get_3d_array_size, cbf_get_3d_array, cbf_set_3d_array, cbf_get_beam_center, cbf_set_beam_center, cbf_set_reference_beam_center, cbf_get_pixel_coordinates, cbf_get_pixel_normal, cbf_get_pixel_area, cbf_get_inferred_pixel_size
    cbf_alloc.h   Add prototype of cbf_free_text.
    cbf_binary.h   Add prototype of cbf_check_digest.
    cbf_canonical.h   Add definitions of cbf_compress_node and cbf_compress_data, and prototypes of cbf_make_compressdata, cbf_free_compressdata, cbf_initialise_compressdata, cbf_put_table, cbf_get_table, cbf_put_stopcode, cbf_insert_node, cbf_append_node, cbf_order_node, cbf_create_list, cbf_reduce_list, cbf_generate_codelengths, cbf_reverse_bitcodes, cbf_generate_canonicalcodes, cbf_compare_bitcodes, cbf_construct_tree, cbf_setup_decode, cbf_count_bits, cbf_get_code, cbf_put_code and cbf_count_values.
    cbf_simple.h   Add prototypes of cbf_get_detector_id and cbf_gregorian_julian.
    cbf_string.c, cbf_string.h   Add cbf_swab function for MS windows and other machines that do not provide swab.
    cbf.c, cbf_binary.c, cbf_byte_offset.c, cbf_canonical.c, cbf_compress.c, cbf_lex.c, cbf_packed.c, cbf_predictor.c, cbf_read_mime.c, cbf_simple.c, cbf_uncompressed.c, cbf_write_binary.c   Change dim1, dim2, dim3 to dimfast, dimmid, dimslow, ndim1, ndim2 to ndimslow, ndimfast. machines that do not provide swab.
    cif2c.c   Make declaration of xciftmp conditional to avoid compiler warnings.
    convert_image.c   Add code to check variations on pixel_size functions.
    convert_minicbf.c   Add second quick exit option (-Q). Improve error reporting. Update for most recent SLS miniheader.
    getopt.c   Fix some compiler warnings.
    Makefile.m4   add adscimg2cbf support
    template_pilatus6m_2463x2527.cbf   Update pilatus6m template for correct detector axis definitions, better comments and to list all categories used by SLS.
    template_adscquantum315_3072x3072_rev.cbf   New, corrected ADSC Quantum 315 template.


    Release 0.7.8.1, Chris Nielsen, Herbert J. Bernstein, 28 July 2007

    Source FileChange
    cbf.c   Rework cbf_free_handle to ensure release of memory from root, not current position. Rework cbf_read_anyfile to ensure close of file stream on all exit cases. Fix save frame code in cbf_validate to restart counts on each save frame. Add name, idname and aliasname types from latest DDL2 dictionary.
    cbf_alloc.c, cbf_alloc.h   Add cbf_free_text to avoid type punning warnings from gcc 4. Add memory debug based on adding -DCBFLIB_MEM_DEBUG to CFLAGS.
    cbf_simple.c   Add code to ensure against memory leaks when working with a detector or positioner object.
    cbf.stx.y, cbf_stx.c   Add calls to cbf_undo_links and cbf_free_text to clean up memory leaks in parser. Add validation calls to mark end of save frames.
    cbf_tree.c, cbf_tree.h   Add cbf_undo_links to recover memory from links used to rotate among columns of a table. Rework cbf_free_node to avoid memory leaks.
    cbf_uncompressed.c   Add #define __USE_XOPEN to avoid a warning on use of swab on some systems.
    sauter_test.C Makefile.m4   Add sauter_test to stress test for memory leaks. On make install, place cbf.h and cbf_simple.h into include directory.


    Release 0.7.8, Herbert J. Bernstein, 8 July 2007

    Source FileChange
    cbf_simple.c   Update handling of both beam center and reference beam center to allow for units and new dictionary.
    convert_minicbf.c   Add code to handle data in _array_data.header-contents. Clean up error handling, map all SLS tags. Add -Q option to convert old SLS comment format to new text field format.
    Makefile, Makefile_AIX, Makefile_LINUX, Makefile_OSX   As per ND add Makefile_LINUX_gcc42 and Makefile_OSX_gcc42 to handle gfortran 4.2 problems.


    Release 0.7.7.6, Herbert J. Bernstein, 30 June 2007

    Source FileChange
    cbf_codes.c   Fix memory leaks in base32k encoding by G. Darakev.
    cbf_byte_offset.c   Fix in handling 32 bit offsets in the fast write code, which were incorrectly handled as 16 bit offsets.
    Makefile, Makefile_AIX, Makefile_LINUX, Makefile_OSX   Add M4FLAGS variable to control m4 expansion of f90 test programs with different record lengths. For g95, the record length must not be larger than the padding.


    Release 0.7.7.5, Herbert J. Bernstein, 9 May 2007

    Source FileChange
    cbf_codes.c   Change from use of bzero to memset and remove include of strings.h
    cbf_codes.c   Change from use of bzero to memset and remove include of strings.h
    cbf_simple.c   Fix ordering of dimensions in cbf_get_3d_array_size and handling of non-zero binary ids to fix problems with cbf_get_image and cbf_get_image_size
    cbf_uncompressed.c   Add include of unistd.h for use of swab on more systems
    Makefile   Introduce $(TIME) variable for time command so it can be suppressed in windows
    fcb_read_bits.m4   Changes for g95 compatibility.
    cif2c.c, cif2cbf.c, etc.   Make use of mkstemp conditional on NOMKSTEMP. Make use of /tmp conditional on NOTMPDIR.


    Release 0.7.7.4, Herbert J. Bernstein, 6 May 2007

    Source FileChange
    cbf_simple.c   Fix ordering of dimensions in cbf_set_3d_array.
    cbf_uncompressed.c   Add include of ctype.h to provide prototype for toupper.
    convert_image.c   Enable -p option for non-standard templates; correct handling of seconds in timestamps.
    convert_minicbf.c   Enable code for timestamp, exposure time, comment-style header.
    fcb_packed.m4   As per H. Powell, move declarations for dimensions before declarations of arrays.
    fcb_read_image.m4   As per H. Powell, move declarations for dimensions before declarations of arrays.
    fcblib_defines.m4   As per H. Powell, move declarations for dimensions before declarations of arrays.


    Release 0.7.7.3, Herbert J. Bernstein, 3 April 2007

    Source FileChange
    Makefile   Add m4 directory to build f90 sources. Add .f90 routines to src and examples. Add libfcb.a to lib. Add tests for f90 routines to extra tests.
    testflat.c   Add support for 3D test.
    testflatpacked.c   Add support for 3D test.
    cbf_binary.c   Correct dim2,dim2 to be dim1,dim2 in check_digest.
    cbf_packed.c   Correct JPA pointer logic for 3D case. Work around compiler problems with handling of sign bits
    fcb_exit_binary.m4   New m4 macro file to build fcb_exit_binary.f90 a routine to skip from the end of a binary to the end of the text field.
    fcb_next_binary.m4   New m4 macro file to build fcb_next_binary.f90 a routine to skip to the start of the next binary.
    fcb_open_cifin.m4   New m4 macro file to build fcb_open_cifin.f90 a routine to open a cbf file.
    fcb_packed.m4   New m4 macro file to build fcb_packed.f90 a routine to uncompress JPA packed binaries.
    fcb_read_bits.m4   New m4 macro file to build fcb_read_bits.f90 a routine to read an arbitrary number of bits as an integer.
    fcb_read_image.m4   New m4 macro file to build fcb_read_image.f90 a set of routines to read a byte offset or packed image
    fcb_read_xds_i2.m4   New m4 macro file to build fcb_read_xds_i2.f90 a routine to read a single xds I2 image.
    fcblib_define.m4   New m4 macro file of common definitions for all f90 code
    test_fcb_read_image.m4   New m4 macro file of build test_fcb_read_image.f90 a test program for the f90 routines.
    test_xds_binary.m4   New m4 macro file of build test_xds_binary.f90 a test program for the f90 routines.
    fcb_atol_wcnt.f90   f90 code to convert a string to an integer.
    fcb_ci_strncmparr.f90   f90 code to do a case-insensitive string comparison
    fcb_nblen.f90   f90 code to do test the non-blank length of a string
    fcb_read_byte.f90   f90 code to read a byte
    fcb_read_line.f90   f90 code to read a line
    fcb_skip_whitespace.f90   f90 code to skip MIME whitespace


    Release 0.7.7.2, Herbert J. Bernstein, 27 February 2007

    Source FileChange
    Makefile   Add testflatpacked build to extra test dependencies.
    testflat.c   Add more test cases.
    testflatpacked.c   Add version of testflat for packed compression.
    cbf_binary.c   Add recovery of sign from mime header.
    cbf_byte_offset.c   Change limit logic to simple mask and remove overflow report.
    cbf_packed.c   Change limit logic to simple mask and remove overflow report.
    cbf_uncompressed.c   Change limit logic to simple mask and remove overflow report.


    Release 0.7.7.1, Herbert J. Bernstein, 25 February 2007

    Source FileChange
    Makefile   Add testflat build to extra test dependencies.
    CBFlib.html   Add descriptions of cbf_get_integerarrayparameters_wdims, cbf_get_realarrayparameters_wdims, cbf_set_integerarray_wdims, cbf_set_realarray_wdims
    cif2cbf.c   Change to use of byteorder as a pointer to a constant string, rather than as a local copy of a string.
    testflat.c   Add report of byteorder, dim1, dim2, dim2, padding.
    cbf.h,
    cbf_binary.h,
    cbf_byte_offset.h,
    cbf_canonical.h,
    cbf_compress.h,
    cbf_packed.h,
    cbf_predictor.h,
    cbf_read_mime.h,
    cbf_uncompressed.h
      Change prototypes for all functions that return byteorder from char * byteorder to const char ** byteorder. Change prototypes of all functions that set byteorder from char * byteorder to const char * byteorder
    cbf.c,
    cbf_binary.c,
    cbf_byte_offset.c,
    cbf_canonical.c,
    cbf_compress.c,
    cbf_lex.c,
    cbf_packed.c,
    cbf_predictor.c,
    cbf_read_mime.c,
    cbf_uncompressed.c,
    cbf_write_binary.c
      Change signatures for all functions that return byteorder from char * byteorder to const char ** byteorder. Change prototypes of all functions that set byteorder from char * byteorder to const char * byteorder, and make the matching changes in all calls.


    Release 0.7.7, Herbert J. Bernstein, 19 February 2007

    Source FileChange
    cif2cbf.c   Add support for byte offset, packed version 2 and flat compression, and binary section padding. Add support for base-32K encoding. Allow command line compression to override compression_type in the file and to set compression_type_flag.
    convert_image.c   Add support for new -R and -F flags, for use of reference beam center and flat packed compression respectively.
    cbf.h   Add constants CBF_PACKED_V2 for packed version 2 compression, CBF_UNCORRELATED_SECTIONS for uncorrelated sections in packed compression, CBF_FLAT_IMAGE for original CBFlib packed compression, PAD_1K, PAD_2K and PAD_4K for trailing pad on binary sections, ENC_BASE32K for base 32K encoding. Fix bad code in DEBUG mode for failnez macros. Add prototypes for cbf_get_arrayparameters_wdims, cbf_get_integerarrayparameters_wdims, cbf_get_realarrayparameters_wdims, cbf_set_integerarray_wdims, cbf_set_realarray_wdims, cbf_mpint_load_acc, cbf_mpint_store_acc, cbf_mpint_clear_acc, cbf_mpint_increment_acc, cbf_mpint_decrement_acc, cbf_mpint_negate_acc, cbf_mpint_add_acc, cbf_mpint_rightshift_acc, cbf_mpint_leftshift_acc.
    cbf_binary.h   Update prototypes for cbf_get_bintext, cbf_set_bintext, cbf_set_binary, cbf_binary_parameters, cbf_get_binary to carry byteorder, dimensions and padding.
    cbf_byte_offset.h   Update prototypes for cbf_compress_byte_offset, cbf_decompress_byte_offset to carry byteorder, dimensions and padding.
    cbf_canonical.h   Update prototypes for cbf_compress_canonical, cbf_decompress_canonical to carry byteorder, dimensions and padding.
    cbf_codes.h   Add prototypes for base 32K encoding: cbf_tobase32k, cbf_encode32k_bit_op, cbf_isBigEndian, cbf_endianFix, cbf_frombase32k, cbf_decode32k_bit_op.
    cbf_compress.h    Update prototypes for cbf_compress, cbf_decompress to carry byteorder, dimensions and padding.
    cbf_packed.h   Update prototypes for cbf_compress_packed, cbf_decompress_packed to carry byteorder, dimensions and padding.
    cbf_predictor.h   Update prototypes for cbf_compress_predictor, cbf_decompress_predictor to carry byteorder, dimensions and padding.
    cbf_read_mime.h   Update prototype for cbf_parse_mimeheader to carry byteorder, dimensions and padding.
    cbf_simple.h   Add prototypes for cbf_get_3d_array_size, cbf_get_3d_array, cbf_get_3d_image_size, cbf_get_3d_image, cbf_get_map_array_id, cbf_get_map_segment_mask, cbf_get_map_segment_size, cbf_get_map_segment, cbf_get_real_3d_image, cbf_get_real_map_segment, cbf_get_real_map_segment_mask, cbf_set_3d_array, cbf_set_3d_image, cbf_set_map_segment, cbf_set_map_segment_mask, cbf_set_real_3d_image, cbf_set_real_map_segment, cbf_set_real_map_segment_mask.
    cbf_uncompressed.h   Update prototypes for cbf_compress_none, cbf_decompress_none to carry byteorder, dimensions and padding.
    Makefile   Update version and tests to work against data files in CBFlib_0.7.7_Data_Files.
    cbf.c    Remove compiler warnings on signedness and type punned pointers. Fix bug in detection of local real format. Add base32K support. Fix inverted test in value range checking. Add new routines cbf_get_arrayparameters_wdims, cbf_get_integerarrayparameters_wdims, cbf_get_realarrayparameters_wdims, cbf_set_integerarray_wdims, cbf_set_realarray_wdims, cbf_mpint_load_acc, cbf_mpint_store_acc, cbf_mpint_clear_acc, cbf_mpint_increment_acc, cbf_mpint_decrement_acc, cbf_mpint_negate_acc, cbf_mpint_add_acc, cbf_mpint_rightshift_acc, cbf_mpint_leftshift_acc.
    cbf.stx.y   Temporarily change to use of YYSTYPE argument type to remove an error when compiling under on MS Windows. A better solution is needed./
    cbf_binary.c   Update cbf_get_bintext, cbf_set_bintext, cbf_set_binary, cbf_binary_parameters, cbf_get_binary to carry byteorder, dimensions and padding.
    cbf_byte_offset.c   Implement byte_offset compression and decompression as designed by A. Hammersley and modified by W. Kabsch.
    cbf_canonical.c   Fix warnings from gcc 4 on punned pointers. Update cbf_compress_canonical, cbf_decompress_canonical to carry byteorder, dimensions and padding.
    cbf_codes.c   Add support forr base 32K encoding: cbf_tobase32k, cbf_encode32k_bit_op, cbf_isBigEndian, cbf_endianFix, cbf_frombase32k, cbf_decode32k_bit_op.
    cbf_compress.c    Update cbf_compress, cbf_decompress carry byteorder, dimensions and padding.
    cbf_file.c   Fix warnings from gcc 4 on punned pointers.
    cbf_lex.c   Add support for byteorder, dimensions and padding and base 32K encoding.
    cbf_packed.c   Update cbf_compress_packed, cbf_decompress_packed to carry byteorder, dimensions and padding. Add support for J. P. Abrahams packed compression, versions 1 and 2, while preserving support for original CBFlib flat packed compression. Add support for 64 bit elements.
    cbf_predictor.c   Update cbf_compress_predictor, cbf_decompress_predictor to carry byteorder, dimensions and padding.
    cbf_simple.c   Change logic of most image handling routines to work as special cases of 3d routines. Add new routines cbf_get_detector_id, cbf_get_real_map_segment, cbf_get_real_map_segment_mask, cbf_set_map_segment, cbf_set_map_segment_mask, cbf_set_real_map_segment, cbf_set_real_map_segment_mask, cbf_get_3d_array_size, cbf_get_3d_array, cbf_set_3d_array, cbf_get_axis_reference_setting, cbf_set_axis_reference_setting, cbf_construct_reference_detector, cbf_require_reference_detector, cbf_set_reference_beam_center.
    cbf_read_mime.c   Update cbf_parse_mimeheader to read MIME headers for new compression types and flags and byteorder, dimensions and padding. Add support for base 32K encoding.
    cbf_tree.c   Fix warnings from gcc 4 on punned pointers.
    cbf_uncompressed.c   Fix handling of 64-bit reads and writes.
    cbf_write_binary.c   Add code to write out base-32K encoded sections, to write byte order, dimensions and padding. Add code to write out MIME headers for packed compressions or packed version 2 compression with flags for uncorrelated sections and for flat packed images.


    Release 0.7.6, Herbert J. Bernstein, 15 July 2006

    Source FileChange
    cbf.h   Add include of stdio.h; change CBF_LINELENGTH into CBF_LINELENGTH_10 and CBF_LINELENGTH_11; add new symbols CBF_CASE_INSENSITIVE, CBF_CASE_SENSITIVE, CBF_LOGERROR, CBF_LOGWARNING, CBF_LOGWOLINE, CBF_LOGWOCOLUMN, CBF_LOGSTARTLOC, CBF_LOGCURRENTLOC; add information on input file and log file to cbf handle struct; and prototypes for cbf_read_widefile, cbf_write_local_file, cbf_write_widefile, cbf_column_number, cbf_blockitem_number, cbf_warning, cbf_error, cbf_log, cbf_increment_column, cbf_reset_column, cbf_reset_refcounts, cbf_validate; added valuerow argument to cbf_set_hashedvalue and caseinsensitive to cbf_find_hashedvalue.
    cbf.c   In cbf_make_handle, added include of cbf_ascii.h, initialized handle->logfile, handle->warnings, handle->errors, handle->startline, handle->startcolumn; added new routine cbf_set_logfile; in cbf_free_handle removed gcc4 warning; broke up cbf_read_file into cbf_read_anyfile, cbf_read_file, added two more entries to parse array, one for the cbf handle and one to carry an auxillary node, such as a parent category; in cbf_write_file, reset reference counts; added new routine cbf_write_local_file to allow writing of a local portion of a cbf instead of the whole thing; added new routines cbf_column_number and cbf_blockitem_number; added new routine cbf_log to report parse errors with line numbers; fixed cbf_require_category when dealing with null datablocks; fixed cbf_require_column to preserve current row number; fixed inverted logic in cbf_require_dictionary; rewrote cbf_set_hashed_value to deal with insertions correctly; revised cbf_find_hashedvalue to survive commong errors; revised cbf_convert_dictionary_definition to recover category information properly and top deal with more complex loop-singleton interactions; added new routines cbf_increment_column, cbf_reset_column, cbf_reset_refcounts; updated cbf_convert_dictionary to align database with changes in cbf_convert_dictionary_definition and to distribute unspecified items from parents to children; fixed cbf_find_local_tag for DDL1 names and categories; updated cbf_find_category_root and cbf_require_category_root to allow for DDL1 categories drawn from dictionaries; changed cbf_find_tag_root and cbf_set_tag_root to use cbf_find_hashedvalue and cbf_set_hashedvalue; added routines cbf_check_category_tags, cbf_validate.
    cbf.stx.y   To facilitate validation, changed save frame logic to append partial save frame to the base cif from the beginning instead of waiting for the end of the save frame; added cbf_validate calls at all levels and provided detailed parse form common errors with reports via cbf_log
    cbf_ascii.h   Add prototype for cbf_foldtextline.
    cbf_ascii.c   Added new routine cbf_foldtextline; in cbf_write_ascii changed logic to no longer backslash-quote individual embedded semicolons in text fields and to use full line-folding spec;
    cbf_canonical.c   fixed gcc4 warning.
    cbf_cantext.c   fixed gcc4 warnings.
    cbf_file.h   Add columnlimit to strcut; add prototype for cbf_make_widefile.
    cbf_file.c   In cbf_make_file added intialization of line length; added new routine cbf_make_widefile; in cbf_read_character do not increment column number at EOF; in cbf_read_line report lines over the limit
    cbf_lex.c   Added lexical validation for line length, illegal characters, long data block names, long save frame names, failure to provide whitespace after loop_, unterminated quoted strings.
    cbf_packed.c   Fix gcc4 warnings
    cbf_read_mime.c   Pick up corrections to parse of types from work by GD for X-BASE32K.
    cbf_simple.h   Add prototypes for cbf_get_bin_sizes, cbf_set_bin_sizes
    cbf_simple.c   Changed cbf_read_template to use cbf_read_widefile; added new routines cbf_get_bin_sizes and cbf_set_bin_sizes; changed cbf_set_gain, cbf_set_overload, cbf_set_integration_time, cbf_set_datestamp, cbf_set_axis_setting to force in intervening categories and columns; in cbf_free_positioner, cbf_free_detector, fixed gcc4 warnings; revised cbf_set_beam_center to adjust the displacement rather than the offset.
    cbf_tree.h   Add symbol for CBF_VALUE as a node type to use for validation; add prototype for cbf_find_last_typed_child.
    cbf_tree.c   In cbf_free_node fixed gcc4 warning; added new routine cbf_find_last_typed_child; changed cbf_make_child to use cbf_find_last_typed_child instead of cbf_fid_last_child to avoid confusion between categories and save frames when the same name is used for both; changed cbf_compute_hashcode to return values between 0 and 255.
    cbf_write.d   Add prototype for cbf_compose_itemname.
    cbf_write.c   In cbf_set_value fold text fields that contain the text field terminator; add new routine cbf_compose_itemname, int cbf_write_itemname catch names that are too long;
    cif2cbf.c   Add "-v dictionary" command line argument and suppress output to /dev/null and "-w" to process a wide file; add hooks (based on symbol GNUGETOPT) to use a local copy of getopt; add text for error exits; add code to load layered dictionaries.
    convert_image.c   Add text for error exits; add logic for binning; alias support with command line arguments "-c category_alias=category_root" and "-t tag_alias=tag_root", change from _diffrn_detector.sample_detector_distance to _diffrn_measurement.sample_detector_distance; change to support row-major images to agree with adxv; remove most advisory messages to stdout.
    img.h   Added rowmajor to struct; redefined img_pixel to be conditional on rowmajor; added img_pixelptr to get the pointers to the image.
    img.c   Added recognition of ADSC QUANTUM315; added row major support
    img2cif.c   Changed to use to new img.h macros
    makecbf.c   Changed to use to new img.h macros


    Release 0.7.5, Herbert J. Bernstein, 15 April 2006

    Source FileChange
    cbf.c   Revised header for open source licenses; added support for aliases, dictionaries and real arrays; added convenience routines to do searches with default creation of what is being searched for; added reference count and dictionary link for cbf handles; added cbf_new_saveframe, cbf_force_new_saveframe, cbf_set_saveframename, cbf_reset_saveframe, cbf_remove_saveframe, cbf_rewind_saveframe, cbf_rewind_blockitem, cbf_next_saveframe, cbf_next_blockitem, cbf_select_saveframe, cbf_select_blockitem, cbf_find_saveframe, cbf_require_row, cbf_require_nextrow, cbf_count_saveframes, cbf_count_blockitems, cbf_saveframe_name, cbf_require_value, cbf_require_integervalue, cbf_require_doublevalue, cbf_get_realarrayparameters, cbf_get_realarray, cbf_set_realarray, cbf_require_datablock, cbf_require_category, cbf_require_column, cbf_require_column_value, cbf_require_column_integervalue, cbf_require_column_doublevalue, cbf_get_local_integer_byte_order, cbf_get_local_real_byte_order, cbf_get_local_real_format, cbf_get_dictionary, cbf_set_dictionary, cbf_require_dictionary, cbf_set_hashedvalue, cbf_find_hashedvalue, cbf_convert_dictionary_definition, cbf_convert_dictionary, cbf_find_tag, cbf_find_local_tag, cbf_srch_tag, cbf_find_category_root, cbf_require_category_root, cbf_set_category_root, cbf_find_tag_root, cbf_require_tag_root, cbf_set_tag_root, cbf_find_tag_category, cbf_set_tag_category.
    cbf.h   Revised header for open source licenses; added definitions of CBF_API_VERSION and CBF_DIC_VERSION; changed the debug versions of cbf_failnez and cbf_onfailnez to stringfy the argument; added dictionary and reference count to cbf_handle definition; added prototypes for cbf_new_saveframe, cbf_force_new_saveframe, cbf_set_saveframename, cbf_remove_saveframe, cbf_rewind_saveframe, cbf_rewind_blockitem, cbf_next_saveframe, cbf_next_blockitem, cbf_saveframe_name, cbf_select_saveframe, cbf_select_blockitem, cbf_find_saveframe, cbf_require_row, cbf_require_nextrow, cbf_count_saveframes, cbf_count_blockitems, cbf_require_value, cbf_require_integervalue, cbf_require_doublevalue, cbf_get_realarrayparameters, cbf_get_realarray, cbf_set_realarray, cbf_require_datablock, cbf_require_category, cbf_require_column, cbf_require_column_value, cbf_require_column_integervalue, cbf_require_column_doublevalue, cbf_get_local_integer_byte_order, cbf_get_local_real_byte_order, cbf_get_local_real_format, cbf_get_dictionary, cbf_set_dictionary, cbf_require_dictionary, cbf_set_hashedvalue, cbf_find_hashedvalue, cbf_convert_dictionary_definition, cbf_convert_dictionary, cbf_find_tag, cbf_find_local_tag, cbf_srch_tag, cbf_find_category_root, cbf_require_category_root, cbf_set_category_root, cbf_find_tag_root, cbf_require_tag_root, cbf_set_tag_root, cbf_find_tag_category, cbf_set_tag_category,
    cbf_alloc.c   Revised header for open source licenses.
    cbf_alloc.h   Revised header for open source licenses.
    cbf_ascii.c   Revised header for open source licenses.
    cbf_ascii.h   Revised header for open source licenses.
    cbf_binary.c   Revised header for open source licenses; added support of real arrays.
    cbf_binary.h   Revised header for open source licenses; added support of real arrays.
    cbf_byte_offset.c   Revised header for open source licenses; changed signature for support of real arrays; no actual changes to the code.
    cbf_byte_offset.h   Revised header for open source licenses; changed signature for support of real arrays; no actual changes to the code.
    cbf_canonical.c   Revised header for open source licenses; changed signatures for support of real arrays; no actual changes to the code.
    cbf_canonical.h   Revised header for open source licenses; changed signatures for support of real arrays; no actual changes to the code.
    cbf_codes.c   Revised header for open source licenses.
    cbf_codes.h   Revised header for open source licenses.
    cbf_compress.c   Revised header for open source licenses; added support of real arrays.
    cbf_compress.h   Revised header for open source licenses; added support of real arrays.
    cbf_context.c   Revised header for open source licenses.
    cbf_context.h   Revised header for open source licenses.
    cbf_file.c   Revised header for open source licenses; added support of real arrays, making extensive changes to the handling of integers to get past 32 bit limits.
    cbf_file.h   Revised header for open source licenses..
    cbf_lex.c   Revised header for open source licenses; added save frame support; required whitespace before a comment; changed WORD to CBFWORD; corrected quoted string parse to allow for a blank immediately after the opening quote mark.
    cbf_lex.h   Revised header for open source licenses.
    cbf_packed.c   Revised header for open source licenses; changed signatures for support of real arrays; no actual changes to the code.
    cbf_packed.h   Revised header for open source licenses; changed signatures for support of real arrays; no actual changes to the code.
    cbf_predictor.c   Revised header for open source licenses; changed signatures for support of real arrays; no actual changes to the code.
    cbf_predictor.h   Revised header for open source licenses; changed signatures for support of real arrays; no actual changes to the code.
    cbf_read_binary.c   Revised header for open source licenses.
    cbf_read_binary.h   Revised header for open source licenses.
    cbf_read_mime.c   Revised header for open source licenses; added support for real arrays.
    cbf_read_mime.h   Revised header for open source licenses; added support for real arrays.
    cbf_simple.c   Revised header for open source licenses; increased precision of all numbers to 15 digits; added support for cells and orientation matrices; built in support for diffrn_frame_data as an alternative to diffrn_data_frame; added new routines cbf_require_diffrn_id, cbf_get_pixel_size, cbf_set_pixel_size, cbf_get_real_image, cbf_set_real_image, int cbf_require_detector, cbf_set_beam_center, cbf_get_inferred_pixel_size, cbf_get_unit_cell, cbf_set_unit_cell, cbf_get_reciprocal_cell, cbf_set_reciprocal_cell, cbf_compute_cell_volume, cbf_compute_reciprocal_cell, cbf_get_orientation_matrix, cbf_set_orientation_matrix; added braces to deal with compiler warnings on dangling else.
    cbf_simple.h   Revised header for open source licenses; added prototypes for cbf_require_diffrn_id, cbf_get_array_id, cbf_get_pixel_size, cbf_set_pixel_size, cbf_get_real_image, cbf_set_real_image, cbf_require_detector, cbf_set_beam_center, cbf_get_inferred_pixel_size, cbf_get_unit_cell, cbf_set_unit_cell, cbf_get_reciprocal_cell, cbf_set_reciprocal_cell, cbf_compute_cell_volume, cbf_compute_reciprocal_cell, cbf_get_orientation_matrix, cbf_set_orientation_matrix.
    cbf_string.c   Revised header for open source licenses.
    cbf_string.h   Revised header for open source licenses.
    cbf_stx.c   Rebuilt from new cbf.stx.y.
    cbf_stx.h   Changed WORD to CBFWORD; added SAVE and SAVEEND.
    cbf.stx.y   Revised header for open source licenses; Revised grammar to support save frames and to be more comprehensible; changed name from cbf.stx
    cbf_tree.c   Revised header for open source licenses; added code to support save frames, allowing typed searches for children; added new routines cbf_find_typed_child, cbf_count_typed_children, cbf_compute_hashcode.
    cbf_tree.c   Revised header for open source licenses; added definition of CBF_SAVEFRAME as node type; added prototypes for cbf_find_typed_child, cbf_count_typed_children, cbf_compute_hashcode.
    cbf.uncompressed.c   Revised header for open source licenses; Added support for real arrays, and to remove 32 bit limits.
    cbf.uncompressed.h   Revised header for open source licenses; Added support for real arrays.
    cbf.write.c   Revised header for open source licenses; added support for save frames and aliases; changed logic for single row categories to present item-by-item, instead of as a loop except for vectors and matrices, present matrices row by row; carried cbf handle through nest of calls.
    cbf.write.h   Revised header for open source licenses; adjusted prototype of cbf_write_node to carry the cbf handle as the first argument.
    cbf.write_binary.c   Revised header for open source licenses; added support for real arrays.
    cbf.write_binary.h   Revised header for open source licenses.
    Makefile   Revised header for open source licenses; defined C++; added symbol RANLIB for use on systems that require a ranlib pass after creating a library with ar; added build and tests of testcell and cif2c; added ADSC test case to tests of convert_image; updated list of contents of tar;changed cbf.stx to cbf.stx.y.
    connvert_image.c   Revised header for open source licenses; added command line arguments for detector name, detector distance, rotation and reflection of the image; added usage report on errors; added code for axis transforms; added code to report image header fields; cleaned up PHI reporting; recovered pixel size and beam center from header; commented out most debug code.
    cif2cbf.c   Revised header for open source licenses; renamed BUFSIZ as C2CBUFSIZ to remove a compiler warning; process save frames.
    img2cif.c   Revised header for open source licenses; renamed BUFSIZ as I2CBUFSIZ to remove a compiler warning.
    testcell.C   New program to test cell functions.
    cif2c.c   New program to test cell functions.


    Release 0.7.4, Herbert J. Bernstein, 12 January 2004

    Source FileChange
    cbf.c   added cbf_set_typeofvalue, cbf_get_typeofvalue; added braces for nested if-else to remove a compiler warning.
    cbf_ascii.c   added braces to remove a compiler warnings.
    cbf_binary.c   added braces to remove a compiler warnings.
    cbf_canonical.c   added braces to remove a compiler warnings.
    cbf_compress.c   added braces to remove a compiler warnings.
    cbf_file.c   simplied dynamic array logic and went to straight doubling; added braces to remove a compiler warnings.
    cbf_lex.c   changed parse of quoted strings to allow for embedded quote marks; removed unused variables; fixed mismatch of formats; added braces to remove a compiler warnings.
    cbf_packed.c   added braces to remove a compiler warnings; intialized variables.
    cbf_simple.c   typed default typed variable; removed unused variables; added braces to remove a compiler warnings; intialized variables.
    cbf_uncompressed.c   added braces to remove a compiler warnings.
    cbf_write.c   added internal functions cbf_get_value_type and cbf_set_value_type for typeofvalue functions; updated magic number and set magic number to match dictionary, not CBFlib version; initialized variable.
    cbf.h   added new external typeofvalue function prototypes; added notices.
    cbf_write.h   added new value_type function prototypes.
    cif2cbf.c   added code to transfer typeofvalue from input to output to fix handling of nulls; increased buffer to 8192 and called it BUFSIZ; changed from tmpnam to mkstemp to remove warning; unlinked temporary file; added braces to remove compiler warnings.
    img2cif.c   added code to transfer typeofvalue from input to output to fix handling of nulls; increased buffer to 8192 and called it BUFSIZ; changed from tmpnam to mkstemp to remove warning; unlinked temporary file; removed unused variables.


    Release 0.7.3, Paul J. Ellis, 2 October 2002

    Source FileChange
    cbf_simple.c   modified cbf_get_image to reorder the image data on read so that the indices are always increasing in memory (this behavior was undefined previously).

    Note: Early versions of Release 0.7.3 carried the version number 0.7.2.3. Other than the change in number on 7 Nov 2002, there is no difference between these versions.


    Release 0.7.2.1, Paul J. Ellis, 7 May 2001

    Source FileChange
    cbf_simple.c   corrected nesting in if statements introduced for the prior mod.


    Release 0.7.2, Herbert J. Bernstein, 22 April 2001

    Source FileChange
    cbf_simple.c   changed _diffrn_measurement_axis.id (now deprecated) to _diffrn_measurement_axis.measurement_id and _diffrn_detector_axis.id (now deprecated) to _diffrn_detector_axis.detector_id, but allowed old forms as aliases.


    Release 0.7.1, Paul J. Ellis, 30 March 2001

    Source FileChange
    cbf_simple.c   add reserved argument to various routines; in cbf_update_pixel use index2 instead of index1; add new routine cbf_get_pixel_normal; in cbf_get_pixel_area, shift by (-0.5,-0.5)


    Release 0.7.1, Paul J. Ellis, 13 March 2001

    Source FileChange
    cbf.c   remove unused declaration of little.
    cbf.h   add definitions of CBF_UNDEFINED and CBF_NOTIMPLEMENTED.
    cbf_binary.c   cast type argument to (char) in cbf_copy-string call.
    cbf_compress.c   remove unused declaration of compression_file.
    cbf_simple.c   add this new routine for higher level calls.
    cbf_simple.h   add this new header for higher level calls.
    cbf_uncompressed.c   remove unused declaration of bit.


    Release 0.6.1, H. Powell (per Herbert J. Bernstein), 23 February 2001

    Source FileChange
    cbf.c   fix memory leak as corrected by H. Powell


    Release 0.6, Herbert J. Bernstein, 13 January 1999

    Source FileChange
    cbf.c   remove argument repeat from cbf_set_integerarray
    cbf.h   remove argument repeat from cbf_set_integerarray
    cbf_binary.h   carry compression id in text as argument to cbf_get/set_bintext, remove repeat as argument to cbf_set_binary
    cbf_binary.c   carry compression id in text, rather than header, as an argument to cbf_get/set_bintext, remove repeat as argument to cbf_set_binary
    cbf_byte_offset.h   remove argument repeat from cbf_compress_byte_offset
    cbf_byte_offset.c   remove argument repeat from cbf_compress_byte_offset
    cbf_canonical.   remove argument repeat from cbf_compress_canonical
    cbf_canonical.c   remove argument repeat from cbf_compress_canonical
    cbf_compress.h   remove argument repeat from cbf_compress, change argument compression from pointer to value in cbf_decompress_parameters
    cbf_compress.c   remove argument repeat from cbf_compress, use compression as an input argument in cbf_decompress_parameters, do not write compression id
    cbf_file.c   tune buffer size allocations to current size
    cbf_lex.c   carry compression in text, not header, suppress binary header when there is a MIME header
    cbf_packed.h   remove argument repeat from cbf_compress_packed
    cbf_packed.c   remove argument repeat from cbf_compress_packed
    cbf_predictor.h   remove argument repeat from cbf_compress_predictor
    cbf_predictor.c   remove argument repeat from cbf_compress_predictor
    cbf_read_binary.h   make pointer to compression an argument to cbf_parse_binaryheader
    cbf_read_binary.c   carry compression in text, not header, suppress binary header when there is a MIME header
    cbf_read_mime.h   add prototype for cbf_nblen
    cbf_read_mime.c   carry compression in text, not header, suppress binary header when there is a MIME header, allow trailing blanks on header lines, test for early terminations, allow arbitrary spacing on element type, add cbf_nblen
    cbf_stx.c   rebuilt from cbf.stx with bison 1.25
    cbf_tree.c   tune allocation of memory for extra children to current use levels
    cbf_uncompressed.h   remove argument repeat from cbf_compress_none
    cbf_uncompressed.c   remove argument repeat from cbf_compress_none
    cbf_write.c   update version numbers in file headers
    cbf_write_binary.c   carry compression in text, not header, suppress binary header when there is a MIME header, quote X-Binary-Element-Type


    Release 0.5, Paul J. Ellis, 5 December 1998

    Source FileChange
    cbf.c   Add option for immediate digest evaluation (MSG_DIGESTNOW) or deferred digest evaluation (MSG_DIGEST); adjust layout of error messages; remove unused repeat.
    cbf.stx   Add new argument for cbf_set_columnrow.
    cbf_ascii.c   Add buffer flush.
    cbf_binary.c   Add call to cbf_codes.h; convert to use of cbf_get/set_bintext; digests saved in the text for deferred evaluation.
    cbf_byte_offset.c   Add storedbits argument on compression; remove repeat on decompression.
    cbf_canonical.c   Stylistic cleanup; add storedbits argument on compression; remove repeat on decompression.
    cbf_codes.c   Add routines cbf_is_base64digest, cbf_md5digest_to64, flush buffers when done, general cleanup
    cbf_compress.c   Add argument bits to cbf_compress and each actual compression routine, add bits and remove repeat on decompression.
    cbf_file.c   Reorganize digest logic; remove nblen argument from cbf_read_line.
    cbf_lex.c   Argument type and stylisic cleanup; allow for deferred digest evaluation, adjust binary size to agree with MIME size.
    cbf_packed.c   Stylistic cleanup; add storedbits argument on compression; remove repeat on decompression.
    cbf_predictor.c   Add storedbits argument on compression; remove repeat on decompression.
    cbf_read_mime.c   Add binary element type logic; cleanup header scan; allow for deferred digest evaluation.
    cbf_tree.c   Add argument free to cbf_set_columnrow. If free is true, free the old value, otherwise a user responsibility.
    cbf_uncompressed.c   Add storedbits argument on compression; remove repeat on decompression.
    cbf_write.c   Add buffer flush.
    cbf_write_binary.c   Reorganize digest calculation, adjust binary size by 8, add X-Binary-E;ement-Type.
    global.h   Change definition of UINT4 from unsigned long int to unsigned int.
    md5.c   Mask 32 bits for longer words.


    Release 0.4, Herbert J. Bernstein, 15 November 1998

    Source FileChange
    cbf_stx.c   rebuilt from cbf.stx with bison 1.25
    cbf_binary.c   add digest, elsize, elsign to text
    cbf_canonical.c   remove write of compression id
    cbf_codes.h   add argument *digest to cbf_fromqp, cbf_frombase64, cbf_frombasex
    cbf_codes.c   add mpack notice, add cbf_md5context_to64, add digest to cbf_from...
    cbf_compress.h   add argument *digest to cbf_compress
    cbf_compress.c   add digest to cbf_compress
    cbf_file.h   add nscolumn, digest_buffer, digest_bpoint, context to cbf_file struct, add argument *nblen to cbf_read_line
    cbf_file.c   add file->nscolumn, file->digest_buffer, file->digest_bpoint, update digest when writing
    cbf_lex.c   add notices, compute digests on intial read
    cbf_packed.c   do not write compression id
    cbf_read_mime.h   add prototype for cbf_skip_whitespace, add argument *compression to cbf_parse_mimeheader
    cbf_read_mime.c   add notices, remove redundant digest calculation, adjust handling of compression id, add cbf_skip_whitespace, have cbf_parse_mimeheader return compression id, add checks for garbled files, allow more general headers
    cbf_uncompressed.c   make uncompressed section free of headers
    cbf_write.c   update version in headers
    cbf_write_binary.c   carry digest, elsize, elsign in text rather than header


    Release 0.3.1.1, Paul J. Ellis, 21 September 1998

    Source FileChange
    cbf.h   remove globals, add tolen CBF_TOKEN_MIME_BIN, change MIME_NOHEADERS to PLAIN_HEADERS, add HDR_DEFAULT, add arguments ciforcbf, headers, encoding to cbf_write_file, add argument headers to cbf_read_file, restore const in several places, merge int cbf_get_integerarrayparams into cbf_get_integerarrayparameters
    cbf.c    add notices, add argument headers to cbf_read_file to replace use of globals in release 0.2, add arguments ciforcbf, headers, encoding to cbf_write_file to replace use of globals in release 0.2, restore some uses of const, remove integerarrayparams and merge arguments into cbf_get_integerparameters, replace cbf_binary_params with cbf_binary_parameters with extended argument list
    cbf.stx   add notices, remove gcc use of malloc, define alloca(x) as NULL, and set large inital depth, adopts mods from cbf.stx.y in release 0.2
    cbf_alloc.c   add notices
    cbf_ascii.c   change use of range of token values to explicit symbolic tokens
    cbf_binary.h   merge cbf_binary_params into cbf_binary_parameters, remove cbf_write_binary
    cbf_binary.c   add cbf_read_mime.h, and CBF_TOKEN_MIME_BIN token, use cbf_set/get_fileposition, merge cbf_binary_params into cbf_binary_parameters, restore some uses of const, use cbf_decompress_parameters with extended argument list, use cbf_mime_temp, move cbf_write_binary to its own file.
    cbf_canonical.h   add argument binsize to cbf_compress_canonical, add argument repeat to cbf_decompress_canonical
    cbf_canonical.c   add notices, remove binbitcount, handle binsize as an argument
    cbf_codes.h   new header
    cbf_codes.c   revise notices, major cleanup.
    cbf_compress.c   add notices, add compressedsize argument, add repeat to decompression calls
    cbf_context.c   add notices
    cbf_compress.h   add argument compressedsize to cbf_compress, repeat to cbf_decompress
    cbf_file.h   map "text..." to "buffer..." in cbf_file, remove CBFbytedir, change cbf_set_textsize to cbf_set_buffersize, add cbf_reset_buffer, add cbf_get_buffer, change cbf_get/put_text to cbf_get/put_block, add cbf_get/set_position
    cbf_file.c
      add notices, change file->text to file->buffer, file->text_size to file->buffer_size, file->text_used to file->buffer_used, file->read_headers, file->write_headers, file->write_encoding, remove file->fpos, file->fend, add cbf_get/set_fileposition
    cbf_lex.c   read by buffers, move MIME processing later in the flow
    cbf_packed.h
      add compressedsize argument to cbf-compress-packed, repeat to cbf_decompress_packed, remove ..none, ..byte_off, ..predict
    cbf_packed.c   add notices, add bitcount argument to cbf_pack_chunk
    cbf_predictor.h   new header
    cbf_predictor.c   New routine
    cbf_read_binary.h   new header
    cbf_read_binary.c   New routine
    cbf_read_mime.h   new header
    cbf_string.h   new header
    cbf_string.c   New routine, replacing string.c
    cbf_stx.c   Rebuild of cbf.stx with bison A2.6
    cbf_tree.h   remove CBF_INDEX, cbf_init_index, cbf_add_index, cleanup, add const
    cbf_tree.c   add notices, general cleanup, restore const, remove cbf_init_index, cbf_add_index
    cbf_uncompressed.h   new header
    cbf_uncompressed.c   New routine
    cbf_write.c   add notices, change tests for "?" and ".", change range test on tokens to explicit list
    cbf_write_binary.h   new header
    cbf_write_binary.c   New routine
    global.h   new routine with part of md5.h
    md5c.c   use global.h
    md5.h   move portion of this header to global.h, from whence it came


    Release 0.2, Herbert J. Bernstein, 27 August 1998

    Source FileChange
    cbf.h   Define CBF and CIF, add cbf_force_new_datablock, cbf_force_new_category, remove some uses of const, add, cbf_get_integerarrayparams, add globals CBForCIF, CIFCRterm, CIFNLterm, CBFbinsize, CBFmime, CBFdigest, CBFencoding, CBFelsize, CBFbytedir
    cbf.c   Define CBF and CIF, add cbf_force_new_datablock, cbf_force_new_category, remove some uses of const, add, cbf_get_integerarrayparams, add globals CBForCIF, CIFCRterm, CIFNLterm, CBFbinsize, CBFmime, CBFdigest, CBFencoding, CBFelsize, CBFbytedir
    cbf.stx   Add malloc.h when using gcc
    cbf.stx.y   Version of cbf.stx with changes to allow DDL1
    cbf_ascii.c   Use symbols for tokens
    cbf_binary.h   Add cbf_binary_params
    cbf_binary.c   Add digest logic, change file position tracking
    cbf_canonical.c   Make writing repeat consistent; track binbitcount add cbf_binary_params, use cbf_decompress_params; allow MIME header
    cbf_codes.c   New routine adapted from mpack
    cbf_compress.h   Add cbf_decompress_params
    cbf_compress.c   Add hooks for CBF_NONE, CBF_BYTE_OFFSET, CBF_PREDICTOR, add cbf_decompress_params
    cbf_context.h   Remove const from cbf_copy_string
    cbf_context.c   Remove const from cbf_copy_string
    cbf_decode.c   New routine adapted from mpack
    cbf_file.h   Add files to record file position
    cbf_file.c   Track file position; allow writing CIFs and CBFs
    cbf_lex.c   Add mime processing; add DDL1 support; process "."
    cbf_mime.c   New routine
    cbf_packed.h   Add cbf_compress_none, cbf_decompress_none, cbf_compress_byte_off, cbf_decompress_byte_off, cbf_compress_predict, cbf_decompress_predict
    cbf_packed.c   Add cbf_compress_none, cbf_decompress_none, dummy cbf_compress_byte_off, dummy cbf_decompress_byte_off, dummy cbf_compress_predict, dummy cbf_decompress_predict; ensure consistent writing of repeat
    cbf_part.h   New header adapted from mpack
    cbf_part.c   New routine adapted from pack
    cbf_stx.c   rebuilt with correct bison parser from cbf.stx.y
    cbf_tree.c   added cbf_make_new_node, cbf_find_last_child, cbf_name_new_node, cbf_add_new_child, cbf_make_new_child, cbf_init_index, cbf_add_index; report CBF_ARGUMENT for cbf_make_child for type CBF_LINK; removed some uses of const
    cbf_write.c   Added symbols for parse tokens; recognize "."; adjusted file header line to conform to documentation; removed some uses of const
    cif2cbf.c   New program
    common.h   New header from mpack
    img2cif.c   New program
    makecbf.c   Add local_exit and change cbf_failnez to facilitate debugging, add _array_intensities.binary_id, _array_data.binary.id
    md5.h   New header from mpack
    md5c.c   New routine from mpack
    string.c   New routine from mpack
    uudecode.c   New routine from mpack


    Release 0.1, Paul J. Ellis, 17 April 1998

    This was the first CBFlib release. It supported binary CBF files using binary strings.



    Updated 13 February 2011.
    ./CBFlib-0.9.2.2/doc/cif_img_1.6.3_26Aug10.dic0000644000076500007650000117011411603702115016260 0ustar yayayayadata_cif_img.dic _datablock.id cif_img.dic _datablock.description ; ############################################################################## # # # Image CIF Dictionary (imgCIF) # # and Crystallographic Binary File Dictionary (CBF) # # Extending the Macromolecular CIF Dictionary (mmCIF) # # # # Version 1.6.3 # # of 2010-08-26 # # ################################################################### # # # *** WARNING *** THIS IS A DRAFT FOR DISCUSSSION *** WARNING *** # # # # SUBJECT TO CHANGE WITHOUT NOTICE # # # # SEND COMMENTS TO imgcif-l@iucr.org CITING THE VERSION # # # ################################################################### # # This draft edited by H. J. Bernstein # # # # by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook # # # # This dictionary was adapted from format discussed at the imgCIF Workshop, # # held at BNL Oct 1997 and the Crystallographic Binary File Format Draft # # Proposal by Andrew Hammersley. The first DDL 2.1 Version was created by # # John Westbrook. This version was drafted by Herbert J. Bernstein and # # incorporates comments by I. David Brown, John Westbrook, Brian McMahon, # # Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li, Gotzon Madariaga, # # Frances C. Bernstein, Chris Nielsen, Nicola Ashcroft and others. # ############################################################################## ############################################################################## # CONTENTS # # CATEGORY_GROUP_LIST # SUB_CATEGORY # # category ARRAY_DATA # # _array_data.array_id # _array_data.binary_id # _array_data.data # _array_data.header_contents # _array_data.header_convention # _array_data.variant # # category ARRAY_ELEMENT_SIZE # # _array_element_size.array_id # _array_element_size.index # _array_element_size.size # _array_element_size.variant # # category ARRAY_INTENSITIES # # _array_intensities.array_id # _array_intensities.binary_id # _array_intensities.gain # _array_intensities.gain_esd # _array_intensities.linearity # _array_intensities.offset # _array_intensities.scaling # _array_intensities.overload # _array_intensities.undefined_value # _array_intensities.pixel_fast_bin_size # _array_intensities.pixel_slow_bin_size # _array_intensities.pixel_binning_method # _array_intensities.variant # # category ARRAY_STRUCTURE # # _array_structure.byte_order # _array_structure.compression_type # _array_structure.compression_type_flag # _array_structure.encoding_type # _array_structure.id # _array_structure.variant # # category ARRAY_STRUCTURE_LIST # # _array_structure_list.axis_set_id # _array_structure_list.array_id # _array_structure_list.dimension # _array_structure_list.direction # _array_structure_list.index # _array_structure_list.precedence # _array_structure_list.variant # # category ARRAY_STRUCTURE_LIST_AXIS # # _array_structure_list_axis.axis_id # _array_structure_list_axis.axis_set_id # _array_structure_list_axis.angle # _array_structure_list_axis.angle_increment # _array_structure_list_axis.displacement # _array_structure_list_axis.fract_displacement # _array_structure_list_axis.displacement_increment # _array_structure_list_axis.fract_displacement_increment # _array_structure_list_axis.angular_pitch # _array_structure_list_axis.radial_pitch # _array_structure_list_axis.reference_angle # _array_structure_list_axis.reference_displacement # _array_structure_list_axis.variant # # category AXIS # # _axis.depends_on # _axis.equipment # _axis.id # _axis.offset[1] # _axis.offset[2] # _axis.offset[3] # _axis.type # _axis.system # _axis.vector[1] # _axis.vector[2] # _axis.vector[3] # _axis.variant # # category DIFFRN_DATA_FRAME # # _diffrn_data_frame.array_id # _diffrn_data_frame.binary_id # _diffrn_data_frame.center_fast # _diffrn_data_frame.center_slow # _diffrn_data_frame.center_units # _diffrn_data_frame.detector_element_id # _diffrn_data_frame.id # _diffrn_data_frame.details # _diffrn_data_frame.variant # # category DIFFRN_DETECTOR # # _diffrn_detector.details # _diffrn_detector.detector # _diffrn_detector.diffrn_id # _diffrn_detector.dtime # _diffrn_detector.id # _diffrn_detector.number_of_axes # _diffrn_detector.type # _diffrn_detector.variant # # category DIFFRN_DETECTOR_AXIS # # _diffrn_detector_axis.axis_id # _diffrn_detector_axis.detector_id # _diffrn_detector_axis.variant # # category DIFFRN_DETECTOR_ELEMENT # # _diffrn_detector_element.id # _diffrn_detector_element.detector_id # _diffrn_detector_element.reference_center_fast # _diffrn_detector_element.reference_center_slow # _diffrn_detector_element.reference_center_units # _diffrn_detector_element.variant # # category DIFFRN_MEASUREMENT # # _diffrn_measurement.diffrn_id # _diffrn_measurement.details # _diffrn_measurement.device # _diffrn_measurement.device_details # _diffrn_measurement.device_type # _diffrn_measurement.id # _diffrn_measurement.method # _diffrn_measurement.number_of_axes # _diffrn_measurement.sample_detector_distance # _diffrn_measurement.sample_detector_voffset # _diffrn_measurement.specimen_support # _diffrn_measurement.variant # # category DIFFRN_MEASUREMENT_AXIS # # _diffrn_measurement_axis.axis_id # _diffrn_measurement_axis.measurement_device # _diffrn_measurement_axis.measurement_id # _diffrn_measurement_axis.variant # # category DIFFRN_RADIATION # # _diffrn_radiation.collimation # _diffrn_radiation.diffrn_id # _diffrn_radiation.div_x_source # _diffrn_radiation.div_y_source # _diffrn_radiation.div_x_y_source # _diffrn_radiation.filter_edge' # _diffrn_radiation.inhomogeneity # _diffrn_radiation.monochromator # _diffrn_radiation.polarisn_norm # _diffrn_radiation.polarisn_ratio # _diffrn_radiation.polarizn_source_norm # _diffrn_radiation.polarizn_source_ratio # _diffrn_radiation.probe # _diffrn_radiation.type # _diffrn_radiation.xray_symbol # _diffrn_radiation.wavelength_id # _diffrn_radiation.variant # # category DIFFRN_REFLN # # _diffrn_refln.frame_id # _diffrn_refln.variant # # category DIFFRN_SCAN # # _diffrn_scan.id # _diffrn_scan.date_end # _diffrn_scan.date_start # _diffrn_scan.integration_time # _diffrn_scan.frame_id_start # _diffrn_scan.frame_id_end # _diffrn_scan.frames # _diffrn_scan.variant # # category DIFFRN_SCAN_AXIS # # _diffrn_scan_axis.axis_id # _diffrn_scan_axis.angle_start # _diffrn_scan_axis.angle_range # _diffrn_scan_axis.angle_increment # _diffrn_scan_axis.angle_rstrt_incr # _diffrn_scan_axis.displacement_start # _diffrn_scan_axis.displacement_range # _diffrn_scan_axis.displacement_increment # _diffrn_scan_axis.displacement_rstrt_incr # _diffrn_scan_axis.reference_angle # _diffrn_scan_axis.reference_displacement # _diffrn_scan_axis.scan_id # _diffrn_scan_axis.variant # # category DIFFRN_SCAN_FRAME # # _diffrn_scan_frame.date # _diffrn_scan_frame.frame_id # _diffrn_scan_frame.frame_number # _diffrn_scan_frame.integration_time # _diffrn_scan_frame.scan_id # _diffrn_scan_frame.variant # # category DIFFRN_SCAN_FRAME_AXIS # # _diffrn_scan_frame_axis.axis_id # _diffrn_scan_frame_axis.angle # _diffrn_scan_frame_axis.angle_increment # _diffrn_scan_frame_axis.angle_rstrt_incr # _diffrn_scan_frame_axis.displacement # _diffrn_scan_frame_axis.displacement_increment # _diffrn_scan_frame_axis.displacement_rstrt_incr # _diffrn_scan_frame_axis.reference_angle # _diffrn_scan_frame_axis.reference_displacement # _diffrn_scan_frame_axis.frame_id # _diffrn_scan_frame_axis.variant # # category DIFFRN_SCAN_FRAME_MONITOR # # _diffrn_scan_frame_monitor.id # _diffrn_scan_frame_monitor.detector_id # _diffrn_scan_frame_monitor.scan_id # _diffrn_data_frame_monitor.frame_id # _diffrn_data_frame_monitor.integration_time # _diffrn_data_frame_monitor.monitor_value # _diffrn_data_frame_monitor.variant # # category MAP # # _map.details # _map.diffrn_id # _map.entry_id # _map.id # _map.variant # # category MAP_SEGMENT # # _map_segment.array_id # _map_segment.binary_id # _map_segment.mask_array_id # _map_segment.mask_binary_id # _map_segment.id # _map_segment.map_id # _map_segment.details # _map_segment.variant # # category VARIANT # # _variant.details # _variant.role # _variant.timestamp # _variant.variant # _variant.variant_of # # ***DEPRECATED*** data items # # _diffrn_detector_axis.id # _diffrn_detector_element.center[1] # _diffrn_detector_element.center[2] # _diffrn_measurement_axis.id # # ***DEPRECATED*** category DIFFRN_FRAME_DATA # # _diffrn_frame_data.array_id # _diffrn_frame_data.binary_id # _diffrn_frame_data.detector_element_id # _diffrn_frame_data.id # _diffrn_frame_data.details # # # ITEM_TYPE_LIST # ITEM_UNITS_LIST # DICTIONARY_HISTORY # ############################################################################## +-------------------------------------------------------------------------------------------------------------+ |ARRAY_DATA_GROUP|Categories that describe array data. | | |--------------------------------------------------------------------------------------------| | |+------------------------------------------------------------------------------------------+| | || ARRAY_DATA | Data items in the ARRAY_DATA category are the containers for the || | || | array data items described in the category ARRAY_STRUCTURE. || | || | || | || | It is recognized that the data in this category needs to be used || | || | in two distinct ways. During a data collection the lack of || | || | ancillary data and timing constraints in processing data may || | || | dictate the need to make a 'miniCBF' nothing more than an || | || | essential minimum of information to record the results of the || | || | data collection. In that case it is proper to use the ARRAY_DATA || | || | category as a container for just a single image and a compacted, || | || | beam-line dependent list of data collection parameter values. In || | || | such a case, only the tags '_array_data.header_convention', || | || | '_array_data.header_contents' and '_array_data.data' need be || | || | populated. || | || | || | || | For full processing and archiving, most of the tags in this || | || | dictionary will need to be populated. || | ||----------------------+-------------------------------------------------------------------|| | || ARRAY_ELEMENT_SIZE | Data items in the ARRAY_ELEMENT_SIZE category record the physical || | || | size of array elements along each array dimension. || | ||----------------------+-------------------------------------------------------------------|| | || ARRAY_INTENSITIES | Data items in the ARRAY_INTENSITIES category record the || | || | information required to recover the intensity data from the set || | || | of data values stored in the ARRAY_DATA category. || | || | || | || | The detector may have a complex relationship between the raw || | || | intensity values and the number of incident photons. In most || | || | cases, the number stored in the final array will have a simple || | || | linear relationship to the actual number of incident photons, || | || | given by _array_intensities.gain. If raw, uncorrected values are || | || | presented (e.g. for calibration experiments), the value of || | || | _array_intensities.linearity will be 'raw' and || | || | _array_intensities.gain will not be used. || | ||----------------------+-------------------------------------------------------------------|| | || ARRAY_STRUCTURE | Data items in the ARRAY_STRUCTURE category record the || | || | organization and encoding of array data that may be stored in the || | || | ARRAY_DATA category. || | ||------------------------------------------------------------------------------------------|| | || +--------------------------------------------------------------------------------------+ || | || | | ARRAY_STRUCTURE_LIST | Data items in the ARRAY_STRUCTURE_LIST category | || | || | | | record the size and organization of each array | || | || | | | dimension. | || | || | | | | || | || | | | The relationship to physical axes may be given. | || | || | |----------------------------------------------------------------------------------| || | || | | +------------------------------------------------------------------------------+ | || | || | | | | ARRAY_STRUCTURE_LIST_AXIS | Data items in the ARRAY_STRUCTURE_LIST_AXIS | | || | || | | | | | category describe the physical settings of | | || | || | | | | | sets of axes for the centres of pixels that | | || | || | | | | | correspond to data points described in the | | || | || | | | | | ARRAY_STRUCTURE_LIST category. | | || | || | | | | | | | || | || | | | | | In the simplest cases, the physical | | || | || | | | | | increments of a single axis correspond to | | || | || | | | | | the increments of a single array index. More | | || | || | | | | | complex organizations, e.g. spiral scans, | | || | || | | | | | may require coupled motions along multiple | | || | || | | | | | axes. | | || | || | | | | | | | || | || | | | | | Note that a spiral scan uses two coupled | | || | || | | | | | axes: one for the angular direction and one | | || | || | | | | | for the radial direction. This differs from | | || | || | | | | | a cylindrical scan for which the two axes | | || | || | | | | | are not coupled into one set. | | || | || | | +------------------------------------------------------------------------------+ | || | || +--------------------------------------------------------------------------------------+ || | |+------------------------------------------------------------------------------------------+| |----------------+--------------------------------------------------------------------------------------------| |AXIS_GROUP |Categories that describe axes. | | |--------------------------------------------------------------------------------------------| | |+------------------------------------------------------------------------------------------+| | || AXIS | Data items in the AXIS category record the information required to describe the || | || | various goniometer, detector, source and other axes needed to specify a data || | || | collection or the axes defining the coordinate system of an image. || | || | || | || | The location of each axis is specified by two vectors: the axis itself, given by || | || | a unit vector in the direction of the axis, and an offset to the base of the unit || | || | vector. || | || | || | || | The vectors defining an axis are referenced to an appropriate coordinate system. || | || | The axis vector, itself, is a dimensionless unit vector. Where meaningful, the || | || | offset vector is given in millimetres. In coordinate systems not measured in || | || | metres, the offset is not specified and is taken as zero. || | || | || | || | The available coordinate systems are: || | || | || | || | The imgCIF standard laboratory coordinate system || | || | The direct lattice (fractional atomic coordinates) || | || | The orthogonal Cartesian coordinate system (real space) || | || | The reciprocal lattice || | || | An abstract orthogonal Cartesian coordinate frame || | |+------------------------------------------------------------------------------------------+| |----------------+--------------------------------------------------------------------------------------------| |DIFFRN_GROUP |Categories that describe details of the diffraction experiment. | | |--------------------------------------------------------------------------------------------| | |+------------------------------------------------------------------------------------------+| | || DIFFRN_DATA_FRAME | Data items in the DIFFRN_DATA_FRAME category record the || | || | details about each frame of data. || | || | || | || | The items in this category were previously in a || | || | DIFFRN_FRAME_DATA category, which is now deprecated. The || | || | items from the old category are provided as aliases but || | || | should not be used for new work. || | ||--------------------------+---------------------------------------------------------------|| | || DIFFRN_DETECTOR | Data items in the DIFFRN_DETECTOR category describe the || | || | detector used to measure the scattered radiation, including || | || | any analyser and post-sample collimation. || | ||------------------------------------------------------------------------------------------|| | || +--------------------------------------------------------------------------------------+ || | || | | DIFFRN_DETECTOR_AXIS | Data items in the DIFFRN_DETECTOR_AXIS category associate | || | || | | | axes with detectors. | || | || +--------------------------------------------------------------------------------------+ || | ||------------------------------------------------------------------------------------------|| | || +--------------------------------------------------------------------------------------+ || | || | | DIFFRN_DETECTOR_ELEMENT | Data items in the DIFFRN_DETECTOR_ELEMENT category | || | || | | | record the details about spatial layout and other | || | || | | | characteristics of each element of a detector which | || | || | | | may have multiple elements. | || | || | | | | || | || | | | In most cases, giving more detailed information in | || | || | | | ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS is | || | || | | | preferable to simply providing the centre of the | || | || | | | detector element. | || | || +--------------------------------------------------------------------------------------+ || | ||------------------------------------------------------------------------------------------|| | || DIFFRN_MEASUREMENT | Data items in the DIFFRN_MEASUREMENT category record details || | || | about the device used to orient and/or position the crystal || | || | during data measurement and the manner in which the || | || | diffraction data were measured. || | ||------------------------------------------------------------------------------------------|| | || +--------------------------------------------------------------------------------------+ || | || | | DIFFRN_MEASUREMENT_AXIS | Data items in the DIFFRN_MEASUREMENT_AXIS category | || | || | | | associate axes with goniometers. | || | || +--------------------------------------------------------------------------------------+ || | ||------------------------------------------------------------------------------------------|| | || DIFFRN_RADIATION | Data items in the DIFFRN_RADIATION category describe the || | || | radiation used for measuring diffraction intensities, its || | || | collimation and monochromatization before the sample. || | || | || | || | Post-sample treatment of the beam is described by data items || | || | in the DIFFRN_DETECTOR category. || | ||--------------------------+---------------------------------------------------------------|| | || DIFFRN_REFLN | This category redefinition has been added to extend the key || | || | of the standard DIFFRN_REFLN category. || | || | || | || | Data items in the DIFFRN_REFLN category record details about || | || | the intensities in the diffraction data set identified by || | || | _diffrn_refln.diffrn_id. || | || | || | || | The DIFFRN_REFLN data items refer to individual intensity || | || | measurements and must be included in looped lists. || | || | || | || | The DIFFRN_REFLNS data items specify the parameters that || | || | apply to all intensity measurements in the particular || | || | diffraction data set identified by _diffrn_reflns.diffrn_id || | || | and _diffrn_refln.frame_id || | ||--------------------------+---------------------------------------------------------------|| | || DIFFRN_SCAN | Data items in the DIFFRN_SCAN category describe the || | || | parameters of one or more scans, relating axis positions to || | || | frames. || | ||------------------------------------------------------------------------------------------|| | || +--------------------------------------------------------------------------------------+ || | || | | DIFFRN_SCAN_AXIS | Data items in the DIFFRN_SCAN_AXIS category describe the | || | || | | | settings of axes for particular scans. Unspecified axes are | || | || | | | assumed to be at their zero points. | || | || +--------------------------------------------------------------------------------------+ || | ||------------------------------------------------------------------------------------------|| | || +--------------------------------------------------------------------------------------+ || | || | | DIFFRN_SCAN_FRAME | Data items in the DIFFRN_SCAN_FRAME category describe the | || | || | | | relationships of particular frames to scans. | || | || +--------------------------------------------------------------------------------------+ || | ||------------------------------------------------------------------------------------------|| | || +--------------------------------------------------------------------------------------+ || | || | | +------------------------------------------------------------------------------+ | || | || | | | | DIFFRN_SCAN_FRAME_AXIS | Data items in the DIFFRN_SCAN_FRAME_AXIS | | || | || | | | | | category describe the settings of axes for | | || | || | | | | | particular frames. Unspecified axes are assumed | | || | || | | | | | to be at their zero points. If, for any given | | || | || | | | | | frame, nonzero values apply for any of the data | | || | || | | | | | items in this category, those values should be | | || | || | | | | | given explicitly in this category and not | | || | || | | | | | simply inferred from values in | | || | || | | | | | DIFFRN_SCAN_AXIS. | | || | || | | +------------------------------------------------------------------------------+ | || | || |---+----------------------------------------------------------------------------------| || | || | | +------------------------------------------------------------------------------+ | || | || | | | | DIFFRN_SCAN_FRAME_MONITOR | Data items in the DIFFRN_SCAN_FRAME_MONITOR | | || | || | | | | | category record the values and details about | | || | || | | | | | each monitor for each frame of data during a | | || | || | | | | | scan. | | || | || | | | | | | | || | || | | | | | Each monitor value is uniquely identified by | | || | || | | | | | the combination of the scan_id given by | | || | || | | | | | _diffrn_scan_frame.scan_id the frame_id | | || | || | | | | | given by | | || | || | | | | | _diffrn_scan_frame_monitor.frame_id, the | | || | || | | | | | monitor's detector_id given by | | || | || | | | | | _diffrn_scan_frame_monitor.monitor_id, and a | | || | || | | | | | 1-based ordinal given by | | || | || | | | | | _diffrn_scan_frame_monitor.id. | | || | || | | | | | | | || | || | | | | | If there is only one frame for the scan, the | | || | || | | | | | value of _diffrn_scan_frame_monitor.frame_id | | || | || | | | | | may be omitted. | | || | || | | | | | | | || | || | | | | | A single frame may have more than one | | || | || | | | | | monitor value, and each monitor value may be | | || | || | | | | | the result of integration over the entire | | || | || | | | | | frame integration time given by the value of | | || | || | | | | | _diffrn_scan_frame.integration_time or many | | || | || | | | | | monitor values may be reported over shorter | | || | || | | | | | times given by the value of | | || | || | | | | | _diffrn_scan_frame_monitor.integration_time. | | || | || | | | | | If only one monitor value for a given | | || | || | | | | | monitor is collected during the integration | | || | || | | | | | time of the frame, the value of | | || | || | | | | | _diffrn_scan_frame_monitor.id may be | | || | || | | | | | omitted. | | || | || | | +------------------------------------------------------------------------------+ | || | || +--------------------------------------------------------------------------------------+ || | |+------------------------------------------------------------------------------------------+| |----------------+--------------------------------------------------------------------------------------------| |MAP_GROUP |Categories that describe maps. | | |--------------------------------------------------------------------------------------------| | |+------------------------------------------------------------------------------------------+| | || MAP | Data items in the MAP category record the details of a maps. Maps record values || | || | of parameters, such as density, that are functions of position within a cell or || | || | are functions of orthogonal coordinates in three space. || | || | || | || | A map may is composed of one or more map segments specified in the MAP_SEGMENT || | || | category. || | || | || | || | Examples are given in the MAP_SEGMENT category. || | ||------------------------------------------------------------------------------------------|| | || +--------------------------------------------------------------------------------------+ || | || | | MAP_SEGMENT | Data items in the MAP_SEGMENT category record the details about | || | || | | | each segment (section or brick) of a map. | || | || +--------------------------------------------------------------------------------------+ || | |+------------------------------------------------------------------------------------------+| |----------------+--------------------------------------------------------------------------------------------| |VARIANT_GROUP |Categories that describe variants | | |--------------------------------------------------------------------------------------------| | |+------------------------------------------------------------------------------------------+| | || VARIANT | Data items in the VARIANT category record the details about sets of variants || | || | of data items. || | || | || | || | There is sometimes a need to allow for multiple versions of the same data || | || | items in order to allow for refinements and corrections to earlier || | || | assumptions, observations and calculations. In order to allow data sets to || | || | contain more than one variant of the same information, an optional ...variant || | || | data item as a pointer to _variant.variant has been added to the key of every || | || | category, as an implicit data item with a null (empty) default value. || | || | || | || | All rows in a category with the same variant value are considered to be || | || | related to one another and to all rows in other categories with the same || | || | variant value. For a given variant, all such rows are also considered to be || | || | related to all rows with a null variant value, except that a row with a null || | || | variant value is for which all other components of its key are identical to || | || | those entries in another row with a non-null variant value is not related the || | || | the rows with that non-null variant value. This behavior is similar to the || | || | convention for identifying alternate conformers in an atom list. || | || | || | || | An optional role may be specified for a variant as the value of _variant.role. || | || | Possible roles are null, "preferred", "raw data", "unsuccessful trial". || | || | || | || | Variants may carry an optional timestamp as the value of _variant.timestamp. || | || | || | || | Variants may be related to other variants from which they were derived by the || | || | value of _variant.variant_of || | || | || | || | Further details about the variant may be specified as the value of || | || | _variant.details. || | || | || | || | In order to allow variant information from multiple datasets to be combined, || | || | _variant.diffrn_id and/or _variant.entry_id may be used. || | |+------------------------------------------------------------------------------------------+| +-------------------------------------------------------------------------------------------------------------+ ; _dictionary.title cif_img.dic _dictionary.version 1.6.3 _dictionary.datablock_id cif_img.dic ######################### ## CATEGORY_GROUP_LIST ## ######################### loop_ _category_group_list.id _category_group_list.parent_id _category_group_list.description 'inclusive_group' . ; Categories that belong to the dictionary extension. ; 'array_data_group' 'inclusive_group' ; Categories that describe array data. ; 'axis_group' 'inclusive_group' ; Categories that describe axes. ; 'diffrn_group' 'inclusive_group' ; Categories that describe details of the diffraction experiment. ; 'map_group' 'inclusive_group' ; Categories that describe details of map data. ; 'variant_group' 'inclusive_group' ; Categories that describe details of map data. ; ################## ## SUB_CATEGORY ## ################## loop_ _sub_category.id _sub_category.description 'matrix' ; The collection of elements of a matrix. ; 'vector' ; The collection of elements of a vector. ; ############## # ARRAY_DATA # ############## save_ARRAY_DATA _category.description ; Data items in the ARRAY_DATA category are the containers for the array data items described in the category ARRAY_STRUCTURE. It is recognized that the data in this category needs to be used in two distinct ways. During a data collection the lack of ancillary data and timing constraints in processing data may dictate the need to make a 'miniCBF' nothing more than an essential minimum of information to record the results of the data collection. In that case it is proper to use the ARRAY_DATA category as a container for just a single image and a compacted, beam-line dependent list of data collection parameter values. In such a case, only the tags '_array_data.header_convention', '_array_data.header_contents' and '_array_data.data' need be populated. For full processing and archiving, most of the tags in this dictionary will need to be populated. ; _category.id array_data _category.mandatory_code no loop_ _category_key.name '_array_data.array_id' '_array_data.binary_id' '_array_data.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows two binary data blocks. The first one was compressed by the CBF_CANONICAL compression algorithm and is presented as hexadecimal data. The first character 'H' on the data lines means hexadecimal. It could have been 'O' for octal or 'D' for decimal. The second character on the line shows the number of bytes in each word (in this case '4'), which then requires eight hexadecimal digits per word. The third character gives the order of octets within a word, in this case '<' for the ordering 4321 (i.e. 'big-endian'). Alternatively, the character '>' could have been used for the ordering 1234 (i.e. 'little-endian'). The block has a 'message digest' to check the integrity of the data. The second block is similar, but uses CBF_PACKED compression and BASE64 encoding. Note that the size and the digest are different. ; ; loop_ _array_data.array_id _array_data.binary_id _array_data.data image_1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF_CANONICAL" Content-Transfer-Encoding: X-BASE16 X-Binary-Size: 3927126 X-Binary-ID: 1 Content-MD5: u2sTJEovAHkmkDjPi+gWsg== # Hexadecimal encoding, byte 0, byte order ...21 # H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ... .... --CIF-BINARY-FORMAT-SECTION---- ; image_2 2 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF-PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3745758 X-Binary-ID: 2 Content-MD5: 1zsJjWPfol2GYl2V+QSXrw== ELhQAAAAAAAA... ... --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - This example shows a single image in a miniCBF, provided by E. Eikenberry. The entire CBF consists of one data block containing one category and three tags. The CBFlib program convert_miniCBF and a suitable template file can be used to convert this miniCBF to a full imgCIF file. ; ; ###CBF: VERSION 1.5 # CBF file written by CBFlib v0.7.8 data_insulin_pilatus6m _array_data.header_convention SLS_1.0 _array_data.header_contents ; # Detector: PILATUS 6M SN: 60-0001 # 2007/Jun/17 15:12:36.928 # Pixel_size 172e-6 m x 172e-6 m # Silicon sensor, thickness 0.000320 m # Exposure_time 0.995000 s # Exposure_period 1.000000 s # Tau = 194.0e-09 s # Count_cutoff 1048575 counts # Threshold_setting 5000 eV # Wavelength 1.2398 A # Energy_range (0, 0) eV # Detector_distance 0.15500 m # Detector_Voffset -0.01003 m # Beam_xy (1231.00, 1277.00) pixels # Flux 22487563295 ph/s # Filter_transmission 0.0008 # Start_angle 13.0000 deg. # Angle_increment 1.0000 deg. # Detector_2theta 0.0000 deg. # Polarization 0.990 # Alpha 0.0000 deg. # Kappa 0.0000 deg. # Phi 0.0000 deg. # Chi 0.0000 deg. # Oscillation_axis X, CW # N_oscillations 1 ; _array_data.data ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_BYTE_OFFSET" Content-Transfer-Encoding: BINARY X-Binary-Size: 6247567 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" X-Binary-Element-Byte-Order: LITTLE_ENDIAN Content-MD5: 8wO6i2+899lf5iO8QPdgrw== X-Binary-Number-of-Elements: 6224001 X-Binary-Size-Fastest-Dimension: 2463 X-Binary-Size-Second-Dimension: 2527 X-Binary-Size-Padding: 4095 ... --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_data.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. If not given, it defaults to 1. ; _item.name '_array_data.array_id' _item.category_id array_data _item.mandatory_code implicit _item_default.value 1 _item_type.code code save_ save__array_data.binary_id _item_description.description ; This item is an integer identifier which, along with _array_data.array_id, should uniquely identify the particular block of array data. If _array_data.binary_id is not explicitly given, it defaults to 1. The value of _array_data.binary_id distinguishes among multiple sets of data with the same array structure. If the MIME header of the data array specifies a value for X-Binary-ID, the value of _array_data.binary_id should be equal to the value given for X-Binary-ID. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_data.binary_id' array_data implicit '_diffrn_data_frame.binary_id' diffrn_data_frame implicit '_array_intensities.binary_id' array_intensities implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.binary_id' '_array_data.binary_id' '_array_intensities.binary_id' '_array_data.binary_id' _item_default.value 1 _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_data.data _item_description.description ; The value of _array_data.data contains the array data encapsulated in a STAR string. The representation used is a variant on the Multipurpose Internet Mail Extensions (MIME) specified in RFC 2045-2049 by N. Freed et al. The boundary delimiter used in writing an imgCIF or CBF is '\n--CIF-BINARY-FORMAT-SECTION--' (including the required initial '\n--'). The Content-Type may be any of the discrete types permitted in RFC 2045; 'application/octet-stream' is recommended for diffraction images in the ARRAY_DATA category. Note: When appropriate in other categories, e.g. for photographs of crystals, more precise types, such as 'image/jpeg', 'image/tiff', 'image/png', etc. should be used. If an octet stream was compressed, the compression should be specified by the parameter 'conversions="X-CBF_PACKED"' or the parameter 'conversions="X-CBF_CANONICAL"' or the parameter 'conversions="X-CBF_BYTE_OFFSET"' or the parameter 'conversions="X-CBF_BACKGROUND_OFFSET_DELTA"' If the parameter 'conversions="X-CBF_PACKED"' is given it may be further modified with the parameters '"uncorrelated_sections"' or '"flat"' If the '"uncorrelated_sections"' parameter is given, each section will be compressed without using the prior section for averaging. If the '"flat"' parameter is given, each the image will be treated as one long row. Note that the X-CBF_CANONICAL and X-CBF_PACKED are slower but more efficient compressions that the others. The X-CBF_BYTE_OFFSET compression is a good compromise between speed and efficiency for ordinary diffraction images. The X-CBF_BACKGROUND_OFFSET_DELTA compression is oriented towards sparse data, such as masks and tables of replacement pixel values for images with overloaded spots. The Content-Transfer-Encoding may be 'BASE64', 'Quoted-Printable', 'X-BASE8', 'X-BASE10', 'X-BASE16' or 'X-BASE32K', for an imgCIF or 'BINARY' for a CBF. The octal, decimal and hexadecimal transfer encodings are provided for convenience in debugging and are not recommended for archiving and data interchange. In a CIF, one of the parameters 'charset=us-ascii', 'charset=utf-8' or 'charset=utf-16' may be used on the Content-Transfer-Encoding to specify the character set used for the external presentation of the encoded data. If no charset parameter is given, the character set of the enclosing CIF is assumed. In any case, if a BOM flag is detected (FE FF for big-endian UTF-16, FF FE for little-endian UTF-16 or EF BB BF for UTF-8) is detected, the indicated charset will be assumed until the end of the encoded data or the detection of a different BOM. The charset of the Content-Transfer-Encoding is not the character set of the encoded data, only the character set of the presentation of the encoded data and should be respecified for each distinct STAR string. In an imgCIF file, the encoded binary data begins after the empty line terminating the header. In an imgCIF file, the encoded binary data ends with the terminating boundary delimiter '\n--CIF-BINARY-FORMAT-SECTION----' in the currently effective charset or with the '\n; ' that terminates the STAR string. In a CBF, the raw binary data begins after an empty line terminating the header and after the sequence: Octet Hex Decimal Purpose 0 0C 12 (ctrl-L) Page break 1 1A 26 (ctrl-Z) Stop listings in MS-DOS 2 04 04 (Ctrl-D) Stop listings in UNIX 3 D5 213 Binary section begins None of these octets are included in the calculation of the message size or in the calculation of the message digest. The X-Binary-Size header specifies the size of the equivalent binary data in octets. If compression was used, this size is the size after compression, including any book-keeping fields. An adjustment is made for the deprecated binary formats in which eight bytes of binary header are used for the compression type. In this case, the eight bytes used for the compression type are subtracted from the size, so that the same size will be reported if the compression type is supplied in the MIME header. Use of the MIME header is the recommended way to supply the compression type. In general, no portion of the binary header is included in the calculation of the size. The X-Binary-Element-Type header specifies the type of binary data in the octets, using the same descriptive phrases as in _array_structure.encoding_type. The default value is 'unsigned 32-bit integer'. An MD5 message digest may, optionally, be used. The 'RSA Data Security, Inc. MD5 Message-Digest Algorithm' should be used. No portion of the header is included in the calculation of the message digest. If the Transfer Encoding is 'X-BASE8', 'X-BASE10' or 'X-BASE16', the data are presented as octal, decimal or hexadecimal data organized into lines or words. Each word is created by composing octets of data in fixed groups of 2, 3, 4, 6 or 8 octets, either in the order ...4321 ('big- endian') or 1234... ('little-endian'). If there are fewer than the specified number of octets to fill the last word, then the missing octets are presented as '==' for each missing octet. Exactly two equal signs are used for each missing octet even for octal and decimal encoding. The format of lines is: rnd xxxxxx xxxxxx xxxxxx where r is 'H', 'O' or 'D' for hexadecimal, octal or decimal, n is the number of octets per word and d is '<' or '>' for the '...4321' and '1234...' octet orderings, respectively. The '==' padding for the last word should be on the appropriate side to correspond to the missing octets, e.g. H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000 or H3> FF0700 00==== For these hexadecimal, octal and decimal formats only, comments beginning with '#' are permitted to improve readability. BASE64 encoding follows MIME conventions. Octets are in groups of three: c1, c2, c3. The resulting 24 bits are broken into four six-bit quantities, starting with the high-order six bits (c1 >> 2) of the first octet, then the low-order two bits of the first octet followed by the high-order four bits of the second octet [(c1 & 3)<<4 | (c2>>4)], then the bottom four bits of the second octet followed by the high-order two bits of the last octet [(c2 & 15)<<2 | (c3>>6)], then the bottom six bits of the last octet (c3 & 63). Each of these four quantities is translated into an ASCII character using the mapping: 1 2 3 4 5 6 0123456789012345678901234567890123456789012345678901234567890123 | | | | | | | ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/ With short groups of octets padded on the right with one '=' if c3 is missing, and with '==' if both c2 and c3 are missing. X-BASE32K encoding is similar to BASE64 encoding, except that sets of 15 octets are encoded as sets of 8 16-bit unicode characters, by breaking the 120 bits into 8 15-bit quantities. 256 is added to each 15 bit quantity to bring it into a printable uncode range. When encoding, zero padding is used to fill out the last 15 bit quantity. If 8 or more bits of padding are used, a single equals sign (hexadecimal 003D) is appended. Embedded whitespace and newlines are introduced to produce lines of no more than 80 characters each. On decoding, all printable ascii characters and ascii whitespace characters are ignored except for any trailing equals signs. The number of trailing equals signs indicated the number of trailing octets to be trimmed from the end of the decoded data. (see Georgi Darakev, Vassil Litchev, Kostadin Z. Mitev, Herbert J. Bernstein, 'Efficient Support of Binary Data in the XML Implementation of the NeXus File Format',absract W0165, ACA Summer Meeting, Honolulu, HI, July 2006). QUOTED-PRINTABLE encoding also follows MIME conventions, copying octets without translation if their ASCII values are 32...38, 42, 48...57, 59, 60, 62, 64...126 and the octet is not a ';' in column 1. All other characters are translated to =nn, where nn is the hexadecimal encoding of the octet. All lines are 'wrapped' with a terminating '=' (i.e. the MIME conventions for an implicit line terminator are never used). The "X-Binary-Element-Byte-Order" can specify either '"BIG_ENDIAN"' or '"LITTLE_ENDIAN"' byte order of the imaage data. Only LITTLE_ENDIAN is recommended. Processors may treat BIG_ENDIAN as a warning of data that can only be processed by special software. The "X-Binary-Number-of-Elements" specifies the number of elements (not the number of octets) in the decompressed, decoded image. The optional "X-Binary-Size-Fastest-Dimension" specifies the number of elements (not the number of octets) in one row of the fastest changing dimension of the binary data array. This information must be in the MIME header for proper operation of some of the decompression algorithms. The optional "X-Binary-Size-Second-Dimension" specifies the number of elements (not the number of octets) in one column of the second-fastest changing dimension of the binary data array. This information must be in the MIME header for proper operation of some of the decompression algorithms. The optional "X-Binary-Size-Third-Dimension" specifies the number of sections for the third-fastest changing dimension of the binary data array. The optional "X-Binary-Size-Padding" specifies the size in octets of an optional padding after the binary array data and before the closing flags for a binary section. ; _item.name '_array_data.data' _item.category_id array_data _item.mandatory_code yes _item_type.code binary save_ save__array_data.header_contents _item_description.description ; This item is an text field for use in minimal CBF files to carry essential header information to be kept with image data in _array_data.data when the tags that normally carry the structured metadata for the image have not been populated. Normally this data item should not appear when the full set of tags have been populated and _diffrn_data_frame.details appears. ; _item.name '_array_data.header_contents' _item.category_id array_data _item.mandatory_code no _item_type.code text save_ save__array_data.header_convention _item_description.description ; This item is an identifier for the convention followed in constructing the contents of _array_data.header_contents The permitted values are of the of an image creator identifier followed by an underscore and a version string. To avoid confusion about conventions, all creator identifiers should be registered with the IUCr and the conventions for all identifiers and versions should be posted on the MEDSBIO.org web site. ; _item.name '_array_data.header_convention' _item.category_id array_data _item.mandatory_code no _item_type.code code save_ save__array_data.variant _item_description.description ; The value of _array_data.variant gives the variant to which the given array_data row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_array_data.variant' _item.category_id array_data _item.mandatory_code no _item_type.code code save_ ###################### # ARRAY_ELEMENT_SIZE # ###################### save_ARRAY_ELEMENT_SIZE _category.description ; Data items in the ARRAY_ELEMENT_SIZE category record the physical size of array elements along each array dimension. ; _category.id array_element_size _category.mandatory_code no loop_ _category_key.name '_array_element_size.array_id' '_array_element_size.index' '_array_element_size.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A regular 2D array with a uniform element dimension of 1220 nanometres. ; ; loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size image_1 1 1.22e-6 image_1 2 1.22e-6 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_element_size.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_element_size.array_id' _item.category_id array_element_size _item.mandatory_code implicit _item_type.code code save_ save__array_element_size.index _item_description.description ; This item is a pointer to _array_structure_list.index in the ARRAY_STRUCTURE_LIST category. ; _item.name '_array_element_size.index' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.size _item_description.description ; The size in metres of an image element in this dimension. This supposes that the elements are arranged on a regular grid. ; _item.name '_array_element_size.size' _item.category_id array_element_size _item.mandatory_code yes _item_type.code float _item_units.code 'metres' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__array_element_size.variant _item_description.description ; The value of _array_element_size.variant gives the variant to which the given array_element_size row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_array_element_size.variant' _item.category_id array_element_size _item.mandatory_code no _item_type.code code save_ ##################### # ARRAY_INTENSITIES # ##################### save_ARRAY_INTENSITIES _category.description ; Data items in the ARRAY_INTENSITIES category record the information required to recover the intensity data from the set of data values stored in the ARRAY_DATA category. The detector may have a complex relationship between the raw intensity values and the number of incident photons. In most cases, the number stored in the final array will have a simple linear relationship to the actual number of incident photons, given by _array_intensities.gain. If raw, uncorrected values are presented (e.g. for calibration experiments), the value of _array_intensities.linearity will be 'raw' and _array_intensities.gain will not be used. ; _category.id array_intensities _category.mandatory_code no loop_ _category_key.name '_array_intensities.array_id' '_array_intensities.binary_id' '_array_intensities.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 ; ; loop_ _array_intensities.array_id _array_intensities.linearity _array_intensities.gain _array_intensities.overload _array_intensities.undefined_value _array_intensities.pixel_fast_bin_size _array_intensities.pixel_slow_bin_size _array_intensities.pixel_binning_method image_1 linear 1.2 655535 0 2 2 hardware ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_intensities.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_intensities.array_id' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code code save_ save__array_intensities.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_array_intensities.binary_id' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code int save_ save__array_intensities.gain _item_description.description ; Detector 'gain'. The factor by which linearized intensity count values should be divided to produce true photon counts. ; _item.name '_array_intensities.gain' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain_esd' 'associated_value' save_ save__array_intensities.gain_esd _item_description.description ; The estimated standard deviation in detector 'gain'. ; _item.name '_array_intensities.gain_esd' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain' 'associated_esd' save_ save__array_intensities.linearity _item_description.description ; The intensity linearity scaling method used to convert from the raw intensity to the stored element value: 'linear' is linear. 'offset' means that the value defined by _array_intensities.offset should be added to each element value. 'scaling' means that the value defined by _array_intensities.scaling should be multiplied with each element value. 'scaling_offset' is the combination of the two previous cases, with the scale factor applied before the offset value. 'sqrt_scaled' means that the square root of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and squaring the result. 'logarithmic_scaled' means that the logarithm base 10 of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and calculating 10 to the power of this number. 'raw' means that the data are a set of raw values straight from the detector. ; _item.name '_array_intensities.linearity' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'linear' . 'offset' ; The value defined by _array_intensities.offset should be added to each element value. ; 'scaling' ; The value defined by _array_intensities.scaling should be multiplied with each element value. ; 'scaling_offset' ; The combination of the scaling and offset with the scale factor applied before the offset value. ; 'sqrt_scaled' ; The square root of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and squaring the result. ; 'logarithmic_scaled' ; The logarithm base 10 of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and calculating 10 to the power of this number. ; 'raw' ; The array consists of raw values to which no corrections have been applied. While the handling of the data is similar to that given for 'linear' data with no offset, the meaning of the data differs in that the number of incident photons is not necessarily linearly related to the number of counts reported. This value is intended for use either in calibration experiments or to allow for handling more complex data-fitting algorithms than are allowed for by this data item. ; save_ save__array_intensities.offset _item_description.description ; Offset value to add to array element values in the manner described by the item _array_intensities.linearity. ; _item.name '_array_intensities.offset' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.overload _item_description.description ; The saturation intensity level for this data array. ; _item.name '_array_intensities.overload' _item.category_id array_intensities _item.mandatory_code no _item_type.code float _item_units.code 'counts' save_ save__array_intensities.pixel_fast_bin_size _item_description.description ; The value of _array_intensities.pixel_fast_bin_size specifies the number of pixels that compose one element in the direction of the most rapidly varying array dimension. Typical values are 1, 2, 4 or 8. When there is 1 pixel per array element in both directions, the value given for _array_intensities.pixel_binning_method normally should be 'none'. It is specified as a float to allow for binning algorithms that create array elements that are not integer multiples of the detector pixel size. ; _item.name '_array_intensities.pixel_fast_bin_size' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code float _item_default.value 1. loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'pixels_per_element' save_ save__array_intensities.pixel_slow_bin_size _item_description.description ; The value of _array_intensities.pixel_slow_bin_size specifies the number of pixels that compose one element in the direction of the second most rapidly varying array dimension. Typical values are 1, 2, 4 or 8. When there is 1 pixel per array element in both directions, the value given for _array_intensities.pixel_binning_method normally should be 'none'. It is specified as a float to allow for binning algorithms that create array elements that are not integer multiples of the detector pixel size. ; _item.name '_array_intensities.pixel_slow_bin_size' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code float _item_default.value 1. loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'pixels_per_element' save_ save__array_intensities.pixel_binning_method _item_description.description ; The value of _array_intensities.pixel_binning_method specifies the method used to derive array elements from multiple pixels. ; _item.name '_array_intensities.pixel_binning_method' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'hardware' ; The element intensities were derived from the raw data of one or more pixels by used of hardware in the detector, e.g. by use of shift registers in a CCD to combine pixels into super-pixels. ; 'software' ; The element intensities were derived from the raw data of more than one pixel by use of software. ; 'combined' ; The element intensities were derived from the raw data of more than one pixel by use of both hardware and software, as when hardware binning is used in one direction and software in the other. ; 'none' ; In the both directions, the data has not been binned. The number of pixels is equal to the number of elements. When the value of _array_intensities.pixel_binning_method is 'none' the values of _array_intensities.pixel_fast_bin_size and _array_intensities.pixel_slow_bin_size both must be 1. ; 'unspecified' ; The method used to derive element intensities is not specified. ; _item_default.value 'unspecified' save_ save__array_intensities.scaling _item_description.description ; Multiplicative scaling value to be applied to array data in the manner described by item _array_intensities.linearity. ; _item.name '_array_intensities.scaling' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.undefined_value _item_description.description ; A value to be substituted for undefined values in the data array. ; _item.name '_array_intensities.undefined_value' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.variant _item_description.description ; The value of _array_intensities.variant gives the variant to which the given array_intensities row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_array_intensities.variant' _item.category_id array_intensities _item.mandatory_code no _item_type.code code save_ ################### # ARRAY_STRUCTURE # ################### save_ARRAY_STRUCTURE _category.description ; Data items in the ARRAY_STRUCTURE category record the organization and encoding of array data that may be stored in the ARRAY_DATA category. ; _category.id array_structure _category.mandatory_code no loop_ _category_key.name '_array_structure.id' '_array_structure.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order image_1 "unsigned 16-bit integer" none little_endian ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure.byte_order _item_description.description ; The order of bytes for integer values which require more than 1 byte. (IBM-PC's and compatibles and DEC VAXs use low-byte-first ordered integers, whereas Hewlett Packard 700 series, Sun-4 and Silicon Graphics use high-byte-first ordered integers. DEC Alphas can produce/use either depending on a compiler switch.) ; _item.name '_array_structure.byte_order' _item.category_id array_structure _item.mandatory_code yes _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail 'big_endian' ; The first byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; 'little_endian' ; The last byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; save_ save__array_structure.compression_type _item_description.description ; Type of data-compression method used to compress the array data. ; _item.name '_array_structure.compression_type' _item.category_id array_structure _item.mandatory_code no _item_type.code ucode _item_default.value 'none' loop_ _item_enumeration.value _item_enumeration.detail 'byte_offset' ; Using the 'byte_offset' compression scheme as per A. Hammersley and the CBFlib manual, section 3.3.3 ; 'canonical' ; Using the 'canonical' compression scheme (International Tables for Crystallography Volume G, Section 5.6.3.1) and CBFlib manual section 3.3.1 ; 'none' ; Data are stored in normal format as defined by _array_structure.encoding_type and _array_structure.byte_order. ; 'packed' ; Using the 'packed' compression scheme, a CCP4-style packing as per J. P. Abrahams pack_c.c and CBFlib manual, section 3.3.2. ; 'packed_v2' ; Using the 'packed' compression scheme, version 2, as per J. P. Abrahams pack_c.c and CBFlib manual, section 3.3.2. ; save_ save__array_structure.compression_type_flag _item_description.description ; Flags modifying the type of data-compression method used to compress the arraydata. ; _item.name '_array_structure.compression_type_flag' _item.category_id array_structure _item.mandatory_code no _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail 'uncorrelated_sections' ; When applying packed or packed_v2 compression on an array with uncorrelated sections, do not average in points from the prior section. ; 'flat' ; When applying packed or packed_v2 compression on an array with treat the entire image as a single line set the maximum number of bits for an offset to 65 bits. The flag is included for compatibility with software prior to CBFlib_0.7.7, and should not be used for new data sets. ; save_ save__array_structure.encoding_type _item_description.description ; Data encoding of a single element of array data. The type 'unsigned 1-bit integer' is used for packed Booleans arrays for masks. Each element of the array corresponds to a single bit packed in unsigned 8-bit data. In several cases, the IEEE format is referenced. See IEEE Standard 754-1985 (IEEE, 1985). Ref: IEEE (1985). IEEE Standard for Binary Floating-Point Arithmetic. ANSI/IEEE Std 754-1985. New York: Institute of Electrical and Electronics Engineers. ; _item.name '_array_structure.encoding_type' _item.category_id array_structure _item.mandatory_code yes _item_type.code uline loop_ _item_enumeration.value 'unsigned 1-bit integer' 'unsigned 8-bit integer' 'signed 8-bit integer' 'unsigned 16-bit integer' 'signed 16-bit integer' 'unsigned 32-bit integer' 'signed 32-bit integer' 'signed 32-bit real IEEE' 'signed 64-bit real IEEE' 'signed 32-bit complex IEEE' save_ save__array_structure.id _item_description.description ; The value of _array_structure.id must uniquely identify each item of array data. This item has been made implicit and given a default value of 1 as a convenience in writing miniCBF files. Normally an explicit name with useful content should be used. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure.id' array_structure implicit '_array_data.array_id' array_data implicit '_array_structure_list.array_id' array_structure_list implicit '_array_intensities.array_id' array_intensities implicit '_diffrn_data_frame.array_id' diffrn_data_frame implicit _item_default.value 1 _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_data.array_id' '_array_structure.id' '_array_structure_list.array_id' '_array_structure.id' '_array_intensities.array_id' '_array_structure.id' '_diffrn_data_frame.array_id' '_array_structure.id' save_ save__array_structure.variant _item_description.description ; The value of _array_structure.variant gives the variant to which the given array_structure row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_array_structure.variant' _item.category_id array_structure _item.mandatory_code no _item_type.code code save_ ######################## # ARRAY_STRUCTURE_LIST # ######################## save_ARRAY_STRUCTURE_LIST _category.description ; Data items in the ARRAY_STRUCTURE_LIST category record the size and organization of each array dimension. The relationship to physical axes may be given. ; _category.id array_structure_list _category.mandatory_code no loop_ _category_key.name '_array_structure_list.array_id' '_array_structure_list.index' '_array_structure_list.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - An image array of 1300 x 1200 elements. The raster order of the image is left to right (increasing) in the first dimension and bottom to top (decreasing) in the second dimension. ; ; loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id image_1 1 1300 1 increasing ELEMENT_X image_1 2 1200 2 decreasing ELEMENY_Y ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure_list.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_structure_list.array_id' _item.category_id array_structure_list _item.mandatory_code implicit _item_type.code code save_ save__array_structure_list.axis_set_id _item_description.description ; This is a descriptor for the physical axis or set of axes corresponding to an array index. This data item is related to the axes of the detector itself given in DIFFRN_DETECTOR_AXIS, but usually differs in that the axes in this category are the axes of the coordinate system of reported data points, while the axes in DIFFRN_DETECTOR_AXIS are the physical axes of the detector describing the 'poise' of the detector as an overall physical object. If there is only one axis in the set, the identifier of that axis should be used as the identifier of the set. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.axis_set_id' array_structure_list yes '_array_structure_list_axis.axis_set_id' array_structure_list_axis implicit _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_structure_list_axis.axis_set_id' '_array_structure_list.axis_set_id' save_ save__array_structure_list.dimension _item_description.description ; The number of elements stored in the array structure in this dimension. ; _item.name '_array_structure_list.dimension' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.direction _item_description.description ; Identifies the direction in which this array index changes. ; _item.name '_array_structure_list.direction' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'increasing' ; Indicates the index changes from 1 to the maximum dimension. ; 'decreasing' ; Indicates the index changes from the maximum dimension to 1. ; save_ save__array_structure_list.index _item_description.description ; Identifies the one-based index of the row or column in the array structure. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.index' array_structure_list yes '_array_structure_list.precedence' array_structure_list yes '_array_element_size.index' array_element_size yes _item_type.code int loop_ _item_linked.child_name _item_linked.parent_name '_array_element_size.index' '_array_structure_list.index' loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.precedence _item_description.description ; Identifies the rank order in which this array index changes with respect to other array indices. The precedence of 1 indicates the index which changes fastest. ; _item.name '_array_structure_list.precedence' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.variant _item_description.description ; The value of _array_structure_list.variant gives the variant to which the given array_structure_list row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_array_structure_list.variant' _item.category_id array_structure_list _item.mandatory_code no _item_type.code code save_ ############################# # ARRAY_STRUCTURE_LIST_AXIS # ############################# save_ARRAY_STRUCTURE_LIST_AXIS _category.description ; Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe the physical settings of sets of axes for the centres of pixels that correspond to data points described in the ARRAY_STRUCTURE_LIST category. In the simplest cases, the physical increments of a single axis correspond to the increments of a single array index. More complex organizations, e.g. spiral scans, may require coupled motions along multiple axes. Note that a spiral scan uses two coupled axes: one for the angular direction and one for the radial direction. This differs from a cylindrical scan for which the two axes are not coupled into one set. ; _category.id array_structure_list_axis _category.mandatory_code no loop_ _category_key.name '_array_structure_list_axis.axis_set_id' '_array_structure_list_axis.axis_id' '_array_structure_list_axis.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' save_ save__array_structure_list_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes in the set of axes for which settings are being specified. Multiple axes may be specified for the same value of _array_structure_list_axis.axis_set_id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_array_structure_list_axis.axis_id' _item.category_id array_structure_list_axis _item.mandatory_code yes _item_type.code code save_ save__array_structure_list_axis.axis_set_id _item_description.description ; The value of this data item is the identifier of the set of axes for which axis settings are being specified. Multiple axes may be specified for the same value of _array_structure_list_axis.axis_set_id. This item is a pointer to _array_structure_list.axis_set_id in the ARRAY_STRUCTURE_LIST category. If this item is not specified, it defaults to the corresponding axis identifier. ; _item.name '_array_structure_list_axis.axis_set_id' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_type.code code save_ save__array_structure_list_axis.angle _item_description.description ; The setting of the specified axis in degrees for the first data point of the array index with the corresponding value of _array_structure_list.axis_set_id. If the index is specified as 'increasing', this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing', this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.angle' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.angle_increment _item_description.description ; The pixel-centre-to-pixel-centre increment in the angular setting of the specified axis in degrees. This is not meaningful in the case of 'constant velocity' spiral scans and should not be specified for this case. See _array_structure_list_axis.angular_pitch. ; _item.name '_array_structure_list_axis.angle_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for the first data point of the array index with the corresponding value of _array_structure_list.axis_set_id. If the index is specified as 'increasing', this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing', this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.displacement' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.fract_displacement _item_description.description ; The setting of the specified axis as a decimal fraction of the axis unit vector for the first data point of the array index with the corresponding value of _array_structure_list.axis_set_id. If the index is specified as 'increasing', this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing', this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.fract_displacement' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float save_ save__array_structure_list_axis.displacement_increment _item_description.description ; The pixel-centre-to-pixel-centre increment for the displacement setting of the specified axis in millimetres. ; _item.name '_array_structure_list_axis.displacement_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.fract_displacement_increment _item_description.description ; The pixel-centre-to-pixel-centre increment for the displacement setting of the specified axis as a decimal fraction of the axis unit vector. ; _item.name '_array_structure_list_axis.fract_displacement_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.angular_pitch _item_description.description ; The pixel-centre-to-pixel-centre distance for a one-step change in the setting of the specified axis in millimetres. This is meaningful only for 'constant velocity' spiral scans or for uncoupled angular scans at a constant radius (cylindrical scans) and should not be specified for cases in which the angle between pixels (rather than the distance between pixels) is uniform. See _array_structure_list_axis.angle_increment. ; _item.name '_array_structure_list_axis.angular_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.radial_pitch _item_description.description ; The radial distance from one 'cylinder' of pixels to the next in millimetres. If the scan is a 'constant velocity' scan with differing angular displacements between pixels, the value of this item may differ significantly from the value of _array_structure_list_axis.displacement_increment. ; _item.name '_array_structure_list_axis.radial_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.reference_angle _item_description.description ; The value of _array_structure_list_axis.reference_angle specifies the setting of the angle of this axis used for determining a reference beam center and a reference detector distance. It is normally expected to be identical to the value of _array_structure_list.angle. ; _item.name '_array_structure_list_axis.reference_angle' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.reference_displacement _item_description.description ; The value of _array_structure_list_axis.reference_displacement specifies the setting of the displacement of this axis used for determining a reference beam center and a reference detector distance. It is normally expected to be identical to the value of _array_structure_list.displacement. ; _item.name '_array_structure_list_axis.reference_displacement' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.variant _item_description.description ; The value of _array_structure_list_axis.variant gives the variant to which the given array_structure_list_axis row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_array_structure_list_axis.variant' _item.category_id array_structure_list_axis _item.mandatory_code no _item_type.code code save_ ######## # AXIS # ######## save_AXIS _category.description ; Data items in the AXIS category record the information required to describe the various goniometer, detector, source and other axes needed to specify a data collection or the axes defining the coordinate system of an image. The location of each axis is specified by two vectors: the axis itself, given by a unit vector in the direction of the axis, and an offset to the base of the unit vector. The vectors defining an axis are referenced to an appropriate coordinate system. The axis vector, itself, is a dimensionless unit vector. Where meaningful, the offset vector is given in millimetres. In coordinate systems not measured in metres, the offset is not specified and is taken as zero. The available coordinate systems are: The imgCIF standard laboratory coordinate system The direct lattice (fractional atomic coordinates) The orthogonal Cartesian coordinate system (real space) The reciprocal lattice An abstract orthogonal Cartesian coordinate frame For consistency in this discussion, we call the three coordinate system axes X, Y and Z. This is appropriate for the imgCIF standard laboratory coordinate system, and last two Cartesian coordinate systems, but for the direct lattice, X corresponds to a, Y to b and Z to c, while for the reciprocal lattice, X corresponds to a*, Y to b* and Z to c*. For purposes of visualization, all the coordinate systems are taken as right-handed, i.e., using the convention that the extended thumb of a right hand could point along the first (X) axis, the straightened pointer finger could point along the second (Y) axis and the middle finger folded inward could point along the third (Z) axis. THE IMGCIF STANDARD LABORATORY COORDINATE SYSTEM The imgCIF standard laboratory coordinate system is a right-handed orthogonal coordinate similar to the MOSFLM coordinate system, but imgCIF puts Z along the X-ray beam, rather than putting X along the X-ray beam as in MOSFLM. The vectors for the imgCIF standard laboratory coordinate system form a right-handed Cartesian coordinate system with its origin in the sample or specimen. The origin of the axis system should, if possible, be defined in terms of mechanically stable axes to be be both in the sample and in the beam. If the sample goniometer or other sample positioner has two axes the intersection of which defines a unique point at which the sample should be mounted to be bathed by the beam, that will be the origin of the axis system. If no such point is defined, then the midpoint of the line of intersection between the sample and the center of the beam will define the origin. For this definition the sample positioning system will be set at its initial reference position for the experiment. | Y (to complete right-handed system) | | | | | |________________X / principal goniometer axis / / / / /Z (to source) Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from the sample or specimen along the principal axis of the goniometer or sample positioning system if the sample positioning system has an axis that intersects the origin and which form an angle of more than 22.5 degrees with the beam axis. Axis 2 (Y): The Y-axis completes an orthogonal right-handed system defined by the X-axis and the Z-axis (see below). Axis 3 (Z): The Z-axis is derived from the source axis which goes from the sample to the source. The Z-axis is the component of the source axis in the direction of the source orthogonal to the X-axis in the plane defined by the X-axis and the source axis. If the conditions for the X-axis can be met, the coordinate system will be based on the goniometer or other sample positioning system and the beam and not on the orientation of the detector, gravity etc. The vectors necessary to specify all other axes are given by sets of three components in the order (X, Y, Z). If the axis involved is a rotation axis, it is right-handed, i.e. as one views the object to be rotated from the origin (the tail) of the unit vector, the rotation is clockwise. If a translation axis is specified, the direction of the unit vector specifies the sense of positive translation. Note: This choice of coordinate system is similar to but significantly different from the choice in MOSFLM (Leslie & Powell, 2004). In MOSFLM, X is along the X-ray beam (the CBF/imgCIF Z axis) and Z is along the rotation axis. In some experimental techniques, there is no goniometer or the principal axis of the goniometer is at a small acute angle with respect to the source axis. In such cases, other reference axes are needed to define a useful coordinate system. The order of priority in defining directions in such cases is to use the detector, then gravity, then north. If the X-axis cannot be defined as above, then the direction (not the origin) of the X-axis should be parallel to the axis of the primary detector element corresponding to the most rapidly varying dimension of that detector element's data array, with its positive sense corresponding to increasing values of the index for that dimension. If the detector is such that such a direction cannot be defined (as with a point detector) or that direction forms an angle of less than 22.5 degrees with respect to the source axis, then the X-axis should be chosen so that if the Y-axis is chosen in the direction of gravity, and the Z-axis is chosen to be along the source axis, a right-handed orthogonal coordinate system is chosen. In the case of a vertical source axis, as a last resort, the X-axis should be chosen to point North. All rotations are given in degrees and all translations are given in mm. Axes may be dependent on one another. The X-axis is the only goniometer axis the direction of which is strictly connected to the hardware. All other axes are specified by the positions they would assume when the axes upon which they depend are at their zero points. When specifying detector axes, the axis is given to the beam centre. The location of the beam centre on the detector should be given in the DIFFRN_DETECTOR category in distortion-corrected millimetres from the (0,0) corner of the detector. It should be noted that many different origins arise in the definition of an experiment. In particular, as noted above, it is necessary to specify the location of the beam centre on the detector in terms of the origin of the detector, which is, of course, not coincident with the centre of the sample. The unit cell, reciprocal cell and crystallographic orthogonal Cartesian coordinate system are defined by the CELL and the matrices in the ATOM_SITES category. THE DIRECT LATTICE (FRACTIONAL COORDINATES) The direct lattice coordinate system is a system of fractional coordinates aligned to the crystal, rather than to the laboratory. This is a natural coordinate system for maps and atomic coordinates. It is the simplest coordinate system in which to apply symmetry. The axes are determined by the cell edges, and are not necessarily othogonal. This coordinate system is not uniquely defined and depends on the cell parameters in the CELL category and the settings chosen to index the crystal. Molecules in a crystal studied by X-ray diffracraction are organized into a repeating regular array of unit cells. Each unit cell is defined by three vectors, a, b and c. To quote from Drenth, "The choice of the unit cell is not unique and therefore, guidelines have been established for selecting the standard basis vectors and the origin. They are based on symmetry and metric considerations: "(1) The axial system should be right handed. (2) The basis vectors should coincide as much as possible with directions of highest symmetry." (3) The cell taken should be the smallest one that satisfies condition (2) (4) Of all the lattice vectors, none is shorter than a. (5) Of those not directed along a, none is shorter than b. (6) Of those not lying in the ab plane, none is shorter than c. (7) The three angles between the basis vectors a, b and c are either all acute (<90\%) or all obtuse (>=90\%)." These rules do not produce a unique result that is stable under the assumption of experimental errors, and the the resulting cell may not be primitive. In this coordinate system, the vector (.5, .5, .5) is in the middle of the given unit cell. Grid coordinates are an important variation on fractional coordinates used when working with maps. In imgCIF, the conversion from fractional to grid coordinates is implicit in the array indexing specified by _array_structure_list.dimension. Note that this implicit grid-coordinate scheme is 1-based, not zero-based, i.e. the origin of the cell for axes along the cell edges with no specified _array_structure_list_axis.displacement will have grid coordinates of (1,1,1), i.e. array indices of (1,1,1). THE ORTHOGONAL CARTESIAN COORDINATE SYSTEM (REAL SPACE) The orthogonal Cartesian coordinate system is a transformation of the direct lattice to the actual physical coordinates of atoms in space. It is similar to the laboratory coordinate system, but is anchored to and moves with the crystal, rather than being schored to the laboratory. The transformation from fractional to orthogonal cartesian coordinates is given by the _atom_sites.Cartn_transf_matrix[i][j] and _atom_sites.Cartn_transf_vector[i] tags. A common choice for the matrix of the transformation is given in the 1992 PDB format document | a b cos(\g) c cos(\b) | | 0 b sin(\g) c (cos(\a) - cos(\b)cos(\g))/sin(\g) | | 0 0 V/(a b sin(\g)) | This is a convenient coordinate system in which to do fitting of models to maps and in which to understand the chemistry of a molecule. THE RECIPROCAL LATTICE The reciprocal lattice coordinate system is used for diffraction intensitities. It is based on the reciprocal cell, the dual of the cell, in which reciprocal cell edges are derived from direct cell faces: a* = bc sin(\a)/V b* = ac sin(\b)/V c* = ab sin(\g)/V cos(\a*) = (cos(\b) cos(\g) - cos(\a))/(sin(\b) sin(\g)) cos(\b*) = (cos(\a) cos(\g) - cos(\b))/(sin(\a) sin(\g)) cos(\g*) = (cos(\a) cos(\b) - cos(\g))/(sin(\a) sin(\b)) V = abc SQRT(1 - cos(\a)^2^ - cos(\b)^2^ - cos(\g)^2^ + 2 cos(\a) cos(\b) cos(\g) ) In this form the dimensions of the reciprocal lattice are in reciprocal \%Angstroms (\%A^-1^). A dimensionless form can be obtained by multiplying by the wavelength. Reflections are commonly indexed against this coordinate system as (h, k, l) triples. References: Drenth, J., "Introduction to basic crystallography." chapter 2.1 in Rossmann, M. G. and Arnold, E. "Crystallography of biological macromolecules", Volume F of the IUCr's "International tables for crystallography", Kluwer, Dordrecht 2001, pp 44 -- 63 Leslie, A. G. W. and Powell, H. (2004). MOSFLM v6.11. MRC Laboratory of Molecular Biology, Hills Road, Cambridge, England. http://www.CCP4.ac.uk/dist/X-windows/Mosflm/. Stout, G. H. and Jensen, L. H., "X-ray structure determination", 2nd ed., Wiley, New York, 1989, 453 pp. __, "PROTEIN DATA BANK ATOMIC COORDINATE AND BIBLIOGRAPHIC ENTRY FORMAT DESCRIPTION," Brookhaven National Laboratory, February 1992. ; _category.id axis _category.mandatory_code no loop_ _category_key.name '_axis.id' '_axis.equipment' '_axis.variant' loop_ _category_group.id 'inclusive_group' 'axis_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows the axis specification of the axes of a kappa- geometry goniometer [see Stout, G. H. & Jensen, L. H. (1989). X-ray structure determination. A practical guide, 2nd ed. p. 134. New York: Wiley Interscience]. There are three axes specified, and no offsets. The outermost axis, omega, is pointed along the X axis. The next innermost axis, kappa, is at a 50 degree angle to the X axis, pointed away from the source. The innermost axis, phi, aligns with the X axis when omega and phi are at their zero points. If T-omega, T-kappa and T-phi are the transformation matrices derived from the axis settings, the complete transformation would be: X' = (T-omega) (T-kappa) (T-phi) X ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] omega rotation goniometer . 1 0 0 kappa rotation goniometer omega -.64279 0 -.76604 phi rotation goniometer kappa 1 0 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - This example shows the axis specification of the axes of a detector, source and gravity. The order has been changed as a reminder that the ordering of presentation of tokens is not significant. The centre of rotation of the detector has been taken to be 68 millimetres in the direction away from the source. ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] source . source . 0 0 1 . . . gravity . gravity . 0 -1 0 . . . tranz translation detector rotz 0 0 1 0 0 -68 twotheta rotation detector . 1 0 0 . . . roty rotation detector twotheta 0 1 0 0 0 -68 rotz rotation detector roty 0 0 1 0 0 -68 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 3 - This example show the axis specification of the axes for a map, using fractional coordinates. Each cell edge has been divided into a grid of 50 divisions in the ARRAY_STRUCTURE_LIST_AXIS category. The map is using only the first octant of the grid in the ARRAY_STRUCTURE_LIST category. The fastest changing axis is the gris along A, then along B, and the slowest is along C. The map sampling is being done in the middle of each grid division ; ; loop_ _axis.id _axis.system _axis.vector[1] _axis.vector[2] _axis.vector[3] CELL_A_AXIS fractional 1 0 0 CELL_B_AXIS fractional 0 1 0 CELL_C_AXIS fractional 0 0 1 loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_id MAP 1 25 1 increasing CELL_A_AXIS MAP 1 25 2 increasing CELL_B_AXIS MAP 1 25 3 increasing CELL_C_AXIS loop_ _array_structure_list_axis.axis_id _array_structure_list_axis.fract_displacement _array_structure_list_axis.fract_displacement_increment CELL_A_AXIS 0.01 0.02 CELL_B_AXIS 0.01 0.02 CELL_C_AXIS 0.01 0.02 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 4 - This example show the axis specification of the axes for a map, this time as orthogonal \%Angstroms, using the same coordinate system as for the atomic coordinates. The map is sampling every 1.5 \%Angstroms (1.5e-7 millimeters) in a map segment 37.5 \%Angstroms on a side. ; ; loop_ _axis.id _axis.system _axis.vector[1] _axis.vector[2] _axis.vector[3] X orthogonal 1 0 0 Y orthogonal 0 1 0 Z orthogonal 0 0 1 loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_id MAP 1 25 1 increasing X MAP 2 25 2 increasing Y MAP 3 25 3 increasing Z loop_ _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment X 7.5e-8 1.5e-7 Y 7.5e-8 1.5e-7 Z 7.5e-8 1.5e-7 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__axis.depends_on _item_description.description ; The value of _axis.depends_on specifies the next outermost axis upon which this axis depends. This item is a pointer to _axis.id in the same category. ; _item.name '_axis.depends_on' _item.category_id axis _item.mandatory_code no save_ save__axis.equipment _item_description.description ; The value of _axis.equipment specifies the type of equipment using the axis: 'goniometer', 'detector', 'gravity', 'source' or 'general'. ; _item.name '_axis.equipment' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail goniometer 'equipment used to orient or position samples' detector 'equipment used to detect reflections' general 'equipment used for general purposes' gravity 'axis specifying the downward direction' source 'axis specifying the direction sample to source' save_ save__axis.offset[1] _item_description.description ; The [1] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[2] _item_description.description ; The [2] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[3] _item_description.description ; The [3] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.id _item_description.description ; The value of _axis.id must uniquely identify each axis relevant to the experiment. Note that multiple pieces of equipment may share the same axis (e.g. a twotheta arm), so the category key for AXIS also includes the equipment. ; loop_ _item.name _item.category_id _item.mandatory_code '_axis.id' axis yes '_array_structure_list_axis.axis_id' array_structure_list_axis yes '_diffrn_detector_axis.axis_id' diffrn_detector_axis yes '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes '_diffrn_scan_axis.axis_id' diffrn_scan_axis yes '_diffrn_scan_frame_axis.axis_id' diffrn_scan_frame_axis yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_axis.depends_on' '_axis.id' '_array_structure_list_axis.axis_id' '_axis.id' '_diffrn_detector_axis.axis_id' '_axis.id' '_diffrn_measurement_axis.axis_id' '_axis.id' '_diffrn_scan_axis.axis_id' '_axis.id' '_diffrn_scan_frame_axis.axis_id' '_axis.id' save_ save__axis.system _item_description.description ; The value of _axis.system specifies the coordinate system used to define the axis: 'laboratory', 'direct', 'orthogonal', 'reciprocal' or 'abstract'. ; _item.name '_axis.system' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value laboratory loop_ _item_enumeration.value _item_enumeration.detail laboratory ; the axis is referenced to the imgCIF standard laboratory Cartesian coordinate system ; direct ; the axis is referenced to the direct lattice ; orthogonal ; the axis is referenced to the cell Cartesian orthogonal coordinates ; reciprocal ; the axis is referenced to the reciprocal lattice ; abstract ; the axis is referenced to abstract Cartesian cooridinate system ; save_ save__axis.type _item_description.description ; The value of _axis.type specifies the type of axis: 'rotation' or 'translation' (or 'general' when the type is not relevant, as for gravity). ; _item.name '_axis.type' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail rotation 'right-handed axis of rotation' translation 'translation in the direction of the axis' general 'axis for which the type is not relevant' save_ save__axis.vector[1] _item_description.description ; The [1] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[2] _item_description.description ; The [2] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[3] _item_description.description ; The [3] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.variant _item_description.description ; The value of _axis.variant gives the variant to which the given axis row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_axis.variant' _item.category_id axis _item.mandatory_code no _item_type.code code save_ ##################### # DIFFRN_DATA_FRAME # ##################### save_DIFFRN_DATA_FRAME _category.description ; Data items in the DIFFRN_DATA_FRAME category record the details about each frame of data. The items in this category were previously in a DIFFRN_FRAME_DATA category, which is now deprecated. The items from the old category are provided as aliases but should not be used for new work. ; _category.id diffrn_data_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_data_frame.id' '_diffrn_data_frame.detector_element_id' '_diffrn_data_frame.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A frame containing data from 4 frame elements. Each frame element has a common array configuration 'array_1' described in ARRAY_STRUCTURE and related categories. The data for each detector element are stored in four groups of binary data in the ARRAY_DATA category, linked by the array_id and binary_id. ; ; loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id frame_1 d1_ccd_1 array_1 1 frame_1 d1_ccd_2 array_1 2 frame_1 d1_ccd_3 array_1 3 frame_1 d1_ccd_4 array_1 4 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_data_frame.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_diffrn_data_frame.array_id' _item.category_id diffrn_data_frame _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_frame_data.array_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_diffrn_data_frame.binary_id' _item.category_id diffrn_data_frame _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_frame_data.binary_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code int save_ save__diffrn_data_frame.center_fast _item_description.description ; The value of _diffrn_data_frame.center_fast is the fast index axis beam center position relative to the detector element face in the units specified in the data item '_diffrn_data_frame.center_units' along the fast axis of the detector from the center of the first pixel to the point at which the Z-axis (which should be colinear with the beam) intersects the face of the detector, if in fact is does. At the time of the measurement the current setting of detector positioner given frame are used. It is important to note that for measurements in millimetres, the sense of the axis is used, rather than the sign of the pixel-to-pixel increments. ; _item.name '_diffrn_data_frame.center_fast' _item.category_id diffrn_data_frame _item.mandatory_code no _item_type.code float save_ save__diffrn_data_frame.center_slow _item_description.description ; The value of _diffrn_data_frame.center_slow is the slow index axis beam center position relative to the detector element face in the units specified in the data item '_diffrn_data_frame.center_units' along the slow axis of the detector from the center of the first pixel to the point at which the Z-axis (which should be colinear with the beam) intersects the face of the detector, if in fact is does. At the time of the measurement the current setting of detector positioner given frame are used. It is important to note that the sense of the axis is used, rather than the sign of the pixel-to-pixel increments. ; _item.name '_diffrn_data_frame.center_slow' _item.category_id diffrn_data_frame _item.mandatory_code no _item_type.code float save_ save__diffrn_data_frame.center_units _item_description.description ; The value of _diffrn_data_frame.center_units specifies the units in which the values of '_diffrn_data_frame.center_fast' and '_diffrn_data_frame.center_slow' are presented. The default is 'mm' for millimetres. The alternatives are 'pixels' and 'bins'. In all cases the center distances are measured from the center of the first pixel, i.e. in a 2x2 binning, the measuring origin is offset from the centers of the bins by one half pixel towards the first pixel. If 'bins' is specified, the data in '_array_intensities.pixel_fast_bin_size', '_array_intensities.pixel_slow_bin_size', and '_array_intensities.pixel_binning_method' is used to define the binning scheme. ; _item.name '_diffrn_data_frame.center_units' _item.category_id diffrn_data_frame _item.mandatory_code no _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail mm 'millimetres' pixels 'detector pixels' bins 'detector bins' save_ save__diffrn_data_frame.detector_element_id _item_description.description ; This item is a pointer to _diffrn_detector_element.id in the DIFFRN_DETECTOR_ELEMENT category. ; _item.name '_diffrn_data_frame.detector_element_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.detector_element_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.id _item_description.description ; The value of _diffrn_data_frame.id must uniquely identify each complete frame of data. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_data_frame.id' diffrn_data_frame yes '_diffrn_refln.frame_id' diffrn_refln yes '_diffrn_scan.frame_id_start' diffrn_scan yes '_diffrn_scan.frame_id_end' diffrn_scan yes '_diffrn_scan_frame.frame_id' diffrn_scan_frame yes '_diffrn_scan_frame_axis.frame_id' diffrn_scan_frame_axis yes '_diffrn_scan_frame_monitor.frame_id' diffrn_scan_frame_monitor implicit _item_aliases.alias_name '_diffrn_frame_data.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_refln.frame_id' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_start' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_end' '_diffrn_data_frame.id' '_diffrn_scan_frame.frame_id' '_diffrn_data_frame.id' '_diffrn_scan_frame_axis.frame_id' '_diffrn_data_frame.id' '_diffrn_scan_frame_monitor.frame_id' '_diffrn_data_frame.id' save_ save__diffrn_data_frame.details _item_description.description ; The value of _diffrn_data_frame.details should give a description of special aspects of each frame of data. This is an appropriate location in which to record information from vendor headers as presented in those headers, but it should never be used as a substitute for providing the fully parsed information within the appropriate imgCIF/CBF categories. Normally, when a conversion from a miniCBF has been done the data from '_array_data.header_convention' should be transferred to this data item and '_array_data.header_convention' should be removed. ; _item.name '_diffrn_data_frame.details' _item.category_id diffrn_data_frame _item.mandatory_code no _item_aliases.alias_name '_diffrn_frame_data.details' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.4 _item_type.code text loop_ _item_examples.case _item_examples.detail ; HEADER_BYTES = 512; DIM = 2; BYTE_ORDER = big_endian; TYPE = unsigned_short; SIZE1 = 3072; SIZE2 = 3072; PIXEL_SIZE = 0.102588; BIN = 2x2; DETECTOR_SN = 901; TIME = 29.945155; DISTANCE = 200.000000; PHI = 85.000000; OSC_START = 85.000000; OSC_RANGE = 1.000000; WAVELENGTH = 0.979381; BEAM_CENTER_X = 157.500000; BEAM_CENTER_Y = 157.500000; PIXEL SIZE = 0.102588; OSCILLATION RANGE = 1; EXPOSURE TIME = 29.9452; TWO THETA = 0; BEAM CENTRE = 157.5 157.5; ; ; Example of header information extracted from an ADSC Quantum 315 detector header by CBFlib_0.7.6. Image provided by Chris Nielsen of ADSC from a data collection at SSRL beamline 1-5. ; save_ save__diffrn_data_frame.variant _item_description.description ; The value of _diffrn_data_frame.variant gives the variant to which the given diffrn_data_frame row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_data_frame.variant' _item.category_id diffrn_data_frame _item.mandatory_code no _item_type.code code save_ ########################################################################## # The following is a restatement of the mmCIF DIFFRN_DETECTOR, # # DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for # # the CBF/imgCIF extensions # ########################################################################## ################### # DIFFRN_DETECTOR # ################### save_DIFFRN_DETECTOR _category.description ; Data items in the DIFFRN_DETECTOR category describe the detector used to measure the scattered radiation, including any analyser and post-sample collimation. ; _category.id diffrn_detector _category.mandatory_code no loop_ _category_key.name '_diffrn_detector.diffrn_id' '_diffrn_detector.id' '_diffrn_detector.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _diffrn_detector.diffrn_id 'd1' _diffrn_detector.detector 'multiwire' _diffrn_detector.type 'Siemens' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector.details _item_description.description ; A description of special aspects of the radiation detector. ; _item.name '_diffrn_detector.details' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'slow mode' save_ save__diffrn_detector.detector _item_description.description ; The general class of the radiation detector. ; _item.name '_diffrn_detector.detector' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector' cifdic.c91 1.0 '_diffrn_detector' cif_core.dic 2.0 _item_type.code text loop_ _item_examples.case 'photographic film' 'scintillation counter' 'CCD plate' 'BF~3~ counter' save_ save__diffrn_detector.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. The value of _diffrn.id uniquely defines a set of diffraction data. ; _item.name '_diffrn_detector.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector.dtime _item_description.description ; The deadtime in microseconds of the detector(s) used to measure the diffraction intensities. ; _item.name '_diffrn_detector.dtime' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector_dtime' cifdic.c91 1.0 '_diffrn_detector_dtime' cif_core.dic 2.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code microseconds save_ save__diffrn_detector.id _item_description.description ; The value of _diffrn_detector.id must uniquely identify each detector used to collect each diffraction data set. If the value of _diffrn_detector.id is not given, it is implicitly equal to the value of _diffrn_detector.diffrn_id. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector.id' diffrn_detector implicit '_diffrn_detector_axis.detector_id' diffrn_detector_axis yes '_diffrn_scan_frame_monitor.detector_id' _diffrn_scan_frame_monitor.detector_id yes loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_detector_axis.detector_id' '_diffrn_detector.id' '_diffrn_scan_frame_monitor.detector_id' '_diffrn_detector.id' _item_type.code code save_ save__diffrn_detector.number_of_axes _item_description.description ; The value of _diffrn_detector.number_of_axes gives the number of axes of the positioner for the detector identified by _diffrn_detector.id. The word 'positioner' is a general term used in instrumentation design for devices that are used to change the positions of portions of apparatus by linear translation, rotation or combinations of such motions. Axes which are used to provide a coordinate system for the face of an area detetctor should not be counted for this data item. The description of each axis should be provided by entries in DIFFRN_DETECTOR_AXIS. ; _item.name '_diffrn_detector.number_of_axes' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_detector.type _item_description.description ; The make, model or name of the detector device used. ; _item.name '_diffrn_detector.type' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__diffrn_detector.variant _item_description.description ; The value of _diffrn_detector.variant gives the variant to which the given diffrn_detector row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_detector.variant' _item.category_id diffrn_detector _item.mandatory_code no _item_type.code code save_ ######################## # DIFFRN_DETECTOR_AXIS # ######################## save_DIFFRN_DETECTOR_AXIS _category.description ; Data items in the DIFFRN_DETECTOR_AXIS category associate axes with detectors. ; _category.id diffrn_detector_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_axis.detector_id' '_diffrn_detector_axis.axis_id' '_diffrn_detector_axis.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_detector_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_detector_axis.axis_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_axis.detector_id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. This item was previously named _diffrn_detector_axis.id which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_detector_axis.detector_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_aliases.alias_name '_diffrn_detector_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_detector_axis.variant _item_description.description ; The value of _diffrn_detector_axis.variant gives the variant to which the given diffrn_detector_axis row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_detector_axis.variant' _item.category_id diffrn_detector_axis _item.mandatory_code no _item_type.code code save_ ########################### # DIFFRN_DETECTOR_ELEMENT # ########################### save_DIFFRN_DETECTOR_ELEMENT _category.description ; Data items in the DIFFRN_DETECTOR_ELEMENT category record the details about spatial layout and other characteristics of each element of a detector which may have multiple elements. In most cases, giving more detailed information in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS is preferable to simply providing the centre of the detector element. ; _category.id diffrn_detector_element _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_element.id' '_diffrn_detector_element.detector_id' '_diffrn_detector_element.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Detector d1 is composed of four CCD detector elements, each 200 mm by 200 mm, arranged in a square, in the pattern 1 2 * 3 4 Note that the beam centre is slightly displaced from each of the detector elements, just beyond the lower right corner of 1, the lower left corner of 2, the upper right corner of 3 and the upper left corner of 4. For each element, the detector face coordiate system, is assumed to have the fast axis running from left to right and the slow axis running from top to bottom with the origin at the top left corner. ; ; loop_ _diffrn_detector_element.detector_id _diffrn_detector_element.id _diffrn_detector_element.reference_center_fast _diffrn_detector_element.reference_center_slow _diffrn_detector_element.reference_center_units d1 d1_ccd_1 201.5 201.5 mm d1 d1_ccd_2 -1.8 201.5 mm d1 d1_ccd_3 201.6 -1.4 mm d1 d1_ccd_4 -1.7 -1.5 mm ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector_element.id _item_description.description ; The value of _diffrn_detector_element.id must uniquely identify each element of a detector. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector_element.id' diffrn_detector_element yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.detector_element_id' '_diffrn_detector_element.id' save_ save__diffrn_detector_element.detector_id _item_description.description ; This item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. ; _item.name '_diffrn_detector_element.detector_id' _item.category_id diffrn_detector_element _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_element.reference_center_fast _item_description.description ; The value of _diffrn_detector_element.reference_center_fast is the fast index axis beam center position relative to the detector element face in the units specified in the data item '_diffrn_detector_element.reference_center_units' along the fast axis of the detector from the center of the first pixel to the point at which the Z-axis (which should be colinear with the beam) intersects the face of the detector, if in fact is does. At the time of the measurement all settings of the detector positioner should be at their reference settings. If more than one reference setting has been used the value given whould be representive of the beam center as determined from the ensemble of settings. It is important to note that for measurements in millimetres, the sense of the axis is used, rather than the sign of the pixel-to-pixel increments. ; _item.name '_diffrn_detector_element.reference_center_fast' _item.category_id diffrn_detector_element _item.mandatory_code no _item_type.code float save_ save__diffrn_detector_element.reference_center_slow _item_description.description ; The value of _diffrn_detector_element.reference_center_slow is the slow index axis beam center position relative to the detector element face in the units specified in the data item '_diffrn_detector_element.reference_center_units' along the slow axis of the detector from the center of the first pixel to the point at which the Z-axis (which should be colinear with the beam) intersects the face of the detector, if in fact is does. At the time of the measurement all settings of the detector positioner should be at their reference settings. If more than one reference setting has been used the value givien whould be representive of the beam center as determined from the ensemble of settings. It is important to note that the sense of the axis is used, rather than the sign of the pixel-to-pixel increments. ; _item.name '_diffrn_detector_element.reference_center_slow' _item.category_id diffrn_detector_element _item.mandatory_code no _item_type.code float save_ save__diffrn_detector_element.reference_center_units _item_description.description ; The value of _diffrn_detector_element.reference_center_units specifies the units in which the values of '_diffrn_detector_element.reference_center_fast' and '_diffrn_detector_element.reference_center_slow' are presented. The default is 'mm' for millimetres. The alternatives are 'pixels' and 'bins'. In all cases the center distances are measured from the center of the first pixel, i.e. in a 2x2 binning, the measuring origin is offset from the centers of the bins by one half pixel towards the first pixel. If 'bins' is specified, the data in '_array_intensities.pixel_fast_bin_size', '_array_intensities.pixel_slow_bin_size', and '_array_intensities.pixel_binning_method' is used to define the binning scheme. ; _item.name '_diffrn_detector_element.reference_center_units' _item.category_id diffrn_detector_element _item.mandatory_code no _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail mm 'millimetres' pixels 'detector pixels' bins 'detector bins' save_ save__diffrn_detector_element.variant _item_description.description ; The value of _diffrn_detector_element.variant gives the variant to which the given diffrn_detector_element row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_detector_element.variant' _item.category_id diffrn_detector_element _item.mandatory_code no _item_type.code code save_ ######################## ## DIFFRN_MEASUREMENT ## ######################## save_DIFFRN_MEASUREMENT _category.description ; Data items in the DIFFRN_MEASUREMENT category record details about the device used to orient and/or position the crystal during data measurement and the manner in which the diffraction data were measured. ; _category.id diffrn_measurement _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement.device' '_diffrn_measurement.diffrn_id' '_diffrn_measurement.id' '_diffrn_measurement.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_measurement.diffrn_id 'd1' _diffrn_measurement.device '3-circle camera' _diffrn_measurement.device_type 'Supper model X' _diffrn_measurement.device_details 'none' _diffrn_measurement.method 'omega scan' _diffrn_measurement.details ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _diffrn_measurement.diffrn_id 's1' _diffrn_measurement.device_type 'Philips PW1100/20 diffractometer' _diffrn_measurement.method 'theta/2theta (\q/2\q)' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_measurement.device _item_description.description ; The general class of goniometer or device used to support and orient the specimen. If the value of _diffrn_measurement.device is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id. Either _diffrn_measurement.device or _diffrn_measurement.id may be used to link to other categories. If the experimental setup admits multiple devices, then _diffrn_measurement.id is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.device' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_device' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement.device' _item_aliases.alias_name '_diffrn_measurement_device' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '3-circle camera' '4-circle camera' 'kappa-geometry camera' 'oscillation camera' 'precession camera' save_ save__diffrn_measurement.device_details _item_description.description ; A description of special aspects of the device used to measure the diffraction intensities. ; _item.name '_diffrn_measurement.device_details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; commercial goniometer modified locally to allow for 90\% \t arc ; save_ save__diffrn_measurement.device_type _item_description.description ; The make, model or name of the measurement device (goniometer) used. ; _item.name '_diffrn_measurement.device_type' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Supper model q' 'Huber model r' 'Enraf-Nonius model s' 'home-made' save_ save__diffrn_measurement.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_measurement.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement.details _item_description.description ; A description of special aspects of the intensity measurement. ; _item.name '_diffrn_measurement.details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; save_ save__diffrn_measurement.id _item_description.description ; The value of _diffrn_measurement.id must uniquely identify the set of mechanical characteristics of the device used to orient and/or position the sample used during the collection of each diffraction data set. If the value of _diffrn_measurement.id is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id. Either _diffrn_measurement.device or _diffrn_measurement.id may be used to link to other categories. If the experimental setup admits multiple devices, then _diffrn_measurement.id is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.id' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_id' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement.id' _item_type.code code save_ save__diffrn_measurement.method _item_description.description ; Method used to measure intensities. ; _item.name '_diffrn_measurement.method' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_method' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'profile data from theta/2theta (\q/2\q) scans' save_ save__diffrn_measurement.number_of_axes _item_description.description ; The value of _diffrn_measurement.number_of_axes gives the number of axes of the positioner for the goniometer or other sample orientation or positioning device identified by _diffrn_measurement.id. The description of the axes should be provided by entries in DIFFRN_MEASUREMENT_AXIS. ; _item.name '_diffrn_measurement.number_of_axes' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ # _diffrn_measurement.sample_detector_distance # _diffrn_measurement.sample_detector_voffset save__diffrn_measurement.sample_detector_distance _item_description.description ; The value of _diffrn_measurement.sample_detector_distance gives the unsigned distance in millimetres from the sample to the detector along the beam. ; _item.name '_diffrn_measurement.sample_detector_distance' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 _item_type.code float _item_units.code mm save_ save__diffrn_measurement.sample_detector_voffset _item_description.description ; The value of _diffrn_measurement.sample_detector_voffset gives the signed distance in millimetres in the vertical direction (positive for up) from the center of the beam to the center of the detector. ; _item.name '_diffrn_measurement.sample_detector_voffset' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . . . . _item_type.code float _item_units.code mm save_ save__diffrn_measurement.specimen_support _item_description.description ; The physical device used to support the crystal during data collection. ; _item.name '_diffrn_measurement.specimen_support' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_specimen_support' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'glass capillary' 'quartz capillary' 'fiber' 'metal loop' save_ save__diffrn_measurement.variant _item_description.description ; The value of _diffrn_measurement.variant gives the variant to which the given diffrn_measurement row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_measurement.variant' _item.category_id diffrn_measurement _item.mandatory_code no _item_type.code code save_ ########################### # DIFFRN_MEASUREMENT_AXIS # ########################### save_DIFFRN_MEASUREMENT_AXIS _category.description ; Data items in the DIFFRN_MEASUREMENT_AXIS category associate axes with goniometers. ; _category.id diffrn_measurement_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement_axis.axis_id' '_diffrn_measurement_axis.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_measurement_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_measurement_axis.axis_id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.measurement_device _item_description.description ; This data item is a pointer to _diffrn_measurement.device in the DIFFRN_MEASUREMENT category. ; _item.name '_diffrn_measurement_axis.measurement_device' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit _item_type.code text save_ save__diffrn_measurement_axis.measurement_id _item_description.description ; This data item is a pointer to _diffrn_measurement.id in the DIFFRN_MEASUREMENT category. This item was previously named _diffrn_measurement_axis.id, which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_measurement_axis.measurement_id' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_measurement_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_measurement_axis.variant _item_description.description ; The value of _diffrn_measurement_axis.variant gives the variant to which the given diffrn_measurement_axis row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_measurement_axis.variant' _item.category_id diffrn_measurement_axis _item.mandatory_code no _item_type.code code save_ #################### # DIFFRN_RADIATION # #################### save_DIFFRN_RADIATION _category.description ; Data items in the DIFFRN_RADIATION category describe the radiation used for measuring diffraction intensities, its collimation and monochromatization before the sample. Post-sample treatment of the beam is described by data items in the DIFFRN_DETECTOR category. ; _category.id diffrn_radiation _category.mandatory_code no loop_ _category_key.name '_diffrn_radiation.diffrn_id' '_diffrn_radiation.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_radiation.diffrn_id 'set1' _diffrn_radiation.collimation '0.3 mm double pinhole' _diffrn_radiation.monochromator 'graphite' _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.wavelength_id 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _diffrn_radiation.wavelength_id 1 _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.monochromator 'graphite' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_radiation.collimation _item_description.description ; The collimation or focusing applied to the radiation. ; _item.name '_diffrn_radiation.collimation' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_collimation' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '0.3 mm double-pinhole' '0.5 mm' 'focusing mirrors' save_ save__diffrn_radiation.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_radiation.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_radiation.div_x_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory X axis (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the standard uncertainty (e.s.d.) of the directions of photons in the XZ plane around the mean source beam direction. Note that for some synchrotrons this value is specified in milliradians, in which case a conversion is needed. To convert a value in milliradians to a value in degrees, multiply by 0.180 and divide by \p. ; _item.name '_diffrn_radiation.div_x_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.div_y_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory Y axis (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the standard uncertainty (e.s.d.) of the directions of photons in the YZ plane around the mean source beam direction. Note that for some synchrotrons this value is specified in milliradians, in which case a conversion is needed. To convert a value in milliradians to a value in degrees, multiply by 0.180 and divide by \p. ; _item.name '_diffrn_radiation.div_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.div_x_y_source _item_description.description ; Beam crossfire correlation degrees^2^ between the crossfire laboratory X-axis component and the crossfire laboratory Y-axis component (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the mean of the products of the deviations of the direction of each photon in XZ plane times the deviations of the direction of the same photon in the YZ plane around the mean source beam direction. This will be zero for uncorrelated crossfire. Note that some synchrotrons, this value is specified in milliradians^2^, in which case a conversion would be needed. To go from a value in milliradians^2^ to a value in degrees^2^, multiply by 0.180^2^ and divide by \p^2^. ; _item.name '_diffrn_radiation.div_x_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees_squared _item_default.value 0.0 save_ save__diffrn_radiation.filter_edge _item_description.description ; Absorption edge in \%Angstroms of the radiation filter used. ; _item.name '_diffrn_radiation.filter_edge' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_filter_edge' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__diffrn_radiation.inhomogeneity _item_description.description ; Half-width in millimetres of the incident beam in the direction perpendicular to the diffraction plane. ; _item.name '_diffrn_radiation.inhomogeneity' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_inhomogeneity' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code millimetres save_ save__diffrn_radiation.monochromator _item_description.description ; The method used to obtain monochromatic radiation. If a monochromator crystal is used, the material and the indices of the Bragg reflection are specified. ; _item.name '_diffrn_radiation.monochromator' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_monochromator' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Zr filter' 'Ge 220' 'none' 'equatorial mounted graphite' save_ save__diffrn_radiation.polarisn_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the perpendicular component of the polarization and the diffraction plane. See _diffrn_radiation_polarisn_ratio. ; _item.name '_diffrn_radiation.polarisn_norm' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_norm' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.polarisn_ratio _item_description.description ; Polarization ratio of the diffraction beam incident on the crystal. This is the ratio of the perpendicularly polarized to the parallel polarized component of the radiation. The perpendicular component forms an angle of _diffrn_radiation.polarisn_norm to the normal to the diffraction plane of the sample (i.e. the plane containing the incident and reflected beams). ; _item.name '_diffrn_radiation.polarisn_ratio' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_ratio' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__diffrn_radiation.polarizn_source_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the normal to the polarization plane and the laboratory Y axis as defined in the AXIS category. Note that this is the angle of polarization of the source photons, either directly from a synchrotron beamline or from a monochromater. This differs from the value of _diffrn_radiation.polarisn_norm in that _diffrn_radiation.polarisn_norm refers to polarization relative to the diffraction plane rather than to the laboratory axis system. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane should be taken as the XZ plane and the angle as 0. See _diffrn_radiation.polarizn_source_ratio. ; _item.name '_diffrn_radiation.polarizn_source_norm' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.polarizn_source_ratio _item_description.description ; (Ip-In)/(Ip+In), where Ip is the intensity (amplitude squared) of the electric vector in the plane of polarization and In is the intensity (amplitude squared) of the electric vector in the plane of the normal to the plane of polarization. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane is to be taken as the XZ plane and the normal is parallel to the Y axis. Thus, if there was complete polarization in the plane of polarization, the value of _diffrn_radiation.polarizn_source_ratio would be 1, and for an unpolarized beam _diffrn_radiation.polarizn_source_ratio would have a value of 0. If the X axis has been chosen to lie in the plane of polarization, this definition will agree with the definition of 'MONOCHROMATOR' in the Denzo glossary, and values of near 1 should be expected for a bending-magnet source. However, if the X axis were perpendicular to the polarization plane (not a common choice), then the Denzo value would be the negative of _diffrn_radiation.polarizn_source_ratio. See http://www.hkl-xray.com for information on Denzo and Otwinowski & Minor (1997). This differs both in the choice of ratio and choice of orientation from _diffrn_radiation.polarisn_ratio, which, unlike _diffrn_radiation.polarizn_source_ratio, is unbounded. Reference: Otwinowski, Z. & Minor, W. (1997). 'Processing of X-ray diffraction data collected in oscillation mode.' Methods Enzymol. 276, 307-326. ; _item.name '_diffrn_radiation.polarizn_source_ratio' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 -1.0 -1.0 -1.0 _item_type.code float save_ save__diffrn_radiation.probe _item_description.description ; Name of the type of radiation used. It is strongly recommended that this be given so that the probe radiation is clearly specified. ; _item.name '_diffrn_radiation.probe' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_probe' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value 'X-ray' 'neutron' 'electron' 'gamma' save_ save__diffrn_radiation.type _item_description.description ; The nature of the radiation. This is typically a description of the X-ray wavelength in Siegbahn notation. ; _item.name '_diffrn_radiation.type' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'CuK\a' 'Cu K\a~1~' 'Cu K-L~2,3~' 'white-beam' save_ save__diffrn_radiation.xray_symbol _item_description.description ; The IUPAC symbol for the X-ray wavelength for the probe radiation. ; _item.name '_diffrn_radiation.xray_symbol' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_xray_symbol' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value _item_enumeration.detail 'K-L~3~' 'K\a~1~ in older Siegbahn notation' 'K-L~2~' 'K\a~2~ in older Siegbahn notation' 'K-M~3~' 'K\b~1~ in older Siegbahn notation' 'K-L~2,3~' 'use where K-L~3~ and K-L~2~ are not resolved' save_ save__diffrn_radiation.wavelength_id _item_description.description ; This data item is a pointer to _diffrn_radiation_wavelength.id in the DIFFRN_RADIATION_WAVELENGTH category. ; _item.name '_diffrn_radiation.wavelength_id' _item.category_id diffrn_radiation _item.mandatory_code yes _item_type.code code save_ save__diffrn_radiation.variant _item_description.description ; The value of _diffrn_radiation.variant gives the variant to which the given diffrn_radiation row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_radiation.variant' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code code save_ ################ # DIFFRN_REFLN # ################ save_DIFFRN_REFLN _category.description ; This category redefinition has been added to extend the key of the standard DIFFRN_REFLN category. Data items in the DIFFRN_REFLN category record details about the intensities in the diffraction data set identified by _diffrn_refln.diffrn_id. The DIFFRN_REFLN data items refer to individual intensity measurements and must be included in looped lists. The DIFFRN_REFLNS data items specify the parameters that apply to all intensity measurements in the particular diffraction data set identified by _diffrn_reflns.diffrn_id and _diffrn_refln.frame_id ; ; _category.id diffrn_refln _category.mandatory_code no loop_ _category_key.name '_diffrn_refln.diffrn_id' '_diffrn_refln.id' '_diffrn_refln.frame_id' '_diffrn_refln.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_refln.frame_id _item_description.description ; This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_refln.frame_id' _item.category_id diffrn_refln _item.mandatory_code yes _item_type.code code save_ save__diffrn_refln.variant _item_description.description ; The value of _diffrn_refln.variant gives the variant to which the given diffrn_refln row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_refln.variant' _item.category_id diffrn_refln _item.mandatory_code no _item_type.code code save_ ############### # DIFFRN_SCAN # ############### save_DIFFRN_SCAN _category.description ; Data items in the DIFFRN_SCAN category describe the parameters of one or more scans, relating axis positions to frames. ; _category.id diffrn_scan _category.mandatory_code no loop_ _category_key.name '_diffrn_scan.id' '_diffrn_scan.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - derived from a suggestion by R. M. Sweet. The vector of each axis is not given here, because it is provided in the AXIS category. By making _diffrn_scan_axis.scan_id and _diffrn_scan_axis.axis_id keys of the DIFFRN_SCAN_AXIS category, an arbitrary number of scanning and fixed axes can be specified for a scan. In this example, three rotation axes and one translation axis at nonzero values are specified, with one axis stepping. There is no reason why more axes could not have been specified to step. Range information has been specified, but note that it can be calculated from the number of frames and the increment, so the data item _diffrn_scan_axis.angle_range could be dropped. Both the sweep data and the data for a single frame are specified. Note that the information on how the axes are stepped is given twice, once in terms of the overall averages in the value of _diffrn_scan.integration_time and the values for DIFFRN_SCAN_AXIS, and precisely for the given frame in the value for _diffrn_scan_frame.integration_time and the values for DIFFRN_SCAN_FRAME_AXIS. If dose-related adjustments are made to scan times and nonlinear stepping is done, these values may differ. Therefore, in interpreting the data for a particular frame it is important to use the frame-specific data. ; ; _diffrn_scan.id 1 _diffrn_scan.date_start '2001-11-18T03:26:42' _diffrn_scan.date_end '2001-11-18T03:36:45' _diffrn_scan.integration_time 3.0 _diffrn_scan.frame_id_start mad_L2_000 _diffrn_scan.frame_id_end mad_L2_200 _diffrn_scan.frames 201 loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment 1 omega 200.0 20.0 0.1 . . . 1 kappa -40.0 0.0 0.0 . . . 1 phi 127.5 0.0 0.0 . . . 1 tranz . . . 2.3 0.0 0.0 _diffrn_scan_frame.scan_id 1 _diffrn_scan_frame.date '2001-11-18T03:27:33' _diffrn_scan_frame.integration_time 3.0 _diffrn_scan_frame.frame_id mad_L2_018 _diffrn_scan_frame.frame_number 18 loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.angle_increment _diffrn_scan_frame_axis.displacement _diffrn_scan_frame_axis.displacement_increment mad_L2_018 omega 201.8 0.1 . . mad_L2_018 kappa -40.0 0.0 . . mad_L2_018 phi 127.5 0.0 . . mad_L2_018 tranz . . 2.3 0.0 ; ; Example 2 - a more extensive example (R. M. Sweet, P. J. Ellis & H. J. Bernstein). A detector is placed 240 mm along the Z axis from the goniometer. This leads to a choice: either the axes of the detector are defined at the origin, and then a Z setting of -240 is entered, or the axes are defined with the necessary Z offset. In this case, the setting is used and the offset is left as zero. This axis is called DETECTOR_Z. The axis for positioning the detector in the Y direction depends on the detector Z axis. This axis is called DETECTOR_Y. The axis for positioning the detector in the X direction depends on the detector Y axis (and therefore on the detector Z axis). This axis is called DETECTOR_X. This detector may be rotated around the Y axis. This rotation axis depends on the three translation axes. It is called DETECTOR_PITCH. A coordinate system is defined on the face of the detector in terms of 2300 0.150 mm pixels in each direction. The ELEMENT_X axis is used to index the first array index of the data array and the ELEMENT_Y axis is used to index the second array index. Because the pixels are 0.150mm X 0.150mm, the centre of the first pixel is at (0.075, 0.075) in this coordinate system. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 172.43 -172.43 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 2300 1 increasing ELEMENT_X ARRAY1 2 2300 2 increasing ELEMENT_Y # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.075 0.150 ELEMENT_Y ELEMENT_Y 0.075 0.150 # category ARRAY_ELEMENT_SIZE loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 ARRAY1 2 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; ; Example 3 - Example 2 revised for a spiral scan (R. M. Sweet, P. J. Ellis & H. J. Bernstein). A detector is placed 240 mm along the Z axis from the goniometer, as in Example 2 above, but in this example the image plate is scanned in a spiral pattern from the outside edge in. The axis for positioning the detector in the Y direction depends on the detector Z axis. This axis is called DETECTOR_Y. The axis for positioning the detector in the X direction depends on the detector Y axis (and therefore on the detector Z axis). This axis is called DETECTOR_X. This detector may be rotated around the Y axis. This rotation axis depends on the three translation axes. It is called DETECTOR_PITCH. A coordinate system is defined on the face of the detector in terms of a coupled rotation axis and radial scan axis to form a spiral scan. The rotation axis is called ELEMENT_ROT and the radial axis is called ELEMENT_RAD. A 150 micrometre radial pitch and a 75 micrometre 'constant velocity' angular pitch are assumed. Indexing is carried out first on the rotation axis and the radial axis is made to be dependent on it. The two axes are coupled to form an axis set ELEMENT_SPIRAL. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_ROT translation detector DETECTOR_PITCH 0 0 1 0 0 0 ELEMENT_RAD translation detector ELEMENT_ROT 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.angle _array_structure_list_axis.displacement _array_structure_list_axis.angular_pitch _array_structure_list_axis.radial_pitch ELEMENT_SPIRAL ELEMENT_ROT 0 . 0.075 . ELEMENT_SPIRAL ELEMENT_RAD . 172.5 . -0.150 # category ARRAY_ELEMENT_SIZE # the actual pixels are 0.075 by 0.150 mm # We give the coarser dimension here. loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_scan.id _item_description.description ; The value of _diffrn_scan.id uniquely identifies each scan. The identifier is used to tie together all the information about the scan. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_scan.id' diffrn_scan yes '_diffrn_scan_axis.scan_id' diffrn_scan_axis yes '_diffrn_scan_frame.scan_id' diffrn_scan_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_scan_axis.scan_id' '_diffrn_scan.id' '_diffrn_scan_frame.scan_id' '_diffrn_scan.id' save_ save__diffrn_scan.date_end _item_description.description ; The date and time of the end of the scan. Note that this may be an estimate generated during the scan, before the precise time of the end of the scan is known. ; _item.name '_diffrn_scan.date_end' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.date_start _item_description.description ; The date and time of the start of the scan. ; _item.name '_diffrn_scan.date_start' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.integration_time _item_description.description ; Approximate average time in seconds to integrate each step of the scan. The precise time for integration of each particular step must be provided in _diffrn_scan_frame.integration_time, even if all steps have the same integration time. ; _item.name '_diffrn_scan.integration_time' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan.frame_id_start _item_description.description ; The value of this data item is the identifier of the first frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_start' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frame_id_end _item_description.description ; The value of this data item is the identifier of the last frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_end' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frames _item_description.description ; The value of this data item is the number of frames in the scan. ; _item.name '_diffrn_scan.frames' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 1 1 1 save_ save__diffrn_scan.variant _item_description.description ; The value of _diffrn_scan.variant gives the variant to which the given diffrn_scan row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_scan.variant' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code code save_ #################### # DIFFRN_SCAN_AXIS # #################### save_DIFFRN_SCAN_AXIS _category.description ; Data items in the DIFFRN_SCAN_AXIS category describe the settings of axes for particular scans. Unspecified axes are assumed to be at their zero points. ; _category.id diffrn_scan_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_axis.scan_id' '_diffrn_scan_axis.axis_id' '_diffrn_scan_axis.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_axis.scan_id _item_description.description ; The value of this data item is the identifier of the scan for which axis settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan.id. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_axis.scan_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the scan for which settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan.id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_axis.axis_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.angle_start _item_description.description ; The starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_range _item_description.description ; The range from the starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_increment _item_description.description ; The increment for each step for the specified axis in degrees. In general, this will agree with _diffrn_scan_frame_axis.angle_increment. The sum of the values of _diffrn_scan_frame_axis.angle and _diffrn_scan_frame_axis.angle_increment is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of _diffrn_scan_axis.angle_increment will be representative of the ensemble of values of _diffrn_scan_frame_axis.angle_increment (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_rstrt_incr _item_description.description ; The increment after each step for the specified axis in degrees. In general, this will agree with _diffrn_scan_frame_axis.angle_rstrt_incr. The sum of the values of _diffrn_scan_frame_axis.angle, _diffrn_scan_frame_axis.angle_increment and _diffrn_scan_frame_axis.angle_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame and should equal _diffrn_scan_frame_axis.angle for this next frame. If the individual frame values vary, then the value of _diffrn_scan_axis.angle_rstrt_incr will be representative of the ensemble of values of _diffrn_scan_frame_axis.angle_rstrt_incr (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.displacement_start _item_description.description ; The starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_range _item_description.description ; The range from the starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_increment _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with _diffrn_scan_frame_axis.displacement_increment. The sum of the values of _diffrn_scan_frame_axis.displacement and _diffrn_scan_frame_axis.displacement_increment is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of _diffrn_scan_axis.displacement_increment will be representative of the ensemble of values of _diffrn_scan_frame_axis.displacement_increment (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_rstrt_incr _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with _diffrn_scan_frame_axis.displacement_rstrt_incr. The sum of the values of _diffrn_scan_frame_axis.displacement, _diffrn_scan_frame_axis.displacement_increment and _diffrn_scan_frame_axis.displacement_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame and should equal _diffrn_scan_frame_axis.displacement for this next frame. If the individual frame values vary, then the value of _diffrn_scan_axis.displacement_rstrt_incr will be representative of the ensemble of values of _diffrn_scan_frame_axis.displacement_rstrt_incr (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.reference_angle _item_description.description ; The setting of the specified axis in degrees against which measurements of the reference beam center and reference detector distance should be made. In general, this will agree with _diffrn_scan_frame_axis.reference_angle. If the individual frame values vary, then the value of _diffrn_scan_axis.reference_angle will be representative of the ensemble of values of _diffrn_scan_frame_axis.reference_angle (e.g. the mean). If not specified, the value defaults to zero. ; _item.name '_diffrn_scan_axis.reference_angle' _item.category_id diffrn_scan_axis _item.mandatory_code implicit _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.reference_displacement _item_description.description ; The setting of the specified axis in millimetres against which measurements of the reference beam center and reference detector distance should be made. In general, this will agree with _diffrn_scan_frame_axis.reference_displacement. If the individual frame values vary, then the value of _diffrn_scan_axis.reference_displacement will be representative of the ensemble of values of _diffrn_scan_frame_axis.reference_displacement (e.g. the mean). If not specified, the value defaults to to the value of _diffrn_scan_axis.displacement. ; _item.name '_diffrn_scan_axis.reference_displacement' _item.category_id diffrn_scan_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.variant _item_description.description ; The value of _diffrn_scan_axis.variant gives the variant to which the given diffrn_scan_axis row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_scan_axis.variant' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_type.code code save_ ##################### # DIFFRN_SCAN_FRAME # ##################### save_DIFFRN_SCAN_FRAME _category.description ; Data items in the DIFFRN_SCAN_FRAME category describe the relationships of particular frames to scans. ; _category.id diffrn_scan_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame.scan_id' '_diffrn_scan_frame.frame_id' '_diffrn_scan_frame.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame.date _item_description.description ; The date and time of the start of the frame being scanned. ; _item.name '_diffrn_scan_frame.date' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan_frame.frame_id _item_description.description ; The value of this data item is the identifier of the frame being examined. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame.frame_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame.frame_number _item_description.description ; The value of this data item is the number of the frame within the scan, starting with 1. It is not necessarily the same as the value of _diffrn_scan_frame.frame_id, but it may be. ; _item.name '_diffrn_scan_frame.frame_number' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 0 0 0 save_ save__diffrn_scan_frame.integration_time _item_description.description ; The time in seconds to integrate this step of the scan. This should be the precise time of integration of each particular frame. The value of this data item should be given explicitly for each frame and not inferred from the value of _diffrn_scan.integration_time. ; _item.name '_diffrn_scan_frame.integration_time' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame.scan_id _item_description.description ; The value of _diffrn_scan_frame.scan_id identifies the scan containing this frame. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_frame.scan_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame.variant _item_description.description ; The value of _diffrn_scan_frame.variant gives the variant to which the given diffrn_scan_frame row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_scan_frame.variant' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code code save_ ########################## # DIFFRN_SCAN_FRAME_AXIS # ########################## save_DIFFRN_SCAN_FRAME_AXIS _category.description ; Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the settings of axes for particular frames. Unspecified axes are assumed to be at their zero points. If, for any given frame, nonzero values apply for any of the data items in this category, those values should be given explicitly in this category and not simply inferred from values in DIFFRN_SCAN_AXIS. ; _category.id diffrn_scan_frame_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame_axis.frame_id' '_diffrn_scan_frame_axis.axis_id' '_diffrn_scan_frame_axis.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the frame for which settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_frame_axis.axis_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_axis.angle _item_description.description ; The setting of the specified axis in degrees for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.angle' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_increment _item_description.description ; The increment for this frame for the angular setting of the specified axis in degrees. The sum of the values of _diffrn_scan_frame_axis.angle and _diffrn_scan_frame_axis.angle_increment is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.angle_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_rstrt_incr _item_description.description ; The increment after this frame for the angular setting of the specified axis in degrees. The sum of the values of _diffrn_scan_frame_axis.angle, _diffrn_scan_frame_axis.angle_increment and _diffrn_scan_frame_axis.angle_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame and should equal _diffrn_scan_frame_axis.angle for this next frame. ; _item.name '_diffrn_scan_frame_axis.angle_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.displacement' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_increment _item_description.description ; The increment for this frame for the displacement setting of the specified axis in millimetres. The sum of the values of _diffrn_scan_frame_axis.displacement and _diffrn_scan_frame_axis.displacement_increment is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.displacement_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_rstrt_incr _item_description.description ; The increment for this frame for the displacement setting of the specified axis in millimetres. The sum of the values of _diffrn_scan_frame_axis.displacement, _diffrn_scan_frame_axis.displacement_increment and _diffrn_scan_frame_axis.displacement_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame and should equal _diffrn_scan_frame_axis.displacement for this next frame. ; _item.name '_diffrn_scan_frame_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.frame_id _item_description.description ; The value of this data item is the identifier of the frame for which axis settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame_axis.frame_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_axis.reference_angle _item_description.description ; The setting of the specified axis in degrees against which measurements of the reference beam center and reference detector distance should be made. This is normally the same for all frames, but the option is provided here of making changes when needed. If not provided, it is assumed to be zero. ; _item.name '_diffrn_scan_frame_axis.reference_angle' _item.category_id diffrn_scan_frame_axis _item.mandatory_code implicit _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.reference_displacement _item_description.description ; The setting of the specified axis in millimetres for this frame against which measurements of the reference beam center and reference detector distance should be made. This is normally the same for all frames, but the option is provided here of making changes when needed. If not provided, it is assumed to be equal to _diffrn_scan_frame_axis.displacement. ; _item.name '_diffrn_scan_frame_axis.reference_displacement' _item.category_id diffrn_scan_frame_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.variant _item_description.description ; The value of _diffrn_scan_frame_axis.variant gives the variant to which the given diffrn_scan_frame_axis row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_scan_frame_axis.variant' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_type.code code save_ ############################# # DIFFRN_SCAN_FRAME_MONITOR # ############################# save_DIFFRN_SCAN_FRAME_MONITOR _category.description ; Data items in the DIFFRN_SCAN_FRAME_MONITOR category record the values and details about each monitor for each frame of data during a scan. Each monitor value is uniquely identified by the combination of the scan_id given by _diffrn_scan_frame.scan_id the frame_id given by _diffrn_scan_frame_monitor.frame_id, the monitor's detector_id given by _diffrn_scan_frame_monitor.monitor_id, and a 1-based ordinal given by _diffrn_scan_frame_monitor.id. If there is only one frame for the scan, the value of _diffrn_scan_frame_monitor.frame_id may be omitted. A single frame may have more than one monitor value, and each monitor value may be the result of integration over the entire frame integration time given by the value of _diffrn_scan_frame.integration_time or many monitor values may be reported over shorter times given by the value of _diffrn_scan_frame_monitor.integration_time. If only one monitor value for a given monitor is collected during the integration time of the frame, the value of _diffrn_scan_frame_monitor.id may be omitted. ; _category.id diffrn_data_frame_monitor _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame_monitor.id' '_diffrn_scan_frame_monitor.detector_id' '_diffrn_scan_frame_monitor.scan_id' '_diffrn_data_frame_monitor.frame_id' '_diffrn_data_frame_monitor.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - The beam intensity for frame FRAME1 is being tracked by a beamstop monitor detector BSM01, made from metal foil and a PIN diode, locate 20 mm in front of a MAR345 detector and being sampled every 2 seconds in a 20 second scan. ; ; # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 P6MB BSM01 'metal foil and PIN diode' 1 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH BSM01 MONITOR_Z # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 MONITOR_Z 0.0 0.0 0.0 -220.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_MONITOR loop_ _diffrn_scan_frame_monitor.id _diffrn_scan_frame_monitor.detector_id _diffrn_scan_frame_monitor.scan_id _diffrn_data_frame_monitor.frame_id _diffrn_data_frame_monitor.integration_time _diffrn_data_frame_monitor.monitor_value 1 BSM01 SCAN1 FRAME1 2.0 23838345642 2 BSM01 SCAN1 FRAME1 2.0 23843170669 3 BSM01 SCAN1 FRAME1 2.0 23839478690 4 BSM01 SCAN1 FRAME1 2.0 23856642085 5 BSM01 SCAN1 FRAME1 2.0 23781717656 6 BSM01 SCAN1 FRAME1 2.0 23788850775 7 BSM01 SCAN1 FRAME1 2.0 23815576677 8 BSM01 SCAN1 FRAME1 2.0 23789299964 9 BSM01 SCAN1 FRAME1 2.0 23830195536 10 BSM01 SCAN1 FRAME1 2.0 23673082270 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 FRAME1 MONITOR_Z 0.0 -220.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 172.43 -172.43 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 MONITOR_Z translation detector . 0 0 1 0 0 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_scan_frame_monitor.id _item_description.description ; This item is an integer identifier which, along with _diffrn_scan_frame_monitor.detector_id, _diffrn_scan_frame_monitor.scan_id, and _diffrn_data_frame_monitor.frame_id should uniquely identify the monitor value being recorded If _array_data.binary_id is not explicitly given, it defaults to 1. ; loop_ _item.name _diffrn_scan_frame_monitor.id _item.category_id diffrn_scan_frame_monitor _item.mandatory_code implicit _item_default.value 1 _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__diffrn_scan_frame_monitor.detector_id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. ; _item.name '_diffrn_scan_frame_monitor.detector_id' _item.category_id diffrn_scan_frame_monitor _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_monitor.frame_id _item_description.description ; This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame_monitor.frame_id' _item.category_id diffrn_scan_frame_monitor _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_monitor.integration_time _item_description.description ; The precise time for integration of the monitor value given in _diffrn_scan_frame_monitor.value must be given in _diffrn_scan_frame_monitor.integration_time. ; _item.name '_diffrn_scan_frame_monitor.integration_time' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame_monitor.value _item_description.description ; The value reported by the monitor detector should be given in _diffrn_scan_frame_monitor.value. The value is typed as float to allow of monitors for very intense beams that cannot report all digits, but when available, all digits of the monitor should be recorded. ; _item.name '_diffrn_scan_frame_monitor.value' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame_monitor.variant _item_description.description ; The value of _diffrn_scan_frame_monitor.variant gives the variant to which the given diffrn_scan_frame_monitor row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_scan_frame_monitor.variant' _item.category_id diffrn_scan_frame_monitor _item.mandatory_code no _item_type.code code save_ ####### # MAP # ####### save_MAP _category.description ; Data items in the MAP category record the details of a maps. Maps record values of parameters, such as density, that are functions of position within a cell or are functions of orthogonal coordinates in three space. A map may is composed of one or more map segments specified in the MAP_SEGMENT category. Examples are given in the MAP_SEGMENT category. ; _category.id map _category.mandatory_code no loop_ _category_key.name '_map.id' '_map.diffrn_id' '_map.entry_id' '_map.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' 'map_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Identifying an observed density map and a calculated density map ; ; loop_ _map.id _map.details rho_calc ; density calculated from F_calc derived from the ATOM_SITE list ; rho_obs ; density combining the observed structure factors with the calculated phases ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__map.details _item_description.description ; The value of _map.details should give a description of special aspects of each map. ; _item.name '_map.details' _item.category_id map _item.mandatory_code no _item_type.code text loop_ _item_examples.case _item_examples.detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Identifying an observed density map and a calculated density map ; ; loop_ _map.id _map.details rho_calc ; density calculated from F_calc derived from the ATOM_SITE list ; rho_obs ; density combining the observed structure factors with the calculated phases ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__map.diffrn_id _item_description.description ; This item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_map.diffrn_id' _item.category_id map _item.mandatory_code implicit _item_type.code code save_ save__map.entry_id _item_description.description ; This item is a pointer to _entry.id in the ENTRY category. ; _item.name '_map.entry_id' _item.category_id map _item.mandatory_code implicit _item_type.code code save_ save__map.id _item_description.description ; The value of _map.id must uniquely identify each map for the given diffrn.id or entry.id. ; loop_ _item.name _item.category_id _item.mandatory_code '_map.id' map yes '_map_segment.id' map_segment yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_map_segment.id' '_map.id' save_ save__map.variant _item_description.description ; The value of _map.variant gives the variant to which the given map row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_map.variant' _item.category_id map _item.mandatory_code no _item_type.code code save_ ############### # MAP_SEGMENT # ############### save_MAP_SEGMENT _category.description ; Data items in the MAP_SEGMENT category record the details about each segment (section or brick) of a map. ; _category.id map_segment _category.mandatory_code no loop_ _category_key.name '_map_segment.id' '_map_segment.map_id' '_map_segment.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' 'map_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Identifying an observed density map and a calculated density map, each consisting of one segment, both using the same array structure and mask. ; ; loop_ _map.id _map.details rho_calc ; density calculated from F_calc derived from the ATOM_SITE list ; rho_obs ; density combining the observed structure factors with the calculated phases ; loop_ _map_segment.map_id _map_segment.id _map_segment.array_id _map_segment.binary_id _map_segment.mask_array_id _map_segment.mask_binary_id rho_calc rho_calc map_structure 1 mask_structure 1 rho_obs rho_obs map_structure 2 mask_structure 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__map_segment.array_id _item_description.description ; The value of _map_segment.array_id identifies the array structure into which the map is organized. This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_map_segment.array_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code code save_ save__map_segment.binary_id _item_description.description ; The value of _map_segment.binary_id distinguishes the particular set of data organized according to _map_segment.array_id in which the data values of the map are stored. This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_map_segment.binary_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code int save_ save__map_segment.mask_array_id _item_description.description ; The value of _map_segment.mask_array_id, if given, the array structure into which the mask for the map is organized. If no value is given, then all elements of the map are valid. If a value is given, then only elements of the map for which the corresponding element of the mask is non-zero are valid. The value of _map_segment.mask_array_id differs from the value of _map_segment.array_id in order to permit the mask to be given as, say, unsigned 8-bit integers, while the map is given as a data type with more range. However, the two array structures must be aligned, using the same axes in the same order with the same displacements and increments This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_map_segment.mask_array_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code code save_ save__map_segment.mask_binary_id _item_description.description ; The value of _map_segment.mask_binary_id identifies the particular set of data organized according to _map_segment.mask_array_id specifying the mask for the map. This item is a pointer to _array_data.mask_binary_id in the ARRAY_DATA category. ; _item.name '_map_segment.mask_binary_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code int save_ save__map_segment.id _item_description.description ; The value of _map_segment.id must uniquely identify each segment of a map. ; loop_ _item.name _item.category_id _item.mandatory_code '_map_segment.id' map_segment yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_map_data_frame.map_segment_id' '_map_segment.id' save_ save__map_segment.map_id _item_description.description ; This item is a pointer to _map.id in the MAP category. ; _item.name '_map_segment.map_id' _item.category_id map_segment _item.mandatory_code yes _item_type.code code save_ save__map_segment.details _item_description.description ; The value of _map_segment.details should give a description of special aspects of each segment of a map. ; _item.name '_map_segment.details' _item.category_id map_segment _item.mandatory_code no _item_type.code text loop_ _item_examples.case _item_examples.detail ; Example to be provided ; ; ; save_ save__map_segment.variant _item_description.description ; The value of _map_segment.variant gives the variant to which the given map segment is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_map_segment.variant' _item.category_id map_segment _item.mandatory_code no _item_type.code code save_ ########### # VARIANT # ########### save_VARIANT _category.description ; Data items in the VARIANT category record the details about sets of variants of data items. There is sometimes a need to allow for multiple versions of the same data items in order to allow for refinements and corrections to earlier assumptions, observations and calculations. In order to allow data sets to contain more than one variant of the same information, an optional ...variant data item as a pointer to _variant.variant has been added to the key of every category, as an implicit data item with a null (empty) default value. All rows in a category with the same variant value are considered to be related to one another and to all rows in other categories with the same variant value. For a given variant, all such rows are also considered to be related to all rows with a null variant value, except that a row with a null variant value is for which all other components of its key are identical to those entries in another row with a non-null variant value is not related the the rows with that non-null variant value. This behavior is similar to the convention for identifying alternate conformers in an atom list. An optional role may be specified for a variant as the value of _variant.role. Possible roles are null, "preferred", "raw data", "unsuccessful trial". Variants may carry an optional timestamp as the value of _variant.timestamp. Variants may be related to other variants from which they were derived by the value of _variant.variant_of Further details about the variant may be specified as the value of _variant.details. In order to allow variant information from multiple datasets to be combined, _variant.diffrn_id and/or _variant.entry_id may be used. ; _category.id variant _category.mandatory_code no loop_ _category_key.name '_variant.variant' '_variant.diffrn_id' '_variant.entry_id' loop_ _category_group.id 'inclusive_group' 'variant_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Distinguishing between a raw beam center and a refined beam center inferred after indexing. Detector d1 is composed of four CCD detector elements, each 200 mm by 200 mm, arranged in a square, in the pattern 1 2 * 3 4 Note that the beam centre is slightly displaced from each of the detector elements, just beyond the lower right corner of 1, the lower left corner of 2, the upper right corner of 3 and the upper left corner of 4. For each element, the detector face coordiate system, is assumed to have the fast axis running from left to right and the slow axis running from top to bottom with the origin at the top left corner. After indexing and refinement, the center is shifted by .2 mm left and .1 mm down. ; ; loop_ _variant.variant _variant.role _variant.timestamp _variant.variant_of _variant.details . "raw data" 2007-08-03T23:20:00 . . indexed "preferred" 2007-08-04T01:17:28 . "indexed cell and refined beam center" loop_ _diffrn_detector_element.detector_id _diffrn_detector_element.id _diffrn_detector_element.reference_center_fast _diffrn_detector_element.reference_center_slow _diffrn_detector_element.reference_center_units _diffrn_detector_element.variant d1 d1_ccd_1 201.5 201.5 mm . d1 d1_ccd_2 -1.8 201.5 mm . d1 d1_ccd_3 201.6 -1.4 mm . d1 d1_ccd_4 -1.7 -1.5 mm . d1 d1_ccd_1 201.3 201.6 mm indexed d1 d1_ccd_2 -2.0 201.6 mm indexed d1 d1_ccd_3 201.3 -1.5 mm indexed d1 d1_ccd_4 -1.9 -1.6 mm indexed ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__variant.details _item_description.description ; A description of special aspects of the variant. ; _item.name '_variant.details' _item.category_id variant _item.mandatory_code no _item_type.code text _item_examples.case ; indexed cell and refined beam center ; save_ save__variant.role _item_description.description ; The value of _variant.role specified a role for this variant. Possible roles are null, "preferred", "raw data", and "unsuccessful trial". ; _item.name '_variant.role' _item.category_id variant _item.mandatory_code no _item_type.code uline loop_ _item_enumeration.value _item_enumeration.detail . ; A null value for _variant.role leaves the precise role of the variant unspecified. No inference should be made that the variant with the latest time stamp is preferred. ; "preferred" ; A value of "preferred" indicates that rows of any categories specifying this variant should be used in preference to rows with the same key specifying other variants or the null variant. It is an error to specify two variants that appear in the same category with the same key as being preferred, but it is not an error to specify more than one variant as preferred in other cases. ; "raw data" ; A value of "raw data" indicates data prior to any corrections, calculations or refinements. It is not necessarily an error for raw data to also be a variant of an earlier variant. It may be replacement raw data for earlier data believed to be erroneous. ; "unsuccessful trial" ; A value of "unsuccessful trial" indicates data that should not be used for further calculation. ; save_ save__variant.timestamp _item_description.description ; The date and time identifying a variant. This is not necessarily the precise time of the measurement or calculation of the individual related data items, but a timestamp that reflects the order in which the variants were defined. ; _item.name '_variant.timestamp' _item.category_id variant _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__variant.variant _item_description.description ; The value of _variant.variant must uniquely identify each variant for the given diffraction experiment and/or entry This item has been made implicit and given a default value of null. ; loop_ _item.name _item.category_id _item.mandatory_code '_variant.variant' variant implicit '_variant.variant_of' variant implicit '_array_data.variant' array_data implicit '_array_element_size.variant' array_element_size implicit '_array_intensities.variant' array_intensities implicit '_array_structure.variant' array_structure implicit '_array_structure_list.variant' array_structure_list implicit '_array_structure_list_axis.variant' array_structure_list_axis implicit '_axis.variant' axis implicit '_diffrn_data_frame.variant' diffrn_data_frame implicit '_diffrn_detector.variant' diffrn_detector implicit '_diffrn_detector_axis.variant' diffrn_detector_axis implicit '_diffrn_detector_element.variant' diffrn_detector_element implicit '_diffrn_measurement.variant' diffrn_measurement implicit '_diffrn_measurement_axis.variant' diffrn_measurement_axis implicit '_diffrn_radiation.variant' diffrn_radiation implicit '_diffrn_refln.variant' diffrn_refln implicit '_diffrn_scan.variant' diffrn_scan implicit '_diffrn_scan_axis.variant' diffrn_scan_axis implicit '_diffrn_scan_frame.variant' diffrn_scan_frame implicit '_diffrn_scan_frame_axis.variant' diffrn_scan_frame_axis implicit '_diffrn_scan_frame_monitor.variant' diffrn_scan_frame_monitor implicit '_map.variant' map implicit '_map_segment.variant' map_segment implicit _item_default.value . _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_data.variant' '_variant.variant' '_array_data.variant_of' '_variant.variant' '_array_element_size.variant' '_variant.variant' '_array_intensities.variant' '_variant.variant' '_array_structure.variant' '_variant.variant' '_array_structure_list.variant' '_variant.variant' '_array_structure_list_axis.variant' '_variant.variant' '_axis.variant' '_variant.variant' '_diffrn_data_frame.variant' '_variant.variant' '_diffrn_detector.variant' '_variant.variant' '_diffrn_detector_axis.variant' '_variant.variant' '_diffrn_detector_element.variant' '_variant.variant' '_diffrn_measurement.variant' '_variant.variant' '_diffrn_measurement_axis.variant' '_variant.variant' '_diffrn_radiation.variant' '_variant.variant' '_diffrn_refln.variant' '_variant.variant' '_diffrn_scan.variant' '_variant.variant' '_diffrn_scan_axis.variant' '_variant.variant' '_diffrn_scan_frame.variant' '_variant.variant' '_diffrn_scan_frame_axis.variant' '_variant.variant' '_diffrn_scan_frame_monitor.variant' '_variant.variant' '_map.variant' '_variant.variant' '_map_segment.variant' '_variant.variant' save_ save__variant.variant_of _item_description.description ; The value of _variant.variant_of gives the variant from which this variant was derived. If this value is not given, the variant is assumed to be derived from the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_variant.variant_of' _item.category_id variant _item.mandatory_code no _item_type.code code save_ ######################## DEPRECATED DATA ITEMS ######################## save__diffrn_detector_axis.id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_detector_axis.id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_element.center[1] _item_description.description ; The value of _diffrn_detector_element.center[1] is the X component of the distortion-corrected beam centre in millimetres from the (0, 0) (lower-left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. Because of ambiguity about the setting used to determine this center, use of this data item is deprecated. The data item _diffrn_data_frame.center_fast which is referenced to the detector coordinate system and not directly to the laboratory coordinate system should be used instead. ; _item.name '_diffrn_detector_element.center[1]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.center[2] _item_description.description ; The value of _diffrn_detector_element.center[2] is the Y component of the distortion-corrected beam centre in millimetres from the (0, 0) (lower-left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. Because of ambiguity about the setting used to determine this center, use of this data item is deprecated. The data item _diffrn_data_frame.center_slow which is referenced to the detector coordinate system and not directly to the laboratory coordinate system should be used instead. ; _item.name '_diffrn_detector_element.center[2]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_measurement_axis.id _item_description.description ; This data item is a pointer to _diffrn_measurement.id in the DIFFRN_MEASUREMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_measurement_axis.id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ ######################### DEPRECATED CATEGORY ######################### ##################### # DIFFRN_FRAME_DATA # ##################### save_DIFFRN_FRAME_DATA _category.description ; Data items in the DIFFRN_FRAME_DATA category record the details about each frame of data. The items in this category are now in the DIFFRN_DATA_FRAME category. The items in the DIFFRN_FRAME_DATA category are now deprecated. The items from this category are provided as aliases in the 1.0 dictionary or, in the case of _diffrn_frame_data.details, in the 1.4 dictionary. THESE ITEMS SHOULD NOT BE USED FOR NEW WORK. The items from the old category are provided in this dictionary for completeness but should not be used or cited. To avoid confusion, the example has been removed and the redundant parent-child links to other categories have been removed. ; _category.id diffrn_frame_data _category.mandatory_code no loop_ _category_key.name '_diffrn_frame_data.id' '_diffrn_frame_data.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; THE DIFFRN_FRAME_DATA category is deprecated and should not be used. ; ; # EXAMPLE REMOVED # ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_frame_data.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.array_id' _item.category_id diffrn_frame_data _item.mandatory_code implicit _item_type.code code save_ save__diffrn_frame_data.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.binary_id' _item.category_id diffrn_frame_data _item.mandatory_code implicit _item_type.code int save_ save__diffrn_frame_data.detector_element_id _item_description.description ; This item is a pointer to _diffrn_detector_element.id in the DIFFRN_DETECTOR_ELEMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.detector_element_id' _item.category_id diffrn_frame_data _item.mandatory_code yes _item_type.code code save_ save__diffrn_frame_data.id _item_description.description ; The value of _diffrn_frame_data.id must uniquely identify each complete frame of data. DEPRECATED -- DO NOT USE ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_frame_data.id' diffrn_frame_data yes _item_type.code code save_ save__diffrn_frame_data.details _item_description.description ; The value of _diffrn_data_frame.details should give a description of special aspects of each frame of data. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.details' _item.category_id diffrn_frame_data _item.mandatory_code no _item_type.code text save_ ################ END DEPRECATED SECTION ########### #################### ## ITEM_TYPE_LIST ## #################### # # # The regular expressions defined here are not compliant # with the POSIX 1003.2 standard as they include the # '\n' and '\t' special characters. These regular expressions # have been tested using version 0.12 of Richard Stallman's # GNU regular expression library in POSIX mode. # In order to allow presentation of a regular expression # in a text field concatenate any line ending in a backslash # with the following line, after discarding the backslash. # # A formal definition of the '\n' and '\t' special characters # is most properly done in the DDL, but for completeness, please # note that '\n' is the line termination character ('newline') # and '\t' is the horizontal tab character. There is a formal # ambiguity in the use of '\n' for line termination, in that # the intention is that the equivalent machine/OS-dependent line # termination character sequence should be accepted as a match, e.g. # # '\r' (control-M) under MacOS # '\n' (control-J) under Unix # '\r\n' (control-M control-J) under DOS and MS Windows # loop_ _item_type_list.code _item_type_list.primitive_code _item_type_list.construct _item_type_list.detail code char '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words ... ; ucode uchar '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words (case insensitive) ... ; line char '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; char item types / multi-word items ... ; uline uchar '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; char item types / multi-word items (case insensitive)... ; text char '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; text item types / multi-line text ... ; binary char ;\n--CIF-BINARY-FORMAT-SECTION--\n\ [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\ \n--CIF-BINARY-FORMAT-SECTION---- ; ; binary items are presented as MIME-like ascii-encoded sections in an imgCIF. In a CBF, raw octet streams are used to convey the same information. ; int numb '-?[0-9]+' ; int item types are the subset of numbers that are the negative or positive integers. ; float numb '-?(([0-9]+)[.]?|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?' ; float item types are the subset of numbers that are the floating point numbers. ; any char '.*' ; A catch all for items that may take any form... ; yyyy-mm-dd char ;\ [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9]?[0-9]\ ((T[0-2][0-9](:[0-5][0-9](:[0-5][0-9](.[0-9]+)?)?)?)?\ ([+-][0-5][0-9]:[0-5][0-9]))? ; ; Standard format for CIF date and time strings (see http://www.iucr.org/iucr-top/cif/spec/datetime.html), consisting of a yyyy-mm-dd date optionally followed by the character 'T' followed by a 24-hour clock time, optionally followed by a signed time-zone offset. The IUCr standard has been extended to allow for an optional decimal fraction on the seconds of time. Time is local time if no time-zone offset is given. Note that this type extends the mmCIF yyyy-mm-dd type but does not conform to the mmCIF yyyy-mm-dd:hh:mm type that uses a ':' in place if the 'T' specified by the IUCr standard. For reading, both forms should be accepted, but for writing, only the IUCr form should be used. For maximal compatibility, the special time zone indicator 'Z' (for 'zulu') should be accepted on reading in place of '+00:00' for GMT. ; ##################### ## ITEM_UNITS_LIST ## ##################### loop_ _item_units_list.code _item_units_list.detail # 'metres' 'metres' 'centimetres' 'centimetres (metres * 10^( -2)^)' 'millimetres' 'millimetres (metres * 10^( -3)^)' 'nanometres' 'nanometres (metres * 10^( -9)^)' 'angstroms' '\%Angstroms (metres * 10^(-10)^)' 'picometres' 'picometres (metres * 10^(-12)^)' 'femtometres' 'femtometres (metres * 10^(-15)^)' # 'reciprocal_metres' 'reciprocal metres (metres^(-1)^)' 'reciprocal_centimetres' 'reciprocal centimetres ((metres * 10^( -2)^)^(-1)^)' 'reciprocal_millimetres' 'reciprocal millimetres ((metres * 10^( -3)^)^(-1)^)' 'reciprocal_nanometres' 'reciprocal nanometres ((metres * 10^( -9)^)^(-1)^)' 'reciprocal_angstroms' 'reciprocal \%Angstroms ((metres * 10^(-10)^)^(-1)^)' 'reciprocal_picometres' 'reciprocal picometres ((metres * 10^(-12)^)^(-1)^)' # 'nanometres_squared' 'nanometres squared (metres * 10^( -9)^)^2^' 'angstroms_squared' '\%Angstroms squared (metres * 10^(-10)^)^2^' '8pi2_angstroms_squared' '8\p^2^ * \%Angstroms squared (metres * 10^(-10)^)^2^' 'picometres_squared' 'picometres squared (metres * 10^(-12)^)^2^' # 'nanometres_cubed' 'nanometres cubed (metres * 10^( -9)^)^3^' 'angstroms_cubed' '\%Angstroms cubed (metres * 10^(-10)^)^3^' 'picometres_cubed' 'picometres cubed (metres * 10^(-12)^)^3^' # 'kilopascals' 'kilopascals' 'gigapascals' 'gigapascals' # 'hours' 'hours' 'minutes' 'minutes' 'seconds' 'seconds' 'microseconds' 'microseconds' # 'degrees' 'degrees (of arc)' 'degrees_squared' 'degrees (of arc) squared' # 'degrees_per_minute' 'degrees (of arc) per minute' # 'celsius' 'degrees (of temperature) Celsius' 'kelvins' 'degrees (of temperature) Kelvin' # 'counts' 'counts' 'counts_per_photon' 'counts per photon' # 'electrons' 'electrons' # 'electrons_squared' 'electrons squared' # 'electrons_per_nanometres_cubed' ; electrons per nanometres cubed (electrons/(metres * 10^( -9)^)^(-3)^) ; 'electrons_per_angstroms_cubed' ; electrons per \%Angstroms cubed (electrons/(metres * 10^(-10)^)^(-3)^) ; 'electrons_per_picometres_cubed' ; electrons per picometres cubed (electrons/(metres * 10^(-12)^)^(-3)^) ; 'kilowatts' 'kilowatts' 'milliamperes' 'milliamperes' 'kilovolts' 'kilovolts' # 'pixels_per_element' '(image) pixels per (array) element' # 'arbitrary' ; arbitrary system of units. ; # loop_ _item_units_conversion.from_code _item_units_conversion.to_code _item_units_conversion.operator _item_units_conversion.factor ### 'metres' 'centimetres' '*' 1.0E+02 'metres' 'millimetres' '*' 1.0E+03 'metres' 'nanometres' '*' 1.0E+09 'metres' 'angstroms' '*' 1.0E+10 'metres' 'picometres' '*' 1.0E+12 'metres' 'femtometres' '*' 1.0E+15 # 'centimetres' 'metres' '*' 1.0E-02 'centimetres' 'millimetres' '*' 1.0E+01 'centimetres' 'nanometres' '*' 1.0E+07 'centimetres' 'angstroms' '*' 1.0E+08 'centimetres' 'picometres' '*' 1.0E+10 'centimetres' 'femtometres' '*' 1.0E+13 # 'millimetres' 'metres' '*' 1.0E-03 'millimetres' 'centimetres' '*' 1.0E-01 'millimetres' 'nanometres' '*' 1.0E+06 'millimetres' 'angstroms' '*' 1.0E+07 'millimetres' 'picometres' '*' 1.0E+09 'millimetres' 'femtometres' '*' 1.0E+12 # 'nanometres' 'metres' '*' 1.0E-09 'nanometres' 'centimetres' '*' 1.0E-07 'nanometres' 'millimetres' '*' 1.0E-06 'nanometres' 'angstroms' '*' 1.0E+01 'nanometres' 'picometres' '*' 1.0E+03 'nanometres' 'femtometres' '*' 1.0E+06 # 'angstroms' 'metres' '*' 1.0E-10 'angstroms' 'centimetres' '*' 1.0E-08 'angstroms' 'millimetres' '*' 1.0E-07 'angstroms' 'nanometres' '*' 1.0E-01 'angstroms' 'picometres' '*' 1.0E+02 'angstroms' 'femtometres' '*' 1.0E+05 # 'picometres' 'metres' '*' 1.0E-12 'picometres' 'centimetres' '*' 1.0E-10 'picometres' 'millimetres' '*' 1.0E-09 'picometres' 'nanometres' '*' 1.0E-03 'picometres' 'angstroms' '*' 1.0E-02 'picometres' 'femtometres' '*' 1.0E+03 # 'femtometres' 'metres' '*' 1.0E-15 'femtometres' 'centimetres' '*' 1.0E-13 'femtometres' 'millimetres' '*' 1.0E-12 'femtometres' 'nanometres' '*' 1.0E-06 'femtometres' 'angstroms' '*' 1.0E-05 'femtometres' 'picometres' '*' 1.0E-03 ### 'reciprocal_centimetres' 'reciprocal_metres' '*' 1.0E+02 'reciprocal_centimetres' 'reciprocal_millimetres' '*' 1.0E-01 'reciprocal_centimetres' 'reciprocal_nanometres' '*' 1.0E-07 'reciprocal_centimetres' 'reciprocal_angstroms' '*' 1.0E-08 'reciprocal_centimetres' 'reciprocal_picometres' '*' 1.0E-10 # 'reciprocal_millimetres' 'reciprocal_metres' '*' 1.0E+03 'reciprocal_millimetres' 'reciprocal_centimetres' '*' 1.0E+01 'reciprocal_millimetres' 'reciprocal_nanometres' '*' 1.0E-06 'reciprocal_millimetres' 'reciprocal_angstroms' '*' 1.0E-07 'reciprocal_millimetres' 'reciprocal_picometres' '*' 1.0E-09 # 'reciprocal_nanometres' 'reciprocal_metres' '*' 1.0E+09 'reciprocal_nanometres' 'reciprocal_centimetres' '*' 1.0E+07 'reciprocal_nanometres' 'reciprocal_millimetres' '*' 1.0E+06 'reciprocal_nanometres' 'reciprocal_angstroms' '*' 1.0E-01 'reciprocal_nanometres' 'reciprocal_picometres' '*' 1.0E-03 # 'reciprocal_angstroms' 'reciprocal_metres' '*' 1.0E+10 'reciprocal_angstroms' 'reciprocal_centimetres' '*' 1.0E+08 'reciprocal_angstroms' 'reciprocal_millimetres' '*' 1.0E+07 'reciprocal_angstroms' 'reciprocal_nanometres' '*' 1.0E+01 'reciprocal_angstroms' 'reciprocal_picometres' '*' 1.0E-02 # 'reciprocal_picometres' 'reciprocal_metres' '*' 1.0E+12 'reciprocal_picometres' 'reciprocal_centimetres' '*' 1.0E+10 'reciprocal_picometres' 'reciprocal_millimetres' '*' 1.0E+09 'reciprocal_picometres' 'reciprocal_nanometres' '*' 1.0E+03 'reciprocal_picometres' 'reciprocal_angstroms' '*' 1.0E+01 ### 'nanometres_squared' 'angstroms_squared' '*' 1.0E+02 'nanometres_squared' 'picometres_squared' '*' 1.0E+06 # 'angstroms_squared' 'nanometres_squared' '*' 1.0E-02 'angstroms_squared' 'picometres_squared' '*' 1.0E+04 'angstroms_squared' '8pi2_angstroms_squared' '*' 78.9568 # 'picometres_squared' 'nanometres_squared' '*' 1.0E-06 'picometres_squared' 'angstroms_squared' '*' 1.0E-04 ### 'nanometres_cubed' 'angstroms_cubed' '*' 1.0E+03 'nanometres_cubed' 'picometres_cubed' '*' 1.0E+09 # 'angstroms_cubed' 'nanometres_cubed' '*' 1.0E-03 'angstroms_cubed' 'picometres_cubed' '*' 1.0E+06 # 'picometres_cubed' 'nanometres_cubed' '*' 1.0E-09 'picometres_cubed' 'angstroms_cubed' '*' 1.0E-06 ### 'kilopascals' 'gigapascals' '*' 1.0E-06 'gigapascals' 'kilopascals' '*' 1.0E+06 ### 'hours' 'minutes' '*' 6.0E+01 'hours' 'seconds' '*' 3.6E+03 'hours' 'microseconds' '*' 3.6E+09 # 'minutes' 'hours' '/' 6.0E+01 'minutes' 'seconds' '*' 6.0E+01 'minutes' 'microseconds' '*' 6.0E+07 # 'seconds' 'hours' '/' 3.6E+03 'seconds' 'minutes' '/' 6.0E+01 'seconds' 'microseconds' '*' 1.0E+06 # 'microseconds' 'hours' '/' 3.6E+09 'microseconds' 'minutes' '/' 6.0E+07 'microseconds' 'seconds' '/' 1.0E+06 ### 'celsius' 'kelvins' '-' 273.0 'kelvins' 'celsius' '+' 273.0 ### 'electrons_per_nanometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E+03 'electrons_per_nanometres_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+09 # 'electrons_per_angstroms_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-03 'electrons_per_angstroms_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+06 # 'electrons_per_picometres_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-09 'electrons_per_picometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E-06 ### ######################## ## DICTIONARY_HISTORY ## ######################## loop_ _dictionary_history.version _dictionary_history.update _dictionary_history.revision 1.6.3 2010-08-26 ; Cummulative corrections from 1.6.0, 1, 2 drafts (HJB) + Move descriptive dictionary comments into _datablock.description with catgeory tree described + add default _array_data.array_id value of 1 + add option of CBF_BACKGROUND_OFFSET_DELTA compression + add VARIANT catgeory and tags + add DIFFRN_SCAN_FRAME_MONITOR category ; 1.5.4 2007-07-28 ; Typographics corrections (HJB) + Corrected embedded degree characters to \% + Corrected embedded Aring to \%A + Added trailing ^ for a power + Removed 2 cases of a space after an underscore in tag name. ; 1.5.3 2007-07-08 ; Changes to support SLS miniCBF and suggestions from the 24 May 07 BNL imgCIF workshop (HJB) + Added new data items '_array_data.header_contents', '_array_data.header_convention', '_diffrn_data_frame.center_fast', '_diffrn_data_frame.center_slow', '_diffrn_data_frame.center_units', '_diffrn_measurement.sample_detector_distance', '_diffrn_measurement.sample_detector_voffset + Deprecated data items '_diffrn_detector_element.center[1]', '_diffrn_detector_element.center[2]' + Added comments and example on miniCBF + Changed all array_id data items to implicit ; 1.5.2 2007-05-06 ; Further clarifications of the coordinate system. (HJB) ; 1.5.1 2007-04-26 ; Improve defintion of X-axis to cover the case of no goniometer and clean up more line folds (HJB) ; 1.5 2007-07-25 ; This is a cummulative list of the changes proposed since the imgCIF workshop in Hawaii in July 2006. It is the result of contributions by H. J. Bernstein, A. Hammersley, J. Wright and W. Kabsch. 2007-02-19 Consolidated changes (edited by HJB) + Added new data items '_array_structure.compression_type_flag', '_array_structure_list_axis.fract_displacement', '_array_structure_list_axis.displacement_increment', '_array_structure_list_axis.reference_angle', '_array_structure_list_axis.reference_displacement', '_axis.system', '_diffrn_detector_element.reference_center_fast', '_diffrn_detector_element.reference_center_slow', '_diffrn_scan_axis.reference_angle', '_diffrn_scan_axis.reference_displacement', '_map.details', '_map.diffrn_id', '_map.entry_id', '_map.id', '_map_segment.array_id', '_map_segment.binary_id', '_map_segment.mask_array_id', '_map_segment.mask_binary_id', '_map_segment.id', '_map_segment.map_id', '_map_segment.details. + Change type of '_array_structure.byte_order' and '_array_structure.compression_type' to ucode to make these values case-insensitive + Add values 'packed_v2' and 'byte_offset' to enumeration of values for '_array_structure.compression_type' + Add to definitions for the binary data type to handle new compression types, maps, and a variety of new axis types. 2007-07-25 Cleanup of typos for formal release (HJB) + Corrected text fields for reference_ tag descriptions that were off by one column + Fix typos in comments listing fract_ tags + Changed name of release from 1.5_DRAFT to 1.5 + Fix unclosed text fields in various map definitions ; 1.4 2006-07-04 ; This is a change to reintegrate all changes made in the course of publication of ITVG, by the RCSB from April 2005 through August 2008 and changes for the 2006 imgCIF workshop in Hawaii. 2006-07-04 Consolidated changes for the 2006 imgCIF workshop (edited by HJB) + Correct type of '_array_structure_list.direction' from 'int' to 'code'. + Added new data items suggested by CN '_diffrn_data_frame.details' '_array_intensities.pixel_fast_bin_size', '_array_intensities.pixel_slow_bin_size and '_array_intensities.pixel_binning_method + Added deprecated item for completeness '_diffrn_frame_data.details' + Added entry for missing item in contents list '_array_structure_list_axis.displacement' + Added new MIME type X-BASE32K based on work by VL, KM, GD, HJB + Correct description of MIME boundary delimiter to start in column 1. + General cleanup of text fields to conform to changes for ITVG by removing empty lines at start and finish of text field. + Amend example for ARRAY_INTENSITIES to include binning. + Add local copy of type specification (as 'code') for all children of '_diffrn.id'. + For consistency, change all references to 'pi' to '\p' and all references to 'Angstroms' to '\%Angstroms'. + Clean up all powers to use IUCr convention of '^power^', as in '10^3^' for '10**3'. + Update 'yyyy-mm-dd' type regex to allow truncation from the right and improve comments to explain handling of related mmCIF 'yyyy-mm-dd:hh:mm' type, and use of 'Z' for GMT time zone. 2005-03-08 and 2004-08-08 fixed cases where _item_units.code used instead of _item_type.code (JDW) 2004-04-15 fixed item ordering in _diffrn_measurement_axis.measurement_id added sub_category 'vector' (JDW) ; 1.3.2 2005-06-25 ; 2005-06-25 ITEM_TYPE_LIST: code, ucode, line, uline regexps updated to those of current mmCIF; float modified by allowing integers terminated by a point as valid. The 'time' part of yyyy-mm-dd types made optional in the regexp. (BM) 2005-06-17 Minor corrections as for proofs for IT G Chapter 4.6 (NJA) 2005-02-21 Minor corrections to spelling and punctuation (NJA) 2005-01-08 Changes as per Nicola Ashcroft. + Updated example 1 for DIFFRN_MEASUREMENT to agree with mmCIF. + Spelled out "micrometres" for "um" and "millimetres" for "mm". + Removed phrase "which may be stored" from ARRAY_STRUCTURE description. + Removed unused 'byte-offsets' compressions and updated cites to ITVG for '_array_structure.compression_type'. (HJB) ; 1.3.1 2003-08-13 ; Changes as per Frances C. Bernstein. + Identify initials. + Adopt British spelling for centre in text. + Set \p and \%Angstrom and powers. + Clean up commas and unclear wordings. + Clean up tenses in history. Changes as per Gotzon Madariaga. + Fix the ARRAY_DATA example to align '_array_data.binary_id' and X-Binary-ID. + Add a range to '_array_intensities.gain_esd'. + In the example of DIFFRN_DETECTOR_ELEMENT, '_diffrn_detector_element.id' and '_diffrn_detector_element.detector_id' interchanged. + Fix typos for direction, detector and axes. + Clarify description of polarisation. + Clarify axes in '_diffrn_detector_element.center[1]' '_diffrn_detector_element.center[2]'. + Add local item types for items that are pointers. (HJB) ; 1.3.0 2003-07-24 ; Changes as per Brian McMahon. + Consistently quote tags embedded in text. + Clean up introductory comments. + Adjust line lengths to fit in 80 character window. + Fix several descriptions in AXIS category which referred to '_axis.type' instead of the current item. + Fix erroneous use of deprecated item '_diffrn_detector_axis.id' in examples for DIFFRN_SCAN_AXIS. + Add deprecated items '_diffrn_detector_axis.id' and '_diffrn_measurement_axis.id'. (HJB) ; 1.2.4 2003-07-14 ; Changes as per I. David Brown. + Enhance descriptions in DIFFRN_SCAN_AXIS to make them less dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS. + Provide a copy of the deprecated DIFFRN_FRAME_DATA category for completeness. (HJB) ; 1.2.3 2003-07-03 ; Cleanup to conform to ITVG. + Correct sign error in ..._cubed units. + Correct '_diffrn_radiation.polarisn_norm' range. (HJB) ; 1.2.2 2003-03-10 ; Correction of typos in various DIFFRN_SCAN_AXIS descriptions. (HJB) ; 1.2.1 2003-02-22 ; Correction of ATOM_ for ARRAY_ typos in various descriptions. (HJB) ; 1.2 2003-02-07 ; Corrections to encodings (remove extraneous hyphens) remove extraneous underscore in '_array_structure.encoding_type' enumeration. Correct typos in items units list. (HJB) ; 1.1.3 2001-04-19 ; Another typo corrections by Wilfred Li, and cleanup by HJB. ; 1.1.2 2001-03-06 ; Several typo corrections by Wilfred Li. ; 1.1.1 2001-02-16 ; Several typo corrections by JW. ; 1.1 2001-02-06 ; Draft resulting from discussions on header for use at NSLS. (HJB) + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME. + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'. + Add '_diffrn_measurement_axis.measurement_device' and change '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'. + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source', '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm', '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end', '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr', '_diffrn_scan_axis.displacement_rstrt_incr', '_diffrn_scan_frame_axis.angle_increment', '_diffrn_scan_frame_axis.angle_rstrt_incr', '_diffrn_scan_frame_axis.displacement', '_diffrn_scan_frame_axis.displacement_increment',and '_diffrn_scan_frame_axis.displacement_rstrt_incr'. + Add '_diffrn_measurement.device' to category key. + Update yyyy-mm-dd to allow optional time with fractional seconds for time stamps. + Fix typos caught by RS. + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to allow for coupled axes, as in spiral scans. + Add examples for fairly complete headers thanks to R. Sweet and P. Ellis. ; 1.0 2000-12-21 ; Release version - few typos and tidying up. (BM & HJB) + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end of dictionary. + Alphabetize dictionary. ; 0.7.1 2000-09-29 ; Cleanup fixes. (JW) + Correct spelling of diffrn_measurement_axis in '_axis.id' + Correct ordering of uses of '_item.mandatory_code' and '_item_default.value'. ; 0.7.0 2000-09-09 ; Respond to comments by I. David Brown. (HJB) + Add further comments on '\n' and '\t'. + Update ITEM_UNITS_LIST by taking section from mmCIF dictionary and adding metres. Change 'meter' to 'metre' throughout. + Add missing enumerations to '_array_structure.compression_type' and make 'none' the default. + Remove parent-child relationship between '_array_structure_list.index' and '_array_structure_list.precedence'. + Improve alphabetization. + Fix '_array_intensities_gain.esd' related function. + Improve comments in AXIS. + Fix DIFFRN_FRAME_DATA example. + Remove erroneous DIFFRN_MEASUREMENT example. + Add '_diffrn_measurement_axis.id' to the category key. ; 0.6.0 1999-01-14 ; Remove redundant information for ENC_NONE data. (HJB) + After the D5 remove binary section identifier, size and compression type. + Add Control-L to header. ; 0.5.1 1999-01-03 ; Cleanup of typos and syntax errors. (HJB) + Cleanup example details for DIFFRN_SCAN category. + Add missing quote marks for '_diffrn_scan.id' definition. ; 0.5 1999-01-01 ; Modifications for axis definitions and reduction of binary header. (HJB) + Restore '_diffrn_detector.diffrn_id' to DIFFRN_DETECTOR KEY. + Add AXIS category. + Bring in complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories from cif_mm.dic for clarity. + Change '_array_structure.encoding_type' from type code to uline and added X-Binary-Element-Type to MIME header. + Add detector beam centre '_diffrn_detector_element.center[1]' and '_diffrn_detector_element.center[2]'. + Correct item name of '_diffrn_refln.frame_id'. + Replace reference to '_array_intensities.undefined' by '_array_intensities.undefined_value'. + Replace references to '_array_intensity.scaling' with '_array_intensities.scaling'. + Add DIFFRN_SCAN... categories. ; 0.4 1998-08-11 ; Modifications to the 0.3 imgCIF draft. (HJB) + Reflow comment lines over 80 characters and corrected typos. + Update examples and descriptions of MIME encoded data. + Change name to cbfext98.dic. ; 0.3 1998-07-04 ; Modifications for imgCIF. (HJB) + Add binary type, which is a text field containing a variant on MIME encoded data. + Change type of '_array_data.data' to binary and specify internal structure of raw binary data. + Add '_array_data.binary_id', and make '_diffrn_frame_data.binary_id' and '_array_intensities.binary_id' into pointers to this item. ; 0.2 1997-12-02 ; Modifications to the CBF draft. (JW) + Add category hierarchy for describing frame data developed from discussions at the BNL imgCIF Workshop Oct 1997. The following changes are made in implementing the workshop draft. Category DIFFRN_ARRAY_DATA is renamed to DIFFRN_FRAME_DATA. Category DIFFRN_FRAME_TYPE is renamed to DIFFRN_DETECTOR_ELEMENT. The parent item for '_diffrn_frame_data.array_id' is changed from '_array_structure_list.array_id' to '_array_structure.id'. Item '_diffrn_detector.array_id' is deleted. + Add data item '_diffrn_frame_data.binary_id' to identify data groups within a binary section. The formal identification of the binary section is still fuzzy. ; 0.1 1997-01-24 ; First draft of this dictionary in DDL 2.1 compliant format by John Westbrook (JW). This version is adapted from the Crystallographic Binary File (CBF) Format Draft Proposal provided by Andy Hammersley (AH). Modifications to the CBF draft. (JW) + In this version the array description has been cast in the categories ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. These categories have been generalized to describe array data of arbitrary dimension. + Array data in this description are contained in the category ARRAY_DATA. This departs from the CBF notion of data existing in some special comment. In this description, data are handled as an ordinary data item encapsulated in a character data type. Although data this manner deviates from CIF conventions, it does not violate any DDL 2.1 rules. DDL 2.1 regular expressions can be used to define the binary representation which will permit some level of data validation. In this version, the placeholder type code "any" has been used. This translates to a regular expression which will match any pattern. It should be noted that DDL 2.1 already supports array data objects although these have not been used in the current mmCIF dictionary. It may be possible to use the DDL 2.1 ITEM_STRUCTURE and ITEM_STRUCTURE_LIST categories to provide the information that is carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. By moving the array structure to the DDL level it would be possible to define an array type as well as a regular expression defining the data format. + Multiple array sections can be properly handled within a single datablock. ; #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof ./CBFlib-0.9.2.2/doc/cif_img_1.6.html0000777000076500007650000000000011603751102021324 2cif_img_1.6.3_26Aug10.htmlustar yayayaya./CBFlib-0.9.2.2/doc/Iarray_structure_list.index.html0000644000076500007650000000523111603702115020742 0ustar yayayaya (IUCr) CIF Definition save__array_structure_list.index

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _array_structure_list.index

    Name:
    '_array_structure_list.index'

    Definition:

            Identifies the one-based index of the row or column in the
                   array structure.
    
    

    Type: int

    Mandatory item: yes

    _array_element_size.index

    The permitted range is [1, infinity)

    Category: array_structure_list

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_data_frame.details.html0000644000076500007650000001051411603702115020402 0ustar yayayaya (IUCr) CIF Definition save__diffrn_data_frame.details

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_data_frame.details

    Name:
    '_diffrn_data_frame.details'

    Definition:

            The value of _diffrn_data_frame.details should give a
                   description of special aspects of each frame of data.
    
                   This is an appropriate location in which to record
                   information from vendor headers as presented in those
                   headers, but it should never be used as a substitute
                   for providing the fully parsed information within
                   the appropriate imgCIF/CBF categories.
    
                   Normally, when a conversion from a miniCBF has been done
                   the data from '_array_data.header_convention'
                   should be transferred to this data item and
                   '_array_data.header_convention'
                   should be removed.
    
    
    Example:

    ;
     HEADER_BYTES = 512;
     DIM = 2;
     BYTE_ORDER = big_endian;
     TYPE = unsigned_short;
     SIZE1 = 3072;
     SIZE2 = 3072;
     PIXEL_SIZE = 0.102588;
     BIN = 2x2;
     DETECTOR_SN = 901;
     TIME = 29.945155;
     DISTANCE = 200.000000;
     PHI = 85.000000;
     OSC_START = 85.000000;
     OSC_RANGE = 1.000000;
     WAVELENGTH = 0.979381;
     BEAM_CENTER_X = 157.500000;
     BEAM_CENTER_Y = 157.500000;
     PIXEL SIZE = 0.102588;
     OSCILLATION RANGE = 1;
     EXPOSURE TIME = 29.9452;
     TWO THETA = 0;
     BEAM CENTRE = 157.5 157.5;
    ;
    Example of header information extracted from an ADSC Quantum 315 detector header by CBFlib_0.7.6. Image provided by Chris Nielsen of ADSC from a data collection at SSRL beamline 1-5.

    Type: text

    Mandatory item: no

    Alias:
    _diffrn_frame_data.details (cif_img.dic version 1.4)

    Category: diffrn_data_frame

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_measurement.method.html0000644000076500007650000000536711603702115020511 0ustar yayayaya (IUCr) CIF Definition save__diffrn_measurement.method

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_measurement.method

    Name:
    '_diffrn_measurement.method'

    Definition:

            Method used to measure intensities.
    
    
    Example:

    'profile data from theta/2theta (\q/2\q) scans'

    Type: text

    Mandatory item: no

    Alias:
    _diffrn_measurement_method (cif_core.dic version 2.0.1)

    Category: diffrn_measurement

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_detector_element.reference_center_fast.html0000644000076500007650000000724711603702115024540 0ustar yayayaya (IUCr) CIF Definition save__diffrn_detector_element.reference_center_fast

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_detector_element.reference_center_fast

    Name:
    '_diffrn_detector_element.reference_center_fast'

    Definition:

           The value of _diffrn_detector_element.reference_center_fast is
                  the fast index axis beam center position relative to the detector
                  element face in the units specified in the data item
                  '_diffrn_detector_element.reference_center_units' along the fast
                  axis of the detector from the center of the first pixel to
                  the point at which the Z-axis (which should be colinear with the
                  beam) intersects the face of the detector, if in fact is does.
                  At the time of the measurement all settings of the detector
                  positioner should be at their reference settings.  If more than
                  one reference setting has been used the value given whould be
                  representive of the beam center as determined from the ensemble
                  of settings.
    
                  It is important to note that for measurements in millimetres,
                  the sense of the axis is used, rather than the sign of the
                  pixel-to-pixel increments.
    
    
    

    Type: float

    Mandatory item: no

    Category: diffrn_detector_element

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_frame_data.array_id.html0000644000076500007650000000523611603702115020554 0ustar yayayaya (IUCr) CIF Definition save__diffrn_frame_data.array_id

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_frame_data.array_id

    Name:
    '_diffrn_frame_data.array_id'

    Definition:

           This item is a pointer to _array_structure.id in the
                  ARRAY_STRUCTURE category.
    
                  DEPRECATED -- DO NOT USE
    
    

    Type: code

    Mandatory item: implicit

    Category: diffrn_frame_data

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Cdiffrn_refln.html0000644000076500007650000000517711603702115016004 0ustar yayayaya (IUCr) CIF Definition save_diffrn_refln

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    Category DIFFRN_REFLN

    Name:
    'diffrn_refln'

    Description:

        This category redefinition has been added to extend the key of
         the standard DIFFRN_REFLN category.
    
    
    Category groups:
        inclusive_group
        diffrn_group
    Category key:
        _diffrn_refln.frame_id

    Mandatory category: no

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/CBFlib_NOTICES.html0000644000076500007650000016452411603702115015512 0ustar yayayaya CBFlib_NOTICES.html

    CBFlib Notices

    COPYING

    All of the CBFlib 0.7.7 package may be distributed under the terms of the GNU General Public License (the GPL), see

    Alternatively most of the CBFlib 0.7.7 package may be distributed under the terms of the GNU Lesser General Public License (the LGPL), see

    The portions that may be distributed under the LGPL indentified as such in the comments of the relevant files, and include the portions constituting the API, but do not include the documentation nor does it include the example programs. The documentation and examples may only be distributed under the GPL.



    THE FIRST ALTERNATIVE LICENSE FOR ALL OF CBFLIB (GPL)
    (Valid for versions of CBFlib starting with release 0.7.5)

    ========================== GPL STARTS HERE =================================
    		    GNU GENERAL PUBLIC LICENSE
    		       Version 2, June 1991
    
     Copyright (C) 1989, 1991 Free Software Foundation, Inc.
                           59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
     Everyone is permitted to copy and distribute verbatim copies
     of this license document, but changing it is not allowed.
    
    			    Preamble
    
      The licenses for most software are designed to take away your
    freedom to share and change it.  By contrast, the GNU General Public
    License is intended to guarantee your freedom to share and change free
    software--to make sure the software is free for all its users.  This
    General Public License applies to most of the Free Software
    Foundation's software and to any other program whose authors commit to
    using it.  (Some other Free Software Foundation software is covered by
    the GNU Library General Public License instead.)  You can apply it to
    your programs, too.
    
      When we speak of free software, we are referring to freedom, not
    price.  Our General Public Licenses are designed to make sure that you
    have the freedom to distribute copies of free software (and charge for
    this service if you wish), that you receive source code or can get it
    if you want it, that you can change the software or use pieces of it
    in new free programs; and that you know you can do these things.
    
      To protect your rights, we need to make restrictions that forbid
    anyone to deny you these rights or to ask you to surrender the rights.
    These restrictions translate to certain responsibilities for you if you
    distribute copies of the software, or if you modify it.
    
      For example, if you distribute copies of such a program, whether
    gratis or for a fee, you must give the recipients all the rights that
    you have.  You must make sure that they, too, receive or can get the
    source code.  And you must show them these terms so they know their
    rights.
    
      We protect your rights with two steps: (1) copyright the software, and
    (2) offer you this license which gives you legal permission to copy,
    distribute and/or modify the software.
    
      Also, for each author's protection and ours, we want to make certain
    that everyone understands that there is no warranty for this free
    software.  If the software is modified by someone else and passed on, we
    want its recipients to know that what they have is not the original, so
    that any problems introduced by others will not reflect on the original
    authors' reputations.
    
      Finally, any free program is threatened constantly by software
    patents.  We wish to avoid the danger that redistributors of a free
    program will individually obtain patent licenses, in effect making the
    program proprietary.  To prevent this, we have made it clear that any
    patent must be licensed for everyone's free use or not licensed at all.
    
      The precise terms and conditions for copying, distribution and
    modification follow.
    
    		    GNU GENERAL PUBLIC LICENSE
       TERMS AND CONDITIONS FOR COPYING, DISTRIBUTION AND MODIFICATION
    
      0. This License applies to any program or other work which contains
    a notice placed by the copyright holder saying it may be distributed
    under the terms of this General Public License.  The "Program", below,
    refers to any such program or work, and a "work based on the Program"
    means either the Program or any derivative work under copyright law:
    that is to say, a work containing the Program or a portion of it,
    either verbatim or with modifications and/or translated into another
    language.  (Hereinafter, translation is included without limitation in
    the term "modification".)  Each licensee is addressed as "you".
    
    Activities other than copying, distribution and modification are not
    covered by this License; they are outside its scope.  The act of
    running the Program is not restricted, and the output from the Program
    is covered only if its contents constitute a work based on the
    Program (independent of having been made by running the Program).
    Whether that is true depends on what the Program does.
    
      1. You may copy and distribute verbatim copies of the Program's
    source code as you receive it, in any medium, provided that you
    conspicuously and appropriately publish on each copy an appropriate
    copyright notice and disclaimer of warranty; keep intact all the
    notices that refer to this License and to the absence of any warranty;
    and give any other recipients of the Program a copy of this License
    along with the Program.
    
    You may charge a fee for the physical act of transferring a copy, and
    you may at your option offer warranty protection in exchange for a fee.
    
      2. You may modify your copy or copies of the Program or any portion
    of it, thus forming a work based on the Program, and copy and
    distribute such modifications or work under the terms of Section 1
    above, provided that you also meet all of these conditions:
    
        a) You must cause the modified files to carry prominent notices
        stating that you changed the files and the date of any change.
    
        b) You must cause any work that you distribute or publish, that in
        whole or in part contains or is derived from the Program or any
        part thereof, to be licensed as a whole at no charge to all third
        parties under the terms of this License.
    
        c) If the modified program normally reads commands interactively
        when run, you must cause it, when started running for such
        interactive use in the most ordinary way, to print or display an
        announcement including an appropriate copyright notice and a
        notice that there is no warranty (or else, saying that you provide
        a warranty) and that users may redistribute the program under
        these conditions, and telling the user how to view a copy of this
        License.  (Exception: if the Program itself is interactive but
        does not normally print such an announcement, your work based on
        the Program is not required to print an announcement.)
    
    These requirements apply to the modified work as a whole.  If
    identifiable sections of that work are not derived from the Program,
    and can be reasonably considered independent and separate works in
    themselves, then this License, and its terms, do not apply to those
    sections when you distribute them as separate works.  But when you
    distribute the same sections as part of a whole which is a work based
    on the Program, the distribution of the whole must be on the terms of
    this License, whose permissions for other licensees extend to the
    entire whole, and thus to each and every part regardless of who wrote it.
    
    Thus, it is not the intent of this section to claim rights or contest
    your rights to work written entirely by you; rather, the intent is to
    exercise the right to control the distribution of derivative or
    collective works based on the Program.
    
    In addition, mere aggregation of another work not based on the Program
    with the Program (or with a work based on the Program) on a volume of
    a storage or distribution medium does not bring the other work under
    the scope of this License.
    
      3. You may copy and distribute the Program (or a work based on it,
    under Section 2) in object code or executable form under the terms of
    Sections 1 and 2 above provided that you also do one of the following:
    
        a) Accompany it with the complete corresponding machine-readable
        source code, which must be distributed under the terms of Sections
        1 and 2 above on a medium customarily used for software interchange; or,
    
        b) Accompany it with a written offer, valid for at least three
        years, to give any third party, for a charge no more than your
        cost of physically performing source distribution, a complete
        machine-readable copy of the corresponding source code, to be
        distributed under the terms of Sections 1 and 2 above on a medium
        customarily used for software interchange; or,
    
        c) Accompany it with the information you received as to the offer
        to distribute corresponding source code.  (This alternative is
        allowed only for noncommercial distribution and only if you
        received the program in object code or executable form with such
        an offer, in accord with Subsection b above.)
    
    The source code for a work means the preferred form of the work for
    making modifications to it.  For an executable work, complete source
    code means all the source code for all modules it contains, plus any
    associated interface definition files, plus the scripts used to
    control compilation and installation of the executable.  However, as a
    special exception, the source code distributed need not include
    anything that is normally distributed (in either source or binary
    form) with the major components (compiler, kernel, and so on) of the
    operating system on which the executable runs, unless that component
    itself accompanies the executable.
    
    If distribution of executable or object code is made by offering
    access to copy from a designated place, then offering equivalent
    access to copy the source code from the same place counts as
    distribution of the source code, even though third parties are not
    compelled to copy the source along with the object code.
    
      4. You may not copy, modify, sublicense, or distribute the Program
    except as expressly provided under this License.  Any attempt
    otherwise to copy, modify, sublicense or distribute the Program is
    void, and will automatically terminate your rights under this License.
    However, parties who have received copies, or rights, from you under
    this License will not have their licenses terminated so long as such
    parties remain in full compliance.
    
      5. You are not required to accept this License, since you have not
    signed it.  However, nothing else grants you permission to modify or
    distribute the Program or its derivative works.  These actions are
    prohibited by law if you do not accept this License.  Therefore, by
    modifying or distributing the Program (or any work based on the
    Program), you indicate your acceptance of this License to do so, and
    all its terms and conditions for copying, distributing or modifying
    the Program or works based on it.
    
      6. Each time you redistribute the Program (or any work based on the
    Program), the recipient automatically receives a license from the
    original licensor to copy, distribute or modify the Program subject to
    these terms and conditions.  You may not impose any further
    restrictions on the recipients' exercise of the rights granted herein.
    You are not responsible for enforcing compliance by third parties to
    this License.
    
      7. If, as a consequence of a court judgment or allegation of patent
    infringement or for any other reason (not limited to patent issues),
    conditions are imposed on you (whether by court order, agreement or
    otherwise) that contradict the conditions of this License, they do not
    excuse you from the conditions of this License.  If you cannot
    distribute so as to satisfy simultaneously your obligations under this
    License and any other pertinent obligations, then as a consequence you
    may not distribute the Program at all.  For example, if a patent
    license would not permit royalty-free redistribution of the Program by
    all those who receive copies directly or indirectly through you, then
    the only way you could satisfy both it and this License would be to
    refrain entirely from distribution of the Program.
    
    If any portion of this section is held invalid or unenforceable under
    any particular circumstance, the balance of the section is intended to
    apply and the section as a whole is intended to apply in other
    circumstances.
    
    It is not the purpose of this section to induce you to infringe any
    patents or other property right claims or to contest validity of any
    such claims; this section has the sole purpose of protecting the
    integrity of the free software distribution system, which is
    implemented by public license practices.  Many people have made
    generous contributions to the wide range of software distributed
    through that system in reliance on consistent application of that
    system; it is up to the author/donor to decide if he or she is willing
    to distribute software through any other system and a licensee cannot
    impose that choice.
    
    This section is intended to make thoroughly clear what is believed to
    be a consequence of the rest of this License.
    
      8. If the distribution and/or use of the Program is restricted in
    certain countries either by patents or by copyrighted interfaces, the
    original copyright holder who places the Program under this License
    may add an explicit geographical distribution limitation excluding
    those countries, so that distribution is permitted only in or among
    countries not thus excluded.  In such case, this License incorporates
    the limitation as if written in the body of this License.
    
      9. The Free Software Foundation may publish revised and/or new versions
    of the General Public License from time to time.  Such new versions will
    be similar in spirit to the present version, but may differ in detail to
    address new problems or concerns.
    
    Each version is given a distinguishing version number.  If the Program
    specifies a version number of this License which applies to it and "any
    later version", you have the option of following the terms and conditions
    either of that version or of any later version published by the Free
    Software Foundation.  If the Program does not specify a version number of
    this License, you may choose any version ever published by the Free Software
    Foundation.
    
      10. If you wish to incorporate parts of the Program into other free
    programs whose distribution conditions are different, write to the author
    to ask for permission.  For software which is copyrighted by the Free
    Software Foundation, write to the Free Software Foundation; we sometimes
    make exceptions for this.  Our decision will be guided by the two goals
    of preserving the free status of all derivatives of our free software and
    of promoting the sharing and reuse of software generally.
    
    			    NO WARRANTY
    
      11. BECAUSE THE PROGRAM IS LICENSED FREE OF CHARGE, THERE IS NO WARRANTY
    FOR THE PROGRAM, TO THE EXTENT PERMITTED BY APPLICABLE LAW.  EXCEPT WHEN
    OTHERWISE STATED IN WRITING THE COPYRIGHT HOLDERS AND/OR OTHER PARTIES
    PROVIDE THE PROGRAM "AS IS" WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESSED
    OR IMPLIED, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF
    MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE.  THE ENTIRE RISK AS
    TO THE QUALITY AND PERFORMANCE OF THE PROGRAM IS WITH YOU.  SHOULD THE
    PROGRAM PROVE DEFECTIVE, YOU ASSUME THE COST OF ALL NECESSARY SERVICING,
    REPAIR OR CORRECTION.
    
      12. IN NO EVENT UNLESS REQUIRED BY APPLICABLE LAW OR AGREED TO IN WRITING
    WILL ANY COPYRIGHT HOLDER, OR ANY OTHER PARTY WHO MAY MODIFY AND/OR
    REDISTRIBUTE THE PROGRAM AS PERMITTED ABOVE, BE LIABLE TO YOU FOR DAMAGES,
    INCLUDING ANY GENERAL, SPECIAL, INCIDENTAL OR CONSEQUENTIAL DAMAGES ARISING
    OUT OF THE USE OR INABILITY TO USE THE PROGRAM (INCLUDING BUT NOT LIMITED
    TO LOSS OF DATA OR DATA BEING RENDERED INACCURATE OR LOSSES SUSTAINED BY
    YOU OR THIRD PARTIES OR A FAILURE OF THE PROGRAM TO OPERATE WITH ANY OTHER
    PROGRAMS), EVEN IF SUCH HOLDER OR OTHER PARTY HAS BEEN ADVISED OF THE
    POSSIBILITY OF SUCH DAMAGES.
    
    		     END OF TERMS AND CONDITIONS
    
    	    How to Apply These Terms to Your New Programs
    
      If you develop a new program, and you want it to be of the greatest
    possible use to the public, the best way to achieve this is to make it
    free software which everyone can redistribute and change under these terms.
    
      To do so, attach the following notices to the program.  It is safest
    to attach them to the start of each source file to most effectively
    convey the exclusion of warranty; and each file should have at least
    the "copyright" line and a pointer to where the full notice is found.
    
        
        Copyright (C)   
    
        This program is free software; you can redistribute it and/or modify
        it under the terms of the GNU General Public License as published by
        the Free Software Foundation; either version 2 of the License, or
        (at your option) any later version.
    
        This program is distributed in the hope that it will be useful,
        but WITHOUT ANY WARRANTY; without even the implied warranty of
        MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
        GNU General Public License for more details.
    
        You should have received a copy of the GNU General Public License
        along with this program; if not, write to the Free Software
        Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
    
    
    Also add information on how to contact you by electronic and paper mail.
    
    If the program is interactive, make it output a short notice like this
    when it starts in an interactive mode:
    
        Gnomovision version 69, Copyright (C) year name of author
        Gnomovision comes with ABSOLUTELY NO WARRANTY; for details type `show w'.
        This is free software, and you are welcome to redistribute it
        under certain conditions; type `show c' for details.
    
    The hypothetical commands `show w' and `show c' should show the appropriate
    parts of the General Public License.  Of course, the commands you use may
    be called something other than `show w' and `show c'; they could even be
    mouse-clicks or menu items--whatever suits your program.
    
    You should also get your employer (if you work as a programmer) or your
    school, if any, to sign a "copyright disclaimer" for the program, if
    necessary.  Here is a sample; alter the names:
    
      Yoyodyne, Inc., hereby disclaims all copyright interest in the program
      `Gnomovision' (which makes passes at compilers) written by James Hacker.
    
      , 1 April 1989
      Ty Coon, President of Vice
    
    This General Public License does not permit incorporating your program into
    proprietary programs.  If your program is a subroutine library, you may
    consider it more useful to permit linking proprietary applications with the
    library.  If this is what you want to do, use the GNU Library General
    Public License instead of this License.
    
    =========================== GPL ENDS HERE ==================================	
    



    THE SECOND ALTERNATIVE LICENSE FOR CERTAIN PORTIONS OF CBFLIB
    INCLUDING THE API ITSELF,
    BUT NOT THE DOCUMENTATION AND NOT THE EXAMPLES (LGPL)
    (Valid for versions of CBFlib starting with release 0.7.5)

    ========================== LGPL STARTS HERE ================================
    		  GNU LESSER GENERAL PUBLIC LICENSE
    		       Version 2.1, February 1999
    
     Copyright (C) 1991, 1999 Free Software Foundation, Inc.
         51 Franklin St, Fifth Floor, Boston, MA  02110-1301  USA
     Everyone is permitted to copy and distribute verbatim copies
     of this license document, but changing it is not allowed.
    
    [This is the first released version of the Lesser GPL.  It also counts
     as the successor of the GNU Library Public License, version 2, hence
     the version number 2.1.]
    
    			    Preamble
    
      The licenses for most software are designed to take away your
    freedom to share and change it.  By contrast, the GNU General Public
    Licenses are intended to guarantee your freedom to share and change
    free software--to make sure the software is free for all its users.
    
      This license, the Lesser General Public License, applies to some
    specially designated software packages--typically libraries--of the
    Free Software Foundation and other authors who decide to use it.  You
    can use it too, but we suggest you first think carefully about whether
    this license or the ordinary General Public License is the better
    strategy to use in any particular case, based on the explanations below.
    
      When we speak of free software, we are referring to freedom of use,
    not price.  Our General Public Licenses are designed to make sure that
    you have the freedom to distribute copies of free software (and charge
    for this service if you wish); that you receive source code or can get
    it if you want it; that you can change the software and use pieces of
    it in new free programs; and that you are informed that you can do
    these things.
    
      To protect your rights, we need to make restrictions that forbid
    distributors to deny you these rights or to ask you to surrender these
    rights.  These restrictions translate to certain responsibilities for
    you if you distribute copies of the library or if you modify it.
    
      For example, if you distribute copies of the library, whether gratis
    or for a fee, you must give the recipients all the rights that we gave
    you.  You must make sure that they, too, receive or can get the source
    code.  If you link other code with the library, you must provide
    complete object files to the recipients, so that they can relink them
    with the library after making changes to the library and recompiling
    it.  And you must show them these terms so they know their rights.
    
      We protect your rights with a two-step method: (1) we copyright the
    library, and (2) we offer you this license, which gives you legal
    permission to copy, distribute and/or modify the library.
    
      To protect each distributor, we want to make it very clear that
    there is no warranty for the free library.  Also, if the library is
    modified by someone else and passed on, the recipients should know
    that what they have is not the original version, so that the original
    author's reputation will not be affected by problems that might be
    introduced by others.
    
      Finally, software patents pose a constant threat to the existence of
    any free program.  We wish to make sure that a company cannot
    effectively restrict the users of a free program by obtaining a
    restrictive license from a patent holder.  Therefore, we insist that
    any patent license obtained for a version of the library must be
    consistent with the full freedom of use specified in this license.
    
      Most GNU software, including some libraries, is covered by the
    ordinary GNU General Public License.  This license, the GNU Lesser
    General Public License, applies to certain designated libraries, and
    is quite different from the ordinary General Public License.  We use
    this license for certain libraries in order to permit linking those
    libraries into non-free programs.
    
      When a program is linked with a library, whether statically or using
    a shared library, the combination of the two is legally speaking a
    combined work, a derivative of the original library.  The ordinary
    General Public License therefore permits such linking only if the
    entire combination fits its criteria of freedom.  The Lesser General
    Public License permits more lax criteria for linking other code with
    the library.
    
      We call this license the "Lesser" General Public License because it
    does Less to protect the user's freedom than the ordinary General
    Public License.  It also provides other free software developers Less
    of an advantage over competing non-free programs.  These disadvantages
    are the reason we use the ordinary General Public License for many
    libraries.  However, the Lesser license provides advantages in certain
    special circumstances.
    
      For example, on rare occasions, there may be a special need to
    encourage the widest possible use of a certain library, so that it becomes
    a de-facto standard.  To achieve this, non-free programs must be
    allowed to use the library.  A more frequent case is that a free
    library does the same job as widely used non-free libraries.  In this
    case, there is little to gain by limiting the free library to free
    software only, so we use the Lesser General Public License.
    
      In other cases, permission to use a particular library in non-free
    programs enables a greater number of people to use a large body of
    free software.  For example, permission to use the GNU C Library in
    non-free programs enables many more people to use the whole GNU
    operating system, as well as its variant, the GNU/Linux operating
    system.
    
      Although the Lesser General Public License is Less protective of the
    users' freedom, it does ensure that the user of a program that is
    linked with the Library has the freedom and the wherewithal to run
    that program using a modified version of the Library.
    
      The precise terms and conditions for copying, distribution and
    modification follow.  Pay close attention to the difference between a
    "work based on the library" and a "work that uses the library".  The
    former contains code derived from the library, whereas the latter must
    be combined with the library in order to run.
    
    		  GNU LESSER GENERAL PUBLIC LICENSE
       TERMS AND CONDITIONS FOR COPYING, DISTRIBUTION AND MODIFICATION
    
      0. This License Agreement applies to any software library or other
    program which contains a notice placed by the copyright holder or
    other authorized party saying it may be distributed under the terms of
    this Lesser General Public License (also called "this License").
    Each licensee is addressed as "you".
    
      A "library" means a collection of software functions and/or data
    prepared so as to be conveniently linked with application programs
    (which use some of those functions and data) to form executables.
    
      The "Library", below, refers to any such software library or work
    which has been distributed under these terms.  A "work based on the
    Library" means either the Library or any derivative work under
    copyright law: that is to say, a work containing the Library or a
    portion of it, either verbatim or with modifications and/or translated
    straightforwardly into another language.  (Hereinafter, translation is
    included without limitation in the term "modification".)
    
      "Source code" for a work means the preferred form of the work for
    making modifications to it.  For a library, complete source code means
    all the source code for all modules it contains, plus any associated
    interface definition files, plus the scripts used to control compilation
    and installation of the library.
    
      Activities other than copying, distribution and modification are not
    covered by this License; they are outside its scope.  The act of
    running a program using the Library is not restricted, and output from
    such a program is covered only if its contents constitute a work based
    on the Library (independent of the use of the Library in a tool for
    writing it).  Whether that is true depends on what the Library does
    and what the program that uses the Library does.
      
      1. You may copy and distribute verbatim copies of the Library's
    complete source code as you receive it, in any medium, provided that
    you conspicuously and appropriately publish on each copy an
    appropriate copyright notice and disclaimer of warranty; keep intact
    all the notices that refer to this License and to the absence of any
    warranty; and distribute a copy of this License along with the
    Library.
    
      You may charge a fee for the physical act of transferring a copy,
    and you may at your option offer warranty protection in exchange for a
    fee.
    
      2. You may modify your copy or copies of the Library or any portion
    of it, thus forming a work based on the Library, and copy and
    distribute such modifications or work under the terms of Section 1
    above, provided that you also meet all of these conditions:
    
        a) The modified work must itself be a software library.
    
        b) You must cause the files modified to carry prominent notices
        stating that you changed the files and the date of any change.
    
        c) You must cause the whole of the work to be licensed at no
        charge to all third parties under the terms of this License.
    
        d) If a facility in the modified Library refers to a function or a
        table of data to be supplied by an application program that uses
        the facility, other than as an argument passed when the facility
        is invoked, then you must make a good faith effort to ensure that,
        in the event an application does not supply such function or
        table, the facility still operates, and performs whatever part of
        its purpose remains meaningful.
    
        (For example, a function in a library to compute square roots has
        a purpose that is entirely well-defined independent of the
        application.  Therefore, Subsection 2d requires that any
        application-supplied function or table used by this function must
        be optional: if the application does not supply it, the square
        root function must still compute square roots.)
    
    These requirements apply to the modified work as a whole.  If
    identifiable sections of that work are not derived from the Library,
    and can be reasonably considered independent and separate works in
    themselves, then this License, and its terms, do not apply to those
    sections when you distribute them as separate works.  But when you
    distribute the same sections as part of a whole which is a work based
    on the Library, the distribution of the whole must be on the terms of
    this License, whose permissions for other licensees extend to the
    entire whole, and thus to each and every part regardless of who wrote
    it.
    
    Thus, it is not the intent of this section to claim rights or contest
    your rights to work written entirely by you; rather, the intent is to
    exercise the right to control the distribution of derivative or
    collective works based on the Library.
    
    In addition, mere aggregation of another work not based on the Library
    with the Library (or with a work based on the Library) on a volume of
    a storage or distribution medium does not bring the other work under
    the scope of this License.
    
      3. You may opt to apply the terms of the ordinary GNU General Public
    License instead of this License to a given copy of the Library.  To do
    this, you must alter all the notices that refer to this License, so
    that they refer to the ordinary GNU General Public License, version 2,
    instead of to this License.  (If a newer version than version 2 of the
    ordinary GNU General Public License has appeared, then you can specify
    that version instead if you wish.)  Do not make any other change in
    these notices.
    
      Once this change is made in a given copy, it is irreversible for
    that copy, so the ordinary GNU General Public License applies to all
    subsequent copies and derivative works made from that copy.
    
      This option is useful when you wish to copy part of the code of
    the Library into a program that is not a library.
    
      4. You may copy and distribute the Library (or a portion or
    derivative of it, under Section 2) in object code or executable form
    under the terms of Sections 1 and 2 above provided that you accompany
    it with the complete corresponding machine-readable source code, which
    must be distributed under the terms of Sections 1 and 2 above on a
    medium customarily used for software interchange.
    
      If distribution of object code is made by offering access to copy
    from a designated place, then offering equivalent access to copy the
    source code from the same place satisfies the requirement to
    distribute the source code, even though third parties are not
    compelled to copy the source along with the object code.
    
      5. A program that contains no derivative of any portion of the
    Library, but is designed to work with the Library by being compiled or
    linked with it, is called a "work that uses the Library".  Such a
    work, in isolation, is not a derivative work of the Library, and
    therefore falls outside the scope of this License.
    
      However, linking a "work that uses the Library" with the Library
    creates an executable that is a derivative of the Library (because it
    contains portions of the Library), rather than a "work that uses the
    library".  The executable is therefore covered by this License.
    Section 6 states terms for distribution of such executables.
    
      When a "work that uses the Library" uses material from a header file
    that is part of the Library, the object code for the work may be a
    derivative work of the Library even though the source code is not.
    Whether this is true is especially significant if the work can be
    linked without the Library, or if the work is itself a library.  The
    threshold for this to be true is not precisely defined by law.
    
      If such an object file uses only numerical parameters, data
    structure layouts and accessors, and small macros and small inline
    functions (ten lines or less in length), then the use of the object
    file is unrestricted, regardless of whether it is legally a derivative
    work.  (Executables containing this object code plus portions of the
    Library will still fall under Section 6.)
    
      Otherwise, if the work is a derivative of the Library, you may
    distribute the object code for the work under the terms of Section 6.
    Any executables containing that work also fall under Section 6,
    whether or not they are linked directly with the Library itself.
    
      6. As an exception to the Sections above, you may also combine or
    link a "work that uses the Library" with the Library to produce a
    work containing portions of the Library, and distribute that work
    under terms of your choice, provided that the terms permit
    modification of the work for the customer's own use and reverse
    engineering for debugging such modifications.
    
      You must give prominent notice with each copy of the work that the
    Library is used in it and that the Library and its use are covered by
    this License.  You must supply a copy of this License.  If the work
    during execution displays copyright notices, you must include the
    copyright notice for the Library among them, as well as a reference
    directing the user to the copy of this License.  Also, you must do one
    of these things:
    
        a) Accompany the work with the complete corresponding
        machine-readable source code for the Library including whatever
        changes were used in the work (which must be distributed under
        Sections 1 and 2 above); and, if the work is an executable linked
        with the Library, with the complete machine-readable "work that
        uses the Library", as object code and/or source code, so that the
        user can modify the Library and then relink to produce a modified
        executable containing the modified Library.  (It is understood
        that the user who changes the contents of definitions files in the
        Library will not necessarily be able to recompile the application
        to use the modified definitions.)
    
        b) Use a suitable shared library mechanism for linking with the
        Library.  A suitable mechanism is one that (1) uses at run time a
        copy of the library already present on the user's computer system,
        rather than copying library functions into the executable, and (2)
        will operate properly with a modified version of the library, if
        the user installs one, as long as the modified version is
        interface-compatible with the version that the work was made with.
    
        c) Accompany the work with a written offer, valid for at
        least three years, to give the same user the materials
        specified in Subsection 6a, above, for a charge no more
        than the cost of performing this distribution.
    
        d) If distribution of the work is made by offering access to copy
        from a designated place, offer equivalent access to copy the above
        specified materials from the same place.
    
        e) Verify that the user has already received a copy of these
        materials or that you have already sent this user a copy.
    
      For an executable, the required form of the "work that uses the
    Library" must include any data and utility programs needed for
    reproducing the executable from it.  However, as a special exception,
    the materials to be distributed need not include anything that is
    normally distributed (in either source or binary form) with the major
    components (compiler, kernel, and so on) of the operating system on
    which the executable runs, unless that component itself accompanies
    the executable.
    
      It may happen that this requirement contradicts the license
    restrictions of other proprietary libraries that do not normally
    accompany the operating system.  Such a contradiction means you cannot
    use both them and the Library together in an executable that you
    distribute.
    
      7. You may place library facilities that are a work based on the
    Library side-by-side in a single library together with other library
    facilities not covered by this License, and distribute such a combined
    library, provided that the separate distribution of the work based on
    the Library and of the other library facilities is otherwise
    permitted, and provided that you do these two things:
    
        a) Accompany the combined library with a copy of the same work
        based on the Library, uncombined with any other library
        facilities.  This must be distributed under the terms of the
        Sections above.
    
        b) Give prominent notice with the combined library of the fact
        that part of it is a work based on the Library, and explaining
        where to find the accompanying uncombined form of the same work.
    
      8. You may not copy, modify, sublicense, link with, or distribute
    the Library except as expressly provided under this License.  Any
    attempt otherwise to copy, modify, sublicense, link with, or
    distribute the Library is void, and will automatically terminate your
    rights under this License.  However, parties who have received copies,
    or rights, from you under this License will not have their licenses
    terminated so long as such parties remain in full compliance.
    
      9. You are not required to accept this License, since you have not
    signed it.  However, nothing else grants you permission to modify or
    distribute the Library or its derivative works.  These actions are
    prohibited by law if you do not accept this License.  Therefore, by
    modifying or distributing the Library (or any work based on the
    Library), you indicate your acceptance of this License to do so, and
    all its terms and conditions for copying, distributing or modifying
    the Library or works based on it.
    
      10. Each time you redistribute the Library (or any work based on the
    Library), the recipient automatically receives a license from the
    original licensor to copy, distribute, link with or modify the Library
    subject to these terms and conditions.  You may not impose any further
    restrictions on the recipients' exercise of the rights granted herein.
    You are not responsible for enforcing compliance by third parties with
    this License.
    
      11. If, as a consequence of a court judgment or allegation of patent
    infringement or for any other reason (not limited to patent issues),
    conditions are imposed on you (whether by court order, agreement or
    otherwise) that contradict the conditions of this License, they do not
    excuse you from the conditions of this License.  If you cannot
    distribute so as to satisfy simultaneously your obligations under this
    License and any other pertinent obligations, then as a consequence you
    may not distribute the Library at all.  For example, if a patent
    license would not permit royalty-free redistribution of the Library by
    all those who receive copies directly or indirectly through you, then
    the only way you could satisfy both it and this License would be to
    refrain entirely from distribution of the Library.
    
    If any portion of this section is held invalid or unenforceable under any
    particular circumstance, the balance of the section is intended to apply,
    and the section as a whole is intended to apply in other circumstances.
    
    It is not the purpose of this section to induce you to infringe any
    patents or other property right claims or to contest validity of any
    such claims; this section has the sole purpose of protecting the
    integrity of the free software distribution system which is
    implemented by public license practices.  Many people have made
    generous contributions to the wide range of software distributed
    through that system in reliance on consistent application of that
    system; it is up to the author/donor to decide if he or she is willing
    to distribute software through any other system and a licensee cannot
    impose that choice.
    
    This section is intended to make thoroughly clear what is believed to
    be a consequence of the rest of this License.
    
      12. If the distribution and/or use of the Library is restricted in
    certain countries either by patents or by copyrighted interfaces, the
    original copyright holder who places the Library under this License may add
    an explicit geographical distribution limitation excluding those countries,
    so that distribution is permitted only in or among countries not thus
    excluded.  In such case, this License incorporates the limitation as if
    written in the body of this License.
    
      13. The Free Software Foundation may publish revised and/or new
    versions of the Lesser General Public License from time to time.
    Such new versions will be similar in spirit to the present version,
    but may differ in detail to address new problems or concerns.
    
    Each version is given a distinguishing version number.  If the Library
    specifies a version number of this License which applies to it and
    "any later version", you have the option of following the terms and
    conditions either of that version or of any later version published by
    the Free Software Foundation.  If the Library does not specify a
    license version number, you may choose any version ever published by
    the Free Software Foundation.
    
      14. If you wish to incorporate parts of the Library into other free
    programs whose distribution conditions are incompatible with these,
    write to the author to ask for permission.  For software which is
    copyrighted by the Free Software Foundation, write to the Free
    Software Foundation; we sometimes make exceptions for this.  Our
    decision will be guided by the two goals of preserving the free status
    of all derivatives of our free software and of promoting the sharing
    and reuse of software generally.
    
    			    NO WARRANTY
    
      15. BECAUSE THE LIBRARY IS LICENSED FREE OF CHARGE, THERE IS NO
    WARRANTY FOR THE LIBRARY, TO THE EXTENT PERMITTED BY APPLICABLE LAW.
    EXCEPT WHEN OTHERWISE STATED IN WRITING THE COPYRIGHT HOLDERS AND/OR
    OTHER PARTIES PROVIDE THE LIBRARY "AS IS" WITHOUT WARRANTY OF ANY
    KIND, EITHER EXPRESSED OR IMPLIED, INCLUDING, BUT NOT LIMITED TO, THE
    IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR
    PURPOSE.  THE ENTIRE RISK AS TO THE QUALITY AND PERFORMANCE OF THE
    LIBRARY IS WITH YOU.  SHOULD THE LIBRARY PROVE DEFECTIVE, YOU ASSUME
    THE COST OF ALL NECESSARY SERVICING, REPAIR OR CORRECTION.
    
      16. IN NO EVENT UNLESS REQUIRED BY APPLICABLE LAW OR AGREED TO IN
    WRITING WILL ANY COPYRIGHT HOLDER, OR ANY OTHER PARTY WHO MAY MODIFY
    AND/OR REDISTRIBUTE THE LIBRARY AS PERMITTED ABOVE, BE LIABLE TO YOU
    FOR DAMAGES, INCLUDING ANY GENERAL, SPECIAL, INCIDENTAL OR
    CONSEQUENTIAL DAMAGES ARISING OUT OF THE USE OR INABILITY TO USE THE
    LIBRARY (INCLUDING BUT NOT LIMITED TO LOSS OF DATA OR DATA BEING
    RENDERED INACCURATE OR LOSSES SUSTAINED BY YOU OR THIRD PARTIES OR A
    FAILURE OF THE LIBRARY TO OPERATE WITH ANY OTHER SOFTWARE), EVEN IF
    SUCH HOLDER OR OTHER PARTY HAS BEEN ADVISED OF THE POSSIBILITY OF SUCH
    DAMAGES.
    
    		     END OF TERMS AND CONDITIONS
    
               How to Apply These Terms to Your New Libraries
    
      If you develop a new library, and you want it to be of the greatest
    possible use to the public, we recommend making it free software that
    everyone can redistribute and change.  You can do so by permitting
    redistribution under these terms (or, alternatively, under the terms of the
    ordinary General Public License).
    
      To apply these terms, attach the following notices to the library.  It is
    safest to attach them to the start of each source file to most effectively
    convey the exclusion of warranty; and each file should have at least the
    "copyright" line and a pointer to where the full notice is found.
    
        
        Copyright (C)   
    
        This library is free software; you can redistribute it and/or
        modify it under the terms of the GNU Lesser General Public
        License as published by the Free Software Foundation; either
        version 2.1 of the License, or (at your option) any later version.
    
        This library is distributed in the hope that it will be useful,
        but WITHOUT ANY WARRANTY; without even the implied warranty of
        MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
        Lesser General Public License for more details.
    
        You should have received a copy of the GNU Lesser General Public
        License along with this library; if not, write to the Free Software
        Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, MA  02110-1301  USA
    
    Also add information on how to contact you by electronic and paper mail.
    
    You should also get your employer (if you work as a programmer) or your
    school, if any, to sign a "copyright disclaimer" for the library, if
    necessary.  Here is a sample; alter the names:
    
      Yoyodyne, Inc., hereby disclaims all copyright interest in the
      library `Frob' (a library for tweaking knobs) written by James Random Hacker.
    
      , 1 April 1990
      Ty Coon, President of Vice
    
    That's all there is to it!
    
    =========================== LGPL ENDS HERE =================================	
    

    The following notice applies to this work as a whole and to the works included within it:

    • Creative endeavors depend on the lively exchange of ideas. There are laws and customs which establish rights and responsibilities for authors and the users of what authors create. This notice is not intended to prevent you from using the software and documents in this package, but to ensure that there are no misunderstandings about terms and conditions of such use.
    • Please read the following notice carefully. If you do not understand any portion of this notice, please seek appropriate professional legal advice before making use of the software and documents included in this software package. In addition to whatever other steps you may be obliged to take to respect the intellectual property rights of the various parties involved, if you do make use of the software and documents in this package, please give credit where credit is due by citing this package, its authors and the URL or other source from which you obtained it, or equivalent primary references in the literature with the same authors.
    • Some of the software and documents included within this software package are the intellectual property of various parties, and placement in this package does not in any way imply that any such rights have in any way been waived or diminished.
    • With respect to any software or documents for which a copyright exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT.
    • Even though the authors of the various documents and software found here have made a good faith effort to ensure that the documents are correct and that the software performs according to its documentation, and we would greatly appreciate hearing of any problems you may encounter, the programs and documents any files created by the programs are provided **AS IS** without any warranty as to correctness, merchantability or fitness for any particular or general use.
    • THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE PROGRAMS OR DOCUMENTS.


    Stanford University Notices
    for the CBFlib software package that incorporates SLAC software on which copyright is disclaimed

    This software

    The term 'this software', as used in these Notices, refers to those portions of the software package CBFlib that were created by employees of the Stanford Linear Accelerator Center, Stanford University.

    Stanford disclaimer of copyright

    Stanford University, owner of the copyright, hereby disclaims its copyright and all other rights in this software. Hence, anyone may freely use it for any purpose without restriction.

    Acknowledgement of sponsorship

    This software was produced by the Stanford Linear Accelerator Center, Stanford University, under Contract DE-AC03-76SFO0515 with the Department of Energy.

    Government disclaimer of liability

    Neither the United States nor the United States Department of Energy, nor any of their employees, makes any warranty, express or implied, or assumes any legal liability or responsibility for the accuracy, completeness, or usefulness of any data, apparatus, product, or process disclosed, or represents that its use would not infringe privately owned rights.

    Stanford disclaimer of liability

    Stanford University makes no representations or warranties, express or implied, nor assumes any liability for the use of this software.

    Maintenance of notices

    In the interest of clarity regarding the origin and status of this software, this and all the preceding Stanford University notices are to remain affixed to any copy or derivative of this software made or distributed by the recipient and are to be affixed to any copy of software made or distributed by the recipient that contains a copy or derivative of this software.

    Based on SLAC Software Notices, Set 4 OTT.002a, 2004 FEB 03



    The IUCr Policy
    for the Protection and the Promotion of the STAR File and
    CIF Standards for Exchanging and Archiving Electronic Data

    Overview

    The Crystallographic Information File (CIF)[1] is a standard for information interchange promulgated by the International Union of Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the recommended method for submitting publications to Acta Crystallographica Section C and reports of crystal structure determinations to other sections of Acta Crystallographica and many other journals. The syntax of a CIF is a subset of the more general STAR File[2] format. The CIF and STAR File approaches are used increasingly in the structural sciences for data exchange and archiving, and are having a significant influence on these activities in other fields.

    Statement of intent

    The IUCr's interest in the STAR File is as a general data interchange standard for science, and its interest in the CIF, a conformant derivative of the STAR File, is as a concise data exchange and archival standard for crystallography and structural science.

    Protection of the standards

    To protect the STAR File and the CIF as standards for interchanging and archiving electronic data, the IUCr, on behalf of the scientific community,

    * holds the copyrights on the standards themselves,

    * owns the associated trademarks and service marks, and

    * holds a patent on the STAR File.

    These intellectual property rights relate solely to the interchange formats, not to the data contained therein, nor to the software used in the generation, access or manipulation of the data.

    Promotion of the standards

    The sole requirement that the IUCr, in its protective role, imposes on software purporting to process STAR File or CIF data is that the following conditions be met prior to sale or distribution.

    * Software claiming to read files written to either the STAR File or the CIF standard must be able to extract the pertinent data from a file conformant to the STAR File syntax, or the CIF syntax, respectively.

    * Software claiming to write files in either the STAR File, or the CIF, standard must produce files that are conformant to the STAR File syntax, or the CIF syntax, respectively.

    * Software claiming to read definitions from a specific data dictionary approved by the IUCr must be able to extract any pertinent definition which is conformant to the dictionary definition language (DDL)[3] associated with that dictionary.

    The IUCr, through its Committee on CIF Standards, will assist any developer to verify that software meets these conformance conditions.

    Glossary of terms

    [1] CIF:

    is a data file conformant to the file syntax defined at http://www.iucr.org/iucr-top/cif/spec/index.html

    [2] STAR File:

    is a data file conformant to the file syntax defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html

    [3] DDL:

    is a language used in a data dictionary to define data items in terms of "attributes". Dictionaries currently approved by the IUCr, and the DDL versions used to construct these dictionaries, are listed at http://www.iucr.org/iucr-top/cif/spec/ddl/index.html

    Last modified: 30 September 2000

    IUCr Policy Copyright (C) 2000 International Union of Crystallography



    CBFlib V0.1 Notice

    The following Diclaimer Notice applies to CBFlib V0.1, from which this version is derived.

    • The items furnished herewith were developed under the sponsorship of the U.S. Government. Neither the U.S., nor the U.S. D.O.E., nor the Leland Stanford Junior University, nor their employees, makes any warranty, express or implied, or assumes any liability or responsibility for accuracy, completeness or usefulness of any information, apparatus, product or process disclosed, or represents that its use will not infringe privately-owned rights. Mention of any product, its manufacturer, or suppliers shall not, nor is it intended to, imply approval, disapproval, or fitness for any particular use. The U.S. and the University at all times retain the right to use and disseminate the furnished items for any purpose whatsoever.
    • Notice 91 02 01


    CIFPARSE notice

    Portions of this software are loosely based on the CIFPARSE software package from the NDB at Rutgers university (see http://ndbserver.rutgers.edu/NDB/mmcif/software). CIFPARSE is part of the NDBQUERY application, a program component of the Nucleic Acid Database Project [ H. M. Berman, W. K. Olson, D. L. Beveridge, J. K. Westbrook, A. Gelbin, T. Demeny, S. H. Shieh, A. R. Srinivasan, and B. Schneider. (1992). The Nucleic Acid Database: A Comprehensive Relational Database of Three-Dimensional Structures of Nucleic Acids. Biophys J., 63, 751-759.], whose cooperation is gratefully acknowledged, especially in the form of design concepts created by J. Westbrook.

    Please be aware of the following notice in the CIFPARSE API:

    • This software is provided WITHOUT WARRANTY OF MERCHANTABILITY OR FITNESS FOR A PARTICULAR PURPOSE OR ANY OTHER WARRANTY, EXPRESS OR IMPLIED. RUTGERS MAKE NO REPRESENTATION OR WARRANTY THAT THE SOFTWARE WILL NOT INFRINGE ANY PATENT, COPYRIGHT OR OTHER PROPRIETARY RIGHT.


    MPACK notice

    Portions of this library are adapted from the "mpack/munpack version 1.5" routines, written by John G. Myers. Mpack and munpack are utilities for encoding and decoding (respectively) binary files in MIME (Multipurpose Internet Mail Extensions) format mail messages. The mpack software used is (C) Copyright 1993,1994 by Carnegie Mellon University, All Rights Reserved, and is subject to the following notice:

    • Permission to use, copy, modify, distribute, and sell this software and its documentation for any purpose is hereby granted without fee, provided that the above copyright notice appear in all copies and that both that copyright notice and this permission notice appear in supporting documentation, and that the name of Carnegie Mellon University not be used in advertising or publicity pertaining to distribution of the software without specific, written prior permission. Carnegie Mellon University makes no representations about the suitability of this software for any purpose. It is provided "as is" without express or implied warranty.
    • CARNEGIE MELLON UNIVERSITY DISCLAIMS ALL WARRANTIES WITH REGARD TO THIS SOFTWARE, INCLUDING ALL IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS, IN NO EVENT SHALL CARNEGIE MELLON UNIVERSITY BE LIABLE FOR ANY SPECIAL, INDIRECT OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.


    MD5 Notice

    The following notice applies to the message digest software in md5.h and md5.c which are optionally used by this library. To that extent, this library is a work "derived from the RSA Data Security, Inc. MD5 Message-Digest Algorithm".

    The software in md5.h and md5.c is Copyright (C) 1991-2, RSA Data Security, Inc. Created 1991. All rights reserved, and is subject to the following notice:

    • License to copy and use this software is granted provided that it is identified as the "RSA Data Security, Inc. MD5 Message-Digest Algorithm" in all material mentioning or referencing this software or this function.
    • License is also granted to make and use derivative works provided that such works are identified as "derived from the RSA Data Security, Inc. MD5 Message-Digest Algorithm" in all material mentioning or referencing the derived work.
    • RSA Data Security, Inc. makes no representations concerning either the merchantability of this software or the suitability of this software for any particular purpose. It is provided "as is" without express or implied warranty of any kind.
    • These notices must be retained in any copies of any part of this documentation and/or software.



    CCP4 Packed Compression Notice

    The CBF_PACKED and CBF_PACKED_V2 compression and decompression code incorporated in CBFlib is derived in large part from the J. P. Abrahams pack_c.c compression code in CCP4. This code is incorporated in CBFlib under the GPL and the LGPL with both the permission Jan Pieter Abrahams, the original author of pack_c.c (email from Jan Pieter Abrahams of 15 January 2007) and of the CCP4 project (email from Martyn Winn on 12 January 2007). The cooperation of J. P. Abrahams and of the CCP4 project is gratefully acknowledged.



    Updated 7 April 2007. yaya@bernstein-plus-sons.com ./CBFlib-0.9.2.2/doc/Iarray_intensities.array_id.html0000644000076500007650000000516611603702115020677 0ustar yayayaya (IUCr) CIF Definition save__array_intensities.array_id

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _array_intensities.array_id

    Name:
    '_array_intensities.array_id'

    Definition:

           This item is a pointer to _array_structure.id in the
                  ARRAY_STRUCTURE category.
    
    

    Type: code

    Mandatory item: implicit

    Category: array_intensities

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Iaxis.equipment.html0000644000076500007650000000675711603702115016333 0ustar yayayaya (IUCr) CIF Definition save__axis.equipment

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _axis.equipment

    Name:
    '_axis.equipment'

    Definition:

           The value of  _axis.equipment specifies the type of
                  equipment using the axis:  'goniometer', 'detector',
                  'gravity', 'source' or 'general'.
    
    

    Type: ucode

    Mandatory item: no


    The data value must be one of the following:


    goniometer
    equipment used to orient or position samples

    detector
    equipment used to detect reflections

    general
    equipment used for general purposes

    gravity
    axis specifying the downward direction

    source
    axis specifying the direction sample to source

    Enumeration default: general

    Category: axis

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_radiation.diffrn_id.html0000644000076500007650000000461411603702115020574 0ustar yayayaya (IUCr) CIF Definition save__diffrn_radiation.diffrn_id

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_radiation.diffrn_id

    Name:
    '_diffrn_radiation.diffrn_id'

    Definition:

            This data item is a pointer to _diffrn.id in the DIFFRN
                   category.
    
    

    Type: code

    Mandatory item: yes

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Iarray_structure_list_axis.reference_displacement.html0000644000076500007650000000566711603702115025362 0ustar yayayaya (IUCr) CIF Definition save__array_structure_list_axis.reference_displacement

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _array_structure_list_axis.reference_displacement

    Name:
    '_array_structure_list_axis.reference_displacement'

    Definition:

            The value of _array_structure_list_axis.reference_displacement
                   specifies the setting of the displacement of this axis used
                   for determining a reference beam center and a reference detector
                   distance.  It is normally expected to be identical to the value
                   of _array_structure_list.displacement.
    
    
    

    Type: float

    Mandatory item: implicit

    Category: array_structure_list_axis

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_scan_frame_axis.frame_id.html0000644000076500007650000000571411603702115021570 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan_frame_axis.frame_id

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_scan_frame_axis.frame_id

    Name:
    '_diffrn_scan_frame_axis.frame_id'

    Definition:

            The value of this data item is the identifier of the
                   frame for which axis settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   _diffrn_scan_frame.frame_id.
    
                   This item is a pointer to _diffrn_data_frame.id in the
                   DIFFRN_DATA_FRAME category.
    
    

    Type: code

    Mandatory item: yes

    Category: diffrn_scan_frame_axis

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/cif_img_1.3.1.html0000644000076500007650000071176211603702115015364 0ustar yayayaya cif_img.dic v1.3.1

    # [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib] #

    # imgCIF/CBF #

    # Extensions Dictionary #

    ##############################################################################
    #                                                                            #
    #                       Image CIF Dictionary (imgCIF)                        #
    #             and Crystallographic Binary File Dictionary (CBF)              #
    #            Extending the Macromolecular CIF Dictionary (mmCIF)             #
    #                                                                            #
    #                              Version 1.3.1                                 #
    #                              of 2003-08-13                                 #
    #                                                                            #
    #     by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook    #
    #                                                                            #
    # This dictionary was adapted from format discussed at the imgCIF Workshop,  #
    # held at BNL Oct 1997 and the Crystallographic Binary File Format Draft     #
    # Proposal by Andrew Hammersley.  The first DDL 2.1 Version was created by   #
    # John Westbrook.  This version was drafted by Herbert J. Bernstein and      #
    # incorporates comments by I. David Brown, John Westbrook, Brian McMahon,    #
    # Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li, Gotzon Madariaga,         #
    # Frances C. Bernstein and others.                                           #
    ##############################################################################
                                                                        
    data_cif_img.dic
    
        _dictionary.title           cif_img.dic
        _dictionary.version         1.3.1
        _dictionary.datablock_id    cif_img.dic
    
    ##############################################################################
    #    CONTENTS
    #
    #        CATEGORY_GROUP_LIST
    #
    #        category  ARRAY_DATA
    #
    #                  _array_data.array_id
    #                  _array_data.binary_id
    #                  _array_data.data
    #
    #        category  ARRAY_ELEMENT_SIZE
    #        
    #                  _array_element_size.array_id
    #                  _array_element_size.index
    #                  _array_element_size.size
    #        
    #        category  ARRAY_INTENSITIES
    #        
    #                  _array_intensities.array_id
    #                  _array_intensities.binary_id
    #                  _array_intensities.gain
    #                  _array_intensities.gain_esd
    #                  _array_intensities.linearity
    #                  _array_intensities.offset
    #                  _array_intensities.scaling
    #                  _array_intensities.overload
    #                  _array_intensities.undefined_value
    #        
    #        category  ARRAY_STRUCTURE
    #        
    #                  _array_structure.byte_order
    #                  _array_structure.compression_type
    #                  _array_structure.encoding_type
    #                  _array_structure.id
    #        
    #        category  ARRAY_STRUCTURE_LIST
    #        
    #                  _array_structure_list.axis_set_id
    #                  _array_structure_list.array_id
    #                  _array_structure_list.dimension
    #                  _array_structure_list.direction
    #                  _array_structure_list.index
    #                  _array_structure_list.precedence
    #
    #        category  ARRAY_STRUCTURE_LIST_AXIS
    #        
    #                  _array_structure_list_axis.axis_id
    #                  _array_structure_list_axis.axis_set_id
    #                  _array_structure_list_axis.angle
    #                  _array_structure_list_axis.angle_increment
    #                  _array_structure_list_axis.displacement_increment
    #                  _array_structure_list_axis.angular_pitch
    #                  _array_structure_list_axis.radial_pitch
    #
    #        category  AXIS
    #        
    #                  _axis.depends_on
    #                  _axis.equipment
    #                  _axis.id
    #                  _axis.offset[1]
    #                  _axis.offset[2]
    #                  _axis.offset[3]
    #                  _axis.type
    #                  _axis.vector[1]
    #                  _axis.vector[2]
    #                  _axis.vector[3]
    #
    #        category  DIFFRN_DATA_FRAME
    #
    #                  _diffrn_data_frame.array_id
    #                  _diffrn_data_frame.binary_id
    #                  _diffrn_data_frame.detector_element_id
    #                  _diffrn_data_frame.id
    #
    #        category  DIFFRN_DETECTOR
    #        
    #                  _diffrn_detector.details
    #                  _diffrn_detector.detector
    #                  _diffrn_detector.diffrn_id
    #                  _diffrn_detector.dtime
    #                  _diffrn_detector.id
    #                  _diffrn_detector.number_of_axes
    #                  _diffrn_detector.type
    #
    #        category  DIFFRN_DETECTOR_AXIS
    #        
    #                  _diffrn_detector_axis.axis_id
    #                  _diffrn_detector_axis.detector_id    
    #        
    #        category  DIFFRN_DETECTOR_ELEMENT
    #
    #                  _diffrn_detector_element.center[1]
    #                  _diffrn_detector_element.center[2]
    #                  _diffrn_detector_element.id
    #                  _diffrn_detector_element.detector_id
    #        
    #        category  DIFFRN_MEASUREMENT
    #        
    #                  _diffrn_measurement.diffrn_id
    #                  _diffrn_measurement.details
    #                  _diffrn_measurement.device
    #                  _diffrn_measurement.device_details
    #                  _diffrn_measurement.device_type
    #                  _diffrn_measurement.id
    #                  _diffrn_measurement.method
    #                  _diffrn_measurement.number_of_axes
    #                  _diffrn_measurement.specimen_support
    #
    #        category  DIFFRN_MEASUREMENT_AXIS
    #        
    #                  _diffrn_measurement_axis.axis_id
    #                  _diffrn_measurement_axis.measurement_device
    #                  _diffrn_measurement_axis.measurement_id
    #
    #        category  DIFFRN_RADIATION
    #
    #                  _diffrn_radiation.collimation
    #                  _diffrn_radiation.diffrn_id
    #                  _diffrn_radiation.div_x_source
    #                  _diffrn_radiation.div_y_source
    #                  _diffrn_radiation.div_x_y_source
    #                  _diffrn_radiation.filter_edge'
    #                  _diffrn_radiation.inhomogeneity
    #                  _diffrn_radiation.monochromator
    #                  _diffrn_radiation.polarisn_norm
    #                  _diffrn_radiation.polarisn_ratio
    #                  _diffrn_radiation.polarizn_source_norm
    #                  _diffrn_radiation.polarizn_source_ratio
    #                  _diffrn_radiation.probe
    #                  _diffrn_radiation.type
    #                  _diffrn_radiation.xray_symbol
    #                  _diffrn_radiation.wavelength_id
    #        
    #        category  DIFFRN_REFLN
    #        
    #                  _diffrn_refln.frame_id
    #
    #        category  DIFFRN_SCAN
    #        
    #                  _diffrn_scan.id
    #                  _diffrn_scan.date_end
    #                  _diffrn_scan.date_start
    #                  _diffrn_scan.integration_time
    #                  _diffrn_scan.frame_id_start
    #                  _diffrn_scan.frame_id_end
    #                  _diffrn_scan.frames
    #
    #        category  DIFFRN_SCAN_AXIS
    #        
    #                  _diffrn_scan_axis.axis_id
    #                  _diffrn_scan_axis.angle_start
    #                  _diffrn_scan_axis.angle_range
    #                  _diffrn_scan_axis.angle_increment
    #                  _diffrn_scan_axis.angle_rstrt_incr
    #                  _diffrn_scan_axis.displacement_start
    #                  _diffrn_scan_axis.displacement_range
    #                  _diffrn_scan_axis.displacement_increment
    #                  _diffrn_scan_axis.displacement_rstrt_incr
    #                  _diffrn_scan_axis.scan_id
    #
    #        category  DIFFRN_SCAN_FRAME
    #        
    #                  _diffrn_scan_frame.date
    #                  _diffrn_scan_frame.frame_id
    #                  _diffrn_scan_frame.frame_number
    #                  _diffrn_scan_frame.integration_time
    #                  _diffrn_scan_frame.scan_id
    #
    #        category  DIFFRN_SCAN_FRAME_AXIS
    #        
    #                  _diffrn_scan_frame_axis.axis_id
    #                  _diffrn_scan_frame_axis.angle
    #                  _diffrn_scan_frame_axis.angle_increment
    #                  _diffrn_scan_frame_axis.angle_rstrt_incr
    #                  _diffrn_scan_frame_axis.displacement
    #                  _diffrn_scan_frame_axis.displacement_increment
    #                  _diffrn_scan_frame_axis.displacement_rstrt_incr
    #                  _diffrn_scan_frame_axis.frame_id
    #
    #       ***DEPRECATED*** data items
    #
    #                  _diffrn_detector_axis.id
    #                  _diffrn_measurement_axis.id
    #
    #       ***DEPRECATED*** category  DIFFRN_FRAME_DATA
    #
    #                  _diffrn_frame_data.array_id
    #                  _diffrn_frame_data.binary_id
    #                  _diffrn_frame_data.detector_element_id
    #                  _diffrn_frame_data.id
    #
    #
    #        ITEM_TYPE_LIST
    #        ITEM_UNITS_LIST
    #        DICTIONARY_HISTORY
    #
    ##############################################################################
    
    
    #########################
    ## CATEGORY_GROUP_LIST ##
    #########################
    
         loop_
        _category_group_list.id
        _category_group_list.parent_id
        _category_group_list.description
                 'inclusive_group'   .
    ;             Categories that belong to the dictionary extension.
    ;
                 'array_data_group'
                 'inclusive_group'
    ;             Categories that describe array data.
    ;
                 'axis_group'
                 'inclusive_group'
    ;             Categories that describe axes.
    ;
                 'diffrn_group'
                 'inclusive_group'
    ;            Categories that describe details of the diffraction experiment.
    ;
    
    
    
    
    ##############
    # ARRAY_DATA #
    ##############
    
      
    save_ARRAY_DATA
        _category.description
    ;
         Data items in the ARRAY_DATA category are the containers for
         the array data items described in category ARRAY_STRUCTURE.
    ;
        _category.id                   array_data
        _category.mandatory_code       no
         loop_
        _category_key.name             '_array_data.array_id'
                                       '_array_data.binary_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 -
    
            This example shows two binary data blocks.  The first one
            was compressed by the CBF_CANONICAL compression algorithm and
            presented as hexadecimal data.  The first character "H" on the
            data lines means hexadecimal.  It could have been "O" for octal
            or "D" for decimal.  The second character on the line shows
            the number of bytes in each word (in this case "4"), which then
            requires 8 hexadecimal digits per word.  The third character
            gives the order of octets within a word, in this case "<"
            for the ordering 4321 (i.e. "big-endian").  Alternatively the
            character ">" could have been used for the ordering 1234
            (i.e. "little-endian").  The block has a "message digest"
            to check the integrity of the data.
    
            The second block is similar, but uses CBF_PACKED compression
            and BASE64 encoding.  Note that the size and the digest are
            different.
    ;
    ;
    
            loop_
            _array_data.array_id
            _array_data.binary_id
            _array_data.data
            image_1 1
            ;
            --CIF-BINARY-FORMAT-SECTION--
            Content-Type: application/octet-stream;
                 conversions="x-CBF_CANONICAL"
            Content-Transfer-Encoding: X-BASE16
            X-Binary-Size: 3927126
            X-Binary-ID: 1
            Content-MD5: u2sTJEovAHkmkDjPi+gWsg==
    
            # Hexadecimal encoding, byte 0, byte order ...21
            #
            H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ...
            ....
            --CIF-BINARY-FORMAT-SECTION----
            ;
            image_2 2
            ;
            --CIF-BINARY-FORMAT-SECTION--
            Content-Type: application/octet-stream;
                 conversions="x-CBF-PACKED"
            Content-Transfer-Encoding: BASE64
            X-Binary-Size: 3745758
            X-Binary-ID: 2
            Content-MD5: 1zsJjWPfol2GYl2V+QSXrw==
    
            ELhQAAAAAAAA...
            ...
            --CIF-BINARY-FORMAT-SECTION----
            ;
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    save_
    
    
    save__array_data.array_id
        _item_description.description
    ;             This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category. 
    ;
        _item.name                  '_array_data.array_id'
        _item.category_id             array_data
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__array_data.binary_id
        _item_description.description
    ;             This item is an integer identifier which, along with
                  '_array_data.array_id' should uniquely identify the 
                  particular block of array data.
                  
                  If '_array_data.binary_id' is not explicitly given,
                  it defaults to 1.
                  
                  The value of '_array_data.binary_id' distinguishes
                  among multiple sets of data with the same array
                  structure.
                  
                  If the MIME header of the data array specifies a 
                  value for X-Binary-Id, the value of  '_array_data.binary_id'
                  should be equal the value given for X-Binary-Id.
    ;
         loop_
        _item.name                  
        _item.category_id             
        _item.mandatory_code          
                 '_array_data.binary_id'            array_data      
                                                                    implicit
                 '_diffrn_data_frame.binary_id'     diffrn_data_frame
                                                                    implicit
                 '_array_intensities.binary_id'     array_intensities
                                                                    implicit
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_data_frame.binary_id'     '_array_data.binary_id'
                 '_array_intensities.binary_id'     '_array_data.binary_id'
    
        _item_default.value           1
        _item_type.code               int
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                1  1
                                .  1
         save_
    
    
    save__array_data.data
        _item_description.description
    ;             The value of '_array_data.data' contains the array data 
                  encapsulated in a STAR string.
                  
                  The representation used is a variant on the
                  Multipurpose Internet Mail Extensions (MIME) specified
                  in RFC 2045-2049 by N. Freed et al.  The boundary
                  delimiter used in writing an imgCIF or CBF is
                  "--CIF-BINARY-FORMAT-SECTION--" (including the
                  required initial "--").
    
                  The Content-Type may be any of the discrete types permitted
                  in RFC 2045; "application/octet-stream" is recommended.  
                  If an octet stream was compressed, the compression should 
                  be specified by the parameter 'conversions="x-CBF_PACKED"' 
                  or the parameter 'conversions="x-CBF_CANONICAL"'.
                  
                  The Content-Transfer-Encoding may be "BASE64",
                  "Quoted-Printable", "X-BASE8", "X-BASE10", or
                  "X-BASE16" for an imgCIF or "BINARY" for a CBF.  The
                  octal, decimal and hexadecimal transfer encodings are
                  for convenience in debugging, and are not recommended
                  for archiving and data interchange.
                  
                  In an imgCIF file, the encoded binary data begins after
                  the empty line terminating the header.  In a CBF, the
                  raw binary data begins after an empty line terminating
                  the header and after the sequence:
                        
                  Octet   Hex   Decimal  Purpose
                    0     0C       12    (ctrl-L) Page break
                    1     1A       26    (ctrl-Z) Stop listings in MS-DOS
                    2     04       04    (Ctrl-D) Stop listings in UNIX
                    3     D5      213    Binary section begins
    
                  None of these octets are included in the calculation of
                  the message size, nor in the calculation of the
                  message digest.
                                 
                  The X-Binary-Size header specifies the size of the
                  equivalent binary data in octets.  If compression was
                  used, this size is the size after compression, including
                  any book-keeping fields.  An adjustment is made for
                  the deprecated binary formats in which 8 bytes of binary
                  header are used for the compression type.  In that case,
                  the 8 bytes used for the compression type is subtracted
                  from the size, so that the same size will be reported
                  if the compression type is supplied in the MIME header.
                  Use of the MIME header is the recommended way to
                  supply the compression type.  In general, no portion of
                  the  binary header is included in the calculation of the size.
    
                  The X-Binary-Element-Type header specifies the type of
                  binary data in the octets, using the same descriptive
                  phrases as in '_array_structure.encoding_type'.  The default
                  value is "unsigned 32-bit integer".
                  
                  An MD5 message digest may, optionally, be used. The "RSA Data
                  Security, Inc. MD5 Message-Digest Algorithm" should be used.
                  No portion of the header is included in the calculation of the
                  message digest.
    
                  If the Transfer Encoding is "X-BASE8", "X-BASE10", or
                  "X-BASE16", the data is presented as octal, decimal or
                  hexadecimal data organized into lines or words.  Each word
                  is created by composing octets of data in fixed groups of
                  2, 3, 4, 6 or 8 octets, either in the order ...4321 ("big-
                  endian") or 1234... (little-endian).  If there are fewer
                  than the specified number of octets to fill the last word,
                  then the missing octets are presented as "==" for each
                  missing octet.  Exactly two equal signs are used for each
                  missing octet even for octal and decimal encoding.
                  The format of lines is:
    
                  rnd xxxxxx xxxxxx xxxxxx
    
                  where r is "H", "O", or "D" for hexadecimal, octal or
                  decimal, n is the number of octets per word. and d is "<"
                  for ">" for the "...4321" and "1234..." octet orderings
                  respectively.  The "==" padding for the last word should
                  be on the appropriate side to correspond to the missing
                  octets, e.g.
    
                  H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000
    
                  or
    
                  H3> FF0700 00====
    
                  For these hex, octal and decimal formats, only, comments
                  beginning with "#" are permitted to improve readability.
    
                  BASE64 encoding follows MIME conventions.  Octets are
                  in groups of three, c1, c2, c3.  The resulting 24 bits 
                  are broken into four 6-bit quantities, starting with 
                  the high-order six bits (c1 >> 2) of the first octet, then
                  the low-order two bits of the first octet followed by the
                  high-order 4 bits of the second octet ((c1 & 3)<<4 | (c2>>4)),
                  then the bottom 4 bits of the second octet followed by the
                  high order two bits of the last octet ((c2 & 15)<<2 | (c3>>6)),
                  then the bottom six bits of the last octet (c3 & 63).  Each
                  of these four quantities is translated into an ASCII character
                  using the mapping:
    
                            1         2         3         4         5         6
                  0123456789012345678901234567890123456789012345678901234567890123
                  |         |         |         |         |         |         |
                  ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/
    
                  With short groups of octets padded on the right with one "="
                  if c3 is missing, and with "==" if both c2 and c3 are missing.
    
                  QUOTED-PRINTABLE encoding also follows MIME conventions, copying
                  octets without translation if their ASCII values are 32..38,
                  42, 48..57, 59..60, 62, 64..126 and the octet is not a ";"
                  in column 1.  All other characters are translated to =nn, where
                  nn is the hexadecimal encoding of the octet.  All lines are
                  "wrapped" with a terminating "=" (i.e. the MIME conventions
                  for an implicit line terminator are never used).
    ;
        _item.name                  '_array_data.data'
        _item.category_id             array_data
        _item.mandatory_code          yes
        _item_type.code               binary
    save_
    
    
    ######################
    # ARRAY_ELEMENT_SIZE #
    ######################
    
    
    save_ARRAY_ELEMENT_SIZE
        _category.description
    ;
         Data items in the ARRAY_ELEMENT_SIZE category record the physical 
         size of array elements along each array dimension.
    ;
        _category.id                   array_element_size
        _category.mandatory_code       no
         loop_
        _category_key.name             '_array_element_size.array_id'
                                       '_array_element_size.index'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 - A regular 2D array with a uniform element dimension
                        of 1220 nanometres.
    ;
    ;
            loop_
           _array_element_size.array_id  
           _array_element_size.index
           _array_element_size.size
            image_1   1    1.22e-6
            image_1   2    1.22e-6
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_element_size.array_id
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category. 
    ;
        _item.name                  '_array_element_size.array_id'
        _item.category_id             array_element_size
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__array_element_size.index
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure_list.index' in
                  the ARRAY_STRUCTURE_LIST category. 
    ;
        _item.name                  '_array_element_size.index'
        _item.category_id             array_element_size
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__array_element_size.size
        _item_description.description
    ;
                   The size in metres of an image element in this 
                   dimension. This supposes that the elements are arranged
                   on a regular grid.
    ;
        _item.name               '_array_element_size.size'
        _item.category_id          array_element_size
        _item.mandatory_code       yes 
        _item_type.code            float
        _item_units.code           'metres'
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0.0
         save_
    
    
    #####################
    # ARRAY_INTENSITIES #
    #####################
    
    
    save_ARRAY_INTENSITIES
        _category.description
    ;
                  Data items in the ARRAY_INTENSITIES category record the
                  information required to recover the intensity data from 
                  the set of data values stored in the ARRAY_DATA category.
    
                  The actual detector may have a complex relationship
                  between the raw intensity values and the number of
                  incident photons.  In most cases, the number stored
                  in the final array will have a simple linear relationship
                  to the actual number of incident photons, given by
                  '_array_intensities.gain'.  If raw, uncorrected values
                  are presented (e.g for calibration experiments), the
                  value of '_array_intensities.linearity' will be 'raw'
                  and '_array_intensities.gain' will not be used.
    
    ;
        _category.id                   array_intensities
        _category.mandatory_code       no
        loop_
        _category_key.name             '_array_intensities.array_id'
                                       '_array_intensities.binary_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1
    ;
    ;
            loop_
            _array_intensities.array_id
            _array_intensities.linearity 
            _array_intensities.gain      
            _array_intensities.overload  
            _array_intensities.undefined_value 
            image_1   linear  1.2    655535   0
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_intensities.array_id
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category. 
    ;
        _item.name                  '_array_intensities.array_id'
        _item.category_id             array_intensities
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__array_intensities.binary_id
        _item_description.description
    ;             This item is a pointer to '_array_data.binary_id' in the
                  ARRAY_DATA category. 
    ;
        _item.name                  '_array_intensities.binary_id'
        _item.category_id             array_intensities
        _item.mandatory_code          implicit
        _item_type.code               int
         save_
    
    
    save__array_intensities.gain
        _item_description.description
    ;              
                   Detector "gain". The factor by which linearized 
                   intensity count values should be divided to produce
                   true photon counts.
    ;
        _item.name              '_array_intensities.gain'
        _item.category_id          array_intensities
        _item.mandatory_code       yes
        _item_type.code            float
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0.0
        _item_units.code           'counts_per_photon'
         loop_
        _item_related.related_name
        _item_related.function_code  '_array_intensities.gain_esd'
                                     'associated_value'
        save_
    
      
    save__array_intensities.gain_esd
        _item_description.description
    ;              
                  The estimated standard deviation in detector "gain".
    ;
        _item.name              '_array_intensities.gain_esd'
        _item.category_id          array_intensities
        _item.mandatory_code       yes
        _item_type.code            float
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0.0
    
        _item_units.code          'counts_per_photon'
         loop_
        _item_related.related_name
        _item_related.function_code  '_array_intensities.gain'
                                     'associated_esd'
        save_
    
    
    save__array_intensities.linearity
        _item_description.description
    ;
                   The intensity linearity scaling used from raw intensity
                   to the stored element value:
    
                   'linear' is obvious
    
                   'offset'  means that the value defined by 
                   '_array_intensities.offset' should be added to each
                    element value.  
    
                   'scaling' means that the value defined by 
                   '_array_intensities.scaling' should be multiplied with each 
                   element value.  
    
                   'scaling_offset' is the combination of the two previous cases, 
                   with the scale factor applied before the offset value.
    
                   'sqrt_scaled' means that the square root of raw 
                   intensities multiplied by '_array_intensities.scaling' is
                   calculated and stored, perhaps rounded to the nearest 
                   integer. Thus, linearization involves dividing the stored
                   values by '_array_intensities.scaling' and squaring the 
                   result. 
    
                   'logarithmic_scaled' means that the logarithm based 10 of
                   raw intensities multiplied by '_array_intensities.scaling' 
                   is calculated and stored, perhaps rounded to the nearest 
                   integer. Thus, linearization involves dividing the stored
                   values by '_array_intensities.scaling' and calculating 10
                   to the power of this number.
    
                   'raw' means that the data is a set of raw values straight 
                   from the detector.
    ;
    
        _item.name               '_array_intensities.linearity'
        _item.category_id          array_intensities
        _item.mandatory_code       yes
        _item_type.code            code
         loop_
        _item_enumeration.value   
        _item_enumeration.detail   
                                  'linear' .
                                  'offset'           
    ;
                   The value defined by  '_array_intensities.offset' should 
                   be added to each element value.  
    ;
                                  'scaling'
    ;
                   The value defined by '_array_intensities.scaling' should be 
                   multiplied with each element value.  
    ;
                                  'scaling_offset'   
    ;
                   The combination of the scaling and offset 
                   with the scale factor applied before the offset value.
    ;
                                  'sqrt_scaled'      
    ;
                   The square root of raw intensities multiplied by 
                   '_array_intensities.scaling' is calculated and stored, 
                   perhaps rounded to the nearest integer. Thus, 
                   linearization involves dividing the stored
                   values by '_array_intensities.scaling' and squaring the 
                   result. 
    ;
                                  'logarithmic_scaled'
    ;
                   The logarithm based 10 of raw intensities multiplied by 
                   '_array_intensities.scaling'  is calculated and stored, 
                   perhaps rounded to the nearest integer. Thus, 
                   linearization involves dividing the stored values by 
                   '_array_intensities.scaling' and calculating 10 to the 
                   power of this number.
    ;
                                  'raw'
    ;
                   The array consists of raw values to which no corrections have
                   been applied.  While the handling of the data is similar to 
                   that given for 'linear' data with no offset, the meaning of 
                   the data differs in that the number of incident photons is 
                   not necessarily linearly related to the number of counts 
                   reported.  This value is intended for use either in 
                   calibration experiments or to allow for handling more 
                   complex data fitting algorithms than are allowed for by 
                   this data item.
    ;
    
        save_
      
      
    save__array_intensities.offset
        _item_description.description
    ;
                   Offset value to add to array element values in the manner
                   described by item '_array_intensities.linearity'.
    ;
        _item.name                 '_array_intensities.offset'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        save_
    
    
    save__array_intensities.scaling
        _item_description.description
    ;
                   Multiplicative scaling value to be applied to array data
                   in the manner described by item
                   '_array_intensities.linearity'.
    ;
        _item.name                 '_array_intensities.scaling'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        save_
    
    
    save__array_intensities.overload
        _item_description.description
    ;
                   The saturation intensity level for this data array.
    ;
        _item.name                 '_array_intensities.overload'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        _item_units.code          'counts'
        save_
    
      
    save__array_intensities.undefined_value
        _item_description.description
    ;
                   A value to be substituted for undefined values in 
                   the data array.
    ;
        _item.name                 '_array_intensities.undefined_value'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        save_
    
    
    ###################
    # ARRAY_STRUCTURE #
    ###################
    
    
    save_ARRAY_STRUCTURE
        _category.description
    ;
         Data items in the ARRAY_STRUCTURE category record the organization and 
         encoding of array data which may be stored in the ARRAY_DATA category.
    ;
        _category.id                   array_structure
        _category.mandatory_code       no
        _category_key.name             '_array_structure.id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 -
    ;
    ;
         loop_
        _array_structure.id 
        _array_structure.encoding_type        
        _array_structure.compression_type     
        _array_structure.byte_order           
         image_1       "unsigned 16-bit integer"  none  little_endian
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_structure.byte_order
        _item_description.description
    ;
                   The order of bytes for integer values which require more
                   than 1-byte. 
    
                   (IBM-PC's and compatibles, and Dec-Vaxes use low-byte-first
                   ordered integers, whereas Hewlett Packard 700 
                   series, Sun-4 and Silicon Graphics use high-byte-first
                   ordered integers.  Dec-Alphas can produce/use either
                   depending on a compiler switch.)
    ;
    
        _item.name                     '_array_structure.byte_order'
        _item.category_id               array_structure
        _item.mandatory_code            yes 
        _item_type.code                 code
         loop_
        _item_enumeration.value        
        _item_enumeration.detail        
                                       'big_endian'
    ;
            The first byte in the byte stream of the bytes which make up an 
            integer value is the most significant byte of an integer. 
    ;
                                       'little_endian'
    ;
            The last byte in the byte stream of the bytes which make up an 
            integer value is the most significant byte of an integer.
    ;
         save_
    
    
    save__array_structure.compression_type 
        _item_description.description
    ;
                  Type of data compression method used to compress the array
                  data. 
    ;
        _item.name                   '_array_structure.compression_type'
        _item.category_id             array_structure
        _item.mandatory_code          no 
        _item_type.code               code
        _item_default.value           'none'
         loop_
        _item_enumeration.value       
        _item_enumeration.detail
                                      'none'
    ;
            Data are stored in normal format as defined by 
            '_array_structure.encoding_type' and 
            '_array_structure.byte_order'.
    ;
                                      'byte_offsets'
    ;
            Using the compression scheme defined in CBF definition
            Section 5.0.
    ;
                                      'packed'
    ;
            Using the 'packed' compression scheme, a CCP4-style packing
            (CBFlib section 3.3.2)
    ;
                                      'canonical'
    ;
            Using the 'canonical' compression scheme (CBFlib section
            3.3.1)
    ;
        save_
    
    
    save__array_structure.encoding_type
        _item_description.description
    ;
                   Data encoding of a single element of array data. 
                   
                   In several cases, the IEEE format is referenced.
                   See "IEEE Standard for Binary Floating-Point Arithmetic",
                   ANSI/IEEE Std 754-1985, the Institute of Electrical and
                   Electronics Engineers, Inc., NY 1985.  
    ;
    
        _item.name                '_array_structure.encoding_type'
        _item.category_id          array_structure
        _item.mandatory_code       yes 
        _item_type.code            uline
         loop_
        _item_enumeration.value   
                                  'unsigned 8-bit integer'
                                  'signed 8-bit integer'
                                  'unsigned 16-bit integer'
                                  'signed 16-bit integer'
                                  'unsigned 32-bit integer'
                                  'signed 32-bit integer'
                                  'signed 32-bit real IEEE'
                                  'signed 64-bit real IEEE'
                                  'signed 32-bit complex IEEE'
         save_
    
    
    save__array_structure.id
        _item_description.description
    ;             The value of '_array_structure.id' must uniquely identify 
                  each item of array data. 
    ;
        loop_
        _item.name                  
        _item.category_id             
        _item.mandatory_code          
                 '_array_structure.id'              array_structure      yes
                 '_array_data.array_id'             array_data           yes
                 '_array_structure_list.array_id'   array_structure_list yes
                 '_array_intensities.array_id'      array_intensities    yes
                 '_diffrn_data_frame.array_id'      diffrn_data_frame    yes
    
    
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_array_data.array_id'             '_array_structure.id'
                 '_array_structure_list.array_id'   '_array_structure.id'
                 '_array_intensities.array_id'      '_array_structure.id'
                 '_diffrn_data_frame.array_id'      '_array_structure.id'
    
         save_
    
    
    ########################
    # ARRAY_STRUCTURE_LIST #
    ########################
    
    
    save_ARRAY_STRUCTURE_LIST
        _category.description
    ;
         Data items in the ARRAY_STRUCTURE_LIST category record the size 
         and organization of each array dimension.
    
         The relationship to physical axes may be given.
    ;
        _category.id                   array_structure_list
        _category.mandatory_code       no
         loop_
        _category_key.name             '_array_structure_list.array_id'
                                       '_array_structure_list.index'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 - An image array of 1300 x 1200 elements.  The raster 
                        order of the image is left-to-right (increasing) in the
                        first dimension and bottom-to-top (decreasing) in 
                        the second dimension.
    ;
    ;
            loop_
           _array_structure_list.array_id  
           _array_structure_list.index
           _array_structure_list.dimension 
           _array_structure_list.precedence 
           _array_structure_list.direction
           _array_structure_list.axis_set_id
            image_1   1    1300    1     increasing  ELEMENT_X
            image_1   2    1200    2     decreasing  ELEMENY_Y
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_structure_list.array_id
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category. 
    ;
        _item.name                  '_array_structure_list.array_id'
        _item.category_id             array_structure_list
        _item.mandatory_code          yes
        _item_type.code               code
    save_
    
    
    save__array_structure_list.axis_set_id
        _item_description.description
    ;              This is a descriptor for the physical axis or set of axes 
                   corresponding to an array index.
                   
                   This data item is related to the axes of the detector 
                   itself given in DIFFRN_DETECTOR_AXIS, but usually differ
                   in that the axes in this category are the axes of the
                   coordinate system of reported data points, while the axes in
                   DIFFRN_DETECTOR_AXIS are the physical axes 
                   of the detector describing the "poise" of the detector as an
                   overall physical object.
                   
                   If there is only one axis in the set, the identifier of 
                   that axis should be used as the identifier of the set.
                   
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
               '_array_structure_list.axis_set_id'
                                      array_structure_list            yes
               '_array_structure_list_axis.axis_set_id'
                                      array_structure_list_axis       implicit
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_array_structure_list_axis.axis_set_id'
                                   '_array_structure_list.axis_set_id'
    
    
         save_
    
    
    save__array_structure_list.dimension
        _item_description.description
    ;              
                   The number of elements stored in the array structure in this 
                   dimension.
    ;
        _item.name                '_array_structure_list.dimension'
        _item.category_id          array_structure_list
        _item.mandatory_code       yes 
        _item_type.code            int
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                1  1
                                .  1
         save_
    
    
    save__array_structure_list.direction
        _item_description.description
    ;
                  Identifies the direction in which this array index changes.
    ;
        _item.name                '_array_structure_list.direction'
        _item.category_id          array_structure_list
        _item.mandatory_code       yes 
        _item_type.code            int
         loop_
        _item_enumeration.value
        _item_enumeration.detail        
    
                                  'increasing'
    ;
             Indicates the index changes from 1 to the maximum dimension.
    ;
                                  'decreasing'
    ;
             Indicates the index changes from the maximum dimension to 1.
    ;
         save_
    
    
    save__array_structure_list.index
        _item_description.description
    ;              
                   Identifies the one-based index of the row or column in the
                   array structure.
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
               '_array_structure_list.index'        array_structure_list   yes
               '_array_structure_list.precedence'   array_structure_list   yes
               '_array_element_size.index'          array_element_size     yes
    
        _item_type.code            int
    
         loop_
        _item_linked.child_name
        _item_linked.parent_name
              '_array_element_size.index'         '_array_structure_list.index'
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                1  1
                                .  1
         save_
    
    
    save__array_structure_list.precedence
        _item_description.description
    ;
                   Identifies the rank order in which this array index changes 
                   with respect to other array indices.  The precedence of 1  
                   indicates the index which changes fastest.
    ;
        _item.name                '_array_structure_list.precedence'
        _item.category_id          array_structure_list
        _item.mandatory_code       yes 
        _item_type.code            int
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                1  1
                                .  1
         save_
    
    
    #############################
    # ARRAY_STRUCTURE_LIST_AXIS #
    #############################
    
    save_ARRAY_STRUCTURE_LIST_AXIS
        _category.description
    ;
         Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe
         the physical settings of sets axes for the centres of pixels that 
         correspond to data points described in the 
         ARRAY_STRUCTURE_LIST category. 
         
         In the simplest cases, the physical increments of a single axis correspond
         to the increments of a single array index.  More complex organizations,
         e.g. spiral scans, may require coupled motions along multiple axes.
         
         Note that a spiral scan uses two coupled axis, one for the angular 
         direction, one for the radial direction.  This differs from a 
         cylindrical scan for which the two axes are not coupled into one set.
         
    ;
        _category.id                   array_structure_list_axis
        _category.mandatory_code       no
         loop_
        _category_key.name
                                      '_array_structure_list_axis.axis_set_id'
                                      '_array_structure_list_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'array_data_group'
         save_
    
    
    save__array_structure_list_axis.axis_id
        _item_description.description
    ;
                   The value of this data item is the identifier of one of
                   the axes from the set of axes for which settings are being 
                   specified.
    
                   Multiple axes may be specified for the same value of
                   '_array_structure_list_axis.axis_set_id'
    
                   This item is a pointer to '_axis.id' in the
                   AXIS category.
    ;
        _item.name                 '_array_structure_list_axis.axis_id'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       yes
        _item_units.code           code
         save_
    
    
    save__array_structure_list_axis.axis_set_id
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   set of axes for which axis settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   '_array_structure_list_axis.axis_set_id'.
    
                   This item is a pointer to
                   '_array_structure_list.axis_set_id'
                   in the ARRAY_STRUCTURE_LIST category.
                   
                   If this item is not specified, it defaults to the corresponding
                   axis identifier.
    ;
        _item.name                 '_array_structure_list_axis.axis_set_id'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       implicit
        _item_units.code           code
         save_
    
    
    save__array_structure_list_axis.angle
        _item_description.description
    ;
                   The setting of the specified axis in degrees for the first
                   data point of the array index with the corresponding value
                   of '_array_structure_list.axis_set_id'.  If the index is
                   specified as 'increasing' this will be the centre of the
                   pixel with index value 1.  If the index is specified as
                   'decreasing' this will be the centre of the pixel with
                   maximum index value. 
    ;
        _item.name                 '_array_structure_list_axis.angle'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__array_structure_list_axis.angle_increment
        _item_description.description
    ;
                   The pixel-centre-to-pixel-centre increment in the angular 
                   setting of the specified axis in degrees.  This is not 
                   meaningful in the case of 'constant velocity' spiral scans  
                   and should not be specified in that case.  
    
                   See '_array_structure_list_axis.angular_pitch'.
                   
    ;
        _item.name                 '_array_structure_list_axis.angle_increment'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__array_structure_list_axis.displacement
        _item_description.description
    ;
                   The setting of the specified axis in millimetres for the first
                   data point of the array index with the corresponding value
                   of '_array_structure_list.axis_set_id'.  If the index is
                   specified as 'increasing' this will be the centre of the
                   pixel with index value 1.  If the index is specified as
                   'decreasing' this will be the centre of the pixel with
                   maximum index value. 
    
    ;
        _item.name               '_array_structure_list_axis.displacement'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__array_structure_list_axis.displacement_increment
        _item_description.description
    ;
                   The pixel-centre-to-pixel-centre increment for the displacement 
                   setting of the specified axis in millimetres.
                   
    ;
        _item.name                 
            '_array_structure_list_axis.displacement_increment'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
      
    
    save__array_structure_list_axis.angular_pitch
        _item_description.description
    ;
                   The pixel-centre-to-pixel-centre distance for a one step 
                   change in the setting of the specified axis in millimetres.
                   
                   This is meaningful only for 'constant velocity' spiral scans,
                   or for uncoupled angular scans at a constant radius
                   (cylindrical scan) and should not be specified for cases
                   in which the angle between pixels, rather than the distance
                   between pixels is uniform.
                   
                   See '_array_structure_list_axis.angle_increment'.
                   
    ;
        _item.name               '_array_structure_list_axis.angular_pitch'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
       
    
    save__array_structure_list_axis.radial_pitch
        _item_description.description
    ;
                   The radial distance from one "cylinder" of pixels to the
                   next in millimetres.  If the scan is a 'constant velocity'
                   scan with differing angular displacements between pixels,
                   the value of this item may differ significantly from the
                   value of '_array_structure_list_axis.displacement_increment'.
                   
    ;
        _item.name               '_array_structure_list_axis.radial_pitch'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
      
    
    
    ########
    # AXIS #
    ########
    
    save_AXIS
        _category.description
    ;
         Data items in the AXIS category record the information required
         to describe the various goniometer, detector, source and other
         axes needed to specify a data collection.  The location of each
         axis is specified by two vectors: the axis itself, given as a unit
         vector, and an offset to the base of the unit vector.  These vectors
         are referenced to a right-handed laboratory coordinate system with
         its origin in the sample or specimen:
         
                                 | Y (to complete right-handed system)
                                 |
                                 |
                                 |
                                 |
                                 |
                                 |________________X
                                /       principal goniometer axis
                               /
                              /
                             /
                            /
                           /Z (to source)
    
    
                                                          
         Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from
         the sample or specimen along the  principal axis of the goniometer.
         
         Axis 2 (Y): The Y-axis completes an orthogonal right-handed system
         defined by the X-axis and the Z-axis (see below).
         
         Axis 3 (Z): The Z-axis is derived from the source axis which goes from 
         the sample to the source.  The Z-axis is the component of the source axis
         in the direction of the source orthogonal to the X-axis in the plane 
         defined by the X-axis and the source axis.
              
         These axes are based on the goniometer, not on the orientation of the 
         detector, gravity, etc.  The vectors necessary to specify all other
         axes are given by sets of three components in the order (X, Y, Z).
         If the axis involved is a rotation axis, it is right handed, i.e. as
         one views the object to be rotated from the origin (the tail) of the 
         unit vector, the rotation is clockwise.  If a translation axis is
         specified, the direction of the unit vector specifies the sense of
         positive translation.
         
         Note:  This choice of coordinate system is similar to, but significantly
         different from the choice in MOSFLM (Andrew G.W. Leslie, Harry Powell,
         MRC Laboratory of Molecular Biology, Hills Road, Cambridge CB2 2QH, UK
         http://www.dl.ac.uk/CCP/CCP4/dist/x-windows/Mosflm/).  In MOSFLM,
         X is along the X-ray beam (the CBF/imgCIF Z axis) and Z is along the 
         rotation axis.
    
         All rotations are given in degrees and all translations are given in mm.
         
         Axes may be dependent on one another.  The X-axis is the only goniometer
         axis the direction of which is strictly connected to the hardware.  All
         other axes are specified by the positions they would assume when the
         axes upon which they depend are at their zero points.
         
         When specifying detector axes, the axis is given to the beam centre.
         The location of the beam centre on the detector should be given in the
         DIFFRN_DETECTOR category in distortion-corrected mm from the (0,0) corner
         of the detector.
         
         It should be noted that many different origins arise in the definition
         of an experiment.  In particular, as noted above, we need to specify the
         location of the beam centre on the detector in terms of the origin of the
         detector, which is, of course, not coincident with the centre of the
         sample.  
    ;
        _category.id                   axis
        _category.mandatory_code       no
         loop_
        _category_key.name          '_axis.id' 
                                    '_axis.equipment'               
         loop_
        _category_group.id           'inclusive_group'
                                     'axis_group'
                                     'diffrn_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 -
            
            This example shows the axis specification of the axes of a kappa
            geometry goniometer (See "X-Ray Structure Determination, A Practical
            Guide", 2nd ed. by  G. H. Stout, L. H. Jensen, Wiley Interscience,
            1989, 453 pp, p 134.).
            
            There are three axes specified, and no offsets.  The outermost axis,
            omega, is pointed along the X-axis.  The next innermost axis, kappa,
            is at a 50 degree angle to the X-axis, pointed away from the source.
            The innermost axis, phi, aligns with the X-axis when omega and
            phi are at their zero-points.  If T-omega, T-kappa and T-phi
            are the transformation matrices derived from the axis settings,
            the complete transformation would be:
                x' = (T-omega) (T-kappa) (T-phi) x
    ;
    ;
             loop_
            _axis.id
            _axis.type
            _axis.equipment
            _axis.depends_on
            _axis.vector[1] _axis.vector[2] _axis.vector[3]
            omega rotation goniometer     .    1        0        0
            kappa rotation goniometer omega    -.64279  0       -.76604
            phi   rotation goniometer kappa    1        0        0   
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 2 -
            
            This example show the axis specification of the axes of a
            detector, source and gravity.  We have juggled the order as a
            reminder that the ordering of presentation of tokens is not
            significant.  We have taken the centre of rotation of the detector
            to be 68 millimetres in the direction away from the source.
    ;
    ;
            loop_
            _axis.id
            _axis.type
            _axis.equipment
            _axis.depends_on
            _axis.vector[1] _axis.vector[2] _axis.vector[3]
            _axis.offset[1] _axis.offset[2] _axis.offset[3]
            source       .        source     .       0     0     1   . . .
            gravity      .        gravity    .       0    -1     0   . . .
            tranz     translation detector rotz      0     0     1   0 0 -68
            twotheta  rotation    detector   .       1     0     0   . . .
            roty      rotation    detector twotheta  0     1     0   0 0 -68
            rotz      rotation    detector roty      0     0     1   0 0 -68
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__axis.depends_on
        _item_description.description
    ;             The value of '_axis.depends_on' specifies the next outermost
                  axis upon which this axis depends.
                  
                  This item is a pointer to '_axis.id' in the same category.
    ;
        _item.name                      '_axis.depends_on'
        _item.category_id                 axis
        _item.mandatory_code              no
    
         save_
    
    
    save__axis.equipment
        _item_description.description
    ;             The value of  '_axis.equipment' specifies the type of
                  equipment using the axis:  'goniometer', 'detector',
                  'gravity', 'source' or 'general'.
    ;
        _item.name                      '_axis.equipment'
        _item.category_id                 axis
        _item.mandatory_code              no
        _item_type.code                   ucode
        _item_default.value               general
         loop_
        _item_enumeration.value
        _item_enumeration.detail   goniometer
                                  'equipment used to orient or position samples'
                                   detector
                                  'equipment used to detect reflections'
                                   general
                                  'equipment used for general purposes'
                                   gravity
                                  'axis specifying the downward direction'
                                   source
                                  'axis specifying the direction sample to source'
    
         save_
    
    
    save__axis.offset[1]
        _item_description.description
    ;              The [1] element of the 3-element vector used to specify
                   the offset to the base of a rotation or translation axis.
                   
                   The vector is specified in millimetres
    ;
        _item.name                  '_axis.offset[1]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    
    save__axis.offset[2]
        _item_description.description
    ;              The [2] element of the 3-element vector used to specify
                   the offset to the base of a rotation or translation axis.
                   
                   The vector is specified in millimetres
    ;
        _item.name                  '_axis.offset[2]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    
    save__axis.offset[3]
        _item_description.description
    ;              The [3] element of the 3-element vector used to specify
                   the offset to the base of a rotation or translation axis.
                   
                   The vector is specified in millimetres
    ;
        _item.name                  '_axis.offset[3]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    
    save__axis.id
        _item_description.description
    ;             The value of '_axis.id' must uniquely identify
                  each axis relevant to the experiment.  Note that multiple
                  pieces of equipment may share the same axis (e.g. a twotheta
                  arm), so that the category key for AXIS also includes the
                  equipment.
    ;
        loop_
        _item.name
        _item.category_id
        _item.mandatory_code
             '_axis.id'                         axis                    yes
             '_array_structure_list_axis.axis_id'
                                                array_structure_list_axis
                                                                        yes
             '_diffrn_detector_axis.axis_id'    diffrn_detector_axis    yes
             '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes
             '_diffrn_scan_axis.axis_id'        diffrn_scan_axis        yes
             '_diffrn_scan_frame_axis.axis_id'  diffrn_scan_frame_axis  yes
    
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
             '_axis.depends_on'                   '_axis.id'
             '_array_structure_list_axis.axis_id' '_axis.id'
             '_diffrn_detector_axis.axis_id'      '_axis.id'
             '_diffrn_measurement_axis.axis_id'   '_axis.id'
             '_diffrn_scan_axis.axis_id'          '_axis.id'      
             '_diffrn_scan_frame_axis.axis_id'    '_axis.id'
    
         save_
    
    
    save__axis.type
        _item_description.description
    ;             The value of '_axis.type' specifies the type of
                  axis:  'rotation', 'translation' (or 'general' when
                  the type is not relevant, as for gravity).
    ;
        _item.name                      '_axis.type'
        _item.category_id                 axis
        _item.mandatory_code              no
        _item_type.code                   ucode
        _item_default.value               general
         loop_
        _item_enumeration.value
        _item_enumeration.detail      rotation
                                     'right-handed axis of rotation'
                                      translation
                                     'translation in the direction of the axis'
                                      general
                                     'axis for which the type is not relevant'
    
         save_
    
    
    save__axis.vector[1]
        _item_description.description
    ;              The [1] element of the 3-element vector used to specify
                   the direction of a rotation or translation axis.
                   The vector should be normalized to be a unit vector and
                   is dimensionless.
    ;
        _item.name                  '_axis.vector[1]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
         save_
    
    save__axis.vector[2]
        _item_description.description
    ;              The [2] element of the 3-element vector used to specify
                   the direction of a rotation or translation axis.
                   The vector should be normalized to be a unit vector and
                   is dimensionless.
    ;
        _item.name                  '_axis.vector[2]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
         save_
    
    save__axis.vector[3]
        _item_description.description
    ;              The [3] element of the 3-element vector used to specify
                   the direction of a rotation or translation axis.
                   The vector should be normalized to be a unit vector and
                   is dimensionless.
    ;
        _item.name                  '_axis.vector[3]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
         save_
    
    
    
    #####################
    # DIFFRN_DATA_FRAME #
    #####################
    
    
    save_DIFFRN_DATA_FRAME
        _category.description
    ;
                  Data items in the DIFFRN_DATA_FRAME category record
                  the details about each frame of data. 
                  
                  The items in this category were previously in a
                  DIFFRN_FRAME_DATA category, which is now deprecated.
                  The items from the old category are provided
                  as aliases but should not be used for new work.
    ;
        _category.id                   diffrn_data_frame
        _category.mandatory_code       no
         loop_
        _category_key.name             '_diffrn_data_frame.id'
                                       '_diffrn_data_frame.detector_element_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 - A frame containing data from 4 frame elements.
                    Each frame element has a common array configuration
                    'array_1' described in ARRAY_STRUCTURE and related
                    categories.  The data for each detector element is 
                    stored in four groups of binary data in the
                    ARRAY_DATA category, linked by the array_id and
                    binary_id
    ;
    ;
            loop_
            _diffrn_data_frame.id
            _diffrn_data_frame.detector_element_id
            _diffrn_data_frame.array_id
            _diffrn_data_frame.binary_id
            frame_1   d1_ccd_1  array_1  1  
            frame_1   d1_ccd_2  array_1  2 
            frame_1   d1_ccd_3  array_1  3 
            frame_1   d1_ccd_4  array_1  4 
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
    
    
    save__diffrn_data_frame.array_id
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category. 
    ;
        _item.name                  '_diffrn_data_frame.array_id'
        _item.category_id             diffrn_data_frame
        _item.mandatory_code          yes
        _item_aliases.alias_name    '_diffrn_frame_data.array_id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0.00
        _item_type.code               code
         save_
    
    
    save__diffrn_data_frame.binary_id
        _item_description.description
    ;             This item is a pointer to '_array_data.binary_id' in the
                  ARRAY_DATA category. 
    ;
        _item.name                  '_diffrn_data_frame.binary_id'
        _item.category_id             diffrn_data_frame
        _item.mandatory_code          implicit
        _item_aliases.alias_name    '_diffrn_frame_data.binary_id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               int
         save_
    
    
    save__diffrn_data_frame.detector_element_id
        _item_description.description
    ;             
                   This item is a pointer to '_diffrn_detector_element.id'
                   in the DIFFRN_DETECTOR_ELEMENT category. 
    ;
        _item.name                  '_diffrn_data_frame.detector_element_id'
        _item.category_id             diffrn_data_frame
        _item.mandatory_code          yes
        _item_aliases.alias_name    '_diffrn_frame_data.detector_element_id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         save_
    
    
    save__diffrn_data_frame.id
        _item_description.description
    ;             
                  The value of '_diffrn_data_frame.id' must uniquely identify
                  each complete frame of data.
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
               '_diffrn_data_frame.id'        diffrn_data_frame  yes
               '_diffrn_refln.frame_id'       diffrn_refln       yes
               '_diffrn_scan.frame_id_start'  diffrn_scan        yes
               '_diffrn_scan.frame_id_end'    diffrn_scan        yes
               '_diffrn_scan_frame.frame_id'  diffrn_scan_frame  yes
               '_diffrn_scan_frame_axis.frame_id'  
                                              diffrn_scan_frame_axis
                                                                 yes
        _item_aliases.alias_name    '_diffrn_frame_data.id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_diffrn_refln.frame_id'        '_diffrn_data_frame.id'
               '_diffrn_scan.frame_id_start'   '_diffrn_data_frame.id'
               '_diffrn_scan.frame_id_end'     '_diffrn_data_frame.id'
               '_diffrn_scan_frame.frame_id'   '_diffrn_data_frame.id'
               '_diffrn_scan_frame_axis.frame_id'
                                               '_diffrn_data_frame.id'
         save_
    
    
    ##########################################################################
    #  The following is a restatement of the mmCIF DIFFRN_DETECTOR,          #
    #  DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for      #
    #  the CBF/imgCIF extensions                                             #
    ##########################################################################
    
    ###################
    # DIFFRN_DETECTOR #
    ###################
    
    
    save_DIFFRN_DETECTOR
        _category.description
    ;              Data items in the DIFFRN_DETECTOR category describe the 
                   detector used to measure the scattered radiation, including
                   any analyser and post-sample collimation.
    ;
        _category.id                  diffrn_detector
        _category.mandatory_code      no
         loop_
        _category_key.name          '_diffrn_detector.diffrn_id'
                                    '_diffrn_detector.id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 - based on PDB entry 5HVP and laboratory records for the
                    structure corresponding to PDB entry 5HVP
    ;
    ;
        _diffrn_detector.diffrn_id             'd1'
        _diffrn_detector.detector              'multiwire'
        _diffrn_detector.type                  'Siemens'
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__diffrn_detector.details
        _item_description.description
    ;              A description of special aspects of the radiation detector.
    ;
        _item.name                  '_diffrn_detector.details'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_detector_details'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code                   text
        _item_examples.case        'slow mode' 
         save_
    
    
    save__diffrn_detector.detector
        _item_description.description
    ;              The general class of the radiation detector.
    ;
        _item.name                  '_diffrn_detector.detector'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
         loop_
        _item_aliases.alias_name
        _item_aliases.dictionary
        _item_aliases.version       '_diffrn_radiation_detector'
                                      cifdic.c91
                                      1.0
                                    '_diffrn_detector'
                                      cif_core.dic
                                      2.0
        _item_type.code               text
         loop_
        _item_examples.case          'photographic film'
                                     'scintillation counter'
                                     'CCD plate'
                                     'BF~3~ counter'
         save_
    
    
    save__diffrn_detector.diffrn_id
        _item_description.description
    ;              This data item is a pointer to '_diffrn.id' in the DIFFRN
                   category.
    
                   The value of '_diffrn.id' uniquely defines a set of
                   diffraction data.
    ;
        _item.name                  '_diffrn_detector.diffrn_id'
        _item.mandatory_code          yes
         save_
    
    
    save__diffrn_detector.dtime
        _item_description.description
    ;              The deadtime in microseconds of the detectors used to
                   measure the diffraction intensities.
    ;
        _item.name                  '_diffrn_detector.dtime'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
         loop_
        _item_aliases.alias_name
        _item_aliases.dictionary
        _item_aliases.version       '_diffrn_radiation_detector_dtime'
                                      cifdic.c91
                                      1.0
                                    '_diffrn_detector_dtime'
                                      cif_core.dic
                                      2.0
         loop_  
        _item_range.maximum           
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
        _item_units.code              microseconds
         save_
    
    
    save__diffrn_detector.id
        _item_description.description
    ;             
                   The value of '_diffrn_detector.id' must uniquely identify
                   each detector used to collect each diffraction data set.
    
                   If the value of '_diffrn_detector.id' is not given, it is
                   implicitly equal to the value of
                   '_diffrn_detector.diffrn_id'
    ;
         loop_
        _item.name                 
        _item.category_id
        _item.mandatory_code
                 '_diffrn_detector.id'         diffrn_detector       implicit
                 '_diffrn_detector_axis.detector_id'
                                               diffrn_detector_axis       yes
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_detector_axis.detector_id'
                                             '_diffrn_detector.id'
    
        _item_type.code               code
         save_
    
    
    save__diffrn_detector.number_of_axes
        _item_description.description
    ;             
                   The value of '_diffrn_detector.number_of_axes' gives the 
                   number of axes of the positioner for the detector identified 
                   by '_diffrn_detector.id'.
                   
                   The word "positioner" is a general term used in
                   instrumentation design for devices that are used to change
                   the positions of portions of apparatus by linear
                   translation, rotation, or combinations of such motions.
                   
                   Axes which are used to provide a coordinate system for the
                   face of an area detetctor should not be counted for this
                   data item.
    
                   The description of each axis should be provided by entries 
                   in DIFFRN_DETECTOR_AXIS.
    ;
        _item.name                  '_diffrn_detector.number_of_axes'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
         loop_
        _item_range.maximum
        _item_range.minimum           .   1
                                      1   1
        _item_type.code               int
         save_
    
    
    save__diffrn_detector.type
        _item_description.description
    ;              The make, model or name of the detector device used.
    ;
        _item.name                  '_diffrn_detector.type'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_detector_type'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         save_
    
    
    ########################
    # DIFFRN_DETECTOR_AXIS #
    ########################
    
    
    save_DIFFRN_DETECTOR_AXIS
        _category.description
    ;
         Data items in the DIFFRN_DETECTOR_AXIS category associate
         axes with detectors.
    ;
        _category.id                   diffrn_detector_axis
        _category.mandatory_code       no
         loop_
        _category_key.name          '_diffrn_detector_axis.detector_id'
                                    '_diffrn_detector_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_detector_axis.axis_id
        _item_description.description
    ;
                   This data item is a pointer to '_axis.id' in
                   the AXIS category.
    ;
        _item.name                  '_diffrn_detector_axis.axis_id'
        _item.category_id             diffrn_detector_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_detector_axis.detector_id
        _item_description.description
    ;
                   This data item is a pointer to '_diffrn_detector.id' in
                   the DIFFRN_DETECTOR category.
    
                   This item was previously named '_diffrn_detector_axis.id'
                   which is now a deprecated name.  The old name is
                   provided as an alias but should not be used for new work.
    
    ;
        _item.name                  '_diffrn_detector_axis.detector_id'
        _item.category_id             diffrn_detector_axis
        _item.mandatory_code          yes
        _item_aliases.alias_name    '_diffrn_detector_axis.id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         save_
    
    
    ###########################
    # DIFFRN_DETECTOR_ELEMENT #
    ###########################
    
    
    save_DIFFRN_DETECTOR_ELEMENT
        _category.description
    ;
                  Data items in the DIFFRN_DETECTOR_ELEMENT category record
                  the details about spatial layout and other characteristics
                  of each element of a detector which may have multiple elements.
                  
                  In most cases, the more detailed information provided
                  in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS
                  are preferable to simply providing the centre.
    
    ;
        _category.id                   diffrn_detector_element
        _category.mandatory_code       no
         loop_
        _category_key.name             '_diffrn_detector_element.id'
                                       '_diffrn_detector_element.detector_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 - Detector d1 is composed of four CCD detector elements,
            each 200 mm by 200 mm, arranged in a square. in the pattern
                        
                       1     2
                          *
                       3     4
    
            Note that the beam centre is slightly displaced from each of the
            detector elements, just beyond the lower right corner of 1,
            the lower left corner of 2, the upper right corner of 3 and
            the upper left corner of 4.
    ;
    ;
            loop_
            _diffrn_detector_element.detector_id
            _diffrn_detector_element.id
            _diffrn_detector_element.center[1]
            _diffrn_detector_element.center[2]
            d1     d1_ccd_1  201.5 -1.5
            d1     d1_ccd_2  -1.8  -1.5
            d1     d1_ccd_3  201.6 201.4  
            d1     d1_ccd_4  -1.7  201.5
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
    
    
    save__diffrn_detector_element.center[1]
        _item_description.description
    ;             
                  The value of '_diffrn_detector_element.center[1]' is the X
                  component of the distortion-corrected beam-centre in mm from
                  the (0, 0) (lower left) corner of the detector element viewed
                  from the sample side.
                  
                  The X and Y axes are the laboratory coordinate system
                  coordinates defined in the AXIS category measured
                  when all positioning axes for the detector are at their zero
                  settings.  If the resulting X or Y axis is then orthogonal to the
                  detector, the Z axis is used instead of the orthogonal axis.
                  
    ;
        _item.name                  '_diffrn_detector_element.center[1]'
        _item.category_id             diffrn_detector_element
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
    
        save_
    
    
    save__diffrn_detector_element.center[2]
        _item_description.description
    ;             
                  The value of '_diffrn_detector_element.center[2]' is the Y
                  component of the distortion-corrected beam-centre in mm from
                  the (0, 0) (lower left) corner of the detector element viewed
                  from the sample side.
                  
                  The X and Y axes are the laboratory coordinate system
                  coordinates defined in the AXIS category measured
                  when all positioning axes for the detector are at their zero
                  settings.  If the resulting X or Y axis is then orthogonal to the
                  detector, the Z axis is used instead of the orthogonal axis.
    
    ;
        _item.name                  '_diffrn_detector_element.center[2]'
        _item.category_id             diffrn_detector_element
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
    
        save_
    
    
    save__diffrn_detector_element.id
        _item_description.description
    ;             
                  The value of '_diffrn_detector_element.id' must uniquely
                  identify each element of a detector.
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
               '_diffrn_detector_element.id'
               diffrn_detector_element
               yes
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_diffrn_data_frame.detector_element_id'
               '_diffrn_detector_element.id'
    
         save_
    
    
    save__diffrn_detector_element.detector_id
        _item_description.description
    ;             
                   This item is a pointer to '_diffrn_detector.id'
                   in the DIFFRN_DETECTOR category. 
    ;
        _item.name                  '_diffrn_detector_element.detector_id'
        _item.category_id             diffrn_detector_element
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    
    ########################
    ## DIFFRN_MEASUREMENT ##
    ########################
    
    
    save_DIFFRN_MEASUREMENT
        _category.description
    ;              Data items in the DIFFRN_MEASUREMENT category record details
                   about the device used to orient and/or position the crystal
                   during data measurement and the manner in which the
                   diffraction data were measured.
    ;
        _category.id                  diffrn_measurement
        _category.mandatory_code      no
         loop_
        _category_key.name          '_diffrn_measurement.device'
                                    '_diffrn_measurement.diffrn_id'
                                    '_diffrn_measurement.id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 - based on PDB entry 5HVP and laboratory records for the
                    structure corresponding to PDB entry 5HVP
    ;
    ;
        _diffrn_measurement.diffrn_id          'd1'
        _diffrn_measurement.device             '3-circle camera'
        _diffrn_measurement.device_type        'Supper model x'
        _diffrn_measurement.device_details     'none'
        _diffrn_measurement.method             'omega scan'
        _diffrn_measurement.details
        ; Need new example here
        ;
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991).
                    Acta Cryst. C47, 2276-2277].
    ;
    ;
        _diffrn_measurement.diffrn_id       's1'
        _diffrn_measurement.device_type     'Philips PW1100/20 diffractometer'
        _diffrn_measurement.method          'theta/2theta (\q/2\q)'
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__diffrn_measurement.device
        _item_description.description
    ;              The general class of goniometer or device used to support
                   and orient the specimen.
                   
                   If the value of '_diffrn_measurement.device' is not given,
                   it is implicitly equal to the value of
                   '_diffrn_measurement.diffrn_id'.
    
                   Either '_diffrn_measurement.device' or
                   '_diffrn_measurement.id' may be used to link to other
                   categories.  If the experimental setup admits multiple
                   devices, then '_diffrn_measurement.id' is used to provide
                   a unique link.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
                 '_diffrn_measurement.device'  diffrn_measurement      implicit
                 '_diffrn_measurement_axis.measurement_device' 
                                               diffrn_measurement_axis implicit
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_measurement_axis.measurement_device'  
                                             '_diffrn_measurement.device'
        _item_aliases.alias_name    '_diffrn_measurement_device'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          '3-circle camera'
                                     '4-circle camera'
                                     'kappa-geometry camera'
                                     'oscillation camera'
                                     'precession camera'
         save_
    
    
    save__diffrn_measurement.device_details
        _item_description.description
    ;              A description of special aspects of the device used to
                   measure the diffraction intensities.
    ;
        _item.name                  '_diffrn_measurement.device_details'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_device_details'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
        _item_examples.case
    ;                                 commercial goniometer modified locally to
                                      allow for 90\% \t arc
    ;
         save_
    
    
    save__diffrn_measurement.device_type
        _item_description.description
    ;              The make, model or name of the measurement device
                   (goniometer) used.
    ;
        _item.name                  '_diffrn_measurement.device_type'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_device_type'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          'Supper model q'
                                     'Huber model r'
                                     'Enraf-Nonius model s'
                                     'homemade'
         save_
    
    
    save__diffrn_measurement.diffrn_id
        _item_description.description
    ;              This data item is a pointer to '_diffrn.id' in the DIFFRN 
                   category.
    ;
        _item.name                  '_diffrn_measurement.diffrn_id'
        _item.mandatory_code          yes
         save_
    
    
    save__diffrn_measurement.details
        _item_description.description
    ;              A description of special aspects of the intensity
                   measurement.
    ;
        _item.name                  '_diffrn_measurement.details'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_details'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
        _item_examples.case
    ;                                 440 frames, 0.20 degrees, 150 sec, detector
                                      distance 12 cm, detector angle 22.5 degrees
    ;
         save_
    
    
    save__diffrn_measurement.id
        _item_description.description
    ;             
                   The value of '_diffrn_measurement.id' must uniquely identify
                   the set of mechanical characteristics of the device used to 
                   orient and/or position the sample used during collection 
                   of each diffraction data set.
    
                   If the value of '_diffrn_measurement.id' is not given, it is
                   implicitly equal to the value of 
                   '_diffrn_measurement.diffrn_id'.
    
                   Either '_diffrn_measurement.device' or
                   '_diffrn_measurement.id' may be used to link to other
                   categories.  If the experimental setup admits multiple
                   devices, then '_diffrn_measurement.id' is used to provide
                   a unique link.
    ;
         loop_
        _item.name                 
        _item.category_id
        _item.mandatory_code
                 '_diffrn_measurement.id'      diffrn_measurement      implicit
                 '_diffrn_measurement_axis.measurement_id'
                                               diffrn_measurement_axis implicit
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_measurement_axis.measurement_id'
                                             '_diffrn_measurement.id'
    
        _item_type.code               code
         save_
    
    
    save__diffrn_measurement.method
        _item_description.description
    ;              Method used to measure intensities.
    ;
        _item.name                  '_diffrn_measurement.method'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_method'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
        _item_examples.case
          'profile data from theta/2theta (\q/2\q) scans'
         save_
    
    
    save__diffrn_measurement.number_of_axes
        _item_description.description
    ;             
                   The value of '_diffrn_measurement.number_of_axes' gives the 
                   number of axes of the positioner for the goniometer or
                   other sample orientation or positioning device identified 
                   by '_diffrn_measurement.id'.
    
                   The description of the axes should be provided by entries in 
                   DIFFRN_MEASUREMENT_AXIS.
    ;
        _item.name                  '_diffrn_measurement.number_of_axes'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
         loop_
        _item_range.maximum
        _item_range.minimum           .   1
                                      1   1
        _item_type.code               int
         save_
    
    
    save__diffrn_measurement.specimen_support
        _item_description.description
    ;              The physical device used to support the crystal during data
                   collection.
    ;
        _item.name                  '_diffrn_measurement.specimen_support'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_specimen_support'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          'glass capillary'
                                     'quartz capillary'
                                     'fiber'
                                     'metal loop'
         save_
    
    
    ###########################
    # DIFFRN_MEASUREMENT_AXIS #
    ###########################
    
    
    save_DIFFRN_MEASUREMENT_AXIS
        _category.description
    ;
         Data items in the DIFFRN_MEASUREMENT_AXIS category associate
         axes with goniometers.
    ;
        _category.id                   diffrn_measurement_axis
        _category.mandatory_code       no
         loop_
        _category_key.name
                                  '_diffrn_measurement_axis.measurement_device'
                                    '_diffrn_measurement_axis.measurement_id'
                                    '_diffrn_measurement_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_measurement_axis.axis_id
        _item_description.description
    ;
                   This data item is a pointer to '_axis.id' in
                   the AXIS category.
    ;
        _item.name                  '_diffrn_measurement_axis.axis_id'
        _item.category_id             diffrn_measurement_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_measurement_axis.measurement_device
        _item_description.description
    ;
                   This data item is a pointer to '_diffrn_measurement.device'
                   in the DIFFRN_MEASUREMENT category.
    
    ;
        _item.name
          '_diffrn_measurement_axis.measurement_device'
        _item.category_id             diffrn_measurement_axis
        _item.mandatory_code          implicit
        _item_type.code               text
         save_
    
    
    save__diffrn_measurement_axis.measurement_id
        _item_description.description
    ;
                   This data item is a pointer to '_diffrn_measurement.id' in
                   the DIFFRN_MEASUREMENT category.
                  
                   This item was previously named '_diffrn_measurement_axis.id'
                   which is now a deprecated name.  The old name is
                   provided as an alias but should not be used for new work.
    
    ;
        _item.name                  '_diffrn_measurement_axis.measurement_id'
        _item.category_id             diffrn_measurement_axis
        _item_aliases.alias_name    '_diffrn_measurement_axis.id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0.00
        _item.mandatory_code          implicit
        _item_type.code               code
         save_
    
    
    ####################
    # DIFFRN_RADIATION #
    ####################
    
    
    save_DIFFRN_RADIATION
        _category.description
    ;              Data items in the DIFFRN_RADIATION category describe
                   the radiation used in measuring diffraction intensities,
                   its collimation and monochromatisation before the sample.
    
                   Post-sample treatment of the beam is described by data
                   items in the DIFFRN_DETECTOR category.
    
    ;
        _category.id                  diffrn_radiation
        _category.mandatory_code      no
        _category_key.name          '_diffrn_radiation.diffrn_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 - based on PDB entry 5HVP and laboratory records for the
                    structure corresponding to PDB entry 5HVP
    ;
    ;
        _diffrn_radiation.diffrn_id            'set1'
    
        _diffrn_radiation.collimation          '0.3 mm double pinhole'
        _diffrn_radiation.monochromator        'graphite'
        _diffrn_radiation.type                 'Cu K\a'
        _diffrn_radiation.wavelength_id         1
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991).
                    Acta Cryst. C47, 2276-2277].
    ;
    ;
        _diffrn_radiation.wavelength_id    1
        _diffrn_radiation.type             'Cu K\a'
        _diffrn_radiation.monochromator    'graphite'
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    save__diffrn_radiation.collimation
        _item_description.description
    ;              The collimation or focusing applied to the radiation.
    ;
        _item.name                  '_diffrn_radiation.collimation'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_collimation'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          '0.3 mm double-pinhole'
                                     '0.5 mm'
                                     'focusing mirrors'
         save_
    
    
    save__diffrn_radiation.diffrn_id
        _item_description.description
    ;              This data item is a pointer to '_diffrn.id' in the DIFFRN
                   category.
    ;
        _item.name                  '_diffrn_radiation.diffrn_id'
        _item.mandatory_code          yes
         save_
    
    
    
    save__diffrn_radiation.div_x_source
        _item_description.description
    ;              Beam crossfire in degrees parallel to the laboratory X axis
                   (see AXIS category).
                   
                   This is a characteristic of the xray beam as it illuminates
                   the sample (or specimen) after all monochromation and 
                   collimation.
                   
                   This is the esd of the directions of photons in the X-Z plane
                   around the mean source beam direction.
                   
                   Note that some synchrotrons specify this value in milliradians,
                   in which case a conversion would be needed.  To go from a
                   value in milliradians to a value in degrees, multiply by 0.180
                   and divide by π.
    
    ;
        _item.name                  '_diffrn_radiation.div_x_source'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_type.code               float
        _item_units.code              degrees
         save_
    
    
    save__diffrn_radiation.div_y_source
        _item_description.description
    ;              Beam crossfire in degrees parallel to the laboratory Y axis
                   (see AXIS category).
                   
                   This is a characteristic of the xray beam as it illuminates
                   the sample (or specimen) after all monochromation and 
                   collimation.
                   
                   This is the esd of the directions of photons in the Y-Z plane
                   around the mean source beam direction.
    
                   Note that some synchrotrons specify this value in milliradians,
                   in which case a conversion would be needed.  To go from a
                   value in milliradians to a value in degrees, multiply by 0.180
                   and divide by π.
    
    ;
        _item.name                  '_diffrn_radiation.div_y_source'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_type.code               float
        _item_units.code              degrees
        _item_default.value           0.0
         save_
    
    
    save__diffrn_radiation.div_x_y_source
        _item_description.description
    ;              Beam crossfire correlation degrees2 between the
                   crossfire laboratory X-axis component and the crossfire
                   laboratory Y-axis component (see AXIS category).
                   
                   This is a characteristic of the xray beam as it illuminates
                   the sample (or specimen) after all monochromation and 
                   collimation.
                   
                   This is the mean of the products of the deviations of the
                   direction of each photons in X-Z plane times the deviations
                   of the direction of the same photon in the Y-Z plane
                   around the mean source beam direction.  This will be zero
                   for uncorrelated crossfire.
                   
                   Note that some synchrotrons specify this value in 
                   milliradians2, in which case a conversion would be needed.  
                   To go from a value in milliradians2 to a value in
                   degrees2, multiply by 0.1802 and divide by π2.
    
    ;
        _item.name                  '_diffrn_radiation.div_x_y_source'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_type.code               float
        _item_units.code              degrees_squared
        _item_default.value           0.0
         save_
    
    save__diffrn_radiation.filter_edge
        _item_description.description
    ;              Absorption edge in Ångstroms of the radiation filter used.
    ;
        _item.name                  '_diffrn_radiation.filter_edge'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_filter_edge'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum           
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
        _item_units.code              angstroms
         save_
    
    save__diffrn_radiation.inhomogeneity
        _item_description.description
    ;              Half-width in millimetres of the incident beam in the
                   direction perpendicular to the diffraction plane.
    ;
        _item.name                  '_diffrn_radiation.inhomogeneity'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_inhomogeneity'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum           
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    save__diffrn_radiation.monochromator
        _item_description.description
    ;              The method used to obtain monochromatic radiation. If a
                   monochromator crystal is used the material and the
                   indices of the Bragg reflection are specified.
    ;
        _item.name                  '_diffrn_radiation.monochromator'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_monochromator'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          'Zr filter'
                                     'Ge 220'
                                     'none'
                                     'equatorial mounted graphite'
         save_
    
    save__diffrn_radiation.polarisn_norm
        _item_description.description
    ;              The angle in degrees, as viewed from the specimen, between the
                   perpendicular component of the polarisation and the diffraction
                   plane. See _diffrn_radiation_polarisn_ratio.
    ;
        _item.name                  '_diffrn_radiation.polarisn_norm'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_polarisn_norm'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum           
        _item_range.minimum           90.0  90.0
                                      90.0 -90.0
                                     -90.0 -90.0
        _item_type.code               float
        _item_units.code              degrees
         save_
    
    save__diffrn_radiation.polarisn_ratio
        _item_description.description
    ;              Polarisation ratio of the diffraction beam incident on the
                   crystal. It is the ratio of the perpendicularly polarised to
                   the parallel polarised component of the radiation. The
                   perpendicular component forms an angle of
                   '_diffrn_radiation.polarisn_norm' to the normal to the
                   diffraction plane of the sample (i.e. the plane containing
                   the incident and reflected beams).
    ;
        _item.name                  '_diffrn_radiation.polarisn_ratio'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_polarisn_ratio'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum           
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
         save_
    
    
    
    save__diffrn_radiation.polarizn_source_norm
        _item_description.description
    ;              The angle in degrees, as viewed from the specimen, between
                   the normal to the polarization plane and the laboratory Y
                   axis as defined in the AXIS category.
                   
                   Note that this is the angle of polarization of the source 
                   photons, either directly from a synchrotron beamline or
                   from a monchromater.
                   
                   This differs from the value of
                   '_diffrn_radiation.polarisn_norm'
                   in that '_diffrn_radiation.polarisn_norm' refers to
                   polarization relative to the diffraction plane rather than
                   to the laboratory axis system.
                   
                   In the case of an unpolarized beam, or a beam with true
                   circular polarization, in which no single plane of
                   polarization can be determined, the plane should be taken
                   as the X-Z plane, and the angle as 0.
                   
                   See '_diffrn_radiation.polarizn_source_ratio'.
    ;
        _item.name                  '_diffrn_radiation.polarizn_source_norm'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
         loop_
        _item_range.maximum           
        _item_range.minimum           90.0   90.0
                                      90.0  -90.0
                                     -90.0  -90.0
        _item_type.code               float
        _item_units.code              degrees
        _item_default.value           0.0
         save_
    
    
    save__diffrn_radiation.polarizn_source_ratio
        _item_description.description
    ;              (Ip-In)/(Ip+In), where Ip is the intensity (amplitude
                   squared) of the electric vector in the plane of
                   polarization and In is the intensity (amplitude squared)
                   of the electric vector in plane of the normal to the
                   plane of polarization.
                   
                   In the case of an unpolarized beam, or a beam with true
                   circular polarization, in which no single plane of
                   polarization can be determined, the plane is be taken
                   as the X-Z plane, and the normal is parallel to the Y-axis.
                   
                   Thus, if we had complete polarization in the plane of
                   polarization, the value of 
                   '_diffrn_radiation.polarizn_source_ratio' would
                   be 1, and an unpolarized beam would have a value of 0.
                   
                   If the X-axis has been chosen to lie in the plane of
                   polarization, this definition will agree with the definition
                   of "MONOCHROMATOR" in the Denzo glossary, and values of near
                   1 should be expected for a bending magnet source.  However,
                   if the X-axis were, for some reason to be, say,
                   perpendicular to the polarization plane (not a common
                   choice), then the Denzo value would be the negative of
                   '_diffrn_radiation.polarizn_source_ratio'.
                   
                   See http://www.hkl-xray.com for information on Denzo, and
                   Z. Otwinowski and W. Minor, "Processing of X-ray
                   Diffraction Data Collected in Oscillation Mode", Methods
                   in Enzymology, Volume 276: Macromolecular Crystallography,
                   part A, p.307-326, 1997,C.W. Carter, Jr. & R. M. Sweet,
                   Eds., Academic Press.
    
                   This differs both in the choice of ratio and choice of
                   orientation from '_diffrn_radiation.polarisn_ratio', which,
                   unlike '_diffrn_radiation.polarizn_source_ratio', is
                   unbounded.
    
    ;
        _item.name                  '_diffrn_radiation.polarizn_source_ratio'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
         loop_
        _item_range.maximum           
        _item_range.minimum           1.0    1.0
                                      1.0   -1.0
                                     -1.0   -1.0
        _item_type.code               float
         save_
    
    
    save__diffrn_radiation.probe
        _item_description.description
    ;              Name of the type of radiation used. It is strongly
                   encouraged that this field be specified so that the
                   probe radiation can be simply determined.
    ;
        _item.name                  '_diffrn_radiation.probe'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_probe'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               line
         loop_
        _item_enumeration.value      'x-ray'
                                     'neutron'
                                     'electron'
                                     'gamma'
         save_
    
    save__diffrn_radiation.type
        _item_description.description
    ;              The nature of the radiation. This is typically a description
                   of the X-ray wavelength in Siegbahn notation.
    ;
        _item.name                  '_diffrn_radiation.type'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_type'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               line
         loop_
        _item_examples.case          'CuK\a'
                                     'Cu K\a~1~'
                                     'Cu K-L~2,3~' 
                                     'white-beam'
    
         save_
    
    save__diffrn_radiation.xray_symbol
        _item_description.description
    ;              The IUPAC symbol for the X-ray wavelength for probe
                   radiation.
    ;
        _item.name                  '_diffrn_radiation.xray_symbol'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_xray_symbol'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               line
         loop_
        _item_enumeration.value
        _item_enumeration.detail     'K-L~3~'
                                     'K\a~1~ in older Siegbahn notation'
                                     'K-L~2~'
                                     'K\a~2~ in older Siegbahn notation'
                                     'K-M~3~'
                                     'K\b~1~ in older Siegbahn notation'
                                     'K-L~2,3~'
                                     'use where K-L~3~ and K-L~2~ are not resolved'
         save_
    
    save__diffrn_radiation.wavelength_id
        _item_description.description
    ;              This data item is a pointer to 
                   '_diffrn_radiation_wavelength.id' in the
                   DIFFRN_RADIATION_WAVELENGTH category.
    ;
        _item.name                  '_diffrn_radiation.wavelength_id'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    
    ################
    # DIFFRN_REFLN #
    ################
    
    
    save_DIFFRN_REFLN
        _category.description 
    ;
         This category redefinition has been added to extend the key of 
         the standard DIFFRN_REFLN category.
    ;
        _category.id                   diffrn_refln
        _category.mandatory_code       no
        _category_key.name             '_diffrn_refln.frame_id'
         loop_
        _category_group.id             'inclusive_group'
                                       'diffrn_group'
         save_
    
    
    save__diffrn_refln.frame_id
        _item_description.description
    ;             
                   This item is a pointer to '_diffrn_data_frame.id'
                   in the DIFFRN_DATA_FRAME category. 
    ;
        _item.name                  '_diffrn_refln.frame_id'
        _item.category_id             diffrn_refln
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    ###############
    # DIFFRN_SCAN #
    ###############
    
    save_DIFFRN_SCAN
        _category.description 
    ;
         Data items in the DIFFRN_SCAN category describe the parameters of one
         or more scans, relating axis positions to frames.
    
    ;
        _category.id                   diffrn_scan
        _category.mandatory_code       no
        _category_key.name            '_diffrn_scan.id'
         loop_
        _category_group.id            'inclusive_group'
                                      'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 - derived from a suggestion by R. M. Sweet.
    
       The vector of each axis is not given here, because it is provided in
       the AXIS category.  By making '_diffrn_scan_axis.scan_id' and
       '_diffrn_scan_axis.axis_id' keys of the DIFFRN_SCAN_AXIS category,
       an arbitrary number of scanning and fixed axes can be specified for a 
       scan.  We have specified three rotation axes and one translation axis 
       at non-zero values, with one axis stepping.  There is no reason why 
       more axes could not have been specified to step.   We have specified
       range information, but note that it is redundant from the  number of 
       frames and the increment, so we could drop the data item
       '_diffrn_scan_axis.angle_range'.
       
       We have specified both the sweep data and the data for a single frame.
    
       Note that the information on how the axes are stepped is given twice,
       once in terms of the overall averages in the value of
       '_diffrn_scan.integration_time' and the values for DIFFRN_SCAN_AXIS,
       and precisely for the given frame in the value for 
       '_diffrn_scan_frame.integration_time' and the values for
       DIFFRN_SCAN_FRAME_AXIS.  If dose-related adjustements are made to
       scan times and non-linear stepping is done, these values may differ.
       Therefore, in interpreting the data for a particular frame it is
       important to use the frame-specific data.
    
    ;
    ;
          _diffrn_scan.id                   1
          _diffrn_scan.date_start         '2001-11-18T03:26:42'
          _diffrn_scan.date_end           '2001-11-18T03:36:45'
          _diffrn_scan.integration_time    3.0
          _diffrn_scan.frame_id_start      mad_L2_000
          _diffrn_scan.frame_id_end        mad_L2_200
          _diffrn_scan.frames              201
    
           loop_
          _diffrn_scan_axis.scan_id
          _diffrn_scan_axis.axis_id
          _diffrn_scan_axis.angle_start
          _diffrn_scan_axis.angle_range
          _diffrn_scan_axis.angle_increment
          _diffrn_scan_axis.displacement_start
          _diffrn_scan_axis.displacement_range
          _diffrn_scan_axis.displacement_increment
    
           1 omega 200.0 20.0 0.1 . . . 
           1 kappa -40.0  0.0 0.0 . . . 
           1 phi   127.5  0.0 0.0 . . . 
           1 tranz  . . .   2.3 0.0 0.0 
    
          _diffrn_scan_frame.scan_id                   1
          _diffrn_scan_frame.date               '2001-11-18T03:27:33'
          _diffrn_scan_frame.integration_time    3.0
          _diffrn_scan_frame.frame_id            mad_L2_018
          _diffrn_scan_frame.frame_number        18
    
          loop_
          _diffrn_scan_frame_axis.frame_id
          _diffrn_scan_frame_axis.axis_id
          _diffrn_scan_frame_axis.angle
          _diffrn_scan_frame_axis.angle_increment
          _diffrn_scan_frame_axis.displacement
          _diffrn_scan_frame_axis.displacement_increment
    
           mad_L2_018 omega 201.8  0.1 . .
           mad_L2_018 kappa -40.0  0.0 . .
           mad_L2_018 phi   127.5  0.0 . .
           mad_L2_018 tranz  .     .  2.3 0.0
    
    ;
    
    ;
        Example 2 - a more extensive example, R. M. Sweet, P. Ellis, H. Bernstein.
        
       We place a detector 240 mm along the Z axis from the goniometer.
       This presents us with a choice -- either we define the axes of
       the detector at the origin, and then put a Z setting of -240 in
       for the actual use, or we define the axes with the necessary Z-offset.
       In this case we use the setting, and leave the offset as zero.
       We call this axis DETECTOR_Z.
       
       The axis for positioning the detector in the Y-direction depends
       on the detector Z-axis.  We call this axis, DETECTOR_Y.
       
       The axis for positioning the detector in the X-direction depends
       on the detector Y-axis (and therefore on the detector Z-axis).
       We call this axis DETECTOR_X.
       
       This detector may be rotated around the Y-axis.  This rotation axis
       depends on the three translation axes.  We call it DETECTOR_PITCH.
       
       We define a coordinate system on the face of the detector in terms of
       2300 0.150 mm pixels in each direction.  The ELEMENT_X axis is used to
       index the first array index of the data array and the ELEMENT_Y
       axis is used to index the second array index.  Because the pixels
       are 0.150mm x 0.150mm, the centre of the first pixel is at (0.075, 
       0.075) in this coordinate system.
    
    ;
    ;
         ###CBF: VERSION 1.1 
    
         data_image_1 
    
    
         # category DIFFRN 
    
         _diffrn.id P6MB 
         _diffrn.crystal_id P6MB_CRYSTAL7 
    
    
         # category DIFFRN_SOURCE 
    
         loop_ 
         _diffrn_source.diffrn_id 
         _diffrn_source.source 
         _diffrn_source.type 
          P6MB synchrotron 'SSRL beamline 9-1' 
    
    
         # category DIFFRN_RADIATION 
    
              loop_ 
         _diffrn_radiation.diffrn_id 
         _diffrn_radiation.wavelength_id 
         _diffrn_radiation.monochromator 
         _diffrn_radiation.polarizn_source_ratio 
         _diffrn_radiation.polarizn_source_norm 
         _diffrn_radiation.div_x_source 
         _diffrn_radiation.div_y_source 
         _diffrn_radiation.div_x_y_source 
          P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08
         0.01 0.00 
    
    
         # category DIFFRN_RADIATION_WAVELENGTH 
    
         loop_ 
         _diffrn_radiation_wavelength.id 
         _diffrn_radiation_wavelength.wavelength 
         _diffrn_radiation_wavelength.wt 
          WAVELENGTH1 0.98 1.0 
    
    
         # category DIFFRN_DETECTOR 
    
         loop_ 
         _diffrn_detector.diffrn_id 
         _diffrn_detector.id 
         _diffrn_detector.type 
         _diffrn_detector.number_of_axes 
          P6MB MAR345-SN26 'MAR 345' 4 
    
    
         # category DIFFRN_DETECTOR_AXIS 
    
         loop_ 
         _diffrn_detector_axis.detector_id 
         _diffrn_detector_axis.axis_id 
          MAR345-SN26 DETECTOR_X 
          MAR345-SN26 DETECTOR_Y 
          MAR345-SN26 DETECTOR_Z 
          MAR345-SN26 DETECTOR_PITCH 
    
    
         # category DIFFRN_DETECTOR_ELEMENT 
    
         loop_ 
         _diffrn_detector_element.id 
         _diffrn_detector_element.detector_id 
          ELEMENT1 MAR345-SN26 
    
    
         # category DIFFRN_DATA_FRAME 
    
         loop_ 
         _diffrn_data_frame.id 
         _diffrn_data_frame.detector_element_id 
         _diffrn_data_frame.array_id 
         _diffrn_data_frame.binary_id 
          FRAME1 ELEMENT1 ARRAY1 1 
    
    
         # category DIFFRN_MEASUREMENT 
    
         loop_ 
         _diffrn_measurement.diffrn_id 
         _diffrn_measurement.id 
         _diffrn_measurement.number_of_axes 
         _diffrn_measurement.method 
          P6MB GONIOMETER 3 rotation 
    
    
         # category DIFFRN_MEASUREMENT_AXIS 
    
         loop_ 
         _diffrn_measurement_axis.measurement_id 
         _diffrn_measurement_axis.axis_id 
          GONIOMETER GONIOMETER_PHI 
          GONIOMETER GONIOMETER_KAPPA 
          GONIOMETER GONIOMETER_OMEGA 
    
    
         # category DIFFRN_SCAN 
    
         loop_ 
         _diffrn_scan.id 
         _diffrn_scan.frame_id_start 
         _diffrn_scan.frame_id_end 
         _diffrn_scan.frames 
          SCAN1 FRAME1 FRAME1 1 
    
    
         # category DIFFRN_SCAN_AXIS 
    
         loop_ 
         _diffrn_scan_axis.scan_id 
         _diffrn_scan_axis.axis_id 
         _diffrn_scan_axis.angle_start 
         _diffrn_scan_axis.angle_range 
         _diffrn_scan_axis.angle_increment 
         _diffrn_scan_axis.displacement_start 
         _diffrn_scan_axis.displacement_range 
         _diffrn_scan_axis.displacement_increment 
          SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 
          SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 
          SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 
          SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 
          SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 
          SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 
          SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 
    
    
         # category DIFFRN_SCAN_FRAME 
    
         loop_ 
         _diffrn_scan_frame.frame_id 
         _diffrn_scan_frame.frame_number 
         _diffrn_scan_frame.integration_time 
         _diffrn_scan_frame.scan_id 
         _diffrn_scan_frame.date 
          FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 
    
    
         # category DIFFRN_SCAN_FRAME_AXIS 
    
         loop_ 
         _diffrn_scan_frame_axis.frame_id 
         _diffrn_scan_frame_axis.axis_id 
         _diffrn_scan_frame_axis.angle 
         _diffrn_scan_frame_axis.displacement 
          FRAME1 GONIOMETER_OMEGA 12.0 0.0 
          FRAME1 GONIOMETER_KAPPA 23.3 0.0 
          FRAME1 GONIOMETER_PHI -165.8 0.0 
          FRAME1 DETECTOR_Z 0.0 -240.0 
          FRAME1 DETECTOR_Y 0.0 0.6 
          FRAME1 DETECTOR_X 0.0 -0.5 
          FRAME1 DETECTOR_PITCH 0.0 0.0 
    
    
         # category AXIS 
    
         loop_ 
         _axis.id 
         _axis.type 
         _axis.equipment 
         _axis.depends_on 
         _axis.vector[1] _axis.vector[2] _axis.vector[3] 
         _axis.offset[1] _axis.offset[2] _axis.offset[3] 
          GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . 
          GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279
          0 0.76604 . . . 
          GONIOMETER_PHI   rotation goniometer GONIOMETER_KAPPA 1 0 0
         . . . 
          SOURCE           general source . 0 0 1 . . . 
          GRAVITY          general gravity . 0 -1 0 . . . 
          DETECTOR_Z       translation detector . 0 0 1 0 0 0
          DETECTOR_Y       translation detector DETECTOR_Z 0 1 0 0 0 0 
          DETECTOR_X       translation detector DETECTOR_Y 1 0 0 0 0 0 
          DETECTOR_PITCH   rotation    detector DETECTOR_X 0 1 0 0 0 0 
          ELEMENT_X        translation detector DETECTOR_PITCH
         1 0 0 172.43 -172.43 0
          ELEMENT_Y        translation detector ELEMENT_X
         0 1 0 0 0 0 
    
         # category ARRAY_STRUCTURE_LIST 
    
         loop_ 
         _array_structure_list.array_id 
         _array_structure_list.index 
         _array_structure_list.dimension 
         _array_structure_list.precedence 
         _array_structure_list.direction 
         _array_structure_list.axis_set_id 
          ARRAY1 1 2300 1 increasing ELEMENT_X 
          ARRAY1 2 2300 2 increasing ELEMENT_Y 
    
    
         # category ARRAY_STRUCTURE_LIST_AXIS 
    
         loop_
         _array_structure_list_axis.axis_set_id
         _array_structure_list_axis.axis_id
         _array_structure_list_axis.displacement
         _array_structure_list_axis.displacement_increment
          ELEMENT_X ELEMENT_X 0.075 0.150
          ELEMENT_Y ELEMENT_Y 0.075 0.150
    
         # category ARRAY_ELEMENT_SIZE 
    
         loop_ 
         _array_element_size.array_id 
         _array_element_size.index 
         _array_element_size.size 
          ARRAY1 1 150e-6 
          ARRAY1 2 150e-6 
    
    
         # category ARRAY_INTENSITIES 
    
         loop_ 
         _array_intensities.array_id 
         _array_intensities.binary_id 
         _array_intensities.linearity 
         _array_intensities.gain 
         _array_intensities.gain_esd 
         _array_intensities.overload
         _array_intensities.undefined_value 
          ARRAY1 1 linear 1.15 0.2 240000 0 
    
    
          # category ARRAY_STRUCTURE 
    
          loop_ 
          _array_structure.id 
          _array_structure.encoding_type 
          _array_structure.compression_type 
          _array_structure.byte_order 
          ARRAY1 "signed 32-bit integer" packed little_endian 
    
    
         # category ARRAY_DATA         
    
         loop_ 
         _array_data.array_id 
         _array_data.binary_id 
         _array_data.data 
          ARRAY1 1 
         ; 
         --CIF-BINARY-FORMAT-SECTION-- 
         Content-Type: application/octet-stream; 
             conversions="x-CBF_PACKED" 
         Content-Transfer-Encoding: BASE64 
         X-Binary-Size: 3801324 
         X-Binary-ID: 1 
         X-Binary-Element-Type: "signed 32-bit integer" 
         Content-MD5: 07lZFvF+aOcW85IN7usl8A== 
    
         AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg 
         ... 
         8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE 
    
         --CIF-BINARY-FORMAT-SECTION---- 
         ; 
    ;
    
    ;
        Example 3 - Example 2 revised for a spiral scan, R. M. Sweet, 
        P. Ellis, H. Bernstein.
        
       We place a detector 240 mm along the Z axis from the goniometer,
       as in Example 2, above, but in this example, the image plate is
       scanned in a spiral pattern outside edge in.
       
       The axis for positioning the detector in the Y-direction depends
       on the detector Z-axis.  We call this axis, DETECTOR_Y.
       
       The axis for positioning the detector in the X-direction depends
       on the detector Y-axis (and therefore on the detector Z-axis).
       We call this axis DETECTOR_X.
       
       This detector may be rotated around the Y-axis.  This rotation axis
       depends on the three translation axes.  We call it DETECTOR_PITCH.
    
       We define a coordinate system on the face of the detector in
       terms of a coupled rotation axis and radial scan axis to form 
       a spiral scan.  Let us call rotation axis ELEMENT_ROT, and the
       radial axis ELEMENT_RAD.   We assume 150 um radial pitch and 75 um 
       'constant velocity' angular pitch. 
    
       We index first on the rotation axis and make the radial axis
       dependent on 
       it. 
    
       The two axes are coupled to form an axis set ELEMENT_SPIRAL. 
    
    ;
    ;
         ###CBF: VERSION 1.1 
    
         data_image_1 
    
    
         # category DIFFRN 
    
         _diffrn.id P6MB 
         _diffrn.crystal_id P6MB_CRYSTAL7 
    
    
         # category DIFFRN_SOURCE 
    
         loop_ 
         _diffrn_source.diffrn_id 
         _diffrn_source.source 
         _diffrn_source.type 
          P6MB synchrotron 'SSRL beamline 9-1' 
    
    
         # category DIFFRN_RADIATION 
    
              loop_ 
         _diffrn_radiation.diffrn_id 
         _diffrn_radiation.wavelength_id 
         _diffrn_radiation.monochromator 
         _diffrn_radiation.polarizn_source_ratio 
         _diffrn_radiation.polarizn_source_norm 
         _diffrn_radiation.div_x_source 
         _diffrn_radiation.div_y_source 
         _diffrn_radiation.div_x_y_source 
          P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08
         0.01 0.00 
    
    
         # category DIFFRN_RADIATION_WAVELENGTH 
    
         loop_ 
         _diffrn_radiation_wavelength.id 
         _diffrn_radiation_wavelength.wavelength 
         _diffrn_radiation_wavelength.wt 
          WAVELENGTH1 0.98 1.0 
    
    
         # category DIFFRN_DETECTOR 
    
         loop_ 
         _diffrn_detector.diffrn_id 
         _diffrn_detector.id 
         _diffrn_detector.type 
         _diffrn_detector.number_of_axes 
          P6MB MAR345-SN26 'MAR 345' 4 
    
    
         # category DIFFRN_DETECTOR_AXIS 
    
         loop_ 
         _diffrn_detector_axis.detector_id 
         _diffrn_detector_axis.axis_id 
          MAR345-SN26 DETECTOR_X 
          MAR345-SN26 DETECTOR_Y 
          MAR345-SN26 DETECTOR_Z 
          MAR345-SN26 DETECTOR_PITCH 
    
    
         # category DIFFRN_DETECTOR_ELEMENT 
    
         loop_ 
         _diffrn_detector_element.id 
         _diffrn_detector_element.detector_id 
          ELEMENT1 MAR345-SN26 
    
    
         # category DIFFRN_DATA_FRAME 
    
         loop_ 
         _diffrn_data_frame.id 
         _diffrn_data_frame.detector_element_id 
         _diffrn_data_frame.array_id 
         _diffrn_data_frame.binary_id 
          FRAME1 ELEMENT1 ARRAY1 1 
    
    
         # category DIFFRN_MEASUREMENT 
    
         loop_ 
         _diffrn_measurement.diffrn_id 
         _diffrn_measurement.id 
         _diffrn_measurement.number_of_axes 
         _diffrn_measurement.method 
          P6MB GONIOMETER 3 rotation 
    
    
         # category DIFFRN_MEASUREMENT_AXIS 
    
         loop_ 
         _diffrn_measurement_axis.measurement_id 
         _diffrn_measurement_axis.axis_id 
          GONIOMETER GONIOMETER_PHI 
          GONIOMETER GONIOMETER_KAPPA 
          GONIOMETER GONIOMETER_OMEGA 
    
    
         # category DIFFRN_SCAN 
    
         loop_ 
         _diffrn_scan.id 
         _diffrn_scan.frame_id_start 
         _diffrn_scan.frame_id_end 
         _diffrn_scan.frames 
          SCAN1 FRAME1 FRAME1 1 
    
    
         # category DIFFRN_SCAN_AXIS 
    
         loop_ 
         _diffrn_scan_axis.scan_id 
         _diffrn_scan_axis.axis_id 
         _diffrn_scan_axis.angle_start 
         _diffrn_scan_axis.angle_range 
         _diffrn_scan_axis.angle_increment 
         _diffrn_scan_axis.displacement_start 
         _diffrn_scan_axis.displacement_range 
         _diffrn_scan_axis.displacement_increment 
          SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 
          SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 
          SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 
          SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 
          SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 
          SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 
          SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 
    
    
         # category DIFFRN_SCAN_FRAME 
    
         loop_ 
         _diffrn_scan_frame.frame_id 
         _diffrn_scan_frame.frame_number 
         _diffrn_scan_frame.integration_time 
         _diffrn_scan_frame.scan_id 
         _diffrn_scan_frame.date 
          FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 
    
    
         # category DIFFRN_SCAN_FRAME_AXIS 
    
         loop_ 
         _diffrn_scan_frame_axis.frame_id 
         _diffrn_scan_frame_axis.axis_id 
         _diffrn_scan_frame_axis.angle 
         _diffrn_scan_frame_axis.displacement 
          FRAME1 GONIOMETER_OMEGA 12.0 0.0 
          FRAME1 GONIOMETER_KAPPA 23.3 0.0 
          FRAME1 GONIOMETER_PHI -165.8 0.0 
          FRAME1 DETECTOR_Z 0.0 -240.0 
          FRAME1 DETECTOR_Y 0.0 0.6 
          FRAME1 DETECTOR_X 0.0 -0.5 
          FRAME1 DETECTOR_PITCH 0.0 0.0 
    
    
         # category AXIS 
    
         loop_ 
         _axis.id 
         _axis.type 
         _axis.equipment 
         _axis.depends_on 
         _axis.vector[1] _axis.vector[2] _axis.vector[3] 
         _axis.offset[1] _axis.offset[2] _axis.offset[3] 
          GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . 
          GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279
          0 0.76604 . . . 
          GONIOMETER_PHI   rotation goniometer GONIOMETER_KAPPA 1 0 0
         . . . 
          SOURCE           general source . 0 0 1 . . . 
          GRAVITY          general gravity . 0 -1 0 . . . 
          DETECTOR_Z       translation detector . 0 0 1 0 0 0
          DETECTOR_Y       translation detector DETECTOR_Z 0 1 0 0 0 0 
          DETECTOR_X       translation detector DETECTOR_Y 1 0 0 0 0 0 
          DETECTOR_PITCH   rotation    detector DETECTOR_X 0 1 0 0 0 0 
          ELEMENT_ROT      translation detector DETECTOR_PITCH 0 0 1 0 0 0
          ELEMENT_RAD      translation detector ELEMENT_ROT 0 1 0 0 0 0 
    
         # category ARRAY_STRUCTURE_LIST 
    
         loop_ 
         _array_structure_list.array_id 
         _array_structure_list.index 
         _array_structure_list.dimension 
         _array_structure_list.precedence 
         _array_structure_list.direction 
         _array_structure_list.axis_set_id 
          ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL
    
    
         # category ARRAY_STRUCTURE_LIST_AXIS 
    
         loop_
         _array_structure_list_axis.axis_set_id
         _array_structure_list_axis.axis_id
         _array_structure_list_axis.angle
         _array_structure_list_axis.displacement
         _array_structure_list_axis.angular_pitch
         _array_structure_list_axis.radial_pitch
          ELEMENT_SPIRAL ELEMENT_ROT 0    .  0.075   .
          ELEMENT_SPIRAL ELEMENT_RAD . 172.5  .    -0.150
    
         # category ARRAY_ELEMENT_SIZE 
         # the actual pixels are 0.075 by 0.150 mm
         # We give the coarser dimension here.
    
         loop_ 
         _array_element_size.array_id 
         _array_element_size.index 
         _array_element_size.size 
          ARRAY1 1 150e-6 
    
    
         # category ARRAY_INTENSITIES 
    
         loop_ 
         _array_intensities.array_id 
         _array_intensities.binary_id 
         _array_intensities.linearity 
         _array_intensities.gain 
         _array_intensities.gain_esd 
         _array_intensities.overload
         _array_intensities.undefined_value 
          ARRAY1 1 linear 1.15 0.2 240000 0 
    
    
          # category ARRAY_STRUCTURE 
    
          loop_ 
          _array_structure.id 
          _array_structure.encoding_type 
          _array_structure.compression_type 
          _array_structure.byte_order 
          ARRAY1 "signed 32-bit integer" packed little_endian 
    
    
         # category ARRAY_DATA         
    
         loop_ 
         _array_data.array_id 
         _array_data.binary_id 
         _array_data.data 
          ARRAY1 1 
         ; 
         --CIF-BINARY-FORMAT-SECTION-- 
         Content-Type: application/octet-stream; 
             conversions="x-CBF_PACKED" 
         Content-Transfer-Encoding: BASE64 
         X-Binary-Size: 3801324 
         X-Binary-ID: 1 
         X-Binary-Element-Type: "signed 32-bit integer" 
         Content-MD5: 07lZFvF+aOcW85IN7usl8A== 
    
         AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg 
         ... 
         8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE 
    
         --CIF-BINARY-FORMAT-SECTION---- 
         ; 
    ;
    
    
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
           save_
    
    
    save__diffrn_scan.id
        _item_description.description
    ;             The value of '_diffrn_scan.id' uniquely identifies each
                  scan.  The identifier is used to tie together all the 
                  information about the scan.
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
           '_diffrn_scan.id'                 diffrn_scan             yes
           '_diffrn_scan_axis.scan_id'       diffrn_scan_axis        yes
           '_diffrn_scan_frame.scan_id'      diffrn_scan_frame       yes
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
           '_diffrn_scan_axis.scan_id'          '_diffrn_scan.id'
           '_diffrn_scan_frame.scan_id'         '_diffrn_scan.id'
         save_
    
    
    save__diffrn_scan.date_end
        _item_description.description
    ;
                   The date and time of the end of the scan.  Note that this
                   may be an estimate generated during the scan, before the
                   precise time of the end of the scan is known.
    ;
        _item.name                 '_diffrn_scan.date_end'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no
        _item_type.code            yyyy-mm-dd
         save_
    
    
    save__diffrn_scan.date_start
        _item_description.description
    ;
                   The date and time of the start of the scan.
    ;
        _item.name                 '_diffrn_scan.date_start'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no
        _item_type.code            yyyy-mm-dd
         save_
    
    
    save__diffrn_scan.integration_time
        _item_description.description
    ;
                   Approximate average time in seconds to integrate each 
                   step of the scan.  The precise time for integration
                   of each particular step must be provided in
                   '_diffrn_scan_frame.integration_time', even
                   if all steps have the same integration time.
    ;
        _item.name                 '_diffrn_scan.integration_time'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no
        _item_type.code            float
        _item_units.code           'seconds'
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0.0
         save_
    
    
    save__diffrn_scan.frame_id_start
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   first frame in the scan.
    
                   This item is a pointer to '_diffrn_data_frame.id' in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name                 '_diffrn_scan.frame_id_start'
        _item.category_id          diffrn_scan
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan.frame_id_end
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   last frame in the scan.
    
                   This item is a pointer to '_diffrn_data_frame.id' in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name                 '_diffrn_scan.frame_id_end'
        _item.category_id          diffrn_scan
        _item.mandatory_code       yes 
        _item_type.code            code
         save_
    
    
    save__diffrn_scan.frames
        _item_description.description
    ;
                   The value of this data item is the number of frames in
                   the scan.
    
    ;
        _item.name                 '_diffrn_scan.frames'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no 
        _item_type.code            int
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   1
                                1   1
         save_
    
    
    ####################
    # DIFFRN_SCAN_AXIS #
    ####################
    
    save_DIFFRN_SCAN_AXIS
        _category.description 
    ;
         Data items in the DIFFRN_SCAN_AXIS category describe the settings of
         axes for particular scans.  Unspecified axes are assumed to be at
         their zero points.
    
    ;
        _category.id                   diffrn_scan_axis
        _category.mandatory_code       no
         loop_
        _category_key.name            
                                      '_diffrn_scan_axis.scan_id'
                                      '_diffrn_scan_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_scan_axis.scan_id
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   scan for which axis settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   '_diffrn_scan.id'.
    
                   This item is a pointer to '_diffrn_scan.id' in the
                   DIFFRN_SCAN category.
    ;
        _item.name                 '_diffrn_scan_axis.scan_id'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_axis.axis_id
        _item_description.description
    ;
                   The value of this data item is the identifier of one of
                   the axes for the scan for which settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   '_diffrn_scan.id'.
    
                   This item is a pointer to '_axis.id' in the
                   AXIS category.
    ;
        _item.name                 '_diffrn_scan_axis.axis_id'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_axis.angle_start
        _item_description.description
    ;
                   The starting position for the specified axis in degrees.
    ;
        _item.name                 '_diffrn_scan_axis.angle_start'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.angle_range
        _item_description.description
    ;
                   The range from the starting position for the specified axis 
                   in degrees.
    ;
        _item.name                 '_diffrn_scan_axis.angle_range'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.angle_increment
        _item_description.description
    ;
                   The increment for each step for the specified axis
                   in degrees.  In general, this will agree with
                   '_diffrn_scan_frame_axis.angle_increment'. The 
                   sum of the values of '_diffrn_scan_frame_axis.angle' and
                   '_diffrn_scan_frame_axis.angle_increment' is the
                   angular setting of the axis at the end of the integration
                   time for a given frame.  If the individual frame values
                   vary, then the value of 
                   '_diffrn_scan_axis.angle_increment' will be 
                   representative
                   of the ensemble of values of
                   '_diffrn_scan_frame_axis.angle_increment' (e.g.
                   the mean).
    
    ;
        _item.name                 '_diffrn_scan_axis.angle_increment'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.angle_rstrt_incr
        _item_description.description
    ;
                   The increment after each step for the specified axis
                   in degrees.  In general, this will agree with
                   '_diffrn_scan_frame_axis.angle_rstrt_incr'.  The
                   sum of the values of '_diffrn_scan_frame_axis.angle' 
                   and  '_diffrn_scan_frame_axis.angle_increment' 
                   and  '_diffrn_scan_frame_axis.angle_rstrt_incr' is the
                   angular setting of the axis at the start of the integration
                   time for the next frame relative to a given frame, and 
                   should equal '_diffrn_scan_frame_axis.angle' for that 
                   next frame.   If the individual frame values
                   vary, then the value of 
                   '_diffrn_scan_axis.angle_rstrt_incr' will be 
                   representative
                   of the ensemble of values of
                   '_diffrn_scan_frame_axis.angle_rstrt_incr' (e.g.
                   the mean).
    ;
        _item.name                 '_diffrn_scan_axis.angle_rstrt_incr'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.displacement_start
        _item_description.description
    ;
                   The starting position for the specified axis in millimetres.
    ;
        _item.name                 '_diffrn_scan_axis.displacement_start'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_axis.displacement_range
        _item_description.description
    ;
                   The range from the starting position for the specified axis 
                   in millimetres.
    ;
        _item.name                 '_diffrn_scan_axis.displacement_range'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_axis.displacement_increment
        _item_description.description
    ;
                   The increment for each step for the specified axis
                   in millimetres.  In general, this will agree with
                   '_diffrn_scan_frame_axis.displacement_increment'.
                   The sum of the values of 
                   '_diffrn_scan_frame_axis.displacement' and
                   '_diffrn_scan_frame_axis.displacement_increment' is the
                   angular setting of the axis at the end of the integration
                   time for a given frame.  If the individual frame values
                   vary, then the value of 
                   '_diffrn_scan_axis.displacement_increment' will be 
                   representative
                   of the ensemble of values of
                   '_diffrn_scan_frame_axis.displacement_increment' (e.g.
                   the mean).
    ;
        _item.name                 '_diffrn_scan_axis.displacement_increment'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_axis.displacement_rstrt_incr
        _item_description.description
    ;
                   The increment for each step for the specified axis
                   in millimetres.  In general, this will agree with
                   '_diffrn_scan_frame_axis.displacement_rstrt_incr'.
                   The sum of the values of 
                   '_diffrn_scan_frame_axis.displacement' and
                   '_diffrn_scan_frame_axis.displacement_increment' and
                   '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the
                   angular setting of the axis at the start of the integration
                   time for the next frame relative to a given frame, and 
                   should equal '_diffrn_scan_frame_axis.displacement' 
                   for that next frame.  If the individual frame values
                   vary, then the value of 
                   '_diffrn_scan_axis.displacement_rstrt_incr' will be 
                   representative
                   of the ensemble of values of
                   '_diffrn_scan_frame_axis.displacement_rstrt_incr' (e.g.
                   the mean).
    ;
        _item.name                 '_diffrn_scan_axis.displacement_rstrt_incr'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    #####################
    # DIFFRN_SCAN_FRAME #
    #####################
    
    save_DIFFRN_SCAN_FRAME
        _category.description 
    ;
                Data items in the DIFFRN_SCAN_FRAME category describe
                the relationship of particular frames to scans.
    
    ;
        _category.id                   diffrn_scan_frame
        _category.mandatory_code       no
         loop_
        _category_key.name     
                                      '_diffrn_scan_frame.scan_id'
                                      '_diffrn_scan_frame.frame_id'
         loop_
        _category_group.id            'inclusive_group'
                                      'diffrn_group'
         save_
    
    
    save__diffrn_scan_frame.date
        _item_description.description
    ;
                   The date and time of the start of the frame being scanned.
    ;
        _item.name                 '_diffrn_scan_frame.date'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       no
        _item_type.code            yyyy-mm-dd
         save_
    
    
    save__diffrn_scan_frame.frame_id
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   frame being examined.
    
                   This item is a pointer to '_diffrn_data_frame.id' in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name                 '_diffrn_scan_frame.frame_id'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_frame.frame_number
        _item_description.description
    ;
                   The value of this data item is the number of the frame
                   within the scan, starting with 1.  It is not necessarily
                   the same as the value of '_diffrn_scan_frame.frame_id',
                   but may be.
    
    ;
        _item.name                 '_diffrn_scan_frame.frame_number'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       no 
        _item_type.code            int
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0
                                0   0
         save_
    
    
    save__diffrn_scan_frame.integration_time
        _item_description.description
    ;
                   The time in seconds to integrate this step of the scan.
                   This should be the precise time of integration of each
                   particular frame.  The value of this data item should
                   be given explicitly for each frame and not inferred
                   from the value of '_diffrn_scan.integration_time'.
    ;
        _item.name                 '_diffrn_scan_frame.integration_time'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       yes 
        _item_type.code            float
        _item_units.code           'seconds'
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0.0
         save_
    
    
    save__diffrn_scan_frame.scan_id
        _item_description.description
    ;             The value of '_diffrn_scan_frame.scan_id' identifies the scan
                  containing this frame.
    
                  This item is a pointer to '_diffrn_scan.id' in the
                  DIFFRN_SCAN category.
    ;
        _item.name             '_diffrn_scan_frame.scan_id'    
        _item.category_id        diffrn_scan_frame        
        _item.mandatory_code     yes     
        _item_type.code          code
         save_
    
    
    ##########################
    # DIFFRN_SCAN_FRAME_AXIS #
    ##########################
    
    save_DIFFRN_SCAN_FRAME_AXIS
        _category.description
    ;
         Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the
         settings of axes for particular frames.  Unspecified axes are
         assumed to be at their zero points.  If, for any given frame,
         non-zero values apply for any of the data items in this category,
         those values should be given explicitly in this category and not
         simply inferred from values in DIFFRN_SCAN_AXIS.
    
    ;
        _category.id                   diffrn_scan_frame_axis
        _category.mandatory_code       no
         loop_
        _category_key.name
                                      '_diffrn_scan_frame_axis.frame_id'
                                      '_diffrn_scan_frame_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_scan_frame_axis.axis_id
        _item_description.description
    ;
                   The value of this data item is the identifier of one of
                   the axes for the frame for which settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   '_diffrn_scan_frame.frame_id'.
    
                   This item is a pointer to '_axis.id' in the
                   AXIS category.
    ;
        _item.name                 '_diffrn_scan_frame_axis.axis_id'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_frame_axis.angle
        _item_description.description
    ;
                   The setting of the specified axis in degrees for this frame.
                   This is the setting at the start of the integration time.
    ;
        _item.name                 '_diffrn_scan_frame_axis.angle'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_frame_axis.angle_increment
        _item_description.description
    ;
                   The increment for this frame for angular setting of
                   the specified axis in degrees.  The sum of the values
                   of '_diffrn_scan_frame_axis.angle' and
                   '_diffrn_scan_frame_axis.angle_increment' is the
                   angular setting of the axis at the end of the integration
                   time for this frame.
    ;
        _item.name                 '_diffrn_scan_frame_axis.angle_increment'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_frame_axis.angle_rstrt_incr
        _item_description.description
    ;
                   The increment after this frame for angular setting of
                   the specified axis in degrees.  The sum of the values
                   of '_diffrn_scan_frame_axis.angle' and
                   '_diffrn_scan_frame_axis.angle_increment' and
                   '_diffrn_scan_frame_axis.angle_rstrt_incr' is the
                   angular setting of the axis at the start of the integration
                   time for the next frame, and should equal
                   '_diffrn_scan_frame_axis.angle' for that next frame.
    ;
        _item.name               '_diffrn_scan_frame_axis.angle_rstrt_incr'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_frame_axis.displacement
        _item_description.description
    ;
                   The setting of the specified axis in millimetres for this
                   frame.  This is the setting at the start of the integration
                   time.
    
    ;
        _item.name               '_diffrn_scan_frame_axis.displacement'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_frame_axis.displacement_increment
        _item_description.description
    ;
                   The increment for this frame for displacement setting of
                   the specified axis in millimetres.  The sum of the values
                   of '_diffrn_scan_frame_axis.displacement' and
                   '_diffrn_scan_frame_axis.displacement_increment' is the
                   angular setting of the axis at the end of the integration
                   time for this frame.
    ;
        _item.name               '_diffrn_scan_frame_axis.displacement_increment'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_frame_axis.displacement_rstrt_incr
        _item_description.description
    ;
                   The increment for this frame for displacement setting of
                   the specified axis in millimetres.  The sum of the values
                   of '_diffrn_scan_frame_axis.displacement' and
                   '_diffrn_scan_frame_axis.displacement_increment' and
                   '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the
                   angular setting of the axis at the start of the integration
                   time for the next frame, and should equal
                   '_diffrn_scan_frame_axis.displacement' for that next frame.
    ;
        _item.name               '_diffrn_scan_frame_axis.displacement_rstrt_incr'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    save__diffrn_scan_frame_axis.frame_id
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   frame for which axis settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   '_diffrn_scan_frame.frame_id'.
    
                   This item is a pointer to '_diffrn_data_frame.id' in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name               '_diffrn_scan_frame_axis.frame_id'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    ########################   DEPRECATED DATA ITEMS ########################
    
    save__diffrn_detector_axis.id
        _item_description.description
    ;
                   This data item is a pointer to '_diffrn_detector.id' in
                   the DIFFRN_DETECTOR category.
                  
                   DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_detector_axis.id'
        _item.category_id             diffrn_detector_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    save__diffrn_measurement_axis.id
        _item_description.description
    ;
                   This data item is a pointer to '_diffrn_measurement.id' in
                   the DIFFRN_MEASUREMENT category.
                  
                   DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_measurement_axis.id'
        _item.category_id             diffrn_measurement_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    #########################   DEPRECATED CATEGORY #########################
    #####################
    # DIFFRN_FRAME_DATA #
    #####################
    
    
    save_DIFFRN_FRAME_DATA
        _category.description
    ;
                  Data items in the DIFFRN_FRAME_DATA category record
                  the details about each frame of data. 
    
                  The items in this category are now in the
                  DIFFRN_DATA_FRAME category.
                  
                  The items in the DIFFRN_FRAME_DATA category
                  are now deprecated.  The items from this category 
                  are provided as aliases in the 1.0.0 dictionary, 
                  but should not be used for new work.
                  The items from the old category are provided
                  in this dictionary for completeness,
                  but should not be used or cited.  To avoid
                  confusion, the example has been removed,
                  and the redundant parent child-links to other
                  categories removed.
                  
    ;
        _category.id                   diffrn_frame_data
        _category.mandatory_code       no
         loop_
        _category_key.name             '_diffrn_frame_data.id'
                                       '_diffrn_frame_data.detector_element_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        THE DIFFRN_FRAME_DATA category is deprecated and should not be used.
    ;
    ;
           # EXAMPLE REMOVED #
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
    
    
    save__diffrn_frame_data.array_id
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category.
    
                  DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_frame_data.array_id'
        _item.category_id             diffrn_frame_data
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_frame_data.binary_id
        _item_description.description
    ;             This item is a pointer to '_array_data.binary_id' in the
                  ARRAY_STRUCTURE category. 
                  
                  DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_frame_data.binary_id'
        _item.category_id             diffrn_frame_data
        _item.mandatory_code          implicit
        _item_type.code               int
         save_
    
    
    save__diffrn_frame_data.detector_element_id
        _item_description.description
    ;             
                  This item is a pointer to '_diffrn_detector_element.id'
                  in the DIFFRN_DETECTOR_ELEMENT category.
    
                  DEPRECATED -- DO NOT USE 
    ;
        _item.name                  '_diffrn_frame_data.detector_element_id'
        _item.category_id             diffrn_frame_data
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_frame_data.id
        _item_description.description
    ;             
                  The value of '_diffrn_frame_data.id' must uniquely identify
                  each complete frame of data.
    
                  DEPRECATED -- DO NOT USE 
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
               '_diffrn_frame_data.id'        diffrn_frame_data  yes
        _item_type.code               code
         save_
    
    ################ END DEPRECATED SECTION ###########
    
    
    ####################
    ## ITEM_TYPE_LIST ##
    ####################
    #
    #
    #  The regular expressions defined here are not compliant
    #  with the POSIX 1003.2 standard as they include the
    #  '\n' and '\t' special characters.  These regular expressions
    #  have been tested using version 0.12 of Richard Stallman's
    #  GNU regular expression library in POSIX mode.
    #  In order to allow presentation of a regular expression
    #  in a text field concatenate any line ending in a backslash
    #  with the following line, after discarding the backslash.
    #
    #  A formal definition of the '\n' and '\t' special characters
    #  is most properly done in the DDL, but for completeness, please
    #  note that '\n' is the line termination character ('newline')
    #  and '\t' is the horizontal tab character.  There is a formal
    #  ambiguity in the use of '\n' for line termination, in that
    #  the intention is that the equivalent machine/OS-dependent line
    #  termination character sequence should be accepted as a match, e.g.
    #
    #      '\r' (control-M) under MacOS
    #      '\n' (control-J) under Unix
    #      '\r\n' (control-M control-J) under DOS and MS Windows
    #
         loop_
        _item_type_list.code
        _item_type_list.primitive_code
        _item_type_list.construct
        _item_type_list.detail
                   code      char
    '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
    ;              code item types/single words ...
    ;
                   ucode      uchar
    '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
    ;              code item types/single words (case insensitive)
    ;
                   line      char
    '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
    ;              code item types / multi-word items  ...
    ;
                   uline     uchar
    '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
    ;              code item types / multi-word items (case insensitive)
    ;
                   text      char
    '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*'
    ;              text item types / multi-line text ...
    ;
                   binary    char
    ;\n--CIF-BINARY-FORMAT-SECTION--\n\
    [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\
    \n--CIF-BINARY-FORMAT-SECTION----
    ;
    ;              binary items are presented as MIME-like ascii-encoded
                   sections in an imgCIF.  In a CBF, raw octet streams
                   are used to convey the same information.
    ;
                   int       numb
    '-?[0-9]+'
    ;              int item types are the subset of numbers that are the negative
                   or positive integers.
    ;
                   float     numb
    '-?(([0-9]+)|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?'
    ;              float item types are the subset of numbers that are the floating
                   numbers.
    ;
                   any       char
    '.*'
    ;              A catch all for items that may take any form...
    ;
                   yyyy-mm-dd  char
    ;\
    [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9][0-9]\
    (T[0-2][0-9]:[0-5][0-9]:[0-5][0-9](.[0-9]+)([+-][0-5][0-9]:[0-5][0-9]))
    ;
    ;
                   Standard format for CIF date and time strings (see
                   http://www.iucr.org/iucr-top/cif/spec/datetime.html),
                   consisting of a yyyy-mm-dd date optionally followed by
                   the character "T" followed by a 24-hour clock time,
                   optionally followed by a signed time-zone offset.
                   
                   The IUCr standard has been extended to allow for an optional
                   decimal fraction on the seconds of time.
                   
                   Time is local time if no time-zone offset is given.
    ;
    
    
    #####################
    ## ITEM_UNITS_LIST ##
    #####################
    
         loop_
        _item_units_list.code
        _item_units_list.detail
    #
         'metres'                 'metres'
         'centimetres'            'centimetres (metres * 10( -2))'
         'millimetres'            'millimetres (metres * 10( -3))'
         'nanometres'             'nanometres  (metres * 10( -9))'
         'angstroms'              'Ångstroms   (metres * 10(-10))'
         'picometres'             'picometres  (metres * 10(-12))'
         'femtometres'            'femtometres (metres * 10(-15))'
    #
         'reciprocal_metres'      'reciprocal metres (metres(-1))'
         'reciprocal_centimetres' 
            'reciprocal centimetres ((metres * 10( -2))(-1))'
         'reciprocal_millimetres' 
            'reciprocal millimetres ((metres * 10( -3))(-1))'
         'reciprocal_nanometres'  
            'reciprocal nanometres  ((metres * 10( -9))(-1))'
         'reciprocal_angstroms'   
            'reciprocal Ångstroms   ((metres * 10(-10))(-1))'
         'reciprocal_picometres'  
            'reciprocal picometres  ((metres * 10(-12))(-1))'
    #
         'nanometres_squared'     'nanometres squared (metres * 10( -9))2'
         'angstroms_squared'      'Ångstroms squared  (metres * 10(-10))2'
         '8pi2_angstroms_squared' '8π2 * Ångstroms squared (metres * 10(-10))2'
         'picometres_squared'     'picometres squared (metres * 10(-12))2'
    #
         'nanometres_cubed'       'nanometres cubed (metres * 10( -9))3'
         'angstroms_cubed'        'Ångstroms cubed  (metres * 10(-10))3'
         'picometres_cubed'       'picometres cubed (metres * 10(-12))3'
    #
         'kilopascals'            'kilopascals'
         'gigapascals'            'gigapascals'
    #
         'hours'                  'hours'
         'minutes'                'minutes'
         'seconds'                'seconds'
         'microseconds'           'microseconds'
    #
         'degrees'                'degrees (of arc)'
         'degrees_squared'        'degrees (of arc) squared'
    #
         'degrees_per_minute'     'degrees (of arc) per minute'
    #
         'celsius'                'degrees (of temperature) Celsius'
         'kelvins'                'degrees (of temperature) Kelvin'
    #
         'counts'                 'counts'
         'counts_per_photon'      'counts per photon'
    #
         'electrons'              'electrons'
    #
         'electrons_squared'      'electrons squared'
    #
         'electrons_per_nanometres_cubed'
    ; electrons per nanometres cubed (electrons/(metres * 10( -9))(-3))
    ;
         'electrons_per_angstroms_cubed'
    ; electrons per Ångstroms cubed (electrons/(metres * 10(-10))(-3))
    ;
         'electrons_per_picometres_cubed'
    ; electrons per picometres cubed (electrons/(metres * 10(-12))(-3)) 
    ;
         'kilowatts'              'kilowatts'
         'milliamperes'           'milliamperes'
         'kilovolts'              'kilovolts'
    #
         'arbitrary'
    ; arbitrary system of units.
    ;
    #
    
         loop_
        _item_units_conversion.from_code
        _item_units_conversion.to_code
        _item_units_conversion.operator
        _item_units_conversion.factor
    ###
         'metres'                   'centimetres'              '*'   1.0E+02
         'metres'                   'millimetres'              '*'   1.0E+03
         'metres'                   'nanometres'               '*'   1.0E+09
         'metres'                   'angstroms'                '*'   1.0E+10
         'metres'                   'picometres'               '*'   1.0E+12
         'metres'                   'femtometres'              '*'   1.0E+15
    #
         'centimetres'              'metres'                   '*'   1.0E-02
         'centimetres'              'millimetres'              '*'   1.0E+01
         'centimetres'              'nanometres'               '*'   1.0E+07
         'centimetres'              'angstroms'                '*'   1.0E+08
         'centimetres'              'picometres'               '*'   1.0E+10
         'centimetres'              'femtometres'              '*'   1.0E+13
    #
         'millimetres'              'metres'                   '*'   1.0E-03
         'millimetres'              'centimetres'              '*'   1.0E-01
         'millimetres'              'nanometres'               '*'   1.0E+06
         'millimetres'              'angstroms'                '*'   1.0E+07
         'millimetres'              'picometres'               '*'   1.0E+09
         'millimetres'              'femtometres'              '*'   1.0E+12
    #
         'nanometres'               'metres'                   '*'   1.0E-09
         'nanometres'               'centimetres'              '*'   1.0E-07
         'nanometres'               'millimetres'              '*'   1.0E-06
         'nanometres'               'angstroms'                '*'   1.0E+01
         'nanometres'               'picometres'               '*'   1.0E+03
         'nanometres'               'femtometres'              '*'   1.0E+06
    #
         'angstroms'                'metres'                   '*'   1.0E-10
         'angstroms'                'centimetres'              '*'   1.0E-08
         'angstroms'                'millimetres'              '*'   1.0E-07
         'angstroms'                'nanometres'               '*'   1.0E-01
         'angstroms'                'picometres'               '*'   1.0E+02
         'angstroms'                'femtometres'              '*'   1.0E+05
    #
         'picometres'               'metres'                   '*'   1.0E-12
         'picometres'               'centimetres'              '*'   1.0E-10
         'picometres'               'millimetres'              '*'   1.0E-09
         'picometres'               'nanometres'               '*'   1.0E-03
         'picometres'               'angstroms'                '*'   1.0E-02
         'picometres'               'femtometres'              '*'   1.0E+03
    #
         'femtometres'              'metres'                   '*'   1.0E-15
         'femtometres'              'centimetres'              '*'   1.0E-13
         'femtometres'              'millimetres'              '*'   1.0E-12
         'femtometres'              'nanometres'               '*'   1.0E-06
         'femtometres'              'angstroms'                '*'   1.0E-05
         'femtometres'              'picometres'               '*'   1.0E-03
    ###
         'reciprocal_centimetres'   'reciprocal_metres'        '*'   1.0E+02
         'reciprocal_centimetres'   'reciprocal_millimetres'   '*'   1.0E-01
         'reciprocal_centimetres'   'reciprocal_nanometres'    '*'   1.0E-07
         'reciprocal_centimetres'   'reciprocal_angstroms'     '*'   1.0E-08
         'reciprocal_centimetres'   'reciprocal_picometres'    '*'   1.0E-10
    #
         'reciprocal_millimetres'   'reciprocal_metres'        '*'   1.0E+03
         'reciprocal_millimetres'   'reciprocal_centimetres'   '*'   1.0E+01
         'reciprocal_millimetres'   'reciprocal_nanometres'    '*'   1.0E-06
         'reciprocal_millimetres'   'reciprocal_angstroms'     '*'   1.0E-07
         'reciprocal_millimetres'   'reciprocal_picometres'    '*'   1.0E-09
    #
         'reciprocal_nanometres'    'reciprocal_metres'        '*'   1.0E+09
         'reciprocal_nanometres'    'reciprocal_centimetres'   '*'   1.0E+07
         'reciprocal_nanometres'    'reciprocal_millimetres'   '*'   1.0E+06
         'reciprocal_nanometres'    'reciprocal_angstroms'     '*'   1.0E-01
         'reciprocal_nanometres'    'reciprocal_picometres'    '*'   1.0E-03
    #
         'reciprocal_angstroms'     'reciprocal_metres'        '*'   1.0E+10
         'reciprocal_angstroms'     'reciprocal_centimetres'   '*'   1.0E+08
         'reciprocal_angstroms'     'reciprocal_millimetres'   '*'   1.0E+07
         'reciprocal_angstroms'     'reciprocal_nanometres'    '*'   1.0E+01
         'reciprocal_angstroms'     'reciprocal_picometres'    '*'   1.0E-02
    #
         'reciprocal_picometres'    'reciprocal_metres'        '*'   1.0E+12
         'reciprocal_picometres'    'reciprocal_centimetres'   '*'   1.0E+10
         'reciprocal_picometres'    'reciprocal_millimetres'   '*'   1.0E+09
         'reciprocal_picometres'    'reciprocal_nanometres'    '*'   1.0E+03
         'reciprocal_picometres'    'reciprocal_angstroms'     '*'   1.0E+01
    ###
         'nanometres_squared'       'angstroms_squared'        '*'   1.0E+02
         'nanometres_squared'       'picometres_squared'       '*'   1.0E+06
    #
         'angstroms_squared'        'nanometres_squared'       '*'   1.0E-02
         'angstroms_squared'        'picometres_squared'       '*'   1.0E+04
         'angstroms_squared'        '8pi2_angstroms_squared'   '*'   78.9568
    
    #
         'picometres_squared'       'nanometres_squared'       '*'   1.0E-06
         'picometres_squared'       'angstroms_squared'        '*'   1.0E-04
    ###
         'nanometres_cubed'         'angstroms_cubed'          '*'   1.0E+03
         'nanometres_cubed'         'picometres_cubed'         '*'   1.0E+09
    #
         'angstroms_cubed'          'nanometres_cubed'         '*'   1.0E-03
         'angstroms_cubed'          'picometres_cubed'         '*'   1.0E+06
    #
         'picometres_cubed'         'nanometres_cubed'         '*'   1.0E-09
         'picometres_cubed'         'angstroms_cubed'          '*'   1.0E-06
    ###
         'kilopascals'              'gigapascals'              '*'   1.0E-06
         'gigapascals'              'kilopascals'              '*'   1.0E+06
    ###
         'hours'                    'minutes'                  '*'   6.0E+01
         'hours'                    'seconds'                  '*'   3.6E+03
         'hours'                    'microseconds'             '*'   3.6E+09
    #
         'minutes'                  'hours'                    '/'   6.0E+01
         'minutes'                  'seconds'                  '*'   6.0E+01
         'minutes'                  'microseconds'             '*'   6.0E+07
    #
         'seconds'                  'hours'                    '/'   3.6E+03
         'seconds'                  'minutes'                  '/'   6.0E+01
         'seconds'                  'microseconds'             '*'   1.0E+06
    #
         'microseconds'             'hours'                    '/'   3.6E+09
         'microseconds'             'minutes'                  '/'   6.0E+07
         'microseconds'             'seconds'                  '/'   1.0E+06
    ###
         'celsius'                  'kelvins'                  '-'     273.0
         'kelvins'                  'celsius'                  '+'     273.0
    ###
         'electrons_per_nanometres_cubed'
         'electrons_per_angstroms_cubed'                       '*'   1.0E+03
         'electrons_per_nanometres_cubed'
         'electrons_per_picometres_cubed'                      '*'   1.0E+09
    #
         'electrons_per_angstroms_cubed'
         'electrons_per_nanometres_cubed'                      '*'   1.0E-03
         'electrons_per_angstroms_cubed'
         'electrons_per_picometres_cubed'                      '*'   1.0E+06
    #
         'electrons_per_picometres_cubed'
         'electrons_per_nanometres_cubed'                      '*'   1.0E-09
         'electrons_per_picometres_cubed'
         'electrons_per_angstroms_cubed'                       '*'   1.0E-06
    ###
    
    
    ########################
    ## DICTIONARY_HISTORY ##
    ########################
    
         loop_
        _dictionary_history.version
        _dictionary_history.update
        _dictionary_history.revision
    
    
       1.3.1   2003-08-13
    ;
       Changes as per Frances C. Bernstein.
       + Identify initials.
       + Adopt British spelling for centre in text.
       + Set π and Ångstrom and powers.
       + Clean up commas and unclear wordings.
       + Clean up tenses in history.
       Changes as per Gotzon Madariaga.
       + Fix the ARRAY_DATA example to align '_array_data.binary_id'
       and X-Binary-Id.
       + Add a range to '_array_intensities.gain_esd'.
       + In the example of DIFFRN_DETECTOR_ELEMENT, 
       '_diffrn_detector_element.id' and
       '_diffrn_detector_element.detector_id' interchanged.
       + Fix typos for direction, detector and axes.
       + Clarify description of polarisation.
       + Clarify axes in '_diffrn_detector_element.center[1]'
        '_diffrn_detector_element.center[2]'.
       + Add local item types for items that are pointers.
       (HJB)
    ;
    
    
       1.3.0   2003-07-24
    ;
       Changes as per Brian McMahon. 
       + Consistently quote tags embedded in text.
       + Clean up introductory comments.
       + Adjust line lengths to fit in 80 character window.
       + Fix several descriptions in AXIS category which
         referred to '_axis.type' instead of the current item.
       + Fix erroneous use of deprecated item
         '_diffrn_detector_axis.id' in examples for 
         DIFFRN_SCAN_AXIS.
       + Add deprecated items '_diffrn_detector_axis.id'
         and '_diffrn_measurement_axis.id'.
       (HJB)
    ;
    
    
       1.2.4   2003-07-14
    ;
       Changes as per I. David Brown. 
       + Enhance descriptions in DIFFRN_SCAN_AXIS to make them less
         dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS.
       + Provide a copy of the deprecated DIFFRN_FRAME_DATA
         category for completeness.
       (HJB)
    ;
    
    
       1.2.3   2003-07-03
    ;
       Cleanup to conform to ITVG. 
       + Correct sign error in ..._cubed units.
       + Correct '_diffrn_radiation.polarisn_norm' range.
       (HJB)
    ;
    
    
       1.2.2   2003-03-10
    ;
       Correction of typos in various DIFFRN_SCAN_AXIS descriptions. 
       (HJB)
    ;
    
    
       1.2.1   2003-02-22
    ;
       Correction of ATOM_ for ARRAY_ typos in various descriptions. 
       (HJB)
    ;
    
    
       1.2     2003-02-07
    ;
       Corrections to encodings (remove extraneous hyphens) remove
       extraneous underscore in '_array_structure.encoding_type'
       enumeration.  Correct typos in items units list.  (HJB)
    ;
    
    
       1.1.3   2001-04-19
    ;
       Another typo corrections by Wilfred Li, and cleanup by HJB.
    ;
    
    
       1.1.2   2001-03-06
    ;
       Several typo corrections by Wilfred Li.
    ;
    
    
       1.1.1   2001-02-16
    ;
       Several typo corrections by JW.
    ;
    
    
       1.1     2001-02-06
    ;
       Draft resulting from discussions on header for use at NSLS.  (HJB)
       
       + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME.
       
       + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'.
       
       + Add '_diffrn_measurement_axis.measurement_device' and change
         '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'.
       
       + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source',
        '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm',
       '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end',
       '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr',
       '_diffrn_scan_axis.displacement_rstrt_incr', 
       '_diffrn_scan_frame_axis.angle_increment',
       '_diffrn_scan_frame_axis.angle_rstrt_incr',
       '_diffrn_scan_frame_axis.displacement',
       '_diffrn_scan_frame_axis.displacement_increment',and
       '_diffrn_scan_frame_axis.displacement_rstrt_incr'.
       
       + Add '_diffrn_measurement.device' to category key.
       
       + Update yyyy-mm-dd to allow optional time with fractional seconds
         for time stamps.
    
       + Fix typos caught by RS.
       
       + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to
         allow for coupled axes, as in spiral scans.
    
       + Add examples for fairly complete headers thanks to R. Sweet and P. 
         Ellis.
    ;
    
    
       1.0     2000-12-21
    ;
       Release version - few typos and tidying up.  (BM & HJB)
       
       + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end
       of dictionary.
       
       + Alphabetize dictionary.
    ;
    
    
       0.7.1   2000-09-29
    ;
       Cleanup fixes.  (JW)
    
       + Correct spelling of diffrn_measurement_axis in '_axis.id'
    
       + Correct ordering of uses of '_item.mandatory_code' and
       '_item_default.value'.
    ;
    
    
       0.7.0   2000-09-09
    ;
       Respond to comments by I. David Brown.  (HJB)
    
       + Add further comments on '\n' and '\t'.
    
       + Update ITEM_UNITS_LIST by taking section from mmCIF dictionary
         and adding metres.  Change 'meter' to 'metre' throughout.
    
       + Add missing enumerations to '_array_structure.compression_type'
         and make 'none' the default.
    
       + Remove parent-child relationship between
         '_array_structure_list.index' and '_array_structure_list.precedence'.
    
       + Improve alphabetization.
    
       + Fix '_array_intensities_gain.esd' related function.
    
       + Improve comments in AXIS.
    
       + Fix DIFFRN_FRAME_DATA example.
    
       + Remove erroneous DIFFRN_MEASUREMENT example.
    
       + Add '_diffrn_measurement_axis.id' to the category key.
    ;
    
    
       0.6.0   1999-01-14
    ;
       Remove redundant information for ENC_NONE data.  (HJB)
    
       + After the D5 remove binary section identifier, size and
         compression type.
    
       + Add Control-L to header.
    ;
    
    
       0.5.1   1999-01-03
    ;
       Cleanup of typos and syntax errors.  (HJB)
    
       + Cleanup example details for DIFFRN_SCAN category.
    
       + Add missing quote marks for '_diffrn_scan.id' definition.
    ;
    
    
       0.5   1999-01-01
    ;
       Modifications for axis definitions and reduction of binary header.  (HJB)
    
       + Restore '_diffrn_detector.diffrn_id' to DIFFRN_DETECTOR KEY.
    
       + Add AXIS category.
    
       + Bring in complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories
         from cif_mm.dic for clarity.
    
       + Change '_array_structure.encoding_type' from type code to uline and
         added X-Binary-Element-Type to MIME header.
    
       + Add detector beam centre '_diffrn_detector_element.center[1]' and 
         '_diffrn_detector_element.center[2]'.
    
       + Correct item name of '_diffrn_refln.frame_id'.
    
       + Replace reference to '_array_intensities.undefined' by
         '_array_intensities.undefined_value'.
    
       + Replace references to '_array_intensity.scaling' with
         '_array_intensities.scaling'.
    
       + Add DIFFRN_SCAN... categories.
    ;
    
    
       0.4   1998-08-11
    ;
       Modifications to the 0.3 imgCIF draft.  (HJB)
    
       + Reflow comment lines over 80 characters and corrected typos.
    
       + Update examples and descriptions of MIME encoded data.
    
       + Change name to cbfext98.dic.
    ;
    
    
       0.3   1998-07-04
    ;
       Modifications for imgCIF.  (HJB)
    
       + Add binary type, which is a text field containing a variant on
         MIME encoded data.
          
       + Change type of '_array_data.data' to binary and specify internal
         structure of raw binary data.
          
       + Add '_array_data.binary_id', and make 
         '_diffrn_frame_data.binary_id' and '_array_intensities.binary_id'
         into pointers to this item.
    ;
    
    
       0.2   1997-12-02
    ;
       Modifications to the CBF draft.  (JW)  
    
       + Add category hierarchy for describing frame data developed from
         discussions at the BNL imgCIF Workshop Oct 1997.   The following
         changes are made in implementing the workshop draft.  Category
         DIFFRN_ARRAY_DATA is renamed to DIFFRN_FRAME_DATA.  Category
         DIFFRN_FRAME_TYPE is renamed to DIFFRN_DETECTOR_ELEMENT.   The
         parent item for '_diffrn_frame_data.array_id' is changed from
         '_array_structure_list.array_id' to '_array_structure.id'. Item 
         '_diffrn_detector.array_id' is deleted.  
       + Add data item '_diffrn_frame_data.binary_id' to identify data 
         groups within a binary section.  The formal identification of the
         binary section is still fuzzy.  
    ;
    
    
       0.1   1997-01-24
    ;
       First draft of this dictionary in DDL 2.1 compliant format by John 
       Westbrook (JW).  This version is adapted from the Crystallographic 
       Binary File (CBF) Format Draft Proposal provided by Andy Hammersley
       (AH).  
    
       Modifications to the CBF draft.  (JW)  
    
       + In this version the array description has been cast in the categories 
         ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST.  These categories
         have been generalized to describe array data  of arbitrary dimension.  
    
       + Array data in this description are contained in the category
         ARRAY_DATA.  This departs from the CBF notion of data existing
         in some special comment. In this description, data is handled as an 
         ordinary data item encapsulated in a character data type.   Although
         data this manner deviates from CIF conventions, it does not violate 
         any DDL 2.1 rules.  DDL 2.1 regular expressions can be used to define 
         the binary representation which will permit some level of data 
         validation.  In this version, the placeholder type code "any" has
         been used. This translates to a regular expression which will match 
         any pattern.
    
         It should be noted that DDL 2.1 already supports array data objects 
         although these have not been used in the current mmCIF dictionary.
         It may be possible to use the DDL 2.1 ITEM_STRUCTURE and
         ITEM_STRUCTURE_LIST categories to provide the information that is
         carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST.  By
         moving the array structure to the DDL level it would be possible to
         define an array type as well as a regular expression defining the
         data format. 
    
       + Multiple array sections can be properly handled within a single
         datablock.
    ;
    
    
    #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof
    
    ./CBFlib-0.9.2.2/doc/Iaxis.offset[2].html0000644000076500007650000000511411603702115016146 0ustar yayayaya (IUCr) CIF Definition save__axis.offset[2]

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _axis.offset[2]

    Name:
    '_axis.offset[2]'

    Definition:

            The [2] element of the three-element vector used to specify
                   the offset to the base of a rotation or translation axis.
    
                   The vector is specified in millimetres.
    
    

    Type: float

    Mandatory item: no


    Enumeration default: 0.0

    Category: axis

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/cif_img_1.3.2.html0000644000076500007650000071257411603702115015367 0ustar yayayaya cif_img.dic v1.3.2

    # [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib] #

    # imgCIF/CBF #

    # Extensions Dictionary #

    ##############################################################################
    #                                                                            #
    #                       Image CIF Dictionary (imgCIF)                        #
    #             and Crystallographic Binary File Dictionary (CBF)              #
    #            Extending the Macromolecular CIF Dictionary (mmCIF)             #
    #                                                                            #
    #                              Version 1.3.2                                 #
    #                              of 2005-06-22                                 #
    #                                                                            #
    #     by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook    #
    #                                                                            #
    # This dictionary was adapted from format discussed at the imgCIF Workshop,  #
    # held at BNL Oct 1997 and the Crystallographic Binary File Format Draft     #
    # Proposal by Andrew Hammersley.  The first DDL 2.1 Version was created by   #
    # John Westbrook.  This version was drafted by Herbert J. Bernstein and      #
    # incorporates comments by I. David Brown, John Westbrook, Brian McMahon,    #
    # Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li, Gotzon Madariaga,         #
    # Frances C. Bernstein and others.                                           #
    ##############################################################################
                                                                        
    data_cif_img.dic
    
        _dictionary.title           cif_img.dic
        _dictionary.version         1.3.2
        _dictionary.datablock_id    cif_img.dic
    
    ##############################################################################
    #    CONTENTS
    #
    #        CATEGORY_GROUP_LIST
    #
    #        category  ARRAY_DATA
    #
    #                  _array_data.array_id
    #                  _array_data.binary_id
    #                  _array_data.data
    #
    #        category  ARRAY_ELEMENT_SIZE
    #        
    #                  _array_element_size.array_id
    #                  _array_element_size.index
    #                  _array_element_size.size
    #        
    #        category  ARRAY_INTENSITIES
    #        
    #                  _array_intensities.array_id
    #                  _array_intensities.binary_id
    #                  _array_intensities.gain
    #                  _array_intensities.gain_esd
    #                  _array_intensities.linearity
    #                  _array_intensities.offset
    #                  _array_intensities.scaling
    #                  _array_intensities.overload
    #                  _array_intensities.undefined_value
    #        
    #        category  ARRAY_STRUCTURE
    #        
    #                  _array_structure.byte_order
    #                  _array_structure.compression_type
    #                  _array_structure.encoding_type
    #                  _array_structure.id
    #        
    #        category  ARRAY_STRUCTURE_LIST
    #        
    #                  _array_structure_list.axis_set_id
    #                  _array_structure_list.array_id
    #                  _array_structure_list.dimension
    #                  _array_structure_list.direction
    #                  _array_structure_list.index
    #                  _array_structure_list.precedence
    #
    #        category  ARRAY_STRUCTURE_LIST_AXIS
    #        
    #                  _array_structure_list_axis.axis_id
    #                  _array_structure_list_axis.axis_set_id
    #                  _array_structure_list_axis.angle
    #                  _array_structure_list_axis.angle_increment
    #                  _array_structure_list_axis.displacement_increment
    #                  _array_structure_list_axis.angular_pitch
    #                  _array_structure_list_axis.radial_pitch
    #
    #        category  AXIS
    #        
    #                  _axis.depends_on
    #                  _axis.equipment
    #                  _axis.id
    #                  _axis.offset[1]
    #                  _axis.offset[2]
    #                  _axis.offset[3]
    #                  _axis.type
    #                  _axis.vector[1]
    #                  _axis.vector[2]
    #                  _axis.vector[3]
    #
    #        category  DIFFRN_DATA_FRAME
    #
    #                  _diffrn_data_frame.array_id
    #                  _diffrn_data_frame.binary_id
    #                  _diffrn_data_frame.detector_element_id
    #                  _diffrn_data_frame.id
    #
    #        category  DIFFRN_DETECTOR
    #        
    #                  _diffrn_detector.details
    #                  _diffrn_detector.detector
    #                  _diffrn_detector.diffrn_id
    #                  _diffrn_detector.dtime
    #                  _diffrn_detector.id
    #                  _diffrn_detector.number_of_axes
    #                  _diffrn_detector.type
    #
    #        category  DIFFRN_DETECTOR_AXIS
    #        
    #                  _diffrn_detector_axis.axis_id
    #                  _diffrn_detector_axis.detector_id    
    #        
    #        category  DIFFRN_DETECTOR_ELEMENT
    #
    #                  _diffrn_detector_element.center[1]
    #                  _diffrn_detector_element.center[2]
    #                  _diffrn_detector_element.id
    #                  _diffrn_detector_element.detector_id
    #        
    #        category  DIFFRN_MEASUREMENT
    #        
    #                  _diffrn_measurement.diffrn_id
    #                  _diffrn_measurement.details
    #                  _diffrn_measurement.device
    #                  _diffrn_measurement.device_details
    #                  _diffrn_measurement.device_type
    #                  _diffrn_measurement.id
    #                  _diffrn_measurement.method
    #                  _diffrn_measurement.number_of_axes
    #                  _diffrn_measurement.specimen_support
    #
    #        category  DIFFRN_MEASUREMENT_AXIS
    #        
    #                  _diffrn_measurement_axis.axis_id
    #                  _diffrn_measurement_axis.measurement_device
    #                  _diffrn_measurement_axis.measurement_id
    #
    #        category  DIFFRN_RADIATION
    #
    #                  _diffrn_radiation.collimation
    #                  _diffrn_radiation.diffrn_id
    #                  _diffrn_radiation.div_x_source
    #                  _diffrn_radiation.div_y_source
    #                  _diffrn_radiation.div_x_y_source
    #                  _diffrn_radiation.filter_edge'
    #                  _diffrn_radiation.inhomogeneity
    #                  _diffrn_radiation.monochromator
    #                  _diffrn_radiation.polarisn_norm
    #                  _diffrn_radiation.polarisn_ratio
    #                  _diffrn_radiation.polarizn_source_norm
    #                  _diffrn_radiation.polarizn_source_ratio
    #                  _diffrn_radiation.probe
    #                  _diffrn_radiation.type
    #                  _diffrn_radiation.xray_symbol
    #                  _diffrn_radiation.wavelength_id
    #        
    #        category  DIFFRN_REFLN
    #        
    #                  _diffrn_refln.frame_id
    #
    #        category  DIFFRN_SCAN
    #        
    #                  _diffrn_scan.id
    #                  _diffrn_scan.date_end
    #                  _diffrn_scan.date_start
    #                  _diffrn_scan.integration_time
    #                  _diffrn_scan.frame_id_start
    #                  _diffrn_scan.frame_id_end
    #                  _diffrn_scan.frames
    #
    #        category  DIFFRN_SCAN_AXIS
    #        
    #                  _diffrn_scan_axis.axis_id
    #                  _diffrn_scan_axis.angle_start
    #                  _diffrn_scan_axis.angle_range
    #                  _diffrn_scan_axis.angle_increment
    #                  _diffrn_scan_axis.angle_rstrt_incr
    #                  _diffrn_scan_axis.displacement_start
    #                  _diffrn_scan_axis.displacement_range
    #                  _diffrn_scan_axis.displacement_increment
    #                  _diffrn_scan_axis.displacement_rstrt_incr
    #                  _diffrn_scan_axis.scan_id
    #
    #        category  DIFFRN_SCAN_FRAME
    #        
    #                  _diffrn_scan_frame.date
    #                  _diffrn_scan_frame.frame_id
    #                  _diffrn_scan_frame.frame_number
    #                  _diffrn_scan_frame.integration_time
    #                  _diffrn_scan_frame.scan_id
    #
    #        category  DIFFRN_SCAN_FRAME_AXIS
    #        
    #                  _diffrn_scan_frame_axis.axis_id
    #                  _diffrn_scan_frame_axis.angle
    #                  _diffrn_scan_frame_axis.angle_increment
    #                  _diffrn_scan_frame_axis.angle_rstrt_incr
    #                  _diffrn_scan_frame_axis.displacement
    #                  _diffrn_scan_frame_axis.displacement_increment
    #                  _diffrn_scan_frame_axis.displacement_rstrt_incr
    #                  _diffrn_scan_frame_axis.frame_id
    #
    #       ***DEPRECATED*** data items
    #
    #                  _diffrn_detector_axis.id
    #                  _diffrn_measurement_axis.id
    #
    #       ***DEPRECATED*** category  DIFFRN_FRAME_DATA
    #
    #                  _diffrn_frame_data.array_id
    #                  _diffrn_frame_data.binary_id
    #                  _diffrn_frame_data.detector_element_id
    #                  _diffrn_frame_data.id
    #
    #
    #        ITEM_TYPE_LIST
    #        ITEM_UNITS_LIST
    #        DICTIONARY_HISTORY
    #
    ##############################################################################
    
    
    #########################
    ## CATEGORY_GROUP_LIST ##
    #########################
    
         loop_
        _category_group_list.id
        _category_group_list.parent_id
        _category_group_list.description
                 'inclusive_group'   .
    ;             Categories that belong to the dictionary extension.
    ;
                 'array_data_group'
                 'inclusive_group'
    ;             Categories that describe array data.
    ;
                 'axis_group'
                 'inclusive_group'
    ;             Categories that describe axes.
    ;
                 'diffrn_group'
                 'inclusive_group'
    ;            Categories that describe details of the diffraction experiment.
    ;
    
    
    
    
    ##############
    # ARRAY_DATA #
    ##############
    
      
    save_ARRAY_DATA
        _category.description
    ;
         Data items in the ARRAY_DATA category are the containers for
         the array data items described in category ARRAY_STRUCTURE.
    ;
        _category.id                   array_data
        _category.mandatory_code       no
         loop_
        _category_key.name             '_array_data.array_id'
                                       '_array_data.binary_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 -
    
            This example shows two binary data blocks.  The first one
            was compressed by the CBF_CANONICAL compression algorithm and
            presented as hexadecimal data.  The first character "H" on the
            data lines means hexadecimal.  It could have been "O" for octal
            or "D" for decimal.  The second character on the line shows
            the number of bytes in each word (in this case "4"), which then
            requires 8 hexadecimal digits per word.  The third character
            gives the order of octets within a word, in this case "<"
            for the ordering 4321 (i.e. "big-endian").  Alternatively the
            character ">" could have been used for the ordering 1234
            (i.e. "little-endian").  The block has a "message digest"
            to check the integrity of the data.
    
            The second block is similar, but uses CBF_PACKED compression
            and BASE64 encoding.  Note that the size and the digest are
            different.
    ;
    ;
    
            loop_
            _array_data.array_id
            _array_data.binary_id
            _array_data.data
            image_1 1
            ;
            --CIF-BINARY-FORMAT-SECTION--
            Content-Type: application/octet-stream;
                 conversions="x-CBF_CANONICAL"
            Content-Transfer-Encoding: X-BASE16
            X-Binary-Size: 3927126
            X-Binary-ID: 1
            Content-MD5: u2sTJEovAHkmkDjPi+gWsg==
    
            # Hexadecimal encoding, byte 0, byte order ...21
            #
            H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ...
            ....
            --CIF-BINARY-FORMAT-SECTION----
            ;
            image_2 2
            ;
            --CIF-BINARY-FORMAT-SECTION--
            Content-Type: application/octet-stream;
                 conversions="x-CBF-PACKED"
            Content-Transfer-Encoding: BASE64
            X-Binary-Size: 3745758
            X-Binary-ID: 2
            Content-MD5: 1zsJjWPfol2GYl2V+QSXrw==
    
            ELhQAAAAAAAA...
            ...
            --CIF-BINARY-FORMAT-SECTION----
            ;
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    save_
    
    
    save__array_data.array_id
        _item_description.description
    ;             This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category. 
    ;
        _item.name                  '_array_data.array_id'
        _item.category_id             array_data
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__array_data.binary_id
        _item_description.description
    ;             This item is an integer identifier which, along with
                  '_array_data.array_id' should uniquely identify the 
                  particular block of array data.
                  
                  If '_array_data.binary_id' is not explicitly given,
                  it defaults to 1.
                  
                  The value of '_array_data.binary_id' distinguishes
                  among multiple sets of data with the same array
                  structure.
                  
                  If the MIME header of the data array specifies a 
                  value for X-Binary-Id, the value of  '_array_data.binary_id'
                  should be equal the value given for X-Binary-Id.
    ;
         loop_
        _item.name                  
        _item.category_id             
        _item.mandatory_code          
                 '_array_data.binary_id'            array_data      
                                                                    implicit
                 '_diffrn_data_frame.binary_id'     diffrn_data_frame
                                                                    implicit
                 '_array_intensities.binary_id'     array_intensities
                                                                    implicit
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_data_frame.binary_id'     '_array_data.binary_id'
                 '_array_intensities.binary_id'     '_array_data.binary_id'
    
        _item_default.value           1
        _item_type.code               int
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                1  1
                                .  1
         save_
    
    
    save__array_data.data
        _item_description.description
    ;             The value of '_array_data.data' contains the array data 
                  encapsulated in a STAR string.
                  
                  The representation used is a variant on the
                  Multipurpose Internet Mail Extensions (MIME) specified
                  in RFC 2045-2049 by N. Freed et al.  The boundary
                  delimiter used in writing an imgCIF or CBF is
                  "--CIF-BINARY-FORMAT-SECTION--" (including the
                  required initial "--").
    
                  The Content-Type may be any of the discrete types permitted
                  in RFC 2045; "application/octet-stream" is recommended.  
                  If an octet stream was compressed, the compression should 
                  be specified by the parameter 'conversions="x-CBF_PACKED"' 
                  or the parameter 'conversions="x-CBF_CANONICAL"'.
                  
                  The Content-Transfer-Encoding may be "BASE64",
                  "Quoted-Printable", "X-BASE8", "X-BASE10", or
                  "X-BASE16" for an imgCIF or "BINARY" for a CBF.  The
                  octal, decimal and hexadecimal transfer encodings are
                  for convenience in debugging, and are not recommended
                  for archiving and data interchange.
                  
                  In an imgCIF file, the encoded binary data begins after
                  the empty line terminating the header.  In a CBF, the
                  raw binary data begins after an empty line terminating
                  the header and after the sequence:
                        
                  Octet   Hex   Decimal  Purpose
                    0     0C       12    (ctrl-L) Page break
                    1     1A       26    (ctrl-Z) Stop listings in MS-DOS
                    2     04       04    (Ctrl-D) Stop listings in UNIX
                    3     D5      213    Binary section begins
    
                  None of these octets are included in the calculation of
                  the message size, nor in the calculation of the
                  message digest.
                                 
                  The X-Binary-Size header specifies the size of the
                  equivalent binary data in octets.  If compression was
                  used, this size is the size after compression, including
                  any book-keeping fields.  An adjustment is made for
                  the deprecated binary formats in which 8 bytes of binary
                  header are used for the compression type.  In that case,
                  the 8 bytes used for the compression type is subtracted
                  from the size, so that the same size will be reported
                  if the compression type is supplied in the MIME header.
                  Use of the MIME header is the recommended way to
                  supply the compression type.  In general, no portion of
                  the  binary header is included in the calculation of the size.
    
                  The X-Binary-Element-Type header specifies the type of
                  binary data in the octets, using the same descriptive
                  phrases as in '_array_structure.encoding_type'.  The default
                  value is "unsigned 32-bit integer".
                  
                  An MD5 message digest may, optionally, be used. The "RSA Data
                  Security, Inc. MD5 Message-Digest Algorithm" should be used.
                  No portion of the header is included in the calculation of the
                  message digest.
    
                  If the Transfer Encoding is "X-BASE8", "X-BASE10", or
                  "X-BASE16", the data is presented as octal, decimal or
                  hexadecimal data organized into lines or words.  Each word
                  is created by composing octets of data in fixed groups of
                  2, 3, 4, 6 or 8 octets, either in the order ...4321 ("big-
                  endian") or 1234... (little-endian).  If there are fewer
                  than the specified number of octets to fill the last word,
                  then the missing octets are presented as "==" for each
                  missing octet.  Exactly two equal signs are used for each
                  missing octet even for octal and decimal encoding.
                  The format of lines is:
    
                  rnd xxxxxx xxxxxx xxxxxx
    
                  where r is "H", "O", or "D" for hexadecimal, octal or
                  decimal, n is the number of octets per word. and d is "<"
                  for ">" for the "...4321" and "1234..." octet orderings
                  respectively.  The "==" padding for the last word should
                  be on the appropriate side to correspond to the missing
                  octets, e.g.
    
                  H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000
    
                  or
    
                  H3> FF0700 00====
    
                  For these hex, octal and decimal formats, only, comments
                  beginning with "#" are permitted to improve readability.
    
                  BASE64 encoding follows MIME conventions.  Octets are
                  in groups of three, c1, c2, c3.  The resulting 24 bits 
                  are broken into four 6-bit quantities, starting with 
                  the high-order six bits (c1 >> 2) of the first octet, then
                  the low-order two bits of the first octet followed by the
                  high-order 4 bits of the second octet ((c1 & 3)<<4 | (c2>>4)),
                  then the bottom 4 bits of the second octet followed by the
                  high order two bits of the last octet ((c2 & 15)<<2 | (c3>>6)),
                  then the bottom six bits of the last octet (c3 & 63).  Each
                  of these four quantities is translated into an ASCII character
                  using the mapping:
    
                            1         2         3         4         5         6
                  0123456789012345678901234567890123456789012345678901234567890123
                  |         |         |         |         |         |         |
                  ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/
    
                  With short groups of octets padded on the right with one "="
                  if c3 is missing, and with "==" if both c2 and c3 are missing.
    
                  QUOTED-PRINTABLE encoding also follows MIME conventions, copying
                  octets without translation if their ASCII values are 32..38,
                  42, 48..57, 59..60, 62, 64..126 and the octet is not a ";"
                  in column 1.  All other characters are translated to =nn, where
                  nn is the hexadecimal encoding of the octet.  All lines are
                  "wrapped" with a terminating "=" (i.e. the MIME conventions
                  for an implicit line terminator are never used).
    ;
        _item.name                  '_array_data.data'
        _item.category_id             array_data
        _item.mandatory_code          yes
        _item_type.code               binary
    save_
    
    
    ######################
    # ARRAY_ELEMENT_SIZE #
    ######################
    
    
    save_ARRAY_ELEMENT_SIZE
        _category.description
    ;
         Data items in the ARRAY_ELEMENT_SIZE category record the physical 
         size of array elements along each array dimension.
    ;
        _category.id                   array_element_size
        _category.mandatory_code       no
         loop_
        _category_key.name             '_array_element_size.array_id'
                                       '_array_element_size.index'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 - A regular 2D array with a uniform element dimension
                        of 1220 nanometres.
    ;
    ;
            loop_
           _array_element_size.array_id  
           _array_element_size.index
           _array_element_size.size
            image_1   1    1.22e-6
            image_1   2    1.22e-6
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_element_size.array_id
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category. 
    ;
        _item.name                  '_array_element_size.array_id'
        _item.category_id             array_element_size
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__array_element_size.index
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure_list.index' in
                  the ARRAY_STRUCTURE_LIST category. 
    ;
        _item.name                  '_array_element_size.index'
        _item.category_id             array_element_size
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__array_element_size.size
        _item_description.description
    ;
                   The size in metres of an image element in this 
                   dimension. This supposes that the elements are arranged
                   on a regular grid.
    ;
        _item.name               '_array_element_size.size'
        _item.category_id          array_element_size
        _item.mandatory_code       yes 
        _item_type.code            float
        _item_units.code           'metres'
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0.0
         save_
    
    
    #####################
    # ARRAY_INTENSITIES #
    #####################
    
    
    save_ARRAY_INTENSITIES
        _category.description
    ;
                  Data items in the ARRAY_INTENSITIES category record the
                  information required to recover the intensity data from 
                  the set of data values stored in the ARRAY_DATA category.
    
                  The actual detector may have a complex relationship
                  between the raw intensity values and the number of
                  incident photons.  In most cases, the number stored
                  in the final array will have a simple linear relationship
                  to the actual number of incident photons, given by
                  '_array_intensities.gain'.  If raw, uncorrected values
                  are presented (e.g for calibration experiments), the
                  value of '_array_intensities.linearity' will be 'raw'
                  and '_array_intensities.gain' will not be used.
    
    ;
        _category.id                   array_intensities
        _category.mandatory_code       no
        loop_
        _category_key.name             '_array_intensities.array_id'
                                       '_array_intensities.binary_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1
    ;
    ;
            loop_
            _array_intensities.array_id
            _array_intensities.linearity 
            _array_intensities.gain      
            _array_intensities.overload  
            _array_intensities.undefined_value 
            image_1   linear  1.2    655535   0
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_intensities.array_id
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category. 
    ;
        _item.name                  '_array_intensities.array_id'
        _item.category_id             array_intensities
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__array_intensities.binary_id
        _item_description.description
    ;             This item is a pointer to '_array_data.binary_id' in the
                  ARRAY_DATA category. 
    ;
        _item.name                  '_array_intensities.binary_id'
        _item.category_id             array_intensities
        _item.mandatory_code          implicit
        _item_type.code               int
         save_
    
    
    save__array_intensities.gain
        _item_description.description
    ;              
                   Detector "gain". The factor by which linearized 
                   intensity count values should be divided to produce
                   true photon counts.
    ;
        _item.name              '_array_intensities.gain'
        _item.category_id          array_intensities
        _item.mandatory_code       yes
        _item_type.code            float
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0.0
        _item_units.code           'counts_per_photon'
         loop_
        _item_related.related_name
        _item_related.function_code  '_array_intensities.gain_esd'
                                     'associated_value'
        save_
    
      
    save__array_intensities.gain_esd
        _item_description.description
    ;              
                  The estimated standard deviation in detector "gain".
    ;
        _item.name              '_array_intensities.gain_esd'
        _item.category_id          array_intensities
        _item.mandatory_code       yes
        _item_type.code            float
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0.0
    
        _item_units.code          'counts_per_photon'
         loop_
        _item_related.related_name
        _item_related.function_code  '_array_intensities.gain'
                                     'associated_esd'
        save_
    
    
    save__array_intensities.linearity
        _item_description.description
    ;
                   The intensity linearity scaling used from raw intensity
                   to the stored element value:
    
                   'linear' is obvious
    
                   'offset'  means that the value defined by 
                   '_array_intensities.offset' should be added to each
                    element value.  
    
                   'scaling' means that the value defined by 
                   '_array_intensities.scaling' should be multiplied with each 
                   element value.  
    
                   'scaling_offset' is the combination of the two previous cases, 
                   with the scale factor applied before the offset value.
    
                   'sqrt_scaled' means that the square root of raw 
                   intensities multiplied by '_array_intensities.scaling' is
                   calculated and stored, perhaps rounded to the nearest 
                   integer. Thus, linearization involves dividing the stored
                   values by '_array_intensities.scaling' and squaring the 
                   result. 
    
                   'logarithmic_scaled' means that the logarithm based 10 of
                   raw intensities multiplied by '_array_intensities.scaling' 
                   is calculated and stored, perhaps rounded to the nearest 
                   integer. Thus, linearization involves dividing the stored
                   values by '_array_intensities.scaling' and calculating 10
                   to the power of this number.
    
                   'raw' means that the data is a set of raw values straight 
                   from the detector.
    ;
    
        _item.name               '_array_intensities.linearity'
        _item.category_id          array_intensities
        _item.mandatory_code       yes
        _item_type.code            code
         loop_
        _item_enumeration.value   
        _item_enumeration.detail   
                                  'linear' .
                                  'offset'           
    ;
                   The value defined by  '_array_intensities.offset' should 
                   be added to each element value.  
    ;
                                  'scaling'
    ;
                   The value defined by '_array_intensities.scaling' should be 
                   multiplied with each element value.  
    ;
                                  'scaling_offset'   
    ;
                   The combination of the scaling and offset 
                   with the scale factor applied before the offset value.
    ;
                                  'sqrt_scaled'      
    ;
                   The square root of raw intensities multiplied by 
                   '_array_intensities.scaling' is calculated and stored, 
                   perhaps rounded to the nearest integer. Thus, 
                   linearization involves dividing the stored
                   values by '_array_intensities.scaling' and squaring the 
                   result. 
    ;
                                  'logarithmic_scaled'
    ;
                   The logarithm based 10 of raw intensities multiplied by 
                   '_array_intensities.scaling'  is calculated and stored, 
                   perhaps rounded to the nearest integer. Thus, 
                   linearization involves dividing the stored values by 
                   '_array_intensities.scaling' and calculating 10 to the 
                   power of this number.
    ;
                                  'raw'
    ;
                   The array consists of raw values to which no corrections have
                   been applied.  While the handling of the data is similar to 
                   that given for 'linear' data with no offset, the meaning of 
                   the data differs in that the number of incident photons is 
                   not necessarily linearly related to the number of counts 
                   reported.  This value is intended for use either in 
                   calibration experiments or to allow for handling more 
                   complex data fitting algorithms than are allowed for by 
                   this data item.
    ;
    
        save_
      
      
    save__array_intensities.offset
        _item_description.description
    ;
                   Offset value to add to array element values in the manner
                   described by item '_array_intensities.linearity'.
    ;
        _item.name                 '_array_intensities.offset'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        save_
    
    
    save__array_intensities.scaling
        _item_description.description
    ;
                   Multiplicative scaling value to be applied to array data
                   in the manner described by item
                   '_array_intensities.linearity'.
    ;
        _item.name                 '_array_intensities.scaling'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        save_
    
    
    save__array_intensities.overload
        _item_description.description
    ;
                   The saturation intensity level for this data array.
    ;
        _item.name                 '_array_intensities.overload'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        _item_units.code          'counts'
        save_
    
      
    save__array_intensities.undefined_value
        _item_description.description
    ;
                   A value to be substituted for undefined values in 
                   the data array.
    ;
        _item.name                 '_array_intensities.undefined_value'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        save_
    
    
    ###################
    # ARRAY_STRUCTURE #
    ###################
    
    
    save_ARRAY_STRUCTURE
        _category.description
    ;
         Data items in the ARRAY_STRUCTURE category record the organization and 
         encoding of array data which may be stored in the ARRAY_DATA category.
    ;
        _category.id                   array_structure
        _category.mandatory_code       no
        _category_key.name             '_array_structure.id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 -
    ;
    ;
         loop_
        _array_structure.id 
        _array_structure.encoding_type        
        _array_structure.compression_type     
        _array_structure.byte_order           
         image_1       "unsigned 16-bit integer"  none  little_endian
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_structure.byte_order
        _item_description.description
    ;
                   The order of bytes for integer values which require more
                   than 1-byte. 
    
                   (IBM-PC's and compatibles, and Dec-Vaxes use low-byte-first
                   ordered integers, whereas Hewlett Packard 700 
                   series, Sun-4 and Silicon Graphics use high-byte-first
                   ordered integers.  Dec-Alphas can produce/use either
                   depending on a compiler switch.)
    ;
    
        _item.name                     '_array_structure.byte_order'
        _item.category_id               array_structure
        _item.mandatory_code            yes 
        _item_type.code                 code
         loop_
        _item_enumeration.value        
        _item_enumeration.detail        
                                       'big_endian'
    ;
            The first byte in the byte stream of the bytes which make up an 
            integer value is the most significant byte of an integer. 
    ;
                                       'little_endian'
    ;
            The last byte in the byte stream of the bytes which make up an 
            integer value is the most significant byte of an integer.
    ;
         save_
    
    
    save__array_structure.compression_type 
        _item_description.description
    ;
                  Type of data compression method used to compress the array
                  data. 
    ;
        _item.name                   '_array_structure.compression_type'
        _item.category_id             array_structure
        _item.mandatory_code          no 
        _item_type.code               code
        _item_default.value           'none'
         loop_
        _item_enumeration.value       
        _item_enumeration.detail
                                      'none'
    ;
            Data are stored in normal format as defined by 
            '_array_structure.encoding_type' and 
            '_array_structure.byte_order'.
    ;
                                      'byte_offsets'
    ;
            Using the compression scheme defined in CBF definition
            Section 5.0.
    ;
                                      'packed'
    ;
            Using the 'packed' compression scheme, a CCP4-style packing
            (CBFlib section 3.3.2)
    ;
                                      'canonical'
    ;
            Using the 'canonical' compression scheme (CBFlib section
            3.3.1)
    ;
        save_
    
    
    save__array_structure.encoding_type
        _item_description.description
    ;
                   Data encoding of a single element of array data. 
                   
                   In several cases, the IEEE format is referenced.
                   See "IEEE Standard for Binary Floating-Point Arithmetic",
                   ANSI/IEEE Std 754-1985, the Institute of Electrical and
                   Electronics Engineers, Inc., NY 1985.  
    ;
    
        _item.name                '_array_structure.encoding_type'
        _item.category_id          array_structure
        _item.mandatory_code       yes 
        _item_type.code            uline
         loop_
        _item_enumeration.value   
                                  'unsigned 8-bit integer'
                                  'signed 8-bit integer'
                                  'unsigned 16-bit integer'
                                  'signed 16-bit integer'
                                  'unsigned 32-bit integer'
                                  'signed 32-bit integer'
                                  'signed 32-bit real IEEE'
                                  'signed 64-bit real IEEE'
                                  'signed 32-bit complex IEEE'
         save_
    
    
    save__array_structure.id
        _item_description.description
    ;             The value of '_array_structure.id' must uniquely identify 
                  each item of array data. 
    ;
        loop_
        _item.name                  
        _item.category_id             
        _item.mandatory_code          
                 '_array_structure.id'              array_structure      yes
                 '_array_data.array_id'             array_data           yes
                 '_array_structure_list.array_id'   array_structure_list yes
                 '_array_intensities.array_id'      array_intensities    yes
                 '_diffrn_data_frame.array_id'      diffrn_data_frame    yes
    
    
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_array_data.array_id'             '_array_structure.id'
                 '_array_structure_list.array_id'   '_array_structure.id'
                 '_array_intensities.array_id'      '_array_structure.id'
                 '_diffrn_data_frame.array_id'      '_array_structure.id'
    
         save_
    
    
    ########################
    # ARRAY_STRUCTURE_LIST #
    ########################
    
    
    save_ARRAY_STRUCTURE_LIST
        _category.description
    ;
         Data items in the ARRAY_STRUCTURE_LIST category record the size 
         and organization of each array dimension.
    
         The relationship to physical axes may be given.
    ;
        _category.id                   array_structure_list
        _category.mandatory_code       no
         loop_
        _category_key.name             '_array_structure_list.array_id'
                                       '_array_structure_list.index'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 - An image array of 1300 x 1200 elements.  The raster 
                        order of the image is left-to-right (increasing) in the
                        first dimension and bottom-to-top (decreasing) in 
                        the second dimension.
    ;
    ;
            loop_
           _array_structure_list.array_id  
           _array_structure_list.index
           _array_structure_list.dimension 
           _array_structure_list.precedence 
           _array_structure_list.direction
           _array_structure_list.axis_set_id
            image_1   1    1300    1     increasing  ELEMENT_X
            image_1   2    1200    2     decreasing  ELEMENY_Y
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_structure_list.array_id
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category. 
    ;
        _item.name                  '_array_structure_list.array_id'
        _item.category_id             array_structure_list
        _item.mandatory_code          yes
        _item_type.code               code
    save_
    
    
    save__array_structure_list.axis_set_id
        _item_description.description
    ;              This is a descriptor for the physical axis or set of axes 
                   corresponding to an array index.
                   
                   This data item is related to the axes of the detector 
                   itself given in DIFFRN_DETECTOR_AXIS, but usually differ
                   in that the axes in this category are the axes of the
                   coordinate system of reported data points, while the axes in
                   DIFFRN_DETECTOR_AXIS are the physical axes 
                   of the detector describing the "poise" of the detector as an
                   overall physical object.
                   
                   If there is only one axis in the set, the identifier of 
                   that axis should be used as the identifier of the set.
                   
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
               '_array_structure_list.axis_set_id'
                                      array_structure_list            yes
               '_array_structure_list_axis.axis_set_id'
                                      array_structure_list_axis       implicit
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_array_structure_list_axis.axis_set_id'
                                   '_array_structure_list.axis_set_id'
    
    
         save_
    
    
    save__array_structure_list.dimension
        _item_description.description
    ;              
                   The number of elements stored in the array structure in this 
                   dimension.
    ;
        _item.name                '_array_structure_list.dimension'
        _item.category_id          array_structure_list
        _item.mandatory_code       yes 
        _item_type.code            int
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                1  1
                                .  1
         save_
    
    
    save__array_structure_list.direction
        _item_description.description
    ;
                  Identifies the direction in which this array index changes.
    ;
        _item.name                '_array_structure_list.direction'
        _item.category_id          array_structure_list
        _item.mandatory_code       yes 
        _item_type.code            int
         loop_
        _item_enumeration.value
        _item_enumeration.detail        
    
                                  'increasing'
    ;
             Indicates the index changes from 1 to the maximum dimension.
    ;
                                  'decreasing'
    ;
             Indicates the index changes from the maximum dimension to 1.
    ;
         save_
    
    
    save__array_structure_list.index
        _item_description.description
    ;              
                   Identifies the one-based index of the row or column in the
                   array structure.
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
               '_array_structure_list.index'        array_structure_list   yes
               '_array_structure_list.precedence'   array_structure_list   yes
               '_array_element_size.index'          array_element_size     yes
    
        _item_type.code            int
    
         loop_
        _item_linked.child_name
        _item_linked.parent_name
              '_array_element_size.index'         '_array_structure_list.index'
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                1  1
                                .  1
         save_
    
    
    save__array_structure_list.precedence
        _item_description.description
    ;
                   Identifies the rank order in which this array index changes 
                   with respect to other array indices.  The precedence of 1  
                   indicates the index which changes fastest.
    ;
        _item.name                '_array_structure_list.precedence'
        _item.category_id          array_structure_list
        _item.mandatory_code       yes 
        _item_type.code            int
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                1  1
                                .  1
         save_
    
    
    #############################
    # ARRAY_STRUCTURE_LIST_AXIS #
    #############################
    
    save_ARRAY_STRUCTURE_LIST_AXIS
        _category.description
    ;
         Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe
         the physical settings of sets axes for the centres of pixels that 
         correspond to data points described in the 
         ARRAY_STRUCTURE_LIST category. 
         
         In the simplest cases, the physical increments of a single axis correspond
         to the increments of a single array index.  More complex organizations,
         e.g. spiral scans, may require coupled motions along multiple axes.
         
         Note that a spiral scan uses two coupled axis, one for the angular 
         direction, one for the radial direction.  This differs from a 
         cylindrical scan for which the two axes are not coupled into one set.
         
    ;
        _category.id                   array_structure_list_axis
        _category.mandatory_code       no
         loop_
        _category_key.name
                                      '_array_structure_list_axis.axis_set_id'
                                      '_array_structure_list_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'array_data_group'
         save_
    
    
    save__array_structure_list_axis.axis_id
        _item_description.description
    ;
                   The value of this data item is the identifier of one of
                   the axes from the set of axes for which settings are being 
                   specified.
    
                   Multiple axes may be specified for the same value of
                   '_array_structure_list_axis.axis_set_id'
    
                   This item is a pointer to '_axis.id' in the
                   AXIS category.
    ;
        _item.name                 '_array_structure_list_axis.axis_id'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__array_structure_list_axis.axis_set_id
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   set of axes for which axis settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   '_array_structure_list_axis.axis_set_id'.
    
                   This item is a pointer to
                   '_array_structure_list.axis_set_id'
                   in the ARRAY_STRUCTURE_LIST category.
                   
                   If this item is not specified, it defaults to the corresponding
                   axis identifier.
    ;
        _item.name                 '_array_structure_list_axis.axis_set_id'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       implicit
        _item_type.code            code
         save_
    
    
    save__array_structure_list_axis.angle
        _item_description.description
    ;
                   The setting of the specified axis in degrees for the first
                   data point of the array index with the corresponding value
                   of '_array_structure_list.axis_set_id'.  If the index is
                   specified as 'increasing' this will be the centre of the
                   pixel with index value 1.  If the index is specified as
                   'decreasing' this will be the centre of the pixel with
                   maximum index value. 
    ;
        _item.name                 '_array_structure_list_axis.angle'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__array_structure_list_axis.angle_increment
        _item_description.description
    ;
                   The pixel-centre-to-pixel-centre increment in the angular 
                   setting of the specified axis in degrees.  This is not 
                   meaningful in the case of 'constant velocity' spiral scans  
                   and should not be specified in that case.  
    
                   See '_array_structure_list_axis.angular_pitch'.
                   
    ;
        _item.name                 '_array_structure_list_axis.angle_increment'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__array_structure_list_axis.displacement
        _item_description.description
    ;
                   The setting of the specified axis in millimetres for the first
                   data point of the array index with the corresponding value
                   of '_array_structure_list.axis_set_id'.  If the index is
                   specified as 'increasing' this will be the centre of the
                   pixel with index value 1.  If the index is specified as
                   'decreasing' this will be the centre of the pixel with
                   maximum index value. 
    
    ;
        _item.name               '_array_structure_list_axis.displacement'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__array_structure_list_axis.displacement_increment
        _item_description.description
    ;
                   The pixel-centre-to-pixel-centre increment for the displacement 
                   setting of the specified axis in millimetres.
                   
    ;
        _item.name                 
            '_array_structure_list_axis.displacement_increment'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
      
    
    save__array_structure_list_axis.angular_pitch
        _item_description.description
    ;
                   The pixel-centre-to-pixel-centre distance for a one step 
                   change in the setting of the specified axis in millimetres.
                   
                   This is meaningful only for 'constant velocity' spiral scans,
                   or for uncoupled angular scans at a constant radius
                   (cylindrical scan) and should not be specified for cases
                   in which the angle between pixels, rather than the distance
                   between pixels is uniform.
                   
                   See '_array_structure_list_axis.angle_increment'.
                   
    ;
        _item.name               '_array_structure_list_axis.angular_pitch'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
       
    
    save__array_structure_list_axis.radial_pitch
        _item_description.description
    ;
                   The radial distance from one "cylinder" of pixels to the
                   next in millimetres.  If the scan is a 'constant velocity'
                   scan with differing angular displacements between pixels,
                   the value of this item may differ significantly from the
                   value of '_array_structure_list_axis.displacement_increment'.
                   
    ;
        _item.name               '_array_structure_list_axis.radial_pitch'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
      
    
    
    ########
    # AXIS #
    ########
    
    save_AXIS
        _category.description
    ;
         Data items in the AXIS category record the information required
         to describe the various goniometer, detector, source and other
         axes needed to specify a data collection.  The location of each
         axis is specified by two vectors: the axis itself, given as a unit
         vector, and an offset to the base of the unit vector.  These vectors
         are referenced to a right-handed laboratory coordinate system with
         its origin in the sample or specimen:
         
                                 | Y (to complete right-handed system)
                                 |
                                 |
                                 |
                                 |
                                 |
                                 |________________X
                                /       principal goniometer axis
                               /
                              /
                             /
                            /
                           /Z (to source)
    
    
                                                          
         Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from
         the sample or specimen along the  principal axis of the goniometer.
         
         Axis 2 (Y): The Y-axis completes an orthogonal right-handed system
         defined by the X-axis and the Z-axis (see below).
         
         Axis 3 (Z): The Z-axis is derived from the source axis which goes from 
         the sample to the source.  The Z-axis is the component of the source axis
         in the direction of the source orthogonal to the X-axis in the plane 
         defined by the X-axis and the source axis.
              
         These axes are based on the goniometer, not on the orientation of the 
         detector, gravity, etc.  The vectors necessary to specify all other
         axes are given by sets of three components in the order (X, Y, Z).
         If the axis involved is a rotation axis, it is right handed, i.e. as
         one views the object to be rotated from the origin (the tail) of the 
         unit vector, the rotation is clockwise.  If a translation axis is
         specified, the direction of the unit vector specifies the sense of
         positive translation.
         
         Note:  This choice of coordinate system is similar to, but significantly
         different from the choice in MOSFLM (Andrew G.W. Leslie, Harry Powell,
         MRC Laboratory of Molecular Biology, Hills Road, Cambridge CB2 2QH, UK
         http://www.dl.ac.uk/CCP/CCP4/dist/x-windows/Mosflm/).  In MOSFLM,
         X is along the X-ray beam (the CBF/imgCIF Z axis) and Z is along the 
         rotation axis.
    
         All rotations are given in degrees and all translations are given in mm.
         
         Axes may be dependent on one another.  The X-axis is the only goniometer
         axis the direction of which is strictly connected to the hardware.  All
         other axes are specified by the positions they would assume when the
         axes upon which they depend are at their zero points.
         
         When specifying detector axes, the axis is given to the beam centre.
         The location of the beam centre on the detector should be given in the
         DIFFRN_DETECTOR category in distortion-corrected mm from the (0,0) corner
         of the detector.
         
         It should be noted that many different origins arise in the definition
         of an experiment.  In particular, as noted above, we need to specify the
         location of the beam centre on the detector in terms of the origin of the
         detector, which is, of course, not coincident with the centre of the
         sample.  
    ;
        _category.id                   axis
        _category.mandatory_code       no
         loop_
        _category_key.name          '_axis.id' 
                                    '_axis.equipment'               
         loop_
        _category_group.id           'inclusive_group'
                                     'axis_group'
                                     'diffrn_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 -
            
            This example shows the axis specification of the axes of a kappa
            geometry goniometer (See "X-Ray Structure Determination, A Practical
            Guide", 2nd ed. by  G. H. Stout, L. H. Jensen, Wiley Interscience,
            1989, 453 pp, p 134.).
            
            There are three axes specified, and no offsets.  The outermost axis,
            omega, is pointed along the X-axis.  The next innermost axis, kappa,
            is at a 50 degree angle to the X-axis, pointed away from the source.
            The innermost axis, phi, aligns with the X-axis when omega and
            phi are at their zero-points.  If T-omega, T-kappa and T-phi
            are the transformation matrices derived from the axis settings,
            the complete transformation would be:
                x' = (T-omega) (T-kappa) (T-phi) x
    ;
    ;
             loop_
            _axis.id
            _axis.type
            _axis.equipment
            _axis.depends_on
            _axis.vector[1] _axis.vector[2] _axis.vector[3]
            omega rotation goniometer     .    1        0        0
            kappa rotation goniometer omega    -.64279  0       -.76604
            phi   rotation goniometer kappa    1        0        0   
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 2 -
            
            This example show the axis specification of the axes of a
            detector, source and gravity.  We have juggled the order as a
            reminder that the ordering of presentation of tokens is not
            significant.  We have taken the centre of rotation of the detector
            to be 68 millimetres in the direction away from the source.
    ;
    ;
            loop_
            _axis.id
            _axis.type
            _axis.equipment
            _axis.depends_on
            _axis.vector[1] _axis.vector[2] _axis.vector[3]
            _axis.offset[1] _axis.offset[2] _axis.offset[3]
            source       .        source     .       0     0     1   . . .
            gravity      .        gravity    .       0    -1     0   . . .
            tranz     translation detector rotz      0     0     1   0 0 -68
            twotheta  rotation    detector   .       1     0     0   . . .
            roty      rotation    detector twotheta  0     1     0   0 0 -68
            rotz      rotation    detector roty      0     0     1   0 0 -68
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__axis.depends_on
        _item_description.description
    ;             The value of '_axis.depends_on' specifies the next outermost
                  axis upon which this axis depends.
                  
                  This item is a pointer to '_axis.id' in the same category.
    ;
        _item.name                      '_axis.depends_on'
        _item.category_id                 axis
        _item.mandatory_code              no
    
         save_
    
    
    save__axis.equipment
        _item_description.description
    ;             The value of  '_axis.equipment' specifies the type of
                  equipment using the axis:  'goniometer', 'detector',
                  'gravity', 'source' or 'general'.
    ;
        _item.name                      '_axis.equipment'
        _item.category_id                 axis
        _item.mandatory_code              no
        _item_type.code                   ucode
        _item_default.value               general
         loop_
        _item_enumeration.value
        _item_enumeration.detail   goniometer
                                  'equipment used to orient or position samples'
                                   detector
                                  'equipment used to detect reflections'
                                   general
                                  'equipment used for general purposes'
                                   gravity
                                  'axis specifying the downward direction'
                                   source
                                  'axis specifying the direction sample to source'
    
         save_
    
    
    save__axis.offset[1]
        _item_description.description
    ;              The [1] element of the 3-element vector used to specify
                   the offset to the base of a rotation or translation axis.
                   
                   The vector is specified in millimetres
    ;
        _item.name                  '_axis.offset[1]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    
    save__axis.offset[2]
        _item_description.description
    ;              The [2] element of the 3-element vector used to specify
                   the offset to the base of a rotation or translation axis.
                   
                   The vector is specified in millimetres
    ;
        _item.name                  '_axis.offset[2]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    
    save__axis.offset[3]
        _item_description.description
    ;              The [3] element of the 3-element vector used to specify
                   the offset to the base of a rotation or translation axis.
                   
                   The vector is specified in millimetres
    ;
        _item.name                  '_axis.offset[3]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    
    save__axis.id
        _item_description.description
    ;             The value of '_axis.id' must uniquely identify
                  each axis relevant to the experiment.  Note that multiple
                  pieces of equipment may share the same axis (e.g. a twotheta
                  arm), so that the category key for AXIS also includes the
                  equipment.
    ;
        loop_
        _item.name
        _item.category_id
        _item.mandatory_code
             '_axis.id'                         axis                    yes
             '_array_structure_list_axis.axis_id'
                                                array_structure_list_axis
                                                                        yes
             '_diffrn_detector_axis.axis_id'    diffrn_detector_axis    yes
             '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes
             '_diffrn_scan_axis.axis_id'        diffrn_scan_axis        yes
             '_diffrn_scan_frame_axis.axis_id'  diffrn_scan_frame_axis  yes
    
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
             '_axis.depends_on'                   '_axis.id'
             '_array_structure_list_axis.axis_id' '_axis.id'
             '_diffrn_detector_axis.axis_id'      '_axis.id'
             '_diffrn_measurement_axis.axis_id'   '_axis.id'
             '_diffrn_scan_axis.axis_id'          '_axis.id'      
             '_diffrn_scan_frame_axis.axis_id'    '_axis.id'
    
         save_
    
    
    save__axis.type
        _item_description.description
    ;             The value of '_axis.type' specifies the type of
                  axis:  'rotation', 'translation' (or 'general' when
                  the type is not relevant, as for gravity).
    ;
        _item.name                      '_axis.type'
        _item.category_id                 axis
        _item.mandatory_code              no
        _item_type.code                   ucode
        _item_default.value               general
         loop_
        _item_enumeration.value
        _item_enumeration.detail      rotation
                                     'right-handed axis of rotation'
                                      translation
                                     'translation in the direction of the axis'
                                      general
                                     'axis for which the type is not relevant'
    
         save_
    
    
    save__axis.vector[1]
        _item_description.description
    ;              The [1] element of the 3-element vector used to specify
                   the direction of a rotation or translation axis.
                   The vector should be normalized to be a unit vector and
                   is dimensionless.
    ;
        _item.name                  '_axis.vector[1]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
         save_
    
    save__axis.vector[2]
        _item_description.description
    ;              The [2] element of the 3-element vector used to specify
                   the direction of a rotation or translation axis.
                   The vector should be normalized to be a unit vector and
                   is dimensionless.
    ;
        _item.name                  '_axis.vector[2]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
         save_
    
    save__axis.vector[3]
        _item_description.description
    ;              The [3] element of the 3-element vector used to specify
                   the direction of a rotation or translation axis.
                   The vector should be normalized to be a unit vector and
                   is dimensionless.
    ;
        _item.name                  '_axis.vector[3]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
         save_
    
    
    
    #####################
    # DIFFRN_DATA_FRAME #
    #####################
    
    
    save_DIFFRN_DATA_FRAME
        _category.description
    ;
                  Data items in the DIFFRN_DATA_FRAME category record
                  the details about each frame of data. 
                  
                  The items in this category were previously in a
                  DIFFRN_FRAME_DATA category, which is now deprecated.
                  The items from the old category are provided
                  as aliases but should not be used for new work.
    ;
        _category.id                   diffrn_data_frame
        _category.mandatory_code       no
         loop_
        _category_key.name             '_diffrn_data_frame.id'
                                       '_diffrn_data_frame.detector_element_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 - A frame containing data from 4 frame elements.
                    Each frame element has a common array configuration
                    'array_1' described in ARRAY_STRUCTURE and related
                    categories.  The data for each detector element is 
                    stored in four groups of binary data in the
                    ARRAY_DATA category, linked by the array_id and
                    binary_id
    ;
    ;
            loop_
            _diffrn_data_frame.id
            _diffrn_data_frame.detector_element_id
            _diffrn_data_frame.array_id
            _diffrn_data_frame.binary_id
            frame_1   d1_ccd_1  array_1  1  
            frame_1   d1_ccd_2  array_1  2 
            frame_1   d1_ccd_3  array_1  3 
            frame_1   d1_ccd_4  array_1  4 
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
    
    
    save__diffrn_data_frame.array_id
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category. 
    ;
        _item.name                  '_diffrn_data_frame.array_id'
        _item.category_id             diffrn_data_frame
        _item.mandatory_code          yes
        _item_aliases.alias_name    '_diffrn_frame_data.array_id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0.00
        _item_type.code               code
         save_
    
    
    save__diffrn_data_frame.binary_id
        _item_description.description
    ;             This item is a pointer to '_array_data.binary_id' in the
                  ARRAY_DATA category. 
    ;
        _item.name                  '_diffrn_data_frame.binary_id'
        _item.category_id             diffrn_data_frame
        _item.mandatory_code          implicit
        _item_aliases.alias_name    '_diffrn_frame_data.binary_id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               int
         save_
    
    
    save__diffrn_data_frame.detector_element_id
        _item_description.description
    ;             
                   This item is a pointer to '_diffrn_detector_element.id'
                   in the DIFFRN_DETECTOR_ELEMENT category. 
    ;
        _item.name                  '_diffrn_data_frame.detector_element_id'
        _item.category_id             diffrn_data_frame
        _item.mandatory_code          yes
        _item_aliases.alias_name    '_diffrn_frame_data.detector_element_id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         save_
    
    
    save__diffrn_data_frame.id
        _item_description.description
    ;             
                  The value of '_diffrn_data_frame.id' must uniquely identify
                  each complete frame of data.
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
               '_diffrn_data_frame.id'        diffrn_data_frame  yes
               '_diffrn_refln.frame_id'       diffrn_refln       yes
               '_diffrn_scan.frame_id_start'  diffrn_scan        yes
               '_diffrn_scan.frame_id_end'    diffrn_scan        yes
               '_diffrn_scan_frame.frame_id'  diffrn_scan_frame  yes
               '_diffrn_scan_frame_axis.frame_id'  
                                              diffrn_scan_frame_axis
                                                                 yes
        _item_aliases.alias_name    '_diffrn_frame_data.id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_diffrn_refln.frame_id'        '_diffrn_data_frame.id'
               '_diffrn_scan.frame_id_start'   '_diffrn_data_frame.id'
               '_diffrn_scan.frame_id_end'     '_diffrn_data_frame.id'
               '_diffrn_scan_frame.frame_id'   '_diffrn_data_frame.id'
               '_diffrn_scan_frame_axis.frame_id'
                                               '_diffrn_data_frame.id'
         save_
    
    
    ##########################################################################
    #  The following is a restatement of the mmCIF DIFFRN_DETECTOR,          #
    #  DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for      #
    #  the CBF/imgCIF extensions                                             #
    ##########################################################################
    
    ###################
    # DIFFRN_DETECTOR #
    ###################
    
    
    save_DIFFRN_DETECTOR
        _category.description
    ;              Data items in the DIFFRN_DETECTOR category describe the 
                   detector used to measure the scattered radiation, including
                   any analyser and post-sample collimation.
    ;
        _category.id                  diffrn_detector
        _category.mandatory_code      no
         loop_
        _category_key.name          '_diffrn_detector.diffrn_id'
                                    '_diffrn_detector.id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 - based on PDB entry 5HVP and laboratory records for the
                    structure corresponding to PDB entry 5HVP
    ;
    ;
        _diffrn_detector.diffrn_id             'd1'
        _diffrn_detector.detector              'multiwire'
        _diffrn_detector.type                  'Siemens'
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__diffrn_detector.details
        _item_description.description
    ;              A description of special aspects of the radiation detector.
    ;
        _item.name                  '_diffrn_detector.details'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_detector_details'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code                   text
        _item_examples.case        'slow mode' 
         save_
    
    
    save__diffrn_detector.detector
        _item_description.description
    ;              The general class of the radiation detector.
    ;
        _item.name                  '_diffrn_detector.detector'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
         loop_
        _item_aliases.alias_name
        _item_aliases.dictionary
        _item_aliases.version       '_diffrn_radiation_detector'
                                      cifdic.c91
                                      1.0
                                    '_diffrn_detector'
                                      cif_core.dic
                                      2.0
        _item_type.code               text
         loop_
        _item_examples.case          'photographic film'
                                     'scintillation counter'
                                     'CCD plate'
                                     'BF~3~ counter'
         save_
    
    
    save__diffrn_detector.diffrn_id
        _item_description.description
    ;              This data item is a pointer to '_diffrn.id' in the DIFFRN
                   category.
    
                   The value of '_diffrn.id' uniquely defines a set of
                   diffraction data.
    ;
        _item.name                  '_diffrn_detector.diffrn_id'
        _item.mandatory_code          yes
         save_
    
    
    save__diffrn_detector.dtime
        _item_description.description
    ;              The deadtime in microseconds of the detectors used to
                   measure the diffraction intensities.
    ;
        _item.name                  '_diffrn_detector.dtime'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
         loop_
        _item_aliases.alias_name
        _item_aliases.dictionary
        _item_aliases.version       '_diffrn_radiation_detector_dtime'
                                      cifdic.c91
                                      1.0
                                    '_diffrn_detector_dtime'
                                      cif_core.dic
                                      2.0
         loop_  
        _item_range.maximum           
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
        _item_units.code              microseconds
         save_
    
    
    save__diffrn_detector.id
        _item_description.description
    ;             
                   The value of '_diffrn_detector.id' must uniquely identify
                   each detector used to collect each diffraction data set.
    
                   If the value of '_diffrn_detector.id' is not given, it is
                   implicitly equal to the value of
                   '_diffrn_detector.diffrn_id'
    ;
         loop_
        _item.name                 
        _item.category_id
        _item.mandatory_code
                 '_diffrn_detector.id'         diffrn_detector       implicit
                 '_diffrn_detector_axis.detector_id'
                                               diffrn_detector_axis       yes
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_detector_axis.detector_id'
                                             '_diffrn_detector.id'
    
        _item_type.code               code
         save_
    
    
    save__diffrn_detector.number_of_axes
        _item_description.description
    ;             
                   The value of '_diffrn_detector.number_of_axes' gives the 
                   number of axes of the positioner for the detector identified 
                   by '_diffrn_detector.id'.
                   
                   The word "positioner" is a general term used in
                   instrumentation design for devices that are used to change
                   the positions of portions of apparatus by linear
                   translation, rotation, or combinations of such motions.
                   
                   Axes which are used to provide a coordinate system for the
                   face of an area detetctor should not be counted for this
                   data item.
    
                   The description of each axis should be provided by entries 
                   in DIFFRN_DETECTOR_AXIS.
    ;
        _item.name                  '_diffrn_detector.number_of_axes'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
         loop_
        _item_range.maximum
        _item_range.minimum           .   1
                                      1   1
        _item_type.code               int
         save_
    
    
    save__diffrn_detector.type
        _item_description.description
    ;              The make, model or name of the detector device used.
    ;
        _item.name                  '_diffrn_detector.type'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_detector_type'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         save_
    
    
    ########################
    # DIFFRN_DETECTOR_AXIS #
    ########################
    
    
    save_DIFFRN_DETECTOR_AXIS
        _category.description
    ;
         Data items in the DIFFRN_DETECTOR_AXIS category associate
         axes with detectors.
    ;
        _category.id                   diffrn_detector_axis
        _category.mandatory_code       no
         loop_
        _category_key.name          '_diffrn_detector_axis.detector_id'
                                    '_diffrn_detector_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_detector_axis.axis_id
        _item_description.description
    ;
                   This data item is a pointer to '_axis.id' in
                   the AXIS category.
    ;
        _item.name                  '_diffrn_detector_axis.axis_id'
        _item.category_id             diffrn_detector_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_detector_axis.detector_id
        _item_description.description
    ;
                   This data item is a pointer to '_diffrn_detector.id' in
                   the DIFFRN_DETECTOR category.
    
                   This item was previously named '_diffrn_detector_axis.id'
                   which is now a deprecated name.  The old name is
                   provided as an alias but should not be used for new work.
    
    ;
        _item.name                  '_diffrn_detector_axis.detector_id'
        _item.category_id             diffrn_detector_axis
        _item.mandatory_code          yes
        _item_aliases.alias_name    '_diffrn_detector_axis.id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         save_
    
    
    ###########################
    # DIFFRN_DETECTOR_ELEMENT #
    ###########################
    
    
    save_DIFFRN_DETECTOR_ELEMENT
        _category.description
    ;
                  Data items in the DIFFRN_DETECTOR_ELEMENT category record
                  the details about spatial layout and other characteristics
                  of each element of a detector which may have multiple elements.
                  
                  In most cases, the more detailed information provided
                  in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS
                  are preferable to simply providing the centre.
    
    ;
        _category.id                   diffrn_detector_element
        _category.mandatory_code       no
         loop_
        _category_key.name             '_diffrn_detector_element.id'
                                       '_diffrn_detector_element.detector_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 - Detector d1 is composed of four CCD detector elements,
            each 200 mm by 200 mm, arranged in a square. in the pattern
                        
                       1     2
                          *
                       3     4
    
            Note that the beam centre is slightly displaced from each of the
            detector elements, just beyond the lower right corner of 1,
            the lower left corner of 2, the upper right corner of 3 and
            the upper left corner of 4.
    ;
    ;
            loop_
            _diffrn_detector_element.detector_id
            _diffrn_detector_element.id
            _diffrn_detector_element.center[1]
            _diffrn_detector_element.center[2]
            d1     d1_ccd_1  201.5 -1.5
            d1     d1_ccd_2  -1.8  -1.5
            d1     d1_ccd_3  201.6 201.4  
            d1     d1_ccd_4  -1.7  201.5
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
    
    
    save__diffrn_detector_element.center[1]
        _item_description.description
    ;             
                  The value of '_diffrn_detector_element.center[1]' is the X
                  component of the distortion-corrected beam-centre in mm from
                  the (0, 0) (lower left) corner of the detector element viewed
                  from the sample side.
                  
                  The X and Y axes are the laboratory coordinate system
                  coordinates defined in the AXIS category measured
                  when all positioning axes for the detector are at their zero
                  settings.  If the resulting X or Y axis is then orthogonal to the
                  detector, the Z axis is used instead of the orthogonal axis.
                  
    ;
        _item.name                  '_diffrn_detector_element.center[1]'
        _item.category_id             diffrn_detector_element
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
    
        save_
    
    
    save__diffrn_detector_element.center[2]
        _item_description.description
    ;             
                  The value of '_diffrn_detector_element.center[2]' is the Y
                  component of the distortion-corrected beam-centre in mm from
                  the (0, 0) (lower left) corner of the detector element viewed
                  from the sample side.
                  
                  The X and Y axes are the laboratory coordinate system
                  coordinates defined in the AXIS category measured
                  when all positioning axes for the detector are at their zero
                  settings.  If the resulting X or Y axis is then orthogonal to the
                  detector, the Z axis is used instead of the orthogonal axis.
    
    ;
        _item.name                  '_diffrn_detector_element.center[2]'
        _item.category_id             diffrn_detector_element
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
    
        save_
    
    
    save__diffrn_detector_element.id
        _item_description.description
    ;             
                  The value of '_diffrn_detector_element.id' must uniquely
                  identify each element of a detector.
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
               '_diffrn_detector_element.id'
               diffrn_detector_element
               yes
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_diffrn_data_frame.detector_element_id'
               '_diffrn_detector_element.id'
    
         save_
    
    
    save__diffrn_detector_element.detector_id
        _item_description.description
    ;             
                   This item is a pointer to '_diffrn_detector.id'
                   in the DIFFRN_DETECTOR category. 
    ;
        _item.name                  '_diffrn_detector_element.detector_id'
        _item.category_id             diffrn_detector_element
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    
    ########################
    ## DIFFRN_MEASUREMENT ##
    ########################
    
    
    save_DIFFRN_MEASUREMENT
        _category.description
    ;              Data items in the DIFFRN_MEASUREMENT category record details
                   about the device used to orient and/or position the crystal
                   during data measurement and the manner in which the
                   diffraction data were measured.
    ;
        _category.id                  diffrn_measurement
        _category.mandatory_code      no
         loop_
        _category_key.name          '_diffrn_measurement.device'
                                    '_diffrn_measurement.diffrn_id'
                                    '_diffrn_measurement.id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 - based on PDB entry 5HVP and laboratory records for the
                    structure corresponding to PDB entry 5HVP
    ;
    ;
        _diffrn_measurement.diffrn_id          'd1'
        _diffrn_measurement.device             '3-circle camera'
        _diffrn_measurement.device_type        'Supper model x'
        _diffrn_measurement.device_details     'none'
        _diffrn_measurement.method             'omega scan'
        _diffrn_measurement.details
        ; Need new example here
        ;
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991).
                    Acta Cryst. C47, 2276-2277].
    ;
    ;
        _diffrn_measurement.diffrn_id       's1'
        _diffrn_measurement.device_type     'Philips PW1100/20 diffractometer'
        _diffrn_measurement.method          'theta/2theta (\q/2\q)'
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__diffrn_measurement.device
        _item_description.description
    ;              The general class of goniometer or device used to support
                   and orient the specimen.
                   
                   If the value of '_diffrn_measurement.device' is not given,
                   it is implicitly equal to the value of
                   '_diffrn_measurement.diffrn_id'.
    
                   Either '_diffrn_measurement.device' or
                   '_diffrn_measurement.id' may be used to link to other
                   categories.  If the experimental setup admits multiple
                   devices, then '_diffrn_measurement.id' is used to provide
                   a unique link.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
                 '_diffrn_measurement.device'  diffrn_measurement      implicit
                 '_diffrn_measurement_axis.measurement_device' 
                                               diffrn_measurement_axis implicit
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_measurement_axis.measurement_device'  
                                             '_diffrn_measurement.device'
        _item_aliases.alias_name    '_diffrn_measurement_device'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          '3-circle camera'
                                     '4-circle camera'
                                     'kappa-geometry camera'
                                     'oscillation camera'
                                     'precession camera'
         save_
    
    
    save__diffrn_measurement.device_details
        _item_description.description
    ;              A description of special aspects of the device used to
                   measure the diffraction intensities.
    ;
        _item.name                  '_diffrn_measurement.device_details'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_device_details'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
        _item_examples.case
    ;                                 commercial goniometer modified locally to
                                      allow for 90\% \t arc
    ;
         save_
    
    
    save__diffrn_measurement.device_type
        _item_description.description
    ;              The make, model or name of the measurement device
                   (goniometer) used.
    ;
        _item.name                  '_diffrn_measurement.device_type'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_device_type'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          'Supper model q'
                                     'Huber model r'
                                     'Enraf-Nonius model s'
                                     'homemade'
         save_
    
    
    save__diffrn_measurement.diffrn_id
        _item_description.description
    ;              This data item is a pointer to '_diffrn.id' in the DIFFRN 
                   category.
    ;
        _item.name                  '_diffrn_measurement.diffrn_id'
        _item.mandatory_code          yes
         save_
    
    
    save__diffrn_measurement.details
        _item_description.description
    ;              A description of special aspects of the intensity
                   measurement.
    ;
        _item.name                  '_diffrn_measurement.details'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_details'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
        _item_examples.case
    ;                                 440 frames, 0.20 degrees, 150 sec, detector
                                      distance 12 cm, detector angle 22.5 degrees
    ;
         save_
    
    
    save__diffrn_measurement.id
        _item_description.description
    ;             
                   The value of '_diffrn_measurement.id' must uniquely identify
                   the set of mechanical characteristics of the device used to 
                   orient and/or position the sample used during collection 
                   of each diffraction data set.
    
                   If the value of '_diffrn_measurement.id' is not given, it is
                   implicitly equal to the value of 
                   '_diffrn_measurement.diffrn_id'.
    
                   Either '_diffrn_measurement.device' or
                   '_diffrn_measurement.id' may be used to link to other
                   categories.  If the experimental setup admits multiple
                   devices, then '_diffrn_measurement.id' is used to provide
                   a unique link.
    ;
         loop_
        _item.name                 
        _item.category_id
        _item.mandatory_code
                 '_diffrn_measurement.id'      diffrn_measurement      implicit
                 '_diffrn_measurement_axis.measurement_id'
                                               diffrn_measurement_axis implicit
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_measurement_axis.measurement_id'
                                             '_diffrn_measurement.id'
    
        _item_type.code               code
         save_
    
    
    save__diffrn_measurement.method
        _item_description.description
    ;              Method used to measure intensities.
    ;
        _item.name                  '_diffrn_measurement.method'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_method'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
        _item_examples.case
          'profile data from theta/2theta (\q/2\q) scans'
         save_
    
    
    save__diffrn_measurement.number_of_axes
        _item_description.description
    ;             
                   The value of '_diffrn_measurement.number_of_axes' gives the 
                   number of axes of the positioner for the goniometer or
                   other sample orientation or positioning device identified 
                   by '_diffrn_measurement.id'.
    
                   The description of the axes should be provided by entries in 
                   DIFFRN_MEASUREMENT_AXIS.
    ;
        _item.name                  '_diffrn_measurement.number_of_axes'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
         loop_
        _item_range.maximum
        _item_range.minimum           .   1
                                      1   1
        _item_type.code               int
         save_
    
    
    save__diffrn_measurement.specimen_support
        _item_description.description
    ;              The physical device used to support the crystal during data
                   collection.
    ;
        _item.name                  '_diffrn_measurement.specimen_support'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_specimen_support'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          'glass capillary'
                                     'quartz capillary'
                                     'fiber'
                                     'metal loop'
         save_
    
    
    ###########################
    # DIFFRN_MEASUREMENT_AXIS #
    ###########################
    
    
    save_DIFFRN_MEASUREMENT_AXIS
        _category.description
    ;
         Data items in the DIFFRN_MEASUREMENT_AXIS category associate
         axes with goniometers.
    ;
        _category.id                   diffrn_measurement_axis
        _category.mandatory_code       no
         loop_
        _category_key.name
                                  '_diffrn_measurement_axis.measurement_device'
                                    '_diffrn_measurement_axis.measurement_id'
                                    '_diffrn_measurement_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_measurement_axis.axis_id
        _item_description.description
    ;
                   This data item is a pointer to '_axis.id' in
                   the AXIS category.
    ;
        _item.name                  '_diffrn_measurement_axis.axis_id'
        _item.category_id             diffrn_measurement_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_measurement_axis.measurement_device
        _item_description.description
    ;
                   This data item is a pointer to '_diffrn_measurement.device'
                   in the DIFFRN_MEASUREMENT category.
    
    ;
        _item.name
          '_diffrn_measurement_axis.measurement_device'
        _item.category_id             diffrn_measurement_axis
        _item.mandatory_code          implicit
        _item_type.code               text
         save_
    
    
    save__diffrn_measurement_axis.measurement_id
        _item_description.description
    ;
                   This data item is a pointer to '_diffrn_measurement.id' in
                   the DIFFRN_MEASUREMENT category.
                  
                   This item was previously named '_diffrn_measurement_axis.id'
                   which is now a deprecated name.  The old name is
                   provided as an alias but should not be used for new work.
    
    ;
        _item.name                  '_diffrn_measurement_axis.measurement_id'
        _item.category_id             diffrn_measurement_axis
        _item_aliases.alias_name    '_diffrn_measurement_axis.id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0.00
        _item.mandatory_code          implicit
        _item_type.code               code
         save_
    
    
    ####################
    # DIFFRN_RADIATION #
    ####################
    
    
    save_DIFFRN_RADIATION
        _category.description
    ;              Data items in the DIFFRN_RADIATION category describe
                   the radiation used in measuring diffraction intensities,
                   its collimation and monochromatisation before the sample.
    
                   Post-sample treatment of the beam is described by data
                   items in the DIFFRN_DETECTOR category.
    
    ;
        _category.id                  diffrn_radiation
        _category.mandatory_code      no
        _category_key.name          '_diffrn_radiation.diffrn_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 - based on PDB entry 5HVP and laboratory records for the
                    structure corresponding to PDB entry 5HVP
    ;
    ;
        _diffrn_radiation.diffrn_id            'set1'
    
        _diffrn_radiation.collimation          '0.3 mm double pinhole'
        _diffrn_radiation.monochromator        'graphite'
        _diffrn_radiation.type                 'Cu K\a'
        _diffrn_radiation.wavelength_id         1
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991).
                    Acta Cryst. C47, 2276-2277].
    ;
    ;
        _diffrn_radiation.wavelength_id    1
        _diffrn_radiation.type             'Cu K\a'
        _diffrn_radiation.monochromator    'graphite'
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    save__diffrn_radiation.collimation
        _item_description.description
    ;              The collimation or focusing applied to the radiation.
    ;
        _item.name                  '_diffrn_radiation.collimation'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_collimation'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          '0.3 mm double-pinhole'
                                     '0.5 mm'
                                     'focusing mirrors'
         save_
    
    
    save__diffrn_radiation.diffrn_id
        _item_description.description
    ;              This data item is a pointer to '_diffrn.id' in the DIFFRN
                   category.
    ;
        _item.name                  '_diffrn_radiation.diffrn_id'
        _item.mandatory_code          yes
         save_
    
    
    
    save__diffrn_radiation.div_x_source
        _item_description.description
    ;              Beam crossfire in degrees parallel to the laboratory X axis
                   (see AXIS category).
                   
                   This is a characteristic of the xray beam as it illuminates
                   the sample (or specimen) after all monochromation and 
                   collimation.
                   
                   This is the esd of the directions of photons in the X-Z plane
                   around the mean source beam direction.
                   
                   Note that some synchrotrons specify this value in milliradians,
                   in which case a conversion would be needed.  To go from a
                   value in milliradians to a value in degrees, multiply by 0.180
                   and divide by π.
    
    ;
        _item.name                  '_diffrn_radiation.div_x_source'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_type.code               float
        _item_units.code              degrees
         save_
    
    
    save__diffrn_radiation.div_y_source
        _item_description.description
    ;              Beam crossfire in degrees parallel to the laboratory Y axis
                   (see AXIS category).
                   
                   This is a characteristic of the xray beam as it illuminates
                   the sample (or specimen) after all monochromation and 
                   collimation.
                   
                   This is the esd of the directions of photons in the Y-Z plane
                   around the mean source beam direction.
    
                   Note that some synchrotrons specify this value in milliradians,
                   in which case a conversion would be needed.  To go from a
                   value in milliradians to a value in degrees, multiply by 0.180
                   and divide by π.
    
    ;
        _item.name                  '_diffrn_radiation.div_y_source'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_type.code               float
        _item_units.code              degrees
        _item_default.value           0.0
         save_
    
    
    save__diffrn_radiation.div_x_y_source
        _item_description.description
    ;              Beam crossfire correlation degrees2 between the
                   crossfire laboratory X-axis component and the crossfire
                   laboratory Y-axis component (see AXIS category).
                   
                   This is a characteristic of the xray beam as it illuminates
                   the sample (or specimen) after all monochromation and 
                   collimation.
                   
                   This is the mean of the products of the deviations of the
                   direction of each photons in X-Z plane times the deviations
                   of the direction of the same photon in the Y-Z plane
                   around the mean source beam direction.  This will be zero
                   for uncorrelated crossfire.
                   
                   Note that some synchrotrons specify this value in 
                   milliradians2, in which case a conversion would be needed.  
                   To go from a value in milliradians2 to a value in
                   degrees2, multiply by 0.1802 and divide by π2.
    
    ;
        _item.name                  '_diffrn_radiation.div_x_y_source'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_type.code               float
        _item_units.code              degrees_squared
        _item_default.value           0.0
         save_
    
    save__diffrn_radiation.filter_edge
        _item_description.description
    ;              Absorption edge in Ångstroms of the radiation filter used.
    ;
        _item.name                  '_diffrn_radiation.filter_edge'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_filter_edge'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum           
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
        _item_units.code              angstroms
         save_
    
    save__diffrn_radiation.inhomogeneity
        _item_description.description
    ;              Half-width in millimetres of the incident beam in the
                   direction perpendicular to the diffraction plane.
    ;
        _item.name                  '_diffrn_radiation.inhomogeneity'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_inhomogeneity'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum           
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    save__diffrn_radiation.monochromator
        _item_description.description
    ;              The method used to obtain monochromatic radiation. If a
                   monochromator crystal is used the material and the
                   indices of the Bragg reflection are specified.
    ;
        _item.name                  '_diffrn_radiation.monochromator'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_monochromator'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          'Zr filter'
                                     'Ge 220'
                                     'none'
                                     'equatorial mounted graphite'
         save_
    
    save__diffrn_radiation.polarisn_norm
        _item_description.description
    ;              The angle in degrees, as viewed from the specimen, between the
                   perpendicular component of the polarisation and the diffraction
                   plane. See _diffrn_radiation_polarisn_ratio.
    ;
        _item.name                  '_diffrn_radiation.polarisn_norm'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_polarisn_norm'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum           
        _item_range.minimum           90.0  90.0
                                      90.0 -90.0
                                     -90.0 -90.0
        _item_type.code               float
        _item_units.code              degrees
         save_
    
    save__diffrn_radiation.polarisn_ratio
        _item_description.description
    ;              Polarisation ratio of the diffraction beam incident on the
                   crystal. It is the ratio of the perpendicularly polarised to
                   the parallel polarised component of the radiation. The
                   perpendicular component forms an angle of
                   '_diffrn_radiation.polarisn_norm' to the normal to the
                   diffraction plane of the sample (i.e. the plane containing
                   the incident and reflected beams).
    ;
        _item.name                  '_diffrn_radiation.polarisn_ratio'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_polarisn_ratio'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum           
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
         save_
    
    
    
    save__diffrn_radiation.polarizn_source_norm
        _item_description.description
    ;              The angle in degrees, as viewed from the specimen, between
                   the normal to the polarization plane and the laboratory Y
                   axis as defined in the AXIS category.
                   
                   Note that this is the angle of polarization of the source 
                   photons, either directly from a synchrotron beamline or
                   from a monchromater.
                   
                   This differs from the value of
                   '_diffrn_radiation.polarisn_norm'
                   in that '_diffrn_radiation.polarisn_norm' refers to
                   polarization relative to the diffraction plane rather than
                   to the laboratory axis system.
                   
                   In the case of an unpolarized beam, or a beam with true
                   circular polarization, in which no single plane of
                   polarization can be determined, the plane should be taken
                   as the X-Z plane, and the angle as 0.
                   
                   See '_diffrn_radiation.polarizn_source_ratio'.
    ;
        _item.name                  '_diffrn_radiation.polarizn_source_norm'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
         loop_
        _item_range.maximum           
        _item_range.minimum           90.0   90.0
                                      90.0  -90.0
                                     -90.0  -90.0
        _item_type.code               float
        _item_units.code              degrees
        _item_default.value           0.0
         save_
    
    
    save__diffrn_radiation.polarizn_source_ratio
        _item_description.description
    ;              (Ip-In)/(Ip+In), where Ip is the intensity (amplitude
                   squared) of the electric vector in the plane of
                   polarization and In is the intensity (amplitude squared)
                   of the electric vector in plane of the normal to the
                   plane of polarization.
                   
                   In the case of an unpolarized beam, or a beam with true
                   circular polarization, in which no single plane of
                   polarization can be determined, the plane is be taken
                   as the X-Z plane, and the normal is parallel to the Y-axis.
                   
                   Thus, if we had complete polarization in the plane of
                   polarization, the value of 
                   '_diffrn_radiation.polarizn_source_ratio' would
                   be 1, and an unpolarized beam would have a value of 0.
                   
                   If the X-axis has been chosen to lie in the plane of
                   polarization, this definition will agree with the definition
                   of "MONOCHROMATOR" in the Denzo glossary, and values of near
                   1 should be expected for a bending magnet source.  However,
                   if the X-axis were, for some reason to be, say,
                   perpendicular to the polarization plane (not a common
                   choice), then the Denzo value would be the negative of
                   '_diffrn_radiation.polarizn_source_ratio'.
                   
                   See http://www.hkl-xray.com for information on Denzo, and
                   Z. Otwinowski and W. Minor, "Processing of X-ray
                   Diffraction Data Collected in Oscillation Mode", Methods
                   in Enzymology, Volume 276: Macromolecular Crystallography,
                   part A, p.307-326, 1997,C.W. Carter, Jr. & R. M. Sweet,
                   Eds., Academic Press.
    
                   This differs both in the choice of ratio and choice of
                   orientation from '_diffrn_radiation.polarisn_ratio', which,
                   unlike '_diffrn_radiation.polarizn_source_ratio', is
                   unbounded.
    
    ;
        _item.name                  '_diffrn_radiation.polarizn_source_ratio'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
         loop_
        _item_range.maximum           
        _item_range.minimum           1.0    1.0
                                      1.0   -1.0
                                     -1.0   -1.0
        _item_type.code               float
         save_
    
    
    save__diffrn_radiation.probe
        _item_description.description
    ;              Name of the type of radiation used. It is strongly
                   encouraged that this field be specified so that the
                   probe radiation can be simply determined.
    ;
        _item.name                  '_diffrn_radiation.probe'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_probe'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               line
         loop_
        _item_enumeration.value      'x-ray'
                                     'neutron'
                                     'electron'
                                     'gamma'
         save_
    
    save__diffrn_radiation.type
        _item_description.description
    ;              The nature of the radiation. This is typically a description
                   of the X-ray wavelength in Siegbahn notation.
    ;
        _item.name                  '_diffrn_radiation.type'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_type'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               line
         loop_
        _item_examples.case          'CuK\a'
                                     'Cu K\a~1~'
                                     'Cu K-L~2,3~' 
                                     'white-beam'
    
         save_
    
    save__diffrn_radiation.xray_symbol
        _item_description.description
    ;              The IUPAC symbol for the X-ray wavelength for probe
                   radiation.
    ;
        _item.name                  '_diffrn_radiation.xray_symbol'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_xray_symbol'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               line
         loop_
        _item_enumeration.value
        _item_enumeration.detail     'K-L~3~'
                                     'K\a~1~ in older Siegbahn notation'
                                     'K-L~2~'
                                     'K\a~2~ in older Siegbahn notation'
                                     'K-M~3~'
                                     'K\b~1~ in older Siegbahn notation'
                                     'K-L~2,3~'
                                     'use where K-L~3~ and K-L~2~ are not resolved'
         save_
    
    save__diffrn_radiation.wavelength_id
        _item_description.description
    ;              This data item is a pointer to 
                   '_diffrn_radiation_wavelength.id' in the
                   DIFFRN_RADIATION_WAVELENGTH category.
    ;
        _item.name                  '_diffrn_radiation.wavelength_id'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    
    ################
    # DIFFRN_REFLN #
    ################
    
    
    save_DIFFRN_REFLN
        _category.description 
    ;
         This category redefinition has been added to extend the key of 
         the standard DIFFRN_REFLN category.
    ;
        _category.id                   diffrn_refln
        _category.mandatory_code       no
        _category_key.name             '_diffrn_refln.frame_id'
         loop_
        _category_group.id             'inclusive_group'
                                       'diffrn_group'
         save_
    
    
    save__diffrn_refln.frame_id
        _item_description.description
    ;             
                   This item is a pointer to '_diffrn_data_frame.id'
                   in the DIFFRN_DATA_FRAME category. 
    ;
        _item.name                  '_diffrn_refln.frame_id'
        _item.category_id             diffrn_refln
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    ###############
    # DIFFRN_SCAN #
    ###############
    
    save_DIFFRN_SCAN
        _category.description 
    ;
         Data items in the DIFFRN_SCAN category describe the parameters of one
         or more scans, relating axis positions to frames.
    
    ;
        _category.id                   diffrn_scan
        _category.mandatory_code       no
        _category_key.name            '_diffrn_scan.id'
         loop_
        _category_group.id            'inclusive_group'
                                      'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 - derived from a suggestion by R. M. Sweet.
    
       The vector of each axis is not given here, because it is provided in
       the AXIS category.  By making '_diffrn_scan_axis.scan_id' and
       '_diffrn_scan_axis.axis_id' keys of the DIFFRN_SCAN_AXIS category,
       an arbitrary number of scanning and fixed axes can be specified for a 
       scan.  We have specified three rotation axes and one translation axis 
       at non-zero values, with one axis stepping.  There is no reason why 
       more axes could not have been specified to step.   We have specified
       range information, but note that it is redundant from the  number of 
       frames and the increment, so we could drop the data item
       '_diffrn_scan_axis.angle_range'.
       
       We have specified both the sweep data and the data for a single frame.
    
       Note that the information on how the axes are stepped is given twice,
       once in terms of the overall averages in the value of
       '_diffrn_scan.integration_time' and the values for DIFFRN_SCAN_AXIS,
       and precisely for the given frame in the value for 
       '_diffrn_scan_frame.integration_time' and the values for
       DIFFRN_SCAN_FRAME_AXIS.  If dose-related adjustements are made to
       scan times and non-linear stepping is done, these values may differ.
       Therefore, in interpreting the data for a particular frame it is
       important to use the frame-specific data.
    
    ;
    ;
          _diffrn_scan.id                   1
          _diffrn_scan.date_start         '2001-11-18T03:26:42'
          _diffrn_scan.date_end           '2001-11-18T03:36:45'
          _diffrn_scan.integration_time    3.0
          _diffrn_scan.frame_id_start      mad_L2_000
          _diffrn_scan.frame_id_end        mad_L2_200
          _diffrn_scan.frames              201
    
           loop_
          _diffrn_scan_axis.scan_id
          _diffrn_scan_axis.axis_id
          _diffrn_scan_axis.angle_start
          _diffrn_scan_axis.angle_range
          _diffrn_scan_axis.angle_increment
          _diffrn_scan_axis.displacement_start
          _diffrn_scan_axis.displacement_range
          _diffrn_scan_axis.displacement_increment
    
           1 omega 200.0 20.0 0.1 . . . 
           1 kappa -40.0  0.0 0.0 . . . 
           1 phi   127.5  0.0 0.0 . . . 
           1 tranz  . . .   2.3 0.0 0.0 
    
          _diffrn_scan_frame.scan_id                   1
          _diffrn_scan_frame.date               '2001-11-18T03:27:33'
          _diffrn_scan_frame.integration_time    3.0
          _diffrn_scan_frame.frame_id            mad_L2_018
          _diffrn_scan_frame.frame_number        18
    
          loop_
          _diffrn_scan_frame_axis.frame_id
          _diffrn_scan_frame_axis.axis_id
          _diffrn_scan_frame_axis.angle
          _diffrn_scan_frame_axis.angle_increment
          _diffrn_scan_frame_axis.displacement
          _diffrn_scan_frame_axis.displacement_increment
    
           mad_L2_018 omega 201.8  0.1 . .
           mad_L2_018 kappa -40.0  0.0 . .
           mad_L2_018 phi   127.5  0.0 . .
           mad_L2_018 tranz  .     .  2.3 0.0
    
    ;
    
    ;
        Example 2 - a more extensive example, R. M. Sweet, P. Ellis, H. Bernstein.
        
       We place a detector 240 mm along the Z axis from the goniometer.
       This presents us with a choice -- either we define the axes of
       the detector at the origin, and then put a Z setting of -240 in
       for the actual use, or we define the axes with the necessary Z-offset.
       In this case we use the setting, and leave the offset as zero.
       We call this axis DETECTOR_Z.
       
       The axis for positioning the detector in the Y-direction depends
       on the detector Z-axis.  We call this axis, DETECTOR_Y.
       
       The axis for positioning the detector in the X-direction depends
       on the detector Y-axis (and therefore on the detector Z-axis).
       We call this axis DETECTOR_X.
       
       This detector may be rotated around the Y-axis.  This rotation axis
       depends on the three translation axes.  We call it DETECTOR_PITCH.
       
       We define a coordinate system on the face of the detector in terms of
       2300 0.150 mm pixels in each direction.  The ELEMENT_X axis is used to
       index the first array index of the data array and the ELEMENT_Y
       axis is used to index the second array index.  Because the pixels
       are 0.150mm x 0.150mm, the centre of the first pixel is at (0.075, 
       0.075) in this coordinate system.
    
    ;
    ;
         ###CBF: VERSION 1.1 
    
         data_image_1 
    
    
         # category DIFFRN 
    
         _diffrn.id P6MB 
         _diffrn.crystal_id P6MB_CRYSTAL7 
    
    
         # category DIFFRN_SOURCE 
    
         loop_ 
         _diffrn_source.diffrn_id 
         _diffrn_source.source 
         _diffrn_source.type 
          P6MB synchrotron 'SSRL beamline 9-1' 
    
    
         # category DIFFRN_RADIATION 
    
              loop_ 
         _diffrn_radiation.diffrn_id 
         _diffrn_radiation.wavelength_id 
         _diffrn_radiation.monochromator 
         _diffrn_radiation.polarizn_source_ratio 
         _diffrn_radiation.polarizn_source_norm 
         _diffrn_radiation.div_x_source 
         _diffrn_radiation.div_y_source 
         _diffrn_radiation.div_x_y_source 
          P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08
         0.01 0.00 
    
    
         # category DIFFRN_RADIATION_WAVELENGTH 
    
         loop_ 
         _diffrn_radiation_wavelength.id 
         _diffrn_radiation_wavelength.wavelength 
         _diffrn_radiation_wavelength.wt 
          WAVELENGTH1 0.98 1.0 
    
    
         # category DIFFRN_DETECTOR 
    
         loop_ 
         _diffrn_detector.diffrn_id 
         _diffrn_detector.id 
         _diffrn_detector.type 
         _diffrn_detector.number_of_axes 
          P6MB MAR345-SN26 'MAR 345' 4 
    
    
         # category DIFFRN_DETECTOR_AXIS 
    
         loop_ 
         _diffrn_detector_axis.detector_id 
         _diffrn_detector_axis.axis_id 
          MAR345-SN26 DETECTOR_X 
          MAR345-SN26 DETECTOR_Y 
          MAR345-SN26 DETECTOR_Z 
          MAR345-SN26 DETECTOR_PITCH 
    
    
         # category DIFFRN_DETECTOR_ELEMENT 
    
         loop_ 
         _diffrn_detector_element.id 
         _diffrn_detector_element.detector_id 
          ELEMENT1 MAR345-SN26 
    
    
         # category DIFFRN_DATA_FRAME 
    
         loop_ 
         _diffrn_data_frame.id 
         _diffrn_data_frame.detector_element_id 
         _diffrn_data_frame.array_id 
         _diffrn_data_frame.binary_id 
          FRAME1 ELEMENT1 ARRAY1 1 
    
    
         # category DIFFRN_MEASUREMENT 
    
         loop_ 
         _diffrn_measurement.diffrn_id 
         _diffrn_measurement.id 
         _diffrn_measurement.number_of_axes 
         _diffrn_measurement.method 
          P6MB GONIOMETER 3 rotation 
    
    
         # category DIFFRN_MEASUREMENT_AXIS 
    
         loop_ 
         _diffrn_measurement_axis.measurement_id 
         _diffrn_measurement_axis.axis_id 
          GONIOMETER GONIOMETER_PHI 
          GONIOMETER GONIOMETER_KAPPA 
          GONIOMETER GONIOMETER_OMEGA 
    
    
         # category DIFFRN_SCAN 
    
         loop_ 
         _diffrn_scan.id 
         _diffrn_scan.frame_id_start 
         _diffrn_scan.frame_id_end 
         _diffrn_scan.frames 
          SCAN1 FRAME1 FRAME1 1 
    
    
         # category DIFFRN_SCAN_AXIS 
    
         loop_ 
         _diffrn_scan_axis.scan_id 
         _diffrn_scan_axis.axis_id 
         _diffrn_scan_axis.angle_start 
         _diffrn_scan_axis.angle_range 
         _diffrn_scan_axis.angle_increment 
         _diffrn_scan_axis.displacement_start 
         _diffrn_scan_axis.displacement_range 
         _diffrn_scan_axis.displacement_increment 
          SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 
          SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 
          SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 
          SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 
          SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 
          SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 
          SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 
    
    
         # category DIFFRN_SCAN_FRAME 
    
         loop_ 
         _diffrn_scan_frame.frame_id 
         _diffrn_scan_frame.frame_number 
         _diffrn_scan_frame.integration_time 
         _diffrn_scan_frame.scan_id 
         _diffrn_scan_frame.date 
          FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 
    
    
         # category DIFFRN_SCAN_FRAME_AXIS 
    
         loop_ 
         _diffrn_scan_frame_axis.frame_id 
         _diffrn_scan_frame_axis.axis_id 
         _diffrn_scan_frame_axis.angle 
         _diffrn_scan_frame_axis.displacement 
          FRAME1 GONIOMETER_OMEGA 12.0 0.0 
          FRAME1 GONIOMETER_KAPPA 23.3 0.0 
          FRAME1 GONIOMETER_PHI -165.8 0.0 
          FRAME1 DETECTOR_Z 0.0 -240.0 
          FRAME1 DETECTOR_Y 0.0 0.6 
          FRAME1 DETECTOR_X 0.0 -0.5 
          FRAME1 DETECTOR_PITCH 0.0 0.0 
    
    
         # category AXIS 
    
         loop_ 
         _axis.id 
         _axis.type 
         _axis.equipment 
         _axis.depends_on 
         _axis.vector[1] _axis.vector[2] _axis.vector[3] 
         _axis.offset[1] _axis.offset[2] _axis.offset[3] 
          GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . 
          GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279
          0 0.76604 . . . 
          GONIOMETER_PHI   rotation goniometer GONIOMETER_KAPPA 1 0 0
         . . . 
          SOURCE           general source . 0 0 1 . . . 
          GRAVITY          general gravity . 0 -1 0 . . . 
          DETECTOR_Z       translation detector . 0 0 1 0 0 0
          DETECTOR_Y       translation detector DETECTOR_Z 0 1 0 0 0 0 
          DETECTOR_X       translation detector DETECTOR_Y 1 0 0 0 0 0 
          DETECTOR_PITCH   rotation    detector DETECTOR_X 0 1 0 0 0 0 
          ELEMENT_X        translation detector DETECTOR_PITCH
         1 0 0 172.43 -172.43 0
          ELEMENT_Y        translation detector ELEMENT_X
         0 1 0 0 0 0 
    
         # category ARRAY_STRUCTURE_LIST 
    
         loop_ 
         _array_structure_list.array_id 
         _array_structure_list.index 
         _array_structure_list.dimension 
         _array_structure_list.precedence 
         _array_structure_list.direction 
         _array_structure_list.axis_set_id 
          ARRAY1 1 2300 1 increasing ELEMENT_X 
          ARRAY1 2 2300 2 increasing ELEMENT_Y 
    
    
         # category ARRAY_STRUCTURE_LIST_AXIS 
    
         loop_
         _array_structure_list_axis.axis_set_id
         _array_structure_list_axis.axis_id
         _array_structure_list_axis.displacement
         _array_structure_list_axis.displacement_increment
          ELEMENT_X ELEMENT_X 0.075 0.150
          ELEMENT_Y ELEMENT_Y 0.075 0.150
    
         # category ARRAY_ELEMENT_SIZE 
    
         loop_ 
         _array_element_size.array_id 
         _array_element_size.index 
         _array_element_size.size 
          ARRAY1 1 150e-6 
          ARRAY1 2 150e-6 
    
    
         # category ARRAY_INTENSITIES 
    
         loop_ 
         _array_intensities.array_id 
         _array_intensities.binary_id 
         _array_intensities.linearity 
         _array_intensities.gain 
         _array_intensities.gain_esd 
         _array_intensities.overload
         _array_intensities.undefined_value 
          ARRAY1 1 linear 1.15 0.2 240000 0 
    
    
          # category ARRAY_STRUCTURE 
    
          loop_ 
          _array_structure.id 
          _array_structure.encoding_type 
          _array_structure.compression_type 
          _array_structure.byte_order 
          ARRAY1 "signed 32-bit integer" packed little_endian 
    
    
         # category ARRAY_DATA         
    
         loop_ 
         _array_data.array_id 
         _array_data.binary_id 
         _array_data.data 
          ARRAY1 1 
         ; 
         --CIF-BINARY-FORMAT-SECTION-- 
         Content-Type: application/octet-stream; 
             conversions="x-CBF_PACKED" 
         Content-Transfer-Encoding: BASE64 
         X-Binary-Size: 3801324 
         X-Binary-ID: 1 
         X-Binary-Element-Type: "signed 32-bit integer" 
         Content-MD5: 07lZFvF+aOcW85IN7usl8A== 
    
         AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg 
         ... 
         8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE 
    
         --CIF-BINARY-FORMAT-SECTION---- 
         ; 
    ;
    
    ;
        Example 3 - Example 2 revised for a spiral scan, R. M. Sweet, 
        P. Ellis, H. Bernstein.
        
       We place a detector 240 mm along the Z axis from the goniometer,
       as in Example 2, above, but in this example, the image plate is
       scanned in a spiral pattern outside edge in.
       
       The axis for positioning the detector in the Y-direction depends
       on the detector Z-axis.  We call this axis, DETECTOR_Y.
       
       The axis for positioning the detector in the X-direction depends
       on the detector Y-axis (and therefore on the detector Z-axis).
       We call this axis DETECTOR_X.
       
       This detector may be rotated around the Y-axis.  This rotation axis
       depends on the three translation axes.  We call it DETECTOR_PITCH.
    
       We define a coordinate system on the face of the detector in
       terms of a coupled rotation axis and radial scan axis to form 
       a spiral scan.  Let us call rotation axis ELEMENT_ROT, and the
       radial axis ELEMENT_RAD.   We assume 150 um radial pitch and 75 um 
       'constant velocity' angular pitch. 
    
       We index first on the rotation axis and make the radial axis
       dependent on 
       it. 
    
       The two axes are coupled to form an axis set ELEMENT_SPIRAL. 
    
    ;
    ;
         ###CBF: VERSION 1.1 
    
         data_image_1 
    
    
         # category DIFFRN 
    
         _diffrn.id P6MB 
         _diffrn.crystal_id P6MB_CRYSTAL7 
    
    
         # category DIFFRN_SOURCE 
    
         loop_ 
         _diffrn_source.diffrn_id 
         _diffrn_source.source 
         _diffrn_source.type 
          P6MB synchrotron 'SSRL beamline 9-1' 
    
    
         # category DIFFRN_RADIATION 
    
              loop_ 
         _diffrn_radiation.diffrn_id 
         _diffrn_radiation.wavelength_id 
         _diffrn_radiation.monochromator 
         _diffrn_radiation.polarizn_source_ratio 
         _diffrn_radiation.polarizn_source_norm 
         _diffrn_radiation.div_x_source 
         _diffrn_radiation.div_y_source 
         _diffrn_radiation.div_x_y_source 
          P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08
         0.01 0.00 
    
    
         # category DIFFRN_RADIATION_WAVELENGTH 
    
         loop_ 
         _diffrn_radiation_wavelength.id 
         _diffrn_radiation_wavelength.wavelength 
         _diffrn_radiation_wavelength.wt 
          WAVELENGTH1 0.98 1.0 
    
    
         # category DIFFRN_DETECTOR 
    
         loop_ 
         _diffrn_detector.diffrn_id 
         _diffrn_detector.id 
         _diffrn_detector.type 
         _diffrn_detector.number_of_axes 
          P6MB MAR345-SN26 'MAR 345' 4 
    
    
         # category DIFFRN_DETECTOR_AXIS 
    
         loop_ 
         _diffrn_detector_axis.detector_id 
         _diffrn_detector_axis.axis_id 
          MAR345-SN26 DETECTOR_X 
          MAR345-SN26 DETECTOR_Y 
          MAR345-SN26 DETECTOR_Z 
          MAR345-SN26 DETECTOR_PITCH 
    
    
         # category DIFFRN_DETECTOR_ELEMENT 
    
         loop_ 
         _diffrn_detector_element.id 
         _diffrn_detector_element.detector_id 
          ELEMENT1 MAR345-SN26 
    
    
         # category DIFFRN_DATA_FRAME 
    
         loop_ 
         _diffrn_data_frame.id 
         _diffrn_data_frame.detector_element_id 
         _diffrn_data_frame.array_id 
         _diffrn_data_frame.binary_id 
          FRAME1 ELEMENT1 ARRAY1 1 
    
    
         # category DIFFRN_MEASUREMENT 
    
         loop_ 
         _diffrn_measurement.diffrn_id 
         _diffrn_measurement.id 
         _diffrn_measurement.number_of_axes 
         _diffrn_measurement.method 
          P6MB GONIOMETER 3 rotation 
    
    
         # category DIFFRN_MEASUREMENT_AXIS 
    
         loop_ 
         _diffrn_measurement_axis.measurement_id 
         _diffrn_measurement_axis.axis_id 
          GONIOMETER GONIOMETER_PHI 
          GONIOMETER GONIOMETER_KAPPA 
          GONIOMETER GONIOMETER_OMEGA 
    
    
         # category DIFFRN_SCAN 
    
         loop_ 
         _diffrn_scan.id 
         _diffrn_scan.frame_id_start 
         _diffrn_scan.frame_id_end 
         _diffrn_scan.frames 
          SCAN1 FRAME1 FRAME1 1 
    
    
         # category DIFFRN_SCAN_AXIS 
    
         loop_ 
         _diffrn_scan_axis.scan_id 
         _diffrn_scan_axis.axis_id 
         _diffrn_scan_axis.angle_start 
         _diffrn_scan_axis.angle_range 
         _diffrn_scan_axis.angle_increment 
         _diffrn_scan_axis.displacement_start 
         _diffrn_scan_axis.displacement_range 
         _diffrn_scan_axis.displacement_increment 
          SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 
          SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 
          SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 
          SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 
          SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 
          SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 
          SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 
    
    
         # category DIFFRN_SCAN_FRAME 
    
         loop_ 
         _diffrn_scan_frame.frame_id 
         _diffrn_scan_frame.frame_number 
         _diffrn_scan_frame.integration_time 
         _diffrn_scan_frame.scan_id 
         _diffrn_scan_frame.date 
          FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 
    
    
         # category DIFFRN_SCAN_FRAME_AXIS 
    
         loop_ 
         _diffrn_scan_frame_axis.frame_id 
         _diffrn_scan_frame_axis.axis_id 
         _diffrn_scan_frame_axis.angle 
         _diffrn_scan_frame_axis.displacement 
          FRAME1 GONIOMETER_OMEGA 12.0 0.0 
          FRAME1 GONIOMETER_KAPPA 23.3 0.0 
          FRAME1 GONIOMETER_PHI -165.8 0.0 
          FRAME1 DETECTOR_Z 0.0 -240.0 
          FRAME1 DETECTOR_Y 0.0 0.6 
          FRAME1 DETECTOR_X 0.0 -0.5 
          FRAME1 DETECTOR_PITCH 0.0 0.0 
    
    
         # category AXIS 
    
         loop_ 
         _axis.id 
         _axis.type 
         _axis.equipment 
         _axis.depends_on 
         _axis.vector[1] _axis.vector[2] _axis.vector[3] 
         _axis.offset[1] _axis.offset[2] _axis.offset[3] 
          GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . 
          GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279
          0 0.76604 . . . 
          GONIOMETER_PHI   rotation goniometer GONIOMETER_KAPPA 1 0 0
         . . . 
          SOURCE           general source . 0 0 1 . . . 
          GRAVITY          general gravity . 0 -1 0 . . . 
          DETECTOR_Z       translation detector . 0 0 1 0 0 0
          DETECTOR_Y       translation detector DETECTOR_Z 0 1 0 0 0 0 
          DETECTOR_X       translation detector DETECTOR_Y 1 0 0 0 0 0 
          DETECTOR_PITCH   rotation    detector DETECTOR_X 0 1 0 0 0 0 
          ELEMENT_ROT      translation detector DETECTOR_PITCH 0 0 1 0 0 0
          ELEMENT_RAD      translation detector ELEMENT_ROT 0 1 0 0 0 0 
    
         # category ARRAY_STRUCTURE_LIST 
    
         loop_ 
         _array_structure_list.array_id 
         _array_structure_list.index 
         _array_structure_list.dimension 
         _array_structure_list.precedence 
         _array_structure_list.direction 
         _array_structure_list.axis_set_id 
          ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL
    
    
         # category ARRAY_STRUCTURE_LIST_AXIS 
    
         loop_
         _array_structure_list_axis.axis_set_id
         _array_structure_list_axis.axis_id
         _array_structure_list_axis.angle
         _array_structure_list_axis.displacement
         _array_structure_list_axis.angular_pitch
         _array_structure_list_axis.radial_pitch
          ELEMENT_SPIRAL ELEMENT_ROT 0    .  0.075   .
          ELEMENT_SPIRAL ELEMENT_RAD . 172.5  .    -0.150
    
         # category ARRAY_ELEMENT_SIZE 
         # the actual pixels are 0.075 by 0.150 mm
         # We give the coarser dimension here.
    
         loop_ 
         _array_element_size.array_id 
         _array_element_size.index 
         _array_element_size.size 
          ARRAY1 1 150e-6 
    
    
         # category ARRAY_INTENSITIES 
    
         loop_ 
         _array_intensities.array_id 
         _array_intensities.binary_id 
         _array_intensities.linearity 
         _array_intensities.gain 
         _array_intensities.gain_esd 
         _array_intensities.overload
         _array_intensities.undefined_value 
          ARRAY1 1 linear 1.15 0.2 240000 0 
    
    
          # category ARRAY_STRUCTURE 
    
          loop_ 
          _array_structure.id 
          _array_structure.encoding_type 
          _array_structure.compression_type 
          _array_structure.byte_order 
          ARRAY1 "signed 32-bit integer" packed little_endian 
    
    
         # category ARRAY_DATA         
    
         loop_ 
         _array_data.array_id 
         _array_data.binary_id 
         _array_data.data 
          ARRAY1 1 
         ; 
         --CIF-BINARY-FORMAT-SECTION-- 
         Content-Type: application/octet-stream; 
             conversions="x-CBF_PACKED" 
         Content-Transfer-Encoding: BASE64 
         X-Binary-Size: 3801324 
         X-Binary-ID: 1 
         X-Binary-Element-Type: "signed 32-bit integer" 
         Content-MD5: 07lZFvF+aOcW85IN7usl8A== 
    
         AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg 
         ... 
         8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE 
    
         --CIF-BINARY-FORMAT-SECTION---- 
         ; 
    ;
    
    
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
           save_
    
    
    save__diffrn_scan.id
        _item_description.description
    ;             The value of '_diffrn_scan.id' uniquely identifies each
                  scan.  The identifier is used to tie together all the 
                  information about the scan.
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
           '_diffrn_scan.id'                 diffrn_scan             yes
           '_diffrn_scan_axis.scan_id'       diffrn_scan_axis        yes
           '_diffrn_scan_frame.scan_id'      diffrn_scan_frame       yes
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
           '_diffrn_scan_axis.scan_id'          '_diffrn_scan.id'
           '_diffrn_scan_frame.scan_id'         '_diffrn_scan.id'
         save_
    
    
    save__diffrn_scan.date_end
        _item_description.description
    ;
                   The date and time of the end of the scan.  Note that this
                   may be an estimate generated during the scan, before the
                   precise time of the end of the scan is known.
    ;
        _item.name                 '_diffrn_scan.date_end'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no
        _item_type.code            yyyy-mm-dd
         save_
    
    
    save__diffrn_scan.date_start
        _item_description.description
    ;
                   The date and time of the start of the scan.
    ;
        _item.name                 '_diffrn_scan.date_start'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no
        _item_type.code            yyyy-mm-dd
         save_
    
    
    save__diffrn_scan.integration_time
        _item_description.description
    ;
                   Approximate average time in seconds to integrate each 
                   step of the scan.  The precise time for integration
                   of each particular step must be provided in
                   '_diffrn_scan_frame.integration_time', even
                   if all steps have the same integration time.
    ;
        _item.name                 '_diffrn_scan.integration_time'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no
        _item_type.code            float
        _item_units.code           'seconds'
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0.0
         save_
    
    
    save__diffrn_scan.frame_id_start
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   first frame in the scan.
    
                   This item is a pointer to '_diffrn_data_frame.id' in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name                 '_diffrn_scan.frame_id_start'
        _item.category_id          diffrn_scan
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan.frame_id_end
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   last frame in the scan.
    
                   This item is a pointer to '_diffrn_data_frame.id' in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name                 '_diffrn_scan.frame_id_end'
        _item.category_id          diffrn_scan
        _item.mandatory_code       yes 
        _item_type.code            code
         save_
    
    
    save__diffrn_scan.frames
        _item_description.description
    ;
                   The value of this data item is the number of frames in
                   the scan.
    
    ;
        _item.name                 '_diffrn_scan.frames'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no 
        _item_type.code            int
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   1
                                1   1
         save_
    
    
    ####################
    # DIFFRN_SCAN_AXIS #
    ####################
    
    save_DIFFRN_SCAN_AXIS
        _category.description 
    ;
         Data items in the DIFFRN_SCAN_AXIS category describe the settings of
         axes for particular scans.  Unspecified axes are assumed to be at
         their zero points.
    
    ;
        _category.id                   diffrn_scan_axis
        _category.mandatory_code       no
         loop_
        _category_key.name            
                                      '_diffrn_scan_axis.scan_id'
                                      '_diffrn_scan_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_scan_axis.scan_id
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   scan for which axis settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   '_diffrn_scan.id'.
    
                   This item is a pointer to '_diffrn_scan.id' in the
                   DIFFRN_SCAN category.
    ;
        _item.name                 '_diffrn_scan_axis.scan_id'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_axis.axis_id
        _item_description.description
    ;
                   The value of this data item is the identifier of one of
                   the axes for the scan for which settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   '_diffrn_scan.id'.
    
                   This item is a pointer to '_axis.id' in the
                   AXIS category.
    ;
        _item.name                 '_diffrn_scan_axis.axis_id'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_axis.angle_start
        _item_description.description
    ;
                   The starting position for the specified axis in degrees.
    ;
        _item.name                 '_diffrn_scan_axis.angle_start'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.angle_range
        _item_description.description
    ;
                   The range from the starting position for the specified axis 
                   in degrees.
    ;
        _item.name                 '_diffrn_scan_axis.angle_range'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.angle_increment
        _item_description.description
    ;
                   The increment for each step for the specified axis
                   in degrees.  In general, this will agree with
                   '_diffrn_scan_frame_axis.angle_increment'. The 
                   sum of the values of '_diffrn_scan_frame_axis.angle' and
                   '_diffrn_scan_frame_axis.angle_increment' is the
                   angular setting of the axis at the end of the integration
                   time for a given frame.  If the individual frame values
                   vary, then the value of 
                   '_diffrn_scan_axis.angle_increment' will be 
                   representative
                   of the ensemble of values of
                   '_diffrn_scan_frame_axis.angle_increment' (e.g.
                   the mean).
    
    ;
        _item.name                 '_diffrn_scan_axis.angle_increment'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.angle_rstrt_incr
        _item_description.description
    ;
                   The increment after each step for the specified axis
                   in degrees.  In general, this will agree with
                   '_diffrn_scan_frame_axis.angle_rstrt_incr'.  The
                   sum of the values of '_diffrn_scan_frame_axis.angle' 
                   and  '_diffrn_scan_frame_axis.angle_increment' 
                   and  '_diffrn_scan_frame_axis.angle_rstrt_incr' is the
                   angular setting of the axis at the start of the integration
                   time for the next frame relative to a given frame, and 
                   should equal '_diffrn_scan_frame_axis.angle' for that 
                   next frame.   If the individual frame values
                   vary, then the value of 
                   '_diffrn_scan_axis.angle_rstrt_incr' will be 
                   representative
                   of the ensemble of values of
                   '_diffrn_scan_frame_axis.angle_rstrt_incr' (e.g.
                   the mean).
    ;
        _item.name                 '_diffrn_scan_axis.angle_rstrt_incr'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.displacement_start
        _item_description.description
    ;
                   The starting position for the specified axis in millimetres.
    ;
        _item.name                 '_diffrn_scan_axis.displacement_start'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_axis.displacement_range
        _item_description.description
    ;
                   The range from the starting position for the specified axis 
                   in millimetres.
    ;
        _item.name                 '_diffrn_scan_axis.displacement_range'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_axis.displacement_increment
        _item_description.description
    ;
                   The increment for each step for the specified axis
                   in millimetres.  In general, this will agree with
                   '_diffrn_scan_frame_axis.displacement_increment'.
                   The sum of the values of 
                   '_diffrn_scan_frame_axis.displacement' and
                   '_diffrn_scan_frame_axis.displacement_increment' is the
                   angular setting of the axis at the end of the integration
                   time for a given frame.  If the individual frame values
                   vary, then the value of 
                   '_diffrn_scan_axis.displacement_increment' will be 
                   representative
                   of the ensemble of values of
                   '_diffrn_scan_frame_axis.displacement_increment' (e.g.
                   the mean).
    ;
        _item.name                 '_diffrn_scan_axis.displacement_increment'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_axis.displacement_rstrt_incr
        _item_description.description
    ;
                   The increment for each step for the specified axis
                   in millimetres.  In general, this will agree with
                   '_diffrn_scan_frame_axis.displacement_rstrt_incr'.
                   The sum of the values of 
                   '_diffrn_scan_frame_axis.displacement' and
                   '_diffrn_scan_frame_axis.displacement_increment' and
                   '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the
                   angular setting of the axis at the start of the integration
                   time for the next frame relative to a given frame, and 
                   should equal '_diffrn_scan_frame_axis.displacement' 
                   for that next frame.  If the individual frame values
                   vary, then the value of 
                   '_diffrn_scan_axis.displacement_rstrt_incr' will be 
                   representative
                   of the ensemble of values of
                   '_diffrn_scan_frame_axis.displacement_rstrt_incr' (e.g.
                   the mean).
    ;
        _item.name                 '_diffrn_scan_axis.displacement_rstrt_incr'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    #####################
    # DIFFRN_SCAN_FRAME #
    #####################
    
    save_DIFFRN_SCAN_FRAME
        _category.description 
    ;
                Data items in the DIFFRN_SCAN_FRAME category describe
                the relationship of particular frames to scans.
    
    ;
        _category.id                   diffrn_scan_frame
        _category.mandatory_code       no
         loop_
        _category_key.name     
                                      '_diffrn_scan_frame.scan_id'
                                      '_diffrn_scan_frame.frame_id'
         loop_
        _category_group.id            'inclusive_group'
                                      'diffrn_group'
         save_
    
    
    save__diffrn_scan_frame.date
        _item_description.description
    ;
                   The date and time of the start of the frame being scanned.
    ;
        _item.name                 '_diffrn_scan_frame.date'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       no
        _item_type.code            yyyy-mm-dd
         save_
    
    
    save__diffrn_scan_frame.frame_id
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   frame being examined.
    
                   This item is a pointer to '_diffrn_data_frame.id' in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name                 '_diffrn_scan_frame.frame_id'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_frame.frame_number
        _item_description.description
    ;
                   The value of this data item is the number of the frame
                   within the scan, starting with 1.  It is not necessarily
                   the same as the value of '_diffrn_scan_frame.frame_id',
                   but may be.
    
    ;
        _item.name                 '_diffrn_scan_frame.frame_number'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       no 
        _item_type.code            int
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0
                                0   0
         save_
    
    
    save__diffrn_scan_frame.integration_time
        _item_description.description
    ;
                   The time in seconds to integrate this step of the scan.
                   This should be the precise time of integration of each
                   particular frame.  The value of this data item should
                   be given explicitly for each frame and not inferred
                   from the value of '_diffrn_scan.integration_time'.
    ;
        _item.name                 '_diffrn_scan_frame.integration_time'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       yes 
        _item_type.code            float
        _item_units.code           'seconds'
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0.0
         save_
    
    
    save__diffrn_scan_frame.scan_id
        _item_description.description
    ;             The value of '_diffrn_scan_frame.scan_id' identifies the scan
                  containing this frame.
    
                  This item is a pointer to '_diffrn_scan.id' in the
                  DIFFRN_SCAN category.
    ;
        _item.name             '_diffrn_scan_frame.scan_id'    
        _item.category_id        diffrn_scan_frame        
        _item.mandatory_code     yes     
        _item_type.code          code
         save_
    
    
    ##########################
    # DIFFRN_SCAN_FRAME_AXIS #
    ##########################
    
    save_DIFFRN_SCAN_FRAME_AXIS
        _category.description
    ;
         Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the
         settings of axes for particular frames.  Unspecified axes are
         assumed to be at their zero points.  If, for any given frame,
         non-zero values apply for any of the data items in this category,
         those values should be given explicitly in this category and not
         simply inferred from values in DIFFRN_SCAN_AXIS.
    
    ;
        _category.id                   diffrn_scan_frame_axis
        _category.mandatory_code       no
         loop_
        _category_key.name
                                      '_diffrn_scan_frame_axis.frame_id'
                                      '_diffrn_scan_frame_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_scan_frame_axis.axis_id
        _item_description.description
    ;
                   The value of this data item is the identifier of one of
                   the axes for the frame for which settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   '_diffrn_scan_frame.frame_id'.
    
                   This item is a pointer to '_axis.id' in the
                   AXIS category.
    ;
        _item.name                 '_diffrn_scan_frame_axis.axis_id'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_frame_axis.angle
        _item_description.description
    ;
                   The setting of the specified axis in degrees for this frame.
                   This is the setting at the start of the integration time.
    ;
        _item.name                 '_diffrn_scan_frame_axis.angle'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_frame_axis.angle_increment
        _item_description.description
    ;
                   The increment for this frame for angular setting of
                   the specified axis in degrees.  The sum of the values
                   of '_diffrn_scan_frame_axis.angle' and
                   '_diffrn_scan_frame_axis.angle_increment' is the
                   angular setting of the axis at the end of the integration
                   time for this frame.
    ;
        _item.name                 '_diffrn_scan_frame_axis.angle_increment'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_frame_axis.angle_rstrt_incr
        _item_description.description
    ;
                   The increment after this frame for angular setting of
                   the specified axis in degrees.  The sum of the values
                   of '_diffrn_scan_frame_axis.angle' and
                   '_diffrn_scan_frame_axis.angle_increment' and
                   '_diffrn_scan_frame_axis.angle_rstrt_incr' is the
                   angular setting of the axis at the start of the integration
                   time for the next frame, and should equal
                   '_diffrn_scan_frame_axis.angle' for that next frame.
    ;
        _item.name               '_diffrn_scan_frame_axis.angle_rstrt_incr'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_frame_axis.displacement
        _item_description.description
    ;
                   The setting of the specified axis in millimetres for this
                   frame.  This is the setting at the start of the integration
                   time.
    
    ;
        _item.name               '_diffrn_scan_frame_axis.displacement'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_frame_axis.displacement_increment
        _item_description.description
    ;
                   The increment for this frame for displacement setting of
                   the specified axis in millimetres.  The sum of the values
                   of '_diffrn_scan_frame_axis.displacement' and
                   '_diffrn_scan_frame_axis.displacement_increment' is the
                   angular setting of the axis at the end of the integration
                   time for this frame.
    ;
        _item.name               '_diffrn_scan_frame_axis.displacement_increment'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_frame_axis.displacement_rstrt_incr
        _item_description.description
    ;
                   The increment for this frame for displacement setting of
                   the specified axis in millimetres.  The sum of the values
                   of '_diffrn_scan_frame_axis.displacement' and
                   '_diffrn_scan_frame_axis.displacement_increment' and
                   '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the
                   angular setting of the axis at the start of the integration
                   time for the next frame, and should equal
                   '_diffrn_scan_frame_axis.displacement' for that next frame.
    ;
        _item.name               '_diffrn_scan_frame_axis.displacement_rstrt_incr'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    save__diffrn_scan_frame_axis.frame_id
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   frame for which axis settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   '_diffrn_scan_frame.frame_id'.
    
                   This item is a pointer to '_diffrn_data_frame.id' in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name               '_diffrn_scan_frame_axis.frame_id'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    ########################   DEPRECATED DATA ITEMS ########################
    
    save__diffrn_detector_axis.id
        _item_description.description
    ;
                   This data item is a pointer to '_diffrn_detector.id' in
                   the DIFFRN_DETECTOR category.
                  
                   DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_detector_axis.id'
        _item.category_id             diffrn_detector_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    save__diffrn_measurement_axis.id
        _item_description.description
    ;
                   This data item is a pointer to '_diffrn_measurement.id' in
                   the DIFFRN_MEASUREMENT category.
                  
                   DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_measurement_axis.id'
        _item.category_id             diffrn_measurement_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    #########################   DEPRECATED CATEGORY #########################
    #####################
    # DIFFRN_FRAME_DATA #
    #####################
    
    
    save_DIFFRN_FRAME_DATA
        _category.description
    ;
                  Data items in the DIFFRN_FRAME_DATA category record
                  the details about each frame of data. 
    
                  The items in this category are now in the
                  DIFFRN_DATA_FRAME category.
                  
                  The items in the DIFFRN_FRAME_DATA category
                  are now deprecated.  The items from this category 
                  are provided as aliases in the 1.0.0 dictionary, 
                  but should not be used for new work.
                  The items from the old category are provided
                  in this dictionary for completeness,
                  but should not be used or cited.  To avoid
                  confusion, the example has been removed,
                  and the redundant parent child-links to other
                  categories removed.
                  
    ;
        _category.id                   diffrn_frame_data
        _category.mandatory_code       no
         loop_
        _category_key.name             '_diffrn_frame_data.id'
                                       '_diffrn_frame_data.detector_element_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        THE DIFFRN_FRAME_DATA category is deprecated and should not be used.
    ;
    ;
           # EXAMPLE REMOVED #
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
    
    
    save__diffrn_frame_data.array_id
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category.
    
                  DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_frame_data.array_id'
        _item.category_id             diffrn_frame_data
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_frame_data.binary_id
        _item_description.description
    ;             This item is a pointer to '_array_data.binary_id' in the
                  ARRAY_STRUCTURE category. 
                  
                  DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_frame_data.binary_id'
        _item.category_id             diffrn_frame_data
        _item.mandatory_code          implicit
        _item_type.code               int
         save_
    
    
    save__diffrn_frame_data.detector_element_id
        _item_description.description
    ;             
                  This item is a pointer to '_diffrn_detector_element.id'
                  in the DIFFRN_DETECTOR_ELEMENT category.
    
                  DEPRECATED -- DO NOT USE 
    ;
        _item.name                  '_diffrn_frame_data.detector_element_id'
        _item.category_id             diffrn_frame_data
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_frame_data.id
        _item_description.description
    ;             
                  The value of '_diffrn_frame_data.id' must uniquely identify
                  each complete frame of data.
    
                  DEPRECATED -- DO NOT USE 
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
               '_diffrn_frame_data.id'        diffrn_frame_data  yes
        _item_type.code               code
         save_
    
    ################ END DEPRECATED SECTION ###########
    
    
    ####################
    ## ITEM_TYPE_LIST ##
    ####################
    #
    #
    #  The regular expressions defined here are not compliant
    #  with the POSIX 1003.2 standard as they include the
    #  '\n' and '\t' special characters.  These regular expressions
    #  have been tested using version 0.12 of Richard Stallman's
    #  GNU regular expression library in POSIX mode.
    #  In order to allow presentation of a regular expression
    #  in a text field concatenate any line ending in a backslash
    #  with the following line, after discarding the backslash.
    #
    #  A formal definition of the '\n' and '\t' special characters
    #  is most properly done in the DDL, but for completeness, please
    #  note that '\n' is the line termination character ('newline')
    #  and '\t' is the horizontal tab character.  There is a formal
    #  ambiguity in the use of '\n' for line termination, in that
    #  the intention is that the equivalent machine/OS-dependent line
    #  termination character sequence should be accepted as a match, e.g.
    #
    #      '\r' (control-M) under MacOS
    #      '\n' (control-J) under Unix
    #      '\r\n' (control-M control-J) under DOS and MS Windows
    #
         loop_
        _item_type_list.code
        _item_type_list.primitive_code
        _item_type_list.construct
        _item_type_list.detail
                   code      char
    '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
    ;              code item types/single words ...
    ;
                   ucode      uchar
    '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
    ;              code item types/single words (case insensitive)
    ;
                   line      char
    '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
    ;              code item types / multi-word items  ...
    ;
                   uline     uchar
    '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
    ;              code item types / multi-word items (case insensitive)
    ;
                   text      char
    '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*'
    ;              text item types / multi-line text ...
    ;
                   binary    char
    ;\n--CIF-BINARY-FORMAT-SECTION--\n\
    [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\
    \n--CIF-BINARY-FORMAT-SECTION----
    ;
    ;              binary items are presented as MIME-like ascii-encoded
                   sections in an imgCIF.  In a CBF, raw octet streams
                   are used to convey the same information.
    ;
                   int       numb
    '-?[0-9]+'
    ;              int item types are the subset of numbers that are the negative
                   or positive integers.
    ;
                   float     numb
    '-?(([0-9]+)|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?'
    ;              float item types are the subset of numbers that are the floating
                   numbers.
    ;
                   any       char
    '.*'
    ;              A catch all for items that may take any form...
    ;
                   yyyy-mm-dd  char
    ;\
    [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9][0-9]\
    (T[0-2][0-9]:[0-5][0-9]:[0-5][0-9](.[0-9]+)([+-][0-5][0-9]:[0-5][0-9]))
    ;
    ;
                   Standard format for CIF date and time strings (see
                   http://www.iucr.org/iucr-top/cif/spec/datetime.html),
                   consisting of a yyyy-mm-dd date optionally followed by
                   the character "T" followed by a 24-hour clock time,
                   optionally followed by a signed time-zone offset.
                   
                   The IUCr standard has been extended to allow for an optional
                   decimal fraction on the seconds of time.
                   
                   Time is local time if no time-zone offset is given.
    ;
    
    
    #####################
    ## ITEM_UNITS_LIST ##
    #####################
    
         loop_
        _item_units_list.code
        _item_units_list.detail
    #
         'metres'                 'metres'
         'centimetres'            'centimetres (metres * 10( -2))'
         'millimetres'            'millimetres (metres * 10( -3))'
         'nanometres'             'nanometres  (metres * 10( -9))'
         'angstroms'              'Ångstroms   (metres * 10(-10))'
         'picometres'             'picometres  (metres * 10(-12))'
         'femtometres'            'femtometres (metres * 10(-15))'
    #
         'reciprocal_metres'      'reciprocal metres (metres(-1))'
         'reciprocal_centimetres' 
            'reciprocal centimetres ((metres * 10( -2))(-1))'
         'reciprocal_millimetres' 
            'reciprocal millimetres ((metres * 10( -3))(-1))'
         'reciprocal_nanometres'  
            'reciprocal nanometres  ((metres * 10( -9))(-1))'
         'reciprocal_angstroms'   
            'reciprocal Ångstroms   ((metres * 10(-10))(-1))'
         'reciprocal_picometres'  
            'reciprocal picometres  ((metres * 10(-12))(-1))'
    #
         'nanometres_squared'     'nanometres squared (metres * 10( -9))2'
         'angstroms_squared'      'Ångstroms squared  (metres * 10(-10))2'
         '8pi2_angstroms_squared' '8π2 * Ångstroms squared (metres * 10(-10))2'
         'picometres_squared'     'picometres squared (metres * 10(-12))2'
    #
         'nanometres_cubed'       'nanometres cubed (metres * 10( -9))3'
         'angstroms_cubed'        'Ångstroms cubed  (metres * 10(-10))3'
         'picometres_cubed'       'picometres cubed (metres * 10(-12))3'
    #
         'kilopascals'            'kilopascals'
         'gigapascals'            'gigapascals'
    #
         'hours'                  'hours'
         'minutes'                'minutes'
         'seconds'                'seconds'
         'microseconds'           'microseconds'
    #
         'degrees'                'degrees (of arc)'
         'degrees_squared'        'degrees (of arc) squared'
    #
         'degrees_per_minute'     'degrees (of arc) per minute'
    #
         'celsius'                'degrees (of temperature) Celsius'
         'kelvins'                'degrees (of temperature) Kelvin'
    #
         'counts'                 'counts'
         'counts_per_photon'      'counts per photon'
    #
         'electrons'              'electrons'
    #
         'electrons_squared'      'electrons squared'
    #
         'electrons_per_nanometres_cubed'
    ; electrons per nanometres cubed (electrons/(metres * 10( -9))(-3))
    ;
         'electrons_per_angstroms_cubed'
    ; electrons per Ångstroms cubed (electrons/(metres * 10(-10))(-3))
    ;
         'electrons_per_picometres_cubed'
    ; electrons per picometres cubed (electrons/(metres * 10(-12))(-3)) 
    ;
         'kilowatts'              'kilowatts'
         'milliamperes'           'milliamperes'
         'kilovolts'              'kilovolts'
    #
         'arbitrary'
    ; arbitrary system of units.
    ;
    #
    
         loop_
        _item_units_conversion.from_code
        _item_units_conversion.to_code
        _item_units_conversion.operator
        _item_units_conversion.factor
    ###
         'metres'                   'centimetres'              '*'   1.0E+02
         'metres'                   'millimetres'              '*'   1.0E+03
         'metres'                   'nanometres'               '*'   1.0E+09
         'metres'                   'angstroms'                '*'   1.0E+10
         'metres'                   'picometres'               '*'   1.0E+12
         'metres'                   'femtometres'              '*'   1.0E+15
    #
         'centimetres'              'metres'                   '*'   1.0E-02
         'centimetres'              'millimetres'              '*'   1.0E+01
         'centimetres'              'nanometres'               '*'   1.0E+07
         'centimetres'              'angstroms'                '*'   1.0E+08
         'centimetres'              'picometres'               '*'   1.0E+10
         'centimetres'              'femtometres'              '*'   1.0E+13
    #
         'millimetres'              'metres'                   '*'   1.0E-03
         'millimetres'              'centimetres'              '*'   1.0E-01
         'millimetres'              'nanometres'               '*'   1.0E+06
         'millimetres'              'angstroms'                '*'   1.0E+07
         'millimetres'              'picometres'               '*'   1.0E+09
         'millimetres'              'femtometres'              '*'   1.0E+12
    #
         'nanometres'               'metres'                   '*'   1.0E-09
         'nanometres'               'centimetres'              '*'   1.0E-07
         'nanometres'               'millimetres'              '*'   1.0E-06
         'nanometres'               'angstroms'                '*'   1.0E+01
         'nanometres'               'picometres'               '*'   1.0E+03
         'nanometres'               'femtometres'              '*'   1.0E+06
    #
         'angstroms'                'metres'                   '*'   1.0E-10
         'angstroms'                'centimetres'              '*'   1.0E-08
         'angstroms'                'millimetres'              '*'   1.0E-07
         'angstroms'                'nanometres'               '*'   1.0E-01
         'angstroms'                'picometres'               '*'   1.0E+02
         'angstroms'                'femtometres'              '*'   1.0E+05
    #
         'picometres'               'metres'                   '*'   1.0E-12
         'picometres'               'centimetres'              '*'   1.0E-10
         'picometres'               'millimetres'              '*'   1.0E-09
         'picometres'               'nanometres'               '*'   1.0E-03
         'picometres'               'angstroms'                '*'   1.0E-02
         'picometres'               'femtometres'              '*'   1.0E+03
    #
         'femtometres'              'metres'                   '*'   1.0E-15
         'femtometres'              'centimetres'              '*'   1.0E-13
         'femtometres'              'millimetres'              '*'   1.0E-12
         'femtometres'              'nanometres'               '*'   1.0E-06
         'femtometres'              'angstroms'                '*'   1.0E-05
         'femtometres'              'picometres'               '*'   1.0E-03
    ###
         'reciprocal_centimetres'   'reciprocal_metres'        '*'   1.0E+02
         'reciprocal_centimetres'   'reciprocal_millimetres'   '*'   1.0E-01
         'reciprocal_centimetres'   'reciprocal_nanometres'    '*'   1.0E-07
         'reciprocal_centimetres'   'reciprocal_angstroms'     '*'   1.0E-08
         'reciprocal_centimetres'   'reciprocal_picometres'    '*'   1.0E-10
    #
         'reciprocal_millimetres'   'reciprocal_metres'        '*'   1.0E+03
         'reciprocal_millimetres'   'reciprocal_centimetres'   '*'   1.0E+01
         'reciprocal_millimetres'   'reciprocal_nanometres'    '*'   1.0E-06
         'reciprocal_millimetres'   'reciprocal_angstroms'     '*'   1.0E-07
         'reciprocal_millimetres'   'reciprocal_picometres'    '*'   1.0E-09
    #
         'reciprocal_nanometres'    'reciprocal_metres'        '*'   1.0E+09
         'reciprocal_nanometres'    'reciprocal_centimetres'   '*'   1.0E+07
         'reciprocal_nanometres'    'reciprocal_millimetres'   '*'   1.0E+06
         'reciprocal_nanometres'    'reciprocal_angstroms'     '*'   1.0E-01
         'reciprocal_nanometres'    'reciprocal_picometres'    '*'   1.0E-03
    #
         'reciprocal_angstroms'     'reciprocal_metres'        '*'   1.0E+10
         'reciprocal_angstroms'     'reciprocal_centimetres'   '*'   1.0E+08
         'reciprocal_angstroms'     'reciprocal_millimetres'   '*'   1.0E+07
         'reciprocal_angstroms'     'reciprocal_nanometres'    '*'   1.0E+01
         'reciprocal_angstroms'     'reciprocal_picometres'    '*'   1.0E-02
    #
         'reciprocal_picometres'    'reciprocal_metres'        '*'   1.0E+12
         'reciprocal_picometres'    'reciprocal_centimetres'   '*'   1.0E+10
         'reciprocal_picometres'    'reciprocal_millimetres'   '*'   1.0E+09
         'reciprocal_picometres'    'reciprocal_nanometres'    '*'   1.0E+03
         'reciprocal_picometres'    'reciprocal_angstroms'     '*'   1.0E+01
    ###
         'nanometres_squared'       'angstroms_squared'        '*'   1.0E+02
         'nanometres_squared'       'picometres_squared'       '*'   1.0E+06
    #
         'angstroms_squared'        'nanometres_squared'       '*'   1.0E-02
         'angstroms_squared'        'picometres_squared'       '*'   1.0E+04
         'angstroms_squared'        '8pi2_angstroms_squared'   '*'   78.9568
    
    #
         'picometres_squared'       'nanometres_squared'       '*'   1.0E-06
         'picometres_squared'       'angstroms_squared'        '*'   1.0E-04
    ###
         'nanometres_cubed'         'angstroms_cubed'          '*'   1.0E+03
         'nanometres_cubed'         'picometres_cubed'         '*'   1.0E+09
    #
         'angstroms_cubed'          'nanometres_cubed'         '*'   1.0E-03
         'angstroms_cubed'          'picometres_cubed'         '*'   1.0E+06
    #
         'picometres_cubed'         'nanometres_cubed'         '*'   1.0E-09
         'picometres_cubed'         'angstroms_cubed'          '*'   1.0E-06
    ###
         'kilopascals'              'gigapascals'              '*'   1.0E-06
         'gigapascals'              'kilopascals'              '*'   1.0E+06
    ###
         'hours'                    'minutes'                  '*'   6.0E+01
         'hours'                    'seconds'                  '*'   3.6E+03
         'hours'                    'microseconds'             '*'   3.6E+09
    #
         'minutes'                  'hours'                    '/'   6.0E+01
         'minutes'                  'seconds'                  '*'   6.0E+01
         'minutes'                  'microseconds'             '*'   6.0E+07
    #
         'seconds'                  'hours'                    '/'   3.6E+03
         'seconds'                  'minutes'                  '/'   6.0E+01
         'seconds'                  'microseconds'             '*'   1.0E+06
    #
         'microseconds'             'hours'                    '/'   3.6E+09
         'microseconds'             'minutes'                  '/'   6.0E+07
         'microseconds'             'seconds'                  '/'   1.0E+06
    ###
         'celsius'                  'kelvins'                  '-'     273.0
         'kelvins'                  'celsius'                  '+'     273.0
    ###
         'electrons_per_nanometres_cubed'
         'electrons_per_angstroms_cubed'                       '*'   1.0E+03
         'electrons_per_nanometres_cubed'
         'electrons_per_picometres_cubed'                      '*'   1.0E+09
    #
         'electrons_per_angstroms_cubed'
         'electrons_per_nanometres_cubed'                      '*'   1.0E-03
         'electrons_per_angstroms_cubed'
         'electrons_per_picometres_cubed'                      '*'   1.0E+06
    #
         'electrons_per_picometres_cubed'
         'electrons_per_nanometres_cubed'                      '*'   1.0E-09
         'electrons_per_picometres_cubed'
         'electrons_per_angstroms_cubed'                       '*'   1.0E-06
    ###
    
    
    ########################
    ## DICTIONARY_HISTORY ##
    ########################
    
         loop_
        _dictionary_history.version
        _dictionary_history.update
        _dictionary_history.revision
    
       1.3.2   2005-06-22
    ;
       Changes as per Nicola Ashcroft.
       + Fix '_item_units.code  code' to be '_item_type.code  code'
       in  '_array_structure_list_axis.axis_id' and in
       '_array_structure_list_axis.axis_set_id'
       Also fix typos in exponents and long lines in units list
       (HJB)
    
    ;
    
       1.3.1   2003-08-13
    ;
       Changes as per Frances C. Bernstein.
       + Identify initials.
       + Adopt British spelling for centre in text.
       + Set π and Ångstrom and powers.
       + Clean up commas and unclear wordings.
       + Clean up tenses in history.
       Changes as per Gotzon Madariaga.
       + Fix the ARRAY_DATA example to align '_array_data.binary_id'
       and X-Binary-Id.
       + Add a range to '_array_intensities.gain_esd'.
       + In the example of DIFFRN_DETECTOR_ELEMENT, 
       '_diffrn_detector_element.id' and
       '_diffrn_detector_element.detector_id' interchanged.
       + Fix typos for direction, detector and axes.
       + Clarify description of polarisation.
       + Clarify axes in '_diffrn_detector_element.center[1]'
        '_diffrn_detector_element.center[2]'.
       + Add local item types for items that are pointers.
       (HJB)
    ;
    
    
       1.3.0   2003-07-24
    ;
       Changes as per Brian McMahon. 
       + Consistently quote tags embedded in text.
       + Clean up introductory comments.
       + Adjust line lengths to fit in 80 character window.
       + Fix several descriptions in AXIS category which
         referred to '_axis.type' instead of the current item.
       + Fix erroneous use of deprecated item
         '_diffrn_detector_axis.id' in examples for 
         DIFFRN_SCAN_AXIS.
       + Add deprecated items '_diffrn_detector_axis.id'
         and '_diffrn_measurement_axis.id'.
       (HJB)
    ;
    
    
       1.2.4   2003-07-14
    ;
       Changes as per I. David Brown. 
       + Enhance descriptions in DIFFRN_SCAN_AXIS to make them less
         dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS.
       + Provide a copy of the deprecated DIFFRN_FRAME_DATA
         category for completeness.
       (HJB)
    ;
    
    
       1.2.3   2003-07-03
    ;
       Cleanup to conform to ITVG. 
       + Correct sign error in ..._cubed units.
       + Correct '_diffrn_radiation.polarisn_norm' range.
       (HJB)
    ;
    
    
       1.2.2   2003-03-10
    ;
       Correction of typos in various DIFFRN_SCAN_AXIS descriptions. 
       (HJB)
    ;
    
    
       1.2.1   2003-02-22
    ;
       Correction of ATOM_ for ARRAY_ typos in various descriptions. 
       (HJB)
    ;
    
    
       1.2     2003-02-07
    ;
       Corrections to encodings (remove extraneous hyphens) remove
       extraneous underscore in '_array_structure.encoding_type'
       enumeration.  Correct typos in items units list.  (HJB)
    ;
    
    
       1.1.3   2001-04-19
    ;
       Another typo corrections by Wilfred Li, and cleanup by HJB.
    ;
    
    
       1.1.2   2001-03-06
    ;
       Several typo corrections by Wilfred Li.
    ;
    
    
       1.1.1   2001-02-16
    ;
       Several typo corrections by JW.
    ;
    
    
       1.1     2001-02-06
    ;
       Draft resulting from discussions on header for use at NSLS.  (HJB)
       
       + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME.
       
       + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'.
       
       + Add '_diffrn_measurement_axis.measurement_device' and change
         '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'.
       
       + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source',
        '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm',
       '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end',
       '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr',
       '_diffrn_scan_axis.displacement_rstrt_incr', 
       '_diffrn_scan_frame_axis.angle_increment',
       '_diffrn_scan_frame_axis.angle_rstrt_incr',
       '_diffrn_scan_frame_axis.displacement',
       '_diffrn_scan_frame_axis.displacement_increment',and
       '_diffrn_scan_frame_axis.displacement_rstrt_incr'.
       
       + Add '_diffrn_measurement.device' to category key.
       
       + Update yyyy-mm-dd to allow optional time with fractional seconds
         for time stamps.
    
       + Fix typos caught by RS.
       
       + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to
         allow for coupled axes, as in spiral scans.
    
       + Add examples for fairly complete headers thanks to R. Sweet and P. 
         Ellis.
    ;
    
    
       1.0     2000-12-21
    ;
       Release version - few typos and tidying up.  (BM & HJB)
       
       + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end
       of dictionary.
       
       + Alphabetize dictionary.
    ;
    
    
       0.7.1   2000-09-29
    ;
       Cleanup fixes.  (JW)
    
       + Correct spelling of diffrn_measurement_axis in '_axis.id'
    
       + Correct ordering of uses of '_item.mandatory_code' and
       '_item_default.value'.
    ;
    
    
       0.7.0   2000-09-09
    ;
       Respond to comments by I. David Brown.  (HJB)
    
       + Add further comments on '\n' and '\t'.
    
       + Update ITEM_UNITS_LIST by taking section from mmCIF dictionary
         and adding metres.  Change 'meter' to 'metre' throughout.
    
       + Add missing enumerations to '_array_structure.compression_type'
         and make 'none' the default.
    
       + Remove parent-child relationship between
         '_array_structure_list.index' and '_array_structure_list.precedence'.
    
       + Improve alphabetization.
    
       + Fix '_array_intensities_gain.esd' related function.
    
       + Improve comments in AXIS.
    
       + Fix DIFFRN_FRAME_DATA example.
    
       + Remove erroneous DIFFRN_MEASUREMENT example.
    
       + Add '_diffrn_measurement_axis.id' to the category key.
    ;
    
    
       0.6.0   1999-01-14
    ;
       Remove redundant information for ENC_NONE data.  (HJB)
    
       + After the D5 remove binary section identifier, size and
         compression type.
    
       + Add Control-L to header.
    ;
    
    
       0.5.1   1999-01-03
    ;
       Cleanup of typos and syntax errors.  (HJB)
    
       + Cleanup example details for DIFFRN_SCAN category.
    
       + Add missing quote marks for '_diffrn_scan.id' definition.
    ;
    
    
       0.5   1999-01-01
    ;
       Modifications for axis definitions and reduction of binary header.  (HJB)
    
       + Restore '_diffrn_detector.diffrn_id' to DIFFRN_DETECTOR KEY.
    
       + Add AXIS category.
    
       + Bring in complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories
         from cif_mm.dic for clarity.
    
       + Change '_array_structure.encoding_type' from type code to uline and
         added X-Binary-Element-Type to MIME header.
    
       + Add detector beam centre '_diffrn_detector_element.center[1]' and 
         '_diffrn_detector_element.center[2]'.
    
       + Correct item name of '_diffrn_refln.frame_id'.
    
       + Replace reference to '_array_intensities.undefined' by
         '_array_intensities.undefined_value'.
    
       + Replace references to '_array_intensity.scaling' with
         '_array_intensities.scaling'.
    
       + Add DIFFRN_SCAN... categories.
    ;
    
    
       0.4   1998-08-11
    ;
       Modifications to the 0.3 imgCIF draft.  (HJB)
    
       + Reflow comment lines over 80 characters and corrected typos.
    
       + Update examples and descriptions of MIME encoded data.
    
       + Change name to cbfext98.dic.
    ;
    
    
       0.3   1998-07-04
    ;
       Modifications for imgCIF.  (HJB)
    
       + Add binary type, which is a text field containing a variant on
         MIME encoded data.
          
       + Change type of '_array_data.data' to binary and specify internal
         structure of raw binary data.
          
       + Add '_array_data.binary_id', and make 
         '_diffrn_frame_data.binary_id' and '_array_intensities.binary_id'
         into pointers to this item.
    ;
    
    
       0.2   1997-12-02
    ;
       Modifications to the CBF draft.  (JW)  
    
       + Add category hierarchy for describing frame data developed from
         discussions at the BNL imgCIF Workshop Oct 1997.   The following
         changes are made in implementing the workshop draft.  Category
         DIFFRN_ARRAY_DATA is renamed to DIFFRN_FRAME_DATA.  Category
         DIFFRN_FRAME_TYPE is renamed to DIFFRN_DETECTOR_ELEMENT.   The
         parent item for '_diffrn_frame_data.array_id' is changed from
         '_array_structure_list.array_id' to '_array_structure.id'. Item 
         '_diffrn_detector.array_id' is deleted.  
       + Add data item '_diffrn_frame_data.binary_id' to identify data 
         groups within a binary section.  The formal identification of the
         binary section is still fuzzy.  
    ;
    
    
       0.1   1997-01-24
    ;
       First draft of this dictionary in DDL 2.1 compliant format by John 
       Westbrook (JW).  This version is adapted from the Crystallographic 
       Binary File (CBF) Format Draft Proposal provided by Andy Hammersley
       (AH).  
    
       Modifications to the CBF draft.  (JW)  
    
       + In this version the array description has been cast in the categories 
         ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST.  These categories
         have been generalized to describe array data  of arbitrary dimension.  
    
       + Array data in this description are contained in the category
         ARRAY_DATA.  This departs from the CBF notion of data existing
         in some special comment. In this description, data is handled as an 
         ordinary data item encapsulated in a character data type.   Although
         data this manner deviates from CIF conventions, it does not violate 
         any DDL 2.1 rules.  DDL 2.1 regular expressions can be used to define 
         the binary representation which will permit some level of data 
         validation.  In this version, the placeholder type code "any" has
         been used. This translates to a regular expression which will match 
         any pattern.
    
         It should be noted that DDL 2.1 already supports array data objects 
         although these have not been used in the current mmCIF dictionary.
         It may be possible to use the DDL 2.1 ITEM_STRUCTURE and
         ITEM_STRUCTURE_LIST categories to provide the information that is
         carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST.  By
         moving the array structure to the DDL level it would be possible to
         define an array type as well as a regular expression defining the
         data format. 
    
       + Multiple array sections can be properly handled within a single
         datablock.
    ;
    
    
    #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof
    
    ./CBFlib-0.9.2.2/doc/Idiffrn_scan_frame_axis.angle_rstrt_incr.html0000644000076500007650000000641211603702115023355 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan_frame_axis.angle_rstrt_incr

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_scan_frame_axis.angle_rstrt_incr

    Name:
    '_diffrn_scan_frame_axis.angle_rstrt_incr'

    Definition:

            The increment after this frame for the angular setting of
                   the specified axis in degrees.  The sum of the values
                   of _diffrn_scan_frame_axis.angle,
                   _diffrn_scan_frame_axis.angle_increment and
                   _diffrn_scan_frame_axis.angle_rstrt_incr is the
                   angular setting of the axis at the start of the integration
                   time for the next frame and should equal
                   _diffrn_scan_frame_axis.angle for this next frame.
    
    

    Type: float

    Mandatory item: no


    Enumeration default: 0.0

    Category: diffrn_scan_frame_axis

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Iarray_intensities.gain_esd.html0000644000076500007650000000524211603702115020651 0ustar yayayaya (IUCr) CIF Definition save__array_intensities.gain_esd

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _array_intensities.gain_esd

    Name:
    '_array_intensities.gain_esd'

    Definition:

          The estimated standard deviation in detector 'gain'.
    
    

    Type: float

    Mandatory item: yes


    The permitted range is [0.0, infinity)

    Related item: _array_intensities.gain (associated_esd)

    Category: array_intensities

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_measurement.device_type.html0000644000076500007650000000634311603702115021524 0ustar yayayaya (IUCr) CIF Definition save__diffrn_measurement.device_type

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_measurement.device_type

    Name:
    '_diffrn_measurement.device_type'

    Definition:

            The make, model or name of the measurement device
                   (goniometer) used.
    
    
    Examples:

    'Supper model q'
    'Huber model r'
    'Enraf-Nonius model s'
    home-made

    Type: text

    Mandatory item: no

    Alias:
    _diffrn_measurement_device_type (cif_core.dic version 2.0.1)

    Category: diffrn_measurement

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_detector_element.center[1].html0000644000076500007650000000701411603702115022046 0ustar yayayaya (IUCr) CIF Definition save__diffrn_detector_element.center[1]

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_detector_element.center[1]

    Name:
    '_diffrn_detector_element.center[1]'

    Definition:

           The value of _diffrn_detector_element.center[1] is the X
                  component of the distortion-corrected beam centre in
                  millimetres from the (0, 0) (lower-left) corner of the
                  detector element viewed from the sample side.
    
                  The X and Y axes are the laboratory coordinate system
                  coordinates defined in the AXIS category measured
                  when all positioning axes for the detector are at their zero
                  settings.  If the resulting X or Y axis is then orthogonal to the
                  detector, the Z axis is used instead of the orthogonal axis.
    
                  Because of ambiguity about the setting used to determine this 
                  center, use of this data item is deprecated.  The data item
                  _diffrn_data_frame.center_fast
                  which is referenced to the detector coordinate system and not
                  directly to the laboratory coordinate system should be used 
                  instead.
    
    
    

    Type: float

    Mandatory item: no


    Enumeration default: 0.0

    Category: diffrn_detector_element

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/gpl.txt0000644000076500007650000004313311603702115013672 0ustar yayayaya GNU GENERAL PUBLIC LICENSE Version 2, June 1991 Copyright (C) 1989, 1991 Free Software Foundation, Inc. 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA Everyone is permitted to copy and distribute verbatim copies of this license document, but changing it is not allowed. Preamble The licenses for most software are designed to take away your freedom to share and change it. By contrast, the GNU General Public License is intended to guarantee your freedom to share and change free software--to make sure the software is free for all its users. This General Public License applies to most of the Free Software Foundation's software and to any other program whose authors commit to using it. (Some other Free Software Foundation software is covered by the GNU Library General Public License instead.) You can apply it to your programs, too. When we speak of free software, we are referring to freedom, not price. Our General Public Licenses are designed to make sure that you have the freedom to distribute copies of free software (and charge for this service if you wish), that you receive source code or can get it if you want it, that you can change the software or use pieces of it in new free programs; and that you know you can do these things. To protect your rights, we need to make restrictions that forbid anyone to deny you these rights or to ask you to surrender the rights. These restrictions translate to certain responsibilities for you if you distribute copies of the software, or if you modify it. For example, if you distribute copies of such a program, whether gratis or for a fee, you must give the recipients all the rights that you have. You must make sure that they, too, receive or can get the source code. And you must show them these terms so they know their rights. We protect your rights with two steps: (1) copyright the software, and (2) offer you this license which gives you legal permission to copy, distribute and/or modify the software. Also, for each author's protection and ours, we want to make certain that everyone understands that there is no warranty for this free software. If the software is modified by someone else and passed on, we want its recipients to know that what they have is not the original, so that any problems introduced by others will not reflect on the original authors' reputations. Finally, any free program is threatened constantly by software patents. We wish to avoid the danger that redistributors of a free program will individually obtain patent licenses, in effect making the program proprietary. To prevent this, we have made it clear that any patent must be licensed for everyone's free use or not licensed at all. The precise terms and conditions for copying, distribution and modification follow. GNU GENERAL PUBLIC LICENSE TERMS AND CONDITIONS FOR COPYING, DISTRIBUTION AND MODIFICATION 0. This License applies to any program or other work which contains a notice placed by the copyright holder saying it may be distributed under the terms of this General Public License. The "Program", below, refers to any such program or work, and a "work based on the Program" means either the Program or any derivative work under copyright law: that is to say, a work containing the Program or a portion of it, either verbatim or with modifications and/or translated into another language. (Hereinafter, translation is included without limitation in the term "modification".) Each licensee is addressed as "you". Activities other than copying, distribution and modification are not covered by this License; they are outside its scope. The act of running the Program is not restricted, and the output from the Program is covered only if its contents constitute a work based on the Program (independent of having been made by running the Program). Whether that is true depends on what the Program does. 1. You may copy and distribute verbatim copies of the Program's source code as you receive it, in any medium, provided that you conspicuously and appropriately publish on each copy an appropriate copyright notice and disclaimer of warranty; keep intact all the notices that refer to this License and to the absence of any warranty; and give any other recipients of the Program a copy of this License along with the Program. You may charge a fee for the physical act of transferring a copy, and you may at your option offer warranty protection in exchange for a fee. 2. You may modify your copy or copies of the Program or any portion of it, thus forming a work based on the Program, and copy and distribute such modifications or work under the terms of Section 1 above, provided that you also meet all of these conditions: a) You must cause the modified files to carry prominent notices stating that you changed the files and the date of any change. b) You must cause any work that you distribute or publish, that in whole or in part contains or is derived from the Program or any part thereof, to be licensed as a whole at no charge to all third parties under the terms of this License. c) If the modified program normally reads commands interactively when run, you must cause it, when started running for such interactive use in the most ordinary way, to print or display an announcement including an appropriate copyright notice and a notice that there is no warranty (or else, saying that you provide a warranty) and that users may redistribute the program under these conditions, and telling the user how to view a copy of this License. (Exception: if the Program itself is interactive but does not normally print such an announcement, your work based on the Program is not required to print an announcement.) These requirements apply to the modified work as a whole. If identifiable sections of that work are not derived from the Program, and can be reasonably considered independent and separate works in themselves, then this License, and its terms, do not apply to those sections when you distribute them as separate works. But when you distribute the same sections as part of a whole which is a work based on the Program, the distribution of the whole must be on the terms of this License, whose permissions for other licensees extend to the entire whole, and thus to each and every part regardless of who wrote it. Thus, it is not the intent of this section to claim rights or contest your rights to work written entirely by you; rather, the intent is to exercise the right to control the distribution of derivative or collective works based on the Program. In addition, mere aggregation of another work not based on the Program with the Program (or with a work based on the Program) on a volume of a storage or distribution medium does not bring the other work under the scope of this License. 3. You may copy and distribute the Program (or a work based on it, under Section 2) in object code or executable form under the terms of Sections 1 and 2 above provided that you also do one of the following: a) Accompany it with the complete corresponding machine-readable source code, which must be distributed under the terms of Sections 1 and 2 above on a medium customarily used for software interchange; or, b) Accompany it with a written offer, valid for at least three years, to give any third party, for a charge no more than your cost of physically performing source distribution, a complete machine-readable copy of the corresponding source code, to be distributed under the terms of Sections 1 and 2 above on a medium customarily used for software interchange; or, c) Accompany it with the information you received as to the offer to distribute corresponding source code. (This alternative is allowed only for noncommercial distribution and only if you received the program in object code or executable form with such an offer, in accord with Subsection b above.) The source code for a work means the preferred form of the work for making modifications to it. For an executable work, complete source code means all the source code for all modules it contains, plus any associated interface definition files, plus the scripts used to control compilation and installation of the executable. However, as a special exception, the source code distributed need not include anything that is normally distributed (in either source or binary form) with the major components (compiler, kernel, and so on) of the operating system on which the executable runs, unless that component itself accompanies the executable. If distribution of executable or object code is made by offering access to copy from a designated place, then offering equivalent access to copy the source code from the same place counts as distribution of the source code, even though third parties are not compelled to copy the source along with the object code. 4. You may not copy, modify, sublicense, or distribute the Program except as expressly provided under this License. Any attempt otherwise to copy, modify, sublicense or distribute the Program is void, and will automatically terminate your rights under this License. However, parties who have received copies, or rights, from you under this License will not have their licenses terminated so long as such parties remain in full compliance. 5. You are not required to accept this License, since you have not signed it. However, nothing else grants you permission to modify or distribute the Program or its derivative works. These actions are prohibited by law if you do not accept this License. Therefore, by modifying or distributing the Program (or any work based on the Program), you indicate your acceptance of this License to do so, and all its terms and conditions for copying, distributing or modifying the Program or works based on it. 6. Each time you redistribute the Program (or any work based on the Program), the recipient automatically receives a license from the original licensor to copy, distribute or modify the Program subject to these terms and conditions. You may not impose any further restrictions on the recipients' exercise of the rights granted herein. You are not responsible for enforcing compliance by third parties to this License. 7. If, as a consequence of a court judgment or allegation of patent infringement or for any other reason (not limited to patent issues), conditions are imposed on you (whether by court order, agreement or otherwise) that contradict the conditions of this License, they do not excuse you from the conditions of this License. If you cannot distribute so as to satisfy simultaneously your obligations under this License and any other pertinent obligations, then as a consequence you may not distribute the Program at all. For example, if a patent license would not permit royalty-free redistribution of the Program by all those who receive copies directly or indirectly through you, then the only way you could satisfy both it and this License would be to refrain entirely from distribution of the Program. If any portion of this section is held invalid or unenforceable under any particular circumstance, the balance of the section is intended to apply and the section as a whole is intended to apply in other circumstances. It is not the purpose of this section to induce you to infringe any patents or other property right claims or to contest validity of any such claims; this section has the sole purpose of protecting the integrity of the free software distribution system, which is implemented by public license practices. Many people have made generous contributions to the wide range of software distributed through that system in reliance on consistent application of that system; it is up to the author/donor to decide if he or she is willing to distribute software through any other system and a licensee cannot impose that choice. This section is intended to make thoroughly clear what is believed to be a consequence of the rest of this License. 8. If the distribution and/or use of the Program is restricted in certain countries either by patents or by copyrighted interfaces, the original copyright holder who places the Program under this License may add an explicit geographical distribution limitation excluding those countries, so that distribution is permitted only in or among countries not thus excluded. In such case, this License incorporates the limitation as if written in the body of this License. 9. The Free Software Foundation may publish revised and/or new versions of the General Public License from time to time. Such new versions will be similar in spirit to the present version, but may differ in detail to address new problems or concerns. Each version is given a distinguishing version number. If the Program specifies a version number of this License which applies to it and "any later version", you have the option of following the terms and conditions either of that version or of any later version published by the Free Software Foundation. If the Program does not specify a version number of this License, you may choose any version ever published by the Free Software Foundation. 10. If you wish to incorporate parts of the Program into other free programs whose distribution conditions are different, write to the author to ask for permission. For software which is copyrighted by the Free Software Foundation, write to the Free Software Foundation; we sometimes make exceptions for this. Our decision will be guided by the two goals of preserving the free status of all derivatives of our free software and of promoting the sharing and reuse of software generally. NO WARRANTY 11. BECAUSE THE PROGRAM IS LICENSED FREE OF CHARGE, THERE IS NO WARRANTY FOR THE PROGRAM, TO THE EXTENT PERMITTED BY APPLICABLE LAW. EXCEPT WHEN OTHERWISE STATED IN WRITING THE COPYRIGHT HOLDERS AND/OR OTHER PARTIES PROVIDE THE PROGRAM "AS IS" WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESSED OR IMPLIED, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE. THE ENTIRE RISK AS TO THE QUALITY AND PERFORMANCE OF THE PROGRAM IS WITH YOU. SHOULD THE PROGRAM PROVE DEFECTIVE, YOU ASSUME THE COST OF ALL NECESSARY SERVICING, REPAIR OR CORRECTION. 12. IN NO EVENT UNLESS REQUIRED BY APPLICABLE LAW OR AGREED TO IN WRITING WILL ANY COPYRIGHT HOLDER, OR ANY OTHER PARTY WHO MAY MODIFY AND/OR REDISTRIBUTE THE PROGRAM AS PERMITTED ABOVE, BE LIABLE TO YOU FOR DAMAGES, INCLUDING ANY GENERAL, SPECIAL, INCIDENTAL OR CONSEQUENTIAL DAMAGES ARISING OUT OF THE USE OR INABILITY TO USE THE PROGRAM (INCLUDING BUT NOT LIMITED TO LOSS OF DATA OR DATA BEING RENDERED INACCURATE OR LOSSES SUSTAINED BY YOU OR THIRD PARTIES OR A FAILURE OF THE PROGRAM TO OPERATE WITH ANY OTHER PROGRAMS), EVEN IF SUCH HOLDER OR OTHER PARTY HAS BEEN ADVISED OF THE POSSIBILITY OF SUCH DAMAGES. END OF TERMS AND CONDITIONS How to Apply These Terms to Your New Programs If you develop a new program, and you want it to be of the greatest possible use to the public, the best way to achieve this is to make it free software which everyone can redistribute and change under these terms. To do so, attach the following notices to the program. It is safest to attach them to the start of each source file to most effectively convey the exclusion of warranty; and each file should have at least the "copyright" line and a pointer to where the full notice is found. Copyright (C) This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA Also add information on how to contact you by electronic and paper mail. If the program is interactive, make it output a short notice like this when it starts in an interactive mode: Gnomovision version 69, Copyright (C) year name of author Gnomovision comes with ABSOLUTELY NO WARRANTY; for details type `show w'. This is free software, and you are welcome to redistribute it under certain conditions; type `show c' for details. The hypothetical commands `show w' and `show c' should show the appropriate parts of the General Public License. Of course, the commands you use may be called something other than `show w' and `show c'; they could even be mouse-clicks or menu items--whatever suits your program. You should also get your employer (if you work as a programmer) or your school, if any, to sign a "copyright disclaimer" for the program, if necessary. Here is a sample; alter the names: Yoyodyne, Inc., hereby disclaims all copyright interest in the program `Gnomovision' (which makes passes at compilers) written by James Hacker. , 1 April 1989 Ty Coon, President of Vice This General Public License does not permit incorporating your program into proprietary programs. If your program is a subroutine library, you may consider it more useful to permit linking proprietary applications with the library. If this is what you want to do, use the GNU Library General Public License instead of this License. ./CBFlib-0.9.2.2/doc/Idiffrn_scan.date_end.html0000644000076500007650000000511711603702115017364 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan.date_end

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_scan.date_end

    Name:
    '_diffrn_scan.date_end'

    Definition:

            The date and time of the end of the scan.  Note that this
                   may be an estimate generated during the scan, before the
                   precise time of the end of the scan is known.
    
    

    Type: yyyy-mm-dd

    Mandatory item: no

    Category: diffrn_scan

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_scan.date_start.html0000644000076500007650000000470211603702115017752 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan.date_start

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_scan.date_start

    Name:
    '_diffrn_scan.date_start'

    Definition:

            The date and time of the start of the scan.
    
    

    Type: yyyy-mm-dd

    Mandatory item: no

    Category: diffrn_scan

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Iarray_structure_list_axis.reference_angle.html0000644000076500007650000000560611603702115023771 0ustar yayayaya (IUCr) CIF Definition save__array_structure_list_axis.reference_angle

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _array_structure_list_axis.reference_angle

    Name:
    '_array_structure_list_axis.reference_angle'

    Definition:

            The value of _array_structure_list_axis.reference_angle
                   specifies the setting of the angle of this axis used for
                   determining a reference beam center and a reference detector
                   distance.  It is normally expected to be identical to the
                   value of _array_structure_list.angle.
    
    
    

    Type: float

    Mandatory item: implicit

    Category: array_structure_list_axis

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Iarray_intensities.scaling.html0000644000076500007650000000517411603702115020524 0ustar yayayaya (IUCr) CIF Definition save__array_intensities.scaling

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _array_intensities.scaling

    Name:
    '_array_intensities.scaling'

    Definition:

            Multiplicative scaling value to be applied to array data
                   in the manner described by item
                   _array_intensities.linearity.
    
    

    Type: float

    Mandatory item: no

    Category: array_intensities

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Imap_segment.mask_array_id.html0000644000076500007650000000711011603702115020444 0ustar yayayaya (IUCr) CIF Definition save__map_segment.mask_array_id

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _map_segment.mask_array_id

    Name:
    '_map_segment.mask_array_id'

    Definition:

           The value of _map_segment.mask_array_id, if given, the array
                  structure into which the mask for the map is organized.  If no
                  value is given, then all elements of the map are valid.  If a
                  value is given, then only elements of the map for which the
                  corresponding element of the mask is non-zero are valid.  The
                  value of _map_segment.mask_array_id differs from the value of
                  _map_segment.array_id in order to permit the mask to be given
                  as, say, unsigned 8-bit integers, while the map is given as
                  a data type with more range.  However, the two array structures
                  must be aligned, using the same axes in the same order with the
                  same displacements and increments
    
                  This item is a pointer to _array_structure.id in the
                  ARRAY_STRUCTURE category.
    
    

    Type: code

    Mandatory item: implicit

    Category: map_segment

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_frame_data.binary_id.html0000644000076500007650000000524411603702115020721 0ustar yayayaya (IUCr) CIF Definition save__diffrn_frame_data.binary_id

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_frame_data.binary_id

    Name:
    '_diffrn_frame_data.binary_id'

    Definition:

           This item is a pointer to _array_data.binary_id in the
                  ARRAY_STRUCTURE category.
    
                  DEPRECATED -- DO NOT USE
    
    

    Type: int

    Mandatory item: implicit

    Category: diffrn_frame_data

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_frame_data.id.html0000644000076500007650000000513511603702115017354 0ustar yayayaya (IUCr) CIF Definition save__diffrn_frame_data.id

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_frame_data.id

    Name:
    '_diffrn_frame_data.id'

    Definition:

           The value of _diffrn_frame_data.id must uniquely identify
                  each complete frame of data.
    
                  DEPRECATED -- DO NOT USE
    
    

    Type: code

    Mandatory item: yes

    Category: diffrn_frame_data

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Iarray_element_size.size.html0000644000076500007650000000515711603702115020204 0ustar yayayaya (IUCr) CIF Definition save__array_element_size.size

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _array_element_size.size

    Name:
    '_array_element_size.size'

    Definition:

            The size in metres of an image element in this
                   dimension. This supposes that the elements are arranged
                   on a regular grid.
    
    

    Type: float

    Mandatory item: yes


    The permitted range is [0.0, infinity)

    Category: array_element_size

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/cif_img_1.3.2_22Jun05.html0000644000076500007650000071257411603702115016514 0ustar yayayaya cif_img.dic v1.3.2

    # [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib] #

    # imgCIF/CBF #

    # Extensions Dictionary #

    ##############################################################################
    #                                                                            #
    #                       Image CIF Dictionary (imgCIF)                        #
    #             and Crystallographic Binary File Dictionary (CBF)              #
    #            Extending the Macromolecular CIF Dictionary (mmCIF)             #
    #                                                                            #
    #                              Version 1.3.2                                 #
    #                              of 2005-06-22                                 #
    #                                                                            #
    #     by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook    #
    #                                                                            #
    # This dictionary was adapted from format discussed at the imgCIF Workshop,  #
    # held at BNL Oct 1997 and the Crystallographic Binary File Format Draft     #
    # Proposal by Andrew Hammersley.  The first DDL 2.1 Version was created by   #
    # John Westbrook.  This version was drafted by Herbert J. Bernstein and      #
    # incorporates comments by I. David Brown, John Westbrook, Brian McMahon,    #
    # Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li, Gotzon Madariaga,         #
    # Frances C. Bernstein and others.                                           #
    ##############################################################################
                                                                        
    data_cif_img.dic
    
        _dictionary.title           cif_img.dic
        _dictionary.version         1.3.2
        _dictionary.datablock_id    cif_img.dic
    
    ##############################################################################
    #    CONTENTS
    #
    #        CATEGORY_GROUP_LIST
    #
    #        category  ARRAY_DATA
    #
    #                  _array_data.array_id
    #                  _array_data.binary_id
    #                  _array_data.data
    #
    #        category  ARRAY_ELEMENT_SIZE
    #        
    #                  _array_element_size.array_id
    #                  _array_element_size.index
    #                  _array_element_size.size
    #        
    #        category  ARRAY_INTENSITIES
    #        
    #                  _array_intensities.array_id
    #                  _array_intensities.binary_id
    #                  _array_intensities.gain
    #                  _array_intensities.gain_esd
    #                  _array_intensities.linearity
    #                  _array_intensities.offset
    #                  _array_intensities.scaling
    #                  _array_intensities.overload
    #                  _array_intensities.undefined_value
    #        
    #        category  ARRAY_STRUCTURE
    #        
    #                  _array_structure.byte_order
    #                  _array_structure.compression_type
    #                  _array_structure.encoding_type
    #                  _array_structure.id
    #        
    #        category  ARRAY_STRUCTURE_LIST
    #        
    #                  _array_structure_list.axis_set_id
    #                  _array_structure_list.array_id
    #                  _array_structure_list.dimension
    #                  _array_structure_list.direction
    #                  _array_structure_list.index
    #                  _array_structure_list.precedence
    #
    #        category  ARRAY_STRUCTURE_LIST_AXIS
    #        
    #                  _array_structure_list_axis.axis_id
    #                  _array_structure_list_axis.axis_set_id
    #                  _array_structure_list_axis.angle
    #                  _array_structure_list_axis.angle_increment
    #                  _array_structure_list_axis.displacement_increment
    #                  _array_structure_list_axis.angular_pitch
    #                  _array_structure_list_axis.radial_pitch
    #
    #        category  AXIS
    #        
    #                  _axis.depends_on
    #                  _axis.equipment
    #                  _axis.id
    #                  _axis.offset[1]
    #                  _axis.offset[2]
    #                  _axis.offset[3]
    #                  _axis.type
    #                  _axis.vector[1]
    #                  _axis.vector[2]
    #                  _axis.vector[3]
    #
    #        category  DIFFRN_DATA_FRAME
    #
    #                  _diffrn_data_frame.array_id
    #                  _diffrn_data_frame.binary_id
    #                  _diffrn_data_frame.detector_element_id
    #                  _diffrn_data_frame.id
    #
    #        category  DIFFRN_DETECTOR
    #        
    #                  _diffrn_detector.details
    #                  _diffrn_detector.detector
    #                  _diffrn_detector.diffrn_id
    #                  _diffrn_detector.dtime
    #                  _diffrn_detector.id
    #                  _diffrn_detector.number_of_axes
    #                  _diffrn_detector.type
    #
    #        category  DIFFRN_DETECTOR_AXIS
    #        
    #                  _diffrn_detector_axis.axis_id
    #                  _diffrn_detector_axis.detector_id    
    #        
    #        category  DIFFRN_DETECTOR_ELEMENT
    #
    #                  _diffrn_detector_element.center[1]
    #                  _diffrn_detector_element.center[2]
    #                  _diffrn_detector_element.id
    #                  _diffrn_detector_element.detector_id
    #        
    #        category  DIFFRN_MEASUREMENT
    #        
    #                  _diffrn_measurement.diffrn_id
    #                  _diffrn_measurement.details
    #                  _diffrn_measurement.device
    #                  _diffrn_measurement.device_details
    #                  _diffrn_measurement.device_type
    #                  _diffrn_measurement.id
    #                  _diffrn_measurement.method
    #                  _diffrn_measurement.number_of_axes
    #                  _diffrn_measurement.specimen_support
    #
    #        category  DIFFRN_MEASUREMENT_AXIS
    #        
    #                  _diffrn_measurement_axis.axis_id
    #                  _diffrn_measurement_axis.measurement_device
    #                  _diffrn_measurement_axis.measurement_id
    #
    #        category  DIFFRN_RADIATION
    #
    #                  _diffrn_radiation.collimation
    #                  _diffrn_radiation.diffrn_id
    #                  _diffrn_radiation.div_x_source
    #                  _diffrn_radiation.div_y_source
    #                  _diffrn_radiation.div_x_y_source
    #                  _diffrn_radiation.filter_edge'
    #                  _diffrn_radiation.inhomogeneity
    #                  _diffrn_radiation.monochromator
    #                  _diffrn_radiation.polarisn_norm
    #                  _diffrn_radiation.polarisn_ratio
    #                  _diffrn_radiation.polarizn_source_norm
    #                  _diffrn_radiation.polarizn_source_ratio
    #                  _diffrn_radiation.probe
    #                  _diffrn_radiation.type
    #                  _diffrn_radiation.xray_symbol
    #                  _diffrn_radiation.wavelength_id
    #        
    #        category  DIFFRN_REFLN
    #        
    #                  _diffrn_refln.frame_id
    #
    #        category  DIFFRN_SCAN
    #        
    #                  _diffrn_scan.id
    #                  _diffrn_scan.date_end
    #                  _diffrn_scan.date_start
    #                  _diffrn_scan.integration_time
    #                  _diffrn_scan.frame_id_start
    #                  _diffrn_scan.frame_id_end
    #                  _diffrn_scan.frames
    #
    #        category  DIFFRN_SCAN_AXIS
    #        
    #                  _diffrn_scan_axis.axis_id
    #                  _diffrn_scan_axis.angle_start
    #                  _diffrn_scan_axis.angle_range
    #                  _diffrn_scan_axis.angle_increment
    #                  _diffrn_scan_axis.angle_rstrt_incr
    #                  _diffrn_scan_axis.displacement_start
    #                  _diffrn_scan_axis.displacement_range
    #                  _diffrn_scan_axis.displacement_increment
    #                  _diffrn_scan_axis.displacement_rstrt_incr
    #                  _diffrn_scan_axis.scan_id
    #
    #        category  DIFFRN_SCAN_FRAME
    #        
    #                  _diffrn_scan_frame.date
    #                  _diffrn_scan_frame.frame_id
    #                  _diffrn_scan_frame.frame_number
    #                  _diffrn_scan_frame.integration_time
    #                  _diffrn_scan_frame.scan_id
    #
    #        category  DIFFRN_SCAN_FRAME_AXIS
    #        
    #                  _diffrn_scan_frame_axis.axis_id
    #                  _diffrn_scan_frame_axis.angle
    #                  _diffrn_scan_frame_axis.angle_increment
    #                  _diffrn_scan_frame_axis.angle_rstrt_incr
    #                  _diffrn_scan_frame_axis.displacement
    #                  _diffrn_scan_frame_axis.displacement_increment
    #                  _diffrn_scan_frame_axis.displacement_rstrt_incr
    #                  _diffrn_scan_frame_axis.frame_id
    #
    #       ***DEPRECATED*** data items
    #
    #                  _diffrn_detector_axis.id
    #                  _diffrn_measurement_axis.id
    #
    #       ***DEPRECATED*** category  DIFFRN_FRAME_DATA
    #
    #                  _diffrn_frame_data.array_id
    #                  _diffrn_frame_data.binary_id
    #                  _diffrn_frame_data.detector_element_id
    #                  _diffrn_frame_data.id
    #
    #
    #        ITEM_TYPE_LIST
    #        ITEM_UNITS_LIST
    #        DICTIONARY_HISTORY
    #
    ##############################################################################
    
    
    #########################
    ## CATEGORY_GROUP_LIST ##
    #########################
    
         loop_
        _category_group_list.id
        _category_group_list.parent_id
        _category_group_list.description
                 'inclusive_group'   .
    ;             Categories that belong to the dictionary extension.
    ;
                 'array_data_group'
                 'inclusive_group'
    ;             Categories that describe array data.
    ;
                 'axis_group'
                 'inclusive_group'
    ;             Categories that describe axes.
    ;
                 'diffrn_group'
                 'inclusive_group'
    ;            Categories that describe details of the diffraction experiment.
    ;
    
    
    
    
    ##############
    # ARRAY_DATA #
    ##############
    
      
    save_ARRAY_DATA
        _category.description
    ;
         Data items in the ARRAY_DATA category are the containers for
         the array data items described in category ARRAY_STRUCTURE.
    ;
        _category.id                   array_data
        _category.mandatory_code       no
         loop_
        _category_key.name             '_array_data.array_id'
                                       '_array_data.binary_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 -
    
            This example shows two binary data blocks.  The first one
            was compressed by the CBF_CANONICAL compression algorithm and
            presented as hexadecimal data.  The first character "H" on the
            data lines means hexadecimal.  It could have been "O" for octal
            or "D" for decimal.  The second character on the line shows
            the number of bytes in each word (in this case "4"), which then
            requires 8 hexadecimal digits per word.  The third character
            gives the order of octets within a word, in this case "<"
            for the ordering 4321 (i.e. "big-endian").  Alternatively the
            character ">" could have been used for the ordering 1234
            (i.e. "little-endian").  The block has a "message digest"
            to check the integrity of the data.
    
            The second block is similar, but uses CBF_PACKED compression
            and BASE64 encoding.  Note that the size and the digest are
            different.
    ;
    ;
    
            loop_
            _array_data.array_id
            _array_data.binary_id
            _array_data.data
            image_1 1
            ;
            --CIF-BINARY-FORMAT-SECTION--
            Content-Type: application/octet-stream;
                 conversions="x-CBF_CANONICAL"
            Content-Transfer-Encoding: X-BASE16
            X-Binary-Size: 3927126
            X-Binary-ID: 1
            Content-MD5: u2sTJEovAHkmkDjPi+gWsg==
    
            # Hexadecimal encoding, byte 0, byte order ...21
            #
            H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ...
            ....
            --CIF-BINARY-FORMAT-SECTION----
            ;
            image_2 2
            ;
            --CIF-BINARY-FORMAT-SECTION--
            Content-Type: application/octet-stream;
                 conversions="x-CBF-PACKED"
            Content-Transfer-Encoding: BASE64
            X-Binary-Size: 3745758
            X-Binary-ID: 2
            Content-MD5: 1zsJjWPfol2GYl2V+QSXrw==
    
            ELhQAAAAAAAA...
            ...
            --CIF-BINARY-FORMAT-SECTION----
            ;
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    save_
    
    
    save__array_data.array_id
        _item_description.description
    ;             This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category. 
    ;
        _item.name                  '_array_data.array_id'
        _item.category_id             array_data
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__array_data.binary_id
        _item_description.description
    ;             This item is an integer identifier which, along with
                  '_array_data.array_id' should uniquely identify the 
                  particular block of array data.
                  
                  If '_array_data.binary_id' is not explicitly given,
                  it defaults to 1.
                  
                  The value of '_array_data.binary_id' distinguishes
                  among multiple sets of data with the same array
                  structure.
                  
                  If the MIME header of the data array specifies a 
                  value for X-Binary-Id, the value of  '_array_data.binary_id'
                  should be equal the value given for X-Binary-Id.
    ;
         loop_
        _item.name                  
        _item.category_id             
        _item.mandatory_code          
                 '_array_data.binary_id'            array_data      
                                                                    implicit
                 '_diffrn_data_frame.binary_id'     diffrn_data_frame
                                                                    implicit
                 '_array_intensities.binary_id'     array_intensities
                                                                    implicit
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_data_frame.binary_id'     '_array_data.binary_id'
                 '_array_intensities.binary_id'     '_array_data.binary_id'
    
        _item_default.value           1
        _item_type.code               int
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                1  1
                                .  1
         save_
    
    
    save__array_data.data
        _item_description.description
    ;             The value of '_array_data.data' contains the array data 
                  encapsulated in a STAR string.
                  
                  The representation used is a variant on the
                  Multipurpose Internet Mail Extensions (MIME) specified
                  in RFC 2045-2049 by N. Freed et al.  The boundary
                  delimiter used in writing an imgCIF or CBF is
                  "--CIF-BINARY-FORMAT-SECTION--" (including the
                  required initial "--").
    
                  The Content-Type may be any of the discrete types permitted
                  in RFC 2045; "application/octet-stream" is recommended.  
                  If an octet stream was compressed, the compression should 
                  be specified by the parameter 'conversions="x-CBF_PACKED"' 
                  or the parameter 'conversions="x-CBF_CANONICAL"'.
                  
                  The Content-Transfer-Encoding may be "BASE64",
                  "Quoted-Printable", "X-BASE8", "X-BASE10", or
                  "X-BASE16" for an imgCIF or "BINARY" for a CBF.  The
                  octal, decimal and hexadecimal transfer encodings are
                  for convenience in debugging, and are not recommended
                  for archiving and data interchange.
                  
                  In an imgCIF file, the encoded binary data begins after
                  the empty line terminating the header.  In a CBF, the
                  raw binary data begins after an empty line terminating
                  the header and after the sequence:
                        
                  Octet   Hex   Decimal  Purpose
                    0     0C       12    (ctrl-L) Page break
                    1     1A       26    (ctrl-Z) Stop listings in MS-DOS
                    2     04       04    (Ctrl-D) Stop listings in UNIX
                    3     D5      213    Binary section begins
    
                  None of these octets are included in the calculation of
                  the message size, nor in the calculation of the
                  message digest.
                                 
                  The X-Binary-Size header specifies the size of the
                  equivalent binary data in octets.  If compression was
                  used, this size is the size after compression, including
                  any book-keeping fields.  An adjustment is made for
                  the deprecated binary formats in which 8 bytes of binary
                  header are used for the compression type.  In that case,
                  the 8 bytes used for the compression type is subtracted
                  from the size, so that the same size will be reported
                  if the compression type is supplied in the MIME header.
                  Use of the MIME header is the recommended way to
                  supply the compression type.  In general, no portion of
                  the  binary header is included in the calculation of the size.
    
                  The X-Binary-Element-Type header specifies the type of
                  binary data in the octets, using the same descriptive
                  phrases as in '_array_structure.encoding_type'.  The default
                  value is "unsigned 32-bit integer".
                  
                  An MD5 message digest may, optionally, be used. The "RSA Data
                  Security, Inc. MD5 Message-Digest Algorithm" should be used.
                  No portion of the header is included in the calculation of the
                  message digest.
    
                  If the Transfer Encoding is "X-BASE8", "X-BASE10", or
                  "X-BASE16", the data is presented as octal, decimal or
                  hexadecimal data organized into lines or words.  Each word
                  is created by composing octets of data in fixed groups of
                  2, 3, 4, 6 or 8 octets, either in the order ...4321 ("big-
                  endian") or 1234... (little-endian).  If there are fewer
                  than the specified number of octets to fill the last word,
                  then the missing octets are presented as "==" for each
                  missing octet.  Exactly two equal signs are used for each
                  missing octet even for octal and decimal encoding.
                  The format of lines is:
    
                  rnd xxxxxx xxxxxx xxxxxx
    
                  where r is "H", "O", or "D" for hexadecimal, octal or
                  decimal, n is the number of octets per word. and d is "<"
                  for ">" for the "...4321" and "1234..." octet orderings
                  respectively.  The "==" padding for the last word should
                  be on the appropriate side to correspond to the missing
                  octets, e.g.
    
                  H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000
    
                  or
    
                  H3> FF0700 00====
    
                  For these hex, octal and decimal formats, only, comments
                  beginning with "#" are permitted to improve readability.
    
                  BASE64 encoding follows MIME conventions.  Octets are
                  in groups of three, c1, c2, c3.  The resulting 24 bits 
                  are broken into four 6-bit quantities, starting with 
                  the high-order six bits (c1 >> 2) of the first octet, then
                  the low-order two bits of the first octet followed by the
                  high-order 4 bits of the second octet ((c1 & 3)<<4 | (c2>>4)),
                  then the bottom 4 bits of the second octet followed by the
                  high order two bits of the last octet ((c2 & 15)<<2 | (c3>>6)),
                  then the bottom six bits of the last octet (c3 & 63).  Each
                  of these four quantities is translated into an ASCII character
                  using the mapping:
    
                            1         2         3         4         5         6
                  0123456789012345678901234567890123456789012345678901234567890123
                  |         |         |         |         |         |         |
                  ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/
    
                  With short groups of octets padded on the right with one "="
                  if c3 is missing, and with "==" if both c2 and c3 are missing.
    
                  QUOTED-PRINTABLE encoding also follows MIME conventions, copying
                  octets without translation if their ASCII values are 32..38,
                  42, 48..57, 59..60, 62, 64..126 and the octet is not a ";"
                  in column 1.  All other characters are translated to =nn, where
                  nn is the hexadecimal encoding of the octet.  All lines are
                  "wrapped" with a terminating "=" (i.e. the MIME conventions
                  for an implicit line terminator are never used).
    ;
        _item.name                  '_array_data.data'
        _item.category_id             array_data
        _item.mandatory_code          yes
        _item_type.code               binary
    save_
    
    
    ######################
    # ARRAY_ELEMENT_SIZE #
    ######################
    
    
    save_ARRAY_ELEMENT_SIZE
        _category.description
    ;
         Data items in the ARRAY_ELEMENT_SIZE category record the physical 
         size of array elements along each array dimension.
    ;
        _category.id                   array_element_size
        _category.mandatory_code       no
         loop_
        _category_key.name             '_array_element_size.array_id'
                                       '_array_element_size.index'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 - A regular 2D array with a uniform element dimension
                        of 1220 nanometres.
    ;
    ;
            loop_
           _array_element_size.array_id  
           _array_element_size.index
           _array_element_size.size
            image_1   1    1.22e-6
            image_1   2    1.22e-6
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_element_size.array_id
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category. 
    ;
        _item.name                  '_array_element_size.array_id'
        _item.category_id             array_element_size
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__array_element_size.index
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure_list.index' in
                  the ARRAY_STRUCTURE_LIST category. 
    ;
        _item.name                  '_array_element_size.index'
        _item.category_id             array_element_size
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__array_element_size.size
        _item_description.description
    ;
                   The size in metres of an image element in this 
                   dimension. This supposes that the elements are arranged
                   on a regular grid.
    ;
        _item.name               '_array_element_size.size'
        _item.category_id          array_element_size
        _item.mandatory_code       yes 
        _item_type.code            float
        _item_units.code           'metres'
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0.0
         save_
    
    
    #####################
    # ARRAY_INTENSITIES #
    #####################
    
    
    save_ARRAY_INTENSITIES
        _category.description
    ;
                  Data items in the ARRAY_INTENSITIES category record the
                  information required to recover the intensity data from 
                  the set of data values stored in the ARRAY_DATA category.
    
                  The actual detector may have a complex relationship
                  between the raw intensity values and the number of
                  incident photons.  In most cases, the number stored
                  in the final array will have a simple linear relationship
                  to the actual number of incident photons, given by
                  '_array_intensities.gain'.  If raw, uncorrected values
                  are presented (e.g for calibration experiments), the
                  value of '_array_intensities.linearity' will be 'raw'
                  and '_array_intensities.gain' will not be used.
    
    ;
        _category.id                   array_intensities
        _category.mandatory_code       no
        loop_
        _category_key.name             '_array_intensities.array_id'
                                       '_array_intensities.binary_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1
    ;
    ;
            loop_
            _array_intensities.array_id
            _array_intensities.linearity 
            _array_intensities.gain      
            _array_intensities.overload  
            _array_intensities.undefined_value 
            image_1   linear  1.2    655535   0
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_intensities.array_id
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category. 
    ;
        _item.name                  '_array_intensities.array_id'
        _item.category_id             array_intensities
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__array_intensities.binary_id
        _item_description.description
    ;             This item is a pointer to '_array_data.binary_id' in the
                  ARRAY_DATA category. 
    ;
        _item.name                  '_array_intensities.binary_id'
        _item.category_id             array_intensities
        _item.mandatory_code          implicit
        _item_type.code               int
         save_
    
    
    save__array_intensities.gain
        _item_description.description
    ;              
                   Detector "gain". The factor by which linearized 
                   intensity count values should be divided to produce
                   true photon counts.
    ;
        _item.name              '_array_intensities.gain'
        _item.category_id          array_intensities
        _item.mandatory_code       yes
        _item_type.code            float
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0.0
        _item_units.code           'counts_per_photon'
         loop_
        _item_related.related_name
        _item_related.function_code  '_array_intensities.gain_esd'
                                     'associated_value'
        save_
    
      
    save__array_intensities.gain_esd
        _item_description.description
    ;              
                  The estimated standard deviation in detector "gain".
    ;
        _item.name              '_array_intensities.gain_esd'
        _item.category_id          array_intensities
        _item.mandatory_code       yes
        _item_type.code            float
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0.0
    
        _item_units.code          'counts_per_photon'
         loop_
        _item_related.related_name
        _item_related.function_code  '_array_intensities.gain'
                                     'associated_esd'
        save_
    
    
    save__array_intensities.linearity
        _item_description.description
    ;
                   The intensity linearity scaling used from raw intensity
                   to the stored element value:
    
                   'linear' is obvious
    
                   'offset'  means that the value defined by 
                   '_array_intensities.offset' should be added to each
                    element value.  
    
                   'scaling' means that the value defined by 
                   '_array_intensities.scaling' should be multiplied with each 
                   element value.  
    
                   'scaling_offset' is the combination of the two previous cases, 
                   with the scale factor applied before the offset value.
    
                   'sqrt_scaled' means that the square root of raw 
                   intensities multiplied by '_array_intensities.scaling' is
                   calculated and stored, perhaps rounded to the nearest 
                   integer. Thus, linearization involves dividing the stored
                   values by '_array_intensities.scaling' and squaring the 
                   result. 
    
                   'logarithmic_scaled' means that the logarithm based 10 of
                   raw intensities multiplied by '_array_intensities.scaling' 
                   is calculated and stored, perhaps rounded to the nearest 
                   integer. Thus, linearization involves dividing the stored
                   values by '_array_intensities.scaling' and calculating 10
                   to the power of this number.
    
                   'raw' means that the data is a set of raw values straight 
                   from the detector.
    ;
    
        _item.name               '_array_intensities.linearity'
        _item.category_id          array_intensities
        _item.mandatory_code       yes
        _item_type.code            code
         loop_
        _item_enumeration.value   
        _item_enumeration.detail   
                                  'linear' .
                                  'offset'           
    ;
                   The value defined by  '_array_intensities.offset' should 
                   be added to each element value.  
    ;
                                  'scaling'
    ;
                   The value defined by '_array_intensities.scaling' should be 
                   multiplied with each element value.  
    ;
                                  'scaling_offset'   
    ;
                   The combination of the scaling and offset 
                   with the scale factor applied before the offset value.
    ;
                                  'sqrt_scaled'      
    ;
                   The square root of raw intensities multiplied by 
                   '_array_intensities.scaling' is calculated and stored, 
                   perhaps rounded to the nearest integer. Thus, 
                   linearization involves dividing the stored
                   values by '_array_intensities.scaling' and squaring the 
                   result. 
    ;
                                  'logarithmic_scaled'
    ;
                   The logarithm based 10 of raw intensities multiplied by 
                   '_array_intensities.scaling'  is calculated and stored, 
                   perhaps rounded to the nearest integer. Thus, 
                   linearization involves dividing the stored values by 
                   '_array_intensities.scaling' and calculating 10 to the 
                   power of this number.
    ;
                                  'raw'
    ;
                   The array consists of raw values to which no corrections have
                   been applied.  While the handling of the data is similar to 
                   that given for 'linear' data with no offset, the meaning of 
                   the data differs in that the number of incident photons is 
                   not necessarily linearly related to the number of counts 
                   reported.  This value is intended for use either in 
                   calibration experiments or to allow for handling more 
                   complex data fitting algorithms than are allowed for by 
                   this data item.
    ;
    
        save_
      
      
    save__array_intensities.offset
        _item_description.description
    ;
                   Offset value to add to array element values in the manner
                   described by item '_array_intensities.linearity'.
    ;
        _item.name                 '_array_intensities.offset'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        save_
    
    
    save__array_intensities.scaling
        _item_description.description
    ;
                   Multiplicative scaling value to be applied to array data
                   in the manner described by item
                   '_array_intensities.linearity'.
    ;
        _item.name                 '_array_intensities.scaling'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        save_
    
    
    save__array_intensities.overload
        _item_description.description
    ;
                   The saturation intensity level for this data array.
    ;
        _item.name                 '_array_intensities.overload'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        _item_units.code          'counts'
        save_
    
      
    save__array_intensities.undefined_value
        _item_description.description
    ;
                   A value to be substituted for undefined values in 
                   the data array.
    ;
        _item.name                 '_array_intensities.undefined_value'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        save_
    
    
    ###################
    # ARRAY_STRUCTURE #
    ###################
    
    
    save_ARRAY_STRUCTURE
        _category.description
    ;
         Data items in the ARRAY_STRUCTURE category record the organization and 
         encoding of array data which may be stored in the ARRAY_DATA category.
    ;
        _category.id                   array_structure
        _category.mandatory_code       no
        _category_key.name             '_array_structure.id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 -
    ;
    ;
         loop_
        _array_structure.id 
        _array_structure.encoding_type        
        _array_structure.compression_type     
        _array_structure.byte_order           
         image_1       "unsigned 16-bit integer"  none  little_endian
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_structure.byte_order
        _item_description.description
    ;
                   The order of bytes for integer values which require more
                   than 1-byte. 
    
                   (IBM-PC's and compatibles, and Dec-Vaxes use low-byte-first
                   ordered integers, whereas Hewlett Packard 700 
                   series, Sun-4 and Silicon Graphics use high-byte-first
                   ordered integers.  Dec-Alphas can produce/use either
                   depending on a compiler switch.)
    ;
    
        _item.name                     '_array_structure.byte_order'
        _item.category_id               array_structure
        _item.mandatory_code            yes 
        _item_type.code                 code
         loop_
        _item_enumeration.value        
        _item_enumeration.detail        
                                       'big_endian'
    ;
            The first byte in the byte stream of the bytes which make up an 
            integer value is the most significant byte of an integer. 
    ;
                                       'little_endian'
    ;
            The last byte in the byte stream of the bytes which make up an 
            integer value is the most significant byte of an integer.
    ;
         save_
    
    
    save__array_structure.compression_type 
        _item_description.description
    ;
                  Type of data compression method used to compress the array
                  data. 
    ;
        _item.name                   '_array_structure.compression_type'
        _item.category_id             array_structure
        _item.mandatory_code          no 
        _item_type.code               code
        _item_default.value           'none'
         loop_
        _item_enumeration.value       
        _item_enumeration.detail
                                      'none'
    ;
            Data are stored in normal format as defined by 
            '_array_structure.encoding_type' and 
            '_array_structure.byte_order'.
    ;
                                      'byte_offsets'
    ;
            Using the compression scheme defined in CBF definition
            Section 5.0.
    ;
                                      'packed'
    ;
            Using the 'packed' compression scheme, a CCP4-style packing
            (CBFlib section 3.3.2)
    ;
                                      'canonical'
    ;
            Using the 'canonical' compression scheme (CBFlib section
            3.3.1)
    ;
        save_
    
    
    save__array_structure.encoding_type
        _item_description.description
    ;
                   Data encoding of a single element of array data. 
                   
                   In several cases, the IEEE format is referenced.
                   See "IEEE Standard for Binary Floating-Point Arithmetic",
                   ANSI/IEEE Std 754-1985, the Institute of Electrical and
                   Electronics Engineers, Inc., NY 1985.  
    ;
    
        _item.name                '_array_structure.encoding_type'
        _item.category_id          array_structure
        _item.mandatory_code       yes 
        _item_type.code            uline
         loop_
        _item_enumeration.value   
                                  'unsigned 8-bit integer'
                                  'signed 8-bit integer'
                                  'unsigned 16-bit integer'
                                  'signed 16-bit integer'
                                  'unsigned 32-bit integer'
                                  'signed 32-bit integer'
                                  'signed 32-bit real IEEE'
                                  'signed 64-bit real IEEE'
                                  'signed 32-bit complex IEEE'
         save_
    
    
    save__array_structure.id
        _item_description.description
    ;             The value of '_array_structure.id' must uniquely identify 
                  each item of array data. 
    ;
        loop_
        _item.name                  
        _item.category_id             
        _item.mandatory_code          
                 '_array_structure.id'              array_structure      yes
                 '_array_data.array_id'             array_data           yes
                 '_array_structure_list.array_id'   array_structure_list yes
                 '_array_intensities.array_id'      array_intensities    yes
                 '_diffrn_data_frame.array_id'      diffrn_data_frame    yes
    
    
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_array_data.array_id'             '_array_structure.id'
                 '_array_structure_list.array_id'   '_array_structure.id'
                 '_array_intensities.array_id'      '_array_structure.id'
                 '_diffrn_data_frame.array_id'      '_array_structure.id'
    
         save_
    
    
    ########################
    # ARRAY_STRUCTURE_LIST #
    ########################
    
    
    save_ARRAY_STRUCTURE_LIST
        _category.description
    ;
         Data items in the ARRAY_STRUCTURE_LIST category record the size 
         and organization of each array dimension.
    
         The relationship to physical axes may be given.
    ;
        _category.id                   array_structure_list
        _category.mandatory_code       no
         loop_
        _category_key.name             '_array_structure_list.array_id'
                                       '_array_structure_list.index'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 - An image array of 1300 x 1200 elements.  The raster 
                        order of the image is left-to-right (increasing) in the
                        first dimension and bottom-to-top (decreasing) in 
                        the second dimension.
    ;
    ;
            loop_
           _array_structure_list.array_id  
           _array_structure_list.index
           _array_structure_list.dimension 
           _array_structure_list.precedence 
           _array_structure_list.direction
           _array_structure_list.axis_set_id
            image_1   1    1300    1     increasing  ELEMENT_X
            image_1   2    1200    2     decreasing  ELEMENY_Y
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_structure_list.array_id
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category. 
    ;
        _item.name                  '_array_structure_list.array_id'
        _item.category_id             array_structure_list
        _item.mandatory_code          yes
        _item_type.code               code
    save_
    
    
    save__array_structure_list.axis_set_id
        _item_description.description
    ;              This is a descriptor for the physical axis or set of axes 
                   corresponding to an array index.
                   
                   This data item is related to the axes of the detector 
                   itself given in DIFFRN_DETECTOR_AXIS, but usually differ
                   in that the axes in this category are the axes of the
                   coordinate system of reported data points, while the axes in
                   DIFFRN_DETECTOR_AXIS are the physical axes 
                   of the detector describing the "poise" of the detector as an
                   overall physical object.
                   
                   If there is only one axis in the set, the identifier of 
                   that axis should be used as the identifier of the set.
                   
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
               '_array_structure_list.axis_set_id'
                                      array_structure_list            yes
               '_array_structure_list_axis.axis_set_id'
                                      array_structure_list_axis       implicit
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_array_structure_list_axis.axis_set_id'
                                   '_array_structure_list.axis_set_id'
    
    
         save_
    
    
    save__array_structure_list.dimension
        _item_description.description
    ;              
                   The number of elements stored in the array structure in this 
                   dimension.
    ;
        _item.name                '_array_structure_list.dimension'
        _item.category_id          array_structure_list
        _item.mandatory_code       yes 
        _item_type.code            int
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                1  1
                                .  1
         save_
    
    
    save__array_structure_list.direction
        _item_description.description
    ;
                  Identifies the direction in which this array index changes.
    ;
        _item.name                '_array_structure_list.direction'
        _item.category_id          array_structure_list
        _item.mandatory_code       yes 
        _item_type.code            int
         loop_
        _item_enumeration.value
        _item_enumeration.detail        
    
                                  'increasing'
    ;
             Indicates the index changes from 1 to the maximum dimension.
    ;
                                  'decreasing'
    ;
             Indicates the index changes from the maximum dimension to 1.
    ;
         save_
    
    
    save__array_structure_list.index
        _item_description.description
    ;              
                   Identifies the one-based index of the row or column in the
                   array structure.
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
               '_array_structure_list.index'        array_structure_list   yes
               '_array_structure_list.precedence'   array_structure_list   yes
               '_array_element_size.index'          array_element_size     yes
    
        _item_type.code            int
    
         loop_
        _item_linked.child_name
        _item_linked.parent_name
              '_array_element_size.index'         '_array_structure_list.index'
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                1  1
                                .  1
         save_
    
    
    save__array_structure_list.precedence
        _item_description.description
    ;
                   Identifies the rank order in which this array index changes 
                   with respect to other array indices.  The precedence of 1  
                   indicates the index which changes fastest.
    ;
        _item.name                '_array_structure_list.precedence'
        _item.category_id          array_structure_list
        _item.mandatory_code       yes 
        _item_type.code            int
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                1  1
                                .  1
         save_
    
    
    #############################
    # ARRAY_STRUCTURE_LIST_AXIS #
    #############################
    
    save_ARRAY_STRUCTURE_LIST_AXIS
        _category.description
    ;
         Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe
         the physical settings of sets axes for the centres of pixels that 
         correspond to data points described in the 
         ARRAY_STRUCTURE_LIST category. 
         
         In the simplest cases, the physical increments of a single axis correspond
         to the increments of a single array index.  More complex organizations,
         e.g. spiral scans, may require coupled motions along multiple axes.
         
         Note that a spiral scan uses two coupled axis, one for the angular 
         direction, one for the radial direction.  This differs from a 
         cylindrical scan for which the two axes are not coupled into one set.
         
    ;
        _category.id                   array_structure_list_axis
        _category.mandatory_code       no
         loop_
        _category_key.name
                                      '_array_structure_list_axis.axis_set_id'
                                      '_array_structure_list_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'array_data_group'
         save_
    
    
    save__array_structure_list_axis.axis_id
        _item_description.description
    ;
                   The value of this data item is the identifier of one of
                   the axes from the set of axes for which settings are being 
                   specified.
    
                   Multiple axes may be specified for the same value of
                   '_array_structure_list_axis.axis_set_id'
    
                   This item is a pointer to '_axis.id' in the
                   AXIS category.
    ;
        _item.name                 '_array_structure_list_axis.axis_id'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__array_structure_list_axis.axis_set_id
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   set of axes for which axis settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   '_array_structure_list_axis.axis_set_id'.
    
                   This item is a pointer to
                   '_array_structure_list.axis_set_id'
                   in the ARRAY_STRUCTURE_LIST category.
                   
                   If this item is not specified, it defaults to the corresponding
                   axis identifier.
    ;
        _item.name                 '_array_structure_list_axis.axis_set_id'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       implicit
        _item_type.code            code
         save_
    
    
    save__array_structure_list_axis.angle
        _item_description.description
    ;
                   The setting of the specified axis in degrees for the first
                   data point of the array index with the corresponding value
                   of '_array_structure_list.axis_set_id'.  If the index is
                   specified as 'increasing' this will be the centre of the
                   pixel with index value 1.  If the index is specified as
                   'decreasing' this will be the centre of the pixel with
                   maximum index value. 
    ;
        _item.name                 '_array_structure_list_axis.angle'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__array_structure_list_axis.angle_increment
        _item_description.description
    ;
                   The pixel-centre-to-pixel-centre increment in the angular 
                   setting of the specified axis in degrees.  This is not 
                   meaningful in the case of 'constant velocity' spiral scans  
                   and should not be specified in that case.  
    
                   See '_array_structure_list_axis.angular_pitch'.
                   
    ;
        _item.name                 '_array_structure_list_axis.angle_increment'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__array_structure_list_axis.displacement
        _item_description.description
    ;
                   The setting of the specified axis in millimetres for the first
                   data point of the array index with the corresponding value
                   of '_array_structure_list.axis_set_id'.  If the index is
                   specified as 'increasing' this will be the centre of the
                   pixel with index value 1.  If the index is specified as
                   'decreasing' this will be the centre of the pixel with
                   maximum index value. 
    
    ;
        _item.name               '_array_structure_list_axis.displacement'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__array_structure_list_axis.displacement_increment
        _item_description.description
    ;
                   The pixel-centre-to-pixel-centre increment for the displacement 
                   setting of the specified axis in millimetres.
                   
    ;
        _item.name                 
            '_array_structure_list_axis.displacement_increment'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
      
    
    save__array_structure_list_axis.angular_pitch
        _item_description.description
    ;
                   The pixel-centre-to-pixel-centre distance for a one step 
                   change in the setting of the specified axis in millimetres.
                   
                   This is meaningful only for 'constant velocity' spiral scans,
                   or for uncoupled angular scans at a constant radius
                   (cylindrical scan) and should not be specified for cases
                   in which the angle between pixels, rather than the distance
                   between pixels is uniform.
                   
                   See '_array_structure_list_axis.angle_increment'.
                   
    ;
        _item.name               '_array_structure_list_axis.angular_pitch'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
       
    
    save__array_structure_list_axis.radial_pitch
        _item_description.description
    ;
                   The radial distance from one "cylinder" of pixels to the
                   next in millimetres.  If the scan is a 'constant velocity'
                   scan with differing angular displacements between pixels,
                   the value of this item may differ significantly from the
                   value of '_array_structure_list_axis.displacement_increment'.
                   
    ;
        _item.name               '_array_structure_list_axis.radial_pitch'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
      
    
    
    ########
    # AXIS #
    ########
    
    save_AXIS
        _category.description
    ;
         Data items in the AXIS category record the information required
         to describe the various goniometer, detector, source and other
         axes needed to specify a data collection.  The location of each
         axis is specified by two vectors: the axis itself, given as a unit
         vector, and an offset to the base of the unit vector.  These vectors
         are referenced to a right-handed laboratory coordinate system with
         its origin in the sample or specimen:
         
                                 | Y (to complete right-handed system)
                                 |
                                 |
                                 |
                                 |
                                 |
                                 |________________X
                                /       principal goniometer axis
                               /
                              /
                             /
                            /
                           /Z (to source)
    
    
                                                          
         Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from
         the sample or specimen along the  principal axis of the goniometer.
         
         Axis 2 (Y): The Y-axis completes an orthogonal right-handed system
         defined by the X-axis and the Z-axis (see below).
         
         Axis 3 (Z): The Z-axis is derived from the source axis which goes from 
         the sample to the source.  The Z-axis is the component of the source axis
         in the direction of the source orthogonal to the X-axis in the plane 
         defined by the X-axis and the source axis.
              
         These axes are based on the goniometer, not on the orientation of the 
         detector, gravity, etc.  The vectors necessary to specify all other
         axes are given by sets of three components in the order (X, Y, Z).
         If the axis involved is a rotation axis, it is right handed, i.e. as
         one views the object to be rotated from the origin (the tail) of the 
         unit vector, the rotation is clockwise.  If a translation axis is
         specified, the direction of the unit vector specifies the sense of
         positive translation.
         
         Note:  This choice of coordinate system is similar to, but significantly
         different from the choice in MOSFLM (Andrew G.W. Leslie, Harry Powell,
         MRC Laboratory of Molecular Biology, Hills Road, Cambridge CB2 2QH, UK
         http://www.dl.ac.uk/CCP/CCP4/dist/x-windows/Mosflm/).  In MOSFLM,
         X is along the X-ray beam (the CBF/imgCIF Z axis) and Z is along the 
         rotation axis.
    
         All rotations are given in degrees and all translations are given in mm.
         
         Axes may be dependent on one another.  The X-axis is the only goniometer
         axis the direction of which is strictly connected to the hardware.  All
         other axes are specified by the positions they would assume when the
         axes upon which they depend are at their zero points.
         
         When specifying detector axes, the axis is given to the beam centre.
         The location of the beam centre on the detector should be given in the
         DIFFRN_DETECTOR category in distortion-corrected mm from the (0,0) corner
         of the detector.
         
         It should be noted that many different origins arise in the definition
         of an experiment.  In particular, as noted above, we need to specify the
         location of the beam centre on the detector in terms of the origin of the
         detector, which is, of course, not coincident with the centre of the
         sample.  
    ;
        _category.id                   axis
        _category.mandatory_code       no
         loop_
        _category_key.name          '_axis.id' 
                                    '_axis.equipment'               
         loop_
        _category_group.id           'inclusive_group'
                                     'axis_group'
                                     'diffrn_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 -
            
            This example shows the axis specification of the axes of a kappa
            geometry goniometer (See "X-Ray Structure Determination, A Practical
            Guide", 2nd ed. by  G. H. Stout, L. H. Jensen, Wiley Interscience,
            1989, 453 pp, p 134.).
            
            There are three axes specified, and no offsets.  The outermost axis,
            omega, is pointed along the X-axis.  The next innermost axis, kappa,
            is at a 50 degree angle to the X-axis, pointed away from the source.
            The innermost axis, phi, aligns with the X-axis when omega and
            phi are at their zero-points.  If T-omega, T-kappa and T-phi
            are the transformation matrices derived from the axis settings,
            the complete transformation would be:
                x' = (T-omega) (T-kappa) (T-phi) x
    ;
    ;
             loop_
            _axis.id
            _axis.type
            _axis.equipment
            _axis.depends_on
            _axis.vector[1] _axis.vector[2] _axis.vector[3]
            omega rotation goniometer     .    1        0        0
            kappa rotation goniometer omega    -.64279  0       -.76604
            phi   rotation goniometer kappa    1        0        0   
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 2 -
            
            This example show the axis specification of the axes of a
            detector, source and gravity.  We have juggled the order as a
            reminder that the ordering of presentation of tokens is not
            significant.  We have taken the centre of rotation of the detector
            to be 68 millimetres in the direction away from the source.
    ;
    ;
            loop_
            _axis.id
            _axis.type
            _axis.equipment
            _axis.depends_on
            _axis.vector[1] _axis.vector[2] _axis.vector[3]
            _axis.offset[1] _axis.offset[2] _axis.offset[3]
            source       .        source     .       0     0     1   . . .
            gravity      .        gravity    .       0    -1     0   . . .
            tranz     translation detector rotz      0     0     1   0 0 -68
            twotheta  rotation    detector   .       1     0     0   . . .
            roty      rotation    detector twotheta  0     1     0   0 0 -68
            rotz      rotation    detector roty      0     0     1   0 0 -68
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__axis.depends_on
        _item_description.description
    ;             The value of '_axis.depends_on' specifies the next outermost
                  axis upon which this axis depends.
                  
                  This item is a pointer to '_axis.id' in the same category.
    ;
        _item.name                      '_axis.depends_on'
        _item.category_id                 axis
        _item.mandatory_code              no
    
         save_
    
    
    save__axis.equipment
        _item_description.description
    ;             The value of  '_axis.equipment' specifies the type of
                  equipment using the axis:  'goniometer', 'detector',
                  'gravity', 'source' or 'general'.
    ;
        _item.name                      '_axis.equipment'
        _item.category_id                 axis
        _item.mandatory_code              no
        _item_type.code                   ucode
        _item_default.value               general
         loop_
        _item_enumeration.value
        _item_enumeration.detail   goniometer
                                  'equipment used to orient or position samples'
                                   detector
                                  'equipment used to detect reflections'
                                   general
                                  'equipment used for general purposes'
                                   gravity
                                  'axis specifying the downward direction'
                                   source
                                  'axis specifying the direction sample to source'
    
         save_
    
    
    save__axis.offset[1]
        _item_description.description
    ;              The [1] element of the 3-element vector used to specify
                   the offset to the base of a rotation or translation axis.
                   
                   The vector is specified in millimetres
    ;
        _item.name                  '_axis.offset[1]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    
    save__axis.offset[2]
        _item_description.description
    ;              The [2] element of the 3-element vector used to specify
                   the offset to the base of a rotation or translation axis.
                   
                   The vector is specified in millimetres
    ;
        _item.name                  '_axis.offset[2]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    
    save__axis.offset[3]
        _item_description.description
    ;              The [3] element of the 3-element vector used to specify
                   the offset to the base of a rotation or translation axis.
                   
                   The vector is specified in millimetres
    ;
        _item.name                  '_axis.offset[3]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    
    save__axis.id
        _item_description.description
    ;             The value of '_axis.id' must uniquely identify
                  each axis relevant to the experiment.  Note that multiple
                  pieces of equipment may share the same axis (e.g. a twotheta
                  arm), so that the category key for AXIS also includes the
                  equipment.
    ;
        loop_
        _item.name
        _item.category_id
        _item.mandatory_code
             '_axis.id'                         axis                    yes
             '_array_structure_list_axis.axis_id'
                                                array_structure_list_axis
                                                                        yes
             '_diffrn_detector_axis.axis_id'    diffrn_detector_axis    yes
             '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes
             '_diffrn_scan_axis.axis_id'        diffrn_scan_axis        yes
             '_diffrn_scan_frame_axis.axis_id'  diffrn_scan_frame_axis  yes
    
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
             '_axis.depends_on'                   '_axis.id'
             '_array_structure_list_axis.axis_id' '_axis.id'
             '_diffrn_detector_axis.axis_id'      '_axis.id'
             '_diffrn_measurement_axis.axis_id'   '_axis.id'
             '_diffrn_scan_axis.axis_id'          '_axis.id'      
             '_diffrn_scan_frame_axis.axis_id'    '_axis.id'
    
         save_
    
    
    save__axis.type
        _item_description.description
    ;             The value of '_axis.type' specifies the type of
                  axis:  'rotation', 'translation' (or 'general' when
                  the type is not relevant, as for gravity).
    ;
        _item.name                      '_axis.type'
        _item.category_id                 axis
        _item.mandatory_code              no
        _item_type.code                   ucode
        _item_default.value               general
         loop_
        _item_enumeration.value
        _item_enumeration.detail      rotation
                                     'right-handed axis of rotation'
                                      translation
                                     'translation in the direction of the axis'
                                      general
                                     'axis for which the type is not relevant'
    
         save_
    
    
    save__axis.vector[1]
        _item_description.description
    ;              The [1] element of the 3-element vector used to specify
                   the direction of a rotation or translation axis.
                   The vector should be normalized to be a unit vector and
                   is dimensionless.
    ;
        _item.name                  '_axis.vector[1]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
         save_
    
    save__axis.vector[2]
        _item_description.description
    ;              The [2] element of the 3-element vector used to specify
                   the direction of a rotation or translation axis.
                   The vector should be normalized to be a unit vector and
                   is dimensionless.
    ;
        _item.name                  '_axis.vector[2]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
         save_
    
    save__axis.vector[3]
        _item_description.description
    ;              The [3] element of the 3-element vector used to specify
                   the direction of a rotation or translation axis.
                   The vector should be normalized to be a unit vector and
                   is dimensionless.
    ;
        _item.name                  '_axis.vector[3]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
         save_
    
    
    
    #####################
    # DIFFRN_DATA_FRAME #
    #####################
    
    
    save_DIFFRN_DATA_FRAME
        _category.description
    ;
                  Data items in the DIFFRN_DATA_FRAME category record
                  the details about each frame of data. 
                  
                  The items in this category were previously in a
                  DIFFRN_FRAME_DATA category, which is now deprecated.
                  The items from the old category are provided
                  as aliases but should not be used for new work.
    ;
        _category.id                   diffrn_data_frame
        _category.mandatory_code       no
         loop_
        _category_key.name             '_diffrn_data_frame.id'
                                       '_diffrn_data_frame.detector_element_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 - A frame containing data from 4 frame elements.
                    Each frame element has a common array configuration
                    'array_1' described in ARRAY_STRUCTURE and related
                    categories.  The data for each detector element is 
                    stored in four groups of binary data in the
                    ARRAY_DATA category, linked by the array_id and
                    binary_id
    ;
    ;
            loop_
            _diffrn_data_frame.id
            _diffrn_data_frame.detector_element_id
            _diffrn_data_frame.array_id
            _diffrn_data_frame.binary_id
            frame_1   d1_ccd_1  array_1  1  
            frame_1   d1_ccd_2  array_1  2 
            frame_1   d1_ccd_3  array_1  3 
            frame_1   d1_ccd_4  array_1  4 
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
    
    
    save__diffrn_data_frame.array_id
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category. 
    ;
        _item.name                  '_diffrn_data_frame.array_id'
        _item.category_id             diffrn_data_frame
        _item.mandatory_code          yes
        _item_aliases.alias_name    '_diffrn_frame_data.array_id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0.00
        _item_type.code               code
         save_
    
    
    save__diffrn_data_frame.binary_id
        _item_description.description
    ;             This item is a pointer to '_array_data.binary_id' in the
                  ARRAY_DATA category. 
    ;
        _item.name                  '_diffrn_data_frame.binary_id'
        _item.category_id             diffrn_data_frame
        _item.mandatory_code          implicit
        _item_aliases.alias_name    '_diffrn_frame_data.binary_id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               int
         save_
    
    
    save__diffrn_data_frame.detector_element_id
        _item_description.description
    ;             
                   This item is a pointer to '_diffrn_detector_element.id'
                   in the DIFFRN_DETECTOR_ELEMENT category. 
    ;
        _item.name                  '_diffrn_data_frame.detector_element_id'
        _item.category_id             diffrn_data_frame
        _item.mandatory_code          yes
        _item_aliases.alias_name    '_diffrn_frame_data.detector_element_id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         save_
    
    
    save__diffrn_data_frame.id
        _item_description.description
    ;             
                  The value of '_diffrn_data_frame.id' must uniquely identify
                  each complete frame of data.
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
               '_diffrn_data_frame.id'        diffrn_data_frame  yes
               '_diffrn_refln.frame_id'       diffrn_refln       yes
               '_diffrn_scan.frame_id_start'  diffrn_scan        yes
               '_diffrn_scan.frame_id_end'    diffrn_scan        yes
               '_diffrn_scan_frame.frame_id'  diffrn_scan_frame  yes
               '_diffrn_scan_frame_axis.frame_id'  
                                              diffrn_scan_frame_axis
                                                                 yes
        _item_aliases.alias_name    '_diffrn_frame_data.id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_diffrn_refln.frame_id'        '_diffrn_data_frame.id'
               '_diffrn_scan.frame_id_start'   '_diffrn_data_frame.id'
               '_diffrn_scan.frame_id_end'     '_diffrn_data_frame.id'
               '_diffrn_scan_frame.frame_id'   '_diffrn_data_frame.id'
               '_diffrn_scan_frame_axis.frame_id'
                                               '_diffrn_data_frame.id'
         save_
    
    
    ##########################################################################
    #  The following is a restatement of the mmCIF DIFFRN_DETECTOR,          #
    #  DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for      #
    #  the CBF/imgCIF extensions                                             #
    ##########################################################################
    
    ###################
    # DIFFRN_DETECTOR #
    ###################
    
    
    save_DIFFRN_DETECTOR
        _category.description
    ;              Data items in the DIFFRN_DETECTOR category describe the 
                   detector used to measure the scattered radiation, including
                   any analyser and post-sample collimation.
    ;
        _category.id                  diffrn_detector
        _category.mandatory_code      no
         loop_
        _category_key.name          '_diffrn_detector.diffrn_id'
                                    '_diffrn_detector.id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 - based on PDB entry 5HVP and laboratory records for the
                    structure corresponding to PDB entry 5HVP
    ;
    ;
        _diffrn_detector.diffrn_id             'd1'
        _diffrn_detector.detector              'multiwire'
        _diffrn_detector.type                  'Siemens'
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__diffrn_detector.details
        _item_description.description
    ;              A description of special aspects of the radiation detector.
    ;
        _item.name                  '_diffrn_detector.details'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_detector_details'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code                   text
        _item_examples.case        'slow mode' 
         save_
    
    
    save__diffrn_detector.detector
        _item_description.description
    ;              The general class of the radiation detector.
    ;
        _item.name                  '_diffrn_detector.detector'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
         loop_
        _item_aliases.alias_name
        _item_aliases.dictionary
        _item_aliases.version       '_diffrn_radiation_detector'
                                      cifdic.c91
                                      1.0
                                    '_diffrn_detector'
                                      cif_core.dic
                                      2.0
        _item_type.code               text
         loop_
        _item_examples.case          'photographic film'
                                     'scintillation counter'
                                     'CCD plate'
                                     'BF~3~ counter'
         save_
    
    
    save__diffrn_detector.diffrn_id
        _item_description.description
    ;              This data item is a pointer to '_diffrn.id' in the DIFFRN
                   category.
    
                   The value of '_diffrn.id' uniquely defines a set of
                   diffraction data.
    ;
        _item.name                  '_diffrn_detector.diffrn_id'
        _item.mandatory_code          yes
         save_
    
    
    save__diffrn_detector.dtime
        _item_description.description
    ;              The deadtime in microseconds of the detectors used to
                   measure the diffraction intensities.
    ;
        _item.name                  '_diffrn_detector.dtime'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
         loop_
        _item_aliases.alias_name
        _item_aliases.dictionary
        _item_aliases.version       '_diffrn_radiation_detector_dtime'
                                      cifdic.c91
                                      1.0
                                    '_diffrn_detector_dtime'
                                      cif_core.dic
                                      2.0
         loop_  
        _item_range.maximum           
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
        _item_units.code              microseconds
         save_
    
    
    save__diffrn_detector.id
        _item_description.description
    ;             
                   The value of '_diffrn_detector.id' must uniquely identify
                   each detector used to collect each diffraction data set.
    
                   If the value of '_diffrn_detector.id' is not given, it is
                   implicitly equal to the value of
                   '_diffrn_detector.diffrn_id'
    ;
         loop_
        _item.name                 
        _item.category_id
        _item.mandatory_code
                 '_diffrn_detector.id'         diffrn_detector       implicit
                 '_diffrn_detector_axis.detector_id'
                                               diffrn_detector_axis       yes
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_detector_axis.detector_id'
                                             '_diffrn_detector.id'
    
        _item_type.code               code
         save_
    
    
    save__diffrn_detector.number_of_axes
        _item_description.description
    ;             
                   The value of '_diffrn_detector.number_of_axes' gives the 
                   number of axes of the positioner for the detector identified 
                   by '_diffrn_detector.id'.
                   
                   The word "positioner" is a general term used in
                   instrumentation design for devices that are used to change
                   the positions of portions of apparatus by linear
                   translation, rotation, or combinations of such motions.
                   
                   Axes which are used to provide a coordinate system for the
                   face of an area detetctor should not be counted for this
                   data item.
    
                   The description of each axis should be provided by entries 
                   in DIFFRN_DETECTOR_AXIS.
    ;
        _item.name                  '_diffrn_detector.number_of_axes'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
         loop_
        _item_range.maximum
        _item_range.minimum           .   1
                                      1   1
        _item_type.code               int
         save_
    
    
    save__diffrn_detector.type
        _item_description.description
    ;              The make, model or name of the detector device used.
    ;
        _item.name                  '_diffrn_detector.type'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_detector_type'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         save_
    
    
    ########################
    # DIFFRN_DETECTOR_AXIS #
    ########################
    
    
    save_DIFFRN_DETECTOR_AXIS
        _category.description
    ;
         Data items in the DIFFRN_DETECTOR_AXIS category associate
         axes with detectors.
    ;
        _category.id                   diffrn_detector_axis
        _category.mandatory_code       no
         loop_
        _category_key.name          '_diffrn_detector_axis.detector_id'
                                    '_diffrn_detector_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_detector_axis.axis_id
        _item_description.description
    ;
                   This data item is a pointer to '_axis.id' in
                   the AXIS category.
    ;
        _item.name                  '_diffrn_detector_axis.axis_id'
        _item.category_id             diffrn_detector_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_detector_axis.detector_id
        _item_description.description
    ;
                   This data item is a pointer to '_diffrn_detector.id' in
                   the DIFFRN_DETECTOR category.
    
                   This item was previously named '_diffrn_detector_axis.id'
                   which is now a deprecated name.  The old name is
                   provided as an alias but should not be used for new work.
    
    ;
        _item.name                  '_diffrn_detector_axis.detector_id'
        _item.category_id             diffrn_detector_axis
        _item.mandatory_code          yes
        _item_aliases.alias_name    '_diffrn_detector_axis.id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         save_
    
    
    ###########################
    # DIFFRN_DETECTOR_ELEMENT #
    ###########################
    
    
    save_DIFFRN_DETECTOR_ELEMENT
        _category.description
    ;
                  Data items in the DIFFRN_DETECTOR_ELEMENT category record
                  the details about spatial layout and other characteristics
                  of each element of a detector which may have multiple elements.
                  
                  In most cases, the more detailed information provided
                  in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS
                  are preferable to simply providing the centre.
    
    ;
        _category.id                   diffrn_detector_element
        _category.mandatory_code       no
         loop_
        _category_key.name             '_diffrn_detector_element.id'
                                       '_diffrn_detector_element.detector_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 - Detector d1 is composed of four CCD detector elements,
            each 200 mm by 200 mm, arranged in a square. in the pattern
                        
                       1     2
                          *
                       3     4
    
            Note that the beam centre is slightly displaced from each of the
            detector elements, just beyond the lower right corner of 1,
            the lower left corner of 2, the upper right corner of 3 and
            the upper left corner of 4.
    ;
    ;
            loop_
            _diffrn_detector_element.detector_id
            _diffrn_detector_element.id
            _diffrn_detector_element.center[1]
            _diffrn_detector_element.center[2]
            d1     d1_ccd_1  201.5 -1.5
            d1     d1_ccd_2  -1.8  -1.5
            d1     d1_ccd_3  201.6 201.4  
            d1     d1_ccd_4  -1.7  201.5
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
    
    
    save__diffrn_detector_element.center[1]
        _item_description.description
    ;             
                  The value of '_diffrn_detector_element.center[1]' is the X
                  component of the distortion-corrected beam-centre in mm from
                  the (0, 0) (lower left) corner of the detector element viewed
                  from the sample side.
                  
                  The X and Y axes are the laboratory coordinate system
                  coordinates defined in the AXIS category measured
                  when all positioning axes for the detector are at their zero
                  settings.  If the resulting X or Y axis is then orthogonal to the
                  detector, the Z axis is used instead of the orthogonal axis.
                  
    ;
        _item.name                  '_diffrn_detector_element.center[1]'
        _item.category_id             diffrn_detector_element
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
    
        save_
    
    
    save__diffrn_detector_element.center[2]
        _item_description.description
    ;             
                  The value of '_diffrn_detector_element.center[2]' is the Y
                  component of the distortion-corrected beam-centre in mm from
                  the (0, 0) (lower left) corner of the detector element viewed
                  from the sample side.
                  
                  The X and Y axes are the laboratory coordinate system
                  coordinates defined in the AXIS category measured
                  when all positioning axes for the detector are at their zero
                  settings.  If the resulting X or Y axis is then orthogonal to the
                  detector, the Z axis is used instead of the orthogonal axis.
    
    ;
        _item.name                  '_diffrn_detector_element.center[2]'
        _item.category_id             diffrn_detector_element
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
    
        save_
    
    
    save__diffrn_detector_element.id
        _item_description.description
    ;             
                  The value of '_diffrn_detector_element.id' must uniquely
                  identify each element of a detector.
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
               '_diffrn_detector_element.id'
               diffrn_detector_element
               yes
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_diffrn_data_frame.detector_element_id'
               '_diffrn_detector_element.id'
    
         save_
    
    
    save__diffrn_detector_element.detector_id
        _item_description.description
    ;             
                   This item is a pointer to '_diffrn_detector.id'
                   in the DIFFRN_DETECTOR category. 
    ;
        _item.name                  '_diffrn_detector_element.detector_id'
        _item.category_id             diffrn_detector_element
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    
    ########################
    ## DIFFRN_MEASUREMENT ##
    ########################
    
    
    save_DIFFRN_MEASUREMENT
        _category.description
    ;              Data items in the DIFFRN_MEASUREMENT category record details
                   about the device used to orient and/or position the crystal
                   during data measurement and the manner in which the
                   diffraction data were measured.
    ;
        _category.id                  diffrn_measurement
        _category.mandatory_code      no
         loop_
        _category_key.name          '_diffrn_measurement.device'
                                    '_diffrn_measurement.diffrn_id'
                                    '_diffrn_measurement.id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 - based on PDB entry 5HVP and laboratory records for the
                    structure corresponding to PDB entry 5HVP
    ;
    ;
        _diffrn_measurement.diffrn_id          'd1'
        _diffrn_measurement.device             '3-circle camera'
        _diffrn_measurement.device_type        'Supper model x'
        _diffrn_measurement.device_details     'none'
        _diffrn_measurement.method             'omega scan'
        _diffrn_measurement.details
        ; Need new example here
        ;
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991).
                    Acta Cryst. C47, 2276-2277].
    ;
    ;
        _diffrn_measurement.diffrn_id       's1'
        _diffrn_measurement.device_type     'Philips PW1100/20 diffractometer'
        _diffrn_measurement.method          'theta/2theta (\q/2\q)'
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__diffrn_measurement.device
        _item_description.description
    ;              The general class of goniometer or device used to support
                   and orient the specimen.
                   
                   If the value of '_diffrn_measurement.device' is not given,
                   it is implicitly equal to the value of
                   '_diffrn_measurement.diffrn_id'.
    
                   Either '_diffrn_measurement.device' or
                   '_diffrn_measurement.id' may be used to link to other
                   categories.  If the experimental setup admits multiple
                   devices, then '_diffrn_measurement.id' is used to provide
                   a unique link.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
                 '_diffrn_measurement.device'  diffrn_measurement      implicit
                 '_diffrn_measurement_axis.measurement_device' 
                                               diffrn_measurement_axis implicit
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_measurement_axis.measurement_device'  
                                             '_diffrn_measurement.device'
        _item_aliases.alias_name    '_diffrn_measurement_device'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          '3-circle camera'
                                     '4-circle camera'
                                     'kappa-geometry camera'
                                     'oscillation camera'
                                     'precession camera'
         save_
    
    
    save__diffrn_measurement.device_details
        _item_description.description
    ;              A description of special aspects of the device used to
                   measure the diffraction intensities.
    ;
        _item.name                  '_diffrn_measurement.device_details'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_device_details'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
        _item_examples.case
    ;                                 commercial goniometer modified locally to
                                      allow for 90\% \t arc
    ;
         save_
    
    
    save__diffrn_measurement.device_type
        _item_description.description
    ;              The make, model or name of the measurement device
                   (goniometer) used.
    ;
        _item.name                  '_diffrn_measurement.device_type'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_device_type'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          'Supper model q'
                                     'Huber model r'
                                     'Enraf-Nonius model s'
                                     'homemade'
         save_
    
    
    save__diffrn_measurement.diffrn_id
        _item_description.description
    ;              This data item is a pointer to '_diffrn.id' in the DIFFRN 
                   category.
    ;
        _item.name                  '_diffrn_measurement.diffrn_id'
        _item.mandatory_code          yes
         save_
    
    
    save__diffrn_measurement.details
        _item_description.description
    ;              A description of special aspects of the intensity
                   measurement.
    ;
        _item.name                  '_diffrn_measurement.details'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_details'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
        _item_examples.case
    ;                                 440 frames, 0.20 degrees, 150 sec, detector
                                      distance 12 cm, detector angle 22.5 degrees
    ;
         save_
    
    
    save__diffrn_measurement.id
        _item_description.description
    ;             
                   The value of '_diffrn_measurement.id' must uniquely identify
                   the set of mechanical characteristics of the device used to 
                   orient and/or position the sample used during collection 
                   of each diffraction data set.
    
                   If the value of '_diffrn_measurement.id' is not given, it is
                   implicitly equal to the value of 
                   '_diffrn_measurement.diffrn_id'.
    
                   Either '_diffrn_measurement.device' or
                   '_diffrn_measurement.id' may be used to link to other
                   categories.  If the experimental setup admits multiple
                   devices, then '_diffrn_measurement.id' is used to provide
                   a unique link.
    ;
         loop_
        _item.name                 
        _item.category_id
        _item.mandatory_code
                 '_diffrn_measurement.id'      diffrn_measurement      implicit
                 '_diffrn_measurement_axis.measurement_id'
                                               diffrn_measurement_axis implicit
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_measurement_axis.measurement_id'
                                             '_diffrn_measurement.id'
    
        _item_type.code               code
         save_
    
    
    save__diffrn_measurement.method
        _item_description.description
    ;              Method used to measure intensities.
    ;
        _item.name                  '_diffrn_measurement.method'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_method'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
        _item_examples.case
          'profile data from theta/2theta (\q/2\q) scans'
         save_
    
    
    save__diffrn_measurement.number_of_axes
        _item_description.description
    ;             
                   The value of '_diffrn_measurement.number_of_axes' gives the 
                   number of axes of the positioner for the goniometer or
                   other sample orientation or positioning device identified 
                   by '_diffrn_measurement.id'.
    
                   The description of the axes should be provided by entries in 
                   DIFFRN_MEASUREMENT_AXIS.
    ;
        _item.name                  '_diffrn_measurement.number_of_axes'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
         loop_
        _item_range.maximum
        _item_range.minimum           .   1
                                      1   1
        _item_type.code               int
         save_
    
    
    save__diffrn_measurement.specimen_support
        _item_description.description
    ;              The physical device used to support the crystal during data
                   collection.
    ;
        _item.name                  '_diffrn_measurement.specimen_support'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_specimen_support'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          'glass capillary'
                                     'quartz capillary'
                                     'fiber'
                                     'metal loop'
         save_
    
    
    ###########################
    # DIFFRN_MEASUREMENT_AXIS #
    ###########################
    
    
    save_DIFFRN_MEASUREMENT_AXIS
        _category.description
    ;
         Data items in the DIFFRN_MEASUREMENT_AXIS category associate
         axes with goniometers.
    ;
        _category.id                   diffrn_measurement_axis
        _category.mandatory_code       no
         loop_
        _category_key.name
                                  '_diffrn_measurement_axis.measurement_device'
                                    '_diffrn_measurement_axis.measurement_id'
                                    '_diffrn_measurement_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_measurement_axis.axis_id
        _item_description.description
    ;
                   This data item is a pointer to '_axis.id' in
                   the AXIS category.
    ;
        _item.name                  '_diffrn_measurement_axis.axis_id'
        _item.category_id             diffrn_measurement_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_measurement_axis.measurement_device
        _item_description.description
    ;
                   This data item is a pointer to '_diffrn_measurement.device'
                   in the DIFFRN_MEASUREMENT category.
    
    ;
        _item.name
          '_diffrn_measurement_axis.measurement_device'
        _item.category_id             diffrn_measurement_axis
        _item.mandatory_code          implicit
        _item_type.code               text
         save_
    
    
    save__diffrn_measurement_axis.measurement_id
        _item_description.description
    ;
                   This data item is a pointer to '_diffrn_measurement.id' in
                   the DIFFRN_MEASUREMENT category.
                  
                   This item was previously named '_diffrn_measurement_axis.id'
                   which is now a deprecated name.  The old name is
                   provided as an alias but should not be used for new work.
    
    ;
        _item.name                  '_diffrn_measurement_axis.measurement_id'
        _item.category_id             diffrn_measurement_axis
        _item_aliases.alias_name    '_diffrn_measurement_axis.id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0.00
        _item.mandatory_code          implicit
        _item_type.code               code
         save_
    
    
    ####################
    # DIFFRN_RADIATION #
    ####################
    
    
    save_DIFFRN_RADIATION
        _category.description
    ;              Data items in the DIFFRN_RADIATION category describe
                   the radiation used in measuring diffraction intensities,
                   its collimation and monochromatisation before the sample.
    
                   Post-sample treatment of the beam is described by data
                   items in the DIFFRN_DETECTOR category.
    
    ;
        _category.id                  diffrn_radiation
        _category.mandatory_code      no
        _category_key.name          '_diffrn_radiation.diffrn_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 - based on PDB entry 5HVP and laboratory records for the
                    structure corresponding to PDB entry 5HVP
    ;
    ;
        _diffrn_radiation.diffrn_id            'set1'
    
        _diffrn_radiation.collimation          '0.3 mm double pinhole'
        _diffrn_radiation.monochromator        'graphite'
        _diffrn_radiation.type                 'Cu K\a'
        _diffrn_radiation.wavelength_id         1
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991).
                    Acta Cryst. C47, 2276-2277].
    ;
    ;
        _diffrn_radiation.wavelength_id    1
        _diffrn_radiation.type             'Cu K\a'
        _diffrn_radiation.monochromator    'graphite'
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    save__diffrn_radiation.collimation
        _item_description.description
    ;              The collimation or focusing applied to the radiation.
    ;
        _item.name                  '_diffrn_radiation.collimation'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_collimation'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          '0.3 mm double-pinhole'
                                     '0.5 mm'
                                     'focusing mirrors'
         save_
    
    
    save__diffrn_radiation.diffrn_id
        _item_description.description
    ;              This data item is a pointer to '_diffrn.id' in the DIFFRN
                   category.
    ;
        _item.name                  '_diffrn_radiation.diffrn_id'
        _item.mandatory_code          yes
         save_
    
    
    
    save__diffrn_radiation.div_x_source
        _item_description.description
    ;              Beam crossfire in degrees parallel to the laboratory X axis
                   (see AXIS category).
                   
                   This is a characteristic of the xray beam as it illuminates
                   the sample (or specimen) after all monochromation and 
                   collimation.
                   
                   This is the esd of the directions of photons in the X-Z plane
                   around the mean source beam direction.
                   
                   Note that some synchrotrons specify this value in milliradians,
                   in which case a conversion would be needed.  To go from a
                   value in milliradians to a value in degrees, multiply by 0.180
                   and divide by π.
    
    ;
        _item.name                  '_diffrn_radiation.div_x_source'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_type.code               float
        _item_units.code              degrees
         save_
    
    
    save__diffrn_radiation.div_y_source
        _item_description.description
    ;              Beam crossfire in degrees parallel to the laboratory Y axis
                   (see AXIS category).
                   
                   This is a characteristic of the xray beam as it illuminates
                   the sample (or specimen) after all monochromation and 
                   collimation.
                   
                   This is the esd of the directions of photons in the Y-Z plane
                   around the mean source beam direction.
    
                   Note that some synchrotrons specify this value in milliradians,
                   in which case a conversion would be needed.  To go from a
                   value in milliradians to a value in degrees, multiply by 0.180
                   and divide by π.
    
    ;
        _item.name                  '_diffrn_radiation.div_y_source'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_type.code               float
        _item_units.code              degrees
        _item_default.value           0.0
         save_
    
    
    save__diffrn_radiation.div_x_y_source
        _item_description.description
    ;              Beam crossfire correlation degrees2 between the
                   crossfire laboratory X-axis component and the crossfire
                   laboratory Y-axis component (see AXIS category).
                   
                   This is a characteristic of the xray beam as it illuminates
                   the sample (or specimen) after all monochromation and 
                   collimation.
                   
                   This is the mean of the products of the deviations of the
                   direction of each photons in X-Z plane times the deviations
                   of the direction of the same photon in the Y-Z plane
                   around the mean source beam direction.  This will be zero
                   for uncorrelated crossfire.
                   
                   Note that some synchrotrons specify this value in 
                   milliradians2, in which case a conversion would be needed.  
                   To go from a value in milliradians2 to a value in
                   degrees2, multiply by 0.1802 and divide by π2.
    
    ;
        _item.name                  '_diffrn_radiation.div_x_y_source'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_type.code               float
        _item_units.code              degrees_squared
        _item_default.value           0.0
         save_
    
    save__diffrn_radiation.filter_edge
        _item_description.description
    ;              Absorption edge in Ångstroms of the radiation filter used.
    ;
        _item.name                  '_diffrn_radiation.filter_edge'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_filter_edge'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum           
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
        _item_units.code              angstroms
         save_
    
    save__diffrn_radiation.inhomogeneity
        _item_description.description
    ;              Half-width in millimetres of the incident beam in the
                   direction perpendicular to the diffraction plane.
    ;
        _item.name                  '_diffrn_radiation.inhomogeneity'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_inhomogeneity'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum           
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    save__diffrn_radiation.monochromator
        _item_description.description
    ;              The method used to obtain monochromatic radiation. If a
                   monochromator crystal is used the material and the
                   indices of the Bragg reflection are specified.
    ;
        _item.name                  '_diffrn_radiation.monochromator'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_monochromator'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          'Zr filter'
                                     'Ge 220'
                                     'none'
                                     'equatorial mounted graphite'
         save_
    
    save__diffrn_radiation.polarisn_norm
        _item_description.description
    ;              The angle in degrees, as viewed from the specimen, between the
                   perpendicular component of the polarisation and the diffraction
                   plane. See _diffrn_radiation_polarisn_ratio.
    ;
        _item.name                  '_diffrn_radiation.polarisn_norm'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_polarisn_norm'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum           
        _item_range.minimum           90.0  90.0
                                      90.0 -90.0
                                     -90.0 -90.0
        _item_type.code               float
        _item_units.code              degrees
         save_
    
    save__diffrn_radiation.polarisn_ratio
        _item_description.description
    ;              Polarisation ratio of the diffraction beam incident on the
                   crystal. It is the ratio of the perpendicularly polarised to
                   the parallel polarised component of the radiation. The
                   perpendicular component forms an angle of
                   '_diffrn_radiation.polarisn_norm' to the normal to the
                   diffraction plane of the sample (i.e. the plane containing
                   the incident and reflected beams).
    ;
        _item.name                  '_diffrn_radiation.polarisn_ratio'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_polarisn_ratio'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum           
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
         save_
    
    
    
    save__diffrn_radiation.polarizn_source_norm
        _item_description.description
    ;              The angle in degrees, as viewed from the specimen, between
                   the normal to the polarization plane and the laboratory Y
                   axis as defined in the AXIS category.
                   
                   Note that this is the angle of polarization of the source 
                   photons, either directly from a synchrotron beamline or
                   from a monchromater.
                   
                   This differs from the value of
                   '_diffrn_radiation.polarisn_norm'
                   in that '_diffrn_radiation.polarisn_norm' refers to
                   polarization relative to the diffraction plane rather than
                   to the laboratory axis system.
                   
                   In the case of an unpolarized beam, or a beam with true
                   circular polarization, in which no single plane of
                   polarization can be determined, the plane should be taken
                   as the X-Z plane, and the angle as 0.
                   
                   See '_diffrn_radiation.polarizn_source_ratio'.
    ;
        _item.name                  '_diffrn_radiation.polarizn_source_norm'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
         loop_
        _item_range.maximum           
        _item_range.minimum           90.0   90.0
                                      90.0  -90.0
                                     -90.0  -90.0
        _item_type.code               float
        _item_units.code              degrees
        _item_default.value           0.0
         save_
    
    
    save__diffrn_radiation.polarizn_source_ratio
        _item_description.description
    ;              (Ip-In)/(Ip+In), where Ip is the intensity (amplitude
                   squared) of the electric vector in the plane of
                   polarization and In is the intensity (amplitude squared)
                   of the electric vector in plane of the normal to the
                   plane of polarization.
                   
                   In the case of an unpolarized beam, or a beam with true
                   circular polarization, in which no single plane of
                   polarization can be determined, the plane is be taken
                   as the X-Z plane, and the normal is parallel to the Y-axis.
                   
                   Thus, if we had complete polarization in the plane of
                   polarization, the value of 
                   '_diffrn_radiation.polarizn_source_ratio' would
                   be 1, and an unpolarized beam would have a value of 0.
                   
                   If the X-axis has been chosen to lie in the plane of
                   polarization, this definition will agree with the definition
                   of "MONOCHROMATOR" in the Denzo glossary, and values of near
                   1 should be expected for a bending magnet source.  However,
                   if the X-axis were, for some reason to be, say,
                   perpendicular to the polarization plane (not a common
                   choice), then the Denzo value would be the negative of
                   '_diffrn_radiation.polarizn_source_ratio'.
                   
                   See http://www.hkl-xray.com for information on Denzo, and
                   Z. Otwinowski and W. Minor, "Processing of X-ray
                   Diffraction Data Collected in Oscillation Mode", Methods
                   in Enzymology, Volume 276: Macromolecular Crystallography,
                   part A, p.307-326, 1997,C.W. Carter, Jr. & R. M. Sweet,
                   Eds., Academic Press.
    
                   This differs both in the choice of ratio and choice of
                   orientation from '_diffrn_radiation.polarisn_ratio', which,
                   unlike '_diffrn_radiation.polarizn_source_ratio', is
                   unbounded.
    
    ;
        _item.name                  '_diffrn_radiation.polarizn_source_ratio'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
         loop_
        _item_range.maximum           
        _item_range.minimum           1.0    1.0
                                      1.0   -1.0
                                     -1.0   -1.0
        _item_type.code               float
         save_
    
    
    save__diffrn_radiation.probe
        _item_description.description
    ;              Name of the type of radiation used. It is strongly
                   encouraged that this field be specified so that the
                   probe radiation can be simply determined.
    ;
        _item.name                  '_diffrn_radiation.probe'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_probe'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               line
         loop_
        _item_enumeration.value      'x-ray'
                                     'neutron'
                                     'electron'
                                     'gamma'
         save_
    
    save__diffrn_radiation.type
        _item_description.description
    ;              The nature of the radiation. This is typically a description
                   of the X-ray wavelength in Siegbahn notation.
    ;
        _item.name                  '_diffrn_radiation.type'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_type'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               line
         loop_
        _item_examples.case          'CuK\a'
                                     'Cu K\a~1~'
                                     'Cu K-L~2,3~' 
                                     'white-beam'
    
         save_
    
    save__diffrn_radiation.xray_symbol
        _item_description.description
    ;              The IUPAC symbol for the X-ray wavelength for probe
                   radiation.
    ;
        _item.name                  '_diffrn_radiation.xray_symbol'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_xray_symbol'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               line
         loop_
        _item_enumeration.value
        _item_enumeration.detail     'K-L~3~'
                                     'K\a~1~ in older Siegbahn notation'
                                     'K-L~2~'
                                     'K\a~2~ in older Siegbahn notation'
                                     'K-M~3~'
                                     'K\b~1~ in older Siegbahn notation'
                                     'K-L~2,3~'
                                     'use where K-L~3~ and K-L~2~ are not resolved'
         save_
    
    save__diffrn_radiation.wavelength_id
        _item_description.description
    ;              This data item is a pointer to 
                   '_diffrn_radiation_wavelength.id' in the
                   DIFFRN_RADIATION_WAVELENGTH category.
    ;
        _item.name                  '_diffrn_radiation.wavelength_id'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    
    ################
    # DIFFRN_REFLN #
    ################
    
    
    save_DIFFRN_REFLN
        _category.description 
    ;
         This category redefinition has been added to extend the key of 
         the standard DIFFRN_REFLN category.
    ;
        _category.id                   diffrn_refln
        _category.mandatory_code       no
        _category_key.name             '_diffrn_refln.frame_id'
         loop_
        _category_group.id             'inclusive_group'
                                       'diffrn_group'
         save_
    
    
    save__diffrn_refln.frame_id
        _item_description.description
    ;             
                   This item is a pointer to '_diffrn_data_frame.id'
                   in the DIFFRN_DATA_FRAME category. 
    ;
        _item.name                  '_diffrn_refln.frame_id'
        _item.category_id             diffrn_refln
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    ###############
    # DIFFRN_SCAN #
    ###############
    
    save_DIFFRN_SCAN
        _category.description 
    ;
         Data items in the DIFFRN_SCAN category describe the parameters of one
         or more scans, relating axis positions to frames.
    
    ;
        _category.id                   diffrn_scan
        _category.mandatory_code       no
        _category_key.name            '_diffrn_scan.id'
         loop_
        _category_group.id            'inclusive_group'
                                      'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 - derived from a suggestion by R. M. Sweet.
    
       The vector of each axis is not given here, because it is provided in
       the AXIS category.  By making '_diffrn_scan_axis.scan_id' and
       '_diffrn_scan_axis.axis_id' keys of the DIFFRN_SCAN_AXIS category,
       an arbitrary number of scanning and fixed axes can be specified for a 
       scan.  We have specified three rotation axes and one translation axis 
       at non-zero values, with one axis stepping.  There is no reason why 
       more axes could not have been specified to step.   We have specified
       range information, but note that it is redundant from the  number of 
       frames and the increment, so we could drop the data item
       '_diffrn_scan_axis.angle_range'.
       
       We have specified both the sweep data and the data for a single frame.
    
       Note that the information on how the axes are stepped is given twice,
       once in terms of the overall averages in the value of
       '_diffrn_scan.integration_time' and the values for DIFFRN_SCAN_AXIS,
       and precisely for the given frame in the value for 
       '_diffrn_scan_frame.integration_time' and the values for
       DIFFRN_SCAN_FRAME_AXIS.  If dose-related adjustements are made to
       scan times and non-linear stepping is done, these values may differ.
       Therefore, in interpreting the data for a particular frame it is
       important to use the frame-specific data.
    
    ;
    ;
          _diffrn_scan.id                   1
          _diffrn_scan.date_start         '2001-11-18T03:26:42'
          _diffrn_scan.date_end           '2001-11-18T03:36:45'
          _diffrn_scan.integration_time    3.0
          _diffrn_scan.frame_id_start      mad_L2_000
          _diffrn_scan.frame_id_end        mad_L2_200
          _diffrn_scan.frames              201
    
           loop_
          _diffrn_scan_axis.scan_id
          _diffrn_scan_axis.axis_id
          _diffrn_scan_axis.angle_start
          _diffrn_scan_axis.angle_range
          _diffrn_scan_axis.angle_increment
          _diffrn_scan_axis.displacement_start
          _diffrn_scan_axis.displacement_range
          _diffrn_scan_axis.displacement_increment
    
           1 omega 200.0 20.0 0.1 . . . 
           1 kappa -40.0  0.0 0.0 . . . 
           1 phi   127.5  0.0 0.0 . . . 
           1 tranz  . . .   2.3 0.0 0.0 
    
          _diffrn_scan_frame.scan_id                   1
          _diffrn_scan_frame.date               '2001-11-18T03:27:33'
          _diffrn_scan_frame.integration_time    3.0
          _diffrn_scan_frame.frame_id            mad_L2_018
          _diffrn_scan_frame.frame_number        18
    
          loop_
          _diffrn_scan_frame_axis.frame_id
          _diffrn_scan_frame_axis.axis_id
          _diffrn_scan_frame_axis.angle
          _diffrn_scan_frame_axis.angle_increment
          _diffrn_scan_frame_axis.displacement
          _diffrn_scan_frame_axis.displacement_increment
    
           mad_L2_018 omega 201.8  0.1 . .
           mad_L2_018 kappa -40.0  0.0 . .
           mad_L2_018 phi   127.5  0.0 . .
           mad_L2_018 tranz  .     .  2.3 0.0
    
    ;
    
    ;
        Example 2 - a more extensive example, R. M. Sweet, P. Ellis, H. Bernstein.
        
       We place a detector 240 mm along the Z axis from the goniometer.
       This presents us with a choice -- either we define the axes of
       the detector at the origin, and then put a Z setting of -240 in
       for the actual use, or we define the axes with the necessary Z-offset.
       In this case we use the setting, and leave the offset as zero.
       We call this axis DETECTOR_Z.
       
       The axis for positioning the detector in the Y-direction depends
       on the detector Z-axis.  We call this axis, DETECTOR_Y.
       
       The axis for positioning the detector in the X-direction depends
       on the detector Y-axis (and therefore on the detector Z-axis).
       We call this axis DETECTOR_X.
       
       This detector may be rotated around the Y-axis.  This rotation axis
       depends on the three translation axes.  We call it DETECTOR_PITCH.
       
       We define a coordinate system on the face of the detector in terms of
       2300 0.150 mm pixels in each direction.  The ELEMENT_X axis is used to
       index the first array index of the data array and the ELEMENT_Y
       axis is used to index the second array index.  Because the pixels
       are 0.150mm x 0.150mm, the centre of the first pixel is at (0.075, 
       0.075) in this coordinate system.
    
    ;
    ;
         ###CBF: VERSION 1.1 
    
         data_image_1 
    
    
         # category DIFFRN 
    
         _diffrn.id P6MB 
         _diffrn.crystal_id P6MB_CRYSTAL7 
    
    
         # category DIFFRN_SOURCE 
    
         loop_ 
         _diffrn_source.diffrn_id 
         _diffrn_source.source 
         _diffrn_source.type 
          P6MB synchrotron 'SSRL beamline 9-1' 
    
    
         # category DIFFRN_RADIATION 
    
              loop_ 
         _diffrn_radiation.diffrn_id 
         _diffrn_radiation.wavelength_id 
         _diffrn_radiation.monochromator 
         _diffrn_radiation.polarizn_source_ratio 
         _diffrn_radiation.polarizn_source_norm 
         _diffrn_radiation.div_x_source 
         _diffrn_radiation.div_y_source 
         _diffrn_radiation.div_x_y_source 
          P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08
         0.01 0.00 
    
    
         # category DIFFRN_RADIATION_WAVELENGTH 
    
         loop_ 
         _diffrn_radiation_wavelength.id 
         _diffrn_radiation_wavelength.wavelength 
         _diffrn_radiation_wavelength.wt 
          WAVELENGTH1 0.98 1.0 
    
    
         # category DIFFRN_DETECTOR 
    
         loop_ 
         _diffrn_detector.diffrn_id 
         _diffrn_detector.id 
         _diffrn_detector.type 
         _diffrn_detector.number_of_axes 
          P6MB MAR345-SN26 'MAR 345' 4 
    
    
         # category DIFFRN_DETECTOR_AXIS 
    
         loop_ 
         _diffrn_detector_axis.detector_id 
         _diffrn_detector_axis.axis_id 
          MAR345-SN26 DETECTOR_X 
          MAR345-SN26 DETECTOR_Y 
          MAR345-SN26 DETECTOR_Z 
          MAR345-SN26 DETECTOR_PITCH 
    
    
         # category DIFFRN_DETECTOR_ELEMENT 
    
         loop_ 
         _diffrn_detector_element.id 
         _diffrn_detector_element.detector_id 
          ELEMENT1 MAR345-SN26 
    
    
         # category DIFFRN_DATA_FRAME 
    
         loop_ 
         _diffrn_data_frame.id 
         _diffrn_data_frame.detector_element_id 
         _diffrn_data_frame.array_id 
         _diffrn_data_frame.binary_id 
          FRAME1 ELEMENT1 ARRAY1 1 
    
    
         # category DIFFRN_MEASUREMENT 
    
         loop_ 
         _diffrn_measurement.diffrn_id 
         _diffrn_measurement.id 
         _diffrn_measurement.number_of_axes 
         _diffrn_measurement.method 
          P6MB GONIOMETER 3 rotation 
    
    
         # category DIFFRN_MEASUREMENT_AXIS 
    
         loop_ 
         _diffrn_measurement_axis.measurement_id 
         _diffrn_measurement_axis.axis_id 
          GONIOMETER GONIOMETER_PHI 
          GONIOMETER GONIOMETER_KAPPA 
          GONIOMETER GONIOMETER_OMEGA 
    
    
         # category DIFFRN_SCAN 
    
         loop_ 
         _diffrn_scan.id 
         _diffrn_scan.frame_id_start 
         _diffrn_scan.frame_id_end 
         _diffrn_scan.frames 
          SCAN1 FRAME1 FRAME1 1 
    
    
         # category DIFFRN_SCAN_AXIS 
    
         loop_ 
         _diffrn_scan_axis.scan_id 
         _diffrn_scan_axis.axis_id 
         _diffrn_scan_axis.angle_start 
         _diffrn_scan_axis.angle_range 
         _diffrn_scan_axis.angle_increment 
         _diffrn_scan_axis.displacement_start 
         _diffrn_scan_axis.displacement_range 
         _diffrn_scan_axis.displacement_increment 
          SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 
          SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 
          SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 
          SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 
          SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 
          SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 
          SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 
    
    
         # category DIFFRN_SCAN_FRAME 
    
         loop_ 
         _diffrn_scan_frame.frame_id 
         _diffrn_scan_frame.frame_number 
         _diffrn_scan_frame.integration_time 
         _diffrn_scan_frame.scan_id 
         _diffrn_scan_frame.date 
          FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 
    
    
         # category DIFFRN_SCAN_FRAME_AXIS 
    
         loop_ 
         _diffrn_scan_frame_axis.frame_id 
         _diffrn_scan_frame_axis.axis_id 
         _diffrn_scan_frame_axis.angle 
         _diffrn_scan_frame_axis.displacement 
          FRAME1 GONIOMETER_OMEGA 12.0 0.0 
          FRAME1 GONIOMETER_KAPPA 23.3 0.0 
          FRAME1 GONIOMETER_PHI -165.8 0.0 
          FRAME1 DETECTOR_Z 0.0 -240.0 
          FRAME1 DETECTOR_Y 0.0 0.6 
          FRAME1 DETECTOR_X 0.0 -0.5 
          FRAME1 DETECTOR_PITCH 0.0 0.0 
    
    
         # category AXIS 
    
         loop_ 
         _axis.id 
         _axis.type 
         _axis.equipment 
         _axis.depends_on 
         _axis.vector[1] _axis.vector[2] _axis.vector[3] 
         _axis.offset[1] _axis.offset[2] _axis.offset[3] 
          GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . 
          GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279
          0 0.76604 . . . 
          GONIOMETER_PHI   rotation goniometer GONIOMETER_KAPPA 1 0 0
         . . . 
          SOURCE           general source . 0 0 1 . . . 
          GRAVITY          general gravity . 0 -1 0 . . . 
          DETECTOR_Z       translation detector . 0 0 1 0 0 0
          DETECTOR_Y       translation detector DETECTOR_Z 0 1 0 0 0 0 
          DETECTOR_X       translation detector DETECTOR_Y 1 0 0 0 0 0 
          DETECTOR_PITCH   rotation    detector DETECTOR_X 0 1 0 0 0 0 
          ELEMENT_X        translation detector DETECTOR_PITCH
         1 0 0 172.43 -172.43 0
          ELEMENT_Y        translation detector ELEMENT_X
         0 1 0 0 0 0 
    
         # category ARRAY_STRUCTURE_LIST 
    
         loop_ 
         _array_structure_list.array_id 
         _array_structure_list.index 
         _array_structure_list.dimension 
         _array_structure_list.precedence 
         _array_structure_list.direction 
         _array_structure_list.axis_set_id 
          ARRAY1 1 2300 1 increasing ELEMENT_X 
          ARRAY1 2 2300 2 increasing ELEMENT_Y 
    
    
         # category ARRAY_STRUCTURE_LIST_AXIS 
    
         loop_
         _array_structure_list_axis.axis_set_id
         _array_structure_list_axis.axis_id
         _array_structure_list_axis.displacement
         _array_structure_list_axis.displacement_increment
          ELEMENT_X ELEMENT_X 0.075 0.150
          ELEMENT_Y ELEMENT_Y 0.075 0.150
    
         # category ARRAY_ELEMENT_SIZE 
    
         loop_ 
         _array_element_size.array_id 
         _array_element_size.index 
         _array_element_size.size 
          ARRAY1 1 150e-6 
          ARRAY1 2 150e-6 
    
    
         # category ARRAY_INTENSITIES 
    
         loop_ 
         _array_intensities.array_id 
         _array_intensities.binary_id 
         _array_intensities.linearity 
         _array_intensities.gain 
         _array_intensities.gain_esd 
         _array_intensities.overload
         _array_intensities.undefined_value 
          ARRAY1 1 linear 1.15 0.2 240000 0 
    
    
          # category ARRAY_STRUCTURE 
    
          loop_ 
          _array_structure.id 
          _array_structure.encoding_type 
          _array_structure.compression_type 
          _array_structure.byte_order 
          ARRAY1 "signed 32-bit integer" packed little_endian 
    
    
         # category ARRAY_DATA         
    
         loop_ 
         _array_data.array_id 
         _array_data.binary_id 
         _array_data.data 
          ARRAY1 1 
         ; 
         --CIF-BINARY-FORMAT-SECTION-- 
         Content-Type: application/octet-stream; 
             conversions="x-CBF_PACKED" 
         Content-Transfer-Encoding: BASE64 
         X-Binary-Size: 3801324 
         X-Binary-ID: 1 
         X-Binary-Element-Type: "signed 32-bit integer" 
         Content-MD5: 07lZFvF+aOcW85IN7usl8A== 
    
         AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg 
         ... 
         8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE 
    
         --CIF-BINARY-FORMAT-SECTION---- 
         ; 
    ;
    
    ;
        Example 3 - Example 2 revised for a spiral scan, R. M. Sweet, 
        P. Ellis, H. Bernstein.
        
       We place a detector 240 mm along the Z axis from the goniometer,
       as in Example 2, above, but in this example, the image plate is
       scanned in a spiral pattern outside edge in.
       
       The axis for positioning the detector in the Y-direction depends
       on the detector Z-axis.  We call this axis, DETECTOR_Y.
       
       The axis for positioning the detector in the X-direction depends
       on the detector Y-axis (and therefore on the detector Z-axis).
       We call this axis DETECTOR_X.
       
       This detector may be rotated around the Y-axis.  This rotation axis
       depends on the three translation axes.  We call it DETECTOR_PITCH.
    
       We define a coordinate system on the face of the detector in
       terms of a coupled rotation axis and radial scan axis to form 
       a spiral scan.  Let us call rotation axis ELEMENT_ROT, and the
       radial axis ELEMENT_RAD.   We assume 150 um radial pitch and 75 um 
       'constant velocity' angular pitch. 
    
       We index first on the rotation axis and make the radial axis
       dependent on 
       it. 
    
       The two axes are coupled to form an axis set ELEMENT_SPIRAL. 
    
    ;
    ;
         ###CBF: VERSION 1.1 
    
         data_image_1 
    
    
         # category DIFFRN 
    
         _diffrn.id P6MB 
         _diffrn.crystal_id P6MB_CRYSTAL7 
    
    
         # category DIFFRN_SOURCE 
    
         loop_ 
         _diffrn_source.diffrn_id 
         _diffrn_source.source 
         _diffrn_source.type 
          P6MB synchrotron 'SSRL beamline 9-1' 
    
    
         # category DIFFRN_RADIATION 
    
              loop_ 
         _diffrn_radiation.diffrn_id 
         _diffrn_radiation.wavelength_id 
         _diffrn_radiation.monochromator 
         _diffrn_radiation.polarizn_source_ratio 
         _diffrn_radiation.polarizn_source_norm 
         _diffrn_radiation.div_x_source 
         _diffrn_radiation.div_y_source 
         _diffrn_radiation.div_x_y_source 
          P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08
         0.01 0.00 
    
    
         # category DIFFRN_RADIATION_WAVELENGTH 
    
         loop_ 
         _diffrn_radiation_wavelength.id 
         _diffrn_radiation_wavelength.wavelength 
         _diffrn_radiation_wavelength.wt 
          WAVELENGTH1 0.98 1.0 
    
    
         # category DIFFRN_DETECTOR 
    
         loop_ 
         _diffrn_detector.diffrn_id 
         _diffrn_detector.id 
         _diffrn_detector.type 
         _diffrn_detector.number_of_axes 
          P6MB MAR345-SN26 'MAR 345' 4 
    
    
         # category DIFFRN_DETECTOR_AXIS 
    
         loop_ 
         _diffrn_detector_axis.detector_id 
         _diffrn_detector_axis.axis_id 
          MAR345-SN26 DETECTOR_X 
          MAR345-SN26 DETECTOR_Y 
          MAR345-SN26 DETECTOR_Z 
          MAR345-SN26 DETECTOR_PITCH 
    
    
         # category DIFFRN_DETECTOR_ELEMENT 
    
         loop_ 
         _diffrn_detector_element.id 
         _diffrn_detector_element.detector_id 
          ELEMENT1 MAR345-SN26 
    
    
         # category DIFFRN_DATA_FRAME 
    
         loop_ 
         _diffrn_data_frame.id 
         _diffrn_data_frame.detector_element_id 
         _diffrn_data_frame.array_id 
         _diffrn_data_frame.binary_id 
          FRAME1 ELEMENT1 ARRAY1 1 
    
    
         # category DIFFRN_MEASUREMENT 
    
         loop_ 
         _diffrn_measurement.diffrn_id 
         _diffrn_measurement.id 
         _diffrn_measurement.number_of_axes 
         _diffrn_measurement.method 
          P6MB GONIOMETER 3 rotation 
    
    
         # category DIFFRN_MEASUREMENT_AXIS 
    
         loop_ 
         _diffrn_measurement_axis.measurement_id 
         _diffrn_measurement_axis.axis_id 
          GONIOMETER GONIOMETER_PHI 
          GONIOMETER GONIOMETER_KAPPA 
          GONIOMETER GONIOMETER_OMEGA 
    
    
         # category DIFFRN_SCAN 
    
         loop_ 
         _diffrn_scan.id 
         _diffrn_scan.frame_id_start 
         _diffrn_scan.frame_id_end 
         _diffrn_scan.frames 
          SCAN1 FRAME1 FRAME1 1 
    
    
         # category DIFFRN_SCAN_AXIS 
    
         loop_ 
         _diffrn_scan_axis.scan_id 
         _diffrn_scan_axis.axis_id 
         _diffrn_scan_axis.angle_start 
         _diffrn_scan_axis.angle_range 
         _diffrn_scan_axis.angle_increment 
         _diffrn_scan_axis.displacement_start 
         _diffrn_scan_axis.displacement_range 
         _diffrn_scan_axis.displacement_increment 
          SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 
          SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 
          SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 
          SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 
          SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 
          SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 
          SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 
    
    
         # category DIFFRN_SCAN_FRAME 
    
         loop_ 
         _diffrn_scan_frame.frame_id 
         _diffrn_scan_frame.frame_number 
         _diffrn_scan_frame.integration_time 
         _diffrn_scan_frame.scan_id 
         _diffrn_scan_frame.date 
          FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 
    
    
         # category DIFFRN_SCAN_FRAME_AXIS 
    
         loop_ 
         _diffrn_scan_frame_axis.frame_id 
         _diffrn_scan_frame_axis.axis_id 
         _diffrn_scan_frame_axis.angle 
         _diffrn_scan_frame_axis.displacement 
          FRAME1 GONIOMETER_OMEGA 12.0 0.0 
          FRAME1 GONIOMETER_KAPPA 23.3 0.0 
          FRAME1 GONIOMETER_PHI -165.8 0.0 
          FRAME1 DETECTOR_Z 0.0 -240.0 
          FRAME1 DETECTOR_Y 0.0 0.6 
          FRAME1 DETECTOR_X 0.0 -0.5 
          FRAME1 DETECTOR_PITCH 0.0 0.0 
    
    
         # category AXIS 
    
         loop_ 
         _axis.id 
         _axis.type 
         _axis.equipment 
         _axis.depends_on 
         _axis.vector[1] _axis.vector[2] _axis.vector[3] 
         _axis.offset[1] _axis.offset[2] _axis.offset[3] 
          GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . 
          GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279
          0 0.76604 . . . 
          GONIOMETER_PHI   rotation goniometer GONIOMETER_KAPPA 1 0 0
         . . . 
          SOURCE           general source . 0 0 1 . . . 
          GRAVITY          general gravity . 0 -1 0 . . . 
          DETECTOR_Z       translation detector . 0 0 1 0 0 0
          DETECTOR_Y       translation detector DETECTOR_Z 0 1 0 0 0 0 
          DETECTOR_X       translation detector DETECTOR_Y 1 0 0 0 0 0 
          DETECTOR_PITCH   rotation    detector DETECTOR_X 0 1 0 0 0 0 
          ELEMENT_ROT      translation detector DETECTOR_PITCH 0 0 1 0 0 0
          ELEMENT_RAD      translation detector ELEMENT_ROT 0 1 0 0 0 0 
    
         # category ARRAY_STRUCTURE_LIST 
    
         loop_ 
         _array_structure_list.array_id 
         _array_structure_list.index 
         _array_structure_list.dimension 
         _array_structure_list.precedence 
         _array_structure_list.direction 
         _array_structure_list.axis_set_id 
          ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL
    
    
         # category ARRAY_STRUCTURE_LIST_AXIS 
    
         loop_
         _array_structure_list_axis.axis_set_id
         _array_structure_list_axis.axis_id
         _array_structure_list_axis.angle
         _array_structure_list_axis.displacement
         _array_structure_list_axis.angular_pitch
         _array_structure_list_axis.radial_pitch
          ELEMENT_SPIRAL ELEMENT_ROT 0    .  0.075   .
          ELEMENT_SPIRAL ELEMENT_RAD . 172.5  .    -0.150
    
         # category ARRAY_ELEMENT_SIZE 
         # the actual pixels are 0.075 by 0.150 mm
         # We give the coarser dimension here.
    
         loop_ 
         _array_element_size.array_id 
         _array_element_size.index 
         _array_element_size.size 
          ARRAY1 1 150e-6 
    
    
         # category ARRAY_INTENSITIES 
    
         loop_ 
         _array_intensities.array_id 
         _array_intensities.binary_id 
         _array_intensities.linearity 
         _array_intensities.gain 
         _array_intensities.gain_esd 
         _array_intensities.overload
         _array_intensities.undefined_value 
          ARRAY1 1 linear 1.15 0.2 240000 0 
    
    
          # category ARRAY_STRUCTURE 
    
          loop_ 
          _array_structure.id 
          _array_structure.encoding_type 
          _array_structure.compression_type 
          _array_structure.byte_order 
          ARRAY1 "signed 32-bit integer" packed little_endian 
    
    
         # category ARRAY_DATA         
    
         loop_ 
         _array_data.array_id 
         _array_data.binary_id 
         _array_data.data 
          ARRAY1 1 
         ; 
         --CIF-BINARY-FORMAT-SECTION-- 
         Content-Type: application/octet-stream; 
             conversions="x-CBF_PACKED" 
         Content-Transfer-Encoding: BASE64 
         X-Binary-Size: 3801324 
         X-Binary-ID: 1 
         X-Binary-Element-Type: "signed 32-bit integer" 
         Content-MD5: 07lZFvF+aOcW85IN7usl8A== 
    
         AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg 
         ... 
         8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE 
    
         --CIF-BINARY-FORMAT-SECTION---- 
         ; 
    ;
    
    
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
           save_
    
    
    save__diffrn_scan.id
        _item_description.description
    ;             The value of '_diffrn_scan.id' uniquely identifies each
                  scan.  The identifier is used to tie together all the 
                  information about the scan.
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
           '_diffrn_scan.id'                 diffrn_scan             yes
           '_diffrn_scan_axis.scan_id'       diffrn_scan_axis        yes
           '_diffrn_scan_frame.scan_id'      diffrn_scan_frame       yes
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
           '_diffrn_scan_axis.scan_id'          '_diffrn_scan.id'
           '_diffrn_scan_frame.scan_id'         '_diffrn_scan.id'
         save_
    
    
    save__diffrn_scan.date_end
        _item_description.description
    ;
                   The date and time of the end of the scan.  Note that this
                   may be an estimate generated during the scan, before the
                   precise time of the end of the scan is known.
    ;
        _item.name                 '_diffrn_scan.date_end'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no
        _item_type.code            yyyy-mm-dd
         save_
    
    
    save__diffrn_scan.date_start
        _item_description.description
    ;
                   The date and time of the start of the scan.
    ;
        _item.name                 '_diffrn_scan.date_start'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no
        _item_type.code            yyyy-mm-dd
         save_
    
    
    save__diffrn_scan.integration_time
        _item_description.description
    ;
                   Approximate average time in seconds to integrate each 
                   step of the scan.  The precise time for integration
                   of each particular step must be provided in
                   '_diffrn_scan_frame.integration_time', even
                   if all steps have the same integration time.
    ;
        _item.name                 '_diffrn_scan.integration_time'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no
        _item_type.code            float
        _item_units.code           'seconds'
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0.0
         save_
    
    
    save__diffrn_scan.frame_id_start
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   first frame in the scan.
    
                   This item is a pointer to '_diffrn_data_frame.id' in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name                 '_diffrn_scan.frame_id_start'
        _item.category_id          diffrn_scan
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan.frame_id_end
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   last frame in the scan.
    
                   This item is a pointer to '_diffrn_data_frame.id' in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name                 '_diffrn_scan.frame_id_end'
        _item.category_id          diffrn_scan
        _item.mandatory_code       yes 
        _item_type.code            code
         save_
    
    
    save__diffrn_scan.frames
        _item_description.description
    ;
                   The value of this data item is the number of frames in
                   the scan.
    
    ;
        _item.name                 '_diffrn_scan.frames'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no 
        _item_type.code            int
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   1
                                1   1
         save_
    
    
    ####################
    # DIFFRN_SCAN_AXIS #
    ####################
    
    save_DIFFRN_SCAN_AXIS
        _category.description 
    ;
         Data items in the DIFFRN_SCAN_AXIS category describe the settings of
         axes for particular scans.  Unspecified axes are assumed to be at
         their zero points.
    
    ;
        _category.id                   diffrn_scan_axis
        _category.mandatory_code       no
         loop_
        _category_key.name            
                                      '_diffrn_scan_axis.scan_id'
                                      '_diffrn_scan_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_scan_axis.scan_id
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   scan for which axis settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   '_diffrn_scan.id'.
    
                   This item is a pointer to '_diffrn_scan.id' in the
                   DIFFRN_SCAN category.
    ;
        _item.name                 '_diffrn_scan_axis.scan_id'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_axis.axis_id
        _item_description.description
    ;
                   The value of this data item is the identifier of one of
                   the axes for the scan for which settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   '_diffrn_scan.id'.
    
                   This item is a pointer to '_axis.id' in the
                   AXIS category.
    ;
        _item.name                 '_diffrn_scan_axis.axis_id'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_axis.angle_start
        _item_description.description
    ;
                   The starting position for the specified axis in degrees.
    ;
        _item.name                 '_diffrn_scan_axis.angle_start'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.angle_range
        _item_description.description
    ;
                   The range from the starting position for the specified axis 
                   in degrees.
    ;
        _item.name                 '_diffrn_scan_axis.angle_range'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.angle_increment
        _item_description.description
    ;
                   The increment for each step for the specified axis
                   in degrees.  In general, this will agree with
                   '_diffrn_scan_frame_axis.angle_increment'. The 
                   sum of the values of '_diffrn_scan_frame_axis.angle' and
                   '_diffrn_scan_frame_axis.angle_increment' is the
                   angular setting of the axis at the end of the integration
                   time for a given frame.  If the individual frame values
                   vary, then the value of 
                   '_diffrn_scan_axis.angle_increment' will be 
                   representative
                   of the ensemble of values of
                   '_diffrn_scan_frame_axis.angle_increment' (e.g.
                   the mean).
    
    ;
        _item.name                 '_diffrn_scan_axis.angle_increment'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.angle_rstrt_incr
        _item_description.description
    ;
                   The increment after each step for the specified axis
                   in degrees.  In general, this will agree with
                   '_diffrn_scan_frame_axis.angle_rstrt_incr'.  The
                   sum of the values of '_diffrn_scan_frame_axis.angle' 
                   and  '_diffrn_scan_frame_axis.angle_increment' 
                   and  '_diffrn_scan_frame_axis.angle_rstrt_incr' is the
                   angular setting of the axis at the start of the integration
                   time for the next frame relative to a given frame, and 
                   should equal '_diffrn_scan_frame_axis.angle' for that 
                   next frame.   If the individual frame values
                   vary, then the value of 
                   '_diffrn_scan_axis.angle_rstrt_incr' will be 
                   representative
                   of the ensemble of values of
                   '_diffrn_scan_frame_axis.angle_rstrt_incr' (e.g.
                   the mean).
    ;
        _item.name                 '_diffrn_scan_axis.angle_rstrt_incr'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.displacement_start
        _item_description.description
    ;
                   The starting position for the specified axis in millimetres.
    ;
        _item.name                 '_diffrn_scan_axis.displacement_start'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_axis.displacement_range
        _item_description.description
    ;
                   The range from the starting position for the specified axis 
                   in millimetres.
    ;
        _item.name                 '_diffrn_scan_axis.displacement_range'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_axis.displacement_increment
        _item_description.description
    ;
                   The increment for each step for the specified axis
                   in millimetres.  In general, this will agree with
                   '_diffrn_scan_frame_axis.displacement_increment'.
                   The sum of the values of 
                   '_diffrn_scan_frame_axis.displacement' and
                   '_diffrn_scan_frame_axis.displacement_increment' is the
                   angular setting of the axis at the end of the integration
                   time for a given frame.  If the individual frame values
                   vary, then the value of 
                   '_diffrn_scan_axis.displacement_increment' will be 
                   representative
                   of the ensemble of values of
                   '_diffrn_scan_frame_axis.displacement_increment' (e.g.
                   the mean).
    ;
        _item.name                 '_diffrn_scan_axis.displacement_increment'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_axis.displacement_rstrt_incr
        _item_description.description
    ;
                   The increment for each step for the specified axis
                   in millimetres.  In general, this will agree with
                   '_diffrn_scan_frame_axis.displacement_rstrt_incr'.
                   The sum of the values of 
                   '_diffrn_scan_frame_axis.displacement' and
                   '_diffrn_scan_frame_axis.displacement_increment' and
                   '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the
                   angular setting of the axis at the start of the integration
                   time for the next frame relative to a given frame, and 
                   should equal '_diffrn_scan_frame_axis.displacement' 
                   for that next frame.  If the individual frame values
                   vary, then the value of 
                   '_diffrn_scan_axis.displacement_rstrt_incr' will be 
                   representative
                   of the ensemble of values of
                   '_diffrn_scan_frame_axis.displacement_rstrt_incr' (e.g.
                   the mean).
    ;
        _item.name                 '_diffrn_scan_axis.displacement_rstrt_incr'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    #####################
    # DIFFRN_SCAN_FRAME #
    #####################
    
    save_DIFFRN_SCAN_FRAME
        _category.description 
    ;
                Data items in the DIFFRN_SCAN_FRAME category describe
                the relationship of particular frames to scans.
    
    ;
        _category.id                   diffrn_scan_frame
        _category.mandatory_code       no
         loop_
        _category_key.name     
                                      '_diffrn_scan_frame.scan_id'
                                      '_diffrn_scan_frame.frame_id'
         loop_
        _category_group.id            'inclusive_group'
                                      'diffrn_group'
         save_
    
    
    save__diffrn_scan_frame.date
        _item_description.description
    ;
                   The date and time of the start of the frame being scanned.
    ;
        _item.name                 '_diffrn_scan_frame.date'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       no
        _item_type.code            yyyy-mm-dd
         save_
    
    
    save__diffrn_scan_frame.frame_id
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   frame being examined.
    
                   This item is a pointer to '_diffrn_data_frame.id' in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name                 '_diffrn_scan_frame.frame_id'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_frame.frame_number
        _item_description.description
    ;
                   The value of this data item is the number of the frame
                   within the scan, starting with 1.  It is not necessarily
                   the same as the value of '_diffrn_scan_frame.frame_id',
                   but may be.
    
    ;
        _item.name                 '_diffrn_scan_frame.frame_number'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       no 
        _item_type.code            int
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0
                                0   0
         save_
    
    
    save__diffrn_scan_frame.integration_time
        _item_description.description
    ;
                   The time in seconds to integrate this step of the scan.
                   This should be the precise time of integration of each
                   particular frame.  The value of this data item should
                   be given explicitly for each frame and not inferred
                   from the value of '_diffrn_scan.integration_time'.
    ;
        _item.name                 '_diffrn_scan_frame.integration_time'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       yes 
        _item_type.code            float
        _item_units.code           'seconds'
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0.0
         save_
    
    
    save__diffrn_scan_frame.scan_id
        _item_description.description
    ;             The value of '_diffrn_scan_frame.scan_id' identifies the scan
                  containing this frame.
    
                  This item is a pointer to '_diffrn_scan.id' in the
                  DIFFRN_SCAN category.
    ;
        _item.name             '_diffrn_scan_frame.scan_id'    
        _item.category_id        diffrn_scan_frame        
        _item.mandatory_code     yes     
        _item_type.code          code
         save_
    
    
    ##########################
    # DIFFRN_SCAN_FRAME_AXIS #
    ##########################
    
    save_DIFFRN_SCAN_FRAME_AXIS
        _category.description
    ;
         Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the
         settings of axes for particular frames.  Unspecified axes are
         assumed to be at their zero points.  If, for any given frame,
         non-zero values apply for any of the data items in this category,
         those values should be given explicitly in this category and not
         simply inferred from values in DIFFRN_SCAN_AXIS.
    
    ;
        _category.id                   diffrn_scan_frame_axis
        _category.mandatory_code       no
         loop_
        _category_key.name
                                      '_diffrn_scan_frame_axis.frame_id'
                                      '_diffrn_scan_frame_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_scan_frame_axis.axis_id
        _item_description.description
    ;
                   The value of this data item is the identifier of one of
                   the axes for the frame for which settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   '_diffrn_scan_frame.frame_id'.
    
                   This item is a pointer to '_axis.id' in the
                   AXIS category.
    ;
        _item.name                 '_diffrn_scan_frame_axis.axis_id'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_frame_axis.angle
        _item_description.description
    ;
                   The setting of the specified axis in degrees for this frame.
                   This is the setting at the start of the integration time.
    ;
        _item.name                 '_diffrn_scan_frame_axis.angle'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_frame_axis.angle_increment
        _item_description.description
    ;
                   The increment for this frame for angular setting of
                   the specified axis in degrees.  The sum of the values
                   of '_diffrn_scan_frame_axis.angle' and
                   '_diffrn_scan_frame_axis.angle_increment' is the
                   angular setting of the axis at the end of the integration
                   time for this frame.
    ;
        _item.name                 '_diffrn_scan_frame_axis.angle_increment'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_frame_axis.angle_rstrt_incr
        _item_description.description
    ;
                   The increment after this frame for angular setting of
                   the specified axis in degrees.  The sum of the values
                   of '_diffrn_scan_frame_axis.angle' and
                   '_diffrn_scan_frame_axis.angle_increment' and
                   '_diffrn_scan_frame_axis.angle_rstrt_incr' is the
                   angular setting of the axis at the start of the integration
                   time for the next frame, and should equal
                   '_diffrn_scan_frame_axis.angle' for that next frame.
    ;
        _item.name               '_diffrn_scan_frame_axis.angle_rstrt_incr'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_frame_axis.displacement
        _item_description.description
    ;
                   The setting of the specified axis in millimetres for this
                   frame.  This is the setting at the start of the integration
                   time.
    
    ;
        _item.name               '_diffrn_scan_frame_axis.displacement'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_frame_axis.displacement_increment
        _item_description.description
    ;
                   The increment for this frame for displacement setting of
                   the specified axis in millimetres.  The sum of the values
                   of '_diffrn_scan_frame_axis.displacement' and
                   '_diffrn_scan_frame_axis.displacement_increment' is the
                   angular setting of the axis at the end of the integration
                   time for this frame.
    ;
        _item.name               '_diffrn_scan_frame_axis.displacement_increment'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_frame_axis.displacement_rstrt_incr
        _item_description.description
    ;
                   The increment for this frame for displacement setting of
                   the specified axis in millimetres.  The sum of the values
                   of '_diffrn_scan_frame_axis.displacement' and
                   '_diffrn_scan_frame_axis.displacement_increment' and
                   '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the
                   angular setting of the axis at the start of the integration
                   time for the next frame, and should equal
                   '_diffrn_scan_frame_axis.displacement' for that next frame.
    ;
        _item.name               '_diffrn_scan_frame_axis.displacement_rstrt_incr'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    save__diffrn_scan_frame_axis.frame_id
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   frame for which axis settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   '_diffrn_scan_frame.frame_id'.
    
                   This item is a pointer to '_diffrn_data_frame.id' in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name               '_diffrn_scan_frame_axis.frame_id'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    ########################   DEPRECATED DATA ITEMS ########################
    
    save__diffrn_detector_axis.id
        _item_description.description
    ;
                   This data item is a pointer to '_diffrn_detector.id' in
                   the DIFFRN_DETECTOR category.
                  
                   DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_detector_axis.id'
        _item.category_id             diffrn_detector_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    save__diffrn_measurement_axis.id
        _item_description.description
    ;
                   This data item is a pointer to '_diffrn_measurement.id' in
                   the DIFFRN_MEASUREMENT category.
                  
                   DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_measurement_axis.id'
        _item.category_id             diffrn_measurement_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    #########################   DEPRECATED CATEGORY #########################
    #####################
    # DIFFRN_FRAME_DATA #
    #####################
    
    
    save_DIFFRN_FRAME_DATA
        _category.description
    ;
                  Data items in the DIFFRN_FRAME_DATA category record
                  the details about each frame of data. 
    
                  The items in this category are now in the
                  DIFFRN_DATA_FRAME category.
                  
                  The items in the DIFFRN_FRAME_DATA category
                  are now deprecated.  The items from this category 
                  are provided as aliases in the 1.0.0 dictionary, 
                  but should not be used for new work.
                  The items from the old category are provided
                  in this dictionary for completeness,
                  but should not be used or cited.  To avoid
                  confusion, the example has been removed,
                  and the redundant parent child-links to other
                  categories removed.
                  
    ;
        _category.id                   diffrn_frame_data
        _category.mandatory_code       no
         loop_
        _category_key.name             '_diffrn_frame_data.id'
                                       '_diffrn_frame_data.detector_element_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        THE DIFFRN_FRAME_DATA category is deprecated and should not be used.
    ;
    ;
           # EXAMPLE REMOVED #
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
    
    
    save__diffrn_frame_data.array_id
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category.
    
                  DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_frame_data.array_id'
        _item.category_id             diffrn_frame_data
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_frame_data.binary_id
        _item_description.description
    ;             This item is a pointer to '_array_data.binary_id' in the
                  ARRAY_STRUCTURE category. 
                  
                  DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_frame_data.binary_id'
        _item.category_id             diffrn_frame_data
        _item.mandatory_code          implicit
        _item_type.code               int
         save_
    
    
    save__diffrn_frame_data.detector_element_id
        _item_description.description
    ;             
                  This item is a pointer to '_diffrn_detector_element.id'
                  in the DIFFRN_DETECTOR_ELEMENT category.
    
                  DEPRECATED -- DO NOT USE 
    ;
        _item.name                  '_diffrn_frame_data.detector_element_id'
        _item.category_id             diffrn_frame_data
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_frame_data.id
        _item_description.description
    ;             
                  The value of '_diffrn_frame_data.id' must uniquely identify
                  each complete frame of data.
    
                  DEPRECATED -- DO NOT USE 
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
               '_diffrn_frame_data.id'        diffrn_frame_data  yes
        _item_type.code               code
         save_
    
    ################ END DEPRECATED SECTION ###########
    
    
    ####################
    ## ITEM_TYPE_LIST ##
    ####################
    #
    #
    #  The regular expressions defined here are not compliant
    #  with the POSIX 1003.2 standard as they include the
    #  '\n' and '\t' special characters.  These regular expressions
    #  have been tested using version 0.12 of Richard Stallman's
    #  GNU regular expression library in POSIX mode.
    #  In order to allow presentation of a regular expression
    #  in a text field concatenate any line ending in a backslash
    #  with the following line, after discarding the backslash.
    #
    #  A formal definition of the '\n' and '\t' special characters
    #  is most properly done in the DDL, but for completeness, please
    #  note that '\n' is the line termination character ('newline')
    #  and '\t' is the horizontal tab character.  There is a formal
    #  ambiguity in the use of '\n' for line termination, in that
    #  the intention is that the equivalent machine/OS-dependent line
    #  termination character sequence should be accepted as a match, e.g.
    #
    #      '\r' (control-M) under MacOS
    #      '\n' (control-J) under Unix
    #      '\r\n' (control-M control-J) under DOS and MS Windows
    #
         loop_
        _item_type_list.code
        _item_type_list.primitive_code
        _item_type_list.construct
        _item_type_list.detail
                   code      char
    '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
    ;              code item types/single words ...
    ;
                   ucode      uchar
    '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
    ;              code item types/single words (case insensitive)
    ;
                   line      char
    '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
    ;              code item types / multi-word items  ...
    ;
                   uline     uchar
    '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
    ;              code item types / multi-word items (case insensitive)
    ;
                   text      char
    '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*'
    ;              text item types / multi-line text ...
    ;
                   binary    char
    ;\n--CIF-BINARY-FORMAT-SECTION--\n\
    [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\
    \n--CIF-BINARY-FORMAT-SECTION----
    ;
    ;              binary items are presented as MIME-like ascii-encoded
                   sections in an imgCIF.  In a CBF, raw octet streams
                   are used to convey the same information.
    ;
                   int       numb
    '-?[0-9]+'
    ;              int item types are the subset of numbers that are the negative
                   or positive integers.
    ;
                   float     numb
    '-?(([0-9]+)|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?'
    ;              float item types are the subset of numbers that are the floating
                   numbers.
    ;
                   any       char
    '.*'
    ;              A catch all for items that may take any form...
    ;
                   yyyy-mm-dd  char
    ;\
    [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9][0-9]\
    (T[0-2][0-9]:[0-5][0-9]:[0-5][0-9](.[0-9]+)([+-][0-5][0-9]:[0-5][0-9]))
    ;
    ;
                   Standard format for CIF date and time strings (see
                   http://www.iucr.org/iucr-top/cif/spec/datetime.html),
                   consisting of a yyyy-mm-dd date optionally followed by
                   the character "T" followed by a 24-hour clock time,
                   optionally followed by a signed time-zone offset.
                   
                   The IUCr standard has been extended to allow for an optional
                   decimal fraction on the seconds of time.
                   
                   Time is local time if no time-zone offset is given.
    ;
    
    
    #####################
    ## ITEM_UNITS_LIST ##
    #####################
    
         loop_
        _item_units_list.code
        _item_units_list.detail
    #
         'metres'                 'metres'
         'centimetres'            'centimetres (metres * 10( -2))'
         'millimetres'            'millimetres (metres * 10( -3))'
         'nanometres'             'nanometres  (metres * 10( -9))'
         'angstroms'              'Ångstroms   (metres * 10(-10))'
         'picometres'             'picometres  (metres * 10(-12))'
         'femtometres'            'femtometres (metres * 10(-15))'
    #
         'reciprocal_metres'      'reciprocal metres (metres(-1))'
         'reciprocal_centimetres' 
            'reciprocal centimetres ((metres * 10( -2))(-1))'
         'reciprocal_millimetres' 
            'reciprocal millimetres ((metres * 10( -3))(-1))'
         'reciprocal_nanometres'  
            'reciprocal nanometres  ((metres * 10( -9))(-1))'
         'reciprocal_angstroms'   
            'reciprocal Ångstroms   ((metres * 10(-10))(-1))'
         'reciprocal_picometres'  
            'reciprocal picometres  ((metres * 10(-12))(-1))'
    #
         'nanometres_squared'     'nanometres squared (metres * 10( -9))2'
         'angstroms_squared'      'Ångstroms squared  (metres * 10(-10))2'
         '8pi2_angstroms_squared' '8π2 * Ångstroms squared (metres * 10(-10))2'
         'picometres_squared'     'picometres squared (metres * 10(-12))2'
    #
         'nanometres_cubed'       'nanometres cubed (metres * 10( -9))3'
         'angstroms_cubed'        'Ångstroms cubed  (metres * 10(-10))3'
         'picometres_cubed'       'picometres cubed (metres * 10(-12))3'
    #
         'kilopascals'            'kilopascals'
         'gigapascals'            'gigapascals'
    #
         'hours'                  'hours'
         'minutes'                'minutes'
         'seconds'                'seconds'
         'microseconds'           'microseconds'
    #
         'degrees'                'degrees (of arc)'
         'degrees_squared'        'degrees (of arc) squared'
    #
         'degrees_per_minute'     'degrees (of arc) per minute'
    #
         'celsius'                'degrees (of temperature) Celsius'
         'kelvins'                'degrees (of temperature) Kelvin'
    #
         'counts'                 'counts'
         'counts_per_photon'      'counts per photon'
    #
         'electrons'              'electrons'
    #
         'electrons_squared'      'electrons squared'
    #
         'electrons_per_nanometres_cubed'
    ; electrons per nanometres cubed (electrons/(metres * 10( -9))(-3))
    ;
         'electrons_per_angstroms_cubed'
    ; electrons per Ångstroms cubed (electrons/(metres * 10(-10))(-3))
    ;
         'electrons_per_picometres_cubed'
    ; electrons per picometres cubed (electrons/(metres * 10(-12))(-3)) 
    ;
         'kilowatts'              'kilowatts'
         'milliamperes'           'milliamperes'
         'kilovolts'              'kilovolts'
    #
         'arbitrary'
    ; arbitrary system of units.
    ;
    #
    
         loop_
        _item_units_conversion.from_code
        _item_units_conversion.to_code
        _item_units_conversion.operator
        _item_units_conversion.factor
    ###
         'metres'                   'centimetres'              '*'   1.0E+02
         'metres'                   'millimetres'              '*'   1.0E+03
         'metres'                   'nanometres'               '*'   1.0E+09
         'metres'                   'angstroms'                '*'   1.0E+10
         'metres'                   'picometres'               '*'   1.0E+12
         'metres'                   'femtometres'              '*'   1.0E+15
    #
         'centimetres'              'metres'                   '*'   1.0E-02
         'centimetres'              'millimetres'              '*'   1.0E+01
         'centimetres'              'nanometres'               '*'   1.0E+07
         'centimetres'              'angstroms'                '*'   1.0E+08
         'centimetres'              'picometres'               '*'   1.0E+10
         'centimetres'              'femtometres'              '*'   1.0E+13
    #
         'millimetres'              'metres'                   '*'   1.0E-03
         'millimetres'              'centimetres'              '*'   1.0E-01
         'millimetres'              'nanometres'               '*'   1.0E+06
         'millimetres'              'angstroms'                '*'   1.0E+07
         'millimetres'              'picometres'               '*'   1.0E+09
         'millimetres'              'femtometres'              '*'   1.0E+12
    #
         'nanometres'               'metres'                   '*'   1.0E-09
         'nanometres'               'centimetres'              '*'   1.0E-07
         'nanometres'               'millimetres'              '*'   1.0E-06
         'nanometres'               'angstroms'                '*'   1.0E+01
         'nanometres'               'picometres'               '*'   1.0E+03
         'nanometres'               'femtometres'              '*'   1.0E+06
    #
         'angstroms'                'metres'                   '*'   1.0E-10
         'angstroms'                'centimetres'              '*'   1.0E-08
         'angstroms'                'millimetres'              '*'   1.0E-07
         'angstroms'                'nanometres'               '*'   1.0E-01
         'angstroms'                'picometres'               '*'   1.0E+02
         'angstroms'                'femtometres'              '*'   1.0E+05
    #
         'picometres'               'metres'                   '*'   1.0E-12
         'picometres'               'centimetres'              '*'   1.0E-10
         'picometres'               'millimetres'              '*'   1.0E-09
         'picometres'               'nanometres'               '*'   1.0E-03
         'picometres'               'angstroms'                '*'   1.0E-02
         'picometres'               'femtometres'              '*'   1.0E+03
    #
         'femtometres'              'metres'                   '*'   1.0E-15
         'femtometres'              'centimetres'              '*'   1.0E-13
         'femtometres'              'millimetres'              '*'   1.0E-12
         'femtometres'              'nanometres'               '*'   1.0E-06
         'femtometres'              'angstroms'                '*'   1.0E-05
         'femtometres'              'picometres'               '*'   1.0E-03
    ###
         'reciprocal_centimetres'   'reciprocal_metres'        '*'   1.0E+02
         'reciprocal_centimetres'   'reciprocal_millimetres'   '*'   1.0E-01
         'reciprocal_centimetres'   'reciprocal_nanometres'    '*'   1.0E-07
         'reciprocal_centimetres'   'reciprocal_angstroms'     '*'   1.0E-08
         'reciprocal_centimetres'   'reciprocal_picometres'    '*'   1.0E-10
    #
         'reciprocal_millimetres'   'reciprocal_metres'        '*'   1.0E+03
         'reciprocal_millimetres'   'reciprocal_centimetres'   '*'   1.0E+01
         'reciprocal_millimetres'   'reciprocal_nanometres'    '*'   1.0E-06
         'reciprocal_millimetres'   'reciprocal_angstroms'     '*'   1.0E-07
         'reciprocal_millimetres'   'reciprocal_picometres'    '*'   1.0E-09
    #
         'reciprocal_nanometres'    'reciprocal_metres'        '*'   1.0E+09
         'reciprocal_nanometres'    'reciprocal_centimetres'   '*'   1.0E+07
         'reciprocal_nanometres'    'reciprocal_millimetres'   '*'   1.0E+06
         'reciprocal_nanometres'    'reciprocal_angstroms'     '*'   1.0E-01
         'reciprocal_nanometres'    'reciprocal_picometres'    '*'   1.0E-03
    #
         'reciprocal_angstroms'     'reciprocal_metres'        '*'   1.0E+10
         'reciprocal_angstroms'     'reciprocal_centimetres'   '*'   1.0E+08
         'reciprocal_angstroms'     'reciprocal_millimetres'   '*'   1.0E+07
         'reciprocal_angstroms'     'reciprocal_nanometres'    '*'   1.0E+01
         'reciprocal_angstroms'     'reciprocal_picometres'    '*'   1.0E-02
    #
         'reciprocal_picometres'    'reciprocal_metres'        '*'   1.0E+12
         'reciprocal_picometres'    'reciprocal_centimetres'   '*'   1.0E+10
         'reciprocal_picometres'    'reciprocal_millimetres'   '*'   1.0E+09
         'reciprocal_picometres'    'reciprocal_nanometres'    '*'   1.0E+03
         'reciprocal_picometres'    'reciprocal_angstroms'     '*'   1.0E+01
    ###
         'nanometres_squared'       'angstroms_squared'        '*'   1.0E+02
         'nanometres_squared'       'picometres_squared'       '*'   1.0E+06
    #
         'angstroms_squared'        'nanometres_squared'       '*'   1.0E-02
         'angstroms_squared'        'picometres_squared'       '*'   1.0E+04
         'angstroms_squared'        '8pi2_angstroms_squared'   '*'   78.9568
    
    #
         'picometres_squared'       'nanometres_squared'       '*'   1.0E-06
         'picometres_squared'       'angstroms_squared'        '*'   1.0E-04
    ###
         'nanometres_cubed'         'angstroms_cubed'          '*'   1.0E+03
         'nanometres_cubed'         'picometres_cubed'         '*'   1.0E+09
    #
         'angstroms_cubed'          'nanometres_cubed'         '*'   1.0E-03
         'angstroms_cubed'          'picometres_cubed'         '*'   1.0E+06
    #
         'picometres_cubed'         'nanometres_cubed'         '*'   1.0E-09
         'picometres_cubed'         'angstroms_cubed'          '*'   1.0E-06
    ###
         'kilopascals'              'gigapascals'              '*'   1.0E-06
         'gigapascals'              'kilopascals'              '*'   1.0E+06
    ###
         'hours'                    'minutes'                  '*'   6.0E+01
         'hours'                    'seconds'                  '*'   3.6E+03
         'hours'                    'microseconds'             '*'   3.6E+09
    #
         'minutes'                  'hours'                    '/'   6.0E+01
         'minutes'                  'seconds'                  '*'   6.0E+01
         'minutes'                  'microseconds'             '*'   6.0E+07
    #
         'seconds'                  'hours'                    '/'   3.6E+03
         'seconds'                  'minutes'                  '/'   6.0E+01
         'seconds'                  'microseconds'             '*'   1.0E+06
    #
         'microseconds'             'hours'                    '/'   3.6E+09
         'microseconds'             'minutes'                  '/'   6.0E+07
         'microseconds'             'seconds'                  '/'   1.0E+06
    ###
         'celsius'                  'kelvins'                  '-'     273.0
         'kelvins'                  'celsius'                  '+'     273.0
    ###
         'electrons_per_nanometres_cubed'
         'electrons_per_angstroms_cubed'                       '*'   1.0E+03
         'electrons_per_nanometres_cubed'
         'electrons_per_picometres_cubed'                      '*'   1.0E+09
    #
         'electrons_per_angstroms_cubed'
         'electrons_per_nanometres_cubed'                      '*'   1.0E-03
         'electrons_per_angstroms_cubed'
         'electrons_per_picometres_cubed'                      '*'   1.0E+06
    #
         'electrons_per_picometres_cubed'
         'electrons_per_nanometres_cubed'                      '*'   1.0E-09
         'electrons_per_picometres_cubed'
         'electrons_per_angstroms_cubed'                       '*'   1.0E-06
    ###
    
    
    ########################
    ## DICTIONARY_HISTORY ##
    ########################
    
         loop_
        _dictionary_history.version
        _dictionary_history.update
        _dictionary_history.revision
    
       1.3.2   2005-06-22
    ;
       Changes as per Nicola Ashcroft.
       + Fix '_item_units.code  code' to be '_item_type.code  code'
       in  '_array_structure_list_axis.axis_id' and in
       '_array_structure_list_axis.axis_set_id'
       Also fix typos in exponents and long lines in units list
       (HJB)
    
    ;
    
       1.3.1   2003-08-13
    ;
       Changes as per Frances C. Bernstein.
       + Identify initials.
       + Adopt British spelling for centre in text.
       + Set π and Ångstrom and powers.
       + Clean up commas and unclear wordings.
       + Clean up tenses in history.
       Changes as per Gotzon Madariaga.
       + Fix the ARRAY_DATA example to align '_array_data.binary_id'
       and X-Binary-Id.
       + Add a range to '_array_intensities.gain_esd'.
       + In the example of DIFFRN_DETECTOR_ELEMENT, 
       '_diffrn_detector_element.id' and
       '_diffrn_detector_element.detector_id' interchanged.
       + Fix typos for direction, detector and axes.
       + Clarify description of polarisation.
       + Clarify axes in '_diffrn_detector_element.center[1]'
        '_diffrn_detector_element.center[2]'.
       + Add local item types for items that are pointers.
       (HJB)
    ;
    
    
       1.3.0   2003-07-24
    ;
       Changes as per Brian McMahon. 
       + Consistently quote tags embedded in text.
       + Clean up introductory comments.
       + Adjust line lengths to fit in 80 character window.
       + Fix several descriptions in AXIS category which
         referred to '_axis.type' instead of the current item.
       + Fix erroneous use of deprecated item
         '_diffrn_detector_axis.id' in examples for 
         DIFFRN_SCAN_AXIS.
       + Add deprecated items '_diffrn_detector_axis.id'
         and '_diffrn_measurement_axis.id'.
       (HJB)
    ;
    
    
       1.2.4   2003-07-14
    ;
       Changes as per I. David Brown. 
       + Enhance descriptions in DIFFRN_SCAN_AXIS to make them less
         dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS.
       + Provide a copy of the deprecated DIFFRN_FRAME_DATA
         category for completeness.
       (HJB)
    ;
    
    
       1.2.3   2003-07-03
    ;
       Cleanup to conform to ITVG. 
       + Correct sign error in ..._cubed units.
       + Correct '_diffrn_radiation.polarisn_norm' range.
       (HJB)
    ;
    
    
       1.2.2   2003-03-10
    ;
       Correction of typos in various DIFFRN_SCAN_AXIS descriptions. 
       (HJB)
    ;
    
    
       1.2.1   2003-02-22
    ;
       Correction of ATOM_ for ARRAY_ typos in various descriptions. 
       (HJB)
    ;
    
    
       1.2     2003-02-07
    ;
       Corrections to encodings (remove extraneous hyphens) remove
       extraneous underscore in '_array_structure.encoding_type'
       enumeration.  Correct typos in items units list.  (HJB)
    ;
    
    
       1.1.3   2001-04-19
    ;
       Another typo corrections by Wilfred Li, and cleanup by HJB.
    ;
    
    
       1.1.2   2001-03-06
    ;
       Several typo corrections by Wilfred Li.
    ;
    
    
       1.1.1   2001-02-16
    ;
       Several typo corrections by JW.
    ;
    
    
       1.1     2001-02-06
    ;
       Draft resulting from discussions on header for use at NSLS.  (HJB)
       
       + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME.
       
       + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'.
       
       + Add '_diffrn_measurement_axis.measurement_device' and change
         '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'.
       
       + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source',
        '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm',
       '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end',
       '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr',
       '_diffrn_scan_axis.displacement_rstrt_incr', 
       '_diffrn_scan_frame_axis.angle_increment',
       '_diffrn_scan_frame_axis.angle_rstrt_incr',
       '_diffrn_scan_frame_axis.displacement',
       '_diffrn_scan_frame_axis.displacement_increment',and
       '_diffrn_scan_frame_axis.displacement_rstrt_incr'.
       
       + Add '_diffrn_measurement.device' to category key.
       
       + Update yyyy-mm-dd to allow optional time with fractional seconds
         for time stamps.
    
       + Fix typos caught by RS.
       
       + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to
         allow for coupled axes, as in spiral scans.
    
       + Add examples for fairly complete headers thanks to R. Sweet and P. 
         Ellis.
    ;
    
    
       1.0     2000-12-21
    ;
       Release version - few typos and tidying up.  (BM & HJB)
       
       + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end
       of dictionary.
       
       + Alphabetize dictionary.
    ;
    
    
       0.7.1   2000-09-29
    ;
       Cleanup fixes.  (JW)
    
       + Correct spelling of diffrn_measurement_axis in '_axis.id'
    
       + Correct ordering of uses of '_item.mandatory_code' and
       '_item_default.value'.
    ;
    
    
       0.7.0   2000-09-09
    ;
       Respond to comments by I. David Brown.  (HJB)
    
       + Add further comments on '\n' and '\t'.
    
       + Update ITEM_UNITS_LIST by taking section from mmCIF dictionary
         and adding metres.  Change 'meter' to 'metre' throughout.
    
       + Add missing enumerations to '_array_structure.compression_type'
         and make 'none' the default.
    
       + Remove parent-child relationship between
         '_array_structure_list.index' and '_array_structure_list.precedence'.
    
       + Improve alphabetization.
    
       + Fix '_array_intensities_gain.esd' related function.
    
       + Improve comments in AXIS.
    
       + Fix DIFFRN_FRAME_DATA example.
    
       + Remove erroneous DIFFRN_MEASUREMENT example.
    
       + Add '_diffrn_measurement_axis.id' to the category key.
    ;
    
    
       0.6.0   1999-01-14
    ;
       Remove redundant information for ENC_NONE data.  (HJB)
    
       + After the D5 remove binary section identifier, size and
         compression type.
    
       + Add Control-L to header.
    ;
    
    
       0.5.1   1999-01-03
    ;
       Cleanup of typos and syntax errors.  (HJB)
    
       + Cleanup example details for DIFFRN_SCAN category.
    
       + Add missing quote marks for '_diffrn_scan.id' definition.
    ;
    
    
       0.5   1999-01-01
    ;
       Modifications for axis definitions and reduction of binary header.  (HJB)
    
       + Restore '_diffrn_detector.diffrn_id' to DIFFRN_DETECTOR KEY.
    
       + Add AXIS category.
    
       + Bring in complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories
         from cif_mm.dic for clarity.
    
       + Change '_array_structure.encoding_type' from type code to uline and
         added X-Binary-Element-Type to MIME header.
    
       + Add detector beam centre '_diffrn_detector_element.center[1]' and 
         '_diffrn_detector_element.center[2]'.
    
       + Correct item name of '_diffrn_refln.frame_id'.
    
       + Replace reference to '_array_intensities.undefined' by
         '_array_intensities.undefined_value'.
    
       + Replace references to '_array_intensity.scaling' with
         '_array_intensities.scaling'.
    
       + Add DIFFRN_SCAN... categories.
    ;
    
    
       0.4   1998-08-11
    ;
       Modifications to the 0.3 imgCIF draft.  (HJB)
    
       + Reflow comment lines over 80 characters and corrected typos.
    
       + Update examples and descriptions of MIME encoded data.
    
       + Change name to cbfext98.dic.
    ;
    
    
       0.3   1998-07-04
    ;
       Modifications for imgCIF.  (HJB)
    
       + Add binary type, which is a text field containing a variant on
         MIME encoded data.
          
       + Change type of '_array_data.data' to binary and specify internal
         structure of raw binary data.
          
       + Add '_array_data.binary_id', and make 
         '_diffrn_frame_data.binary_id' and '_array_intensities.binary_id'
         into pointers to this item.
    ;
    
    
       0.2   1997-12-02
    ;
       Modifications to the CBF draft.  (JW)  
    
       + Add category hierarchy for describing frame data developed from
         discussions at the BNL imgCIF Workshop Oct 1997.   The following
         changes are made in implementing the workshop draft.  Category
         DIFFRN_ARRAY_DATA is renamed to DIFFRN_FRAME_DATA.  Category
         DIFFRN_FRAME_TYPE is renamed to DIFFRN_DETECTOR_ELEMENT.   The
         parent item for '_diffrn_frame_data.array_id' is changed from
         '_array_structure_list.array_id' to '_array_structure.id'. Item 
         '_diffrn_detector.array_id' is deleted.  
       + Add data item '_diffrn_frame_data.binary_id' to identify data 
         groups within a binary section.  The formal identification of the
         binary section is still fuzzy.  
    ;
    
    
       0.1   1997-01-24
    ;
       First draft of this dictionary in DDL 2.1 compliant format by John 
       Westbrook (JW).  This version is adapted from the Crystallographic 
       Binary File (CBF) Format Draft Proposal provided by Andy Hammersley
       (AH).  
    
       Modifications to the CBF draft.  (JW)  
    
       + In this version the array description has been cast in the categories 
         ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST.  These categories
         have been generalized to describe array data  of arbitrary dimension.  
    
       + Array data in this description are contained in the category
         ARRAY_DATA.  This departs from the CBF notion of data existing
         in some special comment. In this description, data is handled as an 
         ordinary data item encapsulated in a character data type.   Although
         data this manner deviates from CIF conventions, it does not violate 
         any DDL 2.1 rules.  DDL 2.1 regular expressions can be used to define 
         the binary representation which will permit some level of data 
         validation.  In this version, the placeholder type code "any" has
         been used. This translates to a regular expression which will match 
         any pattern.
    
         It should be noted that DDL 2.1 already supports array data objects 
         although these have not been used in the current mmCIF dictionary.
         It may be possible to use the DDL 2.1 ITEM_STRUCTURE and
         ITEM_STRUCTURE_LIST categories to provide the information that is
         carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST.  By
         moving the array structure to the DDL level it would be possible to
         define an array type as well as a regular expression defining the
         data format. 
    
       + Multiple array sections can be properly handled within a single
         datablock.
    ;
    
    
    #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof
    
    ./CBFlib-0.9.2.2/doc/cif_img_1_3.html0000644000076500007650000070344311603702115015303 0ustar yayayaya cif_img.dic v1.3.0

    # [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib] #

    # imgCIF/CBF #

    # Extensions Dictionary #

    ##############################################################################
    #                                                                            #
    #                       Image CIF Dictionary (imgCIF)                        #
    #             and Crystallographic Binary File Dictionary (CBF)              #
    #            Extending the Macromolecular CIF Dictionary (mmCIF)             #
    #                                                                            #
    #                              Version 1.3.0                                 #
    #                              of 2003-07-24                                 #
    #                                                                            #
    #     by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook    #
    #                                                                            #
    # This dictionary was adapted from format discussed at the imgCIF Workshop,  #
    # held at BNL Oct 1997 and the Crystallographic Binary File Format Draft     #
    # Proposal by Andrew Hammersley.  The first DDL 2.1 Version was created by   #
    # John Westbrook.  This version was drafted by Herbert J. Bernstein and      #
    # incorporates comments by I. David Brown, John Westbrook, Brian McMahon,    #
    # Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li and others.                #
    ##############################################################################
                                                                        
    data_cif_img.dic
    
        _dictionary.title           cif_img.dic
        _dictionary.version         1.3.0
        _dictionary.datablock_id    cif_img.dic
    
    ##############################################################################
    #    CONTENTS
    #
    #        CATEGORY_GROUP_LIST
    #
    #        category  ARRAY_DATA
    #
    #                  _array_data.array_id
    #                  _array_data.binary_id
    #                  _array_data.data
    #
    #        category  ARRAY_ELEMENT_SIZE
    #        
    #                  _array_element_size.array_id
    #                  _array_element_size.index
    #                  _array_element_size.size
    #        
    #        category  ARRAY_INTENSITIES
    #        
    #                  _array_intensities.array_id
    #                  _array_intensities.binary_id
    #                  _array_intensities.gain
    #                  _array_intensities.gain_esd
    #                  _array_intensities.linearity
    #                  _array_intensities.offset
    #                  _array_intensities.scaling
    #                  _array_intensities.overload
    #                  _array_intensities.undefined_value
    #        
    #        category  ARRAY_STRUCTURE
    #        
    #                  _array_structure.byte_order
    #                  _array_structure.compression_type
    #                  _array_structure.encoding_type
    #                  _array_structure.id
    #        
    #        category  ARRAY_STRUCTURE_LIST
    #        
    #                  _array_structure_list.axis_set_id
    #                  _array_structure_list.array_id
    #                  _array_structure_list.dimension
    #                  _array_structure_list.direction
    #                  _array_structure_list.index
    #                  _array_structure_list.precedence
    #
    #        category  ARRAY_STRUCTURE_LIST_AXIS
    #        
    #                  _array_structure_list_axis.axis_id
    #                  _array_structure_list_axis.axis_set_id
    #                  _array_structure_list_axis.angle
    #                  _array_structure_list_axis.angle_increment
    #                  _array_structure_list_axis.displacement_increment
    #                  _array_structure_list_axis.angular_pitch
    #                  _array_structure_list_axis.radial_pitch
    #
    #        category  AXIS
    #        
    #                  _axis.depends_on
    #                  _axis.equipment
    #                  _axis.id
    #                  _axis.offset[1]
    #                  _axis.offset[2]
    #                  _axis.offset[3]
    #                  _axis.type
    #                  _axis.vector[1]
    #                  _axis.vector[2]
    #                  _axis.vector[3]
    #
    #        category  DIFFRN_DATA_FRAME
    #
    #                  _diffrn_data_frame.array_id
    #                  _diffrn_data_frame.binary_id
    #                  _diffrn_data_frame.detector_element_id
    #                  _diffrn_data_frame.id
    #
    #        category  DIFFRN_DETECTOR
    #        
    #                  _diffrn_detector.details
    #                  _diffrn_detector.detector
    #                  _diffrn_detector.diffrn_id
    #                  _diffrn_detector.dtime
    #                  _diffrn_detector.id
    #                  _diffrn_detector.number_of_axes
    #                  _diffrn_detector.type
    #
    #        category  DIFFRN_DETECTOR_AXIS
    #        
    #                  _diffrn_detector_axis.axis_id
    #                  _diffrn_detector_axis.detector_id    
    #        
    #        category  DIFFRN_DETECTOR_ELEMENT
    #
    #                  _diffrn_detector_element.center[1]
    #                  _diffrn_detector_element.center[2]
    #                  _diffrn_detector_element.id
    #                  _diffrn_detector_element.detector_id
    #        
    #        category  DIFFRN_MEASUREMENT
    #        
    #                  _diffrn_measurement.diffrn_id
    #                  _diffrn_measurement.details
    #                  _diffrn_measurement.device
    #                  _diffrn_measurement.device_details
    #                  _diffrn_measurement.device_type
    #                  _diffrn_measurement.id
    #                  _diffrn_measurement.method
    #                  _diffrn_measurement.number_of_axes
    #                  _diffrn_measurement.specimen_support
    #
    #        category  DIFFRN_MEASUREMENT_AXIS
    #        
    #                  _diffrn_measurement_axis.axis_id
    #                  _diffrn_measurement_axis.measurement_device
    #                  _diffrn_measurement_axis.measurement_id
    #
    #        category  DIFFRN_RADIATION
    #
    #                  _diffrn_radiation.collimation
    #                  _diffrn_radiation.diffrn_id
    #                  _diffrn_radiation.div_x_source
    #                  _diffrn_radiation.div_y_source
    #                  _diffrn_radiation.div_x_y_source
    #                  _diffrn_radiation.filter_edge'
    #                  _diffrn_radiation.inhomogeneity
    #                  _diffrn_radiation.monochromator
    #                  _diffrn_radiation.polarisn_norm
    #                  _diffrn_radiation.polarisn_ratio
    #                  _diffrn_radiation.polarizn_source_norm
    #                  _diffrn_radiation.polarizn_source_ratio
    #                  _diffrn_radiation.probe
    #                  _diffrn_radiation.type
    #                  _diffrn_radiation.xray_symbol
    #                  _diffrn_radiation.wavelength_id
    #        
    #        category  DIFFRN_REFLN
    #        
    #                  _diffrn_refln.frame_id
    #
    #        category  DIFFRN_SCAN
    #        
    #                  _diffrn_scan.id
    #                  _diffrn_scan.date_end
    #                  _diffrn_scan.date_start
    #                  _diffrn_scan.integration_time
    #                  _diffrn_scan.frame_id_start
    #                  _diffrn_scan.frame_id_end
    #                  _diffrn_scan.frames
    #
    #        category  DIFFRN_SCAN_AXIS
    #        
    #                  _diffrn_scan_axis.axis_id
    #                  _diffrn_scan_axis.angle_start
    #                  _diffrn_scan_axis.angle_range
    #                  _diffrn_scan_axis.angle_increment
    #                  _diffrn_scan_axis.angle_rstrt_incr
    #                  _diffrn_scan_axis.displacement_start
    #                  _diffrn_scan_axis.displacement_range
    #                  _diffrn_scan_axis.displacement_increment
    #                  _diffrn_scan_axis.displacement_rstrt_incr
    #                  _diffrn_scan_axis.scan_id
    #
    #        category  DIFFRN_SCAN_FRAME
    #        
    #                  _diffrn_scan_frame.date
    #                  _diffrn_scan_frame.frame_id
    #                  _diffrn_scan_frame.frame_number
    #                  _diffrn_scan_frame.integration_time
    #                  _diffrn_scan_frame.scan_id
    #
    #        category  DIFFRN_SCAN_FRAME_AXIS
    #        
    #                  _diffrn_scan_frame_axis.axis_id
    #                  _diffrn_scan_frame_axis.angle
    #                  _diffrn_scan_frame_axis.angle_increment
    #                  _diffrn_scan_frame_axis.angle_rstrt_incr
    #                  _diffrn_scan_frame_axis.displacement
    #                  _diffrn_scan_frame_axis.displacement_increment
    #                  _diffrn_scan_frame_axis.displacement_rstrt_incr
    #                  _diffrn_scan_frame_axis.frame_id
    #
    #       ***DEPRECATED*** data items
    #
    #                  _diffrn_detector_axis.id
    #                  _diffrn_measurement_axis.id
    #
    #       ***DEPRECATED*** category  DIFFRN_FRAME_DATA
    #
    #                  _diffrn_frame_data.array_id
    #                  _diffrn_frame_data.binary_id
    #                  _diffrn_frame_data.detector_element_id
    #                  _diffrn_frame_data.id
    #
    #
    #        ITEM_TYPE_LIST
    #        ITEM_UNITS_LIST
    #        DICTIONARY_HISTORY
    #
    ##############################################################################
    
    
    #########################
    ## CATEGORY_GROUP_LIST ##
    #########################
    
         loop_
        _category_group_list.id
        _category_group_list.parent_id
        _category_group_list.description
                 'inclusive_group'   .
    ;             Categories that belong to the dictionary extension.
    ;
                 'array_data_group'
                 'inclusive_group'
    ;             Categories that describe array data.
    ;
                 'axis_group'
                 'inclusive_group'
    ;             Categories that describe axes.
    ;
                 'diffrn_group'
                 'inclusive_group'
    ;            Categories that describe details of the diffraction experiment.
    ;
     
     
     
     
    ##############
    # ARRAY_DATA #
    ##############
     
      
    save_ARRAY_DATA
        _category.description
    ;
         Data items in the ARRAY_DATA category are the containers for
         the array data items described in category ARRAY_STRUCTURE.
    ;
        _category.id                   array_data
        _category.mandatory_code       no
         loop_
        _category_key.name             '_array_data.array_id'
                                       '_array_data.binary_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 -
    
            This example shows two binary data blocks.  The first one
            was compressed by the CBF_CANONICAL compression algorithm and
            presented as hexadecimal data.  The first character "H" on the
            data lines means hexadecimal.  It could have been "O" for octal
            or "D" for decimal.  The second character on the line shows
            the number of bytes in each word (in this case "4"), which then
            requires 8 hexadecimal digits per word.  The third character
            gives the order of octets within a word, in this case "<"
            for the ordering 4321 (i.e. "big-endian").  Alternatively the
            character ">" could have been used for the ordering 1234
            (i.e. "little-endian").  The block has a "message digest"
            to check the integrity of the data.
    
            The second block is similar, but uses CBF_PACKED compression
            and BASE64 encoding.  Note that the size and the digest are
            different.
    ;
    ;
    
            loop_
            _array_data.array_id
            _array_data.binary_id
            _array_data.data
            image_1 1
            ;
            --CIF-BINARY-FORMAT-SECTION--
            Content-Type: application/octet-stream;
                 conversions="x-CBF_CANONICAL"
            Content-Transfer-Encoding: X-BASE16
            X-Binary-Size: 3927126
            X-Binary-ID: 1
            Content-MD5: u2sTJEovAHkmkDjPi+gWsg==
    
            # Hexadecimal encoding, byte 0, byte order ...21
            #
            H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ...
            ....
            --CIF-BINARY-FORMAT-SECTION----
            ;
            image_2 2
            ;
            --CIF-BINARY-FORMAT-SECTION--
            Content-Type: application/octet-stream;
                 conversions="x-CBF-PACKED"
            Content-Transfer-Encoding: BASE64
            X-Binary-Size: 3745758
            X-Binary-ID: 1
            Content-MD5: 1zsJjWPfol2GYl2V+QSXrw==
    
            ELhQAAAAAAAA...
            ...
            --CIF-BINARY-FORMAT-SECTION----
            ;
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    save_
     
     
    save__array_data.array_id
        _item_description.description
    ;             This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category. 
    ;
        _item.name                  '_array_data.array_id'
        _item.category_id             array_data
        _item.mandatory_code          yes
        _item_type.code               code
         save_
     
     
    save__array_data.binary_id
        _item_description.description
    ;             This item is an integer identifier which, along with
                  '_array_data.array_id' should uniquely identify the 
                  particular block of array data.
                  
                  If '_array_data.binary_id' is not explicitly given,
                  it defaults to 1.
                  
                  The value of '_array_data.binary_id' distinguishes
                  among multiple sets of data with the same array
                  structure.
                  
                  If the MIME header of the data array specifies a 
                  value for X-Binary-Id, these values should be equal.
    ;
         loop_
        _item.name                  
        _item.category_id             
        _item.mandatory_code          
                 '_array_data.binary_id'            array_data      
                                                                    implicit
                 '_diffrn_data_frame.binary_id'     diffrn_data_frame
                                                                    implicit
                 '_array_intensities.binary_id'     array_intensities
                                                                    implicit
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_data_frame.binary_id'     '_array_data.binary_id'
                 '_array_intensities.binary_id'     '_array_data.binary_id'
    
        _item_default.value           1
        _item_type.code               int
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                1  1
                                .  1
         save_
     
     
    save__array_data.data
        _item_description.description
    ;             The value of '_array_data.data' contains the array data 
                  encapsulated in a STAR string.
                  
                  The representation used is a variant on the
                  Multipurpose Internet Mail Extensions (MIME) specified
                  in RFC 2045-2049 by N. Freed et al.  The boundary
                  delimiter used in writing an imgCIF or CBF is
                  "--CIF-BINARY-FORMAT-SECTION--" (including the
                  required initial "--").
    
                  The Content-Type may be any of the discrete types permitted
                  in RFC 2045; "application/octet-stream" is recommended.  
                  If an octet stream was compressed, the compression should 
                  be specified by the parameter 'conversions="x-CBF_PACKED"' 
                  or the parameter 'conversions="x-CBF_CANONICAL"'.
                  
                  The Content-Transfer-Encoding may be "BASE64",
                  "Quoted-Printable", "X-BASE8", "X-BASE10", or
                  "X-BASE16" for an imgCIF or "BINARY" for a CBF.  The
                  octal, decimal and hexadecimal transfer encodings are
                  for convenience in debugging, and are not recommended
                  for archiving and data interchange.
                  
                  In an imgCIF file, the encoded binary data begins after
                  the empty line terminating the header.  In a CBF, the
                  raw binary data begins after an empty line terminating
                  the header and after the sequence:
                        
                  Octet   Hex   Decimal  Purpose
                    0     0C       12    (ctrl-L) Page break
                    1     1A       26    (ctrl-Z) Stop listings in MS-DOS
                    2     04       04    (Ctrl-D) Stop listings in UNIX
                    3     D5      213    Binary section begins
    
                  None of these octets are included in the calculation of
                  the message size, nor in the calculation of the
                  message digest.
                                 
                  The X-Binary-Size header specifies the size of the
                  equivalent binary data in octets.  If compression was
                  used, this size is the size after compression, including
                  any book-keeping fields.  An adjustment is made for
                  the deprecated binary formats in which 8 bytes of binary
                  header are used for the compression type.  In that case,
                  the 8 bytes used for the compression type is subtracted
                  from the size, so that the same size will be reported
                  if the compression type is supplied in the MIME header.
                  Use of the MIME header is the recommended way to
                  supply the compression type.  In general, no portion of
                  the  binary header is included in the calculation of the size.
    
                  The X-Binary-Element-Type header specifies the type of
                  binary data in the octets, using the same descriptive
                  phrases as in '_array_structure.encoding_type'.  The default
                  value is "unsigned 32-bit integer".
                  
                  An MD5 message digest may, optionally, be used. The "RSA Data
                  Security, Inc. MD5 Message-Digest Algorithm" should be used.
                  No portion of the header is included in the calculation of the
                  message digest.
    
                  If the Transfer Encoding is "X-BASE8", "X-BASE10", or
                  "X-BASE16", the data is presented as octal, decimal or
                  hexadecimal data organized into lines or words.  Each word
                  is created by composing octets of data in fixed groups of
                  2, 3, 4, 6 or 8 octets, either in the order ...4321 ("big-
                  endian") or 1234... (little-endian).  If there are fewer
                  than the specified number of octets to fill the last word,
                  then the missing octets are presented as "==" for each
                  missing octet.  Exactly two equal signs are used for each
                  missing octet even for octal and decimal encoding.
                  The format of lines is:
    
                  rnd xxxxxx xxxxxx xxxxxx
    
                  where r is "H", "O", or "D" for hexadecimal, octal or
                  decimal, n is the number of octets per word. and d is "<"
                  for ">" for the "...4321" and "1234..." octet orderings
                  respectively.  The "==" padding for the last word should
                  be on the appropriate side to correspond to the missing
                  octets, e.g.
    
                  H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000
    
                  or
    
                  H3> FF0700 00====
    
                  For these hex, octal and decimal formats, only, comments
                  beginning with "#" are permitted to improve readability.
    
                  BASE64 encoding follows MIME conventions.  Octets are
                  in groups of three, c1, c2, c3.  The resulting 24 bits 
                  are broken into four 6-bit quantities, starting with 
                  the high-order six bits (c1 >> 2) of the first octet, then
                  the low-order two bits of the first octet followed by the
                  high-order 4 bits of the second octet ((c1 & 3)<<4 | (c2>>4)),
                  then the bottom 4 bits of the second octet followed by the
                  high order two bits of the last octet ((c2 & 15)<<2 | (c3>>6)),
                  then the bottom six bits of the last octet (c3 & 63).  Each
                  of these four quantities is translated into an ASCII character
                  using the mapping:
    
                            1         2         3         4         5         6
                  0123456789012345678901234567890123456789012345678901234567890123
                  |         |         |         |         |         |         |
                  ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/
    
                  With short groups of octets padded on the right with one "="
                  if c3 is missing, and with "==" if both c2 and c3 are missing.
    
                  QUOTED-PRINTABLE encoding also follows MIME conventions, copying
                  octets without translation if their ASCII values are 32..38,
                  42, 48..57, 59..60, 62, 64..126 and the octet is not a ";"
                  in column 1.  All other characters are translated to =nn, where
                  nn is the hexadecimal encoding of the octet.  All lines are
                  "wrapped" with a terminating "=" (i.e. the MIME conventions
                  for an implicit line terminator are never used).
    ;
        _item.name                  '_array_data.data'
        _item.category_id             array_data
        _item.mandatory_code          yes
        _item_type.code               binary
    save_
     
     
    ######################
    # ARRAY_ELEMENT_SIZE #
    ######################
     
     
    save_ARRAY_ELEMENT_SIZE
        _category.description
    ;
         Data items in the ARRAY_ELEMENT_SIZE category record the physical 
         size of array elements along each array dimension.
    ;
        _category.id                   array_element_size
        _category.mandatory_code       no
         loop_
        _category_key.name             '_array_element_size.array_id'
                                       '_array_element_size.index'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 - A regular 2D array with a uniform element dimension
                        of 1220 nanometres.
    ;
    ;
            loop_
           _array_element_size.array_id  
           _array_element_size.index
           _array_element_size.size
            image_1   1    1.22e-6
            image_1   2    1.22e-6
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
     
     
    save__array_element_size.array_id
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category. 
    ;
        _item.name                  '_array_element_size.array_id'
        _item.category_id             array_element_size
        _item.mandatory_code          yes
        _item_type.code               code
         save_
     
     
    save__array_element_size.index
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure_list.index' in
                  the ARRAY_STRUCTURE_LIST category. 
    ;
        _item.name                  '_array_element_size.index'
        _item.category_id             array_element_size
        _item.mandatory_code          yes
        _item_type.code               code
         save_
     
     
    save__array_element_size.size
        _item_description.description
    ;
                   The size in metres of an image element in this 
                   dimension. This supposes that the elements are arranged
                   on a regular grid.
    ;
        _item.name               '_array_element_size.size'
        _item.category_id          array_element_size
        _item.mandatory_code       yes 
        _item_type.code            float
        _item_units.code           'metres'
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0.0
         save_
     
     
    #####################
    # ARRAY_INTENSITIES #
    #####################
     
     
    save_ARRAY_INTENSITIES
        _category.description
    ;
                  Data items in the ARRAY_INTENSITIES category record the
                  information required to recover the intensity data from 
                  the set of data values stored in the ARRAY_DATA category.
    
                  The actual detector may have a complex relationship
                  between the raw intensity values and the number of
                  incident photons.  In most cases, the number stored
                  in the final array will have a simple linear relationship
                  to the actual number of incident photons, given by
                  '_array_intensities.gain'.  If raw, uncorrected values
                  are presented (e.g for calibration experiments), the
                  value of '_array_intensities.linearity' will be 'raw'
                  and '_array_intensities.gain' will not be used.
    
    ;
        _category.id                   array_intensities
        _category.mandatory_code       no
        loop_
        _category_key.name             '_array_intensities.array_id'
                                       '_array_intensities.binary_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1
    ;
    ;
            loop_
            _array_intensities.array_id
            _array_intensities.linearity 
            _array_intensities.gain      
            _array_intensities.overload  
            _array_intensities.undefined_value 
            image_1   linear  1.2    655535   0
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
     
     
    save__array_intensities.array_id
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category. 
    ;
        _item.name                  '_array_intensities.array_id'
        _item.category_id             array_intensities
        _item.mandatory_code          yes
        _item_type.code               code
         save_
     
     
    save__array_intensities.binary_id
        _item_description.description
    ;             This item is a pointer to '_array_data.binary_id' in the
                  ARRAY_DATA category. 
    ;
        _item.name                  '_array_intensities.binary_id'
        _item.category_id             array_intensities
        _item.mandatory_code          implicit
        _item_type.code               int
         save_
     
     
    save__array_intensities.gain
        _item_description.description
    ;              
                   Detector "gain". The factor by which linearized 
                   intensity count values should be divided to produce
                   true photon counts.
    ;
        _item.name              '_array_intensities.gain'
        _item.category_id          array_intensities
        _item.mandatory_code       yes
        _item_type.code            float
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0.0
        _item_units.code           'counts_per_photon'
         loop_
        _item_related.related_name
        _item_related.function_code  '_array_intensities.gain_esd'
                                     'associated_value'
        save_
     
      
    save__array_intensities.gain_esd
        _item_description.description
    ;              
                  The estimated standard deviation in detector "gain".
    ;
        _item.name              '_array_intensities.gain_esd'
        _item.category_id          array_intensities
        _item.mandatory_code       yes
        _item_type.code            float
    
        _item_units.code          'counts_per_photon'
         loop_
        _item_related.related_name
        _item_related.function_code  '_array_intensities.gain'
                                     'associated_esd'
        save_
     
     
    save__array_intensities.linearity
        _item_description.description
    ;
                   The intensity linearity scaling used from raw intensity
                   to the stored element value:
    
                   'linear' is obvious
    
                   'offset'  means that the value defined by 
                   '_array_intensities.offset' should be added to each
                    element value.  
    
                   'scaling' means that the value defined by 
                   '_array_intensities.scaling' should be multiplied with each 
                   element value.  
    
                   'scaling_offset' is the combination of the two previous cases, 
                   with the scale factor applied before the offset value.
    
                   'sqrt_scaled' means that the square root of raw 
                   intensities multiplied by '_array_intensities.scaling' is
                   calculated and stored, perhaps rounded to the nearest 
                   integer. Thus, linearization involves dividing the stored
                   values by '_array_intensities.scaling' and squaring the 
                   result. 
    
                   'logarithmic_scaled' means that the logarithm based 10 of
                   raw intensities multiplied by '_array_intensities.scaling' 
                   is calculated and stored, perhaps rounded to the nearest 
                   integer. Thus, linearization involves dividing the stored
                   values by '_array_intensities.scaling' and calculating 10
                   to the power of this number.
    
                   'raw' means that the data is the raw is a set of raw values
                   straight from the detector.
    ;
    
        _item.name               '_array_intensities.linearity'
        _item.category_id          array_intensities
        _item.mandatory_code       yes
        _item_type.code            code
         loop_
        _item_enumeration.value   
        _item_enumeration.detail   
                                  'linear' .
                                  'offset'           
    ;
                   The value defined by  '_array_intensities.offset' should 
                   be added to each element value.  
    ;
                                  'scaling'
    ;
                   The value defined by '_array_intensities.scaling' should be 
                   multiplied with each element value.  
    ;
                                  'scaling_offset'   
    ;
                   The combination of the scaling and offset 
                   with the scale factor applied before the offset value.
    ;
                                  'sqrt_scaled'      
    ;
                   The square root of raw intensities multiplied by 
                   '_array_intensities.scaling' is calculated and stored, 
                   perhaps rounded to the nearest integer. Thus, 
                   linearization involves dividing the stored
                   values by '_array_intensities.scaling' and squaring the 
                   result. 
    ;
                                  'logarithmic_scaled'
    ;
                   The logarithm based 10 of raw intensities multiplied by 
                   '_array_intensities.scaling'  is calculated and stored, 
                   perhaps rounded to the nearest integer. Thus, 
                   linearization involves dividing the stored values by 
                   '_array_intensities.scaling' and calculating 10 to the 
                   power of this number.
    ;
                                  'raw'
    ;
                   The array consists of raw values to which no corrections have
                   been applied.  While the handling of the data is similar to 
                   that given for 'linear' data with no offset, the meaning of 
                   the data differs in that the number of incident photons is 
                   not necessarily linearly related to the number of counts 
                   reported.  This value is intended for use either in 
                   calibration experiments or to allow for handling more 
                   complex data fitting algorithms than are allowed for by 
                   this data item.
    ;
    
        save_
      
      
    save__array_intensities.offset
        _item_description.description
    ;
                   Offset value to add to array element values in the manner
                   described by item '_array_intensities.linearity'.
    ;
        _item.name                 '_array_intensities.offset'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        save_
     
     
    save__array_intensities.scaling
        _item_description.description
    ;
                   Multiplicative scaling value to be applied to array data
                   in the manner described by item
                   '_array_intensities.linearity'.
    ;
        _item.name                 '_array_intensities.scaling'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        save_
     
     
    save__array_intensities.overload
        _item_description.description
    ;
                   The saturation intensity level for this data array.
    ;
        _item.name                 '_array_intensities.overload'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        _item_units.code          'counts'
        save_
     
      
    save__array_intensities.undefined_value
        _item_description.description
    ;
                   A value to be substituted for undefined values in 
                   the data array.
    ;
        _item.name                 '_array_intensities.undefined_value'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        save_
     
     
    ###################
    # ARRAY_STRUCTURE #
    ###################
     
     
    save_ARRAY_STRUCTURE
        _category.description
    ;
         Data items in the ARRAY_STRUCTURE category record the organization and 
         encoding of array data which may be stored in the ARRAY_DATA category.
    ;
        _category.id                   array_structure
        _category.mandatory_code       no
        _category_key.name             '_array_structure.id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 -
    ;
    ;
         loop_
        _array_structure.id 
        _array_structure.encoding_type        
        _array_structure.compression_type     
        _array_structure.byte_order           
         image_1       "unsigned 16-bit integer"  none  little_endian
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
     
     
    save__array_structure.byte_order
        _item_description.description
    ;
                   The order of bytes for integer values which require more
                   than 1-byte. 
    
                   (IBM-PC's and compatibles, and Dec-Vaxes use low-byte-first
                   ordered integers, whereas Hewlett Packard 700 
                   series, Sun-4 and Silicon Graphics use high-byte-first
                   ordered integers.  Dec-Alphas can produce/use either
                   depending on a compiler switch.)
    ;
    
        _item.name                     '_array_structure.byte_order'
        _item.category_id               array_structure
        _item.mandatory_code            yes 
        _item_type.code                 code
         loop_
        _item_enumeration.value        
        _item_enumeration.detail        
                                       'big_endian'
    ;
            The first byte in the byte stream of the bytes which make up an 
            integer value is the most significant byte of an integer. 
    ;
                                       'little_endian'
    ;
            The last byte in the byte stream of the bytes which make up an 
            integer value is the most significant byte of an integer.
    ;
         save_
     
     
    save__array_structure.compression_type 
        _item_description.description
    ;
                  Type of data compression method used to compress the array
                  data. 
    ;
        _item.name                   '_array_structure.compression_type'
        _item.category_id             array_structure
        _item.mandatory_code          no 
        _item_type.code               code
        _item_default.value           'none'
         loop_
        _item_enumeration.value       
        _item_enumeration.detail
                                      'none'
    ;
            Data are stored in normal format as defined by 
            '_array_structure.encoding_type' and 
            '_array_structure.byte_order'.
    ;
                                      'byte_offsets'
    ;
            Using the compression scheme defined in CBF definition
            Section 5.0.
    ;
                                      'packed'
    ;
            Using the 'packed' compression scheme, a CCP4-style packing
            (CBFlib section 3.3.2)
    ;
                                      'canonical'
    ;
            Using the 'canonical' compression scheme (CBFlib section
            3.3.1)
    ;
        save_
     
     
    save__array_structure.encoding_type
        _item_description.description
    ;
                   Data encoding of a single element of array data. 
                   
                   In several cases, the IEEE format is referenced.
                   See "IEEE Standard for Binary Floating-Point Arithmetic",
                   ANSI/IEEE Std 754-1985, the Institute of Electrical and
                   Electronics Engineers, Inc., NY 1985.  
    ;
    
        _item.name                '_array_structure.encoding_type'
        _item.category_id          array_structure
        _item.mandatory_code       yes 
        _item_type.code            uline
         loop_
        _item_enumeration.value   
                                  'unsigned 8-bit integer'
                                  'signed 8-bit integer'
                                  'unsigned 16-bit integer'
                                  'signed 16-bit integer'
                                  'unsigned 32-bit integer'
                                  'signed 32-bit integer'
                                  'signed 32-bit real IEEE'
                                  'signed 64-bit real IEEE'
                                  'signed 32-bit complex IEEE'
         save_
     
     
    save__array_structure.id
        _item_description.description
    ;             The value of '_array_structure.id' must uniquely identify 
                  each item of array data. 
    ;
        loop_
        _item.name                  
        _item.category_id             
        _item.mandatory_code          
                 '_array_structure.id'              array_structure      yes
                 '_array_data.array_id'             array_data           yes
                 '_array_structure_list.array_id'   array_structure_list yes
                 '_array_intensities.array_id'      array_intensities    yes
                 '_diffrn_data_frame.array_id'      diffrn_data_frame    yes
     
    
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_array_data.array_id'             '_array_structure.id'
                 '_array_structure_list.array_id'   '_array_structure.id'
                 '_array_intensities.array_id'      '_array_structure.id'
                 '_diffrn_data_frame.array_id'      '_array_structure.id'
    
         save_
     
     
    ########################
    # ARRAY_STRUCTURE_LIST #
    ########################
     
     
    save_ARRAY_STRUCTURE_LIST
        _category.description
    ;
         Data items in the ARRAY_STRUCTURE_LIST category record the size 
         and organization of each array dimension.
    
         The relationship to physical axes may be given.
    ;
        _category.id                   array_structure_list
        _category.mandatory_code       no
         loop_
        _category_key.name             '_array_structure_list.array_id'
                                       '_array_structure_list.index'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 - An image array of 1300 x 1200 elements.  The raster 
                        order of the image is left-to-right (increasing) in 
                        first dimension and bottom-to-top (decreasing) in 
                        the second dimension.
    ;
    ;
            loop_
           _array_structure_list.array_id  
           _array_structure_list.index
           _array_structure_list.dimension 
           _array_structure_list.precedence 
           _array_structure_list.direction
           _array_structure_list.axis_set_id
            image_1   1    1300    1     increasing  ELEMENT_X
            image_1   2    1200    2     decreasing  ELEMENY_Y
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
     
     
    save__array_structure_list.array_id
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category. 
    ;
        _item.name                  '_array_structure_list.array_id'
        _item.category_id             array_structure_list
        _item.mandatory_code          yes
        _item_type.code               code
    save_
     
     
    save__array_structure_list.axis_set_id
        _item_description.description
    ;              This is a descriptor for the physical axis or set of axes 
                   corresponding to an array index.
                   
                   This data item is related to the axes of the detector 
                   itself given in DIFFRN_DETECTOR_AXIS, but usually differ
                   in that the axes in this category are the axes of the
                   coordinate system of reported data points, while the axes in
                   DIFFRN_DETECTOR_AXIS are the physical axes 
                   of the detector describing the "poise" of the detector as an
                   overall physical object.
                   
                   If there is only one axis in the set, the identifier of 
                   that axis should be used as the identifier of the set.
                   
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
               '_array_structure_list.axis_set_id'
                                      array_structure_list            yes
               '_array_structure_list_axis.axis_set_id'
                                      array_structure_list_axis       implicit
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_array_structure_list_axis.axis_set_id'
                                   '_array_structure_list.axis_set_id'
    
    
         save_
     
     
    save__array_structure_list.dimension
        _item_description.description
    ;              
                   The number of elements stored in the array structure in this 
                   dimension.
    ;
        _item.name                '_array_structure_list.dimension'
        _item.category_id          array_structure_list
        _item.mandatory_code       yes 
        _item_type.code            int
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                1  1
                                .  1
         save_
     
     
    save__array_structure_list.direction
        _item_description.description
    ;
                  Identifies the direction in which this array index changes.
    ;
        _item.name                '_array_structure_list.direction'
        _item.category_id          array_structure_list
        _item.mandatory_code       yes 
        _item_type.code            int
         loop_
        _item_enumeration.value
        _item_enumeration.detail        
    
                                  'increasing'
    ;
             Indicates the index changes from 1 to the maximum dimension.
    ;
                                  'decreasing'
    ;
             Indicates the index changes from the maximum dimension to 1.
    ;
         save_
     
     
    save__array_structure_list.index
        _item_description.description
    ;              
                   Identifies the one-based index of the row or column in the
                   array structure.
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
               '_array_structure_list.index'        array_structure_list   yes
               '_array_structure_list.precedence'   array_structure_list   yes
               '_array_element_size.index'          array_element_size     yes
    
        _item_type.code            int
    
         loop_
        _item_linked.child_name
        _item_linked.parent_name
              '_array_element_size.index'         '_array_structure_list.index'
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                1  1
                                .  1
         save_
     
     
    save__array_structure_list.precedence
        _item_description.description
    ;
                   Identifies the rank order in which this array index changes 
                   with respect to other array indices.  The precedence of 1  
                   indicates the index which changes fastest.
    ;
        _item.name                '_array_structure_list.precedence'
        _item.category_id          array_structure_list
        _item.mandatory_code       yes 
        _item_type.code            int
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                1  1
                                .  1
         save_
     
     
    #############################
    # ARRAY_STRUCTURE_LIST_AXIS #
    #############################
     
    save_ARRAY_STRUCTURE_LIST_AXIS
        _category.description
    ;
         Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe
         the physical settings of sets axes for the centres of pixels that 
         correspond to data points described in the 
         ARRAY_STRUCTURE_LIST category. 
         
         In the simplest cases, the physical increments of a single axis correspond
         to the increments of a single array index.  More complex organizations,
         e.g. spiral scans, may require coupled motions along multiple axes.
         
         Note that a spiral scan uses two coupled axis, one for the angular 
         direction, one for the radial direction.  This differs from a 
         cylindrical scan for which the two axes are not coupled into one set.
         
    ;
        _category.id                   array_structure_list_axis
        _category.mandatory_code       no
         loop_
        _category_key.name
                                      '_array_structure_list_axis.axis_set_id'
                                      '_array_structure_list_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'array_data_group'
         save_
     
     
    save__array_structure_list_axis.axis_id
        _item_description.description
    ;
                   The value of this data item is the identifier of one of
                   the axes for the set of axes for which settings are being 
                   specified.
    
                   Multiple axes may be specified for the same value of
                   '_array_structure_list_axis.axis_set_id'
    
                   This item is a pointer to '_axis.id' in the
                   AXIS category.
    ;
        _item.name                 '_array_structure_list_axis.axis_id'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       yes
         save_
     
     
    save__array_structure_list_axis.axis_set_id
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   set of axes for which axis settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   '_array_structure_list_axis.axis_set_id'.
    
                   This item is a pointer to
                   '_array_structure_list.axis_set_id'
                   in the ARRAY_STRUCTURE_LIST category.
                   
                   If this item is not specified, it defaults to the corresponding
                   axis identifier.
    ;
        _item.name                 '_array_structure_list_axis.axis_set_id'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       implicit
         save_
     
     
    save__array_structure_list_axis.angle
        _item_description.description
    ;
                   The setting of the specified axis in degrees for the first
                   data point of the array index with the corresponding value
                   of '_array_structure_list.axis_set_id'.  If the index is
                   specified as 'increasing' this will be the center of the
                   pixel with index value 1.  If the index is specified as
                   'decreasing' this will be the center of the pixel with
                   maximum index value. 
    ;
        _item.name                 '_array_structure_list_axis.angle'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
     
     
    save__array_structure_list_axis.angle_increment
        _item_description.description
    ;
                   The pixel-center-to-pixel-center increment in the angular 
                   setting of the specified axis in degrees.  This is not 
                   meaningful in the case of 'constant velocity' spiral scans  
                   and should not be specified in that case.  
    
                   See '_array_structure_list_axis.angular_pitch'.
                   
    ;
        _item.name                 '_array_structure_list_axis.angle_increment'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
     
     
    save__array_structure_list_axis.displacement
        _item_description.description
    ;
                   The setting of the specified axis in millimetres for the first
                   data point of the array index with the corresponding value
                   of '_array_structure_list.axis_set_id'.  If the index is
                   specified as 'increasing' this will be the center of the
                   pixel with index value 1.  If the index is specified as
                   'decreasing' this will be the center of the pixel with
                   maximum index value. 
    
    ;
        _item.name               '_array_structure_list_axis.displacement'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
     
     
    save__array_structure_list_axis.displacement_increment
        _item_description.description
    ;
                   The pixel-center-to-pixel-center increment for the displacement 
                   setting of the specified axis in millimetres.
                   
    ;
        _item.name                 
            '_array_structure_list_axis.displacement_increment'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
      
     
    save__array_structure_list_axis.angular_pitch
        _item_description.description
    ;
                   The pixel-center-to-pixel-center distance for a one step 
                   change in the setting of the specified axis in millimetres.
                   
                   This is meaningful only for 'constant velocity' spiral scans,
                   or for uncoupled angular scans at a constant radius
                   (cylindrical scan) and should not be specified for cases
                   in which the angle between pixels, rather than the distance
                   between pixels is uniform.
                   
                   See '_array_structure_list_axis.angle_increment'.
                   
    ;
        _item.name               '_array_structure_list_axis.angular_pitch'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
       
     
    save__array_structure_list_axis.radial_pitch
        _item_description.description
    ;
                   The radial distance from one "cylinder" of pixels to the
                   next in millimetres.  If the scan is a 'constant velocity'
                   scan with differing angular displacements between pixels,
                   the value of this item may differ significantly from the
                   value of '_array_structure_list_axis.displacement_increment'.
                   
    ;
        _item.name               '_array_structure_list_axis.radial_pitch'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
      
    
     
    ########
    # AXIS #
    ########
    
    save_AXIS
        _category.description
    ;
         Data items in the AXIS category record the information required
         to describe the various goniometer, detector, source and other
         axes needed to specify a data collection.  The location of each
         axis is specified by two vectors: the axis itself, given as a unit
         vector, and an offset to the base of the unit vector.  These vectors
         are referenced to a right-handed laboratory coordinate system with
         its origin in the sample or specimen:
         
                                 | Y (to complete right-handed system)
                                 |
                                 |
                                 |
                                 |
                                 |
                                 |________________X
                                /       principal goniometer axis
                               /
                              /
                             /
                            /
                           /Z (to source)
     
     
                                                          
         Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from
         the sample or specimen along the  principal axis of the goniometer.
         
         Axis 2 (Y): The Y-axis completes an orthogonal right-handed system
         defined by the X-axis and the Z-axis (see below).
         
         Axis 3 (Z): The Z-axis is derived from the source axis which goes from 
         the sample to the source.  The Z-axis is the component of the source axis
         in the direction of the source orthogonal to the X-axis in the plane 
         defined by the X-axis and the source axis.
              
         These axes are based on the goniometer, not on the orientation of the 
         detector, gravity, etc.  The vectors necessary to specify all other
         axes are given by sets of three components in the order (X, Y, Z).
         If the axis involved is a rotation axis, it is right handed, i.e. as
         one views the object to be rotated from the origin (the tail) of the 
         unit vector, the rotation is clockwise.  If a translation axis is
         specified, the direction of the unit vector specifies the sense of
         positive translation.
         
         Note:  This choice of coordinate system is similar to, but significantly
         different from the choice in MOSFLM (Andrew G.W. Leslie, Harry Powell,
         MRC Laboratory of Molecular Biology, Hills Road, Cambridge CB2 2QH,UK
         http://www.dl.ac.uk/CCP/CCP4/dist/x-windows/Mosflm/).  In MOSFLM,
         X is along the X-ray beam (our Z axis) and Z is along the rotation axis.
    
         All rotations are given in degrees and all translations are given in mm.
         
         Axes may be dependent on one another.  The X-axis is the only goniometer
         axis the direction of which is strictly connected to the hardware.  All
         other axes are specified by the positions they would assume when the
         axes upon which they depend are at their zero points.
         
         When specifying detector axes, the axis is given to the beam center.
         The location of the beam center on the detector should be given in the
         DIFFRN_DETECTOR category in distortion-corrected mm from the (0,0) corner
         of the detector.
         
         It should be noted that many different origins arise in the definition
         of an experiment.  In particular, as noted above, we need to specify the
         location of the beam center on the detector in terms of the origin of the
         detector, which is, of course, not coincident with the center of the
         sample.  
    ;
        _category.id                   axis
        _category.mandatory_code       no
         loop_
        _category_key.name          '_axis.id' 
                                    '_axis.equipment'               
         loop_
        _category_group.id           'inclusive_group'
                                     'axis_group'
                                     'diffrn_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 -
            
            This example shows the axis specification of the axes of a kappa
            geometry goniometer (See "X-Ray Structure Determination, A Practical
            Guide", 2nd ed. by  G. H. Stout, L. H. Jensen, Wiley Interscience,
            1989, 453 pp, p 134.).
            
            There are three axes specified, and no offsets.  The outermost axis,
            omega, is pointed along the X-axis.  The next innermost axis, kappa,
            is at a 50 degree angle to the X-axis, pointed away from the source.
            The innermost axis, phi, aligns with the X-axis when omega and
            phi are at their zero-points.  If T-omega, T-kappa and T-phi
            are the transformation matrices derived from the axis settings,
            the complete transformation would be:
                x' = (T-omega) (T-kappa) (T-phi) x
    ;
    ;
             loop_
            _axis.id
            _axis.type
            _axis.equipment
            _axis.depends_on
            _axis.vector[1] _axis.vector[2] _axis.vector[3]
            omega rotation goniometer     .    1        0        0
            kappa rotation goniometer omega    -.64279  0       -.76604
            phi   rotation goniometer kappa    1        0        0   
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 2 -
            
            This example show the axis specification of the axes of a
            detector, source and gravity.  We have juggled the order as a
            reminder that the ordering of presentation of tokens is not
            significant.  We have taken the center of rotation of the detector
            to be 68 millimetres in the direction away from the source.
    ;
    ;
            loop_
            _axis.id
            _axis.type
            _axis.equipment
            _axis.depends_on
            _axis.vector[1] _axis.vector[2] _axis.vector[3]
            _axis.offset[1] _axis.offset[2] _axis.offset[3]
            source       .        source     .       0     0     1   . . .
            gravity      .        gravity    .       0    -1     0   . . .
            tranz     translation detector rotz      0     0     1   0 0 -68
            twotheta  rotation    detector   .       1     0     0   . . .
            roty      rotation    detector twotheta  0     1     0   0 0 -68
            rotz      rotation    detector roty      0     0     1   0 0 -68
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
     
     
    save__axis.depends_on
        _item_description.description
    ;             The value of '_axis.depends_on' specifies the next outermost
                  axis upon which this axis depends.
                  
                  This item is a pointer to '_axis.id' in the same category.
    ;
        _item.name                      '_axis.depends_on'
        _item.category_id                 axis
        _item.mandatory_code              no
    
         save_
     
     
    save__axis.equipment
        _item_description.description
    ;             The value of  '_axis.equipment' specifies the type of
                  equipment using the axis:  'goniometer', 'detector',
                  'gravity', 'source' or 'general'.
    ;
        _item.name                      '_axis.equipment'
        _item.category_id                 axis
        _item.mandatory_code              no
        _item_type.code                   ucode
        _item_default.value               general
         loop_
        _item_enumeration.value
        _item_enumeration.detail   goniometer
                                  'equipment used to orient or position samples'
                                   detector
                                  'equipment used to detect reflections'
                                   general
                                  'equipment used for general purposes'
                                   gravity
                                  'axis specifying the downward direction'
                                   source
                                  'axis specifying the direction sample to source'
    
         save_
     
     
    save__axis.offset[1]
        _item_description.description
    ;              The [1] element of the 3-element vector used to specify
                   the offset to the base of a rotation or translation axis.
                   
                   The vector is specified in millimetres
    ;
        _item.name                  '_axis.offset[1]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
         save_
     
     
    save__axis.offset[2]
        _item_description.description
    ;              The [2] element of the 3-element vector used to specify
                   the offset to the base of a rotation or translation axis.
                   
                   The vector is specified in millimetres
    ;
        _item.name                  '_axis.offset[2]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
         save_
     
     
    save__axis.offset[3]
        _item_description.description
    ;              The [3] element of the 3-element vector used to specify
                   the offset to the base of a rotation or translation axis.
                   
                   The vector is specified in millimetres
    ;
        _item.name                  '_axis.offset[3]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
         save_
     
     
    save__axis.id
        _item_description.description
    ;             The value of '_axis.id' must uniquely identify
                  each axis relevant to the experiment.  Note that multiple
                  pieces of equipment may share the same axis (e.g. a twotheta
                  arm), so that the category key for AXIS also includes the
                  equipment.
    ;
        loop_
        _item.name
        _item.category_id
        _item.mandatory_code
             '_axis.id'                         axis                    yes
             '_array_structure_list_axis.axis_id'
                                                array_structure_list_axis
                                                                        yes
             '_diffrn_detector_axis.axis_id'    diffrn_detector_axis    yes
             '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes
             '_diffrn_scan_axis.axis_id'        diffrn_scan_axis        yes
             '_diffrn_scan_frame_axis.axis_id'  diffrn_scan_frame_axis  yes
    
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
             '_axis.depends_on'                   '_axis.id'
             '_array_structure_list_axis.axis_id' '_axis.id'
             '_diffrn_detector_axis.axis_id'      '_axis.id'
             '_diffrn_measurement_axis.axis_id'   '_axis.id'
             '_diffrn_scan_axis.axis_id'          '_axis.id'      
             '_diffrn_scan_frame_axis.axis_id'    '_axis.id'
    
         save_
     
     
    save__axis.type
        _item_description.description
    ;             The value of '_axis.type' specifies the type of
                  axis:  'rotation', 'translation' (or 'general' when
                  the type is not relevant, as for gravity).
    ;
        _item.name                      '_axis.type'
        _item.category_id                 axis
        _item.mandatory_code              no
        _item_type.code                   ucode
        _item_default.value               general
         loop_
        _item_enumeration.value
        _item_enumeration.detail      rotation
                                     'right-handed axis of rotation'
                                      translation
                                     'translation in the direction of the axis'
                                      general
                                     'axis for which the type is not relevant'
    
         save_
    
    
    save__axis.vector[1]
        _item_description.description
    ;              The [1] element of the 3-element vector used to specify
                   the direction of a rotation or translation axis.
                   The vector should be normalized to be a unit vector, and
                   is dimensionless.
    ;
        _item.name                  '_axis.vector[1]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
         save_
    
    save__axis.vector[2]
        _item_description.description
    ;              The [2] element of the 3-element vector used to specify
                   the direction of a rotation or translation axis.
                   The vector should be normalized to be a unit vector, and
                   is dimensionless.
    ;
        _item.name                  '_axis.vector[2]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
         save_
    
    save__axis.vector[3]
        _item_description.description
    ;              The [3] element of the 3-element vector used to specify
                   the direction of a rotation or translation axis.
                   The vector should be normalized to be a unit vector, and
                   is dimensionless.
    ;
        _item.name                  '_axis.vector[3]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
         save_
     
    
     
    #####################
    # DIFFRN_DATA_FRAME #
    #####################
     
     
    save_DIFFRN_DATA_FRAME
        _category.description
    ;
                  Data items in the DIFFRN_DATA_FRAME category record
                  the details about each frame of data. 
                  
                  The items in this category were previously in a
                  DIFFRN_FRAME_DATA category, which is now deprecated.
                  The items from the old category are provided
                  as aliases, but should not be used for new work.
    ;
        _category.id                   diffrn_data_frame
        _category.mandatory_code       no
         loop_
        _category_key.name             '_diffrn_data_frame.id'
                                       '_diffrn_data_frame.detector_element_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 - A frame containing data from 4 frame elements.
                    Each frame element has a common array configuration
                    'array_1' described in ARRAY_STRUCTURE and related
                    categories.  The data for each detector element is 
                    stored in four groups of binary data in the
                    ARRAY_DATA category, linked by the array_id and
                    binary_id
    ;
    ;
            loop_
            _diffrn_data_frame.id
            _diffrn_data_frame.detector_element_id
            _diffrn_data_frame.array_id
            _diffrn_data_frame.binary_id
            frame_1   d1_ccd_1  array_1  1  
            frame_1   d1_ccd_2  array_1  2 
            frame_1   d1_ccd_3  array_1  3 
            frame_1   d1_ccd_4  array_1  4 
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
     
     
    save__diffrn_data_frame.array_id
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category. 
    ;
        _item.name                  '_diffrn_data_frame.array_id'
        _item.category_id             diffrn_data_frame
        _item.mandatory_code          yes
        _item_aliases.alias_name    '_diffrn_frame_data.array_id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0.00
        _item_type.code               code
         save_
     
     
    save__diffrn_data_frame.binary_id
        _item_description.description
    ;             This item is a pointer to '_array_data.binary_id' in the
                  ARRAY_DATA category. 
    ;
        _item.name                  '_diffrn_data_frame.binary_id'
        _item.category_id             diffrn_data_frame
        _item.mandatory_code          implicit
        _item_aliases.alias_name    '_diffrn_frame_data.binary_id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               int
         save_
     
     
    save__diffrn_data_frame.detector_element_id
        _item_description.description
    ;             
                   This item is a pointer to '_diffrn_detector_element.id'
                   in the DIFFRN_DETECTOR_ELEMENT category. 
    ;
        _item.name                  '_diffrn_data_frame.detector_element_id'
        _item.category_id             diffrn_data_frame
        _item.mandatory_code          yes
        _item_aliases.alias_name    '_diffrn_frame_data.detector_element_id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         save_
     
     
    save__diffrn_data_frame.id
        _item_description.description
    ;             
                  The value of '_diffrn_data_frame.id' must uniquely identify
                  each complete frame of data.
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
               '_diffrn_data_frame.id'        diffrn_data_frame  yes
               '_diffrn_refln.frame_id'       diffrn_refln       yes
               '_diffrn_scan.frame_id_start'  diffrn_scan        yes
               '_diffrn_scan.frame_id_end'    diffrn_scan        yes
               '_diffrn_scan_frame.frame_id'  diffrn_scan_frame  yes
               '_diffrn_scan_frame_axis.frame_id'  
                                              diffrn_scan_frame_axis
                                                                 yes
        _item_aliases.alias_name    '_diffrn_frame_data.id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_diffrn_refln.frame_id'        '_diffrn_data_frame.id'
               '_diffrn_scan.frame_id_start'   '_diffrn_data_frame.id'
               '_diffrn_scan.frame_id_end'     '_diffrn_data_frame.id'
               '_diffrn_scan_frame.frame_id'   '_diffrn_data_frame.id'
               '_diffrn_scan_frame_axis.frame_id'
                                               '_diffrn_data_frame.id'
         save_
     
    
    ##########################################################################
    #  The following is a restatement of the mmCIF DIFFRN_DETECTOR,          #
    #  DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for      #
    #  the CBF/imgCIF extensions                                             #
    ##########################################################################
    
    ###################
    # DIFFRN_DETECTOR #
    ###################
     
     
    save_DIFFRN_DETECTOR
        _category.description
    ;              Data items in the DIFFRN_DETECTOR category describe the 
                   detector used to measure the scattered radiation, including
                   any analyser and post-sample collimation.
    ;
        _category.id                  diffrn_detector
        _category.mandatory_code      no
         loop_
        _category_key.name          '_diffrn_detector.diffrn_id'
                                    '_diffrn_detector.id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 - based on PDB entry 5HVP and laboratory records for the
                    structure corresponding to PDB entry 5HVP
    ;
    ;
        _diffrn_detector.diffrn_id             'd1'
        _diffrn_detector.detector              'multiwire'
        _diffrn_detector.type                  'Siemens'
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
     
     
    save__diffrn_detector.details
        _item_description.description
    ;              A description of special aspects of the radiation detector.
    ;
        _item.name                  '_diffrn_detector.details'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_detector_details'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
        _item_examples.case
    ;                                 Need new example here.
    ;
         save_
     
     
    save__diffrn_detector.detector
        _item_description.description
    ;              The general class of the radiation detector.
    ;
        _item.name                  '_diffrn_detector.detector'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
         loop_
        _item_aliases.alias_name
        _item_aliases.dictionary
        _item_aliases.version       '_diffrn_radiation_detector'
                                      cifdic.c91
                                      1.0
                                    '_diffrn_detector'
                                      cif_core.dic
                                      2.0
        _item_type.code               text
         loop_
        _item_examples.case          'photographic film'
                                     'scintillation counter'
                                     'CCD plate'
                                     'BF~3~ counter'
         save_
     
     
    save__diffrn_detector.diffrn_id
        _item_description.description
    ;              This data item is a pointer to '_diffrn.id' in the DIFFRN
                   category.
    
                   The value of '_diffrn.id' uniquely defines a set of
                   diffraction data.
    ;
        _item.name                  '_diffrn_detector.diffrn_id'
        _item.mandatory_code          yes
         save_
     
     
    save__diffrn_detector.dtime
        _item_description.description
    ;              The deadtime in microseconds of the detectors used to
                   measure the diffraction intensities.
    ;
        _item.name                  '_diffrn_detector.dtime'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
         loop_
        _item_aliases.alias_name
        _item_aliases.dictionary
        _item_aliases.version       '_diffrn_radiation_detector_dtime'
                                      cifdic.c91
                                      1.0
                                    '_diffrn_detector_dtime'
                                      cif_core.dic
                                      2.0
         loop_  
        _item_range.maximum           
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
        _item_units.code              microseconds
         save_
     
     
    save__diffrn_detector.id
        _item_description.description
    ;             
                   The value of '_diffrn_detector.id' must uniquely identify
                   each detector used to collect each diffraction data set.
    
                   If the value of '_diffrn_detector.id' is not given, it is
                   implicitly equal to the value of
                   '_diffrn_detector.diffrn_id'
    ;
         loop_
        _item.name                 
        _item.category_id
        _item.mandatory_code
                 '_diffrn_detector.id'         diffrn_detector       implicit
                 '_diffrn_detector_axis.detector_id'
                                               diffrn_detector_axis       yes
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_detector_axis.detector_id'
                                             '_diffrn_detector.id'
    
        _item_type.code               code
         save_
     
     
    save__diffrn_detector.number_of_axes
        _item_description.description
    ;             
                   The value of '_diffrn_detector.number_of_axes' gives the 
                   number of axes of the positioner for the detector identified 
                   by '_diffrn_detector.id'.
                   
                   The word "positioner" is a general term used in
                   instrumentation design for devices that are used to change
                   the positions of portions of apparatus by linear
                   translation, rotation, or combinations of such motions.
                   
                   Axes which are used to provide a coordinate system for the
                   face of an area detetctor should not be counted for this
                   data item.
    
                   The description of each axis should be provided by entries 
                   in DIFFRN_DETECTOR_AXIS.
    ;
        _item.name                  '_diffrn_detector.number_of_axes'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
         loop_
        _item_range.maximum
        _item_range.minimum           .   1
                                      1   1
        _item_type.code               int
         save_
     
     
    save__diffrn_detector.type
        _item_description.description
    ;              The make, model or name of the detector device used.
    ;
        _item.name                  '_diffrn_detector.type'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_detector_type'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         save_
     
     
    ########################
    # DIFFRN_DETECTOR_AXIS #
    ########################
     
     
    save_DIFFRN_DETECTOR_AXIS
        _category.description
    ;
         Data items in the DIFFRN_DETECTOR_AXIS category associate
         axes with detectors.
    ;
        _category.id                   diffrn_detector_axis
        _category.mandatory_code       no
         loop_
        _category_key.name          '_diffrn_detector_axis.detector_id'
                                    '_diffrn_detector_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
     
     
    save__diffrn_detector_axis.axis_id
        _item_description.description
    ;
                   This data item is a pointer to '_axis.id' in
                   the AXIS category.
    ;
        _item.name                  '_diffrn_detector_axis.axis_id'
        _item.category_id             diffrn_detector_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
     
     
    save__diffrn_detector_axis.detector_id
        _item_description.description
    ;
                   This data item is a pointer to '_diffrn_detector.id' in
                   the DIFFRN_DETECTOR category.
    
                   This item was previously named '_diffrn_detector_axis.id'
                   which is now a deprecated name.  The old name is
                   provided as an alias, but should not be used for new work.
    
    ;
        _item.name                  '_diffrn_detector_axis.detector_id'
        _item.category_id             diffrn_detector_axis
        _item.mandatory_code          yes
        _item_aliases.alias_name    '_diffrn_detector_axis.id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
         save_
     
     
    ###########################
    # DIFFRN_DETECTOR_ELEMENT #
    ###########################
     
     
    save_DIFFRN_DETECTOR_ELEMENT
        _category.description
    ;
                  Data items in the DIFFRN_DETECTOR_ELEMENT category record
                  the details about spatial layout and other characteristics
                  of each element of a detector which may have multiple elements.
                  
                  In most cases, the more detailed information provided
                  in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS
                  are preferable to simply providing the centre.
    
    ;
        _category.id                   diffrn_detector_element
        _category.mandatory_code       no
         loop_
        _category_key.name             '_diffrn_detector_element.id'
                                       '_diffrn_detector_element.detector_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 - Detector d1 is composed of four CCD detector elements,
            each 200 mm by 200 mm, arranged in a square. in the pattern
                        
                       1     2
                          *
                       3     4
    
            Note that the beam center is slightly off of each of the
            detector elements, just beyond the lower right corner of 1,
            the lower left corner of 2, the upper right corner of 3 and
            the upper left corner of 4.
    ;
    ;
            loop_
            _diffrn_detector_element.id
            _diffrn_detector_element.detector_id
            _diffrn_detector_element.center[1]
            _diffrn_detector_element.center[2]
            d1     d1_ccd_1  201.5 -1.5
            d1     d1_ccd_2  -1.8  -1.5
            d1     d1_ccd_3  201.6 201.4  
            d1     d1_ccd_4  -1.7  201.5
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
     
     
    save__diffrn_detector_element.center[1]
        _item_description.description
    ;             
                  The value of '_diffrn_detector_element.center[1]' is the X
                  component of the distortion-corrected beam-center in mm from
                  the (0, 0) (lower left) corner of the detector element viewed
                  from the sample side.
    ;
        _item.name                  '_diffrn_detector_element.center[1]'
        _item.category_id             diffrn_detector_element
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
    
        save_
     
     
    save__diffrn_detector_element.center[2]
        _item_description.description
    ;             
                  The value of '_diffrn_detector_element.center[2]' is the Y
                  component of the distortion-corrected beam-center in mm from
                  the (0, 0) (lower left) corner of the detector element viewed
                  from the sample side.
    ;
        _item.name                  '_diffrn_detector_element.center[2]'
        _item.category_id             diffrn_detector_element
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
    
        save_
     
     
    save__diffrn_detector_element.id
        _item_description.description
    ;             
                  The value of '_diffrn_detector_element.id' must uniquely
                  identify each element of a detector.
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
               '_diffrn_detector_element.id'
               diffrn_detector_element
               yes
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_diffrn_data_frame.detector_element_id'
               '_diffrn_detector_element.id'
    
         save_
     
     
    save__diffrn_detector_element.detector_id
        _item_description.description
    ;             
                   This item is a pointer to '_diffrn_detector.id'
                   in the DIFFRN_DETECTOR category. 
    ;
        _item.name                  '_diffrn_detector_element.detector_id'
        _item.category_id             diffrn_detector_element
        _item.mandatory_code          yes
        _item_type.code               code
         save_
     
     
     
    ########################
    ## DIFFRN_MEASUREMENT ##
    ########################
     
     
    save_DIFFRN_MEASUREMENT
        _category.description
    ;              Data items in the DIFFRN_MEASUREMENT category record details
                   about the device used to orient and/or position the crystal
                   during data measurement and the manner in which the
                   diffraction data were measured.
    ;
        _category.id                  diffrn_measurement
        _category.mandatory_code      no
         loop_
        _category_key.name          '_diffrn_measurement.device'
                                    '_diffrn_measurement.diffrn_id'
                                    '_diffrn_measurement.id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 - based on PDB entry 5HVP and laboratory records for the
                    structure corresponding to PDB entry 5HVP
    ;
    ;
        _diffrn_measurement.diffrn_id          'd1'
        _diffrn_measurement.device             '3-circle camera'
        _diffrn_measurement.device_type        'Supper model x'
        _diffrn_measurement.device_details     'none'
        _diffrn_measurement.method             'omega scan'
        _diffrn_measurement.details
        ; Need new example here
        ;
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991).
                    Acta Cryst. C47, 2276-2277].
    ;
    ;
        _diffrn_measurement.diffrn_id       's1'
        _diffrn_measurement.device_type     'Philips PW1100/20 diffractometer'
        _diffrn_measurement.method          'theta/2theta (\q/2\q)'
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
     
     
    save__diffrn_measurement.device
        _item_description.description
    ;              The general class of goniometer or device used to support
                   and orient the specimen.
                   
                   If the value of '_diffrn_measurement.device' is not given,
                   it is implicitly equal to the value of
                   '_diffrn_measurement.diffrn_id'.
    
                   Either '_diffrn_measurement.device' or
                   '_diffrn_measurement.id' may be used to link to other
                   categories.  If the experimental setup admits multiple
                   devices, then '_diffrn_measurement.id' is used to provide
                   a unique link.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
                 '_diffrn_measurement.device'  diffrn_measurement      implicit
                 '_diffrn_measurement_axis.measurement_device' 
                                               diffrn_measurement_axis implicit
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_measurement_axis.measurement_device'  
                                             '_diffrn_measurement.device'
        _item_aliases.alias_name    '_diffrn_measurement_device'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          '3-circle camera'
                                     '4-circle camera'
                                     'kappa-geometry camera'
                                     'oscillation camera'
                                     'precession camera'
         save_
     
     
    save__diffrn_measurement.device_details
        _item_description.description
    ;              A description of special aspects of the device used to
                   measure the diffraction intensities.
    ;
        _item.name                  '_diffrn_measurement.device_details'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_device_details'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
        _item_examples.case
    ;                                 commercial goniometer modified locally to
                                      allow for 90\% \t arc
    ;
         save_
     
     
    save__diffrn_measurement.device_type
        _item_description.description
    ;              The make, model or name of the measurement device
                   (goniometer) used.
    ;
        _item.name                  '_diffrn_measurement.device_type'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_device_type'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          'Supper model q'
                                     'Huber model r'
                                     'Enraf-Nonius model s'
                                     'homemade'
         save_
     
     
    save__diffrn_measurement.diffrn_id
        _item_description.description
    ;              This data item is a pointer to '_diffrn.id' in the DIFFRN 
                   category.
    ;
        _item.name                  '_diffrn_measurement.diffrn_id'
        _item.mandatory_code          yes
         save_
     
     
    save__diffrn_measurement.details
        _item_description.description
    ;              A description of special aspects of the intensity
                   measurement.
    ;
        _item.name                  '_diffrn_measurement.details'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_details'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
        _item_examples.case
    ;                                 440 frames, 0.20 degrees, 150 sec, detector
                                      distance 12 cm, detector angle 22.5 degrees
    ;
         save_
     
     
    save__diffrn_measurement.id
        _item_description.description
    ;             
                   The value of '_diffrn_measurement.id' must uniquely identify
                   the set of mechanical characteristics of the device used to 
                   orient and/or position the sample used during collection 
                   of each diffraction data set.
    
                   If the value of '_diffrn_measurement.id' is not given, it is
                   implicitly equal to the value of 
                   '_diffrn_measurement.diffrn_id'.
    
                   Either '_diffrn_measurement.device' or
                   '_diffrn_measurement.id' may be used to link to other
                   categories.  If the experimental setup admits multiple
                   devices, then '_diffrn_measurement.id' is used to provide
                   a unique link.
    ;
         loop_
        _item.name                 
        _item.category_id
        _item.mandatory_code
                 '_diffrn_measurement.id'      diffrn_measurement      implicit
                 '_diffrn_measurement_axis.measurement_id'
                                               diffrn_measurement_axis implicit
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_measurement_axis.measurement_id'
                                             '_diffrn_measurement.id'
    
        _item_type.code               code
         save_
     
     
    save__diffrn_measurement.method
        _item_description.description
    ;              Method used to measure intensities.
    ;
        _item.name                  '_diffrn_measurement.method'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_method'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
        _item_examples.case
          'profile data from theta/2theta (\q/2\q) scans'
         save_
     
     
    save__diffrn_measurement.number_of_axes
        _item_description.description
    ;             
                   The value of '_diffrn_measurement.number_of_axes' gives the 
                   number of axes of the positioner for the goniometer or
                   other sample orientation or positioning device identified 
                   by '_diffrn_measurement.id'.
    
                   The description of the axes should be provided by entries in 
                   DIFFRN_MEASUREMENT_AXIS.
    ;
        _item.name                  '_diffrn_measurement.number_of_axes'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
         loop_
        _item_range.maximum
        _item_range.minimum           .   1
                                      1   1
        _item_type.code               int
         save_
     
     
    save__diffrn_measurement.specimen_support
        _item_description.description
    ;              The physical device used to support the crystal during data
                   collection.
    ;
        _item.name                  '_diffrn_measurement.specimen_support'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_specimen_support'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          'glass capillary'
                                     'quartz capillary'
                                     'fiber'
                                     'metal loop'
         save_
     
     
    ###########################
    # DIFFRN_MEASUREMENT_AXIS #
    ###########################
     
     
    save_DIFFRN_MEASUREMENT_AXIS
        _category.description
    ;
         Data items in the DIFFRN_MEASUREMENT_AXIS category associate
         axes with goniometers.
    ;
        _category.id                   diffrn_measurement_axis
        _category.mandatory_code       no
         loop_
        _category_key.name
                                  '_diffrn_measurement_axis.measurement_device'
                                    '_diffrn_measurement_axis.measurement_id'
                                    '_diffrn_measurement_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
     
     
    save__diffrn_measurement_axis.axis_id
        _item_description.description
    ;
                   This data item is a pointer to '_axis.id' in
                   the AXIS category.
    ;
        _item.name                  '_diffrn_measurement_axis.axis_id'
        _item.category_id             diffrn_measurement_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
     
     
    save__diffrn_measurement_axis.measurement_device
        _item_description.description
    ;
                   This data item is a pointer to '_diffrn_measurement.device'
                   in the DIFFRN_MEASUREMENT category.
    
    ;
        _item.name
          '_diffrn_measurement_axis.measurement_device'
        _item.category_id             diffrn_measurement_axis
        _item.mandatory_code          implicit
         save_
     
     
    save__diffrn_measurement_axis.measurement_id
        _item_description.description
    ;
                   This data item is a pointer to '_diffrn_measurement.id' in
                   the DIFFRN_MEASUREMENT category.
                  
                   This item was previously named '_diffrn_measurement_axis.id'
                   which is now a deprecated name.  The old name is
                   provided as an alias, but should not be used for new work.
    
    ;
        _item.name                  '_diffrn_measurement_axis.measurement_id'
        _item.category_id             diffrn_measurement_axis
        _item_aliases.alias_name    '_diffrn_measurement_axis.id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0.00
        _item.mandatory_code          implicit
         save_
    
     
    ####################
    # DIFFRN_RADIATION #
    ####################
     
     
    save_DIFFRN_RADIATION
        _category.description
    ;              Data items in the DIFFRN_RADIATION category describe
                   the radiation used in measuring diffraction intensities,
                   its collimation and monochromatisation before the sample.
    
                   Post-sample treatment of the beam is described by data
                   items in the DIFFRN_DETECTOR category.
    
    ;
        _category.id                  diffrn_radiation
        _category.mandatory_code      no
        _category_key.name          '_diffrn_radiation.diffrn_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 - based on PDB entry 5HVP and laboratory records for the
                    structure corresponding to PDB entry 5HVP
    ;
    ;
        _diffrn_radiation.diffrn_id            'set1'
    
        _diffrn_radiation.collimation          '0.3 mm double pinhole'
        _diffrn_radiation.monochromator        'graphite'
        _diffrn_radiation.type                 'Cu K\a'
        _diffrn_radiation.wavelength_id         1
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991).
                    Acta Cryst. C47, 2276-2277].
    ;
    ;
        _diffrn_radiation.wavelength_id    1
        _diffrn_radiation.type             'Cu K\a'
        _diffrn_radiation.monochromator    'graphite'
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    save__diffrn_radiation.collimation
        _item_description.description
    ;              The collimation or focusing applied to the radiation.
    ;
        _item.name                  '_diffrn_radiation.collimation'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_collimation'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          '0.3 mm double-pinhole'
                                     '0.5 mm'
                                     'focusing mirrors'
         save_
    
    
    save__diffrn_radiation.diffrn_id
        _item_description.description
    ;              This data item is a pointer to '_diffrn.id' in the DIFFRN
                   category.
    ;
        _item.name                  '_diffrn_radiation.diffrn_id'
        _item.mandatory_code          yes
         save_
    
     
     
    save__diffrn_radiation.div_x_source
        _item_description.description
    ;              Beam crossfire in degrees parallel to the laboratory X axis
                   (see AXIS category).
                   
                   This is a characteristic of the xray beam as it illuminates
                   the sample (or specimen) after all monochromation and 
                   collimation.
                   
                   This is the esd of the directions of photons in the X-Z plane
                   around the mean source beam direction.
                   
                   Note that some synchrotrons specify this value in milliradians,
                   in which case a conversion would be needed.  To go from a
                   value in milliradians to a value in degrees, multiply by 0.180
                   and divide by Pi.
    
    ;
        _item.name                  '_diffrn_radiation.div_x_source'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_type.code               float
        _item_units.code              degrees
         save_
     
     
    save__diffrn_radiation.div_y_source
        _item_description.description
    ;              Beam crossfire in degrees parallel to the laboratory Y axis
                   (see AXIS category).
                   
                   This is a characteristic of the xray beam as it illuminates
                   the sample (or specimen) after all monochromation and 
                   collimation.
                   
                   This is the esd of the directions of photons in the Y-Z plane
                   around the mean source beam direction.
    
                   Note that some synchrotrons specify this value in milliradians,
                   in which case a conversion would be needed.  To go from a
                   value in milliradians to a value in degrees, multiply by 0.180
                   and divide by Pi.
    
    ;
        _item.name                  '_diffrn_radiation.div_y_source'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_type.code               float
        _item_units.code              degrees
        _item_default.value           0.0
         save_
     
     
    save__diffrn_radiation.div_x_y_source
        _item_description.description
    ;              Beam crossfire correlation degrees**2 between the
                   crossfire laboratory X-axis component and the crossfire
                   laboratory Y-axis component (see AXIS category).
                   
                   This is a characteristic of the xray beam as it illuminates
                   the sample (or specimen) after all monochromation and 
                   collimation.
                   
                   This is the mean of the products of the deviations of the
                   directin of each photons in X-Z plane times the deviations
                   of the direction of the same photon in the Y-Z plane
                   around the mean source beam direction.  This will be zero
                   for uncorrelated crossfire.
                   
                   Note that some synchrotrons specify this value in 
                   milliradians**2, in which case a conversion would be needed.  
                   To go from a value in milliradians**2 to a value in
                   degrees**2, multiply by 0.180**2 and divide by Pi**2.
    
    ;
        _item.name                  '_diffrn_radiation.div_x_y_source'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_type.code               float
        _item_units.code              degrees_squared
        _item_default.value           0.0
         save_
    
    save__diffrn_radiation.filter_edge
        _item_description.description
    ;              Absorption edge in angstroms of the radiation filter used.
    ;
        _item.name                  '_diffrn_radiation.filter_edge'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_filter_edge'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum           
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
        _item_units.code              angstroms
         save_
    
    save__diffrn_radiation.inhomogeneity
        _item_description.description
    ;              Half-width in millimetres of the incident beam in the
                   direction perpendicular to the diffraction plane.
    ;
        _item.name                  '_diffrn_radiation.inhomogeneity'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_inhomogeneity'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum           
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    save__diffrn_radiation.monochromator
        _item_description.description
    ;              The method used to obtain monochromatic radiation. If a
                   monochromator crystal is used the material and the
                   indices of the Bragg reflection are specified.
    ;
        _item.name                  '_diffrn_radiation.monochromator'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_monochromator'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          'Zr filter'
                                     'Ge 220'
                                     'none'
                                     'equatorial mounted graphite'
         save_
    
    save__diffrn_radiation.polarisn_norm
        _item_description.description
    ;              The angle in degrees, as viewed from the specimen, between the
                   perpendicular component of the polarisation and the diffraction
                   plane. See _diffrn_radiation_polarisn_ratio.
    ;
        _item.name                  '_diffrn_radiation.polarisn_norm'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_polarisn_norm'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum           
        _item_range.minimum           90.0  90.0
                                      90.0 -90.0
                                     -90.0 -90.0
        _item_type.code               float
        _item_units.code              degrees
         save_
    
    save__diffrn_radiation.polarisn_ratio
        _item_description.description
    ;              Polarisation ratio of the diffraction beam incident on the
                   crystal. It is the ratio of the perpendicularly polarised to
                   the parallel polarised component of the radiation. The
                   perpendicular component forms an angle of
                   '_diffrn_radiation.polarisn_norm' to the normal to the
                   diffraction plane of the sample (i.e. the plane containing
                   the incident and reflected beams).
    ;
        _item.name                  '_diffrn_radiation.polarisn_ratio'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_polarisn_ratio'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum           
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
         save_
    
     
     
    save__diffrn_radiation.polarizn_source_norm
        _item_description.description
    ;              The angle in degrees, as viewed from the specimen, between
                   the normal to the polarization plane and the laboratory Y
                   axis as defined in the AXIS category.
                   
                   Note that this is the angle of polarization of the source 
                   photons, either directly from a synchrotron beamline or
                   from a monchromater.
                   
                   This differs from the value of
                   '_diffrn_radiation.polarisn_norm'
                   in that '_diffrn_radiation.polarisn_norm' refers to
                   polarization relative to the diffraction plane rather than
                   to the laboratory axis system.
                   
                   In the case of an unpolarized beam, or a beam with true
                   circular polarization, in which no single plane of
                   polarization can be determined, the plane should be taken
                   as the X-Z plane, and the angle as 0.
                   
                   See '_diffrn_radiation.polarizn_source_ratio'.
    ;
        _item.name                  '_diffrn_radiation.polarizn_source_norm'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
         loop_
        _item_range.maximum           
        _item_range.minimum           90.0   90.0
                                      90.0  -90.0
                                     -90.0  -90.0
        _item_type.code               float
        _item_units.code              degrees
        _item_default.value           0.0
         save_
     
     
    save__diffrn_radiation.polarizn_source_ratio
        _item_description.description
    ;              (Ip-In)/(Ip+In), where Ip is the intensity (amplitude
                   squared) of the electric vector in the plane of
                   polarization and In is the intensity (amplitude squared)
                   of the electric vector in plane of the normal to the
                   plane of polarization.
                   
                   Thus, if we had complete polarization in the plane of
                   polarization, the value of 
                   '_diffrn_radiation.polarizn_source_ratio' would
                   be 1, and an unpolarized beam would have a value of 0.
                   
                   If the X-axis has been chosen to lie in the plane of
                   polarization, this definition will agree with the definition
                   of "MONOCHROMATOR" in the Denzo glossary, and values of near
                   1 should be expected for a bending magnet source.  However,
                   if the X-axis were, for some reason to be, say,
                   perpendicular to the polarization plane (not a common
                   choice), then the Denzo value would be the negative of
                   '_diffrn_radiation.polarizn_source_ratio'.
                   
                   See http://www.hkl-xray.com for information on Denzo, and
                   Z. Otwinowski and W. Minor, "Processing of X-ray
                   Diffraction Data Collected in Oscillation Mode", Methods
                   in Enzymology, Volume 276: Macromolecular Crystallography,
                   part A, p.307-326, 1997,C.W. Carter, Jr. & R. M. Sweet,
                   Eds., Academic Press.
    
                   This differs both in the choice of ratio and choice of
                   orientation from '_diffrn_radiation.polarisn_ratio', which,
                   unlike '_diffrn_radiation.polarizn_source_ratio', is
                   unbounded.
    
    ;
        _item.name                  '_diffrn_radiation.polarizn_source_ratio'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
         loop_
        _item_range.maximum           
        _item_range.minimum           1.0    1.0
                                      1.0   -1.0
                                     -1.0   -1.0
        _item_type.code               float
         save_
    
    
    save__diffrn_radiation.probe
        _item_description.description
    ;              Name of the type of radiation used. It is strongly
                   encouraged that this field be specified so that the
                   probe radiation can be simply determined.
    ;
        _item.name                  '_diffrn_radiation.probe'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_probe'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               line
         loop_
        _item_enumeration.value      'x-ray'
                                     'neutron'
                                     'electron'
                                     'gamma'
         save_
    
    save__diffrn_radiation.type
        _item_description.description
    ;              The nature of the radiation. This is typically a description
                   of the X-ray wavelength in Siegbahn notation.
    ;
        _item.name                  '_diffrn_radiation.type'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_type'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               line
         loop_
        _item_examples.case          'CuK\a'
                                     'Cu K\a~1~'
                                     'Cu K-L~2,3~' 
                                     'white-beam'
    
         save_
    
    save__diffrn_radiation.xray_symbol
        _item_description.description
    ;              The IUPAC symbol for the X-ray wavelength for probe
                   radiation.
    ;
        _item.name                  '_diffrn_radiation.xray_symbol'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_xray_symbol'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               line
         loop_
        _item_enumeration.value
        _item_enumeration.detail     'K-L~3~'
                                     'K\a~1~ in older Siegbahn notation'
                                     'K-L~2~'
                                     'K\a~2~ in older Siegbahn notation'
                                     'K-M~3~'
                                     'K\b~1~ in older Siegbahn notation'
                                     'K-L~2,3~'
                                     'use where K-L~3~ and K-L~2~ are not resolved'
         save_
    
    save__diffrn_radiation.wavelength_id
        _item_description.description
    ;              This data item is a pointer to 
                   '_diffrn_radiation_wavelength.id' in the
                   DIFFRN_RADIATION_WAVELENGTH category.
    ;
        _item.name                  '_diffrn_radiation.wavelength_id'
        _item.mandatory_code          yes
         save_
    
    
     
    ################
    # DIFFRN_REFLN #
    ################
     
     
    save_DIFFRN_REFLN
        _category.description 
    ;
         This category redefinition has been added to extend the key of 
         the standard DIFFRN_REFLN category.
    ;
        _category.id                   diffrn_refln
        _category.mandatory_code       no
        _category_key.name             '_diffrn_refln.frame_id'
         loop_
        _category_group.id             'inclusive_group'
                                       'diffrn_group'
         save_
     
     
    save__diffrn_refln.frame_id
        _item_description.description
    ;             
                   This item is a pointer to '_diffrn_data_frame.id'
                   in the DIFFRN_DATA_FRAME category. 
    ;
        _item.name                  '_diffrn_refln.frame_id'
        _item.category_id             diffrn_refln
        _item.mandatory_code          yes
        _item_type.code               code
         save_
     
     
    ###############
    # DIFFRN_SCAN #
    ###############
    
    save_DIFFRN_SCAN
        _category.description 
    ;
         Data items in the DIFFRN_SCAN category describe the parameters of one
         or more scans, relating axis positions to frames.
    
    ;
        _category.id                   diffrn_scan
        _category.mandatory_code       no
        _category_key.name            '_diffrn_scan.id'
         loop_
        _category_group.id            'inclusive_group'
                                      'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 - derived from a suggestion by R. M. Sweet.
    
       The vector of each axis is not given here, because it is provided in
       the AXIS category.  By making '_diffrn_scan_axis.scan_id' and
       '_diffrn_scan_axis.axis_id' keys of the DIFFRN_SCAN_AXIS category,
       an arbitrary number of scanning and fixed axes can be specified for a 
       scan.  We have specified three rotation axes and one translation axis 
       at non-zero values, with one axis stepping.  There is no reason why 
       more axes could not have been specified to step.   We have specified
       range information, but note that it is redundant from the  number of 
       frames and the increment, so we could drop the data item
       '_diffrn_scan_axis.angle_range'.
       
       We have specified both the sweep data and the data for a single frame.
     
       Note that the information on how the axes are stepped is given twice,
       once in terms of the overall averages in the value of
       '_diffrn_scan.integration_time' and the values for DIFFRN_SCAN_AXIS,
       and precisely for the given frame in the value for 
       '_diffrn_scan_frame.integration_time' and the values for
       DIFFRN_SCAN_FRAME_AXIS.  If dose-related adjustements are made to
       scan times and non-linear stepping is done, these values may differ.
       Therefore, in interpreting the data for a particular frame it is
       important to use the frame-specific data.
     
    ;
    ;
          _diffrn_scan.id                   1
          _diffrn_scan.date_start         '2001-11-18T03:26:42'
          _diffrn_scan.date_end           '2001-11-18T03:36:45'
          _diffrn_scan.integration_time    3.0
          _diffrn_scan.frame_id_start      mad_L2_000
          _diffrn_scan.frame_id_end        mad_L2_200
          _diffrn_scan.frames              201
    
           loop_
          _diffrn_scan_axis.scan_id
          _diffrn_scan_axis.axis_id
          _diffrn_scan_axis.angle_start
          _diffrn_scan_axis.angle_range
          _diffrn_scan_axis.angle_increment
          _diffrn_scan_axis.displacement_start
          _diffrn_scan_axis.displacement_range
          _diffrn_scan_axis.displacement_increment
    
           1 omega 200.0 20.0 0.1 . . . 
           1 kappa -40.0  0.0 0.0 . . . 
           1 phi   127.5  0.0 0.0 . . . 
           1 tranz  . . .   2.3 0.0 0.0 
    
          _diffrn_scan_frame.scan_id                   1
          _diffrn_scan_frame.date               '2001-11-18T03:27:33'
          _diffrn_scan_frame.integration_time    3.0
          _diffrn_scan_frame.frame_id            mad_L2_018
          _diffrn_scan_frame.frame_number        18
    
          loop_
          _diffrn_scan_frame_axis.frame_id
          _diffrn_scan_frame_axis.axis_id
          _diffrn_scan_frame_axis.angle
          _diffrn_scan_frame_axis.angle_increment
          _diffrn_scan_frame_axis.displacement
          _diffrn_scan_frame_axis.displacement_increment
    
           mad_L2_018 omega 201.8  0.1 . .
           mad_L2_018 kappa -40.0  0.0 . .
           mad_L2_018 phi   127.5  0.0 . .
           mad_L2_018 tranz  .     .  2.3 0.0
    
    ;
    
    ;
        Example 2 - a more extensive example, R. M. Sweet, P. Ellis, H. Bernstein.
        
       We place a detector 240 mm along the Z axis from the goniometer.
       This presents us with a choice -- either we define the axes of
       the detector at the origin, and then put a Z setting of -240 in
       for the actual use, or we define the axes with the necessary Z-offset.
       In this case we use the setting, and leave the offset as zero.
       We call this axis DETECTOR_Z.
       
       The axis for positioning the detector in the Y-direction depends
       on the detector Z-axis.  We call this axis, DETECTOR_Y.
       
       The axis for positioning the dector in the X-direction depends
       on the detector Y-axis (and therefore on the detector Z-axis).
       We call this axis DETECTOR_X.
       
       This detector may be rotated around the Y-axis.  This rotation axis
       depends on the three translation axies.  We call it DETECTOR_PITCH.
       
       We define a coordinate system on the face of the detector in terms of
       2300 0.150 mm pixels in each direction.  The ELEMENT_X axis is used to
       index the first array index of the data array and the ELEMENT_Y
       axis is used to index the second array index.  Because the pixels
       are 0.150mm x 0.150mm, the center of the first pixel is at (0.075, 
       0.075) in this coordinate system.
     
    ;
    ;
         ###CBF: VERSION 1.1 
    
         data_image_1 
     
    
         # category DIFFRN 
    
         _diffrn.id P6MB 
         _diffrn.crystal_id P6MB_CRYSTAL7 
     
    
         # category DIFFRN_SOURCE 
    
         loop_ 
         _diffrn_source.diffrn_id 
         _diffrn_source.source 
         _diffrn_source.type 
          P6MB synchrotron 'SSRL beamline 9-1' 
     
    
         # category DIFFRN_RADIATION 
    
              loop_ 
         _diffrn_radiation.diffrn_id 
         _diffrn_radiation.wavelength_id 
         _diffrn_radiation.monochromator 
         _diffrn_radiation.polarizn_source_ratio 
         _diffrn_radiation.polarizn_source_norm 
         _diffrn_radiation.div_x_source 
         _diffrn_radiation.div_y_source 
         _diffrn_radiation.div_x_y_source 
          P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08
         0.01 0.00 
     
    
         # category DIFFRN_RADIATION_WAVELENGTH 
    
         loop_ 
         _diffrn_radiation_wavelength.id 
         _diffrn_radiation_wavelength.wavelength 
         _diffrn_radiation_wavelength.wt 
          WAVELENGTH1 0.98 1.0 
     
    
         # category DIFFRN_DETECTOR 
    
         loop_ 
         _diffrn_detector.diffrn_id 
         _diffrn_detector.id 
         _diffrn_detector.type 
         _diffrn_detector.number_of_axes 
          P6MB MAR345-SN26 'MAR 345' 4 
     
    
         # category DIFFRN_DETECTOR_AXIS 
    
         loop_ 
         _diffrn_detector_axis.detector_id 
         _diffrn_detector_axis.axis_id 
          MAR345-SN26 DETECTOR_X 
          MAR345-SN26 DETECTOR_Y 
          MAR345-SN26 DETECTOR_Z 
          MAR345-SN26 DETECTOR_PITCH 
     
    
         # category DIFFRN_DETECTOR_ELEMENT 
    
         loop_ 
         _diffrn_detector_element.id 
         _diffrn_detector_element.detector_id 
          ELEMENT1 MAR345-SN26 
     
    
         # category DIFFRN_DATA_FRAME 
    
         loop_ 
         _diffrn_data_frame.id 
         _diffrn_data_frame.detector_element_id 
         _diffrn_data_frame.array_id 
         _diffrn_data_frame.binary_id 
          FRAME1 ELEMENT1 ARRAY1 1 
     
    
         # category DIFFRN_MEASUREMENT 
    
         loop_ 
         _diffrn_measurement.diffrn_id 
         _diffrn_measurement.id 
         _diffrn_measurement.number_of_axes 
         _diffrn_measurement.method 
          P6MB GONIOMETER 3 rotation 
     
    
         # category DIFFRN_MEASUREMENT_AXIS 
    
         loop_ 
         _diffrn_measurement_axis.measurement_id 
         _diffrn_measurement_axis.axis_id 
          GONIOMETER GONIOMETER_PHI 
          GONIOMETER GONIOMETER_KAPPA 
          GONIOMETER GONIOMETER_OMEGA 
     
    
         # category DIFFRN_SCAN 
    
         loop_ 
         _diffrn_scan.id 
         _diffrn_scan.frame_id_start 
         _diffrn_scan.frame_id_end 
         _diffrn_scan.frames 
          SCAN1 FRAME1 FRAME1 1 
     
    
         # category DIFFRN_SCAN_AXIS 
    
         loop_ 
         _diffrn_scan_axis.scan_id 
         _diffrn_scan_axis.axis_id 
         _diffrn_scan_axis.angle_start 
         _diffrn_scan_axis.angle_range 
         _diffrn_scan_axis.angle_increment 
         _diffrn_scan_axis.displacement_start 
         _diffrn_scan_axis.displacement_range 
         _diffrn_scan_axis.displacement_increment 
          SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 
          SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 
          SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 
          SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 
          SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 
          SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 
          SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 
     
    
         # category DIFFRN_SCAN_FRAME 
    
         loop_ 
         _diffrn_scan_frame.frame_id 
         _diffrn_scan_frame.frame_number 
         _diffrn_scan_frame.integration_time 
         _diffrn_scan_frame.scan_id 
         _diffrn_scan_frame.date 
          FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 
     
    
         # category DIFFRN_SCAN_FRAME_AXIS 
    
         loop_ 
         _diffrn_scan_frame_axis.frame_id 
         _diffrn_scan_frame_axis.axis_id 
         _diffrn_scan_frame_axis.angle 
         _diffrn_scan_frame_axis.displacement 
          FRAME1 GONIOMETER_OMEGA 12.0 0.0 
          FRAME1 GONIOMETER_KAPPA 23.3 0.0 
          FRAME1 GONIOMETER_PHI -165.8 0.0 
          FRAME1 DETECTOR_Z 0.0 -240.0 
          FRAME1 DETECTOR_Y 0.0 0.6 
          FRAME1 DETECTOR_X 0.0 -0.5 
          FRAME1 DETECTOR_PITCH 0.0 0.0 
     
    
         # category AXIS 
    
         loop_ 
         _axis.id 
         _axis.type 
         _axis.equipment 
         _axis.depends_on 
         _axis.vector[1] _axis.vector[2] _axis.vector[3] 
         _axis.offset[1] _axis.offset[2] _axis.offset[3] 
          GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . 
          GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279
          0 0.76604 . . . 
          GONIOMETER_PHI   rotation goniometer GONIOMETER_KAPPA 1 0 0
         . . . 
          SOURCE           general source . 0 0 1 . . . 
          GRAVITY          general gravity . 0 -1 0 . . . 
          DETECTOR_Z       translation detector . 0 0 1 0 0 0
          DETECTOR_Y       translation detector DETECTOR_Z 0 1 0 0 0 0 
          DETECTOR_X       translation detector DETECTOR_Y 1 0 0 0 0 0 
          DETECTOR_PITCH   rotation    detector DETECTOR_X 0 1 0 0 0 0 
          ELEMENT_X        translation detector DETECTOR_PITCH
         1 0 0 172.43 -172.43 0
          ELEMENT_Y        translation detector ELEMENT_X
         0 1 0 0 0 0 
     
         # category ARRAY_STRUCTURE_LIST 
    
         loop_ 
         _array_structure_list.array_id 
         _array_structure_list.index 
         _array_structure_list.dimension 
         _array_structure_list.precedence 
         _array_structure_list.direction 
         _array_structure_list.axis_set_id 
          ARRAY1 1 2300 1 increasing ELEMENT_X 
          ARRAY1 2 2300 2 increasing ELEMENT_Y 
     
     
         # category ARRAY_STRUCTURE_LIST_AXIS 
    
         loop_
         _array_structure_list_axis.axis_set_id
         _array_structure_list_axis.axis_id
         _array_structure_list_axis.displacement
         _array_structure_list_axis.displacement_increment
          ELEMENT_X ELEMENT_X 0.075 0.150
          ELEMENT_Y ELEMENT_Y 0.075 0.150
    
         # category ARRAY_ELEMENT_SIZE 
    
         loop_ 
         _array_element_size.array_id 
         _array_element_size.index 
         _array_element_size.size 
          ARRAY1 1 150e-6 
          ARRAY1 2 150e-6 
     
    
         # category ARRAY_INTENSITIES 
    
         loop_ 
         _array_intensities.array_id 
         _array_intensities.binary_id 
         _array_intensities.linearity 
         _array_intensities.gain 
         _array_intensities.gain_esd 
         _array_intensities.overload
         _array_intensities.undefined_value 
          ARRAY1 1 linear 1.15 0.2 240000 0 
     
    
          # category ARRAY_STRUCTURE 
    
          loop_ 
          _array_structure.id 
          _array_structure.encoding_type 
          _array_structure.compression_type 
          _array_structure.byte_order 
          ARRAY1 "signed 32-bit integer" packed little_endian 
     
    
         # category ARRAY_DATA         
    
         loop_ 
         _array_data.array_id 
         _array_data.binary_id 
         _array_data.data 
          ARRAY1 1 
         ; 
         --CIF-BINARY-FORMAT-SECTION-- 
         Content-Type: application/octet-stream; 
             conversions="x-CBF_PACKED" 
         Content-Transfer-Encoding: BASE64 
         X-Binary-Size: 3801324 
         X-Binary-ID: 1 
         X-Binary-Element-Type: "signed 32-bit integer" 
         Content-MD5: 07lZFvF+aOcW85IN7usl8A== 
    
         AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg 
         ... 
         8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE 
    
         --CIF-BINARY-FORMAT-SECTION---- 
         ; 
    ;
    
    ;
        Example 3 - Example 2 revised for a spiral scan, R. M. Sweet, 
        P. Ellis, H. Bernstein.
        
       We place a detector 240 mm along the Z axis from the goniometer,
       as in Example 2, above, but in this example, the image plate is
       scanned in a spiral pattern outside edge in.
       
       The axis for positioning the detector in the Y-direction depends
       on the detector Z-axis.  We call this axis, DETECTOR_Y.
       
       The axis for positioning the dector in the X-direction depends
       on the detector Y-axis (and therefore on the detector Z-axis).
       We call this axis DETECTOR_X.
       
       This detector may be rotated around the Y-axis.  This rotation axis
       depends on the three translation axies.  We call it DETECTOR_PITCH.
     
       We define a coordinate system on the face of the detector in
       terms of a coupled rotation axis and radial scan axis to form 
       a spiral scan.  Let us call rotation axis ELEMENT_ROT, and the
       radial axis ELEMENT_RAD.   We assume 150 um radial pitch and 75 um 
       'constant velocity' angular pitch. 
    
       We index first on the rotation axis and make the radial axis
       dependent on 
       it. 
    
       The two axes are coupled to form an axis set ELEMENT_SPIRAL. 
     
    ;
    ;
         ###CBF: VERSION 1.1 
    
         data_image_1 
     
    
         # category DIFFRN 
    
         _diffrn.id P6MB 
         _diffrn.crystal_id P6MB_CRYSTAL7 
     
    
         # category DIFFRN_SOURCE 
    
         loop_ 
         _diffrn_source.diffrn_id 
         _diffrn_source.source 
         _diffrn_source.type 
          P6MB synchrotron 'SSRL beamline 9-1' 
     
    
         # category DIFFRN_RADIATION 
    
              loop_ 
         _diffrn_radiation.diffrn_id 
         _diffrn_radiation.wavelength_id 
         _diffrn_radiation.monochromator 
         _diffrn_radiation.polarizn_source_ratio 
         _diffrn_radiation.polarizn_source_norm 
         _diffrn_radiation.div_x_source 
         _diffrn_radiation.div_y_source 
         _diffrn_radiation.div_x_y_source 
          P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08
         0.01 0.00 
     
    
         # category DIFFRN_RADIATION_WAVELENGTH 
    
         loop_ 
         _diffrn_radiation_wavelength.id 
         _diffrn_radiation_wavelength.wavelength 
         _diffrn_radiation_wavelength.wt 
          WAVELENGTH1 0.98 1.0 
     
    
         # category DIFFRN_DETECTOR 
    
         loop_ 
         _diffrn_detector.diffrn_id 
         _diffrn_detector.id 
         _diffrn_detector.type 
         _diffrn_detector.number_of_axes 
          P6MB MAR345-SN26 'MAR 345' 4 
     
    
         # category DIFFRN_DETECTOR_AXIS 
    
         loop_ 
         _diffrn_detector_axis.detector_id 
         _diffrn_detector_axis.axis_id 
          MAR345-SN26 DETECTOR_X 
          MAR345-SN26 DETECTOR_Y 
          MAR345-SN26 DETECTOR_Z 
          MAR345-SN26 DETECTOR_PITCH 
     
    
         # category DIFFRN_DETECTOR_ELEMENT 
    
         loop_ 
         _diffrn_detector_element.id 
         _diffrn_detector_element.detector_id 
          ELEMENT1 MAR345-SN26 
     
    
         # category DIFFRN_DATA_FRAME 
    
         loop_ 
         _diffrn_data_frame.id 
         _diffrn_data_frame.detector_element_id 
         _diffrn_data_frame.array_id 
         _diffrn_data_frame.binary_id 
          FRAME1 ELEMENT1 ARRAY1 1 
     
    
         # category DIFFRN_MEASUREMENT 
    
         loop_ 
         _diffrn_measurement.diffrn_id 
         _diffrn_measurement.id 
         _diffrn_measurement.number_of_axes 
         _diffrn_measurement.method 
          P6MB GONIOMETER 3 rotation 
     
    
         # category DIFFRN_MEASUREMENT_AXIS 
    
         loop_ 
         _diffrn_measurement_axis.measurement_id 
         _diffrn_measurement_axis.axis_id 
          GONIOMETER GONIOMETER_PHI 
          GONIOMETER GONIOMETER_KAPPA 
          GONIOMETER GONIOMETER_OMEGA 
     
    
         # category DIFFRN_SCAN 
    
         loop_ 
         _diffrn_scan.id 
         _diffrn_scan.frame_id_start 
         _diffrn_scan.frame_id_end 
         _diffrn_scan.frames 
          SCAN1 FRAME1 FRAME1 1 
     
    
         # category DIFFRN_SCAN_AXIS 
    
         loop_ 
         _diffrn_scan_axis.scan_id 
         _diffrn_scan_axis.axis_id 
         _diffrn_scan_axis.angle_start 
         _diffrn_scan_axis.angle_range 
         _diffrn_scan_axis.angle_increment 
         _diffrn_scan_axis.displacement_start 
         _diffrn_scan_axis.displacement_range 
         _diffrn_scan_axis.displacement_increment 
          SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 
          SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 
          SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 
          SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 
          SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 
          SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 
          SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 
     
    
         # category DIFFRN_SCAN_FRAME 
    
         loop_ 
         _diffrn_scan_frame.frame_id 
         _diffrn_scan_frame.frame_number 
         _diffrn_scan_frame.integration_time 
         _diffrn_scan_frame.scan_id 
         _diffrn_scan_frame.date 
          FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 
     
    
         # category DIFFRN_SCAN_FRAME_AXIS 
    
         loop_ 
         _diffrn_scan_frame_axis.frame_id 
         _diffrn_scan_frame_axis.axis_id 
         _diffrn_scan_frame_axis.angle 
         _diffrn_scan_frame_axis.displacement 
          FRAME1 GONIOMETER_OMEGA 12.0 0.0 
          FRAME1 GONIOMETER_KAPPA 23.3 0.0 
          FRAME1 GONIOMETER_PHI -165.8 0.0 
          FRAME1 DETECTOR_Z 0.0 -240.0 
          FRAME1 DETECTOR_Y 0.0 0.6 
          FRAME1 DETECTOR_X 0.0 -0.5 
          FRAME1 DETECTOR_PITCH 0.0 0.0 
     
    
         # category AXIS 
    
         loop_ 
         _axis.id 
         _axis.type 
         _axis.equipment 
         _axis.depends_on 
         _axis.vector[1] _axis.vector[2] _axis.vector[3] 
         _axis.offset[1] _axis.offset[2] _axis.offset[3] 
          GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . 
          GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279
          0 0.76604 . . . 
          GONIOMETER_PHI   rotation goniometer GONIOMETER_KAPPA 1 0 0
         . . . 
          SOURCE           general source . 0 0 1 . . . 
          GRAVITY          general gravity . 0 -1 0 . . . 
          DETECTOR_Z       translation detector . 0 0 1 0 0 0
          DETECTOR_Y       translation detector DETECTOR_Z 0 1 0 0 0 0 
          DETECTOR_X       translation detector DETECTOR_Y 1 0 0 0 0 0 
          DETECTOR_PITCH   rotation    detector DETECTOR_X 0 1 0 0 0 0 
          ELEMENT_ROT      translation detector DETECTOR_PITCH 0 0 1 0 0 0
          ELEMENT_RAD      translation detector ELEMENT_ROT 0 1 0 0 0 0 
     
         # category ARRAY_STRUCTURE_LIST 
    
         loop_ 
         _array_structure_list.array_id 
         _array_structure_list.index 
         _array_structure_list.dimension 
         _array_structure_list.precedence 
         _array_structure_list.direction 
         _array_structure_list.axis_set_id 
          ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL
     
     
         # category ARRAY_STRUCTURE_LIST_AXIS 
    
         loop_
         _array_structure_list_axis.axis_set_id
         _array_structure_list_axis.axis_id
         _array_structure_list_axis.angle
         _array_structure_list_axis.displacement
         _array_structure_list_axis.angular_pitch
         _array_structure_list_axis.radial_pitch
          ELEMENT_SPIRAL ELEMENT_ROT 0    .  0.075   .
          ELEMENT_SPIRAL ELEMENT_RAD . 172.5  .    -0.150
    
         # category ARRAY_ELEMENT_SIZE 
         # the actual pixels are 0.075 by 0.150 mm
         # We give the coarser dimension here.
    
         loop_ 
         _array_element_size.array_id 
         _array_element_size.index 
         _array_element_size.size 
          ARRAY1 1 150e-6 
     
    
         # category ARRAY_INTENSITIES 
    
         loop_ 
         _array_intensities.array_id 
         _array_intensities.binary_id 
         _array_intensities.linearity 
         _array_intensities.gain 
         _array_intensities.gain_esd 
         _array_intensities.overload
         _array_intensities.undefined_value 
          ARRAY1 1 linear 1.15 0.2 240000 0 
     
    
          # category ARRAY_STRUCTURE 
    
          loop_ 
          _array_structure.id 
          _array_structure.encoding_type 
          _array_structure.compression_type 
          _array_structure.byte_order 
          ARRAY1 "signed 32-bit integer" packed little_endian 
     
    
         # category ARRAY_DATA         
    
         loop_ 
         _array_data.array_id 
         _array_data.binary_id 
         _array_data.data 
          ARRAY1 1 
         ; 
         --CIF-BINARY-FORMAT-SECTION-- 
         Content-Type: application/octet-stream; 
             conversions="x-CBF_PACKED" 
         Content-Transfer-Encoding: BASE64 
         X-Binary-Size: 3801324 
         X-Binary-ID: 1 
         X-Binary-Element-Type: "signed 32-bit integer" 
         Content-MD5: 07lZFvF+aOcW85IN7usl8A== 
    
         AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg 
         ... 
         8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE 
    
         --CIF-BINARY-FORMAT-SECTION---- 
         ; 
    ;
    
    
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
           save_
     
     
    save__diffrn_scan.id
        _item_description.description
    ;             The value of '_diffrn_scan.id' uniquely identifies each
                  scan.  The identifier is used to tie together all the 
                  information about the scan.
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
           '_diffrn_scan.id'                 diffrn_scan             yes
           '_diffrn_scan_axis.scan_id'       diffrn_scan_axis        yes
           '_diffrn_scan_frame.scan_id'      diffrn_scan_frame       yes
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
           '_diffrn_scan_axis.scan_id'          '_diffrn_scan.id'
           '_diffrn_scan_frame.scan_id'         '_diffrn_scan.id'
         save_
     
     
    save__diffrn_scan.date_end
        _item_description.description
    ;
                   The date and time of the end of the scan.  Note that this
                   may be an estimate generated during the scan, before the
                   precise time of the end of the scan is known.
    ;
        _item.name                 '_diffrn_scan.date_end'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no
        _item_type.code            yyyy-mm-dd
         save_
     
     
    save__diffrn_scan.date_start
        _item_description.description
    ;
                   The date and time of the start of the scan.
    ;
        _item.name                 '_diffrn_scan.date_start'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no
        _item_type.code            yyyy-mm-dd
         save_
     
     
    save__diffrn_scan.integration_time
        _item_description.description
    ;
                   Approximate average time in seconds to integrate each 
                   step of the scan.  The precise time for integration
                   of each particular step must be provided in
                   '_diffrn_scan_frame.integration_time', even
                   if all steps have the same integration time.
    ;
        _item.name                 '_diffrn_scan.integration_time'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no
        _item_type.code            float
        _item_units.code           'seconds'
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0.0
         save_
     
     
    save__diffrn_scan.frame_id_start
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   first frame in the scan.
    
                   This item is a pointer to '_diffrn_data_frame.id' in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name                 '_diffrn_scan.frame_id_start'
        _item.category_id          diffrn_scan
        _item.mandatory_code       yes
         save_
     
     
    save__diffrn_scan.frame_id_end
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   last frame in the scan.
    
                   This item is a pointer to '_diffrn_data_frame.id' in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name                 '_diffrn_scan.frame_id_end'
        _item.category_id          diffrn_scan
        _item.mandatory_code       yes 
         save_
     
     
    save__diffrn_scan.frames
        _item_description.description
    ;
                   The value of this data item is the number of frames in
                   the scan.
    
    ;
        _item.name                 '_diffrn_scan.frames'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no 
        _item_type.code            int
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   1
                                1   1
         save_
     
     
    ####################
    # DIFFRN_SCAN_AXIS #
    ####################
    
    save_DIFFRN_SCAN_AXIS
        _category.description 
    ;
         Data items in the DIFFRN_SCAN_AXIS category describe the settings of
         axes for particular scans.  Unspecified axes are assumed to be at
         their zero points.
    
    ;
        _category.id                   diffrn_scan_axis
        _category.mandatory_code       no
         loop_
        _category_key.name            
                                      '_diffrn_scan_axis.scan_id'
                                      '_diffrn_scan_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
     
     
    save__diffrn_scan_axis.scan_id
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   scan for which axis settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   '_diffrn_scan.id'.
    
                   This item is a pointer to '_diffrn_scan.id' in the
                   DIFFRN_SCAN category.
    ;
        _item.name                 '_diffrn_scan_axis.scan_id'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       yes
         save_
     
     
    save__diffrn_scan_axis.axis_id
        _item_description.description
    ;
                   The value of this data item is the identifier of one of
                   the axes for the scan for which settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   '_diffrn_scan.id'.
    
                   This item is a pointer to '_axis.id' in the
                   AXIS category.
    ;
        _item.name                 '_diffrn_scan_axis.axis_id'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       yes
         save_
     
     
    save__diffrn_scan_axis.angle_start
        _item_description.description
    ;
                   The starting position for the specified axis in degrees.
    ;
        _item.name                 '_diffrn_scan_axis.angle_start'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
     
     
    save__diffrn_scan_axis.angle_range
        _item_description.description
    ;
                   The range from the starting position for the specified axis 
                   in degrees.
    ;
        _item.name                 '_diffrn_scan_axis.angle_range'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
     
     
    save__diffrn_scan_axis.angle_increment
        _item_description.description
    ;
                   The increment for each step for the specified axis
                   in degrees.  In general, this will agree with
                   '_diffrn_scan_frame_axis.angle_increment'. The 
                   sum of the values of '_diffrn_scan_frame_axis.angle' and
                   '_diffrn_scan_frame_axis.angle_increment' is the
                   angular setting of the axis at the end of the integration
                   time for a given frame.  If the individual frame values
                   vary, then the value of 
                   '_diffrn_scan_axis.angle_increment' will be 
                   representative
                   of the ensemble of values of
                   '_diffrn_scan_frame_axis.angle_increment' (e.g.
                   the mean).
    
    ;
        _item.name                 '_diffrn_scan_axis.angle_increment'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
     
     
    save__diffrn_scan_axis.angle_rstrt_incr
        _item_description.description
    ;
                   The increment after each step for the specified axis
                   in degrees.  In general, this will agree with
                   '_diffrn_scan_frame_axis.angle_rstrt_incr'.  The
                   sum of the values of '_diffrn_scan_frame_axis.angle' 
                   and  '_diffrn_scan_frame_axis.angle_increment' 
                   and  '_diffrn_scan_frame_axis.angle_rstrt_incr' is the
                   angular setting of the axis at the start of the integration
                   time for the next frame relative to a given frame, and 
                   should equal '_diffrn_scan_frame_axis.angle' for that 
                   next frame.   If the individual frame values
                   vary, then the value of 
                   '_diffrn_scan_axis.angle_rstrt_incr' will be 
                   representative
                   of the ensemble of values of
                   '_diffrn_scan_frame_axis.angle_rstrt_incr' (e.g.
                   the mean).
    ;
        _item.name                 '_diffrn_scan_axis.angle_rstrt_incr'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
     
     
    save__diffrn_scan_axis.displacement_start
        _item_description.description
    ;
                   The starting position for the specified axis in millimetres.
    ;
        _item.name                 '_diffrn_scan_axis.displacement_start'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
     
     
    save__diffrn_scan_axis.displacement_range
        _item_description.description
    ;
                   The range from the starting position for the specified axis 
                   in millimetres.
    ;
        _item.name                 '_diffrn_scan_axis.displacement_range'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
     
     
    save__diffrn_scan_axis.displacement_increment
        _item_description.description
    ;
                   The increment for each step for the specified axis
                   in millimetres.  In general, this will agree with
                   '_diffrn_scan_frame_axis.displacement_increment'.
                   The sum of the values of 
                   '_diffrn_scan_frame_axis.displacement' and
                   '_diffrn_scan_frame_axis.displacement_increment' is the
                   angular setting of the axis at the end of the integration
                   time for a given frame.  If the individual frame values
                   vary, then the value of 
                   '_diffrn_scan_axis.displacement_increment' will be 
                   representative
                   of the ensemble of values of
                   '_diffrn_scan_frame_axis.displacement_increment' (e.g.
                   the mean).
    ;
        _item.name                 '_diffrn_scan_axis.displacement_increment'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
     
     
    save__diffrn_scan_axis.displacement_rstrt_incr
        _item_description.description
    ;
                   The increment for each step for the specified axis
                   in millimetres.  In general, this will agree with
                   '_diffrn_scan_frame_axis.displacement_rstrt_incr'.
                   The sum of the values of 
                   '_diffrn_scan_frame_axis.displacement' and
                   '_diffrn_scan_frame_axis.displacement_increment' and
                   '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the
                   angular setting of the axis at the start of the integration
                   time for the next frame relative to a given frame, and 
                   should equal '_diffrn_scan_frame_axis.displacement' 
                   for that next frame.  If the individual frame values
                   vary, then the value of 
                   '_diffrn_scan_axis.displacement_rstrt_incr' will be 
                   representative
                   of the ensemble of values of
                   '_diffrn_scan_frame_axis.displacement_rstrt_incr' (e.g.
                   the mean).
    ;
        _item.name                 '_diffrn_scan_axis.displacement_rstrt_incr'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
     
     
    #####################
    # DIFFRN_SCAN_FRAME #
    #####################
    
    save_DIFFRN_SCAN_FRAME
        _category.description 
    ;
                Data items in the DIFFRN_SCAN_FRAME category describe
                the relationship of particular frames to scans.
    
    ;
        _category.id                   diffrn_scan_frame
        _category.mandatory_code       no
         loop_
        _category_key.name     
                                      '_diffrn_scan_frame.scan_id'
                                      '_diffrn_scan_frame.frame_id'
         loop_
        _category_group.id            'inclusive_group'
                                      'diffrn_group'
         save_
     
     
    save__diffrn_scan_frame.date
        _item_description.description
    ;
                   The date and time of the start of the frame being scanned.
    ;
        _item.name                 '_diffrn_scan_frame.date'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       no
        _item_type.code            yyyy-mm-dd
         save_
     
     
    save__diffrn_scan_frame.frame_id
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   frame being examined.
    
                   This item is a pointer to '_diffrn_data_frame.id' in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name                 '_diffrn_scan_frame.frame_id'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       yes
         save_
     
     
    save__diffrn_scan_frame.frame_number
        _item_description.description
    ;
                   The value of this data item is the number of the frame
                   within the scan, starting with 1.  It is not necessarily
                   the same as the value of '_diffrn_scan_frame.frame_id',
                   but may be.
    
    ;
        _item.name                 '_diffrn_scan_frame.frame_number'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       no 
        _item_type.code            int
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0
                                0   0
         save_
     
     
    save__diffrn_scan_frame.integration_time
        _item_description.description
    ;
                   The time in seconds to integrate this step of the scan.
                   This should be the precise time of integration of each
                   particular frame.  The value of this data item should
                   be given explicitly for each frame and not inferred
                   from the value of '_diffrn_scan.integration_time'.
    ;
        _item.name                 '_diffrn_scan_frame.integration_time'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       yes 
        _item_type.code            float
        _item_units.code           'seconds'
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0.0
         save_
     
     
    save__diffrn_scan_frame.scan_id
        _item_description.description
    ;             The value of '_diffrn_scan_frame.scan_id' identifies the scan
                  containing this frame.
    
                  This item is a pointer to '_diffrn_scan.id' in the
                  DIFFRN_SCAN category.
    ;
        _item.name             '_diffrn_scan_frame.scan_id'    
        _item.category_id        diffrn_scan_frame        
        _item.mandatory_code     yes     
         save_
     
     
    ##########################
    # DIFFRN_SCAN_FRAME_AXIS #
    ##########################
    
    save_DIFFRN_SCAN_FRAME_AXIS
        _category.description
    ;
         Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the
         settings of axes for particular frames.  Unspecified axes are
         assumed to be at their zero points.  If, for any given frame,
         non-zero values apply for any of the data items in this category,
         those values should be given explicitly in this category and not
         simply inferred from values in DIFFRN_SCAN_AXIS.
    
    ;
        _category.id                   diffrn_scan_frame_axis
        _category.mandatory_code       no
         loop_
        _category_key.name
                                      '_diffrn_scan_frame_axis.frame_id'
                                      '_diffrn_scan_frame_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
     
     
    save__diffrn_scan_frame_axis.axis_id
        _item_description.description
    ;
                   The value of this data item is the identifier of one of
                   the axes for the frame for which settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   '_diffrn_scan_frame.frame_id'.
    
                   This item is a pointer to '_axis.id' in the
                   AXIS category.
    ;
        _item.name                 '_diffrn_scan_frame_axis.axis_id'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       yes
         save_
     
     
    save__diffrn_scan_frame_axis.angle
        _item_description.description
    ;
                   The setting of the specified axis in degrees for this frame.
                   This is the setting at the start of the integration time.
    ;
        _item.name                 '_diffrn_scan_frame_axis.angle'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
     
     
    save__diffrn_scan_frame_axis.angle_increment
        _item_description.description
    ;
                   The increment for this frame for angular setting of
                   the specified axis in degrees.  The sum of the values
                   of '_diffrn_scan_frame_axis.angle' and
                   '_diffrn_scan_frame_axis.angle_increment' is the
                   angular setting of the axis at the end of the integration
                   time for this frame.
    ;
        _item.name                 '_diffrn_scan_frame_axis.angle_increment'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
     
     
    save__diffrn_scan_frame_axis.angle_rstrt_incr
        _item_description.description
    ;
                   The increment after this frame for angular setting of
                   the specified axis in degrees.  The sum of the values
                   of '_diffrn_scan_frame_axis.angle' and
                   '_diffrn_scan_frame_axis.angle_increment' and
                   '_diffrn_scan_frame_axis.angle_rstrt_incr' is the
                   angular setting of the axis at the start of the integration
                   time for the next frame, and should equal
                   '_diffrn_scan_frame_axis.angle' for that next frame.
    ;
        _item.name               '_diffrn_scan_frame_axis.angle_rstrt_incr'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
     
     
    save__diffrn_scan_frame_axis.displacement
        _item_description.description
    ;
                   The setting of the specified axis in millimetres for this
                   frame.  This is the setting at the start of the integration
                   time.
    
    ;
        _item.name               '_diffrn_scan_frame_axis.displacement'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
     
     
    save__diffrn_scan_frame_axis.displacement_increment
        _item_description.description
    ;
                   The increment for this frame for displacement setting of
                   the specified axis in millimetres.  The sum of the values
                   of '_diffrn_scan_frame_axis.displacement' and
                   '_diffrn_scan_frame_axis.displacement_increment' is the
                   angular setting of the axis at the end of the integration
                   time for this frame.
    ;
        _item.name               '_diffrn_scan_frame_axis.displacement_increment'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
     
     
    save__diffrn_scan_frame_axis.displacement_rstrt_incr
        _item_description.description
    ;
                   The increment for this frame for displacement setting of
                   the specified axis in millimetres.  The sum of the values
                   of '_diffrn_scan_frame_axis.displacement' and
                   '_diffrn_scan_frame_axis.displacement_increment' and
                   '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the
                   angular setting of the axis at the start of the integration
                   time for the next frame, and should equal
                   '_diffrn_scan_frame_axis.displacement' for that next frame.
    ;
        _item.name               '_diffrn_scan_frame_axis.displacement_rstrt_incr'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    save__diffrn_scan_frame_axis.frame_id
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   frame for which axis settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   '_diffrn_scan_frame.frame_id'.
    
                   This item is a pointer to '_diffrn_data_frame.id' in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name               '_diffrn_scan_frame_axis.frame_id'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       yes
         save_
    
    ########################   DEPRECATED DATA ITEMS ########################
    
    save__diffrn_detector_axis.id
        _item_description.description
    ;
                   This data item is a pointer to '_diffrn_detector.id' in
                   the DIFFRN_DETECTOR category.
                  
                   DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_detector_axis.id'
        _item.category_id             diffrn_detector_axis
        _item.mandatory_code          yes
         save_
    
    save__diffrn_measurement_axis.id
        _item_description.description
    ;
                   This data item is a pointer to '_diffrn_measurement.id' in
                   the DIFFRN_MEASUREMENT category.
                  
                   DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_measurement_axis.id'
        _item.category_id             diffrn_measurement_axis
        _item.mandatory_code          yes
         save_
    
    #########################   DEPRECATED CATEGORY #########################
    #####################
    # DIFFRN_FRAME_DATA #
    #####################
     
     
    save_DIFFRN_FRAME_DATA
        _category.description
    ;
                  Data items in the DIFFRN_FRAME_DATA category record
                  the details about each frame of data. 
    
                  The items in this category are now in the
                  DIFFRN_DATA_FRAME category.
                  
                  The items in the DIFFRN_FRAME_DATA category
                  are now deprecated.  The items from this category 
                  are provided as aliases in the 1.0.0 dictionary, 
                  but should not be used for new work.
                  The items from the old category are provided
                  in this dictionary for completeness,
                  but should not be used or cited.  To avoid
                  confusion, the example has been removed,
                  and the redundant parent child-links to other
                  categories removed.
    ;
        _category.id                   diffrn_frame_data
        _category.mandatory_code       no
         loop_
        _category_key.name             '_diffrn_frame_data.id'
                                       '_diffrn_frame_data.detector_element_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        THE DIFFRN_DATA_FRAME category is deprecated and should not be used.
    ;
    ;
           # EXAMPLE REMOVED #
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
     
     
    save__diffrn_frame_data.array_id
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category.
    
                  DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_frame_data.array_id'
        _item.category_id             diffrn_frame_data
        _item.mandatory_code          yes
        _item_type.code               code
         save_
     
     
    save__diffrn_frame_data.binary_id
        _item_description.description
    ;             This item is a pointer to '_array_data.binary_id' in the
                  ARRAY_STRUCTURE category. 
                  
                  DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_frame_data.binary_id'
        _item.category_id             diffrn_frame_data
        _item.mandatory_code          implicit
        _item_type.code               int
         save_
     
     
    save__diffrn_frame_data.detector_element_id
        _item_description.description
    ;             
                  This item is a pointer to '_diffrn_detector_element.id'
                  in the DIFFRN_DETECTOR_ELEMENT category.
    
                  DEPRECATED -- DO NOT USE 
    ;
        _item.name                  '_diffrn_frame_data.detector_element_id'
        _item.category_id             diffrn_frame_data
        _item.mandatory_code          yes
        _item_type.code               code
         save_
     
     
    save__diffrn_frame_data.id
        _item_description.description
    ;             
                  The value of '_diffrn_frame_data.id' must uniquely identify
                  each complete frame of data.
    
                  DEPRECATED -- DO NOT USE 
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
               '_diffrn_frame_data.id'        diffrn_frame_data  yes
        _item_type.code               code
         save_
    
    ################ END DEPRECATED SECTION ###########
    
    
    ####################
    ## ITEM_TYPE_LIST ##
    ####################
    #
    #
    #  The regular expressions defined here are not compliant
    #  with the POSIX 1003.2 standard as they include the
    #  '\n' and '\t' special characters.  These regular expressions
    #  have been tested using version 0.12 of Richard Stallman's
    #  GNU regular expression library in POSIX mode.
    #  In order to allow presentation of a regular expression
    #  in a text field concatenate any line ending in a backslash
    #  with the following line, after discarding the backslash.
    #
    #  A formal definition of the '\n' and '\t' special characters
    #  is most properly done in the DDL, but for completeness, please
    #  note that '\n' is the line termination character ('newline')
    #  and '\t' is the horizontal tab character.  There is a formal
    #  ambiguity in the use of '\n' for line termination, in that
    #  the intention is that the equivalent machine/OS-dependent line
    #  termination character sequence should be accepted as a match, e.g.
    #
    #      '\r' (control-M) under MacOS
    #      '\n' (control-J) under Unix
    #      '\r\n' (control-M control-J) under DOS and MS Windows
    #
         loop_
        _item_type_list.code
        _item_type_list.primitive_code
        _item_type_list.construct
        _item_type_list.detail
                   code      char
    '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
    ;              code item types/single words ...
    ;
                   ucode      uchar
    '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
    ;              code item types/single words (case insensitive)
    ;
                   line      char
    '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
    ;              code item types / multi-word items  ...
    ;
                   uline     uchar
    '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
    ;              code item types / multi-word items (case insensitive)
    ;
                   text      char
    '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*'
    ;              text item types / multi-line text ...
    ;
                   binary    char
    ;\n--CIF-BINARY-FORMAT-SECTION--\n\
    [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\
    \n--CIF-BINARY-FORMAT-SECTION----
    ;
    ;              binary items are presented as MIME-like ascii-encoded
                   sections in an imgCIF.  In a CBF, raw octet streams
                   are used to convey the same information.
    ;
                   int       numb
    '-?[0-9]+'
    ;              int item types are the subset of numbers that are the negative
                   or positive integers.
    ;
                   float     numb
    '-?(([0-9]+)|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?'
    ;              float item types are the subset of numbers that are the floating
                   numbers.
    ;
                   any       char
    '.*'
    ;              A catch all for items that may take any form...
    ;
                   yyyy-mm-dd  char
    ;\
    [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9][0-9]\
    (T[0-2][0-9]:[0-5][0-9]:[0-5][0-9](.[0-9]+)([+-][0-5][0-9]:[0-5][0-9]))
    ;
    ;
                   Standard format for CIF date and time strings (see
                   http://www.iucr.org/iucr-top/cif/spec/datetime.html),
                   consisting of a yyyy-mm-dd date optionally followed by
                   the character "T" followed by a 24-hour clock time,
                   optionally followed by a signed time-zone offset.
                   
                   The IUCr standard has been extended to allow for an optional
                   decimal fraction on the seconds of time.
                   
                   Time is local time if no time-zone offset is given.
    ;
     
     
    #####################
    ## ITEM_UNITS_LIST ##
    #####################
    
         loop_
        _item_units_list.code
        _item_units_list.detail
    #
         'metres'                 'metres'
         'centimetres'            'centimetres (metres * 10^( -2))'
         'millimetres'            'millimetres (metres * 10^( -3))'
         'nanometres'             'nanometres  (metres * 10^( -9))'
         'angstroms'              'angstroms   (metres * 10^(-10))'
         'picometres'             'picometres  (metres * 10^(-12))'
         'femtometres'            'femtometres (metres * 10^(-15))'
    #
         'reciprocal_metres'      'reciprocal metres (metres^(-1))'
         'reciprocal_centimetres' 
            'reciprocal centimetres ((metres * 10^( -2))^(-1))'
         'reciprocal_millimetres' 
            'reciprocal millimetres ((metres * 10^( -3))^(-1))'
         'reciprocal_nanometres'  
            'reciprocal nanometres  ((metres * 10^( -9))^(-1))'
         'reciprocal_angstroms'   
            'reciprocal angstroms   ((metres * 10^(-10))^(-1))'
         'reciprocal_picometres'  
            'reciprocal picometres  ((metres * 10^(-12))^(-1))'
    #
         'nanometres_squared'     'nanometres squared (metres * 10^( -9))^2'
         'angstroms_squared'      'angstroms squared  (metres * 10^(-10))^2'
         '8pi2_angstroms_squared' '8pi^2 * angstroms squared (metres * 10^(-10))^2'
         'picometres_squared'     'picometres squared (metres * 10^(-12))^2'
    #
         'nanometres_cubed'       'nanometres cubed (metres * 10^( -9))^3'
         'angstroms_cubed'        'angstroms cubed  (metres * 10^(-10))^3'
         'picometres_cubed'       'picometres cubed (metres * 10^(-12))^3'
    #
         'kilopascals'            'kilopascals'
         'gigapascals'            'gigapascals'
    #
         'hours'                  'hours'
         'minutes'                'minutes'
         'seconds'                'seconds'
         'microseconds'           'microseconds'
    #
         'degrees'                'degrees (of arc)'
         'degrees_squared'        'degrees (of arc) squared'
    #
         'degrees_per_minute'     'degrees (of arc) per minute'
    #
         'celsius'                'degrees (of temperature) Celsius'
         'kelvins'                'degrees (of temperature) Kelvin'
    #
         'counts'                 'counts'
         'counts_per_photon'      'counts per photon'
    #
         'electrons'              'electrons'
    #
         'electrons_squared'      'electrons squared'
    #
         'electrons_per_nanometres_cubed'
    ; electrons per nanometres cubed (electrons/(metres * 10^( -9))^(-3))
    ;
         'electrons_per_angstroms_cubed'
    ; electrons per angstroms cubed (electrons/(metres * 10^(-10))^(-3))
    ;
         'electrons_per_picometres_cubed'
    ; electrons per picometres cubed (electrons/(metres * 10^(-12))^(-3)) 
    ;
         'kilowatts'              'kilowatts'
         'milliamperes'           'milliamperes'
         'kilovolts'              'kilovolts'
    #
         'arbitrary'
    ; arbitrary system of units.
    ;
    #
    
         loop_
        _item_units_conversion.from_code
        _item_units_conversion.to_code
        _item_units_conversion.operator
        _item_units_conversion.factor
    ###
         'metres'                   'centimetres'              '*'   1.0E+02
         'metres'                   'millimetres'              '*'   1.0E+03
         'metres'                   'nanometres'               '*'   1.0E+09
         'metres'                   'angstroms'                '*'   1.0E+10
         'metres'                   'picometres'               '*'   1.0E+12
         'metres'                   'femtometres'              '*'   1.0E+15
    #
         'centimetres'              'metres'                   '*'   1.0E-02
         'centimetres'              'millimetres'              '*'   1.0E+01
         'centimetres'              'nanometres'               '*'   1.0E+07
         'centimetres'              'angstroms'                '*'   1.0E+08
         'centimetres'              'picometres'               '*'   1.0E+10
         'centimetres'              'femtometres'              '*'   1.0E+13
    #
         'millimetres'              'metres'                   '*'   1.0E-03
         'millimetres'              'centimetres'              '*'   1.0E-01
         'millimetres'              'nanometres'               '*'   1.0E+06
         'millimetres'              'angstroms'                '*'   1.0E+07
         'millimetres'              'picometres'               '*'   1.0E+09
         'millimetres'              'femtometres'              '*'   1.0E+12
    #
         'nanometres'               'metres'                   '*'   1.0E-09
         'nanometres'               'centimetres'              '*'   1.0E-07
         'nanometres'               'millimetres'              '*'   1.0E-06
         'nanometres'               'angstroms'                '*'   1.0E+01
         'nanometres'               'picometres'               '*'   1.0E+03
         'nanometres'               'femtometres'              '*'   1.0E+06
    #
         'angstroms'                'metres'                   '*'   1.0E-10
         'angstroms'                'centimetres'              '*'   1.0E-08
         'angstroms'                'millimetres'              '*'   1.0E-07
         'angstroms'                'nanometres'               '*'   1.0E-01
         'angstroms'                'picometres'               '*'   1.0E+02
         'angstroms'                'femtometres'              '*'   1.0E+05
    #
         'picometres'               'metres'                   '*'   1.0E-12
         'picometres'               'centimetres'              '*'   1.0E-10
         'picometres'               'millimetres'              '*'   1.0E-09
         'picometres'               'nanometres'               '*'   1.0E-03
         'picometres'               'angstroms'                '*'   1.0E-02
         'picometres'               'femtometres'              '*'   1.0E+03
    #
         'femtometres'              'metres'                   '*'   1.0E-15
         'femtometres'              'centimetres'              '*'   1.0E-13
         'femtometres'              'millimetres'              '*'   1.0E-12
         'femtometres'              'nanometres'               '*'   1.0E-06
         'femtometres'              'angstroms'                '*'   1.0E-05
         'femtometres'              'picometres'               '*'   1.0E-03
    ###
         'reciprocal_centimetres'   'reciprocal_metres'        '*'   1.0E+02
         'reciprocal_centimetres'   'reciprocal_millimetres'   '*'   1.0E-01
         'reciprocal_centimetres'   'reciprocal_nanometres'    '*'   1.0E-07
         'reciprocal_centimetres'   'reciprocal_angstroms'     '*'   1.0E-08
         'reciprocal_centimetres'   'reciprocal_picometres'    '*'   1.0E-10
    #
         'reciprocal_millimetres'   'reciprocal_metres'        '*'   1.0E+03
         'reciprocal_millimetres'   'reciprocal_centimetres'   '*'   1.0E+01
         'reciprocal_millimetres'   'reciprocal_nanometres'    '*'   1.0E-06
         'reciprocal_millimetres'   'reciprocal_angstroms'     '*'   1.0E-07
         'reciprocal_millimetres'   'reciprocal_picometres'    '*'   1.0E-09
    #
         'reciprocal_nanometres'    'reciprocal_metres'        '*'   1.0E+09
         'reciprocal_nanometres'    'reciprocal_centimetres'   '*'   1.0E+07
         'reciprocal_nanometres'    'reciprocal_millimetres'   '*'   1.0E+06
         'reciprocal_nanometres'    'reciprocal_angstroms'     '*'   1.0E-01
         'reciprocal_nanometres'    'reciprocal_picometres'    '*'   1.0E-03
    #
         'reciprocal_angstroms'     'reciprocal_metres'        '*'   1.0E+10
         'reciprocal_angstroms'     'reciprocal_centimetres'   '*'   1.0E+08
         'reciprocal_angstroms'     'reciprocal_millimetres'   '*'   1.0E+07
         'reciprocal_angstroms'     'reciprocal_nanometres'    '*'   1.0E+01
         'reciprocal_angstroms'     'reciprocal_picometres'    '*'   1.0E-02
    #
         'reciprocal_picometres'    'reciprocal_metres'        '*'   1.0E+12
         'reciprocal_picometres'    'reciprocal_centimetres'   '*'   1.0E+10
         'reciprocal_picometres'    'reciprocal_millimetres'   '*'   1.0E+09
         'reciprocal_picometres'    'reciprocal_nanometres'    '*'   1.0E+03
         'reciprocal_picometres'    'reciprocal_angstroms'     '*'   1.0E+01
    ###
         'nanometres_squared'       'angstroms_squared'        '*'   1.0E+02
         'nanometres_squared'       'picometres_squared'       '*'   1.0E+06
    #
         'angstroms_squared'        'nanometres_squared'       '*'   1.0E-02
         'angstroms_squared'        'picometres_squared'       '*'   1.0E+04
         'angstroms_squared'        '8pi2_angstroms_squared'   '*'   78.9568
    
    #
         'picometres_squared'       'nanometres_squared'       '*'   1.0E-06
         'picometres_squared'       'angstroms_squared'        '*'   1.0E-04
    ###
         'nanometres_cubed'         'angstroms_cubed'          '*'   1.0E+03
         'nanometres_cubed'         'picometres_cubed'         '*'   1.0E+09
    #
         'angstroms_cubed'          'nanometres_cubed'         '*'   1.0E-03
         'angstroms_cubed'          'picometres_cubed'         '*'   1.0E+06
    #
         'picometres_cubed'         'nanometres_cubed'         '*'   1.0E-09
         'picometres_cubed'         'angstroms_cubed'          '*'   1.0E-06
    ###
         'kilopascals'              'gigapascals'              '*'   1.0E-06
         'gigapascals'              'kilopascals'              '*'   1.0E+06
    ###
         'hours'                    'minutes'                  '*'   6.0E+01
         'hours'                    'seconds'                  '*'   3.6E+03
         'hours'                    'microseconds'             '*'   3.6E+09
    #
         'minutes'                  'hours'                    '/'   6.0E+01
         'minutes'                  'seconds'                  '*'   6.0E+01
         'minutes'                  'microseconds'             '*'   6.0E+07
    #
         'seconds'                  'hours'                    '/'   3.6E+03
         'seconds'                  'minutes'                  '/'   6.0E+01
         'seconds'                  'microseconds'             '*'   1.0E+06
    #
         'microseconds'             'hours'                    '/'   3.6E+09
         'microseconds'             'minutes'                  '/'   6.0E+07
         'microseconds'             'seconds'                  '/'   1.0E+06
    ###
         'celsius'                  'kelvins'                  '-'     273.0
         'kelvins'                  'celsius'                  '+'     273.0
    ###
         'electrons_per_nanometres_cubed'
         'electrons_per_angstroms_cubed'                       '*'   1.0E+03
         'electrons_per_nanometres_cubed'
         'electrons_per_picometres_cubed'                      '*'   1.0E+09
    #
         'electrons_per_angstroms_cubed'
         'electrons_per_nanometres_cubed'                      '*'   1.0E-03
         'electrons_per_angstroms_cubed'
         'electrons_per_picometres_cubed'                      '*'   1.0E+06
    #
         'electrons_per_picometres_cubed'
         'electrons_per_nanometres_cubed'                      '*'   1.0E-09
         'electrons_per_picometres_cubed'
         'electrons_per_angstroms_cubed'                       '*'   1.0E-06
    ###
     
     
    ########################
    ## DICTIONARY_HISTORY ##
    ########################
    
         loop_
        _dictionary_history.version
        _dictionary_history.update
        _dictionary_history.revision
    
       1.3.0   2003-07-24
    ;
       Changes as per Brian McMahon. 
       +  Consistently quote tags embedded in text.
       +  Clean up introductory comments.
       +  Adjust line lengths to fit in 80 character window
       +  Fix several descriptions in AXIS category which
       referred to '_axis.type' instead of the current item.
       +  Fix erroneous use of deprecated item
       '_diffrn_detector_axis.id' in examples for 
       DIFFRN_SCAN_AXIS.
       +  Add deprecated items '_diffrn_detector_axis.id'
       and '_diffrn_measurement_axis.id'
       (HJB)
    ;
    
       1.2.4   2003-07-14
    ;
       Changes as per I. David Brown. 
       +  Enhance descriptions in DIFFRN_SCAN_AXIS to make them less
       dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS.
       +  Provide a copy of the deprecated DIFFRN_FRAME_DATA
       category for completeness.
       (HJB)
    ;
    
       1.2.3   2003-07-03
    ;
       Cleanup to conform to ITVG. 
       +  Correct sign error in ..._cubed units.
       +  Correct '_diffrn_radiation.polarisn_norm' range.
       (HJB)
    ;
    
       1.2.2   2003-03-10
    ;
       Correction of  typos in various DIFFRN_SCAN_AXIS descriptions. 
       (HJB)
    ;
    
       1.2.1   2003-02-22
    ;
       Correction of ATOM_ for ARRAY_ typos in various descriptions. 
       (HJB)
    ;
    
    
       1.2     2003-02-07
    ;
       Corrections to encodings (remove extraneous hyphens) remove
       extraneous underscore in '_array_structure.encoding_type'
       enumeration.  Correct typos in items units list. 
       (HJB)
    ;
    
    
       1.1.3   2001-04-19
    ;
       Another typo corrections by Wilfred Li, and cleanup by HJB
    ;
    
       1.1.2   2001-03-06
    ;
       Several typo corrections by Wilfred Li
    ;
    
    
       1.1.1   2001-02-16
    ;
       Several typo corrections by JW
    ;
    
    
       1.1     2001-02-06
    ;
       Draft resulting from discussions on header for use at NSLS (HJB)
       
       + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME
       
       + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'.
       
       + Add '_diffrn_measurement_axis.measurement_device' and change
       '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'.
       
       + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source',
       '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm',
       '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end',
       '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr',
       '_diffrn_scan_axis.displacement_rstrt_incr', 
       '_diffrn_scan_frame_axis.angle_increment',
       '_diffrn_scan_frame_axis.angle_rstrt_incr',
       '_diffrn_scan_frame_axis.displacement',
       '_diffrn_scan_frame_axis.displacement_increment',and
       '_diffrn_scan_frame_axis.displacement_rstrt_incr'.
       
       + Add '_diffrn_measurement.device' to category key
       
       + Update yyyy-mm-dd to allow optional time with fractional seconds
       for time stamps.
    
       + Fix typos caught by RS.
       
       + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to
       allow for coupled axes, as in spiral scans.
    
       + Add examples for fairly complete headers thanks to R. Sweet and P. 
       Ellis.
    ;
    
    
       1.0     2000-12-21
    ;
       Release version - few typos and tidying up (BM & HJB)
       
       + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end
       of dictionary.
       
       + Alphabetize dictionary.
    ;
    
       0.7.1   2000-09-29
    ;
       Cleanup fixes (JW)
    
       + Correct spelling of diffrn_measurement_axis in '_axis.id'
    
       + Correct ordering of uses of '_item.mandatory_code' and
       '_item_default.value'.
    ;
    
       0.7.0   2000-09-09
    ;
       Respond to comments by I. David Brown (HJB)
    
       + Added further comments on '\n' and '\t'
    
       + Updated ITEM_UNITS_LIST by taking section from mmCIF dictionary
     and adding metres.  Changed all spelling 'meter' to 'metre' throughout.
    
       + Added missing enumerations to '_array_structure.compression_type'
     and made 'none' the default.
    
       + Removed parent-child relationship between
       '_array_structure_list.index' and '_array_structure_list.precedence'.
    
       + Improve alphabetization.
    
       + Fix '_array_intensities_gain.esd' related function.
    
       + Improved comments in AXIS.
    
       + Fixed DIFFRN_FRAME_DATA example.
    
       + Removed erroneous DIFFRN_MEASUREMENT example.
    
       + Added '_diffrn_measurement_axis.id' to the category key.
    ;
    
       0.6.0   1999-01-14
    ;
       Remove redundant information for ENC_NONE data (HJB)
    
       + After the D5 remove binary section identifier, size and
     compression type.
    
       + Add Control-L to header.
    ;
       0.5.1   1999-01-03
    ;
       Cleanup of typos and syntax errors (HJB)
    
       + Cleanup example details for DIFFRN_SCAN category.
    
       + Add missing quote marks for '_diffrn_scan.id' definition.
    ;
    
       0.5   1999-01-01
    ;
       Modifications for axis definitions and reduction of binary header (HJB)
    
       + Restored '_diffrn_detector.diffrn_id' to DIFFRN_DETECTOR KEY.
    
       + Added AXIS category.
    
       + Brought complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories
     in from cif_mm.dic for clarity.
    
       + changed '_array_structure.encoding_type' from type code to uline and
     added X-Binary-Element-Type to MIME header.
    
       + added detector beam center '_diffrn_detector_element.center[1]' and 
    '_diffrn_detector_element.center[2]'.
    
       + corrected item name of '_diffrn_refln.frame_id'.
    
       + replace reference to '_array_intensities.undefined' by
     '_array_intensities.undefined_value'.
    
       + replace references to '_array_intensity.scaling' with
     '_array_intensities.scaling'.
    
       + added DIFFRN_SCAN... categories
    ;
    
       0.4   1998-08-11
    ;
       Modifications to the 0.3 imgCIF draft (HJB)
    
       +  Reflowed comment lines over 80 characters and corrected typos.
    
       +  Updated examples and descriptions of MIME encoded data.
    
       +  Change name to cbfext98.dic.
    ;
    
       0.3   1998-07-04
    ;
       Modifications for imgCIF (HJB)
    
       +  Added binary type, which is a text field containing a variant on
          MIME encoded data.
          
       +  Changed type of '_array_data.data' to binary and specified internal
          structure of raw binary data.
          
       +  Added '_array_data.binary_id', and made 
          '_diffrn_frame_data.binary_id' and '_array_intensities.binary_id'
          into pointers to this item.
    ;
    
       0.2   1997-12-02
    ;
       Modifications to the CBF draft (JW):  
    
       +  Added category hierarchy for describing frame data developed from
          discussions at the BNL imgCIF Workshop Oct 1997.   The following
          changes were made in implementing the workshop draft.  Category
          DIFFRN_ARRAY_DATA was renamed to DIFFRN_FRAME_DATA.  Category
          DIFFRN_FRAME_TYPE was renamed to DIFFRN_DETECTOR_ELEMENT.   The
          parent item for '_diffrn_frame_data.array_id' was changed from
          '_array_structure_list.array_id' to '_array_structure.id'. Item 
          '_diffrn_detector.array_id' was deleted.  
       +  Added data item '_diffrn_frame_data.binary_id' to identify data 
          groups within a binary section.  The formal identification of the
          binary section is still fuzzy.  
    ;
    
       0.1   1997-01-24
    ;
       First draft of this dictionary in DDL 2.1 compliant format by John 
       Westbrook (JW).  This version was adapted from the Crystallographic 
       Binary File (CBF) Format Draft Proposal provided by Andy Hammersley
       (AH).  
     
       Modifications to the CBF draft (JW):  
     
       + In this version the array description has been cast in the categories 
         ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST.  These categories
         have been generalized to describe array data  of arbitrary dimension.  
    
       + Array data in this description are contained in the category
         ARRAY_DATA.  This departs from the CBF notion of data existing
         in some special comment. In this description, data is handled as an 
         ordinary data item encapsulated in a character data type.   Although
         data this manner deviates from CIF conventions, it does not violate 
         any DDL 2.1 rules.  DDL 2.1 regular expressions can be used to define 
         the binary representation which will permit some level of data 
         validation.  In this version, the placeholder type code "any" has
         been used. This translates to a regular expression which will match 
         any pattern.
    
         It should be noted that DDL 2.1 already supports array data objects 
         although these have not been used in the current mmCIF dictionary.
         It may be possible to use the DDL 2.1 ITEM_STRUCTURE and
         ITEM_STRUCTURE_LIST categories to provide the information that is
         carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST.  By
         moving the array structure to the DDL level it would be possible to
         define an array type as well as a regular expression defining the
         data format. 
    
       + Multiple array sections can be properly handled within a single
         datablock.
    ;
     
     
    #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof
    
    ./CBFlib-0.9.2.2/doc/Idiffrn_scan_frame_axis.displacement_rstrt_incr.html0000644000076500007650000000653611603702115024746 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan_frame_axis.displacement_rstrt_incr

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_scan_frame_axis.displacement_rstrt_incr

    Name:
    '_diffrn_scan_frame_axis.displacement_rstrt_incr'

    Definition:

            The increment for this frame for the displacement setting of
                   the specified axis in millimetres.  The sum of the values
                   of _diffrn_scan_frame_axis.displacement,
                   _diffrn_scan_frame_axis.displacement_increment and
                   _diffrn_scan_frame_axis.displacement_rstrt_incr is the
                   angular setting of the axis at the start of the integration
                   time for the next frame and should equal
                   _diffrn_scan_frame_axis.displacement for this next frame.
    
    

    Type: float

    Mandatory item: no


    Enumeration default: 0.0

    Category: diffrn_scan_frame_axis

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_scan_axis.displacement_rstrt_incr.html0000644000076500007650000000774311603702115023575 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan_axis.displacement_rstrt_incr

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_scan_axis.displacement_rstrt_incr

    Name:
    '_diffrn_scan_axis.displacement_rstrt_incr'

    Definition:

            The increment for each step for the specified axis
                   in millimetres.  In general, this will agree with
                   _diffrn_scan_frame_axis.displacement_rstrt_incr.
                   The sum of the values of
                   _diffrn_scan_frame_axis.displacement,
                   _diffrn_scan_frame_axis.displacement_increment and
                   _diffrn_scan_frame_axis.displacement_rstrt_incr is the
                   angular setting of the axis at the start of the integration
                   time for the next frame relative to a given frame and
                   should equal _diffrn_scan_frame_axis.displacement
                   for this next frame.  If the individual frame values
                   vary, then the value of
                   _diffrn_scan_axis.displacement_rstrt_incr will be
                   representative
                   of the ensemble of values of
                   _diffrn_scan_frame_axis.displacement_rstrt_incr (e.g.
                   the mean).
    
    

    Type: float

    Mandatory item: no


    Enumeration default: 0.0

    Category: diffrn_scan_axis

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_scan_axis.angle_rstrt_incr.html0000644000076500007650000000753611603702115022213 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan_axis.angle_rstrt_incr

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_scan_axis.angle_rstrt_incr

    Name:
    '_diffrn_scan_axis.angle_rstrt_incr'

    Definition:

            The increment after each step for the specified axis
                   in degrees.  In general, this will agree with
                   _diffrn_scan_frame_axis.angle_rstrt_incr.  The
                   sum of the values of _diffrn_scan_frame_axis.angle,
                   _diffrn_scan_frame_axis.angle_increment
                   and  _diffrn_scan_frame_axis.angle_rstrt_incr is the
                   angular setting of the axis at the start of the integration
                   time for the next frame relative to a given frame and
                   should equal _diffrn_scan_frame_axis.angle for this
                   next frame.   If the individual frame values
                   vary, then the value of
                   _diffrn_scan_axis.angle_rstrt_incr will be
                   representative
                   of the ensemble of values of
                   _diffrn_scan_frame_axis.angle_rstrt_incr (e.g.
                   the mean).
    
    

    Type: float

    Mandatory item: no


    Enumeration default: 0.0

    Category: diffrn_scan_axis

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Cdiffrn_detector_element.html0000644000076500007650000001070611603702115020212 0ustar yayayaya (IUCr) CIF Definition save_diffrn_detector_element

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    Category DIFFRN_DETECTOR_ELEMENT

    Name:
    'diffrn_detector_element'

    Description:

           Data items in the DIFFRN_DETECTOR_ELEMENT category record
                  the details about spatial layout and other characteristics
                  of each element of a detector which may have multiple elements.
    
                  In most cases, giving more detailed information
                  in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS
                  is preferable to simply providing the centre of the
                  detector element.
    
    
    Example:

    Example 1 - Detector d1 is composed of four CCD detector elements, each 200 mm by 200 mm, arranged in a square, in the pattern 1 2 * 3 4 Note that the beam centre is slightly displaced from each of the detector elements, just beyond the lower right corner of 1, the lower left corner of 2, the upper right corner of 3 and the upper left corner of 4. For each element, the detector face coordiate system, is assumed to have the fast axis running from left to right and the slow axis running from top to bottom with the origin at the top left corner.
     
            loop_
            _diffrn_detector_element.detector_id
            _diffrn_detector_element.id
            _diffrn_detector_element.reference_center_fast
            _diffrn_detector_element.reference_center_slow
            _diffrn_detector_element.reference_center_units
            d1     d1_ccd_1  201.5 201.5  mm
            d1     d1_ccd_2  -1.8  201.5  mm
            d1     d1_ccd_3  201.6  -1.4  mm
            d1     d1_ccd_4  -1.7   -1.5  mm
    
    


    Category groups:
        inclusive_group
        array_data_group
    Category keys:
        _diffrn_detector_element.id
        _diffrn_detector_element.detector_id

    Mandatory category: no

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_scan_frame_axis.reference_displacement.html0000644000076500007650000000601311603702115024501 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan_frame_axis.reference_displacement

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_scan_frame_axis.reference_displacement

    Name:
    '_diffrn_scan_frame_axis.reference_displacement'

    Definition:

            The setting of the specified axis in millimetres for this
                   frame against which measurements of the reference beam center
                   and reference detector distance should be made.
    
                   This is normally the same for all frames, but the
                   option is provided here of making changes when
                   needed.
    
                   If not provided, it is assumed to be equal to
                   _diffrn_scan_frame_axis.displacement.
    
    

    Type: float

    Mandatory item: implicit

    Category: diffrn_scan_frame_axis

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Cdiffrn_detector.html0000644000076500007650000000634111603702115016501 0ustar yayayaya (IUCr) CIF Definition save_diffrn_detector

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    Category DIFFRN_DETECTOR

    Name:
    'diffrn_detector'

    Description:

            Data items in the DIFFRN_DETECTOR category describe the
                   detector used to measure the scattered radiation, including
                   any analyser and post-sample collimation.
    
    
    Example:

    Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP.
     
        _diffrn_detector.diffrn_id             'd1'
        _diffrn_detector.detector              'multiwire'
        _diffrn_detector.type                  'Siemens'
    
    


    Category groups:
        inclusive_group
        diffrn_group
    Category keys:
        _diffrn_detector.diffrn_id
        _diffrn_detector.id

    Mandatory category: no

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_scan_frame_axis.angle_increment.html0000644000076500007650000000574511603702115023160 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan_frame_axis.angle_increment

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_scan_frame_axis.angle_increment

    Name:
    '_diffrn_scan_frame_axis.angle_increment'

    Definition:

            The increment for this frame for the angular setting of
                   the specified axis in degrees.  The sum of the values
                   of _diffrn_scan_frame_axis.angle and
                   _diffrn_scan_frame_axis.angle_increment is the
                   angular setting of the axis at the end of the integration
                   time for this frame.
    
    

    Type: float

    Mandatory item: no


    Enumeration default: 0.0

    Category: diffrn_scan_frame_axis

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Iaxis.system.html0000644000076500007650000000716511603702115015642 0ustar yayayaya (IUCr) CIF Definition save__axis.system

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _axis.system

    Name:
    '_axis.system'

    Definition:

           The value of  _axis.system specifies the coordinate
                  system used to define the axis: 'laboratory', 'direct', 
                  'orthogonal', 'reciprocal' or 'abstract'.
    
    

    Type: ucode

    Mandatory item: no


    The data value must be one of the following:


    laboratory
    the axis is referenced to the imgCIF standard laboratory Cartesian coordinate system

    direct
    the axis is referenced to the direct lattice

    orthogonal
    the axis is referenced to the cell Cartesian orthogonal coordinates

    reciprocal
    the axis is referenced to the reciprocal lattice

    abstract
    the axis is referenced to abstract Cartesian cooridinate system

    Enumeration default: laboratory

    Category: axis

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/lgpl.txt0000644000076500007650000006350011603702115014046 0ustar yayayaya GNU LESSER GENERAL PUBLIC LICENSE Version 2.1, February 1999 Copyright (C) 1991, 1999 Free Software Foundation, Inc. 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA Everyone is permitted to copy and distribute verbatim copies of this license document, but changing it is not allowed. [This is the first released version of the Lesser GPL. It also counts as the successor of the GNU Library Public License, version 2, hence the version number 2.1.] Preamble The licenses for most software are designed to take away your freedom to share and change it. By contrast, the GNU General Public Licenses are intended to guarantee your freedom to share and change free software--to make sure the software is free for all its users. This license, the Lesser General Public License, applies to some specially designated software packages--typically libraries--of the Free Software Foundation and other authors who decide to use it. You can use it too, but we suggest you first think carefully about whether this license or the ordinary General Public License is the better strategy to use in any particular case, based on the explanations below. When we speak of free software, we are referring to freedom of use, not price. Our General Public Licenses are designed to make sure that you have the freedom to distribute copies of free software (and charge for this service if you wish); that you receive source code or can get it if you want it; that you can change the software and use pieces of it in new free programs; and that you are informed that you can do these things. To protect your rights, we need to make restrictions that forbid distributors to deny you these rights or to ask you to surrender these rights. These restrictions translate to certain responsibilities for you if you distribute copies of the library or if you modify it. For example, if you distribute copies of the library, whether gratis or for a fee, you must give the recipients all the rights that we gave you. You must make sure that they, too, receive or can get the source code. If you link other code with the library, you must provide complete object files to the recipients, so that they can relink them with the library after making changes to the library and recompiling it. And you must show them these terms so they know their rights. We protect your rights with a two-step method: (1) we copyright the library, and (2) we offer you this license, which gives you legal permission to copy, distribute and/or modify the library. To protect each distributor, we want to make it very clear that there is no warranty for the free library. Also, if the library is modified by someone else and passed on, the recipients should know that what they have is not the original version, so that the original author's reputation will not be affected by problems that might be introduced by others. Finally, software patents pose a constant threat to the existence of any free program. We wish to make sure that a company cannot effectively restrict the users of a free program by obtaining a restrictive license from a patent holder. Therefore, we insist that any patent license obtained for a version of the library must be consistent with the full freedom of use specified in this license. Most GNU software, including some libraries, is covered by the ordinary GNU General Public License. This license, the GNU Lesser General Public License, applies to certain designated libraries, and is quite different from the ordinary General Public License. We use this license for certain libraries in order to permit linking those libraries into non-free programs. When a program is linked with a library, whether statically or using a shared library, the combination of the two is legally speaking a combined work, a derivative of the original library. The ordinary General Public License therefore permits such linking only if the entire combination fits its criteria of freedom. The Lesser General Public License permits more lax criteria for linking other code with the library. We call this license the "Lesser" General Public License because it does Less to protect the user's freedom than the ordinary General Public License. It also provides other free software developers Less of an advantage over competing non-free programs. These disadvantages are the reason we use the ordinary General Public License for many libraries. However, the Lesser license provides advantages in certain special circumstances. For example, on rare occasions, there may be a special need to encourage the widest possible use of a certain library, so that it becomes a de-facto standard. To achieve this, non-free programs must be allowed to use the library. A more frequent case is that a free library does the same job as widely used non-free libraries. In this case, there is little to gain by limiting the free library to free software only, so we use the Lesser General Public License. In other cases, permission to use a particular library in non-free programs enables a greater number of people to use a large body of free software. For example, permission to use the GNU C Library in non-free programs enables many more people to use the whole GNU operating system, as well as its variant, the GNU/Linux operating system. Although the Lesser General Public License is Less protective of the users' freedom, it does ensure that the user of a program that is linked with the Library has the freedom and the wherewithal to run that program using a modified version of the Library. The precise terms and conditions for copying, distribution and modification follow. Pay close attention to the difference between a "work based on the library" and a "work that uses the library". The former contains code derived from the library, whereas the latter must be combined with the library in order to run. GNU LESSER GENERAL PUBLIC LICENSE TERMS AND CONDITIONS FOR COPYING, DISTRIBUTION AND MODIFICATION 0. This License Agreement applies to any software library or other program which contains a notice placed by the copyright holder or other authorized party saying it may be distributed under the terms of this Lesser General Public License (also called "this License"). Each licensee is addressed as "you". A "library" means a collection of software functions and/or data prepared so as to be conveniently linked with application programs (which use some of those functions and data) to form executables. The "Library", below, refers to any such software library or work which has been distributed under these terms. A "work based on the Library" means either the Library or any derivative work under copyright law: that is to say, a work containing the Library or a portion of it, either verbatim or with modifications and/or translated straightforwardly into another language. (Hereinafter, translation is included without limitation in the term "modification".) "Source code" for a work means the preferred form of the work for making modifications to it. For a library, complete source code means all the source code for all modules it contains, plus any associated interface definition files, plus the scripts used to control compilation and installation of the library. Activities other than copying, distribution and modification are not covered by this License; they are outside its scope. The act of running a program using the Library is not restricted, and output from such a program is covered only if its contents constitute a work based on the Library (independent of the use of the Library in a tool for writing it). Whether that is true depends on what the Library does and what the program that uses the Library does. 1. You may copy and distribute verbatim copies of the Library's complete source code as you receive it, in any medium, provided that you conspicuously and appropriately publish on each copy an appropriate copyright notice and disclaimer of warranty; keep intact all the notices that refer to this License and to the absence of any warranty; and distribute a copy of this License along with the Library. You may charge a fee for the physical act of transferring a copy, and you may at your option offer warranty protection in exchange for a fee. 2. You may modify your copy or copies of the Library or any portion of it, thus forming a work based on the Library, and copy and distribute such modifications or work under the terms of Section 1 above, provided that you also meet all of these conditions: a) The modified work must itself be a software library. b) You must cause the files modified to carry prominent notices stating that you changed the files and the date of any change. c) You must cause the whole of the work to be licensed at no charge to all third parties under the terms of this License. d) If a facility in the modified Library refers to a function or a table of data to be supplied by an application program that uses the facility, other than as an argument passed when the facility is invoked, then you must make a good faith effort to ensure that, in the event an application does not supply such function or table, the facility still operates, and performs whatever part of its purpose remains meaningful. (For example, a function in a library to compute square roots has a purpose that is entirely well-defined independent of the application. Therefore, Subsection 2d requires that any application-supplied function or table used by this function must be optional: if the application does not supply it, the square root function must still compute square roots.) These requirements apply to the modified work as a whole. If identifiable sections of that work are not derived from the Library, and can be reasonably considered independent and separate works in themselves, then this License, and its terms, do not apply to those sections when you distribute them as separate works. But when you distribute the same sections as part of a whole which is a work based on the Library, the distribution of the whole must be on the terms of this License, whose permissions for other licensees extend to the entire whole, and thus to each and every part regardless of who wrote it. Thus, it is not the intent of this section to claim rights or contest your rights to work written entirely by you; rather, the intent is to exercise the right to control the distribution of derivative or collective works based on the Library. In addition, mere aggregation of another work not based on the Library with the Library (or with a work based on the Library) on a volume of a storage or distribution medium does not bring the other work under the scope of this License. 3. You may opt to apply the terms of the ordinary GNU General Public License instead of this License to a given copy of the Library. To do this, you must alter all the notices that refer to this License, so that they refer to the ordinary GNU General Public License, version 2, instead of to this License. (If a newer version than version 2 of the ordinary GNU General Public License has appeared, then you can specify that version instead if you wish.) Do not make any other change in these notices. Once this change is made in a given copy, it is irreversible for that copy, so the ordinary GNU General Public License applies to all subsequent copies and derivative works made from that copy. This option is useful when you wish to copy part of the code of the Library into a program that is not a library. 4. You may copy and distribute the Library (or a portion or derivative of it, under Section 2) in object code or executable form under the terms of Sections 1 and 2 above provided that you accompany it with the complete corresponding machine-readable source code, which must be distributed under the terms of Sections 1 and 2 above on a medium customarily used for software interchange. If distribution of object code is made by offering access to copy from a designated place, then offering equivalent access to copy the source code from the same place satisfies the requirement to distribute the source code, even though third parties are not compelled to copy the source along with the object code. 5. A program that contains no derivative of any portion of the Library, but is designed to work with the Library by being compiled or linked with it, is called a "work that uses the Library". Such a work, in isolation, is not a derivative work of the Library, and therefore falls outside the scope of this License. However, linking a "work that uses the Library" with the Library creates an executable that is a derivative of the Library (because it contains portions of the Library), rather than a "work that uses the library". The executable is therefore covered by this License. Section 6 states terms for distribution of such executables. When a "work that uses the Library" uses material from a header file that is part of the Library, the object code for the work may be a derivative work of the Library even though the source code is not. Whether this is true is especially significant if the work can be linked without the Library, or if the work is itself a library. The threshold for this to be true is not precisely defined by law. If such an object file uses only numerical parameters, data structure layouts and accessors, and small macros and small inline functions (ten lines or less in length), then the use of the object file is unrestricted, regardless of whether it is legally a derivative work. (Executables containing this object code plus portions of the Library will still fall under Section 6.) Otherwise, if the work is a derivative of the Library, you may distribute the object code for the work under the terms of Section 6. Any executables containing that work also fall under Section 6, whether or not they are linked directly with the Library itself. 6. As an exception to the Sections above, you may also combine or link a "work that uses the Library" with the Library to produce a work containing portions of the Library, and distribute that work under terms of your choice, provided that the terms permit modification of the work for the customer's own use and reverse engineering for debugging such modifications. You must give prominent notice with each copy of the work that the Library is used in it and that the Library and its use are covered by this License. You must supply a copy of this License. If the work during execution displays copyright notices, you must include the copyright notice for the Library among them, as well as a reference directing the user to the copy of this License. Also, you must do one of these things: a) Accompany the work with the complete corresponding machine-readable source code for the Library including whatever changes were used in the work (which must be distributed under Sections 1 and 2 above); and, if the work is an executable linked with the Library, with the complete machine-readable "work that uses the Library", as object code and/or source code, so that the user can modify the Library and then relink to produce a modified executable containing the modified Library. (It is understood that the user who changes the contents of definitions files in the Library will not necessarily be able to recompile the application to use the modified definitions.) b) Use a suitable shared library mechanism for linking with the Library. A suitable mechanism is one that (1) uses at run time a copy of the library already present on the user's computer system, rather than copying library functions into the executable, and (2) will operate properly with a modified version of the library, if the user installs one, as long as the modified version is interface-compatible with the version that the work was made with. c) Accompany the work with a written offer, valid for at least three years, to give the same user the materials specified in Subsection 6a, above, for a charge no more than the cost of performing this distribution. d) If distribution of the work is made by offering access to copy from a designated place, offer equivalent access to copy the above specified materials from the same place. e) Verify that the user has already received a copy of these materials or that you have already sent this user a copy. For an executable, the required form of the "work that uses the Library" must include any data and utility programs needed for reproducing the executable from it. However, as a special exception, the materials to be distributed need not include anything that is normally distributed (in either source or binary form) with the major components (compiler, kernel, and so on) of the operating system on which the executable runs, unless that component itself accompanies the executable. It may happen that this requirement contradicts the license restrictions of other proprietary libraries that do not normally accompany the operating system. Such a contradiction means you cannot use both them and the Library together in an executable that you distribute. 7. You may place library facilities that are a work based on the Library side-by-side in a single library together with other library facilities not covered by this License, and distribute such a combined library, provided that the separate distribution of the work based on the Library and of the other library facilities is otherwise permitted, and provided that you do these two things: a) Accompany the combined library with a copy of the same work based on the Library, uncombined with any other library facilities. This must be distributed under the terms of the Sections above. b) Give prominent notice with the combined library of the fact that part of it is a work based on the Library, and explaining where to find the accompanying uncombined form of the same work. 8. You may not copy, modify, sublicense, link with, or distribute the Library except as expressly provided under this License. Any attempt otherwise to copy, modify, sublicense, link with, or distribute the Library is void, and will automatically terminate your rights under this License. However, parties who have received copies, or rights, from you under this License will not have their licenses terminated so long as such parties remain in full compliance. 9. You are not required to accept this License, since you have not signed it. However, nothing else grants you permission to modify or distribute the Library or its derivative works. These actions are prohibited by law if you do not accept this License. Therefore, by modifying or distributing the Library (or any work based on the Library), you indicate your acceptance of this License to do so, and all its terms and conditions for copying, distributing or modifying the Library or works based on it. 10. Each time you redistribute the Library (or any work based on the Library), the recipient automatically receives a license from the original licensor to copy, distribute, link with or modify the Library subject to these terms and conditions. You may not impose any further restrictions on the recipients' exercise of the rights granted herein. You are not responsible for enforcing compliance by third parties with this License. 11. If, as a consequence of a court judgment or allegation of patent infringement or for any other reason (not limited to patent issues), conditions are imposed on you (whether by court order, agreement or otherwise) that contradict the conditions of this License, they do not excuse you from the conditions of this License. If you cannot distribute so as to satisfy simultaneously your obligations under this License and any other pertinent obligations, then as a consequence you may not distribute the Library at all. For example, if a patent license would not permit royalty-free redistribution of the Library by all those who receive copies directly or indirectly through you, then the only way you could satisfy both it and this License would be to refrain entirely from distribution of the Library. If any portion of this section is held invalid or unenforceable under any particular circumstance, the balance of the section is intended to apply, and the section as a whole is intended to apply in other circumstances. It is not the purpose of this section to induce you to infringe any patents or other property right claims or to contest validity of any such claims; this section has the sole purpose of protecting the integrity of the free software distribution system which is implemented by public license practices. Many people have made generous contributions to the wide range of software distributed through that system in reliance on consistent application of that system; it is up to the author/donor to decide if he or she is willing to distribute software through any other system and a licensee cannot impose that choice. This section is intended to make thoroughly clear what is believed to be a consequence of the rest of this License. 12. If the distribution and/or use of the Library is restricted in certain countries either by patents or by copyrighted interfaces, the original copyright holder who places the Library under this License may add an explicit geographical distribution limitation excluding those countries, so that distribution is permitted only in or among countries not thus excluded. In such case, this License incorporates the limitation as if written in the body of this License. 13. The Free Software Foundation may publish revised and/or new versions of the Lesser General Public License from time to time. Such new versions will be similar in spirit to the present version, but may differ in detail to address new problems or concerns. Each version is given a distinguishing version number. If the Library specifies a version number of this License which applies to it and "any later version", you have the option of following the terms and conditions either of that version or of any later version published by the Free Software Foundation. If the Library does not specify a license version number, you may choose any version ever published by the Free Software Foundation. 14. If you wish to incorporate parts of the Library into other free programs whose distribution conditions are incompatible with these, write to the author to ask for permission. For software which is copyrighted by the Free Software Foundation, write to the Free Software Foundation; we sometimes make exceptions for this. Our decision will be guided by the two goals of preserving the free status of all derivatives of our free software and of promoting the sharing and reuse of software generally. NO WARRANTY 15. BECAUSE THE LIBRARY IS LICENSED FREE OF CHARGE, THERE IS NO WARRANTY FOR THE LIBRARY, TO THE EXTENT PERMITTED BY APPLICABLE LAW. EXCEPT WHEN OTHERWISE STATED IN WRITING THE COPYRIGHT HOLDERS AND/OR OTHER PARTIES PROVIDE THE LIBRARY "AS IS" WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESSED OR IMPLIED, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE. THE ENTIRE RISK AS TO THE QUALITY AND PERFORMANCE OF THE LIBRARY IS WITH YOU. SHOULD THE LIBRARY PROVE DEFECTIVE, YOU ASSUME THE COST OF ALL NECESSARY SERVICING, REPAIR OR CORRECTION. 16. IN NO EVENT UNLESS REQUIRED BY APPLICABLE LAW OR AGREED TO IN WRITING WILL ANY COPYRIGHT HOLDER, OR ANY OTHER PARTY WHO MAY MODIFY AND/OR REDISTRIBUTE THE LIBRARY AS PERMITTED ABOVE, BE LIABLE TO YOU FOR DAMAGES, INCLUDING ANY GENERAL, SPECIAL, INCIDENTAL OR CONSEQUENTIAL DAMAGES ARISING OUT OF THE USE OR INABILITY TO USE THE LIBRARY (INCLUDING BUT NOT LIMITED TO LOSS OF DATA OR DATA BEING RENDERED INACCURATE OR LOSSES SUSTAINED BY YOU OR THIRD PARTIES OR A FAILURE OF THE LIBRARY TO OPERATE WITH ANY OTHER SOFTWARE), EVEN IF SUCH HOLDER OR OTHER PARTY HAS BEEN ADVISED OF THE POSSIBILITY OF SUCH DAMAGES. END OF TERMS AND CONDITIONS How to Apply These Terms to Your New Libraries If you develop a new library, and you want it to be of the greatest possible use to the public, we recommend making it free software that everyone can redistribute and change. You can do so by permitting redistribution under these terms (or, alternatively, under the terms of the ordinary General Public License). To apply these terms, attach the following notices to the library. It is safest to attach them to the start of each source file to most effectively convey the exclusion of warranty; and each file should have at least the "copyright" line and a pointer to where the full notice is found. Copyright (C) This library is free software; you can redistribute it and/or modify it under the terms of the GNU Lesser General Public License as published by the Free Software Foundation; either version 2.1 of the License, or (at your option) any later version. This library is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public License for more details. You should have received a copy of the GNU Lesser General Public License along with this library; if not, write to the Free Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, MA 02110-1301 USA Also add information on how to contact you by electronic and paper mail. You should also get your employer (if you work as a programmer) or your school, if any, to sign a "copyright disclaimer" for the library, if necessary. Here is a sample; alter the names: Yoyodyne, Inc., hereby disclaims all copyright interest in the library `Frob' (a library for tweaking knobs) written by James Random Hacker. , 1 April 1990 Ty Coon, President of Vice That's all there is to it! ./CBFlib-0.9.2.2/doc/Idiffrn_scan_axis.displacement_increment.html0000644000076500007650000000717011603702115023362 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan_axis.displacement_increment

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_scan_axis.displacement_increment

    Name:
    '_diffrn_scan_axis.displacement_increment'

    Definition:

            The increment for each step for the specified axis
                   in millimetres.  In general, this will agree with
                   _diffrn_scan_frame_axis.displacement_increment.
                   The sum of the values of
                   _diffrn_scan_frame_axis.displacement and
                   _diffrn_scan_frame_axis.displacement_increment is the
                   angular setting of the axis at the end of the integration
                   time for a given frame.  If the individual frame values
                   vary, then the value of
                   _diffrn_scan_axis.displacement_increment will be
                   representative
                   of the ensemble of values of
                   _diffrn_scan_frame_axis.displacement_increment (e.g.
                   the mean).
    
    

    Type: float

    Mandatory item: no


    Enumeration default: 0.0

    Category: diffrn_scan_axis

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Iarray_structure_list.precedence.html0000644000076500007650000000525611603702115021737 0ustar yayayaya (IUCr) CIF Definition save__array_structure_list.precedence

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _array_structure_list.precedence

    Name:
    '_array_structure_list.precedence'

    Definition:

            Identifies the rank order in which this array index changes
                   with respect to other array indices.  The precedence of 1
                   indicates the index which changes fastest.
    
    

    Type: int

    Mandatory item: yes


    The permitted range is [1, infinity)

    Category: array_structure_list

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Iarray_intensities.binary_id.html0000644000076500007650000000516211603702115021041 0ustar yayayaya (IUCr) CIF Definition save__array_intensities.binary_id

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _array_intensities.binary_id

    Name:
    '_array_intensities.binary_id'

    Definition:

           This item is a pointer to _array_data.binary_id in the
                  ARRAY_DATA category.
    
    

    Type: int

    Mandatory item: implicit

    Category: array_intensities

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Iarray_structure.compression_type.html0000644000076500007650000000762311603702115022211 0ustar yayayaya (IUCr) CIF Definition save__array_structure.compression_type

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _array_structure.compression_type

    Name:
    '_array_structure.compression_type'

    Definition:

           Type of data-compression method used to compress the array
                  data.
    
    

    Type: ucode

    Mandatory item: no


    The data value must be one of the following:


    byte_offset
    Using the 'byte_offset' compression scheme as per A. Hammersley and the CBFlib manual, section 3.3.3

    canonical
    Using the 'canonical' compression scheme (International Tables for Crystallography Volume G, Section 5.6.3.1) and CBFlib manual section 3.3.1

    none
    Data are stored in normal format as defined by _array_structure.encoding_type and _array_structure.byte_order.

    packed
    Using the 'packed' compression scheme, a CCP4-style packing as per J. P. Abrahams pack_c.c and CBFlib manual, section 3.3.2.

    packed_v2
    Using the 'packed' compression scheme, version 2, as per J. P. Abrahams pack_c.c and CBFlib manual, section 3.3.2.

    Enumeration default: none

    Category: array_structure

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/cif_img_1.5.2_6May07.html0000644000076500007650000107543511603702115016433 0ustar yayayaya cif_img.dic v1.5_DRAFT

    # [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib] #

    # imgCIF/CBF #

    # Extensions Dictionary #

    ##############################################################################
    #                                                                            #
    #                       Image CIF Dictionary (imgCIF)                        #
    #             and Crystallographic Binary File Dictionary (CBF)              #
    #            Extending the Macromolecular CIF Dictionary (mmCIF)             #
    #                                                                            #
    #                              Version 1.5.2                                 #
    #                              of 2007-05-07                                 #
    #    ###################################################################     #
    #    # *** WARNING *** THIS IS A DRAFT FOR DISCUSSSION *** WARNING *** #     #
    #    #                 SUBJECT TO CHANGE WITHOUT NOTICE                #     #
    #    #     VERSIONS WILL BE POSTED AS cif_img_1.5_DDMMMYY_draft.html   #     #
    #    #       SEND COMMENTS TO imgcif-l@iucr.org CITING THE VERSION     #     #
    #    ###################################################################     #
    #                  This draft edited by H. J. Bernstein                      #
    #                                                                            #
    #     by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook    #
    #                                                                            #
    # This dictionary was adapted from format discussed at the imgCIF Workshop,  #
    # held at BNL Oct 1997 and the Crystallographic Binary File Format Draft     #
    # Proposal by Andrew Hammersley.  The first DDL 2.1 Version was created by   #
    # John Westbrook.  This version was drafted by Herbert J. Bernstein and      #
    # incorporates comments by I. David Brown, John Westbrook, Brian McMahon,    #
    # Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li, Gotzon Madariaga,         #
    # Frances C. Bernstein, Chris Nielsen, Nicola Ashcroft and others.           #
    ##############################################################################
    
    data_cif_img.dic
    
        _dictionary.title           cif_img.dic
        _dictionary.version         1.5.2
        _dictionary.datablock_id    cif_img.dic
    
    ##############################################################################
    #    CONTENTS
    #
    #        CATEGORY_GROUP_LIST
    #        SUB_CATEGORY
    #
    #        category  ARRAY_DATA
    #
    #                  _array_data.array_id
    #                  _array_data.binary_id
    #                  _array_data.data
    #
    #        category  ARRAY_ELEMENT_SIZE
    #
    #                  _array_element_size.array_id
    #                  _array_element_size.index
    #                  _array_element_size.size
    #
    #        category  ARRAY_INTENSITIES
    #
    #                  _array_intensities.array_id
    #                  _array_intensities.binary_id
    #                  _array_intensities.gain
    #                  _array_intensities.gain_esd
    #                  _array_intensities.linearity
    #                  _array_intensities.offset
    #                  _array_intensities.scaling
    #                  _array_intensities.overload
    #                  _array_intensities.undefined_value
    #                  _array_intensities.pixel_fast_bin_size
    #                  _array_intensities.pixel_slow_bin_size
    #                  _array_intensities.pixel_binning_method
    #
    #        category  ARRAY_STRUCTURE
    #
    #                  _array_structure.byte_order
    #                  _array_structure.compression_type
    #                  _array_structure.compression_type_flag
    #                  _array_structure.encoding_type
    #                  _array_structure.id
    #
    #        category  ARRAY_STRUCTURE_LIST
    #
    #                  _array_structure_list.axis_set_id
    #                  _array_structure_list.array_id
    #                  _array_structure_list.dimension
    #                  _array_structure_list.direction
    #                  _array_structure_list.index
    #                  _array_structure_list.precedence
    #
    #        category  ARRAY_STRUCTURE_LIST_AXIS
    #
    #                  _array_structure_list_axis.axis_id
    #                  _array_structure_list_axis.axis_set_id
    #                  _array_structure_list_axis.angle
    #                  _array_structure_list_axis.angle_increment
    #                  _array_structure_list_axis.displacement
    #                  _array_structure_list_axis.fract_displacement
    #                  _array_structure_list_axis.displacement_increment
    #                  _array_structure_list_axis.fract_displacement_increment
    #                  _array_structure_list_axis.angular_pitch
    #                  _array_structure_list_axis.radial_pitch
    #                  _array_structure_list_axis.reference_angle
    #                  _array_structure_list_axis.reference_displacement
    #
    #        category  AXIS
    #
    #                  _axis.depends_on
    #                  _axis.equipment
    #                  _axis.id
    #                  _axis.offset[1]
    #                  _axis.offset[2]
    #                  _axis.offset[3]
    #                  _axis.type
    #                  _axis.system
    #                  _axis.vector[1]
    #                  _axis.vector[2]
    #                  _axis.vector[3]
    #
    #        category  DIFFRN_DATA_FRAME
    #
    #                  _diffrn_data_frame.array_id
    #                  _diffrn_data_frame.binary_id
    #                  _diffrn_data_frame.detector_element_id
    #                  _diffrn_data_frame.id
    #                  _diffrn_data_frame.details
    #
    #        category  DIFFRN_DETECTOR
    #
    #                  _diffrn_detector.details
    #                  _diffrn_detector.detector
    #                  _diffrn_detector.diffrn_id
    #                  _diffrn_detector.dtime
    #                  _diffrn_detector.id
    #                  _diffrn_detector.number_of_axes
    #                  _diffrn_detector.type
    #
    #        category  DIFFRN_DETECTOR_AXIS
    #
    #                  _diffrn_detector_axis.axis_id
    #                  _diffrn_detector_axis.detector_id
    #
    #        category  DIFFRN_DETECTOR_ELEMENT
    #
    #                  _diffrn_detector_element.center[1]
    #                  _diffrn_detector_element.center[2]
    #                  _diffrn_detector_element.id
    #                  _diffrn_detector_element.detector_id
    #                  _diffrn_detector_element.reference_center_fast
    #                  _diffrn_detector_element.reference_center_slow
    #
    #        category  DIFFRN_MEASUREMENT
    #
    #                  _diffrn_measurement.diffrn_id
    #                  _diffrn_measurement.details
    #                  _diffrn_measurement.device
    #                  _diffrn_measurement.device_details
    #                  _diffrn_measurement.device_type
    #                  _diffrn_measurement.id
    #                  _diffrn_measurement.method
    #                  _diffrn_measurement.number_of_axes
    #                  _diffrn_measurement.specimen_support
    #
    #        category  DIFFRN_MEASUREMENT_AXIS
    #
    #                  _diffrn_measurement_axis.axis_id
    #                  _diffrn_measurement_axis.measurement_device
    #                  _diffrn_measurement_axis.measurement_id
    #
    #        category  DIFFRN_RADIATION
    #
    #                  _diffrn_radiation.collimation
    #                  _diffrn_radiation.diffrn_id
    #                  _diffrn_radiation.div_x_source
    #                  _diffrn_radiation.div_y_source
    #                  _diffrn_radiation.div_x_y_source
    #                  _diffrn_radiation.filter_edge'
    #                  _diffrn_radiation.inhomogeneity
    #                  _diffrn_radiation.monochromator
    #                  _diffrn_radiation.polarisn_norm
    #                  _diffrn_radiation.polarisn_ratio
    #                  _diffrn_radiation.polarizn_source_norm
    #                  _diffrn_radiation.polarizn_source_ratio
    #                  _diffrn_radiation.probe
    #                  _diffrn_radiation.type
    #                  _diffrn_radiation.xray_symbol
    #                  _diffrn_radiation.wavelength_id
    #
    #        category  DIFFRN_REFLN
    #
    #                  _diffrn_refln.frame_id
    #
    #        category  DIFFRN_SCAN
    #
    #                  _diffrn_scan.id
    #                  _diffrn_scan.date_end
    #                  _diffrn_scan.date_start
    #                  _diffrn_scan.integration_time
    #                  _diffrn_scan.frame_id_start
    #                  _diffrn_scan.frame_id_end
    #                  _diffrn_scan.frames
    #
    #        category  DIFFRN_SCAN_AXIS
    #
    #                  _diffrn_scan_axis.axis_id
    #                  _diffrn_scan_axis.angle_start
    #                  _diffrn_scan_axis.angle_range
    #                  _diffrn_scan_axis.angle_increment
    #                  _diffrn_scan_axis.angle_rstrt_incr
    #                  _diffrn_scan_axis.displacement_start
    #                  _diffrn_scan_axis.displacement_range
    #                  _diffrn_scan_axis.displacement_increment
    #                  _diffrn_scan_axis.displacement_rstrt_incr
    #                  _diffrn_scan_axis.reference_angle
    #                  _diffrn_scan_axis.reference_displacement
    #                  _diffrn_scan_axis.scan_id
    #
    #        category  DIFFRN_SCAN_FRAME
    #
    #                  _diffrn_scan_frame.date
    #                  _diffrn_scan_frame.frame_id
    #                  _diffrn_scan_frame.frame_number
    #                  _diffrn_scan_frame.integration_time
    #                  _diffrn_scan_frame.scan_id
    #
    #        category  DIFFRN_SCAN_FRAME_AXIS
    #
    #                  _diffrn_scan_frame_axis.axis_id
    #                  _diffrn_scan_frame_axis.angle
    #                  _diffrn_scan_frame_axis.angle_increment
    #                  _diffrn_scan_frame_axis.angle_rstrt_incr
    #                  _diffrn_scan_frame_axis.displacement
    #                  _diffrn_scan_frame_axis.displacement_increment
    #                  _diffrn_scan_frame_axis.displacement_rstrt_incr
    #                  _diffrn_scan_frame_axis.reference_angle
    #                  _diffrn_scan_frame_axis.reference_displacement
    #                  _diffrn_scan_frame_axis.frame_id
    #
    #       categor    MAP
    #
    #                  _map.details
    #                  _map.diffrn_id
    #                  _map.entry_id
    #                  _map.id
    #
    #       categor    MAP_SEGMENT
    #
    #                  _map_segment.array_id
    #                  _map_segment.binary_id
    #                  _map_segment.mask_array_id
    #                  _map_segment.mask_binary_id
    #                  _map_segment.id
    #                  _map_segment.map_id
    #                  _map_segment.details
    #
    #       ***DEPRECATED*** data items
    #
    #                  _diffrn_detector_axis.id
    #                  _diffrn_measurement_axis.id
    #
    #       ***DEPRECATED*** category  DIFFRN_FRAME_DATA
    #
    #                  _diffrn_frame_data.array_id
    #                  _diffrn_frame_data.binary_id
    #                  _diffrn_frame_data.detector_element_id
    #                  _diffrn_frame_data.id
    #                  _diffrn_frame_data.details
    #
    #
    #        ITEM_TYPE_LIST
    #        ITEM_UNITS_LIST
    #        DICTIONARY_HISTORY
    #
    ##############################################################################
    
    
    #########################
    ## CATEGORY_GROUP_LIST ##
    #########################
    
         loop_
        _category_group_list.id
        _category_group_list.parent_id
        _category_group_list.description
                 'inclusive_group'   .
    ;             Categories that belong to the dictionary extension.
    ;
                 'array_data_group'
                 'inclusive_group'
    ;             Categories that describe array data.
    ;
                 'axis_group'
                 'inclusive_group'
    ;             Categories that describe axes.
    ;
                 'diffrn_group'
                 'inclusive_group'
    ;            Categories that describe details of the diffraction experiment.
    ;
    
    
    ##################
    ## SUB_CATEGORY ##
    ##################
    
         loop_
        _sub_category.id
        _sub_category.description
                  'matrix'
    ;              The collection of elements of a matrix.
    ;
                  'vector'
    ;              The collection of elements of a vector.
    ;
    
    
    
    
    ##############
    # ARRAY_DATA #
    ##############
    
    
    save_ARRAY_DATA
        _category.description
    ;    Data items in the ARRAY_DATA category are the containers for
         the array data items described in the category ARRAY_STRUCTURE.
    ;
        _category.id                   array_data
        _category.mandatory_code       no
         loop_
        _category_key.name             '_array_data.array_id'
                                       '_array_data.binary_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 -
    
            This example shows two binary data blocks.  The first one
            was compressed by the CBF_CANONICAL compression algorithm and is
            presented as hexadecimal data.  The first character 'H' on the
            data lines means hexadecimal.  It could have been 'O' for octal
            or 'D' for decimal.  The second character on the line shows
            the number of bytes in each word (in this case '4'), which then
            requires eight hexadecimal digits per word.  The third character
            gives the order of octets within a word, in this case '<'
            for the ordering 4321 (i.e. 'big-endian').  Alternatively, the
            character '>' could have been used for the ordering 1234
            (i.e. 'little-endian').  The block has a 'message digest'
            to check the integrity of the data.
    
            The second block is similar, but uses CBF_PACKED compression
            and BASE64 encoding.  Note that the size and the digest are
            different.
    ;
    ;
    
            loop_
            _array_data.array_id
            _array_data.binary_id
            _array_data.data
            image_1 1
            ;
            --CIF-BINARY-FORMAT-SECTION--
            Content-Type: application/octet-stream;
                 conversions="X-CBF_CANONICAL"
            Content-Transfer-Encoding: X-BASE16
            X-Binary-Size: 3927126
            X-Binary-ID: 1
            Content-MD5: u2sTJEovAHkmkDjPi+gWsg==
    
            # Hexadecimal encoding, byte 0, byte order ...21
            #
            H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ...
            ....
            --CIF-BINARY-FORMAT-SECTION----
            ;
            image_2 2
            ;
            --CIF-BINARY-FORMAT-SECTION--
            Content-Type: application/octet-stream;
                 conversions="X-CBF-PACKED"
            Content-Transfer-Encoding: BASE64
            X-Binary-Size: 3745758
            X-Binary-ID: 2
            Content-MD5: 1zsJjWPfol2GYl2V+QSXrw==
    
            ELhQAAAAAAAA...
            ...
            --CIF-BINARY-FORMAT-SECTION----
            ;
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    save_
    
    
    save__array_data.array_id
        _item_description.description
    ;             This item is a pointer to _array_structure.id in the
                  ARRAY_STRUCTURE category.
    ;
        _item.name                  '_array_data.array_id'
        _item.category_id             array_data
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__array_data.binary_id
        _item_description.description
    ;             This item is an integer identifier which, along with
                  _array_data.array_id, should uniquely identify the
                  particular block of array data.
    
                  If _array_data.binary_id is not explicitly given,
                  it defaults to 1.
    
                  The value of _array_data.binary_id distinguishes
                  among multiple sets of data with the same array
                  structure.
    
                  If the MIME header of the data array specifies a
                  value for X-Binary-ID, the value of  _array_data.binary_id
                  should be equal to the value given for X-Binary-ID.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
                 '_array_data.binary_id'            array_data
                                                                    implicit
                 '_diffrn_data_frame.binary_id'     diffrn_data_frame
                                                                    implicit
                 '_array_intensities.binary_id'     array_intensities
                                                                    implicit
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_data_frame.binary_id'     '_array_data.binary_id'
                 '_array_intensities.binary_id'     '_array_data.binary_id'
    
        _item_default.value           1
        _item_type.code               int
         loop_
        _item_range.maximum
        _item_range.minimum
                                1  1
                                .  1
         save_
    
    
    save__array_data.data
        _item_description.description
    ;             The value of _array_data.data contains the array data
                  encapsulated in a STAR string.
    
                  The representation used is a variant on the
                  Multipurpose Internet Mail Extensions (MIME) specified
                  in RFC 2045-2049 by N. Freed et al.  The boundary
                  delimiter used in writing an imgCIF or CBF is
                  '\n--CIF-BINARY-FORMAT-SECTION--' (including the
                  required initial '\n--').
    
                  The Content-Type may be any of the discrete types permitted
                  in RFC 2045; 'application/octet-stream' is recommended.
                  If an octet stream was compressed, the compression should
                  be specified by the parameter 
                    'conversions="X-CBF_PACKED"'
                  or the parameter 
                    'conversions="X-CBF_CANONICAL"'
                  or the parameter 
                    'conversions="X-CBF_BYTE_OFFSET"'
                    
                  If the parameter 
                    'conversions="X-CBF_PACKED"'
                  is given it may be further modified with the parameters
                    '"uncorrelated_sections"'
                  or
                    '"flat"'
                  
                  If the '"uncorrelated_sections"' parameter is
                  given, each section will be compressed without using
                  the prior section for averaging.
                  
                  If the '"flat"' parameter is given, each the
                  image will be treated as one long row.
    
                  The Content-Transfer-Encoding may be 'BASE64',
                  'Quoted-Printable', 'X-BASE8', 'X-BASE10',
                  'X-BASE16' or 'X-BASE32K', for an imgCIF or 'BINARY'
                  for a CBF.  The octal, decimal and hexadecimal transfer
                  encodings are provided for convenience in debugging and
                  are not recommended for archiving and data interchange.
    
                  In a CIF, one of the parameters 'charset=us-ascii',
                  'charset=utf-8' or 'charset=utf-16' may be used on the
                  Content-Transfer-Encoding to specify the character set
                  used for the external presentation of the encoded data.
                  If no charset parameter is given, the character set of
                  the enclosing CIF is assumed.  In any case, if a BOM
                  flag is detected (FE FF for big-endian UTF-16, FF FE for
                  little-endian UTF-16 or EF BB BF for UTF-8) is detected,
                  the indicated charset will be assumed until the end of the
                  encoded data or the detection of a different BOM.  The
                  charset of the Content-Transfer-Encoding is not the character
                  set of the encoded data, only the character set of the
                  presentation of the encoded data and should be respecified
                  for each distinct STAR string.
    
                  In an imgCIF file, the encoded binary data begins after
                  the empty line terminating the header.  In an imgCIF file,
                  the encoded binary data ends with the terminating boundary
                  delimiter '\n--CIF-BINARY-FORMAT-SECTION----'
                  in the currently effective charset or with the '\n; '
                  that terminates the STAR string.
    
                  In a CBF, the raw binary data begins after an empty line
                  terminating the header and after the sequence:
    
                  Octet   Hex   Decimal  Purpose
                    0     0C       12    (ctrl-L) Page break
                    1     1A       26    (ctrl-Z) Stop listings in MS-DOS
                    2     04       04    (Ctrl-D) Stop listings in UNIX
                    3     D5      213    Binary section begins
    
                  None of these octets are included in the calculation of
                  the message size or in the calculation of the
                  message digest.
    
                  The X-Binary-Size header specifies the size of the
                  equivalent binary data in octets.  If compression was
                  used, this size is the size after compression, including
                  any book-keeping fields.  An adjustment is made for
                  the deprecated binary formats in which eight bytes of binary
                  header are used for the compression type.  In this case,
                  the eight bytes used for the compression type are subtracted
                  from the size, so that the same size will be reported
                  if the compression type is supplied in the MIME header.
                  Use of the MIME header is the recommended way to
                  supply the compression type.  In general, no portion of
                  the  binary header is included in the calculation of the size.
    
                  The X-Binary-Element-Type header specifies the type of
                  binary data in the octets, using the same descriptive
                  phrases as in _array_structure.encoding_type.  The default
                  value is 'unsigned 32-bit integer'.
    
                  An MD5 message digest may, optionally, be used. The 'RSA Data
                  Security, Inc. MD5 Message-Digest Algorithm' should be used.
                  No portion of the header is included in the calculation of the
                  message digest.
    
                  If the Transfer Encoding is 'X-BASE8', 'X-BASE10' or
                  'X-BASE16', the data are presented as octal, decimal or
                  hexadecimal data organized into lines or words.  Each word
                  is created by composing octets of data in fixed groups of
                  2, 3, 4, 6 or 8 octets, either in the order ...4321 ('big-
                  endian') or 1234... ('little-endian').  If there are fewer
                  than the specified number of octets to fill the last word,
                  then the missing octets are presented as '==' for each
                  missing octet.  Exactly two equal signs are used for each
                  missing octet even for octal and decimal encoding.
                  The format of lines is:
    
                  rnd xxxxxx xxxxxx xxxxxx
    
                  where r is 'H', 'O' or 'D' for hexadecimal, octal or
                  decimal, n is the number of octets per word and d is '<'
                  or '>' for the '...4321' and '1234...' octet orderings,
                  respectively.  The '==' padding for the last word should
                  be on the appropriate side to correspond to the missing
                  octets, e.g.
    
                  H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000
    
                  or
    
                  H3> FF0700 00====
    
                  For these hexadecimal, octal and decimal formats only,
                  comments beginning with '#' are permitted to improve
                  readability.
    
                  BASE64 encoding follows MIME conventions.  Octets are
                  in groups of three: c1, c2, c3.  The resulting 24 bits
                  are broken into four six-bit quantities, starting with
                  the high-order six bits (c1 >> 2) of the first octet, then
                  the low-order two bits of the first octet followed by the
                  high-order four bits of the second octet [(c1 & 3)<<4 | (c2>>4)],
                  then the bottom four bits of the second octet followed by the
                  high-order two bits of the last octet [(c2 & 15)<<2 | (c3>>6)],
                  then the bottom six bits of the last octet (c3 & 63).  Each
                  of these four quantities is translated into an ASCII character
                  using the mapping:
    
                            1         2         3         4         5         6
                  0123456789012345678901234567890123456789012345678901234567890123
                  |         |         |         |         |         |         |
                  ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/
    
                  With short groups of octets padded on the right with one '='
                  if c3 is missing, and with '==' if both c2 and c3 are missing.
    
                  X-BASE32K encoding is similar to BASE64 encoding, except that
                  sets of 15 octets are encoded as sets of 8 16-bit unicode
                  characters, by breaking the 120 bits into 8 15-bit quantities.
                  256 is added to each 15 bit quantity to bring it into a
                  printable uncode range.  When encoding, zero padding is used
                  to fill out the last 15 bit quantity.  If 8 or more bits of
                  padding are used, a single equals sign (hexadecimal 003D) is
                  appended.  Embedded whitespace and newlines are introduced
                  to produce lines of no more than 80 characters each.  On
                  decoding, all printable ascii characters and ascii whitespace
                  characters are ignored except for any trailing equals signs.
                  The number of trailing equals signs indicated the number of
                  trailing octets to be trimmed from the end of the decoded data.
                  (see Georgi Darakev, Vassil Litchev, Kostadin Z. Mitev, Herbert
                  J. Bernstein, 'Efficient Support of Binary Data in the XML
                  Implementation of the NeXus File Format',absract W0165,
                  ACA Summer Meeting, Honolulu, HI, July 2006).
    
                  QUOTED-PRINTABLE encoding also follows MIME conventions, copying
                  octets without translation if their ASCII values are 32...38,
                  42, 48...57, 59, 60, 62, 64...126 and the octet is not a ';'
                  in column 1.  All other characters are translated to =nn, where
                  nn is the hexadecimal encoding of the octet.  All lines are
                  'wrapped' with a terminating '=' (i.e. the MIME conventions
                  for an implicit line terminator are never used).
                  
                  The "X-Binary-Element-Byte-Order" can specify either 
                  '"BIG_ENDIAN"' or '"LITTLE_ENDIAN"' byte order of the imaage 
                  data.  Only LITTLE_ENDIAN is recommended.  Processors
                  may treat BIG_ENDIAN as a warning of data that can
                  only be processed by special software.
    
                  The "X-Binary-Number-of-Elements" specifies the number of 
                  elements (not the number of octets) in the decompressed, decoded 
                  image.
    
                  The optional "X-Binary-Size-Fastest-Dimension" specifies the 
                  number of elements (not the number of octets) in one row of the 
                  fastest changing dimension of the binary data array. This 
                  information must be in the MIME header for proper operation of 
                  some of the decompression algorithms.
    
                  The optional "X-Binary-Size-Second-Dimension" specifies the 
                  number of elements (not the number of octets) in one column of 
                  the second-fastest changing dimension of the binary data array. 
                  This information must be in the MIME header for proper operation 
                  of some of the decompression algorithms.
    
                  The optional "X-Binary-Size-Third-Dimension" specifies the number 
                  of sections for the third-fastest changing dimension of the
                  binary data array.
                  
                  The optional "X-Binary-Size-Padding" specifies the size in 
                  octets of an optional padding after the binary array data and 
                  before the closing flags for a binary section.
    ;
        _item.name                  '_array_data.data'
        _item.category_id             array_data
        _item.mandatory_code          yes
        _item_type.code               binary
    save_
    
    
    ######################
    # ARRAY_ELEMENT_SIZE #
    ######################
    
    
    save_ARRAY_ELEMENT_SIZE
        _category.description
    ;    Data items in the ARRAY_ELEMENT_SIZE category record the physical
         size of array elements along each array dimension.
    ;
        _category.id                   array_element_size
        _category.mandatory_code       no
         loop_
        _category_key.name             '_array_element_size.array_id'
                                       '_array_element_size.index'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;       Example 1 - A regular 2D array with a uniform element dimension
                        of 1220 nanometres.
    ;
    ;
            loop_
           _array_element_size.array_id
           _array_element_size.index
           _array_element_size.size
            image_1   1    1.22e-6
            image_1   2    1.22e-6
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_element_size.array_id
        _item_description.description
    ;             This item is a pointer to _array_structure.id in the
                  ARRAY_STRUCTURE category.
    ;
        _item.name                  '_array_element_size.array_id'
        _item.category_id             array_element_size
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__array_element_size.index
        _item_description.description
    ;             This item is a pointer to _array_structure_list.index in
                  the ARRAY_STRUCTURE_LIST category.
    ;
        _item.name                  '_array_element_size.index'
        _item.category_id             array_element_size
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__array_element_size.size
        _item_description.description
    ;              The size in metres of an image element in this
                   dimension. This supposes that the elements are arranged
                   on a regular grid.
    ;
        _item.name               '_array_element_size.size'
        _item.category_id          array_element_size
        _item.mandatory_code       yes
        _item_type.code            float
        _item_units.code           'metres'
         loop_
        _item_range.maximum
        _item_range.minimum
                                .   0.0
         save_
    
    
    #####################
    # ARRAY_INTENSITIES #
    #####################
    
    
    save_ARRAY_INTENSITIES
        _category.description
    ;             Data items in the ARRAY_INTENSITIES category record the
                  information required to recover the intensity data from
                  the set of data values stored in the ARRAY_DATA category.
    
                  The detector may have a complex relationship
                  between the raw intensity values and the number of
                  incident photons.  In most cases, the number stored
                  in the final array will have a simple linear relationship
                  to the actual number of incident photons, given by
                  _array_intensities.gain.  If raw, uncorrected values
                  are presented (e.g. for calibration experiments), the
                  value of _array_intensities.linearity will be 'raw'
                  and _array_intensities.gain will not be used.
    
    ;
        _category.id                   array_intensities
        _category.mandatory_code       no
        loop_
        _category_key.name             '_array_intensities.array_id'
                                       '_array_intensities.binary_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1
    ;
    ;
            loop_
            _array_intensities.array_id
            _array_intensities.linearity
            _array_intensities.gain
            _array_intensities.overload
            _array_intensities.undefined_value
            _array_intensities.pixel_fast_bin_size
            _array_intensities.pixel_slow_bin_size
            _array_intensities.pixel_binning_method
            image_1   linear  1.2    655535   0   2   2    hardware
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_intensities.array_id
        _item_description.description
    ;             This item is a pointer to _array_structure.id in the
                  ARRAY_STRUCTURE category.
    ;
        _item.name                  '_array_intensities.array_id'
        _item.category_id             array_intensities
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__array_intensities.binary_id
        _item_description.description
    ;             This item is a pointer to _array_data.binary_id in the
                  ARRAY_DATA category.
    ;
        _item.name                  '_array_intensities.binary_id'
        _item.category_id             array_intensities
        _item.mandatory_code          implicit
        _item_type.code               int
         save_
    
    
    save__array_intensities.gain
        _item_description.description
    ;              Detector 'gain'. The factor by which linearized
                   intensity count values should be divided to produce
                   true photon counts.
    ;
        _item.name              '_array_intensities.gain'
        _item.category_id          array_intensities
        _item.mandatory_code       yes
        _item_type.code            float
         loop_
        _item_range.maximum
        _item_range.minimum
                                .   0.0
        _item_units.code           'counts_per_photon'
         loop_
        _item_related.related_name
        _item_related.function_code  '_array_intensities.gain_esd'
                                     'associated_value'
        save_
    
    
    save__array_intensities.gain_esd
        _item_description.description
    ;            The estimated standard deviation in detector 'gain'.
    ;
        _item.name              '_array_intensities.gain_esd'
        _item.category_id          array_intensities
        _item.mandatory_code       yes
        _item_type.code            float
         loop_
        _item_range.maximum
        _item_range.minimum
                                .   0.0
    
        _item_units.code          'counts_per_photon'
         loop_
        _item_related.related_name
        _item_related.function_code  '_array_intensities.gain'
                                     'associated_esd'
        save_
    
    
    save__array_intensities.linearity
        _item_description.description
    ;              The intensity linearity scaling method used to convert
                   from the raw intensity to the stored element value:
    
                   'linear' is linear.
    
                   'offset'  means that the value defined by
                   _array_intensities.offset should be added to each
                    element value.
    
                   'scaling' means that the value defined by
                   _array_intensities.scaling should be multiplied with each
                   element value.
    
                   'scaling_offset' is the combination of the two previous cases,
                   with the scale factor applied before the offset value.
    
                   'sqrt_scaled' means that the square root of raw
                   intensities multiplied by _array_intensities.scaling is
                   calculated and stored, perhaps rounded to the nearest
                   integer. Thus, linearization involves dividing the stored
                   values by _array_intensities.scaling and squaring the
                   result.
    
                   'logarithmic_scaled' means that the logarithm base 10 of
                   raw intensities multiplied by _array_intensities.scaling
                   is calculated and stored, perhaps rounded to the nearest
                   integer. Thus, linearization involves dividing the stored
                   values by _array_intensities.scaling and calculating 10
                   to the power of this number.
    
                   'raw' means that the data are a set of raw values straight
                   from the detector.
    ;
    
        _item.name               '_array_intensities.linearity'
        _item.category_id          array_intensities
        _item.mandatory_code       yes
        _item_type.code            code
         loop_
        _item_enumeration.value
        _item_enumeration.detail
                                  'linear' .
                                  'offset'
    ;              The value defined by  _array_intensities.offset should
                   be added to each element value.
    ;
                                  'scaling'
    ;              The value defined by _array_intensities.scaling should be
                   multiplied with each element value.
    ;
                                  'scaling_offset'
    ;              The combination of the scaling and offset
                   with the scale factor applied before the offset value.
    ;
                                  'sqrt_scaled'
    ;              The square root of raw intensities multiplied by
                   _array_intensities.scaling is calculated and stored,
                   perhaps rounded to the nearest integer. Thus,
                   linearization involves dividing the stored
                   values by _array_intensities.scaling and squaring the
                   result.
    ;
                                  'logarithmic_scaled'
    ;              The logarithm base 10 of raw intensities multiplied by
                   _array_intensities.scaling  is calculated and stored,
                   perhaps rounded to the nearest integer. Thus,
                   linearization involves dividing the stored values by
                   _array_intensities.scaling and calculating 10 to the
                   power of this number.
    ;
                                  'raw'
    ;              The array consists of raw values to which no corrections have
                   been applied.  While the handling of the data is similar to
                   that given for 'linear' data with no offset, the meaning of
                   the data differs in that the number of incident photons is
                   not necessarily linearly related to the number of counts
                   reported.  This value is intended for use either in
                   calibration experiments or to allow for handling more
                   complex data-fitting algorithms than are allowed for by
                   this data item.
    ;
    
        save_
    
    
    save__array_intensities.offset
        _item_description.description
    ;              Offset value to add to array element values in the manner
                   described by the item _array_intensities.linearity.
    ;
        _item.name                 '_array_intensities.offset'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        save_
    
    
    save__array_intensities.overload
        _item_description.description
    ;              The saturation intensity level for this data array.
    ;
        _item.name                 '_array_intensities.overload'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        _item_units.code          'counts'
        save_
    
    
    save__array_intensities.pixel_fast_bin_size
        _item_description.description
    ;              The value of _array_intensities.pixel_fast_bin_size specifies
                   the number of pixels that compose one element in the direction
                   of the most rapidly varying array dimension.
    
                   Typical values are 1, 2, 4 or 8.  When there is 1 pixel per
                   array element in both directions, the value given for
                   _array_intensities.pixel_binning_method normally should be
                   'none'.
    
                   It is specified as a float to allow for binning algorithms that
                   create array elements that are not integer multiples of the 
                   detector pixel size.
    ;
        _item.name              '_array_intensities.pixel_fast_bin_size'
        _item.category_id          array_intensities
        _item.mandatory_code       implicit
        _item_type.code            float
        _item_default.value        1.
         loop_
        _item_range.maximum
        _item_range.minimum
                                .   0.0
        _item_units.code           'pixels_per_element'
        save_
    
    
    save__array_intensities.pixel_slow_bin_size
        _item_description.description
    ;              The value of _array_intensities.pixel_slow_bin_size specifies
                   the number of pixels that compose one element in the direction
                   of the second most rapidly varying array dimension.
    
                   Typical values are 1, 2, 4 or 8.  When there is 1 pixel per
                   array element in both directions, the value given for
                   _array_intensities.pixel_binning_method normally should be
                   'none'.
    
                   It is specified as a float to allow for binning algorithms that
                   create array elements that are not integer multiples of the
                   detector pixel size.
    ;
        _item.name              '_array_intensities.pixel_slow_bin_size'
        _item.category_id          array_intensities
        _item.mandatory_code       implicit
        _item_type.code            float
        _item_default.value        1.
         loop_
        _item_range.maximum
        _item_range.minimum
                                .   0.0
        _item_units.code           'pixels_per_element'
        save_
    
    
    save__array_intensities.pixel_binning_method
        _item_description.description
    ;              The value of _array_intensities.pixel_binning_method specifies
                   the method used to derive array elements from multiple pixels.
    ;
        _item.name              '_array_intensities.pixel_binning_method'
        _item.category_id          array_intensities
        _item.mandatory_code       implicit
        _item_type.code            code
         loop_
        _item_enumeration.value
        _item_enumeration.detail
                                   'hardware'
    ;              The element intensities were derived from the raw data of one
                   or more pixels by used of hardware in the detector, e.g. by use
                   of shift registers in a CCD to combine pixels into super-pixels.
    ;
                                   'software'
    ;              The element intensities were derived from the raw data of more
                   than one pixel by use of software.
    ;
                                   'combined'
    ;              The element intensities were derived from the raw data of more
                   than one pixel by use of both hardware and software, as when
                   hardware binning is used in one direction and software in the
                   other.
    ;
                                   'none'
    ;              In the both directions, the data has not been binned.  The
                   number of pixels is equal to the number of elements.
    
                   When the value of _array_intensities.pixel_binning_method is
                   'none' the values of _array_intensities.pixel_fast_bin_size
                   and _array_intensities.pixel_slow_bin_size both must be 1.
    ;
                                   'unspecified'
    ;              The method used to derive element intensities is not specified.
    ;
        _item_default.value        'unspecified'
        save_
    
    save__array_intensities.scaling
        _item_description.description
    ;              Multiplicative scaling value to be applied to array data
                   in the manner described by item
                   _array_intensities.linearity.
    ;
        _item.name                 '_array_intensities.scaling'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        save_
    
    
    
    save__array_intensities.undefined_value
        _item_description.description
    ;              A value to be substituted for undefined values in
                   the data array.
    ;
        _item.name                 '_array_intensities.undefined_value'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        save_
    
    
    ###################
    # ARRAY_STRUCTURE #
    ###################
    
    
    save_ARRAY_STRUCTURE
        _category.description
    ;    Data items in the ARRAY_STRUCTURE category record the organization and
         encoding of array data that may be stored in the ARRAY_DATA category.
    ;
        _category.id                   array_structure
        _category.mandatory_code       no
        _category_key.name             '_array_structure.id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;   Example 1 -
    ;
    ;
         loop_
        _array_structure.id
        _array_structure.encoding_type
        _array_structure.compression_type
        _array_structure.byte_order
         image_1       "unsigned 16-bit integer"  none  little_endian
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_structure.byte_order
        _item_description.description
    ;              The order of bytes for integer values which require more
                   than 1 byte.
    
                   (IBM-PC's and compatibles and DEC VAXs use low-byte-first
                   ordered integers, whereas Hewlett Packard 700
                   series, Sun-4 and Silicon Graphics use high-byte-first
                   ordered integers.  DEC Alphas can produce/use either
                   depending on a compiler switch.)
    ;
    
        _item.name                     '_array_structure.byte_order'
        _item.category_id               array_structure
        _item.mandatory_code            yes
        _item_type.code                 ucode
         loop_
        _item_enumeration.value
        _item_enumeration.detail
                                       'big_endian'
    ;       The first byte in the byte stream of the bytes which make up an
            integer value is the most significant byte of an integer.
    ;
                                       'little_endian'
    ;       The last byte in the byte stream of the bytes which make up an
            integer value is the most significant byte of an integer.
    ;
         save_
    
    
    save__array_structure.compression_type
        _item_description.description
    ;             Type of data-compression method used to compress the array
                  data.
    ;
        _item.name                   '_array_structure.compression_type'
        _item.category_id             array_structure
        _item.mandatory_code          no
        _item_type.code               ucode
        _item_default.value           'none'
         loop_
        _item_enumeration.value
        _item_enumeration.detail
                                      'byte_offset'
    ;       Using the 'byte_offset' compression scheme as per A. Hammersley
            and the CBFlib manual, section 3.3.3
    ;
                                      'canonical'
    ;       Using the 'canonical' compression scheme (International Tables
            for Crystallography Volume G, Section 5.6.3.1) and CBFlib
            manual section 3.3.1
    ;
                                      'none'
    ;       Data are stored in normal format as defined by
            _array_structure.encoding_type and
            _array_structure.byte_order.
    ;
                                      'packed'
    ;       Using the 'packed' compression scheme, a CCP4-style packing
            as per J. P. Abrahams pack_c.c and CBFlib manual, section 3.3.2.
    ;
                                      'packed_v2'
    ;       Using the 'packed' compression scheme, version 2, as per
            J. P. Abrahams pack_c.c and CBFlib manual, section 3.3.2.
    ;
        save_
    
    save__array_structure.compression_type_flag
        _item_description.description
    ;             Flags modifying the type of data-compression method used to 
                  compress the arraydata.
    ;
        _item.name                   '_array_structure.compression_type_flag'
        _item.category_id             array_structure
        _item.mandatory_code          no
        _item_type.code               ucode
         loop_
        _item_enumeration.value
        _item_enumeration.detail
                                      'uncorrelated_sections'
    ;       When applying packed or packed_v2 compression on an array with
            uncorrelated sections, do not average in points from the prior
            section.
    ;
                                      'flat'
    ;       When applying packed or packed_v2 compression on an array with
            treat the entire image as a single line set the maximum number
            of bits for an offset to 65 bits.
            
            The flag is included for compatibility with software prior to
            CBFlib_0.7.7, and should not be used for new data sets.
    
    ;
    
        save_
    
    save__array_structure.encoding_type
        _item_description.description
    ;              Data encoding of a single element of array data.
    
                   In several cases, the IEEE format is referenced.
                   See IEEE Standard 754-1985 (IEEE, 1985).
    
                   Ref: IEEE (1985). IEEE Standard for Binary Floating-Point
                   Arithmetic. ANSI/IEEE Std 754-1985. New York: Institute of
                   Electrical and Electronics Engineers.
    ;
    
        _item.name                '_array_structure.encoding_type'
        _item.category_id          array_structure
        _item.mandatory_code       yes
        _item_type.code            uline
         loop_
        _item_enumeration.value
                                  'unsigned 8-bit integer'
                                  'signed 8-bit integer'
                                  'unsigned 16-bit integer'
                                  'signed 16-bit integer'
                                  'unsigned 32-bit integer'
                                  'signed 32-bit integer'
                                  'signed 32-bit real IEEE'
                                  'signed 64-bit real IEEE'
                                  'signed 32-bit complex IEEE'
         save_
    
    
    save__array_structure.id
        _item_description.description
    ;             The value of _array_structure.id must uniquely identify
                  each item of array data.
    ;
        loop_
        _item.name
        _item.category_id
        _item.mandatory_code
                 '_array_structure.id'              array_structure      yes
                 '_array_data.array_id'             array_data           yes
                 '_array_structure_list.array_id'   array_structure_list yes
                 '_array_intensities.array_id'      array_intensities    yes
                 '_diffrn_data_frame.array_id'      diffrn_data_frame    yes
    
    
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_array_data.array_id'             '_array_structure.id'
                 '_array_structure_list.array_id'   '_array_structure.id'
                 '_array_intensities.array_id'      '_array_structure.id'
                 '_diffrn_data_frame.array_id'      '_array_structure.id'
    
         save_
    
    
    ########################
    # ARRAY_STRUCTURE_LIST #
    ########################
    
    
    save_ARRAY_STRUCTURE_LIST
        _category.description
    ;    Data items in the ARRAY_STRUCTURE_LIST category record the size
         and organization of each array dimension.
    
         The relationship to physical axes may be given.
    ;
        _category.id                   array_structure_list
        _category.mandatory_code       no
         loop_
        _category_key.name             '_array_structure_list.array_id'
                                       '_array_structure_list.index'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;       Example 1 - An image array of 1300 x 1200 elements.  The raster
                        order of the image is left to right (increasing) in the
                        first dimension and bottom to top (decreasing) in
                        the second dimension.
    ;
    ;
            loop_
           _array_structure_list.array_id
           _array_structure_list.index
           _array_structure_list.dimension
           _array_structure_list.precedence
           _array_structure_list.direction
           _array_structure_list.axis_set_id
            image_1   1    1300    1     increasing  ELEMENT_X
            image_1   2    1200    2     decreasing  ELEMENY_Y
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_structure_list.array_id
        _item_description.description
    ;             This item is a pointer to _array_structure.id in the
                  ARRAY_STRUCTURE category.
    ;
        _item.name                  '_array_structure_list.array_id'
        _item.category_id             array_structure_list
        _item.mandatory_code          yes
        _item_type.code               code
    save_
    
    
    save__array_structure_list.axis_set_id
        _item_description.description
    ;              This is a descriptor for the physical axis or set of axes
                   corresponding to an array index.
    
                   This data item is related to the axes of the detector
                   itself given in DIFFRN_DETECTOR_AXIS, but usually differs
                   in that the axes in this category are the axes of the
                   coordinate system of reported data points, while the axes in
                   DIFFRN_DETECTOR_AXIS are the physical axes
                   of the detector describing the 'poise' of the detector as an
                   overall physical object.
    
                   If there is only one axis in the set, the identifier of
                   that axis should be used as the identifier of the set.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
               '_array_structure_list.axis_set_id'
                                      array_structure_list            yes
               '_array_structure_list_axis.axis_set_id'
                                      array_structure_list_axis       implicit
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_array_structure_list_axis.axis_set_id'
                                   '_array_structure_list.axis_set_id'
    
    
         save_
    
    
    save__array_structure_list.dimension
        _item_description.description
    ;              The number of elements stored in the array structure in this
                   dimension.
    ;
        _item.name                '_array_structure_list.dimension'
        _item.category_id          array_structure_list
        _item.mandatory_code       yes
        _item_type.code            int
         loop_
        _item_range.maximum
        _item_range.minimum
                                1  1
                                .  1
         save_
    
    
    save__array_structure_list.direction
        _item_description.description
    ;             Identifies the direction in which this array index changes.
    ;
        _item.name                '_array_structure_list.direction'
        _item.category_id          array_structure_list
        _item.mandatory_code       yes
        _item_type.code            code
         loop_
        _item_enumeration.value
        _item_enumeration.detail
    
                                  'increasing'
    ;        Indicates the index changes from 1 to the maximum dimension.
    ;
                                  'decreasing'
    ;        Indicates the index changes from the maximum dimension to 1.
    ;
         save_
    
    
    save__array_structure_list.index
        _item_description.description
    ;              Identifies the one-based index of the row or column in the
                   array structure.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
               '_array_structure_list.index'        array_structure_list   yes
               '_array_structure_list.precedence'   array_structure_list   yes
               '_array_element_size.index'          array_element_size     yes
    
        _item_type.code            int
    
         loop_
        _item_linked.child_name
        _item_linked.parent_name
              '_array_element_size.index'         '_array_structure_list.index'
         loop_
        _item_range.maximum
        _item_range.minimum
                                1  1
                                .  1
         save_
    
    
    save__array_structure_list.precedence
        _item_description.description
    ;              Identifies the rank order in which this array index changes
                   with respect to other array indices.  The precedence of 1
                   indicates the index which changes fastest.
    ;
        _item.name                '_array_structure_list.precedence'
        _item.category_id          array_structure_list
        _item.mandatory_code       yes
        _item_type.code            int
         loop_
        _item_range.maximum
        _item_range.minimum
                                1  1
                                .  1
         save_
    
    
    #############################
    # ARRAY_STRUCTURE_LIST_AXIS #
    #############################
    
    save_ARRAY_STRUCTURE_LIST_AXIS
        _category.description
    ;    Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe
         the physical settings of sets of axes for the centres of pixels that
         correspond to data points described in the
         ARRAY_STRUCTURE_LIST category.
    
         In the simplest cases, the physical increments of a single axis correspond
         to the increments of a single array index.  More complex organizations,
         e.g. spiral scans, may require coupled motions along multiple axes.
    
         Note that a spiral scan uses two coupled axes: one for the angular
         direction and one for the radial direction.  This differs from a
         cylindrical scan for which the two axes are not coupled into one set.
    ;
        _category.id                   array_structure_list_axis
        _category.mandatory_code       no
         loop_
        _category_key.name
                                      '_array_structure_list_axis.axis_set_id'
                                      '_array_structure_list_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'array_data_group'
         save_
    
    
    save__array_structure_list_axis.axis_id
        _item_description.description
    ;              The value of this data item is the identifier of one of
                   the axes in the set of axes for which settings are being
                   specified.
    
                   Multiple axes may be specified for the same value of
                   _array_structure_list_axis.axis_set_id.
    
                   This item is a pointer to _axis.id in the
                   AXIS category.
    ;
        _item.name                 '_array_structure_list_axis.axis_id'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__array_structure_list_axis.axis_set_id
        _item_description.description
    ;              The value of this data item is the identifier of the
                   set of axes for which axis settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   _array_structure_list_axis.axis_set_id.
    
                   This item is a pointer to
                   _array_structure_list.axis_set_id
                   in the ARRAY_STRUCTURE_LIST category.
    
                   If this item is not specified, it defaults to the corresponding
                   axis identifier.
    ;
        _item.name                 '_array_structure_list_axis.axis_set_id'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       implicit
        _item_type.code            code
         save_
    
    
    save__array_structure_list_axis.angle
        _item_description.description
    ;              The setting of the specified axis in degrees for the first
                   data point of the array index with the corresponding value
                   of _array_structure_list.axis_set_id.  If the index is
                   specified as 'increasing', this will be the centre of the
                   pixel with index value 1.  If the index is specified as
                   'decreasing', this will be the centre of the pixel with
                   maximum index value.
    ;
        _item.name                 '_array_structure_list_axis.angle'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__array_structure_list_axis.angle_increment
        _item_description.description
    ;              The pixel-centre-to-pixel-centre increment in the angular
                   setting of the specified axis in degrees.  This is not
                   meaningful in the case of 'constant velocity' spiral scans
                   and should not be specified for this case.
    
                   See _array_structure_list_axis.angular_pitch.
    
    ;
        _item.name                 '_array_structure_list_axis.angle_increment'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__array_structure_list_axis.displacement
        _item_description.description
    ;              The setting of the specified axis in millimetres for the first
                   data point of the array index with the corresponding value
                   of _array_structure_list.axis_set_id.  If the index is
                   specified as 'increasing', this will be the centre of the
                   pixel with index value 1.  If the index is specified as
                   'decreasing', this will be the centre of the pixel with
                   maximum index value.
    ;
        _item.name               '_array_structure_list_axis.displacement'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    save__array_structure_list_axis.fract_displacement
        _item_description.description
    ;              The setting of the specified axis as a decimal fraction of 
                   the axis unit vector for the first data point of the array 
                   index with the corresponding value of 
                   _array_structure_list.axis_set_id.  
                   If the index is specified as 'increasing', this will be the 
                   centre of the pixel with index value 1.  If the index is 
                   specified as 'decreasing', this will be the centre of the 
                   pixel with maximum index value.
    ;
        _item.name               '_array_structure_list_axis.fract_displacement'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
         save_
    
    save__array_structure_list_axis.displacement_increment
        _item_description.description
    ;              The pixel-centre-to-pixel-centre increment for the displacement
                   setting of the specified axis in millimetres.
    ;
        _item.name
            '_array_structure_list_axis.displacement_increment'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    save__array_structure_list_axis.fract_displacement_increment
        _item_description.description
    ;              The pixel-centre-to-pixel-centre increment for the displacement
                   setting of the specified axis as a decimal fraction of the
                   axis unit vector.
    ;
        _item.name
            '_array_structure_list_axis.fract_displacement_increment'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__array_structure_list_axis.angular_pitch
        _item_description.description
    ;              The pixel-centre-to-pixel-centre distance for a one-step
                   change in the setting of the specified axis in millimetres.
    
                   This is meaningful only for 'constant velocity' spiral scans
                   or for uncoupled angular scans at a constant radius
                   (cylindrical scans) and should not be specified for cases
                   in which the angle between pixels (rather than the distance
                   between pixels) is uniform.
    
                   See _array_structure_list_axis.angle_increment.
    ;
        _item.name               '_array_structure_list_axis.angular_pitch'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__array_structure_list_axis.radial_pitch
        _item_description.description
    ;              The radial distance from one 'cylinder' of pixels to the
                   next in millimetres.  If the scan is a 'constant velocity'
                   scan with differing angular displacements between pixels,
                   the value of this item may differ significantly from the
                   value of _array_structure_list_axis.displacement_increment.
    ;
        _item.name               '_array_structure_list_axis.radial_pitch'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__array_structure_list_axis.reference_angle
         _item_description.description
    ;              The value of _array_structure_list_axis.reference_angle
                   specifies the setting of the angle of this axis used for 
                   determining a reference beam center and a reference detector 
                   distance.  It is normally expected to be identical to the 
                   value of _array_structure_list.angle.
    
    ;
         _item.name '_array_structure_list_axis.reference_angle'
         _item.category_id          array_structure_list_axis
         _item.mandatory_code       implicit
         _item_type.code            float
         _item_units.code           'degrees'
          save_
    
    
    save__array_structure_list_axis.reference_displacement
         _item_description.description
    ;              The value of _array_structure_list_axis.reference_displacement
                   specifies the setting of the displacement of this axis used 
                   for determining a reference beam center and a reference detector
                   distance.  It is normally expected to be identical to the value
                   of _array_structure_list.displacement.
    
    ;
         _item.name '_array_structure_list_axis.reference_displacement'
         _item.category_id          array_structure_list_axis
         _item.mandatory_code       implicit
         _item_type.code            float
         _item_units.code           'millimetres'
          save_
    
    
    
    
    ########
    # AXIS #
    ########
    
    save_AXIS
        _category.description
    ;    Data items in the AXIS category record the information required
         to describe the various goniometer, detector, source and other
         axes needed to specify a data collection or the axes defining the
         coordinate system of an image.  
         
         The location of each axis is specified by two vectors: the axis 
         itself, given by a  unit vector in the direction of the axis, and 
         an offset to the base of the unit vector.  
         
         The vectors defining an axis are referenced to an appropriate
         coordinate system.  The axis vector, itself, is a dimensionless
         unit vector.  Where meaningful, the offset vector is given in
         millimetres.  In coordinate systems not measured in metres,
         the offset is not specified and is taken as zero. 
         
         The available coordinate systems are:
         
             The imgCIF standard laboratory coordinate system
             The direct lattice (fractional atomic coordinates)
             The orthogonal Cartesian coordinate system (real space)
             The reciprocal lattice
             An abstract orthogonal Cartesian coordinate frame
          
         For consistency in this discussion, we call the three coordinate 
         system axes X, Y and Z.  This is appropriate for the imgCIF
         standard laboratory coordinate system, and last two Cartesian
         coordinate systems, but for the direct lattice, X corresponds
         to a, Y to b and Z to c, while for the reciprocal lattice,
         X corresponds to a*, Y to b* and Z to c*.
         
         For purposes of visualization, all the coordinate systems are 
         taken as right-handed, i.e., using the convention that the extended 
         thumb of a right hand could point along the first (X) axis, the 
         straightened pointer finger could point along the second (Y) axis 
         and the middle finger folded inward could point along the third (Z)
         axis.  
         
         THE IMGCIF STANDARD LABORATORY COORDINATE SYSTEM
         
         The imgCIF standard laboratory coordinate system is a right-handed   
         orthogonal coordinate similar to the MOSFLM coordinate system,  
         but imgCIF puts Z along the X-ray beam, rather than putting X along the
         X-ray beam as in MOSFLM.
         
         The vectors for the imgCIF standard laboratory coordinate system
         form a right-handed Cartesian coordinate system with its origin
         in the sample or specimen.  The origin of the axis system should,
         if possible, be defined in terms of mechanically stable axes to be
         in the sample and in the beam.  If the sample goniometer or other
         sample positioner has two axes the intersection which defines a
         unique point at which the sample should be mounted to be bathed
         by the beam, that will be the origin of the axis system.  If no such
         point is defined, then the midpoint of the line of intersection
         between the sample and the center of the beam will define the origin.
         For this definition the sample positioning system will be set at 
         its initial reference position for the experiment.
    
    
                                 | Y (to complete right-handed system)
                                 |
                                 |
                                 |
                                 |
                                 |
                                 |________________X
                                /       principal goniometer axis
                               /
                              /
                             /
                            /
                           /Z (to source)
    
    
    
    
         Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from
         the sample or specimen along the  principal axis of the goniometer or
         sample positioning system if the sample positioning system has an axis that
         intersects the origin and which form an angle of more than 22.5 degrees
         with the beam axis.
         
         Axis 2 (Y): The Y-axis completes an orthogonal right-handed system
         defined by the X-axis and the Z-axis (see below).
    
         Axis 3 (Z): The Z-axis is derived from the source axis which goes from
         the sample to the source.  The Z-axis is the component of the source axis
         in the direction of the source orthogonal to the X-axis in the plane
         defined by the X-axis and the source axis.
    
         If the conditions for the X-axis can be met, the coordinate system
         will be based on the goniometer or other sample positioning system
         and the beam and not on the orientation of the detector, gravity etc.  
         The vectors necessary to specify all other axes are given by sets of 
         three components in the order (X, Y, Z).
         If the axis involved is a rotation axis, it is right-handed, i.e. as
         one views the object to be rotated from the origin (the tail) of the
         unit vector, the rotation is clockwise.  If a translation axis is
         specified, the direction of the unit vector specifies the sense of
         positive translation.
    
         Note:  This choice of coordinate system is similar to but significantly
         different from the choice in MOSFLM (Leslie & Powell, 2004).  In MOSFLM,
         X is along the X-ray beam (the CBF/imgCIF Z axis) and Z is along the
         rotation axis.
         
         In some experimental techniques, there is no goniometer or the principal
         axis of the goniometer is at a small acute angle with respect to
         the source axis.  In such cases, other reference axes are needed
         to define a useful coordinate system.  The order of priority in
         defining directions in such cases is to use the detector, then
         gravity, then north.
         
         
         If the X-axis cannot be defined as above, then the
         direction (not the origin) of the X-axis should be parallel to the axis 
         of the primary detector element corresponding to the most rapidly 
         varying dimension of that detector element's data array, with its 
         positive sense corresponding to increasing values of the index for 
         that dimension.  If the detector is such that such a direction cannot 
         be defined (as with a point detector) or that direction forms an
         angle of less than 22.5 degrees with respect to the source axis, then 
         the X-axis should be chosen so that if the Y-axis is chosen 
         in the direction of gravity, and the Z-axis is chosen to be along 
         the source axis, a right-handed orthogonal coordinate system is chosen.  
         In the case of a vertical source axis, as a last resort, the 
         X-axis should be chosen to point North.
         
         All rotations are given in degrees and all translations are given in mm.
    
         Axes may be dependent on one another.  The X-axis is the only goniometer
         axis the direction of which is strictly connected to the hardware.  All
         other axes are specified by the positions they would assume when the
         axes upon which they depend are at their zero points.
    
         When specifying detector axes, the axis is given to the beam centre.
         The location of the beam centre on the detector should be given in the
         DIFFRN_DETECTOR category in distortion-corrected millimetres from
         the (0,0) corner of the detector.
    
         It should be noted that many different origins arise in the definition
         of an experiment.  In particular, as noted above, it is necessary to
         specify the location of the beam centre on the detector in terms
         of the origin of the detector, which is, of course, not coincident
         with the centre of the sample.
         
         The unit cell, reciprocal cell and crystallographic orthogonal 
         Cartesian coordinate system are defined by the CELL and the matrices 
         in the ATOM_SITES category.
         
         THE DIRECT LATTICE (FRACTIONAL COORDINATES)
         
         The direct lattice coordinate system is a system of fractional
         coordinates aligned to the crystal, rather than to the laboratory.
         This is a natural coordinate system for maps and atomic coordinates.
         It is the simplest coordinate system in which to apply symmetry.
         The axes are determined by the cell edges, and are not necessarily
         othogonal.  This coordinate system is not uniquely defined and 
         depends on the cell parameters in the CELL category and the
         settings chosen to index the crystal. 
         
         Molecules in a crystal studied by X-ray diffracraction are organized
         into a repeating regular array of unit cells.  Each unit cell is defined 
         by three vectors, a, b and c.  To quote from Drenth,
         
         
         "The choice of the unit cell is not unique and therefore, guidelines
         have been established for selecting the standard basis vectors and
         the origin.  They are based on symmetry and metric considerations:
         
          "(1)  The axial system should be right handed.
           (2)  The basis vectors should coincide as much as possible with
           directions of highest symmetry."
           (3)  The cell taken should be the smallest one that satisfies
           condition (2)
           (4)  Of all the lattice vectors, none is shorter than a.
           (5)  Of those not directed along a, none is shorter than b.
           (6)  Of those not lying in the ab plane, none is shorter than c.
           (7)  The three angles between the basis vectors a, b and c are
           either all acute (<90°) or all obtuse (≥90°)."
         
         These rules do not produce a unique result that is stable under
         the assumption of experimental errors, and the the resulting cell
         may not be primitive.
         
         In this coordinate system, the vector (.5, .5, .5) is in the middle
         of the given unit cell.
         
         Grid coordinates are an important variation on fractional coordinates
         used when working with maps.  In imgCIF, the conversion from
         fractional to grid coordinates is implicit in the array indexing
         specified by _array_structure_list.dimension.  Note that this
         implicit grid-coordinate scheme is 1-based, not zero-based, i.e.
         the origin of the cell for axes along the cell edges with no
         specified _array_structure_list_axis.displacement will have
         grid coordinates of (1,1,1), i.e. array indices of (1,1,1).
         
         THE ORTHOGONAL CARTESIAN COORDINATE SYSTEM (REAL SPACE)
         
         The orthogonal Cartesian coordinate system is a transformation of
         the direct lattice to the actual physical coordinates of atoms in
         space.  It is similar to the laboratory coordinate system, but
         is anchored to and moves with the crystal, rather than being
         schored to the laboratory.  The transformation from fractional
         to orthogonal cartesian coordinates is given by the
                  _atom_sites.Cartn_transf_matrix[i][j]  and
                  _atom_sites.Cartn_transf_vector[i]
         tags.  A common choice for the matrix of the transformation is 
         given in the 1992 PDB format document
         
                  | a      b cos(γ)   c cos(β)                         |
                  | 0      b sin(γ)   c (cos(α) - cos(β)cos(γ))/sin(γ) |
                  | 0      0          V/(a b sin(γ))                   |
         
         This is a convenient coordinate system in which to do fitting
         of models to maps and in which to understand the chemistry of
         a molecule.
         
         THE RECIPROCAL LATTICE
         
         The reciprocal lattice coordinate system is used for diffraction
         intensitities.  It is based on the reciprocal cell, the dual of the cell,
         in which reciprocal cell edges are derived from direct cell faces:
         
            a* = bc sin(α)/V  b* = ac sin(β)/V  c* = ab sin(γ)/V
            cos(α*) = (cos(β)  cos(γ) - cos(α))/(sin(β)  sin(γ))
            cos(β*)  = (cos(γ) cos(γ) - cos(β) )/(sin(α) sin(γ))
            cos(γ*) = (cos(α) cos(β)  - cos(γ))/(sin(α) sin(β))
            V = abc √(1 - cos(α)2 -  cos(β)2 - cos(γ)2 
                               + 2 cos(α) cos(β) cos(γ) )
         
         In this form the dimensions of the reciprocal lattice are in reciprocal
         Ångstroms (&A-1).  A dimensionless form can be obtained by 
         multiplying by the wavelength.  Reflections are commonly indexed against
         this coordinate system as (h, k, l) triples.
         
         
         References:
         
         Drenth, J., "Introduction to basic crystallography." chapter
         2.1 in Rossmann, M. G. and Arnold, E. "Crystallography of 
         biological macromolecules", Volume F of the IUCr's "International 
         tables for crystallography", Kluwer, Dordrecht 2001, pp 44 -- 63
    
         Leslie, A. G. W. and Powell, H. (2004). MOSFLM v6.11.
         MRC Laboratory of Molecular Biology, Hills Road, Cambridge, England.
         http://www.CCP4.ac.uk/dist/X-windows/Mosflm/.
         
         Stout, G. H. and Jensen, L. H., "X-ray structure determination",
         2nd ed., Wiley, New York, 1989, 453 pp.
         
         __, "PROTEIN DATA BANK ATOMIC COORDINATE AND BIBLIOGRAPHIC ENTRY
         FORMAT DESCRIPTION," Brookhaven National Laboratory, February 1992.
    ;
        _category.id                   axis
        _category.mandatory_code       no
         loop_
        _category_key.name          '_axis.id'
                                    '_axis.equipment'
         loop_
        _category_group.id           'inclusive_group'
                                     'axis_group'
                                     'diffrn_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;       Example 1 -
    
            This example shows the axis specification of the axes of a kappa-
            geometry goniometer [see Stout, G. H. & Jensen, L. H. (1989). X-ray
            structure determination. A practical
            guide, 2nd ed. p. 134. New York: Wiley Interscience].
    
            There are three axes specified, and no offsets.  The outermost axis,
            omega, is pointed along the X axis.  The next innermost axis, kappa,
            is at a 50 degree angle to the X axis, pointed away from the source.
            The innermost axis, phi, aligns with the X axis when omega and
            phi are at their zero points.  If T-omega, T-kappa and T-phi
            are the transformation matrices derived from the axis settings,
            the complete transformation would be:
                X' = (T-omega) (T-kappa) (T-phi) X
    ;
    ;
             loop_
            _axis.id
            _axis.type
            _axis.equipment
            _axis.depends_on
            _axis.vector[1] _axis.vector[2] _axis.vector[3]
            omega rotation goniometer     .    1        0        0
            kappa rotation goniometer omega    -.64279  0       -.76604
            phi   rotation goniometer kappa    1        0        0
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;       Example 2 -
    
            This example shows the axis specification of the axes of a
            detector, source and gravity.  The order has been changed as a
            reminder that the ordering of presentation of tokens is not
            significant.  The centre of rotation of the detector has been taken
            to be 68 millimetres in the direction away from the source.
    ;
    ;
            loop_
            _axis.id
            _axis.type
            _axis.equipment
            _axis.depends_on
            _axis.vector[1] _axis.vector[2] _axis.vector[3]
            _axis.offset[1] _axis.offset[2] _axis.offset[3]
            source       .        source     .       0     0     1   . . .
            gravity      .        gravity    .       0    -1     0   . . .
            tranz     translation detector rotz      0     0     1   0 0 -68
            twotheta  rotation    detector   .       1     0     0   . . .
            roty      rotation    detector twotheta  0     1     0   0 0 -68
            rotz      rotation    detector roty      0     0     1   0 0 -68
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;       Example 3 -
    
            This example show the axis specification of the axes for a map,
            using fractional coordinates.  Each cell edge has been divided
            into a grid of 50 divisions in the ARRAY_STRUCTURE_LIST_AXIS 
            category.  The map is using only the first octant of the grid
            in the ARRAY_STRUCTURE_LIST category.
    
            The fastest changing axis is the gris along A, then along B,
            and the slowest is along C. 
            
            The map sampling is being done in the middle of each grid
            division
            
    ;
    ;
            loop_
            _axis.id
            _axis.system
            _axis.vector[1] _axis.vector[2] _axis.vector[3]
            CELL_A_AXIS    fractional       1 0 0
            CELL_B_AXIS    fractional       0 1 0
            CELL_C_AXIS    fractional       0 0 1
            
            loop_
            _array_structure_list.array_id
            _array_structure_list.index
            _array_structure_list.dimension
            _array_structure_list.precedence
            _array_structure_list.direction
            _array_structure_list.axis_id
            MAP 1 25 1 increasing CELL_A_AXIS
            MAP 1 25 2 increasing CELL_B_AXIS
            MAP 1 25 3 increasing CELL_C_AXIS
            
            loop_
            _array_structure_list_axis.axis_id
            _array_structure_list_axis.fract_displacement
            _array_structure_list_axis.fract_displacement_increment
            CELL_A_AXIS 0.01 0.02
            CELL_B_AXIS 0.01 0.02
            CELL_C_AXIS 0.01 0.02
    
            
            
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;       Example 4 -
    
            This example show the axis specification of the axes for a map,
            this time as orthogonal Angstroms, using the same coordinate system 
            as for the atomic coordinates.  The map is sampling every 1.5
            Angstroms (1.5e-7 millimeters) in a map segment 37.5 Angstroms on 
            a side.
            
    ;
    ;
            loop_
            _axis.id
            _axis.system
            _axis.vector[1] _axis.vector[2] _axis.vector[3]
            X    orthogonal       1 0 0
            Y    orthogonal       0 1 0
            Z    orthogonal       0 0 1
            
                    loop_
            _array_structure_list.array_id
            _array_structure_list.index
            _array_structure_list.dimension
            _array_structure_list.precedence
            _array_structure_list.direction
            _array_structure_list.axis_id
            MAP 1 25 1 increasing X
            MAP 2 25 2 increasing Y
            MAP 3 25 3 increasing Z
            
            loop_
            _array_structure_list_axis.axis_id
            _array_structure_list_axis.displacement
            _array_structure_list_axis.displacement_increment
            X 7.5e-8 1.5e-7
            Y 7.5e-8 1.5e-7
            Z 7.5e-8 1.5e-7
    
    
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__axis.depends_on
        _item_description.description
    ;             The value of _axis.depends_on specifies the next outermost
                  axis upon which this axis depends.
    
                  This item is a pointer to _axis.id in the same category.
    ;
        _item.name                      '_axis.depends_on'
        _item.category_id                 axis
        _item.mandatory_code              no
    
         save_
    
    
    save__axis.equipment
        _item_description.description
    ;             The value of  _axis.equipment specifies the type of
                  equipment using the axis:  'goniometer', 'detector',
                  'gravity', 'source' or 'general'.
    ;
        _item.name                      '_axis.equipment'
        _item.category_id                 axis
        _item.mandatory_code              no
        _item_type.code                   ucode
        _item_default.value               general
         loop_
        _item_enumeration.value
        _item_enumeration.detail   goniometer
                                  'equipment used to orient or position samples'
                                   detector
                                  'equipment used to detect reflections'
                                   general
                                  'equipment used for general purposes'
                                   gravity
                                  'axis specifying the downward direction'
                                   source
                                  'axis specifying the direction sample to source'
    
         save_
    
    
    save__axis.offset[1]
        _item_description.description
    ;              The [1] element of the three-element vector used to specify
                   the offset to the base of a rotation or translation axis.
    
                   The vector is specified in millimetres.
    ;
        _item.name                  '_axis.offset[1]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    
    save__axis.offset[2]
        _item_description.description
    ;              The [2] element of the three-element vector used to specify
                   the offset to the base of a rotation or translation axis.
    
                   The vector is specified in millimetres.
    ;
        _item.name                  '_axis.offset[2]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    
    save__axis.offset[3]
        _item_description.description
    ;              The [3] element of the three-element vector used to specify
                   the offset to the base of a rotation or translation axis.
    
                   The vector is specified in millimetres.
    ;
        _item.name                  '_axis.offset[3]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    
    save__axis.id
        _item_description.description
    ;             The value of _axis.id must uniquely identify
                  each axis relevant to the experiment.  Note that multiple
                  pieces of equipment may share the same axis (e.g. a twotheta
                  arm), so the category key for AXIS also includes the
                  equipment.
    ;
        loop_
        _item.name
        _item.category_id
        _item.mandatory_code
             '_axis.id'                         axis                    yes
             '_array_structure_list_axis.axis_id'
                                                array_structure_list_axis
                                                                        yes
             '_diffrn_detector_axis.axis_id'    diffrn_detector_axis    yes
             '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes
             '_diffrn_scan_axis.axis_id'        diffrn_scan_axis        yes
             '_diffrn_scan_frame_axis.axis_id'  diffrn_scan_frame_axis  yes
    
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
             '_axis.depends_on'                   '_axis.id'
             '_array_structure_list_axis.axis_id' '_axis.id'
             '_diffrn_detector_axis.axis_id'      '_axis.id'
             '_diffrn_measurement_axis.axis_id'   '_axis.id'
             '_diffrn_scan_axis.axis_id'          '_axis.id'
             '_diffrn_scan_frame_axis.axis_id'    '_axis.id'
    
         save_
    
    save__axis.system
        _item_description.description
    ;             The value of  _axis.system specifies the coordinate
                  system used to define the axis: 'laboratory', 'direct', 'orthogonal',
                  'reciprocal' or 'abstract'.
    ;
        _item.name                      '_axis.system'
        _item.category_id                 axis
        _item.mandatory_code              no
        _item_type.code                   ucode
        _item_default.value               laboratory
         loop_
        _item_enumeration.value
        _item_enumeration.detail   
    
    laboratory
    ;  the axis is referenced to the imgCIF standard laboratory Cartesian
       coordinate system
    ;
    
    direct
    ;  the axis is referenced to the direct lattice
    ;
    
    orthogonal
    ;  the axis is referenced to the cell Cartesian orthogonal coordinates
    ;
    
    reciprocal
    ;  the axis is referenced to the reciprocal lattice
    ;
    
    abstract
    ;  the axis is referenced to abstract Cartesian cooridinate system
    ;
    
         save_
    
    
    save__axis.type
        _item_description.description
    ;             The value of _axis.type specifies the type of
                  axis:  'rotation' or 'translation' (or 'general' when
                  the type is not relevant, as for gravity).
    ;
        _item.name                      '_axis.type'
        _item.category_id                 axis
        _item.mandatory_code              no
        _item_type.code                   ucode
        _item_default.value               general
         loop_
        _item_enumeration.value
        _item_enumeration.detail      rotation
                                     'right-handed axis of rotation'
                                      translation
                                     'translation in the direction of the axis'
                                      general
                                     'axis for which the type is not relevant'
    
         save_
    
    
    save__axis.vector[1]
        _item_description.description
    ;              The [1] element of the three-element vector used to specify
                   the direction of a rotation or translation axis.
                   The vector should be normalized to be a unit vector and
                   is dimensionless.
    ;
        _item.name                  '_axis.vector[1]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
         save_
    
    save__axis.vector[2]
        _item_description.description
    ;              The [2] element of the three-element vector used to specify
                   the direction of a rotation or translation axis.
                   The vector should be normalized to be a unit vector and
                   is dimensionless.
    ;
        _item.name                  '_axis.vector[2]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
         save_
    
    save__axis.vector[3]
        _item_description.description
    ;              The [3] element of the three-element vector used to specify
                   the direction of a rotation or translation axis.
                   The vector should be normalized to be a unit vector and
                   is dimensionless.
    ;
        _item.name                  '_axis.vector[3]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
         save_
    
    
    
    #####################
    # DIFFRN_DATA_FRAME #
    #####################
    
    
    save_DIFFRN_DATA_FRAME
        _category.description
    ;             Data items in the DIFFRN_DATA_FRAME category record
                  the details about each frame of data.
    
                  The items in this category were previously in a
                  DIFFRN_FRAME_DATA category, which is now deprecated.
                  The items from the old category are provided
                  as aliases but should not be used for new work.
    ;
        _category.id                   diffrn_data_frame
        _category.mandatory_code       no
         loop_
        _category_key.name             '_diffrn_data_frame.id'
                                       '_diffrn_data_frame.detector_element_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;   Example 1 - A frame containing data from 4 frame elements.
                    Each frame element has a common array configuration
                    'array_1' described in ARRAY_STRUCTURE and related
                    categories.  The data for each detector element are
                    stored in four groups of binary data in the
                    ARRAY_DATA category, linked by the array_id and
                    binary_id.
    ;
    ;
            loop_
            _diffrn_data_frame.id
            _diffrn_data_frame.detector_element_id
            _diffrn_data_frame.array_id
            _diffrn_data_frame.binary_id
            frame_1   d1_ccd_1  array_1  1
            frame_1   d1_ccd_2  array_1  2
            frame_1   d1_ccd_3  array_1  3
            frame_1   d1_ccd_4  array_1  4
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
    
    
    save__diffrn_data_frame.array_id
        _item_description.description
    ;             This item is a pointer to _array_structure.id in the
                  ARRAY_STRUCTURE category.
    ;
        _item.name                  '_diffrn_data_frame.array_id'
        _item.category_id             diffrn_data_frame
        _item.mandatory_code          yes
        _item_aliases.alias_name    '_diffrn_frame_data.array_id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         save_
    
    
    save__diffrn_data_frame.binary_id
        _item_description.description
    ;             This item is a pointer to _array_data.binary_id in the
                  ARRAY_DATA category.
    ;
        _item.name                  '_diffrn_data_frame.binary_id'
        _item.category_id             diffrn_data_frame
        _item.mandatory_code          implicit
        _item_aliases.alias_name    '_diffrn_frame_data.binary_id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               int
         save_
    
    
    save__diffrn_data_frame.detector_element_id
        _item_description.description
    ;              This item is a pointer to _diffrn_detector_element.id
                   in the DIFFRN_DETECTOR_ELEMENT category.
    ;
        _item.name                  '_diffrn_data_frame.detector_element_id'
        _item.category_id             diffrn_data_frame
        _item.mandatory_code          yes
        _item_aliases.alias_name    '_diffrn_frame_data.detector_element_id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         save_
    
    
    save__diffrn_data_frame.id
        _item_description.description
    ;             The value of _diffrn_data_frame.id must uniquely identify
                  each complete frame of data.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
               '_diffrn_data_frame.id'        diffrn_data_frame  yes
               '_diffrn_refln.frame_id'       diffrn_refln       yes
               '_diffrn_scan.frame_id_start'  diffrn_scan        yes
               '_diffrn_scan.frame_id_end'    diffrn_scan        yes
               '_diffrn_scan_frame.frame_id'  diffrn_scan_frame  yes
               '_diffrn_scan_frame_axis.frame_id'
                                              diffrn_scan_frame_axis
                                                                 yes
        _item_aliases.alias_name    '_diffrn_frame_data.id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_diffrn_refln.frame_id'        '_diffrn_data_frame.id'
               '_diffrn_scan.frame_id_start'   '_diffrn_data_frame.id'
               '_diffrn_scan.frame_id_end'     '_diffrn_data_frame.id'
               '_diffrn_scan_frame.frame_id'   '_diffrn_data_frame.id'
               '_diffrn_scan_frame_axis.frame_id'
                                               '_diffrn_data_frame.id'
         save_
    
    
    save__diffrn_data_frame.details
         _item_description.description
    ;              The value of _diffrn_data_frame.details should give a
                   description of special aspects of each frame of data.
    
                   This is an appropriate location in which to record
                   information from vendor headers as presented in those
                   headers, but it should never be used as a substitute
                   for providing the fully parsed information within
                   the appropriate imgCIF/CBF categories.
    ;
        _item.name                  '_diffrn_data_frame.details'
        _item.category_id             diffrn_data_frame
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_frame_data.details'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.4
        _item_type.code               text
         loop_
        _item_examples.case
        _item_examples.detail
    ;
     HEADER_BYTES = 512;
     DIM = 2;
     BYTE_ORDER = big_endian;
     TYPE = unsigned_short;
     SIZE1 = 3072;
     SIZE2 = 3072;
     PIXEL_SIZE = 0.102588;
     BIN = 2x2;
     DETECTOR_SN = 901;
     TIME = 29.945155;
     DISTANCE = 200.000000;
     PHI = 85.000000;
     OSC_START = 85.000000;
     OSC_RANGE = 1.000000;
     WAVELENGTH = 0.979381;
     BEAM_CENTER_X = 157.500000;
     BEAM_CENTER_Y = 157.500000;
     PIXEL SIZE = 0.102588;
     OSCILLATION RANGE = 1;
     EXPOSURE TIME = 29.9452;
     TWO THETA = 0;
     BEAM CENTRE = 157.5 157.5;
    ;
    ;               Example of header information extracted from an ADSC Quantum
                    315 detector header by CBFlib_0.7.6.  Image provided by Chris
                    Nielsen of ADSC from a data collection at SSRL beamline 1-5.
    ;
          save_
    
    
    
    ##########################################################################
    #  The following is a restatement of the mmCIF DIFFRN_DETECTOR,          #
    #  DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for      #
    #  the CBF/imgCIF extensions                                             #
    ##########################################################################
    
    ###################
    # DIFFRN_DETECTOR #
    ###################
    
    
    save_DIFFRN_DETECTOR
        _category.description
    ;              Data items in the DIFFRN_DETECTOR category describe the
                   detector used to measure the scattered radiation, including
                   any analyser and post-sample collimation.
    ;
        _category.id                  diffrn_detector
        _category.mandatory_code      no
         loop_
        _category_key.name          '_diffrn_detector.diffrn_id'
                                    '_diffrn_detector.id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;   Example 1 - based on PDB entry 5HVP and laboratory records for the
                    structure corresponding to PDB entry 5HVP.
    ;
    ;
        _diffrn_detector.diffrn_id             'd1'
        _diffrn_detector.detector              'multiwire'
        _diffrn_detector.type                  'Siemens'
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__diffrn_detector.details
        _item_description.description
    ;              A description of special aspects of the radiation detector.
    ;
        _item.name                  '_diffrn_detector.details'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_detector_details'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code                   text
        _item_examples.case        'slow mode'
         save_
    
    
    save__diffrn_detector.detector
        _item_description.description
    ;              The general class of the radiation detector.
    ;
        _item.name                  '_diffrn_detector.detector'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
         loop_
        _item_aliases.alias_name
        _item_aliases.dictionary
        _item_aliases.version       '_diffrn_radiation_detector'
                                      cifdic.c91
                                      1.0
                                    '_diffrn_detector'
                                      cif_core.dic
                                      2.0
        _item_type.code               text
         loop_
        _item_examples.case          'photographic film'
                                     'scintillation counter'
                                     'CCD plate'
                                     'BF~3~ counter'
         save_
    
    
    save__diffrn_detector.diffrn_id
        _item_description.description
    ;              This data item is a pointer to _diffrn.id in the DIFFRN
                   category.
    
                   The value of _diffrn.id uniquely defines a set of
                   diffraction data.
    ;
        _item.name                  '_diffrn_detector.diffrn_id'
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_detector.dtime
        _item_description.description
    ;              The deadtime in microseconds of the detector(s) used to
                   measure the diffraction intensities.
    ;
        _item.name                  '_diffrn_detector.dtime'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
         loop_
        _item_aliases.alias_name
        _item_aliases.dictionary
        _item_aliases.version       '_diffrn_radiation_detector_dtime'
                                      cifdic.c91
                                      1.0
                                    '_diffrn_detector_dtime'
                                      cif_core.dic
                                      2.0
         loop_
        _item_range.maximum
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
        _item_units.code              microseconds
         save_
    
    
    save__diffrn_detector.id
        _item_description.description
    ;              The value of _diffrn_detector.id must uniquely identify
                   each detector used to collect each diffraction data set.
    
                   If the value of _diffrn_detector.id is not given, it is
                   implicitly equal to the value of
                   _diffrn_detector.diffrn_id.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
                 '_diffrn_detector.id'         diffrn_detector       implicit
                 '_diffrn_detector_axis.detector_id'
                                               diffrn_detector_axis       yes
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_detector_axis.detector_id'
                                             '_diffrn_detector.id'
    
        _item_type.code               code
         save_
    
    
    save__diffrn_detector.number_of_axes
        _item_description.description
    ;              The value of _diffrn_detector.number_of_axes gives the
                   number of axes of the positioner for the detector identified
                   by _diffrn_detector.id.
    
                   The word 'positioner' is a general term used in
                   instrumentation design for devices that are used to change
                   the positions of portions of apparatus by linear
                   translation, rotation or combinations of such motions.
    
                   Axes which are used to provide a coordinate system for the
                   face of an area detetctor should not be counted for this
                   data item.
    
                   The description of each axis should be provided by entries
                   in DIFFRN_DETECTOR_AXIS.
    ;
        _item.name                  '_diffrn_detector.number_of_axes'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
         loop_
        _item_range.maximum
        _item_range.minimum           .   1
                                      1   1
        _item_type.code               int
         save_
    
    
    save__diffrn_detector.type
        _item_description.description
    ;              The make, model or name of the detector device used.
    ;
        _item.name                  '_diffrn_detector.type'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_detector_type'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         save_
    
    
    ########################
    # DIFFRN_DETECTOR_AXIS #
    ########################
    
    
    save_DIFFRN_DETECTOR_AXIS
        _category.description
    ;    Data items in the DIFFRN_DETECTOR_AXIS category associate
         axes with detectors.
    ;
        _category.id                   diffrn_detector_axis
        _category.mandatory_code       no
         loop_
        _category_key.name          '_diffrn_detector_axis.detector_id'
                                    '_diffrn_detector_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_detector_axis.axis_id
        _item_description.description
    ;              This data item is a pointer to _axis.id in
                   the AXIS category.
    ;
        _item.name                  '_diffrn_detector_axis.axis_id'
        _item.category_id             diffrn_detector_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_detector_axis.detector_id
        _item_description.description
    ;              This data item is a pointer to _diffrn_detector.id in
                   the DIFFRN_DETECTOR category.
    
                   This item was previously named _diffrn_detector_axis.id
                   which is now a deprecated name.  The old name is
                   provided as an alias but should not be used for new work.
    ;
        _item.name                  '_diffrn_detector_axis.detector_id'
        _item.category_id             diffrn_detector_axis
        _item.mandatory_code          yes
        _item_aliases.alias_name    '_diffrn_detector_axis.id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         save_
    
    
    ###########################
    # DIFFRN_DETECTOR_ELEMENT #
    ###########################
    
    
    save_DIFFRN_DETECTOR_ELEMENT
        _category.description
    ;             Data items in the DIFFRN_DETECTOR_ELEMENT category record
                  the details about spatial layout and other characteristics
                  of each element of a detector which may have multiple elements.
    
                  In most cases, giving more detailed information
                  in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS
                  is preferable to simply providing the centre of the
                  detector element.
    ;
        _category.id                   diffrn_detector_element
        _category.mandatory_code       no
         loop_
        _category_key.name             '_diffrn_detector_element.id'
                                       '_diffrn_detector_element.detector_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;       Example 1 - Detector d1 is composed of four CCD detector elements,
            each 200 mm by 200 mm, arranged in a square, in the pattern
    
                       1     2
                          *
                       3     4
    
            Note that the beam centre is slightly displaced from each of the
            detector elements, just beyond the lower right corner of 1,
            the lower left corner of 2, the upper right corner of 3 and
            the upper left corner of 4.
    ;
    ;
            loop_
            _diffrn_detector_element.detector_id
            _diffrn_detector_element.id
            _diffrn_detector_element.center[1]
            _diffrn_detector_element.center[2]
            d1     d1_ccd_1  201.5 -1.5
            d1     d1_ccd_2  -1.8  -1.5
            d1     d1_ccd_3  201.6 201.4
            d1     d1_ccd_4  -1.7  201.5
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
    
    
    save__diffrn_detector_element.center[1]
        _item_description.description
    ;             The value of _diffrn_detector_element.center[1] is the X
                  component of the distortion-corrected beam centre in
                  millimetres from the (0, 0) (lower-left) corner of the
                  detector element viewed from the sample side.
    
                  The X and Y axes are the laboratory coordinate system
                  coordinates defined in the AXIS category measured
                  when all positioning axes for the detector are at their zero
                  settings.  If the resulting X or Y axis is then orthogonal to the
                  detector, the Z axis is used instead of the orthogonal axis.
    
    ;
        _item.name                  '_diffrn_detector_element.center[1]'
        _item.category_id             diffrn_detector_element
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
    
        save_
    
    
    save__diffrn_detector_element.center[2]
        _item_description.description
    ;             The value of _diffrn_detector_element.center[2] is the Y
                  component of the distortion-corrected beam centre in
                  millimetres from the (0, 0) (lower-left) corner of the
                  detector element viewed from the sample side.
    
                  The X and Y axes are the laboratory coordinate system
                  coordinates defined in the AXIS category measured
                  when all positioning axes for the detector are at their zero
                  settings.  If the resulting X or Y axis is then orthogonal to the
                  detector, the Z axis is used instead of the orthogonal axis.
    
    ;
        _item.name                  '_diffrn_detector_element.center[2]'
        _item.category_id             diffrn_detector_element
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
    
        save_
    
    
    save__diffrn_detector_element.id
        _item_description.description
    ;             The value of _diffrn_detector_element.id must uniquely
                  identify each element of a detector.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
               '_diffrn_detector_element.id'
               diffrn_detector_element
               yes
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_diffrn_data_frame.detector_element_id'
               '_diffrn_detector_element.id'
    
         save_
    
    
    save__diffrn_detector_element.detector_id
        _item_description.description
    ;              This item is a pointer to _diffrn_detector.id
                   in the DIFFRN_DETECTOR category.
    ;
        _item.name                  '_diffrn_detector_element.detector_id'
        _item.category_id             diffrn_detector_element
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    save__diffrn_detector_element.reference_center_fast
         _item_description.description
    ;             The value of _diffrn_detector_element.reference_center_fast is 
                  the fast index axis beam center position relative to the detector
                  element face in millimetres along that from the first pixel to 
                  the point at which the Z-axis (which should be colinear with the 
                  beam) intersects the face of the detector, if in fact is does.   
                  At the time of the measurement all settings of the detector
                  positioner should be at their reference settings.  If more than 
                  one reference setting has been used the value given whould be 
                  representive of the beam center as determined from the ensemble 
                  of settings.
    
                  It is important to note that the sense of the axis is used, 
                  rather than the sign of the pixel-to-pixel increments.
    
    ;
         _item.name '_diffrn_detector_element.reference_center_fast'
         _item.category_id             diffrn_detector_element
         _item.mandatory_code          no
         _item_type.code               float
         _item_units.code              millimetres
    
         save_
    
    
    save__diffrn_detector_element.reference_center_slow
         _item_description.description
    ;             The value of _diffrn_detector_element.reference_center_slow is
                  the slow index axis beam center position relative to the detector
                  element face in millimetres along that from the first pixel to
                  the point at which the Z-axis (which should be colinear with the
                  beam) intersects the face of the detector, if in fact is does.
                  At the time of the measurement all settings of the detector
                  positioner should be at their reference settings.  If more than
                  one reference setting has been used the value givien whould be 
                  representive of the beam center as determined from the ensemble
                  of settings.
    
                  It is important to note that the sense of the axis is used,
                  rather than the sign of the pixel-to-pixel increments.
    
    ;
         _item.name '_diffrn_detector_element.reference_center_slow'
         _item.category_id             diffrn_detector_element
         _item.mandatory_code          no
         _item_type.code               float
         _item_units.code              millimetres
    
         save_
    
    
    
    
    ########################
    ## DIFFRN_MEASUREMENT ##
    ########################
    
    
    save_DIFFRN_MEASUREMENT
        _category.description
    ;              Data items in the DIFFRN_MEASUREMENT category record details
                   about the device used to orient and/or position the crystal
                   during data measurement and the manner in which the
                   diffraction data were measured.
    ;
        _category.id                  diffrn_measurement
        _category.mandatory_code      no
         loop_
        _category_key.name          '_diffrn_measurement.device'
                                    '_diffrn_measurement.diffrn_id'
                                    '_diffrn_measurement.id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;    Example 1 - based on PDB entry 5HVP and laboratory records for the
                     structure corresponding to PDB entry 5HVP
    ;
    ;
        _diffrn_measurement.diffrn_id          'd1'
        _diffrn_measurement.device             '3-circle camera'
        _diffrn_measurement.device_type        'Supper model X'
        _diffrn_measurement.device_details     'none'
        _diffrn_measurement.method             'omega scan'
        _diffrn_measurement.details
        ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector
          angle 22.5 degrees
        ;
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;     Example 2 - based on data set TOZ of Willis, Beckwith & Tozer
                      [Acta Cryst. (1991), C47, 2276-2277].
    ;
    ;
        _diffrn_measurement.diffrn_id       's1'
        _diffrn_measurement.device_type     'Philips PW1100/20 diffractometer'
        _diffrn_measurement.method          'theta/2theta (\q/2\q)'
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__diffrn_measurement.device
        _item_description.description
    ;              The general class of goniometer or device used to support
                   and orient the specimen.
    
                   If the value of _diffrn_measurement.device is not given,
                   it is implicitly equal to the value of
                   _diffrn_measurement.diffrn_id.
    
                   Either _diffrn_measurement.device or
                   _diffrn_measurement.id may be used to link to other
                   categories.  If the experimental setup admits multiple
                   devices, then _diffrn_measurement.id is used to provide
                   a unique link.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
                 '_diffrn_measurement.device'  diffrn_measurement      implicit
                 '_diffrn_measurement_axis.measurement_device'
                                               diffrn_measurement_axis implicit
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_measurement_axis.measurement_device'
                                             '_diffrn_measurement.device'
        _item_aliases.alias_name    '_diffrn_measurement_device'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          '3-circle camera'
                                     '4-circle camera'
                                     'kappa-geometry camera'
                                     'oscillation camera'
                                     'precession camera'
         save_
    
    
    save__diffrn_measurement.device_details
        _item_description.description
    ;              A description of special aspects of the device used to
                   measure the diffraction intensities.
    ;
        _item.name                  '_diffrn_measurement.device_details'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_device_details'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
        _item_examples.case
    ;                                 commercial goniometer modified locally to
                                      allow for 90\% \t arc
    ;
         save_
    
    
    save__diffrn_measurement.device_type
        _item_description.description
    ;              The make, model or name of the measurement device
                   (goniometer) used.
    ;
        _item.name                  '_diffrn_measurement.device_type'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_device_type'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          'Supper model q'
                                     'Huber model r'
                                     'Enraf-Nonius model s'
                                     'home-made'
         save_
    
    
    save__diffrn_measurement.diffrn_id
        _item_description.description
    ;              This data item is a pointer to _diffrn.id in the DIFFRN
                   category.
    ;
        _item.name                  '_diffrn_measurement.diffrn_id'
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_measurement.details
        _item_description.description
    ;              A description of special aspects of the intensity
                   measurement.
    ;
        _item.name                  '_diffrn_measurement.details'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_details'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
        _item_examples.case
    ;                                 440 frames, 0.20 degrees, 150 sec, detector
                                      distance 12 cm, detector angle 22.5 degrees
    ;
         save_
    
    
    save__diffrn_measurement.id
        _item_description.description
    ;              The value of _diffrn_measurement.id must uniquely identify
                   the set of mechanical characteristics of the device used to
                   orient and/or position the sample used during the collection
                   of each diffraction data set.
    
                   If the value of _diffrn_measurement.id is not given, it is
                   implicitly equal to the value of
                   _diffrn_measurement.diffrn_id.
    
                   Either _diffrn_measurement.device or
                   _diffrn_measurement.id may be used to link to other
                   categories.  If the experimental setup admits multiple
                   devices, then _diffrn_measurement.id is used to provide
                   a unique link.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
                 '_diffrn_measurement.id'      diffrn_measurement      implicit
                 '_diffrn_measurement_axis.measurement_id'
                                               diffrn_measurement_axis implicit
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_measurement_axis.measurement_id'
                                             '_diffrn_measurement.id'
    
        _item_type.code               code
         save_
    
    
    save__diffrn_measurement.method
        _item_description.description
    ;              Method used to measure intensities.
    ;
        _item.name                  '_diffrn_measurement.method'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_method'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
        _item_examples.case
          'profile data from theta/2theta (\q/2\q) scans'
         save_
    
    
    save__diffrn_measurement.number_of_axes
        _item_description.description
    ;              The value of _diffrn_measurement.number_of_axes gives the
                   number of axes of the positioner for the goniometer or
                   other sample orientation or positioning device identified
                   by _diffrn_measurement.id.
    
                   The description of the axes should be provided by entries in
                   DIFFRN_MEASUREMENT_AXIS.
    ;
        _item.name                  '_diffrn_measurement.number_of_axes'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
         loop_
        _item_range.maximum
        _item_range.minimum           .   1
                                      1   1
        _item_type.code               int
         save_
    
    
    save__diffrn_measurement.specimen_support
        _item_description.description
    ;              The physical device used to support the crystal during data
                   collection.
    ;
        _item.name                  '_diffrn_measurement.specimen_support'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_specimen_support'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          'glass capillary'
                                     'quartz capillary'
                                     'fiber'
                                     'metal loop'
         save_
    
    
    ###########################
    # DIFFRN_MEASUREMENT_AXIS #
    ###########################
    
    
    save_DIFFRN_MEASUREMENT_AXIS
        _category.description
    ;    Data items in the DIFFRN_MEASUREMENT_AXIS category associate
         axes with goniometers.
    ;
        _category.id                   diffrn_measurement_axis
        _category.mandatory_code       no
         loop_
        _category_key.name
                                  '_diffrn_measurement_axis.measurement_device'
                                    '_diffrn_measurement_axis.measurement_id'
                                    '_diffrn_measurement_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_measurement_axis.axis_id
        _item_description.description
    ;              This data item is a pointer to _axis.id in
                   the AXIS category.
    ;
        _item.name                  '_diffrn_measurement_axis.axis_id'
        _item.category_id             diffrn_measurement_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_measurement_axis.measurement_device
        _item_description.description
    ;              This data item is a pointer to _diffrn_measurement.device
                   in the DIFFRN_MEASUREMENT category.
    ;
        _item.name
          '_diffrn_measurement_axis.measurement_device'
        _item.category_id             diffrn_measurement_axis
        _item.mandatory_code          implicit
        _item_type.code               text
         save_
    
    
    save__diffrn_measurement_axis.measurement_id
        _item_description.description
    ;              This data item is a pointer to _diffrn_measurement.id in
                   the DIFFRN_MEASUREMENT category.
    
                   This item was previously named _diffrn_measurement_axis.id,
                   which is now a deprecated name.  The old name is
                   provided as an alias but should not be used for new work.
    ;
        _item.name                  '_diffrn_measurement_axis.measurement_id'
        _item.category_id             diffrn_measurement_axis
        _item.mandatory_code          implicit
        _item_aliases.alias_name    '_diffrn_measurement_axis.id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         save_
    
    
    ####################
    # DIFFRN_RADIATION #
    ####################
    
    
    save_DIFFRN_RADIATION
        _category.description
    ;              Data items in the DIFFRN_RADIATION category describe
                   the radiation used for measuring diffraction intensities,
                   its collimation and monochromatization before the sample.
    
                   Post-sample treatment of the beam is described by data
                   items in the DIFFRN_DETECTOR category.
    ;
        _category.id                  diffrn_radiation
        _category.mandatory_code      no
        _category_key.name          '_diffrn_radiation.diffrn_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;   Example 1 - based on PDB entry 5HVP and laboratory records for the
                    structure corresponding to PDB entry 5HVP
    ;
    ;
        _diffrn_radiation.diffrn_id            'set1'
    
        _diffrn_radiation.collimation          '0.3 mm double pinhole'
        _diffrn_radiation.monochromator        'graphite'
        _diffrn_radiation.type                 'Cu K\a'
        _diffrn_radiation.wavelength_id         1
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;    Example 2 - based on data set TOZ of Willis, Beckwith & Tozer
                    [Acta Cryst. (1991), C47, 2276-2277].
    ;
    ;
        _diffrn_radiation.wavelength_id    1
        _diffrn_radiation.type             'Cu K\a'
        _diffrn_radiation.monochromator    'graphite'
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    save__diffrn_radiation.collimation
        _item_description.description
    ;              The collimation or focusing applied to the radiation.
    ;
        _item.name                  '_diffrn_radiation.collimation'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_collimation'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          '0.3 mm double-pinhole'
                                     '0.5 mm'
                                     'focusing mirrors'
         save_
    
    
    save__diffrn_radiation.diffrn_id
        _item_description.description
    ;              This data item is a pointer to _diffrn.id in the DIFFRN
                   category.
    ;
        _item.name                  '_diffrn_radiation.diffrn_id'
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    
    save__diffrn_radiation.div_x_source
        _item_description.description
    ;              Beam crossfire in degrees parallel to the laboratory X axis
                   (see AXIS category).
    
                   This is a characteristic of the X-ray beam as it illuminates
                   the sample (or specimen) after all monochromation and
                   collimation.
    
                   This is the standard uncertainty (e.s.d.)  of the directions of
                   photons in the XZ plane around the mean source beam
                   direction.
    
                   Note that for some synchrotrons this value is specified
                   in milliradians, in which case a conversion is needed.
                   To convert a value in milliradians to a value in degrees,
                   multiply by 0.180 and divide by \p.
    ;
        _item.name                  '_diffrn_radiation.div_x_source'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_type.code               float
        _item_units.code              degrees
         save_
    
    
    save__diffrn_radiation.div_y_source
        _item_description.description
    ;              Beam crossfire in degrees parallel to the laboratory Y axis
                   (see AXIS category).
    
                   This is a characteristic of the X-ray beam as it illuminates
                   the sample (or specimen) after all monochromation and
                   collimation.
    
                   This is the standard uncertainty (e.s.d.) of the directions
                   of photons in the YZ plane around the mean source beam
                   direction.
    
                   Note that for some synchrotrons this value is specified
                   in milliradians, in which case a conversion is needed.
                   To convert a value in milliradians to a value in degrees,
                   multiply by 0.180 and divide by \p.
    ;
        _item.name                  '_diffrn_radiation.div_y_source'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_type.code               float
        _item_units.code              degrees
        _item_default.value           0.0
         save_
    
    
    save__diffrn_radiation.div_x_y_source
        _item_description.description
    ;              Beam crossfire correlation degrees^2^ between the
                   crossfire laboratory X-axis component and the crossfire
                   laboratory Y-axis component (see AXIS category).
    
                   This is a characteristic of the X-ray beam as it illuminates
                   the sample (or specimen) after all monochromation and
                   collimation.
    
                   This is the mean of the products of the deviations of the
                   direction of each photon in XZ plane times the deviations
                   of the direction of the same photon in the YZ plane
                   around the mean source beam direction.  This will be zero
                   for uncorrelated crossfire.
    
                   Note that some synchrotrons, this value is specified in
                   milliradians^2^, in which case a conversion would be needed.
                   To go from a value in milliradians^2^ to a value in
                   degrees^2^, multiply by 0.180^2^ and divide by \p^2^.
    
    ;
        _item.name                  '_diffrn_radiation.div_x_y_source'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_type.code               float
        _item_units.code              degrees_squared
        _item_default.value           0.0
         save_
    
    save__diffrn_radiation.filter_edge
        _item_description.description
    ;              Absorption edge in \%Angstroms of the radiation filter used.
    ;
        _item.name                  '_diffrn_radiation.filter_edge'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_filter_edge'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
        _item_units.code              angstroms
         save_
    
    save__diffrn_radiation.inhomogeneity
        _item_description.description
    ;              Half-width in millimetres of the incident beam in the
                   direction perpendicular to the diffraction plane.
    ;
        _item.name                  '_diffrn_radiation.inhomogeneity'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_inhomogeneity'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    save__diffrn_radiation.monochromator
        _item_description.description
    ;              The method used to obtain monochromatic radiation. If a
                   monochromator crystal is used, the material and the
                   indices of the Bragg reflection are specified.
    ;
        _item.name                  '_diffrn_radiation.monochromator'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_monochromator'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          'Zr filter'
                                     'Ge 220'
                                     'none'
                                     'equatorial mounted graphite'
         save_
    
    save__diffrn_radiation.polarisn_norm
        _item_description.description
    ;              The angle in degrees, as viewed from the specimen, between the
                   perpendicular component of the polarization and the diffraction
                   plane. See _diffrn_radiation_polarisn_ratio.
    ;
        _item.name                  '_diffrn_radiation.polarisn_norm'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_polarisn_norm'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum
        _item_range.minimum           90.0  90.0
                                      90.0 -90.0
                                     -90.0 -90.0
        _item_type.code               float
        _item_units.code              degrees
         save_
    
    save__diffrn_radiation.polarisn_ratio
        _item_description.description
    ;              Polarization ratio of the diffraction beam incident on the
                   crystal. This is the ratio of the perpendicularly polarized to
                   the parallel polarized component of the radiation. The
                   perpendicular component forms an angle of
                   _diffrn_radiation.polarisn_norm to the normal to the
                   diffraction plane of the sample (i.e. the plane containing
                   the incident and reflected beams).
    ;
        _item.name                  '_diffrn_radiation.polarisn_ratio'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_polarisn_ratio'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
         save_
    
    
    
    save__diffrn_radiation.polarizn_source_norm
        _item_description.description
    ;              The angle in degrees, as viewed from the specimen, between
                   the normal to the polarization plane and the laboratory Y
                   axis as defined in the AXIS category.
    
                   Note that this is the angle of polarization of the source
                   photons, either directly from a synchrotron beamline or
                   from a monochromater.
    
                   This differs from the value of
                   _diffrn_radiation.polarisn_norm
                   in that _diffrn_radiation.polarisn_norm refers to
                   polarization relative to the diffraction plane rather than
                   to the laboratory axis system.
    
                   In the case of an unpolarized beam, or a beam with true
                   circular polarization, in which no single plane of
                   polarization can be determined, the plane should be taken
                   as the XZ plane and the angle as 0.
    
                   See _diffrn_radiation.polarizn_source_ratio.
    ;
        _item.name                  '_diffrn_radiation.polarizn_source_norm'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
         loop_
        _item_range.maximum
        _item_range.minimum           90.0   90.0
                                      90.0  -90.0
                                     -90.0  -90.0
        _item_type.code               float
        _item_units.code              degrees
        _item_default.value           0.0
         save_
    
    
    save__diffrn_radiation.polarizn_source_ratio
        _item_description.description
    ;              (Ip-In)/(Ip+In), where Ip is the intensity
                   (amplitude squared) of the electric vector in the plane of
                   polarization and In is the intensity (amplitude squared)
                   of the electric vector in the plane of the normal to the
                   plane of polarization.
    
                   In the case of an unpolarized beam, or a beam with true
                   circular polarization, in which no single plane of
                   polarization can be determined, the plane is to be taken
                   as the XZ plane and the normal is parallel to the Y axis.
    
                   Thus, if there was complete polarization in the plane of
                   polarization, the value of
                   _diffrn_radiation.polarizn_source_ratio would be 1, and
                   for an unpolarized beam
                   _diffrn_radiation.polarizn_source_ratio would have a
                   value of 0.
    
                   If the X axis has been chosen to lie in the plane of
                   polarization, this definition will agree with the definition
                   of 'MONOCHROMATOR' in the Denzo glossary, and values of near
                   1 should be expected for a bending-magnet source.  However,
                   if the X axis were perpendicular to the polarization plane
                   (not a common choice), then the Denzo value would be the
                   negative of _diffrn_radiation.polarizn_source_ratio.
    
                   See http://www.hkl-xray.com for information on Denzo and
                   Otwinowski & Minor (1997).
    
                   This differs both in the choice of ratio and choice of
                   orientation from _diffrn_radiation.polarisn_ratio, which,
                   unlike _diffrn_radiation.polarizn_source_ratio, is
                   unbounded.
    
                   Reference: Otwinowski, Z. & Minor, W. (1997). 'Processing of
                   X-ray diffraction data collected in oscillation mode.' Methods
                   Enzymol. 276, 307-326.
    ;
        _item.name                  '_diffrn_radiation.polarizn_source_ratio'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
         loop_
        _item_range.maximum
        _item_range.minimum           1.0    1.0
                                      1.0   -1.0
                                     -1.0   -1.0
        _item_type.code               float
         save_
    
    
    save__diffrn_radiation.probe
        _item_description.description
    ;              Name of the type of radiation used. It is strongly
                   recommended that this be given so that the
                   probe radiation is clearly specified.
    ;
        _item.name                  '_diffrn_radiation.probe'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_probe'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               line
         loop_
        _item_enumeration.value      'X-ray'
                                     'neutron'
                                     'electron'
                                     'gamma'
         save_
    
    save__diffrn_radiation.type
        _item_description.description
    ;              The nature of the radiation. This is typically a description
                   of the X-ray wavelength in Siegbahn notation.
    ;
        _item.name                  '_diffrn_radiation.type'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_type'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               line
         loop_
        _item_examples.case          'CuK\a'
                                     'Cu K\a~1~'
                                     'Cu K-L~2,3~'
                                     'white-beam'
    
         save_
    
    save__diffrn_radiation.xray_symbol
        _item_description.description
    ;              The IUPAC symbol for the X-ray wavelength for the probe
                   radiation.
    ;
        _item.name                  '_diffrn_radiation.xray_symbol'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_xray_symbol'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               line
         loop_
        _item_enumeration.value
        _item_enumeration.detail     'K-L~3~'
                                     'K\a~1~ in older Siegbahn notation'
                                     'K-L~2~'
                                     'K\a~2~ in older Siegbahn notation'
                                     'K-M~3~'
                                     'K\b~1~ in older Siegbahn notation'
                                     'K-L~2,3~'
                                     'use where K-L~3~ and K-L~2~ are not resolved'
         save_
    
    save__diffrn_radiation.wavelength_id
        _item_description.description
    ;              This data item is a pointer to
                   _diffrn_radiation_wavelength.id in the
                   DIFFRN_RADIATION_WAVELENGTH category.
    ;
        _item.name                  '_diffrn_radiation.wavelength_id'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    
    ################
    # DIFFRN_REFLN #
    ################
    
    
    save_DIFFRN_REFLN
        _category.description
    ;    This category redefinition has been added to extend the key of
         the standard DIFFRN_REFLN category.
    ;
        _category.id                   diffrn_refln
        _category.mandatory_code       no
        _category_key.name             '_diffrn_refln.frame_id'
         loop_
        _category_group.id             'inclusive_group'
                                       'diffrn_group'
         save_
    
    
    save__diffrn_refln.frame_id
        _item_description.description
    ;              This item is a pointer to _diffrn_data_frame.id
                   in the DIFFRN_DATA_FRAME category.
    ;
        _item.name                  '_diffrn_refln.frame_id'
        _item.category_id             diffrn_refln
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    ###############
    # DIFFRN_SCAN #
    ###############
    
    save_DIFFRN_SCAN
        _category.description
    ;    Data items in the DIFFRN_SCAN category describe the parameters of one
         or more scans, relating axis positions to frames.
    
    ;
        _category.id                   diffrn_scan
        _category.mandatory_code       no
        _category_key.name            '_diffrn_scan.id'
         loop_
        _category_group.id            'inclusive_group'
                                      'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;   Example 1 - derived from a suggestion by R. M. Sweet.
    
       The vector of each axis is not given here, because it is provided in
       the AXIS category.  By making _diffrn_scan_axis.scan_id and
       _diffrn_scan_axis.axis_id keys of the DIFFRN_SCAN_AXIS category,
       an arbitrary number of scanning and fixed axes can be specified for a
       scan.  In this example, three rotation axes and one translation axis
       at nonzero values are specified, with one axis stepping.  There is no
       reason why more axes could not have been specified to step. Range
       information has been specified, but note that it can be calculated from
       the  number of frames and the increment, so the data item
       _diffrn_scan_axis.angle_range could be dropped.
    
       Both the sweep data and the data for a single frame are specified.
    
       Note that the information on how the axes are stepped is given twice,
       once in terms of the overall averages in the value of
       _diffrn_scan.integration_time and the values for DIFFRN_SCAN_AXIS,
       and precisely for the given frame in the value for
       _diffrn_scan_frame.integration_time and the values for
       DIFFRN_SCAN_FRAME_AXIS.  If dose-related adjustments are made to
       scan times and nonlinear stepping is done, these values may differ.
       Therefore, in interpreting the data for a particular frame it is
       important to use the frame-specific data.
    ;
    ;
          _diffrn_scan.id                   1
          _diffrn_scan.date_start         '2001-11-18T03:26:42'
          _diffrn_scan.date_end           '2001-11-18T03:36:45'
          _diffrn_scan.integration_time    3.0
          _diffrn_scan.frame_id_start      mad_L2_000
          _diffrn_scan.frame_id_end        mad_L2_200
          _diffrn_scan.frames              201
    
           loop_
          _diffrn_scan_axis.scan_id
          _diffrn_scan_axis.axis_id
          _diffrn_scan_axis.angle_start
          _diffrn_scan_axis.angle_range
          _diffrn_scan_axis.angle_increment
          _diffrn_scan_axis.displacement_start
          _diffrn_scan_axis.displacement_range
          _diffrn_scan_axis.displacement_increment
    
           1 omega 200.0 20.0 0.1 . . .
           1 kappa -40.0  0.0 0.0 . . .
           1 phi   127.5  0.0 0.0 . . .
           1 tranz  . . .   2.3 0.0 0.0
    
          _diffrn_scan_frame.scan_id                   1
          _diffrn_scan_frame.date               '2001-11-18T03:27:33'
          _diffrn_scan_frame.integration_time    3.0
          _diffrn_scan_frame.frame_id            mad_L2_018
          _diffrn_scan_frame.frame_number        18
    
          loop_
          _diffrn_scan_frame_axis.frame_id
          _diffrn_scan_frame_axis.axis_id
          _diffrn_scan_frame_axis.angle
          _diffrn_scan_frame_axis.angle_increment
          _diffrn_scan_frame_axis.displacement
          _diffrn_scan_frame_axis.displacement_increment
    
           mad_L2_018 omega 201.8  0.1 . .
           mad_L2_018 kappa -40.0  0.0 . .
           mad_L2_018 phi   127.5  0.0 . .
           mad_L2_018 tranz  .     .  2.3 0.0
    ;
    
    ;  Example 2 - a more extensive example (R. M. Sweet, P. J. Ellis &
       H. J. Bernstein).
    
       A detector is placed 240 mm along the Z axis from the goniometer.
       This leads to a choice:  either the axes of
       the detector are defined at the origin, and then a Z setting of -240
       is entered, or the axes are defined with the necessary Z offset.
       In this case, the setting is used and the offset is left as zero.
       This axis is called DETECTOR_Z.
    
       The axis for positioning the detector in the Y direction depends
       on the detector Z axis.  This axis is called DETECTOR_Y.
    
       The axis for positioning the detector in the X direction depends
       on the detector Y axis (and therefore on the detector Z axis).
       This axis is called DETECTOR_X.
    
       This detector may be rotated around the Y axis.  This rotation axis
       depends on the three translation axes.  It is called DETECTOR_PITCH.
    
       A coordinate system is defined on the face of the detector in terms of
       2300 0.150 mm pixels in each direction.  The ELEMENT_X axis is used to
       index the first array index of the data array and the ELEMENT_Y
       axis is used to index the second array index.  Because the pixels
       are 0.150mm X 0.150mm, the centre of the first pixel is at (0.075,
       0.075) in this coordinate system.
    ;
    
    ;    ###CBF: VERSION 1.1
    
         data_image_1
    
         # category DIFFRN
         _diffrn.id P6MB
         _diffrn.crystal_id P6MB_CRYSTAL7
    
         # category DIFFRN_SOURCE
         loop_
         _diffrn_source.diffrn_id
         _diffrn_source.source
         _diffrn_source.type
          P6MB synchrotron 'SSRL beamline 9-1'
    
         # category DIFFRN_RADIATION
         loop_
         _diffrn_radiation.diffrn_id
         _diffrn_radiation.wavelength_id
         _diffrn_radiation.monochromator
         _diffrn_radiation.polarizn_source_ratio
         _diffrn_radiation.polarizn_source_norm
         _diffrn_radiation.div_x_source
         _diffrn_radiation.div_y_source
         _diffrn_radiation.div_x_y_source
          P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08
         0.01 0.00
    
         # category DIFFRN_RADIATION_WAVELENGTH
         loop_
         _diffrn_radiation_wavelength.id
         _diffrn_radiation_wavelength.wavelength
         _diffrn_radiation_wavelength.wt
          WAVELENGTH1 0.98 1.0
    
         # category DIFFRN_DETECTOR
         loop_
         _diffrn_detector.diffrn_id
         _diffrn_detector.id
         _diffrn_detector.type
         _diffrn_detector.number_of_axes
          P6MB MAR345-SN26 'MAR 345' 4
    
         # category DIFFRN_DETECTOR_AXIS
         loop_
         _diffrn_detector_axis.detector_id
         _diffrn_detector_axis.axis_id
          MAR345-SN26 DETECTOR_X
          MAR345-SN26 DETECTOR_Y
          MAR345-SN26 DETECTOR_Z
          MAR345-SN26 DETECTOR_PITCH
    
         # category DIFFRN_DETECTOR_ELEMENT
         loop_
         _diffrn_detector_element.id
         _diffrn_detector_element.detector_id
          ELEMENT1 MAR345-SN26
    
         # category DIFFRN_DATA_FRAME
         loop_
         _diffrn_data_frame.id
         _diffrn_data_frame.detector_element_id
         _diffrn_data_frame.array_id
         _diffrn_data_frame.binary_id
          FRAME1 ELEMENT1 ARRAY1 1
    
         # category DIFFRN_MEASUREMENT
         loop_
         _diffrn_measurement.diffrn_id
         _diffrn_measurement.id
         _diffrn_measurement.number_of_axes
         _diffrn_measurement.method
          P6MB GONIOMETER 3 rotation
    
         # category DIFFRN_MEASUREMENT_AXIS
         loop_
         _diffrn_measurement_axis.measurement_id
         _diffrn_measurement_axis.axis_id
          GONIOMETER GONIOMETER_PHI
          GONIOMETER GONIOMETER_KAPPA
          GONIOMETER GONIOMETER_OMEGA
    
         # category DIFFRN_SCAN
         loop_
         _diffrn_scan.id
         _diffrn_scan.frame_id_start
         _diffrn_scan.frame_id_end
         _diffrn_scan.frames
          SCAN1 FRAME1 FRAME1 1
    
         # category DIFFRN_SCAN_AXIS
         loop_
         _diffrn_scan_axis.scan_id
         _diffrn_scan_axis.axis_id
         _diffrn_scan_axis.angle_start
         _diffrn_scan_axis.angle_range
         _diffrn_scan_axis.angle_increment
         _diffrn_scan_axis.displacement_start
         _diffrn_scan_axis.displacement_range
         _diffrn_scan_axis.displacement_increment
          SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0
          SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0
          SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0
          SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0
          SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0
          SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0
          SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0
    
         # category DIFFRN_SCAN_FRAME
         loop_
         _diffrn_scan_frame.frame_id
         _diffrn_scan_frame.frame_number
         _diffrn_scan_frame.integration_time
         _diffrn_scan_frame.scan_id
         _diffrn_scan_frame.date
          FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48
    
         # category DIFFRN_SCAN_FRAME_AXIS
         loop_
         _diffrn_scan_frame_axis.frame_id
         _diffrn_scan_frame_axis.axis_id
         _diffrn_scan_frame_axis.angle
         _diffrn_scan_frame_axis.displacement
          FRAME1 GONIOMETER_OMEGA 12.0 0.0
          FRAME1 GONIOMETER_KAPPA 23.3 0.0
          FRAME1 GONIOMETER_PHI -165.8 0.0
          FRAME1 DETECTOR_Z 0.0 -240.0
          FRAME1 DETECTOR_Y 0.0 0.6
          FRAME1 DETECTOR_X 0.0 -0.5
          FRAME1 DETECTOR_PITCH 0.0 0.0
    
         # category AXIS
         loop_
         _axis.id
         _axis.type
         _axis.equipment
         _axis.depends_on
         _axis.vector[1] _axis.vector[2] _axis.vector[3]
         _axis.offset[1] _axis.offset[2] _axis.offset[3]
          GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . .
          GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279
          0 0.76604 . . .
          GONIOMETER_PHI   rotation goniometer GONIOMETER_KAPPA 1 0 0
         . . .
          SOURCE           general source . 0 0 1 . . .
          GRAVITY          general gravity . 0 -1 0 . . .
          DETECTOR_Z       translation detector . 0 0 1 0 0 0
          DETECTOR_Y       translation detector DETECTOR_Z 0 1 0 0 0 0
          DETECTOR_X       translation detector DETECTOR_Y 1 0 0 0 0 0
          DETECTOR_PITCH   rotation    detector DETECTOR_X 0 1 0 0 0 0
          ELEMENT_X        translation detector DETECTOR_PITCH
         1 0 0 172.43 -172.43 0
          ELEMENT_Y        translation detector ELEMENT_X
         0 1 0 0 0 0
    
         # category ARRAY_STRUCTURE_LIST
         loop_
         _array_structure_list.array_id
         _array_structure_list.index
         _array_structure_list.dimension
         _array_structure_list.precedence
         _array_structure_list.direction
         _array_structure_list.axis_set_id
          ARRAY1 1 2300 1 increasing ELEMENT_X
          ARRAY1 2 2300 2 increasing ELEMENT_Y
    
         # category ARRAY_STRUCTURE_LIST_AXIS
         loop_
         _array_structure_list_axis.axis_set_id
         _array_structure_list_axis.axis_id
         _array_structure_list_axis.displacement
         _array_structure_list_axis.displacement_increment
          ELEMENT_X ELEMENT_X 0.075 0.150
          ELEMENT_Y ELEMENT_Y 0.075 0.150
    
         # category ARRAY_ELEMENT_SIZE
         loop_
         _array_element_size.array_id
         _array_element_size.index
         _array_element_size.size
          ARRAY1 1 150e-6
          ARRAY1 2 150e-6
    
         # category ARRAY_INTENSITIES
         loop_
         _array_intensities.array_id
         _array_intensities.binary_id
         _array_intensities.linearity
         _array_intensities.gain
         _array_intensities.gain_esd
         _array_intensities.overload
         _array_intensities.undefined_value
          ARRAY1 1 linear 1.15 0.2 240000 0
    
          # category ARRAY_STRUCTURE
          loop_
          _array_structure.id
          _array_structure.encoding_type
          _array_structure.compression_type
          _array_structure.byte_order
          ARRAY1 "signed 32-bit integer" packed little_endian
    
         # category ARRAY_DATA
         loop_
         _array_data.array_id
         _array_data.binary_id
         _array_data.data
          ARRAY1 1
         ;
         --CIF-BINARY-FORMAT-SECTION--
         Content-Type: application/octet-stream;
             conversions="X-CBF_PACKED"
         Content-Transfer-Encoding: BASE64
         X-Binary-Size: 3801324
         X-Binary-ID: 1
         X-Binary-Element-Type: "signed 32-bit integer"
         Content-MD5: 07lZFvF+aOcW85IN7usl8A==
    
         AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg
         ...
         8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE
    
         --CIF-BINARY-FORMAT-SECTION----
         ;
    ;
    
    ;   Example 3 - Example 2 revised for a spiral scan (R. M. Sweet,
        P. J. Ellis & H. J. Bernstein).
    
       A detector is placed 240 mm along the Z axis from the
       goniometer, as in Example 2 above, but in this example the
       image plate is scanned in a spiral pattern from the outside edge in.
    
       The axis for positioning the detector in the Y direction depends
       on the detector Z axis.  This axis is called DETECTOR_Y.
    
       The axis for positioning the detector in the X direction depends
       on the detector Y axis (and therefore on the detector Z axis).
       This axis is called DETECTOR_X.
    
       This detector may be rotated around the Y axis.  This rotation axis
       depends on the three translation axes.  It is called DETECTOR_PITCH.
    
       A coordinate system is defined on the face of the detector in
       terms of a coupled rotation axis and radial scan axis to form
       a spiral scan.  The rotation axis is called  ELEMENT_ROT  and the
       radial axis is called ELEMENT_RAD.  A 150 micrometre radial pitch
       and a 75 micrometre 'constant velocity' angular pitch are assumed.
    
       Indexing is carried out first on the rotation axis and the radial axis
       is made to be dependent on it.
    
       The two axes are coupled to form an axis set ELEMENT_SPIRAL.
    ;
    ;    ###CBF: VERSION 1.1
    
         data_image_1
    
         # category DIFFRN
         _diffrn.id P6MB
         _diffrn.crystal_id P6MB_CRYSTAL7
    
         # category DIFFRN_SOURCE
         loop_
         _diffrn_source.diffrn_id
         _diffrn_source.source
         _diffrn_source.type
          P6MB synchrotron 'SSRL beamline 9-1'
    
         # category DIFFRN_RADIATION
              loop_
         _diffrn_radiation.diffrn_id
         _diffrn_radiation.wavelength_id
         _diffrn_radiation.monochromator
         _diffrn_radiation.polarizn_source_ratio
         _diffrn_radiation.polarizn_source_norm
         _diffrn_radiation.div_x_source
         _diffrn_radiation.div_y_source
         _diffrn_radiation.div_x_y_source
          P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08
         0.01 0.00
    
         # category DIFFRN_RADIATION_WAVELENGTH
         loop_
         _diffrn_radiation_wavelength.id
         _diffrn_radiation_wavelength.wavelength
         _diffrn_radiation_wavelength.wt
          WAVELENGTH1 0.98 1.0
    
         # category DIFFRN_DETECTOR
         loop_
         _diffrn_detector.diffrn_id
         _diffrn_detector.id
         _diffrn_detector.type
         _diffrn_detector.number_of_axes
          P6MB MAR345-SN26 'MAR 345' 4
    
         # category DIFFRN_DETECTOR_AXIS
         loop_
         _diffrn_detector_axis.detector_id
         _diffrn_detector_axis.axis_id
          MAR345-SN26 DETECTOR_X
          MAR345-SN26 DETECTOR_Y
          MAR345-SN26 DETECTOR_Z
          MAR345-SN26 DETECTOR_PITCH
    
         # category DIFFRN_DETECTOR_ELEMENT
         loop_
         _diffrn_detector_element.id
         _diffrn_detector_element.detector_id
          ELEMENT1 MAR345-SN26
    
         # category DIFFRN_DATA_FRAME
         loop_
         _diffrn_data_frame.id
         _diffrn_data_frame.detector_element_id
         _diffrn_data_frame.array_id
         _diffrn_data_frame.binary_id
          FRAME1 ELEMENT1 ARRAY1 1
    
         # category DIFFRN_MEASUREMENT
         loop_
         _diffrn_measurement.diffrn_id
         _diffrn_measurement.id
         _diffrn_measurement.number_of_axes
         _diffrn_measurement.method
          P6MB GONIOMETER 3 rotation
    
         # category DIFFRN_MEASUREMENT_AXIS
         loop_
         _diffrn_measurement_axis.measurement_id
         _diffrn_measurement_axis.axis_id
          GONIOMETER GONIOMETER_PHI
          GONIOMETER GONIOMETER_KAPPA
          GONIOMETER GONIOMETER_OMEGA
    
         # category DIFFRN_SCAN
         loop_
         _diffrn_scan.id
         _diffrn_scan.frame_id_start
         _diffrn_scan.frame_id_end
         _diffrn_scan.frames
          SCAN1 FRAME1 FRAME1 1
    
         # category DIFFRN_SCAN_AXIS
         loop_
         _diffrn_scan_axis.scan_id
         _diffrn_scan_axis.axis_id
         _diffrn_scan_axis.angle_start
         _diffrn_scan_axis.angle_range
         _diffrn_scan_axis.angle_increment
         _diffrn_scan_axis.displacement_start
         _diffrn_scan_axis.displacement_range
         _diffrn_scan_axis.displacement_increment
          SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0
          SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0
          SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0
          SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0
          SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0
          SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0
          SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0
    
         # category DIFFRN_SCAN_FRAME
         loop_
         _diffrn_scan_frame.frame_id
         _diffrn_scan_frame.frame_number
         _diffrn_scan_frame.integration_time
         _diffrn_scan_frame.scan_id
         _diffrn_scan_frame.date
          FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48
    
         # category DIFFRN_SCAN_FRAME_AXIS
         loop_
         _diffrn_scan_frame_axis.frame_id
         _diffrn_scan_frame_axis.axis_id
         _diffrn_scan_frame_axis.angle
         _diffrn_scan_frame_axis.displacement
          FRAME1 GONIOMETER_OMEGA 12.0 0.0
          FRAME1 GONIOMETER_KAPPA 23.3 0.0
          FRAME1 GONIOMETER_PHI -165.8 0.0
          FRAME1 DETECTOR_Z 0.0 -240.0
          FRAME1 DETECTOR_Y 0.0 0.6
          FRAME1 DETECTOR_X 0.0 -0.5
          FRAME1 DETECTOR_PITCH 0.0 0.0
    
         # category AXIS
         loop_
         _axis.id
         _axis.type
         _axis.equipment
         _axis.depends_on
         _axis.vector[1] _axis.vector[2] _axis.vector[3]
         _axis.offset[1] _axis.offset[2] _axis.offset[3]
          GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . .
          GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279
          0 0.76604 . . .
          GONIOMETER_PHI   rotation goniometer GONIOMETER_KAPPA 1 0 0
         . . .
          SOURCE           general source . 0 0 1 . . .
          GRAVITY          general gravity . 0 -1 0 . . .
          DETECTOR_Z       translation detector . 0 0 1 0 0 0
          DETECTOR_Y       translation detector DETECTOR_Z 0 1 0 0 0 0
          DETECTOR_X       translation detector DETECTOR_Y 1 0 0 0 0 0
          DETECTOR_PITCH   rotation    detector DETECTOR_X 0 1 0 0 0 0
          ELEMENT_ROT      translation detector DETECTOR_PITCH 0 0 1 0 0 0
          ELEMENT_RAD      translation detector ELEMENT_ROT 0 1 0 0 0 0
    
         # category ARRAY_STRUCTURE_LIST
         loop_
         _array_structure_list.array_id
         _array_structure_list.index
         _array_structure_list.dimension
         _array_structure_list.precedence
         _array_structure_list.direction
         _array_structure_list.axis_set_id
          ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL
    
         # category ARRAY_STRUCTURE_LIST_AXIS
         loop_
         _array_structure_list_axis.axis_set_id
         _array_structure_list_axis.axis_id
         _array_structure_list_axis.angle
         _array_structure_list_axis.displacement
         _array_structure_list_axis.angular_pitch
         _array_structure_list_axis.radial_pitch
          ELEMENT_SPIRAL ELEMENT_ROT 0    .  0.075   .
          ELEMENT_SPIRAL ELEMENT_RAD . 172.5  .    -0.150
    
         # category ARRAY_ELEMENT_SIZE
         # the actual pixels are 0.075 by 0.150 mm
         # We give the coarser dimension here.
         loop_
         _array_element_size.array_id
         _array_element_size.index
         _array_element_size.size
          ARRAY1 1 150e-6
    
         # category ARRAY_INTENSITIES
         loop_
         _array_intensities.array_id
         _array_intensities.binary_id
         _array_intensities.linearity
         _array_intensities.gain
         _array_intensities.gain_esd
         _array_intensities.overload
         _array_intensities.undefined_value
          ARRAY1 1 linear 1.15 0.2 240000 0
    
          # category ARRAY_STRUCTURE
          loop_
          _array_structure.id
          _array_structure.encoding_type
          _array_structure.compression_type
          _array_structure.byte_order
          ARRAY1 "signed 32-bit integer" packed little_endian
    
         # category ARRAY_DATA
         loop_
         _array_data.array_id
         _array_data.binary_id
         _array_data.data
          ARRAY1 1
         ;
         --CIF-BINARY-FORMAT-SECTION--
         Content-Type: application/octet-stream;
             conversions="X-CBF_PACKED"
         Content-Transfer-Encoding: BASE64
         X-Binary-Size: 3801324
         X-Binary-ID: 1
         X-Binary-Element-Type: "signed 32-bit integer"
         Content-MD5: 07lZFvF+aOcW85IN7usl8A==
    
         AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg
         ...
         8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE
    
         --CIF-BINARY-FORMAT-SECTION----
         ;
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
           save_
    
    
    save__diffrn_scan.id
        _item_description.description
    ;             The value of _diffrn_scan.id uniquely identifies each
                  scan.  The identifier is used to tie together all the
                  information about the scan.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
           '_diffrn_scan.id'                 diffrn_scan             yes
           '_diffrn_scan_axis.scan_id'       diffrn_scan_axis        yes
           '_diffrn_scan_frame.scan_id'      diffrn_scan_frame       yes
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
           '_diffrn_scan_axis.scan_id'          '_diffrn_scan.id'
           '_diffrn_scan_frame.scan_id'         '_diffrn_scan.id'
         save_
    
    
    save__diffrn_scan.date_end
        _item_description.description
    ;              The date and time of the end of the scan.  Note that this
                   may be an estimate generated during the scan, before the
                   precise time of the end of the scan is known.
    ;
        _item.name                 '_diffrn_scan.date_end'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no
        _item_type.code            yyyy-mm-dd
         save_
    
    
    save__diffrn_scan.date_start
        _item_description.description
    ;              The date and time of the start of the scan.
    ;
        _item.name                 '_diffrn_scan.date_start'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no
        _item_type.code            yyyy-mm-dd
         save_
    
    
    save__diffrn_scan.integration_time
        _item_description.description
    ;              Approximate average time in seconds to integrate each
                   step of the scan.  The precise time for integration
                   of each particular step must be provided in
                   _diffrn_scan_frame.integration_time, even
                   if all steps have the same integration time.
    ;
        _item.name                 '_diffrn_scan.integration_time'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no
        _item_type.code            float
        _item_units.code           'seconds'
         loop_
        _item_range.maximum
        _item_range.minimum
                                .   0.0
         save_
    
    
    save__diffrn_scan.frame_id_start
        _item_description.description
    ;              The value of this data item is the identifier of the
                   first frame in the scan.
    
                   This item is a pointer to _diffrn_data_frame.id in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name                 '_diffrn_scan.frame_id_start'
        _item.category_id          diffrn_scan
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan.frame_id_end
        _item_description.description
    ;              The value of this data item is the identifier of the
                   last frame in the scan.
    
                   This item is a pointer to _diffrn_data_frame.id in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name                 '_diffrn_scan.frame_id_end'
        _item.category_id          diffrn_scan
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan.frames
        _item_description.description
    ;              The value of this data item is the number of frames in
                   the scan.
    ;
        _item.name                 '_diffrn_scan.frames'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no
        _item_type.code            int
         loop_
        _item_range.maximum
        _item_range.minimum
                                .   1
                                1   1
         save_
    
    
    ####################
    # DIFFRN_SCAN_AXIS #
    ####################
    
    save_DIFFRN_SCAN_AXIS
        _category.description
    ;    Data items in the DIFFRN_SCAN_AXIS category describe the settings of
         axes for particular scans.  Unspecified axes are assumed to be at
         their zero points.
    ;
        _category.id                   diffrn_scan_axis
        _category.mandatory_code       no
         loop_
        _category_key.name
                                      '_diffrn_scan_axis.scan_id'
                                      '_diffrn_scan_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_scan_axis.scan_id
        _item_description.description
    ;              The value of this data item is the identifier of the
                   scan for which axis settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   _diffrn_scan.id.
    
                   This item is a pointer to _diffrn_scan.id in the
                   DIFFRN_SCAN category.
    ;
        _item.name                 '_diffrn_scan_axis.scan_id'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_axis.axis_id
        _item_description.description
    ;              The value of this data item is the identifier of one of
                   the axes for the scan for which settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   _diffrn_scan.id.
    
                   This item is a pointer to _axis.id in the
                   AXIS category.
    ;
        _item.name                 '_diffrn_scan_axis.axis_id'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_axis.angle_start
        _item_description.description
    ;              The starting position for the specified axis in degrees.
    ;
        _item.name                 '_diffrn_scan_axis.angle_start'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.angle_range
        _item_description.description
    ;              The range from the starting position for the specified axis
                   in degrees.
    ;
        _item.name                 '_diffrn_scan_axis.angle_range'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.angle_increment
        _item_description.description
    ;              The increment for each step for the specified axis
                   in degrees.  In general, this will agree with
                   _diffrn_scan_frame_axis.angle_increment. The
                   sum of the values of _diffrn_scan_frame_axis.angle and
                   _diffrn_scan_frame_axis.angle_increment is the
                   angular setting of the axis at the end of the integration
                   time for a given frame.  If the individual frame values
                   vary, then the value of
                   _diffrn_scan_axis.angle_increment will be
                   representative
                   of the ensemble of values of
                   _diffrn_scan_frame_axis.angle_increment (e.g.
                   the mean).
    ;
        _item.name                 '_diffrn_scan_axis.angle_increment'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.angle_rstrt_incr
        _item_description.description
    ;              The increment after each step for the specified axis
                   in degrees.  In general, this will agree with
                   _diffrn_scan_frame_axis.angle_rstrt_incr.  The
                   sum of the values of _diffrn_scan_frame_axis.angle,
                   _diffrn_scan_frame_axis.angle_increment
                   and  _diffrn_scan_frame_axis.angle_rstrt_incr is the
                   angular setting of the axis at the start of the integration
                   time for the next frame relative to a given frame and
                   should equal _diffrn_scan_frame_axis.angle for this
                   next frame.   If the individual frame values
                   vary, then the value of
                   _diffrn_scan_axis.angle_rstrt_incr will be
                   representative
                   of the ensemble of values of
                   _diffrn_scan_frame_axis.angle_rstrt_incr (e.g.
                   the mean).
    ;
        _item.name                 '_diffrn_scan_axis.angle_rstrt_incr'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.displacement_start
        _item_description.description
    ;              The starting position for the specified axis in millimetres.
    ;
        _item.name                 '_diffrn_scan_axis.displacement_start'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_axis.displacement_range
        _item_description.description
    ;              The range from the starting position for the specified axis
                   in millimetres.
    ;
        _item.name                 '_diffrn_scan_axis.displacement_range'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_axis.displacement_increment
        _item_description.description
    ;              The increment for each step for the specified axis
                   in millimetres.  In general, this will agree with
                   _diffrn_scan_frame_axis.displacement_increment.
                   The sum of the values of
                   _diffrn_scan_frame_axis.displacement and
                   _diffrn_scan_frame_axis.displacement_increment is the
                   angular setting of the axis at the end of the integration
                   time for a given frame.  If the individual frame values
                   vary, then the value of
                   _diffrn_scan_axis.displacement_increment will be
                   representative
                   of the ensemble of values of
                   _diffrn_scan_frame_axis.displacement_increment (e.g.
                   the mean).
    ;
        _item.name                 '_diffrn_scan_axis.displacement_increment'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_axis.displacement_rstrt_incr
        _item_description.description
    ;              The increment for each step for the specified axis
                   in millimetres.  In general, this will agree with
                   _diffrn_scan_frame_axis.displacement_rstrt_incr.
                   The sum of the values of
                   _diffrn_scan_frame_axis.displacement,
                   _diffrn_scan_frame_axis.displacement_increment and
                   _diffrn_scan_frame_axis.displacement_rstrt_incr is the
                   angular setting of the axis at the start of the integration
                   time for the next frame relative to a given frame and
                   should equal _diffrn_scan_frame_axis.displacement
                   for this next frame.  If the individual frame values
                   vary, then the value of
                   _diffrn_scan_axis.displacement_rstrt_incr will be
                   representative
                   of the ensemble of values of
                   _diffrn_scan_frame_axis.displacement_rstrt_incr (e.g.
                   the mean).
    ;
        _item.name                 '_diffrn_scan_axis.displacement_rstrt_incr'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    save__diffrn_scan_axis.reference_angle
         _item_description.description
    ;              The setting of the specified axis in degrees
                   against which measurements of the reference beam center
                   and reference detector distance should be made.
    
                   In general, this will agree with
                   _diffrn_scan_frame_axis.reference_angle.
    
                   If the individual frame values vary, then the value of
                   _diffrn_scan_axis.reference_angle will be
                   representative of the ensemble of values of
                   _diffrn_scan_frame_axis.reference_angle (e.g.
                   the mean).
    
                   If not specified, the value defaults to zero.
    ;
         _item.name                 '_diffrn_scan_axis.reference_angle'
         _item.category_id          diffrn_scan_axis
         _item.mandatory_code       implicit
         _item_default.value        0.0
         _item_type.code            float
         _item_units.code           'degrees'
          save_
    
    
    save__diffrn_scan_axis.reference_displacement
         _item_description.description
    ;              The setting of the specified axis in millimetres
                   against which measurements of the reference beam center
                   and reference detector distance should be made.
    
                   In general, this will agree with
                   _diffrn_scan_frame_axis.reference_displacement.
    
                   If the individual frame values vary, then the value of
                   _diffrn_scan_axis.reference_displacement will be
                   representative of the ensemble of values of
                   _diffrn_scan_frame_axis.reference_displacement (e.g.
                   the mean).
    
                   If not specified, the value defaults to to the value of
                   _diffrn_scan_axis.displacement.
    ;
         _item.name                 '_diffrn_scan_axis.reference_displacement'
         _item.category_id          diffrn_scan_axis
         _item.mandatory_code       implicit
         _item_type.code            float
         _item_units.code           'millimetres'
          save_
    
    
    
    #####################
    # DIFFRN_SCAN_FRAME #
    #####################
    
    save_DIFFRN_SCAN_FRAME
        _category.description
    ;           Data items in the DIFFRN_SCAN_FRAME category describe
                the relationships of particular frames to scans.
    ;
        _category.id                   diffrn_scan_frame
        _category.mandatory_code       no
         loop_
        _category_key.name
                                      '_diffrn_scan_frame.scan_id'
                                      '_diffrn_scan_frame.frame_id'
         loop_
        _category_group.id            'inclusive_group'
                                      'diffrn_group'
         save_
    
    
    save__diffrn_scan_frame.date
        _item_description.description
    ;              The date and time of the start of the frame being scanned.
    ;
        _item.name                 '_diffrn_scan_frame.date'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       no
        _item_type.code            yyyy-mm-dd
         save_
    
    
    save__diffrn_scan_frame.frame_id
        _item_description.description
    ;              The value of this data item is the identifier of the
                   frame being examined.
    
                   This item is a pointer to _diffrn_data_frame.id in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name                 '_diffrn_scan_frame.frame_id'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_frame.frame_number
        _item_description.description
    ;              The value of this data item is the number of the frame
                   within the scan, starting with 1.  It is not necessarily
                   the same as the value of _diffrn_scan_frame.frame_id,
                   but it may be.
    
    ;
        _item.name                 '_diffrn_scan_frame.frame_number'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       no
        _item_type.code            int
         loop_
        _item_range.maximum
        _item_range.minimum
                                .   0
                                0   0
         save_
    
    
    save__diffrn_scan_frame.integration_time
        _item_description.description
    ;              The time in seconds to integrate this step of the scan.
                   This should be the precise time of integration of each
                   particular frame.  The value of this data item should
                   be given explicitly for each frame and not inferred
                   from the value of _diffrn_scan.integration_time.
    ;
        _item.name                 '_diffrn_scan_frame.integration_time'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       yes
        _item_type.code            float
        _item_units.code           'seconds'
         loop_
        _item_range.maximum
        _item_range.minimum
                                .   0.0
         save_
    
    
    save__diffrn_scan_frame.scan_id
        _item_description.description
    ;             The value of _diffrn_scan_frame.scan_id identifies the scan
                  containing this frame.
    
                  This item is a pointer to _diffrn_scan.id in the
                  DIFFRN_SCAN category.
    ;
        _item.name             '_diffrn_scan_frame.scan_id'
        _item.category_id        diffrn_scan_frame
        _item.mandatory_code     yes
        _item_type.code          code
         save_
    
    
    ##########################
    # DIFFRN_SCAN_FRAME_AXIS #
    ##########################
    
    save_DIFFRN_SCAN_FRAME_AXIS
        _category.description
    ;    Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the
         settings of axes for particular frames.  Unspecified axes are
         assumed to be at their zero points.  If, for any given frame,
         nonzero values apply for any of the data items in this category,
         those values should be given explicitly in this category and not
         simply inferred from values in DIFFRN_SCAN_AXIS.
    ;
        _category.id                   diffrn_scan_frame_axis
        _category.mandatory_code       no
         loop_
        _category_key.name
                                      '_diffrn_scan_frame_axis.frame_id'
                                      '_diffrn_scan_frame_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_scan_frame_axis.axis_id
        _item_description.description
    ;              The value of this data item is the identifier of one of
                   the axes for the frame for which settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   _diffrn_scan_frame.frame_id.
    
                   This item is a pointer to _axis.id in the
                   AXIS category.
    ;
        _item.name                 '_diffrn_scan_frame_axis.axis_id'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_frame_axis.angle
        _item_description.description
    ;              The setting of the specified axis in degrees for this frame.
                   This is the setting at the start of the integration time.
    ;
        _item.name                 '_diffrn_scan_frame_axis.angle'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_frame_axis.angle_increment
        _item_description.description
    ;              The increment for this frame for the angular setting of
                   the specified axis in degrees.  The sum of the values
                   of _diffrn_scan_frame_axis.angle and
                   _diffrn_scan_frame_axis.angle_increment is the
                   angular setting of the axis at the end of the integration
                   time for this frame.
    ;
        _item.name                 '_diffrn_scan_frame_axis.angle_increment'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_frame_axis.angle_rstrt_incr
        _item_description.description
    ;              The increment after this frame for the angular setting of
                   the specified axis in degrees.  The sum of the values
                   of _diffrn_scan_frame_axis.angle,
                   _diffrn_scan_frame_axis.angle_increment and
                   _diffrn_scan_frame_axis.angle_rstrt_incr is the
                   angular setting of the axis at the start of the integration
                   time for the next frame and should equal
                   _diffrn_scan_frame_axis.angle for this next frame.
    ;
        _item.name               '_diffrn_scan_frame_axis.angle_rstrt_incr'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_frame_axis.displacement
        _item_description.description
    ;              The setting of the specified axis in millimetres for this
                   frame.  This is the setting at the start of the integration
                   time.
    ;
        _item.name               '_diffrn_scan_frame_axis.displacement'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_frame_axis.displacement_increment
        _item_description.description
    ;              The increment for this frame for the displacement setting of
                   the specified axis in millimetres.  The sum of the values
                   of _diffrn_scan_frame_axis.displacement and
                   _diffrn_scan_frame_axis.displacement_increment is the
                   angular setting of the axis at the end of the integration
                   time for this frame.
    ;
        _item.name               '_diffrn_scan_frame_axis.displacement_increment'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_frame_axis.displacement_rstrt_incr
        _item_description.description
    ;              The increment for this frame for the displacement setting of
                   the specified axis in millimetres.  The sum of the values
                   of _diffrn_scan_frame_axis.displacement,
                   _diffrn_scan_frame_axis.displacement_increment and
                   _diffrn_scan_frame_axis.displacement_rstrt_incr is the
                   angular setting of the axis at the start of the integration
                   time for the next frame and should equal
                   _diffrn_scan_frame_axis.displacement for this next frame.
    ;
        _item.name               '_diffrn_scan_frame_axis.displacement_rstrt_incr'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    save__diffrn_scan_frame_axis.frame_id
        _item_description.description
    ;              The value of this data item is the identifier of the
                   frame for which axis settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   _diffrn_scan_frame.frame_id.
    
                   This item is a pointer to _diffrn_data_frame.id in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name               '_diffrn_scan_frame_axis.frame_id'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    save__diffrn_scan_frame_axis.reference_angle
         _item_description.description
    ;              The setting of the specified axis in degrees
                   against which measurements of the reference beam center
                   and reference detector distance should be made.
    
                   This is normally the same for all frames, but the
                   option is provided here of making changes when
                   needed.
    
                   If not provided, it is assumed to be zero.
    ;
         _item.name               '_diffrn_scan_frame_axis.reference_angle'
         _item.category_id          diffrn_scan_frame_axis
         _item.mandatory_code       implicit
         _item_default.value        0.0
         _item_type.code            float
         _item_units.code           'degrees'
          save_
    
    
    save__diffrn_scan_frame_axis.reference_displacement
         _item_description.description
    ;              The setting of the specified axis in millimetres for this
                   frame against which measurements of the reference beam center
                   and reference detector distance should be made.
    
                   This is normally the same for all frames, but the
                   option is provided here of making changes when
                   needed.
    
                   If not provided, it is assumed to be equal to
                   _diffrn_scan_frame_axis.displacement.
    ;
         _item.name               '_diffrn_scan_frame_axis.reference_displacement'
         _item.category_id          diffrn_scan_frame_axis
         _item.mandatory_code       implicit
         _item_type.code            float
         _item_units.code           'millimetres'
          save_
    
    
    
    #######
    # MAP #
    #######
    
    save_MAP
        _category.description
    ;             Data items in the MAP category record
                  the details of a maps. Maps record values of parameters,
                  such as density, that are functions of position within
                  a cell or are functions of orthogonal coordinates in
                  three space.
                  
                  A map may is composed of one or more map segments
                  specified in the MAP_SEGMENT category.
                                
                  Examples are given in the MAP_SEGMENT category.
    ;
        _category.id                   map
        _category.mandatory_code       no
         loop_
        _category_key.name             '_map.id'
                                       '_map.diffrn_id'
                                       '_map.entry_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;   Example 1 - Identifying an observed density map
                    and a calculated density map
    ;
    ;
            
            loop_
            _map.id
            _map.details
            
            rho_calc
       ;
            density calculated from F_calc derived from the ATOM_SITE list
       ;
            rho_obs
       ;
            density combining the observed structure factors with the
            calculated phases
       ;
    ;
    
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
    
    
    save__map.details
         _item_description.description
    ;              The value of _map.details should give a
                   description of special aspects of each map.
    
    ;
        _item.name                  '_map.details'
        _item.category_id             map
        _item.mandatory_code          no
        _item_type.code               text
         loop_
        _item_examples.case
        _item_examples.detail
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;   Example 1 - Identifying an observed density map
                    and a calculated density map
    ;
    ;
            
            loop_
            _map.id
            _map.details
            
            rho_calc
        ;
            density calculated from F_calc derived from the ATOM_SITE list
        ;
            rho_obs
        ;
            density combining the observed structure factors with the
            calculated phases
        ;
    ;
    
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
          save_
          
    save__map.diffrn_id
        _item_description.description
    ;             This item is a pointer to _diffrn.id in the
                  DIFFRN category.
    ;
        _item.name                  '_map.diffrn_id'
        _item.category_id             map
        _item.mandatory_code          implicit
        _item_type.code               code
         save_
    
    save__map.entry_id
        _item_description.description
    ;             This item is a pointer to _entry.id in the
                  ENTRY category.
    ;
        _item.name                  '_map.entry_id'
        _item.category_id             map
        _item.mandatory_code          implicit
        _item_type.code               code
         save_
    
    
    save__map.id
        _item_description.description
    ;             The value of _map.id must uniquely identify
                  each map for the given diffrn.id or entry.id.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
               '_map.id'                map          yes
               '_map_segment.id'        map_segment  yes
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_map_segment.id'        '_map.id'
         save_
    
    
    
    
    ###########################
    # MAP_SEGMENT #
    ###########################
    
    
    save_MAP_SEGMENT
        _category.description
    ;             Data items in the MAP_SEGMENT category record
                  the details about each segment (section or brick) of a map. 
    ;
        _category.id                   map_segment
        _category.mandatory_code       no
         loop_
        _category_key.name             '_map_segment.id'
                                       '_map_segment.map_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;   Example 1 - Identifying an observed density map
                    and a calculated density map, each consisting of one
                    segment, both using the same array structure
                    and mask.
    ;
    ;
            
            loop_
            _map.id
            _map.details
            
            rho_calc
         ;
            density calculated from F_calc derived from the ATOM_SITE list
         ;
            rho_obs
         ;
            density combining the observed structure factors with the
            calculated phases
         ;
    
            loop_
            _map_segment.map_id
            _map_segment.id
            _map_segment.array_id
            _map_segment.binary_id
            _map_segment.mask_array_id
            _map_segment.mask_binary_id
            rho_calc rho_calc map_structure 1 mask_structure 1
            rho_obs  rho_obs  map_structure 2 mask_structure 1
    ;
    
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
    
    
    save__map_segment.array_id
        _item_description.description
    ;             The value of _map_segment.array_id identifies the array structure 
                  into which the map is organized.
    
                  This item is a pointer to _array_structure.id in the
                  ARRAY_STRUCTURE category.
    ;
        _item.name                  '_map_segment.array_id'
        _item.category_id             map_segment
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__map_segment.binary_id
        _item_description.description
    ;             The value of _map_segment.binary_id distinguishes the particular 
                  set of data organized according to _map_segment.array_id in 
                  which the data values of the map are stored.
    
                  This item is a pointer to _array_data.binary_id in the
                  ARRAY_DATA category.
    ;
        _item.name                  '_map_segment.binary_id'
        _item.category_id             map_segment
        _item.mandatory_code          implicit
        _item_type.code               int
         save_
    
    save__map_segment.mask_array_id
        _item_description.description
    ;             The value of _map_segment.mask_array_id, if given, the array 
                  structure into which the mask for the map is organized.  If no 
                  value is given, then all elements of the map are valid.  If a 
                  value is given, then only elements of the map for which the 
                  corresponding element of the mask is non-zero are valid.  The 
                  value of _map_segment.mask_array_id differs from the value of
                  _map_segment.array_id in order to permit the mask to be given
                  as, say, unsigned 8-bit integers, while the map is given as
                  a data type with more range.  However, the two array structures
                  must be aligned, using the same axes in the same order with the
                  same displacements and increments
    
                  This item is a pointer to _array_structure.id in the
                  ARRAY_STRUCTURE category.
    ;
        _item.name                  '_map_segment.mask_array_id'
        _item.category_id             map_segment
        _item.mandatory_code          no
        _item_type.code               code
         save_
    
    
    save__map_segment.mask_binary_id
        _item_description.description
    ;             The value of _map_segment.mask_binary_id identifies the 
                  particular set of data organized according to 
                  _map_segment.mask_array_id specifying the mask for the map.
    
                  This item is a pointer to _array_data.mask_binary_id in the
                  ARRAY_DATA category.
    ;
        _item.name                  '_map_segment.mask_binary_id'
        _item.category_id             map_segment
        _item.mandatory_code          implicit
        _item_type.code               int
         save_
    
    
    save__map_segment.id
        _item_description.description
    ;             The value of _map_segment.id must uniquely
                  identify each segment of a map.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
               '_map_segment.id'
               map_segment
               yes
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_map_data_frame.map_segment_id'
               '_map_segment.id'
    
         save_
    
    
    save__map_segment.map_id
        _item_description.description
    ;              This item is a pointer to _map.id
                   in the MAP category.
    ;
        _item.name                  '_map_segment.map_id'
        _item.category_id             map_segment
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    save__map_segment.details
         _item_description.description
    ;              The value of _map_segment.details should give a
                   description of special aspects of each segment of a map.
    
    ;
        _item.name                  '_map_segment.details'
        _item.category_id             map_segment
        _item.mandatory_code          no
        _item_type.code               text
         loop_
        _item_examples.case
        _item_examples.detail
    ;               Example to be provided
    ;
    ;               
    
    ;
          save_
    
    
    ########################   DEPRECATED DATA ITEMS ########################
    
    save__diffrn_detector_axis.id
        _item_description.description
    ;              This data item is a pointer to _diffrn_detector.id in
                   the DIFFRN_DETECTOR category.
    
                   DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_detector_axis.id'
        _item.category_id             diffrn_detector_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    save__diffrn_measurement_axis.id
        _item_description.description
    ;              This data item is a pointer to _diffrn_measurement.id in
                   the DIFFRN_MEASUREMENT category.
    
                   DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_measurement_axis.id'
        _item.category_id             diffrn_measurement_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    #########################   DEPRECATED CATEGORY #########################
    #####################
    # DIFFRN_FRAME_DATA #
    #####################
    
    
    save_DIFFRN_FRAME_DATA
        _category.description
    ;             Data items in the DIFFRN_FRAME_DATA category record
                  the details about each frame of data.
    
                  The items in this category are now in the
                  DIFFRN_DATA_FRAME category.
    
                  The items in the DIFFRN_FRAME_DATA category
                  are now deprecated.  The items from this category
                  are provided as aliases in the 1.0 dictionary
                  or, in the case of _diffrn_frame_data.details,
                  in the 1.4 dictionary.  THESE ITEMS SHOULD NOT
                  BE USED FOR NEW WORK.
    
                  The items from the old category are provided
                  in this dictionary for completeness
                  but should not be used or cited.  To avoid
                  confusion, the example has been removed
                  and the redundant parent-child links to other
                  categories have been removed.
    ;
        _category.id                   diffrn_frame_data
        _category.mandatory_code       no
         loop_
        _category_key.name             '_diffrn_frame_data.id'
                                       '_diffrn_frame_data.detector_element_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        THE DIFFRN_FRAME_DATA category is deprecated and should not be used.
    ;
    ;
           # EXAMPLE REMOVED #
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
    
    
    save__diffrn_frame_data.array_id
        _item_description.description
    ;             This item is a pointer to _array_structure.id in the
                  ARRAY_STRUCTURE category.
    
                  DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_frame_data.array_id'
        _item.category_id             diffrn_frame_data
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_frame_data.binary_id
        _item_description.description
    ;             This item is a pointer to _array_data.binary_id in the
                  ARRAY_STRUCTURE category.
    
                  DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_frame_data.binary_id'
        _item.category_id             diffrn_frame_data
        _item.mandatory_code          implicit
        _item_type.code               int
         save_
    
    
    save__diffrn_frame_data.detector_element_id
        _item_description.description
    ;             This item is a pointer to _diffrn_detector_element.id
                  in the DIFFRN_DETECTOR_ELEMENT category.
    
                  DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_frame_data.detector_element_id'
        _item.category_id             diffrn_frame_data
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_frame_data.id
        _item_description.description
    ;             The value of _diffrn_frame_data.id must uniquely identify
                  each complete frame of data.
    
                  DEPRECATED -- DO NOT USE
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
               '_diffrn_frame_data.id'        diffrn_frame_data  yes
        _item_type.code               code
         save_
    
    save__diffrn_frame_data.details
         _item_description.description
    ;             The value of _diffrn_data_frame.details should give a
                  description of special aspects of each frame of data.
    
                  DEPRECATED -- DO NOT USE
    ;
         _item.name                  '_diffrn_frame_data.details'
         _item.category_id             diffrn_frame_data
         _item.mandatory_code          no
         _item_type.code               text
          save_
    
    ################ END DEPRECATED SECTION ###########
    
    
    ####################
    ## ITEM_TYPE_LIST ##
    ####################
    #
    #
    #  The regular expressions defined here are not compliant
    #  with the POSIX 1003.2 standard as they include the
    #  '\n' and '\t' special characters.  These regular expressions
    #  have been tested using version 0.12 of Richard Stallman's
    #  GNU regular expression library in POSIX mode.
    #  In order to allow presentation of a regular expression
    #  in a text field concatenate any line ending in a backslash
    #  with the following line, after discarding the backslash.
    #
    #  A formal definition of the '\n' and '\t' special characters
    #  is most properly done in the DDL, but for completeness, please
    #  note that '\n' is the line termination character ('newline')
    #  and '\t' is the horizontal tab character.  There is a formal
    #  ambiguity in the use of '\n' for line termination, in that
    #  the intention is that the equivalent machine/OS-dependent line
    #  termination character sequence should be accepted as a match, e.g.
    #
    #      '\r' (control-M) under MacOS
    #      '\n' (control-J) under Unix
    #      '\r\n' (control-M control-J) under DOS and MS Windows
    #
         loop_
        _item_type_list.code
        _item_type_list.primitive_code
        _item_type_list.construct
        _item_type_list.detail
                   code      char
                   '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*'
    ;              code item types/single words ...
    ;
                   ucode      uchar
                   '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*'
    ;              code item types/single words (case insensitive) ...
    ;
                   line      char
                   '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*'
    ;              char item types / multi-word items ...
    ;
                   uline     uchar
                   '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*'
    ;              char item types / multi-word items (case insensitive)...
    ;
                   text      char
                 '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*'
    ;              text item types / multi-line text ...
    ;
                   binary    char
    ;\n--CIF-BINARY-FORMAT-SECTION--\n\
    [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\
    \n--CIF-BINARY-FORMAT-SECTION----
    ;
    ;              binary items are presented as MIME-like ascii-encoded
                   sections in an imgCIF.  In a CBF, raw octet streams
                   are used to convey the same information.
    ;
                   int       numb
                   '-?[0-9]+'
    ;              int item types are the subset of numbers that are the negative
                   or positive integers.
    ;
                   float     numb
              '-?(([0-9]+)[.]?|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?'
    ;              float item types are the subset of numbers that are the floating
                   point numbers.
    ;
                   any       char
                   '.*'
    ;              A catch all for items that may take any form...
    ;
                   yyyy-mm-dd  char
    ;\
    [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9]?[0-9]\
    ((T[0-2][0-9](:[0-5][0-9](:[0-5][0-9](.[0-9]+)?)?)?)?\
    ([+-][0-5][0-9]:[0-5][0-9]))?
    ;
    ;
                   Standard format for CIF date and time strings (see
                   http://www.iucr.org/iucr-top/cif/spec/datetime.html),
                   consisting of a yyyy-mm-dd date optionally followed by
                   the character 'T' followed by a 24-hour clock time,
                   optionally followed by a signed time-zone offset.
    
                   The IUCr standard has been extended to allow for an optional
                   decimal fraction on the seconds of time.
    
                   Time is local time if no time-zone offset is given.
    
                   Note that this type extends the mmCIF yyyy-mm-dd type
                   but does not conform to the mmCIF yyyy-mm-dd:hh:mm
                   type that uses a ':' in place if the 'T' specified
                   by the IUCr standard.  For reading, both forms should
                   be accepted,  but for writing, only the IUCr form should
                   be used.
    
                   For maximal compatibility, the special time zone
                   indicator 'Z' (for 'zulu') should be accepted on
                   reading in place of '+00:00' for GMT.
    ;
    
    
    #####################
    ## ITEM_UNITS_LIST ##
    #####################
    
         loop_
        _item_units_list.code
        _item_units_list.detail
    #
         'metres'                 'metres'
         'centimetres'            'centimetres (metres * 10^( -2)^)'
         'millimetres'            'millimetres (metres * 10^( -3)^)'
         'nanometres'             'nanometres  (metres * 10^( -9)^)'
         'angstroms'              '\%Angstroms   (metres * 10^(-10)^)'
         'picometres'             'picometres  (metres * 10^(-12)^)'
         'femtometres'            'femtometres (metres * 10^(-15)^)'
    #
         'reciprocal_metres'      'reciprocal metres (metres^(-1)^)'
         'reciprocal_centimetres'
            'reciprocal centimetres ((metres * 10^( -2)^)^(-1)^)'
         'reciprocal_millimetres'
            'reciprocal millimetres ((metres * 10^( -3)^)^(-1)^)'
         'reciprocal_nanometres'
            'reciprocal nanometres  ((metres * 10^( -9)^)^(-1)^)'
         'reciprocal_angstroms'
            'reciprocal \%Angstroms   ((metres * 10^(-10)^)^(-1)^)'
         'reciprocal_picometres'
            'reciprocal picometres  ((metres * 10^(-12)^)^(-1)^)'
    #
         'nanometres_squared'     'nanometres squared (metres * 10^( -9)^)^2^'
         'angstroms_squared'      '\%Angstroms squared  (metres * 10^(-10)^)^2^'
         '8pi2_angstroms_squared'
           '8\p^2^ * \%Angstroms squared (metres * 10^(-10)^)^2^'
         'picometres_squared'     'picometres squared (metres * 10^(-12)^)^2^'
    #
         'nanometres_cubed'       'nanometres cubed (metres * 10^( -9)^)^3^'
         'angstroms_cubed'        '\%Angstroms cubed  (metres * 10^(-10)^)^3^'
         'picometres_cubed'       'picometres cubed (metres * 10^(-12)^)^3^'
    #
         'kilopascals'            'kilopascals'
         'gigapascals'            'gigapascals'
    #
         'hours'                  'hours'
         'minutes'                'minutes'
         'seconds'                'seconds'
         'microseconds'           'microseconds'
    #
         'degrees'                'degrees (of arc)'
         'degrees_squared'        'degrees (of arc) squared'
    #
         'degrees_per_minute'     'degrees (of arc) per minute'
    #
         'celsius'                'degrees (of temperature) Celsius'
         'kelvins'                'degrees (of temperature) Kelvin'
    #
         'counts'                 'counts'
         'counts_per_photon'      'counts per photon'
    #
         'electrons'              'electrons'
    #
         'electrons_squared'      'electrons squared'
    #
         'electrons_per_nanometres_cubed'
    ; electrons per nanometres cubed (electrons/(metres * 10^( -9)^)^(-3)^)
    ;
         'electrons_per_angstroms_cubed'
    ; electrons per \%Angstroms cubed (electrons/(metres * 10^(-10)^)^(-3)^)
    ;
         'electrons_per_picometres_cubed'
    ; electrons per picometres cubed (electrons/(metres * 10^(-12)^)^(-3)^)
    ;
         'kilowatts'              'kilowatts'
         'milliamperes'           'milliamperes'
         'kilovolts'              'kilovolts'
    #
         'pixels_per_element'     '(image) pixels per (array) element'
    #
         'arbitrary'
    ; arbitrary system of units.
    ;
    #
    
         loop_
        _item_units_conversion.from_code
        _item_units_conversion.to_code
        _item_units_conversion.operator
        _item_units_conversion.factor
    ###
         'metres'                   'centimetres'              '*'   1.0E+02
         'metres'                   'millimetres'              '*'   1.0E+03
         'metres'                   'nanometres'               '*'   1.0E+09
         'metres'                   'angstroms'                '*'   1.0E+10
         'metres'                   'picometres'               '*'   1.0E+12
         'metres'                   'femtometres'              '*'   1.0E+15
    #
         'centimetres'              'metres'                   '*'   1.0E-02
         'centimetres'              'millimetres'              '*'   1.0E+01
         'centimetres'              'nanometres'               '*'   1.0E+07
         'centimetres'              'angstroms'                '*'   1.0E+08
         'centimetres'              'picometres'               '*'   1.0E+10
         'centimetres'              'femtometres'              '*'   1.0E+13
    #
         'millimetres'              'metres'                   '*'   1.0E-03
         'millimetres'              'centimetres'              '*'   1.0E-01
         'millimetres'              'nanometres'               '*'   1.0E+06
         'millimetres'              'angstroms'                '*'   1.0E+07
         'millimetres'              'picometres'               '*'   1.0E+09
         'millimetres'              'femtometres'              '*'   1.0E+12
    #
         'nanometres'               'metres'                   '*'   1.0E-09
         'nanometres'               'centimetres'              '*'   1.0E-07
         'nanometres'               'millimetres'              '*'   1.0E-06
         'nanometres'               'angstroms'                '*'   1.0E+01
         'nanometres'               'picometres'               '*'   1.0E+03
         'nanometres'               'femtometres'              '*'   1.0E+06
    #
         'angstroms'                'metres'                   '*'   1.0E-10
         'angstroms'                'centimetres'              '*'   1.0E-08
         'angstroms'                'millimetres'              '*'   1.0E-07
         'angstroms'                'nanometres'               '*'   1.0E-01
         'angstroms'                'picometres'               '*'   1.0E+02
         'angstroms'                'femtometres'              '*'   1.0E+05
    #
         'picometres'               'metres'                   '*'   1.0E-12
         'picometres'               'centimetres'              '*'   1.0E-10
         'picometres'               'millimetres'              '*'   1.0E-09
         'picometres'               'nanometres'               '*'   1.0E-03
         'picometres'               'angstroms'                '*'   1.0E-02
         'picometres'               'femtometres'              '*'   1.0E+03
    #
         'femtometres'              'metres'                   '*'   1.0E-15
         'femtometres'              'centimetres'              '*'   1.0E-13
         'femtometres'              'millimetres'              '*'   1.0E-12
         'femtometres'              'nanometres'               '*'   1.0E-06
         'femtometres'              'angstroms'                '*'   1.0E-05
         'femtometres'              'picometres'               '*'   1.0E-03
    ###
         'reciprocal_centimetres'   'reciprocal_metres'        '*'   1.0E+02
         'reciprocal_centimetres'   'reciprocal_millimetres'   '*'   1.0E-01
         'reciprocal_centimetres'   'reciprocal_nanometres'    '*'   1.0E-07
         'reciprocal_centimetres'   'reciprocal_angstroms'     '*'   1.0E-08
         'reciprocal_centimetres'   'reciprocal_picometres'    '*'   1.0E-10
    #
         'reciprocal_millimetres'   'reciprocal_metres'        '*'   1.0E+03
         'reciprocal_millimetres'   'reciprocal_centimetres'   '*'   1.0E+01
         'reciprocal_millimetres'   'reciprocal_nanometres'    '*'   1.0E-06
         'reciprocal_millimetres'   'reciprocal_angstroms'     '*'   1.0E-07
         'reciprocal_millimetres'   'reciprocal_picometres'    '*'   1.0E-09
    #
         'reciprocal_nanometres'    'reciprocal_metres'        '*'   1.0E+09
         'reciprocal_nanometres'    'reciprocal_centimetres'   '*'   1.0E+07
         'reciprocal_nanometres'    'reciprocal_millimetres'   '*'   1.0E+06
         'reciprocal_nanometres'    'reciprocal_angstroms'     '*'   1.0E-01
         'reciprocal_nanometres'    'reciprocal_picometres'    '*'   1.0E-03
    #
         'reciprocal_angstroms'     'reciprocal_metres'        '*'   1.0E+10
         'reciprocal_angstroms'     'reciprocal_centimetres'   '*'   1.0E+08
         'reciprocal_angstroms'     'reciprocal_millimetres'   '*'   1.0E+07
         'reciprocal_angstroms'     'reciprocal_nanometres'    '*'   1.0E+01
         'reciprocal_angstroms'     'reciprocal_picometres'    '*'   1.0E-02
    #
         'reciprocal_picometres'    'reciprocal_metres'        '*'   1.0E+12
         'reciprocal_picometres'    'reciprocal_centimetres'   '*'   1.0E+10
         'reciprocal_picometres'    'reciprocal_millimetres'   '*'   1.0E+09
         'reciprocal_picometres'    'reciprocal_nanometres'    '*'   1.0E+03
         'reciprocal_picometres'    'reciprocal_angstroms'     '*'   1.0E+01
    ###
         'nanometres_squared'       'angstroms_squared'        '*'   1.0E+02
         'nanometres_squared'       'picometres_squared'       '*'   1.0E+06
    #
         'angstroms_squared'        'nanometres_squared'       '*'   1.0E-02
         'angstroms_squared'        'picometres_squared'       '*'   1.0E+04
         'angstroms_squared'        '8pi2_angstroms_squared'   '*'   78.9568
    
    #
         'picometres_squared'       'nanometres_squared'       '*'   1.0E-06
         'picometres_squared'       'angstroms_squared'        '*'   1.0E-04
    ###
         'nanometres_cubed'         'angstroms_cubed'          '*'   1.0E+03
         'nanometres_cubed'         'picometres_cubed'         '*'   1.0E+09
    #
         'angstroms_cubed'          'nanometres_cubed'         '*'   1.0E-03
         'angstroms_cubed'          'picometres_cubed'         '*'   1.0E+06
    #
         'picometres_cubed'         'nanometres_cubed'         '*'   1.0E-09
         'picometres_cubed'         'angstroms_cubed'          '*'   1.0E-06
    ###
         'kilopascals'              'gigapascals'              '*'   1.0E-06
         'gigapascals'              'kilopascals'              '*'   1.0E+06
    ###
         'hours'                    'minutes'                  '*'   6.0E+01
         'hours'                    'seconds'                  '*'   3.6E+03
         'hours'                    'microseconds'             '*'   3.6E+09
    #
         'minutes'                  'hours'                    '/'   6.0E+01
         'minutes'                  'seconds'                  '*'   6.0E+01
         'minutes'                  'microseconds'             '*'   6.0E+07
    #
         'seconds'                  'hours'                    '/'   3.6E+03
         'seconds'                  'minutes'                  '/'   6.0E+01
         'seconds'                  'microseconds'             '*'   1.0E+06
    #
         'microseconds'             'hours'                    '/'   3.6E+09
         'microseconds'             'minutes'                  '/'   6.0E+07
         'microseconds'             'seconds'                  '/'   1.0E+06
    ###
         'celsius'                  'kelvins'                  '-'     273.0
         'kelvins'                  'celsius'                  '+'     273.0
    ###
         'electrons_per_nanometres_cubed'
         'electrons_per_angstroms_cubed'                       '*'   1.0E+03
         'electrons_per_nanometres_cubed'
         'electrons_per_picometres_cubed'                      '*'   1.0E+09
    #
         'electrons_per_angstroms_cubed'
         'electrons_per_nanometres_cubed'                      '*'   1.0E-03
         'electrons_per_angstroms_cubed'
         'electrons_per_picometres_cubed'                      '*'   1.0E+06
    #
         'electrons_per_picometres_cubed'
         'electrons_per_nanometres_cubed'                      '*'   1.0E-09
         'electrons_per_picometres_cubed'
         'electrons_per_angstroms_cubed'                       '*'   1.0E-06
    ###
    
    ########################
    ## DICTIONARY_HISTORY ##
    ########################
    
         loop_
        _dictionary_history.version
        _dictionary_history.update
        _dictionary_history.revision
        
       1.5.2   2007-05-06
       
    ;  Further clarifications of the coordinate system. (HJB)
    ;
    
       1.5.1   2007-04-26
       
    ;  Improve defintion of X-axis to cover the case of no goniometer
       and clean up more line folds (HJB)
    ;
    
       1.5     2007-07-25
       
    ;  This is a cummulative list of the changes proposed since the
       imgCIF workshop in Hawaii in July 2006.  It is the result
       of contributions by H. J. Bernstein, A. Hammersley,
       J. Wright and W. Kabsch.
       
       2007-02-19 Consolidated changes (edited by HJB)
         + Added new data items
           '_array_structure.compression_type_flag',
           '_array_structure_list_axis.fract_displacement',
           '_array_structure_list_axis.displacement_increment',
           '_array_structure_list_axis.reference_angle',
           '_array_structure_list_axis.reference_displacement',
           '_axis.system',
           '_diffrn_detector_element.reference_center_fast',
           '_diffrn_detector_element.reference_center_slow',
           '_diffrn_scan_axis.reference_angle',
           '_diffrn_scan_axis.reference_displacement',
           '_map.details', '_map.diffrn_id',
           '_map.entry_id', '_map.id',
           '_map_segment.array_id', '_map_segment.binary_id',
           '_map_segment.mask_array_id', '_map_segment.mask_binary_id',
           '_map_segment.id', '_map_segment.map_id',
           '_map_segment.details.
         + Change type of 
           '_array_structure.byte_order' and
           '_array_structure.compression_type'
           to ucode to make these values case-insensitive
         + Add values 'packed_v2' and 'byte_offset' to enumeration of values for
           '_array_structure.compression_type'
         + Add to defintions for the binary data type to handle new compression types, maps,
           and a variety of new axis types.
        2007-07-25 Cleanup of typos for formal release (HJB)
         + Corrected text fields for reference_ tag descriptions that
           were off by one column
         + Fix typos in comments listing fract_ tags
         + Changed name of release from 1.5_DRAFT to 1.5
         + Fix unclosed text fields in various map definitions
          
    ;
    
       1.4     2006-07-04
    
    ;  This is a change to reintegrate all changes made in the course of
       publication of ITVG, by the RCSB from April 2005 through
       August 2008 and changes for the 2006 imgCIF workshop in
       Hawaii.
    
       2006-07-04 Consolidated changes for the 2006 imgCIF workshop (edited by HJB)
         + Correct type of '_array_structure_list.direction' from 'int' to 'code'.
         + Added new data items suggested by CN
           '_diffrn_data_frame.details'
           '_array_intensities.pixel_fast_bin_size',
           '_array_intensities.pixel_slow_bin_size and
           '_array_intensities.pixel_binning_method
         + Added deprecated item for completeness
           '_diffrn_frame_data.details'
         + Added entry for missing item in contents list
           '_array_structure_list_axis.displacement'
         + Added new MIME type X-BASE32K based on work by VL, KM, GD, HJB
         + Correct description of MIME boundary delimiter to start in
           column 1.
         + General cleanup of text fields to conform to changes for ITVG
           by removing empty lines at start and finish of text field.
         + Amend example for ARRAY_INTENSITIES to include binning.
         + Add local copy of type specification (as 'code') for all children
           of '_diffrn.id'.
         + For consistency, change all references to 'pi' to '\p' and all
           references to 'Angstroms' to '\%Angstroms'.
         + Clean up all powers to use IUCr convention of '^power^', as in
           '10^3^' for '10**3'.
         + Update 'yyyy-mm-dd' type regex to allow truncation from the right
           and improve comments to explain handling of related mmCIF
           'yyyy-mm-dd:hh:mm' type, and use of 'Z' for GMT time zone.
    
       2005-03-08 and
       2004-08-08 fixed cases where _item_units.code  used
                  instead of _item_type.code (JDW)
       2004-04-15 fixed item ordering in
                   _diffrn_measurement_axis.measurement_id
                   added sub_category 'vector' (JDW)
    ;
    
       1.3.2   2005-06-25
    
    ;  2005-06-25 ITEM_TYPE_LIST: code, ucode, line, uline regexps updated
                  to those of current mmCIF; float modified by allowing integers
                  terminated by a point as valid. The 'time' part of
                  yyyy-mm-dd types made optional in the regexp. (BM)
    
       2005-06-17 Minor corrections as for proofs for IT G Chapter 4.6
       (NJA)
    
       2005-02-21  Minor corrections to spelling and punctuation
       (NJA)
    
       2005-01-08 Changes as per Nicola Ashcroft.
       + Updated example 1 for DIFFRN_MEASUREMENT to agree with mmCIF.
       + Spelled out "micrometres" for "um" and "millimetres" for "mm".
       + Removed phrase "which may be stored" from ARRAY_STRUCTURE
         description.
       + Removed unused 'byte-offsets' compressions and updated
         cites to ITVG for '_array_structure.compression_type'.
       (HJB)
    ;
    
       1.3.1   2003-08-13
    ;
       Changes as per Frances C. Bernstein.
       + Identify initials.
       + Adopt British spelling for centre in text.
       + Set \p and \%Angstrom and powers.
       + Clean up commas and unclear wordings.
       + Clean up tenses in history.
       Changes as per Gotzon Madariaga.
       + Fix the ARRAY_DATA example to align '_array_data.binary_id'
       and X-Binary-ID.
       + Add a range to '_array_intensities.gain_esd'.
       + In the example of DIFFRN_DETECTOR_ELEMENT,
       '_diffrn_detector_element.id' and
       '_diffrn_detector_element.detector_id' interchanged.
       + Fix typos for direction, detector and axes.
       + Clarify description of polarisation.
       + Clarify axes in '_diffrn_detector_element.center[1]'
        '_diffrn_detector_element.center[2]'.
       + Add local item types for items that are pointers.
       (HJB)
    ;
    
    
       1.3.0   2003-07-24
    ;
       Changes as per Brian McMahon.
       + Consistently quote tags embedded in text.
       + Clean up introductory comments.
       + Adjust line lengths to fit in 80 character window.
       + Fix several descriptions in AXIS category which
         referred to '_axis.type' instead of the current item.
       + Fix erroneous use of deprecated item
         '_diffrn_detector_axis.id' in examples for
         DIFFRN_SCAN_AXIS.
       + Add deprecated items '_diffrn_detector_axis.id'
         and '_diffrn_measurement_axis.id'.
       (HJB)
    ;
    
    
       1.2.4   2003-07-14
    ;
       Changes as per I. David Brown.
       + Enhance descriptions in DIFFRN_SCAN_AXIS to make them less
         dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS.
       + Provide a copy of the deprecated DIFFRN_FRAME_DATA
         category for completeness.
       (HJB)
    ;
    
    
       1.2.3   2003-07-03
    ;
       Cleanup to conform to ITVG.
       + Correct sign error in ..._cubed units.
       + Correct '_diffrn_radiation.polarisn_norm' range.
       (HJB)
    ;
    
    
       1.2.2   2003-03-10
    ;
       Correction of typos in various DIFFRN_SCAN_AXIS descriptions.
       (HJB)
    ;
    
    
       1.2.1   2003-02-22
    ;
       Correction of ATOM_ for ARRAY_ typos in various descriptions.
       (HJB)
    ;
    
    
       1.2     2003-02-07
    ;
       Corrections to encodings (remove extraneous hyphens) remove
       extraneous underscore in '_array_structure.encoding_type'
       enumeration.  Correct typos in items units list.  (HJB)
    ;
    
    
       1.1.3   2001-04-19
    ;
       Another typo corrections by Wilfred Li, and cleanup by HJB.
    ;
    
    
       1.1.2   2001-03-06
    ;
       Several typo corrections by Wilfred Li.
    ;
    
    
       1.1.1   2001-02-16
    ;
       Several typo corrections by JW.
    ;
    
    
       1.1     2001-02-06
    ;
       Draft resulting from discussions on header for use at NSLS.  (HJB)
    
       + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME.
    
       + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'.
    
       + Add '_diffrn_measurement_axis.measurement_device' and change
         '_diffrn_measurement_axis.id' to
         '_diffrn_measurement_axis.measurement_id'.
    
       + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source',
        '_diffrn_radiation.div_x_y_source',
        '_diffrn_radiation.polarizn_source_norm',
       '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end',
       '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr',
       '_diffrn_scan_axis.displacement_rstrt_incr',
       '_diffrn_scan_frame_axis.angle_increment',
       '_diffrn_scan_frame_axis.angle_rstrt_incr',
       '_diffrn_scan_frame_axis.displacement',
       '_diffrn_scan_frame_axis.displacement_increment',and
       '_diffrn_scan_frame_axis.displacement_rstrt_incr'.
    
       + Add '_diffrn_measurement.device' to category key.
    
       + Update yyyy-mm-dd to allow optional time with fractional seconds
         for time stamps.
    
       + Fix typos caught by RS.
    
       + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to
         allow for coupled axes, as in spiral scans.
    
       + Add examples for fairly complete headers thanks to R. Sweet and P.
         Ellis.
    ;
    
    
       1.0     2000-12-21
    ;
       Release version - few typos and tidying up.  (BM & HJB)
    
       + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end
       of dictionary.
    
       + Alphabetize dictionary.
    ;
    
    
       0.7.1   2000-09-29
    ;
       Cleanup fixes.  (JW)
    
       + Correct spelling of diffrn_measurement_axis in '_axis.id'
    
       + Correct ordering of uses of '_item.mandatory_code' and
       '_item_default.value'.
    ;
    
    
       0.7.0   2000-09-09
    ;
       Respond to comments by I. David Brown.  (HJB)
    
       + Add further comments on '\n' and '\t'.
    
       + Update ITEM_UNITS_LIST by taking section from mmCIF dictionary
         and adding metres.  Change 'meter' to 'metre' throughout.
    
       + Add missing enumerations to '_array_structure.compression_type'
         and make 'none' the default.
    
       + Remove parent-child relationship between
         '_array_structure_list.index' and '_array_structure_list.precedence'.
    
       + Improve alphabetization.
    
       + Fix '_array_intensities_gain.esd' related function.
    
       + Improve comments in AXIS.
    
       + Fix DIFFRN_FRAME_DATA example.
    
       + Remove erroneous DIFFRN_MEASUREMENT example.
    
       + Add '_diffrn_measurement_axis.id' to the category key.
    ;
    
    
       0.6.0   1999-01-14
    ;
       Remove redundant information for ENC_NONE data.  (HJB)
    
       + After the D5 remove binary section identifier, size and
         compression type.
    
       + Add Control-L to header.
    ;
    
    
       0.5.1   1999-01-03
    ;
       Cleanup of typos and syntax errors.  (HJB)
    
       + Cleanup example details for DIFFRN_SCAN category.
    
       + Add missing quote marks for '_diffrn_scan.id' definition.
    ;
    
    
       0.5   1999-01-01
    ;
       Modifications for axis definitions and reduction of binary header.  (HJB)
    
       + Restore '_diffrn_detector.diffrn_id' to DIFFRN_DETECTOR KEY.
    
       + Add AXIS category.
    
       + Bring in complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories
         from cif_mm.dic for clarity.
    
       + Change '_array_structure.encoding_type' from type code to uline and
         added X-Binary-Element-Type to MIME header.
    
       + Add detector beam centre '_diffrn_detector_element.center[1]' and
         '_diffrn_detector_element.center[2]'.
    
       + Correct item name of '_diffrn_refln.frame_id'.
    
       + Replace reference to '_array_intensities.undefined' by
         '_array_intensities.undefined_value'.
    
       + Replace references to '_array_intensity.scaling' with
         '_array_intensities.scaling'.
    
       + Add DIFFRN_SCAN... categories.
    ;
    
    
       0.4   1998-08-11
    ;
       Modifications to the 0.3 imgCIF draft.  (HJB)
    
       + Reflow comment lines over 80 characters and corrected typos.
    
       + Update examples and descriptions of MIME encoded data.
    
       + Change name to cbfext98.dic.
    ;
    
    
       0.3   1998-07-04
    ;
       Modifications for imgCIF.  (HJB)
    
       + Add binary type, which is a text field containing a variant on
         MIME encoded data.
    
       + Change type of '_array_data.data' to binary and specify internal
         structure of raw binary data.
    
       + Add '_array_data.binary_id', and make
         '_diffrn_frame_data.binary_id' and '_array_intensities.binary_id'
         into pointers to this item.
    ;
    
    
       0.2   1997-12-02
    ;
       Modifications to the CBF draft.  (JW)
    
       + Add category hierarchy for describing frame data developed from
         discussions at the BNL imgCIF Workshop Oct 1997.   The following
         changes are made in implementing the workshop draft.  Category
         DIFFRN_ARRAY_DATA is renamed to DIFFRN_FRAME_DATA.  Category
         DIFFRN_FRAME_TYPE is renamed to DIFFRN_DETECTOR_ELEMENT.   The
         parent item for '_diffrn_frame_data.array_id' is changed from
         '_array_structure_list.array_id' to '_array_structure.id'. Item
         '_diffrn_detector.array_id' is deleted.
       + Add data item '_diffrn_frame_data.binary_id' to identify data
         groups within a binary section.  The formal identification of the
         binary section is still fuzzy.
    ;
    
    
       0.1   1997-01-24
    ;
       First draft of this dictionary in DDL 2.1 compliant format by John
       Westbrook (JW).  This version is adapted from the Crystallographic
       Binary File (CBF) Format Draft Proposal provided by Andy Hammersley
       (AH).
    
       Modifications to the CBF draft.  (JW)
    
       + In this version the array description has been cast in the categories
         ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST.  These categories
         have been generalized to describe array data  of arbitrary dimension.
    
       + Array data in this description are contained in the category
         ARRAY_DATA.  This departs from the CBF notion of data existing
         in some special comment. In this description, data are handled as an
         ordinary data item encapsulated in a character data type.   Although
         data this manner deviates from CIF conventions, it does not violate
         any DDL 2.1 rules.  DDL 2.1 regular expressions can be used to define
         the binary representation which will permit some level of data
         validation.  In this version, the placeholder type code "any" has
         been used. This translates to a regular expression which will match
         any pattern.
    
         It should be noted that DDL 2.1 already supports array data objects
         although these have not been used in the current mmCIF dictionary.
         It may be possible to use the DDL 2.1 ITEM_STRUCTURE and
         ITEM_STRUCTURE_LIST categories to provide the information that is
         carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST.  By
         moving the array structure to the DDL level it would be possible to
         define an array type as well as a regular expression defining the
         data format.
    
       + Multiple array sections can be properly handled within a single
         datablock.
    ;
    
    
    #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof
    
    ./CBFlib-0.9.2.2/doc/Idiffrn_measurement_axis.measurement_device.html0000644000076500007650000000531511603702115024112 0ustar yayayaya (IUCr) CIF Definition save__diffrn_measurement_axis.measurement_device

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_measurement_axis.measurement_device

    Name:
    '_diffrn_measurement_axis.measurement_device'

    Definition:

            This data item is a pointer to _diffrn_measurement.device
                   in the DIFFRN_MEASUREMENT category.
    
    

    Type: text

    Mandatory item: implicit

    Category: diffrn_measurement_axis

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Iaxis.offset[3].html0000644000076500007650000000511411603702115016147 0ustar yayayaya (IUCr) CIF Definition save__axis.offset[3]

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _axis.offset[3]

    Name:
    '_axis.offset[3]'

    Definition:

            The [3] element of the three-element vector used to specify
                   the offset to the base of a rotation or translation axis.
    
                   The vector is specified in millimetres.
    
    

    Type: float

    Mandatory item: no


    Enumeration default: 0.0

    Category: axis

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Dtypecodes.html0000644000076500007650000001427411603702115015344 0ustar yayayaya (IUCr) CIF dictionary cif_img.dic Extended data types

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF)

    Extended data types

    The following extended data types are defined in this dictionary:

    Code Primitive data type Regular expression construct Description
     
    code char [_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]* code item types/single words ...
    ucode uchar [_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]* code item types/single words (case insensitive) ...
    line char [][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]* char item types / multi-word items ...
    uline uchar [][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]* char item types / multi-word items (case insensitive)...
    text char [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]* text item types / multi-line text ...
    binary char \n--CIF-BINARY-FORMAT-SECTION--\n\ [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\ \n--CIF-BINARY-FORMAT-SECTION---- binary items are presented as MIME-like ascii-encoded sections in an imgCIF. In a CBF, raw octet streams are used to convey the same information.
    int numb -?[0-9]+ int item types are the subset of numbers that are the negative or positive integers.
    float numb -?(([0-9]+)[.]?|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)? float item types are the subset of numbers that are the floating point numbers.
    any char .* A catch all for items that may take any form...
    yyyy-mm-dd char \ [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9]?[0-9]\ ((T[0-2][0-9](:[0-5][0-9](:[0-5][0-9](.[0-9]+)?)?)?)?\ ([+-][0-5][0-9]:[0-5][0-9]))? Standard format for CIF date and time strings (see http://www.iucr.org/iucr-top/cif/spec/datetime.html), consisting of a yyyy-mm-dd date optionally followed by the character 'T' followed by a 24-hour clock time, optionally followed by a signed time-zone offset. The IUCr standard has been extended to allow for an optional decimal fraction on the seconds of time. Time is local time if no time-zone offset is given. Note that this type extends the mmCIF yyyy-mm-dd type but does not conform to the mmCIF yyyy-mm-dd:hh:mm type that uses a ':' in place if the 'T' specified by the IUCr standard. For reading, both forms should be accepted, but for writing, only the IUCr form should be used. For maximal compatibility, the special time zone indicator 'Z' (for 'zulu') should be accepted on reading in place of '+00:00' for GMT.

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/cif_img_1.6.4_2Jul11.dic0000644000076500007650000120075511603745600016225 0ustar yayayayadata_cif_img.dic _datablock.id cif_img.dic _datablock.description ; ############################################################################## # # # Image CIF Dictionary (imgCIF) # # and Crystallographic Binary File Dictionary (CBF) # # Extending the Macromolecular CIF Dictionary (mmCIF) # # # # Version 1.6.4 # # of 2011-07-02 # # ################################################################### # # # *** WARNING *** THIS IS A DRAFT FOR DISCUSSSION *** WARNING *** # # # # SUBJECT TO CHANGE WITHOUT NOTICE # # # # SEND COMMENTS TO imgcif-l@iucr.org CITING THE VERSION # # # ################################################################### # # This draft edited by H. J. Bernstein # # # # by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook # # # # This dictionary was adapted from format discussed at the imgCIF Workshop, # # held at BNL Oct 1997 and the Crystallographic Binary File Format Draft # # Proposal by Andrew Hammersley. The first DDL 2.1 Version was created by # # John Westbrook. This version was drafted by Herbert J. Bernstein and # # incorporates comments by I. David Brown, John Westbrook, Brian McMahon, # # Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li, Gotzon Madariaga, # # Frances C. Bernstein, Chris Nielsen, Nicola Ashcroft and others. # ############################################################################## ############################################################################## # CONTENTS # # CATEGORY_GROUP_LIST # SUB_CATEGORY # # category ARRAY_DATA # # _array_data.array_id # _array_data.binary_id # _array_data.data # _array_data.header_contents # _array_data.header_convention # _array_data.variant # # category ARRAY_ELEMENT_SIZE # # _array_element_size.array_id # _array_element_size.index # _array_element_size.size # _array_element_size.variant # # category ARRAY_INTENSITIES # # _array_intensities.array_id # _array_intensities.binary_id # _array_intensities.gain # _array_intensities.gain_esd # _array_intensities.linearity # _array_intensities.offset # _array_intensities.scaling # _array_intensities.overload # _array_intensities.undefined_value # _array_intensities.pixel_fast_bin_size # _array_intensities.pixel_slow_bin_size # _array_intensities.pixel_binning_method # _array_intensities.variant # # category ARRAY_STRUCTURE # # _array_structure.byte_order # _array_structure.compression_type # _array_structure.compression_type_flag # _array_structure.encoding_type # _array_structure.id # _array_structure.variant # # category ARRAY_STRUCTURE_LIST # # _array_structure_list.axis_set_id # _array_structure_list.array_id # _array_structure_list.dimension # _array_structure_list.direction # _array_structure_list.index # _array_structure_list.precedence # _array_structure_list.variant # # category ARRAY_STRUCTURE_LIST_AXIS # # _array_structure_list_axis.axis_id # _array_structure_list_axis.axis_set_id # _array_structure_list_axis.angle # _array_structure_list_axis.angle_increment # _array_structure_list_axis.displacement # _array_structure_list_axis.fract_displacement # _array_structure_list_axis.displacement_increment # _array_structure_list_axis.fract_displacement_increment # _array_structure_list_axis.angular_pitch # _array_structure_list_axis.radial_pitch # _array_structure_list_axis.reference_angle # _array_structure_list_axis.reference_displacement # _array_structure_list_axis.variant # # category AXIS # # _axis.depends_on # _axis.equipment # _axis.id # _axis.offset[1] # _axis.offset[2] # _axis.offset[3] # _axis.type # _axis.system # _axis.vector[1] # _axis.vector[2] # _axis.vector[3] # _axis.variant # # category DIFFRN_DATA_FRAME # # _diffrn_data_frame.array_id # _diffrn_data_frame.binary_id # _diffrn_data_frame.center_fast # _diffrn_data_frame.center_slow # _diffrn_data_frame.center_units # _diffrn_data_frame.detector_element_id # _diffrn_data_frame.id # _diffrn_data_frame.details # _diffrn_data_frame.variant # # category DIFFRN_DETECTOR # # _diffrn_detector.details # _diffrn_detector.detector # _diffrn_detector.diffrn_id # _diffrn_detector.dtime # _diffrn_detector.id # _diffrn_detector.number_of_axes # _diffrn_detector.type # _diffrn_detector.variant # # category DIFFRN_DETECTOR_AXIS # # _diffrn_detector_axis.axis_id # _diffrn_detector_axis.detector_id # _diffrn_detector_axis.variant # # category DIFFRN_DETECTOR_ELEMENT # # _diffrn_detector_element.id # _diffrn_detector_element.detector_id # _diffrn_detector_element.reference_center_fast # _diffrn_detector_element.reference_center_slow # _diffrn_detector_element.reference_center_units # _diffrn_detector_element.variant # # category DIFFRN_MEASUREMENT # # _diffrn_measurement.diffrn_id # _diffrn_measurement.details # _diffrn_measurement.device # _diffrn_measurement.device_details # _diffrn_measurement.device_type # _diffrn_measurement.id # _diffrn_measurement.method # _diffrn_measurement.number_of_axes # _diffrn_measurement.sample_detector_distance # _diffrn_measurement.sample_detector_voffset # _diffrn_measurement.specimen_support # _diffrn_measurement.variant # # category DIFFRN_MEASUREMENT_AXIS # # _diffrn_measurement_axis.axis_id # _diffrn_measurement_axis.measurement_device # _diffrn_measurement_axis.measurement_id # _diffrn_measurement_axis.variant # # category DIFFRN_RADIATION # # _diffrn_radiation.collimation # _diffrn_radiation.diffrn_id # _diffrn_radiation.div_x_source # _diffrn_radiation.div_y_source # _diffrn_radiation.div_x_y_source # _diffrn_radiation.filter_edge' # _diffrn_radiation.inhomogeneity # _diffrn_radiation.monochromator # _diffrn_radiation.polarisn_norm # _diffrn_radiation.polarisn_ratio # _diffrn_radiation.polarizn_source_norm # _diffrn_radiation.polarizn_source_ratio # _diffrn_radiation.probe # _diffrn_radiation.type # _diffrn_radiation.xray_symbol # _diffrn_radiation.wavelength_id # _diffrn_radiation.variant # # category DIFFRN_REFLN # # _diffrn_refln.frame_id # _diffrn_refln.variant # # category DIFFRN_SCAN # # _diffrn_scan.id # _diffrn_scan.date_end # _diffrn_scan.date_start # _diffrn_scan.integration_time # _diffrn_scan.frame_id_start # _diffrn_scan.frame_id_end # _diffrn_scan.frames # _diffrn_scan.time_period # _diffrn_scan.time_rstrt_incr # _diffrn_scan.variant # # category DIFFRN_SCAN_AXIS # # _diffrn_scan_axis.axis_id # _diffrn_scan_axis.angle_start # _diffrn_scan_axis.angle_range # _diffrn_scan_axis.angle_increment # _diffrn_scan_axis.angle_rstrt_incr # _diffrn_scan_axis.displacement_start # _diffrn_scan_axis.displacement_range # _diffrn_scan_axis.displacement_increment # _diffrn_scan_axis.displacement_rstrt_incr # _diffrn_scan_axis.reference_angle # _diffrn_scan_axis.reference_displacement # _diffrn_scan_axis.scan_id # _diffrn_scan_axis.variant # # category DIFFRN_SCAN_FRAME # # _diffrn_scan_frame.date # _diffrn_scan_frame.frame_id # _diffrn_scan_frame.frame_number # _diffrn_scan_frame.integration_time # _diffrn_scan_frame.scan_id # _diffrn_scan_frame.time_period # _diffrn_scan_frame.time_rstrt_incr # _diffrn_scan_frame.variant # # category DIFFRN_SCAN_FRAME_AXIS # # _diffrn_scan_frame_axis.axis_id # _diffrn_scan_frame_axis.angle # _diffrn_scan_frame_axis.angle_increment # _diffrn_scan_frame_axis.angle_rstrt_incr # _diffrn_scan_frame_axis.displacement # _diffrn_scan_frame_axis.displacement_increment # _diffrn_scan_frame_axis.displacement_rstrt_incr # _diffrn_scan_frame_axis.reference_angle # _diffrn_scan_frame_axis.reference_displacement # _diffrn_scan_frame_axis.frame_id # _diffrn_scan_frame_axis.variant # # category DIFFRN_SCAN_FRAME_MONITOR # # _diffrn_scan_frame_monitor.id # _diffrn_scan_frame_monitor.detector_id # _diffrn_scan_frame_monitor.scan_id # _diffrn_data_frame_monitor.frame_id # _diffrn_data_frame_monitor.integration_time # _diffrn_data_frame_monitor.monitor_value # _diffrn_data_frame_monitor.variant # # category MAP # # _map.details # _map.diffrn_id # _map.entry_id # _map.id # _map.variant # # category MAP_SEGMENT # # _map_segment.array_id # _map_segment.binary_id # _map_segment.mask_array_id # _map_segment.mask_binary_id # _map_segment.id # _map_segment.map_id # _map_segment.details # _map_segment.variant # # category VARIANT # # _variant.details # _variant.role # _variant.timestamp # _variant.variant # _variant.variant_of # # ***DEPRECATED*** data items # # _diffrn_detector_axis.id # _diffrn_detector_element.center[1] # _diffrn_detector_element.center[2] # _diffrn_measurement_axis.id # # ***DEPRECATED*** category DIFFRN_FRAME_DATA # # _diffrn_frame_data.array_id # _diffrn_frame_data.binary_id # _diffrn_frame_data.detector_element_id # _diffrn_frame_data.id # _diffrn_frame_data.details # # # ITEM_TYPE_LIST # ITEM_UNITS_LIST # DICTIONARY_HISTORY # ############################################################################## +-------------------------------------------------------------------------------------------------------------+ |ARRAY_DATA_GROUP|Categories that describe array data. | | |--------------------------------------------------------------------------------------------| | |+------------------------------------------------------------------------------------------+| | || ARRAY_DATA | Data items in the ARRAY_DATA category are the containers for the || | || | array data items described in the category ARRAY_STRUCTURE. || | || | || | || | It is recognized that the data in this category needs to be used || | || | in two distinct ways. During a data collection the lack of || | || | ancillary data and timing constraints in processing data may || | || | dictate the need to make a 'miniCBF' nothing more than an || | || | essential minimum of information to record the results of the || | || | data collection. In that case it is proper to use the ARRAY_DATA || | || | category as a container for just a single image and a compacted, || | || | beam-line dependent list of data collection parameter values. In || | || | such a case, only the tags '_array_data.header_convention', || | || | '_array_data.header_contents' and '_array_data.data' need be || | || | populated. || | || | || | || | For full processing and archiving, most of the tags in this || | || | dictionary will need to be populated. || | ||----------------------+-------------------------------------------------------------------|| | || ARRAY_ELEMENT_SIZE | Data items in the ARRAY_ELEMENT_SIZE category record the physical || | || | size of array elements along each array dimension. || | ||----------------------+-------------------------------------------------------------------|| | || ARRAY_INTENSITIES | Data items in the ARRAY_INTENSITIES category record the || | || | information required to recover the intensity data from the set || | || | of data values stored in the ARRAY_DATA category. || | || | || | || | The detector may have a complex relationship between the raw || | || | intensity values and the number of incident photons. In most || | || | cases, the number stored in the final array will have a simple || | || | linear relationship to the actual number of incident photons, || | || | given by _array_intensities.gain. If raw, uncorrected values are || | || | presented (e.g. for calibration experiments), the value of || | || | _array_intensities.linearity will be 'raw' and || | || | _array_intensities.gain will not be used. || | ||----------------------+-------------------------------------------------------------------|| | || ARRAY_STRUCTURE | Data items in the ARRAY_STRUCTURE category record the || | || | organization and encoding of array data that may be stored in the || | || | ARRAY_DATA category. || | ||------------------------------------------------------------------------------------------|| | || +--------------------------------------------------------------------------------------+ || | || | | ARRAY_STRUCTURE_LIST | Data items in the ARRAY_STRUCTURE_LIST category | || | || | | | record the size and organization of each array | || | || | | | dimension. | || | || | | | | || | || | | | The relationship to physical axes may be given. | || | || | |----------------------------------------------------------------------------------| || | || | | +------------------------------------------------------------------------------+ | || | || | | | | ARRAY_STRUCTURE_LIST_AXIS | Data items in the ARRAY_STRUCTURE_LIST_AXIS | | || | || | | | | | category describe the physical settings of | | || | || | | | | | sets of axes for the centres of pixels that | | || | || | | | | | correspond to data points described in the | | || | || | | | | | ARRAY_STRUCTURE_LIST category. | | || | || | | | | | | | || | || | | | | | In the simplest cases, the physical | | || | || | | | | | increments of a single axis correspond to | | || | || | | | | | the increments of a single array index. More | | || | || | | | | | complex organizations, e.g. spiral scans, | | || | || | | | | | may require coupled motions along multiple | | || | || | | | | | axes. | | || | || | | | | | | | || | || | | | | | Note that a spiral scan uses two coupled | | || | || | | | | | axes: one for the angular direction and one | | || | || | | | | | for the radial direction. This differs from | | || | || | | | | | a cylindrical scan for which the two axes | | || | || | | | | | are not coupled into one set. | | || | || | | +------------------------------------------------------------------------------+ | || | || +--------------------------------------------------------------------------------------+ || | |+------------------------------------------------------------------------------------------+| |----------------+--------------------------------------------------------------------------------------------| |AXIS_GROUP |Categories that describe axes. | | |--------------------------------------------------------------------------------------------| | |+------------------------------------------------------------------------------------------+| | || AXIS | Data items in the AXIS category record the information required to describe the || | || | various goniometer, detector, source and other axes needed to specify a data || | || | collection or the axes defining the coordinate system of an image. || | || | || | || | The location of each axis is specified by two vectors: the axis itself, given by || | || | a unit vector in the direction of the axis, and an offset to the base of the unit || | || | vector. || | || | || | || | The vectors defining an axis are referenced to an appropriate coordinate system. || | || | The axis vector, itself, is a dimensionless unit vector. Where meaningful, the || | || | offset vector is given in millimetres. In coordinate systems not measured in || | || | metres, the offset is not specified and is taken as zero. || | || | || | || | The available coordinate systems are: || | || | || | || | The imgCIF standard laboratory coordinate system || | || | The direct lattice (fractional atomic coordinates) || | || | The orthogonal Cartesian coordinate system (real space) || | || | The reciprocal lattice || | || | An abstract orthogonal Cartesian coordinate frame || | |+------------------------------------------------------------------------------------------+| |----------------+--------------------------------------------------------------------------------------------| |DIFFRN_GROUP |Categories that describe details of the diffraction experiment. | | |--------------------------------------------------------------------------------------------| | |+------------------------------------------------------------------------------------------+| | || DIFFRN_DATA_FRAME | Data items in the DIFFRN_DATA_FRAME category record the || | || | details about each frame of data. || | || | || | || | The items in this category were previously in a || | || | DIFFRN_FRAME_DATA category, which is now deprecated. The || | || | items from the old category are provided as aliases but || | || | should not be used for new work. || | ||--------------------------+---------------------------------------------------------------|| | || DIFFRN_DETECTOR | Data items in the DIFFRN_DETECTOR category describe the || | || | detector used to measure the scattered radiation, including || | || | any analyser and post-sample collimation. || | ||------------------------------------------------------------------------------------------|| | || +--------------------------------------------------------------------------------------+ || | || | | DIFFRN_DETECTOR_AXIS | Data items in the DIFFRN_DETECTOR_AXIS category associate | || | || | | | axes with detectors. | || | || +--------------------------------------------------------------------------------------+ || | ||------------------------------------------------------------------------------------------|| | || +--------------------------------------------------------------------------------------+ || | || | | DIFFRN_DETECTOR_ELEMENT | Data items in the DIFFRN_DETECTOR_ELEMENT category | || | || | | | record the details about spatial layout and other | || | || | | | characteristics of each element of a detector which | || | || | | | may have multiple elements. | || | || | | | | || | || | | | In most cases, giving more detailed information in | || | || | | | ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS is | || | || | | | preferable to simply providing the centre of the | || | || | | | detector element. | || | || +--------------------------------------------------------------------------------------+ || | ||------------------------------------------------------------------------------------------|| | || DIFFRN_MEASUREMENT | Data items in the DIFFRN_MEASUREMENT category record details || | || | about the device used to orient and/or position the crystal || | || | during data measurement and the manner in which the || | || | diffraction data were measured. || | ||------------------------------------------------------------------------------------------|| | || +--------------------------------------------------------------------------------------+ || | || | | DIFFRN_MEASUREMENT_AXIS | Data items in the DIFFRN_MEASUREMENT_AXIS category | || | || | | | associate axes with goniometers. | || | || +--------------------------------------------------------------------------------------+ || | ||------------------------------------------------------------------------------------------|| | || DIFFRN_RADIATION | Data items in the DIFFRN_RADIATION category describe the || | || | radiation used for measuring diffraction intensities, its || | || | collimation and monochromatization before the sample. || | || | || | || | Post-sample treatment of the beam is described by data items || | || | in the DIFFRN_DETECTOR category. || | ||--------------------------+---------------------------------------------------------------|| | || DIFFRN_REFLN | This category redefinition has been added to extend the key || | || | of the standard DIFFRN_REFLN category. || | || | || | || | Data items in the DIFFRN_REFLN category record details about || | || | the intensities in the diffraction data set identified by || | || | _diffrn_refln.diffrn_id. || | || | || | || | The DIFFRN_REFLN data items refer to individual intensity || | || | measurements and must be included in looped lists. || | || | || | || | The DIFFRN_REFLNS data items specify the parameters that || | || | apply to all intensity measurements in the particular || | || | diffraction data set identified by _diffrn_reflns.diffrn_id || | || | and _diffrn_refln.frame_id || | ||--------------------------+---------------------------------------------------------------|| | || DIFFRN_SCAN | Data items in the DIFFRN_SCAN category describe the || | || | parameters of one or more scans, relating axis positions to || | || | frames. || | ||------------------------------------------------------------------------------------------|| | || +--------------------------------------------------------------------------------------+ || | || | | DIFFRN_SCAN_AXIS | Data items in the DIFFRN_SCAN_AXIS category describe the | || | || | | | settings of axes for particular scans. Unspecified axes are | || | || | | | assumed to be at their zero points. | || | || +--------------------------------------------------------------------------------------+ || | ||------------------------------------------------------------------------------------------|| | || +--------------------------------------------------------------------------------------+ || | || | | DIFFRN_SCAN_FRAME | Data items in the DIFFRN_SCAN_FRAME category describe the | || | || | | | relationships of particular frames to scans. | || | || +--------------------------------------------------------------------------------------+ || | ||------------------------------------------------------------------------------------------|| | || +--------------------------------------------------------------------------------------+ || | || | | +------------------------------------------------------------------------------+ | || | || | | | | DIFFRN_SCAN_FRAME_AXIS | Data items in the DIFFRN_SCAN_FRAME_AXIS | | || | || | | | | | category describe the settings of axes for | | || | || | | | | | particular frames. Unspecified axes are assumed | | || | || | | | | | to be at their zero points. If, for any given | | || | || | | | | | frame, nonzero values apply for any of the data | | || | || | | | | | items in this category, those values should be | | || | || | | | | | given explicitly in this category and not | | || | || | | | | | simply inferred from values in | | || | || | | | | | DIFFRN_SCAN_AXIS. | | || | || | | +------------------------------------------------------------------------------+ | || | || |---+----------------------------------------------------------------------------------| || | || | | +------------------------------------------------------------------------------+ | || | || | | | | DIFFRN_SCAN_FRAME_MONITOR | Data items in the DIFFRN_SCAN_FRAME_MONITOR | | || | || | | | | | category record the values and details about | | || | || | | | | | each monitor for each frame of data during a | | || | || | | | | | scan. | | || | || | | | | | | | || | || | | | | | Each monitor value is uniquely identified by | | || | || | | | | | the combination of the scan_id given by | | || | || | | | | | _diffrn_scan_frame.scan_id the frame_id | | || | || | | | | | given by | | || | || | | | | | _diffrn_scan_frame_monitor.frame_id, the | | || | || | | | | | monitor's detector_id given by | | || | || | | | | | _diffrn_scan_frame_monitor.monitor_id, and a | | || | || | | | | | 1-based ordinal given by | | || | || | | | | | _diffrn_scan_frame_monitor.id. | | || | || | | | | | | | || | || | | | | | If there is only one frame for the scan, the | | || | || | | | | | value of _diffrn_scan_frame_monitor.frame_id | | || | || | | | | | may be omitted. | | || | || | | | | | | | || | || | | | | | A single frame may have more than one | | || | || | | | | | monitor value, and each monitor value may be | | || | || | | | | | the result of integration over the entire | | || | || | | | | | frame integration time given by the value of | | || | || | | | | | _diffrn_scan_frame.integration_time or many | | || | || | | | | | monitor values may be reported over shorter | | || | || | | | | | times given by the value of | | || | || | | | | | _diffrn_scan_frame_monitor.integration_time. | | || | || | | | | | If only one monitor value for a given | | || | || | | | | | monitor is collected during the integration | | || | || | | | | | time of the frame, the value of | | || | || | | | | | _diffrn_scan_frame_monitor.id may be | | || | || | | | | | omitted. | | || | || | | +------------------------------------------------------------------------------+ | || | || +--------------------------------------------------------------------------------------+ || | |+------------------------------------------------------------------------------------------+| |----------------+--------------------------------------------------------------------------------------------| |MAP_GROUP |Categories that describe maps. | | |--------------------------------------------------------------------------------------------| | |+------------------------------------------------------------------------------------------+| | || MAP | Data items in the MAP category record the details of a maps. Maps record values || | || | of parameters, such as density, that are functions of position within a cell or || | || | are functions of orthogonal coordinates in three space. || | || | || | || | A map may is composed of one or more map segments specified in the MAP_SEGMENT || | || | category. || | || | || | || | Examples are given in the MAP_SEGMENT category. || | ||------------------------------------------------------------------------------------------|| | || +--------------------------------------------------------------------------------------+ || | || | | MAP_SEGMENT | Data items in the MAP_SEGMENT category record the details about | || | || | | | each segment (section or brick) of a map. | || | || +--------------------------------------------------------------------------------------+ || | |+------------------------------------------------------------------------------------------+| |----------------+--------------------------------------------------------------------------------------------| |VARIANT_GROUP |Categories that describe variants | | |--------------------------------------------------------------------------------------------| | |+------------------------------------------------------------------------------------------+| | || VARIANT | Data items in the VARIANT category record the details about sets of variants || | || | of data items. || | || | || | || | There is sometimes a need to allow for multiple versions of the same data || | || | items in order to allow for refinements and corrections to earlier || | || | assumptions, observations and calculations. In order to allow data sets to || | || | contain more than one variant of the same information, an optional ...variant || | || | data item as a pointer to _variant.variant has been added to the key of every || | || | category, as an implicit data item with a null (empty) default value. || | || | || | || | All rows in a category with the same variant value are considered to be || | || | related to one another and to all rows in other categories with the same || | || | variant value. For a given variant, all such rows are also considered to be || | || | related to all rows with a null variant value, except that a row with a null || | || | variant value is for which all other components of its key are identical to || | || | those entries in another row with a non-null variant value is not related the || | || | the rows with that non-null variant value. This behavior is similar to the || | || | convention for identifying alternate conformers in an atom list. || | || | || | || | An optional role may be specified for a variant as the value of _variant.role. || | || | Possible roles are null, "preferred", "raw data", "unsuccessful trial". || | || | || | || | Variants may carry an optional timestamp as the value of _variant.timestamp. || | || | || | || | Variants may be related to other variants from which they were derived by the || | || | value of _variant.variant_of || | || | || | || | Further details about the variant may be specified as the value of || | || | _variant.details. || | || | || | || | In order to allow variant information from multiple datasets to be combined, || | || | _variant.diffrn_id and/or _variant.entry_id may be used. || | |+------------------------------------------------------------------------------------------+| +-------------------------------------------------------------------------------------------------------------+ ; _dictionary.title cif_img.dic _dictionary.version 1.6.4 _dictionary.datablock_id cif_img.dic ######################### ## CATEGORY_GROUP_LIST ## ######################### loop_ _category_group_list.id _category_group_list.parent_id _category_group_list.description 'inclusive_group' . ; Categories that belong to the dictionary extension. ; 'array_data_group' 'inclusive_group' ; Categories that describe array data. ; 'axis_group' 'inclusive_group' ; Categories that describe axes. ; 'diffrn_group' 'inclusive_group' ; Categories that describe details of the diffraction experiment. ; 'map_group' 'inclusive_group' ; Categories that describe details of map data. ; 'variant_group' 'inclusive_group' ; Categories that describe details of map data. ; ################## ## SUB_CATEGORY ## ################## loop_ _sub_category.id _sub_category.description 'matrix' ; The collection of elements of a matrix. ; 'vector' ; The collection of elements of a vector. ; ############## # ARRAY_DATA # ############## save_ARRAY_DATA _category.description ; Data items in the ARRAY_DATA category are the containers for the array data items described in the category ARRAY_STRUCTURE. It is recognized that the data in this category needs to be used in two distinct ways. During a data collection the lack of ancillary data and timing constraints in processing data may dictate the need to make a 'miniCBF' nothing more than an essential minimum of information to record the results of the data collection. In that case it is proper to use the ARRAY_DATA category as a container for just a single image and a compacted, beam-line dependent list of data collection parameter values. In such a case, only the tags '_array_data.header_convention', '_array_data.header_contents' and '_array_data.data' need be populated. For full processing and archiving, most of the tags in this dictionary will need to be populated. ; _category.id array_data _category.mandatory_code no loop_ _category_key.name '_array_data.array_id' '_array_data.binary_id' '_array_data.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows two binary data blocks. The first one was compressed by the CBF_CANONICAL compression algorithm and is presented as hexadecimal data. The first character 'H' on the data lines means hexadecimal. It could have been 'O' for octal or 'D' for decimal. The second character on the line shows the number of bytes in each word (in this case '4'), which then requires eight hexadecimal digits per word. The third character gives the order of octets within a word, in this case '<' for the ordering 4321 (i.e. 'big-endian'). Alternatively, the character '>' could have been used for the ordering 1234 (i.e. 'little-endian'). The block has a 'message digest' to check the integrity of the data. The second block is similar, but uses CBF_PACKED compression and BASE64 encoding. Note that the size and the digest are different. ; ; loop_ _array_data.array_id _array_data.binary_id _array_data.data image_1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF_CANONICAL" Content-Transfer-Encoding: X-BASE16 X-Binary-Size: 3927126 X-Binary-ID: 1 Content-MD5: u2sTJEovAHkmkDjPi+gWsg== # Hexadecimal encoding, byte 0, byte order ...21 # H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ... .... --CIF-BINARY-FORMAT-SECTION---- ; image_2 2 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF-PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3745758 X-Binary-ID: 2 Content-MD5: 1zsJjWPfol2GYl2V+QSXrw== ELhQAAAAAAAA... ... --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - This example shows a single image in a miniCBF, provided by E. Eikenberry. The entire CBF consists of one data block containing one category and three tags. The CBFlib program convert_miniCBF and a suitable template file can be used to convert this miniCBF to a full imgCIF file. ; ; ###CBF: VERSION 1.5 # CBF file written by CBFlib v0.7.8 data_insulin_pilatus6m _array_data.header_convention SLS_1.0 _array_data.header_contents ; # Detector: PILATUS 6M SN: 60-0001 # 2007/Jun/17 15:12:36.928 # Pixel_size 172e-6 m x 172e-6 m # Silicon sensor, thickness 0.000320 m # Exposure_time 0.995000 s # Exposure_period 1.000000 s # Tau = 194.0e-09 s # Count_cutoff 1048575 counts # Threshold_setting 5000 eV # Wavelength 1.2398 A # Energy_range (0, 0) eV # Detector_distance 0.15500 m # Detector_Voffset -0.01003 m # Beam_xy (1231.00, 1277.00) pixels # Flux 22487563295 ph/s # Filter_transmission 0.0008 # Start_angle 13.0000 deg. # Angle_increment 1.0000 deg. # Detector_2theta 0.0000 deg. # Polarization 0.990 # Alpha 0.0000 deg. # Kappa 0.0000 deg. # Phi 0.0000 deg. # Chi 0.0000 deg. # Oscillation_axis X, CW # N_oscillations 1 ; _array_data.data ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_BYTE_OFFSET" Content-Transfer-Encoding: BINARY X-Binary-Size: 6247567 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" X-Binary-Element-Byte-Order: LITTLE_ENDIAN Content-MD5: 8wO6i2+899lf5iO8QPdgrw== X-Binary-Number-of-Elements: 6224001 X-Binary-Size-Fastest-Dimension: 2463 X-Binary-Size-Second-Dimension: 2527 X-Binary-Size-Padding: 4095 ... --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_data.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. If not given, it defaults to 1. ; _item.name '_array_data.array_id' _item.category_id array_data _item.mandatory_code implicit _item_default.value 1 _item_type.code code save_ save__array_data.binary_id _item_description.description ; This item is an integer identifier which, along with _array_data.array_id, should uniquely identify the particular block of array data. If _array_data.binary_id is not explicitly given, it defaults to 1. The value of _array_data.binary_id distinguishes among multiple sets of data with the same array structure. If the MIME header of the data array specifies a value for X-Binary-ID, the value of _array_data.binary_id should be equal to the value given for X-Binary-ID. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_data.binary_id' array_data implicit '_diffrn_data_frame.binary_id' diffrn_data_frame implicit '_array_intensities.binary_id' array_intensities implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.binary_id' '_array_data.binary_id' '_array_intensities.binary_id' '_array_data.binary_id' _item_default.value 1 _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_data.data _item_description.description ; The value of _array_data.data contains the array data encapsulated in a STAR string. The representation used is a variant on the Multipurpose Internet Mail Extensions (MIME) specified in RFC 2045-2049 by N. Freed et al. The boundary delimiter used in writing an imgCIF or CBF is '\n--CIF-BINARY-FORMAT-SECTION--' (including the required initial '\n--'). The Content-Type may be any of the discrete types permitted in RFC 2045; 'application/octet-stream' is recommended for diffraction images in the ARRAY_DATA category. Note: When appropriate in other categories, e.g. for photographs of crystals, more precise types, such as 'image/jpeg', 'image/tiff', 'image/png', etc. should be used. If an octet stream was compressed, the compression should be specified by the parameter 'conversions="X-CBF_PACKED"' or the parameter 'conversions="X-CBF_CANONICAL"' or the parameter 'conversions="X-CBF_BYTE_OFFSET"' or the parameter 'conversions="X-CBF_BACKGROUND_OFFSET_DELTA"' If the parameter 'conversions="X-CBF_PACKED"' is given it may be further modified with the parameters '"uncorrelated_sections"' or '"flat"' If the '"uncorrelated_sections"' parameter is given, each section will be compressed without using the prior section for averaging. If the '"flat"' parameter is given, each the image will be treated as one long row. Note that the X-CBF_CANONICAL and X-CBF_PACKED are slower but more efficient compressions that the others. The X-CBF_BYTE_OFFSET compression is a good compromise between speed and efficiency for ordinary diffraction images. The X-CBF_BACKGROUND_OFFSET_DELTA compression is oriented towards sparse data, such as masks and tables of replacement pixel values for images with overloaded spots. The Content-Transfer-Encoding may be 'BASE64', 'Quoted-Printable', 'X-BASE8', 'X-BASE10', 'X-BASE16' or 'X-BASE32K', for an imgCIF or 'BINARY' for a CBF. The octal, decimal and hexadecimal transfer encodings are provided for convenience in debugging and are not recommended for archiving and data interchange. In a CIF, one of the parameters 'charset=us-ascii', 'charset=utf-8' or 'charset=utf-16' may be used on the Content-Transfer-Encoding to specify the character set used for the external presentation of the encoded data. If no charset parameter is given, the character set of the enclosing CIF is assumed. In any case, if a BOM flag is detected (FE FF for big-endian UTF-16, FF FE for little-endian UTF-16 or EF BB BF for UTF-8) is detected, the indicated charset will be assumed until the end of the encoded data or the detection of a different BOM. The charset of the Content-Transfer-Encoding is not the character set of the encoded data, only the character set of the presentation of the encoded data and should be respecified for each distinct STAR string. In an imgCIF file, the encoded binary data begins after the empty line terminating the header. In an imgCIF file, the encoded binary data ends with the terminating boundary delimiter '\n--CIF-BINARY-FORMAT-SECTION----' in the currently effective charset or with the '\n; ' that terminates the STAR string. In a CBF, the raw binary data begins after an empty line terminating the header and after the sequence: Octet Hex Decimal Purpose 0 0C 12 (ctrl-L) Page break 1 1A 26 (ctrl-Z) Stop listings in MS-DOS 2 04 04 (Ctrl-D) Stop listings in UNIX 3 D5 213 Binary section begins None of these octets are included in the calculation of the message size or in the calculation of the message digest. The X-Binary-Size header specifies the size of the equivalent binary data in octets. If compression was used, this size is the size after compression, including any book-keeping fields. An adjustment is made for the deprecated binary formats in which eight bytes of binary header are used for the compression type. In this case, the eight bytes used for the compression type are subtracted from the size, so that the same size will be reported if the compression type is supplied in the MIME header. Use of the MIME header is the recommended way to supply the compression type. In general, no portion of the binary header is included in the calculation of the size. The X-Binary-Element-Type header specifies the type of binary data in the octets, using the same descriptive phrases as in _array_structure.encoding_type. The default value is 'unsigned 32-bit integer'. An MD5 message digest may, optionally, be used. The 'RSA Data Security, Inc. MD5 Message-Digest Algorithm' should be used. No portion of the header is included in the calculation of the message digest. If the Transfer Encoding is 'X-BASE8', 'X-BASE10' or 'X-BASE16', the data are presented as octal, decimal or hexadecimal data organized into lines or words. Each word is created by composing octets of data in fixed groups of 2, 3, 4, 6 or 8 octets, either in the order ...4321 ('big- endian') or 1234... ('little-endian'). If there are fewer than the specified number of octets to fill the last word, then the missing octets are presented as '==' for each missing octet. Exactly two equal signs are used for each missing octet even for octal and decimal encoding. The format of lines is: rnd xxxxxx xxxxxx xxxxxx where r is 'H', 'O' or 'D' for hexadecimal, octal or decimal, n is the number of octets per word and d is '<' or '>' for the '...4321' and '1234...' octet orderings, respectively. The '==' padding for the last word should be on the appropriate side to correspond to the missing octets, e.g. H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000 or H3> FF0700 00==== For these hexadecimal, octal and decimal formats only, comments beginning with '#' are permitted to improve readability. BASE64 encoding follows MIME conventions. Octets are in groups of three: c1, c2, c3. The resulting 24 bits are broken into four six-bit quantities, starting with the high-order six bits (c1 >> 2) of the first octet, then the low-order two bits of the first octet followed by the high-order four bits of the second octet [(c1 & 3)<<4 | (c2>>4)], then the bottom four bits of the second octet followed by the high-order two bits of the last octet [(c2 & 15)<<2 | (c3>>6)], then the bottom six bits of the last octet (c3 & 63). Each of these four quantities is translated into an ASCII character using the mapping: 1 2 3 4 5 6 0123456789012345678901234567890123456789012345678901234567890123 | | | | | | | ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/ With short groups of octets padded on the right with one '=' if c3 is missing, and with '==' if both c2 and c3 are missing. X-BASE32K encoding is similar to BASE64 encoding, except that sets of 15 octets are encoded as sets of 8 16-bit unicode characters, by breaking the 120 bits into 8 15-bit quantities. 256 is added to each 15 bit quantity to bring it into a printable uncode range. When encoding, zero padding is used to fill out the last 15 bit quantity. If 8 or more bits of padding are used, a single equals sign (hexadecimal 003D) is appended. Embedded whitespace and newlines are introduced to produce lines of no more than 80 characters each. On decoding, all printable ascii characters and ascii whitespace characters are ignored except for any trailing equals signs. The number of trailing equals signs indicated the number of trailing octets to be trimmed from the end of the decoded data. (see Georgi Darakev, Vassil Litchev, Kostadin Z. Mitev, Herbert J. Bernstein, 'Efficient Support of Binary Data in the XML Implementation of the NeXus File Format',absract W0165, ACA Summer Meeting, Honolulu, HI, July 2006). QUOTED-PRINTABLE encoding also follows MIME conventions, copying octets without translation if their ASCII values are 32...38, 42, 48...57, 59, 60, 62, 64...126 and the octet is not a ';' in column 1. All other characters are translated to =nn, where nn is the hexadecimal encoding of the octet. All lines are 'wrapped' with a terminating '=' (i.e. the MIME conventions for an implicit line terminator are never used). The "X-Binary-Element-Byte-Order" can specify either '"BIG_ENDIAN"' or '"LITTLE_ENDIAN"' byte order of the imaage data. Only LITTLE_ENDIAN is recommended. Processors may treat BIG_ENDIAN as a warning of data that can only be processed by special software. The "X-Binary-Number-of-Elements" specifies the number of elements (not the number of octets) in the decompressed, decoded image. The optional "X-Binary-Size-Fastest-Dimension" specifies the number of elements (not the number of octets) in one row of the fastest changing dimension of the binary data array. This information must be in the MIME header for proper operation of some of the decompression algorithms. The optional "X-Binary-Size-Second-Dimension" specifies the number of elements (not the number of octets) in one column of the second-fastest changing dimension of the binary data array. This information must be in the MIME header for proper operation of some of the decompression algorithms. The optional "X-Binary-Size-Third-Dimension" specifies the number of sections for the third-fastest changing dimension of the binary data array. The optional "X-Binary-Size-Padding" specifies the size in octets of an optional padding after the binary array data and before the closing flags for a binary section. ; _item.name '_array_data.data' _item.category_id array_data _item.mandatory_code yes _item_type.code binary save_ save__array_data.header_contents _item_description.description ; This item is an text field for use in minimal CBF files to carry essential header information to be kept with image data in _array_data.data when the tags that normally carry the structured metadata for the image have not been populated. Normally this data item should not appear when the full set of tags have been populated and _diffrn_data_frame.details appears. ; _item.name '_array_data.header_contents' _item.category_id array_data _item.mandatory_code no _item_type.code text save_ save__array_data.header_convention _item_description.description ; This item is an identifier for the convention followed in constructing the contents of _array_data.header_contents The permitted values are of the of an image creator identifier followed by an underscore and a version string. To avoid confusion about conventions, all creator identifiers should be registered with the IUCr and the conventions for all identifiers and versions should be posted on the MEDSBIO.org web site. ; _item.name '_array_data.header_convention' _item.category_id array_data _item.mandatory_code no _item_type.code code save_ save__array_data.variant _item_description.description ; The value of _array_data.variant gives the variant to which the given array_data row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_array_data.variant' _item.category_id array_data _item.mandatory_code no _item_type.code code save_ ###################### # ARRAY_ELEMENT_SIZE # ###################### save_ARRAY_ELEMENT_SIZE _category.description ; Data items in the ARRAY_ELEMENT_SIZE category record the physical size of array elements along each array dimension. ; _category.id array_element_size _category.mandatory_code no loop_ _category_key.name '_array_element_size.array_id' '_array_element_size.index' '_array_element_size.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A regular 2D array with a uniform element dimension of 1220 nanometres. ; ; loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size image_1 1 1.22e-6 image_1 2 1.22e-6 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_element_size.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_element_size.array_id' _item.category_id array_element_size _item.mandatory_code implicit _item_type.code code save_ save__array_element_size.index _item_description.description ; This item is a pointer to _array_structure_list.index in the ARRAY_STRUCTURE_LIST category. ; _item.name '_array_element_size.index' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.size _item_description.description ; The size in metres of an image element in this dimension. This supposes that the elements are arranged on a regular grid. ; _item.name '_array_element_size.size' _item.category_id array_element_size _item.mandatory_code yes _item_type.code float _item_units.code 'metres' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__array_element_size.variant _item_description.description ; The value of _array_element_size.variant gives the variant to which the given array_element_size row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_array_element_size.variant' _item.category_id array_element_size _item.mandatory_code no _item_type.code code save_ ##################### # ARRAY_INTENSITIES # ##################### save_ARRAY_INTENSITIES _category.description ; Data items in the ARRAY_INTENSITIES category record the information required to recover the intensity data from the set of data values stored in the ARRAY_DATA category. The detector may have a complex relationship between the raw intensity values and the number of incident photons. In most cases, the number stored in the final array will have a simple linear relationship to the actual number of incident photons, given by _array_intensities.gain. If raw, uncorrected values are presented (e.g. for calibration experiments), the value of _array_intensities.linearity will be 'raw' and _array_intensities.gain will not be used. ; _category.id array_intensities _category.mandatory_code no loop_ _category_key.name '_array_intensities.array_id' '_array_intensities.binary_id' '_array_intensities.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 ; ; loop_ _array_intensities.array_id _array_intensities.linearity _array_intensities.gain _array_intensities.overload _array_intensities.undefined_value _array_intensities.pixel_fast_bin_size _array_intensities.pixel_slow_bin_size _array_intensities.pixel_binning_method image_1 linear 1.2 655535 0 2 2 hardware ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_intensities.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_intensities.array_id' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code code save_ save__array_intensities.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_array_intensities.binary_id' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code int save_ save__array_intensities.gain _item_description.description ; Detector 'gain'. The factor by which linearized intensity count values should be divided to produce true photon counts. ; _item.name '_array_intensities.gain' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain_esd' 'associated_value' save_ save__array_intensities.gain_esd _item_description.description ; The estimated standard deviation in detector 'gain'. ; _item.name '_array_intensities.gain_esd' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain' 'associated_esd' save_ save__array_intensities.linearity _item_description.description ; The intensity linearity scaling method used to convert from the raw intensity to the stored element value: 'linear' is linear. 'offset' means that the value defined by _array_intensities.offset should be added to each element value. 'scaling' means that the value defined by _array_intensities.scaling should be multiplied with each element value. 'scaling_offset' is the combination of the two previous cases, with the scale factor applied before the offset value. 'sqrt_scaled' means that the square root of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and squaring the result. 'logarithmic_scaled' means that the logarithm base 10 of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and calculating 10 to the power of this number. 'raw' means that the data are a set of raw values straight from the detector. ; _item.name '_array_intensities.linearity' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'linear' . 'offset' ; The value defined by _array_intensities.offset should be added to each element value. ; 'scaling' ; The value defined by _array_intensities.scaling should be multiplied with each element value. ; 'scaling_offset' ; The combination of the scaling and offset with the scale factor applied before the offset value. ; 'sqrt_scaled' ; The square root of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and squaring the result. ; 'logarithmic_scaled' ; The logarithm base 10 of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and calculating 10 to the power of this number. ; 'raw' ; The array consists of raw values to which no corrections have been applied. While the handling of the data is similar to that given for 'linear' data with no offset, the meaning of the data differs in that the number of incident photons is not necessarily linearly related to the number of counts reported. This value is intended for use either in calibration experiments or to allow for handling more complex data-fitting algorithms than are allowed for by this data item. ; save_ save__array_intensities.offset _item_description.description ; Offset value to add to array element values in the manner described by the item _array_intensities.linearity. ; _item.name '_array_intensities.offset' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.overload _item_description.description ; The saturation intensity level for this data array. ; _item.name '_array_intensities.overload' _item.category_id array_intensities _item.mandatory_code no _item_type.code float _item_units.code 'counts' save_ save__array_intensities.pixel_fast_bin_size _item_description.description ; The value of _array_intensities.pixel_fast_bin_size specifies the number of pixels that compose one element in the direction of the most rapidly varying array dimension. Typical values are 1, 2, 4 or 8. When there is 1 pixel per array element in both directions, the value given for _array_intensities.pixel_binning_method normally should be 'none'. It is specified as a float to allow for binning algorithms that create array elements that are not integer multiples of the detector pixel size. ; _item.name '_array_intensities.pixel_fast_bin_size' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code float _item_default.value 1. loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'pixels_per_element' save_ save__array_intensities.pixel_slow_bin_size _item_description.description ; The value of _array_intensities.pixel_slow_bin_size specifies the number of pixels that compose one element in the direction of the second most rapidly varying array dimension. Typical values are 1, 2, 4 or 8. When there is 1 pixel per array element in both directions, the value given for _array_intensities.pixel_binning_method normally should be 'none'. It is specified as a float to allow for binning algorithms that create array elements that are not integer multiples of the detector pixel size. ; _item.name '_array_intensities.pixel_slow_bin_size' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code float _item_default.value 1. loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'pixels_per_element' save_ save__array_intensities.pixel_binning_method _item_description.description ; The value of _array_intensities.pixel_binning_method specifies the method used to derive array elements from multiple pixels. ; _item.name '_array_intensities.pixel_binning_method' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'hardware' ; The element intensities were derived from the raw data of one or more pixels by used of hardware in the detector, e.g. by use of shift registers in a CCD to combine pixels into super-pixels. ; 'software' ; The element intensities were derived from the raw data of more than one pixel by use of software. ; 'combined' ; The element intensities were derived from the raw data of more than one pixel by use of both hardware and software, as when hardware binning is used in one direction and software in the other. ; 'none' ; In the both directions, the data has not been binned. The number of pixels is equal to the number of elements. When the value of _array_intensities.pixel_binning_method is 'none' the values of _array_intensities.pixel_fast_bin_size and _array_intensities.pixel_slow_bin_size both must be 1. ; 'unspecified' ; The method used to derive element intensities is not specified. ; _item_default.value 'unspecified' save_ save__array_intensities.scaling _item_description.description ; Multiplicative scaling value to be applied to array data in the manner described by item _array_intensities.linearity. ; _item.name '_array_intensities.scaling' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.undefined_value _item_description.description ; A value to be substituted for undefined values in the data array. ; _item.name '_array_intensities.undefined_value' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.variant _item_description.description ; The value of _array_intensities.variant gives the variant to which the given array_intensities row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_array_intensities.variant' _item.category_id array_intensities _item.mandatory_code no _item_type.code code save_ ################### # ARRAY_STRUCTURE # ################### save_ARRAY_STRUCTURE _category.description ; Data items in the ARRAY_STRUCTURE category record the organization and encoding of array data that may be stored in the ARRAY_DATA category. ; _category.id array_structure _category.mandatory_code no loop_ _category_key.name '_array_structure.id' '_array_structure.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order image_1 "unsigned 16-bit integer" none little_endian ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure.byte_order _item_description.description ; The order of bytes for integer values which require more than 1 byte. (IBM-PC's and compatibles and DEC VAXs use low-byte-first ordered integers, whereas Hewlett Packard 700 series, Sun-4 and Silicon Graphics use high-byte-first ordered integers. DEC Alphas can produce/use either depending on a compiler switch.) ; _item.name '_array_structure.byte_order' _item.category_id array_structure _item.mandatory_code yes _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail 'big_endian' ; The first byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; 'little_endian' ; The last byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; save_ save__array_structure.compression_type _item_description.description ; Type of data-compression method used to compress the array data. ; _item.name '_array_structure.compression_type' _item.category_id array_structure _item.mandatory_code no _item_type.code ucode _item_default.value 'none' loop_ _item_enumeration.value _item_enumeration.detail 'byte_offset' ; Using the 'byte_offset' compression scheme as per A. Hammersley and the CBFlib manual, section 3.3.3 ; 'canonical' ; Using the 'canonical' compression scheme (International Tables for Crystallography Volume G, Section 5.6.3.1) and CBFlib manual section 3.3.1 ; 'none' ; Data are stored in normal format as defined by _array_structure.encoding_type and _array_structure.byte_order. ; 'packed' ; Using the 'packed' compression scheme, a CCP4-style packing as per J. P. Abrahams pack_c.c and CBFlib manual, section 3.3.2. ; 'packed_v2' ; Using the 'packed' compression scheme, version 2, as per J. P. Abrahams pack_c.c and CBFlib manual, section 3.3.2. ; save_ save__array_structure.compression_type_flag _item_description.description ; Flags modifying the type of data-compression method used to compress the arraydata. ; _item.name '_array_structure.compression_type_flag' _item.category_id array_structure _item.mandatory_code no _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail 'uncorrelated_sections' ; When applying packed or packed_v2 compression on an array with uncorrelated sections, do not average in points from the prior section. ; 'flat' ; When applying packed or packed_v2 compression on an array with treat the entire image as a single line set the maximum number of bits for an offset to 65 bits. The flag is included for compatibility with software prior to CBFlib_0.7.7, and should not be used for new data sets. ; save_ save__array_structure.encoding_type _item_description.description ; Data encoding of a single element of array data. The type 'unsigned 1-bit integer' is used for packed Booleans arrays for masks. Each element of the array corresponds to a single bit packed in unsigned 8-bit data. In several cases, the IEEE format is referenced. See IEEE Standard 754-1985 (IEEE, 1985). Ref: IEEE (1985). IEEE Standard for Binary Floating-Point Arithmetic. ANSI/IEEE Std 754-1985. New York: Institute of Electrical and Electronics Engineers. ; _item.name '_array_structure.encoding_type' _item.category_id array_structure _item.mandatory_code yes _item_type.code uline loop_ _item_enumeration.value 'unsigned 1-bit integer' 'unsigned 8-bit integer' 'signed 8-bit integer' 'unsigned 16-bit integer' 'signed 16-bit integer' 'unsigned 32-bit integer' 'signed 32-bit integer' 'signed 32-bit real IEEE' 'signed 64-bit real IEEE' 'signed 32-bit complex IEEE' save_ save__array_structure.id _item_description.description ; The value of _array_structure.id must uniquely identify each item of array data. This item has been made implicit and given a default value of 1 as a convenience in writing miniCBF files. Normally an explicit name with useful content should be used. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure.id' array_structure implicit '_array_data.array_id' array_data implicit '_array_structure_list.array_id' array_structure_list implicit '_array_intensities.array_id' array_intensities implicit '_diffrn_data_frame.array_id' diffrn_data_frame implicit _item_default.value 1 _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_data.array_id' '_array_structure.id' '_array_structure_list.array_id' '_array_structure.id' '_array_intensities.array_id' '_array_structure.id' '_diffrn_data_frame.array_id' '_array_structure.id' save_ save__array_structure.variant _item_description.description ; The value of _array_structure.variant gives the variant to which the given array_structure row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_array_structure.variant' _item.category_id array_structure _item.mandatory_code no _item_type.code code save_ ######################## # ARRAY_STRUCTURE_LIST # ######################## save_ARRAY_STRUCTURE_LIST _category.description ; Data items in the ARRAY_STRUCTURE_LIST category record the size and organization of each array dimension. The relationship to physical axes may be given. ; _category.id array_structure_list _category.mandatory_code no loop_ _category_key.name '_array_structure_list.array_id' '_array_structure_list.index' '_array_structure_list.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - An image array of 1300 x 1200 elements. The raster order of the image is left to right (increasing) in the first dimension and bottom to top (decreasing) in the second dimension. ; ; loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id image_1 1 1300 1 increasing ELEMENT_X image_1 2 1200 2 decreasing ELEMENY_Y ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure_list.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_structure_list.array_id' _item.category_id array_structure_list _item.mandatory_code implicit _item_type.code code save_ save__array_structure_list.axis_set_id _item_description.description ; This is a descriptor for the physical axis or set of axes corresponding to an array index. This data item is related to the axes of the detector itself given in DIFFRN_DETECTOR_AXIS, but usually differs in that the axes in this category are the axes of the coordinate system of reported data points, while the axes in DIFFRN_DETECTOR_AXIS are the physical axes of the detector describing the 'poise' of the detector as an overall physical object. If there is only one axis in the set, the identifier of that axis should be used as the identifier of the set. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.axis_set_id' array_structure_list yes '_array_structure_list_axis.axis_set_id' array_structure_list_axis implicit _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_structure_list_axis.axis_set_id' '_array_structure_list.axis_set_id' save_ save__array_structure_list.dimension _item_description.description ; The number of elements stored in the array structure in this dimension. ; _item.name '_array_structure_list.dimension' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.direction _item_description.description ; Identifies the direction in which this array index changes. ; _item.name '_array_structure_list.direction' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'increasing' ; Indicates the index changes from 1 to the maximum dimension. ; 'decreasing' ; Indicates the index changes from the maximum dimension to 1. ; save_ save__array_structure_list.index _item_description.description ; Identifies the one-based index of the row or column in the array structure. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.index' array_structure_list yes '_array_structure_list.precedence' array_structure_list yes '_array_element_size.index' array_element_size yes _item_type.code int loop_ _item_linked.child_name _item_linked.parent_name '_array_element_size.index' '_array_structure_list.index' loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.precedence _item_description.description ; Identifies the rank order in which this array index changes with respect to other array indices. The precedence of 1 indicates the index which changes fastest. ; _item.name '_array_structure_list.precedence' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.variant _item_description.description ; The value of _array_structure_list.variant gives the variant to which the given array_structure_list row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_array_structure_list.variant' _item.category_id array_structure_list _item.mandatory_code no _item_type.code code save_ ############################# # ARRAY_STRUCTURE_LIST_AXIS # ############################# save_ARRAY_STRUCTURE_LIST_AXIS _category.description ; Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe the physical settings of sets of axes for the centres of pixels that correspond to data points described in the ARRAY_STRUCTURE_LIST category. In the simplest cases, the physical increments of a single axis correspond to the increments of a single array index. More complex organizations, e.g. spiral scans, may require coupled motions along multiple axes. Note that a spiral scan uses two coupled axes: one for the angular direction and one for the radial direction. This differs from a cylindrical scan for which the two axes are not coupled into one set. ; _category.id array_structure_list_axis _category.mandatory_code no loop_ _category_key.name '_array_structure_list_axis.axis_set_id' '_array_structure_list_axis.axis_id' '_array_structure_list_axis.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' save_ save__array_structure_list_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes in the set of axes for which settings are being specified. Multiple axes may be specified for the same value of _array_structure_list_axis.axis_set_id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_array_structure_list_axis.axis_id' _item.category_id array_structure_list_axis _item.mandatory_code yes _item_type.code code save_ save__array_structure_list_axis.axis_set_id _item_description.description ; The value of this data item is the identifier of the set of axes for which axis settings are being specified. Multiple axes may be specified for the same value of _array_structure_list_axis.axis_set_id. This item is a pointer to _array_structure_list.axis_set_id in the ARRAY_STRUCTURE_LIST category. If this item is not specified, it defaults to the corresponding axis identifier. ; _item.name '_array_structure_list_axis.axis_set_id' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_type.code code save_ save__array_structure_list_axis.angle _item_description.description ; The setting of the specified axis in degrees for the first data point of the array index with the corresponding value of _array_structure_list.axis_set_id. If the index is specified as 'increasing', this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing', this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.angle' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.angle_increment _item_description.description ; The pixel-centre-to-pixel-centre increment in the angular setting of the specified axis in degrees. This is not meaningful in the case of 'constant velocity' spiral scans and should not be specified for this case. See _array_structure_list_axis.angular_pitch. ; _item.name '_array_structure_list_axis.angle_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for the first data point of the array index with the corresponding value of _array_structure_list.axis_set_id. If the index is specified as 'increasing', this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing', this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.displacement' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.fract_displacement _item_description.description ; The setting of the specified axis as a decimal fraction of the axis unit vector for the first data point of the array index with the corresponding value of _array_structure_list.axis_set_id. If the index is specified as 'increasing', this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing', this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.fract_displacement' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float save_ save__array_structure_list_axis.displacement_increment _item_description.description ; The pixel-centre-to-pixel-centre increment for the displacement setting of the specified axis in millimetres. ; _item.name '_array_structure_list_axis.displacement_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.fract_displacement_increment _item_description.description ; The pixel-centre-to-pixel-centre increment for the displacement setting of the specified axis as a decimal fraction of the axis unit vector. ; _item.name '_array_structure_list_axis.fract_displacement_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.angular_pitch _item_description.description ; The pixel-centre-to-pixel-centre distance for a one-step change in the setting of the specified axis in millimetres. This is meaningful only for 'constant velocity' spiral scans or for uncoupled angular scans at a constant radius (cylindrical scans) and should not be specified for cases in which the angle between pixels (rather than the distance between pixels) is uniform. See _array_structure_list_axis.angle_increment. ; _item.name '_array_structure_list_axis.angular_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.radial_pitch _item_description.description ; The radial distance from one 'cylinder' of pixels to the next in millimetres. If the scan is a 'constant velocity' scan with differing angular displacements between pixels, the value of this item may differ significantly from the value of _array_structure_list_axis.displacement_increment. ; _item.name '_array_structure_list_axis.radial_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.reference_angle _item_description.description ; The value of _array_structure_list_axis.reference_angle specifies the setting of the angle of this axis used for determining a reference beam center and a reference detector distance. It is normally expected to be identical to the value of _array_structure_list.angle. ; _item.name '_array_structure_list_axis.reference_angle' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.reference_displacement _item_description.description ; The value of _array_structure_list_axis.reference_displacement specifies the setting of the displacement of this axis used for determining a reference beam center and a reference detector distance. It is normally expected to be identical to the value of _array_structure_list.displacement. ; _item.name '_array_structure_list_axis.reference_displacement' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.variant _item_description.description ; The value of _array_structure_list_axis.variant gives the variant to which the given array_structure_list_axis row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_array_structure_list_axis.variant' _item.category_id array_structure_list_axis _item.mandatory_code no _item_type.code code save_ ######## # AXIS # ######## save_AXIS _category.description ; Data items in the AXIS category record the information required to describe the various goniometer, detector, source and other axes needed to specify a data collection or the axes defining the coordinate system of an image. The location of each axis is specified by two vectors: the axis itself, given by a unit vector in the direction of the axis, and an offset to the base of the unit vector. The vectors defining an axis are referenced to an appropriate coordinate system. The axis vector, itself, is a dimensionless unit vector. Where meaningful, the offset vector is given in millimetres. In coordinate systems not measured in metres, the offset is not specified and is taken as zero. The available coordinate systems are: The imgCIF standard laboratory coordinate system The direct lattice (fractional atomic coordinates) The orthogonal Cartesian coordinate system (real space) The reciprocal lattice An abstract orthogonal Cartesian coordinate frame For consistency in this discussion, we call the three coordinate system axes X, Y and Z. This is appropriate for the imgCIF standard laboratory coordinate system, and last two Cartesian coordinate systems, but for the direct lattice, X corresponds to a, Y to b and Z to c, while for the reciprocal lattice, X corresponds to a*, Y to b* and Z to c*. For purposes of visualization, all the coordinate systems are taken as right-handed, i.e., using the convention that the extended thumb of a right hand could point along the first (X) axis, the straightened pointer finger could point along the second (Y) axis and the middle finger folded inward could point along the third (Z) axis. THE IMGCIF STANDARD LABORATORY COORDINATE SYSTEM The imgCIF standard laboratory coordinate system is a right-handed orthogonal coordinate similar to the MOSFLM coordinate system, but imgCIF puts Z along the X-ray beam, rather than putting X along the X-ray beam as in MOSFLM. The vectors for the imgCIF standard laboratory coordinate system form a right-handed Cartesian coordinate system with its origin in the sample or specimen. The origin of the axis system should, if possible, be defined in terms of mechanically stable axes to be be both in the sample and in the beam. If the sample goniometer or other sample positioner has two axes the intersection of which defines a unique point at which the sample should be mounted to be bathed by the beam, that will be the origin of the axis system. If no such point is defined, then the midpoint of the line of intersection between the sample and the center of the beam will define the origin. For this definition the sample positioning system will be set at its initial reference position for the experiment. | Y (to complete right-handed system) | | | | | |________________X / principal goniometer axis / / / / /Z (to source) Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from the sample or specimen along the principal axis of the goniometer or sample positioning system if the sample positioning system has an axis that intersects the origin and which form an angle of more than 22.5 degrees with the beam axis. Axis 2 (Y): The Y-axis completes an orthogonal right-handed system defined by the X-axis and the Z-axis (see below). Axis 3 (Z): The Z-axis is derived from the source axis which goes from the sample to the source. The Z-axis is the component of the source axis in the direction of the source orthogonal to the X-axis in the plane defined by the X-axis and the source axis. If the conditions for the X-axis can be met, the coordinate system will be based on the goniometer or other sample positioning system and the beam and not on the orientation of the detector, gravity etc. The vectors necessary to specify all other axes are given by sets of three components in the order (X, Y, Z). If the axis involved is a rotation axis, it is right-handed, i.e. as one views the object to be rotated from the origin (the tail) of the unit vector, the rotation is clockwise. If a translation axis is specified, the direction of the unit vector specifies the sense of positive translation. Note: This choice of coordinate system is similar to but significantly different from the choice in MOSFLM (Leslie & Powell, 2004). In MOSFLM, X is along the X-ray beam (the CBF/imgCIF Z axis) and Z is along the rotation axis. In some experimental techniques, there is no goniometer or the principal axis of the goniometer is at a small acute angle with respect to the source axis. In such cases, other reference axes are needed to define a useful coordinate system. The order of priority in defining directions in such cases is to use the detector, then gravity, then north. If the X-axis cannot be defined as above, then the direction (not the origin) of the X-axis should be parallel to the axis of the primary detector element corresponding to the most rapidly varying dimension of that detector element's data array, with its positive sense corresponding to increasing values of the index for that dimension. If the detector is such that such a direction cannot be defined (as with a point detector) or that direction forms an angle of less than 22.5 degrees with respect to the source axis, then the X-axis should be chosen so that if the Y-axis is chosen in the direction of gravity, and the Z-axis is chosen to be along the source axis, a right-handed orthogonal coordinate system is chosen. In the case of a vertical source axis, as a last resort, the X-axis should be chosen to point North. All rotations are given in degrees and all translations are given in mm. Axes may be dependent on one another. The X-axis is the only goniometer axis the direction of which is strictly connected to the hardware. All other axes are specified by the positions they would assume when the axes upon which they depend are at their zero points. When specifying detector axes, the axis is given to the beam centre. The location of the beam centre on the detector should be given in the DIFFRN_DETECTOR category in distortion-corrected millimetres from the (0,0) corner of the detector. It should be noted that many different origins arise in the definition of an experiment. In particular, as noted above, it is necessary to specify the location of the beam centre on the detector in terms of the origin of the detector, which is, of course, not coincident with the centre of the sample. The unit cell, reciprocal cell and crystallographic orthogonal Cartesian coordinate system are defined by the CELL and the matrices in the ATOM_SITES category. THE DIRECT LATTICE (FRACTIONAL COORDINATES) The direct lattice coordinate system is a system of fractional coordinates aligned to the crystal, rather than to the laboratory. This is a natural coordinate system for maps and atomic coordinates. It is the simplest coordinate system in which to apply symmetry. The axes are determined by the cell edges, and are not necessarily othogonal. This coordinate system is not uniquely defined and depends on the cell parameters in the CELL category and the settings chosen to index the crystal. Molecules in a crystal studied by X-ray diffracraction are organized into a repeating regular array of unit cells. Each unit cell is defined by three vectors, a, b and c. To quote from Drenth, "The choice of the unit cell is not unique and therefore, guidelines have been established for selecting the standard basis vectors and the origin. They are based on symmetry and metric considerations: "(1) The axial system should be right handed. (2) The basis vectors should coincide as much as possible with directions of highest symmetry." (3) The cell taken should be the smallest one that satisfies condition (2) (4) Of all the lattice vectors, none is shorter than a. (5) Of those not directed along a, none is shorter than b. (6) Of those not lying in the ab plane, none is shorter than c. (7) The three angles between the basis vectors a, b and c are either all acute (<90\%) or all obtuse (>=90\%)." These rules do not produce a unique result that is stable under the assumption of experimental errors, and the the resulting cell may not be primitive. In this coordinate system, the vector (.5, .5, .5) is in the middle of the given unit cell. Grid coordinates are an important variation on fractional coordinates used when working with maps. In imgCIF, the conversion from fractional to grid coordinates is implicit in the array indexing specified by _array_structure_list.dimension. Note that this implicit grid-coordinate scheme is 1-based, not zero-based, i.e. the origin of the cell for axes along the cell edges with no specified _array_structure_list_axis.displacement will have grid coordinates of (1,1,1), i.e. array indices of (1,1,1). THE ORTHOGONAL CARTESIAN COORDINATE SYSTEM (REAL SPACE) The orthogonal Cartesian coordinate system is a transformation of the direct lattice to the actual physical coordinates of atoms in space. It is similar to the laboratory coordinate system, but is anchored to and moves with the crystal, rather than being schored to the laboratory. The transformation from fractional to orthogonal cartesian coordinates is given by the _atom_sites.Cartn_transf_matrix[i][j] and _atom_sites.Cartn_transf_vector[i] tags. A common choice for the matrix of the transformation is given in the 1992 PDB format document | a b cos(\g) c cos(\b) | | 0 b sin(\g) c (cos(\a) - cos(\b)cos(\g))/sin(\g) | | 0 0 V/(a b sin(\g)) | This is a convenient coordinate system in which to do fitting of models to maps and in which to understand the chemistry of a molecule. THE RECIPROCAL LATTICE The reciprocal lattice coordinate system is used for diffraction intensitities. It is based on the reciprocal cell, the dual of the cell, in which reciprocal cell edges are derived from direct cell faces: a* = bc sin(\a)/V b* = ac sin(\b)/V c* = ab sin(\g)/V cos(\a*) = (cos(\b) cos(\g) - cos(\a))/(sin(\b) sin(\g)) cos(\b*) = (cos(\a) cos(\g) - cos(\b))/(sin(\a) sin(\g)) cos(\g*) = (cos(\a) cos(\b) - cos(\g))/(sin(\a) sin(\b)) V = abc SQRT(1 - cos(\a)^2^ - cos(\b)^2^ - cos(\g)^2^ + 2 cos(\a) cos(\b) cos(\g) ) In this form the dimensions of the reciprocal lattice are in reciprocal \%Angstroms (\%A^-1^). A dimensionless form can be obtained by multiplying by the wavelength. Reflections are commonly indexed against this coordinate system as (h, k, l) triples. References: Drenth, J., "Introduction to basic crystallography." chapter 2.1 in Rossmann, M. G. and Arnold, E. "Crystallography of biological macromolecules", Volume F of the IUCr's "International tables for crystallography", Kluwer, Dordrecht 2001, pp 44 -- 63 Leslie, A. G. W. and Powell, H. (2004). MOSFLM v6.11. MRC Laboratory of Molecular Biology, Hills Road, Cambridge, England. http://www.CCP4.ac.uk/dist/X-windows/Mosflm/. Stout, G. H. and Jensen, L. H., "X-ray structure determination", 2nd ed., Wiley, New York, 1989, 453 pp. __, "PROTEIN DATA BANK ATOMIC COORDINATE AND BIBLIOGRAPHIC ENTRY FORMAT DESCRIPTION," Brookhaven National Laboratory, February 1992. ; _category.id axis _category.mandatory_code no loop_ _category_key.name '_axis.id' '_axis.equipment' '_axis.variant' loop_ _category_group.id 'inclusive_group' 'axis_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows the axis specification of the axes of a kappa- geometry goniometer [see Stout, G. H. & Jensen, L. H. (1989). X-ray structure determination. A practical guide, 2nd ed. p. 134. New York: Wiley Interscience]. There are three axes specified, and no offsets. The outermost axis, omega, is pointed along the X axis. The next innermost axis, kappa, is at a 50 degree angle to the X axis, pointed away from the source. The innermost axis, phi, aligns with the X axis when omega and phi are at their zero points. If T-omega, T-kappa and T-phi are the transformation matrices derived from the axis settings, the complete transformation would be: X' = (T-omega) (T-kappa) (T-phi) X ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] omega rotation goniometer . 1 0 0 kappa rotation goniometer omega -.64279 0 -.76604 phi rotation goniometer kappa 1 0 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - This example shows the axis specification of the axes of a detector, source and gravity. The order has been changed as a reminder that the ordering of presentation of tokens is not significant. The centre of rotation of the detector has been taken to be 68 millimetres in the direction away from the source. ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] source . source . 0 0 1 . . . gravity . gravity . 0 -1 0 . . . tranz translation detector rotz 0 0 1 0 0 -68 twotheta rotation detector . 1 0 0 . . . roty rotation detector twotheta 0 1 0 0 0 -68 rotz rotation detector roty 0 0 1 0 0 -68 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 3 - This example show the axis specification of the axes for a map, using fractional coordinates. Each cell edge has been divided into a grid of 50 divisions in the ARRAY_STRUCTURE_LIST_AXIS category. The map is using only the first octant of the grid in the ARRAY_STRUCTURE_LIST category. The fastest changing axis is the gris along A, then along B, and the slowest is along C. The map sampling is being done in the middle of each grid division ; ; loop_ _axis.id _axis.system _axis.vector[1] _axis.vector[2] _axis.vector[3] CELL_A_AXIS fractional 1 0 0 CELL_B_AXIS fractional 0 1 0 CELL_C_AXIS fractional 0 0 1 loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_id MAP 1 25 1 increasing CELL_A_AXIS MAP 1 25 2 increasing CELL_B_AXIS MAP 1 25 3 increasing CELL_C_AXIS loop_ _array_structure_list_axis.axis_id _array_structure_list_axis.fract_displacement _array_structure_list_axis.fract_displacement_increment CELL_A_AXIS 0.01 0.02 CELL_B_AXIS 0.01 0.02 CELL_C_AXIS 0.01 0.02 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 4 - This example show the axis specification of the axes for a map, this time as orthogonal \%Angstroms, using the same coordinate system as for the atomic coordinates. The map is sampling every 1.5 \%Angstroms (1.5e-7 millimeters) in a map segment 37.5 \%Angstroms on a side. ; ; loop_ _axis.id _axis.system _axis.vector[1] _axis.vector[2] _axis.vector[3] X orthogonal 1 0 0 Y orthogonal 0 1 0 Z orthogonal 0 0 1 loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_id MAP 1 25 1 increasing X MAP 2 25 2 increasing Y MAP 3 25 3 increasing Z loop_ _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment X 7.5e-8 1.5e-7 Y 7.5e-8 1.5e-7 Z 7.5e-8 1.5e-7 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__axis.depends_on _item_description.description ; The value of _axis.depends_on specifies the next outermost axis upon which this axis depends. This item is a pointer to _axis.id in the same category. ; _item.name '_axis.depends_on' _item.category_id axis _item.mandatory_code no save_ save__axis.equipment _item_description.description ; The value of _axis.equipment specifies the type of equipment using the axis: 'goniometer', 'detector', 'gravity', 'source' or 'general'. ; _item.name '_axis.equipment' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail goniometer 'equipment used to orient or position samples' detector 'equipment used to detect reflections' general 'equipment used for general purposes' gravity 'axis specifying the downward direction' source 'axis specifying the direction sample to source' save_ save__axis.offset[1] _item_description.description ; The [1] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[2] _item_description.description ; The [2] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[3] _item_description.description ; The [3] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.id _item_description.description ; The value of _axis.id must uniquely identify each axis relevant to the experiment. Note that multiple pieces of equipment may share the same axis (e.g. a twotheta arm), so the category key for AXIS also includes the equipment. ; loop_ _item.name _item.category_id _item.mandatory_code '_axis.id' axis yes '_array_structure_list_axis.axis_id' array_structure_list_axis yes '_diffrn_detector_axis.axis_id' diffrn_detector_axis yes '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes '_diffrn_scan_axis.axis_id' diffrn_scan_axis yes '_diffrn_scan_frame_axis.axis_id' diffrn_scan_frame_axis yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_axis.depends_on' '_axis.id' '_array_structure_list_axis.axis_id' '_axis.id' '_diffrn_detector_axis.axis_id' '_axis.id' '_diffrn_measurement_axis.axis_id' '_axis.id' '_diffrn_scan_axis.axis_id' '_axis.id' '_diffrn_scan_frame_axis.axis_id' '_axis.id' save_ save__axis.system _item_description.description ; The value of _axis.system specifies the coordinate system used to define the axis: 'laboratory', 'direct', 'orthogonal', 'reciprocal' or 'abstract'. ; _item.name '_axis.system' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value laboratory loop_ _item_enumeration.value _item_enumeration.detail laboratory ; the axis is referenced to the imgCIF standard laboratory Cartesian coordinate system ; direct ; the axis is referenced to the direct lattice ; orthogonal ; the axis is referenced to the cell Cartesian orthogonal coordinates ; reciprocal ; the axis is referenced to the reciprocal lattice ; abstract ; the axis is referenced to abstract Cartesian cooridinate system ; save_ save__axis.type _item_description.description ; The value of _axis.type specifies the type of axis: 'rotation' or 'translation' (or 'general' when the type is not relevant, as for gravity). ; _item.name '_axis.type' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail rotation 'right-handed axis of rotation' translation 'translation in the direction of the axis' general 'axis for which the type is not relevant' save_ save__axis.vector[1] _item_description.description ; The [1] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[2] _item_description.description ; The [2] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[3] _item_description.description ; The [3] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.variant _item_description.description ; The value of _axis.variant gives the variant to which the given axis row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_axis.variant' _item.category_id axis _item.mandatory_code no _item_type.code code save_ ##################### # DIFFRN_DATA_FRAME # ##################### save_DIFFRN_DATA_FRAME _category.description ; Data items in the DIFFRN_DATA_FRAME category record the details about each frame of data. The items in this category were previously in a DIFFRN_FRAME_DATA category, which is now deprecated. The items from the old category are provided as aliases but should not be used for new work. ; _category.id diffrn_data_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_data_frame.id' '_diffrn_data_frame.detector_element_id' '_diffrn_data_frame.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A frame containing data from 4 frame elements. Each frame element has a common array configuration 'array_1' described in ARRAY_STRUCTURE and related categories. The data for each detector element are stored in four groups of binary data in the ARRAY_DATA category, linked by the array_id and binary_id. ; ; loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id frame_1 d1_ccd_1 array_1 1 frame_1 d1_ccd_2 array_1 2 frame_1 d1_ccd_3 array_1 3 frame_1 d1_ccd_4 array_1 4 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_data_frame.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_diffrn_data_frame.array_id' _item.category_id diffrn_data_frame _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_frame_data.array_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_diffrn_data_frame.binary_id' _item.category_id diffrn_data_frame _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_frame_data.binary_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code int save_ save__diffrn_data_frame.center_fast _item_description.description ; The value of _diffrn_data_frame.center_fast is the fast index axis beam center position relative to the detector element face in the units specified in the data item '_diffrn_data_frame.center_units' along the fast axis of the detector from the center of the first pixel to the point at which the Z-axis (which should be colinear with the beam) intersects the face of the detector, if in fact is does. At the time of the measurement the current setting of detector positioner given frame are used. It is important to note that for measurements in millimetres, the sense of the axis is used, rather than the sign of the pixel-to-pixel increments. ; _item.name '_diffrn_data_frame.center_fast' _item.category_id diffrn_data_frame _item.mandatory_code no _item_type.code float save_ save__diffrn_data_frame.center_slow _item_description.description ; The value of _diffrn_data_frame.center_slow is the slow index axis beam center position relative to the detector element face in the units specified in the data item '_diffrn_data_frame.center_units' along the slow axis of the detector from the center of the first pixel to the point at which the Z-axis (which should be colinear with the beam) intersects the face of the detector, if in fact is does. At the time of the measurement the current setting of detector positioner given frame are used. It is important to note that the sense of the axis is used, rather than the sign of the pixel-to-pixel increments. ; _item.name '_diffrn_data_frame.center_slow' _item.category_id diffrn_data_frame _item.mandatory_code no _item_type.code float save_ save__diffrn_data_frame.center_units _item_description.description ; The value of _diffrn_data_frame.center_units specifies the units in which the values of '_diffrn_data_frame.center_fast' and '_diffrn_data_frame.center_slow' are presented. The default is 'mm' for millimetres. The alternatives are 'pixels' and 'bins'. In all cases the center distances are measured from the center of the first pixel, i.e. in a 2x2 binning, the measuring origin is offset from the centers of the bins by one half pixel towards the first pixel. If 'bins' is specified, the data in '_array_intensities.pixel_fast_bin_size', '_array_intensities.pixel_slow_bin_size', and '_array_intensities.pixel_binning_method' is used to define the binning scheme. ; _item.name '_diffrn_data_frame.center_units' _item.category_id diffrn_data_frame _item.mandatory_code no _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail mm 'millimetres' pixels 'detector pixels' bins 'detector bins' save_ save__diffrn_data_frame.detector_element_id _item_description.description ; This item is a pointer to _diffrn_detector_element.id in the DIFFRN_DETECTOR_ELEMENT category. ; _item.name '_diffrn_data_frame.detector_element_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.detector_element_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.id _item_description.description ; The value of _diffrn_data_frame.id must uniquely identify each complete frame of data. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_data_frame.id' diffrn_data_frame yes '_diffrn_refln.frame_id' diffrn_refln yes '_diffrn_scan.frame_id_start' diffrn_scan yes '_diffrn_scan.frame_id_end' diffrn_scan yes '_diffrn_scan_frame.frame_id' diffrn_scan_frame yes '_diffrn_scan_frame_axis.frame_id' diffrn_scan_frame_axis yes '_diffrn_scan_frame_monitor.frame_id' diffrn_scan_frame_monitor implicit _item_aliases.alias_name '_diffrn_frame_data.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_refln.frame_id' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_start' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_end' '_diffrn_data_frame.id' '_diffrn_scan_frame.frame_id' '_diffrn_data_frame.id' '_diffrn_scan_frame_axis.frame_id' '_diffrn_data_frame.id' '_diffrn_scan_frame_monitor.frame_id' '_diffrn_data_frame.id' save_ save__diffrn_data_frame.details _item_description.description ; The value of _diffrn_data_frame.details should give a description of special aspects of each frame of data. This is an appropriate location in which to record information from vendor headers as presented in those headers, but it should never be used as a substitute for providing the fully parsed information within the appropriate imgCIF/CBF categories. Normally, when a conversion from a miniCBF has been done the data from '_array_data.header_convention' should be transferred to this data item and '_array_data.header_convention' should be removed. ; _item.name '_diffrn_data_frame.details' _item.category_id diffrn_data_frame _item.mandatory_code no _item_aliases.alias_name '_diffrn_frame_data.details' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.4 _item_type.code text loop_ _item_examples.case _item_examples.detail ; HEADER_BYTES = 512; DIM = 2; BYTE_ORDER = big_endian; TYPE = unsigned_short; SIZE1 = 3072; SIZE2 = 3072; PIXEL_SIZE = 0.102588; BIN = 2x2; DETECTOR_SN = 901; TIME = 29.945155; DISTANCE = 200.000000; PHI = 85.000000; OSC_START = 85.000000; OSC_RANGE = 1.000000; WAVELENGTH = 0.979381; BEAM_CENTER_X = 157.500000; BEAM_CENTER_Y = 157.500000; PIXEL SIZE = 0.102588; OSCILLATION RANGE = 1; EXPOSURE TIME = 29.9452; TWO THETA = 0; BEAM CENTRE = 157.5 157.5; ; ; Example of header information extracted from an ADSC Quantum 315 detector header by CBFlib_0.7.6. Image provided by Chris Nielsen of ADSC from a data collection at SSRL beamline 1-5. ; save_ save__diffrn_data_frame.variant _item_description.description ; The value of _diffrn_data_frame.variant gives the variant to which the given diffrn_data_frame row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_data_frame.variant' _item.category_id diffrn_data_frame _item.mandatory_code no _item_type.code code save_ ########################################################################## # The following is a restatement of the mmCIF DIFFRN_DETECTOR, # # DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for # # the CBF/imgCIF extensions # ########################################################################## ################### # DIFFRN_DETECTOR # ################### save_DIFFRN_DETECTOR _category.description ; Data items in the DIFFRN_DETECTOR category describe the detector used to measure the scattered radiation, including any analyser and post-sample collimation. ; _category.id diffrn_detector _category.mandatory_code no loop_ _category_key.name '_diffrn_detector.diffrn_id' '_diffrn_detector.id' '_diffrn_detector.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _diffrn_detector.diffrn_id 'd1' _diffrn_detector.detector 'multiwire' _diffrn_detector.type 'Siemens' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector.details _item_description.description ; A description of special aspects of the radiation detector. ; _item.name '_diffrn_detector.details' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'slow mode' save_ save__diffrn_detector.detector _item_description.description ; The general class of the radiation detector. ; _item.name '_diffrn_detector.detector' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector' cifdic.c91 1.0 '_diffrn_detector' cif_core.dic 2.0 _item_type.code text loop_ _item_examples.case 'photographic film' 'scintillation counter' 'CCD plate' 'BF~3~ counter' save_ save__diffrn_detector.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. The value of _diffrn.id uniquely defines a set of diffraction data. ; _item.name '_diffrn_detector.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector.dtime _item_description.description ; The deadtime in microseconds of the detector(s) used to measure the diffraction intensities. ; _item.name '_diffrn_detector.dtime' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector_dtime' cifdic.c91 1.0 '_diffrn_detector_dtime' cif_core.dic 2.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code microseconds save_ save__diffrn_detector.id _item_description.description ; The value of _diffrn_detector.id must uniquely identify each detector used to collect each diffraction data set. If the value of _diffrn_detector.id is not given, it is implicitly equal to the value of _diffrn_detector.diffrn_id. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector.id' diffrn_detector implicit '_diffrn_detector_axis.detector_id' diffrn_detector_axis yes '_diffrn_scan_frame_monitor.detector_id' diffrn_scan_frame_monitor yes loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_detector_axis.detector_id' '_diffrn_detector.id' '_diffrn_scan_frame_monitor.detector_id' '_diffrn_detector.id' _item_type.code code save_ save__diffrn_detector.number_of_axes _item_description.description ; The value of _diffrn_detector.number_of_axes gives the number of axes of the positioner for the detector identified by _diffrn_detector.id. The word 'positioner' is a general term used in instrumentation design for devices that are used to change the positions of portions of apparatus by linear translation, rotation or combinations of such motions. Axes which are used to provide a coordinate system for the face of an area detetctor should not be counted for this data item. The description of each axis should be provided by entries in DIFFRN_DETECTOR_AXIS. ; _item.name '_diffrn_detector.number_of_axes' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_detector.type _item_description.description ; The make, model or name of the detector device used. ; _item.name '_diffrn_detector.type' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ save__diffrn_detector.variant _item_description.description ; The value of _diffrn_detector.variant gives the variant to which the given diffrn_detector row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_detector.variant' _item.category_id diffrn_detector _item.mandatory_code no _item_type.code code save_ ######################## # DIFFRN_DETECTOR_AXIS # ######################## save_DIFFRN_DETECTOR_AXIS _category.description ; Data items in the DIFFRN_DETECTOR_AXIS category associate axes with detectors. ; _category.id diffrn_detector_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_axis.detector_id' '_diffrn_detector_axis.axis_id' '_diffrn_detector_axis.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_detector_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_detector_axis.axis_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_axis.detector_id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. This item was previously named _diffrn_detector_axis.id which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_detector_axis.detector_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_aliases.alias_name '_diffrn_detector_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_detector_axis.variant _item_description.description ; The value of _diffrn_detector_axis.variant gives the variant to which the given diffrn_detector_axis row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_detector_axis.variant' _item.category_id diffrn_detector_axis _item.mandatory_code no _item_type.code code save_ ########################### # DIFFRN_DETECTOR_ELEMENT # ########################### save_DIFFRN_DETECTOR_ELEMENT _category.description ; Data items in the DIFFRN_DETECTOR_ELEMENT category record the details about spatial layout and other characteristics of each element of a detector which may have multiple elements. In most cases, giving more detailed information in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS is preferable to simply providing the centre of the detector element. ; _category.id diffrn_detector_element _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_element.id' '_diffrn_detector_element.detector_id' '_diffrn_detector_element.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Detector d1 is composed of four CCD detector elements, each 200 mm by 200 mm, arranged in a square, in the pattern 1 2 * 3 4 Note that the beam centre is slightly displaced from each of the detector elements, just beyond the lower right corner of 1, the lower left corner of 2, the upper right corner of 3 and the upper left corner of 4. For each element, the detector face coordiate system, is assumed to have the fast axis running from left to right and the slow axis running from top to bottom with the origin at the top left corner. ; ; loop_ _diffrn_detector_element.detector_id _diffrn_detector_element.id _diffrn_detector_element.reference_center_fast _diffrn_detector_element.reference_center_slow _diffrn_detector_element.reference_center_units d1 d1_ccd_1 201.5 201.5 mm d1 d1_ccd_2 -1.8 201.5 mm d1 d1_ccd_3 201.6 -1.4 mm d1 d1_ccd_4 -1.7 -1.5 mm ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector_element.id _item_description.description ; The value of _diffrn_detector_element.id must uniquely identify each element of a detector. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector_element.id' diffrn_detector_element yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.detector_element_id' '_diffrn_detector_element.id' save_ save__diffrn_detector_element.detector_id _item_description.description ; This item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. ; _item.name '_diffrn_detector_element.detector_id' _item.category_id diffrn_detector_element _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_element.reference_center_fast _item_description.description ; The value of _diffrn_detector_element.reference_center_fast is the fast index axis beam center position relative to the detector element face in the units specified in the data item '_diffrn_detector_element.reference_center_units' along the fast axis of the detector from the center of the first pixel to the point at which the Z-axis (which should be colinear with the beam) intersects the face of the detector, if in fact is does. At the time of the measurement all settings of the detector positioner should be at their reference settings. If more than one reference setting has been used the value given whould be representive of the beam center as determined from the ensemble of settings. It is important to note that for measurements in millimetres, the sense of the axis is used, rather than the sign of the pixel-to-pixel increments. ; _item.name '_diffrn_detector_element.reference_center_fast' _item.category_id diffrn_detector_element _item.mandatory_code no _item_type.code float save_ save__diffrn_detector_element.reference_center_slow _item_description.description ; The value of _diffrn_detector_element.reference_center_slow is the slow index axis beam center position relative to the detector element face in the units specified in the data item '_diffrn_detector_element.reference_center_units' along the slow axis of the detector from the center of the first pixel to the point at which the Z-axis (which should be colinear with the beam) intersects the face of the detector, if in fact is does. At the time of the measurement all settings of the detector positioner should be at their reference settings. If more than one reference setting has been used the value givien whould be representive of the beam center as determined from the ensemble of settings. It is important to note that the sense of the axis is used, rather than the sign of the pixel-to-pixel increments. ; _item.name '_diffrn_detector_element.reference_center_slow' _item.category_id diffrn_detector_element _item.mandatory_code no _item_type.code float save_ save__diffrn_detector_element.reference_center_units _item_description.description ; The value of _diffrn_detector_element.reference_center_units specifies the units in which the values of '_diffrn_detector_element.reference_center_fast' and '_diffrn_detector_element.reference_center_slow' are presented. The default is 'mm' for millimetres. The alternatives are 'pixels' and 'bins'. In all cases the center distances are measured from the center of the first pixel, i.e. in a 2x2 binning, the measuring origin is offset from the centers of the bins by one half pixel towards the first pixel. If 'bins' is specified, the data in '_array_intensities.pixel_fast_bin_size', '_array_intensities.pixel_slow_bin_size', and '_array_intensities.pixel_binning_method' is used to define the binning scheme. ; _item.name '_diffrn_detector_element.reference_center_units' _item.category_id diffrn_detector_element _item.mandatory_code no _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail mm 'millimetres' pixels 'detector pixels' bins 'detector bins' save_ save__diffrn_detector_element.variant _item_description.description ; The value of _diffrn_detector_element.variant gives the variant to which the given diffrn_detector_element row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_detector_element.variant' _item.category_id diffrn_detector_element _item.mandatory_code no _item_type.code code save_ ######################## ## DIFFRN_MEASUREMENT ## ######################## save_DIFFRN_MEASUREMENT _category.description ; Data items in the DIFFRN_MEASUREMENT category record details about the device used to orient and/or position the crystal during data measurement and the manner in which the diffraction data were measured. ; _category.id diffrn_measurement _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement.device' '_diffrn_measurement.diffrn_id' '_diffrn_measurement.id' '_diffrn_measurement.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_measurement.diffrn_id 'd1' _diffrn_measurement.device '3-circle camera' _diffrn_measurement.device_type 'Supper model X' _diffrn_measurement.device_details 'none' _diffrn_measurement.method 'omega scan' _diffrn_measurement.details ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _diffrn_measurement.diffrn_id 's1' _diffrn_measurement.device_type 'Philips PW1100/20 diffractometer' _diffrn_measurement.method 'theta/2theta (\q/2\q)' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_measurement.device _item_description.description ; The general class of goniometer or device used to support and orient the specimen. If the value of _diffrn_measurement.device is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id. Either _diffrn_measurement.device or _diffrn_measurement.id may be used to link to other categories. If the experimental setup admits multiple devices, then _diffrn_measurement.id is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.device' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_device' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement.device' _item_aliases.alias_name '_diffrn_measurement_device' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '3-circle camera' '4-circle camera' 'kappa-geometry camera' 'oscillation camera' 'precession camera' save_ save__diffrn_measurement.device_details _item_description.description ; A description of special aspects of the device used to measure the diffraction intensities. ; _item.name '_diffrn_measurement.device_details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; commercial goniometer modified locally to allow for 90\% \t arc ; save_ save__diffrn_measurement.device_type _item_description.description ; The make, model or name of the measurement device (goniometer) used. ; _item.name '_diffrn_measurement.device_type' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Supper model q' 'Huber model r' 'Enraf-Nonius model s' 'home-made' save_ save__diffrn_measurement.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_measurement.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement.details _item_description.description ; A description of special aspects of the intensity measurement. ; _item.name '_diffrn_measurement.details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; save_ save__diffrn_measurement.id _item_description.description ; The value of _diffrn_measurement.id must uniquely identify the set of mechanical characteristics of the device used to orient and/or position the sample used during the collection of each diffraction data set. If the value of _diffrn_measurement.id is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id. Either _diffrn_measurement.device or _diffrn_measurement.id may be used to link to other categories. If the experimental setup admits multiple devices, then _diffrn_measurement.id is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.id' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_id' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement.id' _item_type.code code save_ save__diffrn_measurement.method _item_description.description ; Method used to measure intensities. ; _item.name '_diffrn_measurement.method' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_method' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'profile data from theta/2theta (\q/2\q) scans' save_ save__diffrn_measurement.number_of_axes _item_description.description ; The value of _diffrn_measurement.number_of_axes gives the number of axes of the positioner for the goniometer or other sample orientation or positioning device identified by _diffrn_measurement.id. The description of the axes should be provided by entries in DIFFRN_MEASUREMENT_AXIS. ; _item.name '_diffrn_measurement.number_of_axes' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ # _diffrn_measurement.sample_detector_distance # _diffrn_measurement.sample_detector_voffset save__diffrn_measurement.sample_detector_distance _item_description.description ; The value of _diffrn_measurement.sample_detector_distance gives the unsigned distance in millimetres from the sample to the detector along the beam. ; _item.name '_diffrn_measurement.sample_detector_distance' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 _item_type.code float _item_units.code mm save_ save__diffrn_measurement.sample_detector_voffset _item_description.description ; The value of _diffrn_measurement.sample_detector_voffset gives the signed distance in millimetres in the vertical direction (positive for up) from the center of the beam to the center of the detector. ; _item.name '_diffrn_measurement.sample_detector_voffset' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . . . . _item_type.code float _item_units.code mm save_ save__diffrn_measurement.specimen_support _item_description.description ; The physical device used to support the crystal during data collection. ; _item.name '_diffrn_measurement.specimen_support' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_specimen_support' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'glass capillary' 'quartz capillary' 'fiber' 'metal loop' save_ save__diffrn_measurement.variant _item_description.description ; The value of _diffrn_measurement.variant gives the variant to which the given diffrn_measurement row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_measurement.variant' _item.category_id diffrn_measurement _item.mandatory_code no _item_type.code code save_ ########################### # DIFFRN_MEASUREMENT_AXIS # ########################### save_DIFFRN_MEASUREMENT_AXIS _category.description ; Data items in the DIFFRN_MEASUREMENT_AXIS category associate axes with goniometers. ; _category.id diffrn_measurement_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement_axis.axis_id' '_diffrn_measurement_axis.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_measurement_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_measurement_axis.axis_id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.measurement_device _item_description.description ; This data item is a pointer to _diffrn_measurement.device in the DIFFRN_MEASUREMENT category. ; _item.name '_diffrn_measurement_axis.measurement_device' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit _item_type.code text save_ save__diffrn_measurement_axis.measurement_id _item_description.description ; This data item is a pointer to _diffrn_measurement.id in the DIFFRN_MEASUREMENT category. This item was previously named _diffrn_measurement_axis.id, which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_measurement_axis.measurement_id' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_measurement_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_measurement_axis.variant _item_description.description ; The value of _diffrn_measurement_axis.variant gives the variant to which the given diffrn_measurement_axis row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_measurement_axis.variant' _item.category_id diffrn_measurement_axis _item.mandatory_code no _item_type.code code save_ #################### # DIFFRN_RADIATION # #################### save_DIFFRN_RADIATION _category.description ; Data items in the DIFFRN_RADIATION category describe the radiation used for measuring diffraction intensities, its collimation and monochromatization before the sample. Post-sample treatment of the beam is described by data items in the DIFFRN_DETECTOR category. ; _category.id diffrn_radiation _category.mandatory_code no loop_ _category_key.name '_diffrn_radiation.diffrn_id' '_diffrn_radiation.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_radiation.diffrn_id 'set1' _diffrn_radiation.collimation '0.3 mm double pinhole' _diffrn_radiation.monochromator 'graphite' _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.wavelength_id 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _diffrn_radiation.wavelength_id 1 _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.monochromator 'graphite' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_radiation.collimation _item_description.description ; The collimation or focusing applied to the radiation. ; _item.name '_diffrn_radiation.collimation' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_collimation' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '0.3 mm double-pinhole' '0.5 mm' 'focusing mirrors' save_ save__diffrn_radiation.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_radiation.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_radiation.div_x_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory X axis (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the standard uncertainty (e.s.d.) of the directions of photons in the XZ plane around the mean source beam direction. Note that for some synchrotrons this value is specified in milliradians, in which case a conversion is needed. To convert a value in milliradians to a value in degrees, multiply by 0.180 and divide by \p. ; _item.name '_diffrn_radiation.div_x_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.div_y_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory Y axis (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the standard uncertainty (e.s.d.) of the directions of photons in the YZ plane around the mean source beam direction. Note that for some synchrotrons this value is specified in milliradians, in which case a conversion is needed. To convert a value in milliradians to a value in degrees, multiply by 0.180 and divide by \p. ; _item.name '_diffrn_radiation.div_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.div_x_y_source _item_description.description ; Beam crossfire correlation degrees^2^ between the crossfire laboratory X-axis component and the crossfire laboratory Y-axis component (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the mean of the products of the deviations of the direction of each photon in XZ plane times the deviations of the direction of the same photon in the YZ plane around the mean source beam direction. This will be zero for uncorrelated crossfire. Note that some synchrotrons, this value is specified in milliradians^2^, in which case a conversion would be needed. To go from a value in milliradians^2^ to a value in degrees^2^, multiply by 0.180^2^ and divide by \p^2^. ; _item.name '_diffrn_radiation.div_x_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees_squared _item_default.value 0.0 save_ save__diffrn_radiation.filter_edge _item_description.description ; Absorption edge in \%Angstroms of the radiation filter used. ; _item.name '_diffrn_radiation.filter_edge' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_filter_edge' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__diffrn_radiation.inhomogeneity _item_description.description ; Half-width in millimetres of the incident beam in the direction perpendicular to the diffraction plane. ; _item.name '_diffrn_radiation.inhomogeneity' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_inhomogeneity' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code millimetres save_ save__diffrn_radiation.monochromator _item_description.description ; The method used to obtain monochromatic radiation. If a monochromator crystal is used, the material and the indices of the Bragg reflection are specified. ; _item.name '_diffrn_radiation.monochromator' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_monochromator' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Zr filter' 'Ge 220' 'none' 'equatorial mounted graphite' save_ save__diffrn_radiation.polarisn_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the perpendicular component of the polarization and the diffraction plane. See _diffrn_radiation_polarisn_ratio. ; _item.name '_diffrn_radiation.polarisn_norm' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_norm' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.polarisn_ratio _item_description.description ; Polarization ratio of the diffraction beam incident on the crystal. This is the ratio of the perpendicularly polarized to the parallel polarized component of the radiation. The perpendicular component forms an angle of _diffrn_radiation.polarisn_norm to the normal to the diffraction plane of the sample (i.e. the plane containing the incident and reflected beams). ; _item.name '_diffrn_radiation.polarisn_ratio' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_ratio' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__diffrn_radiation.polarizn_source_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the normal to the polarization plane and the laboratory Y axis as defined in the AXIS category. Note that this is the angle of polarization of the source photons, either directly from a synchrotron beamline or from a monochromater. This differs from the value of _diffrn_radiation.polarisn_norm in that _diffrn_radiation.polarisn_norm refers to polarization relative to the diffraction plane rather than to the laboratory axis system. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane should be taken as the XZ plane and the angle as 0. See _diffrn_radiation.polarizn_source_ratio. ; _item.name '_diffrn_radiation.polarizn_source_norm' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.polarizn_source_ratio _item_description.description ; (Ip-In)/(Ip+In), where Ip is the intensity (amplitude squared) of the electric vector in the plane of polarization and In is the intensity (amplitude squared) of the electric vector in the plane of the normal to the plane of polarization. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane is to be taken as the XZ plane and the normal is parallel to the Y axis. Thus, if there was complete polarization in the plane of polarization, the value of _diffrn_radiation.polarizn_source_ratio would be 1, and for an unpolarized beam _diffrn_radiation.polarizn_source_ratio would have a value of 0. If the X axis has been chosen to lie in the plane of polarization, this definition will agree with the definition of 'MONOCHROMATOR' in the Denzo glossary, and values of near 1 should be expected for a bending-magnet source. However, if the X axis were perpendicular to the polarization plane (not a common choice), then the Denzo value would be the negative of _diffrn_radiation.polarizn_source_ratio. See http://www.hkl-xray.com for information on Denzo and Otwinowski & Minor (1997). This differs both in the choice of ratio and choice of orientation from _diffrn_radiation.polarisn_ratio, which, unlike _diffrn_radiation.polarizn_source_ratio, is unbounded. Reference: Otwinowski, Z. & Minor, W. (1997). 'Processing of X-ray diffraction data collected in oscillation mode.' Methods Enzymol. 276, 307-326. ; _item.name '_diffrn_radiation.polarizn_source_ratio' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 -1.0 -1.0 -1.0 _item_type.code float save_ save__diffrn_radiation.probe _item_description.description ; Name of the type of radiation used. It is strongly recommended that this be given so that the probe radiation is clearly specified. ; _item.name '_diffrn_radiation.probe' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_probe' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value 'X-ray' 'neutron' 'electron' 'gamma' save_ save__diffrn_radiation.type _item_description.description ; The nature of the radiation. This is typically a description of the X-ray wavelength in Siegbahn notation. ; _item.name '_diffrn_radiation.type' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'CuK\a' 'Cu K\a~1~' 'Cu K-L~2,3~' 'white-beam' save_ save__diffrn_radiation.xray_symbol _item_description.description ; The IUPAC symbol for the X-ray wavelength for the probe radiation. ; _item.name '_diffrn_radiation.xray_symbol' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_xray_symbol' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value _item_enumeration.detail 'K-L~3~' 'K\a~1~ in older Siegbahn notation' 'K-L~2~' 'K\a~2~ in older Siegbahn notation' 'K-M~3~' 'K\b~1~ in older Siegbahn notation' 'K-L~2,3~' 'use where K-L~3~ and K-L~2~ are not resolved' save_ save__diffrn_radiation.wavelength_id _item_description.description ; This data item is a pointer to _diffrn_radiation_wavelength.id in the DIFFRN_RADIATION_WAVELENGTH category. ; _item.name '_diffrn_radiation.wavelength_id' _item.category_id diffrn_radiation _item.mandatory_code yes _item_type.code code save_ save__diffrn_radiation.variant _item_description.description ; The value of _diffrn_radiation.variant gives the variant to which the given diffrn_radiation row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_radiation.variant' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code code save_ ################ # DIFFRN_REFLN # ################ save_DIFFRN_REFLN _category.description ; This category redefinition has been added to extend the key of the standard DIFFRN_REFLN category. Data items in the DIFFRN_REFLN category record details about the intensities in the diffraction data set identified by _diffrn_refln.diffrn_id. The DIFFRN_REFLN data items refer to individual intensity measurements and must be included in looped lists. The DIFFRN_REFLNS data items specify the parameters that apply to all intensity measurements in the particular diffraction data set identified by _diffrn_reflns.diffrn_id and _diffrn_refln.frame_id ; _category.id diffrn_refln _category.mandatory_code no loop_ _category_key.name '_diffrn_refln.diffrn_id' '_diffrn_refln.id' '_diffrn_refln.frame_id' '_diffrn_refln.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_refln.frame_id _item_description.description ; This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_refln.frame_id' _item.category_id diffrn_refln _item.mandatory_code yes _item_type.code code save_ save__diffrn_refln.variant _item_description.description ; The value of _diffrn_refln.variant gives the variant to which the given diffrn_refln row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_refln.variant' _item.category_id diffrn_refln _item.mandatory_code no _item_type.code code save_ ############### # DIFFRN_SCAN # ############### save_DIFFRN_SCAN _category.description ; Data items in the DIFFRN_SCAN category describe the parameters of one or more scans, relating axis positions to frames. ; _category.id diffrn_scan _category.mandatory_code no loop_ _category_key.name '_diffrn_scan.id' '_diffrn_scan.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - derived from a suggestion by R. M. Sweet. The vector of each axis is not given here, because it is provided in the AXIS category. By making _diffrn_scan_axis.scan_id and _diffrn_scan_axis.axis_id keys of the DIFFRN_SCAN_AXIS category, an arbitrary number of scanning and fixed axes can be specified for a scan. In this example, three rotation axes and one translation axis at nonzero values are specified, with one axis stepping. There is no reason why more axes could not have been specified to step. Range information has been specified, but note that it can be calculated from the number of frames and the increment, so the data item _diffrn_scan_axis.angle_range could be dropped. Both the sweep data and the data for a single frame are specified. Note that the information on how the axes are stepped is given twice, once in terms of the overall averages in the value of _diffrn_scan.integration_time and the values for DIFFRN_SCAN_AXIS, and precisely for the given frame in the value for _diffrn_scan_frame.integration_time and the values for DIFFRN_SCAN_FRAME_AXIS. If dose-related adjustments are made to scan times and nonlinear stepping is done, these values may differ. Therefore, in interpreting the data for a particular frame it is important to use the frame-specific data. ; ; _diffrn_scan.id 1 _diffrn_scan.date_start '2001-11-18T03:26:42' _diffrn_scan.date_end '2001-11-18T03:36:45' _diffrn_scan.integration_time 3.0 _diffrn_scan.frame_id_start mad_L2_000 _diffrn_scan.frame_id_end mad_L2_200 _diffrn_scan.frames 201 loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment 1 omega 200.0 20.0 0.1 . . . 1 kappa -40.0 0.0 0.0 . . . 1 phi 127.5 0.0 0.0 . . . 1 tranz . . . 2.3 0.0 0.0 _diffrn_scan_frame.scan_id 1 _diffrn_scan_frame.date '2001-11-18T03:27:33' _diffrn_scan_frame.integration_time 3.0 _diffrn_scan_frame.frame_id mad_L2_018 _diffrn_scan_frame.frame_number 18 loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.angle_increment _diffrn_scan_frame_axis.displacement _diffrn_scan_frame_axis.displacement_increment mad_L2_018 omega 201.8 0.1 . . mad_L2_018 kappa -40.0 0.0 . . mad_L2_018 phi 127.5 0.0 . . mad_L2_018 tranz . . 2.3 0.0 ; ; Example 2 - a more extensive example (R. M. Sweet, P. J. Ellis & H. J. Bernstein). A detector is placed 240 mm along the Z axis from the goniometer. This leads to a choice: either the axes of the detector are defined at the origin, and then a Z setting of -240 is entered, or the axes are defined with the necessary Z offset. In this case, the setting is used and the offset is left as zero. This axis is called DETECTOR_Z. The axis for positioning the detector in the Y direction depends on the detector Z axis. This axis is called DETECTOR_Y. The axis for positioning the detector in the X direction depends on the detector Y axis (and therefore on the detector Z axis). This axis is called DETECTOR_X. This detector may be rotated around the Y axis. This rotation axis depends on the three translation axes. It is called DETECTOR_PITCH. A coordinate system is defined on the face of the detector in terms of 2300 0.150 mm pixels in each direction. The ELEMENT_X axis is used to index the first array index of the data array and the ELEMENT_Y axis is used to index the second array index. Because the pixels are 0.150mm X 0.150mm, the centre of the first pixel is at (0.075, 0.075) in this coordinate system. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 172.43 -172.43 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 2300 1 increasing ELEMENT_X ARRAY1 2 2300 2 increasing ELEMENT_Y # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.075 0.150 ELEMENT_Y ELEMENT_Y 0.075 0.150 # category ARRAY_ELEMENT_SIZE loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 ARRAY1 2 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; ; Example 3 - Example 2 revised for a spiral scan (R. M. Sweet, P. J. Ellis & H. J. Bernstein). A detector is placed 240 mm along the Z axis from the goniometer, as in Example 2 above, but in this example the image plate is scanned in a spiral pattern from the outside edge in. The axis for positioning the detector in the Y direction depends on the detector Z axis. This axis is called DETECTOR_Y. The axis for positioning the detector in the X direction depends on the detector Y axis (and therefore on the detector Z axis). This axis is called DETECTOR_X. This detector may be rotated around the Y axis. This rotation axis depends on the three translation axes. It is called DETECTOR_PITCH. A coordinate system is defined on the face of the detector in terms of a coupled rotation axis and radial scan axis to form a spiral scan. The rotation axis is called ELEMENT_ROT and the radial axis is called ELEMENT_RAD. A 150 micrometre radial pitch and a 75 micrometre 'constant velocity' angular pitch are assumed. Indexing is carried out first on the rotation axis and the radial axis is made to be dependent on it. The two axes are coupled to form an axis set ELEMENT_SPIRAL. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_ROT translation detector DETECTOR_PITCH 0 0 1 0 0 0 ELEMENT_RAD translation detector ELEMENT_ROT 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.angle _array_structure_list_axis.displacement _array_structure_list_axis.angular_pitch _array_structure_list_axis.radial_pitch ELEMENT_SPIRAL ELEMENT_ROT 0 . 0.075 . ELEMENT_SPIRAL ELEMENT_RAD . 172.5 . -0.150 # category ARRAY_ELEMENT_SIZE # the actual pixels are 0.075 by 0.150 mm # We give the coarser dimension here. loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_scan.id _item_description.description ; The value of _diffrn_scan.id uniquely identifies each scan. The identifier is used to tie together all the information about the scan. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_scan.id' diffrn_scan yes '_diffrn_scan_axis.scan_id' diffrn_scan_axis yes '_diffrn_scan_frame.scan_id' diffrn_scan_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_scan_axis.scan_id' '_diffrn_scan.id' '_diffrn_scan_frame.scan_id' '_diffrn_scan.id' save_ save__diffrn_scan.date_end _item_description.description ; The date and time of the end of the scan. Note that this may be an estimate generated during the scan, before the precise time of the end of the scan is known. ; _item.name '_diffrn_scan.date_end' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.date_start _item_description.description ; The date and time of the start of the scan. ; _item.name '_diffrn_scan.date_start' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.integration_time _item_description.description ; Approximate average time in seconds to integrate each step of the scan. The precise time for integration of each particular step must be provided in _diffrn_scan_frame.integration_time, even if all steps have the same integration time. ; _item.name '_diffrn_scan.integration_time' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan.frame_id_start _item_description.description ; The value of this data item is the identifier of the first frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_start' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frame_id_end _item_description.description ; The value of this data item is the identifier of the last frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_end' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frames _item_description.description ; The value of this data item is the number of frames in the scan. ; _item.name '_diffrn_scan.frames' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 1 1 1 save_ save__diffrn_scan.time_period _item_description.description ; Approximate average time in seconds between the start of each step of the scan. The precise start-to-start time increment of each particular step may be provided in _diffrn_scan_frame.time_period. ; _item.name '_diffrn_scan.time_period' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan.time_rstrt_incr _item_description.description ; Approximate average time in seconds between the end of integration of each step of the scan than the start of integration of the next step. In general, this will agree with _diffrn_scan_frame.time_rstrt_incr. The sum of the values of _diffrn_scan_frame.integration_time and _diffrn_scan_frame.time_rstrt_incr is the time from the start of integration of one frame and the start of integration for the next frame and should equal the value of _diffrn_scan_frame.time_period for this frame. If the individual frame values vary, then the value of _diffrn_scan.time_rstrt_incr will be representative of the ensemble of values of _diffrn_scan_frame_axis.time_rstrt_incr (e.g. the mean). ; _item.name '_diffrn_scan.time_period' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan.variant _item_description.description ; The value of _diffrn_scan.variant gives the variant to which the given diffrn_scan row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_scan.variant' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code code save_ #################### # DIFFRN_SCAN_AXIS # #################### save_DIFFRN_SCAN_AXIS _category.description ; Data items in the DIFFRN_SCAN_AXIS category describe the settings of axes for particular scans. Unspecified axes are assumed to be at their zero points. ; _category.id diffrn_scan_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_axis.scan_id' '_diffrn_scan_axis.axis_id' '_diffrn_scan_axis.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_axis.scan_id _item_description.description ; The value of this data item is the identifier of the scan for which axis settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan.id. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_axis.scan_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the scan for which settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan.id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_axis.axis_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.angle_start _item_description.description ; The starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_range _item_description.description ; The range from the starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_increment _item_description.description ; The increment for each step for the specified axis in degrees. In general, this will agree with _diffrn_scan_frame_axis.angle_increment. The sum of the values of _diffrn_scan_frame_axis.angle and _diffrn_scan_frame_axis.angle_increment is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of _diffrn_scan_axis.angle_increment will be representative of the ensemble of values of _diffrn_scan_frame_axis.angle_increment (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_rstrt_incr _item_description.description ; The increment after each step for the specified axis in degrees. In general, this will agree with _diffrn_scan_frame_axis.angle_rstrt_incr. The sum of the values of _diffrn_scan_frame_axis.angle, _diffrn_scan_frame_axis.angle_increment and _diffrn_scan_frame_axis.angle_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame and should equal _diffrn_scan_frame_axis.angle for this next frame. If the individual frame values vary, then the value of _diffrn_scan_axis.angle_rstrt_incr will be representative of the ensemble of values of _diffrn_scan_frame_axis.angle_rstrt_incr (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.displacement_start _item_description.description ; The starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_range _item_description.description ; The range from the starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_increment _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with _diffrn_scan_frame_axis.displacement_increment. The sum of the values of _diffrn_scan_frame_axis.displacement and _diffrn_scan_frame_axis.displacement_increment is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of _diffrn_scan_axis.displacement_increment will be representative of the ensemble of values of _diffrn_scan_frame_axis.displacement_increment (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_rstrt_incr _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with _diffrn_scan_frame_axis.displacement_rstrt_incr. The sum of the values of _diffrn_scan_frame_axis.displacement, _diffrn_scan_frame_axis.displacement_increment and _diffrn_scan_frame_axis.displacement_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame and should equal _diffrn_scan_frame_axis.displacement for this next frame. If the individual frame values vary, then the value of _diffrn_scan_axis.displacement_rstrt_incr will be representative of the ensemble of values of _diffrn_scan_frame_axis.displacement_rstrt_incr (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.reference_angle _item_description.description ; The setting of the specified axis in degrees against which measurements of the reference beam center and reference detector distance should be made. In general, this will agree with _diffrn_scan_frame_axis.reference_angle. If the individual frame values vary, then the value of _diffrn_scan_axis.reference_angle will be representative of the ensemble of values of _diffrn_scan_frame_axis.reference_angle (e.g. the mean). If not specified, the value defaults to zero. ; _item.name '_diffrn_scan_axis.reference_angle' _item.category_id diffrn_scan_axis _item.mandatory_code implicit _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.reference_displacement _item_description.description ; The setting of the specified axis in millimetres against which measurements of the reference beam center and reference detector distance should be made. In general, this will agree with _diffrn_scan_frame_axis.reference_displacement. If the individual frame values vary, then the value of _diffrn_scan_axis.reference_displacement will be representative of the ensemble of values of _diffrn_scan_frame_axis.reference_displacement (e.g. the mean). If not specified, the value defaults to to the value of _diffrn_scan_axis.displacement. ; _item.name '_diffrn_scan_axis.reference_displacement' _item.category_id diffrn_scan_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.variant _item_description.description ; The value of _diffrn_scan_axis.variant gives the variant to which the given diffrn_scan_axis row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_scan_axis.variant' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_type.code code save_ ##################### # DIFFRN_SCAN_FRAME # ##################### save_DIFFRN_SCAN_FRAME _category.description ; Data items in the DIFFRN_SCAN_FRAME category describe the relationships of particular frames to scans. ; _category.id diffrn_scan_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame.scan_id' '_diffrn_scan_frame.frame_id' '_diffrn_scan_frame.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame.date _item_description.description ; The date and time of the start of the frame being scanned. ; _item.name '_diffrn_scan_frame.date' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan_frame.frame_id _item_description.description ; The value of this data item is the identifier of the frame being examined. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame.frame_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame.frame_number _item_description.description ; The value of this data item is the number of the frame within the scan, starting with 1. It is not necessarily the same as the value of _diffrn_scan_frame.frame_id, but it may be. ; _item.name '_diffrn_scan_frame.frame_number' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 0 0 0 save_ save__diffrn_scan_frame.integration_time _item_description.description ; The time in seconds to integrate this step of the scan. This should be the precise time of integration of each particular frame. The value of this data item should be given explicitly for each frame and not inferred from the value of _diffrn_scan.integration_time. ; _item.name '_diffrn_scan_frame.integration_time' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame.scan_id _item_description.description ; The value of _diffrn_scan_frame.scan_id identifies the scan containing this frame. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_frame.scan_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame.time_period _item_description.description ; The time in seconds between the start of this frame and the start of the next frame, if any. If there is no next frame, a null value should be given. ; _item.name '_diffrn_scan_frame.time_period' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame.time_rstrt_incr _item_description.description ; The time in seconds between the end of integration of this step of the scan and the start of integration of the next step. The sum of the values of _diffrn_scan_frame.integration_time and _diffrn_scan_frame.time_rstrt_incr is the time from the start of integration of one frame and the start of integration for the next frame and should equal the value of _diffrn_scan_frame.time_period for this frame. The value of _diffrn_scan.time_rstrt_incr will be representative of the ensemble of values of _diffrn_scan_frame_axis.time_rstrt_incr (e.g. the mean). If there is no next frame, a null value should be given. ; _item.name '_diffrn_scan.time_period' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame.variant _item_description.description ; The value of _diffrn_scan_frame.variant gives the variant to which the given diffrn_scan_frame row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_scan_frame.variant' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code code save_ ########################## # DIFFRN_SCAN_FRAME_AXIS # ########################## save_DIFFRN_SCAN_FRAME_AXIS _category.description ; Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the settings of axes for particular frames. Unspecified axes are assumed to be at their zero points. If, for any given frame, nonzero values apply for any of the data items in this category, those values should be given explicitly in this category and not simply inferred from values in DIFFRN_SCAN_AXIS. ; _category.id diffrn_scan_frame_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame_axis.frame_id' '_diffrn_scan_frame_axis.axis_id' '_diffrn_scan_frame_axis.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the frame for which settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_frame_axis.axis_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_axis.angle _item_description.description ; The setting of the specified axis in degrees for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.angle' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_increment _item_description.description ; The increment for this frame for the angular setting of the specified axis in degrees. The sum of the values of _diffrn_scan_frame_axis.angle and _diffrn_scan_frame_axis.angle_increment is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.angle_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_rstrt_incr _item_description.description ; The increment after this frame for the angular setting of the specified axis in degrees. The sum of the values of _diffrn_scan_frame_axis.angle, _diffrn_scan_frame_axis.angle_increment and _diffrn_scan_frame_axis.angle_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame and should equal _diffrn_scan_frame_axis.angle for this next frame. ; _item.name '_diffrn_scan_frame_axis.angle_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.displacement' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_increment _item_description.description ; The increment for this frame for the displacement setting of the specified axis in millimetres. The sum of the values of _diffrn_scan_frame_axis.displacement and _diffrn_scan_frame_axis.displacement_increment is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.displacement_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_rstrt_incr _item_description.description ; The increment for this frame for the displacement setting of the specified axis in millimetres. The sum of the values of _diffrn_scan_frame_axis.displacement, _diffrn_scan_frame_axis.displacement_increment and _diffrn_scan_frame_axis.displacement_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame and should equal _diffrn_scan_frame_axis.displacement for this next frame. ; _item.name '_diffrn_scan_frame_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.frame_id _item_description.description ; The value of this data item is the identifier of the frame for which axis settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame_axis.frame_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_axis.reference_angle _item_description.description ; The setting of the specified axis in degrees against which measurements of the reference beam center and reference detector distance should be made. This is normally the same for all frames, but the option is provided here of making changes when needed. If not provided, it is assumed to be zero. ; _item.name '_diffrn_scan_frame_axis.reference_angle' _item.category_id diffrn_scan_frame_axis _item.mandatory_code implicit _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.reference_displacement _item_description.description ; The setting of the specified axis in millimetres for this frame against which measurements of the reference beam center and reference detector distance should be made. This is normally the same for all frames, but the option is provided here of making changes when needed. If not provided, it is assumed to be equal to _diffrn_scan_frame_axis.displacement. ; _item.name '_diffrn_scan_frame_axis.reference_displacement' _item.category_id diffrn_scan_frame_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.variant _item_description.description ; The value of _diffrn_scan_frame_axis.variant gives the variant to which the given diffrn_scan_frame_axis row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_scan_frame_axis.variant' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_type.code code save_ ############################# # DIFFRN_SCAN_FRAME_MONITOR # ############################# save_DIFFRN_SCAN_FRAME_MONITOR _category.description ; Data items in the DIFFRN_SCAN_FRAME_MONITOR category record the values and details about each monitor for each frame of data during a scan. Each monitor value is uniquely identified by the combination of the scan_id given by _diffrn_scan_frame.scan_id the frame_id given by _diffrn_scan_frame_monitor.frame_id, the monitor's detector_id given by _diffrn_scan_frame_monitor.monitor_id, and a 1-based ordinal given by _diffrn_scan_frame_monitor.id. If there is only one frame for the scan, the value of _diffrn_scan_frame_monitor.frame_id may be omitted. A single frame may have more than one monitor value, and each monitor value may be the result of integration over the entire frame integration time given by the value of _diffrn_scan_frame.integration_time or many monitor values may be reported over shorter times given by the value of _diffrn_scan_frame_monitor.integration_time. If only one monitor value for a given monitor is collected during the integration time of the frame, the value of _diffrn_scan_frame_monitor.id may be omitted. ; _category.id diffrn_data_frame_monitor _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame_monitor.id' '_diffrn_scan_frame_monitor.detector_id' '_diffrn_scan_frame_monitor.scan_id' '_diffrn_data_frame_monitor.frame_id' '_diffrn_data_frame_monitor.variant' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - The beam intensity for frame FRAME1 is being tracked by a beamstop monitor detector BSM01, made from metal foil and a PIN diode, locate 20 mm in front of a MAR345 detector and being sampled every 2 seconds in a 20 second scan. ; ; # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 P6MB BSM01 'metal foil and PIN diode' 1 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH BSM01 MONITOR_Z # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 MONITOR_Z 0.0 0.0 0.0 -220.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_MONITOR loop_ _diffrn_scan_frame_monitor.id _diffrn_scan_frame_monitor.detector_id _diffrn_scan_frame_monitor.scan_id _diffrn_data_frame_monitor.frame_id _diffrn_data_frame_monitor.integration_time _diffrn_data_frame_monitor.monitor_value 1 BSM01 SCAN1 FRAME1 2.0 23838345642 2 BSM01 SCAN1 FRAME1 2.0 23843170669 3 BSM01 SCAN1 FRAME1 2.0 23839478690 4 BSM01 SCAN1 FRAME1 2.0 23856642085 5 BSM01 SCAN1 FRAME1 2.0 23781717656 6 BSM01 SCAN1 FRAME1 2.0 23788850775 7 BSM01 SCAN1 FRAME1 2.0 23815576677 8 BSM01 SCAN1 FRAME1 2.0 23789299964 9 BSM01 SCAN1 FRAME1 2.0 23830195536 10 BSM01 SCAN1 FRAME1 2.0 23673082270 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 FRAME1 MONITOR_Z 0.0 -220.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 172.43 -172.43 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 MONITOR_Z translation detector . 0 0 1 0 0 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_scan_frame_monitor.id _item_description.description ; This item is an integer identifier which, along with _diffrn_scan_frame_monitor.detector_id, _diffrn_scan_frame_monitor.scan_id, and _diffrn_data_frame_monitor.frame_id should uniquely identify the monitor value being recorded If _array_data.binary_id is not explicitly given, it defaults to 1. ; loop_ _item.name '_diffrn_scan_frame_monitor.id' _item.category_id diffrn_scan_frame_monitor _item.mandatory_code implicit _item_default.value 1 _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__diffrn_scan_frame_monitor.detector_id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. ; _item.name '_diffrn_scan_frame_monitor.detector_id' _item.category_id diffrn_scan_frame_monitor _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_monitor.frame_id _item_description.description ; This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame_monitor.frame_id' _item.category_id diffrn_scan_frame_monitor _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_monitor.integration_time _item_description.description ; The precise time for integration of the monitor value given in _diffrn_scan_frame_monitor.value must be given in _diffrn_scan_frame_monitor.integration_time. ; _item.name '_diffrn_scan_frame_monitor.integration_time' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame_monitor.value _item_description.description ; The value reported by the monitor detector should be given in _diffrn_scan_frame_monitor.value. The value is typed as float to allow of monitors for very intense beams that cannot report all digits, but when available, all digits of the monitor should be recorded. ; _item.name '_diffrn_scan_frame_monitor.value' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame_monitor.variant _item_description.description ; The value of _diffrn_scan_frame_monitor.variant gives the variant to which the given diffrn_scan_frame_monitor row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_diffrn_scan_frame_monitor.variant' _item.category_id diffrn_scan_frame_monitor _item.mandatory_code no _item_type.code code save_ ####### # MAP # ####### save_MAP _category.description ; Data items in the MAP category record the details of a maps. Maps record values of parameters, such as density, that are functions of position within a cell or are functions of orthogonal coordinates in three space. A map may is composed of one or more map segments specified in the MAP_SEGMENT category. Examples are given in the MAP_SEGMENT category. ; _category.id map _category.mandatory_code no loop_ _category_key.name '_map.id' '_map.diffrn_id' '_map.entry_id' '_map.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' 'map_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Identifying an observed density map and a calculated density map ; ; loop_ _map.id _map.details rho_calc ; density calculated from F_calc derived from the ATOM_SITE list ; rho_obs ; density combining the observed structure factors with the calculated phases ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__map.details _item_description.description ; The value of _map.details should give a description of special aspects of each map. ; _item.name '_map.details' _item.category_id map _item.mandatory_code no _item_type.code text loop_ _item_examples.case _item_examples.detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Identifying an observed density map and a calculated density map ; ; loop_ _map.id _map.details rho_calc ; density calculated from F_calc derived from the ATOM_SITE list ; rho_obs ; density combining the observed structure factors with the calculated phases ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__map.diffrn_id _item_description.description ; This item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_map.diffrn_id' _item.category_id map _item.mandatory_code implicit _item_type.code code save_ save__map.entry_id _item_description.description ; This item is a pointer to _entry.id in the ENTRY category. ; _item.name '_map.entry_id' _item.category_id map _item.mandatory_code implicit _item_type.code code save_ save__map.id _item_description.description ; The value of _map.id must uniquely identify each map for the given diffrn.id or entry.id. ; loop_ _item.name _item.category_id _item.mandatory_code '_map.id' map yes '_map_segment.id' map_segment yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_map_segment.id' '_map.id' save_ save__map.variant _item_description.description ; The value of _map.variant gives the variant to which the given map row is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_map.variant' _item.category_id map _item.mandatory_code no _item_type.code code save_ ############### # MAP_SEGMENT # ############### save_MAP_SEGMENT _category.description ; Data items in the MAP_SEGMENT category record the details about each segment (section or brick) of a map. ; _category.id map_segment _category.mandatory_code no loop_ _category_key.name '_map_segment.id' '_map_segment.map_id' '_map_segment.variant' loop_ _category_group.id 'inclusive_group' 'array_data_group' 'map_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Identifying an observed density map and a calculated density map, each consisting of one segment, both using the same array structure and mask. ; ; loop_ _map.id _map.details rho_calc ; density calculated from F_calc derived from the ATOM_SITE list ; rho_obs ; density combining the observed structure factors with the calculated phases ; loop_ _map_segment.map_id _map_segment.id _map_segment.array_id _map_segment.binary_id _map_segment.mask_array_id _map_segment.mask_binary_id rho_calc rho_calc map_structure 1 mask_structure 1 rho_obs rho_obs map_structure 2 mask_structure 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__map_segment.array_id _item_description.description ; The value of _map_segment.array_id identifies the array structure into which the map is organized. This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_map_segment.array_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code code save_ save__map_segment.binary_id _item_description.description ; The value of _map_segment.binary_id distinguishes the particular set of data organized according to _map_segment.array_id in which the data values of the map are stored. This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_map_segment.binary_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code int save_ save__map_segment.mask_array_id _item_description.description ; The value of _map_segment.mask_array_id, if given, the array structure into which the mask for the map is organized. If no value is given, then all elements of the map are valid. If a value is given, then only elements of the map for which the corresponding element of the mask is non-zero are valid. The value of _map_segment.mask_array_id differs from the value of _map_segment.array_id in order to permit the mask to be given as, say, unsigned 8-bit integers, while the map is given as a data type with more range. However, the two array structures must be aligned, using the same axes in the same order with the same displacements and increments This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_map_segment.mask_array_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code code save_ save__map_segment.mask_binary_id _item_description.description ; The value of _map_segment.mask_binary_id identifies the particular set of data organized according to _map_segment.mask_array_id specifying the mask for the map. This item is a pointer to _array_data.mask_binary_id in the ARRAY_DATA category. ; _item.name '_map_segment.mask_binary_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code int save_ save__map_segment.id _item_description.description ; The value of _map_segment.id must uniquely identify each segment of a map. ; loop_ _item.name _item.category_id _item.mandatory_code '_map_segment.id' map_segment yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_map_data_frame.map_segment_id' '_map_segment.id' save_ save__map_segment.map_id _item_description.description ; This item is a pointer to _map.id in the MAP category. ; _item.name '_map_segment.map_id' _item.category_id map_segment _item.mandatory_code yes _item_type.code code save_ save__map_segment.details _item_description.description ; The value of _map_segment.details should give a description of special aspects of each segment of a map. ; _item.name '_map_segment.details' _item.category_id map_segment _item.mandatory_code no _item_type.code text loop_ _item_examples.case _item_examples.detail ; Example to be provided ; ; ; save_ save__map_segment.variant _item_description.description ; The value of _map_segment.variant gives the variant to which the given map segment is related. If this value is not given, the variant is assumed to the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_map_segment.variant' _item.category_id map_segment _item.mandatory_code no _item_type.code code save_ ########### # VARIANT # ########### save_VARIANT _category.description ; Data items in the VARIANT category record the details about sets of variants of data items. There is sometimes a need to allow for multiple versions of the same data items in order to allow for refinements and corrections to earlier assumptions, observations and calculations. In order to allow data sets to contain more than one variant of the same information, an optional ...variant data item as a pointer to _variant.variant has been added to the key of every category, as an implicit data item with a null (empty) default value. All rows in a category with the same variant value are considered to be related to one another and to all rows in other categories with the same variant value. For a given variant, all such rows are also considered to be related to all rows with a null variant value, except that a row with a null variant value is for which all other components of its key are identical to those entries in another row with a non-null variant value is not related the the rows with that non-null variant value. This behavior is similar to the convention for identifying alternate conformers in an atom list. An optional role may be specified for a variant as the value of _variant.role. Possible roles are null, "preferred", "raw data", "unsuccessful trial". Variants may carry an optional timestamp as the value of _variant.timestamp. Variants may be related to other variants from which they were derived by the value of _variant.variant_of Further details about the variant may be specified as the value of _variant.details. In order to allow variant information from multiple datasets to be combined, _variant.diffrn_id and/or _variant.entry_id may be used. ; _category.id variant _category.mandatory_code no loop_ _category_key.name '_variant.variant' '_variant.diffrn_id' '_variant.entry_id' loop_ _category_group.id 'inclusive_group' 'variant_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Distinguishing between a raw beam center and a refined beam center inferred after indexing. Detector d1 is composed of four CCD detector elements, each 200 mm by 200 mm, arranged in a square, in the pattern 1 2 * 3 4 Note that the beam centre is slightly displaced from each of the detector elements, just beyond the lower right corner of 1, the lower left corner of 2, the upper right corner of 3 and the upper left corner of 4. For each element, the detector face coordiate system, is assumed to have the fast axis running from left to right and the slow axis running from top to bottom with the origin at the top left corner. After indexing and refinement, the center is shifted by .2 mm left and .1 mm down. ; ; loop_ _variant.variant _variant.role _variant.timestamp _variant.variant_of _variant.details . "raw data" 2007-08-03T23:20:00 . . indexed "preferred" 2007-08-04T01:17:28 . "indexed cell and refined beam center" loop_ _diffrn_detector_element.detector_id _diffrn_detector_element.id _diffrn_detector_element.reference_center_fast _diffrn_detector_element.reference_center_slow _diffrn_detector_element.reference_center_units _diffrn_detector_element.variant d1 d1_ccd_1 201.5 201.5 mm . d1 d1_ccd_2 -1.8 201.5 mm . d1 d1_ccd_3 201.6 -1.4 mm . d1 d1_ccd_4 -1.7 -1.5 mm . d1 d1_ccd_1 201.3 201.6 mm indexed d1 d1_ccd_2 -2.0 201.6 mm indexed d1 d1_ccd_3 201.3 -1.5 mm indexed d1 d1_ccd_4 -1.9 -1.6 mm indexed ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__variant.details _item_description.description ; A description of special aspects of the variant. ; _item.name '_variant.details' _item.category_id variant _item.mandatory_code no _item_type.code text _item_examples.case ; indexed cell and refined beam center ; save_ save__variant.role _item_description.description ; The value of _variant.role specified a role for this variant. Possible roles are null, "preferred", "raw data", and "unsuccessful trial". ; _item.name '_variant.role' _item.category_id variant _item.mandatory_code no _item_type.code uline loop_ _item_enumeration.value _item_enumeration.detail . ; A null value for _variant.role leaves the precise role of the variant unspecified. No inference should be made that the variant with the latest time stamp is preferred. ; "preferred" ; A value of "preferred" indicates that rows of any categories specifying this variant should be used in preference to rows with the same key specifying other variants or the null variant. It is an error to specify two variants that appear in the same category with the same key as being preferred, but it is not an error to specify more than one variant as preferred in other cases. ; "raw data" ; A value of "raw data" indicates data prior to any corrections, calculations or refinements. It is not necessarily an error for raw data to also be a variant of an earlier variant. It may be replacement raw data for earlier data believed to be erroneous. ; "unsuccessful trial" ; A value of "unsuccessful trial" indicates data that should not be used for further calculation. ; save_ save__variant.timestamp _item_description.description ; The date and time identifying a variant. This is not necessarily the precise time of the measurement or calculation of the individual related data items, but a timestamp that reflects the order in which the variants were defined. ; _item.name '_variant.timestamp' _item.category_id variant _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__variant.variant _item_description.description ; The value of _variant.variant must uniquely identify each variant for the given diffraction experiment and/or entry This item has been made implicit and given a default value of null. ; loop_ _item.name _item.category_id _item.mandatory_code '_variant.variant' variant implicit '_variant.variant_of' variant implicit '_array_data.variant' array_data implicit '_array_element_size.variant' array_element_size implicit '_array_intensities.variant' array_intensities implicit '_array_structure.variant' array_structure implicit '_array_structure_list.variant' array_structure_list implicit '_array_structure_list_axis.variant' array_structure_list_axis implicit '_axis.variant' axis implicit '_diffrn_data_frame.variant' diffrn_data_frame implicit '_diffrn_detector.variant' diffrn_detector implicit '_diffrn_detector_axis.variant' diffrn_detector_axis implicit '_diffrn_detector_element.variant' diffrn_detector_element implicit '_diffrn_measurement.variant' diffrn_measurement implicit '_diffrn_measurement_axis.variant' diffrn_measurement_axis implicit '_diffrn_radiation.variant' diffrn_radiation implicit '_diffrn_refln.variant' diffrn_refln implicit '_diffrn_scan.variant' diffrn_scan implicit '_diffrn_scan_axis.variant' diffrn_scan_axis implicit '_diffrn_scan_frame.variant' diffrn_scan_frame implicit '_diffrn_scan_frame_axis.variant' diffrn_scan_frame_axis implicit '_diffrn_scan_frame_monitor.variant' diffrn_scan_frame_monitor implicit '_map.variant' map implicit '_map_segment.variant' map_segment implicit _item_default.value . _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_data.variant' '_variant.variant' '_array_data.variant_of' '_variant.variant' '_array_element_size.variant' '_variant.variant' '_array_intensities.variant' '_variant.variant' '_array_structure.variant' '_variant.variant' '_array_structure_list.variant' '_variant.variant' '_array_structure_list_axis.variant' '_variant.variant' '_axis.variant' '_variant.variant' '_diffrn_data_frame.variant' '_variant.variant' '_diffrn_detector.variant' '_variant.variant' '_diffrn_detector_axis.variant' '_variant.variant' '_diffrn_detector_element.variant' '_variant.variant' '_diffrn_measurement.variant' '_variant.variant' '_diffrn_measurement_axis.variant' '_variant.variant' '_diffrn_radiation.variant' '_variant.variant' '_diffrn_refln.variant' '_variant.variant' '_diffrn_scan.variant' '_variant.variant' '_diffrn_scan_axis.variant' '_variant.variant' '_diffrn_scan_frame.variant' '_variant.variant' '_diffrn_scan_frame_axis.variant' '_variant.variant' '_diffrn_scan_frame_monitor.variant' '_variant.variant' '_map.variant' '_variant.variant' '_map_segment.variant' '_variant.variant' save_ save__variant.variant_of _item_description.description ; The value of _variant.variant_of gives the variant from which this variant was derived. If this value is not given, the variant is assumed to be derived from the default null variant. This item is a pointer to _variant.variant in the VARIANT category. ; _item.name '_variant.variant_of' _item.category_id variant _item.mandatory_code no _item_type.code code save_ ######################## DEPRECATED DATA ITEMS ######################## save__diffrn_detector_axis.id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_detector_axis.id' _item.category_id diffrn_detector_axis _item.mandatory_code no _item_type.code code save_ save__diffrn_detector_element.center[1] _item_description.description ; The value of _diffrn_detector_element.center[1] is the X component of the distortion-corrected beam centre in millimetres from the (0, 0) (lower-left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. Because of ambiguity about the setting used to determine this center, use of this data item is deprecated. The data item _diffrn_data_frame.center_fast which is referenced to the detector coordinate system and not directly to the laboratory coordinate system should be used instead. ; _item.name '_diffrn_detector_element.center[1]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.center[2] _item_description.description ; The value of _diffrn_detector_element.center[2] is the Y component of the distortion-corrected beam centre in millimetres from the (0, 0) (lower-left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. Because of ambiguity about the setting used to determine this center, use of this data item is deprecated. The data item _diffrn_data_frame.center_slow which is referenced to the detector coordinate system and not directly to the laboratory coordinate system should be used instead. ; _item.name '_diffrn_detector_element.center[2]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_measurement_axis.id _item_description.description ; This data item is a pointer to _diffrn_measurement.id in the DIFFRN_MEASUREMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_measurement_axis.id' _item.category_id diffrn_measurement_axis _item.mandatory_code no _item_type.code code save_ ######################### DEPRECATED CATEGORY ######################### ##################### # DIFFRN_FRAME_DATA # ##################### save_DIFFRN_FRAME_DATA _category.description ; Data items in the DIFFRN_FRAME_DATA category record the details about each frame of data. The items in this category are now in the DIFFRN_DATA_FRAME category. The items in the DIFFRN_FRAME_DATA category are now deprecated. The items from this category are provided as aliases in the 1.0 dictionary or, in the case of _diffrn_frame_data.details, in the 1.4 dictionary. THESE ITEMS SHOULD NOT BE USED FOR NEW WORK. The items from the old category are provided in this dictionary for completeness but should not be used or cited. To avoid confusion, the example has been removed and the redundant parent-child links to other categories have been removed. All _item.mandatory_code values have been changed to no ; _category.id diffrn_frame_data _category.mandatory_code no loop_ _category_key.name '_diffrn_frame_data.id' '_diffrn_frame_data.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; THE DIFFRN_FRAME_DATA category is deprecated and should not be used. ; ; # EXAMPLE REMOVED # ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_frame_data.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.array_id' _item.category_id diffrn_frame_data _item.mandatory_code no _item_type.code code save_ save__diffrn_frame_data.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.binary_id' _item.category_id diffrn_frame_data _item.mandatory_code no _item_type.code int save_ save__diffrn_frame_data.detector_element_id _item_description.description ; This item is a pointer to _diffrn_detector_element.id in the DIFFRN_DETECTOR_ELEMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.detector_element_id' _item.category_id diffrn_frame_data _item.mandatory_code no _item_type.code code save_ save__diffrn_frame_data.id _item_description.description ; The value of _diffrn_frame_data.id must uniquely identify each complete frame of data. DEPRECATED -- DO NOT USE ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_frame_data.id' diffrn_frame_data yes _item_type.code code save_ save__diffrn_frame_data.details _item_description.description ; The value of _diffrn_data_frame.details should give a description of special aspects of each frame of data. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.details' _item.category_id diffrn_frame_data _item.mandatory_code no _item_type.code text save_ ################ END DEPRECATED SECTION ########### #################### ## ITEM_TYPE_LIST ## #################### # # # The regular expressions defined here are not compliant # with the POSIX 1003.2 standard as they include the # '\n' and '\t' special characters. These regular expressions # have been tested using version 0.12 of Richard Stallman's # GNU regular expression library in POSIX mode. # In order to allow presentation of a regular expression # in a text field concatenate any line ending in a backslash # with the following line, after discarding the backslash. # # A formal definition of the '\n' and '\t' special characters # is most properly done in the DDL, but for completeness, please # note that '\n' is the line termination character ('newline') # and '\t' is the horizontal tab character. There is a formal # ambiguity in the use of '\n' for line termination, in that # the intention is that the equivalent machine/OS-dependent line # termination character sequence should be accepted as a match, e.g. # # '\r' (control-M) under MacOS # '\n' (control-J) under Unix # '\r\n' (control-M control-J) under DOS and MS Windows # loop_ _item_type_list.code _item_type_list.primitive_code _item_type_list.construct _item_type_list.detail code char '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words ... ; ucode uchar '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words (case insensitive) ... ; line char '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; char item types / multi-word items ... ; uline uchar '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; char item types / multi-word items (case insensitive)... ; text char '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; text item types / multi-line text ... ; binary char ;\n--CIF-BINARY-FORMAT-SECTION--\n\ [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\ \n--CIF-BINARY-FORMAT-SECTION---- ; ; binary items are presented as MIME-like ascii-encoded sections in an imgCIF. In a CBF, raw octet streams are used to convey the same information. ; int numb '-?[0-9]+' ; int item types are the subset of numbers that are the negative or positive integers. ; float numb '-?(([0-9]+)[.]?|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?' ; float item types are the subset of numbers that are the floating point numbers. ; any char '.*' ; A catch all for items that may take any form... ; yyyy-mm-dd char ;\ [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9]?[0-9]\ ((T[0-2][0-9](:[0-5][0-9](:[0-5][0-9](.[0-9]+)?)?)?)?\ ([+-][0-5][0-9]:[0-5][0-9]))? ; ; Standard format for CIF date and time strings (see http://www.iucr.org/iucr-top/cif/spec/datetime.html), consisting of a yyyy-mm-dd date optionally followed by the character 'T' followed by a 24-hour clock time, optionally followed by a signed time-zone offset. The IUCr standard has been extended to allow for an optional decimal fraction on the seconds of time. Time is local time if no time-zone offset is given. Note that this type extends the mmCIF yyyy-mm-dd type but does not conform to the mmCIF yyyy-mm-dd:hh:mm type that uses a ':' in place if the 'T' specified by the IUCr standard. For reading, both forms should be accepted, but for writing, only the IUCr form should be used. For maximal compatibility, the special time zone indicator 'Z' (for 'zulu') should be accepted on reading in place of '+00:00' for GMT. ; ##################### ## ITEM_UNITS_LIST ## ##################### loop_ _item_units_list.code _item_units_list.detail # 'metres' 'metres' 'centimetres' 'centimetres (metres * 10^( -2)^)' 'millimetres' 'millimetres (metres * 10^( -3)^)' 'nanometres' 'nanometres (metres * 10^( -9)^)' 'angstroms' '\%Angstroms (metres * 10^(-10)^)' 'picometres' 'picometres (metres * 10^(-12)^)' 'femtometres' 'femtometres (metres * 10^(-15)^)' # 'reciprocal_metres' 'reciprocal metres (metres^(-1)^)' 'reciprocal_centimetres' 'reciprocal centimetres ((metres * 10^( -2)^)^(-1)^)' 'reciprocal_millimetres' 'reciprocal millimetres ((metres * 10^( -3)^)^(-1)^)' 'reciprocal_nanometres' 'reciprocal nanometres ((metres * 10^( -9)^)^(-1)^)' 'reciprocal_angstroms' 'reciprocal \%Angstroms ((metres * 10^(-10)^)^(-1)^)' 'reciprocal_picometres' 'reciprocal picometres ((metres * 10^(-12)^)^(-1)^)' # 'nanometres_squared' 'nanometres squared (metres * 10^( -9)^)^2^' 'angstroms_squared' '\%Angstroms squared (metres * 10^(-10)^)^2^' '8pi2_angstroms_squared' '8\p^2^ * \%Angstroms squared (metres * 10^(-10)^)^2^' 'picometres_squared' 'picometres squared (metres * 10^(-12)^)^2^' # 'nanometres_cubed' 'nanometres cubed (metres * 10^( -9)^)^3^' 'angstroms_cubed' '\%Angstroms cubed (metres * 10^(-10)^)^3^' 'picometres_cubed' 'picometres cubed (metres * 10^(-12)^)^3^' # 'kilopascals' 'kilopascals' 'gigapascals' 'gigapascals' # 'hours' 'hours' 'minutes' 'minutes' 'seconds' 'seconds' 'microseconds' 'microseconds' # 'degrees' 'degrees (of arc)' 'degrees_squared' 'degrees (of arc) squared' # 'degrees_per_minute' 'degrees (of arc) per minute' # 'celsius' 'degrees (of temperature) Celsius' 'kelvins' 'degrees (of temperature) Kelvin' # 'counts' 'counts' 'counts_per_photon' 'counts per photon' # 'electrons' 'electrons' # 'electrons_squared' 'electrons squared' # 'electrons_per_nanometres_cubed' ; electrons per nanometres cubed (electrons/(metres * 10^( -9)^)^(-3)^) ; 'electrons_per_angstroms_cubed' ; electrons per \%Angstroms cubed (electrons/(metres * 10^(-10)^)^(-3)^) ; 'electrons_per_picometres_cubed' ; electrons per picometres cubed (electrons/(metres * 10^(-12)^)^(-3)^) ; 'kilowatts' 'kilowatts' 'milliamperes' 'milliamperes' 'kilovolts' 'kilovolts' # 'pixels_per_element' '(image) pixels per (array) element' # 'arbitrary' ; arbitrary system of units. ; # loop_ _item_units_conversion.from_code _item_units_conversion.to_code _item_units_conversion.operator _item_units_conversion.factor ### 'metres' 'centimetres' '*' 1.0E+02 'metres' 'millimetres' '*' 1.0E+03 'metres' 'nanometres' '*' 1.0E+09 'metres' 'angstroms' '*' 1.0E+10 'metres' 'picometres' '*' 1.0E+12 'metres' 'femtometres' '*' 1.0E+15 # 'centimetres' 'metres' '*' 1.0E-02 'centimetres' 'millimetres' '*' 1.0E+01 'centimetres' 'nanometres' '*' 1.0E+07 'centimetres' 'angstroms' '*' 1.0E+08 'centimetres' 'picometres' '*' 1.0E+10 'centimetres' 'femtometres' '*' 1.0E+13 # 'millimetres' 'metres' '*' 1.0E-03 'millimetres' 'centimetres' '*' 1.0E-01 'millimetres' 'nanometres' '*' 1.0E+06 'millimetres' 'angstroms' '*' 1.0E+07 'millimetres' 'picometres' '*' 1.0E+09 'millimetres' 'femtometres' '*' 1.0E+12 # 'nanometres' 'metres' '*' 1.0E-09 'nanometres' 'centimetres' '*' 1.0E-07 'nanometres' 'millimetres' '*' 1.0E-06 'nanometres' 'angstroms' '*' 1.0E+01 'nanometres' 'picometres' '*' 1.0E+03 'nanometres' 'femtometres' '*' 1.0E+06 # 'angstroms' 'metres' '*' 1.0E-10 'angstroms' 'centimetres' '*' 1.0E-08 'angstroms' 'millimetres' '*' 1.0E-07 'angstroms' 'nanometres' '*' 1.0E-01 'angstroms' 'picometres' '*' 1.0E+02 'angstroms' 'femtometres' '*' 1.0E+05 # 'picometres' 'metres' '*' 1.0E-12 'picometres' 'centimetres' '*' 1.0E-10 'picometres' 'millimetres' '*' 1.0E-09 'picometres' 'nanometres' '*' 1.0E-03 'picometres' 'angstroms' '*' 1.0E-02 'picometres' 'femtometres' '*' 1.0E+03 # 'femtometres' 'metres' '*' 1.0E-15 'femtometres' 'centimetres' '*' 1.0E-13 'femtometres' 'millimetres' '*' 1.0E-12 'femtometres' 'nanometres' '*' 1.0E-06 'femtometres' 'angstroms' '*' 1.0E-05 'femtometres' 'picometres' '*' 1.0E-03 ### 'reciprocal_centimetres' 'reciprocal_metres' '*' 1.0E+02 'reciprocal_centimetres' 'reciprocal_millimetres' '*' 1.0E-01 'reciprocal_centimetres' 'reciprocal_nanometres' '*' 1.0E-07 'reciprocal_centimetres' 'reciprocal_angstroms' '*' 1.0E-08 'reciprocal_centimetres' 'reciprocal_picometres' '*' 1.0E-10 # 'reciprocal_millimetres' 'reciprocal_metres' '*' 1.0E+03 'reciprocal_millimetres' 'reciprocal_centimetres' '*' 1.0E+01 'reciprocal_millimetres' 'reciprocal_nanometres' '*' 1.0E-06 'reciprocal_millimetres' 'reciprocal_angstroms' '*' 1.0E-07 'reciprocal_millimetres' 'reciprocal_picometres' '*' 1.0E-09 # 'reciprocal_nanometres' 'reciprocal_metres' '*' 1.0E+09 'reciprocal_nanometres' 'reciprocal_centimetres' '*' 1.0E+07 'reciprocal_nanometres' 'reciprocal_millimetres' '*' 1.0E+06 'reciprocal_nanometres' 'reciprocal_angstroms' '*' 1.0E-01 'reciprocal_nanometres' 'reciprocal_picometres' '*' 1.0E-03 # 'reciprocal_angstroms' 'reciprocal_metres' '*' 1.0E+10 'reciprocal_angstroms' 'reciprocal_centimetres' '*' 1.0E+08 'reciprocal_angstroms' 'reciprocal_millimetres' '*' 1.0E+07 'reciprocal_angstroms' 'reciprocal_nanometres' '*' 1.0E+01 'reciprocal_angstroms' 'reciprocal_picometres' '*' 1.0E-02 # 'reciprocal_picometres' 'reciprocal_metres' '*' 1.0E+12 'reciprocal_picometres' 'reciprocal_centimetres' '*' 1.0E+10 'reciprocal_picometres' 'reciprocal_millimetres' '*' 1.0E+09 'reciprocal_picometres' 'reciprocal_nanometres' '*' 1.0E+03 'reciprocal_picometres' 'reciprocal_angstroms' '*' 1.0E+01 ### 'nanometres_squared' 'angstroms_squared' '*' 1.0E+02 'nanometres_squared' 'picometres_squared' '*' 1.0E+06 # 'angstroms_squared' 'nanometres_squared' '*' 1.0E-02 'angstroms_squared' 'picometres_squared' '*' 1.0E+04 'angstroms_squared' '8pi2_angstroms_squared' '*' 78.9568 # 'picometres_squared' 'nanometres_squared' '*' 1.0E-06 'picometres_squared' 'angstroms_squared' '*' 1.0E-04 ### 'nanometres_cubed' 'angstroms_cubed' '*' 1.0E+03 'nanometres_cubed' 'picometres_cubed' '*' 1.0E+09 # 'angstroms_cubed' 'nanometres_cubed' '*' 1.0E-03 'angstroms_cubed' 'picometres_cubed' '*' 1.0E+06 # 'picometres_cubed' 'nanometres_cubed' '*' 1.0E-09 'picometres_cubed' 'angstroms_cubed' '*' 1.0E-06 ### 'kilopascals' 'gigapascals' '*' 1.0E-06 'gigapascals' 'kilopascals' '*' 1.0E+06 ### 'hours' 'minutes' '*' 6.0E+01 'hours' 'seconds' '*' 3.6E+03 'hours' 'microseconds' '*' 3.6E+09 # 'minutes' 'hours' '/' 6.0E+01 'minutes' 'seconds' '*' 6.0E+01 'minutes' 'microseconds' '*' 6.0E+07 # 'seconds' 'hours' '/' 3.6E+03 'seconds' 'minutes' '/' 6.0E+01 'seconds' 'microseconds' '*' 1.0E+06 # 'microseconds' 'hours' '/' 3.6E+09 'microseconds' 'minutes' '/' 6.0E+07 'microseconds' 'seconds' '/' 1.0E+06 ### 'celsius' 'kelvins' '-' 273.0 'kelvins' 'celsius' '+' 273.0 ### 'electrons_per_nanometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E+03 'electrons_per_nanometres_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+09 # 'electrons_per_angstroms_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-03 'electrons_per_angstroms_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+06 # 'electrons_per_picometres_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-09 'electrons_per_picometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E-06 ### ######################## ## DICTIONARY_HISTORY ## ######################## loop_ _dictionary_history.version _dictionary_history.update _dictionary_history.revision 1.6.4 2011-07-02 ; Corrections to support DLS Dectris header as per G. Winter (HJB) + Define new tags _diffrn_scan.time_period, _diffrn_scan.time_rstrt_incr, _diffrn_scan_frame.time_period, _diffrn_scan_frame.time_rstrt_incr + fix bad category name in loop in _diffrn_detector.id + remove stray text field terminator at line 4642 + fix unquoted tag as a value in _diffrn_scan_frame_monitor.id + make formerly mandatory and implicit deprecated items non-mandatory ; 1.6.3 2010-08-26 ; Cummulative corrections from 1.6.0, 1, 2 drafts (HJB) + Move descriptive dictionary comments into _datablock.description with catgeory tree described + add default _array_data.array_id value of 1 + add option of CBF_BACKGROUND_OFFSET_DELTA compression + add VARIANT catgeory and tags + add DIFFRN_SCAN_FRAME_MONITOR category ; 1.5.4 2007-07-28 ; Typographics corrections (HJB) + Corrected embedded degree characters to \% + Corrected embedded Aring to \%A + Added trailing ^ for a power + Removed 2 cases of a space after an underscore in tag name. ; 1.5.3 2007-07-08 ; Changes to support SLS miniCBF and suggestions from the 24 May 07 BNL imgCIF workshop (HJB) + Added new data items '_array_data.header_contents', '_array_data.header_convention', '_diffrn_data_frame.center_fast', '_diffrn_data_frame.center_slow', '_diffrn_data_frame.center_units', '_diffrn_measurement.sample_detector_distance', '_diffrn_measurement.sample_detector_voffset + Deprecated data items '_diffrn_detector_element.center[1]', '_diffrn_detector_element.center[2]' + Added comments and example on miniCBF + Changed all array_id data items to implicit ; 1.5.2 2007-05-06 ; Further clarifications of the coordinate system. (HJB) ; 1.5.1 2007-04-26 ; Improve defintion of X-axis to cover the case of no goniometer and clean up more line folds (HJB) ; 1.5 2007-07-25 ; This is a cummulative list of the changes proposed since the imgCIF workshop in Hawaii in July 2006. It is the result of contributions by H. J. Bernstein, A. Hammersley, J. Wright and W. Kabsch. 2007-02-19 Consolidated changes (edited by HJB) + Added new data items '_array_structure.compression_type_flag', '_array_structure_list_axis.fract_displacement', '_array_structure_list_axis.displacement_increment', '_array_structure_list_axis.reference_angle', '_array_structure_list_axis.reference_displacement', '_axis.system', '_diffrn_detector_element.reference_center_fast', '_diffrn_detector_element.reference_center_slow', '_diffrn_scan_axis.reference_angle', '_diffrn_scan_axis.reference_displacement', '_map.details', '_map.diffrn_id', '_map.entry_id', '_map.id', '_map_segment.array_id', '_map_segment.binary_id', '_map_segment.mask_array_id', '_map_segment.mask_binary_id', '_map_segment.id', '_map_segment.map_id', '_map_segment.details. + Change type of '_array_structure.byte_order' and '_array_structure.compression_type' to ucode to make these values case-insensitive + Add values 'packed_v2' and 'byte_offset' to enumeration of values for '_array_structure.compression_type' + Add to definitions for the binary data type to handle new compression types, maps, and a variety of new axis types. 2007-07-25 Cleanup of typos for formal release (HJB) + Corrected text fields for reference_ tag descriptions that were off by one column + Fix typos in comments listing fract_ tags + Changed name of release from 1.5_DRAFT to 1.5 + Fix unclosed text fields in various map definitions ; 1.4 2006-07-04 ; This is a change to reintegrate all changes made in the course of publication of ITVG, by the RCSB from April 2005 through August 2008 and changes for the 2006 imgCIF workshop in Hawaii. 2006-07-04 Consolidated changes for the 2006 imgCIF workshop (edited by HJB) + Correct type of '_array_structure_list.direction' from 'int' to 'code'. + Added new data items suggested by CN '_diffrn_data_frame.details' '_array_intensities.pixel_fast_bin_size', '_array_intensities.pixel_slow_bin_size and '_array_intensities.pixel_binning_method + Added deprecated item for completeness '_diffrn_frame_data.details' + Added entry for missing item in contents list '_array_structure_list_axis.displacement' + Added new MIME type X-BASE32K based on work by VL, KM, GD, HJB + Correct description of MIME boundary delimiter to start in column 1. + General cleanup of text fields to conform to changes for ITVG by removing empty lines at start and finish of text field. + Amend example for ARRAY_INTENSITIES to include binning. + Add local copy of type specification (as 'code') for all children of '_diffrn.id'. + For consistency, change all references to 'pi' to '\p' and all references to 'Angstroms' to '\%Angstroms'. + Clean up all powers to use IUCr convention of '^power^', as in '10^3^' for '10**3'. + Update 'yyyy-mm-dd' type regex to allow truncation from the right and improve comments to explain handling of related mmCIF 'yyyy-mm-dd:hh:mm' type, and use of 'Z' for GMT time zone. 2005-03-08 and 2004-08-08 fixed cases where _item_units.code used instead of _item_type.code (JDW) 2004-04-15 fixed item ordering in _diffrn_measurement_axis.measurement_id added sub_category 'vector' (JDW) ; 1.3.2 2005-06-25 ; 2005-06-25 ITEM_TYPE_LIST: code, ucode, line, uline regexps updated to those of current mmCIF; float modified by allowing integers terminated by a point as valid. The 'time' part of yyyy-mm-dd types made optional in the regexp. (BM) 2005-06-17 Minor corrections as for proofs for IT G Chapter 4.6 (NJA) 2005-02-21 Minor corrections to spelling and punctuation (NJA) 2005-01-08 Changes as per Nicola Ashcroft. + Updated example 1 for DIFFRN_MEASUREMENT to agree with mmCIF. + Spelled out "micrometres" for "um" and "millimetres" for "mm". + Removed phrase "which may be stored" from ARRAY_STRUCTURE description. + Removed unused 'byte-offsets' compressions and updated cites to ITVG for '_array_structure.compression_type'. (HJB) ; 1.3.1 2003-08-13 ; Changes as per Frances C. Bernstein. + Identify initials. + Adopt British spelling for centre in text. + Set \p and \%Angstrom and powers. + Clean up commas and unclear wordings. + Clean up tenses in history. Changes as per Gotzon Madariaga. + Fix the ARRAY_DATA example to align '_array_data.binary_id' and X-Binary-ID. + Add a range to '_array_intensities.gain_esd'. + In the example of DIFFRN_DETECTOR_ELEMENT, '_diffrn_detector_element.id' and '_diffrn_detector_element.detector_id' interchanged. + Fix typos for direction, detector and axes. + Clarify description of polarisation. + Clarify axes in '_diffrn_detector_element.center[1]' '_diffrn_detector_element.center[2]'. + Add local item types for items that are pointers. (HJB) ; 1.3.0 2003-07-24 ; Changes as per Brian McMahon. + Consistently quote tags embedded in text. + Clean up introductory comments. + Adjust line lengths to fit in 80 character window. + Fix several descriptions in AXIS category which referred to '_axis.type' instead of the current item. + Fix erroneous use of deprecated item '_diffrn_detector_axis.id' in examples for DIFFRN_SCAN_AXIS. + Add deprecated items '_diffrn_detector_axis.id' and '_diffrn_measurement_axis.id'. (HJB) ; 1.2.4 2003-07-14 ; Changes as per I. David Brown. + Enhance descriptions in DIFFRN_SCAN_AXIS to make them less dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS. + Provide a copy of the deprecated DIFFRN_FRAME_DATA category for completeness. (HJB) ; 1.2.3 2003-07-03 ; Cleanup to conform to ITVG. + Correct sign error in ..._cubed units. + Correct '_diffrn_radiation.polarisn_norm' range. (HJB) ; 1.2.2 2003-03-10 ; Correction of typos in various DIFFRN_SCAN_AXIS descriptions. (HJB) ; 1.2.1 2003-02-22 ; Correction of ATOM_ for ARRAY_ typos in various descriptions. (HJB) ; 1.2 2003-02-07 ; Corrections to encodings (remove extraneous hyphens) remove extraneous underscore in '_array_structure.encoding_type' enumeration. Correct typos in items units list. (HJB) ; 1.1.3 2001-04-19 ; Another typo corrections by Wilfred Li, and cleanup by HJB. ; 1.1.2 2001-03-06 ; Several typo corrections by Wilfred Li. ; 1.1.1 2001-02-16 ; Several typo corrections by JW. ; 1.1 2001-02-06 ; Draft resulting from discussions on header for use at NSLS. (HJB) + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME. + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'. + Add '_diffrn_measurement_axis.measurement_device' and change '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'. + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source', '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm', '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end', '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr', '_diffrn_scan_axis.displacement_rstrt_incr', '_diffrn_scan_frame_axis.angle_increment', '_diffrn_scan_frame_axis.angle_rstrt_incr', '_diffrn_scan_frame_axis.displacement', '_diffrn_scan_frame_axis.displacement_increment',and '_diffrn_scan_frame_axis.displacement_rstrt_incr'. + Add '_diffrn_measurement.device' to category key. + Update yyyy-mm-dd to allow optional time with fractional seconds for time stamps. + Fix typos caught by RS. + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to allow for coupled axes, as in spiral scans. + Add examples for fairly complete headers thanks to R. Sweet and P. Ellis. ; 1.0 2000-12-21 ; Release version - few typos and tidying up. (BM & HJB) + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end of dictionary. + Alphabetize dictionary. ; 0.7.1 2000-09-29 ; Cleanup fixes. (JW) + Correct spelling of diffrn_measurement_axis in '_axis.id' + Correct ordering of uses of '_item.mandatory_code' and '_item_default.value'. ; 0.7.0 2000-09-09 ; Respond to comments by I. David Brown. (HJB) + Add further comments on '\n' and '\t'. + Update ITEM_UNITS_LIST by taking section from mmCIF dictionary and adding metres. Change 'meter' to 'metre' throughout. + Add missing enumerations to '_array_structure.compression_type' and make 'none' the default. + Remove parent-child relationship between '_array_structure_list.index' and '_array_structure_list.precedence'. + Improve alphabetization. + Fix '_array_intensities_gain.esd' related function. + Improve comments in AXIS. + Fix DIFFRN_FRAME_DATA example. + Remove erroneous DIFFRN_MEASUREMENT example. + Add '_diffrn_measurement_axis.id' to the category key. ; 0.6.0 1999-01-14 ; Remove redundant information for ENC_NONE data. (HJB) + After the D5 remove binary section identifier, size and compression type. + Add Control-L to header. ; 0.5.1 1999-01-03 ; Cleanup of typos and syntax errors. (HJB) + Cleanup example details for DIFFRN_SCAN category. + Add missing quote marks for '_diffrn_scan.id' definition. ; 0.5 1999-01-01 ; Modifications for axis definitions and reduction of binary header. (HJB) + Restore '_diffrn_detector.diffrn_id' to DIFFRN_DETECTOR KEY. + Add AXIS category. + Bring in complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories from cif_mm.dic for clarity. + Change '_array_structure.encoding_type' from type code to uline and added X-Binary-Element-Type to MIME header. + Add detector beam centre '_diffrn_detector_element.center[1]' and '_diffrn_detector_element.center[2]'. + Correct item name of '_diffrn_refln.frame_id'. + Replace reference to '_array_intensities.undefined' by '_array_intensities.undefined_value'. + Replace references to '_array_intensity.scaling' with '_array_intensities.scaling'. + Add DIFFRN_SCAN... categories. ; 0.4 1998-08-11 ; Modifications to the 0.3 imgCIF draft. (HJB) + Reflow comment lines over 80 characters and corrected typos. + Update examples and descriptions of MIME encoded data. + Change name to cbfext98.dic. ; 0.3 1998-07-04 ; Modifications for imgCIF. (HJB) + Add binary type, which is a text field containing a variant on MIME encoded data. + Change type of '_array_data.data' to binary and specify internal structure of raw binary data. + Add '_array_data.binary_id', and make '_diffrn_frame_data.binary_id' and '_array_intensities.binary_id' into pointers to this item. ; 0.2 1997-12-02 ; Modifications to the CBF draft. (JW) + Add category hierarchy for describing frame data developed from discussions at the BNL imgCIF Workshop Oct 1997. The following changes are made in implementing the workshop draft. Category DIFFRN_ARRAY_DATA is renamed to DIFFRN_FRAME_DATA. Category DIFFRN_FRAME_TYPE is renamed to DIFFRN_DETECTOR_ELEMENT. The parent item for '_diffrn_frame_data.array_id' is changed from '_array_structure_list.array_id' to '_array_structure.id'. Item '_diffrn_detector.array_id' is deleted. + Add data item '_diffrn_frame_data.binary_id' to identify data groups within a binary section. The formal identification of the binary section is still fuzzy. ; 0.1 1997-01-24 ; First draft of this dictionary in DDL 2.1 compliant format by John Westbrook (JW). This version is adapted from the Crystallographic Binary File (CBF) Format Draft Proposal provided by Andy Hammersley (AH). Modifications to the CBF draft. (JW) + In this version the array description has been cast in the categories ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. These categories have been generalized to describe array data of arbitrary dimension. + Array data in this description are contained in the category ARRAY_DATA. This departs from the CBF notion of data existing in some special comment. In this description, data are handled as an ordinary data item encapsulated in a character data type. Although data this manner deviates from CIF conventions, it does not violate any DDL 2.1 rules. DDL 2.1 regular expressions can be used to define the binary representation which will permit some level of data validation. In this version, the placeholder type code "any" has been used. This translates to a regular expression which will match any pattern. It should be noted that DDL 2.1 already supports array data objects although these have not been used in the current mmCIF dictionary. It may be possible to use the DDL 2.1 ITEM_STRUCTURE and ITEM_STRUCTURE_LIST categories to provide the information that is carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. By moving the array structure to the DDL level it would be possible to define an array type as well as a regular expression defining the data format. + Multiple array sections can be properly handled within a single datablock. ; #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof ./CBFlib-0.9.2.2/doc/Dcategorygroups.html0000644000076500007650000000507711603702115016423 0ustar yayayaya (IUCr) CIF dictionary cif_img.dic category groups

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF)

    Category groups

    The following category groups are defined in this dictionary:

    inclusive_group
    Categories that belong to the dictionary extension.
    array_data_group
    Categories that describe array data.
    axis_group
    Categories that describe axes.
    diffrn_group
    Categories that describe details of the diffraction experiment.

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_radiation.polarisn_norm.html0000644000076500007650000000541411603702115021531 0ustar yayayaya (IUCr) CIF Definition save__diffrn_radiation.polarisn_norm

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_radiation.polarisn_norm

    Name:
    '_diffrn_radiation.polarisn_norm'

    Definition:

            The angle in degrees, as viewed from the specimen, between the
                   perpendicular component of the polarization and the diffraction
                   plane. See _diffrn_radiation_polarisn_ratio.
    
    

    Type: float

    Mandatory item: no

    Alias:
    _diffrn_radiation_polarisn_norm (cif_core.dic version 2.0.1)
    The permitted range is [-90.0, 90.0]

    Category: diffrn_radiation

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_detector_element.center[2].html0000644000076500007650000000703111603702115022046 0ustar yayayaya (IUCr) CIF Definition save__diffrn_detector_element.center[2]

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_detector_element.center[2]

    Name:
    '_diffrn_detector_element.center[2]'

    Definition:

           The value of _diffrn_detector_element.center[2] is the Y
                  component of the distortion-corrected beam centre in
                  millimetres from the (0, 0) (lower-left) corner of the
                  detector element viewed from the sample side.
    
                  The X and Y axes are the laboratory coordinate system
                  coordinates defined in the AXIS category measured
                  when all positioning axes for the detector are at their zero
                  settings.  If the resulting X or Y axis is then orthogonal to the
                  detector, the Z axis is used instead of the orthogonal axis.
    
                  Because of ambiguity about the setting used to determine this 
                  center, use of this data item is deprecated. The data item
                  _diffrn_data_frame.center_slow
                  which is referenced to the detector coordinate system and not
                  directly to the laboratory coordinate system should be used 
                  instead.
                  
    
    

    Type: float

    Mandatory item: no


    Enumeration default: 0.0

    Category: diffrn_detector_element

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Iarray_intensities.linearity.html0000644000076500007650000001554211603702115021104 0ustar yayayaya (IUCr) CIF Definition save__array_intensities.linearity

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _array_intensities.linearity

    Name:
    '_array_intensities.linearity'

    Definition:

            The intensity linearity scaling method used to convert
                   from the raw intensity to the stored element value:
    
                   'linear' is linear.
    
                   'offset'  means that the value defined by
                   _array_intensities.offset should be added to each
                    element value.
    
                   'scaling' means that the value defined by
                   _array_intensities.scaling should be multiplied with each
                   element value.
    
                   'scaling_offset' is the combination of the two previous cases,
                   with the scale factor applied before the offset value.
    
                   'sqrt_scaled' means that the square root of raw
                   intensities multiplied by _array_intensities.scaling is
                   calculated and stored, perhaps rounded to the nearest
                   integer. Thus, linearization involves dividing the stored
                   values by _array_intensities.scaling and squaring the
                   result.
    
                   'logarithmic_scaled' means that the logarithm base 10 of
                   raw intensities multiplied by _array_intensities.scaling
                   is calculated and stored, perhaps rounded to the nearest
                   integer. Thus, linearization involves dividing the stored
                   values by _array_intensities.scaling and calculating 10
                   to the power of this number.
    
                   'raw' means that the data are a set of raw values straight
                   from the detector.
    
    

    Type: code

    Mandatory item: yes


    The data value must be one of the following:


    linear
    .

    offset
    The value defined by _array_intensities.offset should be added to each element value.

    scaling
    The value defined by _array_intensities.scaling should be multiplied with each element value.

    scaling_offset
    The combination of the scaling and offset with the scale factor applied before the offset value.

    sqrt_scaled
    The square root of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and squaring the result.

    logarithmic_scaled
    The logarithm base 10 of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and calculating 10 to the power of this number.

    raw
    The array consists of raw values to which no corrections have been applied. While the handling of the data is similar to that given for 'linear' data with no offset, the meaning of the data differs in that the number of incident photons is not necessarily linearly related to the number of counts reported. This value is intended for use either in calibration experiments or to allow for handling more complex data-fitting algorithms than are allowed for by this data item.

    Category: array_intensities

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/cif_img_1.3.1.dic0000644000076500007650000054572011603702115015156 0ustar yayayaya ############################################################################## # # # Image CIF Dictionary (imgCIF) # # and Crystallographic Binary File Dictionary (CBF) # # Extending the Macromolecular CIF Dictionary (mmCIF) # # # # Version 1.3.1 # # of 2003-08-13 # # # # by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook # # # # This dictionary was adapted from format discussed at the imgCIF Workshop, # # held at BNL Oct 1997 and the Crystallographic Binary File Format Draft # # Proposal by Andrew Hammersley. The first DDL 2.1 Version was created by # # John Westbrook. This version was drafted by Herbert J. Bernstein and # # incorporates comments by I. David Brown, John Westbrook, Brian McMahon, # # Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li, Gotzon Madariaga, # # Frances C. Bernstein and others. # ############################################################################## data_cif_img.dic _dictionary.title cif_img.dic _dictionary.version 1.3.1 _dictionary.datablock_id cif_img.dic ############################################################################## # CONTENTS # # CATEGORY_GROUP_LIST # # category ARRAY_DATA # # _array_data.array_id # _array_data.binary_id # _array_data.data # # category ARRAY_ELEMENT_SIZE # # _array_element_size.array_id # _array_element_size.index # _array_element_size.size # # category ARRAY_INTENSITIES # # _array_intensities.array_id # _array_intensities.binary_id # _array_intensities.gain # _array_intensities.gain_esd # _array_intensities.linearity # _array_intensities.offset # _array_intensities.scaling # _array_intensities.overload # _array_intensities.undefined_value # # category ARRAY_STRUCTURE # # _array_structure.byte_order # _array_structure.compression_type # _array_structure.encoding_type # _array_structure.id # # category ARRAY_STRUCTURE_LIST # # _array_structure_list.axis_set_id # _array_structure_list.array_id # _array_structure_list.dimension # _array_structure_list.direction # _array_structure_list.index # _array_structure_list.precedence # # category ARRAY_STRUCTURE_LIST_AXIS # # _array_structure_list_axis.axis_id # _array_structure_list_axis.axis_set_id # _array_structure_list_axis.angle # _array_structure_list_axis.angle_increment # _array_structure_list_axis.displacement_increment # _array_structure_list_axis.angular_pitch # _array_structure_list_axis.radial_pitch # # category AXIS # # _axis.depends_on # _axis.equipment # _axis.id # _axis.offset[1] # _axis.offset[2] # _axis.offset[3] # _axis.type # _axis.vector[1] # _axis.vector[2] # _axis.vector[3] # # category DIFFRN_DATA_FRAME # # _diffrn_data_frame.array_id # _diffrn_data_frame.binary_id # _diffrn_data_frame.detector_element_id # _diffrn_data_frame.id # # category DIFFRN_DETECTOR # # _diffrn_detector.details # _diffrn_detector.detector # _diffrn_detector.diffrn_id # _diffrn_detector.dtime # _diffrn_detector.id # _diffrn_detector.number_of_axes # _diffrn_detector.type # # category DIFFRN_DETECTOR_AXIS # # _diffrn_detector_axis.axis_id # _diffrn_detector_axis.detector_id # # category DIFFRN_DETECTOR_ELEMENT # # _diffrn_detector_element.center[1] # _diffrn_detector_element.center[2] # _diffrn_detector_element.id # _diffrn_detector_element.detector_id # # category DIFFRN_MEASUREMENT # # _diffrn_measurement.diffrn_id # _diffrn_measurement.details # _diffrn_measurement.device # _diffrn_measurement.device_details # _diffrn_measurement.device_type # _diffrn_measurement.id # _diffrn_measurement.method # _diffrn_measurement.number_of_axes # _diffrn_measurement.specimen_support # # category DIFFRN_MEASUREMENT_AXIS # # _diffrn_measurement_axis.axis_id # _diffrn_measurement_axis.measurement_device # _diffrn_measurement_axis.measurement_id # # category DIFFRN_RADIATION # # _diffrn_radiation.collimation # _diffrn_radiation.diffrn_id # _diffrn_radiation.div_x_source # _diffrn_radiation.div_y_source # _diffrn_radiation.div_x_y_source # _diffrn_radiation.filter_edge' # _diffrn_radiation.inhomogeneity # _diffrn_radiation.monochromator # _diffrn_radiation.polarisn_norm # _diffrn_radiation.polarisn_ratio # _diffrn_radiation.polarizn_source_norm # _diffrn_radiation.polarizn_source_ratio # _diffrn_radiation.probe # _diffrn_radiation.type # _diffrn_radiation.xray_symbol # _diffrn_radiation.wavelength_id # # category DIFFRN_REFLN # # _diffrn_refln.frame_id # # category DIFFRN_SCAN # # _diffrn_scan.id # _diffrn_scan.date_end # _diffrn_scan.date_start # _diffrn_scan.integration_time # _diffrn_scan.frame_id_start # _diffrn_scan.frame_id_end # _diffrn_scan.frames # # category DIFFRN_SCAN_AXIS # # _diffrn_scan_axis.axis_id # _diffrn_scan_axis.angle_start # _diffrn_scan_axis.angle_range # _diffrn_scan_axis.angle_increment # _diffrn_scan_axis.angle_rstrt_incr # _diffrn_scan_axis.displacement_start # _diffrn_scan_axis.displacement_range # _diffrn_scan_axis.displacement_increment # _diffrn_scan_axis.displacement_rstrt_incr # _diffrn_scan_axis.scan_id # # category DIFFRN_SCAN_FRAME # # _diffrn_scan_frame.date # _diffrn_scan_frame.frame_id # _diffrn_scan_frame.frame_number # _diffrn_scan_frame.integration_time # _diffrn_scan_frame.scan_id # # category DIFFRN_SCAN_FRAME_AXIS # # _diffrn_scan_frame_axis.axis_id # _diffrn_scan_frame_axis.angle # _diffrn_scan_frame_axis.angle_increment # _diffrn_scan_frame_axis.angle_rstrt_incr # _diffrn_scan_frame_axis.displacement # _diffrn_scan_frame_axis.displacement_increment # _diffrn_scan_frame_axis.displacement_rstrt_incr # _diffrn_scan_frame_axis.frame_id # # ***DEPRECATED*** data items # # _diffrn_detector_axis.id # _diffrn_measurement_axis.id # # ***DEPRECATED*** category DIFFRN_FRAME_DATA # # _diffrn_frame_data.array_id # _diffrn_frame_data.binary_id # _diffrn_frame_data.detector_element_id # _diffrn_frame_data.id # # # ITEM_TYPE_LIST # ITEM_UNITS_LIST # DICTIONARY_HISTORY # ############################################################################## ######################### ## CATEGORY_GROUP_LIST ## ######################### loop_ _category_group_list.id _category_group_list.parent_id _category_group_list.description 'inclusive_group' . ; Categories that belong to the dictionary extension. ; 'array_data_group' 'inclusive_group' ; Categories that describe array data. ; 'axis_group' 'inclusive_group' ; Categories that describe axes. ; 'diffrn_group' 'inclusive_group' ; Categories that describe details of the diffraction experiment. ; ############## # ARRAY_DATA # ############## save_ARRAY_DATA _category.description ; Data items in the ARRAY_DATA category are the containers for the array data items described in category ARRAY_STRUCTURE. ; _category.id array_data _category.mandatory_code no loop_ _category_key.name '_array_data.array_id' '_array_data.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows two binary data blocks. The first one was compressed by the CBF_CANONICAL compression algorithm and presented as hexadecimal data. The first character "H" on the data lines means hexadecimal. It could have been "O" for octal or "D" for decimal. The second character on the line shows the number of bytes in each word (in this case "4"), which then requires 8 hexadecimal digits per word. The third character gives the order of octets within a word, in this case "<" for the ordering 4321 (i.e. "big-endian"). Alternatively the character ">" could have been used for the ordering 1234 (i.e. "little-endian"). The block has a "message digest" to check the integrity of the data. The second block is similar, but uses CBF_PACKED compression and BASE64 encoding. Note that the size and the digest are different. ; ; loop_ _array_data.array_id _array_data.binary_id _array_data.data image_1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_CANONICAL" Content-Transfer-Encoding: X-BASE16 X-Binary-Size: 3927126 X-Binary-ID: 1 Content-MD5: u2sTJEovAHkmkDjPi+gWsg== # Hexadecimal encoding, byte 0, byte order ...21 # H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ... .... --CIF-BINARY-FORMAT-SECTION---- ; image_2 2 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF-PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3745758 X-Binary-ID: 2 Content-MD5: 1zsJjWPfol2GYl2V+QSXrw== ELhQAAAAAAAA... ... --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_data.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_array_data.array_id' _item.category_id array_data _item.mandatory_code yes _item_type.code code save_ save__array_data.binary_id _item_description.description ; This item is an integer identifier which, along with '_array_data.array_id' should uniquely identify the particular block of array data. If '_array_data.binary_id' is not explicitly given, it defaults to 1. The value of '_array_data.binary_id' distinguishes among multiple sets of data with the same array structure. If the MIME header of the data array specifies a value for X-Binary-Id, the value of '_array_data.binary_id' should be equal the value given for X-Binary-Id. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_data.binary_id' array_data implicit '_diffrn_data_frame.binary_id' diffrn_data_frame implicit '_array_intensities.binary_id' array_intensities implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.binary_id' '_array_data.binary_id' '_array_intensities.binary_id' '_array_data.binary_id' _item_default.value 1 _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_data.data _item_description.description ; The value of '_array_data.data' contains the array data encapsulated in a STAR string. The representation used is a variant on the Multipurpose Internet Mail Extensions (MIME) specified in RFC 2045-2049 by N. Freed et al. The boundary delimiter used in writing an imgCIF or CBF is "--CIF-BINARY-FORMAT-SECTION--" (including the required initial "--"). The Content-Type may be any of the discrete types permitted in RFC 2045; "application/octet-stream" is recommended. If an octet stream was compressed, the compression should be specified by the parameter 'conversions="x-CBF_PACKED"' or the parameter 'conversions="x-CBF_CANONICAL"'. The Content-Transfer-Encoding may be "BASE64", "Quoted-Printable", "X-BASE8", "X-BASE10", or "X-BASE16" for an imgCIF or "BINARY" for a CBF. The octal, decimal and hexadecimal transfer encodings are for convenience in debugging, and are not recommended for archiving and data interchange. In an imgCIF file, the encoded binary data begins after the empty line terminating the header. In a CBF, the raw binary data begins after an empty line terminating the header and after the sequence: Octet Hex Decimal Purpose 0 0C 12 (ctrl-L) Page break 1 1A 26 (ctrl-Z) Stop listings in MS-DOS 2 04 04 (Ctrl-D) Stop listings in UNIX 3 D5 213 Binary section begins None of these octets are included in the calculation of the message size, nor in the calculation of the message digest. The X-Binary-Size header specifies the size of the equivalent binary data in octets. If compression was used, this size is the size after compression, including any book-keeping fields. An adjustment is made for the deprecated binary formats in which 8 bytes of binary header are used for the compression type. In that case, the 8 bytes used for the compression type is subtracted from the size, so that the same size will be reported if the compression type is supplied in the MIME header. Use of the MIME header is the recommended way to supply the compression type. In general, no portion of the binary header is included in the calculation of the size. The X-Binary-Element-Type header specifies the type of binary data in the octets, using the same descriptive phrases as in '_array_structure.encoding_type'. The default value is "unsigned 32-bit integer". An MD5 message digest may, optionally, be used. The "RSA Data Security, Inc. MD5 Message-Digest Algorithm" should be used. No portion of the header is included in the calculation of the message digest. If the Transfer Encoding is "X-BASE8", "X-BASE10", or "X-BASE16", the data is presented as octal, decimal or hexadecimal data organized into lines or words. Each word is created by composing octets of data in fixed groups of 2, 3, 4, 6 or 8 octets, either in the order ...4321 ("big- endian") or 1234... (little-endian). If there are fewer than the specified number of octets to fill the last word, then the missing octets are presented as "==" for each missing octet. Exactly two equal signs are used for each missing octet even for octal and decimal encoding. The format of lines is: rnd xxxxxx xxxxxx xxxxxx where r is "H", "O", or "D" for hexadecimal, octal or decimal, n is the number of octets per word. and d is "<" for ">" for the "...4321" and "1234..." octet orderings respectively. The "==" padding for the last word should be on the appropriate side to correspond to the missing octets, e.g. H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000 or H3> FF0700 00==== For these hex, octal and decimal formats, only, comments beginning with "#" are permitted to improve readability. BASE64 encoding follows MIME conventions. Octets are in groups of three, c1, c2, c3. The resulting 24 bits are broken into four 6-bit quantities, starting with the high-order six bits (c1 >> 2) of the first octet, then the low-order two bits of the first octet followed by the high-order 4 bits of the second octet ((c1 & 3)<<4 | (c2>>4)), then the bottom 4 bits of the second octet followed by the high order two bits of the last octet ((c2 & 15)<<2 | (c3>>6)), then the bottom six bits of the last octet (c3 & 63). Each of these four quantities is translated into an ASCII character using the mapping: 1 2 3 4 5 6 0123456789012345678901234567890123456789012345678901234567890123 | | | | | | | ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/ With short groups of octets padded on the right with one "=" if c3 is missing, and with "==" if both c2 and c3 are missing. QUOTED-PRINTABLE encoding also follows MIME conventions, copying octets without translation if their ASCII values are 32..38, 42, 48..57, 59..60, 62, 64..126 and the octet is not a ";" in column 1. All other characters are translated to =nn, where nn is the hexadecimal encoding of the octet. All lines are "wrapped" with a terminating "=" (i.e. the MIME conventions for an implicit line terminator are never used). ; _item.name '_array_data.data' _item.category_id array_data _item.mandatory_code yes _item_type.code binary save_ ###################### # ARRAY_ELEMENT_SIZE # ###################### save_ARRAY_ELEMENT_SIZE _category.description ; Data items in the ARRAY_ELEMENT_SIZE category record the physical size of array elements along each array dimension. ; _category.id array_element_size _category.mandatory_code no loop_ _category_key.name '_array_element_size.array_id' '_array_element_size.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A regular 2D array with a uniform element dimension of 1220 nanometres. ; ; loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size image_1 1 1.22e-6 image_1 2 1.22e-6 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_element_size.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_array_element_size.array_id' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.index _item_description.description ; This item is a pointer to '_array_structure_list.index' in the ARRAY_STRUCTURE_LIST category. ; _item.name '_array_element_size.index' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.size _item_description.description ; The size in metres of an image element in this dimension. This supposes that the elements are arranged on a regular grid. ; _item.name '_array_element_size.size' _item.category_id array_element_size _item.mandatory_code yes _item_type.code float _item_units.code 'metres' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ ##################### # ARRAY_INTENSITIES # ##################### save_ARRAY_INTENSITIES _category.description ; Data items in the ARRAY_INTENSITIES category record the information required to recover the intensity data from the set of data values stored in the ARRAY_DATA category. The actual detector may have a complex relationship between the raw intensity values and the number of incident photons. In most cases, the number stored in the final array will have a simple linear relationship to the actual number of incident photons, given by '_array_intensities.gain'. If raw, uncorrected values are presented (e.g for calibration experiments), the value of '_array_intensities.linearity' will be 'raw' and '_array_intensities.gain' will not be used. ; _category.id array_intensities _category.mandatory_code no loop_ _category_key.name '_array_intensities.array_id' '_array_intensities.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 ; ; loop_ _array_intensities.array_id _array_intensities.linearity _array_intensities.gain _array_intensities.overload _array_intensities.undefined_value image_1 linear 1.2 655535 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_intensities.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_array_intensities.array_id' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code save_ save__array_intensities.binary_id _item_description.description ; This item is a pointer to '_array_data.binary_id' in the ARRAY_DATA category. ; _item.name '_array_intensities.binary_id' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code int save_ save__array_intensities.gain _item_description.description ; Detector "gain". The factor by which linearized intensity count values should be divided to produce true photon counts. ; _item.name '_array_intensities.gain' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain_esd' 'associated_value' save_ save__array_intensities.gain_esd _item_description.description ; The estimated standard deviation in detector "gain". ; _item.name '_array_intensities.gain_esd' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain' 'associated_esd' save_ save__array_intensities.linearity _item_description.description ; The intensity linearity scaling used from raw intensity to the stored element value: 'linear' is obvious 'offset' means that the value defined by '_array_intensities.offset' should be added to each element value. 'scaling' means that the value defined by '_array_intensities.scaling' should be multiplied with each element value. 'scaling_offset' is the combination of the two previous cases, with the scale factor applied before the offset value. 'sqrt_scaled' means that the square root of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and squaring the result. 'logarithmic_scaled' means that the logarithm based 10 of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and calculating 10 to the power of this number. 'raw' means that the data is a set of raw values straight from the detector. ; _item.name '_array_intensities.linearity' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'linear' . 'offset' ; The value defined by '_array_intensities.offset' should be added to each element value. ; 'scaling' ; The value defined by '_array_intensities.scaling' should be multiplied with each element value. ; 'scaling_offset' ; The combination of the scaling and offset with the scale factor applied before the offset value. ; 'sqrt_scaled' ; The square root of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and squaring the result. ; 'logarithmic_scaled' ; The logarithm based 10 of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and calculating 10 to the power of this number. ; 'raw' ; The array consists of raw values to which no corrections have been applied. While the handling of the data is similar to that given for 'linear' data with no offset, the meaning of the data differs in that the number of incident photons is not necessarily linearly related to the number of counts reported. This value is intended for use either in calibration experiments or to allow for handling more complex data fitting algorithms than are allowed for by this data item. ; save_ save__array_intensities.offset _item_description.description ; Offset value to add to array element values in the manner described by item '_array_intensities.linearity'. ; _item.name '_array_intensities.offset' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.scaling _item_description.description ; Multiplicative scaling value to be applied to array data in the manner described by item '_array_intensities.linearity'. ; _item.name '_array_intensities.scaling' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.overload _item_description.description ; The saturation intensity level for this data array. ; _item.name '_array_intensities.overload' _item.category_id array_intensities _item.mandatory_code no _item_type.code float _item_units.code 'counts' save_ save__array_intensities.undefined_value _item_description.description ; A value to be substituted for undefined values in the data array. ; _item.name '_array_intensities.undefined_value' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ ################### # ARRAY_STRUCTURE # ################### save_ARRAY_STRUCTURE _category.description ; Data items in the ARRAY_STRUCTURE category record the organization and encoding of array data which may be stored in the ARRAY_DATA category. ; _category.id array_structure _category.mandatory_code no _category_key.name '_array_structure.id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order image_1 "unsigned 16-bit integer" none little_endian ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure.byte_order _item_description.description ; The order of bytes for integer values which require more than 1-byte. (IBM-PC's and compatibles, and Dec-Vaxes use low-byte-first ordered integers, whereas Hewlett Packard 700 series, Sun-4 and Silicon Graphics use high-byte-first ordered integers. Dec-Alphas can produce/use either depending on a compiler switch.) ; _item.name '_array_structure.byte_order' _item.category_id array_structure _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'big_endian' ; The first byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; 'little_endian' ; The last byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; save_ save__array_structure.compression_type _item_description.description ; Type of data compression method used to compress the array data. ; _item.name '_array_structure.compression_type' _item.category_id array_structure _item.mandatory_code no _item_type.code code _item_default.value 'none' loop_ _item_enumeration.value _item_enumeration.detail 'none' ; Data are stored in normal format as defined by '_array_structure.encoding_type' and '_array_structure.byte_order'. ; 'byte_offsets' ; Using the compression scheme defined in CBF definition Section 5.0. ; 'packed' ; Using the 'packed' compression scheme, a CCP4-style packing (CBFlib section 3.3.2) ; 'canonical' ; Using the 'canonical' compression scheme (CBFlib section 3.3.1) ; save_ save__array_structure.encoding_type _item_description.description ; Data encoding of a single element of array data. In several cases, the IEEE format is referenced. See "IEEE Standard for Binary Floating-Point Arithmetic", ANSI/IEEE Std 754-1985, the Institute of Electrical and Electronics Engineers, Inc., NY 1985. ; _item.name '_array_structure.encoding_type' _item.category_id array_structure _item.mandatory_code yes _item_type.code uline loop_ _item_enumeration.value 'unsigned 8-bit integer' 'signed 8-bit integer' 'unsigned 16-bit integer' 'signed 16-bit integer' 'unsigned 32-bit integer' 'signed 32-bit integer' 'signed 32-bit real IEEE' 'signed 64-bit real IEEE' 'signed 32-bit complex IEEE' save_ save__array_structure.id _item_description.description ; The value of '_array_structure.id' must uniquely identify each item of array data. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure.id' array_structure yes '_array_data.array_id' array_data yes '_array_structure_list.array_id' array_structure_list yes '_array_intensities.array_id' array_intensities yes '_diffrn_data_frame.array_id' diffrn_data_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_data.array_id' '_array_structure.id' '_array_structure_list.array_id' '_array_structure.id' '_array_intensities.array_id' '_array_structure.id' '_diffrn_data_frame.array_id' '_array_structure.id' save_ ######################## # ARRAY_STRUCTURE_LIST # ######################## save_ARRAY_STRUCTURE_LIST _category.description ; Data items in the ARRAY_STRUCTURE_LIST category record the size and organization of each array dimension. The relationship to physical axes may be given. ; _category.id array_structure_list _category.mandatory_code no loop_ _category_key.name '_array_structure_list.array_id' '_array_structure_list.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - An image array of 1300 x 1200 elements. The raster order of the image is left-to-right (increasing) in the first dimension and bottom-to-top (decreasing) in the second dimension. ; ; loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id image_1 1 1300 1 increasing ELEMENT_X image_1 2 1200 2 decreasing ELEMENY_Y ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure_list.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_array_structure_list.array_id' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code code save_ save__array_structure_list.axis_set_id _item_description.description ; This is a descriptor for the physical axis or set of axes corresponding to an array index. This data item is related to the axes of the detector itself given in DIFFRN_DETECTOR_AXIS, but usually differ in that the axes in this category are the axes of the coordinate system of reported data points, while the axes in DIFFRN_DETECTOR_AXIS are the physical axes of the detector describing the "poise" of the detector as an overall physical object. If there is only one axis in the set, the identifier of that axis should be used as the identifier of the set. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.axis_set_id' array_structure_list yes '_array_structure_list_axis.axis_set_id' array_structure_list_axis implicit _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_structure_list_axis.axis_set_id' '_array_structure_list.axis_set_id' save_ save__array_structure_list.dimension _item_description.description ; The number of elements stored in the array structure in this dimension. ; _item.name '_array_structure_list.dimension' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.direction _item_description.description ; Identifies the direction in which this array index changes. ; _item.name '_array_structure_list.direction' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_enumeration.value _item_enumeration.detail 'increasing' ; Indicates the index changes from 1 to the maximum dimension. ; 'decreasing' ; Indicates the index changes from the maximum dimension to 1. ; save_ save__array_structure_list.index _item_description.description ; Identifies the one-based index of the row or column in the array structure. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.index' array_structure_list yes '_array_structure_list.precedence' array_structure_list yes '_array_element_size.index' array_element_size yes _item_type.code int loop_ _item_linked.child_name _item_linked.parent_name '_array_element_size.index' '_array_structure_list.index' loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.precedence _item_description.description ; Identifies the rank order in which this array index changes with respect to other array indices. The precedence of 1 indicates the index which changes fastest. ; _item.name '_array_structure_list.precedence' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ ############################# # ARRAY_STRUCTURE_LIST_AXIS # ############################# save_ARRAY_STRUCTURE_LIST_AXIS _category.description ; Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe the physical settings of sets axes for the centres of pixels that correspond to data points described in the ARRAY_STRUCTURE_LIST category. In the simplest cases, the physical increments of a single axis correspond to the increments of a single array index. More complex organizations, e.g. spiral scans, may require coupled motions along multiple axes. Note that a spiral scan uses two coupled axis, one for the angular direction, one for the radial direction. This differs from a cylindrical scan for which the two axes are not coupled into one set. ; _category.id array_structure_list_axis _category.mandatory_code no loop_ _category_key.name '_array_structure_list_axis.axis_set_id' '_array_structure_list_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' save_ save__array_structure_list_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes from the set of axes for which settings are being specified. Multiple axes may be specified for the same value of '_array_structure_list_axis.axis_set_id' This item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_array_structure_list_axis.axis_id' _item.category_id array_structure_list_axis _item.mandatory_code yes _item_units.code code save_ save__array_structure_list_axis.axis_set_id _item_description.description ; The value of this data item is the identifier of the set of axes for which axis settings are being specified. Multiple axes may be specified for the same value of '_array_structure_list_axis.axis_set_id'. This item is a pointer to '_array_structure_list.axis_set_id' in the ARRAY_STRUCTURE_LIST category. If this item is not specified, it defaults to the corresponding axis identifier. ; _item.name '_array_structure_list_axis.axis_set_id' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_units.code code save_ save__array_structure_list_axis.angle _item_description.description ; The setting of the specified axis in degrees for the first data point of the array index with the corresponding value of '_array_structure_list.axis_set_id'. If the index is specified as 'increasing' this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing' this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.angle' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.angle_increment _item_description.description ; The pixel-centre-to-pixel-centre increment in the angular setting of the specified axis in degrees. This is not meaningful in the case of 'constant velocity' spiral scans and should not be specified in that case. See '_array_structure_list_axis.angular_pitch'. ; _item.name '_array_structure_list_axis.angle_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for the first data point of the array index with the corresponding value of '_array_structure_list.axis_set_id'. If the index is specified as 'increasing' this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing' this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.displacement' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.displacement_increment _item_description.description ; The pixel-centre-to-pixel-centre increment for the displacement setting of the specified axis in millimetres. ; _item.name '_array_structure_list_axis.displacement_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.angular_pitch _item_description.description ; The pixel-centre-to-pixel-centre distance for a one step change in the setting of the specified axis in millimetres. This is meaningful only for 'constant velocity' spiral scans, or for uncoupled angular scans at a constant radius (cylindrical scan) and should not be specified for cases in which the angle between pixels, rather than the distance between pixels is uniform. See '_array_structure_list_axis.angle_increment'. ; _item.name '_array_structure_list_axis.angular_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.radial_pitch _item_description.description ; The radial distance from one "cylinder" of pixels to the next in millimetres. If the scan is a 'constant velocity' scan with differing angular displacements between pixels, the value of this item may differ significantly from the value of '_array_structure_list_axis.displacement_increment'. ; _item.name '_array_structure_list_axis.radial_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ ######## # AXIS # ######## save_AXIS _category.description ; Data items in the AXIS category record the information required to describe the various goniometer, detector, source and other axes needed to specify a data collection. The location of each axis is specified by two vectors: the axis itself, given as a unit vector, and an offset to the base of the unit vector. These vectors are referenced to a right-handed laboratory coordinate system with its origin in the sample or specimen: | Y (to complete right-handed system) | | | | | |________________X / principal goniometer axis / / / / /Z (to source) Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from the sample or specimen along the principal axis of the goniometer. Axis 2 (Y): The Y-axis completes an orthogonal right-handed system defined by the X-axis and the Z-axis (see below). Axis 3 (Z): The Z-axis is derived from the source axis which goes from the sample to the source. The Z-axis is the component of the source axis in the direction of the source orthogonal to the X-axis in the plane defined by the X-axis and the source axis. These axes are based on the goniometer, not on the orientation of the detector, gravity, etc. The vectors necessary to specify all other axes are given by sets of three components in the order (X, Y, Z). If the axis involved is a rotation axis, it is right handed, i.e. as one views the object to be rotated from the origin (the tail) of the unit vector, the rotation is clockwise. If a translation axis is specified, the direction of the unit vector specifies the sense of positive translation. Note: This choice of coordinate system is similar to, but significantly different from the choice in MOSFLM (Andrew G.W. Leslie, Harry Powell, MRC Laboratory of Molecular Biology, Hills Road, Cambridge CB2 2QH, UK http://www.dl.ac.uk/CCP/CCP4/dist/x-windows/Mosflm/). In MOSFLM, X is along the X-ray beam (the CBF/imgCIF Z axis) and Z is along the rotation axis. All rotations are given in degrees and all translations are given in mm. Axes may be dependent on one another. The X-axis is the only goniometer axis the direction of which is strictly connected to the hardware. All other axes are specified by the positions they would assume when the axes upon which they depend are at their zero points. When specifying detector axes, the axis is given to the beam centre. The location of the beam centre on the detector should be given in the DIFFRN_DETECTOR category in distortion-corrected mm from the (0,0) corner of the detector. It should be noted that many different origins arise in the definition of an experiment. In particular, as noted above, we need to specify the location of the beam centre on the detector in terms of the origin of the detector, which is, of course, not coincident with the centre of the sample. ; _category.id axis _category.mandatory_code no loop_ _category_key.name '_axis.id' '_axis.equipment' loop_ _category_group.id 'inclusive_group' 'axis_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows the axis specification of the axes of a kappa geometry goniometer (See "X-Ray Structure Determination, A Practical Guide", 2nd ed. by G. H. Stout, L. H. Jensen, Wiley Interscience, 1989, 453 pp, p 134.). There are three axes specified, and no offsets. The outermost axis, omega, is pointed along the X-axis. The next innermost axis, kappa, is at a 50 degree angle to the X-axis, pointed away from the source. The innermost axis, phi, aligns with the X-axis when omega and phi are at their zero-points. If T-omega, T-kappa and T-phi are the transformation matrices derived from the axis settings, the complete transformation would be: x' = (T-omega) (T-kappa) (T-phi) x ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] omega rotation goniometer . 1 0 0 kappa rotation goniometer omega -.64279 0 -.76604 phi rotation goniometer kappa 1 0 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - This example show the axis specification of the axes of a detector, source and gravity. We have juggled the order as a reminder that the ordering of presentation of tokens is not significant. We have taken the centre of rotation of the detector to be 68 millimetres in the direction away from the source. ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] source . source . 0 0 1 . . . gravity . gravity . 0 -1 0 . . . tranz translation detector rotz 0 0 1 0 0 -68 twotheta rotation detector . 1 0 0 . . . roty rotation detector twotheta 0 1 0 0 0 -68 rotz rotation detector roty 0 0 1 0 0 -68 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__axis.depends_on _item_description.description ; The value of '_axis.depends_on' specifies the next outermost axis upon which this axis depends. This item is a pointer to '_axis.id' in the same category. ; _item.name '_axis.depends_on' _item.category_id axis _item.mandatory_code no save_ save__axis.equipment _item_description.description ; The value of '_axis.equipment' specifies the type of equipment using the axis: 'goniometer', 'detector', 'gravity', 'source' or 'general'. ; _item.name '_axis.equipment' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail goniometer 'equipment used to orient or position samples' detector 'equipment used to detect reflections' general 'equipment used for general purposes' gravity 'axis specifying the downward direction' source 'axis specifying the direction sample to source' save_ save__axis.offset[1] _item_description.description ; The [1] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[2] _item_description.description ; The [2] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[3] _item_description.description ; The [3] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.id _item_description.description ; The value of '_axis.id' must uniquely identify each axis relevant to the experiment. Note that multiple pieces of equipment may share the same axis (e.g. a twotheta arm), so that the category key for AXIS also includes the equipment. ; loop_ _item.name _item.category_id _item.mandatory_code '_axis.id' axis yes '_array_structure_list_axis.axis_id' array_structure_list_axis yes '_diffrn_detector_axis.axis_id' diffrn_detector_axis yes '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes '_diffrn_scan_axis.axis_id' diffrn_scan_axis yes '_diffrn_scan_frame_axis.axis_id' diffrn_scan_frame_axis yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_axis.depends_on' '_axis.id' '_array_structure_list_axis.axis_id' '_axis.id' '_diffrn_detector_axis.axis_id' '_axis.id' '_diffrn_measurement_axis.axis_id' '_axis.id' '_diffrn_scan_axis.axis_id' '_axis.id' '_diffrn_scan_frame_axis.axis_id' '_axis.id' save_ save__axis.type _item_description.description ; The value of '_axis.type' specifies the type of axis: 'rotation', 'translation' (or 'general' when the type is not relevant, as for gravity). ; _item.name '_axis.type' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail rotation 'right-handed axis of rotation' translation 'translation in the direction of the axis' general 'axis for which the type is not relevant' save_ save__axis.vector[1] _item_description.description ; The [1] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[2] _item_description.description ; The [2] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[3] _item_description.description ; The [3] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ ##################### # DIFFRN_DATA_FRAME # ##################### save_DIFFRN_DATA_FRAME _category.description ; Data items in the DIFFRN_DATA_FRAME category record the details about each frame of data. The items in this category were previously in a DIFFRN_FRAME_DATA category, which is now deprecated. The items from the old category are provided as aliases but should not be used for new work. ; _category.id diffrn_data_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_data_frame.id' '_diffrn_data_frame.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A frame containing data from 4 frame elements. Each frame element has a common array configuration 'array_1' described in ARRAY_STRUCTURE and related categories. The data for each detector element is stored in four groups of binary data in the ARRAY_DATA category, linked by the array_id and binary_id ; ; loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id frame_1 d1_ccd_1 array_1 1 frame_1 d1_ccd_2 array_1 2 frame_1 d1_ccd_3 array_1 3 frame_1 d1_ccd_4 array_1 4 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_data_frame.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_diffrn_data_frame.array_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.array_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0.00 _item_type.code code save_ save__diffrn_data_frame.binary_id _item_description.description ; This item is a pointer to '_array_data.binary_id' in the ARRAY_DATA category. ; _item.name '_diffrn_data_frame.binary_id' _item.category_id diffrn_data_frame _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_frame_data.binary_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code int save_ save__diffrn_data_frame.detector_element_id _item_description.description ; This item is a pointer to '_diffrn_detector_element.id' in the DIFFRN_DETECTOR_ELEMENT category. ; _item.name '_diffrn_data_frame.detector_element_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.detector_element_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.id _item_description.description ; The value of '_diffrn_data_frame.id' must uniquely identify each complete frame of data. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_data_frame.id' diffrn_data_frame yes '_diffrn_refln.frame_id' diffrn_refln yes '_diffrn_scan.frame_id_start' diffrn_scan yes '_diffrn_scan.frame_id_end' diffrn_scan yes '_diffrn_scan_frame.frame_id' diffrn_scan_frame yes '_diffrn_scan_frame_axis.frame_id' diffrn_scan_frame_axis yes _item_aliases.alias_name '_diffrn_frame_data.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_refln.frame_id' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_start' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_end' '_diffrn_data_frame.id' '_diffrn_scan_frame.frame_id' '_diffrn_data_frame.id' '_diffrn_scan_frame_axis.frame_id' '_diffrn_data_frame.id' save_ ########################################################################## # The following is a restatement of the mmCIF DIFFRN_DETECTOR, # # DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for # # the CBF/imgCIF extensions # ########################################################################## ################### # DIFFRN_DETECTOR # ################### save_DIFFRN_DETECTOR _category.description ; Data items in the DIFFRN_DETECTOR category describe the detector used to measure the scattered radiation, including any analyser and post-sample collimation. ; _category.id diffrn_detector _category.mandatory_code no loop_ _category_key.name '_diffrn_detector.diffrn_id' '_diffrn_detector.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_detector.diffrn_id 'd1' _diffrn_detector.detector 'multiwire' _diffrn_detector.type 'Siemens' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector.details _item_description.description ; A description of special aspects of the radiation detector. ; _item.name '_diffrn_detector.details' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'slow mode' save_ save__diffrn_detector.detector _item_description.description ; The general class of the radiation detector. ; _item.name '_diffrn_detector.detector' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector' cifdic.c91 1.0 '_diffrn_detector' cif_core.dic 2.0 _item_type.code text loop_ _item_examples.case 'photographic film' 'scintillation counter' 'CCD plate' 'BF~3~ counter' save_ save__diffrn_detector.diffrn_id _item_description.description ; This data item is a pointer to '_diffrn.id' in the DIFFRN category. The value of '_diffrn.id' uniquely defines a set of diffraction data. ; _item.name '_diffrn_detector.diffrn_id' _item.mandatory_code yes save_ save__diffrn_detector.dtime _item_description.description ; The deadtime in microseconds of the detectors used to measure the diffraction intensities. ; _item.name '_diffrn_detector.dtime' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector_dtime' cifdic.c91 1.0 '_diffrn_detector_dtime' cif_core.dic 2.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code microseconds save_ save__diffrn_detector.id _item_description.description ; The value of '_diffrn_detector.id' must uniquely identify each detector used to collect each diffraction data set. If the value of '_diffrn_detector.id' is not given, it is implicitly equal to the value of '_diffrn_detector.diffrn_id' ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector.id' diffrn_detector implicit '_diffrn_detector_axis.detector_id' diffrn_detector_axis yes loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_detector_axis.detector_id' '_diffrn_detector.id' _item_type.code code save_ save__diffrn_detector.number_of_axes _item_description.description ; The value of '_diffrn_detector.number_of_axes' gives the number of axes of the positioner for the detector identified by '_diffrn_detector.id'. The word "positioner" is a general term used in instrumentation design for devices that are used to change the positions of portions of apparatus by linear translation, rotation, or combinations of such motions. Axes which are used to provide a coordinate system for the face of an area detetctor should not be counted for this data item. The description of each axis should be provided by entries in DIFFRN_DETECTOR_AXIS. ; _item.name '_diffrn_detector.number_of_axes' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_detector.type _item_description.description ; The make, model or name of the detector device used. ; _item.name '_diffrn_detector.type' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ ######################## # DIFFRN_DETECTOR_AXIS # ######################## save_DIFFRN_DETECTOR_AXIS _category.description ; Data items in the DIFFRN_DETECTOR_AXIS category associate axes with detectors. ; _category.id diffrn_detector_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_axis.detector_id' '_diffrn_detector_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_detector_axis.axis_id _item_description.description ; This data item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_diffrn_detector_axis.axis_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_axis.detector_id _item_description.description ; This data item is a pointer to '_diffrn_detector.id' in the DIFFRN_DETECTOR category. This item was previously named '_diffrn_detector_axis.id' which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_detector_axis.detector_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_aliases.alias_name '_diffrn_detector_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ ########################### # DIFFRN_DETECTOR_ELEMENT # ########################### save_DIFFRN_DETECTOR_ELEMENT _category.description ; Data items in the DIFFRN_DETECTOR_ELEMENT category record the details about spatial layout and other characteristics of each element of a detector which may have multiple elements. In most cases, the more detailed information provided in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS are preferable to simply providing the centre. ; _category.id diffrn_detector_element _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_element.id' '_diffrn_detector_element.detector_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Detector d1 is composed of four CCD detector elements, each 200 mm by 200 mm, arranged in a square. in the pattern 1 2 * 3 4 Note that the beam centre is slightly displaced from each of the detector elements, just beyond the lower right corner of 1, the lower left corner of 2, the upper right corner of 3 and the upper left corner of 4. ; ; loop_ _diffrn_detector_element.detector_id _diffrn_detector_element.id _diffrn_detector_element.center[1] _diffrn_detector_element.center[2] d1 d1_ccd_1 201.5 -1.5 d1 d1_ccd_2 -1.8 -1.5 d1 d1_ccd_3 201.6 201.4 d1 d1_ccd_4 -1.7 201.5 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector_element.center[1] _item_description.description ; The value of '_diffrn_detector_element.center[1]' is the X component of the distortion-corrected beam-centre in mm from the (0, 0) (lower left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. ; _item.name '_diffrn_detector_element.center[1]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.center[2] _item_description.description ; The value of '_diffrn_detector_element.center[2]' is the Y component of the distortion-corrected beam-centre in mm from the (0, 0) (lower left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. ; _item.name '_diffrn_detector_element.center[2]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.id _item_description.description ; The value of '_diffrn_detector_element.id' must uniquely identify each element of a detector. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector_element.id' diffrn_detector_element yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.detector_element_id' '_diffrn_detector_element.id' save_ save__diffrn_detector_element.detector_id _item_description.description ; This item is a pointer to '_diffrn_detector.id' in the DIFFRN_DETECTOR category. ; _item.name '_diffrn_detector_element.detector_id' _item.category_id diffrn_detector_element _item.mandatory_code yes _item_type.code code save_ ######################## ## DIFFRN_MEASUREMENT ## ######################## save_DIFFRN_MEASUREMENT _category.description ; Data items in the DIFFRN_MEASUREMENT category record details about the device used to orient and/or position the crystal during data measurement and the manner in which the diffraction data were measured. ; _category.id diffrn_measurement _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement.device' '_diffrn_measurement.diffrn_id' '_diffrn_measurement.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_measurement.diffrn_id 'd1' _diffrn_measurement.device '3-circle camera' _diffrn_measurement.device_type 'Supper model x' _diffrn_measurement.device_details 'none' _diffrn_measurement.method 'omega scan' _diffrn_measurement.details ; Need new example here ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991). Acta Cryst. C47, 2276-2277]. ; ; _diffrn_measurement.diffrn_id 's1' _diffrn_measurement.device_type 'Philips PW1100/20 diffractometer' _diffrn_measurement.method 'theta/2theta (\q/2\q)' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_measurement.device _item_description.description ; The general class of goniometer or device used to support and orient the specimen. If the value of '_diffrn_measurement.device' is not given, it is implicitly equal to the value of '_diffrn_measurement.diffrn_id'. Either '_diffrn_measurement.device' or '_diffrn_measurement.id' may be used to link to other categories. If the experimental setup admits multiple devices, then '_diffrn_measurement.id' is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.device' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_device' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement.device' _item_aliases.alias_name '_diffrn_measurement_device' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '3-circle camera' '4-circle camera' 'kappa-geometry camera' 'oscillation camera' 'precession camera' save_ save__diffrn_measurement.device_details _item_description.description ; A description of special aspects of the device used to measure the diffraction intensities. ; _item.name '_diffrn_measurement.device_details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; commercial goniometer modified locally to allow for 90\% \t arc ; save_ save__diffrn_measurement.device_type _item_description.description ; The make, model or name of the measurement device (goniometer) used. ; _item.name '_diffrn_measurement.device_type' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Supper model q' 'Huber model r' 'Enraf-Nonius model s' 'homemade' save_ save__diffrn_measurement.diffrn_id _item_description.description ; This data item is a pointer to '_diffrn.id' in the DIFFRN category. ; _item.name '_diffrn_measurement.diffrn_id' _item.mandatory_code yes save_ save__diffrn_measurement.details _item_description.description ; A description of special aspects of the intensity measurement. ; _item.name '_diffrn_measurement.details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; save_ save__diffrn_measurement.id _item_description.description ; The value of '_diffrn_measurement.id' must uniquely identify the set of mechanical characteristics of the device used to orient and/or position the sample used during collection of each diffraction data set. If the value of '_diffrn_measurement.id' is not given, it is implicitly equal to the value of '_diffrn_measurement.diffrn_id'. Either '_diffrn_measurement.device' or '_diffrn_measurement.id' may be used to link to other categories. If the experimental setup admits multiple devices, then '_diffrn_measurement.id' is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.id' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_id' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement.id' _item_type.code code save_ save__diffrn_measurement.method _item_description.description ; Method used to measure intensities. ; _item.name '_diffrn_measurement.method' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_method' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'profile data from theta/2theta (\q/2\q) scans' save_ save__diffrn_measurement.number_of_axes _item_description.description ; The value of '_diffrn_measurement.number_of_axes' gives the number of axes of the positioner for the goniometer or other sample orientation or positioning device identified by '_diffrn_measurement.id'. The description of the axes should be provided by entries in DIFFRN_MEASUREMENT_AXIS. ; _item.name '_diffrn_measurement.number_of_axes' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_measurement.specimen_support _item_description.description ; The physical device used to support the crystal during data collection. ; _item.name '_diffrn_measurement.specimen_support' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_specimen_support' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'glass capillary' 'quartz capillary' 'fiber' 'metal loop' save_ ########################### # DIFFRN_MEASUREMENT_AXIS # ########################### save_DIFFRN_MEASUREMENT_AXIS _category.description ; Data items in the DIFFRN_MEASUREMENT_AXIS category associate axes with goniometers. ; _category.id diffrn_measurement_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_measurement_axis.axis_id _item_description.description ; This data item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_diffrn_measurement_axis.axis_id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.measurement_device _item_description.description ; This data item is a pointer to '_diffrn_measurement.device' in the DIFFRN_MEASUREMENT category. ; _item.name '_diffrn_measurement_axis.measurement_device' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit _item_type.code text save_ save__diffrn_measurement_axis.measurement_id _item_description.description ; This data item is a pointer to '_diffrn_measurement.id' in the DIFFRN_MEASUREMENT category. This item was previously named '_diffrn_measurement_axis.id' which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_measurement_axis.measurement_id' _item.category_id diffrn_measurement_axis _item_aliases.alias_name '_diffrn_measurement_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0.00 _item.mandatory_code implicit _item_type.code code save_ #################### # DIFFRN_RADIATION # #################### save_DIFFRN_RADIATION _category.description ; Data items in the DIFFRN_RADIATION category describe the radiation used in measuring diffraction intensities, its collimation and monochromatisation before the sample. Post-sample treatment of the beam is described by data items in the DIFFRN_DETECTOR category. ; _category.id diffrn_radiation _category.mandatory_code no _category_key.name '_diffrn_radiation.diffrn_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_radiation.diffrn_id 'set1' _diffrn_radiation.collimation '0.3 mm double pinhole' _diffrn_radiation.monochromator 'graphite' _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.wavelength_id 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991). Acta Cryst. C47, 2276-2277]. ; ; _diffrn_radiation.wavelength_id 1 _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.monochromator 'graphite' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_radiation.collimation _item_description.description ; The collimation or focusing applied to the radiation. ; _item.name '_diffrn_radiation.collimation' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_collimation' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '0.3 mm double-pinhole' '0.5 mm' 'focusing mirrors' save_ save__diffrn_radiation.diffrn_id _item_description.description ; This data item is a pointer to '_diffrn.id' in the DIFFRN category. ; _item.name '_diffrn_radiation.diffrn_id' _item.mandatory_code yes save_ save__diffrn_radiation.div_x_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory X axis (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the esd of the directions of photons in the X-Z plane around the mean source beam direction. Note that some synchrotrons specify this value in milliradians, in which case a conversion would be needed. To go from a value in milliradians to a value in degrees, multiply by 0.180 and divide by \p. ; _item.name '_diffrn_radiation.div_x_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.div_y_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory Y axis (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the esd of the directions of photons in the Y-Z plane around the mean source beam direction. Note that some synchrotrons specify this value in milliradians, in which case a conversion would be needed. To go from a value in milliradians to a value in degrees, multiply by 0.180 and divide by \p. ; _item.name '_diffrn_radiation.div_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.div_x_y_source _item_description.description ; Beam crossfire correlation degrees^2^ between the crossfire laboratory X-axis component and the crossfire laboratory Y-axis component (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the mean of the products of the deviations of the direction of each photons in X-Z plane times the deviations of the direction of the same photon in the Y-Z plane around the mean source beam direction. This will be zero for uncorrelated crossfire. Note that some synchrotrons specify this value in milliradians^2^, in which case a conversion would be needed. To go from a value in milliradians^2^ to a value in degrees^2^, multiply by 0.180^2^ and divide by \p^2^. ; _item.name '_diffrn_radiation.div_x_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees_squared _item_default.value 0.0 save_ save__diffrn_radiation.filter_edge _item_description.description ; Absorption edge in \%Angstroms of the radiation filter used. ; _item.name '_diffrn_radiation.filter_edge' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_filter_edge' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__diffrn_radiation.inhomogeneity _item_description.description ; Half-width in millimetres of the incident beam in the direction perpendicular to the diffraction plane. ; _item.name '_diffrn_radiation.inhomogeneity' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_inhomogeneity' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code millimetres save_ save__diffrn_radiation.monochromator _item_description.description ; The method used to obtain monochromatic radiation. If a monochromator crystal is used the material and the indices of the Bragg reflection are specified. ; _item.name '_diffrn_radiation.monochromator' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_monochromator' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Zr filter' 'Ge 220' 'none' 'equatorial mounted graphite' save_ save__diffrn_radiation.polarisn_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the perpendicular component of the polarisation and the diffraction plane. See _diffrn_radiation_polarisn_ratio. ; _item.name '_diffrn_radiation.polarisn_norm' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_norm' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.polarisn_ratio _item_description.description ; Polarisation ratio of the diffraction beam incident on the crystal. It is the ratio of the perpendicularly polarised to the parallel polarised component of the radiation. The perpendicular component forms an angle of '_diffrn_radiation.polarisn_norm' to the normal to the diffraction plane of the sample (i.e. the plane containing the incident and reflected beams). ; _item.name '_diffrn_radiation.polarisn_ratio' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_ratio' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__diffrn_radiation.polarizn_source_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the normal to the polarization plane and the laboratory Y axis as defined in the AXIS category. Note that this is the angle of polarization of the source photons, either directly from a synchrotron beamline or from a monchromater. This differs from the value of '_diffrn_radiation.polarisn_norm' in that '_diffrn_radiation.polarisn_norm' refers to polarization relative to the diffraction plane rather than to the laboratory axis system. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane should be taken as the X-Z plane, and the angle as 0. See '_diffrn_radiation.polarizn_source_ratio'. ; _item.name '_diffrn_radiation.polarizn_source_norm' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.polarizn_source_ratio _item_description.description ; (Ip-In)/(Ip+In), where Ip is the intensity (amplitude squared) of the electric vector in the plane of polarization and In is the intensity (amplitude squared) of the electric vector in plane of the normal to the plane of polarization. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane is be taken as the X-Z plane, and the normal is parallel to the Y-axis. Thus, if we had complete polarization in the plane of polarization, the value of '_diffrn_radiation.polarizn_source_ratio' would be 1, and an unpolarized beam would have a value of 0. If the X-axis has been chosen to lie in the plane of polarization, this definition will agree with the definition of "MONOCHROMATOR" in the Denzo glossary, and values of near 1 should be expected for a bending magnet source. However, if the X-axis were, for some reason to be, say, perpendicular to the polarization plane (not a common choice), then the Denzo value would be the negative of '_diffrn_radiation.polarizn_source_ratio'. See http://www.hkl-xray.com for information on Denzo, and Z. Otwinowski and W. Minor, "Processing of X-ray Diffraction Data Collected in Oscillation Mode", Methods in Enzymology, Volume 276: Macromolecular Crystallography, part A, p.307-326, 1997,C.W. Carter, Jr. & R. M. Sweet, Eds., Academic Press. This differs both in the choice of ratio and choice of orientation from '_diffrn_radiation.polarisn_ratio', which, unlike '_diffrn_radiation.polarizn_source_ratio', is unbounded. ; _item.name '_diffrn_radiation.polarizn_source_ratio' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 -1.0 -1.0 -1.0 _item_type.code float save_ save__diffrn_radiation.probe _item_description.description ; Name of the type of radiation used. It is strongly encouraged that this field be specified so that the probe radiation can be simply determined. ; _item.name '_diffrn_radiation.probe' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_probe' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value 'x-ray' 'neutron' 'electron' 'gamma' save_ save__diffrn_radiation.type _item_description.description ; The nature of the radiation. This is typically a description of the X-ray wavelength in Siegbahn notation. ; _item.name '_diffrn_radiation.type' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'CuK\a' 'Cu K\a~1~' 'Cu K-L~2,3~' 'white-beam' save_ save__diffrn_radiation.xray_symbol _item_description.description ; The IUPAC symbol for the X-ray wavelength for probe radiation. ; _item.name '_diffrn_radiation.xray_symbol' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_xray_symbol' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value _item_enumeration.detail 'K-L~3~' 'K\a~1~ in older Siegbahn notation' 'K-L~2~' 'K\a~2~ in older Siegbahn notation' 'K-M~3~' 'K\b~1~ in older Siegbahn notation' 'K-L~2,3~' 'use where K-L~3~ and K-L~2~ are not resolved' save_ save__diffrn_radiation.wavelength_id _item_description.description ; This data item is a pointer to '_diffrn_radiation_wavelength.id' in the DIFFRN_RADIATION_WAVELENGTH category. ; _item.name '_diffrn_radiation.wavelength_id' _item.category_id diffrn_radiation _item.mandatory_code yes _item_type.code code save_ ################ # DIFFRN_REFLN # ################ save_DIFFRN_REFLN _category.description ; This category redefinition has been added to extend the key of the standard DIFFRN_REFLN category. ; _category.id diffrn_refln _category.mandatory_code no _category_key.name '_diffrn_refln.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_refln.frame_id _item_description.description ; This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_refln.frame_id' _item.category_id diffrn_refln _item.mandatory_code yes _item_type.code code save_ ############### # DIFFRN_SCAN # ############### save_DIFFRN_SCAN _category.description ; Data items in the DIFFRN_SCAN category describe the parameters of one or more scans, relating axis positions to frames. ; _category.id diffrn_scan _category.mandatory_code no _category_key.name '_diffrn_scan.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - derived from a suggestion by R. M. Sweet. The vector of each axis is not given here, because it is provided in the AXIS category. By making '_diffrn_scan_axis.scan_id' and '_diffrn_scan_axis.axis_id' keys of the DIFFRN_SCAN_AXIS category, an arbitrary number of scanning and fixed axes can be specified for a scan. We have specified three rotation axes and one translation axis at non-zero values, with one axis stepping. There is no reason why more axes could not have been specified to step. We have specified range information, but note that it is redundant from the number of frames and the increment, so we could drop the data item '_diffrn_scan_axis.angle_range'. We have specified both the sweep data and the data for a single frame. Note that the information on how the axes are stepped is given twice, once in terms of the overall averages in the value of '_diffrn_scan.integration_time' and the values for DIFFRN_SCAN_AXIS, and precisely for the given frame in the value for '_diffrn_scan_frame.integration_time' and the values for DIFFRN_SCAN_FRAME_AXIS. If dose-related adjustements are made to scan times and non-linear stepping is done, these values may differ. Therefore, in interpreting the data for a particular frame it is important to use the frame-specific data. ; ; _diffrn_scan.id 1 _diffrn_scan.date_start '2001-11-18T03:26:42' _diffrn_scan.date_end '2001-11-18T03:36:45' _diffrn_scan.integration_time 3.0 _diffrn_scan.frame_id_start mad_L2_000 _diffrn_scan.frame_id_end mad_L2_200 _diffrn_scan.frames 201 loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment 1 omega 200.0 20.0 0.1 . . . 1 kappa -40.0 0.0 0.0 . . . 1 phi 127.5 0.0 0.0 . . . 1 tranz . . . 2.3 0.0 0.0 _diffrn_scan_frame.scan_id 1 _diffrn_scan_frame.date '2001-11-18T03:27:33' _diffrn_scan_frame.integration_time 3.0 _diffrn_scan_frame.frame_id mad_L2_018 _diffrn_scan_frame.frame_number 18 loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.angle_increment _diffrn_scan_frame_axis.displacement _diffrn_scan_frame_axis.displacement_increment mad_L2_018 omega 201.8 0.1 . . mad_L2_018 kappa -40.0 0.0 . . mad_L2_018 phi 127.5 0.0 . . mad_L2_018 tranz . . 2.3 0.0 ; ; Example 2 - a more extensive example, R. M. Sweet, P. Ellis, H. Bernstein. We place a detector 240 mm along the Z axis from the goniometer. This presents us with a choice -- either we define the axes of the detector at the origin, and then put a Z setting of -240 in for the actual use, or we define the axes with the necessary Z-offset. In this case we use the setting, and leave the offset as zero. We call this axis DETECTOR_Z. The axis for positioning the detector in the Y-direction depends on the detector Z-axis. We call this axis, DETECTOR_Y. The axis for positioning the detector in the X-direction depends on the detector Y-axis (and therefore on the detector Z-axis). We call this axis DETECTOR_X. This detector may be rotated around the Y-axis. This rotation axis depends on the three translation axes. We call it DETECTOR_PITCH. We define a coordinate system on the face of the detector in terms of 2300 0.150 mm pixels in each direction. The ELEMENT_X axis is used to index the first array index of the data array and the ELEMENT_Y axis is used to index the second array index. Because the pixels are 0.150mm x 0.150mm, the centre of the first pixel is at (0.075, 0.075) in this coordinate system. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 172.43 -172.43 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 2300 1 increasing ELEMENT_X ARRAY1 2 2300 2 increasing ELEMENT_Y # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.075 0.150 ELEMENT_Y ELEMENT_Y 0.075 0.150 # category ARRAY_ELEMENT_SIZE loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 ARRAY1 2 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; ; Example 3 - Example 2 revised for a spiral scan, R. M. Sweet, P. Ellis, H. Bernstein. We place a detector 240 mm along the Z axis from the goniometer, as in Example 2, above, but in this example, the image plate is scanned in a spiral pattern outside edge in. The axis for positioning the detector in the Y-direction depends on the detector Z-axis. We call this axis, DETECTOR_Y. The axis for positioning the detector in the X-direction depends on the detector Y-axis (and therefore on the detector Z-axis). We call this axis DETECTOR_X. This detector may be rotated around the Y-axis. This rotation axis depends on the three translation axes. We call it DETECTOR_PITCH. We define a coordinate system on the face of the detector in terms of a coupled rotation axis and radial scan axis to form a spiral scan. Let us call rotation axis ELEMENT_ROT, and the radial axis ELEMENT_RAD. We assume 150 um radial pitch and 75 um 'constant velocity' angular pitch. We index first on the rotation axis and make the radial axis dependent on it. The two axes are coupled to form an axis set ELEMENT_SPIRAL. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_ROT translation detector DETECTOR_PITCH 0 0 1 0 0 0 ELEMENT_RAD translation detector ELEMENT_ROT 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.angle _array_structure_list_axis.displacement _array_structure_list_axis.angular_pitch _array_structure_list_axis.radial_pitch ELEMENT_SPIRAL ELEMENT_ROT 0 . 0.075 . ELEMENT_SPIRAL ELEMENT_RAD . 172.5 . -0.150 # category ARRAY_ELEMENT_SIZE # the actual pixels are 0.075 by 0.150 mm # We give the coarser dimension here. loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_scan.id _item_description.description ; The value of '_diffrn_scan.id' uniquely identifies each scan. The identifier is used to tie together all the information about the scan. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_scan.id' diffrn_scan yes '_diffrn_scan_axis.scan_id' diffrn_scan_axis yes '_diffrn_scan_frame.scan_id' diffrn_scan_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_scan_axis.scan_id' '_diffrn_scan.id' '_diffrn_scan_frame.scan_id' '_diffrn_scan.id' save_ save__diffrn_scan.date_end _item_description.description ; The date and time of the end of the scan. Note that this may be an estimate generated during the scan, before the precise time of the end of the scan is known. ; _item.name '_diffrn_scan.date_end' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.date_start _item_description.description ; The date and time of the start of the scan. ; _item.name '_diffrn_scan.date_start' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.integration_time _item_description.description ; Approximate average time in seconds to integrate each step of the scan. The precise time for integration of each particular step must be provided in '_diffrn_scan_frame.integration_time', even if all steps have the same integration time. ; _item.name '_diffrn_scan.integration_time' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan.frame_id_start _item_description.description ; The value of this data item is the identifier of the first frame in the scan. This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_start' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frame_id_end _item_description.description ; The value of this data item is the identifier of the last frame in the scan. This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_end' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frames _item_description.description ; The value of this data item is the number of frames in the scan. ; _item.name '_diffrn_scan.frames' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 1 1 1 save_ #################### # DIFFRN_SCAN_AXIS # #################### save_DIFFRN_SCAN_AXIS _category.description ; Data items in the DIFFRN_SCAN_AXIS category describe the settings of axes for particular scans. Unspecified axes are assumed to be at their zero points. ; _category.id diffrn_scan_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_axis.scan_id' '_diffrn_scan_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_axis.scan_id _item_description.description ; The value of this data item is the identifier of the scan for which axis settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan.id'. This item is a pointer to '_diffrn_scan.id' in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_axis.scan_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the scan for which settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan.id'. This item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_diffrn_scan_axis.axis_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.angle_start _item_description.description ; The starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_range _item_description.description ; The range from the starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_increment _item_description.description ; The increment for each step for the specified axis in degrees. In general, this will agree with '_diffrn_scan_frame_axis.angle_increment'. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.angle_increment' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.angle_increment' (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_rstrt_incr _item_description.description ; The increment after each step for the specified axis in degrees. In general, this will agree with '_diffrn_scan_frame_axis.angle_rstrt_incr'. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' and '_diffrn_scan_frame_axis.angle_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame, and should equal '_diffrn_scan_frame_axis.angle' for that next frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.angle_rstrt_incr' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.angle_rstrt_incr' (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.displacement_start _item_description.description ; The starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_range _item_description.description ; The range from the starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_increment _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with '_diffrn_scan_frame_axis.displacement_increment'. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.displacement_increment' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.displacement_increment' (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_rstrt_incr _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with '_diffrn_scan_frame_axis.displacement_rstrt_incr'. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' and '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame, and should equal '_diffrn_scan_frame_axis.displacement' for that next frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.displacement_rstrt_incr' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.displacement_rstrt_incr' (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ ##################### # DIFFRN_SCAN_FRAME # ##################### save_DIFFRN_SCAN_FRAME _category.description ; Data items in the DIFFRN_SCAN_FRAME category describe the relationship of particular frames to scans. ; _category.id diffrn_scan_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame.scan_id' '_diffrn_scan_frame.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame.date _item_description.description ; The date and time of the start of the frame being scanned. ; _item.name '_diffrn_scan_frame.date' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan_frame.frame_id _item_description.description ; The value of this data item is the identifier of the frame being examined. This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame.frame_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame.frame_number _item_description.description ; The value of this data item is the number of the frame within the scan, starting with 1. It is not necessarily the same as the value of '_diffrn_scan_frame.frame_id', but may be. ; _item.name '_diffrn_scan_frame.frame_number' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 0 0 0 save_ save__diffrn_scan_frame.integration_time _item_description.description ; The time in seconds to integrate this step of the scan. This should be the precise time of integration of each particular frame. The value of this data item should be given explicitly for each frame and not inferred from the value of '_diffrn_scan.integration_time'. ; _item.name '_diffrn_scan_frame.integration_time' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame.scan_id _item_description.description ; The value of '_diffrn_scan_frame.scan_id' identifies the scan containing this frame. This item is a pointer to '_diffrn_scan.id' in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_frame.scan_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ ########################## # DIFFRN_SCAN_FRAME_AXIS # ########################## save_DIFFRN_SCAN_FRAME_AXIS _category.description ; Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the settings of axes for particular frames. Unspecified axes are assumed to be at their zero points. If, for any given frame, non-zero values apply for any of the data items in this category, those values should be given explicitly in this category and not simply inferred from values in DIFFRN_SCAN_AXIS. ; _category.id diffrn_scan_frame_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame_axis.frame_id' '_diffrn_scan_frame_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the frame for which settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan_frame.frame_id'. This item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_diffrn_scan_frame_axis.axis_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_axis.angle _item_description.description ; The setting of the specified axis in degrees for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.angle' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_increment _item_description.description ; The increment for this frame for angular setting of the specified axis in degrees. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.angle_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_rstrt_incr _item_description.description ; The increment after this frame for angular setting of the specified axis in degrees. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' and '_diffrn_scan_frame_axis.angle_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame, and should equal '_diffrn_scan_frame_axis.angle' for that next frame. ; _item.name '_diffrn_scan_frame_axis.angle_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.displacement' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_increment _item_description.description ; The increment for this frame for displacement setting of the specified axis in millimetres. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.displacement_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_rstrt_incr _item_description.description ; The increment for this frame for displacement setting of the specified axis in millimetres. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' and '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame, and should equal '_diffrn_scan_frame_axis.displacement' for that next frame. ; _item.name '_diffrn_scan_frame_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.frame_id _item_description.description ; The value of this data item is the identifier of the frame for which axis settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan_frame.frame_id'. This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame_axis.frame_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ ######################## DEPRECATED DATA ITEMS ######################## save__diffrn_detector_axis.id _item_description.description ; This data item is a pointer to '_diffrn_detector.id' in the DIFFRN_DETECTOR category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_detector_axis.id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.id _item_description.description ; This data item is a pointer to '_diffrn_measurement.id' in the DIFFRN_MEASUREMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_measurement_axis.id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ ######################### DEPRECATED CATEGORY ######################### ##################### # DIFFRN_FRAME_DATA # ##################### save_DIFFRN_FRAME_DATA _category.description ; Data items in the DIFFRN_FRAME_DATA category record the details about each frame of data. The items in this category are now in the DIFFRN_DATA_FRAME category. The items in the DIFFRN_FRAME_DATA category are now deprecated. The items from this category are provided as aliases in the 1.0.0 dictionary, but should not be used for new work. The items from the old category are provided in this dictionary for completeness, but should not be used or cited. To avoid confusion, the example has been removed, and the redundant parent child-links to other categories removed. ; _category.id diffrn_frame_data _category.mandatory_code no loop_ _category_key.name '_diffrn_frame_data.id' '_diffrn_frame_data.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; THE DIFFRN_FRAME_DATA category is deprecated and should not be used. ; ; # EXAMPLE REMOVED # ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_frame_data.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.array_id' _item.category_id diffrn_frame_data _item.mandatory_code yes _item_type.code code save_ save__diffrn_frame_data.binary_id _item_description.description ; This item is a pointer to '_array_data.binary_id' in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.binary_id' _item.category_id diffrn_frame_data _item.mandatory_code implicit _item_type.code int save_ save__diffrn_frame_data.detector_element_id _item_description.description ; This item is a pointer to '_diffrn_detector_element.id' in the DIFFRN_DETECTOR_ELEMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.detector_element_id' _item.category_id diffrn_frame_data _item.mandatory_code yes _item_type.code code save_ save__diffrn_frame_data.id _item_description.description ; The value of '_diffrn_frame_data.id' must uniquely identify each complete frame of data. DEPRECATED -- DO NOT USE ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_frame_data.id' diffrn_frame_data yes _item_type.code code save_ ################ END DEPRECATED SECTION ########### #################### ## ITEM_TYPE_LIST ## #################### # # # The regular expressions defined here are not compliant # with the POSIX 1003.2 standard as they include the # '\n' and '\t' special characters. These regular expressions # have been tested using version 0.12 of Richard Stallman's # GNU regular expression library in POSIX mode. # In order to allow presentation of a regular expression # in a text field concatenate any line ending in a backslash # with the following line, after discarding the backslash. # # A formal definition of the '\n' and '\t' special characters # is most properly done in the DDL, but for completeness, please # note that '\n' is the line termination character ('newline') # and '\t' is the horizontal tab character. There is a formal # ambiguity in the use of '\n' for line termination, in that # the intention is that the equivalent machine/OS-dependent line # termination character sequence should be accepted as a match, e.g. # # '\r' (control-M) under MacOS # '\n' (control-J) under Unix # '\r\n' (control-M control-J) under DOS and MS Windows # loop_ _item_type_list.code _item_type_list.primitive_code _item_type_list.construct _item_type_list.detail code char '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words ... ; ucode uchar '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words (case insensitive) ; line char '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types / multi-word items ... ; uline uchar '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types / multi-word items (case insensitive) ; text char '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; text item types / multi-line text ... ; binary char ;\n--CIF-BINARY-FORMAT-SECTION--\n\ [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\ \n--CIF-BINARY-FORMAT-SECTION---- ; ; binary items are presented as MIME-like ascii-encoded sections in an imgCIF. In a CBF, raw octet streams are used to convey the same information. ; int numb '-?[0-9]+' ; int item types are the subset of numbers that are the negative or positive integers. ; float numb '-?(([0-9]+)|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?' ; float item types are the subset of numbers that are the floating numbers. ; any char '.*' ; A catch all for items that may take any form... ; yyyy-mm-dd char ;\ [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9][0-9]\ (T[0-2][0-9]:[0-5][0-9]:[0-5][0-9](.[0-9]+)([+-][0-5][0-9]:[0-5][0-9])) ; ; Standard format for CIF date and time strings (see http://www.iucr.org/iucr-top/cif/spec/datetime.html), consisting of a yyyy-mm-dd date optionally followed by the character "T" followed by a 24-hour clock time, optionally followed by a signed time-zone offset. The IUCr standard has been extended to allow for an optional decimal fraction on the seconds of time. Time is local time if no time-zone offset is given. ; ##################### ## ITEM_UNITS_LIST ## ##################### loop_ _item_units_list.code _item_units_list.detail # 'metres' 'metres' 'centimetres' 'centimetres (metres * 10^( -2)^)' 'millimetres' 'millimetres (metres * 10^( -3)^)' 'nanometres' 'nanometres (metres * 10^( -9)^)' 'angstroms' '\%Angstroms (metres * 10^(-10)^)' 'picometres' 'picometres (metres * 10^(-12)^)' 'femtometres' 'femtometres (metres * 10^(-15)^)' # 'reciprocal_metres' 'reciprocal metres (metres^(-1)^)' 'reciprocal_centimetres' 'reciprocal centimetres ((metres * 10^( -2))^(-1)^)' 'reciprocal_millimetres' 'reciprocal millimetres ((metres * 10^( -3))^(-1)^)' 'reciprocal_nanometres' 'reciprocal nanometres ((metres * 10^( -9))^(-1)^)' 'reciprocal_angstroms' 'reciprocal angstroms ((metres * 10^(-10))^(-1)^)' 'reciprocal_picometres' 'reciprocal picometres ((metres * 10^(-12))^(-1)^)' # 'nanometres_squared' 'nanometres squared (metres * 10^( -9)^)^2^' 'angstroms_squared' '\%Angstroms squared (metres * 10^(-10)^)^2^' '8pi2_angstroms_squared' '8\p^2^ * \%Angstroms squared (metres * 10^(-10)^)^2^' 'picometres_squared' 'picometres squared (metres * 10^(-12)^)^2^' # 'nanometres_cubed' 'nanometres cubed (metres * 10^( -9)^)^3^' 'angstroms_cubed' '\%Angstroms cubed (metres * 10^(-10)^)^3^' 'picometres_cubed' 'picometres cubed (metres * 10^(-12)^)^3^' # 'kilopascals' 'kilopascals' 'gigapascals' 'gigapascals' # 'hours' 'hours' 'minutes' 'minutes' 'seconds' 'seconds' 'microseconds' 'microseconds' # 'degrees' 'degrees (of arc)' 'degrees_squared' 'degrees (of arc) squared' # 'degrees_per_minute' 'degrees (of arc) per minute' # 'celsius' 'degrees (of temperature) Celsius' 'kelvins' 'degrees (of temperature) Kelvin' # 'counts' 'counts' 'counts_per_photon' 'counts per photon' # 'electrons' 'electrons' # 'electrons_squared' 'electrons squared' # 'electrons_per_nanometres_cubed' ; electrons per nanometres cubed (electrons/(metres * 10^( -9)^)^(-3)^) ; 'electrons_per_angstroms_cubed' ; electrons per angstroms cubed (electrons/(metres * 10^(-10)^)^(-3)^) ; 'electrons_per_picometres_cubed' ; electrons per picometres cubed (electrons/(metres * 10^(-12)^)^(-3)^) ; 'kilowatts' 'kilowatts' 'milliamperes' 'milliamperes' 'kilovolts' 'kilovolts' # 'arbitrary' ; arbitrary system of units. ; # loop_ _item_units_conversion.from_code _item_units_conversion.to_code _item_units_conversion.operator _item_units_conversion.factor ### 'metres' 'centimetres' '*' 1.0E+02 'metres' 'millimetres' '*' 1.0E+03 'metres' 'nanometres' '*' 1.0E+09 'metres' 'angstroms' '*' 1.0E+10 'metres' 'picometres' '*' 1.0E+12 'metres' 'femtometres' '*' 1.0E+15 # 'centimetres' 'metres' '*' 1.0E-02 'centimetres' 'millimetres' '*' 1.0E+01 'centimetres' 'nanometres' '*' 1.0E+07 'centimetres' 'angstroms' '*' 1.0E+08 'centimetres' 'picometres' '*' 1.0E+10 'centimetres' 'femtometres' '*' 1.0E+13 # 'millimetres' 'metres' '*' 1.0E-03 'millimetres' 'centimetres' '*' 1.0E-01 'millimetres' 'nanometres' '*' 1.0E+06 'millimetres' 'angstroms' '*' 1.0E+07 'millimetres' 'picometres' '*' 1.0E+09 'millimetres' 'femtometres' '*' 1.0E+12 # 'nanometres' 'metres' '*' 1.0E-09 'nanometres' 'centimetres' '*' 1.0E-07 'nanometres' 'millimetres' '*' 1.0E-06 'nanometres' 'angstroms' '*' 1.0E+01 'nanometres' 'picometres' '*' 1.0E+03 'nanometres' 'femtometres' '*' 1.0E+06 # 'angstroms' 'metres' '*' 1.0E-10 'angstroms' 'centimetres' '*' 1.0E-08 'angstroms' 'millimetres' '*' 1.0E-07 'angstroms' 'nanometres' '*' 1.0E-01 'angstroms' 'picometres' '*' 1.0E+02 'angstroms' 'femtometres' '*' 1.0E+05 # 'picometres' 'metres' '*' 1.0E-12 'picometres' 'centimetres' '*' 1.0E-10 'picometres' 'millimetres' '*' 1.0E-09 'picometres' 'nanometres' '*' 1.0E-03 'picometres' 'angstroms' '*' 1.0E-02 'picometres' 'femtometres' '*' 1.0E+03 # 'femtometres' 'metres' '*' 1.0E-15 'femtometres' 'centimetres' '*' 1.0E-13 'femtometres' 'millimetres' '*' 1.0E-12 'femtometres' 'nanometres' '*' 1.0E-06 'femtometres' 'angstroms' '*' 1.0E-05 'femtometres' 'picometres' '*' 1.0E-03 ### 'reciprocal_centimetres' 'reciprocal_metres' '*' 1.0E+02 'reciprocal_centimetres' 'reciprocal_millimetres' '*' 1.0E-01 'reciprocal_centimetres' 'reciprocal_nanometres' '*' 1.0E-07 'reciprocal_centimetres' 'reciprocal_angstroms' '*' 1.0E-08 'reciprocal_centimetres' 'reciprocal_picometres' '*' 1.0E-10 # 'reciprocal_millimetres' 'reciprocal_metres' '*' 1.0E+03 'reciprocal_millimetres' 'reciprocal_centimetres' '*' 1.0E+01 'reciprocal_millimetres' 'reciprocal_nanometres' '*' 1.0E-06 'reciprocal_millimetres' 'reciprocal_angstroms' '*' 1.0E-07 'reciprocal_millimetres' 'reciprocal_picometres' '*' 1.0E-09 # 'reciprocal_nanometres' 'reciprocal_metres' '*' 1.0E+09 'reciprocal_nanometres' 'reciprocal_centimetres' '*' 1.0E+07 'reciprocal_nanometres' 'reciprocal_millimetres' '*' 1.0E+06 'reciprocal_nanometres' 'reciprocal_angstroms' '*' 1.0E-01 'reciprocal_nanometres' 'reciprocal_picometres' '*' 1.0E-03 # 'reciprocal_angstroms' 'reciprocal_metres' '*' 1.0E+10 'reciprocal_angstroms' 'reciprocal_centimetres' '*' 1.0E+08 'reciprocal_angstroms' 'reciprocal_millimetres' '*' 1.0E+07 'reciprocal_angstroms' 'reciprocal_nanometres' '*' 1.0E+01 'reciprocal_angstroms' 'reciprocal_picometres' '*' 1.0E-02 # 'reciprocal_picometres' 'reciprocal_metres' '*' 1.0E+12 'reciprocal_picometres' 'reciprocal_centimetres' '*' 1.0E+10 'reciprocal_picometres' 'reciprocal_millimetres' '*' 1.0E+09 'reciprocal_picometres' 'reciprocal_nanometres' '*' 1.0E+03 'reciprocal_picometres' 'reciprocal_angstroms' '*' 1.0E+01 ### 'nanometres_squared' 'angstroms_squared' '*' 1.0E+02 'nanometres_squared' 'picometres_squared' '*' 1.0E+06 # 'angstroms_squared' 'nanometres_squared' '*' 1.0E-02 'angstroms_squared' 'picometres_squared' '*' 1.0E+04 'angstroms_squared' '8pi2_angstroms_squared' '*' 78.9568 # 'picometres_squared' 'nanometres_squared' '*' 1.0E-06 'picometres_squared' 'angstroms_squared' '*' 1.0E-04 ### 'nanometres_cubed' 'angstroms_cubed' '*' 1.0E+03 'nanometres_cubed' 'picometres_cubed' '*' 1.0E+09 # 'angstroms_cubed' 'nanometres_cubed' '*' 1.0E-03 'angstroms_cubed' 'picometres_cubed' '*' 1.0E+06 # 'picometres_cubed' 'nanometres_cubed' '*' 1.0E-09 'picometres_cubed' 'angstroms_cubed' '*' 1.0E-06 ### 'kilopascals' 'gigapascals' '*' 1.0E-06 'gigapascals' 'kilopascals' '*' 1.0E+06 ### 'hours' 'minutes' '*' 6.0E+01 'hours' 'seconds' '*' 3.6E+03 'hours' 'microseconds' '*' 3.6E+09 # 'minutes' 'hours' '/' 6.0E+01 'minutes' 'seconds' '*' 6.0E+01 'minutes' 'microseconds' '*' 6.0E+07 # 'seconds' 'hours' '/' 3.6E+03 'seconds' 'minutes' '/' 6.0E+01 'seconds' 'microseconds' '*' 1.0E+06 # 'microseconds' 'hours' '/' 3.6E+09 'microseconds' 'minutes' '/' 6.0E+07 'microseconds' 'seconds' '/' 1.0E+06 ### 'celsius' 'kelvins' '-' 273.0 'kelvins' 'celsius' '+' 273.0 ### 'electrons_per_nanometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E+03 'electrons_per_nanometres_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+09 # 'electrons_per_angstroms_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-03 'electrons_per_angstroms_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+06 # 'electrons_per_picometres_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-09 'electrons_per_picometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E-06 ### ######################## ## DICTIONARY_HISTORY ## ######################## loop_ _dictionary_history.version _dictionary_history.update _dictionary_history.revision 1.3.1 2003-08-13 ; Changes as per Frances C. Bernstein. + Identify initials. + Adopt British spelling for centre in text. + Set \p and \%Angstrom and powers. + Clean up commas and unclear wordings. + Clean up tenses in history. Changes as per Gotzon Madariaga. + Fix the ARRAY_DATA example to align '_array_data.binary_id' and X-Binary-Id. + Add a range to '_array_intensities.gain_esd'. + In the example of DIFFRN_DETECTOR_ELEMENT, '_diffrn_detector_element.id' and '_diffrn_detector_element.detector_id' interchanged. + Fix typos for direction, detector and axes. + Clarify description of polarisation. + Clarify axes in '_diffrn_detector_element.center[1]' '_diffrn_detector_element.center[2]'. + Add local item types for items that are pointers. (HJB) ; 1.3.0 2003-07-24 ; Changes as per Brian McMahon. + Consistently quote tags embedded in text. + Clean up introductory comments. + Adjust line lengths to fit in 80 character window. + Fix several descriptions in AXIS category which referred to '_axis.type' instead of the current item. + Fix erroneous use of deprecated item '_diffrn_detector_axis.id' in examples for DIFFRN_SCAN_AXIS. + Add deprecated items '_diffrn_detector_axis.id' and '_diffrn_measurement_axis.id'. (HJB) ; 1.2.4 2003-07-14 ; Changes as per I. David Brown. + Enhance descriptions in DIFFRN_SCAN_AXIS to make them less dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS. + Provide a copy of the deprecated DIFFRN_FRAME_DATA category for completeness. (HJB) ; 1.2.3 2003-07-03 ; Cleanup to conform to ITVG. + Correct sign error in ..._cubed units. + Correct '_diffrn_radiation.polarisn_norm' range. (HJB) ; 1.2.2 2003-03-10 ; Correction of typos in various DIFFRN_SCAN_AXIS descriptions. (HJB) ; 1.2.1 2003-02-22 ; Correction of ATOM_ for ARRAY_ typos in various descriptions. (HJB) ; 1.2 2003-02-07 ; Corrections to encodings (remove extraneous hyphens) remove extraneous underscore in '_array_structure.encoding_type' enumeration. Correct typos in items units list. (HJB) ; 1.1.3 2001-04-19 ; Another typo corrections by Wilfred Li, and cleanup by HJB. ; 1.1.2 2001-03-06 ; Several typo corrections by Wilfred Li. ; 1.1.1 2001-02-16 ; Several typo corrections by JW. ; 1.1 2001-02-06 ; Draft resulting from discussions on header for use at NSLS. (HJB) + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME. + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'. + Add '_diffrn_measurement_axis.measurement_device' and change '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'. + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source', '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm', '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end', '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr', '_diffrn_scan_axis.displacement_rstrt_incr', '_diffrn_scan_frame_axis.angle_increment', '_diffrn_scan_frame_axis.angle_rstrt_incr', '_diffrn_scan_frame_axis.displacement', '_diffrn_scan_frame_axis.displacement_increment',and '_diffrn_scan_frame_axis.displacement_rstrt_incr'. + Add '_diffrn_measurement.device' to category key. + Update yyyy-mm-dd to allow optional time with fractional seconds for time stamps. + Fix typos caught by RS. + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to allow for coupled axes, as in spiral scans. + Add examples for fairly complete headers thanks to R. Sweet and P. Ellis. ; 1.0 2000-12-21 ; Release version - few typos and tidying up. (BM & HJB) + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end of dictionary. + Alphabetize dictionary. ; 0.7.1 2000-09-29 ; Cleanup fixes. (JW) + Correct spelling of diffrn_measurement_axis in '_axis.id' + Correct ordering of uses of '_item.mandatory_code' and '_item_default.value'. ; 0.7.0 2000-09-09 ; Respond to comments by I. David Brown. (HJB) + Add further comments on '\n' and '\t'. + Update ITEM_UNITS_LIST by taking section from mmCIF dictionary and adding metres. Change 'meter' to 'metre' throughout. + Add missing enumerations to '_array_structure.compression_type' and make 'none' the default. + Remove parent-child relationship between '_array_structure_list.index' and '_array_structure_list.precedence'. + Improve alphabetization. + Fix '_array_intensities_gain.esd' related function. + Improve comments in AXIS. + Fix DIFFRN_FRAME_DATA example. + Remove erroneous DIFFRN_MEASUREMENT example. + Add '_diffrn_measurement_axis.id' to the category key. ; 0.6.0 1999-01-14 ; Remove redundant information for ENC_NONE data. (HJB) + After the D5 remove binary section identifier, size and compression type. + Add Control-L to header. ; 0.5.1 1999-01-03 ; Cleanup of typos and syntax errors. (HJB) + Cleanup example details for DIFFRN_SCAN category. + Add missing quote marks for '_diffrn_scan.id' definition. ; 0.5 1999-01-01 ; Modifications for axis definitions and reduction of binary header. (HJB) + Restore '_diffrn_detector.diffrn_id' to DIFFRN_DETECTOR KEY. + Add AXIS category. + Bring in complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories from cif_mm.dic for clarity. + Change '_array_structure.encoding_type' from type code to uline and added X-Binary-Element-Type to MIME header. + Add detector beam centre '_diffrn_detector_element.center[1]' and '_diffrn_detector_element.center[2]'. + Correct item name of '_diffrn_refln.frame_id'. + Replace reference to '_array_intensities.undefined' by '_array_intensities.undefined_value'. + Replace references to '_array_intensity.scaling' with '_array_intensities.scaling'. + Add DIFFRN_SCAN... categories. ; 0.4 1998-08-11 ; Modifications to the 0.3 imgCIF draft. (HJB) + Reflow comment lines over 80 characters and corrected typos. + Update examples and descriptions of MIME encoded data. + Change name to cbfext98.dic. ; 0.3 1998-07-04 ; Modifications for imgCIF. (HJB) + Add binary type, which is a text field containing a variant on MIME encoded data. + Change type of '_array_data.data' to binary and specify internal structure of raw binary data. + Add '_array_data.binary_id', and make '_diffrn_frame_data.binary_id' and '_array_intensities.binary_id' into pointers to this item. ; 0.2 1997-12-02 ; Modifications to the CBF draft. (JW) + Add category hierarchy for describing frame data developed from discussions at the BNL imgCIF Workshop Oct 1997. The following changes are made in implementing the workshop draft. Category DIFFRN_ARRAY_DATA is renamed to DIFFRN_FRAME_DATA. Category DIFFRN_FRAME_TYPE is renamed to DIFFRN_DETECTOR_ELEMENT. The parent item for '_diffrn_frame_data.array_id' is changed from '_array_structure_list.array_id' to '_array_structure.id'. Item '_diffrn_detector.array_id' is deleted. + Add data item '_diffrn_frame_data.binary_id' to identify data groups within a binary section. The formal identification of the binary section is still fuzzy. ; 0.1 1997-01-24 ; First draft of this dictionary in DDL 2.1 compliant format by John Westbrook (JW). This version is adapted from the Crystallographic Binary File (CBF) Format Draft Proposal provided by Andy Hammersley (AH). Modifications to the CBF draft. (JW) + In this version the array description has been cast in the categories ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. These categories have been generalized to describe array data of arbitrary dimension. + Array data in this description are contained in the category ARRAY_DATA. This departs from the CBF notion of data existing in some special comment. In this description, data is handled as an ordinary data item encapsulated in a character data type. Although data this manner deviates from CIF conventions, it does not violate any DDL 2.1 rules. DDL 2.1 regular expressions can be used to define the binary representation which will permit some level of data validation. In this version, the placeholder type code "any" has been used. This translates to a regular expression which will match any pattern. It should be noted that DDL 2.1 already supports array data objects although these have not been used in the current mmCIF dictionary. It may be possible to use the DDL 2.1 ITEM_STRUCTURE and ITEM_STRUCTURE_LIST categories to provide the information that is carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. By moving the array structure to the DDL level it would be possible to define an array type as well as a regular expression defining the data format. + Multiple array sections can be properly handled within a single datablock. ; #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof ./CBFlib-0.9.2.2/doc/cif_img_1.3.2.dic0000644000076500007650000054712511603702115015160 0ustar yayayaya############################################################################## # # # Image CIF Dictionary (imgCIF) # # and Crystallographic Binary File Dictionary (CBF) # # Extending the Macromolecular CIF Dictionary (mmCIF) # # # # Version 1.3.2 # # of 2005-06-25 # # # # by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook # # # # This dictionary was adapted from format discussed at the imgCIF Workshop, # # held at BNL Oct 1997 and the Crystallographic Binary File Format Draft # # Proposal by Andrew Hammersley. The first DDL 2.1 Version was created by # # John Westbrook. This version was drafted by Herbert J. Bernstein and # # incorporates comments by I. David Brown, John Westbrook, Brian McMahon, # # Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li, Gotzon Madariaga, # # Frances C. Bernstein and others. # ############################################################################## data_cif_img.dic _dictionary.title cif_img.dic _dictionary.version 1.3.2 _dictionary.datablock_id cif_img.dic ############################################################################## # CONTENTS # # CATEGORY_GROUP_LIST # # category ARRAY_DATA # # _array_data.array_id # _array_data.binary_id # _array_data.data # # category ARRAY_ELEMENT_SIZE # # _array_element_size.array_id # _array_element_size.index # _array_element_size.size # # category ARRAY_INTENSITIES # # _array_intensities.array_id # _array_intensities.binary_id # _array_intensities.gain # _array_intensities.gain_esd # _array_intensities.linearity # _array_intensities.offset # _array_intensities.scaling # _array_intensities.overload # _array_intensities.undefined_value # # category ARRAY_STRUCTURE # # _array_structure.byte_order # _array_structure.compression_type # _array_structure.encoding_type # _array_structure.id # # category ARRAY_STRUCTURE_LIST # # _array_structure_list.axis_set_id # _array_structure_list.array_id # _array_structure_list.dimension # _array_structure_list.direction # _array_structure_list.index # _array_structure_list.precedence # # category ARRAY_STRUCTURE_LIST_AXIS # # _array_structure_list_axis.axis_id # _array_structure_list_axis.axis_set_id # _array_structure_list_axis.angle # _array_structure_list_axis.angle_increment # _array_structure_list_axis.displacement_increment # _array_structure_list_axis.angular_pitch # _array_structure_list_axis.radial_pitch # # category AXIS # # _axis.depends_on # _axis.equipment # _axis.id # _axis.offset[1] # _axis.offset[2] # _axis.offset[3] # _axis.type # _axis.vector[1] # _axis.vector[2] # _axis.vector[3] # # category DIFFRN_DATA_FRAME # # _diffrn_data_frame.array_id # _diffrn_data_frame.binary_id # _diffrn_data_frame.detector_element_id # _diffrn_data_frame.id # # category DIFFRN_DETECTOR # # _diffrn_detector.details # _diffrn_detector.detector # _diffrn_detector.diffrn_id # _diffrn_detector.dtime # _diffrn_detector.id # _diffrn_detector.number_of_axes # _diffrn_detector.type # # category DIFFRN_DETECTOR_AXIS # # _diffrn_detector_axis.axis_id # _diffrn_detector_axis.detector_id # # category DIFFRN_DETECTOR_ELEMENT # # _diffrn_detector_element.center[1] # _diffrn_detector_element.center[2] # _diffrn_detector_element.id # _diffrn_detector_element.detector_id # # category DIFFRN_MEASUREMENT # # _diffrn_measurement.diffrn_id # _diffrn_measurement.details # _diffrn_measurement.device # _diffrn_measurement.device_details # _diffrn_measurement.device_type # _diffrn_measurement.id # _diffrn_measurement.method # _diffrn_measurement.number_of_axes # _diffrn_measurement.specimen_support # # category DIFFRN_MEASUREMENT_AXIS # # _diffrn_measurement_axis.axis_id # _diffrn_measurement_axis.measurement_device # _diffrn_measurement_axis.measurement_id # # category DIFFRN_RADIATION # # _diffrn_radiation.collimation # _diffrn_radiation.diffrn_id # _diffrn_radiation.div_x_source # _diffrn_radiation.div_y_source # _diffrn_radiation.div_x_y_source # _diffrn_radiation.filter_edge' # _diffrn_radiation.inhomogeneity # _diffrn_radiation.monochromator # _diffrn_radiation.polarisn_norm # _diffrn_radiation.polarisn_ratio # _diffrn_radiation.polarizn_source_norm # _diffrn_radiation.polarizn_source_ratio # _diffrn_radiation.probe # _diffrn_radiation.type # _diffrn_radiation.xray_symbol # _diffrn_radiation.wavelength_id # # category DIFFRN_REFLN # # _diffrn_refln.frame_id # # category DIFFRN_SCAN # # _diffrn_scan.id # _diffrn_scan.date_end # _diffrn_scan.date_start # _diffrn_scan.integration_time # _diffrn_scan.frame_id_start # _diffrn_scan.frame_id_end # _diffrn_scan.frames # # category DIFFRN_SCAN_AXIS # # _diffrn_scan_axis.axis_id # _diffrn_scan_axis.angle_start # _diffrn_scan_axis.angle_range # _diffrn_scan_axis.angle_increment # _diffrn_scan_axis.angle_rstrt_incr # _diffrn_scan_axis.displacement_start # _diffrn_scan_axis.displacement_range # _diffrn_scan_axis.displacement_increment # _diffrn_scan_axis.displacement_rstrt_incr # _diffrn_scan_axis.scan_id # # category DIFFRN_SCAN_FRAME # # _diffrn_scan_frame.date # _diffrn_scan_frame.frame_id # _diffrn_scan_frame.frame_number # _diffrn_scan_frame.integration_time # _diffrn_scan_frame.scan_id # # category DIFFRN_SCAN_FRAME_AXIS # # _diffrn_scan_frame_axis.axis_id # _diffrn_scan_frame_axis.angle # _diffrn_scan_frame_axis.angle_increment # _diffrn_scan_frame_axis.angle_rstrt_incr # _diffrn_scan_frame_axis.displacement # _diffrn_scan_frame_axis.displacement_increment # _diffrn_scan_frame_axis.displacement_rstrt_incr # _diffrn_scan_frame_axis.frame_id # # ***DEPRECATED*** data items # # _diffrn_detector_axis.id # _diffrn_measurement_axis.id # # ***DEPRECATED*** category DIFFRN_FRAME_DATA # # _diffrn_frame_data.array_id # _diffrn_frame_data.binary_id # _diffrn_frame_data.detector_element_id # _diffrn_frame_data.id # # # ITEM_TYPE_LIST # ITEM_UNITS_LIST # DICTIONARY_HISTORY # ############################################################################## ######################### ## CATEGORY_GROUP_LIST ## ######################### loop_ _category_group_list.id _category_group_list.parent_id _category_group_list.description 'inclusive_group' . ; Categories that belong to the dictionary extension. ; 'array_data_group' 'inclusive_group' ; Categories that describe array data. ; 'axis_group' 'inclusive_group' ; Categories that describe axes. ; 'diffrn_group' 'inclusive_group' ; Categories that describe details of the diffraction experiment. ; ############## # ARRAY_DATA # ############## save_ARRAY_DATA _category.description ; Data items in the ARRAY_DATA category are the containers for the array data items described in the category ARRAY_STRUCTURE. ; _category.id array_data _category.mandatory_code no loop_ _category_key.name '_array_data.array_id' '_array_data.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows two binary data blocks. The first one was compressed by the CBF_CANONICAL compression algorithm and is presented as hexadecimal data. The first character 'H' on the data lines means hexadecimal. It could have been 'O' for octal or 'D' for decimal. The second character on the line shows the number of bytes in each word (in this case '4'), which then requires eight hexadecimal digits per word. The third character gives the order of octets within a word, in this case '<' for the ordering 4321 (i.e. 'big-endian'). Alternatively, the character '>' could have been used for the ordering 1234 (i.e. 'little-endian'). The block has a 'message digest' to check the integrity of the data. The second block is similar, but uses CBF_PACKED compression and BASE64 encoding. Note that the size and the digest are different. ; ; loop_ _array_data.array_id _array_data.binary_id _array_data.data image_1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_CANONICAL" Content-Transfer-Encoding: X-BASE16 X-Binary-Size: 3927126 X-Binary-ID: 1 Content-MD5: u2sTJEovAHkmkDjPi+gWsg== # Hexadecimal encoding, byte 0, byte order ...21 # H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ... .... --CIF-BINARY-FORMAT-SECTION---- ; image_2 2 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF-PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3745758 X-Binary-ID: 2 Content-MD5: 1zsJjWPfol2GYl2V+QSXrw== ELhQAAAAAAAA... ... --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_data.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_data.array_id' _item.category_id array_data _item.mandatory_code yes _item_type.code code save_ save__array_data.binary_id _item_description.description ; This item is an integer identifier which, along with _array_data.array_id, should uniquely identify the particular block of array data. If _array_data.binary_id is not explicitly given, it defaults to 1. The value of _array_data.binary_id distinguishes among multiple sets of data with the same array structure. If the MIME header of the data array specifies a value for X-Binary-ID, the value of _array_data.binary_id should be equal to the value given for X-Binary-ID. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_data.binary_id' array_data implicit '_diffrn_data_frame.binary_id' diffrn_data_frame implicit '_array_intensities.binary_id' array_intensities implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.binary_id' '_array_data.binary_id' '_array_intensities.binary_id' '_array_data.binary_id' _item_default.value 1 _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_data.data _item_description.description ; The value of _array_data.data contains the array data encapsulated in a STAR string. The representation used is a variant on the Multipurpose Internet Mail Extensions (MIME) specified in RFC 2045-2049 by N. Freed et al. The boundary delimiter used in writing an imgCIF or CBF is "--CIF-BINARY-FORMAT-SECTION--" (including the required initial "--"). The Content-Type may be any of the discrete types permitted in RFC 2045; 'application/octet-stream' is recommended. If an octet stream was compressed, the compression should be specified by the parameter 'conversions="x-CBF_PACKED"' or the parameter 'conversions="x-CBF_CANONICAL"'. The Content-Transfer-Encoding may be 'BASE64', 'Quoted-Printable', 'X-BASE8', 'X-BASE10' or 'X-BASE16' for an imgCIF or 'BINARY' for a CBF. The octal, decimal and hexadecimal transfer encodings are for convenience in debugging and are not recommended for archiving and data interchange. In an imgCIF file, the encoded binary data begin after the empty line terminating the header. In a CBF, the raw binary data begin after an empty line terminating the header and after the sequence: Octet Hex Decimal Purpose 0 0C 12 (Ctrl-L) page break 1 1A 26 (Ctrl-Z) stop listings in MS-DOS 2 04 04 (Ctrl-D) stop listings in UNIX 3 D5 213 binary section begins None of these octets are included in the calculation of the message size or in the calculation of the message digest. The X-Binary-Size header specifies the size of the equivalent binary data in octets. If compression was used, this size is the size after compression, including any book-keeping fields. An adjustment is made for the deprecated binary formats in which eight bytes of binary header are used for the compression type. In this case, the eight bytes used for the compression type are subtracted from the size, so that the same size will be reported if the compression type is supplied in the MIME header. Use of the MIME header is the recommended way to supply the compression type. In general, no portion of the binary header is included in the calculation of the size. The X-Binary-Element-Type header specifies the type of binary data in the octets, using the same descriptive phrases as in _array_structure.encoding_type. The default value is 'unsigned 32-bit integer'. An MD5 message digest may, optionally, be used. The 'RSA Data Security, Inc. MD5 Message-Digest Algorithm' should be used. No portion of the header is included in the calculation of the message digest. If the Transfer Encoding is 'X-BASE8', 'X-BASE10' or 'X-BASE16', the data are presented as octal, decimal or hexadecimal data organized into lines or words. Each word is created by composing octets of data in fixed groups of 2, 3, 4, 6 or 8 octets, either in the order ...4321 ('big- endian') or 1234... ('little-endian'). If there are fewer than the specified number of octets to fill the last word, then the missing octets are presented as '==' for each missing octet. Exactly two equal signs are used for each missing octet even for octal and decimal encoding. The format of lines is: rnd xxxxxx xxxxxx xxxxxx where r is 'H', 'O' or 'D' for hexadecimal, octal or decimal, n is the number of octets per word and d is '<' or '>' for the '...4321' and '1234...' octet orderings, respectively. The '==' padding for the last word should be on the appropriate side to correspond to the missing octets, e.g. H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000 or H3> FF0700 00==== For these hexadecimal, octal and decimal formats only, comments beginning with '#' are permitted to improve readability. BASE64 encoding follows MIME conventions. Octets are in groups of three: c1, c2, c3. The resulting 24 bits are broken into four six-bit quantities, starting with the high-order six bits (c1 >> 2) of the first octet, then the low-order two bits of the first octet followed by the high-order four bits of the second octet [(c1 & 3)<<4 | (c2>>4)], then the bottom four bits of the second octet followed by the high-order two bits of the last octet [(c2 & 15)<<2 | (c3>>6)], then the bottom six bits of the last octet (c3 & 63). Each of these four quantities is translated into an ASCII character using the mapping: 1 2 3 4 5 6 0123456789012345678901234567890123456789012345678901234567890123 | | | | | | | ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/ with short groups of octets padded on the right with one '=' if c3 is missing, and with '==' if both c2 and c3 are missing. QUOTED-PRINTABLE encoding also follows MIME conventions, copying octets without translation if their ASCII values are 32...38, 42, 48...57, 59, 60, 62, 64...126 and the octet is not a ';' in column 1. All other characters are translated to =nn, where nn is the hexadecimal encoding of the octet. All lines are 'wrapped' with a terminating '=' (i.e. the MIME conventions for an implicit line terminator are never used). ; _item.name '_array_data.data' _item.category_id array_data _item.mandatory_code yes _item_type.code binary save_ ###################### # ARRAY_ELEMENT_SIZE # ###################### save_ARRAY_ELEMENT_SIZE _category.description ; Data items in the ARRAY_ELEMENT_SIZE category record the physical size of array elements along each array dimension. ; _category.id array_element_size _category.mandatory_code no loop_ _category_key.name '_array_element_size.array_id' '_array_element_size.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - a regular 2D array with a uniform element dimension of 1220 nanometres. ; ; loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size image_1 1 1.22e-6 image_1 2 1.22e-6 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_element_size.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_element_size.array_id' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.index _item_description.description ; This item is a pointer to _array_structure_list.index in the ARRAY_STRUCTURE_LIST category. ; _item.name '_array_element_size.index' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.size _item_description.description ; The size in metres of an image element in this dimension. This supposes that the elements are arranged on a regular grid. ; _item.name '_array_element_size.size' _item.category_id array_element_size _item.mandatory_code yes _item_type.code float _item_units.code 'metres' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ ##################### # ARRAY_INTENSITIES # ##################### save_ARRAY_INTENSITIES _category.description ; Data items in the ARRAY_INTENSITIES category record the information required to recover the intensity data from the set of data values stored in the ARRAY_DATA category. The detector may have a complex relationship between the raw intensity values and the number of incident photons. In most cases, the number stored in the final array will have a simple linear relationship to the actual number of incident photons, given by _array_intensities.gain. If raw, uncorrected values are presented (e.g. for calibration experiments), the value of _array_intensities.linearity will be 'raw' and _array_intensities.gain will not be used. ; _category.id array_intensities _category.mandatory_code no loop_ _category_key.name '_array_intensities.array_id' '_array_intensities.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 ; ; loop_ _array_intensities.array_id _array_intensities.linearity _array_intensities.gain _array_intensities.overload _array_intensities.undefined_value image_1 linear 1.2 655535 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_intensities.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_intensities.array_id' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code save_ save__array_intensities.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_array_intensities.binary_id' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code int save_ save__array_intensities.gain _item_description.description ; Detector 'gain'. The factor by which linearized intensity count values should be divided to produce true photon counts. ; _item.name '_array_intensities.gain' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain_esd' 'associated_value' save_ save__array_intensities.gain_esd _item_description.description ; The estimated standard deviation in detector 'gain'. ; _item.name '_array_intensities.gain_esd' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain' 'associated_esd' save_ save__array_intensities.linearity _item_description.description ; The intensity linearity scaling method used to convert from the raw intensity to the stored element value: 'linear' is linear. 'offset' means that the value defined by _array_intensities.offset should be added to each element value. 'scaling' means that the value defined by _array_intensities.scaling should be multiplied with each element value. 'scaling_offset' is the combination of the two previous cases, with the scale factor applied before the offset value. 'sqrt_scaled' means that the square root of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and squaring the result. 'logarithmic_scaled' means that the logarithm base 10 of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and calculating 10 to the power of this number. 'raw' means that the data are a set of raw values straight from the detector. ; _item.name '_array_intensities.linearity' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'linear' . 'offset' ; The value defined by _array_intensities.offset should be added to each element value. ; 'scaling' ; The value defined by _array_intensities.scaling should be multiplied with each element value. ; 'scaling_offset' ; The combination of the scaling and offset with the scale factor applied before the offset value. ; 'sqrt_scaled' ; The square root of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and squaring the result. ; 'logarithmic_scaled' ; The logarithm base 10 of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and calculating 10 to the power of this number. ; 'raw' ; The array consists of raw values to which no corrections have been applied. While the handling of the data is similar to that given for 'linear' data with no offset, the meaning of the data differs in that the number of incident photons is not necessarily linearly related to the number of counts reported. This value is intended for use either in calibration experiments or to allow for handling more complex data-fitting algorithms than are allowed for by this data item. ; save_ save__array_intensities.offset _item_description.description ; Offset value to add to array element values in the manner described by the item _array_intensities.linearity. ; _item.name '_array_intensities.offset' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.overload _item_description.description ; The saturation intensity level for this data array. ; _item.name '_array_intensities.overload' _item.category_id array_intensities _item.mandatory_code no _item_type.code float _item_units.code 'counts' save_ save__array_intensities.scaling _item_description.description ; Multiplicative scaling value to be applied to array data in the manner described by item _array_intensities.linearity. ; _item.name '_array_intensities.scaling' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.undefined_value _item_description.description ; A value to be substituted for undefined values in the data array. ; _item.name '_array_intensities.undefined_value' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ ################### # ARRAY_STRUCTURE # ################### save_ARRAY_STRUCTURE _category.description ; Data items in the ARRAY_STRUCTURE category record the organization and encoding of array data in the ARRAY_DATA category. ; _category.id array_structure _category.mandatory_code no _category_key.name '_array_structure.id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order image_1 "unsigned 16-bit integer" none little_endian ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure.byte_order _item_description.description ; The order of bytes for integer values which require more than 1 byte. (IBM PCs and compatibles, and Dec VAXs use low-byte-first ordered integers, whereas Hewlett Packard 700 series, Sun-4 and Silicon Graphics use high-byte-first ordered integers. Dec Alphas can produce/use either depending on a compiler switch.) ; _item.name '_array_structure.byte_order' _item.category_id array_structure _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'big_endian' ; The first byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; 'little_endian' ; The last byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; save_ save__array_structure.compression_type _item_description.description ; Type of data-compression method used to compress the array data. ; _item.name '_array_structure.compression_type' _item.category_id array_structure _item.mandatory_code no _item_type.code code _item_default.value 'none' loop_ _item_enumeration.value _item_enumeration.detail 'none' ; Data are stored in normal format as defined by _array_structure.encoding_type and _array_structure.byte_order. ; 'packed' ; Using the 'packed' compression scheme, a CCP4-style packing (International Tables for Crystallography Volume G, Section 5.6.3.2) ; 'canonical' ; Using the 'canonical' compression scheme (International Tables for Crystallography Volume G, Section 5.6.3.1) ; save_ save__array_structure.encoding_type _item_description.description ; Data encoding of a single element of array data. In several cases, the IEEE format is referenced. See IEEE Standard 754-1985 (IEEE, 1985). Ref: IEEE (1985). IEEE Standard for Binary Floating-Point Arithmetic. ANSI/IEEE Std 754-1985. New York: Institute of Electrical and Electronics Engineers. ; _item.name '_array_structure.encoding_type' _item.category_id array_structure _item.mandatory_code yes _item_type.code uline loop_ _item_enumeration.value 'unsigned 8-bit integer' 'signed 8-bit integer' 'unsigned 16-bit integer' 'signed 16-bit integer' 'unsigned 32-bit integer' 'signed 32-bit integer' 'signed 32-bit real IEEE' 'signed 64-bit real IEEE' 'signed 32-bit complex IEEE' save_ save__array_structure.id _item_description.description ; The value of _array_structure.id must uniquely identify each item of array data. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure.id' array_structure yes '_array_data.array_id' array_data yes '_array_structure_list.array_id' array_structure_list yes '_array_intensities.array_id' array_intensities yes '_diffrn_data_frame.array_id' diffrn_data_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_data.array_id' '_array_structure.id' '_array_structure_list.array_id' '_array_structure.id' '_array_intensities.array_id' '_array_structure.id' '_diffrn_data_frame.array_id' '_array_structure.id' save_ ######################## # ARRAY_STRUCTURE_LIST # ######################## save_ARRAY_STRUCTURE_LIST _category.description ; Data items in the ARRAY_STRUCTURE_LIST category record the size and organization of each array dimension. The relationship to physical axes may be given. ; _category.id array_structure_list _category.mandatory_code no loop_ _category_key.name '_array_structure_list.array_id' '_array_structure_list.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - An image array of 1300 x 1200 elements. The raster order of the image is left to right (increasing) in the first dimension and bottom to top (decreasing) in the second dimension. ; ; loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id image_1 1 1300 1 increasing ELEMENT_X image_1 2 1200 2 decreasing ELEMENY_Y ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure_list.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_structure_list.array_id' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code code save_ save__array_structure_list.axis_set_id _item_description.description ; This is a descriptor for the physical axis or set of axes corresponding to an array index. This data item is related to the axes of the detector itself given in DIFFRN_DETECTOR_AXIS, but usually differs in that the axes in this category are the axes of the coordinate system of reported data points, while the axes in DIFFRN_DETECTOR_AXIS are the physical axes of the detector describing the 'poise' of the detector as an overall physical object. If there is only one axis in the set, the identifier of that axis should be used as the identifier of the set. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.axis_set_id' array_structure_list yes '_array_structure_list_axis.axis_set_id' array_structure_list_axis implicit _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_structure_list_axis.axis_set_id' '_array_structure_list.axis_set_id' save_ save__array_structure_list.dimension _item_description.description ; The number of elements stored in the array structure in this dimension. ; _item.name '_array_structure_list.dimension' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.direction _item_description.description ; Identifies the direction in which this array index changes. ; _item.name '_array_structure_list.direction' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_enumeration.value _item_enumeration.detail 'increasing' ; Indicates the index changes from 1 to the maximum dimension ; 'decreasing' ; Indicates the index changes from the maximum dimension to 1 ; save_ save__array_structure_list.index _item_description.description ; Identifies the one-based index of the row or column in the array structure. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.index' array_structure_list yes '_array_structure_list.precedence' array_structure_list yes '_array_element_size.index' array_element_size yes _item_type.code int loop_ _item_linked.child_name _item_linked.parent_name '_array_element_size.index' '_array_structure_list.index' loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.precedence _item_description.description ; Identifies the rank order in which this array index changes with respect to other array indices. The precedence of 1 indicates the index which changes fastest. ; _item.name '_array_structure_list.precedence' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ ############################# # ARRAY_STRUCTURE_LIST_AXIS # ############################# save_ARRAY_STRUCTURE_LIST_AXIS _category.description ; Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe the physical settings of sets of axes for the centres of pixels that correspond to data points described in the ARRAY_STRUCTURE_LIST category. In the simplest cases, the physical increments of a single axis correspond to the increments of a single array index. More complex organizations, e.g. spiral scans, may require coupled motions along multiple axes. Note that a spiral scan uses two coupled axes: one for the angular direction and one for the radial direction. This differs from a cylindrical scan for which the two axes are not coupled into one set. ; _category.id array_structure_list_axis _category.mandatory_code no loop_ _category_key.name '_array_structure_list_axis.axis_set_id' '_array_structure_list_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' save_ save__array_structure_list_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes in the set of axes for which settings are being specified. Multiple axes may be specified for the same value of _array_structure_list_axis.axis_set_id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_array_structure_list_axis.axis_id' _item.category_id array_structure_list_axis _item.mandatory_code yes _item_type.code code save_ save__array_structure_list_axis.axis_set_id _item_description.description ; The value of this data item is the identifier of the set of axes for which axis settings are being specified. Multiple axes may be specified for the same value of _array_structure_list_axis.axis_set_id. This item is a pointer to _array_structure_list.axis_set_id in the ARRAY_STRUCTURE_LIST category. If this item is not specified, it defaults to the corresponding axis identifier. ; _item.name '_array_structure_list_axis.axis_set_id' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_type.code code save_ save__array_structure_list_axis.angle _item_description.description ; The setting of the specified axis in degrees for the first data point of the array index with the corresponding value of _array_structure_list.axis_set_id. If the index is specified as 'increasing', this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing', this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.angle' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.angle_increment _item_description.description ; The pixel-centre-to-pixel-centre increment in the angular setting of the specified axis in degrees. This is not meaningful in the case of 'constant velocity' spiral scans and should not be specified for this case. See _array_structure_list_axis.angular_pitch. ; _item.name '_array_structure_list_axis.angle_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for the first data point of the array index with the corresponding value of _array_structure_list.axis_set_id. If the index is specified as 'increasing', this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing', this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.displacement' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.displacement_increment _item_description.description ; The pixel-centre-to-pixel-centre increment for the displacement setting of the specified axis in millimetres. ; _item.name '_array_structure_list_axis.displacement_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.angular_pitch _item_description.description ; The pixel-centre-to-pixel-centre distance for a one-step change in the setting of the specified axis in millimetres. This is meaningful only for 'constant velocity' spiral scans or for uncoupled angular scans at a constant radius (cylindrical scans) and should not be specified for cases in which the angle between pixels (rather than the distance between pixels) is uniform. See _array_structure_list_axis.angle_increment. ; _item.name '_array_structure_list_axis.angular_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.radial_pitch _item_description.description ; The radial distance from one 'cylinder' of pixels to the next in millimetres. If the scan is a 'constant velocity' scan with differing angular displacements between pixels, the value of this item may differ significantly from the value of _array_structure_list_axis.displacement_increment. ; _item.name '_array_structure_list_axis.radial_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ ######## # AXIS # ######## save_AXIS _category.description ; Data items in the AXIS category record the information required to describe the various goniometer, detector, source and other axes needed to specify a data collection. The location of each axis is specified by two vectors: the axis itself, given as a unit vector, and an offset to the base of the unit vector. These vectors are referenced to a right-handed laboratory coordinate system with its origin in the sample or specimen: | Y (to complete right-handed system) | | | | | |________________X / principal goniometer axis / / / / /Z (to source) Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from the sample or specimen along the principal axis of the goniometer. Axis 2 (Y): The Y-axis completes an orthogonal right-handed system defined by the X-axis and the Z-axis (see below). Axis 3 (Z): The Z-axis is derived from the source axis which goes from the sample to the source. The Z-axis is the component of the source axis in the direction of the source orthogonal to the X-axis in the plane defined by the X-axis and the source axis. These axes are based on the goniometer, not on the orientation of the detector, gravity etc. The vectors necessary to specify all other axes are given by sets of three components in the order (X, Y, Z). If the axis involved is a rotation axis, it is right-handed, i.e. as one views the object to be rotated from the origin (the tail) of the unit vector, the rotation is clockwise. If a translation axis is specified, the direction of the unit vector specifies the sense of positive translation. Note: This choice of coordinate system is similar to but significantly different from the choice in MOSFLM (Leslie & Powell, 2004). In MOSFLM, X is along the X-ray beam (the CBF/imgCIF Z axis) and Z is along the rotation axis. All rotations are given in degrees and all translations are given in mm. Axes may be dependent on one another. The X-axis is the only goniometer axis the direction of which is strictly connected to the hardware. All other axes are specified by the positions they would assume when the axes upon which they depend are at their zero points. When specifying detector axes, the axis is given to the beam centre. The location of the beam centre on the detector should be given in the DIFFRN_DETECTOR category in distortion-corrected millimetres from the (0,0) corner of the detector. It should be noted that many different origins arise in the definition of an experiment. In particular, as noted above, it is necessary to specify the location of the beam centre on the detector in terms of the origin of the detector, which is, of course, not coincident with the centre of the sample. Ref: Leslie, A. G. W. & Powell, H. (2004). MOSFLM v6.11. MRC Laboratory of Molecular Biology, Hills Road, Cambridge, England. http://www.CCP4.ac.uk/dist/x-windows/Mosflm/. ; _category.id axis _category.mandatory_code no loop_ _category_key.name '_axis.id' '_axis.equipment' loop_ _category_group.id 'inclusive_group' 'axis_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 This example shows the axis specification of the axes of a kappa- geometry goniometer [see Stout, G. H. & Jensen, L. H. (1989). X-ray structure determination. A practical guide, 2nd ed. p. 134. New York: Wiley Interscience]. There are three axes specified, and no offsets. The outermost axis, omega, is pointed along the X axis. The next innermost axis, kappa, is at a 50 degree angle to the X axis, pointed away from the source. The innermost axis, phi, aligns with the X axis when omega and phi are at their zero points. If T-omega, T-kappa and T-phi are the transformation matrices derived from the axis settings, the complete transformation would be: x' = (T-omega) (T-kappa) (T-phi) x ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] omega rotation goniometer . 1 0 0 kappa rotation goniometer omega -.64279 0 -.76604 phi rotation goniometer kappa 1 0 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 This example show the axis specification of the axes of a detector, source and gravity. The order has been changed as a reminder that the ordering of presentation of tokens is not significant. The centre of rotation of the detector has been taken to be 68 millimetres in the direction away from the source. ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] source . source . 0 0 1 . . . gravity . gravity . 0 -1 0 . . . tranz translation detector rotz 0 0 1 0 0 -68 twotheta rotation detector . 1 0 0 . . . roty rotation detector twotheta 0 1 0 0 0 -68 rotz rotation detector roty 0 0 1 0 0 -68 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__axis.depends_on _item_description.description ; The value of _axis.depends_on specifies the next outermost axis upon which this axis depends. This item is a pointer to _axis.id in the same category. ; _item.name '_axis.depends_on' _item.category_id axis _item.mandatory_code no save_ save__axis.equipment _item_description.description ; The value of _axis.equipment specifies the type of equipment using the axis: 'goniometer', 'detector', 'gravity', 'source' or 'general'. ; _item.name '_axis.equipment' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail goniometer 'equipment used to orient or position samples' detector 'equipment used to detect reflections' general 'equipment used for general purposes' gravity 'axis specifying the downward direction' source 'axis specifying the direction sample to source' save_ save__axis.offset[1] _item_description.description ; The [1] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[2] _item_description.description ; The [2] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[3] _item_description.description ; The [3] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.id _item_description.description ; The value of _axis.id must uniquely identify each axis relevant to the experiment. Note that multiple pieces of equipment may share the same axis (e.g. a twotheta arm), so the category key for AXIS also includes the equipment. ; loop_ _item.name _item.category_id _item.mandatory_code '_axis.id' axis yes '_array_structure_list_axis.axis_id' array_structure_list_axis yes '_diffrn_detector_axis.axis_id' diffrn_detector_axis yes '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes '_diffrn_scan_axis.axis_id' diffrn_scan_axis yes '_diffrn_scan_frame_axis.axis_id' diffrn_scan_frame_axis yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_axis.depends_on' '_axis.id' '_array_structure_list_axis.axis_id' '_axis.id' '_diffrn_detector_axis.axis_id' '_axis.id' '_diffrn_measurement_axis.axis_id' '_axis.id' '_diffrn_scan_axis.axis_id' '_axis.id' '_diffrn_scan_frame_axis.axis_id' '_axis.id' save_ save__axis.type _item_description.description ; The value of _axis.type specifies the type of axis: 'rotation' or 'translation' (or 'general' when the type is not relevant, as for gravity). ; _item.name '_axis.type' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail rotation 'right-handed axis of rotation' translation 'translation in the direction of the axis' general 'axis for which the type is not relevant' save_ save__axis.vector[1] _item_description.description ; The [1] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[2] _item_description.description ; The [2] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[3] _item_description.description ; The [3] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ ##################### # DIFFRN_DATA_FRAME # ##################### save_DIFFRN_DATA_FRAME _category.description ; Data items in the DIFFRN_DATA_FRAME category record the details about each frame of data. The items in this category were previously in a DIFFRN_FRAME_DATA category, which is now deprecated. The items from the old category are provided as aliases but should not be used for new work. ; _category.id diffrn_data_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_data_frame.id' '_diffrn_data_frame.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - a frame containing data from four frame elements. Each frame element has a common array configuration 'array_1' described in ARRAY_STRUCTURE and related categories. The data for each detector element are stored in four groups of binary data in the ARRAY_DATA category, linked by the array_id and binary_id. ; ; loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id frame_1 d1_ccd_1 array_1 1 frame_1 d1_ccd_2 array_1 2 frame_1 d1_ccd_3 array_1 3 frame_1 d1_ccd_4 array_1 4 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_data_frame.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_diffrn_data_frame.array_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.array_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_diffrn_data_frame.binary_id' _item.category_id diffrn_data_frame _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_frame_data.binary_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code int save_ save__diffrn_data_frame.detector_element_id _item_description.description ; This item is a pointer to _diffrn_detector_element.id in the DIFFRN_DETECTOR_ELEMENT category. ; _item.name '_diffrn_data_frame.detector_element_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.detector_element_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.id _item_description.description ; The value of _diffrn_data_frame.id must uniquely identify each complete frame of data. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_data_frame.id' diffrn_data_frame yes '_diffrn_refln.frame_id' diffrn_refln yes '_diffrn_scan.frame_id_start' diffrn_scan yes '_diffrn_scan.frame_id_end' diffrn_scan yes '_diffrn_scan_frame.frame_id' diffrn_scan_frame yes '_diffrn_scan_frame_axis.frame_id' diffrn_scan_frame_axis yes _item_aliases.alias_name '_diffrn_frame_data.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_refln.frame_id' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_start' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_end' '_diffrn_data_frame.id' '_diffrn_scan_frame.frame_id' '_diffrn_data_frame.id' '_diffrn_scan_frame_axis.frame_id' '_diffrn_data_frame.id' save_ ########################################################################## # The following is a restatement of the mmCIF DIFFRN_DETECTOR, # # DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for # # the CBF/imgCIF extensions # ########################################################################## ################### # DIFFRN_DETECTOR # ################### save_DIFFRN_DETECTOR _category.description ; Data items in the DIFFRN_DETECTOR category describe the detector used to measure the scattered radiation, including any analyser and post-sample collimation. ; _category.id diffrn_detector _category.mandatory_code no loop_ _category_key.name '_diffrn_detector.diffrn_id' '_diffrn_detector.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _diffrn_detector.diffrn_id 'd1' _diffrn_detector.detector 'multiwire' _diffrn_detector.type 'Siemens' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector.details _item_description.description ; A description of special aspects of the radiation detector. ; _item.name '_diffrn_detector.details' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'slow mode' save_ save__diffrn_detector.detector _item_description.description ; The general class of the radiation detector. ; _item.name '_diffrn_detector.detector' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector' cifdic.c91 1.0 '_diffrn_detector' cif_core.dic 2.0 _item_type.code text loop_ _item_examples.case 'photographic film' 'scintillation counter' 'CCD plate' 'BF~3~ counter' save_ save__diffrn_detector.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. The value of _diffrn.id uniquely defines a set of diffraction data. ; _item.name '_diffrn_detector.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector.dtime _item_description.description ; The deadtime in microseconds of the detector(s) used to measure the diffraction intensities. ; _item.name '_diffrn_detector.dtime' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector_dtime' cifdic.c91 1.0 '_diffrn_detector_dtime' cif_core.dic 2.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code microseconds save_ save__diffrn_detector.id _item_description.description ; The value of _diffrn_detector.id must uniquely identify each detector used to collect each diffraction data set. If the value of _diffrn_detector.id is not given, it is implicitly equal to the value of _diffrn_detector.diffrn_id. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector.id' diffrn_detector implicit '_diffrn_detector_axis.detector_id' diffrn_detector_axis yes loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_detector_axis.detector_id' '_diffrn_detector.id' _item_type.code code save_ save__diffrn_detector.number_of_axes _item_description.description ; The value of _diffrn_detector.number_of_axes gives the number of axes of the positioner for the detector identified by _diffrn_detector.id. The word 'positioner' is a general term used in instrumentation design for devices that are used to change the positions of portions of apparatus by linear translation, rotation or combinations of such motions. Axes which are used to provide a coordinate system for the face of an area detetctor should not be counted for this data item. The description of each axis should be provided by entries in DIFFRN_DETECTOR_AXIS. ; _item.name '_diffrn_detector.number_of_axes' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_detector.type _item_description.description ; The make, model or name of the detector device used. ; _item.name '_diffrn_detector.type' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ ######################## # DIFFRN_DETECTOR_AXIS # ######################## save_DIFFRN_DETECTOR_AXIS _category.description ; Data items in the DIFFRN_DETECTOR_AXIS category associate axes with detectors. ; _category.id diffrn_detector_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_axis.detector_id' '_diffrn_detector_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_detector_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_detector_axis.axis_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_axis.detector_id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. This item was previously named _diffrn_detector_axis.id, which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_detector_axis.detector_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_aliases.alias_name '_diffrn_detector_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ ########################### # DIFFRN_DETECTOR_ELEMENT # ########################### save_DIFFRN_DETECTOR_ELEMENT _category.description ; Data items in the DIFFRN_DETECTOR_ELEMENT category record the details about spatial layout and other characteristics of each element of a detector which may have multiple elements. In most cases, giving more detailed information in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS is preferable to simply providing the centre of the detector element. ; _category.id diffrn_detector_element _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_element.id' '_diffrn_detector_element.detector_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Detector d1 is composed of four CCD detector elements, each 200 mm by 200 mm, arranged in a square, in the pattern 1 2 * 3 4 Note that the beam centre is slightly displaced from each of the detector elements, just beyond the lower right corner of 1, the lower left corner of 2, the upper right corner of 3 and the upper left corner of 4. ; ; loop_ _diffrn_detector_element.detector_id _diffrn_detector_element.id _diffrn_detector_element.center[1] _diffrn_detector_element.center[2] d1 d1_ccd_1 201.5 -1.5 d1 d1_ccd_2 -1.8 -1.5 d1 d1_ccd_3 201.6 201.4 d1 d1_ccd_4 -1.7 201.5 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector_element.center[1] _item_description.description ; The value of _diffrn_detector_element.center[1] is the X component of the distortion-corrected beam centre in millimetres from the (0, 0) (lower-left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. ; _item.name '_diffrn_detector_element.center[1]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.center[2] _item_description.description ; The value of _diffrn_detector_element.center[2] is the Y component of the distortion-corrected beam centre in millimetres from the (0, 0) (lower-left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. ; _item.name '_diffrn_detector_element.center[2]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.id _item_description.description ; The value of _diffrn_detector_element.id must uniquely identify each element of a detector. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector_element.id' diffrn_detector_element yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.detector_element_id' '_diffrn_detector_element.id' save_ save__diffrn_detector_element.detector_id _item_description.description ; This item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. ; _item.name '_diffrn_detector_element.detector_id' _item.category_id diffrn_detector_element _item.mandatory_code yes _item_type.code code save_ ######################## ## DIFFRN_MEASUREMENT ## ######################## save_DIFFRN_MEASUREMENT _category.description ; Data items in the DIFFRN_MEASUREMENT category record details about the device used to orient and/or position the crystal during data measurement and the manner in which the diffraction data were measured. ; _category.id diffrn_measurement _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement.device' '_diffrn_measurement.diffrn_id' '_diffrn_measurement.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _diffrn_measurement.diffrn_id 'd1' _diffrn_measurement.device '3-circle camera' _diffrn_measurement.device_type 'Supper model x' _diffrn_measurement.device_details 'none' _diffrn_measurement.method 'omega scan' _diffrn_measurement.details ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _diffrn_measurement.diffrn_id 's1' _diffrn_measurement.device_type 'Philips PW1100/20 diffractometer' _diffrn_measurement.method 'theta/2theta (\q/2\q)' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_measurement.device _item_description.description ; The general class of goniometer or device used to support and orient the specimen. If the value of _diffrn_measurement.device is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id. Either _diffrn_measurement.device or _diffrn_measurement.id may be used to link to other categories. If the experimental setup admits multiple devices, then _diffrn_measurement.id is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.device' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_device' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement.device' _item_aliases.alias_name '_diffrn_measurement_device' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '3-circle camera' '4-circle camera' 'kappa-geometry camera' 'oscillation camera' 'precession camera' save_ save__diffrn_measurement.device_details _item_description.description ; A description of special aspects of the device used to measure the diffraction intensities. ; _item.name '_diffrn_measurement.device_details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; commercial goniometer modified locally to allow for 90\% \t arc ; save_ save__diffrn_measurement.device_type _item_description.description ; The make, model or name of the measurement device (goniometer) used. ; _item.name '_diffrn_measurement.device_type' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Supper model q' 'Huber model r' 'Enraf-Nonius model s' 'home-made' save_ save__diffrn_measurement.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_measurement.diffrn_id' _item.mandatory_code yes save_ save__diffrn_measurement.details _item_description.description ; A description of special aspects of the intensity measurement. ; _item.name '_diffrn_measurement.details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; save_ save__diffrn_measurement.id _item_description.description ; The value of _diffrn_measurement.id must uniquely identify the set of mechanical characteristics of the device used to orient and/or position the sample used during the collection of each diffraction data set. If the value of _diffrn_measurement.id is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id. Either _diffrn_measurement.device or _diffrn_measurement.id may be used to link to other categories. If the experimental setup admits multiple devices, then _diffrn_measurement.id is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.id' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_id' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement.id' _item_type.code code save_ save__diffrn_measurement.method _item_description.description ; Method used to measure intensities. ; _item.name '_diffrn_measurement.method' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_method' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'profile data from theta/2theta (\q/2\q) scans' save_ save__diffrn_measurement.number_of_axes _item_description.description ; The value of _diffrn_measurement.number_of_axes gives the number of axes of the positioner for the goniometer or other sample orientation or positioning device identified by _diffrn_measurement.id. The description of the axes should be provided by entries in DIFFRN_MEASUREMENT_AXIS. ; _item.name '_diffrn_measurement.number_of_axes' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_measurement.specimen_support _item_description.description ; The physical device used to support the crystal during data collection. ; _item.name '_diffrn_measurement.specimen_support' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_specimen_support' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'glass capillary' 'quartz capillary' 'fiber' 'metal loop' save_ ########################### # DIFFRN_MEASUREMENT_AXIS # ########################### save_DIFFRN_MEASUREMENT_AXIS _category.description ; Data items in the DIFFRN_MEASUREMENT_AXIS category associate axes with goniometers. ; _category.id diffrn_measurement_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_measurement_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_measurement_axis.axis_id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.measurement_device _item_description.description ; This data item is a pointer to _diffrn_measurement.device in the DIFFRN_MEASUREMENT category. ; _item.name '_diffrn_measurement_axis.measurement_device' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit _item_type.code text save_ save__diffrn_measurement_axis.measurement_id _item_description.description ; This data item is a pointer to _diffrn_measurement.id in the DIFFRN_MEASUREMENT category. This item was previously named _diffrn_measurement_axis.id, which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_measurement_axis.measurement_id' _item.category_id diffrn_measurement_axis _item_aliases.alias_name '_diffrn_measurement_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item.mandatory_code implicit _item_type.code code save_ #################### # DIFFRN_RADIATION # #################### save_DIFFRN_RADIATION _category.description ; Data items in the DIFFRN_RADIATION category describe the radiation used for measuring diffraction intensities, its collimation and monochromatization before the sample. Post-sample treatment of the beam is described by data items in the DIFFRN_DETECTOR category. ; _category.id diffrn_radiation _category.mandatory_code no _category_key.name '_diffrn_radiation.diffrn_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _diffrn_radiation.diffrn_id 'set1' _diffrn_radiation.collimation '0.3 mm double pinhole' _diffrn_radiation.monochromator 'graphite' _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.wavelength_id 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _diffrn_radiation.wavelength_id 1 _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.monochromator 'graphite' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_radiation.collimation _item_description.description ; The collimation or focusing applied to the radiation. ; _item.name '_diffrn_radiation.collimation' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_collimation' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '0.3 mm double-pinhole' '0.5 mm' 'focusing mirrors' save_ save__diffrn_radiation.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_radiation.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_radiation.div_x_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory X axis (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the standard uncertainty (e.s.d.) of the directions of photons in the XZ plane around the mean source beam direction. Note that for some synchrotrons this value is specified in milliradians, in which case a conversion is needed. To convert a value in milliradians to a value in degrees, multiply by 0.180 and divide by pi. ; _item.name '_diffrn_radiation.div_x_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.div_y_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory Y axis (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the standard uncertainty (e.s.d.) of the directions of photons in the YZ plane around the mean source beam direction. Note that for some synchrotrons this value is specified in milliradians, in which case a conversion is needed. To convert a value in milliradians to a value in degrees, multiply by 0.180 and divide by pi. ; _item.name '_diffrn_radiation.div_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.div_x_y_source _item_description.description ; Beam crossfire correlation in degrees squared between the crossfire laboratory X-axis component and the crossfire laboratory Y-axis component (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the mean of the products of the deviations of the direction of each photon in XZ plane times the deviations of the direction of the same photon in the YZ plane around the mean source beam direction. This will be zero for uncorrelated crossfire. Note that for some synchrotrons, this value is specified in milliradians squared, in which case a conversion is needed. To convert a value in milliradians squared to a value in degrees squared, multiply by 0.180**2 and divide by pi**2. ; _item.name '_diffrn_radiation.div_x_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees_squared _item_default.value 0.0 save_ save__diffrn_radiation.filter_edge _item_description.description ; Absorption edge in angstroms of the radiation filter used. ; _item.name '_diffrn_radiation.filter_edge' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_filter_edge' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__diffrn_radiation.inhomogeneity _item_description.description ; Half-width in millimetres of the incident beam in the direction perpendicular to the diffraction plane. ; _item.name '_diffrn_radiation.inhomogeneity' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_inhomogeneity' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code millimetres save_ save__diffrn_radiation.monochromator _item_description.description ; The method used to obtain monochromatic radiation. If a monochromator crystal is used, the material and the indices of the Bragg reflection are specified. ; _item.name '_diffrn_radiation.monochromator' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_monochromator' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Zr filter' 'Ge 220' 'none' 'equatorial mounted graphite' save_ save__diffrn_radiation.polarisn_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the perpendicular component of the polarization and the diffraction plane. See _diffrn_radiation_polarisn_ratio. ; _item.name '_diffrn_radiation.polarisn_norm' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_norm' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.polarisn_ratio _item_description.description ; Polarization ratio of the diffraction beam incident on the crystal. This is the ratio of the perpendicularly polarized to the parallel polarized component of the radiation. The perpendicular component forms an angle of _diffrn_radiation.polarisn_norm to the normal to the diffraction plane of the sample (i.e. the plane containing the incident and reflected beams). ; _item.name '_diffrn_radiation.polarisn_ratio' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_ratio' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__diffrn_radiation.polarizn_source_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the normal to the polarization plane and the laboratory Y axis as defined in the AXIS category. Note that this is the angle of polarization of the source photons, either directly from a synchrotron beamline or from a monchromator. This differs from the value of _diffrn_radiation.polarisn_norm in that _diffrn_radiation.polarisn_norm refers to polarization relative to the diffraction plane rather than to the laboratory axis system. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane should be taken as the XZ plane and the angle as 0. See _diffrn_radiation.polarizn_source_ratio. ; _item.name '_diffrn_radiation.polarizn_source_norm' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.polarizn_source_ratio _item_description.description ; (Ip-In)/(Ip+In), where Ip is the intensity (amplitude squared) of the electric vector in the plane of polarization and In is the intensity (amplitude squared) of the electric vector in the plane of the normal to the plane of polarization. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane is to be taken as the XZ plane and the normal is parallel to the Y axis. Thus, if there was complete polarization in the plane of polarization, the value of _diffrn_radiation.polarizn_source_ratio would be 1, and for an unpolarized beam _diffrn_radiation.polarizn_source_ratio would have a value of 0. If the X axis has been chosen to lie in the plane of polarization, this definition will agree with the definition of 'MONOCHROMATOR' in the Denzo glossary, and values of near 1 should be expected for a bending-magnet source. However, if the X axis were perpendicular to the polarization plane (not a common choice), then the Denzo value would be the negative of _diffrn_radiation.polarizn_source_ratio. See http://www.hkl-xray.com for information on Denzo and Otwinowski & Minor (1997). This differs both in the choice of ratio and choice of orientation from _diffrn_radiation.polarisn_ratio, which, unlike _diffrn_radiation.polarizn_source_ratio, is unbounded. Reference: Otwinowski, Z. & Minor, W. (1997). 'Processing of X-ray diffraction data collected in oscillation mode.' Methods Enzymol. 276, 307-326. ; _item.name '_diffrn_radiation.polarizn_source_ratio' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 -1.0 -1.0 -1.0 _item_type.code float save_ save__diffrn_radiation.probe _item_description.description ; Name of the type of radiation used. It is strongly recommended that this be given so that the probe radiation is clearly specified. ; _item.name '_diffrn_radiation.probe' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_probe' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value 'x-ray' 'neutron' 'electron' 'gamma' save_ save__diffrn_radiation.type _item_description.description ; The nature of the radiation. This is typically a description of the X-ray wavelength in Siegbahn notation. ; _item.name '_diffrn_radiation.type' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'CuK\a' 'Cu K\a~1~' 'Cu K-L~2,3~' 'white-beam' save_ save__diffrn_radiation.xray_symbol _item_description.description ; The IUPAC symbol for the X-ray wavelength for the probe radiation. ; _item.name '_diffrn_radiation.xray_symbol' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_xray_symbol' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value _item_enumeration.detail 'K-L~3~' 'K\a~1~ in older Siegbahn notation' 'K-L~2~' 'K\a~2~ in older Siegbahn notation' 'K-M~3~' 'K\b~1~ in older Siegbahn notation' 'K-L~2,3~' 'use where K-L~3~ and K-L~2~ are not resolved' save_ save__diffrn_radiation.wavelength_id _item_description.description ; This data item is a pointer to _diffrn_radiation_wavelength.id in the DIFFRN_RADIATION_WAVELENGTH category. ; _item.name '_diffrn_radiation.wavelength_id' _item.category_id diffrn_radiation _item.mandatory_code yes _item_type.code code save_ ################ # DIFFRN_REFLN # ################ save_DIFFRN_REFLN _category.description ; This category redefinition has been added to extend the key of the standard DIFFRN_REFLN category. ; _category.id diffrn_refln _category.mandatory_code no _category_key.name '_diffrn_refln.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_refln.frame_id _item_description.description ; This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_refln.frame_id' _item.category_id diffrn_refln _item.mandatory_code yes _item_type.code code save_ ############### # DIFFRN_SCAN # ############### save_DIFFRN_SCAN _category.description ; Data items in the DIFFRN_SCAN category describe the parameters of one or more scans, relating axis positions to frames. ; _category.id diffrn_scan _category.mandatory_code no _category_key.name '_diffrn_scan.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - derived from a suggestion by R. M. Sweet. The vector of each axis is not given here, because it is provided in the AXIS category. By making _diffrn_scan_axis.scan_id and _diffrn_scan_axis.axis_id keys of the DIFFRN_SCAN_AXIS category, an arbitrary number of scanning and fixed axes can be specified for a scan. In this example, three rotation axes and one translation axis at nonzero values are specified, with one axis stepping. There is no reason why more axes could not have been specified to step. Range information has been specified, but note that it can be calculated from the number of frames and the increment, so the data item _diffrn_scan_axis.angle_range could be dropped. Both the sweep data and the data for a single frame are specified. Note that the information on how the axes are stepped is given twice, once in terms of the overall averages in the value of _diffrn_scan.integration_time and the values for DIFFRN_SCAN_AXIS, and precisely for the given frame in the value for _diffrn_scan_frame.integration_time and the values for DIFFRN_SCAN_FRAME_AXIS. If dose-related adjustments are made to scan times and nonlinear stepping is done, these values may differ. Therefore, in interpreting the data for a particular frame it is important to use the frame-specific data. ; ; _diffrn_scan.id 1 _diffrn_scan.date_start '2001-11-18T03:26:42' _diffrn_scan.date_end '2001-11-18T03:36:45' _diffrn_scan.integration_time 3.0 _diffrn_scan.frame_id_start mad_L2_000 _diffrn_scan.frame_id_end mad_L2_200 _diffrn_scan.frames 201 loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment 1 omega 200.0 20.0 0.1 . . . 1 kappa -40.0 0.0 0.0 . . . 1 phi 127.5 0.0 0.0 . . . 1 tranz . . . 2.3 0.0 0.0 _diffrn_scan_frame.scan_id 1 _diffrn_scan_frame.date '2001-11-18T03:27:33' _diffrn_scan_frame.integration_time 3.0 _diffrn_scan_frame.frame_id mad_L2_018 _diffrn_scan_frame.frame_number 18 loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.angle_increment _diffrn_scan_frame_axis.displacement _diffrn_scan_frame_axis.displacement_increment mad_L2_018 omega 201.8 0.1 . . mad_L2_018 kappa -40.0 0.0 . . mad_L2_018 phi 127.5 0.0 . . mad_L2_018 tranz . . 2.3 0.0 ; ; Example 2 - a more extensive example (R. M. Sweet, P. J. Ellis & H. J. Bernstein). A detector is placed 240 mm along the Z axis from the goniometer. This leads to a choice: either the axes of the detector are defined at the origin, and then a Z setting of -240 is entered, or the axes are defined with the necessary Z offset. In this case, the setting is used and the offset is left as zero. This axis is called DETECTOR_Z. The axis for positioning the detector in the Y direction depends on the detector Z axis. This axis is called DETECTOR_Y. The axis for positioning the detector in the X direction depends on the detector Y axis (and therefore on the detector Z axis). This axis is called DETECTOR_X. This detector may be rotated around the Y axis. This rotation axis depends on the three translation axes. It is called DETECTOR_PITCH. A coordinate system is defined on the face of the detector in terms of 2300 0.150 mm pixels in each direction. The ELEMENT_X axis is used to index the first array index of the data array and the ELEMENT_Y axis is used to index the second array index. Because the pixels are 0.150mm x 0.150mm, the centre of the first pixel is at (0.075, 0.075) in this coordinate system. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 172.43 -172.43 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 2300 1 increasing ELEMENT_X ARRAY1 2 2300 2 increasing ELEMENT_Y # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.075 0.150 ELEMENT_Y ELEMENT_Y 0.075 0.150 # category ARRAY_ELEMENT_SIZE loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 ARRAY1 2 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; ; Example 3 - Example 2 revised for a spiral scan (R. M. Sweet, P. J. Ellis & H. J. Bernstein). A detector is placed 240 mm along the Z axis from the goniometer, as in Example 2 above, but in this example the image plate is scanned in a spiral pattern from the outside edge in. The axis for positioning the detector in the Y direction depends on the detector Z axis. This axis is called DETECTOR_Y. The axis for positioning the detector in the X direction depends on the detector Y axis (and therefore on the detector Z axis). This axis is called DETECTOR_X. This detector may be rotated around the Y axis. This rotation axis depends on the three translation axes. It is called DETECTOR_PITCH. A coordinate system is defined on the face of the detector in terms of a coupled rotation axis and radial scan axis to form a spiral scan. The rotation axis is called ELEMENT_ROT and the radial axis is called ELEMENT_RAD. A 150 micrometre radial pitch and a 75 micrometre 'constant velocity' angular pitch are assumed. Indexing is carried out first on the rotation axis and the radial axis is made to be dependent on it. The two axes are coupled to form an axis set ELEMENT_SPIRAL. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_ROT translation detector DETECTOR_PITCH 0 0 1 0 0 0 ELEMENT_RAD translation detector ELEMENT_ROT 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.angle _array_structure_list_axis.displacement _array_structure_list_axis.angular_pitch _array_structure_list_axis.radial_pitch ELEMENT_SPIRAL ELEMENT_ROT 0 . 0.075 . ELEMENT_SPIRAL ELEMENT_RAD . 172.5 . -0.150 # category ARRAY_ELEMENT_SIZE # the actual pixels are 0.075 by 0.150 mm # We give the coarser dimension here. loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_scan.id _item_description.description ; The value of _diffrn_scan.id uniquely identifies each scan. The identifier is used to tie together all the information about the scan. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_scan.id' diffrn_scan yes '_diffrn_scan_axis.scan_id' diffrn_scan_axis yes '_diffrn_scan_frame.scan_id' diffrn_scan_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_scan_axis.scan_id' '_diffrn_scan.id' '_diffrn_scan_frame.scan_id' '_diffrn_scan.id' save_ save__diffrn_scan.date_end _item_description.description ; The date and time of the end of the scan. Note that this may be an estimate generated during the scan, before the precise time of the end of the scan is known. ; _item.name '_diffrn_scan.date_end' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.date_start _item_description.description ; The date and time of the start of the scan. ; _item.name '_diffrn_scan.date_start' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.integration_time _item_description.description ; Approximate average time in seconds to integrate each step of the scan. The precise time for integration of each particular step must be provided in _diffrn_scan_frame.integration_time, even if all steps have the same integration time. ; _item.name '_diffrn_scan.integration_time' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan.frame_id_start _item_description.description ; The value of this data item is the identifier of the first frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_start' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frame_id_end _item_description.description ; The value of this data item is the identifier of the last frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_end' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frames _item_description.description ; The value of this data item is the number of frames in the scan. ; _item.name '_diffrn_scan.frames' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 1 1 1 save_ #################### # DIFFRN_SCAN_AXIS # #################### save_DIFFRN_SCAN_AXIS _category.description ; Data items in the DIFFRN_SCAN_AXIS category describe the settings of axes for particular scans. Unspecified axes are assumed to be at their zero points. ; _category.id diffrn_scan_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_axis.scan_id' '_diffrn_scan_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_axis.scan_id _item_description.description ; The value of this data item is the identifier of the scan for which axis settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan.id. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_axis.scan_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the scan for which settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan.id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_axis.axis_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.angle_start _item_description.description ; The starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_range _item_description.description ; The range from the starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_increment _item_description.description ; The increment for each step for the specified axis in degrees. In general, this will agree with _diffrn_scan_frame_axis.angle_increment. The sum of the values of _diffrn_scan_frame_axis.angle and _diffrn_scan_frame_axis.angle_increment is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of _diffrn_scan_axis.angle_increment will be representative of the ensemble of values of _diffrn_scan_frame_axis.angle_increment (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_rstrt_incr _item_description.description ; The increment after each step for the specified axis in degrees. In general, this will agree with _diffrn_scan_frame_axis.angle_rstrt_incr. The sum of the values of _diffrn_scan_frame_axis.angle, _diffrn_scan_frame_axis.angle_increment and _diffrn_scan_frame_axis.angle_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame and should equal _diffrn_scan_frame_axis.angle for this next frame. If the individual frame values vary, then the value of _diffrn_scan_axis.angle_rstrt_incr will be representative of the ensemble of values of _diffrn_scan_frame_axis.angle_rstrt_incr (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.displacement_start _item_description.description ; The starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_range _item_description.description ; The range from the starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_increment _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with _diffrn_scan_frame_axis.displacement_increment. The sum of the values of _diffrn_scan_frame_axis.displacement and _diffrn_scan_frame_axis.displacement_increment is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of _diffrn_scan_axis.displacement_increment will be representative of the ensemble of values of _diffrn_scan_frame_axis.displacement_increment (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_rstrt_incr _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with _diffrn_scan_frame_axis.displacement_rstrt_incr. The sum of the values of _diffrn_scan_frame_axis.displacement, _diffrn_scan_frame_axis.displacement_increment and _diffrn_scan_frame_axis.displacement_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame and should equal _diffrn_scan_frame_axis.displacement for this next frame. If the individual frame values vary, then the value of _diffrn_scan_axis.displacement_rstrt_incr will be representative of the ensemble of values of _diffrn_scan_frame_axis.displacement_rstrt_incr (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ ##################### # DIFFRN_SCAN_FRAME # ##################### save_DIFFRN_SCAN_FRAME _category.description ; Data items in the DIFFRN_SCAN_FRAME category describe the relationships of particular frames to scans. ; _category.id diffrn_scan_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame.scan_id' '_diffrn_scan_frame.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame.date _item_description.description ; The date and time of the start of the frame being scanned. ; _item.name '_diffrn_scan_frame.date' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan_frame.frame_id _item_description.description ; The value of this data item is the identifier of the frame being examined. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame.frame_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame.frame_number _item_description.description ; The value of this data item is the number of the frame within the scan, starting with 1. It is not necessarily the same as the value of _diffrn_scan_frame.frame_id, but it may be. ; _item.name '_diffrn_scan_frame.frame_number' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 0 0 0 save_ save__diffrn_scan_frame.integration_time _item_description.description ; The time in seconds to integrate this step of the scan. This should be the precise time of integration of each particular frame. The value of this data item should be given explicitly for each frame and not inferred from the value of _diffrn_scan.integration_time. ; _item.name '_diffrn_scan_frame.integration_time' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame.scan_id _item_description.description ; The value of _diffrn_scan_frame.scan_id identifies the scan containing this frame. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_frame.scan_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ ########################## # DIFFRN_SCAN_FRAME_AXIS # ########################## save_DIFFRN_SCAN_FRAME_AXIS _category.description ; Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the settings of axes for particular frames. Unspecified axes are assumed to be at their zero points. If, for any given frame, nonzero values apply for any of the data items in this category, those values should be given explicitly in this category and not simply inferred from values in DIFFRN_SCAN_AXIS. ; _category.id diffrn_scan_frame_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame_axis.frame_id' '_diffrn_scan_frame_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the frame for which settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_frame_axis.axis_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_axis.angle _item_description.description ; The setting of the specified axis in degrees for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.angle' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_increment _item_description.description ; The increment for this frame for the angular setting of the specified axis in degrees. The sum of the values of _diffrn_scan_frame_axis.angle and _diffrn_scan_frame_axis.angle_increment is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.angle_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_rstrt_incr _item_description.description ; The increment after this frame for the angular setting of the specified axis in degrees. The sum of the values of _diffrn_scan_frame_axis.angle, _diffrn_scan_frame_axis.angle_increment and _diffrn_scan_frame_axis.angle_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame and should equal _diffrn_scan_frame_axis.angle for this next frame. ; _item.name '_diffrn_scan_frame_axis.angle_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.displacement' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_increment _item_description.description ; The increment for this frame for the displacement setting of the specified axis in millimetres. The sum of the values of _diffrn_scan_frame_axis.displacement and _diffrn_scan_frame_axis.displacement_increment is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.displacement_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_rstrt_incr _item_description.description ; The increment for this frame for the displacement setting of the specified axis in millimetres. The sum of the values of _diffrn_scan_frame_axis.displacement, _diffrn_scan_frame_axis.displacement_increment and _diffrn_scan_frame_axis.displacement_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame and should equal _diffrn_scan_frame_axis.displacement for this next frame. ; _item.name '_diffrn_scan_frame_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.frame_id _item_description.description ; The value of this data item is the identifier of the frame for which axis settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame_axis.frame_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ ######################## DEPRECATED DATA ITEMS ######################## save__diffrn_detector_axis.id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_detector_axis.id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.id _item_description.description ; This data item is a pointer to _diffrn_measurement.id in the DIFFRN_MEASUREMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_measurement_axis.id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ ######################### DEPRECATED CATEGORY ######################### ##################### # DIFFRN_FRAME_DATA # ##################### save_DIFFRN_FRAME_DATA _category.description ; Data items in the DIFFRN_FRAME_DATA category record the details about each frame of data. The items in this category are now in the DIFFRN_DATA_FRAME category. The items in the DIFFRN_FRAME_DATA category are now deprecated. The items from this category are provided as aliases in version 1.0 of the dictionary but should not be used for new work. The items from the old category are provided in this dictionary for completeness but should not be used or cited. To avoid confusion, the example has been removed and the redundant parent-child links to other categories have been removed. ; _category.id diffrn_frame_data _category.mandatory_code no loop_ _category_key.name '_diffrn_frame_data.id' '_diffrn_frame_data.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; THE DIFFRN_FRAME_DATA category is deprecated and should not be used. ; ; # EXAMPLE REMOVED # ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_frame_data.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.array_id' _item.category_id diffrn_frame_data _item.mandatory_code yes _item_type.code code save_ save__diffrn_frame_data.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.binary_id' _item.category_id diffrn_frame_data _item.mandatory_code implicit _item_type.code int save_ save__diffrn_frame_data.detector_element_id _item_description.description ; This item is a pointer to _diffrn_detector_element.id in the DIFFRN_DETECTOR_ELEMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.detector_element_id' _item.category_id diffrn_frame_data _item.mandatory_code yes _item_type.code code save_ save__diffrn_frame_data.id _item_description.description ; The value of _diffrn_frame_data.id must uniquely identify each complete frame of data. DEPRECATED -- DO NOT USE ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_frame_data.id' diffrn_frame_data yes _item_type.code code save_ ################ END DEPRECATED SECTION ########### #################### ## ITEM_TYPE_LIST ## #################### # # # The regular expressions defined here are not compliant # with the POSIX 1003.2 standard as they include the # '\n' and '\t' special characters. These regular expressions # have been tested using version 0.12 of Richard Stallman's # GNU regular expression library in POSIX mode. # In order to allow presentation of a regular expression # in a text field concatenate any line ending in a backslash # with the following line, after discarding the backslash. # # A formal definition of the '\n' and '\t' special characters # is most properly done in the DDL, but for completeness, please # note that '\n' is the line termination character ('newline') # and '\t' is the horizontal tab character. There is a formal # ambiguity in the use of '\n' for line termination, in that # the intention is that the equivalent machine/OS-dependent line # termination character sequence should be accepted as a match, e.g. # # '\r' (control-M) under MacOS # '\n' (control-J) under Unix # '\r\n' (control-M control-J) under DOS and MS Windows # loop_ _item_type_list.code _item_type_list.primitive_code _item_type_list.construct _item_type_list.detail code char '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words ... ; ucode uchar '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words (case insensitive) ... ; line char '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; char item types / multi-word items ... ; uline uchar '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; char item types / multi-word items (case insensitive)... ; text char '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; text item types / multi-line text ... ; binary char ;\n--CIF-BINARY-FORMAT-SECTION--\n\ [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\ \n--CIF-BINARY-FORMAT-SECTION---- ; ; binary items are presented as MIME-like ascii-encoded sections in an imgCIF. In a CBF, raw octet streams are used to convey the same information. ; int numb '-?[0-9]+' ; int item types are the subset of numbers that are the negative or positive integers. ; float numb '-?(([0-9]+)[.]?|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?' ; float item types are the subset of numbers that are the floating numbers. ; any char '.*' ; A catch all for items that may take any form... ; yyyy-mm-dd char ;\ [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9][0-9]\ (T[0-2][0-9]:[0-5][0-9]:[0-5][0-9](.[0-9]+)([+-][0-5][0-9]:[0-5][0-9]))? ; ; Standard format for CIF date and time strings (see http://www.iucr.org/iucr-top/cif/spec/datetime.html), consisting of a yyyy-mm-dd date optionally followed by the character "T" followed by a 24-hour clock time, optionally followed by a signed time-zone offset. The IUCr standard has been extended to allow for an optional decimal fraction on the seconds of time. Time is local time if no time-zone offset is given. ; ##################### ## ITEM_UNITS_LIST ## ##################### loop_ _item_units_list.code _item_units_list.detail # 'metres' 'metres' 'centimetres' 'centimetres (metres * 10^( -2))' 'millimetres' 'millimetres (metres * 10^( -3))' 'nanometres' 'nanometres (metres * 10^( -9))' 'angstroms' 'angstroms (metres * 10^(-10))' 'picometres' 'picometres (metres * 10^(-12))' 'femtometres' 'femtometres (metres * 10^(-15))' # 'reciprocal_metres' 'reciprocal metres (metres^(-1))' 'reciprocal_centimetres' 'reciprocal centimetres ((metres * 10^( -2))^(-1))' 'reciprocal_millimetres' 'reciprocal millimetres ((metres * 10^( -3))^(-1))' 'reciprocal_nanometres' 'reciprocal nanometres ((metres * 10^( -9))^(-1))' 'reciprocal_angstroms' 'reciprocal angstroms ((metres * 10^(-10))^(-1))' 'reciprocal_picometres' 'reciprocal picometres ((metres * 10^(-12))^(-1))' # 'nanometres_squared' 'nanometres squared (metres * 10^( -9))^2' 'angstroms_squared' 'angstroms squared (metres * 10^(-10))^2' '8pi2_angstroms_squared' '8pi^2 * angstroms squared (metres * 10^(-10))^2' 'picometres_squared' 'picometres squared (metres * 10^(-12))^2' # 'nanometres_cubed' 'nanometres cubed (metres * 10^( -9))^3' 'angstroms_cubed' 'angstroms cubed (metres * 10^(-10))^3' 'picometres_cubed' 'picometres cubed (metres * 10^(-12))^3' # 'kilopascals' 'kilopascals' 'gigapascals' 'gigapascals' # 'hours' 'hours' 'minutes' 'minutes' 'seconds' 'seconds' 'microseconds' 'microseconds' # 'degrees' 'degrees (of arc)' 'degrees_squared' 'degrees (of arc) squared' # 'degrees_per_minute' 'degrees (of arc) per minute' # 'celsius' 'degrees (of temperature) Celsius' 'kelvins' 'degrees (of temperature) Kelvin' # 'counts' 'counts' 'counts_per_photon' 'counts per photon' # 'electrons' 'electrons' # 'electrons_squared' 'electrons squared' # 'electrons_per_nanometres_cubed' ; electrons per nanometres cubed (electrons/(metres * 10^( -9))^(-3)) ; 'electrons_per_angstroms_cubed' ; electrons per angstroms cubed (electrons/(metres * 10^(-10))^(-3)) ; 'electrons_per_picometres_cubed' ; electrons per picometres cubed (electrons/(metres * 10^(-12))^(-3)) ; 'kilowatts' 'kilowatts' 'milliamperes' 'milliamperes' 'kilovolts' 'kilovolts' # 'arbitrary' ; arbitrary system of units. ; # loop_ _item_units_conversion.from_code _item_units_conversion.to_code _item_units_conversion.operator _item_units_conversion.factor ### 'metres' 'centimetres' '*' 1.0E+02 'metres' 'millimetres' '*' 1.0E+03 'metres' 'nanometres' '*' 1.0E+09 'metres' 'angstroms' '*' 1.0E+10 'metres' 'picometres' '*' 1.0E+12 'metres' 'femtometres' '*' 1.0E+15 # 'centimetres' 'metres' '*' 1.0E-02 'centimetres' 'millimetres' '*' 1.0E+01 'centimetres' 'nanometres' '*' 1.0E+07 'centimetres' 'angstroms' '*' 1.0E+08 'centimetres' 'picometres' '*' 1.0E+10 'centimetres' 'femtometres' '*' 1.0E+13 # 'millimetres' 'metres' '*' 1.0E-03 'millimetres' 'centimetres' '*' 1.0E-01 'millimetres' 'nanometres' '*' 1.0E+06 'millimetres' 'angstroms' '*' 1.0E+07 'millimetres' 'picometres' '*' 1.0E+09 'millimetres' 'femtometres' '*' 1.0E+12 # 'nanometres' 'metres' '*' 1.0E-09 'nanometres' 'centimetres' '*' 1.0E-07 'nanometres' 'millimetres' '*' 1.0E-06 'nanometres' 'angstroms' '*' 1.0E+01 'nanometres' 'picometres' '*' 1.0E+03 'nanometres' 'femtometres' '*' 1.0E+06 # 'angstroms' 'metres' '*' 1.0E-10 'angstroms' 'centimetres' '*' 1.0E-08 'angstroms' 'millimetres' '*' 1.0E-07 'angstroms' 'nanometres' '*' 1.0E-01 'angstroms' 'picometres' '*' 1.0E+02 'angstroms' 'femtometres' '*' 1.0E+05 # 'picometres' 'metres' '*' 1.0E-12 'picometres' 'centimetres' '*' 1.0E-10 'picometres' 'millimetres' '*' 1.0E-09 'picometres' 'nanometres' '*' 1.0E-03 'picometres' 'angstroms' '*' 1.0E-02 'picometres' 'femtometres' '*' 1.0E+03 # 'femtometres' 'metres' '*' 1.0E-15 'femtometres' 'centimetres' '*' 1.0E-13 'femtometres' 'millimetres' '*' 1.0E-12 'femtometres' 'nanometres' '*' 1.0E-06 'femtometres' 'angstroms' '*' 1.0E-05 'femtometres' 'picometres' '*' 1.0E-03 ### 'reciprocal_centimetres' 'reciprocal_metres' '*' 1.0E+02 'reciprocal_centimetres' 'reciprocal_millimetres' '*' 1.0E-01 'reciprocal_centimetres' 'reciprocal_nanometres' '*' 1.0E-07 'reciprocal_centimetres' 'reciprocal_angstroms' '*' 1.0E-08 'reciprocal_centimetres' 'reciprocal_picometres' '*' 1.0E-10 # 'reciprocal_millimetres' 'reciprocal_metres' '*' 1.0E+03 'reciprocal_millimetres' 'reciprocal_centimetres' '*' 1.0E+01 'reciprocal_millimetres' 'reciprocal_nanometres' '*' 1.0E-06 'reciprocal_millimetres' 'reciprocal_angstroms' '*' 1.0E-07 'reciprocal_millimetres' 'reciprocal_picometres' '*' 1.0E-09 # 'reciprocal_nanometres' 'reciprocal_metres' '*' 1.0E+09 'reciprocal_nanometres' 'reciprocal_centimetres' '*' 1.0E+07 'reciprocal_nanometres' 'reciprocal_millimetres' '*' 1.0E+06 'reciprocal_nanometres' 'reciprocal_angstroms' '*' 1.0E-01 'reciprocal_nanometres' 'reciprocal_picometres' '*' 1.0E-03 # 'reciprocal_angstroms' 'reciprocal_metres' '*' 1.0E+10 'reciprocal_angstroms' 'reciprocal_centimetres' '*' 1.0E+08 'reciprocal_angstroms' 'reciprocal_millimetres' '*' 1.0E+07 'reciprocal_angstroms' 'reciprocal_nanometres' '*' 1.0E+01 'reciprocal_angstroms' 'reciprocal_picometres' '*' 1.0E-02 # 'reciprocal_picometres' 'reciprocal_metres' '*' 1.0E+12 'reciprocal_picometres' 'reciprocal_centimetres' '*' 1.0E+10 'reciprocal_picometres' 'reciprocal_millimetres' '*' 1.0E+09 'reciprocal_picometres' 'reciprocal_nanometres' '*' 1.0E+03 'reciprocal_picometres' 'reciprocal_angstroms' '*' 1.0E+01 ### 'nanometres_squared' 'angstroms_squared' '*' 1.0E+02 'nanometres_squared' 'picometres_squared' '*' 1.0E+06 # 'angstroms_squared' 'nanometres_squared' '*' 1.0E-02 'angstroms_squared' 'picometres_squared' '*' 1.0E+04 'angstroms_squared' '8pi2_angstroms_squared' '*' 78.9568 # 'picometres_squared' 'nanometres_squared' '*' 1.0E-06 'picometres_squared' 'angstroms_squared' '*' 1.0E-04 ### 'nanometres_cubed' 'angstroms_cubed' '*' 1.0E+03 'nanometres_cubed' 'picometres_cubed' '*' 1.0E+09 # 'angstroms_cubed' 'nanometres_cubed' '*' 1.0E-03 'angstroms_cubed' 'picometres_cubed' '*' 1.0E+06 # 'picometres_cubed' 'nanometres_cubed' '*' 1.0E-09 'picometres_cubed' 'angstroms_cubed' '*' 1.0E-06 ### 'kilopascals' 'gigapascals' '*' 1.0E-06 'gigapascals' 'kilopascals' '*' 1.0E+06 ### 'hours' 'minutes' '*' 6.0E+01 'hours' 'seconds' '*' 3.6E+03 'hours' 'microseconds' '*' 3.6E+09 # 'minutes' 'hours' '/' 6.0E+01 'minutes' 'seconds' '*' 6.0E+01 'minutes' 'microseconds' '*' 6.0E+07 # 'seconds' 'hours' '/' 3.6E+03 'seconds' 'minutes' '/' 6.0E+01 'seconds' 'microseconds' '*' 1.0E+06 # 'microseconds' 'hours' '/' 3.6E+09 'microseconds' 'minutes' '/' 6.0E+07 'microseconds' 'seconds' '/' 1.0E+06 ### 'celsius' 'kelvins' '-' 273.0 'kelvins' 'celsius' '+' 273.0 ### 'electrons_per_nanometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E+03 'electrons_per_nanometres_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+09 # 'electrons_per_angstroms_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-03 'electrons_per_angstroms_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+06 # 'electrons_per_picometres_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-09 'electrons_per_picometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E-06 ### ######################## ## DICTIONARY_HISTORY ## ######################## loop_ _dictionary_history.version _dictionary_history.update _dictionary_history.revision 1.3.2 2005-06-25 ; 2005-06-25 ITEM_TYPE_LIST: code, ucode, line, uline regexps updated to those of current mmCIF; float modified by allowing integers terminated by a point as valid. The 'time' part of yyyy-mm-dd types made optional in the regexp. (BM) 2005-06-17 Minor corrections as for proofs for IT G Chapter 4.6 (NJA) 2005-02-21 Minor corrections to spelling and punctuation (NJA) 2005-01-08 Changes as per Nicola Ashcroft. + Updated example 1 for DIFFRN_MEASUREMENT to agree with mmCIF. + Spelled out "micrometres" for "um" and "millimetres" for "mm". + Removed phrase "which may be stored" from ARRAY_STRUCTURE description. + Removed unused 'byte-offsets' compressions and updated cites to ITVG for '_array_structure.compression_type'. (HJB) ; 1.3.1 2003-08-13 ; Changes as per Frances C. Bernstein. + Identify initials. + Adopt British spelling for centre in text. + Set \p and \%Angstrom and powers. + Clean up commas and unclear wordings. + Clean up tenses in history. Changes as per Gotzon Madariaga. + Fix the ARRAY_DATA example to align '_array_data.binary_id' and X-Binary-Id. + Add a range to '_array_intensities.gain_esd'. + In the example of DIFFRN_DETECTOR_ELEMENT, '_diffrn_detector_element.id' and '_diffrn_detector_element.detector_id' interchanged. + Fix typos for direction, detector and axes. + Clarify description of polarisation. + Clarify axes in '_diffrn_detector_element.center[1]' '_diffrn_detector_element.center[2]'. + Add local item types for items that are pointers. (HJB) ; 1.3.0 2003-07-24 ; Changes as per Brian McMahon. + Consistently quote tags embedded in text. + Clean up introductory comments. + Adjust line lengths to fit in 80 character window. + Fix several descriptions in AXIS category which referred to '_axis.type' instead of the current item. + Fix erroneous use of deprecated item '_diffrn_detector_axis.id' in examples for DIFFRN_SCAN_AXIS. + Add deprecated items '_diffrn_detector_axis.id' and '_diffrn_measurement_axis.id'. (HJB) ; 1.2.4 2003-07-14 ; Changes as per I. David Brown. + Enhance descriptions in DIFFRN_SCAN_AXIS to make them less dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS. + Provide a copy of the deprecated DIFFRN_FRAME_DATA category for completeness. (HJB) ; 1.2.3 2003-07-03 ; Cleanup to conform to ITVG. + Correct sign error in ..._cubed units. + Correct '_diffrn_radiation.polarisn_norm' range. (HJB) ; 1.2.2 2003-03-10 ; Correction of typos in various DIFFRN_SCAN_AXIS descriptions. (HJB) ; 1.2.1 2003-02-22 ; Correction of ATOM_ for ARRAY_ typos in various descriptions. (HJB) ; 1.2 2003-02-07 ; Corrections to encodings (remove extraneous hyphens) remove extraneous underscore in '_array_structure.encoding_type' enumeration. Correct typos in items units list. (HJB) ; 1.1.3 2001-04-19 ; Another typo corrections by Wilfred Li, and cleanup by HJB. ; 1.1.2 2001-03-06 ; Several typo corrections by Wilfred Li. ; 1.1.1 2001-02-16 ; Several typo corrections by JW. ; 1.1 2001-02-06 ; Draft resulting from discussions on header for use at NSLS. (HJB) + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME. + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'. + Add '_diffrn_measurement_axis.measurement_device' and change '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'. + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source', '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm', '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end', '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr', '_diffrn_scan_axis.displacement_rstrt_incr', '_diffrn_scan_frame_axis.angle_increment', '_diffrn_scan_frame_axis.angle_rstrt_incr', '_diffrn_scan_frame_axis.displacement', '_diffrn_scan_frame_axis.displacement_increment',and '_diffrn_scan_frame_axis.displacement_rstrt_incr'. + Add '_diffrn_measurement.device' to category key. + Update yyyy-mm-dd to allow optional time with fractional seconds for time stamps. + Fix typos caught by RS. + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to allow for coupled axes, as in spiral scans. + Add examples for fairly complete headers thanks to R. Sweet and P. Ellis. ; 1.0 2000-12-21 ; Release version - few typos and tidying up. (BM & HJB) + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end of dictionary. + Alphabetize dictionary. ; 0.7.1 2000-09-29 ; Cleanup fixes. (JW) + Correct spelling of diffrn_measurement_axis in '_axis.id' + Correct ordering of uses of '_item.mandatory_code' and '_item_default.value'. ; 0.7.0 2000-09-09 ; Respond to comments by I. David Brown. (HJB) + Add further comments on '\n' and '\t'. + Update ITEM_UNITS_LIST by taking section from mmCIF dictionary and adding metres. Change 'meter' to 'metre' throughout. + Add missing enumerations to '_array_structure.compression_type' and make 'none' the default. + Remove parent-child relationship between '_array_structure_list.index' and '_array_structure_list.precedence'. + Improve alphabetization. + Fix '_array_intensities_gain.esd' related function. + Improve comments in AXIS. + Fix DIFFRN_FRAME_DATA example. + Remove erroneous DIFFRN_MEASUREMENT example. + Add '_diffrn_measurement_axis.id' to the category key. ; 0.6.0 1999-01-14 ; Remove redundant information for ENC_NONE data. (HJB) + After the D5 remove binary section identifier, size and compression type. + Add Control-L to header. ; 0.5.1 1999-01-03 ; Cleanup of typos and syntax errors. (HJB) + Cleanup example details for DIFFRN_SCAN category. + Add missing quote marks for '_diffrn_scan.id' definition. ; 0.5 1999-01-01 ; Modifications for axis definitions and reduction of binary header. (HJB) + Restore '_diffrn_detector.diffrn_id' to DIFFRN_DETECTOR KEY. + Add AXIS category. + Bring in complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories from cif_mm.dic for clarity. + Change '_array_structure.encoding_type' from type code to uline and added X-Binary-Element-Type to MIME header. + Add detector beam centre '_diffrn_detector_element.center[1]' and '_diffrn_detector_element.center[2]'. + Correct item name of '_diffrn_refln.frame_id'. + Replace reference to '_array_intensities.undefined' by '_array_intensities.undefined_value'. + Replace references to '_array_intensity.scaling' with '_array_intensities.scaling'. + Add DIFFRN_SCAN... categories. ; 0.4 1998-08-11 ; Modifications to the 0.3 imgCIF draft. (HJB) + Reflow comment lines over 80 characters and corrected typos. + Update examples and descriptions of MIME encoded data. + Change name to cbfext98.dic. ; 0.3 1998-07-04 ; Modifications for imgCIF. (HJB) + Add binary type, which is a text field containing a variant on MIME encoded data. + Change type of '_array_data.data' to binary and specify internal structure of raw binary data. + Add '_array_data.binary_id', and make '_diffrn_frame_data.binary_id' and '_array_intensities.binary_id' into pointers to this item. ; 0.2 1997-12-02 ; Modifications to the CBF draft. (JW) + Add category hierarchy for describing frame data developed from discussions at the BNL imgCIF Workshop Oct 1997. The following changes are made in implementing the workshop draft. Category DIFFRN_ARRAY_DATA is renamed to DIFFRN_FRAME_DATA. Category DIFFRN_FRAME_TYPE is renamed to DIFFRN_DETECTOR_ELEMENT. The parent item for '_diffrn_frame_data.array_id' is changed from '_array_structure_list.array_id' to '_array_structure.id'. Item '_diffrn_detector.array_id' is deleted. + Add data item '_diffrn_frame_data.binary_id' to identify data groups within a binary section. The formal identification of the binary section is still fuzzy. ; 0.1 1997-01-24 ; First draft of this dictionary in DDL 2.1 compliant format by John Westbrook (JW). This version is adapted from the Crystallographic Binary File (CBF) Format Draft Proposal provided by Andy Hammersley (AH). Modifications to the CBF draft. (JW) + In this version the array description has been cast in the categories ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. These categories have been generalized to describe array data of arbitrary dimension. + Array data in this description are contained in the category ARRAY_DATA. This departs from the CBF notion of data existing in some special comment. In this description, data is handled as an ordinary data item encapsulated in a character data type. Although data this manner deviates from CIF conventions, it does not violate any DDL 2.1 rules. DDL 2.1 regular expressions can be used to define the binary representation which will permit some level of data validation. In this version, the placeholder type code "any" has been used. This translates to a regular expression which will match any pattern. It should be noted that DDL 2.1 already supports array data objects although these have not been used in the current mmCIF dictionary. It may be possible to use the DDL 2.1 ITEM_STRUCTURE and ITEM_STRUCTURE_LIST categories to provide the information that is carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. By moving the array structure to the DDL level it would be possible to define an array type as well as a regular expression defining the data format. + Multiple array sections can be properly handled within a single datablock. ; #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof ./CBFlib-0.9.2.2/doc/cif_img_1_3.dic0000644000076500007650000054034611603702115015077 0ustar yayayaya ############################################################################## # # # Image CIF Dictionary (imgCIF) # # and Crystallographic Binary File Dictionary (CBF) # # Extending the Macromolecular CIF Dictionary (mmCIF) # # # # Version 1.3.0 # # of 2003-07-24 # # # # by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook # # # # This dictionary was adapted from format discussed at the imgCIF Workshop, # # held at BNL Oct 1997 and the Crystallographic Binary File Format Draft # # Proposal by Andrew Hammersley. The first DDL 2.1 Version was created by # # John Westbrook. This version was drafted by Herbert J. Bernstein and # # incorporates comments by I. David Brown, John Westbrook, Brian McMahon, # # Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li and others. # ############################################################################## data_cif_img.dic _dictionary.title cif_img.dic _dictionary.version 1.3.0 _dictionary.datablock_id cif_img.dic ############################################################################## # CONTENTS # # CATEGORY_GROUP_LIST # # category ARRAY_DATA # # _array_data.array_id # _array_data.binary_id # _array_data.data # # category ARRAY_ELEMENT_SIZE # # _array_element_size.array_id # _array_element_size.index # _array_element_size.size # # category ARRAY_INTENSITIES # # _array_intensities.array_id # _array_intensities.binary_id # _array_intensities.gain # _array_intensities.gain_esd # _array_intensities.linearity # _array_intensities.offset # _array_intensities.scaling # _array_intensities.overload # _array_intensities.undefined_value # # category ARRAY_STRUCTURE # # _array_structure.byte_order # _array_structure.compression_type # _array_structure.encoding_type # _array_structure.id # # category ARRAY_STRUCTURE_LIST # # _array_structure_list.axis_set_id # _array_structure_list.array_id # _array_structure_list.dimension # _array_structure_list.direction # _array_structure_list.index # _array_structure_list.precedence # # category ARRAY_STRUCTURE_LIST_AXIS # # _array_structure_list_axis.axis_id # _array_structure_list_axis.axis_set_id # _array_structure_list_axis.angle # _array_structure_list_axis.angle_increment # _array_structure_list_axis.displacement_increment # _array_structure_list_axis.angular_pitch # _array_structure_list_axis.radial_pitch # # category AXIS # # _axis.depends_on # _axis.equipment # _axis.id # _axis.offset[1] # _axis.offset[2] # _axis.offset[3] # _axis.type # _axis.vector[1] # _axis.vector[2] # _axis.vector[3] # # category DIFFRN_DATA_FRAME # # _diffrn_data_frame.array_id # _diffrn_data_frame.binary_id # _diffrn_data_frame.detector_element_id # _diffrn_data_frame.id # # category DIFFRN_DETECTOR # # _diffrn_detector.details # _diffrn_detector.detector # _diffrn_detector.diffrn_id # _diffrn_detector.dtime # _diffrn_detector.id # _diffrn_detector.number_of_axes # _diffrn_detector.type # # category DIFFRN_DETECTOR_AXIS # # _diffrn_detector_axis.axis_id # _diffrn_detector_axis.detector_id # # category DIFFRN_DETECTOR_ELEMENT # # _diffrn_detector_element.center[1] # _diffrn_detector_element.center[2] # _diffrn_detector_element.id # _diffrn_detector_element.detector_id # # category DIFFRN_MEASUREMENT # # _diffrn_measurement.diffrn_id # _diffrn_measurement.details # _diffrn_measurement.device # _diffrn_measurement.device_details # _diffrn_measurement.device_type # _diffrn_measurement.id # _diffrn_measurement.method # _diffrn_measurement.number_of_axes # _diffrn_measurement.specimen_support # # category DIFFRN_MEASUREMENT_AXIS # # _diffrn_measurement_axis.axis_id # _diffrn_measurement_axis.measurement_device # _diffrn_measurement_axis.measurement_id # # category DIFFRN_RADIATION # # _diffrn_radiation.collimation # _diffrn_radiation.diffrn_id # _diffrn_radiation.div_x_source # _diffrn_radiation.div_y_source # _diffrn_radiation.div_x_y_source # _diffrn_radiation.filter_edge' # _diffrn_radiation.inhomogeneity # _diffrn_radiation.monochromator # _diffrn_radiation.polarisn_norm # _diffrn_radiation.polarisn_ratio # _diffrn_radiation.polarizn_source_norm # _diffrn_radiation.polarizn_source_ratio # _diffrn_radiation.probe # _diffrn_radiation.type # _diffrn_radiation.xray_symbol # _diffrn_radiation.wavelength_id # # category DIFFRN_REFLN # # _diffrn_refln.frame_id # # category DIFFRN_SCAN # # _diffrn_scan.id # _diffrn_scan.date_end # _diffrn_scan.date_start # _diffrn_scan.integration_time # _diffrn_scan.frame_id_start # _diffrn_scan.frame_id_end # _diffrn_scan.frames # # category DIFFRN_SCAN_AXIS # # _diffrn_scan_axis.axis_id # _diffrn_scan_axis.angle_start # _diffrn_scan_axis.angle_range # _diffrn_scan_axis.angle_increment # _diffrn_scan_axis.angle_rstrt_incr # _diffrn_scan_axis.displacement_start # _diffrn_scan_axis.displacement_range # _diffrn_scan_axis.displacement_increment # _diffrn_scan_axis.displacement_rstrt_incr # _diffrn_scan_axis.scan_id # # category DIFFRN_SCAN_FRAME # # _diffrn_scan_frame.date # _diffrn_scan_frame.frame_id # _diffrn_scan_frame.frame_number # _diffrn_scan_frame.integration_time # _diffrn_scan_frame.scan_id # # category DIFFRN_SCAN_FRAME_AXIS # # _diffrn_scan_frame_axis.axis_id # _diffrn_scan_frame_axis.angle # _diffrn_scan_frame_axis.angle_increment # _diffrn_scan_frame_axis.angle_rstrt_incr # _diffrn_scan_frame_axis.displacement # _diffrn_scan_frame_axis.displacement_increment # _diffrn_scan_frame_axis.displacement_rstrt_incr # _diffrn_scan_frame_axis.frame_id # # ***DEPRECATED*** data items # # _diffrn_detector_axis.id # _diffrn_measurement_axis.id # # ***DEPRECATED*** category DIFFRN_FRAME_DATA # # _diffrn_frame_data.array_id # _diffrn_frame_data.binary_id # _diffrn_frame_data.detector_element_id # _diffrn_frame_data.id # # # ITEM_TYPE_LIST # ITEM_UNITS_LIST # DICTIONARY_HISTORY # ############################################################################## ######################### ## CATEGORY_GROUP_LIST ## ######################### loop_ _category_group_list.id _category_group_list.parent_id _category_group_list.description 'inclusive_group' . ; Categories that belong to the dictionary extension. ; 'array_data_group' 'inclusive_group' ; Categories that describe array data. ; 'axis_group' 'inclusive_group' ; Categories that describe axes. ; 'diffrn_group' 'inclusive_group' ; Categories that describe details of the diffraction experiment. ; ############## # ARRAY_DATA # ############## save_ARRAY_DATA _category.description ; Data items in the ARRAY_DATA category are the containers for the array data items described in category ARRAY_STRUCTURE. ; _category.id array_data _category.mandatory_code no loop_ _category_key.name '_array_data.array_id' '_array_data.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows two binary data blocks. The first one was compressed by the CBF_CANONICAL compression algorithm and presented as hexadecimal data. The first character "H" on the data lines means hexadecimal. It could have been "O" for octal or "D" for decimal. The second character on the line shows the number of bytes in each word (in this case "4"), which then requires 8 hexadecimal digits per word. The third character gives the order of octets within a word, in this case "<" for the ordering 4321 (i.e. "big-endian"). Alternatively the character ">" could have been used for the ordering 1234 (i.e. "little-endian"). The block has a "message digest" to check the integrity of the data. The second block is similar, but uses CBF_PACKED compression and BASE64 encoding. Note that the size and the digest are different. ; ; loop_ _array_data.array_id _array_data.binary_id _array_data.data image_1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_CANONICAL" Content-Transfer-Encoding: X-BASE16 X-Binary-Size: 3927126 X-Binary-ID: 1 Content-MD5: u2sTJEovAHkmkDjPi+gWsg== # Hexadecimal encoding, byte 0, byte order ...21 # H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ... .... --CIF-BINARY-FORMAT-SECTION---- ; image_2 2 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF-PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3745758 X-Binary-ID: 1 Content-MD5: 1zsJjWPfol2GYl2V+QSXrw== ELhQAAAAAAAA... ... --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_data.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_array_data.array_id' _item.category_id array_data _item.mandatory_code yes _item_type.code code save_ save__array_data.binary_id _item_description.description ; This item is an integer identifier which, along with '_array_data.array_id' should uniquely identify the particular block of array data. If '_array_data.binary_id' is not explicitly given, it defaults to 1. The value of '_array_data.binary_id' distinguishes among multiple sets of data with the same array structure. If the MIME header of the data array specifies a value for X-Binary-Id, these values should be equal. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_data.binary_id' array_data implicit '_diffrn_data_frame.binary_id' diffrn_data_frame implicit '_array_intensities.binary_id' array_intensities implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.binary_id' '_array_data.binary_id' '_array_intensities.binary_id' '_array_data.binary_id' _item_default.value 1 _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_data.data _item_description.description ; The value of '_array_data.data' contains the array data encapsulated in a STAR string. The representation used is a variant on the Multipurpose Internet Mail Extensions (MIME) specified in RFC 2045-2049 by N. Freed et al. The boundary delimiter used in writing an imgCIF or CBF is "--CIF-BINARY-FORMAT-SECTION--" (including the required initial "--"). The Content-Type may be any of the discrete types permitted in RFC 2045; "application/octet-stream" is recommended. If an octet stream was compressed, the compression should be specified by the parameter 'conversions="x-CBF_PACKED"' or the parameter 'conversions="x-CBF_CANONICAL"'. The Content-Transfer-Encoding may be "BASE64", "Quoted-Printable", "X-BASE8", "X-BASE10", or "X-BASE16" for an imgCIF or "BINARY" for a CBF. The octal, decimal and hexadecimal transfer encodings are for convenience in debugging, and are not recommended for archiving and data interchange. In an imgCIF file, the encoded binary data begins after the empty line terminating the header. In a CBF, the raw binary data begins after an empty line terminating the header and after the sequence: Octet Hex Decimal Purpose 0 0C 12 (ctrl-L) Page break 1 1A 26 (ctrl-Z) Stop listings in MS-DOS 2 04 04 (Ctrl-D) Stop listings in UNIX 3 D5 213 Binary section begins None of these octets are included in the calculation of the message size, nor in the calculation of the message digest. The X-Binary-Size header specifies the size of the equivalent binary data in octets. If compression was used, this size is the size after compression, including any book-keeping fields. An adjustment is made for the deprecated binary formats in which 8 bytes of binary header are used for the compression type. In that case, the 8 bytes used for the compression type is subtracted from the size, so that the same size will be reported if the compression type is supplied in the MIME header. Use of the MIME header is the recommended way to supply the compression type. In general, no portion of the binary header is included in the calculation of the size. The X-Binary-Element-Type header specifies the type of binary data in the octets, using the same descriptive phrases as in '_array_structure.encoding_type'. The default value is "unsigned 32-bit integer". An MD5 message digest may, optionally, be used. The "RSA Data Security, Inc. MD5 Message-Digest Algorithm" should be used. No portion of the header is included in the calculation of the message digest. If the Transfer Encoding is "X-BASE8", "X-BASE10", or "X-BASE16", the data is presented as octal, decimal or hexadecimal data organized into lines or words. Each word is created by composing octets of data in fixed groups of 2, 3, 4, 6 or 8 octets, either in the order ...4321 ("big- endian") or 1234... (little-endian). If there are fewer than the specified number of octets to fill the last word, then the missing octets are presented as "==" for each missing octet. Exactly two equal signs are used for each missing octet even for octal and decimal encoding. The format of lines is: rnd xxxxxx xxxxxx xxxxxx where r is "H", "O", or "D" for hexadecimal, octal or decimal, n is the number of octets per word. and d is "<" for ">" for the "...4321" and "1234..." octet orderings respectively. The "==" padding for the last word should be on the appropriate side to correspond to the missing octets, e.g. H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000 or H3> FF0700 00==== For these hex, octal and decimal formats, only, comments beginning with "#" are permitted to improve readability. BASE64 encoding follows MIME conventions. Octets are in groups of three, c1, c2, c3. The resulting 24 bits are broken into four 6-bit quantities, starting with the high-order six bits (c1 >> 2) of the first octet, then the low-order two bits of the first octet followed by the high-order 4 bits of the second octet ((c1 & 3)<<4 | (c2>>4)), then the bottom 4 bits of the second octet followed by the high order two bits of the last octet ((c2 & 15)<<2 | (c3>>6)), then the bottom six bits of the last octet (c3 & 63). Each of these four quantities is translated into an ASCII character using the mapping: 1 2 3 4 5 6 0123456789012345678901234567890123456789012345678901234567890123 | | | | | | | ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/ With short groups of octets padded on the right with one "=" if c3 is missing, and with "==" if both c2 and c3 are missing. QUOTED-PRINTABLE encoding also follows MIME conventions, copying octets without translation if their ASCII values are 32..38, 42, 48..57, 59..60, 62, 64..126 and the octet is not a ";" in column 1. All other characters are translated to =nn, where nn is the hexadecimal encoding of the octet. All lines are "wrapped" with a terminating "=" (i.e. the MIME conventions for an implicit line terminator are never used). ; _item.name '_array_data.data' _item.category_id array_data _item.mandatory_code yes _item_type.code binary save_ ###################### # ARRAY_ELEMENT_SIZE # ###################### save_ARRAY_ELEMENT_SIZE _category.description ; Data items in the ARRAY_ELEMENT_SIZE category record the physical size of array elements along each array dimension. ; _category.id array_element_size _category.mandatory_code no loop_ _category_key.name '_array_element_size.array_id' '_array_element_size.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A regular 2D array with a uniform element dimension of 1220 nanometres. ; ; loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size image_1 1 1.22e-6 image_1 2 1.22e-6 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_element_size.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_array_element_size.array_id' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.index _item_description.description ; This item is a pointer to '_array_structure_list.index' in the ARRAY_STRUCTURE_LIST category. ; _item.name '_array_element_size.index' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.size _item_description.description ; The size in metres of an image element in this dimension. This supposes that the elements are arranged on a regular grid. ; _item.name '_array_element_size.size' _item.category_id array_element_size _item.mandatory_code yes _item_type.code float _item_units.code 'metres' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ ##################### # ARRAY_INTENSITIES # ##################### save_ARRAY_INTENSITIES _category.description ; Data items in the ARRAY_INTENSITIES category record the information required to recover the intensity data from the set of data values stored in the ARRAY_DATA category. The actual detector may have a complex relationship between the raw intensity values and the number of incident photons. In most cases, the number stored in the final array will have a simple linear relationship to the actual number of incident photons, given by '_array_intensities.gain'. If raw, uncorrected values are presented (e.g for calibration experiments), the value of '_array_intensities.linearity' will be 'raw' and '_array_intensities.gain' will not be used. ; _category.id array_intensities _category.mandatory_code no loop_ _category_key.name '_array_intensities.array_id' '_array_intensities.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 ; ; loop_ _array_intensities.array_id _array_intensities.linearity _array_intensities.gain _array_intensities.overload _array_intensities.undefined_value image_1 linear 1.2 655535 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_intensities.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_array_intensities.array_id' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code save_ save__array_intensities.binary_id _item_description.description ; This item is a pointer to '_array_data.binary_id' in the ARRAY_DATA category. ; _item.name '_array_intensities.binary_id' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code int save_ save__array_intensities.gain _item_description.description ; Detector "gain". The factor by which linearized intensity count values should be divided to produce true photon counts. ; _item.name '_array_intensities.gain' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain_esd' 'associated_value' save_ save__array_intensities.gain_esd _item_description.description ; The estimated standard deviation in detector "gain". ; _item.name '_array_intensities.gain_esd' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain' 'associated_esd' save_ save__array_intensities.linearity _item_description.description ; The intensity linearity scaling used from raw intensity to the stored element value: 'linear' is obvious 'offset' means that the value defined by '_array_intensities.offset' should be added to each element value. 'scaling' means that the value defined by '_array_intensities.scaling' should be multiplied with each element value. 'scaling_offset' is the combination of the two previous cases, with the scale factor applied before the offset value. 'sqrt_scaled' means that the square root of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and squaring the result. 'logarithmic_scaled' means that the logarithm based 10 of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and calculating 10 to the power of this number. 'raw' means that the data is the raw is a set of raw values straight from the detector. ; _item.name '_array_intensities.linearity' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'linear' . 'offset' ; The value defined by '_array_intensities.offset' should be added to each element value. ; 'scaling' ; The value defined by '_array_intensities.scaling' should be multiplied with each element value. ; 'scaling_offset' ; The combination of the scaling and offset with the scale factor applied before the offset value. ; 'sqrt_scaled' ; The square root of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and squaring the result. ; 'logarithmic_scaled' ; The logarithm based 10 of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and calculating 10 to the power of this number. ; 'raw' ; The array consists of raw values to which no corrections have been applied. While the handling of the data is similar to that given for 'linear' data with no offset, the meaning of the data differs in that the number of incident photons is not necessarily linearly related to the number of counts reported. This value is intended for use either in calibration experiments or to allow for handling more complex data fitting algorithms than are allowed for by this data item. ; save_ save__array_intensities.offset _item_description.description ; Offset value to add to array element values in the manner described by item '_array_intensities.linearity'. ; _item.name '_array_intensities.offset' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.scaling _item_description.description ; Multiplicative scaling value to be applied to array data in the manner described by item '_array_intensities.linearity'. ; _item.name '_array_intensities.scaling' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.overload _item_description.description ; The saturation intensity level for this data array. ; _item.name '_array_intensities.overload' _item.category_id array_intensities _item.mandatory_code no _item_type.code float _item_units.code 'counts' save_ save__array_intensities.undefined_value _item_description.description ; A value to be substituted for undefined values in the data array. ; _item.name '_array_intensities.undefined_value' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ ################### # ARRAY_STRUCTURE # ################### save_ARRAY_STRUCTURE _category.description ; Data items in the ARRAY_STRUCTURE category record the organization and encoding of array data which may be stored in the ARRAY_DATA category. ; _category.id array_structure _category.mandatory_code no _category_key.name '_array_structure.id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order image_1 "unsigned 16-bit integer" none little_endian ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure.byte_order _item_description.description ; The order of bytes for integer values which require more than 1-byte. (IBM-PC's and compatibles, and Dec-Vaxes use low-byte-first ordered integers, whereas Hewlett Packard 700 series, Sun-4 and Silicon Graphics use high-byte-first ordered integers. Dec-Alphas can produce/use either depending on a compiler switch.) ; _item.name '_array_structure.byte_order' _item.category_id array_structure _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'big_endian' ; The first byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; 'little_endian' ; The last byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; save_ save__array_structure.compression_type _item_description.description ; Type of data compression method used to compress the array data. ; _item.name '_array_structure.compression_type' _item.category_id array_structure _item.mandatory_code no _item_type.code code _item_default.value 'none' loop_ _item_enumeration.value _item_enumeration.detail 'none' ; Data are stored in normal format as defined by '_array_structure.encoding_type' and '_array_structure.byte_order'. ; 'byte_offsets' ; Using the compression scheme defined in CBF definition Section 5.0. ; 'packed' ; Using the 'packed' compression scheme, a CCP4-style packing (CBFlib section 3.3.2) ; 'canonical' ; Using the 'canonical' compression scheme (CBFlib section 3.3.1) ; save_ save__array_structure.encoding_type _item_description.description ; Data encoding of a single element of array data. In several cases, the IEEE format is referenced. See "IEEE Standard for Binary Floating-Point Arithmetic", ANSI/IEEE Std 754-1985, the Institute of Electrical and Electronics Engineers, Inc., NY 1985. ; _item.name '_array_structure.encoding_type' _item.category_id array_structure _item.mandatory_code yes _item_type.code uline loop_ _item_enumeration.value 'unsigned 8-bit integer' 'signed 8-bit integer' 'unsigned 16-bit integer' 'signed 16-bit integer' 'unsigned 32-bit integer' 'signed 32-bit integer' 'signed 32-bit real IEEE' 'signed 64-bit real IEEE' 'signed 32-bit complex IEEE' save_ save__array_structure.id _item_description.description ; The value of '_array_structure.id' must uniquely identify each item of array data. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure.id' array_structure yes '_array_data.array_id' array_data yes '_array_structure_list.array_id' array_structure_list yes '_array_intensities.array_id' array_intensities yes '_diffrn_data_frame.array_id' diffrn_data_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_data.array_id' '_array_structure.id' '_array_structure_list.array_id' '_array_structure.id' '_array_intensities.array_id' '_array_structure.id' '_diffrn_data_frame.array_id' '_array_structure.id' save_ ######################## # ARRAY_STRUCTURE_LIST # ######################## save_ARRAY_STRUCTURE_LIST _category.description ; Data items in the ARRAY_STRUCTURE_LIST category record the size and organization of each array dimension. The relationship to physical axes may be given. ; _category.id array_structure_list _category.mandatory_code no loop_ _category_key.name '_array_structure_list.array_id' '_array_structure_list.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - An image array of 1300 x 1200 elements. The raster order of the image is left-to-right (increasing) in first dimension and bottom-to-top (decreasing) in the second dimension. ; ; loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id image_1 1 1300 1 increasing ELEMENT_X image_1 2 1200 2 decreasing ELEMENY_Y ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure_list.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_array_structure_list.array_id' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code code save_ save__array_structure_list.axis_set_id _item_description.description ; This is a descriptor for the physical axis or set of axes corresponding to an array index. This data item is related to the axes of the detector itself given in DIFFRN_DETECTOR_AXIS, but usually differ in that the axes in this category are the axes of the coordinate system of reported data points, while the axes in DIFFRN_DETECTOR_AXIS are the physical axes of the detector describing the "poise" of the detector as an overall physical object. If there is only one axis in the set, the identifier of that axis should be used as the identifier of the set. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.axis_set_id' array_structure_list yes '_array_structure_list_axis.axis_set_id' array_structure_list_axis implicit _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_structure_list_axis.axis_set_id' '_array_structure_list.axis_set_id' save_ save__array_structure_list.dimension _item_description.description ; The number of elements stored in the array structure in this dimension. ; _item.name '_array_structure_list.dimension' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.direction _item_description.description ; Identifies the direction in which this array index changes. ; _item.name '_array_structure_list.direction' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_enumeration.value _item_enumeration.detail 'increasing' ; Indicates the index changes from 1 to the maximum dimension. ; 'decreasing' ; Indicates the index changes from the maximum dimension to 1. ; save_ save__array_structure_list.index _item_description.description ; Identifies the one-based index of the row or column in the array structure. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.index' array_structure_list yes '_array_structure_list.precedence' array_structure_list yes '_array_element_size.index' array_element_size yes _item_type.code int loop_ _item_linked.child_name _item_linked.parent_name '_array_element_size.index' '_array_structure_list.index' loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.precedence _item_description.description ; Identifies the rank order in which this array index changes with respect to other array indices. The precedence of 1 indicates the index which changes fastest. ; _item.name '_array_structure_list.precedence' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ ############################# # ARRAY_STRUCTURE_LIST_AXIS # ############################# save_ARRAY_STRUCTURE_LIST_AXIS _category.description ; Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe the physical settings of sets axes for the centres of pixels that correspond to data points described in the ARRAY_STRUCTURE_LIST category. In the simplest cases, the physical increments of a single axis correspond to the increments of a single array index. More complex organizations, e.g. spiral scans, may require coupled motions along multiple axes. Note that a spiral scan uses two coupled axis, one for the angular direction, one for the radial direction. This differs from a cylindrical scan for which the two axes are not coupled into one set. ; _category.id array_structure_list_axis _category.mandatory_code no loop_ _category_key.name '_array_structure_list_axis.axis_set_id' '_array_structure_list_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' save_ save__array_structure_list_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the set of axes for which settings are being specified. Multiple axes may be specified for the same value of '_array_structure_list_axis.axis_set_id' This item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_array_structure_list_axis.axis_id' _item.category_id array_structure_list_axis _item.mandatory_code yes save_ save__array_structure_list_axis.axis_set_id _item_description.description ; The value of this data item is the identifier of the set of axes for which axis settings are being specified. Multiple axes may be specified for the same value of '_array_structure_list_axis.axis_set_id'. This item is a pointer to '_array_structure_list.axis_set_id' in the ARRAY_STRUCTURE_LIST category. If this item is not specified, it defaults to the corresponding axis identifier. ; _item.name '_array_structure_list_axis.axis_set_id' _item.category_id array_structure_list_axis _item.mandatory_code implicit save_ save__array_structure_list_axis.angle _item_description.description ; The setting of the specified axis in degrees for the first data point of the array index with the corresponding value of '_array_structure_list.axis_set_id'. If the index is specified as 'increasing' this will be the center of the pixel with index value 1. If the index is specified as 'decreasing' this will be the center of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.angle' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.angle_increment _item_description.description ; The pixel-center-to-pixel-center increment in the angular setting of the specified axis in degrees. This is not meaningful in the case of 'constant velocity' spiral scans and should not be specified in that case. See '_array_structure_list_axis.angular_pitch'. ; _item.name '_array_structure_list_axis.angle_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for the first data point of the array index with the corresponding value of '_array_structure_list.axis_set_id'. If the index is specified as 'increasing' this will be the center of the pixel with index value 1. If the index is specified as 'decreasing' this will be the center of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.displacement' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.displacement_increment _item_description.description ; The pixel-center-to-pixel-center increment for the displacement setting of the specified axis in millimetres. ; _item.name '_array_structure_list_axis.displacement_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.angular_pitch _item_description.description ; The pixel-center-to-pixel-center distance for a one step change in the setting of the specified axis in millimetres. This is meaningful only for 'constant velocity' spiral scans, or for uncoupled angular scans at a constant radius (cylindrical scan) and should not be specified for cases in which the angle between pixels, rather than the distance between pixels is uniform. See '_array_structure_list_axis.angle_increment'. ; _item.name '_array_structure_list_axis.angular_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.radial_pitch _item_description.description ; The radial distance from one "cylinder" of pixels to the next in millimetres. If the scan is a 'constant velocity' scan with differing angular displacements between pixels, the value of this item may differ significantly from the value of '_array_structure_list_axis.displacement_increment'. ; _item.name '_array_structure_list_axis.radial_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ ######## # AXIS # ######## save_AXIS _category.description ; Data items in the AXIS category record the information required to describe the various goniometer, detector, source and other axes needed to specify a data collection. The location of each axis is specified by two vectors: the axis itself, given as a unit vector, and an offset to the base of the unit vector. These vectors are referenced to a right-handed laboratory coordinate system with its origin in the sample or specimen: | Y (to complete right-handed system) | | | | | |________________X / principal goniometer axis / / / / /Z (to source) Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from the sample or specimen along the principal axis of the goniometer. Axis 2 (Y): The Y-axis completes an orthogonal right-handed system defined by the X-axis and the Z-axis (see below). Axis 3 (Z): The Z-axis is derived from the source axis which goes from the sample to the source. The Z-axis is the component of the source axis in the direction of the source orthogonal to the X-axis in the plane defined by the X-axis and the source axis. These axes are based on the goniometer, not on the orientation of the detector, gravity, etc. The vectors necessary to specify all other axes are given by sets of three components in the order (X, Y, Z). If the axis involved is a rotation axis, it is right handed, i.e. as one views the object to be rotated from the origin (the tail) of the unit vector, the rotation is clockwise. If a translation axis is specified, the direction of the unit vector specifies the sense of positive translation. Note: This choice of coordinate system is similar to, but significantly different from the choice in MOSFLM (Andrew G.W. Leslie, Harry Powell, MRC Laboratory of Molecular Biology, Hills Road, Cambridge CB2 2QH,UK http://www.dl.ac.uk/CCP/CCP4/dist/x-windows/Mosflm/). In MOSFLM, X is along the X-ray beam (our Z axis) and Z is along the rotation axis. All rotations are given in degrees and all translations are given in mm. Axes may be dependent on one another. The X-axis is the only goniometer axis the direction of which is strictly connected to the hardware. All other axes are specified by the positions they would assume when the axes upon which they depend are at their zero points. When specifying detector axes, the axis is given to the beam center. The location of the beam center on the detector should be given in the DIFFRN_DETECTOR category in distortion-corrected mm from the (0,0) corner of the detector. It should be noted that many different origins arise in the definition of an experiment. In particular, as noted above, we need to specify the location of the beam center on the detector in terms of the origin of the detector, which is, of course, not coincident with the center of the sample. ; _category.id axis _category.mandatory_code no loop_ _category_key.name '_axis.id' '_axis.equipment' loop_ _category_group.id 'inclusive_group' 'axis_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows the axis specification of the axes of a kappa geometry goniometer (See "X-Ray Structure Determination, A Practical Guide", 2nd ed. by G. H. Stout, L. H. Jensen, Wiley Interscience, 1989, 453 pp, p 134.). There are three axes specified, and no offsets. The outermost axis, omega, is pointed along the X-axis. The next innermost axis, kappa, is at a 50 degree angle to the X-axis, pointed away from the source. The innermost axis, phi, aligns with the X-axis when omega and phi are at their zero-points. If T-omega, T-kappa and T-phi are the transformation matrices derived from the axis settings, the complete transformation would be: x' = (T-omega) (T-kappa) (T-phi) x ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] omega rotation goniometer . 1 0 0 kappa rotation goniometer omega -.64279 0 -.76604 phi rotation goniometer kappa 1 0 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - This example show the axis specification of the axes of a detector, source and gravity. We have juggled the order as a reminder that the ordering of presentation of tokens is not significant. We have taken the center of rotation of the detector to be 68 millimetres in the direction away from the source. ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] source . source . 0 0 1 . . . gravity . gravity . 0 -1 0 . . . tranz translation detector rotz 0 0 1 0 0 -68 twotheta rotation detector . 1 0 0 . . . roty rotation detector twotheta 0 1 0 0 0 -68 rotz rotation detector roty 0 0 1 0 0 -68 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__axis.depends_on _item_description.description ; The value of '_axis.depends_on' specifies the next outermost axis upon which this axis depends. This item is a pointer to '_axis.id' in the same category. ; _item.name '_axis.depends_on' _item.category_id axis _item.mandatory_code no save_ save__axis.equipment _item_description.description ; The value of '_axis.equipment' specifies the type of equipment using the axis: 'goniometer', 'detector', 'gravity', 'source' or 'general'. ; _item.name '_axis.equipment' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail goniometer 'equipment used to orient or position samples' detector 'equipment used to detect reflections' general 'equipment used for general purposes' gravity 'axis specifying the downward direction' source 'axis specifying the direction sample to source' save_ save__axis.offset[1] _item_description.description ; The [1] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[2] _item_description.description ; The [2] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[3] _item_description.description ; The [3] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.id _item_description.description ; The value of '_axis.id' must uniquely identify each axis relevant to the experiment. Note that multiple pieces of equipment may share the same axis (e.g. a twotheta arm), so that the category key for AXIS also includes the equipment. ; loop_ _item.name _item.category_id _item.mandatory_code '_axis.id' axis yes '_array_structure_list_axis.axis_id' array_structure_list_axis yes '_diffrn_detector_axis.axis_id' diffrn_detector_axis yes '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes '_diffrn_scan_axis.axis_id' diffrn_scan_axis yes '_diffrn_scan_frame_axis.axis_id' diffrn_scan_frame_axis yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_axis.depends_on' '_axis.id' '_array_structure_list_axis.axis_id' '_axis.id' '_diffrn_detector_axis.axis_id' '_axis.id' '_diffrn_measurement_axis.axis_id' '_axis.id' '_diffrn_scan_axis.axis_id' '_axis.id' '_diffrn_scan_frame_axis.axis_id' '_axis.id' save_ save__axis.type _item_description.description ; The value of '_axis.type' specifies the type of axis: 'rotation', 'translation' (or 'general' when the type is not relevant, as for gravity). ; _item.name '_axis.type' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail rotation 'right-handed axis of rotation' translation 'translation in the direction of the axis' general 'axis for which the type is not relevant' save_ save__axis.vector[1] _item_description.description ; The [1] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector, and is dimensionless. ; _item.name '_axis.vector[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[2] _item_description.description ; The [2] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector, and is dimensionless. ; _item.name '_axis.vector[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[3] _item_description.description ; The [3] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector, and is dimensionless. ; _item.name '_axis.vector[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ ##################### # DIFFRN_DATA_FRAME # ##################### save_DIFFRN_DATA_FRAME _category.description ; Data items in the DIFFRN_DATA_FRAME category record the details about each frame of data. The items in this category were previously in a DIFFRN_FRAME_DATA category, which is now deprecated. The items from the old category are provided as aliases, but should not be used for new work. ; _category.id diffrn_data_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_data_frame.id' '_diffrn_data_frame.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A frame containing data from 4 frame elements. Each frame element has a common array configuration 'array_1' described in ARRAY_STRUCTURE and related categories. The data for each detector element is stored in four groups of binary data in the ARRAY_DATA category, linked by the array_id and binary_id ; ; loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id frame_1 d1_ccd_1 array_1 1 frame_1 d1_ccd_2 array_1 2 frame_1 d1_ccd_3 array_1 3 frame_1 d1_ccd_4 array_1 4 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_data_frame.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_diffrn_data_frame.array_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.array_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0.00 _item_type.code code save_ save__diffrn_data_frame.binary_id _item_description.description ; This item is a pointer to '_array_data.binary_id' in the ARRAY_DATA category. ; _item.name '_diffrn_data_frame.binary_id' _item.category_id diffrn_data_frame _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_frame_data.binary_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code int save_ save__diffrn_data_frame.detector_element_id _item_description.description ; This item is a pointer to '_diffrn_detector_element.id' in the DIFFRN_DETECTOR_ELEMENT category. ; _item.name '_diffrn_data_frame.detector_element_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.detector_element_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.id _item_description.description ; The value of '_diffrn_data_frame.id' must uniquely identify each complete frame of data. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_data_frame.id' diffrn_data_frame yes '_diffrn_refln.frame_id' diffrn_refln yes '_diffrn_scan.frame_id_start' diffrn_scan yes '_diffrn_scan.frame_id_end' diffrn_scan yes '_diffrn_scan_frame.frame_id' diffrn_scan_frame yes '_diffrn_scan_frame_axis.frame_id' diffrn_scan_frame_axis yes _item_aliases.alias_name '_diffrn_frame_data.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_refln.frame_id' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_start' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_end' '_diffrn_data_frame.id' '_diffrn_scan_frame.frame_id' '_diffrn_data_frame.id' '_diffrn_scan_frame_axis.frame_id' '_diffrn_data_frame.id' save_ ########################################################################## # The following is a restatement of the mmCIF DIFFRN_DETECTOR, # # DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for # # the CBF/imgCIF extensions # ########################################################################## ################### # DIFFRN_DETECTOR # ################### save_DIFFRN_DETECTOR _category.description ; Data items in the DIFFRN_DETECTOR category describe the detector used to measure the scattered radiation, including any analyser and post-sample collimation. ; _category.id diffrn_detector _category.mandatory_code no loop_ _category_key.name '_diffrn_detector.diffrn_id' '_diffrn_detector.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_detector.diffrn_id 'd1' _diffrn_detector.detector 'multiwire' _diffrn_detector.type 'Siemens' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector.details _item_description.description ; A description of special aspects of the radiation detector. ; _item.name '_diffrn_detector.details' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; Need new example here. ; save_ save__diffrn_detector.detector _item_description.description ; The general class of the radiation detector. ; _item.name '_diffrn_detector.detector' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector' cifdic.c91 1.0 '_diffrn_detector' cif_core.dic 2.0 _item_type.code text loop_ _item_examples.case 'photographic film' 'scintillation counter' 'CCD plate' 'BF~3~ counter' save_ save__diffrn_detector.diffrn_id _item_description.description ; This data item is a pointer to '_diffrn.id' in the DIFFRN category. The value of '_diffrn.id' uniquely defines a set of diffraction data. ; _item.name '_diffrn_detector.diffrn_id' _item.mandatory_code yes save_ save__diffrn_detector.dtime _item_description.description ; The deadtime in microseconds of the detectors used to measure the diffraction intensities. ; _item.name '_diffrn_detector.dtime' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector_dtime' cifdic.c91 1.0 '_diffrn_detector_dtime' cif_core.dic 2.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code microseconds save_ save__diffrn_detector.id _item_description.description ; The value of '_diffrn_detector.id' must uniquely identify each detector used to collect each diffraction data set. If the value of '_diffrn_detector.id' is not given, it is implicitly equal to the value of '_diffrn_detector.diffrn_id' ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector.id' diffrn_detector implicit '_diffrn_detector_axis.detector_id' diffrn_detector_axis yes loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_detector_axis.detector_id' '_diffrn_detector.id' _item_type.code code save_ save__diffrn_detector.number_of_axes _item_description.description ; The value of '_diffrn_detector.number_of_axes' gives the number of axes of the positioner for the detector identified by '_diffrn_detector.id'. The word "positioner" is a general term used in instrumentation design for devices that are used to change the positions of portions of apparatus by linear translation, rotation, or combinations of such motions. Axes which are used to provide a coordinate system for the face of an area detetctor should not be counted for this data item. The description of each axis should be provided by entries in DIFFRN_DETECTOR_AXIS. ; _item.name '_diffrn_detector.number_of_axes' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_detector.type _item_description.description ; The make, model or name of the detector device used. ; _item.name '_diffrn_detector.type' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ ######################## # DIFFRN_DETECTOR_AXIS # ######################## save_DIFFRN_DETECTOR_AXIS _category.description ; Data items in the DIFFRN_DETECTOR_AXIS category associate axes with detectors. ; _category.id diffrn_detector_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_axis.detector_id' '_diffrn_detector_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_detector_axis.axis_id _item_description.description ; This data item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_diffrn_detector_axis.axis_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_axis.detector_id _item_description.description ; This data item is a pointer to '_diffrn_detector.id' in the DIFFRN_DETECTOR category. This item was previously named '_diffrn_detector_axis.id' which is now a deprecated name. The old name is provided as an alias, but should not be used for new work. ; _item.name '_diffrn_detector_axis.detector_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_aliases.alias_name '_diffrn_detector_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 save_ ########################### # DIFFRN_DETECTOR_ELEMENT # ########################### save_DIFFRN_DETECTOR_ELEMENT _category.description ; Data items in the DIFFRN_DETECTOR_ELEMENT category record the details about spatial layout and other characteristics of each element of a detector which may have multiple elements. In most cases, the more detailed information provided in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS are preferable to simply providing the centre. ; _category.id diffrn_detector_element _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_element.id' '_diffrn_detector_element.detector_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Detector d1 is composed of four CCD detector elements, each 200 mm by 200 mm, arranged in a square. in the pattern 1 2 * 3 4 Note that the beam center is slightly off of each of the detector elements, just beyond the lower right corner of 1, the lower left corner of 2, the upper right corner of 3 and the upper left corner of 4. ; ; loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id _diffrn_detector_element.center[1] _diffrn_detector_element.center[2] d1 d1_ccd_1 201.5 -1.5 d1 d1_ccd_2 -1.8 -1.5 d1 d1_ccd_3 201.6 201.4 d1 d1_ccd_4 -1.7 201.5 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector_element.center[1] _item_description.description ; The value of '_diffrn_detector_element.center[1]' is the X component of the distortion-corrected beam-center in mm from the (0, 0) (lower left) corner of the detector element viewed from the sample side. ; _item.name '_diffrn_detector_element.center[1]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.center[2] _item_description.description ; The value of '_diffrn_detector_element.center[2]' is the Y component of the distortion-corrected beam-center in mm from the (0, 0) (lower left) corner of the detector element viewed from the sample side. ; _item.name '_diffrn_detector_element.center[2]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.id _item_description.description ; The value of '_diffrn_detector_element.id' must uniquely identify each element of a detector. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector_element.id' diffrn_detector_element yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.detector_element_id' '_diffrn_detector_element.id' save_ save__diffrn_detector_element.detector_id _item_description.description ; This item is a pointer to '_diffrn_detector.id' in the DIFFRN_DETECTOR category. ; _item.name '_diffrn_detector_element.detector_id' _item.category_id diffrn_detector_element _item.mandatory_code yes _item_type.code code save_ ######################## ## DIFFRN_MEASUREMENT ## ######################## save_DIFFRN_MEASUREMENT _category.description ; Data items in the DIFFRN_MEASUREMENT category record details about the device used to orient and/or position the crystal during data measurement and the manner in which the diffraction data were measured. ; _category.id diffrn_measurement _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement.device' '_diffrn_measurement.diffrn_id' '_diffrn_measurement.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_measurement.diffrn_id 'd1' _diffrn_measurement.device '3-circle camera' _diffrn_measurement.device_type 'Supper model x' _diffrn_measurement.device_details 'none' _diffrn_measurement.method 'omega scan' _diffrn_measurement.details ; Need new example here ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991). Acta Cryst. C47, 2276-2277]. ; ; _diffrn_measurement.diffrn_id 's1' _diffrn_measurement.device_type 'Philips PW1100/20 diffractometer' _diffrn_measurement.method 'theta/2theta (\q/2\q)' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_measurement.device _item_description.description ; The general class of goniometer or device used to support and orient the specimen. If the value of '_diffrn_measurement.device' is not given, it is implicitly equal to the value of '_diffrn_measurement.diffrn_id'. Either '_diffrn_measurement.device' or '_diffrn_measurement.id' may be used to link to other categories. If the experimental setup admits multiple devices, then '_diffrn_measurement.id' is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.device' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_device' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement.device' _item_aliases.alias_name '_diffrn_measurement_device' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '3-circle camera' '4-circle camera' 'kappa-geometry camera' 'oscillation camera' 'precession camera' save_ save__diffrn_measurement.device_details _item_description.description ; A description of special aspects of the device used to measure the diffraction intensities. ; _item.name '_diffrn_measurement.device_details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; commercial goniometer modified locally to allow for 90\% \t arc ; save_ save__diffrn_measurement.device_type _item_description.description ; The make, model or name of the measurement device (goniometer) used. ; _item.name '_diffrn_measurement.device_type' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Supper model q' 'Huber model r' 'Enraf-Nonius model s' 'homemade' save_ save__diffrn_measurement.diffrn_id _item_description.description ; This data item is a pointer to '_diffrn.id' in the DIFFRN category. ; _item.name '_diffrn_measurement.diffrn_id' _item.mandatory_code yes save_ save__diffrn_measurement.details _item_description.description ; A description of special aspects of the intensity measurement. ; _item.name '_diffrn_measurement.details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; save_ save__diffrn_measurement.id _item_description.description ; The value of '_diffrn_measurement.id' must uniquely identify the set of mechanical characteristics of the device used to orient and/or position the sample used during collection of each diffraction data set. If the value of '_diffrn_measurement.id' is not given, it is implicitly equal to the value of '_diffrn_measurement.diffrn_id'. Either '_diffrn_measurement.device' or '_diffrn_measurement.id' may be used to link to other categories. If the experimental setup admits multiple devices, then '_diffrn_measurement.id' is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.id' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_id' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement.id' _item_type.code code save_ save__diffrn_measurement.method _item_description.description ; Method used to measure intensities. ; _item.name '_diffrn_measurement.method' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_method' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'profile data from theta/2theta (\q/2\q) scans' save_ save__diffrn_measurement.number_of_axes _item_description.description ; The value of '_diffrn_measurement.number_of_axes' gives the number of axes of the positioner for the goniometer or other sample orientation or positioning device identified by '_diffrn_measurement.id'. The description of the axes should be provided by entries in DIFFRN_MEASUREMENT_AXIS. ; _item.name '_diffrn_measurement.number_of_axes' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_measurement.specimen_support _item_description.description ; The physical device used to support the crystal during data collection. ; _item.name '_diffrn_measurement.specimen_support' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_specimen_support' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'glass capillary' 'quartz capillary' 'fiber' 'metal loop' save_ ########################### # DIFFRN_MEASUREMENT_AXIS # ########################### save_DIFFRN_MEASUREMENT_AXIS _category.description ; Data items in the DIFFRN_MEASUREMENT_AXIS category associate axes with goniometers. ; _category.id diffrn_measurement_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_measurement_axis.axis_id _item_description.description ; This data item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_diffrn_measurement_axis.axis_id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.measurement_device _item_description.description ; This data item is a pointer to '_diffrn_measurement.device' in the DIFFRN_MEASUREMENT category. ; _item.name '_diffrn_measurement_axis.measurement_device' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit save_ save__diffrn_measurement_axis.measurement_id _item_description.description ; This data item is a pointer to '_diffrn_measurement.id' in the DIFFRN_MEASUREMENT category. This item was previously named '_diffrn_measurement_axis.id' which is now a deprecated name. The old name is provided as an alias, but should not be used for new work. ; _item.name '_diffrn_measurement_axis.measurement_id' _item.category_id diffrn_measurement_axis _item_aliases.alias_name '_diffrn_measurement_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0.00 _item.mandatory_code implicit save_ #################### # DIFFRN_RADIATION # #################### save_DIFFRN_RADIATION _category.description ; Data items in the DIFFRN_RADIATION category describe the radiation used in measuring diffraction intensities, its collimation and monochromatisation before the sample. Post-sample treatment of the beam is described by data items in the DIFFRN_DETECTOR category. ; _category.id diffrn_radiation _category.mandatory_code no _category_key.name '_diffrn_radiation.diffrn_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_radiation.diffrn_id 'set1' _diffrn_radiation.collimation '0.3 mm double pinhole' _diffrn_radiation.monochromator 'graphite' _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.wavelength_id 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991). Acta Cryst. C47, 2276-2277]. ; ; _diffrn_radiation.wavelength_id 1 _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.monochromator 'graphite' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_radiation.collimation _item_description.description ; The collimation or focusing applied to the radiation. ; _item.name '_diffrn_radiation.collimation' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_collimation' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '0.3 mm double-pinhole' '0.5 mm' 'focusing mirrors' save_ save__diffrn_radiation.diffrn_id _item_description.description ; This data item is a pointer to '_diffrn.id' in the DIFFRN category. ; _item.name '_diffrn_radiation.diffrn_id' _item.mandatory_code yes save_ save__diffrn_radiation.div_x_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory X axis (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the esd of the directions of photons in the X-Z plane around the mean source beam direction. Note that some synchrotrons specify this value in milliradians, in which case a conversion would be needed. To go from a value in milliradians to a value in degrees, multiply by 0.180 and divide by Pi. ; _item.name '_diffrn_radiation.div_x_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.div_y_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory Y axis (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the esd of the directions of photons in the Y-Z plane around the mean source beam direction. Note that some synchrotrons specify this value in milliradians, in which case a conversion would be needed. To go from a value in milliradians to a value in degrees, multiply by 0.180 and divide by Pi. ; _item.name '_diffrn_radiation.div_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.div_x_y_source _item_description.description ; Beam crossfire correlation degrees**2 between the crossfire laboratory X-axis component and the crossfire laboratory Y-axis component (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the mean of the products of the deviations of the directin of each photons in X-Z plane times the deviations of the direction of the same photon in the Y-Z plane around the mean source beam direction. This will be zero for uncorrelated crossfire. Note that some synchrotrons specify this value in milliradians**2, in which case a conversion would be needed. To go from a value in milliradians**2 to a value in degrees**2, multiply by 0.180**2 and divide by Pi**2. ; _item.name '_diffrn_radiation.div_x_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees_squared _item_default.value 0.0 save_ save__diffrn_radiation.filter_edge _item_description.description ; Absorption edge in angstroms of the radiation filter used. ; _item.name '_diffrn_radiation.filter_edge' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_filter_edge' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__diffrn_radiation.inhomogeneity _item_description.description ; Half-width in millimetres of the incident beam in the direction perpendicular to the diffraction plane. ; _item.name '_diffrn_radiation.inhomogeneity' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_inhomogeneity' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code millimetres save_ save__diffrn_radiation.monochromator _item_description.description ; The method used to obtain monochromatic radiation. If a monochromator crystal is used the material and the indices of the Bragg reflection are specified. ; _item.name '_diffrn_radiation.monochromator' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_monochromator' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Zr filter' 'Ge 220' 'none' 'equatorial mounted graphite' save_ save__diffrn_radiation.polarisn_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the perpendicular component of the polarisation and the diffraction plane. See _diffrn_radiation_polarisn_ratio. ; _item.name '_diffrn_radiation.polarisn_norm' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_norm' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.polarisn_ratio _item_description.description ; Polarisation ratio of the diffraction beam incident on the crystal. It is the ratio of the perpendicularly polarised to the parallel polarised component of the radiation. The perpendicular component forms an angle of '_diffrn_radiation.polarisn_norm' to the normal to the diffraction plane of the sample (i.e. the plane containing the incident and reflected beams). ; _item.name '_diffrn_radiation.polarisn_ratio' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_ratio' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__diffrn_radiation.polarizn_source_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the normal to the polarization plane and the laboratory Y axis as defined in the AXIS category. Note that this is the angle of polarization of the source photons, either directly from a synchrotron beamline or from a monchromater. This differs from the value of '_diffrn_radiation.polarisn_norm' in that '_diffrn_radiation.polarisn_norm' refers to polarization relative to the diffraction plane rather than to the laboratory axis system. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane should be taken as the X-Z plane, and the angle as 0. See '_diffrn_radiation.polarizn_source_ratio'. ; _item.name '_diffrn_radiation.polarizn_source_norm' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.polarizn_source_ratio _item_description.description ; (Ip-In)/(Ip+In), where Ip is the intensity (amplitude squared) of the electric vector in the plane of polarization and In is the intensity (amplitude squared) of the electric vector in plane of the normal to the plane of polarization. Thus, if we had complete polarization in the plane of polarization, the value of '_diffrn_radiation.polarizn_source_ratio' would be 1, and an unpolarized beam would have a value of 0. If the X-axis has been chosen to lie in the plane of polarization, this definition will agree with the definition of "MONOCHROMATOR" in the Denzo glossary, and values of near 1 should be expected for a bending magnet source. However, if the X-axis were, for some reason to be, say, perpendicular to the polarization plane (not a common choice), then the Denzo value would be the negative of '_diffrn_radiation.polarizn_source_ratio'. See http://www.hkl-xray.com for information on Denzo, and Z. Otwinowski and W. Minor, "Processing of X-ray Diffraction Data Collected in Oscillation Mode", Methods in Enzymology, Volume 276: Macromolecular Crystallography, part A, p.307-326, 1997,C.W. Carter, Jr. & R. M. Sweet, Eds., Academic Press. This differs both in the choice of ratio and choice of orientation from '_diffrn_radiation.polarisn_ratio', which, unlike '_diffrn_radiation.polarizn_source_ratio', is unbounded. ; _item.name '_diffrn_radiation.polarizn_source_ratio' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 -1.0 -1.0 -1.0 _item_type.code float save_ save__diffrn_radiation.probe _item_description.description ; Name of the type of radiation used. It is strongly encouraged that this field be specified so that the probe radiation can be simply determined. ; _item.name '_diffrn_radiation.probe' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_probe' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value 'x-ray' 'neutron' 'electron' 'gamma' save_ save__diffrn_radiation.type _item_description.description ; The nature of the radiation. This is typically a description of the X-ray wavelength in Siegbahn notation. ; _item.name '_diffrn_radiation.type' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'CuK\a' 'Cu K\a~1~' 'Cu K-L~2,3~' 'white-beam' save_ save__diffrn_radiation.xray_symbol _item_description.description ; The IUPAC symbol for the X-ray wavelength for probe radiation. ; _item.name '_diffrn_radiation.xray_symbol' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_xray_symbol' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value _item_enumeration.detail 'K-L~3~' 'K\a~1~ in older Siegbahn notation' 'K-L~2~' 'K\a~2~ in older Siegbahn notation' 'K-M~3~' 'K\b~1~ in older Siegbahn notation' 'K-L~2,3~' 'use where K-L~3~ and K-L~2~ are not resolved' save_ save__diffrn_radiation.wavelength_id _item_description.description ; This data item is a pointer to '_diffrn_radiation_wavelength.id' in the DIFFRN_RADIATION_WAVELENGTH category. ; _item.name '_diffrn_radiation.wavelength_id' _item.mandatory_code yes save_ ################ # DIFFRN_REFLN # ################ save_DIFFRN_REFLN _category.description ; This category redefinition has been added to extend the key of the standard DIFFRN_REFLN category. ; _category.id diffrn_refln _category.mandatory_code no _category_key.name '_diffrn_refln.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_refln.frame_id _item_description.description ; This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_refln.frame_id' _item.category_id diffrn_refln _item.mandatory_code yes _item_type.code code save_ ############### # DIFFRN_SCAN # ############### save_DIFFRN_SCAN _category.description ; Data items in the DIFFRN_SCAN category describe the parameters of one or more scans, relating axis positions to frames. ; _category.id diffrn_scan _category.mandatory_code no _category_key.name '_diffrn_scan.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - derived from a suggestion by R. M. Sweet. The vector of each axis is not given here, because it is provided in the AXIS category. By making '_diffrn_scan_axis.scan_id' and '_diffrn_scan_axis.axis_id' keys of the DIFFRN_SCAN_AXIS category, an arbitrary number of scanning and fixed axes can be specified for a scan. We have specified three rotation axes and one translation axis at non-zero values, with one axis stepping. There is no reason why more axes could not have been specified to step. We have specified range information, but note that it is redundant from the number of frames and the increment, so we could drop the data item '_diffrn_scan_axis.angle_range'. We have specified both the sweep data and the data for a single frame. Note that the information on how the axes are stepped is given twice, once in terms of the overall averages in the value of '_diffrn_scan.integration_time' and the values for DIFFRN_SCAN_AXIS, and precisely for the given frame in the value for '_diffrn_scan_frame.integration_time' and the values for DIFFRN_SCAN_FRAME_AXIS. If dose-related adjustements are made to scan times and non-linear stepping is done, these values may differ. Therefore, in interpreting the data for a particular frame it is important to use the frame-specific data. ; ; _diffrn_scan.id 1 _diffrn_scan.date_start '2001-11-18T03:26:42' _diffrn_scan.date_end '2001-11-18T03:36:45' _diffrn_scan.integration_time 3.0 _diffrn_scan.frame_id_start mad_L2_000 _diffrn_scan.frame_id_end mad_L2_200 _diffrn_scan.frames 201 loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment 1 omega 200.0 20.0 0.1 . . . 1 kappa -40.0 0.0 0.0 . . . 1 phi 127.5 0.0 0.0 . . . 1 tranz . . . 2.3 0.0 0.0 _diffrn_scan_frame.scan_id 1 _diffrn_scan_frame.date '2001-11-18T03:27:33' _diffrn_scan_frame.integration_time 3.0 _diffrn_scan_frame.frame_id mad_L2_018 _diffrn_scan_frame.frame_number 18 loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.angle_increment _diffrn_scan_frame_axis.displacement _diffrn_scan_frame_axis.displacement_increment mad_L2_018 omega 201.8 0.1 . . mad_L2_018 kappa -40.0 0.0 . . mad_L2_018 phi 127.5 0.0 . . mad_L2_018 tranz . . 2.3 0.0 ; ; Example 2 - a more extensive example, R. M. Sweet, P. Ellis, H. Bernstein. We place a detector 240 mm along the Z axis from the goniometer. This presents us with a choice -- either we define the axes of the detector at the origin, and then put a Z setting of -240 in for the actual use, or we define the axes with the necessary Z-offset. In this case we use the setting, and leave the offset as zero. We call this axis DETECTOR_Z. The axis for positioning the detector in the Y-direction depends on the detector Z-axis. We call this axis, DETECTOR_Y. The axis for positioning the dector in the X-direction depends on the detector Y-axis (and therefore on the detector Z-axis). We call this axis DETECTOR_X. This detector may be rotated around the Y-axis. This rotation axis depends on the three translation axies. We call it DETECTOR_PITCH. We define a coordinate system on the face of the detector in terms of 2300 0.150 mm pixels in each direction. The ELEMENT_X axis is used to index the first array index of the data array and the ELEMENT_Y axis is used to index the second array index. Because the pixels are 0.150mm x 0.150mm, the center of the first pixel is at (0.075, 0.075) in this coordinate system. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 172.43 -172.43 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 2300 1 increasing ELEMENT_X ARRAY1 2 2300 2 increasing ELEMENT_Y # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.075 0.150 ELEMENT_Y ELEMENT_Y 0.075 0.150 # category ARRAY_ELEMENT_SIZE loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 ARRAY1 2 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; ; Example 3 - Example 2 revised for a spiral scan, R. M. Sweet, P. Ellis, H. Bernstein. We place a detector 240 mm along the Z axis from the goniometer, as in Example 2, above, but in this example, the image plate is scanned in a spiral pattern outside edge in. The axis for positioning the detector in the Y-direction depends on the detector Z-axis. We call this axis, DETECTOR_Y. The axis for positioning the dector in the X-direction depends on the detector Y-axis (and therefore on the detector Z-axis). We call this axis DETECTOR_X. This detector may be rotated around the Y-axis. This rotation axis depends on the three translation axies. We call it DETECTOR_PITCH. We define a coordinate system on the face of the detector in terms of a coupled rotation axis and radial scan axis to form a spiral scan. Let us call rotation axis ELEMENT_ROT, and the radial axis ELEMENT_RAD. We assume 150 um radial pitch and 75 um 'constant velocity' angular pitch. We index first on the rotation axis and make the radial axis dependent on it. The two axes are coupled to form an axis set ELEMENT_SPIRAL. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_ROT translation detector DETECTOR_PITCH 0 0 1 0 0 0 ELEMENT_RAD translation detector ELEMENT_ROT 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.angle _array_structure_list_axis.displacement _array_structure_list_axis.angular_pitch _array_structure_list_axis.radial_pitch ELEMENT_SPIRAL ELEMENT_ROT 0 . 0.075 . ELEMENT_SPIRAL ELEMENT_RAD . 172.5 . -0.150 # category ARRAY_ELEMENT_SIZE # the actual pixels are 0.075 by 0.150 mm # We give the coarser dimension here. loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_scan.id _item_description.description ; The value of '_diffrn_scan.id' uniquely identifies each scan. The identifier is used to tie together all the information about the scan. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_scan.id' diffrn_scan yes '_diffrn_scan_axis.scan_id' diffrn_scan_axis yes '_diffrn_scan_frame.scan_id' diffrn_scan_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_scan_axis.scan_id' '_diffrn_scan.id' '_diffrn_scan_frame.scan_id' '_diffrn_scan.id' save_ save__diffrn_scan.date_end _item_description.description ; The date and time of the end of the scan. Note that this may be an estimate generated during the scan, before the precise time of the end of the scan is known. ; _item.name '_diffrn_scan.date_end' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.date_start _item_description.description ; The date and time of the start of the scan. ; _item.name '_diffrn_scan.date_start' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.integration_time _item_description.description ; Approximate average time in seconds to integrate each step of the scan. The precise time for integration of each particular step must be provided in '_diffrn_scan_frame.integration_time', even if all steps have the same integration time. ; _item.name '_diffrn_scan.integration_time' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan.frame_id_start _item_description.description ; The value of this data item is the identifier of the first frame in the scan. This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_start' _item.category_id diffrn_scan _item.mandatory_code yes save_ save__diffrn_scan.frame_id_end _item_description.description ; The value of this data item is the identifier of the last frame in the scan. This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_end' _item.category_id diffrn_scan _item.mandatory_code yes save_ save__diffrn_scan.frames _item_description.description ; The value of this data item is the number of frames in the scan. ; _item.name '_diffrn_scan.frames' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 1 1 1 save_ #################### # DIFFRN_SCAN_AXIS # #################### save_DIFFRN_SCAN_AXIS _category.description ; Data items in the DIFFRN_SCAN_AXIS category describe the settings of axes for particular scans. Unspecified axes are assumed to be at their zero points. ; _category.id diffrn_scan_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_axis.scan_id' '_diffrn_scan_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_axis.scan_id _item_description.description ; The value of this data item is the identifier of the scan for which axis settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan.id'. This item is a pointer to '_diffrn_scan.id' in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_axis.scan_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes save_ save__diffrn_scan_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the scan for which settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan.id'. This item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_diffrn_scan_axis.axis_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes save_ save__diffrn_scan_axis.angle_start _item_description.description ; The starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_range _item_description.description ; The range from the starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_increment _item_description.description ; The increment for each step for the specified axis in degrees. In general, this will agree with '_diffrn_scan_frame_axis.angle_increment'. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.angle_increment' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.angle_increment' (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_rstrt_incr _item_description.description ; The increment after each step for the specified axis in degrees. In general, this will agree with '_diffrn_scan_frame_axis.angle_rstrt_incr'. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' and '_diffrn_scan_frame_axis.angle_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame, and should equal '_diffrn_scan_frame_axis.angle' for that next frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.angle_rstrt_incr' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.angle_rstrt_incr' (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.displacement_start _item_description.description ; The starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_range _item_description.description ; The range from the starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_increment _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with '_diffrn_scan_frame_axis.displacement_increment'. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.displacement_increment' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.displacement_increment' (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_rstrt_incr _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with '_diffrn_scan_frame_axis.displacement_rstrt_incr'. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' and '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame, and should equal '_diffrn_scan_frame_axis.displacement' for that next frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.displacement_rstrt_incr' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.displacement_rstrt_incr' (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ ##################### # DIFFRN_SCAN_FRAME # ##################### save_DIFFRN_SCAN_FRAME _category.description ; Data items in the DIFFRN_SCAN_FRAME category describe the relationship of particular frames to scans. ; _category.id diffrn_scan_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame.scan_id' '_diffrn_scan_frame.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame.date _item_description.description ; The date and time of the start of the frame being scanned. ; _item.name '_diffrn_scan_frame.date' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan_frame.frame_id _item_description.description ; The value of this data item is the identifier of the frame being examined. This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame.frame_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes save_ save__diffrn_scan_frame.frame_number _item_description.description ; The value of this data item is the number of the frame within the scan, starting with 1. It is not necessarily the same as the value of '_diffrn_scan_frame.frame_id', but may be. ; _item.name '_diffrn_scan_frame.frame_number' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 0 0 0 save_ save__diffrn_scan_frame.integration_time _item_description.description ; The time in seconds to integrate this step of the scan. This should be the precise time of integration of each particular frame. The value of this data item should be given explicitly for each frame and not inferred from the value of '_diffrn_scan.integration_time'. ; _item.name '_diffrn_scan_frame.integration_time' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame.scan_id _item_description.description ; The value of '_diffrn_scan_frame.scan_id' identifies the scan containing this frame. This item is a pointer to '_diffrn_scan.id' in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_frame.scan_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes save_ ########################## # DIFFRN_SCAN_FRAME_AXIS # ########################## save_DIFFRN_SCAN_FRAME_AXIS _category.description ; Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the settings of axes for particular frames. Unspecified axes are assumed to be at their zero points. If, for any given frame, non-zero values apply for any of the data items in this category, those values should be given explicitly in this category and not simply inferred from values in DIFFRN_SCAN_AXIS. ; _category.id diffrn_scan_frame_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame_axis.frame_id' '_diffrn_scan_frame_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the frame for which settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan_frame.frame_id'. This item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_diffrn_scan_frame_axis.axis_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes save_ save__diffrn_scan_frame_axis.angle _item_description.description ; The setting of the specified axis in degrees for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.angle' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_increment _item_description.description ; The increment for this frame for angular setting of the specified axis in degrees. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.angle_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_rstrt_incr _item_description.description ; The increment after this frame for angular setting of the specified axis in degrees. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' and '_diffrn_scan_frame_axis.angle_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame, and should equal '_diffrn_scan_frame_axis.angle' for that next frame. ; _item.name '_diffrn_scan_frame_axis.angle_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.displacement' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_increment _item_description.description ; The increment for this frame for displacement setting of the specified axis in millimetres. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.displacement_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_rstrt_incr _item_description.description ; The increment for this frame for displacement setting of the specified axis in millimetres. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' and '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame, and should equal '_diffrn_scan_frame_axis.displacement' for that next frame. ; _item.name '_diffrn_scan_frame_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.frame_id _item_description.description ; The value of this data item is the identifier of the frame for which axis settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan_frame.frame_id'. This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame_axis.frame_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes save_ ######################## DEPRECATED DATA ITEMS ######################## save__diffrn_detector_axis.id _item_description.description ; This data item is a pointer to '_diffrn_detector.id' in the DIFFRN_DETECTOR category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_detector_axis.id' _item.category_id diffrn_detector_axis _item.mandatory_code yes save_ save__diffrn_measurement_axis.id _item_description.description ; This data item is a pointer to '_diffrn_measurement.id' in the DIFFRN_MEASUREMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_measurement_axis.id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes save_ ######################### DEPRECATED CATEGORY ######################### ##################### # DIFFRN_FRAME_DATA # ##################### save_DIFFRN_FRAME_DATA _category.description ; Data items in the DIFFRN_FRAME_DATA category record the details about each frame of data. The items in this category are now in the DIFFRN_DATA_FRAME category. The items in the DIFFRN_FRAME_DATA category are now deprecated. The items from this category are provided as aliases in the 1.0.0 dictionary, but should not be used for new work. The items from the old category are provided in this dictionary for completeness, but should not be used or cited. To avoid confusion, the example has been removed, and the redundant parent child-links to other categories removed. ; _category.id diffrn_frame_data _category.mandatory_code no loop_ _category_key.name '_diffrn_frame_data.id' '_diffrn_frame_data.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; THE DIFFRN_DATA_FRAME category is deprecated and should not be used. ; ; # EXAMPLE REMOVED # ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_frame_data.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.array_id' _item.category_id diffrn_frame_data _item.mandatory_code yes _item_type.code code save_ save__diffrn_frame_data.binary_id _item_description.description ; This item is a pointer to '_array_data.binary_id' in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.binary_id' _item.category_id diffrn_frame_data _item.mandatory_code implicit _item_type.code int save_ save__diffrn_frame_data.detector_element_id _item_description.description ; This item is a pointer to '_diffrn_detector_element.id' in the DIFFRN_DETECTOR_ELEMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.detector_element_id' _item.category_id diffrn_frame_data _item.mandatory_code yes _item_type.code code save_ save__diffrn_frame_data.id _item_description.description ; The value of '_diffrn_frame_data.id' must uniquely identify each complete frame of data. DEPRECATED -- DO NOT USE ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_frame_data.id' diffrn_frame_data yes _item_type.code code save_ ################ END DEPRECATED SECTION ########### #################### ## ITEM_TYPE_LIST ## #################### # # # The regular expressions defined here are not compliant # with the POSIX 1003.2 standard as they include the # '\n' and '\t' special characters. These regular expressions # have been tested using version 0.12 of Richard Stallman's # GNU regular expression library in POSIX mode. # In order to allow presentation of a regular expression # in a text field concatenate any line ending in a backslash # with the following line, after discarding the backslash. # # A formal definition of the '\n' and '\t' special characters # is most properly done in the DDL, but for completeness, please # note that '\n' is the line termination character ('newline') # and '\t' is the horizontal tab character. There is a formal # ambiguity in the use of '\n' for line termination, in that # the intention is that the equivalent machine/OS-dependent line # termination character sequence should be accepted as a match, e.g. # # '\r' (control-M) under MacOS # '\n' (control-J) under Unix # '\r\n' (control-M control-J) under DOS and MS Windows # loop_ _item_type_list.code _item_type_list.primitive_code _item_type_list.construct _item_type_list.detail code char '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words ... ; ucode uchar '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words (case insensitive) ; line char '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types / multi-word items ... ; uline uchar '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types / multi-word items (case insensitive) ; text char '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; text item types / multi-line text ... ; binary char ;\n--CIF-BINARY-FORMAT-SECTION--\n\ [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\ \n--CIF-BINARY-FORMAT-SECTION---- ; ; binary items are presented as MIME-like ascii-encoded sections in an imgCIF. In a CBF, raw octet streams are used to convey the same information. ; int numb '-?[0-9]+' ; int item types are the subset of numbers that are the negative or positive integers. ; float numb '-?(([0-9]+)|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?' ; float item types are the subset of numbers that are the floating numbers. ; any char '.*' ; A catch all for items that may take any form... ; yyyy-mm-dd char ;\ [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9][0-9]\ (T[0-2][0-9]:[0-5][0-9]:[0-5][0-9](.[0-9]+)([+-][0-5][0-9]:[0-5][0-9])) ; ; Standard format for CIF date and time strings (see http://www.iucr.org/iucr-top/cif/spec/datetime.html), consisting of a yyyy-mm-dd date optionally followed by the character "T" followed by a 24-hour clock time, optionally followed by a signed time-zone offset. The IUCr standard has been extended to allow for an optional decimal fraction on the seconds of time. Time is local time if no time-zone offset is given. ; ##################### ## ITEM_UNITS_LIST ## ##################### loop_ _item_units_list.code _item_units_list.detail # 'metres' 'metres' 'centimetres' 'centimetres (metres * 10^( -2))' 'millimetres' 'millimetres (metres * 10^( -3))' 'nanometres' 'nanometres (metres * 10^( -9))' 'angstroms' 'angstroms (metres * 10^(-10))' 'picometres' 'picometres (metres * 10^(-12))' 'femtometres' 'femtometres (metres * 10^(-15))' # 'reciprocal_metres' 'reciprocal metres (metres^(-1))' 'reciprocal_centimetres' 'reciprocal centimetres ((metres * 10^( -2))^(-1))' 'reciprocal_millimetres' 'reciprocal millimetres ((metres * 10^( -3))^(-1))' 'reciprocal_nanometres' 'reciprocal nanometres ((metres * 10^( -9))^(-1))' 'reciprocal_angstroms' 'reciprocal angstroms ((metres * 10^(-10))^(-1))' 'reciprocal_picometres' 'reciprocal picometres ((metres * 10^(-12))^(-1))' # 'nanometres_squared' 'nanometres squared (metres * 10^( -9))^2' 'angstroms_squared' 'angstroms squared (metres * 10^(-10))^2' '8pi2_angstroms_squared' '8pi^2 * angstroms squared (metres * 10^(-10))^2' 'picometres_squared' 'picometres squared (metres * 10^(-12))^2' # 'nanometres_cubed' 'nanometres cubed (metres * 10^( -9))^3' 'angstroms_cubed' 'angstroms cubed (metres * 10^(-10))^3' 'picometres_cubed' 'picometres cubed (metres * 10^(-12))^3' # 'kilopascals' 'kilopascals' 'gigapascals' 'gigapascals' # 'hours' 'hours' 'minutes' 'minutes' 'seconds' 'seconds' 'microseconds' 'microseconds' # 'degrees' 'degrees (of arc)' 'degrees_squared' 'degrees (of arc) squared' # 'degrees_per_minute' 'degrees (of arc) per minute' # 'celsius' 'degrees (of temperature) Celsius' 'kelvins' 'degrees (of temperature) Kelvin' # 'counts' 'counts' 'counts_per_photon' 'counts per photon' # 'electrons' 'electrons' # 'electrons_squared' 'electrons squared' # 'electrons_per_nanometres_cubed' ; electrons per nanometres cubed (electrons/(metres * 10^( -9))^(-3)) ; 'electrons_per_angstroms_cubed' ; electrons per angstroms cubed (electrons/(metres * 10^(-10))^(-3)) ; 'electrons_per_picometres_cubed' ; electrons per picometres cubed (electrons/(metres * 10^(-12))^(-3)) ; 'kilowatts' 'kilowatts' 'milliamperes' 'milliamperes' 'kilovolts' 'kilovolts' # 'arbitrary' ; arbitrary system of units. ; # loop_ _item_units_conversion.from_code _item_units_conversion.to_code _item_units_conversion.operator _item_units_conversion.factor ### 'metres' 'centimetres' '*' 1.0E+02 'metres' 'millimetres' '*' 1.0E+03 'metres' 'nanometres' '*' 1.0E+09 'metres' 'angstroms' '*' 1.0E+10 'metres' 'picometres' '*' 1.0E+12 'metres' 'femtometres' '*' 1.0E+15 # 'centimetres' 'metres' '*' 1.0E-02 'centimetres' 'millimetres' '*' 1.0E+01 'centimetres' 'nanometres' '*' 1.0E+07 'centimetres' 'angstroms' '*' 1.0E+08 'centimetres' 'picometres' '*' 1.0E+10 'centimetres' 'femtometres' '*' 1.0E+13 # 'millimetres' 'metres' '*' 1.0E-03 'millimetres' 'centimetres' '*' 1.0E-01 'millimetres' 'nanometres' '*' 1.0E+06 'millimetres' 'angstroms' '*' 1.0E+07 'millimetres' 'picometres' '*' 1.0E+09 'millimetres' 'femtometres' '*' 1.0E+12 # 'nanometres' 'metres' '*' 1.0E-09 'nanometres' 'centimetres' '*' 1.0E-07 'nanometres' 'millimetres' '*' 1.0E-06 'nanometres' 'angstroms' '*' 1.0E+01 'nanometres' 'picometres' '*' 1.0E+03 'nanometres' 'femtometres' '*' 1.0E+06 # 'angstroms' 'metres' '*' 1.0E-10 'angstroms' 'centimetres' '*' 1.0E-08 'angstroms' 'millimetres' '*' 1.0E-07 'angstroms' 'nanometres' '*' 1.0E-01 'angstroms' 'picometres' '*' 1.0E+02 'angstroms' 'femtometres' '*' 1.0E+05 # 'picometres' 'metres' '*' 1.0E-12 'picometres' 'centimetres' '*' 1.0E-10 'picometres' 'millimetres' '*' 1.0E-09 'picometres' 'nanometres' '*' 1.0E-03 'picometres' 'angstroms' '*' 1.0E-02 'picometres' 'femtometres' '*' 1.0E+03 # 'femtometres' 'metres' '*' 1.0E-15 'femtometres' 'centimetres' '*' 1.0E-13 'femtometres' 'millimetres' '*' 1.0E-12 'femtometres' 'nanometres' '*' 1.0E-06 'femtometres' 'angstroms' '*' 1.0E-05 'femtometres' 'picometres' '*' 1.0E-03 ### 'reciprocal_centimetres' 'reciprocal_metres' '*' 1.0E+02 'reciprocal_centimetres' 'reciprocal_millimetres' '*' 1.0E-01 'reciprocal_centimetres' 'reciprocal_nanometres' '*' 1.0E-07 'reciprocal_centimetres' 'reciprocal_angstroms' '*' 1.0E-08 'reciprocal_centimetres' 'reciprocal_picometres' '*' 1.0E-10 # 'reciprocal_millimetres' 'reciprocal_metres' '*' 1.0E+03 'reciprocal_millimetres' 'reciprocal_centimetres' '*' 1.0E+01 'reciprocal_millimetres' 'reciprocal_nanometres' '*' 1.0E-06 'reciprocal_millimetres' 'reciprocal_angstroms' '*' 1.0E-07 'reciprocal_millimetres' 'reciprocal_picometres' '*' 1.0E-09 # 'reciprocal_nanometres' 'reciprocal_metres' '*' 1.0E+09 'reciprocal_nanometres' 'reciprocal_centimetres' '*' 1.0E+07 'reciprocal_nanometres' 'reciprocal_millimetres' '*' 1.0E+06 'reciprocal_nanometres' 'reciprocal_angstroms' '*' 1.0E-01 'reciprocal_nanometres' 'reciprocal_picometres' '*' 1.0E-03 # 'reciprocal_angstroms' 'reciprocal_metres' '*' 1.0E+10 'reciprocal_angstroms' 'reciprocal_centimetres' '*' 1.0E+08 'reciprocal_angstroms' 'reciprocal_millimetres' '*' 1.0E+07 'reciprocal_angstroms' 'reciprocal_nanometres' '*' 1.0E+01 'reciprocal_angstroms' 'reciprocal_picometres' '*' 1.0E-02 # 'reciprocal_picometres' 'reciprocal_metres' '*' 1.0E+12 'reciprocal_picometres' 'reciprocal_centimetres' '*' 1.0E+10 'reciprocal_picometres' 'reciprocal_millimetres' '*' 1.0E+09 'reciprocal_picometres' 'reciprocal_nanometres' '*' 1.0E+03 'reciprocal_picometres' 'reciprocal_angstroms' '*' 1.0E+01 ### 'nanometres_squared' 'angstroms_squared' '*' 1.0E+02 'nanometres_squared' 'picometres_squared' '*' 1.0E+06 # 'angstroms_squared' 'nanometres_squared' '*' 1.0E-02 'angstroms_squared' 'picometres_squared' '*' 1.0E+04 'angstroms_squared' '8pi2_angstroms_squared' '*' 78.9568 # 'picometres_squared' 'nanometres_squared' '*' 1.0E-06 'picometres_squared' 'angstroms_squared' '*' 1.0E-04 ### 'nanometres_cubed' 'angstroms_cubed' '*' 1.0E+03 'nanometres_cubed' 'picometres_cubed' '*' 1.0E+09 # 'angstroms_cubed' 'nanometres_cubed' '*' 1.0E-03 'angstroms_cubed' 'picometres_cubed' '*' 1.0E+06 # 'picometres_cubed' 'nanometres_cubed' '*' 1.0E-09 'picometres_cubed' 'angstroms_cubed' '*' 1.0E-06 ### 'kilopascals' 'gigapascals' '*' 1.0E-06 'gigapascals' 'kilopascals' '*' 1.0E+06 ### 'hours' 'minutes' '*' 6.0E+01 'hours' 'seconds' '*' 3.6E+03 'hours' 'microseconds' '*' 3.6E+09 # 'minutes' 'hours' '/' 6.0E+01 'minutes' 'seconds' '*' 6.0E+01 'minutes' 'microseconds' '*' 6.0E+07 # 'seconds' 'hours' '/' 3.6E+03 'seconds' 'minutes' '/' 6.0E+01 'seconds' 'microseconds' '*' 1.0E+06 # 'microseconds' 'hours' '/' 3.6E+09 'microseconds' 'minutes' '/' 6.0E+07 'microseconds' 'seconds' '/' 1.0E+06 ### 'celsius' 'kelvins' '-' 273.0 'kelvins' 'celsius' '+' 273.0 ### 'electrons_per_nanometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E+03 'electrons_per_nanometres_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+09 # 'electrons_per_angstroms_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-03 'electrons_per_angstroms_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+06 # 'electrons_per_picometres_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-09 'electrons_per_picometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E-06 ### ######################## ## DICTIONARY_HISTORY ## ######################## loop_ _dictionary_history.version _dictionary_history.update _dictionary_history.revision 1.3.0 2003-07-24 ; Changes as per Brian McMahon. + Consistently quote tags embedded in text. + Clean up introductory comments. + Adjust line lengths to fit in 80 character window + Fix several descriptions in AXIS category which referred to '_axis.type' instead of the current item. + Fix erroneous use of deprecated item '_diffrn_detector_axis.id' in examples for DIFFRN_SCAN_AXIS. + Add deprecated items '_diffrn_detector_axis.id' and '_diffrn_measurement_axis.id' (HJB) ; 1.2.4 2003-07-14 ; Changes as per I. David Brown. + Enhance descriptions in DIFFRN_SCAN_AXIS to make them less dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS. + Provide a copy of the deprecated DIFFRN_FRAME_DATA category for completeness. (HJB) ; 1.2.3 2003-07-03 ; Cleanup to conform to ITVG. + Correct sign error in ..._cubed units. + Correct '_diffrn_radiation.polarisn_norm' range. (HJB) ; 1.2.2 2003-03-10 ; Correction of typos in various DIFFRN_SCAN_AXIS descriptions. (HJB) ; 1.2.1 2003-02-22 ; Correction of ATOM_ for ARRAY_ typos in various descriptions. (HJB) ; 1.2 2003-02-07 ; Corrections to encodings (remove extraneous hyphens) remove extraneous underscore in '_array_structure.encoding_type' enumeration. Correct typos in items units list. (HJB) ; 1.1.3 2001-04-19 ; Another typo corrections by Wilfred Li, and cleanup by HJB ; 1.1.2 2001-03-06 ; Several typo corrections by Wilfred Li ; 1.1.1 2001-02-16 ; Several typo corrections by JW ; 1.1 2001-02-06 ; Draft resulting from discussions on header for use at NSLS (HJB) + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'. + Add '_diffrn_measurement_axis.measurement_device' and change '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'. + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source', '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm', '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end', '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr', '_diffrn_scan_axis.displacement_rstrt_incr', '_diffrn_scan_frame_axis.angle_increment', '_diffrn_scan_frame_axis.angle_rstrt_incr', '_diffrn_scan_frame_axis.displacement', '_diffrn_scan_frame_axis.displacement_increment',and '_diffrn_scan_frame_axis.displacement_rstrt_incr'. + Add '_diffrn_measurement.device' to category key + Update yyyy-mm-dd to allow optional time with fractional seconds for time stamps. + Fix typos caught by RS. + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to allow for coupled axes, as in spiral scans. + Add examples for fairly complete headers thanks to R. Sweet and P. Ellis. ; 1.0 2000-12-21 ; Release version - few typos and tidying up (BM & HJB) + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end of dictionary. + Alphabetize dictionary. ; 0.7.1 2000-09-29 ; Cleanup fixes (JW) + Correct spelling of diffrn_measurement_axis in '_axis.id' + Correct ordering of uses of '_item.mandatory_code' and '_item_default.value'. ; 0.7.0 2000-09-09 ; Respond to comments by I. David Brown (HJB) + Added further comments on '\n' and '\t' + Updated ITEM_UNITS_LIST by taking section from mmCIF dictionary and adding metres. Changed all spelling 'meter' to 'metre' throughout. + Added missing enumerations to '_array_structure.compression_type' and made 'none' the default. + Removed parent-child relationship between '_array_structure_list.index' and '_array_structure_list.precedence'. + Improve alphabetization. + Fix '_array_intensities_gain.esd' related function. + Improved comments in AXIS. + Fixed DIFFRN_FRAME_DATA example. + Removed erroneous DIFFRN_MEASUREMENT example. + Added '_diffrn_measurement_axis.id' to the category key. ; 0.6.0 1999-01-14 ; Remove redundant information for ENC_NONE data (HJB) + After the D5 remove binary section identifier, size and compression type. + Add Control-L to header. ; 0.5.1 1999-01-03 ; Cleanup of typos and syntax errors (HJB) + Cleanup example details for DIFFRN_SCAN category. + Add missing quote marks for '_diffrn_scan.id' definition. ; 0.5 1999-01-01 ; Modifications for axis definitions and reduction of binary header (HJB) + Restored '_diffrn_detector.diffrn_id' to DIFFRN_DETECTOR KEY. + Added AXIS category. + Brought complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories in from cif_mm.dic for clarity. + changed '_array_structure.encoding_type' from type code to uline and added X-Binary-Element-Type to MIME header. + added detector beam center '_diffrn_detector_element.center[1]' and '_diffrn_detector_element.center[2]'. + corrected item name of '_diffrn_refln.frame_id'. + replace reference to '_array_intensities.undefined' by '_array_intensities.undefined_value'. + replace references to '_array_intensity.scaling' with '_array_intensities.scaling'. + added DIFFRN_SCAN... categories ; 0.4 1998-08-11 ; Modifications to the 0.3 imgCIF draft (HJB) + Reflowed comment lines over 80 characters and corrected typos. + Updated examples and descriptions of MIME encoded data. + Change name to cbfext98.dic. ; 0.3 1998-07-04 ; Modifications for imgCIF (HJB) + Added binary type, which is a text field containing a variant on MIME encoded data. + Changed type of '_array_data.data' to binary and specified internal structure of raw binary data. + Added '_array_data.binary_id', and made '_diffrn_frame_data.binary_id' and '_array_intensities.binary_id' into pointers to this item. ; 0.2 1997-12-02 ; Modifications to the CBF draft (JW): + Added category hierarchy for describing frame data developed from discussions at the BNL imgCIF Workshop Oct 1997. The following changes were made in implementing the workshop draft. Category DIFFRN_ARRAY_DATA was renamed to DIFFRN_FRAME_DATA. Category DIFFRN_FRAME_TYPE was renamed to DIFFRN_DETECTOR_ELEMENT. The parent item for '_diffrn_frame_data.array_id' was changed from '_array_structure_list.array_id' to '_array_structure.id'. Item '_diffrn_detector.array_id' was deleted. + Added data item '_diffrn_frame_data.binary_id' to identify data groups within a binary section. The formal identification of the binary section is still fuzzy. ; 0.1 1997-01-24 ; First draft of this dictionary in DDL 2.1 compliant format by John Westbrook (JW). This version was adapted from the Crystallographic Binary File (CBF) Format Draft Proposal provided by Andy Hammersley (AH). Modifications to the CBF draft (JW): + In this version the array description has been cast in the categories ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. These categories have been generalized to describe array data of arbitrary dimension. + Array data in this description are contained in the category ARRAY_DATA. This departs from the CBF notion of data existing in some special comment. In this description, data is handled as an ordinary data item encapsulated in a character data type. Although data this manner deviates from CIF conventions, it does not violate any DDL 2.1 rules. DDL 2.1 regular expressions can be used to define the binary representation which will permit some level of data validation. In this version, the placeholder type code "any" has been used. This translates to a regular expression which will match any pattern. It should be noted that DDL 2.1 already supports array data objects although these have not been used in the current mmCIF dictionary. It may be possible to use the DDL 2.1 ITEM_STRUCTURE and ITEM_STRUCTURE_LIST categories to provide the information that is carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. By moving the array structure to the DDL level it would be possible to define an array type as well as a regular expression defining the data format. + Multiple array sections can be properly handled within a single datablock. ; #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof ./CBFlib-0.9.2.2/doc/Idiffrn_detector_element.detector_id.html0000644000076500007650000000523211603702115022502 0ustar yayayaya (IUCr) CIF Definition save__diffrn_detector_element.detector_id

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_detector_element.detector_id

    Name:
    '_diffrn_detector_element.detector_id'

    Definition:

            This item is a pointer to _diffrn_detector.id
                   in the DIFFRN_DETECTOR category.
    
    

    Type: code

    Mandatory item: yes

    Category: diffrn_detector_element

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_detector.details.html0000644000076500007650000000533511603702115020135 0ustar yayayaya (IUCr) CIF Definition save__diffrn_detector.details

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_detector.details

    Name:
    '_diffrn_detector.details'

    Definition:

            A description of special aspects of the radiation detector.
    
    
    Example:

    'slow mode'

    Type: text

    Mandatory item: no

    Alias:
    _diffrn_detector_details (cif_core.dic version 2.0.1)

    Category: diffrn_detector

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Imap_segment.binary_id.html0000644000076500007650000000563611603702115017612 0ustar yayayaya (IUCr) CIF Definition save__map_segment.binary_id

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _map_segment.binary_id

    Name:
    '_map_segment.binary_id'

    Definition:

           The value of _map_segment.binary_id distinguishes the particular
                  set of data organized according to _map_segment.array_id in
                  which the data values of the map are stored.
    
                  This item is a pointer to _array_data.binary_id in the
                  ARRAY_DATA category.
    
    

    Type: int

    Mandatory item: implicit

    Category: map_segment

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_measurement.details.html0000644000076500007650000000562511603702115020653 0ustar yayayaya (IUCr) CIF Definition save__diffrn_measurement.details

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_measurement.details

    Name:
    '_diffrn_measurement.details'

    Definition:

            A description of special aspects of the intensity
                   measurement.
    
    
    Example:

    ;                                 440 frames, 0.20 degrees, 150 sec, detector
                                      distance 12 cm, detector angle 22.5 degrees
    ;

    Type: text

    Mandatory item: no

    Alias:
    _diffrn_measurement_details (cif_core.dic version 2.0.1)

    Category: diffrn_measurement

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Iarray_intensities.offset.html0000644000076500007650000000514111603702115020364 0ustar yayayaya (IUCr) CIF Definition save__array_intensities.offset

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _array_intensities.offset

    Name:
    '_array_intensities.offset'

    Definition:

            Offset value to add to array element values in the manner
                   described by the item _array_intensities.linearity.
    
    

    Type: float

    Mandatory item: no

    Category: array_intensities

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Cmap.html0000644000076500007650000000714311603702115014116 0ustar yayayaya (IUCr) CIF Definition save_map

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    Category MAP

    Name:
    'map'

    Description:

           Data items in the MAP category record
                  the details of a maps. Maps record values of parameters,
                  such as density, that are functions of position within
                  a cell or are functions of orthogonal coordinates in
                  three space.
    
                  A map may is composed of one or more map segments
                  specified in the MAP_SEGMENT category.
    
                  Examples are given in the MAP_SEGMENT category.
    
    
    Example:

    Example 1 - Identifying an observed density map and a calculated density map
     
    
            loop_
            _map.id
            _map.details
    
            rho_calc
       ;
            density calculated from F_calc derived from the ATOM_SITE list
       ;
            rho_obs
       ;
            density combining the observed structure factors with the
            calculated phases
       ;
    
    


    Category groups:
        inclusive_group
        array_data_group
    Category keys:
        _map.id
        _map.diffrn_id
        _map.entry_id

    Mandatory category: no

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/cif_img_1.5.4.html0000777000076500007650000000000011603751102021513 2cif_img_1.5.4_28Jul07.htmlustar yayayaya./CBFlib-0.9.2.2/doc/Cdiffrn_scan_frame_axis.html0000644000076500007650000000611611603702115020012 0ustar yayayaya (IUCr) CIF Definition save_diffrn_scan_frame_axis

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    Category DIFFRN_SCAN_FRAME_AXIS

    Name:
    'diffrn_scan_frame_axis'

    Description:

        Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the
         settings of axes for particular frames.  Unspecified axes are
         assumed to be at their zero points.  If, for any given frame,
         nonzero values apply for any of the data items in this category,
         those values should be given explicitly in this category and not
         simply inferred from values in DIFFRN_SCAN_AXIS.
    
    
    Category groups:
        inclusive_group
        diffrn_group
    Category keys:
        _diffrn_scan_frame_axis.frame_id
        _diffrn_scan_frame_axis.axis_id

    Mandatory category: no

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/cif_img_1_2_3.dic0000644000076500007650000051741411603702115015320 0ustar yayayaya############################################################################## # # # Image CIF Dictionary (imgCIF) # # and Crystallographic Binary File Dictionary (CBF) # # Extending the Macromolecular CIF Dictionary (mmCIF) # # # # Version 1.2.3 # # of 2003-07-04 # # # # by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook # # # # This dictionary was adapted from the imgCIF Workshop, held at BNL Oct 1997# # and the Crystallographic Binary File Format Draft Proposal by Andy # # Hammersley. The first DDL 2.1 Version was created by John Westbrook. # # This version was drafted by Herbert J. Bernstein and incorporates comments # # by I. David Brown, John Westbrook, Brian McMahon, Bob Sweet, Paul Ellis, # # Harry Powell, Wilfred Li and others. # ############################################################################## data_cif_img.dic _dictionary.title cif_img.dic _dictionary.version 1.2.3 _dictionary.datablock_id cif_img.dic ############################################################################## # CONTENTS # # CATEGORY_GROUP_LIST # # category ARRAY_DATA # # _array_data.array_id # _array_data.binary_id # _array_data.data # # category ARRAY_ELEMENT_SIZE # # _array_element_size.array_id # _array_element_size.index # _array_element_size.size # # category ARRAY_INTENSITIES # # _array_intensities.array_id # _array_intensities.binary_id # _array_intensities.gain # _array_intensities.gain_esd # _array_intensities.linearity # _array_intensities.offset # _array_intensities.scaling # _array_intensities.overload # _array_intensities.undefined_value # # category ARRAY_STRUCTURE # # _array_structure.byte_order # _array_structure.compression_type # _array_structure.encoding_type # _array_structure.id # # category ARRAY_STRUCTURE_LIST # # _array_structure_list.axis_set_id # _array_structure_list.array_id # _array_structure_list.dimension # _array_structure_list.direction # _array_structure_list.index # _array_structure_list.precedence # # category ARRAY_STRUCTURE_LIST_AXIS # # _array_structure_list_axis.axis_id # _array_structure_list_axis.axis_set_id # _array_structure_list_axis.angle # _array_structure_list_axis.angle_increment # _array_structure_list_axis.displacement_increment # _array_structure_list_axis.angular_pitch # _array_structure_list_axis.radial_pitch # # category AXIS # # _axis.depends_on # _axis.equipment # _axis.id # _axis.offset[1] # _axis.offset[2] # _axis.offset[3] # _axis.type # _axis.vector[1] # _axis.vector[2] # _axis.vector[3] # # category DIFFRN_DATA_FRAME # # _diffrn_data_frame.array_id # _diffrn_data_frame.binary_id # _diffrn_data_frame.detector_element_id # _diffrn_data_frame.id # # category DIFFRN_DETECTOR # # _diffrn_detector.details # _diffrn_detector.detector # _diffrn_detector.diffrn_id # _diffrn_detector.dtime # _diffrn_detector.id # _diffrn_detector.number_of_axes # _diffrn_detector.type # # category DIFFRN_DETECTOR_AXIS # # _diffrn_detector_axis.axis_id # _diffrn_detector_axis.detector_id # # category DIFFRN_DETECTOR_ELEMENT # # _diffrn_detector_element.center[1] # _diffrn_detector_element.center[2] # _diffrn_detector_element.id # _diffrn_detector_element.detector_id # # category DIFFRN_MEASUREMENT # # _diffrn_measurement.diffrn_id # _diffrn_measurement.details # _diffrn_measurement.device # _diffrn_measurement.device_details # _diffrn_measurement.device_type # _diffrn_measurement.id # _diffrn_measurement.method # _diffrn_measurement.number_of_axes # _diffrn_measurement.specimen_support # # category DIFFRN_MEASUREMENT_AXIS # # _diffrn_measurement_axis.axis_id # _diffrn_measurement_axis.measurement_device # _diffrn_measurement_axis.measurement_id # # category DIFFRN_RADIATION # # _diffrn_radiation.collimation # _diffrn_radiation.diffrn_id # _diffrn_radiation.div_x_source # _diffrn_radiation.div_y_source # _diffrn_radiation.div_x_y_source # _diffrn_radiation.filter_edge' # _diffrn_radiation.inhomogeneity # _diffrn_radiation.monochromator # _diffrn_radiation.polarisn_norm # _diffrn_radiation.polarisn_ratio # _diffrn_radiation.polarizn_source_norm # _diffrn_radiation.polarizn_source_ratio # _diffrn_radiation.probe # _diffrn_radiation.type # _diffrn_radiation.xray_symbol # _diffrn_radiation.wavelength_id # # category DIFFRN_REFLN # # _diffrn_refln.frame_id # # category DIFFRN_SCAN # # _diffrn_scan.id # _diffrn_scan.date_end # _diffrn_scan.date_start # _diffrn_scan.integration_time # _diffrn_scan.frame_id_start # _diffrn_scan.frame_id_end # _diffrn_scan.frames # # category DIFFRN_SCAN_AXIS # # _diffrn_scan_axis.axis_id # _diffrn_scan_axis.angle_start # _diffrn_scan_axis.angle_range # _diffrn_scan_axis.angle_increment # _diffrn_scan_axis.angle_rstrt_incr # _diffrn_scan_axis.displacement_start # _diffrn_scan_axis.displacement_range # _diffrn_scan_axis.displacement_increment # _diffrn_scan_axis.displacement_rstrt_incr # _diffrn_scan_axis.scan_id # # category DIFFRN_SCAN_FRAME # # _diffrn_scan_frame.date # _diffrn_scan_frame.frame_id # _diffrn_scan_frame.frame_number # _diffrn_scan_frame.integration_time # _diffrn_scan_frame.scan_id # # category DIFFRN_SCAN_FRAME_AXIS # # _diffrn_scan_frame_axis.axis_id # _diffrn_scan_frame_axis.angle # _diffrn_scan_frame_axis.angle_increment # _diffrn_scan_frame_axis.angle_rstrt_incr # _diffrn_scan_frame_axis.displacement # _diffrn_scan_frame_axis.displacement_increment # _diffrn_scan_frame_axis.displacement_rstrt_incr # _diffrn_scan_frame_axis.frame_id # # ITEM_TYPE_LIST # ITEM_UNITS_LIST # DICTIONARY_HISTORY # ############################################################################## ######################### ## CATEGORY_GROUP_LIST ## ######################### loop_ _category_group_list.id _category_group_list.parent_id _category_group_list.description 'inclusive_group' . ; Categories that belong to the dictionary extension. ; 'array_data_group' 'inclusive_group' ; Categories that describe array data. ; 'axis_group' 'inclusive_group' ; Categories that describe axes. ; 'diffrn_group' 'inclusive_group' ; Categories that describe details of the diffraction experiment. ; ############## # ARRAY_DATA # ############## save_ARRAY_DATA _category.description ; Data items in the ARRAY_DATA category are the containers for the array data items described in category ARRAY_STRUCTURE. ; _category.id array_data _category.mandatory_code no loop_ _category_key.name '_array_data.array_id' '_array_data.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows two binary data blocks. The first one was compressed by the CBF_CANONICAL compression algorithm and presented as hexadecimal data. The first character "H" on the data lines means hexadecimal. It could have been "O" for octal or "D" for decimal. The second character on the line shows the number of bytes in each word (in this case "4"), which then requires 8 hexadecimal digits per word. The third character gives the order of octets within a word, in this case "<" for the ordering 4321 (i.e. "big-endian"). Alternatively the character ">" could have been used for the ordering 1234 (i.e. "little-endian"). The block has a "message digest" to check the integrity of the data. The second block is similar, but uses CBF_PACKED compression and BASE64 encoding. Note that the size and the digest are different. ; ; loop_ _array_data.array_id _array_data.binary_id _array_data.data image_1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_CANONICAL" Content-Transfer-Encoding: X-BASE16 X-Binary-Size: 3927126 X-Binary-ID: 1 Content-MD5: u2sTJEovAHkmkDjPi+gWsg== # Hexadecimal encoding, byte 0, byte order ...21 # H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ... .... --CIF-BINARY-FORMAT-SECTION---- ; image_2 2 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF-PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3745758 X-Binary-ID: 1 Content-MD5: 1zsJjWPfol2GYl2V+QSXrw== ELhQAAAAAAAA... ... --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_data.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_data.array_id' _item.category_id array_data _item.mandatory_code yes _item_type.code code save_ save__array_data.binary_id _item_description.description ; This item is an integer identifier which, along with _array_data.array_id should uniquely identify the particular block of array data. If _array_data.binary_id is not explicitly given, it defaults to 1. The value of _array_data.binary_id distinguishes among multiple sets of data with the same array structure. If the MIME header of the data array specifies a value for X-Binary-Id, these values should be equal. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_data.binary_id' array_data implicit '_diffrn_data_frame.binary_id' diffrn_data_frame implicit '_array_intensities.binary_id' array_intensities implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.binary_id' '_array_data.binary_id' '_array_intensities.binary_id' '_array_data.binary_id' _item_default.value 1 _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_data.data _item_description.description ; The value of _array_data.data contains the array data encapsulated in a STAR string. The representation used is a variant on the Multipurpose Internet Mail Extensions (MIME) specified in RFC 2045-2049 by N. Freed et al. The boundary delimiter used in writing an imgCIF or CBF is "--CIF-BINARY-FORMAT-SECTION--" (including the required initial "--"). The Content-Type may be any of the discrete types permitted in RFC 2045; "application/octet-stream" is recommended. If an octet stream was compressed, the compression should be specified by the parameter 'conversions="x-CBF_PACKED"' or the parameter 'conversions="x-CBF_CANONICAL"'. The Content-Transfer-Encoding may be "BASE64", "Quoted-Printable", "X-BASE8", "X-BASE10", or "X-BASE16" for an imgCIF or "BINARY" for a CBF. The octal, decimal and hexadecimal transfer encodings are for convenience in debugging, and are not recommended for archiving and data interchange. In an imgCIF file, the encoded binary data begins after the empty line terminating the header. In a CBF, the raw binary data begins after an empty line terminating the header and after the sequence: Octet Hex Decimal Purpose 0 0C 12 (ctrl-L) Page break 1 1A 26 (ctrl-Z) Stop listings in MS-DOS 2 04 04 (Ctrl-D) Stop listings in UNIX 3 D5 213 Binary section begins None of these octets are included in the calculation of the message size, nor in the calculation of the message digest. The X-Binary-Size header specifies the size of the equivalent binary data in octets. If compression was used, this size is the size after compression, including any book-keeping fields. An adjustment is made for the deprecated binary formats in which 8 bytes of binary header are used for the compression type. In that case, the 8 bytes used for the compression type is subtracted from the size, so that the same size will be reported if the compression type is supplied in the MIME header. Use of the MIME header is the recommended way to supply the compression type. In general, no portion of the binary header is included in the calculation of the size. The X-Binary-Element-Type header specifies the type of binary data in the octets, using the same descriptive phrases as in _array_structure.encoding_type. The default value is "unsigned 32-bit integer". An MD5 message digest may, optionally, be used. The "RSA Data Security, Inc. MD5 Message-Digest Algorithm" should be used. No portion of the header is included in the calculation of the message digest. If the Transfer Encoding is "X-BASE8", "X-BASE10", or "X-BASE16", the data is presented as octal, decimal or hexadecimal data organized into lines or words. Each word is created by composing octets of data in fixed groups of 2, 3, 4, 6 or 8 octets, either in the order ...4321 ("big- endian") or 1234... (little-endian). If there are fewer than the specified number of octets to fill the last word, then the missing octets are presented as "==" for each missing octet. Exactly two equal signs are used for each missing octet even for octal and decimal encoding. The format of lines is: rnd xxxxxx xxxxxx xxxxxx where r is "H", "O", or "D" for hexadecimal, octal or decimal, n is the number of octets per word. and d is "<" for ">" for the "...4321" and "1234..." octet orderings respectively. The "==" padding for the last word should be on the appropriate side to correspond to the missing octets, e.g. H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000 or H3> FF0700 00==== For these hex, octal and decimal formats, only, comments beginning with "#" are permitted to improve readability. BASE64 encoding follows MIME conventions. Octets are in groups of three, c1, c2, c3. The resulting 24 bits are broken into four 6-bit quantities, starting with the high-order six bits (c1 >> 2) of the first octet, then the low-order two bits of the first octet followed by the high-order 4 bits of the second octet ((c1 & 3)<<4 | (c2>>4)), then the bottom 4 bits of the second octet followed by the high order two bits of the last octet ((c2 & 15)<<2 | (c3>>6)), then the bottom six bits of the last octet (c3 & 63). Each of these four quantities is translated into an ASCII character using the mapping: 1 2 3 4 5 6 0123456789012345678901234567890123456789012345678901234567890123 | | | | | | | ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/ With short groups of octets padded on the right with one "=" if c3 is missing, and with "==" if both c2 and c3 are missing. QUOTED-PRINTABLE encoding also follows MIME conventions, copying octets without translation if their ASCII values are 32..38, 42, 48..57, 59..60, 62, 64..126 and the octet is not a ";" in column 1. All other characters are translated to =nn, where nn is the hexadecimal encoding of the octet. All lines are "wrapped" with a terminating "=" (i.e. the MIME conventions for an implicit line terminator are never used). ; _item.name '_array_data.data' _item.category_id array_data _item.mandatory_code yes _item_type.code binary save_ ###################### # ARRAY_ELEMENT_SIZE # ###################### save_ARRAY_ELEMENT_SIZE _category.description ; Data items in the ARRAY_ELEMENT_SIZE category record the physical size of array elements along each array dimension. ; _category.id array_element_size _category.mandatory_code no loop_ _category_key.name '_array_element_size.array_id' '_array_element_size.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A regular 2D array with a uniform element dimension of 1220 nanometres. ; ; loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size image_1 1 1.22e-6 image_1 2 1.22e-6 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_element_size.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_element_size.array_id' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.index _item_description.description ; This item is a pointer to _array_structure_list.index in the ARRAY_STRUCTURE_LIST category. ; _item.name '_array_element_size.index' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.size _item_description.description ; The size in metres of an image element in this dimension. This supposes that the elements are arranged on a regular grid. ; _item.name '_array_element_size.size' _item.category_id array_element_size _item.mandatory_code yes _item_type.code float _item_units.code 'metres' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ ##################### # ARRAY_INTENSITIES # ##################### save_ARRAY_INTENSITIES _category.description ; Data items in the ARRAY_INTENSITIES category record the information required to recover the intensity data from the set of data values stored in the ARRAY_DATA category. The actual detector may have a complex relationship between the raw intensity values and the number of incident photons. In most cases, the number stored in the final array will have a simple linear relationship to the actual number of incident photons, given by '_array_intensities.gain'. If raw, uncorrected values are presented (e.g for calibration experiments), the value of '_array_intensities.linearity' will be 'raw' and '_array_intensities.gain' will not be used. ; _category.id array_intensities _category.mandatory_code no loop_ _category_key.name '_array_intensities.array_id' '_array_intensities.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 ; ; loop_ _array_intensities.array_id _array_intensities.linearity _array_intensities.gain _array_intensities.overload _array_intensities.undefined_value image_1 linear 1.2 655535 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_intensities.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_intensities.array_id' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code save_ save__array_intensities.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_array_intensities.binary_id' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code int save_ save__array_intensities.gain _item_description.description ; Detector "gain". The factor by which linearized intensity count values should be divided to produce true photon counts. ; _item.name '_array_intensities.gain' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain_esd' 'associated_value' save_ save__array_intensities.gain_esd _item_description.description ; The estimated standard deviation in detector "gain". ; _item.name '_array_intensities.gain_esd' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain' 'associated_esd' save_ save__array_intensities.linearity _item_description.description ; The intensity linearity scaling used from raw intensity to the stored element value: 'linear' is obvious 'offset' means that the value defined by '_array_intensities.offset' should be added to each element value. 'scaling' means that the value defined by '_array_intensities.scaling' should be multiplied with each element value. 'scaling_offset' is the combination of the two previous cases, with the scale factor applied before the offset value. 'sqrt_scaled' means that the square root of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and squaring the result. 'logarithmic_scaled' means that the logarithm based 10 of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and calculating 10 to the power of this number. 'raw' means that the data is the raw is a set of raw values straight from the detector. ; _item.name '_array_intensities.linearity' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'linear' . 'offset' ; The value defined by '_array_intensities.offset' should be added to each element value. ; 'scaling' ; The value defined by '_array_intensities.scaling' should be multiplied with each element value. ; 'scaling_offset' ; The combination of the scaling and offset with the scale factor applied before the offset value. ; 'sqrt_scaled' ; The square root of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and squaring the result. ; 'logarithmic_scaled' ; The logarithm based 10 of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and calculating 10 to the power of this number. ; 'raw' ; The array consists of raw values to which no corrections have been applied. While the handling of the data is similar to that given for 'linear' data with no offset, the meaning of the data differs in that the number of incident photons is not necessarily linearly related to the number of counts reported. This value is intended for use either in calibration experiments or to allow for handling more complex data fitting algorithms than are allowed for by this data item. ; save_ save__array_intensities.offset _item_description.description ; Offset value to add to array element values in the manner described by item _array_intensities.linearity. ; _item.name '_array_intensities.offset' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.scaling _item_description.description ; Multiplicative scaling value to be applied to array data in the manner described by item _array_intensities.linearity. ; _item.name '_array_intensities.scaling' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.overload _item_description.description ; The saturation intensity level for this data array. ; _item.name '_array_intensities.overload' _item.category_id array_intensities _item.mandatory_code no _item_type.code float _item_units.code 'counts' save_ save__array_intensities.undefined_value _item_description.description ; A value to be substituted for undefined values in the data array. ; _item.name '_array_intensities.undefined_value' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ ################### # ARRAY_STRUCTURE # ################### save_ARRAY_STRUCTURE _category.description ; Data items in the ARRAY_STRUCTURE category record the organization and encoding of array data which may be stored in the ARRAY_DATA category. ; _category.id array_structure _category.mandatory_code no _category_key.name '_array_structure.id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order image_1 "unsigned 16-bit integer" none little_endian ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure.byte_order _item_description.description ; The order of bytes for integer values which require more than 1-byte. (IBM-PC's and compatibles, and Dec-Vaxes use low-byte-first ordered integers, whereas Hewlett Packard 700 series, Sun-4 and Silicon Graphics use high-byte-first ordered integers. Dec-Alphas can produce/use either depending on a compiler switch.) ; _item.name '_array_structure.byte_order' _item.category_id array_structure _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'big_endian' ; The first byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; 'little_endian' ; The last byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; save_ save__array_structure.compression_type _item_description.description ; Type of data compression method used to compress the array data. ; _item.name '_array_structure.compression_type' _item.category_id array_structure _item.mandatory_code no _item_type.code code _item_default.value 'none' loop_ _item_enumeration.value _item_enumeration.detail 'none' ; Data are stored in normal format as defined by '_array_structure.encoding_type' and '_array_structure.byte_order'. ; 'byte_offsets' ; Using the compression scheme defined in CBF definition Section 5.0. ; 'packed' ; Using the 'packed' compression scheme, a CCP4-style packing (CBFlib section 3.3.2) ; 'canonical' ; Using the 'canonical' compression scheme (CBFlib section 3.3.1) ; save_ save__array_structure.encoding_type _item_description.description ; Data encoding of a single element of array data. In several cases, the IEEE format is referenced. See "IEEE Standard for Binary Floating-Point Arithmetic", ANSI/IEEE Std 754-1985, the Institute of Electrical and Electronics Engineers, Inc., NY 1985. ; _item.name '_array_structure.encoding_type' _item.category_id array_structure _item.mandatory_code yes _item_type.code uline loop_ _item_enumeration.value 'unsigned 8-bit integer' 'signed 8-bit integer' 'unsigned 16-bit integer' 'signed 16-bit integer' 'unsigned 32-bit integer' 'signed 32-bit integer' 'signed 32-bit real IEEE' 'signed 64-bit real IEEE' 'signed 32-bit complex IEEE' save_ save__array_structure.id _item_description.description ; The value of _array_structure.id must uniquely identify each item of array data. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure.id' array_structure yes '_array_data.array_id' array_data yes '_array_structure_list.array_id' array_structure_list yes '_array_intensities.array_id' array_intensities yes '_diffrn_data_frame.array_id' diffrn_data_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_data.array_id' '_array_structure.id' '_array_structure_list.array_id' '_array_structure.id' '_array_intensities.array_id' '_array_structure.id' '_diffrn_data_frame.array_id' '_array_structure.id' save_ ######################## # ARRAY_STRUCTURE_LIST # ######################## save_ARRAY_STRUCTURE_LIST _category.description ; Data items in the ARRAY_STRUCTURE_LIST category record the size and organization of each array dimension. The relationship to physical axes may be given. ; _category.id array_structure_list _category.mandatory_code no loop_ _category_key.name '_array_structure_list.array_id' '_array_structure_list.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - An image array of 1300 x 1200 elements. The raster order of the image is left-to-right (increasing) in first dimension and bottom-to-top (decreasing) in the second dimension. ; ; loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id image_1 1 1300 1 increasing ELEMENT_X image_1 2 1200 2 decreasing ELEMENY_Y ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure_list.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_structure_list.array_id' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code code save_ save__array_structure_list.axis_set_id _item_description.description ; This is a descriptor for the physical axis or set of axes corresponding to an array index. This data item is related to the axes of the detector itself given in DIFFRN_DETECTOR_AXIS, but usually differ in that the axes in this category are the axes of the coordinate system of reported data points, while the axes in DIFFRN_DETECTOR_AXIS are the physical axes of the detector describing the "poise" of the detector as an overall physical object. If there is only one axis in the set, the identifier of that axis should be used as the identifier of the set. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.axis_set_id' array_structure_list yes '_array_structure_list_axis.axis_set_id' array_structure_list_axis implicit _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_structure_list_axis.axis_set_id' '_array_structure_list.axis_set_id' save_ save__array_structure_list.dimension _item_description.description ; The number of elements stored in the array structure in this dimension. ; _item.name '_array_structure_list.dimension' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.direction _item_description.description ; Identifies the direction in which this array index changes. ; _item.name '_array_structure_list.direction' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_enumeration.value _item_enumeration.detail 'increasing' ; Indicates the index changes from 1 to the maximum dimension. ; 'decreasing' ; Indicates the index changes from the maximum dimension to 1. ; save_ save__array_structure_list.index _item_description.description ; Identifies the one-based index of the row or column in the array structure. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.index' array_structure_list yes '_array_structure_list.precedence' array_structure_list yes '_array_element_size.index' array_element_size yes _item_type.code int loop_ _item_linked.child_name _item_linked.parent_name '_array_element_size.index' '_array_structure_list.index' loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.precedence _item_description.description ; Identifies the rank order in which this array index changes with respect to other array indices. The precedence of 1 indicates the index which changes fastest. ; _item.name '_array_structure_list.precedence' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ ############################# # ARRAY_STRUCTURE_LIST_AXIS # ############################# save_ARRAY_STRUCTURE_LIST_AXIS _category.description ; Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe the physical settings of sets axes for the centres of pixels that correspond to data points described in the ARRAY_STRUCTURE_LIST category. In the simplest cases, the physical increments of a single axis correspond to the increments of a single array index. More complex organizations, e.g. spiral scans, may require coupled motions along multiple axes. Note that a spiral scan uses two coupled axis, one for the angular direction, one for the radial direction. This differs from a cylindrical scan for which the two axes are not coupled into one set. ; _category.id array_structure_list_axis _category.mandatory_code no loop_ _category_key.name '_array_structure_list_axis.axis_set_id' '_array_structure_list_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' save_ save__array_structure_list_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the set of axes for which settings are being specified. Multiple axes may be specified for the same value of '_array_structure_list_axis.axis_set_id' This item is a pointer to _axis.id in the AXIS category. ; _item.name '_array_structure_list_axis.axis_id' _item.category_id array_structure_list_axis _item.mandatory_code yes save_ save__array_structure_list_axis.axis_set_id _item_description.description ; The value of this data item is the identifier of the set of axes for which axis settings are being specified. Multiple axes may be specified for the same value of _array_structure_list_axis.axis_set_id . This item is a pointer to _array_structure_list.axis_set_id in the ARRAY_STRUCTURE_LIST category. If this item is not specified, it defaults to the corresponding axis identifier. ; _item.name '_array_structure_list_axis.axis_set_id' _item.category_id array_structure_list_axis _item.mandatory_code implicit save_ save__array_structure_list_axis.angle _item_description.description ; The setting of the specified axis in degrees for the first data point of the array index with the corresponding value of '_array_structure_list.axis_set_id'. If the index is specified as 'increasing' this will be the center of the pixel with index value 1. If the index is specified as 'decreasing' this will be the center of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.angle' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.angle_increment _item_description.description ; The pixel-center-to-pixel-center increment in the angular setting of the specified axis in degrees. This is not meaningful in the case of 'constant velocity' spiral scans and should not be specified in that case. See '_array_structure_list_axis.angular_pitch'. ; _item.name '_array_structure_list_axis.angle_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for the first data point of the array index with the corresponding value of '_array_structure_list.axis_set_id'. If the index is specified as 'increasing' this will be the center of the pixel with index value 1. If the index is specified as 'decreasing' this will be the center of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.displacement' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.displacement_increment _item_description.description ; The pixel-center-to-pixel-center increment for the displacement setting of the specified axis in millimetres. ; _item.name '_array_structure_list_axis.displacement_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.angular_pitch _item_description.description ; The pixel-center-to-pixel-center distance for a one step change in the setting of the specified axis in millimetres. This is meaningful only for 'constant velocity' spiral scans, or for uncoupled angular scans at a constant radius (cylindrical scan) and should not be specified for cases in which the angle between pixels, rather than the distance between pixels is uniform. See '_array_structure_list_axis.angle_increment'. ; _item.name '_array_structure_list_axis.angular_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.radial_pitch _item_description.description ; The radial distance from one "cylinder" of pixels to the next in millimetres. If the scan is a 'constant velocity' scan with differing angular displacements between pixels, the value of this item may differ significantly from the value of '_array_structure_list_axis.displacement_increment'. ; _item.name '_array_structure_list_axis.radial_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ ######## # AXIS # ######## save_AXIS _category.description ; Data items in the AXIS category record the information required to describe the various goniometer, detector, source and other axes needed to specify a data collection. The location of each axis is specified by two vectors: the axis itself, given as a unit vector, and an offset to the base of the unit vector. These vectors are referenced to a right-handed laboratory coordinate system with its origin in the sample or specimen: | Y (to complete right-handed system) | | | | | |________________X / principal goniometer axis / / / / /Z (to source) Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from the sample or specimen along the principal axis of the goniometer. Axis 2 (Y): The Y-axis completes an orthogonal right-handed system defined by the X-axis and the Z-axis (see below). Axis 3 (Z): The Z-axis is derived from the source axis which goes from the sample to the source. The Z-axis is the component of the source axis in the direction of the source orthogonal to the X-axis in the plane defined by the X-axis and the source axis. These axes are based on the goniometer, not on the orientation of the detector, gravity, etc. The vectors necessary to specify all other axes are given by sets of three components in the order (X, Y, Z). If the axis involved is a rotation axis, it is right handed, i.e. as one views the object to be rotated from the origin (the tail) of the unit vector, the rotation is clockwise. If a translation axis is specified, the direction of the unit vector specifies the sense of positive translation. Note: This choice of coordinate system is similar to, but significantly different from the choice in MOSFLM (Andrew G.W. Leslie, Harry Powell, MRC Laboratory of Molecular Biology, Hills Road, Cambridge CB2 2QH,UK http://www.dl.ac.uk/CCP/CCP4/dist/x-windows/Mosflm/). In MOSFLM, X is along the X-ray beam (our Z axis) and Z is along the rotation axis. All rotations are given in degrees and all translations are given in mm. Axes may be dependent on one another. The X-axis is the only goniometer axis the direction of which is strictly connected to the hardware. All other axes are specified by the positions they would assume when the axes upon which they depend are at their zero points. When specifying detector axes, the axis is given to the beam center. The location of the beam center on the detector should be given in the DIFFRN_DETECTOR category in distortion-corrected mm from the (0,0) corner of the detector. It should be noted that many different origins arise in the definition of an experiment. In particular, as noted above, we need to specify the location of the beam center on the detector in terms of the origin of the detector, which is, of course, not coincident with the center of the sample. ; _category.id axis _category.mandatory_code no loop_ _category_key.name '_axis.id' '_axis.equipment' loop_ _category_group.id 'inclusive_group' 'axis_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows the axis specification of the axes of a kappa geometry goniometer (See "X-Ray Structure Determination, A Practical Guide", 2nd ed. by G. H. Stout, L. H. Jensen, Wiley Interscience, 1989, 453 pp, p 134.). There are three axes specified, and no offsets. The outermost axis, omega, is pointed along the X-axis. The next innermost axis, kappa, is at a 50 degree angle to the X-axis, pointed away from the source. The innermost axis, phi, aligns with the X-axis when omega and phi are at their zero-points. If T-omega, T-kappa and T-phi are the transformation matrices derived from the axis settings, the complete transformation would be: x' = (T-omega) (T-kappa) (T-phi) x ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] omega rotation goniometer . 1 0 0 kappa rotation goniometer omega -.64279 0 -.76604 phi rotation goniometer kappa 1 0 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - This example show the axis specification of the axes of a detector, source and gravity. We have juggled the order as a reminder that the ordering of presentation of tokens is not significant. We have taken the center of rotation of the detector to be 68 millimetres in the direction away from the source. ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] source . source . 0 0 1 . . . gravity . gravity . 0 -1 0 . . . tranz translation detector rotz 0 0 1 0 0 -68 twotheta rotation detector . 1 0 0 . . . roty rotation detector twotheta 0 1 0 0 0 -68 rotz rotation detector roty 0 0 1 0 0 -68 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__axis.depends_on _item_description.description ; The value of _axis.type specifies the next outermost axis upon which this axis depends. This item is a pointer to axis.id in the same category. ; _item.name '_axis.depends_on' _item.category_id axis _item.mandatory_code no save_ save__axis.equipment _item_description.description ; The value of _axis.type specifies the type of equipment using the axis: goniometer, detector, gravity, source or general ; _item.name '_axis.equipment' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail goniometer 'equipment used to orient or position samples' detector 'equipment used to detect reflections' general 'equipment used for general purposes' gravity 'axis specifying the downward direction' source 'axis specifying the direction sample to source' save_ save__axis.offset[1] _item_description.description ; The [1] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[2] _item_description.description ; The [2] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[3] _item_description.description ; The [3] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.id _item_description.description ; The value of _axis.id must uniquely identify each axis relevant to the experiment. Note that multiple pieces of equipment may share the same axis (e.g. a twotheta arm), so that the category key for AXIS also includes the equipment. ; loop_ _item.name _item.category_id _item.mandatory_code '_axis.id' axis yes '_array_structure_list_axis.axis_id' array_structure_list_axis yes '_diffrn_detector_axis.axis_id' diffrn_detector_axis yes '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes '_diffrn_scan_axis.axis_id' diffrn_scan_axis yes '_diffrn_scan_frame_axis.axis_id' diffrn_scan_frame_axis yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_axis.depends_on' '_axis.id' '_array_structure_list_axis.axis_id' '_axis.id' '_diffrn_detector_axis.axis_id' '_axis.id' '_diffrn_measurement_axis.axis_id' '_axis.id' '_diffrn_scan_axis.axis_id' '_axis.id' '_diffrn_scan_frame_axis.axis_id' '_axis.id' save_ save__axis.type _item_description.description ; The value of _axis.type specifies the type of axis: rotation, translation (or general when the type is not relevant, as for gravity) ; _item.name '_axis.type' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail rotation 'right-handed axis of rotation' translation 'translation in the direction of the axis' general 'axis for which the type is not relevant' save_ save__axis.vector[1] _item_description.description ; The [1] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector, and is dimensionless. ; _item.name '_axis.vector[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[2] _item_description.description ; The [2] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector, and is dimensionless. ; _item.name '_axis.vector[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[3] _item_description.description ; The [3] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector, and is dimensionless. ; _item.name '_axis.vector[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ ##################### # DIFFRN_DATA_FRAME # ##################### save_DIFFRN_DATA_FRAME _category.description ; Data items in the DIFFRN_DATA_FRAME category record the details about each frame of data. The items in this category were previously in a DIFFRN_FRAME_DATA category, which is now deprecated. The items from the old category are provided as aliases, but should not be used for new work. ; _category.id diffrn_data_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_data_frame.id' '_diffrn_data_frame.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A frame containing data from 4 frame elements. Each frame element has a common array configuration 'array_1' described in ARRAY_STRUCTURE and related categories. The data for each detector element is stored in four groups of binary data in the ARRAY_DATA category, linked by the array_id and binary_id ; ; loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id frame_1 d1_ccd_1 array_1 1 frame_1 d1_ccd_2 array_1 2 frame_1 d1_ccd_3 array_1 3 frame_1 d1_ccd_4 array_1 4 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_data_frame.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_diffrn_data_frame.array_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.array_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0.00 _item_type.code code save_ save__diffrn_data_frame.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_diffrn_data_frame.binary_id' _item.category_id diffrn_data_frame _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_frame_data.binary_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code int save_ save__diffrn_data_frame.detector_element_id _item_description.description ; This item is a pointer to _diffrn_detector_element.id in the DIFFRN_DETECTOR_ELEMENT category. ; _item.name '_diffrn_data_frame.detector_element_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.detector_element_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.id _item_description.description ; The value of _diffrn_data_frame.id must uniquely identify each complete frame of data. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_data_frame.id' diffrn_data_frame yes '_diffrn_refln.frame_id' diffrn_refln yes '_diffrn_scan.frame_id_start' diffrn_scan yes '_diffrn_scan.frame_id_end' diffrn_scan yes '_diffrn_scan_frame.frame_id' diffrn_scan_frame yes '_diffrn_scan_frame_axis.frame_id' diffrn_scan_frame_axis yes _item_aliases.alias_name '_diffrn_frame_data.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_refln.frame_id' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_start' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_end' '_diffrn_data_frame.id' '_diffrn_scan_frame.frame_id' '_diffrn_data_frame.id' '_diffrn_scan_frame_axis.frame_id' '_diffrn_data_frame.id' save_ ########################################################################## # The following is a restatement of the mmCIF DIFFRN_DETECTOR, # # DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for # # the CBF/imgCIF extensions # ########################################################################## ################### # DIFFRN_DETECTOR # ################### save_DIFFRN_DETECTOR _category.description ; Data items in the DIFFRN_DETECTOR category describe the detector used to measure the scattered radiation, including any analyser and post-sample collimation. ; _category.id diffrn_detector _category.mandatory_code no loop_ _category_key.name '_diffrn_detector.diffrn_id' '_diffrn_detector.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_detector.diffrn_id 'd1' _diffrn_detector.detector 'multiwire' _diffrn_detector.type 'Siemens' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector.details _item_description.description ; A description of special aspects of the radiation detector. ; _item.name '_diffrn_detector.details' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; Need new example here. ; save_ save__diffrn_detector.detector _item_description.description ; The general class of the radiation detector. ; _item.name '_diffrn_detector.detector' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector' cifdic.c91 1.0 '_diffrn_detector' cif_core.dic 2.0 _item_type.code text loop_ _item_examples.case 'photographic film' 'scintillation counter' 'CCD plate' 'BF~3~ counter' save_ save__diffrn_detector.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. The value of _diffrn.id uniquely defines a set of diffraction data. ; _item.name '_diffrn_detector.diffrn_id' _item.mandatory_code yes save_ save__diffrn_detector.dtime _item_description.description ; The deadtime in microseconds of the detectors used to measure the diffraction intensities. ; _item.name '_diffrn_detector.dtime' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector_dtime' cifdic.c91 1.0 '_diffrn_detector_dtime' cif_core.dic 2.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code microseconds save_ save__diffrn_detector.id _item_description.description ; The value of _diffrn_detector.id must uniquely identify each detector used to collect each diffraction data set. If the value of _diffrn_detector.id is not given, it is implicitly equal to the value of _diffrn_detector.diffrn_id ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector.id' diffrn_detector implicit '_diffrn_detector_axis.detector_id' diffrn_detector_axis yes loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_detector_axis.detector_id' '_diffrn_detector.id' _item_type.code code save_ save__diffrn_detector.number_of_axes _item_description.description ; The value of _diffrn_detector.number_of_axes gives the number of axes of the positioner for the detector identified by _diffrn_detector.id The word "positioner" is a general term used in instrumentation design for devices that are used to change the positions of portions of apparatus by linear translation, rotation, or combinations of such motions. Axes which are used to provide a coordinate system for the face of an area detetctor should not be counted for this data item. The description of each axis should be provided by entries in DIFFRN_DETECTOR_AXIS. ; _item.name '_diffrn_detector.number_of_axes' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_detector.type _item_description.description ; The make, model or name of the detector device used. ; _item.name '_diffrn_detector.type' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ ######################## # DIFFRN_DETECTOR_AXIS # ######################## save_DIFFRN_DETECTOR_AXIS _category.description ; Data items in the DIFFRN_DETECTOR_AXIS category associate axes with detectors. ; _category.id diffrn_detector_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_axis.detector_id' '_diffrn_detector_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_detector_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_detector_axis.axis_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_axis.detector_id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. This item was previously named '_diffrn_detector_axis.id' which is now a deprecated name. The old name is provided as an alias, but should not be used for new work. ; _item.name '_diffrn_detector_axis.detector_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_aliases.alias_name '_diffrn_detector_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 save_ ########################### # DIFFRN_DETECTOR_ELEMENT # ########################### save_DIFFRN_DETECTOR_ELEMENT _category.description ; Data items in the DIFFRN_DETECTOR_ELEMENT category record the details about spatial layout and other characteristics of each element of a detector which may have multiple elements. In most cases, the more detailed information provided in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS are preferable to simply providing the centre. ; _category.id diffrn_detector_element _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_element.id' '_diffrn_detector_element.detector_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Detector d1 is composed of four CCD detector elements, each 200 mm by 200 mm, arranged in a square. in the pattern 1 2 * 3 4 Note that the beam center is slightly off of each of the detector elements, just beyond the lower right corner of 1, the lower left corner of 2, the upper right corner of 3 and the upper left corner of 4. ; ; loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id _diffrn_detector_element.center[1] _diffrn_detector_element.center[2] d1 d1_ccd_1 201.5 -1.5 d1 d1_ccd_2 -1.8 -1.5 d1 d1_ccd_3 201.6 201.4 d1 d1_ccd_4 -1.7 201.5 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector_element.center[1] _item_description.description ; The value of _diffrn_detector_element.center[1] is the X component of the distortion-corrected beam-center in mm from the (0, 0) (lower left) corner of the detector element viewed from the sample side. ; _item.name '_diffrn_detector_element.center[1]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.center[2] _item_description.description ; The value of _diffrn_detector_element.center[2] is the Y component of the distortion-corrected beam-center in mm from the (0, 0) (lower left) corner of the detector element viewed from the sample side. ; _item.name '_diffrn_detector_element.center[2]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.id _item_description.description ; The value of _diffrn_detector_element.id must uniquely identify each element of a detector. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector_element.id' diffrn_detector_element yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.detector_element_id' '_diffrn_detector_element.id' save_ save__diffrn_detector_element.detector_id _item_description.description ; This item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. ; _item.name '_diffrn_detector_element.detector_id' _item.category_id diffrn_detector_element _item.mandatory_code yes _item_type.code code save_ ######################## ## DIFFRN_MEASUREMENT ## ######################## save_DIFFRN_MEASUREMENT _category.description ; Data items in the DIFFRN_MEASUREMENT category record details about the device used to orient and/or position the crystal during data measurement and the manner in which the diffraction data were measured. ; _category.id diffrn_measurement _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement.device' '_diffrn_measurement.diffrn_id' '_diffrn_measurement.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_measurement.diffrn_id 'd1' _diffrn_measurement.device '3-circle camera' _diffrn_measurement.device_type 'Supper model x' _diffrn_measurement.device_details 'none' _diffrn_measurement.method 'omega scan' _diffrn_measurement.details ; Need new example here ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991). Acta Cryst. C47, 2276-2277]. ; ; _diffrn_measurement.diffrn_id 's1' _diffrn_measurement.device_type 'Philips PW1100/20 diffractometer' _diffrn_measurement.method 'theta/2theta (\q/2\q)' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_measurement.device _item_description.description ; The general class of goniometer or device used to support and orient the specimen. If the value of _diffrn_measurement.device is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id Either '_diffrn_measurement.device' or '_diffrn_measurement.id' may be used to link to other categories. If the experimental setup admits multiple devices, then '_diffrn_measurement.id' is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.device' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_device' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement.device' _item_aliases.alias_name '_diffrn_measurement_device' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '3-circle camera' '4-circle camera' 'kappa-geometry camera' 'oscillation camera' 'precession camera' save_ save__diffrn_measurement.device_details _item_description.description ; A description of special aspects of the device used to measure the diffraction intensities. ; _item.name '_diffrn_measurement.device_details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; commercial goniometer modified locally to allow for 90\% \t arc ; save_ save__diffrn_measurement.device_type _item_description.description ; The make, model or name of the measurement device (goniometer) used. ; _item.name '_diffrn_measurement.device_type' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Supper model q' 'Huber model r' 'Enraf-Nonius model s' 'homemade' save_ save__diffrn_measurement.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_measurement.diffrn_id' _item.mandatory_code yes save_ save__diffrn_measurement.details _item_description.description ; A description of special aspects of the intensity measurement. ; _item.name '_diffrn_measurement.details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; save_ save__diffrn_measurement.id _item_description.description ; The value of _diffrn_measurement.id must uniquely identify the set of mechanical characteristics of the device used to orient and/or position the sample used during collection of each diffraction data set. If the value of _diffrn_measurement.id is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id Either '_diffrn_measurement.device' or '_diffrn_measurement.id' may be used to link to other categories. If the experimental setup admits multiple devices, then '_diffrn_measurement.id' is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.id' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_id' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement.id' _item_type.code code save_ save__diffrn_measurement.method _item_description.description ; Method used to measure intensities. ; _item.name '_diffrn_measurement.method' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_method' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'profile data from theta/2theta (\q/2\q) scans' save_ save__diffrn_measurement.number_of_axes _item_description.description ; The value of _diffrn_measurement.number_of_axes gives the number of axes of the positioner for the goniometer or other sample orientation or positioning device identified by _diffrn_measurement.id The description of the axes should be provided by entries in DIFFRN_MEASUREMENT_AXIS. ; _item.name '_diffrn_measurement.number_of_axes' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_measurement.specimen_support _item_description.description ; The physical device used to support the crystal during data collection. ; _item.name '_diffrn_measurement.specimen_support' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_specimen_support' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'glass capillary' 'quartz capillary' 'fiber' 'metal loop' save_ ########################### # DIFFRN_MEASUREMENT_AXIS # ########################### save_DIFFRN_MEASUREMENT_AXIS _category.description ; Data items in the DIFFRN_MEASUREMENT_AXIS category associate axes with goniometers. ; _category.id diffrn_measurement_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_measurement_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_measurement_axis.axis_id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.measurement_device _item_description.description ; This data item is a pointer to _diffrn_measurement.device in the DIFFRN_MEASUREMENT category. ; _item.name '_diffrn_measurement_axis.measurement_device' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit save_ save__diffrn_measurement_axis.measurement_id _item_description.description ; This data item is a pointer to _diffrn_measurement.id in the DIFFRN_MEASUREMENT category. This item was previously named '_diffrn_measurement_axis.id' which is now a deprecated name. The old name is provided as an alias, but should not be used for new work. ; _item.name '_diffrn_measurement_axis.measurement_id' _item.category_id diffrn_measurement_axis _item_aliases.alias_name '_diffrn_measurement_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0.00 _item.mandatory_code implicit save_ #################### # DIFFRN_RADIATION # #################### save_DIFFRN_RADIATION _category.description ; Data items in the DIFFRN_RADIATION category describe the radiation used in measuring diffraction intensities, its collimation and monochromatisation before the sample. Post-sample treatment of the beam is described by data items in the DIFFRN_DETECTOR category. ; _category.id diffrn_radiation _category.mandatory_code no _category_key.name '_diffrn_radiation.diffrn_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_radiation.diffrn_id 'set1' _diffrn_radiation.collimation '0.3 mm double pinhole' _diffrn_radiation.monochromator 'graphite' _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.wavelength_id 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991). Acta Cryst. C47, 2276-2277]. ; ; _diffrn_radiation.wavelength_id 1 _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.monochromator 'graphite' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_radiation.collimation _item_description.description ; The collimation or focusing applied to the radiation. ; _item.name '_diffrn_radiation.collimation' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_collimation' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '0.3 mm double-pinhole' '0.5 mm' 'focusing mirrors' save_ save__diffrn_radiation.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_radiation.diffrn_id' _item.mandatory_code yes save_ save__diffrn_radiation.div_x_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory X axis (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the esd of the directions of photons in the X-Z plane around the mean source beam direction. Note that some synchrotrons specify this value in milliradians, in which case a conversion would be needed. To go from a value in milliradians to a value in degrees, multiply by 0.180 and divide by Pi. ; _item.name '_diffrn_radiation.div_x_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.div_y_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory Y axis (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the esd of the directions of photons in the Y-Z plane around the mean source beam direction. Note that some synchrotrons specify this value in milliradians, in which case a conversion would be needed. To go from a value in milliradians to a value in degrees, multiply by 0.180 and divide by Pi. ; _item.name '_diffrn_radiation.div_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.div_x_y_source _item_description.description ; Beam crossfire correlation degrees**2 between the crossfire laboratory X-axis component and the crossfire laboratory Y-axis component (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the mean of the products of the deviations of the directin of each photons in X-Z plane times the deviations of the direction of the same photon in the Y-Z plane around the mean source beam direction. This will be zero for uncorrelated crossfire. Note that some synchrotrons specify this value in milliradians**2, in which case a conversion would be needed. To go from a value in milliradians**2 to a value in degrees**2, multiply by 0.180**2 and divide by Pi**2. ; _item.name '_diffrn_radiation.div_x_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees_squared _item_default.value 0.0 save_ save__diffrn_radiation.filter_edge _item_description.description ; Absorption edge in angstroms of the radiation filter used. ; _item.name '_diffrn_radiation.filter_edge' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_filter_edge' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__diffrn_radiation.inhomogeneity _item_description.description ; Half-width in millimetres of the incident beam in the direction perpendicular to the diffraction plane. ; _item.name '_diffrn_radiation.inhomogeneity' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_inhomogeneity' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code millimetres save_ save__diffrn_radiation.monochromator _item_description.description ; The method used to obtain monochromatic radiation. If a mono- chromator crystal is used the material and the indices of the Bragg reflection are specified. ; _item.name '_diffrn_radiation.monochromator' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_monochromator' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Zr filter' 'Ge 220' 'none' 'equatorial mounted graphite' save_ save__diffrn_radiation.polarisn_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the perpendicular component of the polarisation and the diffraction plane. See _diffrn_radiation_polarisn_ratio. ; _item.name '_diffrn_radiation.polarisn_norm' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_norm' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.polarisn_ratio _item_description.description ; Polarisation ratio of the diffraction beam incident on the crystal. It is the ratio of the perpendicularly polarised to the parallel polarised component of the radiation. The perpendicular component forms an angle of _diffrn_radiation.polarisn_norm to the normal to the diffraction plane of the sample (i.e. the plane containing the incident and reflected beams). ; _item.name '_diffrn_radiation.polarisn_ratio' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_ratio' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__diffrn_radiation.polarizn_source_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the normal to the polarization plane and the laboratory Y axis as defined in the AXIS category. Note that this is the angle of polarization of the source photons, either directly from a synchrotron beamline or from a monchromater. This differs from the value of '_diffrn_radiation.polarisn_norm' in that '_diffrn_radiation.polarisn_norm' refers to polarization relative to the diffraction plane rather than to the laboratory axis system. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane should be taken as the X-Z plane, and the angle as 0. See '_diffrn_radiation.polarizn_source_ratio'. ; _item.name '_diffrn_radiation.polarizn_source_norm' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.polarizn_source_ratio _item_description.description ; (Ip-In)/(Ip+In), where Ip is the intensity (amplitude squared) of the electric vector in the plane of polarization and In is the intensity (amplitude squared) of the electric vector in plane of the normal to the plane of polarization. Thus, if we had complete polarization in the plane of polarization, the value of '_diffrn_radiation.polarizn_source_ratio' would be 1, and an unpolarized beam would have a value of 0. If the X-axis has been chosen to lie in the plane of polarization, this definition will agree with the definition of "MONOCHROMATOR" in the Denzo glossary, and values of near 1 should be expected for a bending magnet source. However, if the X-axis were, for some reason to be, say, perpendicular to the polarization plane (not a common choice), then the Denzo value would be the negative of '_diffrn_radiation.polarizn_source_ratio'. See http://www.hkl-xray.com for information on Denzo, and Z. Otwinowski and W. Minor, " Processing of X-ray Diffraction Data Collected in Oscillation Mode ", Methods in Enzymology, Volume 276: Macromolecular Crystallography, part A, p.307-326, 1997,C.W. Carter, Jr. & R. M. Sweet, Eds., Academic Press. This differs both in the choice of ratio and choice of orientation from '_diffrn_radiation.polarisn_ratio', which, unlike '_diffrn_radiation.polarizn_source_ratio', is unbounded. ; _item.name '_diffrn_radiation.polarizn_source_ratio' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 -1.0 -1.0 -1.0 _item_type.code float save_ save__diffrn_radiation.probe _item_description.description ; Name of the type of radiation used. It is strongly encouraged that this field be specified so that the probe radiation can be simply determined. ; _item.name '_diffrn_radiation.probe' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_probe' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value 'x-ray' 'neutron' 'electron' 'gamma' save_ save__diffrn_radiation.type _item_description.description ; The nature of the radiation. This is typically a description of the X-ray wavelength in Siegbahn notation. ; _item.name '_diffrn_radiation.type' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'CuK\a' 'Cu K\a~1~' 'Cu K-L~2,3~' 'white-beam' save_ save__diffrn_radiation.xray_symbol _item_description.description ; The IUPAC symbol for the X-ray wavelength for probe radiation. ; _item.name '_diffrn_radiation.xray_symbol' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_xray_symbol' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value _item_enumeration.detail 'K-L~3~' 'K\a~1~ in older Siegbahn notation' 'K-L~2~' 'K\a~2~ in older Siegbahn notation' 'K-M~3~' 'K\b~1~ in older Siegbahn notation' 'K-L~2,3~' 'use where K-L~3~ and K-L~2~ are not resolved' save_ save__diffrn_radiation.wavelength_id _item_description.description ; This data item is a pointer to _diffrn_radiation_wavelength.id in the DIFFRN_RADIATION_WAVELENGTH category. ; _item.name '_diffrn_radiation.wavelength_id' _item.mandatory_code yes save_ ################ # DIFFRN_REFLN # ################ save_DIFFRN_REFLN _category.description ; This category redefinition has been added to extend the key of the standard DIFFRN_REFLN category. ; _category.id diffrn_refln _category.mandatory_code no _category_key.name '_diffrn_refln.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_refln.frame_id _item_description.description ; This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_refln.frame_id' _item.category_id diffrn_refln _item.mandatory_code yes _item_type.code code save_ ############### # DIFFRN_SCAN # ############### save_DIFFRN_SCAN _category.description ; Data items in the DIFFRN_SCAN category describe the parameters of one or more scans, relating axis positions to frames. ; _category.id diffrn_scan _category.mandatory_code no _category_key.name '_diffrn_scan.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - derived from a suggestion by R. M. Sweet. The vector of each axis is not given here, because it is provided in the AXIS category. By making _diffrn_scan_axis.scan_id and _diffrn_scan_axis.axis_id keys of the DIFFRN_SCAN_AXIS category, an arbitrary number of scanning and fixed axes can be specified for a scan. We have specified three rotation axes and one translation axis at non-zero values, with one axis stepping. There is no reason why more axes could not have been specified to step. We have specified range information, but note that it is redundant from the number of frames and the increment, so we could drop the data item _diffrn_scan_axis.angle_range . We have specified both the sweep data and the data for a single frame. Note that the information on how the axes are stepped is given twice, once in terms of the overall averages in the value of '_diffrn_scan.integration_time' and the values for DIFFRN_SCAN_AXIS, and precisely for the given frame in the value for '_diffrn_scan_frame.integration_time' and the values for DIFFRN_SCAN_FRAME_AXIS. If dose-related adjustements are made to scan times and non-linear stepping is done, these values may differ. Therefore, in interpreting the data for a particular frame it is important to use the frame-specific data. ; ; _diffrn_scan.id 1 _diffrn_scan.date_start '2001-11-18T03:26:42' _diffrn_scan.date_end '2001-11-18T03:36:45' _diffrn_scan.integration_time 3.0 _diffrn_scan.frame_id_start mad_L2_000 _diffrn_scan.frame_id_end mad_L2_200 _diffrn_scan.frames 201 loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment 1 omega 200.0 20.0 0.1 . . . 1 kappa -40.0 0.0 0.0 . . . 1 phi 127.5 0.0 0.0 . . . 1 tranz . . . 2.3 0.0 0.0 _diffrn_scan_frame.scan_id 1 _diffrn_scan_frame.date '2001-11-18T03:27:33' _diffrn_scan_frame.integration_time 3.0 _diffrn_scan_frame.frame_id mad_L2_018 _diffrn_scan_frame.frame_number 18 loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.angle_increment _diffrn_scan_frame_axis.displacement _diffrn_scan_frame_axis.displacement_increment mad_L2_018 omega 201.8 0.1 . . mad_L2_018 kappa -40.0 0.0 . . mad_L2_018 phi 127.5 0.0 . . mad_L2_018 tranz . . 2.3 0.0 ; ; Example 2 - a more extensive example, R. M. Sweet, P. Ellis, H. Bernstein. We place a detector 240 mm along the Z axis from the goniometer. This presents us with a choice -- either we define the axes of the detector at the origin, and then put a Z setting of -240 in for the actual use, or we define the axes with the necessary Z-offset. In this case we use the setting, and leave the offset as zero. We call this axis DETECTOR_Z. The axis for positioning the detector in the Y-direction depends on the detector Z-axis. We call this axis, DETECTOR_Y. The axis for positioning the dector in the X-direction depends on the detector Y-axis (and therefore on the detector Z-axis). We call this axis DETECTOR_X. This detector may be rotated around the Y-axis. This rotation axis depends on the three translation axies. We call it DETECTOR_PITCH. We define a coordinate system on the face of the detector in terms of 2300 0.150 mm pixels in each direction. The ELEMENT_X axis is used to index the first array index of the data array and the ELEMENT_Y axis is used to index the second array index. Because the pixels are 0.150mm x 0.150mm, the center of the first pixel is at (0.075, 0.075) in this coordinate system. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 172.43 -172.43 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 2300 1 increasing ELEMENT_X ARRAY1 2 2300 2 increasing ELEMENT_Y # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.075 0.150 ELEMENT_Y ELEMENT_Y 0.075 0.150 # category ARRAY_ELEMENT_SIZE loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 ARRAY1 2 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; ; Example 3 - Example 2 revised for a spiral scan, R. M. Sweet, P. Ellis, H. Bernstein. We place a detector 240 mm along the Z axis from the goniometer, as in Example 2, above, but in this example, the image plate is scanned in a spiral pattern outside edge in. The axis for positioning the detector in the Y-direction depends on the detector Z-axis. We call this axis, DETECTOR_Y. The axis for positioning the dector in the X-direction depends on the detector Y-axis (and therefore on the detector Z-axis). We call this axis DETECTOR_X. This detector may be rotated around the Y-axis. This rotation axis depends on the three translation axies. We call it DETECTOR_PITCH. We define a coordinate system on the face of the detector in terms of a coupled rotation axis and radial scan axis to form a spiral scan. Let us call rotation axis ELEMENT_ROT, and the radial axis ELEMENT_RAD. We assume 150 um radial pitch and 75 um 'constant velocity' angular pitch. We index first on the rotation axis and make the radial axis dependent on it. The two axes are coupled to form an axis set ELEMENT_SPIRAL. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_ROT translation detector DETECTOR_PITCH 0 0 1 0 0 0 ELEMENT_RAD translation detector ELEMENT_ROT 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.angle _array_structure_list_axis.displacement _array_structure_list_axis.angular_pitch _array_structure_list_axis.radial_pitch ELEMENT_SPIRAL ELEMENT_ROT 0 . 0.075 . ELEMENT_SPIRAL ELEMENT_RAD . 172.5 . -0.150 # category ARRAY_ELEMENT_SIZE # the actual pixels are 0.075 by 0.150 mm # We give the coarser dimension here. loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_scan.id _item_description.description ; The value of _diffrn_scan.id uniquely identifies each scan. The identifier is used to tie together all the information about the scan. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_scan.id' diffrn_scan yes '_diffrn_scan_axis.scan_id' diffrn_scan_axis yes '_diffrn_scan_frame.scan_id' diffrn_scan_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_scan_axis.scan_id' '_diffrn_scan.id' '_diffrn_scan_frame.scan_id' '_diffrn_scan.id' save_ save__diffrn_scan.date_end _item_description.description ; The date and time of the end of the scan. Note that this may be an estimate generated during the scan, before the precise time of the end of the scan is known. ; _item.name '_diffrn_scan.date_end' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.date_start _item_description.description ; The date and time of the start of the scan. ; _item.name '_diffrn_scan.date_start' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.integration_time _item_description.description ; Approximate average time in seconds to integrate each step of the scan. The precise time for integration of each particular step must be provided in '_diffrn_scan_frame.integration_time', even if all steps have the same integration time. ; _item.name '_diffrn_scan.integration_time' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan.frame_id_start _item_description.description ; The value of this data item is the identifier of the first frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_start' _item.category_id diffrn_scan _item.mandatory_code yes save_ save__diffrn_scan.frame_id_end _item_description.description ; The value of this data item is the identifier of the last frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_end' _item.category_id diffrn_scan _item.mandatory_code yes save_ save__diffrn_scan.frames _item_description.description ; The value of this data item is the number of frames in the scan. ; _item.name '_diffrn_scan.frames' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 1 1 1 save_ #################### # DIFFRN_SCAN_AXIS # #################### save_DIFFRN_SCAN_AXIS _category.description ; Data items in the DIFFRN_SCAN_AXIS category describe the settings of axes for particular scans. Unspecified axes are assumed to be at their zero points. ; _category.id diffrn_scan_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_axis.scan_id' '_diffrn_scan_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_axis.scan_id _item_description.description ; The value of this data item is the identifier of the scan for which axis settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan.id'. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_axis.scan_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes save_ save__diffrn_scan_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the scan for which settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan.id'. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_axis.axis_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes save_ save__diffrn_scan_axis.angle_start _item_description.description ; The starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_range _item_description.description ; The range from the starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_increment _item_description.description ; The increment for each step for the specified axis in degrees. In general, this will agree with '_diffrn_scan_frame_axis.angle_increment', which see for a precise description. ; _item.name '_diffrn_scan_axis.angle_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_rstrt_incr _item_description.description ; The increment after each step for the specified axis in degrees. In general, this will agree with '_diffrn_scan_frame_axis.angle_rstrt_incr', which see for a precise description. ; _item.name '_diffrn_scan_axis.angle_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.displacement_start _item_description.description ; The starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_range _item_description.description ; The range from the starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_increment _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with '_diffrn_scan_frame_axis.displacement_increment', which see for a precise description. ; _item.name '_diffrn_scan_axis.displacement_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_rstrt_incr _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with '_diffrn_scan_frame_axis.displacement_rstrt_incr', which see for a precise description. ; _item.name '_diffrn_scan_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ ##################### # DIFFRN_SCAN_FRAME # ##################### save_DIFFRN_SCAN_FRAME _category.description ; Data items in the DIFFRN_SCAN_FRAME category describe the relationship of particular frames to scans. ; _category.id diffrn_scan_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame.scan_id' '_diffrn_scan_frame.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame.date _item_description.description ; The date and time of the start of the frame being scanned. ; _item.name '_diffrn_scan_frame.date' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan_frame.frame_id _item_description.description ; The value of this data item is the identifier of the frame being examined. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame.frame_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes save_ save__diffrn_scan_frame.frame_number _item_description.description ; The value of this data item is the number of the frame within the scan, starting with 1. It is not necessarily the same as the value of _diffrn_scan_frame.frame_id, but may be. ; _item.name '_diffrn_scan_frame.frame_number' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 0 0 0 save_ save__diffrn_scan_frame.integration_time _item_description.description ; The time in seconds to integrate this step of the scan. This should be the precise time of integration of each particular frame. The value of this data item should be given explicitly for each frame and not inferred from the value of '_diffrn_scan.integration_time'. ; _item.name '_diffrn_scan_frame.integration_time' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame.scan_id _item_description.description ; The value of _diffrn_scan_frame.scan_id identifies the scan containing this frame. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_frame.scan_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes save_ ########################## # DIFFRN_SCAN_FRAME_AXIS # ########################## save_DIFFRN_SCAN_FRAME_AXIS _category.description ; Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the settings of axes for particular frames. Unspecified axes are assumed to be at their zero points. If, for any given frame, non-zero values apply for any of the data items in this category, those values should be given explicitly in this category and not simply inferred from values in DIFFRN_SCAN_AXIS. ; _category.id diffrn_scan_frame_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame_axis.frame_id' '_diffrn_scan_frame_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the frame for which settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_frame_axis.axis_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes save_ save__diffrn_scan_frame_axis.angle _item_description.description ; The setting of the specified axis in degrees for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.angle' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_increment _item_description.description ; The increment for this frame for angular setting of the specified axis in degrees. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.angle_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_rstrt_incr _item_description.description ; The increment after this frame for angular setting of the specified axis in degrees. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' and '_diffrn_scan_frame_axis.angle_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame, and should equal '_diffrn_scan_frame_axis.angle' for that next frame. ; _item.name '_diffrn_scan_frame_axis.angle_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.displacement' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_increment _item_description.description ; The increment for this frame for displacement setting of the specified axis in millimetres. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.displacement_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_rstrt_incr _item_description.description ; The increment for this frame for displacement setting of the specified axis in millimetres. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' and '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame, and should equal '_diffrn_scan_frame_axis.displacement' for that next frame. ; _item.name '_diffrn_scan_frame_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.frame_id _item_description.description ; The value of this data item is the identifier of the frame for which axis settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id . This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame_axis.frame_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes save_ #################### ## ITEM_TYPE_LIST ## #################### # # # The regular expressions defined here are not compliant # with the POSIX 1003.2 standard as they include the # '\n' and '\t' special characters. These regular expressions # have been tested using version 0.12 of Richard Stallman's # GNU regular expression library in POSIX mode. # In order to allow presentation of a regular expression # in a text field concatenate any line ending in a backslash # with the following line, after discarding the backslash. # # A formal definition of the '\n' and '\t' special characters # is most properly done in the DDL, but for completeness, please # note that '\n' is the line termination character ('newline') # and '\t' is the horizontal tab character. There is a formal # ambiguity in the use of '\n' for line termination, in that # the intention is that the equivalent machine/OS-dependent line # termination character sequence should be accepted as a match, e.g. # # '\r' (control-M) under MacOS # '\n' (control-J) under Unix # '\r\n' (control-M control-J) under DOS and MS Windows # loop_ _item_type_list.code _item_type_list.primitive_code _item_type_list.construct _item_type_list.detail code char '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words ... ; ucode uchar '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words (case insensitive) ; line char '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types / multi-word items ... ; uline uchar '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types / multi-word items (case insensitive) ; text char '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; text item types / multi-line text ... ; binary char ;\n--CIF-BINARY-FORMAT-SECTION--\n\ [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\ \n--CIF-BINARY-FORMAT-SECTION---- ; ; binary items are presented as MIME-like ascii-encoded sections in an imgCIF. In a CBF, raw octet streams are used to convey the same information. ; int numb '-?[0-9]+' ; int item types are the subset of numbers that are the negative or positive integers. ; float numb '-?(([0-9]+)|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?' ; float item types are the subset of numbers that are the floating numbers. ; any char '.*' ; A catch all for items that may take any form... ; yyyy-mm-dd char ;\ [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9][0-9]\ (T[0-2][0-9]:[0-5][0-9]:[0-5][0-9](.[0-9]+)([+-][0-5][0-9]:[0-5][0-9])) ; ; Standard format for CIF date and time strings (see http://www.iucr.orgiucr-top/cif/spec/datetime.html), consisting of a yyyy-mm-dd date optionally followed by the character "T" followed by a 24-hour clock time, optionally followed by a signed time-zone offset. The IUCr standard has been extended to allow for an optional decimal fraction on the seconds of time. Time is local time if no time-zone offset is given. ; ##################### ## ITEM_UNITS_LIST ## ##################### loop_ _item_units_list.code _item_units_list.detail # 'metres' 'metres' 'centimetres' 'centimetres (metres * 10^( -2))' 'millimetres' 'millimetres (metres * 10^( -3))' 'nanometres' 'nanometres (metres * 10^( -9))' 'angstroms' 'angstroms (metres * 10^(-10))' 'picometres' 'picometres (metres * 10^(-12))' 'femtometres' 'femtometres (metres * 10^(-15))' # 'reciprocal_metres' 'reciprocal metres (metres^(-1))' 'reciprocal_centimetres' 'reciprocal centimetres ((metres * 10^( -2))^(-1))' 'reciprocal_millimetres' 'reciprocal millimetres ((metres * 10^( -3))^(-1))' 'reciprocal_nanometres' 'reciprocal nanometres ((metres * 10^( -9))^(-1))' 'reciprocal_angstroms' 'reciprocal angstroms ((metres * 10^(-10))^(-1))' 'reciprocal_picometres' 'reciprocal picometres ((metres * 10^(-12))^(-1))' # 'nanometres_squared' 'nanometres squared (metres * 10^( -9))^2' 'angstroms_squared' 'angstroms squared (metres * 10^(-10))^2' '8pi2_angstroms_squared' '8pi^2 * angstroms squared (metres * 10^(-10))^2' 'picometres_squared' 'picometres squared (metres * 10^(-12))^2' # 'nanometres_cubed' 'nanometres cubed (metres * 10^( -9))^3' 'angstroms_cubed' 'angstroms cubed (metres * 10^(-10))^3' 'picometres_cubed' 'picometres cubed (metres * 10^(-12))^3' # 'kilopascals' 'kilopascals' 'gigapascals' 'gigapascals' # 'hours' 'hours' 'minutes' 'minutes' 'seconds' 'seconds' 'microseconds' 'microseconds' # 'degrees' 'degrees (of arc)' 'degrees_squared' 'degrees (of arc) squared' # 'degrees_per_minute' 'degrees (of arc) per minute' # 'celsius' 'degrees (of temperature) Celsius' 'kelvins' 'degrees (of temperature) Kelvin' # 'counts' 'counts' 'counts_per_photon' 'counts per photon' # 'electrons' 'electrons' # 'electrons_squared' 'electrons squared' # 'electrons_per_nanometres_cubed' ; electrons per nanometres cubed (electrons/(metres * 10^( -9))^(-3)) ; 'electrons_per_angstroms_cubed' ; electrons per angstroms cubed (electrons/(metres * 10^(-10))^(-3)) ; 'electrons_per_picometres_cubed' ; electrons per picometres cubed (electrons/(metres * 10^(-12))^(-3)) ; 'kilowatts' 'kilowatts' 'milliamperes' 'milliamperes' 'kilovolts' 'kilovolts' # 'arbitrary' ; arbitrary system of units. ; # loop_ _item_units_conversion.from_code _item_units_conversion.to_code _item_units_conversion.operator _item_units_conversion.factor ### 'metres' 'centimetres' '*' 1.0E+02 'metres' 'millimetres' '*' 1.0E+03 'metres' 'nanometres' '*' 1.0E+09 'metres' 'angstroms' '*' 1.0E+10 'metres' 'picometres' '*' 1.0E+12 'metres' 'femtometres' '*' 1.0E+15 # 'centimetres' 'metres' '*' 1.0E-02 'centimetres' 'millimetres' '*' 1.0E+01 'centimetres' 'nanometres' '*' 1.0E+07 'centimetres' 'angstroms' '*' 1.0E+08 'centimetres' 'picometres' '*' 1.0E+10 'centimetres' 'femtometres' '*' 1.0E+13 # 'millimetres' 'metres' '*' 1.0E-03 'millimetres' 'centimetres' '*' 1.0E-01 'millimetres' 'nanometres' '*' 1.0E+06 'millimetres' 'angstroms' '*' 1.0E+07 'millimetres' 'picometres' '*' 1.0E+09 'millimetres' 'femtometres' '*' 1.0E+12 # 'nanometres' 'metres' '*' 1.0E-09 'nanometres' 'centimetres' '*' 1.0E-07 'nanometres' 'millimetres' '*' 1.0E-06 'nanometres' 'angstroms' '*' 1.0E+01 'nanometres' 'picometres' '*' 1.0E+03 'nanometres' 'femtometres' '*' 1.0E+06 # 'angstroms' 'metres' '*' 1.0E-10 'angstroms' 'centimetres' '*' 1.0E-08 'angstroms' 'millimetres' '*' 1.0E-07 'angstroms' 'nanometres' '*' 1.0E-01 'angstroms' 'picometres' '*' 1.0E+02 'angstroms' 'femtometres' '*' 1.0E+05 # 'picometres' 'metres' '*' 1.0E-12 'picometres' 'centimetres' '*' 1.0E-10 'picometres' 'millimetres' '*' 1.0E-09 'picometres' 'nanometres' '*' 1.0E-03 'picometres' 'angstroms' '*' 1.0E-02 'picometres' 'femtometres' '*' 1.0E+03 # 'femtometres' 'metres' '*' 1.0E-15 'femtometres' 'centimetres' '*' 1.0E-13 'femtometres' 'millimetres' '*' 1.0E-12 'femtometres' 'nanometres' '*' 1.0E-06 'femtometres' 'angstroms' '*' 1.0E-05 'femtometres' 'picometres' '*' 1.0E-03 ### 'reciprocal_centimetres' 'reciprocal_metres' '*' 1.0E+02 'reciprocal_centimetres' 'reciprocal_millimetres' '*' 1.0E-01 'reciprocal_centimetres' 'reciprocal_nanometres' '*' 1.0E-07 'reciprocal_centimetres' 'reciprocal_angstroms' '*' 1.0E-08 'reciprocal_centimetres' 'reciprocal_picometres' '*' 1.0E-10 # 'reciprocal_millimetres' 'reciprocal_metres' '*' 1.0E+03 'reciprocal_millimetres' 'reciprocal_centimetres' '*' 1.0E+01 'reciprocal_millimetres' 'reciprocal_nanometres' '*' 1.0E-06 'reciprocal_millimetres' 'reciprocal_angstroms' '*' 1.0E-07 'reciprocal_millimetres' 'reciprocal_picometres' '*' 1.0E-09 # 'reciprocal_nanometres' 'reciprocal_metres' '*' 1.0E+09 'reciprocal_nanometres' 'reciprocal_centimetres' '*' 1.0E+07 'reciprocal_nanometres' 'reciprocal_millimetres' '*' 1.0E+06 'reciprocal_nanometres' 'reciprocal_angstroms' '*' 1.0E-01 'reciprocal_nanometres' 'reciprocal_picometres' '*' 1.0E-03 # 'reciprocal_angstroms' 'reciprocal_metres' '*' 1.0E+10 'reciprocal_angstroms' 'reciprocal_centimetres' '*' 1.0E+08 'reciprocal_angstroms' 'reciprocal_millimetres' '*' 1.0E+07 'reciprocal_angstroms' 'reciprocal_nanometres' '*' 1.0E+01 'reciprocal_angstroms' 'reciprocal_picometres' '*' 1.0E-02 # 'reciprocal_picometres' 'reciprocal_metres' '*' 1.0E+12 'reciprocal_picometres' 'reciprocal_centimetres' '*' 1.0E+10 'reciprocal_picometres' 'reciprocal_millimetres' '*' 1.0E+09 'reciprocal_picometres' 'reciprocal_nanometres' '*' 1.0E+03 'reciprocal_picometres' 'reciprocal_angstroms' '*' 1.0E+01 ### 'nanometres_squared' 'angstroms_squared' '*' 1.0E+02 'nanometres_squared' 'picometres_squared' '*' 1.0E+06 # 'angstroms_squared' 'nanometres_squared' '*' 1.0E-02 'angstroms_squared' 'picometres_squared' '*' 1.0E+04 'angstroms_squared' '8pi2_angstroms_squared' '*' 78.9568 # 'picometres_squared' 'nanometres_squared' '*' 1.0E-06 'picometres_squared' 'angstroms_squared' '*' 1.0E-04 ### 'nanometres_cubed' 'angstroms_cubed' '*' 1.0E+03 'nanometres_cubed' 'picometres_cubed' '*' 1.0E+09 # 'angstroms_cubed' 'nanometres_cubed' '*' 1.0E-03 'angstroms_cubed' 'picometres_cubed' '*' 1.0E+06 # 'picometres_cubed' 'nanometres_cubed' '*' 1.0E-09 'picometres_cubed' 'angstroms_cubed' '*' 1.0E-06 ### 'kilopascals' 'gigapascals' '*' 1.0E-06 'gigapascals' 'kilopascals' '*' 1.0E+06 ### 'hours' 'minutes' '*' 6.0E+01 'hours' 'seconds' '*' 3.6E+03 'hours' 'microseconds' '*' 3.6E+09 # 'minutes' 'hours' '/' 6.0E+01 'minutes' 'seconds' '*' 6.0E+01 'minutes' 'microseconds' '*' 6.0E+07 # 'seconds' 'hours' '/' 3.6E+03 'seconds' 'minutes' '/' 6.0E+01 'seconds' 'microseconds' '*' 1.0E+06 # 'microseconds' 'hours' '/' 3.6E+09 'microseconds' 'minutes' '/' 6.0E+07 'microseconds' 'seconds' '/' 1.0E+06 ### 'celsius' 'kelvins' '-' 273.0 'kelvins' 'celsius' '+' 273.0 ### 'electrons_per_nanometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E+03 'electrons_per_nanometres_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+09 # 'electrons_per_angstroms_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-03 'electrons_per_angstroms_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+06 # 'electrons_per_picometres_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-09 'electrons_per_picometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E-06 ### ######################## ## DICTIONARY_HISTORY ## ######################## loop_ _dictionary_history.version _dictionary_history.update _dictionary_history.revision 1.2.3 2003-07-03 ; Cleanup to conform to ITVG. + Correct sign error in ..._cubed units. + Correct '_diffrn_radiation.polarisn_norm' range. (HJB) ; 1.2.2 2003-03-10 ; Correction of typos in various DIFFRN_SCAN_AXIS descriptions. (HJB) ; 1.2.1 2003-02-22 ; Correction of ATOM_ for ARRAY_ typos in various descriptions. (HJB) ; 1.2 2003-02-07 ; Corrections to encodings (remove extraneous hyphens) remove extraneous underscore in _array_structure.encoding_type enumeration. Correct typos in items units list. (HJB) ; 1.1.3 2001-04-19 ; Another typo corrections by Wilfred Li, and cleanup by HJB ; 1.1.2 2001-03-06 ; Several typo corrections by Wilfred Li ; 1.1.1 2001-02-16 ; Several typo corrections by JW ; 1.1 2001-02-06 ; Draft resulting from discussions on header for use at NSLS (HJB) + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'. + Add '_diffrn_measurement_axis.measurement_device' and change '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'. + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source', '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm' , '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end', '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr', '_diffrn_scan_axis.displacement_rstrt_incr', '_diffrn_scan_frame_axis.angle_increment', '_diffrn_scan_frame_axis.angle_rstrt_incr', '_diffrn_scan_frame_axis.displacement', '_diffrn_scan_frame_axis.displacement_increment',and '_diffrn_scan_frame_axis.displacement_rstrt_incr'. + Add _diffrn_measurement.device to category key + Update yyyy-mm-dd to allow optional time with fractional seconds for time stamps. + Fix typos caught by RS. + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to al low for coupled axes, as in spiral scans. + Add examples for fairly complete headers thanks to R. Sweet and P. Ellis. ; 1.0 2000-12-21 ; Release version - few typos and tidying up (BM & HJB) + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end of dictionary. + Alphabetize dictionary. ; 0.7.1 2000-09-29 ; Cleanup fixes (JW) + Correct spelling of diffrn_measurement_axis in _axis.id + Correct ordering of uses of _item.mandatory_code and _item_default.value ; 0.7.0 2000-09-09 ; Respond to comments by I. David Brown (HJB) + Added further comments on '\n' and '\t' + Updated ITEM_UNITS_LIST by taking section from mmCIF dictionary and adding metres. Changed all spelling 'meter' to 'metre' throughout. + Added missing enumerations to _array_structure.compression_type and made 'none' the default. + Removed parent-child relationship between _array_structure_list.index and _array_structure_list.precedence . + Improve alphabetization. + Fix _array_intensities_gain.esd related function. + Improved comments in AXIS. + Fixed DIFFRN_FRAME_DATA example. + Removed erroneous DIFFRN_MEASUREMENT example. + Added _diffrn_measurement_axis.id to the category key. ; 0.6.0 1999-01-14 ; Remove redundant information for ENC_NONE data (HJB) + After the D5 remove binary section identifier, size and compression type. + Add Control-L to header. ; 0.5.1 1999-01-03 ; Cleanup of typos and syntax errors (HJB) + Cleanup example details for DIFFRN_SCAN category. + Add missing quote marks for _diffrn_scan.id definition. ; 0.5 1999-01-01 ; Modifications for axis definitions and reduction of binary header (HJB) + Restored _diffrn_detector.diffrn_id to DIFFRN_DETECTOR KEY. + Added AXIS category. + Brought complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories in from cif_mm.dic for clarity. + changed _array_structure.encoding_type from type code to uline and added X-Binary-Element-Type to MIME header. + added detector beam center _diffrn_detector_element.center[1] and _diffrn_detector_element.center[2] + corrected item name of _diffrn_refln.frame_id + replace reference to _array_intensities.undefined by _array_intensities.undefined_value + replace references to _array_intensity.scaling with _array_intensities.scaling + added DIFFRN_SCAN... categories ; 0.4 1998-08-11 ; Modifications to the 0.3 imgCIF draft (HJB) + Reflowed comment lines over 80 characters and corrected typos. + Updated examples and descriptions of MIME encoded data. + Change name to cbfext98.dic. ; 0.3 1998-07-04 ; Modifications for imgCIF (HJB) + Added binary type, which is a text field containing a variant on MIME encoded data. + Changed type of _array_data.data to binary and specified internal structure of raw binary data. + Added _array_data.binary_id, and made _diffrn_frame_data.binary_id and _array_intensities.binary_id into pointers to this item. ; 0.2 1997-12-02 ; Modifications to the CBF draft (JW): + Added category hierarchy for describing frame data developed from discussions at the BNL imgCIF Workshop Oct 1997. The following changes were made in implementing the workshop draft. Category DIFFRN_ARRAY_DATA was renamed to DIFFRN_FRAME_DATA. Category DIFFRN_FRAME_TYPE was renamed to DIFFRN_DETECTOR_ELEMENT. The parent item for _diffrn_frame_data.array_id was changed from array_structure_list.array_id to array_structure.id. Item _diffrn_detector.array_id was deleted. + Added data item _diffrn_frame_data.binary_id to identify data groups within a binary section. The formal identification of the binary section is still fuzzy. ; 0.1 1997-01-24 ; First draft of this dictionary in DDL 2.1 compliant format by John Westbrook (JW). This version was adapted from the Crystallographic Binary File (CBF) Format Draft Proposal provided by Andy Hammersley (AH). Modifications to the CBF draft (JW): + In this version the array description has been cast in the categories ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. These categories have been generalized to describe array data of arbitrary dimension. + Array data in this description are contained in the category ARRAY_DATA . This departs from the CBF notion of data existing in some special comment. In this description, data is handled as an ordinary data item encapsulated in a character data type. Although handling binary data this manner deviates from CIF conventions, it does not violate any DDL 2.1 rules. DDL 2.1 regular expressions can be used to define the binary representation which will permit some level of data validation. In this version, the placeholder type code "any" has been used. This translates to a regular expression which will match any pattern. It should be noted that DDL 2.1 already supports array data objects although these have not been used in the current mmCIF dictionary. It may be possible to use the DDL 2.1 ITEM_STRUCTURE and ITEM_STRUCTURE_LIST categories to provide the information that is carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. By moving the array structure to the DDL level it would be possible to define an array type as well as a regular expression defining the data format. + Multiple array sections can be properly handled within a single datablock. ; #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof ./CBFlib-0.9.2.2/doc/cif_img_1_2_4.dic0000644000076500007650000053431511603702115015320 0ustar yayayaya ############################################################################## # # # Image CIF Dictionary (imgCIF) # # and Crystallographic Binary File Dictionary (CBF) # # Extending the Macromolecular CIF Dictionary (mmCIF) # # # # Version 1.2.4 # # of 2003-07-14 # # # # by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook # # # # This dictionary was adapted from the imgCIF Workshop, held at BNL Oct 1997# # and the Crystallographic Binary File Format Draft Proposal by Andy # # Hammersley. The first DDL 2.1 Version was created by John Westbrook. # # This version was drafted by Herbert J. Bernstein and incorporates comments # # by I. David Brown, John Westbrook, Brian McMahon, Bob Sweet, Paul Ellis, # # Harry Powell, Wilfred Li and others. # ############################################################################## data_cif_img.dic _dictionary.title cif_img.dic _dictionary.version 1.2.4 _dictionary.datablock_id cif_img.dic ############################################################################## # CONTENTS # # CATEGORY_GROUP_LIST # # category ARRAY_DATA # # _array_data.array_id # _array_data.binary_id # _array_data.data # # category ARRAY_ELEMENT_SIZE # # _array_element_size.array_id # _array_element_size.index # _array_element_size.size # # category ARRAY_INTENSITIES # # _array_intensities.array_id # _array_intensities.binary_id # _array_intensities.gain # _array_intensities.gain_esd # _array_intensities.linearity # _array_intensities.offset # _array_intensities.scaling # _array_intensities.overload # _array_intensities.undefined_value # # category ARRAY_STRUCTURE # # _array_structure.byte_order # _array_structure.compression_type # _array_structure.encoding_type # _array_structure.id # # category ARRAY_STRUCTURE_LIST # # _array_structure_list.axis_set_id # _array_structure_list.array_id # _array_structure_list.dimension # _array_structure_list.direction # _array_structure_list.index # _array_structure_list.precedence # # category ARRAY_STRUCTURE_LIST_AXIS # # _array_structure_list_axis.axis_id # _array_structure_list_axis.axis_set_id # _array_structure_list_axis.angle # _array_structure_list_axis.angle_increment # _array_structure_list_axis.displacement_increment # _array_structure_list_axis.angular_pitch # _array_structure_list_axis.radial_pitch # # category AXIS # # _axis.depends_on # _axis.equipment # _axis.id # _axis.offset[1] # _axis.offset[2] # _axis.offset[3] # _axis.type # _axis.vector[1] # _axis.vector[2] # _axis.vector[3] # # category DIFFRN_DATA_FRAME # # _diffrn_data_frame.array_id # _diffrn_data_frame.binary_id # _diffrn_data_frame.detector_element_id # _diffrn_data_frame.id # # category DIFFRN_DETECTOR # # _diffrn_detector.details # _diffrn_detector.detector # _diffrn_detector.diffrn_id # _diffrn_detector.dtime # _diffrn_detector.id # _diffrn_detector.number_of_axes # _diffrn_detector.type # # category DIFFRN_DETECTOR_AXIS # # _diffrn_detector_axis.axis_id # _diffrn_detector_axis.detector_id # # category DIFFRN_DETECTOR_ELEMENT # # _diffrn_detector_element.center[1] # _diffrn_detector_element.center[2] # _diffrn_detector_element.id # _diffrn_detector_element.detector_id # # category DIFFRN_MEASUREMENT # # _diffrn_measurement.diffrn_id # _diffrn_measurement.details # _diffrn_measurement.device # _diffrn_measurement.device_details # _diffrn_measurement.device_type # _diffrn_measurement.id # _diffrn_measurement.method # _diffrn_measurement.number_of_axes # _diffrn_measurement.specimen_support # # category DIFFRN_MEASUREMENT_AXIS # # _diffrn_measurement_axis.axis_id # _diffrn_measurement_axis.measurement_device # _diffrn_measurement_axis.measurement_id # # category DIFFRN_RADIATION # # _diffrn_radiation.collimation # _diffrn_radiation.diffrn_id # _diffrn_radiation.div_x_source # _diffrn_radiation.div_y_source # _diffrn_radiation.div_x_y_source # _diffrn_radiation.filter_edge' # _diffrn_radiation.inhomogeneity # _diffrn_radiation.monochromator # _diffrn_radiation.polarisn_norm # _diffrn_radiation.polarisn_ratio # _diffrn_radiation.polarizn_source_norm # _diffrn_radiation.polarizn_source_ratio # _diffrn_radiation.probe # _diffrn_radiation.type # _diffrn_radiation.xray_symbol # _diffrn_radiation.wavelength_id # # category DIFFRN_REFLN # # _diffrn_refln.frame_id # # category DIFFRN_SCAN # # _diffrn_scan.id # _diffrn_scan.date_end # _diffrn_scan.date_start # _diffrn_scan.integration_time # _diffrn_scan.frame_id_start # _diffrn_scan.frame_id_end # _diffrn_scan.frames # # category DIFFRN_SCAN_AXIS # # _diffrn_scan_axis.axis_id # _diffrn_scan_axis.angle_start # _diffrn_scan_axis.angle_range # _diffrn_scan_axis.angle_increment # _diffrn_scan_axis.angle_rstrt_incr # _diffrn_scan_axis.displacement_start # _diffrn_scan_axis.displacement_range # _diffrn_scan_axis.displacement_increment # _diffrn_scan_axis.displacement_rstrt_incr # _diffrn_scan_axis.scan_id # # category DIFFRN_SCAN_FRAME # # _diffrn_scan_frame.date # _diffrn_scan_frame.frame_id # _diffrn_scan_frame.frame_number # _diffrn_scan_frame.integration_time # _diffrn_scan_frame.scan_id # # category DIFFRN_SCAN_FRAME_AXIS # # _diffrn_scan_frame_axis.axis_id # _diffrn_scan_frame_axis.angle # _diffrn_scan_frame_axis.angle_increment # _diffrn_scan_frame_axis.angle_rstrt_incr # _diffrn_scan_frame_axis.displacement # _diffrn_scan_frame_axis.displacement_increment # _diffrn_scan_frame_axis.displacement_rstrt_incr # _diffrn_scan_frame_axis.frame_id # # ***DEPRECATED*** category DIFFRN_FRAME_DATA # # _diffrn_frame_data.array_id # _diffrn_frame_data.binary_id # _diffrn_frame_data.detector_element_id # _diffrn_frame_data.id # # # ITEM_TYPE_LIST # ITEM_UNITS_LIST # DICTIONARY_HISTORY # ############################################################################## ######################### ## CATEGORY_GROUP_LIST ## ######################### loop_ _category_group_list.id _category_group_list.parent_id _category_group_list.description 'inclusive_group' . ; Categories that belong to the dictionary extension. ; 'array_data_group' 'inclusive_group' ; Categories that describe array data. ; 'axis_group' 'inclusive_group' ; Categories that describe axes. ; 'diffrn_group' 'inclusive_group' ; Categories that describe details of the diffraction experiment. ; ############## # ARRAY_DATA # ############## save_ARRAY_DATA _category.description ; Data items in the ARRAY_DATA category are the containers for the array data items described in category ARRAY_STRUCTURE. ; _category.id array_data _category.mandatory_code no loop_ _category_key.name '_array_data.array_id' '_array_data.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows two binary data blocks. The first one was compressed by the CBF_CANONICAL compression algorithm and presented as hexadecimal data. The first character "H" on the data lines means hexadecimal. It could have been "O" for octal or "D" for decimal. The second character on the line shows the number of bytes in each word (in this case "4"), which then requires 8 hexadecimal digits per word. The third character gives the order of octets within a word, in this case "<" for the ordering 4321 (i.e. "big-endian"). Alternatively the character ">" could have been used for the ordering 1234 (i.e. "little-endian"). The block has a "message digest" to check the integrity of the data. The second block is similar, but uses CBF_PACKED compression and BASE64 encoding. Note that the size and the digest are different. ; ; loop_ _array_data.array_id _array_data.binary_id _array_data.data image_1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_CANONICAL" Content-Transfer-Encoding: X-BASE16 X-Binary-Size: 3927126 X-Binary-ID: 1 Content-MD5: u2sTJEovAHkmkDjPi+gWsg== # Hexadecimal encoding, byte 0, byte order ...21 # H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ... .... --CIF-BINARY-FORMAT-SECTION---- ; image_2 2 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF-PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3745758 X-Binary-ID: 1 Content-MD5: 1zsJjWPfol2GYl2V+QSXrw== ELhQAAAAAAAA... ... --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_data.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_data.array_id' _item.category_id array_data _item.mandatory_code yes _item_type.code code save_ save__array_data.binary_id _item_description.description ; This item is an integer identifier which, along with _array_data.array_id should uniquely identify the particular block of array data. If _array_data.binary_id is not explicitly given, it defaults to 1. The value of _array_data.binary_id distinguishes among multiple sets of data with the same array structure. If the MIME header of the data array specifies a value for X-Binary-Id, these values should be equal. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_data.binary_id' array_data implicit '_diffrn_data_frame.binary_id' diffrn_data_frame implicit '_array_intensities.binary_id' array_intensities implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.binary_id' '_array_data.binary_id' '_array_intensities.binary_id' '_array_data.binary_id' _item_default.value 1 _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_data.data _item_description.description ; The value of _array_data.data contains the array data encapsulated in a STAR string. The representation used is a variant on the Multipurpose Internet Mail Extensions (MIME) specified in RFC 2045-2049 by N. Freed et al. The boundary delimiter used in writing an imgCIF or CBF is "--CIF-BINARY-FORMAT-SECTION--" (including the required initial "--"). The Content-Type may be any of the discrete types permitted in RFC 2045; "application/octet-stream" is recommended. If an octet stream was compressed, the compression should be specified by the parameter 'conversions="x-CBF_PACKED"' or the parameter 'conversions="x-CBF_CANONICAL"'. The Content-Transfer-Encoding may be "BASE64", "Quoted-Printable", "X-BASE8", "X-BASE10", or "X-BASE16" for an imgCIF or "BINARY" for a CBF. The octal, decimal and hexadecimal transfer encodings are for convenience in debugging, and are not recommended for archiving and data interchange. In an imgCIF file, the encoded binary data begins after the empty line terminating the header. In a CBF, the raw binary data begins after an empty line terminating the header and after the sequence: Octet Hex Decimal Purpose 0 0C 12 (ctrl-L) Page break 1 1A 26 (ctrl-Z) Stop listings in MS-DOS 2 04 04 (Ctrl-D) Stop listings in UNIX 3 D5 213 Binary section begins None of these octets are included in the calculation of the message size, nor in the calculation of the message digest. The X-Binary-Size header specifies the size of the equivalent binary data in octets. If compression was used, this size is the size after compression, including any book-keeping fields. An adjustment is made for the deprecated binary formats in which 8 bytes of binary header are used for the compression type. In that case, the 8 bytes used for the compression type is subtracted from the size, so that the same size will be reported if the compression type is supplied in the MIME header. Use of the MIME header is the recommended way to supply the compression type. In general, no portion of the binary header is included in the calculation of the size. The X-Binary-Element-Type header specifies the type of binary data in the octets, using the same descriptive phrases as in _array_structure.encoding_type. The default value is "unsigned 32-bit integer". An MD5 message digest may, optionally, be used. The "RSA Data Security, Inc. MD5 Message-Digest Algorithm" should be used. No portion of the header is included in the calculation of the message digest. If the Transfer Encoding is "X-BASE8", "X-BASE10", or "X-BASE16", the data is presented as octal, decimal or hexadecimal data organized into lines or words. Each word is created by composing octets of data in fixed groups of 2, 3, 4, 6 or 8 octets, either in the order ...4321 ("big- endian") or 1234... (little-endian). If there are fewer than the specified number of octets to fill the last word, then the missing octets are presented as "==" for each missing octet. Exactly two equal signs are used for each missing octet even for octal and decimal encoding. The format of lines is: rnd xxxxxx xxxxxx xxxxxx where r is "H", "O", or "D" for hexadecimal, octal or decimal, n is the number of octets per word. and d is "<" for ">" for the "...4321" and "1234..." octet orderings respectively. The "==" padding for the last word should be on the appropriate side to correspond to the missing octets, e.g. H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000 or H3> FF0700 00==== For these hex, octal and decimal formats, only, comments beginning with "#" are permitted to improve readability. BASE64 encoding follows MIME conventions. Octets are in groups of three, c1, c2, c3. The resulting 24 bits are broken into four 6-bit quantities, starting with the high-order six bits (c1 >> 2) of the first octet, then the low-order two bits of the first octet followed by the high-order 4 bits of the second octet ((c1 & 3)<<4 | (c2>>4)), then the bottom 4 bits of the second octet followed by the high order two bits of the last octet ((c2 & 15)<<2 | (c3>>6)), then the bottom six bits of the last octet (c3 & 63). Each of these four quantities is translated into an ASCII character using the mapping: 1 2 3 4 5 6 0123456789012345678901234567890123456789012345678901234567890123 | | | | | | | ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/ With short groups of octets padded on the right with one "=" if c3 is missing, and with "==" if both c2 and c3 are missing. QUOTED-PRINTABLE encoding also follows MIME conventions, copying octets without translation if their ASCII values are 32..38, 42, 48..57, 59..60, 62, 64..126 and the octet is not a ";" in column 1. All other characters are translated to =nn, where nn is the hexadecimal encoding of the octet. All lines are "wrapped" with a terminating "=" (i.e. the MIME conventions for an implicit line terminator are never used). ; _item.name '_array_data.data' _item.category_id array_data _item.mandatory_code yes _item_type.code binary save_ ###################### # ARRAY_ELEMENT_SIZE # ###################### save_ARRAY_ELEMENT_SIZE _category.description ; Data items in the ARRAY_ELEMENT_SIZE category record the physical size of array elements along each array dimension. ; _category.id array_element_size _category.mandatory_code no loop_ _category_key.name '_array_element_size.array_id' '_array_element_size.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A regular 2D array with a uniform element dimension of 1220 nanometres. ; ; loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size image_1 1 1.22e-6 image_1 2 1.22e-6 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_element_size.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_element_size.array_id' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.index _item_description.description ; This item is a pointer to _array_structure_list.index in the ARRAY_STRUCTURE_LIST category. ; _item.name '_array_element_size.index' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.size _item_description.description ; The size in metres of an image element in this dimension. This supposes that the elements are arranged on a regular grid. ; _item.name '_array_element_size.size' _item.category_id array_element_size _item.mandatory_code yes _item_type.code float _item_units.code 'metres' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ ##################### # ARRAY_INTENSITIES # ##################### save_ARRAY_INTENSITIES _category.description ; Data items in the ARRAY_INTENSITIES category record the information required to recover the intensity data from the set of data values stored in the ARRAY_DATA category. The actual detector may have a complex relationship between the raw intensity values and the number of incident photons. In most cases, the number stored in the final array will have a simple linear relationship to the actual number of incident photons, given by '_array_intensities.gain'. If raw, uncorrected values are presented (e.g for calibration experiments), the value of '_array_intensities.linearity' will be 'raw' and '_array_intensities.gain' will not be used. ; _category.id array_intensities _category.mandatory_code no loop_ _category_key.name '_array_intensities.array_id' '_array_intensities.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 ; ; loop_ _array_intensities.array_id _array_intensities.linearity _array_intensities.gain _array_intensities.overload _array_intensities.undefined_value image_1 linear 1.2 655535 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_intensities.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_intensities.array_id' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code save_ save__array_intensities.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_array_intensities.binary_id' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code int save_ save__array_intensities.gain _item_description.description ; Detector "gain". The factor by which linearized intensity count values should be divided to produce true photon counts. ; _item.name '_array_intensities.gain' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain_esd' 'associated_value' save_ save__array_intensities.gain_esd _item_description.description ; The estimated standard deviation in detector "gain". ; _item.name '_array_intensities.gain_esd' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain' 'associated_esd' save_ save__array_intensities.linearity _item_description.description ; The intensity linearity scaling used from raw intensity to the stored element value: 'linear' is obvious 'offset' means that the value defined by '_array_intensities.offset' should be added to each element value. 'scaling' means that the value defined by '_array_intensities.scaling' should be multiplied with each element value. 'scaling_offset' is the combination of the two previous cases, with the scale factor applied before the offset value. 'sqrt_scaled' means that the square root of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and squaring the result. 'logarithmic_scaled' means that the logarithm based 10 of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and calculating 10 to the power of this number. 'raw' means that the data is the raw is a set of raw values straight from the detector. ; _item.name '_array_intensities.linearity' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'linear' . 'offset' ; The value defined by '_array_intensities.offset' should be added to each element value. ; 'scaling' ; The value defined by '_array_intensities.scaling' should be multiplied with each element value. ; 'scaling_offset' ; The combination of the scaling and offset with the scale factor applied before the offset value. ; 'sqrt_scaled' ; The square root of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and squaring the result. ; 'logarithmic_scaled' ; The logarithm based 10 of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and calculating 10 to the power of this number. ; 'raw' ; The array consists of raw values to which no corrections have been applied. While the handling of the data is similar to that given for 'linear' data with no offset, the meaning of the data differs in that the number of incident photons is not necessarily linearly related to the number of counts reported. This value is intended for use either in calibration experiments or to allow for handling more complex data fitting algorithms than are allowed for by this data item. ; save_ save__array_intensities.offset _item_description.description ; Offset value to add to array element values in the manner described by item _array_intensities.linearity. ; _item.name '_array_intensities.offset' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.scaling _item_description.description ; Multiplicative scaling value to be applied to array data in the manner described by item _array_intensities.linearity. ; _item.name '_array_intensities.scaling' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.overload _item_description.description ; The saturation intensity level for this data array. ; _item.name '_array_intensities.overload' _item.category_id array_intensities _item.mandatory_code no _item_type.code float _item_units.code 'counts' save_ save__array_intensities.undefined_value _item_description.description ; A value to be substituted for undefined values in the data array. ; _item.name '_array_intensities.undefined_value' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ ################### # ARRAY_STRUCTURE # ################### save_ARRAY_STRUCTURE _category.description ; Data items in the ARRAY_STRUCTURE category record the organization and encoding of array data which may be stored in the ARRAY_DATA category. ; _category.id array_structure _category.mandatory_code no _category_key.name '_array_structure.id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order image_1 "unsigned 16-bit integer" none little_endian ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure.byte_order _item_description.description ; The order of bytes for integer values which require more than 1-byte. (IBM-PC's and compatibles, and Dec-Vaxes use low-byte-first ordered integers, whereas Hewlett Packard 700 series, Sun-4 and Silicon Graphics use high-byte-first ordered integers. Dec-Alphas can produce/use either depending on a compiler switch.) ; _item.name '_array_structure.byte_order' _item.category_id array_structure _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'big_endian' ; The first byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; 'little_endian' ; The last byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; save_ save__array_structure.compression_type _item_description.description ; Type of data compression method used to compress the array data. ; _item.name '_array_structure.compression_type' _item.category_id array_structure _item.mandatory_code no _item_type.code code _item_default.value 'none' loop_ _item_enumeration.value _item_enumeration.detail 'none' ; Data are stored in normal format as defined by '_array_structure.encoding_type' and '_array_structure.byte_order'. ; 'byte_offsets' ; Using the compression scheme defined in CBF definition Section 5.0. ; 'packed' ; Using the 'packed' compression scheme, a CCP4-style packing (CBFlib section 3.3.2) ; 'canonical' ; Using the 'canonical' compression scheme (CBFlib section 3.3.1) ; save_ save__array_structure.encoding_type _item_description.description ; Data encoding of a single element of array data. In several cases, the IEEE format is referenced. See "IEEE Standard for Binary Floating-Point Arithmetic", ANSI/IEEE Std 754-1985, the Institute of Electrical and Electronics Engineers, Inc., NY 1985. ; _item.name '_array_structure.encoding_type' _item.category_id array_structure _item.mandatory_code yes _item_type.code uline loop_ _item_enumeration.value 'unsigned 8-bit integer' 'signed 8-bit integer' 'unsigned 16-bit integer' 'signed 16-bit integer' 'unsigned 32-bit integer' 'signed 32-bit integer' 'signed 32-bit real IEEE' 'signed 64-bit real IEEE' 'signed 32-bit complex IEEE' save_ save__array_structure.id _item_description.description ; The value of _array_structure.id must uniquely identify each item of array data. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure.id' array_structure yes '_array_data.array_id' array_data yes '_array_structure_list.array_id' array_structure_list yes '_array_intensities.array_id' array_intensities yes '_diffrn_data_frame.array_id' diffrn_data_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_data.array_id' '_array_structure.id' '_array_structure_list.array_id' '_array_structure.id' '_array_intensities.array_id' '_array_structure.id' '_diffrn_data_frame.array_id' '_array_structure.id' save_ ######################## # ARRAY_STRUCTURE_LIST # ######################## save_ARRAY_STRUCTURE_LIST _category.description ; Data items in the ARRAY_STRUCTURE_LIST category record the size and organization of each array dimension. The relationship to physical axes may be given. ; _category.id array_structure_list _category.mandatory_code no loop_ _category_key.name '_array_structure_list.array_id' '_array_structure_list.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - An image array of 1300 x 1200 elements. The raster order of the image is left-to-right (increasing) in first dimension and bottom-to-top (decreasing) in the second dimension. ; ; loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id image_1 1 1300 1 increasing ELEMENT_X image_1 2 1200 2 decreasing ELEMENY_Y ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure_list.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_structure_list.array_id' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code code save_ save__array_structure_list.axis_set_id _item_description.description ; This is a descriptor for the physical axis or set of axes corresponding to an array index. This data item is related to the axes of the detector itself given in DIFFRN_DETECTOR_AXIS, but usually differ in that the axes in this category are the axes of the coordinate system of reported data points, while the axes in DIFFRN_DETECTOR_AXIS are the physical axes of the detector describing the "poise" of the detector as an overall physical object. If there is only one axis in the set, the identifier of that axis should be used as the identifier of the set. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.axis_set_id' array_structure_list yes '_array_structure_list_axis.axis_set_id' array_structure_list_axis implicit _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_structure_list_axis.axis_set_id' '_array_structure_list.axis_set_id' save_ save__array_structure_list.dimension _item_description.description ; The number of elements stored in the array structure in this dimension. ; _item.name '_array_structure_list.dimension' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.direction _item_description.description ; Identifies the direction in which this array index changes. ; _item.name '_array_structure_list.direction' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_enumeration.value _item_enumeration.detail 'increasing' ; Indicates the index changes from 1 to the maximum dimension. ; 'decreasing' ; Indicates the index changes from the maximum dimension to 1. ; save_ save__array_structure_list.index _item_description.description ; Identifies the one-based index of the row or column in the array structure. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.index' array_structure_list yes '_array_structure_list.precedence' array_structure_list yes '_array_element_size.index' array_element_size yes _item_type.code int loop_ _item_linked.child_name _item_linked.parent_name '_array_element_size.index' '_array_structure_list.index' loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.precedence _item_description.description ; Identifies the rank order in which this array index changes with respect to other array indices. The precedence of 1 indicates the index which changes fastest. ; _item.name '_array_structure_list.precedence' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ ############################# # ARRAY_STRUCTURE_LIST_AXIS # ############################# save_ARRAY_STRUCTURE_LIST_AXIS _category.description ; Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe the physical settings of sets axes for the centres of pixels that correspond to data points described in the ARRAY_STRUCTURE_LIST category. In the simplest cases, the physical increments of a single axis correspond to the increments of a single array index. More complex organizations, e.g. spiral scans, may require coupled motions along multiple axes. Note that a spiral scan uses two coupled axis, one for the angular direction, one for the radial direction. This differs from a cylindrical scan for which the two axes are not coupled into one set. ; _category.id array_structure_list_axis _category.mandatory_code no loop_ _category_key.name '_array_structure_list_axis.axis_set_id' '_array_structure_list_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' save_ save__array_structure_list_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the set of axes for which settings are being specified. Multiple axes may be specified for the same value of '_array_structure_list_axis.axis_set_id' This item is a pointer to _axis.id in the AXIS category. ; _item.name '_array_structure_list_axis.axis_id' _item.category_id array_structure_list_axis _item.mandatory_code yes save_ save__array_structure_list_axis.axis_set_id _item_description.description ; The value of this data item is the identifier of the set of axes for which axis settings are being specified. Multiple axes may be specified for the same value of _array_structure_list_axis.axis_set_id . This item is a pointer to _array_structure_list.axis_set_id in the ARRAY_STRUCTURE_LIST category. If this item is not specified, it defaults to the corresponding axis identifier. ; _item.name '_array_structure_list_axis.axis_set_id' _item.category_id array_structure_list_axis _item.mandatory_code implicit save_ save__array_structure_list_axis.angle _item_description.description ; The setting of the specified axis in degrees for the first data point of the array index with the corresponding value of '_array_structure_list.axis_set_id'. If the index is specified as 'increasing' this will be the center of the pixel with index value 1. If the index is specified as 'decreasing' this will be the center of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.angle' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.angle_increment _item_description.description ; The pixel-center-to-pixel-center increment in the angular setting of the specified axis in degrees. This is not meaningful in the case of 'constant velocity' spiral scans and should not be specified in that case. See '_array_structure_list_axis.angular_pitch'. ; _item.name '_array_structure_list_axis.angle_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for the first data point of the array index with the corresponding value of '_array_structure_list.axis_set_id'. If the index is specified as 'increasing' this will be the center of the pixel with index value 1. If the index is specified as 'decreasing' this will be the center of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.displacement' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.displacement_increment _item_description.description ; The pixel-center-to-pixel-center increment for the displacement setting of the specified axis in millimetres. ; _item.name '_array_structure_list_axis.displacement_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.angular_pitch _item_description.description ; The pixel-center-to-pixel-center distance for a one step change in the setting of the specified axis in millimetres. This is meaningful only for 'constant velocity' spiral scans, or for uncoupled angular scans at a constant radius (cylindrical scan) and should not be specified for cases in which the angle between pixels, rather than the distance between pixels is uniform. See '_array_structure_list_axis.angle_increment'. ; _item.name '_array_structure_list_axis.angular_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.radial_pitch _item_description.description ; The radial distance from one "cylinder" of pixels to the next in millimetres. If the scan is a 'constant velocity' scan with differing angular displacements between pixels, the value of this item may differ significantly from the value of '_array_structure_list_axis.displacement_increment'. ; _item.name '_array_structure_list_axis.radial_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ ######## # AXIS # ######## save_AXIS _category.description ; Data items in the AXIS category record the information required to describe the various goniometer, detector, source and other axes needed to specify a data collection. The location of each axis is specified by two vectors: the axis itself, given as a unit vector, and an offset to the base of the unit vector. These vectors are referenced to a right-handed laboratory coordinate system with its origin in the sample or specimen: | Y (to complete right-handed system) | | | | | |________________X / principal goniometer axis / / / / /Z (to source) Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from the sample or specimen along the principal axis of the goniometer. Axis 2 (Y): The Y-axis completes an orthogonal right-handed system defined by the X-axis and the Z-axis (see below). Axis 3 (Z): The Z-axis is derived from the source axis which goes from the sample to the source. The Z-axis is the component of the source axis in the direction of the source orthogonal to the X-axis in the plane defined by the X-axis and the source axis. These axes are based on the goniometer, not on the orientation of the detector, gravity, etc. The vectors necessary to specify all other axes are given by sets of three components in the order (X, Y, Z). If the axis involved is a rotation axis, it is right handed, i.e. as one views the object to be rotated from the origin (the tail) of the unit vector, the rotation is clockwise. If a translation axis is specified, the direction of the unit vector specifies the sense of positive translation. Note: This choice of coordinate system is similar to, but significantly different from the choice in MOSFLM (Andrew G.W. Leslie, Harry Powell, MRC Laboratory of Molecular Biology, Hills Road, Cambridge CB2 2QH,UK http://www.dl.ac.uk/CCP/CCP4/dist/x-windows/Mosflm/). In MOSFLM, X is along the X-ray beam (our Z axis) and Z is along the rotation axis. All rotations are given in degrees and all translations are given in mm. Axes may be dependent on one another. The X-axis is the only goniometer axis the direction of which is strictly connected to the hardware. All other axes are specified by the positions they would assume when the axes upon which they depend are at their zero points. When specifying detector axes, the axis is given to the beam center. The location of the beam center on the detector should be given in the DIFFRN_DETECTOR category in distortion-corrected mm from the (0,0) corner of the detector. It should be noted that many different origins arise in the definition of an experiment. In particular, as noted above, we need to specify the location of the beam center on the detector in terms of the origin of the detector, which is, of course, not coincident with the center of the sample. ; _category.id axis _category.mandatory_code no loop_ _category_key.name '_axis.id' '_axis.equipment' loop_ _category_group.id 'inclusive_group' 'axis_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows the axis specification of the axes of a kappa geometry goniometer (See "X-Ray Structure Determination, A Practical Guide", 2nd ed. by G. H. Stout, L. H. Jensen, Wiley Interscience, 1989, 453 pp, p 134.). There are three axes specified, and no offsets. The outermost axis, omega, is pointed along the X-axis. The next innermost axis, kappa, is at a 50 degree angle to the X-axis, pointed away from the source. The innermost axis, phi, aligns with the X-axis when omega and phi are at their zero-points. If T-omega, T-kappa and T-phi are the transformation matrices derived from the axis settings, the complete transformation would be: x' = (T-omega) (T-kappa) (T-phi) x ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] omega rotation goniometer . 1 0 0 kappa rotation goniometer omega -.64279 0 -.76604 phi rotation goniometer kappa 1 0 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - This example show the axis specification of the axes of a detector, source and gravity. We have juggled the order as a reminder that the ordering of presentation of tokens is not significant. We have taken the center of rotation of the detector to be 68 millimetres in the direction away from the source. ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] source . source . 0 0 1 . . . gravity . gravity . 0 -1 0 . . . tranz translation detector rotz 0 0 1 0 0 -68 twotheta rotation detector . 1 0 0 . . . roty rotation detector twotheta 0 1 0 0 0 -68 rotz rotation detector roty 0 0 1 0 0 -68 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__axis.depends_on _item_description.description ; The value of _axis.type specifies the next outermost axis upon which this axis depends. This item is a pointer to axis.id in the same category. ; _item.name '_axis.depends_on' _item.category_id axis _item.mandatory_code no save_ save__axis.equipment _item_description.description ; The value of _axis.type specifies the type of equipment using the axis: goniometer, detector, gravity, source or general ; _item.name '_axis.equipment' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail goniometer 'equipment used to orient or position samples' detector 'equipment used to detect reflections' general 'equipment used for general purposes' gravity 'axis specifying the downward direction' source 'axis specifying the direction sample to source' save_ save__axis.offset[1] _item_description.description ; The [1] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[2] _item_description.description ; The [2] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[3] _item_description.description ; The [3] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.id _item_description.description ; The value of _axis.id must uniquely identify each axis relevant to the experiment. Note that multiple pieces of equipment may share the same axis (e.g. a twotheta arm), so that the category key for AXIS also includes the equipment. ; loop_ _item.name _item.category_id _item.mandatory_code '_axis.id' axis yes '_array_structure_list_axis.axis_id' array_structure_list_axis yes '_diffrn_detector_axis.axis_id' diffrn_detector_axis yes '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes '_diffrn_scan_axis.axis_id' diffrn_scan_axis yes '_diffrn_scan_frame_axis.axis_id' diffrn_scan_frame_axis yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_axis.depends_on' '_axis.id' '_array_structure_list_axis.axis_id' '_axis.id' '_diffrn_detector_axis.axis_id' '_axis.id' '_diffrn_measurement_axis.axis_id' '_axis.id' '_diffrn_scan_axis.axis_id' '_axis.id' '_diffrn_scan_frame_axis.axis_id' '_axis.id' save_ save__axis.type _item_description.description ; The value of _axis.type specifies the type of axis: rotation, translation (or general when the type is not relevant, as for gravity) ; _item.name '_axis.type' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail rotation 'right-handed axis of rotation' translation 'translation in the direction of the axis' general 'axis for which the type is not relevant' save_ save__axis.vector[1] _item_description.description ; The [1] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector, and is dimensionless. ; _item.name '_axis.vector[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[2] _item_description.description ; The [2] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector, and is dimensionless. ; _item.name '_axis.vector[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[3] _item_description.description ; The [3] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector, and is dimensionless. ; _item.name '_axis.vector[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ ##################### # DIFFRN_DATA_FRAME # ##################### save_DIFFRN_DATA_FRAME _category.description ; Data items in the DIFFRN_DATA_FRAME category record the details about each frame of data. The items in this category were previously in a DIFFRN_FRAME_DATA category, which is now deprecated. The items from the old category are provided as aliases, but should not be used for new work. ; _category.id diffrn_data_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_data_frame.id' '_diffrn_data_frame.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A frame containing data from 4 frame elements. Each frame element has a common array configuration 'array_1' described in ARRAY_STRUCTURE and related categories. The data for each detector element is stored in four groups of binary data in the ARRAY_DATA category, linked by the array_id and binary_id ; ; loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id frame_1 d1_ccd_1 array_1 1 frame_1 d1_ccd_2 array_1 2 frame_1 d1_ccd_3 array_1 3 frame_1 d1_ccd_4 array_1 4 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_data_frame.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_diffrn_data_frame.array_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.array_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0.00 _item_type.code code save_ save__diffrn_data_frame.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_diffrn_data_frame.binary_id' _item.category_id diffrn_data_frame _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_frame_data.binary_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code int save_ save__diffrn_data_frame.detector_element_id _item_description.description ; This item is a pointer to _diffrn_detector_element.id in the DIFFRN_DETECTOR_ELEMENT category. ; _item.name '_diffrn_data_frame.detector_element_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.detector_element_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.id _item_description.description ; The value of _diffrn_data_frame.id must uniquely identify each complete frame of data. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_data_frame.id' diffrn_data_frame yes '_diffrn_refln.frame_id' diffrn_refln yes '_diffrn_scan.frame_id_start' diffrn_scan yes '_diffrn_scan.frame_id_end' diffrn_scan yes '_diffrn_scan_frame.frame_id' diffrn_scan_frame yes '_diffrn_scan_frame_axis.frame_id' diffrn_scan_frame_axis yes _item_aliases.alias_name '_diffrn_frame_data.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_refln.frame_id' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_start' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_end' '_diffrn_data_frame.id' '_diffrn_scan_frame.frame_id' '_diffrn_data_frame.id' '_diffrn_scan_frame_axis.frame_id' '_diffrn_data_frame.id' save_ ########################################################################## # The following is a restatement of the mmCIF DIFFRN_DETECTOR, # # DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for # # the CBF/imgCIF extensions # ########################################################################## ################### # DIFFRN_DETECTOR # ################### save_DIFFRN_DETECTOR _category.description ; Data items in the DIFFRN_DETECTOR category describe the detector used to measure the scattered radiation, including any analyser and post-sample collimation. ; _category.id diffrn_detector _category.mandatory_code no loop_ _category_key.name '_diffrn_detector.diffrn_id' '_diffrn_detector.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_detector.diffrn_id 'd1' _diffrn_detector.detector 'multiwire' _diffrn_detector.type 'Siemens' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector.details _item_description.description ; A description of special aspects of the radiation detector. ; _item.name '_diffrn_detector.details' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; Need new example here. ; save_ save__diffrn_detector.detector _item_description.description ; The general class of the radiation detector. ; _item.name '_diffrn_detector.detector' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector' cifdic.c91 1.0 '_diffrn_detector' cif_core.dic 2.0 _item_type.code text loop_ _item_examples.case 'photographic film' 'scintillation counter' 'CCD plate' 'BF~3~ counter' save_ save__diffrn_detector.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. The value of _diffrn.id uniquely defines a set of diffraction data. ; _item.name '_diffrn_detector.diffrn_id' _item.mandatory_code yes save_ save__diffrn_detector.dtime _item_description.description ; The deadtime in microseconds of the detectors used to measure the diffraction intensities. ; _item.name '_diffrn_detector.dtime' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector_dtime' cifdic.c91 1.0 '_diffrn_detector_dtime' cif_core.dic 2.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code microseconds save_ save__diffrn_detector.id _item_description.description ; The value of _diffrn_detector.id must uniquely identify each detector used to collect each diffraction data set. If the value of _diffrn_detector.id is not given, it is implicitly equal to the value of _diffrn_detector.diffrn_id ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector.id' diffrn_detector implicit '_diffrn_detector_axis.detector_id' diffrn_detector_axis yes loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_detector_axis.detector_id' '_diffrn_detector.id' _item_type.code code save_ save__diffrn_detector.number_of_axes _item_description.description ; The value of _diffrn_detector.number_of_axes gives the number of axes of the positioner for the detector identified by _diffrn_detector.id The word "positioner" is a general term used in instrumentation design for devices that are used to change the positions of portions of apparatus by linear translation, rotation, or combinations of such motions. Axes which are used to provide a coordinate system for the face of an area detetctor should not be counted for this data item. The description of each axis should be provided by entries in DIFFRN_DETECTOR_AXIS. ; _item.name '_diffrn_detector.number_of_axes' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_detector.type _item_description.description ; The make, model or name of the detector device used. ; _item.name '_diffrn_detector.type' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ ######################## # DIFFRN_DETECTOR_AXIS # ######################## save_DIFFRN_DETECTOR_AXIS _category.description ; Data items in the DIFFRN_DETECTOR_AXIS category associate axes with detectors. ; _category.id diffrn_detector_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_axis.detector_id' '_diffrn_detector_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_detector_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_detector_axis.axis_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_axis.detector_id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. This item was previously named '_diffrn_detector_axis.id' which is now a deprecated name. The old name is provided as an alias, but should not be used for new work. ; _item.name '_diffrn_detector_axis.detector_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_aliases.alias_name '_diffrn_detector_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 save_ ########################### # DIFFRN_DETECTOR_ELEMENT # ########################### save_DIFFRN_DETECTOR_ELEMENT _category.description ; Data items in the DIFFRN_DETECTOR_ELEMENT category record the details about spatial layout and other characteristics of each element of a detector which may have multiple elements. In most cases, the more detailed information provided in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS are preferable to simply providing the centre. ; _category.id diffrn_detector_element _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_element.id' '_diffrn_detector_element.detector_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Detector d1 is composed of four CCD detector elements, each 200 mm by 200 mm, arranged in a square. in the pattern 1 2 * 3 4 Note that the beam center is slightly off of each of the detector elements, just beyond the lower right corner of 1, the lower left corner of 2, the upper right corner of 3 and the upper left corner of 4. ; ; loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id _diffrn_detector_element.center[1] _diffrn_detector_element.center[2] d1 d1_ccd_1 201.5 -1.5 d1 d1_ccd_2 -1.8 -1.5 d1 d1_ccd_3 201.6 201.4 d1 d1_ccd_4 -1.7 201.5 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector_element.center[1] _item_description.description ; The value of _diffrn_detector_element.center[1] is the X component of the distortion-corrected beam-center in mm from the (0, 0) (lower left) corner of the detector element viewed from the sample side. ; _item.name '_diffrn_detector_element.center[1]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.center[2] _item_description.description ; The value of _diffrn_detector_element.center[2] is the Y component of the distortion-corrected beam-center in mm from the (0, 0) (lower left) corner of the detector element viewed from the sample side. ; _item.name '_diffrn_detector_element.center[2]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.id _item_description.description ; The value of _diffrn_detector_element.id must uniquely identify each element of a detector. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector_element.id' diffrn_detector_element yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.detector_element_id' '_diffrn_detector_element.id' save_ save__diffrn_detector_element.detector_id _item_description.description ; This item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. ; _item.name '_diffrn_detector_element.detector_id' _item.category_id diffrn_detector_element _item.mandatory_code yes _item_type.code code save_ ######################## ## DIFFRN_MEASUREMENT ## ######################## save_DIFFRN_MEASUREMENT _category.description ; Data items in the DIFFRN_MEASUREMENT category record details about the device used to orient and/or position the crystal during data measurement and the manner in which the diffraction data were measured. ; _category.id diffrn_measurement _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement.device' '_diffrn_measurement.diffrn_id' '_diffrn_measurement.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_measurement.diffrn_id 'd1' _diffrn_measurement.device '3-circle camera' _diffrn_measurement.device_type 'Supper model x' _diffrn_measurement.device_details 'none' _diffrn_measurement.method 'omega scan' _diffrn_measurement.details ; Need new example here ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991). Acta Cryst. C47, 2276-2277]. ; ; _diffrn_measurement.diffrn_id 's1' _diffrn_measurement.device_type 'Philips PW1100/20 diffractometer' _diffrn_measurement.method 'theta/2theta (\q/2\q)' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_measurement.device _item_description.description ; The general class of goniometer or device used to support and orient the specimen. If the value of _diffrn_measurement.device is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id Either '_diffrn_measurement.device' or '_diffrn_measurement.id' may be used to link to other categories. If the experimental setup admits multiple devices, then '_diffrn_measurement.id' is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.device' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_device' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement.device' _item_aliases.alias_name '_diffrn_measurement_device' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '3-circle camera' '4-circle camera' 'kappa-geometry camera' 'oscillation camera' 'precession camera' save_ save__diffrn_measurement.device_details _item_description.description ; A description of special aspects of the device used to measure the diffraction intensities. ; _item.name '_diffrn_measurement.device_details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; commercial goniometer modified locally to allow for 90\% \t arc ; save_ save__diffrn_measurement.device_type _item_description.description ; The make, model or name of the measurement device (goniometer) used. ; _item.name '_diffrn_measurement.device_type' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Supper model q' 'Huber model r' 'Enraf-Nonius model s' 'homemade' save_ save__diffrn_measurement.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_measurement.diffrn_id' _item.mandatory_code yes save_ save__diffrn_measurement.details _item_description.description ; A description of special aspects of the intensity measurement. ; _item.name '_diffrn_measurement.details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; save_ save__diffrn_measurement.id _item_description.description ; The value of _diffrn_measurement.id must uniquely identify the set of mechanical characteristics of the device used to orient and/or position the sample used during collection of each diffraction data set. If the value of _diffrn_measurement.id is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id Either '_diffrn_measurement.device' or '_diffrn_measurement.id' may be used to link to other categories. If the experimental setup admits multiple devices, then '_diffrn_measurement.id' is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.id' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_id' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement.id' _item_type.code code save_ save__diffrn_measurement.method _item_description.description ; Method used to measure intensities. ; _item.name '_diffrn_measurement.method' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_method' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'profile data from theta/2theta (\q/2\q) scans' save_ save__diffrn_measurement.number_of_axes _item_description.description ; The value of _diffrn_measurement.number_of_axes gives the number of axes of the positioner for the goniometer or other sample orientation or positioning device identified by _diffrn_measurement.id The description of the axes should be provided by entries in DIFFRN_MEASUREMENT_AXIS. ; _item.name '_diffrn_measurement.number_of_axes' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_measurement.specimen_support _item_description.description ; The physical device used to support the crystal during data collection. ; _item.name '_diffrn_measurement.specimen_support' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_specimen_support' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'glass capillary' 'quartz capillary' 'fiber' 'metal loop' save_ ########################### # DIFFRN_MEASUREMENT_AXIS # ########################### save_DIFFRN_MEASUREMENT_AXIS _category.description ; Data items in the DIFFRN_MEASUREMENT_AXIS category associate axes with goniometers. ; _category.id diffrn_measurement_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_measurement_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_measurement_axis.axis_id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.measurement_device _item_description.description ; This data item is a pointer to _diffrn_measurement.device in the DIFFRN_MEASUREMENT category. ; _item.name '_diffrn_measurement_axis.measurement_device' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit save_ save__diffrn_measurement_axis.measurement_id _item_description.description ; This data item is a pointer to _diffrn_measurement.id in the DIFFRN_MEASUREMENT category. This item was previously named '_diffrn_measurement_axis.id' which is now a deprecated name. The old name is provided as an alias, but should not be used for new work. ; _item.name '_diffrn_measurement_axis.measurement_id' _item.category_id diffrn_measurement_axis _item_aliases.alias_name '_diffrn_measurement_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0.00 _item.mandatory_code implicit save_ #################### # DIFFRN_RADIATION # #################### save_DIFFRN_RADIATION _category.description ; Data items in the DIFFRN_RADIATION category describe the radiation used in measuring diffraction intensities, its collimation and monochromatisation before the sample. Post-sample treatment of the beam is described by data items in the DIFFRN_DETECTOR category. ; _category.id diffrn_radiation _category.mandatory_code no _category_key.name '_diffrn_radiation.diffrn_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_radiation.diffrn_id 'set1' _diffrn_radiation.collimation '0.3 mm double pinhole' _diffrn_radiation.monochromator 'graphite' _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.wavelength_id 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991). Acta Cryst. C47, 2276-2277]. ; ; _diffrn_radiation.wavelength_id 1 _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.monochromator 'graphite' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_radiation.collimation _item_description.description ; The collimation or focusing applied to the radiation. ; _item.name '_diffrn_radiation.collimation' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_collimation' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '0.3 mm double-pinhole' '0.5 mm' 'focusing mirrors' save_ save__diffrn_radiation.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_radiation.diffrn_id' _item.mandatory_code yes save_ save__diffrn_radiation.div_x_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory X axis (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the esd of the directions of photons in the X-Z plane around the mean source beam direction. Note that some synchrotrons specify this value in milliradians, in which case a conversion would be needed. To go from a value in milliradians to a value in degrees, multiply by 0.180 and divide by Pi. ; _item.name '_diffrn_radiation.div_x_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.div_y_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory Y axis (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the esd of the directions of photons in the Y-Z plane around the mean source beam direction. Note that some synchrotrons specify this value in milliradians, in which case a conversion would be needed. To go from a value in milliradians to a value in degrees, multiply by 0.180 and divide by Pi. ; _item.name '_diffrn_radiation.div_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.div_x_y_source _item_description.description ; Beam crossfire correlation degrees**2 between the crossfire laboratory X-axis component and the crossfire laboratory Y-axis component (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the mean of the products of the deviations of the directin of each photons in X-Z plane times the deviations of the direction of the same photon in the Y-Z plane around the mean source beam direction. This will be zero for uncorrelated crossfire. Note that some synchrotrons specify this value in milliradians**2, in which case a conversion would be needed. To go from a value in milliradians**2 to a value in degrees**2, multiply by 0.180**2 and divide by Pi**2. ; _item.name '_diffrn_radiation.div_x_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees_squared _item_default.value 0.0 save_ save__diffrn_radiation.filter_edge _item_description.description ; Absorption edge in angstroms of the radiation filter used. ; _item.name '_diffrn_radiation.filter_edge' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_filter_edge' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__diffrn_radiation.inhomogeneity _item_description.description ; Half-width in millimetres of the incident beam in the direction perpendicular to the diffraction plane. ; _item.name '_diffrn_radiation.inhomogeneity' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_inhomogeneity' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code millimetres save_ save__diffrn_radiation.monochromator _item_description.description ; The method used to obtain monochromatic radiation. If a mono- chromator crystal is used the material and the indices of the Bragg reflection are specified. ; _item.name '_diffrn_radiation.monochromator' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_monochromator' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Zr filter' 'Ge 220' 'none' 'equatorial mounted graphite' save_ save__diffrn_radiation.polarisn_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the perpendicular component of the polarisation and the diffraction plane. See _diffrn_radiation_polarisn_ratio. ; _item.name '_diffrn_radiation.polarisn_norm' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_norm' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.polarisn_ratio _item_description.description ; Polarisation ratio of the diffraction beam incident on the crystal. It is the ratio of the perpendicularly polarised to the parallel polarised component of the radiation. The perpendicular component forms an angle of _diffrn_radiation.polarisn_norm to the normal to the diffraction plane of the sample (i.e. the plane containing the incident and reflected beams). ; _item.name '_diffrn_radiation.polarisn_ratio' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_ratio' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__diffrn_radiation.polarizn_source_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the normal to the polarization plane and the laboratory Y axis as defined in the AXIS category. Note that this is the angle of polarization of the source photons, either directly from a synchrotron beamline or from a monchromater. This differs from the value of '_diffrn_radiation.polarisn_norm' in that '_diffrn_radiation.polarisn_norm' refers to polarization relative to the diffraction plane rather than to the laboratory axis system. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane should be taken as the X-Z plane, and the angle as 0. See '_diffrn_radiation.polarizn_source_ratio'. ; _item.name '_diffrn_radiation.polarizn_source_norm' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.polarizn_source_ratio _item_description.description ; (Ip-In)/(Ip+In), where Ip is the intensity (amplitude squared) of the electric vector in the plane of polarization and In is the intensity (amplitude squared) of the electric vector in plane of the normal to the plane of polarization. Thus, if we had complete polarization in the plane of polarization, the value of '_diffrn_radiation.polarizn_source_ratio' would be 1, and an unpolarized beam would have a value of 0. If the X-axis has been chosen to lie in the plane of polarization, this definition will agree with the definition of "MONOCHROMATOR" in the Denzo glossary, and values of near 1 should be expected for a bending magnet source. However, if the X-axis were, for some reason to be, say, perpendicular to the polarization plane (not a common choice), then the Denzo value would be the negative of '_diffrn_radiation.polarizn_source_ratio'. See http://www.hkl-xray.com for information on Denzo, and Z. Otwinowski and W. Minor, " Processing of X-ray Diffraction Data Collected in Oscillation Mode ", Methods in Enzymology, Volume 276: Macromolecular Crystallography, part A, p.307-326, 1997,C.W. Carter, Jr. & R. M. Sweet, Eds., Academic Press. This differs both in the choice of ratio and choice of orientation from '_diffrn_radiation.polarisn_ratio', which, unlike '_diffrn_radiation.polarizn_source_ratio', is unbounded. ; _item.name '_diffrn_radiation.polarizn_source_ratio' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 -1.0 -1.0 -1.0 _item_type.code float save_ save__diffrn_radiation.probe _item_description.description ; Name of the type of radiation used. It is strongly encouraged that this field be specified so that the probe radiation can be simply determined. ; _item.name '_diffrn_radiation.probe' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_probe' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value 'x-ray' 'neutron' 'electron' 'gamma' save_ save__diffrn_radiation.type _item_description.description ; The nature of the radiation. This is typically a description of the X-ray wavelength in Siegbahn notation. ; _item.name '_diffrn_radiation.type' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'CuK\a' 'Cu K\a~1~' 'Cu K-L~2,3~' 'white-beam' save_ save__diffrn_radiation.xray_symbol _item_description.description ; The IUPAC symbol for the X-ray wavelength for probe radiation. ; _item.name '_diffrn_radiation.xray_symbol' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_xray_symbol' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value _item_enumeration.detail 'K-L~3~' 'K\a~1~ in older Siegbahn notation' 'K-L~2~' 'K\a~2~ in older Siegbahn notation' 'K-M~3~' 'K\b~1~ in older Siegbahn notation' 'K-L~2,3~' 'use where K-L~3~ and K-L~2~ are not resolved' save_ save__diffrn_radiation.wavelength_id _item_description.description ; This data item is a pointer to _diffrn_radiation_wavelength.id in the DIFFRN_RADIATION_WAVELENGTH category. ; _item.name '_diffrn_radiation.wavelength_id' _item.mandatory_code yes save_ ################ # DIFFRN_REFLN # ################ save_DIFFRN_REFLN _category.description ; This category redefinition has been added to extend the key of the standard DIFFRN_REFLN category. ; _category.id diffrn_refln _category.mandatory_code no _category_key.name '_diffrn_refln.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_refln.frame_id _item_description.description ; This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_refln.frame_id' _item.category_id diffrn_refln _item.mandatory_code yes _item_type.code code save_ ############### # DIFFRN_SCAN # ############### save_DIFFRN_SCAN _category.description ; Data items in the DIFFRN_SCAN category describe the parameters of one or more scans, relating axis positions to frames. ; _category.id diffrn_scan _category.mandatory_code no _category_key.name '_diffrn_scan.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - derived from a suggestion by R. M. Sweet. The vector of each axis is not given here, because it is provided in the AXIS category. By making _diffrn_scan_axis.scan_id and _diffrn_scan_axis.axis_id keys of the DIFFRN_SCAN_AXIS category, an arbitrary number of scanning and fixed axes can be specified for a scan. We have specified three rotation axes and one translation axis at non-zero values, with one axis stepping. There is no reason why more axes could not have been specified to step. We have specified range information, but note that it is redundant from the number of frames and the increment, so we could drop the data item _diffrn_scan_axis.angle_range . We have specified both the sweep data and the data for a single frame. Note that the information on how the axes are stepped is given twice, once in terms of the overall averages in the value of '_diffrn_scan.integration_time' and the values for DIFFRN_SCAN_AXIS, and precisely for the given frame in the value for '_diffrn_scan_frame.integration_time' and the values for DIFFRN_SCAN_FRAME_AXIS. If dose-related adjustements are made to scan times and non-linear stepping is done, these values may differ. Therefore, in interpreting the data for a particular frame it is important to use the frame-specific data. ; ; _diffrn_scan.id 1 _diffrn_scan.date_start '2001-11-18T03:26:42' _diffrn_scan.date_end '2001-11-18T03:36:45' _diffrn_scan.integration_time 3.0 _diffrn_scan.frame_id_start mad_L2_000 _diffrn_scan.frame_id_end mad_L2_200 _diffrn_scan.frames 201 loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment 1 omega 200.0 20.0 0.1 . . . 1 kappa -40.0 0.0 0.0 . . . 1 phi 127.5 0.0 0.0 . . . 1 tranz . . . 2.3 0.0 0.0 _diffrn_scan_frame.scan_id 1 _diffrn_scan_frame.date '2001-11-18T03:27:33' _diffrn_scan_frame.integration_time 3.0 _diffrn_scan_frame.frame_id mad_L2_018 _diffrn_scan_frame.frame_number 18 loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.angle_increment _diffrn_scan_frame_axis.displacement _diffrn_scan_frame_axis.displacement_increment mad_L2_018 omega 201.8 0.1 . . mad_L2_018 kappa -40.0 0.0 . . mad_L2_018 phi 127.5 0.0 . . mad_L2_018 tranz . . 2.3 0.0 ; ; Example 2 - a more extensive example, R. M. Sweet, P. Ellis, H. Bernstein. We place a detector 240 mm along the Z axis from the goniometer. This presents us with a choice -- either we define the axes of the detector at the origin, and then put a Z setting of -240 in for the actual use, or we define the axes with the necessary Z-offset. In this case we use the setting, and leave the offset as zero. We call this axis DETECTOR_Z. The axis for positioning the detector in the Y-direction depends on the detector Z-axis. We call this axis, DETECTOR_Y. The axis for positioning the dector in the X-direction depends on the detector Y-axis (and therefore on the detector Z-axis). We call this axis DETECTOR_X. This detector may be rotated around the Y-axis. This rotation axis depends on the three translation axies. We call it DETECTOR_PITCH. We define a coordinate system on the face of the detector in terms of 2300 0.150 mm pixels in each direction. The ELEMENT_X axis is used to index the first array index of the data array and the ELEMENT_Y axis is used to index the second array index. Because the pixels are 0.150mm x 0.150mm, the center of the first pixel is at (0.075, 0.075) in this coordinate system. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 172.43 -172.43 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 2300 1 increasing ELEMENT_X ARRAY1 2 2300 2 increasing ELEMENT_Y # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.075 0.150 ELEMENT_Y ELEMENT_Y 0.075 0.150 # category ARRAY_ELEMENT_SIZE loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 ARRAY1 2 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; ; Example 3 - Example 2 revised for a spiral scan, R. M. Sweet, P. Ellis, H. Bernstein. We place a detector 240 mm along the Z axis from the goniometer, as in Example 2, above, but in this example, the image plate is scanned in a spiral pattern outside edge in. The axis for positioning the detector in the Y-direction depends on the detector Z-axis. We call this axis, DETECTOR_Y. The axis for positioning the dector in the X-direction depends on the detector Y-axis (and therefore on the detector Z-axis). We call this axis DETECTOR_X. This detector may be rotated around the Y-axis. This rotation axis depends on the three translation axies. We call it DETECTOR_PITCH. We define a coordinate system on the face of the detector in terms of a coupled rotation axis and radial scan axis to form a spiral scan. Let us call rotation axis ELEMENT_ROT, and the radial axis ELEMENT_RAD. We assume 150 um radial pitch and 75 um 'constant velocity' angular pitch. We index first on the rotation axis and make the radial axis dependent on it. The two axes are coupled to form an axis set ELEMENT_SPIRAL. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_ROT translation detector DETECTOR_PITCH 0 0 1 0 0 0 ELEMENT_RAD translation detector ELEMENT_ROT 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.angle _array_structure_list_axis.displacement _array_structure_list_axis.angular_pitch _array_structure_list_axis.radial_pitch ELEMENT_SPIRAL ELEMENT_ROT 0 . 0.075 . ELEMENT_SPIRAL ELEMENT_RAD . 172.5 . -0.150 # category ARRAY_ELEMENT_SIZE # the actual pixels are 0.075 by 0.150 mm # We give the coarser dimension here. loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_scan.id _item_description.description ; The value of _diffrn_scan.id uniquely identifies each scan. The identifier is used to tie together all the information about the scan. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_scan.id' diffrn_scan yes '_diffrn_scan_axis.scan_id' diffrn_scan_axis yes '_diffrn_scan_frame.scan_id' diffrn_scan_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_scan_axis.scan_id' '_diffrn_scan.id' '_diffrn_scan_frame.scan_id' '_diffrn_scan.id' save_ save__diffrn_scan.date_end _item_description.description ; The date and time of the end of the scan. Note that this may be an estimate generated during the scan, before the precise time of the end of the scan is known. ; _item.name '_diffrn_scan.date_end' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.date_start _item_description.description ; The date and time of the start of the scan. ; _item.name '_diffrn_scan.date_start' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.integration_time _item_description.description ; Approximate average time in seconds to integrate each step of the scan. The precise time for integration of each particular step must be provided in '_diffrn_scan_frame.integration_time', even if all steps have the same integration time. ; _item.name '_diffrn_scan.integration_time' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan.frame_id_start _item_description.description ; The value of this data item is the identifier of the first frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_start' _item.category_id diffrn_scan _item.mandatory_code yes save_ save__diffrn_scan.frame_id_end _item_description.description ; The value of this data item is the identifier of the last frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_end' _item.category_id diffrn_scan _item.mandatory_code yes save_ save__diffrn_scan.frames _item_description.description ; The value of this data item is the number of frames in the scan. ; _item.name '_diffrn_scan.frames' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 1 1 1 save_ #################### # DIFFRN_SCAN_AXIS # #################### save_DIFFRN_SCAN_AXIS _category.description ; Data items in the DIFFRN_SCAN_AXIS category describe the settings of axes for particular scans. Unspecified axes are assumed to be at their zero points. ; _category.id diffrn_scan_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_axis.scan_id' '_diffrn_scan_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_axis.scan_id _item_description.description ; The value of this data item is the identifier of the scan for which axis settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan.id'. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_axis.scan_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes save_ save__diffrn_scan_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the scan for which settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan.id'. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_axis.axis_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes save_ save__diffrn_scan_axis.angle_start _item_description.description ; The starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_range _item_description.description ; The range from the starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_increment _item_description.description ; The increment for each step for the specified axis in degrees. In general, this will agree with '_diffrn_scan_frame_axis.angle_increment'. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.angle_increment' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.angle_increment' (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_rstrt_incr _item_description.description ; The increment after each step for the specified axis in degrees. In general, this will agree with '_diffrn_scan_frame_axis.angle_rstrt_incr'. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' and '_diffrn_scan_frame_axis.angle_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame, and should equal '_diffrn_scan_frame_axis.angle' for that next frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.angle_rstrt_incr' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.angle_rstrt_incr' (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.displacement_start _item_description.description ; The starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_range _item_description.description ; The range from the starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_increment _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with '_diffrn_scan_frame_axis.displacement_increment'. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.displacement_increment' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.displacement_increment' (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_rstrt_incr _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with '_diffrn_scan_frame_axis.displacement_rstrt_incr'. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' and '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame, and should equal '_diffrn_scan_frame_axis.displacement' for that next frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.displacement_rstrt_incr' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.displacement_rstrt_incr' (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ ##################### # DIFFRN_SCAN_FRAME # ##################### save_DIFFRN_SCAN_FRAME _category.description ; Data items in the DIFFRN_SCAN_FRAME category describe the relationship of particular frames to scans. ; _category.id diffrn_scan_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame.scan_id' '_diffrn_scan_frame.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame.date _item_description.description ; The date and time of the start of the frame being scanned. ; _item.name '_diffrn_scan_frame.date' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan_frame.frame_id _item_description.description ; The value of this data item is the identifier of the frame being examined. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame.frame_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes save_ save__diffrn_scan_frame.frame_number _item_description.description ; The value of this data item is the number of the frame within the scan, starting with 1. It is not necessarily the same as the value of _diffrn_scan_frame.frame_id, but may be. ; _item.name '_diffrn_scan_frame.frame_number' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 0 0 0 save_ save__diffrn_scan_frame.integration_time _item_description.description ; The time in seconds to integrate this step of the scan. This should be the precise time of integration of each particular frame. The value of this data item should be given explicitly for each frame and not inferred from the value of '_diffrn_scan.integration_time'. ; _item.name '_diffrn_scan_frame.integration_time' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame.scan_id _item_description.description ; The value of _diffrn_scan_frame.scan_id identifies the scan containing this frame. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_frame.scan_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes save_ ########################## # DIFFRN_SCAN_FRAME_AXIS # ########################## save_DIFFRN_SCAN_FRAME_AXIS _category.description ; Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the settings of axes for particular frames. Unspecified axes are assumed to be at their zero points. If, for any given frame, non-zero values apply for any of the data items in this category, those values should be given explicitly in this category and not simply inferred from values in DIFFRN_SCAN_AXIS. ; _category.id diffrn_scan_frame_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame_axis.frame_id' '_diffrn_scan_frame_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the frame for which settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_frame_axis.axis_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes save_ save__diffrn_scan_frame_axis.angle _item_description.description ; The setting of the specified axis in degrees for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.angle' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_increment _item_description.description ; The increment for this frame for angular setting of the specified axis in degrees. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.angle_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_rstrt_incr _item_description.description ; The increment after this frame for angular setting of the specified axis in degrees. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' and '_diffrn_scan_frame_axis.angle_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame, and should equal '_diffrn_scan_frame_axis.angle' for that next frame. ; _item.name '_diffrn_scan_frame_axis.angle_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.displacement' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_increment _item_description.description ; The increment for this frame for displacement setting of the specified axis in millimetres. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.displacement_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_rstrt_incr _item_description.description ; The increment for this frame for displacement setting of the specified axis in millimetres. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' and '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame, and should equal '_diffrn_scan_frame_axis.displacement' for that next frame. ; _item.name '_diffrn_scan_frame_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.frame_id _item_description.description ; The value of this data item is the identifier of the frame for which axis settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id . This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame_axis.frame_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes save_ ######################### DEPRECATED CATEGORY ############################## ##################### # DIFFRN_FRAME_DATA # ##################### save_DIFFRN_FRAME_DATA _category.description ; Data items in the DIFFRN_FRAME_DATA category record the details about each frame of data. The items in this category are now in the DIFFRN_DATA_FRAME category. The items in the DIFFRN_FRAME_DATA category are now deprecated. The items from this category are provided as aliases in the 1.0.0 dictionary, but should not be used for new work. The items from the old category are provided in this dictionary for completeness, but should not be used or cited. To avoid confusion, the example has been removed, and the redundant parent child-links to other categories removed. ; _category.id diffrn_frame_data _category.mandatory_code no loop_ _category_key.name '_diffrn_frame_data.id' '_diffrn_frame_data.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; THE DIFFRN_DATA_FRAME category is deprecated and should not be used. ; ; # EXAMPLE REMOVED # ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_frame_data.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.array_id' _item.category_id diffrn_frame_data _item.mandatory_code yes _item_type.code code save_ save__diffrn_frame_data.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.binary_id' _item.category_id diffrn_frame_data _item.mandatory_code implicit _item_type.code int save_ save__diffrn_frame_data.detector_element_id _item_description.description ; This item is a pointer to _diffrn_detector_element.id in the DIFFRN_DETECTOR_ELEMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.detector_element_id' _item.category_id diffrn_frame_data _item.mandatory_code yes _item_type.code code save_ save__diffrn_frame_data.id _item_description.description ; The value of _diffrn_frame_data.id must uniquely identify each complete frame of data. DEPRECATED -- DO NOT USE ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_frame_data.id' diffrn_frame_data yes _item_type.code code save_ ################ END DEPRECATED SECTION ########### #################### ## ITEM_TYPE_LIST ## #################### # # # The regular expressions defined here are not compliant # with the POSIX 1003.2 standard as they include the # '\n' and '\t' special characters. These regular expressions # have been tested using version 0.12 of Richard Stallman's # GNU regular expression library in POSIX mode. # In order to allow presentation of a regular expression # in a text field concatenate any line ending in a backslash # with the following line, after discarding the backslash. # # A formal definition of the '\n' and '\t' special characters # is most properly done in the DDL, but for completeness, please # note that '\n' is the line termination character ('newline') # and '\t' is the horizontal tab character. There is a formal # ambiguity in the use of '\n' for line termination, in that # the intention is that the equivalent machine/OS-dependent line # termination character sequence should be accepted as a match, e.g. # # '\r' (control-M) under MacOS # '\n' (control-J) under Unix # '\r\n' (control-M control-J) under DOS and MS Windows # loop_ _item_type_list.code _item_type_list.primitive_code _item_type_list.construct _item_type_list.detail code char '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words ... ; ucode uchar '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words (case insensitive) ; line char '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types / multi-word items ... ; uline uchar '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types / multi-word items (case insensitive) ; text char '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; text item types / multi-line text ... ; binary char ;\n--CIF-BINARY-FORMAT-SECTION--\n\ [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\ \n--CIF-BINARY-FORMAT-SECTION---- ; ; binary items are presented as MIME-like ascii-encoded sections in an imgCIF. In a CBF, raw octet streams are used to convey the same information. ; int numb '-?[0-9]+' ; int item types are the subset of numbers that are the negative or positive integers. ; float numb '-?(([0-9]+)|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?' ; float item types are the subset of numbers that are the floating numbers. ; any char '.*' ; A catch all for items that may take any form... ; yyyy-mm-dd char ;\ [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9][0-9]\ (T[0-2][0-9]:[0-5][0-9]:[0-5][0-9](.[0-9]+)([+-][0-5][0-9]:[0-5][0-9])) ; ; Standard format for CIF date and time strings (see http://www.iucr.orgiucr-top/cif/spec/datetime.html), consisting of a yyyy-mm-dd date optionally followed by the character "T" followed by a 24-hour clock time, optionally followed by a signed time-zone offset. The IUCr standard has been extended to allow for an optional decimal fraction on the seconds of time. Time is local time if no time-zone offset is given. ; ##################### ## ITEM_UNITS_LIST ## ##################### loop_ _item_units_list.code _item_units_list.detail # 'metres' 'metres' 'centimetres' 'centimetres (metres * 10^( -2))' 'millimetres' 'millimetres (metres * 10^( -3))' 'nanometres' 'nanometres (metres * 10^( -9))' 'angstroms' 'angstroms (metres * 10^(-10))' 'picometres' 'picometres (metres * 10^(-12))' 'femtometres' 'femtometres (metres * 10^(-15))' # 'reciprocal_metres' 'reciprocal metres (metres^(-1))' 'reciprocal_centimetres' 'reciprocal centimetres ((metres * 10^( -2))^(-1))' 'reciprocal_millimetres' 'reciprocal millimetres ((metres * 10^( -3))^(-1))' 'reciprocal_nanometres' 'reciprocal nanometres ((metres * 10^( -9))^(-1))' 'reciprocal_angstroms' 'reciprocal angstroms ((metres * 10^(-10))^(-1))' 'reciprocal_picometres' 'reciprocal picometres ((metres * 10^(-12))^(-1))' # 'nanometres_squared' 'nanometres squared (metres * 10^( -9))^2' 'angstroms_squared' 'angstroms squared (metres * 10^(-10))^2' '8pi2_angstroms_squared' '8pi^2 * angstroms squared (metres * 10^(-10))^2' 'picometres_squared' 'picometres squared (metres * 10^(-12))^2' # 'nanometres_cubed' 'nanometres cubed (metres * 10^( -9))^3' 'angstroms_cubed' 'angstroms cubed (metres * 10^(-10))^3' 'picometres_cubed' 'picometres cubed (metres * 10^(-12))^3' # 'kilopascals' 'kilopascals' 'gigapascals' 'gigapascals' # 'hours' 'hours' 'minutes' 'minutes' 'seconds' 'seconds' 'microseconds' 'microseconds' # 'degrees' 'degrees (of arc)' 'degrees_squared' 'degrees (of arc) squared' # 'degrees_per_minute' 'degrees (of arc) per minute' # 'celsius' 'degrees (of temperature) Celsius' 'kelvins' 'degrees (of temperature) Kelvin' # 'counts' 'counts' 'counts_per_photon' 'counts per photon' # 'electrons' 'electrons' # 'electrons_squared' 'electrons squared' # 'electrons_per_nanometres_cubed' ; electrons per nanometres cubed (electrons/(metres * 10^( -9))^(-3)) ; 'electrons_per_angstroms_cubed' ; electrons per angstroms cubed (electrons/(metres * 10^(-10))^(-3)) ; 'electrons_per_picometres_cubed' ; electrons per picometres cubed (electrons/(metres * 10^(-12))^(-3)) ; 'kilowatts' 'kilowatts' 'milliamperes' 'milliamperes' 'kilovolts' 'kilovolts' # 'arbitrary' ; arbitrary system of units. ; # loop_ _item_units_conversion.from_code _item_units_conversion.to_code _item_units_conversion.operator _item_units_conversion.factor ### 'metres' 'centimetres' '*' 1.0E+02 'metres' 'millimetres' '*' 1.0E+03 'metres' 'nanometres' '*' 1.0E+09 'metres' 'angstroms' '*' 1.0E+10 'metres' 'picometres' '*' 1.0E+12 'metres' 'femtometres' '*' 1.0E+15 # 'centimetres' 'metres' '*' 1.0E-02 'centimetres' 'millimetres' '*' 1.0E+01 'centimetres' 'nanometres' '*' 1.0E+07 'centimetres' 'angstroms' '*' 1.0E+08 'centimetres' 'picometres' '*' 1.0E+10 'centimetres' 'femtometres' '*' 1.0E+13 # 'millimetres' 'metres' '*' 1.0E-03 'millimetres' 'centimetres' '*' 1.0E-01 'millimetres' 'nanometres' '*' 1.0E+06 'millimetres' 'angstroms' '*' 1.0E+07 'millimetres' 'picometres' '*' 1.0E+09 'millimetres' 'femtometres' '*' 1.0E+12 # 'nanometres' 'metres' '*' 1.0E-09 'nanometres' 'centimetres' '*' 1.0E-07 'nanometres' 'millimetres' '*' 1.0E-06 'nanometres' 'angstroms' '*' 1.0E+01 'nanometres' 'picometres' '*' 1.0E+03 'nanometres' 'femtometres' '*' 1.0E+06 # 'angstroms' 'metres' '*' 1.0E-10 'angstroms' 'centimetres' '*' 1.0E-08 'angstroms' 'millimetres' '*' 1.0E-07 'angstroms' 'nanometres' '*' 1.0E-01 'angstroms' 'picometres' '*' 1.0E+02 'angstroms' 'femtometres' '*' 1.0E+05 # 'picometres' 'metres' '*' 1.0E-12 'picometres' 'centimetres' '*' 1.0E-10 'picometres' 'millimetres' '*' 1.0E-09 'picometres' 'nanometres' '*' 1.0E-03 'picometres' 'angstroms' '*' 1.0E-02 'picometres' 'femtometres' '*' 1.0E+03 # 'femtometres' 'metres' '*' 1.0E-15 'femtometres' 'centimetres' '*' 1.0E-13 'femtometres' 'millimetres' '*' 1.0E-12 'femtometres' 'nanometres' '*' 1.0E-06 'femtometres' 'angstroms' '*' 1.0E-05 'femtometres' 'picometres' '*' 1.0E-03 ### 'reciprocal_centimetres' 'reciprocal_metres' '*' 1.0E+02 'reciprocal_centimetres' 'reciprocal_millimetres' '*' 1.0E-01 'reciprocal_centimetres' 'reciprocal_nanometres' '*' 1.0E-07 'reciprocal_centimetres' 'reciprocal_angstroms' '*' 1.0E-08 'reciprocal_centimetres' 'reciprocal_picometres' '*' 1.0E-10 # 'reciprocal_millimetres' 'reciprocal_metres' '*' 1.0E+03 'reciprocal_millimetres' 'reciprocal_centimetres' '*' 1.0E+01 'reciprocal_millimetres' 'reciprocal_nanometres' '*' 1.0E-06 'reciprocal_millimetres' 'reciprocal_angstroms' '*' 1.0E-07 'reciprocal_millimetres' 'reciprocal_picometres' '*' 1.0E-09 # 'reciprocal_nanometres' 'reciprocal_metres' '*' 1.0E+09 'reciprocal_nanometres' 'reciprocal_centimetres' '*' 1.0E+07 'reciprocal_nanometres' 'reciprocal_millimetres' '*' 1.0E+06 'reciprocal_nanometres' 'reciprocal_angstroms' '*' 1.0E-01 'reciprocal_nanometres' 'reciprocal_picometres' '*' 1.0E-03 # 'reciprocal_angstroms' 'reciprocal_metres' '*' 1.0E+10 'reciprocal_angstroms' 'reciprocal_centimetres' '*' 1.0E+08 'reciprocal_angstroms' 'reciprocal_millimetres' '*' 1.0E+07 'reciprocal_angstroms' 'reciprocal_nanometres' '*' 1.0E+01 'reciprocal_angstroms' 'reciprocal_picometres' '*' 1.0E-02 # 'reciprocal_picometres' 'reciprocal_metres' '*' 1.0E+12 'reciprocal_picometres' 'reciprocal_centimetres' '*' 1.0E+10 'reciprocal_picometres' 'reciprocal_millimetres' '*' 1.0E+09 'reciprocal_picometres' 'reciprocal_nanometres' '*' 1.0E+03 'reciprocal_picometres' 'reciprocal_angstroms' '*' 1.0E+01 ### 'nanometres_squared' 'angstroms_squared' '*' 1.0E+02 'nanometres_squared' 'picometres_squared' '*' 1.0E+06 # 'angstroms_squared' 'nanometres_squared' '*' 1.0E-02 'angstroms_squared' 'picometres_squared' '*' 1.0E+04 'angstroms_squared' '8pi2_angstroms_squared' '*' 78.9568 # 'picometres_squared' 'nanometres_squared' '*' 1.0E-06 'picometres_squared' 'angstroms_squared' '*' 1.0E-04 ### 'nanometres_cubed' 'angstroms_cubed' '*' 1.0E+03 'nanometres_cubed' 'picometres_cubed' '*' 1.0E+09 # 'angstroms_cubed' 'nanometres_cubed' '*' 1.0E-03 'angstroms_cubed' 'picometres_cubed' '*' 1.0E+06 # 'picometres_cubed' 'nanometres_cubed' '*' 1.0E-09 'picometres_cubed' 'angstroms_cubed' '*' 1.0E-06 ### 'kilopascals' 'gigapascals' '*' 1.0E-06 'gigapascals' 'kilopascals' '*' 1.0E+06 ### 'hours' 'minutes' '*' 6.0E+01 'hours' 'seconds' '*' 3.6E+03 'hours' 'microseconds' '*' 3.6E+09 # 'minutes' 'hours' '/' 6.0E+01 'minutes' 'seconds' '*' 6.0E+01 'minutes' 'microseconds' '*' 6.0E+07 # 'seconds' 'hours' '/' 3.6E+03 'seconds' 'minutes' '/' 6.0E+01 'seconds' 'microseconds' '*' 1.0E+06 # 'microseconds' 'hours' '/' 3.6E+09 'microseconds' 'minutes' '/' 6.0E+07 'microseconds' 'seconds' '/' 1.0E+06 ### 'celsius' 'kelvins' '-' 273.0 'kelvins' 'celsius' '+' 273.0 ### 'electrons_per_nanometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E+03 'electrons_per_nanometres_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+09 # 'electrons_per_angstroms_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-03 'electrons_per_angstroms_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+06 # 'electrons_per_picometres_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-09 'electrons_per_picometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E-06 ### ######################## ## DICTIONARY_HISTORY ## ######################## loop_ _dictionary_history.version _dictionary_history.update _dictionary_history.revision 1.2.4 2003-07-14 ; Changes as per I. David Brown. + Enhance descriptions in DIFFRN_SCAN_AXIS to make them less dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS. + Provide a copy of the deprecated DIFFRN_FRAME_DATA category for completeness. (HJB) ; 1.2.3 2003-07-03 ; Cleanup to conform to ITVG. + Correct sign error in ..._cubed units. + Correct '_diffrn_radiation.polarisn_norm' range. (HJB) ; 1.2.2 2003-03-10 ; Correction of typos in various DIFFRN_SCAN_AXIS descriptions. (HJB) ; 1.2.1 2003-02-22 ; Correction of ATOM_ for ARRAY_ typos in various descriptions. (HJB) ; 1.2 2003-02-07 ; Corrections to encodings (remove extraneous hyphens) remove extraneous underscore in _array_structure.encoding_type enumeration. Correct typos in items units list. (HJB) ; 1.1.3 2001-04-19 ; Another typo corrections by Wilfred Li, and cleanup by HJB ; 1.1.2 2001-03-06 ; Several typo corrections by Wilfred Li ; 1.1.1 2001-02-16 ; Several typo corrections by JW ; 1.1 2001-02-06 ; Draft resulting from discussions on header for use at NSLS (HJB) + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'. + Add '_diffrn_measurement_axis.measurement_device' and change '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'. + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source', '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm' , '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end', '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr', '_diffrn_scan_axis.displacement_rstrt_incr', '_diffrn_scan_frame_axis.angle_increment', '_diffrn_scan_frame_axis.angle_rstrt_incr', '_diffrn_scan_frame_axis.displacement', '_diffrn_scan_frame_axis.displacement_increment',and '_diffrn_scan_frame_axis.displacement_rstrt_incr'. + Add _diffrn_measurement.device to category key + Update yyyy-mm-dd to allow optional time with fractional seconds for time stamps. + Fix typos caught by RS. + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to al low for coupled axes, as in spiral scans. + Add examples for fairly complete headers thanks to R. Sweet and P. Ellis. ; 1.0 2000-12-21 ; Release version - few typos and tidying up (BM & HJB) + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end of dictionary. + Alphabetize dictionary. ; 0.7.1 2000-09-29 ; Cleanup fixes (JW) + Correct spelling of diffrn_measurement_axis in _axis.id + Correct ordering of uses of _item.mandatory_code and _item_default.value ; 0.7.0 2000-09-09 ; Respond to comments by I. David Brown (HJB) + Added further comments on '\n' and '\t' + Updated ITEM_UNITS_LIST by taking section from mmCIF dictionary and adding metres. Changed all spelling 'meter' to 'metre' throughout. + Added missing enumerations to _array_structure.compression_type and made 'none' the default. + Removed parent-child relationship between _array_structure_list.index and _array_structure_list.precedence . + Improve alphabetization. + Fix _array_intensities_gain.esd related function. + Improved comments in AXIS. + Fixed DIFFRN_FRAME_DATA example. + Removed erroneous DIFFRN_MEASUREMENT example. + Added _diffrn_measurement_axis.id to the category key. ; 0.6.0 1999-01-14 ; Remove redundant information for ENC_NONE data (HJB) + After the D5 remove binary section identifier, size and compression type. + Add Control-L to header. ; 0.5.1 1999-01-03 ; Cleanup of typos and syntax errors (HJB) + Cleanup example details for DIFFRN_SCAN category. + Add missing quote marks for _diffrn_scan.id definition. ; 0.5 1999-01-01 ; Modifications for axis definitions and reduction of binary header (HJB) + Restored _diffrn_detector.diffrn_id to DIFFRN_DETECTOR KEY. + Added AXIS category. + Brought complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories in from cif_mm.dic for clarity. + changed _array_structure.encoding_type from type code to uline and added X-Binary-Element-Type to MIME header. + added detector beam center _diffrn_detector_element.center[1] and _diffrn_detector_element.center[2] + corrected item name of _diffrn_refln.frame_id + replace reference to _array_intensities.undefined by _array_intensities.undefined_value + replace references to _array_intensity.scaling with _array_intensities.scaling + added DIFFRN_SCAN... categories ; 0.4 1998-08-11 ; Modifications to the 0.3 imgCIF draft (HJB) + Reflowed comment lines over 80 characters and corrected typos. + Updated examples and descriptions of MIME encoded data. + Change name to cbfext98.dic. ; 0.3 1998-07-04 ; Modifications for imgCIF (HJB) + Added binary type, which is a text field containing a variant on MIME encoded data. + Changed type of _array_data.data to binary and specified internal structure of raw binary data. + Added _array_data.binary_id, and made _diffrn_frame_data.binary_id and _array_intensities.binary_id into pointers to this item. ; 0.2 1997-12-02 ; Modifications to the CBF draft (JW): + Added category hierarchy for describing frame data developed from discussions at the BNL imgCIF Workshop Oct 1997. The following changes were made in implementing the workshop draft. Category DIFFRN_ARRAY_DATA was renamed to DIFFRN_FRAME_DATA. Category DIFFRN_FRAME_TYPE was renamed to DIFFRN_DETECTOR_ELEMENT. The parent item for _diffrn_frame_data.array_id was changed from array_structure_list.array_id to array_structure.id. Item _diffrn_detector.array_id was deleted. + Added data item _diffrn_frame_data.binary_id to identify data groups within a binary section. The formal identification of the binary section is still fuzzy. ; 0.1 1997-01-24 ; First draft of this dictionary in DDL 2.1 compliant format by John Westbrook (JW). This version was adapted from the Crystallographic Binary File (CBF) Format Draft Proposal provided by Andy Hammersley (AH). Modifications to the CBF draft (JW): + In this version the array description has been cast in the categories ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. These categories have been generalized to describe array data of arbitrary dimension. + Array data in this description are contained in the category ARRAY_DATA . This departs from the CBF notion of data existing in some special comment. In this description, data is handled as an ordinary data item encapsulated in a character data type. Although handling binary data this manner deviates from CIF conventions, it does not violate any DDL 2.1 rules. DDL 2.1 regular expressions can be used to define the binary representation which will permit some level of data validation. In this version, the placeholder type code "any" has been used. This translates to a regular expression which will match any pattern. It should be noted that DDL 2.1 already supports array data objects although these have not been used in the current mmCIF dictionary. It may be possible to use the DDL 2.1 ITEM_STRUCTURE and ITEM_STRUCTURE_LIST categories to provide the information that is carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. By moving the array structure to the DDL level it would be possible to define an array type as well as a regular expression defining the data format. + Multiple array sections can be properly handled within a single datablock. ; #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof ./CBFlib-0.9.2.2/doc/cbf_definition_rev.txt0000644000076500007650000017722711603702115016742 0ustar yayayaya Proposed revised DRAFT CBF/imgCIF DEFINITION Revisions by Herbert J. Bernstein Bernstein + Sons, P.O. Box 177, Bellport, NY 11713-0177 yaya@bernstein-plus-sons.com based on DRAFT CBF DEFINITION by Andy Hammersley European Synchrotron Radiation Facility, BP 200, Grenoble, 38043, CEDEX, France hammersley@esrf.fr ------------------------------------------------------------------------ This document and the CBF definitions are still subject to change. This document is a draft proposal for discussion. This is an version of the CBF draft proposal, revised to include a coordinated pure ASCII ImgCIF definition, based on the Draft CBF Definition by Andy Hammersley, the work done at the Brookhaven imgCIF workshop, and the work on "CBFLIB: An ANSI-C API for Crystallographic Binary File" by Paul Ellis, ellis@SSRL.SLAC.STANFORD.EDU. For the binary CBF format, a "binary-string" approach, as proposed by Paul Ellis, is used, while for the ASCII ImgCIF format, binary information is encoded using a variant on MIME (Multipurpose Internet Mail Extensions) format, which makes the CBF and ImgCIF formats very similar. We have included an updated version of John Westbrook's DDL2-compliant CBF Extensions Dictionary, of Paul Ellis's CBFLIB manual, and examples of CBF/imgCIF files. This is just a proposal. My apologies in advance, especially to Andy, John and especially to Paul for whatever I may have muddled here. Please be careful about basing any code on this until and unless there has been a general agreement. ------------------------------------------------------------------------ ------------------------------------------------------------------------ Notices Please read the NOTICES, which are part of this package, before making use of this software. ------------------------------------------------------------------------ ------------------------------------------------------------------------ Most of this document is adapted from Andy's, so we follow his convention by "...[separating] the definition from comments on discussion items by using round brackets to refer to notes kept separate from the main text e.g. (1) refers to point 1 in the notes section.". Major differences from Andy's draft are noted by comments bracketed by <<< >>> pairs. ------------------------------------------------------------------------ A Draft Proposal for A Combined Crystallographic Binary File (CBF) and Image-supporting Crystallographic Information File (ImgCIF) Format ABSTRACT This document describes a proposal for a combined Crystallographic Binary File (CBF) and Image-supporting Crystallographic Information File (ImgCIF) format; a simple self-describing binary format for efficient transport and archiving of experimental data for the crystallographic community, and well as for the presentation of other image data, such as PICT, GIFs and JPEG, within publication CIFs. With minor differences, both the binary CBF format and the ASCII ImgCIF have a similar, CIF-like structure. All the information other than actual binary data is presented as ASCII strings in both formats. The formats differ only in the handling of line termination and the actual presentation of the binary data of an image. The CBF format, presents binary information as a raw string of octets, while the ImgCIF format presents the binary information as ASCII-encoded lines. The format of the binary file, and the new CIF data- items are defined. NOTE: o All numbers are decimal unless otherwise stated. o The terms octet and byte refer to a group of eight bits. 1.0 INTRODUCTION The Crystallographic Binary File (CBF) format is a complementary format to the Crystallographic Information File (CIF) [1], supporting efficient storage of large quantities of experimental data in a self-describing binary format (1). <<>> It is our expectation that, for large images, the raw binary CBF format will be used both with in laboratories and for interchange among collaborating groups. For smaller chunks of binary data, either format should be be suitable, with the ASCII ImgCIF format being more appropriate for interchange and archiving. The initial aim is to support efficient storage of raw experimental data from area-detectors (images) with no loss of information compared to existing formats. The format should be both efficient in terms of writing and reading speeds, and in terms of stored file sizes, and should be simple enough to be easily coded, or ported to new computer systems. Flexibility and extensibility are required, and later the storage of other forms of data may be added without affecting the present definitions. The aims are achieved by a simple file format, consisting of lines of ASCII information defining information about the binary data as CIF tag-value pairs and tables, and either raw octets of binary data in delimited sections, or ASCII-based presentations of the same binary information in similarly delimited sections. The present version of the format only tries to deal with simple Cartesian data. This is essentially the "raw" data from detectors that is typically stored in commercial formats or individual formats internal to particular institutes, but could be other forms of data. It is hoped that CBF can replace individual laboratory or institute formats for "home" built detector systems, be used as a inter-program data exchange format, and may be offered as an output choice by a number of commercial detector manufacturers specialising in X-ray and other detector systems. This format does not imply any particular demands on processing software nor on the manner in which such software should work. Definitions of units, coordinate systems, etc. may quite different. The clear precise definitions within CIF, and hence CBF, help, when necessary, to convert from one system to another. Whilst no strict demands are made, it is clearly to be hoped that software will make as much use as is reasonable of information relevant to the processing which is stored within the file. It is expected that processing software will give clear and informative error messages when they encounter problems within CBF's or do not support necessary mechanisms for inputting a file. 1.1 CBF and "imgCIF" CBF and "imgCIF" are two aspects of the same format. Since CIF's are pure ASCII text files, a separate binary format is needed to be defined to allow the combination of pseudo-ASCII sections and binary data sections. The binary file format is the Crystallographic Binary File (CBF). The ASCII sections are very close to the CIF standard, but must use operating system independent "line separators". In describing the ASCII sections, we use the notation "\r\n" (for the pair of characters carriage return, line-feed) for a line terminator would allow the ASCII sections to viewed with standard system utilities on a very wide range of operating systems. However, an API to read the binary format must accept any of the following three alternative line terminators as the end of an ascii line: "\r", "\n" or "\r\n". An API to write CBF should write "\r\n" as the line terminator, if at all possible. imgCIF is also the name of the CIF dictionary which contains the terms specific to describing the binary data (the orginal, designed by John Westbrook, without the modifications in this proposal is avaliable from http://ndbserver.rutgers.edu/NDB/mmcif. Thus a CBF or ImgCIF files uses data names from the imgCIF dictionary and other CIF dictionaries. 2.0 A SIMPLE EXAMPLE Before fully describing the format we start by showing a simple, but important and complete usage of the format; that of storing a single detector image in a file together with a small amount of useful auxiliary information. It is intened to be a useful example for people who like working from examples, as opposed to full definitions. It should also serve as an introduction or overview of the format defintion. This example uses CIF DDL2 based dictionary items. The example is an image of 768 by 512 pixels stored as 16 bit unsigned integers, in little endian byte order. (This is the native byte ordering on a PC.) The pixel sizes are 100.5 by 99.5 microns. Comment lines starting with a hash sign (#) are used to explain the contents of the header. Only the ASCII part of the file is shown, but comments are used to describe the start of the binary section. First the file is shown with the minimum of comments that a typical outputting program might add. Then it is repeated, but with "over- commenting" to explain the format. Here is how a file might appear if listed on a PC or on a Unix system using "more": ###CBF: VERSION 0.3 # Data block for image 1 data_image_1 _entry.id 'image_1' # Sample details _chemical.entry_id 'image_1' _chemical.name_common 'Protein X' # Experimental details _exptl_crystal.id 'CX-1A' _exptl_crystal.colour 'pale yellow' _diffrn.id DS1 _diffrn.crystal_id 'CX-1A' _diffrn_measurement.diffrn_id DS1 _diffrn_measurement.method Oscillation _diffrn_measurement.sample_detector_distance 0.15 _diffrn_radiation_wavelength.id L1 _diffrn_radiation_wavelength.wavelength 0.7653 _diffrn_radiation_wavelength.wt 1.0 _diffrn_radiation.diffrn_id DS1 _diffrn_radiation.wavelength_id L1 _diffrn_source.diffrn_id DS1 _diffrn_source.source synchrotron _diffrn_source.type 'ESRF BM-14' _diffrn_detector.diffrn_id DS1 _diffrn_detector.id ESRFCCD1 _diffrn_detector.detector CCD _diffrn_detector.type 'ESRF Be XRII/CCD' _diffrn_detector_element.id 1 _diffrn_detector_element.detector_id ESRFCCD1 _diffrn_frame_data.id F1 _diffrn_frame_data.detector_element_id 1 _diffrn_frame_data.array_id 'image_1' _diffrn_frame_data.binary_id 1 # Define image storage mechanism ###<<>> # loop_ _array_structure.array_id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order image_1 unsigned_16_bit_integer none little_endian loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.undefined_value _array_intensities.overload_value image_1 1 linear 0 65535 # Define dimensionality and element rastering loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction image_1 1 768 1 increasing image_1 2 512 2 decreasing loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size image_1 1 100.5e-6 image_1 2 99.5e-6 ###<<>> loop_ _array_data.id _array_data.binary_id _array_data.data image_1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BINARY X-Binary-ID: 1 Content-MD5: jGmkxiOetd9T/Np4NufAmA== START_OF_BIN *************'9*****`********* ... [This is where the raw binary data would be -- we can't print it here] --CIF-BINARY-FORMAT-SECTION---- ; <<>> Here the file is shown again, but this time with many comment lines added to explain the format: ###CBF: VERSION 0.3 # This line starting with a "#" is a CIF and CBF comment line, # but the first line with the three "#"s is a CBF identifier. # (a "magic number") The text "###_CBF: VERSION" identifies # the file as a CBF and must be present as the very first line of # every CBF file. Following "VERSION" is the version number of the # file, which is the corresponding version of the CBF/imgCIF # extensions dictionary and supporting documentation. A version # 0.3 CIF should be readable by any program which # fully supports the version 1.0 CBF definitions. # Comment lines and white space (blanks and new lines) may appear # anywhere outside the binary sections. # In a CIF, the descriptive tags and values may be presented in # any convenient order, e.g. the data could come first, and the # parameters necessary to interpret the data could come later. # This order-independent convention holds for an imgCIF file, but # for a CBF, all the tags and values describing binary data (i.e. # all the tags other than those in the ARRAY_DATA category) should # be presented before the binary data, in the form of a header. # This does not mean that there cannot be more useful information # after the binary data. There could be another full header and # more blocks of binary data. All we are saying is that, in # the interest of efficiency in processing a CBF, the parameters # that relate to a particular block of binary data must appear # earlier in the CBF than the block itself. # The header begins with "data_", which is the CIF token to identify # a data block. Within a data block, any given tag may be presented # only once, either directly with an immediately following value, # or as one of the column headings for the rows of a table. If you will # need to resuse the same tag, you will have to start a new data block. # Data block for image 1 data_image_1 # We've chosen to call this data block 'image_1', but this was an # arbitary choice. Within a data block a data item may only be used # once. _entry.id 'image_1' # Sample details _chemical.entry_id 'image_1' _chemical.name_common 'Protein X' # The apostrophes enclose the string which contains a space. # A double quote (") could have been used, just as well. # There is also a third way to quote string, with the string # "\n;", i.e. with a semicolon at the beginning of a line # which allows multi-lined strings to be presented. We'll # use that form of text quotation for the binary data. # Experimental details _exptl_crystal.id 'CX-1A' _exptl_crystal.colour 'pale yellow' _diffrn.id DS1 _diffrn.crystal_id 'CX-1A' _diffrn_measurement.diffrn_id DS1 _diffrn_measurement.method Oscillation _diffrn_measurement.sample_detector_distance 0.15 _diffrn_radiation_wavelength.id L1 _diffrn_radiation_wavelength.wavelength 0.7653 _diffrn_radiation_wavelength.wt 1.0 _diffrn_radiation.diffrn_id DS1 _diffrn_radiation.wavelength_id L1 _diffrn_source.diffrn_id DS1 _diffrn_source.source synchrotron _diffrn_source.type 'ESRF BM-14' _diffrn_detector.diffrn_id DS1 _diffrn_detector.id ESRFCCD1 _diffrn_detector.detector CCD _diffrn_detector.type 'ESRF Be XRII/CCD' _diffrn_detector_element.id 1 _diffrn_detector_element.detector_id ESRFCCD1 _diffrn_frame_data.id F1 _diffrn_frame_data.detector_element_id 1 _diffrn_frame_data.array_id 'image_1' _diffrn_frame_data.binary_id 1 # Many more data items can be defined, but the above gives the idea # of a useful minimum set (but not minimum in the sense of compulsory, # the above data items are optional in a CIF or CBF). # Define image storage mechanism # # Notice that we did not include a binary ID here. The idea of # the ARRAY_STRUCTURE category is to present parameters which # could be common to multiple blocks of binary data, which # would all have the same array ID, but would have distinct # binary ID's loop_ _array_structure.array_id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order image_1 unsigned_16_bit_integer none little_endian # On the other hand, we do provide a binary ID for # ARRAY INTENSITIES, since there might be different # paremeters for each binary block. We could have # left it out here, since there is only one block and # the default binary ID happens to be 1 loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.undefined_value _array_intensities.overload_value image_1 1 linear 0 65535 # Define dimensionality and element rastering # Here the size of the image and the ordering (rastering) of the # data elements is defined. The CIF "loop_" structure is used to # define different dimensions. (It can be used for defining multiple # images.) loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction image_1 1 768 1 increasing image_1 2 512 2 decreasing loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size image_1 1 100.5e-6 image_1 2 99.5e-6 # The "array_id" identifies data items belong to the same array. Here # we have chosen the name "image_1", but another name could have been # used, so long as it's used consistently. The "index" component refers # to the dimension being defined, and the "dimension" component defines # the number of elements in that dimension. The "precedence" component # defines which precedence of rastering of the data. In this case the # first dimension is the faster changing dimension. The "direction" # component tells us the direction in which the data rasters within a # dimension. Here the data rasters faster from minimum elements towards # the maximum element ("increasing") in the first dimension, and more # slowly from the maximum element towards the minimum element in the # second dimension. (This is the default rastering order.) # The storage of the binary data is now fully defined. # Further data items could be defined, but we are ready to # present the data. That is done with the ARRAY_DATA category. # The start of this category marks the end of the header # (Well, almost the end, there is a bit more header information # below). loop_ _array_data.id _array_data.binary_id _array_data.data image_1 1 # The binary data itself will come just a little further down, # as the essential part of the value of _array_data.data, which begins # as semicolon-quoted text. The line immediately after the # line with the semicolon is a MIME boundary marker. As for # all MIME boundary markers, it begins with "--". The next # few lines are MIME headers, describing some useful information # we will need to process the binary section. MIME headers can # appear in different orders, and can be very confusing (look # at the raw contents of a email message with attachments), but # there is only one header which is has to be understood to # process a CBF; "Content-Transfer-Encoding". If the value given # on this header is "BINARY", this is a CBF and the data will # be presented as raw binary, containing a count (in yet another # header we did not tell you about yet) so we'll know when to # start looking for more information. # ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BINARY X-Binary-ID: 1 X-Binary-Size: 2432840 Content-MD5: jGmkxiOetd9T/Np4NufAmA== START_OF_BIN *************'9*****`********* ... [This is where the raw binary data would be -- we can't print it here] --CIF-BINARY-FORMAT-SECTION---- ; # After the last octet (i.e. byte) of the binary data, there is a # special trailer "\n--CIF-BINARY-FORMAT-SECTION----\n;" # which repeats the initial bounday marker with an extra "--" # at the end (a MIME convention for the last boundary marker), and # then the closing semicolon quote for a text section. This # is essential in an imgCIF, and we include it in a CBF for consistency. # OVERVIEW OF THE FORMAT This section describes the major "components" of the CBF format. 1. CBF is a binary file, containing self-describing array data e.g. one or more images, and auxiliary data e.g. describing the experiment. 2. Except for the handling of line terminators, the way binary data is presented, and more liberal rules in ordinger information, an ASCII imgCIF file is the same as a CBF binary file. 3. A CBF consists of pseudo-ASCII text header sections, which are "lines" of no more tha 80 ASCII characters separated by "line separators" which are the pair of ASCII characters carriage return and line-feed (ASCII 13, ASCII 10), followed by zero, one, or more binary sections presented as "binary strings". This structure may be repeated. 4. An imgCIF consists of ASCII lines of no more than 80 characters using the the normal line termination conventions of the current system (e.g. ASCII 10 in UNIX) with MIME-encoded binary strings at any appropriate point in the file. 5. The very start of the file has an identification item (magic number) (2). This item also describes the CBF version or level. The identifier is: ###CBF: VERSION which must always be present so that a program can easily identify whether or not a file is a CBF, by simply inputting the first 15 characters. (The space is a blank (ASCII 32) and not a tab. All identifier characters are uppercase only.) The first hash means that this line within a CIF would be a comment line, but the three hashes mean that this is a line describing the binary file layout for CBF. (All CBF internal identifiers start with the three hashes, and all other must immediately follow a "line separator".) No whitespace may precede the first hash sign. Following the file identifier is the version number of the file. e.g. the full line might appear as: ###CBF: VERSION 0.3 The version number must be separated from the file identifier characters by whitespace e.g. a blank (ASCII 32). The version number is defined as a major version number and minor version number separated by the decimal point. A change in the major version may well mean that a program for the previous version cannot input the new version as some major change has occurred to CBF (3). A change in the minor version may also mean incompatibility, if the CBF has been written using some new feature. e.g. a new form of linearity scaling may be specified and this would be considered a minor version change. A file containing the new feature would not be readable by a program supporting only an older version of the format. <<< Until we reach major version 1 (the first official release), the rules are a little more relaxed. While there will be some effort at upwards compatability, in order to ensure a reasonable agreed specification without too many strange artifacts, changes between minor versions may, unfortunately, introduce incompatabilities which require program changes to still read CBFs compliant with an earlier draft, e.g. the change in the "magic number" and from binary sections to binary strings in going to version 0.3. Naturally, such changes should be sufficiently well documented to allow for conversions.>>> 6. Header Information: a. The start of an header section is delimited by the usual CIF "data_" token. Optionally, the formerly specified header identifier, ###_START_OF_HEADER may be used before the "data_" taken, followed by the carriage return, line-feed pair, as an aid in debugging, but it is no longer required. (Naturally, another carriage return, line-feed pair should immediately precedes this and all other CBF identifiers, with the exception of the CBF file identifier which is at the very start of the file.) b. A header section, including the identification items which delimit it, uses only ASCII characters, and is divided into "lines". The "line separator" symbols, "\r\n" (carriage return, line-feed) are the same regardless of the operating system on which the file is written. (This is an importance difference with CIF, but must be so, as the file contains binary data, so cannot be translated from one O.S. to another, which is the case for ASCII text files.) While a properly functioning CBF API should write the full "\r\n" line separator, it should recognize any of three sequences "\r", "\n", "\r\n" as valid line separators, so that hand-edited headers will not be rejected. c. The header section within the delimiting identification items obeys all CIF rules [1] with the exception of the line separators. e.g. o "Lines" are a maximum of 80 characters long. (For CBF it is probably best to allow for this maximum to be larger.) o The tokens "data_" and "loop_" have special meaning to CIF, and should not be used except in their indicated places. The tokens "save_", "stop_" and "global_" also have special meaning to CIF's parent language, STAR, and also should not be used. o All data names (tags) start with an underscore character. o The hash symbol (#) (outside a character string) means that all text up to the line separator is a comment. o Whitespace outside of character strings is not significant. o Data names are case insensitive. o The data item follows the data name separator, and may be of one of two types: character string (char) or number (numb). (The type is specified for each data name.) o Character strings may be delimited with single of double quotes, or blocks of text may be delimited by semi-colons occurring as the first character on a line. o The "loop_" mechanism allows a data name to have multiple values. Immediately following the "loop_", one or more data names are listed without their values, as column headings. Then one or more rows of values are given. Any CIF data name may occur within the header section. d. A single header section may contain one or more data blocks (CIF terminology). e. The end of the header information is marked by comin the tags from the "ARRAY_DATA" category. The formerly specifier special identifier: ###_END_OF_HEADER followed by carriage return, line-feed, may be used as well as an aid to debugging, but it is not required. 7. The header information must contain sufficient data names to fully describe the binary data section(s) which follow(s). 8. Binary Information: <<>> a. Before getting to the binary data, itself, there are some preliminaries to allow a smooth transition from the conventions of CIF to those of raw streams of "octets" (8-bit bytes). The binary data is given as the essential part of a specially formatted semicolon-delimited CIF multi-line text string. This text string is the value associated with the tag "_array_data.data&. b. Within that text string, the conventions developed for transmitting email messages including binary attachments are followed. There is secondary ASCII header information, formatted as Multipurpose Internet Mail Extensions (MIME) headers (see RFCs 2045-49 by Freed, et. al). The bounday marker for the beginning of all this is the special string --CIF-BINARY-FORMAT-SECTION-- at the beginning of a line. The initial "--" says that this is a MIME boundary. We cannot put "###" in front of it and conform to MIME conventions. Immediately after the boundary marker are MIME headers, describing some useful information we will need to process the binary section. MIME headers can appear in different orders, and can be very confusing (look at the raw contents of a email message with attachments), but there is only one header which is has to be understood to process a CBF; "Content-Transfer-Encoding". If the value given on this header is "BINARY", this is a CBF and the data will be presented as raw binary, containing a count (in yet another header we did not tell you about yet) so we'll know when to start looking for more information. If the value given for "Content-Tranfer-Encoding" is one of the real encodings: "BASE64", "QUOTED-PRINTABLE", "X-BASE8", "X-BASE10" or "X-BASE16", this file is an imgCIF, and we'll need some other the other headers to process the encoded binary data properly. It is a good practice to give headers in all cases The "Content-Type" header tells us what sort of data we have (almost always "application/octet-stream" for a miscellaneous stream of binary data) and, optionally, the conversions that were applied to the original data. In this case we have compressed the data with the "CBF-PACKED" algorithm. The optional "X-Binary-ID" header should contain the same value as was given for _array_data.binary-id above. The "X-Binary-Size" header gives the expected size of the binary data. This is the size after any compressions, but before any ascii encodings. This is useful in making a simple check for a missing portion of this file. The optional "Content-MD5" header provides a much more sophisticated check on the integrity of the binary data. In a CBF, the raw binary data begins after an empty line terminating the MIME headers and after the START_OF_BIN identifier. "START_OF_BIN" contains bytes to separate the "ASCII" lines from the binary data, bytes to try to stop the listing of the header, bytes which define the binary identifier which should match the "binary_id" defined in the header, and bytes which define the length of the binary section. Octet Hex Decimal Purpose 1 1A 26 (ctrl-Z) Stop listings in MS-DOS 2 04 04 (Ctrl-D) Stop listings in UNIX 3 D5 213 Binary section begins 4..11 Binary Section Identifier (See _array_data.binary_id) 64-bit, little endian 12..19 8+ the size (n) of the binary section in octets (i.e. the offset from octet 20 to the first byte following the data) 20..27 Compression type: CBF_NONE 0x0040 (64) CBF_CANONICAL 0x0050 (80) CBF_PACKED 0x0060 (96) ... &NBSP; 28..28+n-1 Binary data (n octets) Only bytes 28..28+n-1 are encoded for an imgCIF file using the indicated Content-Transfer-Encoding. The binary characters serve specific purposes: o The Control-Z will stop the listing of the file on MS-DOS type operating systems. o The Control-D will stop the listing of the file on Unix type operating systems. o The unsigned byte value 213 (decimal) is binary 11010101. (Octal 325, and hexadecimal D5). This has the eighth bit set so can be used for error checking on 7-bit transmission. It is also asymmetric, but with the first bit also set in the case that the bit order could be reversed (which is not a known concern). o (The carriage return, line-feed pair before the START_OF_BIN and other lines can also be used to check that the file has not been corrupted e.g. by being sent by ftp in ASCII mode.) o Bytes 4-11 define the binary id of the binary data. This id is also used within the header sections, so that binary data definitions can be matched to the binary data sections. 64-bits allows many many more binary data sections to be addressed than can conceivably be needed. o Bytes 12-19 define the length in bytes of the binary data plus the flag word for the compression type (8 bytes). This information is critical to recovering alignment with the CIF world, since the binary data could easily include bytes which look like "\n;" or the boundary marker. The use of 64 bits provides for enormous expansion from present images sizes, but volume and higher dimensional data may need more than 32-bit sizes in the future. It is tempting to set this value to zero if this is the last binary information or header information in the file, but you could cause unpleasant warnings in code that expects to be able to find the rest of a CIF. This allows a program writing, for example, a single compressed image to avoid having to rewind the file to write the size of the compressed data. (For small files compression within memory may be practical, and this may not be an issue. However very large files exist where writing the compressed data "on the fly" may be the only realistic method.) This should only be done for internal use within a group, and a cleanup utility should be used to restore the missing data before exporting it to groups which may have difficulty processing this truncated file. In any case, it is recommended that this value be set, as it permits concatenation of files, and a file with a zero for this field is not a valid CBF. Since the data may have been compressed, knowing the numbers of elements and size of each element does not necessarily tell a program how many bytes to jump over, so here it is stored explicitly. This also means that the reading program does not have to decode information in the header section to move through the file. Bytes 20-27 hold the flag for the compression type. At present three are defined: CBF_NONE (for no compression), CBF_CANONICAL (for and entropy-coding scheme based on the canonical-code algorithm described by Moffat, et al. (International Journal of High Speed Electronics and Systems, Vol 8, No 1 (1997) 179-231)) and CBF_PACKED for a CCP4-style packing scheme. Flags for other compression schemes, such as the two in this document will be added to this list in the future. c. The "line separator" immediately precedes the "start of binary identifier", but blank spaces may be added prior to the preceding "line separator" if desired (e.g. to force word or block alignment). d. The binary data does not have to completely fill the bytes defined by the byte length value, but clearly cannot be greater than this value (except when the value zero has been stored, which means that the size is unknown, and no other headers follow). The values of any unused bytes are undefined. e. At exactly the byte following the full binary section as defined by the length value is the end of binary section identifier. This consists of the carriage return / line feed pair followed by: --CIF-BINARY-FORMAT-SECTION-- ; with each of these lines followed by the carriage return / line feed pair. This brings us back into a normal CIF environment The first "line separator" separates the binary data from the pseudo-ASCII line. This identifier is in a sense redundant since the binary data length value tells the a program how many bytes to jump over to the end of the binary data. However, this redundancy has been deliberately added for error checking, and for possible file recovery in the case of a corrupted file. This identifier must be present at the end of every block of binary data. 9. Whitespace may be used within the pseudo-ASCII sections prior to the "start of binary section" identifier to align the start binary data sections to word or block boundaries. Similar use may be made of unused bytes in binary sections. However, no blank lines should be introduced among the MIME headers, since that would terminate processing of those headers and start the scan for binary data. However, in general no guarantee is made of block nor word alignment in a CBF of unknown origin. 10. The end of the file need not be not explicitly indicated, but including a comment of the form: ###_END_OF_CBF (including the carriage return, line-feed pair) can help in debugging. 11. All binary data described in a single data block must follow the header section prior to another data block, or the end of the file. The binary identifier values used within a given data block section, and hence the binary data must be unique for any given array_id, and, it would be best to make them truly unique. A different data block may reuse binary identifier values. (This allows concatenation of files without re-numbering the binary identifiers, and provides a certain level of localization of data within the file, to avoid programs having to search potentially huge files for missing binary sections.) 12. The recommended file extension for a CBF is: cbf This allows users to recognise file types easily, and gives programs a chance to "know" the file type without having to prompt the user. Although they should check for at least the file identifier to ensure that the file type is indeed a CBF. 13. The recommended file extensions for imgCIF are: icf or cif (use of "cif" subject to IUCr approval). 14. CBF format files are binary files and when ftp is used to transfer files between different computer systems "binary" or "image" mode transfer should be selected. 15. imgCIF files are ASCII files and when ftp is used to transfer files between different computer systems "ascii" transfer should be selected. 3.1 SIMPLE EXAMPLE OF THE ORDERING OF IDENTIFIERS Here only the ASCII part of the file structuring identifiers is shown. The CIF data items are not shown, apart from the "data_" identifier which indicates the beginning of a data block. This shows the structuring of a simple example e.g. one header section followed by one binary section. Such as could be used to store a single image. ###CBF: VERSION 0.3 data_ ### ... various CIF tags and values here loop_ array_data.id array_data.binary_id array_data.data image_1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BINARY X-Binary-ID: 1 Content-MD5: jGmkxiOetd9T/Np4NufAmA== START_OF_BIN *************'9*****`********* ... [This is where the raw binary data would be -- we can't print it here] --CIF-BINARY-FORMAT-SECTION---- ; ###_END_OF_CBF 3.2 MORE COMPLICATED EXAMPLE OF THE ORDERING OF IDENTIFIERS Here only the ASCII part of the file structuring identifiers is shown. The CIF data items are not shown, apart from the "data_" identifier which indicates the beginning of a data block. This shows the a possible structuring of a more complicated example. Two header sections, the first contains two data blocks and defines three binary sections. CIF comment lines, starting with a hash (#) are used to example the structure. ###CBF: VERSION 0.3 # A comment cannot appear before the file identifier, but can appear # anywhere else, except within the binary sections. # Here the first data block starts data_ ### ... various CIF tags and values here ### but none that define array data items # The "data_" identifier finishes the first data block and starts the # second data_ ### ... various CIF tags and values here ### including ones that define array data items loop_ array_data.id array_data.binary_id array_data.data image_1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BINARY X-Binary-ID: 1 Content-MD5: jGmkxiOetd9T/Np4NufAmA== START_OF_BIN *************'9*****`********* ... [This is where the raw binary data would be -- we can't print it here] --CIF-BINARY-FORMAT-SECTION---- ; # Following the "end of binary" identifier the file is pseudo-ASCII # again, so comments are valid up to the next "start of binary" # identifier. Note that we have bumped the binary ID. image_1 2 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BINARY X-Binary-ID: 2 Content-MD5: xR5kxiOetd9T/Nr5vMfAmA== START_OF_BIN *************'9*****`********* ... [This is where the raw binary data would be -- we can't print it here] --CIF-BINARY-FORMAT-SECTION---- ; # Third binary section, note that we have a new array id. image_2 3 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BINARY X-Binary-ID: 3 Content-MD5: yS5kxiOetd9T/NrqTLfAmA== START_OF_BIN *************'9*****`********* ... [This is where the raw binary data would be -- we can't print it here] --CIF-BINARY-FORMAT-SECTION---- ; # Second Header section data_ ### ... various CIF tags and values here ### including ones that define array data items # Since we only have one block left, we won't use a loop array_data.id image array_data.binary_id 1 array_data.data # Note that I can put a comment here ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BINARY X-Binary-ID: 1 Content-MD5: fooxiOetd9T/serNufAmA== START_OF_BIN *************'9*****`********* ... [This is where the raw binary data would be -- we can't print it here] --CIF-BINARY-FORMAT-SECTION---- ; ###_END_OF_CBF DATA NAME CATEGORIES John Westbrook has proposed a number of data name categories as part of his DDL2 based "imgCIF" dictionary. This category list may be expanded to cover a structuring of the often multiple data-sets which might be used in a structurial investigation. Here we only consider the categories concerned with storing an image (or other N-dimensional topographically regular cartesian grid). The _array_* categories cover all data names concerned with the storage of images or regular array data. Data names from any of the existing categories may be relevant as auxiliary information in the header section, but data names from the _diffrn_ category, are likely to be the most relevant, and a number of new data names in this category are necessary. The "array" Class of Binary Data The "array" class is used to store regular arrays of data values, such as 1-D histograms, area-detector data, series of area-detector data, and volume data. Normally such data is regularly spaced in space or time, however spatial distorted data could nevertheless be stored in such a format. There is only one data "value" stored per lattice position, although that value may be of type complex. The "array" class is defined by data names from the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST categories. Here is a short summary of the data names and their purposes. * _array_structure.array_id: Alpha numeric identifier for the array structure * _array_structure.compression_type: Type of data compression used * _array_structure.byte_order: Order of bytes for multi-byte integer or reals * _array_structure.encoding_type: Native data type used to store elements. e.g. "unsigned_16_bit_integer" is used if the stored image was 16 bit unsigned integer values, regardless of any compression scheme used. "Array" Dimensions and Element Rastering and Orientation The array dimension sizes, i.e. the number of elements in each dimension are defined by _array_structure_list.dimension. Which takes an integer value. This is used in a loop together with the _array_structure_list.index item to define the different dimensions for one or more arrays. Fundamental to treating a long line of data values as a 2-D image or an N-dimensional volume or hyper-volume is the knowledge of the manner in which the values need to be wrapped. For the raster orientation to be meaningful we define the sense of the view: For a detector image the sense of the view is defined as that looking from the crystal towards the detector. (For the present we consider only an equatorial plane geometry, with 2-theta = 0; the detector as being vertically mounted.) The rastering is defined by the three data names _array_structure_list.index, _array_structure_list.precedence, and _array_structure_list.direction data names. index refers to the dimension index i.e. In an image 1 refers to the X-direction (horizontal), 2 refers to the Y-direction (vertical). precedence refers to the order in which the data in wrapped. direction refers the direction of the rastering for that index. We define a preferred rastering orientation, which is the default if the keyword is not defined. This is with the start in the upper-left-hand corner and the fastest changing direction for the rastering horizontally, and the slower change from top to bottom. (Note: With off-line scanners the rastering type depending on which way round the imaging plate or film is entered into the scanner. Care may need to be taken to make this consistent.) "Array_Structure" Examples To define an image array of 1300 times 1200 elements, with the raster faster in the first dimension, from left to right, and slower in the second dimension from top to bottom, the following header section might be used: # Define image size and rastering loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction image_1 1 1300 1 increasing image_1 2 1200 2 decreasing To define two arrays, the first a volume of 100 times 100 times 50 elements, fastest changing in the first dimension, from left to right, changing from bottom to top in the second dimension, and slowest changing in the third dimension from front to back; the second an image of 1024 times 1280 pixels, with the second dimension changing fastest from top to bottom, and the first dimension changing slower from left to right; the following header section might be used: # Define array sizes and rasterings loop_ _ARRAY_STRUCTURE_LIST.ARRAY_ID _ARRAY_STRUCTURE_LIST.INDEX _ARRAY_STRUCTURE_LIST.DIMENSION _array_structure.precedence _array_structure.direction volume_a 1 100 1 increasing volume_a 2 100 2 increasing volume_a 3 50 3 increasing slice_1 1 1024 2 increasing slice_1 2 1280 1 decreasing "Array" Element Intensity Scaling Existing data storage formats use a wide variety of methods for storing physical intensities as element values. The simplest is a linear relationship, but square root and logarithm scaling methods have attractions and are used. Additionally some formats use a lower dynamic range to store the vast majority of element values, and use some other mechanism to store the elements which over-flow this limited dynamic range. The problem of limited dynamic range storage is solved by the data compression methods byte_offsets and predictor_huffman (see next Section), but the possibility of defining non-linear scaling must also be provided. The _array_intensities.linearity data item specifies how the intensity scaling is defined. Apart from linear scaling, which is specified by the value linear, two other methods are available to specify the scaling. One is to refer to the detector system, and then knowledge of the manufacturers method will either be known or not by a program. This has the advantage that any system can be easily accommodated, but requires external knowledge of the scaling system. The recommended alternative is to define a number of standard intensity linearity scaling methods, with additional data items when needed. A number of standard methods are defined by _array_intensities.linearity values: offset, scaling_offset, sqrt_scaled, and logarithmic_scaled. The "offset" methods require the data item _array_intensities.offset to be defined, and the "scaling" methods require the data item _array_intensities.scaling to be defined. The above scaling methods allow the element values to be converted to a linear scale, but do not necessarily relate the linear intensities to physical units. When appropriate the data item _array_intensities.gain can be defined. Dividing the linearized intensities by the value of _array_intensities.gain should produce counts. Two special optional data flag values may be defined which both refer to the values of the "raw" stored intensities in the file (after decompression if necessary), and not to the linearized scaled values. _array_intensities.undefined_value specifies a value which indicates that the element value is not known. This may be due to data missing e.g. a circular image stored in a square array, or where the data values are flagged as missing e.g. behind a beam-stop. _array_intensities.overload_value indicates the intensity value at which and above, values are considered unreliable. This is usually due to saturation. "Array_intensities" Example To define the characteristics of image_1 as linear with a gain of 1.2, and an undefined value of 0, and a saturated (overloaded) value of 65535, the following header section might be used: # Define image intensity scaling loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.undefined_value _array_intensities.overload_value image_1 1 linear 1.2 0 65535 DATA COMPRESSION One of the primary aims of imgCIF / CBF is to allow efficient storage, and efficient reading and writing of data, so data compression is of great interest. Despite the extra CPU over-heads it can very often be faster to compress data prior to storage, as much smaller amounts of data need to be written to disk, and disk I/O is relatively slow. However, optimum data compression can result in complicated algorithms, and be highly data specific. In CBFlib version 0.1, Paul Ellis has coded two lossless compression algorithms: canonical and packed. Canonical-code compression The canonical-code compression scheme encodes errors in two ways: directly or indirectly. Errors are coded directly using a symbol corresponding to the error value. Errors are coded indirectly using a symbol for the number of bits in the (signed) error, followed by the error iteslf. At the start of the compression, CBFLIB constructs a table containing a set of symbols, one for each of the 2^n direct codes from -(2^(n-1)) .. 2^(n-1) -1, one for a stop code, and one for each of the maxbits -n indirect codes, where n is chosen at compress time and maxbits is the maximum number of bits in an error. CBFLIB then assigns to each symbol a bit-code, using a shorter bit code for the more common symbols and a longer bit code for the less common symbols. The bit-code lengths are calculated using a Huffman-type algorithm, and the actual bit-codes are constructed using the canonical-code algorithm described by Moffat, et al. (International Journal of High Speed Electronics and Systems, Vol 8, No 1 (1997) 179-231). The structure of the compressed data is: Byte Value 1 .. 8 Number of elements (64-bit little-endian number) 9 .. 16 Minimum element 17 .. 24 Maximum element 25 .. 32 Repeat length (currently unused) 33 Number of bits directly coded, n 34 Maximum number of bits encoded, maxbits 35 .. 35+2^n-1 Number of bits in each direct code 35+2^n Number of bits in the stop code 35+2^n+1 .. 35+2^n+maxbits-n Number of bits in each indirect code 35+2^n+maxbits-n+1 .. Coded data CCP4-style compression The CCP4-style compression writes the errors in blocks . Each block begins with a 6-bit code. The number of errors in the block is 2^n, where n is the value in bits 0 .. 2. Bits 3 .. 5 encode the number of bits in each error: Value in Number of bits bits 3 .. 5 in each error 0 0 1 4 2 5 3 6 4 7 5 8 6 16 7 65 The structure of the compressed data is: Byte Value 1 .. 8 Number of elements (64-bit little-endian number) 9 .. 16 Minumum element (currently unused) 17 .. 24Maximum element (currently unused) 25 .. 32Repeat length (used, starting with version 0.2) 33 .. Coded data Additional Compression Schemes In addition, Andy Hammersley has proposed two types of lossless data compression algorithms for CBF version 1.0. In later versions other types including lossy algorithms may be added. The first algorithm is referred to as byte_offsets and has been chosen for the following characteristics: it is very simple, may be easily implemented, and can easily lead to faster reading and writing to hard disk as the arithmetic complication is very small. This algorithm can never achieve better than a factor of two compression relative to 16-bit raw data, but for most diffraction data the compression will indeed be very close to a factor 2. The second algorithm is referred to as predictor_huffman and has been chosen as it can achieve close to optimum compression on typical diffraction patterns, with a relatively fast algorithm, whilst avoiding patent problems and licensing fees. This will typically provide a compression ratio between 2.5 and 3 on well exposed diffraction images, and will achieve greater ratios on more weakly exposed data e.g. 4 - 5 on "thin phi-slicing" images. Normally, this would be a two pass algorithm; 1st pass to define symbol probabilities; second pass to entropy encode the data symbols. However, the Huffman algorithm makes it possible to use a fixed table of symbol codes, so faster single pass compression may be implemented with a small loss in compression ratio. With very fast cpus this approach may provide faster hard disk reading and writing than the "byte_offsets" algorithm owing to the smaller amounts of data to be stored. There are practical disadvantages to data compression: the value of a particular element cannot be obtained without calculating the values of all previous elements, and there is no simple relationship between element position and stored bytes. If generally the whole array is required this disadvantage does not apply. These disadvantages can be reduced by compressing separately different regions of the arrays, which is an approach available in TIFF, but this adds to the complexity reading and writing images. For simple predictor algorithms such as the byte_offsets algorithm a simple alternative is an optional data item, which defines a look-up table of element addresses, values, and byte positions within the compressed data, and it is suggested that this approach is followed. THE "BYTE_OFFSETS" ALGORITHM The byte_offsets algorithm will typically result in close to a factor of two reduction in data storage size relative to typical 2-byte diffraction images. It should give similar gains in disk I/O and network transfer. It also has the advantage that integer values up to 32 bits (31 bits unsigned) may be stored efficiently without the need for special over-load tables. It is a fixed algorithm which does not need to calculate any image statistics, so is fast. The algorithm works because of the following property of almost all diffraction data and much other image data: The value of one element tends to be close to the value of the adjacent elements, and the vast majority of the differences use little of the full dynamic range. However, noise in experimental data means that run-length encoding is not useful (unless the image is separated into different bit-planes). If a variable length code is used to store the differences, with the number of bits used being inversely proportional to the probability of occurrence, then compression ratios of 2.5 to 3.0 may be achieved. However, the optimum encoding becomes dependent of the exact properties of the image, and in particular on the noise. Here a lower compression ratio is achieved, but the resulting algorithm is much simpler and more robust. The byte_offsets algorithm is the following: 1. The first element of the array is stored as a 4-byte signed two's integer regardless of the raw array element type. The byte order for this and all subsequent multi-byte integers is little_endian regardless of the native computer architecture i.e. the first byte is the least significant, and the last byte the most. This value is the first reference value ("previous element") for calculating pixel to pixel differences. 2. For all elements, including the first element, the value of the previous element is subtracted to produce the difference. For the first element on a line the value to subtract is the value of the first element of the previous line. For the first element of a subsequent image (or plane) the value to subtract is the value of the first element of the previous image (or plane). 3. If the difference is less than +-127, then one byte is used to store the difference as a signed two's complement integer, otherwise the byte is set to -128 (80 in hex) and if the difference is less than +-32767, then the next two bytes are used to store the difference as a signed two byte two's complement integer, otherwise -32768 (8000 in hex, which will be output as 00 80 in little-endian format) is written into the two bytes and the following 4-bytes store the difference as a full signed 32-bit two's complement integer. 4. The array element order follows the normal ordering as defined by the _array_structure_list entries index, precedence and direction. It may be noted that one element value may require up to 7 bytes for storage, however for almost all 16-bit experimental data the vast majority of element values will be within +-127 units of the previous element and so only require 1 byte for storage and a compression factor of close to 2 is achieved. The PREDICTOR_HUFFMAN ALGORITHM Section to be added. OTHER SECTIONS Other sections will be added. 9.0 REFERENCES 1. S R Hall, F H Allen, and I D Brown, "The Crystallographic Information File (CIF): a New Standard Archive File for Crystallography", Acta Cryst., A47, 655-685 (1991) 10.0 NOTES (1) A pure CIF based format has been considered inappropriate given the enormous size of many raw experimental data-sets and the desire for efficient storage, and reading and writing. <<< However, an ASCII format is helpful for debugging software and in understanding what has been written in a CBF when problems arise, and there are other CIF application for which a convenience binary format should be useful (e.g. illustrations in a manuscript). <<< (2) Some simple method of checking whether the file is a CBF or not is needed. Ideally this would be right at the start of the file. Thus, a program only needs to read in n bytes and should then know immediately if the file is of the right type or not. Andy though this identifier should be some straightforward and clear ASCII string. <<< With the use of binary strings and MIME conventions identification of a CBF versus a CIF is less critical than it was before, but the distinct header as a simple ASCII string is still a good idea for the sake of the most efficient processing of large files.<<< The underscore character has been used to avoid any ambiguity in the spaces. (Such an identifier should be long enough that it is highly unlikely to occur randomly, and if it is ASCII text, should be very slightly obscure, again to reduce the chances that it is found accidently. Hence I added the three hashes, but some other form may be equally valid.) (3) The format should maintain backward compatibility e.g. a version 1.0 file can be read in by a version 1.1, 3.0, etc. program, but to allow future extensions the reverse cannot be guaranteed to be true. <<< However, prior to actual adoption of version 1.0, we are not yet trying to ensure full upwards compatibility, just that the effort to convert won't be unreasonable. <<< ------------------------------------------------------------------------ EXAMPLE CBF ------------------------------------------------------------------------ This page was produced on 14 November 1998 by Herbert J. Bernstein (email: yaya@bernstein-plus-sons.com), based on the the 8 July version and the page produced by Andy Hammersley (E-mail: hammersley@esrf.fr). Further modification is highly likely, especially after Andy reads this and finds all the mistakes. ------------------------------------------------------------------------ ./CBFlib-0.9.2.2/doc/Iaxis.type.html0000644000076500007650000000621411603702115015271 0ustar yayayaya (IUCr) CIF Definition save__axis.type

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _axis.type

    Name:
    '_axis.type'

    Definition:

           The value of _axis.type specifies the type of
                  axis:  'rotation' or 'translation' (or 'general' when
                  the type is not relevant, as for gravity).
    
    

    Type: ucode

    Mandatory item: no


    The data value must be one of the following:


    rotation
    right-handed axis of rotation

    translation
    translation in the direction of the axis

    general
    axis for which the type is not relevant

    Enumeration default: general

    Category: axis

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Iarray_data.data.html0000644000076500007650000003341611603702115016370 0ustar yayayaya (IUCr) CIF Definition save__array_data.data

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _array_data.data

    Name:
    '_array_data.data'

    Definition:

           The value of _array_data.data contains the array data
                  encapsulated in a STAR string.
    
                  The representation used is a variant on the
                  Multipurpose Internet Mail Extensions (MIME) specified
                  in RFC 2045-2049 by N. Freed et al.  The boundary
                  delimiter used in writing an imgCIF or CBF is
                  '\n--CIF-BINARY-FORMAT-SECTION--' (including the
                  required initial '\n--').
    
                  The Content-Type may be any of the discrete types permitted
                  in RFC 2045; 'application/octet-stream' is recommended
                  for diffraction images in the ARRAY_DATA category.
                  Note:  When appropriate in other categories, e.g. for
                  photographs of crystals, more precise types, such as
                  'image/jpeg', 'image/tiff', 'image/png', etc. should be used.
    
                  If an octet stream was compressed, the compression should
                  be specified by the parameter
                    'conversions="X-CBF_PACKED"'
                  or the parameter
                    'conversions="X-CBF_CANONICAL"'
                  or the parameter
                    'conversions="X-CBF_BYTE_OFFSET"'
    
                  If the parameter
                    'conversions="X-CBF_PACKED"'
                  is given it may be further modified with the parameters
                    '"uncorrelated_sections"'
                  or
                    '"flat"'
    
                  If the '"uncorrelated_sections"' parameter is
                  given, each section will be compressed without using
                  the prior section for averaging.
    
                  If the '"flat"' parameter is given, each the
                  image will be treated as one long row.
    
                  The Content-Transfer-Encoding may be 'BASE64',
                  'Quoted-Printable', 'X-BASE8', 'X-BASE10',
                  'X-BASE16' or 'X-BASE32K', for an imgCIF or 'BINARY'
                  for a CBF.  The octal, decimal and hexadecimal transfer
                  encodings are provided for convenience in debugging and
                  are not recommended for archiving and data interchange.
    
                  In a CIF, one of the parameters 'charset=us-ascii',
                  'charset=utf-8' or 'charset=utf-16' may be used on the
                  Content-Transfer-Encoding to specify the character set
                  used for the external presentation of the encoded data.
                  If no charset parameter is given, the character set of
                  the enclosing CIF is assumed.  In any case, if a BOM
                  flag is detected (FE FF for big-endian UTF-16, FF FE for
                  little-endian UTF-16 or EF BB BF for UTF-8) is detected,
                  the indicated charset will be assumed until the end of the
                  encoded data or the detection of a different BOM.  The
                  charset of the Content-Transfer-Encoding is not the character
                  set of the encoded data, only the character set of the
                  presentation of the encoded data and should be respecified
                  for each distinct STAR string.
    
                  In an imgCIF file, the encoded binary data begins after
                  the empty line terminating the header.  In an imgCIF file,
                  the encoded binary data ends with the terminating boundary
                  delimiter '\n--CIF-BINARY-FORMAT-SECTION----'
                  in the currently effective charset or with the '\n; '
                  that terminates the STAR string.
    
                  In a CBF, the raw binary data begins after an empty line
                  terminating the header and after the sequence:
    
                  Octet   Hex   Decimal  Purpose
                    0     0C       12    (ctrl-L) Page break
                    1     1A       26    (ctrl-Z) Stop listings in MS-DOS
                    2     04       04    (Ctrl-D) Stop listings in UNIX
                    3     D5      213    Binary section begins
    
                  None of these octets are included in the calculation of
                  the message size or in the calculation of the
                  message digest.
    
                  The X-Binary-Size header specifies the size of the
                  equivalent binary data in octets.  If compression was
                  used, this size is the size after compression, including
                  any book-keeping fields.  An adjustment is made for
                  the deprecated binary formats in which eight bytes of binary
                  header are used for the compression type.  In this case,
                  the eight bytes used for the compression type are subtracted
                  from the size, so that the same size will be reported
                  if the compression type is supplied in the MIME header.
                  Use of the MIME header is the recommended way to
                  supply the compression type.  In general, no portion of
                  the  binary header is included in the calculation of the size.
    
                  The X-Binary-Element-Type header specifies the type of
                  binary data in the octets, using the same descriptive
                  phrases as in _array_structure.encoding_type.  The default
                  value is 'unsigned 32-bit integer'.
    
                  An MD5 message digest may, optionally, be used. The 'RSA Data
                  Security, Inc. MD5 Message-Digest Algorithm' should be used.
                  No portion of the header is included in the calculation of the
                  message digest.
    
                  If the Transfer Encoding is 'X-BASE8', 'X-BASE10' or
                  'X-BASE16', the data are presented as octal, decimal or
                  hexadecimal data organized into lines or words.  Each word
                  is created by composing octets of data in fixed groups of
                  2, 3, 4, 6 or 8 octets, either in the order ...4321 ('big-
                  endian') or 1234... ('little-endian').  If there are fewer
                  than the specified number of octets to fill the last word,
                  then the missing octets are presented as '==' for each
                  missing octet.  Exactly two equal signs are used for each
                  missing octet even for octal and decimal encoding.
                  The format of lines is:
    
                  rnd xxxxxx xxxxxx xxxxxx
    
                  where r is 'H', 'O' or 'D' for hexadecimal, octal or
                  decimal, n is the number of octets per word and d is '<'
                  or '>' for the '...4321' and '1234...' octet orderings,
                  respectively.  The '==' padding for the last word should
                  be on the appropriate side to correspond to the missing
                  octets, e.g.
    
                  H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000
    
                  or
    
                  H3> FF0700 00====
    
                  For these hexadecimal, octal and decimal formats only,
                  comments beginning with '#' are permitted to improve
                  readability.
    
                  BASE64 encoding follows MIME conventions.  Octets are
                  in groups of three: c1, c2, c3.  The resulting 24 bits
                  are broken into four six-bit quantities, starting with
                  the high-order six bits (c1 >> 2) of the first octet, then
                  the low-order two bits of the first octet followed by the
                  high-order four bits of the second octet [(c1 & 3)<<4 | (c2>>4)],
                  then the bottom four bits of the second octet followed by the
                  high-order two bits of the last octet [(c2 & 15)<<2 | (c3>>6)],
                  then the bottom six bits of the last octet (c3 & 63).  Each
                  of these four quantities is translated into an ASCII character
                  using the mapping:
    
                            1         2         3         4         5         6
                  0123456789012345678901234567890123456789012345678901234567890123
                  |         |         |         |         |         |         |
                  ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/
    
                  With short groups of octets padded on the right with one '='
                  if c3 is missing, and with '==' if both c2 and c3 are missing.
    
                  X-BASE32K encoding is similar to BASE64 encoding, except that
                  sets of 15 octets are encoded as sets of 8 16-bit unicode
                  characters, by breaking the 120 bits into 8 15-bit quantities.
                  256 is added to each 15 bit quantity to bring it into a
                  printable uncode range.  When encoding, zero padding is used
                  to fill out the last 15 bit quantity.  If 8 or more bits of
                  padding are used, a single equals sign (hexadecimal 003D) is
                  appended.  Embedded whitespace and newlines are introduced
                  to produce lines of no more than 80 characters each.  On
                  decoding, all printable ascii characters and ascii whitespace
                  characters are ignored except for any trailing equals signs.
                  The number of trailing equals signs indicated the number of
                  trailing octets to be trimmed from the end of the decoded data.
                  (see Georgi Darakev, Vassil Litchev, Kostadin Z. Mitev, Herbert
                  J. Bernstein, 'Efficient Support of Binary Data in the XML
                  Implementation of the NeXus File Format',absract W0165,
                  ACA Summer Meeting, Honolulu, HI, July 2006).
    
                  QUOTED-PRINTABLE encoding also follows MIME conventions, copying
                  octets without translation if their ASCII values are 32...38,
                  42, 48...57, 59, 60, 62, 64...126 and the octet is not a ';'
                  in column 1.  All other characters are translated to =nn, where
                  nn is the hexadecimal encoding of the octet.  All lines are
                  'wrapped' with a terminating '=' (i.e. the MIME conventions
                  for an implicit line terminator are never used).
    
                  The "X-Binary-Element-Byte-Order" can specify either
                  '"BIG_ENDIAN"' or '"LITTLE_ENDIAN"' byte order of the imaage
                  data.  Only LITTLE_ENDIAN is recommended.  Processors
                  may treat BIG_ENDIAN as a warning of data that can
                  only be processed by special software.
    
                  The "X-Binary-Number-of-Elements" specifies the number of
                  elements (not the number of octets) in the decompressed, decoded
                  image.
    
                  The optional "X-Binary-Size-Fastest-Dimension" specifies the
                  number of elements (not the number of octets) in one row of the
                  fastest changing dimension of the binary data array. This
                  information must be in the MIME header for proper operation of
                  some of the decompression algorithms.
    
                  The optional "X-Binary-Size-Second-Dimension" specifies the
                  number of elements (not the number of octets) in one column of
                  the second-fastest changing dimension of the binary data array.
                  This information must be in the MIME header for proper operation
                  of some of the decompression algorithms.
    
                  The optional "X-Binary-Size-Third-Dimension" specifies the
                  number of sections for the third-fastest changing dimension of
                  the binary data array.
    
                  The optional "X-Binary-Size-Padding" specifies the size in
                  octets of an optional padding after the binary array data and
                  before the closing flags for a binary section.
    
    

    Type: binary

    Mandatory item: yes

    Category: array_data

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_scan_frame.frame_number.html0000644000076500007650000000541011603702115021431 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan_frame.frame_number

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_scan_frame.frame_number

    Name:
    '_diffrn_scan_frame.frame_number'

    Definition:

            The value of this data item is the number of the frame
                   within the scan, starting with 1.  It is not necessarily
                   the same as the value of _diffrn_scan_frame.frame_id,
                   but it may be.
    
    
    

    Type: int

    Mandatory item: no


    The permitted range is [0, infinity)

    Category: diffrn_scan_frame

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Iarray_intensities.pixel_slow_bin_size.html0000644000076500007650000000647611603702115023161 0ustar yayayaya (IUCr) CIF Definition save__array_intensities.pixel_slow_bin_size

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _array_intensities.pixel_slow_bin_size

    Name:
    '_array_intensities.pixel_slow_bin_size'

    Definition:

            The value of _array_intensities.pixel_slow_bin_size specifies
                   the number of pixels that compose one element in the direction
                   of the second most rapidly varying array dimension.
    
                   Typical values are 1, 2, 4 or 8.  When there is 1 pixel per
                   array element in both directions, the value given for
                   _array_intensities.pixel_binning_method normally should be
                   'none'.
    
                   It is specified as a float to allow for binning algorithms that
                   create array elements that are not integer multiples of the
                   detector pixel size.
    
    

    Type: float

    Mandatory item: implicit


    The permitted range is [0.0, infinity)

    Enumeration default: 1.

    Category: array_intensities

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Cdiffrn_scan_frame.html0000644000076500007650000000535011603702115016765 0ustar yayayaya (IUCr) CIF Definition save_diffrn_scan_frame

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    Category DIFFRN_SCAN_FRAME

    Name:
    'diffrn_scan_frame'

    Description:

         Data items in the DIFFRN_SCAN_FRAME category describe
                the relationships of particular frames to scans.
    
    
    Category groups:
        inclusive_group
        diffrn_group
    Category keys:
        _diffrn_scan_frame.scan_id
        _diffrn_scan_frame.frame_id

    Mandatory category: no

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Cmap_segment.html0000644000076500007650000000721111603702115015634 0ustar yayayaya (IUCr) CIF Definition save_map_segment

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    Category MAP_SEGMENT

    Name:
    'map_segment'

    Description:

           Data items in the MAP_SEGMENT category record
                  the details about each segment (section or brick) of a map.
    
    
    Example:

    Example 1 - Identifying an observed density map and a calculated density map, each consisting of one segment, both using the same array structure and mask.
     
    
            loop_
            _map.id
            _map.details
    
            rho_calc
         ;
            density calculated from F_calc derived from the ATOM_SITE list
         ;
            rho_obs
         ;
            density combining the observed structure factors with the
            calculated phases
         ;
    
            loop_
            _map_segment.map_id
            _map_segment.id
            _map_segment.array_id
            _map_segment.binary_id
            _map_segment.mask_array_id
            _map_segment.mask_binary_id
            rho_calc rho_calc map_structure 1 mask_structure 1
            rho_obs  rho_obs  map_structure 2 mask_structure 1
    
    


    Category groups:
        inclusive_group
        array_data_group
    Category keys:
        _map_segment.id
        _map_segment.map_id

    Mandatory category: no

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Iarray_structure_list_axis.angle.html0000644000076500007650000000577011603702115021755 0ustar yayayaya (IUCr) CIF Definition save__array_structure_list_axis.angle

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _array_structure_list_axis.angle

    Name:
    '_array_structure_list_axis.angle'

    Definition:

            The setting of the specified axis in degrees for the first
                   data point of the array index with the corresponding value
                   of _array_structure_list.axis_set_id.  If the index is
                   specified as 'increasing', this will be the centre of the
                   pixel with index value 1.  If the index is specified as
                   'decreasing', this will be the centre of the pixel with
                   maximum index value.
    
    

    Type: float

    Mandatory item: no


    Enumeration default: 0.0

    Category: array_structure_list_axis

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Carray_structure_list_axis.html0000644000076500007650000000660711603702115020662 0ustar yayayaya (IUCr) CIF Definition save_array_structure_list_axis

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    Category ARRAY_STRUCTURE_LIST_AXIS

    Name:
    'array_structure_list_axis'

    Description:

        Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe
         the physical settings of sets of axes for the centres of pixels that
         correspond to data points described in the
         ARRAY_STRUCTURE_LIST category.
    
         In the simplest cases, the physical increments of a single axis correspond
         to the increments of a single array index.  More complex organizations,
         e.g. spiral scans, may require coupled motions along multiple axes.
    
         Note that a spiral scan uses two coupled axes: one for the angular
         direction and one for the radial direction.  This differs from a
         cylindrical scan for which the two axes are not coupled into one 
         set.
    
    
    Category groups:
        inclusive_group
        array_data_group
    Category keys:
        _array_structure_list_axis.axis_set_id
        _array_structure_list_axis.axis_id

    Mandatory category: no

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Iarray_structure_list_axis.radial_pitch.html0000644000076500007650000000566611603702115023316 0ustar yayayaya (IUCr) CIF Definition save__array_structure_list_axis.radial_pitch

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _array_structure_list_axis.radial_pitch

    Name:
    '_array_structure_list_axis.radial_pitch'

    Definition:

            The radial distance from one 'cylinder' of pixels to the
                   next in millimetres.  If the scan is a 'constant velocity'
                   scan with differing angular displacements between pixels,
                   the value of this item may differ significantly from the
                   value of _array_structure_list_axis.displacement_increment.
    
    

    Type: float

    Mandatory item: no


    Enumeration default: 0.0

    Category: array_structure_list_axis

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/cif_img_1_3_1.html0000644000076500007650000071176211603702115015526 0ustar yayayaya cif_img.dic v1.3.1

    # [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib] #

    # imgCIF/CBF #

    # Extensions Dictionary #

    ##############################################################################
    #                                                                            #
    #                       Image CIF Dictionary (imgCIF)                        #
    #             and Crystallographic Binary File Dictionary (CBF)              #
    #            Extending the Macromolecular CIF Dictionary (mmCIF)             #
    #                                                                            #
    #                              Version 1.3.1                                 #
    #                              of 2003-08-13                                 #
    #                                                                            #
    #     by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook    #
    #                                                                            #
    # This dictionary was adapted from format discussed at the imgCIF Workshop,  #
    # held at BNL Oct 1997 and the Crystallographic Binary File Format Draft     #
    # Proposal by Andrew Hammersley.  The first DDL 2.1 Version was created by   #
    # John Westbrook.  This version was drafted by Herbert J. Bernstein and      #
    # incorporates comments by I. David Brown, John Westbrook, Brian McMahon,    #
    # Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li, Gotzon Madariaga,         #
    # Frances C. Bernstein and others.                                           #
    ##############################################################################
                                                                        
    data_cif_img.dic
    
        _dictionary.title           cif_img.dic
        _dictionary.version         1.3.1
        _dictionary.datablock_id    cif_img.dic
    
    ##############################################################################
    #    CONTENTS
    #
    #        CATEGORY_GROUP_LIST
    #
    #        category  ARRAY_DATA
    #
    #                  _array_data.array_id
    #                  _array_data.binary_id
    #                  _array_data.data
    #
    #        category  ARRAY_ELEMENT_SIZE
    #        
    #                  _array_element_size.array_id
    #                  _array_element_size.index
    #                  _array_element_size.size
    #        
    #        category  ARRAY_INTENSITIES
    #        
    #                  _array_intensities.array_id
    #                  _array_intensities.binary_id
    #                  _array_intensities.gain
    #                  _array_intensities.gain_esd
    #                  _array_intensities.linearity
    #                  _array_intensities.offset
    #                  _array_intensities.scaling
    #                  _array_intensities.overload
    #                  _array_intensities.undefined_value
    #        
    #        category  ARRAY_STRUCTURE
    #        
    #                  _array_structure.byte_order
    #                  _array_structure.compression_type
    #                  _array_structure.encoding_type
    #                  _array_structure.id
    #        
    #        category  ARRAY_STRUCTURE_LIST
    #        
    #                  _array_structure_list.axis_set_id
    #                  _array_structure_list.array_id
    #                  _array_structure_list.dimension
    #                  _array_structure_list.direction
    #                  _array_structure_list.index
    #                  _array_structure_list.precedence
    #
    #        category  ARRAY_STRUCTURE_LIST_AXIS
    #        
    #                  _array_structure_list_axis.axis_id
    #                  _array_structure_list_axis.axis_set_id
    #                  _array_structure_list_axis.angle
    #                  _array_structure_list_axis.angle_increment
    #                  _array_structure_list_axis.displacement_increment
    #                  _array_structure_list_axis.angular_pitch
    #                  _array_structure_list_axis.radial_pitch
    #
    #        category  AXIS
    #        
    #                  _axis.depends_on
    #                  _axis.equipment
    #                  _axis.id
    #                  _axis.offset[1]
    #                  _axis.offset[2]
    #                  _axis.offset[3]
    #                  _axis.type
    #                  _axis.vector[1]
    #                  _axis.vector[2]
    #                  _axis.vector[3]
    #
    #        category  DIFFRN_DATA_FRAME
    #
    #                  _diffrn_data_frame.array_id
    #                  _diffrn_data_frame.binary_id
    #                  _diffrn_data_frame.detector_element_id
    #                  _diffrn_data_frame.id
    #
    #        category  DIFFRN_DETECTOR
    #        
    #                  _diffrn_detector.details
    #                  _diffrn_detector.detector
    #                  _diffrn_detector.diffrn_id
    #                  _diffrn_detector.dtime
    #                  _diffrn_detector.id
    #                  _diffrn_detector.number_of_axes
    #                  _diffrn_detector.type
    #
    #        category  DIFFRN_DETECTOR_AXIS
    #        
    #                  _diffrn_detector_axis.axis_id
    #                  _diffrn_detector_axis.detector_id    
    #        
    #        category  DIFFRN_DETECTOR_ELEMENT
    #
    #                  _diffrn_detector_element.center[1]
    #                  _diffrn_detector_element.center[2]
    #                  _diffrn_detector_element.id
    #                  _diffrn_detector_element.detector_id
    #        
    #        category  DIFFRN_MEASUREMENT
    #        
    #                  _diffrn_measurement.diffrn_id
    #                  _diffrn_measurement.details
    #                  _diffrn_measurement.device
    #                  _diffrn_measurement.device_details
    #                  _diffrn_measurement.device_type
    #                  _diffrn_measurement.id
    #                  _diffrn_measurement.method
    #                  _diffrn_measurement.number_of_axes
    #                  _diffrn_measurement.specimen_support
    #
    #        category  DIFFRN_MEASUREMENT_AXIS
    #        
    #                  _diffrn_measurement_axis.axis_id
    #                  _diffrn_measurement_axis.measurement_device
    #                  _diffrn_measurement_axis.measurement_id
    #
    #        category  DIFFRN_RADIATION
    #
    #                  _diffrn_radiation.collimation
    #                  _diffrn_radiation.diffrn_id
    #                  _diffrn_radiation.div_x_source
    #                  _diffrn_radiation.div_y_source
    #                  _diffrn_radiation.div_x_y_source
    #                  _diffrn_radiation.filter_edge'
    #                  _diffrn_radiation.inhomogeneity
    #                  _diffrn_radiation.monochromator
    #                  _diffrn_radiation.polarisn_norm
    #                  _diffrn_radiation.polarisn_ratio
    #                  _diffrn_radiation.polarizn_source_norm
    #                  _diffrn_radiation.polarizn_source_ratio
    #                  _diffrn_radiation.probe
    #                  _diffrn_radiation.type
    #                  _diffrn_radiation.xray_symbol
    #                  _diffrn_radiation.wavelength_id
    #        
    #        category  DIFFRN_REFLN
    #        
    #                  _diffrn_refln.frame_id
    #
    #        category  DIFFRN_SCAN
    #        
    #                  _diffrn_scan.id
    #                  _diffrn_scan.date_end
    #                  _diffrn_scan.date_start
    #                  _diffrn_scan.integration_time
    #                  _diffrn_scan.frame_id_start
    #                  _diffrn_scan.frame_id_end
    #                  _diffrn_scan.frames
    #
    #        category  DIFFRN_SCAN_AXIS
    #        
    #                  _diffrn_scan_axis.axis_id
    #                  _diffrn_scan_axis.angle_start
    #                  _diffrn_scan_axis.angle_range
    #                  _diffrn_scan_axis.angle_increment
    #                  _diffrn_scan_axis.angle_rstrt_incr
    #                  _diffrn_scan_axis.displacement_start
    #                  _diffrn_scan_axis.displacement_range
    #                  _diffrn_scan_axis.displacement_increment
    #                  _diffrn_scan_axis.displacement_rstrt_incr
    #                  _diffrn_scan_axis.scan_id
    #
    #        category  DIFFRN_SCAN_FRAME
    #        
    #                  _diffrn_scan_frame.date
    #                  _diffrn_scan_frame.frame_id
    #                  _diffrn_scan_frame.frame_number
    #                  _diffrn_scan_frame.integration_time
    #                  _diffrn_scan_frame.scan_id
    #
    #        category  DIFFRN_SCAN_FRAME_AXIS
    #        
    #                  _diffrn_scan_frame_axis.axis_id
    #                  _diffrn_scan_frame_axis.angle
    #                  _diffrn_scan_frame_axis.angle_increment
    #                  _diffrn_scan_frame_axis.angle_rstrt_incr
    #                  _diffrn_scan_frame_axis.displacement
    #                  _diffrn_scan_frame_axis.displacement_increment
    #                  _diffrn_scan_frame_axis.displacement_rstrt_incr
    #                  _diffrn_scan_frame_axis.frame_id
    #
    #       ***DEPRECATED*** data items
    #
    #                  _diffrn_detector_axis.id
    #                  _diffrn_measurement_axis.id
    #
    #       ***DEPRECATED*** category  DIFFRN_FRAME_DATA
    #
    #                  _diffrn_frame_data.array_id
    #                  _diffrn_frame_data.binary_id
    #                  _diffrn_frame_data.detector_element_id
    #                  _diffrn_frame_data.id
    #
    #
    #        ITEM_TYPE_LIST
    #        ITEM_UNITS_LIST
    #        DICTIONARY_HISTORY
    #
    ##############################################################################
    
    
    #########################
    ## CATEGORY_GROUP_LIST ##
    #########################
    
         loop_
        _category_group_list.id
        _category_group_list.parent_id
        _category_group_list.description
                 'inclusive_group'   .
    ;             Categories that belong to the dictionary extension.
    ;
                 'array_data_group'
                 'inclusive_group'
    ;             Categories that describe array data.
    ;
                 'axis_group'
                 'inclusive_group'
    ;             Categories that describe axes.
    ;
                 'diffrn_group'
                 'inclusive_group'
    ;            Categories that describe details of the diffraction experiment.
    ;
    
    
    
    
    ##############
    # ARRAY_DATA #
    ##############
    
      
    save_ARRAY_DATA
        _category.description
    ;
         Data items in the ARRAY_DATA category are the containers for
         the array data items described in category ARRAY_STRUCTURE.
    ;
        _category.id                   array_data
        _category.mandatory_code       no
         loop_
        _category_key.name             '_array_data.array_id'
                                       '_array_data.binary_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 -
    
            This example shows two binary data blocks.  The first one
            was compressed by the CBF_CANONICAL compression algorithm and
            presented as hexadecimal data.  The first character "H" on the
            data lines means hexadecimal.  It could have been "O" for octal
            or "D" for decimal.  The second character on the line shows
            the number of bytes in each word (in this case "4"), which then
            requires 8 hexadecimal digits per word.  The third character
            gives the order of octets within a word, in this case "<"
            for the ordering 4321 (i.e. "big-endian").  Alternatively the
            character ">" could have been used for the ordering 1234
            (i.e. "little-endian").  The block has a "message digest"
            to check the integrity of the data.
    
            The second block is similar, but uses CBF_PACKED compression
            and BASE64 encoding.  Note that the size and the digest are
            different.
    ;
    ;
    
            loop_
            _array_data.array_id
            _array_data.binary_id
            _array_data.data
            image_1 1
            ;
            --CIF-BINARY-FORMAT-SECTION--
            Content-Type: application/octet-stream;
                 conversions="x-CBF_CANONICAL"
            Content-Transfer-Encoding: X-BASE16
            X-Binary-Size: 3927126
            X-Binary-ID: 1
            Content-MD5: u2sTJEovAHkmkDjPi+gWsg==
    
            # Hexadecimal encoding, byte 0, byte order ...21
            #
            H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ...
            ....
            --CIF-BINARY-FORMAT-SECTION----
            ;
            image_2 2
            ;
            --CIF-BINARY-FORMAT-SECTION--
            Content-Type: application/octet-stream;
                 conversions="x-CBF-PACKED"
            Content-Transfer-Encoding: BASE64
            X-Binary-Size: 3745758
            X-Binary-ID: 2
            Content-MD5: 1zsJjWPfol2GYl2V+QSXrw==
    
            ELhQAAAAAAAA...
            ...
            --CIF-BINARY-FORMAT-SECTION----
            ;
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    save_
    
    
    save__array_data.array_id
        _item_description.description
    ;             This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category. 
    ;
        _item.name                  '_array_data.array_id'
        _item.category_id             array_data
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__array_data.binary_id
        _item_description.description
    ;             This item is an integer identifier which, along with
                  '_array_data.array_id' should uniquely identify the 
                  particular block of array data.
                  
                  If '_array_data.binary_id' is not explicitly given,
                  it defaults to 1.
                  
                  The value of '_array_data.binary_id' distinguishes
                  among multiple sets of data with the same array
                  structure.
                  
                  If the MIME header of the data array specifies a 
                  value for X-Binary-Id, the value of  '_array_data.binary_id'
                  should be equal the value given for X-Binary-Id.
    ;
         loop_
        _item.name                  
        _item.category_id             
        _item.mandatory_code          
                 '_array_data.binary_id'            array_data      
                                                                    implicit
                 '_diffrn_data_frame.binary_id'     diffrn_data_frame
                                                                    implicit
                 '_array_intensities.binary_id'     array_intensities
                                                                    implicit
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_data_frame.binary_id'     '_array_data.binary_id'
                 '_array_intensities.binary_id'     '_array_data.binary_id'
    
        _item_default.value           1
        _item_type.code               int
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                1  1
                                .  1
         save_
    
    
    save__array_data.data
        _item_description.description
    ;             The value of '_array_data.data' contains the array data 
                  encapsulated in a STAR string.
                  
                  The representation used is a variant on the
                  Multipurpose Internet Mail Extensions (MIME) specified
                  in RFC 2045-2049 by N. Freed et al.  The boundary
                  delimiter used in writing an imgCIF or CBF is
                  "--CIF-BINARY-FORMAT-SECTION--" (including the
                  required initial "--").
    
                  The Content-Type may be any of the discrete types permitted
                  in RFC 2045; "application/octet-stream" is recommended.  
                  If an octet stream was compressed, the compression should 
                  be specified by the parameter 'conversions="x-CBF_PACKED"' 
                  or the parameter 'conversions="x-CBF_CANONICAL"'.
                  
                  The Content-Transfer-Encoding may be "BASE64",
                  "Quoted-Printable", "X-BASE8", "X-BASE10", or
                  "X-BASE16" for an imgCIF or "BINARY" for a CBF.  The
                  octal, decimal and hexadecimal transfer encodings are
                  for convenience in debugging, and are not recommended
                  for archiving and data interchange.
                  
                  In an imgCIF file, the encoded binary data begins after
                  the empty line terminating the header.  In a CBF, the
                  raw binary data begins after an empty line terminating
                  the header and after the sequence:
                        
                  Octet   Hex   Decimal  Purpose
                    0     0C       12    (ctrl-L) Page break
                    1     1A       26    (ctrl-Z) Stop listings in MS-DOS
                    2     04       04    (Ctrl-D) Stop listings in UNIX
                    3     D5      213    Binary section begins
    
                  None of these octets are included in the calculation of
                  the message size, nor in the calculation of the
                  message digest.
                                 
                  The X-Binary-Size header specifies the size of the
                  equivalent binary data in octets.  If compression was
                  used, this size is the size after compression, including
                  any book-keeping fields.  An adjustment is made for
                  the deprecated binary formats in which 8 bytes of binary
                  header are used for the compression type.  In that case,
                  the 8 bytes used for the compression type is subtracted
                  from the size, so that the same size will be reported
                  if the compression type is supplied in the MIME header.
                  Use of the MIME header is the recommended way to
                  supply the compression type.  In general, no portion of
                  the  binary header is included in the calculation of the size.
    
                  The X-Binary-Element-Type header specifies the type of
                  binary data in the octets, using the same descriptive
                  phrases as in '_array_structure.encoding_type'.  The default
                  value is "unsigned 32-bit integer".
                  
                  An MD5 message digest may, optionally, be used. The "RSA Data
                  Security, Inc. MD5 Message-Digest Algorithm" should be used.
                  No portion of the header is included in the calculation of the
                  message digest.
    
                  If the Transfer Encoding is "X-BASE8", "X-BASE10", or
                  "X-BASE16", the data is presented as octal, decimal or
                  hexadecimal data organized into lines or words.  Each word
                  is created by composing octets of data in fixed groups of
                  2, 3, 4, 6 or 8 octets, either in the order ...4321 ("big-
                  endian") or 1234... (little-endian).  If there are fewer
                  than the specified number of octets to fill the last word,
                  then the missing octets are presented as "==" for each
                  missing octet.  Exactly two equal signs are used for each
                  missing octet even for octal and decimal encoding.
                  The format of lines is:
    
                  rnd xxxxxx xxxxxx xxxxxx
    
                  where r is "H", "O", or "D" for hexadecimal, octal or
                  decimal, n is the number of octets per word. and d is "<"
                  for ">" for the "...4321" and "1234..." octet orderings
                  respectively.  The "==" padding for the last word should
                  be on the appropriate side to correspond to the missing
                  octets, e.g.
    
                  H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000
    
                  or
    
                  H3> FF0700 00====
    
                  For these hex, octal and decimal formats, only, comments
                  beginning with "#" are permitted to improve readability.
    
                  BASE64 encoding follows MIME conventions.  Octets are
                  in groups of three, c1, c2, c3.  The resulting 24 bits 
                  are broken into four 6-bit quantities, starting with 
                  the high-order six bits (c1 >> 2) of the first octet, then
                  the low-order two bits of the first octet followed by the
                  high-order 4 bits of the second octet ((c1 & 3)<<4 | (c2>>4)),
                  then the bottom 4 bits of the second octet followed by the
                  high order two bits of the last octet ((c2 & 15)<<2 | (c3>>6)),
                  then the bottom six bits of the last octet (c3 & 63).  Each
                  of these four quantities is translated into an ASCII character
                  using the mapping:
    
                            1         2         3         4         5         6
                  0123456789012345678901234567890123456789012345678901234567890123
                  |         |         |         |         |         |         |
                  ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/
    
                  With short groups of octets padded on the right with one "="
                  if c3 is missing, and with "==" if both c2 and c3 are missing.
    
                  QUOTED-PRINTABLE encoding also follows MIME conventions, copying
                  octets without translation if their ASCII values are 32..38,
                  42, 48..57, 59..60, 62, 64..126 and the octet is not a ";"
                  in column 1.  All other characters are translated to =nn, where
                  nn is the hexadecimal encoding of the octet.  All lines are
                  "wrapped" with a terminating "=" (i.e. the MIME conventions
                  for an implicit line terminator are never used).
    ;
        _item.name                  '_array_data.data'
        _item.category_id             array_data
        _item.mandatory_code          yes
        _item_type.code               binary
    save_
    
    
    ######################
    # ARRAY_ELEMENT_SIZE #
    ######################
    
    
    save_ARRAY_ELEMENT_SIZE
        _category.description
    ;
         Data items in the ARRAY_ELEMENT_SIZE category record the physical 
         size of array elements along each array dimension.
    ;
        _category.id                   array_element_size
        _category.mandatory_code       no
         loop_
        _category_key.name             '_array_element_size.array_id'
                                       '_array_element_size.index'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 - A regular 2D array with a uniform element dimension
                        of 1220 nanometres.
    ;
    ;
            loop_
           _array_element_size.array_id  
           _array_element_size.index
           _array_element_size.size
            image_1   1    1.22e-6
            image_1   2    1.22e-6
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_element_size.array_id
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category. 
    ;
        _item.name                  '_array_element_size.array_id'
        _item.category_id             array_element_size
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__array_element_size.index
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure_list.index' in
                  the ARRAY_STRUCTURE_LIST category. 
    ;
        _item.name                  '_array_element_size.index'
        _item.category_id             array_element_size
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__array_element_size.size
        _item_description.description
    ;
                   The size in metres of an image element in this 
                   dimension. This supposes that the elements are arranged
                   on a regular grid.
    ;
        _item.name               '_array_element_size.size'
        _item.category_id          array_element_size
        _item.mandatory_code       yes 
        _item_type.code            float
        _item_units.code           'metres'
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0.0
         save_
    
    
    #####################
    # ARRAY_INTENSITIES #
    #####################
    
    
    save_ARRAY_INTENSITIES
        _category.description
    ;
                  Data items in the ARRAY_INTENSITIES category record the
                  information required to recover the intensity data from 
                  the set of data values stored in the ARRAY_DATA category.
    
                  The actual detector may have a complex relationship
                  between the raw intensity values and the number of
                  incident photons.  In most cases, the number stored
                  in the final array will have a simple linear relationship
                  to the actual number of incident photons, given by
                  '_array_intensities.gain'.  If raw, uncorrected values
                  are presented (e.g for calibration experiments), the
                  value of '_array_intensities.linearity' will be 'raw'
                  and '_array_intensities.gain' will not be used.
    
    ;
        _category.id                   array_intensities
        _category.mandatory_code       no
        loop_
        _category_key.name             '_array_intensities.array_id'
                                       '_array_intensities.binary_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1
    ;
    ;
            loop_
            _array_intensities.array_id
            _array_intensities.linearity 
            _array_intensities.gain      
            _array_intensities.overload  
            _array_intensities.undefined_value 
            image_1   linear  1.2    655535   0
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_intensities.array_id
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category. 
    ;
        _item.name                  '_array_intensities.array_id'
        _item.category_id             array_intensities
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__array_intensities.binary_id
        _item_description.description
    ;             This item is a pointer to '_array_data.binary_id' in the
                  ARRAY_DATA category. 
    ;
        _item.name                  '_array_intensities.binary_id'
        _item.category_id             array_intensities
        _item.mandatory_code          implicit
        _item_type.code               int
         save_
    
    
    save__array_intensities.gain
        _item_description.description
    ;              
                   Detector "gain". The factor by which linearized 
                   intensity count values should be divided to produce
                   true photon counts.
    ;
        _item.name              '_array_intensities.gain'
        _item.category_id          array_intensities
        _item.mandatory_code       yes
        _item_type.code            float
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0.0
        _item_units.code           'counts_per_photon'
         loop_
        _item_related.related_name
        _item_related.function_code  '_array_intensities.gain_esd'
                                     'associated_value'
        save_
    
      
    save__array_intensities.gain_esd
        _item_description.description
    ;              
                  The estimated standard deviation in detector "gain".
    ;
        _item.name              '_array_intensities.gain_esd'
        _item.category_id          array_intensities
        _item.mandatory_code       yes
        _item_type.code            float
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0.0
    
        _item_units.code          'counts_per_photon'
         loop_
        _item_related.related_name
        _item_related.function_code  '_array_intensities.gain'
                                     'associated_esd'
        save_
    
    
    save__array_intensities.linearity
        _item_description.description
    ;
                   The intensity linearity scaling used from raw intensity
                   to the stored element value:
    
                   'linear' is obvious
    
                   'offset'  means that the value defined by 
                   '_array_intensities.offset' should be added to each
                    element value.  
    
                   'scaling' means that the value defined by 
                   '_array_intensities.scaling' should be multiplied with each 
                   element value.  
    
                   'scaling_offset' is the combination of the two previous cases, 
                   with the scale factor applied before the offset value.
    
                   'sqrt_scaled' means that the square root of raw 
                   intensities multiplied by '_array_intensities.scaling' is
                   calculated and stored, perhaps rounded to the nearest 
                   integer. Thus, linearization involves dividing the stored
                   values by '_array_intensities.scaling' and squaring the 
                   result. 
    
                   'logarithmic_scaled' means that the logarithm based 10 of
                   raw intensities multiplied by '_array_intensities.scaling' 
                   is calculated and stored, perhaps rounded to the nearest 
                   integer. Thus, linearization involves dividing the stored
                   values by '_array_intensities.scaling' and calculating 10
                   to the power of this number.
    
                   'raw' means that the data is a set of raw values straight 
                   from the detector.
    ;
    
        _item.name               '_array_intensities.linearity'
        _item.category_id          array_intensities
        _item.mandatory_code       yes
        _item_type.code            code
         loop_
        _item_enumeration.value   
        _item_enumeration.detail   
                                  'linear' .
                                  'offset'           
    ;
                   The value defined by  '_array_intensities.offset' should 
                   be added to each element value.  
    ;
                                  'scaling'
    ;
                   The value defined by '_array_intensities.scaling' should be 
                   multiplied with each element value.  
    ;
                                  'scaling_offset'   
    ;
                   The combination of the scaling and offset 
                   with the scale factor applied before the offset value.
    ;
                                  'sqrt_scaled'      
    ;
                   The square root of raw intensities multiplied by 
                   '_array_intensities.scaling' is calculated and stored, 
                   perhaps rounded to the nearest integer. Thus, 
                   linearization involves dividing the stored
                   values by '_array_intensities.scaling' and squaring the 
                   result. 
    ;
                                  'logarithmic_scaled'
    ;
                   The logarithm based 10 of raw intensities multiplied by 
                   '_array_intensities.scaling'  is calculated and stored, 
                   perhaps rounded to the nearest integer. Thus, 
                   linearization involves dividing the stored values by 
                   '_array_intensities.scaling' and calculating 10 to the 
                   power of this number.
    ;
                                  'raw'
    ;
                   The array consists of raw values to which no corrections have
                   been applied.  While the handling of the data is similar to 
                   that given for 'linear' data with no offset, the meaning of 
                   the data differs in that the number of incident photons is 
                   not necessarily linearly related to the number of counts 
                   reported.  This value is intended for use either in 
                   calibration experiments or to allow for handling more 
                   complex data fitting algorithms than are allowed for by 
                   this data item.
    ;
    
        save_
      
      
    save__array_intensities.offset
        _item_description.description
    ;
                   Offset value to add to array element values in the manner
                   described by item '_array_intensities.linearity'.
    ;
        _item.name                 '_array_intensities.offset'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        save_
    
    
    save__array_intensities.scaling
        _item_description.description
    ;
                   Multiplicative scaling value to be applied to array data
                   in the manner described by item
                   '_array_intensities.linearity'.
    ;
        _item.name                 '_array_intensities.scaling'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        save_
    
    
    save__array_intensities.overload
        _item_description.description
    ;
                   The saturation intensity level for this data array.
    ;
        _item.name                 '_array_intensities.overload'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        _item_units.code          'counts'
        save_
    
      
    save__array_intensities.undefined_value
        _item_description.description
    ;
                   A value to be substituted for undefined values in 
                   the data array.
    ;
        _item.name                 '_array_intensities.undefined_value'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        save_
    
    
    ###################
    # ARRAY_STRUCTURE #
    ###################
    
    
    save_ARRAY_STRUCTURE
        _category.description
    ;
         Data items in the ARRAY_STRUCTURE category record the organization and 
         encoding of array data which may be stored in the ARRAY_DATA category.
    ;
        _category.id                   array_structure
        _category.mandatory_code       no
        _category_key.name             '_array_structure.id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 -
    ;
    ;
         loop_
        _array_structure.id 
        _array_structure.encoding_type        
        _array_structure.compression_type     
        _array_structure.byte_order           
         image_1       "unsigned 16-bit integer"  none  little_endian
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_structure.byte_order
        _item_description.description
    ;
                   The order of bytes for integer values which require more
                   than 1-byte. 
    
                   (IBM-PC's and compatibles, and Dec-Vaxes use low-byte-first
                   ordered integers, whereas Hewlett Packard 700 
                   series, Sun-4 and Silicon Graphics use high-byte-first
                   ordered integers.  Dec-Alphas can produce/use either
                   depending on a compiler switch.)
    ;
    
        _item.name                     '_array_structure.byte_order'
        _item.category_id               array_structure
        _item.mandatory_code            yes 
        _item_type.code                 code
         loop_
        _item_enumeration.value        
        _item_enumeration.detail        
                                       'big_endian'
    ;
            The first byte in the byte stream of the bytes which make up an 
            integer value is the most significant byte of an integer. 
    ;
                                       'little_endian'
    ;
            The last byte in the byte stream of the bytes which make up an 
            integer value is the most significant byte of an integer.
    ;
         save_
    
    
    save__array_structure.compression_type 
        _item_description.description
    ;
                  Type of data compression method used to compress the array
                  data. 
    ;
        _item.name                   '_array_structure.compression_type'
        _item.category_id             array_structure
        _item.mandatory_code          no 
        _item_type.code               code
        _item_default.value           'none'
         loop_
        _item_enumeration.value       
        _item_enumeration.detail
                                      'none'
    ;
            Data are stored in normal format as defined by 
            '_array_structure.encoding_type' and 
            '_array_structure.byte_order'.
    ;
                                      'byte_offsets'
    ;
            Using the compression scheme defined in CBF definition
            Section 5.0.
    ;
                                      'packed'
    ;
            Using the 'packed' compression scheme, a CCP4-style packing
            (CBFlib section 3.3.2)
    ;
                                      'canonical'
    ;
            Using the 'canonical' compression scheme (CBFlib section
            3.3.1)
    ;
        save_
    
    
    save__array_structure.encoding_type
        _item_description.description
    ;
                   Data encoding of a single element of array data. 
                   
                   In several cases, the IEEE format is referenced.
                   See "IEEE Standard for Binary Floating-Point Arithmetic",
                   ANSI/IEEE Std 754-1985, the Institute of Electrical and
                   Electronics Engineers, Inc., NY 1985.  
    ;
    
        _item.name                '_array_structure.encoding_type'
        _item.category_id          array_structure
        _item.mandatory_code       yes 
        _item_type.code            uline
         loop_
        _item_enumeration.value   
                                  'unsigned 8-bit integer'
                                  'signed 8-bit integer'
                                  'unsigned 16-bit integer'
                                  'signed 16-bit integer'
                                  'unsigned 32-bit integer'
                                  'signed 32-bit integer'
                                  'signed 32-bit real IEEE'
                                  'signed 64-bit real IEEE'
                                  'signed 32-bit complex IEEE'
         save_
    
    
    save__array_structure.id
        _item_description.description
    ;             The value of '_array_structure.id' must uniquely identify 
                  each item of array data. 
    ;
        loop_
        _item.name                  
        _item.category_id             
        _item.mandatory_code          
                 '_array_structure.id'              array_structure      yes
                 '_array_data.array_id'             array_data           yes
                 '_array_structure_list.array_id'   array_structure_list yes
                 '_array_intensities.array_id'      array_intensities    yes
                 '_diffrn_data_frame.array_id'      diffrn_data_frame    yes
    
    
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_array_data.array_id'             '_array_structure.id'
                 '_array_structure_list.array_id'   '_array_structure.id'
                 '_array_intensities.array_id'      '_array_structure.id'
                 '_diffrn_data_frame.array_id'      '_array_structure.id'
    
         save_
    
    
    ########################
    # ARRAY_STRUCTURE_LIST #
    ########################
    
    
    save_ARRAY_STRUCTURE_LIST
        _category.description
    ;
         Data items in the ARRAY_STRUCTURE_LIST category record the size 
         and organization of each array dimension.
    
         The relationship to physical axes may be given.
    ;
        _category.id                   array_structure_list
        _category.mandatory_code       no
         loop_
        _category_key.name             '_array_structure_list.array_id'
                                       '_array_structure_list.index'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 - An image array of 1300 x 1200 elements.  The raster 
                        order of the image is left-to-right (increasing) in the
                        first dimension and bottom-to-top (decreasing) in 
                        the second dimension.
    ;
    ;
            loop_
           _array_structure_list.array_id  
           _array_structure_list.index
           _array_structure_list.dimension 
           _array_structure_list.precedence 
           _array_structure_list.direction
           _array_structure_list.axis_set_id
            image_1   1    1300    1     increasing  ELEMENT_X
            image_1   2    1200    2     decreasing  ELEMENY_Y
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_structure_list.array_id
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category. 
    ;
        _item.name                  '_array_structure_list.array_id'
        _item.category_id             array_structure_list
        _item.mandatory_code          yes
        _item_type.code               code
    save_
    
    
    save__array_structure_list.axis_set_id
        _item_description.description
    ;              This is a descriptor for the physical axis or set of axes 
                   corresponding to an array index.
                   
                   This data item is related to the axes of the detector 
                   itself given in DIFFRN_DETECTOR_AXIS, but usually differ
                   in that the axes in this category are the axes of the
                   coordinate system of reported data points, while the axes in
                   DIFFRN_DETECTOR_AXIS are the physical axes 
                   of the detector describing the "poise" of the detector as an
                   overall physical object.
                   
                   If there is only one axis in the set, the identifier of 
                   that axis should be used as the identifier of the set.
                   
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
               '_array_structure_list.axis_set_id'
                                      array_structure_list            yes
               '_array_structure_list_axis.axis_set_id'
                                      array_structure_list_axis       implicit
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_array_structure_list_axis.axis_set_id'
                                   '_array_structure_list.axis_set_id'
    
    
         save_
    
    
    save__array_structure_list.dimension
        _item_description.description
    ;              
                   The number of elements stored in the array structure in this 
                   dimension.
    ;
        _item.name                '_array_structure_list.dimension'
        _item.category_id          array_structure_list
        _item.mandatory_code       yes 
        _item_type.code            int
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                1  1
                                .  1
         save_
    
    
    save__array_structure_list.direction
        _item_description.description
    ;
                  Identifies the direction in which this array index changes.
    ;
        _item.name                '_array_structure_list.direction'
        _item.category_id          array_structure_list
        _item.mandatory_code       yes 
        _item_type.code            int
         loop_
        _item_enumeration.value
        _item_enumeration.detail        
    
                                  'increasing'
    ;
             Indicates the index changes from 1 to the maximum dimension.
    ;
                                  'decreasing'
    ;
             Indicates the index changes from the maximum dimension to 1.
    ;
         save_
    
    
    save__array_structure_list.index
        _item_description.description
    ;              
                   Identifies the one-based index of the row or column in the
                   array structure.
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
               '_array_structure_list.index'        array_structure_list   yes
               '_array_structure_list.precedence'   array_structure_list   yes
               '_array_element_size.index'          array_element_size     yes
    
        _item_type.code            int
    
         loop_
        _item_linked.child_name
        _item_linked.parent_name
              '_array_element_size.index'         '_array_structure_list.index'
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                1  1
                                .  1
         save_
    
    
    save__array_structure_list.precedence
        _item_description.description
    ;
                   Identifies the rank order in which this array index changes 
                   with respect to other array indices.  The precedence of 1  
                   indicates the index which changes fastest.
    ;
        _item.name                '_array_structure_list.precedence'
        _item.category_id          array_structure_list
        _item.mandatory_code       yes 
        _item_type.code            int
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                1  1
                                .  1
         save_
    
    
    #############################
    # ARRAY_STRUCTURE_LIST_AXIS #
    #############################
    
    save_ARRAY_STRUCTURE_LIST_AXIS
        _category.description
    ;
         Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe
         the physical settings of sets axes for the centres of pixels that 
         correspond to data points described in the 
         ARRAY_STRUCTURE_LIST category. 
         
         In the simplest cases, the physical increments of a single axis correspond
         to the increments of a single array index.  More complex organizations,
         e.g. spiral scans, may require coupled motions along multiple axes.
         
         Note that a spiral scan uses two coupled axis, one for the angular 
         direction, one for the radial direction.  This differs from a 
         cylindrical scan for which the two axes are not coupled into one set.
         
    ;
        _category.id                   array_structure_list_axis
        _category.mandatory_code       no
         loop_
        _category_key.name
                                      '_array_structure_list_axis.axis_set_id'
                                      '_array_structure_list_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'array_data_group'
         save_
    
    
    save__array_structure_list_axis.axis_id
        _item_description.description
    ;
                   The value of this data item is the identifier of one of
                   the axes from the set of axes for which settings are being 
                   specified.
    
                   Multiple axes may be specified for the same value of
                   '_array_structure_list_axis.axis_set_id'
    
                   This item is a pointer to '_axis.id' in the
                   AXIS category.
    ;
        _item.name                 '_array_structure_list_axis.axis_id'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       yes
        _item_units.code           code
         save_
    
    
    save__array_structure_list_axis.axis_set_id
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   set of axes for which axis settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   '_array_structure_list_axis.axis_set_id'.
    
                   This item is a pointer to
                   '_array_structure_list.axis_set_id'
                   in the ARRAY_STRUCTURE_LIST category.
                   
                   If this item is not specified, it defaults to the corresponding
                   axis identifier.
    ;
        _item.name                 '_array_structure_list_axis.axis_set_id'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       implicit
        _item_units.code           code
         save_
    
    
    save__array_structure_list_axis.angle
        _item_description.description
    ;
                   The setting of the specified axis in degrees for the first
                   data point of the array index with the corresponding value
                   of '_array_structure_list.axis_set_id'.  If the index is
                   specified as 'increasing' this will be the centre of the
                   pixel with index value 1.  If the index is specified as
                   'decreasing' this will be the centre of the pixel with
                   maximum index value. 
    ;
        _item.name                 '_array_structure_list_axis.angle'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__array_structure_list_axis.angle_increment
        _item_description.description
    ;
                   The pixel-centre-to-pixel-centre increment in the angular 
                   setting of the specified axis in degrees.  This is not 
                   meaningful in the case of 'constant velocity' spiral scans  
                   and should not be specified in that case.  
    
                   See '_array_structure_list_axis.angular_pitch'.
                   
    ;
        _item.name                 '_array_structure_list_axis.angle_increment'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__array_structure_list_axis.displacement
        _item_description.description
    ;
                   The setting of the specified axis in millimetres for the first
                   data point of the array index with the corresponding value
                   of '_array_structure_list.axis_set_id'.  If the index is
                   specified as 'increasing' this will be the centre of the
                   pixel with index value 1.  If the index is specified as
                   'decreasing' this will be the centre of the pixel with
                   maximum index value. 
    
    ;
        _item.name               '_array_structure_list_axis.displacement'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__array_structure_list_axis.displacement_increment
        _item_description.description
    ;
                   The pixel-centre-to-pixel-centre increment for the displacement 
                   setting of the specified axis in millimetres.
                   
    ;
        _item.name                 
            '_array_structure_list_axis.displacement_increment'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
      
    
    save__array_structure_list_axis.angular_pitch
        _item_description.description
    ;
                   The pixel-centre-to-pixel-centre distance for a one step 
                   change in the setting of the specified axis in millimetres.
                   
                   This is meaningful only for 'constant velocity' spiral scans,
                   or for uncoupled angular scans at a constant radius
                   (cylindrical scan) and should not be specified for cases
                   in which the angle between pixels, rather than the distance
                   between pixels is uniform.
                   
                   See '_array_structure_list_axis.angle_increment'.
                   
    ;
        _item.name               '_array_structure_list_axis.angular_pitch'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
       
    
    save__array_structure_list_axis.radial_pitch
        _item_description.description
    ;
                   The radial distance from one "cylinder" of pixels to the
                   next in millimetres.  If the scan is a 'constant velocity'
                   scan with differing angular displacements between pixels,
                   the value of this item may differ significantly from the
                   value of '_array_structure_list_axis.displacement_increment'.
                   
    ;
        _item.name               '_array_structure_list_axis.radial_pitch'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
      
    
    
    ########
    # AXIS #
    ########
    
    save_AXIS
        _category.description
    ;
         Data items in the AXIS category record the information required
         to describe the various goniometer, detector, source and other
         axes needed to specify a data collection.  The location of each
         axis is specified by two vectors: the axis itself, given as a unit
         vector, and an offset to the base of the unit vector.  These vectors
         are referenced to a right-handed laboratory coordinate system with
         its origin in the sample or specimen:
         
                                 | Y (to complete right-handed system)
                                 |
                                 |
                                 |
                                 |
                                 |
                                 |________________X
                                /       principal goniometer axis
                               /
                              /
                             /
                            /
                           /Z (to source)
    
    
                                                          
         Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from
         the sample or specimen along the  principal axis of the goniometer.
         
         Axis 2 (Y): The Y-axis completes an orthogonal right-handed system
         defined by the X-axis and the Z-axis (see below).
         
         Axis 3 (Z): The Z-axis is derived from the source axis which goes from 
         the sample to the source.  The Z-axis is the component of the source axis
         in the direction of the source orthogonal to the X-axis in the plane 
         defined by the X-axis and the source axis.
              
         These axes are based on the goniometer, not on the orientation of the 
         detector, gravity, etc.  The vectors necessary to specify all other
         axes are given by sets of three components in the order (X, Y, Z).
         If the axis involved is a rotation axis, it is right handed, i.e. as
         one views the object to be rotated from the origin (the tail) of the 
         unit vector, the rotation is clockwise.  If a translation axis is
         specified, the direction of the unit vector specifies the sense of
         positive translation.
         
         Note:  This choice of coordinate system is similar to, but significantly
         different from the choice in MOSFLM (Andrew G.W. Leslie, Harry Powell,
         MRC Laboratory of Molecular Biology, Hills Road, Cambridge CB2 2QH, UK
         http://www.dl.ac.uk/CCP/CCP4/dist/x-windows/Mosflm/).  In MOSFLM,
         X is along the X-ray beam (the CBF/imgCIF Z axis) and Z is along the 
         rotation axis.
    
         All rotations are given in degrees and all translations are given in mm.
         
         Axes may be dependent on one another.  The X-axis is the only goniometer
         axis the direction of which is strictly connected to the hardware.  All
         other axes are specified by the positions they would assume when the
         axes upon which they depend are at their zero points.
         
         When specifying detector axes, the axis is given to the beam centre.
         The location of the beam centre on the detector should be given in the
         DIFFRN_DETECTOR category in distortion-corrected mm from the (0,0) corner
         of the detector.
         
         It should be noted that many different origins arise in the definition
         of an experiment.  In particular, as noted above, we need to specify the
         location of the beam centre on the detector in terms of the origin of the
         detector, which is, of course, not coincident with the centre of the
         sample.  
    ;
        _category.id                   axis
        _category.mandatory_code       no
         loop_
        _category_key.name          '_axis.id' 
                                    '_axis.equipment'               
         loop_
        _category_group.id           'inclusive_group'
                                     'axis_group'
                                     'diffrn_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 -
            
            This example shows the axis specification of the axes of a kappa
            geometry goniometer (See "X-Ray Structure Determination, A Practical
            Guide", 2nd ed. by  G. H. Stout, L. H. Jensen, Wiley Interscience,
            1989, 453 pp, p 134.).
            
            There are three axes specified, and no offsets.  The outermost axis,
            omega, is pointed along the X-axis.  The next innermost axis, kappa,
            is at a 50 degree angle to the X-axis, pointed away from the source.
            The innermost axis, phi, aligns with the X-axis when omega and
            phi are at their zero-points.  If T-omega, T-kappa and T-phi
            are the transformation matrices derived from the axis settings,
            the complete transformation would be:
                x' = (T-omega) (T-kappa) (T-phi) x
    ;
    ;
             loop_
            _axis.id
            _axis.type
            _axis.equipment
            _axis.depends_on
            _axis.vector[1] _axis.vector[2] _axis.vector[3]
            omega rotation goniometer     .    1        0        0
            kappa rotation goniometer omega    -.64279  0       -.76604
            phi   rotation goniometer kappa    1        0        0   
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 2 -
            
            This example show the axis specification of the axes of a
            detector, source and gravity.  We have juggled the order as a
            reminder that the ordering of presentation of tokens is not
            significant.  We have taken the centre of rotation of the detector
            to be 68 millimetres in the direction away from the source.
    ;
    ;
            loop_
            _axis.id
            _axis.type
            _axis.equipment
            _axis.depends_on
            _axis.vector[1] _axis.vector[2] _axis.vector[3]
            _axis.offset[1] _axis.offset[2] _axis.offset[3]
            source       .        source     .       0     0     1   . . .
            gravity      .        gravity    .       0    -1     0   . . .
            tranz     translation detector rotz      0     0     1   0 0 -68
            twotheta  rotation    detector   .       1     0     0   . . .
            roty      rotation    detector twotheta  0     1     0   0 0 -68
            rotz      rotation    detector roty      0     0     1   0 0 -68
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__axis.depends_on
        _item_description.description
    ;             The value of '_axis.depends_on' specifies the next outermost
                  axis upon which this axis depends.
                  
                  This item is a pointer to '_axis.id' in the same category.
    ;
        _item.name                      '_axis.depends_on'
        _item.category_id                 axis
        _item.mandatory_code              no
    
         save_
    
    
    save__axis.equipment
        _item_description.description
    ;             The value of  '_axis.equipment' specifies the type of
                  equipment using the axis:  'goniometer', 'detector',
                  'gravity', 'source' or 'general'.
    ;
        _item.name                      '_axis.equipment'
        _item.category_id                 axis
        _item.mandatory_code              no
        _item_type.code                   ucode
        _item_default.value               general
         loop_
        _item_enumeration.value
        _item_enumeration.detail   goniometer
                                  'equipment used to orient or position samples'
                                   detector
                                  'equipment used to detect reflections'
                                   general
                                  'equipment used for general purposes'
                                   gravity
                                  'axis specifying the downward direction'
                                   source
                                  'axis specifying the direction sample to source'
    
         save_
    
    
    save__axis.offset[1]
        _item_description.description
    ;              The [1] element of the 3-element vector used to specify
                   the offset to the base of a rotation or translation axis.
                   
                   The vector is specified in millimetres
    ;
        _item.name                  '_axis.offset[1]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    
    save__axis.offset[2]
        _item_description.description
    ;              The [2] element of the 3-element vector used to specify
                   the offset to the base of a rotation or translation axis.
                   
                   The vector is specified in millimetres
    ;
        _item.name                  '_axis.offset[2]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    
    save__axis.offset[3]
        _item_description.description
    ;              The [3] element of the 3-element vector used to specify
                   the offset to the base of a rotation or translation axis.
                   
                   The vector is specified in millimetres
    ;
        _item.name                  '_axis.offset[3]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    
    save__axis.id
        _item_description.description
    ;             The value of '_axis.id' must uniquely identify
                  each axis relevant to the experiment.  Note that multiple
                  pieces of equipment may share the same axis (e.g. a twotheta
                  arm), so that the category key for AXIS also includes the
                  equipment.
    ;
        loop_
        _item.name
        _item.category_id
        _item.mandatory_code
             '_axis.id'                         axis                    yes
             '_array_structure_list_axis.axis_id'
                                                array_structure_list_axis
                                                                        yes
             '_diffrn_detector_axis.axis_id'    diffrn_detector_axis    yes
             '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes
             '_diffrn_scan_axis.axis_id'        diffrn_scan_axis        yes
             '_diffrn_scan_frame_axis.axis_id'  diffrn_scan_frame_axis  yes
    
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
             '_axis.depends_on'                   '_axis.id'
             '_array_structure_list_axis.axis_id' '_axis.id'
             '_diffrn_detector_axis.axis_id'      '_axis.id'
             '_diffrn_measurement_axis.axis_id'   '_axis.id'
             '_diffrn_scan_axis.axis_id'          '_axis.id'      
             '_diffrn_scan_frame_axis.axis_id'    '_axis.id'
    
         save_
    
    
    save__axis.type
        _item_description.description
    ;             The value of '_axis.type' specifies the type of
                  axis:  'rotation', 'translation' (or 'general' when
                  the type is not relevant, as for gravity).
    ;
        _item.name                      '_axis.type'
        _item.category_id                 axis
        _item.mandatory_code              no
        _item_type.code                   ucode
        _item_default.value               general
         loop_
        _item_enumeration.value
        _item_enumeration.detail      rotation
                                     'right-handed axis of rotation'
                                      translation
                                     'translation in the direction of the axis'
                                      general
                                     'axis for which the type is not relevant'
    
         save_
    
    
    save__axis.vector[1]
        _item_description.description
    ;              The [1] element of the 3-element vector used to specify
                   the direction of a rotation or translation axis.
                   The vector should be normalized to be a unit vector and
                   is dimensionless.
    ;
        _item.name                  '_axis.vector[1]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
         save_
    
    save__axis.vector[2]
        _item_description.description
    ;              The [2] element of the 3-element vector used to specify
                   the direction of a rotation or translation axis.
                   The vector should be normalized to be a unit vector and
                   is dimensionless.
    ;
        _item.name                  '_axis.vector[2]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
         save_
    
    save__axis.vector[3]
        _item_description.description
    ;              The [3] element of the 3-element vector used to specify
                   the direction of a rotation or translation axis.
                   The vector should be normalized to be a unit vector and
                   is dimensionless.
    ;
        _item.name                  '_axis.vector[3]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
         save_
    
    
    
    #####################
    # DIFFRN_DATA_FRAME #
    #####################
    
    
    save_DIFFRN_DATA_FRAME
        _category.description
    ;
                  Data items in the DIFFRN_DATA_FRAME category record
                  the details about each frame of data. 
                  
                  The items in this category were previously in a
                  DIFFRN_FRAME_DATA category, which is now deprecated.
                  The items from the old category are provided
                  as aliases but should not be used for new work.
    ;
        _category.id                   diffrn_data_frame
        _category.mandatory_code       no
         loop_
        _category_key.name             '_diffrn_data_frame.id'
                                       '_diffrn_data_frame.detector_element_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 - A frame containing data from 4 frame elements.
                    Each frame element has a common array configuration
                    'array_1' described in ARRAY_STRUCTURE and related
                    categories.  The data for each detector element is 
                    stored in four groups of binary data in the
                    ARRAY_DATA category, linked by the array_id and
                    binary_id
    ;
    ;
            loop_
            _diffrn_data_frame.id
            _diffrn_data_frame.detector_element_id
            _diffrn_data_frame.array_id
            _diffrn_data_frame.binary_id
            frame_1   d1_ccd_1  array_1  1  
            frame_1   d1_ccd_2  array_1  2 
            frame_1   d1_ccd_3  array_1  3 
            frame_1   d1_ccd_4  array_1  4 
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
    
    
    save__diffrn_data_frame.array_id
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category. 
    ;
        _item.name                  '_diffrn_data_frame.array_id'
        _item.category_id             diffrn_data_frame
        _item.mandatory_code          yes
        _item_aliases.alias_name    '_diffrn_frame_data.array_id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0.00
        _item_type.code               code
         save_
    
    
    save__diffrn_data_frame.binary_id
        _item_description.description
    ;             This item is a pointer to '_array_data.binary_id' in the
                  ARRAY_DATA category. 
    ;
        _item.name                  '_diffrn_data_frame.binary_id'
        _item.category_id             diffrn_data_frame
        _item.mandatory_code          implicit
        _item_aliases.alias_name    '_diffrn_frame_data.binary_id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               int
         save_
    
    
    save__diffrn_data_frame.detector_element_id
        _item_description.description
    ;             
                   This item is a pointer to '_diffrn_detector_element.id'
                   in the DIFFRN_DETECTOR_ELEMENT category. 
    ;
        _item.name                  '_diffrn_data_frame.detector_element_id'
        _item.category_id             diffrn_data_frame
        _item.mandatory_code          yes
        _item_aliases.alias_name    '_diffrn_frame_data.detector_element_id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         save_
    
    
    save__diffrn_data_frame.id
        _item_description.description
    ;             
                  The value of '_diffrn_data_frame.id' must uniquely identify
                  each complete frame of data.
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
               '_diffrn_data_frame.id'        diffrn_data_frame  yes
               '_diffrn_refln.frame_id'       diffrn_refln       yes
               '_diffrn_scan.frame_id_start'  diffrn_scan        yes
               '_diffrn_scan.frame_id_end'    diffrn_scan        yes
               '_diffrn_scan_frame.frame_id'  diffrn_scan_frame  yes
               '_diffrn_scan_frame_axis.frame_id'  
                                              diffrn_scan_frame_axis
                                                                 yes
        _item_aliases.alias_name    '_diffrn_frame_data.id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_diffrn_refln.frame_id'        '_diffrn_data_frame.id'
               '_diffrn_scan.frame_id_start'   '_diffrn_data_frame.id'
               '_diffrn_scan.frame_id_end'     '_diffrn_data_frame.id'
               '_diffrn_scan_frame.frame_id'   '_diffrn_data_frame.id'
               '_diffrn_scan_frame_axis.frame_id'
                                               '_diffrn_data_frame.id'
         save_
    
    
    ##########################################################################
    #  The following is a restatement of the mmCIF DIFFRN_DETECTOR,          #
    #  DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for      #
    #  the CBF/imgCIF extensions                                             #
    ##########################################################################
    
    ###################
    # DIFFRN_DETECTOR #
    ###################
    
    
    save_DIFFRN_DETECTOR
        _category.description
    ;              Data items in the DIFFRN_DETECTOR category describe the 
                   detector used to measure the scattered radiation, including
                   any analyser and post-sample collimation.
    ;
        _category.id                  diffrn_detector
        _category.mandatory_code      no
         loop_
        _category_key.name          '_diffrn_detector.diffrn_id'
                                    '_diffrn_detector.id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 - based on PDB entry 5HVP and laboratory records for the
                    structure corresponding to PDB entry 5HVP
    ;
    ;
        _diffrn_detector.diffrn_id             'd1'
        _diffrn_detector.detector              'multiwire'
        _diffrn_detector.type                  'Siemens'
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__diffrn_detector.details
        _item_description.description
    ;              A description of special aspects of the radiation detector.
    ;
        _item.name                  '_diffrn_detector.details'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_detector_details'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code                   text
        _item_examples.case        'slow mode' 
         save_
    
    
    save__diffrn_detector.detector
        _item_description.description
    ;              The general class of the radiation detector.
    ;
        _item.name                  '_diffrn_detector.detector'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
         loop_
        _item_aliases.alias_name
        _item_aliases.dictionary
        _item_aliases.version       '_diffrn_radiation_detector'
                                      cifdic.c91
                                      1.0
                                    '_diffrn_detector'
                                      cif_core.dic
                                      2.0
        _item_type.code               text
         loop_
        _item_examples.case          'photographic film'
                                     'scintillation counter'
                                     'CCD plate'
                                     'BF~3~ counter'
         save_
    
    
    save__diffrn_detector.diffrn_id
        _item_description.description
    ;              This data item is a pointer to '_diffrn.id' in the DIFFRN
                   category.
    
                   The value of '_diffrn.id' uniquely defines a set of
                   diffraction data.
    ;
        _item.name                  '_diffrn_detector.diffrn_id'
        _item.mandatory_code          yes
         save_
    
    
    save__diffrn_detector.dtime
        _item_description.description
    ;              The deadtime in microseconds of the detectors used to
                   measure the diffraction intensities.
    ;
        _item.name                  '_diffrn_detector.dtime'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
         loop_
        _item_aliases.alias_name
        _item_aliases.dictionary
        _item_aliases.version       '_diffrn_radiation_detector_dtime'
                                      cifdic.c91
                                      1.0
                                    '_diffrn_detector_dtime'
                                      cif_core.dic
                                      2.0
         loop_  
        _item_range.maximum           
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
        _item_units.code              microseconds
         save_
    
    
    save__diffrn_detector.id
        _item_description.description
    ;             
                   The value of '_diffrn_detector.id' must uniquely identify
                   each detector used to collect each diffraction data set.
    
                   If the value of '_diffrn_detector.id' is not given, it is
                   implicitly equal to the value of
                   '_diffrn_detector.diffrn_id'
    ;
         loop_
        _item.name                 
        _item.category_id
        _item.mandatory_code
                 '_diffrn_detector.id'         diffrn_detector       implicit
                 '_diffrn_detector_axis.detector_id'
                                               diffrn_detector_axis       yes
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_detector_axis.detector_id'
                                             '_diffrn_detector.id'
    
        _item_type.code               code
         save_
    
    
    save__diffrn_detector.number_of_axes
        _item_description.description
    ;             
                   The value of '_diffrn_detector.number_of_axes' gives the 
                   number of axes of the positioner for the detector identified 
                   by '_diffrn_detector.id'.
                   
                   The word "positioner" is a general term used in
                   instrumentation design for devices that are used to change
                   the positions of portions of apparatus by linear
                   translation, rotation, or combinations of such motions.
                   
                   Axes which are used to provide a coordinate system for the
                   face of an area detetctor should not be counted for this
                   data item.
    
                   The description of each axis should be provided by entries 
                   in DIFFRN_DETECTOR_AXIS.
    ;
        _item.name                  '_diffrn_detector.number_of_axes'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
         loop_
        _item_range.maximum
        _item_range.minimum           .   1
                                      1   1
        _item_type.code               int
         save_
    
    
    save__diffrn_detector.type
        _item_description.description
    ;              The make, model or name of the detector device used.
    ;
        _item.name                  '_diffrn_detector.type'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_detector_type'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         save_
    
    
    ########################
    # DIFFRN_DETECTOR_AXIS #
    ########################
    
    
    save_DIFFRN_DETECTOR_AXIS
        _category.description
    ;
         Data items in the DIFFRN_DETECTOR_AXIS category associate
         axes with detectors.
    ;
        _category.id                   diffrn_detector_axis
        _category.mandatory_code       no
         loop_
        _category_key.name          '_diffrn_detector_axis.detector_id'
                                    '_diffrn_detector_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_detector_axis.axis_id
        _item_description.description
    ;
                   This data item is a pointer to '_axis.id' in
                   the AXIS category.
    ;
        _item.name                  '_diffrn_detector_axis.axis_id'
        _item.category_id             diffrn_detector_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_detector_axis.detector_id
        _item_description.description
    ;
                   This data item is a pointer to '_diffrn_detector.id' in
                   the DIFFRN_DETECTOR category.
    
                   This item was previously named '_diffrn_detector_axis.id'
                   which is now a deprecated name.  The old name is
                   provided as an alias but should not be used for new work.
    
    ;
        _item.name                  '_diffrn_detector_axis.detector_id'
        _item.category_id             diffrn_detector_axis
        _item.mandatory_code          yes
        _item_aliases.alias_name    '_diffrn_detector_axis.id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         save_
    
    
    ###########################
    # DIFFRN_DETECTOR_ELEMENT #
    ###########################
    
    
    save_DIFFRN_DETECTOR_ELEMENT
        _category.description
    ;
                  Data items in the DIFFRN_DETECTOR_ELEMENT category record
                  the details about spatial layout and other characteristics
                  of each element of a detector which may have multiple elements.
                  
                  In most cases, the more detailed information provided
                  in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS
                  are preferable to simply providing the centre.
    
    ;
        _category.id                   diffrn_detector_element
        _category.mandatory_code       no
         loop_
        _category_key.name             '_diffrn_detector_element.id'
                                       '_diffrn_detector_element.detector_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 - Detector d1 is composed of four CCD detector elements,
            each 200 mm by 200 mm, arranged in a square. in the pattern
                        
                       1     2
                          *
                       3     4
    
            Note that the beam centre is slightly displaced from each of the
            detector elements, just beyond the lower right corner of 1,
            the lower left corner of 2, the upper right corner of 3 and
            the upper left corner of 4.
    ;
    ;
            loop_
            _diffrn_detector_element.detector_id
            _diffrn_detector_element.id
            _diffrn_detector_element.center[1]
            _diffrn_detector_element.center[2]
            d1     d1_ccd_1  201.5 -1.5
            d1     d1_ccd_2  -1.8  -1.5
            d1     d1_ccd_3  201.6 201.4  
            d1     d1_ccd_4  -1.7  201.5
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
    
    
    save__diffrn_detector_element.center[1]
        _item_description.description
    ;             
                  The value of '_diffrn_detector_element.center[1]' is the X
                  component of the distortion-corrected beam-centre in mm from
                  the (0, 0) (lower left) corner of the detector element viewed
                  from the sample side.
                  
                  The X and Y axes are the laboratory coordinate system
                  coordinates defined in the AXIS category measured
                  when all positioning axes for the detector are at their zero
                  settings.  If the resulting X or Y axis is then orthogonal to the
                  detector, the Z axis is used instead of the orthogonal axis.
                  
    ;
        _item.name                  '_diffrn_detector_element.center[1]'
        _item.category_id             diffrn_detector_element
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
    
        save_
    
    
    save__diffrn_detector_element.center[2]
        _item_description.description
    ;             
                  The value of '_diffrn_detector_element.center[2]' is the Y
                  component of the distortion-corrected beam-centre in mm from
                  the (0, 0) (lower left) corner of the detector element viewed
                  from the sample side.
                  
                  The X and Y axes are the laboratory coordinate system
                  coordinates defined in the AXIS category measured
                  when all positioning axes for the detector are at their zero
                  settings.  If the resulting X or Y axis is then orthogonal to the
                  detector, the Z axis is used instead of the orthogonal axis.
    
    ;
        _item.name                  '_diffrn_detector_element.center[2]'
        _item.category_id             diffrn_detector_element
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
    
        save_
    
    
    save__diffrn_detector_element.id
        _item_description.description
    ;             
                  The value of '_diffrn_detector_element.id' must uniquely
                  identify each element of a detector.
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
               '_diffrn_detector_element.id'
               diffrn_detector_element
               yes
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_diffrn_data_frame.detector_element_id'
               '_diffrn_detector_element.id'
    
         save_
    
    
    save__diffrn_detector_element.detector_id
        _item_description.description
    ;             
                   This item is a pointer to '_diffrn_detector.id'
                   in the DIFFRN_DETECTOR category. 
    ;
        _item.name                  '_diffrn_detector_element.detector_id'
        _item.category_id             diffrn_detector_element
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    
    ########################
    ## DIFFRN_MEASUREMENT ##
    ########################
    
    
    save_DIFFRN_MEASUREMENT
        _category.description
    ;              Data items in the DIFFRN_MEASUREMENT category record details
                   about the device used to orient and/or position the crystal
                   during data measurement and the manner in which the
                   diffraction data were measured.
    ;
        _category.id                  diffrn_measurement
        _category.mandatory_code      no
         loop_
        _category_key.name          '_diffrn_measurement.device'
                                    '_diffrn_measurement.diffrn_id'
                                    '_diffrn_measurement.id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 - based on PDB entry 5HVP and laboratory records for the
                    structure corresponding to PDB entry 5HVP
    ;
    ;
        _diffrn_measurement.diffrn_id          'd1'
        _diffrn_measurement.device             '3-circle camera'
        _diffrn_measurement.device_type        'Supper model x'
        _diffrn_measurement.device_details     'none'
        _diffrn_measurement.method             'omega scan'
        _diffrn_measurement.details
        ; Need new example here
        ;
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991).
                    Acta Cryst. C47, 2276-2277].
    ;
    ;
        _diffrn_measurement.diffrn_id       's1'
        _diffrn_measurement.device_type     'Philips PW1100/20 diffractometer'
        _diffrn_measurement.method          'theta/2theta (\q/2\q)'
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__diffrn_measurement.device
        _item_description.description
    ;              The general class of goniometer or device used to support
                   and orient the specimen.
                   
                   If the value of '_diffrn_measurement.device' is not given,
                   it is implicitly equal to the value of
                   '_diffrn_measurement.diffrn_id'.
    
                   Either '_diffrn_measurement.device' or
                   '_diffrn_measurement.id' may be used to link to other
                   categories.  If the experimental setup admits multiple
                   devices, then '_diffrn_measurement.id' is used to provide
                   a unique link.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
                 '_diffrn_measurement.device'  diffrn_measurement      implicit
                 '_diffrn_measurement_axis.measurement_device' 
                                               diffrn_measurement_axis implicit
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_measurement_axis.measurement_device'  
                                             '_diffrn_measurement.device'
        _item_aliases.alias_name    '_diffrn_measurement_device'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          '3-circle camera'
                                     '4-circle camera'
                                     'kappa-geometry camera'
                                     'oscillation camera'
                                     'precession camera'
         save_
    
    
    save__diffrn_measurement.device_details
        _item_description.description
    ;              A description of special aspects of the device used to
                   measure the diffraction intensities.
    ;
        _item.name                  '_diffrn_measurement.device_details'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_device_details'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
        _item_examples.case
    ;                                 commercial goniometer modified locally to
                                      allow for 90\% \t arc
    ;
         save_
    
    
    save__diffrn_measurement.device_type
        _item_description.description
    ;              The make, model or name of the measurement device
                   (goniometer) used.
    ;
        _item.name                  '_diffrn_measurement.device_type'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_device_type'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          'Supper model q'
                                     'Huber model r'
                                     'Enraf-Nonius model s'
                                     'homemade'
         save_
    
    
    save__diffrn_measurement.diffrn_id
        _item_description.description
    ;              This data item is a pointer to '_diffrn.id' in the DIFFRN 
                   category.
    ;
        _item.name                  '_diffrn_measurement.diffrn_id'
        _item.mandatory_code          yes
         save_
    
    
    save__diffrn_measurement.details
        _item_description.description
    ;              A description of special aspects of the intensity
                   measurement.
    ;
        _item.name                  '_diffrn_measurement.details'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_details'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
        _item_examples.case
    ;                                 440 frames, 0.20 degrees, 150 sec, detector
                                      distance 12 cm, detector angle 22.5 degrees
    ;
         save_
    
    
    save__diffrn_measurement.id
        _item_description.description
    ;             
                   The value of '_diffrn_measurement.id' must uniquely identify
                   the set of mechanical characteristics of the device used to 
                   orient and/or position the sample used during collection 
                   of each diffraction data set.
    
                   If the value of '_diffrn_measurement.id' is not given, it is
                   implicitly equal to the value of 
                   '_diffrn_measurement.diffrn_id'.
    
                   Either '_diffrn_measurement.device' or
                   '_diffrn_measurement.id' may be used to link to other
                   categories.  If the experimental setup admits multiple
                   devices, then '_diffrn_measurement.id' is used to provide
                   a unique link.
    ;
         loop_
        _item.name                 
        _item.category_id
        _item.mandatory_code
                 '_diffrn_measurement.id'      diffrn_measurement      implicit
                 '_diffrn_measurement_axis.measurement_id'
                                               diffrn_measurement_axis implicit
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_measurement_axis.measurement_id'
                                             '_diffrn_measurement.id'
    
        _item_type.code               code
         save_
    
    
    save__diffrn_measurement.method
        _item_description.description
    ;              Method used to measure intensities.
    ;
        _item.name                  '_diffrn_measurement.method'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_method'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
        _item_examples.case
          'profile data from theta/2theta (\q/2\q) scans'
         save_
    
    
    save__diffrn_measurement.number_of_axes
        _item_description.description
    ;             
                   The value of '_diffrn_measurement.number_of_axes' gives the 
                   number of axes of the positioner for the goniometer or
                   other sample orientation or positioning device identified 
                   by '_diffrn_measurement.id'.
    
                   The description of the axes should be provided by entries in 
                   DIFFRN_MEASUREMENT_AXIS.
    ;
        _item.name                  '_diffrn_measurement.number_of_axes'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
         loop_
        _item_range.maximum
        _item_range.minimum           .   1
                                      1   1
        _item_type.code               int
         save_
    
    
    save__diffrn_measurement.specimen_support
        _item_description.description
    ;              The physical device used to support the crystal during data
                   collection.
    ;
        _item.name                  '_diffrn_measurement.specimen_support'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_specimen_support'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          'glass capillary'
                                     'quartz capillary'
                                     'fiber'
                                     'metal loop'
         save_
    
    
    ###########################
    # DIFFRN_MEASUREMENT_AXIS #
    ###########################
    
    
    save_DIFFRN_MEASUREMENT_AXIS
        _category.description
    ;
         Data items in the DIFFRN_MEASUREMENT_AXIS category associate
         axes with goniometers.
    ;
        _category.id                   diffrn_measurement_axis
        _category.mandatory_code       no
         loop_
        _category_key.name
                                  '_diffrn_measurement_axis.measurement_device'
                                    '_diffrn_measurement_axis.measurement_id'
                                    '_diffrn_measurement_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_measurement_axis.axis_id
        _item_description.description
    ;
                   This data item is a pointer to '_axis.id' in
                   the AXIS category.
    ;
        _item.name                  '_diffrn_measurement_axis.axis_id'
        _item.category_id             diffrn_measurement_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_measurement_axis.measurement_device
        _item_description.description
    ;
                   This data item is a pointer to '_diffrn_measurement.device'
                   in the DIFFRN_MEASUREMENT category.
    
    ;
        _item.name
          '_diffrn_measurement_axis.measurement_device'
        _item.category_id             diffrn_measurement_axis
        _item.mandatory_code          implicit
        _item_type.code               text
         save_
    
    
    save__diffrn_measurement_axis.measurement_id
        _item_description.description
    ;
                   This data item is a pointer to '_diffrn_measurement.id' in
                   the DIFFRN_MEASUREMENT category.
                  
                   This item was previously named '_diffrn_measurement_axis.id'
                   which is now a deprecated name.  The old name is
                   provided as an alias but should not be used for new work.
    
    ;
        _item.name                  '_diffrn_measurement_axis.measurement_id'
        _item.category_id             diffrn_measurement_axis
        _item_aliases.alias_name    '_diffrn_measurement_axis.id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0.00
        _item.mandatory_code          implicit
        _item_type.code               code
         save_
    
    
    ####################
    # DIFFRN_RADIATION #
    ####################
    
    
    save_DIFFRN_RADIATION
        _category.description
    ;              Data items in the DIFFRN_RADIATION category describe
                   the radiation used in measuring diffraction intensities,
                   its collimation and monochromatisation before the sample.
    
                   Post-sample treatment of the beam is described by data
                   items in the DIFFRN_DETECTOR category.
    
    ;
        _category.id                  diffrn_radiation
        _category.mandatory_code      no
        _category_key.name          '_diffrn_radiation.diffrn_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 - based on PDB entry 5HVP and laboratory records for the
                    structure corresponding to PDB entry 5HVP
    ;
    ;
        _diffrn_radiation.diffrn_id            'set1'
    
        _diffrn_radiation.collimation          '0.3 mm double pinhole'
        _diffrn_radiation.monochromator        'graphite'
        _diffrn_radiation.type                 'Cu K\a'
        _diffrn_radiation.wavelength_id         1
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991).
                    Acta Cryst. C47, 2276-2277].
    ;
    ;
        _diffrn_radiation.wavelength_id    1
        _diffrn_radiation.type             'Cu K\a'
        _diffrn_radiation.monochromator    'graphite'
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    save__diffrn_radiation.collimation
        _item_description.description
    ;              The collimation or focusing applied to the radiation.
    ;
        _item.name                  '_diffrn_radiation.collimation'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_collimation'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          '0.3 mm double-pinhole'
                                     '0.5 mm'
                                     'focusing mirrors'
         save_
    
    
    save__diffrn_radiation.diffrn_id
        _item_description.description
    ;              This data item is a pointer to '_diffrn.id' in the DIFFRN
                   category.
    ;
        _item.name                  '_diffrn_radiation.diffrn_id'
        _item.mandatory_code          yes
         save_
    
    
    
    save__diffrn_radiation.div_x_source
        _item_description.description
    ;              Beam crossfire in degrees parallel to the laboratory X axis
                   (see AXIS category).
                   
                   This is a characteristic of the xray beam as it illuminates
                   the sample (or specimen) after all monochromation and 
                   collimation.
                   
                   This is the esd of the directions of photons in the X-Z plane
                   around the mean source beam direction.
                   
                   Note that some synchrotrons specify this value in milliradians,
                   in which case a conversion would be needed.  To go from a
                   value in milliradians to a value in degrees, multiply by 0.180
                   and divide by π.
    
    ;
        _item.name                  '_diffrn_radiation.div_x_source'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_type.code               float
        _item_units.code              degrees
         save_
    
    
    save__diffrn_radiation.div_y_source
        _item_description.description
    ;              Beam crossfire in degrees parallel to the laboratory Y axis
                   (see AXIS category).
                   
                   This is a characteristic of the xray beam as it illuminates
                   the sample (or specimen) after all monochromation and 
                   collimation.
                   
                   This is the esd of the directions of photons in the Y-Z plane
                   around the mean source beam direction.
    
                   Note that some synchrotrons specify this value in milliradians,
                   in which case a conversion would be needed.  To go from a
                   value in milliradians to a value in degrees, multiply by 0.180
                   and divide by π.
    
    ;
        _item.name                  '_diffrn_radiation.div_y_source'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_type.code               float
        _item_units.code              degrees
        _item_default.value           0.0
         save_
    
    
    save__diffrn_radiation.div_x_y_source
        _item_description.description
    ;              Beam crossfire correlation degrees2 between the
                   crossfire laboratory X-axis component and the crossfire
                   laboratory Y-axis component (see AXIS category).
                   
                   This is a characteristic of the xray beam as it illuminates
                   the sample (or specimen) after all monochromation and 
                   collimation.
                   
                   This is the mean of the products of the deviations of the
                   direction of each photons in X-Z plane times the deviations
                   of the direction of the same photon in the Y-Z plane
                   around the mean source beam direction.  This will be zero
                   for uncorrelated crossfire.
                   
                   Note that some synchrotrons specify this value in 
                   milliradians2, in which case a conversion would be needed.  
                   To go from a value in milliradians2 to a value in
                   degrees2, multiply by 0.1802 and divide by π2.
    
    ;
        _item.name                  '_diffrn_radiation.div_x_y_source'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_type.code               float
        _item_units.code              degrees_squared
        _item_default.value           0.0
         save_
    
    save__diffrn_radiation.filter_edge
        _item_description.description
    ;              Absorption edge in Ångstroms of the radiation filter used.
    ;
        _item.name                  '_diffrn_radiation.filter_edge'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_filter_edge'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum           
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
        _item_units.code              angstroms
         save_
    
    save__diffrn_radiation.inhomogeneity
        _item_description.description
    ;              Half-width in millimetres of the incident beam in the
                   direction perpendicular to the diffraction plane.
    ;
        _item.name                  '_diffrn_radiation.inhomogeneity'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_inhomogeneity'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum           
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    save__diffrn_radiation.monochromator
        _item_description.description
    ;              The method used to obtain monochromatic radiation. If a
                   monochromator crystal is used the material and the
                   indices of the Bragg reflection are specified.
    ;
        _item.name                  '_diffrn_radiation.monochromator'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_monochromator'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          'Zr filter'
                                     'Ge 220'
                                     'none'
                                     'equatorial mounted graphite'
         save_
    
    save__diffrn_radiation.polarisn_norm
        _item_description.description
    ;              The angle in degrees, as viewed from the specimen, between the
                   perpendicular component of the polarisation and the diffraction
                   plane. See _diffrn_radiation_polarisn_ratio.
    ;
        _item.name                  '_diffrn_radiation.polarisn_norm'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_polarisn_norm'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum           
        _item_range.minimum           90.0  90.0
                                      90.0 -90.0
                                     -90.0 -90.0
        _item_type.code               float
        _item_units.code              degrees
         save_
    
    save__diffrn_radiation.polarisn_ratio
        _item_description.description
    ;              Polarisation ratio of the diffraction beam incident on the
                   crystal. It is the ratio of the perpendicularly polarised to
                   the parallel polarised component of the radiation. The
                   perpendicular component forms an angle of
                   '_diffrn_radiation.polarisn_norm' to the normal to the
                   diffraction plane of the sample (i.e. the plane containing
                   the incident and reflected beams).
    ;
        _item.name                  '_diffrn_radiation.polarisn_ratio'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_polarisn_ratio'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum           
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
         save_
    
    
    
    save__diffrn_radiation.polarizn_source_norm
        _item_description.description
    ;              The angle in degrees, as viewed from the specimen, between
                   the normal to the polarization plane and the laboratory Y
                   axis as defined in the AXIS category.
                   
                   Note that this is the angle of polarization of the source 
                   photons, either directly from a synchrotron beamline or
                   from a monchromater.
                   
                   This differs from the value of
                   '_diffrn_radiation.polarisn_norm'
                   in that '_diffrn_radiation.polarisn_norm' refers to
                   polarization relative to the diffraction plane rather than
                   to the laboratory axis system.
                   
                   In the case of an unpolarized beam, or a beam with true
                   circular polarization, in which no single plane of
                   polarization can be determined, the plane should be taken
                   as the X-Z plane, and the angle as 0.
                   
                   See '_diffrn_radiation.polarizn_source_ratio'.
    ;
        _item.name                  '_diffrn_radiation.polarizn_source_norm'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
         loop_
        _item_range.maximum           
        _item_range.minimum           90.0   90.0
                                      90.0  -90.0
                                     -90.0  -90.0
        _item_type.code               float
        _item_units.code              degrees
        _item_default.value           0.0
         save_
    
    
    save__diffrn_radiation.polarizn_source_ratio
        _item_description.description
    ;              (Ip-In)/(Ip+In), where Ip is the intensity (amplitude
                   squared) of the electric vector in the plane of
                   polarization and In is the intensity (amplitude squared)
                   of the electric vector in plane of the normal to the
                   plane of polarization.
                   
                   In the case of an unpolarized beam, or a beam with true
                   circular polarization, in which no single plane of
                   polarization can be determined, the plane is be taken
                   as the X-Z plane, and the normal is parallel to the Y-axis.
                   
                   Thus, if we had complete polarization in the plane of
                   polarization, the value of 
                   '_diffrn_radiation.polarizn_source_ratio' would
                   be 1, and an unpolarized beam would have a value of 0.
                   
                   If the X-axis has been chosen to lie in the plane of
                   polarization, this definition will agree with the definition
                   of "MONOCHROMATOR" in the Denzo glossary, and values of near
                   1 should be expected for a bending magnet source.  However,
                   if the X-axis were, for some reason to be, say,
                   perpendicular to the polarization plane (not a common
                   choice), then the Denzo value would be the negative of
                   '_diffrn_radiation.polarizn_source_ratio'.
                   
                   See http://www.hkl-xray.com for information on Denzo, and
                   Z. Otwinowski and W. Minor, "Processing of X-ray
                   Diffraction Data Collected in Oscillation Mode", Methods
                   in Enzymology, Volume 276: Macromolecular Crystallography,
                   part A, p.307-326, 1997,C.W. Carter, Jr. & R. M. Sweet,
                   Eds., Academic Press.
    
                   This differs both in the choice of ratio and choice of
                   orientation from '_diffrn_radiation.polarisn_ratio', which,
                   unlike '_diffrn_radiation.polarizn_source_ratio', is
                   unbounded.
    
    ;
        _item.name                  '_diffrn_radiation.polarizn_source_ratio'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
         loop_
        _item_range.maximum           
        _item_range.minimum           1.0    1.0
                                      1.0   -1.0
                                     -1.0   -1.0
        _item_type.code               float
         save_
    
    
    save__diffrn_radiation.probe
        _item_description.description
    ;              Name of the type of radiation used. It is strongly
                   encouraged that this field be specified so that the
                   probe radiation can be simply determined.
    ;
        _item.name                  '_diffrn_radiation.probe'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_probe'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               line
         loop_
        _item_enumeration.value      'x-ray'
                                     'neutron'
                                     'electron'
                                     'gamma'
         save_
    
    save__diffrn_radiation.type
        _item_description.description
    ;              The nature of the radiation. This is typically a description
                   of the X-ray wavelength in Siegbahn notation.
    ;
        _item.name                  '_diffrn_radiation.type'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_type'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               line
         loop_
        _item_examples.case          'CuK\a'
                                     'Cu K\a~1~'
                                     'Cu K-L~2,3~' 
                                     'white-beam'
    
         save_
    
    save__diffrn_radiation.xray_symbol
        _item_description.description
    ;              The IUPAC symbol for the X-ray wavelength for probe
                   radiation.
    ;
        _item.name                  '_diffrn_radiation.xray_symbol'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_xray_symbol'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               line
         loop_
        _item_enumeration.value
        _item_enumeration.detail     'K-L~3~'
                                     'K\a~1~ in older Siegbahn notation'
                                     'K-L~2~'
                                     'K\a~2~ in older Siegbahn notation'
                                     'K-M~3~'
                                     'K\b~1~ in older Siegbahn notation'
                                     'K-L~2,3~'
                                     'use where K-L~3~ and K-L~2~ are not resolved'
         save_
    
    save__diffrn_radiation.wavelength_id
        _item_description.description
    ;              This data item is a pointer to 
                   '_diffrn_radiation_wavelength.id' in the
                   DIFFRN_RADIATION_WAVELENGTH category.
    ;
        _item.name                  '_diffrn_radiation.wavelength_id'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    
    ################
    # DIFFRN_REFLN #
    ################
    
    
    save_DIFFRN_REFLN
        _category.description 
    ;
         This category redefinition has been added to extend the key of 
         the standard DIFFRN_REFLN category.
    ;
        _category.id                   diffrn_refln
        _category.mandatory_code       no
        _category_key.name             '_diffrn_refln.frame_id'
         loop_
        _category_group.id             'inclusive_group'
                                       'diffrn_group'
         save_
    
    
    save__diffrn_refln.frame_id
        _item_description.description
    ;             
                   This item is a pointer to '_diffrn_data_frame.id'
                   in the DIFFRN_DATA_FRAME category. 
    ;
        _item.name                  '_diffrn_refln.frame_id'
        _item.category_id             diffrn_refln
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    ###############
    # DIFFRN_SCAN #
    ###############
    
    save_DIFFRN_SCAN
        _category.description 
    ;
         Data items in the DIFFRN_SCAN category describe the parameters of one
         or more scans, relating axis positions to frames.
    
    ;
        _category.id                   diffrn_scan
        _category.mandatory_code       no
        _category_key.name            '_diffrn_scan.id'
         loop_
        _category_group.id            'inclusive_group'
                                      'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        Example 1 - derived from a suggestion by R. M. Sweet.
    
       The vector of each axis is not given here, because it is provided in
       the AXIS category.  By making '_diffrn_scan_axis.scan_id' and
       '_diffrn_scan_axis.axis_id' keys of the DIFFRN_SCAN_AXIS category,
       an arbitrary number of scanning and fixed axes can be specified for a 
       scan.  We have specified three rotation axes and one translation axis 
       at non-zero values, with one axis stepping.  There is no reason why 
       more axes could not have been specified to step.   We have specified
       range information, but note that it is redundant from the  number of 
       frames and the increment, so we could drop the data item
       '_diffrn_scan_axis.angle_range'.
       
       We have specified both the sweep data and the data for a single frame.
    
       Note that the information on how the axes are stepped is given twice,
       once in terms of the overall averages in the value of
       '_diffrn_scan.integration_time' and the values for DIFFRN_SCAN_AXIS,
       and precisely for the given frame in the value for 
       '_diffrn_scan_frame.integration_time' and the values for
       DIFFRN_SCAN_FRAME_AXIS.  If dose-related adjustements are made to
       scan times and non-linear stepping is done, these values may differ.
       Therefore, in interpreting the data for a particular frame it is
       important to use the frame-specific data.
    
    ;
    ;
          _diffrn_scan.id                   1
          _diffrn_scan.date_start         '2001-11-18T03:26:42'
          _diffrn_scan.date_end           '2001-11-18T03:36:45'
          _diffrn_scan.integration_time    3.0
          _diffrn_scan.frame_id_start      mad_L2_000
          _diffrn_scan.frame_id_end        mad_L2_200
          _diffrn_scan.frames              201
    
           loop_
          _diffrn_scan_axis.scan_id
          _diffrn_scan_axis.axis_id
          _diffrn_scan_axis.angle_start
          _diffrn_scan_axis.angle_range
          _diffrn_scan_axis.angle_increment
          _diffrn_scan_axis.displacement_start
          _diffrn_scan_axis.displacement_range
          _diffrn_scan_axis.displacement_increment
    
           1 omega 200.0 20.0 0.1 . . . 
           1 kappa -40.0  0.0 0.0 . . . 
           1 phi   127.5  0.0 0.0 . . . 
           1 tranz  . . .   2.3 0.0 0.0 
    
          _diffrn_scan_frame.scan_id                   1
          _diffrn_scan_frame.date               '2001-11-18T03:27:33'
          _diffrn_scan_frame.integration_time    3.0
          _diffrn_scan_frame.frame_id            mad_L2_018
          _diffrn_scan_frame.frame_number        18
    
          loop_
          _diffrn_scan_frame_axis.frame_id
          _diffrn_scan_frame_axis.axis_id
          _diffrn_scan_frame_axis.angle
          _diffrn_scan_frame_axis.angle_increment
          _diffrn_scan_frame_axis.displacement
          _diffrn_scan_frame_axis.displacement_increment
    
           mad_L2_018 omega 201.8  0.1 . .
           mad_L2_018 kappa -40.0  0.0 . .
           mad_L2_018 phi   127.5  0.0 . .
           mad_L2_018 tranz  .     .  2.3 0.0
    
    ;
    
    ;
        Example 2 - a more extensive example, R. M. Sweet, P. Ellis, H. Bernstein.
        
       We place a detector 240 mm along the Z axis from the goniometer.
       This presents us with a choice -- either we define the axes of
       the detector at the origin, and then put a Z setting of -240 in
       for the actual use, or we define the axes with the necessary Z-offset.
       In this case we use the setting, and leave the offset as zero.
       We call this axis DETECTOR_Z.
       
       The axis for positioning the detector in the Y-direction depends
       on the detector Z-axis.  We call this axis, DETECTOR_Y.
       
       The axis for positioning the detector in the X-direction depends
       on the detector Y-axis (and therefore on the detector Z-axis).
       We call this axis DETECTOR_X.
       
       This detector may be rotated around the Y-axis.  This rotation axis
       depends on the three translation axes.  We call it DETECTOR_PITCH.
       
       We define a coordinate system on the face of the detector in terms of
       2300 0.150 mm pixels in each direction.  The ELEMENT_X axis is used to
       index the first array index of the data array and the ELEMENT_Y
       axis is used to index the second array index.  Because the pixels
       are 0.150mm x 0.150mm, the centre of the first pixel is at (0.075, 
       0.075) in this coordinate system.
    
    ;
    ;
         ###CBF: VERSION 1.1 
    
         data_image_1 
    
    
         # category DIFFRN 
    
         _diffrn.id P6MB 
         _diffrn.crystal_id P6MB_CRYSTAL7 
    
    
         # category DIFFRN_SOURCE 
    
         loop_ 
         _diffrn_source.diffrn_id 
         _diffrn_source.source 
         _diffrn_source.type 
          P6MB synchrotron 'SSRL beamline 9-1' 
    
    
         # category DIFFRN_RADIATION 
    
              loop_ 
         _diffrn_radiation.diffrn_id 
         _diffrn_radiation.wavelength_id 
         _diffrn_radiation.monochromator 
         _diffrn_radiation.polarizn_source_ratio 
         _diffrn_radiation.polarizn_source_norm 
         _diffrn_radiation.div_x_source 
         _diffrn_radiation.div_y_source 
         _diffrn_radiation.div_x_y_source 
          P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08
         0.01 0.00 
    
    
         # category DIFFRN_RADIATION_WAVELENGTH 
    
         loop_ 
         _diffrn_radiation_wavelength.id 
         _diffrn_radiation_wavelength.wavelength 
         _diffrn_radiation_wavelength.wt 
          WAVELENGTH1 0.98 1.0 
    
    
         # category DIFFRN_DETECTOR 
    
         loop_ 
         _diffrn_detector.diffrn_id 
         _diffrn_detector.id 
         _diffrn_detector.type 
         _diffrn_detector.number_of_axes 
          P6MB MAR345-SN26 'MAR 345' 4 
    
    
         # category DIFFRN_DETECTOR_AXIS 
    
         loop_ 
         _diffrn_detector_axis.detector_id 
         _diffrn_detector_axis.axis_id 
          MAR345-SN26 DETECTOR_X 
          MAR345-SN26 DETECTOR_Y 
          MAR345-SN26 DETECTOR_Z 
          MAR345-SN26 DETECTOR_PITCH 
    
    
         # category DIFFRN_DETECTOR_ELEMENT 
    
         loop_ 
         _diffrn_detector_element.id 
         _diffrn_detector_element.detector_id 
          ELEMENT1 MAR345-SN26 
    
    
         # category DIFFRN_DATA_FRAME 
    
         loop_ 
         _diffrn_data_frame.id 
         _diffrn_data_frame.detector_element_id 
         _diffrn_data_frame.array_id 
         _diffrn_data_frame.binary_id 
          FRAME1 ELEMENT1 ARRAY1 1 
    
    
         # category DIFFRN_MEASUREMENT 
    
         loop_ 
         _diffrn_measurement.diffrn_id 
         _diffrn_measurement.id 
         _diffrn_measurement.number_of_axes 
         _diffrn_measurement.method 
          P6MB GONIOMETER 3 rotation 
    
    
         # category DIFFRN_MEASUREMENT_AXIS 
    
         loop_ 
         _diffrn_measurement_axis.measurement_id 
         _diffrn_measurement_axis.axis_id 
          GONIOMETER GONIOMETER_PHI 
          GONIOMETER GONIOMETER_KAPPA 
          GONIOMETER GONIOMETER_OMEGA 
    
    
         # category DIFFRN_SCAN 
    
         loop_ 
         _diffrn_scan.id 
         _diffrn_scan.frame_id_start 
         _diffrn_scan.frame_id_end 
         _diffrn_scan.frames 
          SCAN1 FRAME1 FRAME1 1 
    
    
         # category DIFFRN_SCAN_AXIS 
    
         loop_ 
         _diffrn_scan_axis.scan_id 
         _diffrn_scan_axis.axis_id 
         _diffrn_scan_axis.angle_start 
         _diffrn_scan_axis.angle_range 
         _diffrn_scan_axis.angle_increment 
         _diffrn_scan_axis.displacement_start 
         _diffrn_scan_axis.displacement_range 
         _diffrn_scan_axis.displacement_increment 
          SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 
          SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 
          SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 
          SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 
          SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 
          SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 
          SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 
    
    
         # category DIFFRN_SCAN_FRAME 
    
         loop_ 
         _diffrn_scan_frame.frame_id 
         _diffrn_scan_frame.frame_number 
         _diffrn_scan_frame.integration_time 
         _diffrn_scan_frame.scan_id 
         _diffrn_scan_frame.date 
          FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 
    
    
         # category DIFFRN_SCAN_FRAME_AXIS 
    
         loop_ 
         _diffrn_scan_frame_axis.frame_id 
         _diffrn_scan_frame_axis.axis_id 
         _diffrn_scan_frame_axis.angle 
         _diffrn_scan_frame_axis.displacement 
          FRAME1 GONIOMETER_OMEGA 12.0 0.0 
          FRAME1 GONIOMETER_KAPPA 23.3 0.0 
          FRAME1 GONIOMETER_PHI -165.8 0.0 
          FRAME1 DETECTOR_Z 0.0 -240.0 
          FRAME1 DETECTOR_Y 0.0 0.6 
          FRAME1 DETECTOR_X 0.0 -0.5 
          FRAME1 DETECTOR_PITCH 0.0 0.0 
    
    
         # category AXIS 
    
         loop_ 
         _axis.id 
         _axis.type 
         _axis.equipment 
         _axis.depends_on 
         _axis.vector[1] _axis.vector[2] _axis.vector[3] 
         _axis.offset[1] _axis.offset[2] _axis.offset[3] 
          GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . 
          GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279
          0 0.76604 . . . 
          GONIOMETER_PHI   rotation goniometer GONIOMETER_KAPPA 1 0 0
         . . . 
          SOURCE           general source . 0 0 1 . . . 
          GRAVITY          general gravity . 0 -1 0 . . . 
          DETECTOR_Z       translation detector . 0 0 1 0 0 0
          DETECTOR_Y       translation detector DETECTOR_Z 0 1 0 0 0 0 
          DETECTOR_X       translation detector DETECTOR_Y 1 0 0 0 0 0 
          DETECTOR_PITCH   rotation    detector DETECTOR_X 0 1 0 0 0 0 
          ELEMENT_X        translation detector DETECTOR_PITCH
         1 0 0 172.43 -172.43 0
          ELEMENT_Y        translation detector ELEMENT_X
         0 1 0 0 0 0 
    
         # category ARRAY_STRUCTURE_LIST 
    
         loop_ 
         _array_structure_list.array_id 
         _array_structure_list.index 
         _array_structure_list.dimension 
         _array_structure_list.precedence 
         _array_structure_list.direction 
         _array_structure_list.axis_set_id 
          ARRAY1 1 2300 1 increasing ELEMENT_X 
          ARRAY1 2 2300 2 increasing ELEMENT_Y 
    
    
         # category ARRAY_STRUCTURE_LIST_AXIS 
    
         loop_
         _array_structure_list_axis.axis_set_id
         _array_structure_list_axis.axis_id
         _array_structure_list_axis.displacement
         _array_structure_list_axis.displacement_increment
          ELEMENT_X ELEMENT_X 0.075 0.150
          ELEMENT_Y ELEMENT_Y 0.075 0.150
    
         # category ARRAY_ELEMENT_SIZE 
    
         loop_ 
         _array_element_size.array_id 
         _array_element_size.index 
         _array_element_size.size 
          ARRAY1 1 150e-6 
          ARRAY1 2 150e-6 
    
    
         # category ARRAY_INTENSITIES 
    
         loop_ 
         _array_intensities.array_id 
         _array_intensities.binary_id 
         _array_intensities.linearity 
         _array_intensities.gain 
         _array_intensities.gain_esd 
         _array_intensities.overload
         _array_intensities.undefined_value 
          ARRAY1 1 linear 1.15 0.2 240000 0 
    
    
          # category ARRAY_STRUCTURE 
    
          loop_ 
          _array_structure.id 
          _array_structure.encoding_type 
          _array_structure.compression_type 
          _array_structure.byte_order 
          ARRAY1 "signed 32-bit integer" packed little_endian 
    
    
         # category ARRAY_DATA         
    
         loop_ 
         _array_data.array_id 
         _array_data.binary_id 
         _array_data.data 
          ARRAY1 1 
         ; 
         --CIF-BINARY-FORMAT-SECTION-- 
         Content-Type: application/octet-stream; 
             conversions="x-CBF_PACKED" 
         Content-Transfer-Encoding: BASE64 
         X-Binary-Size: 3801324 
         X-Binary-ID: 1 
         X-Binary-Element-Type: "signed 32-bit integer" 
         Content-MD5: 07lZFvF+aOcW85IN7usl8A== 
    
         AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg 
         ... 
         8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE 
    
         --CIF-BINARY-FORMAT-SECTION---- 
         ; 
    ;
    
    ;
        Example 3 - Example 2 revised for a spiral scan, R. M. Sweet, 
        P. Ellis, H. Bernstein.
        
       We place a detector 240 mm along the Z axis from the goniometer,
       as in Example 2, above, but in this example, the image plate is
       scanned in a spiral pattern outside edge in.
       
       The axis for positioning the detector in the Y-direction depends
       on the detector Z-axis.  We call this axis, DETECTOR_Y.
       
       The axis for positioning the detector in the X-direction depends
       on the detector Y-axis (and therefore on the detector Z-axis).
       We call this axis DETECTOR_X.
       
       This detector may be rotated around the Y-axis.  This rotation axis
       depends on the three translation axes.  We call it DETECTOR_PITCH.
    
       We define a coordinate system on the face of the detector in
       terms of a coupled rotation axis and radial scan axis to form 
       a spiral scan.  Let us call rotation axis ELEMENT_ROT, and the
       radial axis ELEMENT_RAD.   We assume 150 um radial pitch and 75 um 
       'constant velocity' angular pitch. 
    
       We index first on the rotation axis and make the radial axis
       dependent on 
       it. 
    
       The two axes are coupled to form an axis set ELEMENT_SPIRAL. 
    
    ;
    ;
         ###CBF: VERSION 1.1 
    
         data_image_1 
    
    
         # category DIFFRN 
    
         _diffrn.id P6MB 
         _diffrn.crystal_id P6MB_CRYSTAL7 
    
    
         # category DIFFRN_SOURCE 
    
         loop_ 
         _diffrn_source.diffrn_id 
         _diffrn_source.source 
         _diffrn_source.type 
          P6MB synchrotron 'SSRL beamline 9-1' 
    
    
         # category DIFFRN_RADIATION 
    
              loop_ 
         _diffrn_radiation.diffrn_id 
         _diffrn_radiation.wavelength_id 
         _diffrn_radiation.monochromator 
         _diffrn_radiation.polarizn_source_ratio 
         _diffrn_radiation.polarizn_source_norm 
         _diffrn_radiation.div_x_source 
         _diffrn_radiation.div_y_source 
         _diffrn_radiation.div_x_y_source 
          P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08
         0.01 0.00 
    
    
         # category DIFFRN_RADIATION_WAVELENGTH 
    
         loop_ 
         _diffrn_radiation_wavelength.id 
         _diffrn_radiation_wavelength.wavelength 
         _diffrn_radiation_wavelength.wt 
          WAVELENGTH1 0.98 1.0 
    
    
         # category DIFFRN_DETECTOR 
    
         loop_ 
         _diffrn_detector.diffrn_id 
         _diffrn_detector.id 
         _diffrn_detector.type 
         _diffrn_detector.number_of_axes 
          P6MB MAR345-SN26 'MAR 345' 4 
    
    
         # category DIFFRN_DETECTOR_AXIS 
    
         loop_ 
         _diffrn_detector_axis.detector_id 
         _diffrn_detector_axis.axis_id 
          MAR345-SN26 DETECTOR_X 
          MAR345-SN26 DETECTOR_Y 
          MAR345-SN26 DETECTOR_Z 
          MAR345-SN26 DETECTOR_PITCH 
    
    
         # category DIFFRN_DETECTOR_ELEMENT 
    
         loop_ 
         _diffrn_detector_element.id 
         _diffrn_detector_element.detector_id 
          ELEMENT1 MAR345-SN26 
    
    
         # category DIFFRN_DATA_FRAME 
    
         loop_ 
         _diffrn_data_frame.id 
         _diffrn_data_frame.detector_element_id 
         _diffrn_data_frame.array_id 
         _diffrn_data_frame.binary_id 
          FRAME1 ELEMENT1 ARRAY1 1 
    
    
         # category DIFFRN_MEASUREMENT 
    
         loop_ 
         _diffrn_measurement.diffrn_id 
         _diffrn_measurement.id 
         _diffrn_measurement.number_of_axes 
         _diffrn_measurement.method 
          P6MB GONIOMETER 3 rotation 
    
    
         # category DIFFRN_MEASUREMENT_AXIS 
    
         loop_ 
         _diffrn_measurement_axis.measurement_id 
         _diffrn_measurement_axis.axis_id 
          GONIOMETER GONIOMETER_PHI 
          GONIOMETER GONIOMETER_KAPPA 
          GONIOMETER GONIOMETER_OMEGA 
    
    
         # category DIFFRN_SCAN 
    
         loop_ 
         _diffrn_scan.id 
         _diffrn_scan.frame_id_start 
         _diffrn_scan.frame_id_end 
         _diffrn_scan.frames 
          SCAN1 FRAME1 FRAME1 1 
    
    
         # category DIFFRN_SCAN_AXIS 
    
         loop_ 
         _diffrn_scan_axis.scan_id 
         _diffrn_scan_axis.axis_id 
         _diffrn_scan_axis.angle_start 
         _diffrn_scan_axis.angle_range 
         _diffrn_scan_axis.angle_increment 
         _diffrn_scan_axis.displacement_start 
         _diffrn_scan_axis.displacement_range 
         _diffrn_scan_axis.displacement_increment 
          SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 
          SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 
          SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 
          SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 
          SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 
          SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 
          SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 
    
    
         # category DIFFRN_SCAN_FRAME 
    
         loop_ 
         _diffrn_scan_frame.frame_id 
         _diffrn_scan_frame.frame_number 
         _diffrn_scan_frame.integration_time 
         _diffrn_scan_frame.scan_id 
         _diffrn_scan_frame.date 
          FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 
    
    
         # category DIFFRN_SCAN_FRAME_AXIS 
    
         loop_ 
         _diffrn_scan_frame_axis.frame_id 
         _diffrn_scan_frame_axis.axis_id 
         _diffrn_scan_frame_axis.angle 
         _diffrn_scan_frame_axis.displacement 
          FRAME1 GONIOMETER_OMEGA 12.0 0.0 
          FRAME1 GONIOMETER_KAPPA 23.3 0.0 
          FRAME1 GONIOMETER_PHI -165.8 0.0 
          FRAME1 DETECTOR_Z 0.0 -240.0 
          FRAME1 DETECTOR_Y 0.0 0.6 
          FRAME1 DETECTOR_X 0.0 -0.5 
          FRAME1 DETECTOR_PITCH 0.0 0.0 
    
    
         # category AXIS 
    
         loop_ 
         _axis.id 
         _axis.type 
         _axis.equipment 
         _axis.depends_on 
         _axis.vector[1] _axis.vector[2] _axis.vector[3] 
         _axis.offset[1] _axis.offset[2] _axis.offset[3] 
          GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . 
          GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279
          0 0.76604 . . . 
          GONIOMETER_PHI   rotation goniometer GONIOMETER_KAPPA 1 0 0
         . . . 
          SOURCE           general source . 0 0 1 . . . 
          GRAVITY          general gravity . 0 -1 0 . . . 
          DETECTOR_Z       translation detector . 0 0 1 0 0 0
          DETECTOR_Y       translation detector DETECTOR_Z 0 1 0 0 0 0 
          DETECTOR_X       translation detector DETECTOR_Y 1 0 0 0 0 0 
          DETECTOR_PITCH   rotation    detector DETECTOR_X 0 1 0 0 0 0 
          ELEMENT_ROT      translation detector DETECTOR_PITCH 0 0 1 0 0 0
          ELEMENT_RAD      translation detector ELEMENT_ROT 0 1 0 0 0 0 
    
         # category ARRAY_STRUCTURE_LIST 
    
         loop_ 
         _array_structure_list.array_id 
         _array_structure_list.index 
         _array_structure_list.dimension 
         _array_structure_list.precedence 
         _array_structure_list.direction 
         _array_structure_list.axis_set_id 
          ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL
    
    
         # category ARRAY_STRUCTURE_LIST_AXIS 
    
         loop_
         _array_structure_list_axis.axis_set_id
         _array_structure_list_axis.axis_id
         _array_structure_list_axis.angle
         _array_structure_list_axis.displacement
         _array_structure_list_axis.angular_pitch
         _array_structure_list_axis.radial_pitch
          ELEMENT_SPIRAL ELEMENT_ROT 0    .  0.075   .
          ELEMENT_SPIRAL ELEMENT_RAD . 172.5  .    -0.150
    
         # category ARRAY_ELEMENT_SIZE 
         # the actual pixels are 0.075 by 0.150 mm
         # We give the coarser dimension here.
    
         loop_ 
         _array_element_size.array_id 
         _array_element_size.index 
         _array_element_size.size 
          ARRAY1 1 150e-6 
    
    
         # category ARRAY_INTENSITIES 
    
         loop_ 
         _array_intensities.array_id 
         _array_intensities.binary_id 
         _array_intensities.linearity 
         _array_intensities.gain 
         _array_intensities.gain_esd 
         _array_intensities.overload
         _array_intensities.undefined_value 
          ARRAY1 1 linear 1.15 0.2 240000 0 
    
    
          # category ARRAY_STRUCTURE 
    
          loop_ 
          _array_structure.id 
          _array_structure.encoding_type 
          _array_structure.compression_type 
          _array_structure.byte_order 
          ARRAY1 "signed 32-bit integer" packed little_endian 
    
    
         # category ARRAY_DATA         
    
         loop_ 
         _array_data.array_id 
         _array_data.binary_id 
         _array_data.data 
          ARRAY1 1 
         ; 
         --CIF-BINARY-FORMAT-SECTION-- 
         Content-Type: application/octet-stream; 
             conversions="x-CBF_PACKED" 
         Content-Transfer-Encoding: BASE64 
         X-Binary-Size: 3801324 
         X-Binary-ID: 1 
         X-Binary-Element-Type: "signed 32-bit integer" 
         Content-MD5: 07lZFvF+aOcW85IN7usl8A== 
    
         AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg 
         ... 
         8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE 
    
         --CIF-BINARY-FORMAT-SECTION---- 
         ; 
    ;
    
    
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
           save_
    
    
    save__diffrn_scan.id
        _item_description.description
    ;             The value of '_diffrn_scan.id' uniquely identifies each
                  scan.  The identifier is used to tie together all the 
                  information about the scan.
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
           '_diffrn_scan.id'                 diffrn_scan             yes
           '_diffrn_scan_axis.scan_id'       diffrn_scan_axis        yes
           '_diffrn_scan_frame.scan_id'      diffrn_scan_frame       yes
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
           '_diffrn_scan_axis.scan_id'          '_diffrn_scan.id'
           '_diffrn_scan_frame.scan_id'         '_diffrn_scan.id'
         save_
    
    
    save__diffrn_scan.date_end
        _item_description.description
    ;
                   The date and time of the end of the scan.  Note that this
                   may be an estimate generated during the scan, before the
                   precise time of the end of the scan is known.
    ;
        _item.name                 '_diffrn_scan.date_end'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no
        _item_type.code            yyyy-mm-dd
         save_
    
    
    save__diffrn_scan.date_start
        _item_description.description
    ;
                   The date and time of the start of the scan.
    ;
        _item.name                 '_diffrn_scan.date_start'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no
        _item_type.code            yyyy-mm-dd
         save_
    
    
    save__diffrn_scan.integration_time
        _item_description.description
    ;
                   Approximate average time in seconds to integrate each 
                   step of the scan.  The precise time for integration
                   of each particular step must be provided in
                   '_diffrn_scan_frame.integration_time', even
                   if all steps have the same integration time.
    ;
        _item.name                 '_diffrn_scan.integration_time'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no
        _item_type.code            float
        _item_units.code           'seconds'
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0.0
         save_
    
    
    save__diffrn_scan.frame_id_start
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   first frame in the scan.
    
                   This item is a pointer to '_diffrn_data_frame.id' in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name                 '_diffrn_scan.frame_id_start'
        _item.category_id          diffrn_scan
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan.frame_id_end
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   last frame in the scan.
    
                   This item is a pointer to '_diffrn_data_frame.id' in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name                 '_diffrn_scan.frame_id_end'
        _item.category_id          diffrn_scan
        _item.mandatory_code       yes 
        _item_type.code            code
         save_
    
    
    save__diffrn_scan.frames
        _item_description.description
    ;
                   The value of this data item is the number of frames in
                   the scan.
    
    ;
        _item.name                 '_diffrn_scan.frames'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no 
        _item_type.code            int
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   1
                                1   1
         save_
    
    
    ####################
    # DIFFRN_SCAN_AXIS #
    ####################
    
    save_DIFFRN_SCAN_AXIS
        _category.description 
    ;
         Data items in the DIFFRN_SCAN_AXIS category describe the settings of
         axes for particular scans.  Unspecified axes are assumed to be at
         their zero points.
    
    ;
        _category.id                   diffrn_scan_axis
        _category.mandatory_code       no
         loop_
        _category_key.name            
                                      '_diffrn_scan_axis.scan_id'
                                      '_diffrn_scan_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_scan_axis.scan_id
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   scan for which axis settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   '_diffrn_scan.id'.
    
                   This item is a pointer to '_diffrn_scan.id' in the
                   DIFFRN_SCAN category.
    ;
        _item.name                 '_diffrn_scan_axis.scan_id'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_axis.axis_id
        _item_description.description
    ;
                   The value of this data item is the identifier of one of
                   the axes for the scan for which settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   '_diffrn_scan.id'.
    
                   This item is a pointer to '_axis.id' in the
                   AXIS category.
    ;
        _item.name                 '_diffrn_scan_axis.axis_id'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_axis.angle_start
        _item_description.description
    ;
                   The starting position for the specified axis in degrees.
    ;
        _item.name                 '_diffrn_scan_axis.angle_start'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.angle_range
        _item_description.description
    ;
                   The range from the starting position for the specified axis 
                   in degrees.
    ;
        _item.name                 '_diffrn_scan_axis.angle_range'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.angle_increment
        _item_description.description
    ;
                   The increment for each step for the specified axis
                   in degrees.  In general, this will agree with
                   '_diffrn_scan_frame_axis.angle_increment'. The 
                   sum of the values of '_diffrn_scan_frame_axis.angle' and
                   '_diffrn_scan_frame_axis.angle_increment' is the
                   angular setting of the axis at the end of the integration
                   time for a given frame.  If the individual frame values
                   vary, then the value of 
                   '_diffrn_scan_axis.angle_increment' will be 
                   representative
                   of the ensemble of values of
                   '_diffrn_scan_frame_axis.angle_increment' (e.g.
                   the mean).
    
    ;
        _item.name                 '_diffrn_scan_axis.angle_increment'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.angle_rstrt_incr
        _item_description.description
    ;
                   The increment after each step for the specified axis
                   in degrees.  In general, this will agree with
                   '_diffrn_scan_frame_axis.angle_rstrt_incr'.  The
                   sum of the values of '_diffrn_scan_frame_axis.angle' 
                   and  '_diffrn_scan_frame_axis.angle_increment' 
                   and  '_diffrn_scan_frame_axis.angle_rstrt_incr' is the
                   angular setting of the axis at the start of the integration
                   time for the next frame relative to a given frame, and 
                   should equal '_diffrn_scan_frame_axis.angle' for that 
                   next frame.   If the individual frame values
                   vary, then the value of 
                   '_diffrn_scan_axis.angle_rstrt_incr' will be 
                   representative
                   of the ensemble of values of
                   '_diffrn_scan_frame_axis.angle_rstrt_incr' (e.g.
                   the mean).
    ;
        _item.name                 '_diffrn_scan_axis.angle_rstrt_incr'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.displacement_start
        _item_description.description
    ;
                   The starting position for the specified axis in millimetres.
    ;
        _item.name                 '_diffrn_scan_axis.displacement_start'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_axis.displacement_range
        _item_description.description
    ;
                   The range from the starting position for the specified axis 
                   in millimetres.
    ;
        _item.name                 '_diffrn_scan_axis.displacement_range'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_axis.displacement_increment
        _item_description.description
    ;
                   The increment for each step for the specified axis
                   in millimetres.  In general, this will agree with
                   '_diffrn_scan_frame_axis.displacement_increment'.
                   The sum of the values of 
                   '_diffrn_scan_frame_axis.displacement' and
                   '_diffrn_scan_frame_axis.displacement_increment' is the
                   angular setting of the axis at the end of the integration
                   time for a given frame.  If the individual frame values
                   vary, then the value of 
                   '_diffrn_scan_axis.displacement_increment' will be 
                   representative
                   of the ensemble of values of
                   '_diffrn_scan_frame_axis.displacement_increment' (e.g.
                   the mean).
    ;
        _item.name                 '_diffrn_scan_axis.displacement_increment'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_axis.displacement_rstrt_incr
        _item_description.description
    ;
                   The increment for each step for the specified axis
                   in millimetres.  In general, this will agree with
                   '_diffrn_scan_frame_axis.displacement_rstrt_incr'.
                   The sum of the values of 
                   '_diffrn_scan_frame_axis.displacement' and
                   '_diffrn_scan_frame_axis.displacement_increment' and
                   '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the
                   angular setting of the axis at the start of the integration
                   time for the next frame relative to a given frame, and 
                   should equal '_diffrn_scan_frame_axis.displacement' 
                   for that next frame.  If the individual frame values
                   vary, then the value of 
                   '_diffrn_scan_axis.displacement_rstrt_incr' will be 
                   representative
                   of the ensemble of values of
                   '_diffrn_scan_frame_axis.displacement_rstrt_incr' (e.g.
                   the mean).
    ;
        _item.name                 '_diffrn_scan_axis.displacement_rstrt_incr'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    #####################
    # DIFFRN_SCAN_FRAME #
    #####################
    
    save_DIFFRN_SCAN_FRAME
        _category.description 
    ;
                Data items in the DIFFRN_SCAN_FRAME category describe
                the relationship of particular frames to scans.
    
    ;
        _category.id                   diffrn_scan_frame
        _category.mandatory_code       no
         loop_
        _category_key.name     
                                      '_diffrn_scan_frame.scan_id'
                                      '_diffrn_scan_frame.frame_id'
         loop_
        _category_group.id            'inclusive_group'
                                      'diffrn_group'
         save_
    
    
    save__diffrn_scan_frame.date
        _item_description.description
    ;
                   The date and time of the start of the frame being scanned.
    ;
        _item.name                 '_diffrn_scan_frame.date'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       no
        _item_type.code            yyyy-mm-dd
         save_
    
    
    save__diffrn_scan_frame.frame_id
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   frame being examined.
    
                   This item is a pointer to '_diffrn_data_frame.id' in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name                 '_diffrn_scan_frame.frame_id'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_frame.frame_number
        _item_description.description
    ;
                   The value of this data item is the number of the frame
                   within the scan, starting with 1.  It is not necessarily
                   the same as the value of '_diffrn_scan_frame.frame_id',
                   but may be.
    
    ;
        _item.name                 '_diffrn_scan_frame.frame_number'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       no 
        _item_type.code            int
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0
                                0   0
         save_
    
    
    save__diffrn_scan_frame.integration_time
        _item_description.description
    ;
                   The time in seconds to integrate this step of the scan.
                   This should be the precise time of integration of each
                   particular frame.  The value of this data item should
                   be given explicitly for each frame and not inferred
                   from the value of '_diffrn_scan.integration_time'.
    ;
        _item.name                 '_diffrn_scan_frame.integration_time'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       yes 
        _item_type.code            float
        _item_units.code           'seconds'
         loop_
        _item_range.maximum           
        _item_range.minimum           
                                .   0.0
         save_
    
    
    save__diffrn_scan_frame.scan_id
        _item_description.description
    ;             The value of '_diffrn_scan_frame.scan_id' identifies the scan
                  containing this frame.
    
                  This item is a pointer to '_diffrn_scan.id' in the
                  DIFFRN_SCAN category.
    ;
        _item.name             '_diffrn_scan_frame.scan_id'    
        _item.category_id        diffrn_scan_frame        
        _item.mandatory_code     yes     
        _item_type.code          code
         save_
    
    
    ##########################
    # DIFFRN_SCAN_FRAME_AXIS #
    ##########################
    
    save_DIFFRN_SCAN_FRAME_AXIS
        _category.description
    ;
         Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the
         settings of axes for particular frames.  Unspecified axes are
         assumed to be at their zero points.  If, for any given frame,
         non-zero values apply for any of the data items in this category,
         those values should be given explicitly in this category and not
         simply inferred from values in DIFFRN_SCAN_AXIS.
    
    ;
        _category.id                   diffrn_scan_frame_axis
        _category.mandatory_code       no
         loop_
        _category_key.name
                                      '_diffrn_scan_frame_axis.frame_id'
                                      '_diffrn_scan_frame_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_scan_frame_axis.axis_id
        _item_description.description
    ;
                   The value of this data item is the identifier of one of
                   the axes for the frame for which settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   '_diffrn_scan_frame.frame_id'.
    
                   This item is a pointer to '_axis.id' in the
                   AXIS category.
    ;
        _item.name                 '_diffrn_scan_frame_axis.axis_id'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_frame_axis.angle
        _item_description.description
    ;
                   The setting of the specified axis in degrees for this frame.
                   This is the setting at the start of the integration time.
    ;
        _item.name                 '_diffrn_scan_frame_axis.angle'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no 
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_frame_axis.angle_increment
        _item_description.description
    ;
                   The increment for this frame for angular setting of
                   the specified axis in degrees.  The sum of the values
                   of '_diffrn_scan_frame_axis.angle' and
                   '_diffrn_scan_frame_axis.angle_increment' is the
                   angular setting of the axis at the end of the integration
                   time for this frame.
    ;
        _item.name                 '_diffrn_scan_frame_axis.angle_increment'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_frame_axis.angle_rstrt_incr
        _item_description.description
    ;
                   The increment after this frame for angular setting of
                   the specified axis in degrees.  The sum of the values
                   of '_diffrn_scan_frame_axis.angle' and
                   '_diffrn_scan_frame_axis.angle_increment' and
                   '_diffrn_scan_frame_axis.angle_rstrt_incr' is the
                   angular setting of the axis at the start of the integration
                   time for the next frame, and should equal
                   '_diffrn_scan_frame_axis.angle' for that next frame.
    ;
        _item.name               '_diffrn_scan_frame_axis.angle_rstrt_incr'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_frame_axis.displacement
        _item_description.description
    ;
                   The setting of the specified axis in millimetres for this
                   frame.  This is the setting at the start of the integration
                   time.
    
    ;
        _item.name               '_diffrn_scan_frame_axis.displacement'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_frame_axis.displacement_increment
        _item_description.description
    ;
                   The increment for this frame for displacement setting of
                   the specified axis in millimetres.  The sum of the values
                   of '_diffrn_scan_frame_axis.displacement' and
                   '_diffrn_scan_frame_axis.displacement_increment' is the
                   angular setting of the axis at the end of the integration
                   time for this frame.
    ;
        _item.name               '_diffrn_scan_frame_axis.displacement_increment'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_frame_axis.displacement_rstrt_incr
        _item_description.description
    ;
                   The increment for this frame for displacement setting of
                   the specified axis in millimetres.  The sum of the values
                   of '_diffrn_scan_frame_axis.displacement' and
                   '_diffrn_scan_frame_axis.displacement_increment' and
                   '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the
                   angular setting of the axis at the start of the integration
                   time for the next frame, and should equal
                   '_diffrn_scan_frame_axis.displacement' for that next frame.
    ;
        _item.name               '_diffrn_scan_frame_axis.displacement_rstrt_incr'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    save__diffrn_scan_frame_axis.frame_id
        _item_description.description
    ;
                   The value of this data item is the identifier of the
                   frame for which axis settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   '_diffrn_scan_frame.frame_id'.
    
                   This item is a pointer to '_diffrn_data_frame.id' in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name               '_diffrn_scan_frame_axis.frame_id'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    ########################   DEPRECATED DATA ITEMS ########################
    
    save__diffrn_detector_axis.id
        _item_description.description
    ;
                   This data item is a pointer to '_diffrn_detector.id' in
                   the DIFFRN_DETECTOR category.
                  
                   DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_detector_axis.id'
        _item.category_id             diffrn_detector_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    save__diffrn_measurement_axis.id
        _item_description.description
    ;
                   This data item is a pointer to '_diffrn_measurement.id' in
                   the DIFFRN_MEASUREMENT category.
                  
                   DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_measurement_axis.id'
        _item.category_id             diffrn_measurement_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    #########################   DEPRECATED CATEGORY #########################
    #####################
    # DIFFRN_FRAME_DATA #
    #####################
    
    
    save_DIFFRN_FRAME_DATA
        _category.description
    ;
                  Data items in the DIFFRN_FRAME_DATA category record
                  the details about each frame of data. 
    
                  The items in this category are now in the
                  DIFFRN_DATA_FRAME category.
                  
                  The items in the DIFFRN_FRAME_DATA category
                  are now deprecated.  The items from this category 
                  are provided as aliases in the 1.0.0 dictionary, 
                  but should not be used for new work.
                  The items from the old category are provided
                  in this dictionary for completeness,
                  but should not be used or cited.  To avoid
                  confusion, the example has been removed,
                  and the redundant parent child-links to other
                  categories removed.
                  
    ;
        _category.id                   diffrn_frame_data
        _category.mandatory_code       no
         loop_
        _category_key.name             '_diffrn_frame_data.id'
                                       '_diffrn_frame_data.detector_element_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        THE DIFFRN_FRAME_DATA category is deprecated and should not be used.
    ;
    ;
           # EXAMPLE REMOVED #
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
    
    
    save__diffrn_frame_data.array_id
        _item_description.description
    ;             
                  This item is a pointer to '_array_structure.id' in the
                  ARRAY_STRUCTURE category.
    
                  DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_frame_data.array_id'
        _item.category_id             diffrn_frame_data
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_frame_data.binary_id
        _item_description.description
    ;             This item is a pointer to '_array_data.binary_id' in the
                  ARRAY_STRUCTURE category. 
                  
                  DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_frame_data.binary_id'
        _item.category_id             diffrn_frame_data
        _item.mandatory_code          implicit
        _item_type.code               int
         save_
    
    
    save__diffrn_frame_data.detector_element_id
        _item_description.description
    ;             
                  This item is a pointer to '_diffrn_detector_element.id'
                  in the DIFFRN_DETECTOR_ELEMENT category.
    
                  DEPRECATED -- DO NOT USE 
    ;
        _item.name                  '_diffrn_frame_data.detector_element_id'
        _item.category_id             diffrn_frame_data
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_frame_data.id
        _item_description.description
    ;             
                  The value of '_diffrn_frame_data.id' must uniquely identify
                  each complete frame of data.
    
                  DEPRECATED -- DO NOT USE 
    ;
         loop_
        _item.name                
        _item.category_id          
        _item.mandatory_code       
               '_diffrn_frame_data.id'        diffrn_frame_data  yes
        _item_type.code               code
         save_
    
    ################ END DEPRECATED SECTION ###########
    
    
    ####################
    ## ITEM_TYPE_LIST ##
    ####################
    #
    #
    #  The regular expressions defined here are not compliant
    #  with the POSIX 1003.2 standard as they include the
    #  '\n' and '\t' special characters.  These regular expressions
    #  have been tested using version 0.12 of Richard Stallman's
    #  GNU regular expression library in POSIX mode.
    #  In order to allow presentation of a regular expression
    #  in a text field concatenate any line ending in a backslash
    #  with the following line, after discarding the backslash.
    #
    #  A formal definition of the '\n' and '\t' special characters
    #  is most properly done in the DDL, but for completeness, please
    #  note that '\n' is the line termination character ('newline')
    #  and '\t' is the horizontal tab character.  There is a formal
    #  ambiguity in the use of '\n' for line termination, in that
    #  the intention is that the equivalent machine/OS-dependent line
    #  termination character sequence should be accepted as a match, e.g.
    #
    #      '\r' (control-M) under MacOS
    #      '\n' (control-J) under Unix
    #      '\r\n' (control-M control-J) under DOS and MS Windows
    #
         loop_
        _item_type_list.code
        _item_type_list.primitive_code
        _item_type_list.construct
        _item_type_list.detail
                   code      char
    '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
    ;              code item types/single words ...
    ;
                   ucode      uchar
    '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
    ;              code item types/single words (case insensitive)
    ;
                   line      char
    '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
    ;              code item types / multi-word items  ...
    ;
                   uline     uchar
    '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*'
    ;              code item types / multi-word items (case insensitive)
    ;
                   text      char
    '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*'
    ;              text item types / multi-line text ...
    ;
                   binary    char
    ;\n--CIF-BINARY-FORMAT-SECTION--\n\
    [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\
    \n--CIF-BINARY-FORMAT-SECTION----
    ;
    ;              binary items are presented as MIME-like ascii-encoded
                   sections in an imgCIF.  In a CBF, raw octet streams
                   are used to convey the same information.
    ;
                   int       numb
    '-?[0-9]+'
    ;              int item types are the subset of numbers that are the negative
                   or positive integers.
    ;
                   float     numb
    '-?(([0-9]+)|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?'
    ;              float item types are the subset of numbers that are the floating
                   numbers.
    ;
                   any       char
    '.*'
    ;              A catch all for items that may take any form...
    ;
                   yyyy-mm-dd  char
    ;\
    [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9][0-9]\
    (T[0-2][0-9]:[0-5][0-9]:[0-5][0-9](.[0-9]+)([+-][0-5][0-9]:[0-5][0-9]))
    ;
    ;
                   Standard format for CIF date and time strings (see
                   http://www.iucr.org/iucr-top/cif/spec/datetime.html),
                   consisting of a yyyy-mm-dd date optionally followed by
                   the character "T" followed by a 24-hour clock time,
                   optionally followed by a signed time-zone offset.
                   
                   The IUCr standard has been extended to allow for an optional
                   decimal fraction on the seconds of time.
                   
                   Time is local time if no time-zone offset is given.
    ;
    
    
    #####################
    ## ITEM_UNITS_LIST ##
    #####################
    
         loop_
        _item_units_list.code
        _item_units_list.detail
    #
         'metres'                 'metres'
         'centimetres'            'centimetres (metres * 10( -2))'
         'millimetres'            'millimetres (metres * 10( -3))'
         'nanometres'             'nanometres  (metres * 10( -9))'
         'angstroms'              'Ångstroms   (metres * 10(-10))'
         'picometres'             'picometres  (metres * 10(-12))'
         'femtometres'            'femtometres (metres * 10(-15))'
    #
         'reciprocal_metres'      'reciprocal metres (metres(-1))'
         'reciprocal_centimetres' 
            'reciprocal centimetres ((metres * 10( -2))(-1))'
         'reciprocal_millimetres' 
            'reciprocal millimetres ((metres * 10( -3))(-1))'
         'reciprocal_nanometres'  
            'reciprocal nanometres  ((metres * 10( -9))(-1))'
         'reciprocal_angstroms'   
            'reciprocal Ångstroms   ((metres * 10(-10))(-1))'
         'reciprocal_picometres'  
            'reciprocal picometres  ((metres * 10(-12))(-1))'
    #
         'nanometres_squared'     'nanometres squared (metres * 10( -9))2'
         'angstroms_squared'      'Ångstroms squared  (metres * 10(-10))2'
         '8pi2_angstroms_squared' '8π2 * Ångstroms squared (metres * 10(-10))2'
         'picometres_squared'     'picometres squared (metres * 10(-12))2'
    #
         'nanometres_cubed'       'nanometres cubed (metres * 10( -9))3'
         'angstroms_cubed'        'Ångstroms cubed  (metres * 10(-10))3'
         'picometres_cubed'       'picometres cubed (metres * 10(-12))3'
    #
         'kilopascals'            'kilopascals'
         'gigapascals'            'gigapascals'
    #
         'hours'                  'hours'
         'minutes'                'minutes'
         'seconds'                'seconds'
         'microseconds'           'microseconds'
    #
         'degrees'                'degrees (of arc)'
         'degrees_squared'        'degrees (of arc) squared'
    #
         'degrees_per_minute'     'degrees (of arc) per minute'
    #
         'celsius'                'degrees (of temperature) Celsius'
         'kelvins'                'degrees (of temperature) Kelvin'
    #
         'counts'                 'counts'
         'counts_per_photon'      'counts per photon'
    #
         'electrons'              'electrons'
    #
         'electrons_squared'      'electrons squared'
    #
         'electrons_per_nanometres_cubed'
    ; electrons per nanometres cubed (electrons/(metres * 10( -9))(-3))
    ;
         'electrons_per_angstroms_cubed'
    ; electrons per Ångstroms cubed (electrons/(metres * 10(-10))(-3))
    ;
         'electrons_per_picometres_cubed'
    ; electrons per picometres cubed (electrons/(metres * 10(-12))(-3)) 
    ;
         'kilowatts'              'kilowatts'
         'milliamperes'           'milliamperes'
         'kilovolts'              'kilovolts'
    #
         'arbitrary'
    ; arbitrary system of units.
    ;
    #
    
         loop_
        _item_units_conversion.from_code
        _item_units_conversion.to_code
        _item_units_conversion.operator
        _item_units_conversion.factor
    ###
         'metres'                   'centimetres'              '*'   1.0E+02
         'metres'                   'millimetres'              '*'   1.0E+03
         'metres'                   'nanometres'               '*'   1.0E+09
         'metres'                   'angstroms'                '*'   1.0E+10
         'metres'                   'picometres'               '*'   1.0E+12
         'metres'                   'femtometres'              '*'   1.0E+15
    #
         'centimetres'              'metres'                   '*'   1.0E-02
         'centimetres'              'millimetres'              '*'   1.0E+01
         'centimetres'              'nanometres'               '*'   1.0E+07
         'centimetres'              'angstroms'                '*'   1.0E+08
         'centimetres'              'picometres'               '*'   1.0E+10
         'centimetres'              'femtometres'              '*'   1.0E+13
    #
         'millimetres'              'metres'                   '*'   1.0E-03
         'millimetres'              'centimetres'              '*'   1.0E-01
         'millimetres'              'nanometres'               '*'   1.0E+06
         'millimetres'              'angstroms'                '*'   1.0E+07
         'millimetres'              'picometres'               '*'   1.0E+09
         'millimetres'              'femtometres'              '*'   1.0E+12
    #
         'nanometres'               'metres'                   '*'   1.0E-09
         'nanometres'               'centimetres'              '*'   1.0E-07
         'nanometres'               'millimetres'              '*'   1.0E-06
         'nanometres'               'angstroms'                '*'   1.0E+01
         'nanometres'               'picometres'               '*'   1.0E+03
         'nanometres'               'femtometres'              '*'   1.0E+06
    #
         'angstroms'                'metres'                   '*'   1.0E-10
         'angstroms'                'centimetres'              '*'   1.0E-08
         'angstroms'                'millimetres'              '*'   1.0E-07
         'angstroms'                'nanometres'               '*'   1.0E-01
         'angstroms'                'picometres'               '*'   1.0E+02
         'angstroms'                'femtometres'              '*'   1.0E+05
    #
         'picometres'               'metres'                   '*'   1.0E-12
         'picometres'               'centimetres'              '*'   1.0E-10
         'picometres'               'millimetres'              '*'   1.0E-09
         'picometres'               'nanometres'               '*'   1.0E-03
         'picometres'               'angstroms'                '*'   1.0E-02
         'picometres'               'femtometres'              '*'   1.0E+03
    #
         'femtometres'              'metres'                   '*'   1.0E-15
         'femtometres'              'centimetres'              '*'   1.0E-13
         'femtometres'              'millimetres'              '*'   1.0E-12
         'femtometres'              'nanometres'               '*'   1.0E-06
         'femtometres'              'angstroms'                '*'   1.0E-05
         'femtometres'              'picometres'               '*'   1.0E-03
    ###
         'reciprocal_centimetres'   'reciprocal_metres'        '*'   1.0E+02
         'reciprocal_centimetres'   'reciprocal_millimetres'   '*'   1.0E-01
         'reciprocal_centimetres'   'reciprocal_nanometres'    '*'   1.0E-07
         'reciprocal_centimetres'   'reciprocal_angstroms'     '*'   1.0E-08
         'reciprocal_centimetres'   'reciprocal_picometres'    '*'   1.0E-10
    #
         'reciprocal_millimetres'   'reciprocal_metres'        '*'   1.0E+03
         'reciprocal_millimetres'   'reciprocal_centimetres'   '*'   1.0E+01
         'reciprocal_millimetres'   'reciprocal_nanometres'    '*'   1.0E-06
         'reciprocal_millimetres'   'reciprocal_angstroms'     '*'   1.0E-07
         'reciprocal_millimetres'   'reciprocal_picometres'    '*'   1.0E-09
    #
         'reciprocal_nanometres'    'reciprocal_metres'        '*'   1.0E+09
         'reciprocal_nanometres'    'reciprocal_centimetres'   '*'   1.0E+07
         'reciprocal_nanometres'    'reciprocal_millimetres'   '*'   1.0E+06
         'reciprocal_nanometres'    'reciprocal_angstroms'     '*'   1.0E-01
         'reciprocal_nanometres'    'reciprocal_picometres'    '*'   1.0E-03
    #
         'reciprocal_angstroms'     'reciprocal_metres'        '*'   1.0E+10
         'reciprocal_angstroms'     'reciprocal_centimetres'   '*'   1.0E+08
         'reciprocal_angstroms'     'reciprocal_millimetres'   '*'   1.0E+07
         'reciprocal_angstroms'     'reciprocal_nanometres'    '*'   1.0E+01
         'reciprocal_angstroms'     'reciprocal_picometres'    '*'   1.0E-02
    #
         'reciprocal_picometres'    'reciprocal_metres'        '*'   1.0E+12
         'reciprocal_picometres'    'reciprocal_centimetres'   '*'   1.0E+10
         'reciprocal_picometres'    'reciprocal_millimetres'   '*'   1.0E+09
         'reciprocal_picometres'    'reciprocal_nanometres'    '*'   1.0E+03
         'reciprocal_picometres'    'reciprocal_angstroms'     '*'   1.0E+01
    ###
         'nanometres_squared'       'angstroms_squared'        '*'   1.0E+02
         'nanometres_squared'       'picometres_squared'       '*'   1.0E+06
    #
         'angstroms_squared'        'nanometres_squared'       '*'   1.0E-02
         'angstroms_squared'        'picometres_squared'       '*'   1.0E+04
         'angstroms_squared'        '8pi2_angstroms_squared'   '*'   78.9568
    
    #
         'picometres_squared'       'nanometres_squared'       '*'   1.0E-06
         'picometres_squared'       'angstroms_squared'        '*'   1.0E-04
    ###
         'nanometres_cubed'         'angstroms_cubed'          '*'   1.0E+03
         'nanometres_cubed'         'picometres_cubed'         '*'   1.0E+09
    #
         'angstroms_cubed'          'nanometres_cubed'         '*'   1.0E-03
         'angstroms_cubed'          'picometres_cubed'         '*'   1.0E+06
    #
         'picometres_cubed'         'nanometres_cubed'         '*'   1.0E-09
         'picometres_cubed'         'angstroms_cubed'          '*'   1.0E-06
    ###
         'kilopascals'              'gigapascals'              '*'   1.0E-06
         'gigapascals'              'kilopascals'              '*'   1.0E+06
    ###
         'hours'                    'minutes'                  '*'   6.0E+01
         'hours'                    'seconds'                  '*'   3.6E+03
         'hours'                    'microseconds'             '*'   3.6E+09
    #
         'minutes'                  'hours'                    '/'   6.0E+01
         'minutes'                  'seconds'                  '*'   6.0E+01
         'minutes'                  'microseconds'             '*'   6.0E+07
    #
         'seconds'                  'hours'                    '/'   3.6E+03
         'seconds'                  'minutes'                  '/'   6.0E+01
         'seconds'                  'microseconds'             '*'   1.0E+06
    #
         'microseconds'             'hours'                    '/'   3.6E+09
         'microseconds'             'minutes'                  '/'   6.0E+07
         'microseconds'             'seconds'                  '/'   1.0E+06
    ###
         'celsius'                  'kelvins'                  '-'     273.0
         'kelvins'                  'celsius'                  '+'     273.0
    ###
         'electrons_per_nanometres_cubed'
         'electrons_per_angstroms_cubed'                       '*'   1.0E+03
         'electrons_per_nanometres_cubed'
         'electrons_per_picometres_cubed'                      '*'   1.0E+09
    #
         'electrons_per_angstroms_cubed'
         'electrons_per_nanometres_cubed'                      '*'   1.0E-03
         'electrons_per_angstroms_cubed'
         'electrons_per_picometres_cubed'                      '*'   1.0E+06
    #
         'electrons_per_picometres_cubed'
         'electrons_per_nanometres_cubed'                      '*'   1.0E-09
         'electrons_per_picometres_cubed'
         'electrons_per_angstroms_cubed'                       '*'   1.0E-06
    ###
    
    
    ########################
    ## DICTIONARY_HISTORY ##
    ########################
    
         loop_
        _dictionary_history.version
        _dictionary_history.update
        _dictionary_history.revision
    
    
       1.3.1   2003-08-13
    ;
       Changes as per Frances C. Bernstein.
       + Identify initials.
       + Adopt British spelling for centre in text.
       + Set π and Ångstrom and powers.
       + Clean up commas and unclear wordings.
       + Clean up tenses in history.
       Changes as per Gotzon Madariaga.
       + Fix the ARRAY_DATA example to align '_array_data.binary_id'
       and X-Binary-Id.
       + Add a range to '_array_intensities.gain_esd'.
       + In the example of DIFFRN_DETECTOR_ELEMENT, 
       '_diffrn_detector_element.id' and
       '_diffrn_detector_element.detector_id' interchanged.
       + Fix typos for direction, detector and axes.
       + Clarify description of polarisation.
       + Clarify axes in '_diffrn_detector_element.center[1]'
        '_diffrn_detector_element.center[2]'.
       + Add local item types for items that are pointers.
       (HJB)
    ;
    
    
       1.3.0   2003-07-24
    ;
       Changes as per Brian McMahon. 
       + Consistently quote tags embedded in text.
       + Clean up introductory comments.
       + Adjust line lengths to fit in 80 character window.
       + Fix several descriptions in AXIS category which
         referred to '_axis.type' instead of the current item.
       + Fix erroneous use of deprecated item
         '_diffrn_detector_axis.id' in examples for 
         DIFFRN_SCAN_AXIS.
       + Add deprecated items '_diffrn_detector_axis.id'
         and '_diffrn_measurement_axis.id'.
       (HJB)
    ;
    
    
       1.2.4   2003-07-14
    ;
       Changes as per I. David Brown. 
       + Enhance descriptions in DIFFRN_SCAN_AXIS to make them less
         dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS.
       + Provide a copy of the deprecated DIFFRN_FRAME_DATA
         category for completeness.
       (HJB)
    ;
    
    
       1.2.3   2003-07-03
    ;
       Cleanup to conform to ITVG. 
       + Correct sign error in ..._cubed units.
       + Correct '_diffrn_radiation.polarisn_norm' range.
       (HJB)
    ;
    
    
       1.2.2   2003-03-10
    ;
       Correction of typos in various DIFFRN_SCAN_AXIS descriptions. 
       (HJB)
    ;
    
    
       1.2.1   2003-02-22
    ;
       Correction of ATOM_ for ARRAY_ typos in various descriptions. 
       (HJB)
    ;
    
    
       1.2     2003-02-07
    ;
       Corrections to encodings (remove extraneous hyphens) remove
       extraneous underscore in '_array_structure.encoding_type'
       enumeration.  Correct typos in items units list.  (HJB)
    ;
    
    
       1.1.3   2001-04-19
    ;
       Another typo corrections by Wilfred Li, and cleanup by HJB.
    ;
    
    
       1.1.2   2001-03-06
    ;
       Several typo corrections by Wilfred Li.
    ;
    
    
       1.1.1   2001-02-16
    ;
       Several typo corrections by JW.
    ;
    
    
       1.1     2001-02-06
    ;
       Draft resulting from discussions on header for use at NSLS.  (HJB)
       
       + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME.
       
       + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'.
       
       + Add '_diffrn_measurement_axis.measurement_device' and change
         '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'.
       
       + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source',
        '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm',
       '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end',
       '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr',
       '_diffrn_scan_axis.displacement_rstrt_incr', 
       '_diffrn_scan_frame_axis.angle_increment',
       '_diffrn_scan_frame_axis.angle_rstrt_incr',
       '_diffrn_scan_frame_axis.displacement',
       '_diffrn_scan_frame_axis.displacement_increment',and
       '_diffrn_scan_frame_axis.displacement_rstrt_incr'.
       
       + Add '_diffrn_measurement.device' to category key.
       
       + Update yyyy-mm-dd to allow optional time with fractional seconds
         for time stamps.
    
       + Fix typos caught by RS.
       
       + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to
         allow for coupled axes, as in spiral scans.
    
       + Add examples for fairly complete headers thanks to R. Sweet and P. 
         Ellis.
    ;
    
    
       1.0     2000-12-21
    ;
       Release version - few typos and tidying up.  (BM & HJB)
       
       + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end
       of dictionary.
       
       + Alphabetize dictionary.
    ;
    
    
       0.7.1   2000-09-29
    ;
       Cleanup fixes.  (JW)
    
       + Correct spelling of diffrn_measurement_axis in '_axis.id'
    
       + Correct ordering of uses of '_item.mandatory_code' and
       '_item_default.value'.
    ;
    
    
       0.7.0   2000-09-09
    ;
       Respond to comments by I. David Brown.  (HJB)
    
       + Add further comments on '\n' and '\t'.
    
       + Update ITEM_UNITS_LIST by taking section from mmCIF dictionary
         and adding metres.  Change 'meter' to 'metre' throughout.
    
       + Add missing enumerations to '_array_structure.compression_type'
         and make 'none' the default.
    
       + Remove parent-child relationship between
         '_array_structure_list.index' and '_array_structure_list.precedence'.
    
       + Improve alphabetization.
    
       + Fix '_array_intensities_gain.esd' related function.
    
       + Improve comments in AXIS.
    
       + Fix DIFFRN_FRAME_DATA example.
    
       + Remove erroneous DIFFRN_MEASUREMENT example.
    
       + Add '_diffrn_measurement_axis.id' to the category key.
    ;
    
    
       0.6.0   1999-01-14
    ;
       Remove redundant information for ENC_NONE data.  (HJB)
    
       + After the D5 remove binary section identifier, size and
         compression type.
    
       + Add Control-L to header.
    ;
    
    
       0.5.1   1999-01-03
    ;
       Cleanup of typos and syntax errors.  (HJB)
    
       + Cleanup example details for DIFFRN_SCAN category.
    
       + Add missing quote marks for '_diffrn_scan.id' definition.
    ;
    
    
       0.5   1999-01-01
    ;
       Modifications for axis definitions and reduction of binary header.  (HJB)
    
       + Restore '_diffrn_detector.diffrn_id' to DIFFRN_DETECTOR KEY.
    
       + Add AXIS category.
    
       + Bring in complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories
         from cif_mm.dic for clarity.
    
       + Change '_array_structure.encoding_type' from type code to uline and
         added X-Binary-Element-Type to MIME header.
    
       + Add detector beam centre '_diffrn_detector_element.center[1]' and 
         '_diffrn_detector_element.center[2]'.
    
       + Correct item name of '_diffrn_refln.frame_id'.
    
       + Replace reference to '_array_intensities.undefined' by
         '_array_intensities.undefined_value'.
    
       + Replace references to '_array_intensity.scaling' with
         '_array_intensities.scaling'.
    
       + Add DIFFRN_SCAN... categories.
    ;
    
    
       0.4   1998-08-11
    ;
       Modifications to the 0.3 imgCIF draft.  (HJB)
    
       + Reflow comment lines over 80 characters and corrected typos.
    
       + Update examples and descriptions of MIME encoded data.
    
       + Change name to cbfext98.dic.
    ;
    
    
       0.3   1998-07-04
    ;
       Modifications for imgCIF.  (HJB)
    
       + Add binary type, which is a text field containing a variant on
         MIME encoded data.
          
       + Change type of '_array_data.data' to binary and specify internal
         structure of raw binary data.
          
       + Add '_array_data.binary_id', and make 
         '_diffrn_frame_data.binary_id' and '_array_intensities.binary_id'
         into pointers to this item.
    ;
    
    
       0.2   1997-12-02
    ;
       Modifications to the CBF draft.  (JW)  
    
       + Add category hierarchy for describing frame data developed from
         discussions at the BNL imgCIF Workshop Oct 1997.   The following
         changes are made in implementing the workshop draft.  Category
         DIFFRN_ARRAY_DATA is renamed to DIFFRN_FRAME_DATA.  Category
         DIFFRN_FRAME_TYPE is renamed to DIFFRN_DETECTOR_ELEMENT.   The
         parent item for '_diffrn_frame_data.array_id' is changed from
         '_array_structure_list.array_id' to '_array_structure.id'. Item 
         '_diffrn_detector.array_id' is deleted.  
       + Add data item '_diffrn_frame_data.binary_id' to identify data 
         groups within a binary section.  The formal identification of the
         binary section is still fuzzy.  
    ;
    
    
       0.1   1997-01-24
    ;
       First draft of this dictionary in DDL 2.1 compliant format by John 
       Westbrook (JW).  This version is adapted from the Crystallographic 
       Binary File (CBF) Format Draft Proposal provided by Andy Hammersley
       (AH).  
    
       Modifications to the CBF draft.  (JW)  
    
       + In this version the array description has been cast in the categories 
         ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST.  These categories
         have been generalized to describe array data  of arbitrary dimension.  
    
       + Array data in this description are contained in the category
         ARRAY_DATA.  This departs from the CBF notion of data existing
         in some special comment. In this description, data is handled as an 
         ordinary data item encapsulated in a character data type.   Although
         data this manner deviates from CIF conventions, it does not violate 
         any DDL 2.1 rules.  DDL 2.1 regular expressions can be used to define 
         the binary representation which will permit some level of data 
         validation.  In this version, the placeholder type code "any" has
         been used. This translates to a regular expression which will match 
         any pattern.
    
         It should be noted that DDL 2.1 already supports array data objects 
         although these have not been used in the current mmCIF dictionary.
         It may be possible to use the DDL 2.1 ITEM_STRUCTURE and
         ITEM_STRUCTURE_LIST categories to provide the information that is
         carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST.  By
         moving the array structure to the DDL level it would be possible to
         define an array type as well as a regular expression defining the
         data format. 
    
       + Multiple array sections can be properly handled within a single
         datablock.
    ;
    
    
    #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof
    
    ./CBFlib-0.9.2.2/doc/ChangeLog0000644000076500007650000032730111603702115014123 0ustar yayayaya CBFlib ChangeLog An API for CBF/imgCIF Crystallographic Binary Files with ASCII Support Version 0.9.2 12 February 2011 by Paul J. Ellis Stanford Synchrotron Radiation Laboratory and Herbert J. Bernstein Bernstein + Sons yaya at bernstein-plus-sons dot com (c) Copyright 2006, 2007, 2008, 2011 Herbert J. Bernstein ---------------------------------------------------------------------- YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL. ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS OF THE LGPL. ---------------------------------------------------------------------- Before using this software, please read the NOTICE for important disclaimers and the IUCr Policy on the Use of the Crystallographic Information File (CIF) and for other important information. Work on imgCIF and CBFlib supported in part by the U. S. Department of Energy (DOE) under grants ER63601-1021466-0009501 and ER64212-1027708-0011962, by the U. S. National Science Foundation (NSF) under grants DBI-0610407, DBI-0315281 and EF-0312612, the U. S. National Institutes of Health (NIH) under grants 1R15GM078077 from NIGMS and 1R13RR023192 from NCRR and funding from the International Union for Crystallographyn (IUCr). The content is solely the responsibility of the authors and does not necessarily represent the official views of DOE, NSF, NIH, NIGMS, NCRR or IUCr. ---------------------------------------------------------------------- Version History Version Date By Description 0.1 Apr. 1998 PJE This was the first CBFlib release. It supported binary CBF files using binary strings. 0.2 Aug. 1998 HJB This release added ascii imgCIF support using MIME-encoded binary sections, added the option of MIME headers for the binary strings was well. MIME code adapted from mpack 1.5. Added hooks needed for DDL1-style names without categories. 0.3 Sep. 1998 PJE This release cleaned up the changes made for version 0.2, allowing multi-threaded use of the code, and removing dependence on the mpack package. 0.4 Nov. 1998 HJB This release merged much of the message digest code into the general file reading and writing to reduce the number of passes. More consistency checking between the MIME header and the binary header was introduced. The size in the MIME header was adjusted to agree with the version 0.2 documentation. 0.5 Dec. 1998 PJE This release greatly increased the speed of processing by allowing for deferred digest evaluation. 0.6 Jan. 1999 HJB This release removed the redundant information (binary id, size, compression id) from a binary header when there is a MIME header, removed the unused repeat argument, and made the memory allocation for buffering and tables with many rows sensitive to the current memory allocation already used. 0.6.1 Feb. 2001 HP (per This release fixed a memory leak due HJB) to misallocation by size of cbf_handle instead of cbf_handle_struct 0.7 Mar. 2001 PJE This release added high-level instructions based on the imgCIF dictionary version 1.1. 0.7.1 Mar. 2001 PJE The high-level functions were revised to permit future expansion to files with multiple images. 0.7.2 Apr. 2001 HJB This release adjusted cbf_cimple.c to conform to cif_img.dic version 1.1.3 0.7.2.1 May 2001 PJE This release corrected an if nesting error in the prior mod to cbf_cimple.c. 0.7.3 Oct. 2002 PJE This release modified cbf_simple.c to reorder image data on read so that the indices are always increasing in memory (this behavior was undefined previously). 0.7.4 Jan 2004 HJB This release fixes a parse error for quoted strings, adds code to get and set character string types, and removes compiler warnings 0.7.5 Apr 2006 HJB This release cleans up some compiler warnings, corrects a parse error on quoted strings with a leading blank as adds the new routines for support of aliases, dictionaries and real arrays, higher level routines to get and set pixel sizes, do cell computations, and to set beam centers, improves support for conversion of images, picking up more data from headers. 0.7.6 Jul 2006 HJB This release reorganizes the kit into two pieces: CBFlib_0.7.6_Data_Files and CBFlib_0.7.6. An optional local copy of getopt is added. The 1.4 draft dictionary has been added. cif2cbf updated to support vcif2 validation. convert_image and cif2cbf updated to report text of error messages. convert_image updated to support tag and category aliases, default to adxv images. convert_image and img updated to support row-major images. Support added for binning. API Support added for validation, wide files and line folding. Logic changed for beam center reporting. Added new routines: cbf_validate, cbf_get_bin_sizes, cbf_set_bin_sizes, cbf_find_last_typed_child, cbf_compose_itemname, cbf_set_cbf_logfile, cbf_make_widefile, cbf_read_anyfile, cbf_read_widefile, cbf_write_local_file, cbf_write_widefile, cbf_column_number, cbf_blockitem_number, cbf_log, cbf_check_category_tags, cbf_set_beam_center 0.7.7 February 2007 HJB This release reflects changes for base 32K support developed by G. Darakev, and changes for support of reals, 3d arrays, byte_offset compression and J. P. Abrahams packed compression made in consultation with (in alphabetic order) E. Eikenberry, A. Hammerley, W. Kabsch, M. Kobas, J. Wright and others at PSI and ESRF in January 2007, as well accumulated changes fixing problems in release 0.7.6. 0.7.7.1 February 2007 HJB This release is a patch to 0.7.7 to change the treatment of the byteorder parameter from strcpy semantics to return of a pointer to a string constant. Our thanks to E. Eikenberry for pointing out the problem. 0.7.7.2 February 2007 HJB This release is a patch to 0.7.7.1 to add testing for JPA packed compression and to respect signs declared in the MIME header. 0.7.7.3 April 2007 HJB This release is a patch to 0.7.7.3 to add f90 support for reading of CBF byte-offset and packed compression, to fix problems with gcc 4.4.1 and to correct errors in multidimensional packed compression. 0.7.7.4 May 2007 HJB Corrects in handling SLS detector mincbfs and reorder dimensions versus arrays for some f90 compilers as per H. Powell. 0.7.7.5 May 2007 HJB Fix to cbf_get_image for bug reported by F. Remacle, fixes for windows builds as per J. Wright and F. Remacle. 0.7.7.6 Jun 2007 HJB Fix to CBF byte-offset compression writes, fix to Makefiles and m4 for f90 test programs to allow adjustable record length. 0.7.8 Jul 2007 HJB Release for full support of SLS data files with updated convert_minicbf, and support for gfortran from gcc 4.2. 0.7.8.1 Jul 2007 HJB Update to 0.7.8 release to fix memory leaks reported by N. Sauter and to update validation checks for recent changes. 0.7.8.2 Dec 2007 CN, HJB Update to 0.7.8.1 to add ADSC jiffie by Chris Nielsen, and to add ..._fs and ..._sf macros. 0.7.9 Dec 2007 CN, HJB Identical to 0.7.8.2 except for a cleanup of deprecated examples, e.g. diffrn_frame_data 0.7.9.1 Jan 2008 CN, HJB Update to 0.7.8.2 to add inverse ADSC jiffie by Chris Nielsen, to clean up problems in handling maps for RasMol. 0.8.0 Jul 2008 GT, HJB Cleanup of 0.7.9.1 to start 0.8 series. 0.8.1 Jul 2009 EZ, CN, Release with EZ's 2008 DDLm support PC, GW, using JH's PyCifRW, also cbff f95 JH, HJB wrapper code, PC's java bindings. 0.9.1 Aug 2010 PC, EE, Release with EE's Dectris template JLM, NS, software, also with vcif3, new EZ, HJB arvai_test, sequence_match. 0.9.2 Feb 2011 PC, EE, New default release with updated JLM, NS, pycbf, tiff support, removal of EZ, HJB default use of PyCifRW to avoid Fedora license issue. ---------------------------------------------------------------------- Release 0.9.2, Herbert J. Bernstein, 12 February 2011 Source File Change Makefile.m4, Makefiles Changes for libtiff and tiff2cbf. Create a separate setup.py for MINGW. Allow CBF_DONT_USE_LONG_LONG variable to control Makefiles. Disable default use of PyCifRW because of Fedora concerns about PyCifRW license issues. Force use of long long for SWIG. Update Makefiles to run changtestcompression. Update pycbf build. cbf_template_t.c Don't use /tmp for dectris template code. Add EE's change for DLS signs cbf_copy.c Fix cbf_copy.c to handle not using long long correctly jcbf.i Move cbf.i to jcbf directory. cbf_byte_offset.h, cbf_canonical.h, Implement P. Chang's fast byte-offset cbf_compress.h, decompress, but with hooks to run on machines cbf_packed.h, without long long support. Fix bad mask, fix cbf_predictor.h, sign extension for MINGW and other systems in cbf_uncompressed.h, cbf.c, which long long is not used. Fix error in cbf_binary.c, mpint_shift logic causing erroneous sign Add cbf_byte_offset.c, changes in the compression infrastructure by P. cbf_canonical.c, Chang to make the compressed size available on cbf_compress.c, decompression. Extend cbf_canonical to support cbf_packed.c, long long and double. Correct cbf_packed for cbf_predictor.c, elsize 8 data. cbf_uncompressed.c, cbff.c cbfdetectorwrappers.i, Update pycbf for 0.9 release Add cbfgenericwrappers.i, cbf_get_detector_axis_slow, cbfgoniometerwrappers.i, cbf_get_detector_axis_fast, cbfhandlewrappers.i, cbf_get_detector_axes, make_pycbf.py, pycbf.py, cbf_get_detector_axes_fs, cbf_get_detector_sf, pycbf_test2.py, and changes for pycbf wrapper pycbf_wrap.c, cbf_simple.c cbf2adscimg_sub.c Fix buffer overflow cif_img_1.6.3_26Aug10.dic, cif_img_1.6.3_26Aug10.html Add variant category and tags and diffrn_scan_frame_monitor ---------------------------------------------------------------------- Release 0.9.1, P. Chang, E. Eikenberry, J. Lewis Muir, N. Sauter, E. Zlateva, Herbert J. Bernstein, 15 August 2010 Source File Change cbf_simple.c Fix nested axis handling. cbf_template_t.c Add E.E.'s Dectris template software. Change to C-style comments. Makefile.m4, Add DMALLOC hooks. Makefiles arvai_test.c, seqmatchsub.c, seqmatchsub.h, sequence_match.c, Add arvai_test and sequence_match examples. Transfer cbf_copy.h, copy logic from cib2cbf into cbf_copy.c Makefile.m4, cbf_ascii.c, cbf_copy.c cbf.h, cbf_ascii.h, cbf_file.h, As per request by J. Lewis Muir, direct all warning cbf_write.h, messages through cbf_log or new cbf_flog, so such cbff.h, cbf.c, messages can all be suppressed by setting the logfile cbf_ascii.c, to NULL cbf_file.c, cbf_lex.c, cbf_write.c cbf_byte_offset.c, Fix to byte-offset compression for 16 bit data with a cbf_file.c delta that looks like a flag. Fix to setting/getting file position when there is no stream. Fix incorrect sign extension test as per N. Sauter. convert_minicbf.c Allow for changes in miniheader and report unrecognized lines but continue. Also allow S/N instead of SN Makefile.m4, Makefiles, As per P. Chang, decouple CBF_UNDEFINED error return Java.txt, from CBF_UNDEFINED node type by defining CBF_UNDEFNODE testcbf.java, (rather than PC's CBF_UNDEFINEDNODE) cbf.c drel_prep.py, drel_yacc.py, cif2cbf.c, cbf.h, cbf.c, cbf_ascii.c, vcif 3 release. cbf_lex.c, cbf.stx.y, cbf_getopt.c, cbf_stx.c cbf.h, cbf.c Add function cbf_set_column_name ---------------------------------------------------------------------- Release 0.8.1, E. Zlateva, C. Neilsen, P. Chang, G. Winter, J. Hester, Herbert J. Bernstein, 24 July 2009 Source File Change cbf.h, cbf_stx.h, cbf_tree.h, cbf.c, cbf.stx.y, As per EZ, Add DDLm support, parsing of function cbf_lex.c, definitions. Add auto download of J. Hester's PyCifRW cbf_stx.c, and PLY Makefile.m4, Makefiles cbf_getopt.c Correct a memory leak and ensure correct handling of unspecified options when a '-' is given on the option string. CBFlib.html, As per G. Winter correct documentation of byte-offset CBFlib.txt algorithm to refer to hex 80 not hex F0. cbf_getopt.h, cbf_getopt.c, Makefile.m4, Makefiles, Introduce cbf_getopt.h, cbf_getopt.c, remove use of cif2cbf.c, getopt convert_image.c, convert_minicbf.c, img2cif.c Java.txt, testcbf.c, P. Chang's java bindings testcbf.java, Makefile.m4, cbf.i libtool directory Add a libtool build directory for future use of shared libraries. cif2cbf.c Add test for construct_detector to cif2cbf. Fix getopt option string. cif_tree.h Add DDLm bracket types for nodes adscimg2cbf.c, Apply mods to adscimg2cbf by C. Nielsen: Add new adscimg2cbf_sub.c command line options: --beam_center_from_header, Figure out beam center from ADSC header information (default); --beam_center_mosflm, Beam center in ADSC header: MOSFLM coordinates; --beam_center_ulhc, Beam center in ADSC header: origin: upper left hand corner of image.(HKL mm); --beam_center_llhc, Beam center in ADSC header: origin: lower left hand corner of image.(adxv mm) cbff.h, cbff.c Add src/cbff.c and include/cbff.h as start of full f95 wrapper for C code ---------------------------------------------------------------------- Release 0.8.0, G. Todorov, Herbert J. Bernstein, 21 July 2008 Source File Change adscimg2cbf_sub.c, Patch to deal with gcc 4 optimization error in get_bo adscimg2cbf_sub.c Replaced with call to cbf_get_local_integer_byte_order. cbf.c, cbf.h, Clean up spacing; trim trailing blanks in text cbf_ascii.c, fields; validate DDLm types. Add MSG_DIGESTWARN. Update cbf_file.c, spacing. Fix includes for regex use. Fixes on achar and cbf_lex.c, anchar and element. Added cbf_check_type_contents cbf_write.c function that will verify ddlm types based on regular expressions. Fix handling for bracketed unquoted words and handle more DDLm tags. Fix scan of DDLm bracketed constructs with embedded quotes. Pick up item names in DDLm save frames. Fix cif2cbf handling of bracketed constructs in dictionaries. Updates to bracketed construct parse and output logic. Update write logic for bracketed constructs with folding. cbf_set_tag_category() code fixed. Change internal routine cbf_read_anyfile and add new user routine cbf_read_buffered_file to support pre-read of input files and memory-only files. Add new routines cbf_io_buffersize and cbf_reset_in_bits and change read logic to allow buffered reads. ---------------------------------------------------------------------- Release 0.7.9.1, Chris Nielsen, Herbert J. Bernstein, 24 January 2008 Source File Change cbf2adscimg.c Last minutes fixes on release: Put missing byte swap cbf2adscimg_sub.c in cbf2adscimg.c for when byte orders differ. Bypass problems with gcc optimization, and handle case then array header is there but invalid. .symlinks Update version to 0.7.9 .undosymlinks Makefile.m4 Update for CN's jiffies, and testing with MD5 Makefile, signatures only Makefile_AIX ... cbf2adscimg.c New inverse jiffie by Chris Nielsen of ADSC to cbf2adscimg_sub.c convert CBF files created by convert_image or adscimg2cbf to ADSC detector images. This version depends on the header extract planted by convert_image or adscimg2cbf. cbf_byte_offset.c Fix handling of byte offset compression when the data does not compress. cbf_codes.c Fix 32K encoding big-endian test as per Ladislav Michnovic . cbf_packed.c Correct mishandling of 64 bit data. cbf_uncompressed.c Remove redundant initialization of unsigned_char_data. cbf_write.c.c Fix conflicting uses of variable column by introducing separate variable xcol. README.html README Update to version 0.7.9 directory structure and programs. cbf.c Fix local sensitivity of cbf_get_doublevalue and cbf_set_doublevalue so "." will be accepted and written as the decimal point in locales that use ",". ---------------------------------------------------------------------- Release 0.7.9, Chris Nielsen, Herbert J. Bernstein, 30 December 2007 Source File Change Makefiles and test data Change test cases to avoid deprecated features. ---------------------------------------------------------------------- Release 0.7.8.2, Chris Nielsen, Herbert J. Bernstein, 25 December 2007 Source File Change adscimg2cbf.c adscimg2cbf_sub.c New jiffie by Chris Nielsen of ADSC to convert ADSC detector images to CBF. cbf.h cbf_byte_offset.h, cbf_compress.h, Add _fs and _sf versions of cbf_read_mime.h, cbf_simple.h cbf_get_arrayparameters_wdims, cbf_get_integerarrayparameters_wdims, cbf_get_realarrayparameters_wdims, cbf_set_integerarray_wdims, cbf_set_realarray_wdims, cbf_compress_byte_offset, cbf_compress, cbf_decompress, cbf_parse_mimeheader, cbf_get_pixel_size, cbf_set_pixel_size, cbf_get_image_size, cbf_get_image, cbf_get_real_image, cbf_get_3d_image_size, cbf_get_3d_image, cbf_get_real_3d_image, cbf_set_image, cbf_set_real_image, cbf_set_3d_image, cbf_set_real_3d_image, cbf_get_map_array_id, cbf_get_map_segment_size, cbf_get_map_segment, cbf_get_map_segment_mask, cbf_get_real_map_segment, cbf_get_real_map_segment_mask, cbf_set_map_segment, cbf_set_map_segment_mask, cbf_set_real_map_segment, cbf_set_real_map_segment_mask, cbf_get_3d_array_size, cbf_get_3d_array, cbf_set_3d_array, cbf_get_beam_center, cbf_set_beam_center, cbf_set_reference_beam_center, cbf_get_pixel_coordinates, cbf_get_pixel_normal, cbf_get_pixel_area, cbf_get_inferred_pixel_size cbf_alloc.h Add prototype of cbf_free_text. cbf_binary.h Add prototype of cbf_check_digest. cbf_canonical.h Add definitions of cbf_compress_node and cbf_compress_data, and prototypes of cbf_make_compressdata, cbf_free_compressdata, cbf_initialise_compressdata, cbf_put_table, cbf_get_table, cbf_put_stopcode, cbf_insert_node, cbf_append_node, cbf_order_node, cbf_create_list, cbf_reduce_list, cbf_generate_codelengths, cbf_reverse_bitcodes, cbf_generate_canonicalcodes, cbf_compare_bitcodes, cbf_construct_tree, cbf_setup_decode, cbf_count_bits, cbf_get_code, cbf_put_code and cbf_count_values. cbf_simple.h Add prototypes of cbf_get_detector_id and cbf_gregorian_julian. cbf_string.c, cbf_string.h Add cbf_swab function for MS windows and other machines that do not provide swab. cbf.c, cbf_binary.c, cbf_byte_offset.c, Change dim1, dim2, dim3 to dimfast, cbf_canonical.c, cbf_compress.c, dimmid, dimslow, ndim1, ndim2 to cbf_lex.c, cbf_packed.c, cbf_predictor.c, ndimslow, ndimfast. machines that do cbf_read_mime.c, cbf_simple.c, not provide swab. cbf_uncompressed.c, cbf_write_binary.c cif2c.c Make declaration of xciftmp conditional to avoid compiler warnings. convert_image.c Add code to check variations on pixel_size functions. convert_minicbf.c Add second quick exit option (-Q). Improve error reporting. Update for most recent SLS miniheader. getopt.c Fix some compiler warnings. Makefile.m4 add adscimg2cbf support template_pilatus6m_2463x2527.cbf Update pilatus6m template for correct detector axis definitions, better comments and to list all categories used by SLS. template_adscquantum315_3072x3072_rev.cbf New, corrected ADSC Quantum 315 template. ---------------------------------------------------------------------- Release 0.7.8.1, Chris Nielsen, Herbert J. Bernstein, 28 July 2007 Source File Change cbf.c Rework cbf_free_handle to ensure release of memory from root, not current position. Rework cbf_read_anyfile to ensure close of file stream on all exit cases. Fix save frame code in cbf_validate to restart counts on each save frame. Add name, idname and aliasname types from latest DDL2 dictionary. cbf_alloc.c, Add cbf_free_text to avoid type punning warnings from cbf_alloc.h gcc 4. Add memory debug based on adding -DCBFLIB_MEM_DEBUG to CFLAGS. cbf_simple.c Add code to ensure against memory leaks when working with a detector or positioner object. cbf.stx.y, Add calls to cbf_undo_links and cbf_free_text to cbf_stx.c clean up memory leaks in parser. Add validation calls to mark end of save frames. cbf_tree.c, Add cbf_undo_links to recover memory from links used cbf_tree.h to rotate among columns of a table. Rework cbf_free_node to avoid memory leaks. cbf_uncompressed.c Add #define __USE_XOPEN to avoid a warning on use of swab on some systems. sauter_test.C Add sauter_test to stress test for memory leaks. On Makefile.m4 make install, place cbf.h and cbf_simple.h into include directory. ---------------------------------------------------------------------- Release 0.7.8, Herbert J. Bernstein, 8 July 2007 Source File Change cbf_simple.c Update handling of both beam center and reference beam center to allow for units and new dictionary. convert_minicbf.c Add code to handle data in _array_data.header-contents. Clean up error handling, map all SLS tags. Add -Q option to convert old SLS comment format to new text field format. Makefile, Makefile_AIX, As per ND add Makefile_LINUX_gcc42 and Makefile_LINUX, Makefile_OSX_gcc42 to handle gfortran 4.2 problems. Makefile_OSX ---------------------------------------------------------------------- Release 0.7.7.6, Herbert J. Bernstein, 30 June 2007 Source File Change cbf_codes.c Fix memory leaks in base32k encoding by G. Darakev. cbf_byte_offset.c Fix in handling 32 bit offsets in the fast write code, which were incorrectly handled as 16 bit offsets. Makefile, Add M4FLAGS variable to control m4 expansion of f90 Makefile_AIX, test programs with different record lengths. For g95, Makefile_LINUX, the record length must not be larger than the padding. Makefile_OSX ---------------------------------------------------------------------- Release 0.7.7.5, Herbert J. Bernstein, 9 May 2007 Source File Change cbf_codes.c Change from use of bzero to memset and remove include of strings.h cbf_codes.c Change from use of bzero to memset and remove include of strings.h cbf_simple.c Fix ordering of dimensions in cbf_get_3d_array_size and handling of non-zero binary ids to fix problems with cbf_get_image and cbf_get_image_size cbf_uncompressed.c Add include of unistd.h for use of swab on more systems Makefile Introduce $(TIME) variable for time command so it can be suppressed in windows fcb_read_bits.m4 Changes for g95 compatibility. cif2c.c, Make use of mkstemp conditional on NOMKSTEMP. Make cif2cbf.c, etc. use of /tmp conditional on NOTMPDIR. ---------------------------------------------------------------------- Release 0.7.7.4, Herbert J. Bernstein, 6 May 2007 Source File Change cbf_simple.c Fix ordering of dimensions in cbf_set_3d_array. cbf_uncompressed.c Add include of ctype.h to provide prototype for toupper. convert_image.c Enable -p option for non-standard templates; correct handling of seconds in timestamps. convert_minicbf.c Enable code for timestamp, exposure time, comment-style header. fcb_packed.m4 As per H. Powell, move declarations for dimensions before declarations of arrays. fcb_read_image.m4 As per H. Powell, move declarations for dimensions before declarations of arrays. fcblib_defines.m4 As per H. Powell, move declarations for dimensions before declarations of arrays. ---------------------------------------------------------------------- Release 0.7.7.3, Herbert J. Bernstein, 3 April 2007 Source File Change Makefile Add m4 directory to build f90 sources. Add .f90 routines to src and examples. Add libfcb.a to lib. Add tests for f90 routines to extra tests. testflat.c Add support for 3D test. testflatpacked.c Add support for 3D test. cbf_binary.c Correct dim2,dim2 to be dim1,dim2 in check_digest. cbf_packed.c Correct JPA pointer logic for 3D case. Work around compiler problems with handling of sign bits fcb_exit_binary.m4 New m4 macro file to build fcb_exit_binary.f90 a routine to skip from the end of a binary to the end of the text field. fcb_next_binary.m4 New m4 macro file to build fcb_next_binary.f90 a routine to skip to the start of the next binary. fcb_open_cifin.m4 New m4 macro file to build fcb_open_cifin.f90 a routine to open a cbf file. fcb_packed.m4 New m4 macro file to build fcb_packed.f90 a routine to uncompress JPA packed binaries. fcb_read_bits.m4 New m4 macro file to build fcb_read_bits.f90 a routine to read an arbitrary number of bits as an integer. fcb_read_image.m4 New m4 macro file to build fcb_read_image.f90 a set of routines to read a byte offset or packed image fcb_read_xds_i2.m4 New m4 macro file to build fcb_read_xds_i2.f90 a routine to read a single xds I2 image. fcblib_define.m4 New m4 macro file of common definitions for all f90 code test_fcb_read_image.m4 New m4 macro file of build test_fcb_read_image.f90 a test program for the f90 routines. test_xds_binary.m4 New m4 macro file of build test_xds_binary.f90 a test program for the f90 routines. fcb_atol_wcnt.f90 f90 code to convert a string to an integer. fcb_ci_strncmparr.f90 f90 code to do a case-insensitive string comparison fcb_nblen.f90 f90 code to do test the non-blank length of a string fcb_read_byte.f90 f90 code to read a byte fcb_read_line.f90 f90 code to read a line fcb_skip_whitespace.f90 f90 code to skip MIME whitespace ---------------------------------------------------------------------- Release 0.7.7.2, Herbert J. Bernstein, 27 February 2007 Source File Change Makefile Add testflatpacked build to extra test dependencies. testflat.c Add more test cases. testflatpacked.c Add version of testflat for packed compression. cbf_binary.c Add recovery of sign from mime header. cbf_byte_offset.c Change limit logic to simple mask and remove overflow report. cbf_packed.c Change limit logic to simple mask and remove overflow report. cbf_uncompressed.c Change limit logic to simple mask and remove overflow report. ---------------------------------------------------------------------- Release 0.7.7.1, Herbert J. Bernstein, 25 February 2007 Source File Change Makefile Add testflat build to extra test dependencies. CBFlib.html Add descriptions of cbf_get_integerarrayparameters_wdims, cbf_get_realarrayparameters_wdims, cbf_set_integerarray_wdims, cbf_set_realarray_wdims cif2cbf.c Change to use of byteorder as a pointer to a constant string, rather than as a local copy of a string. testflat.c Add report of byteorder, dim1, dim2, dim2, padding. cbf.h, Change prototypes for all functions that return cbf_binary.h, byteorder from char * byteorder to const char ** cbf_byte_offset.h, byteorder. Change prototypes of all functions that set cbf_canonical.h, byteorder from char * byteorder to const char * cbf_compress.h, byteorder cbf_packed.h, cbf_predictor.h, cbf_read_mime.h, cbf_uncompressed.h cbf.c, Change signatures for all functions that return cbf_binary.c, byteorder from char * byteorder to const char ** cbf_byte_offset.c, byteorder. Change prototypes of all functions that set cbf_canonical.c, byteorder from char * byteorder to const char * cbf_compress.c, byteorder, and make the matching changes in all calls. cbf_lex.c, cbf_packed.c, cbf_predictor.c, cbf_read_mime.c, cbf_uncompressed.c, cbf_write_binary.c ---------------------------------------------------------------------- Release 0.7.7, Herbert J. Bernstein, 19 February 2007 Source File Change cif2cbf.c Add support for byte offset, packed version 2 and flat compression, and binary section padding. Add support for base-32K encoding. Allow command line compression to override compression_type in the file and to set compression_type_flag. convert_image.c Add support for new -R and -F flags, for use of reference beam center and flat packed compression respectively. cbf.h Add constants CBF_PACKED_V2 for packed version 2 compression, CBF_UNCORRELATED_SECTIONS for uncorrelated sections in packed compression, CBF_FLAT_IMAGE for original CBFlib packed compression, PAD_1K, PAD_2K and PAD_4K for trailing pad on binary sections, ENC_BASE32K for base 32K encoding. Fix bad code in DEBUG mode for failnez macros. Add prototypes for cbf_get_arrayparameters_wdims, cbf_get_integerarrayparameters_wdims, cbf_get_realarrayparameters_wdims, cbf_set_integerarray_wdims, cbf_set_realarray_wdims, cbf_mpint_load_acc, cbf_mpint_store_acc, cbf_mpint_clear_acc, cbf_mpint_increment_acc, cbf_mpint_decrement_acc, cbf_mpint_negate_acc, cbf_mpint_add_acc, cbf_mpint_rightshift_acc, cbf_mpint_leftshift_acc. cbf_binary.h Update prototypes for cbf_get_bintext, cbf_set_bintext, cbf_set_binary, cbf_binary_parameters, cbf_get_binary to carry byteorder, dimensions and padding. cbf_byte_offset.h Update prototypes for cbf_compress_byte_offset, cbf_decompress_byte_offset to carry byteorder, dimensions and padding. cbf_canonical.h Update prototypes for cbf_compress_canonical, cbf_decompress_canonical to carry byteorder, dimensions and padding. cbf_codes.h Add prototypes for base 32K encoding: cbf_tobase32k, cbf_encode32k_bit_op, cbf_isBigEndian, cbf_endianFix, cbf_frombase32k, cbf_decode32k_bit_op. cbf_compress.h Update prototypes for cbf_compress, cbf_decompress to carry byteorder, dimensions and padding. cbf_packed.h Update prototypes for cbf_compress_packed, cbf_decompress_packed to carry byteorder, dimensions and padding. cbf_predictor.h Update prototypes for cbf_compress_predictor, cbf_decompress_predictor to carry byteorder, dimensions and padding. cbf_read_mime.h Update prototype for cbf_parse_mimeheader to carry byteorder, dimensions and padding. cbf_simple.h Add prototypes for cbf_get_3d_array_size, cbf_get_3d_array, cbf_get_3d_image_size, cbf_get_3d_image, cbf_get_map_array_id, cbf_get_map_segment_mask, cbf_get_map_segment_size, cbf_get_map_segment, cbf_get_real_3d_image, cbf_get_real_map_segment, cbf_get_real_map_segment_mask, cbf_set_3d_array, cbf_set_3d_image, cbf_set_map_segment, cbf_set_map_segment_mask, cbf_set_real_3d_image, cbf_set_real_map_segment, cbf_set_real_map_segment_mask. cbf_uncompressed.h Update prototypes for cbf_compress_none, cbf_decompress_none to carry byteorder, dimensions and padding. Makefile Update version and tests to work against data files in CBFlib_0.7.7_Data_Files. cbf.c Remove compiler warnings on signedness and type punned pointers. Fix bug in detection of local real format. Add base32K support. Fix inverted test in value range checking. Add new routines cbf_get_arrayparameters_wdims, cbf_get_integerarrayparameters_wdims, cbf_get_realarrayparameters_wdims, cbf_set_integerarray_wdims, cbf_set_realarray_wdims, cbf_mpint_load_acc, cbf_mpint_store_acc, cbf_mpint_clear_acc, cbf_mpint_increment_acc, cbf_mpint_decrement_acc, cbf_mpint_negate_acc, cbf_mpint_add_acc, cbf_mpint_rightshift_acc, cbf_mpint_leftshift_acc. cbf.stx.y Temporarily change to use of YYSTYPE argument type to remove an error when compiling under on MS Windows. A better solution is needed./ cbf_binary.c Update cbf_get_bintext, cbf_set_bintext, cbf_set_binary, cbf_binary_parameters, cbf_get_binary to carry byteorder, dimensions and padding. cbf_byte_offset.c Implement byte_offset compression and decompression as designed by A. Hammersley and modified by W. Kabsch. cbf_canonical.c Fix warnings from gcc 4 on punned pointers. Update cbf_compress_canonical, cbf_decompress_canonical to carry byteorder, dimensions and padding. cbf_codes.c Add support forr base 32K encoding: cbf_tobase32k, cbf_encode32k_bit_op, cbf_isBigEndian, cbf_endianFix, cbf_frombase32k, cbf_decode32k_bit_op. cbf_compress.c Update cbf_compress, cbf_decompress carry byteorder, dimensions and padding. cbf_file.c Fix warnings from gcc 4 on punned pointers. cbf_lex.c Add support for byteorder, dimensions and padding and base 32K encoding. cbf_packed.c Update cbf_compress_packed, cbf_decompress_packed to carry byteorder, dimensions and padding. Add support for J. P. Abrahams packed compression, versions 1 and 2, while preserving support for original CBFlib flat packed compression. Add support for 64 bit elements. cbf_predictor.c Update cbf_compress_predictor, cbf_decompress_predictor to carry byteorder, dimensions and padding. cbf_simple.c Change logic of most image handling routines to work as special cases of 3d routines. Add new routines cbf_get_detector_id, cbf_get_real_map_segment, cbf_get_real_map_segment_mask, cbf_set_map_segment, cbf_set_map_segment_mask, cbf_set_real_map_segment, cbf_set_real_map_segment_mask, cbf_get_3d_array_size, cbf_get_3d_array, cbf_set_3d_array, cbf_get_axis_reference_setting, cbf_set_axis_reference_setting, cbf_construct_reference_detector, cbf_require_reference_detector, cbf_set_reference_beam_center. cbf_read_mime.c Update cbf_parse_mimeheader to read MIME headers for new compression types and flags and byteorder, dimensions and padding. Add support for base 32K encoding. cbf_tree.c Fix warnings from gcc 4 on punned pointers. cbf_uncompressed.c Fix handling of 64-bit reads and writes. cbf_write_binary.c Add code to write out base-32K encoded sections, to write byte order, dimensions and padding. Add code to write out MIME headers for packed compressions or packed version 2 compression with flags for uncorrelated sections and for flat packed images. ---------------------------------------------------------------------- Release 0.7.6, Herbert J. Bernstein, 15 July 2006 Source File Change cbf.h Add include of stdio.h; change CBF_LINELENGTH into CBF_LINELENGTH_10 and CBF_LINELENGTH_11; add new symbols CBF_CASE_INSENSITIVE, CBF_CASE_SENSITIVE, CBF_LOGERROR, CBF_LOGWARNING, CBF_LOGWOLINE, CBF_LOGWOCOLUMN, CBF_LOGSTARTLOC, CBF_LOGCURRENTLOC; add information on input file and log file to cbf handle struct; and prototypes for cbf_read_widefile, cbf_write_local_file, cbf_write_widefile, cbf_column_number, cbf_blockitem_number, cbf_warning, cbf_error, cbf_log, cbf_increment_column, cbf_reset_column, cbf_reset_refcounts, cbf_validate; added valuerow argument to cbf_set_hashedvalue and caseinsensitive to cbf_find_hashedvalue. cbf.c In cbf_make_handle, added include of cbf_ascii.h, initialized handle->logfile, handle->warnings, handle->errors, handle->startline, handle->startcolumn; added new routine cbf_set_logfile; in cbf_free_handle removed gcc4 warning; broke up cbf_read_file into cbf_read_anyfile, cbf_read_file, added two more entries to parse array, one for the cbf handle and one to carry an auxillary node, such as a parent category; in cbf_write_file, reset reference counts; added new routine cbf_write_local_file to allow writing of a local portion of a cbf instead of the whole thing; added new routines cbf_column_number and cbf_blockitem_number; added new routine cbf_log to report parse errors with line numbers; fixed cbf_require_category when dealing with null datablocks; fixed cbf_require_column to preserve current row number; fixed inverted logic in cbf_require_dictionary; rewrote cbf_set_hashed_value to deal with insertions correctly; revised cbf_find_hashedvalue to survive commong errors; revised cbf_convert_dictionary_definition to recover category information properly and top deal with more complex loop-singleton interactions; added new routines cbf_increment_column, cbf_reset_column, cbf_reset_refcounts; updated cbf_convert_dictionary to align database with changes in cbf_convert_dictionary_definition and to distribute unspecified items from parents to children; fixed cbf_find_local_tag for DDL1 names and categories; updated cbf_find_category_root and cbf_require_category_root to allow for DDL1 categories drawn from dictionaries; changed cbf_find_tag_root and cbf_set_tag_root to use cbf_find_hashedvalue and cbf_set_hashedvalue; added routines cbf_check_category_tags, cbf_validate. cbf.stx.y To facilitate validation, changed save frame logic to append partial save frame to the base cif from the beginning instead of waiting for the end of the save frame; added cbf_validate calls at all levels and provided detailed parse form common errors with reports via cbf_log cbf_ascii.h Add prototype for cbf_foldtextline. cbf_ascii.c Added new routine cbf_foldtextline; in cbf_write_ascii changed logic to no longer backslash-quote individual embedded semicolons in text fields and to use full line-folding spec; cbf_canonical.c fixed gcc4 warning. cbf_cantext.c fixed gcc4 warnings. cbf_file.h Add columnlimit to strcut; add prototype for cbf_make_widefile. cbf_file.c In cbf_make_file added intialization of line length; added new routine cbf_make_widefile; in cbf_read_character do not increment column number at EOF; in cbf_read_line report lines over the limit cbf_lex.c Added lexical validation for line length, illegal characters, long data block names, long save frame names, failure to provide whitespace after loop_, unterminated quoted strings. cbf_packed.c Fix gcc4 warnings cbf_read_mime.c Pick up corrections to parse of types from work by GD for X-BASE32K. cbf_simple.h Add prototypes for cbf_get_bin_sizes, cbf_set_bin_sizes cbf_simple.c Changed cbf_read_template to use cbf_read_widefile; added new routines cbf_get_bin_sizes and cbf_set_bin_sizes; changed cbf_set_gain, cbf_set_overload, cbf_set_integration_time, cbf_set_datestamp, cbf_set_axis_setting to force in intervening categories and columns; in cbf_free_positioner, cbf_free_detector, fixed gcc4 warnings; revised cbf_set_beam_center to adjust the displacement rather than the offset. cbf_tree.h Add symbol for CBF_VALUE as a node type to use for validation; add prototype for cbf_find_last_typed_child. cbf_tree.c In cbf_free_node fixed gcc4 warning; added new routine cbf_find_last_typed_child; changed cbf_make_child to use cbf_find_last_typed_child instead of cbf_fid_last_child to avoid confusion between categories and save frames when the same name is used for both; changed cbf_compute_hashcode to return values between 0 and 255. cbf_write.d Add prototype for cbf_compose_itemname. cbf_write.c In cbf_set_value fold text fields that contain the text field terminator; add new routine cbf_compose_itemname, int cbf_write_itemname catch names that are too long; cif2cbf.c Add "-v dictionary" command line argument and suppress output to /dev/null and "-w" to process a wide file; add hooks (based on symbol GNUGETOPT) to use a local copy of getopt; add text for error exits; add code to load layered dictionaries. convert_image.c Add text for error exits; add logic for binning; alias support with command line arguments "-c category_alias=category_root" and "-t tag_alias=tag_root", change from _diffrn_detector.sample_detector_distance to _diffrn_measurement.sample_detector_distance; change to support row-major images to agree with adxv; remove most advisory messages to stdout. img.h Added rowmajor to struct; redefined img_pixel to be conditional on rowmajor; added img_pixelptr to get the pointers to the image. img.c Added recognition of ADSC QUANTUM315; added row major support img2cif.c Changed to use to new img.h macros makecbf.c Changed to use to new img.h macros ---------------------------------------------------------------------- Release 0.7.5, Herbert J. Bernstein, 15 April 2006 Source File Change cbf.c Revised header for open source licenses; added support for aliases, dictionaries and real arrays; added convenience routines to do searches with default creation of what is being searched for; added reference count and dictionary link for cbf handles; added cbf_new_saveframe, cbf_force_new_saveframe, cbf_set_saveframename, cbf_reset_saveframe, cbf_remove_saveframe, cbf_rewind_saveframe, cbf_rewind_blockitem, cbf_next_saveframe, cbf_next_blockitem, cbf_select_saveframe, cbf_select_blockitem, cbf_find_saveframe, cbf_require_row, cbf_require_nextrow, cbf_count_saveframes, cbf_count_blockitems, cbf_saveframe_name, cbf_require_value, cbf_require_integervalue, cbf_require_doublevalue, cbf_get_realarrayparameters, cbf_get_realarray, cbf_set_realarray, cbf_require_datablock, cbf_require_category, cbf_require_column, cbf_require_column_value, cbf_require_column_integervalue, cbf_require_column_doublevalue, cbf_get_local_integer_byte_order, cbf_get_local_real_byte_order, cbf_get_local_real_format, cbf_get_dictionary, cbf_set_dictionary, cbf_require_dictionary, cbf_set_hashedvalue, cbf_find_hashedvalue, cbf_convert_dictionary_definition, cbf_convert_dictionary, cbf_find_tag, cbf_find_local_tag, cbf_srch_tag, cbf_find_category_root, cbf_require_category_root, cbf_set_category_root, cbf_find_tag_root, cbf_require_tag_root, cbf_set_tag_root, cbf_find_tag_category, cbf_set_tag_category. cbf.h Revised header for open source licenses; added definitions of CBF_API_VERSION and CBF_DIC_VERSION; changed the debug versions of cbf_failnez and cbf_onfailnez to stringfy the argument; added dictionary and reference count to cbf_handle definition; added prototypes for cbf_new_saveframe, cbf_force_new_saveframe, cbf_set_saveframename, cbf_remove_saveframe, cbf_rewind_saveframe, cbf_rewind_blockitem, cbf_next_saveframe, cbf_next_blockitem, cbf_saveframe_name, cbf_select_saveframe, cbf_select_blockitem, cbf_find_saveframe, cbf_require_row, cbf_require_nextrow, cbf_count_saveframes, cbf_count_blockitems, cbf_require_value, cbf_require_integervalue, cbf_require_doublevalue, cbf_get_realarrayparameters, cbf_get_realarray, cbf_set_realarray, cbf_require_datablock, cbf_require_category, cbf_require_column, cbf_require_column_value, cbf_require_column_integervalue, cbf_require_column_doublevalue, cbf_get_local_integer_byte_order, cbf_get_local_real_byte_order, cbf_get_local_real_format, cbf_get_dictionary, cbf_set_dictionary, cbf_require_dictionary, cbf_set_hashedvalue, cbf_find_hashedvalue, cbf_convert_dictionary_definition, cbf_convert_dictionary, cbf_find_tag, cbf_find_local_tag, cbf_srch_tag, cbf_find_category_root, cbf_require_category_root, cbf_set_category_root, cbf_find_tag_root, cbf_require_tag_root, cbf_set_tag_root, cbf_find_tag_category, cbf_set_tag_category, cbf_alloc.c Revised header for open source licenses. cbf_alloc.h Revised header for open source licenses. cbf_ascii.c Revised header for open source licenses. cbf_ascii.h Revised header for open source licenses. cbf_binary.c Revised header for open source licenses; added support of real arrays. cbf_binary.h Revised header for open source licenses; added support of real arrays. cbf_byte_offset.c Revised header for open source licenses; changed signature for support of real arrays; no actual changes to the code. cbf_byte_offset.h Revised header for open source licenses; changed signature for support of real arrays; no actual changes to the code. cbf_canonical.c Revised header for open source licenses; changed signatures for support of real arrays; no actual changes to the code. cbf_canonical.h Revised header for open source licenses; changed signatures for support of real arrays; no actual changes to the code. cbf_codes.c Revised header for open source licenses. cbf_codes.h Revised header for open source licenses. cbf_compress.c Revised header for open source licenses; added support of real arrays. cbf_compress.h Revised header for open source licenses; added support of real arrays. cbf_context.c Revised header for open source licenses. cbf_context.h Revised header for open source licenses. cbf_file.c Revised header for open source licenses; added support of real arrays, making extensive changes to the handling of integers to get past 32 bit limits. cbf_file.h Revised header for open source licenses.. cbf_lex.c Revised header for open source licenses; added save frame support; required whitespace before a comment; changed WORD to CBFWORD; corrected quoted string parse to allow for a blank immediately after the opening quote mark. cbf_lex.h Revised header for open source licenses. cbf_packed.c Revised header for open source licenses; changed signatures for support of real arrays; no actual changes to the code. cbf_packed.h Revised header for open source licenses; changed signatures for support of real arrays; no actual changes to the code. cbf_predictor.c Revised header for open source licenses; changed signatures for support of real arrays; no actual changes to the code. cbf_predictor.h Revised header for open source licenses; changed signatures for support of real arrays; no actual changes to the code. cbf_read_binary.c Revised header for open source licenses. cbf_read_binary.h Revised header for open source licenses. cbf_read_mime.c Revised header for open source licenses; added support for real arrays. cbf_read_mime.h Revised header for open source licenses; added support for real arrays. cbf_simple.c Revised header for open source licenses; increased precision of all numbers to 15 digits; added support for cells and orientation matrices; built in support for diffrn_frame_data as an alternative to diffrn_data_frame; added new routines cbf_require_diffrn_id, cbf_get_pixel_size, cbf_set_pixel_size, cbf_get_real_image, cbf_set_real_image, int cbf_require_detector, cbf_set_beam_center, cbf_get_inferred_pixel_size, cbf_get_unit_cell, cbf_set_unit_cell, cbf_get_reciprocal_cell, cbf_set_reciprocal_cell, cbf_compute_cell_volume, cbf_compute_reciprocal_cell, cbf_get_orientation_matrix, cbf_set_orientation_matrix; added braces to deal with compiler warnings on dangling else. cbf_simple.h Revised header for open source licenses; added prototypes for cbf_require_diffrn_id, cbf_get_array_id, cbf_get_pixel_size, cbf_set_pixel_size, cbf_get_real_image, cbf_set_real_image, cbf_require_detector, cbf_set_beam_center, cbf_get_inferred_pixel_size, cbf_get_unit_cell, cbf_set_unit_cell, cbf_get_reciprocal_cell, cbf_set_reciprocal_cell, cbf_compute_cell_volume, cbf_compute_reciprocal_cell, cbf_get_orientation_matrix, cbf_set_orientation_matrix. cbf_string.c Revised header for open source licenses. cbf_string.h Revised header for open source licenses. cbf_stx.c Rebuilt from new cbf.stx.y. cbf_stx.h Changed WORD to CBFWORD; added SAVE and SAVEEND. cbf.stx.y Revised header for open source licenses; Revised grammar to support save frames and to be more comprehensible; changed name from cbf.stx cbf_tree.c Revised header for open source licenses; added code to support save frames, allowing typed searches for children; added new routines cbf_find_typed_child, cbf_count_typed_children, cbf_compute_hashcode. cbf_tree.c Revised header for open source licenses; added definition of CBF_SAVEFRAME as node type; added prototypes for cbf_find_typed_child, cbf_count_typed_children, cbf_compute_hashcode. cbf.uncompressed.c Revised header for open source licenses; Added support for real arrays, and to remove 32 bit limits. cbf.uncompressed.h Revised header for open source licenses; Added support for real arrays. cbf.write.c Revised header for open source licenses; added support for save frames and aliases; changed logic for single row categories to present item-by-item, instead of as a loop except for vectors and matrices, present matrices row by row; carried cbf handle through nest of calls. cbf.write.h Revised header for open source licenses; adjusted prototype of cbf_write_node to carry the cbf handle as the first argument. cbf.write_binary.c Revised header for open source licenses; added support for real arrays. cbf.write_binary.h Revised header for open source licenses. Makefile Revised header for open source licenses; defined C++; added symbol RANLIB for use on systems that require a ranlib pass after creating a library with ar; added build and tests of testcell and cif2c; added ADSC test case to tests of convert_image; updated list of contents of tar;changed cbf.stx to cbf.stx.y. connvert_image.c Revised header for open source licenses; added command line arguments for detector name, detector distance, rotation and reflection of the image; added usage report on errors; added code for axis transforms; added code to report image header fields; cleaned up PHI reporting; recovered pixel size and beam center from header; commented out most debug code. cif2cbf.c Revised header for open source licenses; renamed BUFSIZ as C2CBUFSIZ to remove a compiler warning; process save frames. img2cif.c Revised header for open source licenses; renamed BUFSIZ as I2CBUFSIZ to remove a compiler warning. testcell.C New program to test cell functions. cif2c.c New program to test cell functions. ---------------------------------------------------------------------- Release 0.7.4, Herbert J. Bernstein, 12 January 2004 Source File Change cbf.c added cbf_set_typeofvalue, cbf_get_typeofvalue; added braces for nested if-else to remove a compiler warning. cbf_ascii.c added braces to remove a compiler warnings. cbf_binary.c added braces to remove a compiler warnings. cbf_canonical.c added braces to remove a compiler warnings. cbf_compress.c added braces to remove a compiler warnings. cbf_file.c simplied dynamic array logic and went to straight doubling; added braces to remove a compiler warnings. cbf_lex.c changed parse of quoted strings to allow for embedded quote marks; removed unused variables; fixed mismatch of formats; added braces to remove a compiler warnings. cbf_packed.c added braces to remove a compiler warnings; intialized variables. cbf_simple.c typed default typed variable; removed unused variables; added braces to remove a compiler warnings; intialized variables. cbf_uncompressed.c added braces to remove a compiler warnings. cbf_write.c added internal functions cbf_get_value_type and cbf_set_value_type for typeofvalue functions; updated magic number and set magic number to match dictionary, not CBFlib version; initialized variable. cbf.h added new external typeofvalue function prototypes; added notices. cbf_write.h added new value_type function prototypes. cif2cbf.c added code to transfer typeofvalue from input to output to fix handling of nulls; increased buffer to 8192 and called it BUFSIZ; changed from tmpnam to mkstemp to remove warning; unlinked temporary file; added braces to remove compiler warnings. img2cif.c added code to transfer typeofvalue from input to output to fix handling of nulls; increased buffer to 8192 and called it BUFSIZ; changed from tmpnam to mkstemp to remove warning; unlinked temporary file; removed unused variables. ---------------------------------------------------------------------- Release 0.7.3, Paul J. Ellis, 2 October 2002 Source File Change cbf_simple.c modified cbf_get_image to reorder the image data on read so that the indices are always increasing in memory (this behavior was undefined previously). Note: Early versions of Release 0.7.3 carried the version number 0.7.2.3. Other than the change in number on 7 Nov 2002, there is no difference between these versions. ---------------------------------------------------------------------- Release 0.7.2.1, Paul J. Ellis, 7 May 2001 Source File Change cbf_simple.c corrected nesting in if statements introduced for the prior mod. ---------------------------------------------------------------------- Release 0.7.2, Herbert J. Bernstein, 22 April 2001 Source File Change cbf_simple.c changed _diffrn_measurement_axis.id (now deprecated) to _diffrn_measurement_axis.measurement_id and _diffrn_detector_axis.id (now deprecated) to _diffrn_detector_axis.detector_id, but allowed old forms as aliases. ---------------------------------------------------------------------- Release 0.7.1, Paul J. Ellis, 30 March 2001 Source File Change cbf_simple.c add reserved argument to various routines; in cbf_update_pixel use index2 instead of index1; add new routine cbf_get_pixel_normal; in cbf_get_pixel_area, shift by (-0.5,-0.5) ---------------------------------------------------------------------- Release 0.7.1, Paul J. Ellis, 13 March 2001 Source File Change cbf.c remove unused declaration of little. cbf.h add definitions of CBF_UNDEFINED and CBF_NOTIMPLEMENTED. cbf_binary.c cast type argument to (char) in cbf_copy-string call. cbf_compress.c remove unused declaration of compression_file. cbf_simple.c add this new routine for higher level calls. cbf_simple.h add this new header for higher level calls. cbf_uncompressed.c remove unused declaration of bit. ---------------------------------------------------------------------- Release 0.6.1, H. Powell (per Herbert J. Bernstein), 23 February 2001 Source File Change cbf.c fix memory leak as corrected by H. Powell ---------------------------------------------------------------------- Release 0.6, Herbert J. Bernstein, 13 January 1999 Source File Change cbf.c remove argument repeat from cbf_set_integerarray cbf.h remove argument repeat from cbf_set_integerarray cbf_binary.h carry compression id in text as argument to cbf_get/set_bintext, remove repeat as argument to cbf_set_binary cbf_binary.c carry compression id in text, rather than header, as an argument to cbf_get/set_bintext, remove repeat as argument to cbf_set_binary cbf_byte_offset.h remove argument repeat from cbf_compress_byte_offset cbf_byte_offset.c remove argument repeat from cbf_compress_byte_offset cbf_canonical. remove argument repeat from cbf_compress_canonical cbf_canonical.c remove argument repeat from cbf_compress_canonical cbf_compress.h remove argument repeat from cbf_compress, change argument compression from pointer to value in cbf_decompress_parameters cbf_compress.c remove argument repeat from cbf_compress, use compression as an input argument in cbf_decompress_parameters, do not write compression id cbf_file.c tune buffer size allocations to current size cbf_lex.c carry compression in text, not header, suppress binary header when there is a MIME header cbf_packed.h remove argument repeat from cbf_compress_packed cbf_packed.c remove argument repeat from cbf_compress_packed cbf_predictor.h remove argument repeat from cbf_compress_predictor cbf_predictor.c remove argument repeat from cbf_compress_predictor cbf_read_binary.h make pointer to compression an argument to cbf_parse_binaryheader cbf_read_binary.c carry compression in text, not header, suppress binary header when there is a MIME header cbf_read_mime.h add prototype for cbf_nblen cbf_read_mime.c carry compression in text, not header, suppress binary header when there is a MIME header, allow trailing blanks on header lines, test for early terminations, allow arbitrary spacing on element type, add cbf_nblen cbf_stx.c rebuilt from cbf.stx with bison 1.25 cbf_tree.c tune allocation of memory for extra children to current use levels cbf_uncompressed.h remove argument repeat from cbf_compress_none cbf_uncompressed.c remove argument repeat from cbf_compress_none cbf_write.c update version numbers in file headers cbf_write_binary.c carry compression in text, not header, suppress binary header when there is a MIME header, quote X-Binary-Element-Type ---------------------------------------------------------------------- Release 0.5, Paul J. Ellis, 5 December 1998 Source File Change cbf.c Add option for immediate digest evaluation (MSG_DIGESTNOW) or deferred digest evaluation (MSG_DIGEST); adjust layout of error messages; remove unused repeat. cbf.stx Add new argument for cbf_set_columnrow. cbf_ascii.c Add buffer flush. cbf_binary.c Add call to cbf_codes.h; convert to use of cbf_get/set_bintext; digests saved in the text for deferred evaluation. cbf_byte_offset.c Add storedbits argument on compression; remove repeat on decompression. cbf_canonical.c Stylistic cleanup; add storedbits argument on compression; remove repeat on decompression. cbf_codes.c Add routines cbf_is_base64digest, cbf_md5digest_to64, flush buffers when done, general cleanup cbf_compress.c Add argument bits to cbf_compress and each actual compression routine, add bits and remove repeat on decompression. cbf_file.c Reorganize digest logic; remove nblen argument from cbf_read_line. cbf_lex.c Argument type and stylisic cleanup; allow for deferred digest evaluation, adjust binary size to agree with MIME size. cbf_packed.c Stylistic cleanup; add storedbits argument on compression; remove repeat on decompression. cbf_predictor.c Add storedbits argument on compression; remove repeat on decompression. cbf_read_mime.c Add binary element type logic; cleanup header scan; allow for deferred digest evaluation. cbf_tree.c Add argument free to cbf_set_columnrow. If free is true, free the old value, otherwise a user responsibility. cbf_uncompressed.c Add storedbits argument on compression; remove repeat on decompression. cbf_write.c Add buffer flush. cbf_write_binary.c Reorganize digest calculation, adjust binary size by 8, add X-Binary-E;ement-Type. global.h Change definition of UINT4 from unsigned long int to unsigned int. md5.c Mask 32 bits for longer words. ---------------------------------------------------------------------- Release 0.4, Herbert J. Bernstein, 15 November 1998 Source File Change cbf_stx.c rebuilt from cbf.stx with bison 1.25 cbf_binary.c add digest, elsize, elsign to text cbf_canonical.c remove write of compression id cbf_codes.h add argument *digest to cbf_fromqp, cbf_frombase64, cbf_frombasex cbf_codes.c add mpack notice, add cbf_md5context_to64, add digest to cbf_from... cbf_compress.h add argument *digest to cbf_compress cbf_compress.c add digest to cbf_compress cbf_file.h add nscolumn, digest_buffer, digest_bpoint, context to cbf_file struct, add argument *nblen to cbf_read_line cbf_file.c add file->nscolumn, file->digest_buffer, file->digest_bpoint, update digest when writing cbf_lex.c add notices, compute digests on intial read cbf_packed.c do not write compression id cbf_read_mime.h add prototype for cbf_skip_whitespace, add argument *compression to cbf_parse_mimeheader cbf_read_mime.c add notices, remove redundant digest calculation, adjust handling of compression id, add cbf_skip_whitespace, have cbf_parse_mimeheader return compression id, add checks for garbled files, allow more general headers cbf_uncompressed.c make uncompressed section free of headers cbf_write.c update version in headers cbf_write_binary.c carry digest, elsize, elsign in text rather than header ---------------------------------------------------------------------- Release 0.3.1.1, Paul J. Ellis, 21 September 1998 Source File Change cbf.h remove globals, add tolen CBF_TOKEN_MIME_BIN, change MIME_NOHEADERS to PLAIN_HEADERS, add HDR_DEFAULT, add arguments ciforcbf, headers, encoding to cbf_write_file, add argument headers to cbf_read_file, restore const in several places, merge int cbf_get_integerarrayparams into cbf_get_integerarrayparameters cbf.c add notices, add argument headers to cbf_read_file to replace use of globals in release 0.2, add arguments ciforcbf, headers, encoding to cbf_write_file to replace use of globals in release 0.2, restore some uses of const, remove integerarrayparams and merge arguments into cbf_get_integerparameters, replace cbf_binary_params with cbf_binary_parameters with extended argument list cbf.stx add notices, remove gcc use of malloc, define alloca(x) as NULL, and set large inital depth, adopts mods from cbf.stx.y in release 0.2 cbf_alloc.c add notices cbf_ascii.c change use of range of token values to explicit symbolic tokens cbf_binary.h merge cbf_binary_params into cbf_binary_parameters, remove cbf_write_binary cbf_binary.c add cbf_read_mime.h, and CBF_TOKEN_MIME_BIN token, use cbf_set/get_fileposition, merge cbf_binary_params into cbf_binary_parameters, restore some uses of const, use cbf_decompress_parameters with extended argument list, use cbf_mime_temp, move cbf_write_binary to its own file. cbf_canonical.h add argument binsize to cbf_compress_canonical, add argument repeat to cbf_decompress_canonical cbf_canonical.c add notices, remove binbitcount, handle binsize as an argument cbf_codes.h new header cbf_codes.c revise notices, major cleanup. cbf_compress.c add notices, add compressedsize argument, add repeat to decompression calls cbf_context.c add notices cbf_compress.h add argument compressedsize to cbf_compress, repeat to cbf_decompress cbf_file.h map "text..." to "buffer..." in cbf_file, remove CBFbytedir, change cbf_set_textsize to cbf_set_buffersize, add cbf_reset_buffer, add cbf_get_buffer, change cbf_get/put_text to cbf_get/put_block, add cbf_get/set_position cbf_file.c add notices, change file->text to file->buffer, file->text_size to file->buffer_size, file->text_used to file->buffer_used, file->read_headers, file->write_headers, file->write_encoding, remove file->fpos, file->fend, add cbf_get/set_fileposition cbf_lex.c read by buffers, move MIME processing later in the flow cbf_packed.h add compressedsize argument to cbf-compress-packed, repeat to cbf_decompress_packed, remove ..none, ..byte_off, ..predict cbf_packed.c add notices, add bitcount argument to cbf_pack_chunk cbf_predictor.h new header cbf_predictor.c New routine cbf_read_binary.h new header cbf_read_binary.c New routine cbf_read_mime.h new header cbf_string.h new header cbf_string.c New routine, replacing string.c cbf_stx.c Rebuild of cbf.stx with bison A2.6 cbf_tree.h remove CBF_INDEX, cbf_init_index, cbf_add_index, cleanup, add const cbf_tree.c add notices, general cleanup, restore const, remove cbf_init_index, cbf_add_index cbf_uncompressed.h new header cbf_uncompressed.c New routine cbf_write.c add notices, change tests for "?" and ".", change range test on tokens to explicit list cbf_write_binary.h new header cbf_write_binary.c New routine global.h new routine with part of md5.h md5c.c use global.h md5.h move portion of this header to global.h, from whence it came ---------------------------------------------------------------------- Release 0.2, Herbert J. Bernstein, 27 August 1998 Source File Change cbf.h Define CBF and CIF, add cbf_force_new_datablock, cbf_force_new_category, remove some uses of const, add, cbf_get_integerarrayparams, add globals CBForCIF, CIFCRterm, CIFNLterm, CBFbinsize, CBFmime, CBFdigest, CBFencoding, CBFelsize, CBFbytedir cbf.c Define CBF and CIF, add cbf_force_new_datablock, cbf_force_new_category, remove some uses of const, add, cbf_get_integerarrayparams, add globals CBForCIF, CIFCRterm, CIFNLterm, CBFbinsize, CBFmime, CBFdigest, CBFencoding, CBFelsize, CBFbytedir cbf.stx Add malloc.h when using gcc cbf.stx.y Version of cbf.stx with changes to allow DDL1 cbf_ascii.c Use symbols for tokens cbf_binary.h Add cbf_binary_params cbf_binary.c Add digest logic, change file position tracking cbf_canonical.c Make writing repeat consistent; track binbitcount add cbf_binary_params, use cbf_decompress_params; allow MIME header cbf_codes.c New routine adapted from mpack cbf_compress.h Add cbf_decompress_params cbf_compress.c Add hooks for CBF_NONE, CBF_BYTE_OFFSET, CBF_PREDICTOR, add cbf_decompress_params cbf_context.h Remove const from cbf_copy_string cbf_context.c Remove const from cbf_copy_string cbf_decode.c New routine adapted from mpack cbf_file.h Add files to record file position cbf_file.c Track file position; allow writing CIFs and CBFs cbf_lex.c Add mime processing; add DDL1 support; process "." cbf_mime.c New routine cbf_packed.h Add cbf_compress_none, cbf_decompress_none, cbf_compress_byte_off, cbf_decompress_byte_off, cbf_compress_predict, cbf_decompress_predict cbf_packed.c Add cbf_compress_none, cbf_decompress_none, dummy cbf_compress_byte_off, dummy cbf_decompress_byte_off, dummy cbf_compress_predict, dummy cbf_decompress_predict; ensure consistent writing of repeat cbf_part.h New header adapted from mpack cbf_part.c New routine adapted from pack cbf_stx.c rebuilt with correct bison parser from cbf.stx.y cbf_tree.c added cbf_make_new_node, cbf_find_last_child, cbf_name_new_node, cbf_add_new_child, cbf_make_new_child, cbf_init_index, cbf_add_index; report CBF_ARGUMENT for cbf_make_child for type CBF_LINK; removed some uses of const cbf_write.c Added symbols for parse tokens; recognize "."; adjusted file header line to conform to documentation; removed some uses of const cif2cbf.c New program common.h New header from mpack img2cif.c New program makecbf.c Add local_exit and change cbf_failnez to facilitate debugging, add _array_intensities.binary_id, _array_data.binary.id md5.h New header from mpack md5c.c New routine from mpack string.c New routine from mpack uudecode.c New routine from mpack ---------------------------------------------------------------------- Release 0.1, Paul J. Ellis, 17 April 1998 This was the first CBFlib release. It supported binary CBF files using binary strings. ---------------------------------------------------------------------- ---------------------------------------------------------------------- Updated 13 February 2011. yaya at bernstein-plus-sons dot com ./CBFlib-0.9.2.2/doc/Idiffrn_detector.type.html0000644000076500007650000000503211603702115017463 0ustar yayayaya (IUCr) CIF Definition save__diffrn_detector.type

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_detector.type

    Name:
    '_diffrn_detector.type'

    Definition:

            The make, model or name of the detector device used.
    
    

    Type: text

    Mandatory item: no

    Alias:
    _diffrn_detector_type (cif_core.dic version 2.0.1)

    Category: diffrn_detector

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/cif_img_1_3_2.html0000777000076500007650000000000011603751102020512 2cif_img_1.3.2.htmlustar yayayaya./CBFlib-0.9.2.2/doc/Imap.id.html0000644000076500007650000000505611603702115014520 0ustar yayayaya (IUCr) CIF Definition save__map.id

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _map.id

    Name:
    '_map.id'

    Definition:

           The value of _map.id must uniquely identify
                  each map for the given diffrn.id or entry.id.
    
    

    Type: code

    Mandatory item: yes

    _map_segment.id

    Category: map

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Iarray_structure_list_axis.angle_increment.html0000644000076500007650000000563211603702115024016 0ustar yayayaya (IUCr) CIF Definition save__array_structure_list_axis.angle_increment

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _array_structure_list_axis.angle_increment

    Name:
    '_array_structure_list_axis.angle_increment'

    Definition:

            The pixel-centre-to-pixel-centre increment in the angular
                   setting of the specified axis in degrees.  This is not
                   meaningful in the case of 'constant velocity' spiral scans
                   and should not be specified for this case.
    
                   See _array_structure_list_axis.angular_pitch.
    
    
    

    Type: float

    Mandatory item: no


    Enumeration default: 0.0

    Category: array_structure_list_axis

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Cdiffrn_radiation.html0000644000076500007650000000754111603702115016645 0ustar yayayaya (IUCr) CIF Definition save_diffrn_radiation

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    Category DIFFRN_RADIATION

    Name:
    'diffrn_radiation'

    Description:

            Data items in the DIFFRN_RADIATION category describe
                   the radiation used for measuring diffraction intensities,
                   its collimation and monochromatization before the sample.
    
                   Post-sample treatment of the beam is described by data
                   items in the DIFFRN_DETECTOR category.
    
    
    Examples:

    Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP
     
        _diffrn_radiation.diffrn_id            'set1'
    
        _diffrn_radiation.collimation          '0.3 mm double pinhole'
        _diffrn_radiation.monochromator        'graphite'
        _diffrn_radiation.type                 'Cu K\a'
        _diffrn_radiation.wavelength_id         1
    
    


    Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277].
     
        _diffrn_radiation.wavelength_id    1
        _diffrn_radiation.type             'Cu K\a'
        _diffrn_radiation.monochromator    'graphite'
    
    


    Category groups:
        inclusive_group
        diffrn_group
    Category key:
        _diffrn_radiation.diffrn_id

    Mandatory category: no

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_scan_axis.reference_angle.html0000644000076500007650000000645511603702115021757 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan_axis.reference_angle

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_scan_axis.reference_angle

    Name:
    '_diffrn_scan_axis.reference_angle'

    Definition:

            The setting of the specified axis in degrees
                   against which measurements of the reference beam center
                   and reference detector distance should be made.
    
                   In general, this will agree with
                   _diffrn_scan_frame_axis.reference_angle.
    
                   If the individual frame values vary, then the value of
                   _diffrn_scan_axis.reference_angle will be
                   representative of the ensemble of values of
                   _diffrn_scan_frame_axis.reference_angle (e.g.
                   the mean).
    
                   If not specified, the value defaults to zero.
    
    

    Type: float

    Mandatory item: implicit


    Enumeration default: 0.0

    Category: diffrn_scan_axis

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_scan_axis.angle_range.html0000644000076500007650000000505011603702115021103 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan_axis.angle_range

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_scan_axis.angle_range

    Name:
    '_diffrn_scan_axis.angle_range'

    Definition:

            The range from the starting position for the specified axis
                   in degrees.
    
    

    Type: float

    Mandatory item: no


    Enumeration default: 0.0

    Category: diffrn_scan_axis

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/.symlinks0000755000076500007650000001257111603750276014241 0ustar yayayaya#!/bin/sh ###################################################################### # # # .symlinks for CBFlib/doc directory # # # # originally a csh script by H. J. Bernstein # # converted to sh by J. Wright, 12 Jun 2007 # # # # Version 0.9.2.2 2 Jul 2011 # # # # Paul Ellis and # # Herbert J. Bernstein (yaya@bernstein-plus-sons.com) # # # # (C) Copyright 2006 - 2011 Herbert J. Bernstein # # # ###################################################################### ###################################################################### # # # YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL # # # # ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS # # OF THE LGPL # # # ###################################################################### ########################### GPL NOTICES ############################## # # # This program is free software; you can redistribute it and/or # # modify it under the terms of the GNU General Public License as # # published by the Free Software Foundation; either version 2 of # # (the License, or (at your option) any later version. # # # # This program is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # # GNU General Public License for more details. # # # # You should have received a copy of the GNU General Public License # # along with this program; if not, write to the Free Software # # Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA # # 02111-1307 USA # # # ###################################################################### ######################### LGPL NOTICES ############################### # # # This library is free software; you can redistribute it and/or # # modify it under the terms of the GNU Lesser General Public # # License as published by the Free Software Foundation; either # # version 2.1 of the License, or (at your option) any later version. # # # # This library is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # # Lesser General Public License for more details. # # # # You should have received a copy of the GNU Lesser General Public # # License along with this library; if not, write to the Free # # Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, # # MA 02110-1301 USA # # # ###################################################################### # Usage ./.symlinks [--use_cp] if [ ${1:-NOARG} = "--use_cp" ] ; then LN="cp -p" else LN="ln -s" fi if [ ! -e cif_img.dic ] ; then $LN cif_img_1.6.4_2Jul11.dic cif_img.dic fi if [ ! -e cif_img.html ] ; then $LN cif_img_1.6.4_2Jul11.html cif_img.html fi if [ ! -e cif_img_1.6.3.html ] ; then $LN cif_img_1.6.3_26Aug10.html cif_img_1.6.3.html fi if [ ! -e cif_img_1.6.html ] ; then $LN cif_img_1.6.3_26Aug10.html cif_img_1.6.html fi if [ ! -e cif_img_1_3_2.html ] ; then $LN cif_img_1.3.2.html cif_img_1_3_2.html fi if [ ! -e cif_img_1.5.dic ] ; then $LN cif_img_1.5.4_28Jul07.dic cif_img_1.5.dic fi if [ ! -e cif_img_1.5.html ] ; then $LN cif_img_1.5.4_28Jul07.html cif_img_1.5.html fi if [ ! -e cif_img_1.5.4.html ] ; then $LN cif_img_1.5.4_28Jul07.html cif_img_1.5.4.html fi if [ ! -e cif_img_1.6.dic ] ; then $LN cif_img_1.6.4_2Jul11.dic cif_img_1.6.dic fi if [ ! -e cif_img_1.6.4.dic ] ; then $LN cif_img_1.6.4_2Jul11.dic cif_img_1.6.4.dic fi if [ ! -e cif_img_1.6.html ] ; then $LN cif_img_1.6.4_2Jul11.html cif_img_1.6.html fi if [ ! -e cif_img_1.6.4.html ] ; then $LN cif_img_1.6.4_2Jul11.html cif_img_1.6.4.html fi for file in * do if [ -d "$file" ] ; then if [ -e "$file/.symlinks" ] ; then (cd "$file"; sh -c "./.symlinks $1") fi fi done ./CBFlib-0.9.2.2/doc/Imap_segment.details.html0000644000076500007650000000541111603702115017266 0ustar yayayaya (IUCr) CIF Definition save__map_segment.details

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _map_segment.details

    Name:
    '_map_segment.details'

    Definition:

            The value of _map_segment.details should give a
                   description of special aspects of each segment of a map.
    
    
    
    Example:

    '               Example to be provided'

    Type: text

    Mandatory item: no

    Category: map_segment

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_scan_axis.displacement_range.html0000644000076500007650000000510111603702115022462 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan_axis.displacement_range

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_scan_axis.displacement_range

    Name:
    '_diffrn_scan_axis.displacement_range'

    Definition:

            The range from the starting position for the specified axis
                   in millimetres.
    
    

    Type: float

    Mandatory item: no


    Enumeration default: 0.0

    Category: diffrn_scan_axis

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_measurement.sample_detector_voffset.html0000644000076500007650000000553311603702115024132 0ustar yayayaya (IUCr) CIF Definition save__diffrn_measurement.sample_detector_voffset

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_measurement.sample_detector_voffset

    Name:
    '_diffrn_measurement.sample_detector_voffset'

    Definition:

            The value of _diffrn_measurement.sample_detector_voffset gives
                   the signed distance in millimetres in the vertical
                   direction (positive for up) from the center of
                   the beam to the center of the detector.
    
    

    Type: float

    Mandatory item: no


    The permitted range is (-infinity, infinity)

    Category: diffrn_measurement

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Caxis.html0000644000076500007650000005045411603702115014310 0ustar yayayaya (IUCr) CIF Definition save_axis

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    Category AXIS

    Name:
    'axis'

    Description:

        Data items in the AXIS category record the information required
         to describe the various goniometer, detector, source and other
         axes needed to specify a data collection or the axes defining the
         coordinate system of an image.
    
         The location of each axis is specified by two vectors: the axis
         itself, given by a  unit vector in the direction of the axis, and
         an offset to the base of the unit vector.
    
         The vectors defining an axis are referenced to an appropriate
         coordinate system.  The axis vector, itself, is a dimensionless
         unit vector.  Where meaningful, the offset vector is given in
         millimetres.  In coordinate systems not measured in metres,
         the offset is not specified and is taken as zero.
    
         The available coordinate systems are:
    
             The imgCIF standard laboratory coordinate system
             The direct lattice (fractional atomic coordinates)
             The orthogonal Cartesian coordinate system (real space)
             The reciprocal lattice
             An abstract orthogonal Cartesian coordinate frame
    
         For consistency in this discussion, we call the three coordinate
         system axes X, Y and Z.  This is appropriate for the imgCIF
         standard laboratory coordinate system, and last two Cartesian
         coordinate systems, but for the direct lattice, X corresponds
         to a, Y to b and Z to c, while for the reciprocal lattice,
         X corresponds to a*, Y to b* and Z to c*.
    
         For purposes of visualization, all the coordinate systems are
         taken as right-handed, i.e., using the convention that the extended
         thumb of a right hand could point along the first (X) axis, the
         straightened pointer finger could point along the second (Y) axis
         and the middle finger folded inward could point along the third (Z)
         axis.
    
         THE IMGCIF STANDARD LABORATORY COORDINATE SYSTEM
    
         The imgCIF standard laboratory coordinate system is a right-handed
         orthogonal coordinate similar to the MOSFLM coordinate system,
         but imgCIF puts Z along the X-ray beam, rather than putting X along the
         X-ray beam as in MOSFLM.
    
         The vectors for the imgCIF standard laboratory coordinate system
         form a right-handed Cartesian coordinate system with its origin
         in the sample or specimen.  The origin of the axis system should,
         if possible, be defined in terms of mechanically stable axes to be
         be both in the sample and in the beam.  If the sample goniometer or other
         sample positioner has two axes the intersection of which defines a
         unique point at which the sample should be mounted to be bathed
         by the beam, that will be the origin of the axis system.  If no such
         point is defined, then the midpoint of the line of intersection
         between the sample and the center of the beam will define the origin.
         For this definition the sample positioning system will be set at
         its initial reference position for the experiment.
    
    
                                 | Y (to complete right-handed system)
                                 |
                                 |
                                 |
                                 |
                                 |
                                 |________________X
                                /       principal goniometer axis
                               /
                              /
                             /
                            /
                           /Z (to source)
    
    
    
    
         Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from
         the sample or specimen along the  principal axis of the goniometer or
         sample positioning system if the sample positioning system has an axis
         that intersects the origin and which form an angle of more than 22.5
         degrees with the beam axis.
    
         Axis 2 (Y): The Y-axis completes an orthogonal right-handed system
         defined by the X-axis and the Z-axis (see below).
    
         Axis 3 (Z): The Z-axis is derived from the source axis which goes from
         the sample to the source.  The Z-axis is the component of the source axis
         in the direction of the source orthogonal to the X-axis in the plane
         defined by the X-axis and the source axis.
    
         If the conditions for the X-axis can be met, the coordinate system
         will be based on the goniometer or other sample positioning system
         and the beam and not on the orientation of the detector, gravity etc.
         The vectors necessary to specify all other axes are given by sets of
         three components in the order (X, Y, Z).
         If the axis involved is a rotation axis, it is right-handed, i.e. as
         one views the object to be rotated from the origin (the tail) of the
         unit vector, the rotation is clockwise.  If a translation axis is
         specified, the direction of the unit vector specifies the sense of
         positive translation.
    
         Note:  This choice of coordinate system is similar to but significantly
         different from the choice in MOSFLM (Leslie & Powell, 2004).  In MOSFLM,
         X is along the X-ray beam (the CBF/imgCIF Z axis) and Z is along the
         rotation axis.
    
         In some experimental techniques, there is no goniometer or the principal
         axis of the goniometer is at a small acute angle with respect to
         the source axis.  In such cases, other reference axes are needed
         to define a useful coordinate system.  The order of priority in
         defining directions in such cases is to use the detector, then
         gravity, then north.
    
    
         If the X-axis cannot be defined as above, then the
         direction (not the origin) of the X-axis should be parallel to the axis
         of the primary detector element corresponding to the most rapidly
         varying dimension of that detector element's data array, with its
         positive sense corresponding to increasing values of the index for
         that dimension.  If the detector is such that such a direction cannot
         be defined (as with a point detector) or that direction forms an
         angle of less than 22.5 degrees with respect to the source axis, then
         the X-axis should be chosen so that if the Y-axis is chosen
         in the direction of gravity, and the Z-axis is chosen to be along
         the source axis, a right-handed orthogonal coordinate system is chosen.
         In the case of a vertical source axis, as a last resort, the
         X-axis should be chosen to point North.
    
         All rotations are given in degrees and all translations are given in mm.
    
         Axes may be dependent on one another.  The X-axis is the only goniometer
         axis the direction of which is strictly connected to the hardware.  All
         other axes are specified by the positions they would assume when the
         axes upon which they depend are at their zero points.
    
         When specifying detector axes, the axis is given to the beam centre.
         The location of the beam centre on the detector should be given in the
         DIFFRN_DETECTOR category in distortion-corrected millimetres from
         the (0,0) corner of the detector.
    
         It should be noted that many different origins arise in the definition
         of an experiment.  In particular, as noted above, it is necessary to
         specify the location of the beam centre on the detector in terms
         of the origin of the detector, which is, of course, not coincident
         with the centre of the sample.
    
         The unit cell, reciprocal cell and crystallographic orthogonal
         Cartesian coordinate system are defined by the CELL and the matrices
         in the ATOM_SITES category.
    
         THE DIRECT LATTICE (FRACTIONAL COORDINATES)
    
         The direct lattice coordinate system is a system of fractional
         coordinates aligned to the crystal, rather than to the laboratory.
         This is a natural coordinate system for maps and atomic coordinates.
         It is the simplest coordinate system in which to apply symmetry.
         The axes are determined by the cell edges, and are not necessarily
         othogonal.  This coordinate system is not uniquely defined and
         depends on the cell parameters in the CELL category and the
         settings chosen to index the crystal.
    
         Molecules in a crystal studied by X-ray diffracraction are organized
         into a repeating regular array of unit cells.  Each unit cell is defined
         by three vectors, a, b and c.  To quote from Drenth,
    
    
         "The choice of the unit cell is not unique and therefore, guidelines
         have been established for selecting the standard basis vectors and
         the origin.  They are based on symmetry and metric considerations:
    
          "(1)  The axial system should be right handed.
           (2)  The basis vectors should coincide as much as possible with
           directions of highest symmetry."
           (3)  The cell taken should be the smallest one that satisfies
           condition (2)
           (4)  Of all the lattice vectors, none is shorter than a.
           (5)  Of those not directed along a, none is shorter than b.
           (6)  Of those not lying in the ab plane, none is shorter than c.
           (7)  The three angles between the basis vectors a, b and c are
           either all acute (<90\%) or all obtuse (>=90\%)."
    
         These rules do not produce a unique result that is stable under
         the assumption of experimental errors, and the the resulting cell
         may not be primitive.
    
         In this coordinate system, the vector (.5, .5, .5) is in the middle
         of the given unit cell.
    
         Grid coordinates are an important variation on fractional coordinates
         used when working with maps.  In imgCIF, the conversion from
         fractional to grid coordinates is implicit in the array indexing
         specified by _array_structure_list.dimension.  Note that this
         implicit grid-coordinate scheme is 1-based, not zero-based, i.e.
         the origin of the cell for axes along the cell edges with no
         specified _array_structure_list_axis.displacement will have
         grid coordinates of (1,1,1), i.e. array indices of (1,1,1).
    
         THE ORTHOGONAL CARTESIAN COORDINATE SYSTEM (REAL SPACE)
    
         The orthogonal Cartesian coordinate system is a transformation of
         the direct lattice to the actual physical coordinates of atoms in
         space.  It is similar to the laboratory coordinate system, but
         is anchored to and moves with the crystal, rather than being
         schored to the laboratory.  The transformation from fractional
         to orthogonal cartesian coordinates is given by the
                  _atom_sites.Cartn_transf_matrix[i][j]  and
                  _atom_sites.Cartn_transf_vector[i]
         tags.  A common choice for the matrix of the transformation is
         given in the 1992 PDB format document
    
                  | a      b cos(\g)   c cos(\b)                            |
                  | 0      b sin(\g)   c (cos(\a) - cos(\b)cos(\g))/sin(\g) |
                  | 0      0           V/(a b sin(\g))                      |
    
         This is a convenient coordinate system in which to do fitting
         of models to maps and in which to understand the chemistry of
         a molecule.
    
         THE RECIPROCAL LATTICE
    
         The reciprocal lattice coordinate system is used for diffraction
         intensitities.  It is based on the reciprocal cell, the dual of the cell,
         in which reciprocal cell edges are derived from direct cell faces:
    
            a* = bc sin(\a)/V  b* = ac sin(\b)/V  c* = ab sin(\g)/V
            cos(\a*) = (cos(\b) cos(\g) - cos(\a))/(sin(\b)  sin(\g))
            cos(\b*) = (cos(\a) cos(\g) - cos(\b))/(sin(\a) sin(\g))
            cos(\g*) = (cos(\a) cos(\b) - cos(\g))/(sin(\a) sin(\b))
            V = abc  SQRT(1 - cos(\a)^2^
                            - cos(\b)^2^
                            - cos(\g)^2^
                            + 2 cos(\a) cos(\b) cos(\g) )
    
         In this form the dimensions of the reciprocal lattice are in reciprocal
         \%Angstroms (\%A^-1^).  A dimensionless form can be obtained by
         multiplying by the wavelength.  Reflections are commonly indexed against
         this coordinate system as (h, k, l) triples.
    
    
         References:
    
         Drenth, J., "Introduction to basic crystallography." chapter
         2.1 in Rossmann, M. G. and Arnold, E. "Crystallography of
         biological macromolecules", Volume F of the IUCr's "International
         tables for crystallography", Kluwer, Dordrecht 2001, pp 44 -- 63
    
         Leslie, A. G. W. and Powell, H. (2004). MOSFLM v6.11.
         MRC Laboratory of Molecular Biology, Hills Road, Cambridge, England.
         http://www.CCP4.ac.uk/dist/X-windows/Mosflm/.
    
         Stout, G. H. and Jensen, L. H., "X-ray structure determination",
         2nd ed., Wiley, New York, 1989, 453 pp.
    
         __, "PROTEIN DATA BANK ATOMIC COORDINATE AND BIBLIOGRAPHIC ENTRY
         FORMAT DESCRIPTION," Brookhaven National Laboratory, February 1992.
    
    
    Examples:

    Example 1 - This example shows the axis specification of the axes of a kappa- geometry goniometer [see Stout, G. H. & Jensen, L. H. (1989). X-ray structure determination. A practical guide, 2nd ed. p. 134. New York: Wiley Interscience]. There are three axes specified, and no offsets. The outermost axis, omega, is pointed along the X axis. The next innermost axis, kappa, is at a 50 degree angle to the X axis, pointed away from the source. The innermost axis, phi, aligns with the X axis when omega and phi are at their zero points. If T-omega, T-kappa and T-phi are the transformation matrices derived from the axis settings, the complete transformation would be: X' = (T-omega) (T-kappa) (T-phi) X
     
             loop_
            _axis.id
            _axis.type
            _axis.equipment
            _axis.depends_on
            _axis.vector[1] _axis.vector[2] _axis.vector[3]
            omega rotation goniometer     .    1        0        0
            kappa rotation goniometer omega    -.64279  0       -.76604
            phi   rotation goniometer kappa    1        0        0
    
    


    Example 2 - This example shows the axis specification of the axes of a detector, source and gravity. The order has been changed as a reminder that the ordering of presentation of tokens is not significant. The centre of rotation of the detector has been taken to be 68 millimetres in the direction away from the source.
     
            loop_
            _axis.id
            _axis.type
            _axis.equipment
            _axis.depends_on
            _axis.vector[1] _axis.vector[2] _axis.vector[3]
            _axis.offset[1] _axis.offset[2] _axis.offset[3]
            source       .        source     .       0     0     1   . . .
            gravity      .        gravity    .       0    -1     0   . . .
            tranz     translation detector rotz      0     0     1   0 0 -68
            twotheta  rotation    detector   .       1     0     0   . . .
            roty      rotation    detector twotheta  0     1     0   0 0 -68
            rotz      rotation    detector roty      0     0     1   0 0 -68
    
    


    Example 3 - This example show the axis specification of the axes for a map, using fractional coordinates. Each cell edge has been divided into a grid of 50 divisions in the ARRAY_STRUCTURE_LIST_AXIS category. The map is using only the first octant of the grid in the ARRAY_STRUCTURE_LIST category. The fastest changing axis is the gris along A, then along B, and the slowest is along C. The map sampling is being done in the middle of each grid division
     
            loop_
            _axis.id
            _axis.system
            _axis.vector[1] _axis.vector[2] _axis.vector[3]
            CELL_A_AXIS    fractional       1 0 0
            CELL_B_AXIS    fractional       0 1 0
            CELL_C_AXIS    fractional       0 0 1
    
            loop_
            _array_structure_list.array_id
            _array_structure_list.index
            _array_structure_list.dimension
            _array_structure_list.precedence
            _array_structure_list.direction
            _array_structure_list.axis_id
            MAP 1 25 1 increasing CELL_A_AXIS
            MAP 1 25 2 increasing CELL_B_AXIS
            MAP 1 25 3 increasing CELL_C_AXIS
    
            loop_
            _array_structure_list_axis.axis_id
            _array_structure_list_axis.fract_displacement
            _array_structure_list_axis.fract_displacement_increment
            CELL_A_AXIS 0.01 0.02
            CELL_B_AXIS 0.01 0.02
            CELL_C_AXIS 0.01 0.02
    
    
    
    
    


    Example 4 - This example show the axis specification of the axes for a map, this time as orthogonal \%Angstroms, using the same coordinate system as for the atomic coordinates. The map is sampling every 1.5 \%Angstroms (1.5e-7 millimeters) in a map segment 37.5 \%Angstroms on a side.
     
            loop_
            _axis.id
            _axis.system
            _axis.vector[1] _axis.vector[2] _axis.vector[3]
            X    orthogonal       1 0 0
            Y    orthogonal       0 1 0
            Z    orthogonal       0 0 1
    
                    loop_
            _array_structure_list.array_id
            _array_structure_list.index
            _array_structure_list.dimension
            _array_structure_list.precedence
            _array_structure_list.direction
            _array_structure_list.axis_id
            MAP 1 25 1 increasing X
            MAP 2 25 2 increasing Y
            MAP 3 25 3 increasing Z
    
            loop_
            _array_structure_list_axis.axis_id
            _array_structure_list_axis.displacement
            _array_structure_list_axis.displacement_increment
            X 7.5e-8 1.5e-7
            Y 7.5e-8 1.5e-7
            Z 7.5e-8 1.5e-7
    
    
    
    


    Category groups:
        inclusive_group
        axis_group
        diffrn_group
    Category keys:
        _axis.id
        _axis.equipment

    Mandatory category: no

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/cif_img_1.5.4_28Jul07.html0000644000076500007650000114145011603702115016514 0ustar yayayaya cif_img.dic v1.5_DRAFT

    # [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib] #

    # imgCIF/CBF #

    # Extensions Dictionary #

    ##############################################################################
    #                                                                            #
    #                       Image CIF Dictionary (imgCIF)                        #
    #             and Crystallographic Binary File Dictionary (CBF)              #
    #            Extending the Macromolecular CIF Dictionary (mmCIF)             #
    #                                                                            #
    #                              Version 1.5.4                                 #
    #                              of 2007-07-28                                 #
    #    ###################################################################     #
    #    # *** WARNING *** THIS IS A DRAFT FOR DISCUSSSION *** WARNING *** #     #
    #    #                 SUBJECT TO CHANGE WITHOUT NOTICE                #     #
    #    #       SEND COMMENTS TO imgcif-l@iucr.org CITING THE VERSION     #     #
    #    ###################################################################     #
    #                  This draft edited by H. J. Bernstein                      #
    #                                                                            #
    #     by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook    #
    #                                                                            #
    # This dictionary was adapted from format discussed at the imgCIF Workshop,  #
    # held at BNL Oct 1997 and the Crystallographic Binary File Format Draft     #
    # Proposal by Andrew Hammersley.  The first DDL 2.1 Version was created by   #
    # John Westbrook.  This version was drafted by Herbert J. Bernstein and      #
    # incorporates comments by I. David Brown, John Westbrook, Brian McMahon,    #
    # Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li, Gotzon Madariaga,         #
    # Frances C. Bernstein, Chris Nielsen, Nicola Ashcroft and others.           #
    ##############################################################################
    
    data_cif_img.dic
    
        _dictionary.title           cif_img.dic
        _dictionary.version         1.5.4
        _dictionary.datablock_id    cif_img.dic
    
    ##############################################################################
    #    CONTENTS
    #
    #        CATEGORY_GROUP_LIST
    #        SUB_CATEGORY
    #
    #        category  ARRAY_DATA
    #
    #                  _array_data.array_id
    #                  _array_data.binary_id
    #                  _array_data.data
    #                  _array_data.header_contents
    #                  _array_data.header_convention
    #
    #        category  ARRAY_ELEMENT_SIZE
    #
    #                  _array_element_size.array_id
    #                  _array_element_size.index
    #                  _array_element_size.size
    #
    #        category  ARRAY_INTENSITIES
    #
    #                  _array_intensities.array_id
    #                  _array_intensities.binary_id
    #                  _array_intensities.gain
    #                  _array_intensities.gain_esd
    #                  _array_intensities.linearity
    #                  _array_intensities.offset
    #                  _array_intensities.scaling
    #                  _array_intensities.overload
    #                  _array_intensities.undefined_value
    #                  _array_intensities.pixel_fast_bin_size
    #                  _array_intensities.pixel_slow_bin_size
    #                  _array_intensities.pixel_binning_method
    #
    #        category  ARRAY_STRUCTURE
    #
    #                  _array_structure.byte_order
    #                  _array_structure.compression_type
    #                  _array_structure.compression_type_flag
    #                  _array_structure.encoding_type
    #                  _array_structure.id
    #
    #        category  ARRAY_STRUCTURE_LIST
    #
    #                  _array_structure_list.axis_set_id
    #                  _array_structure_list.array_id
    #                  _array_structure_list.dimension
    #                  _array_structure_list.direction
    #                  _array_structure_list.index
    #                  _array_structure_list.precedence
    #
    #        category  ARRAY_STRUCTURE_LIST_AXIS
    #
    #                  _array_structure_list_axis.axis_id
    #                  _array_structure_list_axis.axis_set_id
    #                  _array_structure_list_axis.angle
    #                  _array_structure_list_axis.angle_increment
    #                  _array_structure_list_axis.displacement
    #                  _array_structure_list_axis.fract_displacement
    #                  _array_structure_list_axis.displacement_increment
    #                  _array_structure_list_axis.fract_displacement_increment
    #                  _array_structure_list_axis.angular_pitch
    #                  _array_structure_list_axis.radial_pitch
    #                  _array_structure_list_axis.reference_angle
    #                  _array_structure_list_axis.reference_displacement
    #
    #        category  AXIS
    #
    #                  _axis.depends_on
    #                  _axis.equipment
    #                  _axis.id
    #                  _axis.offset[1]
    #                  _axis.offset[2]
    #                  _axis.offset[3]
    #                  _axis.type
    #                  _axis.system
    #                  _axis.vector[1]
    #                  _axis.vector[2]
    #                  _axis.vector[3]
    #
    #        category  DIFFRN_DATA_FRAME
    #
    #                  _diffrn_data_frame.array_id
    #                  _diffrn_data_frame.binary_id
    #                  _diffrn_data_frame.center_fast
    #                  _diffrn_data_frame.center_slow
    #                  _diffrn_data_frame.center_units
    #                  _diffrn_data_frame.detector_element_id
    #                  _diffrn_data_frame.id
    #                  _diffrn_data_frame.details
    #
    #        category  DIFFRN_DETECTOR
    #
    #                  _diffrn_detector.details
    #                  _diffrn_detector.detector
    #                  _diffrn_detector.diffrn_id
    #                  _diffrn_detector.dtime
    #                  _diffrn_detector.id
    #                  _diffrn_detector.number_of_axes
    #                  _diffrn_detector.type
    #
    #        category  DIFFRN_DETECTOR_AXIS
    #
    #                  _diffrn_detector_axis.axis_id
    #                  _diffrn_detector_axis.detector_id
    #
    #        category  DIFFRN_DETECTOR_ELEMENT
    #
    #                  _diffrn_detector_element.id
    #                  _diffrn_detector_element.detector_id
    #                  _diffrn_detector_element.reference_center_fast
    #                  _diffrn_detector_element.reference_center_slow
    #                  _diffrn_detector_element.reference_center_units
    #
    #        category  DIFFRN_MEASUREMENT
    #
    #                  _diffrn_measurement.diffrn_id
    #                  _diffrn_measurement.details
    #                  _diffrn_measurement.device
    #                  _diffrn_measurement.device_details
    #                  _diffrn_measurement.device_type
    #                  _diffrn_measurement.id
    #                  _diffrn_measurement.method
    #                  _diffrn_measurement.number_of_axes
    #                  _diffrn_measurement.sample_detector_distance
    #                  _diffrn_measurement.sample_detector_voffset
    #                  _diffrn_measurement.specimen_support
    #
    #        category  DIFFRN_MEASUREMENT_AXIS
    #
    #                  _diffrn_measurement_axis.axis_id
    #                  _diffrn_measurement_axis.measurement_device
    #                  _diffrn_measurement_axis.measurement_id
    #
    #        category  DIFFRN_RADIATION
    #
    #                  _diffrn_radiation.collimation
    #                  _diffrn_radiation.diffrn_id
    #                  _diffrn_radiation.div_x_source
    #                  _diffrn_radiation.div_y_source
    #                  _diffrn_radiation.div_x_y_source
    #                  _diffrn_radiation.filter_edge'
    #                  _diffrn_radiation.inhomogeneity
    #                  _diffrn_radiation.monochromator
    #                  _diffrn_radiation.polarisn_norm
    #                  _diffrn_radiation.polarisn_ratio
    #                  _diffrn_radiation.polarizn_source_norm
    #                  _diffrn_radiation.polarizn_source_ratio
    #                  _diffrn_radiation.probe
    #                  _diffrn_radiation.type
    #                  _diffrn_radiation.xray_symbol
    #                  _diffrn_radiation.wavelength_id
    #
    #        category  DIFFRN_REFLN
    #
    #                  _diffrn_refln.frame_id
    #
    #        category  DIFFRN_SCAN
    #
    #                  _diffrn_scan.id
    #                  _diffrn_scan.date_end
    #                  _diffrn_scan.date_start
    #                  _diffrn_scan.integration_time
    #                  _diffrn_scan.frame_id_start
    #                  _diffrn_scan.frame_id_end
    #                  _diffrn_scan.frames
    #
    #        category  DIFFRN_SCAN_AXIS
    #
    #                  _diffrn_scan_axis.axis_id
    #                  _diffrn_scan_axis.angle_start
    #                  _diffrn_scan_axis.angle_range
    #                  _diffrn_scan_axis.angle_increment
    #                  _diffrn_scan_axis.angle_rstrt_incr
    #                  _diffrn_scan_axis.displacement_start
    #                  _diffrn_scan_axis.displacement_range
    #                  _diffrn_scan_axis.displacement_increment
    #                  _diffrn_scan_axis.displacement_rstrt_incr
    #                  _diffrn_scan_axis.reference_angle
    #                  _diffrn_scan_axis.reference_displacement
    #                  _diffrn_scan_axis.scan_id
    #
    #        category  DIFFRN_SCAN_FRAME
    #
    #                  _diffrn_scan_frame.date
    #                  _diffrn_scan_frame.frame_id
    #                  _diffrn_scan_frame.frame_number
    #                  _diffrn_scan_frame.integration_time
    #                  _diffrn_scan_frame.scan_id
    #
    #        category  DIFFRN_SCAN_FRAME_AXIS
    #
    #                  _diffrn_scan_frame_axis.axis_id
    #                  _diffrn_scan_frame_axis.angle
    #                  _diffrn_scan_frame_axis.angle_increment
    #                  _diffrn_scan_frame_axis.angle_rstrt_incr
    #                  _diffrn_scan_frame_axis.displacement
    #                  _diffrn_scan_frame_axis.displacement_increment
    #                  _diffrn_scan_frame_axis.displacement_rstrt_incr
    #                  _diffrn_scan_frame_axis.reference_angle
    #                  _diffrn_scan_frame_axis.reference_displacement
    #                  _diffrn_scan_frame_axis.frame_id
    #
    #       categor    MAP
    #
    #                  _map.details
    #                  _map.diffrn_id
    #                  _map.entry_id
    #                  _map.id
    #
    #       categor    MAP_SEGMENT
    #
    #                  _map_segment.array_id
    #                  _map_segment.binary_id
    #                  _map_segment.mask_array_id
    #                  _map_segment.mask_binary_id
    #                  _map_segment.id
    #                  _map_segment.map_id
    #                  _map_segment.details
    #
    #       ***DEPRECATED*** data items
    #
    #                  _diffrn_detector_axis.id
    #                  _diffrn_detector_element.center[1]
    #                  _diffrn_detector_element.center[2]
    #                  _diffrn_measurement_axis.id
    #
    #       ***DEPRECATED*** category  DIFFRN_FRAME_DATA
    #
    #                  _diffrn_frame_data.array_id
    #                  _diffrn_frame_data.binary_id
    #                  _diffrn_frame_data.detector_element_id
    #                  _diffrn_frame_data.id
    #                  _diffrn_frame_data.details
    #
    #
    #        ITEM_TYPE_LIST
    #        ITEM_UNITS_LIST
    #        DICTIONARY_HISTORY
    #
    ##############################################################################
    
    
    #########################
    ## CATEGORY_GROUP_LIST ##
    #########################
    
         loop_
        _category_group_list.id
        _category_group_list.parent_id
        _category_group_list.description
                 'inclusive_group'   .
    ;             Categories that belong to the dictionary extension.
    ;
                 'array_data_group'
                 'inclusive_group'
    ;             Categories that describe array data.
    ;
                 'axis_group'
                 'inclusive_group'
    ;             Categories that describe axes.
    ;
                 'diffrn_group'
                 'inclusive_group'
    ;            Categories that describe details of the diffraction experiment.
    ;
    
    
    ##################
    ## SUB_CATEGORY ##
    ##################
    
         loop_
        _sub_category.id
        _sub_category.description
                  'matrix'
    ;              The collection of elements of a matrix.
    ;
                  'vector'
    ;              The collection of elements of a vector.
    ;
    
    
    
    
    ##############
    # ARRAY_DATA #
    ##############
    
    
    save_ARRAY_DATA
        _category.description
    ;    Data items in the ARRAY_DATA category are the containers for
         the array data items described in the category ARRAY_STRUCTURE.
         
         It is recognized that the data in this category needs to be used in
         two distinct ways.  During a data collection the lack of ancillary
         data and timing constraints in processing data may dictate the
         need to make a 'miniCBF' nothing more than an essential minimum
         of information to record the results of the data collection.  In that
         case it is proper to use the ARRAY_DATA category as a
         container for just a single image and a compacted, beam-line
         dependent list of data collection parameter values.  In such
         a case, only the tags '_array_data.header_convention',
         '_array_data.header_contents' and '_array_data.data' need be
         populated.
         
         For full processing and archiving, most of the tags in this
         dictionary will need to be populated.
         
    ;
        _category.id                   array_data
        _category.mandatory_code       no
         loop_
        _category_key.name             '_array_data.array_id'
                                       '_array_data.binary_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 -
    
            This example shows two binary data blocks.  The first one
            was compressed by the CBF_CANONICAL compression algorithm and is
            presented as hexadecimal data.  The first character 'H' on the
            data lines means hexadecimal.  It could have been 'O' for octal
            or 'D' for decimal.  The second character on the line shows
            the number of bytes in each word (in this case '4'), which then
            requires eight hexadecimal digits per word.  The third character
            gives the order of octets within a word, in this case '<'
            for the ordering 4321 (i.e. 'big-endian').  Alternatively, the
            character '>' could have been used for the ordering 1234
            (i.e. 'little-endian').  The block has a 'message digest'
            to check the integrity of the data.
    
            The second block is similar, but uses CBF_PACKED compression
            and BASE64 encoding.  Note that the size and the digest are
            different.
    ;
    ;
    
            loop_
            _array_data.array_id
            _array_data.binary_id
            _array_data.data
            image_1 1
            ;
            --CIF-BINARY-FORMAT-SECTION--
            Content-Type: application/octet-stream;
                 conversions="X-CBF_CANONICAL"
            Content-Transfer-Encoding: X-BASE16
            X-Binary-Size: 3927126
            X-Binary-ID: 1
            Content-MD5: u2sTJEovAHkmkDjPi+gWsg==
    
            # Hexadecimal encoding, byte 0, byte order ...21
            #
            H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ...
            ....
            --CIF-BINARY-FORMAT-SECTION----
            ;
            image_2 2
            ;
            --CIF-BINARY-FORMAT-SECTION--
            Content-Type: application/octet-stream;
                 conversions="X-CBF-PACKED"
            Content-Transfer-Encoding: BASE64
            X-Binary-Size: 3745758
            X-Binary-ID: 2
            Content-MD5: 1zsJjWPfol2GYl2V+QSXrw==
    
            ELhQAAAAAAAA...
            ...
            --CIF-BINARY-FORMAT-SECTION----
            ;
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 2 -
    
            This example shows a single image in a miniCBF, provided by
            E. Eikenberry.  The entire CBF consists of one data block
            containing one category and three tags.  The CBFlib
            program convert_miniCBF and a suitable template file
            can be used to convert this miniCBF to a full imgCIF
            file.
    ;
    ;
            ###CBF: VERSION 1.5
            # CBF file written by CBFlib v0.7.8
    
            data_insulin_pilatus6m
    
            _array_data.header_convention SLS_1.0
            _array_data.header_contents
            ;
            # Detector: PILATUS 6M SN: 60-0001
            # 2007/Jun/17 15:12:36.928
            # Pixel_size 172e-6 m x 172e-6 m
            # Silicon sensor, thickness 0.000320 m
            # Exposure_time 0.995000 s
            # Exposure_period 1.000000 s
            # Tau = 194.0e-09 s
            # Count_cutoff 1048575 counts
            # Threshold_setting 5000 eV
            # Wavelength 1.2398 A
            # Energy_range (0, 0) eV
            # Detector_distance 0.15500 m
            # Detector_Voffset -0.01003 m
            # Beam_xy (1231.00, 1277.00) pixels
            # Flux 22487563295 ph/s
            # Filter_transmission 0.0008
            # Start_angle 13.0000 deg.
            # Angle_increment 1.0000 deg.
            # Detector_2theta 0.0000 deg.
            # Polarization 0.990
            # Alpha 0.0000 deg.
            # Kappa 0.0000 deg.
            # Phi 0.0000 deg.
            # Chi 0.0000 deg.
            # Oscillation_axis  X, CW
            # N_oscillations 1
            ;
    
            _array_data.data
            ;
            --CIF-BINARY-FORMAT-SECTION--
            Content-Type: application/octet-stream;
                 conversions="x-CBF_BYTE_OFFSET"
            Content-Transfer-Encoding: BINARY
            X-Binary-Size: 6247567
            X-Binary-ID: 1
            X-Binary-Element-Type: "signed 32-bit integer"
            X-Binary-Element-Byte-Order: LITTLE_ENDIAN
            Content-MD5: 8wO6i2+899lf5iO8QPdgrw==
            X-Binary-Number-of-Elements: 6224001
            X-Binary-Size-Fastest-Dimension: 2463
            X-Binary-Size-Second-Dimension: 2527
            X-Binary-Size-Padding: 4095
    
            ...
            
            --CIF-BINARY-FORMAT-SECTION----
            ;
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    
    save_
    
    
    save__array_data.array_id
        _item_description.description
    ;             This item is a pointer to _array_structure.id in the
                  ARRAY_STRUCTURE category.
                  
                  If not given, it defaults to 1.
    ;
        _item.name                  '_array_data.array_id'
        _item.category_id             array_data
        _item.mandatory_code          implicit
        _item_type.code               code
         save_
    
    
    save__array_data.binary_id
        _item_description.description
    ;             This item is an integer identifier which, along with
                  _array_data.array_id, should uniquely identify the
                  particular block of array data.
    
                  If _array_data.binary_id is not explicitly given,
                  it defaults to 1.
    
                  The value of _array_data.binary_id distinguishes
                  among multiple sets of data with the same array
                  structure.
    
                  If the MIME header of the data array specifies a
                  value for X-Binary-ID, the value of  _array_data.binary_id
                  should be equal to the value given for X-Binary-ID.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
                 '_array_data.binary_id'            array_data
                                                                    implicit
                 '_diffrn_data_frame.binary_id'     diffrn_data_frame
                                                                    implicit
                 '_array_intensities.binary_id'     array_intensities
                                                                    implicit
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_data_frame.binary_id'     '_array_data.binary_id'
                 '_array_intensities.binary_id'     '_array_data.binary_id'
    
        _item_default.value           1
        _item_type.code               int
         loop_
        _item_range.maximum
        _item_range.minimum
                                1  1
                                .  1
         save_
    
    
    save__array_data.data
        _item_description.description
    ;             The value of _array_data.data contains the array data
                  encapsulated in a STAR string.
    
                  The representation used is a variant on the
                  Multipurpose Internet Mail Extensions (MIME) specified
                  in RFC 2045-2049 by N. Freed et al.  The boundary
                  delimiter used in writing an imgCIF or CBF is
                  '\n--CIF-BINARY-FORMAT-SECTION--' (including the
                  required initial '\n--').
    
                  The Content-Type may be any of the discrete types permitted
                  in RFC 2045; 'application/octet-stream' is recommended
                  for diffraction images in the ARRAY_DATA category.
                  Note:  When appropriate in other categories, e.g. for
                  photographs of crystals, more precise types, such as
                  'image/jpeg', 'image/tiff', 'image/png', etc. should be used.
                  
                  If an octet stream was compressed, the compression should
                  be specified by the parameter 
                    'conversions="X-CBF_PACKED"'
                  or the parameter 
                    'conversions="X-CBF_CANONICAL"'
                  or the parameter 
                    'conversions="X-CBF_BYTE_OFFSET"'
                    
                  If the parameter 
                    'conversions="X-CBF_PACKED"'
                  is given it may be further modified with the parameters
                    '"uncorrelated_sections"'
                  or
                    '"flat"'
                  
                  If the '"uncorrelated_sections"' parameter is
                  given, each section will be compressed without using
                  the prior section for averaging.
                  
                  If the '"flat"' parameter is given, each the
                  image will be treated as one long row.
    
                  The Content-Transfer-Encoding may be 'BASE64',
                  'Quoted-Printable', 'X-BASE8', 'X-BASE10',
                  'X-BASE16' or 'X-BASE32K', for an imgCIF or 'BINARY'
                  for a CBF.  The octal, decimal and hexadecimal transfer
                  encodings are provided for convenience in debugging and
                  are not recommended for archiving and data interchange.
    
                  In a CIF, one of the parameters 'charset=us-ascii',
                  'charset=utf-8' or 'charset=utf-16' may be used on the
                  Content-Transfer-Encoding to specify the character set
                  used for the external presentation of the encoded data.
                  If no charset parameter is given, the character set of
                  the enclosing CIF is assumed.  In any case, if a BOM
                  flag is detected (FE FF for big-endian UTF-16, FF FE for
                  little-endian UTF-16 or EF BB BF for UTF-8) is detected,
                  the indicated charset will be assumed until the end of the
                  encoded data or the detection of a different BOM.  The
                  charset of the Content-Transfer-Encoding is not the character
                  set of the encoded data, only the character set of the
                  presentation of the encoded data and should be respecified
                  for each distinct STAR string.
    
                  In an imgCIF file, the encoded binary data begins after
                  the empty line terminating the header.  In an imgCIF file,
                  the encoded binary data ends with the terminating boundary
                  delimiter '\n--CIF-BINARY-FORMAT-SECTION----'
                  in the currently effective charset or with the '\n; '
                  that terminates the STAR string.
    
                  In a CBF, the raw binary data begins after an empty line
                  terminating the header and after the sequence:
    
                  Octet   Hex   Decimal  Purpose
                    0     0C       12    (ctrl-L) Page break
                    1     1A       26    (ctrl-Z) Stop listings in MS-DOS
                    2     04       04    (Ctrl-D) Stop listings in UNIX
                    3     D5      213    Binary section begins
    
                  None of these octets are included in the calculation of
                  the message size or in the calculation of the
                  message digest.
    
                  The X-Binary-Size header specifies the size of the
                  equivalent binary data in octets.  If compression was
                  used, this size is the size after compression, including
                  any book-keeping fields.  An adjustment is made for
                  the deprecated binary formats in which eight bytes of binary
                  header are used for the compression type.  In this case,
                  the eight bytes used for the compression type are subtracted
                  from the size, so that the same size will be reported
                  if the compression type is supplied in the MIME header.
                  Use of the MIME header is the recommended way to
                  supply the compression type.  In general, no portion of
                  the  binary header is included in the calculation of the size.
    
                  The X-Binary-Element-Type header specifies the type of
                  binary data in the octets, using the same descriptive
                  phrases as in _array_structure.encoding_type.  The default
                  value is 'unsigned 32-bit integer'.
    
                  An MD5 message digest may, optionally, be used. The 'RSA Data
                  Security, Inc. MD5 Message-Digest Algorithm' should be used.
                  No portion of the header is included in the calculation of the
                  message digest.
    
                  If the Transfer Encoding is 'X-BASE8', 'X-BASE10' or
                  'X-BASE16', the data are presented as octal, decimal or
                  hexadecimal data organized into lines or words.  Each word
                  is created by composing octets of data in fixed groups of
                  2, 3, 4, 6 or 8 octets, either in the order ...4321 ('big-
                  endian') or 1234... ('little-endian').  If there are fewer
                  than the specified number of octets to fill the last word,
                  then the missing octets are presented as '==' for each
                  missing octet.  Exactly two equal signs are used for each
                  missing octet even for octal and decimal encoding.
                  The format of lines is:
    
                  rnd xxxxxx xxxxxx xxxxxx
    
                  where r is 'H', 'O' or 'D' for hexadecimal, octal or
                  decimal, n is the number of octets per word and d is '<'
                  or '>' for the '...4321' and '1234...' octet orderings,
                  respectively.  The '==' padding for the last word should
                  be on the appropriate side to correspond to the missing
                  octets, e.g.
    
                  H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000
    
                  or
    
                  H3> FF0700 00====
    
                  For these hexadecimal, octal and decimal formats only,
                  comments beginning with '#' are permitted to improve
                  readability.
    
                  BASE64 encoding follows MIME conventions.  Octets are
                  in groups of three: c1, c2, c3.  The resulting 24 bits
                  are broken into four six-bit quantities, starting with
                  the high-order six bits (c1 >> 2) of the first octet, then
                  the low-order two bits of the first octet followed by the
                  high-order four bits of the second octet [(c1 & 3)<<4 | (c2>>4)],
                  then the bottom four bits of the second octet followed by the
                  high-order two bits of the last octet [(c2 & 15)<<2 | (c3>>6)],
                  then the bottom six bits of the last octet (c3 & 63).  Each
                  of these four quantities is translated into an ASCII character
                  using the mapping:
    
                            1         2         3         4         5         6
                  0123456789012345678901234567890123456789012345678901234567890123
                  |         |         |         |         |         |         |
                  ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/
    
                  With short groups of octets padded on the right with one '='
                  if c3 is missing, and with '==' if both c2 and c3 are missing.
    
                  X-BASE32K encoding is similar to BASE64 encoding, except that
                  sets of 15 octets are encoded as sets of 8 16-bit unicode
                  characters, by breaking the 120 bits into 8 15-bit quantities.
                  256 is added to each 15 bit quantity to bring it into a
                  printable uncode range.  When encoding, zero padding is used
                  to fill out the last 15 bit quantity.  If 8 or more bits of
                  padding are used, a single equals sign (hexadecimal 003D) is
                  appended.  Embedded whitespace and newlines are introduced
                  to produce lines of no more than 80 characters each.  On
                  decoding, all printable ascii characters and ascii whitespace
                  characters are ignored except for any trailing equals signs.
                  The number of trailing equals signs indicated the number of
                  trailing octets to be trimmed from the end of the decoded data.
                  (see Georgi Darakev, Vassil Litchev, Kostadin Z. Mitev, Herbert
                  J. Bernstein, 'Efficient Support of Binary Data in the XML
                  Implementation of the NeXus File Format',absract W0165,
                  ACA Summer Meeting, Honolulu, HI, July 2006).
    
                  QUOTED-PRINTABLE encoding also follows MIME conventions, copying
                  octets without translation if their ASCII values are 32...38,
                  42, 48...57, 59, 60, 62, 64...126 and the octet is not a ';'
                  in column 1.  All other characters are translated to =nn, where
                  nn is the hexadecimal encoding of the octet.  All lines are
                  'wrapped' with a terminating '=' (i.e. the MIME conventions
                  for an implicit line terminator are never used).
                  
                  The "X-Binary-Element-Byte-Order" can specify either 
                  '"BIG_ENDIAN"' or '"LITTLE_ENDIAN"' byte order of the imaage 
                  data.  Only LITTLE_ENDIAN is recommended.  Processors
                  may treat BIG_ENDIAN as a warning of data that can
                  only be processed by special software.
    
                  The "X-Binary-Number-of-Elements" specifies the number of 
                  elements (not the number of octets) in the decompressed, decoded 
                  image.
    
                  The optional "X-Binary-Size-Fastest-Dimension" specifies the 
                  number of elements (not the number of octets) in one row of the 
                  fastest changing dimension of the binary data array. This 
                  information must be in the MIME header for proper operation of 
                  some of the decompression algorithms.
    
                  The optional "X-Binary-Size-Second-Dimension" specifies the 
                  number of elements (not the number of octets) in one column of 
                  the second-fastest changing dimension of the binary data array. 
                  This information must be in the MIME header for proper operation 
                  of some of the decompression algorithms.
    
                  The optional "X-Binary-Size-Third-Dimension" specifies the
                  number of sections for the third-fastest changing dimension of
                  the binary data array.
                  
                  The optional "X-Binary-Size-Padding" specifies the size in 
                  octets of an optional padding after the binary array data and 
                  before the closing flags for a binary section.
    ;
        _item.name                  '_array_data.data'
        _item.category_id             array_data
        _item.mandatory_code          yes
        _item_type.code               binary
    save_
    
    
    save__array_data.header_contents
        _item_description.description
    ;             This item is an text field for use in minimal CBF files to carry
                  essential header information to be kept with image data
                  in _array_data.data when the tags that normally carry the
                  structured metadata for the image have not been populated.
                  
                  Normally this data item should not appear when the full set
                  of tags have been populated and _diffrn_data_frame.details
                  appears.
    ;
        _item.name                  '_array_data.header_contents'
        _item.category_id            array_data
        _item.mandatory_code         no
        _item_type.code              text
         save_
    
    
    
    save__array_data.header_convention
        _item_description.description
    ;             This item is an identifier for the convention followed in
                  constructing the contents of _array_data.header_contents
                  
                  The permitted values are of the of an image creator identifier
                  followed by an underscore and a version string.  To avoid
                  confusion about conventions, all creator identifiers
                  should be registered with the IUCr and the conventions
                  for all identifiers and versions should be posted on
                  the MEDSBIO.org web site.
    ;
        _item.name                  '_array_data.header_convention'
        _item.category_id            array_data
        _item.mandatory_code         no
        _item_type.code              code
         save_
    
    
    
    
    ######################
    # ARRAY_ELEMENT_SIZE #
    ######################
    
    
    save_ARRAY_ELEMENT_SIZE
        _category.description
    ;    Data items in the ARRAY_ELEMENT_SIZE category record the physical
         size of array elements along each array dimension.
    ;
        _category.id                   array_element_size
        _category.mandatory_code       no
         loop_
        _category_key.name             '_array_element_size.array_id'
                                       '_array_element_size.index'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;       Example 1 - A regular 2D array with a uniform element dimension
                        of 1220 nanometres.
    ;
    ;
            loop_
           _array_element_size.array_id
           _array_element_size.index
           _array_element_size.size
            image_1   1    1.22e-6
            image_1   2    1.22e-6
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_element_size.array_id
        _item_description.description
    ;             This item is a pointer to _array_structure.id in the
                  ARRAY_STRUCTURE category.
    ;
        _item.name                  '_array_element_size.array_id'
        _item.category_id             array_element_size
        _item.mandatory_code          implicit
        _item_type.code               code
         save_
    
    
    save__array_element_size.index
        _item_description.description
    ;             This item is a pointer to _array_structure_list.index in
                  the ARRAY_STRUCTURE_LIST category.
    ;
        _item.name                  '_array_element_size.index'
        _item.category_id             array_element_size
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__array_element_size.size
        _item_description.description
    ;              The size in metres of an image element in this
                   dimension. This supposes that the elements are arranged
                   on a regular grid.
    ;
        _item.name               '_array_element_size.size'
        _item.category_id          array_element_size
        _item.mandatory_code       yes
        _item_type.code            float
        _item_units.code           'metres'
         loop_
        _item_range.maximum
        _item_range.minimum
                                .   0.0
         save_
    
    
    #####################
    # ARRAY_INTENSITIES #
    #####################
    
    
    save_ARRAY_INTENSITIES
        _category.description
    ;             Data items in the ARRAY_INTENSITIES category record the
                  information required to recover the intensity data from
                  the set of data values stored in the ARRAY_DATA category.
    
                  The detector may have a complex relationship
                  between the raw intensity values and the number of
                  incident photons.  In most cases, the number stored
                  in the final array will have a simple linear relationship
                  to the actual number of incident photons, given by
                  _array_intensities.gain.  If raw, uncorrected values
                  are presented (e.g. for calibration experiments), the
                  value of _array_intensities.linearity will be 'raw'
                  and _array_intensities.gain will not be used.
    
    ;
        _category.id                   array_intensities
        _category.mandatory_code       no
        loop_
        _category_key.name             '_array_intensities.array_id'
                                       '_array_intensities.binary_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1
    ;
    ;
            loop_
            _array_intensities.array_id
            _array_intensities.linearity
            _array_intensities.gain
            _array_intensities.overload
            _array_intensities.undefined_value
            _array_intensities.pixel_fast_bin_size
            _array_intensities.pixel_slow_bin_size
            _array_intensities.pixel_binning_method
            image_1   linear  1.2    655535   0   2   2    hardware
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_intensities.array_id
        _item_description.description
    ;             This item is a pointer to _array_structure.id in the
                  ARRAY_STRUCTURE category.
    ;
        _item.name                  '_array_intensities.array_id'
        _item.category_id             array_intensities
        _item.mandatory_code          implicit
        _item_type.code               code
         save_
    
    
    save__array_intensities.binary_id
        _item_description.description
    ;             This item is a pointer to _array_data.binary_id in the
                  ARRAY_DATA category.
    ;
        _item.name                  '_array_intensities.binary_id'
        _item.category_id             array_intensities
        _item.mandatory_code          implicit
        _item_type.code               int
         save_
    
    
    save__array_intensities.gain
        _item_description.description
    ;              Detector 'gain'. The factor by which linearized
                   intensity count values should be divided to produce
                   true photon counts.
    ;
        _item.name              '_array_intensities.gain'
        _item.category_id          array_intensities
        _item.mandatory_code       yes
        _item_type.code            float
         loop_
        _item_range.maximum
        _item_range.minimum
                                .   0.0
        _item_units.code           'counts_per_photon'
         loop_
        _item_related.related_name
        _item_related.function_code  '_array_intensities.gain_esd'
                                     'associated_value'
        save_
    
    
    save__array_intensities.gain_esd
        _item_description.description
    ;            The estimated standard deviation in detector 'gain'.
    ;
        _item.name              '_array_intensities.gain_esd'
        _item.category_id          array_intensities
        _item.mandatory_code       yes
        _item_type.code            float
         loop_
        _item_range.maximum
        _item_range.minimum
                                .   0.0
    
        _item_units.code          'counts_per_photon'
         loop_
        _item_related.related_name
        _item_related.function_code  '_array_intensities.gain'
                                     'associated_esd'
        save_
    
    
    save__array_intensities.linearity
        _item_description.description
    ;              The intensity linearity scaling method used to convert
                   from the raw intensity to the stored element value:
    
                   'linear' is linear.
    
                   'offset'  means that the value defined by
                   _array_intensities.offset should be added to each
                    element value.
    
                   'scaling' means that the value defined by
                   _array_intensities.scaling should be multiplied with each
                   element value.
    
                   'scaling_offset' is the combination of the two previous cases,
                   with the scale factor applied before the offset value.
    
                   'sqrt_scaled' means that the square root of raw
                   intensities multiplied by _array_intensities.scaling is
                   calculated and stored, perhaps rounded to the nearest
                   integer. Thus, linearization involves dividing the stored
                   values by _array_intensities.scaling and squaring the
                   result.
    
                   'logarithmic_scaled' means that the logarithm base 10 of
                   raw intensities multiplied by _array_intensities.scaling
                   is calculated and stored, perhaps rounded to the nearest
                   integer. Thus, linearization involves dividing the stored
                   values by _array_intensities.scaling and calculating 10
                   to the power of this number.
    
                   'raw' means that the data are a set of raw values straight
                   from the detector.
    ;
    
        _item.name               '_array_intensities.linearity'
        _item.category_id          array_intensities
        _item.mandatory_code       yes
        _item_type.code            code
         loop_
        _item_enumeration.value
        _item_enumeration.detail
                                  'linear' .
                                  'offset'
    ;              The value defined by  _array_intensities.offset should
                   be added to each element value.
    ;
                                  'scaling'
    ;              The value defined by _array_intensities.scaling should be
                   multiplied with each element value.
    ;
                                  'scaling_offset'
    ;              The combination of the scaling and offset
                   with the scale factor applied before the offset value.
    ;
                                  'sqrt_scaled'
    ;              The square root of raw intensities multiplied by
                   _array_intensities.scaling is calculated and stored,
                   perhaps rounded to the nearest integer. Thus,
                   linearization involves dividing the stored
                   values by _array_intensities.scaling and squaring the
                   result.
    ;
                                  'logarithmic_scaled'
    ;              The logarithm base 10 of raw intensities multiplied by
                   _array_intensities.scaling  is calculated and stored,
                   perhaps rounded to the nearest integer. Thus,
                   linearization involves dividing the stored values by
                   _array_intensities.scaling and calculating 10 to the
                   power of this number.
    ;
                                  'raw'
    ;              The array consists of raw values to which no corrections have
                   been applied.  While the handling of the data is similar to
                   that given for 'linear' data with no offset, the meaning of
                   the data differs in that the number of incident photons is
                   not necessarily linearly related to the number of counts
                   reported.  This value is intended for use either in
                   calibration experiments or to allow for handling more
                   complex data-fitting algorithms than are allowed for by
                   this data item.
    ;
    
        save_
    
    
    save__array_intensities.offset
        _item_description.description
    ;              Offset value to add to array element values in the manner
                   described by the item _array_intensities.linearity.
    ;
        _item.name                 '_array_intensities.offset'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        save_
    
    
    save__array_intensities.overload
        _item_description.description
    ;              The saturation intensity level for this data array.
    ;
        _item.name                 '_array_intensities.overload'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        _item_units.code          'counts'
        save_
    
    
    save__array_intensities.pixel_fast_bin_size
        _item_description.description
    ;              The value of _array_intensities.pixel_fast_bin_size specifies
                   the number of pixels that compose one element in the direction
                   of the most rapidly varying array dimension.
    
                   Typical values are 1, 2, 4 or 8.  When there is 1 pixel per
                   array element in both directions, the value given for
                   _array_intensities.pixel_binning_method normally should be
                   'none'.
    
                   It is specified as a float to allow for binning algorithms that
                   create array elements that are not integer multiples of the 
                   detector pixel size.
    ;
        _item.name              '_array_intensities.pixel_fast_bin_size'
        _item.category_id          array_intensities
        _item.mandatory_code       implicit
        _item_type.code            float
        _item_default.value        1.
         loop_
        _item_range.maximum
        _item_range.minimum
                                .   0.0
        _item_units.code           'pixels_per_element'
        save_
    
    
    save__array_intensities.pixel_slow_bin_size
        _item_description.description
    ;              The value of _array_intensities.pixel_slow_bin_size specifies
                   the number of pixels that compose one element in the direction
                   of the second most rapidly varying array dimension.
    
                   Typical values are 1, 2, 4 or 8.  When there is 1 pixel per
                   array element in both directions, the value given for
                   _array_intensities.pixel_binning_method normally should be
                   'none'.
    
                   It is specified as a float to allow for binning algorithms that
                   create array elements that are not integer multiples of the
                   detector pixel size.
    ;
        _item.name              '_array_intensities.pixel_slow_bin_size'
        _item.category_id          array_intensities
        _item.mandatory_code       implicit
        _item_type.code            float
        _item_default.value        1.
         loop_
        _item_range.maximum
        _item_range.minimum
                                .   0.0
        _item_units.code           'pixels_per_element'
        save_
    
    
    save__array_intensities.pixel_binning_method
        _item_description.description
    ;              The value of _array_intensities.pixel_binning_method specifies
                   the method used to derive array elements from multiple pixels.
    ;
        _item.name              '_array_intensities.pixel_binning_method'
        _item.category_id          array_intensities
        _item.mandatory_code       implicit
        _item_type.code            code
         loop_
        _item_enumeration.value
        _item_enumeration.detail
                                   'hardware'
    ;              The element intensities were derived from the raw data of one
                   or more pixels by used of hardware in the detector, e.g. by use
                   of shift registers in a CCD to combine pixels into super-pixels.
    ;
                                   'software'
    ;              The element intensities were derived from the raw data of more
                   than one pixel by use of software.
    ;
                                   'combined'
    ;              The element intensities were derived from the raw data of more
                   than one pixel by use of both hardware and software, as when
                   hardware binning is used in one direction and software in the
                   other.
    ;
                                   'none'
    ;              In the both directions, the data has not been binned.  The
                   number of pixels is equal to the number of elements.
    
                   When the value of _array_intensities.pixel_binning_method is
                   'none' the values of _array_intensities.pixel_fast_bin_size
                   and _array_intensities.pixel_slow_bin_size both must be 1.
    ;
                                   'unspecified'
    ;              The method used to derive element intensities is not specified.
    ;
        _item_default.value        'unspecified'
        save_
    
    save__array_intensities.scaling
        _item_description.description
    ;              Multiplicative scaling value to be applied to array data
                   in the manner described by item
                   _array_intensities.linearity.
    ;
        _item.name                 '_array_intensities.scaling'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        save_
    
    
    
    save__array_intensities.undefined_value
        _item_description.description
    ;              A value to be substituted for undefined values in
                   the data array.
    ;
        _item.name                 '_array_intensities.undefined_value'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        save_
    
    
    ###################
    # ARRAY_STRUCTURE #
    ###################
    
    
    save_ARRAY_STRUCTURE
        _category.description
    ;    Data items in the ARRAY_STRUCTURE category record the organization and
         encoding of array data that may be stored in the ARRAY_DATA category.
    ;
        _category.id                   array_structure
        _category.mandatory_code       no
        _category_key.name             '_array_structure.id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;   Example 1 -
    ;
    ;
         loop_
        _array_structure.id
        _array_structure.encoding_type
        _array_structure.compression_type
        _array_structure.byte_order
         image_1       "unsigned 16-bit integer"  none  little_endian
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_structure.byte_order
        _item_description.description
    ;              The order of bytes for integer values which require more
                   than 1 byte.
    
                   (IBM-PC's and compatibles and DEC VAXs use low-byte-first
                   ordered integers, whereas Hewlett Packard 700
                   series, Sun-4 and Silicon Graphics use high-byte-first
                   ordered integers.  DEC Alphas can produce/use either
                   depending on a compiler switch.)
    ;
    
        _item.name                     '_array_structure.byte_order'
        _item.category_id               array_structure
        _item.mandatory_code            yes
        _item_type.code                 ucode
         loop_
        _item_enumeration.value
        _item_enumeration.detail
                                       'big_endian'
    ;       The first byte in the byte stream of the bytes which make up an
            integer value is the most significant byte of an integer.
    ;
                                       'little_endian'
    ;       The last byte in the byte stream of the bytes which make up an
            integer value is the most significant byte of an integer.
    ;
         save_
    
    
    save__array_structure.compression_type
        _item_description.description
    ;             Type of data-compression method used to compress the array
                  data.
    ;
        _item.name                   '_array_structure.compression_type'
        _item.category_id             array_structure
        _item.mandatory_code          no
        _item_type.code               ucode
        _item_default.value           'none'
         loop_
        _item_enumeration.value
        _item_enumeration.detail
                                      'byte_offset'
    ;       Using the 'byte_offset' compression scheme as per A. Hammersley
            and the CBFlib manual, section 3.3.3
    ;
                                      'canonical'
    ;       Using the 'canonical' compression scheme (International Tables
            for Crystallography Volume G, Section 5.6.3.1) and CBFlib
            manual section 3.3.1
    ;
                                      'none'
    ;       Data are stored in normal format as defined by
            _array_structure.encoding_type and
            _array_structure.byte_order.
    ;
                                      'packed'
    ;       Using the 'packed' compression scheme, a CCP4-style packing
            as per J. P. Abrahams pack_c.c and CBFlib manual, section 3.3.2.
    ;
                                      'packed_v2'
    ;       Using the 'packed' compression scheme, version 2, as per
            J. P. Abrahams pack_c.c and CBFlib manual, section 3.3.2.
    ;
        save_
    
    save__array_structure.compression_type_flag
        _item_description.description
    ;             Flags modifying the type of data-compression method used to 
                  compress the arraydata.
    ;
        _item.name                   '_array_structure.compression_type_flag'
        _item.category_id             array_structure
        _item.mandatory_code          no
        _item_type.code               ucode
         loop_
        _item_enumeration.value
        _item_enumeration.detail
                                      'uncorrelated_sections'
    ;       When applying packed or packed_v2 compression on an array with
            uncorrelated sections, do not average in points from the prior
            section.
    ;
                                      'flat'
    ;       When applying packed or packed_v2 compression on an array with
            treat the entire image as a single line set the maximum number
            of bits for an offset to 65 bits.
            
            The flag is included for compatibility with software prior to
            CBFlib_0.7.7, and should not be used for new data sets.
    
    ;
    
        save_
    
    save__array_structure.encoding_type
        _item_description.description
    ;              Data encoding of a single element of array data.
    
                   The type 'unsigned 1-bit integer' is used for
                   packed Booleans arrays for masks.  Each element
                   of the array corresponds to a single bit
                   packed in unsigned 8-bit data.
                   
                   In several cases, the IEEE format is referenced.
                   See IEEE Standard 754-1985 (IEEE, 1985).
    
                   Ref: IEEE (1985). IEEE Standard for Binary Floating-Point
                   Arithmetic. ANSI/IEEE Std 754-1985. New York: Institute of
                   Electrical and Electronics Engineers.
    ;
    
        _item.name                '_array_structure.encoding_type'
        _item.category_id          array_structure
        _item.mandatory_code       yes
        _item_type.code            uline
         loop_
        _item_enumeration.value
                                  'unsigned 1-bit integer'
                                  'unsigned 8-bit integer'
                                  'signed 8-bit integer'
                                  'unsigned 16-bit integer'
                                  'signed 16-bit integer'
                                  'unsigned 32-bit integer'
                                  'signed 32-bit integer'
                                  'signed 32-bit real IEEE'
                                  'signed 64-bit real IEEE'
                                  'signed 32-bit complex IEEE'
         save_
    
    
    save__array_structure.id
        _item_description.description
    ;             The value of _array_structure.id must uniquely identify
                  each item of array data.
                  
                  This item has been made implicit and given a default value of 1
                  as a convenience in writing miniCBF files.  Normally an
                  explicit name with useful content should be used.
    ;
        loop_
        _item.name
        _item.category_id
        _item.mandatory_code
                 '_array_structure.id'              array_structure      implicit
                 '_array_data.array_id'             array_data           implicit
                 '_array_structure_list.array_id'   array_structure_list implicit
                 '_array_intensities.array_id'      array_intensities    implicit
                 '_diffrn_data_frame.array_id'      diffrn_data_frame    implicit
    
    
        _item_default.value           1
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_array_data.array_id'             '_array_structure.id'
                 '_array_structure_list.array_id'   '_array_structure.id'
                 '_array_intensities.array_id'      '_array_structure.id'
                 '_diffrn_data_frame.array_id'      '_array_structure.id'
    
         save_
    
    
    ########################
    # ARRAY_STRUCTURE_LIST #
    ########################
    
    
    save_ARRAY_STRUCTURE_LIST
        _category.description
    ;    Data items in the ARRAY_STRUCTURE_LIST category record the size
         and organization of each array dimension.
    
         The relationship to physical axes may be given.
    ;
        _category.id                   array_structure_list
        _category.mandatory_code       no
         loop_
        _category_key.name             '_array_structure_list.array_id'
                                       '_array_structure_list.index'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;       Example 1 - An image array of 1300 x 1200 elements.  The raster
                        order of the image is left to right (increasing) in the
                        first dimension and bottom to top (decreasing) in
                        the second dimension.
    ;
    ;
            loop_
           _array_structure_list.array_id
           _array_structure_list.index
           _array_structure_list.dimension
           _array_structure_list.precedence
           _array_structure_list.direction
           _array_structure_list.axis_set_id
            image_1   1    1300    1     increasing  ELEMENT_X
            image_1   2    1200    2     decreasing  ELEMENY_Y
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_structure_list.array_id
        _item_description.description
    ;             This item is a pointer to _array_structure.id in the
                  ARRAY_STRUCTURE category.
    ;
        _item.name                  '_array_structure_list.array_id'
        _item.category_id             array_structure_list
        _item.mandatory_code          implicit
        _item_type.code               code
    save_
    
    
    save__array_structure_list.axis_set_id
        _item_description.description
    ;              This is a descriptor for the physical axis or set of axes
                   corresponding to an array index.
    
                   This data item is related to the axes of the detector
                   itself given in DIFFRN_DETECTOR_AXIS, but usually differs
                   in that the axes in this category are the axes of the
                   coordinate system of reported data points, while the axes in
                   DIFFRN_DETECTOR_AXIS are the physical axes
                   of the detector describing the 'poise' of the detector as an
                   overall physical object.
    
                   If there is only one axis in the set, the identifier of
                   that axis should be used as the identifier of the set.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
               '_array_structure_list.axis_set_id'
                                      array_structure_list            yes
               '_array_structure_list_axis.axis_set_id'
                                      array_structure_list_axis       implicit
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_array_structure_list_axis.axis_set_id'
                                   '_array_structure_list.axis_set_id'
    
    
         save_
    
    
    save__array_structure_list.dimension
        _item_description.description
    ;              The number of elements stored in the array structure in 
                   this dimension.
    ;
        _item.name                '_array_structure_list.dimension'
        _item.category_id          array_structure_list
        _item.mandatory_code       yes
        _item_type.code            int
         loop_
        _item_range.maximum
        _item_range.minimum
                                1  1
                                .  1
         save_
    
    
    save__array_structure_list.direction
        _item_description.description
    ;             Identifies the direction in which this array index changes.
    ;
        _item.name                '_array_structure_list.direction'
        _item.category_id          array_structure_list
        _item.mandatory_code       yes
        _item_type.code            code
         loop_
        _item_enumeration.value
        _item_enumeration.detail
    
                                  'increasing'
    ;        Indicates the index changes from 1 to the maximum dimension.
    ;
                                  'decreasing'
    ;        Indicates the index changes from the maximum dimension to 1.
    ;
         save_
    
    
    save__array_structure_list.index
        _item_description.description
    ;              Identifies the one-based index of the row or column in the
                   array structure.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
               '_array_structure_list.index'        array_structure_list   yes
               '_array_structure_list.precedence'   array_structure_list   yes
               '_array_element_size.index'          array_element_size     yes
    
        _item_type.code            int
    
         loop_
        _item_linked.child_name
        _item_linked.parent_name
              '_array_element_size.index'         '_array_structure_list.index'
         loop_
        _item_range.maximum
        _item_range.minimum
                                1  1
                                .  1
         save_
    
    
    save__array_structure_list.precedence
        _item_description.description
    ;              Identifies the rank order in which this array index changes
                   with respect to other array indices.  The precedence of 1
                   indicates the index which changes fastest.
    ;
        _item.name                '_array_structure_list.precedence'
        _item.category_id          array_structure_list
        _item.mandatory_code       yes
        _item_type.code            int
         loop_
        _item_range.maximum
        _item_range.minimum
                                1  1
                                .  1
         save_
    
    
    #############################
    # ARRAY_STRUCTURE_LIST_AXIS #
    #############################
    
    save_ARRAY_STRUCTURE_LIST_AXIS
        _category.description
    ;    Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe
         the physical settings of sets of axes for the centres of pixels that
         correspond to data points described in the
         ARRAY_STRUCTURE_LIST category.
    
         In the simplest cases, the physical increments of a single axis correspond
         to the increments of a single array index.  More complex organizations,
         e.g. spiral scans, may require coupled motions along multiple axes.
    
         Note that a spiral scan uses two coupled axes: one for the angular
         direction and one for the radial direction.  This differs from a
         cylindrical scan for which the two axes are not coupled into one 
         set.
    ;
        _category.id                   array_structure_list_axis
        _category.mandatory_code       no
         loop_
        _category_key.name
                                      '_array_structure_list_axis.axis_set_id'
                                      '_array_structure_list_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'array_data_group'
         save_
    
    
    save__array_structure_list_axis.axis_id
        _item_description.description
    ;              The value of this data item is the identifier of one of
                   the axes in the set of axes for which settings are being
                   specified.
    
                   Multiple axes may be specified for the same value of
                   _array_structure_list_axis.axis_set_id.
    
                   This item is a pointer to _axis.id in the
                   AXIS category.
    ;
        _item.name                 '_array_structure_list_axis.axis_id'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__array_structure_list_axis.axis_set_id
        _item_description.description
    ;              The value of this data item is the identifier of the
                   set of axes for which axis settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   _array_structure_list_axis.axis_set_id.
    
                   This item is a pointer to
                   _array_structure_list.axis_set_id
                   in the ARRAY_STRUCTURE_LIST category.
    
                   If this item is not specified, it defaults to the corresponding
                   axis identifier.
    ;
        _item.name                 '_array_structure_list_axis.axis_set_id'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       implicit
        _item_type.code            code
         save_
    
    
    save__array_structure_list_axis.angle
        _item_description.description
    ;              The setting of the specified axis in degrees for the first
                   data point of the array index with the corresponding value
                   of _array_structure_list.axis_set_id.  If the index is
                   specified as 'increasing', this will be the centre of the
                   pixel with index value 1.  If the index is specified as
                   'decreasing', this will be the centre of the pixel with
                   maximum index value.
    ;
        _item.name                 '_array_structure_list_axis.angle'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__array_structure_list_axis.angle_increment
        _item_description.description
    ;              The pixel-centre-to-pixel-centre increment in the angular
                   setting of the specified axis in degrees.  This is not
                   meaningful in the case of 'constant velocity' spiral scans
                   and should not be specified for this case.
    
                   See _array_structure_list_axis.angular_pitch.
    
    ;
        _item.name                 '_array_structure_list_axis.angle_increment'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__array_structure_list_axis.displacement
        _item_description.description
    ;              The setting of the specified axis in millimetres for the first
                   data point of the array index with the corresponding value
                   of _array_structure_list.axis_set_id.  If the index is
                   specified as 'increasing', this will be the centre of the
                   pixel with index value 1.  If the index is specified as
                   'decreasing', this will be the centre of the pixel with
                   maximum index value.
    ;
        _item.name               '_array_structure_list_axis.displacement'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    save__array_structure_list_axis.fract_displacement
        _item_description.description
    ;              The setting of the specified axis as a decimal fraction of 
                   the axis unit vector for the first data point of the array 
                   index with the corresponding value of 
                   _array_structure_list.axis_set_id.  
                   If the index is specified as 'increasing', this will be the 
                   centre of the pixel with index value 1.  If the index is 
                   specified as 'decreasing', this will be the centre of the 
                   pixel with maximum index value.
    ;
        _item.name               '_array_structure_list_axis.fract_displacement'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
         save_
    
    save__array_structure_list_axis.displacement_increment
        _item_description.description
    ;              The pixel-centre-to-pixel-centre increment for the displacement
                   setting of the specified axis in millimetres.
    ;
        _item.name
            '_array_structure_list_axis.displacement_increment'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    save__array_structure_list_axis.fract_displacement_increment
        _item_description.description
    ;              The pixel-centre-to-pixel-centre increment for the displacement
                   setting of the specified axis as a decimal fraction of the
                   axis unit vector.
    ;
        _item.name
            '_array_structure_list_axis.fract_displacement_increment'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__array_structure_list_axis.angular_pitch
        _item_description.description
    ;              The pixel-centre-to-pixel-centre distance for a one-step
                   change in the setting of the specified axis in millimetres.
    
                   This is meaningful only for 'constant velocity' spiral scans
                   or for uncoupled angular scans at a constant radius
                   (cylindrical scans) and should not be specified for cases
                   in which the angle between pixels (rather than the distance
                   between pixels) is uniform.
    
                   See _array_structure_list_axis.angle_increment.
    ;
        _item.name               '_array_structure_list_axis.angular_pitch'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__array_structure_list_axis.radial_pitch
        _item_description.description
    ;              The radial distance from one 'cylinder' of pixels to the
                   next in millimetres.  If the scan is a 'constant velocity'
                   scan with differing angular displacements between pixels,
                   the value of this item may differ significantly from the
                   value of _array_structure_list_axis.displacement_increment.
    ;
        _item.name               '_array_structure_list_axis.radial_pitch'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__array_structure_list_axis.reference_angle
         _item_description.description
    ;              The value of _array_structure_list_axis.reference_angle
                   specifies the setting of the angle of this axis used for 
                   determining a reference beam center and a reference detector 
                   distance.  It is normally expected to be identical to the 
                   value of _array_structure_list.angle.
    
    ;
         _item.name '_array_structure_list_axis.reference_angle'
         _item.category_id          array_structure_list_axis
         _item.mandatory_code       implicit
         _item_type.code            float
         _item_units.code           'degrees'
          save_
    
    
    save__array_structure_list_axis.reference_displacement
         _item_description.description
    ;              The value of _array_structure_list_axis.reference_displacement
                   specifies the setting of the displacement of this axis used 
                   for determining a reference beam center and a reference detector
                   distance.  It is normally expected to be identical to the value
                   of _array_structure_list.displacement.
    
    ;
         _item.name '_array_structure_list_axis.reference_displacement'
         _item.category_id          array_structure_list_axis
         _item.mandatory_code       implicit
         _item_type.code            float
         _item_units.code           'millimetres'
          save_
    
    
    
    
    ########
    # AXIS #
    ########
    
    save_AXIS
        _category.description
    ;    Data items in the AXIS category record the information required
         to describe the various goniometer, detector, source and other
         axes needed to specify a data collection or the axes defining the
         coordinate system of an image.  
         
         The location of each axis is specified by two vectors: the axis 
         itself, given by a  unit vector in the direction of the axis, and 
         an offset to the base of the unit vector.  
         
         The vectors defining an axis are referenced to an appropriate
         coordinate system.  The axis vector, itself, is a dimensionless
         unit vector.  Where meaningful, the offset vector is given in
         millimetres.  In coordinate systems not measured in metres,
         the offset is not specified and is taken as zero. 
         
         The available coordinate systems are:
         
             The imgCIF standard laboratory coordinate system
             The direct lattice (fractional atomic coordinates)
             The orthogonal Cartesian coordinate system (real space)
             The reciprocal lattice
             An abstract orthogonal Cartesian coordinate frame
          
         For consistency in this discussion, we call the three coordinate 
         system axes X, Y and Z.  This is appropriate for the imgCIF
         standard laboratory coordinate system, and last two Cartesian
         coordinate systems, but for the direct lattice, X corresponds
         to a, Y to b and Z to c, while for the reciprocal lattice,
         X corresponds to a*, Y to b* and Z to c*.
         
         For purposes of visualization, all the coordinate systems are 
         taken as right-handed, i.e., using the convention that the extended 
         thumb of a right hand could point along the first (X) axis, the 
         straightened pointer finger could point along the second (Y) axis 
         and the middle finger folded inward could point along the third (Z)
         axis.  
         
         THE IMGCIF STANDARD LABORATORY COORDINATE SYSTEM
         
         The imgCIF standard laboratory coordinate system is a right-handed   
         orthogonal coordinate similar to the MOSFLM coordinate system,  
         but imgCIF puts Z along the X-ray beam, rather than putting X along the
         X-ray beam as in MOSFLM.
         
         The vectors for the imgCIF standard laboratory coordinate system
         form a right-handed Cartesian coordinate system with its origin
         in the sample or specimen.  The origin of the axis system should,
         if possible, be defined in terms of mechanically stable axes to be
         be both in the sample and in the beam.  If the sample goniometer or other
         sample positioner has two axes the intersection of which defines a
         unique point at which the sample should be mounted to be bathed
         by the beam, that will be the origin of the axis system.  If no such
         point is defined, then the midpoint of the line of intersection
         between the sample and the center of the beam will define the origin.
         For this definition the sample positioning system will be set at 
         its initial reference position for the experiment.
    
    
                                 | Y (to complete right-handed system)
                                 |
                                 |
                                 |
                                 |
                                 |
                                 |________________X
                                /       principal goniometer axis
                               /
                              /
                             /
                            /
                           /Z (to source)
    
    
    
    
         Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from
         the sample or specimen along the  principal axis of the goniometer or
         sample positioning system if the sample positioning system has an axis 
         that intersects the origin and which form an angle of more than 22.5 
         degrees with the beam axis.
         
         Axis 2 (Y): The Y-axis completes an orthogonal right-handed system
         defined by the X-axis and the Z-axis (see below).
    
         Axis 3 (Z): The Z-axis is derived from the source axis which goes from
         the sample to the source.  The Z-axis is the component of the source axis
         in the direction of the source orthogonal to the X-axis in the plane
         defined by the X-axis and the source axis.
    
         If the conditions for the X-axis can be met, the coordinate system
         will be based on the goniometer or other sample positioning system
         and the beam and not on the orientation of the detector, gravity etc.  
         The vectors necessary to specify all other axes are given by sets of 
         three components in the order (X, Y, Z).
         If the axis involved is a rotation axis, it is right-handed, i.e. as
         one views the object to be rotated from the origin (the tail) of the
         unit vector, the rotation is clockwise.  If a translation axis is
         specified, the direction of the unit vector specifies the sense of
         positive translation.
    
         Note:  This choice of coordinate system is similar to but significantly
         different from the choice in MOSFLM (Leslie & Powell, 2004).  In MOSFLM,
         X is along the X-ray beam (the CBF/imgCIF Z axis) and Z is along the
         rotation axis.
         
         In some experimental techniques, there is no goniometer or the principal
         axis of the goniometer is at a small acute angle with respect to
         the source axis.  In such cases, other reference axes are needed
         to define a useful coordinate system.  The order of priority in
         defining directions in such cases is to use the detector, then
         gravity, then north.
         
         
         If the X-axis cannot be defined as above, then the
         direction (not the origin) of the X-axis should be parallel to the axis 
         of the primary detector element corresponding to the most rapidly 
         varying dimension of that detector element's data array, with its 
         positive sense corresponding to increasing values of the index for 
         that dimension.  If the detector is such that such a direction cannot 
         be defined (as with a point detector) or that direction forms an
         angle of less than 22.5 degrees with respect to the source axis, then 
         the X-axis should be chosen so that if the Y-axis is chosen 
         in the direction of gravity, and the Z-axis is chosen to be along 
         the source axis, a right-handed orthogonal coordinate system is chosen.  
         In the case of a vertical source axis, as a last resort, the 
         X-axis should be chosen to point North.
         
         All rotations are given in degrees and all translations are given in mm.
    
         Axes may be dependent on one another.  The X-axis is the only goniometer
         axis the direction of which is strictly connected to the hardware.  All
         other axes are specified by the positions they would assume when the
         axes upon which they depend are at their zero points.
    
         When specifying detector axes, the axis is given to the beam centre.
         The location of the beam centre on the detector should be given in the
         DIFFRN_DETECTOR category in distortion-corrected millimetres from
         the (0,0) corner of the detector.
    
         It should be noted that many different origins arise in the definition
         of an experiment.  In particular, as noted above, it is necessary to
         specify the location of the beam centre on the detector in terms
         of the origin of the detector, which is, of course, not coincident
         with the centre of the sample.
         
         The unit cell, reciprocal cell and crystallographic orthogonal 
         Cartesian coordinate system are defined by the CELL and the matrices 
         in the ATOM_SITES category.
         
         THE DIRECT LATTICE (FRACTIONAL COORDINATES)
         
         The direct lattice coordinate system is a system of fractional
         coordinates aligned to the crystal, rather than to the laboratory.
         This is a natural coordinate system for maps and atomic coordinates.
         It is the simplest coordinate system in which to apply symmetry.
         The axes are determined by the cell edges, and are not necessarily
         othogonal.  This coordinate system is not uniquely defined and 
         depends on the cell parameters in the CELL category and the
         settings chosen to index the crystal. 
         
         Molecules in a crystal studied by X-ray diffracraction are organized
         into a repeating regular array of unit cells.  Each unit cell is defined 
         by three vectors, a, b and c.  To quote from Drenth,
         
         
         "The choice of the unit cell is not unique and therefore, guidelines
         have been established for selecting the standard basis vectors and
         the origin.  They are based on symmetry and metric considerations:
         
          "(1)  The axial system should be right handed.
           (2)  The basis vectors should coincide as much as possible with
           directions of highest symmetry."
           (3)  The cell taken should be the smallest one that satisfies
           condition (2)
           (4)  Of all the lattice vectors, none is shorter than a.
           (5)  Of those not directed along a, none is shorter than b.
           (6)  Of those not lying in the ab plane, none is shorter than c.
           (7)  The three angles between the basis vectors a, b and c are
           either all acute (<90\%) or all obtuse (≥90\%)."
         
         These rules do not produce a unique result that is stable under
         the assumption of experimental errors, and the the resulting cell
         may not be primitive.
         
         In this coordinate system, the vector (.5, .5, .5) is in the middle
         of the given unit cell.
         
         Grid coordinates are an important variation on fractional coordinates
         used when working with maps.  In imgCIF, the conversion from
         fractional to grid coordinates is implicit in the array indexing
         specified by _array_structure_list.dimension.  Note that this
         implicit grid-coordinate scheme is 1-based, not zero-based, i.e.
         the origin of the cell for axes along the cell edges with no
         specified _array_structure_list_axis.displacement will have
         grid coordinates of (1,1,1), i.e. array indices of (1,1,1).
         
         THE ORTHOGONAL CARTESIAN COORDINATE SYSTEM (REAL SPACE)
         
         The orthogonal Cartesian coordinate system is a transformation of
         the direct lattice to the actual physical coordinates of atoms in
         space.  It is similar to the laboratory coordinate system, but
         is anchored to and moves with the crystal, rather than being
         schored to the laboratory.  The transformation from fractional
         to orthogonal cartesian coordinates is given by the
                  _atom_sites.Cartn_transf_matrix[i][j]  and
                  _atom_sites.Cartn_transf_vector[i]
         tags.  A common choice for the matrix of the transformation is 
         given in the 1992 PDB format document
         
                  | a      b cos(\g)   c cos(\b)                            |
                  | 0      b sin(\g)   c (cos(\a) - cos(\b)cos(\g))/sin(\g) |
                  | 0      0           V/(a b sin(\g))                      |
         
         This is a convenient coordinate system in which to do fitting
         of models to maps and in which to understand the chemistry of
         a molecule.
         
         THE RECIPROCAL LATTICE
         
         The reciprocal lattice coordinate system is used for diffraction
         intensitities.  It is based on the reciprocal cell, the dual of the cell,
         in which reciprocal cell edges are derived from direct cell faces:
         
            a* = bc sin(\a)/V  b* = ac sin(\b)/V  c* = ab sin(\g)/V
            cos(\a*) = (cos(\b) cos(\g) - cos(\a))/(sin(\b) sin(\g))
            cos(\b*) = (cos(\a) cos(\g) - cos(\b))/(sin(\a) sin(\g))
            cos(\g*) = (cos(\a) cos(\b) - cos(\g))/(sin(\a) sin(\b))
            V = abc SQRT(1 - cos(\a)^2^ 
                           - cos(\b)^2^ 
                           - cos(\g)^2^ 
                           + 2 cos(\a) cos(\b) cos(\g) )
         
         In this form the dimensions of the reciprocal lattice are in reciprocal
         \%Angstroms (\%A^-1^).  A dimensionless form can be obtained by 
         multiplying by the wavelength.  Reflections are commonly indexed against
         this coordinate system as (h, k, l) triples.
         
         
         References:
         
         Drenth, J., "Introduction to basic crystallography." chapter
         2.1 in Rossmann, M. G. and Arnold, E. "Crystallography of 
         biological macromolecules", Volume F of the IUCr's "International 
         tables for crystallography", Kluwer, Dordrecht 2001, pp 44 -- 63
    
         Leslie, A. G. W. and Powell, H. (2004). MOSFLM v6.11.
         MRC Laboratory of Molecular Biology, Hills Road, Cambridge, England.
         http://www.CCP4.ac.uk/dist/X-windows/Mosflm/.
         
         Stout, G. H. and Jensen, L. H., "X-ray structure determination",
         2nd ed., Wiley, New York, 1989, 453 pp.
         
         __, "PROTEIN DATA BANK ATOMIC COORDINATE AND BIBLIOGRAPHIC ENTRY
         FORMAT DESCRIPTION," Brookhaven National Laboratory, February 1992.
    ;
        _category.id                   axis
        _category.mandatory_code       no
         loop_
        _category_key.name          '_axis.id'
                                    '_axis.equipment'
         loop_
        _category_group.id           'inclusive_group'
                                     'axis_group'
                                     'diffrn_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;       Example 1 -
    
            This example shows the axis specification of the axes of a kappa-
            geometry goniometer [see Stout, G. H. & Jensen, L. H. (1989). X-ray
            structure determination. A practical
            guide, 2nd ed. p. 134. New York: Wiley Interscience].
    
            There are three axes specified, and no offsets.  The outermost axis,
            omega, is pointed along the X axis.  The next innermost axis, kappa,
            is at a 50 degree angle to the X axis, pointed away from the source.
            The innermost axis, phi, aligns with the X axis when omega and
            phi are at their zero points.  If T-omega, T-kappa and T-phi
            are the transformation matrices derived from the axis settings,
            the complete transformation would be:
                X' = (T-omega) (T-kappa) (T-phi) X
    ;
    ;
             loop_
            _axis.id
            _axis.type
            _axis.equipment
            _axis.depends_on
            _axis.vector[1] _axis.vector[2] _axis.vector[3]
            omega rotation goniometer     .    1        0        0
            kappa rotation goniometer omega    -.64279  0       -.76604
            phi   rotation goniometer kappa    1        0        0
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;       Example 2 -
    
            This example shows the axis specification of the axes of a
            detector, source and gravity.  The order has been changed as a
            reminder that the ordering of presentation of tokens is not
            significant.  The centre of rotation of the detector has been taken
            to be 68 millimetres in the direction away from the source.
    ;
    ;
            loop_
            _axis.id
            _axis.type
            _axis.equipment
            _axis.depends_on
            _axis.vector[1] _axis.vector[2] _axis.vector[3]
            _axis.offset[1] _axis.offset[2] _axis.offset[3]
            source       .        source     .       0     0     1   . . .
            gravity      .        gravity    .       0    -1     0   . . .
            tranz     translation detector rotz      0     0     1   0 0 -68
            twotheta  rotation    detector   .       1     0     0   . . .
            roty      rotation    detector twotheta  0     1     0   0 0 -68
            rotz      rotation    detector roty      0     0     1   0 0 -68
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;       Example 3 -
    
            This example show the axis specification of the axes for a map,
            using fractional coordinates.  Each cell edge has been divided
            into a grid of 50 divisions in the ARRAY_STRUCTURE_LIST_AXIS 
            category.  The map is using only the first octant of the grid
            in the ARRAY_STRUCTURE_LIST category.
    
            The fastest changing axis is the gris along A, then along B,
            and the slowest is along C. 
            
            The map sampling is being done in the middle of each grid
            division
            
    ;
    ;
            loop_
            _axis.id
            _axis.system
            _axis.vector[1] _axis.vector[2] _axis.vector[3]
            CELL_A_AXIS    fractional       1 0 0
            CELL_B_AXIS    fractional       0 1 0
            CELL_C_AXIS    fractional       0 0 1
            
            loop_
            _array_structure_list.array_id
            _array_structure_list.index
            _array_structure_list.dimension
            _array_structure_list.precedence
            _array_structure_list.direction
            _array_structure_list.axis_id
            MAP 1 25 1 increasing CELL_A_AXIS
            MAP 1 25 2 increasing CELL_B_AXIS
            MAP 1 25 3 increasing CELL_C_AXIS
            
            loop_
            _array_structure_list_axis.axis_id
            _array_structure_list_axis.fract_displacement
            _array_structure_list_axis.fract_displacement_increment
            CELL_A_AXIS 0.01 0.02
            CELL_B_AXIS 0.01 0.02
            CELL_C_AXIS 0.01 0.02
    
            
            
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;       Example 4 -
    
            This example show the axis specification of the axes for a map,
            this time as orthogonal \%Angstroms, using the same coordinate system 
            as for the atomic coordinates.  The map is sampling every 1.5
            \%Angstroms (1.5e-7 millimeters) in a map segment 37.5 \%Angstroms on 
            a side.
            
    ;
    ;
            loop_
            _axis.id
            _axis.system
            _axis.vector[1] _axis.vector[2] _axis.vector[3]
            X    orthogonal       1 0 0
            Y    orthogonal       0 1 0
            Z    orthogonal       0 0 1
            
                    loop_
            _array_structure_list.array_id
            _array_structure_list.index
            _array_structure_list.dimension
            _array_structure_list.precedence
            _array_structure_list.direction
            _array_structure_list.axis_id
            MAP 1 25 1 increasing X
            MAP 2 25 2 increasing Y
            MAP 3 25 3 increasing Z
            
            loop_
            _array_structure_list_axis.axis_id
            _array_structure_list_axis.displacement
            _array_structure_list_axis.displacement_increment
            X 7.5e-8 1.5e-7
            Y 7.5e-8 1.5e-7
            Z 7.5e-8 1.5e-7
    
    
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__axis.depends_on
        _item_description.description
    ;             The value of _axis.depends_on specifies the next outermost
                  axis upon which this axis depends.
    
                  This item is a pointer to _axis.id in the same category.
    ;
        _item.name                      '_axis.depends_on'
        _item.category_id                 axis
        _item.mandatory_code              no
    
         save_
    
    
    save__axis.equipment
        _item_description.description
    ;             The value of  _axis.equipment specifies the type of
                  equipment using the axis:  'goniometer', 'detector',
                  'gravity', 'source' or 'general'.
    ;
        _item.name                      '_axis.equipment'
        _item.category_id                 axis
        _item.mandatory_code              no
        _item_type.code                   ucode
        _item_default.value               general
         loop_
        _item_enumeration.value
        _item_enumeration.detail   goniometer
                                  'equipment used to orient or position samples'
                                   detector
                                  'equipment used to detect reflections'
                                   general
                                  'equipment used for general purposes'
                                   gravity
                                  'axis specifying the downward direction'
                                   source
                                  'axis specifying the direction sample to source'
    
         save_
    
    
    save__axis.offset[1]
        _item_description.description
    ;              The [1] element of the three-element vector used to specify
                   the offset to the base of a rotation or translation axis.
    
                   The vector is specified in millimetres.
    ;
        _item.name                  '_axis.offset[1]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    
    save__axis.offset[2]
        _item_description.description
    ;              The [2] element of the three-element vector used to specify
                   the offset to the base of a rotation or translation axis.
    
                   The vector is specified in millimetres.
    ;
        _item.name                  '_axis.offset[2]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    
    save__axis.offset[3]
        _item_description.description
    ;              The [3] element of the three-element vector used to specify
                   the offset to the base of a rotation or translation axis.
    
                   The vector is specified in millimetres.
    ;
        _item.name                  '_axis.offset[3]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    
    save__axis.id
        _item_description.description
    ;             The value of _axis.id must uniquely identify
                  each axis relevant to the experiment.  Note that multiple
                  pieces of equipment may share the same axis (e.g. a twotheta
                  arm), so the category key for AXIS also includes the
                  equipment.
    ;
        loop_
        _item.name
        _item.category_id
        _item.mandatory_code
             '_axis.id'                         axis                    yes
             '_array_structure_list_axis.axis_id'
                                                array_structure_list_axis
                                                                        yes
             '_diffrn_detector_axis.axis_id'    diffrn_detector_axis    yes
             '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes
             '_diffrn_scan_axis.axis_id'        diffrn_scan_axis        yes
             '_diffrn_scan_frame_axis.axis_id'  diffrn_scan_frame_axis  yes
    
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
             '_axis.depends_on'                   '_axis.id'
             '_array_structure_list_axis.axis_id' '_axis.id'
             '_diffrn_detector_axis.axis_id'      '_axis.id'
             '_diffrn_measurement_axis.axis_id'   '_axis.id'
             '_diffrn_scan_axis.axis_id'          '_axis.id'
             '_diffrn_scan_frame_axis.axis_id'    '_axis.id'
    
         save_
    
    save__axis.system
        _item_description.description
    ;             The value of  _axis.system specifies the coordinate
                  system used to define the axis: 'laboratory', 'direct', 
                  'orthogonal', 'reciprocal' or 'abstract'.
    ;
        _item.name                      '_axis.system'
        _item.category_id                 axis
        _item.mandatory_code              no
        _item_type.code                   ucode
        _item_default.value               laboratory
         loop_
        _item_enumeration.value
        _item_enumeration.detail   
    
    laboratory
    ;  the axis is referenced to the imgCIF standard laboratory Cartesian
       coordinate system
    ;
    
    direct
    ;  the axis is referenced to the direct lattice
    ;
    
    orthogonal
    ;  the axis is referenced to the cell Cartesian orthogonal coordinates
    ;
    
    reciprocal
    ;  the axis is referenced to the reciprocal lattice
    ;
    
    abstract
    ;  the axis is referenced to abstract Cartesian cooridinate system
    ;
    
         save_
    
    
    save__axis.type
        _item_description.description
    ;             The value of _axis.type specifies the type of
                  axis:  'rotation' or 'translation' (or 'general' when
                  the type is not relevant, as for gravity).
    ;
        _item.name                      '_axis.type'
        _item.category_id                 axis
        _item.mandatory_code              no
        _item_type.code                   ucode
        _item_default.value               general
         loop_
        _item_enumeration.value
        _item_enumeration.detail      rotation
                                     'right-handed axis of rotation'
                                      translation
                                     'translation in the direction of the axis'
                                      general
                                     'axis for which the type is not relevant'
    
         save_
    
    
    save__axis.vector[1]
        _item_description.description
    ;              The [1] element of the three-element vector used to specify
                   the direction of a rotation or translation axis.
                   The vector should be normalized to be a unit vector and
                   is dimensionless.
    ;
        _item.name                  '_axis.vector[1]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
         save_
    
    save__axis.vector[2]
        _item_description.description
    ;              The [2] element of the three-element vector used to specify
                   the direction of a rotation or translation axis.
                   The vector should be normalized to be a unit vector and
                   is dimensionless.
    ;
        _item.name                  '_axis.vector[2]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
         save_
    
    save__axis.vector[3]
        _item_description.description
    ;              The [3] element of the three-element vector used to specify
                   the direction of a rotation or translation axis.
                   The vector should be normalized to be a unit vector and
                   is dimensionless.
    ;
        _item.name                  '_axis.vector[3]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
         save_
    
    
    
    #####################
    # DIFFRN_DATA_FRAME #
    #####################
    
    
    save_DIFFRN_DATA_FRAME
        _category.description
    ;             Data items in the DIFFRN_DATA_FRAME category record
                  the details about each frame of data.
    
                  The items in this category were previously in a
                  DIFFRN_FRAME_DATA category, which is now deprecated.
                  The items from the old category are provided
                  as aliases but should not be used for new work.
    ;
        _category.id                   diffrn_data_frame
        _category.mandatory_code       no
         loop_
        _category_key.name             '_diffrn_data_frame.id'
                                       '_diffrn_data_frame.detector_element_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;   Example 1 - A frame containing data from 4 frame elements.
                    Each frame element has a common array configuration
                    'array_1' described in ARRAY_STRUCTURE and related
                    categories.  The data for each detector element are
                    stored in four groups of binary data in the
                    ARRAY_DATA category, linked by the array_id and
                    binary_id.
    ;
    ;
            loop_
            _diffrn_data_frame.id
            _diffrn_data_frame.detector_element_id
            _diffrn_data_frame.array_id
            _diffrn_data_frame.binary_id
            frame_1   d1_ccd_1  array_1  1
            frame_1   d1_ccd_2  array_1  2
            frame_1   d1_ccd_3  array_1  3
            frame_1   d1_ccd_4  array_1  4
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
    
    
    save__diffrn_data_frame.array_id
        _item_description.description
    ;             This item is a pointer to _array_structure.id in the
                  ARRAY_STRUCTURE category.
    ;
        _item.name                  '_diffrn_data_frame.array_id'
        _item.category_id             diffrn_data_frame
        _item.mandatory_code          implicit
        _item_aliases.alias_name    '_diffrn_frame_data.array_id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         save_
    
    
    save__diffrn_data_frame.binary_id
        _item_description.description
    ;             This item is a pointer to _array_data.binary_id in the
                  ARRAY_DATA category.
    ;
        _item.name                  '_diffrn_data_frame.binary_id'
        _item.category_id             diffrn_data_frame
        _item.mandatory_code          implicit
        _item_aliases.alias_name    '_diffrn_frame_data.binary_id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               int
         save_
    
    
    save__diffrn_data_frame.center_fast
         _item_description.description
    ;             The value of _diffrn_data_frame.center_fast is 
                  the fast index axis beam center position relative to the detector
                  element face in the units specified in the data item
                  '_diffrn_data_frame.center_units' along the fast
                  axis of the detector from the center of the first pixel to 
                  the point at which the Z-axis (which should be colinear with the
                  beam) intersects the face of the detector, if in fact is does.
                  At the time of the measurement the current setting of detector
                  positioner given frame are used.
    
                  It is important to note that for measurements in millimetres,
                  the sense of the axis is used, rather than the sign of the 
                  pixel-to-pixel increments.
    
    ;
         _item.name '_diffrn_data_frame.center_fast'
         _item.category_id             diffrn_data_frame
         _item.mandatory_code          no
         _item_type.code               float
    
         save_
    
    
    save__diffrn_data_frame.center_slow
         _item_description.description
    ;             The value of _diffrn_data_frame.center_slow is
                  the slow index axis beam center position relative to the detector
                  element face in the units specified in the data item
                  '_diffrn_data_frame.center_units' along the slow
                  axis of the detector from the center of the first pixel to 
                  the point at which the Z-axis (which should be colinear with the
                  beam) intersects the face of the detector, if in fact is does.
                  At the time of the measurement the current setting of detector
                  positioner given frame are used.
    
                  It is important to note that the sense of the axis is used,
                  rather than the sign of the pixel-to-pixel increments.
    
    ;
         _item.name '_diffrn_data_frame.center_slow'
         _item.category_id             diffrn_data_frame
         _item.mandatory_code          no
         _item_type.code               float
    
         save_
    
    
    save__diffrn_data_frame.center_units
         _item_description.description
    ;             The value of _diffrn_data_frame.center_units
                  specifies the units in which the values of 
                  '_diffrn_data_frame.center_fast' and
                  '_diffrn_data_frame.center_slow'
                  are presented.  The default is 'mm' for millimetres.  The 
                  alternatives are 'pixels' and 'bins'.  In all cases the
                  center distances are measured from the center of the
                  first pixel, i.e. in a 2x2 binning, the measuring origin
                  is offset from the centers of the bins by one half pixel
                  towards the first pixel.
                  
                  If 'bins' is specified, the data in
                      '_array_intensities.pixel_fast_bin_size',
                      '_array_intensities.pixel_slow_bin_size', and
                      '_array_intensities.pixel_binning_method'
                  is used to define the binning scheme.
    
    
    ;
         _item.name '_diffrn_data_frame.center_units'
         _item.category_id             diffrn_data_frame
         _item.mandatory_code          no
         _item_type.code               code
          loop_
         _item_enumeration.value
         _item_enumeration.detail
                                       mm        'millimetres'
                                       pixels    'detector pixels'
                                       bins      'detector bins'
    
         save_
    
    
    
    
    save__diffrn_data_frame.detector_element_id
        _item_description.description
    ;              This item is a pointer to _diffrn_detector_element.id
                   in the DIFFRN_DETECTOR_ELEMENT category.
    ;
        _item.name                  '_diffrn_data_frame.detector_element_id'
        _item.category_id             diffrn_data_frame
        _item.mandatory_code          yes
        _item_aliases.alias_name    '_diffrn_frame_data.detector_element_id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         save_
    
    
    save__diffrn_data_frame.id
        _item_description.description
    ;             The value of _diffrn_data_frame.id must uniquely identify
                  each complete frame of data.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
               '_diffrn_data_frame.id'        diffrn_data_frame  yes
               '_diffrn_refln.frame_id'       diffrn_refln       yes
               '_diffrn_scan.frame_id_start'  diffrn_scan        yes
               '_diffrn_scan.frame_id_end'    diffrn_scan        yes
               '_diffrn_scan_frame.frame_id'  diffrn_scan_frame  yes
               '_diffrn_scan_frame_axis.frame_id'
                                              diffrn_scan_frame_axis
                                                                 yes
        _item_aliases.alias_name    '_diffrn_frame_data.id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_diffrn_refln.frame_id'        '_diffrn_data_frame.id'
               '_diffrn_scan.frame_id_start'   '_diffrn_data_frame.id'
               '_diffrn_scan.frame_id_end'     '_diffrn_data_frame.id'
               '_diffrn_scan_frame.frame_id'   '_diffrn_data_frame.id'
               '_diffrn_scan_frame_axis.frame_id'
                                               '_diffrn_data_frame.id'
         save_
    
    
    save__diffrn_data_frame.details
         _item_description.description
    ;              The value of _diffrn_data_frame.details should give a
                   description of special aspects of each frame of data.
    
                   This is an appropriate location in which to record
                   information from vendor headers as presented in those
                   headers, but it should never be used as a substitute
                   for providing the fully parsed information within
                   the appropriate imgCIF/CBF categories.
                   
                   Normally, when a conversion from a miniCBF has been done
                   the data from '_array_data.header_convention'
                   should be transferred to this data item and 
                   '_array_data.header_convention'
                   should be removed.
    ;
        _item.name                  '_diffrn_data_frame.details'
        _item.category_id             diffrn_data_frame
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_frame_data.details'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.4
        _item_type.code               text
         loop_
        _item_examples.case
        _item_examples.detail
    ;
     HEADER_BYTES = 512;
     DIM = 2;
     BYTE_ORDER = big_endian;
     TYPE = unsigned_short;
     SIZE1 = 3072;
     SIZE2 = 3072;
     PIXEL_SIZE = 0.102588;
     BIN = 2x2;
     DETECTOR_SN = 901;
     TIME = 29.945155;
     DISTANCE = 200.000000;
     PHI = 85.000000;
     OSC_START = 85.000000;
     OSC_RANGE = 1.000000;
     WAVELENGTH = 0.979381;
     BEAM_CENTER_X = 157.500000;
     BEAM_CENTER_Y = 157.500000;
     PIXEL SIZE = 0.102588;
     OSCILLATION RANGE = 1;
     EXPOSURE TIME = 29.9452;
     TWO THETA = 0;
     BEAM CENTRE = 157.5 157.5;
    ;
    ;               Example of header information extracted from an ADSC Quantum
                    315 detector header by CBFlib_0.7.6.  Image provided by Chris
                    Nielsen of ADSC from a data collection at SSRL beamline 1-5.
    ;
          save_
    
    
    
    ##########################################################################
    #  The following is a restatement of the mmCIF DIFFRN_DETECTOR,          #
    #  DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for      #
    #  the CBF/imgCIF extensions                                             #
    ##########################################################################
    
    ###################
    # DIFFRN_DETECTOR #
    ###################
    
    
    save_DIFFRN_DETECTOR
        _category.description
    ;              Data items in the DIFFRN_DETECTOR category describe the
                   detector used to measure the scattered radiation, including
                   any analyser and post-sample collimation.
    ;
        _category.id                  diffrn_detector
        _category.mandatory_code      no
         loop_
        _category_key.name          '_diffrn_detector.diffrn_id'
                                    '_diffrn_detector.id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;   Example 1 - based on PDB entry 5HVP and laboratory records for the
                    structure corresponding to PDB entry 5HVP.
    ;
    ;
        _diffrn_detector.diffrn_id             'd1'
        _diffrn_detector.detector              'multiwire'
        _diffrn_detector.type                  'Siemens'
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__diffrn_detector.details
        _item_description.description
    ;              A description of special aspects of the radiation detector.
    ;
        _item.name                  '_diffrn_detector.details'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_detector_details'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code                   text
        _item_examples.case        'slow mode'
         save_
    
    
    save__diffrn_detector.detector
        _item_description.description
    ;              The general class of the radiation detector.
    ;
        _item.name                  '_diffrn_detector.detector'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
         loop_
        _item_aliases.alias_name
        _item_aliases.dictionary
        _item_aliases.version       '_diffrn_radiation_detector'
                                      cifdic.c91
                                      1.0
                                    '_diffrn_detector'
                                      cif_core.dic
                                      2.0
        _item_type.code               text
         loop_
        _item_examples.case          'photographic film'
                                     'scintillation counter'
                                     'CCD plate'
                                     'BF~3~ counter'
         save_
    
    
    save__diffrn_detector.diffrn_id
        _item_description.description
    ;              This data item is a pointer to _diffrn.id in the DIFFRN
                   category.
    
                   The value of _diffrn.id uniquely defines a set of
                   diffraction data.
    ;
        _item.name                  '_diffrn_detector.diffrn_id'
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_detector.dtime
        _item_description.description
    ;              The deadtime in microseconds of the detector(s) used to
                   measure the diffraction intensities.
    ;
        _item.name                  '_diffrn_detector.dtime'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
         loop_
        _item_aliases.alias_name
        _item_aliases.dictionary
        _item_aliases.version       '_diffrn_radiation_detector_dtime'
                                      cifdic.c91
                                      1.0
                                    '_diffrn_detector_dtime'
                                      cif_core.dic
                                      2.0
         loop_
        _item_range.maximum
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
        _item_units.code              microseconds
         save_
    
    
    save__diffrn_detector.id
        _item_description.description
    ;              The value of _diffrn_detector.id must uniquely identify
                   each detector used to collect each diffraction data set.
    
                   If the value of _diffrn_detector.id is not given, it is
                   implicitly equal to the value of
                   _diffrn_detector.diffrn_id.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
                 '_diffrn_detector.id'         diffrn_detector       implicit
                 '_diffrn_detector_axis.detector_id'
                                               diffrn_detector_axis       yes
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_detector_axis.detector_id'
                                             '_diffrn_detector.id'
    
        _item_type.code               code
         save_
    
    
    save__diffrn_detector.number_of_axes
        _item_description.description
    ;              The value of _diffrn_detector.number_of_axes gives the
                   number of axes of the positioner for the detector identified
                   by _diffrn_detector.id.
    
                   The word 'positioner' is a general term used in
                   instrumentation design for devices that are used to change
                   the positions of portions of apparatus by linear
                   translation, rotation or combinations of such motions.
    
                   Axes which are used to provide a coordinate system for the
                   face of an area detetctor should not be counted for this
                   data item.
    
                   The description of each axis should be provided by entries
                   in DIFFRN_DETECTOR_AXIS.
    ;
        _item.name                  '_diffrn_detector.number_of_axes'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
         loop_
        _item_range.maximum
        _item_range.minimum           .   1
                                      1   1
        _item_type.code               int
         save_
    
    
    save__diffrn_detector.type
        _item_description.description
    ;              The make, model or name of the detector device used.
    ;
        _item.name                  '_diffrn_detector.type'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_detector_type'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         save_
    
    
    ########################
    # DIFFRN_DETECTOR_AXIS #
    ########################
    
    
    save_DIFFRN_DETECTOR_AXIS
        _category.description
    ;    Data items in the DIFFRN_DETECTOR_AXIS category associate
         axes with detectors.
    ;
        _category.id                   diffrn_detector_axis
        _category.mandatory_code       no
         loop_
        _category_key.name          '_diffrn_detector_axis.detector_id'
                                    '_diffrn_detector_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_detector_axis.axis_id
        _item_description.description
    ;              This data item is a pointer to _axis.id in
                   the AXIS category.
    ;
        _item.name                  '_diffrn_detector_axis.axis_id'
        _item.category_id             diffrn_detector_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_detector_axis.detector_id
        _item_description.description
    ;              This data item is a pointer to _diffrn_detector.id in
                   the DIFFRN_DETECTOR category.
    
                   This item was previously named _diffrn_detector_axis.id
                   which is now a deprecated name.  The old name is
                   provided as an alias but should not be used for new work.
    ;
        _item.name                  '_diffrn_detector_axis.detector_id'
        _item.category_id             diffrn_detector_axis
        _item.mandatory_code          yes
        _item_aliases.alias_name    '_diffrn_detector_axis.id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         save_
    
    
    ###########################
    # DIFFRN_DETECTOR_ELEMENT #
    ###########################
    
    
    save_DIFFRN_DETECTOR_ELEMENT
        _category.description
    ;             Data items in the DIFFRN_DETECTOR_ELEMENT category record
                  the details about spatial layout and other characteristics
                  of each element of a detector which may have multiple elements.
    
                  In most cases, giving more detailed information
                  in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS
                  is preferable to simply providing the centre of the
                  detector element.
    ;
        _category.id                   diffrn_detector_element
        _category.mandatory_code       no
         loop_
        _category_key.name             '_diffrn_detector_element.id'
                                       '_diffrn_detector_element.detector_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;       Example 1 - Detector d1 is composed of four CCD detector elements,
            each 200 mm by 200 mm, arranged in a square, in the pattern
    
                       1     2
                          *
                       3     4
    
            Note that the beam centre is slightly displaced from each of the
            detector elements, just beyond the lower right corner of 1,
            the lower left corner of 2, the upper right corner of 3 and
            the upper left corner of 4.  For each element, the detector
            face coordiate system, is assumed to have the fast axis
            running from left to right and the slow axis running from
            top to bottom with the origin at the top left corner.
    ;
    ;
            loop_
            _diffrn_detector_element.detector_id
            _diffrn_detector_element.id
            _diffrn_detector_element.reference_center_fast
            _diffrn_detector_element.reference_center_slow
            _diffrn_detector_element.reference_center_units
            d1     d1_ccd_1  201.5 201.5  mm
            d1     d1_ccd_2  -1.8  201.5  mm
            d1     d1_ccd_3  201.6  -1.4  mm
            d1     d1_ccd_4  -1.7   -1.5  mm
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
    
    
    
    save__diffrn_detector_element.id
        _item_description.description
    ;             The value of _diffrn_detector_element.id must uniquely
                  identify each element of a detector.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
               '_diffrn_detector_element.id'
               diffrn_detector_element
               yes
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_diffrn_data_frame.detector_element_id'
               '_diffrn_detector_element.id'
    
         save_
    
    
    save__diffrn_detector_element.detector_id
        _item_description.description
    ;              This item is a pointer to _diffrn_detector.id
                   in the DIFFRN_DETECTOR category.
    ;
        _item.name                  '_diffrn_detector_element.detector_id'
        _item.category_id             diffrn_detector_element
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    save__diffrn_detector_element.reference_center_fast
         _item_description.description
    ;             The value of _diffrn_detector_element.reference_center_fast is 
                  the fast index axis beam center position relative to the detector
                  element face in the units specified in the data item
                  '_diffrn_detector_element.reference_center_units' along the fast
                  axis of the detector from the center of the first pixel to 
                  the point at which the Z-axis (which should be colinear with the 
                  beam) intersects the face of the detector, if in fact is does.   
                  At the time of the measurement all settings of the detector
                  positioner should be at their reference settings.  If more than 
                  one reference setting has been used the value given whould be 
                  representive of the beam center as determined from the ensemble 
                  of settings.
    
                  It is important to note that for measurements in millimetres,
                  the sense of the axis is used, rather than the sign of the 
                  pixel-to-pixel increments.
    
    ;
         _item.name '_diffrn_detector_element.reference_center_fast'
         _item.category_id             diffrn_detector_element
         _item.mandatory_code          no
         _item_type.code               float
    
         save_
    
    
    save__diffrn_detector_element.reference_center_slow
         _item_description.description
    ;             The value of _diffrn_detector_element.reference_center_slow is
                  the slow index axis beam center position relative to the detector
                  element face in the units specified in the data item
                  '_diffrn_detector_element.reference_center_units' along the slow
                  axis of the detector from the center of the first pixel to 
                  the point at which the Z-axis (which should be colinear with the
                  beam) intersects the face of the detector, if in fact is does.
                  At the time of the measurement all settings of the detector
                  positioner should be at their reference settings.  If more than
                  one reference setting has been used the value givien whould be 
                  representive of the beam center as determined from the ensemble
                  of settings.
    
                  It is important to note that the sense of the axis is used,
                  rather than the sign of the pixel-to-pixel increments.
    
    ;
         _item.name '_diffrn_detector_element.reference_center_slow'
         _item.category_id             diffrn_detector_element
         _item.mandatory_code          no
         _item_type.code               float
    
         save_
    
    
    save__diffrn_detector_element.reference_center_units
         _item_description.description
    ;             The value of _diffrn_detector_element.reference_center_units
                  specifies the units in which the values of 
                  '_diffrn_detector_element.reference_center_fast' and
                  '_diffrn_detector_element.reference_center_slow'
                  are presented.  The default is 'mm' for millimetres.  The 
                  alternatives are 'pixels' and 'bins'.  In all cases the
                  center distances are measured from the center of the
                  first pixel, i.e. in a 2x2 binning, the measuring origin
                  is offset from the centers of the bins by one half pixel
                  towards the first pixel.
                  
                  If 'bins' is specified, the data in
                      '_array_intensities.pixel_fast_bin_size',
                      '_array_intensities.pixel_slow_bin_size', and
                      '_array_intensities.pixel_binning_method'
                  is used to define the binning scheme.
    
    
    ;
         _item.name '_diffrn_detector_element.reference_center_units'
         _item.category_id             diffrn_detector_element
         _item.mandatory_code          no
         _item_type.code               code
          loop_
         _item_enumeration.value
         _item_enumeration.detail
                                       mm        'millimetres'
                                       pixels    'detector pixels'
                                       bins      'detector bins'
    
         save_
    
    
    ########################
    ## DIFFRN_MEASUREMENT ##
    ########################
    
    
    save_DIFFRN_MEASUREMENT
        _category.description
    ;              Data items in the DIFFRN_MEASUREMENT category record details
                   about the device used to orient and/or position the crystal
                   during data measurement and the manner in which the
                   diffraction data were measured.
    ;
        _category.id                  diffrn_measurement
        _category.mandatory_code      no
         loop_
        _category_key.name          '_diffrn_measurement.device'
                                    '_diffrn_measurement.diffrn_id'
                                    '_diffrn_measurement.id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;    Example 1 - based on PDB entry 5HVP and laboratory records for the
                     structure corresponding to PDB entry 5HVP
    ;
    ;
        _diffrn_measurement.diffrn_id          'd1'
        _diffrn_measurement.device             '3-circle camera'
        _diffrn_measurement.device_type        'Supper model X'
        _diffrn_measurement.device_details     'none'
        _diffrn_measurement.method             'omega scan'
        _diffrn_measurement.details
        ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector
          angle 22.5 degrees
        ;
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;     Example 2 - based on data set TOZ of Willis, Beckwith & Tozer
                      [Acta Cryst. (1991), C47, 2276-2277].
    ;
    ;
        _diffrn_measurement.diffrn_id       's1'
        _diffrn_measurement.device_type     'Philips PW1100/20 diffractometer'
        _diffrn_measurement.method          'theta/2theta (\q/2\q)'
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__diffrn_measurement.device
        _item_description.description
    ;              The general class of goniometer or device used to support
                   and orient the specimen.
    
                   If the value of _diffrn_measurement.device is not given,
                   it is implicitly equal to the value of
                   _diffrn_measurement.diffrn_id.
    
                   Either _diffrn_measurement.device or
                   _diffrn_measurement.id may be used to link to other
                   categories.  If the experimental setup admits multiple
                   devices, then _diffrn_measurement.id is used to provide
                   a unique link.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
                 '_diffrn_measurement.device'  diffrn_measurement      implicit
                 '_diffrn_measurement_axis.measurement_device'
                                               diffrn_measurement_axis implicit
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_measurement_axis.measurement_device'
                                             '_diffrn_measurement.device'
        _item_aliases.alias_name    '_diffrn_measurement_device'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          '3-circle camera'
                                     '4-circle camera'
                                     'kappa-geometry camera'
                                     'oscillation camera'
                                     'precession camera'
         save_
    
    
    save__diffrn_measurement.device_details
        _item_description.description
    ;              A description of special aspects of the device used to
                   measure the diffraction intensities.
    ;
        _item.name                  '_diffrn_measurement.device_details'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_device_details'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
        _item_examples.case
    ;                                 commercial goniometer modified locally to
                                      allow for 90\% \t arc
    ;
         save_
    
    
    save__diffrn_measurement.device_type
        _item_description.description
    ;              The make, model or name of the measurement device
                   (goniometer) used.
    ;
        _item.name                  '_diffrn_measurement.device_type'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_device_type'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          'Supper model q'
                                     'Huber model r'
                                     'Enraf-Nonius model s'
                                     'home-made'
         save_
    
    
    save__diffrn_measurement.diffrn_id
        _item_description.description
    ;              This data item is a pointer to _diffrn.id in the DIFFRN
                   category.
    ;
        _item.name                  '_diffrn_measurement.diffrn_id'
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_measurement.details
        _item_description.description
    ;              A description of special aspects of the intensity
                   measurement.
    ;
        _item.name                  '_diffrn_measurement.details'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_details'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
        _item_examples.case
    ;                                 440 frames, 0.20 degrees, 150 sec, detector
                                      distance 12 cm, detector angle 22.5 degrees
    ;
         save_
    
    
    save__diffrn_measurement.id
        _item_description.description
    ;              The value of _diffrn_measurement.id must uniquely identify
                   the set of mechanical characteristics of the device used to
                   orient and/or position the sample used during the collection
                   of each diffraction data set.
    
                   If the value of _diffrn_measurement.id is not given, it is
                   implicitly equal to the value of
                   _diffrn_measurement.diffrn_id.
    
                   Either _diffrn_measurement.device or
                   _diffrn_measurement.id may be used to link to other
                   categories.  If the experimental setup admits multiple
                   devices, then _diffrn_measurement.id is used to provide
                   a unique link.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
                 '_diffrn_measurement.id'      diffrn_measurement      implicit
                 '_diffrn_measurement_axis.measurement_id'
                                               diffrn_measurement_axis implicit
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_measurement_axis.measurement_id'
                                             '_diffrn_measurement.id'
    
        _item_type.code               code
         save_
    
    
    save__diffrn_measurement.method
        _item_description.description
    ;              Method used to measure intensities.
    ;
        _item.name                  '_diffrn_measurement.method'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_method'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
        _item_examples.case
          'profile data from theta/2theta (\q/2\q) scans'
         save_
    
    
    save__diffrn_measurement.number_of_axes
        _item_description.description
    ;              The value of _diffrn_measurement.number_of_axes gives the
                   number of axes of the positioner for the goniometer or
                   other sample orientation or positioning device identified
                   by _diffrn_measurement.id.
    
                   The description of the axes should be provided by entries in
                   DIFFRN_MEASUREMENT_AXIS.
    ;
        _item.name                  '_diffrn_measurement.number_of_axes'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
         loop_
        _item_range.maximum
        _item_range.minimum           .   1
                                      1   1
        _item_type.code               int
         save_
    
    
    #                  _diffrn_measurement.sample_detector_distance
    #                  _diffrn_measurement.sample_detector_voffset
    
    save__diffrn_measurement.sample_detector_distance
        _item_description.description
    ;              The value of _diffrn_measurement.sample_detector_distance gives
                   the unsigned distance in millimetres from the sample to the 
                   detector along the beam.
    ;
        _item.name                  '_diffrn_measurement.sample_detector_distance'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
         loop_
        _item_range.maximum
        _item_range.minimum           .   0.0
        _item_type.code               float
        _item_units.code              mm
         save_
    
    save__diffrn_measurement.sample_detector_voffset
        _item_description.description
    ;              The value of _diffrn_measurement.sample_detector_voffset gives
                   the signed distance in millimetres in the vertical
                   direction (positive for up) from the center of
                   the beam to the center of the detector. 
    ;
        _item.name                  '_diffrn_measurement.sample_detector_voffset'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
         loop_
        _item_range.maximum
        _item_range.minimum           .   .
                                      .   .
        _item_type.code               float
        _item_units.code              mm
         save_
    
    
    save__diffrn_measurement.specimen_support
        _item_description.description
    ;              The physical device used to support the crystal during data
                   collection.
    ;
        _item.name                  '_diffrn_measurement.specimen_support'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_specimen_support'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          'glass capillary'
                                     'quartz capillary'
                                     'fiber'
                                     'metal loop'
         save_
    
    
    ###########################
    # DIFFRN_MEASUREMENT_AXIS #
    ###########################
    
    
    save_DIFFRN_MEASUREMENT_AXIS
        _category.description
    ;    Data items in the DIFFRN_MEASUREMENT_AXIS category associate
         axes with goniometers.
    ;
        _category.id                   diffrn_measurement_axis
        _category.mandatory_code       no
         loop_
        _category_key.name
                                  '_diffrn_measurement_axis.measurement_device'
                                    '_diffrn_measurement_axis.measurement_id'
                                    '_diffrn_measurement_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_measurement_axis.axis_id
        _item_description.description
    ;              This data item is a pointer to _axis.id in
                   the AXIS category.
    ;
        _item.name                  '_diffrn_measurement_axis.axis_id'
        _item.category_id             diffrn_measurement_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_measurement_axis.measurement_device
        _item_description.description
    ;              This data item is a pointer to _diffrn_measurement.device
                   in the DIFFRN_MEASUREMENT category.
    ;
        _item.name
          '_diffrn_measurement_axis.measurement_device'
        _item.category_id             diffrn_measurement_axis
        _item.mandatory_code          implicit
        _item_type.code               text
         save_
    
    
    save__diffrn_measurement_axis.measurement_id
        _item_description.description
    ;              This data item is a pointer to _diffrn_measurement.id in
                   the DIFFRN_MEASUREMENT category.
    
                   This item was previously named _diffrn_measurement_axis.id,
                   which is now a deprecated name.  The old name is
                   provided as an alias but should not be used for new work.
    ;
        _item.name                  '_diffrn_measurement_axis.measurement_id'
        _item.category_id             diffrn_measurement_axis
        _item.mandatory_code          implicit
        _item_aliases.alias_name    '_diffrn_measurement_axis.id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         save_
    
    
    ####################
    # DIFFRN_RADIATION #
    ####################
    
    
    save_DIFFRN_RADIATION
        _category.description
    ;              Data items in the DIFFRN_RADIATION category describe
                   the radiation used for measuring diffraction intensities,
                   its collimation and monochromatization before the sample.
    
                   Post-sample treatment of the beam is described by data
                   items in the DIFFRN_DETECTOR category.
    ;
        _category.id                  diffrn_radiation
        _category.mandatory_code      no
        _category_key.name          '_diffrn_radiation.diffrn_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;   Example 1 - based on PDB entry 5HVP and laboratory records for the
                    structure corresponding to PDB entry 5HVP
    ;
    ;
        _diffrn_radiation.diffrn_id            'set1'
    
        _diffrn_radiation.collimation          '0.3 mm double pinhole'
        _diffrn_radiation.monochromator        'graphite'
        _diffrn_radiation.type                 'Cu K\a'
        _diffrn_radiation.wavelength_id         1
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;    Example 2 - based on data set TOZ of Willis, Beckwith & Tozer
                    [Acta Cryst. (1991), C47, 2276-2277].
    ;
    ;
        _diffrn_radiation.wavelength_id    1
        _diffrn_radiation.type             'Cu K\a'
        _diffrn_radiation.monochromator    'graphite'
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    save__diffrn_radiation.collimation
        _item_description.description
    ;              The collimation or focusing applied to the radiation.
    ;
        _item.name                  '_diffrn_radiation.collimation'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_collimation'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          '0.3 mm double-pinhole'
                                     '0.5 mm'
                                     'focusing mirrors'
         save_
    
    
    save__diffrn_radiation.diffrn_id
        _item_description.description
    ;              This data item is a pointer to _diffrn.id in the DIFFRN
                   category.
    ;
        _item.name                  '_diffrn_radiation.diffrn_id'
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    
    save__diffrn_radiation.div_x_source
        _item_description.description
    ;              Beam crossfire in degrees parallel to the laboratory X axis
                   (see AXIS category).
    
                   This is a characteristic of the X-ray beam as it illuminates
                   the sample (or specimen) after all monochromation and
                   collimation.
    
                   This is the standard uncertainty (e.s.d.)  of the directions of
                   photons in the XZ plane around the mean source beam
                   direction.
    
                   Note that for some synchrotrons this value is specified
                   in milliradians, in which case a conversion is needed.
                   To convert a value in milliradians to a value in degrees,
                   multiply by 0.180 and divide by \p.
    ;
        _item.name                  '_diffrn_radiation.div_x_source'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_type.code               float
        _item_units.code              degrees
         save_
    
    
    save__diffrn_radiation.div_y_source
        _item_description.description
    ;              Beam crossfire in degrees parallel to the laboratory Y axis
                   (see AXIS category).
    
                   This is a characteristic of the X-ray beam as it illuminates
                   the sample (or specimen) after all monochromation and
                   collimation.
    
                   This is the standard uncertainty (e.s.d.) of the directions
                   of photons in the YZ plane around the mean source beam
                   direction.
    
                   Note that for some synchrotrons this value is specified
                   in milliradians, in which case a conversion is needed.
                   To convert a value in milliradians to a value in degrees,
                   multiply by 0.180 and divide by \p.
    ;
        _item.name                  '_diffrn_radiation.div_y_source'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_type.code               float
        _item_units.code              degrees
        _item_default.value           0.0
         save_
    
    
    save__diffrn_radiation.div_x_y_source
        _item_description.description
    ;              Beam crossfire correlation degrees^2^ between the
                   crossfire laboratory X-axis component and the crossfire
                   laboratory Y-axis component (see AXIS category).
    
                   This is a characteristic of the X-ray beam as it illuminates
                   the sample (or specimen) after all monochromation and
                   collimation.
    
                   This is the mean of the products of the deviations of the
                   direction of each photon in XZ plane times the deviations
                   of the direction of the same photon in the YZ plane
                   around the mean source beam direction.  This will be zero
                   for uncorrelated crossfire.
    
                   Note that some synchrotrons, this value is specified in
                   milliradians^2^, in which case a conversion would be needed.
                   To go from a value in milliradians^2^ to a value in
                   degrees^2^, multiply by 0.180^2^ and divide by \p^2^.
    
    ;
        _item.name                  '_diffrn_radiation.div_x_y_source'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_type.code               float
        _item_units.code              degrees_squared
        _item_default.value           0.0
         save_
    
    save__diffrn_radiation.filter_edge
        _item_description.description
    ;              Absorption edge in \%Angstroms of the radiation filter used.
    ;
        _item.name                  '_diffrn_radiation.filter_edge'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_filter_edge'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
        _item_units.code              angstroms
         save_
    
    save__diffrn_radiation.inhomogeneity
        _item_description.description
    ;              Half-width in millimetres of the incident beam in the
                   direction perpendicular to the diffraction plane.
    ;
        _item.name                  '_diffrn_radiation.inhomogeneity'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_inhomogeneity'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    save__diffrn_radiation.monochromator
        _item_description.description
    ;              The method used to obtain monochromatic radiation. If a
                   monochromator crystal is used, the material and the
                   indices of the Bragg reflection are specified.
    ;
        _item.name                  '_diffrn_radiation.monochromator'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_monochromator'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          'Zr filter'
                                     'Ge 220'
                                     'none'
                                     'equatorial mounted graphite'
         save_
    
    save__diffrn_radiation.polarisn_norm
        _item_description.description
    ;              The angle in degrees, as viewed from the specimen, between the
                   perpendicular component of the polarization and the diffraction
                   plane. See _diffrn_radiation_polarisn_ratio.
    ;
        _item.name                  '_diffrn_radiation.polarisn_norm'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_polarisn_norm'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum
        _item_range.minimum           90.0  90.0
                                      90.0 -90.0
                                     -90.0 -90.0
        _item_type.code               float
        _item_units.code              degrees
         save_
    
    save__diffrn_radiation.polarisn_ratio
        _item_description.description
    ;              Polarization ratio of the diffraction beam incident on the
                   crystal. This is the ratio of the perpendicularly polarized to
                   the parallel polarized component of the radiation. The
                   perpendicular component forms an angle of
                   _diffrn_radiation.polarisn_norm to the normal to the
                   diffraction plane of the sample (i.e. the plane containing
                   the incident and reflected beams).
    ;
        _item.name                  '_diffrn_radiation.polarisn_ratio'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_polarisn_ratio'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
         save_
    
    
    
    save__diffrn_radiation.polarizn_source_norm
        _item_description.description
    ;              The angle in degrees, as viewed from the specimen, between
                   the normal to the polarization plane and the laboratory Y
                   axis as defined in the AXIS category.
    
                   Note that this is the angle of polarization of the source
                   photons, either directly from a synchrotron beamline or
                   from a monochromater.
    
                   This differs from the value of
                   _diffrn_radiation.polarisn_norm
                   in that _diffrn_radiation.polarisn_norm refers to
                   polarization relative to the diffraction plane rather than
                   to the laboratory axis system.
    
                   In the case of an unpolarized beam, or a beam with true
                   circular polarization, in which no single plane of
                   polarization can be determined, the plane should be taken
                   as the XZ plane and the angle as 0.
    
                   See _diffrn_radiation.polarizn_source_ratio.
    ;
        _item.name                  '_diffrn_radiation.polarizn_source_norm'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
         loop_
        _item_range.maximum
        _item_range.minimum           90.0   90.0
                                      90.0  -90.0
                                     -90.0  -90.0
        _item_type.code               float
        _item_units.code              degrees
        _item_default.value           0.0
         save_
    
    
    save__diffrn_radiation.polarizn_source_ratio
        _item_description.description
    ;              (Ip-In)/(Ip+In), where Ip is the intensity
                   (amplitude squared) of the electric vector in the plane of
                   polarization and In is the intensity (amplitude squared)
                   of the electric vector in the plane of the normal to the
                   plane of polarization.
    
                   In the case of an unpolarized beam, or a beam with true
                   circular polarization, in which no single plane of
                   polarization can be determined, the plane is to be taken
                   as the XZ plane and the normal is parallel to the Y axis.
    
                   Thus, if there was complete polarization in the plane of
                   polarization, the value of
                   _diffrn_radiation.polarizn_source_ratio would be 1, and
                   for an unpolarized beam
                   _diffrn_radiation.polarizn_source_ratio would have a
                   value of 0.
    
                   If the X axis has been chosen to lie in the plane of
                   polarization, this definition will agree with the definition
                   of 'MONOCHROMATOR' in the Denzo glossary, and values of near
                   1 should be expected for a bending-magnet source.  However,
                   if the X axis were perpendicular to the polarization plane
                   (not a common choice), then the Denzo value would be the
                   negative of _diffrn_radiation.polarizn_source_ratio.
    
                   See http://www.hkl-xray.com for information on Denzo and
                   Otwinowski & Minor (1997).
    
                   This differs both in the choice of ratio and choice of
                   orientation from _diffrn_radiation.polarisn_ratio, which,
                   unlike _diffrn_radiation.polarizn_source_ratio, is
                   unbounded.
    
                   Reference: Otwinowski, Z. & Minor, W. (1997). 'Processing of
                   X-ray diffraction data collected in oscillation mode.' Methods
                   Enzymol. 276, 307-326.
    ;
        _item.name                  '_diffrn_radiation.polarizn_source_ratio'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
         loop_
        _item_range.maximum
        _item_range.minimum           1.0    1.0
                                      1.0   -1.0
                                     -1.0   -1.0
        _item_type.code               float
         save_
    
    
    save__diffrn_radiation.probe
        _item_description.description
    ;              Name of the type of radiation used. It is strongly
                   recommended that this be given so that the
                   probe radiation is clearly specified.
    ;
        _item.name                  '_diffrn_radiation.probe'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_probe'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               line
         loop_
        _item_enumeration.value      'X-ray'
                                     'neutron'
                                     'electron'
                                     'gamma'
         save_
    
    save__diffrn_radiation.type
        _item_description.description
    ;              The nature of the radiation. This is typically a description
                   of the X-ray wavelength in Siegbahn notation.
    ;
        _item.name                  '_diffrn_radiation.type'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_type'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               line
         loop_
        _item_examples.case          'CuK\a'
                                     'Cu K\a~1~'
                                     'Cu K-L~2,3~'
                                     'white-beam'
    
         save_
    
    save__diffrn_radiation.xray_symbol
        _item_description.description
    ;              The IUPAC symbol for the X-ray wavelength for the probe
                   radiation.
    ;
        _item.name                  '_diffrn_radiation.xray_symbol'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_xray_symbol'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               line
         loop_
        _item_enumeration.value
        _item_enumeration.detail     'K-L~3~'
                                     'K\a~1~ in older Siegbahn notation'
                                     'K-L~2~'
                                     'K\a~2~ in older Siegbahn notation'
                                     'K-M~3~'
                                     'K\b~1~ in older Siegbahn notation'
                                     'K-L~2,3~'
                                     'use where K-L~3~ and K-L~2~ are not resolved'
         save_
    
    save__diffrn_radiation.wavelength_id
        _item_description.description
    ;              This data item is a pointer to
                   _diffrn_radiation_wavelength.id in the
                   DIFFRN_RADIATION_WAVELENGTH category.
    ;
        _item.name                  '_diffrn_radiation.wavelength_id'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    
    ################
    # DIFFRN_REFLN #
    ################
    
    
    save_DIFFRN_REFLN
        _category.description
    ;    This category redefinition has been added to extend the key of
         the standard DIFFRN_REFLN category.
    ;
        _category.id                   diffrn_refln
        _category.mandatory_code       no
        _category_key.name             '_diffrn_refln.frame_id'
         loop_
        _category_group.id             'inclusive_group'
                                       'diffrn_group'
         save_
    
    
    save__diffrn_refln.frame_id
        _item_description.description
    ;              This item is a pointer to _diffrn_data_frame.id
                   in the DIFFRN_DATA_FRAME category.
    ;
        _item.name                  '_diffrn_refln.frame_id'
        _item.category_id             diffrn_refln
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    ###############
    # DIFFRN_SCAN #
    ###############
    
    save_DIFFRN_SCAN
        _category.description
    ;    Data items in the DIFFRN_SCAN category describe the parameters of one
         or more scans, relating axis positions to frames.
    
    ;
        _category.id                   diffrn_scan
        _category.mandatory_code       no
        _category_key.name            '_diffrn_scan.id'
         loop_
        _category_group.id            'inclusive_group'
                                      'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;   Example 1 - derived from a suggestion by R. M. Sweet.
    
       The vector of each axis is not given here, because it is provided in
       the AXIS category.  By making _diffrn_scan_axis.scan_id and
       _diffrn_scan_axis.axis_id keys of the DIFFRN_SCAN_AXIS category,
       an arbitrary number of scanning and fixed axes can be specified for a
       scan.  In this example, three rotation axes and one translation axis
       at nonzero values are specified, with one axis stepping.  There is no
       reason why more axes could not have been specified to step. Range
       information has been specified, but note that it can be calculated from
       the  number of frames and the increment, so the data item
       _diffrn_scan_axis.angle_range could be dropped.
    
       Both the sweep data and the data for a single frame are specified.
    
       Note that the information on how the axes are stepped is given twice,
       once in terms of the overall averages in the value of
       _diffrn_scan.integration_time and the values for DIFFRN_SCAN_AXIS,
       and precisely for the given frame in the value for
       _diffrn_scan_frame.integration_time and the values for
       DIFFRN_SCAN_FRAME_AXIS.  If dose-related adjustments are made to
       scan times and nonlinear stepping is done, these values may differ.
       Therefore, in interpreting the data for a particular frame it is
       important to use the frame-specific data.
    ;
    ;
          _diffrn_scan.id                   1
          _diffrn_scan.date_start         '2001-11-18T03:26:42'
          _diffrn_scan.date_end           '2001-11-18T03:36:45'
          _diffrn_scan.integration_time    3.0
          _diffrn_scan.frame_id_start      mad_L2_000
          _diffrn_scan.frame_id_end        mad_L2_200
          _diffrn_scan.frames              201
    
           loop_
          _diffrn_scan_axis.scan_id
          _diffrn_scan_axis.axis_id
          _diffrn_scan_axis.angle_start
          _diffrn_scan_axis.angle_range
          _diffrn_scan_axis.angle_increment
          _diffrn_scan_axis.displacement_start
          _diffrn_scan_axis.displacement_range
          _diffrn_scan_axis.displacement_increment
    
           1 omega 200.0 20.0 0.1 . . .
           1 kappa -40.0  0.0 0.0 . . .
           1 phi   127.5  0.0 0.0 . . .
           1 tranz  . . .   2.3 0.0 0.0
    
          _diffrn_scan_frame.scan_id                   1
          _diffrn_scan_frame.date               '2001-11-18T03:27:33'
          _diffrn_scan_frame.integration_time    3.0
          _diffrn_scan_frame.frame_id            mad_L2_018
          _diffrn_scan_frame.frame_number        18
    
          loop_
          _diffrn_scan_frame_axis.frame_id
          _diffrn_scan_frame_axis.axis_id
          _diffrn_scan_frame_axis.angle
          _diffrn_scan_frame_axis.angle_increment
          _diffrn_scan_frame_axis.displacement
          _diffrn_scan_frame_axis.displacement_increment
    
           mad_L2_018 omega 201.8  0.1 . .
           mad_L2_018 kappa -40.0  0.0 . .
           mad_L2_018 phi   127.5  0.0 . .
           mad_L2_018 tranz  .     .  2.3 0.0
    ;
    
    ;  Example 2 - a more extensive example (R. M. Sweet, P. J. Ellis &
       H. J. Bernstein).
    
       A detector is placed 240 mm along the Z axis from the goniometer.
       This leads to a choice:  either the axes of
       the detector are defined at the origin, and then a Z setting of -240
       is entered, or the axes are defined with the necessary Z offset.
       In this case, the setting is used and the offset is left as zero.
       This axis is called DETECTOR_Z.
    
       The axis for positioning the detector in the Y direction depends
       on the detector Z axis.  This axis is called DETECTOR_Y.
    
       The axis for positioning the detector in the X direction depends
       on the detector Y axis (and therefore on the detector Z axis).
       This axis is called DETECTOR_X.
    
       This detector may be rotated around the Y axis.  This rotation axis
       depends on the three translation axes.  It is called DETECTOR_PITCH.
    
       A coordinate system is defined on the face of the detector in terms of
       2300 0.150 mm pixels in each direction.  The ELEMENT_X axis is used to
       index the first array index of the data array and the ELEMENT_Y
       axis is used to index the second array index.  Because the pixels
       are 0.150mm X 0.150mm, the centre of the first pixel is at (0.075,
       0.075) in this coordinate system.
    ;
    
    ;    ###CBF: VERSION 1.1
    
         data_image_1
    
         # category DIFFRN
         _diffrn.id P6MB
         _diffrn.crystal_id P6MB_CRYSTAL7
    
         # category DIFFRN_SOURCE
         loop_
         _diffrn_source.diffrn_id
         _diffrn_source.source
         _diffrn_source.type
          P6MB synchrotron 'SSRL beamline 9-1'
    
         # category DIFFRN_RADIATION
         loop_
         _diffrn_radiation.diffrn_id
         _diffrn_radiation.wavelength_id
         _diffrn_radiation.monochromator
         _diffrn_radiation.polarizn_source_ratio
         _diffrn_radiation.polarizn_source_norm
         _diffrn_radiation.div_x_source
         _diffrn_radiation.div_y_source
         _diffrn_radiation.div_x_y_source
          P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08
         0.01 0.00
    
         # category DIFFRN_RADIATION_WAVELENGTH
         loop_
         _diffrn_radiation_wavelength.id
         _diffrn_radiation_wavelength.wavelength
         _diffrn_radiation_wavelength.wt
          WAVELENGTH1 0.98 1.0
    
         # category DIFFRN_DETECTOR
         loop_
         _diffrn_detector.diffrn_id
         _diffrn_detector.id
         _diffrn_detector.type
         _diffrn_detector.number_of_axes
          P6MB MAR345-SN26 'MAR 345' 4
    
         # category DIFFRN_DETECTOR_AXIS
         loop_
         _diffrn_detector_axis.detector_id
         _diffrn_detector_axis.axis_id
          MAR345-SN26 DETECTOR_X
          MAR345-SN26 DETECTOR_Y
          MAR345-SN26 DETECTOR_Z
          MAR345-SN26 DETECTOR_PITCH
    
         # category DIFFRN_DETECTOR_ELEMENT
         loop_
         _diffrn_detector_element.id
         _diffrn_detector_element.detector_id
          ELEMENT1 MAR345-SN26
    
         # category DIFFRN_DATA_FRAME
         loop_
         _diffrn_data_frame.id
         _diffrn_data_frame.detector_element_id
         _diffrn_data_frame.array_id
         _diffrn_data_frame.binary_id
          FRAME1 ELEMENT1 ARRAY1 1
    
         # category DIFFRN_MEASUREMENT
         loop_
         _diffrn_measurement.diffrn_id
         _diffrn_measurement.id
         _diffrn_measurement.number_of_axes
         _diffrn_measurement.method
          P6MB GONIOMETER 3 rotation
    
         # category DIFFRN_MEASUREMENT_AXIS
         loop_
         _diffrn_measurement_axis.measurement_id
         _diffrn_measurement_axis.axis_id
          GONIOMETER GONIOMETER_PHI
          GONIOMETER GONIOMETER_KAPPA
          GONIOMETER GONIOMETER_OMEGA
    
         # category DIFFRN_SCAN
         loop_
         _diffrn_scan.id
         _diffrn_scan.frame_id_start
         _diffrn_scan.frame_id_end
         _diffrn_scan.frames
          SCAN1 FRAME1 FRAME1 1
    
         # category DIFFRN_SCAN_AXIS
         loop_
         _diffrn_scan_axis.scan_id
         _diffrn_scan_axis.axis_id
         _diffrn_scan_axis.angle_start
         _diffrn_scan_axis.angle_range
         _diffrn_scan_axis.angle_increment
         _diffrn_scan_axis.displacement_start
         _diffrn_scan_axis.displacement_range
         _diffrn_scan_axis.displacement_increment
          SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0
          SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0
          SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0
          SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0
          SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0
          SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0
          SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0
    
         # category DIFFRN_SCAN_FRAME
         loop_
         _diffrn_scan_frame.frame_id
         _diffrn_scan_frame.frame_number
         _diffrn_scan_frame.integration_time
         _diffrn_scan_frame.scan_id
         _diffrn_scan_frame.date
          FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48
    
         # category DIFFRN_SCAN_FRAME_AXIS
         loop_
         _diffrn_scan_frame_axis.frame_id
         _diffrn_scan_frame_axis.axis_id
         _diffrn_scan_frame_axis.angle
         _diffrn_scan_frame_axis.displacement
          FRAME1 GONIOMETER_OMEGA 12.0 0.0
          FRAME1 GONIOMETER_KAPPA 23.3 0.0
          FRAME1 GONIOMETER_PHI -165.8 0.0
          FRAME1 DETECTOR_Z 0.0 -240.0
          FRAME1 DETECTOR_Y 0.0 0.6
          FRAME1 DETECTOR_X 0.0 -0.5
          FRAME1 DETECTOR_PITCH 0.0 0.0
    
         # category AXIS
         loop_
         _axis.id
         _axis.type
         _axis.equipment
         _axis.depends_on
         _axis.vector[1] _axis.vector[2] _axis.vector[3]
         _axis.offset[1] _axis.offset[2] _axis.offset[3]
          GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . .
          GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279
          0 0.76604 . . .
          GONIOMETER_PHI   rotation goniometer GONIOMETER_KAPPA 1 0 0
         . . .
          SOURCE           general source . 0 0 1 . . .
          GRAVITY          general gravity . 0 -1 0 . . .
          DETECTOR_Z       translation detector . 0 0 1 0 0 0
          DETECTOR_Y       translation detector DETECTOR_Z 0 1 0 0 0 0
          DETECTOR_X       translation detector DETECTOR_Y 1 0 0 0 0 0
          DETECTOR_PITCH   rotation    detector DETECTOR_X 0 1 0 0 0 0
          ELEMENT_X        translation detector DETECTOR_PITCH
         1 0 0 172.43 -172.43 0
          ELEMENT_Y        translation detector ELEMENT_X
         0 1 0 0 0 0
    
         # category ARRAY_STRUCTURE_LIST
         loop_
         _array_structure_list.array_id
         _array_structure_list.index
         _array_structure_list.dimension
         _array_structure_list.precedence
         _array_structure_list.direction
         _array_structure_list.axis_set_id
          ARRAY1 1 2300 1 increasing ELEMENT_X
          ARRAY1 2 2300 2 increasing ELEMENT_Y
    
         # category ARRAY_STRUCTURE_LIST_AXIS
         loop_
         _array_structure_list_axis.axis_set_id
         _array_structure_list_axis.axis_id
         _array_structure_list_axis.displacement
         _array_structure_list_axis.displacement_increment
          ELEMENT_X ELEMENT_X 0.075 0.150
          ELEMENT_Y ELEMENT_Y 0.075 0.150
    
         # category ARRAY_ELEMENT_SIZE
         loop_
         _array_element_size.array_id
         _array_element_size.index
         _array_element_size.size
          ARRAY1 1 150e-6
          ARRAY1 2 150e-6
    
         # category ARRAY_INTENSITIES
         loop_
         _array_intensities.array_id
         _array_intensities.binary_id
         _array_intensities.linearity
         _array_intensities.gain
         _array_intensities.gain_esd
         _array_intensities.overload
         _array_intensities.undefined_value
          ARRAY1 1 linear 1.15 0.2 240000 0
    
          # category ARRAY_STRUCTURE
          loop_
          _array_structure.id
          _array_structure.encoding_type
          _array_structure.compression_type
          _array_structure.byte_order
          ARRAY1 "signed 32-bit integer" packed little_endian
    
         # category ARRAY_DATA
         loop_
         _array_data.array_id
         _array_data.binary_id
         _array_data.data
          ARRAY1 1
         ;
         --CIF-BINARY-FORMAT-SECTION--
         Content-Type: application/octet-stream;
             conversions="X-CBF_PACKED"
         Content-Transfer-Encoding: BASE64
         X-Binary-Size: 3801324
         X-Binary-ID: 1
         X-Binary-Element-Type: "signed 32-bit integer"
         Content-MD5: 07lZFvF+aOcW85IN7usl8A==
    
         AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg
         ...
         8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE
    
         --CIF-BINARY-FORMAT-SECTION----
         ;
    ;
    
    ;   Example 3 - Example 2 revised for a spiral scan (R. M. Sweet,
        P. J. Ellis & H. J. Bernstein).
    
       A detector is placed 240 mm along the Z axis from the
       goniometer, as in Example 2 above, but in this example the
       image plate is scanned in a spiral pattern from the outside edge in.
    
       The axis for positioning the detector in the Y direction depends
       on the detector Z axis.  This axis is called DETECTOR_Y.
    
       The axis for positioning the detector in the X direction depends
       on the detector Y axis (and therefore on the detector Z axis).
       This axis is called DETECTOR_X.
    
       This detector may be rotated around the Y axis.  This rotation axis
       depends on the three translation axes.  It is called DETECTOR_PITCH.
    
       A coordinate system is defined on the face of the detector in
       terms of a coupled rotation axis and radial scan axis to form
       a spiral scan.  The rotation axis is called  ELEMENT_ROT  and the
       radial axis is called ELEMENT_RAD.  A 150 micrometre radial pitch
       and a 75 micrometre 'constant velocity' angular pitch are assumed.
    
       Indexing is carried out first on the rotation axis and the radial axis
       is made to be dependent on it.
    
       The two axes are coupled to form an axis set ELEMENT_SPIRAL.
    ;
    ;    ###CBF: VERSION 1.1
    
         data_image_1
    
         # category DIFFRN
         _diffrn.id P6MB
         _diffrn.crystal_id P6MB_CRYSTAL7
    
         # category DIFFRN_SOURCE
         loop_
         _diffrn_source.diffrn_id
         _diffrn_source.source
         _diffrn_source.type
          P6MB synchrotron 'SSRL beamline 9-1'
    
         # category DIFFRN_RADIATION
              loop_
         _diffrn_radiation.diffrn_id
         _diffrn_radiation.wavelength_id
         _diffrn_radiation.monochromator
         _diffrn_radiation.polarizn_source_ratio
         _diffrn_radiation.polarizn_source_norm
         _diffrn_radiation.div_x_source
         _diffrn_radiation.div_y_source
         _diffrn_radiation.div_x_y_source
          P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08
         0.01 0.00
    
         # category DIFFRN_RADIATION_WAVELENGTH
         loop_
         _diffrn_radiation_wavelength.id
         _diffrn_radiation_wavelength.wavelength
         _diffrn_radiation_wavelength.wt
          WAVELENGTH1 0.98 1.0
    
         # category DIFFRN_DETECTOR
         loop_
         _diffrn_detector.diffrn_id
         _diffrn_detector.id
         _diffrn_detector.type
         _diffrn_detector.number_of_axes
          P6MB MAR345-SN26 'MAR 345' 4
    
         # category DIFFRN_DETECTOR_AXIS
         loop_
         _diffrn_detector_axis.detector_id
         _diffrn_detector_axis.axis_id
          MAR345-SN26 DETECTOR_X
          MAR345-SN26 DETECTOR_Y
          MAR345-SN26 DETECTOR_Z
          MAR345-SN26 DETECTOR_PITCH
    
         # category DIFFRN_DETECTOR_ELEMENT
         loop_
         _diffrn_detector_element.id
         _diffrn_detector_element.detector_id
          ELEMENT1 MAR345-SN26
    
         # category DIFFRN_DATA_FRAME
         loop_
         _diffrn_data_frame.id
         _diffrn_data_frame.detector_element_id
         _diffrn_data_frame.array_id
         _diffrn_data_frame.binary_id
          FRAME1 ELEMENT1 ARRAY1 1
    
         # category DIFFRN_MEASUREMENT
         loop_
         _diffrn_measurement.diffrn_id
         _diffrn_measurement.id
         _diffrn_measurement.number_of_axes
         _diffrn_measurement.method
          P6MB GONIOMETER 3 rotation
    
         # category DIFFRN_MEASUREMENT_AXIS
         loop_
         _diffrn_measurement_axis.measurement_id
         _diffrn_measurement_axis.axis_id
          GONIOMETER GONIOMETER_PHI
          GONIOMETER GONIOMETER_KAPPA
          GONIOMETER GONIOMETER_OMEGA
    
         # category DIFFRN_SCAN
         loop_
         _diffrn_scan.id
         _diffrn_scan.frame_id_start
         _diffrn_scan.frame_id_end
         _diffrn_scan.frames
          SCAN1 FRAME1 FRAME1 1
    
         # category DIFFRN_SCAN_AXIS
         loop_
         _diffrn_scan_axis.scan_id
         _diffrn_scan_axis.axis_id
         _diffrn_scan_axis.angle_start
         _diffrn_scan_axis.angle_range
         _diffrn_scan_axis.angle_increment
         _diffrn_scan_axis.displacement_start
         _diffrn_scan_axis.displacement_range
         _diffrn_scan_axis.displacement_increment
          SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0
          SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0
          SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0
          SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0
          SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0
          SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0
          SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0
    
         # category DIFFRN_SCAN_FRAME
         loop_
         _diffrn_scan_frame.frame_id
         _diffrn_scan_frame.frame_number
         _diffrn_scan_frame.integration_time
         _diffrn_scan_frame.scan_id
         _diffrn_scan_frame.date
          FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48
    
         # category DIFFRN_SCAN_FRAME_AXIS
         loop_
         _diffrn_scan_frame_axis.frame_id
         _diffrn_scan_frame_axis.axis_id
         _diffrn_scan_frame_axis.angle
         _diffrn_scan_frame_axis.displacement
          FRAME1 GONIOMETER_OMEGA 12.0 0.0
          FRAME1 GONIOMETER_KAPPA 23.3 0.0
          FRAME1 GONIOMETER_PHI -165.8 0.0
          FRAME1 DETECTOR_Z 0.0 -240.0
          FRAME1 DETECTOR_Y 0.0 0.6
          FRAME1 DETECTOR_X 0.0 -0.5
          FRAME1 DETECTOR_PITCH 0.0 0.0
    
         # category AXIS
         loop_
         _axis.id
         _axis.type
         _axis.equipment
         _axis.depends_on
         _axis.vector[1] _axis.vector[2] _axis.vector[3]
         _axis.offset[1] _axis.offset[2] _axis.offset[3]
          GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . .
          GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279
          0 0.76604 . . .
          GONIOMETER_PHI   rotation goniometer GONIOMETER_KAPPA 1 0 0
         . . .
          SOURCE           general source . 0 0 1 . . .
          GRAVITY          general gravity . 0 -1 0 . . .
          DETECTOR_Z       translation detector . 0 0 1 0 0 0
          DETECTOR_Y       translation detector DETECTOR_Z 0 1 0 0 0 0
          DETECTOR_X       translation detector DETECTOR_Y 1 0 0 0 0 0
          DETECTOR_PITCH   rotation    detector DETECTOR_X 0 1 0 0 0 0
          ELEMENT_ROT      translation detector DETECTOR_PITCH 0 0 1 0 0 0
          ELEMENT_RAD      translation detector ELEMENT_ROT 0 1 0 0 0 0
    
         # category ARRAY_STRUCTURE_LIST
         loop_
         _array_structure_list.array_id
         _array_structure_list.index
         _array_structure_list.dimension
         _array_structure_list.precedence
         _array_structure_list.direction
         _array_structure_list.axis_set_id
          ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL
    
         # category ARRAY_STRUCTURE_LIST_AXIS
         loop_
         _array_structure_list_axis.axis_set_id
         _array_structure_list_axis.axis_id
         _array_structure_list_axis.angle
         _array_structure_list_axis.displacement
         _array_structure_list_axis.angular_pitch
         _array_structure_list_axis.radial_pitch
          ELEMENT_SPIRAL ELEMENT_ROT 0    .  0.075   .
          ELEMENT_SPIRAL ELEMENT_RAD . 172.5  .    -0.150
    
         # category ARRAY_ELEMENT_SIZE
         # the actual pixels are 0.075 by 0.150 mm
         # We give the coarser dimension here.
         loop_
         _array_element_size.array_id
         _array_element_size.index
         _array_element_size.size
          ARRAY1 1 150e-6
    
         # category ARRAY_INTENSITIES
         loop_
         _array_intensities.array_id
         _array_intensities.binary_id
         _array_intensities.linearity
         _array_intensities.gain
         _array_intensities.gain_esd
         _array_intensities.overload
         _array_intensities.undefined_value
          ARRAY1 1 linear 1.15 0.2 240000 0
    
          # category ARRAY_STRUCTURE
          loop_
          _array_structure.id
          _array_structure.encoding_type
          _array_structure.compression_type
          _array_structure.byte_order
          ARRAY1 "signed 32-bit integer" packed little_endian
    
         # category ARRAY_DATA
         loop_
         _array_data.array_id
         _array_data.binary_id
         _array_data.data
          ARRAY1 1
         ;
         --CIF-BINARY-FORMAT-SECTION--
         Content-Type: application/octet-stream;
             conversions="X-CBF_PACKED"
         Content-Transfer-Encoding: BASE64
         X-Binary-Size: 3801324
         X-Binary-ID: 1
         X-Binary-Element-Type: "signed 32-bit integer"
         Content-MD5: 07lZFvF+aOcW85IN7usl8A==
    
         AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg
         ...
         8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE
    
         --CIF-BINARY-FORMAT-SECTION----
         ;
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
           save_
    
    
    save__diffrn_scan.id
        _item_description.description
    ;             The value of _diffrn_scan.id uniquely identifies each
                  scan.  The identifier is used to tie together all the
                  information about the scan.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
           '_diffrn_scan.id'                 diffrn_scan             yes
           '_diffrn_scan_axis.scan_id'       diffrn_scan_axis        yes
           '_diffrn_scan_frame.scan_id'      diffrn_scan_frame       yes
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
           '_diffrn_scan_axis.scan_id'          '_diffrn_scan.id'
           '_diffrn_scan_frame.scan_id'         '_diffrn_scan.id'
         save_
    
    
    save__diffrn_scan.date_end
        _item_description.description
    ;              The date and time of the end of the scan.  Note that this
                   may be an estimate generated during the scan, before the
                   precise time of the end of the scan is known.
    ;
        _item.name                 '_diffrn_scan.date_end'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no
        _item_type.code            yyyy-mm-dd
         save_
    
    
    save__diffrn_scan.date_start
        _item_description.description
    ;              The date and time of the start of the scan.
    ;
        _item.name                 '_diffrn_scan.date_start'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no
        _item_type.code            yyyy-mm-dd
         save_
    
    
    save__diffrn_scan.integration_time
        _item_description.description
    ;              Approximate average time in seconds to integrate each
                   step of the scan.  The precise time for integration
                   of each particular step must be provided in
                   _diffrn_scan_frame.integration_time, even
                   if all steps have the same integration time.
    ;
        _item.name                 '_diffrn_scan.integration_time'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no
        _item_type.code            float
        _item_units.code           'seconds'
         loop_
        _item_range.maximum
        _item_range.minimum
                                .   0.0
         save_
    
    
    save__diffrn_scan.frame_id_start
        _item_description.description
    ;              The value of this data item is the identifier of the
                   first frame in the scan.
    
                   This item is a pointer to _diffrn_data_frame.id in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name                 '_diffrn_scan.frame_id_start'
        _item.category_id          diffrn_scan
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan.frame_id_end
        _item_description.description
    ;              The value of this data item is the identifier of the
                   last frame in the scan.
    
                   This item is a pointer to _diffrn_data_frame.id in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name                 '_diffrn_scan.frame_id_end'
        _item.category_id          diffrn_scan
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan.frames
        _item_description.description
    ;              The value of this data item is the number of frames in
                   the scan.
    ;
        _item.name                 '_diffrn_scan.frames'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no
        _item_type.code            int
         loop_
        _item_range.maximum
        _item_range.minimum
                                .   1
                                1   1
         save_
    
    
    ####################
    # DIFFRN_SCAN_AXIS #
    ####################
    
    save_DIFFRN_SCAN_AXIS
        _category.description
    ;    Data items in the DIFFRN_SCAN_AXIS category describe the settings of
         axes for particular scans.  Unspecified axes are assumed to be at
         their zero points.
    ;
        _category.id                   diffrn_scan_axis
        _category.mandatory_code       no
         loop_
        _category_key.name
                                      '_diffrn_scan_axis.scan_id'
                                      '_diffrn_scan_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_scan_axis.scan_id
        _item_description.description
    ;              The value of this data item is the identifier of the
                   scan for which axis settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   _diffrn_scan.id.
    
                   This item is a pointer to _diffrn_scan.id in the
                   DIFFRN_SCAN category.
    ;
        _item.name                 '_diffrn_scan_axis.scan_id'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_axis.axis_id
        _item_description.description
    ;              The value of this data item is the identifier of one of
                   the axes for the scan for which settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   _diffrn_scan.id.
    
                   This item is a pointer to _axis.id in the
                   AXIS category.
    ;
        _item.name                 '_diffrn_scan_axis.axis_id'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_axis.angle_start
        _item_description.description
    ;              The starting position for the specified axis in degrees.
    ;
        _item.name                 '_diffrn_scan_axis.angle_start'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.angle_range
        _item_description.description
    ;              The range from the starting position for the specified axis
                   in degrees.
    ;
        _item.name                 '_diffrn_scan_axis.angle_range'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.angle_increment
        _item_description.description
    ;              The increment for each step for the specified axis
                   in degrees.  In general, this will agree with
                   _diffrn_scan_frame_axis.angle_increment. The
                   sum of the values of _diffrn_scan_frame_axis.angle and
                   _diffrn_scan_frame_axis.angle_increment is the
                   angular setting of the axis at the end of the integration
                   time for a given frame.  If the individual frame values
                   vary, then the value of
                   _diffrn_scan_axis.angle_increment will be
                   representative
                   of the ensemble of values of
                   _diffrn_scan_frame_axis.angle_increment (e.g.
                   the mean).
    ;
        _item.name                 '_diffrn_scan_axis.angle_increment'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.angle_rstrt_incr
        _item_description.description
    ;              The increment after each step for the specified axis
                   in degrees.  In general, this will agree with
                   _diffrn_scan_frame_axis.angle_rstrt_incr.  The
                   sum of the values of _diffrn_scan_frame_axis.angle,
                   _diffrn_scan_frame_axis.angle_increment
                   and  _diffrn_scan_frame_axis.angle_rstrt_incr is the
                   angular setting of the axis at the start of the integration
                   time for the next frame relative to a given frame and
                   should equal _diffrn_scan_frame_axis.angle for this
                   next frame.   If the individual frame values
                   vary, then the value of
                   _diffrn_scan_axis.angle_rstrt_incr will be
                   representative
                   of the ensemble of values of
                   _diffrn_scan_frame_axis.angle_rstrt_incr (e.g.
                   the mean).
    ;
        _item.name                 '_diffrn_scan_axis.angle_rstrt_incr'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.displacement_start
        _item_description.description
    ;              The starting position for the specified axis in millimetres.
    ;
        _item.name                 '_diffrn_scan_axis.displacement_start'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_axis.displacement_range
        _item_description.description
    ;              The range from the starting position for the specified axis
                   in millimetres.
    ;
        _item.name                 '_diffrn_scan_axis.displacement_range'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_axis.displacement_increment
        _item_description.description
    ;              The increment for each step for the specified axis
                   in millimetres.  In general, this will agree with
                   _diffrn_scan_frame_axis.displacement_increment.
                   The sum of the values of
                   _diffrn_scan_frame_axis.displacement and
                   _diffrn_scan_frame_axis.displacement_increment is the
                   angular setting of the axis at the end of the integration
                   time for a given frame.  If the individual frame values
                   vary, then the value of
                   _diffrn_scan_axis.displacement_increment will be
                   representative
                   of the ensemble of values of
                   _diffrn_scan_frame_axis.displacement_increment (e.g.
                   the mean).
    ;
        _item.name                 '_diffrn_scan_axis.displacement_increment'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_axis.displacement_rstrt_incr
        _item_description.description
    ;              The increment for each step for the specified axis
                   in millimetres.  In general, this will agree with
                   _diffrn_scan_frame_axis.displacement_rstrt_incr.
                   The sum of the values of
                   _diffrn_scan_frame_axis.displacement,
                   _diffrn_scan_frame_axis.displacement_increment and
                   _diffrn_scan_frame_axis.displacement_rstrt_incr is the
                   angular setting of the axis at the start of the integration
                   time for the next frame relative to a given frame and
                   should equal _diffrn_scan_frame_axis.displacement
                   for this next frame.  If the individual frame values
                   vary, then the value of
                   _diffrn_scan_axis.displacement_rstrt_incr will be
                   representative
                   of the ensemble of values of
                   _diffrn_scan_frame_axis.displacement_rstrt_incr (e.g.
                   the mean).
    ;
        _item.name                 '_diffrn_scan_axis.displacement_rstrt_incr'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    save__diffrn_scan_axis.reference_angle
         _item_description.description
    ;              The setting of the specified axis in degrees
                   against which measurements of the reference beam center
                   and reference detector distance should be made.
    
                   In general, this will agree with
                   _diffrn_scan_frame_axis.reference_angle.
    
                   If the individual frame values vary, then the value of
                   _diffrn_scan_axis.reference_angle will be
                   representative of the ensemble of values of
                   _diffrn_scan_frame_axis.reference_angle (e.g.
                   the mean).
    
                   If not specified, the value defaults to zero.
    ;
         _item.name                 '_diffrn_scan_axis.reference_angle'
         _item.category_id          diffrn_scan_axis
         _item.mandatory_code       implicit
         _item_default.value        0.0
         _item_type.code            float
         _item_units.code           'degrees'
          save_
    
    
    save__diffrn_scan_axis.reference_displacement
         _item_description.description
    ;              The setting of the specified axis in millimetres
                   against which measurements of the reference beam center
                   and reference detector distance should be made.
    
                   In general, this will agree with
                   _diffrn_scan_frame_axis.reference_displacement.
    
                   If the individual frame values vary, then the value of
                   _diffrn_scan_axis.reference_displacement will be
                   representative of the ensemble of values of
                   _diffrn_scan_frame_axis.reference_displacement (e.g.
                   the mean).
    
                   If not specified, the value defaults to to the value of
                   _diffrn_scan_axis.displacement.
    ;
         _item.name                 '_diffrn_scan_axis.reference_displacement'
         _item.category_id          diffrn_scan_axis
         _item.mandatory_code       implicit
         _item_type.code            float
         _item_units.code           'millimetres'
          save_
    
    
    
    #####################
    # DIFFRN_SCAN_FRAME #
    #####################
    
    save_DIFFRN_SCAN_FRAME
        _category.description
    ;           Data items in the DIFFRN_SCAN_FRAME category describe
                the relationships of particular frames to scans.
    ;
        _category.id                   diffrn_scan_frame
        _category.mandatory_code       no
         loop_
        _category_key.name
                                      '_diffrn_scan_frame.scan_id'
                                      '_diffrn_scan_frame.frame_id'
         loop_
        _category_group.id            'inclusive_group'
                                      'diffrn_group'
         save_
    
    
    save__diffrn_scan_frame.date
        _item_description.description
    ;              The date and time of the start of the frame being scanned.
    ;
        _item.name                 '_diffrn_scan_frame.date'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       no
        _item_type.code            yyyy-mm-dd
         save_
    
    
    save__diffrn_scan_frame.frame_id
        _item_description.description
    ;              The value of this data item is the identifier of the
                   frame being examined.
    
                   This item is a pointer to _diffrn_data_frame.id in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name                 '_diffrn_scan_frame.frame_id'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_frame.frame_number
        _item_description.description
    ;              The value of this data item is the number of the frame
                   within the scan, starting with 1.  It is not necessarily
                   the same as the value of _diffrn_scan_frame.frame_id,
                   but it may be.
    
    ;
        _item.name                 '_diffrn_scan_frame.frame_number'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       no
        _item_type.code            int
         loop_
        _item_range.maximum
        _item_range.minimum
                                .   0
                                0   0
         save_
    
    
    save__diffrn_scan_frame.integration_time
        _item_description.description
    ;              The time in seconds to integrate this step of the scan.
                   This should be the precise time of integration of each
                   particular frame.  The value of this data item should
                   be given explicitly for each frame and not inferred
                   from the value of _diffrn_scan.integration_time.
    ;
        _item.name                 '_diffrn_scan_frame.integration_time'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       yes
        _item_type.code            float
        _item_units.code           'seconds'
         loop_
        _item_range.maximum
        _item_range.minimum
                                .   0.0
         save_
    
    
    save__diffrn_scan_frame.scan_id
        _item_description.description
    ;             The value of _diffrn_scan_frame.scan_id identifies the scan
                  containing this frame.
    
                  This item is a pointer to _diffrn_scan.id in the
                  DIFFRN_SCAN category.
    ;
        _item.name             '_diffrn_scan_frame.scan_id'
        _item.category_id        diffrn_scan_frame
        _item.mandatory_code     yes
        _item_type.code          code
         save_
    
    
    ##########################
    # DIFFRN_SCAN_FRAME_AXIS #
    ##########################
    
    save_DIFFRN_SCAN_FRAME_AXIS
        _category.description
    ;    Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the
         settings of axes for particular frames.  Unspecified axes are
         assumed to be at their zero points.  If, for any given frame,
         nonzero values apply for any of the data items in this category,
         those values should be given explicitly in this category and not
         simply inferred from values in DIFFRN_SCAN_AXIS.
    ;
        _category.id                   diffrn_scan_frame_axis
        _category.mandatory_code       no
         loop_
        _category_key.name
                                      '_diffrn_scan_frame_axis.frame_id'
                                      '_diffrn_scan_frame_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_scan_frame_axis.axis_id
        _item_description.description
    ;              The value of this data item is the identifier of one of
                   the axes for the frame for which settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   _diffrn_scan_frame.frame_id.
    
                   This item is a pointer to _axis.id in the
                   AXIS category.
    ;
        _item.name                 '_diffrn_scan_frame_axis.axis_id'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_frame_axis.angle
        _item_description.description
    ;              The setting of the specified axis in degrees for this frame.
                   This is the setting at the start of the integration time.
    ;
        _item.name                 '_diffrn_scan_frame_axis.angle'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_frame_axis.angle_increment
        _item_description.description
    ;              The increment for this frame for the angular setting of
                   the specified axis in degrees.  The sum of the values
                   of _diffrn_scan_frame_axis.angle and
                   _diffrn_scan_frame_axis.angle_increment is the
                   angular setting of the axis at the end of the integration
                   time for this frame.
    ;
        _item.name                 '_diffrn_scan_frame_axis.angle_increment'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_frame_axis.angle_rstrt_incr
        _item_description.description
    ;              The increment after this frame for the angular setting of
                   the specified axis in degrees.  The sum of the values
                   of _diffrn_scan_frame_axis.angle,
                   _diffrn_scan_frame_axis.angle_increment and
                   _diffrn_scan_frame_axis.angle_rstrt_incr is the
                   angular setting of the axis at the start of the integration
                   time for the next frame and should equal
                   _diffrn_scan_frame_axis.angle for this next frame.
    ;
        _item.name               '_diffrn_scan_frame_axis.angle_rstrt_incr'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_frame_axis.displacement
        _item_description.description
    ;              The setting of the specified axis in millimetres for this
                   frame.  This is the setting at the start of the integration
                   time.
    ;
        _item.name               '_diffrn_scan_frame_axis.displacement'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_frame_axis.displacement_increment
        _item_description.description
    ;              The increment for this frame for the displacement setting of
                   the specified axis in millimetres.  The sum of the values
                   of _diffrn_scan_frame_axis.displacement and
                   _diffrn_scan_frame_axis.displacement_increment is the
                   angular setting of the axis at the end of the integration
                   time for this frame.
    ;
        _item.name               '_diffrn_scan_frame_axis.displacement_increment'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_frame_axis.displacement_rstrt_incr
        _item_description.description
    ;              The increment for this frame for the displacement setting of
                   the specified axis in millimetres.  The sum of the values
                   of _diffrn_scan_frame_axis.displacement,
                   _diffrn_scan_frame_axis.displacement_increment and
                   _diffrn_scan_frame_axis.displacement_rstrt_incr is the
                   angular setting of the axis at the start of the integration
                   time for the next frame and should equal
                   _diffrn_scan_frame_axis.displacement for this next frame.
    ;
        _item.name               '_diffrn_scan_frame_axis.displacement_rstrt_incr'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    save__diffrn_scan_frame_axis.frame_id
        _item_description.description
    ;              The value of this data item is the identifier of the
                   frame for which axis settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   _diffrn_scan_frame.frame_id.
    
                   This item is a pointer to _diffrn_data_frame.id in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name               '_diffrn_scan_frame_axis.frame_id'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    save__diffrn_scan_frame_axis.reference_angle
         _item_description.description
    ;              The setting of the specified axis in degrees
                   against which measurements of the reference beam center
                   and reference detector distance should be made.
    
                   This is normally the same for all frames, but the
                   option is provided here of making changes when
                   needed.
    
                   If not provided, it is assumed to be zero.
    ;
         _item.name               '_diffrn_scan_frame_axis.reference_angle'
         _item.category_id          diffrn_scan_frame_axis
         _item.mandatory_code       implicit
         _item_default.value        0.0
         _item_type.code            float
         _item_units.code           'degrees'
          save_
    
    
    save__diffrn_scan_frame_axis.reference_displacement
         _item_description.description
    ;              The setting of the specified axis in millimetres for this
                   frame against which measurements of the reference beam center
                   and reference detector distance should be made.
    
                   This is normally the same for all frames, but the
                   option is provided here of making changes when
                   needed.
    
                   If not provided, it is assumed to be equal to
                   _diffrn_scan_frame_axis.displacement.
    ;
         _item.name               '_diffrn_scan_frame_axis.reference_displacement'
         _item.category_id          diffrn_scan_frame_axis
         _item.mandatory_code       implicit
         _item_type.code            float
         _item_units.code           'millimetres'
          save_
    
    
    
    #######
    # MAP #
    #######
    
    save_MAP
        _category.description
    ;             Data items in the MAP category record
                  the details of a maps. Maps record values of parameters,
                  such as density, that are functions of position within
                  a cell or are functions of orthogonal coordinates in
                  three space.
                  
                  A map may is composed of one or more map segments
                  specified in the MAP_SEGMENT category.
                                
                  Examples are given in the MAP_SEGMENT category.
    ;
        _category.id                   map
        _category.mandatory_code       no
         loop_
        _category_key.name             '_map.id'
                                       '_map.diffrn_id'
                                       '_map.entry_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;   Example 1 - Identifying an observed density map
                    and a calculated density map
    ;
    ;
            
            loop_
            _map.id
            _map.details
            
            rho_calc
       ;
            density calculated from F_calc derived from the ATOM_SITE list
       ;
            rho_obs
       ;
            density combining the observed structure factors with the
            calculated phases
       ;
    ;
    
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
    
    
    save__map.details
         _item_description.description
    ;              The value of _map.details should give a
                   description of special aspects of each map.
    
    ;
        _item.name                  '_map.details'
        _item.category_id             map
        _item.mandatory_code          no
        _item_type.code               text
         loop_
        _item_examples.case
        _item_examples.detail
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;   Example 1 - Identifying an observed density map
                    and a calculated density map
    ;
    ;
            
            loop_
            _map.id
            _map.details
            
            rho_calc
        ;
            density calculated from F_calc derived from the ATOM_SITE list
        ;
            rho_obs
        ;
            density combining the observed structure factors with the
            calculated phases
        ;
    ;
    
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
          save_
          
    save__map.diffrn_id
        _item_description.description
    ;             This item is a pointer to _diffrn.id in the
                  DIFFRN category.
    ;
        _item.name                  '_map.diffrn_id'
        _item.category_id             map
        _item.mandatory_code          implicit
        _item_type.code               code
         save_
    
    save__map.entry_id
        _item_description.description
    ;             This item is a pointer to _entry.id in the
                  ENTRY category.
    ;
        _item.name                  '_map.entry_id'
        _item.category_id             map
        _item.mandatory_code          implicit
        _item_type.code               code
         save_
    
    
    save__map.id
        _item_description.description
    ;             The value of _map.id must uniquely identify
                  each map for the given diffrn.id or entry.id.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
               '_map.id'                map          yes
               '_map_segment.id'        map_segment  yes
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_map_segment.id'        '_map.id'
         save_
    
    
    
    
    ###########################
    # MAP_SEGMENT #
    ###########################
    
    
    save_MAP_SEGMENT
        _category.description
    ;             Data items in the MAP_SEGMENT category record
                  the details about each segment (section or brick) of a map. 
    ;
        _category.id                   map_segment
        _category.mandatory_code       no
         loop_
        _category_key.name             '_map_segment.id'
                                       '_map_segment.map_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;   Example 1 - Identifying an observed density map
                    and a calculated density map, each consisting of one
                    segment, both using the same array structure
                    and mask.
    ;
    ;
            
            loop_
            _map.id
            _map.details
            
            rho_calc
         ;
            density calculated from F_calc derived from the ATOM_SITE list
         ;
            rho_obs
         ;
            density combining the observed structure factors with the
            calculated phases
         ;
    
            loop_
            _map_segment.map_id
            _map_segment.id
            _map_segment.array_id
            _map_segment.binary_id
            _map_segment.mask_array_id
            _map_segment.mask_binary_id
            rho_calc rho_calc map_structure 1 mask_structure 1
            rho_obs  rho_obs  map_structure 2 mask_structure 1
    ;
    
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
    
    
    save__map_segment.array_id
        _item_description.description
    ;             The value of _map_segment.array_id identifies the array 
                  structure into which the map is organized.
    
                  This item is a pointer to _array_structure.id in the
                  ARRAY_STRUCTURE category.
    ;
        _item.name                  '_map_segment.array_id'
        _item.category_id             map_segment
        _item.mandatory_code          implicit
        _item_type.code               code
         save_
    
    
    save__map_segment.binary_id
        _item_description.description
    ;             The value of _map_segment.binary_id distinguishes the particular 
                  set of data organized according to _map_segment.array_id in 
                  which the data values of the map are stored.
    
                  This item is a pointer to _array_data.binary_id in the
                  ARRAY_DATA category.
    ;
        _item.name                  '_map_segment.binary_id'
        _item.category_id             map_segment
        _item.mandatory_code          implicit
        _item_type.code               int
         save_
    
    save__map_segment.mask_array_id
        _item_description.description
    ;             The value of _map_segment.mask_array_id, if given, the array 
                  structure into which the mask for the map is organized.  If no 
                  value is given, then all elements of the map are valid.  If a 
                  value is given, then only elements of the map for which the 
                  corresponding element of the mask is non-zero are valid.  The 
                  value of _map_segment.mask_array_id differs from the value of
                  _map_segment.array_id in order to permit the mask to be given
                  as, say, unsigned 8-bit integers, while the map is given as
                  a data type with more range.  However, the two array structures
                  must be aligned, using the same axes in the same order with the
                  same displacements and increments
    
                  This item is a pointer to _array_structure.id in the
                  ARRAY_STRUCTURE category.
    ;
        _item.name                  '_map_segment.mask_array_id'
        _item.category_id             map_segment
        _item.mandatory_code          implicit
        _item_type.code               code
         save_
    
    
    save__map_segment.mask_binary_id
        _item_description.description
    ;             The value of _map_segment.mask_binary_id identifies the 
                  particular set of data organized according to 
                  _map_segment.mask_array_id specifying the mask for the map.
    
                  This item is a pointer to _array_data.mask_binary_id in the
                  ARRAY_DATA category.
    ;
        _item.name                  '_map_segment.mask_binary_id'
        _item.category_id             map_segment
        _item.mandatory_code          implicit
        _item_type.code               int
         save_
    
    
    save__map_segment.id
        _item_description.description
    ;             The value of _map_segment.id must uniquely
                  identify each segment of a map.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
               '_map_segment.id'
               map_segment
               yes
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_map_data_frame.map_segment_id'
               '_map_segment.id'
    
         save_
    
    
    save__map_segment.map_id
        _item_description.description
    ;              This item is a pointer to _map.id
                   in the MAP category.
    ;
        _item.name                  '_map_segment.map_id'
        _item.category_id             map_segment
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    save__map_segment.details
         _item_description.description
    ;              The value of _map_segment.details should give a
                   description of special aspects of each segment of a map.
    
    ;
        _item.name                  '_map_segment.details'
        _item.category_id             map_segment
        _item.mandatory_code          no
        _item_type.code               text
         loop_
        _item_examples.case
        _item_examples.detail
    ;               Example to be provided
    ;
    ;               
    
    ;
          save_
    
    
    ########################   DEPRECATED DATA ITEMS ########################
    
    save__diffrn_detector_axis.id
        _item_description.description
    ;              This data item is a pointer to _diffrn_detector.id in
                   the DIFFRN_DETECTOR category.
    
                   DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_detector_axis.id'
        _item.category_id             diffrn_detector_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    save__diffrn_detector_element.center[1]
        _item_description.description
    ;             The value of _diffrn_detector_element.center[1] is the X
                  component of the distortion-corrected beam centre in
                  millimetres from the (0, 0) (lower-left) corner of the
                  detector element viewed from the sample side.
    
                  The X and Y axes are the laboratory coordinate system
                  coordinates defined in the AXIS category measured
                  when all positioning axes for the detector are at their zero
                  settings.  If the resulting X or Y axis is then orthogonal to the
                  detector, the Z axis is used instead of the orthogonal axis.
                  
                  Because of ambiguity about the setting used to determine this
                  center, use of this data item is deprecated.  The data item
                  _diffrn_data_frame.center_fast
                  which is referenced to the detector coordinate system and not
                  directly to the laboratory coordinate system should be used 
                  instead.
    
    ;
        _item.name                  '_diffrn_detector_element.center[1]'
        _item.category_id             diffrn_detector_element
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
    
        save_
    
    
    save__diffrn_detector_element.center[2]
        _item_description.description
    ;             The value of _diffrn_detector_element.center[2] is the Y
                  component of the distortion-corrected beam centre in
                  millimetres from the (0, 0) (lower-left) corner of the
                  detector element viewed from the sample side.
    
                  The X and Y axes are the laboratory coordinate system
                  coordinates defined in the AXIS category measured
                  when all positioning axes for the detector are at their zero
                  settings.  If the resulting X or Y axis is then orthogonal to the
                  detector, the Z axis is used instead of the orthogonal axis.
                  
                  Because of ambiguity about the setting used to determine this
                  center,  use of this data item is deprecated. The data item
                  _diffrn_data_frame.center_slow
                  which is referenced to the detector coordinate system and not
                  directly to the laboratory coordinate system should be used
                  instead.
    
    ;
        _item.name                  '_diffrn_detector_element.center[2]'
        _item.category_id             diffrn_detector_element
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
    
        save_
    
    
    
    save__diffrn_measurement_axis.id
        _item_description.description
    ;              This data item is a pointer to _diffrn_measurement.id in
                   the DIFFRN_MEASUREMENT category.
    
                   DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_measurement_axis.id'
        _item.category_id             diffrn_measurement_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    #########################   DEPRECATED CATEGORY #########################
    #####################
    # DIFFRN_FRAME_DATA #
    #####################
    
    
    save_DIFFRN_FRAME_DATA
        _category.description
    ;             Data items in the DIFFRN_FRAME_DATA category record
                  the details about each frame of data.
    
                  The items in this category are now in the
                  DIFFRN_DATA_FRAME category.
    
                  The items in the DIFFRN_FRAME_DATA category
                  are now deprecated.  The items from this category
                  are provided as aliases in the 1.0 dictionary
                  or, in the case of _diffrn_frame_data.details,
                  in the 1.4 dictionary.  THESE ITEMS SHOULD NOT
                  BE USED FOR NEW WORK.
    
                  The items from the old category are provided
                  in this dictionary for completeness
                  but should not be used or cited.  To avoid
                  confusion, the example has been removed
                  and the redundant parent-child links to other
                  categories have been removed.
    ;
        _category.id                   diffrn_frame_data
        _category.mandatory_code       no
         loop_
        _category_key.name             '_diffrn_frame_data.id'
                                       '_diffrn_frame_data.detector_element_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        THE DIFFRN_FRAME_DATA category is deprecated and should not be used.
    ;
    ;
           # EXAMPLE REMOVED #
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
    
    
    save__diffrn_frame_data.array_id
        _item_description.description
    ;             This item is a pointer to _array_structure.id in the
                  ARRAY_STRUCTURE category.
    
                  DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_frame_data.array_id'
        _item.category_id             diffrn_frame_data
        _item.mandatory_code          implicit
        _item_type.code               code
         save_
    
    
    save__diffrn_frame_data.binary_id
        _item_description.description
    ;             This item is a pointer to _array_data.binary_id in the
                  ARRAY_STRUCTURE category.
    
                  DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_frame_data.binary_id'
        _item.category_id             diffrn_frame_data
        _item.mandatory_code          implicit
        _item_type.code               int
         save_
    
    
    save__diffrn_frame_data.detector_element_id
        _item_description.description
    ;             This item is a pointer to _diffrn_detector_element.id
                  in the DIFFRN_DETECTOR_ELEMENT category.
    
                  DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_frame_data.detector_element_id'
        _item.category_id             diffrn_frame_data
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_frame_data.id
        _item_description.description
    ;             The value of _diffrn_frame_data.id must uniquely identify
                  each complete frame of data.
    
                  DEPRECATED -- DO NOT USE
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
               '_diffrn_frame_data.id'        diffrn_frame_data  yes
        _item_type.code               code
         save_
    
    save__diffrn_frame_data.details
         _item_description.description
    ;             The value of _diffrn_data_frame.details should give a
                  description of special aspects of each frame of data.
    
                  DEPRECATED -- DO NOT USE
    ;
         _item.name                  '_diffrn_frame_data.details'
         _item.category_id             diffrn_frame_data
         _item.mandatory_code          no
         _item_type.code               text
          save_
    
    ################ END DEPRECATED SECTION ###########
    
    
    ####################
    ## ITEM_TYPE_LIST ##
    ####################
    #
    #
    #  The regular expressions defined here are not compliant
    #  with the POSIX 1003.2 standard as they include the
    #  '\n' and '\t' special characters.  These regular expressions
    #  have been tested using version 0.12 of Richard Stallman's
    #  GNU regular expression library in POSIX mode.
    #  In order to allow presentation of a regular expression
    #  in a text field concatenate any line ending in a backslash
    #  with the following line, after discarding the backslash.
    #
    #  A formal definition of the '\n' and '\t' special characters
    #  is most properly done in the DDL, but for completeness, please
    #  note that '\n' is the line termination character ('newline')
    #  and '\t' is the horizontal tab character.  There is a formal
    #  ambiguity in the use of '\n' for line termination, in that
    #  the intention is that the equivalent machine/OS-dependent line
    #  termination character sequence should be accepted as a match, e.g.
    #
    #      '\r' (control-M) under MacOS
    #      '\n' (control-J) under Unix
    #      '\r\n' (control-M control-J) under DOS and MS Windows
    #
         loop_
        _item_type_list.code
        _item_type_list.primitive_code
        _item_type_list.construct
        _item_type_list.detail
                   code      char
                   '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*'
    ;              code item types/single words ...
    ;
                   ucode      uchar
                   '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*'
    ;              code item types/single words (case insensitive) ...
    ;
                   line      char
                   '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*'
    ;              char item types / multi-word items ...
    ;
                   uline     uchar
                   '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*'
    ;              char item types / multi-word items (case insensitive)...
    ;
                   text      char
                 '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*'
    ;              text item types / multi-line text ...
    ;
                   binary    char
    ;\n--CIF-BINARY-FORMAT-SECTION--\n\
    [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\
    \n--CIF-BINARY-FORMAT-SECTION----
    ;
    ;              binary items are presented as MIME-like ascii-encoded
                   sections in an imgCIF.  In a CBF, raw octet streams
                   are used to convey the same information.
    ;
                   int       numb
                   '-?[0-9]+'
    ;              int item types are the subset of numbers that are the negative
                   or positive integers.
    ;
                   float     numb
              '-?(([0-9]+)[.]?|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?'
    ;              float item types are the subset of numbers that are the floating
                   point numbers.
    ;
                   any       char
                   '.*'
    ;              A catch all for items that may take any form...
    ;
                   yyyy-mm-dd  char
    ;\
    [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9]?[0-9]\
    ((T[0-2][0-9](:[0-5][0-9](:[0-5][0-9](.[0-9]+)?)?)?)?\
    ([+-][0-5][0-9]:[0-5][0-9]))?
    ;
    ;
                   Standard format for CIF date and time strings (see
                   http://www.iucr.org/iucr-top/cif/spec/datetime.html),
                   consisting of a yyyy-mm-dd date optionally followed by
                   the character 'T' followed by a 24-hour clock time,
                   optionally followed by a signed time-zone offset.
    
                   The IUCr standard has been extended to allow for an optional
                   decimal fraction on the seconds of time.
    
                   Time is local time if no time-zone offset is given.
    
                   Note that this type extends the mmCIF yyyy-mm-dd type
                   but does not conform to the mmCIF yyyy-mm-dd:hh:mm
                   type that uses a ':' in place if the 'T' specified
                   by the IUCr standard.  For reading, both forms should
                   be accepted,  but for writing, only the IUCr form should
                   be used.
    
                   For maximal compatibility, the special time zone
                   indicator 'Z' (for 'zulu') should be accepted on
                   reading in place of '+00:00' for GMT.
    ;
    
    
    #####################
    ## ITEM_UNITS_LIST ##
    #####################
    
         loop_
        _item_units_list.code
        _item_units_list.detail
    #
         'metres'                 'metres'
         'centimetres'            'centimetres (metres * 10^( -2)^)'
         'millimetres'            'millimetres (metres * 10^( -3)^)'
         'nanometres'             'nanometres  (metres * 10^( -9)^)'
         'angstroms'              '\%Angstroms   (metres * 10^(-10)^)'
         'picometres'             'picometres  (metres * 10^(-12)^)'
         'femtometres'            'femtometres (metres * 10^(-15)^)'
    #
         'reciprocal_metres'      'reciprocal metres (metres^(-1)^)'
         'reciprocal_centimetres'
            'reciprocal centimetres ((metres * 10^( -2)^)^(-1)^)'
         'reciprocal_millimetres'
            'reciprocal millimetres ((metres * 10^( -3)^)^(-1)^)'
         'reciprocal_nanometres'
            'reciprocal nanometres  ((metres * 10^( -9)^)^(-1)^)'
         'reciprocal_angstroms'
            'reciprocal \%Angstroms   ((metres * 10^(-10)^)^(-1)^)'
         'reciprocal_picometres'
            'reciprocal picometres  ((metres * 10^(-12)^)^(-1)^)'
    #
         'nanometres_squared'     'nanometres squared (metres * 10^( -9)^)^2^'
         'angstroms_squared'      '\%Angstroms squared  (metres * 10^(-10)^)^2^'
         '8pi2_angstroms_squared'
           '8\p^2^ * \%Angstroms squared (metres * 10^(-10)^)^2^'
         'picometres_squared'     'picometres squared (metres * 10^(-12)^)^2^'
    #
         'nanometres_cubed'       'nanometres cubed (metres * 10^( -9)^)^3^'
         'angstroms_cubed'        '\%Angstroms cubed  (metres * 10^(-10)^)^3^'
         'picometres_cubed'       'picometres cubed (metres * 10^(-12)^)^3^'
    #
         'kilopascals'            'kilopascals'
         'gigapascals'            'gigapascals'
    #
         'hours'                  'hours'
         'minutes'                'minutes'
         'seconds'                'seconds'
         'microseconds'           'microseconds'
    #
         'degrees'                'degrees (of arc)'
         'degrees_squared'        'degrees (of arc) squared'
    #
         'degrees_per_minute'     'degrees (of arc) per minute'
    #
         'celsius'                'degrees (of temperature) Celsius'
         'kelvins'                'degrees (of temperature) Kelvin'
    #
         'counts'                 'counts'
         'counts_per_photon'      'counts per photon'
    #
         'electrons'              'electrons'
    #
         'electrons_squared'      'electrons squared'
    #
         'electrons_per_nanometres_cubed'
    ; electrons per nanometres cubed (electrons/(metres * 10^( -9)^)^(-3)^)
    ;
         'electrons_per_angstroms_cubed'
    ; electrons per \%Angstroms cubed (electrons/(metres * 10^(-10)^)^(-3)^)
    ;
         'electrons_per_picometres_cubed'
    ; electrons per picometres cubed (electrons/(metres * 10^(-12)^)^(-3)^)
    ;
         'kilowatts'              'kilowatts'
         'milliamperes'           'milliamperes'
         'kilovolts'              'kilovolts'
    #
         'pixels_per_element'     '(image) pixels per (array) element'
    #
         'arbitrary'
    ; arbitrary system of units.
    ;
    #
    
         loop_
        _item_units_conversion.from_code
        _item_units_conversion.to_code
        _item_units_conversion.operator
        _item_units_conversion.factor
    ###
         'metres'                   'centimetres'              '*'   1.0E+02
         'metres'                   'millimetres'              '*'   1.0E+03
         'metres'                   'nanometres'               '*'   1.0E+09
         'metres'                   'angstroms'                '*'   1.0E+10
         'metres'                   'picometres'               '*'   1.0E+12
         'metres'                   'femtometres'              '*'   1.0E+15
    #
         'centimetres'              'metres'                   '*'   1.0E-02
         'centimetres'              'millimetres'              '*'   1.0E+01
         'centimetres'              'nanometres'               '*'   1.0E+07
         'centimetres'              'angstroms'                '*'   1.0E+08
         'centimetres'              'picometres'               '*'   1.0E+10
         'centimetres'              'femtometres'              '*'   1.0E+13
    #
         'millimetres'              'metres'                   '*'   1.0E-03
         'millimetres'              'centimetres'              '*'   1.0E-01
         'millimetres'              'nanometres'               '*'   1.0E+06
         'millimetres'              'angstroms'                '*'   1.0E+07
         'millimetres'              'picometres'               '*'   1.0E+09
         'millimetres'              'femtometres'              '*'   1.0E+12
    #
         'nanometres'               'metres'                   '*'   1.0E-09
         'nanometres'               'centimetres'              '*'   1.0E-07
         'nanometres'               'millimetres'              '*'   1.0E-06
         'nanometres'               'angstroms'                '*'   1.0E+01
         'nanometres'               'picometres'               '*'   1.0E+03
         'nanometres'               'femtometres'              '*'   1.0E+06
    #
         'angstroms'                'metres'                   '*'   1.0E-10
         'angstroms'                'centimetres'              '*'   1.0E-08
         'angstroms'                'millimetres'              '*'   1.0E-07
         'angstroms'                'nanometres'               '*'   1.0E-01
         'angstroms'                'picometres'               '*'   1.0E+02
         'angstroms'                'femtometres'              '*'   1.0E+05
    #
         'picometres'               'metres'                   '*'   1.0E-12
         'picometres'               'centimetres'              '*'   1.0E-10
         'picometres'               'millimetres'              '*'   1.0E-09
         'picometres'               'nanometres'               '*'   1.0E-03
         'picometres'               'angstroms'                '*'   1.0E-02
         'picometres'               'femtometres'              '*'   1.0E+03
    #
         'femtometres'              'metres'                   '*'   1.0E-15
         'femtometres'              'centimetres'              '*'   1.0E-13
         'femtometres'              'millimetres'              '*'   1.0E-12
         'femtometres'              'nanometres'               '*'   1.0E-06
         'femtometres'              'angstroms'                '*'   1.0E-05
         'femtometres'              'picometres'               '*'   1.0E-03
    ###
         'reciprocal_centimetres'   'reciprocal_metres'        '*'   1.0E+02
         'reciprocal_centimetres'   'reciprocal_millimetres'   '*'   1.0E-01
         'reciprocal_centimetres'   'reciprocal_nanometres'    '*'   1.0E-07
         'reciprocal_centimetres'   'reciprocal_angstroms'     '*'   1.0E-08
         'reciprocal_centimetres'   'reciprocal_picometres'    '*'   1.0E-10
    #
         'reciprocal_millimetres'   'reciprocal_metres'        '*'   1.0E+03
         'reciprocal_millimetres'   'reciprocal_centimetres'   '*'   1.0E+01
         'reciprocal_millimetres'   'reciprocal_nanometres'    '*'   1.0E-06
         'reciprocal_millimetres'   'reciprocal_angstroms'     '*'   1.0E-07
         'reciprocal_millimetres'   'reciprocal_picometres'    '*'   1.0E-09
    #
         'reciprocal_nanometres'    'reciprocal_metres'        '*'   1.0E+09
         'reciprocal_nanometres'    'reciprocal_centimetres'   '*'   1.0E+07
         'reciprocal_nanometres'    'reciprocal_millimetres'   '*'   1.0E+06
         'reciprocal_nanometres'    'reciprocal_angstroms'     '*'   1.0E-01
         'reciprocal_nanometres'    'reciprocal_picometres'    '*'   1.0E-03
    #
         'reciprocal_angstroms'     'reciprocal_metres'        '*'   1.0E+10
         'reciprocal_angstroms'     'reciprocal_centimetres'   '*'   1.0E+08
         'reciprocal_angstroms'     'reciprocal_millimetres'   '*'   1.0E+07
         'reciprocal_angstroms'     'reciprocal_nanometres'    '*'   1.0E+01
         'reciprocal_angstroms'     'reciprocal_picometres'    '*'   1.0E-02
    #
         'reciprocal_picometres'    'reciprocal_metres'        '*'   1.0E+12
         'reciprocal_picometres'    'reciprocal_centimetres'   '*'   1.0E+10
         'reciprocal_picometres'    'reciprocal_millimetres'   '*'   1.0E+09
         'reciprocal_picometres'    'reciprocal_nanometres'    '*'   1.0E+03
         'reciprocal_picometres'    'reciprocal_angstroms'     '*'   1.0E+01
    ###
         'nanometres_squared'       'angstroms_squared'        '*'   1.0E+02
         'nanometres_squared'       'picometres_squared'       '*'   1.0E+06
    #
         'angstroms_squared'        'nanometres_squared'       '*'   1.0E-02
         'angstroms_squared'        'picometres_squared'       '*'   1.0E+04
         'angstroms_squared'        '8pi2_angstroms_squared'   '*'   78.9568
    
    #
         'picometres_squared'       'nanometres_squared'       '*'   1.0E-06
         'picometres_squared'       'angstroms_squared'        '*'   1.0E-04
    ###
         'nanometres_cubed'         'angstroms_cubed'          '*'   1.0E+03
         'nanometres_cubed'         'picometres_cubed'         '*'   1.0E+09
    #
         'angstroms_cubed'          'nanometres_cubed'         '*'   1.0E-03
         'angstroms_cubed'          'picometres_cubed'         '*'   1.0E+06
    #
         'picometres_cubed'         'nanometres_cubed'         '*'   1.0E-09
         'picometres_cubed'         'angstroms_cubed'          '*'   1.0E-06
    ###
         'kilopascals'              'gigapascals'              '*'   1.0E-06
         'gigapascals'              'kilopascals'              '*'   1.0E+06
    ###
         'hours'                    'minutes'                  '*'   6.0E+01
         'hours'                    'seconds'                  '*'   3.6E+03
         'hours'                    'microseconds'             '*'   3.6E+09
    #
         'minutes'                  'hours'                    '/'   6.0E+01
         'minutes'                  'seconds'                  '*'   6.0E+01
         'minutes'                  'microseconds'             '*'   6.0E+07
    #
         'seconds'                  'hours'                    '/'   3.6E+03
         'seconds'                  'minutes'                  '/'   6.0E+01
         'seconds'                  'microseconds'             '*'   1.0E+06
    #
         'microseconds'             'hours'                    '/'   3.6E+09
         'microseconds'             'minutes'                  '/'   6.0E+07
         'microseconds'             'seconds'                  '/'   1.0E+06
    ###
         'celsius'                  'kelvins'                  '-'     273.0
         'kelvins'                  'celsius'                  '+'     273.0
    ###
         'electrons_per_nanometres_cubed'
         'electrons_per_angstroms_cubed'                       '*'   1.0E+03
         'electrons_per_nanometres_cubed'
         'electrons_per_picometres_cubed'                      '*'   1.0E+09
    #
         'electrons_per_angstroms_cubed'
         'electrons_per_nanometres_cubed'                      '*'   1.0E-03
         'electrons_per_angstroms_cubed'
         'electrons_per_picometres_cubed'                      '*'   1.0E+06
    #
         'electrons_per_picometres_cubed'
         'electrons_per_nanometres_cubed'                      '*'   1.0E-09
         'electrons_per_picometres_cubed'
         'electrons_per_angstroms_cubed'                       '*'   1.0E-06
    ###
    
    ########################
    ## DICTIONARY_HISTORY ##
    ########################
    
         loop_
        _dictionary_history.version
        _dictionary_history.update
        _dictionary_history.revision
    
       1.5.4   2007-07-28
    
    ;  Typographics corrections (HJB)
    
         + Corrected embedded degree characters to \%
         + Corrected embedded Aring to \%A
         + Added trailing ^ for a power
         + Removed 2 cases of a space after an underscore
           in tag name.
    ;
      
       1.5.3   2007-07-08
       
    ;  Changes to support SLS miniCBF and suggestions
       from the 24 May 07 BNL imgCIF workshop (HJB)
     
         + Added new data items
           '_array_data.header_contents',
           '_array_data.header_convention',
           '_diffrn_data_frame.center_fast',
           '_diffrn_data_frame.center_slow',
           '_diffrn_data_frame.center_units',
           '_diffrn_measurement.sample_detector_distance',
           '_diffrn_measurement.sample_detector_voffset
         + Deprecated data items
           '_diffrn_detector_element.center[1]',
           '_diffrn_detector_element.center[2]'
         + Added comments and example on miniCBF
         + Changed all array_id data items to implicit
    ;
       
       1.5.2   2007-05-06
       
    ;  Further clarifications of the coordinate system. (HJB)
    ;
    
       1.5.1   2007-04-26
       
    ;  Improve defintion of X-axis to cover the case of no goniometer
       and clean up more line folds (HJB)
    ;
    
       1.5     2007-07-25
       
    ;  This is a cummulative list of the changes proposed since the
       imgCIF workshop in Hawaii in July 2006.  It is the result
       of contributions by H. J. Bernstein, A. Hammersley,
       J. Wright and W. Kabsch.
       
       2007-02-19 Consolidated changes (edited by HJB)
         + Added new data items
           '_array_structure.compression_type_flag',
           '_array_structure_list_axis.fract_displacement',
           '_array_structure_list_axis.displacement_increment',
           '_array_structure_list_axis.reference_angle',
           '_array_structure_list_axis.reference_displacement',
           '_axis.system',
           '_diffrn_detector_element.reference_center_fast',
           '_diffrn_detector_element.reference_center_slow',
           '_diffrn_scan_axis.reference_angle',
           '_diffrn_scan_axis.reference_displacement',
           '_map.details', '_map.diffrn_id',
           '_map.entry_id', '_map.id',
           '_map_segment.array_id', '_map_segment.binary_id',
           '_map_segment.mask_array_id', '_map_segment.mask_binary_id',
           '_map_segment.id', '_map_segment.map_id',
           '_map_segment.details.
         + Change type of 
           '_array_structure.byte_order' and
           '_array_structure.compression_type'
           to ucode to make these values case-insensitive
         + Add values 'packed_v2' and 'byte_offset' to enumeration of values for
           '_array_structure.compression_type'
         + Add to definitions for the binary data type to handle new compression
           types, maps, and a variety of new axis types.
        2007-07-25 Cleanup of typos for formal release (HJB)
         + Corrected text fields for reference_ tag descriptions that
           were off by one column
         + Fix typos in comments listing fract_ tags
         + Changed name of release from 1.5_DRAFT to 1.5
         + Fix unclosed text fields in various map definitions
          
    ;
    
       1.4     2006-07-04
    
    ;  This is a change to reintegrate all changes made in the course of
       publication of ITVG, by the RCSB from April 2005 through
       August 2008 and changes for the 2006 imgCIF workshop in
       Hawaii.
    
       2006-07-04 Consolidated changes for the 2006 imgCIF workshop (edited by HJB)
         + Correct type of '_array_structure_list.direction' from 'int' to 'code'.
         + Added new data items suggested by CN
           '_diffrn_data_frame.details'
           '_array_intensities.pixel_fast_bin_size',
           '_array_intensities.pixel_slow_bin_size and
           '_array_intensities.pixel_binning_method
         + Added deprecated item for completeness
           '_diffrn_frame_data.details'
         + Added entry for missing item in contents list
           '_array_structure_list_axis.displacement'
         + Added new MIME type X-BASE32K based on work by VL, KM, GD, HJB
         + Correct description of MIME boundary delimiter to start in
           column 1.
         + General cleanup of text fields to conform to changes for ITVG
           by removing empty lines at start and finish of text field.
         + Amend example for ARRAY_INTENSITIES to include binning.
         + Add local copy of type specification (as 'code') for all children
           of '_diffrn.id'.
         + For consistency, change all references to 'pi' to '\p' and all
           references to 'Angstroms' to '\%Angstroms'.
         + Clean up all powers to use IUCr convention of '^power^', as in
           '10^3^' for '10**3'.
         + Update 'yyyy-mm-dd' type regex to allow truncation from the right
           and improve comments to explain handling of related mmCIF
           'yyyy-mm-dd:hh:mm' type, and use of 'Z' for GMT time zone.
    
       2005-03-08 and
       2004-08-08 fixed cases where _item_units.code  used
                  instead of _item_type.code (JDW)
       2004-04-15 fixed item ordering in
                   _diffrn_measurement_axis.measurement_id
                   added sub_category 'vector' (JDW)
    ;
    
       1.3.2   2005-06-25
    
    ;  2005-06-25 ITEM_TYPE_LIST: code, ucode, line, uline regexps updated
                  to those of current mmCIF; float modified by allowing integers
                  terminated by a point as valid. The 'time' part of
                  yyyy-mm-dd types made optional in the regexp. (BM)
    
       2005-06-17 Minor corrections as for proofs for IT G Chapter 4.6
       (NJA)
    
       2005-02-21  Minor corrections to spelling and punctuation
       (NJA)
    
       2005-01-08 Changes as per Nicola Ashcroft.
       + Updated example 1 for DIFFRN_MEASUREMENT to agree with mmCIF.
       + Spelled out "micrometres" for "um" and "millimetres" for "mm".
       + Removed phrase "which may be stored" from ARRAY_STRUCTURE
         description.
       + Removed unused 'byte-offsets' compressions and updated
         cites to ITVG for '_array_structure.compression_type'.
       (HJB)
    ;
    
       1.3.1   2003-08-13
    ;
       Changes as per Frances C. Bernstein.
       + Identify initials.
       + Adopt British spelling for centre in text.
       + Set \p and \%Angstrom and powers.
       + Clean up commas and unclear wordings.
       + Clean up tenses in history.
       Changes as per Gotzon Madariaga.
       + Fix the ARRAY_DATA example to align '_array_data.binary_id'
       and X-Binary-ID.
       + Add a range to '_array_intensities.gain_esd'.
       + In the example of DIFFRN_DETECTOR_ELEMENT,
       '_diffrn_detector_element.id' and
       '_diffrn_detector_element.detector_id' interchanged.
       + Fix typos for direction, detector and axes.
       + Clarify description of polarisation.
       + Clarify axes in '_diffrn_detector_element.center[1]'
        '_diffrn_detector_element.center[2]'.
       + Add local item types for items that are pointers.
       (HJB)
    ;
    
    
       1.3.0   2003-07-24
    ;
       Changes as per Brian McMahon.
       + Consistently quote tags embedded in text.
       + Clean up introductory comments.
       + Adjust line lengths to fit in 80 character window.
       + Fix several descriptions in AXIS category which
         referred to '_axis.type' instead of the current item.
       + Fix erroneous use of deprecated item
         '_diffrn_detector_axis.id' in examples for
         DIFFRN_SCAN_AXIS.
       + Add deprecated items '_diffrn_detector_axis.id'
         and '_diffrn_measurement_axis.id'.
       (HJB)
    ;
    
    
       1.2.4   2003-07-14
    ;
       Changes as per I. David Brown.
       + Enhance descriptions in DIFFRN_SCAN_AXIS to make them less
         dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS.
       + Provide a copy of the deprecated DIFFRN_FRAME_DATA
         category for completeness.
       (HJB)
    ;
    
    
       1.2.3   2003-07-03
    ;
       Cleanup to conform to ITVG.
       + Correct sign error in ..._cubed units.
       + Correct '_diffrn_radiation.polarisn_norm' range.
       (HJB)
    ;
    
    
       1.2.2   2003-03-10
    ;
       Correction of typos in various DIFFRN_SCAN_AXIS descriptions.
       (HJB)
    ;
    
    
       1.2.1   2003-02-22
    ;
       Correction of ATOM_ for ARRAY_ typos in various descriptions.
       (HJB)
    ;
    
    
       1.2     2003-02-07
    ;
       Corrections to encodings (remove extraneous hyphens) remove
       extraneous underscore in '_array_structure.encoding_type'
       enumeration.  Correct typos in items units list.  (HJB)
    ;
    
    
       1.1.3   2001-04-19
    ;
       Another typo corrections by Wilfred Li, and cleanup by HJB.
    ;
    
    
       1.1.2   2001-03-06
    ;
       Several typo corrections by Wilfred Li.
    ;
    
    
       1.1.1   2001-02-16
    ;
       Several typo corrections by JW.
    ;
    
    
       1.1     2001-02-06
    ;
       Draft resulting from discussions on header for use at NSLS.  (HJB)
    
       + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME.
    
       + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'.
    
       + Add '_diffrn_measurement_axis.measurement_device' and change
         '_diffrn_measurement_axis.id' to
         '_diffrn_measurement_axis.measurement_id'.
    
       + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source',
        '_diffrn_radiation.div_x_y_source',
        '_diffrn_radiation.polarizn_source_norm',
       '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end',
       '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr',
       '_diffrn_scan_axis.displacement_rstrt_incr',
       '_diffrn_scan_frame_axis.angle_increment',
       '_diffrn_scan_frame_axis.angle_rstrt_incr',
       '_diffrn_scan_frame_axis.displacement',
       '_diffrn_scan_frame_axis.displacement_increment',and
       '_diffrn_scan_frame_axis.displacement_rstrt_incr'.
    
       + Add '_diffrn_measurement.device' to category key.
    
       + Update yyyy-mm-dd to allow optional time with fractional seconds
         for time stamps.
    
       + Fix typos caught by RS.
    
       + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to
         allow for coupled axes, as in spiral scans.
    
       + Add examples for fairly complete headers thanks to R. Sweet and P.
         Ellis.
    ;
    
    
       1.0     2000-12-21
    ;
       Release version - few typos and tidying up.  (BM & HJB)
    
       + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end
       of dictionary.
    
       + Alphabetize dictionary.
    ;
    
    
       0.7.1   2000-09-29
    ;
       Cleanup fixes.  (JW)
    
       + Correct spelling of diffrn_measurement_axis in '_axis.id'
    
       + Correct ordering of uses of '_item.mandatory_code' and
       '_item_default.value'.
    ;
    
    
       0.7.0   2000-09-09
    ;
       Respond to comments by I. David Brown.  (HJB)
    
       + Add further comments on '\n' and '\t'.
    
       + Update ITEM_UNITS_LIST by taking section from mmCIF dictionary
         and adding metres.  Change 'meter' to 'metre' throughout.
    
       + Add missing enumerations to '_array_structure.compression_type'
         and make 'none' the default.
    
       + Remove parent-child relationship between
         '_array_structure_list.index' and '_array_structure_list.precedence'.
    
       + Improve alphabetization.
    
       + Fix '_array_intensities_gain.esd' related function.
    
       + Improve comments in AXIS.
    
       + Fix DIFFRN_FRAME_DATA example.
    
       + Remove erroneous DIFFRN_MEASUREMENT example.
    
       + Add '_diffrn_measurement_axis.id' to the category key.
    ;
    
    
       0.6.0   1999-01-14
    ;
       Remove redundant information for ENC_NONE data.  (HJB)
    
       + After the D5 remove binary section identifier, size and
         compression type.
    
       + Add Control-L to header.
    ;
    
    
       0.5.1   1999-01-03
    ;
       Cleanup of typos and syntax errors.  (HJB)
    
       + Cleanup example details for DIFFRN_SCAN category.
    
       + Add missing quote marks for '_diffrn_scan.id' definition.
    ;
    
    
       0.5   1999-01-01
    ;
       Modifications for axis definitions and reduction of binary header.  (HJB)
    
       + Restore '_diffrn_detector.diffrn_id' to DIFFRN_DETECTOR KEY.
    
       + Add AXIS category.
    
       + Bring in complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories
         from cif_mm.dic for clarity.
    
       + Change '_array_structure.encoding_type' from type code to uline and
         added X-Binary-Element-Type to MIME header.
    
       + Add detector beam centre '_diffrn_detector_element.center[1]' and
         '_diffrn_detector_element.center[2]'.
    
       + Correct item name of '_diffrn_refln.frame_id'.
    
       + Replace reference to '_array_intensities.undefined' by
         '_array_intensities.undefined_value'.
    
       + Replace references to '_array_intensity.scaling' with
         '_array_intensities.scaling'.
    
       + Add DIFFRN_SCAN... categories.
    ;
    
    
       0.4   1998-08-11
    ;
       Modifications to the 0.3 imgCIF draft.  (HJB)
    
       + Reflow comment lines over 80 characters and corrected typos.
    
       + Update examples and descriptions of MIME encoded data.
    
       + Change name to cbfext98.dic.
    ;
    
    
       0.3   1998-07-04
    ;
       Modifications for imgCIF.  (HJB)
    
       + Add binary type, which is a text field containing a variant on
         MIME encoded data.
    
       + Change type of '_array_data.data' to binary and specify internal
         structure of raw binary data.
    
       + Add '_array_data.binary_id', and make
         '_diffrn_frame_data.binary_id' and '_array_intensities.binary_id'
         into pointers to this item.
    ;
    
    
       0.2   1997-12-02
    ;
       Modifications to the CBF draft.  (JW)
    
       + Add category hierarchy for describing frame data developed from
         discussions at the BNL imgCIF Workshop Oct 1997.   The following
         changes are made in implementing the workshop draft.  Category
         DIFFRN_ARRAY_DATA is renamed to DIFFRN_FRAME_DATA.  Category
         DIFFRN_FRAME_TYPE is renamed to DIFFRN_DETECTOR_ELEMENT.   The
         parent item for '_diffrn_frame_data.array_id' is changed from
         '_array_structure_list.array_id' to '_array_structure.id'. Item
         '_diffrn_detector.array_id' is deleted.
       + Add data item '_diffrn_frame_data.binary_id' to identify data
         groups within a binary section.  The formal identification of the
         binary section is still fuzzy.
    ;
    
    
       0.1   1997-01-24
    ;
       First draft of this dictionary in DDL 2.1 compliant format by John
       Westbrook (JW).  This version is adapted from the Crystallographic
       Binary File (CBF) Format Draft Proposal provided by Andy Hammersley
       (AH).
    
       Modifications to the CBF draft.  (JW)
    
       + In this version the array description has been cast in the categories
         ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST.  These categories
         have been generalized to describe array data  of arbitrary dimension.
    
       + Array data in this description are contained in the category
         ARRAY_DATA.  This departs from the CBF notion of data existing
         in some special comment. In this description, data are handled as an
         ordinary data item encapsulated in a character data type.   Although
         data this manner deviates from CIF conventions, it does not violate
         any DDL 2.1 rules.  DDL 2.1 regular expressions can be used to define
         the binary representation which will permit some level of data
         validation.  In this version, the placeholder type code "any" has
         been used. This translates to a regular expression which will match
         any pattern.
    
         It should be noted that DDL 2.1 already supports array data objects
         although these have not been used in the current mmCIF dictionary.
         It may be possible to use the DDL 2.1 ITEM_STRUCTURE and
         ITEM_STRUCTURE_LIST categories to provide the information that is
         carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST.  By
         moving the array structure to the DDL level it would be possible to
         define an array type as well as a regular expression defining the
         data format.
    
       + Multiple array sections can be properly handled within a single
         datablock.
    ;
    
    
    #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof
    
    ./CBFlib-0.9.2.2/doc/Iarray_structure.id.html0000644000076500007650000000623711603702115017203 0ustar yayayaya (IUCr) CIF Definition save__array_structure.id

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _array_structure.id

    Name:
    '_array_structure.id'

    Definition:

           The value of _array_structure.id must uniquely identify
                  each item of array data.
    
                  This item has been made implicit and given a default value of 1
                  as a convenience in writing miniCBF files.  Normally an
                  explicit name with useful content should be used.
    
    

    Type: code

    Mandatory item: implicit

    _array_data.array_id
    _array_structure_list.array_id
    _array_intensities.array_id
    _diffrn_data_frame.array_id

    Enumeration default: 1

    Category: array_structure

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_data_frame.detector_element_id.html0000644000076500007650000000556411603702115022764 0ustar yayayaya (IUCr) CIF Definition save__diffrn_data_frame.detector_element_id

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_data_frame.detector_element_id

    Name:
    '_diffrn_data_frame.detector_element_id'

    Definition:

            This item is a pointer to _diffrn_detector_element.id
                   in the DIFFRN_DETECTOR_ELEMENT category.
    
    

    Type: code

    Mandatory item: yes

    Alias:
    _diffrn_frame_data.detector_element_id (cif_img.dic version 1.0)

    Category: diffrn_data_frame

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Iaxis.id.html0000644000076500007650000000636411603702115014712 0ustar yayayaya (IUCr) CIF Definition save__axis.id

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _axis.id

    Name:
    '_axis.id'

    Definition:

           The value of _axis.id must uniquely identify
                  each axis relevant to the experiment.  Note that multiple
                  pieces of equipment may share the same axis (e.g. a twotheta
                  arm), so the category key for AXIS also includes the
                  equipment.
    
    

    Type: code

    Mandatory item: yes

    _axis.depends_on
    _array_structure_list_axis.axis_id
    _diffrn_detector_axis.axis_id
    _diffrn_measurement_axis.axis_id
    _diffrn_scan_axis.axis_id
    _diffrn_scan_frame_axis.axis_id

    Category: axis

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_measurement.device.html0000644000076500007650000001042511603702115020457 0ustar yayayaya (IUCr) CIF Definition save__diffrn_measurement.device

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_measurement.device

    Name:
    '_diffrn_measurement.device'

    Definition:

            The general class of goniometer or device used to support
                   and orient the specimen.
    
                   If the value of _diffrn_measurement.device is not given,
                   it is implicitly equal to the value of
                   _diffrn_measurement.diffrn_id.
    
                   Either _diffrn_measurement.device or
                   _diffrn_measurement.id may be used to link to other
                   categories.  If the experimental setup admits multiple
                   devices, then _diffrn_measurement.id is used to provide
                   a unique link.
    
    
    Examples:

    '3-circle camera'
    '4-circle camera'
    'kappa-geometry camera'
    'oscillation camera'
    'precession camera'

    Type: text

    Mandatory item: implicit

    Alias:
    _diffrn_measurement_device (cif_core.dic version 2.0.1) _diffrn_measurement_axis.measurement_device

    Category: diffrn_measurement

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Iarray_intensities.pixel_binning_method.html0000644000076500007650000001066611603702115023273 0ustar yayayaya (IUCr) CIF Definition save__array_intensities.pixel_binning_method

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _array_intensities.pixel_binning_method

    Name:
    '_array_intensities.pixel_binning_method'

    Definition:

            The value of _array_intensities.pixel_binning_method specifies
                   the method used to derive array elements from multiple pixels.
    
    

    Type: code

    Mandatory item: implicit


    The data value must be one of the following:


    hardware
    The element intensities were derived from the raw data of one or more pixels by used of hardware in the detector, e.g. by use of shift registers in a CCD to combine pixels into super-pixels.

    software
    The element intensities were derived from the raw data of more than one pixel by use of software.

    combined
    The element intensities were derived from the raw data of more than one pixel by use of both hardware and software, as when hardware binning is used in one direction and software in the other.

    none
    In the both directions, the data has not been binned. The number of pixels is equal to the number of elements. When the value of _array_intensities.pixel_binning_method is 'none' the values of _array_intensities.pixel_fast_bin_size and _array_intensities.pixel_slow_bin_size both must be 1.

    unspecified
    The method used to derive element intensities is not specified.

    Enumeration default: unspecified

    Category: array_intensities

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Idiffrn_data_frame.center_fast.html0000644000076500007650000000653211603702115021257 0ustar yayayaya (IUCr) CIF Definition save__diffrn_data_frame.center_fast

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_data_frame.center_fast

    Name:
    '_diffrn_data_frame.center_fast'

    Definition:

           The value of _diffrn_data_frame.center_fast is
                  the fast index axis beam center position relative to the detector
                  element face in the units specified in the data item
                  '_diffrn_data_frame.center_units' along the fast
                  axis of the detector from the center of the first pixel to
                  the point at which the Z-axis (which should be colinear with the
                  beam) intersects the face of the detector, if in fact is does.
                  At the time of the measurement the current setting of detector
                  positioner given frame are used.
    
                  It is important to note that for measurements in millimetres,
                  the sense of the axis is used, rather than the sign of the
                  pixel-to-pixel increments.
    
    
    

    Type: float

    Mandatory item: no

    Category: diffrn_data_frame

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/Iaxis.vector[1].html0000644000076500007650000000516311603702115016165 0ustar yayayaya (IUCr) CIF Definition save__axis.vector[1]

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _axis.vector[1]

    Name:
    '_axis.vector[1]'

    Definition:

            The [1] element of the three-element vector used to specify
                   the direction of a rotation or translation axis.
                   The vector should be normalized to be a unit vector and
                   is dimensionless.
    
    

    Type: float

    Mandatory item: no


    Enumeration default: 0.0

    Category: axis

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/mmcif_img.dic0000644000076500007650000055115611603702115014770 0ustar yayayaya########################################################################### # # File: mmcif_img.dic # Date: Tue Jun 13 06:05:48 EDT 2006 # # Created from files in CVS module dict-mmcif_img.dic unless noted: # mmcif_img-header.dic # mmcif_img-data.dic # mmcif_img-def-1.dic # ########################################################################### ############################################################################## # # Image CIF Dictionary (imgCIF) # and Crystallographic Binary File Dictionary (CBF) # Extending the Macromolecular CIF Dictionary (mmCIF) # # by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook # # This dictionary was adapted from format discussed at the imgCIF Workshop, # held at BNL Oct 1997 and the Crystallographic Binary File Format Draft # Proposal by Andrew Hammersley. The first DDL 2.1 Version was created by # John Westbrook. This version was drafted by Herbert J. Bernstein and # incorporates comments by I. David Brown, John Westbrook, Brian McMahon, # Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li, Gotzon Madariaga, # Frances C. Bernstein and others. # # Header Section # ############################################################################## data_mmcif_img.dic _datablock.id mmcif_img.dic _datablock.description ; This data block holds the Image mmCIF Dictionary (imgCIF) ; _dictionary.title mmcif_img.dic _dictionary.version 1.3.4 _dictionary.datablock_id mmcif_img.dic ######################## ## DICTIONARY_HISTORY ## ######################## loop_ _dictionary_history.version _dictionary_history.update _dictionary_history.revision 1.3.4 2005-03-08 ; Changes (JDW): + Incorportated Herb Bernstein's latest editoral changes from ITVG. + Repaired _items_units.code -> _item_type.code Changes as per Nicola Ashcroft. + Updated example 1 for DIFFRN_MEASUREMENT to agree with mmCIF. + Spelled out "micrometres" for "um" and "millimetres" for "mm". + Removed phrase "which may be stored" from ARRAY_STRUCTURE description. + Removed unused 'byte-offsets' compressions and updated cites to ITVG for '_array_structure.compression_type'. (HJB) ; 1.3.3 2004-08-08 ; Changes (JDW): + fixed cases where _item_units.code used instead of _item_type.code. ; 1.3.2 2004-04-15 ; Changes (JDW): + fixed item ordering in _diffrn_measurement_axis.measurement_id + added sub_category 'vector' ; 1.3.1 2003-08-13 ; Changes as per Frances C. Bernstein. + Identify initials. + Adopt British spelling for centre in text. + Set \p and \%Angstrom and powers. + Clean up commas and unclear wordings. + Clean up tenses in history. Changes as per Gotzon Madariaga. + Fix the ARRAY_DATA example to align '_array_data.binary_id' and X-Binary-Id. + Add a range to '_array_intensities.gain_esd'. + In the example of DIFFRN_DETECTOR_ELEMENT, '_diffrn_detector_element.id' and '_diffrn_detector_element.detector_id' interchanged. + Fix typos for direction, detector and axes. + Clarify description of polarisation. + Clarify axes in '_diffrn_detector_element.center[1]' '_diffrn_detector_element.center[2]'. + Add local item types for items that are pointers. (HJB) ; 1.3.0 2003-07-24 ; Changes as per Brian McMahon. + Consistently quote tags embedded in text. + Clean up introductory comments. + Adjust line lengths to fit in 80 character window. + Fix several descriptions in AXIS category which referred to '_axis.type' instead of the current item. + Fix erroneous use of deprecated item '_diffrn_detector_axis.id' in examples for DIFFRN_SCAN_AXIS. + Add deprecated items '_diffrn_detector_axis.id' and '_diffrn_measurement_axis.id'. (HJB) ; 1.2.4 2003-07-14 ; Changes as per I. David Brown. + Enhance descriptions in DIFFRN_SCAN_AXIS to make them less dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS. + Provide a copy of the deprecated DIFFRN_FRAME_DATA category for completeness. (HJB) ; 1.2.3 2003-07-03 ; Cleanup to conform to ITVG. + Correct sign error in ..._cubed units. + Correct '_diffrn_radiation.polarisn_norm' range. (HJB) ; 1.2.2 2003-03-10 ; Correction of typos in various DIFFRN_SCAN_AXIS descriptions. (HJB) ; 1.2.1 2003-02-22 ; Correction of ATOM_ for ARRAY_ typos in various descriptions. (HJB) ; 1.2 2003-02-07 ; Corrections to encodings (remove extraneous hyphens) remove extraneous underscore in '_array_structure.encoding_type' enumeration. Correct typos in items units list. (HJB) ; 1.1.3 2001-04-19 ; Another typo corrections by Wilfred Li, and cleanup by HJB. ; 1.1.2 2001-03-06 ; Several typo corrections by Wilfred Li. ; 1.1.1 2001-02-16 ; Several typo corrections by JW. ; 1.1 2001-02-06 ; Draft resulting from discussions on header for use at NSLS. (HJB) + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME. + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'. + Add '_diffrn_measurement_axis.measurement_device' and change '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'. + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source', '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm', '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end', '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr', '_diffrn_scan_axis.displacement_rstrt_incr', '_diffrn_scan_frame_axis.angle_increment', '_diffrn_scan_frame_axis.angle_rstrt_incr', '_diffrn_scan_frame_axis.displacement', '_diffrn_scan_frame_axis.displacement_increment',and '_diffrn_scan_frame_axis.displacement_rstrt_incr'. + Add '_diffrn_measurement.device' to category key. + Update yyyy-mm-dd to allow optional time with fractional seconds for time stamps. + Fix typos caught by RS. + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to allow for coupled axes, as in spiral scans. + Add examples for fairly complete headers thanks to R. Sweet and P. Ellis. ; 1.0 2000-12-21 ; Release version - few typos and tidying up. (BM & HJB) + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end of dictionary. + Alphabetize dictionary. ; 0.7.1 2000-09-29 ; Cleanup fixes. (JW) + Correct spelling of diffrn_measurement_axis in '_axis.id' + Correct ordering of uses of '_item.mandatory_code' and '_item_default.value'. ; 0.7.0 2000-09-09 ; Respond to comments by I. David Brown. (HJB) + Add further comments on '\n' and '\t'. + Update ITEM_UNITS_LIST by taking section from mmCIF dictionary and adding metres. Change 'meter' to 'metre' throughout. + Add missing enumerations to '_array_structure.compression_type' and make 'none' the default. + Remove parent-child relationship between '_array_structure_list.index' and '_array_structure_list.precedence'. + Improve alphabetization. + Fix '_array_intensities_gain.esd' related function. + Improve comments in AXIS. + Fix DIFFRN_FRAME_DATA example. + Remove erroneous DIFFRN_MEASUREMENT example. + Add '_diffrn_measurement_axis.id' to the category key. ; 0.6.0 1999-01-14 ; Remove redundant information for ENC_NONE data. (HJB) + After the D5 remove binary section identifier, size and compression type. + Add Control-L to header. ; 0.5.1 1999-01-03 ; Cleanup of typos and syntax errors. (HJB) + Cleanup example details for DIFFRN_SCAN category. + Add missing quote marks for '_diffrn_scan.id' definition. ; 0.5 1999-01-01 ; Modifications for axis definitions and reduction of binary header. (HJB) + Restore '_diffrn_detector.diffrn_id' to DIFFRN_DETECTOR KEY. + Add AXIS category. + Bring in complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories from cif_mm.dic for clarity. + Change '_array_structure.encoding_type' from type code to uline and added X-Binary-Element-Type to MIME header. + Add detector beam centre '_diffrn_detector_element.center[1]' and '_diffrn_detector_element.center[2]'. + Correct item name of '_diffrn_refln.frame_id'. + Replace reference to '_array_intensities.undefined' by '_array_intensities.undefined_value'. + Replace references to '_array_intensity.scaling' with '_array_intensities.scaling'. + Add DIFFRN_SCAN... categories. ; 0.4 1998-08-11 ; Modifications to the 0.3 imgCIF draft. (HJB) + Reflow comment lines over 80 characters and corrected typos. + Update examples and descriptions of MIME encoded data. + Change name to cbfext98.dic. ; 0.3 1998-07-04 ; Modifications for imgCIF. (HJB) + Add binary type, which is a text field containing a variant on MIME encoded data. + Change type of '_array_data.data' to binary and specify internal structure of raw binary data. + Add '_array_data.binary_id', and make '_diffrn_frame_data.binary_id' and '_array_intensities.binary_id' into pointers to this item. ; 0.2 1997-12-02 ; Modifications to the CBF draft. (JW) + Add category hierarchy for describing frame data developed from discussions at the BNL imgCIF Workshop Oct 1997. The following changes are made in implementing the workshop draft. Category DIFFRN_ARRAY_DATA is renamed to DIFFRN_FRAME_DATA. Category DIFFRN_FRAME_TYPE is renamed to DIFFRN_DETECTOR_ELEMENT. The parent item for '_diffrn_frame_data.array_id' is changed from '_array_structure_list.array_id' to '_array_structure.id'. Item '_diffrn_detector.array_id' is deleted. + Add data item '_diffrn_frame_data.binary_id' to identify data groups within a binary section. The formal identification of the binary section is still fuzzy. ; 0.1 1997-01-24 ; First draft of this dictionary in DDL 2.1 compliant format by John Westbrook (JW). This version is adapted from the Crystallographic Binary File (CBF) Format Draft Proposal provided by Andy Hammersley (AH). Modifications to the CBF draft. (JW) + In this version the array description has been cast in the categories ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. These categories have been generalized to describe array data of arbitrary dimension. + Array data in this description are contained in the category ARRAY_DATA. This departs from the CBF notion of data existing in some special comment. In this description, data is handled as an ordinary data item encapsulated in a character data type. Although data this manner deviates from CIF conventions, it does not violate any DDL 2.1 rules. DDL 2.1 regular expressions can be used to define the binary representation which will permit some level of data validation. In this version, the placeholder type code "any" has been used. This translates to a regular expression which will match any pattern. It should be noted that DDL 2.1 already supports array data objects although these have not been used in the current mmCIF dictionary. It may be possible to use the DDL 2.1 ITEM_STRUCTURE and ITEM_STRUCTURE_LIST categories to provide the information that is carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. By moving the array structure to the DDL level it would be possible to define an array type as well as a regular expression defining the data format. + Multiple array sections can be properly handled within a single datablock. ; ### EOF mmcif_img-header.dic ############################################################################## # # Image CIF Dictionary (imgCIF) # and Crystallographic Binary File Dictionary (CBF) # Extending the Macromolecular CIF Dictionary (mmCIF) # # Data Section # ############################################################################## ######################### ## CATEGORY_GROUP_LIST ## ######################### loop_ _category_group_list.id _category_group_list.parent_id _category_group_list.description 'inclusive_group' . ; Categories that belong to the dictionary extension. ; 'array_data_group' 'inclusive_group' ; Categories that describe array data. ; 'axis_group' 'inclusive_group' ; Categories that describe axes. ; 'diffrn_group' 'inclusive_group' ; Categories that describe details of the diffraction experiment. ; ################## ## SUB_CATEGORY ## ################## loop_ _sub_category.id _sub_category.description 'matrix' ; The collection of elements of a matrix. ; 'vector' ; The collection of elements of a vector. ; #################### ## ITEM_TYPE_LIST ## #################### # # # The regular expressions defined here are not compliant # with the POSIX 1003.2 standard as they include the # '\n' and '\t' special characters. These regular expressions # have been tested using version 0.12 of Richard Stallman's # GNU regular expression library in POSIX mode. # In order to allow presentation of a regular expression # in a text field concatenate any line ending in a backslash # with the following line, after discarding the backslash. # # A formal definition of the '\n' and '\t' special characters # is most properly done in the DDL, but for completeness, please # note that '\n' is the line termination character ('newline') # and '\t' is the horizontal tab character. There is a formal # ambiguity in the use of '\n' for line termination, in that # the intention is that the equivalent machine/OS-dependent line # termination character sequence should be accepted as a match, e.g. # # '\r' (control-M) under MacOS # '\n' (control-J) under Unix # '\r\n' (control-M control-J) under DOS and MS Windows # loop_ _item_type_list.code _item_type_list.primitive_code _item_type_list.construct _item_type_list.detail code char '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words ... ; ucode uchar '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words (case insensitive) ; line char '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types / multi-word items ... ; uline uchar '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types / multi-word items (case insensitive) ; text char '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; text item types / multi-line text ... ; binary char ;\n--CIF-BINARY-FORMAT-SECTION--\n\ [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\ \n--CIF-BINARY-FORMAT-SECTION---- ; ; binary items are presented as MIME-like ascii-encoded sections in an imgCIF. In a CBF, raw octet streams are used to convey the same information. ; int numb '-?[0-9]+' ; int item types are the subset of numbers that are the negative or positive integers. ; float numb '-?(([0-9]+)|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?' ; float item types are the subset of numbers that are the floating numbers. ; any char '.*' ; A catch all for items that may take any form... ; yyyy-mm-dd char ;\ [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9][0-9]\ (T[0-2][0-9]:[0-5][0-9]:[0-5][0-9](.[0-9]+)([+-][0-5][0-9]:[0-5][0-9])) ; ; Standard format for CIF date and time strings (see http://www.iucr.org/iucr-top/cif/spec/datetime.html), consisting of a yyyy-mm-dd date optionally followed by the character "T" followed by a 24-hour clock time, optionally followed by a signed time-zone offset. The IUCr standard has been extended to allow for an optional decimal fraction on the seconds of time. Time is local time if no time-zone offset is given. ; ##################### ## ITEM_UNITS_LIST ## ##################### loop_ _item_units_list.code _item_units_list.detail # 'metres' 'metres' 'centimetres' 'centimetres (metres * 10^( -2)^)' 'millimetres' 'millimetres (metres * 10^( -3)^)' 'nanometres' 'nanometres (metres * 10^( -9)^)' 'angstroms' '\%Angstroms (metres * 10^(-10)^)' 'picometres' 'picometres (metres * 10^(-12)^)' 'femtometres' 'femtometres (metres * 10^(-15)^)' # 'reciprocal_metres' 'reciprocal metres (metres^(-1)^)' 'reciprocal_centimetres' 'reciprocal centimetres ((metres * 10^( -2))^(-1)^)' 'reciprocal_millimetres' 'reciprocal millimetres ((metres * 10^( -3))^(-1)^)' 'reciprocal_nanometres' 'reciprocal nanometres ((metres * 10^( -9))^(-1)^)' 'reciprocal_angstroms' 'reciprocal angstroms ((metres * 10^(-10))^(-1)^)' 'reciprocal_picometres' 'reciprocal picometres ((metres * 10^(-12))^(-1)^)' # 'nanometres_squared' 'nanometres squared (metres * 10^( -9)^)^2^' 'angstroms_squared' '\%Angstroms squared (metres * 10^(-10)^)^2^' '8pi2_angstroms_squared' '8\p^2^ * \%Angstroms squared (metres * 10^(-10)^)^2^' 'picometres_squared' 'picometres squared (metres * 10^(-12)^)^2^' # 'nanometres_cubed' 'nanometres cubed (metres * 10^( -9)^)^3^' 'angstroms_cubed' '\%Angstroms cubed (metres * 10^(-10)^)^3^' 'picometres_cubed' 'picometres cubed (metres * 10^(-12)^)^3^' # 'kilopascals' 'kilopascals' 'gigapascals' 'gigapascals' # 'hours' 'hours' 'minutes' 'minutes' 'seconds' 'seconds' 'microseconds' 'microseconds' # 'degrees' 'degrees (of arc)' 'degrees_squared' 'degrees (of arc) squared' # 'degrees_per_minute' 'degrees (of arc) per minute' # 'celsius' 'degrees (of temperature) Celsius' 'kelvins' 'degrees (of temperature) Kelvin' # 'counts' 'counts' 'counts_per_photon' 'counts per photon' # 'electrons' 'electrons' # 'electrons_squared' 'electrons squared' # 'electrons_per_nanometres_cubed' ; electrons per nanometres cubed (electrons/(metres * 10^( -9)^)^(-3)^) ; 'electrons_per_angstroms_cubed' ; electrons per angstroms cubed (electrons/(metres * 10^(-10)^)^(-3)^) ; 'electrons_per_picometres_cubed' ; electrons per picometres cubed (electrons/(metres * 10^(-12)^)^(-3)^) ; 'kilowatts' 'kilowatts' 'milliamperes' 'milliamperes' 'kilovolts' 'kilovolts' # 'arbitrary' ; arbitrary system of units. ; # loop_ _item_units_conversion.from_code _item_units_conversion.to_code _item_units_conversion.operator _item_units_conversion.factor ### 'metres' 'centimetres' '*' 1.0E+02 'metres' 'millimetres' '*' 1.0E+03 'metres' 'nanometres' '*' 1.0E+09 'metres' 'angstroms' '*' 1.0E+10 'metres' 'picometres' '*' 1.0E+12 'metres' 'femtometres' '*' 1.0E+15 # 'centimetres' 'metres' '*' 1.0E-02 'centimetres' 'millimetres' '*' 1.0E+01 'centimetres' 'nanometres' '*' 1.0E+07 'centimetres' 'angstroms' '*' 1.0E+08 'centimetres' 'picometres' '*' 1.0E+10 'centimetres' 'femtometres' '*' 1.0E+13 # 'millimetres' 'metres' '*' 1.0E-03 'millimetres' 'centimetres' '*' 1.0E-01 'millimetres' 'nanometres' '*' 1.0E+06 'millimetres' 'angstroms' '*' 1.0E+07 'millimetres' 'picometres' '*' 1.0E+09 'millimetres' 'femtometres' '*' 1.0E+12 # 'nanometres' 'metres' '*' 1.0E-09 'nanometres' 'centimetres' '*' 1.0E-07 'nanometres' 'millimetres' '*' 1.0E-06 'nanometres' 'angstroms' '*' 1.0E+01 'nanometres' 'picometres' '*' 1.0E+03 'nanometres' 'femtometres' '*' 1.0E+06 # 'angstroms' 'metres' '*' 1.0E-10 'angstroms' 'centimetres' '*' 1.0E-08 'angstroms' 'millimetres' '*' 1.0E-07 'angstroms' 'nanometres' '*' 1.0E-01 'angstroms' 'picometres' '*' 1.0E+02 'angstroms' 'femtometres' '*' 1.0E+05 # 'picometres' 'metres' '*' 1.0E-12 'picometres' 'centimetres' '*' 1.0E-10 'picometres' 'millimetres' '*' 1.0E-09 'picometres' 'nanometres' '*' 1.0E-03 'picometres' 'angstroms' '*' 1.0E-02 'picometres' 'femtometres' '*' 1.0E+03 # 'femtometres' 'metres' '*' 1.0E-15 'femtometres' 'centimetres' '*' 1.0E-13 'femtometres' 'millimetres' '*' 1.0E-12 'femtometres' 'nanometres' '*' 1.0E-06 'femtometres' 'angstroms' '*' 1.0E-05 'femtometres' 'picometres' '*' 1.0E-03 ### 'reciprocal_centimetres' 'reciprocal_metres' '*' 1.0E+02 'reciprocal_centimetres' 'reciprocal_millimetres' '*' 1.0E-01 'reciprocal_centimetres' 'reciprocal_nanometres' '*' 1.0E-07 'reciprocal_centimetres' 'reciprocal_angstroms' '*' 1.0E-08 'reciprocal_centimetres' 'reciprocal_picometres' '*' 1.0E-10 # 'reciprocal_millimetres' 'reciprocal_metres' '*' 1.0E+03 'reciprocal_millimetres' 'reciprocal_centimetres' '*' 1.0E+01 'reciprocal_millimetres' 'reciprocal_nanometres' '*' 1.0E-06 'reciprocal_millimetres' 'reciprocal_angstroms' '*' 1.0E-07 'reciprocal_millimetres' 'reciprocal_picometres' '*' 1.0E-09 # 'reciprocal_nanometres' 'reciprocal_metres' '*' 1.0E+09 'reciprocal_nanometres' 'reciprocal_centimetres' '*' 1.0E+07 'reciprocal_nanometres' 'reciprocal_millimetres' '*' 1.0E+06 'reciprocal_nanometres' 'reciprocal_angstroms' '*' 1.0E-01 'reciprocal_nanometres' 'reciprocal_picometres' '*' 1.0E-03 # 'reciprocal_angstroms' 'reciprocal_metres' '*' 1.0E+10 'reciprocal_angstroms' 'reciprocal_centimetres' '*' 1.0E+08 'reciprocal_angstroms' 'reciprocal_millimetres' '*' 1.0E+07 'reciprocal_angstroms' 'reciprocal_nanometres' '*' 1.0E+01 'reciprocal_angstroms' 'reciprocal_picometres' '*' 1.0E-02 # 'reciprocal_picometres' 'reciprocal_metres' '*' 1.0E+12 'reciprocal_picometres' 'reciprocal_centimetres' '*' 1.0E+10 'reciprocal_picometres' 'reciprocal_millimetres' '*' 1.0E+09 'reciprocal_picometres' 'reciprocal_nanometres' '*' 1.0E+03 'reciprocal_picometres' 'reciprocal_angstroms' '*' 1.0E+01 ### 'nanometres_squared' 'angstroms_squared' '*' 1.0E+02 'nanometres_squared' 'picometres_squared' '*' 1.0E+06 # 'angstroms_squared' 'nanometres_squared' '*' 1.0E-02 'angstroms_squared' 'picometres_squared' '*' 1.0E+04 'angstroms_squared' '8pi2_angstroms_squared' '*' 78.9568 # 'picometres_squared' 'nanometres_squared' '*' 1.0E-06 'picometres_squared' 'angstroms_squared' '*' 1.0E-04 ### 'nanometres_cubed' 'angstroms_cubed' '*' 1.0E+03 'nanometres_cubed' 'picometres_cubed' '*' 1.0E+09 # 'angstroms_cubed' 'nanometres_cubed' '*' 1.0E-03 'angstroms_cubed' 'picometres_cubed' '*' 1.0E+06 # 'picometres_cubed' 'nanometres_cubed' '*' 1.0E-09 'picometres_cubed' 'angstroms_cubed' '*' 1.0E-06 ### 'kilopascals' 'gigapascals' '*' 1.0E-06 'gigapascals' 'kilopascals' '*' 1.0E+06 ### 'hours' 'minutes' '*' 6.0E+01 'hours' 'seconds' '*' 3.6E+03 'hours' 'microseconds' '*' 3.6E+09 # 'minutes' 'hours' '/' 6.0E+01 'minutes' 'seconds' '*' 6.0E+01 'minutes' 'microseconds' '*' 6.0E+07 # 'seconds' 'hours' '/' 3.6E+03 'seconds' 'minutes' '/' 6.0E+01 'seconds' 'microseconds' '*' 1.0E+06 # 'microseconds' 'hours' '/' 3.6E+09 'microseconds' 'minutes' '/' 6.0E+07 'microseconds' 'seconds' '/' 1.0E+06 ### 'celsius' 'kelvins' '-' 273.0 'kelvins' 'celsius' '+' 273.0 ### 'electrons_per_nanometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E+03 'electrons_per_nanometres_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+09 # 'electrons_per_angstroms_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-03 'electrons_per_angstroms_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+06 # 'electrons_per_picometres_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-09 'electrons_per_picometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E-06 ### ### EOF mmcif_img-data.dic ############################################################################## # CONTENTS # # CATEGORY_GROUP_LIST # # category ARRAY_DATA # # _array_data.array_id # _array_data.binary_id # _array_data.data # # category ARRAY_ELEMENT_SIZE # # _array_element_size.array_id # _array_element_size.index # _array_element_size.size # # category ARRAY_INTENSITIES # # _array_intensities.array_id # _array_intensities.binary_id # _array_intensities.gain # _array_intensities.gain_esd # _array_intensities.linearity # _array_intensities.offset # _array_intensities.scaling # _array_intensities.overload # _array_intensities.undefined_value # # category ARRAY_STRUCTURE # # _array_structure.byte_order # _array_structure.compression_type # _array_structure.encoding_type # _array_structure.id # # category ARRAY_STRUCTURE_LIST # # _array_structure_list.axis_set_id # _array_structure_list.array_id # _array_structure_list.dimension # _array_structure_list.direction # _array_structure_list.index # _array_structure_list.precedence # # category ARRAY_STRUCTURE_LIST_AXIS # # _array_structure_list_axis.axis_id # _array_structure_list_axis.axis_set_id # _array_structure_list_axis.angle # _array_structure_list_axis.angle_increment # _array_structure_list_axis.displacement_increment # _array_structure_list_axis.angular_pitch # _array_structure_list_axis.radial_pitch # # category AXIS # # _axis.depends_on # _axis.equipment # _axis.id # _axis.offset[1] # _axis.offset[2] # _axis.offset[3] # _axis.type # _axis.vector[1] # _axis.vector[2] # _axis.vector[3] # # category DIFFRN_DATA_FRAME # # _diffrn_data_frame.array_id # _diffrn_data_frame.binary_id # _diffrn_data_frame.detector_element_id # _diffrn_data_frame.id # # category DIFFRN_DETECTOR # # _diffrn_detector.details # _diffrn_detector.detector # _diffrn_detector.diffrn_id # _diffrn_detector.dtime # _diffrn_detector.id # _diffrn_detector.number_of_axes # _diffrn_detector.type # # category DIFFRN_DETECTOR_AXIS # # _diffrn_detector_axis.axis_id # _diffrn_detector_axis.detector_id # # category DIFFRN_DETECTOR_ELEMENT # # _diffrn_detector_element.center[1] # _diffrn_detector_element.center[2] # _diffrn_detector_element.id # _diffrn_detector_element.detector_id # # category DIFFRN_MEASUREMENT # # _diffrn_measurement.diffrn_id # _diffrn_measurement.details # _diffrn_measurement.device # _diffrn_measurement.device_details # _diffrn_measurement.device_type # _diffrn_measurement.id # _diffrn_measurement.method # _diffrn_measurement.number_of_axes # _diffrn_measurement.specimen_support # # category DIFFRN_MEASUREMENT_AXIS # # _diffrn_measurement_axis.axis_id # _diffrn_measurement_axis.measurement_device # _diffrn_measurement_axis.measurement_id # # category DIFFRN_RADIATION # # _diffrn_radiation.collimation # _diffrn_radiation.diffrn_id # _diffrn_radiation.div_x_source # _diffrn_radiation.div_y_source # _diffrn_radiation.div_x_y_source # _diffrn_radiation.filter_edge' # _diffrn_radiation.inhomogeneity # _diffrn_radiation.monochromator # _diffrn_radiation.polarisn_norm # _diffrn_radiation.polarisn_ratio # _diffrn_radiation.polarizn_source_norm # _diffrn_radiation.polarizn_source_ratio # _diffrn_radiation.probe # _diffrn_radiation.type # _diffrn_radiation.xray_symbol # _diffrn_radiation.wavelength_id # # category DIFFRN_REFLN # # _diffrn_refln.frame_id # # category DIFFRN_SCAN # # _diffrn_scan.id # _diffrn_scan.date_end # _diffrn_scan.date_start # _diffrn_scan.integration_time # _diffrn_scan.frame_id_start # _diffrn_scan.frame_id_end # _diffrn_scan.frames # # category DIFFRN_SCAN_AXIS # # _diffrn_scan_axis.axis_id # _diffrn_scan_axis.angle_start # _diffrn_scan_axis.angle_range # _diffrn_scan_axis.angle_increment # _diffrn_scan_axis.angle_rstrt_incr # _diffrn_scan_axis.displacement_start # _diffrn_scan_axis.displacement_range # _diffrn_scan_axis.displacement_increment # _diffrn_scan_axis.displacement_rstrt_incr # _diffrn_scan_axis.scan_id # # category DIFFRN_SCAN_FRAME # # _diffrn_scan_frame.date # _diffrn_scan_frame.frame_id # _diffrn_scan_frame.frame_number # _diffrn_scan_frame.integration_time # _diffrn_scan_frame.scan_id # # category DIFFRN_SCAN_FRAME_AXIS # # _diffrn_scan_frame_axis.axis_id # _diffrn_scan_frame_axis.angle # _diffrn_scan_frame_axis.angle_increment # _diffrn_scan_frame_axis.angle_rstrt_incr # _diffrn_scan_frame_axis.displacement # _diffrn_scan_frame_axis.displacement_increment # _diffrn_scan_frame_axis.displacement_rstrt_incr # _diffrn_scan_frame_axis.frame_id # # ***DEPRECATED*** data items # # _diffrn_detector_axis.id # _diffrn_measurement_axis.id # # ***DEPRECATED*** category DIFFRN_FRAME_DATA # # _diffrn_frame_data.array_id # _diffrn_frame_data.binary_id # _diffrn_frame_data.detector_element_id # _diffrn_frame_data.id # # # ITEM_TYPE_LIST # ITEM_UNITS_LIST # DICTIONARY_HISTORY # ############################################################################## ############## # ARRAY_DATA # ############## save_array_data _category.description ; Data items in the ARRAY_DATA category are the containers for the array data items described in category ARRAY_STRUCTURE. ; _category.id array_data _category.mandatory_code no loop_ _category_key.name '_array_data.array_id' '_array_data.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows two binary data blocks. The first one was compressed by the CBF_CANONICAL compression algorithm and presented as hexadecimal data. The first character "H" on the data lines means hexadecimal. It could have been "O" for octal or "D" for decimal. The second character on the line shows the number of bytes in each word (in this case "4"), which then requires 8 hexadecimal digits per word. The third character gives the order of octets within a word, in this case "<" for the ordering 4321 (i.e. "big-endian"). Alternatively the character ">" could have been used for the ordering 1234 (i.e. "little-endian"). The block has a "message digest" to check the integrity of the data. The second block is similar, but uses CBF_PACKED compression and BASE64 encoding. Note that the size and the digest are different. ; ; loop_ _array_data.array_id _array_data.binary_id _array_data.data image_1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_CANONICAL" Content-Transfer-Encoding: X-BASE16 X-Binary-Size: 3927126 X-Binary-ID: 1 Content-MD5: u2sTJEovAHkmkDjPi+gWsg== # Hexadecimal encoding, byte 0, byte order ...21 # H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ... .... --CIF-BINARY-FORMAT-SECTION---- ; image_2 2 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF-PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3745758 X-Binary-ID: 2 Content-MD5: 1zsJjWPfol2GYl2V+QSXrw== ELhQAAAAAAAA... ... --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_data.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_array_data.array_id' _item.category_id array_data _item.mandatory_code yes _item_type.code code save_ save__array_data.binary_id _item_description.description ; This item is an integer identifier which, along with '_array_data.array_id' should uniquely identify the particular block of array data. If '_array_data.binary_id' is not explicitly given, it defaults to 1. The value of '_array_data.binary_id' distinguishes among multiple sets of data with the same array structure. If the MIME header of the data array specifies a value for X-Binary-Id, the value of '_array_data.binary_id' should be equal the value given for X-Binary-Id. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_data.binary_id' array_data implicit '_diffrn_data_frame.binary_id' diffrn_data_frame implicit '_array_intensities.binary_id' array_intensities implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.binary_id' '_array_data.binary_id' '_array_intensities.binary_id' '_array_data.binary_id' _item_default.value 1 _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_data.data _item_description.description ; The value of '_array_data.data' contains the array data encapsulated in a STAR string. The representation used is a variant on the Multipurpose Internet Mail Extensions (MIME) specified in RFC 2045-2049 by N. Freed et al. The boundary delimiter used in writing an imgCIF or CBF is "--CIF-BINARY-FORMAT-SECTION--" (including the required initial "--"). The Content-Type may be any of the discrete types permitted in RFC 2045; "application/octet-stream" is recommended. If an octet stream was compressed, the compression should be specified by the parameter 'conversions="x-CBF_PACKED"' or the parameter 'conversions="x-CBF_CANONICAL"'. The Content-Transfer-Encoding may be "BASE64", "Quoted-Printable", "X-BASE8", "X-BASE10", or "X-BASE16" for an imgCIF or "BINARY" for a CBF. The octal, decimal and hexadecimal transfer encodings are for convenience in debugging, and are not recommended for archiving and data interchange. In an imgCIF file, the encoded binary data begins after the empty line terminating the header. In a CBF, the raw binary data begins after an empty line terminating the header and after the sequence: Octet Hex Decimal Purpose 0 0C 12 (ctrl-L) Page break 1 1A 26 (ctrl-Z) Stop listings in MS-DOS 2 04 04 (Ctrl-D) Stop listings in UNIX 3 D5 213 Binary section begins None of these octets are included in the calculation of the message size, nor in the calculation of the message digest. The X-Binary-Size header specifies the size of the equivalent binary data in octets. If compression was used, this size is the size after compression, including any book-keeping fields. An adjustment is made for the deprecated binary formats in which eight bytes of binary header are used for the compression type. In that case, the eight bytes used for the compression type is subtracted from the size, so that the same size will be reported if the compression type is supplied in the MIME header. Use of the MIME header is the recommended way to supply the compression type. In general, no portion of the binary header is included in the calculation of the size. The X-Binary-Element-Type header specifies the type of binary data in the octets, using the same descriptive phrases as in '_array_structure.encoding_type'. The default value is "unsigned 32-bit integer". An MD5 message digest may, optionally, be used. The "RSA Data Security, Inc. MD5 Message-Digest Algorithm" should be used. No portion of the header is included in the calculation of the message digest. If the Transfer Encoding is "X-BASE8", "X-BASE10", or "X-BASE16", the data is presented as octal, decimal or hexadecimal data organized into lines or words. Each word is created by composing octets of data in fixed groups of 2, 3, 4, 6 or 8 octets, either in the order ...4321 ("big- endian") or 1234... (little-endian). If there are fewer than the specified number of octets to fill the last word, then the missing octets are presented as "==" for each missing octet. Exactly two equal signs are used for each missing octet even for octal and decimal encoding. The format of lines is: rnd xxxxxx xxxxxx xxxxxx where r is "H", "O", or "D" for hexadecimal, octal or decimal, n is the number of octets per word. and d is "<" for ">" for the "...4321" and "1234..." octet orderings respectively. The "==" padding for the last word should be on the appropriate side to correspond to the missing octets, e.g. H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000 or H3> FF0700 00==== For these hex, octal and decimal formats, only, comments beginning with "#" are permitted to improve readability. BASE64 encoding follows MIME conventions. Octets are in groups of three, c1, c2, c3. The resulting 24 bits are broken into four 6-bit quantities, starting with the high-order six bits (c1 >> 2) of the first octet, then the low-order two bits of the first octet followed by the high-order 4 bits of the second octet ((c1 & 3)<<4 | (c2>>4)), then the bottom 4 bits of the second octet followed by the high order two bits of the last octet ((c2 & 15)<<2 | (c3>>6)), then the bottom six bits of the last octet (c3 & 63). Each of these four quantities is translated into an ASCII character using the mapping: 1 2 3 4 5 6 0123456789012345678901234567890123456789012345678901234567890123 | | | | | | | ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/ With short groups of octets padded on the right with one "=" if c3 is missing, and with "==" if both c2 and c3 are missing. QUOTED-PRINTABLE encoding also follows MIME conventions, copying octets without translation if their ASCII values are 32..38, 42, 48..57, 59..60, 62, 64..126 and the octet is not a ";" in column 1. All other characters are translated to =nn, where nn is the hexadecimal encoding of the octet. All lines are "wrapped" with a terminating "=" (i.e. the MIME conventions for an implicit line terminator are never used). ; _item.name '_array_data.data' _item.category_id array_data _item.mandatory_code yes _item_type.code binary save_ ###################### # ARRAY_ELEMENT_SIZE # ###################### save_array_element_size _category.description ; Data items in the ARRAY_ELEMENT_SIZE category record the physical size of array elements along each array dimension. ; _category.id array_element_size _category.mandatory_code no loop_ _category_key.name '_array_element_size.array_id' '_array_element_size.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A regular 2D array with a uniform element dimension of 1220 nanometres. ; ; loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size image_1 1 1.22e-6 image_1 2 1.22e-6 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_element_size.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_array_element_size.array_id' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.index _item_description.description ; This item is a pointer to '_array_structure_list.index' in the ARRAY_STRUCTURE_LIST category. ; _item.name '_array_element_size.index' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.size _item_description.description ; The size in metres of an image element in this dimension. This supposes that the elements are arranged on a regular grid. ; _item.name '_array_element_size.size' _item.category_id array_element_size _item.mandatory_code yes _item_type.code float _item_units.code 'metres' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ ##################### # ARRAY_INTENSITIES # ##################### save_array_intensities _category.description ; Data items in the ARRAY_INTENSITIES category record the information required to recover the intensity data from the set of data values stored in the ARRAY_DATA category. The actual detector may have a complex relationship between the raw intensity values and the number of incident photons. In most cases, the number stored in the final array will have a simple linear relationship to the actual number of incident photons, given by '_array_intensities.gain'. If raw, uncorrected values are presented (e.g for calibration experiments), the value of '_array_intensities.linearity' will be 'raw' and '_array_intensities.gain' will not be used. ; _category.id array_intensities _category.mandatory_code no loop_ _category_key.name '_array_intensities.array_id' '_array_intensities.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 ; ; loop_ _array_intensities.array_id _array_intensities.linearity _array_intensities.gain _array_intensities.overload _array_intensities.undefined_value image_1 linear 1.2 655535 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_intensities.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_array_intensities.array_id' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code save_ save__array_intensities.binary_id _item_description.description ; This item is a pointer to '_array_data.binary_id' in the ARRAY_DATA category. ; _item.name '_array_intensities.binary_id' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code int save_ save__array_intensities.gain _item_description.description ; Detector "gain". The factor by which linearized intensity count values should be divided to produce true photon counts. ; _item.name '_array_intensities.gain' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain_esd' 'associated_value' save_ save__array_intensities.gain_esd _item_description.description ; The estimated standard deviation in detector "gain". ; _item.name '_array_intensities.gain_esd' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain' 'associated_esd' save_ save__array_intensities.linearity _item_description.description ; The intensity linearity scaling used from raw intensity to the stored element value: 'linear' is obvious 'offset' means that the value defined by '_array_intensities.offset' should be added to each element value. 'scaling' means that the value defined by '_array_intensities.scaling' should be multiplied with each element value. 'scaling_offset' is the combination of the two previous cases, with the scale factor applied before the offset value. 'sqrt_scaled' means that the square root of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and squaring the result. 'logarithmic_scaled' means that the logarithm based 10 of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and calculating 10 to the power of this number. 'raw' means that the data is a set of raw values straight from the detector. ; _item.name '_array_intensities.linearity' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'linear' . 'offset' ; The value defined by '_array_intensities.offset' should be added to each element value. ; 'scaling' ; The value defined by '_array_intensities.scaling' should be multiplied with each element value. ; 'scaling_offset' ; The combination of the scaling and offset with the scale factor applied before the offset value. ; 'sqrt_scaled' ; The square root of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and squaring the result. ; 'logarithmic_scaled' ; The logarithm based 10 of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and calculating 10 to the power of this number. ; 'raw' ; The array consists of raw values to which no corrections have been applied. While the handling of the data is similar to that given for 'linear' data with no offset, the meaning of the data differs in that the number of incident photons is not necessarily linearly related to the number of counts reported. This value is intended for use either in calibration experiments or to allow for handling more complex data fitting algorithms than are allowed for by this data item. ; save_ save__array_intensities.offset _item_description.description ; Offset value to add to array element values in the manner described by item '_array_intensities.linearity'. ; _item.name '_array_intensities.offset' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.scaling _item_description.description ; Multiplicative scaling value to be applied to array data in the manner described by item '_array_intensities.linearity'. ; _item.name '_array_intensities.scaling' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.overload _item_description.description ; The saturation intensity level for this data array. ; _item.name '_array_intensities.overload' _item.category_id array_intensities _item.mandatory_code no _item_type.code float _item_units.code 'counts' save_ save__array_intensities.undefined_value _item_description.description ; A value to be substituted for undefined values in the data array. ; _item.name '_array_intensities.undefined_value' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ ################### # ARRAY_STRUCTURE # ################### save_array_structure _category.description ; Data items in the ARRAY_STRUCTURE category record the organization and encoding of array data in the ARRAY_DATA category. ; _category.id array_structure _category.mandatory_code no _category_key.name '_array_structure.id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order image_1 "unsigned 16-bit integer" none little_endian ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure.byte_order _item_description.description ; The order of bytes for integer values which require more than 1-byte. (IBM-PC's and compatibles, and Dec-Vaxes use low-byte-first ordered integers, whereas Hewlett Packard 700 series, Sun-4 and Silicon Graphics use high-byte-first ordered integers. Dec-Alphas can produce/use either depending on a compiler switch.) ; _item.name '_array_structure.byte_order' _item.category_id array_structure _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'big_endian' ; The first byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; 'little_endian' ; The last byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; save_ save__array_structure.compression_type _item_description.description ; Type of data compression method used to compress the array data. ; _item.name '_array_structure.compression_type' _item.category_id array_structure _item.mandatory_code no _item_type.code code _item_default.value 'none' loop_ _item_enumeration.value _item_enumeration.detail 'none' ; Data are stored in normal format as defined by '_array_structure.encoding_type' and '_array_structure.byte_order'. ; 'packed' ; Using the 'packed' compression scheme, a CCP4-style packing (ITVG Chapter 5.6, section 3.1) ; 'canonical' ; Using the 'canonical' compression scheme ((ITVG Chapter 5.6, section 3.2) ; save_ save__array_structure.encoding_type _item_description.description ; Data encoding of a single element of array data. In several cases, the IEEE format is referenced. See "IEEE Standard for Binary Floating-Point Arithmetic", ANSI/IEEE Std 754-1985, the Institute of Electrical and Electronics Engineers, Inc., NY 1985. ; _item.name '_array_structure.encoding_type' _item.category_id array_structure _item.mandatory_code yes _item_type.code uline loop_ _item_enumeration.value 'unsigned 8-bit integer' 'signed 8-bit integer' 'unsigned 16-bit integer' 'signed 16-bit integer' 'unsigned 32-bit integer' 'signed 32-bit integer' 'signed 32-bit real IEEE' 'signed 64-bit real IEEE' 'signed 32-bit complex IEEE' save_ save__array_structure.id _item_description.description ; The value of '_array_structure.id' must uniquely identify each item of array data. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure.id' array_structure yes '_array_data.array_id' array_data yes '_array_structure_list.array_id' array_structure_list yes '_array_intensities.array_id' array_intensities yes '_diffrn_data_frame.array_id' diffrn_data_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_data.array_id' '_array_structure.id' '_array_structure_list.array_id' '_array_structure.id' '_array_intensities.array_id' '_array_structure.id' '_diffrn_data_frame.array_id' '_array_structure.id' save_ ######################## # ARRAY_STRUCTURE_LIST # ######################## save_array_structure_list _category.description ; Data items in the ARRAY_STRUCTURE_LIST category record the size and organization of each array dimension. The relationship to physical axes may be given. ; _category.id array_structure_list _category.mandatory_code no loop_ _category_key.name '_array_structure_list.array_id' '_array_structure_list.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - An image array of 1300 x 1200 elements. The raster order of the image is left-to-right (increasing) in the first dimension and bottom-to-top (decreasing) in the second dimension. ; ; loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id image_1 1 1300 1 increasing ELEMENT_X image_1 2 1200 2 decreasing ELEMENY_Y ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure_list.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_array_structure_list.array_id' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code code save_ save__array_structure_list.axis_set_id _item_description.description ; This is a descriptor for the physical axis or set of axes corresponding to an array index. This data item is related to the axes of the detector itself given in DIFFRN_DETECTOR_AXIS, but usually differ in that the axes in this category are the axes of the coordinate system of reported data points, while the axes in DIFFRN_DETECTOR_AXIS are the physical axes of the detector describing the "poise" of the detector as an overall physical object. If there is only one axis in the set, the identifier of that axis should be used as the identifier of the set. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.axis_set_id' array_structure_list yes '_array_structure_list_axis.axis_set_id' array_structure_list_axis implicit _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_structure_list_axis.axis_set_id' '_array_structure_list.axis_set_id' save_ save__array_structure_list.dimension _item_description.description ; The number of elements stored in the array structure in this dimension. ; _item.name '_array_structure_list.dimension' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.direction _item_description.description ; Identifies the direction in which this array index changes. ; _item.name '_array_structure_list.direction' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_enumeration.value _item_enumeration.detail 'increasing' ; Indicates the index changes from 1 to the maximum dimension. ; 'decreasing' ; Indicates the index changes from the maximum dimension to 1. ; save_ save__array_structure_list.index _item_description.description ; Identifies the one-based index of the row or column in the array structure. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.index' array_structure_list yes '_array_structure_list.precedence' array_structure_list yes '_array_element_size.index' array_element_size yes _item_type.code int loop_ _item_linked.child_name _item_linked.parent_name '_array_element_size.index' '_array_structure_list.index' loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.precedence _item_description.description ; Identifies the rank order in which this array index changes with respect to other array indices. The precedence of 1 indicates the index which changes fastest. ; _item.name '_array_structure_list.precedence' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ ############################# # ARRAY_STRUCTURE_LIST_AXIS # ############################# save_array_structure_list_axis _category.description ; Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe the physical settings of sets axes for the centres of pixels that correspond to data points described in the ARRAY_STRUCTURE_LIST category. In the simplest cases, the physical increments of a single axis correspond to the increments of a single array index. More complex organizations, e.g. spiral scans, may require coupled motions along multiple axes. Note that a spiral scan uses two coupled axis, one for the angular direction, one for the radial direction. This differs from a cylindrical scan for which the two axes are not coupled into one set. ; _category.id array_structure_list_axis _category.mandatory_code no loop_ _category_key.name '_array_structure_list_axis.axis_set_id' '_array_structure_list_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' save_ save__array_structure_list_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes from the set of axes for which settings are being specified. Multiple axes may be specified for the same value of '_array_structure_list_axis.axis_set_id' This item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_array_structure_list_axis.axis_id' _item.category_id array_structure_list_axis _item.mandatory_code yes _item_type.code code save_ save__array_structure_list_axis.axis_set_id _item_description.description ; The value of this data item is the identifier of the set of axes for which axis settings are being specified. Multiple axes may be specified for the same value of '_array_structure_list_axis.axis_set_id'. This item is a pointer to '_array_structure_list.axis_set_id' in the ARRAY_STRUCTURE_LIST category. If this item is not specified, it defaults to the corresponding axis identifier. ; _item.name '_array_structure_list_axis.axis_set_id' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_type.code code save_ save__array_structure_list_axis.angle _item_description.description ; The setting of the specified axis in degrees for the first data point of the array index with the corresponding value of '_array_structure_list.axis_set_id'. If the index is specified as 'increasing' this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing' this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.angle' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.angle_increment _item_description.description ; The pixel-centre-to-pixel-centre increment in the angular setting of the specified axis in degrees. This is not meaningful in the case of 'constant velocity' spiral scans and should not be specified in that case. See '_array_structure_list_axis.angular_pitch'. ; _item.name '_array_structure_list_axis.angle_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for the first data point of the array index with the corresponding value of '_array_structure_list.axis_set_id'. If the index is specified as 'increasing' this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing' this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.displacement' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.displacement_increment _item_description.description ; The pixel-centre-to-pixel-centre increment for the displacement setting of the specified axis in millimetres. ; _item.name '_array_structure_list_axis.displacement_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.angular_pitch _item_description.description ; The pixel-centre-to-pixel-centre distance for a one step change in the setting of the specified axis in millimetres. This is meaningful only for 'constant velocity' spiral scans, or for uncoupled angular scans at a constant radius (cylindrical scan) and should not be specified for cases in which the angle between pixels, rather than the distance between pixels is uniform. See '_array_structure_list_axis.angle_increment'. ; _item.name '_array_structure_list_axis.angular_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.radial_pitch _item_description.description ; The radial distance from one "cylinder" of pixels to the next in millimetres. If the scan is a 'constant velocity' scan with differing angular displacements between pixels, the value of this item may differ significantly from the value of '_array_structure_list_axis.displacement_increment'. ; _item.name '_array_structure_list_axis.radial_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ ######## # AXIS # ######## save_axis _category.description ; Data items in the AXIS category record the information required to describe the various goniometer, detector, source and other axes needed to specify a data collection. The location of each axis is specified by two vectors: the axis itself, given as a unit vector, and an offset to the base of the unit vector. These vectors are referenced to a right-handed laboratory coordinate system with its origin in the sample or specimen: | Y (to complete right-handed system) | | | | | |________________X / principal goniometer axis / / / / /Z (to source) Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from the sample or specimen along the principal axis of the goniometer. Axis 2 (Y): The Y-axis completes an orthogonal right-handed system defined by the X-axis and the Z-axis (see below). Axis 3 (Z): The Z-axis is derived from the source axis which goes from the sample to the source. The Z-axis is the component of the source axis in the direction of the source orthogonal to the X-axis in the plane defined by the X-axis and the source axis. These axes are based on the goniometer, not on the orientation of the detector, gravity, etc. The vectors necessary to specify all other axes are given by sets of three components in the order (X, Y, Z). If the axis involved is a rotation axis, it is right handed, i.e. as one views the object to be rotated from the origin (the tail) of the unit vector, the rotation is clockwise. If a translation axis is specified, the direction of the unit vector specifies the sense of positive translation. Note: This choice of coordinate system is similar to, but significantly different from the choice in MOSFLM (Andrew G.W. Leslie, Harry Powell, MRC Laboratory of Molecular Biology, Hills Road, Cambridge CB2 2QH, UK http://www.dl.ac.uk/CCP/CCP4/dist/x-windows/Mosflm/). In MOSFLM, X is along the X-ray beam (the CBF/imgCIF Z axis) and Z is along the rotation axis. All rotations are given in degrees and all translations are given in mm. Axes may be dependent on one another. The X-axis is the only goniometer axis the direction of which is strictly connected to the hardware. All other axes are specified by the positions they would assume when the axes upon which they depend are at their zero points. When specifying detector axes, the axis is given to the beam centre. The location of the beam centre on the detector should be given in the DIFFRN_DETECTOR category in distortion-corrected mm from the (0,0) corner of the detector. It should be noted that many different origins arise in the definition of an experiment. In particular, as noted above, we need to specify the location of the beam centre on the detector in terms of the origin of the detector, which is, of course, not coincident with the centre of the sample. ; _category.id axis _category.mandatory_code no loop_ _category_key.name '_axis.id' '_axis.equipment' loop_ _category_group.id 'inclusive_group' 'axis_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows the axis specification of the axes of a kappa geometry goniometer (See "X-Ray Structure Determination, A Practical Guide", 2nd ed. by G. H. Stout, L. H. Jensen, Wiley Interscience, 1989, 453 pp, p 134.). There are three axes specified, and no offsets. The outermost axis, omega, is pointed along the X-axis. The next innermost axis, kappa, is at a 50 degree angle to the X-axis, pointed away from the source. The innermost axis, phi, aligns with the X-axis when omega and phi are at their zero-points. If T-omega, T-kappa and T-phi are the transformation matrices derived from the axis settings, the complete transformation would be: x' = (T-omega) (T-kappa) (T-phi) x ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] omega rotation goniometer . 1 0 0 kappa rotation goniometer omega -.64279 0 -.76604 phi rotation goniometer kappa 1 0 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - This example show the axis specification of the axes of a detector, source and gravity. We have juggled the order as a reminder that the ordering of presentation of tokens is not significant. We have taken the centre of rotation of the detector to be 68 millimetres in the direction away from the source. ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] source . source . 0 0 1 . . . gravity . gravity . 0 -1 0 . . . tranz translation detector rotz 0 0 1 0 0 -68 twotheta rotation detector . 1 0 0 . . . roty rotation detector twotheta 0 1 0 0 0 -68 rotz rotation detector roty 0 0 1 0 0 -68 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__axis.depends_on _item_description.description ; The value of '_axis.depends_on' specifies the next outermost axis upon which this axis depends. This item is a pointer to '_axis.id' in the same category. ; _item.name '_axis.depends_on' _item.category_id axis _item.mandatory_code no save_ save__axis.equipment _item_description.description ; The value of '_axis.equipment' specifies the type of equipment using the axis: 'goniometer', 'detector', 'gravity', 'source' or 'general'. ; _item.name '_axis.equipment' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail goniometer 'equipment used to orient or position samples' detector 'equipment used to detect reflections' general 'equipment used for general purposes' gravity 'axis specifying the downward direction' source 'axis specifying the direction sample to source' save_ save__axis.offset[1] _item_description.description ; The [1] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[2] _item_description.description ; The [2] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[3] _item_description.description ; The [3] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.id _item_description.description ; The value of '_axis.id' must uniquely identify each axis relevant to the experiment. Note that multiple pieces of equipment may share the same axis (e.g. a twotheta arm), so that the category key for AXIS also includes the equipment. ; loop_ _item.name _item.category_id _item.mandatory_code '_axis.id' axis yes '_array_structure_list_axis.axis_id' array_structure_list_axis yes '_diffrn_detector_axis.axis_id' diffrn_detector_axis yes '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes '_diffrn_scan_axis.axis_id' diffrn_scan_axis yes '_diffrn_scan_frame_axis.axis_id' diffrn_scan_frame_axis yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_axis.depends_on' '_axis.id' '_array_structure_list_axis.axis_id' '_axis.id' '_diffrn_detector_axis.axis_id' '_axis.id' '_diffrn_measurement_axis.axis_id' '_axis.id' '_diffrn_scan_axis.axis_id' '_axis.id' '_diffrn_scan_frame_axis.axis_id' '_axis.id' save_ save__axis.type _item_description.description ; The value of '_axis.type' specifies the type of axis: 'rotation', 'translation' (or 'general' when the type is not relevant, as for gravity). ; _item.name '_axis.type' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail rotation 'right-handed axis of rotation' translation 'translation in the direction of the axis' general 'axis for which the type is not relevant' save_ save__axis.vector[1] _item_description.description ; The [1] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[2] _item_description.description ; The [2] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[3] _item_description.description ; The [3] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ ##################### # DIFFRN_DATA_FRAME # ##################### save_diffrn_data_frame _category.description ; Data items in the DIFFRN_DATA_FRAME category record the details about each frame of data. The items in this category were previously in a DIFFRN_FRAME_DATA category, which is now deprecated. The items from the old category are provided as aliases but should not be used for new work. ; _category.id diffrn_data_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_data_frame.id' '_diffrn_data_frame.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A frame containing data from 4 frame elements. Each frame element has a common array configuration 'array_1' described in ARRAY_STRUCTURE and related categories. The data for each detector element is stored in four groups of binary data in the ARRAY_DATA category, linked by the array_id and binary_id ; ; loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id frame_1 d1_ccd_1 array_1 1 frame_1 d1_ccd_2 array_1 2 frame_1 d1_ccd_3 array_1 3 frame_1 d1_ccd_4 array_1 4 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_data_frame.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_diffrn_data_frame.array_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.array_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.binary_id _item_description.description ; This item is a pointer to '_array_data.binary_id' in the ARRAY_DATA category. ; _item.name '_diffrn_data_frame.binary_id' _item.category_id diffrn_data_frame _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_frame_data.binary_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code int save_ save__diffrn_data_frame.detector_element_id _item_description.description ; This item is a pointer to '_diffrn_detector_element.id' in the DIFFRN_DETECTOR_ELEMENT category. ; _item.name '_diffrn_data_frame.detector_element_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.detector_element_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.id _item_description.description ; The value of '_diffrn_data_frame.id' must uniquely identify each complete frame of data. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_data_frame.id' diffrn_data_frame yes '_diffrn_refln.frame_id' diffrn_refln yes '_diffrn_scan.frame_id_start' diffrn_scan yes '_diffrn_scan.frame_id_end' diffrn_scan yes '_diffrn_scan_frame.frame_id' diffrn_scan_frame yes '_diffrn_scan_frame_axis.frame_id' diffrn_scan_frame_axis yes _item_aliases.alias_name '_diffrn_frame_data.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_refln.frame_id' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_start' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_end' '_diffrn_data_frame.id' '_diffrn_scan_frame.frame_id' '_diffrn_data_frame.id' '_diffrn_scan_frame_axis.frame_id' '_diffrn_data_frame.id' save_ ########################################################################## # The following is a restatement of the mmCIF DIFFRN_DETECTOR, # # DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for # # the CBF/imgCIF extensions # ########################################################################## ################### # DIFFRN_DETECTOR # ################### save_diffrn_detector _category.description ; Data items in the DIFFRN_DETECTOR category describe the detector used to measure the scattered radiation, including any analyser and post-sample collimation. ; _category.id diffrn_detector _category.mandatory_code no loop_ _category_key.name '_diffrn_detector.diffrn_id' '_diffrn_detector.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_detector.diffrn_id 'd1' _diffrn_detector.detector 'multiwire' _diffrn_detector.type 'Siemens' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector.details _item_description.description ; A description of special aspects of the radiation detector. ; _item.name '_diffrn_detector.details' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'slow mode' save_ save__diffrn_detector.detector _item_description.description ; The general class of the radiation detector. ; _item.name '_diffrn_detector.detector' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector' cifdic.c91 1.0 '_diffrn_detector' cif_core.dic 2.0 _item_type.code text loop_ _item_examples.case 'photographic film' 'scintillation counter' 'CCD plate' 'BF~3~ counter' save_ save__diffrn_detector.diffrn_id _item_description.description ; This data item is a pointer to '_diffrn.id' in the DIFFRN category. The value of '_diffrn.id' uniquely defines a set of diffraction data. ; _item.name '_diffrn_detector.diffrn_id' _item.mandatory_code yes save_ save__diffrn_detector.dtime _item_description.description ; The deadtime in microseconds of the detector(s) used to measure the diffraction intensities. ; _item.name '_diffrn_detector.dtime' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector_dtime' cifdic.c91 1.0 '_diffrn_detector_dtime' cif_core.dic 2.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code microseconds save_ save__diffrn_detector.id _item_description.description ; The value of '_diffrn_detector.id' must uniquely identify each detector used to collect each diffraction data set. If the value of '_diffrn_detector.id' is not given, it is implicitly equal to the value of '_diffrn_detector.diffrn_id' ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector.id' diffrn_detector implicit '_diffrn_detector_axis.detector_id' diffrn_detector_axis yes loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_detector_axis.detector_id' '_diffrn_detector.id' _item_type.code code save_ save__diffrn_detector.number_of_axes _item_description.description ; The value of '_diffrn_detector.number_of_axes' gives the number of axes of the positioner for the detector identified by '_diffrn_detector.id'. The word "positioner" is a general term used in instrumentation design for devices that are used to change the positions of portions of apparatus by linear translation, rotation, or combinations of such motions. Axes which are used to provide a coordinate system for the face of an area detetctor should not be counted for this data item. The description of each axis should be provided by entries in DIFFRN_DETECTOR_AXIS. ; _item.name '_diffrn_detector.number_of_axes' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_detector.type _item_description.description ; The make, model or name of the detector device used. ; _item.name '_diffrn_detector.type' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ ######################## # DIFFRN_DETECTOR_AXIS # ######################## save_diffrn_detector_axis _category.description ; Data items in the DIFFRN_DETECTOR_AXIS category associate axes with detectors. ; _category.id diffrn_detector_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_axis.detector_id' '_diffrn_detector_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_detector_axis.axis_id _item_description.description ; This data item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_diffrn_detector_axis.axis_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_axis.detector_id _item_description.description ; This data item is a pointer to '_diffrn_detector.id' in the DIFFRN_DETECTOR category. This item was previously named '_diffrn_detector_axis.id' which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_detector_axis.detector_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_aliases.alias_name '_diffrn_detector_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ ########################### # DIFFRN_DETECTOR_ELEMENT # ########################### save_diffrn_detector_element _category.description ; Data items in the DIFFRN_DETECTOR_ELEMENT category record the details about spatial layout and other characteristics of each element of a detector which may have multiple elements. In most cases, the more detailed information provided in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS are preferable to simply providing the centre. ; _category.id diffrn_detector_element _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_element.id' '_diffrn_detector_element.detector_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Detector d1 is composed of four CCD detector elements, each 200 mm by 200 mm, arranged in a square. in the pattern 1 2 * 3 4 Note that the beam centre is slightly displaced from each of the detector elements, just beyond the lower right corner of 1, the lower left corner of 2, the upper right corner of 3 and the upper left corner of 4. ; ; loop_ _diffrn_detector_element.detector_id _diffrn_detector_element.id _diffrn_detector_element.center[1] _diffrn_detector_element.center[2] d1 d1_ccd_1 201.5 -1.5 d1 d1_ccd_2 -1.8 -1.5 d1 d1_ccd_3 201.6 201.4 d1 d1_ccd_4 -1.7 201.5 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector_element.center[1] _item_description.description ; The value of '_diffrn_detector_element.center[1]' is the X component of the distortion-corrected beam-centre in mm from the (0, 0) (lower left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. ; _item.name '_diffrn_detector_element.center[1]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.center[2] _item_description.description ; The value of '_diffrn_detector_element.center[2]' is the Y component of the distortion-corrected beam-centre in mm from the (0, 0) (lower left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. ; _item.name '_diffrn_detector_element.center[2]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.id _item_description.description ; The value of '_diffrn_detector_element.id' must uniquely identify each element of a detector. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector_element.id' diffrn_detector_element yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.detector_element_id' '_diffrn_detector_element.id' save_ save__diffrn_detector_element.detector_id _item_description.description ; This item is a pointer to '_diffrn_detector.id' in the DIFFRN_DETECTOR category. ; _item.name '_diffrn_detector_element.detector_id' _item.category_id diffrn_detector_element _item.mandatory_code yes _item_type.code code save_ ######################## ## DIFFRN_MEASUREMENT ## ######################## save_diffrn_measurement _category.description ; Data items in the DIFFRN_MEASUREMENT category record details about the device used to orient and/or position the crystal during data measurement and the manner in which the diffraction data were measured. ; _category.id diffrn_measurement _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement.device' '_diffrn_measurement.diffrn_id' '_diffrn_measurement.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_measurement.diffrn_id 'd1' _diffrn_measurement.device '3-circle camera' _diffrn_measurement.device_type 'Supper model x' _diffrn_measurement.device_details 'none' _diffrn_measurement.method 'omega scan' _diffrn_measurement.details ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991). Acta Cryst. C47, 2276-2277]. ; ; _diffrn_measurement.diffrn_id 's1' _diffrn_measurement.device_type 'Philips PW1100/20 diffractometer' _diffrn_measurement.method 'theta/2theta (\q/2\q)' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_measurement.device _item_description.description ; The general class of goniometer or device used to support and orient the specimen. If the value of '_diffrn_measurement.device' is not given, it is implicitly equal to the value of '_diffrn_measurement.diffrn_id'. Either '_diffrn_measurement.device' or '_diffrn_measurement.id' may be used to link to other categories. If the experimental setup admits multiple devices, then '_diffrn_measurement.id' is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.device' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_device' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement.device' _item_aliases.alias_name '_diffrn_measurement_device' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '3-circle camera' '4-circle camera' 'kappa-geometry camera' 'oscillation camera' 'precession camera' save_ save__diffrn_measurement.device_details _item_description.description ; A description of special aspects of the device used to measure the diffraction intensities. ; _item.name '_diffrn_measurement.device_details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; commercial goniometer modified locally to allow for 90\% \t arc ; save_ save__diffrn_measurement.device_type _item_description.description ; The make, model or name of the measurement device (goniometer) used. ; _item.name '_diffrn_measurement.device_type' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Supper model q' 'Huber model r' 'Enraf-Nonius model s' 'homemade' save_ save__diffrn_measurement.diffrn_id _item_description.description ; This data item is a pointer to '_diffrn.id' in the DIFFRN category. ; _item.name '_diffrn_measurement.diffrn_id' _item.mandatory_code yes save_ save__diffrn_measurement.details _item_description.description ; A description of special aspects of the intensity measurement. ; _item.name '_diffrn_measurement.details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; save_ save__diffrn_measurement.id _item_description.description ; The value of '_diffrn_measurement.id' must uniquely identify the set of mechanical characteristics of the device used to orient and/or position the sample used during collection of each diffraction data set. If the value of '_diffrn_measurement.id' is not given, it is implicitly equal to the value of '_diffrn_measurement.diffrn_id'. Either '_diffrn_measurement.device' or '_diffrn_measurement.id' may be used to link to other categories. If the experimental setup admits multiple devices, then '_diffrn_measurement.id' is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.id' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_id' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement.id' _item_type.code code save_ save__diffrn_measurement.method _item_description.description ; Method used to measure intensities. ; _item.name '_diffrn_measurement.method' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_method' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'profile data from theta/2theta (\q/2\q) scans' save_ save__diffrn_measurement.number_of_axes _item_description.description ; The value of '_diffrn_measurement.number_of_axes' gives the number of axes of the positioner for the goniometer or other sample orientation or positioning device identified by '_diffrn_measurement.id'. The description of the axes should be provided by entries in DIFFRN_MEASUREMENT_AXIS. ; _item.name '_diffrn_measurement.number_of_axes' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_measurement.specimen_support _item_description.description ; The physical device used to support the crystal during data collection. ; _item.name '_diffrn_measurement.specimen_support' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_specimen_support' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'glass capillary' 'quartz capillary' 'fiber' 'metal loop' save_ ########################### # DIFFRN_MEASUREMENT_AXIS # ########################### save_diffrn_measurement_axis _category.description ; Data items in the DIFFRN_MEASUREMENT_AXIS category associate axes with goniometers. ; _category.id diffrn_measurement_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_measurement_axis.axis_id _item_description.description ; This data item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_diffrn_measurement_axis.axis_id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.measurement_device _item_description.description ; This data item is a pointer to '_diffrn_measurement.device' in the DIFFRN_MEASUREMENT category. ; _item.name '_diffrn_measurement_axis.measurement_device' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit _item_type.code text save_ save__diffrn_measurement_axis.measurement_id _item_description.description ; This data item is a pointer to '_diffrn_measurement.id' in the DIFFRN_MEASUREMENT category. This item was previously named '_diffrn_measurement_axis.id' which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_measurement_axis.measurement_id' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_measurement_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ #################### # DIFFRN_RADIATION # #################### save_diffrn_radiation _category.description ; Data items in the DIFFRN_RADIATION category describe the radiation used in measuring diffraction intensities, its collimation and monochromatisation before the sample. Post-sample treatment of the beam is described by data items in the DIFFRN_DETECTOR category. ; _category.id diffrn_radiation _category.mandatory_code no _category_key.name '_diffrn_radiation.diffrn_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_radiation.diffrn_id 'set1' _diffrn_radiation.collimation '0.3 mm double pinhole' _diffrn_radiation.monochromator 'graphite' _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.wavelength_id 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991). Acta Cryst. C47, 2276-2277]. ; ; _diffrn_radiation.wavelength_id 1 _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.monochromator 'graphite' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_radiation.collimation _item_description.description ; The collimation or focusing applied to the radiation. ; _item.name '_diffrn_radiation.collimation' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_collimation' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '0.3 mm double-pinhole' '0.5 mm' 'focusing mirrors' save_ save__diffrn_radiation.diffrn_id _item_description.description ; This data item is a pointer to '_diffrn.id' in the DIFFRN category. ; _item.name '_diffrn_radiation.diffrn_id' _item.mandatory_code yes save_ save__diffrn_radiation.div_x_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory X axis (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the esd of the directions of photons in the X-Z plane around the mean source beam direction. Note that some synchrotrons specify this value in milliradians, in which case a conversion would be needed. To go from a value in milliradians to a value in degrees, multiply by 0.180 and divide by \p. ; _item.name '_diffrn_radiation.div_x_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.div_y_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory Y axis (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the esd of the directions of photons in the Y-Z plane around the mean source beam direction. Note that some synchrotrons specify this value in milliradians, in which case a conversion would be needed. To go from a value in milliradians to a value in degrees, multiply by 0.180 and divide by \p. ; _item.name '_diffrn_radiation.div_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.div_x_y_source _item_description.description ; Beam crossfire correlation degrees^2^ between the crossfire laboratory X-axis component and the crossfire laboratory Y-axis component (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the mean of the products of the deviations of the direction of each photons in X-Z plane times the deviations of the direction of the same photon in the Y-Z plane around the mean source beam direction. This will be zero for uncorrelated crossfire. Note that some synchrotrons specify this value in milliradians^2, in which case a conversion would be needed. To go from a value in milliradians^2^ to a value in degrees^2, multiply by 0.180^2^ and divide by \p^2^. ; _item.name '_diffrn_radiation.div_x_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees_squared _item_default.value 0.0 save_ save__diffrn_radiation.filter_edge _item_description.description ; Absorption edge in \%Angstroms of the radiation filter used. ; _item.name '_diffrn_radiation.filter_edge' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_filter_edge' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__diffrn_radiation.inhomogeneity _item_description.description ; Half-width in millimetres of the incident beam in the direction perpendicular to the diffraction plane. ; _item.name '_diffrn_radiation.inhomogeneity' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_inhomogeneity' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code millimetres save_ save__diffrn_radiation.monochromator _item_description.description ; The method used to obtain monochromatic radiation. If a monochromator crystal is used the material and the indices of the Bragg reflection are specified. ; _item.name '_diffrn_radiation.monochromator' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_monochromator' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Zr filter' 'Ge 220' 'none' 'equatorial mounted graphite' save_ save__diffrn_radiation.polarisn_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the perpendicular component of the polarisation and the diffraction plane. See _diffrn_radiation_polarisn_ratio. ; _item.name '_diffrn_radiation.polarisn_norm' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_norm' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.polarisn_ratio _item_description.description ; Polarisation ratio of the diffraction beam incident on the crystal. It is the ratio of the perpendicularly polarised to the parallel polarised component of the radiation. The perpendicular component forms an angle of '_diffrn_radiation.polarisn_norm' to the normal to the diffraction plane of the sample (i.e. the plane containing the incident and reflected beams). ; _item.name '_diffrn_radiation.polarisn_ratio' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_ratio' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__diffrn_radiation.polarizn_source_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the normal to the polarization plane and the laboratory Y axis as defined in the AXIS category. Note that this is the angle of polarization of the source photons, either directly from a synchrotron beamline or from a monchromater. This differs from the value of '_diffrn_radiation.polarisn_norm' in that '_diffrn_radiation.polarisn_norm' refers to polarization relative to the diffraction plane rather than to the laboratory axis system. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane should be taken as the X-Z plane, and the angle as 0. See '_diffrn_radiation.polarizn_source_ratio'. ; _item.name '_diffrn_radiation.polarizn_source_norm' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.polarizn_source_ratio _item_description.description ; (Ip-In)/(Ip+In), where Ip is the intensity (amplitude squared) of the electric vector in the plane of polarization and In is the intensity (amplitude squared) of the electric vector in plane of the normal to the plane of polarization. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane is be taken as the X-Z plane, and the normal is parallel to the Y-axis. Thus, if we had complete polarization in the plane of polarization, the value of '_diffrn_radiation.polarizn_source_ratio' would be 1, and an unpolarized beam would have a value of 0. If the X-axis has been chosen to lie in the plane of polarization, this definition will agree with the definition of "MONOCHROMATOR" in the Denzo glossary, and values of near 1 should be expected for a bending magnet source. However, if the X-axis were, for some reason to be, say, perpendicular to the polarization plane (not a common choice), then the Denzo value would be the negative of '_diffrn_radiation.polarizn_source_ratio'. See http://www.hkl-xray.com for information on Denzo, and Z. Otwinowski and W. Minor, "Processing of X-ray Diffraction Data Collected in Oscillation Mode", Methods in Enzymology, Volume 276: Macromolecular Crystallography, part A, p.307-326, 1997,C.W. Carter, Jr. & R. M. Sweet, Eds., Academic Press. This differs both in the choice of ratio and choice of orientation from '_diffrn_radiation.polarisn_ratio', which, unlike '_diffrn_radiation.polarizn_source_ratio', is unbounded. ; _item.name '_diffrn_radiation.polarizn_source_ratio' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 -1.0 -1.0 -1.0 _item_type.code float save_ save__diffrn_radiation.probe _item_description.description ; Name of the type of radiation used. It is strongly encouraged that this field be specified so that the probe radiation can be simply determined. ; _item.name '_diffrn_radiation.probe' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_probe' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value 'x-ray' 'neutron' 'electron' 'gamma' save_ save__diffrn_radiation.type _item_description.description ; The nature of the radiation. This is typically a description of the X-ray wavelength in Siegbahn notation. ; _item.name '_diffrn_radiation.type' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'CuK\a' 'Cu K\a~1~' 'Cu K-L~2,3~' 'white-beam' save_ save__diffrn_radiation.xray_symbol _item_description.description ; The IUPAC symbol for the X-ray wavelength for probe radiation. ; _item.name '_diffrn_radiation.xray_symbol' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_xray_symbol' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value _item_enumeration.detail 'K-L~3~' 'K\a~1~ in older Siegbahn notation' 'K-L~2~' 'K\a~2~ in older Siegbahn notation' 'K-M~3~' 'K\b~1~ in older Siegbahn notation' 'K-L~2,3~' 'use where K-L~3~ and K-L~2~ are not resolved' save_ save__diffrn_radiation.wavelength_id _item_description.description ; This data item is a pointer to '_diffrn_radiation_wavelength.id' in the DIFFRN_RADIATION_WAVELENGTH category. ; _item.name '_diffrn_radiation.wavelength_id' _item.category_id diffrn_radiation _item.mandatory_code yes _item_type.code code save_ ################ # DIFFRN_REFLN # ################ save_diffrn_refln _category.description ; This category redefinition has been added to extend the key of the standard DIFFRN_REFLN category. ; _category.id diffrn_refln _category.mandatory_code no _category_key.name '_diffrn_refln.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_refln.frame_id _item_description.description ; This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_refln.frame_id' _item.category_id diffrn_refln _item.mandatory_code yes _item_type.code code save_ ############### # DIFFRN_SCAN # ############### save_diffrn_scan _category.description ; Data items in the DIFFRN_SCAN category describe the parameters of one or more scans, relating axis positions to frames. ; _category.id diffrn_scan _category.mandatory_code no _category_key.name '_diffrn_scan.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - derived from a suggestion by R. M. Sweet. The vector of each axis is not given here, because it is provided in the AXIS category. By making '_diffrn_scan_axis.scan_id' and '_diffrn_scan_axis.axis_id' keys of the DIFFRN_SCAN_AXIS category, an arbitrary number of scanning and fixed axes can be specified for a scan. We have specified three rotation axes and one translation axis at non-zero values, with one axis stepping. There is no reason why more axes could not have been specified to step. We have specified range information, but note that it is redundant from the number of frames and the increment, so we could drop the data item '_diffrn_scan_axis.angle_range'. We have specified both the sweep data and the data for a single frame. Note that the information on how the axes are stepped is given twice, once in terms of the overall averages in the value of '_diffrn_scan.integration_time' and the values for DIFFRN_SCAN_AXIS, and precisely for the given frame in the value for '_diffrn_scan_frame.integration_time' and the values for DIFFRN_SCAN_FRAME_AXIS. If dose-related adjustements are made to scan times and non-linear stepping is done, these values may differ. Therefore, in interpreting the data for a particular frame it is important to use the frame-specific data. ; ; _diffrn_scan.id 1 _diffrn_scan.date_start '2001-11-18T03:26:42' _diffrn_scan.date_end '2001-11-18T03:36:45' _diffrn_scan.integration_time 3.0 _diffrn_scan.frame_id_start mad_L2_000 _diffrn_scan.frame_id_end mad_L2_200 _diffrn_scan.frames 201 loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment 1 omega 200.0 20.0 0.1 . . . 1 kappa -40.0 0.0 0.0 . . . 1 phi 127.5 0.0 0.0 . . . 1 tranz . . . 2.3 0.0 0.0 _diffrn_scan_frame.scan_id 1 _diffrn_scan_frame.date '2001-11-18T03:27:33' _diffrn_scan_frame.integration_time 3.0 _diffrn_scan_frame.frame_id mad_L2_018 _diffrn_scan_frame.frame_number 18 loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.angle_increment _diffrn_scan_frame_axis.displacement _diffrn_scan_frame_axis.displacement_increment mad_L2_018 omega 201.8 0.1 . . mad_L2_018 kappa -40.0 0.0 . . mad_L2_018 phi 127.5 0.0 . . mad_L2_018 tranz . . 2.3 0.0 ; ; Example 2 - a more extensive example, R. M. Sweet, P. Ellis, H. Bernstein. We place a detector 240 mm along the Z axis from the goniometer. This presents us with a choice -- either we define the axes of the detector at the origin, and then put a Z setting of -240 in for the actual use, or we define the axes with the necessary Z-offset. In this case we use the setting, and leave the offset as zero. We call this axis DETECTOR_Z. The axis for positioning the detector in the Y-direction depends on the detector Z-axis. We call this axis, DETECTOR_Y. The axis for positioning the detector in the X-direction depends on the detector Y-axis (and therefore on the detector Z-axis). We call this axis DETECTOR_X. This detector may be rotated around the Y-axis. This rotation axis depends on the three translation axes. We call it DETECTOR_PITCH. We define a coordinate system on the face of the detector in terms of 2300 0.150 mm pixels in each direction. The ELEMENT_X axis is used to index the first array index of the data array and the ELEMENT_Y axis is used to index the second array index. Because the pixels are 0.150mm x 0.150mm, the centre of the first pixel is at (0.075, 0.075) in this coordinate system. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 172.43 -172.43 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 2300 1 increasing ELEMENT_X ARRAY1 2 2300 2 increasing ELEMENT_Y # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.075 0.150 ELEMENT_Y ELEMENT_Y 0.075 0.150 # category ARRAY_ELEMENT_SIZE loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 ARRAY1 2 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; ; Example 3 - Example 2 revised for a spiral scan, R. M. Sweet, P. Ellis, H. Bernstein. We place a detector 240 millimetres along the Z axis from the goniometer, as in Example 2, above, but in this example, the image plate is scanned in a spiral pattern outside edge in. The axis for positioning the detector in the Y-direction depends on the detector Z-axis. We call this axis, DETECTOR_Y. The axis for positioning the detector in the X-direction depends on the detector Y-axis (and therefore on the detector Z-axis). We call this axis DETECTOR_X. This detector may be rotated around the Y-axis. This rotation axis depends on the three translation axes. We call it DETECTOR_PITCH. We define a coordinate system on the face of the detector in terms of a coupled rotation axis and radial scan axis to form a spiral scan. Let us call rotation axis ELEMENT_ROT, and the radial axis ELEMENT_RAD. We assume 150 micrometre radial pitch and 75 micrometre 'constant velocity' angular pitch. We index first on the rotation axis and make the radial axis dependent on it. The two axes are coupled to form an axis set ELEMENT_SPIRAL. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_ROT translation detector DETECTOR_PITCH 0 0 1 0 0 0 ELEMENT_RAD translation detector ELEMENT_ROT 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.angle _array_structure_list_axis.displacement _array_structure_list_axis.angular_pitch _array_structure_list_axis.radial_pitch ELEMENT_SPIRAL ELEMENT_ROT 0 . 0.075 . ELEMENT_SPIRAL ELEMENT_RAD . 172.5 . -0.150 # category ARRAY_ELEMENT_SIZE # the actual pixels are 0.075 by 0.150 millimetres # We give the coarser dimension here. loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_scan.id _item_description.description ; The value of '_diffrn_scan.id' uniquely identifies each scan. The identifier is used to tie together all the information about the scan. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_scan.id' diffrn_scan yes '_diffrn_scan_axis.scan_id' diffrn_scan_axis yes '_diffrn_scan_frame.scan_id' diffrn_scan_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_scan_axis.scan_id' '_diffrn_scan.id' '_diffrn_scan_frame.scan_id' '_diffrn_scan.id' save_ save__diffrn_scan.date_end _item_description.description ; The date and time of the end of the scan. Note that this may be an estimate generated during the scan, before the precise time of the end of the scan is known. ; _item.name '_diffrn_scan.date_end' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.date_start _item_description.description ; The date and time of the start of the scan. ; _item.name '_diffrn_scan.date_start' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.integration_time _item_description.description ; Approximate average time in seconds to integrate each step of the scan. The precise time for integration of each particular step must be provided in '_diffrn_scan_frame.integration_time', even if all steps have the same integration time. ; _item.name '_diffrn_scan.integration_time' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan.frame_id_start _item_description.description ; The value of this data item is the identifier of the first frame in the scan. This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_start' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frame_id_end _item_description.description ; The value of this data item is the identifier of the last frame in the scan. This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_end' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frames _item_description.description ; The value of this data item is the number of frames in the scan. ; _item.name '_diffrn_scan.frames' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 1 1 1 save_ #################### # DIFFRN_SCAN_AXIS # #################### save_diffrn_scan_axis _category.description ; Data items in the DIFFRN_SCAN_AXIS category describe the settings of axes for particular scans. Unspecified axes are assumed to be at their zero points. ; _category.id diffrn_scan_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_axis.scan_id' '_diffrn_scan_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_axis.scan_id _item_description.description ; The value of this data item is the identifier of the scan for which axis settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan.id'. This item is a pointer to '_diffrn_scan.id' in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_axis.scan_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the scan for which settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan.id'. This item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_diffrn_scan_axis.axis_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.angle_start _item_description.description ; The starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_range _item_description.description ; The range from the starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_increment _item_description.description ; The increment for each step for the specified axis in degrees. In general, this will agree with '_diffrn_scan_frame_axis.angle_increment'. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.angle_increment' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.angle_increment' (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_rstrt_incr _item_description.description ; The increment after each step for the specified axis in degrees. In general, this will agree with '_diffrn_scan_frame_axis.angle_rstrt_incr'. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' and '_diffrn_scan_frame_axis.angle_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame, and should equal '_diffrn_scan_frame_axis.angle' for that next frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.angle_rstrt_incr' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.angle_rstrt_incr' (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.displacement_start _item_description.description ; The starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_range _item_description.description ; The range from the starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_increment _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with '_diffrn_scan_frame_axis.displacement_increment'. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.displacement_increment' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.displacement_increment' (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_rstrt_incr _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with '_diffrn_scan_frame_axis.displacement_rstrt_incr'. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' and '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame, and should equal '_diffrn_scan_frame_axis.displacement' for that next frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.displacement_rstrt_incr' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.displacement_rstrt_incr' (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ ##################### # DIFFRN_SCAN_FRAME # ##################### save_diffrn_scan_frame _category.description ; Data items in the DIFFRN_SCAN_FRAME category describe the relationship of particular frames to scans. ; _category.id diffrn_scan_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame.scan_id' '_diffrn_scan_frame.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame.date _item_description.description ; The date and time of the start of the frame being scanned. ; _item.name '_diffrn_scan_frame.date' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan_frame.frame_id _item_description.description ; The value of this data item is the identifier of the frame being examined. This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame.frame_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame.frame_number _item_description.description ; The value of this data item is the number of the frame within the scan, starting with 1. It is not necessarily the same as the value of '_diffrn_scan_frame.frame_id', but may be. ; _item.name '_diffrn_scan_frame.frame_number' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 0 0 0 save_ save__diffrn_scan_frame.integration_time _item_description.description ; The time in seconds to integrate this step of the scan. This should be the precise time of integration of each particular frame. The value of this data item should be given explicitly for each frame and not inferred from the value of '_diffrn_scan.integration_time'. ; _item.name '_diffrn_scan_frame.integration_time' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame.scan_id _item_description.description ; The value of '_diffrn_scan_frame.scan_id' identifies the scan containing this frame. This item is a pointer to '_diffrn_scan.id' in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_frame.scan_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ ########################## # DIFFRN_SCAN_FRAME_AXIS # ########################## save_diffrn_scan_frame_axis _category.description ; Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the settings of axes for particular frames. Unspecified axes are assumed to be at their zero points. If, for any given frame, non-zero values apply for any of the data items in this category, those values should be given explicitly in this category and not simply inferred from values in DIFFRN_SCAN_AXIS. ; _category.id diffrn_scan_frame_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame_axis.frame_id' '_diffrn_scan_frame_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the frame for which settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan_frame.frame_id'. This item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_diffrn_scan_frame_axis.axis_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_axis.angle _item_description.description ; The setting of the specified axis in degrees for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.angle' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_increment _item_description.description ; The increment for this frame for angular setting of the specified axis in degrees. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.angle_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_rstrt_incr _item_description.description ; The increment after this frame for angular setting of the specified axis in degrees. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' and '_diffrn_scan_frame_axis.angle_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame, and should equal '_diffrn_scan_frame_axis.angle' for that next frame. ; _item.name '_diffrn_scan_frame_axis.angle_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.displacement' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_increment _item_description.description ; The increment for this frame for displacement setting of the specified axis in millimetres. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.displacement_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_rstrt_incr _item_description.description ; The increment for this frame for displacement setting of the specified axis in millimetres. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' and '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame, and should equal '_diffrn_scan_frame_axis.displacement' for that next frame. ; _item.name '_diffrn_scan_frame_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.frame_id _item_description.description ; The value of this data item is the identifier of the frame for which axis settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan_frame.frame_id'. This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame_axis.frame_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ ######################## DEPRECATED DATA ITEMS ######################## save__diffrn_detector_axis.id _item_description.description ; This data item is a pointer to '_diffrn_detector.id' in the DIFFRN_DETECTOR category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_detector_axis.id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.id _item_description.description ; This data item is a pointer to '_diffrn_measurement.id' in the DIFFRN_MEASUREMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_measurement_axis.id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ ######################### DEPRECATED CATEGORY ######################### ##################### # DIFFRN_FRAME_DATA # ##################### save_diffrn_frame_data _category.description ; Data items in the DIFFRN_FRAME_DATA category record the details about each frame of data. The items in this category are now in the DIFFRN_DATA_FRAME category. The items in the DIFFRN_FRAME_DATA category are now deprecated. The items from this category are provided as aliases in the 1.0.0 dictionary, but should not be used for new work. The items from the old category are provided in this dictionary for completeness, but should not be used or cited. To avoid confusion, the example has been removed, and the redundant parent child-links to other categories removed. ; _category.id diffrn_frame_data _category.mandatory_code no loop_ _category_key.name '_diffrn_frame_data.id' '_diffrn_frame_data.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; THE DIFFRN_FRAME_DATA category is deprecated and should not be used. ; ; # EXAMPLE REMOVED # ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_frame_data.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.array_id' _item.category_id diffrn_frame_data _item.mandatory_code yes _item_type.code code save_ save__diffrn_frame_data.binary_id _item_description.description ; This item is a pointer to '_array_data.binary_id' in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.binary_id' _item.category_id diffrn_frame_data _item.mandatory_code implicit _item_type.code int save_ save__diffrn_frame_data.detector_element_id _item_description.description ; This item is a pointer to '_diffrn_detector_element.id' in the DIFFRN_DETECTOR_ELEMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.detector_element_id' _item.category_id diffrn_frame_data _item.mandatory_code yes _item_type.code code save_ save__diffrn_frame_data.id _item_description.description ; The value of '_diffrn_frame_data.id' must uniquely identify each complete frame of data. DEPRECATED -- DO NOT USE ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_frame_data.id' diffrn_frame_data yes _item_type.code code save_ ################ END DEPRECATED SECTION ########### ./CBFlib-0.9.2.2/doc/Idiffrn_data_frame.binary_id.html0000644000076500007650000000543611603702115020724 0ustar yayayaya (IUCr) CIF Definition save__diffrn_data_frame.binary_id

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_data_frame.binary_id

    Name:
    '_diffrn_data_frame.binary_id'

    Definition:

           This item is a pointer to _array_data.binary_id in the
                  ARRAY_DATA category.
    
    

    Type: int

    Mandatory item: implicit

    Alias:
    _diffrn_frame_data.binary_id (cif_img.dic version 1.0)

    Category: diffrn_data_frame

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/cif_img_1.3.2_22Jun05.dic0000644000076500007650000054573611603702115016313 0ustar yayayaya############################################################################## # # # Image CIF Dictionary (imgCIF) # # and Crystallographic Binary File Dictionary (CBF) # # Extending the Macromolecular CIF Dictionary (mmCIF) # # # # Version 1.3.2 # # of 2005-06-22 # # # # by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook # # # # This dictionary was adapted from format discussed at the imgCIF Workshop, # # held at BNL Oct 1997 and the Crystallographic Binary File Format Draft # # Proposal by Andrew Hammersley. The first DDL 2.1 Version was created by # # John Westbrook. This version was drafted by Herbert J. Bernstein and # # incorporates comments by I. David Brown, John Westbrook, Brian McMahon, # # Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li, Gotzon Madariaga, # # Frances C. Bernstein and others. # ############################################################################## data_cif_img.dic _dictionary.title cif_img.dic _dictionary.version 1.3.2 _dictionary.datablock_id cif_img.dic ############################################################################## # CONTENTS # # CATEGORY_GROUP_LIST # # category ARRAY_DATA # # _array_data.array_id # _array_data.binary_id # _array_data.data # # category ARRAY_ELEMENT_SIZE # # _array_element_size.array_id # _array_element_size.index # _array_element_size.size # # category ARRAY_INTENSITIES # # _array_intensities.array_id # _array_intensities.binary_id # _array_intensities.gain # _array_intensities.gain_esd # _array_intensities.linearity # _array_intensities.offset # _array_intensities.scaling # _array_intensities.overload # _array_intensities.undefined_value # # category ARRAY_STRUCTURE # # _array_structure.byte_order # _array_structure.compression_type # _array_structure.encoding_type # _array_structure.id # # category ARRAY_STRUCTURE_LIST # # _array_structure_list.axis_set_id # _array_structure_list.array_id # _array_structure_list.dimension # _array_structure_list.direction # _array_structure_list.index # _array_structure_list.precedence # # category ARRAY_STRUCTURE_LIST_AXIS # # _array_structure_list_axis.axis_id # _array_structure_list_axis.axis_set_id # _array_structure_list_axis.angle # _array_structure_list_axis.angle_increment # _array_structure_list_axis.displacement_increment # _array_structure_list_axis.angular_pitch # _array_structure_list_axis.radial_pitch # # category AXIS # # _axis.depends_on # _axis.equipment # _axis.id # _axis.offset[1] # _axis.offset[2] # _axis.offset[3] # _axis.type # _axis.vector[1] # _axis.vector[2] # _axis.vector[3] # # category DIFFRN_DATA_FRAME # # _diffrn_data_frame.array_id # _diffrn_data_frame.binary_id # _diffrn_data_frame.detector_element_id # _diffrn_data_frame.id # # category DIFFRN_DETECTOR # # _diffrn_detector.details # _diffrn_detector.detector # _diffrn_detector.diffrn_id # _diffrn_detector.dtime # _diffrn_detector.id # _diffrn_detector.number_of_axes # _diffrn_detector.type # # category DIFFRN_DETECTOR_AXIS # # _diffrn_detector_axis.axis_id # _diffrn_detector_axis.detector_id # # category DIFFRN_DETECTOR_ELEMENT # # _diffrn_detector_element.center[1] # _diffrn_detector_element.center[2] # _diffrn_detector_element.id # _diffrn_detector_element.detector_id # # category DIFFRN_MEASUREMENT # # _diffrn_measurement.diffrn_id # _diffrn_measurement.details # _diffrn_measurement.device # _diffrn_measurement.device_details # _diffrn_measurement.device_type # _diffrn_measurement.id # _diffrn_measurement.method # _diffrn_measurement.number_of_axes # _diffrn_measurement.specimen_support # # category DIFFRN_MEASUREMENT_AXIS # # _diffrn_measurement_axis.axis_id # _diffrn_measurement_axis.measurement_device # _diffrn_measurement_axis.measurement_id # # category DIFFRN_RADIATION # # _diffrn_radiation.collimation # _diffrn_radiation.diffrn_id # _diffrn_radiation.div_x_source # _diffrn_radiation.div_y_source # _diffrn_radiation.div_x_y_source # _diffrn_radiation.filter_edge' # _diffrn_radiation.inhomogeneity # _diffrn_radiation.monochromator # _diffrn_radiation.polarisn_norm # _diffrn_radiation.polarisn_ratio # _diffrn_radiation.polarizn_source_norm # _diffrn_radiation.polarizn_source_ratio # _diffrn_radiation.probe # _diffrn_radiation.type # _diffrn_radiation.xray_symbol # _diffrn_radiation.wavelength_id # # category DIFFRN_REFLN # # _diffrn_refln.frame_id # # category DIFFRN_SCAN # # _diffrn_scan.id # _diffrn_scan.date_end # _diffrn_scan.date_start # _diffrn_scan.integration_time # _diffrn_scan.frame_id_start # _diffrn_scan.frame_id_end # _diffrn_scan.frames # # category DIFFRN_SCAN_AXIS # # _diffrn_scan_axis.axis_id # _diffrn_scan_axis.angle_start # _diffrn_scan_axis.angle_range # _diffrn_scan_axis.angle_increment # _diffrn_scan_axis.angle_rstrt_incr # _diffrn_scan_axis.displacement_start # _diffrn_scan_axis.displacement_range # _diffrn_scan_axis.displacement_increment # _diffrn_scan_axis.displacement_rstrt_incr # _diffrn_scan_axis.scan_id # # category DIFFRN_SCAN_FRAME # # _diffrn_scan_frame.date # _diffrn_scan_frame.frame_id # _diffrn_scan_frame.frame_number # _diffrn_scan_frame.integration_time # _diffrn_scan_frame.scan_id # # category DIFFRN_SCAN_FRAME_AXIS # # _diffrn_scan_frame_axis.axis_id # _diffrn_scan_frame_axis.angle # _diffrn_scan_frame_axis.angle_increment # _diffrn_scan_frame_axis.angle_rstrt_incr # _diffrn_scan_frame_axis.displacement # _diffrn_scan_frame_axis.displacement_increment # _diffrn_scan_frame_axis.displacement_rstrt_incr # _diffrn_scan_frame_axis.frame_id # # ***DEPRECATED*** data items # # _diffrn_detector_axis.id # _diffrn_measurement_axis.id # # ***DEPRECATED*** category DIFFRN_FRAME_DATA # # _diffrn_frame_data.array_id # _diffrn_frame_data.binary_id # _diffrn_frame_data.detector_element_id # _diffrn_frame_data.id # # # ITEM_TYPE_LIST # ITEM_UNITS_LIST # DICTIONARY_HISTORY # ############################################################################## ######################### ## CATEGORY_GROUP_LIST ## ######################### loop_ _category_group_list.id _category_group_list.parent_id _category_group_list.description 'inclusive_group' . ; Categories that belong to the dictionary extension. ; 'array_data_group' 'inclusive_group' ; Categories that describe array data. ; 'axis_group' 'inclusive_group' ; Categories that describe axes. ; 'diffrn_group' 'inclusive_group' ; Categories that describe details of the diffraction experiment. ; ############## # ARRAY_DATA # ############## save_ARRAY_DATA _category.description ; Data items in the ARRAY_DATA category are the containers for the array data items described in category ARRAY_STRUCTURE. ; _category.id array_data _category.mandatory_code no loop_ _category_key.name '_array_data.array_id' '_array_data.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows two binary data blocks. The first one was compressed by the CBF_CANONICAL compression algorithm and presented as hexadecimal data. The first character "H" on the data lines means hexadecimal. It could have been "O" for octal or "D" for decimal. The second character on the line shows the number of bytes in each word (in this case "4"), which then requires 8 hexadecimal digits per word. The third character gives the order of octets within a word, in this case "<" for the ordering 4321 (i.e. "big-endian"). Alternatively the character ">" could have been used for the ordering 1234 (i.e. "little-endian"). The block has a "message digest" to check the integrity of the data. The second block is similar, but uses CBF_PACKED compression and BASE64 encoding. Note that the size and the digest are different. ; ; loop_ _array_data.array_id _array_data.binary_id _array_data.data image_1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_CANONICAL" Content-Transfer-Encoding: X-BASE16 X-Binary-Size: 3927126 X-Binary-ID: 1 Content-MD5: u2sTJEovAHkmkDjPi+gWsg== # Hexadecimal encoding, byte 0, byte order ...21 # H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ... .... --CIF-BINARY-FORMAT-SECTION---- ; image_2 2 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF-PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3745758 X-Binary-ID: 2 Content-MD5: 1zsJjWPfol2GYl2V+QSXrw== ELhQAAAAAAAA... ... --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_data.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_array_data.array_id' _item.category_id array_data _item.mandatory_code yes _item_type.code code save_ save__array_data.binary_id _item_description.description ; This item is an integer identifier which, along with '_array_data.array_id' should uniquely identify the particular block of array data. If '_array_data.binary_id' is not explicitly given, it defaults to 1. The value of '_array_data.binary_id' distinguishes among multiple sets of data with the same array structure. If the MIME header of the data array specifies a value for X-Binary-Id, the value of '_array_data.binary_id' should be equal the value given for X-Binary-Id. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_data.binary_id' array_data implicit '_diffrn_data_frame.binary_id' diffrn_data_frame implicit '_array_intensities.binary_id' array_intensities implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.binary_id' '_array_data.binary_id' '_array_intensities.binary_id' '_array_data.binary_id' _item_default.value 1 _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_data.data _item_description.description ; The value of '_array_data.data' contains the array data encapsulated in a STAR string. The representation used is a variant on the Multipurpose Internet Mail Extensions (MIME) specified in RFC 2045-2049 by N. Freed et al. The boundary delimiter used in writing an imgCIF or CBF is "--CIF-BINARY-FORMAT-SECTION--" (including the required initial "--"). The Content-Type may be any of the discrete types permitted in RFC 2045; "application/octet-stream" is recommended. If an octet stream was compressed, the compression should be specified by the parameter 'conversions="x-CBF_PACKED"' or the parameter 'conversions="x-CBF_CANONICAL"'. The Content-Transfer-Encoding may be "BASE64", "Quoted-Printable", "X-BASE8", "X-BASE10", or "X-BASE16" for an imgCIF or "BINARY" for a CBF. The octal, decimal and hexadecimal transfer encodings are for convenience in debugging, and are not recommended for archiving and data interchange. In an imgCIF file, the encoded binary data begins after the empty line terminating the header. In a CBF, the raw binary data begins after an empty line terminating the header and after the sequence: Octet Hex Decimal Purpose 0 0C 12 (ctrl-L) Page break 1 1A 26 (ctrl-Z) Stop listings in MS-DOS 2 04 04 (Ctrl-D) Stop listings in UNIX 3 D5 213 Binary section begins None of these octets are included in the calculation of the message size, nor in the calculation of the message digest. The X-Binary-Size header specifies the size of the equivalent binary data in octets. If compression was used, this size is the size after compression, including any book-keeping fields. An adjustment is made for the deprecated binary formats in which 8 bytes of binary header are used for the compression type. In that case, the 8 bytes used for the compression type is subtracted from the size, so that the same size will be reported if the compression type is supplied in the MIME header. Use of the MIME header is the recommended way to supply the compression type. In general, no portion of the binary header is included in the calculation of the size. The X-Binary-Element-Type header specifies the type of binary data in the octets, using the same descriptive phrases as in '_array_structure.encoding_type'. The default value is "unsigned 32-bit integer". An MD5 message digest may, optionally, be used. The "RSA Data Security, Inc. MD5 Message-Digest Algorithm" should be used. No portion of the header is included in the calculation of the message digest. If the Transfer Encoding is "X-BASE8", "X-BASE10", or "X-BASE16", the data is presented as octal, decimal or hexadecimal data organized into lines or words. Each word is created by composing octets of data in fixed groups of 2, 3, 4, 6 or 8 octets, either in the order ...4321 ("big- endian") or 1234... (little-endian). If there are fewer than the specified number of octets to fill the last word, then the missing octets are presented as "==" for each missing octet. Exactly two equal signs are used for each missing octet even for octal and decimal encoding. The format of lines is: rnd xxxxxx xxxxxx xxxxxx where r is "H", "O", or "D" for hexadecimal, octal or decimal, n is the number of octets per word. and d is "<" for ">" for the "...4321" and "1234..." octet orderings respectively. The "==" padding for the last word should be on the appropriate side to correspond to the missing octets, e.g. H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000 or H3> FF0700 00==== For these hex, octal and decimal formats, only, comments beginning with "#" are permitted to improve readability. BASE64 encoding follows MIME conventions. Octets are in groups of three, c1, c2, c3. The resulting 24 bits are broken into four 6-bit quantities, starting with the high-order six bits (c1 >> 2) of the first octet, then the low-order two bits of the first octet followed by the high-order 4 bits of the second octet ((c1 & 3)<<4 | (c2>>4)), then the bottom 4 bits of the second octet followed by the high order two bits of the last octet ((c2 & 15)<<2 | (c3>>6)), then the bottom six bits of the last octet (c3 & 63). Each of these four quantities is translated into an ASCII character using the mapping: 1 2 3 4 5 6 0123456789012345678901234567890123456789012345678901234567890123 | | | | | | | ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/ With short groups of octets padded on the right with one "=" if c3 is missing, and with "==" if both c2 and c3 are missing. QUOTED-PRINTABLE encoding also follows MIME conventions, copying octets without translation if their ASCII values are 32..38, 42, 48..57, 59..60, 62, 64..126 and the octet is not a ";" in column 1. All other characters are translated to =nn, where nn is the hexadecimal encoding of the octet. All lines are "wrapped" with a terminating "=" (i.e. the MIME conventions for an implicit line terminator are never used). ; _item.name '_array_data.data' _item.category_id array_data _item.mandatory_code yes _item_type.code binary save_ ###################### # ARRAY_ELEMENT_SIZE # ###################### save_ARRAY_ELEMENT_SIZE _category.description ; Data items in the ARRAY_ELEMENT_SIZE category record the physical size of array elements along each array dimension. ; _category.id array_element_size _category.mandatory_code no loop_ _category_key.name '_array_element_size.array_id' '_array_element_size.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A regular 2D array with a uniform element dimension of 1220 nanometres. ; ; loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size image_1 1 1.22e-6 image_1 2 1.22e-6 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_element_size.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_array_element_size.array_id' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.index _item_description.description ; This item is a pointer to '_array_structure_list.index' in the ARRAY_STRUCTURE_LIST category. ; _item.name '_array_element_size.index' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.size _item_description.description ; The size in metres of an image element in this dimension. This supposes that the elements are arranged on a regular grid. ; _item.name '_array_element_size.size' _item.category_id array_element_size _item.mandatory_code yes _item_type.code float _item_units.code 'metres' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ ##################### # ARRAY_INTENSITIES # ##################### save_ARRAY_INTENSITIES _category.description ; Data items in the ARRAY_INTENSITIES category record the information required to recover the intensity data from the set of data values stored in the ARRAY_DATA category. The actual detector may have a complex relationship between the raw intensity values and the number of incident photons. In most cases, the number stored in the final array will have a simple linear relationship to the actual number of incident photons, given by '_array_intensities.gain'. If raw, uncorrected values are presented (e.g for calibration experiments), the value of '_array_intensities.linearity' will be 'raw' and '_array_intensities.gain' will not be used. ; _category.id array_intensities _category.mandatory_code no loop_ _category_key.name '_array_intensities.array_id' '_array_intensities.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 ; ; loop_ _array_intensities.array_id _array_intensities.linearity _array_intensities.gain _array_intensities.overload _array_intensities.undefined_value image_1 linear 1.2 655535 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_intensities.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_array_intensities.array_id' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code save_ save__array_intensities.binary_id _item_description.description ; This item is a pointer to '_array_data.binary_id' in the ARRAY_DATA category. ; _item.name '_array_intensities.binary_id' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code int save_ save__array_intensities.gain _item_description.description ; Detector "gain". The factor by which linearized intensity count values should be divided to produce true photon counts. ; _item.name '_array_intensities.gain' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain_esd' 'associated_value' save_ save__array_intensities.gain_esd _item_description.description ; The estimated standard deviation in detector "gain". ; _item.name '_array_intensities.gain_esd' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain' 'associated_esd' save_ save__array_intensities.linearity _item_description.description ; The intensity linearity scaling used from raw intensity to the stored element value: 'linear' is obvious 'offset' means that the value defined by '_array_intensities.offset' should be added to each element value. 'scaling' means that the value defined by '_array_intensities.scaling' should be multiplied with each element value. 'scaling_offset' is the combination of the two previous cases, with the scale factor applied before the offset value. 'sqrt_scaled' means that the square root of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and squaring the result. 'logarithmic_scaled' means that the logarithm based 10 of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and calculating 10 to the power of this number. 'raw' means that the data is a set of raw values straight from the detector. ; _item.name '_array_intensities.linearity' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'linear' . 'offset' ; The value defined by '_array_intensities.offset' should be added to each element value. ; 'scaling' ; The value defined by '_array_intensities.scaling' should be multiplied with each element value. ; 'scaling_offset' ; The combination of the scaling and offset with the scale factor applied before the offset value. ; 'sqrt_scaled' ; The square root of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and squaring the result. ; 'logarithmic_scaled' ; The logarithm based 10 of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and calculating 10 to the power of this number. ; 'raw' ; The array consists of raw values to which no corrections have been applied. While the handling of the data is similar to that given for 'linear' data with no offset, the meaning of the data differs in that the number of incident photons is not necessarily linearly related to the number of counts reported. This value is intended for use either in calibration experiments or to allow for handling more complex data fitting algorithms than are allowed for by this data item. ; save_ save__array_intensities.offset _item_description.description ; Offset value to add to array element values in the manner described by item '_array_intensities.linearity'. ; _item.name '_array_intensities.offset' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.scaling _item_description.description ; Multiplicative scaling value to be applied to array data in the manner described by item '_array_intensities.linearity'. ; _item.name '_array_intensities.scaling' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.overload _item_description.description ; The saturation intensity level for this data array. ; _item.name '_array_intensities.overload' _item.category_id array_intensities _item.mandatory_code no _item_type.code float _item_units.code 'counts' save_ save__array_intensities.undefined_value _item_description.description ; A value to be substituted for undefined values in the data array. ; _item.name '_array_intensities.undefined_value' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ ################### # ARRAY_STRUCTURE # ################### save_ARRAY_STRUCTURE _category.description ; Data items in the ARRAY_STRUCTURE category record the organization and encoding of array data which may be stored in the ARRAY_DATA category. ; _category.id array_structure _category.mandatory_code no _category_key.name '_array_structure.id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order image_1 "unsigned 16-bit integer" none little_endian ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure.byte_order _item_description.description ; The order of bytes for integer values which require more than 1-byte. (IBM-PC's and compatibles, and Dec-Vaxes use low-byte-first ordered integers, whereas Hewlett Packard 700 series, Sun-4 and Silicon Graphics use high-byte-first ordered integers. Dec-Alphas can produce/use either depending on a compiler switch.) ; _item.name '_array_structure.byte_order' _item.category_id array_structure _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'big_endian' ; The first byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; 'little_endian' ; The last byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; save_ save__array_structure.compression_type _item_description.description ; Type of data compression method used to compress the array data. ; _item.name '_array_structure.compression_type' _item.category_id array_structure _item.mandatory_code no _item_type.code code _item_default.value 'none' loop_ _item_enumeration.value _item_enumeration.detail 'none' ; Data are stored in normal format as defined by '_array_structure.encoding_type' and '_array_structure.byte_order'. ; 'byte_offsets' ; Using the compression scheme defined in CBF definition Section 5.0. ; 'packed' ; Using the 'packed' compression scheme, a CCP4-style packing (CBFlib section 3.3.2) ; 'canonical' ; Using the 'canonical' compression scheme (CBFlib section 3.3.1) ; save_ save__array_structure.encoding_type _item_description.description ; Data encoding of a single element of array data. In several cases, the IEEE format is referenced. See "IEEE Standard for Binary Floating-Point Arithmetic", ANSI/IEEE Std 754-1985, the Institute of Electrical and Electronics Engineers, Inc., NY 1985. ; _item.name '_array_structure.encoding_type' _item.category_id array_structure _item.mandatory_code yes _item_type.code uline loop_ _item_enumeration.value 'unsigned 8-bit integer' 'signed 8-bit integer' 'unsigned 16-bit integer' 'signed 16-bit integer' 'unsigned 32-bit integer' 'signed 32-bit integer' 'signed 32-bit real IEEE' 'signed 64-bit real IEEE' 'signed 32-bit complex IEEE' save_ save__array_structure.id _item_description.description ; The value of '_array_structure.id' must uniquely identify each item of array data. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure.id' array_structure yes '_array_data.array_id' array_data yes '_array_structure_list.array_id' array_structure_list yes '_array_intensities.array_id' array_intensities yes '_diffrn_data_frame.array_id' diffrn_data_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_data.array_id' '_array_structure.id' '_array_structure_list.array_id' '_array_structure.id' '_array_intensities.array_id' '_array_structure.id' '_diffrn_data_frame.array_id' '_array_structure.id' save_ ######################## # ARRAY_STRUCTURE_LIST # ######################## save_ARRAY_STRUCTURE_LIST _category.description ; Data items in the ARRAY_STRUCTURE_LIST category record the size and organization of each array dimension. The relationship to physical axes may be given. ; _category.id array_structure_list _category.mandatory_code no loop_ _category_key.name '_array_structure_list.array_id' '_array_structure_list.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - An image array of 1300 x 1200 elements. The raster order of the image is left-to-right (increasing) in the first dimension and bottom-to-top (decreasing) in the second dimension. ; ; loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id image_1 1 1300 1 increasing ELEMENT_X image_1 2 1200 2 decreasing ELEMENY_Y ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure_list.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_array_structure_list.array_id' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code code save_ save__array_structure_list.axis_set_id _item_description.description ; This is a descriptor for the physical axis or set of axes corresponding to an array index. This data item is related to the axes of the detector itself given in DIFFRN_DETECTOR_AXIS, but usually differ in that the axes in this category are the axes of the coordinate system of reported data points, while the axes in DIFFRN_DETECTOR_AXIS are the physical axes of the detector describing the "poise" of the detector as an overall physical object. If there is only one axis in the set, the identifier of that axis should be used as the identifier of the set. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.axis_set_id' array_structure_list yes '_array_structure_list_axis.axis_set_id' array_structure_list_axis implicit _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_structure_list_axis.axis_set_id' '_array_structure_list.axis_set_id' save_ save__array_structure_list.dimension _item_description.description ; The number of elements stored in the array structure in this dimension. ; _item.name '_array_structure_list.dimension' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.direction _item_description.description ; Identifies the direction in which this array index changes. ; _item.name '_array_structure_list.direction' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_enumeration.value _item_enumeration.detail 'increasing' ; Indicates the index changes from 1 to the maximum dimension. ; 'decreasing' ; Indicates the index changes from the maximum dimension to 1. ; save_ save__array_structure_list.index _item_description.description ; Identifies the one-based index of the row or column in the array structure. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.index' array_structure_list yes '_array_structure_list.precedence' array_structure_list yes '_array_element_size.index' array_element_size yes _item_type.code int loop_ _item_linked.child_name _item_linked.parent_name '_array_element_size.index' '_array_structure_list.index' loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.precedence _item_description.description ; Identifies the rank order in which this array index changes with respect to other array indices. The precedence of 1 indicates the index which changes fastest. ; _item.name '_array_structure_list.precedence' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ ############################# # ARRAY_STRUCTURE_LIST_AXIS # ############################# save_ARRAY_STRUCTURE_LIST_AXIS _category.description ; Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe the physical settings of sets axes for the centres of pixels that correspond to data points described in the ARRAY_STRUCTURE_LIST category. In the simplest cases, the physical increments of a single axis correspond to the increments of a single array index. More complex organizations, e.g. spiral scans, may require coupled motions along multiple axes. Note that a spiral scan uses two coupled axis, one for the angular direction, one for the radial direction. This differs from a cylindrical scan for which the two axes are not coupled into one set. ; _category.id array_structure_list_axis _category.mandatory_code no loop_ _category_key.name '_array_structure_list_axis.axis_set_id' '_array_structure_list_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' save_ save__array_structure_list_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes from the set of axes for which settings are being specified. Multiple axes may be specified for the same value of '_array_structure_list_axis.axis_set_id' This item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_array_structure_list_axis.axis_id' _item.category_id array_structure_list_axis _item.mandatory_code yes _item_type.code code save_ save__array_structure_list_axis.axis_set_id _item_description.description ; The value of this data item is the identifier of the set of axes for which axis settings are being specified. Multiple axes may be specified for the same value of '_array_structure_list_axis.axis_set_id'. This item is a pointer to '_array_structure_list.axis_set_id' in the ARRAY_STRUCTURE_LIST category. If this item is not specified, it defaults to the corresponding axis identifier. ; _item.name '_array_structure_list_axis.axis_set_id' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_type.code code save_ save__array_structure_list_axis.angle _item_description.description ; The setting of the specified axis in degrees for the first data point of the array index with the corresponding value of '_array_structure_list.axis_set_id'. If the index is specified as 'increasing' this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing' this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.angle' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.angle_increment _item_description.description ; The pixel-centre-to-pixel-centre increment in the angular setting of the specified axis in degrees. This is not meaningful in the case of 'constant velocity' spiral scans and should not be specified in that case. See '_array_structure_list_axis.angular_pitch'. ; _item.name '_array_structure_list_axis.angle_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for the first data point of the array index with the corresponding value of '_array_structure_list.axis_set_id'. If the index is specified as 'increasing' this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing' this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.displacement' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.displacement_increment _item_description.description ; The pixel-centre-to-pixel-centre increment for the displacement setting of the specified axis in millimetres. ; _item.name '_array_structure_list_axis.displacement_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.angular_pitch _item_description.description ; The pixel-centre-to-pixel-centre distance for a one step change in the setting of the specified axis in millimetres. This is meaningful only for 'constant velocity' spiral scans, or for uncoupled angular scans at a constant radius (cylindrical scan) and should not be specified for cases in which the angle between pixels, rather than the distance between pixels is uniform. See '_array_structure_list_axis.angle_increment'. ; _item.name '_array_structure_list_axis.angular_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.radial_pitch _item_description.description ; The radial distance from one "cylinder" of pixels to the next in millimetres. If the scan is a 'constant velocity' scan with differing angular displacements between pixels, the value of this item may differ significantly from the value of '_array_structure_list_axis.displacement_increment'. ; _item.name '_array_structure_list_axis.radial_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ ######## # AXIS # ######## save_AXIS _category.description ; Data items in the AXIS category record the information required to describe the various goniometer, detector, source and other axes needed to specify a data collection. The location of each axis is specified by two vectors: the axis itself, given as a unit vector, and an offset to the base of the unit vector. These vectors are referenced to a right-handed laboratory coordinate system with its origin in the sample or specimen: | Y (to complete right-handed system) | | | | | |________________X / principal goniometer axis / / / / /Z (to source) Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from the sample or specimen along the principal axis of the goniometer. Axis 2 (Y): The Y-axis completes an orthogonal right-handed system defined by the X-axis and the Z-axis (see below). Axis 3 (Z): The Z-axis is derived from the source axis which goes from the sample to the source. The Z-axis is the component of the source axis in the direction of the source orthogonal to the X-axis in the plane defined by the X-axis and the source axis. These axes are based on the goniometer, not on the orientation of the detector, gravity, etc. The vectors necessary to specify all other axes are given by sets of three components in the order (X, Y, Z). If the axis involved is a rotation axis, it is right handed, i.e. as one views the object to be rotated from the origin (the tail) of the unit vector, the rotation is clockwise. If a translation axis is specified, the direction of the unit vector specifies the sense of positive translation. Note: This choice of coordinate system is similar to, but significantly different from the choice in MOSFLM (Andrew G.W. Leslie, Harry Powell, MRC Laboratory of Molecular Biology, Hills Road, Cambridge CB2 2QH, UK http://www.dl.ac.uk/CCP/CCP4/dist/x-windows/Mosflm/). In MOSFLM, X is along the X-ray beam (the CBF/imgCIF Z axis) and Z is along the rotation axis. All rotations are given in degrees and all translations are given in mm. Axes may be dependent on one another. The X-axis is the only goniometer axis the direction of which is strictly connected to the hardware. All other axes are specified by the positions they would assume when the axes upon which they depend are at their zero points. When specifying detector axes, the axis is given to the beam centre. The location of the beam centre on the detector should be given in the DIFFRN_DETECTOR category in distortion-corrected mm from the (0,0) corner of the detector. It should be noted that many different origins arise in the definition of an experiment. In particular, as noted above, we need to specify the location of the beam centre on the detector in terms of the origin of the detector, which is, of course, not coincident with the centre of the sample. ; _category.id axis _category.mandatory_code no loop_ _category_key.name '_axis.id' '_axis.equipment' loop_ _category_group.id 'inclusive_group' 'axis_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows the axis specification of the axes of a kappa geometry goniometer (See "X-Ray Structure Determination, A Practical Guide", 2nd ed. by G. H. Stout, L. H. Jensen, Wiley Interscience, 1989, 453 pp, p 134.). There are three axes specified, and no offsets. The outermost axis, omega, is pointed along the X-axis. The next innermost axis, kappa, is at a 50 degree angle to the X-axis, pointed away from the source. The innermost axis, phi, aligns with the X-axis when omega and phi are at their zero-points. If T-omega, T-kappa and T-phi are the transformation matrices derived from the axis settings, the complete transformation would be: x' = (T-omega) (T-kappa) (T-phi) x ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] omega rotation goniometer . 1 0 0 kappa rotation goniometer omega -.64279 0 -.76604 phi rotation goniometer kappa 1 0 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - This example show the axis specification of the axes of a detector, source and gravity. We have juggled the order as a reminder that the ordering of presentation of tokens is not significant. We have taken the centre of rotation of the detector to be 68 millimetres in the direction away from the source. ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] source . source . 0 0 1 . . . gravity . gravity . 0 -1 0 . . . tranz translation detector rotz 0 0 1 0 0 -68 twotheta rotation detector . 1 0 0 . . . roty rotation detector twotheta 0 1 0 0 0 -68 rotz rotation detector roty 0 0 1 0 0 -68 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__axis.depends_on _item_description.description ; The value of '_axis.depends_on' specifies the next outermost axis upon which this axis depends. This item is a pointer to '_axis.id' in the same category. ; _item.name '_axis.depends_on' _item.category_id axis _item.mandatory_code no save_ save__axis.equipment _item_description.description ; The value of '_axis.equipment' specifies the type of equipment using the axis: 'goniometer', 'detector', 'gravity', 'source' or 'general'. ; _item.name '_axis.equipment' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail goniometer 'equipment used to orient or position samples' detector 'equipment used to detect reflections' general 'equipment used for general purposes' gravity 'axis specifying the downward direction' source 'axis specifying the direction sample to source' save_ save__axis.offset[1] _item_description.description ; The [1] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[2] _item_description.description ; The [2] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[3] _item_description.description ; The [3] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.id _item_description.description ; The value of '_axis.id' must uniquely identify each axis relevant to the experiment. Note that multiple pieces of equipment may share the same axis (e.g. a twotheta arm), so that the category key for AXIS also includes the equipment. ; loop_ _item.name _item.category_id _item.mandatory_code '_axis.id' axis yes '_array_structure_list_axis.axis_id' array_structure_list_axis yes '_diffrn_detector_axis.axis_id' diffrn_detector_axis yes '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes '_diffrn_scan_axis.axis_id' diffrn_scan_axis yes '_diffrn_scan_frame_axis.axis_id' diffrn_scan_frame_axis yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_axis.depends_on' '_axis.id' '_array_structure_list_axis.axis_id' '_axis.id' '_diffrn_detector_axis.axis_id' '_axis.id' '_diffrn_measurement_axis.axis_id' '_axis.id' '_diffrn_scan_axis.axis_id' '_axis.id' '_diffrn_scan_frame_axis.axis_id' '_axis.id' save_ save__axis.type _item_description.description ; The value of '_axis.type' specifies the type of axis: 'rotation', 'translation' (or 'general' when the type is not relevant, as for gravity). ; _item.name '_axis.type' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail rotation 'right-handed axis of rotation' translation 'translation in the direction of the axis' general 'axis for which the type is not relevant' save_ save__axis.vector[1] _item_description.description ; The [1] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[2] _item_description.description ; The [2] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[3] _item_description.description ; The [3] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ ##################### # DIFFRN_DATA_FRAME # ##################### save_DIFFRN_DATA_FRAME _category.description ; Data items in the DIFFRN_DATA_FRAME category record the details about each frame of data. The items in this category were previously in a DIFFRN_FRAME_DATA category, which is now deprecated. The items from the old category are provided as aliases but should not be used for new work. ; _category.id diffrn_data_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_data_frame.id' '_diffrn_data_frame.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A frame containing data from 4 frame elements. Each frame element has a common array configuration 'array_1' described in ARRAY_STRUCTURE and related categories. The data for each detector element is stored in four groups of binary data in the ARRAY_DATA category, linked by the array_id and binary_id ; ; loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id frame_1 d1_ccd_1 array_1 1 frame_1 d1_ccd_2 array_1 2 frame_1 d1_ccd_3 array_1 3 frame_1 d1_ccd_4 array_1 4 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_data_frame.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_diffrn_data_frame.array_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.array_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0.00 _item_type.code code save_ save__diffrn_data_frame.binary_id _item_description.description ; This item is a pointer to '_array_data.binary_id' in the ARRAY_DATA category. ; _item.name '_diffrn_data_frame.binary_id' _item.category_id diffrn_data_frame _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_frame_data.binary_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code int save_ save__diffrn_data_frame.detector_element_id _item_description.description ; This item is a pointer to '_diffrn_detector_element.id' in the DIFFRN_DETECTOR_ELEMENT category. ; _item.name '_diffrn_data_frame.detector_element_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.detector_element_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.id _item_description.description ; The value of '_diffrn_data_frame.id' must uniquely identify each complete frame of data. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_data_frame.id' diffrn_data_frame yes '_diffrn_refln.frame_id' diffrn_refln yes '_diffrn_scan.frame_id_start' diffrn_scan yes '_diffrn_scan.frame_id_end' diffrn_scan yes '_diffrn_scan_frame.frame_id' diffrn_scan_frame yes '_diffrn_scan_frame_axis.frame_id' diffrn_scan_frame_axis yes _item_aliases.alias_name '_diffrn_frame_data.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_refln.frame_id' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_start' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_end' '_diffrn_data_frame.id' '_diffrn_scan_frame.frame_id' '_diffrn_data_frame.id' '_diffrn_scan_frame_axis.frame_id' '_diffrn_data_frame.id' save_ ########################################################################## # The following is a restatement of the mmCIF DIFFRN_DETECTOR, # # DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for # # the CBF/imgCIF extensions # ########################################################################## ################### # DIFFRN_DETECTOR # ################### save_DIFFRN_DETECTOR _category.description ; Data items in the DIFFRN_DETECTOR category describe the detector used to measure the scattered radiation, including any analyser and post-sample collimation. ; _category.id diffrn_detector _category.mandatory_code no loop_ _category_key.name '_diffrn_detector.diffrn_id' '_diffrn_detector.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_detector.diffrn_id 'd1' _diffrn_detector.detector 'multiwire' _diffrn_detector.type 'Siemens' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector.details _item_description.description ; A description of special aspects of the radiation detector. ; _item.name '_diffrn_detector.details' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'slow mode' save_ save__diffrn_detector.detector _item_description.description ; The general class of the radiation detector. ; _item.name '_diffrn_detector.detector' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector' cifdic.c91 1.0 '_diffrn_detector' cif_core.dic 2.0 _item_type.code text loop_ _item_examples.case 'photographic film' 'scintillation counter' 'CCD plate' 'BF~3~ counter' save_ save__diffrn_detector.diffrn_id _item_description.description ; This data item is a pointer to '_diffrn.id' in the DIFFRN category. The value of '_diffrn.id' uniquely defines a set of diffraction data. ; _item.name '_diffrn_detector.diffrn_id' _item.mandatory_code yes save_ save__diffrn_detector.dtime _item_description.description ; The deadtime in microseconds of the detectors used to measure the diffraction intensities. ; _item.name '_diffrn_detector.dtime' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector_dtime' cifdic.c91 1.0 '_diffrn_detector_dtime' cif_core.dic 2.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code microseconds save_ save__diffrn_detector.id _item_description.description ; The value of '_diffrn_detector.id' must uniquely identify each detector used to collect each diffraction data set. If the value of '_diffrn_detector.id' is not given, it is implicitly equal to the value of '_diffrn_detector.diffrn_id' ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector.id' diffrn_detector implicit '_diffrn_detector_axis.detector_id' diffrn_detector_axis yes loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_detector_axis.detector_id' '_diffrn_detector.id' _item_type.code code save_ save__diffrn_detector.number_of_axes _item_description.description ; The value of '_diffrn_detector.number_of_axes' gives the number of axes of the positioner for the detector identified by '_diffrn_detector.id'. The word "positioner" is a general term used in instrumentation design for devices that are used to change the positions of portions of apparatus by linear translation, rotation, or combinations of such motions. Axes which are used to provide a coordinate system for the face of an area detetctor should not be counted for this data item. The description of each axis should be provided by entries in DIFFRN_DETECTOR_AXIS. ; _item.name '_diffrn_detector.number_of_axes' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_detector.type _item_description.description ; The make, model or name of the detector device used. ; _item.name '_diffrn_detector.type' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ ######################## # DIFFRN_DETECTOR_AXIS # ######################## save_DIFFRN_DETECTOR_AXIS _category.description ; Data items in the DIFFRN_DETECTOR_AXIS category associate axes with detectors. ; _category.id diffrn_detector_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_axis.detector_id' '_diffrn_detector_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_detector_axis.axis_id _item_description.description ; This data item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_diffrn_detector_axis.axis_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_axis.detector_id _item_description.description ; This data item is a pointer to '_diffrn_detector.id' in the DIFFRN_DETECTOR category. This item was previously named '_diffrn_detector_axis.id' which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_detector_axis.detector_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_aliases.alias_name '_diffrn_detector_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ ########################### # DIFFRN_DETECTOR_ELEMENT # ########################### save_DIFFRN_DETECTOR_ELEMENT _category.description ; Data items in the DIFFRN_DETECTOR_ELEMENT category record the details about spatial layout and other characteristics of each element of a detector which may have multiple elements. In most cases, the more detailed information provided in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS are preferable to simply providing the centre. ; _category.id diffrn_detector_element _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_element.id' '_diffrn_detector_element.detector_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Detector d1 is composed of four CCD detector elements, each 200 mm by 200 mm, arranged in a square. in the pattern 1 2 * 3 4 Note that the beam centre is slightly displaced from each of the detector elements, just beyond the lower right corner of 1, the lower left corner of 2, the upper right corner of 3 and the upper left corner of 4. ; ; loop_ _diffrn_detector_element.detector_id _diffrn_detector_element.id _diffrn_detector_element.center[1] _diffrn_detector_element.center[2] d1 d1_ccd_1 201.5 -1.5 d1 d1_ccd_2 -1.8 -1.5 d1 d1_ccd_3 201.6 201.4 d1 d1_ccd_4 -1.7 201.5 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector_element.center[1] _item_description.description ; The value of '_diffrn_detector_element.center[1]' is the X component of the distortion-corrected beam-centre in mm from the (0, 0) (lower left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. ; _item.name '_diffrn_detector_element.center[1]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.center[2] _item_description.description ; The value of '_diffrn_detector_element.center[2]' is the Y component of the distortion-corrected beam-centre in mm from the (0, 0) (lower left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. ; _item.name '_diffrn_detector_element.center[2]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.id _item_description.description ; The value of '_diffrn_detector_element.id' must uniquely identify each element of a detector. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector_element.id' diffrn_detector_element yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.detector_element_id' '_diffrn_detector_element.id' save_ save__diffrn_detector_element.detector_id _item_description.description ; This item is a pointer to '_diffrn_detector.id' in the DIFFRN_DETECTOR category. ; _item.name '_diffrn_detector_element.detector_id' _item.category_id diffrn_detector_element _item.mandatory_code yes _item_type.code code save_ ######################## ## DIFFRN_MEASUREMENT ## ######################## save_DIFFRN_MEASUREMENT _category.description ; Data items in the DIFFRN_MEASUREMENT category record details about the device used to orient and/or position the crystal during data measurement and the manner in which the diffraction data were measured. ; _category.id diffrn_measurement _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement.device' '_diffrn_measurement.diffrn_id' '_diffrn_measurement.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_measurement.diffrn_id 'd1' _diffrn_measurement.device '3-circle camera' _diffrn_measurement.device_type 'Supper model x' _diffrn_measurement.device_details 'none' _diffrn_measurement.method 'omega scan' _diffrn_measurement.details ; Need new example here ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991). Acta Cryst. C47, 2276-2277]. ; ; _diffrn_measurement.diffrn_id 's1' _diffrn_measurement.device_type 'Philips PW1100/20 diffractometer' _diffrn_measurement.method 'theta/2theta (\q/2\q)' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_measurement.device _item_description.description ; The general class of goniometer or device used to support and orient the specimen. If the value of '_diffrn_measurement.device' is not given, it is implicitly equal to the value of '_diffrn_measurement.diffrn_id'. Either '_diffrn_measurement.device' or '_diffrn_measurement.id' may be used to link to other categories. If the experimental setup admits multiple devices, then '_diffrn_measurement.id' is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.device' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_device' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement.device' _item_aliases.alias_name '_diffrn_measurement_device' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '3-circle camera' '4-circle camera' 'kappa-geometry camera' 'oscillation camera' 'precession camera' save_ save__diffrn_measurement.device_details _item_description.description ; A description of special aspects of the device used to measure the diffraction intensities. ; _item.name '_diffrn_measurement.device_details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; commercial goniometer modified locally to allow for 90\% \t arc ; save_ save__diffrn_measurement.device_type _item_description.description ; The make, model or name of the measurement device (goniometer) used. ; _item.name '_diffrn_measurement.device_type' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Supper model q' 'Huber model r' 'Enraf-Nonius model s' 'homemade' save_ save__diffrn_measurement.diffrn_id _item_description.description ; This data item is a pointer to '_diffrn.id' in the DIFFRN category. ; _item.name '_diffrn_measurement.diffrn_id' _item.mandatory_code yes save_ save__diffrn_measurement.details _item_description.description ; A description of special aspects of the intensity measurement. ; _item.name '_diffrn_measurement.details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; save_ save__diffrn_measurement.id _item_description.description ; The value of '_diffrn_measurement.id' must uniquely identify the set of mechanical characteristics of the device used to orient and/or position the sample used during collection of each diffraction data set. If the value of '_diffrn_measurement.id' is not given, it is implicitly equal to the value of '_diffrn_measurement.diffrn_id'. Either '_diffrn_measurement.device' or '_diffrn_measurement.id' may be used to link to other categories. If the experimental setup admits multiple devices, then '_diffrn_measurement.id' is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.id' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_id' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement.id' _item_type.code code save_ save__diffrn_measurement.method _item_description.description ; Method used to measure intensities. ; _item.name '_diffrn_measurement.method' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_method' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'profile data from theta/2theta (\q/2\q) scans' save_ save__diffrn_measurement.number_of_axes _item_description.description ; The value of '_diffrn_measurement.number_of_axes' gives the number of axes of the positioner for the goniometer or other sample orientation or positioning device identified by '_diffrn_measurement.id'. The description of the axes should be provided by entries in DIFFRN_MEASUREMENT_AXIS. ; _item.name '_diffrn_measurement.number_of_axes' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_measurement.specimen_support _item_description.description ; The physical device used to support the crystal during data collection. ; _item.name '_diffrn_measurement.specimen_support' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_specimen_support' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'glass capillary' 'quartz capillary' 'fiber' 'metal loop' save_ ########################### # DIFFRN_MEASUREMENT_AXIS # ########################### save_DIFFRN_MEASUREMENT_AXIS _category.description ; Data items in the DIFFRN_MEASUREMENT_AXIS category associate axes with goniometers. ; _category.id diffrn_measurement_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_measurement_axis.axis_id _item_description.description ; This data item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_diffrn_measurement_axis.axis_id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.measurement_device _item_description.description ; This data item is a pointer to '_diffrn_measurement.device' in the DIFFRN_MEASUREMENT category. ; _item.name '_diffrn_measurement_axis.measurement_device' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit _item_type.code text save_ save__diffrn_measurement_axis.measurement_id _item_description.description ; This data item is a pointer to '_diffrn_measurement.id' in the DIFFRN_MEASUREMENT category. This item was previously named '_diffrn_measurement_axis.id' which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_measurement_axis.measurement_id' _item.category_id diffrn_measurement_axis _item_aliases.alias_name '_diffrn_measurement_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0.00 _item.mandatory_code implicit _item_type.code code save_ #################### # DIFFRN_RADIATION # #################### save_DIFFRN_RADIATION _category.description ; Data items in the DIFFRN_RADIATION category describe the radiation used in measuring diffraction intensities, its collimation and monochromatisation before the sample. Post-sample treatment of the beam is described by data items in the DIFFRN_DETECTOR category. ; _category.id diffrn_radiation _category.mandatory_code no _category_key.name '_diffrn_radiation.diffrn_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_radiation.diffrn_id 'set1' _diffrn_radiation.collimation '0.3 mm double pinhole' _diffrn_radiation.monochromator 'graphite' _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.wavelength_id 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991). Acta Cryst. C47, 2276-2277]. ; ; _diffrn_radiation.wavelength_id 1 _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.monochromator 'graphite' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_radiation.collimation _item_description.description ; The collimation or focusing applied to the radiation. ; _item.name '_diffrn_radiation.collimation' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_collimation' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '0.3 mm double-pinhole' '0.5 mm' 'focusing mirrors' save_ save__diffrn_radiation.diffrn_id _item_description.description ; This data item is a pointer to '_diffrn.id' in the DIFFRN category. ; _item.name '_diffrn_radiation.diffrn_id' _item.mandatory_code yes save_ save__diffrn_radiation.div_x_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory X axis (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the esd of the directions of photons in the X-Z plane around the mean source beam direction. Note that some synchrotrons specify this value in milliradians, in which case a conversion would be needed. To go from a value in milliradians to a value in degrees, multiply by 0.180 and divide by \p. ; _item.name '_diffrn_radiation.div_x_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.div_y_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory Y axis (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the esd of the directions of photons in the Y-Z plane around the mean source beam direction. Note that some synchrotrons specify this value in milliradians, in which case a conversion would be needed. To go from a value in milliradians to a value in degrees, multiply by 0.180 and divide by \p. ; _item.name '_diffrn_radiation.div_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.div_x_y_source _item_description.description ; Beam crossfire correlation degrees^2^ between the crossfire laboratory X-axis component and the crossfire laboratory Y-axis component (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the mean of the products of the deviations of the direction of each photons in X-Z plane times the deviations of the direction of the same photon in the Y-Z plane around the mean source beam direction. This will be zero for uncorrelated crossfire. Note that some synchrotrons specify this value in milliradians^2^, in which case a conversion would be needed. To go from a value in milliradians^2^ to a value in degrees^2^, multiply by 0.180^2^ and divide by \p^2^. ; _item.name '_diffrn_radiation.div_x_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees_squared _item_default.value 0.0 save_ save__diffrn_radiation.filter_edge _item_description.description ; Absorption edge in \%Angstroms of the radiation filter used. ; _item.name '_diffrn_radiation.filter_edge' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_filter_edge' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__diffrn_radiation.inhomogeneity _item_description.description ; Half-width in millimetres of the incident beam in the direction perpendicular to the diffraction plane. ; _item.name '_diffrn_radiation.inhomogeneity' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_inhomogeneity' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code millimetres save_ save__diffrn_radiation.monochromator _item_description.description ; The method used to obtain monochromatic radiation. If a monochromator crystal is used the material and the indices of the Bragg reflection are specified. ; _item.name '_diffrn_radiation.monochromator' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_monochromator' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Zr filter' 'Ge 220' 'none' 'equatorial mounted graphite' save_ save__diffrn_radiation.polarisn_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the perpendicular component of the polarisation and the diffraction plane. See _diffrn_radiation_polarisn_ratio. ; _item.name '_diffrn_radiation.polarisn_norm' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_norm' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.polarisn_ratio _item_description.description ; Polarisation ratio of the diffraction beam incident on the crystal. It is the ratio of the perpendicularly polarised to the parallel polarised component of the radiation. The perpendicular component forms an angle of '_diffrn_radiation.polarisn_norm' to the normal to the diffraction plane of the sample (i.e. the plane containing the incident and reflected beams). ; _item.name '_diffrn_radiation.polarisn_ratio' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_ratio' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__diffrn_radiation.polarizn_source_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the normal to the polarization plane and the laboratory Y axis as defined in the AXIS category. Note that this is the angle of polarization of the source photons, either directly from a synchrotron beamline or from a monchromater. This differs from the value of '_diffrn_radiation.polarisn_norm' in that '_diffrn_radiation.polarisn_norm' refers to polarization relative to the diffraction plane rather than to the laboratory axis system. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane should be taken as the X-Z plane, and the angle as 0. See '_diffrn_radiation.polarizn_source_ratio'. ; _item.name '_diffrn_radiation.polarizn_source_norm' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.polarizn_source_ratio _item_description.description ; (Ip-In)/(Ip+In), where Ip is the intensity (amplitude squared) of the electric vector in the plane of polarization and In is the intensity (amplitude squared) of the electric vector in plane of the normal to the plane of polarization. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane is be taken as the X-Z plane, and the normal is parallel to the Y-axis. Thus, if we had complete polarization in the plane of polarization, the value of '_diffrn_radiation.polarizn_source_ratio' would be 1, and an unpolarized beam would have a value of 0. If the X-axis has been chosen to lie in the plane of polarization, this definition will agree with the definition of "MONOCHROMATOR" in the Denzo glossary, and values of near 1 should be expected for a bending magnet source. However, if the X-axis were, for some reason to be, say, perpendicular to the polarization plane (not a common choice), then the Denzo value would be the negative of '_diffrn_radiation.polarizn_source_ratio'. See http://www.hkl-xray.com for information on Denzo, and Z. Otwinowski and W. Minor, "Processing of X-ray Diffraction Data Collected in Oscillation Mode", Methods in Enzymology, Volume 276: Macromolecular Crystallography, part A, p.307-326, 1997,C.W. Carter, Jr. & R. M. Sweet, Eds., Academic Press. This differs both in the choice of ratio and choice of orientation from '_diffrn_radiation.polarisn_ratio', which, unlike '_diffrn_radiation.polarizn_source_ratio', is unbounded. ; _item.name '_diffrn_radiation.polarizn_source_ratio' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 -1.0 -1.0 -1.0 _item_type.code float save_ save__diffrn_radiation.probe _item_description.description ; Name of the type of radiation used. It is strongly encouraged that this field be specified so that the probe radiation can be simply determined. ; _item.name '_diffrn_radiation.probe' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_probe' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value 'x-ray' 'neutron' 'electron' 'gamma' save_ save__diffrn_radiation.type _item_description.description ; The nature of the radiation. This is typically a description of the X-ray wavelength in Siegbahn notation. ; _item.name '_diffrn_radiation.type' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'CuK\a' 'Cu K\a~1~' 'Cu K-L~2,3~' 'white-beam' save_ save__diffrn_radiation.xray_symbol _item_description.description ; The IUPAC symbol for the X-ray wavelength for probe radiation. ; _item.name '_diffrn_radiation.xray_symbol' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_xray_symbol' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value _item_enumeration.detail 'K-L~3~' 'K\a~1~ in older Siegbahn notation' 'K-L~2~' 'K\a~2~ in older Siegbahn notation' 'K-M~3~' 'K\b~1~ in older Siegbahn notation' 'K-L~2,3~' 'use where K-L~3~ and K-L~2~ are not resolved' save_ save__diffrn_radiation.wavelength_id _item_description.description ; This data item is a pointer to '_diffrn_radiation_wavelength.id' in the DIFFRN_RADIATION_WAVELENGTH category. ; _item.name '_diffrn_radiation.wavelength_id' _item.category_id diffrn_radiation _item.mandatory_code yes _item_type.code code save_ ################ # DIFFRN_REFLN # ################ save_DIFFRN_REFLN _category.description ; This category redefinition has been added to extend the key of the standard DIFFRN_REFLN category. ; _category.id diffrn_refln _category.mandatory_code no _category_key.name '_diffrn_refln.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_refln.frame_id _item_description.description ; This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_refln.frame_id' _item.category_id diffrn_refln _item.mandatory_code yes _item_type.code code save_ ############### # DIFFRN_SCAN # ############### save_DIFFRN_SCAN _category.description ; Data items in the DIFFRN_SCAN category describe the parameters of one or more scans, relating axis positions to frames. ; _category.id diffrn_scan _category.mandatory_code no _category_key.name '_diffrn_scan.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - derived from a suggestion by R. M. Sweet. The vector of each axis is not given here, because it is provided in the AXIS category. By making '_diffrn_scan_axis.scan_id' and '_diffrn_scan_axis.axis_id' keys of the DIFFRN_SCAN_AXIS category, an arbitrary number of scanning and fixed axes can be specified for a scan. We have specified three rotation axes and one translation axis at non-zero values, with one axis stepping. There is no reason why more axes could not have been specified to step. We have specified range information, but note that it is redundant from the number of frames and the increment, so we could drop the data item '_diffrn_scan_axis.angle_range'. We have specified both the sweep data and the data for a single frame. Note that the information on how the axes are stepped is given twice, once in terms of the overall averages in the value of '_diffrn_scan.integration_time' and the values for DIFFRN_SCAN_AXIS, and precisely for the given frame in the value for '_diffrn_scan_frame.integration_time' and the values for DIFFRN_SCAN_FRAME_AXIS. If dose-related adjustements are made to scan times and non-linear stepping is done, these values may differ. Therefore, in interpreting the data for a particular frame it is important to use the frame-specific data. ; ; _diffrn_scan.id 1 _diffrn_scan.date_start '2001-11-18T03:26:42' _diffrn_scan.date_end '2001-11-18T03:36:45' _diffrn_scan.integration_time 3.0 _diffrn_scan.frame_id_start mad_L2_000 _diffrn_scan.frame_id_end mad_L2_200 _diffrn_scan.frames 201 loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment 1 omega 200.0 20.0 0.1 . . . 1 kappa -40.0 0.0 0.0 . . . 1 phi 127.5 0.0 0.0 . . . 1 tranz . . . 2.3 0.0 0.0 _diffrn_scan_frame.scan_id 1 _diffrn_scan_frame.date '2001-11-18T03:27:33' _diffrn_scan_frame.integration_time 3.0 _diffrn_scan_frame.frame_id mad_L2_018 _diffrn_scan_frame.frame_number 18 loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.angle_increment _diffrn_scan_frame_axis.displacement _diffrn_scan_frame_axis.displacement_increment mad_L2_018 omega 201.8 0.1 . . mad_L2_018 kappa -40.0 0.0 . . mad_L2_018 phi 127.5 0.0 . . mad_L2_018 tranz . . 2.3 0.0 ; ; Example 2 - a more extensive example, R. M. Sweet, P. Ellis, H. Bernstein. We place a detector 240 mm along the Z axis from the goniometer. This presents us with a choice -- either we define the axes of the detector at the origin, and then put a Z setting of -240 in for the actual use, or we define the axes with the necessary Z-offset. In this case we use the setting, and leave the offset as zero. We call this axis DETECTOR_Z. The axis for positioning the detector in the Y-direction depends on the detector Z-axis. We call this axis, DETECTOR_Y. The axis for positioning the detector in the X-direction depends on the detector Y-axis (and therefore on the detector Z-axis). We call this axis DETECTOR_X. This detector may be rotated around the Y-axis. This rotation axis depends on the three translation axes. We call it DETECTOR_PITCH. We define a coordinate system on the face of the detector in terms of 2300 0.150 mm pixels in each direction. The ELEMENT_X axis is used to index the first array index of the data array and the ELEMENT_Y axis is used to index the second array index. Because the pixels are 0.150mm x 0.150mm, the centre of the first pixel is at (0.075, 0.075) in this coordinate system. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 172.43 -172.43 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 2300 1 increasing ELEMENT_X ARRAY1 2 2300 2 increasing ELEMENT_Y # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.075 0.150 ELEMENT_Y ELEMENT_Y 0.075 0.150 # category ARRAY_ELEMENT_SIZE loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 ARRAY1 2 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; ; Example 3 - Example 2 revised for a spiral scan, R. M. Sweet, P. Ellis, H. Bernstein. We place a detector 240 mm along the Z axis from the goniometer, as in Example 2, above, but in this example, the image plate is scanned in a spiral pattern outside edge in. The axis for positioning the detector in the Y-direction depends on the detector Z-axis. We call this axis, DETECTOR_Y. The axis for positioning the detector in the X-direction depends on the detector Y-axis (and therefore on the detector Z-axis). We call this axis DETECTOR_X. This detector may be rotated around the Y-axis. This rotation axis depends on the three translation axes. We call it DETECTOR_PITCH. We define a coordinate system on the face of the detector in terms of a coupled rotation axis and radial scan axis to form a spiral scan. Let us call rotation axis ELEMENT_ROT, and the radial axis ELEMENT_RAD. We assume 150 um radial pitch and 75 um 'constant velocity' angular pitch. We index first on the rotation axis and make the radial axis dependent on it. The two axes are coupled to form an axis set ELEMENT_SPIRAL. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_ROT translation detector DETECTOR_PITCH 0 0 1 0 0 0 ELEMENT_RAD translation detector ELEMENT_ROT 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.angle _array_structure_list_axis.displacement _array_structure_list_axis.angular_pitch _array_structure_list_axis.radial_pitch ELEMENT_SPIRAL ELEMENT_ROT 0 . 0.075 . ELEMENT_SPIRAL ELEMENT_RAD . 172.5 . -0.150 # category ARRAY_ELEMENT_SIZE # the actual pixels are 0.075 by 0.150 mm # We give the coarser dimension here. loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_scan.id _item_description.description ; The value of '_diffrn_scan.id' uniquely identifies each scan. The identifier is used to tie together all the information about the scan. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_scan.id' diffrn_scan yes '_diffrn_scan_axis.scan_id' diffrn_scan_axis yes '_diffrn_scan_frame.scan_id' diffrn_scan_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_scan_axis.scan_id' '_diffrn_scan.id' '_diffrn_scan_frame.scan_id' '_diffrn_scan.id' save_ save__diffrn_scan.date_end _item_description.description ; The date and time of the end of the scan. Note that this may be an estimate generated during the scan, before the precise time of the end of the scan is known. ; _item.name '_diffrn_scan.date_end' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.date_start _item_description.description ; The date and time of the start of the scan. ; _item.name '_diffrn_scan.date_start' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.integration_time _item_description.description ; Approximate average time in seconds to integrate each step of the scan. The precise time for integration of each particular step must be provided in '_diffrn_scan_frame.integration_time', even if all steps have the same integration time. ; _item.name '_diffrn_scan.integration_time' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan.frame_id_start _item_description.description ; The value of this data item is the identifier of the first frame in the scan. This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_start' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frame_id_end _item_description.description ; The value of this data item is the identifier of the last frame in the scan. This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_end' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frames _item_description.description ; The value of this data item is the number of frames in the scan. ; _item.name '_diffrn_scan.frames' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 1 1 1 save_ #################### # DIFFRN_SCAN_AXIS # #################### save_DIFFRN_SCAN_AXIS _category.description ; Data items in the DIFFRN_SCAN_AXIS category describe the settings of axes for particular scans. Unspecified axes are assumed to be at their zero points. ; _category.id diffrn_scan_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_axis.scan_id' '_diffrn_scan_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_axis.scan_id _item_description.description ; The value of this data item is the identifier of the scan for which axis settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan.id'. This item is a pointer to '_diffrn_scan.id' in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_axis.scan_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the scan for which settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan.id'. This item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_diffrn_scan_axis.axis_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.angle_start _item_description.description ; The starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_range _item_description.description ; The range from the starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_increment _item_description.description ; The increment for each step for the specified axis in degrees. In general, this will agree with '_diffrn_scan_frame_axis.angle_increment'. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.angle_increment' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.angle_increment' (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_rstrt_incr _item_description.description ; The increment after each step for the specified axis in degrees. In general, this will agree with '_diffrn_scan_frame_axis.angle_rstrt_incr'. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' and '_diffrn_scan_frame_axis.angle_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame, and should equal '_diffrn_scan_frame_axis.angle' for that next frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.angle_rstrt_incr' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.angle_rstrt_incr' (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.displacement_start _item_description.description ; The starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_range _item_description.description ; The range from the starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_increment _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with '_diffrn_scan_frame_axis.displacement_increment'. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.displacement_increment' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.displacement_increment' (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_rstrt_incr _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with '_diffrn_scan_frame_axis.displacement_rstrt_incr'. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' and '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame, and should equal '_diffrn_scan_frame_axis.displacement' for that next frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.displacement_rstrt_incr' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.displacement_rstrt_incr' (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ ##################### # DIFFRN_SCAN_FRAME # ##################### save_DIFFRN_SCAN_FRAME _category.description ; Data items in the DIFFRN_SCAN_FRAME category describe the relationship of particular frames to scans. ; _category.id diffrn_scan_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame.scan_id' '_diffrn_scan_frame.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame.date _item_description.description ; The date and time of the start of the frame being scanned. ; _item.name '_diffrn_scan_frame.date' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan_frame.frame_id _item_description.description ; The value of this data item is the identifier of the frame being examined. This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame.frame_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame.frame_number _item_description.description ; The value of this data item is the number of the frame within the scan, starting with 1. It is not necessarily the same as the value of '_diffrn_scan_frame.frame_id', but may be. ; _item.name '_diffrn_scan_frame.frame_number' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 0 0 0 save_ save__diffrn_scan_frame.integration_time _item_description.description ; The time in seconds to integrate this step of the scan. This should be the precise time of integration of each particular frame. The value of this data item should be given explicitly for each frame and not inferred from the value of '_diffrn_scan.integration_time'. ; _item.name '_diffrn_scan_frame.integration_time' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame.scan_id _item_description.description ; The value of '_diffrn_scan_frame.scan_id' identifies the scan containing this frame. This item is a pointer to '_diffrn_scan.id' in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_frame.scan_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ ########################## # DIFFRN_SCAN_FRAME_AXIS # ########################## save_DIFFRN_SCAN_FRAME_AXIS _category.description ; Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the settings of axes for particular frames. Unspecified axes are assumed to be at their zero points. If, for any given frame, non-zero values apply for any of the data items in this category, those values should be given explicitly in this category and not simply inferred from values in DIFFRN_SCAN_AXIS. ; _category.id diffrn_scan_frame_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame_axis.frame_id' '_diffrn_scan_frame_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the frame for which settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan_frame.frame_id'. This item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_diffrn_scan_frame_axis.axis_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_axis.angle _item_description.description ; The setting of the specified axis in degrees for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.angle' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_increment _item_description.description ; The increment for this frame for angular setting of the specified axis in degrees. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.angle_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_rstrt_incr _item_description.description ; The increment after this frame for angular setting of the specified axis in degrees. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' and '_diffrn_scan_frame_axis.angle_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame, and should equal '_diffrn_scan_frame_axis.angle' for that next frame. ; _item.name '_diffrn_scan_frame_axis.angle_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.displacement' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_increment _item_description.description ; The increment for this frame for displacement setting of the specified axis in millimetres. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.displacement_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_rstrt_incr _item_description.description ; The increment for this frame for displacement setting of the specified axis in millimetres. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' and '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame, and should equal '_diffrn_scan_frame_axis.displacement' for that next frame. ; _item.name '_diffrn_scan_frame_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.frame_id _item_description.description ; The value of this data item is the identifier of the frame for which axis settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan_frame.frame_id'. This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame_axis.frame_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ ######################## DEPRECATED DATA ITEMS ######################## save__diffrn_detector_axis.id _item_description.description ; This data item is a pointer to '_diffrn_detector.id' in the DIFFRN_DETECTOR category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_detector_axis.id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.id _item_description.description ; This data item is a pointer to '_diffrn_measurement.id' in the DIFFRN_MEASUREMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_measurement_axis.id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ ######################### DEPRECATED CATEGORY ######################### ##################### # DIFFRN_FRAME_DATA # ##################### save_DIFFRN_FRAME_DATA _category.description ; Data items in the DIFFRN_FRAME_DATA category record the details about each frame of data. The items in this category are now in the DIFFRN_DATA_FRAME category. The items in the DIFFRN_FRAME_DATA category are now deprecated. The items from this category are provided as aliases in the 1.0.0 dictionary, but should not be used for new work. The items from the old category are provided in this dictionary for completeness, but should not be used or cited. To avoid confusion, the example has been removed, and the redundant parent child-links to other categories removed. ; _category.id diffrn_frame_data _category.mandatory_code no loop_ _category_key.name '_diffrn_frame_data.id' '_diffrn_frame_data.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; THE DIFFRN_FRAME_DATA category is deprecated and should not be used. ; ; # EXAMPLE REMOVED # ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_frame_data.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.array_id' _item.category_id diffrn_frame_data _item.mandatory_code yes _item_type.code code save_ save__diffrn_frame_data.binary_id _item_description.description ; This item is a pointer to '_array_data.binary_id' in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.binary_id' _item.category_id diffrn_frame_data _item.mandatory_code implicit _item_type.code int save_ save__diffrn_frame_data.detector_element_id _item_description.description ; This item is a pointer to '_diffrn_detector_element.id' in the DIFFRN_DETECTOR_ELEMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.detector_element_id' _item.category_id diffrn_frame_data _item.mandatory_code yes _item_type.code code save_ save__diffrn_frame_data.id _item_description.description ; The value of '_diffrn_frame_data.id' must uniquely identify each complete frame of data. DEPRECATED -- DO NOT USE ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_frame_data.id' diffrn_frame_data yes _item_type.code code save_ ################ END DEPRECATED SECTION ########### #################### ## ITEM_TYPE_LIST ## #################### # # # The regular expressions defined here are not compliant # with the POSIX 1003.2 standard as they include the # '\n' and '\t' special characters. These regular expressions # have been tested using version 0.12 of Richard Stallman's # GNU regular expression library in POSIX mode. # In order to allow presentation of a regular expression # in a text field concatenate any line ending in a backslash # with the following line, after discarding the backslash. # # A formal definition of the '\n' and '\t' special characters # is most properly done in the DDL, but for completeness, please # note that '\n' is the line termination character ('newline') # and '\t' is the horizontal tab character. There is a formal # ambiguity in the use of '\n' for line termination, in that # the intention is that the equivalent machine/OS-dependent line # termination character sequence should be accepted as a match, e.g. # # '\r' (control-M) under MacOS # '\n' (control-J) under Unix # '\r\n' (control-M control-J) under DOS and MS Windows # loop_ _item_type_list.code _item_type_list.primitive_code _item_type_list.construct _item_type_list.detail code char '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words ... ; ucode uchar '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words (case insensitive) ; line char '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types / multi-word items ... ; uline uchar '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types / multi-word items (case insensitive) ; text char '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; text item types / multi-line text ... ; binary char ;\n--CIF-BINARY-FORMAT-SECTION--\n\ [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\ \n--CIF-BINARY-FORMAT-SECTION---- ; ; binary items are presented as MIME-like ascii-encoded sections in an imgCIF. In a CBF, raw octet streams are used to convey the same information. ; int numb '-?[0-9]+' ; int item types are the subset of numbers that are the negative or positive integers. ; float numb '-?(([0-9]+)|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?' ; float item types are the subset of numbers that are the floating numbers. ; any char '.*' ; A catch all for items that may take any form... ; yyyy-mm-dd char ;\ [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9][0-9]\ (T[0-2][0-9]:[0-5][0-9]:[0-5][0-9](.[0-9]+)([+-][0-5][0-9]:[0-5][0-9])) ; ; Standard format for CIF date and time strings (see http://www.iucr.org/iucr-top/cif/spec/datetime.html), consisting of a yyyy-mm-dd date optionally followed by the character "T" followed by a 24-hour clock time, optionally followed by a signed time-zone offset. The IUCr standard has been extended to allow for an optional decimal fraction on the seconds of time. Time is local time if no time-zone offset is given. ; ##################### ## ITEM_UNITS_LIST ## ##################### loop_ _item_units_list.code _item_units_list.detail # 'metres' 'metres' 'centimetres' 'centimetres (metres * 10^( -2)^)' 'millimetres' 'millimetres (metres * 10^( -3)^)' 'nanometres' 'nanometres (metres * 10^( -9)^)' 'angstroms' '\%Angstroms (metres * 10^(-10)^)' 'picometres' 'picometres (metres * 10^(-12)^)' 'femtometres' 'femtometres (metres * 10^(-15)^)' # 'reciprocal_metres' 'reciprocal metres (metres^(-1)^)' 'reciprocal_centimetres' 'reciprocal centimetres ((metres * 10^( -2)^)^(-1)^)' 'reciprocal_millimetres' 'reciprocal millimetres ((metres * 10^( -3)^)^(-1)^)' 'reciprocal_nanometres' 'reciprocal nanometres ((metres * 10^( -9)^)^(-1)^)' 'reciprocal_angstroms' 'reciprocal \%Angstroms ((metres * 10^(-10)^)^(-1)^)' 'reciprocal_picometres' 'reciprocal picometres ((metres * 10^(-12)^)^(-1)^)' # 'nanometres_squared' 'nanometres squared (metres * 10^( -9)^)^2^' 'angstroms_squared' '\%Angstroms squared (metres * 10^(-10)^)^2^' '8pi2_angstroms_squared' '8\p^2^ * \%Angstroms squared (metres * 10^(-10)^)^2^' 'picometres_squared' 'picometres squared (metres * 10^(-12)^)^2^' # 'nanometres_cubed' 'nanometres cubed (metres * 10^( -9)^)^3^' 'angstroms_cubed' '\%Angstroms cubed (metres * 10^(-10)^)^3^' 'picometres_cubed' 'picometres cubed (metres * 10^(-12)^)^3^' # 'kilopascals' 'kilopascals' 'gigapascals' 'gigapascals' # 'hours' 'hours' 'minutes' 'minutes' 'seconds' 'seconds' 'microseconds' 'microseconds' # 'degrees' 'degrees (of arc)' 'degrees_squared' 'degrees (of arc) squared' # 'degrees_per_minute' 'degrees (of arc) per minute' # 'celsius' 'degrees (of temperature) Celsius' 'kelvins' 'degrees (of temperature) Kelvin' # 'counts' 'counts' 'counts_per_photon' 'counts per photon' # 'electrons' 'electrons' # 'electrons_squared' 'electrons squared' # 'electrons_per_nanometres_cubed' ; electrons per nanometres cubed (electrons/(metres * 10^( -9)^)^(-3)^) ; 'electrons_per_angstroms_cubed' ; electrons per \%Angstroms cubed (electrons/(metres * 10^(-10)^)^(-3)^) ; 'electrons_per_picometres_cubed' ; electrons per picometres cubed (electrons/(metres * 10^(-12)^)^(-3)^) ; 'kilowatts' 'kilowatts' 'milliamperes' 'milliamperes' 'kilovolts' 'kilovolts' # 'arbitrary' ; arbitrary system of units. ; # loop_ _item_units_conversion.from_code _item_units_conversion.to_code _item_units_conversion.operator _item_units_conversion.factor ### 'metres' 'centimetres' '*' 1.0E+02 'metres' 'millimetres' '*' 1.0E+03 'metres' 'nanometres' '*' 1.0E+09 'metres' 'angstroms' '*' 1.0E+10 'metres' 'picometres' '*' 1.0E+12 'metres' 'femtometres' '*' 1.0E+15 # 'centimetres' 'metres' '*' 1.0E-02 'centimetres' 'millimetres' '*' 1.0E+01 'centimetres' 'nanometres' '*' 1.0E+07 'centimetres' 'angstroms' '*' 1.0E+08 'centimetres' 'picometres' '*' 1.0E+10 'centimetres' 'femtometres' '*' 1.0E+13 # 'millimetres' 'metres' '*' 1.0E-03 'millimetres' 'centimetres' '*' 1.0E-01 'millimetres' 'nanometres' '*' 1.0E+06 'millimetres' 'angstroms' '*' 1.0E+07 'millimetres' 'picometres' '*' 1.0E+09 'millimetres' 'femtometres' '*' 1.0E+12 # 'nanometres' 'metres' '*' 1.0E-09 'nanometres' 'centimetres' '*' 1.0E-07 'nanometres' 'millimetres' '*' 1.0E-06 'nanometres' 'angstroms' '*' 1.0E+01 'nanometres' 'picometres' '*' 1.0E+03 'nanometres' 'femtometres' '*' 1.0E+06 # 'angstroms' 'metres' '*' 1.0E-10 'angstroms' 'centimetres' '*' 1.0E-08 'angstroms' 'millimetres' '*' 1.0E-07 'angstroms' 'nanometres' '*' 1.0E-01 'angstroms' 'picometres' '*' 1.0E+02 'angstroms' 'femtometres' '*' 1.0E+05 # 'picometres' 'metres' '*' 1.0E-12 'picometres' 'centimetres' '*' 1.0E-10 'picometres' 'millimetres' '*' 1.0E-09 'picometres' 'nanometres' '*' 1.0E-03 'picometres' 'angstroms' '*' 1.0E-02 'picometres' 'femtometres' '*' 1.0E+03 # 'femtometres' 'metres' '*' 1.0E-15 'femtometres' 'centimetres' '*' 1.0E-13 'femtometres' 'millimetres' '*' 1.0E-12 'femtometres' 'nanometres' '*' 1.0E-06 'femtometres' 'angstroms' '*' 1.0E-05 'femtometres' 'picometres' '*' 1.0E-03 ### 'reciprocal_centimetres' 'reciprocal_metres' '*' 1.0E+02 'reciprocal_centimetres' 'reciprocal_millimetres' '*' 1.0E-01 'reciprocal_centimetres' 'reciprocal_nanometres' '*' 1.0E-07 'reciprocal_centimetres' 'reciprocal_angstroms' '*' 1.0E-08 'reciprocal_centimetres' 'reciprocal_picometres' '*' 1.0E-10 # 'reciprocal_millimetres' 'reciprocal_metres' '*' 1.0E+03 'reciprocal_millimetres' 'reciprocal_centimetres' '*' 1.0E+01 'reciprocal_millimetres' 'reciprocal_nanometres' '*' 1.0E-06 'reciprocal_millimetres' 'reciprocal_angstroms' '*' 1.0E-07 'reciprocal_millimetres' 'reciprocal_picometres' '*' 1.0E-09 # 'reciprocal_nanometres' 'reciprocal_metres' '*' 1.0E+09 'reciprocal_nanometres' 'reciprocal_centimetres' '*' 1.0E+07 'reciprocal_nanometres' 'reciprocal_millimetres' '*' 1.0E+06 'reciprocal_nanometres' 'reciprocal_angstroms' '*' 1.0E-01 'reciprocal_nanometres' 'reciprocal_picometres' '*' 1.0E-03 # 'reciprocal_angstroms' 'reciprocal_metres' '*' 1.0E+10 'reciprocal_angstroms' 'reciprocal_centimetres' '*' 1.0E+08 'reciprocal_angstroms' 'reciprocal_millimetres' '*' 1.0E+07 'reciprocal_angstroms' 'reciprocal_nanometres' '*' 1.0E+01 'reciprocal_angstroms' 'reciprocal_picometres' '*' 1.0E-02 # 'reciprocal_picometres' 'reciprocal_metres' '*' 1.0E+12 'reciprocal_picometres' 'reciprocal_centimetres' '*' 1.0E+10 'reciprocal_picometres' 'reciprocal_millimetres' '*' 1.0E+09 'reciprocal_picometres' 'reciprocal_nanometres' '*' 1.0E+03 'reciprocal_picometres' 'reciprocal_angstroms' '*' 1.0E+01 ### 'nanometres_squared' 'angstroms_squared' '*' 1.0E+02 'nanometres_squared' 'picometres_squared' '*' 1.0E+06 # 'angstroms_squared' 'nanometres_squared' '*' 1.0E-02 'angstroms_squared' 'picometres_squared' '*' 1.0E+04 'angstroms_squared' '8pi2_angstroms_squared' '*' 78.9568 # 'picometres_squared' 'nanometres_squared' '*' 1.0E-06 'picometres_squared' 'angstroms_squared' '*' 1.0E-04 ### 'nanometres_cubed' 'angstroms_cubed' '*' 1.0E+03 'nanometres_cubed' 'picometres_cubed' '*' 1.0E+09 # 'angstroms_cubed' 'nanometres_cubed' '*' 1.0E-03 'angstroms_cubed' 'picometres_cubed' '*' 1.0E+06 # 'picometres_cubed' 'nanometres_cubed' '*' 1.0E-09 'picometres_cubed' 'angstroms_cubed' '*' 1.0E-06 ### 'kilopascals' 'gigapascals' '*' 1.0E-06 'gigapascals' 'kilopascals' '*' 1.0E+06 ### 'hours' 'minutes' '*' 6.0E+01 'hours' 'seconds' '*' 3.6E+03 'hours' 'microseconds' '*' 3.6E+09 # 'minutes' 'hours' '/' 6.0E+01 'minutes' 'seconds' '*' 6.0E+01 'minutes' 'microseconds' '*' 6.0E+07 # 'seconds' 'hours' '/' 3.6E+03 'seconds' 'minutes' '/' 6.0E+01 'seconds' 'microseconds' '*' 1.0E+06 # 'microseconds' 'hours' '/' 3.6E+09 'microseconds' 'minutes' '/' 6.0E+07 'microseconds' 'seconds' '/' 1.0E+06 ### 'celsius' 'kelvins' '-' 273.0 'kelvins' 'celsius' '+' 273.0 ### 'electrons_per_nanometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E+03 'electrons_per_nanometres_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+09 # 'electrons_per_angstroms_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-03 'electrons_per_angstroms_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+06 # 'electrons_per_picometres_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-09 'electrons_per_picometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E-06 ### ######################## ## DICTIONARY_HISTORY ## ######################## loop_ _dictionary_history.version _dictionary_history.update _dictionary_history.revision 1.3.2 2005-06-22 ; Changes as per Nicola Ashcroft. + Fix '_item_units.code code' to be '_item_type.code code' in '_array_structure_list_axis.axis_id' and in '_array_structure_list_axis.axis_set_id' Also fix typos in exponents and long lines in units list (HJB) ; 1.3.1 2003-08-13 ; Changes as per Frances C. Bernstein. + Identify initials. + Adopt British spelling for centre in text. + Set \p and \%Angstrom and powers. + Clean up commas and unclear wordings. + Clean up tenses in history. Changes as per Gotzon Madariaga. + Fix the ARRAY_DATA example to align '_array_data.binary_id' and X-Binary-Id. + Add a range to '_array_intensities.gain_esd'. + In the example of DIFFRN_DETECTOR_ELEMENT, '_diffrn_detector_element.id' and '_diffrn_detector_element.detector_id' interchanged. + Fix typos for direction, detector and axes. + Clarify description of polarisation. + Clarify axes in '_diffrn_detector_element.center[1]' '_diffrn_detector_element.center[2]'. + Add local item types for items that are pointers. (HJB) ; 1.3.0 2003-07-24 ; Changes as per Brian McMahon. + Consistently quote tags embedded in text. + Clean up introductory comments. + Adjust line lengths to fit in 80 character window. + Fix several descriptions in AXIS category which referred to '_axis.type' instead of the current item. + Fix erroneous use of deprecated item '_diffrn_detector_axis.id' in examples for DIFFRN_SCAN_AXIS. + Add deprecated items '_diffrn_detector_axis.id' and '_diffrn_measurement_axis.id'. (HJB) ; 1.2.4 2003-07-14 ; Changes as per I. David Brown. + Enhance descriptions in DIFFRN_SCAN_AXIS to make them less dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS. + Provide a copy of the deprecated DIFFRN_FRAME_DATA category for completeness. (HJB) ; 1.2.3 2003-07-03 ; Cleanup to conform to ITVG. + Correct sign error in ..._cubed units. + Correct '_diffrn_radiation.polarisn_norm' range. (HJB) ; 1.2.2 2003-03-10 ; Correction of typos in various DIFFRN_SCAN_AXIS descriptions. (HJB) ; 1.2.1 2003-02-22 ; Correction of ATOM_ for ARRAY_ typos in various descriptions. (HJB) ; 1.2 2003-02-07 ; Corrections to encodings (remove extraneous hyphens) remove extraneous underscore in '_array_structure.encoding_type' enumeration. Correct typos in items units list. (HJB) ; 1.1.3 2001-04-19 ; Another typo corrections by Wilfred Li, and cleanup by HJB. ; 1.1.2 2001-03-06 ; Several typo corrections by Wilfred Li. ; 1.1.1 2001-02-16 ; Several typo corrections by JW. ; 1.1 2001-02-06 ; Draft resulting from discussions on header for use at NSLS. (HJB) + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME. + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'. + Add '_diffrn_measurement_axis.measurement_device' and change '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'. + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source', '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm', '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end', '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr', '_diffrn_scan_axis.displacement_rstrt_incr', '_diffrn_scan_frame_axis.angle_increment', '_diffrn_scan_frame_axis.angle_rstrt_incr', '_diffrn_scan_frame_axis.displacement', '_diffrn_scan_frame_axis.displacement_increment',and '_diffrn_scan_frame_axis.displacement_rstrt_incr'. + Add '_diffrn_measurement.device' to category key. + Update yyyy-mm-dd to allow optional time with fractional seconds for time stamps. + Fix typos caught by RS. + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to allow for coupled axes, as in spiral scans. + Add examples for fairly complete headers thanks to R. Sweet and P. Ellis. ; 1.0 2000-12-21 ; Release version - few typos and tidying up. (BM & HJB) + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end of dictionary. + Alphabetize dictionary. ; 0.7.1 2000-09-29 ; Cleanup fixes. (JW) + Correct spelling of diffrn_measurement_axis in '_axis.id' + Correct ordering of uses of '_item.mandatory_code' and '_item_default.value'. ; 0.7.0 2000-09-09 ; Respond to comments by I. David Brown. (HJB) + Add further comments on '\n' and '\t'. + Update ITEM_UNITS_LIST by taking section from mmCIF dictionary and adding metres. Change 'meter' to 'metre' throughout. + Add missing enumerations to '_array_structure.compression_type' and make 'none' the default. + Remove parent-child relationship between '_array_structure_list.index' and '_array_structure_list.precedence'. + Improve alphabetization. + Fix '_array_intensities_gain.esd' related function. + Improve comments in AXIS. + Fix DIFFRN_FRAME_DATA example. + Remove erroneous DIFFRN_MEASUREMENT example. + Add '_diffrn_measurement_axis.id' to the category key. ; 0.6.0 1999-01-14 ; Remove redundant information for ENC_NONE data. (HJB) + After the D5 remove binary section identifier, size and compression type. + Add Control-L to header. ; 0.5.1 1999-01-03 ; Cleanup of typos and syntax errors. (HJB) + Cleanup example details for DIFFRN_SCAN category. + Add missing quote marks for '_diffrn_scan.id' definition. ; 0.5 1999-01-01 ; Modifications for axis definitions and reduction of binary header. (HJB) + Restore '_diffrn_detector.diffrn_id' to DIFFRN_DETECTOR KEY. + Add AXIS category. + Bring in complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories from cif_mm.dic for clarity. + Change '_array_structure.encoding_type' from type code to uline and added X-Binary-Element-Type to MIME header. + Add detector beam centre '_diffrn_detector_element.center[1]' and '_diffrn_detector_element.center[2]'. + Correct item name of '_diffrn_refln.frame_id'. + Replace reference to '_array_intensities.undefined' by '_array_intensities.undefined_value'. + Replace references to '_array_intensity.scaling' with '_array_intensities.scaling'. + Add DIFFRN_SCAN... categories. ; 0.4 1998-08-11 ; Modifications to the 0.3 imgCIF draft. (HJB) + Reflow comment lines over 80 characters and corrected typos. + Update examples and descriptions of MIME encoded data. + Change name to cbfext98.dic. ; 0.3 1998-07-04 ; Modifications for imgCIF. (HJB) + Add binary type, which is a text field containing a variant on MIME encoded data. + Change type of '_array_data.data' to binary and specify internal structure of raw binary data. + Add '_array_data.binary_id', and make '_diffrn_frame_data.binary_id' and '_array_intensities.binary_id' into pointers to this item. ; 0.2 1997-12-02 ; Modifications to the CBF draft. (JW) + Add category hierarchy for describing frame data developed from discussions at the BNL imgCIF Workshop Oct 1997. The following changes are made in implementing the workshop draft. Category DIFFRN_ARRAY_DATA is renamed to DIFFRN_FRAME_DATA. Category DIFFRN_FRAME_TYPE is renamed to DIFFRN_DETECTOR_ELEMENT. The parent item for '_diffrn_frame_data.array_id' is changed from '_array_structure_list.array_id' to '_array_structure.id'. Item '_diffrn_detector.array_id' is deleted. + Add data item '_diffrn_frame_data.binary_id' to identify data groups within a binary section. The formal identification of the binary section is still fuzzy. ; 0.1 1997-01-24 ; First draft of this dictionary in DDL 2.1 compliant format by John Westbrook (JW). This version is adapted from the Crystallographic Binary File (CBF) Format Draft Proposal provided by Andy Hammersley (AH). Modifications to the CBF draft. (JW) + In this version the array description has been cast in the categories ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. These categories have been generalized to describe array data of arbitrary dimension. + Array data in this description are contained in the category ARRAY_DATA. This departs from the CBF notion of data existing in some special comment. In this description, data is handled as an ordinary data item encapsulated in a character data type. Although data this manner deviates from CIF conventions, it does not violate any DDL 2.1 rules. DDL 2.1 regular expressions can be used to define the binary representation which will permit some level of data validation. In this version, the placeholder type code "any" has been used. This translates to a regular expression which will match any pattern. It should be noted that DDL 2.1 already supports array data objects although these have not been used in the current mmCIF dictionary. It may be possible to use the DDL 2.1 ITEM_STRUCTURE and ITEM_STRUCTURE_LIST categories to provide the information that is carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. By moving the array structure to the DDL level it would be possible to define an array type as well as a regular expression defining the data format. + Multiple array sections can be properly handled within a single datablock. ; #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof ./CBFlib-0.9.2.2/doc/Idiffrn_measurement.device_details.html0000644000076500007650000000566611603702115022177 0ustar yayayaya (IUCr) CIF Definition save__diffrn_measurement.device_details

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_measurement.device_details

    Name:
    '_diffrn_measurement.device_details'

    Definition:

            A description of special aspects of the device used to
                   measure the diffraction intensities.
    
    
    Example:

    ;                                 commercial goniometer modified locally to
                                      allow for 90\% \t arc
    ;

    Type: text

    Mandatory item: no

    Alias:
    _diffrn_measurement_device_details (cif_core.dic version 2.0.1)

    Category: diffrn_measurement

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/cif_img_1.4_4Jul06_draft.html0000644000076500007650000074260611603702115017453 0ustar yayayaya cif_img.dic v1.4_DRAFT

    # [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib] #

    # imgCIF/CBF #

    # Extensions Dictionary #

    ##############################################################################
    #                                                                            #
    #                       Image CIF Dictionary (imgCIF)                        #
    #             and Crystallographic Binary File Dictionary (CBF)              #
    #            Extending the Macromolecular CIF Dictionary (mmCIF)             #
    #                                                                            #
    #                             Version 1.4_DRAFT                              #
    #                              of 2006-07-04                                 #
    #    ###################################################################     #
    #    # *** WARNING *** THIS IS A DRAFT FOR DISCUSSSION *** WARNING *** #     #
    #    #                 SUBJECT TO CHANGE WITHOUT NOTICE                #     #
    #    #     VERSIONS WILL BE POSTED AS cif_img_1.4_DDMMMYY_draft.html   #     #
    #    #       SEND COMMENTS TO imgcif-l@iucr.org CITING THE VERSION     #     #
    #    ###################################################################     #
    #                  This draft edited by H. J. Bernstein                      #
    #                                                                            #
    #     by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook    #
    #                                                                            #
    # This dictionary was adapted from format discussed at the imgCIF Workshop,  #
    # held at BNL Oct 1997 and the Crystallographic Binary File Format Draft     #
    # Proposal by Andrew Hammersley.  The first DDL 2.1 Version was created by   #
    # John Westbrook.  This version was drafted by Herbert J. Bernstein and      #
    # incorporates comments by I. David Brown, John Westbrook, Brian McMahon,    #
    # Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li, Gotzon Madariaga,         #
    # Frances C. Bernstein, Chris Nielsen, Nicola Ashcroft and others.           #
    ##############################################################################
    
    data_cif_img.dic
    
        _dictionary.title           cif_img.dic
        _dictionary.version         1.4_DRAFT
        _dictionary.datablock_id    cif_img.dic
    
    ##############################################################################
    #    CONTENTS
    #
    #        CATEGORY_GROUP_LIST
    #        SUB_CATEGORY
    #
    #        category  ARRAY_DATA
    #
    #                  _array_data.array_id
    #                  _array_data.binary_id
    #                  _array_data.data
    #
    #        category  ARRAY_ELEMENT_SIZE
    #
    #                  _array_element_size.array_id
    #                  _array_element_size.index
    #                  _array_element_size.size
    #
    #        category  ARRAY_INTENSITIES
    #
    #                  _array_intensities.array_id
    #                  _array_intensities.binary_id
    #                  _array_intensities.gain
    #                  _array_intensities.gain_esd
    #                  _array_intensities.linearity
    #                  _array_intensities.offset
    #                  _array_intensities.scaling
    #                  _array_intensities.overload
    #                  _array_intensities.undefined_value
    #                  _array_intensities.pixel_fast_bin_size
    #                  _array_intensities.pixel_slow_bin_size
    #                  _array_intensities.pixel_binning_method
    #
    #        category  ARRAY_STRUCTURE
    #
    #                  _array_structure.byte_order
    #                  _array_structure.compression_type
    #                  _array_structure.encoding_type
    #                  _array_structure.id
    #
    #        category  ARRAY_STRUCTURE_LIST
    #
    #                  _array_structure_list.axis_set_id
    #                  _array_structure_list.array_id
    #                  _array_structure_list.dimension
    #                  _array_structure_list.direction
    #                  _array_structure_list.index
    #                  _array_structure_list.precedence
    #
    #        category  ARRAY_STRUCTURE_LIST_AXIS
    #
    #                  _array_structure_list_axis.axis_id
    #                  _array_structure_list_axis.axis_set_id
    #                  _array_structure_list_axis.angle
    #                  _array_structure_list_axis.angle_increment
    #                  _array_structure_list_axis.displacement
    #                  _array_structure_list_axis.displacement_increment
    #                  _array_structure_list_axis.angular_pitch
    #                  _array_structure_list_axis.radial_pitch
    #
    #        category  AXIS
    #
    #                  _axis.depends_on
    #                  _axis.equipment
    #                  _axis.id
    #                  _axis.offset[1]
    #                  _axis.offset[2]
    #                  _axis.offset[3]
    #                  _axis.type
    #                  _axis.vector[1]
    #                  _axis.vector[2]
    #                  _axis.vector[3]
    #
    #        category  DIFFRN_DATA_FRAME
    #
    #                  _diffrn_data_frame.array_id
    #                  _diffrn_data_frame.binary_id
    #                  _diffrn_data_frame.detector_element_id
    #                  _diffrn_data_frame.id
    #                  _diffrn_data_frame.details
    #
    #        category  DIFFRN_DETECTOR
    #
    #                  _diffrn_detector.details
    #                  _diffrn_detector.detector
    #                  _diffrn_detector.diffrn_id
    #                  _diffrn_detector.dtime
    #                  _diffrn_detector.id
    #                  _diffrn_detector.number_of_axes
    #                  _diffrn_detector.type
    #
    #        category  DIFFRN_DETECTOR_AXIS
    #
    #                  _diffrn_detector_axis.axis_id
    #                  _diffrn_detector_axis.detector_id
    #
    #        category  DIFFRN_DETECTOR_ELEMENT
    #
    #                  _diffrn_detector_element.center[1]
    #                  _diffrn_detector_element.center[2]
    #                  _diffrn_detector_element.id
    #                  _diffrn_detector_element.detector_id
    #
    #        category  DIFFRN_MEASUREMENT
    #
    #                  _diffrn_measurement.diffrn_id
    #                  _diffrn_measurement.details
    #                  _diffrn_measurement.device
    #                  _diffrn_measurement.device_details
    #                  _diffrn_measurement.device_type
    #                  _diffrn_measurement.id
    #                  _diffrn_measurement.method
    #                  _diffrn_measurement.number_of_axes
    #                  _diffrn_measurement.specimen_support
    #
    #        category  DIFFRN_MEASUREMENT_AXIS
    #
    #                  _diffrn_measurement_axis.axis_id
    #                  _diffrn_measurement_axis.measurement_device
    #                  _diffrn_measurement_axis.measurement_id
    #
    #        category  DIFFRN_RADIATION
    #
    #                  _diffrn_radiation.collimation
    #                  _diffrn_radiation.diffrn_id
    #                  _diffrn_radiation.div_x_source
    #                  _diffrn_radiation.div_y_source
    #                  _diffrn_radiation.div_x_y_source
    #                  _diffrn_radiation.filter_edge'
    #                  _diffrn_radiation.inhomogeneity
    #                  _diffrn_radiation.monochromator
    #                  _diffrn_radiation.polarisn_norm
    #                  _diffrn_radiation.polarisn_ratio
    #                  _diffrn_radiation.polarizn_source_norm
    #                  _diffrn_radiation.polarizn_source_ratio
    #                  _diffrn_radiation.probe
    #                  _diffrn_radiation.type
    #                  _diffrn_radiation.xray_symbol
    #                  _diffrn_radiation.wavelength_id
    #
    #        category  DIFFRN_REFLN
    #
    #                  _diffrn_refln.frame_id
    #
    #        category  DIFFRN_SCAN
    #
    #                  _diffrn_scan.id
    #                  _diffrn_scan.date_end
    #                  _diffrn_scan.date_start
    #                  _diffrn_scan.integration_time
    #                  _diffrn_scan.frame_id_start
    #                  _diffrn_scan.frame_id_end
    #                  _diffrn_scan.frames
    #
    #        category  DIFFRN_SCAN_AXIS
    #
    #                  _diffrn_scan_axis.axis_id
    #                  _diffrn_scan_axis.angle_start
    #                  _diffrn_scan_axis.angle_range
    #                  _diffrn_scan_axis.angle_increment
    #                  _diffrn_scan_axis.angle_rstrt_incr
    #                  _diffrn_scan_axis.displacement_start
    #                  _diffrn_scan_axis.displacement_range
    #                  _diffrn_scan_axis.displacement_increment
    #                  _diffrn_scan_axis.displacement_rstrt_incr
    #                  _diffrn_scan_axis.scan_id
    #
    #        category  DIFFRN_SCAN_FRAME
    #
    #                  _diffrn_scan_frame.date
    #                  _diffrn_scan_frame.frame_id
    #                  _diffrn_scan_frame.frame_number
    #                  _diffrn_scan_frame.integration_time
    #                  _diffrn_scan_frame.scan_id
    #
    #        category  DIFFRN_SCAN_FRAME_AXIS
    #
    #                  _diffrn_scan_frame_axis.axis_id
    #                  _diffrn_scan_frame_axis.angle
    #                  _diffrn_scan_frame_axis.angle_increment
    #                  _diffrn_scan_frame_axis.angle_rstrt_incr
    #                  _diffrn_scan_frame_axis.displacement
    #                  _diffrn_scan_frame_axis.displacement_increment
    #                  _diffrn_scan_frame_axis.displacement_rstrt_incr
    #                  _diffrn_scan_frame_axis.frame_id
    #
    #       ***DEPRECATED*** data items
    #
    #                  _diffrn_detector_axis.id
    #                  _diffrn_measurement_axis.id
    #
    #       ***DEPRECATED*** category  DIFFRN_FRAME_DATA
    #
    #                  _diffrn_frame_data.array_id
    #                  _diffrn_frame_data.binary_id
    #                  _diffrn_frame_data.detector_element_id
    #                  _diffrn_frame_data.id
    #                  _diffrn_frame_data.details
    #
    #
    #        ITEM_TYPE_LIST
    #        ITEM_UNITS_LIST
    #        DICTIONARY_HISTORY
    #
    ##############################################################################
    
    
    #########################
    ## CATEGORY_GROUP_LIST ##
    #########################
    
         loop_
        _category_group_list.id
        _category_group_list.parent_id
        _category_group_list.description
                 'inclusive_group'   .
    ;             Categories that belong to the dictionary extension.
    ;
                 'array_data_group'
                 'inclusive_group'
    ;             Categories that describe array data.
    ;
                 'axis_group'
                 'inclusive_group'
    ;             Categories that describe axes.
    ;
                 'diffrn_group'
                 'inclusive_group'
    ;            Categories that describe details of the diffraction experiment.
    ;
    
    
    ##################
    ## SUB_CATEGORY ##
    ##################
    
         loop_
        _sub_category.id
        _sub_category.description
                  'matrix'
    ;              The collection of elements of a matrix.
    ;
                  'vector'
    ;              The collection of elements of a vector.
    ;
    
    
    
    
    ##############
    # ARRAY_DATA #
    ##############
    
    
    save_ARRAY_DATA
        _category.description
    ;    Data items in the ARRAY_DATA category are the containers for
         the array data items described in the category ARRAY_STRUCTURE.
    ;
        _category.id                   array_data
        _category.mandatory_code       no
         loop_
        _category_key.name             '_array_data.array_id'
                                       '_array_data.binary_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1 -
    
            This example shows two binary data blocks.  The first one
            was compressed by the CBF_CANONICAL compression algorithm and is
            presented as hexadecimal data.  The first character 'H' on the
            data lines means hexadecimal.  It could have been 'O' for octal
            or 'D' for decimal.  The second character on the line shows
            the number of bytes in each word (in this case '4'), which then
            requires eight hexadecimal digits per word.  The third character
            gives the order of octets within a word, in this case '<'
            for the ordering 4321 (i.e. 'big-endian').  Alternatively, the
            character '>' could have been used for the ordering 1234
            (i.e. 'little-endian').  The block has a 'message digest'
            to check the integrity of the data.
    
            The second block is similar, but uses CBF_PACKED compression
            and BASE64 encoding.  Note that the size and the digest are
            different.
    ;
    ;
    
            loop_
            _array_data.array_id
            _array_data.binary_id
            _array_data.data
            image_1 1
            ;
            --CIF-BINARY-FORMAT-SECTION--
            Content-Type: application/octet-stream;
                 conversions="x-CBF_CANONICAL"
            Content-Transfer-Encoding: X-BASE16
            X-Binary-Size: 3927126
            X-Binary-ID: 1
            Content-MD5: u2sTJEovAHkmkDjPi+gWsg==
    
            # Hexadecimal encoding, byte 0, byte order ...21
            #
            H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ...
            ....
            --CIF-BINARY-FORMAT-SECTION----
            ;
            image_2 2
            ;
            --CIF-BINARY-FORMAT-SECTION--
            Content-Type: application/octet-stream;
                 conversions="x-CBF-PACKED"
            Content-Transfer-Encoding: BASE64
            X-Binary-Size: 3745758
            X-Binary-ID: 2
            Content-MD5: 1zsJjWPfol2GYl2V+QSXrw==
    
            ELhQAAAAAAAA...
            ...
            --CIF-BINARY-FORMAT-SECTION----
            ;
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    save_
    
    
    save__array_data.array_id
        _item_description.description
    ;             This item is a pointer to _array_structure.id in the
                  ARRAY_STRUCTURE category.
    ;
        _item.name                  '_array_data.array_id'
        _item.category_id             array_data
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__array_data.binary_id
        _item_description.description
    ;             This item is an integer identifier which, along with
                  _array_data.array_id, should uniquely identify the
                  particular block of array data.
    
                  If _array_data.binary_id is not explicitly given,
                  it defaults to 1.
    
                  The value of _array_data.binary_id distinguishes
                  among multiple sets of data with the same array
                  structure.
    
                  If the MIME header of the data array specifies a
                  value for X-Binary-ID, the value of  _array_data.binary_id
                  should be equal to the value given for X-Binary-ID.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
                 '_array_data.binary_id'            array_data
                                                                    implicit
                 '_diffrn_data_frame.binary_id'     diffrn_data_frame
                                                                    implicit
                 '_array_intensities.binary_id'     array_intensities
                                                                    implicit
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_data_frame.binary_id'     '_array_data.binary_id'
                 '_array_intensities.binary_id'     '_array_data.binary_id'
    
        _item_default.value           1
        _item_type.code               int
         loop_
        _item_range.maximum
        _item_range.minimum
                                1  1
                                .  1
         save_
    
    
    save__array_data.data
        _item_description.description
    ;             The value of _array_data.data contains the array data
                  encapsulated in a STAR string.
    
                  The representation used is a variant on the
                  Multipurpose Internet Mail Extensions (MIME) specified
                  in RFC 2045-2049 by N. Freed et al.  The boundary
                  delimiter used in writing an imgCIF or CBF is
                  '\n--CIF-BINARY-FORMAT-SECTION--' (including the
                  required initial '\n--').
    
                  The Content-Type may be any of the discrete types permitted
                  in RFC 2045; 'application/octet-stream' is recommended.
                  If an octet stream was compressed, the compression should
                  be specified by the parameter 'conversions="x-CBF_PACKED"'
                  or the parameter 'conversions="x-CBF_CANONICAL"'.
    
                  The Content-Transfer-Encoding may be 'BASE64',
                  'Quoted-Printable', 'X-BASE8', 'X-BASE10',
                  'X-BASE16' or 'X-BASE32K', for an imgCIF or 'BINARY'
                  for a CBF.  The octal, decimal and hexadecimal transfer
                  encodings are provided for convenience in debugging and
                  are not recommended for archiving and data interchange.
    
                  In a CIF, one of the parameters 'charset=us-ascii',
                  'charset=utf-8' or 'charset=utf-16' may be used on the
                  Content-Transfer-Encoding to specify the character set
                  used for the external presentation of the encoded data.
                  If no charset parameter is given, the character set of
                  the enclosing CIF is assumed.  In any case, if a BOM
                  flag is detected (FE FF for big-endian UTF-16, FF FE for
                  little-endian UTF-16 or EF BB BF for UTF-8) is detected,
                  the indicated charset will be assumed until the end of the
                  encoded data or the detection of a different BOM.  The
                  charset of the Content-Transfer-Encoding is not the character
                  set of the encoded data, only the character set of the
                  presentation of the encoded data and should be respecified
                  for each distinct STAR string.
    
                  In an imgCIF file, the encoded binary data begins after
                  the empty line terminating the header.  In an imgCIF file,
                  the encoded binary data ends with the terminating boundary
                  delimiter '\n--CIF-BINARY-FORMAT-SECTION----'
                  in the currently effective charset or with the '\n; '
                  that terminates the STAR string.
    
                  In a CBF, the raw binary data begins after an empty line
                  terminating the header and after the sequence:
    
                  Octet   Hex   Decimal  Purpose
                    0     0C       12    (ctrl-L) Page break
                    1     1A       26    (ctrl-Z) Stop listings in MS-DOS
                    2     04       04    (Ctrl-D) Stop listings in UNIX
                    3     D5      213    Binary section begins
    
                  None of these octets are included in the calculation of
                  the message size or in the calculation of the
                  message digest.
    
                  The X-Binary-Size header specifies the size of the
                  equivalent binary data in octets.  If compression was
                  used, this size is the size after compression, including
                  any book-keeping fields.  An adjustment is made for
                  the deprecated binary formats in which eight bytes of binary
                  header are used for the compression type.  In this case,
                  the eight bytes used for the compression type are subtracted
                  from the size, so that the same size will be reported
                  if the compression type is supplied in the MIME header.
                  Use of the MIME header is the recommended way to
                  supply the compression type.  In general, no portion of
                  the  binary header is included in the calculation of the size.
    
                  The X-Binary-Element-Type header specifies the type of
                  binary data in the octets, using the same descriptive
                  phrases as in _array_structure.encoding_type.  The default
                  value is 'unsigned 32-bit integer'.
    
                  An MD5 message digest may, optionally, be used. The 'RSA Data
                  Security, Inc. MD5 Message-Digest Algorithm' should be used.
                  No portion of the header is included in the calculation of the
                  message digest.
    
                  If the Transfer Encoding is 'X-BASE8', 'X-BASE10' or
                  'X-BASE16', the data are presented as octal, decimal or
                  hexadecimal data organized into lines or words.  Each word
                  is created by composing octets of data in fixed groups of
                  2, 3, 4, 6 or 8 octets, either in the order ...4321 ('big-
                  endian') or 1234... ('little-endian').  If there are fewer
                  than the specified number of octets to fill the last word,
                  then the missing octets are presented as '==' for each
                  missing octet.  Exactly two equal signs are used for each
                  missing octet even for octal and decimal encoding.
                  The format of lines is:
    
                  rnd xxxxxx xxxxxx xxxxxx
    
                  where r is 'H', 'O' or 'D' for hexadecimal, octal or
                  decimal, n is the number of octets per word and d is '<'
                  or '>' for the '...4321' and '1234...' octet orderings,
                  respectively.  The '==' padding for the last word should
                  be on the appropriate side to correspond to the missing
                  octets, e.g.
    
                  H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000
    
                  or
    
                  H3> FF0700 00====
    
                  For these hexadecimal, octal and decimal formats only,
                  comments beginning with '#' are permitted to improve
                  readability.
    
                  BASE64 encoding follows MIME conventions.  Octets are
                  in groups of three: c1, c2, c3.  The resulting 24 bits
                  are broken into four six-bit quantities, starting with
                  the high-order six bits (c1 >> 2) of the first octet, then
                  the low-order two bits of the first octet followed by the
                  high-order four bits of the second octet [(c1 & 3)<<4 | (c2>>4)],
                  then the bottom four bits of the second octet followed by the
                  high-order two bits of the last octet [(c2 & 15)<<2 | (c3>>6)],
                  then the bottom six bits of the last octet (c3 & 63).  Each
                  of these four quantities is translated into an ASCII character
                  using the mapping:
    
                            1         2         3         4         5         6
                  0123456789012345678901234567890123456789012345678901234567890123
                  |         |         |         |         |         |         |
                  ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/
    
                  With short groups of octets padded on the right with one '='
                  if c3 is missing, and with '==' if both c2 and c3 are missing.
    
                  X-BASE32K encoding is similar to BASE64 encoding, except that
                  sets of 15 octets are encoded as sets of 8 16-bit unicode
                  characters, by breaking the 120 bits into 8 15-bit quantities.
                  256 is added to each 15 bit quantity to bring it into a
                  printable uncode range.  When encoding, zero padding is used
                  to fill out the last 15 bit quantity.  If 8 or more bits of
                  padding are used, a single equals sign (hexadecimal 003D) is
                  appended.  Embedded whitespace and newlines are introduced
                  to produce lines of no more than 80 characters each.  On
                  decoding, all printable ascii characters and ascii whitespace
                  characters are ignored except for any trailing equals signs.
                  The number of trailing equals signs indicated the number of
                  trailing octets to be trimmed from the end of the decoded data.
                  (see Georgi Darakev, Vassil Litchev, Kostadin Z. Mitev, Herbert
                  J. Bernstein, 'Efficient Support of Binary Data in the XML
                  Implementation of the NeXus File Format',absract W0165,
                  ACA Summer Meeting, Honolulu, HI, July 2006).
    
                  QUOTED-PRINTABLE encoding also follows MIME conventions, copying
                  octets without translation if their ASCII values are 32...38,
                  42, 48...57, 59, 60, 62, 64...126 and the octet is not a ';'
                  in column 1.  All other characters are translated to =nn, where
                  nn is the hexadecimal encoding of the octet.  All lines are
                  'wrapped' with a terminating '=' (i.e. the MIME conventions
                  for an implicit line terminator are never used).
    ;
        _item.name                  '_array_data.data'
        _item.category_id             array_data
        _item.mandatory_code          yes
        _item_type.code               binary
    save_
    
    
    ######################
    # ARRAY_ELEMENT_SIZE #
    ######################
    
    
    save_ARRAY_ELEMENT_SIZE
        _category.description
    ;    Data items in the ARRAY_ELEMENT_SIZE category record the physical
         size of array elements along each array dimension.
    ;
        _category.id                   array_element_size
        _category.mandatory_code       no
         loop_
        _category_key.name             '_array_element_size.array_id'
                                       '_array_element_size.index'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;       Example 1 - A regular 2D array with a uniform element dimension
                        of 1220 nanometres.
    ;
    ;
            loop_
           _array_element_size.array_id
           _array_element_size.index
           _array_element_size.size
            image_1   1    1.22e-6
            image_1   2    1.22e-6
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_element_size.array_id
        _item_description.description
    ;             This item is a pointer to _array_structure.id in the
                  ARRAY_STRUCTURE category.
    ;
        _item.name                  '_array_element_size.array_id'
        _item.category_id             array_element_size
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__array_element_size.index
        _item_description.description
    ;             This item is a pointer to _array_structure_list.index in
                  the ARRAY_STRUCTURE_LIST category.
    ;
        _item.name                  '_array_element_size.index'
        _item.category_id             array_element_size
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__array_element_size.size
        _item_description.description
    ;              The size in metres of an image element in this
                   dimension. This supposes that the elements are arranged
                   on a regular grid.
    ;
        _item.name               '_array_element_size.size'
        _item.category_id          array_element_size
        _item.mandatory_code       yes
        _item_type.code            float
        _item_units.code           'metres'
         loop_
        _item_range.maximum
        _item_range.minimum
                                .   0.0
         save_
    
    
    #####################
    # ARRAY_INTENSITIES #
    #####################
    
    
    save_ARRAY_INTENSITIES
        _category.description
    ;             Data items in the ARRAY_INTENSITIES category record the
                  information required to recover the intensity data from
                  the set of data values stored in the ARRAY_DATA category.
    
                  The detector may have a complex relationship
                  between the raw intensity values and the number of
                  incident photons.  In most cases, the number stored
                  in the final array will have a simple linear relationship
                  to the actual number of incident photons, given by
                  _array_intensities.gain.  If raw, uncorrected values
                  are presented (e.g. for calibration experiments), the
                  value of _array_intensities.linearity will be 'raw'
                  and _array_intensities.gain will not be used.
    
    ;
        _category.id                   array_intensities
        _category.mandatory_code       no
        loop_
        _category_key.name             '_array_intensities.array_id'
                                       '_array_intensities.binary_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
            Example 1
    ;
    ;
            loop_
            _array_intensities.array_id
            _array_intensities.linearity
            _array_intensities.gain
            _array_intensities.overload
            _array_intensities.undefined_value
            _array_intensities.pixel_fast_bin_size
            _array_intensities.pixel_slow_bin_size
            _array_intensities.pixel_binning_method
            image_1   linear  1.2    655535   0   2   2    hardware
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_intensities.array_id
        _item_description.description
    ;             This item is a pointer to _array_structure.id in the
                  ARRAY_STRUCTURE category.
    ;
        _item.name                  '_array_intensities.array_id'
        _item.category_id             array_intensities
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__array_intensities.binary_id
        _item_description.description
    ;             This item is a pointer to _array_data.binary_id in the
                  ARRAY_DATA category.
    ;
        _item.name                  '_array_intensities.binary_id'
        _item.category_id             array_intensities
        _item.mandatory_code          implicit
        _item_type.code               int
         save_
    
    
    save__array_intensities.gain
        _item_description.description
    ;              Detector 'gain'. The factor by which linearized
                   intensity count values should be divided to produce
                   true photon counts.
    ;
        _item.name              '_array_intensities.gain'
        _item.category_id          array_intensities
        _item.mandatory_code       yes
        _item_type.code            float
         loop_
        _item_range.maximum
        _item_range.minimum
                                .   0.0
        _item_units.code           'counts_per_photon'
         loop_
        _item_related.related_name
        _item_related.function_code  '_array_intensities.gain_esd'
                                     'associated_value'
        save_
    
    
    save__array_intensities.gain_esd
        _item_description.description
    ;            The estimated standard deviation in detector 'gain'.
    ;
        _item.name              '_array_intensities.gain_esd'
        _item.category_id          array_intensities
        _item.mandatory_code       yes
        _item_type.code            float
         loop_
        _item_range.maximum
        _item_range.minimum
                                .   0.0
    
        _item_units.code          'counts_per_photon'
         loop_
        _item_related.related_name
        _item_related.function_code  '_array_intensities.gain'
                                     'associated_esd'
        save_
    
    
    save__array_intensities.linearity
        _item_description.description
    ;              The intensity linearity scaling method used to convert
                   from the raw intensity to the stored element value:
    
                   'linear' is linear.
    
                   'offset'  means that the value defined by
                   _array_intensities.offset should be added to each
                    element value.
    
                   'scaling' means that the value defined by
                   _array_intensities.scaling should be multiplied with each
                   element value.
    
                   'scaling_offset' is the combination of the two previous cases,
                   with the scale factor applied before the offset value.
    
                   'sqrt_scaled' means that the square root of raw
                   intensities multiplied by _array_intensities.scaling is
                   calculated and stored, perhaps rounded to the nearest
                   integer. Thus, linearization involves dividing the stored
                   values by _array_intensities.scaling and squaring the
                   result.
    
                   'logarithmic_scaled' means that the logarithm base 10 of
                   raw intensities multiplied by _array_intensities.scaling
                   is calculated and stored, perhaps rounded to the nearest
                   integer. Thus, linearization involves dividing the stored
                   values by _array_intensities.scaling and calculating 10
                   to the power of this number.
    
                   'raw' means that the data are a set of raw values straight
                   from the detector.
    ;
    
        _item.name               '_array_intensities.linearity'
        _item.category_id          array_intensities
        _item.mandatory_code       yes
        _item_type.code            code
         loop_
        _item_enumeration.value
        _item_enumeration.detail
                                  'linear' .
                                  'offset'
    ;              The value defined by  _array_intensities.offset should
                   be added to each element value.
    ;
                                  'scaling'
    ;              The value defined by _array_intensities.scaling should be
                   multiplied with each element value.
    ;
                                  'scaling_offset'
    ;              The combination of the scaling and offset
                   with the scale factor applied before the offset value.
    ;
                                  'sqrt_scaled'
    ;              The square root of raw intensities multiplied by
                   _array_intensities.scaling is calculated and stored,
                   perhaps rounded to the nearest integer. Thus,
                   linearization involves dividing the stored
                   values by _array_intensities.scaling and squaring the
                   result.
    ;
                                  'logarithmic_scaled'
    ;              The logarithm base 10 of raw intensities multiplied by
                   _array_intensities.scaling  is calculated and stored,
                   perhaps rounded to the nearest integer. Thus,
                   linearization involves dividing the stored values by
                   _array_intensities.scaling and calculating 10 to the
                   power of this number.
    ;
                                  'raw'
    ;              The array consists of raw values to which no corrections have
                   been applied.  While the handling of the data is similar to
                   that given for 'linear' data with no offset, the meaning of
                   the data differs in that the number of incident photons is
                   not necessarily linearly related to the number of counts
                   reported.  This value is intended for use either in
                   calibration experiments or to allow for handling more
                   complex data-fitting algorithms than are allowed for by
                   this data item.
    ;
    
        save_
    
    
    save__array_intensities.offset
        _item_description.description
    ;              Offset value to add to array element values in the manner
                   described by the item _array_intensities.linearity.
    ;
        _item.name                 '_array_intensities.offset'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        save_
    
    
    save__array_intensities.overload
        _item_description.description
    ;              The saturation intensity level for this data array.
    ;
        _item.name                 '_array_intensities.overload'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        _item_units.code          'counts'
        save_
    
    
    save__array_intensities.pixel_fast_bin_size
        _item_description.description
    ;              The value of _array_intensities.pixel_fast_bin_size specifies
                   the number of pixels that compose one element in the direction
                   of the most rapidly varying array dimension.
    
                   Typical values are 1, 2, 4 or 8.  When there is 1 pixel per
                   array element in both directions, the value given for
                   _array_intensities.pixel_binning_method normally should be
                   'none'.
    
                   It is specified as a float to allow for binning algorithms that
                   create array elements that are not integer multiples of the 
                   detector pixel size.
    ;
        _item.name              '_array_intensities.pixel_fast_bin_size'
        _item.category_id          array_intensities
        _item.mandatory_code       implicit
        _item_type.code            float
        _item_default.value        1.
         loop_
        _item_range.maximum
        _item_range.minimum
                                .   0.0
        _item_units.code           'pixels_per_element'
        save_
    
    
    save__array_intensities.pixel_slow_bin_size
        _item_description.description
    ;              The value of _array_intensities.pixel_slow_bin_size specifies
                   the number of pixels that compose one element in the direction
                   of the second most rapidly varying array dimension.
    
                   Typical values are 1, 2, 4 or 8.  When there is 1 pixel per
                   array element in both directions, the value given for
                   _array_intensities.pixel_binning_method normally should be
                   'none'.
    
                   It is specified as a float to allow for binning algorithms that
                   create array elements that are not integer multiples of the
                   detector pixel size.
    ;
        _item.name              '_array_intensities.pixel_slow_bin_size'
        _item.category_id          array_intensities
        _item.mandatory_code       implicit
        _item_type.code            float
        _item_default.value        1.
         loop_
        _item_range.maximum
        _item_range.minimum
                                .   0.0
        _item_units.code           'pixels_per_element'
        save_
    
    
    save__array_intensities.pixel_binning_method
        _item_description.description
    ;              The value of _array_intensities.pixel_binning_method specifies
                   the method used to derive array elements from multiple pixels.
    ;
        _item.name              '_array_intensities.pixel_binning_method'
        _item.category_id          array_intensities
        _item.mandatory_code       implicit
        _item_type.code            code
         loop_
        _item_enumeration.value
        _item_enumeration.detail
                                   'hardware'
    ;              The element intensities were derived from the raw data of one
                   or more pixels by used of hardware in the detector, e.g. by use
                   of shift registers in a CCD to combine pixels into super-pixels.
    ;
                                   'software'
    ;              The element intensities were derived from the raw data of more
                   than one pixel by use of software.
    ;
                                   'combined'
    ;              The element intensities were derived from the raw data of more
                   than one pixel by use of both hardware and software, as when
                   hardware binning is used in one direction and software in the
                   other.
    ;
                                   'none'
    ;              In the both directions, the data has not been binned.  The
                   number of pixels is equal to the number of elements.
    
                   When the value of _array_intensities.pixel_binning_method is
                   'none' the values of _array_intensities.pixel_fast_bin_size
                   and _array_intensities.pixel_slow_bin_size both must be 1.
    ;
                                   'unspecified'
    ;              The method used to derive element intensities is not specified.
    ;
        _item_default.value        'unspecified'
        save_
    
    save__array_intensities.scaling
        _item_description.description
    ;              Multiplicative scaling value to be applied to array data
                   in the manner described by item
                   _array_intensities.linearity.
    ;
        _item.name                 '_array_intensities.scaling'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        save_
    
    
    
    save__array_intensities.undefined_value
        _item_description.description
    ;              A value to be substituted for undefined values in
                   the data array.
    ;
        _item.name                 '_array_intensities.undefined_value'
        _item.category_id          array_intensities
        _item.mandatory_code       no
        _item_type.code            float
        save_
    
    
    ###################
    # ARRAY_STRUCTURE #
    ###################
    
    
    save_ARRAY_STRUCTURE
        _category.description
    ;    Data items in the ARRAY_STRUCTURE category record the organization and
         encoding of array data that may be stored in the ARRAY_DATA category.
    ;
        _category.id                   array_structure
        _category.mandatory_code       no
        _category_key.name             '_array_structure.id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;   Example 1 -
    ;
    ;
         loop_
        _array_structure.id
        _array_structure.encoding_type
        _array_structure.compression_type
        _array_structure.byte_order
         image_1       "unsigned 16-bit integer"  none  little_endian
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_structure.byte_order
        _item_description.description
    ;              The order of bytes for integer values which require more
                   than 1 byte.
    
                   (IBM-PC's and compatibles and DEC VAXs use low-byte-first
                   ordered integers, whereas Hewlett Packard 700
                   series, Sun-4 and Silicon Graphics use high-byte-first
                   ordered integers.  DEC Alphas can produce/use either
                   depending on a compiler switch.)
    ;
    
        _item.name                     '_array_structure.byte_order'
        _item.category_id               array_structure
        _item.mandatory_code            yes
        _item_type.code                 code
         loop_
        _item_enumeration.value
        _item_enumeration.detail
                                       'big_endian'
    ;       The first byte in the byte stream of the bytes which make up an
            integer value is the most significant byte of an integer.
    ;
                                       'little_endian'
    ;       The last byte in the byte stream of the bytes which make up an
            integer value is the most significant byte of an integer.
    ;
         save_
    
    
    save__array_structure.compression_type
        _item_description.description
    ;             Type of data-compression method used to compress the array
                  data.
    ;
        _item.name                   '_array_structure.compression_type'
        _item.category_id             array_structure
        _item.mandatory_code          no
        _item_type.code               code
        _item_default.value           'none'
         loop_
        _item_enumeration.value
        _item_enumeration.detail
                                      'none'
    ;       Data are stored in normal format as defined by
            _array_structure.encoding_type and
            _array_structure.byte_order.
    ;
                                      'packed'
    ;       Using the 'packed' compression scheme, a CCP4-style packing
            (International Tables for Crystallography Volume G,
            Section 5.6.3.2)
    ;
                                      'canonical'
    ;       Using the 'canonical' compression scheme (International Tables
            for Crystallography Volume G, Section 5.6.3.1)
    ;
        save_
    
    
    save__array_structure.encoding_type
        _item_description.description
    ;              Data encoding of a single element of array data.
    
                   In several cases, the IEEE format is referenced.
                   See IEEE Standard 754-1985 (IEEE, 1985).
    
                   Ref: IEEE (1985). IEEE Standard for Binary Floating-Point
                   Arithmetic. ANSI/IEEE Std 754-1985. New York: Institute of
                   Electrical and Electronics Engineers.
    ;
    
        _item.name                '_array_structure.encoding_type'
        _item.category_id          array_structure
        _item.mandatory_code       yes
        _item_type.code            uline
         loop_
        _item_enumeration.value
                                  'unsigned 8-bit integer'
                                  'signed 8-bit integer'
                                  'unsigned 16-bit integer'
                                  'signed 16-bit integer'
                                  'unsigned 32-bit integer'
                                  'signed 32-bit integer'
                                  'signed 32-bit real IEEE'
                                  'signed 64-bit real IEEE'
                                  'signed 32-bit complex IEEE'
         save_
    
    
    save__array_structure.id
        _item_description.description
    ;             The value of _array_structure.id must uniquely identify
                  each item of array data.
    ;
        loop_
        _item.name
        _item.category_id
        _item.mandatory_code
                 '_array_structure.id'              array_structure      yes
                 '_array_data.array_id'             array_data           yes
                 '_array_structure_list.array_id'   array_structure_list yes
                 '_array_intensities.array_id'      array_intensities    yes
                 '_diffrn_data_frame.array_id'      diffrn_data_frame    yes
    
    
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_array_data.array_id'             '_array_structure.id'
                 '_array_structure_list.array_id'   '_array_structure.id'
                 '_array_intensities.array_id'      '_array_structure.id'
                 '_diffrn_data_frame.array_id'      '_array_structure.id'
    
         save_
    
    
    ########################
    # ARRAY_STRUCTURE_LIST #
    ########################
    
    
    save_ARRAY_STRUCTURE_LIST
        _category.description
    ;    Data items in the ARRAY_STRUCTURE_LIST category record the size
         and organization of each array dimension.
    
         The relationship to physical axes may be given.
    ;
        _category.id                   array_structure_list
        _category.mandatory_code       no
         loop_
        _category_key.name             '_array_structure_list.array_id'
                                       '_array_structure_list.index'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;       Example 1 - An image array of 1300 x 1200 elements.  The raster
                        order of the image is left to right (increasing) in the
                        first dimension and bottom to top (decreasing) in
                        the second dimension.
    ;
    ;
            loop_
           _array_structure_list.array_id
           _array_structure_list.index
           _array_structure_list.dimension
           _array_structure_list.precedence
           _array_structure_list.direction
           _array_structure_list.axis_set_id
            image_1   1    1300    1     increasing  ELEMENT_X
            image_1   2    1200    2     decreasing  ELEMENY_Y
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__array_structure_list.array_id
        _item_description.description
    ;             This item is a pointer to _array_structure.id in the
                  ARRAY_STRUCTURE category.
    ;
        _item.name                  '_array_structure_list.array_id'
        _item.category_id             array_structure_list
        _item.mandatory_code          yes
        _item_type.code               code
    save_
    
    
    save__array_structure_list.axis_set_id
        _item_description.description
    ;              This is a descriptor for the physical axis or set of axes
                   corresponding to an array index.
    
                   This data item is related to the axes of the detector
                   itself given in DIFFRN_DETECTOR_AXIS, but usually differs
                   in that the axes in this category are the axes of the
                   coordinate system of reported data points, while the axes in
                   DIFFRN_DETECTOR_AXIS are the physical axes
                   of the detector describing the 'poise' of the detector as an
                   overall physical object.
    
                   If there is only one axis in the set, the identifier of
                   that axis should be used as the identifier of the set.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
               '_array_structure_list.axis_set_id'
                                      array_structure_list            yes
               '_array_structure_list_axis.axis_set_id'
                                      array_structure_list_axis       implicit
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_array_structure_list_axis.axis_set_id'
                                   '_array_structure_list.axis_set_id'
    
    
         save_
    
    
    save__array_structure_list.dimension
        _item_description.description
    ;              The number of elements stored in the array structure in this
                   dimension.
    ;
        _item.name                '_array_structure_list.dimension'
        _item.category_id          array_structure_list
        _item.mandatory_code       yes
        _item_type.code            int
         loop_
        _item_range.maximum
        _item_range.minimum
                                1  1
                                .  1
         save_
    
    
    save__array_structure_list.direction
        _item_description.description
    ;             Identifies the direction in which this array index changes.
    ;
        _item.name                '_array_structure_list.direction'
        _item.category_id          array_structure_list
        _item.mandatory_code       yes
        _item_type.code            code
         loop_
        _item_enumeration.value
        _item_enumeration.detail
    
                                  'increasing'
    ;        Indicates the index changes from 1 to the maximum dimension.
    ;
                                  'decreasing'
    ;        Indicates the index changes from the maximum dimension to 1.
    ;
         save_
    
    
    save__array_structure_list.index
        _item_description.description
    ;              Identifies the one-based index of the row or column in the
                   array structure.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
               '_array_structure_list.index'        array_structure_list   yes
               '_array_structure_list.precedence'   array_structure_list   yes
               '_array_element_size.index'          array_element_size     yes
    
        _item_type.code            int
    
         loop_
        _item_linked.child_name
        _item_linked.parent_name
              '_array_element_size.index'         '_array_structure_list.index'
         loop_
        _item_range.maximum
        _item_range.minimum
                                1  1
                                .  1
         save_
    
    
    save__array_structure_list.precedence
        _item_description.description
    ;              Identifies the rank order in which this array index changes
                   with respect to other array indices.  The precedence of 1
                   indicates the index which changes fastest.
    ;
        _item.name                '_array_structure_list.precedence'
        _item.category_id          array_structure_list
        _item.mandatory_code       yes
        _item_type.code            int
         loop_
        _item_range.maximum
        _item_range.minimum
                                1  1
                                .  1
         save_
    
    
    #############################
    # ARRAY_STRUCTURE_LIST_AXIS #
    #############################
    
    save_ARRAY_STRUCTURE_LIST_AXIS
        _category.description
    ;    Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe
         the physical settings of sets of axes for the centres of pixels that
         correspond to data points described in the
         ARRAY_STRUCTURE_LIST category.
    
         In the simplest cases, the physical increments of a single axis correspond
         to the increments of a single array index.  More complex organizations,
         e.g. spiral scans, may require coupled motions along multiple axes.
    
         Note that a spiral scan uses two coupled axes: one for the angular
         direction and one for the radial direction.  This differs from a
         cylindrical scan for which the two axes are not coupled into one set.
    ;
        _category.id                   array_structure_list_axis
        _category.mandatory_code       no
         loop_
        _category_key.name
                                      '_array_structure_list_axis.axis_set_id'
                                      '_array_structure_list_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'array_data_group'
         save_
    
    
    save__array_structure_list_axis.axis_id
        _item_description.description
    ;              The value of this data item is the identifier of one of
                   the axes in the set of axes for which settings are being
                   specified.
    
                   Multiple axes may be specified for the same value of
                   _array_structure_list_axis.axis_set_id.
    
                   This item is a pointer to _axis.id in the
                   AXIS category.
    ;
        _item.name                 '_array_structure_list_axis.axis_id'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__array_structure_list_axis.axis_set_id
        _item_description.description
    ;              The value of this data item is the identifier of the
                   set of axes for which axis settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   _array_structure_list_axis.axis_set_id.
    
                   This item is a pointer to
                   _array_structure_list.axis_set_id
                   in the ARRAY_STRUCTURE_LIST category.
    
                   If this item is not specified, it defaults to the corresponding
                   axis identifier.
    ;
        _item.name                 '_array_structure_list_axis.axis_set_id'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       implicit
        _item_type.code            code
         save_
    
    
    save__array_structure_list_axis.angle
        _item_description.description
    ;              The setting of the specified axis in degrees for the first
                   data point of the array index with the corresponding value
                   of _array_structure_list.axis_set_id.  If the index is
                   specified as 'increasing', this will be the centre of the
                   pixel with index value 1.  If the index is specified as
                   'decreasing', this will be the centre of the pixel with
                   maximum index value.
    ;
        _item.name                 '_array_structure_list_axis.angle'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__array_structure_list_axis.angle_increment
        _item_description.description
    ;              The pixel-centre-to-pixel-centre increment in the angular
                   setting of the specified axis in degrees.  This is not
                   meaningful in the case of 'constant velocity' spiral scans
                   and should not be specified for this case.
    
                   See _array_structure_list_axis.angular_pitch.
    
    ;
        _item.name                 '_array_structure_list_axis.angle_increment'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__array_structure_list_axis.displacement
        _item_description.description
    ;              The setting of the specified axis in millimetres for the first
                   data point of the array index with the corresponding value
                   of _array_structure_list.axis_set_id.  If the index is
                   specified as 'increasing', this will be the centre of the
                   pixel with index value 1.  If the index is specified as
                   'decreasing', this will be the centre of the pixel with
                   maximum index value.
    ;
        _item.name               '_array_structure_list_axis.displacement'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__array_structure_list_axis.displacement_increment
        _item_description.description
    ;              The pixel-centre-to-pixel-centre increment for the displacement
                   setting of the specified axis in millimetres.
    ;
        _item.name
            '_array_structure_list_axis.displacement_increment'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__array_structure_list_axis.angular_pitch
        _item_description.description
    ;              The pixel-centre-to-pixel-centre distance for a one-step
                   change in the setting of the specified axis in millimetres.
    
                   This is meaningful only for 'constant velocity' spiral scans
                   or for uncoupled angular scans at a constant radius
                   (cylindrical scans) and should not be specified for cases
                   in which the angle between pixels (rather than the distance
                   between pixels) is uniform.
    
                   See _array_structure_list_axis.angle_increment.
    ;
        _item.name               '_array_structure_list_axis.angular_pitch'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__array_structure_list_axis.radial_pitch
        _item_description.description
    ;              The radial distance from one 'cylinder' of pixels to the
                   next in millimetres.  If the scan is a 'constant velocity'
                   scan with differing angular displacements between pixels,
                   the value of this item may differ significantly from the
                   value of _array_structure_list_axis.displacement_increment.
    ;
        _item.name               '_array_structure_list_axis.radial_pitch'
        _item.category_id          array_structure_list_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    
    ########
    # AXIS #
    ########
    
    save_AXIS
        _category.description
    ;    Data items in the AXIS category record the information required
         to describe the various goniometer, detector, source and other
         axes needed to specify a data collection.  The location of each
         axis is specified by two vectors: the axis itself, given as a unit
         vector, and an offset to the base of the unit vector.  These vectors
         are referenced to a right-handed laboratory coordinate system with
         its origin in the sample or specimen:
    
                                 | Y (to complete right-handed system)
                                 |
                                 |
                                 |
                                 |
                                 |
                                 |________________X
                                /       principal goniometer axis
                               /
                              /
                             /
                            /
                           /Z (to source)
    
    
    
         Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from
         the sample or specimen along the  principal axis of the goniometer.
    
         Axis 2 (Y): The Y-axis completes an orthogonal right-handed system
         defined by the X-axis and the Z-axis (see below).
    
         Axis 3 (Z): The Z-axis is derived from the source axis which goes from
         the sample to the source.  The Z-axis is the component of the source axis
         in the direction of the source orthogonal to the X-axis in the plane
         defined by the X-axis and the source axis.
    
         These axes are based on the goniometer, not on the orientation of the
         detector, gravity etc.  The vectors necessary to specify all other
         axes are given by sets of three components in the order (X, Y, Z).
         If the axis involved is a rotation axis, it is right-handed, i.e. as
         one views the object to be rotated from the origin (the tail) of the
         unit vector, the rotation is clockwise.  If a translation axis is
         specified, the direction of the unit vector specifies the sense of
         positive translation.
    
         Note:  This choice of coordinate system is similar to but significantly
         different from the choice in MOSFLM (Leslie & Powell, 2004).  In MOSFLM,
         X is along the X-ray beam (the CBF/imgCIF Z axis) and Z is along the
         rotation axis.
    
         All rotations are given in degrees and all translations are given in mm.
    
         Axes may be dependent on one another.  The X-axis is the only goniometer
         axis the direction of which is strictly connected to the hardware.  All
         other axes are specified by the positions they would assume when the
         axes upon which they depend are at their zero points.
    
         When specifying detector axes, the axis is given to the beam centre.
         The location of the beam centre on the detector should be given in the
         DIFFRN_DETECTOR category in distortion-corrected millimetres from
         the (0,0) corner of the detector.
    
         It should be noted that many different origins arise in the definition
         of an experiment.  In particular, as noted above, it is necessary to
         specify the location of the beam centre on the detector in terms
         of the origin of the detector, which is, of course, not coincident
         with the centre of the sample.
    
         Ref:  Leslie, A. G. W. &  Powell, H. (2004). MOSFLM v6.11.
         MRC Laboratory of Molecular Biology, Hills Road, Cambridge, England.
         http://www.CCP4.ac.uk/dist/x-windows/Mosflm/.
    ;
        _category.id                   axis
        _category.mandatory_code       no
         loop_
        _category_key.name          '_axis.id'
                                    '_axis.equipment'
         loop_
        _category_group.id           'inclusive_group'
                                     'axis_group'
                                     'diffrn_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;       Example 1 -
    
            This example shows the axis specification of the axes of a kappa-
            geometry goniometer [see Stout, G. H. & Jensen, L. H. (1989). X-ray
            structure determination. A practical
            guide, 2nd ed. p. 134. New York: Wiley Interscience].
    
            There are three axes specified, and no offsets.  The outermost axis,
            omega, is pointed along the X axis.  The next innermost axis, kappa,
            is at a 50 degree angle to the X axis, pointed away from the source.
            The innermost axis, phi, aligns with the X axis when omega and
            phi are at their zero points.  If T-omega, T-kappa and T-phi
            are the transformation matrices derived from the axis settings,
            the complete transformation would be:
                x' = (T-omega) (T-kappa) (T-phi) x
    ;
    ;
             loop_
            _axis.id
            _axis.type
            _axis.equipment
            _axis.depends_on
            _axis.vector[1] _axis.vector[2] _axis.vector[3]
            omega rotation goniometer     .    1        0        0
            kappa rotation goniometer omega    -.64279  0       -.76604
            phi   rotation goniometer kappa    1        0        0
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;       Example 2 -
    
            This example show the axis specification of the axes of a
            detector, source and gravity.  The order has been changed as a
            reminder that the ordering of presentation of tokens is not
            significant.  The centre of rotation of the detector has been taken
            to be 68 millimetres in the direction away from the source.
    ;
    ;
            loop_
            _axis.id
            _axis.type
            _axis.equipment
            _axis.depends_on
            _axis.vector[1] _axis.vector[2] _axis.vector[3]
            _axis.offset[1] _axis.offset[2] _axis.offset[3]
            source       .        source     .       0     0     1   . . .
            gravity      .        gravity    .       0    -1     0   . . .
            tranz     translation detector rotz      0     0     1   0 0 -68
            twotheta  rotation    detector   .       1     0     0   . . .
            roty      rotation    detector twotheta  0     1     0   0 0 -68
            rotz      rotation    detector roty      0     0     1   0 0 -68
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__axis.depends_on
        _item_description.description
    ;             The value of _axis.depends_on specifies the next outermost
                  axis upon which this axis depends.
    
                  This item is a pointer to _axis.id in the same category.
    ;
        _item.name                      '_axis.depends_on'
        _item.category_id                 axis
        _item.mandatory_code              no
    
         save_
    
    
    save__axis.equipment
        _item_description.description
    ;             The value of  _axis.equipment specifies the type of
                  equipment using the axis:  'goniometer', 'detector',
                  'gravity', 'source' or 'general'.
    ;
        _item.name                      '_axis.equipment'
        _item.category_id                 axis
        _item.mandatory_code              no
        _item_type.code                   ucode
        _item_default.value               general
         loop_
        _item_enumeration.value
        _item_enumeration.detail   goniometer
                                  'equipment used to orient or position samples'
                                   detector
                                  'equipment used to detect reflections'
                                   general
                                  'equipment used for general purposes'
                                   gravity
                                  'axis specifying the downward direction'
                                   source
                                  'axis specifying the direction sample to source'
    
         save_
    
    
    save__axis.offset[1]
        _item_description.description
    ;              The [1] element of the three-element vector used to specify
                   the offset to the base of a rotation or translation axis.
    
                   The vector is specified in millimetres.
    ;
        _item.name                  '_axis.offset[1]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    
    save__axis.offset[2]
        _item_description.description
    ;              The [2] element of the three-element vector used to specify
                   the offset to the base of a rotation or translation axis.
    
                   The vector is specified in millimetres.
    ;
        _item.name                  '_axis.offset[2]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    
    save__axis.offset[3]
        _item_description.description
    ;              The [3] element of the three-element vector used to specify
                   the offset to the base of a rotation or translation axis.
    
                   The vector is specified in millimetres.
    ;
        _item.name                  '_axis.offset[3]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    
    save__axis.id
        _item_description.description
    ;             The value of _axis.id must uniquely identify
                  each axis relevant to the experiment.  Note that multiple
                  pieces of equipment may share the same axis (e.g. a twotheta
                  arm), so the category key for AXIS also includes the
                  equipment.
    ;
        loop_
        _item.name
        _item.category_id
        _item.mandatory_code
             '_axis.id'                         axis                    yes
             '_array_structure_list_axis.axis_id'
                                                array_structure_list_axis
                                                                        yes
             '_diffrn_detector_axis.axis_id'    diffrn_detector_axis    yes
             '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes
             '_diffrn_scan_axis.axis_id'        diffrn_scan_axis        yes
             '_diffrn_scan_frame_axis.axis_id'  diffrn_scan_frame_axis  yes
    
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
             '_axis.depends_on'                   '_axis.id'
             '_array_structure_list_axis.axis_id' '_axis.id'
             '_diffrn_detector_axis.axis_id'      '_axis.id'
             '_diffrn_measurement_axis.axis_id'   '_axis.id'
             '_diffrn_scan_axis.axis_id'          '_axis.id'
             '_diffrn_scan_frame_axis.axis_id'    '_axis.id'
    
         save_
    
    
    save__axis.type
        _item_description.description
    ;             The value of _axis.type specifies the type of
                  axis:  'rotation' or 'translation' (or 'general' when
                  the type is not relevant, as for gravity).
    ;
        _item.name                      '_axis.type'
        _item.category_id                 axis
        _item.mandatory_code              no
        _item_type.code                   ucode
        _item_default.value               general
         loop_
        _item_enumeration.value
        _item_enumeration.detail      rotation
                                     'right-handed axis of rotation'
                                      translation
                                     'translation in the direction of the axis'
                                      general
                                     'axis for which the type is not relevant'
    
         save_
    
    
    save__axis.vector[1]
        _item_description.description
    ;              The [1] element of the three-element vector used to specify
                   the direction of a rotation or translation axis.
                   The vector should be normalized to be a unit vector and
                   is dimensionless.
    ;
        _item.name                  '_axis.vector[1]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
         save_
    
    save__axis.vector[2]
        _item_description.description
    ;              The [2] element of the three-element vector used to specify
                   the direction of a rotation or translation axis.
                   The vector should be normalized to be a unit vector and
                   is dimensionless.
    ;
        _item.name                  '_axis.vector[2]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
         save_
    
    save__axis.vector[3]
        _item_description.description
    ;              The [3] element of the three-element vector used to specify
                   the direction of a rotation or translation axis.
                   The vector should be normalized to be a unit vector and
                   is dimensionless.
    ;
        _item.name                  '_axis.vector[3]'
        _item.category_id             axis
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
         save_
    
    
    
    #####################
    # DIFFRN_DATA_FRAME #
    #####################
    
    
    save_DIFFRN_DATA_FRAME
        _category.description
    ;             Data items in the DIFFRN_DATA_FRAME category record
                  the details about each frame of data.
    
                  The items in this category were previously in a
                  DIFFRN_FRAME_DATA category, which is now deprecated.
                  The items from the old category are provided
                  as aliases but should not be used for new work.
    ;
        _category.id                   diffrn_data_frame
        _category.mandatory_code       no
         loop_
        _category_key.name             '_diffrn_data_frame.id'
                                       '_diffrn_data_frame.detector_element_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;   Example 1 - A frame containing data from 4 frame elements.
                    Each frame element has a common array configuration
                    'array_1' described in ARRAY_STRUCTURE and related
                    categories.  The data for each detector element are
                    stored in four groups of binary data in the
                    ARRAY_DATA category, linked by the array_id and
                    binary_id.
    ;
    ;
            loop_
            _diffrn_data_frame.id
            _diffrn_data_frame.detector_element_id
            _diffrn_data_frame.array_id
            _diffrn_data_frame.binary_id
            frame_1   d1_ccd_1  array_1  1
            frame_1   d1_ccd_2  array_1  2
            frame_1   d1_ccd_3  array_1  3
            frame_1   d1_ccd_4  array_1  4
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
    
    
    save__diffrn_data_frame.array_id
        _item_description.description
    ;             This item is a pointer to _array_structure.id in the
                  ARRAY_STRUCTURE category.
    ;
        _item.name                  '_diffrn_data_frame.array_id'
        _item.category_id             diffrn_data_frame
        _item.mandatory_code          yes
        _item_aliases.alias_name    '_diffrn_frame_data.array_id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         save_
    
    
    save__diffrn_data_frame.binary_id
        _item_description.description
    ;             This item is a pointer to _array_data.binary_id in the
                  ARRAY_DATA category.
    ;
        _item.name                  '_diffrn_data_frame.binary_id'
        _item.category_id             diffrn_data_frame
        _item.mandatory_code          implicit
        _item_aliases.alias_name    '_diffrn_frame_data.binary_id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               int
         save_
    
    
    save__diffrn_data_frame.detector_element_id
        _item_description.description
    ;              This item is a pointer to _diffrn_detector_element.id
                   in the DIFFRN_DETECTOR_ELEMENT category.
    ;
        _item.name                  '_diffrn_data_frame.detector_element_id'
        _item.category_id             diffrn_data_frame
        _item.mandatory_code          yes
        _item_aliases.alias_name    '_diffrn_frame_data.detector_element_id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         save_
    
    
    save__diffrn_data_frame.id
        _item_description.description
    ;             The value of _diffrn_data_frame.id must uniquely identify
                  each complete frame of data.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
               '_diffrn_data_frame.id'        diffrn_data_frame  yes
               '_diffrn_refln.frame_id'       diffrn_refln       yes
               '_diffrn_scan.frame_id_start'  diffrn_scan        yes
               '_diffrn_scan.frame_id_end'    diffrn_scan        yes
               '_diffrn_scan_frame.frame_id'  diffrn_scan_frame  yes
               '_diffrn_scan_frame_axis.frame_id'
                                              diffrn_scan_frame_axis
                                                                 yes
        _item_aliases.alias_name    '_diffrn_frame_data.id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_diffrn_refln.frame_id'        '_diffrn_data_frame.id'
               '_diffrn_scan.frame_id_start'   '_diffrn_data_frame.id'
               '_diffrn_scan.frame_id_end'     '_diffrn_data_frame.id'
               '_diffrn_scan_frame.frame_id'   '_diffrn_data_frame.id'
               '_diffrn_scan_frame_axis.frame_id'
                                               '_diffrn_data_frame.id'
         save_
    
    
    save__diffrn_data_frame.details
         _item_description.description
    ;              The value of _diffrn_data_frame.details should give a
                   description of special aspects of each frame of data.
    
                   This is an appropriate location in which to record
                   information from vendor headers as presented in those
                   headers, but it should never be used as a substitute
                   for providing the fully parsed information within
                   the appropriate imgCIF/CBF categories.
    ;
        _item.name                  '_diffrn_data_frame.details'
        _item.category_id             diffrn_data_frame
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_frame_data.details'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.4
        _item_type.code               text
         loop_
        _item_examples.case
        _item_examples.detail
    ;
     HEADER_BYTES = 512;
     DIM = 2;
     BYTE_ORDER = big_endian;
     TYPE = unsigned_short;
     SIZE1 = 3072;
     SIZE2 = 3072;
     PIXEL_SIZE = 0.102588;
     BIN = 2x2;
     DETECTOR_SN = 901;
     TIME = 29.945155;
     DISTANCE = 200.000000;
     PHI = 85.000000;
     OSC_START = 85.000000;
     OSC_RANGE = 1.000000;
     WAVELENGTH = 0.979381;
     BEAM_CENTER_X = 157.500000;
     BEAM_CENTER_Y = 157.500000;
     PIXEL SIZE = 0.102588;
     OSCILLATION RANGE = 1;
     EXPOSURE TIME = 29.9452;
     TWO THETA = 0;
     BEAM CENTRE = 157.5 157.5;
    ;
    ;               Example of header information extracted from an ADSC Quantum
                    315 detector header by CBFlib_0.7.6.  Image provided by Chris
                    Nielsen of ADSC from a data collection at SSRL beamline 1-5.
    ;
          save_
    
    
    
    ##########################################################################
    #  The following is a restatement of the mmCIF DIFFRN_DETECTOR,          #
    #  DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for      #
    #  the CBF/imgCIF extensions                                             #
    ##########################################################################
    
    ###################
    # DIFFRN_DETECTOR #
    ###################
    
    
    save_DIFFRN_DETECTOR
        _category.description
    ;              Data items in the DIFFRN_DETECTOR category describe the
                   detector used to measure the scattered radiation, including
                   any analyser and post-sample collimation.
    ;
        _category.id                  diffrn_detector
        _category.mandatory_code      no
         loop_
        _category_key.name          '_diffrn_detector.diffrn_id'
                                    '_diffrn_detector.id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;   Example 1 - based on PDB entry 5HVP and laboratory records for the
                    structure corresponding to PDB entry 5HVP.
    ;
    ;
        _diffrn_detector.diffrn_id             'd1'
        _diffrn_detector.detector              'multiwire'
        _diffrn_detector.type                  'Siemens'
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__diffrn_detector.details
        _item_description.description
    ;              A description of special aspects of the radiation detector.
    ;
        _item.name                  '_diffrn_detector.details'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_detector_details'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code                   text
        _item_examples.case        'slow mode'
         save_
    
    
    save__diffrn_detector.detector
        _item_description.description
    ;              The general class of the radiation detector.
    ;
        _item.name                  '_diffrn_detector.detector'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
         loop_
        _item_aliases.alias_name
        _item_aliases.dictionary
        _item_aliases.version       '_diffrn_radiation_detector'
                                      cifdic.c91
                                      1.0
                                    '_diffrn_detector'
                                      cif_core.dic
                                      2.0
        _item_type.code               text
         loop_
        _item_examples.case          'photographic film'
                                     'scintillation counter'
                                     'CCD plate'
                                     'BF~3~ counter'
         save_
    
    
    save__diffrn_detector.diffrn_id
        _item_description.description
    ;              This data item is a pointer to _diffrn.id in the DIFFRN
                   category.
    
                   The value of _diffrn.id uniquely defines a set of
                   diffraction data.
    ;
        _item.name                  '_diffrn_detector.diffrn_id'
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_detector.dtime
        _item_description.description
    ;              The deadtime in microseconds of the detector(s) used to
                   measure the diffraction intensities.
    ;
        _item.name                  '_diffrn_detector.dtime'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
         loop_
        _item_aliases.alias_name
        _item_aliases.dictionary
        _item_aliases.version       '_diffrn_radiation_detector_dtime'
                                      cifdic.c91
                                      1.0
                                    '_diffrn_detector_dtime'
                                      cif_core.dic
                                      2.0
         loop_
        _item_range.maximum
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
        _item_units.code              microseconds
         save_
    
    
    save__diffrn_detector.id
        _item_description.description
    ;              The value of _diffrn_detector.id must uniquely identify
                   each detector used to collect each diffraction data set.
    
                   If the value of _diffrn_detector.id is not given, it is
                   implicitly equal to the value of
                   _diffrn_detector.diffrn_id.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
                 '_diffrn_detector.id'         diffrn_detector       implicit
                 '_diffrn_detector_axis.detector_id'
                                               diffrn_detector_axis       yes
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_detector_axis.detector_id'
                                             '_diffrn_detector.id'
    
        _item_type.code               code
         save_
    
    
    save__diffrn_detector.number_of_axes
        _item_description.description
    ;              The value of _diffrn_detector.number_of_axes gives the
                   number of axes of the positioner for the detector identified
                   by _diffrn_detector.id.
    
                   The word 'positioner' is a general term used in
                   instrumentation design for devices that are used to change
                   the positions of portions of apparatus by linear
                   translation, rotation or combinations of such motions.
    
                   Axes which are used to provide a coordinate system for the
                   face of an area detetctor should not be counted for this
                   data item.
    
                   The description of each axis should be provided by entries
                   in DIFFRN_DETECTOR_AXIS.
    ;
        _item.name                  '_diffrn_detector.number_of_axes'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
         loop_
        _item_range.maximum
        _item_range.minimum           .   1
                                      1   1
        _item_type.code               int
         save_
    
    
    save__diffrn_detector.type
        _item_description.description
    ;              The make, model or name of the detector device used.
    ;
        _item.name                  '_diffrn_detector.type'
        _item.category_id             diffrn_detector
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_detector_type'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         save_
    
    
    ########################
    # DIFFRN_DETECTOR_AXIS #
    ########################
    
    
    save_DIFFRN_DETECTOR_AXIS
        _category.description
    ;    Data items in the DIFFRN_DETECTOR_AXIS category associate
         axes with detectors.
    ;
        _category.id                   diffrn_detector_axis
        _category.mandatory_code       no
         loop_
        _category_key.name          '_diffrn_detector_axis.detector_id'
                                    '_diffrn_detector_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_detector_axis.axis_id
        _item_description.description
    ;              This data item is a pointer to _axis.id in
                   the AXIS category.
    ;
        _item.name                  '_diffrn_detector_axis.axis_id'
        _item.category_id             diffrn_detector_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_detector_axis.detector_id
        _item_description.description
    ;              This data item is a pointer to _diffrn_detector.id in
                   the DIFFRN_DETECTOR category.
    
                   This item was previously named _diffrn_detector_axis.id
                   which is now a deprecated name.  The old name is
                   provided as an alias but should not be used for new work.
    ;
        _item.name                  '_diffrn_detector_axis.detector_id'
        _item.category_id             diffrn_detector_axis
        _item.mandatory_code          yes
        _item_aliases.alias_name    '_diffrn_detector_axis.id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         save_
    
    
    ###########################
    # DIFFRN_DETECTOR_ELEMENT #
    ###########################
    
    
    save_DIFFRN_DETECTOR_ELEMENT
        _category.description
    ;             Data items in the DIFFRN_DETECTOR_ELEMENT category record
                  the details about spatial layout and other characteristics
                  of each element of a detector which may have multiple elements.
    
                  In most cases, giving more detailed information
                  in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS
                  is preferable to simply providing the centre of the
                  detector element.
    ;
        _category.id                   diffrn_detector_element
        _category.mandatory_code       no
         loop_
        _category_key.name             '_diffrn_detector_element.id'
                                       '_diffrn_detector_element.detector_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;       Example 1 - Detector d1 is composed of four CCD detector elements,
            each 200 mm by 200 mm, arranged in a square, in the pattern
    
                       1     2
                          *
                       3     4
    
            Note that the beam centre is slightly displaced from each of the
            detector elements, just beyond the lower right corner of 1,
            the lower left corner of 2, the upper right corner of 3 and
            the upper left corner of 4.
    ;
    ;
            loop_
            _diffrn_detector_element.detector_id
            _diffrn_detector_element.id
            _diffrn_detector_element.center[1]
            _diffrn_detector_element.center[2]
            d1     d1_ccd_1  201.5 -1.5
            d1     d1_ccd_2  -1.8  -1.5
            d1     d1_ccd_3  201.6 201.4
            d1     d1_ccd_4  -1.7  201.5
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
    
    
    save__diffrn_detector_element.center[1]
        _item_description.description
    ;             The value of _diffrn_detector_element.center[1] is the X
                  component of the distortion-corrected beam centre in
                  millimetres from the (0, 0) (lower-left) corner of the
                  detector element viewed from the sample side.
    
                  The X and Y axes are the laboratory coordinate system
                  coordinates defined in the AXIS category measured
                  when all positioning axes for the detector are at their zero
                  settings.  If the resulting X or Y axis is then orthogonal to the
                  detector, the Z axis is used instead of the orthogonal axis.
    
    ;
        _item.name                  '_diffrn_detector_element.center[1]'
        _item.category_id             diffrn_detector_element
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
    
        save_
    
    
    save__diffrn_detector_element.center[2]
        _item_description.description
    ;             The value of _diffrn_detector_element.center[2] is the Y
                  component of the distortion-corrected beam centre in
                  millimetres from the (0, 0) (lower-left) corner of the
                  detector element viewed from the sample side.
    
                  The X and Y axes are the laboratory coordinate system
                  coordinates defined in the AXIS category measured
                  when all positioning axes for the detector are at their zero
                  settings.  If the resulting X or Y axis is then orthogonal to the
                  detector, the Z axis is used instead of the orthogonal axis.
    
    ;
        _item.name                  '_diffrn_detector_element.center[2]'
        _item.category_id             diffrn_detector_element
        _item.mandatory_code          no
        _item_default.value           0.0
        _item_sub_category.id         vector
        _item_type.code               float
        _item_units.code              millimetres
    
        save_
    
    
    save__diffrn_detector_element.id
        _item_description.description
    ;             The value of _diffrn_detector_element.id must uniquely
                  identify each element of a detector.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
               '_diffrn_detector_element.id'
               diffrn_detector_element
               yes
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
               '_diffrn_data_frame.detector_element_id'
               '_diffrn_detector_element.id'
    
         save_
    
    
    save__diffrn_detector_element.detector_id
        _item_description.description
    ;              This item is a pointer to _diffrn_detector.id
                   in the DIFFRN_DETECTOR category.
    ;
        _item.name                  '_diffrn_detector_element.detector_id'
        _item.category_id             diffrn_detector_element
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    
    ########################
    ## DIFFRN_MEASUREMENT ##
    ########################
    
    
    save_DIFFRN_MEASUREMENT
        _category.description
    ;              Data items in the DIFFRN_MEASUREMENT category record details
                   about the device used to orient and/or position the crystal
                   during data measurement and the manner in which the
                   diffraction data were measured.
    ;
        _category.id                  diffrn_measurement
        _category.mandatory_code      no
         loop_
        _category_key.name          '_diffrn_measurement.device'
                                    '_diffrn_measurement.diffrn_id'
                                    '_diffrn_measurement.id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;    Example 1 - based on PDB entry 5HVP and laboratory records for the
                     structure corresponding to PDB entry 5HVP
    ;
    ;
        _diffrn_measurement.diffrn_id          'd1'
        _diffrn_measurement.device             '3-circle camera'
        _diffrn_measurement.device_type        'Supper model x'
        _diffrn_measurement.device_details     'none'
        _diffrn_measurement.method             'omega scan'
        _diffrn_measurement.details
        ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector
          angle 22.5 degrees
        ;
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;     Example 2 - based on data set TOZ of Willis, Beckwith & Tozer
                      [Acta Cryst. (1991), C47, 2276-2277].
    ;
    ;
        _diffrn_measurement.diffrn_id       's1'
        _diffrn_measurement.device_type     'Philips PW1100/20 diffractometer'
        _diffrn_measurement.method          'theta/2theta (\q/2\q)'
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    
    save__diffrn_measurement.device
        _item_description.description
    ;              The general class of goniometer or device used to support
                   and orient the specimen.
    
                   If the value of _diffrn_measurement.device is not given,
                   it is implicitly equal to the value of
                   _diffrn_measurement.diffrn_id.
    
                   Either _diffrn_measurement.device or
                   _diffrn_measurement.id may be used to link to other
                   categories.  If the experimental setup admits multiple
                   devices, then _diffrn_measurement.id is used to provide
                   a unique link.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
                 '_diffrn_measurement.device'  diffrn_measurement      implicit
                 '_diffrn_measurement_axis.measurement_device'
                                               diffrn_measurement_axis implicit
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_measurement_axis.measurement_device'
                                             '_diffrn_measurement.device'
        _item_aliases.alias_name    '_diffrn_measurement_device'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          '3-circle camera'
                                     '4-circle camera'
                                     'kappa-geometry camera'
                                     'oscillation camera'
                                     'precession camera'
         save_
    
    
    save__diffrn_measurement.device_details
        _item_description.description
    ;              A description of special aspects of the device used to
                   measure the diffraction intensities.
    ;
        _item.name                  '_diffrn_measurement.device_details'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_device_details'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
        _item_examples.case
    ;                                 commercial goniometer modified locally to
                                      allow for 90\% \t arc
    ;
         save_
    
    
    save__diffrn_measurement.device_type
        _item_description.description
    ;              The make, model or name of the measurement device
                   (goniometer) used.
    ;
        _item.name                  '_diffrn_measurement.device_type'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_device_type'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          'Supper model q'
                                     'Huber model r'
                                     'Enraf-Nonius model s'
                                     'home-made'
         save_
    
    
    save__diffrn_measurement.diffrn_id
        _item_description.description
    ;              This data item is a pointer to _diffrn.id in the DIFFRN
                   category.
    ;
        _item.name                  '_diffrn_measurement.diffrn_id'
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_measurement.details
        _item_description.description
    ;              A description of special aspects of the intensity
                   measurement.
    ;
        _item.name                  '_diffrn_measurement.details'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_details'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
        _item_examples.case
    ;                                 440 frames, 0.20 degrees, 150 sec, detector
                                      distance 12 cm, detector angle 22.5 degrees
    ;
         save_
    
    
    save__diffrn_measurement.id
        _item_description.description
    ;              The value of _diffrn_measurement.id must uniquely identify
                   the set of mechanical characteristics of the device used to
                   orient and/or position the sample used during the collection
                   of each diffraction data set.
    
                   If the value of _diffrn_measurement.id is not given, it is
                   implicitly equal to the value of
                   _diffrn_measurement.diffrn_id.
    
                   Either _diffrn_measurement.device or
                   _diffrn_measurement.id may be used to link to other
                   categories.  If the experimental setup admits multiple
                   devices, then _diffrn_measurement.id is used to provide
                   a unique link.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
                 '_diffrn_measurement.id'      diffrn_measurement      implicit
                 '_diffrn_measurement_axis.measurement_id'
                                               diffrn_measurement_axis implicit
         loop_
        _item_linked.child_name
        _item_linked.parent_name
                 '_diffrn_measurement_axis.measurement_id'
                                             '_diffrn_measurement.id'
    
        _item_type.code               code
         save_
    
    
    save__diffrn_measurement.method
        _item_description.description
    ;              Method used to measure intensities.
    ;
        _item.name                  '_diffrn_measurement.method'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_method'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
        _item_examples.case
          'profile data from theta/2theta (\q/2\q) scans'
         save_
    
    
    save__diffrn_measurement.number_of_axes
        _item_description.description
    ;              The value of _diffrn_measurement.number_of_axes gives the
                   number of axes of the positioner for the goniometer or
                   other sample orientation or positioning device identified
                   by _diffrn_measurement.id.
    
                   The description of the axes should be provided by entries in
                   DIFFRN_MEASUREMENT_AXIS.
    ;
        _item.name                  '_diffrn_measurement.number_of_axes'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
         loop_
        _item_range.maximum
        _item_range.minimum           .   1
                                      1   1
        _item_type.code               int
         save_
    
    
    save__diffrn_measurement.specimen_support
        _item_description.description
    ;              The physical device used to support the crystal during data
                   collection.
    ;
        _item.name                  '_diffrn_measurement.specimen_support'
        _item.category_id             diffrn_measurement
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_measurement_specimen_support'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          'glass capillary'
                                     'quartz capillary'
                                     'fiber'
                                     'metal loop'
         save_
    
    
    ###########################
    # DIFFRN_MEASUREMENT_AXIS #
    ###########################
    
    
    save_DIFFRN_MEASUREMENT_AXIS
        _category.description
    ;    Data items in the DIFFRN_MEASUREMENT_AXIS category associate
         axes with goniometers.
    ;
        _category.id                   diffrn_measurement_axis
        _category.mandatory_code       no
         loop_
        _category_key.name
                                  '_diffrn_measurement_axis.measurement_device'
                                    '_diffrn_measurement_axis.measurement_id'
                                    '_diffrn_measurement_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_measurement_axis.axis_id
        _item_description.description
    ;              This data item is a pointer to _axis.id in
                   the AXIS category.
    ;
        _item.name                  '_diffrn_measurement_axis.axis_id'
        _item.category_id             diffrn_measurement_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_measurement_axis.measurement_device
        _item_description.description
    ;              This data item is a pointer to _diffrn_measurement.device
                   in the DIFFRN_MEASUREMENT category.
    ;
        _item.name
          '_diffrn_measurement_axis.measurement_device'
        _item.category_id             diffrn_measurement_axis
        _item.mandatory_code          implicit
        _item_type.code               text
         save_
    
    
    save__diffrn_measurement_axis.measurement_id
        _item_description.description
    ;              This data item is a pointer to _diffrn_measurement.id in
                   the DIFFRN_MEASUREMENT category.
    
                   This item was previously named _diffrn_measurement_axis.id,
                   which is now a deprecated name.  The old name is
                   provided as an alias but should not be used for new work.
    ;
        _item.name                  '_diffrn_measurement_axis.measurement_id'
        _item.category_id             diffrn_measurement_axis
        _item.mandatory_code          implicit
        _item_aliases.alias_name    '_diffrn_measurement_axis.id'
        _item_aliases.dictionary      cif_img.dic
        _item_aliases.version         1.0
        _item_type.code               code
         save_
    
    
    ####################
    # DIFFRN_RADIATION #
    ####################
    
    
    save_DIFFRN_RADIATION
        _category.description
    ;              Data items in the DIFFRN_RADIATION category describe
                   the radiation used for measuring diffraction intensities,
                   its collimation and monochromatization before the sample.
    
                   Post-sample treatment of the beam is described by data
                   items in the DIFFRN_DETECTOR category.
    ;
        _category.id                  diffrn_radiation
        _category.mandatory_code      no
        _category_key.name          '_diffrn_radiation.diffrn_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;   Example 1 - based on PDB entry 5HVP and laboratory records for the
                    structure corresponding to PDB entry 5HVP
    ;
    ;
        _diffrn_radiation.diffrn_id            'set1'
    
        _diffrn_radiation.collimation          '0.3 mm double pinhole'
        _diffrn_radiation.monochromator        'graphite'
        _diffrn_radiation.type                 'Cu K\a'
        _diffrn_radiation.wavelength_id         1
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;    Example 2 - based on data set TOZ of Willis, Beckwith & Tozer
                    [Acta Cryst. (1991), C47, 2276-2277].
    ;
    ;
        _diffrn_radiation.wavelength_id    1
        _diffrn_radiation.type             'Cu K\a'
        _diffrn_radiation.monochromator    'graphite'
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
         save_
    
    save__diffrn_radiation.collimation
        _item_description.description
    ;              The collimation or focusing applied to the radiation.
    ;
        _item.name                  '_diffrn_radiation.collimation'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_collimation'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          '0.3 mm double-pinhole'
                                     '0.5 mm'
                                     'focusing mirrors'
         save_
    
    
    save__diffrn_radiation.diffrn_id
        _item_description.description
    ;              This data item is a pointer to _diffrn.id in the DIFFRN
                   category.
    ;
        _item.name                  '_diffrn_radiation.diffrn_id'
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    
    save__diffrn_radiation.div_x_source
        _item_description.description
    ;              Beam crossfire in degrees parallel to the laboratory X axis
                   (see AXIS category).
    
                   This is a characteristic of the X-ray beam as it illuminates
                   the sample (or specimen) after all monochromation and
                   collimation.
    
                   This is the standard uncertainty (e.s.d.)  of the directions of
                   photons in the XZ plane around the mean source beam
                   direction.
    
                   Note that for some synchrotrons this value is specified
                   in milliradians, in which case a conversion is needed.
                   To convert a value in milliradians to a value in degrees,
                   multiply by 0.180 and divide by \p.
    ;
        _item.name                  '_diffrn_radiation.div_x_source'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_type.code               float
        _item_units.code              degrees
         save_
    
    
    save__diffrn_radiation.div_y_source
        _item_description.description
    ;              Beam crossfire in degrees parallel to the laboratory Y axis
                   (see AXIS category).
    
                   This is a characteristic of the X-ray beam as it illuminates
                   the sample (or specimen) after all monochromation and
                   collimation.
    
                   This is the standard uncertainty (e.s.d.) of the directions
                   of photons in the YZ plane around the mean source beam
                   direction.
    
                   Note that for some synchrotrons this value is specified
                   in milliradians, in which case a conversion is needed.
                   To convert a value in milliradians to a value in degrees,
                   multiply by 0.180 and divide by \p.
    ;
        _item.name                  '_diffrn_radiation.div_y_source'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_type.code               float
        _item_units.code              degrees
        _item_default.value           0.0
         save_
    
    
    save__diffrn_radiation.div_x_y_source
        _item_description.description
    ;              Beam crossfire correlation degrees^2^ between the
                   crossfire laboratory X-axis component and the crossfire
                   laboratory Y-axis component (see AXIS category).
    
                   This is a characteristic of the X-ray beam as it illuminates
                   the sample (or specimen) after all monochromation and
                   collimation.
    
                   This is the mean of the products of the deviations of the
                   direction of each photon in XZ plane times the deviations
                   of the direction of the same photon in the YZ plane
                   around the mean source beam direction.  This will be zero
                   for uncorrelated crossfire.
    
                   Note that some synchrotrons, this value is specified in
                   milliradians^2^, in which case a conversion would be needed.
                   To go from a value in milliradians^2^ to a value in
                   degrees^2^, multiply by 0.180^2^ and divide by \p^2^.
    
    ;
        _item.name                  '_diffrn_radiation.div_x_y_source'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_type.code               float
        _item_units.code              degrees_squared
        _item_default.value           0.0
         save_
    
    save__diffrn_radiation.filter_edge
        _item_description.description
    ;              Absorption edge in \%Angstroms of the radiation filter used.
    ;
        _item.name                  '_diffrn_radiation.filter_edge'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_filter_edge'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
        _item_units.code              angstroms
         save_
    
    save__diffrn_radiation.inhomogeneity
        _item_description.description
    ;              Half-width in millimetres of the incident beam in the
                   direction perpendicular to the diffraction plane.
    ;
        _item.name                  '_diffrn_radiation.inhomogeneity'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_inhomogeneity'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
        _item_units.code              millimetres
         save_
    
    save__diffrn_radiation.monochromator
        _item_description.description
    ;              The method used to obtain monochromatic radiation. If a
                   monochromator crystal is used, the material and the
                   indices of the Bragg reflection are specified.
    ;
        _item.name                  '_diffrn_radiation.monochromator'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_monochromator'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               text
         loop_
        _item_examples.case          'Zr filter'
                                     'Ge 220'
                                     'none'
                                     'equatorial mounted graphite'
         save_
    
    save__diffrn_radiation.polarisn_norm
        _item_description.description
    ;              The angle in degrees, as viewed from the specimen, between the
                   perpendicular component of the polarization and the diffraction
                   plane. See _diffrn_radiation_polarisn_ratio.
    ;
        _item.name                  '_diffrn_radiation.polarisn_norm'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_polarisn_norm'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum
        _item_range.minimum           90.0  90.0
                                      90.0 -90.0
                                     -90.0 -90.0
        _item_type.code               float
        _item_units.code              degrees
         save_
    
    save__diffrn_radiation.polarisn_ratio
        _item_description.description
    ;              Polarization ratio of the diffraction beam incident on the
                   crystal. This is the ratio of the perpendicularly polarized to
                   the parallel polarized component of the radiation. The
                   perpendicular component forms an angle of
                   _diffrn_radiation.polarisn_norm to the normal to the
                   diffraction plane of the sample (i.e. the plane containing
                   the incident and reflected beams).
    ;
        _item.name                  '_diffrn_radiation.polarisn_ratio'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_polarisn_ratio'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
         loop_
        _item_range.maximum
        _item_range.minimum            .    0.0
                                      0.0   0.0
        _item_type.code               float
         save_
    
    
    
    save__diffrn_radiation.polarizn_source_norm
        _item_description.description
    ;              The angle in degrees, as viewed from the specimen, between
                   the normal to the polarization plane and the laboratory Y
                   axis as defined in the AXIS category.
    
                   Note that this is the angle of polarization of the source
                   photons, either directly from a synchrotron beamline or
                   from a monochromater.
    
                   This differs from the value of
                   _diffrn_radiation.polarisn_norm
                   in that _diffrn_radiation.polarisn_norm refers to
                   polarization relative to the diffraction plane rather than
                   to the laboratory axis system.
    
                   In the case of an unpolarized beam, or a beam with true
                   circular polarization, in which no single plane of
                   polarization can be determined, the plane should be taken
                   as the XZ plane and the angle as 0.
    
                   See _diffrn_radiation.polarizn_source_ratio.
    ;
        _item.name                  '_diffrn_radiation.polarizn_source_norm'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
         loop_
        _item_range.maximum
        _item_range.minimum           90.0   90.0
                                      90.0  -90.0
                                     -90.0  -90.0
        _item_type.code               float
        _item_units.code              degrees
        _item_default.value           0.0
         save_
    
    
    save__diffrn_radiation.polarizn_source_ratio
        _item_description.description
    ;              (Ip-In)/(Ip+In), where Ip is the intensity
                   (amplitude squared) of the electric vector in the plane of
                   polarization and In is the intensity (amplitude squared)
                   of the electric vector in the plane of the normal to the
                   plane of polarization.
    
                   In the case of an unpolarized beam, or a beam with true
                   circular polarization, in which no single plane of
                   polarization can be determined, the plane is to be taken
                   as the XZ plane and the normal is parallel to the Y axis.
    
                   Thus, if there was complete polarization in the plane of
                   polarization, the value of
                   _diffrn_radiation.polarizn_source_ratio would be 1, and
                   for an unpolarized beam
                   _diffrn_radiation.polarizn_source_ratio would have a
                   value of 0.
    
                   If the X axis has been chosen to lie in the plane of
                   polarization, this definition will agree with the definition
                   of 'MONOCHROMATOR' in the Denzo glossary, and values of near
                   1 should be expected for a bending-magnet source.  However,
                   if the X axis were perpendicular to the polarization plane
                   (not a common choice), then the Denzo value would be the
                   negative of _diffrn_radiation.polarizn_source_ratio.
    
                   See http://www.hkl-xray.com for information on Denzo and
                   Otwinowski & Minor (1997).
    
                   This differs both in the choice of ratio and choice of
                   orientation from _diffrn_radiation.polarisn_ratio, which,
                   unlike _diffrn_radiation.polarizn_source_ratio, is
                   unbounded.
    
                   Reference: Otwinowski, Z. & Minor, W. (1997). 'Processing of
                   X-ray diffraction data collected in oscillation mode.' Methods
                   Enzymol. 276, 307-326.
    ;
        _item.name                  '_diffrn_radiation.polarizn_source_ratio'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
         loop_
        _item_range.maximum
        _item_range.minimum           1.0    1.0
                                      1.0   -1.0
                                     -1.0   -1.0
        _item_type.code               float
         save_
    
    
    save__diffrn_radiation.probe
        _item_description.description
    ;              Name of the type of radiation used. It is strongly
                   recommended that this be given so that the
                   probe radiation is clearly specified.
    ;
        _item.name                  '_diffrn_radiation.probe'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_probe'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               line
         loop_
        _item_enumeration.value      'x-ray'
                                     'neutron'
                                     'electron'
                                     'gamma'
         save_
    
    save__diffrn_radiation.type
        _item_description.description
    ;              The nature of the radiation. This is typically a description
                   of the X-ray wavelength in Siegbahn notation.
    ;
        _item.name                  '_diffrn_radiation.type'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_type'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               line
         loop_
        _item_examples.case          'CuK\a'
                                     'Cu K\a~1~'
                                     'Cu K-L~2,3~'
                                     'white-beam'
    
         save_
    
    save__diffrn_radiation.xray_symbol
        _item_description.description
    ;              The IUPAC symbol for the X-ray wavelength for the probe
                   radiation.
    ;
        _item.name                  '_diffrn_radiation.xray_symbol'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          no
        _item_aliases.alias_name    '_diffrn_radiation_xray_symbol'
        _item_aliases.dictionary      cif_core.dic
        _item_aliases.version         2.0.1
        _item_type.code               line
         loop_
        _item_enumeration.value
        _item_enumeration.detail     'K-L~3~'
                                     'K\a~1~ in older Siegbahn notation'
                                     'K-L~2~'
                                     'K\a~2~ in older Siegbahn notation'
                                     'K-M~3~'
                                     'K\b~1~ in older Siegbahn notation'
                                     'K-L~2,3~'
                                     'use where K-L~3~ and K-L~2~ are not resolved'
         save_
    
    save__diffrn_radiation.wavelength_id
        _item_description.description
    ;              This data item is a pointer to
                   _diffrn_radiation_wavelength.id in the
                   DIFFRN_RADIATION_WAVELENGTH category.
    ;
        _item.name                  '_diffrn_radiation.wavelength_id'
        _item.category_id             diffrn_radiation
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    
    ################
    # DIFFRN_REFLN #
    ################
    
    
    save_DIFFRN_REFLN
        _category.description
    ;    This category redefinition has been added to extend the key of
         the standard DIFFRN_REFLN category.
    ;
        _category.id                   diffrn_refln
        _category.mandatory_code       no
        _category_key.name             '_diffrn_refln.frame_id'
         loop_
        _category_group.id             'inclusive_group'
                                       'diffrn_group'
         save_
    
    
    save__diffrn_refln.frame_id
        _item_description.description
    ;              This item is a pointer to _diffrn_data_frame.id
                   in the DIFFRN_DATA_FRAME category.
    ;
        _item.name                  '_diffrn_refln.frame_id'
        _item.category_id             diffrn_refln
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    ###############
    # DIFFRN_SCAN #
    ###############
    
    save_DIFFRN_SCAN
        _category.description
    ;    Data items in the DIFFRN_SCAN category describe the parameters of one
         or more scans, relating axis positions to frames.
    
    ;
        _category.id                   diffrn_scan
        _category.mandatory_code       no
        _category_key.name            '_diffrn_scan.id'
         loop_
        _category_group.id            'inclusive_group'
                                      'diffrn_group'
         loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;   Example 1 - derived from a suggestion by R. M. Sweet.
    
       The vector of each axis is not given here, because it is provided in
       the AXIS category.  By making _diffrn_scan_axis.scan_id and
       _diffrn_scan_axis.axis_id keys of the DIFFRN_SCAN_AXIS category,
       an arbitrary number of scanning and fixed axes can be specified for a
       scan.  In this example, three rotation axes and one translation axis
       at nonzero values are specified, with one axis stepping.  There is no
       reason why more axes could not have been specified to step. Range
       information has been specified, but note that it can be calculated from
       the  number of frames and the increment, so the data item
       _diffrn_scan_axis.angle_range could be dropped.
    
       Both the sweep data and the data for a single frame are specified.
    
       Note that the information on how the axes are stepped is given twice,
       once in terms of the overall averages in the value of
       _diffrn_scan.integration_time and the values for DIFFRN_SCAN_AXIS,
       and precisely for the given frame in the value for
       _diffrn_scan_frame.integration_time and the values for
       DIFFRN_SCAN_FRAME_AXIS.  If dose-related adjustments are made to
       scan times and nonlinear stepping is done, these values may differ.
       Therefore, in interpreting the data for a particular frame it is
       important to use the frame-specific data.
    ;
    ;
          _diffrn_scan.id                   1
          _diffrn_scan.date_start         '2001-11-18T03:26:42'
          _diffrn_scan.date_end           '2001-11-18T03:36:45'
          _diffrn_scan.integration_time    3.0
          _diffrn_scan.frame_id_start      mad_L2_000
          _diffrn_scan.frame_id_end        mad_L2_200
          _diffrn_scan.frames              201
    
           loop_
          _diffrn_scan_axis.scan_id
          _diffrn_scan_axis.axis_id
          _diffrn_scan_axis.angle_start
          _diffrn_scan_axis.angle_range
          _diffrn_scan_axis.angle_increment
          _diffrn_scan_axis.displacement_start
          _diffrn_scan_axis.displacement_range
          _diffrn_scan_axis.displacement_increment
    
           1 omega 200.0 20.0 0.1 . . .
           1 kappa -40.0  0.0 0.0 . . .
           1 phi   127.5  0.0 0.0 . . .
           1 tranz  . . .   2.3 0.0 0.0
    
          _diffrn_scan_frame.scan_id                   1
          _diffrn_scan_frame.date               '2001-11-18T03:27:33'
          _diffrn_scan_frame.integration_time    3.0
          _diffrn_scan_frame.frame_id            mad_L2_018
          _diffrn_scan_frame.frame_number        18
    
          loop_
          _diffrn_scan_frame_axis.frame_id
          _diffrn_scan_frame_axis.axis_id
          _diffrn_scan_frame_axis.angle
          _diffrn_scan_frame_axis.angle_increment
          _diffrn_scan_frame_axis.displacement
          _diffrn_scan_frame_axis.displacement_increment
    
           mad_L2_018 omega 201.8  0.1 . .
           mad_L2_018 kappa -40.0  0.0 . .
           mad_L2_018 phi   127.5  0.0 . .
           mad_L2_018 tranz  .     .  2.3 0.0
    ;
    
    ;  Example 2 - a more extensive example (R. M. Sweet, P. J. Ellis &
       H. J. Bernstein).
    
       A detector is placed 240 mm along the Z axis from the goniometer.
       This leads to a choice:  either the axes of
       the detector are defined at the origin, and then a Z setting of -240
       is entered, or the axes are defined with the necessary Z offset.
       In this case, the setting is used and the offset is left as zero.
       This axis is called DETECTOR_Z.
    
       The axis for positioning the detector in the Y direction depends
       on the detector Z axis.  This axis is called DETECTOR_Y.
    
       The axis for positioning the detector in the X direction depends
       on the detector Y axis (and therefore on the detector Z axis).
       This axis is called DETECTOR_X.
    
       This detector may be rotated around the Y axis.  This rotation axis
       depends on the three translation axes.  It is called DETECTOR_PITCH.
    
       A coordinate system is defined on the face of the detector in terms of
       2300 0.150 mm pixels in each direction.  The ELEMENT_X axis is used to
       index the first array index of the data array and the ELEMENT_Y
       axis is used to index the second array index.  Because the pixels
       are 0.150mm x 0.150mm, the centre of the first pixel is at (0.075,
       0.075) in this coordinate system.
    ;
    
    ;    ###CBF: VERSION 1.1
    
         data_image_1
    
         # category DIFFRN
         _diffrn.id P6MB
         _diffrn.crystal_id P6MB_CRYSTAL7
    
         # category DIFFRN_SOURCE
         loop_
         _diffrn_source.diffrn_id
         _diffrn_source.source
         _diffrn_source.type
          P6MB synchrotron 'SSRL beamline 9-1'
    
         # category DIFFRN_RADIATION
         loop_
         _diffrn_radiation.diffrn_id
         _diffrn_radiation.wavelength_id
         _diffrn_radiation.monochromator
         _diffrn_radiation.polarizn_source_ratio
         _diffrn_radiation.polarizn_source_norm
         _diffrn_radiation.div_x_source
         _diffrn_radiation.div_y_source
         _diffrn_radiation.div_x_y_source
          P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08
         0.01 0.00
    
         # category DIFFRN_RADIATION_WAVELENGTH
         loop_
         _diffrn_radiation_wavelength.id
         _diffrn_radiation_wavelength.wavelength
         _diffrn_radiation_wavelength.wt
          WAVELENGTH1 0.98 1.0
    
         # category DIFFRN_DETECTOR
         loop_
         _diffrn_detector.diffrn_id
         _diffrn_detector.id
         _diffrn_detector.type
         _diffrn_detector.number_of_axes
          P6MB MAR345-SN26 'MAR 345' 4
    
         # category DIFFRN_DETECTOR_AXIS
         loop_
         _diffrn_detector_axis.detector_id
         _diffrn_detector_axis.axis_id
          MAR345-SN26 DETECTOR_X
          MAR345-SN26 DETECTOR_Y
          MAR345-SN26 DETECTOR_Z
          MAR345-SN26 DETECTOR_PITCH
    
         # category DIFFRN_DETECTOR_ELEMENT
         loop_
         _diffrn_detector_element.id
         _diffrn_detector_element.detector_id
          ELEMENT1 MAR345-SN26
    
         # category DIFFRN_DATA_FRAME
         loop_
         _diffrn_data_frame.id
         _diffrn_data_frame.detector_element_id
         _diffrn_data_frame.array_id
         _diffrn_data_frame.binary_id
          FRAME1 ELEMENT1 ARRAY1 1
    
         # category DIFFRN_MEASUREMENT
         loop_
         _diffrn_measurement.diffrn_id
         _diffrn_measurement.id
         _diffrn_measurement.number_of_axes
         _diffrn_measurement.method
          P6MB GONIOMETER 3 rotation
    
         # category DIFFRN_MEASUREMENT_AXIS
         loop_
         _diffrn_measurement_axis.measurement_id
         _diffrn_measurement_axis.axis_id
          GONIOMETER GONIOMETER_PHI
          GONIOMETER GONIOMETER_KAPPA
          GONIOMETER GONIOMETER_OMEGA
    
         # category DIFFRN_SCAN
         loop_
         _diffrn_scan.id
         _diffrn_scan.frame_id_start
         _diffrn_scan.frame_id_end
         _diffrn_scan.frames
          SCAN1 FRAME1 FRAME1 1
    
         # category DIFFRN_SCAN_AXIS
         loop_
         _diffrn_scan_axis.scan_id
         _diffrn_scan_axis.axis_id
         _diffrn_scan_axis.angle_start
         _diffrn_scan_axis.angle_range
         _diffrn_scan_axis.angle_increment
         _diffrn_scan_axis.displacement_start
         _diffrn_scan_axis.displacement_range
         _diffrn_scan_axis.displacement_increment
          SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0
          SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0
          SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0
          SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0
          SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0
          SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0
          SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0
    
         # category DIFFRN_SCAN_FRAME
         loop_
         _diffrn_scan_frame.frame_id
         _diffrn_scan_frame.frame_number
         _diffrn_scan_frame.integration_time
         _diffrn_scan_frame.scan_id
         _diffrn_scan_frame.date
          FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48
    
         # category DIFFRN_SCAN_FRAME_AXIS
         loop_
         _diffrn_scan_frame_axis.frame_id
         _diffrn_scan_frame_axis.axis_id
         _diffrn_scan_frame_axis.angle
         _diffrn_scan_frame_axis.displacement
          FRAME1 GONIOMETER_OMEGA 12.0 0.0
          FRAME1 GONIOMETER_KAPPA 23.3 0.0
          FRAME1 GONIOMETER_PHI -165.8 0.0
          FRAME1 DETECTOR_Z 0.0 -240.0
          FRAME1 DETECTOR_Y 0.0 0.6
          FRAME1 DETECTOR_X 0.0 -0.5
          FRAME1 DETECTOR_PITCH 0.0 0.0
    
         # category AXIS
         loop_
         _axis.id
         _axis.type
         _axis.equipment
         _axis.depends_on
         _axis.vector[1] _axis.vector[2] _axis.vector[3]
         _axis.offset[1] _axis.offset[2] _axis.offset[3]
          GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . .
          GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279
          0 0.76604 . . .
          GONIOMETER_PHI   rotation goniometer GONIOMETER_KAPPA 1 0 0
         . . .
          SOURCE           general source . 0 0 1 . . .
          GRAVITY          general gravity . 0 -1 0 . . .
          DETECTOR_Z       translation detector . 0 0 1 0 0 0
          DETECTOR_Y       translation detector DETECTOR_Z 0 1 0 0 0 0
          DETECTOR_X       translation detector DETECTOR_Y 1 0 0 0 0 0
          DETECTOR_PITCH   rotation    detector DETECTOR_X 0 1 0 0 0 0
          ELEMENT_X        translation detector DETECTOR_PITCH
         1 0 0 172.43 -172.43 0
          ELEMENT_Y        translation detector ELEMENT_X
         0 1 0 0 0 0
    
         # category ARRAY_STRUCTURE_LIST
         loop_
         _array_structure_list.array_id
         _array_structure_list.index
         _array_structure_list.dimension
         _array_structure_list.precedence
         _array_structure_list.direction
         _array_structure_list.axis_set_id
          ARRAY1 1 2300 1 increasing ELEMENT_X
          ARRAY1 2 2300 2 increasing ELEMENT_Y
    
         # category ARRAY_STRUCTURE_LIST_AXIS
         loop_
         _array_structure_list_axis.axis_set_id
         _array_structure_list_axis.axis_id
         _array_structure_list_axis.displacement
         _array_structure_list_axis.displacement_increment
          ELEMENT_X ELEMENT_X 0.075 0.150
          ELEMENT_Y ELEMENT_Y 0.075 0.150
    
         # category ARRAY_ELEMENT_SIZE
         loop_
         _array_element_size.array_id
         _array_element_size.index
         _array_element_size.size
          ARRAY1 1 150e-6
          ARRAY1 2 150e-6
    
         # category ARRAY_INTENSITIES
         loop_
         _array_intensities.array_id
         _array_intensities.binary_id
         _array_intensities.linearity
         _array_intensities.gain
         _array_intensities.gain_esd
         _array_intensities.overload
         _array_intensities.undefined_value
          ARRAY1 1 linear 1.15 0.2 240000 0
    
          # category ARRAY_STRUCTURE
          loop_
          _array_structure.id
          _array_structure.encoding_type
          _array_structure.compression_type
          _array_structure.byte_order
          ARRAY1 "signed 32-bit integer" packed little_endian
    
         # category ARRAY_DATA
         loop_
         _array_data.array_id
         _array_data.binary_id
         _array_data.data
          ARRAY1 1
         ;
         --CIF-BINARY-FORMAT-SECTION--
         Content-Type: application/octet-stream;
             conversions="x-CBF_PACKED"
         Content-Transfer-Encoding: BASE64
         X-Binary-Size: 3801324
         X-Binary-ID: 1
         X-Binary-Element-Type: "signed 32-bit integer"
         Content-MD5: 07lZFvF+aOcW85IN7usl8A==
    
         AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg
         ...
         8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE
    
         --CIF-BINARY-FORMAT-SECTION----
         ;
    ;
    
    ;   Example 3 - Example 2 revised for a spiral scan (R. M. Sweet,
        P. J. Ellis & H. J. Bernstein).
    
       A detector is placed 240 mm along the Z axis from the
       goniometer, as in Example 2 above, but in this example the
       image plate is scanned in a spiral pattern from the outside edge in.
    
       The axis for positioning the detector in the Y direction depends
       on the detector Z axis.  This axis is called DETECTOR_Y.
    
       The axis for positioning the detector in the X direction depends
       on the detector Y axis (and therefore on the detector Z axis).
       This axis is called DETECTOR_X.
    
       This detector may be rotated around the Y axis.  This rotation axis
       depends on the three translation axes.  It is called DETECTOR_PITCH.
    
       A coordinate system is defined on the face of the detector in
       terms of a coupled rotation axis and radial scan axis to form
       a spiral scan.  The rotation axis is called  ELEMENT_ROT  and the
       radial axis is called ELEMENT_RAD.  A 150 micrometre radial pitch
       and a 75 micrometre 'constant velocity' angular pitch are assumed.
    
       Indexing is carried out first on the rotation axis and the radial axis
       is made to be dependent on it.
    
       The two axes are coupled to form an axis set ELEMENT_SPIRAL.
    ;
    ;    ###CBF: VERSION 1.1
    
         data_image_1
    
         # category DIFFRN
         _diffrn.id P6MB
         _diffrn.crystal_id P6MB_CRYSTAL7
    
         # category DIFFRN_SOURCE
         loop_
         _diffrn_source.diffrn_id
         _diffrn_source.source
         _diffrn_source.type
          P6MB synchrotron 'SSRL beamline 9-1'
    
         # category DIFFRN_RADIATION
              loop_
         _diffrn_radiation.diffrn_id
         _diffrn_radiation.wavelength_id
         _diffrn_radiation.monochromator
         _diffrn_radiation.polarizn_source_ratio
         _diffrn_radiation.polarizn_source_norm
         _diffrn_radiation.div_x_source
         _diffrn_radiation.div_y_source
         _diffrn_radiation.div_x_y_source
          P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08
         0.01 0.00
    
         # category DIFFRN_RADIATION_WAVELENGTH
         loop_
         _diffrn_radiation_wavelength.id
         _diffrn_radiation_wavelength.wavelength
         _diffrn_radiation_wavelength.wt
          WAVELENGTH1 0.98 1.0
    
         # category DIFFRN_DETECTOR
         loop_
         _diffrn_detector.diffrn_id
         _diffrn_detector.id
         _diffrn_detector.type
         _diffrn_detector.number_of_axes
          P6MB MAR345-SN26 'MAR 345' 4
    
         # category DIFFRN_DETECTOR_AXIS
         loop_
         _diffrn_detector_axis.detector_id
         _diffrn_detector_axis.axis_id
          MAR345-SN26 DETECTOR_X
          MAR345-SN26 DETECTOR_Y
          MAR345-SN26 DETECTOR_Z
          MAR345-SN26 DETECTOR_PITCH
    
         # category DIFFRN_DETECTOR_ELEMENT
         loop_
         _diffrn_detector_element.id
         _diffrn_detector_element.detector_id
          ELEMENT1 MAR345-SN26
    
         # category DIFFRN_DATA_FRAME
         loop_
         _diffrn_data_frame.id
         _diffrn_data_frame.detector_element_id
         _diffrn_data_frame.array_id
         _diffrn_data_frame.binary_id
          FRAME1 ELEMENT1 ARRAY1 1
    
         # category DIFFRN_MEASUREMENT
         loop_
         _diffrn_measurement.diffrn_id
         _diffrn_measurement.id
         _diffrn_measurement.number_of_axes
         _diffrn_measurement.method
          P6MB GONIOMETER 3 rotation
    
         # category DIFFRN_MEASUREMENT_AXIS
         loop_
         _diffrn_measurement_axis.measurement_id
         _diffrn_measurement_axis.axis_id
          GONIOMETER GONIOMETER_PHI
          GONIOMETER GONIOMETER_KAPPA
          GONIOMETER GONIOMETER_OMEGA
    
         # category DIFFRN_SCAN
         loop_
         _diffrn_scan.id
         _diffrn_scan.frame_id_start
         _diffrn_scan.frame_id_end
         _diffrn_scan.frames
          SCAN1 FRAME1 FRAME1 1
    
         # category DIFFRN_SCAN_AXIS
         loop_
         _diffrn_scan_axis.scan_id
         _diffrn_scan_axis.axis_id
         _diffrn_scan_axis.angle_start
         _diffrn_scan_axis.angle_range
         _diffrn_scan_axis.angle_increment
         _diffrn_scan_axis.displacement_start
         _diffrn_scan_axis.displacement_range
         _diffrn_scan_axis.displacement_increment
          SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0
          SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0
          SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0
          SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0
          SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0
          SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0
          SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0
    
         # category DIFFRN_SCAN_FRAME
         loop_
         _diffrn_scan_frame.frame_id
         _diffrn_scan_frame.frame_number
         _diffrn_scan_frame.integration_time
         _diffrn_scan_frame.scan_id
         _diffrn_scan_frame.date
          FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48
    
         # category DIFFRN_SCAN_FRAME_AXIS
         loop_
         _diffrn_scan_frame_axis.frame_id
         _diffrn_scan_frame_axis.axis_id
         _diffrn_scan_frame_axis.angle
         _diffrn_scan_frame_axis.displacement
          FRAME1 GONIOMETER_OMEGA 12.0 0.0
          FRAME1 GONIOMETER_KAPPA 23.3 0.0
          FRAME1 GONIOMETER_PHI -165.8 0.0
          FRAME1 DETECTOR_Z 0.0 -240.0
          FRAME1 DETECTOR_Y 0.0 0.6
          FRAME1 DETECTOR_X 0.0 -0.5
          FRAME1 DETECTOR_PITCH 0.0 0.0
    
         # category AXIS
         loop_
         _axis.id
         _axis.type
         _axis.equipment
         _axis.depends_on
         _axis.vector[1] _axis.vector[2] _axis.vector[3]
         _axis.offset[1] _axis.offset[2] _axis.offset[3]
          GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . .
          GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279
          0 0.76604 . . .
          GONIOMETER_PHI   rotation goniometer GONIOMETER_KAPPA 1 0 0
         . . .
          SOURCE           general source . 0 0 1 . . .
          GRAVITY          general gravity . 0 -1 0 . . .
          DETECTOR_Z       translation detector . 0 0 1 0 0 0
          DETECTOR_Y       translation detector DETECTOR_Z 0 1 0 0 0 0
          DETECTOR_X       translation detector DETECTOR_Y 1 0 0 0 0 0
          DETECTOR_PITCH   rotation    detector DETECTOR_X 0 1 0 0 0 0
          ELEMENT_ROT      translation detector DETECTOR_PITCH 0 0 1 0 0 0
          ELEMENT_RAD      translation detector ELEMENT_ROT 0 1 0 0 0 0
    
         # category ARRAY_STRUCTURE_LIST
         loop_
         _array_structure_list.array_id
         _array_structure_list.index
         _array_structure_list.dimension
         _array_structure_list.precedence
         _array_structure_list.direction
         _array_structure_list.axis_set_id
          ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL
    
         # category ARRAY_STRUCTURE_LIST_AXIS
         loop_
         _array_structure_list_axis.axis_set_id
         _array_structure_list_axis.axis_id
         _array_structure_list_axis.angle
         _array_structure_list_axis.displacement
         _array_structure_list_axis.angular_pitch
         _array_structure_list_axis.radial_pitch
          ELEMENT_SPIRAL ELEMENT_ROT 0    .  0.075   .
          ELEMENT_SPIRAL ELEMENT_RAD . 172.5  .    -0.150
    
         # category ARRAY_ELEMENT_SIZE
         # the actual pixels are 0.075 by 0.150 mm
         # We give the coarser dimension here.
         loop_
         _array_element_size.array_id
         _array_element_size.index
         _array_element_size.size
          ARRAY1 1 150e-6
    
         # category ARRAY_INTENSITIES
         loop_
         _array_intensities.array_id
         _array_intensities.binary_id
         _array_intensities.linearity
         _array_intensities.gain
         _array_intensities.gain_esd
         _array_intensities.overload
         _array_intensities.undefined_value
          ARRAY1 1 linear 1.15 0.2 240000 0
    
          # category ARRAY_STRUCTURE
          loop_
          _array_structure.id
          _array_structure.encoding_type
          _array_structure.compression_type
          _array_structure.byte_order
          ARRAY1 "signed 32-bit integer" packed little_endian
    
         # category ARRAY_DATA
         loop_
         _array_data.array_id
         _array_data.binary_id
         _array_data.data
          ARRAY1 1
         ;
         --CIF-BINARY-FORMAT-SECTION--
         Content-Type: application/octet-stream;
             conversions="x-CBF_PACKED"
         Content-Transfer-Encoding: BASE64
         X-Binary-Size: 3801324
         X-Binary-ID: 1
         X-Binary-Element-Type: "signed 32-bit integer"
         Content-MD5: 07lZFvF+aOcW85IN7usl8A==
    
         AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg
         ...
         8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE
    
         --CIF-BINARY-FORMAT-SECTION----
         ;
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
           save_
    
    
    save__diffrn_scan.id
        _item_description.description
    ;             The value of _diffrn_scan.id uniquely identifies each
                  scan.  The identifier is used to tie together all the
                  information about the scan.
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
           '_diffrn_scan.id'                 diffrn_scan             yes
           '_diffrn_scan_axis.scan_id'       diffrn_scan_axis        yes
           '_diffrn_scan_frame.scan_id'      diffrn_scan_frame       yes
        _item_type.code               code
         loop_
        _item_linked.child_name
        _item_linked.parent_name
           '_diffrn_scan_axis.scan_id'          '_diffrn_scan.id'
           '_diffrn_scan_frame.scan_id'         '_diffrn_scan.id'
         save_
    
    
    save__diffrn_scan.date_end
        _item_description.description
    ;              The date and time of the end of the scan.  Note that this
                   may be an estimate generated during the scan, before the
                   precise time of the end of the scan is known.
    ;
        _item.name                 '_diffrn_scan.date_end'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no
        _item_type.code            yyyy-mm-dd
         save_
    
    
    save__diffrn_scan.date_start
        _item_description.description
    ;              The date and time of the start of the scan.
    ;
        _item.name                 '_diffrn_scan.date_start'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no
        _item_type.code            yyyy-mm-dd
         save_
    
    
    save__diffrn_scan.integration_time
        _item_description.description
    ;              Approximate average time in seconds to integrate each
                   step of the scan.  The precise time for integration
                   of each particular step must be provided in
                   _diffrn_scan_frame.integration_time, even
                   if all steps have the same integration time.
    ;
        _item.name                 '_diffrn_scan.integration_time'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no
        _item_type.code            float
        _item_units.code           'seconds'
         loop_
        _item_range.maximum
        _item_range.minimum
                                .   0.0
         save_
    
    
    save__diffrn_scan.frame_id_start
        _item_description.description
    ;              The value of this data item is the identifier of the
                   first frame in the scan.
    
                   This item is a pointer to _diffrn_data_frame.id in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name                 '_diffrn_scan.frame_id_start'
        _item.category_id          diffrn_scan
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan.frame_id_end
        _item_description.description
    ;              The value of this data item is the identifier of the
                   last frame in the scan.
    
                   This item is a pointer to _diffrn_data_frame.id in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name                 '_diffrn_scan.frame_id_end'
        _item.category_id          diffrn_scan
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan.frames
        _item_description.description
    ;              The value of this data item is the number of frames in
                   the scan.
    ;
        _item.name                 '_diffrn_scan.frames'
        _item.category_id          diffrn_scan
        _item.mandatory_code       no
        _item_type.code            int
         loop_
        _item_range.maximum
        _item_range.minimum
                                .   1
                                1   1
         save_
    
    
    ####################
    # DIFFRN_SCAN_AXIS #
    ####################
    
    save_DIFFRN_SCAN_AXIS
        _category.description
    ;    Data items in the DIFFRN_SCAN_AXIS category describe the settings of
         axes for particular scans.  Unspecified axes are assumed to be at
         their zero points.
    ;
        _category.id                   diffrn_scan_axis
        _category.mandatory_code       no
         loop_
        _category_key.name
                                      '_diffrn_scan_axis.scan_id'
                                      '_diffrn_scan_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_scan_axis.scan_id
        _item_description.description
    ;              The value of this data item is the identifier of the
                   scan for which axis settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   _diffrn_scan.id.
    
                   This item is a pointer to _diffrn_scan.id in the
                   DIFFRN_SCAN category.
    ;
        _item.name                 '_diffrn_scan_axis.scan_id'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_axis.axis_id
        _item_description.description
    ;              The value of this data item is the identifier of one of
                   the axes for the scan for which settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   _diffrn_scan.id.
    
                   This item is a pointer to _axis.id in the
                   AXIS category.
    ;
        _item.name                 '_diffrn_scan_axis.axis_id'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_axis.angle_start
        _item_description.description
    ;              The starting position for the specified axis in degrees.
    ;
        _item.name                 '_diffrn_scan_axis.angle_start'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.angle_range
        _item_description.description
    ;              The range from the starting position for the specified axis
                   in degrees.
    ;
        _item.name                 '_diffrn_scan_axis.angle_range'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.angle_increment
        _item_description.description
    ;              The increment for each step for the specified axis
                   in degrees.  In general, this will agree with
                   _diffrn_scan_frame_axis.angle_increment. The
                   sum of the values of _diffrn_scan_frame_axis.angle and
                   _diffrn_scan_frame_axis.angle_increment is the
                   angular setting of the axis at the end of the integration
                   time for a given frame.  If the individual frame values
                   vary, then the value of
                   _diffrn_scan_axis.angle_increment will be
                   representative
                   of the ensemble of values of
                   _diffrn_scan_frame_axis.angle_increment (e.g.
                   the mean).
    ;
        _item.name                 '_diffrn_scan_axis.angle_increment'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.angle_rstrt_incr
        _item_description.description
    ;              The increment after each step for the specified axis
                   in degrees.  In general, this will agree with
                   _diffrn_scan_frame_axis.angle_rstrt_incr.  The
                   sum of the values of _diffrn_scan_frame_axis.angle,
                   _diffrn_scan_frame_axis.angle_increment
                   and  _diffrn_scan_frame_axis.angle_rstrt_incr is the
                   angular setting of the axis at the start of the integration
                   time for the next frame relative to a given frame and
                   should equal _diffrn_scan_frame_axis.angle for this
                   next frame.   If the individual frame values
                   vary, then the value of
                   _diffrn_scan_axis.angle_rstrt_incr will be
                   representative
                   of the ensemble of values of
                   _diffrn_scan_frame_axis.angle_rstrt_incr (e.g.
                   the mean).
    ;
        _item.name                 '_diffrn_scan_axis.angle_rstrt_incr'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_axis.displacement_start
        _item_description.description
    ;              The starting position for the specified axis in millimetres.
    ;
        _item.name                 '_diffrn_scan_axis.displacement_start'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_axis.displacement_range
        _item_description.description
    ;              The range from the starting position for the specified axis
                   in millimetres.
    ;
        _item.name                 '_diffrn_scan_axis.displacement_range'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_axis.displacement_increment
        _item_description.description
    ;              The increment for each step for the specified axis
                   in millimetres.  In general, this will agree with
                   _diffrn_scan_frame_axis.displacement_increment.
                   The sum of the values of
                   _diffrn_scan_frame_axis.displacement and
                   _diffrn_scan_frame_axis.displacement_increment is the
                   angular setting of the axis at the end of the integration
                   time for a given frame.  If the individual frame values
                   vary, then the value of
                   _diffrn_scan_axis.displacement_increment will be
                   representative
                   of the ensemble of values of
                   _diffrn_scan_frame_axis.displacement_increment (e.g.
                   the mean).
    ;
        _item.name                 '_diffrn_scan_axis.displacement_increment'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_axis.displacement_rstrt_incr
        _item_description.description
    ;              The increment for each step for the specified axis
                   in millimetres.  In general, this will agree with
                   _diffrn_scan_frame_axis.displacement_rstrt_incr.
                   The sum of the values of
                   _diffrn_scan_frame_axis.displacement,
                   _diffrn_scan_frame_axis.displacement_increment and
                   _diffrn_scan_frame_axis.displacement_rstrt_incr is the
                   angular setting of the axis at the start of the integration
                   time for the next frame relative to a given frame and
                   should equal _diffrn_scan_frame_axis.displacement
                   for this next frame.  If the individual frame values
                   vary, then the value of
                   _diffrn_scan_axis.displacement_rstrt_incr will be
                   representative
                   of the ensemble of values of
                   _diffrn_scan_frame_axis.displacement_rstrt_incr (e.g.
                   the mean).
    ;
        _item.name                 '_diffrn_scan_axis.displacement_rstrt_incr'
        _item.category_id          diffrn_scan_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    #####################
    # DIFFRN_SCAN_FRAME #
    #####################
    
    save_DIFFRN_SCAN_FRAME
        _category.description
    ;           Data items in the DIFFRN_SCAN_FRAME category describe
                the relationships of particular frames to scans.
    ;
        _category.id                   diffrn_scan_frame
        _category.mandatory_code       no
         loop_
        _category_key.name
                                      '_diffrn_scan_frame.scan_id'
                                      '_diffrn_scan_frame.frame_id'
         loop_
        _category_group.id            'inclusive_group'
                                      'diffrn_group'
         save_
    
    
    save__diffrn_scan_frame.date
        _item_description.description
    ;              The date and time of the start of the frame being scanned.
    ;
        _item.name                 '_diffrn_scan_frame.date'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       no
        _item_type.code            yyyy-mm-dd
         save_
    
    
    save__diffrn_scan_frame.frame_id
        _item_description.description
    ;              The value of this data item is the identifier of the
                   frame being examined.
    
                   This item is a pointer to _diffrn_data_frame.id in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name                 '_diffrn_scan_frame.frame_id'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_frame.frame_number
        _item_description.description
    ;              The value of this data item is the number of the frame
                   within the scan, starting with 1.  It is not necessarily
                   the same as the value of _diffrn_scan_frame.frame_id,
                   but it may be.
    
    ;
        _item.name                 '_diffrn_scan_frame.frame_number'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       no
        _item_type.code            int
         loop_
        _item_range.maximum
        _item_range.minimum
                                .   0
                                0   0
         save_
    
    
    save__diffrn_scan_frame.integration_time
        _item_description.description
    ;              The time in seconds to integrate this step of the scan.
                   This should be the precise time of integration of each
                   particular frame.  The value of this data item should
                   be given explicitly for each frame and not inferred
                   from the value of _diffrn_scan.integration_time.
    ;
        _item.name                 '_diffrn_scan_frame.integration_time'
        _item.category_id          diffrn_scan_frame
        _item.mandatory_code       yes
        _item_type.code            float
        _item_units.code           'seconds'
         loop_
        _item_range.maximum
        _item_range.minimum
                                .   0.0
         save_
    
    
    save__diffrn_scan_frame.scan_id
        _item_description.description
    ;             The value of _diffrn_scan_frame.scan_id identifies the scan
                  containing this frame.
    
                  This item is a pointer to _diffrn_scan.id in the
                  DIFFRN_SCAN category.
    ;
        _item.name             '_diffrn_scan_frame.scan_id'
        _item.category_id        diffrn_scan_frame
        _item.mandatory_code     yes
        _item_type.code          code
         save_
    
    
    ##########################
    # DIFFRN_SCAN_FRAME_AXIS #
    ##########################
    
    save_DIFFRN_SCAN_FRAME_AXIS
        _category.description
    ;    Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the
         settings of axes for particular frames.  Unspecified axes are
         assumed to be at their zero points.  If, for any given frame,
         nonzero values apply for any of the data items in this category,
         those values should be given explicitly in this category and not
         simply inferred from values in DIFFRN_SCAN_AXIS.
    ;
        _category.id                   diffrn_scan_frame_axis
        _category.mandatory_code       no
         loop_
        _category_key.name
                                      '_diffrn_scan_frame_axis.frame_id'
                                      '_diffrn_scan_frame_axis.axis_id'
         loop_
        _category_group.id           'inclusive_group'
                                     'diffrn_group'
         save_
    
    
    save__diffrn_scan_frame_axis.axis_id
        _item_description.description
    ;              The value of this data item is the identifier of one of
                   the axes for the frame for which settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   _diffrn_scan_frame.frame_id.
    
                   This item is a pointer to _axis.id in the
                   AXIS category.
    ;
        _item.name                 '_diffrn_scan_frame_axis.axis_id'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    
    save__diffrn_scan_frame_axis.angle
        _item_description.description
    ;              The setting of the specified axis in degrees for this frame.
                   This is the setting at the start of the integration time.
    ;
        _item.name                 '_diffrn_scan_frame_axis.angle'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_frame_axis.angle_increment
        _item_description.description
    ;              The increment for this frame for the angular setting of
                   the specified axis in degrees.  The sum of the values
                   of _diffrn_scan_frame_axis.angle and
                   _diffrn_scan_frame_axis.angle_increment is the
                   angular setting of the axis at the end of the integration
                   time for this frame.
    ;
        _item.name                 '_diffrn_scan_frame_axis.angle_increment'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_frame_axis.angle_rstrt_incr
        _item_description.description
    ;              The increment after this frame for the angular setting of
                   the specified axis in degrees.  The sum of the values
                   of _diffrn_scan_frame_axis.angle,
                   _diffrn_scan_frame_axis.angle_increment and
                   _diffrn_scan_frame_axis.angle_rstrt_incr is the
                   angular setting of the axis at the start of the integration
                   time for the next frame and should equal
                   _diffrn_scan_frame_axis.angle for this next frame.
    ;
        _item.name               '_diffrn_scan_frame_axis.angle_rstrt_incr'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'degrees'
         save_
    
    
    save__diffrn_scan_frame_axis.displacement
        _item_description.description
    ;              The setting of the specified axis in millimetres for this
                   frame.  This is the setting at the start of the integration
                   time.
    ;
        _item.name               '_diffrn_scan_frame_axis.displacement'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_frame_axis.displacement_increment
        _item_description.description
    ;              The increment for this frame for the displacement setting of
                   the specified axis in millimetres.  The sum of the values
                   of _diffrn_scan_frame_axis.displacement and
                   _diffrn_scan_frame_axis.displacement_increment is the
                   angular setting of the axis at the end of the integration
                   time for this frame.
    ;
        _item.name               '_diffrn_scan_frame_axis.displacement_increment'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    
    save__diffrn_scan_frame_axis.displacement_rstrt_incr
        _item_description.description
    ;              The increment for this frame for the displacement setting of
                   the specified axis in millimetres.  The sum of the values
                   of _diffrn_scan_frame_axis.displacement,
                   _diffrn_scan_frame_axis.displacement_increment and
                   _diffrn_scan_frame_axis.displacement_rstrt_incr is the
                   angular setting of the axis at the start of the integration
                   time for the next frame and should equal
                   _diffrn_scan_frame_axis.displacement for this next frame.
    ;
        _item.name               '_diffrn_scan_frame_axis.displacement_rstrt_incr'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       no
        _item_default.value        0.0
        _item_type.code            float
        _item_units.code           'millimetres'
         save_
    
    save__diffrn_scan_frame_axis.frame_id
        _item_description.description
    ;              The value of this data item is the identifier of the
                   frame for which axis settings are being specified.
    
                   Multiple axes may be specified for the same value of
                   _diffrn_scan_frame.frame_id.
    
                   This item is a pointer to _diffrn_data_frame.id in the
                   DIFFRN_DATA_FRAME category.
    ;
        _item.name               '_diffrn_scan_frame_axis.frame_id'
        _item.category_id          diffrn_scan_frame_axis
        _item.mandatory_code       yes
        _item_type.code            code
         save_
    
    ########################   DEPRECATED DATA ITEMS ########################
    
    save__diffrn_detector_axis.id
        _item_description.description
    ;              This data item is a pointer to _diffrn_detector.id in
                   the DIFFRN_DETECTOR category.
    
                   DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_detector_axis.id'
        _item.category_id             diffrn_detector_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    save__diffrn_measurement_axis.id
        _item_description.description
    ;              This data item is a pointer to _diffrn_measurement.id in
                   the DIFFRN_MEASUREMENT category.
    
                   DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_measurement_axis.id'
        _item.category_id             diffrn_measurement_axis
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    #########################   DEPRECATED CATEGORY #########################
    #####################
    # DIFFRN_FRAME_DATA #
    #####################
    
    
    save_DIFFRN_FRAME_DATA
        _category.description
    ;             Data items in the DIFFRN_FRAME_DATA category record
                  the details about each frame of data.
    
                  The items in this category are now in the
                  DIFFRN_DATA_FRAME category.
    
                  The items in the DIFFRN_FRAME_DATA category
                  are now deprecated.  The items from this category
                  are provided as aliases in the 1.0 dictionary
                  or, in the case of _diffrn_frame_data.details,
                  in the 1.4 dictionary.  THESE ITEMS SHOULD NOT
                  BE USED FOR NEW WORK.
    
                  The items from the old category are provided
                  in this dictionary for completeness
                  but should not be used or cited.  To avoid
                  confusion, the example has been removed
                  and the redundant parent-child links to other
                  categories have been removed.
    ;
        _category.id                   diffrn_frame_data
        _category.mandatory_code       no
         loop_
        _category_key.name             '_diffrn_frame_data.id'
                                       '_diffrn_frame_data.detector_element_id'
        loop_
        _category_group.id             'inclusive_group'
                                       'array_data_group'
        loop_
        _category_examples.detail
        _category_examples.case
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
    ;
        THE DIFFRN_FRAME_DATA category is deprecated and should not be used.
    ;
    ;
           # EXAMPLE REMOVED #
    ;
    # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
        save_
    
    
    save__diffrn_frame_data.array_id
        _item_description.description
    ;             This item is a pointer to _array_structure.id in the
                  ARRAY_STRUCTURE category.
    
                  DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_frame_data.array_id'
        _item.category_id             diffrn_frame_data
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_frame_data.binary_id
        _item_description.description
    ;             This item is a pointer to _array_data.binary_id in the
                  ARRAY_STRUCTURE category.
    
                  DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_frame_data.binary_id'
        _item.category_id             diffrn_frame_data
        _item.mandatory_code          implicit
        _item_type.code               int
         save_
    
    
    save__diffrn_frame_data.detector_element_id
        _item_description.description
    ;             This item is a pointer to _diffrn_detector_element.id
                  in the DIFFRN_DETECTOR_ELEMENT category.
    
                  DEPRECATED -- DO NOT USE
    ;
        _item.name                  '_diffrn_frame_data.detector_element_id'
        _item.category_id             diffrn_frame_data
        _item.mandatory_code          yes
        _item_type.code               code
         save_
    
    
    save__diffrn_frame_data.id
        _item_description.description
    ;             The value of _diffrn_frame_data.id must uniquely identify
                  each complete frame of data.
    
                  DEPRECATED -- DO NOT USE
    ;
         loop_
        _item.name
        _item.category_id
        _item.mandatory_code
               '_diffrn_frame_data.id'        diffrn_frame_data  yes
        _item_type.code               code
         save_
    
     save__diffrn_frame_data.details
         _item_description.description
    ;             The value of _diffrn_data_frame.details should give a
                  description of special aspects of each frame of data.
    
                  DEPRECATED -- DO NOT USE
    ;
         _item.name                  '_diffrn_frame_data.details'
         _item.category_id             diffrn_frame_data
         _item.mandatory_code          no
         _item_type.code               text
          save_
    
    ################ END DEPRECATED SECTION ###########
    
    
    ####################
    ## ITEM_TYPE_LIST ##
    ####################
    #
    #
    #  The regular expressions defined here are not compliant
    #  with the POSIX 1003.2 standard as they include the
    #  '\n' and '\t' special characters.  These regular expressions
    #  have been tested using version 0.12 of Richard Stallman's
    #  GNU regular expression library in POSIX mode.
    #  In order to allow presentation of a regular expression
    #  in a text field concatenate any line ending in a backslash
    #  with the following line, after discarding the backslash.
    #
    #  A formal definition of the '\n' and '\t' special characters
    #  is most properly done in the DDL, but for completeness, please
    #  note that '\n' is the line termination character ('newline')
    #  and '\t' is the horizontal tab character.  There is a formal
    #  ambiguity in the use of '\n' for line termination, in that
    #  the intention is that the equivalent machine/OS-dependent line
    #  termination character sequence should be accepted as a match, e.g.
    #
    #      '\r' (control-M) under MacOS
    #      '\n' (control-J) under Unix
    #      '\r\n' (control-M control-J) under DOS and MS Windows
    #
         loop_
        _item_type_list.code
        _item_type_list.primitive_code
        _item_type_list.construct
        _item_type_list.detail
                   code      char
                   '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*'
    ;              code item types/single words ...
    ;
                   ucode      uchar
                   '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*'
    ;              code item types/single words (case insensitive) ...
    ;
                   line      char
                   '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*'
    ;              char item types / multi-word items ...
    ;
                   uline     uchar
                   '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*'
    ;              char item types / multi-word items (case insensitive)...
    ;
                   text      char
                 '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*'
    ;              text item types / multi-line text ...
    ;
                   binary    char
    ;\n--CIF-BINARY-FORMAT-SECTION--\n\
    [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\
    \n--CIF-BINARY-FORMAT-SECTION----
    ;
    ;              binary items are presented as MIME-like ascii-encoded
                   sections in an imgCIF.  In a CBF, raw octet streams
                   are used to convey the same information.
    ;
                   int       numb
                   '-?[0-9]+'
    ;              int item types are the subset of numbers that are the negative
                   or positive integers.
    ;
                   float     numb
              '-?(([0-9]+)[.]?|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?'
    ;              float item types are the subset of numbers that are the floating
                   point numbers.
    ;
                   any       char
                   '.*'
    ;              A catch all for items that may take any form...
    ;
                   yyyy-mm-dd  char
    ;\
    [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9]?[0-9]\
    ((T[0-2][0-9](:[0-5][0-9](:[0-5][0-9](.[0-9]+)?)?)?)?\
    ([+-][0-5][0-9]:[0-5][0-9]))?
    ;
    ;
                   Standard format for CIF date and time strings (see
                   http://www.iucr.org/iucr-top/cif/spec/datetime.html),
                   consisting of a yyyy-mm-dd date optionally followed by
                   the character 'T' followed by a 24-hour clock time,
                   optionally followed by a signed time-zone offset.
    
                   The IUCr standard has been extended to allow for an optional
                   decimal fraction on the seconds of time.
    
                   Time is local time if no time-zone offset is given.
    
                   Note that this type extends the mmCIF yyyy-mm-dd type
                   but does not conform to the mmCIF yyyy-mm-dd:hh:mm
                   type that uses a ':' in place if the 'T' specified
                   by the IUCr standard.  For reading, both forms should
                   be accepted,  but for writing, only the IUCr form should
                   be used.
    
                   For maximal compatibility, the special time zone
                   indicator 'Z' (for 'zulu') should be accepted on
                   reading in place of '+00:00' for GMT.
    ;
    
    
    #####################
    ## ITEM_UNITS_LIST ##
    #####################
    
         loop_
        _item_units_list.code
        _item_units_list.detail
    #
         'metres'                 'metres'
         'centimetres'            'centimetres (metres * 10^( -2)^)'
         'millimetres'            'millimetres (metres * 10^( -3)^)'
         'nanometres'             'nanometres  (metres * 10^( -9)^)'
         'angstroms'              '\%Angstroms   (metres * 10^(-10)^)'
         'picometres'             'picometres  (metres * 10^(-12)^)'
         'femtometres'            'femtometres (metres * 10^(-15)^)'
    #
         'reciprocal_metres'      'reciprocal metres (metres^(-1)^)'
         'reciprocal_centimetres'
            'reciprocal centimetres ((metres * 10^( -2)^)^(-1)^)'
         'reciprocal_millimetres'
            'reciprocal millimetres ((metres * 10^( -3)^)^(-1)^)'
         'reciprocal_nanometres'
            'reciprocal nanometres  ((metres * 10^( -9)^)^(-1)^)'
         'reciprocal_angstroms'
            'reciprocal \%Angstroms   ((metres * 10^(-10)^)^(-1)^)'
         'reciprocal_picometres'
            'reciprocal picometres  ((metres * 10^(-12)^)^(-1)^)'
    #
         'nanometres_squared'     'nanometres squared (metres * 10^( -9)^)^2^'
         'angstroms_squared'      '\%Angstroms squared  (metres * 10^(-10)^)^2^'
         '8pi2_angstroms_squared'
           '8\p^2^ * \%Angstroms squared (metres * 10^(-10)^)^2^'
         'picometres_squared'     'picometres squared (metres * 10^(-12)^)^2^'
    #
         'nanometres_cubed'       'nanometres cubed (metres * 10^( -9)^)^3^'
         'angstroms_cubed'        '\%Angstroms cubed  (metres * 10^(-10)^)^3^'
         'picometres_cubed'       'picometres cubed (metres * 10^(-12)^)^3^'
    #
         'kilopascals'            'kilopascals'
         'gigapascals'            'gigapascals'
    #
         'hours'                  'hours'
         'minutes'                'minutes'
         'seconds'                'seconds'
         'microseconds'           'microseconds'
    #
         'degrees'                'degrees (of arc)'
         'degrees_squared'        'degrees (of arc) squared'
    #
         'degrees_per_minute'     'degrees (of arc) per minute'
    #
         'celsius'                'degrees (of temperature) Celsius'
         'kelvins'                'degrees (of temperature) Kelvin'
    #
         'counts'                 'counts'
         'counts_per_photon'      'counts per photon'
    #
         'electrons'              'electrons'
    #
         'electrons_squared'      'electrons squared'
    #
         'electrons_per_nanometres_cubed'
    ; electrons per nanometres cubed (electrons/(metres * 10^( -9)^)^(-3)^)
    ;
         'electrons_per_angstroms_cubed'
    ; electrons per \%Angstroms cubed (electrons/(metres * 10^(-10)^)^(-3)^)
    ;
         'electrons_per_picometres_cubed'
    ; electrons per picometres cubed (electrons/(metres * 10^(-12)^)^(-3)^)
    ;
         'kilowatts'              'kilowatts'
         'milliamperes'           'milliamperes'
         'kilovolts'              'kilovolts'
    #
         'pixels_per_element'     '(image) pixels per (array) element'
    #
         'arbitrary'
    ; arbitrary system of units.
    ;
    #
    
         loop_
        _item_units_conversion.from_code
        _item_units_conversion.to_code
        _item_units_conversion.operator
        _item_units_conversion.factor
    ###
         'metres'                   'centimetres'              '*'   1.0E+02
         'metres'                   'millimetres'              '*'   1.0E+03
         'metres'                   'nanometres'               '*'   1.0E+09
         'metres'                   'angstroms'                '*'   1.0E+10
         'metres'                   'picometres'               '*'   1.0E+12
         'metres'                   'femtometres'              '*'   1.0E+15
    #
         'centimetres'              'metres'                   '*'   1.0E-02
         'centimetres'              'millimetres'              '*'   1.0E+01
         'centimetres'              'nanometres'               '*'   1.0E+07
         'centimetres'              'angstroms'                '*'   1.0E+08
         'centimetres'              'picometres'               '*'   1.0E+10
         'centimetres'              'femtometres'              '*'   1.0E+13
    #
         'millimetres'              'metres'                   '*'   1.0E-03
         'millimetres'              'centimetres'              '*'   1.0E-01
         'millimetres'              'nanometres'               '*'   1.0E+06
         'millimetres'              'angstroms'                '*'   1.0E+07
         'millimetres'              'picometres'               '*'   1.0E+09
         'millimetres'              'femtometres'              '*'   1.0E+12
    #
         'nanometres'               'metres'                   '*'   1.0E-09
         'nanometres'               'centimetres'              '*'   1.0E-07
         'nanometres'               'millimetres'              '*'   1.0E-06
         'nanometres'               'angstroms'                '*'   1.0E+01
         'nanometres'               'picometres'               '*'   1.0E+03
         'nanometres'               'femtometres'              '*'   1.0E+06
    #
         'angstroms'                'metres'                   '*'   1.0E-10
         'angstroms'                'centimetres'              '*'   1.0E-08
         'angstroms'                'millimetres'              '*'   1.0E-07
         'angstroms'                'nanometres'               '*'   1.0E-01
         'angstroms'                'picometres'               '*'   1.0E+02
         'angstroms'                'femtometres'              '*'   1.0E+05
    #
         'picometres'               'metres'                   '*'   1.0E-12
         'picometres'               'centimetres'              '*'   1.0E-10
         'picometres'               'millimetres'              '*'   1.0E-09
         'picometres'               'nanometres'               '*'   1.0E-03
         'picometres'               'angstroms'                '*'   1.0E-02
         'picometres'               'femtometres'              '*'   1.0E+03
    #
         'femtometres'              'metres'                   '*'   1.0E-15
         'femtometres'              'centimetres'              '*'   1.0E-13
         'femtometres'              'millimetres'              '*'   1.0E-12
         'femtometres'              'nanometres'               '*'   1.0E-06
         'femtometres'              'angstroms'                '*'   1.0E-05
         'femtometres'              'picometres'               '*'   1.0E-03
    ###
         'reciprocal_centimetres'   'reciprocal_metres'        '*'   1.0E+02
         'reciprocal_centimetres'   'reciprocal_millimetres'   '*'   1.0E-01
         'reciprocal_centimetres'   'reciprocal_nanometres'    '*'   1.0E-07
         'reciprocal_centimetres'   'reciprocal_angstroms'     '*'   1.0E-08
         'reciprocal_centimetres'   'reciprocal_picometres'    '*'   1.0E-10
    #
         'reciprocal_millimetres'   'reciprocal_metres'        '*'   1.0E+03
         'reciprocal_millimetres'   'reciprocal_centimetres'   '*'   1.0E+01
         'reciprocal_millimetres'   'reciprocal_nanometres'    '*'   1.0E-06
         'reciprocal_millimetres'   'reciprocal_angstroms'     '*'   1.0E-07
         'reciprocal_millimetres'   'reciprocal_picometres'    '*'   1.0E-09
    #
         'reciprocal_nanometres'    'reciprocal_metres'        '*'   1.0E+09
         'reciprocal_nanometres'    'reciprocal_centimetres'   '*'   1.0E+07
         'reciprocal_nanometres'    'reciprocal_millimetres'   '*'   1.0E+06
         'reciprocal_nanometres'    'reciprocal_angstroms'     '*'   1.0E-01
         'reciprocal_nanometres'    'reciprocal_picometres'    '*'   1.0E-03
    #
         'reciprocal_angstroms'     'reciprocal_metres'        '*'   1.0E+10
         'reciprocal_angstroms'     'reciprocal_centimetres'   '*'   1.0E+08
         'reciprocal_angstroms'     'reciprocal_millimetres'   '*'   1.0E+07
         'reciprocal_angstroms'     'reciprocal_nanometres'    '*'   1.0E+01
         'reciprocal_angstroms'     'reciprocal_picometres'    '*'   1.0E-02
    #
         'reciprocal_picometres'    'reciprocal_metres'        '*'   1.0E+12
         'reciprocal_picometres'    'reciprocal_centimetres'   '*'   1.0E+10
         'reciprocal_picometres'    'reciprocal_millimetres'   '*'   1.0E+09
         'reciprocal_picometres'    'reciprocal_nanometres'    '*'   1.0E+03
         'reciprocal_picometres'    'reciprocal_angstroms'     '*'   1.0E+01
    ###
         'nanometres_squared'       'angstroms_squared'        '*'   1.0E+02
         'nanometres_squared'       'picometres_squared'       '*'   1.0E+06
    #
         'angstroms_squared'        'nanometres_squared'       '*'   1.0E-02
         'angstroms_squared'        'picometres_squared'       '*'   1.0E+04
         'angstroms_squared'        '8pi2_angstroms_squared'   '*'   78.9568
    
    #
         'picometres_squared'       'nanometres_squared'       '*'   1.0E-06
         'picometres_squared'       'angstroms_squared'        '*'   1.0E-04
    ###
         'nanometres_cubed'         'angstroms_cubed'          '*'   1.0E+03
         'nanometres_cubed'         'picometres_cubed'         '*'   1.0E+09
    #
         'angstroms_cubed'          'nanometres_cubed'         '*'   1.0E-03
         'angstroms_cubed'          'picometres_cubed'         '*'   1.0E+06
    #
         'picometres_cubed'         'nanometres_cubed'         '*'   1.0E-09
         'picometres_cubed'         'angstroms_cubed'          '*'   1.0E-06
    ###
         'kilopascals'              'gigapascals'              '*'   1.0E-06
         'gigapascals'              'kilopascals'              '*'   1.0E+06
    ###
         'hours'                    'minutes'                  '*'   6.0E+01
         'hours'                    'seconds'                  '*'   3.6E+03
         'hours'                    'microseconds'             '*'   3.6E+09
    #
         'minutes'                  'hours'                    '/'   6.0E+01
         'minutes'                  'seconds'                  '*'   6.0E+01
         'minutes'                  'microseconds'             '*'   6.0E+07
    #
         'seconds'                  'hours'                    '/'   3.6E+03
         'seconds'                  'minutes'                  '/'   6.0E+01
         'seconds'                  'microseconds'             '*'   1.0E+06
    #
         'microseconds'             'hours'                    '/'   3.6E+09
         'microseconds'             'minutes'                  '/'   6.0E+07
         'microseconds'             'seconds'                  '/'   1.0E+06
    ###
         'celsius'                  'kelvins'                  '-'     273.0
         'kelvins'                  'celsius'                  '+'     273.0
    ###
         'electrons_per_nanometres_cubed'
         'electrons_per_angstroms_cubed'                       '*'   1.0E+03
         'electrons_per_nanometres_cubed'
         'electrons_per_picometres_cubed'                      '*'   1.0E+09
    #
         'electrons_per_angstroms_cubed'
         'electrons_per_nanometres_cubed'                      '*'   1.0E-03
         'electrons_per_angstroms_cubed'
         'electrons_per_picometres_cubed'                      '*'   1.0E+06
    #
         'electrons_per_picometres_cubed'
         'electrons_per_nanometres_cubed'                      '*'   1.0E-09
         'electrons_per_picometres_cubed'
         'electrons_per_angstroms_cubed'                       '*'   1.0E-06
    ###
    
    ########################
    ## DICTIONARY_HISTORY ##
    ########################
    
         loop_
        _dictionary_history.version
        _dictionary_history.update
        _dictionary_history.revision
    
       1.4     2005-07-04
    
    ;  This is a change to reintegrate all changes made in the course of
       publication of ITVG, by the RCSB from April 2005 through
       August 2008 and changes for the 2006 imgCIF workshop in
       Hawaii.
    
       2006-07-04 Consolidated changes for the 2006 imgCIF workshop (edited by HJB)
         + Correct type of '_array_structure_list.direction' from 'int' to 'code'.
         + Added new data items suggested by CN
           '_diffrn_data_frame.details'
           '_array_intensities.pixel_fast_bin_size',
           '_array_intensities.pixel_slow_bin_size and
           '_array_intensities.pixel_binning_method
         + Added deprecated item for completeness
           '_diffrn_frame_data.details'
         + Added entry for missing item in contents list
           '_array_structure_list_axis.displacement'
         + Added new MIME type X-BASE32K based on work by VL, KM, GD, HJB
         + Correct description of MIME boundary delimiter to start in
           column 1.
         + General cleanup of text fields to conform to changes for ITVG
           by removing empty lines at start and finish of text field.
         + Amend example for ARRAY_INTENSITIES to include binning.
         + Add local copy of type specification (as 'code') for all children
           of '_diffrn.id'.
         + For consistency, change all references to 'pi' to '\p' and all
           references to 'Angstroms' to '\%Angstroms'.
         + Clean up all powers to use IUCr convention of '^power^', as in
           '10^3^' for '10**3'.
         + Update 'yyyy-mm-dd' type regex to allow truncation from the right
           and improve comments to explain handling of related mmCIF
           'yyyy-mm-dd:hh:mm' type, and use of 'Z' for GMT time zone.
    
       2005-03-08 and
       2004-08-08 fixed cases where _item_units.code  used
                  instead of _item_type.code (JDW)
       2004-04-15 fixed item ordering in
                   _diffrn_measurement_axis.measurement_id
                   added sub_category 'vector' (JDW)
    ;
    
       1.3.2   2005-06-25
    
    ;  2005-06-25 ITEM_TYPE_LIST: code, ucode, line, uline regexps updated
                  to those of current mmCIF; float modified by allowing integers
                  terminated by a point as valid. The 'time' part of
                  yyyy-mm-dd types made optional in the regexp. (BM)
    
       2005-06-17 Minor corrections as for proofs for IT G Chapter 4.6
       (NJA)
    
       2005-02-21  Minor corrections to spelling and punctuation
       (NJA)
    
       2005-01-08 Changes as per Nicola Ashcroft.
       + Updated example 1 for DIFFRN_MEASUREMENT to agree with mmCIF.
       + Spelled out "micrometres" for "um" and "millimetres" for "mm".
       + Removed phrase "which may be stored" from ARRAY_STRUCTURE
         description.
       + Removed unused 'byte-offsets' compressions and updated
         cites to ITVG for '_array_structure.compression_type'.
       (HJB)
    ;
    
       1.3.1   2003-08-13
    ;
       Changes as per Frances C. Bernstein.
       + Identify initials.
       + Adopt British spelling for centre in text.
       + Set \p and \%Angstrom and powers.
       + Clean up commas and unclear wordings.
       + Clean up tenses in history.
       Changes as per Gotzon Madariaga.
       + Fix the ARRAY_DATA example to align '_array_data.binary_id'
       and X-Binary-ID.
       + Add a range to '_array_intensities.gain_esd'.
       + In the example of DIFFRN_DETECTOR_ELEMENT,
       '_diffrn_detector_element.id' and
       '_diffrn_detector_element.detector_id' interchanged.
       + Fix typos for direction, detector and axes.
       + Clarify description of polarisation.
       + Clarify axes in '_diffrn_detector_element.center[1]'
        '_diffrn_detector_element.center[2]'.
       + Add local item types for items that are pointers.
       (HJB)
    ;
    
    
       1.3.0   2003-07-24
    ;
       Changes as per Brian McMahon.
       + Consistently quote tags embedded in text.
       + Clean up introductory comments.
       + Adjust line lengths to fit in 80 character window.
       + Fix several descriptions in AXIS category which
         referred to '_axis.type' instead of the current item.
       + Fix erroneous use of deprecated item
         '_diffrn_detector_axis.id' in examples for
         DIFFRN_SCAN_AXIS.
       + Add deprecated items '_diffrn_detector_axis.id'
         and '_diffrn_measurement_axis.id'.
       (HJB)
    ;
    
    
       1.2.4   2003-07-14
    ;
       Changes as per I. David Brown.
       + Enhance descriptions in DIFFRN_SCAN_AXIS to make them less
         dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS.
       + Provide a copy of the deprecated DIFFRN_FRAME_DATA
         category for completeness.
       (HJB)
    ;
    
    
       1.2.3   2003-07-03
    ;
       Cleanup to conform to ITVG.
       + Correct sign error in ..._cubed units.
       + Correct '_diffrn_radiation.polarisn_norm' range.
       (HJB)
    ;
    
    
       1.2.2   2003-03-10
    ;
       Correction of typos in various DIFFRN_SCAN_AXIS descriptions.
       (HJB)
    ;
    
    
       1.2.1   2003-02-22
    ;
       Correction of ATOM_ for ARRAY_ typos in various descriptions.
       (HJB)
    ;
    
    
       1.2     2003-02-07
    ;
       Corrections to encodings (remove extraneous hyphens) remove
       extraneous underscore in '_array_structure.encoding_type'
       enumeration.  Correct typos in items units list.  (HJB)
    ;
    
    
       1.1.3   2001-04-19
    ;
       Another typo corrections by Wilfred Li, and cleanup by HJB.
    ;
    
    
       1.1.2   2001-03-06
    ;
       Several typo corrections by Wilfred Li.
    ;
    
    
       1.1.1   2001-02-16
    ;
       Several typo corrections by JW.
    ;
    
    
       1.1     2001-02-06
    ;
       Draft resulting from discussions on header for use at NSLS.  (HJB)
    
       + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME.
    
       + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'.
    
       + Add '_diffrn_measurement_axis.measurement_device' and change
         '_diffrn_measurement_axis.id' to
         '_diffrn_measurement_axis.measurement_id'.
    
       + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source',
        '_diffrn_radiation.div_x_y_source',
        '_diffrn_radiation.polarizn_source_norm',
       '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end',
       '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr',
       '_diffrn_scan_axis.displacement_rstrt_incr',
       '_diffrn_scan_frame_axis.angle_increment',
       '_diffrn_scan_frame_axis.angle_rstrt_incr',
       '_diffrn_scan_frame_axis.displacement',
       '_diffrn_scan_frame_axis.displacement_increment',and
       '_diffrn_scan_frame_axis.displacement_rstrt_incr'.
    
       + Add '_diffrn_measurement.device' to category key.
    
       + Update yyyy-mm-dd to allow optional time with fractional seconds
         for time stamps.
    
       + Fix typos caught by RS.
    
       + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to
         allow for coupled axes, as in spiral scans.
    
       + Add examples for fairly complete headers thanks to R. Sweet and P.
         Ellis.
    ;
    
    
       1.0     2000-12-21
    ;
       Release version - few typos and tidying up.  (BM & HJB)
    
       + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end
       of dictionary.
    
       + Alphabetize dictionary.
    ;
    
    
       0.7.1   2000-09-29
    ;
       Cleanup fixes.  (JW)
    
       + Correct spelling of diffrn_measurement_axis in '_axis.id'
    
       + Correct ordering of uses of '_item.mandatory_code' and
       '_item_default.value'.
    ;
    
    
       0.7.0   2000-09-09
    ;
       Respond to comments by I. David Brown.  (HJB)
    
       + Add further comments on '\n' and '\t'.
    
       + Update ITEM_UNITS_LIST by taking section from mmCIF dictionary
         and adding metres.  Change 'meter' to 'metre' throughout.
    
       + Add missing enumerations to '_array_structure.compression_type'
         and make 'none' the default.
    
       + Remove parent-child relationship between
         '_array_structure_list.index' and '_array_structure_list.precedence'.
    
       + Improve alphabetization.
    
       + Fix '_array_intensities_gain.esd' related function.
    
       + Improve comments in AXIS.
    
       + Fix DIFFRN_FRAME_DATA example.
    
       + Remove erroneous DIFFRN_MEASUREMENT example.
    
       + Add '_diffrn_measurement_axis.id' to the category key.
    ;
    
    
       0.6.0   1999-01-14
    ;
       Remove redundant information for ENC_NONE data.  (HJB)
    
       + After the D5 remove binary section identifier, size and
         compression type.
    
       + Add Control-L to header.
    ;
    
    
       0.5.1   1999-01-03
    ;
       Cleanup of typos and syntax errors.  (HJB)
    
       + Cleanup example details for DIFFRN_SCAN category.
    
       + Add missing quote marks for '_diffrn_scan.id' definition.
    ;
    
    
       0.5   1999-01-01
    ;
       Modifications for axis definitions and reduction of binary header.  (HJB)
    
       + Restore '_diffrn_detector.diffrn_id' to DIFFRN_DETECTOR KEY.
    
       + Add AXIS category.
    
       + Bring in complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories
         from cif_mm.dic for clarity.
    
       + Change '_array_structure.encoding_type' from type code to uline and
         added X-Binary-Element-Type to MIME header.
    
       + Add detector beam centre '_diffrn_detector_element.center[1]' and
         '_diffrn_detector_element.center[2]'.
    
       + Correct item name of '_diffrn_refln.frame_id'.
    
       + Replace reference to '_array_intensities.undefined' by
         '_array_intensities.undefined_value'.
    
       + Replace references to '_array_intensity.scaling' with
         '_array_intensities.scaling'.
    
       + Add DIFFRN_SCAN... categories.
    ;
    
    
       0.4   1998-08-11
    ;
       Modifications to the 0.3 imgCIF draft.  (HJB)
    
       + Reflow comment lines over 80 characters and corrected typos.
    
       + Update examples and descriptions of MIME encoded data.
    
       + Change name to cbfext98.dic.
    ;
    
    
       0.3   1998-07-04
    ;
       Modifications for imgCIF.  (HJB)
    
       + Add binary type, which is a text field containing a variant on
         MIME encoded data.
    
       + Change type of '_array_data.data' to binary and specify internal
         structure of raw binary data.
    
       + Add '_array_data.binary_id', and make
         '_diffrn_frame_data.binary_id' and '_array_intensities.binary_id'
         into pointers to this item.
    ;
    
    
       0.2   1997-12-02
    ;
       Modifications to the CBF draft.  (JW)
    
       + Add category hierarchy for describing frame data developed from
         discussions at the BNL imgCIF Workshop Oct 1997.   The following
         changes are made in implementing the workshop draft.  Category
         DIFFRN_ARRAY_DATA is renamed to DIFFRN_FRAME_DATA.  Category
         DIFFRN_FRAME_TYPE is renamed to DIFFRN_DETECTOR_ELEMENT.   The
         parent item for '_diffrn_frame_data.array_id' is changed from
         '_array_structure_list.array_id' to '_array_structure.id'. Item
         '_diffrn_detector.array_id' is deleted.
       + Add data item '_diffrn_frame_data.binary_id' to identify data
         groups within a binary section.  The formal identification of the
         binary section is still fuzzy.
    ;
    
    
       0.1   1997-01-24
    ;
       First draft of this dictionary in DDL 2.1 compliant format by John
       Westbrook (JW).  This version is adapted from the Crystallographic
       Binary File (CBF) Format Draft Proposal provided by Andy Hammersley
       (AH).
    
       Modifications to the CBF draft.  (JW)
    
       + In this version the array description has been cast in the categories
         ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST.  These categories
         have been generalized to describe array data  of arbitrary dimension.
    
       + Array data in this description are contained in the category
         ARRAY_DATA.  This departs from the CBF notion of data existing
         in some special comment. In this description, data are handled as an
         ordinary data item encapsulated in a character data type.   Although
         data this manner deviates from CIF conventions, it does not violate
         any DDL 2.1 rules.  DDL 2.1 regular expressions can be used to define
         the binary representation which will permit some level of data
         validation.  In this version, the placeholder type code "any" has
         been used. This translates to a regular expression which will match
         any pattern.
    
         It should be noted that DDL 2.1 already supports array data objects
         although these have not been used in the current mmCIF dictionary.
         It may be possible to use the DDL 2.1 ITEM_STRUCTURE and
         ITEM_STRUCTURE_LIST categories to provide the information that is
         carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST.  By
         moving the array structure to the DDL level it would be possible to
         define an array type as well as a regular expression defining the
         data format.
    
       + Multiple array sections can be properly handled within a single
         datablock.
    ;
    
    
    #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof
    
    ./CBFlib-0.9.2.2/doc/cif_img_1_3_1.dic0000644000076500007650000054572011603702115015320 0ustar yayayaya ############################################################################## # # # Image CIF Dictionary (imgCIF) # # and Crystallographic Binary File Dictionary (CBF) # # Extending the Macromolecular CIF Dictionary (mmCIF) # # # # Version 1.3.1 # # of 2003-08-13 # # # # by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook # # # # This dictionary was adapted from format discussed at the imgCIF Workshop, # # held at BNL Oct 1997 and the Crystallographic Binary File Format Draft # # Proposal by Andrew Hammersley. The first DDL 2.1 Version was created by # # John Westbrook. This version was drafted by Herbert J. Bernstein and # # incorporates comments by I. David Brown, John Westbrook, Brian McMahon, # # Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li, Gotzon Madariaga, # # Frances C. Bernstein and others. # ############################################################################## data_cif_img.dic _dictionary.title cif_img.dic _dictionary.version 1.3.1 _dictionary.datablock_id cif_img.dic ############################################################################## # CONTENTS # # CATEGORY_GROUP_LIST # # category ARRAY_DATA # # _array_data.array_id # _array_data.binary_id # _array_data.data # # category ARRAY_ELEMENT_SIZE # # _array_element_size.array_id # _array_element_size.index # _array_element_size.size # # category ARRAY_INTENSITIES # # _array_intensities.array_id # _array_intensities.binary_id # _array_intensities.gain # _array_intensities.gain_esd # _array_intensities.linearity # _array_intensities.offset # _array_intensities.scaling # _array_intensities.overload # _array_intensities.undefined_value # # category ARRAY_STRUCTURE # # _array_structure.byte_order # _array_structure.compression_type # _array_structure.encoding_type # _array_structure.id # # category ARRAY_STRUCTURE_LIST # # _array_structure_list.axis_set_id # _array_structure_list.array_id # _array_structure_list.dimension # _array_structure_list.direction # _array_structure_list.index # _array_structure_list.precedence # # category ARRAY_STRUCTURE_LIST_AXIS # # _array_structure_list_axis.axis_id # _array_structure_list_axis.axis_set_id # _array_structure_list_axis.angle # _array_structure_list_axis.angle_increment # _array_structure_list_axis.displacement_increment # _array_structure_list_axis.angular_pitch # _array_structure_list_axis.radial_pitch # # category AXIS # # _axis.depends_on # _axis.equipment # _axis.id # _axis.offset[1] # _axis.offset[2] # _axis.offset[3] # _axis.type # _axis.vector[1] # _axis.vector[2] # _axis.vector[3] # # category DIFFRN_DATA_FRAME # # _diffrn_data_frame.array_id # _diffrn_data_frame.binary_id # _diffrn_data_frame.detector_element_id # _diffrn_data_frame.id # # category DIFFRN_DETECTOR # # _diffrn_detector.details # _diffrn_detector.detector # _diffrn_detector.diffrn_id # _diffrn_detector.dtime # _diffrn_detector.id # _diffrn_detector.number_of_axes # _diffrn_detector.type # # category DIFFRN_DETECTOR_AXIS # # _diffrn_detector_axis.axis_id # _diffrn_detector_axis.detector_id # # category DIFFRN_DETECTOR_ELEMENT # # _diffrn_detector_element.center[1] # _diffrn_detector_element.center[2] # _diffrn_detector_element.id # _diffrn_detector_element.detector_id # # category DIFFRN_MEASUREMENT # # _diffrn_measurement.diffrn_id # _diffrn_measurement.details # _diffrn_measurement.device # _diffrn_measurement.device_details # _diffrn_measurement.device_type # _diffrn_measurement.id # _diffrn_measurement.method # _diffrn_measurement.number_of_axes # _diffrn_measurement.specimen_support # # category DIFFRN_MEASUREMENT_AXIS # # _diffrn_measurement_axis.axis_id # _diffrn_measurement_axis.measurement_device # _diffrn_measurement_axis.measurement_id # # category DIFFRN_RADIATION # # _diffrn_radiation.collimation # _diffrn_radiation.diffrn_id # _diffrn_radiation.div_x_source # _diffrn_radiation.div_y_source # _diffrn_radiation.div_x_y_source # _diffrn_radiation.filter_edge' # _diffrn_radiation.inhomogeneity # _diffrn_radiation.monochromator # _diffrn_radiation.polarisn_norm # _diffrn_radiation.polarisn_ratio # _diffrn_radiation.polarizn_source_norm # _diffrn_radiation.polarizn_source_ratio # _diffrn_radiation.probe # _diffrn_radiation.type # _diffrn_radiation.xray_symbol # _diffrn_radiation.wavelength_id # # category DIFFRN_REFLN # # _diffrn_refln.frame_id # # category DIFFRN_SCAN # # _diffrn_scan.id # _diffrn_scan.date_end # _diffrn_scan.date_start # _diffrn_scan.integration_time # _diffrn_scan.frame_id_start # _diffrn_scan.frame_id_end # _diffrn_scan.frames # # category DIFFRN_SCAN_AXIS # # _diffrn_scan_axis.axis_id # _diffrn_scan_axis.angle_start # _diffrn_scan_axis.angle_range # _diffrn_scan_axis.angle_increment # _diffrn_scan_axis.angle_rstrt_incr # _diffrn_scan_axis.displacement_start # _diffrn_scan_axis.displacement_range # _diffrn_scan_axis.displacement_increment # _diffrn_scan_axis.displacement_rstrt_incr # _diffrn_scan_axis.scan_id # # category DIFFRN_SCAN_FRAME # # _diffrn_scan_frame.date # _diffrn_scan_frame.frame_id # _diffrn_scan_frame.frame_number # _diffrn_scan_frame.integration_time # _diffrn_scan_frame.scan_id # # category DIFFRN_SCAN_FRAME_AXIS # # _diffrn_scan_frame_axis.axis_id # _diffrn_scan_frame_axis.angle # _diffrn_scan_frame_axis.angle_increment # _diffrn_scan_frame_axis.angle_rstrt_incr # _diffrn_scan_frame_axis.displacement # _diffrn_scan_frame_axis.displacement_increment # _diffrn_scan_frame_axis.displacement_rstrt_incr # _diffrn_scan_frame_axis.frame_id # # ***DEPRECATED*** data items # # _diffrn_detector_axis.id # _diffrn_measurement_axis.id # # ***DEPRECATED*** category DIFFRN_FRAME_DATA # # _diffrn_frame_data.array_id # _diffrn_frame_data.binary_id # _diffrn_frame_data.detector_element_id # _diffrn_frame_data.id # # # ITEM_TYPE_LIST # ITEM_UNITS_LIST # DICTIONARY_HISTORY # ############################################################################## ######################### ## CATEGORY_GROUP_LIST ## ######################### loop_ _category_group_list.id _category_group_list.parent_id _category_group_list.description 'inclusive_group' . ; Categories that belong to the dictionary extension. ; 'array_data_group' 'inclusive_group' ; Categories that describe array data. ; 'axis_group' 'inclusive_group' ; Categories that describe axes. ; 'diffrn_group' 'inclusive_group' ; Categories that describe details of the diffraction experiment. ; ############## # ARRAY_DATA # ############## save_ARRAY_DATA _category.description ; Data items in the ARRAY_DATA category are the containers for the array data items described in category ARRAY_STRUCTURE. ; _category.id array_data _category.mandatory_code no loop_ _category_key.name '_array_data.array_id' '_array_data.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows two binary data blocks. The first one was compressed by the CBF_CANONICAL compression algorithm and presented as hexadecimal data. The first character "H" on the data lines means hexadecimal. It could have been "O" for octal or "D" for decimal. The second character on the line shows the number of bytes in each word (in this case "4"), which then requires 8 hexadecimal digits per word. The third character gives the order of octets within a word, in this case "<" for the ordering 4321 (i.e. "big-endian"). Alternatively the character ">" could have been used for the ordering 1234 (i.e. "little-endian"). The block has a "message digest" to check the integrity of the data. The second block is similar, but uses CBF_PACKED compression and BASE64 encoding. Note that the size and the digest are different. ; ; loop_ _array_data.array_id _array_data.binary_id _array_data.data image_1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_CANONICAL" Content-Transfer-Encoding: X-BASE16 X-Binary-Size: 3927126 X-Binary-ID: 1 Content-MD5: u2sTJEovAHkmkDjPi+gWsg== # Hexadecimal encoding, byte 0, byte order ...21 # H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ... .... --CIF-BINARY-FORMAT-SECTION---- ; image_2 2 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF-PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3745758 X-Binary-ID: 2 Content-MD5: 1zsJjWPfol2GYl2V+QSXrw== ELhQAAAAAAAA... ... --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_data.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_array_data.array_id' _item.category_id array_data _item.mandatory_code yes _item_type.code code save_ save__array_data.binary_id _item_description.description ; This item is an integer identifier which, along with '_array_data.array_id' should uniquely identify the particular block of array data. If '_array_data.binary_id' is not explicitly given, it defaults to 1. The value of '_array_data.binary_id' distinguishes among multiple sets of data with the same array structure. If the MIME header of the data array specifies a value for X-Binary-Id, the value of '_array_data.binary_id' should be equal the value given for X-Binary-Id. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_data.binary_id' array_data implicit '_diffrn_data_frame.binary_id' diffrn_data_frame implicit '_array_intensities.binary_id' array_intensities implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.binary_id' '_array_data.binary_id' '_array_intensities.binary_id' '_array_data.binary_id' _item_default.value 1 _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_data.data _item_description.description ; The value of '_array_data.data' contains the array data encapsulated in a STAR string. The representation used is a variant on the Multipurpose Internet Mail Extensions (MIME) specified in RFC 2045-2049 by N. Freed et al. The boundary delimiter used in writing an imgCIF or CBF is "--CIF-BINARY-FORMAT-SECTION--" (including the required initial "--"). The Content-Type may be any of the discrete types permitted in RFC 2045; "application/octet-stream" is recommended. If an octet stream was compressed, the compression should be specified by the parameter 'conversions="x-CBF_PACKED"' or the parameter 'conversions="x-CBF_CANONICAL"'. The Content-Transfer-Encoding may be "BASE64", "Quoted-Printable", "X-BASE8", "X-BASE10", or "X-BASE16" for an imgCIF or "BINARY" for a CBF. The octal, decimal and hexadecimal transfer encodings are for convenience in debugging, and are not recommended for archiving and data interchange. In an imgCIF file, the encoded binary data begins after the empty line terminating the header. In a CBF, the raw binary data begins after an empty line terminating the header and after the sequence: Octet Hex Decimal Purpose 0 0C 12 (ctrl-L) Page break 1 1A 26 (ctrl-Z) Stop listings in MS-DOS 2 04 04 (Ctrl-D) Stop listings in UNIX 3 D5 213 Binary section begins None of these octets are included in the calculation of the message size, nor in the calculation of the message digest. The X-Binary-Size header specifies the size of the equivalent binary data in octets. If compression was used, this size is the size after compression, including any book-keeping fields. An adjustment is made for the deprecated binary formats in which 8 bytes of binary header are used for the compression type. In that case, the 8 bytes used for the compression type is subtracted from the size, so that the same size will be reported if the compression type is supplied in the MIME header. Use of the MIME header is the recommended way to supply the compression type. In general, no portion of the binary header is included in the calculation of the size. The X-Binary-Element-Type header specifies the type of binary data in the octets, using the same descriptive phrases as in '_array_structure.encoding_type'. The default value is "unsigned 32-bit integer". An MD5 message digest may, optionally, be used. The "RSA Data Security, Inc. MD5 Message-Digest Algorithm" should be used. No portion of the header is included in the calculation of the message digest. If the Transfer Encoding is "X-BASE8", "X-BASE10", or "X-BASE16", the data is presented as octal, decimal or hexadecimal data organized into lines or words. Each word is created by composing octets of data in fixed groups of 2, 3, 4, 6 or 8 octets, either in the order ...4321 ("big- endian") or 1234... (little-endian). If there are fewer than the specified number of octets to fill the last word, then the missing octets are presented as "==" for each missing octet. Exactly two equal signs are used for each missing octet even for octal and decimal encoding. The format of lines is: rnd xxxxxx xxxxxx xxxxxx where r is "H", "O", or "D" for hexadecimal, octal or decimal, n is the number of octets per word. and d is "<" for ">" for the "...4321" and "1234..." octet orderings respectively. The "==" padding for the last word should be on the appropriate side to correspond to the missing octets, e.g. H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000 or H3> FF0700 00==== For these hex, octal and decimal formats, only, comments beginning with "#" are permitted to improve readability. BASE64 encoding follows MIME conventions. Octets are in groups of three, c1, c2, c3. The resulting 24 bits are broken into four 6-bit quantities, starting with the high-order six bits (c1 >> 2) of the first octet, then the low-order two bits of the first octet followed by the high-order 4 bits of the second octet ((c1 & 3)<<4 | (c2>>4)), then the bottom 4 bits of the second octet followed by the high order two bits of the last octet ((c2 & 15)<<2 | (c3>>6)), then the bottom six bits of the last octet (c3 & 63). Each of these four quantities is translated into an ASCII character using the mapping: 1 2 3 4 5 6 0123456789012345678901234567890123456789012345678901234567890123 | | | | | | | ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/ With short groups of octets padded on the right with one "=" if c3 is missing, and with "==" if both c2 and c3 are missing. QUOTED-PRINTABLE encoding also follows MIME conventions, copying octets without translation if their ASCII values are 32..38, 42, 48..57, 59..60, 62, 64..126 and the octet is not a ";" in column 1. All other characters are translated to =nn, where nn is the hexadecimal encoding of the octet. All lines are "wrapped" with a terminating "=" (i.e. the MIME conventions for an implicit line terminator are never used). ; _item.name '_array_data.data' _item.category_id array_data _item.mandatory_code yes _item_type.code binary save_ ###################### # ARRAY_ELEMENT_SIZE # ###################### save_ARRAY_ELEMENT_SIZE _category.description ; Data items in the ARRAY_ELEMENT_SIZE category record the physical size of array elements along each array dimension. ; _category.id array_element_size _category.mandatory_code no loop_ _category_key.name '_array_element_size.array_id' '_array_element_size.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A regular 2D array with a uniform element dimension of 1220 nanometres. ; ; loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size image_1 1 1.22e-6 image_1 2 1.22e-6 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_element_size.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_array_element_size.array_id' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.index _item_description.description ; This item is a pointer to '_array_structure_list.index' in the ARRAY_STRUCTURE_LIST category. ; _item.name '_array_element_size.index' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.size _item_description.description ; The size in metres of an image element in this dimension. This supposes that the elements are arranged on a regular grid. ; _item.name '_array_element_size.size' _item.category_id array_element_size _item.mandatory_code yes _item_type.code float _item_units.code 'metres' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ ##################### # ARRAY_INTENSITIES # ##################### save_ARRAY_INTENSITIES _category.description ; Data items in the ARRAY_INTENSITIES category record the information required to recover the intensity data from the set of data values stored in the ARRAY_DATA category. The actual detector may have a complex relationship between the raw intensity values and the number of incident photons. In most cases, the number stored in the final array will have a simple linear relationship to the actual number of incident photons, given by '_array_intensities.gain'. If raw, uncorrected values are presented (e.g for calibration experiments), the value of '_array_intensities.linearity' will be 'raw' and '_array_intensities.gain' will not be used. ; _category.id array_intensities _category.mandatory_code no loop_ _category_key.name '_array_intensities.array_id' '_array_intensities.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 ; ; loop_ _array_intensities.array_id _array_intensities.linearity _array_intensities.gain _array_intensities.overload _array_intensities.undefined_value image_1 linear 1.2 655535 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_intensities.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_array_intensities.array_id' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code save_ save__array_intensities.binary_id _item_description.description ; This item is a pointer to '_array_data.binary_id' in the ARRAY_DATA category. ; _item.name '_array_intensities.binary_id' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code int save_ save__array_intensities.gain _item_description.description ; Detector "gain". The factor by which linearized intensity count values should be divided to produce true photon counts. ; _item.name '_array_intensities.gain' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain_esd' 'associated_value' save_ save__array_intensities.gain_esd _item_description.description ; The estimated standard deviation in detector "gain". ; _item.name '_array_intensities.gain_esd' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain' 'associated_esd' save_ save__array_intensities.linearity _item_description.description ; The intensity linearity scaling used from raw intensity to the stored element value: 'linear' is obvious 'offset' means that the value defined by '_array_intensities.offset' should be added to each element value. 'scaling' means that the value defined by '_array_intensities.scaling' should be multiplied with each element value. 'scaling_offset' is the combination of the two previous cases, with the scale factor applied before the offset value. 'sqrt_scaled' means that the square root of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and squaring the result. 'logarithmic_scaled' means that the logarithm based 10 of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and calculating 10 to the power of this number. 'raw' means that the data is a set of raw values straight from the detector. ; _item.name '_array_intensities.linearity' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'linear' . 'offset' ; The value defined by '_array_intensities.offset' should be added to each element value. ; 'scaling' ; The value defined by '_array_intensities.scaling' should be multiplied with each element value. ; 'scaling_offset' ; The combination of the scaling and offset with the scale factor applied before the offset value. ; 'sqrt_scaled' ; The square root of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and squaring the result. ; 'logarithmic_scaled' ; The logarithm based 10 of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and calculating 10 to the power of this number. ; 'raw' ; The array consists of raw values to which no corrections have been applied. While the handling of the data is similar to that given for 'linear' data with no offset, the meaning of the data differs in that the number of incident photons is not necessarily linearly related to the number of counts reported. This value is intended for use either in calibration experiments or to allow for handling more complex data fitting algorithms than are allowed for by this data item. ; save_ save__array_intensities.offset _item_description.description ; Offset value to add to array element values in the manner described by item '_array_intensities.linearity'. ; _item.name '_array_intensities.offset' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.scaling _item_description.description ; Multiplicative scaling value to be applied to array data in the manner described by item '_array_intensities.linearity'. ; _item.name '_array_intensities.scaling' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.overload _item_description.description ; The saturation intensity level for this data array. ; _item.name '_array_intensities.overload' _item.category_id array_intensities _item.mandatory_code no _item_type.code float _item_units.code 'counts' save_ save__array_intensities.undefined_value _item_description.description ; A value to be substituted for undefined values in the data array. ; _item.name '_array_intensities.undefined_value' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ ################### # ARRAY_STRUCTURE # ################### save_ARRAY_STRUCTURE _category.description ; Data items in the ARRAY_STRUCTURE category record the organization and encoding of array data which may be stored in the ARRAY_DATA category. ; _category.id array_structure _category.mandatory_code no _category_key.name '_array_structure.id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order image_1 "unsigned 16-bit integer" none little_endian ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure.byte_order _item_description.description ; The order of bytes for integer values which require more than 1-byte. (IBM-PC's and compatibles, and Dec-Vaxes use low-byte-first ordered integers, whereas Hewlett Packard 700 series, Sun-4 and Silicon Graphics use high-byte-first ordered integers. Dec-Alphas can produce/use either depending on a compiler switch.) ; _item.name '_array_structure.byte_order' _item.category_id array_structure _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'big_endian' ; The first byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; 'little_endian' ; The last byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; save_ save__array_structure.compression_type _item_description.description ; Type of data compression method used to compress the array data. ; _item.name '_array_structure.compression_type' _item.category_id array_structure _item.mandatory_code no _item_type.code code _item_default.value 'none' loop_ _item_enumeration.value _item_enumeration.detail 'none' ; Data are stored in normal format as defined by '_array_structure.encoding_type' and '_array_structure.byte_order'. ; 'byte_offsets' ; Using the compression scheme defined in CBF definition Section 5.0. ; 'packed' ; Using the 'packed' compression scheme, a CCP4-style packing (CBFlib section 3.3.2) ; 'canonical' ; Using the 'canonical' compression scheme (CBFlib section 3.3.1) ; save_ save__array_structure.encoding_type _item_description.description ; Data encoding of a single element of array data. In several cases, the IEEE format is referenced. See "IEEE Standard for Binary Floating-Point Arithmetic", ANSI/IEEE Std 754-1985, the Institute of Electrical and Electronics Engineers, Inc., NY 1985. ; _item.name '_array_structure.encoding_type' _item.category_id array_structure _item.mandatory_code yes _item_type.code uline loop_ _item_enumeration.value 'unsigned 8-bit integer' 'signed 8-bit integer' 'unsigned 16-bit integer' 'signed 16-bit integer' 'unsigned 32-bit integer' 'signed 32-bit integer' 'signed 32-bit real IEEE' 'signed 64-bit real IEEE' 'signed 32-bit complex IEEE' save_ save__array_structure.id _item_description.description ; The value of '_array_structure.id' must uniquely identify each item of array data. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure.id' array_structure yes '_array_data.array_id' array_data yes '_array_structure_list.array_id' array_structure_list yes '_array_intensities.array_id' array_intensities yes '_diffrn_data_frame.array_id' diffrn_data_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_data.array_id' '_array_structure.id' '_array_structure_list.array_id' '_array_structure.id' '_array_intensities.array_id' '_array_structure.id' '_diffrn_data_frame.array_id' '_array_structure.id' save_ ######################## # ARRAY_STRUCTURE_LIST # ######################## save_ARRAY_STRUCTURE_LIST _category.description ; Data items in the ARRAY_STRUCTURE_LIST category record the size and organization of each array dimension. The relationship to physical axes may be given. ; _category.id array_structure_list _category.mandatory_code no loop_ _category_key.name '_array_structure_list.array_id' '_array_structure_list.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - An image array of 1300 x 1200 elements. The raster order of the image is left-to-right (increasing) in the first dimension and bottom-to-top (decreasing) in the second dimension. ; ; loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id image_1 1 1300 1 increasing ELEMENT_X image_1 2 1200 2 decreasing ELEMENY_Y ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure_list.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_array_structure_list.array_id' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code code save_ save__array_structure_list.axis_set_id _item_description.description ; This is a descriptor for the physical axis or set of axes corresponding to an array index. This data item is related to the axes of the detector itself given in DIFFRN_DETECTOR_AXIS, but usually differ in that the axes in this category are the axes of the coordinate system of reported data points, while the axes in DIFFRN_DETECTOR_AXIS are the physical axes of the detector describing the "poise" of the detector as an overall physical object. If there is only one axis in the set, the identifier of that axis should be used as the identifier of the set. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.axis_set_id' array_structure_list yes '_array_structure_list_axis.axis_set_id' array_structure_list_axis implicit _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_structure_list_axis.axis_set_id' '_array_structure_list.axis_set_id' save_ save__array_structure_list.dimension _item_description.description ; The number of elements stored in the array structure in this dimension. ; _item.name '_array_structure_list.dimension' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.direction _item_description.description ; Identifies the direction in which this array index changes. ; _item.name '_array_structure_list.direction' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_enumeration.value _item_enumeration.detail 'increasing' ; Indicates the index changes from 1 to the maximum dimension. ; 'decreasing' ; Indicates the index changes from the maximum dimension to 1. ; save_ save__array_structure_list.index _item_description.description ; Identifies the one-based index of the row or column in the array structure. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.index' array_structure_list yes '_array_structure_list.precedence' array_structure_list yes '_array_element_size.index' array_element_size yes _item_type.code int loop_ _item_linked.child_name _item_linked.parent_name '_array_element_size.index' '_array_structure_list.index' loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.precedence _item_description.description ; Identifies the rank order in which this array index changes with respect to other array indices. The precedence of 1 indicates the index which changes fastest. ; _item.name '_array_structure_list.precedence' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ ############################# # ARRAY_STRUCTURE_LIST_AXIS # ############################# save_ARRAY_STRUCTURE_LIST_AXIS _category.description ; Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe the physical settings of sets axes for the centres of pixels that correspond to data points described in the ARRAY_STRUCTURE_LIST category. In the simplest cases, the physical increments of a single axis correspond to the increments of a single array index. More complex organizations, e.g. spiral scans, may require coupled motions along multiple axes. Note that a spiral scan uses two coupled axis, one for the angular direction, one for the radial direction. This differs from a cylindrical scan for which the two axes are not coupled into one set. ; _category.id array_structure_list_axis _category.mandatory_code no loop_ _category_key.name '_array_structure_list_axis.axis_set_id' '_array_structure_list_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' save_ save__array_structure_list_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes from the set of axes for which settings are being specified. Multiple axes may be specified for the same value of '_array_structure_list_axis.axis_set_id' This item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_array_structure_list_axis.axis_id' _item.category_id array_structure_list_axis _item.mandatory_code yes _item_units.code code save_ save__array_structure_list_axis.axis_set_id _item_description.description ; The value of this data item is the identifier of the set of axes for which axis settings are being specified. Multiple axes may be specified for the same value of '_array_structure_list_axis.axis_set_id'. This item is a pointer to '_array_structure_list.axis_set_id' in the ARRAY_STRUCTURE_LIST category. If this item is not specified, it defaults to the corresponding axis identifier. ; _item.name '_array_structure_list_axis.axis_set_id' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_units.code code save_ save__array_structure_list_axis.angle _item_description.description ; The setting of the specified axis in degrees for the first data point of the array index with the corresponding value of '_array_structure_list.axis_set_id'. If the index is specified as 'increasing' this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing' this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.angle' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.angle_increment _item_description.description ; The pixel-centre-to-pixel-centre increment in the angular setting of the specified axis in degrees. This is not meaningful in the case of 'constant velocity' spiral scans and should not be specified in that case. See '_array_structure_list_axis.angular_pitch'. ; _item.name '_array_structure_list_axis.angle_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for the first data point of the array index with the corresponding value of '_array_structure_list.axis_set_id'. If the index is specified as 'increasing' this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing' this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.displacement' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.displacement_increment _item_description.description ; The pixel-centre-to-pixel-centre increment for the displacement setting of the specified axis in millimetres. ; _item.name '_array_structure_list_axis.displacement_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.angular_pitch _item_description.description ; The pixel-centre-to-pixel-centre distance for a one step change in the setting of the specified axis in millimetres. This is meaningful only for 'constant velocity' spiral scans, or for uncoupled angular scans at a constant radius (cylindrical scan) and should not be specified for cases in which the angle between pixels, rather than the distance between pixels is uniform. See '_array_structure_list_axis.angle_increment'. ; _item.name '_array_structure_list_axis.angular_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.radial_pitch _item_description.description ; The radial distance from one "cylinder" of pixels to the next in millimetres. If the scan is a 'constant velocity' scan with differing angular displacements between pixels, the value of this item may differ significantly from the value of '_array_structure_list_axis.displacement_increment'. ; _item.name '_array_structure_list_axis.radial_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ ######## # AXIS # ######## save_AXIS _category.description ; Data items in the AXIS category record the information required to describe the various goniometer, detector, source and other axes needed to specify a data collection. The location of each axis is specified by two vectors: the axis itself, given as a unit vector, and an offset to the base of the unit vector. These vectors are referenced to a right-handed laboratory coordinate system with its origin in the sample or specimen: | Y (to complete right-handed system) | | | | | |________________X / principal goniometer axis / / / / /Z (to source) Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from the sample or specimen along the principal axis of the goniometer. Axis 2 (Y): The Y-axis completes an orthogonal right-handed system defined by the X-axis and the Z-axis (see below). Axis 3 (Z): The Z-axis is derived from the source axis which goes from the sample to the source. The Z-axis is the component of the source axis in the direction of the source orthogonal to the X-axis in the plane defined by the X-axis and the source axis. These axes are based on the goniometer, not on the orientation of the detector, gravity, etc. The vectors necessary to specify all other axes are given by sets of three components in the order (X, Y, Z). If the axis involved is a rotation axis, it is right handed, i.e. as one views the object to be rotated from the origin (the tail) of the unit vector, the rotation is clockwise. If a translation axis is specified, the direction of the unit vector specifies the sense of positive translation. Note: This choice of coordinate system is similar to, but significantly different from the choice in MOSFLM (Andrew G.W. Leslie, Harry Powell, MRC Laboratory of Molecular Biology, Hills Road, Cambridge CB2 2QH, UK http://www.dl.ac.uk/CCP/CCP4/dist/x-windows/Mosflm/). In MOSFLM, X is along the X-ray beam (the CBF/imgCIF Z axis) and Z is along the rotation axis. All rotations are given in degrees and all translations are given in mm. Axes may be dependent on one another. The X-axis is the only goniometer axis the direction of which is strictly connected to the hardware. All other axes are specified by the positions they would assume when the axes upon which they depend are at their zero points. When specifying detector axes, the axis is given to the beam centre. The location of the beam centre on the detector should be given in the DIFFRN_DETECTOR category in distortion-corrected mm from the (0,0) corner of the detector. It should be noted that many different origins arise in the definition of an experiment. In particular, as noted above, we need to specify the location of the beam centre on the detector in terms of the origin of the detector, which is, of course, not coincident with the centre of the sample. ; _category.id axis _category.mandatory_code no loop_ _category_key.name '_axis.id' '_axis.equipment' loop_ _category_group.id 'inclusive_group' 'axis_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows the axis specification of the axes of a kappa geometry goniometer (See "X-Ray Structure Determination, A Practical Guide", 2nd ed. by G. H. Stout, L. H. Jensen, Wiley Interscience, 1989, 453 pp, p 134.). There are three axes specified, and no offsets. The outermost axis, omega, is pointed along the X-axis. The next innermost axis, kappa, is at a 50 degree angle to the X-axis, pointed away from the source. The innermost axis, phi, aligns with the X-axis when omega and phi are at their zero-points. If T-omega, T-kappa and T-phi are the transformation matrices derived from the axis settings, the complete transformation would be: x' = (T-omega) (T-kappa) (T-phi) x ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] omega rotation goniometer . 1 0 0 kappa rotation goniometer omega -.64279 0 -.76604 phi rotation goniometer kappa 1 0 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - This example show the axis specification of the axes of a detector, source and gravity. We have juggled the order as a reminder that the ordering of presentation of tokens is not significant. We have taken the centre of rotation of the detector to be 68 millimetres in the direction away from the source. ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] source . source . 0 0 1 . . . gravity . gravity . 0 -1 0 . . . tranz translation detector rotz 0 0 1 0 0 -68 twotheta rotation detector . 1 0 0 . . . roty rotation detector twotheta 0 1 0 0 0 -68 rotz rotation detector roty 0 0 1 0 0 -68 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__axis.depends_on _item_description.description ; The value of '_axis.depends_on' specifies the next outermost axis upon which this axis depends. This item is a pointer to '_axis.id' in the same category. ; _item.name '_axis.depends_on' _item.category_id axis _item.mandatory_code no save_ save__axis.equipment _item_description.description ; The value of '_axis.equipment' specifies the type of equipment using the axis: 'goniometer', 'detector', 'gravity', 'source' or 'general'. ; _item.name '_axis.equipment' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail goniometer 'equipment used to orient or position samples' detector 'equipment used to detect reflections' general 'equipment used for general purposes' gravity 'axis specifying the downward direction' source 'axis specifying the direction sample to source' save_ save__axis.offset[1] _item_description.description ; The [1] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[2] _item_description.description ; The [2] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[3] _item_description.description ; The [3] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.id _item_description.description ; The value of '_axis.id' must uniquely identify each axis relevant to the experiment. Note that multiple pieces of equipment may share the same axis (e.g. a twotheta arm), so that the category key for AXIS also includes the equipment. ; loop_ _item.name _item.category_id _item.mandatory_code '_axis.id' axis yes '_array_structure_list_axis.axis_id' array_structure_list_axis yes '_diffrn_detector_axis.axis_id' diffrn_detector_axis yes '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes '_diffrn_scan_axis.axis_id' diffrn_scan_axis yes '_diffrn_scan_frame_axis.axis_id' diffrn_scan_frame_axis yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_axis.depends_on' '_axis.id' '_array_structure_list_axis.axis_id' '_axis.id' '_diffrn_detector_axis.axis_id' '_axis.id' '_diffrn_measurement_axis.axis_id' '_axis.id' '_diffrn_scan_axis.axis_id' '_axis.id' '_diffrn_scan_frame_axis.axis_id' '_axis.id' save_ save__axis.type _item_description.description ; The value of '_axis.type' specifies the type of axis: 'rotation', 'translation' (or 'general' when the type is not relevant, as for gravity). ; _item.name '_axis.type' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail rotation 'right-handed axis of rotation' translation 'translation in the direction of the axis' general 'axis for which the type is not relevant' save_ save__axis.vector[1] _item_description.description ; The [1] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[2] _item_description.description ; The [2] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[3] _item_description.description ; The [3] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ ##################### # DIFFRN_DATA_FRAME # ##################### save_DIFFRN_DATA_FRAME _category.description ; Data items in the DIFFRN_DATA_FRAME category record the details about each frame of data. The items in this category were previously in a DIFFRN_FRAME_DATA category, which is now deprecated. The items from the old category are provided as aliases but should not be used for new work. ; _category.id diffrn_data_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_data_frame.id' '_diffrn_data_frame.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A frame containing data from 4 frame elements. Each frame element has a common array configuration 'array_1' described in ARRAY_STRUCTURE and related categories. The data for each detector element is stored in four groups of binary data in the ARRAY_DATA category, linked by the array_id and binary_id ; ; loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id frame_1 d1_ccd_1 array_1 1 frame_1 d1_ccd_2 array_1 2 frame_1 d1_ccd_3 array_1 3 frame_1 d1_ccd_4 array_1 4 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_data_frame.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_diffrn_data_frame.array_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.array_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0.00 _item_type.code code save_ save__diffrn_data_frame.binary_id _item_description.description ; This item is a pointer to '_array_data.binary_id' in the ARRAY_DATA category. ; _item.name '_diffrn_data_frame.binary_id' _item.category_id diffrn_data_frame _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_frame_data.binary_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code int save_ save__diffrn_data_frame.detector_element_id _item_description.description ; This item is a pointer to '_diffrn_detector_element.id' in the DIFFRN_DETECTOR_ELEMENT category. ; _item.name '_diffrn_data_frame.detector_element_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.detector_element_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.id _item_description.description ; The value of '_diffrn_data_frame.id' must uniquely identify each complete frame of data. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_data_frame.id' diffrn_data_frame yes '_diffrn_refln.frame_id' diffrn_refln yes '_diffrn_scan.frame_id_start' diffrn_scan yes '_diffrn_scan.frame_id_end' diffrn_scan yes '_diffrn_scan_frame.frame_id' diffrn_scan_frame yes '_diffrn_scan_frame_axis.frame_id' diffrn_scan_frame_axis yes _item_aliases.alias_name '_diffrn_frame_data.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_refln.frame_id' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_start' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_end' '_diffrn_data_frame.id' '_diffrn_scan_frame.frame_id' '_diffrn_data_frame.id' '_diffrn_scan_frame_axis.frame_id' '_diffrn_data_frame.id' save_ ########################################################################## # The following is a restatement of the mmCIF DIFFRN_DETECTOR, # # DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for # # the CBF/imgCIF extensions # ########################################################################## ################### # DIFFRN_DETECTOR # ################### save_DIFFRN_DETECTOR _category.description ; Data items in the DIFFRN_DETECTOR category describe the detector used to measure the scattered radiation, including any analyser and post-sample collimation. ; _category.id diffrn_detector _category.mandatory_code no loop_ _category_key.name '_diffrn_detector.diffrn_id' '_diffrn_detector.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_detector.diffrn_id 'd1' _diffrn_detector.detector 'multiwire' _diffrn_detector.type 'Siemens' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector.details _item_description.description ; A description of special aspects of the radiation detector. ; _item.name '_diffrn_detector.details' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'slow mode' save_ save__diffrn_detector.detector _item_description.description ; The general class of the radiation detector. ; _item.name '_diffrn_detector.detector' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector' cifdic.c91 1.0 '_diffrn_detector' cif_core.dic 2.0 _item_type.code text loop_ _item_examples.case 'photographic film' 'scintillation counter' 'CCD plate' 'BF~3~ counter' save_ save__diffrn_detector.diffrn_id _item_description.description ; This data item is a pointer to '_diffrn.id' in the DIFFRN category. The value of '_diffrn.id' uniquely defines a set of diffraction data. ; _item.name '_diffrn_detector.diffrn_id' _item.mandatory_code yes save_ save__diffrn_detector.dtime _item_description.description ; The deadtime in microseconds of the detectors used to measure the diffraction intensities. ; _item.name '_diffrn_detector.dtime' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector_dtime' cifdic.c91 1.0 '_diffrn_detector_dtime' cif_core.dic 2.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code microseconds save_ save__diffrn_detector.id _item_description.description ; The value of '_diffrn_detector.id' must uniquely identify each detector used to collect each diffraction data set. If the value of '_diffrn_detector.id' is not given, it is implicitly equal to the value of '_diffrn_detector.diffrn_id' ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector.id' diffrn_detector implicit '_diffrn_detector_axis.detector_id' diffrn_detector_axis yes loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_detector_axis.detector_id' '_diffrn_detector.id' _item_type.code code save_ save__diffrn_detector.number_of_axes _item_description.description ; The value of '_diffrn_detector.number_of_axes' gives the number of axes of the positioner for the detector identified by '_diffrn_detector.id'. The word "positioner" is a general term used in instrumentation design for devices that are used to change the positions of portions of apparatus by linear translation, rotation, or combinations of such motions. Axes which are used to provide a coordinate system for the face of an area detetctor should not be counted for this data item. The description of each axis should be provided by entries in DIFFRN_DETECTOR_AXIS. ; _item.name '_diffrn_detector.number_of_axes' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_detector.type _item_description.description ; The make, model or name of the detector device used. ; _item.name '_diffrn_detector.type' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ ######################## # DIFFRN_DETECTOR_AXIS # ######################## save_DIFFRN_DETECTOR_AXIS _category.description ; Data items in the DIFFRN_DETECTOR_AXIS category associate axes with detectors. ; _category.id diffrn_detector_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_axis.detector_id' '_diffrn_detector_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_detector_axis.axis_id _item_description.description ; This data item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_diffrn_detector_axis.axis_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_axis.detector_id _item_description.description ; This data item is a pointer to '_diffrn_detector.id' in the DIFFRN_DETECTOR category. This item was previously named '_diffrn_detector_axis.id' which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_detector_axis.detector_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_aliases.alias_name '_diffrn_detector_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ ########################### # DIFFRN_DETECTOR_ELEMENT # ########################### save_DIFFRN_DETECTOR_ELEMENT _category.description ; Data items in the DIFFRN_DETECTOR_ELEMENT category record the details about spatial layout and other characteristics of each element of a detector which may have multiple elements. In most cases, the more detailed information provided in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS are preferable to simply providing the centre. ; _category.id diffrn_detector_element _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_element.id' '_diffrn_detector_element.detector_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Detector d1 is composed of four CCD detector elements, each 200 mm by 200 mm, arranged in a square. in the pattern 1 2 * 3 4 Note that the beam centre is slightly displaced from each of the detector elements, just beyond the lower right corner of 1, the lower left corner of 2, the upper right corner of 3 and the upper left corner of 4. ; ; loop_ _diffrn_detector_element.detector_id _diffrn_detector_element.id _diffrn_detector_element.center[1] _diffrn_detector_element.center[2] d1 d1_ccd_1 201.5 -1.5 d1 d1_ccd_2 -1.8 -1.5 d1 d1_ccd_3 201.6 201.4 d1 d1_ccd_4 -1.7 201.5 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector_element.center[1] _item_description.description ; The value of '_diffrn_detector_element.center[1]' is the X component of the distortion-corrected beam-centre in mm from the (0, 0) (lower left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. ; _item.name '_diffrn_detector_element.center[1]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.center[2] _item_description.description ; The value of '_diffrn_detector_element.center[2]' is the Y component of the distortion-corrected beam-centre in mm from the (0, 0) (lower left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. ; _item.name '_diffrn_detector_element.center[2]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.id _item_description.description ; The value of '_diffrn_detector_element.id' must uniquely identify each element of a detector. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector_element.id' diffrn_detector_element yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.detector_element_id' '_diffrn_detector_element.id' save_ save__diffrn_detector_element.detector_id _item_description.description ; This item is a pointer to '_diffrn_detector.id' in the DIFFRN_DETECTOR category. ; _item.name '_diffrn_detector_element.detector_id' _item.category_id diffrn_detector_element _item.mandatory_code yes _item_type.code code save_ ######################## ## DIFFRN_MEASUREMENT ## ######################## save_DIFFRN_MEASUREMENT _category.description ; Data items in the DIFFRN_MEASUREMENT category record details about the device used to orient and/or position the crystal during data measurement and the manner in which the diffraction data were measured. ; _category.id diffrn_measurement _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement.device' '_diffrn_measurement.diffrn_id' '_diffrn_measurement.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_measurement.diffrn_id 'd1' _diffrn_measurement.device '3-circle camera' _diffrn_measurement.device_type 'Supper model x' _diffrn_measurement.device_details 'none' _diffrn_measurement.method 'omega scan' _diffrn_measurement.details ; Need new example here ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991). Acta Cryst. C47, 2276-2277]. ; ; _diffrn_measurement.diffrn_id 's1' _diffrn_measurement.device_type 'Philips PW1100/20 diffractometer' _diffrn_measurement.method 'theta/2theta (\q/2\q)' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_measurement.device _item_description.description ; The general class of goniometer or device used to support and orient the specimen. If the value of '_diffrn_measurement.device' is not given, it is implicitly equal to the value of '_diffrn_measurement.diffrn_id'. Either '_diffrn_measurement.device' or '_diffrn_measurement.id' may be used to link to other categories. If the experimental setup admits multiple devices, then '_diffrn_measurement.id' is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.device' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_device' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement.device' _item_aliases.alias_name '_diffrn_measurement_device' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '3-circle camera' '4-circle camera' 'kappa-geometry camera' 'oscillation camera' 'precession camera' save_ save__diffrn_measurement.device_details _item_description.description ; A description of special aspects of the device used to measure the diffraction intensities. ; _item.name '_diffrn_measurement.device_details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; commercial goniometer modified locally to allow for 90\% \t arc ; save_ save__diffrn_measurement.device_type _item_description.description ; The make, model or name of the measurement device (goniometer) used. ; _item.name '_diffrn_measurement.device_type' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Supper model q' 'Huber model r' 'Enraf-Nonius model s' 'homemade' save_ save__diffrn_measurement.diffrn_id _item_description.description ; This data item is a pointer to '_diffrn.id' in the DIFFRN category. ; _item.name '_diffrn_measurement.diffrn_id' _item.mandatory_code yes save_ save__diffrn_measurement.details _item_description.description ; A description of special aspects of the intensity measurement. ; _item.name '_diffrn_measurement.details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; save_ save__diffrn_measurement.id _item_description.description ; The value of '_diffrn_measurement.id' must uniquely identify the set of mechanical characteristics of the device used to orient and/or position the sample used during collection of each diffraction data set. If the value of '_diffrn_measurement.id' is not given, it is implicitly equal to the value of '_diffrn_measurement.diffrn_id'. Either '_diffrn_measurement.device' or '_diffrn_measurement.id' may be used to link to other categories. If the experimental setup admits multiple devices, then '_diffrn_measurement.id' is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.id' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_id' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement.id' _item_type.code code save_ save__diffrn_measurement.method _item_description.description ; Method used to measure intensities. ; _item.name '_diffrn_measurement.method' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_method' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'profile data from theta/2theta (\q/2\q) scans' save_ save__diffrn_measurement.number_of_axes _item_description.description ; The value of '_diffrn_measurement.number_of_axes' gives the number of axes of the positioner for the goniometer or other sample orientation or positioning device identified by '_diffrn_measurement.id'. The description of the axes should be provided by entries in DIFFRN_MEASUREMENT_AXIS. ; _item.name '_diffrn_measurement.number_of_axes' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_measurement.specimen_support _item_description.description ; The physical device used to support the crystal during data collection. ; _item.name '_diffrn_measurement.specimen_support' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_specimen_support' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'glass capillary' 'quartz capillary' 'fiber' 'metal loop' save_ ########################### # DIFFRN_MEASUREMENT_AXIS # ########################### save_DIFFRN_MEASUREMENT_AXIS _category.description ; Data items in the DIFFRN_MEASUREMENT_AXIS category associate axes with goniometers. ; _category.id diffrn_measurement_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_measurement_axis.axis_id _item_description.description ; This data item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_diffrn_measurement_axis.axis_id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.measurement_device _item_description.description ; This data item is a pointer to '_diffrn_measurement.device' in the DIFFRN_MEASUREMENT category. ; _item.name '_diffrn_measurement_axis.measurement_device' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit _item_type.code text save_ save__diffrn_measurement_axis.measurement_id _item_description.description ; This data item is a pointer to '_diffrn_measurement.id' in the DIFFRN_MEASUREMENT category. This item was previously named '_diffrn_measurement_axis.id' which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_measurement_axis.measurement_id' _item.category_id diffrn_measurement_axis _item_aliases.alias_name '_diffrn_measurement_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0.00 _item.mandatory_code implicit _item_type.code code save_ #################### # DIFFRN_RADIATION # #################### save_DIFFRN_RADIATION _category.description ; Data items in the DIFFRN_RADIATION category describe the radiation used in measuring diffraction intensities, its collimation and monochromatisation before the sample. Post-sample treatment of the beam is described by data items in the DIFFRN_DETECTOR category. ; _category.id diffrn_radiation _category.mandatory_code no _category_key.name '_diffrn_radiation.diffrn_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_radiation.diffrn_id 'set1' _diffrn_radiation.collimation '0.3 mm double pinhole' _diffrn_radiation.monochromator 'graphite' _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.wavelength_id 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991). Acta Cryst. C47, 2276-2277]. ; ; _diffrn_radiation.wavelength_id 1 _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.monochromator 'graphite' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_radiation.collimation _item_description.description ; The collimation or focusing applied to the radiation. ; _item.name '_diffrn_radiation.collimation' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_collimation' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '0.3 mm double-pinhole' '0.5 mm' 'focusing mirrors' save_ save__diffrn_radiation.diffrn_id _item_description.description ; This data item is a pointer to '_diffrn.id' in the DIFFRN category. ; _item.name '_diffrn_radiation.diffrn_id' _item.mandatory_code yes save_ save__diffrn_radiation.div_x_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory X axis (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the esd of the directions of photons in the X-Z plane around the mean source beam direction. Note that some synchrotrons specify this value in milliradians, in which case a conversion would be needed. To go from a value in milliradians to a value in degrees, multiply by 0.180 and divide by \p. ; _item.name '_diffrn_radiation.div_x_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.div_y_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory Y axis (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the esd of the directions of photons in the Y-Z plane around the mean source beam direction. Note that some synchrotrons specify this value in milliradians, in which case a conversion would be needed. To go from a value in milliradians to a value in degrees, multiply by 0.180 and divide by \p. ; _item.name '_diffrn_radiation.div_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.div_x_y_source _item_description.description ; Beam crossfire correlation degrees^2^ between the crossfire laboratory X-axis component and the crossfire laboratory Y-axis component (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the mean of the products of the deviations of the direction of each photons in X-Z plane times the deviations of the direction of the same photon in the Y-Z plane around the mean source beam direction. This will be zero for uncorrelated crossfire. Note that some synchrotrons specify this value in milliradians^2^, in which case a conversion would be needed. To go from a value in milliradians^2^ to a value in degrees^2^, multiply by 0.180^2^ and divide by \p^2^. ; _item.name '_diffrn_radiation.div_x_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees_squared _item_default.value 0.0 save_ save__diffrn_radiation.filter_edge _item_description.description ; Absorption edge in \%Angstroms of the radiation filter used. ; _item.name '_diffrn_radiation.filter_edge' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_filter_edge' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__diffrn_radiation.inhomogeneity _item_description.description ; Half-width in millimetres of the incident beam in the direction perpendicular to the diffraction plane. ; _item.name '_diffrn_radiation.inhomogeneity' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_inhomogeneity' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code millimetres save_ save__diffrn_radiation.monochromator _item_description.description ; The method used to obtain monochromatic radiation. If a monochromator crystal is used the material and the indices of the Bragg reflection are specified. ; _item.name '_diffrn_radiation.monochromator' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_monochromator' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Zr filter' 'Ge 220' 'none' 'equatorial mounted graphite' save_ save__diffrn_radiation.polarisn_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the perpendicular component of the polarisation and the diffraction plane. See _diffrn_radiation_polarisn_ratio. ; _item.name '_diffrn_radiation.polarisn_norm' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_norm' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.polarisn_ratio _item_description.description ; Polarisation ratio of the diffraction beam incident on the crystal. It is the ratio of the perpendicularly polarised to the parallel polarised component of the radiation. The perpendicular component forms an angle of '_diffrn_radiation.polarisn_norm' to the normal to the diffraction plane of the sample (i.e. the plane containing the incident and reflected beams). ; _item.name '_diffrn_radiation.polarisn_ratio' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_ratio' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__diffrn_radiation.polarizn_source_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the normal to the polarization plane and the laboratory Y axis as defined in the AXIS category. Note that this is the angle of polarization of the source photons, either directly from a synchrotron beamline or from a monchromater. This differs from the value of '_diffrn_radiation.polarisn_norm' in that '_diffrn_radiation.polarisn_norm' refers to polarization relative to the diffraction plane rather than to the laboratory axis system. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane should be taken as the X-Z plane, and the angle as 0. See '_diffrn_radiation.polarizn_source_ratio'. ; _item.name '_diffrn_radiation.polarizn_source_norm' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.polarizn_source_ratio _item_description.description ; (Ip-In)/(Ip+In), where Ip is the intensity (amplitude squared) of the electric vector in the plane of polarization and In is the intensity (amplitude squared) of the electric vector in plane of the normal to the plane of polarization. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane is be taken as the X-Z plane, and the normal is parallel to the Y-axis. Thus, if we had complete polarization in the plane of polarization, the value of '_diffrn_radiation.polarizn_source_ratio' would be 1, and an unpolarized beam would have a value of 0. If the X-axis has been chosen to lie in the plane of polarization, this definition will agree with the definition of "MONOCHROMATOR" in the Denzo glossary, and values of near 1 should be expected for a bending magnet source. However, if the X-axis were, for some reason to be, say, perpendicular to the polarization plane (not a common choice), then the Denzo value would be the negative of '_diffrn_radiation.polarizn_source_ratio'. See http://www.hkl-xray.com for information on Denzo, and Z. Otwinowski and W. Minor, "Processing of X-ray Diffraction Data Collected in Oscillation Mode", Methods in Enzymology, Volume 276: Macromolecular Crystallography, part A, p.307-326, 1997,C.W. Carter, Jr. & R. M. Sweet, Eds., Academic Press. This differs both in the choice of ratio and choice of orientation from '_diffrn_radiation.polarisn_ratio', which, unlike '_diffrn_radiation.polarizn_source_ratio', is unbounded. ; _item.name '_diffrn_radiation.polarizn_source_ratio' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 -1.0 -1.0 -1.0 _item_type.code float save_ save__diffrn_radiation.probe _item_description.description ; Name of the type of radiation used. It is strongly encouraged that this field be specified so that the probe radiation can be simply determined. ; _item.name '_diffrn_radiation.probe' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_probe' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value 'x-ray' 'neutron' 'electron' 'gamma' save_ save__diffrn_radiation.type _item_description.description ; The nature of the radiation. This is typically a description of the X-ray wavelength in Siegbahn notation. ; _item.name '_diffrn_radiation.type' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'CuK\a' 'Cu K\a~1~' 'Cu K-L~2,3~' 'white-beam' save_ save__diffrn_radiation.xray_symbol _item_description.description ; The IUPAC symbol for the X-ray wavelength for probe radiation. ; _item.name '_diffrn_radiation.xray_symbol' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_xray_symbol' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value _item_enumeration.detail 'K-L~3~' 'K\a~1~ in older Siegbahn notation' 'K-L~2~' 'K\a~2~ in older Siegbahn notation' 'K-M~3~' 'K\b~1~ in older Siegbahn notation' 'K-L~2,3~' 'use where K-L~3~ and K-L~2~ are not resolved' save_ save__diffrn_radiation.wavelength_id _item_description.description ; This data item is a pointer to '_diffrn_radiation_wavelength.id' in the DIFFRN_RADIATION_WAVELENGTH category. ; _item.name '_diffrn_radiation.wavelength_id' _item.category_id diffrn_radiation _item.mandatory_code yes _item_type.code code save_ ################ # DIFFRN_REFLN # ################ save_DIFFRN_REFLN _category.description ; This category redefinition has been added to extend the key of the standard DIFFRN_REFLN category. ; _category.id diffrn_refln _category.mandatory_code no _category_key.name '_diffrn_refln.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_refln.frame_id _item_description.description ; This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_refln.frame_id' _item.category_id diffrn_refln _item.mandatory_code yes _item_type.code code save_ ############### # DIFFRN_SCAN # ############### save_DIFFRN_SCAN _category.description ; Data items in the DIFFRN_SCAN category describe the parameters of one or more scans, relating axis positions to frames. ; _category.id diffrn_scan _category.mandatory_code no _category_key.name '_diffrn_scan.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - derived from a suggestion by R. M. Sweet. The vector of each axis is not given here, because it is provided in the AXIS category. By making '_diffrn_scan_axis.scan_id' and '_diffrn_scan_axis.axis_id' keys of the DIFFRN_SCAN_AXIS category, an arbitrary number of scanning and fixed axes can be specified for a scan. We have specified three rotation axes and one translation axis at non-zero values, with one axis stepping. There is no reason why more axes could not have been specified to step. We have specified range information, but note that it is redundant from the number of frames and the increment, so we could drop the data item '_diffrn_scan_axis.angle_range'. We have specified both the sweep data and the data for a single frame. Note that the information on how the axes are stepped is given twice, once in terms of the overall averages in the value of '_diffrn_scan.integration_time' and the values for DIFFRN_SCAN_AXIS, and precisely for the given frame in the value for '_diffrn_scan_frame.integration_time' and the values for DIFFRN_SCAN_FRAME_AXIS. If dose-related adjustements are made to scan times and non-linear stepping is done, these values may differ. Therefore, in interpreting the data for a particular frame it is important to use the frame-specific data. ; ; _diffrn_scan.id 1 _diffrn_scan.date_start '2001-11-18T03:26:42' _diffrn_scan.date_end '2001-11-18T03:36:45' _diffrn_scan.integration_time 3.0 _diffrn_scan.frame_id_start mad_L2_000 _diffrn_scan.frame_id_end mad_L2_200 _diffrn_scan.frames 201 loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment 1 omega 200.0 20.0 0.1 . . . 1 kappa -40.0 0.0 0.0 . . . 1 phi 127.5 0.0 0.0 . . . 1 tranz . . . 2.3 0.0 0.0 _diffrn_scan_frame.scan_id 1 _diffrn_scan_frame.date '2001-11-18T03:27:33' _diffrn_scan_frame.integration_time 3.0 _diffrn_scan_frame.frame_id mad_L2_018 _diffrn_scan_frame.frame_number 18 loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.angle_increment _diffrn_scan_frame_axis.displacement _diffrn_scan_frame_axis.displacement_increment mad_L2_018 omega 201.8 0.1 . . mad_L2_018 kappa -40.0 0.0 . . mad_L2_018 phi 127.5 0.0 . . mad_L2_018 tranz . . 2.3 0.0 ; ; Example 2 - a more extensive example, R. M. Sweet, P. Ellis, H. Bernstein. We place a detector 240 mm along the Z axis from the goniometer. This presents us with a choice -- either we define the axes of the detector at the origin, and then put a Z setting of -240 in for the actual use, or we define the axes with the necessary Z-offset. In this case we use the setting, and leave the offset as zero. We call this axis DETECTOR_Z. The axis for positioning the detector in the Y-direction depends on the detector Z-axis. We call this axis, DETECTOR_Y. The axis for positioning the detector in the X-direction depends on the detector Y-axis (and therefore on the detector Z-axis). We call this axis DETECTOR_X. This detector may be rotated around the Y-axis. This rotation axis depends on the three translation axes. We call it DETECTOR_PITCH. We define a coordinate system on the face of the detector in terms of 2300 0.150 mm pixels in each direction. The ELEMENT_X axis is used to index the first array index of the data array and the ELEMENT_Y axis is used to index the second array index. Because the pixels are 0.150mm x 0.150mm, the centre of the first pixel is at (0.075, 0.075) in this coordinate system. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 172.43 -172.43 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 2300 1 increasing ELEMENT_X ARRAY1 2 2300 2 increasing ELEMENT_Y # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.075 0.150 ELEMENT_Y ELEMENT_Y 0.075 0.150 # category ARRAY_ELEMENT_SIZE loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 ARRAY1 2 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; ; Example 3 - Example 2 revised for a spiral scan, R. M. Sweet, P. Ellis, H. Bernstein. We place a detector 240 mm along the Z axis from the goniometer, as in Example 2, above, but in this example, the image plate is scanned in a spiral pattern outside edge in. The axis for positioning the detector in the Y-direction depends on the detector Z-axis. We call this axis, DETECTOR_Y. The axis for positioning the detector in the X-direction depends on the detector Y-axis (and therefore on the detector Z-axis). We call this axis DETECTOR_X. This detector may be rotated around the Y-axis. This rotation axis depends on the three translation axes. We call it DETECTOR_PITCH. We define a coordinate system on the face of the detector in terms of a coupled rotation axis and radial scan axis to form a spiral scan. Let us call rotation axis ELEMENT_ROT, and the radial axis ELEMENT_RAD. We assume 150 um radial pitch and 75 um 'constant velocity' angular pitch. We index first on the rotation axis and make the radial axis dependent on it. The two axes are coupled to form an axis set ELEMENT_SPIRAL. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_ROT translation detector DETECTOR_PITCH 0 0 1 0 0 0 ELEMENT_RAD translation detector ELEMENT_ROT 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.angle _array_structure_list_axis.displacement _array_structure_list_axis.angular_pitch _array_structure_list_axis.radial_pitch ELEMENT_SPIRAL ELEMENT_ROT 0 . 0.075 . ELEMENT_SPIRAL ELEMENT_RAD . 172.5 . -0.150 # category ARRAY_ELEMENT_SIZE # the actual pixels are 0.075 by 0.150 mm # We give the coarser dimension here. loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_scan.id _item_description.description ; The value of '_diffrn_scan.id' uniquely identifies each scan. The identifier is used to tie together all the information about the scan. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_scan.id' diffrn_scan yes '_diffrn_scan_axis.scan_id' diffrn_scan_axis yes '_diffrn_scan_frame.scan_id' diffrn_scan_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_scan_axis.scan_id' '_diffrn_scan.id' '_diffrn_scan_frame.scan_id' '_diffrn_scan.id' save_ save__diffrn_scan.date_end _item_description.description ; The date and time of the end of the scan. Note that this may be an estimate generated during the scan, before the precise time of the end of the scan is known. ; _item.name '_diffrn_scan.date_end' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.date_start _item_description.description ; The date and time of the start of the scan. ; _item.name '_diffrn_scan.date_start' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.integration_time _item_description.description ; Approximate average time in seconds to integrate each step of the scan. The precise time for integration of each particular step must be provided in '_diffrn_scan_frame.integration_time', even if all steps have the same integration time. ; _item.name '_diffrn_scan.integration_time' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan.frame_id_start _item_description.description ; The value of this data item is the identifier of the first frame in the scan. This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_start' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frame_id_end _item_description.description ; The value of this data item is the identifier of the last frame in the scan. This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_end' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frames _item_description.description ; The value of this data item is the number of frames in the scan. ; _item.name '_diffrn_scan.frames' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 1 1 1 save_ #################### # DIFFRN_SCAN_AXIS # #################### save_DIFFRN_SCAN_AXIS _category.description ; Data items in the DIFFRN_SCAN_AXIS category describe the settings of axes for particular scans. Unspecified axes are assumed to be at their zero points. ; _category.id diffrn_scan_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_axis.scan_id' '_diffrn_scan_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_axis.scan_id _item_description.description ; The value of this data item is the identifier of the scan for which axis settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan.id'. This item is a pointer to '_diffrn_scan.id' in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_axis.scan_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the scan for which settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan.id'. This item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_diffrn_scan_axis.axis_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.angle_start _item_description.description ; The starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_range _item_description.description ; The range from the starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_increment _item_description.description ; The increment for each step for the specified axis in degrees. In general, this will agree with '_diffrn_scan_frame_axis.angle_increment'. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.angle_increment' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.angle_increment' (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_rstrt_incr _item_description.description ; The increment after each step for the specified axis in degrees. In general, this will agree with '_diffrn_scan_frame_axis.angle_rstrt_incr'. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' and '_diffrn_scan_frame_axis.angle_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame, and should equal '_diffrn_scan_frame_axis.angle' for that next frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.angle_rstrt_incr' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.angle_rstrt_incr' (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.displacement_start _item_description.description ; The starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_range _item_description.description ; The range from the starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_increment _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with '_diffrn_scan_frame_axis.displacement_increment'. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.displacement_increment' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.displacement_increment' (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_rstrt_incr _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with '_diffrn_scan_frame_axis.displacement_rstrt_incr'. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' and '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame, and should equal '_diffrn_scan_frame_axis.displacement' for that next frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.displacement_rstrt_incr' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.displacement_rstrt_incr' (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ ##################### # DIFFRN_SCAN_FRAME # ##################### save_DIFFRN_SCAN_FRAME _category.description ; Data items in the DIFFRN_SCAN_FRAME category describe the relationship of particular frames to scans. ; _category.id diffrn_scan_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame.scan_id' '_diffrn_scan_frame.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame.date _item_description.description ; The date and time of the start of the frame being scanned. ; _item.name '_diffrn_scan_frame.date' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan_frame.frame_id _item_description.description ; The value of this data item is the identifier of the frame being examined. This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame.frame_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame.frame_number _item_description.description ; The value of this data item is the number of the frame within the scan, starting with 1. It is not necessarily the same as the value of '_diffrn_scan_frame.frame_id', but may be. ; _item.name '_diffrn_scan_frame.frame_number' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 0 0 0 save_ save__diffrn_scan_frame.integration_time _item_description.description ; The time in seconds to integrate this step of the scan. This should be the precise time of integration of each particular frame. The value of this data item should be given explicitly for each frame and not inferred from the value of '_diffrn_scan.integration_time'. ; _item.name '_diffrn_scan_frame.integration_time' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame.scan_id _item_description.description ; The value of '_diffrn_scan_frame.scan_id' identifies the scan containing this frame. This item is a pointer to '_diffrn_scan.id' in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_frame.scan_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ ########################## # DIFFRN_SCAN_FRAME_AXIS # ########################## save_DIFFRN_SCAN_FRAME_AXIS _category.description ; Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the settings of axes for particular frames. Unspecified axes are assumed to be at their zero points. If, for any given frame, non-zero values apply for any of the data items in this category, those values should be given explicitly in this category and not simply inferred from values in DIFFRN_SCAN_AXIS. ; _category.id diffrn_scan_frame_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame_axis.frame_id' '_diffrn_scan_frame_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the frame for which settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan_frame.frame_id'. This item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_diffrn_scan_frame_axis.axis_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_axis.angle _item_description.description ; The setting of the specified axis in degrees for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.angle' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_increment _item_description.description ; The increment for this frame for angular setting of the specified axis in degrees. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.angle_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_rstrt_incr _item_description.description ; The increment after this frame for angular setting of the specified axis in degrees. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' and '_diffrn_scan_frame_axis.angle_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame, and should equal '_diffrn_scan_frame_axis.angle' for that next frame. ; _item.name '_diffrn_scan_frame_axis.angle_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.displacement' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_increment _item_description.description ; The increment for this frame for displacement setting of the specified axis in millimetres. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.displacement_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_rstrt_incr _item_description.description ; The increment for this frame for displacement setting of the specified axis in millimetres. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' and '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame, and should equal '_diffrn_scan_frame_axis.displacement' for that next frame. ; _item.name '_diffrn_scan_frame_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.frame_id _item_description.description ; The value of this data item is the identifier of the frame for which axis settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan_frame.frame_id'. This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame_axis.frame_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ ######################## DEPRECATED DATA ITEMS ######################## save__diffrn_detector_axis.id _item_description.description ; This data item is a pointer to '_diffrn_detector.id' in the DIFFRN_DETECTOR category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_detector_axis.id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.id _item_description.description ; This data item is a pointer to '_diffrn_measurement.id' in the DIFFRN_MEASUREMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_measurement_axis.id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ ######################### DEPRECATED CATEGORY ######################### ##################### # DIFFRN_FRAME_DATA # ##################### save_DIFFRN_FRAME_DATA _category.description ; Data items in the DIFFRN_FRAME_DATA category record the details about each frame of data. The items in this category are now in the DIFFRN_DATA_FRAME category. The items in the DIFFRN_FRAME_DATA category are now deprecated. The items from this category are provided as aliases in the 1.0.0 dictionary, but should not be used for new work. The items from the old category are provided in this dictionary for completeness, but should not be used or cited. To avoid confusion, the example has been removed, and the redundant parent child-links to other categories removed. ; _category.id diffrn_frame_data _category.mandatory_code no loop_ _category_key.name '_diffrn_frame_data.id' '_diffrn_frame_data.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; THE DIFFRN_FRAME_DATA category is deprecated and should not be used. ; ; # EXAMPLE REMOVED # ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_frame_data.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.array_id' _item.category_id diffrn_frame_data _item.mandatory_code yes _item_type.code code save_ save__diffrn_frame_data.binary_id _item_description.description ; This item is a pointer to '_array_data.binary_id' in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.binary_id' _item.category_id diffrn_frame_data _item.mandatory_code implicit _item_type.code int save_ save__diffrn_frame_data.detector_element_id _item_description.description ; This item is a pointer to '_diffrn_detector_element.id' in the DIFFRN_DETECTOR_ELEMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.detector_element_id' _item.category_id diffrn_frame_data _item.mandatory_code yes _item_type.code code save_ save__diffrn_frame_data.id _item_description.description ; The value of '_diffrn_frame_data.id' must uniquely identify each complete frame of data. DEPRECATED -- DO NOT USE ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_frame_data.id' diffrn_frame_data yes _item_type.code code save_ ################ END DEPRECATED SECTION ########### #################### ## ITEM_TYPE_LIST ## #################### # # # The regular expressions defined here are not compliant # with the POSIX 1003.2 standard as they include the # '\n' and '\t' special characters. These regular expressions # have been tested using version 0.12 of Richard Stallman's # GNU regular expression library in POSIX mode. # In order to allow presentation of a regular expression # in a text field concatenate any line ending in a backslash # with the following line, after discarding the backslash. # # A formal definition of the '\n' and '\t' special characters # is most properly done in the DDL, but for completeness, please # note that '\n' is the line termination character ('newline') # and '\t' is the horizontal tab character. There is a formal # ambiguity in the use of '\n' for line termination, in that # the intention is that the equivalent machine/OS-dependent line # termination character sequence should be accepted as a match, e.g. # # '\r' (control-M) under MacOS # '\n' (control-J) under Unix # '\r\n' (control-M control-J) under DOS and MS Windows # loop_ _item_type_list.code _item_type_list.primitive_code _item_type_list.construct _item_type_list.detail code char '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words ... ; ucode uchar '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words (case insensitive) ; line char '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types / multi-word items ... ; uline uchar '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types / multi-word items (case insensitive) ; text char '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; text item types / multi-line text ... ; binary char ;\n--CIF-BINARY-FORMAT-SECTION--\n\ [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\ \n--CIF-BINARY-FORMAT-SECTION---- ; ; binary items are presented as MIME-like ascii-encoded sections in an imgCIF. In a CBF, raw octet streams are used to convey the same information. ; int numb '-?[0-9]+' ; int item types are the subset of numbers that are the negative or positive integers. ; float numb '-?(([0-9]+)|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?' ; float item types are the subset of numbers that are the floating numbers. ; any char '.*' ; A catch all for items that may take any form... ; yyyy-mm-dd char ;\ [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9][0-9]\ (T[0-2][0-9]:[0-5][0-9]:[0-5][0-9](.[0-9]+)([+-][0-5][0-9]:[0-5][0-9])) ; ; Standard format for CIF date and time strings (see http://www.iucr.org/iucr-top/cif/spec/datetime.html), consisting of a yyyy-mm-dd date optionally followed by the character "T" followed by a 24-hour clock time, optionally followed by a signed time-zone offset. The IUCr standard has been extended to allow for an optional decimal fraction on the seconds of time. Time is local time if no time-zone offset is given. ; ##################### ## ITEM_UNITS_LIST ## ##################### loop_ _item_units_list.code _item_units_list.detail # 'metres' 'metres' 'centimetres' 'centimetres (metres * 10^( -2)^)' 'millimetres' 'millimetres (metres * 10^( -3)^)' 'nanometres' 'nanometres (metres * 10^( -9)^)' 'angstroms' '\%Angstroms (metres * 10^(-10)^)' 'picometres' 'picometres (metres * 10^(-12)^)' 'femtometres' 'femtometres (metres * 10^(-15)^)' # 'reciprocal_metres' 'reciprocal metres (metres^(-1)^)' 'reciprocal_centimetres' 'reciprocal centimetres ((metres * 10^( -2))^(-1)^)' 'reciprocal_millimetres' 'reciprocal millimetres ((metres * 10^( -3))^(-1)^)' 'reciprocal_nanometres' 'reciprocal nanometres ((metres * 10^( -9))^(-1)^)' 'reciprocal_angstroms' 'reciprocal angstroms ((metres * 10^(-10))^(-1)^)' 'reciprocal_picometres' 'reciprocal picometres ((metres * 10^(-12))^(-1)^)' # 'nanometres_squared' 'nanometres squared (metres * 10^( -9)^)^2^' 'angstroms_squared' '\%Angstroms squared (metres * 10^(-10)^)^2^' '8pi2_angstroms_squared' '8\p^2^ * \%Angstroms squared (metres * 10^(-10)^)^2^' 'picometres_squared' 'picometres squared (metres * 10^(-12)^)^2^' # 'nanometres_cubed' 'nanometres cubed (metres * 10^( -9)^)^3^' 'angstroms_cubed' '\%Angstroms cubed (metres * 10^(-10)^)^3^' 'picometres_cubed' 'picometres cubed (metres * 10^(-12)^)^3^' # 'kilopascals' 'kilopascals' 'gigapascals' 'gigapascals' # 'hours' 'hours' 'minutes' 'minutes' 'seconds' 'seconds' 'microseconds' 'microseconds' # 'degrees' 'degrees (of arc)' 'degrees_squared' 'degrees (of arc) squared' # 'degrees_per_minute' 'degrees (of arc) per minute' # 'celsius' 'degrees (of temperature) Celsius' 'kelvins' 'degrees (of temperature) Kelvin' # 'counts' 'counts' 'counts_per_photon' 'counts per photon' # 'electrons' 'electrons' # 'electrons_squared' 'electrons squared' # 'electrons_per_nanometres_cubed' ; electrons per nanometres cubed (electrons/(metres * 10^( -9)^)^(-3)^) ; 'electrons_per_angstroms_cubed' ; electrons per angstroms cubed (electrons/(metres * 10^(-10)^)^(-3)^) ; 'electrons_per_picometres_cubed' ; electrons per picometres cubed (electrons/(metres * 10^(-12)^)^(-3)^) ; 'kilowatts' 'kilowatts' 'milliamperes' 'milliamperes' 'kilovolts' 'kilovolts' # 'arbitrary' ; arbitrary system of units. ; # loop_ _item_units_conversion.from_code _item_units_conversion.to_code _item_units_conversion.operator _item_units_conversion.factor ### 'metres' 'centimetres' '*' 1.0E+02 'metres' 'millimetres' '*' 1.0E+03 'metres' 'nanometres' '*' 1.0E+09 'metres' 'angstroms' '*' 1.0E+10 'metres' 'picometres' '*' 1.0E+12 'metres' 'femtometres' '*' 1.0E+15 # 'centimetres' 'metres' '*' 1.0E-02 'centimetres' 'millimetres' '*' 1.0E+01 'centimetres' 'nanometres' '*' 1.0E+07 'centimetres' 'angstroms' '*' 1.0E+08 'centimetres' 'picometres' '*' 1.0E+10 'centimetres' 'femtometres' '*' 1.0E+13 # 'millimetres' 'metres' '*' 1.0E-03 'millimetres' 'centimetres' '*' 1.0E-01 'millimetres' 'nanometres' '*' 1.0E+06 'millimetres' 'angstroms' '*' 1.0E+07 'millimetres' 'picometres' '*' 1.0E+09 'millimetres' 'femtometres' '*' 1.0E+12 # 'nanometres' 'metres' '*' 1.0E-09 'nanometres' 'centimetres' '*' 1.0E-07 'nanometres' 'millimetres' '*' 1.0E-06 'nanometres' 'angstroms' '*' 1.0E+01 'nanometres' 'picometres' '*' 1.0E+03 'nanometres' 'femtometres' '*' 1.0E+06 # 'angstroms' 'metres' '*' 1.0E-10 'angstroms' 'centimetres' '*' 1.0E-08 'angstroms' 'millimetres' '*' 1.0E-07 'angstroms' 'nanometres' '*' 1.0E-01 'angstroms' 'picometres' '*' 1.0E+02 'angstroms' 'femtometres' '*' 1.0E+05 # 'picometres' 'metres' '*' 1.0E-12 'picometres' 'centimetres' '*' 1.0E-10 'picometres' 'millimetres' '*' 1.0E-09 'picometres' 'nanometres' '*' 1.0E-03 'picometres' 'angstroms' '*' 1.0E-02 'picometres' 'femtometres' '*' 1.0E+03 # 'femtometres' 'metres' '*' 1.0E-15 'femtometres' 'centimetres' '*' 1.0E-13 'femtometres' 'millimetres' '*' 1.0E-12 'femtometres' 'nanometres' '*' 1.0E-06 'femtometres' 'angstroms' '*' 1.0E-05 'femtometres' 'picometres' '*' 1.0E-03 ### 'reciprocal_centimetres' 'reciprocal_metres' '*' 1.0E+02 'reciprocal_centimetres' 'reciprocal_millimetres' '*' 1.0E-01 'reciprocal_centimetres' 'reciprocal_nanometres' '*' 1.0E-07 'reciprocal_centimetres' 'reciprocal_angstroms' '*' 1.0E-08 'reciprocal_centimetres' 'reciprocal_picometres' '*' 1.0E-10 # 'reciprocal_millimetres' 'reciprocal_metres' '*' 1.0E+03 'reciprocal_millimetres' 'reciprocal_centimetres' '*' 1.0E+01 'reciprocal_millimetres' 'reciprocal_nanometres' '*' 1.0E-06 'reciprocal_millimetres' 'reciprocal_angstroms' '*' 1.0E-07 'reciprocal_millimetres' 'reciprocal_picometres' '*' 1.0E-09 # 'reciprocal_nanometres' 'reciprocal_metres' '*' 1.0E+09 'reciprocal_nanometres' 'reciprocal_centimetres' '*' 1.0E+07 'reciprocal_nanometres' 'reciprocal_millimetres' '*' 1.0E+06 'reciprocal_nanometres' 'reciprocal_angstroms' '*' 1.0E-01 'reciprocal_nanometres' 'reciprocal_picometres' '*' 1.0E-03 # 'reciprocal_angstroms' 'reciprocal_metres' '*' 1.0E+10 'reciprocal_angstroms' 'reciprocal_centimetres' '*' 1.0E+08 'reciprocal_angstroms' 'reciprocal_millimetres' '*' 1.0E+07 'reciprocal_angstroms' 'reciprocal_nanometres' '*' 1.0E+01 'reciprocal_angstroms' 'reciprocal_picometres' '*' 1.0E-02 # 'reciprocal_picometres' 'reciprocal_metres' '*' 1.0E+12 'reciprocal_picometres' 'reciprocal_centimetres' '*' 1.0E+10 'reciprocal_picometres' 'reciprocal_millimetres' '*' 1.0E+09 'reciprocal_picometres' 'reciprocal_nanometres' '*' 1.0E+03 'reciprocal_picometres' 'reciprocal_angstroms' '*' 1.0E+01 ### 'nanometres_squared' 'angstroms_squared' '*' 1.0E+02 'nanometres_squared' 'picometres_squared' '*' 1.0E+06 # 'angstroms_squared' 'nanometres_squared' '*' 1.0E-02 'angstroms_squared' 'picometres_squared' '*' 1.0E+04 'angstroms_squared' '8pi2_angstroms_squared' '*' 78.9568 # 'picometres_squared' 'nanometres_squared' '*' 1.0E-06 'picometres_squared' 'angstroms_squared' '*' 1.0E-04 ### 'nanometres_cubed' 'angstroms_cubed' '*' 1.0E+03 'nanometres_cubed' 'picometres_cubed' '*' 1.0E+09 # 'angstroms_cubed' 'nanometres_cubed' '*' 1.0E-03 'angstroms_cubed' 'picometres_cubed' '*' 1.0E+06 # 'picometres_cubed' 'nanometres_cubed' '*' 1.0E-09 'picometres_cubed' 'angstroms_cubed' '*' 1.0E-06 ### 'kilopascals' 'gigapascals' '*' 1.0E-06 'gigapascals' 'kilopascals' '*' 1.0E+06 ### 'hours' 'minutes' '*' 6.0E+01 'hours' 'seconds' '*' 3.6E+03 'hours' 'microseconds' '*' 3.6E+09 # 'minutes' 'hours' '/' 6.0E+01 'minutes' 'seconds' '*' 6.0E+01 'minutes' 'microseconds' '*' 6.0E+07 # 'seconds' 'hours' '/' 3.6E+03 'seconds' 'minutes' '/' 6.0E+01 'seconds' 'microseconds' '*' 1.0E+06 # 'microseconds' 'hours' '/' 3.6E+09 'microseconds' 'minutes' '/' 6.0E+07 'microseconds' 'seconds' '/' 1.0E+06 ### 'celsius' 'kelvins' '-' 273.0 'kelvins' 'celsius' '+' 273.0 ### 'electrons_per_nanometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E+03 'electrons_per_nanometres_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+09 # 'electrons_per_angstroms_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-03 'electrons_per_angstroms_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+06 # 'electrons_per_picometres_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-09 'electrons_per_picometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E-06 ### ######################## ## DICTIONARY_HISTORY ## ######################## loop_ _dictionary_history.version _dictionary_history.update _dictionary_history.revision 1.3.1 2003-08-13 ; Changes as per Frances C. Bernstein. + Identify initials. + Adopt British spelling for centre in text. + Set \p and \%Angstrom and powers. + Clean up commas and unclear wordings. + Clean up tenses in history. Changes as per Gotzon Madariaga. + Fix the ARRAY_DATA example to align '_array_data.binary_id' and X-Binary-Id. + Add a range to '_array_intensities.gain_esd'. + In the example of DIFFRN_DETECTOR_ELEMENT, '_diffrn_detector_element.id' and '_diffrn_detector_element.detector_id' interchanged. + Fix typos for direction, detector and axes. + Clarify description of polarisation. + Clarify axes in '_diffrn_detector_element.center[1]' '_diffrn_detector_element.center[2]'. + Add local item types for items that are pointers. (HJB) ; 1.3.0 2003-07-24 ; Changes as per Brian McMahon. + Consistently quote tags embedded in text. + Clean up introductory comments. + Adjust line lengths to fit in 80 character window. + Fix several descriptions in AXIS category which referred to '_axis.type' instead of the current item. + Fix erroneous use of deprecated item '_diffrn_detector_axis.id' in examples for DIFFRN_SCAN_AXIS. + Add deprecated items '_diffrn_detector_axis.id' and '_diffrn_measurement_axis.id'. (HJB) ; 1.2.4 2003-07-14 ; Changes as per I. David Brown. + Enhance descriptions in DIFFRN_SCAN_AXIS to make them less dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS. + Provide a copy of the deprecated DIFFRN_FRAME_DATA category for completeness. (HJB) ; 1.2.3 2003-07-03 ; Cleanup to conform to ITVG. + Correct sign error in ..._cubed units. + Correct '_diffrn_radiation.polarisn_norm' range. (HJB) ; 1.2.2 2003-03-10 ; Correction of typos in various DIFFRN_SCAN_AXIS descriptions. (HJB) ; 1.2.1 2003-02-22 ; Correction of ATOM_ for ARRAY_ typos in various descriptions. (HJB) ; 1.2 2003-02-07 ; Corrections to encodings (remove extraneous hyphens) remove extraneous underscore in '_array_structure.encoding_type' enumeration. Correct typos in items units list. (HJB) ; 1.1.3 2001-04-19 ; Another typo corrections by Wilfred Li, and cleanup by HJB. ; 1.1.2 2001-03-06 ; Several typo corrections by Wilfred Li. ; 1.1.1 2001-02-16 ; Several typo corrections by JW. ; 1.1 2001-02-06 ; Draft resulting from discussions on header for use at NSLS. (HJB) + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME. + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'. + Add '_diffrn_measurement_axis.measurement_device' and change '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'. + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source', '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm', '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end', '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr', '_diffrn_scan_axis.displacement_rstrt_incr', '_diffrn_scan_frame_axis.angle_increment', '_diffrn_scan_frame_axis.angle_rstrt_incr', '_diffrn_scan_frame_axis.displacement', '_diffrn_scan_frame_axis.displacement_increment',and '_diffrn_scan_frame_axis.displacement_rstrt_incr'. + Add '_diffrn_measurement.device' to category key. + Update yyyy-mm-dd to allow optional time with fractional seconds for time stamps. + Fix typos caught by RS. + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to allow for coupled axes, as in spiral scans. + Add examples for fairly complete headers thanks to R. Sweet and P. Ellis. ; 1.0 2000-12-21 ; Release version - few typos and tidying up. (BM & HJB) + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end of dictionary. + Alphabetize dictionary. ; 0.7.1 2000-09-29 ; Cleanup fixes. (JW) + Correct spelling of diffrn_measurement_axis in '_axis.id' + Correct ordering of uses of '_item.mandatory_code' and '_item_default.value'. ; 0.7.0 2000-09-09 ; Respond to comments by I. David Brown. (HJB) + Add further comments on '\n' and '\t'. + Update ITEM_UNITS_LIST by taking section from mmCIF dictionary and adding metres. Change 'meter' to 'metre' throughout. + Add missing enumerations to '_array_structure.compression_type' and make 'none' the default. + Remove parent-child relationship between '_array_structure_list.index' and '_array_structure_list.precedence'. + Improve alphabetization. + Fix '_array_intensities_gain.esd' related function. + Improve comments in AXIS. + Fix DIFFRN_FRAME_DATA example. + Remove erroneous DIFFRN_MEASUREMENT example. + Add '_diffrn_measurement_axis.id' to the category key. ; 0.6.0 1999-01-14 ; Remove redundant information for ENC_NONE data. (HJB) + After the D5 remove binary section identifier, size and compression type. + Add Control-L to header. ; 0.5.1 1999-01-03 ; Cleanup of typos and syntax errors. (HJB) + Cleanup example details for DIFFRN_SCAN category. + Add missing quote marks for '_diffrn_scan.id' definition. ; 0.5 1999-01-01 ; Modifications for axis definitions and reduction of binary header. (HJB) + Restore '_diffrn_detector.diffrn_id' to DIFFRN_DETECTOR KEY. + Add AXIS category. + Bring in complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories from cif_mm.dic for clarity. + Change '_array_structure.encoding_type' from type code to uline and added X-Binary-Element-Type to MIME header. + Add detector beam centre '_diffrn_detector_element.center[1]' and '_diffrn_detector_element.center[2]'. + Correct item name of '_diffrn_refln.frame_id'. + Replace reference to '_array_intensities.undefined' by '_array_intensities.undefined_value'. + Replace references to '_array_intensity.scaling' with '_array_intensities.scaling'. + Add DIFFRN_SCAN... categories. ; 0.4 1998-08-11 ; Modifications to the 0.3 imgCIF draft. (HJB) + Reflow comment lines over 80 characters and corrected typos. + Update examples and descriptions of MIME encoded data. + Change name to cbfext98.dic. ; 0.3 1998-07-04 ; Modifications for imgCIF. (HJB) + Add binary type, which is a text field containing a variant on MIME encoded data. + Change type of '_array_data.data' to binary and specify internal structure of raw binary data. + Add '_array_data.binary_id', and make '_diffrn_frame_data.binary_id' and '_array_intensities.binary_id' into pointers to this item. ; 0.2 1997-12-02 ; Modifications to the CBF draft. (JW) + Add category hierarchy for describing frame data developed from discussions at the BNL imgCIF Workshop Oct 1997. The following changes are made in implementing the workshop draft. Category DIFFRN_ARRAY_DATA is renamed to DIFFRN_FRAME_DATA. Category DIFFRN_FRAME_TYPE is renamed to DIFFRN_DETECTOR_ELEMENT. The parent item for '_diffrn_frame_data.array_id' is changed from '_array_structure_list.array_id' to '_array_structure.id'. Item '_diffrn_detector.array_id' is deleted. + Add data item '_diffrn_frame_data.binary_id' to identify data groups within a binary section. The formal identification of the binary section is still fuzzy. ; 0.1 1997-01-24 ; First draft of this dictionary in DDL 2.1 compliant format by John Westbrook (JW). This version is adapted from the Crystallographic Binary File (CBF) Format Draft Proposal provided by Andy Hammersley (AH). Modifications to the CBF draft. (JW) + In this version the array description has been cast in the categories ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. These categories have been generalized to describe array data of arbitrary dimension. + Array data in this description are contained in the category ARRAY_DATA. This departs from the CBF notion of data existing in some special comment. In this description, data is handled as an ordinary data item encapsulated in a character data type. Although data this manner deviates from CIF conventions, it does not violate any DDL 2.1 rules. DDL 2.1 regular expressions can be used to define the binary representation which will permit some level of data validation. In this version, the placeholder type code "any" has been used. This translates to a regular expression which will match any pattern. It should be noted that DDL 2.1 already supports array data objects although these have not been used in the current mmCIF dictionary. It may be possible to use the DDL 2.1 ITEM_STRUCTURE and ITEM_STRUCTURE_LIST categories to provide the information that is carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. By moving the array structure to the DDL level it would be possible to define an array type as well as a regular expression defining the data format. + Multiple array sections can be properly handled within a single datablock. ; #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof ./CBFlib-0.9.2.2/doc/cif_img_1_3_2.dic0000644000076500007650000054573611603702115015330 0ustar yayayaya############################################################################## # # # Image CIF Dictionary (imgCIF) # # and Crystallographic Binary File Dictionary (CBF) # # Extending the Macromolecular CIF Dictionary (mmCIF) # # # # Version 1.3.2 # # of 2005-06-22 # # # # by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook # # # # This dictionary was adapted from format discussed at the imgCIF Workshop, # # held at BNL Oct 1997 and the Crystallographic Binary File Format Draft # # Proposal by Andrew Hammersley. The first DDL 2.1 Version was created by # # John Westbrook. This version was drafted by Herbert J. Bernstein and # # incorporates comments by I. David Brown, John Westbrook, Brian McMahon, # # Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li, Gotzon Madariaga, # # Frances C. Bernstein and others. # ############################################################################## data_cif_img.dic _dictionary.title cif_img.dic _dictionary.version 1.3.2 _dictionary.datablock_id cif_img.dic ############################################################################## # CONTENTS # # CATEGORY_GROUP_LIST # # category ARRAY_DATA # # _array_data.array_id # _array_data.binary_id # _array_data.data # # category ARRAY_ELEMENT_SIZE # # _array_element_size.array_id # _array_element_size.index # _array_element_size.size # # category ARRAY_INTENSITIES # # _array_intensities.array_id # _array_intensities.binary_id # _array_intensities.gain # _array_intensities.gain_esd # _array_intensities.linearity # _array_intensities.offset # _array_intensities.scaling # _array_intensities.overload # _array_intensities.undefined_value # # category ARRAY_STRUCTURE # # _array_structure.byte_order # _array_structure.compression_type # _array_structure.encoding_type # _array_structure.id # # category ARRAY_STRUCTURE_LIST # # _array_structure_list.axis_set_id # _array_structure_list.array_id # _array_structure_list.dimension # _array_structure_list.direction # _array_structure_list.index # _array_structure_list.precedence # # category ARRAY_STRUCTURE_LIST_AXIS # # _array_structure_list_axis.axis_id # _array_structure_list_axis.axis_set_id # _array_structure_list_axis.angle # _array_structure_list_axis.angle_increment # _array_structure_list_axis.displacement_increment # _array_structure_list_axis.angular_pitch # _array_structure_list_axis.radial_pitch # # category AXIS # # _axis.depends_on # _axis.equipment # _axis.id # _axis.offset[1] # _axis.offset[2] # _axis.offset[3] # _axis.type # _axis.vector[1] # _axis.vector[2] # _axis.vector[3] # # category DIFFRN_DATA_FRAME # # _diffrn_data_frame.array_id # _diffrn_data_frame.binary_id # _diffrn_data_frame.detector_element_id # _diffrn_data_frame.id # # category DIFFRN_DETECTOR # # _diffrn_detector.details # _diffrn_detector.detector # _diffrn_detector.diffrn_id # _diffrn_detector.dtime # _diffrn_detector.id # _diffrn_detector.number_of_axes # _diffrn_detector.type # # category DIFFRN_DETECTOR_AXIS # # _diffrn_detector_axis.axis_id # _diffrn_detector_axis.detector_id # # category DIFFRN_DETECTOR_ELEMENT # # _diffrn_detector_element.center[1] # _diffrn_detector_element.center[2] # _diffrn_detector_element.id # _diffrn_detector_element.detector_id # # category DIFFRN_MEASUREMENT # # _diffrn_measurement.diffrn_id # _diffrn_measurement.details # _diffrn_measurement.device # _diffrn_measurement.device_details # _diffrn_measurement.device_type # _diffrn_measurement.id # _diffrn_measurement.method # _diffrn_measurement.number_of_axes # _diffrn_measurement.specimen_support # # category DIFFRN_MEASUREMENT_AXIS # # _diffrn_measurement_axis.axis_id # _diffrn_measurement_axis.measurement_device # _diffrn_measurement_axis.measurement_id # # category DIFFRN_RADIATION # # _diffrn_radiation.collimation # _diffrn_radiation.diffrn_id # _diffrn_radiation.div_x_source # _diffrn_radiation.div_y_source # _diffrn_radiation.div_x_y_source # _diffrn_radiation.filter_edge' # _diffrn_radiation.inhomogeneity # _diffrn_radiation.monochromator # _diffrn_radiation.polarisn_norm # _diffrn_radiation.polarisn_ratio # _diffrn_radiation.polarizn_source_norm # _diffrn_radiation.polarizn_source_ratio # _diffrn_radiation.probe # _diffrn_radiation.type # _diffrn_radiation.xray_symbol # _diffrn_radiation.wavelength_id # # category DIFFRN_REFLN # # _diffrn_refln.frame_id # # category DIFFRN_SCAN # # _diffrn_scan.id # _diffrn_scan.date_end # _diffrn_scan.date_start # _diffrn_scan.integration_time # _diffrn_scan.frame_id_start # _diffrn_scan.frame_id_end # _diffrn_scan.frames # # category DIFFRN_SCAN_AXIS # # _diffrn_scan_axis.axis_id # _diffrn_scan_axis.angle_start # _diffrn_scan_axis.angle_range # _diffrn_scan_axis.angle_increment # _diffrn_scan_axis.angle_rstrt_incr # _diffrn_scan_axis.displacement_start # _diffrn_scan_axis.displacement_range # _diffrn_scan_axis.displacement_increment # _diffrn_scan_axis.displacement_rstrt_incr # _diffrn_scan_axis.scan_id # # category DIFFRN_SCAN_FRAME # # _diffrn_scan_frame.date # _diffrn_scan_frame.frame_id # _diffrn_scan_frame.frame_number # _diffrn_scan_frame.integration_time # _diffrn_scan_frame.scan_id # # category DIFFRN_SCAN_FRAME_AXIS # # _diffrn_scan_frame_axis.axis_id # _diffrn_scan_frame_axis.angle # _diffrn_scan_frame_axis.angle_increment # _diffrn_scan_frame_axis.angle_rstrt_incr # _diffrn_scan_frame_axis.displacement # _diffrn_scan_frame_axis.displacement_increment # _diffrn_scan_frame_axis.displacement_rstrt_incr # _diffrn_scan_frame_axis.frame_id # # ***DEPRECATED*** data items # # _diffrn_detector_axis.id # _diffrn_measurement_axis.id # # ***DEPRECATED*** category DIFFRN_FRAME_DATA # # _diffrn_frame_data.array_id # _diffrn_frame_data.binary_id # _diffrn_frame_data.detector_element_id # _diffrn_frame_data.id # # # ITEM_TYPE_LIST # ITEM_UNITS_LIST # DICTIONARY_HISTORY # ############################################################################## ######################### ## CATEGORY_GROUP_LIST ## ######################### loop_ _category_group_list.id _category_group_list.parent_id _category_group_list.description 'inclusive_group' . ; Categories that belong to the dictionary extension. ; 'array_data_group' 'inclusive_group' ; Categories that describe array data. ; 'axis_group' 'inclusive_group' ; Categories that describe axes. ; 'diffrn_group' 'inclusive_group' ; Categories that describe details of the diffraction experiment. ; ############## # ARRAY_DATA # ############## save_ARRAY_DATA _category.description ; Data items in the ARRAY_DATA category are the containers for the array data items described in category ARRAY_STRUCTURE. ; _category.id array_data _category.mandatory_code no loop_ _category_key.name '_array_data.array_id' '_array_data.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows two binary data blocks. The first one was compressed by the CBF_CANONICAL compression algorithm and presented as hexadecimal data. The first character "H" on the data lines means hexadecimal. It could have been "O" for octal or "D" for decimal. The second character on the line shows the number of bytes in each word (in this case "4"), which then requires 8 hexadecimal digits per word. The third character gives the order of octets within a word, in this case "<" for the ordering 4321 (i.e. "big-endian"). Alternatively the character ">" could have been used for the ordering 1234 (i.e. "little-endian"). The block has a "message digest" to check the integrity of the data. The second block is similar, but uses CBF_PACKED compression and BASE64 encoding. Note that the size and the digest are different. ; ; loop_ _array_data.array_id _array_data.binary_id _array_data.data image_1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_CANONICAL" Content-Transfer-Encoding: X-BASE16 X-Binary-Size: 3927126 X-Binary-ID: 1 Content-MD5: u2sTJEovAHkmkDjPi+gWsg== # Hexadecimal encoding, byte 0, byte order ...21 # H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ... .... --CIF-BINARY-FORMAT-SECTION---- ; image_2 2 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF-PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3745758 X-Binary-ID: 2 Content-MD5: 1zsJjWPfol2GYl2V+QSXrw== ELhQAAAAAAAA... ... --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_data.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_array_data.array_id' _item.category_id array_data _item.mandatory_code yes _item_type.code code save_ save__array_data.binary_id _item_description.description ; This item is an integer identifier which, along with '_array_data.array_id' should uniquely identify the particular block of array data. If '_array_data.binary_id' is not explicitly given, it defaults to 1. The value of '_array_data.binary_id' distinguishes among multiple sets of data with the same array structure. If the MIME header of the data array specifies a value for X-Binary-Id, the value of '_array_data.binary_id' should be equal the value given for X-Binary-Id. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_data.binary_id' array_data implicit '_diffrn_data_frame.binary_id' diffrn_data_frame implicit '_array_intensities.binary_id' array_intensities implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.binary_id' '_array_data.binary_id' '_array_intensities.binary_id' '_array_data.binary_id' _item_default.value 1 _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_data.data _item_description.description ; The value of '_array_data.data' contains the array data encapsulated in a STAR string. The representation used is a variant on the Multipurpose Internet Mail Extensions (MIME) specified in RFC 2045-2049 by N. Freed et al. The boundary delimiter used in writing an imgCIF or CBF is "--CIF-BINARY-FORMAT-SECTION--" (including the required initial "--"). The Content-Type may be any of the discrete types permitted in RFC 2045; "application/octet-stream" is recommended. If an octet stream was compressed, the compression should be specified by the parameter 'conversions="x-CBF_PACKED"' or the parameter 'conversions="x-CBF_CANONICAL"'. The Content-Transfer-Encoding may be "BASE64", "Quoted-Printable", "X-BASE8", "X-BASE10", or "X-BASE16" for an imgCIF or "BINARY" for a CBF. The octal, decimal and hexadecimal transfer encodings are for convenience in debugging, and are not recommended for archiving and data interchange. In an imgCIF file, the encoded binary data begins after the empty line terminating the header. In a CBF, the raw binary data begins after an empty line terminating the header and after the sequence: Octet Hex Decimal Purpose 0 0C 12 (ctrl-L) Page break 1 1A 26 (ctrl-Z) Stop listings in MS-DOS 2 04 04 (Ctrl-D) Stop listings in UNIX 3 D5 213 Binary section begins None of these octets are included in the calculation of the message size, nor in the calculation of the message digest. The X-Binary-Size header specifies the size of the equivalent binary data in octets. If compression was used, this size is the size after compression, including any book-keeping fields. An adjustment is made for the deprecated binary formats in which 8 bytes of binary header are used for the compression type. In that case, the 8 bytes used for the compression type is subtracted from the size, so that the same size will be reported if the compression type is supplied in the MIME header. Use of the MIME header is the recommended way to supply the compression type. In general, no portion of the binary header is included in the calculation of the size. The X-Binary-Element-Type header specifies the type of binary data in the octets, using the same descriptive phrases as in '_array_structure.encoding_type'. The default value is "unsigned 32-bit integer". An MD5 message digest may, optionally, be used. The "RSA Data Security, Inc. MD5 Message-Digest Algorithm" should be used. No portion of the header is included in the calculation of the message digest. If the Transfer Encoding is "X-BASE8", "X-BASE10", or "X-BASE16", the data is presented as octal, decimal or hexadecimal data organized into lines or words. Each word is created by composing octets of data in fixed groups of 2, 3, 4, 6 or 8 octets, either in the order ...4321 ("big- endian") or 1234... (little-endian). If there are fewer than the specified number of octets to fill the last word, then the missing octets are presented as "==" for each missing octet. Exactly two equal signs are used for each missing octet even for octal and decimal encoding. The format of lines is: rnd xxxxxx xxxxxx xxxxxx where r is "H", "O", or "D" for hexadecimal, octal or decimal, n is the number of octets per word. and d is "<" for ">" for the "...4321" and "1234..." octet orderings respectively. The "==" padding for the last word should be on the appropriate side to correspond to the missing octets, e.g. H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000 or H3> FF0700 00==== For these hex, octal and decimal formats, only, comments beginning with "#" are permitted to improve readability. BASE64 encoding follows MIME conventions. Octets are in groups of three, c1, c2, c3. The resulting 24 bits are broken into four 6-bit quantities, starting with the high-order six bits (c1 >> 2) of the first octet, then the low-order two bits of the first octet followed by the high-order 4 bits of the second octet ((c1 & 3)<<4 | (c2>>4)), then the bottom 4 bits of the second octet followed by the high order two bits of the last octet ((c2 & 15)<<2 | (c3>>6)), then the bottom six bits of the last octet (c3 & 63). Each of these four quantities is translated into an ASCII character using the mapping: 1 2 3 4 5 6 0123456789012345678901234567890123456789012345678901234567890123 | | | | | | | ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/ With short groups of octets padded on the right with one "=" if c3 is missing, and with "==" if both c2 and c3 are missing. QUOTED-PRINTABLE encoding also follows MIME conventions, copying octets without translation if their ASCII values are 32..38, 42, 48..57, 59..60, 62, 64..126 and the octet is not a ";" in column 1. All other characters are translated to =nn, where nn is the hexadecimal encoding of the octet. All lines are "wrapped" with a terminating "=" (i.e. the MIME conventions for an implicit line terminator are never used). ; _item.name '_array_data.data' _item.category_id array_data _item.mandatory_code yes _item_type.code binary save_ ###################### # ARRAY_ELEMENT_SIZE # ###################### save_ARRAY_ELEMENT_SIZE _category.description ; Data items in the ARRAY_ELEMENT_SIZE category record the physical size of array elements along each array dimension. ; _category.id array_element_size _category.mandatory_code no loop_ _category_key.name '_array_element_size.array_id' '_array_element_size.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A regular 2D array with a uniform element dimension of 1220 nanometres. ; ; loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size image_1 1 1.22e-6 image_1 2 1.22e-6 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_element_size.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_array_element_size.array_id' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.index _item_description.description ; This item is a pointer to '_array_structure_list.index' in the ARRAY_STRUCTURE_LIST category. ; _item.name '_array_element_size.index' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.size _item_description.description ; The size in metres of an image element in this dimension. This supposes that the elements are arranged on a regular grid. ; _item.name '_array_element_size.size' _item.category_id array_element_size _item.mandatory_code yes _item_type.code float _item_units.code 'metres' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ ##################### # ARRAY_INTENSITIES # ##################### save_ARRAY_INTENSITIES _category.description ; Data items in the ARRAY_INTENSITIES category record the information required to recover the intensity data from the set of data values stored in the ARRAY_DATA category. The actual detector may have a complex relationship between the raw intensity values and the number of incident photons. In most cases, the number stored in the final array will have a simple linear relationship to the actual number of incident photons, given by '_array_intensities.gain'. If raw, uncorrected values are presented (e.g for calibration experiments), the value of '_array_intensities.linearity' will be 'raw' and '_array_intensities.gain' will not be used. ; _category.id array_intensities _category.mandatory_code no loop_ _category_key.name '_array_intensities.array_id' '_array_intensities.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 ; ; loop_ _array_intensities.array_id _array_intensities.linearity _array_intensities.gain _array_intensities.overload _array_intensities.undefined_value image_1 linear 1.2 655535 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_intensities.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_array_intensities.array_id' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code save_ save__array_intensities.binary_id _item_description.description ; This item is a pointer to '_array_data.binary_id' in the ARRAY_DATA category. ; _item.name '_array_intensities.binary_id' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code int save_ save__array_intensities.gain _item_description.description ; Detector "gain". The factor by which linearized intensity count values should be divided to produce true photon counts. ; _item.name '_array_intensities.gain' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain_esd' 'associated_value' save_ save__array_intensities.gain_esd _item_description.description ; The estimated standard deviation in detector "gain". ; _item.name '_array_intensities.gain_esd' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain' 'associated_esd' save_ save__array_intensities.linearity _item_description.description ; The intensity linearity scaling used from raw intensity to the stored element value: 'linear' is obvious 'offset' means that the value defined by '_array_intensities.offset' should be added to each element value. 'scaling' means that the value defined by '_array_intensities.scaling' should be multiplied with each element value. 'scaling_offset' is the combination of the two previous cases, with the scale factor applied before the offset value. 'sqrt_scaled' means that the square root of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and squaring the result. 'logarithmic_scaled' means that the logarithm based 10 of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and calculating 10 to the power of this number. 'raw' means that the data is a set of raw values straight from the detector. ; _item.name '_array_intensities.linearity' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'linear' . 'offset' ; The value defined by '_array_intensities.offset' should be added to each element value. ; 'scaling' ; The value defined by '_array_intensities.scaling' should be multiplied with each element value. ; 'scaling_offset' ; The combination of the scaling and offset with the scale factor applied before the offset value. ; 'sqrt_scaled' ; The square root of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and squaring the result. ; 'logarithmic_scaled' ; The logarithm based 10 of raw intensities multiplied by '_array_intensities.scaling' is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by '_array_intensities.scaling' and calculating 10 to the power of this number. ; 'raw' ; The array consists of raw values to which no corrections have been applied. While the handling of the data is similar to that given for 'linear' data with no offset, the meaning of the data differs in that the number of incident photons is not necessarily linearly related to the number of counts reported. This value is intended for use either in calibration experiments or to allow for handling more complex data fitting algorithms than are allowed for by this data item. ; save_ save__array_intensities.offset _item_description.description ; Offset value to add to array element values in the manner described by item '_array_intensities.linearity'. ; _item.name '_array_intensities.offset' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.scaling _item_description.description ; Multiplicative scaling value to be applied to array data in the manner described by item '_array_intensities.linearity'. ; _item.name '_array_intensities.scaling' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.overload _item_description.description ; The saturation intensity level for this data array. ; _item.name '_array_intensities.overload' _item.category_id array_intensities _item.mandatory_code no _item_type.code float _item_units.code 'counts' save_ save__array_intensities.undefined_value _item_description.description ; A value to be substituted for undefined values in the data array. ; _item.name '_array_intensities.undefined_value' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ ################### # ARRAY_STRUCTURE # ################### save_ARRAY_STRUCTURE _category.description ; Data items in the ARRAY_STRUCTURE category record the organization and encoding of array data which may be stored in the ARRAY_DATA category. ; _category.id array_structure _category.mandatory_code no _category_key.name '_array_structure.id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order image_1 "unsigned 16-bit integer" none little_endian ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure.byte_order _item_description.description ; The order of bytes for integer values which require more than 1-byte. (IBM-PC's and compatibles, and Dec-Vaxes use low-byte-first ordered integers, whereas Hewlett Packard 700 series, Sun-4 and Silicon Graphics use high-byte-first ordered integers. Dec-Alphas can produce/use either depending on a compiler switch.) ; _item.name '_array_structure.byte_order' _item.category_id array_structure _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'big_endian' ; The first byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; 'little_endian' ; The last byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; save_ save__array_structure.compression_type _item_description.description ; Type of data compression method used to compress the array data. ; _item.name '_array_structure.compression_type' _item.category_id array_structure _item.mandatory_code no _item_type.code code _item_default.value 'none' loop_ _item_enumeration.value _item_enumeration.detail 'none' ; Data are stored in normal format as defined by '_array_structure.encoding_type' and '_array_structure.byte_order'. ; 'byte_offsets' ; Using the compression scheme defined in CBF definition Section 5.0. ; 'packed' ; Using the 'packed' compression scheme, a CCP4-style packing (CBFlib section 3.3.2) ; 'canonical' ; Using the 'canonical' compression scheme (CBFlib section 3.3.1) ; save_ save__array_structure.encoding_type _item_description.description ; Data encoding of a single element of array data. In several cases, the IEEE format is referenced. See "IEEE Standard for Binary Floating-Point Arithmetic", ANSI/IEEE Std 754-1985, the Institute of Electrical and Electronics Engineers, Inc., NY 1985. ; _item.name '_array_structure.encoding_type' _item.category_id array_structure _item.mandatory_code yes _item_type.code uline loop_ _item_enumeration.value 'unsigned 8-bit integer' 'signed 8-bit integer' 'unsigned 16-bit integer' 'signed 16-bit integer' 'unsigned 32-bit integer' 'signed 32-bit integer' 'signed 32-bit real IEEE' 'signed 64-bit real IEEE' 'signed 32-bit complex IEEE' save_ save__array_structure.id _item_description.description ; The value of '_array_structure.id' must uniquely identify each item of array data. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure.id' array_structure yes '_array_data.array_id' array_data yes '_array_structure_list.array_id' array_structure_list yes '_array_intensities.array_id' array_intensities yes '_diffrn_data_frame.array_id' diffrn_data_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_data.array_id' '_array_structure.id' '_array_structure_list.array_id' '_array_structure.id' '_array_intensities.array_id' '_array_structure.id' '_diffrn_data_frame.array_id' '_array_structure.id' save_ ######################## # ARRAY_STRUCTURE_LIST # ######################## save_ARRAY_STRUCTURE_LIST _category.description ; Data items in the ARRAY_STRUCTURE_LIST category record the size and organization of each array dimension. The relationship to physical axes may be given. ; _category.id array_structure_list _category.mandatory_code no loop_ _category_key.name '_array_structure_list.array_id' '_array_structure_list.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - An image array of 1300 x 1200 elements. The raster order of the image is left-to-right (increasing) in the first dimension and bottom-to-top (decreasing) in the second dimension. ; ; loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id image_1 1 1300 1 increasing ELEMENT_X image_1 2 1200 2 decreasing ELEMENY_Y ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure_list.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_array_structure_list.array_id' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code code save_ save__array_structure_list.axis_set_id _item_description.description ; This is a descriptor for the physical axis or set of axes corresponding to an array index. This data item is related to the axes of the detector itself given in DIFFRN_DETECTOR_AXIS, but usually differ in that the axes in this category are the axes of the coordinate system of reported data points, while the axes in DIFFRN_DETECTOR_AXIS are the physical axes of the detector describing the "poise" of the detector as an overall physical object. If there is only one axis in the set, the identifier of that axis should be used as the identifier of the set. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.axis_set_id' array_structure_list yes '_array_structure_list_axis.axis_set_id' array_structure_list_axis implicit _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_structure_list_axis.axis_set_id' '_array_structure_list.axis_set_id' save_ save__array_structure_list.dimension _item_description.description ; The number of elements stored in the array structure in this dimension. ; _item.name '_array_structure_list.dimension' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.direction _item_description.description ; Identifies the direction in which this array index changes. ; _item.name '_array_structure_list.direction' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_enumeration.value _item_enumeration.detail 'increasing' ; Indicates the index changes from 1 to the maximum dimension. ; 'decreasing' ; Indicates the index changes from the maximum dimension to 1. ; save_ save__array_structure_list.index _item_description.description ; Identifies the one-based index of the row or column in the array structure. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.index' array_structure_list yes '_array_structure_list.precedence' array_structure_list yes '_array_element_size.index' array_element_size yes _item_type.code int loop_ _item_linked.child_name _item_linked.parent_name '_array_element_size.index' '_array_structure_list.index' loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.precedence _item_description.description ; Identifies the rank order in which this array index changes with respect to other array indices. The precedence of 1 indicates the index which changes fastest. ; _item.name '_array_structure_list.precedence' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ ############################# # ARRAY_STRUCTURE_LIST_AXIS # ############################# save_ARRAY_STRUCTURE_LIST_AXIS _category.description ; Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe the physical settings of sets axes for the centres of pixels that correspond to data points described in the ARRAY_STRUCTURE_LIST category. In the simplest cases, the physical increments of a single axis correspond to the increments of a single array index. More complex organizations, e.g. spiral scans, may require coupled motions along multiple axes. Note that a spiral scan uses two coupled axis, one for the angular direction, one for the radial direction. This differs from a cylindrical scan for which the two axes are not coupled into one set. ; _category.id array_structure_list_axis _category.mandatory_code no loop_ _category_key.name '_array_structure_list_axis.axis_set_id' '_array_structure_list_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' save_ save__array_structure_list_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes from the set of axes for which settings are being specified. Multiple axes may be specified for the same value of '_array_structure_list_axis.axis_set_id' This item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_array_structure_list_axis.axis_id' _item.category_id array_structure_list_axis _item.mandatory_code yes _item_type.code code save_ save__array_structure_list_axis.axis_set_id _item_description.description ; The value of this data item is the identifier of the set of axes for which axis settings are being specified. Multiple axes may be specified for the same value of '_array_structure_list_axis.axis_set_id'. This item is a pointer to '_array_structure_list.axis_set_id' in the ARRAY_STRUCTURE_LIST category. If this item is not specified, it defaults to the corresponding axis identifier. ; _item.name '_array_structure_list_axis.axis_set_id' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_type.code code save_ save__array_structure_list_axis.angle _item_description.description ; The setting of the specified axis in degrees for the first data point of the array index with the corresponding value of '_array_structure_list.axis_set_id'. If the index is specified as 'increasing' this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing' this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.angle' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.angle_increment _item_description.description ; The pixel-centre-to-pixel-centre increment in the angular setting of the specified axis in degrees. This is not meaningful in the case of 'constant velocity' spiral scans and should not be specified in that case. See '_array_structure_list_axis.angular_pitch'. ; _item.name '_array_structure_list_axis.angle_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for the first data point of the array index with the corresponding value of '_array_structure_list.axis_set_id'. If the index is specified as 'increasing' this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing' this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.displacement' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.displacement_increment _item_description.description ; The pixel-centre-to-pixel-centre increment for the displacement setting of the specified axis in millimetres. ; _item.name '_array_structure_list_axis.displacement_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.angular_pitch _item_description.description ; The pixel-centre-to-pixel-centre distance for a one step change in the setting of the specified axis in millimetres. This is meaningful only for 'constant velocity' spiral scans, or for uncoupled angular scans at a constant radius (cylindrical scan) and should not be specified for cases in which the angle between pixels, rather than the distance between pixels is uniform. See '_array_structure_list_axis.angle_increment'. ; _item.name '_array_structure_list_axis.angular_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.radial_pitch _item_description.description ; The radial distance from one "cylinder" of pixels to the next in millimetres. If the scan is a 'constant velocity' scan with differing angular displacements between pixels, the value of this item may differ significantly from the value of '_array_structure_list_axis.displacement_increment'. ; _item.name '_array_structure_list_axis.radial_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ ######## # AXIS # ######## save_AXIS _category.description ; Data items in the AXIS category record the information required to describe the various goniometer, detector, source and other axes needed to specify a data collection. The location of each axis is specified by two vectors: the axis itself, given as a unit vector, and an offset to the base of the unit vector. These vectors are referenced to a right-handed laboratory coordinate system with its origin in the sample or specimen: | Y (to complete right-handed system) | | | | | |________________X / principal goniometer axis / / / / /Z (to source) Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from the sample or specimen along the principal axis of the goniometer. Axis 2 (Y): The Y-axis completes an orthogonal right-handed system defined by the X-axis and the Z-axis (see below). Axis 3 (Z): The Z-axis is derived from the source axis which goes from the sample to the source. The Z-axis is the component of the source axis in the direction of the source orthogonal to the X-axis in the plane defined by the X-axis and the source axis. These axes are based on the goniometer, not on the orientation of the detector, gravity, etc. The vectors necessary to specify all other axes are given by sets of three components in the order (X, Y, Z). If the axis involved is a rotation axis, it is right handed, i.e. as one views the object to be rotated from the origin (the tail) of the unit vector, the rotation is clockwise. If a translation axis is specified, the direction of the unit vector specifies the sense of positive translation. Note: This choice of coordinate system is similar to, but significantly different from the choice in MOSFLM (Andrew G.W. Leslie, Harry Powell, MRC Laboratory of Molecular Biology, Hills Road, Cambridge CB2 2QH, UK http://www.dl.ac.uk/CCP/CCP4/dist/x-windows/Mosflm/). In MOSFLM, X is along the X-ray beam (the CBF/imgCIF Z axis) and Z is along the rotation axis. All rotations are given in degrees and all translations are given in mm. Axes may be dependent on one another. The X-axis is the only goniometer axis the direction of which is strictly connected to the hardware. All other axes are specified by the positions they would assume when the axes upon which they depend are at their zero points. When specifying detector axes, the axis is given to the beam centre. The location of the beam centre on the detector should be given in the DIFFRN_DETECTOR category in distortion-corrected mm from the (0,0) corner of the detector. It should be noted that many different origins arise in the definition of an experiment. In particular, as noted above, we need to specify the location of the beam centre on the detector in terms of the origin of the detector, which is, of course, not coincident with the centre of the sample. ; _category.id axis _category.mandatory_code no loop_ _category_key.name '_axis.id' '_axis.equipment' loop_ _category_group.id 'inclusive_group' 'axis_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows the axis specification of the axes of a kappa geometry goniometer (See "X-Ray Structure Determination, A Practical Guide", 2nd ed. by G. H. Stout, L. H. Jensen, Wiley Interscience, 1989, 453 pp, p 134.). There are three axes specified, and no offsets. The outermost axis, omega, is pointed along the X-axis. The next innermost axis, kappa, is at a 50 degree angle to the X-axis, pointed away from the source. The innermost axis, phi, aligns with the X-axis when omega and phi are at their zero-points. If T-omega, T-kappa and T-phi are the transformation matrices derived from the axis settings, the complete transformation would be: x' = (T-omega) (T-kappa) (T-phi) x ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] omega rotation goniometer . 1 0 0 kappa rotation goniometer omega -.64279 0 -.76604 phi rotation goniometer kappa 1 0 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - This example show the axis specification of the axes of a detector, source and gravity. We have juggled the order as a reminder that the ordering of presentation of tokens is not significant. We have taken the centre of rotation of the detector to be 68 millimetres in the direction away from the source. ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] source . source . 0 0 1 . . . gravity . gravity . 0 -1 0 . . . tranz translation detector rotz 0 0 1 0 0 -68 twotheta rotation detector . 1 0 0 . . . roty rotation detector twotheta 0 1 0 0 0 -68 rotz rotation detector roty 0 0 1 0 0 -68 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__axis.depends_on _item_description.description ; The value of '_axis.depends_on' specifies the next outermost axis upon which this axis depends. This item is a pointer to '_axis.id' in the same category. ; _item.name '_axis.depends_on' _item.category_id axis _item.mandatory_code no save_ save__axis.equipment _item_description.description ; The value of '_axis.equipment' specifies the type of equipment using the axis: 'goniometer', 'detector', 'gravity', 'source' or 'general'. ; _item.name '_axis.equipment' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail goniometer 'equipment used to orient or position samples' detector 'equipment used to detect reflections' general 'equipment used for general purposes' gravity 'axis specifying the downward direction' source 'axis specifying the direction sample to source' save_ save__axis.offset[1] _item_description.description ; The [1] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[2] _item_description.description ; The [2] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[3] _item_description.description ; The [3] element of the 3-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres ; _item.name '_axis.offset[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.id _item_description.description ; The value of '_axis.id' must uniquely identify each axis relevant to the experiment. Note that multiple pieces of equipment may share the same axis (e.g. a twotheta arm), so that the category key for AXIS also includes the equipment. ; loop_ _item.name _item.category_id _item.mandatory_code '_axis.id' axis yes '_array_structure_list_axis.axis_id' array_structure_list_axis yes '_diffrn_detector_axis.axis_id' diffrn_detector_axis yes '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes '_diffrn_scan_axis.axis_id' diffrn_scan_axis yes '_diffrn_scan_frame_axis.axis_id' diffrn_scan_frame_axis yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_axis.depends_on' '_axis.id' '_array_structure_list_axis.axis_id' '_axis.id' '_diffrn_detector_axis.axis_id' '_axis.id' '_diffrn_measurement_axis.axis_id' '_axis.id' '_diffrn_scan_axis.axis_id' '_axis.id' '_diffrn_scan_frame_axis.axis_id' '_axis.id' save_ save__axis.type _item_description.description ; The value of '_axis.type' specifies the type of axis: 'rotation', 'translation' (or 'general' when the type is not relevant, as for gravity). ; _item.name '_axis.type' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail rotation 'right-handed axis of rotation' translation 'translation in the direction of the axis' general 'axis for which the type is not relevant' save_ save__axis.vector[1] _item_description.description ; The [1] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[2] _item_description.description ; The [2] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[3] _item_description.description ; The [3] element of the 3-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ ##################### # DIFFRN_DATA_FRAME # ##################### save_DIFFRN_DATA_FRAME _category.description ; Data items in the DIFFRN_DATA_FRAME category record the details about each frame of data. The items in this category were previously in a DIFFRN_FRAME_DATA category, which is now deprecated. The items from the old category are provided as aliases but should not be used for new work. ; _category.id diffrn_data_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_data_frame.id' '_diffrn_data_frame.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A frame containing data from 4 frame elements. Each frame element has a common array configuration 'array_1' described in ARRAY_STRUCTURE and related categories. The data for each detector element is stored in four groups of binary data in the ARRAY_DATA category, linked by the array_id and binary_id ; ; loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id frame_1 d1_ccd_1 array_1 1 frame_1 d1_ccd_2 array_1 2 frame_1 d1_ccd_3 array_1 3 frame_1 d1_ccd_4 array_1 4 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_data_frame.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. ; _item.name '_diffrn_data_frame.array_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.array_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0.00 _item_type.code code save_ save__diffrn_data_frame.binary_id _item_description.description ; This item is a pointer to '_array_data.binary_id' in the ARRAY_DATA category. ; _item.name '_diffrn_data_frame.binary_id' _item.category_id diffrn_data_frame _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_frame_data.binary_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code int save_ save__diffrn_data_frame.detector_element_id _item_description.description ; This item is a pointer to '_diffrn_detector_element.id' in the DIFFRN_DETECTOR_ELEMENT category. ; _item.name '_diffrn_data_frame.detector_element_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.detector_element_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.id _item_description.description ; The value of '_diffrn_data_frame.id' must uniquely identify each complete frame of data. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_data_frame.id' diffrn_data_frame yes '_diffrn_refln.frame_id' diffrn_refln yes '_diffrn_scan.frame_id_start' diffrn_scan yes '_diffrn_scan.frame_id_end' diffrn_scan yes '_diffrn_scan_frame.frame_id' diffrn_scan_frame yes '_diffrn_scan_frame_axis.frame_id' diffrn_scan_frame_axis yes _item_aliases.alias_name '_diffrn_frame_data.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_refln.frame_id' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_start' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_end' '_diffrn_data_frame.id' '_diffrn_scan_frame.frame_id' '_diffrn_data_frame.id' '_diffrn_scan_frame_axis.frame_id' '_diffrn_data_frame.id' save_ ########################################################################## # The following is a restatement of the mmCIF DIFFRN_DETECTOR, # # DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for # # the CBF/imgCIF extensions # ########################################################################## ################### # DIFFRN_DETECTOR # ################### save_DIFFRN_DETECTOR _category.description ; Data items in the DIFFRN_DETECTOR category describe the detector used to measure the scattered radiation, including any analyser and post-sample collimation. ; _category.id diffrn_detector _category.mandatory_code no loop_ _category_key.name '_diffrn_detector.diffrn_id' '_diffrn_detector.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_detector.diffrn_id 'd1' _diffrn_detector.detector 'multiwire' _diffrn_detector.type 'Siemens' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector.details _item_description.description ; A description of special aspects of the radiation detector. ; _item.name '_diffrn_detector.details' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'slow mode' save_ save__diffrn_detector.detector _item_description.description ; The general class of the radiation detector. ; _item.name '_diffrn_detector.detector' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector' cifdic.c91 1.0 '_diffrn_detector' cif_core.dic 2.0 _item_type.code text loop_ _item_examples.case 'photographic film' 'scintillation counter' 'CCD plate' 'BF~3~ counter' save_ save__diffrn_detector.diffrn_id _item_description.description ; This data item is a pointer to '_diffrn.id' in the DIFFRN category. The value of '_diffrn.id' uniquely defines a set of diffraction data. ; _item.name '_diffrn_detector.diffrn_id' _item.mandatory_code yes save_ save__diffrn_detector.dtime _item_description.description ; The deadtime in microseconds of the detectors used to measure the diffraction intensities. ; _item.name '_diffrn_detector.dtime' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector_dtime' cifdic.c91 1.0 '_diffrn_detector_dtime' cif_core.dic 2.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code microseconds save_ save__diffrn_detector.id _item_description.description ; The value of '_diffrn_detector.id' must uniquely identify each detector used to collect each diffraction data set. If the value of '_diffrn_detector.id' is not given, it is implicitly equal to the value of '_diffrn_detector.diffrn_id' ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector.id' diffrn_detector implicit '_diffrn_detector_axis.detector_id' diffrn_detector_axis yes loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_detector_axis.detector_id' '_diffrn_detector.id' _item_type.code code save_ save__diffrn_detector.number_of_axes _item_description.description ; The value of '_diffrn_detector.number_of_axes' gives the number of axes of the positioner for the detector identified by '_diffrn_detector.id'. The word "positioner" is a general term used in instrumentation design for devices that are used to change the positions of portions of apparatus by linear translation, rotation, or combinations of such motions. Axes which are used to provide a coordinate system for the face of an area detetctor should not be counted for this data item. The description of each axis should be provided by entries in DIFFRN_DETECTOR_AXIS. ; _item.name '_diffrn_detector.number_of_axes' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_detector.type _item_description.description ; The make, model or name of the detector device used. ; _item.name '_diffrn_detector.type' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ ######################## # DIFFRN_DETECTOR_AXIS # ######################## save_DIFFRN_DETECTOR_AXIS _category.description ; Data items in the DIFFRN_DETECTOR_AXIS category associate axes with detectors. ; _category.id diffrn_detector_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_axis.detector_id' '_diffrn_detector_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_detector_axis.axis_id _item_description.description ; This data item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_diffrn_detector_axis.axis_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_axis.detector_id _item_description.description ; This data item is a pointer to '_diffrn_detector.id' in the DIFFRN_DETECTOR category. This item was previously named '_diffrn_detector_axis.id' which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_detector_axis.detector_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_aliases.alias_name '_diffrn_detector_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ ########################### # DIFFRN_DETECTOR_ELEMENT # ########################### save_DIFFRN_DETECTOR_ELEMENT _category.description ; Data items in the DIFFRN_DETECTOR_ELEMENT category record the details about spatial layout and other characteristics of each element of a detector which may have multiple elements. In most cases, the more detailed information provided in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS are preferable to simply providing the centre. ; _category.id diffrn_detector_element _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_element.id' '_diffrn_detector_element.detector_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Detector d1 is composed of four CCD detector elements, each 200 mm by 200 mm, arranged in a square. in the pattern 1 2 * 3 4 Note that the beam centre is slightly displaced from each of the detector elements, just beyond the lower right corner of 1, the lower left corner of 2, the upper right corner of 3 and the upper left corner of 4. ; ; loop_ _diffrn_detector_element.detector_id _diffrn_detector_element.id _diffrn_detector_element.center[1] _diffrn_detector_element.center[2] d1 d1_ccd_1 201.5 -1.5 d1 d1_ccd_2 -1.8 -1.5 d1 d1_ccd_3 201.6 201.4 d1 d1_ccd_4 -1.7 201.5 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector_element.center[1] _item_description.description ; The value of '_diffrn_detector_element.center[1]' is the X component of the distortion-corrected beam-centre in mm from the (0, 0) (lower left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. ; _item.name '_diffrn_detector_element.center[1]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.center[2] _item_description.description ; The value of '_diffrn_detector_element.center[2]' is the Y component of the distortion-corrected beam-centre in mm from the (0, 0) (lower left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. ; _item.name '_diffrn_detector_element.center[2]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.id _item_description.description ; The value of '_diffrn_detector_element.id' must uniquely identify each element of a detector. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector_element.id' diffrn_detector_element yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.detector_element_id' '_diffrn_detector_element.id' save_ save__diffrn_detector_element.detector_id _item_description.description ; This item is a pointer to '_diffrn_detector.id' in the DIFFRN_DETECTOR category. ; _item.name '_diffrn_detector_element.detector_id' _item.category_id diffrn_detector_element _item.mandatory_code yes _item_type.code code save_ ######################## ## DIFFRN_MEASUREMENT ## ######################## save_DIFFRN_MEASUREMENT _category.description ; Data items in the DIFFRN_MEASUREMENT category record details about the device used to orient and/or position the crystal during data measurement and the manner in which the diffraction data were measured. ; _category.id diffrn_measurement _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement.device' '_diffrn_measurement.diffrn_id' '_diffrn_measurement.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_measurement.diffrn_id 'd1' _diffrn_measurement.device '3-circle camera' _diffrn_measurement.device_type 'Supper model x' _diffrn_measurement.device_details 'none' _diffrn_measurement.method 'omega scan' _diffrn_measurement.details ; Need new example here ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991). Acta Cryst. C47, 2276-2277]. ; ; _diffrn_measurement.diffrn_id 's1' _diffrn_measurement.device_type 'Philips PW1100/20 diffractometer' _diffrn_measurement.method 'theta/2theta (\q/2\q)' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_measurement.device _item_description.description ; The general class of goniometer or device used to support and orient the specimen. If the value of '_diffrn_measurement.device' is not given, it is implicitly equal to the value of '_diffrn_measurement.diffrn_id'. Either '_diffrn_measurement.device' or '_diffrn_measurement.id' may be used to link to other categories. If the experimental setup admits multiple devices, then '_diffrn_measurement.id' is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.device' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_device' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement.device' _item_aliases.alias_name '_diffrn_measurement_device' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '3-circle camera' '4-circle camera' 'kappa-geometry camera' 'oscillation camera' 'precession camera' save_ save__diffrn_measurement.device_details _item_description.description ; A description of special aspects of the device used to measure the diffraction intensities. ; _item.name '_diffrn_measurement.device_details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; commercial goniometer modified locally to allow for 90\% \t arc ; save_ save__diffrn_measurement.device_type _item_description.description ; The make, model or name of the measurement device (goniometer) used. ; _item.name '_diffrn_measurement.device_type' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Supper model q' 'Huber model r' 'Enraf-Nonius model s' 'homemade' save_ save__diffrn_measurement.diffrn_id _item_description.description ; This data item is a pointer to '_diffrn.id' in the DIFFRN category. ; _item.name '_diffrn_measurement.diffrn_id' _item.mandatory_code yes save_ save__diffrn_measurement.details _item_description.description ; A description of special aspects of the intensity measurement. ; _item.name '_diffrn_measurement.details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; save_ save__diffrn_measurement.id _item_description.description ; The value of '_diffrn_measurement.id' must uniquely identify the set of mechanical characteristics of the device used to orient and/or position the sample used during collection of each diffraction data set. If the value of '_diffrn_measurement.id' is not given, it is implicitly equal to the value of '_diffrn_measurement.diffrn_id'. Either '_diffrn_measurement.device' or '_diffrn_measurement.id' may be used to link to other categories. If the experimental setup admits multiple devices, then '_diffrn_measurement.id' is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.id' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_id' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement.id' _item_type.code code save_ save__diffrn_measurement.method _item_description.description ; Method used to measure intensities. ; _item.name '_diffrn_measurement.method' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_method' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'profile data from theta/2theta (\q/2\q) scans' save_ save__diffrn_measurement.number_of_axes _item_description.description ; The value of '_diffrn_measurement.number_of_axes' gives the number of axes of the positioner for the goniometer or other sample orientation or positioning device identified by '_diffrn_measurement.id'. The description of the axes should be provided by entries in DIFFRN_MEASUREMENT_AXIS. ; _item.name '_diffrn_measurement.number_of_axes' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_measurement.specimen_support _item_description.description ; The physical device used to support the crystal during data collection. ; _item.name '_diffrn_measurement.specimen_support' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_specimen_support' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'glass capillary' 'quartz capillary' 'fiber' 'metal loop' save_ ########################### # DIFFRN_MEASUREMENT_AXIS # ########################### save_DIFFRN_MEASUREMENT_AXIS _category.description ; Data items in the DIFFRN_MEASUREMENT_AXIS category associate axes with goniometers. ; _category.id diffrn_measurement_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_measurement_axis.axis_id _item_description.description ; This data item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_diffrn_measurement_axis.axis_id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.measurement_device _item_description.description ; This data item is a pointer to '_diffrn_measurement.device' in the DIFFRN_MEASUREMENT category. ; _item.name '_diffrn_measurement_axis.measurement_device' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit _item_type.code text save_ save__diffrn_measurement_axis.measurement_id _item_description.description ; This data item is a pointer to '_diffrn_measurement.id' in the DIFFRN_MEASUREMENT category. This item was previously named '_diffrn_measurement_axis.id' which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_measurement_axis.measurement_id' _item.category_id diffrn_measurement_axis _item_aliases.alias_name '_diffrn_measurement_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0.00 _item.mandatory_code implicit _item_type.code code save_ #################### # DIFFRN_RADIATION # #################### save_DIFFRN_RADIATION _category.description ; Data items in the DIFFRN_RADIATION category describe the radiation used in measuring diffraction intensities, its collimation and monochromatisation before the sample. Post-sample treatment of the beam is described by data items in the DIFFRN_DETECTOR category. ; _category.id diffrn_radiation _category.mandatory_code no _category_key.name '_diffrn_radiation.diffrn_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_radiation.diffrn_id 'set1' _diffrn_radiation.collimation '0.3 mm double pinhole' _diffrn_radiation.monochromator 'graphite' _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.wavelength_id 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [(1991). Acta Cryst. C47, 2276-2277]. ; ; _diffrn_radiation.wavelength_id 1 _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.monochromator 'graphite' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_radiation.collimation _item_description.description ; The collimation or focusing applied to the radiation. ; _item.name '_diffrn_radiation.collimation' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_collimation' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '0.3 mm double-pinhole' '0.5 mm' 'focusing mirrors' save_ save__diffrn_radiation.diffrn_id _item_description.description ; This data item is a pointer to '_diffrn.id' in the DIFFRN category. ; _item.name '_diffrn_radiation.diffrn_id' _item.mandatory_code yes save_ save__diffrn_radiation.div_x_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory X axis (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the esd of the directions of photons in the X-Z plane around the mean source beam direction. Note that some synchrotrons specify this value in milliradians, in which case a conversion would be needed. To go from a value in milliradians to a value in degrees, multiply by 0.180 and divide by \p. ; _item.name '_diffrn_radiation.div_x_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.div_y_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory Y axis (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the esd of the directions of photons in the Y-Z plane around the mean source beam direction. Note that some synchrotrons specify this value in milliradians, in which case a conversion would be needed. To go from a value in milliradians to a value in degrees, multiply by 0.180 and divide by \p. ; _item.name '_diffrn_radiation.div_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.div_x_y_source _item_description.description ; Beam crossfire correlation degrees^2^ between the crossfire laboratory X-axis component and the crossfire laboratory Y-axis component (see AXIS category). This is a characteristic of the xray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the mean of the products of the deviations of the direction of each photons in X-Z plane times the deviations of the direction of the same photon in the Y-Z plane around the mean source beam direction. This will be zero for uncorrelated crossfire. Note that some synchrotrons specify this value in milliradians^2^, in which case a conversion would be needed. To go from a value in milliradians^2^ to a value in degrees^2^, multiply by 0.180^2^ and divide by \p^2^. ; _item.name '_diffrn_radiation.div_x_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees_squared _item_default.value 0.0 save_ save__diffrn_radiation.filter_edge _item_description.description ; Absorption edge in \%Angstroms of the radiation filter used. ; _item.name '_diffrn_radiation.filter_edge' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_filter_edge' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__diffrn_radiation.inhomogeneity _item_description.description ; Half-width in millimetres of the incident beam in the direction perpendicular to the diffraction plane. ; _item.name '_diffrn_radiation.inhomogeneity' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_inhomogeneity' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code millimetres save_ save__diffrn_radiation.monochromator _item_description.description ; The method used to obtain monochromatic radiation. If a monochromator crystal is used the material and the indices of the Bragg reflection are specified. ; _item.name '_diffrn_radiation.monochromator' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_monochromator' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Zr filter' 'Ge 220' 'none' 'equatorial mounted graphite' save_ save__diffrn_radiation.polarisn_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the perpendicular component of the polarisation and the diffraction plane. See _diffrn_radiation_polarisn_ratio. ; _item.name '_diffrn_radiation.polarisn_norm' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_norm' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.polarisn_ratio _item_description.description ; Polarisation ratio of the diffraction beam incident on the crystal. It is the ratio of the perpendicularly polarised to the parallel polarised component of the radiation. The perpendicular component forms an angle of '_diffrn_radiation.polarisn_norm' to the normal to the diffraction plane of the sample (i.e. the plane containing the incident and reflected beams). ; _item.name '_diffrn_radiation.polarisn_ratio' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_ratio' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__diffrn_radiation.polarizn_source_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the normal to the polarization plane and the laboratory Y axis as defined in the AXIS category. Note that this is the angle of polarization of the source photons, either directly from a synchrotron beamline or from a monchromater. This differs from the value of '_diffrn_radiation.polarisn_norm' in that '_diffrn_radiation.polarisn_norm' refers to polarization relative to the diffraction plane rather than to the laboratory axis system. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane should be taken as the X-Z plane, and the angle as 0. See '_diffrn_radiation.polarizn_source_ratio'. ; _item.name '_diffrn_radiation.polarizn_source_norm' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.polarizn_source_ratio _item_description.description ; (Ip-In)/(Ip+In), where Ip is the intensity (amplitude squared) of the electric vector in the plane of polarization and In is the intensity (amplitude squared) of the electric vector in plane of the normal to the plane of polarization. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane is be taken as the X-Z plane, and the normal is parallel to the Y-axis. Thus, if we had complete polarization in the plane of polarization, the value of '_diffrn_radiation.polarizn_source_ratio' would be 1, and an unpolarized beam would have a value of 0. If the X-axis has been chosen to lie in the plane of polarization, this definition will agree with the definition of "MONOCHROMATOR" in the Denzo glossary, and values of near 1 should be expected for a bending magnet source. However, if the X-axis were, for some reason to be, say, perpendicular to the polarization plane (not a common choice), then the Denzo value would be the negative of '_diffrn_radiation.polarizn_source_ratio'. See http://www.hkl-xray.com for information on Denzo, and Z. Otwinowski and W. Minor, "Processing of X-ray Diffraction Data Collected in Oscillation Mode", Methods in Enzymology, Volume 276: Macromolecular Crystallography, part A, p.307-326, 1997,C.W. Carter, Jr. & R. M. Sweet, Eds., Academic Press. This differs both in the choice of ratio and choice of orientation from '_diffrn_radiation.polarisn_ratio', which, unlike '_diffrn_radiation.polarizn_source_ratio', is unbounded. ; _item.name '_diffrn_radiation.polarizn_source_ratio' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 -1.0 -1.0 -1.0 _item_type.code float save_ save__diffrn_radiation.probe _item_description.description ; Name of the type of radiation used. It is strongly encouraged that this field be specified so that the probe radiation can be simply determined. ; _item.name '_diffrn_radiation.probe' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_probe' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value 'x-ray' 'neutron' 'electron' 'gamma' save_ save__diffrn_radiation.type _item_description.description ; The nature of the radiation. This is typically a description of the X-ray wavelength in Siegbahn notation. ; _item.name '_diffrn_radiation.type' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'CuK\a' 'Cu K\a~1~' 'Cu K-L~2,3~' 'white-beam' save_ save__diffrn_radiation.xray_symbol _item_description.description ; The IUPAC symbol for the X-ray wavelength for probe radiation. ; _item.name '_diffrn_radiation.xray_symbol' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_xray_symbol' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value _item_enumeration.detail 'K-L~3~' 'K\a~1~ in older Siegbahn notation' 'K-L~2~' 'K\a~2~ in older Siegbahn notation' 'K-M~3~' 'K\b~1~ in older Siegbahn notation' 'K-L~2,3~' 'use where K-L~3~ and K-L~2~ are not resolved' save_ save__diffrn_radiation.wavelength_id _item_description.description ; This data item is a pointer to '_diffrn_radiation_wavelength.id' in the DIFFRN_RADIATION_WAVELENGTH category. ; _item.name '_diffrn_radiation.wavelength_id' _item.category_id diffrn_radiation _item.mandatory_code yes _item_type.code code save_ ################ # DIFFRN_REFLN # ################ save_DIFFRN_REFLN _category.description ; This category redefinition has been added to extend the key of the standard DIFFRN_REFLN category. ; _category.id diffrn_refln _category.mandatory_code no _category_key.name '_diffrn_refln.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_refln.frame_id _item_description.description ; This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_refln.frame_id' _item.category_id diffrn_refln _item.mandatory_code yes _item_type.code code save_ ############### # DIFFRN_SCAN # ############### save_DIFFRN_SCAN _category.description ; Data items in the DIFFRN_SCAN category describe the parameters of one or more scans, relating axis positions to frames. ; _category.id diffrn_scan _category.mandatory_code no _category_key.name '_diffrn_scan.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - derived from a suggestion by R. M. Sweet. The vector of each axis is not given here, because it is provided in the AXIS category. By making '_diffrn_scan_axis.scan_id' and '_diffrn_scan_axis.axis_id' keys of the DIFFRN_SCAN_AXIS category, an arbitrary number of scanning and fixed axes can be specified for a scan. We have specified three rotation axes and one translation axis at non-zero values, with one axis stepping. There is no reason why more axes could not have been specified to step. We have specified range information, but note that it is redundant from the number of frames and the increment, so we could drop the data item '_diffrn_scan_axis.angle_range'. We have specified both the sweep data and the data for a single frame. Note that the information on how the axes are stepped is given twice, once in terms of the overall averages in the value of '_diffrn_scan.integration_time' and the values for DIFFRN_SCAN_AXIS, and precisely for the given frame in the value for '_diffrn_scan_frame.integration_time' and the values for DIFFRN_SCAN_FRAME_AXIS. If dose-related adjustements are made to scan times and non-linear stepping is done, these values may differ. Therefore, in interpreting the data for a particular frame it is important to use the frame-specific data. ; ; _diffrn_scan.id 1 _diffrn_scan.date_start '2001-11-18T03:26:42' _diffrn_scan.date_end '2001-11-18T03:36:45' _diffrn_scan.integration_time 3.0 _diffrn_scan.frame_id_start mad_L2_000 _diffrn_scan.frame_id_end mad_L2_200 _diffrn_scan.frames 201 loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment 1 omega 200.0 20.0 0.1 . . . 1 kappa -40.0 0.0 0.0 . . . 1 phi 127.5 0.0 0.0 . . . 1 tranz . . . 2.3 0.0 0.0 _diffrn_scan_frame.scan_id 1 _diffrn_scan_frame.date '2001-11-18T03:27:33' _diffrn_scan_frame.integration_time 3.0 _diffrn_scan_frame.frame_id mad_L2_018 _diffrn_scan_frame.frame_number 18 loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.angle_increment _diffrn_scan_frame_axis.displacement _diffrn_scan_frame_axis.displacement_increment mad_L2_018 omega 201.8 0.1 . . mad_L2_018 kappa -40.0 0.0 . . mad_L2_018 phi 127.5 0.0 . . mad_L2_018 tranz . . 2.3 0.0 ; ; Example 2 - a more extensive example, R. M. Sweet, P. Ellis, H. Bernstein. We place a detector 240 mm along the Z axis from the goniometer. This presents us with a choice -- either we define the axes of the detector at the origin, and then put a Z setting of -240 in for the actual use, or we define the axes with the necessary Z-offset. In this case we use the setting, and leave the offset as zero. We call this axis DETECTOR_Z. The axis for positioning the detector in the Y-direction depends on the detector Z-axis. We call this axis, DETECTOR_Y. The axis for positioning the detector in the X-direction depends on the detector Y-axis (and therefore on the detector Z-axis). We call this axis DETECTOR_X. This detector may be rotated around the Y-axis. This rotation axis depends on the three translation axes. We call it DETECTOR_PITCH. We define a coordinate system on the face of the detector in terms of 2300 0.150 mm pixels in each direction. The ELEMENT_X axis is used to index the first array index of the data array and the ELEMENT_Y axis is used to index the second array index. Because the pixels are 0.150mm x 0.150mm, the centre of the first pixel is at (0.075, 0.075) in this coordinate system. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 172.43 -172.43 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 2300 1 increasing ELEMENT_X ARRAY1 2 2300 2 increasing ELEMENT_Y # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.075 0.150 ELEMENT_Y ELEMENT_Y 0.075 0.150 # category ARRAY_ELEMENT_SIZE loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 ARRAY1 2 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; ; Example 3 - Example 2 revised for a spiral scan, R. M. Sweet, P. Ellis, H. Bernstein. We place a detector 240 mm along the Z axis from the goniometer, as in Example 2, above, but in this example, the image plate is scanned in a spiral pattern outside edge in. The axis for positioning the detector in the Y-direction depends on the detector Z-axis. We call this axis, DETECTOR_Y. The axis for positioning the detector in the X-direction depends on the detector Y-axis (and therefore on the detector Z-axis). We call this axis DETECTOR_X. This detector may be rotated around the Y-axis. This rotation axis depends on the three translation axes. We call it DETECTOR_PITCH. We define a coordinate system on the face of the detector in terms of a coupled rotation axis and radial scan axis to form a spiral scan. Let us call rotation axis ELEMENT_ROT, and the radial axis ELEMENT_RAD. We assume 150 um radial pitch and 75 um 'constant velocity' angular pitch. We index first on the rotation axis and make the radial axis dependent on it. The two axes are coupled to form an axis set ELEMENT_SPIRAL. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_ROT translation detector DETECTOR_PITCH 0 0 1 0 0 0 ELEMENT_RAD translation detector ELEMENT_ROT 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.angle _array_structure_list_axis.displacement _array_structure_list_axis.angular_pitch _array_structure_list_axis.radial_pitch ELEMENT_SPIRAL ELEMENT_ROT 0 . 0.075 . ELEMENT_SPIRAL ELEMENT_RAD . 172.5 . -0.150 # category ARRAY_ELEMENT_SIZE # the actual pixels are 0.075 by 0.150 mm # We give the coarser dimension here. loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_scan.id _item_description.description ; The value of '_diffrn_scan.id' uniquely identifies each scan. The identifier is used to tie together all the information about the scan. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_scan.id' diffrn_scan yes '_diffrn_scan_axis.scan_id' diffrn_scan_axis yes '_diffrn_scan_frame.scan_id' diffrn_scan_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_scan_axis.scan_id' '_diffrn_scan.id' '_diffrn_scan_frame.scan_id' '_diffrn_scan.id' save_ save__diffrn_scan.date_end _item_description.description ; The date and time of the end of the scan. Note that this may be an estimate generated during the scan, before the precise time of the end of the scan is known. ; _item.name '_diffrn_scan.date_end' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.date_start _item_description.description ; The date and time of the start of the scan. ; _item.name '_diffrn_scan.date_start' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.integration_time _item_description.description ; Approximate average time in seconds to integrate each step of the scan. The precise time for integration of each particular step must be provided in '_diffrn_scan_frame.integration_time', even if all steps have the same integration time. ; _item.name '_diffrn_scan.integration_time' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan.frame_id_start _item_description.description ; The value of this data item is the identifier of the first frame in the scan. This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_start' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frame_id_end _item_description.description ; The value of this data item is the identifier of the last frame in the scan. This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_end' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frames _item_description.description ; The value of this data item is the number of frames in the scan. ; _item.name '_diffrn_scan.frames' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 1 1 1 save_ #################### # DIFFRN_SCAN_AXIS # #################### save_DIFFRN_SCAN_AXIS _category.description ; Data items in the DIFFRN_SCAN_AXIS category describe the settings of axes for particular scans. Unspecified axes are assumed to be at their zero points. ; _category.id diffrn_scan_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_axis.scan_id' '_diffrn_scan_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_axis.scan_id _item_description.description ; The value of this data item is the identifier of the scan for which axis settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan.id'. This item is a pointer to '_diffrn_scan.id' in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_axis.scan_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the scan for which settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan.id'. This item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_diffrn_scan_axis.axis_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.angle_start _item_description.description ; The starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_range _item_description.description ; The range from the starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_increment _item_description.description ; The increment for each step for the specified axis in degrees. In general, this will agree with '_diffrn_scan_frame_axis.angle_increment'. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.angle_increment' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.angle_increment' (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_rstrt_incr _item_description.description ; The increment after each step for the specified axis in degrees. In general, this will agree with '_diffrn_scan_frame_axis.angle_rstrt_incr'. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' and '_diffrn_scan_frame_axis.angle_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame, and should equal '_diffrn_scan_frame_axis.angle' for that next frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.angle_rstrt_incr' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.angle_rstrt_incr' (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.displacement_start _item_description.description ; The starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_range _item_description.description ; The range from the starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_increment _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with '_diffrn_scan_frame_axis.displacement_increment'. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.displacement_increment' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.displacement_increment' (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_rstrt_incr _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with '_diffrn_scan_frame_axis.displacement_rstrt_incr'. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' and '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame, and should equal '_diffrn_scan_frame_axis.displacement' for that next frame. If the individual frame values vary, then the value of '_diffrn_scan_axis.displacement_rstrt_incr' will be representative of the ensemble of values of '_diffrn_scan_frame_axis.displacement_rstrt_incr' (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ ##################### # DIFFRN_SCAN_FRAME # ##################### save_DIFFRN_SCAN_FRAME _category.description ; Data items in the DIFFRN_SCAN_FRAME category describe the relationship of particular frames to scans. ; _category.id diffrn_scan_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame.scan_id' '_diffrn_scan_frame.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame.date _item_description.description ; The date and time of the start of the frame being scanned. ; _item.name '_diffrn_scan_frame.date' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan_frame.frame_id _item_description.description ; The value of this data item is the identifier of the frame being examined. This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame.frame_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame.frame_number _item_description.description ; The value of this data item is the number of the frame within the scan, starting with 1. It is not necessarily the same as the value of '_diffrn_scan_frame.frame_id', but may be. ; _item.name '_diffrn_scan_frame.frame_number' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 0 0 0 save_ save__diffrn_scan_frame.integration_time _item_description.description ; The time in seconds to integrate this step of the scan. This should be the precise time of integration of each particular frame. The value of this data item should be given explicitly for each frame and not inferred from the value of '_diffrn_scan.integration_time'. ; _item.name '_diffrn_scan_frame.integration_time' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame.scan_id _item_description.description ; The value of '_diffrn_scan_frame.scan_id' identifies the scan containing this frame. This item is a pointer to '_diffrn_scan.id' in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_frame.scan_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ ########################## # DIFFRN_SCAN_FRAME_AXIS # ########################## save_DIFFRN_SCAN_FRAME_AXIS _category.description ; Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the settings of axes for particular frames. Unspecified axes are assumed to be at their zero points. If, for any given frame, non-zero values apply for any of the data items in this category, those values should be given explicitly in this category and not simply inferred from values in DIFFRN_SCAN_AXIS. ; _category.id diffrn_scan_frame_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame_axis.frame_id' '_diffrn_scan_frame_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the frame for which settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan_frame.frame_id'. This item is a pointer to '_axis.id' in the AXIS category. ; _item.name '_diffrn_scan_frame_axis.axis_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_axis.angle _item_description.description ; The setting of the specified axis in degrees for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.angle' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_increment _item_description.description ; The increment for this frame for angular setting of the specified axis in degrees. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.angle_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_rstrt_incr _item_description.description ; The increment after this frame for angular setting of the specified axis in degrees. The sum of the values of '_diffrn_scan_frame_axis.angle' and '_diffrn_scan_frame_axis.angle_increment' and '_diffrn_scan_frame_axis.angle_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame, and should equal '_diffrn_scan_frame_axis.angle' for that next frame. ; _item.name '_diffrn_scan_frame_axis.angle_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.displacement' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_increment _item_description.description ; The increment for this frame for displacement setting of the specified axis in millimetres. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.displacement_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_rstrt_incr _item_description.description ; The increment for this frame for displacement setting of the specified axis in millimetres. The sum of the values of '_diffrn_scan_frame_axis.displacement' and '_diffrn_scan_frame_axis.displacement_increment' and '_diffrn_scan_frame_axis.displacement_rstrt_incr' is the angular setting of the axis at the start of the integration time for the next frame, and should equal '_diffrn_scan_frame_axis.displacement' for that next frame. ; _item.name '_diffrn_scan_frame_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.frame_id _item_description.description ; The value of this data item is the identifier of the frame for which axis settings are being specified. Multiple axes may be specified for the same value of '_diffrn_scan_frame.frame_id'. This item is a pointer to '_diffrn_data_frame.id' in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame_axis.frame_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ ######################## DEPRECATED DATA ITEMS ######################## save__diffrn_detector_axis.id _item_description.description ; This data item is a pointer to '_diffrn_detector.id' in the DIFFRN_DETECTOR category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_detector_axis.id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.id _item_description.description ; This data item is a pointer to '_diffrn_measurement.id' in the DIFFRN_MEASUREMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_measurement_axis.id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ ######################### DEPRECATED CATEGORY ######################### ##################### # DIFFRN_FRAME_DATA # ##################### save_DIFFRN_FRAME_DATA _category.description ; Data items in the DIFFRN_FRAME_DATA category record the details about each frame of data. The items in this category are now in the DIFFRN_DATA_FRAME category. The items in the DIFFRN_FRAME_DATA category are now deprecated. The items from this category are provided as aliases in the 1.0.0 dictionary, but should not be used for new work. The items from the old category are provided in this dictionary for completeness, but should not be used or cited. To avoid confusion, the example has been removed, and the redundant parent child-links to other categories removed. ; _category.id diffrn_frame_data _category.mandatory_code no loop_ _category_key.name '_diffrn_frame_data.id' '_diffrn_frame_data.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; THE DIFFRN_FRAME_DATA category is deprecated and should not be used. ; ; # EXAMPLE REMOVED # ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_frame_data.array_id _item_description.description ; This item is a pointer to '_array_structure.id' in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.array_id' _item.category_id diffrn_frame_data _item.mandatory_code yes _item_type.code code save_ save__diffrn_frame_data.binary_id _item_description.description ; This item is a pointer to '_array_data.binary_id' in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.binary_id' _item.category_id diffrn_frame_data _item.mandatory_code implicit _item_type.code int save_ save__diffrn_frame_data.detector_element_id _item_description.description ; This item is a pointer to '_diffrn_detector_element.id' in the DIFFRN_DETECTOR_ELEMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.detector_element_id' _item.category_id diffrn_frame_data _item.mandatory_code yes _item_type.code code save_ save__diffrn_frame_data.id _item_description.description ; The value of '_diffrn_frame_data.id' must uniquely identify each complete frame of data. DEPRECATED -- DO NOT USE ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_frame_data.id' diffrn_frame_data yes _item_type.code code save_ ################ END DEPRECATED SECTION ########### #################### ## ITEM_TYPE_LIST ## #################### # # # The regular expressions defined here are not compliant # with the POSIX 1003.2 standard as they include the # '\n' and '\t' special characters. These regular expressions # have been tested using version 0.12 of Richard Stallman's # GNU regular expression library in POSIX mode. # In order to allow presentation of a regular expression # in a text field concatenate any line ending in a backslash # with the following line, after discarding the backslash. # # A formal definition of the '\n' and '\t' special characters # is most properly done in the DDL, but for completeness, please # note that '\n' is the line termination character ('newline') # and '\t' is the horizontal tab character. There is a formal # ambiguity in the use of '\n' for line termination, in that # the intention is that the equivalent machine/OS-dependent line # termination character sequence should be accepted as a match, e.g. # # '\r' (control-M) under MacOS # '\n' (control-J) under Unix # '\r\n' (control-M control-J) under DOS and MS Windows # loop_ _item_type_list.code _item_type_list.primitive_code _item_type_list.construct _item_type_list.detail code char '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words ... ; ucode uchar '[_,.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words (case insensitive) ; line char '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types / multi-word items ... ; uline uchar '[][ \t_(),.;:"&<>/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types / multi-word items (case insensitive) ; text char '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; text item types / multi-line text ... ; binary char ;\n--CIF-BINARY-FORMAT-SECTION--\n\ [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\ \n--CIF-BINARY-FORMAT-SECTION---- ; ; binary items are presented as MIME-like ascii-encoded sections in an imgCIF. In a CBF, raw octet streams are used to convey the same information. ; int numb '-?[0-9]+' ; int item types are the subset of numbers that are the negative or positive integers. ; float numb '-?(([0-9]+)|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?' ; float item types are the subset of numbers that are the floating numbers. ; any char '.*' ; A catch all for items that may take any form... ; yyyy-mm-dd char ;\ [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9][0-9]\ (T[0-2][0-9]:[0-5][0-9]:[0-5][0-9](.[0-9]+)([+-][0-5][0-9]:[0-5][0-9])) ; ; Standard format for CIF date and time strings (see http://www.iucr.org/iucr-top/cif/spec/datetime.html), consisting of a yyyy-mm-dd date optionally followed by the character "T" followed by a 24-hour clock time, optionally followed by a signed time-zone offset. The IUCr standard has been extended to allow for an optional decimal fraction on the seconds of time. Time is local time if no time-zone offset is given. ; ##################### ## ITEM_UNITS_LIST ## ##################### loop_ _item_units_list.code _item_units_list.detail # 'metres' 'metres' 'centimetres' 'centimetres (metres * 10^( -2)^)' 'millimetres' 'millimetres (metres * 10^( -3)^)' 'nanometres' 'nanometres (metres * 10^( -9)^)' 'angstroms' '\%Angstroms (metres * 10^(-10)^)' 'picometres' 'picometres (metres * 10^(-12)^)' 'femtometres' 'femtometres (metres * 10^(-15)^)' # 'reciprocal_metres' 'reciprocal metres (metres^(-1)^)' 'reciprocal_centimetres' 'reciprocal centimetres ((metres * 10^( -2)^)^(-1)^)' 'reciprocal_millimetres' 'reciprocal millimetres ((metres * 10^( -3)^)^(-1)^)' 'reciprocal_nanometres' 'reciprocal nanometres ((metres * 10^( -9)^)^(-1)^)' 'reciprocal_angstroms' 'reciprocal \%Angstroms ((metres * 10^(-10)^)^(-1)^)' 'reciprocal_picometres' 'reciprocal picometres ((metres * 10^(-12)^)^(-1)^)' # 'nanometres_squared' 'nanometres squared (metres * 10^( -9)^)^2^' 'angstroms_squared' '\%Angstroms squared (metres * 10^(-10)^)^2^' '8pi2_angstroms_squared' '8\p^2^ * \%Angstroms squared (metres * 10^(-10)^)^2^' 'picometres_squared' 'picometres squared (metres * 10^(-12)^)^2^' # 'nanometres_cubed' 'nanometres cubed (metres * 10^( -9)^)^3^' 'angstroms_cubed' '\%Angstroms cubed (metres * 10^(-10)^)^3^' 'picometres_cubed' 'picometres cubed (metres * 10^(-12)^)^3^' # 'kilopascals' 'kilopascals' 'gigapascals' 'gigapascals' # 'hours' 'hours' 'minutes' 'minutes' 'seconds' 'seconds' 'microseconds' 'microseconds' # 'degrees' 'degrees (of arc)' 'degrees_squared' 'degrees (of arc) squared' # 'degrees_per_minute' 'degrees (of arc) per minute' # 'celsius' 'degrees (of temperature) Celsius' 'kelvins' 'degrees (of temperature) Kelvin' # 'counts' 'counts' 'counts_per_photon' 'counts per photon' # 'electrons' 'electrons' # 'electrons_squared' 'electrons squared' # 'electrons_per_nanometres_cubed' ; electrons per nanometres cubed (electrons/(metres * 10^( -9)^)^(-3)^) ; 'electrons_per_angstroms_cubed' ; electrons per \%Angstroms cubed (electrons/(metres * 10^(-10)^)^(-3)^) ; 'electrons_per_picometres_cubed' ; electrons per picometres cubed (electrons/(metres * 10^(-12)^)^(-3)^) ; 'kilowatts' 'kilowatts' 'milliamperes' 'milliamperes' 'kilovolts' 'kilovolts' # 'arbitrary' ; arbitrary system of units. ; # loop_ _item_units_conversion.from_code _item_units_conversion.to_code _item_units_conversion.operator _item_units_conversion.factor ### 'metres' 'centimetres' '*' 1.0E+02 'metres' 'millimetres' '*' 1.0E+03 'metres' 'nanometres' '*' 1.0E+09 'metres' 'angstroms' '*' 1.0E+10 'metres' 'picometres' '*' 1.0E+12 'metres' 'femtometres' '*' 1.0E+15 # 'centimetres' 'metres' '*' 1.0E-02 'centimetres' 'millimetres' '*' 1.0E+01 'centimetres' 'nanometres' '*' 1.0E+07 'centimetres' 'angstroms' '*' 1.0E+08 'centimetres' 'picometres' '*' 1.0E+10 'centimetres' 'femtometres' '*' 1.0E+13 # 'millimetres' 'metres' '*' 1.0E-03 'millimetres' 'centimetres' '*' 1.0E-01 'millimetres' 'nanometres' '*' 1.0E+06 'millimetres' 'angstroms' '*' 1.0E+07 'millimetres' 'picometres' '*' 1.0E+09 'millimetres' 'femtometres' '*' 1.0E+12 # 'nanometres' 'metres' '*' 1.0E-09 'nanometres' 'centimetres' '*' 1.0E-07 'nanometres' 'millimetres' '*' 1.0E-06 'nanometres' 'angstroms' '*' 1.0E+01 'nanometres' 'picometres' '*' 1.0E+03 'nanometres' 'femtometres' '*' 1.0E+06 # 'angstroms' 'metres' '*' 1.0E-10 'angstroms' 'centimetres' '*' 1.0E-08 'angstroms' 'millimetres' '*' 1.0E-07 'angstroms' 'nanometres' '*' 1.0E-01 'angstroms' 'picometres' '*' 1.0E+02 'angstroms' 'femtometres' '*' 1.0E+05 # 'picometres' 'metres' '*' 1.0E-12 'picometres' 'centimetres' '*' 1.0E-10 'picometres' 'millimetres' '*' 1.0E-09 'picometres' 'nanometres' '*' 1.0E-03 'picometres' 'angstroms' '*' 1.0E-02 'picometres' 'femtometres' '*' 1.0E+03 # 'femtometres' 'metres' '*' 1.0E-15 'femtometres' 'centimetres' '*' 1.0E-13 'femtometres' 'millimetres' '*' 1.0E-12 'femtometres' 'nanometres' '*' 1.0E-06 'femtometres' 'angstroms' '*' 1.0E-05 'femtometres' 'picometres' '*' 1.0E-03 ### 'reciprocal_centimetres' 'reciprocal_metres' '*' 1.0E+02 'reciprocal_centimetres' 'reciprocal_millimetres' '*' 1.0E-01 'reciprocal_centimetres' 'reciprocal_nanometres' '*' 1.0E-07 'reciprocal_centimetres' 'reciprocal_angstroms' '*' 1.0E-08 'reciprocal_centimetres' 'reciprocal_picometres' '*' 1.0E-10 # 'reciprocal_millimetres' 'reciprocal_metres' '*' 1.0E+03 'reciprocal_millimetres' 'reciprocal_centimetres' '*' 1.0E+01 'reciprocal_millimetres' 'reciprocal_nanometres' '*' 1.0E-06 'reciprocal_millimetres' 'reciprocal_angstroms' '*' 1.0E-07 'reciprocal_millimetres' 'reciprocal_picometres' '*' 1.0E-09 # 'reciprocal_nanometres' 'reciprocal_metres' '*' 1.0E+09 'reciprocal_nanometres' 'reciprocal_centimetres' '*' 1.0E+07 'reciprocal_nanometres' 'reciprocal_millimetres' '*' 1.0E+06 'reciprocal_nanometres' 'reciprocal_angstroms' '*' 1.0E-01 'reciprocal_nanometres' 'reciprocal_picometres' '*' 1.0E-03 # 'reciprocal_angstroms' 'reciprocal_metres' '*' 1.0E+10 'reciprocal_angstroms' 'reciprocal_centimetres' '*' 1.0E+08 'reciprocal_angstroms' 'reciprocal_millimetres' '*' 1.0E+07 'reciprocal_angstroms' 'reciprocal_nanometres' '*' 1.0E+01 'reciprocal_angstroms' 'reciprocal_picometres' '*' 1.0E-02 # 'reciprocal_picometres' 'reciprocal_metres' '*' 1.0E+12 'reciprocal_picometres' 'reciprocal_centimetres' '*' 1.0E+10 'reciprocal_picometres' 'reciprocal_millimetres' '*' 1.0E+09 'reciprocal_picometres' 'reciprocal_nanometres' '*' 1.0E+03 'reciprocal_picometres' 'reciprocal_angstroms' '*' 1.0E+01 ### 'nanometres_squared' 'angstroms_squared' '*' 1.0E+02 'nanometres_squared' 'picometres_squared' '*' 1.0E+06 # 'angstroms_squared' 'nanometres_squared' '*' 1.0E-02 'angstroms_squared' 'picometres_squared' '*' 1.0E+04 'angstroms_squared' '8pi2_angstroms_squared' '*' 78.9568 # 'picometres_squared' 'nanometres_squared' '*' 1.0E-06 'picometres_squared' 'angstroms_squared' '*' 1.0E-04 ### 'nanometres_cubed' 'angstroms_cubed' '*' 1.0E+03 'nanometres_cubed' 'picometres_cubed' '*' 1.0E+09 # 'angstroms_cubed' 'nanometres_cubed' '*' 1.0E-03 'angstroms_cubed' 'picometres_cubed' '*' 1.0E+06 # 'picometres_cubed' 'nanometres_cubed' '*' 1.0E-09 'picometres_cubed' 'angstroms_cubed' '*' 1.0E-06 ### 'kilopascals' 'gigapascals' '*' 1.0E-06 'gigapascals' 'kilopascals' '*' 1.0E+06 ### 'hours' 'minutes' '*' 6.0E+01 'hours' 'seconds' '*' 3.6E+03 'hours' 'microseconds' '*' 3.6E+09 # 'minutes' 'hours' '/' 6.0E+01 'minutes' 'seconds' '*' 6.0E+01 'minutes' 'microseconds' '*' 6.0E+07 # 'seconds' 'hours' '/' 3.6E+03 'seconds' 'minutes' '/' 6.0E+01 'seconds' 'microseconds' '*' 1.0E+06 # 'microseconds' 'hours' '/' 3.6E+09 'microseconds' 'minutes' '/' 6.0E+07 'microseconds' 'seconds' '/' 1.0E+06 ### 'celsius' 'kelvins' '-' 273.0 'kelvins' 'celsius' '+' 273.0 ### 'electrons_per_nanometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E+03 'electrons_per_nanometres_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+09 # 'electrons_per_angstroms_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-03 'electrons_per_angstroms_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+06 # 'electrons_per_picometres_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-09 'electrons_per_picometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E-06 ### ######################## ## DICTIONARY_HISTORY ## ######################## loop_ _dictionary_history.version _dictionary_history.update _dictionary_history.revision 1.3.2 2005-06-22 ; Changes as per Nicola Ashcroft. + Fix '_item_units.code code' to be '_item_type.code code' in '_array_structure_list_axis.axis_id' and in '_array_structure_list_axis.axis_set_id' Also fix typos in exponents and long lines in units list (HJB) ; 1.3.1 2003-08-13 ; Changes as per Frances C. Bernstein. + Identify initials. + Adopt British spelling for centre in text. + Set \p and \%Angstrom and powers. + Clean up commas and unclear wordings. + Clean up tenses in history. Changes as per Gotzon Madariaga. + Fix the ARRAY_DATA example to align '_array_data.binary_id' and X-Binary-Id. + Add a range to '_array_intensities.gain_esd'. + In the example of DIFFRN_DETECTOR_ELEMENT, '_diffrn_detector_element.id' and '_diffrn_detector_element.detector_id' interchanged. + Fix typos for direction, detector and axes. + Clarify description of polarisation. + Clarify axes in '_diffrn_detector_element.center[1]' '_diffrn_detector_element.center[2]'. + Add local item types for items that are pointers. (HJB) ; 1.3.0 2003-07-24 ; Changes as per Brian McMahon. + Consistently quote tags embedded in text. + Clean up introductory comments. + Adjust line lengths to fit in 80 character window. + Fix several descriptions in AXIS category which referred to '_axis.type' instead of the current item. + Fix erroneous use of deprecated item '_diffrn_detector_axis.id' in examples for DIFFRN_SCAN_AXIS. + Add deprecated items '_diffrn_detector_axis.id' and '_diffrn_measurement_axis.id'. (HJB) ; 1.2.4 2003-07-14 ; Changes as per I. David Brown. + Enhance descriptions in DIFFRN_SCAN_AXIS to make them less dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS. + Provide a copy of the deprecated DIFFRN_FRAME_DATA category for completeness. (HJB) ; 1.2.3 2003-07-03 ; Cleanup to conform to ITVG. + Correct sign error in ..._cubed units. + Correct '_diffrn_radiation.polarisn_norm' range. (HJB) ; 1.2.2 2003-03-10 ; Correction of typos in various DIFFRN_SCAN_AXIS descriptions. (HJB) ; 1.2.1 2003-02-22 ; Correction of ATOM_ for ARRAY_ typos in various descriptions. (HJB) ; 1.2 2003-02-07 ; Corrections to encodings (remove extraneous hyphens) remove extraneous underscore in '_array_structure.encoding_type' enumeration. Correct typos in items units list. (HJB) ; 1.1.3 2001-04-19 ; Another typo corrections by Wilfred Li, and cleanup by HJB. ; 1.1.2 2001-03-06 ; Several typo corrections by Wilfred Li. ; 1.1.1 2001-02-16 ; Several typo corrections by JW. ; 1.1 2001-02-06 ; Draft resulting from discussions on header for use at NSLS. (HJB) + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME. + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'. + Add '_diffrn_measurement_axis.measurement_device' and change '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'. + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source', '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm', '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end', '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr', '_diffrn_scan_axis.displacement_rstrt_incr', '_diffrn_scan_frame_axis.angle_increment', '_diffrn_scan_frame_axis.angle_rstrt_incr', '_diffrn_scan_frame_axis.displacement', '_diffrn_scan_frame_axis.displacement_increment',and '_diffrn_scan_frame_axis.displacement_rstrt_incr'. + Add '_diffrn_measurement.device' to category key. + Update yyyy-mm-dd to allow optional time with fractional seconds for time stamps. + Fix typos caught by RS. + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to allow for coupled axes, as in spiral scans. + Add examples for fairly complete headers thanks to R. Sweet and P. Ellis. ; 1.0 2000-12-21 ; Release version - few typos and tidying up. (BM & HJB) + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end of dictionary. + Alphabetize dictionary. ; 0.7.1 2000-09-29 ; Cleanup fixes. (JW) + Correct spelling of diffrn_measurement_axis in '_axis.id' + Correct ordering of uses of '_item.mandatory_code' and '_item_default.value'. ; 0.7.0 2000-09-09 ; Respond to comments by I. David Brown. (HJB) + Add further comments on '\n' and '\t'. + Update ITEM_UNITS_LIST by taking section from mmCIF dictionary and adding metres. Change 'meter' to 'metre' throughout. + Add missing enumerations to '_array_structure.compression_type' and make 'none' the default. + Remove parent-child relationship between '_array_structure_list.index' and '_array_structure_list.precedence'. + Improve alphabetization. + Fix '_array_intensities_gain.esd' related function. + Improve comments in AXIS. + Fix DIFFRN_FRAME_DATA example. + Remove erroneous DIFFRN_MEASUREMENT example. + Add '_diffrn_measurement_axis.id' to the category key. ; 0.6.0 1999-01-14 ; Remove redundant information for ENC_NONE data. (HJB) + After the D5 remove binary section identifier, size and compression type. + Add Control-L to header. ; 0.5.1 1999-01-03 ; Cleanup of typos and syntax errors. (HJB) + Cleanup example details for DIFFRN_SCAN category. + Add missing quote marks for '_diffrn_scan.id' definition. ; 0.5 1999-01-01 ; Modifications for axis definitions and reduction of binary header. (HJB) + Restore '_diffrn_detector.diffrn_id' to DIFFRN_DETECTOR KEY. + Add AXIS category. + Bring in complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories from cif_mm.dic for clarity. + Change '_array_structure.encoding_type' from type code to uline and added X-Binary-Element-Type to MIME header. + Add detector beam centre '_diffrn_detector_element.center[1]' and '_diffrn_detector_element.center[2]'. + Correct item name of '_diffrn_refln.frame_id'. + Replace reference to '_array_intensities.undefined' by '_array_intensities.undefined_value'. + Replace references to '_array_intensity.scaling' with '_array_intensities.scaling'. + Add DIFFRN_SCAN... categories. ; 0.4 1998-08-11 ; Modifications to the 0.3 imgCIF draft. (HJB) + Reflow comment lines over 80 characters and corrected typos. + Update examples and descriptions of MIME encoded data. + Change name to cbfext98.dic. ; 0.3 1998-07-04 ; Modifications for imgCIF. (HJB) + Add binary type, which is a text field containing a variant on MIME encoded data. + Change type of '_array_data.data' to binary and specify internal structure of raw binary data. + Add '_array_data.binary_id', and make '_diffrn_frame_data.binary_id' and '_array_intensities.binary_id' into pointers to this item. ; 0.2 1997-12-02 ; Modifications to the CBF draft. (JW) + Add category hierarchy for describing frame data developed from discussions at the BNL imgCIF Workshop Oct 1997. The following changes are made in implementing the workshop draft. Category DIFFRN_ARRAY_DATA is renamed to DIFFRN_FRAME_DATA. Category DIFFRN_FRAME_TYPE is renamed to DIFFRN_DETECTOR_ELEMENT. The parent item for '_diffrn_frame_data.array_id' is changed from '_array_structure_list.array_id' to '_array_structure.id'. Item '_diffrn_detector.array_id' is deleted. + Add data item '_diffrn_frame_data.binary_id' to identify data groups within a binary section. The formal identification of the binary section is still fuzzy. ; 0.1 1997-01-24 ; First draft of this dictionary in DDL 2.1 compliant format by John Westbrook (JW). This version is adapted from the Crystallographic Binary File (CBF) Format Draft Proposal provided by Andy Hammersley (AH). Modifications to the CBF draft. (JW) + In this version the array description has been cast in the categories ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. These categories have been generalized to describe array data of arbitrary dimension. + Array data in this description are contained in the category ARRAY_DATA. This departs from the CBF notion of data existing in some special comment. In this description, data is handled as an ordinary data item encapsulated in a character data type. Although data this manner deviates from CIF conventions, it does not violate any DDL 2.1 rules. DDL 2.1 regular expressions can be used to define the binary representation which will permit some level of data validation. In this version, the placeholder type code "any" has been used. This translates to a regular expression which will match any pattern. It should be noted that DDL 2.1 already supports array data objects although these have not been used in the current mmCIF dictionary. It may be possible to use the DDL 2.1 ITEM_STRUCTURE and ITEM_STRUCTURE_LIST categories to provide the information that is carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. By moving the array structure to the DDL level it would be possible to define an array type as well as a regular expression defining the data format. + Multiple array sections can be properly handled within a single datablock. ; #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof ./CBFlib-0.9.2.2/doc/Iarray_element_size.array_id.html0000644000076500007650000000517311603702115021022 0ustar yayayaya (IUCr) CIF Definition save__array_element_size.array_id

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _array_element_size.array_id

    Name:
    '_array_element_size.array_id'

    Definition:

           This item is a pointer to _array_structure.id in the
                  ARRAY_STRUCTURE category.
    
    

    Type: code

    Mandatory item: implicit

    Category: array_element_size

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/cif_img_1.5.4_28Jul07.dic0000644000076500007650000074743111603702115016321 0ustar yayayaya############################################################################## # # # Image CIF Dictionary (imgCIF) # # and Crystallographic Binary File Dictionary (CBF) # # Extending the Macromolecular CIF Dictionary (mmCIF) # # # # Version 1.5.4 # # of 2007-07-28 # # ################################################################### # # # *** WARNING *** THIS IS A DRAFT FOR DISCUSSSION *** WARNING *** # # # # SUBJECT TO CHANGE WITHOUT NOTICE # # # # SEND COMMENTS TO imgcif-l@iucr.org CITING THE VERSION # # # ################################################################### # # This draft edited by H. J. Bernstein # # # # by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook # # # # This dictionary was adapted from format discussed at the imgCIF Workshop, # # held at BNL Oct 1997 and the Crystallographic Binary File Format Draft # # Proposal by Andrew Hammersley. The first DDL 2.1 Version was created by # # John Westbrook. This version was drafted by Herbert J. Bernstein and # # incorporates comments by I. David Brown, John Westbrook, Brian McMahon, # # Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li, Gotzon Madariaga, # # Frances C. Bernstein, Chris Nielsen, Nicola Ashcroft and others. # ############################################################################## data_cif_img.dic _dictionary.title cif_img.dic _dictionary.version 1.5.4 _dictionary.datablock_id cif_img.dic ############################################################################## # CONTENTS # # CATEGORY_GROUP_LIST # SUB_CATEGORY # # category ARRAY_DATA # # _array_data.array_id # _array_data.binary_id # _array_data.data # _array_data.header_contents # _array_data.header_convention # # category ARRAY_ELEMENT_SIZE # # _array_element_size.array_id # _array_element_size.index # _array_element_size.size # # category ARRAY_INTENSITIES # # _array_intensities.array_id # _array_intensities.binary_id # _array_intensities.gain # _array_intensities.gain_esd # _array_intensities.linearity # _array_intensities.offset # _array_intensities.scaling # _array_intensities.overload # _array_intensities.undefined_value # _array_intensities.pixel_fast_bin_size # _array_intensities.pixel_slow_bin_size # _array_intensities.pixel_binning_method # # category ARRAY_STRUCTURE # # _array_structure.byte_order # _array_structure.compression_type # _array_structure.compression_type_flag # _array_structure.encoding_type # _array_structure.id # # category ARRAY_STRUCTURE_LIST # # _array_structure_list.axis_set_id # _array_structure_list.array_id # _array_structure_list.dimension # _array_structure_list.direction # _array_structure_list.index # _array_structure_list.precedence # # category ARRAY_STRUCTURE_LIST_AXIS # # _array_structure_list_axis.axis_id # _array_structure_list_axis.axis_set_id # _array_structure_list_axis.angle # _array_structure_list_axis.angle_increment # _array_structure_list_axis.displacement # _array_structure_list_axis.fract_displacement # _array_structure_list_axis.displacement_increment # _array_structure_list_axis.fract_displacement_increment # _array_structure_list_axis.angular_pitch # _array_structure_list_axis.radial_pitch # _array_structure_list_axis.reference_angle # _array_structure_list_axis.reference_displacement # # category AXIS # # _axis.depends_on # _axis.equipment # _axis.id # _axis.offset[1] # _axis.offset[2] # _axis.offset[3] # _axis.type # _axis.system # _axis.vector[1] # _axis.vector[2] # _axis.vector[3] # # category DIFFRN_DATA_FRAME # # _diffrn_data_frame.array_id # _diffrn_data_frame.binary_id # _diffrn_data_frame.center_fast # _diffrn_data_frame.center_slow # _diffrn_data_frame.center_units # _diffrn_data_frame.detector_element_id # _diffrn_data_frame.id # _diffrn_data_frame.details # # category DIFFRN_DETECTOR # # _diffrn_detector.details # _diffrn_detector.detector # _diffrn_detector.diffrn_id # _diffrn_detector.dtime # _diffrn_detector.id # _diffrn_detector.number_of_axes # _diffrn_detector.type # # category DIFFRN_DETECTOR_AXIS # # _diffrn_detector_axis.axis_id # _diffrn_detector_axis.detector_id # # category DIFFRN_DETECTOR_ELEMENT # # _diffrn_detector_element.id # _diffrn_detector_element.detector_id # _diffrn_detector_element.reference_center_fast # _diffrn_detector_element.reference_center_slow # _diffrn_detector_element.reference_center_units # # category DIFFRN_MEASUREMENT # # _diffrn_measurement.diffrn_id # _diffrn_measurement.details # _diffrn_measurement.device # _diffrn_measurement.device_details # _diffrn_measurement.device_type # _diffrn_measurement.id # _diffrn_measurement.method # _diffrn_measurement.number_of_axes # _diffrn_measurement.sample_detector_distance # _diffrn_measurement.sample_detector_voffset # _diffrn_measurement.specimen_support # # category DIFFRN_MEASUREMENT_AXIS # # _diffrn_measurement_axis.axis_id # _diffrn_measurement_axis.measurement_device # _diffrn_measurement_axis.measurement_id # # category DIFFRN_RADIATION # # _diffrn_radiation.collimation # _diffrn_radiation.diffrn_id # _diffrn_radiation.div_x_source # _diffrn_radiation.div_y_source # _diffrn_radiation.div_x_y_source # _diffrn_radiation.filter_edge' # _diffrn_radiation.inhomogeneity # _diffrn_radiation.monochromator # _diffrn_radiation.polarisn_norm # _diffrn_radiation.polarisn_ratio # _diffrn_radiation.polarizn_source_norm # _diffrn_radiation.polarizn_source_ratio # _diffrn_radiation.probe # _diffrn_radiation.type # _diffrn_radiation.xray_symbol # _diffrn_radiation.wavelength_id # # category DIFFRN_REFLN # # _diffrn_refln.frame_id # # category DIFFRN_SCAN # # _diffrn_scan.id # _diffrn_scan.date_end # _diffrn_scan.date_start # _diffrn_scan.integration_time # _diffrn_scan.frame_id_start # _diffrn_scan.frame_id_end # _diffrn_scan.frames # # category DIFFRN_SCAN_AXIS # # _diffrn_scan_axis.axis_id # _diffrn_scan_axis.angle_start # _diffrn_scan_axis.angle_range # _diffrn_scan_axis.angle_increment # _diffrn_scan_axis.angle_rstrt_incr # _diffrn_scan_axis.displacement_start # _diffrn_scan_axis.displacement_range # _diffrn_scan_axis.displacement_increment # _diffrn_scan_axis.displacement_rstrt_incr # _diffrn_scan_axis.reference_angle # _diffrn_scan_axis.reference_displacement # _diffrn_scan_axis.scan_id # # category DIFFRN_SCAN_FRAME # # _diffrn_scan_frame.date # _diffrn_scan_frame.frame_id # _diffrn_scan_frame.frame_number # _diffrn_scan_frame.integration_time # _diffrn_scan_frame.scan_id # # category DIFFRN_SCAN_FRAME_AXIS # # _diffrn_scan_frame_axis.axis_id # _diffrn_scan_frame_axis.angle # _diffrn_scan_frame_axis.angle_increment # _diffrn_scan_frame_axis.angle_rstrt_incr # _diffrn_scan_frame_axis.displacement # _diffrn_scan_frame_axis.displacement_increment # _diffrn_scan_frame_axis.displacement_rstrt_incr # _diffrn_scan_frame_axis.reference_angle # _diffrn_scan_frame_axis.reference_displacement # _diffrn_scan_frame_axis.frame_id # # categor MAP # # _map.details # _map.diffrn_id # _map.entry_id # _map.id # # categor MAP_SEGMENT # # _map_segment.array_id # _map_segment.binary_id # _map_segment.mask_array_id # _map_segment.mask_binary_id # _map_segment.id # _map_segment.map_id # _map_segment.details # # ***DEPRECATED*** data items # # _diffrn_detector_axis.id # _diffrn_detector_element.center[1] # _diffrn_detector_element.center[2] # _diffrn_measurement_axis.id # # ***DEPRECATED*** category DIFFRN_FRAME_DATA # # _diffrn_frame_data.array_id # _diffrn_frame_data.binary_id # _diffrn_frame_data.detector_element_id # _diffrn_frame_data.id # _diffrn_frame_data.details # # # ITEM_TYPE_LIST # ITEM_UNITS_LIST # DICTIONARY_HISTORY # ############################################################################## ######################### ## CATEGORY_GROUP_LIST ## ######################### loop_ _category_group_list.id _category_group_list.parent_id _category_group_list.description 'inclusive_group' . ; Categories that belong to the dictionary extension. ; 'array_data_group' 'inclusive_group' ; Categories that describe array data. ; 'axis_group' 'inclusive_group' ; Categories that describe axes. ; 'diffrn_group' 'inclusive_group' ; Categories that describe details of the diffraction experiment. ; ################## ## SUB_CATEGORY ## ################## loop_ _sub_category.id _sub_category.description 'matrix' ; The collection of elements of a matrix. ; 'vector' ; The collection of elements of a vector. ; ############## # ARRAY_DATA # ############## save_ARRAY_DATA _category.description ; Data items in the ARRAY_DATA category are the containers for the array data items described in the category ARRAY_STRUCTURE. It is recognized that the data in this category needs to be used in two distinct ways. During a data collection the lack of ancillary data and timing constraints in processing data may dictate the need to make a 'miniCBF' nothing more than an essential minimum of information to record the results of the data collection. In that case it is proper to use the ARRAY_DATA category as a container for just a single image and a compacted, beam-line dependent list of data collection parameter values. In such a case, only the tags '_array_data.header_convention', '_array_data.header_contents' and '_array_data.data' need be populated. For full processing and archiving, most of the tags in this dictionary will need to be populated. ; _category.id array_data _category.mandatory_code no loop_ _category_key.name '_array_data.array_id' '_array_data.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows two binary data blocks. The first one was compressed by the CBF_CANONICAL compression algorithm and is presented as hexadecimal data. The first character 'H' on the data lines means hexadecimal. It could have been 'O' for octal or 'D' for decimal. The second character on the line shows the number of bytes in each word (in this case '4'), which then requires eight hexadecimal digits per word. The third character gives the order of octets within a word, in this case '<' for the ordering 4321 (i.e. 'big-endian'). Alternatively, the character '>' could have been used for the ordering 1234 (i.e. 'little-endian'). The block has a 'message digest' to check the integrity of the data. The second block is similar, but uses CBF_PACKED compression and BASE64 encoding. Note that the size and the digest are different. ; ; loop_ _array_data.array_id _array_data.binary_id _array_data.data image_1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF_CANONICAL" Content-Transfer-Encoding: X-BASE16 X-Binary-Size: 3927126 X-Binary-ID: 1 Content-MD5: u2sTJEovAHkmkDjPi+gWsg== # Hexadecimal encoding, byte 0, byte order ...21 # H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ... .... --CIF-BINARY-FORMAT-SECTION---- ; image_2 2 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF-PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3745758 X-Binary-ID: 2 Content-MD5: 1zsJjWPfol2GYl2V+QSXrw== ELhQAAAAAAAA... ... --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - This example shows a single image in a miniCBF, provided by E. Eikenberry. The entire CBF consists of one data block containing one category and three tags. The CBFlib program convert_miniCBF and a suitable template file can be used to convert this miniCBF to a full imgCIF file. ; ; ###CBF: VERSION 1.5 # CBF file written by CBFlib v0.7.8 data_insulin_pilatus6m _array_data.header_convention SLS_1.0 _array_data.header_contents ; # Detector: PILATUS 6M SN: 60-0001 # 2007/Jun/17 15:12:36.928 # Pixel_size 172e-6 m x 172e-6 m # Silicon sensor, thickness 0.000320 m # Exposure_time 0.995000 s # Exposure_period 1.000000 s # Tau = 194.0e-09 s # Count_cutoff 1048575 counts # Threshold_setting 5000 eV # Wavelength 1.2398 A # Energy_range (0, 0) eV # Detector_distance 0.15500 m # Detector_Voffset -0.01003 m # Beam_xy (1231.00, 1277.00) pixels # Flux 22487563295 ph/s # Filter_transmission 0.0008 # Start_angle 13.0000 deg. # Angle_increment 1.0000 deg. # Detector_2theta 0.0000 deg. # Polarization 0.990 # Alpha 0.0000 deg. # Kappa 0.0000 deg. # Phi 0.0000 deg. # Chi 0.0000 deg. # Oscillation_axis X, CW # N_oscillations 1 ; _array_data.data ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_BYTE_OFFSET" Content-Transfer-Encoding: BINARY X-Binary-Size: 6247567 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" X-Binary-Element-Byte-Order: LITTLE_ENDIAN Content-MD5: 8wO6i2+899lf5iO8QPdgrw== X-Binary-Number-of-Elements: 6224001 X-Binary-Size-Fastest-Dimension: 2463 X-Binary-Size-Second-Dimension: 2527 X-Binary-Size-Padding: 4095 ... --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_data.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. If not given, it defaults to 1. ; _item.name '_array_data.array_id' _item.category_id array_data _item.mandatory_code implicit _item_type.code code save_ save__array_data.binary_id _item_description.description ; This item is an integer identifier which, along with _array_data.array_id, should uniquely identify the particular block of array data. If _array_data.binary_id is not explicitly given, it defaults to 1. The value of _array_data.binary_id distinguishes among multiple sets of data with the same array structure. If the MIME header of the data array specifies a value for X-Binary-ID, the value of _array_data.binary_id should be equal to the value given for X-Binary-ID. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_data.binary_id' array_data implicit '_diffrn_data_frame.binary_id' diffrn_data_frame implicit '_array_intensities.binary_id' array_intensities implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.binary_id' '_array_data.binary_id' '_array_intensities.binary_id' '_array_data.binary_id' _item_default.value 1 _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_data.data _item_description.description ; The value of _array_data.data contains the array data encapsulated in a STAR string. The representation used is a variant on the Multipurpose Internet Mail Extensions (MIME) specified in RFC 2045-2049 by N. Freed et al. The boundary delimiter used in writing an imgCIF or CBF is '\n--CIF-BINARY-FORMAT-SECTION--' (including the required initial '\n--'). The Content-Type may be any of the discrete types permitted in RFC 2045; 'application/octet-stream' is recommended for diffraction images in the ARRAY_DATA category. Note: When appropriate in other categories, e.g. for photographs of crystals, more precise types, such as 'image/jpeg', 'image/tiff', 'image/png', etc. should be used. If an octet stream was compressed, the compression should be specified by the parameter 'conversions="X-CBF_PACKED"' or the parameter 'conversions="X-CBF_CANONICAL"' or the parameter 'conversions="X-CBF_BYTE_OFFSET"' If the parameter 'conversions="X-CBF_PACKED"' is given it may be further modified with the parameters '"uncorrelated_sections"' or '"flat"' If the '"uncorrelated_sections"' parameter is given, each section will be compressed without using the prior section for averaging. If the '"flat"' parameter is given, each the image will be treated as one long row. The Content-Transfer-Encoding may be 'BASE64', 'Quoted-Printable', 'X-BASE8', 'X-BASE10', 'X-BASE16' or 'X-BASE32K', for an imgCIF or 'BINARY' for a CBF. The octal, decimal and hexadecimal transfer encodings are provided for convenience in debugging and are not recommended for archiving and data interchange. In a CIF, one of the parameters 'charset=us-ascii', 'charset=utf-8' or 'charset=utf-16' may be used on the Content-Transfer-Encoding to specify the character set used for the external presentation of the encoded data. If no charset parameter is given, the character set of the enclosing CIF is assumed. In any case, if a BOM flag is detected (FE FF for big-endian UTF-16, FF FE for little-endian UTF-16 or EF BB BF for UTF-8) is detected, the indicated charset will be assumed until the end of the encoded data or the detection of a different BOM. The charset of the Content-Transfer-Encoding is not the character set of the encoded data, only the character set of the presentation of the encoded data and should be respecified for each distinct STAR string. In an imgCIF file, the encoded binary data begins after the empty line terminating the header. In an imgCIF file, the encoded binary data ends with the terminating boundary delimiter '\n--CIF-BINARY-FORMAT-SECTION----' in the currently effective charset or with the '\n; ' that terminates the STAR string. In a CBF, the raw binary data begins after an empty line terminating the header and after the sequence: Octet Hex Decimal Purpose 0 0C 12 (ctrl-L) Page break 1 1A 26 (ctrl-Z) Stop listings in MS-DOS 2 04 04 (Ctrl-D) Stop listings in UNIX 3 D5 213 Binary section begins None of these octets are included in the calculation of the message size or in the calculation of the message digest. The X-Binary-Size header specifies the size of the equivalent binary data in octets. If compression was used, this size is the size after compression, including any book-keeping fields. An adjustment is made for the deprecated binary formats in which eight bytes of binary header are used for the compression type. In this case, the eight bytes used for the compression type are subtracted from the size, so that the same size will be reported if the compression type is supplied in the MIME header. Use of the MIME header is the recommended way to supply the compression type. In general, no portion of the binary header is included in the calculation of the size. The X-Binary-Element-Type header specifies the type of binary data in the octets, using the same descriptive phrases as in _array_structure.encoding_type. The default value is 'unsigned 32-bit integer'. An MD5 message digest may, optionally, be used. The 'RSA Data Security, Inc. MD5 Message-Digest Algorithm' should be used. No portion of the header is included in the calculation of the message digest. If the Transfer Encoding is 'X-BASE8', 'X-BASE10' or 'X-BASE16', the data are presented as octal, decimal or hexadecimal data organized into lines or words. Each word is created by composing octets of data in fixed groups of 2, 3, 4, 6 or 8 octets, either in the order ...4321 ('big- endian') or 1234... ('little-endian'). If there are fewer than the specified number of octets to fill the last word, then the missing octets are presented as '==' for each missing octet. Exactly two equal signs are used for each missing octet even for octal and decimal encoding. The format of lines is: rnd xxxxxx xxxxxx xxxxxx where r is 'H', 'O' or 'D' for hexadecimal, octal or decimal, n is the number of octets per word and d is '<' or '>' for the '...4321' and '1234...' octet orderings, respectively. The '==' padding for the last word should be on the appropriate side to correspond to the missing octets, e.g. H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000 or H3> FF0700 00==== For these hexadecimal, octal and decimal formats only, comments beginning with '#' are permitted to improve readability. BASE64 encoding follows MIME conventions. Octets are in groups of three: c1, c2, c3. The resulting 24 bits are broken into four six-bit quantities, starting with the high-order six bits (c1 >> 2) of the first octet, then the low-order two bits of the first octet followed by the high-order four bits of the second octet [(c1 & 3)<<4 | (c2>>4)], then the bottom four bits of the second octet followed by the high-order two bits of the last octet [(c2 & 15)<<2 | (c3>>6)], then the bottom six bits of the last octet (c3 & 63). Each of these four quantities is translated into an ASCII character using the mapping: 1 2 3 4 5 6 0123456789012345678901234567890123456789012345678901234567890123 | | | | | | | ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/ With short groups of octets padded on the right with one '=' if c3 is missing, and with '==' if both c2 and c3 are missing. X-BASE32K encoding is similar to BASE64 encoding, except that sets of 15 octets are encoded as sets of 8 16-bit unicode characters, by breaking the 120 bits into 8 15-bit quantities. 256 is added to each 15 bit quantity to bring it into a printable uncode range. When encoding, zero padding is used to fill out the last 15 bit quantity. If 8 or more bits of padding are used, a single equals sign (hexadecimal 003D) is appended. Embedded whitespace and newlines are introduced to produce lines of no more than 80 characters each. On decoding, all printable ascii characters and ascii whitespace characters are ignored except for any trailing equals signs. The number of trailing equals signs indicated the number of trailing octets to be trimmed from the end of the decoded data. (see Georgi Darakev, Vassil Litchev, Kostadin Z. Mitev, Herbert J. Bernstein, 'Efficient Support of Binary Data in the XML Implementation of the NeXus File Format',absract W0165, ACA Summer Meeting, Honolulu, HI, July 2006). QUOTED-PRINTABLE encoding also follows MIME conventions, copying octets without translation if their ASCII values are 32...38, 42, 48...57, 59, 60, 62, 64...126 and the octet is not a ';' in column 1. All other characters are translated to =nn, where nn is the hexadecimal encoding of the octet. All lines are 'wrapped' with a terminating '=' (i.e. the MIME conventions for an implicit line terminator are never used). The "X-Binary-Element-Byte-Order" can specify either '"BIG_ENDIAN"' or '"LITTLE_ENDIAN"' byte order of the imaage data. Only LITTLE_ENDIAN is recommended. Processors may treat BIG_ENDIAN as a warning of data that can only be processed by special software. The "X-Binary-Number-of-Elements" specifies the number of elements (not the number of octets) in the decompressed, decoded image. The optional "X-Binary-Size-Fastest-Dimension" specifies the number of elements (not the number of octets) in one row of the fastest changing dimension of the binary data array. This information must be in the MIME header for proper operation of some of the decompression algorithms. The optional "X-Binary-Size-Second-Dimension" specifies the number of elements (not the number of octets) in one column of the second-fastest changing dimension of the binary data array. This information must be in the MIME header for proper operation of some of the decompression algorithms. The optional "X-Binary-Size-Third-Dimension" specifies the number of sections for the third-fastest changing dimension of the binary data array. The optional "X-Binary-Size-Padding" specifies the size in octets of an optional padding after the binary array data and before the closing flags for a binary section. ; _item.name '_array_data.data' _item.category_id array_data _item.mandatory_code yes _item_type.code binary save_ save__array_data.header_contents _item_description.description ; This item is an text field for use in minimal CBF files to carry essential header information to be kept with image data in _array_data.data when the tags that normally carry the structured metadata for the image have not been populated. Normally this data item should not appear when the full set of tags have been populated and _diffrn_data_frame.details appears. ; _item.name '_array_data.header_contents' _item.category_id array_data _item.mandatory_code no _item_type.code text save_ save__array_data.header_convention _item_description.description ; This item is an identifier for the convention followed in constructing the contents of _array_data.header_contents The permitted values are of the of an image creator identifier followed by an underscore and a version string. To avoid confusion about conventions, all creator identifiers should be registered with the IUCr and the conventions for all identifiers and versions should be posted on the MEDSBIO.org web site. ; _item.name '_array_data.header_convention' _item.category_id array_data _item.mandatory_code no _item_type.code code save_ ###################### # ARRAY_ELEMENT_SIZE # ###################### save_ARRAY_ELEMENT_SIZE _category.description ; Data items in the ARRAY_ELEMENT_SIZE category record the physical size of array elements along each array dimension. ; _category.id array_element_size _category.mandatory_code no loop_ _category_key.name '_array_element_size.array_id' '_array_element_size.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A regular 2D array with a uniform element dimension of 1220 nanometres. ; ; loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size image_1 1 1.22e-6 image_1 2 1.22e-6 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_element_size.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_element_size.array_id' _item.category_id array_element_size _item.mandatory_code implicit _item_type.code code save_ save__array_element_size.index _item_description.description ; This item is a pointer to _array_structure_list.index in the ARRAY_STRUCTURE_LIST category. ; _item.name '_array_element_size.index' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.size _item_description.description ; The size in metres of an image element in this dimension. This supposes that the elements are arranged on a regular grid. ; _item.name '_array_element_size.size' _item.category_id array_element_size _item.mandatory_code yes _item_type.code float _item_units.code 'metres' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ ##################### # ARRAY_INTENSITIES # ##################### save_ARRAY_INTENSITIES _category.description ; Data items in the ARRAY_INTENSITIES category record the information required to recover the intensity data from the set of data values stored in the ARRAY_DATA category. The detector may have a complex relationship between the raw intensity values and the number of incident photons. In most cases, the number stored in the final array will have a simple linear relationship to the actual number of incident photons, given by _array_intensities.gain. If raw, uncorrected values are presented (e.g. for calibration experiments), the value of _array_intensities.linearity will be 'raw' and _array_intensities.gain will not be used. ; _category.id array_intensities _category.mandatory_code no loop_ _category_key.name '_array_intensities.array_id' '_array_intensities.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 ; ; loop_ _array_intensities.array_id _array_intensities.linearity _array_intensities.gain _array_intensities.overload _array_intensities.undefined_value _array_intensities.pixel_fast_bin_size _array_intensities.pixel_slow_bin_size _array_intensities.pixel_binning_method image_1 linear 1.2 655535 0 2 2 hardware ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_intensities.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_intensities.array_id' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code code save_ save__array_intensities.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_array_intensities.binary_id' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code int save_ save__array_intensities.gain _item_description.description ; Detector 'gain'. The factor by which linearized intensity count values should be divided to produce true photon counts. ; _item.name '_array_intensities.gain' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain_esd' 'associated_value' save_ save__array_intensities.gain_esd _item_description.description ; The estimated standard deviation in detector 'gain'. ; _item.name '_array_intensities.gain_esd' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain' 'associated_esd' save_ save__array_intensities.linearity _item_description.description ; The intensity linearity scaling method used to convert from the raw intensity to the stored element value: 'linear' is linear. 'offset' means that the value defined by _array_intensities.offset should be added to each element value. 'scaling' means that the value defined by _array_intensities.scaling should be multiplied with each element value. 'scaling_offset' is the combination of the two previous cases, with the scale factor applied before the offset value. 'sqrt_scaled' means that the square root of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and squaring the result. 'logarithmic_scaled' means that the logarithm base 10 of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and calculating 10 to the power of this number. 'raw' means that the data are a set of raw values straight from the detector. ; _item.name '_array_intensities.linearity' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'linear' . 'offset' ; The value defined by _array_intensities.offset should be added to each element value. ; 'scaling' ; The value defined by _array_intensities.scaling should be multiplied with each element value. ; 'scaling_offset' ; The combination of the scaling and offset with the scale factor applied before the offset value. ; 'sqrt_scaled' ; The square root of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and squaring the result. ; 'logarithmic_scaled' ; The logarithm base 10 of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and calculating 10 to the power of this number. ; 'raw' ; The array consists of raw values to which no corrections have been applied. While the handling of the data is similar to that given for 'linear' data with no offset, the meaning of the data differs in that the number of incident photons is not necessarily linearly related to the number of counts reported. This value is intended for use either in calibration experiments or to allow for handling more complex data-fitting algorithms than are allowed for by this data item. ; save_ save__array_intensities.offset _item_description.description ; Offset value to add to array element values in the manner described by the item _array_intensities.linearity. ; _item.name '_array_intensities.offset' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.overload _item_description.description ; The saturation intensity level for this data array. ; _item.name '_array_intensities.overload' _item.category_id array_intensities _item.mandatory_code no _item_type.code float _item_units.code 'counts' save_ save__array_intensities.pixel_fast_bin_size _item_description.description ; The value of _array_intensities.pixel_fast_bin_size specifies the number of pixels that compose one element in the direction of the most rapidly varying array dimension. Typical values are 1, 2, 4 or 8. When there is 1 pixel per array element in both directions, the value given for _array_intensities.pixel_binning_method normally should be 'none'. It is specified as a float to allow for binning algorithms that create array elements that are not integer multiples of the detector pixel size. ; _item.name '_array_intensities.pixel_fast_bin_size' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code float _item_default.value 1. loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'pixels_per_element' save_ save__array_intensities.pixel_slow_bin_size _item_description.description ; The value of _array_intensities.pixel_slow_bin_size specifies the number of pixels that compose one element in the direction of the second most rapidly varying array dimension. Typical values are 1, 2, 4 or 8. When there is 1 pixel per array element in both directions, the value given for _array_intensities.pixel_binning_method normally should be 'none'. It is specified as a float to allow for binning algorithms that create array elements that are not integer multiples of the detector pixel size. ; _item.name '_array_intensities.pixel_slow_bin_size' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code float _item_default.value 1. loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'pixels_per_element' save_ save__array_intensities.pixel_binning_method _item_description.description ; The value of _array_intensities.pixel_binning_method specifies the method used to derive array elements from multiple pixels. ; _item.name '_array_intensities.pixel_binning_method' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'hardware' ; The element intensities were derived from the raw data of one or more pixels by used of hardware in the detector, e.g. by use of shift registers in a CCD to combine pixels into super-pixels. ; 'software' ; The element intensities were derived from the raw data of more than one pixel by use of software. ; 'combined' ; The element intensities were derived from the raw data of more than one pixel by use of both hardware and software, as when hardware binning is used in one direction and software in the other. ; 'none' ; In the both directions, the data has not been binned. The number of pixels is equal to the number of elements. When the value of _array_intensities.pixel_binning_method is 'none' the values of _array_intensities.pixel_fast_bin_size and _array_intensities.pixel_slow_bin_size both must be 1. ; 'unspecified' ; The method used to derive element intensities is not specified. ; _item_default.value 'unspecified' save_ save__array_intensities.scaling _item_description.description ; Multiplicative scaling value to be applied to array data in the manner described by item _array_intensities.linearity. ; _item.name '_array_intensities.scaling' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.undefined_value _item_description.description ; A value to be substituted for undefined values in the data array. ; _item.name '_array_intensities.undefined_value' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ ################### # ARRAY_STRUCTURE # ################### save_ARRAY_STRUCTURE _category.description ; Data items in the ARRAY_STRUCTURE category record the organization and encoding of array data that may be stored in the ARRAY_DATA category. ; _category.id array_structure _category.mandatory_code no _category_key.name '_array_structure.id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order image_1 "unsigned 16-bit integer" none little_endian ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure.byte_order _item_description.description ; The order of bytes for integer values which require more than 1 byte. (IBM-PC's and compatibles and DEC VAXs use low-byte-first ordered integers, whereas Hewlett Packard 700 series, Sun-4 and Silicon Graphics use high-byte-first ordered integers. DEC Alphas can produce/use either depending on a compiler switch.) ; _item.name '_array_structure.byte_order' _item.category_id array_structure _item.mandatory_code yes _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail 'big_endian' ; The first byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; 'little_endian' ; The last byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; save_ save__array_structure.compression_type _item_description.description ; Type of data-compression method used to compress the array data. ; _item.name '_array_structure.compression_type' _item.category_id array_structure _item.mandatory_code no _item_type.code ucode _item_default.value 'none' loop_ _item_enumeration.value _item_enumeration.detail 'byte_offset' ; Using the 'byte_offset' compression scheme as per A. Hammersley and the CBFlib manual, section 3.3.3 ; 'canonical' ; Using the 'canonical' compression scheme (International Tables for Crystallography Volume G, Section 5.6.3.1) and CBFlib manual section 3.3.1 ; 'none' ; Data are stored in normal format as defined by _array_structure.encoding_type and _array_structure.byte_order. ; 'packed' ; Using the 'packed' compression scheme, a CCP4-style packing as per J. P. Abrahams pack_c.c and CBFlib manual, section 3.3.2. ; 'packed_v2' ; Using the 'packed' compression scheme, version 2, as per J. P. Abrahams pack_c.c and CBFlib manual, section 3.3.2. ; save_ save__array_structure.compression_type_flag _item_description.description ; Flags modifying the type of data-compression method used to compress the arraydata. ; _item.name '_array_structure.compression_type_flag' _item.category_id array_structure _item.mandatory_code no _item_type.code ucode loop_ _item_enumeration.value _item_enumeration.detail 'uncorrelated_sections' ; When applying packed or packed_v2 compression on an array with uncorrelated sections, do not average in points from the prior section. ; 'flat' ; When applying packed or packed_v2 compression on an array with treat the entire image as a single line set the maximum number of bits for an offset to 65 bits. The flag is included for compatibility with software prior to CBFlib_0.7.7, and should not be used for new data sets. ; save_ save__array_structure.encoding_type _item_description.description ; Data encoding of a single element of array data. The type 'unsigned 1-bit integer' is used for packed Booleans arrays for masks. Each element of the array corresponds to a single bit packed in unsigned 8-bit data. In several cases, the IEEE format is referenced. See IEEE Standard 754-1985 (IEEE, 1985). Ref: IEEE (1985). IEEE Standard for Binary Floating-Point Arithmetic. ANSI/IEEE Std 754-1985. New York: Institute of Electrical and Electronics Engineers. ; _item.name '_array_structure.encoding_type' _item.category_id array_structure _item.mandatory_code yes _item_type.code uline loop_ _item_enumeration.value 'unsigned 1-bit integer' 'unsigned 8-bit integer' 'signed 8-bit integer' 'unsigned 16-bit integer' 'signed 16-bit integer' 'unsigned 32-bit integer' 'signed 32-bit integer' 'signed 32-bit real IEEE' 'signed 64-bit real IEEE' 'signed 32-bit complex IEEE' save_ save__array_structure.id _item_description.description ; The value of _array_structure.id must uniquely identify each item of array data. This item has been made implicit and given a default value of 1 as a convenience in writing miniCBF files. Normally an explicit name with useful content should be used. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure.id' array_structure implicit '_array_data.array_id' array_data implicit '_array_structure_list.array_id' array_structure_list implicit '_array_intensities.array_id' array_intensities implicit '_diffrn_data_frame.array_id' diffrn_data_frame implicit _item_default.value 1 _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_data.array_id' '_array_structure.id' '_array_structure_list.array_id' '_array_structure.id' '_array_intensities.array_id' '_array_structure.id' '_diffrn_data_frame.array_id' '_array_structure.id' save_ ######################## # ARRAY_STRUCTURE_LIST # ######################## save_ARRAY_STRUCTURE_LIST _category.description ; Data items in the ARRAY_STRUCTURE_LIST category record the size and organization of each array dimension. The relationship to physical axes may be given. ; _category.id array_structure_list _category.mandatory_code no loop_ _category_key.name '_array_structure_list.array_id' '_array_structure_list.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - An image array of 1300 x 1200 elements. The raster order of the image is left to right (increasing) in the first dimension and bottom to top (decreasing) in the second dimension. ; ; loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id image_1 1 1300 1 increasing ELEMENT_X image_1 2 1200 2 decreasing ELEMENY_Y ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure_list.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_structure_list.array_id' _item.category_id array_structure_list _item.mandatory_code implicit _item_type.code code save_ save__array_structure_list.axis_set_id _item_description.description ; This is a descriptor for the physical axis or set of axes corresponding to an array index. This data item is related to the axes of the detector itself given in DIFFRN_DETECTOR_AXIS, but usually differs in that the axes in this category are the axes of the coordinate system of reported data points, while the axes in DIFFRN_DETECTOR_AXIS are the physical axes of the detector describing the 'poise' of the detector as an overall physical object. If there is only one axis in the set, the identifier of that axis should be used as the identifier of the set. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.axis_set_id' array_structure_list yes '_array_structure_list_axis.axis_set_id' array_structure_list_axis implicit _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_structure_list_axis.axis_set_id' '_array_structure_list.axis_set_id' save_ save__array_structure_list.dimension _item_description.description ; The number of elements stored in the array structure in this dimension. ; _item.name '_array_structure_list.dimension' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.direction _item_description.description ; Identifies the direction in which this array index changes. ; _item.name '_array_structure_list.direction' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'increasing' ; Indicates the index changes from 1 to the maximum dimension. ; 'decreasing' ; Indicates the index changes from the maximum dimension to 1. ; save_ save__array_structure_list.index _item_description.description ; Identifies the one-based index of the row or column in the array structure. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.index' array_structure_list yes '_array_structure_list.precedence' array_structure_list yes '_array_element_size.index' array_element_size yes _item_type.code int loop_ _item_linked.child_name _item_linked.parent_name '_array_element_size.index' '_array_structure_list.index' loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.precedence _item_description.description ; Identifies the rank order in which this array index changes with respect to other array indices. The precedence of 1 indicates the index which changes fastest. ; _item.name '_array_structure_list.precedence' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ ############################# # ARRAY_STRUCTURE_LIST_AXIS # ############################# save_ARRAY_STRUCTURE_LIST_AXIS _category.description ; Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe the physical settings of sets of axes for the centres of pixels that correspond to data points described in the ARRAY_STRUCTURE_LIST category. In the simplest cases, the physical increments of a single axis correspond to the increments of a single array index. More complex organizations, e.g. spiral scans, may require coupled motions along multiple axes. Note that a spiral scan uses two coupled axes: one for the angular direction and one for the radial direction. This differs from a cylindrical scan for which the two axes are not coupled into one set. ; _category.id array_structure_list_axis _category.mandatory_code no loop_ _category_key.name '_array_structure_list_axis.axis_set_id' '_array_structure_list_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' save_ save__array_structure_list_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes in the set of axes for which settings are being specified. Multiple axes may be specified for the same value of _array_structure_list_axis.axis_set_id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_array_structure_list_axis.axis_id' _item.category_id array_structure_list_axis _item.mandatory_code yes _item_type.code code save_ save__array_structure_list_axis.axis_set_id _item_description.description ; The value of this data item is the identifier of the set of axes for which axis settings are being specified. Multiple axes may be specified for the same value of _array_structure_list_axis.axis_set_id. This item is a pointer to _array_structure_list.axis_set_id in the ARRAY_STRUCTURE_LIST category. If this item is not specified, it defaults to the corresponding axis identifier. ; _item.name '_array_structure_list_axis.axis_set_id' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_type.code code save_ save__array_structure_list_axis.angle _item_description.description ; The setting of the specified axis in degrees for the first data point of the array index with the corresponding value of _array_structure_list.axis_set_id. If the index is specified as 'increasing', this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing', this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.angle' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.angle_increment _item_description.description ; The pixel-centre-to-pixel-centre increment in the angular setting of the specified axis in degrees. This is not meaningful in the case of 'constant velocity' spiral scans and should not be specified for this case. See _array_structure_list_axis.angular_pitch. ; _item.name '_array_structure_list_axis.angle_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for the first data point of the array index with the corresponding value of _array_structure_list.axis_set_id. If the index is specified as 'increasing', this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing', this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.displacement' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.fract_displacement _item_description.description ; The setting of the specified axis as a decimal fraction of the axis unit vector for the first data point of the array index with the corresponding value of _array_structure_list.axis_set_id. If the index is specified as 'increasing', this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing', this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.fract_displacement' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float save_ save__array_structure_list_axis.displacement_increment _item_description.description ; The pixel-centre-to-pixel-centre increment for the displacement setting of the specified axis in millimetres. ; _item.name '_array_structure_list_axis.displacement_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.fract_displacement_increment _item_description.description ; The pixel-centre-to-pixel-centre increment for the displacement setting of the specified axis as a decimal fraction of the axis unit vector. ; _item.name '_array_structure_list_axis.fract_displacement_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.angular_pitch _item_description.description ; The pixel-centre-to-pixel-centre distance for a one-step change in the setting of the specified axis in millimetres. This is meaningful only for 'constant velocity' spiral scans or for uncoupled angular scans at a constant radius (cylindrical scans) and should not be specified for cases in which the angle between pixels (rather than the distance between pixels) is uniform. See _array_structure_list_axis.angle_increment. ; _item.name '_array_structure_list_axis.angular_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.radial_pitch _item_description.description ; The radial distance from one 'cylinder' of pixels to the next in millimetres. If the scan is a 'constant velocity' scan with differing angular displacements between pixels, the value of this item may differ significantly from the value of _array_structure_list_axis.displacement_increment. ; _item.name '_array_structure_list_axis.radial_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.reference_angle _item_description.description ; The value of _array_structure_list_axis.reference_angle specifies the setting of the angle of this axis used for determining a reference beam center and a reference detector distance. It is normally expected to be identical to the value of _array_structure_list.angle. ; _item.name '_array_structure_list_axis.reference_angle' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.reference_displacement _item_description.description ; The value of _array_structure_list_axis.reference_displacement specifies the setting of the displacement of this axis used for determining a reference beam center and a reference detector distance. It is normally expected to be identical to the value of _array_structure_list.displacement. ; _item.name '_array_structure_list_axis.reference_displacement' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'millimetres' save_ ######## # AXIS # ######## save_AXIS _category.description ; Data items in the AXIS category record the information required to describe the various goniometer, detector, source and other axes needed to specify a data collection or the axes defining the coordinate system of an image. The location of each axis is specified by two vectors: the axis itself, given by a unit vector in the direction of the axis, and an offset to the base of the unit vector. The vectors defining an axis are referenced to an appropriate coordinate system. The axis vector, itself, is a dimensionless unit vector. Where meaningful, the offset vector is given in millimetres. In coordinate systems not measured in metres, the offset is not specified and is taken as zero. The available coordinate systems are: The imgCIF standard laboratory coordinate system The direct lattice (fractional atomic coordinates) The orthogonal Cartesian coordinate system (real space) The reciprocal lattice An abstract orthogonal Cartesian coordinate frame For consistency in this discussion, we call the three coordinate system axes X, Y and Z. This is appropriate for the imgCIF standard laboratory coordinate system, and last two Cartesian coordinate systems, but for the direct lattice, X corresponds to a, Y to b and Z to c, while for the reciprocal lattice, X corresponds to a*, Y to b* and Z to c*. For purposes of visualization, all the coordinate systems are taken as right-handed, i.e., using the convention that the extended thumb of a right hand could point along the first (X) axis, the straightened pointer finger could point along the second (Y) axis and the middle finger folded inward could point along the third (Z) axis. THE IMGCIF STANDARD LABORATORY COORDINATE SYSTEM The imgCIF standard laboratory coordinate system is a right-handed orthogonal coordinate similar to the MOSFLM coordinate system, but imgCIF puts Z along the X-ray beam, rather than putting X along the X-ray beam as in MOSFLM. The vectors for the imgCIF standard laboratory coordinate system form a right-handed Cartesian coordinate system with its origin in the sample or specimen. The origin of the axis system should, if possible, be defined in terms of mechanically stable axes to be be both in the sample and in the beam. If the sample goniometer or other sample positioner has two axes the intersection of which defines a unique point at which the sample should be mounted to be bathed by the beam, that will be the origin of the axis system. If no such point is defined, then the midpoint of the line of intersection between the sample and the center of the beam will define the origin. For this definition the sample positioning system will be set at its initial reference position for the experiment. | Y (to complete right-handed system) | | | | | |________________X / principal goniometer axis / / / / /Z (to source) Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from the sample or specimen along the principal axis of the goniometer or sample positioning system if the sample positioning system has an axis that intersects the origin and which form an angle of more than 22.5 degrees with the beam axis. Axis 2 (Y): The Y-axis completes an orthogonal right-handed system defined by the X-axis and the Z-axis (see below). Axis 3 (Z): The Z-axis is derived from the source axis which goes from the sample to the source. The Z-axis is the component of the source axis in the direction of the source orthogonal to the X-axis in the plane defined by the X-axis and the source axis. If the conditions for the X-axis can be met, the coordinate system will be based on the goniometer or other sample positioning system and the beam and not on the orientation of the detector, gravity etc. The vectors necessary to specify all other axes are given by sets of three components in the order (X, Y, Z). If the axis involved is a rotation axis, it is right-handed, i.e. as one views the object to be rotated from the origin (the tail) of the unit vector, the rotation is clockwise. If a translation axis is specified, the direction of the unit vector specifies the sense of positive translation. Note: This choice of coordinate system is similar to but significantly different from the choice in MOSFLM (Leslie & Powell, 2004). In MOSFLM, X is along the X-ray beam (the CBF/imgCIF Z axis) and Z is along the rotation axis. In some experimental techniques, there is no goniometer or the principal axis of the goniometer is at a small acute angle with respect to the source axis. In such cases, other reference axes are needed to define a useful coordinate system. The order of priority in defining directions in such cases is to use the detector, then gravity, then north. If the X-axis cannot be defined as above, then the direction (not the origin) of the X-axis should be parallel to the axis of the primary detector element corresponding to the most rapidly varying dimension of that detector element's data array, with its positive sense corresponding to increasing values of the index for that dimension. If the detector is such that such a direction cannot be defined (as with a point detector) or that direction forms an angle of less than 22.5 degrees with respect to the source axis, then the X-axis should be chosen so that if the Y-axis is chosen in the direction of gravity, and the Z-axis is chosen to be along the source axis, a right-handed orthogonal coordinate system is chosen. In the case of a vertical source axis, as a last resort, the X-axis should be chosen to point North. All rotations are given in degrees and all translations are given in mm. Axes may be dependent on one another. The X-axis is the only goniometer axis the direction of which is strictly connected to the hardware. All other axes are specified by the positions they would assume when the axes upon which they depend are at their zero points. When specifying detector axes, the axis is given to the beam centre. The location of the beam centre on the detector should be given in the DIFFRN_DETECTOR category in distortion-corrected millimetres from the (0,0) corner of the detector. It should be noted that many different origins arise in the definition of an experiment. In particular, as noted above, it is necessary to specify the location of the beam centre on the detector in terms of the origin of the detector, which is, of course, not coincident with the centre of the sample. The unit cell, reciprocal cell and crystallographic orthogonal Cartesian coordinate system are defined by the CELL and the matrices in the ATOM_SITES category. THE DIRECT LATTICE (FRACTIONAL COORDINATES) The direct lattice coordinate system is a system of fractional coordinates aligned to the crystal, rather than to the laboratory. This is a natural coordinate system for maps and atomic coordinates. It is the simplest coordinate system in which to apply symmetry. The axes are determined by the cell edges, and are not necessarily othogonal. This coordinate system is not uniquely defined and depends on the cell parameters in the CELL category and the settings chosen to index the crystal. Molecules in a crystal studied by X-ray diffracraction are organized into a repeating regular array of unit cells. Each unit cell is defined by three vectors, a, b and c. To quote from Drenth, "The choice of the unit cell is not unique and therefore, guidelines have been established for selecting the standard basis vectors and the origin. They are based on symmetry and metric considerations: "(1) The axial system should be right handed. (2) The basis vectors should coincide as much as possible with directions of highest symmetry." (3) The cell taken should be the smallest one that satisfies condition (2) (4) Of all the lattice vectors, none is shorter than a. (5) Of those not directed along a, none is shorter than b. (6) Of those not lying in the ab plane, none is shorter than c. (7) The three angles between the basis vectors a, b and c are either all acute (<90\%) or all obtuse (>=90\%)." These rules do not produce a unique result that is stable under the assumption of experimental errors, and the the resulting cell may not be primitive. In this coordinate system, the vector (.5, .5, .5) is in the middle of the given unit cell. Grid coordinates are an important variation on fractional coordinates used when working with maps. In imgCIF, the conversion from fractional to grid coordinates is implicit in the array indexing specified by _array_structure_list.dimension. Note that this implicit grid-coordinate scheme is 1-based, not zero-based, i.e. the origin of the cell for axes along the cell edges with no specified _array_structure_list_axis.displacement will have grid coordinates of (1,1,1), i.e. array indices of (1,1,1). THE ORTHOGONAL CARTESIAN COORDINATE SYSTEM (REAL SPACE) The orthogonal Cartesian coordinate system is a transformation of the direct lattice to the actual physical coordinates of atoms in space. It is similar to the laboratory coordinate system, but is anchored to and moves with the crystal, rather than being schored to the laboratory. The transformation from fractional to orthogonal cartesian coordinates is given by the _atom_sites.Cartn_transf_matrix[i][j] and _atom_sites.Cartn_transf_vector[i] tags. A common choice for the matrix of the transformation is given in the 1992 PDB format document | a b cos(\g) c cos(\b) | | 0 b sin(\g) c (cos(\a) - cos(\b)cos(\g))/sin(\g) | | 0 0 V/(a b sin(\g)) | This is a convenient coordinate system in which to do fitting of models to maps and in which to understand the chemistry of a molecule. THE RECIPROCAL LATTICE The reciprocal lattice coordinate system is used for diffraction intensitities. It is based on the reciprocal cell, the dual of the cell, in which reciprocal cell edges are derived from direct cell faces: a* = bc sin(\a)/V b* = ac sin(\b)/V c* = ab sin(\g)/V cos(\a*) = (cos(\b) cos(\g) - cos(\a))/(sin(\b) sin(\g)) cos(\b*) = (cos(\a) cos(\g) - cos(\b))/(sin(\a) sin(\g)) cos(\g*) = (cos(\a) cos(\b) - cos(\g))/(sin(\a) sin(\b)) V = abc SQRT(1 - cos(\a)^2^ - cos(\b)^2^ - cos(\g)^2^ + 2 cos(\a) cos(\b) cos(\g) ) In this form the dimensions of the reciprocal lattice are in reciprocal \%Angstroms (\%A^-1^). A dimensionless form can be obtained by multiplying by the wavelength. Reflections are commonly indexed against this coordinate system as (h, k, l) triples. References: Drenth, J., "Introduction to basic crystallography." chapter 2.1 in Rossmann, M. G. and Arnold, E. "Crystallography of biological macromolecules", Volume F of the IUCr's "International tables for crystallography", Kluwer, Dordrecht 2001, pp 44 -- 63 Leslie, A. G. W. and Powell, H. (2004). MOSFLM v6.11. MRC Laboratory of Molecular Biology, Hills Road, Cambridge, England. http://www.CCP4.ac.uk/dist/X-windows/Mosflm/. Stout, G. H. and Jensen, L. H., "X-ray structure determination", 2nd ed., Wiley, New York, 1989, 453 pp. __, "PROTEIN DATA BANK ATOMIC COORDINATE AND BIBLIOGRAPHIC ENTRY FORMAT DESCRIPTION," Brookhaven National Laboratory, February 1992. ; _category.id axis _category.mandatory_code no loop_ _category_key.name '_axis.id' '_axis.equipment' loop_ _category_group.id 'inclusive_group' 'axis_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows the axis specification of the axes of a kappa- geometry goniometer [see Stout, G. H. & Jensen, L. H. (1989). X-ray structure determination. A practical guide, 2nd ed. p. 134. New York: Wiley Interscience]. There are three axes specified, and no offsets. The outermost axis, omega, is pointed along the X axis. The next innermost axis, kappa, is at a 50 degree angle to the X axis, pointed away from the source. The innermost axis, phi, aligns with the X axis when omega and phi are at their zero points. If T-omega, T-kappa and T-phi are the transformation matrices derived from the axis settings, the complete transformation would be: X' = (T-omega) (T-kappa) (T-phi) X ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] omega rotation goniometer . 1 0 0 kappa rotation goniometer omega -.64279 0 -.76604 phi rotation goniometer kappa 1 0 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - This example shows the axis specification of the axes of a detector, source and gravity. The order has been changed as a reminder that the ordering of presentation of tokens is not significant. The centre of rotation of the detector has been taken to be 68 millimetres in the direction away from the source. ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] source . source . 0 0 1 . . . gravity . gravity . 0 -1 0 . . . tranz translation detector rotz 0 0 1 0 0 -68 twotheta rotation detector . 1 0 0 . . . roty rotation detector twotheta 0 1 0 0 0 -68 rotz rotation detector roty 0 0 1 0 0 -68 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 3 - This example show the axis specification of the axes for a map, using fractional coordinates. Each cell edge has been divided into a grid of 50 divisions in the ARRAY_STRUCTURE_LIST_AXIS category. The map is using only the first octant of the grid in the ARRAY_STRUCTURE_LIST category. The fastest changing axis is the gris along A, then along B, and the slowest is along C. The map sampling is being done in the middle of each grid division ; ; loop_ _axis.id _axis.system _axis.vector[1] _axis.vector[2] _axis.vector[3] CELL_A_AXIS fractional 1 0 0 CELL_B_AXIS fractional 0 1 0 CELL_C_AXIS fractional 0 0 1 loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_id MAP 1 25 1 increasing CELL_A_AXIS MAP 1 25 2 increasing CELL_B_AXIS MAP 1 25 3 increasing CELL_C_AXIS loop_ _array_structure_list_axis.axis_id _array_structure_list_axis.fract_displacement _array_structure_list_axis.fract_displacement_increment CELL_A_AXIS 0.01 0.02 CELL_B_AXIS 0.01 0.02 CELL_C_AXIS 0.01 0.02 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 4 - This example show the axis specification of the axes for a map, this time as orthogonal \%Angstroms, using the same coordinate system as for the atomic coordinates. The map is sampling every 1.5 \%Angstroms (1.5e-7 millimeters) in a map segment 37.5 \%Angstroms on a side. ; ; loop_ _axis.id _axis.system _axis.vector[1] _axis.vector[2] _axis.vector[3] X orthogonal 1 0 0 Y orthogonal 0 1 0 Z orthogonal 0 0 1 loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_id MAP 1 25 1 increasing X MAP 2 25 2 increasing Y MAP 3 25 3 increasing Z loop_ _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment X 7.5e-8 1.5e-7 Y 7.5e-8 1.5e-7 Z 7.5e-8 1.5e-7 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__axis.depends_on _item_description.description ; The value of _axis.depends_on specifies the next outermost axis upon which this axis depends. This item is a pointer to _axis.id in the same category. ; _item.name '_axis.depends_on' _item.category_id axis _item.mandatory_code no save_ save__axis.equipment _item_description.description ; The value of _axis.equipment specifies the type of equipment using the axis: 'goniometer', 'detector', 'gravity', 'source' or 'general'. ; _item.name '_axis.equipment' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail goniometer 'equipment used to orient or position samples' detector 'equipment used to detect reflections' general 'equipment used for general purposes' gravity 'axis specifying the downward direction' source 'axis specifying the direction sample to source' save_ save__axis.offset[1] _item_description.description ; The [1] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[2] _item_description.description ; The [2] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[3] _item_description.description ; The [3] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.id _item_description.description ; The value of _axis.id must uniquely identify each axis relevant to the experiment. Note that multiple pieces of equipment may share the same axis (e.g. a twotheta arm), so the category key for AXIS also includes the equipment. ; loop_ _item.name _item.category_id _item.mandatory_code '_axis.id' axis yes '_array_structure_list_axis.axis_id' array_structure_list_axis yes '_diffrn_detector_axis.axis_id' diffrn_detector_axis yes '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes '_diffrn_scan_axis.axis_id' diffrn_scan_axis yes '_diffrn_scan_frame_axis.axis_id' diffrn_scan_frame_axis yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_axis.depends_on' '_axis.id' '_array_structure_list_axis.axis_id' '_axis.id' '_diffrn_detector_axis.axis_id' '_axis.id' '_diffrn_measurement_axis.axis_id' '_axis.id' '_diffrn_scan_axis.axis_id' '_axis.id' '_diffrn_scan_frame_axis.axis_id' '_axis.id' save_ save__axis.system _item_description.description ; The value of _axis.system specifies the coordinate system used to define the axis: 'laboratory', 'direct', 'orthogonal', 'reciprocal' or 'abstract'. ; _item.name '_axis.system' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value laboratory loop_ _item_enumeration.value _item_enumeration.detail laboratory ; the axis is referenced to the imgCIF standard laboratory Cartesian coordinate system ; direct ; the axis is referenced to the direct lattice ; orthogonal ; the axis is referenced to the cell Cartesian orthogonal coordinates ; reciprocal ; the axis is referenced to the reciprocal lattice ; abstract ; the axis is referenced to abstract Cartesian cooridinate system ; save_ save__axis.type _item_description.description ; The value of _axis.type specifies the type of axis: 'rotation' or 'translation' (or 'general' when the type is not relevant, as for gravity). ; _item.name '_axis.type' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail rotation 'right-handed axis of rotation' translation 'translation in the direction of the axis' general 'axis for which the type is not relevant' save_ save__axis.vector[1] _item_description.description ; The [1] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[2] _item_description.description ; The [2] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[3] _item_description.description ; The [3] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ ##################### # DIFFRN_DATA_FRAME # ##################### save_DIFFRN_DATA_FRAME _category.description ; Data items in the DIFFRN_DATA_FRAME category record the details about each frame of data. The items in this category were previously in a DIFFRN_FRAME_DATA category, which is now deprecated. The items from the old category are provided as aliases but should not be used for new work. ; _category.id diffrn_data_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_data_frame.id' '_diffrn_data_frame.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A frame containing data from 4 frame elements. Each frame element has a common array configuration 'array_1' described in ARRAY_STRUCTURE and related categories. The data for each detector element are stored in four groups of binary data in the ARRAY_DATA category, linked by the array_id and binary_id. ; ; loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id frame_1 d1_ccd_1 array_1 1 frame_1 d1_ccd_2 array_1 2 frame_1 d1_ccd_3 array_1 3 frame_1 d1_ccd_4 array_1 4 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_data_frame.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_diffrn_data_frame.array_id' _item.category_id diffrn_data_frame _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_frame_data.array_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_diffrn_data_frame.binary_id' _item.category_id diffrn_data_frame _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_frame_data.binary_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code int save_ save__diffrn_data_frame.center_fast _item_description.description ; The value of _diffrn_data_frame.center_fast is the fast index axis beam center position relative to the detector element face in the units specified in the data item '_diffrn_data_frame.center_units' along the fast axis of the detector from the center of the first pixel to the point at which the Z-axis (which should be colinear with the beam) intersects the face of the detector, if in fact is does. At the time of the measurement the current setting of detector positioner given frame are used. It is important to note that for measurements in millimetres, the sense of the axis is used, rather than the sign of the pixel-to-pixel increments. ; _item.name '_diffrn_data_frame.center_fast' _item.category_id diffrn_data_frame _item.mandatory_code no _item_type.code float save_ save__diffrn_data_frame.center_slow _item_description.description ; The value of _diffrn_data_frame.center_slow is the slow index axis beam center position relative to the detector element face in the units specified in the data item '_diffrn_data_frame.center_units' along the slow axis of the detector from the center of the first pixel to the point at which the Z-axis (which should be colinear with the beam) intersects the face of the detector, if in fact is does. At the time of the measurement the current setting of detector positioner given frame are used. It is important to note that the sense of the axis is used, rather than the sign of the pixel-to-pixel increments. ; _item.name '_diffrn_data_frame.center_slow' _item.category_id diffrn_data_frame _item.mandatory_code no _item_type.code float save_ save__diffrn_data_frame.center_units _item_description.description ; The value of _diffrn_data_frame.center_units specifies the units in which the values of '_diffrn_data_frame.center_fast' and '_diffrn_data_frame.center_slow' are presented. The default is 'mm' for millimetres. The alternatives are 'pixels' and 'bins'. In all cases the center distances are measured from the center of the first pixel, i.e. in a 2x2 binning, the measuring origin is offset from the centers of the bins by one half pixel towards the first pixel. If 'bins' is specified, the data in '_array_intensities.pixel_fast_bin_size', '_array_intensities.pixel_slow_bin_size', and '_array_intensities.pixel_binning_method' is used to define the binning scheme. ; _item.name '_diffrn_data_frame.center_units' _item.category_id diffrn_data_frame _item.mandatory_code no _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail mm 'millimetres' pixels 'detector pixels' bins 'detector bins' save_ save__diffrn_data_frame.detector_element_id _item_description.description ; This item is a pointer to _diffrn_detector_element.id in the DIFFRN_DETECTOR_ELEMENT category. ; _item.name '_diffrn_data_frame.detector_element_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.detector_element_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.id _item_description.description ; The value of _diffrn_data_frame.id must uniquely identify each complete frame of data. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_data_frame.id' diffrn_data_frame yes '_diffrn_refln.frame_id' diffrn_refln yes '_diffrn_scan.frame_id_start' diffrn_scan yes '_diffrn_scan.frame_id_end' diffrn_scan yes '_diffrn_scan_frame.frame_id' diffrn_scan_frame yes '_diffrn_scan_frame_axis.frame_id' diffrn_scan_frame_axis yes _item_aliases.alias_name '_diffrn_frame_data.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_refln.frame_id' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_start' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_end' '_diffrn_data_frame.id' '_diffrn_scan_frame.frame_id' '_diffrn_data_frame.id' '_diffrn_scan_frame_axis.frame_id' '_diffrn_data_frame.id' save_ save__diffrn_data_frame.details _item_description.description ; The value of _diffrn_data_frame.details should give a description of special aspects of each frame of data. This is an appropriate location in which to record information from vendor headers as presented in those headers, but it should never be used as a substitute for providing the fully parsed information within the appropriate imgCIF/CBF categories. Normally, when a conversion from a miniCBF has been done the data from '_array_data.header_convention' should be transferred to this data item and '_array_data.header_convention' should be removed. ; _item.name '_diffrn_data_frame.details' _item.category_id diffrn_data_frame _item.mandatory_code no _item_aliases.alias_name '_diffrn_frame_data.details' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.4 _item_type.code text loop_ _item_examples.case _item_examples.detail ; HEADER_BYTES = 512; DIM = 2; BYTE_ORDER = big_endian; TYPE = unsigned_short; SIZE1 = 3072; SIZE2 = 3072; PIXEL_SIZE = 0.102588; BIN = 2x2; DETECTOR_SN = 901; TIME = 29.945155; DISTANCE = 200.000000; PHI = 85.000000; OSC_START = 85.000000; OSC_RANGE = 1.000000; WAVELENGTH = 0.979381; BEAM_CENTER_X = 157.500000; BEAM_CENTER_Y = 157.500000; PIXEL SIZE = 0.102588; OSCILLATION RANGE = 1; EXPOSURE TIME = 29.9452; TWO THETA = 0; BEAM CENTRE = 157.5 157.5; ; ; Example of header information extracted from an ADSC Quantum 315 detector header by CBFlib_0.7.6. Image provided by Chris Nielsen of ADSC from a data collection at SSRL beamline 1-5. ; save_ ########################################################################## # The following is a restatement of the mmCIF DIFFRN_DETECTOR, # # DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for # # the CBF/imgCIF extensions # ########################################################################## ################### # DIFFRN_DETECTOR # ################### save_DIFFRN_DETECTOR _category.description ; Data items in the DIFFRN_DETECTOR category describe the detector used to measure the scattered radiation, including any analyser and post-sample collimation. ; _category.id diffrn_detector _category.mandatory_code no loop_ _category_key.name '_diffrn_detector.diffrn_id' '_diffrn_detector.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _diffrn_detector.diffrn_id 'd1' _diffrn_detector.detector 'multiwire' _diffrn_detector.type 'Siemens' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector.details _item_description.description ; A description of special aspects of the radiation detector. ; _item.name '_diffrn_detector.details' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'slow mode' save_ save__diffrn_detector.detector _item_description.description ; The general class of the radiation detector. ; _item.name '_diffrn_detector.detector' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector' cifdic.c91 1.0 '_diffrn_detector' cif_core.dic 2.0 _item_type.code text loop_ _item_examples.case 'photographic film' 'scintillation counter' 'CCD plate' 'BF~3~ counter' save_ save__diffrn_detector.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. The value of _diffrn.id uniquely defines a set of diffraction data. ; _item.name '_diffrn_detector.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector.dtime _item_description.description ; The deadtime in microseconds of the detector(s) used to measure the diffraction intensities. ; _item.name '_diffrn_detector.dtime' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector_dtime' cifdic.c91 1.0 '_diffrn_detector_dtime' cif_core.dic 2.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code microseconds save_ save__diffrn_detector.id _item_description.description ; The value of _diffrn_detector.id must uniquely identify each detector used to collect each diffraction data set. If the value of _diffrn_detector.id is not given, it is implicitly equal to the value of _diffrn_detector.diffrn_id. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector.id' diffrn_detector implicit '_diffrn_detector_axis.detector_id' diffrn_detector_axis yes loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_detector_axis.detector_id' '_diffrn_detector.id' _item_type.code code save_ save__diffrn_detector.number_of_axes _item_description.description ; The value of _diffrn_detector.number_of_axes gives the number of axes of the positioner for the detector identified by _diffrn_detector.id. The word 'positioner' is a general term used in instrumentation design for devices that are used to change the positions of portions of apparatus by linear translation, rotation or combinations of such motions. Axes which are used to provide a coordinate system for the face of an area detetctor should not be counted for this data item. The description of each axis should be provided by entries in DIFFRN_DETECTOR_AXIS. ; _item.name '_diffrn_detector.number_of_axes' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_detector.type _item_description.description ; The make, model or name of the detector device used. ; _item.name '_diffrn_detector.type' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ ######################## # DIFFRN_DETECTOR_AXIS # ######################## save_DIFFRN_DETECTOR_AXIS _category.description ; Data items in the DIFFRN_DETECTOR_AXIS category associate axes with detectors. ; _category.id diffrn_detector_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_axis.detector_id' '_diffrn_detector_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_detector_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_detector_axis.axis_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_axis.detector_id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. This item was previously named _diffrn_detector_axis.id which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_detector_axis.detector_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_aliases.alias_name '_diffrn_detector_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ ########################### # DIFFRN_DETECTOR_ELEMENT # ########################### save_DIFFRN_DETECTOR_ELEMENT _category.description ; Data items in the DIFFRN_DETECTOR_ELEMENT category record the details about spatial layout and other characteristics of each element of a detector which may have multiple elements. In most cases, giving more detailed information in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS is preferable to simply providing the centre of the detector element. ; _category.id diffrn_detector_element _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_element.id' '_diffrn_detector_element.detector_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Detector d1 is composed of four CCD detector elements, each 200 mm by 200 mm, arranged in a square, in the pattern 1 2 * 3 4 Note that the beam centre is slightly displaced from each of the detector elements, just beyond the lower right corner of 1, the lower left corner of 2, the upper right corner of 3 and the upper left corner of 4. For each element, the detector face coordiate system, is assumed to have the fast axis running from left to right and the slow axis running from top to bottom with the origin at the top left corner. ; ; loop_ _diffrn_detector_element.detector_id _diffrn_detector_element.id _diffrn_detector_element.reference_center_fast _diffrn_detector_element.reference_center_slow _diffrn_detector_element.reference_center_units d1 d1_ccd_1 201.5 201.5 mm d1 d1_ccd_2 -1.8 201.5 mm d1 d1_ccd_3 201.6 -1.4 mm d1 d1_ccd_4 -1.7 -1.5 mm ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector_element.id _item_description.description ; The value of _diffrn_detector_element.id must uniquely identify each element of a detector. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector_element.id' diffrn_detector_element yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.detector_element_id' '_diffrn_detector_element.id' save_ save__diffrn_detector_element.detector_id _item_description.description ; This item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. ; _item.name '_diffrn_detector_element.detector_id' _item.category_id diffrn_detector_element _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_element.reference_center_fast _item_description.description ; The value of _diffrn_detector_element.reference_center_fast is the fast index axis beam center position relative to the detector element face in the units specified in the data item '_diffrn_detector_element.reference_center_units' along the fast axis of the detector from the center of the first pixel to the point at which the Z-axis (which should be colinear with the beam) intersects the face of the detector, if in fact is does. At the time of the measurement all settings of the detector positioner should be at their reference settings. If more than one reference setting has been used the value given whould be representive of the beam center as determined from the ensemble of settings. It is important to note that for measurements in millimetres, the sense of the axis is used, rather than the sign of the pixel-to-pixel increments. ; _item.name '_diffrn_detector_element.reference_center_fast' _item.category_id diffrn_detector_element _item.mandatory_code no _item_type.code float save_ save__diffrn_detector_element.reference_center_slow _item_description.description ; The value of _diffrn_detector_element.reference_center_slow is the slow index axis beam center position relative to the detector element face in the units specified in the data item '_diffrn_detector_element.reference_center_units' along the slow axis of the detector from the center of the first pixel to the point at which the Z-axis (which should be colinear with the beam) intersects the face of the detector, if in fact is does. At the time of the measurement all settings of the detector positioner should be at their reference settings. If more than one reference setting has been used the value givien whould be representive of the beam center as determined from the ensemble of settings. It is important to note that the sense of the axis is used, rather than the sign of the pixel-to-pixel increments. ; _item.name '_diffrn_detector_element.reference_center_slow' _item.category_id diffrn_detector_element _item.mandatory_code no _item_type.code float save_ save__diffrn_detector_element.reference_center_units _item_description.description ; The value of _diffrn_detector_element.reference_center_units specifies the units in which the values of '_diffrn_detector_element.reference_center_fast' and '_diffrn_detector_element.reference_center_slow' are presented. The default is 'mm' for millimetres. The alternatives are 'pixels' and 'bins'. In all cases the center distances are measured from the center of the first pixel, i.e. in a 2x2 binning, the measuring origin is offset from the centers of the bins by one half pixel towards the first pixel. If 'bins' is specified, the data in '_array_intensities.pixel_fast_bin_size', '_array_intensities.pixel_slow_bin_size', and '_array_intensities.pixel_binning_method' is used to define the binning scheme. ; _item.name '_diffrn_detector_element.reference_center_units' _item.category_id diffrn_detector_element _item.mandatory_code no _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail mm 'millimetres' pixels 'detector pixels' bins 'detector bins' save_ ######################## ## DIFFRN_MEASUREMENT ## ######################## save_DIFFRN_MEASUREMENT _category.description ; Data items in the DIFFRN_MEASUREMENT category record details about the device used to orient and/or position the crystal during data measurement and the manner in which the diffraction data were measured. ; _category.id diffrn_measurement _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement.device' '_diffrn_measurement.diffrn_id' '_diffrn_measurement.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_measurement.diffrn_id 'd1' _diffrn_measurement.device '3-circle camera' _diffrn_measurement.device_type 'Supper model X' _diffrn_measurement.device_details 'none' _diffrn_measurement.method 'omega scan' _diffrn_measurement.details ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _diffrn_measurement.diffrn_id 's1' _diffrn_measurement.device_type 'Philips PW1100/20 diffractometer' _diffrn_measurement.method 'theta/2theta (\q/2\q)' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_measurement.device _item_description.description ; The general class of goniometer or device used to support and orient the specimen. If the value of _diffrn_measurement.device is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id. Either _diffrn_measurement.device or _diffrn_measurement.id may be used to link to other categories. If the experimental setup admits multiple devices, then _diffrn_measurement.id is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.device' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_device' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement.device' _item_aliases.alias_name '_diffrn_measurement_device' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '3-circle camera' '4-circle camera' 'kappa-geometry camera' 'oscillation camera' 'precession camera' save_ save__diffrn_measurement.device_details _item_description.description ; A description of special aspects of the device used to measure the diffraction intensities. ; _item.name '_diffrn_measurement.device_details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; commercial goniometer modified locally to allow for 90\% \t arc ; save_ save__diffrn_measurement.device_type _item_description.description ; The make, model or name of the measurement device (goniometer) used. ; _item.name '_diffrn_measurement.device_type' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Supper model q' 'Huber model r' 'Enraf-Nonius model s' 'home-made' save_ save__diffrn_measurement.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_measurement.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement.details _item_description.description ; A description of special aspects of the intensity measurement. ; _item.name '_diffrn_measurement.details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; save_ save__diffrn_measurement.id _item_description.description ; The value of _diffrn_measurement.id must uniquely identify the set of mechanical characteristics of the device used to orient and/or position the sample used during the collection of each diffraction data set. If the value of _diffrn_measurement.id is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id. Either _diffrn_measurement.device or _diffrn_measurement.id may be used to link to other categories. If the experimental setup admits multiple devices, then _diffrn_measurement.id is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.id' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_id' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement.id' _item_type.code code save_ save__diffrn_measurement.method _item_description.description ; Method used to measure intensities. ; _item.name '_diffrn_measurement.method' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_method' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'profile data from theta/2theta (\q/2\q) scans' save_ save__diffrn_measurement.number_of_axes _item_description.description ; The value of _diffrn_measurement.number_of_axes gives the number of axes of the positioner for the goniometer or other sample orientation or positioning device identified by _diffrn_measurement.id. The description of the axes should be provided by entries in DIFFRN_MEASUREMENT_AXIS. ; _item.name '_diffrn_measurement.number_of_axes' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ # _diffrn_measurement.sample_detector_distance # _diffrn_measurement.sample_detector_voffset save__diffrn_measurement.sample_detector_distance _item_description.description ; The value of _diffrn_measurement.sample_detector_distance gives the unsigned distance in millimetres from the sample to the detector along the beam. ; _item.name '_diffrn_measurement.sample_detector_distance' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 0.0 _item_type.code float _item_units.code mm save_ save__diffrn_measurement.sample_detector_voffset _item_description.description ; The value of _diffrn_measurement.sample_detector_voffset gives the signed distance in millimetres in the vertical direction (positive for up) from the center of the beam to the center of the detector. ; _item.name '_diffrn_measurement.sample_detector_voffset' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . . . . _item_type.code float _item_units.code mm save_ save__diffrn_measurement.specimen_support _item_description.description ; The physical device used to support the crystal during data collection. ; _item.name '_diffrn_measurement.specimen_support' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_specimen_support' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'glass capillary' 'quartz capillary' 'fiber' 'metal loop' save_ ########################### # DIFFRN_MEASUREMENT_AXIS # ########################### save_DIFFRN_MEASUREMENT_AXIS _category.description ; Data items in the DIFFRN_MEASUREMENT_AXIS category associate axes with goniometers. ; _category.id diffrn_measurement_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_measurement_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_measurement_axis.axis_id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.measurement_device _item_description.description ; This data item is a pointer to _diffrn_measurement.device in the DIFFRN_MEASUREMENT category. ; _item.name '_diffrn_measurement_axis.measurement_device' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit _item_type.code text save_ save__diffrn_measurement_axis.measurement_id _item_description.description ; This data item is a pointer to _diffrn_measurement.id in the DIFFRN_MEASUREMENT category. This item was previously named _diffrn_measurement_axis.id, which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_measurement_axis.measurement_id' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_measurement_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ #################### # DIFFRN_RADIATION # #################### save_DIFFRN_RADIATION _category.description ; Data items in the DIFFRN_RADIATION category describe the radiation used for measuring diffraction intensities, its collimation and monochromatization before the sample. Post-sample treatment of the beam is described by data items in the DIFFRN_DETECTOR category. ; _category.id diffrn_radiation _category.mandatory_code no _category_key.name '_diffrn_radiation.diffrn_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_radiation.diffrn_id 'set1' _diffrn_radiation.collimation '0.3 mm double pinhole' _diffrn_radiation.monochromator 'graphite' _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.wavelength_id 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _diffrn_radiation.wavelength_id 1 _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.monochromator 'graphite' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_radiation.collimation _item_description.description ; The collimation or focusing applied to the radiation. ; _item.name '_diffrn_radiation.collimation' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_collimation' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '0.3 mm double-pinhole' '0.5 mm' 'focusing mirrors' save_ save__diffrn_radiation.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_radiation.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_radiation.div_x_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory X axis (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the standard uncertainty (e.s.d.) of the directions of photons in the XZ plane around the mean source beam direction. Note that for some synchrotrons this value is specified in milliradians, in which case a conversion is needed. To convert a value in milliradians to a value in degrees, multiply by 0.180 and divide by \p. ; _item.name '_diffrn_radiation.div_x_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.div_y_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory Y axis (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the standard uncertainty (e.s.d.) of the directions of photons in the YZ plane around the mean source beam direction. Note that for some synchrotrons this value is specified in milliradians, in which case a conversion is needed. To convert a value in milliradians to a value in degrees, multiply by 0.180 and divide by \p. ; _item.name '_diffrn_radiation.div_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.div_x_y_source _item_description.description ; Beam crossfire correlation degrees^2^ between the crossfire laboratory X-axis component and the crossfire laboratory Y-axis component (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the mean of the products of the deviations of the direction of each photon in XZ plane times the deviations of the direction of the same photon in the YZ plane around the mean source beam direction. This will be zero for uncorrelated crossfire. Note that some synchrotrons, this value is specified in milliradians^2^, in which case a conversion would be needed. To go from a value in milliradians^2^ to a value in degrees^2^, multiply by 0.180^2^ and divide by \p^2^. ; _item.name '_diffrn_radiation.div_x_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees_squared _item_default.value 0.0 save_ save__diffrn_radiation.filter_edge _item_description.description ; Absorption edge in \%Angstroms of the radiation filter used. ; _item.name '_diffrn_radiation.filter_edge' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_filter_edge' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__diffrn_radiation.inhomogeneity _item_description.description ; Half-width in millimetres of the incident beam in the direction perpendicular to the diffraction plane. ; _item.name '_diffrn_radiation.inhomogeneity' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_inhomogeneity' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code millimetres save_ save__diffrn_radiation.monochromator _item_description.description ; The method used to obtain monochromatic radiation. If a monochromator crystal is used, the material and the indices of the Bragg reflection are specified. ; _item.name '_diffrn_radiation.monochromator' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_monochromator' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Zr filter' 'Ge 220' 'none' 'equatorial mounted graphite' save_ save__diffrn_radiation.polarisn_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the perpendicular component of the polarization and the diffraction plane. See _diffrn_radiation_polarisn_ratio. ; _item.name '_diffrn_radiation.polarisn_norm' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_norm' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.polarisn_ratio _item_description.description ; Polarization ratio of the diffraction beam incident on the crystal. This is the ratio of the perpendicularly polarized to the parallel polarized component of the radiation. The perpendicular component forms an angle of _diffrn_radiation.polarisn_norm to the normal to the diffraction plane of the sample (i.e. the plane containing the incident and reflected beams). ; _item.name '_diffrn_radiation.polarisn_ratio' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_ratio' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__diffrn_radiation.polarizn_source_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the normal to the polarization plane and the laboratory Y axis as defined in the AXIS category. Note that this is the angle of polarization of the source photons, either directly from a synchrotron beamline or from a monochromater. This differs from the value of _diffrn_radiation.polarisn_norm in that _diffrn_radiation.polarisn_norm refers to polarization relative to the diffraction plane rather than to the laboratory axis system. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane should be taken as the XZ plane and the angle as 0. See _diffrn_radiation.polarizn_source_ratio. ; _item.name '_diffrn_radiation.polarizn_source_norm' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.polarizn_source_ratio _item_description.description ; (Ip-In)/(Ip+In), where Ip is the intensity (amplitude squared) of the electric vector in the plane of polarization and In is the intensity (amplitude squared) of the electric vector in the plane of the normal to the plane of polarization. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane is to be taken as the XZ plane and the normal is parallel to the Y axis. Thus, if there was complete polarization in the plane of polarization, the value of _diffrn_radiation.polarizn_source_ratio would be 1, and for an unpolarized beam _diffrn_radiation.polarizn_source_ratio would have a value of 0. If the X axis has been chosen to lie in the plane of polarization, this definition will agree with the definition of 'MONOCHROMATOR' in the Denzo glossary, and values of near 1 should be expected for a bending-magnet source. However, if the X axis were perpendicular to the polarization plane (not a common choice), then the Denzo value would be the negative of _diffrn_radiation.polarizn_source_ratio. See http://www.hkl-xray.com for information on Denzo and Otwinowski & Minor (1997). This differs both in the choice of ratio and choice of orientation from _diffrn_radiation.polarisn_ratio, which, unlike _diffrn_radiation.polarizn_source_ratio, is unbounded. Reference: Otwinowski, Z. & Minor, W. (1997). 'Processing of X-ray diffraction data collected in oscillation mode.' Methods Enzymol. 276, 307-326. ; _item.name '_diffrn_radiation.polarizn_source_ratio' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 -1.0 -1.0 -1.0 _item_type.code float save_ save__diffrn_radiation.probe _item_description.description ; Name of the type of radiation used. It is strongly recommended that this be given so that the probe radiation is clearly specified. ; _item.name '_diffrn_radiation.probe' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_probe' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value 'X-ray' 'neutron' 'electron' 'gamma' save_ save__diffrn_radiation.type _item_description.description ; The nature of the radiation. This is typically a description of the X-ray wavelength in Siegbahn notation. ; _item.name '_diffrn_radiation.type' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'CuK\a' 'Cu K\a~1~' 'Cu K-L~2,3~' 'white-beam' save_ save__diffrn_radiation.xray_symbol _item_description.description ; The IUPAC symbol for the X-ray wavelength for the probe radiation. ; _item.name '_diffrn_radiation.xray_symbol' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_xray_symbol' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value _item_enumeration.detail 'K-L~3~' 'K\a~1~ in older Siegbahn notation' 'K-L~2~' 'K\a~2~ in older Siegbahn notation' 'K-M~3~' 'K\b~1~ in older Siegbahn notation' 'K-L~2,3~' 'use where K-L~3~ and K-L~2~ are not resolved' save_ save__diffrn_radiation.wavelength_id _item_description.description ; This data item is a pointer to _diffrn_radiation_wavelength.id in the DIFFRN_RADIATION_WAVELENGTH category. ; _item.name '_diffrn_radiation.wavelength_id' _item.category_id diffrn_radiation _item.mandatory_code yes _item_type.code code save_ ################ # DIFFRN_REFLN # ################ save_DIFFRN_REFLN _category.description ; This category redefinition has been added to extend the key of the standard DIFFRN_REFLN category. ; _category.id diffrn_refln _category.mandatory_code no _category_key.name '_diffrn_refln.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_refln.frame_id _item_description.description ; This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_refln.frame_id' _item.category_id diffrn_refln _item.mandatory_code yes _item_type.code code save_ ############### # DIFFRN_SCAN # ############### save_DIFFRN_SCAN _category.description ; Data items in the DIFFRN_SCAN category describe the parameters of one or more scans, relating axis positions to frames. ; _category.id diffrn_scan _category.mandatory_code no _category_key.name '_diffrn_scan.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - derived from a suggestion by R. M. Sweet. The vector of each axis is not given here, because it is provided in the AXIS category. By making _diffrn_scan_axis.scan_id and _diffrn_scan_axis.axis_id keys of the DIFFRN_SCAN_AXIS category, an arbitrary number of scanning and fixed axes can be specified for a scan. In this example, three rotation axes and one translation axis at nonzero values are specified, with one axis stepping. There is no reason why more axes could not have been specified to step. Range information has been specified, but note that it can be calculated from the number of frames and the increment, so the data item _diffrn_scan_axis.angle_range could be dropped. Both the sweep data and the data for a single frame are specified. Note that the information on how the axes are stepped is given twice, once in terms of the overall averages in the value of _diffrn_scan.integration_time and the values for DIFFRN_SCAN_AXIS, and precisely for the given frame in the value for _diffrn_scan_frame.integration_time and the values for DIFFRN_SCAN_FRAME_AXIS. If dose-related adjustments are made to scan times and nonlinear stepping is done, these values may differ. Therefore, in interpreting the data for a particular frame it is important to use the frame-specific data. ; ; _diffrn_scan.id 1 _diffrn_scan.date_start '2001-11-18T03:26:42' _diffrn_scan.date_end '2001-11-18T03:36:45' _diffrn_scan.integration_time 3.0 _diffrn_scan.frame_id_start mad_L2_000 _diffrn_scan.frame_id_end mad_L2_200 _diffrn_scan.frames 201 loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment 1 omega 200.0 20.0 0.1 . . . 1 kappa -40.0 0.0 0.0 . . . 1 phi 127.5 0.0 0.0 . . . 1 tranz . . . 2.3 0.0 0.0 _diffrn_scan_frame.scan_id 1 _diffrn_scan_frame.date '2001-11-18T03:27:33' _diffrn_scan_frame.integration_time 3.0 _diffrn_scan_frame.frame_id mad_L2_018 _diffrn_scan_frame.frame_number 18 loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.angle_increment _diffrn_scan_frame_axis.displacement _diffrn_scan_frame_axis.displacement_increment mad_L2_018 omega 201.8 0.1 . . mad_L2_018 kappa -40.0 0.0 . . mad_L2_018 phi 127.5 0.0 . . mad_L2_018 tranz . . 2.3 0.0 ; ; Example 2 - a more extensive example (R. M. Sweet, P. J. Ellis & H. J. Bernstein). A detector is placed 240 mm along the Z axis from the goniometer. This leads to a choice: either the axes of the detector are defined at the origin, and then a Z setting of -240 is entered, or the axes are defined with the necessary Z offset. In this case, the setting is used and the offset is left as zero. This axis is called DETECTOR_Z. The axis for positioning the detector in the Y direction depends on the detector Z axis. This axis is called DETECTOR_Y. The axis for positioning the detector in the X direction depends on the detector Y axis (and therefore on the detector Z axis). This axis is called DETECTOR_X. This detector may be rotated around the Y axis. This rotation axis depends on the three translation axes. It is called DETECTOR_PITCH. A coordinate system is defined on the face of the detector in terms of 2300 0.150 mm pixels in each direction. The ELEMENT_X axis is used to index the first array index of the data array and the ELEMENT_Y axis is used to index the second array index. Because the pixels are 0.150mm X 0.150mm, the centre of the first pixel is at (0.075, 0.075) in this coordinate system. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 172.43 -172.43 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 2300 1 increasing ELEMENT_X ARRAY1 2 2300 2 increasing ELEMENT_Y # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.075 0.150 ELEMENT_Y ELEMENT_Y 0.075 0.150 # category ARRAY_ELEMENT_SIZE loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 ARRAY1 2 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; ; Example 3 - Example 2 revised for a spiral scan (R. M. Sweet, P. J. Ellis & H. J. Bernstein). A detector is placed 240 mm along the Z axis from the goniometer, as in Example 2 above, but in this example the image plate is scanned in a spiral pattern from the outside edge in. The axis for positioning the detector in the Y direction depends on the detector Z axis. This axis is called DETECTOR_Y. The axis for positioning the detector in the X direction depends on the detector Y axis (and therefore on the detector Z axis). This axis is called DETECTOR_X. This detector may be rotated around the Y axis. This rotation axis depends on the three translation axes. It is called DETECTOR_PITCH. A coordinate system is defined on the face of the detector in terms of a coupled rotation axis and radial scan axis to form a spiral scan. The rotation axis is called ELEMENT_ROT and the radial axis is called ELEMENT_RAD. A 150 micrometre radial pitch and a 75 micrometre 'constant velocity' angular pitch are assumed. Indexing is carried out first on the rotation axis and the radial axis is made to be dependent on it. The two axes are coupled to form an axis set ELEMENT_SPIRAL. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_ROT translation detector DETECTOR_PITCH 0 0 1 0 0 0 ELEMENT_RAD translation detector ELEMENT_ROT 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.angle _array_structure_list_axis.displacement _array_structure_list_axis.angular_pitch _array_structure_list_axis.radial_pitch ELEMENT_SPIRAL ELEMENT_ROT 0 . 0.075 . ELEMENT_SPIRAL ELEMENT_RAD . 172.5 . -0.150 # category ARRAY_ELEMENT_SIZE # the actual pixels are 0.075 by 0.150 mm # We give the coarser dimension here. loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="X-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_scan.id _item_description.description ; The value of _diffrn_scan.id uniquely identifies each scan. The identifier is used to tie together all the information about the scan. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_scan.id' diffrn_scan yes '_diffrn_scan_axis.scan_id' diffrn_scan_axis yes '_diffrn_scan_frame.scan_id' diffrn_scan_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_scan_axis.scan_id' '_diffrn_scan.id' '_diffrn_scan_frame.scan_id' '_diffrn_scan.id' save_ save__diffrn_scan.date_end _item_description.description ; The date and time of the end of the scan. Note that this may be an estimate generated during the scan, before the precise time of the end of the scan is known. ; _item.name '_diffrn_scan.date_end' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.date_start _item_description.description ; The date and time of the start of the scan. ; _item.name '_diffrn_scan.date_start' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.integration_time _item_description.description ; Approximate average time in seconds to integrate each step of the scan. The precise time for integration of each particular step must be provided in _diffrn_scan_frame.integration_time, even if all steps have the same integration time. ; _item.name '_diffrn_scan.integration_time' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan.frame_id_start _item_description.description ; The value of this data item is the identifier of the first frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_start' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frame_id_end _item_description.description ; The value of this data item is the identifier of the last frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_end' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frames _item_description.description ; The value of this data item is the number of frames in the scan. ; _item.name '_diffrn_scan.frames' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 1 1 1 save_ #################### # DIFFRN_SCAN_AXIS # #################### save_DIFFRN_SCAN_AXIS _category.description ; Data items in the DIFFRN_SCAN_AXIS category describe the settings of axes for particular scans. Unspecified axes are assumed to be at their zero points. ; _category.id diffrn_scan_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_axis.scan_id' '_diffrn_scan_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_axis.scan_id _item_description.description ; The value of this data item is the identifier of the scan for which axis settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan.id. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_axis.scan_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the scan for which settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan.id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_axis.axis_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.angle_start _item_description.description ; The starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_range _item_description.description ; The range from the starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_increment _item_description.description ; The increment for each step for the specified axis in degrees. In general, this will agree with _diffrn_scan_frame_axis.angle_increment. The sum of the values of _diffrn_scan_frame_axis.angle and _diffrn_scan_frame_axis.angle_increment is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of _diffrn_scan_axis.angle_increment will be representative of the ensemble of values of _diffrn_scan_frame_axis.angle_increment (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_rstrt_incr _item_description.description ; The increment after each step for the specified axis in degrees. In general, this will agree with _diffrn_scan_frame_axis.angle_rstrt_incr. The sum of the values of _diffrn_scan_frame_axis.angle, _diffrn_scan_frame_axis.angle_increment and _diffrn_scan_frame_axis.angle_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame and should equal _diffrn_scan_frame_axis.angle for this next frame. If the individual frame values vary, then the value of _diffrn_scan_axis.angle_rstrt_incr will be representative of the ensemble of values of _diffrn_scan_frame_axis.angle_rstrt_incr (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.displacement_start _item_description.description ; The starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_range _item_description.description ; The range from the starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_increment _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with _diffrn_scan_frame_axis.displacement_increment. The sum of the values of _diffrn_scan_frame_axis.displacement and _diffrn_scan_frame_axis.displacement_increment is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of _diffrn_scan_axis.displacement_increment will be representative of the ensemble of values of _diffrn_scan_frame_axis.displacement_increment (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_rstrt_incr _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with _diffrn_scan_frame_axis.displacement_rstrt_incr. The sum of the values of _diffrn_scan_frame_axis.displacement, _diffrn_scan_frame_axis.displacement_increment and _diffrn_scan_frame_axis.displacement_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame and should equal _diffrn_scan_frame_axis.displacement for this next frame. If the individual frame values vary, then the value of _diffrn_scan_axis.displacement_rstrt_incr will be representative of the ensemble of values of _diffrn_scan_frame_axis.displacement_rstrt_incr (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.reference_angle _item_description.description ; The setting of the specified axis in degrees against which measurements of the reference beam center and reference detector distance should be made. In general, this will agree with _diffrn_scan_frame_axis.reference_angle. If the individual frame values vary, then the value of _diffrn_scan_axis.reference_angle will be representative of the ensemble of values of _diffrn_scan_frame_axis.reference_angle (e.g. the mean). If not specified, the value defaults to zero. ; _item.name '_diffrn_scan_axis.reference_angle' _item.category_id diffrn_scan_axis _item.mandatory_code implicit _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.reference_displacement _item_description.description ; The setting of the specified axis in millimetres against which measurements of the reference beam center and reference detector distance should be made. In general, this will agree with _diffrn_scan_frame_axis.reference_displacement. If the individual frame values vary, then the value of _diffrn_scan_axis.reference_displacement will be representative of the ensemble of values of _diffrn_scan_frame_axis.reference_displacement (e.g. the mean). If not specified, the value defaults to to the value of _diffrn_scan_axis.displacement. ; _item.name '_diffrn_scan_axis.reference_displacement' _item.category_id diffrn_scan_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'millimetres' save_ ##################### # DIFFRN_SCAN_FRAME # ##################### save_DIFFRN_SCAN_FRAME _category.description ; Data items in the DIFFRN_SCAN_FRAME category describe the relationships of particular frames to scans. ; _category.id diffrn_scan_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame.scan_id' '_diffrn_scan_frame.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame.date _item_description.description ; The date and time of the start of the frame being scanned. ; _item.name '_diffrn_scan_frame.date' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan_frame.frame_id _item_description.description ; The value of this data item is the identifier of the frame being examined. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame.frame_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame.frame_number _item_description.description ; The value of this data item is the number of the frame within the scan, starting with 1. It is not necessarily the same as the value of _diffrn_scan_frame.frame_id, but it may be. ; _item.name '_diffrn_scan_frame.frame_number' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 0 0 0 save_ save__diffrn_scan_frame.integration_time _item_description.description ; The time in seconds to integrate this step of the scan. This should be the precise time of integration of each particular frame. The value of this data item should be given explicitly for each frame and not inferred from the value of _diffrn_scan.integration_time. ; _item.name '_diffrn_scan_frame.integration_time' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame.scan_id _item_description.description ; The value of _diffrn_scan_frame.scan_id identifies the scan containing this frame. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_frame.scan_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ ########################## # DIFFRN_SCAN_FRAME_AXIS # ########################## save_DIFFRN_SCAN_FRAME_AXIS _category.description ; Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the settings of axes for particular frames. Unspecified axes are assumed to be at their zero points. If, for any given frame, nonzero values apply for any of the data items in this category, those values should be given explicitly in this category and not simply inferred from values in DIFFRN_SCAN_AXIS. ; _category.id diffrn_scan_frame_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame_axis.frame_id' '_diffrn_scan_frame_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the frame for which settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_frame_axis.axis_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_axis.angle _item_description.description ; The setting of the specified axis in degrees for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.angle' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_increment _item_description.description ; The increment for this frame for the angular setting of the specified axis in degrees. The sum of the values of _diffrn_scan_frame_axis.angle and _diffrn_scan_frame_axis.angle_increment is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.angle_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_rstrt_incr _item_description.description ; The increment after this frame for the angular setting of the specified axis in degrees. The sum of the values of _diffrn_scan_frame_axis.angle, _diffrn_scan_frame_axis.angle_increment and _diffrn_scan_frame_axis.angle_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame and should equal _diffrn_scan_frame_axis.angle for this next frame. ; _item.name '_diffrn_scan_frame_axis.angle_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.displacement' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_increment _item_description.description ; The increment for this frame for the displacement setting of the specified axis in millimetres. The sum of the values of _diffrn_scan_frame_axis.displacement and _diffrn_scan_frame_axis.displacement_increment is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.displacement_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_rstrt_incr _item_description.description ; The increment for this frame for the displacement setting of the specified axis in millimetres. The sum of the values of _diffrn_scan_frame_axis.displacement, _diffrn_scan_frame_axis.displacement_increment and _diffrn_scan_frame_axis.displacement_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame and should equal _diffrn_scan_frame_axis.displacement for this next frame. ; _item.name '_diffrn_scan_frame_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.frame_id _item_description.description ; The value of this data item is the identifier of the frame for which axis settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame_axis.frame_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_axis.reference_angle _item_description.description ; The setting of the specified axis in degrees against which measurements of the reference beam center and reference detector distance should be made. This is normally the same for all frames, but the option is provided here of making changes when needed. If not provided, it is assumed to be zero. ; _item.name '_diffrn_scan_frame_axis.reference_angle' _item.category_id diffrn_scan_frame_axis _item.mandatory_code implicit _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.reference_displacement _item_description.description ; The setting of the specified axis in millimetres for this frame against which measurements of the reference beam center and reference detector distance should be made. This is normally the same for all frames, but the option is provided here of making changes when needed. If not provided, it is assumed to be equal to _diffrn_scan_frame_axis.displacement. ; _item.name '_diffrn_scan_frame_axis.reference_displacement' _item.category_id diffrn_scan_frame_axis _item.mandatory_code implicit _item_type.code float _item_units.code 'millimetres' save_ ####### # MAP # ####### save_MAP _category.description ; Data items in the MAP category record the details of a maps. Maps record values of parameters, such as density, that are functions of position within a cell or are functions of orthogonal coordinates in three space. A map may is composed of one or more map segments specified in the MAP_SEGMENT category. Examples are given in the MAP_SEGMENT category. ; _category.id map _category.mandatory_code no loop_ _category_key.name '_map.id' '_map.diffrn_id' '_map.entry_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Identifying an observed density map and a calculated density map ; ; loop_ _map.id _map.details rho_calc ; density calculated from F_calc derived from the ATOM_SITE list ; rho_obs ; density combining the observed structure factors with the calculated phases ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__map.details _item_description.description ; The value of _map.details should give a description of special aspects of each map. ; _item.name '_map.details' _item.category_id map _item.mandatory_code no _item_type.code text loop_ _item_examples.case _item_examples.detail # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Identifying an observed density map and a calculated density map ; ; loop_ _map.id _map.details rho_calc ; density calculated from F_calc derived from the ATOM_SITE list ; rho_obs ; density combining the observed structure factors with the calculated phases ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__map.diffrn_id _item_description.description ; This item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_map.diffrn_id' _item.category_id map _item.mandatory_code implicit _item_type.code code save_ save__map.entry_id _item_description.description ; This item is a pointer to _entry.id in the ENTRY category. ; _item.name '_map.entry_id' _item.category_id map _item.mandatory_code implicit _item_type.code code save_ save__map.id _item_description.description ; The value of _map.id must uniquely identify each map for the given diffrn.id or entry.id. ; loop_ _item.name _item.category_id _item.mandatory_code '_map.id' map yes '_map_segment.id' map_segment yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_map_segment.id' '_map.id' save_ ########################### # MAP_SEGMENT # ########################### save_MAP_SEGMENT _category.description ; Data items in the MAP_SEGMENT category record the details about each segment (section or brick) of a map. ; _category.id map_segment _category.mandatory_code no loop_ _category_key.name '_map_segment.id' '_map_segment.map_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Identifying an observed density map and a calculated density map, each consisting of one segment, both using the same array structure and mask. ; ; loop_ _map.id _map.details rho_calc ; density calculated from F_calc derived from the ATOM_SITE list ; rho_obs ; density combining the observed structure factors with the calculated phases ; loop_ _map_segment.map_id _map_segment.id _map_segment.array_id _map_segment.binary_id _map_segment.mask_array_id _map_segment.mask_binary_id rho_calc rho_calc map_structure 1 mask_structure 1 rho_obs rho_obs map_structure 2 mask_structure 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__map_segment.array_id _item_description.description ; The value of _map_segment.array_id identifies the array structure into which the map is organized. This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_map_segment.array_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code code save_ save__map_segment.binary_id _item_description.description ; The value of _map_segment.binary_id distinguishes the particular set of data organized according to _map_segment.array_id in which the data values of the map are stored. This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_map_segment.binary_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code int save_ save__map_segment.mask_array_id _item_description.description ; The value of _map_segment.mask_array_id, if given, the array structure into which the mask for the map is organized. If no value is given, then all elements of the map are valid. If a value is given, then only elements of the map for which the corresponding element of the mask is non-zero are valid. The value of _map_segment.mask_array_id differs from the value of _map_segment.array_id in order to permit the mask to be given as, say, unsigned 8-bit integers, while the map is given as a data type with more range. However, the two array structures must be aligned, using the same axes in the same order with the same displacements and increments This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_map_segment.mask_array_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code code save_ save__map_segment.mask_binary_id _item_description.description ; The value of _map_segment.mask_binary_id identifies the particular set of data organized according to _map_segment.mask_array_id specifying the mask for the map. This item is a pointer to _array_data.mask_binary_id in the ARRAY_DATA category. ; _item.name '_map_segment.mask_binary_id' _item.category_id map_segment _item.mandatory_code implicit _item_type.code int save_ save__map_segment.id _item_description.description ; The value of _map_segment.id must uniquely identify each segment of a map. ; loop_ _item.name _item.category_id _item.mandatory_code '_map_segment.id' map_segment yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_map_data_frame.map_segment_id' '_map_segment.id' save_ save__map_segment.map_id _item_description.description ; This item is a pointer to _map.id in the MAP category. ; _item.name '_map_segment.map_id' _item.category_id map_segment _item.mandatory_code yes _item_type.code code save_ save__map_segment.details _item_description.description ; The value of _map_segment.details should give a description of special aspects of each segment of a map. ; _item.name '_map_segment.details' _item.category_id map_segment _item.mandatory_code no _item_type.code text loop_ _item_examples.case _item_examples.detail ; Example to be provided ; ; ; save_ ######################## DEPRECATED DATA ITEMS ######################## save__diffrn_detector_axis.id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_detector_axis.id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_element.center[1] _item_description.description ; The value of _diffrn_detector_element.center[1] is the X component of the distortion-corrected beam centre in millimetres from the (0, 0) (lower-left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. Because of ambiguity about the setting used to determine this center, use of this data item is deprecated. The data item _diffrn_data_frame.center_fast which is referenced to the detector coordinate system and not directly to the laboratory coordinate system should be used instead. ; _item.name '_diffrn_detector_element.center[1]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.center[2] _item_description.description ; The value of _diffrn_detector_element.center[2] is the Y component of the distortion-corrected beam centre in millimetres from the (0, 0) (lower-left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. Because of ambiguity about the setting used to determine this center, use of this data item is deprecated. The data item _diffrn_data_frame.center_slow which is referenced to the detector coordinate system and not directly to the laboratory coordinate system should be used instead. ; _item.name '_diffrn_detector_element.center[2]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_measurement_axis.id _item_description.description ; This data item is a pointer to _diffrn_measurement.id in the DIFFRN_MEASUREMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_measurement_axis.id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ ######################### DEPRECATED CATEGORY ######################### ##################### # DIFFRN_FRAME_DATA # ##################### save_DIFFRN_FRAME_DATA _category.description ; Data items in the DIFFRN_FRAME_DATA category record the details about each frame of data. The items in this category are now in the DIFFRN_DATA_FRAME category. The items in the DIFFRN_FRAME_DATA category are now deprecated. The items from this category are provided as aliases in the 1.0 dictionary or, in the case of _diffrn_frame_data.details, in the 1.4 dictionary. THESE ITEMS SHOULD NOT BE USED FOR NEW WORK. The items from the old category are provided in this dictionary for completeness but should not be used or cited. To avoid confusion, the example has been removed and the redundant parent-child links to other categories have been removed. ; _category.id diffrn_frame_data _category.mandatory_code no loop_ _category_key.name '_diffrn_frame_data.id' '_diffrn_frame_data.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; THE DIFFRN_FRAME_DATA category is deprecated and should not be used. ; ; # EXAMPLE REMOVED # ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_frame_data.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.array_id' _item.category_id diffrn_frame_data _item.mandatory_code implicit _item_type.code code save_ save__diffrn_frame_data.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.binary_id' _item.category_id diffrn_frame_data _item.mandatory_code implicit _item_type.code int save_ save__diffrn_frame_data.detector_element_id _item_description.description ; This item is a pointer to _diffrn_detector_element.id in the DIFFRN_DETECTOR_ELEMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.detector_element_id' _item.category_id diffrn_frame_data _item.mandatory_code yes _item_type.code code save_ save__diffrn_frame_data.id _item_description.description ; The value of _diffrn_frame_data.id must uniquely identify each complete frame of data. DEPRECATED -- DO NOT USE ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_frame_data.id' diffrn_frame_data yes _item_type.code code save_ save__diffrn_frame_data.details _item_description.description ; The value of _diffrn_data_frame.details should give a description of special aspects of each frame of data. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.details' _item.category_id diffrn_frame_data _item.mandatory_code no _item_type.code text save_ ################ END DEPRECATED SECTION ########### #################### ## ITEM_TYPE_LIST ## #################### # # # The regular expressions defined here are not compliant # with the POSIX 1003.2 standard as they include the # '\n' and '\t' special characters. These regular expressions # have been tested using version 0.12 of Richard Stallman's # GNU regular expression library in POSIX mode. # In order to allow presentation of a regular expression # in a text field concatenate any line ending in a backslash # with the following line, after discarding the backslash. # # A formal definition of the '\n' and '\t' special characters # is most properly done in the DDL, but for completeness, please # note that '\n' is the line termination character ('newline') # and '\t' is the horizontal tab character. There is a formal # ambiguity in the use of '\n' for line termination, in that # the intention is that the equivalent machine/OS-dependent line # termination character sequence should be accepted as a match, e.g. # # '\r' (control-M) under MacOS # '\n' (control-J) under Unix # '\r\n' (control-M control-J) under DOS and MS Windows # loop_ _item_type_list.code _item_type_list.primitive_code _item_type_list.construct _item_type_list.detail code char '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words ... ; ucode uchar '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words (case insensitive) ... ; line char '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; char item types / multi-word items ... ; uline uchar '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; char item types / multi-word items (case insensitive)... ; text char '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; text item types / multi-line text ... ; binary char ;\n--CIF-BINARY-FORMAT-SECTION--\n\ [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\ \n--CIF-BINARY-FORMAT-SECTION---- ; ; binary items are presented as MIME-like ascii-encoded sections in an imgCIF. In a CBF, raw octet streams are used to convey the same information. ; int numb '-?[0-9]+' ; int item types are the subset of numbers that are the negative or positive integers. ; float numb '-?(([0-9]+)[.]?|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?' ; float item types are the subset of numbers that are the floating point numbers. ; any char '.*' ; A catch all for items that may take any form... ; yyyy-mm-dd char ;\ [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9]?[0-9]\ ((T[0-2][0-9](:[0-5][0-9](:[0-5][0-9](.[0-9]+)?)?)?)?\ ([+-][0-5][0-9]:[0-5][0-9]))? ; ; Standard format for CIF date and time strings (see http://www.iucr.org/iucr-top/cif/spec/datetime.html), consisting of a yyyy-mm-dd date optionally followed by the character 'T' followed by a 24-hour clock time, optionally followed by a signed time-zone offset. The IUCr standard has been extended to allow for an optional decimal fraction on the seconds of time. Time is local time if no time-zone offset is given. Note that this type extends the mmCIF yyyy-mm-dd type but does not conform to the mmCIF yyyy-mm-dd:hh:mm type that uses a ':' in place if the 'T' specified by the IUCr standard. For reading, both forms should be accepted, but for writing, only the IUCr form should be used. For maximal compatibility, the special time zone indicator 'Z' (for 'zulu') should be accepted on reading in place of '+00:00' for GMT. ; ##################### ## ITEM_UNITS_LIST ## ##################### loop_ _item_units_list.code _item_units_list.detail # 'metres' 'metres' 'centimetres' 'centimetres (metres * 10^( -2)^)' 'millimetres' 'millimetres (metres * 10^( -3)^)' 'nanometres' 'nanometres (metres * 10^( -9)^)' 'angstroms' '\%Angstroms (metres * 10^(-10)^)' 'picometres' 'picometres (metres * 10^(-12)^)' 'femtometres' 'femtometres (metres * 10^(-15)^)' # 'reciprocal_metres' 'reciprocal metres (metres^(-1)^)' 'reciprocal_centimetres' 'reciprocal centimetres ((metres * 10^( -2)^)^(-1)^)' 'reciprocal_millimetres' 'reciprocal millimetres ((metres * 10^( -3)^)^(-1)^)' 'reciprocal_nanometres' 'reciprocal nanometres ((metres * 10^( -9)^)^(-1)^)' 'reciprocal_angstroms' 'reciprocal \%Angstroms ((metres * 10^(-10)^)^(-1)^)' 'reciprocal_picometres' 'reciprocal picometres ((metres * 10^(-12)^)^(-1)^)' # 'nanometres_squared' 'nanometres squared (metres * 10^( -9)^)^2^' 'angstroms_squared' '\%Angstroms squared (metres * 10^(-10)^)^2^' '8pi2_angstroms_squared' '8\p^2^ * \%Angstroms squared (metres * 10^(-10)^)^2^' 'picometres_squared' 'picometres squared (metres * 10^(-12)^)^2^' # 'nanometres_cubed' 'nanometres cubed (metres * 10^( -9)^)^3^' 'angstroms_cubed' '\%Angstroms cubed (metres * 10^(-10)^)^3^' 'picometres_cubed' 'picometres cubed (metres * 10^(-12)^)^3^' # 'kilopascals' 'kilopascals' 'gigapascals' 'gigapascals' # 'hours' 'hours' 'minutes' 'minutes' 'seconds' 'seconds' 'microseconds' 'microseconds' # 'degrees' 'degrees (of arc)' 'degrees_squared' 'degrees (of arc) squared' # 'degrees_per_minute' 'degrees (of arc) per minute' # 'celsius' 'degrees (of temperature) Celsius' 'kelvins' 'degrees (of temperature) Kelvin' # 'counts' 'counts' 'counts_per_photon' 'counts per photon' # 'electrons' 'electrons' # 'electrons_squared' 'electrons squared' # 'electrons_per_nanometres_cubed' ; electrons per nanometres cubed (electrons/(metres * 10^( -9)^)^(-3)^) ; 'electrons_per_angstroms_cubed' ; electrons per \%Angstroms cubed (electrons/(metres * 10^(-10)^)^(-3)^) ; 'electrons_per_picometres_cubed' ; electrons per picometres cubed (electrons/(metres * 10^(-12)^)^(-3)^) ; 'kilowatts' 'kilowatts' 'milliamperes' 'milliamperes' 'kilovolts' 'kilovolts' # 'pixels_per_element' '(image) pixels per (array) element' # 'arbitrary' ; arbitrary system of units. ; # loop_ _item_units_conversion.from_code _item_units_conversion.to_code _item_units_conversion.operator _item_units_conversion.factor ### 'metres' 'centimetres' '*' 1.0E+02 'metres' 'millimetres' '*' 1.0E+03 'metres' 'nanometres' '*' 1.0E+09 'metres' 'angstroms' '*' 1.0E+10 'metres' 'picometres' '*' 1.0E+12 'metres' 'femtometres' '*' 1.0E+15 # 'centimetres' 'metres' '*' 1.0E-02 'centimetres' 'millimetres' '*' 1.0E+01 'centimetres' 'nanometres' '*' 1.0E+07 'centimetres' 'angstroms' '*' 1.0E+08 'centimetres' 'picometres' '*' 1.0E+10 'centimetres' 'femtometres' '*' 1.0E+13 # 'millimetres' 'metres' '*' 1.0E-03 'millimetres' 'centimetres' '*' 1.0E-01 'millimetres' 'nanometres' '*' 1.0E+06 'millimetres' 'angstroms' '*' 1.0E+07 'millimetres' 'picometres' '*' 1.0E+09 'millimetres' 'femtometres' '*' 1.0E+12 # 'nanometres' 'metres' '*' 1.0E-09 'nanometres' 'centimetres' '*' 1.0E-07 'nanometres' 'millimetres' '*' 1.0E-06 'nanometres' 'angstroms' '*' 1.0E+01 'nanometres' 'picometres' '*' 1.0E+03 'nanometres' 'femtometres' '*' 1.0E+06 # 'angstroms' 'metres' '*' 1.0E-10 'angstroms' 'centimetres' '*' 1.0E-08 'angstroms' 'millimetres' '*' 1.0E-07 'angstroms' 'nanometres' '*' 1.0E-01 'angstroms' 'picometres' '*' 1.0E+02 'angstroms' 'femtometres' '*' 1.0E+05 # 'picometres' 'metres' '*' 1.0E-12 'picometres' 'centimetres' '*' 1.0E-10 'picometres' 'millimetres' '*' 1.0E-09 'picometres' 'nanometres' '*' 1.0E-03 'picometres' 'angstroms' '*' 1.0E-02 'picometres' 'femtometres' '*' 1.0E+03 # 'femtometres' 'metres' '*' 1.0E-15 'femtometres' 'centimetres' '*' 1.0E-13 'femtometres' 'millimetres' '*' 1.0E-12 'femtometres' 'nanometres' '*' 1.0E-06 'femtometres' 'angstroms' '*' 1.0E-05 'femtometres' 'picometres' '*' 1.0E-03 ### 'reciprocal_centimetres' 'reciprocal_metres' '*' 1.0E+02 'reciprocal_centimetres' 'reciprocal_millimetres' '*' 1.0E-01 'reciprocal_centimetres' 'reciprocal_nanometres' '*' 1.0E-07 'reciprocal_centimetres' 'reciprocal_angstroms' '*' 1.0E-08 'reciprocal_centimetres' 'reciprocal_picometres' '*' 1.0E-10 # 'reciprocal_millimetres' 'reciprocal_metres' '*' 1.0E+03 'reciprocal_millimetres' 'reciprocal_centimetres' '*' 1.0E+01 'reciprocal_millimetres' 'reciprocal_nanometres' '*' 1.0E-06 'reciprocal_millimetres' 'reciprocal_angstroms' '*' 1.0E-07 'reciprocal_millimetres' 'reciprocal_picometres' '*' 1.0E-09 # 'reciprocal_nanometres' 'reciprocal_metres' '*' 1.0E+09 'reciprocal_nanometres' 'reciprocal_centimetres' '*' 1.0E+07 'reciprocal_nanometres' 'reciprocal_millimetres' '*' 1.0E+06 'reciprocal_nanometres' 'reciprocal_angstroms' '*' 1.0E-01 'reciprocal_nanometres' 'reciprocal_picometres' '*' 1.0E-03 # 'reciprocal_angstroms' 'reciprocal_metres' '*' 1.0E+10 'reciprocal_angstroms' 'reciprocal_centimetres' '*' 1.0E+08 'reciprocal_angstroms' 'reciprocal_millimetres' '*' 1.0E+07 'reciprocal_angstroms' 'reciprocal_nanometres' '*' 1.0E+01 'reciprocal_angstroms' 'reciprocal_picometres' '*' 1.0E-02 # 'reciprocal_picometres' 'reciprocal_metres' '*' 1.0E+12 'reciprocal_picometres' 'reciprocal_centimetres' '*' 1.0E+10 'reciprocal_picometres' 'reciprocal_millimetres' '*' 1.0E+09 'reciprocal_picometres' 'reciprocal_nanometres' '*' 1.0E+03 'reciprocal_picometres' 'reciprocal_angstroms' '*' 1.0E+01 ### 'nanometres_squared' 'angstroms_squared' '*' 1.0E+02 'nanometres_squared' 'picometres_squared' '*' 1.0E+06 # 'angstroms_squared' 'nanometres_squared' '*' 1.0E-02 'angstroms_squared' 'picometres_squared' '*' 1.0E+04 'angstroms_squared' '8pi2_angstroms_squared' '*' 78.9568 # 'picometres_squared' 'nanometres_squared' '*' 1.0E-06 'picometres_squared' 'angstroms_squared' '*' 1.0E-04 ### 'nanometres_cubed' 'angstroms_cubed' '*' 1.0E+03 'nanometres_cubed' 'picometres_cubed' '*' 1.0E+09 # 'angstroms_cubed' 'nanometres_cubed' '*' 1.0E-03 'angstroms_cubed' 'picometres_cubed' '*' 1.0E+06 # 'picometres_cubed' 'nanometres_cubed' '*' 1.0E-09 'picometres_cubed' 'angstroms_cubed' '*' 1.0E-06 ### 'kilopascals' 'gigapascals' '*' 1.0E-06 'gigapascals' 'kilopascals' '*' 1.0E+06 ### 'hours' 'minutes' '*' 6.0E+01 'hours' 'seconds' '*' 3.6E+03 'hours' 'microseconds' '*' 3.6E+09 # 'minutes' 'hours' '/' 6.0E+01 'minutes' 'seconds' '*' 6.0E+01 'minutes' 'microseconds' '*' 6.0E+07 # 'seconds' 'hours' '/' 3.6E+03 'seconds' 'minutes' '/' 6.0E+01 'seconds' 'microseconds' '*' 1.0E+06 # 'microseconds' 'hours' '/' 3.6E+09 'microseconds' 'minutes' '/' 6.0E+07 'microseconds' 'seconds' '/' 1.0E+06 ### 'celsius' 'kelvins' '-' 273.0 'kelvins' 'celsius' '+' 273.0 ### 'electrons_per_nanometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E+03 'electrons_per_nanometres_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+09 # 'electrons_per_angstroms_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-03 'electrons_per_angstroms_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+06 # 'electrons_per_picometres_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-09 'electrons_per_picometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E-06 ### ######################## ## DICTIONARY_HISTORY ## ######################## loop_ _dictionary_history.version _dictionary_history.update _dictionary_history.revision 1.5.4 2007-07-28 ; Typographics corrections (HJB) + Corrected embedded degree characters to \% + Corrected embedded Aring to \%A + Added trailing ^ for a power + Removed 2 cases of a space after an underscore in tag name. ; 1.5.3 2007-07-08 ; Changes to support SLS miniCBF and suggestions from the 24 May 07 BNL imgCIF workshop (HJB) + Added new data items '_array_data.header_contents', '_array_data.header_convention', '_diffrn_data_frame.center_fast', '_diffrn_data_frame.center_slow', '_diffrn_data_frame.center_units', '_diffrn_measurement.sample_detector_distance', '_diffrn_measurement.sample_detector_voffset + Deprecated data items '_diffrn_detector_element.center[1]', '_diffrn_detector_element.center[2]' + Added comments and example on miniCBF + Changed all array_id data items to implicit ; 1.5.2 2007-05-06 ; Further clarifications of the coordinate system. (HJB) ; 1.5.1 2007-04-26 ; Improve defintion of X-axis to cover the case of no goniometer and clean up more line folds (HJB) ; 1.5 2007-07-25 ; This is a cummulative list of the changes proposed since the imgCIF workshop in Hawaii in July 2006. It is the result of contributions by H. J. Bernstein, A. Hammersley, J. Wright and W. Kabsch. 2007-02-19 Consolidated changes (edited by HJB) + Added new data items '_array_structure.compression_type_flag', '_array_structure_list_axis.fract_displacement', '_array_structure_list_axis.displacement_increment', '_array_structure_list_axis.reference_angle', '_array_structure_list_axis.reference_displacement', '_axis.system', '_diffrn_detector_element.reference_center_fast', '_diffrn_detector_element.reference_center_slow', '_diffrn_scan_axis.reference_angle', '_diffrn_scan_axis.reference_displacement', '_map.details', '_map.diffrn_id', '_map.entry_id', '_map.id', '_map_segment.array_id', '_map_segment.binary_id', '_map_segment.mask_array_id', '_map_segment.mask_binary_id', '_map_segment.id', '_map_segment.map_id', '_map_segment.details. + Change type of '_array_structure.byte_order' and '_array_structure.compression_type' to ucode to make these values case-insensitive + Add values 'packed_v2' and 'byte_offset' to enumeration of values for '_array_structure.compression_type' + Add to definitions for the binary data type to handle new compression types, maps, and a variety of new axis types. 2007-07-25 Cleanup of typos for formal release (HJB) + Corrected text fields for reference_ tag descriptions that were off by one column + Fix typos in comments listing fract_ tags + Changed name of release from 1.5_DRAFT to 1.5 + Fix unclosed text fields in various map definitions ; 1.4 2006-07-04 ; This is a change to reintegrate all changes made in the course of publication of ITVG, by the RCSB from April 2005 through August 2008 and changes for the 2006 imgCIF workshop in Hawaii. 2006-07-04 Consolidated changes for the 2006 imgCIF workshop (edited by HJB) + Correct type of '_array_structure_list.direction' from 'int' to 'code'. + Added new data items suggested by CN '_diffrn_data_frame.details' '_array_intensities.pixel_fast_bin_size', '_array_intensities.pixel_slow_bin_size and '_array_intensities.pixel_binning_method + Added deprecated item for completeness '_diffrn_frame_data.details' + Added entry for missing item in contents list '_array_structure_list_axis.displacement' + Added new MIME type X-BASE32K based on work by VL, KM, GD, HJB + Correct description of MIME boundary delimiter to start in column 1. + General cleanup of text fields to conform to changes for ITVG by removing empty lines at start and finish of text field. + Amend example for ARRAY_INTENSITIES to include binning. + Add local copy of type specification (as 'code') for all children of '_diffrn.id'. + For consistency, change all references to 'pi' to '\p' and all references to 'Angstroms' to '\%Angstroms'. + Clean up all powers to use IUCr convention of '^power^', as in '10^3^' for '10**3'. + Update 'yyyy-mm-dd' type regex to allow truncation from the right and improve comments to explain handling of related mmCIF 'yyyy-mm-dd:hh:mm' type, and use of 'Z' for GMT time zone. 2005-03-08 and 2004-08-08 fixed cases where _item_units.code used instead of _item_type.code (JDW) 2004-04-15 fixed item ordering in _diffrn_measurement_axis.measurement_id added sub_category 'vector' (JDW) ; 1.3.2 2005-06-25 ; 2005-06-25 ITEM_TYPE_LIST: code, ucode, line, uline regexps updated to those of current mmCIF; float modified by allowing integers terminated by a point as valid. The 'time' part of yyyy-mm-dd types made optional in the regexp. (BM) 2005-06-17 Minor corrections as for proofs for IT G Chapter 4.6 (NJA) 2005-02-21 Minor corrections to spelling and punctuation (NJA) 2005-01-08 Changes as per Nicola Ashcroft. + Updated example 1 for DIFFRN_MEASUREMENT to agree with mmCIF. + Spelled out "micrometres" for "um" and "millimetres" for "mm". + Removed phrase "which may be stored" from ARRAY_STRUCTURE description. + Removed unused 'byte-offsets' compressions and updated cites to ITVG for '_array_structure.compression_type'. (HJB) ; 1.3.1 2003-08-13 ; Changes as per Frances C. Bernstein. + Identify initials. + Adopt British spelling for centre in text. + Set \p and \%Angstrom and powers. + Clean up commas and unclear wordings. + Clean up tenses in history. Changes as per Gotzon Madariaga. + Fix the ARRAY_DATA example to align '_array_data.binary_id' and X-Binary-ID. + Add a range to '_array_intensities.gain_esd'. + In the example of DIFFRN_DETECTOR_ELEMENT, '_diffrn_detector_element.id' and '_diffrn_detector_element.detector_id' interchanged. + Fix typos for direction, detector and axes. + Clarify description of polarisation. + Clarify axes in '_diffrn_detector_element.center[1]' '_diffrn_detector_element.center[2]'. + Add local item types for items that are pointers. (HJB) ; 1.3.0 2003-07-24 ; Changes as per Brian McMahon. + Consistently quote tags embedded in text. + Clean up introductory comments. + Adjust line lengths to fit in 80 character window. + Fix several descriptions in AXIS category which referred to '_axis.type' instead of the current item. + Fix erroneous use of deprecated item '_diffrn_detector_axis.id' in examples for DIFFRN_SCAN_AXIS. + Add deprecated items '_diffrn_detector_axis.id' and '_diffrn_measurement_axis.id'. (HJB) ; 1.2.4 2003-07-14 ; Changes as per I. David Brown. + Enhance descriptions in DIFFRN_SCAN_AXIS to make them less dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS. + Provide a copy of the deprecated DIFFRN_FRAME_DATA category for completeness. (HJB) ; 1.2.3 2003-07-03 ; Cleanup to conform to ITVG. + Correct sign error in ..._cubed units. + Correct '_diffrn_radiation.polarisn_norm' range. (HJB) ; 1.2.2 2003-03-10 ; Correction of typos in various DIFFRN_SCAN_AXIS descriptions. (HJB) ; 1.2.1 2003-02-22 ; Correction of ATOM_ for ARRAY_ typos in various descriptions. (HJB) ; 1.2 2003-02-07 ; Corrections to encodings (remove extraneous hyphens) remove extraneous underscore in '_array_structure.encoding_type' enumeration. Correct typos in items units list. (HJB) ; 1.1.3 2001-04-19 ; Another typo corrections by Wilfred Li, and cleanup by HJB. ; 1.1.2 2001-03-06 ; Several typo corrections by Wilfred Li. ; 1.1.1 2001-02-16 ; Several typo corrections by JW. ; 1.1 2001-02-06 ; Draft resulting from discussions on header for use at NSLS. (HJB) + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME. + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'. + Add '_diffrn_measurement_axis.measurement_device' and change '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'. + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source', '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm', '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end', '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr', '_diffrn_scan_axis.displacement_rstrt_incr', '_diffrn_scan_frame_axis.angle_increment', '_diffrn_scan_frame_axis.angle_rstrt_incr', '_diffrn_scan_frame_axis.displacement', '_diffrn_scan_frame_axis.displacement_increment',and '_diffrn_scan_frame_axis.displacement_rstrt_incr'. + Add '_diffrn_measurement.device' to category key. + Update yyyy-mm-dd to allow optional time with fractional seconds for time stamps. + Fix typos caught by RS. + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to allow for coupled axes, as in spiral scans. + Add examples for fairly complete headers thanks to R. Sweet and P. Ellis. ; 1.0 2000-12-21 ; Release version - few typos and tidying up. (BM & HJB) + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end of dictionary. + Alphabetize dictionary. ; 0.7.1 2000-09-29 ; Cleanup fixes. (JW) + Correct spelling of diffrn_measurement_axis in '_axis.id' + Correct ordering of uses of '_item.mandatory_code' and '_item_default.value'. ; 0.7.0 2000-09-09 ; Respond to comments by I. David Brown. (HJB) + Add further comments on '\n' and '\t'. + Update ITEM_UNITS_LIST by taking section from mmCIF dictionary and adding metres. Change 'meter' to 'metre' throughout. + Add missing enumerations to '_array_structure.compression_type' and make 'none' the default. + Remove parent-child relationship between '_array_structure_list.index' and '_array_structure_list.precedence'. + Improve alphabetization. + Fix '_array_intensities_gain.esd' related function. + Improve comments in AXIS. + Fix DIFFRN_FRAME_DATA example. + Remove erroneous DIFFRN_MEASUREMENT example. + Add '_diffrn_measurement_axis.id' to the category key. ; 0.6.0 1999-01-14 ; Remove redundant information for ENC_NONE data. (HJB) + After the D5 remove binary section identifier, size and compression type. + Add Control-L to header. ; 0.5.1 1999-01-03 ; Cleanup of typos and syntax errors. (HJB) + Cleanup example details for DIFFRN_SCAN category. + Add missing quote marks for '_diffrn_scan.id' definition. ; 0.5 1999-01-01 ; Modifications for axis definitions and reduction of binary header. (HJB) + Restore '_diffrn_detector.diffrn_id' to DIFFRN_DETECTOR KEY. + Add AXIS category. + Bring in complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories from cif_mm.dic for clarity. + Change '_array_structure.encoding_type' from type code to uline and added X-Binary-Element-Type to MIME header. + Add detector beam centre '_diffrn_detector_element.center[1]' and '_diffrn_detector_element.center[2]'. + Correct item name of '_diffrn_refln.frame_id'. + Replace reference to '_array_intensities.undefined' by '_array_intensities.undefined_value'. + Replace references to '_array_intensity.scaling' with '_array_intensities.scaling'. + Add DIFFRN_SCAN... categories. ; 0.4 1998-08-11 ; Modifications to the 0.3 imgCIF draft. (HJB) + Reflow comment lines over 80 characters and corrected typos. + Update examples and descriptions of MIME encoded data. + Change name to cbfext98.dic. ; 0.3 1998-07-04 ; Modifications for imgCIF. (HJB) + Add binary type, which is a text field containing a variant on MIME encoded data. + Change type of '_array_data.data' to binary and specify internal structure of raw binary data. + Add '_array_data.binary_id', and make '_diffrn_frame_data.binary_id' and '_array_intensities.binary_id' into pointers to this item. ; 0.2 1997-12-02 ; Modifications to the CBF draft. (JW) + Add category hierarchy for describing frame data developed from discussions at the BNL imgCIF Workshop Oct 1997. The following changes are made in implementing the workshop draft. Category DIFFRN_ARRAY_DATA is renamed to DIFFRN_FRAME_DATA. Category DIFFRN_FRAME_TYPE is renamed to DIFFRN_DETECTOR_ELEMENT. The parent item for '_diffrn_frame_data.array_id' is changed from '_array_structure_list.array_id' to '_array_structure.id'. Item '_diffrn_detector.array_id' is deleted. + Add data item '_diffrn_frame_data.binary_id' to identify data groups within a binary section. The formal identification of the binary section is still fuzzy. ; 0.1 1997-01-24 ; First draft of this dictionary in DDL 2.1 compliant format by John Westbrook (JW). This version is adapted from the Crystallographic Binary File (CBF) Format Draft Proposal provided by Andy Hammersley (AH). Modifications to the CBF draft. (JW) + In this version the array description has been cast in the categories ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. These categories have been generalized to describe array data of arbitrary dimension. + Array data in this description are contained in the category ARRAY_DATA. This departs from the CBF notion of data existing in some special comment. In this description, data are handled as an ordinary data item encapsulated in a character data type. Although data this manner deviates from CIF conventions, it does not violate any DDL 2.1 rules. DDL 2.1 regular expressions can be used to define the binary representation which will permit some level of data validation. In this version, the placeholder type code "any" has been used. This translates to a regular expression which will match any pattern. It should be noted that DDL 2.1 already supports array data objects although these have not been used in the current mmCIF dictionary. It may be possible to use the DDL 2.1 ITEM_STRUCTURE and ITEM_STRUCTURE_LIST categories to provide the information that is carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. By moving the array structure to the DDL level it would be possible to define an array type as well as a regular expression defining the data format. + Multiple array sections can be properly handled within a single datablock. ; #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof ./CBFlib-0.9.2.2/doc/Idiffrn_scan.frames.html0000644000076500007650000000500511603702115017072 0ustar yayayaya (IUCr) CIF Definition save__diffrn_scan.frames

    DRAFT DICTIONARY

    CBF/imgCIF Extensions Dictionary

    Draft version 1.5 for comment


    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib]


    Index

    Image dictionary (imgCIF) version 1.5.4

    _diffrn_scan.frames

    Name:
    '_diffrn_scan.frames'

    Definition:

            The value of this data item is the number of frames in
                   the scan.
    
    

    Type: int

    Mandatory item: no


    The permitted range is [1, infinity)

    Category: diffrn_scan

    HTML version of draft dictionary created by modified version of makedicthtml by B. McMahon from modified version of imgCIF dcitionary 1.3.2 which is subject to the following copyright:

    ./CBFlib-0.9.2.2/doc/cif_img_1.4_4Jul06_draft.dic0000644000076500007650000057771511603702115017255 0ustar yayayaya############################################################################## # # # Image CIF Dictionary (imgCIF) # # and Crystallographic Binary File Dictionary (CBF) # # Extending the Macromolecular CIF Dictionary (mmCIF) # # # # Version 1.4_DRAFT # # of 2006-07-04 # # ################################################################### # # # *** WARNING *** THIS IS A DRAFT FOR DISCUSSSION *** WARNING *** # # # # SUBJECT TO CHANGE WITHOUT NOTICE # # # # VERSIONS WILL BE POSTED AS cif_img_1.4_DDMMMYY_draft.html # # # # SEND COMMENTS TO imgcif-l@iucr.org CITING THE VERSION # # # ################################################################### # # This draft edited by H. J. Bernstein # # # # by Andrew P. Hammersley, Herbert J. Bernstein and John D. Westbrook # # # # This dictionary was adapted from format discussed at the imgCIF Workshop, # # held at BNL Oct 1997 and the Crystallographic Binary File Format Draft # # Proposal by Andrew Hammersley. The first DDL 2.1 Version was created by # # John Westbrook. This version was drafted by Herbert J. Bernstein and # # incorporates comments by I. David Brown, John Westbrook, Brian McMahon, # # Bob Sweet, Paul Ellis, Harry Powell, Wilfred Li, Gotzon Madariaga, # # Frances C. Bernstein, Chris Nielsen, Nicola Ashcroft and others. # ############################################################################## data_cif_img.dic _dictionary.title cif_img.dic _dictionary.version 1.4_DRAFT _dictionary.datablock_id cif_img.dic ############################################################################## # CONTENTS # # CATEGORY_GROUP_LIST # SUB_CATEGORY # # category ARRAY_DATA # # _array_data.array_id # _array_data.binary_id # _array_data.data # # category ARRAY_ELEMENT_SIZE # # _array_element_size.array_id # _array_element_size.index # _array_element_size.size # # category ARRAY_INTENSITIES # # _array_intensities.array_id # _array_intensities.binary_id # _array_intensities.gain # _array_intensities.gain_esd # _array_intensities.linearity # _array_intensities.offset # _array_intensities.scaling # _array_intensities.overload # _array_intensities.undefined_value # _array_intensities.pixel_fast_bin_size # _array_intensities.pixel_slow_bin_size # _array_intensities.pixel_binning_method # # category ARRAY_STRUCTURE # # _array_structure.byte_order # _array_structure.compression_type # _array_structure.encoding_type # _array_structure.id # # category ARRAY_STRUCTURE_LIST # # _array_structure_list.axis_set_id # _array_structure_list.array_id # _array_structure_list.dimension # _array_structure_list.direction # _array_structure_list.index # _array_structure_list.precedence # # category ARRAY_STRUCTURE_LIST_AXIS # # _array_structure_list_axis.axis_id # _array_structure_list_axis.axis_set_id # _array_structure_list_axis.angle # _array_structure_list_axis.angle_increment # _array_structure_list_axis.displacement # _array_structure_list_axis.displacement_increment # _array_structure_list_axis.angular_pitch # _array_structure_list_axis.radial_pitch # # category AXIS # # _axis.depends_on # _axis.equipment # _axis.id # _axis.offset[1] # _axis.offset[2] # _axis.offset[3] # _axis.type # _axis.vector[1] # _axis.vector[2] # _axis.vector[3] # # category DIFFRN_DATA_FRAME # # _diffrn_data_frame.array_id # _diffrn_data_frame.binary_id # _diffrn_data_frame.detector_element_id # _diffrn_data_frame.id # _diffrn_data_frame.details # # category DIFFRN_DETECTOR # # _diffrn_detector.details # _diffrn_detector.detector # _diffrn_detector.diffrn_id # _diffrn_detector.dtime # _diffrn_detector.id # _diffrn_detector.number_of_axes # _diffrn_detector.type # # category DIFFRN_DETECTOR_AXIS # # _diffrn_detector_axis.axis_id # _diffrn_detector_axis.detector_id # # category DIFFRN_DETECTOR_ELEMENT # # _diffrn_detector_element.center[1] # _diffrn_detector_element.center[2] # _diffrn_detector_element.id # _diffrn_detector_element.detector_id # # category DIFFRN_MEASUREMENT # # _diffrn_measurement.diffrn_id # _diffrn_measurement.details # _diffrn_measurement.device # _diffrn_measurement.device_details # _diffrn_measurement.device_type # _diffrn_measurement.id # _diffrn_measurement.method # _diffrn_measurement.number_of_axes # _diffrn_measurement.specimen_support # # category DIFFRN_MEASUREMENT_AXIS # # _diffrn_measurement_axis.axis_id # _diffrn_measurement_axis.measurement_device # _diffrn_measurement_axis.measurement_id # # category DIFFRN_RADIATION # # _diffrn_radiation.collimation # _diffrn_radiation.diffrn_id # _diffrn_radiation.div_x_source # _diffrn_radiation.div_y_source # _diffrn_radiation.div_x_y_source # _diffrn_radiation.filter_edge' # _diffrn_radiation.inhomogeneity # _diffrn_radiation.monochromator # _diffrn_radiation.polarisn_norm # _diffrn_radiation.polarisn_ratio # _diffrn_radiation.polarizn_source_norm # _diffrn_radiation.polarizn_source_ratio # _diffrn_radiation.probe # _diffrn_radiation.type # _diffrn_radiation.xray_symbol # _diffrn_radiation.wavelength_id # # category DIFFRN_REFLN # # _diffrn_refln.frame_id # # category DIFFRN_SCAN # # _diffrn_scan.id # _diffrn_scan.date_end # _diffrn_scan.date_start # _diffrn_scan.integration_time # _diffrn_scan.frame_id_start # _diffrn_scan.frame_id_end # _diffrn_scan.frames # # category DIFFRN_SCAN_AXIS # # _diffrn_scan_axis.axis_id # _diffrn_scan_axis.angle_start # _diffrn_scan_axis.angle_range # _diffrn_scan_axis.angle_increment # _diffrn_scan_axis.angle_rstrt_incr # _diffrn_scan_axis.displacement_start # _diffrn_scan_axis.displacement_range # _diffrn_scan_axis.displacement_increment # _diffrn_scan_axis.displacement_rstrt_incr # _diffrn_scan_axis.scan_id # # category DIFFRN_SCAN_FRAME # # _diffrn_scan_frame.date # _diffrn_scan_frame.frame_id # _diffrn_scan_frame.frame_number # _diffrn_scan_frame.integration_time # _diffrn_scan_frame.scan_id # # category DIFFRN_SCAN_FRAME_AXIS # # _diffrn_scan_frame_axis.axis_id # _diffrn_scan_frame_axis.angle # _diffrn_scan_frame_axis.angle_increment # _diffrn_scan_frame_axis.angle_rstrt_incr # _diffrn_scan_frame_axis.displacement # _diffrn_scan_frame_axis.displacement_increment # _diffrn_scan_frame_axis.displacement_rstrt_incr # _diffrn_scan_frame_axis.frame_id # # ***DEPRECATED*** data items # # _diffrn_detector_axis.id # _diffrn_measurement_axis.id # # ***DEPRECATED*** category DIFFRN_FRAME_DATA # # _diffrn_frame_data.array_id # _diffrn_frame_data.binary_id # _diffrn_frame_data.detector_element_id # _diffrn_frame_data.id # _diffrn_frame_data.details # # # ITEM_TYPE_LIST # ITEM_UNITS_LIST # DICTIONARY_HISTORY # ############################################################################## ######################### ## CATEGORY_GROUP_LIST ## ######################### loop_ _category_group_list.id _category_group_list.parent_id _category_group_list.description 'inclusive_group' . ; Categories that belong to the dictionary extension. ; 'array_data_group' 'inclusive_group' ; Categories that describe array data. ; 'axis_group' 'inclusive_group' ; Categories that describe axes. ; 'diffrn_group' 'inclusive_group' ; Categories that describe details of the diffraction experiment. ; ################## ## SUB_CATEGORY ## ################## loop_ _sub_category.id _sub_category.description 'matrix' ; The collection of elements of a matrix. ; 'vector' ; The collection of elements of a vector. ; ############## # ARRAY_DATA # ############## save_ARRAY_DATA _category.description ; Data items in the ARRAY_DATA category are the containers for the array data items described in the category ARRAY_STRUCTURE. ; _category.id array_data _category.mandatory_code no loop_ _category_key.name '_array_data.array_id' '_array_data.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows two binary data blocks. The first one was compressed by the CBF_CANONICAL compression algorithm and is presented as hexadecimal data. The first character 'H' on the data lines means hexadecimal. It could have been 'O' for octal or 'D' for decimal. The second character on the line shows the number of bytes in each word (in this case '4'), which then requires eight hexadecimal digits per word. The third character gives the order of octets within a word, in this case '<' for the ordering 4321 (i.e. 'big-endian'). Alternatively, the character '>' could have been used for the ordering 1234 (i.e. 'little-endian'). The block has a 'message digest' to check the integrity of the data. The second block is similar, but uses CBF_PACKED compression and BASE64 encoding. Note that the size and the digest are different. ; ; loop_ _array_data.array_id _array_data.binary_id _array_data.data image_1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_CANONICAL" Content-Transfer-Encoding: X-BASE16 X-Binary-Size: 3927126 X-Binary-ID: 1 Content-MD5: u2sTJEovAHkmkDjPi+gWsg== # Hexadecimal encoding, byte 0, byte order ...21 # H4< 0050B810 00000000 00000000 00000000 000F423F 00000000 00000000 ... .... --CIF-BINARY-FORMAT-SECTION---- ; image_2 2 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF-PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3745758 X-Binary-ID: 2 Content-MD5: 1zsJjWPfol2GYl2V+QSXrw== ELhQAAAAAAAA... ... --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_data.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_data.array_id' _item.category_id array_data _item.mandatory_code yes _item_type.code code save_ save__array_data.binary_id _item_description.description ; This item is an integer identifier which, along with _array_data.array_id, should uniquely identify the particular block of array data. If _array_data.binary_id is not explicitly given, it defaults to 1. The value of _array_data.binary_id distinguishes among multiple sets of data with the same array structure. If the MIME header of the data array specifies a value for X-Binary-ID, the value of _array_data.binary_id should be equal to the value given for X-Binary-ID. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_data.binary_id' array_data implicit '_diffrn_data_frame.binary_id' diffrn_data_frame implicit '_array_intensities.binary_id' array_intensities implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.binary_id' '_array_data.binary_id' '_array_intensities.binary_id' '_array_data.binary_id' _item_default.value 1 _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_data.data _item_description.description ; The value of _array_data.data contains the array data encapsulated in a STAR string. The representation used is a variant on the Multipurpose Internet Mail Extensions (MIME) specified in RFC 2045-2049 by N. Freed et al. The boundary delimiter used in writing an imgCIF or CBF is '\n--CIF-BINARY-FORMAT-SECTION--' (including the required initial '\n--'). The Content-Type may be any of the discrete types permitted in RFC 2045; 'application/octet-stream' is recommended. If an octet stream was compressed, the compression should be specified by the parameter 'conversions="x-CBF_PACKED"' or the parameter 'conversions="x-CBF_CANONICAL"'. The Content-Transfer-Encoding may be 'BASE64', 'Quoted-Printable', 'X-BASE8', 'X-BASE10', 'X-BASE16' or 'X-BASE32K', for an imgCIF or 'BINARY' for a CBF. The octal, decimal and hexadecimal transfer encodings are provided for convenience in debugging and are not recommended for archiving and data interchange. In a CIF, one of the parameters 'charset=us-ascii', 'charset=utf-8' or 'charset=utf-16' may be used on the Content-Transfer-Encoding to specify the character set used for the external presentation of the encoded data. If no charset parameter is given, the character set of the enclosing CIF is assumed. In any case, if a BOM flag is detected (FE FF for big-endian UTF-16, FF FE for little-endian UTF-16 or EF BB BF for UTF-8) is detected, the indicated charset will be assumed until the end of the encoded data or the detection of a different BOM. The charset of the Content-Transfer-Encoding is not the character set of the encoded data, only the character set of the presentation of the encoded data and should be respecified for each distinct STAR string. In an imgCIF file, the encoded binary data begins after the empty line terminating the header. In an imgCIF file, the encoded binary data ends with the terminating boundary delimiter '\n--CIF-BINARY-FORMAT-SECTION----' in the currently effective charset or with the '\n; ' that terminates the STAR string. In a CBF, the raw binary data begins after an empty line terminating the header and after the sequence: Octet Hex Decimal Purpose 0 0C 12 (ctrl-L) Page break 1 1A 26 (ctrl-Z) Stop listings in MS-DOS 2 04 04 (Ctrl-D) Stop listings in UNIX 3 D5 213 Binary section begins None of these octets are included in the calculation of the message size or in the calculation of the message digest. The X-Binary-Size header specifies the size of the equivalent binary data in octets. If compression was used, this size is the size after compression, including any book-keeping fields. An adjustment is made for the deprecated binary formats in which eight bytes of binary header are used for the compression type. In this case, the eight bytes used for the compression type are subtracted from the size, so that the same size will be reported if the compression type is supplied in the MIME header. Use of the MIME header is the recommended way to supply the compression type. In general, no portion of the binary header is included in the calculation of the size. The X-Binary-Element-Type header specifies the type of binary data in the octets, using the same descriptive phrases as in _array_structure.encoding_type. The default value is 'unsigned 32-bit integer'. An MD5 message digest may, optionally, be used. The 'RSA Data Security, Inc. MD5 Message-Digest Algorithm' should be used. No portion of the header is included in the calculation of the message digest. If the Transfer Encoding is 'X-BASE8', 'X-BASE10' or 'X-BASE16', the data are presented as octal, decimal or hexadecimal data organized into lines or words. Each word is created by composing octets of data in fixed groups of 2, 3, 4, 6 or 8 octets, either in the order ...4321 ('big- endian') or 1234... ('little-endian'). If there are fewer than the specified number of octets to fill the last word, then the missing octets are presented as '==' for each missing octet. Exactly two equal signs are used for each missing octet even for octal and decimal encoding. The format of lines is: rnd xxxxxx xxxxxx xxxxxx where r is 'H', 'O' or 'D' for hexadecimal, octal or decimal, n is the number of octets per word and d is '<' or '>' for the '...4321' and '1234...' octet orderings, respectively. The '==' padding for the last word should be on the appropriate side to correspond to the missing octets, e.g. H4< FFFFFFFF FFFFFFFF 07FFFFFF ====0000 or H3> FF0700 00==== For these hexadecimal, octal and decimal formats only, comments beginning with '#' are permitted to improve readability. BASE64 encoding follows MIME conventions. Octets are in groups of three: c1, c2, c3. The resulting 24 bits are broken into four six-bit quantities, starting with the high-order six bits (c1 >> 2) of the first octet, then the low-order two bits of the first octet followed by the high-order four bits of the second octet [(c1 & 3)<<4 | (c2>>4)], then the bottom four bits of the second octet followed by the high-order two bits of the last octet [(c2 & 15)<<2 | (c3>>6)], then the bottom six bits of the last octet (c3 & 63). Each of these four quantities is translated into an ASCII character using the mapping: 1 2 3 4 5 6 0123456789012345678901234567890123456789012345678901234567890123 | | | | | | | ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/ With short groups of octets padded on the right with one '=' if c3 is missing, and with '==' if both c2 and c3 are missing. X-BASE32K encoding is similar to BASE64 encoding, except that sets of 15 octets are encoded as sets of 8 16-bit unicode characters, by breaking the 120 bits into 8 15-bit quantities. 256 is added to each 15 bit quantity to bring it into a printable uncode range. When encoding, zero padding is used to fill out the last 15 bit quantity. If 8 or more bits of padding are used, a single equals sign (hexadecimal 003D) is appended. Embedded whitespace and newlines are introduced to produce lines of no more than 80 characters each. On decoding, all printable ascii characters and ascii whitespace characters are ignored except for any trailing equals signs. The number of trailing equals signs indicated the number of trailing octets to be trimmed from the end of the decoded data. (see Georgi Darakev, Vassil Litchev, Kostadin Z. Mitev, Herbert J. Bernstein, 'Efficient Support of Binary Data in the XML Implementation of the NeXus File Format',absract W0165, ACA Summer Meeting, Honolulu, HI, July 2006). QUOTED-PRINTABLE encoding also follows MIME conventions, copying octets without translation if their ASCII values are 32...38, 42, 48...57, 59, 60, 62, 64...126 and the octet is not a ';' in column 1. All other characters are translated to =nn, where nn is the hexadecimal encoding of the octet. All lines are 'wrapped' with a terminating '=' (i.e. the MIME conventions for an implicit line terminator are never used). ; _item.name '_array_data.data' _item.category_id array_data _item.mandatory_code yes _item_type.code binary save_ ###################### # ARRAY_ELEMENT_SIZE # ###################### save_ARRAY_ELEMENT_SIZE _category.description ; Data items in the ARRAY_ELEMENT_SIZE category record the physical size of array elements along each array dimension. ; _category.id array_element_size _category.mandatory_code no loop_ _category_key.name '_array_element_size.array_id' '_array_element_size.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A regular 2D array with a uniform element dimension of 1220 nanometres. ; ; loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size image_1 1 1.22e-6 image_1 2 1.22e-6 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_element_size.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_element_size.array_id' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.index _item_description.description ; This item is a pointer to _array_structure_list.index in the ARRAY_STRUCTURE_LIST category. ; _item.name '_array_element_size.index' _item.category_id array_element_size _item.mandatory_code yes _item_type.code code save_ save__array_element_size.size _item_description.description ; The size in metres of an image element in this dimension. This supposes that the elements are arranged on a regular grid. ; _item.name '_array_element_size.size' _item.category_id array_element_size _item.mandatory_code yes _item_type.code float _item_units.code 'metres' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ ##################### # ARRAY_INTENSITIES # ##################### save_ARRAY_INTENSITIES _category.description ; Data items in the ARRAY_INTENSITIES category record the information required to recover the intensity data from the set of data values stored in the ARRAY_DATA category. The detector may have a complex relationship between the raw intensity values and the number of incident photons. In most cases, the number stored in the final array will have a simple linear relationship to the actual number of incident photons, given by _array_intensities.gain. If raw, uncorrected values are presented (e.g. for calibration experiments), the value of _array_intensities.linearity will be 'raw' and _array_intensities.gain will not be used. ; _category.id array_intensities _category.mandatory_code no loop_ _category_key.name '_array_intensities.array_id' '_array_intensities.binary_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 ; ; loop_ _array_intensities.array_id _array_intensities.linearity _array_intensities.gain _array_intensities.overload _array_intensities.undefined_value _array_intensities.pixel_fast_bin_size _array_intensities.pixel_slow_bin_size _array_intensities.pixel_binning_method image_1 linear 1.2 655535 0 2 2 hardware ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_intensities.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_intensities.array_id' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code save_ save__array_intensities.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_array_intensities.binary_id' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code int save_ save__array_intensities.gain _item_description.description ; Detector 'gain'. The factor by which linearized intensity count values should be divided to produce true photon counts. ; _item.name '_array_intensities.gain' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain_esd' 'associated_value' save_ save__array_intensities.gain_esd _item_description.description ; The estimated standard deviation in detector 'gain'. ; _item.name '_array_intensities.gain_esd' _item.category_id array_intensities _item.mandatory_code yes _item_type.code float loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'counts_per_photon' loop_ _item_related.related_name _item_related.function_code '_array_intensities.gain' 'associated_esd' save_ save__array_intensities.linearity _item_description.description ; The intensity linearity scaling method used to convert from the raw intensity to the stored element value: 'linear' is linear. 'offset' means that the value defined by _array_intensities.offset should be added to each element value. 'scaling' means that the value defined by _array_intensities.scaling should be multiplied with each element value. 'scaling_offset' is the combination of the two previous cases, with the scale factor applied before the offset value. 'sqrt_scaled' means that the square root of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and squaring the result. 'logarithmic_scaled' means that the logarithm base 10 of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and calculating 10 to the power of this number. 'raw' means that the data are a set of raw values straight from the detector. ; _item.name '_array_intensities.linearity' _item.category_id array_intensities _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'linear' . 'offset' ; The value defined by _array_intensities.offset should be added to each element value. ; 'scaling' ; The value defined by _array_intensities.scaling should be multiplied with each element value. ; 'scaling_offset' ; The combination of the scaling and offset with the scale factor applied before the offset value. ; 'sqrt_scaled' ; The square root of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and squaring the result. ; 'logarithmic_scaled' ; The logarithm base 10 of raw intensities multiplied by _array_intensities.scaling is calculated and stored, perhaps rounded to the nearest integer. Thus, linearization involves dividing the stored values by _array_intensities.scaling and calculating 10 to the power of this number. ; 'raw' ; The array consists of raw values to which no corrections have been applied. While the handling of the data is similar to that given for 'linear' data with no offset, the meaning of the data differs in that the number of incident photons is not necessarily linearly related to the number of counts reported. This value is intended for use either in calibration experiments or to allow for handling more complex data-fitting algorithms than are allowed for by this data item. ; save_ save__array_intensities.offset _item_description.description ; Offset value to add to array element values in the manner described by the item _array_intensities.linearity. ; _item.name '_array_intensities.offset' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.overload _item_description.description ; The saturation intensity level for this data array. ; _item.name '_array_intensities.overload' _item.category_id array_intensities _item.mandatory_code no _item_type.code float _item_units.code 'counts' save_ save__array_intensities.pixel_fast_bin_size _item_description.description ; The value of _array_intensities.pixel_fast_bin_size specifies the number of pixels that compose one element in the direction of the most rapidly varying array dimension. Typical values are 1, 2, 4 or 8. When there is 1 pixel per array element in both directions, the value given for _array_intensities.pixel_binning_method normally should be 'none'. It is specified as a float to allow for binning algorithms that create array elements that are not integer multiples of the detector pixel size. ; _item.name '_array_intensities.pixel_fast_bin_size' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code float _item_default.value 1. loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'pixels_per_element' save_ save__array_intensities.pixel_slow_bin_size _item_description.description ; The value of _array_intensities.pixel_slow_bin_size specifies the number of pixels that compose one element in the direction of the second most rapidly varying array dimension. Typical values are 1, 2, 4 or 8. When there is 1 pixel per array element in both directions, the value given for _array_intensities.pixel_binning_method normally should be 'none'. It is specified as a float to allow for binning algorithms that create array elements that are not integer multiples of the detector pixel size. ; _item.name '_array_intensities.pixel_slow_bin_size' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code float _item_default.value 1. loop_ _item_range.maximum _item_range.minimum . 0.0 _item_units.code 'pixels_per_element' save_ save__array_intensities.pixel_binning_method _item_description.description ; The value of _array_intensities.pixel_binning_method specifies the method used to derive array elements from multiple pixels. ; _item.name '_array_intensities.pixel_binning_method' _item.category_id array_intensities _item.mandatory_code implicit _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'hardware' ; The element intensities were derived from the raw data of one or more pixels by used of hardware in the detector, e.g. by use of shift registers in a CCD to combine pixels into super-pixels. ; 'software' ; The element intensities were derived from the raw data of more than one pixel by use of software. ; 'combined' ; The element intensities were derived from the raw data of more than one pixel by use of both hardware and software, as when hardware binning is used in one direction and software in the other. ; 'none' ; In the both directions, the data has not been binned. The number of pixels is equal to the number of elements. When the value of _array_intensities.pixel_binning_method is 'none' the values of _array_intensities.pixel_fast_bin_size and _array_intensities.pixel_slow_bin_size both must be 1. ; 'unspecified' ; The method used to derive element intensities is not specified. ; _item_default.value 'unspecified' save_ save__array_intensities.scaling _item_description.description ; Multiplicative scaling value to be applied to array data in the manner described by item _array_intensities.linearity. ; _item.name '_array_intensities.scaling' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ save__array_intensities.undefined_value _item_description.description ; A value to be substituted for undefined values in the data array. ; _item.name '_array_intensities.undefined_value' _item.category_id array_intensities _item.mandatory_code no _item_type.code float save_ ################### # ARRAY_STRUCTURE # ################### save_ARRAY_STRUCTURE _category.description ; Data items in the ARRAY_STRUCTURE category record the organization and encoding of array data that may be stored in the ARRAY_DATA category. ; _category.id array_structure _category.mandatory_code no _category_key.name '_array_structure.id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - ; ; loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order image_1 "unsigned 16-bit integer" none little_endian ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure.byte_order _item_description.description ; The order of bytes for integer values which require more than 1 byte. (IBM-PC's and compatibles and DEC VAXs use low-byte-first ordered integers, whereas Hewlett Packard 700 series, Sun-4 and Silicon Graphics use high-byte-first ordered integers. DEC Alphas can produce/use either depending on a compiler switch.) ; _item.name '_array_structure.byte_order' _item.category_id array_structure _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'big_endian' ; The first byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; 'little_endian' ; The last byte in the byte stream of the bytes which make up an integer value is the most significant byte of an integer. ; save_ save__array_structure.compression_type _item_description.description ; Type of data-compression method used to compress the array data. ; _item.name '_array_structure.compression_type' _item.category_id array_structure _item.mandatory_code no _item_type.code code _item_default.value 'none' loop_ _item_enumeration.value _item_enumeration.detail 'none' ; Data are stored in normal format as defined by _array_structure.encoding_type and _array_structure.byte_order. ; 'packed' ; Using the 'packed' compression scheme, a CCP4-style packing (International Tables for Crystallography Volume G, Section 5.6.3.2) ; 'canonical' ; Using the 'canonical' compression scheme (International Tables for Crystallography Volume G, Section 5.6.3.1) ; save_ save__array_structure.encoding_type _item_description.description ; Data encoding of a single element of array data. In several cases, the IEEE format is referenced. See IEEE Standard 754-1985 (IEEE, 1985). Ref: IEEE (1985). IEEE Standard for Binary Floating-Point Arithmetic. ANSI/IEEE Std 754-1985. New York: Institute of Electrical and Electronics Engineers. ; _item.name '_array_structure.encoding_type' _item.category_id array_structure _item.mandatory_code yes _item_type.code uline loop_ _item_enumeration.value 'unsigned 8-bit integer' 'signed 8-bit integer' 'unsigned 16-bit integer' 'signed 16-bit integer' 'unsigned 32-bit integer' 'signed 32-bit integer' 'signed 32-bit real IEEE' 'signed 64-bit real IEEE' 'signed 32-bit complex IEEE' save_ save__array_structure.id _item_description.description ; The value of _array_structure.id must uniquely identify each item of array data. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure.id' array_structure yes '_array_data.array_id' array_data yes '_array_structure_list.array_id' array_structure_list yes '_array_intensities.array_id' array_intensities yes '_diffrn_data_frame.array_id' diffrn_data_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_data.array_id' '_array_structure.id' '_array_structure_list.array_id' '_array_structure.id' '_array_intensities.array_id' '_array_structure.id' '_diffrn_data_frame.array_id' '_array_structure.id' save_ ######################## # ARRAY_STRUCTURE_LIST # ######################## save_ARRAY_STRUCTURE_LIST _category.description ; Data items in the ARRAY_STRUCTURE_LIST category record the size and organization of each array dimension. The relationship to physical axes may be given. ; _category.id array_structure_list _category.mandatory_code no loop_ _category_key.name '_array_structure_list.array_id' '_array_structure_list.index' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - An image array of 1300 x 1200 elements. The raster order of the image is left to right (increasing) in the first dimension and bottom to top (decreasing) in the second dimension. ; ; loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id image_1 1 1300 1 increasing ELEMENT_X image_1 2 1200 2 decreasing ELEMENY_Y ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__array_structure_list.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_array_structure_list.array_id' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code code save_ save__array_structure_list.axis_set_id _item_description.description ; This is a descriptor for the physical axis or set of axes corresponding to an array index. This data item is related to the axes of the detector itself given in DIFFRN_DETECTOR_AXIS, but usually differs in that the axes in this category are the axes of the coordinate system of reported data points, while the axes in DIFFRN_DETECTOR_AXIS are the physical axes of the detector describing the 'poise' of the detector as an overall physical object. If there is only one axis in the set, the identifier of that axis should be used as the identifier of the set. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.axis_set_id' array_structure_list yes '_array_structure_list_axis.axis_set_id' array_structure_list_axis implicit _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_array_structure_list_axis.axis_set_id' '_array_structure_list.axis_set_id' save_ save__array_structure_list.dimension _item_description.description ; The number of elements stored in the array structure in this dimension. ; _item.name '_array_structure_list.dimension' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.direction _item_description.description ; Identifies the direction in which this array index changes. ; _item.name '_array_structure_list.direction' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code code loop_ _item_enumeration.value _item_enumeration.detail 'increasing' ; Indicates the index changes from 1 to the maximum dimension. ; 'decreasing' ; Indicates the index changes from the maximum dimension to 1. ; save_ save__array_structure_list.index _item_description.description ; Identifies the one-based index of the row or column in the array structure. ; loop_ _item.name _item.category_id _item.mandatory_code '_array_structure_list.index' array_structure_list yes '_array_structure_list.precedence' array_structure_list yes '_array_element_size.index' array_element_size yes _item_type.code int loop_ _item_linked.child_name _item_linked.parent_name '_array_element_size.index' '_array_structure_list.index' loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ save__array_structure_list.precedence _item_description.description ; Identifies the rank order in which this array index changes with respect to other array indices. The precedence of 1 indicates the index which changes fastest. ; _item.name '_array_structure_list.precedence' _item.category_id array_structure_list _item.mandatory_code yes _item_type.code int loop_ _item_range.maximum _item_range.minimum 1 1 . 1 save_ ############################# # ARRAY_STRUCTURE_LIST_AXIS # ############################# save_ARRAY_STRUCTURE_LIST_AXIS _category.description ; Data items in the ARRAY_STRUCTURE_LIST_AXIS category describe the physical settings of sets of axes for the centres of pixels that correspond to data points described in the ARRAY_STRUCTURE_LIST category. In the simplest cases, the physical increments of a single axis correspond to the increments of a single array index. More complex organizations, e.g. spiral scans, may require coupled motions along multiple axes. Note that a spiral scan uses two coupled axes: one for the angular direction and one for the radial direction. This differs from a cylindrical scan for which the two axes are not coupled into one set. ; _category.id array_structure_list_axis _category.mandatory_code no loop_ _category_key.name '_array_structure_list_axis.axis_set_id' '_array_structure_list_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' save_ save__array_structure_list_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes in the set of axes for which settings are being specified. Multiple axes may be specified for the same value of _array_structure_list_axis.axis_set_id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_array_structure_list_axis.axis_id' _item.category_id array_structure_list_axis _item.mandatory_code yes _item_type.code code save_ save__array_structure_list_axis.axis_set_id _item_description.description ; The value of this data item is the identifier of the set of axes for which axis settings are being specified. Multiple axes may be specified for the same value of _array_structure_list_axis.axis_set_id. This item is a pointer to _array_structure_list.axis_set_id in the ARRAY_STRUCTURE_LIST category. If this item is not specified, it defaults to the corresponding axis identifier. ; _item.name '_array_structure_list_axis.axis_set_id' _item.category_id array_structure_list_axis _item.mandatory_code implicit _item_type.code code save_ save__array_structure_list_axis.angle _item_description.description ; The setting of the specified axis in degrees for the first data point of the array index with the corresponding value of _array_structure_list.axis_set_id. If the index is specified as 'increasing', this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing', this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.angle' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.angle_increment _item_description.description ; The pixel-centre-to-pixel-centre increment in the angular setting of the specified axis in degrees. This is not meaningful in the case of 'constant velocity' spiral scans and should not be specified for this case. See _array_structure_list_axis.angular_pitch. ; _item.name '_array_structure_list_axis.angle_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__array_structure_list_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for the first data point of the array index with the corresponding value of _array_structure_list.axis_set_id. If the index is specified as 'increasing', this will be the centre of the pixel with index value 1. If the index is specified as 'decreasing', this will be the centre of the pixel with maximum index value. ; _item.name '_array_structure_list_axis.displacement' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.displacement_increment _item_description.description ; The pixel-centre-to-pixel-centre increment for the displacement setting of the specified axis in millimetres. ; _item.name '_array_structure_list_axis.displacement_increment' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.angular_pitch _item_description.description ; The pixel-centre-to-pixel-centre distance for a one-step change in the setting of the specified axis in millimetres. This is meaningful only for 'constant velocity' spiral scans or for uncoupled angular scans at a constant radius (cylindrical scans) and should not be specified for cases in which the angle between pixels (rather than the distance between pixels) is uniform. See _array_structure_list_axis.angle_increment. ; _item.name '_array_structure_list_axis.angular_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__array_structure_list_axis.radial_pitch _item_description.description ; The radial distance from one 'cylinder' of pixels to the next in millimetres. If the scan is a 'constant velocity' scan with differing angular displacements between pixels, the value of this item may differ significantly from the value of _array_structure_list_axis.displacement_increment. ; _item.name '_array_structure_list_axis.radial_pitch' _item.category_id array_structure_list_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ ######## # AXIS # ######## save_AXIS _category.description ; Data items in the AXIS category record the information required to describe the various goniometer, detector, source and other axes needed to specify a data collection. The location of each axis is specified by two vectors: the axis itself, given as a unit vector, and an offset to the base of the unit vector. These vectors are referenced to a right-handed laboratory coordinate system with its origin in the sample or specimen: | Y (to complete right-handed system) | | | | | |________________X / principal goniometer axis / / / / /Z (to source) Axis 1 (X): The X-axis is aligned to the mechanical axis pointing from the sample or specimen along the principal axis of the goniometer. Axis 2 (Y): The Y-axis completes an orthogonal right-handed system defined by the X-axis and the Z-axis (see below). Axis 3 (Z): The Z-axis is derived from the source axis which goes from the sample to the source. The Z-axis is the component of the source axis in the direction of the source orthogonal to the X-axis in the plane defined by the X-axis and the source axis. These axes are based on the goniometer, not on the orientation of the detector, gravity etc. The vectors necessary to specify all other axes are given by sets of three components in the order (X, Y, Z). If the axis involved is a rotation axis, it is right-handed, i.e. as one views the object to be rotated from the origin (the tail) of the unit vector, the rotation is clockwise. If a translation axis is specified, the direction of the unit vector specifies the sense of positive translation. Note: This choice of coordinate system is similar to but significantly different from the choice in MOSFLM (Leslie & Powell, 2004). In MOSFLM, X is along the X-ray beam (the CBF/imgCIF Z axis) and Z is along the rotation axis. All rotations are given in degrees and all translations are given in mm. Axes may be dependent on one another. The X-axis is the only goniometer axis the direction of which is strictly connected to the hardware. All other axes are specified by the positions they would assume when the axes upon which they depend are at their zero points. When specifying detector axes, the axis is given to the beam centre. The location of the beam centre on the detector should be given in the DIFFRN_DETECTOR category in distortion-corrected millimetres from the (0,0) corner of the detector. It should be noted that many different origins arise in the definition of an experiment. In particular, as noted above, it is necessary to specify the location of the beam centre on the detector in terms of the origin of the detector, which is, of course, not coincident with the centre of the sample. Ref: Leslie, A. G. W. & Powell, H. (2004). MOSFLM v6.11. MRC Laboratory of Molecular Biology, Hills Road, Cambridge, England. http://www.CCP4.ac.uk/dist/x-windows/Mosflm/. ; _category.id axis _category.mandatory_code no loop_ _category_key.name '_axis.id' '_axis.equipment' loop_ _category_group.id 'inclusive_group' 'axis_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - This example shows the axis specification of the axes of a kappa- geometry goniometer [see Stout, G. H. & Jensen, L. H. (1989). X-ray structure determination. A practical guide, 2nd ed. p. 134. New York: Wiley Interscience]. There are three axes specified, and no offsets. The outermost axis, omega, is pointed along the X axis. The next innermost axis, kappa, is at a 50 degree angle to the X axis, pointed away from the source. The innermost axis, phi, aligns with the X axis when omega and phi are at their zero points. If T-omega, T-kappa and T-phi are the transformation matrices derived from the axis settings, the complete transformation would be: x' = (T-omega) (T-kappa) (T-phi) x ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] omega rotation goniometer . 1 0 0 kappa rotation goniometer omega -.64279 0 -.76604 phi rotation goniometer kappa 1 0 0 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - This example show the axis specification of the axes of a detector, source and gravity. The order has been changed as a reminder that the ordering of presentation of tokens is not significant. The centre of rotation of the detector has been taken to be 68 millimetres in the direction away from the source. ; ; loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] source . source . 0 0 1 . . . gravity . gravity . 0 -1 0 . . . tranz translation detector rotz 0 0 1 0 0 -68 twotheta rotation detector . 1 0 0 . . . roty rotation detector twotheta 0 1 0 0 0 -68 rotz rotation detector roty 0 0 1 0 0 -68 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__axis.depends_on _item_description.description ; The value of _axis.depends_on specifies the next outermost axis upon which this axis depends. This item is a pointer to _axis.id in the same category. ; _item.name '_axis.depends_on' _item.category_id axis _item.mandatory_code no save_ save__axis.equipment _item_description.description ; The value of _axis.equipment specifies the type of equipment using the axis: 'goniometer', 'detector', 'gravity', 'source' or 'general'. ; _item.name '_axis.equipment' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail goniometer 'equipment used to orient or position samples' detector 'equipment used to detect reflections' general 'equipment used for general purposes' gravity 'axis specifying the downward direction' source 'axis specifying the direction sample to source' save_ save__axis.offset[1] _item_description.description ; The [1] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[2] _item_description.description ; The [2] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.offset[3] _item_description.description ; The [3] element of the three-element vector used to specify the offset to the base of a rotation or translation axis. The vector is specified in millimetres. ; _item.name '_axis.offset[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__axis.id _item_description.description ; The value of _axis.id must uniquely identify each axis relevant to the experiment. Note that multiple pieces of equipment may share the same axis (e.g. a twotheta arm), so the category key for AXIS also includes the equipment. ; loop_ _item.name _item.category_id _item.mandatory_code '_axis.id' axis yes '_array_structure_list_axis.axis_id' array_structure_list_axis yes '_diffrn_detector_axis.axis_id' diffrn_detector_axis yes '_diffrn_measurement_axis.axis_id' diffrn_measurement_axis yes '_diffrn_scan_axis.axis_id' diffrn_scan_axis yes '_diffrn_scan_frame_axis.axis_id' diffrn_scan_frame_axis yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_axis.depends_on' '_axis.id' '_array_structure_list_axis.axis_id' '_axis.id' '_diffrn_detector_axis.axis_id' '_axis.id' '_diffrn_measurement_axis.axis_id' '_axis.id' '_diffrn_scan_axis.axis_id' '_axis.id' '_diffrn_scan_frame_axis.axis_id' '_axis.id' save_ save__axis.type _item_description.description ; The value of _axis.type specifies the type of axis: 'rotation' or 'translation' (or 'general' when the type is not relevant, as for gravity). ; _item.name '_axis.type' _item.category_id axis _item.mandatory_code no _item_type.code ucode _item_default.value general loop_ _item_enumeration.value _item_enumeration.detail rotation 'right-handed axis of rotation' translation 'translation in the direction of the axis' general 'axis for which the type is not relevant' save_ save__axis.vector[1] _item_description.description ; The [1] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[1]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[2] _item_description.description ; The [2] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[2]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ save__axis.vector[3] _item_description.description ; The [3] element of the three-element vector used to specify the direction of a rotation or translation axis. The vector should be normalized to be a unit vector and is dimensionless. ; _item.name '_axis.vector[3]' _item.category_id axis _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float save_ ##################### # DIFFRN_DATA_FRAME # ##################### save_DIFFRN_DATA_FRAME _category.description ; Data items in the DIFFRN_DATA_FRAME category record the details about each frame of data. The items in this category were previously in a DIFFRN_FRAME_DATA category, which is now deprecated. The items from the old category are provided as aliases but should not be used for new work. ; _category.id diffrn_data_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_data_frame.id' '_diffrn_data_frame.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - A frame containing data from 4 frame elements. Each frame element has a common array configuration 'array_1' described in ARRAY_STRUCTURE and related categories. The data for each detector element are stored in four groups of binary data in the ARRAY_DATA category, linked by the array_id and binary_id. ; ; loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id frame_1 d1_ccd_1 array_1 1 frame_1 d1_ccd_2 array_1 2 frame_1 d1_ccd_3 array_1 3 frame_1 d1_ccd_4 array_1 4 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_data_frame.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. ; _item.name '_diffrn_data_frame.array_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.array_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_DATA category. ; _item.name '_diffrn_data_frame.binary_id' _item.category_id diffrn_data_frame _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_frame_data.binary_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code int save_ save__diffrn_data_frame.detector_element_id _item_description.description ; This item is a pointer to _diffrn_detector_element.id in the DIFFRN_DETECTOR_ELEMENT category. ; _item.name '_diffrn_data_frame.detector_element_id' _item.category_id diffrn_data_frame _item.mandatory_code yes _item_aliases.alias_name '_diffrn_frame_data.detector_element_id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ save__diffrn_data_frame.id _item_description.description ; The value of _diffrn_data_frame.id must uniquely identify each complete frame of data. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_data_frame.id' diffrn_data_frame yes '_diffrn_refln.frame_id' diffrn_refln yes '_diffrn_scan.frame_id_start' diffrn_scan yes '_diffrn_scan.frame_id_end' diffrn_scan yes '_diffrn_scan_frame.frame_id' diffrn_scan_frame yes '_diffrn_scan_frame_axis.frame_id' diffrn_scan_frame_axis yes _item_aliases.alias_name '_diffrn_frame_data.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_refln.frame_id' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_start' '_diffrn_data_frame.id' '_diffrn_scan.frame_id_end' '_diffrn_data_frame.id' '_diffrn_scan_frame.frame_id' '_diffrn_data_frame.id' '_diffrn_scan_frame_axis.frame_id' '_diffrn_data_frame.id' save_ save__diffrn_data_frame.details _item_description.description ; The value of _diffrn_data_frame.details should give a description of special aspects of each frame of data. This is an appropriate location in which to record information from vendor headers as presented in those headers, but it should never be used as a substitute for providing the fully parsed information within the appropriate imgCIF/CBF categories. ; _item.name '_diffrn_data_frame.details' _item.category_id diffrn_data_frame _item.mandatory_code no _item_aliases.alias_name '_diffrn_frame_data.details' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.4 _item_type.code text loop_ _item_examples.case _item_examples.detail ; HEADER_BYTES = 512; DIM = 2; BYTE_ORDER = big_endian; TYPE = unsigned_short; SIZE1 = 3072; SIZE2 = 3072; PIXEL_SIZE = 0.102588; BIN = 2x2; DETECTOR_SN = 901; TIME = 29.945155; DISTANCE = 200.000000; PHI = 85.000000; OSC_START = 85.000000; OSC_RANGE = 1.000000; WAVELENGTH = 0.979381; BEAM_CENTER_X = 157.500000; BEAM_CENTER_Y = 157.500000; PIXEL SIZE = 0.102588; OSCILLATION RANGE = 1; EXPOSURE TIME = 29.9452; TWO THETA = 0; BEAM CENTRE = 157.5 157.5; ; ; Example of header information extracted from an ADSC Quantum 315 detector header by CBFlib_0.7.6. Image provided by Chris Nielsen of ADSC from a data collection at SSRL beamline 1-5. ; save_ ########################################################################## # The following is a restatement of the mmCIF DIFFRN_DETECTOR, # # DIFFRN_MEASUREMENT and DIFFRN_RADIATION categories, modified for # # the CBF/imgCIF extensions # ########################################################################## ################### # DIFFRN_DETECTOR # ################### save_DIFFRN_DETECTOR _category.description ; Data items in the DIFFRN_DETECTOR category describe the detector used to measure the scattered radiation, including any analyser and post-sample collimation. ; _category.id diffrn_detector _category.mandatory_code no loop_ _category_key.name '_diffrn_detector.diffrn_id' '_diffrn_detector.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP. ; ; _diffrn_detector.diffrn_id 'd1' _diffrn_detector.detector 'multiwire' _diffrn_detector.type 'Siemens' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector.details _item_description.description ; A description of special aspects of the radiation detector. ; _item.name '_diffrn_detector.details' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'slow mode' save_ save__diffrn_detector.detector _item_description.description ; The general class of the radiation detector. ; _item.name '_diffrn_detector.detector' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector' cifdic.c91 1.0 '_diffrn_detector' cif_core.dic 2.0 _item_type.code text loop_ _item_examples.case 'photographic film' 'scintillation counter' 'CCD plate' 'BF~3~ counter' save_ save__diffrn_detector.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. The value of _diffrn.id uniquely defines a set of diffraction data. ; _item.name '_diffrn_detector.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector.dtime _item_description.description ; The deadtime in microseconds of the detector(s) used to measure the diffraction intensities. ; _item.name '_diffrn_detector.dtime' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_aliases.alias_name _item_aliases.dictionary _item_aliases.version '_diffrn_radiation_detector_dtime' cifdic.c91 1.0 '_diffrn_detector_dtime' cif_core.dic 2.0 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code microseconds save_ save__diffrn_detector.id _item_description.description ; The value of _diffrn_detector.id must uniquely identify each detector used to collect each diffraction data set. If the value of _diffrn_detector.id is not given, it is implicitly equal to the value of _diffrn_detector.diffrn_id. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector.id' diffrn_detector implicit '_diffrn_detector_axis.detector_id' diffrn_detector_axis yes loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_detector_axis.detector_id' '_diffrn_detector.id' _item_type.code code save_ save__diffrn_detector.number_of_axes _item_description.description ; The value of _diffrn_detector.number_of_axes gives the number of axes of the positioner for the detector identified by _diffrn_detector.id. The word 'positioner' is a general term used in instrumentation design for devices that are used to change the positions of portions of apparatus by linear translation, rotation or combinations of such motions. Axes which are used to provide a coordinate system for the face of an area detetctor should not be counted for this data item. The description of each axis should be provided by entries in DIFFRN_DETECTOR_AXIS. ; _item.name '_diffrn_detector.number_of_axes' _item.category_id diffrn_detector _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_detector.type _item_description.description ; The make, model or name of the detector device used. ; _item.name '_diffrn_detector.type' _item.category_id diffrn_detector _item.mandatory_code no _item_aliases.alias_name '_diffrn_detector_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text save_ ######################## # DIFFRN_DETECTOR_AXIS # ######################## save_DIFFRN_DETECTOR_AXIS _category.description ; Data items in the DIFFRN_DETECTOR_AXIS category associate axes with detectors. ; _category.id diffrn_detector_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_axis.detector_id' '_diffrn_detector_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_detector_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_detector_axis.axis_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_detector_axis.detector_id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. This item was previously named _diffrn_detector_axis.id which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_detector_axis.detector_id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_aliases.alias_name '_diffrn_detector_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ ########################### # DIFFRN_DETECTOR_ELEMENT # ########################### save_DIFFRN_DETECTOR_ELEMENT _category.description ; Data items in the DIFFRN_DETECTOR_ELEMENT category record the details about spatial layout and other characteristics of each element of a detector which may have multiple elements. In most cases, giving more detailed information in ARRAY_STRUCTURE_LIST and ARRAY_STRUCTURE_LIST_AXIS is preferable to simply providing the centre of the detector element. ; _category.id diffrn_detector_element _category.mandatory_code no loop_ _category_key.name '_diffrn_detector_element.id' '_diffrn_detector_element.detector_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - Detector d1 is composed of four CCD detector elements, each 200 mm by 200 mm, arranged in a square, in the pattern 1 2 * 3 4 Note that the beam centre is slightly displaced from each of the detector elements, just beyond the lower right corner of 1, the lower left corner of 2, the upper right corner of 3 and the upper left corner of 4. ; ; loop_ _diffrn_detector_element.detector_id _diffrn_detector_element.id _diffrn_detector_element.center[1] _diffrn_detector_element.center[2] d1 d1_ccd_1 201.5 -1.5 d1 d1_ccd_2 -1.8 -1.5 d1 d1_ccd_3 201.6 201.4 d1 d1_ccd_4 -1.7 201.5 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_detector_element.center[1] _item_description.description ; The value of _diffrn_detector_element.center[1] is the X component of the distortion-corrected beam centre in millimetres from the (0, 0) (lower-left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. ; _item.name '_diffrn_detector_element.center[1]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.center[2] _item_description.description ; The value of _diffrn_detector_element.center[2] is the Y component of the distortion-corrected beam centre in millimetres from the (0, 0) (lower-left) corner of the detector element viewed from the sample side. The X and Y axes are the laboratory coordinate system coordinates defined in the AXIS category measured when all positioning axes for the detector are at their zero settings. If the resulting X or Y axis is then orthogonal to the detector, the Z axis is used instead of the orthogonal axis. ; _item.name '_diffrn_detector_element.center[2]' _item.category_id diffrn_detector_element _item.mandatory_code no _item_default.value 0.0 _item_sub_category.id vector _item_type.code float _item_units.code millimetres save_ save__diffrn_detector_element.id _item_description.description ; The value of _diffrn_detector_element.id must uniquely identify each element of a detector. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_detector_element.id' diffrn_detector_element yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_data_frame.detector_element_id' '_diffrn_detector_element.id' save_ save__diffrn_detector_element.detector_id _item_description.description ; This item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. ; _item.name '_diffrn_detector_element.detector_id' _item.category_id diffrn_detector_element _item.mandatory_code yes _item_type.code code save_ ######################## ## DIFFRN_MEASUREMENT ## ######################## save_DIFFRN_MEASUREMENT _category.description ; Data items in the DIFFRN_MEASUREMENT category record details about the device used to orient and/or position the crystal during data measurement and the manner in which the diffraction data were measured. ; _category.id diffrn_measurement _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement.device' '_diffrn_measurement.diffrn_id' '_diffrn_measurement.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_measurement.diffrn_id 'd1' _diffrn_measurement.device '3-circle camera' _diffrn_measurement.device_type 'Supper model x' _diffrn_measurement.device_details 'none' _diffrn_measurement.method 'omega scan' _diffrn_measurement.details ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _diffrn_measurement.diffrn_id 's1' _diffrn_measurement.device_type 'Philips PW1100/20 diffractometer' _diffrn_measurement.method 'theta/2theta (\q/2\q)' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_measurement.device _item_description.description ; The general class of goniometer or device used to support and orient the specimen. If the value of _diffrn_measurement.device is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id. Either _diffrn_measurement.device or _diffrn_measurement.id may be used to link to other categories. If the experimental setup admits multiple devices, then _diffrn_measurement.id is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.device' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_device' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement.device' _item_aliases.alias_name '_diffrn_measurement_device' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '3-circle camera' '4-circle camera' 'kappa-geometry camera' 'oscillation camera' 'precession camera' save_ save__diffrn_measurement.device_details _item_description.description ; A description of special aspects of the device used to measure the diffraction intensities. ; _item.name '_diffrn_measurement.device_details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; commercial goniometer modified locally to allow for 90\% \t arc ; save_ save__diffrn_measurement.device_type _item_description.description ; The make, model or name of the measurement device (goniometer) used. ; _item.name '_diffrn_measurement.device_type' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_device_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Supper model q' 'Huber model r' 'Enraf-Nonius model s' 'home-made' save_ save__diffrn_measurement.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_measurement.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement.details _item_description.description ; A description of special aspects of the intensity measurement. ; _item.name '_diffrn_measurement.details' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_details' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case ; 440 frames, 0.20 degrees, 150 sec, detector distance 12 cm, detector angle 22.5 degrees ; save_ save__diffrn_measurement.id _item_description.description ; The value of _diffrn_measurement.id must uniquely identify the set of mechanical characteristics of the device used to orient and/or position the sample used during the collection of each diffraction data set. If the value of _diffrn_measurement.id is not given, it is implicitly equal to the value of _diffrn_measurement.diffrn_id. Either _diffrn_measurement.device or _diffrn_measurement.id may be used to link to other categories. If the experimental setup admits multiple devices, then _diffrn_measurement.id is used to provide a unique link. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_measurement.id' diffrn_measurement implicit '_diffrn_measurement_axis.measurement_id' diffrn_measurement_axis implicit loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement.id' _item_type.code code save_ save__diffrn_measurement.method _item_description.description ; Method used to measure intensities. ; _item.name '_diffrn_measurement.method' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_method' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text _item_examples.case 'profile data from theta/2theta (\q/2\q) scans' save_ save__diffrn_measurement.number_of_axes _item_description.description ; The value of _diffrn_measurement.number_of_axes gives the number of axes of the positioner for the goniometer or other sample orientation or positioning device identified by _diffrn_measurement.id. The description of the axes should be provided by entries in DIFFRN_MEASUREMENT_AXIS. ; _item.name '_diffrn_measurement.number_of_axes' _item.category_id diffrn_measurement _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum . 1 1 1 _item_type.code int save_ save__diffrn_measurement.specimen_support _item_description.description ; The physical device used to support the crystal during data collection. ; _item.name '_diffrn_measurement.specimen_support' _item.category_id diffrn_measurement _item.mandatory_code no _item_aliases.alias_name '_diffrn_measurement_specimen_support' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'glass capillary' 'quartz capillary' 'fiber' 'metal loop' save_ ########################### # DIFFRN_MEASUREMENT_AXIS # ########################### save_DIFFRN_MEASUREMENT_AXIS _category.description ; Data items in the DIFFRN_MEASUREMENT_AXIS category associate axes with goniometers. ; _category.id diffrn_measurement_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_measurement_axis.measurement_device' '_diffrn_measurement_axis.measurement_id' '_diffrn_measurement_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_measurement_axis.axis_id _item_description.description ; This data item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_measurement_axis.axis_id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.measurement_device _item_description.description ; This data item is a pointer to _diffrn_measurement.device in the DIFFRN_MEASUREMENT category. ; _item.name '_diffrn_measurement_axis.measurement_device' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit _item_type.code text save_ save__diffrn_measurement_axis.measurement_id _item_description.description ; This data item is a pointer to _diffrn_measurement.id in the DIFFRN_MEASUREMENT category. This item was previously named _diffrn_measurement_axis.id, which is now a deprecated name. The old name is provided as an alias but should not be used for new work. ; _item.name '_diffrn_measurement_axis.measurement_id' _item.category_id diffrn_measurement_axis _item.mandatory_code implicit _item_aliases.alias_name '_diffrn_measurement_axis.id' _item_aliases.dictionary cif_img.dic _item_aliases.version 1.0 _item_type.code code save_ #################### # DIFFRN_RADIATION # #################### save_DIFFRN_RADIATION _category.description ; Data items in the DIFFRN_RADIATION category describe the radiation used for measuring diffraction intensities, its collimation and monochromatization before the sample. Post-sample treatment of the beam is described by data items in the DIFFRN_DETECTOR category. ; _category.id diffrn_radiation _category.mandatory_code no _category_key.name '_diffrn_radiation.diffrn_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - based on PDB entry 5HVP and laboratory records for the structure corresponding to PDB entry 5HVP ; ; _diffrn_radiation.diffrn_id 'set1' _diffrn_radiation.collimation '0.3 mm double pinhole' _diffrn_radiation.monochromator 'graphite' _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.wavelength_id 1 ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 2 - based on data set TOZ of Willis, Beckwith & Tozer [Acta Cryst. (1991), C47, 2276-2277]. ; ; _diffrn_radiation.wavelength_id 1 _diffrn_radiation.type 'Cu K\a' _diffrn_radiation.monochromator 'graphite' ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_radiation.collimation _item_description.description ; The collimation or focusing applied to the radiation. ; _item.name '_diffrn_radiation.collimation' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_collimation' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case '0.3 mm double-pinhole' '0.5 mm' 'focusing mirrors' save_ save__diffrn_radiation.diffrn_id _item_description.description ; This data item is a pointer to _diffrn.id in the DIFFRN category. ; _item.name '_diffrn_radiation.diffrn_id' _item.mandatory_code yes _item_type.code code save_ save__diffrn_radiation.div_x_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory X axis (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the standard uncertainty (e.s.d.) of the directions of photons in the XZ plane around the mean source beam direction. Note that for some synchrotrons this value is specified in milliradians, in which case a conversion is needed. To convert a value in milliradians to a value in degrees, multiply by 0.180 and divide by \p. ; _item.name '_diffrn_radiation.div_x_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.div_y_source _item_description.description ; Beam crossfire in degrees parallel to the laboratory Y axis (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the standard uncertainty (e.s.d.) of the directions of photons in the YZ plane around the mean source beam direction. Note that for some synchrotrons this value is specified in milliradians, in which case a conversion is needed. To convert a value in milliradians to a value in degrees, multiply by 0.180 and divide by \p. ; _item.name '_diffrn_radiation.div_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.div_x_y_source _item_description.description ; Beam crossfire correlation degrees^2^ between the crossfire laboratory X-axis component and the crossfire laboratory Y-axis component (see AXIS category). This is a characteristic of the X-ray beam as it illuminates the sample (or specimen) after all monochromation and collimation. This is the mean of the products of the deviations of the direction of each photon in XZ plane times the deviations of the direction of the same photon in the YZ plane around the mean source beam direction. This will be zero for uncorrelated crossfire. Note that some synchrotrons, this value is specified in milliradians^2^, in which case a conversion would be needed. To go from a value in milliradians^2^ to a value in degrees^2^, multiply by 0.180^2^ and divide by \p^2^. ; _item.name '_diffrn_radiation.div_x_y_source' _item.category_id diffrn_radiation _item.mandatory_code no _item_type.code float _item_units.code degrees_squared _item_default.value 0.0 save_ save__diffrn_radiation.filter_edge _item_description.description ; Absorption edge in \%Angstroms of the radiation filter used. ; _item.name '_diffrn_radiation.filter_edge' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_filter_edge' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code angstroms save_ save__diffrn_radiation.inhomogeneity _item_description.description ; Half-width in millimetres of the incident beam in the direction perpendicular to the diffraction plane. ; _item.name '_diffrn_radiation.inhomogeneity' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_inhomogeneity' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float _item_units.code millimetres save_ save__diffrn_radiation.monochromator _item_description.description ; The method used to obtain monochromatic radiation. If a monochromator crystal is used, the material and the indices of the Bragg reflection are specified. ; _item.name '_diffrn_radiation.monochromator' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_monochromator' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code text loop_ _item_examples.case 'Zr filter' 'Ge 220' 'none' 'equatorial mounted graphite' save_ save__diffrn_radiation.polarisn_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the perpendicular component of the polarization and the diffraction plane. See _diffrn_radiation_polarisn_ratio. ; _item.name '_diffrn_radiation.polarisn_norm' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_norm' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees save_ save__diffrn_radiation.polarisn_ratio _item_description.description ; Polarization ratio of the diffraction beam incident on the crystal. This is the ratio of the perpendicularly polarized to the parallel polarized component of the radiation. The perpendicular component forms an angle of _diffrn_radiation.polarisn_norm to the normal to the diffraction plane of the sample (i.e. the plane containing the incident and reflected beams). ; _item.name '_diffrn_radiation.polarisn_ratio' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_polarisn_ratio' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 loop_ _item_range.maximum _item_range.minimum . 0.0 0.0 0.0 _item_type.code float save_ save__diffrn_radiation.polarizn_source_norm _item_description.description ; The angle in degrees, as viewed from the specimen, between the normal to the polarization plane and the laboratory Y axis as defined in the AXIS category. Note that this is the angle of polarization of the source photons, either directly from a synchrotron beamline or from a monochromater. This differs from the value of _diffrn_radiation.polarisn_norm in that _diffrn_radiation.polarisn_norm refers to polarization relative to the diffraction plane rather than to the laboratory axis system. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane should be taken as the XZ plane and the angle as 0. See _diffrn_radiation.polarizn_source_ratio. ; _item.name '_diffrn_radiation.polarizn_source_norm' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 90.0 90.0 90.0 -90.0 -90.0 -90.0 _item_type.code float _item_units.code degrees _item_default.value 0.0 save_ save__diffrn_radiation.polarizn_source_ratio _item_description.description ; (Ip-In)/(Ip+In), where Ip is the intensity (amplitude squared) of the electric vector in the plane of polarization and In is the intensity (amplitude squared) of the electric vector in the plane of the normal to the plane of polarization. In the case of an unpolarized beam, or a beam with true circular polarization, in which no single plane of polarization can be determined, the plane is to be taken as the XZ plane and the normal is parallel to the Y axis. Thus, if there was complete polarization in the plane of polarization, the value of _diffrn_radiation.polarizn_source_ratio would be 1, and for an unpolarized beam _diffrn_radiation.polarizn_source_ratio would have a value of 0. If the X axis has been chosen to lie in the plane of polarization, this definition will agree with the definition of 'MONOCHROMATOR' in the Denzo glossary, and values of near 1 should be expected for a bending-magnet source. However, if the X axis were perpendicular to the polarization plane (not a common choice), then the Denzo value would be the negative of _diffrn_radiation.polarizn_source_ratio. See http://www.hkl-xray.com for information on Denzo and Otwinowski & Minor (1997). This differs both in the choice of ratio and choice of orientation from _diffrn_radiation.polarisn_ratio, which, unlike _diffrn_radiation.polarizn_source_ratio, is unbounded. Reference: Otwinowski, Z. & Minor, W. (1997). 'Processing of X-ray diffraction data collected in oscillation mode.' Methods Enzymol. 276, 307-326. ; _item.name '_diffrn_radiation.polarizn_source_ratio' _item.category_id diffrn_radiation _item.mandatory_code no loop_ _item_range.maximum _item_range.minimum 1.0 1.0 1.0 -1.0 -1.0 -1.0 _item_type.code float save_ save__diffrn_radiation.probe _item_description.description ; Name of the type of radiation used. It is strongly recommended that this be given so that the probe radiation is clearly specified. ; _item.name '_diffrn_radiation.probe' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_probe' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value 'x-ray' 'neutron' 'electron' 'gamma' save_ save__diffrn_radiation.type _item_description.description ; The nature of the radiation. This is typically a description of the X-ray wavelength in Siegbahn notation. ; _item.name '_diffrn_radiation.type' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_type' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_examples.case 'CuK\a' 'Cu K\a~1~' 'Cu K-L~2,3~' 'white-beam' save_ save__diffrn_radiation.xray_symbol _item_description.description ; The IUPAC symbol for the X-ray wavelength for the probe radiation. ; _item.name '_diffrn_radiation.xray_symbol' _item.category_id diffrn_radiation _item.mandatory_code no _item_aliases.alias_name '_diffrn_radiation_xray_symbol' _item_aliases.dictionary cif_core.dic _item_aliases.version 2.0.1 _item_type.code line loop_ _item_enumeration.value _item_enumeration.detail 'K-L~3~' 'K\a~1~ in older Siegbahn notation' 'K-L~2~' 'K\a~2~ in older Siegbahn notation' 'K-M~3~' 'K\b~1~ in older Siegbahn notation' 'K-L~2,3~' 'use where K-L~3~ and K-L~2~ are not resolved' save_ save__diffrn_radiation.wavelength_id _item_description.description ; This data item is a pointer to _diffrn_radiation_wavelength.id in the DIFFRN_RADIATION_WAVELENGTH category. ; _item.name '_diffrn_radiation.wavelength_id' _item.category_id diffrn_radiation _item.mandatory_code yes _item_type.code code save_ ################ # DIFFRN_REFLN # ################ save_DIFFRN_REFLN _category.description ; This category redefinition has been added to extend the key of the standard DIFFRN_REFLN category. ; _category.id diffrn_refln _category.mandatory_code no _category_key.name '_diffrn_refln.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_refln.frame_id _item_description.description ; This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_refln.frame_id' _item.category_id diffrn_refln _item.mandatory_code yes _item_type.code code save_ ############### # DIFFRN_SCAN # ############### save_DIFFRN_SCAN _category.description ; Data items in the DIFFRN_SCAN category describe the parameters of one or more scans, relating axis positions to frames. ; _category.id diffrn_scan _category.mandatory_code no _category_key.name '_diffrn_scan.id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; Example 1 - derived from a suggestion by R. M. Sweet. The vector of each axis is not given here, because it is provided in the AXIS category. By making _diffrn_scan_axis.scan_id and _diffrn_scan_axis.axis_id keys of the DIFFRN_SCAN_AXIS category, an arbitrary number of scanning and fixed axes can be specified for a scan. In this example, three rotation axes and one translation axis at nonzero values are specified, with one axis stepping. There is no reason why more axes could not have been specified to step. Range information has been specified, but note that it can be calculated from the number of frames and the increment, so the data item _diffrn_scan_axis.angle_range could be dropped. Both the sweep data and the data for a single frame are specified. Note that the information on how the axes are stepped is given twice, once in terms of the overall averages in the value of _diffrn_scan.integration_time and the values for DIFFRN_SCAN_AXIS, and precisely for the given frame in the value for _diffrn_scan_frame.integration_time and the values for DIFFRN_SCAN_FRAME_AXIS. If dose-related adjustments are made to scan times and nonlinear stepping is done, these values may differ. Therefore, in interpreting the data for a particular frame it is important to use the frame-specific data. ; ; _diffrn_scan.id 1 _diffrn_scan.date_start '2001-11-18T03:26:42' _diffrn_scan.date_end '2001-11-18T03:36:45' _diffrn_scan.integration_time 3.0 _diffrn_scan.frame_id_start mad_L2_000 _diffrn_scan.frame_id_end mad_L2_200 _diffrn_scan.frames 201 loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment 1 omega 200.0 20.0 0.1 . . . 1 kappa -40.0 0.0 0.0 . . . 1 phi 127.5 0.0 0.0 . . . 1 tranz . . . 2.3 0.0 0.0 _diffrn_scan_frame.scan_id 1 _diffrn_scan_frame.date '2001-11-18T03:27:33' _diffrn_scan_frame.integration_time 3.0 _diffrn_scan_frame.frame_id mad_L2_018 _diffrn_scan_frame.frame_number 18 loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.angle_increment _diffrn_scan_frame_axis.displacement _diffrn_scan_frame_axis.displacement_increment mad_L2_018 omega 201.8 0.1 . . mad_L2_018 kappa -40.0 0.0 . . mad_L2_018 phi 127.5 0.0 . . mad_L2_018 tranz . . 2.3 0.0 ; ; Example 2 - a more extensive example (R. M. Sweet, P. J. Ellis & H. J. Bernstein). A detector is placed 240 mm along the Z axis from the goniometer. This leads to a choice: either the axes of the detector are defined at the origin, and then a Z setting of -240 is entered, or the axes are defined with the necessary Z offset. In this case, the setting is used and the offset is left as zero. This axis is called DETECTOR_Z. The axis for positioning the detector in the Y direction depends on the detector Z axis. This axis is called DETECTOR_Y. The axis for positioning the detector in the X direction depends on the detector Y axis (and therefore on the detector Z axis). This axis is called DETECTOR_X. This detector may be rotated around the Y axis. This rotation axis depends on the three translation axes. It is called DETECTOR_PITCH. A coordinate system is defined on the face of the detector in terms of 2300 0.150 mm pixels in each direction. The ELEMENT_X axis is used to index the first array index of the data array and the ELEMENT_Y axis is used to index the second array index. Because the pixels are 0.150mm x 0.150mm, the centre of the first pixel is at (0.075, 0.075) in this coordinate system. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 172.43 -172.43 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 2300 1 increasing ELEMENT_X ARRAY1 2 2300 2 increasing ELEMENT_Y # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.075 0.150 ELEMENT_Y ELEMENT_Y 0.075 0.150 # category ARRAY_ELEMENT_SIZE loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 ARRAY1 2 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; ; Example 3 - Example 2 revised for a spiral scan (R. M. Sweet, P. J. Ellis & H. J. Bernstein). A detector is placed 240 mm along the Z axis from the goniometer, as in Example 2 above, but in this example the image plate is scanned in a spiral pattern from the outside edge in. The axis for positioning the detector in the Y direction depends on the detector Z axis. This axis is called DETECTOR_Y. The axis for positioning the detector in the X direction depends on the detector Y axis (and therefore on the detector Z axis). This axis is called DETECTOR_X. This detector may be rotated around the Y axis. This rotation axis depends on the three translation axes. It is called DETECTOR_PITCH. A coordinate system is defined on the face of the detector in terms of a coupled rotation axis and radial scan axis to form a spiral scan. The rotation axis is called ELEMENT_ROT and the radial axis is called ELEMENT_RAD. A 150 micrometre radial pitch and a 75 micrometre 'constant velocity' angular pitch are assumed. Indexing is carried out first on the rotation axis and the radial axis is made to be dependent on it. The two axes are coupled to form an axis set ELEMENT_SPIRAL. ; ; ###CBF: VERSION 1.1 data_image_1 # category DIFFRN _diffrn.id P6MB _diffrn.crystal_id P6MB_CRYSTAL7 # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type P6MB synchrotron 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source P6MB WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes P6MB MAR345-SN26 'MAR 345' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method P6MB GONIOMETER 3 rotation # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 12.0 1.0 1.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 23.3 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI -165.8 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 20.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 GONIOMETER_KAPPA 23.3 0.0 FRAME1 GONIOMETER_PHI -165.8 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_ROT translation detector DETECTOR_PITCH 0 0 1 0 0 0 ELEMENT_RAD translation detector ELEMENT_ROT 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 8309900 1 increasing ELEMENT_SPIRAL # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.angle _array_structure_list_axis.displacement _array_structure_list_axis.angular_pitch _array_structure_list_axis.radial_pitch ELEMENT_SPIRAL ELEMENT_ROT 0 . 0.075 . ELEMENT_SPIRAL ELEMENT_RAD . 172.5 . -0.150 # category ARRAY_ELEMENT_SIZE # the actual pixels are 0.075 by 0.150 mm # We give the coarser dimension here. loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 150e-6 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_PACKED" Content-Transfer-Encoding: BASE64 X-Binary-Size: 3801324 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: 07lZFvF+aOcW85IN7usl8A== AABRAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAAZBQSr1sKNBOeOe9HITdMdDUnbq7bg ... 8REo6TtBrxJ1vKqAvx9YDMD6J18Qg83OMr/tgssjMIJMXATDsZobL90AEXc4KigE --CIF-BINARY-FORMAT-SECTION---- ; ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_scan.id _item_description.description ; The value of _diffrn_scan.id uniquely identifies each scan. The identifier is used to tie together all the information about the scan. ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_scan.id' diffrn_scan yes '_diffrn_scan_axis.scan_id' diffrn_scan_axis yes '_diffrn_scan_frame.scan_id' diffrn_scan_frame yes _item_type.code code loop_ _item_linked.child_name _item_linked.parent_name '_diffrn_scan_axis.scan_id' '_diffrn_scan.id' '_diffrn_scan_frame.scan_id' '_diffrn_scan.id' save_ save__diffrn_scan.date_end _item_description.description ; The date and time of the end of the scan. Note that this may be an estimate generated during the scan, before the precise time of the end of the scan is known. ; _item.name '_diffrn_scan.date_end' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.date_start _item_description.description ; The date and time of the start of the scan. ; _item.name '_diffrn_scan.date_start' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan.integration_time _item_description.description ; Approximate average time in seconds to integrate each step of the scan. The precise time for integration of each particular step must be provided in _diffrn_scan_frame.integration_time, even if all steps have the same integration time. ; _item.name '_diffrn_scan.integration_time' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan.frame_id_start _item_description.description ; The value of this data item is the identifier of the first frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_start' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frame_id_end _item_description.description ; The value of this data item is the identifier of the last frame in the scan. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan.frame_id_end' _item.category_id diffrn_scan _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan.frames _item_description.description ; The value of this data item is the number of frames in the scan. ; _item.name '_diffrn_scan.frames' _item.category_id diffrn_scan _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 1 1 1 save_ #################### # DIFFRN_SCAN_AXIS # #################### save_DIFFRN_SCAN_AXIS _category.description ; Data items in the DIFFRN_SCAN_AXIS category describe the settings of axes for particular scans. Unspecified axes are assumed to be at their zero points. ; _category.id diffrn_scan_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_axis.scan_id' '_diffrn_scan_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_axis.scan_id _item_description.description ; The value of this data item is the identifier of the scan for which axis settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan.id. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_axis.scan_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the scan for which settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan.id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_axis.axis_id' _item.category_id diffrn_scan_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_axis.angle_start _item_description.description ; The starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_range _item_description.description ; The range from the starting position for the specified axis in degrees. ; _item.name '_diffrn_scan_axis.angle_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_increment _item_description.description ; The increment for each step for the specified axis in degrees. In general, this will agree with _diffrn_scan_frame_axis.angle_increment. The sum of the values of _diffrn_scan_frame_axis.angle and _diffrn_scan_frame_axis.angle_increment is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of _diffrn_scan_axis.angle_increment will be representative of the ensemble of values of _diffrn_scan_frame_axis.angle_increment (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.angle_rstrt_incr _item_description.description ; The increment after each step for the specified axis in degrees. In general, this will agree with _diffrn_scan_frame_axis.angle_rstrt_incr. The sum of the values of _diffrn_scan_frame_axis.angle, _diffrn_scan_frame_axis.angle_increment and _diffrn_scan_frame_axis.angle_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame and should equal _diffrn_scan_frame_axis.angle for this next frame. If the individual frame values vary, then the value of _diffrn_scan_axis.angle_rstrt_incr will be representative of the ensemble of values of _diffrn_scan_frame_axis.angle_rstrt_incr (e.g. the mean). ; _item.name '_diffrn_scan_axis.angle_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_axis.displacement_start _item_description.description ; The starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_start' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_range _item_description.description ; The range from the starting position for the specified axis in millimetres. ; _item.name '_diffrn_scan_axis.displacement_range' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_increment _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with _diffrn_scan_frame_axis.displacement_increment. The sum of the values of _diffrn_scan_frame_axis.displacement and _diffrn_scan_frame_axis.displacement_increment is the angular setting of the axis at the end of the integration time for a given frame. If the individual frame values vary, then the value of _diffrn_scan_axis.displacement_increment will be representative of the ensemble of values of _diffrn_scan_frame_axis.displacement_increment (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_increment' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_axis.displacement_rstrt_incr _item_description.description ; The increment for each step for the specified axis in millimetres. In general, this will agree with _diffrn_scan_frame_axis.displacement_rstrt_incr. The sum of the values of _diffrn_scan_frame_axis.displacement, _diffrn_scan_frame_axis.displacement_increment and _diffrn_scan_frame_axis.displacement_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame relative to a given frame and should equal _diffrn_scan_frame_axis.displacement for this next frame. If the individual frame values vary, then the value of _diffrn_scan_axis.displacement_rstrt_incr will be representative of the ensemble of values of _diffrn_scan_frame_axis.displacement_rstrt_incr (e.g. the mean). ; _item.name '_diffrn_scan_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ ##################### # DIFFRN_SCAN_FRAME # ##################### save_DIFFRN_SCAN_FRAME _category.description ; Data items in the DIFFRN_SCAN_FRAME category describe the relationships of particular frames to scans. ; _category.id diffrn_scan_frame _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame.scan_id' '_diffrn_scan_frame.frame_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame.date _item_description.description ; The date and time of the start of the frame being scanned. ; _item.name '_diffrn_scan_frame.date' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code yyyy-mm-dd save_ save__diffrn_scan_frame.frame_id _item_description.description ; The value of this data item is the identifier of the frame being examined. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame.frame_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame.frame_number _item_description.description ; The value of this data item is the number of the frame within the scan, starting with 1. It is not necessarily the same as the value of _diffrn_scan_frame.frame_id, but it may be. ; _item.name '_diffrn_scan_frame.frame_number' _item.category_id diffrn_scan_frame _item.mandatory_code no _item_type.code int loop_ _item_range.maximum _item_range.minimum . 0 0 0 save_ save__diffrn_scan_frame.integration_time _item_description.description ; The time in seconds to integrate this step of the scan. This should be the precise time of integration of each particular frame. The value of this data item should be given explicitly for each frame and not inferred from the value of _diffrn_scan.integration_time. ; _item.name '_diffrn_scan_frame.integration_time' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code float _item_units.code 'seconds' loop_ _item_range.maximum _item_range.minimum . 0.0 save_ save__diffrn_scan_frame.scan_id _item_description.description ; The value of _diffrn_scan_frame.scan_id identifies the scan containing this frame. This item is a pointer to _diffrn_scan.id in the DIFFRN_SCAN category. ; _item.name '_diffrn_scan_frame.scan_id' _item.category_id diffrn_scan_frame _item.mandatory_code yes _item_type.code code save_ ########################## # DIFFRN_SCAN_FRAME_AXIS # ########################## save_DIFFRN_SCAN_FRAME_AXIS _category.description ; Data items in the DIFFRN_SCAN_FRAME_AXIS category describe the settings of axes for particular frames. Unspecified axes are assumed to be at their zero points. If, for any given frame, nonzero values apply for any of the data items in this category, those values should be given explicitly in this category and not simply inferred from values in DIFFRN_SCAN_AXIS. ; _category.id diffrn_scan_frame_axis _category.mandatory_code no loop_ _category_key.name '_diffrn_scan_frame_axis.frame_id' '_diffrn_scan_frame_axis.axis_id' loop_ _category_group.id 'inclusive_group' 'diffrn_group' save_ save__diffrn_scan_frame_axis.axis_id _item_description.description ; The value of this data item is the identifier of one of the axes for the frame for which settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id. This item is a pointer to _axis.id in the AXIS category. ; _item.name '_diffrn_scan_frame_axis.axis_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_scan_frame_axis.angle _item_description.description ; The setting of the specified axis in degrees for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.angle' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_increment _item_description.description ; The increment for this frame for the angular setting of the specified axis in degrees. The sum of the values of _diffrn_scan_frame_axis.angle and _diffrn_scan_frame_axis.angle_increment is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.angle_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.angle_rstrt_incr _item_description.description ; The increment after this frame for the angular setting of the specified axis in degrees. The sum of the values of _diffrn_scan_frame_axis.angle, _diffrn_scan_frame_axis.angle_increment and _diffrn_scan_frame_axis.angle_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame and should equal _diffrn_scan_frame_axis.angle for this next frame. ; _item.name '_diffrn_scan_frame_axis.angle_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'degrees' save_ save__diffrn_scan_frame_axis.displacement _item_description.description ; The setting of the specified axis in millimetres for this frame. This is the setting at the start of the integration time. ; _item.name '_diffrn_scan_frame_axis.displacement' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_increment _item_description.description ; The increment for this frame for the displacement setting of the specified axis in millimetres. The sum of the values of _diffrn_scan_frame_axis.displacement and _diffrn_scan_frame_axis.displacement_increment is the angular setting of the axis at the end of the integration time for this frame. ; _item.name '_diffrn_scan_frame_axis.displacement_increment' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.displacement_rstrt_incr _item_description.description ; The increment for this frame for the displacement setting of the specified axis in millimetres. The sum of the values of _diffrn_scan_frame_axis.displacement, _diffrn_scan_frame_axis.displacement_increment and _diffrn_scan_frame_axis.displacement_rstrt_incr is the angular setting of the axis at the start of the integration time for the next frame and should equal _diffrn_scan_frame_axis.displacement for this next frame. ; _item.name '_diffrn_scan_frame_axis.displacement_rstrt_incr' _item.category_id diffrn_scan_frame_axis _item.mandatory_code no _item_default.value 0.0 _item_type.code float _item_units.code 'millimetres' save_ save__diffrn_scan_frame_axis.frame_id _item_description.description ; The value of this data item is the identifier of the frame for which axis settings are being specified. Multiple axes may be specified for the same value of _diffrn_scan_frame.frame_id. This item is a pointer to _diffrn_data_frame.id in the DIFFRN_DATA_FRAME category. ; _item.name '_diffrn_scan_frame_axis.frame_id' _item.category_id diffrn_scan_frame_axis _item.mandatory_code yes _item_type.code code save_ ######################## DEPRECATED DATA ITEMS ######################## save__diffrn_detector_axis.id _item_description.description ; This data item is a pointer to _diffrn_detector.id in the DIFFRN_DETECTOR category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_detector_axis.id' _item.category_id diffrn_detector_axis _item.mandatory_code yes _item_type.code code save_ save__diffrn_measurement_axis.id _item_description.description ; This data item is a pointer to _diffrn_measurement.id in the DIFFRN_MEASUREMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_measurement_axis.id' _item.category_id diffrn_measurement_axis _item.mandatory_code yes _item_type.code code save_ ######################### DEPRECATED CATEGORY ######################### ##################### # DIFFRN_FRAME_DATA # ##################### save_DIFFRN_FRAME_DATA _category.description ; Data items in the DIFFRN_FRAME_DATA category record the details about each frame of data. The items in this category are now in the DIFFRN_DATA_FRAME category. The items in the DIFFRN_FRAME_DATA category are now deprecated. The items from this category are provided as aliases in the 1.0 dictionary or, in the case of _diffrn_frame_data.details, in the 1.4 dictionary. THESE ITEMS SHOULD NOT BE USED FOR NEW WORK. The items from the old category are provided in this dictionary for completeness but should not be used or cited. To avoid confusion, the example has been removed and the redundant parent-child links to other categories have been removed. ; _category.id diffrn_frame_data _category.mandatory_code no loop_ _category_key.name '_diffrn_frame_data.id' '_diffrn_frame_data.detector_element_id' loop_ _category_group.id 'inclusive_group' 'array_data_group' loop_ _category_examples.detail _category_examples.case # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - ; THE DIFFRN_FRAME_DATA category is deprecated and should not be used. ; ; # EXAMPLE REMOVED # ; # - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - save_ save__diffrn_frame_data.array_id _item_description.description ; This item is a pointer to _array_structure.id in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.array_id' _item.category_id diffrn_frame_data _item.mandatory_code yes _item_type.code code save_ save__diffrn_frame_data.binary_id _item_description.description ; This item is a pointer to _array_data.binary_id in the ARRAY_STRUCTURE category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.binary_id' _item.category_id diffrn_frame_data _item.mandatory_code implicit _item_type.code int save_ save__diffrn_frame_data.detector_element_id _item_description.description ; This item is a pointer to _diffrn_detector_element.id in the DIFFRN_DETECTOR_ELEMENT category. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.detector_element_id' _item.category_id diffrn_frame_data _item.mandatory_code yes _item_type.code code save_ save__diffrn_frame_data.id _item_description.description ; The value of _diffrn_frame_data.id must uniquely identify each complete frame of data. DEPRECATED -- DO NOT USE ; loop_ _item.name _item.category_id _item.mandatory_code '_diffrn_frame_data.id' diffrn_frame_data yes _item_type.code code save_ save__diffrn_frame_data.details _item_description.description ; The value of _diffrn_data_frame.details should give a description of special aspects of each frame of data. DEPRECATED -- DO NOT USE ; _item.name '_diffrn_frame_data.details' _item.category_id diffrn_frame_data _item.mandatory_code no _item_type.code text save_ ################ END DEPRECATED SECTION ########### #################### ## ITEM_TYPE_LIST ## #################### # # # The regular expressions defined here are not compliant # with the POSIX 1003.2 standard as they include the # '\n' and '\t' special characters. These regular expressions # have been tested using version 0.12 of Richard Stallman's # GNU regular expression library in POSIX mode. # In order to allow presentation of a regular expression # in a text field concatenate any line ending in a backslash # with the following line, after discarding the backslash. # # A formal definition of the '\n' and '\t' special characters # is most properly done in the DDL, but for completeness, please # note that '\n' is the line termination character ('newline') # and '\t' is the horizontal tab character. There is a formal # ambiguity in the use of '\n' for line termination, in that # the intention is that the equivalent machine/OS-dependent line # termination character sequence should be accepted as a match, e.g. # # '\r' (control-M) under MacOS # '\n' (control-J) under Unix # '\r\n' (control-M control-J) under DOS and MS Windows # loop_ _item_type_list.code _item_type_list.primitive_code _item_type_list.construct _item_type_list.detail code char '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words ... ; ucode uchar '[_,.;:"&<>()/\{}'`~!@#$%A-Za-z0-9*|+-]*' ; code item types/single words (case insensitive) ... ; line char '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; char item types / multi-word items ... ; uline uchar '[][ \t_(),.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; char item types / multi-word items (case insensitive)... ; text char '[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*' ; text item types / multi-line text ... ; binary char ;\n--CIF-BINARY-FORMAT-SECTION--\n\ [][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*\ \n--CIF-BINARY-FORMAT-SECTION---- ; ; binary items are presented as MIME-like ascii-encoded sections in an imgCIF. In a CBF, raw octet streams are used to convey the same information. ; int numb '-?[0-9]+' ; int item types are the subset of numbers that are the negative or positive integers. ; float numb '-?(([0-9]+)[.]?|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?' ; float item types are the subset of numbers that are the floating point numbers. ; any char '.*' ; A catch all for items that may take any form... ; yyyy-mm-dd char ;\ [0-9]?[0-9]?[0-9][0-9]-[0-9]?[0-9]-[0-9]?[0-9]\ ((T[0-2][0-9](:[0-5][0-9](:[0-5][0-9](.[0-9]+)?)?)?)?\ ([+-][0-5][0-9]:[0-5][0-9]))? ; ; Standard format for CIF date and time strings (see http://www.iucr.org/iucr-top/cif/spec/datetime.html), consisting of a yyyy-mm-dd date optionally followed by the character 'T' followed by a 24-hour clock time, optionally followed by a signed time-zone offset. The IUCr standard has been extended to allow for an optional decimal fraction on the seconds of time. Time is local time if no time-zone offset is given. Note that this type extends the mmCIF yyyy-mm-dd type but does not conform to the mmCIF yyyy-mm-dd:hh:mm type that uses a ':' in place if the 'T' specified by the IUCr standard. For reading, both forms should be accepted, but for writing, only the IUCr form should be used. For maximal compatibility, the special time zone indicator 'Z' (for 'zulu') should be accepted on reading in place of '+00:00' for GMT. ; ##################### ## ITEM_UNITS_LIST ## ##################### loop_ _item_units_list.code _item_units_list.detail # 'metres' 'metres' 'centimetres' 'centimetres (metres * 10^( -2)^)' 'millimetres' 'millimetres (metres * 10^( -3)^)' 'nanometres' 'nanometres (metres * 10^( -9)^)' 'angstroms' '\%Angstroms (metres * 10^(-10)^)' 'picometres' 'picometres (metres * 10^(-12)^)' 'femtometres' 'femtometres (metres * 10^(-15)^)' # 'reciprocal_metres' 'reciprocal metres (metres^(-1)^)' 'reciprocal_centimetres' 'reciprocal centimetres ((metres * 10^( -2)^)^(-1)^)' 'reciprocal_millimetres' 'reciprocal millimetres ((metres * 10^( -3)^)^(-1)^)' 'reciprocal_nanometres' 'reciprocal nanometres ((metres * 10^( -9)^)^(-1)^)' 'reciprocal_angstroms' 'reciprocal \%Angstroms ((metres * 10^(-10)^)^(-1)^)' 'reciprocal_picometres' 'reciprocal picometres ((metres * 10^(-12)^)^(-1)^)' # 'nanometres_squared' 'nanometres squared (metres * 10^( -9)^)^2^' 'angstroms_squared' '\%Angstroms squared (metres * 10^(-10)^)^2^' '8pi2_angstroms_squared' '8\p^2^ * \%Angstroms squared (metres * 10^(-10)^)^2^' 'picometres_squared' 'picometres squared (metres * 10^(-12)^)^2^' # 'nanometres_cubed' 'nanometres cubed (metres * 10^( -9)^)^3^' 'angstroms_cubed' '\%Angstroms cubed (metres * 10^(-10)^)^3^' 'picometres_cubed' 'picometres cubed (metres * 10^(-12)^)^3^' # 'kilopascals' 'kilopascals' 'gigapascals' 'gigapascals' # 'hours' 'hours' 'minutes' 'minutes' 'seconds' 'seconds' 'microseconds' 'microseconds' # 'degrees' 'degrees (of arc)' 'degrees_squared' 'degrees (of arc) squared' # 'degrees_per_minute' 'degrees (of arc) per minute' # 'celsius' 'degrees (of temperature) Celsius' 'kelvins' 'degrees (of temperature) Kelvin' # 'counts' 'counts' 'counts_per_photon' 'counts per photon' # 'electrons' 'electrons' # 'electrons_squared' 'electrons squared' # 'electrons_per_nanometres_cubed' ; electrons per nanometres cubed (electrons/(metres * 10^( -9)^)^(-3)^) ; 'electrons_per_angstroms_cubed' ; electrons per \%Angstroms cubed (electrons/(metres * 10^(-10)^)^(-3)^) ; 'electrons_per_picometres_cubed' ; electrons per picometres cubed (electrons/(metres * 10^(-12)^)^(-3)^) ; 'kilowatts' 'kilowatts' 'milliamperes' 'milliamperes' 'kilovolts' 'kilovolts' # 'pixels_per_element' '(image) pixels per (array) element' # 'arbitrary' ; arbitrary system of units. ; # loop_ _item_units_conversion.from_code _item_units_conversion.to_code _item_units_conversion.operator _item_units_conversion.factor ### 'metres' 'centimetres' '*' 1.0E+02 'metres' 'millimetres' '*' 1.0E+03 'metres' 'nanometres' '*' 1.0E+09 'metres' 'angstroms' '*' 1.0E+10 'metres' 'picometres' '*' 1.0E+12 'metres' 'femtometres' '*' 1.0E+15 # 'centimetres' 'metres' '*' 1.0E-02 'centimetres' 'millimetres' '*' 1.0E+01 'centimetres' 'nanometres' '*' 1.0E+07 'centimetres' 'angstroms' '*' 1.0E+08 'centimetres' 'picometres' '*' 1.0E+10 'centimetres' 'femtometres' '*' 1.0E+13 # 'millimetres' 'metres' '*' 1.0E-03 'millimetres' 'centimetres' '*' 1.0E-01 'millimetres' 'nanometres' '*' 1.0E+06 'millimetres' 'angstroms' '*' 1.0E+07 'millimetres' 'picometres' '*' 1.0E+09 'millimetres' 'femtometres' '*' 1.0E+12 # 'nanometres' 'metres' '*' 1.0E-09 'nanometres' 'centimetres' '*' 1.0E-07 'nanometres' 'millimetres' '*' 1.0E-06 'nanometres' 'angstroms' '*' 1.0E+01 'nanometres' 'picometres' '*' 1.0E+03 'nanometres' 'femtometres' '*' 1.0E+06 # 'angstroms' 'metres' '*' 1.0E-10 'angstroms' 'centimetres' '*' 1.0E-08 'angstroms' 'millimetres' '*' 1.0E-07 'angstroms' 'nanometres' '*' 1.0E-01 'angstroms' 'picometres' '*' 1.0E+02 'angstroms' 'femtometres' '*' 1.0E+05 # 'picometres' 'metres' '*' 1.0E-12 'picometres' 'centimetres' '*' 1.0E-10 'picometres' 'millimetres' '*' 1.0E-09 'picometres' 'nanometres' '*' 1.0E-03 'picometres' 'angstroms' '*' 1.0E-02 'picometres' 'femtometres' '*' 1.0E+03 # 'femtometres' 'metres' '*' 1.0E-15 'femtometres' 'centimetres' '*' 1.0E-13 'femtometres' 'millimetres' '*' 1.0E-12 'femtometres' 'nanometres' '*' 1.0E-06 'femtometres' 'angstroms' '*' 1.0E-05 'femtometres' 'picometres' '*' 1.0E-03 ### 'reciprocal_centimetres' 'reciprocal_metres' '*' 1.0E+02 'reciprocal_centimetres' 'reciprocal_millimetres' '*' 1.0E-01 'reciprocal_centimetres' 'reciprocal_nanometres' '*' 1.0E-07 'reciprocal_centimetres' 'reciprocal_angstroms' '*' 1.0E-08 'reciprocal_centimetres' 'reciprocal_picometres' '*' 1.0E-10 # 'reciprocal_millimetres' 'reciprocal_metres' '*' 1.0E+03 'reciprocal_millimetres' 'reciprocal_centimetres' '*' 1.0E+01 'reciprocal_millimetres' 'reciprocal_nanometres' '*' 1.0E-06 'reciprocal_millimetres' 'reciprocal_angstroms' '*' 1.0E-07 'reciprocal_millimetres' 'reciprocal_picometres' '*' 1.0E-09 # 'reciprocal_nanometres' 'reciprocal_metres' '*' 1.0E+09 'reciprocal_nanometres' 'reciprocal_centimetres' '*' 1.0E+07 'reciprocal_nanometres' 'reciprocal_millimetres' '*' 1.0E+06 'reciprocal_nanometres' 'reciprocal_angstroms' '*' 1.0E-01 'reciprocal_nanometres' 'reciprocal_picometres' '*' 1.0E-03 # 'reciprocal_angstroms' 'reciprocal_metres' '*' 1.0E+10 'reciprocal_angstroms' 'reciprocal_centimetres' '*' 1.0E+08 'reciprocal_angstroms' 'reciprocal_millimetres' '*' 1.0E+07 'reciprocal_angstroms' 'reciprocal_nanometres' '*' 1.0E+01 'reciprocal_angstroms' 'reciprocal_picometres' '*' 1.0E-02 # 'reciprocal_picometres' 'reciprocal_metres' '*' 1.0E+12 'reciprocal_picometres' 'reciprocal_centimetres' '*' 1.0E+10 'reciprocal_picometres' 'reciprocal_millimetres' '*' 1.0E+09 'reciprocal_picometres' 'reciprocal_nanometres' '*' 1.0E+03 'reciprocal_picometres' 'reciprocal_angstroms' '*' 1.0E+01 ### 'nanometres_squared' 'angstroms_squared' '*' 1.0E+02 'nanometres_squared' 'picometres_squared' '*' 1.0E+06 # 'angstroms_squared' 'nanometres_squared' '*' 1.0E-02 'angstroms_squared' 'picometres_squared' '*' 1.0E+04 'angstroms_squared' '8pi2_angstroms_squared' '*' 78.9568 # 'picometres_squared' 'nanometres_squared' '*' 1.0E-06 'picometres_squared' 'angstroms_squared' '*' 1.0E-04 ### 'nanometres_cubed' 'angstroms_cubed' '*' 1.0E+03 'nanometres_cubed' 'picometres_cubed' '*' 1.0E+09 # 'angstroms_cubed' 'nanometres_cubed' '*' 1.0E-03 'angstroms_cubed' 'picometres_cubed' '*' 1.0E+06 # 'picometres_cubed' 'nanometres_cubed' '*' 1.0E-09 'picometres_cubed' 'angstroms_cubed' '*' 1.0E-06 ### 'kilopascals' 'gigapascals' '*' 1.0E-06 'gigapascals' 'kilopascals' '*' 1.0E+06 ### 'hours' 'minutes' '*' 6.0E+01 'hours' 'seconds' '*' 3.6E+03 'hours' 'microseconds' '*' 3.6E+09 # 'minutes' 'hours' '/' 6.0E+01 'minutes' 'seconds' '*' 6.0E+01 'minutes' 'microseconds' '*' 6.0E+07 # 'seconds' 'hours' '/' 3.6E+03 'seconds' 'minutes' '/' 6.0E+01 'seconds' 'microseconds' '*' 1.0E+06 # 'microseconds' 'hours' '/' 3.6E+09 'microseconds' 'minutes' '/' 6.0E+07 'microseconds' 'seconds' '/' 1.0E+06 ### 'celsius' 'kelvins' '-' 273.0 'kelvins' 'celsius' '+' 273.0 ### 'electrons_per_nanometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E+03 'electrons_per_nanometres_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+09 # 'electrons_per_angstroms_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-03 'electrons_per_angstroms_cubed' 'electrons_per_picometres_cubed' '*' 1.0E+06 # 'electrons_per_picometres_cubed' 'electrons_per_nanometres_cubed' '*' 1.0E-09 'electrons_per_picometres_cubed' 'electrons_per_angstroms_cubed' '*' 1.0E-06 ### ######################## ## DICTIONARY_HISTORY ## ######################## loop_ _dictionary_history.version _dictionary_history.update _dictionary_history.revision 1.4 2005-07-04 ; This is a change to reintegrate all changes made in the course of publication of ITVG, by the RCSB from April 2005 through August 2008 and changes for the 2006 imgCIF workshop in Hawaii. 2006-07-04 Consolidated changes for the 2006 imgCIF workshop (edited by HJB) + Correct type of '_array_structure_list.direction' from 'int' to 'code'. + Added new data items suggested by CN '_diffrn_data_frame.details' '_array_intensities.pixel_fast_bin_size', '_array_intensities.pixel_slow_bin_size and '_array_intensities.pixel_binning_method + Added deprecated item for completeness '_diffrn_frame_data.details' + Added entry for missing item in contents list '_array_structure_list_axis.displacement' + Added new MIME type X-BASE32K based on work by VL, KM, GD, HJB + Correct description of MIME boundary delimiter to start in column 1. + General cleanup of text fields to conform to changes for ITVG by removing empty lines at start and finish of text field. + Amend example for ARRAY_INTENSITIES to include binning. + Add local copy of type specification (as 'code') for all children of '_diffrn.id'. + For consistency, change all references to 'pi' to '\p' and all references to 'Angstroms' to '\%Angstroms'. + Clean up all powers to use IUCr convention of '^power^', as in '10^3^' for '10**3'. + Update 'yyyy-mm-dd' type regex to allow truncation from the right and improve comments to explain handling of related mmCIF 'yyyy-mm-dd:hh:mm' type, and use of 'Z' for GMT time zone. 2005-03-08 and 2004-08-08 fixed cases where _item_units.code used instead of _item_type.code (JDW) 2004-04-15 fixed item ordering in _diffrn_measurement_axis.measurement_id added sub_category 'vector' (JDW) ; 1.3.2 2005-06-25 ; 2005-06-25 ITEM_TYPE_LIST: code, ucode, line, uline regexps updated to those of current mmCIF; float modified by allowing integers terminated by a point as valid. The 'time' part of yyyy-mm-dd types made optional in the regexp. (BM) 2005-06-17 Minor corrections as for proofs for IT G Chapter 4.6 (NJA) 2005-02-21 Minor corrections to spelling and punctuation (NJA) 2005-01-08 Changes as per Nicola Ashcroft. + Updated example 1 for DIFFRN_MEASUREMENT to agree with mmCIF. + Spelled out "micrometres" for "um" and "millimetres" for "mm". + Removed phrase "which may be stored" from ARRAY_STRUCTURE description. + Removed unused 'byte-offsets' compressions and updated cites to ITVG for '_array_structure.compression_type'. (HJB) ; 1.3.1 2003-08-13 ; Changes as per Frances C. Bernstein. + Identify initials. + Adopt British spelling for centre in text. + Set \p and \%Angstrom and powers. + Clean up commas and unclear wordings. + Clean up tenses in history. Changes as per Gotzon Madariaga. + Fix the ARRAY_DATA example to align '_array_data.binary_id' and X-Binary-ID. + Add a range to '_array_intensities.gain_esd'. + In the example of DIFFRN_DETECTOR_ELEMENT, '_diffrn_detector_element.id' and '_diffrn_detector_element.detector_id' interchanged. + Fix typos for direction, detector and axes. + Clarify description of polarisation. + Clarify axes in '_diffrn_detector_element.center[1]' '_diffrn_detector_element.center[2]'. + Add local item types for items that are pointers. (HJB) ; 1.3.0 2003-07-24 ; Changes as per Brian McMahon. + Consistently quote tags embedded in text. + Clean up introductory comments. + Adjust line lengths to fit in 80 character window. + Fix several descriptions in AXIS category which referred to '_axis.type' instead of the current item. + Fix erroneous use of deprecated item '_diffrn_detector_axis.id' in examples for DIFFRN_SCAN_AXIS. + Add deprecated items '_diffrn_detector_axis.id' and '_diffrn_measurement_axis.id'. (HJB) ; 1.2.4 2003-07-14 ; Changes as per I. David Brown. + Enhance descriptions in DIFFRN_SCAN_AXIS to make them less dependent on the descriptions in DIFFRN_SCAN_FRAME_AXIS. + Provide a copy of the deprecated DIFFRN_FRAME_DATA category for completeness. (HJB) ; 1.2.3 2003-07-03 ; Cleanup to conform to ITVG. + Correct sign error in ..._cubed units. + Correct '_diffrn_radiation.polarisn_norm' range. (HJB) ; 1.2.2 2003-03-10 ; Correction of typos in various DIFFRN_SCAN_AXIS descriptions. (HJB) ; 1.2.1 2003-02-22 ; Correction of ATOM_ for ARRAY_ typos in various descriptions. (HJB) ; 1.2 2003-02-07 ; Corrections to encodings (remove extraneous hyphens) remove extraneous underscore in '_array_structure.encoding_type' enumeration. Correct typos in items units list. (HJB) ; 1.1.3 2001-04-19 ; Another typo corrections by Wilfred Li, and cleanup by HJB. ; 1.1.2 2001-03-06 ; Several typo corrections by Wilfred Li. ; 1.1.1 2001-02-16 ; Several typo corrections by JW. ; 1.1 2001-02-06 ; Draft resulting from discussions on header for use at NSLS. (HJB) + Change DIFFRN_FRAME_DATA to DIFFRN_DATA_FRAME. + Change '_diffrn_detector_axis.id' to '_diffrn_detector_axis.detector_id'. + Add '_diffrn_measurement_axis.measurement_device' and change '_diffrn_measurement_axis.id' to '_diffrn_measurement_axis.measurement_id'. + Add '_diffrn_radiation.div_x_source', '_diffrn_radiation.div_y_source', '_diffrn_radiation.div_x_y_source', '_diffrn_radiation.polarizn_source_norm', '_diffrn_radiation.polarizn_source_ratio', '_diffrn_scan.date_end', '_diffrn_scan.date_start', '_diffrn_scan_axis.angle_rstrt_incr', '_diffrn_scan_axis.displacement_rstrt_incr', '_diffrn_scan_frame_axis.angle_increment', '_diffrn_scan_frame_axis.angle_rstrt_incr', '_diffrn_scan_frame_axis.displacement', '_diffrn_scan_frame_axis.displacement_increment',and '_diffrn_scan_frame_axis.displacement_rstrt_incr'. + Add '_diffrn_measurement.device' to category key. + Update yyyy-mm-dd to allow optional time with fractional seconds for time stamps. + Fix typos caught by RS. + Add ARRAY_STRUCTURE_LIST_AXIS category, and use concept of axis sets to allow for coupled axes, as in spiral scans. + Add examples for fairly complete headers thanks to R. Sweet and P. Ellis. ; 1.0 2000-12-21 ; Release version - few typos and tidying up. (BM & HJB) + Move ITEM_TYPE_LIST, ITEM_UNITS_LIST and DICTIONARY_HISTORY to end of dictionary. + Alphabetize dictionary. ; 0.7.1 2000-09-29 ; Cleanup fixes. (JW) + Correct spelling of diffrn_measurement_axis in '_axis.id' + Correct ordering of uses of '_item.mandatory_code' and '_item_default.value'. ; 0.7.0 2000-09-09 ; Respond to comments by I. David Brown. (HJB) + Add further comments on '\n' and '\t'. + Update ITEM_UNITS_LIST by taking section from mmCIF dictionary and adding metres. Change 'meter' to 'metre' throughout. + Add missing enumerations to '_array_structure.compression_type' and make 'none' the default. + Remove parent-child relationship between '_array_structure_list.index' and '_array_structure_list.precedence'. + Improve alphabetization. + Fix '_array_intensities_gain.esd' related function. + Improve comments in AXIS. + Fix DIFFRN_FRAME_DATA example. + Remove erroneous DIFFRN_MEASUREMENT example. + Add '_diffrn_measurement_axis.id' to the category key. ; 0.6.0 1999-01-14 ; Remove redundant information for ENC_NONE data. (HJB) + After the D5 remove binary section identifier, size and compression type. + Add Control-L to header. ; 0.5.1 1999-01-03 ; Cleanup of typos and syntax errors. (HJB) + Cleanup example details for DIFFRN_SCAN category. + Add missing quote marks for '_diffrn_scan.id' definition. ; 0.5 1999-01-01 ; Modifications for axis definitions and reduction of binary header. (HJB) + Restore '_diffrn_detector.diffrn_id' to DIFFRN_DETECTOR KEY. + Add AXIS category. + Bring in complete DIFFRN_DETECTOR and DIFFRN_MEASUREMENT categories from cif_mm.dic for clarity. + Change '_array_structure.encoding_type' from type code to uline and added X-Binary-Element-Type to MIME header. + Add detector beam centre '_diffrn_detector_element.center[1]' and '_diffrn_detector_element.center[2]'. + Correct item name of '_diffrn_refln.frame_id'. + Replace reference to '_array_intensities.undefined' by '_array_intensities.undefined_value'. + Replace references to '_array_intensity.scaling' with '_array_intensities.scaling'. + Add DIFFRN_SCAN... categories. ; 0.4 1998-08-11 ; Modifications to the 0.3 imgCIF draft. (HJB) + Reflow comment lines over 80 characters and corrected typos. + Update examples and descriptions of MIME encoded data. + Change name to cbfext98.dic. ; 0.3 1998-07-04 ; Modifications for imgCIF. (HJB) + Add binary type, which is a text field containing a variant on MIME encoded data. + Change type of '_array_data.data' to binary and specify internal structure of raw binary data. + Add '_array_data.binary_id', and make '_diffrn_frame_data.binary_id' and '_array_intensities.binary_id' into pointers to this item. ; 0.2 1997-12-02 ; Modifications to the CBF draft. (JW) + Add category hierarchy for describing frame data developed from discussions at the BNL imgCIF Workshop Oct 1997. The following changes are made in implementing the workshop draft. Category DIFFRN_ARRAY_DATA is renamed to DIFFRN_FRAME_DATA. Category DIFFRN_FRAME_TYPE is renamed to DIFFRN_DETECTOR_ELEMENT. The parent item for '_diffrn_frame_data.array_id' is changed from '_array_structure_list.array_id' to '_array_structure.id'. Item '_diffrn_detector.array_id' is deleted. + Add data item '_diffrn_frame_data.binary_id' to identify data groups within a binary section. The formal identification of the binary section is still fuzzy. ; 0.1 1997-01-24 ; First draft of this dictionary in DDL 2.1 compliant format by John Westbrook (JW). This version is adapted from the Crystallographic Binary File (CBF) Format Draft Proposal provided by Andy Hammersley (AH). Modifications to the CBF draft. (JW) + In this version the array description has been cast in the categories ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. These categories have been generalized to describe array data of arbitrary dimension. + Array data in this description are contained in the category ARRAY_DATA. This departs from the CBF notion of data existing in some special comment. In this description, data are handled as an ordinary data item encapsulated in a character data type. Although data this manner deviates from CIF conventions, it does not violate any DDL 2.1 rules. DDL 2.1 regular expressions can be used to define the binary representation which will permit some level of data validation. In this version, the placeholder type code "any" has been used. This translates to a regular expression which will match any pattern. It should be noted that DDL 2.1 already supports array data objects although these have not been used in the current mmCIF dictionary. It may be possible to use the DDL 2.1 ITEM_STRUCTURE and ITEM_STRUCTURE_LIST categories to provide the information that is carried in by the ARRAY_STRUCTURE and ARRAY_STRUCTURE_LIST. By moving the array structure to the DDL level it would be possible to define an array type as well as a regular expression defining the data format. + Multiple array sections can be properly handled within a single datablock. ; #-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof-eof ./CBFlib-0.9.2.2/doc/cif_img_1.4_4Jul06_draft.pdf0000644000076500007650000120430411603702115017245 0ustar yayayaya%PDF-1.4 %âãÏÓ 1 0 obj 65 endobj 2 0 obj << /Length 1 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»år¹äÍB–È endstream endobj 3 0 obj << /Type /Page /Parent 4 0 R /Resources 5 0 R /Contents 2 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 4 0 obj << /Type /Pages /Parent 222 0 R /Count 6 /Kids [ 3 0 R 21 0 R 30 0 R 37 0 R 44 0 R 51 0 R ] >> endobj 5 0 obj << /ProcSet [ /PDF ] /XObject << /Fm1 6 0 R >> >> endobj 6 0 obj << /Length 7 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 8 0 R /Filter /FlateDecode >> stream xÚ­}kw·‘èwü Þì%+voÀ¹9çJ²´Qù%f³>ë{|FÃ&9ñpFžJÖþú­BÏèîÂtƒ´Ï±h±Q.Ôõøõâû‹_/^^]pQyË/jøwÿ£Pu%¿°ÒWÂê‹«û‹?¾áüþâêæâ™ªLõû‹«±×WÄzŠxù³Åýí«·opÕE¼ŠE«dí+éu²ìz3»ÙõVÅï’°W+%‹W}:³ÂVµóÉ{šÍv±^ýžå–9UqŸ.㕊_Uâý¤ðã·ºª¥½°ÜVRÛ‘âˆÈ—ÑbWq-ÃûÂOŒ;QI¥â¥Ï~ì½ì"~™—•“ÑöìEv¨ye¼K^Qe¿GÔðdnê»ü;8~†gùw¤+låuúŽ¿DäÖAÔ…ºrB$Ï¿È VHQ žÂG?!༽± ^³ÏyYdžþëîó,z^ËJÔé)üƒ¯=üy„Ïðù÷¹ç ЭKñó÷Ü~Œ¯ŒñùýÇðƹrÉ~ò„*¯:ü=ÎÙv½€¸ÑV6ž/n @[‚.û ^èÞѺ€ç”²‡ç/æ÷ø÷€qçˆî/Àsžÿbyñ|Ø!²ƒmJs³÷?¯…×µ:õÂKƒÇ”}Ýñº-à©ÕV$¯‹ÃÓ×bå"~ÿºèë<Èp.b¤þñ< 㯿~÷îÝ?ößÎ5xbÜ -ÿzV”¬mü¹A°öýA&Vw»ûe•£W®‚Óãì}³ºÎQ,øUâxÉ|}߬vÛ,Íntú&Yçi^g¸c{â²½\þ¿ÅÃ|“*µ©—‡µ­!<#PÀÂG-¸ÍhS¾®;(~~¾Ø-V·¹]™ìQG_´»k²º\Xd è5ŸrÛ xÎ&Ï·b®ÊŠ`0ê@fK`–ºÕ@¯f»æv½ù’[åyÅ%È hÙí&«TAΞ,X?|[¬KÅ‘ïFmf›ÍìKŸ¿À>P‡%l’(‰6 ˆ”¨Ï÷`‚>Ÿífý·9 fw|ßÑÅhY"€)Dü¥€LÀN9le/e²Ï-{ÒàÇ*8êø5ëÍ¢Étlx´£E»»Ù.ÇMð9hfÇK®›í|³ø38„@7;9ïô‡¨J×ÈTÉ'áIU#$K­+]óö5¿‘Êz¤f~ùþÁ1ÄĆԠ­ð÷ñûˆÃ nºfÔáºÃ6áp]òžp¸íF®L–P‡›˜ÈíöÖs'+m%ŒI¾§ÙŽ8W ’Ik¹7Âo2¾GˆàÁ×Ç+n6«>—ƒ%=÷Ï•K$àÌB¸8B¼ÅˆI6YrŽX •¢""ŠË…’ÉçäáÈå||žS³›-–ÛœöÐ`Áë뛽ôxu烲s´mz< ýôW ØÖ¼C?³ùeît F¯ö­ŽÞe}DÆA{á’%YI¦¨Eô<{öÛÇf³@­êS÷o€Êk£ûbÎÈÃíÐwo½ÁõÁåèœÕ5þ>ú-]eë®®/.kû5 X;HÐ`qjøSƒ‘fð{â°Ç‹~8F'fx-$Á:Nâ)?AåਃµxXS, Ð%å`¾àtÞýõÆó >öñPF=ïq;ÉóWz5è=eûð‰ý€]káà5¸òž̴½#òud7 ÉDSYðý¢ÅÏ»æ~›c!ØŸé’,ÿ€qæp¼ ¨ Ã‚ðÍS#‹ŸgÈ~¤W ¥ S ¨ãYþMw¯,=ÔˆàÅÕ‹œ¹híÒïšçÁ%¼×³xÉC_ÛªÎ[f›æŒ¬öl÷Du`Cž~Çz*auy–ì˜rçàëä( ®.¢çoÚ Á6¾»CÄÏgõY])éâç¬W¸5à —°ÄÍt A+¿$f—Á+ˆ t¸¢%5}“°7©Ó7e#™ZVÔG_2±°€óxÁ0õ²“†vI¤C¼){“óÍÖÆ¼s| Ó !¶ ú|̈uN†eºîÄÆï¯~øÇ««üð:'£e¦»ã/BÅ c4.VóåÃvñ©ù¹5~¹„ƒz®–•‘?ø32ÉϱéÌV<|zÿP†ðÅúøŠVÄ‹—ü’y>$–€­?ßd¾Ç”T`1ÄÏ9E÷-¬ý t¿3,D$}ÂgÕþ¸ˆdën€y¥ÁàÓ•ò­aCø°XÍ61ˆSˆ÷p…p'Ë0XM 2„ô§¿:ÚMÈ_¬ËÑ d¹±®ý}üš×¿Íî?.IÅÎàåàMêxù3N V'X&ñפ8l L&Ë[R½J/ÊÒ­®0/ -Ø‚U&¿ÿVjCÞ¢fáÉ’íÝúóЖXkŒ0—Mºb÷y1“€¤ÜqSA¼¶@/Ñ<¼"Rx¬¿LáÒ–ë9ýç*§Yüü/IÐ }<%èœ[Cl‚Ã~Tz?Ii6äA !Â{r;zC ”µÉãë}ÌBßîS}žÑt'ЦïœÀ|}ÿqCïÈÁŠ„RÙ³f»Ml‡t¦ð !”Z—(ú<­ëp|Î:È °G÷ϲ{õòÍ@ÐÆWì‘ÜžÈÝÄÁ `~nîÕ‹o¾ýæí«'¿ˆ [Y¶ñª<’ÑÅu’³xEÓ½;î²°«°ÉKfK ôìîîiz]jeºµÙꚦ—È“çi±’C^Ãééz3ÁŽK7Ûfµ .vX"”Yú™ @¬’ µdˆ ]Q§HýmvÝÌ÷³%)¥Œ)°^ Æ ;4ŒFW,^q•Ù–ÃKr—¾¡;¤øsÒ+‘¬ ÅOÄ JÏÙšW®æÉÓw3z3 A«ÓÍÌæ»fCë"Éád烅ú üGg¸H‰¤´æ8H«pË?¾ËnLÈ:èž3‰UÌVCX.V M®ª²;-`Ïî›Ù*Çp`Ò¢<¢!%“x×—~‘¾3j2|9Oû6£ÄÀ³ã2=½ùúayMëU iqÕ¡¨O´)w`9P— 7÷y }Ö`oi…Òò¸€‚ú6KPÝ1£’×ÜÄ™@¬Ãu!áÁ%ϯç»Ù’>pÌÄ“Ž%+2z‚ƒ“áeòüŒ¯ÃgüÜ严?£K·JTΥϟ¥n1÷çˆ+vN¦qp"0:¿dÛÌ×±2b]åÜ‘, e&¼{0>âí Œ¢IVOîfI(ャéO Á*ŸœsÎÊÁ »H¿%Í@¶õÐlæþ^³ƒÌéq1vGŽ/S:C¢ÖÃý‡†ûàŒOÆK’;›ŽwfAxƒ?þáË.'-1΀&ÞqKcT]æÑ ðf6Ï8C\]™<—q…Dð®÷ObûœccPTÚ¤ŸzM›“šW]<þ”ýPL¼B'"ÚÎ.ãïb %}Ã|¶mHâÇ!Sô R(‡~úýsšêj áÙdáç»E†…ªLr,s$7é¾€¨W´BÃ[¡ -È Y)b›_›¬æDC2¡»--TÀþôéö›Åí]FÕú¨b 6× ¸¸Cx¿]ž5lAIùº÷tŒá6ÊpV$‹®·‹]Ž%†ÂKZ?69-hBê[üŠ>»Åþ˜ ù`É–2šL™I•l'«É?eúÅÀn´ê@þZ¥ûÉp3Ø.N°øéŒmnÑ ä ì“Þˆ°¸ö219cÂ6?°0ÄÒÝß.>59#£,ñy±¼òCqšï€0=z„X˜éu“ãaÑòptº´VºÀ€‰µ)>Á¤kv&ÆD‚Ú¥ä ^yFbcv¤·&9ãÙYU\×AG¥äφ"&N¢s=ý<lôÖ‚I=žÙºƒ³ÕèäD”Í ©«Ô-H•M×åXÏ“.@eóH³¼?tç1Ñ.dgìÞVËΗÐÎTp7eº¯t86ŽJ6Ú jš4ÚefUqžîHIÁinÆœTg1ªž-ª&ÃÍ"\sÆ+rñRS#{Gñaq{™¦ w9Z†‹Î„¦è=a}›K¿b–‘¾u<¢§W­RÑÂJ‘žÝ‹%ˆ½Õl²lù…æn¤_“"ìyF?+›åiªÇÚX.†%o±¬PÏXñ©yòtÎÇ[¤öÚ³øù¬¬Ç;'‘€ßó]õ7½…o66ýŠƒÿ?lns t%:_ò)—£¡Uõa;À:#Lf‰ßðD±Y?¾ª;ÈÍ ‡9¼6An6ËKc"âç“|„.ç{-ÓÇóÒƒa0VÚô“¹Š&VhµŠO奰‘ É ñ+*ÚØÖ¾¿%¨åb·[6(@³#çž¹. dë}Ž{Î83><ÏÎÞ áµt*yÁ/änœB{:ÝÎ]&í1Î/Òí̲†±ã pÄ×}³ÝÎhÂÅB|¬¸ˆVeTŒ‡Ì8?g;á}Œ{Z)`ÓZ'Ï7Û]Nk3¼$ô`ÝÇkv™kHLôLžÓ0äižnÿ®™g¸¼C‘¥…X˜`n$¿£ïî0˸9‹Õ®!¥¤@CH¤{»Yì¾d,oâ½1¹åŒ]8^mDï rÞ3èÔ²7îE/E‹³®h,a±º}~LЇ­ðdIþʸVxÑÏâ¿d¶6ÝÐbKÓ?¦‚+™ìq¿XÎrÑW8ei’5ϳ¡$Ì'N>—&9å€ÛSä<ì2¬hÒ§·¹€¦t¹;løn–;¹?>8x9[Ÿ¿žÅ*¤ÎYG h\oÒ³{‘M Ð^&O¿úÛë¯i“R¨P5/ n}ÙQßjžâ÷Ì­/ÞgÖ§—°3÷·ÁM_ð’æf‡Ü–¢çýk£Î2³³Áµ{iVóõuÎ¥wÑ ¥‹ºë%Ö90Y“§¿YïšüÕ¤+,ZЩcèÇ’šyÉ‚Ì% HTïdòüvñ?ïUq éÅÏç Ë:u½ý°Œú3éöO y`7ÖV–›äù&“‚ù4ÚÄÛgÏ2²˜Ôé×6täëòîl>£žj,ر ÁÝäB=?Ö¦»‰J 2ÜŒ«”i[¦pË»érËõúãϹ¬Áýêp{­{ùqý »CºëBÀ¬!éÎgØe@p̦=ënjéa5(E¹D-îg·ÍÏ<“ʈ\ça»ûU¬›XG`»aå>þ§óhEù$÷¥Ã——¯Þ¾¹|ùö›?üxùæÛÞ½¸º|ÿúÕÕÛo¿¹¼<¾Øs)ƒP_ƒÍµÚ]^}ùØ|•Á+r>¶­‰×Î>~\.æ3,àùcˆ ^nw›fvŸû‡=T nåp7¾ú´oGðçßýv óçc’ÑïF| –ë[•~Ìf¶Úo\¾Þ ä¯2™¥ÁÌ¿,ô_—/Aøs“I-=¾åÝaU ÐË÷ ¿ÊQ ²ˆð,^,½°\˜t£°qOßøöë¯r©ÄÀPÎ$+ùy.À@´Þ÷˜;`öÝ×:ûaûµ+'<ˆíÕ__¯?½øË/÷¿|ý¯ïÿ~ûÏííŸÿ<âC9^~µ‚îßr©Ç¯pÝáù¶1W“$.Q©Ú¢ŽVtøó 㥄s>Y‡—µ9Ìá;ÎY¼¤~žY€¡IÝýwÐÇŒ·øÑ-YoÒë€î§„ž¡áÝiMUUâ¼c ä+c[)ùoç“{SÙº•wQÿ7s,wÃŽcñ 0ƒë—Ž×¹Si‰/]Õþ“;<(ØÔUØÿÂúá—eNc»²·ìòMîÀ³P¡¹â¤Mîk„Њ±rôªVB›‹xPDæ«l}e÷ªÂgµ4F$Ü^ÏfuÚ­Æ ¿jXö‰ËDÝ^Ú·*^ŒPññ*1#Øßg¯,ÿt^àbN¹ßËç‘*žÄ,fptd7¡â»8HÃxíhÁÙ«xŒj×{åÖ×ñ—ß½@òw#°R»7¥à¿k¯àc@/»¾q‚ÞWµÝ÷À˜ªÞ‹[õnhDwžf°U6†í©wšö‚/^)Îs£ ‹¦©÷ÓJöŒÿÏö¯ÿúçw7ë¥ø—â?ÿýû÷ÿµùç㜨9 L‚)ÎëŽé~Šï`‡M¯ëÕ„ë¸&\ïkÂÉŠr9ÂÆ%ÖÞŸ ÒOÕ+)o˾=üÏ¡ð[½¯œ…ŸBÃMºÔ_x>ì¨ T³aÈ'È ƒïØÝé9©·ZïH³îÄYðJ^É(‹KÙ~z6Xþ~¦ªt(DŠ6z*¥™ÒŒ†]΀ä3J§Ÿíô÷9˜ìÓUÞ˜}›DüIbÉZPPÿeH+.4`|¥¥‰€2Wo¡­\­1èÀúpÛêÇ]s?nÜ@Ë 9þ‚‚»…ÚÞn½ÛOPPgE¨Å,Ì Pûq·›"ì*lmU »§{¢ D«0ò†vx§ÝšQgÉ­“å„]H] µÓ&á‘’bÒðÒÜ(K+¯§ÓZPbŒ@B\«>‰‘•ol\n\e<‰••R•Ò†‚[båž…Yî[ʙʈ¸~8°òŸ”æÿ‰ŒD_²#¥a‰ò¹úäû|œR~É—R­ ¦äÔ'ÐÊx‘ê€æâê¨t~÷¥}¼RæÇP@Ÿýáwš˜ëÂ}¼^Öû¾kÃpËô²Â{,£)¨³“²`S$š@?PR¸“¦IJ‰åûŽÂííeKJlÐ&$‰ÚkpØXÙÏÆêÎ]"> Ÿ…º„»çeZĦpŠBÈl¹.BˆÖ*t9$Àž®]'ÑZp°‰å0Ô¨ç3› Ê|ŒÒÇÉSv¾óÄDuªÐKLßsÚýó2öÊ9ÐÑÐíÝú¡H¸a]±Ñ}¸{¤,¯ËØÏˆÊa+¤áÝ>¬¿>D)­9Øý‰5¸‚BÄbÀKdcøƒ«>qD„¼[Ü|¥’{€¥ -±÷€Y¡9ÜkŸŒÇi"û8ÛœWÌlÐ'ðx{Oawþ°LLžéÞ-)Îö\0Lˆú¥Pbíf}Àa˧ä²iJ»ö:sA@¥â1cü[ìk)(À×§ÌiŠ´¶a"LìžgU¡Ãи¤pûö¦Ä¹•uÛã0†™1°#9<ѽ•º2ÒR()´Ú4øûÜ( %«õ®L‘‚Ëo­§È¢)Ó£8š;¦ ý ï.ekl%Ìm·»q½Wi I°.܃ݶ(cf-+Ž(õS#kÌ»rÐfõ¼ˆ‘1ÙÍc> ³exÅÉZžSx½n ¥$3™F€=,w…Þ7a–8ŠªMó6̾Oé ny¡D _K ·Ww…QÐkµSOK´ØÉq’fˇ¦ÌŒtu¥ @ I¶¹-,PFqÛÇfÞ†/·…Ár´ ð³"Öª8 Ÿ å ‚"²È šÈÁa&1ßýü¨VwV¥ÂkZA@ò‘ž—écì8Š.Ï%ÌÀ2 É=lxÓ“í4} ûÁ¢$„yîÔXV’¡w86‘8l¬éªÁ®Sœª#ÉN¶\IŒhpl5ê·Á­cPxYfklØÅuð‡æq!@q¬~‰C€Í¯§.>C€OõOÉÁè‡eèGA½+#7i]%‚,û© µØ4Ç µ¥ „ƒ׿Äf ã18åW£’?‚)!*8  Íª8d yŸfÙx™>œQc7…Wê…1Ú¸`Š¢uEÒͼ8²/—á´“ puª Ìî¹Vñ »ÎïÁ²Ø›õr¹þ¼é w³ôѵ†÷Œwì¡a}B|†nÀC»Œ(,⨅‘Ùj<*¢”kä`°ï»Æ}š-›|B#÷¬Ú¦ôMQ®æÖa.`hjëeS‚‰À%Ö9FE¥µ“³©ï_•!§ø  èØÒMC€Å }ÂeýÚԅ1|Vt.°“ѨKß^ÖWƒPHâH}cã²É°!—!à²ý”º¯Šð±—,ÜW›½ eNáËëÅÍÍfÕN¹ÙÌîÒd#™Å„žÖÉûN~ÒóÇ|Ä…Â6^íÌÃä#ö‰X©°]ìWC±ÔGìß÷4)ƒÇp¼Jô«ËÄ*.g%ëƒm¯à›ÍýbuŽŸDð¼ÞÐrø&•>‰Ld˜"‡³±·¢}U(÷B @méÄ·ûßE b¾Öxb½Å• P—ÍÎa#4¶s ¾â{ ÿ§Ì À¤uì7ŒÓ|–dÆ _ å#µ*B*^×9AÁüç]³)#V¼ZÂXWë2M¥°U±Sƒ=¼*ªO ŒòÀØ  ªÐÍrn_G"Öàl(K!övQ†XìéÜ#ÖÚ0`øûãköIh1h§Àv{6Þ†êR¯³íöá~œF0UdeŒ§Ôͧ"«Uã¸ã¥TËè,}T_jÕ²)(@ë@öyao·b'º2Ô*Ì“±)jAúNÒ4}ÜbƒGšÄ°å\UˆÜ¶ ×½O* Øô ˆ“¹$C[–¹w{­Úi¢¤qzR<6.9[¨ÀÎ*`ÿ©S˜'a?¬ ¨b_«p‚ËÆ×*\µ ìP@H`àE™±ÇƒÂÂ.¬#Qبœ¬¶CöSYJ„!q|ôé®`°2Õ‘›qØï™'±ƒÊª!Y[*"©]ÏÁÑÇ®_•ƒ”QV)¡ëvT¹õ¡:9¢(ô¶LèxAlù¾Ô‰õuh@€-ôb±o(?" ¢]ý²LwqlÑ?¸½î‰eÚKsxMaW¡eþ¼8!GJ‘CÅ÷kpã.ÅÕ8ÅëÞeþw›Åj7û°l&~@’ÁÖæd ¾¡ý€3塳ÏWŒô‹÷eÁŠì².Ô=¼vŸ×ÙÖ VŽ òB‹Žd¤pñš×éÆ'Ý:×àeXKádÂÆŒ^ñZ²ÌÆÍXǶß\¯i@¤À,QÍU±1¹ÍSô£â¸Âº}Ï£}YÆ€8sqÐ@°;KÓ,׊›2àãŠr6ñú»XtÁ²IEÃC×`JYFlvÁV¤•ª¸t֛¦e¦â`Pƒ"|ûMÙmŒ5•P>Í:9ƒEN-Î&÷ûã(FN©‘`ɹ1T6©3waÚ Xö¬03‡œiNqñ˜[ÑA¿ünl H  *`~ Ã) ¥9öØäˆ&ƒõ|7[>œ„„Ô`Îö²Žó8'ç¤b!ýt?ðW)wÎP`Kœ¢u/“ɤәXŠÐDØòn?¯0¡3ŠH,—uâQ³råÐà9íý¦Âɘ±ÅE›²n¨ÇÜ9’*>nÖ…mMUsKý´¸.MÐÁ¦ÆPôVÚ7¦’¦(ìÎ׫ËGµaÄËu?O©°C²Äû4KmV‹f5/»”à´vŽ ÙST0€Š×’Úï¸ùsl¨ù«$j?åE`ë[“¨}¸½Å¸GQì^àüë#fÙ4©ž‘ØŸžÄ±0¹Cuì¶ÛMþpI —µ7qeö4^€ ͈ý¶·{…RUÆSˆ¸)´§q&6Õ"m~·(“Úqfz€ÙAð†í´ÅfÑ‚Bð$ò’ÊH3SÛ Ó"‹îG~À c çwØìãq‰Nô7½hñÛB9©jp…ÔêUz)[IôX†¾*““Z†núÐÂäPi„”V ã~ÆVÜ“H]¯Ê$¤t*T¡S`oÊ ^W‚‚¹»+Ì×À’{IëñJi[ÜO_Õ$)`h8m³mv~Ø^ζóÅ¢ ò”Mý•2œú”äe»›KwÞÏgg\ÀÔù€Ý„$ éCC*ëo¿ŒÚ,ÑwÞöÍåùffR©'aÇ77Ó:Abgê>ØÇ]ãã :S[Flö¡Ö± E+ …9lÈAÖ ’Ö s%«Œr^‹;Ì÷ÖbÃ=iáD¼¤·Š|±¿‹”$'G1„éyçèÉtâ-^”²Žâaþû´æ»è® F(†¡†ü–›/e¾#NØ11è'IO’ÎU–+jÇó»2õ™†µ§ ‚JœM²è 4Ø0šàÐì8ࣰµ­Ä)´ŒØñ´Šo–Âí†Á–:8ap!O­´.YyÔAšÂmaÊW回ÂìoX7<.‚ÙkK^YA²[Ò ¬^M†æý> ‡¾êÕDݶsxÌ ŽØÙSª½Û ´$b6n—äèÐC¦°^MUµ:îù‰r{±Ônǵßëß¼ ìêKÝÛ•eaÏ‹ÞÞh61ph(‡R‚"¶E™¥¦¹dh ùF|[$—õ˜Ç“Ó~(Û‰o8=¶®¸OÍÄ¡AºÓ4™¥ª³¤3÷"ôÔîÏÆ*‹+€ê´à«ïÁ>Ñð ˜]Om¶4ÿKò< „är½mÊ©)EZ›𽺘”sТ¬”aÄž¥Î@µ$&ö=«"BÃÞxŽ€ý¶¬)òàj(CÑYY®HhtmjNíµpÚ3ÇD* æ|¶mž—5å‘hÌž-n e™ÄD' ¯…UixÅA¢õea†É ôÛw…Y ظMQP’ÒÎnÇæÀÒôŠÃËfù2)(_~€Ú¿ðÛ5ó²¨"@aà´ˆpBX΂õŒ2·¶ Ë={óº°u N÷“ŒØî›Â ¯Z‡RÔbûÊ€+A€ý°¸½lV׋Y¡h4*Ô’„ö«7—Ü6{sþ”¥èl¹Øí–Íáô ç˜NU÷ÆT¶§W6ð‡A9׃ÌSšºžØïë7…5ƒíÀ\êË—…aul2B}SXÂaÁJ7PÙ£Æ+IlZ¢Y†ܸνlH@Ôqà4Ñ(;ÏÊŠ×$v[MTfêaŽ<f}MTv[ì2Gí·¸¦Lh0 HÊ]€d˜ÏvÅ)Y*”?,<x˜ˆâÚ‡®Æ½)ÁËea$ʶ®Û0ÜÂj!´N*¢a¨Q“zVÒNåwÄÖV»EaŠ%o³ˆ=Op•¢âšDEÓIa  á׃PYñˆkSW\¡>ÕØaÚà•¢Q@E;ÇØ&ueÑueÍLmá­ØÇébŒCyíÙ#(ŒŒCY½A²ï†jÖ'Å¡”«ú°ÎŠ|-é+‹ÑPöh'Y¨Êcý^”õ®U†³C½i6c§Ù ÓÄ®žÃ€_~û®*l¶äÁ¹0]°ìQ]§Úxº&P;Y«u¦Izaiê*ËgÇŽ^ŽZ|ßÖÞö˜ÅËþâ˜?ÖÚ o¶¼Îº½ëWèr6úªòé¦ÿQAl( ùaP>¶@ÏeðŽŽNk0Ó­ ÀŽïÓw±³‰Ë2· £{±Έ=³±•’žBE)Kpˆ•ƒàIŒ¬\ùÙËF[#¡´§Ð‹ÖÈó⌠…þ6àÕòKá-ž ÅvOŒb]X„¦Pü(f‡É‹Gp® Ç)V—bj\œB;cê˜ $)¨…íèÃëú@Y§–oZtG‚¥n±Õ 2¢ݱàcAaa ÏŸ”=`Sã=Þ0©VÕ„Æù\kŠÔ’¦U§@`_)IYiŸô‹¥§ nš¸oÕ£L®1}M»sÈ<€½†’¢Û£¸YivŸÁ"xCÁ½^lw‹Õ|WØ@ß¶›‘“sÆÙ(¦2Æ1bÇSªà;&Š÷–ÂC;9§¬°ˆŽ<¹ÇUÕp,²×îɪjdè]°‡úT±ÐÊ8 jèàPvéÀÜnío o"Ue0´3ŒY” ˦ìúMH£)Dwº•ؤ›‚Ú¬Êô¦­ŠÆí#l`Ë+WƒêÞî~Jb™,2§Q\!‡YgU±ãBK“}ŸxÙ!ínµ-îÊâ\ßL²«côº:'ŠÛ×ï%™x§ÞWl÷w_ ïKë0· ˜®zW…Æ5FæŒeĆwؤy55¦bø>@WÜO |aØ@agiÁ‡Á2°ƒg×¥1ƒ@šÂGU¦ŽÁZ•’SXx[Ø`µV•T$­¶ZÇTWìNÚÔEeîHÔNÐEýô«=7$³©×àƒ[,u$#VØÜ{qÍ©8âú!@‚׈Øt±âÀÒ$%‰ŒëmÙˆ')Â4Õ.\v¸ëÝÝyCBkFì·ôþ {›bN1–˜#ó(¹EJ€g8˜©°?$1¹ {b‘‚‚¤¶GM{:ðŸ מƒÝÇF‘\§.v‚­&PÕ©—àO«ì0žËË u˜)D‹.cpKîÃ}Üä*l€j¹bÄn‹/o±Ž‚FÂüaƒWŒá]6V¿P ›²»[mt¥ALï¡öâx×\8T†ú"b»e ‚´³•³žÄA™_ºgBí+'„ìùNIó˜ÞsÖ=9ñ€¥…˜%A@=§PX®GŽB'àßЫa³³.بµéŸ §©JH ¹Ófu°´¡Q-†Ù®Ðñ·!‹Š‚[èøc{hIï^Y—Í· Å$ʰô0­£µ ªšû¾°¾6ބŧ9 2ÄË Ú-˜ÐÝKT ÒŒ•ˆ ²ôŠ 7L@-m:d+®<4î·9)à º‡ã¬äXöˆ®8A8 %)´—ø:tg…‚M!bq'‰×Ïe¡¡¦¦”•:^ñ<5Gaöœß•)‡ó!1€€[:§ Œ%W+ j°›hŽb¿0')¢°Kì\"­ç® Ë…[[€Çë¦7z4íFñ:6}N½U~îçeÙÉaĆÁ!»CÕÊ‚€Xÿ¯qhï0ØâÜ¡P®†Á>*ˆ­G7ŒØpiÓ;´ôj\D€½)õ“±•’ÃñÛç<-w[WŠØcC“Â~&®²`ô›ýõ›˜~5* ÈC†qûÛöGÉm¥-³§ozÀù ì÷ÿ D}d endstream endobj 7 0 obj 11969 endobj 8 0 obj << /ProcSet [ /PDF /Text ] /Font << /F4.0 9 0 R /F2.0 10 0 R /F6.0 11 0 R /F5.0 12 0 R /F8.0 13 0 R /F7.0 14 0 R /F9.1 15 0 R /F10.0 16 0 R /F3.0 17 0 R /F1.0 18 0 R >> >> endobj 9 0 obj << /Type /Font /Subtype /Type1 /BaseFont /XOJFNR+NimbusMonL-Bold /FontDescriptor 136 0 R /Widths 137 0 R /FirstChar 34 /LastChar 213 /Encoding /MacRomanEncoding >> endobj 10 0 obj << /Type /Font /Subtype /Type1 /BaseFont /BLSXKR+NimbusRomNo9L-Regu /FontDescriptor 143 0 R /Widths 144 0 R /FirstChar 37 /LastChar 251 /Encoding /MacRomanEncoding >> endobj 11 0 obj << /Type /Font /Subtype /Type1 /BaseFont /VDXOZN+NimbusMonL-BoldObli /FontDescriptor 150 0 R /Widths 151 0 R /FirstChar 46 /LastChar 122 /Encoding /MacRomanEncoding >> endobj 12 0 obj << /Type /Font /Subtype /Type1 /BaseFont /VRKLZQ+NimbusRomNo9L-ReguItal /FontDescriptor 165 0 R /Widths 166 0 R /FirstChar 38 /LastChar 223 /Encoding /MacRomanEncoding >> endobj 13 0 obj << /Type /Font /Subtype /Type1 /BaseFont /RDODNJ+CMMI10 /FontDescriptor 172 0 R /Widths 173 0 R /FirstChar 44 /LastChar 62 /Encoding /MacRomanEncoding >> endobj 14 0 obj << /Type /Font /Subtype /Type1 /BaseFont /JXODNJ+CMR10 /FontDescriptor 181 0 R /Widths 182 0 R /FirstChar 40 /LastChar 93 /Encoding /MacRomanEncoding >> endobj 15 0 obj << /Type /Font /Subtype /Type1 /BaseFont /NLTDNJ+CMSY7 /FontDescriptor 197 0 R /Widths 199 0 R /FirstChar 33 /LastChar 34 /Encoding 200 0 R >> endobj 16 0 obj << /Type /Font /Subtype /Type1 /BaseFont /BFPMAG+NimbusMonL-Regu /FontDescriptor 206 0 R /Widths 207 0 R /FirstChar 37 /LastChar 247 /Encoding /MacRomanEncoding >> endobj 17 0 obj << /Type /Font /Subtype /Type1 /BaseFont /NLTDNJ+NimbusRomNo9L-MediItal /FontDescriptor 213 0 R /Widths 214 0 R /FirstChar 68 /LastChar 89 /Encoding /MacRomanEncoding >> endobj 18 0 obj << /Type /Font /Subtype /Type1 /BaseFont /BLKJPF+NimbusRomNo9L-Medi /FontDescriptor 220 0 R /Widths 221 0 R /FirstChar 45 /LastChar 121 /Encoding /MacRomanEncoding >> endobj 19 0 obj 65 endobj 20 0 obj << /Length 19 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»åq¹äÍBžÉ endstream endobj 21 0 obj << /Type /Page /Parent 4 0 R /Resources 22 0 R /Contents 20 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 22 0 obj << /ProcSet [ /PDF ] /XObject << /Fm2 23 0 R >> >> endobj 23 0 obj << /Length 24 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 25 0 R /Filter /FlateDecode >> stream xÚ­}k“Grà÷úã»ÇèŽlu½»÷¼Ž DÊ¢­‡WäÚ»k9 œÁjRÜð¿Ìj ‘ÙèÊj@Kņ°Tg=²²òY¿\ýáê—«/Þ^µUìU ÿt¿\SYÛ^Å6Tu0Wo®>ÿJWõ•¾zûþêúÅ?¼øìêí_¯^½U#À1TZ{}ýçý÷WueÛæê#L«ˆ¾jlÕÖ^¾ž?àßWºmÚ诮L¿Žqõ=2kª¦uŠNúò0éÈç­­¢m[¤´©þÕxǾ›_éÚÃntü±õ˜á{M¾WŸez”»J‚MeZsu²w•ù¾ñUÝÄ©kS¦Õ•Ž“÷~eà;k=Ý‹¸w[ÃwšÌË×_¾}ýýwG(uåBtÃwñÃëWo„x«:f {¾|>Ò§÷M¥ØR£Zë $êâ±§9…+^>Ü ˜ñ×ËOªºYδtW©1•Ó¶Û⑾Ÿï»áŒŠ\#]5Ñy ~ýõB¾HÖéVQ€_g7‹ùòav/Ài8>Ã&R×/s "˜Ê úÈLc“Ýh ÜÖqÚ<®·Ò–ö(T1êÊÁG¨Zø¾ÇýþKáö{'ÚHÜä°ðånsÿü›ßI÷ÐàÄî•èíqv+mÝ8 ˆâ+{·YÌ~XcOq¡®\ë»Ý›éÑE¿1…Tzum‚p@™!¡ë/¿nN.µÝ­%Îète´e ÷Ëín¹ºÝŠ ȱ°Ž¬$ ßˆ™Ìóí›ç/¿3å\\[y™r.äûÚM9—@çBfHçòR>[Àäc*6•EžD@&‹­BmÙLp,J8[5Î1€?~÷úO§s¨“C±MÜ=Ø)¼¥û>‘ÊK?åPÈ@¢~ûS!ï–«Ùæ“Dùº}Ë0 íb¾[®E:ö5`¸a»y'ò#ÓǦ¹]®¶S  •¯;žÿÝz%Ì¢à:šºv dý^:¸Ž¦s¨ëÝ(&]‡c2é ¢’ ôGo"_Ên‰€µ]ÆEf›…H-JæY®æ÷O7‹ð5  nÌllu 1ä­žÈ3 úØ£8‘Ê|v?ºŸ‰ÌPHrš9}8ØJ;=}qÊ€^æh{Xl·²pí)SÃÙºNo—“@hÒÀÿ Ý^6õôFnIDÑÒÄÊz4Cä“Ñ5>ŸŒ@5€c¾‰h<0~öµt'Áä¬êºaØ-lù=Ú5d~Šj”0áßh­¨›åíb»«„½ôg_ÛʃA›l(qu¡©¢·æ‘öó§ç_$ÆüüL6È"ÌBg»[€V¾‘Ž® †mA‘ÿÑÚ°X®©÷ú ,Ün j›KÞ“q5X‰|¸Ö‚tFòqMyUê¨Ô`Ìx±øåi)jf±2Èr ÈÑ6aÛ86Åì~±Ú 9ÐN&¬ ŸsÂXæf¶›I $F@ DÆ*€9F¾ïT%јµUkØV^¿—XØ#uˆôûùúáq·T¶Ó:MwóQ”60õtžÙVbºÓüÈ÷OÛÅÍ3IfX`ÍÀŸÈîn)ê£ÞÅ“E©âM¦ÖlŽÓ¥ÞγÃÖ$Nhmg>E€õ´ 3Ê ³ïw‹€ÜÐVÑ´ÁS&©MƬa >º¿è[A®Ø"EêŠ0ç+ü$üh(Dþý»õúçç?KÜHÃaÖu‹Å£¼´Hc­ÙVÿ¾¿ÙŠ>D7-ÇÛ Ùôq•±–ŸëÍ_Ÿ¶»çÂñôÔŒ6j³—¸«°0ÔÍC l‰€ˆ·TÓVבÏ¢OâJuò+0÷TÍ:9m\w™ DAÙñeš"Ý›Ðô|¶][ ã@ SíÙ¿p<Ýáv¸£‡ÙNd^ƒºé”ì—•ìv8ï–ó»‚t†#{±¼½›$AÇ¥¨ÃÁ§ÝBÚ ŽG¯8…‘:MMˆŠMR°ƒ¯@Ù®›£¬g%ïƒÉi½«à,ƒxÚ¸™kß'R“I,‚ê V6à½hfèšmDÉžkAÔ†Ýi¢tÒ*´tû`lz\ˆì¬éìZ:Ûë•Dúm¨ZÍÁMàGl†ÐvñLâf@óÖÞ â-O-°‘jÇ ºë"9`i.0˜ÑëÂ43°ÐmÃvó$~ê ßɶ£²œ}µ0Êd^ïV¶ 'ȺýÎk¡¦™k.r4#‘InïÓ-#¢³E¡yáG¹}z·ÛÌæ²èÙ༱¿øýfý Yè7;‚œâîäJ£@¯‘4 *wÏÄ(§«¬ç³l×"»ô•ä{ô›Ívºt1æ7rJýdŸ¶|Q³‘n]εj¸÷‚XÖx˜äãòþ^Ê€­òNbü(Å1J6‹ÇõF&ã¡ul7Ë÷/këìŽs´ZøNö÷ìùçw0!©ÃšÅ{ ’ ex è­ÌñËPÕx+ÉKÉwÑ:௑/ééññ~)¡Xi»¿ÊtšUAýÓˆ± ä1Ö`ýa¸“Nñíëo_I”*Œ ‘ç;. i/²·Ÿa%Q Zʆcê[‘MZ]~‚¢Þ†&g+*¡9w¬ÛsP‹öNSëj ¸ê5àz­ŽeÛ½& $òE-·­cà À¦X?€YusJŠ3V£9äG‘ÃÁk}ø>ÝÅ™¨òhUÑͬ¥a€ßp€t?bеöS” ‘…h4›æ $HÜÛ9Ìt``£¼K1¶ º$[ZQqqװݼõPÄAŸ`sÜ.VϧS ŽZßtåfv/ùUÈ%Y­å¸%hˆÀY ®‚×N'?]¼ÚÀî‘WÙÅ«1¨ƒ(y …ÄLñî'¤åX^ŠôU{© ëJâJ`jÃ`ndÝŒOÓ¶ŠÏRˆ¦Å0†a•Ïd ¨´!p7âò{ÝXäúp·4œ¼ßkùò•nߌº]5e%çÜÇx ÑØt½¢}´æÕý½\ÏߊܲFÍxŸ¸«¬èh¸“ÞZ¶FQÁ×1‚.Õ0™ˆ•n›ªñ b4"4bNÞf[¶’L6UÓ´l.®ê©±|Æ"k `L7md‡T¼ü=-D]Õ?†R”ä³Ô¡ D £-W†~_ŠÁ†îð;uŒ¾<+ˆp_ó­ý´Ýmžæ»§Í¢Z¬æk ü”®“$€"“ÈÇ=fŽVÒMÔt£–m@æ—ÍÅ´ q³T›¾¤³§{Éml0Lc,ù ÙÛ XuÞó)îŸâYƒM_÷ ª¨â÷g ¤ wk 1îiµ]ޮĬ›§@¦J@­yþn)úu¨œ h¹Ú•²ŒÖŠ‚Ü.6°J_MÙ™:Ú;öÅRÀÔadbàÛ±ä6E’Ut Ú.…(çÝ –c«(T—±QÇŽoæaöILŸ)/„B<“¼úÙ²üûµÌîgµý¢:®¿šÝ‹œdÕŽåYé.Ãwô{9GÏ€Tq¡ƒáUñ2óÍ¿ýà3’AfˆÏ¿ò=wúáT½‘bNœÐ^ŠÙª'f°÷Í>úÍbþ´Yî$d#±m{SY"8z÷mÔžMóz5—x­FéV2ùVN 5].ƒÀ[S0Þ È s+Q¿•Ž-û~ñüåòVbM±Ó‚o¾p)[,ðl'/îo×p*wï¾6ŽÌĪk¶wë§{Ñj 4Žów‹‚äiÃFï Aµ©<„Â|·žà^ò =™}VxÙÆŽ-,¤%Ù v|R³ @ÁÈSÖ¢1C ʳu• -Û(I17(À‡ `Jî*î§€‰¹«5ú ‹Ûg–|ˆýºÔU‘C× 'òqƒYåýÉæG)é³`d¹³ö²Ït=B¨32]=Ƈö‰ñ$GRÉPn¹m´¶ßè\`9°ï ~°ÒMm „+ÙПî[6Áf¶Ú¾?%äÆe|dP¯:\¤æ6éP¨ÛBº+¦ßÑï»ë’3ä"ºÉ @ÅóOÏ¿®2ºW¾™o^5¨ >•‚€ùëjÒlÄ*Uðv8›®qºB!FÛ:7Z>hú-†–Ý2&ð[×`K§FH»c3X$ò=î&tÈ8®®¢ ,q\Ðò£e…|OÔ 0±Š‚”Šྵ|Yè5_¬vŽ v0˜ l¦­Èq5°)°žïF\Ôƒ”'ã<ÛÏXPhlÒ^(D*(Tb‹%Ÿ­L$4¬ùt Àp»Èâ@M­§ì™'Â2~UÖgÙØˆ˜J…ÜÊÚpÓ€tü^]ÏVË¿ÉÉHu‹Å5l0X×’Jl°D×2ûåJrÒ(ä·mm&oì;8IöùGÑlÐT ?’ƒÉªU1;ˆ¼šÉ¹tÚ&Ó‹¯JâÊ5°¤v¸*IŰ˜LÁ!$­L! ·o|¾Y’±„=±ˆª+ ­ZÀUƒ,’N³~x>¡0Ìyô‚º½º¼óih ÝŸh=—ó¢Á;Ò¨ëRÙV5äÏñ^Ô0,èð Äí­©¢J! }ýñ ›Ýþ¿ŠF ͧe0ãÇ~`ôÁ'¿*¸Ý¬Å¼3ÔÉl¿®®¨YÄ.fxè3°k’õÂ̳‚÷Úè–áÖÊʘ£Ú²Ü3ñžÄKhRŸ ¶çMÉ£[FµhƒeôàZ â§®¥¦IÉ6Œ>ÀtcPýµ…Þù2åî#ƒÇï‹ÑA ìÏfXK~ƒQj€lܶ°‰Öƒêx„øü«fÌ·>Êî@UŸp“ý>Vƶ8Qê`=[ËvÏ:X£ÅD(à]MöcÒ¤ß-oŸ/V7ËÙ µÝ?+t7h¢.àP­cj~ÄÚX'^9›BlÒä.Ÿ[Á·2BùKm4S¿¿Â ȶϜS:ï—»Ýý‚a´*…%Œ¥ô&šÒGá‹ñM8˜ÉÉ¥E7…µ Ž>m•@¼/”Mטû½HÄÿQv#é®4™o„Vó¨1Ù˜®3ß»(#–+ q ŒËÕØÉ¥!s©ë•(ï°õ‹á({x': °¸ÒGË@ä¸8B‰;Q€R±¹ñÀg³€–®Ä#]sÄ×ý½˜w‡õ?gM²ìµc{¹Ÿ‰^åžöM¨‚!™p†€yß¾£ßƒ-{0S¡†{HA`+¹±Žº_Õ”zfLûGÅ…Lò°Ü WÒ2¶à»/~JÍ ßOÁyé=F¡ó AeðxÈ{_ƒÜ,$ètar¦Šë”7€ ÷÷¿O>'¹:3±&²¡÷²ØÂ;Žèň}Ǩ¿ÅüÜ“ä¥ÒX9røJfzÀZô£ˆDR%/¨r.Ôš½úu6ßÝë3uÐ%F v ±hoß«lË’áb"_Õâ—'ê9Qcuï颌ŋôíæG™Lÿ¦îJò*E„ ý›Ãö^TLS1êýtû‚Ǧ ŒZ8ϪØO(fBÚ©Km>÷f@ØÅcnôûrî´u¾ÿ¾«z[É%2Æ¡iO&«ÞÐôtƒ-$¿d¡ ©3[‰*‚1QÜC¨ë ýÔ0‹Œo½#Tš äû}¢P%êê.‹g`…Lì“Ñ6l;])ªæÊg‘mv”Éü( À+CQé!0ËíïYWW}ÖÕ~-ÆCYÚ•B5}ÃΔƒ‚°tX$M@¯MÈq]×I*K ƒYRU{%‚än¥Å8_>&@0S a~ÈÊP×¹N;`=Ápæ½Ù#Ʋ0  öžÂ&¡ýµäk;:Öq#F±´î’Nö0ê0Ï÷Ý 9¤[Ãæê8‹ÊË-gNöórl5¸ôÀ)œ¬ƒèTuí…(4Éi‘¸è÷}8BŠaa•d†‚1^Io1Pc0~mR{0gÙnúµÉ J›ÚœPížèWÅ|¿F Ú²´XN Ã„°V>Gß0ˆÕÓ˜ùǹ˜àEDó/õª#‹t€30œÐãBì™àBrbRQõCŸäákEBRB¼³l|&iOe`j„ÛRšSv#ÆÅ›¸†ƒ¹WÎAª GîEŠ·]Ô]r‘lP÷Õ?‰ò×$õv¸Ò=±—¬ ³ hv-5o1Àú¼7gl.9ÌP™f+À$`bK´YLæYÜkŠÛNO˜†q•âmž_*O°Uh( ¨‰^¡à’µC§zœÝ¤öS‚²Ô¶ØŽžAÉ ˆú‹„†RÛLpŒ[µtÜC¨ ŽÑ}'›ä£d7•±`JÑï 2‹ÁX§Ål\4tÔz ˜‹îúù²ÄŒÏ “Ï}:r5²ì–#wöø¸Y?n–³Ý¢ ¶(/)–b»*4Žùîwk‰ú=¦s€ùzƒ7Yn‰‚Ф1lO7…²'ôÊ ©²´Ö¦îÖ“h¸®°QöVµØ¤Õ}uVKLÓ¥2qE•ÃE! CªtÂJLæ´`,é†í«*{"0Îã`êúk÷OeOÄôú«ýŸ¼/Bc­–/ñ™jïI'@u”R°Ë7ýòÉýþÔðgŠdc¨F™â&ä8* ¨óûô%ÛQû´:¬^ŸRÔˆ.?¬SãÎzß‚áAn—«U†‘«c% (a êãrw'zð0§²ŸH˜_Cfç°‡:ƒr„ÿ-I °•ë8è¨b¯2ò»üÑÍÉýÄR° -…x\l–»]±Ý_9NvbT­ÅB‹–M´|íF,#´ÉcAa> ±Æ•ã÷%½ Ÿÿ¡ßo31‰ólØÉ^ßÌÞ-ïGJúïgá`SÊ`½ ›R%°ÿþP%œ¤h·©Í/9Ty‹ô‚¹è†½_ß߯ e)ÙÍÇRïI¬¨ “ðÞJ#Í$Û䆣 sY5âªcTB&®ˆfÆaX]%v«Æl8¾MPƒ&–Ÿ§Þ+Îl7b†cOb® ­Òf%‡-[b{w ´~/s[XØÝm‹ß‰ü6?) 4×Ï ~gÙ,só¬ðz6raV Z‚=‡÷(ÄÛB#IŒ¡Q…®§û]!0®» W:S/lFÝ¥˜,Xs€wËœaßv ‰€r0ÍZ;¶›w›õÏ¢gÐV:òu-äª[ÅÐïyÕF6Q3p‚=Äߟ6r—ƇpEA¶Ë_S %iœè/dP¿<Íàþ‹ >LØ0¨åBî¯âàÊ4‘íh»›m D£“‹Ø³™’Z#¨ØHRxÛ Æß–AÜ-oïž'O`!5¼iƒà¼ç„«)D¢i%:¢#êƒäG`†lš7…øü+%:¶õRÊ1Y¬Ë^¡zš‘’•¯¾B ®‡•ƒk{q¢Îzü^”@-ÿ€Y’›1O«ÿÓ–Í’<%ÆkAÇç+[š´õ{Á4A‡ºÍ@Ò6”ŽØ3¬¥ß,hzÝîT1¥ ½ÇÉ–$¸{¬¡{ÚÐÏex v+J"˜I‹!³ÉhM1%~e9äl Id ‡Ö&¹Â¦(Œ© J­¯(ÌG±<´Aµ,ñN2j[àd Ÿ¡àÕèûÕñ>ÑÝÐ¥)Ò)¬rÔ„ó c¡Äðõ$vX÷Àg*WÊ‹EŽBv#Ó0çy„dÑêÔ ŠBl “߈~f@šu (¬ð|@l)¾ÔµHHøÑsRù¯19ÁÓÝ.óºwQôZQ$ôâS<ûWe¢èI·ûè`IHU8$l̆ÎÒá´Øÿ˜¾|lvZ@©øR$ª&¿á#>]]snÃ?~ößrFÜ—x˜YMZhöûH[ ~íM*¦§ïÖ»Ôp]a]¢± *h³øl–|3%Ñ¢ÛÔÎBï¾+íÐÎåw?]ò-= âÝOýn£ëš‹½Ùš®LBŒß}E^h@ÝŸ!ø~B*|ò_5û7EáåAp£¥°è…—ðÞžCqç„X¸ŒïíY‡‰´G€RY n6QÜ•ø(†mØLÅwFBjNDßpì–D˜Õ!fx_x›Ô9Pîî\7¿…07æÙcD‚­ªR·É—Âü×ÛTü!T<)Ì?^ój½gÖb)eJЉœ'‹"4¨°D’Á³Hz‹ŒKßø“i§ˆ¢þ’FÌåô#¢ÈJ-€Ò艢x–mÁÊÌ ¢(uƆ´Ÿ$‹'ˆâãŒ%Y„é;dò1Ý0 ÙdÇ0°Àè¡Êw´Ê:°Iä®ÀÀCó›m]ª= ò]Žpý_Uñ.7Iq¥0ãd§¨æê-Çð?W6¥•`åÞ®i!'ÒDzòSa› •ŸÊ'Ï»a™ˆ/Mܯñ¹Ü=Œš é «÷)º‡iö¸åb[x+Ë·;á f ì±ý`Ë®{9 3a‘ŠÂÝz$º°½»S廼¹†/MzdP%±ä8Ò^¼ùòõëÂÛMÙÙÌïfé…!QÝÒ¹ºÎÐåtv|ž¬5qJ:{—¾Ã fƒ' G34vû‹]ÏnÍ&[ ×W{\^¨®u>ì _µ±%_3‰×­öy*:®ôk[L2áZÅØµ,©1Õƒ.ÔÊ¿²¹$ý Àðš}/ÿ)#ƒ}­JȘ2¶ê‘1i%ýºñy»oáùÅ—/_}õ/_¿þ×ûæÛï¾ÿ÷?üðæíÿã?ÿôç¿ÌÞÍoïoï–ýùþa•]ðaP”0V™ ñ«2è×¾HôëP\ êazÿuî„˃ÔH]¾€ÿÃv&}Ýo‡]Z h¢1Äéã/›íîéÃÇ_?ýí¸¡ÿûùVå:ÆžhZ$‡C¿„ÝFã)4&‰n=@aK‘ÔL•ÀìC¤²Û¯ñ=PÙ³†Ï£¶Agaµó*ӹѸȀ0EX~p ›&Z’°SÓÖ ø(’n’“”N±á ª±.îÁó“‘r6Ä侓E¡7¾€H·"¦ðà«Æ­n8µEÆï%!í»rdZ(ÆCGckù¹ŠÏ®¡ÁÕ:§(€dìK¨AHçË=?AÎ:ô—R€}¾¬”÷©È—€Òà@¹¥) QÊ̲uå±f—€¤cÍJ%¸lMj§Ù°cý½dF×sFsØÉ'‹I0Ær´‹lßñšï@í6©ŸcnÄÚµ6…§§ŸQz÷ tB6…-%34œzö‰Ù+›?ЛhLa—`>Ï” +|c¦Þ÷W–ûÊÐîVt‡+kþMâÓXÇ¢=’²¬Ô±ŸJ“ #`rkÐÙ}hÙv¶Ë‡åýlSp¥Ø4}º…Ê$ñ醯ë Qâ`KÙvˆ³à Ö·õŽm倲g¥ŒÀ×&¥¢g,ÚÀ¾ÿu¾x”4ô;¬Ü¥“ßµî}ã¯bƒ/ot¡ ­ÜÉ:˜ÅêHÙÃi=¬Ç ¥ #Z0U£b3”š5ÙÖUÞ[6ËLlîåR¾HË ÒQŠ :|$Ï4|1sØ; €±Ýlå tÀGœø’ tÝç>{"#Ù!ø_`ÈŽZ ¨³ …”$l§~O«%¢WÀ.>ÈâØí­{)3Iõ”ŒÄ&„)¬3éÙ˜#¦Œ-f?Ë©LÀp|ž£Ú©F)Œâ¦aÚÔÒù`4¿Ö|/²¯ÒaŽaèw£¦d§WÖ Êè,Ô]ûè4ïÃ=ÎÃHÍWÆs £_L’4Ív#‰yƘþìØ\â˸ÓRŽ’™âà3ŽÃˆhî Ñ·on¬E!ö§">‡$2â9LyG¦LW¶¹`ŒÁbkôÈ`ÄÍ8×=mÍ ¤bUÇæ˜‰Öb½:ýü¶±›½»¹Ø ø0…{Z±@FŰØv6³Õ­ø¨ªÇÔýš#í?1R£Êt ·Æ8®üI¦“`ƒ&Cáþ¶ØˆW3'D@%ÃÂ!a¹È %w±6LP€ñdŠ gãøÊqIÿÛ¨|‹GF>ØKбYÖO;)Ì–66ÿfëß$„Ó¯°×…(D’<æÉÕ|/¢bæ­OïkÒ9£9å°hñpôfò’éV"êå‘AIlÉc~Mg‘Ûø{ºY6þk)®×_’,éK5pdaÝ÷ªØåÇ: 6ÁÃz#…M->½DAE°ØÚÂZM@DߟÅçš«*Wúã-l+“{æb ߈À{ûL¼R¦ÒѳÍÌÄï±mbÃæ@£ý^²<¶ âûO­¥âoS2ù`"‘ßcÍŸf;¹»c× TsÀ×âÓr>tÉç$U¤>ŸBõ 7ÍññYqiÐ+H]Û—bF‡`;Ëç‘ø<rüÌÓsðâ›Ç #GË7ôêáÝBÖø÷¶Ö³M}¼[îÛÇÙ\”ä(Àø*WRš0Jþ6òõ­Ä’óY4øXê ˆÜR[ǶS¨Þ:‚ÙÚƒ‚µYß<Íżg jSëZ8.]Õádm§/€Çné€tLõª„gñe>¾4ñ8Ô25_ÙJÚŠKÏâÀYúˆ™ ò8šˆ:mì=¡ð ÍfijI lj=€£-ÒZìü͘ªDj¨f“ }¿šBiµÅ§I÷Íî˜J:jaƒ,Ô j&éc ɬEöUç™BŠï™î¡öoÏ—KÑ4Á~ªl"‚l)šˆmä5ÛÑJzfÄc0 ….(¬ ¹¾æJ¶3«ä­­îIŠÑ4]9x>Á“°‡„ßo&Kž½“Ña¯ÓšÀÕЀ™H§YÞ®àŠÞHŠya×À $µÜa²fË>/¸q̺w›èVäžmHf‘¯i&U2:Ð êÁ&D»Ÿ!4-[Ñn3[Þ ¸Vƒ~í8®:ýIò¢A3 Ô«º݆øziÀäòW°#ŸQ¢Øw²§L|¹¬5e¡am›ž1¢9Ä MlcظâÉ´uìÈÚ* Thò ¤†ÉT|CËÕÍr>“ß»Ãçmœç ”£\ªkiDß¾îš ð-èÔzeßJt0êÙ<ó´Ðq`ùL¢ÚñQãÃ÷厾ÉÞò5½[LP×CD{bï˜Ü,Då(&Pï7RîmR¿ÑÍÊ&º“#-.½6O!+Ñ/c4¾áË D· >p\SÇ3EõϦǜ‡{Ü’Mê&N!’n"Û v‹ ½øŽ™¨5ÕM[6Ó×Û…hàa/âÖ2˜Yˆýõ¼Ã‚Zq+ê  "+#~ ªÌÏ" ëŠÏ zK_¹]‰íð›6å Ð=›Â½ñm®}+åÿ.”ŧË-û~¶Ý.E;Ñ™ (Ì7ËÝ\”E6u!ä}í_¹Ø÷ÒÓ,è~-ÿþßDIìµý÷ûj»›ÉÏû¢Úb‚c³ü¥’T)L­ÎF¾]îDm ËÂS’âb+ÖÎñ{%’ˆÃD<Ã1õõbRJtr‚¦[¾ªo¸ÆÂþ–QÉ‹Íj»[,WÏÄ;ˆ:{dûÁÌžW¢P 1XÐÙÐe=_.V;Amïï ì[ç¾yz|MK<6-ÀzÔ ”ìeD'Á ØM°øD+`¹šm>I¡K´<y)¿&™‚`ñYD‰‚t,›C®qG‚uSúö‰üñ‘¥¦a¯ïû“ÌÒ°n×0÷/¯g}ýØQ×gÏq$˜Šo û1d ·øÓÓv ·±ï#ûÕRôâZ”Üx=)ˆÄ.Á:jþ}ê\—ÞR˜‰¤S$’B¾Û¢¹/z¯<NdÓý'XgâûÙ»Oúz!y£0O2´ìû/_ˆNOŸ0ìTwùA™õulÄ>XÕ·‹Å.¹oåÅ›ôÆûz½Zß?Ý?=›¢ñ¢ò·ïÈóõkQ;1FÐv Ä¿>Ý‹i"X#›ÄÔuÀʦrp5h˜ÐuºÌ$šÃö¨¨’ïÿø½¨hÔ¾l½HçóöÕËçÿþÃëïÞŠ!ü:õ £½øâ›WŸÂæõÆ1©Pa­Wò}©s[²1K÷ö®¨ó·`‚Õ–Íó~]ÓhJQ¹Õt NQ±7œ7M 1P€ÔNŠÍ€væÃ]+Is.ÕäPùÝ(üáv±z>…Ë‚ÜÄÀuâåØKNô‚rRãy ùúQòôº…’Ÿ|*e_á뎀¨rj ƒ}c8–΃©Û…<ˆ ãùvv›™¨b¶‹c©.O–´®[4ôËSÅäë¤oÖ|´Kéa/Œõcª/…)”Ú)äËulŒHg_RgŸÏîŸÄêÇ}0ŠÃˆÁâizÌ06kŒÇb”æ Îxlº. Cç’ÞÑEM£¬MêÚ‡L¼Iu2ý÷4g¿E°6*:•ßð¶1µ `‹s´|ÈÕy¾:qŠ'ü º1)y·i =£Â÷h¡ºâ|u'Ý=lCçÛg¢7*¢³˜A„Z4$I­<膂x<ÈfE€ nòá8 Ô€Žß«Â÷mêW—9m‚¤l´Ø4…/N,úPÑ4f»Ã`~¹g*5 ëBí|]K1î'6À¦«µ8EÄž†]éYÑCØ X^ôÿR­OY7EïvwÈ›¶åÔu–˜ƒvþ †r±µGƒù²G -ÞéÆ&÷xÑ…qU>? «Ê(ÄŸô– ¡Ôf½á{ãßý}Cwidû™Âùøz¸fSõ•úbÈê–J¹)ç(r€ßl{×>WƒwV¢[“m½¥SÑ·¶ŠÎ«È@Ùë‹*Cãøà3›NZêˆyècÒÎyÀÌÚ&ÕØSAí­‘#„’_ @Ø>›¢wPŒ@cÇI¶­)E[ÎaÊ3ŸNôË¡@²HTÀ„×¹S–tË‘ÆÃh§Ž¹T²ÅWµ…KÛéÂ5$/ÄäÛ$"Ÿ¢Ën ˜ã˜@adµåƒ šA 3þ¸ÁÌ´ùM¥>åÁû6=d3¡¸uG|ý}¢JÒÂz¬1l `ybŠiÀ>i d¹ší„f K´a0'•ÉY½ »yiÅ@i›$¶Mý€6(ŸXV‹BäÂ"O#û¬Ä W_9k¯2 •«*-?jÞ=~¤†F§r 2/˜” J4ô”l¹ÕuêIgØw—lJì Ðr(9QÓÁmíè_Ëùm©–žSíòáñ~9‹Ïúûä0óè˜(Ù•.Thê¼Hïrê6×40$XÐ ê.®H!Vb 8˜Ç;E>ˆåcmÇ‹È÷¢ß/zÈÝËírOP$äÀ·A9wvà’8N¿à;|ôxª)lÀþk¶ÙÌ>ý„Áñÿ>Œò ü7¾›#V“úP?àÉã{W'ï ~ÉÙFeôe–(# ?M¡ößc Øô{qI˜Ä ªÙÐõ§ Çe“–ÎBÙü©Ãèþêý„¬¡êþjySµ5)»Åï‹JdžZ®n¿ž*ýÙ–1'ÕkgéÍ)Ì´ÿ«^qàÒ¤;š84_ý:ü™¬0JQ­à÷2Û·)Õb:ö1üùW2±âÍ #!/òkA®Û6ìëM~-M›üPôëE~%éNþõíïË3ÔD°]º6/󟟲»è@ ƒïÕñ{,1FÒ§ß”•Z¥“c:Nø ƒ‹|üüjЛÓpô<­–øe~†¶æÔ(v'ò‹ÃxSù>…éY~ö¨=f7¹ôøYcáNø$ÚäÉôx‡L÷¾õj¶Z?,váæ˜TÊ|‚íÓâ uÊP[, BÂBv4 ÷ëõãO‚Y‰ìØŸì/Œ¥æøÍ)ëRcœ‡ê¢‘WS8—ʈ4 ÈïV»ì8eKåäLB :áÚý¾–³ÛÅOZÎXrƒí©”¸5"›Hî¿ïZÀêσ(»¥øÅº®ÁÒrû9,@™ü$ª_ù~°´£ØðøôÏÀ¸G»RŒûddæŒû£s %$­U”0Š{ˆÐ!VüÁ†¯{+Þ¿×éàWïàEE½1vœ&ÆLùãÈjtäÄ`ÑóIF¦×g@ù*;ü~ქœåƒ£=G—ìYcºÊ£è¡c%3íŽRõÈ©±;ë Wzp&©c6)hÿ±ûe p|W}|ÔÿCU-Œ;'­M‰=ΦpзwÇÈTÆNkÐy:n§^ïÓÇUܹ¡]{•w; µc¦¡7&7êì"Ô:]§ÎÔ>®—+Ò%ü,ìbü,Ô!‡Ýc|ö ¢Åf2uPñÑt7w»Û<ÍwO<}eêYKG=ËÛ†KW»ë"„tÅÝ6‹»K®q7t›ÒTƒ2——Hn¥Ä£åÉGñ…¥Õ$.†=·°„|t¡êúÍÛþøåÛ?þðê2ZþQ 4Æ‘@ÝZg]d,’kPnKíþ³®2z ¹q«IWy¨.ø‹°…0àÛSg"áªPý÷D¤ <>ÊÏÅ|¢9èÌÒjºøï…ôpÕ ifŸ/¡y,hzŽ,í$4_ít ¹ƒ [ég“È$'¡OGUC }u¶„Ƽô!ær\ê¥:å{¶¶÷" ­2¹V¾ÌŒ;\­š†…ô@rfµŠIè3PÛêô¬HµHh’¥‰þü,d !Z´•-¾ÜIÇÌKèŸî—ÛÝþ.«KdjzW8ä°s™¤V¤6YÄLÔêTîHìReŠ’z¢\í$5•Jju6‡®šì«ëhð}ònX5NÉÛËŒ|+;dQ1»ÐÒ…*2ƒ³AÏãjøHwÝœŒº§4Ô"V·ÇîCgÝ=|Ñ!º6·âõê²›W›{žˆÜiDæ¹k%²Íe4–:…ÕmŽÆX |ÚÀêX[ƒ=28¸Ý,o.Ó^{ýÁt!û§Ä4*;å骉ödØ=•=bôn7‘̆1GÛÚôo6j<ú/ÁAzþ£­ûsRZ}bEZ0aØJ›iöQ/&N‚Áµ®@õÍ!ul¥ª¸}ìý†™4™•>›daÚTº¶§í铨gáëOðíÖÓÓŸ`Kô<ñ4ÂÞt²w©Õ$ž˜µdé ÇÔ­©Îñž¥Ô)Wëü¸w®^gB6«^éAAo…¸yúQ;AÁ±UºmRÊîXr½x8ÇáGkrlLŒÌð;#LP3îÃpwÌpÏàNMô­`)tfU¯¿{ûê»7¯ß¾~õæ"_ã!»G7;s*!KþL'7öbíÇý;:¹ñÕ¹˜÷Bwl*2‹U—†FS‡Ìàr¨='4J+ëly™ýC£9#>º+6ïÄT¼=_ðMn¥¿•p±P ê˜ÃL…Úk¨³ËžäËT™rnŸ=7^>p–G kN±¤ótdu™!Ò*w/ó{ Ý¬c–-ºÁ³L/l £eF}~™§îÀA{m†,áµó9-ìQnÕȸH¿<-7ç˜sÔ©¤‹¬£#O |Vâu_í|}™Q ìÆcÝ`ÔD±.óÓaï4 8䉳`s™}Œ^ÕÆd:íb©±w1F=:(Æ=W[òþšè²?5’±R'Ù› Eyª¶ŒM;ŽYÚ%ú<>‹ýsh¸·øÂ¶íø ä¹MÑvKq :CWY]¬vaMHz ùRo~‹Úe4—­öÃeŽCßàûݹA»î^—yñEܸÛ]z…á"å@c®›>ŒüwŠ cæ”Íãá²:¾Ú€<2ƒ^AÇ×`í`ÔßAÇz­¤Ñ“ìËo_\¨pÙôXa“¹Q…K·¾œ÷D‘›Ìd-*žãêi>—‘ŠRP‹œÉÑë…QA…­u±T1ƒ‚›Å޼ýUÈ7Ïð/|Ù¯1§ÊÆæ2 ]¼a'Ã&ÍàaöéB• SʬönvYl4¢K:‡‚—EFñM"—Åëâ2¬bk°Ðä°z™V€nˆ׫ôÄþZÓʺ³|çÎbOØÃÁ¯gêôòzfÐÍ¢kй½[>^&qZl‘@†gÌñÝ¥¶(XåhÚenÙÇÅbuÑõÅÞw±ÎÒ.—dg˜¢®ë_œ!´Í…ú'vâŽ9Bûx!gô©“BI ÿœÑâcž#™D·WgÕuØ”ñ3W¡Ù¶ƒÒmT™Å^È`ãø #ÚâTÞ†“¹qIÈ3ÓF|ÕØ^/uŸàËÀ"s˜å™§Saafd9Í%Ï#Vèæ]®æË›KóF°õš«é¹1Þøx·Þ­ÉÃ^çÅYÁÞÁzÏ̺__–ŸäA_Àî%™QÖýƒÊê2«sSÂI,>Û.úÞÚçj8X~y0òÕTÌTœ˜™g†ÍR±š`¡™ÔÂ;3òo±ý0”ò¢ùïeû¡!E\ŽßÑ>YÙ6¹añ}–Õ±{Ëyl­Å6Œ>Gk¬ýÈ™×C™:Gj—Ç>Œç¹†±Ù&zÆÇ½»,)ÝLɲõÃ….w“°§ƒª¡–~ŽÃÝà‘²½Ìä}eqº]><¿, w`d,?­%jþj²ù‡YÍ㣪ԺovYÙ&¶GߨÌz™öÑ=6Må05>þ‰ï]Mädu1Ö7Ž‹U+æ`7ì ¥ÍwO³ûË,7ìum e¥'®j“™(=çðHl]‰•XÃQÕ©ÖsÁÕ««àšì¹[ÿÆ«WwÚŠ©ê¬ÂqªÔÉÀ‰©Ý./TL,ŒÖªÌr?\œ•Žï]g]\˜•Þå1ûnšÝ6(;Â&"ÈÕé˜ÇúÕ}È!ê³\l«ÛÙ¥¡ÕÚ¥÷ý2˯.»wp‚9 ヾ¾ðÞÁm^q2ª:$^§jáübŽÔ>^¨•ø* ãôÙ…J‰Ny3ƒ>­æëÍf1ß]¨XÐ^:ب ¯3‚çT?f14õ* öá*3îfqáU6I¯õq³Øö00,=7mYgPÓXfLd`—ñZßVÖÚã°jº3.§3¤m¢+=©¥*Cg “F¦"_·Óm›AL2ç/*bǶðÖdsi@ÄÅ*ƘY+¾´PÒr|¡ 9$ЇÎÓt°N øÐ`\uê²>ƒ>ºÛ¡"–M ’F)ÄÌ|¥½¾"eü> >> endobj 26 0 obj << /Type /Font /Subtype /Type1 /BaseFont /TKQDNJ+CMSY10 /FontDescriptor 188 0 R /Widths 189 0 R /FirstChar 124 /LastChar 124 /Encoding /MacRomanEncoding >> endobj 27 0 obj << /Type /Font /Subtype /Type1 /BaseFont /TKQDNJ+CMSY10 /FontDescriptor 188 0 R /Widths 190 0 R /FirstChar 33 /LastChar 35 /Encoding 191 0 R >> endobj 28 0 obj 65 endobj 29 0 obj << /Length 28 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»ås¹äÍB¦Ê endstream endobj 30 0 obj << /Type /Page /Parent 4 0 R /Resources 31 0 R /Contents 29 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 31 0 obj << /ProcSet [ /PDF ] /XObject << /Fm3 32 0 R >> >> endobj 32 0 obj << /Length 33 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 34 0 R /Filter /FlateDecode >> stream xÚ½}[s#¹‘î;~÷mì˜Á)Ü¿yíñ ?ìnìLïqlìlt°%ªÅ’Ø&)õ´ýf‚Ud]ETR³öƒzºÅ¨, oø2óï«_ý}õÏVI&oV üÿô'¥1i’—׫Ï«ÿó%›•Z}xX}w·}øÝêÃÿ_ýøaÕH“¢ø (*\­\’Ö†óGïžñï¥J1·z^i ºüÅÓêgXÃ?ãx-­ñý|·}þÜ}maÉ—Dÿò~{7ó mLÉ ŸRËFœžÒJ/ç>í­lôp…ý—ÿû§¿þ?$Ê2’&†Á‡þüÓÿò¡ôE­LŒñÒ™ágþß?ýü×›Y ZºÆ Äñ¯s¿µT£…)igŦF6ÁP{ä?ýôÇË÷M^¯SAF7øºÿì~½·—´“Þv¿%Š{©QÓÝ4Y¬ÓQzÏHùeýë‡ÿõç¿~øë?O¿¹;1É&Æé.öF6ÊŠÑ7O>ï}#=l1ü<üjjpµ«Þ(X˜IVŒ?ï” ¸¹àµU8EÎKm†çHä'2…Œ‘ÿÐÁ#uP§wäÎïèÇ_×Ï_ž6½×4ütTÒ7Îõ?þêm"¿dó¯Ÿþ䣴öœƒgÒáômöümO»Ý—W?½ 6IãU~E×ûýúÛÇíËqórØ·›ƒlÿ澨ɢ%€ž¶/›õ~{üVdà(èH!}^o_*@4h´vë@vo›ýÓn]ó\ÊH›ôúr¿y€g»ÿø¶~zÝT¼®ÆJ§ÓŠÀû²ýuóôña}8~ü´}ùxØþc‚)&kôÉI?g1O»¯Lqí¹}=˜ü<&À½l_>|Þw÷ !ÈvÛçõçÍG5ópJÁŽjBÿC§]4#de„S,zŸQRÏ}êÕÞ¼sθ™‡Ñ°°`Ÿiè¯Zi1· m­ÔMþúÌZ¼“JÖò¸Þß]ï7#5 vÖÀ“³=éúzÒuzr¬gEOÏêä(=½"õ4Ø0øŸJð–á³ÙrXïZËê¾^£³åCÒ>–(á®(\e¬Éö³²l‚¦›…(n¡Á6'ø‹¸>kâ_¾»Š)&¦D'#½SCÌ‹-¹ÛÝoF¨âúJÁ!Ü"¹Òßu;möé#yŸÿñô'‹Î÷@Eô÷U-»Äƒ-pÉŒúáq{¨‡=·ÕÊðt•q·ÇÍó® –«ÀÓÔ!q/« „ è`ðµÝµk–d•NàäJ´_vxÒö5Ð7Sy/ Ëm‘»¨¸²cU4 ßF/ìâå´ÊápÜ¿Þ_÷¹½¯Ú“ð=?´5§¯ã÷÷Â5(Ð:Èㆡ:©A‡;ÆÄ@à?š! ‡k‡¨=1W uâÎ6Ê÷Záç?ýÇŸ>üÇO?.l»å”Á_±”îÖÇ ïCŒÁ°¸Ÿwûo•æg|0@5ª l{Že• &–6UtJxÔé!_ÙM|¶ÿ®IÑ"ƒ+(ŠÄù»çºÃW6ÎíwˆÑw€q?s½_dEÏ’‚ûÁïà j­³ ì(¸8c©¸žº8ö@EåéŒsq¡óŠaœ Dþq$ÛþÓÿ¾w|»}-Ä‹ 4yÁwÁ ·g —ÀeTÊMpÅÄ@/:×JÛK‚Xíšå£(me2Žm E…5 z¹žWÁAPÑ_®(hˆûõq½à‹¢625ôÖx©2{ÔÖFQE•^Q6ÚÁn¶6º&Îhmt‹:µÑ5.[ÑF/ëüó?ü‘·ÍšœH$`³u,ÏÜ(£(±ö¬ó27-ÛKŠ¡Ê< Â<¯œWÒÚ*ó̱ÝN³˜9 ÄáÇÎ_! æùücóÜOÉ-ðíuR2˜!îØ0‹eO'8Åq´VwVó¿vë#ãD·ÆYP‹]`œÅ$r&@ϲ ÝŽÃ¯ŒžœéÍqswÜí«d;†šöÀ§ÿÅhû™u˜Qg µhØ^€í$ϧGH|è)øE±9„ ÎÙ l»Óxþ„12-(9ton¹Oáœ Ž’Á§o<Éú«%Q¿>nïyáœb¼#dûÄ ÇWº±§3\^/ÞOücsÏÊ|hã¤Ó–E§€¿U…ð Àñ)í`qʾ¾y @5‰Èk«al­"ÏòÓ7©5 KçïuÃ˰yØh Lþ¶Ýi‡ÇÝëÓ=K¶É v‚Xð§ ïƒgÕøH‰á~ËV‘.P oÛûó©XxŽq ¤DI·˜¬@µÐ[EIöË~wÿÊn€èõYøŽ™SŠ¡ …zÜŸo —*Iø™<%Ü/»ãŽ©'Á´)o)g}sàyÅÝ)VNjeçlqïÚêj* ¢Ú¤…úe³Þ›ºÌð;‚ŒÿÞ‚ƒŽýúåófYþ®Šj¼ôæ—W]™?™Üg*#›±,Â%ì¨2@SP þYéµeÔ°ò—JE8Æ~(ظ,êšÜµ*ÝH"%Ô†µi•7ÝÞÔe¥ßW…>SPÐnô¢ ÐjAÿ‰µY¸!MmÖ°4J™sˆ ¹SoЖ N™vn úÓæi}9c¢R Y_±Œ,r ñ¬ÁîxÌöõé`» Œ?n÷,­¦$‰EJB¿|·>vwÛ5W³i§Z…_°¼¿ ÙÁD© µf¤Èüò»+FÌÞw¬,:éß4¡ûÒFpº×.<ꢅ҅‡é¾ƒÈ¨ 6ŽXÉY•öEWWè¬Ê@&®÷/ϪˆÁ•Çt±úJÌò\¢PÏ ÂÎûÂÃ?–ë‡Ç Ë×ò^­•˜Â¶[á¸}ž(Âêûøt£Vøá¸~¹_ïïYò@¦•óMÈãž'å4¸[šÇ3ùÀ)°”@ƒnw/¼D7øöΓÞ¾ðòÜIƒ½ÕêX1ß÷RxµØâìÛƒÛ‘ryÅWSx‚¸³†î§ðÄRKu>{.A(ÆyÇÚ³7¶UmØpA%ÂŽÞ… x?lË\¼6l/»È$Â1@-‡ W@Å4l dÐ0œSØ0-‡ œ6l˜®ô–§ ZPQ6Ô8§°a°Ò~ØÀ pÚ°xû3,ª‚‘SØ@¼~ÉrZϪþи Ÿ¡6\£°¡E.1þÀS§°a|5làÅÑI‹>rY:ƒs¢5>EŠüÕ+ν¸Bf× “ûÍ{°DÁØßÖ¹?}GÁ¹×BˆE®ø‰k<@¿¨¦{Ÿ¹Æb€9Ë5®á]}ûÑJßÉ·/£ÞèÛ+¼~KïæÛ‡L´¢’wBK\{΋[à“r›Å¾=& yîÖ€ÿ™çà'•‰”PÚBŽ—¯a¿%e(‰¼*=¹©c«dã)ØÁÆ‚+={â¾ãfî8‡ÉQÒå…OÚ+銻á¤ÐöGž\‘7¦-û°ßñ˜~'B×t¹¢žt=£#D§2ê©?Ï­`‰Sô+K®™ƒß$s u@T.^Cßx§œŒ*‚]ôºú1?Rî !„DÏLm °àZyxó´yÞœ/ã—“lò„pßx²…³ 5µi1ûžJÐZ‚‘ ¤€IžJЭûZ„=Ù4Ì"°ö®†Ã–“aEù2 À¹ü.Z1·bž„!j0š …~ž±iæ­íX[×€ZO‡íÃ7)\“ 4ð“,îasì¶ÂbçÉ[ô¡ÕŠ€~Þ¬_,2qÂúqK#™xÍ#ê¨~šVÜ¢#û¼Wm¥KIˆáç˜ê„œ" týT•K˜2I|¾ô!P_™„b ‘ŠO”\ï7¿ã_6÷L6I’.K®äܸöˆÕŒö×l*a÷ð'…%.*2BÎF¥ÃáF‰KóQ‹¼ŒEª7‰ÂИ@]ß³iL˜r4i|£ßÅ› ˆånÖgòäÒÛïÍSbº(K¯;°ˆˆ”ðó¶â+Kn3tR$k—i\tÔjÑÞµ‘lÁT€¬#*æÒWˆ¢!©­GmdˆžÚË ‰˜G$î†OÎDU—?ÖÌY’úÙage  ¢Û,Ùb‰™uF‹]¤õ y/„HxAë‹ëVºÉåÃÌY­ßehX¥Ðð2csû;ª} N )› Ó«Õé‘~=ŽÏü¹(SœdZÛ/OÛ  öÏE§{ÝÅýÛ#Sõ7 Jq£”q¯™:èGQé@â^LÊòŒ‚org˜ ´`f¬ •%GÉw¡Ié TaQm¸gRJæDkláΟ>·OÉ=WúÍÚò_Œ›¯´«sôÉÅ×”,µ:îh}0ƒj´ÔöŒ:Ö×1G³ŽFQ+ž Ê­¼—ÊG õ8[ñ3#ˆÜŠÂQ án÷üiûÃ1Œ›¼VÓÒÜ ÅO!€ûíN˜ºöky÷À’oÂâw)T®|3³¡1ØNá~eÉ{¨XÔµ„XrUxûd5%/û K° É“ðµìÛv÷z˜±e3BÀî‰)Q¢½[6‡ïyâMX›DŠ÷Š)£%ŒÎ{Bçïú[¤L#M4,*ï K¨ɲV–ðK¸ÚìZ@ ÷Z9àŒt±&E+J ë/”o#*uÙʘ-åÄÇ{Øí7,;„ Ϊ‡ò²$˜£KO Â’ Þ]s‚èå½¢PsN†¦¶Ïi³$c0e\1ë.Í€‚ßàÑJ”%{Í]rt›rÁ>!…ì.ý§)]‹N ¹w%Ù³@ØžÊġjý¯ê—òL‰—“•ËýR_©w¿­¤‘|-×0£ vô”,¯äft­EBL q™n8÷6La»’Í¿¿òÄ Á©ACV^íz¿á 79„%7ênÇn§f±D¯ ³ZKTË[U`VhŠ*®^rÏ bsƒ3¨XpÉMkí¨0 ÕÔó÷r!<õ¢QSâ}~}êÂŽ%S"ª&Q™½pDoa©ÑŠ«rDœ3Øí>q¶M‹îRiPPéɹ(ƨç¶1Ow¯×ØsÙån²úúåžgÑvbF +Z¦Óµv%/›ýãúK•¨E©ÂÀjK c¿Ã¶Æ< 5i¬¥rÜñ´3ò¥üùí½—ó§qÏ)CÉáeÃÚjý€&’[m¿9Yú/ð›TÀÒ»-ÿÐ`þhÒôpË1|#Â,AU²ô²GF9nƒ"æ‡Ç×s»,z#ÝçǸb@¦üÇ ¦>#¶/®³O»Ï?°Q·["Æ0¥²ì·ÇÇçË´þ™ÁÉ2V?ùÞwLéûÔºz–™À*¼ËS‹Û2ý<”ï1‘âdg8Юh\æEHÂÜ·ŸÀvîÈî33„=’˜ÝTÌ RÊ DùÓúÀÌÖ{ð`—¸ªaÞ㩌FˆwÇÌÕ'ìÕï(é.Ɉ!³Ë= Ô¯·ä޲AVf.wÂ9ŰycJ±ƒtî„uóf›œç ?oš)V¥C¥f‡˜7òkæ¶Ÿ•^+J>¼ä‰ÀígU är7ßvŽe»½fÔ¸i+ßIB¦>˜ÈÎp -nðQr‰ v‡#V¼ !#JíìÆ2t)!SF ØZ)–¡&dxˆQÚx~}ã½6IòTï6ŠÙJIžbÞDGP¡$èãÜÄ›¹ÔQÑ*J´ÚoxßGˆ•gvój)¥š’j!ž-á#¹yûY±(RŠ2úér+F[\ÍGá’In.ͳ¸6øL–ëTùȼӆBîrG,¯Øœ*[hÁJ2R&·œ&üÆSpÔ¢O(¦hö«›ç:R¸L?E»”ël+Õ¹¬¸?–Übmº‡•?Q>sÍ ä¡z\S6yfÓUÔæ{fÔ£o”¸e‡Mµc0 ,%„5O5°ë–< ½,’àd‘&¸‚ÏwöÇ –¤x±üšoY|rëÚöÛæîÌ–Å·Èž›ÂŠÁEoÓimÄŠWµïp®$¼BW5¼ç¢T¦P{nÔ¢ø64¹{:!^fb/Cã)Ñ~Ù1ù·ø:÷t5ÂÍ“7ߋᒌºm¡6D'¹2ï½áÙF)A¬öåõùó ûÿiR ¼+¸Ræ3§P–C‹20?¯ˆ³ˆÐ5¡p¹yE$ÍJÀ8¢‰§T‚(ÓPòeS§Œ•t˼fÀI÷‘íó2éÜSãJ´Üœ¢Çv[¤`™9El¼¹»x9E´8C‰}còš¢FèUn 0q¾êt$àá¸_o??Y1nb×f»×ÖfYüé+ØV])0Öt°Œ^£tu1¼.,‹¢Îþòe†ó˦ù¸+Ôv©jœ´"·RCÐ&ˆå¾Õƒöºð!>çÀË W ciÑbk9o…ûüz8VöRËÒ|áRî§ K´Ø]4_g•W»{Ù°„‹ÔO« %„Ê’©i/L“ÛרGæ¶U8,Þ’}Ø==íxÂuï´)á~…8êÕÑë¥' XIÓ¤ºÔêsÕÔ÷Ë¡np’–*·¿´Ò›+ŠFTÅÙÝJƒ¹ ×=¯T|×¶ÕX¿#Ó ¬ƒòZNo¸?T*ñõÖñÉKäîÃàdáHÌ2"¡^Ä•Çyi&(ôRt/‹ypXrF·²©ód3Û¿¿Øš6+ËÅ‚.N“(Y·ÅöËe’ÀqD‘8¢™TUÚpdÁ¤‡(ê‚I¶WY¢”Æ6¡fEÀÎ_%QºÆËŽ9¨ƒ ö™0§*æûª\ÅE—±q”`ßd3T„6)JW+ºÄ¼R´A¯'ê{˜jK¶+ŽôPù½Ùf2ÊŠ¥a¿‚÷™¼ƒÞ"Vœ“õŠ€¬v¼Æí=àG¤@ÇíHÄ"Íh¤ó–’+S5‚E´#±²2Ðâêw•cY47kG +Mx_íxÆä²^Ä;ç,ÌŠÀ.ÔX‹ªÍÁ ójV’ cŒý}%Z¶’8 ûn«å¸9èÛêFQe%)ª=GLŠu¬Ð‚’,ˆv»µÚ}òLÝŒØÕ ©›&©Ë_<­~^¤bµôÎL—uÎPñÚ¨A€¶µA¯nðh{>R2ž4x37Ú šbˆŠmïÀ¥°+{¤ŒU¢ƒ³ßÇd1ñÇ)ÉÆJ°×zä¶wR£sT.󮮺±º‘Öº±ÖÐØÇ˜èÅM1QC_‰ Ê´qš’kuÊáŽÅB2¬Ë'PkÛUŒ– ÁgVôØ0üXl˜­-ÀŠúVcHÚ9u‚ݨb¨ô[;’tÍ‚&S.ÅØá¦‰nÛ¢¢&_=6ÓN&ç‹°‚«¸±[ªXÞœ¢.À™ÇšzúªSUpQ0'©úÆÉÄÜî€zùÙ8/WÕ­qÎ#òÒÄþ^îeêq)§OÍÛe1*©¸¶"ä¤5ž\Q®¨`ù£°¬àDî#¹º)ÏtŽ~´ÅEÄ\ú³ar¯S0eÔQw±Ät¿0ëÌä„et-¢à]ÃýY%œÂâså˜uÀZÚ2 Õ¡.ŠÜN«tza/„!²iLž»5D¾%øžêÇðŸ§ò•eZÏ Šôä·Pë¬s\DñÜ[›Û^¾o â8¯G‡v_õ¾€6ø#‰þò—5 ÜZ\Æå¦UÒDÔ=O`Ð@,-C'‘ÜÓîs±l¿ëMØ`@÷á~Õ¾Z=‹Kˆ™ÿbaˆ‰éÔÊy¼²+ÆìMx·½&ÀO¥ÕÂ(“x;ÏáÕ£¢dº Úºƒ=…K¨<-×7Æ%©sx)EAŽ#g±Ä©¡V*ntj ïüoìÔ4üÞî»æ„j¡€–il,ƒ^¼Vú¯’M°‚XqE4Qàñƒçßàåe“EÚ=¿Etñ·½Á8˜SnŠ¢¶byŒ˜»´bY½2¥‘Vj‰¯»¯eM¬6hR–ÅJå«§X'*´-Sfø›™‡Øƒ7&æs¯} ÁMÀQ´ÝEZ/á±_eyòFÂÉW˜©³ï•íÀØÎP Ys1BGÛœføMaʼnAŠðp<°2Ø5% bÁ n×{N–u™þM`î×' § zKa~å8Y8ú]ë2¤øŽåbŸ­1$8AŠ+F¶Z¡äRzxf¨Õ`›R ÛÑpÁJ/Ka8`(¡¾ìXNx„—w/&üÑý~s‡ÁUÂ'6DJkV]Îi#µ'"@«o›Hɕ廆ã²T?m6/œ›”Îê7ÁD‚äÇ)V±‡ÀØQÈ{ܲؓVƒjU%XÁ'ûZÛô×*&›êåþi™÷wn; û›R¨,gç}؆Âä¹j˜ÊÁÉlEPQ_=â"²})Án9ÚÕ)'ƒKÔã¶ÏÛ'V«ƒ]í !×'´Ài¾´X¯µ(!¯º0zS”X?o9bõ)G„ÄÓs*<\Ày¤ (*,q5€̆\æÃnK«i²\GNpu监n7ÀcpF-I®a“ÚÕæ«o{p\—(×F:ï ¨b19tKg¼ ÖºÀÇèû¬`²)[ž^ÅT®#1‘šý=G¨p°")S¦ÁÂ’Mè@K­Ú—f+ÚL–þø÷•«ƒ]•(ÄñóWºW´€õeP¾µÂ†)FQR½ß>°.Ö@îªÍžuñ ~E°äùßrJ³ð®Ô‹ZoP­>)L ¼Oq†í>Dqå¶liìñéû‹}­¢H•ÄܾÜmï/5™bQæFWÛ2^¾<îŽKb¬~JGÁQÒÝrÂ6Cž‹G½±‡üjSÊã)ÐÍÝæpXï·Oßåo3- · 鞬÷Ó7–÷¦ÁÊJ¾ûMõ úØßÊiaRżƒ¨=¿8¡lÖù ®‡)n8¾ýD.öKUÔZ+g O¯ÃÑgeÌ»ÝëË‘Sl`ÁÖèDà Ø_vûã•È›<¾`Æœßò’?<òNpÂv€äFxcß(½¶ä ŸÃÞŽ29C0Eܘ\•§*¶˜¢DbZFËç{>Ìë9J;V$ë!ò Âë“!@²Ú±X•g ƒ½¥§—²[VZ ÌM4¦Ã,Ôòl?í¯’H‹n¥õ$8ÇŸµ«ÇtR|÷ë—Í~‹XÖÜ;¨ƒòrw,G)8ø…D‰€ui!²xÆÊ˜ë~/µÑö:£äÊ£3b+jOm×V¥5æ´²&,?{M’LjOàÈÍúܯµ^ c½Íýô¦¨í×ó—'VŽ;bñµUeè׳vÁYVÓ«rŒÀ?ÇÂõ~ [ C†&( ýôy—ÙÍ,* 8øÊ¥ö(vZ¿°H@ k‚'W¼ß°X@IÒ¥6ˆüfpc ¸±êWV%¦k<œ4OÉ”u|Áå€ ömy¥ X5½‹.4 صŒy­Ý9©TNóÏŽ:ÀöË®„zr¹Ž›gÉꃉד¤âá$¤0«þ_jÑWvOÆš¤S^ü“Ñ \Øi ®—ÿT<~ FQÅîKÆ4©™&†W}È\¶†Ë說¿ãl°ðÈ~`º^J܄ݚ“µpg1»ÉbÛ¸ú—ßñ&ÆžÞ ðð3š ;æßxãÿL’]Þ2êµ×Evë6Øu•P—×­Ûøa*€Ššîx4.¨ví)Éys' 삦1”Ö÷÷¼Á;©·«‹]Ò]ÞâÀw3}]¢ÄZÔ'#$CÉvA»¶é[¬¢Ð©f‹ÕÙB·?zE¾µÌ—á ƒÂL€Ñ±~§![ùö9’Ë­-½ "Ñ[R´Ïë——A ¼`ĉÃÞ@Ô ¾ßîöÛOÌyPg ©ðFšé¢Lޱ=õÍ)ƒÖÖ‡NÕ#ö›´*z ÅðQ0ݵgÙHÊmíÂñëü!Q'•ŸAV?ÂZy¤ÖhWã q•ÎryN”¾Êç®”OÙj¿d5õ†Þ6û§ÝšU¹×úCìË9š÷‡VóþÐ@(”?´èƵõ‡¦‹­ð‡Ä•Óžé! ,óôqÛµËZ_÷õµ>c}ìQ^t·ã¾ñ\ÜpÞSàO~Ú¾ !æãóæø¸ãÔ£¬’5Ãï¹9Ķy ÇÓõ®ïY©ÙΞLV*Ä×1§wñO2èÆœ_Lÿ÷Kãv1²Sǰ«:JvÊ *Ã2lLÇ–!Å-áµÂEî»ô5QçzÔÁZg+òŠÇ„ÉáAÑ!Rsø²¹ûá¶‚SàÍ”•‚Iüͽ[¢ò4wÞŸ+†nư¢#éUë¢ rs ½ üzX#öí˜2˜Ç&±cz^F:úÍÝoö[ÖÀJk@'éHÉ—é{Y#=)Y¦ëåšÌÖ$@ùîÖ^›d)àœ?â‰6y©‚£D[{=QM‚}ë(é†óÕ Ø%ú·m`6¬éç΃(‰ Š“©'cΜ´°“òþ§ëÆDœÕ¤Ü`8­‡EÁgÄD6X'`'ž³¨ôE1® ±\±d@ß4J°?¨X8'†–-:Š’Ao>ßBÙFtò#…û©®‰Ê‰–”ì¢ù|ýù xV.Q²­tWÆ’µ ›ÁiJGæ®Åè‹ Øñ|¾ú M ¡,–Ïç›VNcë¦ØõÆëUN?®÷÷_+çùŠiú;p6§NÚUjá*74_ÐS˜Ýíƒ÷ °é|ì n˰BEž³y\±ê¯VõÜßÍ‘òíù8‹ÈKñÄŸ¢ f{W€û Î ØVk)líÈPeÖ %r6hrÊ¨ÌæR¦‘4&«eÅcc¨ÝÊâ˜Ylnkµ›–”·ˆ!+Ô'êáyµ=¹¾•èÐÊÔ7©qù&»*¾ÛÝÂ2EÏ6N¼Ï»=§û—I` 3U)£–œC— L¬mð(¸†,žZÌ…Èè§o=­cîŒxÁ¬0t¤MrOGòñy,~ê99 3ÛUm \.ÊïÖ{^möy±ÔNeñ¡s[ÏËîŸ&Ô®±Ò:´0»|IC&¼U!äú=G¥#„ˆ„T7ò3§½³A*ëfNC¬.ä¶¾æëe÷<¸TaîP1 _Àãï¨ãxÜ>ohI%ciJfÑSMÄ@@Q˜Ÿ·‡ã°³¾³qÈósŠÀ‚×Ó)ÅÊûs¾rοÓOËôOú3G©Zø…à)Ð#‹ó‹eQ‚<äTœa÷Ó ú@,5Ô%MÑöû)®vj¨ëê¬NEQ(?;Vß<°TŠÜ‡×/›=ç²Éœz#Oas€òO®Ø©5Z5#WÉi v ®sû”sá~öÝñ\‹ çÒåò0,õWÉ—¢kF‘$DjاôúN³\Q¿`ÿýòbÏÑ5' Æ»)QÐ¬Ž•˜<>”1ÅÕx,ŠÂŽéPÅ\¼¾¤ñW# µV^ô1À¢DÊ™j“Éü(3Çë w@)©&˜â–:dZ/ˆuîYA0ö¢åù•£[Ïé*’]S¡dhJ/Ipï…óõ½ŽÚõÌ ý@HíWU¦$è€×læ Õz —õS ³ö*gìâ(wÁii–˜þ‰ò2õè½Î>&8âÉ_¬œ§Á1aŠzC¬ªxðSµ& ³…fÕÑa'mM¼"0ùœÐïìN8-µžæê[_õžÕŠ·u'@Ú_IÖ‹¥îD Tð݉UçNœpÇ 6mçN”å°9°š<µîDsàNˆåîÄUð݉UëNb­o‘vî!Ò{V‡Ö(cÒÿb©;QÞ­·¸ÔNeÍ‘=»Ävâtqé܉2d1ù/ê݉2*/Ô¹gLñžîDy¥·º`´tJ×ý QÕÇFç‹/”ïPŒ©Ï ïãQ8Ey¡¬åÜ,|v®KaÐBS/‰ëR$ʘâ»O;^OCsI`‹*®^(Ôé9ñ Š`Öæƒå^‘ “ÁJ¢v<‡"Ï×U˽m¤6?à{ŽJ1޹Ø5oôŽŸ%÷ÿ×ÇI{SQÙ,è@¡žöC¬[ŽÙ±ò¯Tò;™Æ)'21'çãlXÀ¼é Xô€êªŒ™ï*97 èT÷W*n½«;;Jªµ¼­‘®ëß8E=ýý¶íÈΚB¨ ²$_jÎB+#ÎH-Ëõ¤]8mvôɵ"ÖÊR¯NÛÓÍ:±[Y­8΃šL^×=–ˆLVB¨;^ÿ.^`“<µVÉ!«u±µ yÅãØú¥6ýC•E¢†Ñš6¥¥Íaó"56¡ÃÌ™ñ“‚ÈМn­ÊË}cU&çA*˜](ƒر¢²(ŒlÐe\ÁKX"Væ-ô庼¥Æk¤¶ ÖZh;¹w`V âÎŽÚt¨“B*£nîêŽã“‚|ÓåEßP–>ÄHÁ2Ë©¢Å¼ÑS,›½2í‚täfË‘ƒEÃh3TìÇõማñãaû O³tÛÌìt<oZ¸±H0ÐâŒY÷0‡§Ý×ËÃpÊJðºØµêñ厨:›¶Í€H4x1‚]ÂË/V•àdCëVeØO¼£”ðYE€*ÉÉì¶ÖÒxÝ=¸ØÎGéõ«î¶[ÖX^4J-Ê}Ì9õ$¥ÉåIZCÊ˜× ã¨ìr¹ » ;¢#Vß?;•@Emû£)q/ÊNïu÷ìtž`_|vÖͳó§mUDdew¼ÊUìâàB,ä´7JqÅ-å—¯É}?Êk®óÄ”4ãÉWUn….j(3Šm>ÿ¹@ö^VY¡I1‘+dÁ@bºž¤ÎÁoÞ/,']©òC¼l6ˆ —ë±¹¶£PßX5?Xý… „¦ â–ª²ìá}by­•~橌ª_ý…ó÷H |Þòäš¼ôÊ¿³\XF4e¹n^¾çª¡ô‰’kmH6l¾H7¤`ׇÃës%)g²b{šêJJ—srqŠ4ºgLñ.¥ó”h»¶J-NÖê!‚l,zàIY)ä–…@ËòäŠþ¢jÄ^Šb©Ó5ÞgØùÑëv’u†»î/°‰%¼Åߺ‰˜ÁìXË ¿±‡Ø YL›¿œ¿cÔB¬ƒ1–¶ÝÄúßÒëWzC31чä÷“Þ/£¥.k%F´~!0_'°…ýhô¤ÅÀ‡Gf;›»[‹1ìjqS1ìü⛸"@¯iÑ™¼Š>ù)eÜ^ªbAŸÃhrÏ—æl£Cú˜, mÁër´”²>ü•78š ¹ôzë—™íâ¤V°]FÈœÄí`À† fEÀ’nDE–Uçù‡r%cš3;5iQ£Ž±”¿Îeý¨:Ë‹­)ņ2XxWäK)OQÝûÅ«àʸ"O5Øxj öù@î³Ú[½iã9pn¬¥L‘úDE®=¼DAoy%§zm¨Æ½(Áô‘Üôõæ’Vš:OàL%=UdÁëoA'%tûoµã1ÇmÈ0wg¦–{C/'o¤ûMßo¹­œ"òT µÑÀ ؽH^ÚÃZˆà%ݸƞÜß¾lïÖO<…fÑÙzç†ÀäF[~‹%ºË‡&÷.'÷ÿú!jOÁªïoòåu·ÇNb$ý=ó®4JÜ^#Ðv©–Ù°Üeœ¶Vœç<…%³ DèFQRý³ÝdÞ”T7/<¹&•,°ÇÇ sÃbK†~a½ôè¢ÃZÉ 4%ZÅóñÀ-EXê"'zи§y&Jfçfœ;¨ÉV[<µb8*ƒÜ³7ŒÊˆ/ )…K«Ã¥Gå†fð oÂK™ ¹m_XÒÅ›£ˆÖ¦,ÝÛ.ЩjÏþóá{V¼v6>JwøÔ…6à”ª2¬`öÿ4Ø·¶1(»wà„ÊåÁÍU†’Áç-O²ùrž”ìÈ…ãŸm äºyaö¬U¹U!؇/ÃÐà-¦°g²‘s6€üßiž|>(”Ý„ ù²Û?¯Ÿž¾ñÚ'ÃÓ`®ü =ÌÍ=î^Ÿx#—LŠ29OÚ°¸aVaÑFaµ¢»´éXr’·m@u$ŸˆEÿ•9rÉ™œÛ(ƒV²ÖKaaÔŽzo—‹}^øÒhEl¸õ—ŒQVzˆ%¯yãt´–ÞR˜¥QÁ™òV[Âï™TlkÛ Q3³J²~MHá+O²±‘>R˜¥y˜KˆÖÚzpÛUÂR’»Ãô1pu„Å%3*±îIj¹¾ºÏ]}Ü»ýf}dæw@ëÀ‰› ßîq‡ ›áLyÉmnùÀœŽåNÞPµ˜E¥ƒŒÝÛ}·¾!ßTG€;‹XT1¶jN³•!’{ = Þ|º€œ*Oá~Ý<-%ÄkƒïnÒê¬k²Î¼‡C÷ÄGQ¯&mOÓÖØ˜6®T6>Yið0—aû'‰š¾”GÊxþŽõc=µâ_yþŽUÒRº…Ä„¨ÒgJ*øI âí4“ÃØí_mqX±`2™'MáÛÎø-l!‘ò¼=++L9‡MnM€ï×/Ÿë¬F©ç¼CÝ3ËY‡*ŸÉ2 † ·ˆIet§Q–AÃd2&i’‚ÆkY¼~D½0Y©¸ºÒP›{¡¶íe¥ßóè{àæ¨f´i“T-è?ñè{ [Ìûñö ô#QÅãŒ28E½~ž.°8ÂÕDJðùÌØ²ÆaìS^-“ÏŒ:±§ºÞ‡w‹ðqü±[Ù|fë(rA¬•Ég¶'Ë“`ò™-úg¹F-SL”\Ù|fЭK”\¹|æÜÇA“‚½…ÏŒ]œ›hérN.ÒR@yS'—MhÆ–ûÁëÛ–8çHdö1glжaôÖz%_Š5<(wŸˆÖ z¹N2ÙÌ'Ò±ÆÔPR5¤ãºX¸L:Ö°©‘‰Ø}¸™uÜ›kÙ±ŽÇ_2¢/¯–,ÓŽ_óN¼ã&‹x,ÊC'Ç‹c‹Ú¡“h¦ß’fWIIÇ&W<6‚í7ì;Uë;#uò(¿Z?é#Ëj†MÖCP=LÁ®+^8£­:I<ÍièäM;%6à+M¦Yn—3ÅåÅBô km¡ß-7‘›° vÀ<^˜hl O,–§h7=8ó[ b½lÒ„QÒG‰á óxfÞ5¶§Ÿyië#O¶>b'yJ¶·0óÌEç(s™ÇèÜakRÀL~šU¹­[] \šâ¹y·¼;m¼;QÚ Þ¦Ó–Ö³ì Suk*͆/ À™&z©­íPß‹×:§¹ÀNûænw­† †Çb³O!˜ÒK PÆL`Å5¢tÍA†Í• VÌ«lÂ>IJ $Qº¦~\ÿdid¼—bÝY{›çÂ[ ‰Ò/·˜V.ù¦©ç+Lé~¨É¡ü9Žc¾*f™Ò5‡9æöðÄr™5tIË„z§ ºfÒñP(M¡öÙ׋N±BîÀŠeý§JSZ,&qm¨=ËlX†)!ëHá*vg%§ÉS{ÅéŸ)n€¥!ÕlïB’SÜ ,ŽšÐ|Ùì™DS,Ýs>‚]±x£Z­€Š¶ |KMà©Á’£ ™5Ö4r°ÞÁ7—Ô,¬s¹J”Xl%©™Þlà9ámß÷xQ¼±ß³Ôn㑚±K}¹×‘šûçØ)r«UÞÊL¸æZ–QyÝÑkTÖ@Û[v裦û°`Tm¯;Z§pÀƒ.þoó„„Ðûæ÷# ;ìLiÔð©Þ‡ÜÉ óïD@FV‡ %Hñôcìûàð—VÌdcCAƒ6µ„É$›ÛÛ…2æÅoBî”C/ey¶¥g63Kãë6"*-wÍc*bž bs­™IDð,m*Cï`–fƒÔ–-“ÉŒ,P¬(?ÿ""óÀ¹ÖÄñªÁVb²kgÊ•Sˆ§4U#.ŠZ`A{ûB–3áÝ%Ô% fAjCeqˆæ»Qkóí¦]J¸bÈ`^Z’ ¡£¼b¾'Œ|,V™&ÌU4E¬ÊŒiVÌ,gØc/ÛØá F‹ú¢jD27^#–—ûÂÓ|¤@ ´è*É‚…PÔFkiѼZ¼U&%û™Ç §½l yÞªhÑ3-•‚´Q‘æõi¯-&¨·ö9i¡#cÔóàh5,ƒòp”ËØ¥Œ¨T=ÖQ¨›'ö]ˆ2¶CE3«Yj«Ús&Õè…½˜i.lË`&` f±˜Ü2˜/à‚b0/ä]· fbÕLÂVË`¢Ò fQI‹>1˜‹KL^pÇ`nAÅ ƒy /øÄ`&„ÚðxÁ-ƒy:Ï`®hëÙ2˜ }3‹Ü2˜2 • i¡¶ fB¨’'Ô–ÁL€–Ì¢²aì‰ÁLlÖ—½Ú2˜’]z¥4lË`&dP•Ö$ƒ¹Z³Tʵe0rý¼åɵe0¿¯\[3!€³ Ìlmˆ iµe0‚¥Ì«Z³ VüÆã¶ f殥û¶ æëÛV,AË`£ ‚Á¼ZÆ`ж×?Y1‰Æ'3%„ÛÛ&ãÑðÍoÞ69`³ŒÎw¼±o²IÇ`n¿dÊ`>Ü­Ÿ†¹ ±µ<€î¥No`-eÂo—œêk¹¸Øê~ÉTÆ%œô4Aý—S@¸½[·¼ð"`›xÕá >;£Ÿ‘† µè 3%¹ÃHNwÙ‚V­àSiK™Ûû}*lWKH–Ýû' m%‡ŠÌ¬ eqnú‰Ç Ç~#ÁxJ°ë/°uyéy°ÿx{_ e ^ŽÃû5äÄKSdÞÀ½9ÜbqËH­§¸7RQqð‹¢…Ë¤¢"³ÛϰÏëyªÝU%i±ìßNp_˜í猵y°ÔVt)¨ÃÝ~û‰y½„õ ÊGjÍC´‹-¼(I÷]FÝ7Ïœ©× ç ê!ª=ãÂ2¨âÍz¿=~c3‚¦âÆIðŸM|7— œÌQHþ×Ó ÎÚi6%=Öûæ²úÿÅî endstream endobj 33 0 obj 13891 endobj 34 0 obj << /ProcSet [ /PDF /Text ] /Font << /F4.0 9 0 R /F2.0 10 0 R /F5.0 12 0 R /F8.0 13 0 R /F7.0 14 0 R /F10.0 16 0 R /F9.1 15 0 R /F1.0 18 0 R >> >> endobj 35 0 obj 65 endobj 36 0 obj << /Length 35 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»åšp¹äÍB®Ë endstream endobj 37 0 obj << /Type /Page /Parent 4 0 R /Resources 38 0 R /Contents 36 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 38 0 obj << /ProcSet [ /PDF ] /XObject << /Fm4 39 0 R >> >> endobj 39 0 obj << /Length 40 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 41 0 R /Filter /FlateDecode >> stream xÚ½}[“·‘õ;~Eû4Rˆå­è¦(ŒØÕÚäØkÅÊÁhÎÔÌÔj¦{ÜÝËýfÖ¥».ÈjT¹öƒH©ëp*‘Èÿ\ýeõÏÕ/W! …^åðÿæOÆgZ‡• E–juù°úÃÏ2ËWruy³ºxùöíËïV—ÿ³z})"»"“Òž¾øµýý*Ïtð«OðZY?"W^g!·¢ûõÕþûLœ]=¬T:ý‹ûÕ;tä­¾È|0¢ÿÒ7¿\¾þåÝ›Ë7¯ßu¯<¨ —9-{ÃøY'k²¹gÏTPƒ©þ„¿Äï½Írï¿Iã d&üþrn<ð;­m.sø+ÃïäðSýôæÕå›ÿüåô”˜{Ú\—7Õ¦¼~ÿq}ÿTö– Ë‚«Ÿ¯ÿ€Rãôp'þí¢7íæAq|ÐdÚ›á“öô¤Ön»>Loß+tî³V7õâïfønÈ®°ð¡ä¹…±ÉÈ.ÚÞï?Îè¤BeÎZ;ø}ØÄz™ycŠÁ#‡í̘LÕýÄŇ™7¬dªÏ«ÁöOö‡êðt(¯g¦#MÈ «OÞÌŒMH _È _µ›Z¡°ÁÏQú@ ¿ï­r›Ym£fðûV«(™gªð“³ŸÓrZgJ'Ó¬æÍÜFgÕhÿSÞ•3*N¡ê>p½>¬g·—)5”àzÅϪkP2#Ëzä°ªLýûæO ñ™· õÅXÃü÷HÔût`'¥ÚmíªÈ,ˆ‰N…ŸÃÌû:Uüeú¼u2³ÖÔÏÃOCŽzxÕû‹´&sðÏN'O(– þ‰ÚBÚÌäÅŒ‘q¤Nôžv(¡§§OFÆi´˜µ…9þìêA°¬ Yx˜®îpj‘{wùvny—(¤½þõÕå_ß¾žY×·*V DA^Çúó§ˆöq?Hè=|Qʇ¹…¿”N[Ñd3«°TÛÍ ¯¸Ðìè±õæzVŽmæ ûÞåæj{]mæ¦#ÁîUÒ^´½™™„]Ź?°ø– NjCeh¯ô9·ñ€‘Ûã[D##3m*»°¨áÀúÚî‡Fe>r|9”ïÁt*wg¶=Òf%WëÛò½œ[ÿaP«þSÿöîÔíÐa9ap&†)-ý¾šö`D…tbInç,IRôñlH@Ó,>},ùªpGùÀQ,9ز àÛÀ½"aÇÒ±A ¾ºV¶©ŠÓ˱Wê4Tð’”­Í¡ähÓô P§ëU$©j¬€&A3†Zé Sù—Ö«l Ó&Ua-]lþ¾„;=8°MÅØ6]-´M=ÖшӠVƒA¥›¦£º× ›M =¥ÓlÓ³&dîêšRô~ +žaBb±­×=T±Ä2£ôˆ¶ òH SÑx–¤¡0§j4EÐëÒK\“qP®]îàAQ¤ ÓE´†¦>‹m‚¦q¬í×¥UIßjŽÕ=ƒV,tò)«g*¨h½le6øXÃ4Á,°Ú²$@K޹BUТ f)ƒQŸƒYê(FYn¹ò¡>·N®ýÇÕÑyÓö@=c–ŠySÜ(cݼU*ÒV> 3 Gƒg­RÒ|ï!?¢Š9«4Y—(“Yé¨É§X¥"jê*̯ÄA#Viš’†íÓ+qÔ¡UÊÐÖð=ø¯±ªÜdEAš§«¥®Ïš˜+ ¯ÄøôàFl566!P?²bŠ˜Ø ÞP ý«Q;\^ Õç6±paÎÁà)(bo+^´6·™Ë¿2±uãÚ@a–›x±Zl¸QP¬¦OÏe<ÌKѺÞïAӤŦ1` :Ì/áV$–}fgEVpXp²U¶¸ÌZ›É12¼ÇJj´`2™$r2ZX¹ÖDƒ‹t‚«OkM,:ƒ/cIY[o!ð‰R:½Þb>‹­·¨ëeŒ;üKLwÆ{\¶ï˜ô¸\%Û\ÊÜ çÖæ’ÞFÞù⇘§b‹§ûjÃ)Àïª-¦C‰Õ3}.ü&õ¹œ)`èä"—õUsÙ%…!Xî[xMáŽûèŸ)š¶>ÇÜÑ[<§’£Ø‚Z"¼fÕ,H峜fÝÙĀߴ(Äd×Áï=8o‰¥Ó²&eÒB¥B…Š'œP Aõ)R°*œ£€‡µKÄ ; yŒÄÅì͆Wö:(1JÎö%¯8[¤Y’ݬÂ#,_ ¾ el—˜ ŒÝ'‘„®aàz_î`qÛ^†©U­5÷@é˜[ ÖY£Wì›×¯_³èÅöOÞ8 w©]XØ¥°*tмÌLj5zTà¼ãÝ•7àn®Ê댵c`#³ÜxŠŽwe™)ˆve„U…g¿ÞL‹Yø|ùwrÐa½¹žíe6ŧ^&ຆ¢¤ñ… Þ²6Žv¿—Fs&’B~àX‚=/}yÅÿö]ÆÚ;ð‚¼,¬põÏјßv‚÷#¯¼Dç…Þ…‹P£=¡&¸ÇHèsÁ›÷Š™1'¹¤Ó6E˜Nµjd¡ˆDs"$êq¡° ,Á¾ÒEè°¹)´‰­‚†väÓµ°¬6ëÓXq`¶IG!ÿ|¿]À(|‘µ£–66ë›þüy[m,M‡•t°b„ÛµÛU‡»žuŒ€Ô«8py¨®2ÞŠVXÜ—¿¼{ó‡nU/渎…¿;ðê¥ñ´4¿²ÏXKº¾ Ò9‚Š_x¾.0Ž ÐO,^ëŒmp³¿2MmðEìv÷û<[Û¡ooˆé¿Ù´7³²”e·„Áõ°¹Œ”Çr´$ÐŽèu¬%_ß—W‡]RÂ6FGØ·žólkйE,‹¬p–‚m½ÝT¼U Ò&§Cî<¦}\`…¤ ¼¹­6e¤­dZT³ }¼igþø¼XT˜…Ï.Ìïp¿0¿0î ó ’’Š™Â|wÒN,,Ì'È}^a>Eí¢Âü~4¾-Ì'HH<›Iæ¨c\,,Ì'˜}~a>1Þgæ×ç‹§ Lïc·äÔ;‰îëÛÅ8¥¦ª.û?›“´-*l9Cv„H]ßœc$ÊGJ1d€ñb2‚Àfó¡Àè±®‡û-ɸuj‰ˆ$Õ"w"BÀ·WÐq„u²îR‚Ì\®Â7‘ ›ÏFüuÐ߀‘¾•˜PðZ=SLNÀ߀”ìPo¾˜PØ|FZ19F¬ n¿ #ö³9Ù• Ë»s 2 †æçXóí»^c{Že±¸‘+²<Án=”Âôï ]β ½ˆe1¨ñC–)X’e‘Ú$Mƒ–»Y–§].²|Â1Yæ4’id™4îÞ—Ÿ9Å”EQ·;¡ûD fÊfʰHDœŠD´ àÚ•««öüÙShUbð}Tí¢eN¿¥;qΩzw(㺃‹ªOA±¹Ñ0¶ú˜Ñ[²ÂŒ(žmõ!ŠO´ÂŠE¡~Ï M¥¡°™Ñ“ZƒË%)Ûþ…X¢eް¬Æ“Xª¶ªŽ¥ Å™ñÓVÊH õ‰×yBãífZS¼r€ íñÒëb8Ò¹•{Í :Ÿ9é)Bêp + šËºY"AÉ/3™ãÅH¤ mª>•÷_XP«aEAW×åæPÝ|aÅ?QïäÆô°¹ÚrØ5p²îºåŒ7M³ËÕ¡|`Õhj=P°iikVžòhSÄZ{^×'¹Z`±´9Ëtn‹‡ìÙî@‰MU–dA¶6°0| `ëhÚ§¶Vo±M¡ÁÃÁó‚'pÑG‰øíbŸX9!$ÔEúÔÈïÖyŒ¬ÉIFzMå–”¨i2­Š jwéÃ?Ÿªëû21K;àb_b ÿóŽU¤nÀ ·JQ Ûû´,×/¿öäw«6¬2uƒ÷„YJÒweµã1ëx5þ+3ëù¹Êý#ž úÈ«T·9lIk«¯Ö^îÁ*L•‚ôí/Cü‘ÅÇQ·aY•m³ªÅظ¨ugóÇêš'$X;í|÷ž±rþ%!ÇÁ+Y›óñÁ-£÷÷Õþpšç‘ÁÓ#JßxÊ`²¦Ñ}áÀ¡,´'¦¡©Í¾:À§Ïa¡0ð p]õ_×ÿ‚?‡U` ¸6=Ö›Ãuus³ÛÔ‚ôþf·~(é9$ííÚ×Íõß\°|±~<®¨9.ß$?üÈ#AÊSx\Ý#¾ÐY.Íñ_MºÄwܽ š ºŽòùêAÿ‚–Á;¢Í¼–´`AXvvlèrªÓyûö%ýMƸ½‚£l}ˆÀÖ’­3]ØãXtÕ×=ÁŸrIÓuQùet‘ik¨Q½»|KËÊ ‰¨`ðØZVþúêò¯o£Õ€&øº!û™‹„Ï8\¹—ÝÄhÆÿþæÝeú÷í; º #ÇSÀÊ.;²ÒâF êô®¦mäöÕ¿xk а0n¿hN,Q ÖCOP»ƒq;ž¦jÁÄXoyÄz™°KHª­£Dʦˆ½×´¥ÀçÊ(çPAr£;Ôɽj³A³™ýÌÔňähÏœŒ›39°]§qàëê yÞ:Æ3FR‚ß-ã­b¥ë1âKæ*¶°“ ïÊûZÖöwÕ#o‡ï´îsù䊋¹†×s¨¯¶1êXÞyÒVg1”‹uuñe?_<#nÚy7E!¯?³ \‡el¼¢ ”0­'ŸÀ)1Ö‡s+Žr=¤¯»¯°x›…Ñ`„[ tÐÛcã€59VQ¼~dÑŠî0ò%D¶LT “øJ·¾À³SfRZýꌙC–§j¼ËÍJ ·gæÌëƒ ® ™w>Ž+.nwÛ§Ç:êý#‡ŽzIHÂÛ‡7½ðéÕýÓ¾úX¾¯_”$r±W˜VÄæI¯ØS4®}‡àL£ûª¹ãx’POúªQié¾jƒ{ö«&KK÷U㸿'y1ÓüHsMT\”<Á*ï(f¿,—=q lk«‡ã5©¡N–˜àƒZYPÙ°%Ф7V›ëx}M+t¬L7Ó°øJ‡žQãV¨­7õߣùëÏk,ýI2îGÀÌY›p­¯%Ã+ÅÛ#L8BŽ/šùM«œC@3 XC1ðr“´øF# ²nN`VkN!×õõ'è-'t«"ÿö9ÈA•œÐĆaA£éO=Õëe2© jêóÖ "2`\kò»’ô"uòËÆ!Å…ÔyÎaVÞ@ˆýgNÜ V’ÒÔÔ¥J§ˆ°Œ‹@m[¼ì3†2A?+„@)“KNð°.X1*P¼î¼Z´'ɺÞʃX[à$±‘0‰8?ylm(IÌÙ&ú4¨W™ËIu2WÅE+ýnÄà€ tIܸw%˜\x8†êç…¢±SŽVèm’i>ÞD%l¢Ä8K?k<ɯd9–újÏÚBmÝY™˜ù}ysàl¢}^K¡F¢çÅsxxW¹«nïœ}TÚ ÕÓu ÷¿¡‹ÃQ'XŒ}c‰Ñ–klÈ5W‹Do~ «x9µ6œÍ¬xk %¬¬ Ï ‹Y¤ò”¸â…+,f}Ñlþñùï¬ýÏÔ^ Ù„/û!â%û¸r!-ΞY§AÁX)Ií‡íá°}X„+Ú­%dØJ/}Ýž—W‹E¶JÒ˜ =ú>°Z¯Çû삜e[Wb_ÉW0–-qPJ;ød6>àÕ™Ì,µkÁží¦0‡«6™Y<©â,Åì¾¼Ú²D㕎âõ¸ÀíD?¸jÛ ¯óÔa(¸ßnßóBShk õ†ËÍéÿ‹D÷F]·C~f"}‚ªÈœI›ßI>k‚Òe®«X>÷ÊÇ]yU^cß-úaÊ;sŸùÔ@Òuµk¦?gš¦¾ZK¦Msý¹Ú¿ß—‡x…XÊ<ëe€Îœw“Ò°ŒoË÷’7 Š€în¡ÇÓ‘¬à©‘*“® Æ›ärGû—÷h(R¸¬à©qy欋ƒŠÚJl6Vµ©vÕ‚òëý¯¹|ÿ÷pA‰…—YÈ%¬äC'1hq¡X\ŢȚJŒÄĪÖk±ˆó XÜÅ"ŠVÈH,Är±˜ ‹¾Xüú>Z'eáÛ„qIefÎW§¿ª¤²_“iA‘ƒ×u!æ°¨ÿ•H¨Ùž›<¾ecõ¤öi¬"³„Ã# X é¥ï½dhDª£—8ùÝAÍ|Úì3˜ÍAÍsÙìtx«=¨é|—𞪥j¨ß'©Zê ¦©ObMòT—w3oÁ¦’®Ã‹NŒÍ•9€Ž=£ãM Ë¢dÏèkµëßëäy”ÚGlÜXî˜ùxl¼Qb¼‰…)£Ü&¢ÜHRŽ.,1§¸†.R|3ÕçxJŠ$„ýìÖ†ö±®Qg«fçâŸ~ˆJ•¡¦‡?C¡â½¢Y–¬+®R³ùÓjþuŠÜsÙ|º¨ÜGc 7KòÒ§¯òLSÚzsîäFíaüƒµ‡eN¢²—gݧÄrÒQ…n£½Dô7êYÿèll«Û«ûoHkª0Ûj÷ê>&±W/v{õd¤"q¯žiª ˆùÏ«­íd#WõÝc“*ÊùÝo¦h@4[íyõ}¨çëÔùUœ¹wc¶dY××äµ “#ØåþjW=–DªürYPDÜÌÃΔù° Ûß›–Ô„‹-€'¨â9U¤µmé<ì£ñ±b)Zðl¼"el¾2•f›55 jIj=Q¢\“ä~fZJ9ld$·%7 &%•7Ed ø «1X–"«*$ÅkJDí¼RÔ®îM8SU,fSÓ€J s Á†À#Xq<Ëo`Þ—ówÝÌy)ÒÕù-bÜ FNÔGQv)l,qQŒ’A²x–xÔÆS!±)MtÈkÞâ3Ô¥"…nÍ ab=’Ô’üh¬Ì™ÍM؃>£s¶¬vá8ÿIç Ýúþ~°8y•"à\õƒ ¯fÀ&(êsö ¼Á’Ëxûá@py½ÕºîÎZáQÍIYð›fƒDì8ˆ¥éQTXÀ;f‡DÐðx Ü‹‰,k_ÓÉ#ÔŽßÍ=/v–ü“âvöRÖ9¥™Ã|¶W·²ÐÞÁÆQ.Ünx†¤nmÞ8·Ì cÜɽ£¸Ý—‡xäâÎH.Ó–¹E‹àöú˜Z˜ ¸ÿ’Ý nóÊÄ…•!“äN‹_ˆX8¯v®(~'±m‘ÜCVaæ7†+Î.ŠYÕëÔQÆ;ÐþnûtÍÚ‚Ž%8…rzÓ ³+ ^Û"½¤PŸö%¯ð¾.G‹}„+–Û7£ ©œ«)>Zv^—‘Š„æ’¤ÈÊ "{C†1|v™ö‚/ЖnP¿ZzÆÊLc"%NhÊŒ×ø®“_0ü”,ÎÝ;”|Pï qT1¼vˆÑ¯¾vHCN¸vhîìf{í¹v(ñ8k{íÁÈzÃ<ºÙ\;Ô¢Nº'$\;4sÊ¿»vˆàbÇ:ß];D€nèQ×a»¢4½³V” mx¤67˜gn2šãµ½É(ác¥Ÿyén2š‚ ê&£‡m››Œ(z¯õ“›Œ(&蛌ü·ÚR…æÂø”Ë€Þ£Õ28JÃi€1ŠîÍbæHSú íîHÓ`:ô¥°‘#MbáÙc…­áÇ=ÄsΟ^"º#MÑ—´G𦅖5Ö1ðþ>q I$=‹TFÄØ^›ƒ§b¬=ÏÔ‚Šåg#ç™Dwö˜˜þ÷,Oâ(¸©KŸÒ>©¸É€„K uëjÂÃ6þ:¹dôáÃRMœ.‘1E FË ÎcØÂ“ ]‡IúâÇYËÙeÆôé$,÷‡í®¼fß—€õ2Ĩ+æAƒBg•g•‰vxÍ’ŽÃŠ”ËfB»…‚ïQMò|wlï–P,=wk-M1xî¬Ôx}"]S‹®Vç/žå¹+ ;« Óë_Î4Çgã÷÷ETšXÔáÏúé lwدÜ=T‡C⺛ôUwy¦§Æ¼[onˤpz¬Ù¼E¥NU˜e"™­ó7Ë€[YÃs§XøN°€9¡9í´À§Uè}â™+Ý„`Ïö®Íêµ…K+‰ ©W2(øëd'~³¹®0V½çôhÎÁòsNŒ¡ŸÕ² «ù0ÕD€žSéä0›¡P?3ª¾ñš: z! ):uμÆ[KÑz³[Ы½Ç+&CŒ¤R±2P’Ÿê°å\-ŠÌ‚J Xå]-€†ÑãjAÅäNÅÏÕë>V¨Šb ­Où­ áÃå2L´Â°Y,W+8¼í÷›(…!ò×Ñ QÌ窄(è³4B±S‚«N¸‚­ú÷b´ú€ýâ÷b`¸3Ž[f‰g蕯ÃPqÜeæÇ—#C(jt!Æ+œ÷ļ+ º˜‘WNGÓ1#±0œsô$$žwTÅ·í³|zÉ4f»¦@$ñßä9؃x纫&Ï9 ¥Ç3òœ‚è‚p‘˜öX&P¿V×/©M¦Ýl´ˆ×q!dN÷àÅWémãm}KO|Ðà ½ø°ÞÏgÄ\®ÜP„ v$±°EWnÕV,; ª”Mfr)nø%ÊŽâ–_¡,³B ;Þ™ƒ«,>Pqñ‰àT¦…œZç:cÏ~ŠÐ«íýÓÆw"¤¾YÞ’Êk´€wÑE°ÊîâÎéj@œ‰.Ï•J¥3#%™ÎžUU%¥:5µ·_%ôfBu°ã0kPÅ •rR *@nkP ð^ ªXÕikPǸ"¹‹ãL ª F» •º[kP ô/jÖÖ FAÅ uµ¸Uv°bÑ•cô5*MÁ(AÀÙ‚QšÙ¶`ôë2ÛŒÌ~‚QbÄÏ.%p¿FÁ¨Ìê¢x½h[‹õ~_ý«lvVª•>Š_÷.ñìLûñ`aP°`œL)ÏK»?®Éаt-KR&§­e!À›Zn¾kYZ`ÁkP:Í74µ,ƒážê.þ›yŒ¡©e!8> >> endobj 42 0 obj 65 endobj 43 0 obj << /Length 42 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»åšr¹äÍB¶Ì endstream endobj 44 0 obj << /Type /Page /Parent 4 0 R /Resources 45 0 R /Contents 43 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 45 0 obj << /ProcSet [ /PDF ] /XObject << /Fm5 46 0 R >> >> endobj 46 0 obj << /Length 47 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 48 0 R /Filter /FlateDecode >> stream xÚÅ}[³ÛÈ‘æ{ýŠó´!OHeÔ½ªßÚ=ö†"lϺ[Þíöj£ƒâ$Ìð2ɣˆüf‚T—ÄéõDŒ¤–·‡¬¬¼Uæ?ïþv÷Ï»?¼¹K2ysWÀÿ~g£4&Ý…äeáõÝ›‡»ßÿIÉâNݽy÷b]½ÿÝÝ›ÿ¼ûã›»BšÅ@Qõ«;—¤µáò£ëüïR¥˜‚»{¸Ó~÷ô6w?ÁþðFtW൴ƷWð¢zøÐ<6³ä€K¢ýò¾Zßø mLÉ\¿¥–…8½¥•^Þúioe¡¯Wøú/ÿý‡×Âù2…’&†«ú÷¿ÿӛ܃Μã¥3×?ó?ÿøãO¯ÿãÆêLÐÒ抎¿Þú÷QKÕY˜’öÆ«8¥M‘’‘ï~ýSó¼ŠF8¹ŠI1ö…ÃY(ÛZ¸Dëç½R2úÓÏÃ?MEhýA… µJíŸÇç |Zÿó 6óVª0R9X!ˆ“†'!ßÿøã÷Í«üM–‡iÀ¢ÙoAª_/ànoƒ BÆ5ÖP¨Çe Vk 2…úïêß( ÒDŠZT¿Œ¢ ௽fÖ^ÖúëtH¡‚•Qyêõa‹ÓÛ±ÇíõjµHÕa–^­A€Öp~$G­¶Þ b2­¾VÒ-PÁdƒ ðˆuövìh |-RX׫c™Å[Và Ká~Øí¿â•Ò0L?Øc5³O°÷åa½¯Þ•³”A*¤·Êµ°oìÛ ê ˆÒYöÓÇQÚ ‡ªÀþq1ƒ*õÛ¡Z¯6³”­I³Z b½‡òx¬¶FéÛžY­¢‘.yŠ‹]t„Ñ`)Ð÷³äL¥ =*'PÑgá0ËRÑðÝt$ïQ©óܤŒ­¾ŽÒŒ}E±**^”³¸ÓÎIÅìûÝ~±UîüÝK1 Z!*R¸ÖåöËR2 <2Û¥ö¸ŸI.ç¶þõ„+¦‹WŽ[ص*&•_-¨°êë,n““!hKÁ–›Ã,j¸g%àöãê8O1‚?åhn×»=|µO»íý¬ƒX…>£¡È8îæ> Ž_(Ôû+*ÆŸ>è69­3°õé3ÏÊ× ”˜¥èý´«¶ÇyV>ê±"’Ô6FÃýLCÇHï~ò!Äd.po¤¨¯Ìú&äI删Ár€íѵ 'yâ‚ bë5¨†6êhS7kåG+maîˆuvý1ÅÛÁˆHÑ_¬˜o—+㤗Պœÿ0+¢á‚ĸDžÒ,R¹ Ì}«…[›å³t.è™:™Ã/ä<…›À°Ó‘âöõv¦¦d´‘¢`¶¡ ÓÉ“Îê‡O›òpœÉÓ>HíûÒ i8”‡—ót.ꙃŒÜaÖX7 \ ïoº<ãÏ2ð$½A¯:zåòˆI,D/Stª‡,¾žEnJRÙ”±à}ùPŽ<ÒúŽð0l‘‡ÎØyb”ë†^"¿Ûjž'e“ êòÙzž8“›y»  {½Ü¯Õa¦Ñdd@‡2»¾òP¦M^Ú¨2°â$Ç+O­ ÏöüЇŒG*6_.‘4̇`æJcŠ. ›­µ1ÄÜøpíŠÐÝÉóüŸ»S^H‰.êe_Ìa]5åûKÚѧE…¼ÚïWó‚oJ`ë¶pÅõ—»/çÙ:&l ÖûUÎ3ul” =÷<ê_vûrž©4X|Äjh<èçíâ¢Î+RböuÞ&.’Œ:Q4 E[¨M ›7YõÃ,fµÖ2FŠØÕ¶ú¿«cµÛÎ5u|”ÁùkvÝS´avø}•<¦ü0ÜX€ÓN£Î#7:Zċçj?3`|ö+=˜’Φž[¯&}±¶†Lr³wòÃêÛÌ€<ü8€Ø}ùÏÇê¢ÄÄìà"õ C}÷ºaÞG…Œ)R4?ìê­1˘ԅ–ÎyŠÕf·ý0/€ ^…¶*,^<y£zy8×xžÍŠb$%ÆFðøØ³œ0¤½R ¬˜*”ógda µÚ1éPA„r<ŠY¶+£¿*V¼Ø¯î«¹eÑ"ÈÚ€HÈ™ÑYP¼1Qt¼ùXÍË5jL ›Hñq_½ŸiÜ€ »HÉÚûr?³ú< E-p÷»‡YôÌZEn¹YÖc£#<øÛ¡_™4¯|Èãß«´Kì·Mµ½ßO+iiµ&º‰ŽZrÇŸcT #:†ÂE1K£·‚~Ðõ*œóåcµþ83wI¤V;7Á‚©+SXöË,!Ê$å‰ÅŠ»™‰«â俥lž•#4ú­ž”®&iV3*U½¨«™Q2­ì…DñºÝgº±¶CSÌÎp°Å“±ãêADµY‚~tÜ×vƒ˜ìûᯪWÿw(ãr®^¦`ë¿<ý® æX-ƒíÅõ~“w¾ÀŠ'X9}Ô5yÜ^Þ™ÒŒÝ傚 Ú½îâí‹ÃÛß}7JCváU᥶-ô«:Þj»Þ<ªÏå¯õsfƒOp$c$I§|¢Õÿz¿:®z?é×X—ݫՙöIïzŸTôqoÒ!F.Ÿ4û_£6aw±K‹b¤@Ç鸨Ð"äAÅ‹ogÁ›CnJ2zÍm«ªæ$‡ãþq}|Ü—¿nªÃñWÌwJü¿ÂîÿµçŸgœ,(Aåê"‰n…ÌÀƒ«¬ê5ªÉYÑ¿7åÚ÷¦uoª}ï nʵ­ÓKׯ¬R_S[ïÎ*w~Œ3NÇ8DzV¡tŸt—’2 k›Gõ®]´h%³ãÄKu® €3Ìõ+=‰ýÛY›‰x‰.²­KÓ® ÝERÞvDr ¾0E6’KÿÝRˆ ¦.Â;Ó÷óG2ùq;Ùâ[GǺÈÐOa¦ñ+êÜ1µ~"Ë}v6L}^àh¾‹‰Kï^JTºAïUƒ|*×ÈŽŸ@O¿8¼¼DÓ“±Å„ @u\ Œƒ*ÁI…š!¿vâJÚH±×…“Ê üž%öZA 4%öf±ÒTðªS,±ð}Y8"å3xÝ›€§üë±Ä¸~›¥Džò‡Gê‚:c娥m¥AfBB³”âýTÏ(æGHp$1÷ÔuÑ‘Ì4Jã¡iëÉ9Ôtp=‰RÂs©Á¶m –æ˜ÑäÂOåAœÄ°Þ<_— qN6qA’óu†ží${H$5_ªãG3ðY&™am&0'ÁN -L%" O-üéêK×°5(³ bï9çÃõ3çdEUf"Å~Ã:Yëì…¥ÀY'+F× gZàb¼¹GYÙ¢þM£#±ß‰r£üÌ+“s,t\hžÝXÉÙǘöÊ\¿WëæË@ÖÚ€—j)p¦¬ñÊ·-d‘åØ ¶± ÔÚ¿²xñNEbW–­Çm2‘¢åâ7ÁßÌSÄ ¿Ð)Pý‚òÃw¹°2i<;à‡YÛºöy…•¿ð'÷’å)Uß&^åø±b½ ÖÇ`ó"âe¾T› Ë ²õµjõïJŽ®Æ«U],Š–²Fÿ0yŠ˜u¹=îKžƒˆ%DŠZýÈÀt1.¥Ÿ‰TœÞźsx¬Î7¾.6$Ö^nx¢;EòàµaÈQú :ƒ½ð¾¸Ò˜¿ õOë'øš™Ï‹8ˆyZV›Çr ½ÿÔ‹0*É¡´} ¾Ìƒ¿fy‡‹YÌ|aÿ0uÐÔÒ‡„qÐ * pœ-ÿ•å@{´13BsâºåŠ/ÈOúd‚°V‹×H]ï!çóãžut` *9êVÖ©Š ùPðóàhÞܗ׿ Ga¢ î½xŸ‚Øx™!ófPg:,‡öüɼ™o)+|z&å #È"?3i߈±Ëo”²NÒ™Þ•i¾nO)ƒu£cYðIÔäœðÎæN ô®y314Ño ¡‡.Ƙ7Cš¡n¢‰q—üÒ‡â^ƒºAiæÿ°úZ=<>dóÕ£ƒ‚é”Ù8=aiJ/:åù`PXæ IË€ÂÖXuŒ:O P“â,ÝZf³*4Hº+ÿ_Ëý$K¡Waç­š€ßî¦0Ó+ ÒD˜[äH¿›-.e!&® ±ì!£uˆ0‰ Ž}}Z¥_îTÔ6|ž”GTð¢N(±îÏJ°2¿ ¤°Ü¾dQ¢@±PŒLdÃYbôâ“ ²³„¼ bžˆwÒvÀ:!jßWS²÷}èúîCŸª&YŒ`/]§NÐþeqZÅ…kYQÅ~7Ÿè¡'ƒ–Q—–§Ð¤“ jꘕÁÅ¡nÕI3üo²ªìÿd¯EŽ,²:N698 S¯ k·œk’å—/çzzÔÍr®_/=.¦¸@Ù®óÅPa×dÑ)ìºz×®(*ì7WÞv]áw »æ<Í7KÅÍ®ÉV ^Š,BlÐǶAiÂ/’¢ÀËÍ«“oõê¸{…OâdЭ’I)Š¥ó£Xö²‡Y‘/³ç€)¬¯#Àgm®\|!Ù@Q4² ‹ò¡«ó¸Ä XÃÁ…SûK½¹µÉ!C$ågÇfcw ç–­oÄØ‹Šžg¦olÿР?Sž³{èbïÐ+BÓ‹41}Þ…³¥ÿ*·‡ÕàŽZû=3·WÀ×Uø¬”¬@Cðõ-4âû¾aUòÒáá˜_Å+s,\y'ÀñNKeªºžƒ`æ¡\mA+¼ÜpÒÚp÷H~¶œÒÞ¦Bˆû9‘Óvýh¤ÞÁ&Ž ”´[i(-,&ÇMEk³Þ*]XﶇãŠg5€—ðÚ$ñŸyY§Óœ»ÜìÖ˦ƒüÖ¿)ø†NK3˜€Ý$© [¨Œ¼+ÆæýˆK'–Þǹè¨Xmïy• xð*’ž»ÇÍ=GñkcÀ×ÓÔ¦.´ŽN8¡^#ÅóÏ 3-Äó’M^I[DŠ•…Ì8»ät{dˆy>#ØÍ°ÉúZŸw¡Ã;°ÆQn:ð-µ/9‚ƒ4ØzÀÿ©œT²Óin]À‘…žV{ÜmÀ“—ñë§ê¸þÈ+/qÒ)òõ$'¶Û|xlžzÁÝÁôÅàçsú⌟Ï_Ìy7ù ü3‡—&A3µì¦ËK“Á –>ÍÆ¥Rø)‡1??rÊaݲFu#&jáç4ÆlZNi ülÙΦåœÇ ä…LdŒÏ”œ·¤}65˜É YŸMÍ9•APS±$æœË –ÎÛF§d…]g3#WRg3Ü5-7ÒSÅåœÎ Wï$‹s>ÃêTßWŸÏ`\¯+Ô*à¼+1t?}’Q‘Kh˜æQ·­ƒžÎh¿ÚÂéŒö«ù@sóNZÌõœÑŸ!׃Fµ‹X?·™hå IrXÅuº¨;AÔ0/iS÷€'NV¦U› †Lì=eÁfXÌ>KîÇDüL"z¨6›ê¡ÄIŠ’×½ÁÊɯÌMøèàëÖŽE¼„Oôà “ücJ懛‹^ÃÖ”¹«:1ÝÓŸ¤Áž"çô•ÿæ÷*ŠFÕ“‡göý@݃}?vædM²¹`ð_ÃÓGò§éoê‚­.¶heMHm$p£\¤Þ€ŸÚÀ!ßmõÞ–ImhªÈ“/0Ò¸"ç%y}¸%¤œ;™ˆ] ýêNæãv½{|µˆíGM0ýYp›Û‘¡¡-ìá=¿@µ ÁM¡š'ˆÜ|ÞI“…-ù¬&5èO‹ÏZæ³íWÀÉ)bfd„Ev´·‹Ôò÷+V'¯º³\_2›«vÕ#O)€ú7ž¤þí‹5K+h ‚o(ôëFÖó³{8ÁÝý‘ø(ó¾Aò7¶/K9\tWïNå“Âï|/£Có€…“Â ìt}‰å¿ãpJ6~[‚›–ƒÁjÖ¤@¹yŠ fÜÃ2>zê†Jj†ã2`úkMRÄk×d¤Õ/ÌúR¬óJ–Z7ÝØ}¬[aìiÓæñ¹ p¦L EÍŠÕ#ÂÊZùP¯U1b^ŠrŽÞ°Ç/e¹]Äã³WõåsZh´Â…LØ]ýŒÞÙ¸ ó"ŠMý-ç :L[Í?–¢çøqÅm€wž‰`EñêSÁQØÜ®«´õ/—3ÇTƒ³0%jýèszá;ûÂ)8Ýcž¬5 G9-œ ú¼ŽÃÚâÀLRv®â<Ó8¸Úäwœ¸ Ú¹ˆ¡–_ÿu™ÑÄÚE©™$£KSºÏ¿NÕÿ@Iâµ€ó"Xí躙úË ê(Ó3]“Vyô%nIûô³\’Î.z©;ÒYðe®HgYæ†tvÕü Ò”ü-sA:ËÇB÷£ó22\U$F^¾I¸˜};ú‚+ØÕsWU?`»›²Í-úÉB7˜³ä§%(ËüP+_¦ÜÇÔC¯Õo\îcŠ:Lõ[”ûœu«Üç<åƒQè>F]6Óz«¥*}°½ º~ ׊GÞ—ü2Ÿ+ð¹e>±6¥ðßœ~ÖyĹÀ)ÿÆqy1ªë Œ½›VB4"ü|2:«yM°Ò`jž±—îþ‡Ñ5¬º!–έ;PRÃÎ"ÀëK¬)JzŠnß|l°®Œ§Ö^Ë5`T†IxfX­¨ƒî5ÜægúY–\ú=ø § )ëBJ=T4³eÅœ~ß=G×[é5ùu©1¶£û [8"Gî©©´$8¥B ha^ϼèÉhê@̸™#iqAºd=^²¼l8”n f,¹5y%:ˆ©•3{`nµðšB?”GÞLLq\Ö.æµJ&Ó¶NºèæÉËpÚÖÊ–æMy™Ÿ·Åªõ@ÑÂÍÉ_7!–ÎO>Xoˆ $x¡ °Ç‚¡Zíy‡Þ³U¤à¼+ê)Ç4d6†äçS¹^¤æKlÄßoU}ÊJN(9àÎBEzD÷þòÈÉúÇ„˜¶~>E6Çêӆנ]Á°–Z=ï Q< ºä5ý°J:k(bnd;œC-ÙÑ?–Š$/bÙÙÕÚÖ3^ÉçÖЃÒÑÉQïÀm JÇ)R(«^ζn¯(j>³r¶ç&ðÔ~š+&õÞdw7Æë:f€ˆ&] gŠë<‹dJ¹Ø{71ÄN«æ±¨›¥¼®‹¦ øÚx«€¿rBÅuÒFÛ‚ÌFñ-›Ã8ÉÔ¬W¤?¥ìT;^=$Y`0êü„ž ½›¡‹ØöÜvßÞ(ûÕ=oøü«)~NÎÐlËÙR£ÔÔLó@ë1·O½œ­ÄÄ¿ÿùõO¼¨‹—…1ü§€s\­N¨&™!‡¼àõ5’œE¢ûÚÄÚþùm£ûXš“þ-¢ûçG E÷§OvËGø¯ÞlÙÿÕ›,á¿_*Âo‚ŒÑ$š”ãÕÑ^ÄIé×Ñ2£üÁ`G¡ó¢ü ø/+_:Ê}¿žù¥3£üZÕ­û pv”ß‚‘‚ <5ì8PõÀfbõì8?*CŸ€€çPç4E 7Îo¼Tšff©8„Mï1ËÄù›h9%›ünƒ¸kq{eJ£Ë#'¢í¢Ûº`nÛm#Þh&–Î Ü&lD€!Î ÜbOÓënùbzë»~ÄÒÙ[…ÕÅŠޙʋõáØ&ȹą9ÍGqè”'…>Óœu ØvÑÅȸððüc¬6ä–} ’É%T,É)TêoÏVƧ_£Ð…m!æEXIƒ|!_b~ýÓN®P9ƒ-í(jê(7Ë…IÒhGÁ×Qn– ƒÖáµÀ̼Ô#ŽÞ`Ib^¿ç•äXé Î ƒ¡Õf ’—¡8ÕpâÝÌhjõÌLÎÃÚIpîÈÚ¥‹3-›ü%§ÃP£%ërýUGŽÁüŸT¼iÂQ²‚`ŽÛ¤ µô8£,+ K­ £(ü«ó\L÷ÒY×Üg[#€½€“rˆ¥¯wû}yø´Û²FJ8+mt™gˆÓµc^DCÔ;äÇýʳQejúÛ^YÚ-Jï.o±è½Ó&µ‰³C°ÿo˜Ú„Ò'V>fÓ6º‘Ù¼¯Ÿ6«õ2C¯ÞlÙ.ÅWoò ]Нðº¨TÝ,né&Åð©žþ'ô»Ñ HÇk©¾* ÷Ÿ Øi˜³[–±|æÈyìê C’Ó ÊÍœyfq*,ñ}g5 íŒ<Ó‰z^o\¬ t«C(Kƒñ,Å·*#sèëÍŸ1ÃUðx΃£àìGv±8|ÛBÃ&ÐK'°A5¸ x6XÃJåaË ZÔ²¯sªŠfþZi°»0ž›_újÏ«°^“¼ì¹9Œ$=j´<1Õöž™Åðþ’XûWn…F;ý¥:~äUØÁ ^¨g’ ÇÎÔ%ñz&ûÔxyÀžv½ÇN£‰—G%#ºÚ„Ð-$IŒ[ê`Þ˜­³–DãK4ÇLÙ"ó“H_í¼zöÌñZý]O‘=c‹I1§AÅ\¼²Ô¹#8Æ“èµbµ¸óà—QÄ|eÝ–ðNE~Pf4+8™L¤ÀêyÞÍ*kúÓ¤8bã¢LNÆ3x®ÉIÝMjuE‡C^² g¥¤)õ*Gî°` ê#êe¾€}Ë»„êdˆ‚Wò.¡0Q,MMÉ-m¤¿òiî »¶1)ê<Û•ô3QƒŠÓƒ7G,9ô+'µ%‰)yíˆQ µ§ˆ©-,ÖÅ\€·šZûé)F$Iƒ%‰ÿÊbæ|ÿŽ`f‘ûwĺ¹—êF2±?¢B±,Ðö1¤Ø€/kxP8tŠX9Ó‰FF4…ε@0·€£à fX&ˆ*€öhÉ¥3+èÐ "Y2A¸N(έ!ع票ÁJŽzévnË”Góæ¾¼6o˜‰YíE×¼Ñ4Ž&åˆkÞhlƒFÏ3o4 Áß †w†G!E~fÒ¾MpÔŸÚwð3"´+lr–gGÄO3QíÞ5o&†/"úm!ôÐEÛ¼™ÀH^Â_jé£ÍA×kOÂ?¬¾V,w?­»1ï=AÌ•öë–Ãb¦¬wOUrŒ9!ëS*ÀúØç1æl1bŒù¶¸Œ1ϯ»éi<öH%ǘ·á‰®ÆbÆ'mƘ_àŤ¾ÆÃ]“Ï}áEü­:š¨þo7܇S d!œVp~V÷ óõAóæ têmš—¬GÛ%K…ŒQ2Áy†^¾TÈ‚NÅþR¥B^@ê"-\+d°†.©}áØæiª¥Ð—hnÁ³v‰¤éò(ÎmVëu=mƒx؜۬6€Hê>Yg­~Þ_ oÉ ž…£–ÿž7tÓi N¢_[“+{Iudã ]tÆñ<+2¾ðe³Y ;zLåÜDwØ€Íalè>`‘þà1ÕCÙó‹g^ÕÄi§±03Ëô ´ô…Òç‡,]6g±•¥^W6g±Í)8s'kwÍ›‹xì|Ø«œt\‡Ì< ¼² ~ÞqëçÔ¢o4þ™ãüáAã­¥ˆ™5A¤Í ªfpÿˆ¥ófˆìiR¼œ×ÙÄD_Ï1'ˆaE ¦ÐŒ§~ž’3— þ¼*Hô‰ãÝzèàs˜ I•3cÂŽ8ÆÞ÷ÙÜÀiˆÃéìZÜ9ä8°sà%È©,^0‰P¼ 9˜ƒÔ€&pº³›:&‡š¾P 50ÛÁ´ïKÂ~ÕºV–¿­ƒé=ȬúmÌó³hs¿º¯V›_?UÇõÇùn¥ Zú®_m·ÒÁ©®åõ›,èVº§±u×øK»•G—ô‹c¹n%hð~Á3~Y–c‰×çm¤p™ÎÉr(µÄ.{Aï÷»ž1Š*1˜i/y·rζT~ñÌRê‹rÀqpÑ-ªÞŒÁ~•¡Á^º{¹q8~/PKçu/Gc ;àܶM&FœjKQÃmÛd•‚•¨ÕŒ«´¤ð»F’TÉKÊZ01=EÍû’§-a³*KÊû¡ú°­x76Šº;‰38oÖ=p§ÐN6$EÌ€…CKÙhZöK®AeÑñ|ã<^¿.…”Ë”Ò2 '_ã1Y¡ýÝø^­üâœ>‰FzôñNkY´éRóž.áâ°x=n“Ö$ðyõ¸MZó ¾l†íœÖ$έÇmÒš<¯·Ik¼ðêq›´&±rVr­IkØÌzÜ&­IÐÂ,ÈmÒš”Àð r›´fÿ ü‚ÜsZSÌ÷¡’Ü&­ySÜçÖä6iÍ.¸˜X7K”å6iÍ+x¢nvFYn“Ö$¨¹NkŠ9iÓSZÓ…k›ò­qiÍÌ[Ï át¬‹Áà™ðR¥˜àî´Ç®éöé?mî~ÊÜ9œ»eü§©(0QÙúƒ AjÕÿùÓÛšæ7VS3_ÀÃÄ ˜n0î\§òêÄ xÒ•Âܦ®CuV÷¢Òÿ~³Y /ž\)+ujÃ÷Ü‘Ã-|1´ü€ö‰cðànpr¢¿,~’ží£_´c=µðÛƒ‡yÁ€·w$ï·3cÏS‹ fn$àÅu‘¬WŽZý¾\ïö7N ë‡ó9†<¾˜úaûQo'£·‚”É÷»ýÃêXz™ÁÓ2™@1tù“_ã  °/ÿùXíoU6 áFíX Þ/w¿•$¡ÀÑÇ«ø}ÉR ÎÈàmÞÏÇì«w%‹0z]¡Hjn ç 7)ÀÖ"Ñ?s¨S]k(jVûj÷x`éSHo"µø»mµ{(½@Ž˜ôàÑ`_ÆîCÎVØK†jGsØ@Kæ±\oÕÐ`§°ç<õ„—œïë4X5Þ“¢¿{ܯY¢ïfRµøÕöžÅ ¶i0$ù;ØY{ΡxÑi`“À0e@Ö­`qÔolÀ§ È¡À«Q†ÂÞ–åý­Þbc )Ì0DŠ™ÛÚ~‚\hjõõµ‚÷ßXÖ–q…÷b`øÍì(“Â+¤ÙÕßO°¿³Cl¶¾»›…_ï6Ð8Õn+é\äs ‡ÄXêû¾ùÈÓ E¬ÇOï°Ù5[erýb‚fs ;:w1¢–kXé;Ø]¡öó[wukÂãS0h07)ôÎ…1[©ù¿ïÚ‚Õa3âI©E[à#§ÛMÚ¾&`ùRÈ<¥Þ¾ï¾qö¯IXd­ñ Ç/ÀEΠÂNûøŽ¥Ô°I7j†<+ŸYJ çÛH‘RÛ8‡ï8Bo­‘ÞSÄܼ(8bùŽÇ æy™¿}‡l8&bƒ¯§“‹¯Ž‡róþ%ËÒ)ð²2)7·®qoÁ|2—åOHV Sã@p´'­Z¬h/5š9yðÕÅŠ õ”`‚VÍ?[dXý¸­Ž<»Xcwhå:ïO¶Yž•AggÐ4ˆ^ZM-µ‡.ŸóuéhÆáXÄXºoð~ñË ÆJ„ä©•ß6fiÁòK‚¿Çä,OÁÉ„'^ž®§€—`ȵ3#+˜7Ã+þnuà…\ öå‹33LTqÏ51>3ÎŽ£óÎê(½¡VÎÖØ„½¤IÞ%ïœ>ùyVÀ';ð¼2ênˆÄÒ?³N$cd´î&íŽÈ8ÿ€™ÕžG Nî¡å}_¾µÈÉd1P{ììË횯Áyx‚œž°°¡“B,Å¢&Zø5RØûêÃG–¦»º‚—WÁ,˜”é»|&Ö%ÑÄlVïvûÕ±_›‘ôÅ0tR¶õqÚíï«íͱ­cD¬‹t‰79|;äkQÅø4U”Á˜ÌÄðý€a›nÉiuæNžžO‚©w"¹z j±äÞ:lSe2''ù»©e ­rQ,\sAX{K§n¹è¿¦¨¶.r:¥ÕòÈ¿L˜Î œÜ…üö|^‰Y„`|Þ ™sï¶5XïP')Ê/õ5kGò‚GVï\Sß *‡ºøò«Ú©“.>5˜WÎr–øðï'É#‘ðk”±°²˜-ë§+VuIù×ì]$.È¡…0o‰›kÆËjg1ƒ <7\oÖ¿~íüïg†*'_wgðòTÓ_åé%~ÏPØÁO ÚWÛuõiµ™rxä·ëù ]}@– L »àá ^"~£?s,ÀªAûÜ·«áÄbûä€UCJ`adáݤ¯: /¡ÀùQwûfAyAG±âRæˆHDÀ‹¥Š‚gæÒë>ηÐEÆ—çì^…׸¨Õ3Ãó:Ȩ~råË-K±yô/cóˆþÍÒÝ áiÓ“L}ï“úº¼ìlÛHrÿ±ä¥/p~ ÅË“%ψµ¢Úñ6RëϨ1-É€-@B~™¢²àëa£víìè¤vèí„Û…Ö³+éC¨+ÖΙpxĽ£ˆý°õCFæ äcôä(xͪ¢…îEËÛ¿ ‘ɲw`ñÖR‹ÃMöúº£åº»ŽóͦÆPf¤ÄpíA =ÅKê;° Mac)×ç^Ì.ühëœÔJØÝþøq[÷¶Ò›}Ä9&eSl—x%ËÂÙ!ÍSÄØäѳ¯Ü[ê5îK¬;Í™ýbJ¡’ºèSuþجÂSa½•¡ ¿óÀn#V…ktÊUS«Å +3«+¯z>Õ§nž—;$ƒÅÖkÑÕ8Ö§_¼ÃÎÿ…o¡‹6ëÿàÔZ;ÎO$~Å<ë*ô@óöÅ¡,‰á¸0ÓKÙ½+7¼¢›¤ ©ïM|û;É aT¤à¿gFG0ƒ…m9†eI‘o£–~«ùõ˜ÛˆI”š6xGàçßFt2‘"…kD)WÏk"háQÌ×B?/xu8%ж ˜Ç1L»´ŒUö}¹¯X¾8Øþé›.[H˜t=Ü…Xzɻ٢Ž÷ëð:BÄ©–Ó¡îÀAðrd^ï²Ü@O-ž¼U:¾N¨¾ •“H±„Áq9™À¢´½ƒïËÇŠw½Ë`SÊ,ü‡]É»Þ@ƒ«ÐAC‹”Zœ‘üÚ¹&ªÂÎÅ1Àâœ"9œÈׂÌÈ–-†>2ÞD™Å˰ŽÄKò-õn’,mPT~ÀÒw=U:…[«i¹þƒ=‘óÄpTè{+kV˜ù geñLÒÒ\ŠÏƒ¯w¯±Ú‹ îºù´ÛÞ¶7î®KÀxÊé ßu Ø€ÚSà7»1Ú½T¨ØóÜð»)`•£2ÔêW¼lo¬ûÿØÜd/É,É ¯tÕÖwŽÃ­Ê½ê’Hy¼¯ö§ëö,z0¥Eï&+ œÏE61 OK'l=¦ÆŽß7£B Cy£F«)p]fÉŽ44x³Y©¸˜ol·U¬î«‡P·ÐG–€ Zª8;4zŠ–+;[Ì rXíZð‚©Úꦅ–ü¤Ü«V(ôO›Õ–y7¯*\¨£ƒÙS.¦Ô‡!ÉP&˜=%RÁzòû˜90åŸCèëÆ=—Ðã-»ëý*æD³É‹åxo:>“Ôã½ò”Ñd‹)û‹éñý)'uk^)¡‘.ÚÿnêJ1Æù†³–À_}å5¯ÄêaC‘SòŠ,ñ2‡7äÊ÷lu©b¢Ðñ&õ=W]âv‚šϾtJº ¨ÅsO’óG½U˜Á1¢”’Šbç%¯¿˜Ç^SËßîx¾ÃVZ$ó¼öJî™D# &=“ÄàT„¤=…¾ÛWà‚¯ñòU°Øj¾®xô‡-×À/ÝÏB÷$8×Ç^àçÌŒé÷8Ü# \*pó‰xɪ[Æ!k>GN9ÿ°_±¢Ã°_k5Ÿ_ùçêøÛ"J¡qÓ†²úÊãZ²ÂÃ.Õ5ÝOð‚½ê;e×ä†u†`Áx"y_ »^´¤>Ø–ëòpXMj©ÝLõ jß²|pl¡¬ê‹¡–’ãýÍFeâH”Ø/=Ýðj´¬“OÂ<:¿Ó)]jðîtP¡‘‹gv:Ø/Þ’¼ïy~x×I^>T¼p.˜ (”ù¥óTØe1’sV}¬¢O¨ˆó¬¼ãµŠ·àÛ'’•Cyä¸(µòäNzÏ+gMu1AÌñã¾ä%’’!’Ü`Ak€áU¹[ìÕßÁ Ë]Z§yr»23ÈÎc"?îþ¾u—1[CaXº&ÂÛ?³œ)cñvŠoÁ_-ÿ^Gh˜–Â~Éë %à7ØbJ’woÁœWÔº¹e|Ük ýõ{^À¼n•®iY¬Ê|i5),ÜòO«0k)øŠy€2E1ëË'$< cOlxçªÁ*ó@¡Ÿ"òó ù¨/KÑÂ,ãƒM깑xÙc臘YÙïŽ8…UÈç¥väVbøR<¥ŠèÄkÞ‹%0–d§âű´¯»H>‹Ì8㤣¤l+›÷ꦯªOÐ:.G¶ÓÉ÷ *É»V¶’.….9¬ 5€ã䯰[×*x5ŽÃ=ìË~â±p’y Ð?WÌ È^šÂ´Ð¯Œ°/nÚ8\/6Æà!Áú»ÿ,׼Ʃà;ÅtyÀ²m-Æ $5ï˜i©(ðúaæˆ>!RܼçÕ‚ûº®Œ\ýïü°õ œ2ɪ2–âåªoáÌbGPˆ†ÔoÙùºœÜUÇUµY¦¿2Ž ]¶< «ƒÐc=a/Ýw‹ƒÐ Ì£sû4×_ Oó™wßNV©¥ó5Xgê)ü—¼‹JáTü’ç…éøáð¢Úίüdló¦ç`9» }¹¬1—{®à Ñ_v½Ù­ÿë óî"|\ìF ¯ ·ªo»÷5¯Xcgµð/›d $)Çýj{ج¸µ¬çáE;Ü»hU .UtË^EC[>bh2‹Ý]ô’W$ŽósÏY<$¿&ЧReŽfÀnÖ¸y»ì(µ‚ùåOãFäêllp7Ù‰+˱óIžÞè¥T`ĉ`eRµ ¦K¦A¡?°º9%ýs =Æü±= ñå–YÒ×hœ"Ö®Õ¢ù"œkë0Èzïߦ9TÇŠw›æYɯþ3/v®¤¶‰ÂæÍä ©âNÓ:«$«‰ Zó¯ð×ݱüŽ7w of»~§¤„;wì4rœXþúã®Zó\«•CxáÇÒAo õgÍ,èW•xRc¨7È´óœCœûbÔ¦r^×¹ Þ¬¾z¨6«=7á#O˜Öh=×öΗ¼W'Àó#ØQžZøã‘×Å"ÖýHÞ?lëcq½Ú7ßXQ)8•×E÷o HŠšz÷%³¬ýg)ø-+±a± ¸B3³n²‹k/â|œü7Öi’lݱ„XþÿرŠs [ÇÓð/åfó’U«}=¤ô ÿÊ”Òð£,SÊziœ&?-¯Ì”¤TÉPè¯yÅKÉŠ˜Ÿ_íWß–ˆÒá] Õoô®\=ð²pø9þÔÀl¶Íê P©_:B\ݤ’XúøÓ難?¼þ§€³, ÿìê!îr†üƒ¼7§Y Ä `|wäÔ!êA‡MòW÷c§;ä!J[¤úrý±Ù˜¶ŠZ9³/ùº¢•¢…טoÏmWî´ª«‰‰…sílãë¹oúžwC0ɘ> >> endobj 49 0 obj 65 endobj 50 0 obj << /Length 49 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»åšq¹äÍB¾Í endstream endobj 51 0 obj << /Type /Page /Parent 4 0 R /Resources 52 0 R /Contents 50 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 52 0 obj << /ProcSet [ /PDF ] /XObject << /Fm6 53 0 R >> >> endobj 53 0 obj << /Length 54 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 55 0 R /Filter /FlateDecode >> stream xÚµ}[#7’î;…žåƒîtòÎ4p¼ÏŽæ²c70>˜6 uUV•Ž«¤IUíž_"ò"‘™Œ“©Ý¶Û6ù)2 ?ƒÿZý}õ¯Õ~XUEe䪄ÿµS®²ZÙÊ¥«Ï«¯ÿÈ‹rÅWîW7ßþüÃO_­>ü¿Õ÷X¤³0¶°’‡½Å©·*º¾§f^_ë Q ¿ï͆íýßrº(íÛ3lÿíTûŠܪÿÔ<ÐNJ´ŸÂ—%´ãU Ï~øîÃûëT/e Ã]ø+?þð}£e-JKŽÑíæ¾ÿÁ²•cŸa¤yÓŸ¯´v?kmuûŒÿ¡à•«¬^=¯D+ùù_=­~Zý=6ÖÚ >M ùæùþV¦-ÊmƒÅÝæ¶ïr–²7BWÁ»PHB ªV!Çý¹ÐEbhZ•øa«ó?0@\U£þøk%üŸØ7òñ ½R`h´²jï<7æi^Xa˜…Êr4i¾ý=Ô3_ø2«AGj}˜FeqQ­nôE€>¯¿x¨,Y•;•1X†°Ÿê,µòÒ`”^ïê—z{Wo)àlƒVIR½»í•%™•*ªJÓ¨õW,GNÊy¨ÌG]owÇÇ 3QªÂ”Ž´±ýEÔè"Âyá@- ,I‚[°1e7ólLHð0öd¹¬Õ'YÎS+¬ ee)¬ßòktØî5Q³l–´ãcžÉŠª,„–¡bý™ðô%K·­¯?K£’CivÛÍî¹>^²\Fyœ²0bÄуcsæ¯e ñpÙYÇYR‚IÉqï6ûúö¸‰¸²$ KE‰M|wŸç )œ#5üùqsû˜go\¾°lrf$Îc*”°‡ã~s{¼dÇ„© m`~†|»Ûnaðê»>Œœ¥ v,¸¤ÔqÜ-šz²*$ aÄQä85Ä êìãzà²D8UXŽá —Ý|Κq®l–÷ C¯¶Þ×E–jyYÚqJ ß>=eéãg%IÝî†c–ª[®D¡qÕŒëvŸçÍl¸&uû{žfa¿$,¥úçMUØ×¨`™ÎVbCZÁ᥾Ý|”Ò€WÈr‘Bªr”‚?å-È!m¯í8‡û•8ìËî°Á•­>6;6©ôxø.Çæ@ Ëq\æ/YÛÀÞé W(¡GëeÖÚSÂqŒOã »×§»¬0öÒF¢ýp;½®‡×çÌH‡CS1J õ6K»\6»lJ-Š#•+Já(ØÀ•¥ï²¹¶…ÀØi„ÊÒ}Y” 1NSª}}ÙeªÖU°+Òr7yqnY©ÚÛÇ,Õ n ®5¥Ú\ ’uœÒmžGÀ-«0¤b[Z$‚Ì.‹k@ $0®jYËŽ+ Už¼Íh]?æ-;h^H23w“·ì.·…2fˆûïz¿Ë²0Ë‹Jð,k׳Íöx(2i2X*ÁÆâÿ#Û5‚b¦ôÐÄ"÷_6Û‡¼HÇÊ‚W$úìào»}ž½•H«ûJq$òOº¢®ïòÂÉÁzIØÜø (£D–¥P+‚€²ŠSªÍÝf[Ü¥Æð°ÉS­ƒhLZ õ-+sâ…ŠR윩Û®ÇÕºp»^B|î÷ZÛuƒ4¬¦`?Õëç,“…\Yt1\vs[o™›ka©¨ .‹<‹:bG°G*øiw›;ŸšS°ë€Ð›EBZQHëFÀŒ$ôÒŽ&À“ǘYT¹•-œ’ÉfÖ㲋¬ÃãÄq[3Ë[v æ·ê„Ì.(%ùFà QºkÏbt¹Î’j8­¿9vÖùSéB«jhf‡Ç`{9GÃG:e"Ÿl"ËÒ*Ñ„ êÃ&û$ArC¡¾åÑn%žÞº8höêÃaÕá¥ìQG‹zžárk¬„R וmþ[óä99Tøáüñ¯IšÀZX|œqÕI¯¿&)`ÙnÒ¥þáûß÷áo?ÎQ-;oV+ˆ—*J ·ëckK)ɉ°Ûç%àIW1\–o_Í^UiE9ƒ»Íü®•ï³dïĜ¨t8³ßŸgfûGp8{#èFÏ›§§Ís ‹P^,37qÁï÷»ç¼ƒü+!ØñdfÉi ° ¨o2s%À | G_å»òãW™¹º!H“Øf: ÙæŒÄaYúÝoÜX>Ÿ…II'Tv)j˜åÔ*t˜”…Yš•ÈŒXK`þpÌÒlï¬,ŒäCÍ. op¥ˆ/‰nÀpíŠ@Ýî|/6'æ"G´Ú8ðñq}Ì›¾R®ä=.e¨e†#º„= £Äý’™CæŠRq ôn“™#a\á {_ï1é-K¹•*¤2”rwûÍÃf{È›¿B°« „^ï7‡Ì¨DaTBZp>Ì JUE@—ñý¦*¬1Ô¾«ñôv»IÊÉ™ŠJŒ(ŒSrÒVaÓJ»8*»É›p+« e1þoQ‡¦–¥_fq‹Þ,®€ß_ê=OÛcÞrÁÁ„9þCž¥q\Þm µeþ×¥Þ¾>­÷y~ÍŠÂÒ2¿ËLý²`ÆŽ]2³\¡‰ KQ&ÝÏa§ÍIC»Ë¤ûe!$9ÕÖŸvy¼ ¤`3Ii) Yjj×ïò|™g£(µn2OíTU°ÉKư W†ªm}[ëÌÍkOͳ7š?ùqü“K?[ËZ†,”q¼‡¾VBCå Ã1ðÃ>ín}^šÍŽøL%FØ yi…¹T,W-mÊ‚—ŠÒC6-™_F w -Íy“SFØZ.- Ke…œa¾z£îQAe)ØE´4RÞ¼4”™åÒPNNXÒÎêýóaIÞ—X­²¯S¦1^»j6,qÔpØØœ¼/ˆ›\–·™¹ `gʱL5P³ö®‚VnvÖ—„HÄQ¨ãé#qä`ùb³a^tŸ©• ”ÛæâçÞáéif›KÉdê—-ª*mNÌIýª`ãª(ã½Ý½î¹!’ÊR ƈ7+¬¡¾+J·»Íöv¹ÇfÅ&ÍÇi{›cÞý Ì‚ñ–e¯ÇÞ:ä„2š’¶[7³&3l”°r¦±áSð*[vÈÎÁLŽ {X?¿³æ†Z[\ðo‹Ì³ØJC¡þW‘y¶>˜»8*»ùGžU`¾•íAÙ<–~ê`Å‘Zý¼M!æyEþ÷.‹ÂÀ6¯È¡ú\?=½Ë‹Ò ’ÿœRìŸ25 YÅ%îÇÑàǯŠ%y²¦E¯×fÿò·Ÿþøç¿ä]%¯ ‰Š8ÞöͰ›Éô(É"¸ îßeïKiVQÐ?¯?íöëcxj>ÃÔàK¹ °aõÉ»q¯:A~ñ/»§:ƒ†dç;ÄxS2*ínvO»‡/™Gxà,¡†wK—€Ôˆ£ÿÓæééá@ˆ®ë‡søÇÝúî]–r+Ó¥”Äß­Ÿ?í7wÑE%%¶šSèßožÖÛ»"ó,iN©äñx|ùæë¯?þœCPb¤¦$/¾ûî¿U±¾-^ûÓA¾þý}ÖÞ«· ÿèÄpëõy³½Ë#­Á[bŠ ûÅäðõ_v‡RÚç¯Ó<´)*Õð?¶; ®›±ÙÓvûCX£ …$Í—Eò„Vɸ¸XIn!ïÃ~÷úòñæðñ«o’¬!œ£@ë$;Å“æÒR _:›ÎQ.KÎø: îW´¸bs7O¿ìõ‘´Ô×Cck‘ë½n^žcxÀ™ôæ$ËÂZ9.S…åd5¬ååQ²æ/= „óRŠaœùý︳­½’UA&s°Ñ,µö»ßpªõÊÙBÃÄò¿ï‡eÔ¸Œ—…´²-Föx>Á‰b®Q"è@ ¾ÂT}Ø­»o¥ªðR¯pA—ÃãîsL¤V·>ÔºP$ç´6‰j¶oßÔÌò¯;h<š­B‘úKì݉õ9È!–a×3ç2Ò.Þ µÆ$ Þæªœ¯,¼UÓŸ‚¹±Fªiyع9&­ Ä_ÓàZÀ$ ûÛúåeýžîþOºÐ@¼ÒmlÐ-Cij,“sö½„}3]–…â¼Å×!ÌvØf­ünÿ<Ô´Õâªf,:ütܽß~ƒõ]„Ñ\Ð忊 «u7§_h”û§‰æ ³t€þä8ã•leEÐúÿÐØ°_t<¥Þêí;º‹“…Á¡ó~àÏ9мK’aó‰%^ÞQÁ(¼Aì±ã^w—áoüü~O1¸ù&SÐo¿þBOe…T£ šŽû×Ûãë~b:ÀüW"Ô,ÝÚaý‡ð ðxfÿ¼yOª¶sø /ª)×ôÙ6.ŒVDø¥ƒðÜïó-½üX!`Éõ[¿ì½bƒæ°@ãµ ¿ùúö¸¹]?‘ºm¸Qø~Ÿ‡×ÍÝ”Ïç…~v3a­x59_œ/£§2Œ5‡ðÛ×wÅä2°ÅîÚ7Ãü2Õ R¸1z:c¢° ;üuB9•„õMâ|ž˜l <ð>øÿ¥WXÑd¨ÉÝþ·o&V4œe(ÿ˜˜ÁæX(ÊfGyÂHäÔCi¾L¬•àt¨–¶SˆаK0¡]n7xðKáRÏHˆò”ëêÁ>Ò¿ÂðØÌt˜Á$>êÈk½¦½¸”o´'㹕mlÁk}|œXW5&ä ¯=»©' KÙ†²D¢Ïî±2Pé‚^µ¡‰ a¼ª ~)2áÏ×¢ "×áwowäã'™ˆ1ÃÐZZÝÜj¯°BdRºVœ¾ ëŒhbæŒ5Ñ ,»Ã‘ôÕ˜¢j ˆw>^-îö¿ó<µ¤UÐÎò°¦kjvCH?Õ`RènÁlJVÔôP[ÜM•–ù}ÖO»ímä¶9ô;t1|Ü8ʪ‰fýö?Ó–‡^*Šƒ»Ø‰Å dˆíü'BY…¥ ƒæ[ÚppyB© ùïlj¥ŒCt~ìf»íìnj…‰¼Ã~Gî aõ.´§Ùм›ÜUæ4n,jJ^s…™µ6”éH/=¸‡tá(Lí¤l³jz¢è’nm,ˆ¢컉UsÚÃ{˜XÓ`f ˆ2á±Ûr©ƒÏÜ>øk2Ýœ6³eGoçs†Éè·žpsভDwâµÿ™toX÷K ZO»7¼´)à3ý— ÒÊžú´ôÃgz'¶»èC½¹ßÓ‹ ìÙ… 5z¾.Yúl“ à‹3Éžà­¥øÃÎßÓ°ñâ‡1ü·ø°[C\L†®#u¯õyÝ‹¬`%8çª ÚŸý½—ƒåžWé†q^)O=ØÍËãf¢^€•´~Ú²VÁ–® %ûTC/…°µ)mØþ÷Rè ã…ÝÕÐëñ¿'bȲh'ì¹õÇ“aј“7þàÜþý-Ð\U"ça}®€‰"u!u“ˆ˜CèbÃ/h]lôGúM¦›øìøÔð>›õ~sâ;8Ãu8rÞ8’ODSUV Sg‡çÝO»Ý˯Þoµ)^’­øô·MÄŽ?6<|¥F4½˜*]ŸÆßõ:~y©/ö[É æ¿k)yâ@~ª3&Bx?ÚÖ=üœÉR½Žºöz¿5w[þÉñlw”³Iñ‰Þâ— £û•Fѽå/ôg³^pgçª>ÂÚQrìÄM¥ú>ÕíwÇ¡O%o¶þOy'§´nqK†u`üŽEì‡:ãÅ/*nƒö|B0sTìuKS±Å\GtŒšow½š½>ﱺª­.+;ø²)ewK¦„±ÒýXcJ•0ü£3þNŠ0™“I{=ÒõÍünÑdRß§Žì¢MœôíýŸŸÞ¬½öIfݶ§÷Î^7 ¸Ž”Þ3{UYó—ð_±QþR I‰íò—"g¼]þ’×ýF\È_b~ã÷—H ‰5/Ú‹=~þÒX°5g©~‡IþÐ(Åk<ª…ä¿Â'Eü.˜¾DoƹÁúÔ~û‰8–AüíTÐ~:yI)؆¯%/ÑQü!BáÚs+"ˆ2Íå¸Ôoe…·üß2•½a ^1ò¿ew?Éè+9Ðyˆ¡–|ìð¦vt¢´ ,dšäÃÇ’ãè¸Ó8¯àLÁƒÁ›âNY¿ë>x‚Ãê'OsX÷'äv¢ÝŠ» ùúmsüBÈ-Ïăi&6)ê„ñ ³͹™¾£iqˆ29fÙûÍï&(,Îë2æq=1Ï„nN:}üOµÏg²1?PÁ–Ôïp;1ñX04¯õãzâ¯<ò*”gŠD°H£ØppGÔxˆ1°…I?âÊÐÐö§}%Vé%Þlc£Å¼´‘£j¯OS»ö m}6x'ù¥!zL¶6\ÍñÂéÀÚ6ÖÔ2æáO97§`‡þÂDšUóê° Í¿>ÔÛ÷—(A‰™Ý>å8½\€ Á&{]&ݳƒanŽð½ØýF1X…Ô&¨ÞNLÈR‚Iœ¤¹tž‹Oó(\ˆ=xïf{$×D4OLû훇m·®zŻƓïÛqtrto¥ièµ¹>q, …£„Ûãõ ñ”áá9Œ õºŸäö19;ÚÑÛÇ×$´M Dt¾!MMe°ì¡! _êˆò‡Ö„c6±ÀR,ší~ûp9 Öb,ÔäÚ1>®£Oç0@ûíW7#ôàx®ÂW0ýæÇì3cußšµÂÓ¹©ª$pãè•ØÁFGÚ ù©^ðäùœ† JðÁÓYbäêçT¼…E£d‰»)_?SS| ¤¹Ûì'èJ~s÷¨)¹ bQŠDä ttd‰œgøÉ÷3³è¹ yê@àm0}ACa®%^ðÛ‡y£Ö6µ£|ynëÉ\ËÆ»Ÿá‹Ë¬Žhn1ñ$btL»a6›´z1ÚîÊ6t1Úä(ŸÛ<£ÉL?Ç ÇQb”æ6O½K˜lÕ1ÓqOŒ’½ÅµÙ£dï)b´'¡qéÐí3´]çÝ=¦NF0º]o6ê=%ø‰Ñ%¿<^¢¥úir[O);ô)¦>«2ˆ¾9£"ø(ð>°#~ctðД<áwLÒWÏB°[bûŽîòÛó Cî–SdáLi.ª#2,Еܾµ8þÔ¼mT·ÑåsŸ”Aÿ»<ÈI?ÁNc|n>=ÄtÈý=Ÿ’¦â$ø~‚§ßƦpØœ]ß4ô~}ÀÄm[ªî¤x½ý÷Ôxáò[Ú¾ëûž.ÒØíHû? _ÇÇ2®à¶ ºíwLjˆl8§ý. s:ø¤”9íãOQäýˆÃÆÑJyQœÓ·í/Šssÿ}ÇA&mØÎJŽŸñ5êãúòÈ3¿[ÊéE7ì^¯„a笠ßmò4®s¯=Oó¶}ú˜{øe˜㋠ՌiÞ¶g©~|?2âIuÞÝ—”Ñ»¤Ž¶×kÎ$÷ºQÉÆ‹·ß-i¢·íÙE#é} ?2èxÁ¤Ïó¦yú4?£§Íri WM9Îñ˜‡]RÇÜë5gÌÃû’âØ½.IãݶOŸä~ŠcUSì,yÀÛöé#îá{C~~4Er¼P«.¿‚­7ž–ög¥åÊûî‚«ª«öp®N¢ðÉÖª= P~±p-Ïͳ3Èûþ•×½­ÁÑÔ²àüC_k)ɶÖþ­Ç/yó|çTÖKP%cŒÖðép]U¸ff)K^Å{ŠÚÁ®ê„:Y#>ŠÉ"å7%X¹~z­£UÊ.}?ž8îX¢LÙtœÕgÁT|+Œ¶ä ž&/ñ6 !õùâã!ZHç’N0»­β4,=ˆS,njÛÀ é„ÊŤó›Ê€?Ä¡QaÉWK}ØhùdÌ7))ØQ}9–ê·°â5VêŽÀ²›$‡5ï– lîUýëkgãú'×/‰ªíÂ[„·~¦tÅÚ.M g›ê®>þÅw:/AV9š3$óó"_owwõüÙÛœdÌ݉ úUÖ¼•` xRf!jä‚§<Ÿ²ÌH|/¼’ì[ÖÔ• µœde)q~ÊÜ•V5/OÂïp §î ÌeLˆ9i¶lv`gDSnÿü,-ÒŸ„?=¶„õ£´"-ã8½ÿ#<Í >sGžAÙ,mh zçf„Ë’1ŠªKpjŒ–v;³¦ž©ÎéÓ^h~ðòÂfíѤÆÂ2.Ì. [w¼…ØÁަXô7ó€;•HðÀ–;J¥Pç„|¼ ö.k¥°¨­"?ÃúŸi‰µ,'¢pGdÉØOŸ2 ô#å´~öë,¢±FÞ¹›4xPxQlR#󲕜»=pöïÎó%†¥Ð´Î³öŠºIK)¥QwM¼¼~q©éç<ĶbL Ôûõj£HRÇ0;+,û4¹–³TøÐ´Ávú¸[×Y#^R3BÜ·tP惺æd‹½#кÅ+Øœ‚}~õ8ŸYº…©-¸£tû©ÎÓ,V Q¤fwÛ:K·ª´ÍõY ö>K³ª¹%(Ôc¦Õ*¼VkIÍÞïžžvYÊUXrÕZJ¹ŸaÕþ&9º?gÆIi›”P‹öóyéíõ†WÒ&c‚A4 »^Œ_,¸d)$ÇÌßë4|q_}‚faSßeìupô0{Š8ý‡ä ë<"¡ÇÜí7ÃHŽ¥i@ãö•ù«Ð ­,š¬{L6¢ªô;Ûqä>a¾©B©5¥…æ5­é#l¬7`ÞÝЀý[Slž6Næ[b½ý};+ ›/Bç˜ïy2ŸÌ7Ž:m¾„~OæÇ BW6G`¾¡Ü=>ënÛ¬äCkÑ™…Á +ÊŒýZ½Å¨'Çà:«0N4Õ!§6g,Ï© ¡Ù§Ö[#¾Ÿá)€ìcõœS…·Ä5¥ÕÏÛÏ9V azóØ`|¤öw9k˦àeón³ï®V,°X¬ÄùÈbü郅˜Òhqm‹£^ÇdãØËlö„ɦF. ™u^ ö˜ø.6¡ŠàÚþ[smy*J »$†j€Yá<ŽÉæA 0ƒ€ªÑÔøÇc½ÏÛÊfBà ªQàí.o¯­]óF ú–¤Û(¾Ëªb¢²Y‡cb@CKé6q‹7©KR›<Å:Œä•[uïDÆë½ÿ1o›Å"KCé5•ÄqÍ+1¤bׇÃës4¸c Ä^.T´vYÛPAØl{Ðì3¯áÝ…geµÊ7ÛØ…¥«†Ö$P‘:MÚ`p ožhpÛMK si즊©`´ÌºÈ25mlÁ+|º}¾%õDürÂgOô|tC 2‘cþJ¬m[‰ýŒÌ§á« L…ï²°@Zí½è>ã4Ü+Úgìj ƒÔãð“‡tEeLóÛ¿a‡~7Žú¿²žúáÒx%º½)ù!÷<SÕ5£Î Ï‡i}oÁã«iqÐdú|$+ÆæZR¸uÌÒƒg,!²ª“Zç¤3Ü&Ñ*J¹ß?G¿¸—R0¸¯ÛÍ¿^ë§/Y9ÊV…Ô–ÂÞÜÕÛ#ÄýY©š‹¦hR‡=\†êõmæ¡8M‰ü˜u®®¥hòà)oªXr.€£æ»Ù×OyóX›¦r2¥Û·<ÍbéuR™ _R¤…wy¹B½{´¶À WJô“˜–é)7Sµ•**©CÕžôâ!/!ªÄ²†..êê&ïV¦ 8Cju•gŽþ_Ê$@ŸónÏ5%ïe°áõÛYùr¸woÞ%”°þøUf¦8Ly"»,çˆd)ǰa€ÊæQ9cŸ‹/V1BÖ¤”ûXˆ®!ô—’´òM÷‹ÉjŠ7¸¿em-5ìu¥" ,?Êi]CºÚ/™‹î°õù)‡Ÿ,B-Èæ:%úíÏ?ü´l Óºpãc™'˜y!)x/|W½‡ ïImoŸ^ïêCf-æÆ+BâÜdm‰·È]E ž¢š"éˆJWÔX‹Øðá5‰yÌ&¦+ªÊC –&ïësìì+‰@7U¡ñeõ88^ ûxsh¹§ùúÀµ½r”>×o™T/VÎ)I¬·yT/ÇÚx†BEÛx[?C^6”Umm!zŸ”’ÇôÂôÓB0BäÝSæ‘‚¶ÍS”QäeEêªÀ§×ã˜Û¬“e ÎÓ<Ê:'±ÉT¬­pÁ »ÏS«M‚e`xŒ}ܼ¥ÝO+«ÂÐÖÛ9Ç5ºá O¸ÃPú“ oI ËsœÜ%캫²sÆ&¥vÀœ³<Óœ¼¿q'Þ-9}Ýàð].£/ø~¿þòëḽ=¾îë_Ÿ6‡cû5øÿ~0¸,É&ñ%×ÿêpíz—5¼§OἨœ}ÊÝæþ~¿ýµOuœþŠ47€ÕÒlÿƒã¯Èåþ+ÊöúÄù+˜ÿÏõúã |ò‡ÀØP¾G6«²ÿ“ñïH?ì¿OðJcÂÁNßq¸]og|厤*DøS”üsïk ûä¥]ÖÔÈ¿_?×áWd'ò"ËÓOCû¬›¿¬?è ¾cÞÕ_6}Љi<%·ñƒÎs-ÏœóN¬Èn½¸Æy§Æ $ „ÖÞ²´»4Æuø(rwä_8òdÉ{¥±2ºˆÝb™T¹æª‡ZšWzu&]‡ZJÚú©¾D³NlvÀ|µ¡ 3™až»}Æ4D]H~(sŽãÓ¥Qaûº~Ÿ  oê IØ5Ò,ÞòN"šËÄè±›àU•™ç“ ÔQQêHNØ‘A˜ÓÃIsKLä³6¶}¿/ŽÚ%hæ]èln*+šå¤MQ÷ñüš—2óŠühÆIäÈITtëYf†7 ñÂl—¥ÖN‰Ý¶ø,»åŽ)ZÜé©döyœcŸÌ>f)Éì« ÉìŒ7ó–{“ÌNê`Á-÷&™ÂM,¾7N;o“Ù ÅN'³¯.$³_Y±]2;z!™]Hf§`³ï¸wÉì„bédöUj2ûuµÛ'³_ÛlûdöëšmŸÌNhw”̾š—ֻ̪ ËÓ.>fI§_WäÄïøÀ¿ÃÒJ» ùÒ4OKõÈ,Âïˆ_2îøÿRù6É¿3çšá‰ßËæTx£‚†Y>\¥xKJïè8ê…Á¢žŽÝ‰£†t›™ãÔ’;äeÕÁ:n‡Pí1Sµµ³¢P)f'™„é˜>Ë ¬{b§Å¼b\Ýò:„..Ñ:4ÓÑ:„Šw™¹8-«3eRg•Iê\ÙÎzç‹©#Üå–ó¡8ÕãtfNàŽÓâ²Yõp N‡Òf«¶ãtØKœÍ;tœÎå!›GQ·œ¡ÚEœ¥Ù9œÎ8 ´ãt(5ì3ïÏ´ü e ÿ’w…¦å_:x6Ÿ¡|dË¿bÈ­ÓÙñ/ì[ž‹ìø—1(Ë\'VÿBYÛœä1‰/´ 1Å¿devüKžeò/«žéPY&ÿBo‘{¥À6‹¾Ï-&À.ñ/ðv—G>tņ¨löFvTLb긨óne³1ÿBà&ÒˆÿB zü ›Ï¿\Y±-ÿB)vV16æ_ØÔôXŠ¡ÌàÌ¿°LþŃf™ü˸˜ÀÕͶç_®k¶=ÿB zü Ëá_B\¯šÏ,þe5â_-ïÂBðU `b:·r2¿F.ɯ9ÿÀõòk¡¯™__-¿6EM©×+ç×t°£ü¹,¿†öù5ôÂüš!ê•òka¯—_CüÀ²üš(è5òkiç×Pj^–_C ^#¿æ }Õü¬?"tuåüuq~Mwq~M‡zíüB ‹ókR‡l^~ ¡Úeù5„f¯’_C©aŸyµãbâ¨Wãbâ YÎÅÄÅ^ÌÅÄar1#Ðkq1qi—r1\2‰I,AÒ311ðMžx˜“ýϰ0¥(¤ÿ,Lx) 3@½ u9 Ç]ÊÂÄQ—²0WUlÏÂÄE]ÌÂÄa³0„\ƒ…9A_“…¹²ÙžX˜«ší‰…‰£.ga|Ük²0¤¼KYøª,ŒpX]Šx+®y-ƒ€1X ÚyØ× `JX" äÍ}ßp\Ñ1€]Ñ‘¢_„5…×,K})F¿p>†e жµ·)ÇYç=pèÇNVÖ)J‰'ýÃꋪP0̨Ñf½mÛk|ûõŒ~Õ· ¾+9¥Ür ,×*RÏùo–`ðß&Œ-÷mCQ<%emóÞóóI…uá¥\2ú-gðôÛ¬‚k”9'?¸C: ƒäÆèj,Jím;/½YGs2þT¶ÿ™qFâ@üdN¦’…–.ë_­ë˜Ë«è%!‚Õ†ýóc½ÍcR´*ªª¢p‡³1™ Å÷û”¡4âÍÆ™¾ ×'CJæsçX—Ð9I)a»;fé `Ù<vT´”%;˜{FQÊͼž#K0Civ½=f¾D‰|°Ð”Öyþ•q9î3'2fT–4Ûî¥Ï VFQz}[ö–¥€é+íˆeÇ·C¿*²ŠEœ•j¸ÅÌ+eÔC–cXv•‡, q—=dI€.}È’€]üå÷:YÒ.}È’‚]ö%ºô!KB³Ë²$ä]ú¥²9‹^o!OXò;€BˆBU#³ß<<ß?®·wuÎÛxô‚Nòβßbò²„%ÍXA‰œõ¶<H²T¤Æ f3º5ÈjôÎÆÜ;Èñ×®¾,ï¦Ît2tÒ½ØÇÞäX̉¢Âp7.nÞKWÂƹ3æõ^ºÒUQrEH{ÉÎXü @Û2¤2KÅG ¬%0›I6_«½ÙrdDGrÍ{c’z½²ó8à€ cDvuè!wÒ>ÐF Žk¡&½ñ[!IPQ Ÿ7·Y[ÖW@V¾ÃÐãR‚¢&ïÌo "%§IlrµUÚÁ4 0Ã]YòCoÝ¼Š‚ÎxH"2³ª“Qå=#1X¼0›Þ’MyF‚M„÷>Ê‹ÏѱÙ7øÇÀì 7ø q—Ýà'@ßà'pÞà¢^çÿuÛÝà'@—Þà'`—Þà'{üWÕnƒÿÚfÛŸ]^×lû³KB»‹oð¸yñ#ž££4;¿di¥i»óK®Ua‡Æ±¤*Óç—Œ«ò¼L ‚Þš„¢ eÿØtyðÄ!&›—Ebj/OÎ"ßâg”°_-Jâ°ˆ˜EnfYŸENÀúÃ5ët´Ë"²ä,òKù!ñœ³06Î"'P³»«ü$¬ŸEžõÈH—EÞýÀuÞë³È ©2Ùd9d‘Ï: ì²È sËÌGî²È)K›q¡ŸQYä3ÌmÎKj ‹Â*G?žW- \nZp¶`âÙÙe“ïLˆ¼ÎR¯\âþ::‹ ‹åRW"&0»œï<‘ï€%_*FH<—» À’ŽÔò ß™Í{ƒGkJ¹O›j¹õ’RÇ[æÃ>ø®:9;.ºµ‰ôlÑÅqàÃãîõé./ñÆÍUcc›wªBU‚ýLa]5&5öÏë§Í¿öñØÕ­ìÜ'"a§è§P?e^¡«\óô]‡Êr|OäÙ3ݼLˆúºÝää£ßiƒ8î[Þm˜ÊÚ8è’ûbønƒ#!íz›w] ™3«I;È,³©,¦^X õŸô<€ë}ªà&—¼QéÂÉrTéb¶þ˜…ŒW<‘­?‹Dê²õ Ô·> >> endobj 56 0 obj 65 endobj 57 0 obj << /Length 56 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»åšs¹äÍBÆÎ endstream endobj 58 0 obj << /Type /Page /Parent 59 0 R /Resources 60 0 R /Contents 57 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 59 0 obj << /Type /Pages /Parent 222 0 R /Count 6 /Kids [ 58 0 R 66 0 R 73 0 R 81 0 R 89 0 R 97 0 R ] >> endobj 60 0 obj << /ProcSet [ /PDF ] /XObject << /Fm7 61 0 R >> >> endobj 61 0 obj << /Length 62 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 63 0 R /Filter /FlateDecode >> stream xÚ½}]“·­è;ÅÞ·uÊî4?»;®<ÈòêDUŽìH{òqã”j´Û«›ÝefV¶Î¯¿»{†lœîæúTª¢‘ÜAþsñ—‹ÿ\|w}Ñ‘%ü¯û¥êBÊæ¢jLQqqýxñûW¼(/øÅõÝÅåÍúî«‹ëÿwqu}Q²©Ù/€…[p~¡›B©êzóˆÿ^ð¦n*}ñx! øuú‡‡‹w@Ãw×lL…’Æ¥àrýøq6Br…$WÌ(n×7 ¡tÑ4ÒŸ¥(JÖÍR¦HAU”§ðõŸÿëåëWÄâ@²ä…¬+èû·/^]Çêy"¥)´ôaþzõöÝëÔÉJº”;Þ¤¾¯EÁG„ñB%¦¢]H-)ùþõ«Wo‡™#RºjÒòQò ¢‘/¦öyyu}õòšž'ÓUTûóüñ­ Œîð×°Î(߳߿RÇY¾_ýºÞŸÛ›Ãv÷Où/OU4•Ecˆ†•°°AÒz,?_&ŒrÆH}”ÑŸAä·« .˺0M탳˟¿JˆÄ0s£·œº¾oÇÌÙ²¬Ge<Ÿ)ã!@èYjæB´íc»9$ 8¯ Qú”mï¾b4€, ¡µp§;î¡LÁAìÚö›³ä1Q‚æ¨jösJ‘”M¡¹÷¹•§Ä„l"ŽòäÀ<íÛÛÄŒ`þâsØ&õ›)Œ9Neörÿ©Ýÿ%Õ40LE°š%ÄL+Ø!݆¼]ï€ëí&¡kh)=°í]‚0 «.qU:;UJÈ`çð²òØm+‡¬Øl¸‘> ÓѵKH ÇuÑÂ8ìV›ýÊâÀQn@Û6Ÿª£Œí[úä]'—GÀ„êÊçÃç”ô«ª¨J=;qNPUñB;ìr¿}z¸MW0ùFùd}pv4£ÄLÉ¢‚ƒßo¶»ÇÕÃúÚÄ@ N9£a0¹ox©‹ºÑó(‹¨3àlw„UBÍrS.µ÷ýÓfÔ˜°ˆ¦i˜ ò9ù=¨ré“‹˜°8˜}"-÷þ>Àj“Zr^ØÂ>c×û¬]£üYÜ®A{ïac=´ûn§ô2°m•î~ ò"Aü¹²°»owîBAX÷ËÔ¨0…³ÙÆú_h‹ÔhŒtl¼,ãïësé °zxrÅ~ æCiiˆÇ´1/ËBiÃ\€ë$€q¬¼>'Ëá¸+kŸ³íækzÆ9È–ñüÓ;B€í&\v¹Ú@¡&®ëp"k¹® X‹pPsµk“œ­@nå ±wTuø=ØEhI8ßÿ,…J±DJWÞ,Àˆ/–)üJØ€"jæA;f­ºH€ ØÐByâïÚÖÿÄÃìh=ž<ˆag‚¨¹ö„‘E ÄŒˆ^U FÁ²Fxø´)Ñé¸8ýN2‰6ûà„êE ä—`ŠC8@lL>¿Q¢×ÙƒwY|xƒÚC¸Ã_~ŸR¸0_!㨑¸˜1ý(÷OUà’¹Ã½zûâÏW 58a LSÂŸÍØ û~uH„¨9ËÝCw»÷Ð>îSŽG ^x3‚IYµœk뻾®óý;[§áLÉ÷¼# †ƒükwÏ£u¦3yç•è°ïŵ#Nl[£j¢Ç$ˆe¨aJ°¾ˆ1Ï-¸T Á\vÞ¬m2(Ä Ã¥··»/)o |^˜íî6aÅ 0NªF$V:.½ÌT X31ÓVë‡}ÚÁ–B€|œ€V¶O‡¤ÌÂù¬¤ Ò®nîSβ„s |ân·zLÚ¼`.šF»“IzoÃYð¡;yØ®EÊ"mðti\ë™à˜¥]€n§„EªqfΈí}tÂUQ£8Ÿ†8܇6¬+&`Ôœ»ç¸†/Ká²ÖÊïyµö+…¿ ¥ËRºKpY\O»T@Ýu§ ñy½}Ú?¤(ãÎSÞ0*É`Ô‡5®¡°r„d¤•`¯ËÒŸyZ{Z·Å¨Ú™¤É.ðøÅ]ÕÁ±3Šlg·®M0(;7¨(1†Óø€#•Š23µMß)ÊÆUå³ÿŒða˜Ií2æòëd¬N<_ò~¹_»ú‰Eƒî#¡H:Žƒ¦ÕÌ_„~\pWÁai`”ðKB5ÁJ N™ûým ¹{[$}GMíA&µÈ8Øð¼ö&sN­q8ÐJáÓw·Û>¦N ØàVO9 ‡û”¥矆]€¤Z+¥5›ûï­œl“!"n£VÒÁ_J¼†•THZ~™€O9÷GYíÚ3 gŸÁ@y&C±µ­Vyc|^ߺÞ,£”º2EÝôá•ÔšÞ¨Zàa½Ú·)¨†ã ÷†ù8“¥.¥÷ýÓ!%& Á4šIÀÙà —´SÞ\6Ûd€L— ãΣMYÀ¯ c>îD’᮪¨”öçѦÃ]V¤r Øå]2ŒŠ.‘>M›Ô… £Iÿ’ÜP¦P戟ýƒÍÚÇ¿Ýý»HÄT©•• "ÄKÿÄC€7­JU1d´eƒ°[]4’û£|ÜmŸ>ý|¹ÿù«?8âƮЦtÝý¹yxÚ¯?·ï-¶3x´€m#€Ó›)»ÝêË{´j{p:Ð3p :£S=Æ00Ì…žÈ0æ‚ü;§¯CÕµ7D›˜¨7©JŸ¤/ýbÐáV¼Ñ1#.8–Øíúîn·éjÝ‘b}› ”ÜŸ,NQ["(Àã²—ïûkÀ÷€3ˆð ˃»Ëè0¡Aˆd,Äão= »­—áæ·ŸßÕ¯«ÇO-éq×`óðڿ䤡§w >s¿þYŠ’h}+ý ÒÐ抆{ßíhS¹­+ß} *ýÍv¾ñf½ùHÇ3´.à,öÀnýÐÀzŒ/m&O£Âx‰>ï,–GúsX Ö¶‹]¾f§¯Y€é1™–¦.”öiI±Tp †¾ùãý" ¡ȧô€®V7ô `ÎÈRyë|Om0Ô¥ã3ŽÐÆ>É\rÆ5^©k™1 3ìPð¸¥îé_íIÍ«œ‡î÷+ÒÓ¬J8j›Î×7ÛÇGïNx´Í@OWB ¬?V C=þV_h™Ã¼ ps|Š6?Ki>>%FQ LXfw”ÑÝö8ÒާOÞcàTÈÍ\;Q3q‚ïhTÕüHK}– e›U#«½9q¼ïHì@‡œGàm»¿Ù­?´·ä¬„½Œ»ÜZ“|cBª¢©}.¼xûöÅ?[Dæ{‚`¿e&„3ð–ÅÔžtžN'vùîúí¿¼þï·Wç÷&Äéðúwtœ8KA¡zßÓ"gÀó’¹·è[§Î³RÚùœ@¬³È‡TƒópÀŒZ·^þEÃF†ò`®SÑ}Ø9ÔÃ÷,qB6WÂÀóX$(U{Ÿ· …R¯F|½OH¼(Ôh¶ƒý”xð(Qm{KWÃìxìÀùÏýV»„̃ýU*«mòØ©|íýl_I `i]û‚š;tí•21ô·é€f´ î¶O49Ã6«à<ç½”Ò¬Ñh%€cÓÞ™,OŸö$j]ÐÌ~/ïSÚ,bÿóëÍj÷%qFa a.HzX0´€Ž£ñ°Dƒßû:qáÆ0““uÜïÓ*¯Í žšGˆ‰*ÍMU{C¹*Ö¿o öÚo•£ÈíHj˲ñÅd›X!ÊBON¾N| †Oí¯ÈÃzóoš‰ïûÔRÀͲöˆù ]cà±:³â1xÏî Hʦ6©ÇgMÌÁ/›Þ˜%R6'/‘–ˆ·¡ªý¥^ßÒ&Bã1+’v?¦¶ºÜÙ°Û[uyçQÓjdX±˜BQ¥öÆ[ߦ’HÀÌW˜×­A Ëà>æa»ýôþ,ô…VpêÈ.ëLà€D!†BÙŒÀ–3à`du“Šáì"FqDÌ'ŽÃ±!5…¨[Ñ&N³ÔöFéxÉûž§„x xòÔ-ss›Ó`Æhî ÖM–§‚j`Šâ„ ÅÏóFÁލJ1sF.T?#1aF.Øô¹PbÂŒP%H3wFT?#9eFØŒ9PrÂŒªÚË,˜2¡ˆ9óQSæsjÆtN@*Tõj´baÆ™v3Îô…—qMXƒ“…«…ñÞì?áKÐøeÉá,Á¡‡7.,xã¢LIÆ>‡YÅð2¯óv†ËhR.bW9»*ŒÑèdMáÒ:`'ä,þ¦fNP¸š3àSÌõf{ÛNÆÊ‚G8V‡Ò¯&1o ŒýÝ/•L0é¤“HzVp˜–¦·8­©ÊÜz·mþÍøJq%L ÁÅ«o¸ä ² sÀËkS×>Ví½]ŒæÚ–' `Ù—îc‘©jš(̘©D@TŸÁá¼lœ‡ŒH-jFÌÕ}ÿx/s{1ÿŸä!?eÇÐ2Š\ô2¸Ô‚Ÿ6KK¼ìP².¼+³×NzU’AŽèêªlX€¶[°Cû8­›ÀQòB”ò‚@»ŸÄ×𠾄4ÒUBÐóÇXUÅ+‚­Ÿ¶ëÍ¡Ý-â¬uˆ ÁØÓÓš$ÎQ\­¶yè­îM«¤ö‡ÝÓÍáiçšó³8"j{çEp䴙Ōî½Éûv2;NçͰ!De-šN/Z‘³‘g†·–ÊÇI|³YrÙœ+Ê’ŠÎS™-2‰ŸÉçÛ¹Á9xWÝë.‚h7hBâ¾4˜íA¡-'!}:ÌËE¤ŸÆŒ—ìŸ#ø¯‰¬Ž¾V%>EðBzº!©IõhHÇ’ ;CœvªÖ>vç‘ôå •t²ùJL‘p²Ñ º>…³§#eGC2FèCò$zcCRV€L‘H/7ÂË&'½\ÈF ocÒr5bLÆ×p²Í‚Ïϵ?ÜDw€¶X0Ý·»Íêc…0\“…WU!Œ:B·&çq–WxéfâT± küãdY–5éD³0}¯¥ &ž±&r¨7p«áØ$W|¼Økëa4&È­²æä’ó¨ÂªZxY–=é>O¶)͆¢w‚ñ=8¾b'¹°ZÄY|·Œ·™Q¤,Ó¤,Á猠w†QɼŒ‚FÈ ¬Ê¨âbóL@°^›R||Ã<Ã’bIŽe‰ÅePq=¯eéa}Ë’ Ó}ö0OÌ0²ìʞǦÄ;oÉ)r—Û”h5)’ Ť]L•ãNú7¶)¥‚IêßÔ¦<1¶)GÏë’l ¯éñqƒ‡Û3FØl‹­TQŸ'§SôÐ.²REQ—œytžpþzX ##•šûW‹ ±A d3”rð.ÑCcrX<¶Ä¬(!‡ÑØ,[’4ƒðá­PÚŸCÜ–ôž‹;eu¤eª-9Ùl®º÷§UglIÚpF\““ulÉ™T|Ü„xÙ`KªE¦¯}aÇÁ€pÑÎò¬bÁ¾Ah¾ªC[²]í3øpX íçEÁ--Ð Úè–[ÙbÖ‘ .EYUàºÆ‰ÝÞ-Ð0`ÙlM&þÏѱ'äXhªm¬ ü·HÓ0³Óc`¬A°æTte–tÐ2xûý¬Ò41»‚Že¢ïàðÍÁÙÕ"[J€kl]ïøô»”ÛOß,bí°¹±Ïbǵ“Ñ<ëþx[*)¼lÖ 64¬˜V ÑâÔÚJn«‡)¨YhL¥±B܇ý$³=4Y+,(GÍ–òËY5åq寒æ–7˜g¸ÃÙ, ɯB1#n°ò)jfìâRèfHí&>ÖSX¦"ÑŠŒS;ï ŽùõYñ$wáeª] G>%½Ë61ÖijNmâÕ§O»í§Ýz©‹8¨p@ж7ÞsŠY’V+,]"â˜×‹âžÚQ¬ì¤'ƒýNaÜ6ƒ Ý´ß½Œ¡Ånìƒ µËMµ é9É‹ªâQ °o¯—É«Á¦ƒŠÄ¼T^Q1šk/¯yKtWQÙ¾´3—¨ƒbNÙ¤¦ò–ÈþÃìüÞa‰¢Þ¾xó_WyKD`Î\¢1Öc‚ïs¬¯ S†^Ñß^üõꇫ7ÿuý§e¥Aèr„s{'`eƒeØT¬yGÀú42ô޾»z Võqšìù…¶‹ÓPT½¼zs Ô0´Íî¦r!a‰%Æw|‚¤ìï‹—¯¬Yv4àJpF‘Ê5ì°‰{‰%| 8ãûj[iÉa#ÉéÀæ-›ᣨê%'Væ(9ÓcïæzƒäŒ(ë×ø Ír+9Œšï¸£•’‰´ä°9$l‰^Rႜ¸É1 2 ]óN¯Oâ1£Ô:4æïϾ ‚%² <@0D^ÿðËë×?¾YÈøSD°O³(èÀ²„M& …x™YŽýd£ãHÙ%ϱÆQ™uæÁŒv‘°)Yc†4ÿzØ­nÓ24ÛD©Îe pG^L;‹•éGDñ2÷éÍ,N€ZÇ'=ÖqZЋïãq—³Ò¦°hIJÅ_žV›ÃÓã²ûGk µäzÙí¹Äl1 eÃãǾù¢@h¯Š7¿ÁæÓödƇ/‹´¼ûCÔŽ&À¾v{ùÝ«‡õ‡½RcãúÖ1G°ä,l*A샡 ·ðáÐ,Å…¥Á·èÞ ._?®>¦š»IÌÖU•ã÷– FÛ…ƒ-àBŒzK†;NPYÕÞ(¾$¦¢„²™¢.ÀËûׄ58óVMÌ›uû°o7)Ò𬎠å5¤µLJ²Þ0Ve$f>[ÝøLvub$P®ËÊv£rAV ª`¥<~ëüêm¤ºCÜl`Ë; ¾1@­ £|F¯‰¢ÜûÝ 2ïÞ½ý!%eÃn4¸mL×£¡]=>¬7©æŽRcó#XWÒýí¶ýŽíY5È©|CL±qìè« ‡žÕ”Š6nËK¿¨Ìqžh R•ûÇð}â³­{‹ˆÏÖ]øsÍü&uºÂˆt1Äk—„­*Ì®˜/~iƒm±ófdýŒXýA|hS oοKéÅDz´Vñ¤Z0Tׯèöîðzøã -'¼Ï7܇Öx9Å45Þ’jy„!œ‹Ä3lÌRØ‚OÎènBÏ`¢va÷¥[ç/ªgTgd8ƒ8%übM]Á,¢&úU¢¡øq±9¸@µì[f%»wãÞHÍ\·¾^ ¤6ÔÊe½Oô1–]·@`•hc,Û`Äû~Tð.öª,?“Ö܄J P w“&;UÜ�IÐG[0 /Ð! nR°Ö¢“Þ¬ñíÕüë¸ØpZ‚É`¿ÿþõ«Woß½¿¤ÆÐCå‚D‹Ç…cÌ’m˜(Èt Ù¥²u÷{x6y`UbÉÆ‹p\k—^ýpõç«7×)¡P° És˜4<Ô šU£Q$kâLWsUsÛlÓ)Îè‘Ê6Þ¯Ô4ã‚mÑ‹ð5ø¤¯K°›vˆ^ø‡ho;gšøŒO¾îÌ<D4>Kœ™>dòÌdÁ™Iš83Ùpf:°§–‰3Ó`Y˜ŠMÈÂ3sv¬EÇNèh##ô8ö,HaŽH€©m,´ntB² 'ä08½¸pøÐ k@abíAÄOÈ£±¯´´î‘ â¯EتfOÒ'äÅø„4°É ?5•L^Ê`´ËøœÐR•ÒûÞ­=Oñþê¢m]\càÔ£è|+oz~ª°ÿGèNÜ||Úœ¶ÁÁ¡ŠcórgºO›õžÚ‡/‰[ˆaV° nôæ°¾û’:"+¬ëQ3Ì­G”ZpÝ]¿ô?=´‡äªc±"È«O³½<âü¼U %ÄùàèµS4–öh‚–;¾$ÀÀtÕ¸°—wàòn9½ŽFI°?,.±‡¢m9ŸŒ•”ø=sáîWŸS¬Â’±¥Oâ*å+ŽèŒÐþçiýyõà÷@ ã%Ú[.à.E™ª@‹áûn>$ç‚!À1ÛRi,và}~.tÓh0×É9TMQ›ššsèžf#µ¶\Ù:µŠà¢ÁQ=Z”Q?ÍÐM*í™íN§ëü‡)»ΩJ’EówíÝæèNëôA ‡­Q•ƒÏ»zøz )0‘ª¦(Ù߬N„¼ßV»CRæD!PIZœãcn5%>îçGr˜Døä´›$o¤*Ä€p -‹¯‘¢¥?®¦¬”êúGzHgÒSc™»ÞE »=ïW¿®÷I¢†‡Ñ˜éÞ ˆÉÒ´CÀ<ÐI‰ïæÅðŒÄçúA`Äi|ç˜}Xi,'ÐåÖFïá{uLÆ9ÚÁÉÓ‘8að­ððæÇÉÍwTÇnÅ®¤ØÉ¶ógÀ0´¿¢†k@€–6€0`²®±õQS†&“éy.m¦ ¬@ekU:Æ8N± E8ö±á÷ Ú«É` ¶Ë…o{˜°ÿuy8PÝA¼ö½lìnƒÔÞ”¨˜ÂSWÐú.&¹ö›†g,v&¦¬X…™$þìFmèc‹ ^¤ wîvvƒ­+ºÂ¨RF=¶Ø û$ç#±#ðŽ«Ñ8‡öæ›”™:ˆ 4C8þÒï·˜© sDÂ-NDÙÂUÃüA’bÚtûßxlWû§Ô€5\åÁìÚÄîÃk5Óøi[w9ÜAØÝjþphwÉù+|t G¤­n×6ÇáëÄœ4/m¥@p½¹yxºõ-îq>då­’‘C\wb_ÎD)1^å°zøÆÑ ¤¤ ]ˆª dÙ§²Ö®À~qAüîÙ1I3ØYýNö‡oöÇäj0ÆRûcá}ÞúquHIhwƒ‹Z$âGFpBÞµ~™¶n%8À 悌´N4% Id·}úd½®?¤¼‡–×Å>4Lu”ÈøÒ_Ûи+´$w› –¸ºúÓlGÓVÇéž¾o÷Ÿ¶kh°D «o;@ô})“Øœ\çë¤ô—¦kŠìPd¥Ÿ”6lxVzÔ¤¥_I8ß¼)'#§ƒÚÒèjŸÜ6E“¹Ÿg1'*(}Ëñÿ§ƒmÉ»+·€Qþ!=~fÐúñéá°þe½k§RŽ¢‰’qøò©B‚ƒ‡}·ÆÛò½KÁé(Ò (®!ÎpÑǬG?ĬÇïÇâ U‡™èÀbñw‹’_|süï«uŒK)‹žµt'5 /_ûÆB¼§–ó¶/2ÄøÊUª 0­[ëÜ5X ¤\ÜÓzlpÇ´%ã¬.Ü‘^[l:ÝýUrÈv®}Qwv?M‰mGÉ„«c^I¸Ælî˜Ö³µ§ÝqL6µýtC+A½éÏèl+.¼ \³*Z ¦æ%ê)¸ô)Ñö$ÀVã}^÷æÚÄdí3WOyB>ÄŒ5X’¤=ÝE8r–xÓ9o~X„‚ÓÏG§p§ÆBíŠyLëQÔí­Ä¦Óewô‚~XU¾ã¦‡4ræu?J7 ¡†an VÛ±ÄR¯{" L¢;K؇ÎElî¼Ä:S°/ˆ!°ƒQÖ"+¬­­âø“Ý‘¦¯«®ÉH|™Óü?‡,tðDEŸ,¾Ñmav†´yêúc’~j5CÝ1 ‚6`ç^„c°0.ŠZ‘rZ̲q¨;=Y›B)¤ ž­IlÉRÔ{L–°‹‰ì»EÇ0®¬‡b.èwZ&€RÊÍquIÚKë¿fé7nº<º›©`£)˜ŒlÞþc)7À4Ù7ÀÇ}j2zh—»lpƸ'´Ü=Ï“Þ  xòÕ,ž* 0­**íá¨Àß/ZåÐFsºòG%Öy%ŒY¼q°³‘#æjqÓðY'EôY%ý9œFqrC'ù~¡ÁZÚíc±ÙkÊûÃÓßHœñþòN=¼VÐÊËñc/³f¢°ž x.öó^_Y¥©(öz}pvqÃIúr½>ÞØzÝ'ôÏéõ a8´ç{}6Y‹À.º Ä{| ~ ¶Üã‹zKÃRÚVɘÓzŠ»¤ªB |ÆÑl7í.Ó]Âì‡ò8˜=7«ý>‹C¸1loŸB¦?©ðGØI‹}I¬úA ·ÇažÃ¤Œ}IÑŸì;v¦&»jT±‚/¿{O­”°¾&ôÔÖûLW­±- ü¶ÀO–Ÿ†µojÃünŒew—MIѾž—Òbn ­T;;Ó½wŠƒSš¢ÖÅ–QŽe>š¬ì%bˆÃvVäfœD‰)ä>ê ÍËy¯¿Ì‡–&–w“%øø~«fSì™é‚Ó(Aw¡jèU‚ÿØgs´F\Qäßœ1ϳ§Âà©wl¦xŽ^@•ŒqqÏ¢3E#p“ýÑ­²l(ôŸ³n‰ís%äcƸE–ñ¦êÒŸ âgƵƩ®Ü–ŒðpO1Ó‰=0âØs4>ƒq]„eºÓÔ¶à"1Æmû³”fÓî³–,˜»ØôöðSôCÙ=ï f°oyê;ÐèAŒ²”l`^ j‰o×wY6ƒVø¹î°LízÖé¾ýâ6;ö4‚_kx³Äx8=–Äê²´òÊ[,r&Ž ›’ þ¿s/O v{X?¶Y—ò˜]ùsy¶KyÌ+ä>níÄþdµ]ÝÌ3Ïq¡ˆÿ*Ï¥–ä©¡“hÃÛó÷Ý¢dE}me ż±9“ŒHÈ•ñg–¸CgËæÐ€ &‡AØ„+ô9Ôà¥Íáù×Þöá¥F*:Å…,8çÌñùVÜÖ—þ|è‹ô~Ÿ+)ì›ÞjÎE:›yKòÎë€>»H_rK€Bb¨é·™ù.ð§ª)äÞEú’À±Ò5_ øYü*}ñFBe`àOJð¾Ê󆤥â1g#+~Ά©+F ¿mWóÈXý .¨Œü칉Á6a<½1ö^ð×7»í¾½Ùnn3/ì5(<çã³È½°7˜M®rö…}øz•y¹ß H¾TõVû…ÆØB«Ýa±;ã–¿XæÑ`‘QÅÉ%Øæ94ºÁöVv[Xc—¹•ûûeùj±8‰Š„Ú#øG?g&°L€¹>S¦_ƒ°Ñ&1 ‰nöëúݳž¤¶Fx3žËõ}›—äו бÝv÷¸>Ò»á¼ýV•…Ä39>ÈnµùØfÞÅaâ˜kñÖû,sM¢FÂ3ÙÅ^.âòÖ·ÑES’ë[æ­.F¥á#¯çF.)K«ä…ŠZÕ2/QÅ–ÂäålTÎma"kmË«zÈA¥ö”ÿŸ<¶pÓ¹Bqiñ,¸%I¨uQiwEÙòXtPÿ¾¿qöHŸúž‚-|J-0óÕ©¶ÎÜ8Gòçâ7ÎãÁq›óx¸¿jöp/NºŽ÷”ðpO¿j>û¤ºØ”SΛsÕ ¢Z‡lâM—¿[’쓈—¶=¼›“óŽ˜p\‘è?g(»ÈÙâpºWe lÛ†S”O¾•¡Sí½ˆ£÷œ—¹wµ²V…·×ÃP 3nmQ.°BµŸŠSézÙ2klŠlµÌOYˬKS(I è„«¥óކöC|ˆc}î¬û[Á[1b ·˜wÖƒq¶0ÍŹôl¶(q+¬ÊaŒgw'1׬w‰˜C¦;‰¯†÷ö® VfŽ¿°]Å(úórãvG©(ò#Äf¾/­§7ÆÏæ_ðÅŸ‹s›~A?ÅY='+ÐS{ 7qJs¬ù#¨õÝ·‡"ïTJÛk•Àÿú.kµ’¶R$±À‡û6OOëXPÄÎ:Œµ‘öáÜKÁ`‹R_Å—™eFµÃ­\Ãæ=i;Ó@U„*¸6Þh§‰¬÷y ]ñùp oyÙºë¯ÇþqY+¸Q|ùœ©×dQ×5Ax»ù:-Uc ı¯óÌ6¬¤)Cžâ’Ç–Ü!N­ç>O`'¼’½~üô°¾Y¾ä•QÂéî›:ížVy¡s¬-m81‰Üȹí¨VQÈïŸ'hα(»æ 5=aæàK˜’éqä‘d»™µ´,xâmº Ñ>î©eo—?ÌÄ=Z ݨyy›Á–á3ƆX#}w²Bæ]gû©IOVÔ¼kãÈA‚Ž> kÀØž?ÔLÜö?ËîãûA=þñ}üj“wßw"¨ -Ë·è[Gé·^n¶E×§ˆ˜‚Ó²hY¸»ojD QÞ-@׉àË&/]»$‚n¯sÒ2Æô½•ˆvyŒé1œ z2-ªò8tm"f0;mŸjñDàº=e©¸áDÖ]ÆÕ¹Ì1ÛØçø7ÏëXpWÓçòœÿ îj¼™ýÖw5\8•ªÿ»šñ`ƒCõôø¡Ý½ßÞÁbµûYI a•*ÿ­çyŸâë‚1ô›ð /=ä‹_’ñR°7ÁÖgK¯U¨P¦Âjõ€~–̦\« oÇmMä¼:.ܶ½!ðoï2îâ$jtÎ}Ú&òhdE老E-ˆi}\g?`0œºàsCwÚÖ:#?žƒ™‘;Ø`ZS¤çVòÄ‹côEãØa¿Éz×qÜÈB‚™?Ú]^”ª‹²rÑ?k[l/.…}õköF6èùı·û¼'¬ €á£‰œ™yQ–…BE1ÂþLÑjeKIŠøO[LjÛnÒÂæÔLÒ†ån»ËLQ…Pµ¾¹Ù‹góž¢þY®±€‹‘õ0‹^½â˾6ï \ã¹# 5—_f ëèL4àH¨ßü6ü ®”?mo³ÙeÊ*àfV‘»ë°F÷â¤ÿ’y… ;G¾ÝÝf3ªÂf´ÆAÏÆ¥tNZÃmÿ±ìÐ]?yb2ë}Þ[H dYSsY˜—ÃKH‹8ÈX†ê¶Ý¯?nòÎO­ ùñîf<cÄ‹uU6ôò45VoÖšZçÏë›\·‹Ïq’üÃý*ïÊß«s´ãøW»6[ÇÕK>{Þ·/pÜ`Š2ÅžÌ<°KLµŠc¿¹Ÿý˜€ºÅkÊX]¯çxù¢qÇ>”û¼t4|¡å ÁF)¢nÞ_kšþOþ2ý†O8©!:ú—²U!kÕ#êX|ú´Ú­Oû¼Œ4Ð@؈8>_²J=arf>Èm¶ùÃzÓ®vyê Û0‚-JÈÿnµÙ?ôŽó62·EâÃì¶ýAù;sET˜¨œW’W‚5'@KÇ‘ßl?¬7«gØËÕЧažs3«ŽÊ†šÃþ)z;a#×…ƒ7Žþqk¹SäY*FÃn¨‰%~ñkö>®ÅžvŸ¹k \†Èí>þå~=#ï9¾ñEÄûFÄE–6£4Ž}dC,°Q0ë­cgS,ˆóŒ1€ Üá8éŸvÛÌ ®.¸¢Øþy}Û>KP{LÕÍóú§›¿ƒ sÄ=ÒhÛÝ-ª´Ì‚dØbì·ø û/{,²˜¥8/¸à,>@¶ë‚máŠG¡q8ÓuÁbOR±ï–3CLÎ+AP¾ºÉìJ†™¤ä²nóžsƒ_m_ØÅÙ²ÊsܱœASÖ_2{µÛO4Ž{×®ò”$¸@¥ª]€QÕÃÜÆ¡3'ÁU7wö÷Û§‡ÛL3le}Ÿ;½d—n4fŠcÏ~Ç‚é~ ÉX;æCæ=cAßS ‚5×¹g‡Ö6 â#æÎ¥ºà­ìϼòÕãFqÔÃ#®åª@ª¢2".ð˜õ•òÂeQÚŸCIZEFN§Ç²ó}”$IO6‡ÉtQ(nzì1s8WIVpjÿ‡/™Z²){qÖ´›&(æy˜%xÈšäG¯$¦öy·•"ê&Šš-©ê<®ª]_ùœ°;ÙJ³˜2B ®_~kœ%ß_]_½¼þñmÆ­4˜ÒÒÀ¹”Îá ¶ßãŠÅIñ÷×ïò®ê¹±–j}‘ÕñÔœÒñUaÿMŠ ÅÇx¾CqüóF•r‘Ó†æ6…ì* „Û@ÏYØ‹¾ÀÇ”S}¡¯óº~‚­aF"™.ÒÃf”Ñé®â~³gèø©À‘’’ögj ãà~®ž0À¬Ýj¿ê~J2 ¯µí64š‰Ó£ç/ÿ?F endstream endobj 62 0 obj 12948 endobj 63 0 obj << /ProcSet [ /PDF /Text ] /Font << /F4.0 9 0 R /F2.0 10 0 R /F6.0 11 0 R /F5.0 12 0 R /F8.0 13 0 R /F7.0 14 0 R /F10.0 16 0 R /F9.1 15 0 R /F1.0 18 0 R >> >> endobj 64 0 obj 65 endobj 65 0 obj << /Length 64 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»åZp¹äÍBÎÏ endstream endobj 66 0 obj << /Type /Page /Parent 59 0 R /Resources 67 0 R /Contents 65 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 67 0 obj << /ProcSet [ /PDF ] /XObject << /Fm8 68 0 R >> >> endobj 68 0 obj << /Length 69 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 70 0 R /Filter /FlateDecode >> stream xÚ½}m“#7Žæwþ EÜ—¶ÃÎK¾“ó­·]Ží¸±½Ó.ßÌìÚÑ¡®R»´®’j$UÛ}¿þ€”RÊ"3™w'b§ìQ‚àC@ø×âo‹-þív‹èô¢„ÿÿ2¡Ð:.|tEéÔâöiñ¿¿•E¹‹Û‹Wß¼ýöÛwß±¸ýïÅÍ­( Ãâw $+ r\a=}÷„ÿ¾1DoO UÀ_—ñ¸øQü-ÅDˆ…µ¦ÉÄ«onnoÞÜžFn}#ŽI ìÝúè‡w©N)ç ¯eý¨¦ªÎS5Åз>*ª6‡_ú÷Áeð­ß¿˜ŒŠ²¾Àí?ð;­ms.iú§¿t ¿“±ÍÿÛ7·o8/nê+ã 'C{ïÞÞüH$¬ñEéIº[¬?¾H‘µ¡´DRŒJÙ¤ER¬C] —õÓ¯ÈXü¶Wª¸_ß]>%2 ãÇOð¯ã–A‚OC8ÎМgøþ~ýñãnóþ~uXݶ;$$ê±Û„¤Ž0#Ó ôª8|~^5ØõEôÕø‡PÑÀFQ­‘/üó+êC_¨Ò><о=x GÁQE(›s}õÇ¡1¥î¯Cá@Eü}ÑÆÁïÀ/«¿. Â.Ò¿u$ªïkœDƒÜâBNj ÚÔ¤ºœHŠ¥Ôíoí°Kz­¨¿éKp Ú£/¿=¶M,|ð¢1ö«»£ -ˆ‰ÂÞ Ê6¹}5 ì¿kþ¾-ï—OÄé¯a×ú&TÈ!¶([Q ‰u$Y ÿxÒ…«më@*¥Z_<-ë!ÎŽ.´í1V_ 𬋩_é•§íýêqà©¢Ð檹”¢÷œhÑ·?Ø,ŸVÚVÂOK<›c|bÊYXËæâÕáa5ôE( ›¹9DS·g‡’À™ï|50¥L¡PÈ|Zß q¦ ¬¢´­EyٯT°¹„4vé»Êû¿:jæ—Zê.[½–N¥*ÞÛéNÃIkºFOï{ÌGÐwø=ü4–x¾-ÿ‡†kUÑ— *Z)ávƒ–ÛqxQi* O‚Ógã&[ë¤=ï JïàÙu~Àf«?бpA‹æG›í‚ B)bRŒ›J‚Ù&e‹É×ÿxûãÀ&´²ð †NZD·£·¾Y–Ýù‰ËÇÞ Á›¿ZVOû!HJYh«Dë›ÍÐR^¶8¬wpòLF­bKÓú}[8zfFµ¶Æ¶AhX8¤µ Aø õ‡]­”–‘Þ1SJXwã‹i+Y¥Šée5օҭù¾º[6­"Ñ×=`ºµåäÕ¯ÛÝç! ç!ØØÍO–ûýönÝjAI$œYþ¨ä– üÜÁ!dýûãɶ’Y ïÛ¿ÿ}}x: %@î¬h|QëËýî­'âMáÁÛÃïÞàÔù…3…)QŸtP>}"êO@mF-Û£üºÛ¾<ÿüjÿó2YÀGRF4>lÊÞzs÷ø²_Z½¯¨ÐÁ '­?™Ì§SeìË ëàŒ–Gé¿ìž7m1!±:}І÷ŒUã“ß Á Àã†)5?Ä8ÁÚ”g–*Ùý<ºpF×bê²¢ï,ÿXï‹ó?­ï‡)Gr Æz°¶b?Mÿ_ƒÔå`Ò g¢!éÞ¶yzÛöé<ümL8º ã¡õ=h9ø?O8‰$že=˜ >¤gZOîob€ü"M¾v\/ôÛz:âà4Žãˆ®Ó `Ã7f‘vâ¤5….i8¨¬l“¶g!»Û^lÕ |§½`AñýE$°Ea3àoŽäë(L¾Ì„ð»°t÷½}Xïs éK¡°6N‚8èdžY5F<ål€³é´–‹4u4ÁZÔEë²}¡C—º8QçÀ"¤ÅOC¥÷YÓ²sOÄú$oMjä$Ÿ¨*ꓼ5‰F´vä$SNò6ñîI>UO'9É—9t Z†¶v4–ÞP¨"oÄFº,‚Tõ¼îEä­.$øç­ù$#òMê©Û«Èš8Vu0M{u&UkºAÂþT‚âºÞ‚Jß3g8j ˜fè9—wܧ y‘alSä/7?ONrY –*ðåíJ¯s4HZŸc‚L©À™·hÒ¥¹ÿƒŒRhçR¤—{Ρ¡4ì|)Xžw+*îŠbýÓzû²ˆ[³ïM•œÕ@àŸÊÔ®)|Ô”6Àëùû©ô© µ… «ÆN³ÎÙà†Äê8dw©Xß=°¬„è‹R™ö”¦š ãQ›PôõÒÄ7[Ö&ËIâ#á¨L ÜHC2βžxñÚxŠöý ¶/ž(,±QÁÊG ÜGlê  9º¯öW„@ä• ¢¾}dAƒ©D.œyOAÃÚP óÚ8ŠyÞ†BoA÷çÝ–¥k´¬LÖ40ŸÖ÷ÓUg°WKܰiæ—:¤Æ=ÕS¿,`Ð#޶¦}U{¥Êé =w¡9ì•§ Ùî~+²c†"q#RÊ•qâHÖ|’7"àÒ¥UŒ;õFä4ÔÈÍ£È-Ô!—Ää09IZ´.BZ¼O¾±Ó.BZÄçFr‰‹ÖúN»Õúµè`ê]ô‹Ì0ñØ®ÃÄù*PÌÐlu øDþÚÑŠS¨˜`žiXž‚Åñ%Ëz:…‹ XÚ‰ ó9Œ î‡CÆÃ©·HYn%)A–Õ€qc¤†º©·-¾æÒ‹¹ÞcàøD\PÉÍù×ÇÀ1Éõ„Àñè¶R°ž^SCŒähLØY8Ó††8n9l±zHpÏ ;<ƒâà øNúšþuMYâ»4I1ϲeðÌÙ¡PgÚ2˜…FG –«X3øLrAç˜3Ö«‡ú¬Ïñ²QË™¦¤·¼ì+l%zJ–¤À´nðçœ×øˆ+’BÓ|Ö3Ï-Pà(j/íVwÛÝý54MÀ7¢Ž¹z‘³XXÌ ¨Ãa½\?òÒJ05”®GèÅç?l_,uæXpä öÏËÃzɺÇÜGƒÔ¡º\~ž3…æ»…*ENa¹¹ç$ÈàsÎ-E} ´ãdÈ`ÂCéCƒ~KAÜ=,wË»Ãj—•1×#ð­¹'·Áú®K^dMS»>H§ ¨íGÎúÖ;؃BÕ=ç~µœ˜%@¬¯_GÁØùÇÕÓjsÈ9R¯¤ b¡ÿÈÛ¿`æ[C±ÏK†Ô¡(•¥hŸ£Ü¬|H,uc(lØ9 ªt…F›$=…§ågž/‹±zR4–¼L¨P¹4ŸX7øè³$¥†g0€)5O/‡õó#+8„÷ ¥¦-ûõ5,‡Žy¯ìjƒ=+>ª;O ð–uŸ¾ xí²&ÞÅæi»gš º@k-ÍúÝr¿ÚÅR9ÌA/©~]³¢õ`‰”ÞPØ|Zo~ea°â-8Ûo_•˜»(òG[“™Ze|¡5…Ïzóq»{{p»ÉI3ì×CSDSóèyÏbº³Uï\ ‡Šêš¯ß½{ýÏÙ©ØÂƒ…£d‹v®o›LLX+A÷y®èþxûî§7·?½»É±0û5W°`]‡q~nºÔ¶* “æü¯o¼åHIUˆ‚¥oÒg –C%ðg‰Â<m¯/%hÇT6ä$1™§ÅeÁŒÝœ!±XŽÎ-˜b’FÅ›êNqÜ2¢ð!djWŠ ¯›Gu–ÈD?ðfj hlã÷³ç?®vË+–‰a e0By„÷Š©þ4Uz21ƒýúéùñ3+¡ÑÓ‰DgʉE‡µ%(ö?­ï§Ô{yiI|Úñ,‘·À¡ êí`ÄjÃò:ðî"x’w¦}$ ØGñ£—=ÛS¶Ð"ÿÀ»VÔ±Êh"X'³ÉDÆàЋº/6¢å(f¼ß=WdªU­{Y„o2ÃÐTI)‚|nš*?u"ßK7èWíšbÔ¤Ëzµç0XÖK̜αî×B+_HÕË+YîvËÏï1%¬]lΓózÕ«+jdÕ³ŸœŸWýLžõ|*ÐFpÿG`ëeígyëbf'Ú]iýœ'©©ÄÚSá³ó¯Ájý‘—"–®‰"f¾Z1uÐDÁµ¦ÅWK(œÛÞ…9Xa €É|‘åzªh«ËŽN¯›?–OÏ+ÖCà€;9IñJæÜ t({̶ ‚òÏZ•9O›8˜Š2(• .Ž©PyÒIïBb©^)îïå|çBjP>pd¤;vºÈrIïK‹¨ó£Ÿž·û¼Iíì*¬.Åûð•ÃXÖ(À"IÄ?n_v9ª­KSï¦o½yóM.&ŠU Ë -)´(NÔ LÿPJœ´ÕpxtÄ•†ó*xr «åÕËU¤®463(IYWe9Zébj±îòüô4 |᤼"(ø<¬èj´éS\4ßE”QPp|5ÿ¨¼ò` <Àžœ¿m$¸m Úiñj™’ï¦;9,ŒL’¥_E"öi(ùNQ¯øE“HÏða;‡ õ…p«xÓþ_/Ë#AËaxCpÍÉXó²zɘ&ü¬Ž'd޼¾ÎÙ‹¯°¥$XæåïEl±@‰ÝóòpXí6óøjuŠQU/ÃÆìˆ‡õ…/Q¨”»Œ«ùˆ`‘÷ )Â_Η gC“å–€hÆE¨í(–ÍüC«^>8¼\iº„¿ßv0Y«ÛIZÕ#.j©^æ#®²Ál‚sVݧˆê~DÐþ°Z>Í/û$¥È…ÊØ{,ß&Tu ÖW×F1€ó\›ÜlCA²\ÿúpxüÌP¯ìI’õûõþùqy—÷H¼«dCÕðƒá#ýÁbò,.]»}š¯a1øm$eeØ5ƒßÛóqé¨É­Êbº›:òY‡"Z?S§ŒbËK|S28#/®{ýˆÏa%(s\I‘>+ðrV÷fðß/É,¡‰½Ã|tO™õ!:Þ“*tTJ|Þn°Àöø2 Þ™œ¤¼ò5¾Gû¤·¿¯X'P'Ws‡*—sX„K8Ôï¶»M^t·O„Z5È_MH0âB$9—_qülà©Fdef Q_–³»ûgÉJ# Vb.RÊWœ£1ÆY™¯9žDidæÈŠhä¿XRTCTð¹0}UQ9öqŠ /ÏÏ,Q‰ØWn¶Z“œMƒ/®.)à\E|p"MI÷^ÚJ“œëù¬Ú„QÇ4åSÖÛL¥¦'¶% ÉÌ`hË †ð°'Á÷¨ŠÑ2¾,ªû¯4ï¬{ Ÿ }l!=÷‚Ýý*1Åœú¼5/b·Ûç÷œËåš:ø‰îf“îy·Ìõèø¶9x‘qµÍI_9 Ší{ºÄÅÂj÷_ò—+LýÚԳܑ±Õ/9×¿ÔØx»ÔêO-2®g©t0Á¬¢Oüt÷ûþîîþ½äd·`.ÂÓ}mŽéÛoج4 ú­´Û¯›ägä·œÑ/ ðšúq$ú„>M¼B_q÷‚~5DWrÀQCð“3â–ÇŒh]|Áýš¸HƒŸ¤$øiþ«L÷˜ý}q¡oÚAÔð»cEŒ,ÙS gø)âü&'0FÂ"!ûþ*²ŸžA[±%šNö«ÃtšN¶ªÃôªËȪ¤ƒ+/O“,ßbˉm'¥v…ÕvìÄ¥ÕTc¤‘”§¡zlÿ0_L,¥aÝu{R%ÅÐ4º”M¡ƒi“¾¨~ÖÚo‡îxF苺j#Åú9 uW1̆±ŠÝblu{Í"£U¦K\Œ¾Â%-<^^ŠïåãËŠ æÛH£ê×Cd¬eU_“¹{,ª$i‘{¤v‚ŒøÖ§Œ"ÍõpY•6m‘,˜g«6ÄÒ.¬8 ²²¥íRS^¢O0Á¼†c‰ZϧÕrÿ²1mÛºXøÐ ¿þþ°Úpt‚W…2¥:Qï7‘{äh„` +á|J³þ¼Ý¯1ÈÒ¯«"òŒ%Y8ßÃGL9¼Ç‹Â`N¼%&01$AÙ ––çcëÉw»­º7§Aá†Ï|<=´I0žå– º ŒŠ¡m×äœÔÑå&äåÀRbM0°¯y¸Øcj|šüÿ[µ* åã«§B0ûÕá;u¨€æ¸åT·ÙƒP½RÆoY±‹`“¦=˜«9AKJLþ 'âýRç{,:ôàu‚YPÆcÏã$ÿÿ`™2€¦ IÒâÕvÇøª ¹ Q4iÛY^Y)W”´`Ö V‘²O]̼4êh_‰¯Ü)YÜp¬%¬ãà`ƒ¦©ow‡‡í¯Û͹ô»˜å=a¯éà?lYŽ%ªUè¡:Û³´¦Ò^iâ󒺎¥ÇÒÐ|Ås,ÁåŽ2 «gäéúŸWp, ìW×+êœÜ¨ââ\B)OÔY·»£íf°Ø v[KÒ®ZÖ2$%ºÂ»¨\Öðˆ—÷¬à¾ò`åY‚}flLå)ÚÌó‹EcQ»42=6ïøgØFJnª&¬9nG7Íë$óþ©ì%—üýa•|KäÀ9T—ü¹ÕZŽÙ«˜–R°ž ý)ÇÕî•7+1UH¨L΋!@‰¦(8òiÆ×{(², cAûX½|.*4¯/=Ê'$•Õ ®W›¯XTÍÎ Ú‡¼Ü¬mì¿ %(ûýËSV”­WÓy‹øMò\\ॄ°'⹸ §áËš%*X=ˬ&çmð±PšôÏZ™¿´G´ŠõmY‘åø‹KÔXi“æÝh°ü·7mqè yºqþ…“Õªao)° ¼Ç>’nüÙH^H¢“¬«eaðÙÞq°î{/RÄÜ´õªÀ>Ö­YMkzN‘¾¹±UU€Öš…G3hGL†X¥>¶èOë{>nJW+Ä^ªßœËↅ©±öT 5õ,=:ꀫæö4íJ•2¬oí±…˰q<,/ë Ýf<ã]gVŸ=‚OALëŽûi±¬=½ mÈFWÕ^T|¦6¦Žì$g-E½•¨+æiLì?ëÄ`¦î Aå\è/ò¼¯Q ñFž"Î{ fŽ=J `[/OQ”®hå¤9ÿ'OQ‚_çIÈ ?óo²lÕŽ€eźÉ2ÑU Ù)Îw,a±Noå†v*ÇÁ«&Gn¤sÊîgΕõ`ßxr ‰ÔZ‘ç$‚q$¥*¿féÉZ +‰µZó³k)Ui1¨©Zùµb®›m=€H°å¸‹øŠÜy§N†í¬™€œV ˆ™Ìð±DÛN ÞQȼ¤o M´Õƒ`‚vf;W¹YY½e¦˜™þ >[á1†‘f~,ÏvT½O+ÑI“?'ÚrÜ«z˲Ñ "Õvv,Õê*§æD~‘—k;êybÆ'ü¯õf²-Ç€C;%Íȶmn-\Ú@NaµçÙRªêbBÿÈK 2ƨœÓ°xAxãÊ"JRpÆ» Nñm¡Qùw†óŸ5½«;XXRò,ç LpM®k;çvF8ÊêX½Å»ÐI·3bîÀ=½m‡²nE®^sØ£I‡®ûü–]ÆsÞ‡L¹K4Š\á¯XF2¾ˆ²¤äXÊ IKñÍ ـ馔6øÏkä8t }¼¶6И¢ Få‰üuµúÍÑ)Š87ÇWc9yIBs…$_S†ª›%1æ­OJ‘Ĺ·ZƒAï)p@U²€1¦êÅIðNkáɆúúVûÄ‚Ê!ÎÊ=;ï+ìÒ»®žDLäžaòŽ“† ßI"ÎLTÔóŸU—ö5rZÁ.œ¡ØÎ-®×cupé êC ”&€dQ=¦M‚ò++}SƒzwV|³Zu„hGngggoš²,déL2m.(¼&,@DˆJF1 †+¥6“Pϼ­6ÆÀpså 8N¡ŒÓÄ<ðYUIÂM÷5°ý­j¯éõÒ}7Eé-Í;/Ý×_e·5Éÿ¥û:¼ ðã龬l_…oÈB=Vw~YõþÇ~±Õ¶nÏëZ ¿¦JjM£Ù;â~ÅÏömŸ›í°Jõ›ã_°·`[+ ”/¯‘çgï¥ÕAó.›kˆƒ_(=E~×WC<(ðúcMþºU`uôG”æ}É3ÁËÂá;Ç4íçí³†yÁi»)hò^ó¶w’q'uÚdžV>Í^sb±Ø4ÖšÆh‚y±WENjÿ¹¬ZëÀºØ;o-tˆúuú¾yûí·ï¾Ÿ¯*5öyR¾&ß;©îNEIÆonoÞÜþðŽÆÄÔgrˆêZ’#üJaM šé·’ã>(ü@‘ [äCÚX­¸ôÿ³ÆDY^º*ýÙÆÄq,ʘXgU $lˆæt®lC4¹¿º Ñ$~u" ÊUlLµñe¼r> ¥ŒõO¬'V ³²¦-æ†( ëFI±žÅëhŒ:èæÓúbqÂ$8˜ÑPx=¥Ñfd“˜ÂIMáõ²Yÿëe•èFs RUõéËjýØö~µ¹JJ˜Åq?Qhýñ3+ÌØ*¸—¦¾ZÞ=pjAab®ÆjJmê‚®‹œimaX»É¤Ùçµe!E{ɽ-c½¦é’Ô<{dÒ{ Þ}1†ƒU h9°P¦ŠuX´×H‡6URŠŽÛFX0­,Wç>C!únŸ¡ê_uû ÕûN£ ‰FÐŽ°"ŽWD£"Wÿ¡ÉúØ%G¦zž€ží1TÕµê™ ö®¾|×›!6v*eo†‚`p0ɳz. Š&ƒß¾{ýÝMj 0 ¤%Í  \Ld°Qﶉ -îNŠ )M*hŠökZÞǵØeë¬èоâ{ô’¤Jù0È÷\L´VUÖ?Þ¾wÿüÍò°¤M‚qTªe¥OÔ{˜C6*MûÉáµ<ÅùêiÏ‚%èÂM_o8¢¢#–º¶(ƒQ…>ñvZ#uXz1›Úg*\d€‡6àý‚˜Êu“°/J×`»Ã!uÒ0ñs< ½²1¦‡é&Û·U¯óJrã¼¾}M_MQ'<±Ø¥.¦$fRV)8H Ö‡ }XROŽKKmÝên»ùM€ÆƒNÑ‘–ÌíÓóVkuXʪÙsßœ[®yšŒå5ÂòÃöåÀR¹˜»bM_ »ÙZÓ½%M³ÿq·|Z±Îh°ñœ‘ý£0Wó««&6÷pÚ,p<¶Öqó·Ѧ±ðX¤¶iÄ,PÐóÄb³-Pr-±´…‡Z=ZŠíQûQL(0S*MÑçêƒé¹ÒPÒÂÕ-VqÜ,­«Ðï'æö§t Ö6¡p9w`–úŽz©Ô?E½Ô§6](ÍµÕ &[b4íDþŠêEW±@צÜݨ,­«¬nÃrƒ%#°ÁwÏ×ËÕ/`wEç)òlý‚5pÀ4"Ä…«_09Ÿ"Ü3m´¨1_œ Î³]ªuUG<‰ Ëx1U­iŠïûÕ38°°÷}_5ECbNa1É߯€ã ­H±Ÿ®€Åpèk(Ecóª†M±Lm¡Ñš9“9ǨuêuQF’û;žq g6ZìiÚL… «· º¦~u…€ý}&™g*…Ñ%šçÝ–«+%ª›44ŸÖ÷CÉãS”¥)œ%…f¹çéJW(Iâëå~Å‹”®6Pð0#`¨*í)ö¼àIU‹B“à€ÉÃ3UAÛKIs¿¾ÃJ ˬ%H}i±»»›pœq”h¼[E¥Ð!.F›˜Œ$˜˜µ¦Ÿ(6Up¬1ñ¶Ødß—j/ ‹ΙºhÛf{^¸9ùH"3”ô0êË—X|Å·I÷s€ª€íû*òY·Y!D_`—åÓ ­p&Ü‚b¹+çIѨz0pš;5$EXl¨^<°€›ËRœ`‰tdÓ¼ƒòùú7ÄÕ-ê÷}9)6ŽAâÊíÌã"'B1¥¸«ÓŽbþößo~äņªkOÑ{{óÝ<ƒŒX2] CiŠ÷±”1¡L'v[&ÈWN-ËóñEÐä†qjGUÒ@Äæy¨ Ô×ë]ÐZ6[·yrOñ¼B_uŒ¦Ežwo|V” »EÄí¸q”ŽÇ'ã²D 6vο<Æ+<ÁÓSÀf«Ãj³Úï9IxPasêî0'ñÇAħéZj /Žƒhœ.¤!‰ï¶/÷9Ék}#GU© ÄòŽ˜PSúOXŒê¤ÙÿÀ‹Š(Y”¨xà÷LÍ&”FÍ“F†'÷Ž+¬CNÉý:]_40½Ã[A§sSz¥™tUó۫ĉÀ‘vÊËd1Ý®tE¨òLû¤ÅPÉ‘)( \"I®·ë{$à›H r·Ý||ÙƒšÿŠ)Âx‹¶º;†à¤%^¤Ä›*OL`ÅR§«iÒ4ëíϺ†1Ö*6è·hKÖ%ŒÁ¼,GðþaµÚðœW'%5»Õ몡z-çkyÓ«÷Lˆ”´øÒRÒrÏ3&± 8Ê©IÀlË w–ÄdÎ3•ÜC»ÕýËæ:q²ì~;³û冗׋6FùŽä»à<ƒ ²9|}÷°žî¦QÍ»"FYÓ³x\o~Û³Ô$>5îƒ$Æ OLÐ’Úƒ¸iÞ· @;–ª´¡(¥§è·\Ø9šÒëª#腼踰ë/ã©,ÁGÿK–b(á¿q黎âEúLუdŸuƒ&0¹¤Ü#¤ºV(ÉÝÄ>CÀµÑŠÄ…wˆ`g+K KÚ¶&é˜;)KMUx¶CýMfŠC¿Î¡cLÖä¹)ÇBaÍR‡Øñ!PÜÿºÛ¾<ÿüjÿó¡›“L˜DðU2Bksy¾¹{³õÓê}5k>[¹`Ý[(Û«°Üí–Ÿ«;ÂÎPbÆÊÔ É Qu•ܛ̗M'ò¢·ðgòY ?*¶õ§Éÿ–£äz´ñaP´5m–’ëÁ‚· (Ji¾?'…5™PVéÝ­¯›×÷¬ŽãEU=(&]o·žš¿_'»¬•ƒ<¿t®ˆ?-”… êxùW—Î"?‰[€8¥Ï÷nâ|1™Ÿ¯z¢-ª*¯Öõhç''_>bv6­j‘wd¢m(#i†eæKÐ,›¦óóTÅßéa‘ùp¬Z‹íèÓ ä¾í`bBaP1¤9Ï} ÚáÜÙ*ºH_gÅ£»¯o±1©§@ÁüZ(;ÂJŠïcâî|XÐRÖJQä»ö²pÁ›$U: —V°{2ø¶WÇ@±>5Ô†Åb)-@w*pHD¬e–FÃÜÅŒãõR‰¬´Ð°ó‰ó=ûéå€Ò79ðu“¡hßüãõwÿñ×›œû‹”YºXÐ=JßÝ|÷ÃÿÍK¥èÚ—F•UŽ^>°‹(N[§Š-Ui‘ºbKõTÅ–fɰªDïoÔŒéã¹Áq1R³îùKÝ)äÅp]Šü@¬p4§»âbbÝÚ¢]c—`¼®±;0‚˜Xc—á0ðtiLØë»'Ò=çç¨ö‡ÝËÝáe·*&*1\c—Zã gë»ÄÆüi˜D«Æ® pôÛl¿~÷îõ?sV¸_btq‹ø¤r8c«‹0±?Í…r ’oßýôæö§w7Ùâßy¤Id†}Š ¢¯\Œ¤È'cË ¶y1àßžÈg$ “´E³$žÑ®ÍzÕt,& ã"XB’"t-þÂKTà=t œË÷[ŽØ`Êm(=Åþ ý?Ö7+5EüåøÔBÌÅÅÀIuÙU]\²„¦^«JÁÎUïèU—ùŒú…¡Ž[gµf%œæ¨†,Î,ÝŸ¶8/cu,ÎkÌŽ{?T’yÜ.<¶³:‘S’™"}.É€d ªvbs˜¯ÿëŠÌ-ÚÓ*2÷ÙîYœ2AÓ|™eÐöskÂ÷Ž2æ5vßÈÚbÍ5I‘nì0Á.ô±zÚt"ŸÓØa4QQ“Ð,YÚÕ@‘íë0åd”UAW™ÃvþV2Ø5¯ì¬iÏæ¬"í-0Õê[às¡gA,ò†uŽUV§¢VbÄêœÖÙA©itÎÓ•µÑYÑÎ(q1¶ºg›3Éô$“sJW“HÁR[œsO÷³ÅÙfêµßk¹68“¼¨ÍÍ,}k“³‘jk3Éþ°±)&¼ïªŒÍ$í“­9Û<ÙšI`^ö+(µ©™d>p¦Ç®§4`ÂêÖ-ö§xbºÏïªÂ¹ýÄÌØuë9øB.‚ý‘ØõØ»‰³JÃê™!.F< ‘©Œªêht©‹ùÁësòJíRHðD±±uFðºWg*Ã¥P £›Q$1ߣh%Ew¨‹CA$„Š9ÎÅ1oâ<˜àúõ-f6ÑœÆÔ®‚ScØMÚ @Ì aŸ’&Ž´3z Ž[?g!’¶ŠÕ^=|]YC‘燯UaÙü•Ã×`µIOBÃ2 «je4.׈_+]¥{аâ×XI)¨6óÌžˆSN´P…÷¨µ¾J›X«D±eià]nâ)qlìO|"ÕHö±?1Åøhâ1dL‰åàC{€«$~T ê²A¸u†Üüõæ»›ïoyqlÌö&±a§}80ÎEõà„EÝЙke}´…:Ò~½¬¬TŠú5’>ôñiC ›«%}X >—£Øç&} Íï"E gÁ3ú}))`®’õÁáí7ºÿ“’>ÀÌôu׫?9ªc7·² Å<3¹Iûòü{ž™ÜÊ.MÊÓÍä®{—6“;\Óqr‘o&÷h‹¹fr×'øh1³U?':h’´?ñÌo03±³^’tgYß`4•úD]dxF,€ ŒÛŒ½€ÌÒÝóPÁ6m '¦wÛž`…‰©îéE ›mg…Þeÿkzìµ]5Äf)SEzÒK=Ü oúö5r†*»Æz΃NÒ3#-gÍX#ÒìgíÑÏs†Eû’´SmöDn²ÖåjP¿ÄÂfE9›ED@¯™h»Ôg¤LPUD<¬*Ö¡IÐ1Õ2ã„ØnÈ;I@“âLö)ÁÍ †`|jÎõÈ@b&–#ˆ9 P9X³ Ý2 S⛢_%5ÅãŽjl¸U]ˆ¦¼ p!þ·ÿsëWf endstream endobj 69 0 obj 12434 endobj 70 0 obj << /ProcSet [ /PDF /Text ] /Font << /F10.0 16 0 R /F6.0 11 0 R /F1.0 18 0 R /F4.0 9 0 R /F5.0 12 0 R /F2.0 10 0 R >> >> endobj 71 0 obj 65 endobj 72 0 obj << /Length 71 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»åZr¹äÍBÖÐ endstream endobj 73 0 obj << /Type /Page /Parent 59 0 R /Resources 74 0 R /Contents 72 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 74 0 obj << /ProcSet [ /PDF ] /XObject << /Fm9 75 0 R >> >> endobj 75 0 obj << /Length 76 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 77 0 R /Filter /FlateDecode >> stream xÚ½}[“#·ræ;~÷a7F ©T¸ò“Ž4ZëAò±4ö:Ö:¡ Øœi®ØÍ’=Òø×;³XEUȺ=kGœI¬@"‘7d&Þ¯þuõ~õ·7+_y#W5üÿåoÊURú•õ¦ªX½yX}õ=¯ê_½y»zµÙ½ýlõæÿ­^¿YÕ•ôŽý (¼ùœ¯´¯”²×O7øï+î·zõ°üíö/ö«_`{Ãú30¢RÒ„3xµ{x× ›˜²Å)[~PÝí6#_¥+ïe¼JQÕì²JU™jìk£ªZÄ3üáÇÿýíßãG,ý‘¬y%>úîço¾“¨¥‰”¦Ò2þæß_ÿüËÿ22;iE¥k‘ã§±ß;QñÞÄx¥F–¢”êŠG¾ûáûïîFd7öP0bœ?j>ƒC”Ó•à<šò¯¿ùåß~~ýã럮 8ÓèJs¶xäÁÒµq•¶Gþæ?~øe8dwŽœ¯jç†CYÕ\±Þƒïu]WFùæ{ø©¯qš«à„ƒIÏúßãh5üŸäømb)œ{`H·²p|ŒôæÅ[Áqm+ÃÕõ×㇛‘äÖSË`ÔˆwÂ]d$Ëj^Y<ŽT};½ÿ­ÏëŽûRÒBT0E~ýjwÞ>œè3Â`·r½oG¯ üɃØ«óý6øÂVÞ64᎜Ññf´Ÿ°Û'ÊWNʘ êJ…ßè±4È7®A¾ÄAJÉ@ü Mòj³>oÇ>‘²ÒÂFk|w8~ÙhSå:úâ¸ÝŽwýaXðã•×ñ0wÛóz·Ùá–¥˜Õ Ö”l>Zÿ~x>©SI¡€ ƒopéåøþ@澸ێ(§Ÿóxˆ»Í•ñXs8’í' ?y>mïÆ>‘ÀIÞÇ 9Ü>È_®qZ<úàpÜmGÈÅ`R•ã:úhýx÷Õá8Æ3µ¬¬äÑjž§ ÆÔ1ÅvçÝáqd9B‚,òr°‘#ƒhwÂGì²9~<×û±¯ÎŒÉv÷|Ü=¾›!ë$Jkuùæ&à‚/Ø•/ï­Œ¾xØ®OÏ#3Cùƈ„à›ãöatCAf¥¥Š‚ Y W PøAgvÓÜõÖ²~|ÜŽñ ÷¹3Z̨°F&óÈÎÁŽØ?`zTµ~¿ÛÜ,DH,æç,ýj¢‚í'®Ko8ÿîf}'™Ò[‰hŒ·Çõ¦ã~j5øÅÌá°ëj:ž`z}¡×ö8¶ ¢ß*×}®LyÜÞ…¦6hMPÍøÝåoÝH Ô”n¬…Wß¶Z†¥¿Û\Õè…Ÿ4Z&1»ü L/y<Ê»ãáùé×W§_?ûzdz¨æ…bÁ‡¡ Þ=nöϧ݇ío ÚŽÀ²¼3 • »·o“Ÿv÷Bß`h„ÊüÛX%“ĺ~=PÉýO®Ä >ùc„¸`ôK…ffðû±)i/U}RÃ)'7ƒ3ѤnÁ^ýÖÒ²å8”kÕݶ§H^é•ñàN]¦‘„¹ü«ÝÝ$3A»¹)¨Fà¸\v×X8›’³Õ­McE—Øäë` *zÖPG_yäõ_뇧=m›‚ÖÒÚÚöë‹0HïǶRdcðã_¥¨)p²ZÕž‡¿ÿ}›+=땃°Irý€½ •ûÀ®–À"„ÿûwüœ]mjÞXÁÏag"áÑ·¥=ØÒ!e_éþ÷¿Ó¿bÖ°aÁ¨2I߃Œ¾³ôHâ g߇ÓYŸ#󲮜Žès$gƒ¼Ñ# 1Nƒ+0@?³¹;Ñ¿^ÖZ‡èo#“1¶ruÄ8c–€¤®LÜÌåt>>oÎÏôüe âQÄܘ‘įu‡GÛhpl4…Ûï·§§ÃãZƒÔG(Hx<ØéÔQ䵫@±„¿Nñ~w¹Ð žDøó ÞÇ0ÆëºXŸ÷ ]eþ£x¬£â•ÖH‚Ã!á.„E™£ï8þo:l80ÿ‘H ŸT,1þ –_nvÇbUÃÏ- >ÛìÇ‹$ø`ý°=®›e²Iª _ÕJM¬ó·óǧíbh8þ/ÏOOÛã•0 åâi<î¶û±ƒÙ¨¼`á7¥65µZ .œ÷‰Õv9 ¾âÛx*Œš ¸ è-SSyØžïwAÄŠœB„C¶ïÖCR°ÉU%PDß6ëÇYd¦å—~L…ÒèY×ýÓ˜1Z£WåVáGl} n«*ú<ž‡í鋲p0²eSW‘2°ÏÑ}“ÝM¶}wÜ&º}e\å@q„q=¶ ðÁ+#lôÅi»ùbľè:¨xØšíæ|—>È"Úœ»Ýé¼~5Š1„á —$ÆŽX0ŠÇ[´yÛžöÔhŒñ׳×Ó0fÚ¢C&ZÃêÝ~ÂÓ€Óß0öGVƒ~GF>iaZÏh°X„Õñ9˜úÚ`|úrGÁòM}­Atj~ñØún-‚Ï&´±^ Æ3Ã_ÖþÅZòo€tôÁ”¹o+þDûEsôFí}§Gô‚ý(:Z=6úà´=ü¶’ÂGóyCÿL#tBôù¿ôd¬ªÀÕ‹~~x;âLH0l4—ÿ3òk°µ‹Àwûý.a=›eKo:ÛnFœ >ˆÇð÷ü¹;߸®²RE#ü¯@>ý Çcæ|3âOp¼ó‹hù_Ûo¤5ï¡ÿç7àŠýñêÍø˜¢ßb¸"Ìît×)טWÜ{þëg_3aãµgáGß*KÿD.ʨàçBXó%üýG5m(jð ñÖù¥Ìs°#¤Q!lc½œfšçZÀ>Z>Ën±¡ºYh8þßïwûÝÓiÔpÕ"â/ÿ>­Y»ß_N%ØõW£&F·Z>vkÝ7‹]ƒâ q{œgåkðYTSÆæŒí €php®Ïë¯ÄyÄÞm=šèSüŠ^5 ·}sÍŒöjŒºè8Gëýæ¯Lú믣ßúƤkœá·ï¿–5ñ·Ñ¸#$Kõ0·ùöý¯Ÿu'ECÕk•ÈÐa€îr.&Kæ€4¼ÝÙ7]snÿêšCÀÚ‚&ƒ€ûÕ—ƒ\etÞÇ¿µ)ðפvIæëèå(ÌÅÇJî )˜pGƇa—azâä¦Öb r ¥ßØr‰úØ`ûÕ&ÆÖׄ£[~yâÀ„‹‘°>v;ï¿Î4?©QqM>[D“þÁèØøPz}7W¢$Ä×o9»žvçËÉ&”ñgz¡mÝ…-’nݺõÚÂÜÆm¾Îp¬?„DǸ@`bvKù§Exà˜ÊÖÖ‘èÉeùÒ3H”Ò`ø½¸ožú¬MÁÉ5„QâÐΞ¯Â„O@v°þý ò,Y”²@48 Ô*Út6§rÌãVCø–UÃxu–Æt,nèù_¢ÁEÌ*„ƒ#Mo4˜A%¼z9 +…Ñd冻܋³gí28+ÒÓ 2Üe1€gK6¹9 Côv“ƒ~ž­%.©Ôìûÿ¬]Æè«äô — ‚’F“T ɨšë„"“±Æœ>=B§ðòe-¢S `jgØ"µ£g ñ6½ ÷=÷ÿúxÿX´"!}]9ß X:†¹Ð²I%º±ÒA‰.w`¶íšŽIDë!cs°Ù &ÍÿæïŒÆ$†‡¯7¸Ä$ìKL"“&]L‚¢Ég‹h>Ÿ1 Qš¿­$hh×ÛÔàŸã³™§M: |ÊkÌc5óh˜¨HNçkÁ¢Q³ØˆrV€E¡Ó!ÖµÅÛq¼ë¾D'GB‹4™­A»ÁìØÂQñ•U†Zü¶0ž"À­txòȲGA¼XpŸZ|–ò ÄsVõŠb¼ÏŠ‚ÝYNòvœ|s¿ìÐ rÖU¥,÷Œ€·]thúèS-§&ÿ¸=F! –ôÀìE ùÆ›ýút*ò‹±šCIA­àPRSÓ)ðÂx†àÌuæ} òîð¸»Ü¹í°ÀKK.a wزȇæçCtÖ†E!!¼jG¹žz˜™p¶™œÆëÕfɵa±õ啨àó¡ˆñ;±ƒQîû“?=?=Žç¢ˆŸÇ\C•]ü–»²x7•ÿ”X@\É—ôÓàyyCPõÃRBÅð^@7‡>ì²¥å5ûÍ̲ªHº¡W$“ÜŒðÃÛ"Å…Ý œÖlõ3ä¦Ã[rs?”‰5Lª‡‡«këýs™`CÉPkIòþ²`wì˜trdg=/»}¹e? ¯cv )Á AüTv«á/iðÇÃyQˆi¨UŅ裷;ýnW¦ÀfÞibêÊ´—0Í¥C{ûøEÙ•^%ÕÁÌã+s‘hÀö˜î˜Ã.ÓR ;xŠæ»‡§ýn³;ï?1|wȤ©xÍûš}ûþyÙMÞ@¹ƒü‘\èn€Õ"Óa’D/Ô(ø ôB—…£t†ðʤAm+«5÷„h^&ú1w× Ï–IædŠ Öõ©Õçf6.‹Fö+þÁ³Ve×’NYM²Òë0Óq‘šÖfBW\‰å%µY¶Zv£)á¨Ù>S?Ì^î+¢Ó‚’ÜÛ_tŸn@![;¥5N oÓiìjb ‡}á}zÓ1€dÔÝã"ù?¼­WG~CJ?@[îŽeû‹ ‚äβl9 Š­!¹ÓäÏ»e‰(˜xiÅþóý*Ý ©@$Ùçâx|½È¤#òw„ÅŽ.ÈßaTþÎú¯Ý©J$ô”Ìû6ÕÈÈá4n†eUrÛ%2¡±!ààŠ¤ME?}]t­ÇFmX¥äW)T‘ Å>@—<‹’›æ<›}·a«U]»x Á —îdI\-*«I#lËNoóu“,ÒÂfoÄütk%Dý½Žè4؈¬úy/bp6ˆ}†m6†Çð…þX?=­¿|·Å´—ãDz¬k.Ñ-%‡j7£(QºJËõ‰5² ¹ŽT+_• ÊÀnÈ?–N‡Óf·ß¯§Šê¦+A°¯/ªôñ­()ÊÄ{VïFضP>a¦ÖÎÛŠŒ{Y7]?(=·›íé´Ðͳ{ÀðäW†ú ß—JJ—¨u™üX§Œì_ŸŒdòÏ0&3ù±Ÿ·µrêÎn¡÷n/@Œ•è—ŸßeôGcõS±³«.ý-6[”Ñ?Q-ÐeôGóžÙe`ºZ³„=I“ÏŠÎ^ÇH5vj/açdÜ“›½È[ö¢’M+¥fô€|UX²®*+bðÉ^X3Ûˆ¼– Kï—”ˆá(rv½ËÜÅšì ìÁÖ‡g‹ï)µÃ±Û9÷ù½ØH¢’~œxŸãÿe*î|VP#Ó¿nO÷Mžaÿ¸~SkÕ®âN( <ì7PpÕp#†Ym’¼æø<¥Ñï8“âŒ6¤tº‚ Z,î 0Lø±Èyñ?·cÞÕ¹yÐ0dv/•ÖÁñálAíìcac']Iš6 »Öõ/„ÿ¬,ÙJ‚ï~øþûŸÊ£ ëº/aÇbbîS•UÓN¶3—rü$ü;|c¾Ä»Æ§Ö¥7, _-äøXÏJá+áôÊZW"™îþStY„O (PYÄhç%€ _wµ¼òJÆkmäÌfs¨¶ªé aë«E2_Ë&U¸v¾2J“3_V·ÛW³’ƒ‚!Kص;«¡hÇCÆ€Òæ7÷e2©yÅkÕÁ/êÛ5yt%6c‘†oúv]‹¾#gþÂTÊžmæñ±¬xê“"Jƒo4z¡¨Å<<ŸÎEÑn|ÕGmÆ¥•@;“ì($œ0³îî¶_–±kw€³¤6ݽýXȱ¼©Â§ðïKVTÚÀ§áƒçŸ³¶X6M85ûCYî ªÁ— ±ÎºÍýúq·)삈ԥFé̉û5æ(n»Óy·)뚢ˆn®‚¡X¦øH¶1ÃnšŠ±RQ¶:ö+PŠ‚¿+cTmaò6ËnÂ=uб»xñoR›&—†¿8,ÿ#Šœt°¦@­›ñéÙ¯ï¾Zø8ÑàKß´ÛIðtÀÜÜÂåÀ#¨#v 0EZ×5%±€Ss£T&€Bµ3·^¶›]šýïžØ°¦ètç /¸Í‹÷z•ʃëÐûG`sØï·Ë²ÈÓºÌ4OPk(Õe_–ô.Sg½¹/‹á«É¸Û•=m©t]iAÂ_Òø‹º*°ä´´Ô&ç”DÙ:à’‘Ä‰C|ª‘+ðÅ…VVU¦¥ÖtŒÀÿ¡¬‚Kãu†—c‡·$)EÛþtç({°÷b6¤g>¿ƒ>›kø$]-FEÂÒ ™kM¡«bÒ½J»JyE­¦°# OÃûœM5Ð_T† Î16'æ>ÞAúü‚~¯­¡Ð?ÙoÌ+ ôµàl´‡~†nº2šÞÕseÐ0Qz„gŠäš†]UœQè·6ú/rŠ9ÇÞ}«Ñ>úY3ðZ„öÝ/ü4—ÉÄôKÝ:‰Ù VPðe¼/±ðƒ}iÊä=qÂâñ†šü¸C=‘ïJ×ÞÛI¿èTFÆ0bQUÑ˜Ææ¡äYHvÒ_ÒxþzÖj°ž£Õ–´Ò'5ø7^Ä£Y»Kõ´‚ £–¬¨PO£MÃñâ#½šÒVúÝ4‰…yá^úRÕMjØ ý…C-¯,…_ØK_¢­ª:pVÒJ?)ÊAâÜôä‹Hã]ž2…~i¥_d@Z3b€E--“•èÒT¤9ÿ®ì¥¥=Až®™k¢<|¡ nð5#’þ?zàøF§ ‰Sú̞ÃVRRa[t_¯<øŠ<´ãúç· ×J¼L ÃRú3¼MÜaA®cI£þ [ÕXØc':õçEZ$F…ëÆxá ‰ÏÚ8E­àîØZÅ'«ôæ€"W˜—Æ^X~Å‹&¥W½ÙÚ;^,³¶ŠZÏ‚Góqà„"wc ì‡ŽŒjúó÷ñY¾cÕÕœš}ó À‹œe° mxYö®¬qŽT®òRtølÉ;3Ò4tSiDL¾} DZK§+0Ü#°‚‡‚ç+ýõEñ/{ `²~UâCkÎSð·—J²ü¥ñ¶Ïiae/Pý4}Ýd+‰^Èê›Sëæ¡Ó>>Ë Øf…å½h¥g?òÀ¢¢2NÚéQŽe¥ùÊVZj—…Í»•ÆÆ²äþîÊ£=öe$°ËZÉ*숣)²”?2 °1q£›ZP†(€/IŽy™Gt}ñT‰A»d|tù y¸ú¯ ä”é_Å4¦¯´91ã})¯ . å¸'ÖÝ&Ua/r°-¸Œ°?aÍ•–B[øÉ`UQ²±ºé™Ø¬;úgØ£óýá® ø†&šò½!^¨ÐFƒÙ‡éõöò.1É: nŠE‡7Ý볬ö¨Ë.¦hòÙËM\6b3ÚÄôv™e)@|<Öv£²é\ïEbÜÕ[Òdƒ¥°Ô^°î«kë`çíµupÍoÿ*Ý"F¢4¢4'û]‘ó [#,©4ëæBgË&"9£ ô€Š7hn3—)8àÃNiÄM`ŸEíLÁgÄlI»ð^¾{õc_ÜÑtÆd@YÎ’ÈSaó>.‹ã%=è4î˜-‘,T¤ÄZiÔ®é)iúB‰•–4ôòÌ¡0Ãó Þ5çtÐ49( Fƒe‡}»ÂÆ léÁ“h»›ô¬·RÆ`AHÔŽ³7z âðv·Ÿ%+î$ðœîÍ9ÀN¤[±yB<=†Z˜½z{<<äI7 fF;ltx¿=¯¿ÍóáY,‹,jn‚ cêm„í0'ƃQÁ&;W²%´ð®ª N¶e¹÷_‰,kÀ0\±éÙ.!-fÞaEÚ÷cæÐmµ°•PžÄ=mÖ': ?Ff§9кʣïÅÓ`ÚÕÍ+2EM)#ÙŸv1´vMuÏT ›vo#av-ÚAØÐµx|~ø}{üíð¼Áíi–œê»®Rð_£uL˜œl0ñ¾i޽?z´ ß\<Ï¢FÚÞ¿Î~ß`D^·ßg¾C2ma‘©-§`?Ì’ûÃü*Øz.Ó ìÕXýϨÉÅÁt7ê ïü6®˜¼Q“tËH ÈÚKªqðGÝ[ÿøµQïx° úh º÷’¢ÏXÊå}4ºÊë¹ ’>É©¤& î#ºy×fŒ I)®ÃöÇYDu¢r ¢ÞoË3Ø1–û 6Ì0Ë ¬“òXôØÑsøh‚J 6.êú¯¼íE¥}ʦ™`–ÛP_ºÏ!À|1©¾M¢Ž¦Ü9OÍ[~. ˰Ò*‹°˜8ÎÑ IS¶©Þšâ/2¯›WŽ&ïhëøU7ýíæ—-9¼ò ïòà]ƒ,c´σ˜ïÄ[ #î?Æ!½÷$÷æQ÷*n€‹mⱜ ‡”-;ÁÚÀ¶ Qh·D6€U,-£¦ÜTQN¼B9vžU ‘$EŽYvB l\•] 'G‹÷Ƹ®6XøLÑän›Çr\ƒ R)Æs}ÇŽ´t•äžÂÅJÿóîW)Íö.[3Ëïõ…ÜïgQ#¾b¸.›ÄÆyù>Y’_*0«x<ÒUª<¹}|L‡É2\„¤FE?FS_=Ëâ,·éÓ<©°‰~vPógŒ:ç¯Q"Ài±”žìC(<‚ “¾E‚qKˆ))AÒõtxΣ¬“õ »Ï §7f¶§Èú{žd»žf|B¦òÅò´)ÞNqCÁbšØ]ž6Ûk·úÀl‘D¦È7]À1]a˜åÆ]mí4t¢ã›Œž(îšpÙ6#[•Á”´0¯°,’ìË•Åå: а?¾þæ—ûùõ¯z“BÐ|# !øØ|§)ÛˆDM‡oþã‡_ò1;«ëޱùåO#÷ŒÝÙÅT7l:>7Ü•ÊtVR°OÛãÃî|žy~à¶n¼¹>xW°°~|—w™‹ñ$í8#f½;e…âes¡âéÚ[:ïjÍcñ,¹o<ë†\z_I/bPw ?|‘w‡ìjnÆÚû ÞÎôä]㥉°MgÄ~Yò Ã/$×VY—s]¦Sz뉹ôþax5Àâû§Ãòé`èLs:}ÿ„áýCó®-¬â·ÓóÓÓáxÎðºä¦h1óV’ómRS„9šÔ4CзÉLæ_%—7ÌœK RÊ›ºy%fFòÒ`YÎÙw¼2Fuã²å;™<ü—wzâÕLç-y^Ië®sI>yÞæ-v ‚Ù˜ÖÌ ÒP~`GÁn³$=:ƒ: ɲ“–ËG×>ÞîEIK}à6‡«u°$"šðÜS1®Sø`ªµ}–8n-`_=ØÖNqÁdš½Û¯O§,ÍѤÄó ö^?íöûõñc^žÃø^M ýE–ƒ‹²H7.MnTRVÆ3ŠïŸ×Çóe¥6*Ø@ïøB³E)\àíI?BýEfn˜©àp³1~Îʾç”,I·»‰´ƒ‘ô;ìë#^žå0¸¤kþâ,§Q¾ IòÜÃv®6ÐYNÐg{8<åÑØú&5~„ÆU»H>ÂsæF: ß\Ýšà…ÞΑ1²ª¹¢™+@-+)\Ðþˆrû|¡ ˜iGhvã 8±¼ ‰ãò—­éÇ–S>šP•3¶û0á£yçùhƒLØæ1bjt0¹ öàr­®_/›ß¬Ü*LÐP’š_vðXâ…š¦õn_õÝzf ÷`«5Ê Ûá»ìmNy VŽ£¿C?æ%Xa®y[§Ê–\Wö.(jlR¬HÚN¼ë’À½¤ä¢mˆm¢ÉξKaéÛQ‰ÚQTí±?[»Â‹ ãóeùw?ÀZÆ6Ó”mNCV²¥¬+qÃ]Ö°i$Ý¥ñC´¡p›'rr²´q ‰e—½šk§9Í­…¿Ì ¨Ñ%¹U›Ý$u)‘ eSGGI D¨KvÄ•å§G‚üÆÔlψ¹þ¹;ßçkü¥ó Û>s|Þ{%[l®'Ömž#BÛ>§};çd¤›‚èJjÞᲩ“1;²­}c¤%ç ¸ÇÃóSÓäë¼k60¸³1¼ ´Ðfÿ|Ú}ØþÖ ”çû¢•…6TøFy¿¤£5 /øYnG…n:Dõ(4µ£lrGÓ¸ÁŽ.¼Ýív´‡Ûj‘?2Ëúà{͈Énó(Û¼`) |$ùŽÍ`Šºr\ÆÐjYóìšÅ‘d‹Äµ.ƒ÷9r³Í;©¸$p]%Gé²–´»Ë8 !h^7ÐDlÖ §þÅC³iØìz¥.2Ûƒ}©Àlz¶…qÙ4hYX6_—²œ¨lš°EAÙò“Æd‰ÝËË£îB²PV‘]9žù‹%Qwlƒº0…:Ýt¶5_Àñf4l¡ñšg%¦kS…*Yr³/çø‹X’¨UÞñ5—˜L2’µ‹Hêd“I“$i¶LÔàŠ;íÒDý33¢[7ÓIÈufo2Á+í̧ã6ïðc¦ª6)PöêÃîð|ÚçµÐjž‘•Q×Û‹þöòzeŸv¸Ëë–ˆÇB1w-²;¿È;¾F4o•†+(e6ì/Rk·JcÞï6÷™I5¬XKÀF¦[ScÁ÷ÓCPv¹“È<Àø´ Q¢jÞýˆÕ¯3O°¬xÈP½æ pˆ›[¤¬«?´ „”}pv;qUQlS¹…X•4ÈŒ"ËÍX¥Aû»Ì°2¾VjT$Až)îts¾z°¥Ae¬ß6Y'ú,ŽXâ¦éQ‘F Û,.”ØzH‚”Bc‹L¡’˜lôÁÔQ™ V¬ì0x.x¿[/Ü®îuw+š´ó4~ϪRÌY«Ìçs^2(¦©sGPõtŸ+aq«(²>çu0eͽ·¥ˆ^P/*Ü“øÒ/u~ßf%à+à5>éÞ«SnCf0dÀlAcxš¬øÞ5ÕÇmÞëŸü DëŸY]o®íM\åLÚðfËk£M%­ïc²®Gùe™¥€îk÷²™¥è*hù¯—¿J콋àà–ÙA?ã´ýoXÀm endstream endobj 76 0 obj 11368 endobj 77 0 obj << /ProcSet [ /PDF /Text ] /Font << /F4.0 9 0 R /F2.0 10 0 R /F6.0 11 0 R /F5.0 12 0 R /F7.0 14 0 R /F8.0 13 0 R /F10.0 16 0 R /F9.0 78 0 R /F9.1 15 0 R /F1.0 18 0 R >> >> endobj 78 0 obj << /Type /Font /Subtype /Type1 /BaseFont /NLTDNJ+CMSY7 /FontDescriptor 197 0 R /Widths 198 0 R /FirstChar 92 /LastChar 92 /Encoding /MacRomanEncoding >> endobj 79 0 obj 66 endobj 80 0 obj << /Length 79 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»åp¹ä R?ø endstream endobj 81 0 obj << /Type /Page /Parent 59 0 R /Resources 82 0 R /Contents 80 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 82 0 obj << /ProcSet [ /PDF ] /XObject << /Fm10 83 0 R >> >> endobj 83 0 obj << /Length 84 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 85 0 R /Filter /FlateDecode >> stream xÚÅ}ë“Ç‘ß÷ú+Övø°R×»Jß(’g1u$ì£xP0»ìœvg ™Y€Ð_ïÌžî™~TN?²—–"ÚýuVVVVfV>þqóo7ÿ¸ùÛ›$“77ü÷ô7¥1é&$/ ¯oÞ<Þüî_•,nÔÍ›÷7/¾ùî_ÿõ‡?¿¼yóŸ7ß¾…4)Þ| U"¨›è¥óîüÛ·øï¥J1wóx£%üíò/n~ÿ–#"&éœmñâOß~õãÿùáÛ?}ûç7ÕçëÏ u£|’Ñé ß½iWœþ¦‚–Ѫև¿úé»ë/fHÕ>È`ο"J†é3ì¼ö»!Jtësß¼ôÏG'‹Úäåð«å褤 m>¾¹Füœ1®¹–<~õ7SÀϩԦÿ»¯ß|÷ýYDr¿e½ô*¶WñÃwß^á²p6È"by»yß ø_ç¢Tn‰¬PêšXTsùè[|Ù<~¸ÂÞöNÉ»Íí™JQSYŸ7ù"ƾäz,¶]"ËUŠÆï;«àœ~~4¸°›Æ?hà 6Í_ÇÏ üXÿñ 5³e éÈÊ*|è´ÇM-ЀƒƒeŒúüÓ£â…ÃÔXfPMj*9(?|õÍwgmÒ5¬ #]0¢\ XC¤GàŠ† (4HH)*¹½h‡oVÇÕuX‘'ô”Cq!p7Çõãá ,&ðå5(ÓðvwUádˆNäï×£`ƒL¡ä-þåF)74o›BÚÆÜ› .)g·‰kϸ¿ää>KjÒÁ)v‰âj)¶ÓD¬¡á€Ã-BòávuænNOkåNú3ûa·ÿÒÂcšqÒjÇ/îÖ‡ÛýæÝzÞ1…tIq­{Šu´pŒÅŠýên³zAV¯µ~p`KYÓ£w³ÛÖöÀ$>€=¤¼Ò5n×*y:¬ïfÉÜRÆyMÑû~·Ÿ%jª€‹¡ Ùð¸^žö›í‡QG¯ö†±®^¾»‹í0 Öà±+ö«ÛrûF`‹v‚ˆ$›7Ûãz{˜wø” Ôæ‘\›õáÕ¼£g,î!ÅÍñ0ïèÁîig)VÜî6« §Å8ªÞû‘âÇj;뜜µóm÷ø=î¶»Ûûýéþçj””dO‰ðç¯tYón DZ©ï&˜YàÔ”W`YLV£MØh$øK‚ ø°züø°–³NŒVAÆ"Q¼øËîp|}Ÿeá½bŒíÁW:ä¸_¯Žëíq–R­…EG¸]—ôÝûY ñZúà …šÛB1‚à×8ÐÖì»õêqÖ…¥ `‚mÀŠ–ò8̳ŒXð–älmiÜÍ2Á•S'MJpâËÌ“g¥E£«‡Zž¼»A‡áÊÑ ´sžÚ¶Ã0I?`áF’ÇCƒ ®)pkS'½b¤® ¨MÈ®¸æ0 à‚Uèüù¨ Âa˜)´¯l–üú¿ùöÍ·_¿ùþ‡Y¼­Õ hLëý€»0^ráÊð*d`EÖ[ øã 7Oî¨ÛâÆOm)´åßÎ,(¢ìñöëAI4@o. xr ò¨õ‹ë¤6PC'Wei/>ìwOß¾8¼}ùûñ|h€«Œ+0a/ضqrož›Oë_ʯÌb â;­ÀIÒÛý˜Þï÷Û _Ì ¿ÚGæ²ó¡{k|=ÆóÍÀŠz'/¸×=_Ê`£ö’Àýû( ¶ 5hŠó âÅ,à©3¶8s kÀ~™.s¢†Qˆ¾Ãƒ†²¬d¢t©Ñ2–Õ¿ØÜå$¤ °zÑFçË`Þ%Þ(~œ¢Økô€0'JÝÙæûö×¶996ÂuáBÜŠj¢¨A7†doòˆo.Fß6™àÙ")ôݪC{ +p@“YTñbœ¿Ü…ÔàÓz]AŠ¡ùæ3.`e•ßX*ü“ãèxö\4ëi†SYë9}0·žBšYv#>EK-åq–¢-ü8­£@ÅXà“|$˜.^ÜížÞ=̳ÊO»)¼sOõ¨ý¸ÙÞïÖ£dåšä«(­!ù(öÈ‘”–Ó'sÒòa¿úx¿™%ûÚZ© M-èHqJŒv; ¸×â0£Ž_>®yü©?$ºìùúi–ƒ«*“:ò+øß£Î=bñ|š6fºûv§Á{‚ÐU¹ƒœÀAN¨²]Îö·ðóêÓúa½ýp¼GM?KÕ¨$1p~ùdk)*§j**]òŽû°wÛÌícm½ô©{ÖÞíôÛ>ji,ôŒÛºíõ9Iã #ò”{·YCxª5ØãyЮw;Ö"S*š%PG¾Qv­§(Udù 0Ã$³h’b“Àä˜ã†» NÄ6½™ÖP^•îrñûŸçlP°Ò‡DmÐûYþ·‘ÁòßçìH|r‘Ø ˜h#ßè;îwá%¹ô?¬oG©ýŽkw+>Ÿç1ÿþys¼õÌØuÀ£ †:Eÿ‚ˆbº÷•î"Šé²yq¾èñ °ë)îþ¹žWFõ©¬@ÿã«Û™IŒ€FíÑ×û/‡£eèæ¯{¥úZù…JI½}ùj†øƒ7Ÿ\j ·Äÿkæ²" ¨Õ:ø×ð?áorÖå^óƒ&nØ"l›s ¸ò%X†—/ Úš˜è^8gËTŠqví˜üJŠøü‡*»–c0WÈbŽaÛ7–Ár+R‡ÜËvØÛÒÚ\áÁªç›ˆi–­³è-÷œÏ!/nŽá_ïfî‹M'îâpu•·Qœx›IbwÍ$v×Hbo¥6rà­K£sè/OåUê¿E[覆hü[ý­€ŠËJEþ€d™yíKâò%~B;²ó©Š©í@MNLˆïtnPŠÎéöW.YMo_LYBvªeÒ„nÄ&× E7ê«Ë5ýë1ëiŽ¢ÚÕUÙaHuzÞ¾œÂî99Ip °ƒ:a{Z½þ2”Ú8ò³X2­ïÎÝä®nTÁÀ¡mp—«ËiU‰DUz®Õo]*sÊCŽU"EÒ—Ñ©Y©‰sC* scI\Gß =‰ipKS½âë5wƒlM°IÊ›•DWá©XDž¹iÀ}©²¯1#9£áôÕÄo¥e\=EŽÌ­úD›Ò%>Á~s•ïb(‡Éƒ«5…>ZB‹§00ië¯t“+ˆkøx#Oi0’¥–ð~wûtÈ&å‰ÑäƒÉbàÇú_8ezÍÚÝsú#˜/1 ‚úÕÇ"0CÈ~?µÞHø<ñΛ™˜F=‘áSt\\=‡.J_ŽAúŤ›rò—üº^†R<ü~Šø÷² ÜG>ÔßèŠ?‰v²îl„ýán‰6¶Wöe O=?äغ.:OÂ?>rXƒ ËêÂ~ÑE?½½®^z8WVL©FKýçPÁÁ.‡¾`orã1P…»œ®ì²ãì2¦¿¸ži—5V;9wå¸Wœ ÁŠ Þ^Ù[ËaŽÆ¬ú+Ì©®˜, 6áq³ßïö‡ \ê¿W…( ã¯yÅî^‚ãÞÀ.Le·]oñ?ºöþߦ,†ðL­×ÒªÁÐM6€JÞBí/Õžiõ)ÑóL/ #ד‰X¦l˜Ð^Nck^dcÊĺИۥÚЗœ¡ÛÝݤ;:ë> Šî)†¯ˆpéûògN³h[xŠ'ÿƒcÑÕÒã ØbÛõzßÜo›Îãû8¾Yø+%-„¨ô ‚ôàªèXØÂ1é¸JÑļ¸Z˜4Ò¢Sª2ºò´¯Xv.&ÅÆHaÜaé>[P;ÁpéL½¸nJ:H—‡?‹¹>-Ú{êLfUÌh¡/ËÛÑXï1H\)\ —(}Jæ'xíˆIKŽÜÙLÓT7&2&JäÉ~cݘèÁÅSùdqÅH¹ÇœP“</§1&ˬыŒø¯ÿí~ªqË~úå×_»§ým¾\kämî¶iedhÐ ‡–±ò¹ÝLÚ0a·:NÙè|¤¶Kzþªxê}ÖZº~XüXãÊ8UCt=ø:È´ßœVCøÀz. Ÿ§ø•.h«ˆq%ŸâWN{Šú;V|OºGSàöëõÙs •É™«ýêáaý0ÍÒïÆ¯´4<Ì/!s늉¬ (Ég°N]ÚÒ˪º däk0¼êðç¢x~šæût/F'­£vwõë k°YIAEJþÛ‡õ$áo+ÌZ§óîBïZ¬›ÜÍåLÙoæŒ.ƶ Él{çI<š o_JVL×™/ˆÓ³ÓÐ7ø"©lXú^Y|)søŠåþX—Iº6ïWØåf½ŸÁÑìL`œ£ys¼þØ5¨ -uAâŸRþfk¸ ƒñ”àÏQ˜M ÃÉEÉ“þÓëýЧ+.;1ød3ÑêÒKkH­°âiËèKµFHÍ‘Å0^ƒU$øÃÃÓkcj]\À~×ë´Ù‚¾d1'jðý‹Pa¢û9Äž„FŽ6úΫuL! ÆEò zË}"ÅägŒéô\ßn×Û^¸NLZ¶ð2}&Uªsõ~žÚlSJF£©E€É¹SÊø…%Ñ› ¬xoáØr¶Œnæ·šê¿5r§«ƒfb’Þ]{Ηœ­Nà³cßîgêìb®ñ ‹2„XÓx€£†e8Õhg´ùà@UÄzëðp„ý]íY[¬@×¹HÑÿ´½]ï«Íöø…³ÃXcŽí‰~ûb-òNÎÊlÏEI­È¥}ÀÆ^iád¨\ÙgÎ)Ž˜¸~>hÝS|·Ù¯o_/qF}B®MæÃæ9ø<í[}¦½¸ß¨<˜÷AýõxÌ`ÈDß֓¬ç *ˆl›9o}¶cÖmH¶\°fq_á’¢¸òñaµåñ%t „fµß=ñnÆ2©Ý©kÛÊÑ6Æ–mÀ ôÇõŠg4xðxU¤¸Ó‹ŠÏp.ˆ%y¢Þ D€Å8ûß”£z±ëR[žŒ`›ÒUéòèÏ;^HcÀ˜ŸÄŽ÷«#/P ;ÿž(8Ÿ u M±æ°{dq¦,ZŒé¼øµOØë‚€>|Ù¢Q~Üã}Â9^ÚÈdÅŸã=3ÎiUYÐJ¬âKñ`·`¼OòØ«‡'žã½,"Å&[‚®“¤—^)¾ÝôÒ_ŌЃqø;²»ÿH?Å•uʪ‹}Žj€³U>n¯Xg L?óÄgNK˜kª)¬ûˆ±ÂîîïçûÍí=/ðôD~»:0•CždÌŠÅ—`¥ó[nYFöDÄ›%zÇ3]ceg±?±’ VPä²Þ6»-/ð ×_ ŽÒ†åëhwH °·ëõÝúNò”$ØÆÚÌyÃs‘A7*RZx²“ÊRl¹Ý±ô Ú“Ê8‚%ŸX,IØ‹¢{½g™a8à)éô*¥¾ˆ°jT«EY‚ÃVJ)9agN°@Kç…λ€¢Á¢7G±år‰²Rà–ÃÁ9Ä 2Á1%voàÒ=p1'+° µ ´ÈeEBØíÆQØŸXϨp~ŒS†$r- »¢s×Er6_¢—6‘ÒrÇ ''ƒkn¨è%ä¼âݤZ*g(꟎›¬NQðÚ't1IWq&yiRá(ÒϺ’•#tšÕý„˜­+[9Bª»w…õ¬,! ‘‚s®Ýà%—Z©ÐûÉo/ï*Ѿ¥„™ìV˜pl5)÷‡Õ#Ïí´Z(Î, 01J¤Hág*̲Ð?“RÐ œ© )Þüõç%Ô¥ÂY«öfª6¡. ŒÀæá«j7V  ïñé8Žò²ð¢~È“.…‚#eIÞW¹#æàÈgç(î¼›Óî¬Éž„å>${*ó’ÕÈÑ–Ç©ÿQÙ—’åÉUæûôŽPάÃÚcGÁÞ4ÂDbÎã^”)6ÐÛ¹fkNb‡Ž…´‘ÜÙ®÷¼Œü‚oHÎ0kk†£0Š^߉§mY³¾ã4§-#ìhŒœ>såW²,l ŠùÕ°‹==öœóÔ*ØÅž GŠ¯ÆØsl)ç=Å™Ãî‘W(Œ³…1Á#O|£"“©Æ²CÛûHe.¸ <8@ŽÜZ¦vÃ.8šÜ\VR}٥ɑlá&ÕW _‡]¸ëŠÃ¤5(ðN­ç\Ù/ÇÃU_Y¸O'ïŸXB³Ü“W9¾îe =ÙÿÇÓŠ[9a=¹ûõÝ+î°çHÚò†Í€—è)ÆÌ«Uí˜=&ò?T¬:Êì‰$kXM ±jÂÃmH°ævÇNyôÞS”â½liS¤°[…¥³1 +T ‡œD ÷š¨ÊR†¥1!e¾÷1·´´SKJ ‚ø'÷ xmC¡)ÆääQLKÿ´.öÐÅüJÊÆ€'5¹£Å¥Ã h˜H¡óú–šÅ^„)VK¥I÷X»CÐÏ1:y ¾uiL¯· Žm€ v}iÆ(ÆÉˆ¤`&¼ÙòÉ„¯“æ9q4b‰Õ;§/ðÆZô㋘ñlÆÉüä÷¬¥!Yó‰÷c¤ÕžbÊ,[[4¯%ËB’ù¹Ý–°‡…Õ1ÿ°<—/`:ìŽV‹lCyN#W%U E|%î¯x÷GE9R­ý Ѫe%b†ð•-x÷…÷|ídˆ$‹ ^ß“BŸÚÛ‰¢ÇÉOÀ7z ºûÕ·Ó&ØÅF‡.û«¶÷Ö ¹1•d#%ôÜ’ ll«y^7Ü÷)£^–ö²ôc5ž0Ë™¥½¢í2•:¸IûÈâÞÁ™~ È¬qÁ¾¦ÖŠ)’3²Ôí¨‡ûÉ÷r,ÿý~½_søâáJõQQøÛIõÁ½A¨]`_ƒ³z tÑÎ@­˜'|j”ÞT+ _8 þäGÎå Í-Í—ÎpLU¸“œ§üKé©ìïE`¯·¯xÃaSðÉseâ#f-:” !/‡ÃÓã´bÔùÎI¸•2_s¥½¥3e}pŒ|Peǃ«²>wJ(*\LBï‚ ÖœÜË yÐ.t¶µ5'·`M.³6IoÏP3I¾j qÁÍ 3Cˆ+ÓÝðôZ ÂÙÁÎbâx·^gS*ßb±¾­-Û¢ý }!(Òù}!p£ ÎHWCÌìïRÚ gøçi aÊ$1b^LQÛòé½ .f'¶†!Ò÷ ÊÇûÌ‚Âəζyð¾˜ú Ljp‚%E=»¢¼(CsyðF©7«žÜJŸÚ¼¹^é=¾Ù!ÎN äÉ*õÎ8Á lŽ‚?•a‹¹#1Ïj'öÜ YUØ¢3팾tv=-¾Dv5€-Ïn v=-O>Ohêñkyl^ÛÝÓôµOàØ5b)Ìj«jìÚ¼}£Æ®‘û\]ã&ÉÃIÆ8Raz ipîÚ{‚CŨÙâ]LYpÑQàõà5–ÓË)]{˜ ¶¨" ’|nÑw©"t½ã¥Ïv[ÀºµE‡-#¯ ¾š{ ~.½©ÜJ4¼f=)‘üR4¬ˆÎ’GŠ91Ú  M²‡[‹†­qjϯE;•}+Š;ÜZ´ZŸEì`Õ•Ék Ãá4yM÷>"Å8­œÌÓä5b CÅ8c¼œ¼FÀ¿o5v3'¯¬™3y­É™jòA:3+³œ¼F@·&¯q\àjòZõ™çš¼F¬b‘ÉköB“ׯ,3yÚÜ'¯îA ѩ瘽ÖÃ~®ÙkÄw–¾V?ÓôµH¿Ôø5~‰ùkgÀF½Ì6|‰lO–›ÁFÉú"CØð§°üYd %3KÌa£N)¯a=ˆàÊ"“ØÊÅö꥾šðá\ûçÆfjìgÆv!ý9¦±YŠ/ËNc#V°Ì4¶.ø¢Óب­]b½È46‚)KMc»*’ÜiløÓØTü™¦±Ô“µ&bòÈ4jsß}áÕþ–#Óòs#Óf=ËPj™gdô¡·»wN‰ÏifZ›™6³:ŽÙ àO›*•¿&ù"f M£»š¦àE¸äd›×ûià‹~ÿÅSí#ß¼®}¨ðE¶öan¾y]û@ÏJïkì©¡ˆ|탥ø2-Ñ/O8Õ>´ØðêNµט>¿hãTû@pk8l9Õ>„O| é‘^Õ>PòRÕ>pJ7ªÚ‚9¬JŸ²ö᪬sXSÕ>ðÌ:Ÿªöàʬڇ¦ÌTµ-ÚÇ×> ²¦ª} Xsª}`ÈÌy(f“;ÏUû`0¨el4í‡j¶’Sý`6Ôë®ìýæá¸Þÿ²¾û0©l§lë°KKí]©}¸jcv¡ÄGë´;§y±kÀ\G’þ’S±sÞè2ZYzzz£iîCšmù&¬êïŠáý˜pÒ­³åœ–Ö¢.η›lŧdåEý[€ ÿö¸“íæñ§vèB]þÕÃÍòŒâ¹õVê"’ä]{Rk Sœ Fj“ ºh¢_9CW°Eí¥6$åòîÚà'£†-X¸l àa¤¢…n˜5®Ðå^Jè^NáM¯gE}’ànýRò¯Þvû™D=1ø‘fÔ6À©÷‘Ê›½®#á…IØõˆZµHE_ê{îfËjü¿Óœa¶X¾ˆ%6‡ ¡_4 ‡+'¶ÙHîìöÃá¸g±g©ú@èûÓÎÒ™¶#¸cMÙóòBËÑß=fpç2òÌc²)÷×r¶ú¡GzÀ¤-üj‹ìŒÁ|9}–÷®>8_zØÓ ç:fµ|F~èæ O~gÃÉþÈë„§C¾ËÚX­)ΊÍ¾÷ý¼ÚõÙï <Š`(ôëýãæx¼ÖørXï›PHƒøôþ>o?L¿ö†Á¹Ä`òkØ8—¢)cF¶ .v?‹1É•cÛÆ3ÄF\°(5ݦ{T¯œ†ŽRÓ–bxÁá‰-¬ŒJµyr¡û‡'åXt„= -Žà ¶·ž’““q3›)˜Ùê4%(’ħîéåØŽº ÇÖÀ.× ï®8¶Ó®õŽ_ T±ñ­ÖÂäf{¿{Ü}Xo×›ã—)÷áÚž>3Å•¢ E×µm®À5o¯ë®m_j;¤×®m_/$³ç­ÖV&]µú¾æÚ¶÷ƒs½:Ùs§/çƒ ³¢7pÍ·W5ìÛ¾íù·Ú¾­˜ãÛR½Ï¶—Nù¶3D ¢¦Ð×,¾âT2c)Æù¶ƒ1 p­´5é'ß–Á§`‡)r“NRÏë¬O’ÒðϽö\=¼ýysw¼çÊ&à„ÚóG¦4°±‚lAUÜÌÇõq¿>pBÖè“É“_ÓÂYGhæÁ¹®¸ÎøcÄo¶·g@ÿ$OnîÝz{dñ&©“ÖÉÃ_Ÿ‹=ÂÃRp=¡M1‡Ã‡½U®í*ƒ/û:ý2ŒÃ¬.¿|Cô8wb<‡ù¼æpç¬Ö TýÚ¡õtþÓÃjÏa 1šúS:ÃŒ9‚VÃ_ƌ &Pè`>±N‘¤sbÌ{ìeÁ ½`Ü ‹¿©ý¥kûÇÄÔÀ%DÓçÎ9Ûõ"AŸÔÆg ºè‹]ªo<[Ð…XÃ2A—øÂA‚1‹]Zt/t!¾HХœ…ƒ.-ººr²LÐ…”E‚.-Ÿ;èâ±}y¿mã³].ßj]M3v{NÐÅ•“YªÏ,t9=”µVpñkN¼G4 ú×ãq͇r(†¼déúZ€Úùa8Kaö.çB9 üêê˼}îŰ)–é5—5"–S€EiDý[Ï—§tK Ècæ)DujTwF_0OÝ}GRÎÎS(ó²-ÏÏSP…LJ‘B·Hž‚wð§Ó-ËA§ë4¢¦Ð×ÇûÝËŸÂAþL~¯ÓÌáڀΠì€dHú¯ûkƒa õß½Ã9,§ û1`Mqž9͆Q£ƒ™¹F<dÈÑ\j¤’xƬ4†ÜéïÞóâ < ò¬–ˆ+xðuê O˜}7õt°A\ª¿Ó+Þ9W¬Ó€­÷œ¢V2ÍÇê «1e|:pBÖ-uÑR¼¹:Çq_0ZªI¾0/, Ú“ò³:®÷›Õ+h‡Õ£…§Øsud˘¦‘Q›gb5Ë"rB(1j·>°¸ƒÍ=)<;¦æë@ÛgbÎY÷àÀ;Ók”þ‡ýêÖÎq¨?ã÷¢:k|^O ݉¬jóe+±ŒU§WúätA°¯ ÝCC >¦) ë¥A+.¿V,æ¼ÍÚ—Óâ;ØßþZvÿ<üžc…0&, OߘVŽ1§óZ}«&þ¸{Xí7‡í/ÛÝþ‘Ÿ›×ZÒ²¹y­~^¯·KÇž‡GgU‰JÇ…LÚÓB9ØB¨¶þ\ïýîv÷ø\<^nö(I†ZÊ‘•ÛfÐq‰l13üÙIœ÷]P„¿®Dö[ RJîpiEþóì=ˆÙ Á¾L¼$6˜>7§ašóX4¨(\QŽÐ$ЙiK_”¥8³DZçùc{ï³-ÿ%':I‘”ŽÎ ªmWQæ!ðíè윇:,ïDóòŒ/˜é¶FÈ糤"¶îÔ¿t<ÒùÎ… …í}FÔækþ\Žï…“›­¥–12&@õ¿R¦¬þ!ÀÛ¯˜q(gk4I]‡—ÓþÊbÊ-ɘ+ïøxL™ë3ŸÃCÐFlmJeWë~DO?‡å"ô~çÐÁ5e´ÇØÌsk°'¸]ð¥4–JZEñ…«Ð”tn[¦'/ꀳŸò\i…°¾°ž+0¦€CvU$5“!9AðQ-àôì¼à9Û[fߨ"‰q{0µ©SR‰âÍj¿zxX?°b•NÀ¶1…î­ Ù?áê2>I—ùF療÷– ;¤Ì7–xKÐQú bÜ· .g‘(ö,SäR> ÂõR}dá×{Wœ3A-á¤-8Û‹&3N(!¶·~Kc¨iŒVcÇùkBúšu‡Õ'-‚‡ëMôZãÌh¾j,ʨiÀ‹ÎüÔGÖ{»ã°UD¿Ú²LA:¸¤$8f0›€k|^¡E;ƒ)ÿl’~­ƒý쌿~ÝZQ¶÷&Åkùrz WÔŽ,ô@nqè^ÑËùCÎðꎌÃѦþÀÂíp<Ž õ\Þàô·@ò†ùnZ¾à$G1f‘v8Ú˘ µ€Ü¨t1­…X3|zøbvÕTÓIõ…t`jÍÛÛA{”¨§åþÐr°§ RQÖó]ÐE›ñkŽçÊÖ)ä¶^™gÅr>f üzÛÈ5¯¯ZÞ§¶Ð»y#=¶h]¦h<2p˜"ã¯%c@Mz§)mp»Ûb¥øë%²(0cFY×ú|`…4ÀvvxvÐÅü˜L+¤‘@[šv~Ä õ16#&>>¬üËBzkjt²Šr¼—w`B9ÇŠXÆ o_JNèü,E>uWµMt_zY%UÞÇnS6÷Á©ÎûèCÌÏûh6r«ò>ˆ5L‹¿Qy-ðNÞÇØ•÷Ñ%\ÌOq¸0¥jSÖžš) ®·)#^pxR·)ëÒ-æ·)»<¢UmÊZØ#Û” ò¤jSFÈIë…KÌmSFèÉiäS§8´9ôLÌMqÀ¾‘¦¶Óž9Åáò­\ŠÃ?·¿vOûÛõBehÕמ#Ñ¡µgHthá/];ƒèŒM‹×Îé&ÕèÏP;§GŸ[;¥O–b /ð ×V­„3»Ö‚ØX ºYÍ1ݰÒV‘"Ã-žíHÆp‹gœÂü [<ƒÅ…^SŒaWÏ`ü7‘Äsý9eËáúá#ÏÓ`ˆSŒ©Êr81At‡è}¥ËrÄd=©ÁXNݬ,ž7jÒÉ`ÀÊ€ŸcŽœ^28VÖ˜›<~/ä8m_*¤ÆF{7;€`‚<á¯eMÒ ñô ˜ÿ 7”•»ÖÔZºR¦0ÍñüÎrUB*»häÁVïv{ìCñ…W-ceˆŠ`Î_Yñ/Õi)áYýÊëÝvV\X&3"›ezXœ!cjð~Ù.öfÚ²ðeAÿKYbÿ^k3Øbæ´ˆ–ÂQ.+A>ñÉ»mj—¯qK¾úé»9AlÙãŠÐƒ¯TåíêÈÓ•6•#—ê?àAå<€¼Šd«Ü¬ òf°+ÎüyÇã fϪR^®ûfC|q ]¼·4|C͈9I<Åéà /fψÌ\ç´Læ í¼ë›z(R ÙOçµÆ)`z/Û£50¾kTà£M©INØåO…Þg–y1ÄVKÆQkྂIH•AÞÈ^PgEjà‹ÑòÜ[ly[ÍwÉmîýî¸Û^ñæ1Eµ§>±Þ÷÷\ ŒþÓ`£IùÙ¿µ†Œ?;És¨²¿b½ÕºßT/Iäðe‹ý‡û39H—/'ÄWðyéaÃt´•Æéú=%·ç[NÓŸ ú‡bD3‘þ¿bu7®b-_¦y]¾A`+è öš&ÿÆ¡_ÒÅóŸþ/†Š=Eöè|zÊäñ\KÁ·ËIÄôä±´7ÑÛé‚ë=kXûY3€wèœ]Zæ3e)ÏœQhpˆ©©Á»Bÿ‰Å°ÁË•'|õðÄJ{¥(ø“¡3oîJY‰îb›+ãó9®·e\bQ¼ç‡ò8Gmöh¿¥Á3qæÙùx']r¿an(°Uîüå~âǬÞŠˆ»ál{iKͯp×F ¼å°ha/¬¥™ô°z½Äã¬ôý^Ç ë¨c©[ Á?±cø†áv³g½WƒÖ â´nÌièBWÛ°û­:ðK¬ªñÅ¿ä+¡¾@ÛÞSëè½ìNS ÊŸ¡^ÉþçûÍí=× ÌáŸólxF r†Â>lZ©ŽsÞC¢’…Òˆ¡Úµ‰n³CDS ¸þ%Ft‹UQQà‹¹ÍÞŸü ü)¸]1;3ë²9±ˆw‹Ô­àné…T×G¬ôØâÐ>VWfœgUdá61hñ8E­`P>‡'‡ÂáEc? ¸ß==ð’76´ˆoÞ±Xƒ-Ý|LíÇÕßy³Ñ±øšƒ´ ”Ž¥fuàf®iE2…Ÿº†¯¯YìŸ~fÅe òOøz¸êö'} [p-Usù«<ç–õQ(15ÙPÁ8# z='ü›IÒ8¨Ë A¼,ÎÇBž33Úi7"ù©«Õ´ Žä_êj&wÍ=TØh©Õ-ÒU[§ö­~¦®Úú¢]µ«o<[Wmb ËtÕn/ÜU»Å˜…»jLY¦«v |á®Ú„´,ÒU› {‘®ÚWÎíªÝbÊÂ]µ ÂéªMœžEºj‚Âã‰sUGŠ'ÿ~¿Þ³Ô®upò),Ûo•>8Š1ŸXŒñ¡Lˆ#Ÿš#‘gÜuM>|fk’lù°á Ó2%OQþ‰Å”„s=…=qžS¿±2ó6Ql9Þóf“*,_"wtu8<=òz78 ^kÈI¤˜+í l'CLb¦´ΟŚ=§G.bí˜8a{Ø‚1¸»Ñ¨Àˆ¾³¯¹¶ð7V·o Ó(Rÿ¶GÚÎêö}j) #à‡Ô­ò¿ÚR`r™ÿÙ‚ ~pØ?áŒÏ­[ TßC-ÆwÐ×z ´–FöÓÚœz ´ ]C€{ \ÂT÷ H¹D?I%Cu×çËôWac@m¨¸hv[øŽÓkÃÐ×pà4jׂú‘`°Ø>>´™Ö~íïü7V€ÁaMœ¯Á»mľc¹àø°Qîf–)¼z¬¼ ¤ ð:[`‡bãÚ<¹x ¿ãõ  ¡Ã( ŸÑÔBÁñÑmðÎfÎvºÃiÐCµ™bŠ„2®­ÒRË3åò*-P_=KÀx E¤X²åµùðÒ's]ÀçÈ-Êòì¸nûóó3Làþ¹hÙ®]üyÈ®µì½¦Ågó¥Œ:Š/^ïœS 5µ¡Ì'|„Ò)Rè›íq½=l޼jþB•SÄ ö¼}±züø°9>ݱڒ㸠Ó=U·À<­öë»óášÕ•Çïâ[b%ÌâÒÚ@rؾhñ¿Öž|Ú<úúa}{Üony Ç`(¹ó'–-D‰˜««Hòo׳·†Õ&°ƒy|^цUpÈŒ§Ã|bÇ€¢¥ç¿°;L¿‰>3eÑû2e‘`ÌØV.ƒª\[IO¬¡û|:59ÏX©Ug.^Ùw¬˜‚  @©¡¹ôÍ,3„JË€iy”ÈXõzXñ_À—LÓuØÑÜ]9­pk-’™§­“Jg·x7"•ஞПéBÄg:…oŒÄ–¸Q÷¸”¨•ð.D Î1vç$Àµ|Êâ›D¡ã…ÈkûfP+çùRÞ´Î`ŒN“´âUgXéáÿ¥øRÞ´ÌææA;Š5^6N¾Ñî™D ¨}¢øíÍ=Püóœ¦:ËçyXsV˜p*ŸžaB†+ëé OÈÀ ê(êÙ2°5¦¡Ðù­ä0ÅßLò¬a*a­±•E{ÃBã7{r}Í1¢zÞ!‚èk`Q8o{‡Ž’1Çsv¦yªÄ”r¤áYJzK2†™Ým01š\ÿÌz„qIø†”ç û­Á”µ”|¦ŸÍ˜À¤6c–{„Û#ÑCvë?0ßïðzê}@0Zþžc¡“4µ±¹ÁÝ“ew¹¹­øÍŒI’˜ØÙd΢¯ Ø;,Dê¸þ•W’ÚÀ™ÿus¬kÕ¤2{ÔIAP?qÜ@.)s5ôî=;kð® ¡/˜ãfûx €qCv×8›[v¬±–ÚÜÝ–Õ'È9ä?y¾˜-Ò±>fTèŸX¹ÁÉÐCÓk3®ET€;%Ø›yï Ù¤yc‹rŽD ú·­WÖQ&{¦`ÑË›`Û/Šqؤ‚sO:_$àß±ê÷14U‘â‹â™v_)Šrf_ƒ³¼btMõ2ßóÞ±1u?¤3ú²íÖ0½£°éKõ[+ ¨jÕûÊ̶bíb¬¡Å;¬‰ý›žèóö» ­óÏcÞ°—>ÑØÖQà÷+^„—¡ðW˜ÝÂñ¹2R„3‡z¦2]‡ÀæñŒ]ý<IJ&£Iª™ýÓшN4ÙəڔÕ`_ ÉKZŶ–¢ü;–㈱çÎŒT[_HÕaK'x7»í.˜†.ÒâœN‡vai½ÂšN‡EÓAGJ\ÞåGmNÊìJ–TŠ·÷»o–'†Â ‚õbN~QË,Çü¢(â6¼Ê‡ânIÕÈk¿x¾E­/Ÿ(—å‰U Ø;¡‹¾ØÃ$¨ÒŽÊã3&#h_•à‚Ý^3û2‰¥Kä޹¹-bZì×zKmp5Ursä鵨áT7«€§Öø?$úçÍÃ/aÕ–od|ÏÐÇÙÙ,͆!Zåhò¯§¼ˆz þ¾ájìcAÿ/¼/ØáÁQØÎìyyP pœ¡Xóö…J)¼})ÿÆkG‚åI,âÍ=sж Œæ.|ü°yÏŠ_Ø$‹˜(â߯÷^!FwIÞ¼Û5Ä|¥à°ŽÆ÷ŠêfЈˌpØ‹åÁ”# ô“Í븤¥VgòsEüàt‚aÏß”Oã>êzg&GFŠ3ë™y€6‘ìaö,©TšœÝ~³ÞÙiëƒe1ºz> >> endobj 86 0 obj << /Type /Font /Subtype /Type1 /BaseFont /RDODNJ+CMMI10 /FontDescriptor 172 0 R /Widths 174 0 R /FirstChar 33 /LastChar 33 /Encoding 175 0 R >> endobj 87 0 obj 66 endobj 88 0 obj << /Length 87 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»år¹ä RGù endstream endobj 89 0 obj << /Type /Page /Parent 59 0 R /Resources 90 0 R /Contents 88 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 90 0 obj << /ProcSet [ /PDF ] /XObject << /Fm11 91 0 R >> >> endobj 91 0 obj << /Length 92 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 93 0 R /Filter /FlateDecode >> stream xÚµ}m—ܶ‘îwüŠÞýpÏ8GBˆWú¦ØÖ®Žíd#ëîæÜUŽNk†£éõL÷¤»%Yùõ[E6Ù‰B“Ý$ÎŒdÖ P¨7€¬þºúÇêOoWž{«Vü·ûM;®”_ÕÞòÊÊÕÛ‡Õ_ ^­ÄêííêêzsûÝêíÿ¬~|»ª¸òŽ}Ñ’‹•ñ\ëz ½~À¿çÂ;_›ÕÃJrøíü÷«_¡zËÆ=°’keÃ\m>öÍ&º\c—kð›Íu†BjýWñ(%¯X7JÍ-ÏQ[Í+÷ðõ/ÿöýëWHÄÒDª\¹:"úáÍËWoS x¢”åFÅ4ÿùã›__ÿ%Ó;UKn*±ãϹïäbÔ1Áuf(F*øi)ùáõ«WoúY 0±Â˼|Tb†„k Ë"êò¯ß¿ÌŒ’ub $à¥füÔç7Ím³o¶×Í‹ †×\¶œ:c\ýåøe³ÝeØ+€YÎøžˆ!Ñ—Ão›g9]sç}ÔÐÿ $rÂKOVqÏþO®ë¹uŽ…ßÿãØçh`øÂÇm<ûŽe¾u \ôýe„úÏ}e£ï³«P(ø®Žûî Z­ß}—¥ÓšÁœ]ýGŽÒh®¥‰º¸»n‡Íöcfv¤‡õdcÎínsKt…×ñôüíy†`n˜WF‚}vú12ú~ý5#ú ñ´B…Ülrc¨5‡îû€‚]Ýæ˜ë—Öº¸O×ÇÍn›ü >Ö£~­ëÌP„ôÜ¡öH®w÷÷MÎ`£¸­†ÎµÂvln²KÌñzÄâMv(5¬—:&Ø®7÷÷k`Bná°FG„ÛœK ÂDcyØÝ4—ì¥2Q9}$ ;ÿKs¼ÛÝ23#ã×I@õãöŸ_gI¾q õi0÷9| ›/YÛŒVs h܈ølGže˜£ÎÛôJUõ;%+%#‡Ãr_ëv†»ß†AÂ/Rwúàí]“¢8ýf+îe=P´lylö›c,µc:2Xɨ¡ýzû± tɘDT–[”€fs Û`w…ŠûLðÇWõÀÂÿÎtOÐÝÆ³ˆ„åDú¯9R)€ý6äH8q"K a­â»Á[äYR`ÌuDznµ $mBª*^œ޶š´)©_“l51Vv&µÜÕd«<7¯Êq O<Ö ›´äÒæõ,Ï’‚W&5¯¹É‘0Ö*–Ü?¾Òüþ7¸Ûýöý~}³A¼ý{¤T´5§Å¿ K´’ +®]pïGr¡@нîÉ;Î÷»M "à Õ-Qû‹‡ ì™$ø»« 9üž„–×ZÇ”f ¼ßl›íÐ(SèhO·ú]†ß'1ë%¯…éhí@;f×ö}7~Z/ m¹Ò~,˜Ê ¤uƤÝs# Æjh/Š`F0Ä7“øeÚ6XÀ û .È>§ lÝÊGH‘åL]µÚ.ü~OšÀ8lö‰¤•`ÏjF$X»ä|—±¤§Dƒ·¶]”º~h2~Nm¸5ÀÖ€"ëE»šk§ìéûÎe»Ëy9¢RÎ ¿>69Ÿ ƒ;Xs»$”áueXðý í92p¦mÔ¯O‡æ†gƒ/ÇQ\ί9Ï V5ºÁ÷›C6öçVÚðûÃq¿Û~¼ÿšé†O^Èjß\ïšíÍÔ—fSQ¿ÐU‡q¼[s>ð¹Ö·D$Ù1ø[ 2’DÚwLê×ôµ‚›Œ‹ îèûÏYqS úäô}+ÀMVLpV\5pØeøŠ.ˆäÆbj ڌH²‘“áJȨ&𠮀Œ¹4¶ÆâR¯TD3g]IÙö-L^îÄÁÚE ]ß7ë}^î1_8¢:<6×›wJY\Ç´'×K¾Jåæ;þ,¤ÄcP.à{©¨‘χ¿®Á¥q§Ö÷ŸræÈC¯0ä I>Ž9ÓÒ/!>‘°ÓrÌÇÆÇÝÚ…ž K9çZÄÔwʯöÖFÌ=f§£õN•Œš¸ÝÝßïr¶ÞÔ@3ëËfûñÅÄ)c'‡Üž iq'—LTƒþýù>ÊíÄ]O«àO§TÓ¶ù„Êœ"šöù6ûÊ®šûæzªêBû뇇ufzz÷< iÝóéž³ îùÊ€[¤»È›pÎYÆ9¨·<ö FLm]s¶—uÍW#×\ÙÏ|ÕyænÜ&›í˜Ãe]_öËÛ±³l4'€o^zø,µ`´«cÚ¼[΄à…û?ÝX˜å–3LòùZ„m·nyfy[¢rŽ]eÕEQŽ[H¹å, ©!úŽ).{å‚{ãÅÿï.æÓV~)ÙÔàL<­%]÷ÝêX?í›hE\'7XÄ(ç8³ÖªdDpÁ™—àG€ö8S°³OÀ³‰[ÕæÀ¦ޞ\GÊgqš«:æAÎ`¸—"af¢á|}Ü\¯ïï¿fý }3Ñô¬³y[0.nç¦9\ï7½kD I‚Keåü ’tdíLP/i`xÌiào#K•ØS¨0Õx¦˘ño€0tð}Ž]ÜA'tÿ=»ä¡ƒ[#Ũ?` ·˜’Y¨6Ûœ´À¬·ÒüºÉ ?hQgEÄÜÖwù S€ýˆ™µÝÏë…åÇ)ÓÙ&í_?<Þ7‡½V{[Gtï”Ô¹ä4¨y jíLù9ßú)C +N£íˆÙ)s<èÄw9R&I®&ížLë:ëÅÊvK#¢ T±’æYÎ’‚M×*_fÒ9 =«Ñ ¹”KáJÅ•Q{?eÓÛ +(ÊÃ÷l6W…yu[•éÌpB‘Ž/¶ÎæÄAÌ]ÌJqÁsà“-$3ŠÊ˜É\³p®3ä´:9×ÔÖ xÕ:9×S†@4ZîOÏÎfDXrO&bb®Ëg*'ò°Ú”ô«Ë "/a‘¡ò‹ŒzL~))—h" L¶ÚÄÚ$`ü—»Í±yþ¡Y?ä@ sçb¸Ûsv/ „Gö›ì^¬4˜€ªMê³’Í‹39H_ÖŸO¶ðýæ&³‰Qq?Z2VS*nAWE”A¤ïhÇs+Q­†²kk°Ùö7¦±žÇFƒýÃe7GC0ÚõìM²ìþ´×1Iº¦©n¡F$ ÙìbÛ‹,"9d³‹Xç¢6Ö9§Ü ¡løýãn³=6ûÌH0"":îȘ}u°‘ýçl”"˜F®g¡ä››LF±Ÿ5ø‰:y$9omeÀvÀ×3éÈއP+…LØR_@G-Q§>ê\0hr߃(eÉQ½yùÃë—o_ÿåÏä²ÔžÒs[ºl ×Â2¢åÿzùŸ?þüãŸÿíí¿_¨÷²NFŒ½^³e+œÌZEÌý¸Ûgsµ–(å$WšÑka ?eåg$©Fz”M´°òh\ìjÙ2ëµpH¾å¿CDõþðõáÃî>“tê²U'J¶4]µÙê`¶ _Ñ{‡DÌ¡:u9ar!ãz€JײŽaçæ­`×zÔ¥Ky+ŒOÁr÷4CÞÊWUœ·jÿ‚Î[aQ,Ë íKy+/Ûäú™âBÞ 66náBÞ Ë9e­"’K‰+)—’QüŸ‘·RXu'Ýœ¼•Å},ÕSt{¤ÿ÷?rõ[÷nEDñ2—M€ØÍ{ÏÂï¿Ïejà'";5²¾uOB¢Û]ÖÀB\£d<î ™4,.VuÄÛK™ôû¥ˆyõ%·‘މÊ+ø~-F†é1os™‰Õ÷£¹ë35c (¹€»h>jp’æsWZp“¼Š¸KîwÉ9ׯFa+­²{žñÇúb ‡¶‹«Æ©ÐtÝáJa9zU/(;†™µû¶1o÷1¢˜³ûÌÛ} )æî>†4³vñ°ŠÓÓíÇŸžÿŒñ»ñ1,cÈëœkþŸH'Âã®%¨NÈ¡ ô_Â.zAÊî7¬ömj¬_Í„Žýo­ÃΞ"–ü\@  íjwAñæ!&·4ê΀"N÷ŽÐ¦Ýæ9?MöŽÃ&‹ç ¢úTo¸Nîà*,ÁUÔ,Ë`–§ý,WÝ>ÛŒYfÁ,ÇtËf™© +Ô&{aòò,²8îKÏò¹‹ÉY‚±~–ŠY³Ü}ßj¤™³´Î2ËìÓcr¥21Í¿D‹9‰qšfé€ÏF]šf6ZÌ1]0Íÿš™+ð´ H¶˜6pk´Éò«³K[ƒ\m%æ-˜g n£PÑ÷—æMAªÃÑŒW'=o˜•òÓdz¿<Ÿ¥ÕðxælW6Ê`:dijҼö"$½úr×D»À# °ÒD…ùç ê71Åͦa’òâtn0”Æ+H¶»=N{þ"³ÞÀù©}Ô½õö†žg+@—ŠÃÁ:Vp§û¯XÙp°0œ¿p8uæ Æ°h8ûŒØBÄWËxø „t& =½÷fßv÷Ÿi ž†­£&Â2P² ¨ËÑèùAgæŸÅ‚?XßZŸnêþÁzrl¬Âÿ´¤É[˜~caº`ÈFg“Øähí*였˜Ù85N‰wždêLÞw¬+jOt âeÙã³Ñ¡©7?¾ú9Ù/øÑVcÁ:r~¤ºß5»iX–îo-¹uMᆉÿ²|€È«ÆŠŠ1îIE¶ÙÅEl²ëWÚ1¢¿ûæ¦ÁjÑí&´‹8‚a¼ÅÝšt wëÑl~ÇkÛæ¦°­Ä~hšmC¼ƒ_P Yß%ã—Y\ô n?{ÞlXÄ\TMxÚ•@m"P6“\‡Ê©4(»úýØloŠx+1ùåIa ‚ÊeœÅ$¤€ýVÆX~5„°ß–±^€·d)Æ–­`¬€ Ö×8ž<‡öKPY¯añVÆ”ÌK'?ÁÉ0ìážÎz3KCŽý@Ùž"_0`—pU?,‹p[O3 YÕ`Ä &Ì0i”¦Å BOáF¦g™¦õXžF±¶Üôx0é~ÄÚÄ Ê,è8ý?ÈmÕn-0¿y@³v’`Ä*.]S¸Ø¥î†YEǽÓþöf}¿ûôøîêðî»ó¹îÐ`:QÇè:ˆO¯ï?6Ÿ›÷m;ÉØ…` FŠ6Üö¸¤ŠèõwKø1*¹ZJ®ÒÐXª¯„Qc­FŸyða3°ÆÙ¨3zœ• ê³æ0e²]ì Â…µO çJØ"„„9íù2ÖIë§0/ÓÀ«dÒ݈•ðEX¬D]|ljø9ãf@šˆ+S}Šûï[uÊóZ`hŒ }÷)>Ûdè3s‚»ãvŒÍòaÅ.±¾tÄsZé•ñÿ ®Œªå,Æî!v.`sgÖá]2ÙgvõÃË·/‹ÙÑn@oØÜ>ÓÀlºA¥êš`ô«7/ùq C¦W`U´™Â³D³TÁ0,v—àŸ¥;Oº}3Wr9%t¾dᤊ¶k, °mº›*ºF'ãï©!(é¹tx…[ÎM¯Á,8Ú£ÓŠS<ôX{;vÆÎ)^<Ñ+½˜¦zÛ*q)1«±,/»_Z*Ÿ½å1j@ƒSïŒd=áÌ{S=$æWÛš;¼Á+ݵð*È( p ™W /µÁ+Ø0?4¹ô‡ ’%Ý_ ×(¼Ž‚qOà0˜…w}Öí9 x›CedwñìŸsjhrÜÕ•®Úäà“ͱ 4¬ª¸ö2fí,ý:d¤ácÈôð#éZÂVmÐcón RÙ"éÒxÕ¢ „6¯Ks°]Í'%´xŒ´Hf ú–†”®ýæCSÄ^’PkùT©Àjƒ7þQì}\£§.ë¡„ÉlÐ8·&N‘4QSé]@jý uÛÐ&0§ÆÀ³nì,»ÚíË”c«ul<ìöMkÛëÑ4Å„Ãõz{x–G¦Ì„âyßàð 3˜ ÜÇc÷‡"/[Ëã9Ljoʬ®A¥ ’ûC»[y ÝÐܺ6¤À»dó"*LSж6l;ðYÜgÛ†¥¬Eë—ÏMyõÚØãT €°t™À ô;›Óß3.Æ~µ›àÎLy_€gèD´—e‡ðËrÞ9ƒ×>á}±x+‚Xœò¾È ~B%hS=Ùл4¡4gú íp—?Ö''4›Îy_d‚UE˜4(•ó¾ j!†©)Î~].vçUè` ÷wš¤Aí?NÏœÌà0íÂq£·ÉÛ©ð…ÍðX|¼ºº²ã“B§»fI씼A¹€£ô®(ð®ñ€‘ž}Å«‹g£žkËTP[Š7ÍôB*uÆ.ÆU{É|»§sL\­n‚yR“»‡’ ‹…}9¾åi½‘i÷Ê:jä‡Og©”ql Ç gÙõ1dÝ¥ÆÓÍ¡-oZ.û[yo)Ùÿðµd–Pø…¤„ÿ /} »B“•Æü…Ï2„£~‚ôž”ú_¿4Í‘ÏrÒŠÊzÇ…®Ç’ÿö®)Ñ(õ&cžúú¹¹>Î #Æ*Å@_Wl>Œ"ØÚzZR˜Íú:YÅqaøx»…3iPvuW"¦Xy«T9Ñ&¿ÏôîÇ ÅB¬g¨ÑÏÀdÉÅ/…¦0ƒòâæTÙ•4¥A?‚))R( Pµ%*R(w;dªœ…P×RÒß”$«œ‡x‘œ§g%úÄ×í±dòCs½>ŸX¢PŒÄ C)”ͱ€¥·),©PÈþY™í¹ÄûZÓ˜û¦ƒç‘ÈyÚÍJÈŒ!=^÷I©Ò È.|ã$¯ñ–â´àçSÊyKÂlûÆä®õãK¨|¼ÀÝáÕIЗ{ýk‰Ö¯!\mo¶N¢’uãàð”k •-ÊÑN‰6–b+/Q'•åµÔðÿôµDŸHÑž»!0Ö¿ÍM–5¿À[ob\;)øÁPï=ZAÞþ–Û“?75Úk55žz ¥b½-‰Vÿ w±¤¤n±8÷ÿ/¸Ki«°ÔÕME‹ú·[†·Í¢Þ?Ñ–a‹þAòë¡DøjÙÞ%A`Fž!›mÆ1ßdÒ˜l‘: ­.K@Çn\Á;]|¬²Y ð©wcHCíÍe*^*Ow”-ÚÈ;HŠkA±ô’… …½ýÞÜ”¸xR¯Ñq‡´æP¢R*‰7œÂz½`ᆦZJªfî†U4ž1¦x¼=QÅHFEðõvW‹™:JH*jiUYŠ˜þ/Q½–Æ'üü$æz½-I iÁ=>ÂdÑ«5‹5ØNa{Tö÷lxú <>|Ô‘üißb¹?+Ö4î³Çk_j òx·/±}Á 0#Û×9}¬S|*ÝÏ}Q縂¸€Ý#±DO+Å ÍÓH¡.°}àP`9ã•Í0)dæ^s§(Ù—¿ÌLˆ¶GŠH¾ÎðQ Q§»–`éöpÏÖ|¾¢QÑ•&ùZ”^……µš’×õ±(ÛVu¶*¹ÝmÿÙeÜ,èUëÉ…P’qÃ!­)Uýï!;”çÇÚ|”š<û²Þ—hkåÛ°fQ|ÎÆ– ïxÑdàV<+ɑն­æ˜¢·ûes¼+Ê‘x|À:Ùç%º€Ej[ÒŒ¸´¸(+<ú–${Íãca¦ ã@á&Èly¢0ÔÛxY:!²o‹6H˜¶à[Zý-…à ë-™œ©‹u5Þg(Ìí®¤ÎÀ᳞š£¢í&_µÏÒsÔ¬»mI_˜°‚ý—»¯¦#E/©‡IXÁf™+Üõ´8lh¼0,<#½ ,m“©dG¯wŸîoJ2u5Þ*i9=ÁÁXáÎ[=É~Þ­?Õèîhí •M¢à¦DTÛB³3ê…@xq6Èp‡™À4xt“ÌìÔr¥¸C#Í\´EÚZV\ã¶Nš»oÖ‹²Aƒ¶†å%¬¥P¤­ñŽ6Còt³½ÝíÆÌü¼=> diÉ=)YÍ­•ßXpÀ‡9‚[²ÃJ /±"Ð?”¸Æàbx|K3ÍÛOE{û’yе ¾š¢ü}Õ>0C-Û»QLÂ~A(§krµ l¾¦•b9ŸÊ6d1´íª;P6?ÝH&› ZddGï¯?A$ÛÜ”lŒ€Sã¾P;q‘›•É©Q¤1w%[¬–‹YН…›‚£)ÆŽv0x™,M (©—Ó+x^tÎD±eNŠ4&Û6ŠTvv«eËv1([èñ9 R¤æL?Kî6Ô4èf{]ä pµI­Ò<4ÛcÉÖ`[‰U‘ à°+±ºæÊHö®&Ní=W$n.œò¥ljm¸pä’Šnû`Ë3CµÚå¼+Έ‘íÇûæý~”œ®WÚÄÍåâ6ÓGsÒ)XVfspmà3•'Ìñ*¾)I?˜ Â0O~÷ø<Ö¾dƒ£ŸD4n’‰üÓ.Êl±ZZ„¢,ºèdçøKÓ<–„awMÅ€›9çêSž^¡`)Ô©ŸUN,@TÙUdko 5¯1 @Ùâñ'LŽÆ×6ÕÕ9;±,YNe-SKÎ|€ÞS‡ ª¬¢mß¾nApõ¶¬BÜxé5ü‡¢t1Þ J3`]´»QáŽ9‰Ù”„pBò ­´F bNþ„`ƒ÷úJ1îðŸ—sA•„ˆx z)˜#‹€A ð)d µ):ú!Ú’ ŒHmÌ¿%jŠ»»’º¬¯Å³*æÝîKQµÀËa¾-k5ÞÊ]Kе¥µ>¢âBØõ›ìÊᶬ¯,5ü’”™Á[% Ùn5%¦ýdaÈù?¿aº„§øÈ¸Ö&›žÖ)Ùìì<,ã«öìXª¾l®‹*S0)OT§a‹*SðÐFEöt·½.:ú‹/êõÚÀ÷è”aO›ýCÉá<©ê[ H3 (õ¡§Qä<*c¹µ> Ê®vEu)Ucg“ÓE{¦¸Á©H‰ZßßU¦`6K Ó®ÎÒ(˜@GÎýºD¡àñlO þÇ¢Àƒ@ReR·§ŠÌMI=æ[¼ðßVè©9¾qIýç𥽂Ce„à—9Ÿu>`'rÇg8^*úqß½{Ü<4EåÄøÀͨ¹ ž¸¨P­­Ò‚AŸ–ßÒ²­x @/W)‘.c„¢pãx“-LpZð‰Àß ‡™Œ %®ÃeËν›É†×Î¥»zù^8*‹/¥Ö&Fµs.5ÍXnøÀÔTGñÜKI‚W Ýß>ò'çÍÁt ¼S—}},ÚÝ͈Û;&„±‡æþkIÝ–Rp°ÕáÅr†bkéi2‹7 Rl]æg‡GÚ#ÇÔø÷…GªšÖ8ã2ÿ0Ö*J«ùÃÆàáýX¡ÉÓøòŠ%°Ùè%§pËŽ[à“ÉàÍÜ+’§›äD…\µ…PÛ¦§ ü”CéMµ×é)Zè§„¡ã~ÒÕ᎗¯E.ÓÞàœž¢ÍmQ™ªjïßKBÞ6%ñ›Ám2U§çˆ—æ¤C¾ÑÁ,zõ”^jÊJŒSxýY^<µ+ µ|Êo0ÄŒX­&÷íŠàùaÙrHä›}QÎÝÜÊNºÚsóxAk’wâY}M –îc{®UÄd…µ,íøluÊ JYRÇD{D-=øuÉéå¹WÔ$=®÷Ç :—9¤ÞUômib©öþ ÉJKYVQ) ÖÇâ,qk+´ìŠy‘i7 MÎ’»ýq½=–\aˆQ>꼤F9Õ¸ZÍ%!øŸeY%Ï…u³VýÒû‰ŒÂR¶oS…¯p–< òù|(9º.qq1qâÍ~RsÇ ¯o¼Â­QÌ… »ä†ñ¹Ûk°¬ŠlAÌRÚÓgúnCľŸ<)$æÀ›æýáêl>ƒ‚§ñ=Åã–ú;ì*ñ\ÀÿÜÛªh0Fzð¹$1õBÚZbKO›áJpçTv†[^53KM'óÜs*Õ˱jþ`V¥£^(à•¹Ä+vI¬´—à»ÕùÕ0Η¼Ê€UŸBÚ¾Áñ+ŒŠWOšs\zÞˆì8ú·rGk„•ŒbÔë㥛÷?Ë÷€ñ´Á |9=o0±³åC™4Æ‚¡È§Åâ}FîòPæ%XÈA¤›‘•({BÂGµã•3ca½ßíß/c -;|‰Xø[&wŸ²å£è« 0=ݪg\T:g¿‡lL .œ½<²îÄK·ËæèÔ ÀÊ÷ƒ›wÂæ²Æ¬ ’4jîñ°W{6ëIƒÄG±¤«ÙÅFo6‡ÇûõuÛbÒ`ËÚÅ@Tб…»ÐîŒcL¤/•ÁxÙxŸÊënÑ+ãðÐ=˸o ô ¾ æu:Ðî¡ù¸.ãÞAÁ‚ÖæeZ{‘AeÀ¬.³ÓÝQ@‰ƒ‚*óY5¾l)>ð27^{¬ º€±x÷T¥)Æò²™z‘Å‚gc¾±Èv ãáÿ¶~||’ȦaŸër‘íÞQ™³N´ž(±éþ.‚MIlö‰{´@bÓ|}ªÄVxê[Kl :þãݦìa¶“¼&A…¬¹™•0¤å5Ìž*¯g aÙY^“l˜%Œ–×Ù l¼ Or ”ি‹ü›Ék:îéü§–iX'¹s†æEòŠàÐáM‚²R=€g+ŒàkYŠkn”¥F/¹*RxjÕæ=“°ã…5[ ôk ÍÖR50xÐe,0tÕ~3^×`—òy]cß6á©* ¢rÏÓn½èØb,û©´K45JyÅPsRèìªË ª²~¡Ô“sžŸ¡0Ù<UÝY¢ Œ ÏpŸšýÖÙ<é,·^ÌMŸ+Êæ £5eóŠVáiî5J¸"‰T×`ìõlnzÒTwMN, {ÚLÏë)ƒfdØ.d$VÈIs™C]a£§di¤ÆCÒ3”îìtÛÅlÌ w^Îæzö dƒx´œbfƒAb¦È雚{›ÍE-‡™¡§IReð*â¹,þÿ‘ÎñþqTgu› ËV »uø²Ä‹vNXVânVÙ΋FK3…e‹ÓG!¨§Ð9–îlÙ{òx®·K\€É. BíÛʺh EbÖKB‡Î–'|ˆÝŽ^Ò½g|–¤;:YHㆨl¹0L`ÙB’^ÑW^èôâ‚/]FŠrÿƒ8$ÐÙ¬lJN/t¨ìb:e¶õÂäE±ˆ „-̨õªaú 2j ÿ°¹Â0SÔzaèЧ*h˪}“.dðI&˜OàoŸV"ø;'«ÌU´5$‚?!·}9—À‡!@Ïþ^ÓUUfõ^/Þ'äÏu¿ú50ø®ÂJh| Ða×ðKçkuþÃÊâ㵟+ˆkðÙÀÛ£ö´o!ôšnÂgš|÷oÛ_™ø tÒ£NTžE`éÿú¿XèµÝ endstream endobj 92 0 obj 9311 endobj 93 0 obj << /ProcSet [ /PDF /Text ] /Font << /F4.0 9 0 R /F2.0 10 0 R /F6.0 11 0 R /F12.1 94 0 R /F5.0 12 0 R /F8.0 13 0 R /F8.1 86 0 R /F7.0 14 0 R /F9.0 78 0 R /F9.1 15 0 R /F10.0 16 0 R /F1.0 18 0 R >> >> endobj 94 0 obj << /Type /Font /Subtype /Type1 /BaseFont /BNZDNJ+CMMI8 /FontDescriptor 157 0 R /Widths 158 0 R /FirstChar 33 /LastChar 34 /Encoding 159 0 R >> endobj 95 0 obj 66 endobj 96 0 obj << /Length 95 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»åq¹ä ROú endstream endobj 97 0 obj << /Type /Page /Parent 59 0 R /Resources 98 0 R /Contents 96 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 98 0 obj << /ProcSet [ /PDF ] /XObject << /Fm12 99 0 R >> >> endobj 99 0 obj << /Length 100 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 101 0 R /Filter /FlateDecode >> stream xÚµ]mo#7’þÎ_! À!2¼æ;™oÎÄIæ.3ÉÚÞ½LÀPlyF[š••ÍÌþú«êVK­«›]šÛ;¶%>,«ŠUÅ"ùÏÙßfÿœ}{3K2y3«à¿æ'¥1i’—•׳›§Ù~¯d5S³›‡Ù—ß½úþû«7_Ínþwvy#*iRœý@ªFP³è¥ónßúî ÿ.UŠ)¸ÙÓLKøéð‡ÇÙµø[Žˆ˜¤s¶KÄ—×//Ú~3-„öA£ŽéÖ{º­¤ÛÎtˆR'-ºÝ}7ôýèdÃy-OrßOJªp<œ›¡±À÷ŒqYü=¦‚ï©îœ ˜¨—7¯~~3ÔÊzéU<îåêÕåõÀHœ ² ¤tÜ-Úk‘øsQª·²2Q©#©˜¤Btz÷ÈGDñòéÝÀ]@zÃÑÌÊûåÝ•µà¶b’WÅxJd´Ò æ˜È“öF$…º9|3U8®Yç—à@L“è·®f/*Yáÿ,¶…‘ 0øaýƒS2hxHÒÛаdP4l¿ü8úð¸h58½¦J¢¼›P]Ž)˜^F‹‚•ÇüÝèjVäHMZZ p켇)J†Ÿ¢¬l 1ŸÖ›¯Ät¦*UI—tUtQY¥”“Á’µàL”RI*MNÔÇíbõ¼üWZŒ’ ÆÅf$¶K®˜Ê›d¬¥|%Û ¢E±ö÷/¯$‹»°J8´úyØ×’£*95 zý×b±ýz,Êy ¨‚!MÌ/¾j­d4-¤èÑ*BkSE ÿ¿Š EŸÊ(©y*ÅÈÀ–¸˜ä!/—Ï»¢a‘ñÆPvå?Xsä@Q¢„ÿG–èkRª2-¬@ØÇÅüþ™ejkë-„¯hÅûúµæ°ÕW`¾HBtÎa«‡0^§DaÞqŒ ξ%!߯—w‹o8æb8£îGFKÐ… Ër+6†dl‘ŠeL7x›Æ“|˜\<³L·¿8) výÀ²Ü®GŽâ,ÏÆåµt´ ºD$£d…ÞÁÛ ÇÒªÇ3*x‘·® ˜-ÛbŠünŒ_Ã1³:Dò`Ë2³&HïJ5¡t ƒØ;P‚ ¾\o–ï–«¯Yì Fº(;;_ñA’àŠÃ[²‚/µßbJ”n"z=ÈßXG”Ρ³Ç<2Ï‹ívyâupµÂÔVžÚõÇ̦ ”6& ôÅ©7_ff+L£çay18æáœ£8»Xm™ë—QMhŸ§uqÿ5/ô0(äl’*J΢@¹‡wÍ.Až±™¥¶Œ¯Q5v+Oì|Ãb+„ÊΠ W“•6’ÂzXe8y#•$î°¼ý ¼.V.Î@po‡ä€Á[Ìq©@òvµ¸[%6a¯ÄIˆi?É·–†€±’¢$xk§&/òwóÇÇ)6ä ôí*§ÕœúÝåÍåËW±V¢N†ä¾âp5)CÓïãê[Ž”&/½W-d?_ñ›<‡§*ÔäžÈ)Ë×)õÚ 5³1Pd›ANm¥ûÀ+ꀉòu©ÈõH\?¬Ÿ—Ûåz51®õÙÒ¬w¦•hT–äD/}'¦ÅkIjôþ{Ð;»\ñ 1` DgšË¢L¬vÞrë0 æ—Î.YéKÜÒ2è÷çPÅ—0Y a¼J ,1‚„‹Õ=ÏpFÆH27Kî¸;à ˜e¢å€³Ü'mð”OÚ;ßC‹}^БÒðGÂZ‹[ÁoÊçl£äì–yL ¢ûv‚+ =Ž¼Íµàp8'Èå¨nJRUäÏ;R•—V‘ =ÇCL ²`úã)oÅσH¹¤˜ânÏó(5‹>6y¼.¨ßƒÞ²X4Úеo%Ç*î4Áƒ_“\èÅÞî9ø.õCg l'?^IcÀ¥ÍÛøœ9DG<õÔ÷SsæÀŠÓ,¯¨b¥µ h>§R©èÉä%kÍAßCQbvF=M”à4@–œ_YŒM¸aHÆ.7Üjç5ü×CŒ»ÉÍH1h<Îrîp/ÎP¼e:JàyDçÅ€°ªi`ʪ8›® £b»ó<ä·œÌIko#@ÂÌõÌÓ2b™Šshz°û*kæNo4R¹Ú±Éâ”ä“»N†Ê: vqlÉ‹Ý/UE©mÊÀŠ3Ž,`ÞAŠ||ßL¦5\emœôÀI¦fô œ±ÞÔ n‚±¼ÂE,ƒªÅYÔ¬ æ„û’ÚH -;ïW9©•¦`{ª[^a‡Å¶ÖR¼åÙ βq†b.'ý'ö;ˆxD‚`?ÿ‡Ç;žüæ@ÓA{?KP'P^Oqö×s€>øú˜ÈtÍgƒÔX¢AÀžcªzâ'еÐ>Í?ñl-8øZ ‚à?Øç°| ˜À«®Ó"FMa®·ó-3ƵV* ,Ê *òµ‹1&Š«ë?y®F¸Þ’BËMªBŒ‡±Xô-o7ÑKKK@“ì¼ÒE…¦p+¦kmfWQ_ƒå l¾îC+X7$°ÇHùêe1÷(CÀõgµ¯¤MZ¦‹ŸRÅm1Ú(2Sª O­‡tÂɃs_sZt̪…ƃ¶G=v½y{M©®« 0·¬J8¬SIÑR óÕóc#µœÄA…»x†b-ÖÃIžcoeT$s_my~½ƒ`(ÐŒ‚•TÄ™ˆ $ tç ²J ±Ržd-;M+Ы ¸$M›1ŒU%}åA‡Ò´¢d]pÒÄHúË«›—?žsâÑ»€;»ŸçÄ#¬5:Šä±¬×¬tWÐ2Y4‡yØûå $Nº+M¨0ÄÍ?zÞ.žx…DZ>DFð–YÃ¥Ö°QÜp¶Ad:=ʼnÌ2&Êt×%”›¥q0žäíÃüŽwz&†ú8)ÅV±<¦“JCàœ„®-)RÚ@Œã„‡²¤àòò´†TÁR‚»]lžx‡J1ÿ‹3sÊu̼rÕ¦ªxác“„Ú±­$hà½MÒéÀ99øè¥Æó è‡åÇÅã3ÇÞâ9ŸˆûyàFº¦fÀSJ9}º ró;–±­"ˆA¤ûž—:€ ©áoÙÔ®H¡6›A’—>ˆÒá†Xž³ÌÍÜ:ùëÅÙËŸ.__¾¹am5&tBý1½c›ä¢à@¡'¹û+«ÚUî=ÅWv«øŽb,óà>.TÙ‚ÒqAí:(ØÞíÒô¬×2XŸ`^îygJ! 7…5°ýíGVV&j`+)VÜó8ànxŠx™—ñ¬R7Sié¦û¼å¯\€©¤5'Û5^6Ba)šÚžÄøŸ8L xëš÷æ2“íEW¹Yƒ)Ž,(Ë/ŽxÃnÞ·â\)ųžÚcª7K%ï¸Øh“à³<&7Í«*\­ ÐûùvÎ: ®½Tަ ïº9ΕòÄ,1÷9,¨½Ä41·ê•]·Ÿ{žP™%öý¥ÊiAÌÀ™tì÷Þ5ocVi»·%bb!2‘‹2`ê-?Qyûrx™³”Ñãåó´I@)¥Põª/x÷—Rø§ÜÒÒ]ô-`Ašgf¸ÿ¤}þÈry¢‘6ëSY&|EÉÓóâîÅ9yAc¤1ú´T‹uÎbJ…gO¨Ó×ûÌÚ ÆÔO¢~b­ÍšR¤@k‘âœII2z)¾~”¼05` S´~»¸›ÿYxWœ.TuÅ^9¿ˆ’kAµ&Qw©Á+ÿ÷–â.s«»)3¥¸Ë<àb¤ ¤"Ô‰ lÚf|×P1À½Ó<òGV¨ª›[œû˜âˆZÞ]2Éb’€äƒ4TÞ»Åj»aåÐzc)Å€(Lf.ÞœŽež¹Sü듽ãÏÌÖvMЂ!7X–ž›‰x<‰Û ,Eqñje+•a›1üâ.oƒ+ÎȯÖE¼NÇàªçÀœµÅ›ð &mˆé½­‚ûšUº© )½Ëcðï_ñ¢p؃<ÑS¶ޝ(0˜r̓n™µ›Êc&[Q°½N1éBO áóÌØè,8«¨”¦xÛlt–9 Ý[ÚüÔšÁuR ´ÝCñÅ/¿ýþ›2=îCG ¶Âpñ»æÇ?.¯®;Ï& 3¤­êº(XÛótò7WtØ;~3‡—'ºØGÅLÄíòiþnq«Êüýn7ðx z»‹Ôav™çÔÇôx0ÆUôPï@èÞ­7ŸxüP•’xv‹ ùè’w‡à…wÒºÔ¾½_>ùÏŸVwï7ëí¦´òóTsq¿‚ÿÝhw}}õÓ¦aþ ‚d‚',æOËÕ‚iè4%OQž^($þKoƒ“!¹¬µìUï€*Î\õ:BÒš‚ä½¹ºøîÕÅMß…ÓôÕB¼uê›´B“3€ëÀÇõFú¹™ß/ë‚ÙŽÕ)ò¤‰Þð Pò³ÑÞþšÿkñ¸X½Û¾?ÓÎY“d2”™;tø´^­Q¥ŸæÅ—'S6÷{ñÃúq¾Yþ»µð üù¬¡jÆÆÇÚïyµÞ<•¥P‰Ž•‘•Q³ú×íÇ]¯gªæ±ïðÓmÑ*68©&A•bé?5ÆÝ’f"DÊFö%m‡ÛËÿ\üãò§Ë7?Üü¨ÎZÒøzI[24 á­G”¢Ö[ì±=>’(²+yrƒOM¡+GâÖöqu…u±îwŸª­âË0˜ ÷.C.3P°l™4nu–^âã;ÆŒE&bš¯E\_á84É}_áö ç˜fã°¸Ãç#•3,°±Jޝª·‡e\žç8|¾Ë˜QÜíñðãY#Õ¦¾tÊXÿÚòÆÚZ~e%¦¶‡-´`$Ã*iªØÁÇʘx¶C´¦?O·’Õ9$>½j}Ï>ˆ):N îuü¬lÒ\äu¼9ÍTxC” ˜ƒ„к,1Á^`E„3ŽÒ³öÐÁçÉAàûqÎ'Jµö-ïÏb•ÇÓZztHüÄ®‡ïøÑѬþ|úc±¹]?ÜÜ ?l(´ÕÒŸ¤‹zâçbç!žÀÖÙÄ×Wƺ×o´?ËJä‰Fz`:[ŸHÓ4PÝñÅD•Oµô¡wî–=Ç×ÒÚÊ`/­zâhí [•t^Ä$Öï¶Û‹__]Ÿ¥Jø²n8Y øÉŽ]ÞëceÇLÁm}ºÿ[c~s,õûG&ö%'ß'þ;Ų3 x¿Y '«pO}ùÞÃÿhrö“ÿ+/k©ø0†¡ž!Á-õyü=õoÏŠÙ±>)™“m$žé9êk|’úߘώzZt?î9×ð·Ô‹,~‡úúó9QÞ„rªÞgFƒ9ÐÏ æ î›Ó¡ÃR¢Ð w8VþãÀºx¾ cNÏ-DFO‹ÕöÌ(P© Õ¸ùn;ëZð³´ºÂpl_«wÓÂLŒÀ²œõ-x¹Á›TB€g;l•>s Áõÿ§„€ ¹UŠ‹›‹Ûï¯.^_– ȳß À7¨z‹ò¹»)­W1‘Š…!›ùÓâLEð/e/駯çnc¡•£C¶CÇóÍfþéÜí"'AJ†ùÇr5ß|:WÑ „íVŸÈu-nŠçÖÄ$ >/»ƒž•Û’”»oÄ$À/®®.Þªó6‘ –r|-oêO럄ÁBvÌ^¼îeG°>œ·^,ß½ÏæÎŒÆWÖÝ,àÃ1¢ÔÀR¥˜‚›=Õ—T°4ìÿô8»Îà£nFEÌ8áwS¾`û_|!„]û c€)2â³Ë¢O³w6rMAž5^ ß4ÅÑŸ$œrÍð)޽Ólg __^\ÿýjï %ü/|)ŽL]f³hßBkÝ<«¹×»§ÅüùÏÍnío g,ûË9U†a` jJ² §Ù•1¦àƒÂMÍMði±}¿¾š«šKÛhL]Qsœ‚ɃŽ0>©ÕiòÃÏo^ýü\¾« ²¨?¸Îtš¡ï×ß;êgÓÞÛ60¢k|ŠÒ65y¹ÇrÝý~ß åZt›Êu“L˜+<Þߺ#)Üýâ»4MÝFn¼û‡å} Û‚’®±Æ4jé˕ǟ½’®ªDX|"Þþòã+š5bß+Ýo*5ÊDsßkÓPôzýï‹_~¹´»~!"jžWìv+ƻ͵»…~h{CSaŒO–ô=wv’Þù~¹¤·ÍDGÒ¯_^¼)‘Tì‘çL„‹õËn»&µ2©áxjo\G-N6K-¾¦ÒQ‹j° >4¡øÚÊÙ“> ægŽNšŸN›O¤??æXR2?M1Ήýüt:©Êæ‡jAÏOy‹v~z- æÇâS¹iÚütÚû§(ȤÌQãøR},™Ÿ¦Ñ”ùétS8?T z~Ê[´óÓkQ0?úªÌ´ùé´9ÝaÊÍ ˜1:ñáͺÝ/ðÙàÁnšÙåCÙÍæ asƒ6›êåsÓiÓÙ»,˜›Nùٷ(ž›á>rssÔÂ*fª/k˜0pÊ£7'T•LL…w¹ „ ât^öMN7ij šzZD§]é¬ôˆ±I)ëAædßàE%ÝMàæ™NbTUðñš8B’ÈLˆRÒ5û¥tw<#¢Û&¿Ó<Äå¦qɂѲ¹ÓÝÈ‚Ñò™jAË~y‹Vö{-hÙw ¾RãT‰¾gn’‘®©;)Ê‚ï¾/&æPºÝtãÑfOp<€0ÑÂ'Ì$M€É5™P«Ù|j“½G©ôM Ôä°KÆâ‚ •§Ð–+àꦩNÞ.ŸJÂ+cñ®ŽD!–ÇÞ¦¾ZÌP@÷xÅÁ¸6¦’± ‰”îlÕ—é£Fƒ"ÀXÛo×b¨‡µÉ¤$½>î k†Ä@v爨” ¥_TöFUßhó%¢£ð2Q[ª_¢ûý)úÕiv¢_G•}C³_¼°j’’éÔ¸Üy‰iâû®¦ìëèè$nÁ•§€t²ªâ0¦\J°êW~õ V7‘Q 'Ú%‰2OÒ“n£)ù ¼†Îû£æcù‹ÝR·kR°œVIUe2©ÙÜõ~`‡Fc×ÝìÐ|,ðo&ºM ÿªæ6¿v`ÓܬÓ(1g-1õÙÅn㱈yïvÌ4ºã óv`ûFýPS nlvÛxµ-:-F£Àý˜@ tã©”©nÓÐÄØVm§A›èMk·/Œ²R[;q4M£~`3>œN»ÂñtZŒÄûá›!LQÓ( Œª%²ÓxØ;¶6I|N‘hq(PqIÉÔ)OÙ—²ˆ¶<¥®k9*OÉ•·À«gûò˜º¤åItËcê?õÛ7u;m*wT%“KͧõOwEp ¾Žéû¥;JÊvþöOühî endstream endobj 100 0 obj 6505 endobj 101 0 obj << /ProcSet [ /PDF /Text ] /Font << /F6.0 11 0 R /F1.0 18 0 R /F4.0 9 0 R /F5.0 12 0 R /F2.0 10 0 R >> >> endobj 102 0 obj 66 endobj 103 0 obj << /Length 102 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»ås¹ä RWû endstream endobj 104 0 obj << /Type /Page /Parent 105 0 R /Resources 106 0 R /Contents 103 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 105 0 obj << /Type /Pages /Parent 222 0 R /Count 4 /Kids [ 104 0 R 112 0 R 119 0 R 126 0 R ] >> endobj 106 0 obj << /ProcSet [ /PDF ] /XObject << /Fm13 107 0 R >> >> endobj 107 0 obj << /Length 108 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 109 0 R /Filter /FlateDecode >> stream xÚµ]ms7’þŽ_ÁJª®¼u+ìàÈÖ~ %9Q6~YIÉÚ¾\±hr¤p"µ$åÄûë=œ¡È49ŒªX–ÄF¿£ü{ðÁ¿/oŽ:-™ÿoû•´T70NÓLóÁíÃà/¯Ílp{7x1™Ýýipû¯Áåí £ÂYò»GaÅÇÙ@9*¥Ù}tòß§ÌYgÔàaÀ©ÿêùóÁ§áå-©S 9•BïSðböp_  ÙɆì€Ng“#ŸàRQçÄá,9ÍÈv–’jzìÓZÒŒRxõúûó«Wð!þÈÖ|èâzøê64PÉ!4Uâð3¿\^ß\½=B0œªL°ãͱ߷œ²aŒÊ#SQ\ø¿5&#W¯^]W#’=ñð Ë?.k!!J+O2; ùæ|¸›åó˜•4[G3kIcH-hÆd}ÈÆçƒß+(ö¿é²Œ‘lðü6žc‡Á2øc᳞•š:#‹_ååÐÏÃHª¸Û2Rîùm5Ÿc¤9ðÂɵèd¼Éï—«/{ؤ-¹æ…؉6ìáû«›647p 6ã—Uùå­Q<_.GíaI v`”×"gê°£ñ³5MȤÁ# mÒ»Þ|yÌÿDby10ÂR­¥Ç&MìüßO³Ç‡|±Iá wT;&~š?æ‹éz´\D‰I5BF`‡#r„Ïùd³\ýûßy!Œsjux„Áá<<9%éÞbXÆZ !þ7e¡£^ðà ½¼»[ç›N\Ú[èŠK»è\ê`*.5† !DÜRkÿs§&ãÔ4Åõû·o®Þ¾¾¼½¼ù¿¾Æ­µ`” lˆÕr3Þ̼&Ĭ1Ó–Zõ”ؤ†}¿\Ì–ù&_E-0gÒ‹Å(§ÇAI˜dî½;‡x Ê@IK>pÏb-]”¼È¢¼—þ˜Á˜J8¸|К(ž">™{d”êzÚqˆ‚¸ÄAc¶T7íµ‚×­Òžºý}øîÝ0Î,mÕíyˆ°ºÅ°¤R7{OÝbxS©[‰N¶(NäJå@¨>ißNi´òÆÙ§+Ú*ïð™›WÅëQÒâÃ_ëô™$( '“J-,©ƒîÈ5Zg2J ·á« ÐqjȘτýOQÐ(¿Á|øgLJb¬æJµ6Ô5ƒ=Ý~÷ÃU” Uš ¦Ù$ʑֱI¼#Ý×ÀJ³qÖœÄ%GÜ‚[7¥¤³E²>ï”zŸà¾º5¨“T2/.a¢³(£/ÀIYT6²8ÃVDÐZÙ¢*pBGH;ëSfÏAP§x>‰ðR`tÚ¯6KG]3»½yûóõùe’‡ïóE¾Ï#•XR“5i.•x½|ZMò(3ï:·“Ñ4.¼ö2+4Êâ8™å JÑ´uxÍeƒ’X;À÷IJíGj¹ðA>ýÈðZz­Å¦ë×wúÅhÖ0.ß_¹ºýçÛ+ý* ®^«";õ ‘|¿žm¾Ä™g)¸Ç pœ¡å™¦ \c3K Ѓ¬=cq»Sƒ0¡Q»Ó‚6 m™î”Åì_(N•auL’`J½"ZpšÎ:/|Dt~ûözô1*àªt+ ¾YëyBj•² _òcêãO(F† ¥ “i+Ù ƒfq‚V /¥º•ônAÉѪSkžVâÛ~ú-xê¸H"{å©vÛ$²OžVŒ ÿ·©›Ã¦}èÂ[R×´ø M{F']4- ¿Ó´8/QjÚ›4-PZ'Lr+«FŽWúèȘÑ*ƒFÇŒ~ݬfo#K².;"j‘Zì#å\л‚e¡Ár…1I¬ûp‰iVw9;%~1–J\o¡Ä­¢ÆJ‰Ãð5wIâ”åKœün•˜ $w0˜Uâ04‹ó•‡A#}q¥Ä[Ð~•#4I‰Ûƒ¶Vb)c½*±²Žr.Q%~wu{þC7î’o\àôžJ{-F°{Ñbœ1 Zl Br‹‰j1%i1Ê’´¸íU‹;̾½÷ÊÒJ‹=¸’ýj±á”[[ÖËŸ.__¾¹MóÄuìž=1߇ْꉒ»L‚n(-¨àü´/&¶Ð8_\m” ýh±—†Œù,›¾Ü8A+6C †|vݱø"5–7 Ó6›·Å(¥$ªÑ"U©t\ÀW©t;¤Ò$¢U‡ï³…³%i7mXÏ® ‡J**¬ë§¹h§Í[Ð~ R;mQë?wÚÜô´ÿô¾XXÅqÐcæ 5jŸP’lËÊÖa…N¥£:¨û~»¥ƒ:¨;¶Êj{x}=ü0º¹½þùüöçëËÑOW7· Í¥ŠYXÖݱ¡ºÑ®®2Gô=¯Vã/£õfõ4Ù<­òÑ|¶ÞÐí7wmÖ$fYF•jl‡Ç›-¦ù !tÌG£¬Ý䦳‡|±Žm-´Þ(ð@§whÀÇU>ɧùâÔ6ùц éÓ ­lÛ)ú!7‰Sô¥ ž¶˜"ô ÖùflÍ?ÝÍ[FéÒm¸ *X\Bµ5‰¶BîÇ#lM¢ÆÈå"Ëâ6ÂÊ2—EíÙ2o´2‰ð–¼˜-&«|¼ž-îãz8¼Xfž%Éò+‚I…„F\‡HE OvRB&/x+vR±%1RÌ2+©³ÇŹ•T„ARAºKED„èˆ?“ÜRËu¿Ç¯Ð^Ž_5± <ŒºÉj’>°:âHÖqäÓDëÚEÛC$û^!Á¹iåˆöÆôDÛ1…ãÔiÖa®ÓÙúq>žäÅ ¯øÉ =q²Ãd÷z»wÈ,ª3\E3Þw­¬l㮃wsäX™A`àþÓFŲ²ƒaIF™Jªa ‡aYÏ5ŒŠÕíÁIÇŠŽ€“&«#šÅ1–tduÃ& i)ë|\—¯3  5ѱdVú‹:6ÙO6«5¼¹úx™Âá(kž.IõBÀ!kXÏ|¾µUëÙòçL3Ádò¢d¶˜ƒµH3Ï‹qʵh3/ø_JÿÈåÍþŸ`ÌÛ²~\ƼÏÈÝ3!‚ż¨Êò3ÕéRòÎ5ˆFG<ªÐŸ„€Ý"RçB3À„nbdžk;N™®ng%‚ ¯“u0]!xkº®ÞÜ^¾¹¹º½º¼Iá‰6T6x×-W×j4WpM5¿oÍÔb•£Í,_×Kd1Ö—KG¥sˆ9ÙìÓl1^%šI8x«š§C£Íg‹|¼Šm;/GŒ*­[Ìí~Õ˜‚û€FŸœä§/›|´\MOd>1Ã⊮Sunc}kÈ¥0³žÝ{¯g*Š{jAˆüìÓ,îª#¦¸7¶c8¾û|õMä…íÝ7öãxòù4é€B‰L~i“t@!x3ÏGùb:[Ì˨S°ƒP» M önBSèMh»‹Ô8ÕŒï_ÄæS½úElþ[õÏ î(·ªºÉ v½ºÝä¶P”K³?r0ã'h%k^åV0W°“Ý…¦V™nwº•ا+!=ñpñà‰«Ý>Ä)ÙƒÛ-°i; æ]ÃÛá±yœJõw…¯pûk’&VØá»ÕÎÎί^½¼z3¼þpöêíõëáíÙÍåùíÕÛ7gg½¬}qçSC=Ï—ÊmÎn}°ò]’Hû¨]Šêf±†¥?>Îg“¢yñ/ËÉ&ßœù&?ü5inJxm•ØõJ“åÂ'‹­ÿöÍgç/_Þ Ïÿ~yñM ©­ô1H£È°c(tkÞ嫳Ë2ý.e¦RnÃêrÐúL_o.µì,ú'¤½·³Íå{ö²0Dg7³ÿÈ é¼fÎë-ëÙ tÝ Ÿ”ÞÏT´ÿw³^²›ÊÕÅwÁü·õD¶êÃxC´ ¼vSPÛü›Âå¶êÐÞŽ“‘5ÚÆ€-bõS#”¾\z6)#°) Ù[ê¥tpY™ÄØFî):¨¼W(n›ÞP×ÁÕ7½­t˜Ey}¡¾ æ]V6žÍüã«Ï¯þ{üvòO«®Þ˜§õÜÿö·>B6퓈¬Y'_^[ýIZ3¦©1®"¢q# ¥½,“”5ãþáâõ…þ‘ÙÜ[ñöõê/›ûõú_¯¯~|ý~x{±þ¸üô“ˆ—ï'²ÁÜ’QŸäßg÷—}ÌR9 ©R§È¥ŸØEYCyÓ¿ÿµË¬¼Îš"Ô+¾ð$Õ†§½ ½¾@VÏ] Œçys´ÅTøšSU â‹.pÙú4‹í!“}ä_ÏØâs88nñ•¸"3I…ÁàyÁᜄÑcÊkÏÅàõ 1åæ÷<ßü9^T”XBµç]O„¡FZŒ'),‘ .òÃXòc—h«ŽìapwFãM¶ò‰gvÄ%Ìç³u_C׊jµC'5ôÿŠ÷d>Õ V¢òñC K¬ð™ ê~ŒwcÊú¸‡)ÌÅ‹ÙÅ;†QÅdæ—ùj±Þä³Å¯J`Ìn §¯T}aBÐ#Nísôèê‘È^Tå#L’îe<ž+‚‡A?&pž1:à÷Wæ âb=¢ÅHNððÂÊ¢ € Oj5†N^8S<UÇ. 7—YJÈŠ—ˆº‚îY’¡ÐãùòàtT×8Pú°G9Œ)›ßò¦@«C%ûcO|úä>”'(dW–À é–a,¹[%D‚pƒŠ°¡{ùïâ¥ÇÌHx!IÛ0nAE°É©«Ò[ÉŠ’¡¡&%%”PõÀeeoQ”‚-b‹IÊl‘ jF3Ž J‹Lû„­\±òøŽc©vDxìÑÞMä*ú´Lp;ÐÖÃ-Fõç†(ã¡ýç†À#uL` ù/#ÂGÇN8‚Ðü´‰·&E¡G ì˜-â ô8ÿKAhâ Õñ`ê”×>9KòûêSaÆQ *d)‘\Þ‹pg¯Có!¥$#!òFå>#Þ¸’t]É04üHLFçãMžP1† †3{Ýe‹¦=@ÍS(#u܃«Wd$Q¤‹Î·­?pˆ{P¦Œ’mÑ0àª$H"ë1•ÙÎR‘FäP~–Ú"‚Ëàx㣩E[¼ýæ ƒ¿[%Ô œÊÛ§œD‡°;hr”x¾W]O§"ضI6¤9™D —O›õlšÇש„vTòŠòº äÓû„ʃOµ­bå),±š ‹q{¶ ñг[HèÁ2¬ÎÛîÎlúvØ'R¿ÎÛrÌ›@‹—»"‘LW”Ęò¸„ó2>“ZÜ'8K`ô7U¨S„½Û4 l’Vc{V©à5F{K÷ƒìÙâÊ–lé¸oäü_ cˇ”m# ›–¡z:[¥ì©mØÆ.ïgŠOŒ3]œOAe¥x 8¡Z ¤'Fþr‘V.0âëÈŠRÚ» öõTHYYl Äì¡`À5™ ™]_rÅaSÓ@'•ÃHÈ ¤É¸Ž“žR°ö?†}Æ0ø,¡º$¬Ï$4ǘ2Ïç á>‘™-]A(ß^!ž`s… R_=Tx`r}ðìlMZôs3~Jj(¼Ýò&7LôšPQ©ȳÝTv§b¢¶%ˆ‰dš´p4$â-‡éîÐ(B‚!‘tãI3$ŠlýñôïA:d'"—?¡ô·±ç'¢àù9…°‰H¤¨ÛmKÀšt˶ŽÇè¦1²ß'0ÄÇDG$fš’îCL¤2…q$ub ÄDðš/*,XLÔv“F”›4a+°LÙŒð1‘Íf:È ÇDJtÐ!Òµi¢Œ‰j¤è¥I'^ ©±&:°ÛFi¼4BÛzü×ãEÊ^¸–”eºþ\nNØË^IµÂ(ÏÛº $Þr”9¦D[pXÓŸýF'BP“Qé#\¿–Ute‹Õ”Á-­a¶$]ú.ÃOÉWÀ rº–TΞÂ'žpl˜)rŠ0[”;F|-§èÆ(ãðš¹ÕÏG`úE \‡‚Ú•÷´dM±/~\À;; /)Ü3; žnXÀM0Ö(ó0þ’à‚à,“6ñŸRúò½njÜ"Ы„ k&¨“f<¹•”ðså}¾Å¯R’}V?E —O‹”£ > ÒSÒ6Æ5Üœ„.凔5C%(¯ÓÊe°œŒ%iÕ2 ço™k+Þ\§B3TH6øÓ5-}œåÛç9‰ ÇC¶¬8¾ŽZÓí¶ð\¯Å™“éowlw¤÷šéWU-èz°:Ðu¸JÙ³eÛbØyž°ç#O8ÃQB7X²J8"M¯RbT{u´¯ ëÌ…G€r_¾¦)¹Š¢Fy;¦ÿ*¡©LWõ8Œ5³„â\*×°#%T)*7¡<¸ÍfÞ†Iéä)¬§Ø4ÀIêµ>JܾE‹}ìuí–Žúà5Æ–´Rðþ ܘˆ°eœT)÷?ÖãË4¥_û@HbIÙ¤…Ç ¡øðz:Ïã[Káe&¸K¾D' —,­Tž)¬¥˜tå‹wm.CÁ7ËHÁ1¦Ü-W Lñù3(OâÕUÊÄfõ òN‹±$©YÉâ>F·Á”ãòBø¸ “²1&¶ƒßR. Æ”„4Úß±ƒx~ª_·bÐÌ´þl¸¨ÅÙF+rJ ’«Ìè úÄþRTƒ¶öì@àË—‡ù˜µ;ä ¾ Ô1ðPôñ#”_¿½M0,Ìï²!Øe§@¤©…›ÿ„Åd%-Ї¾­0º“§|Æ&Q1LõÉ>’¨úÄšÉAÁ†K‹Qžä­õvœŸÐÍøËZ ÓŽ9Œ-•nÆ7Pù`¥¡û-uó„±õÆ\rT¯‡ ‡aŠe‡²e˜r‡GT#{’®Ó]-pvޏ×/´˜MRŽÂÁ|N× ä›¤»Z¶ýÞé)G¦L¹ F^¥\Õ"©ÝÙ!“¦½ŠwÊ>ð”åÈãl3II”7†ÿ-¥u—y¹Æ™²˜¦´îjª9*ß)'¢½Ã„gäÚ”ßEq•pºê˜HÙà€ÛÒAˆž%äÝ ^F;& etNpØ ã'^g=’EíJdüYµÙÁÆŽËÙÖÿÀ^;Ô™ÃØ ªpEŒ–åH\šò|ªâ}Õr1;ŸëÖEgz+KÛ)JRpÈdÛÆœà}Škj¹@ Êf™p'-.`Æ8ò)å¿‚»-ð¤³Æn’õnáH—MSìÌš’=@[Ú'µÊ# DN=Ü.µ*žË S½ÎSš]¡ƒI„!ábx'OÌ)“‡üÖ;)¥ÜµYLHnÞ]]¢I/V6Ðrïwï£}ûí·ç/_}—ô ö–[šj„ú³0¿\^ß\½}“ôäMñH:FY/ȇtµ¬£ÃŒ£ÙÃø>±>^ÏÏÁ›Ï}›ôRbù®h‰}âìV!ö®hsˆB.®^½º~ÓÇ#kBÀÝïeMgww«M“ÖºšExwúõË^Ö˜Ã±ÏÆûVÕ&«/ëÍxÞöÕRD³!’º+4•Ñùõ‡›ÛáO¦—9Á£>Õá¾åv‹ýUå¶1Ğ܎nÞþ|}Þ˳\"+Î.´ɽ£•⎧¬Ã¢5Z/ŸV“œ–ÿêçZîC;Ù|å²6äö¯4WUŽOŸ˜ úš{Û¹•ãrxÁX2)Ò Yñ\ _ŸÌúËbòÛj¹Y52§NÏ$à ftc²{|LÝÜ\ÿ”ôN$J˱‰|ÊÇóÙ"Oz)ÒÀ† áÎX±¹Ñ‡ ÃûÎÙ×q½%ö×4aÍ!öMØõðâjx›i)C±OS ùõ¬ܘ×|…²Rò”¶ TÙ³!ƒ‡¤3NNŽúûøs>Ï÷›ßF‰ñF52<3-Ôéù>,K0 c8rÑÇœáhíNÏùq9¯fÿ©,¬ÿ‰ÿvÒ‹¼% žƒÎxã÷“,N¤Èm™Ïà•f¡ÛÛçÑåè}ðžÁ£Ê†´÷Ëè´m=áâè‡h;á/}L¹ô§ ^ãækùÓ¾>³ñ)þ›ïo`}øÓú(ûþt–’ãÀéÇÐi0Æ‚ûø]œiù292BFmÒ»çå«ÑÈ*ûO§,²ôq¦`8é™íE9à”‘aø´ô¾ðœ®‚°&ë#½`ðr²h8Îo“8S†0ö.„IáN”CÔ¹SaFÏ ÝË’Ã]ÚÍ%ßF3}Øyx•6S' ýè9® ýÄ,ƒ×–Ü ËÈÏ_ö1w§àV¡NSÿ}“&­[O'b3}̤̮|œ};HS™M2t¥Ÿ O…­¨ò$9â# Ÿn¯;£ü÷þa<´ÉóÁÍÁ§…¸¡MÒçZV xV~Èÿy®ái-ùü­ú籞ÁrnûKÛ/“Åã#pH¢zŽ“?ON<Ïíÿ…ºG endstream endobj 108 0 obj 7400 endobj 109 0 obj << /ProcSet [ /PDF /Text ] /Font << /F6.0 11 0 R /F1.0 18 0 R /F4.0 9 0 R /F5.0 12 0 R /F2.0 10 0 R >> >> endobj 110 0 obj 66 endobj 111 0 obj << /Length 110 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»åšp¹ä R_ü endstream endobj 112 0 obj << /Type /Page /Parent 105 0 R /Resources 113 0 R /Contents 111 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 113 0 obj << /ProcSet [ /PDF ] /XObject << /Fm14 114 0 R >> >> endobj 114 0 obj << /Length 115 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 116 0 R /Filter /FlateDecode >> stream xÚµ]Ys#7’~ǯ`„_¼Ââ>æMÓ–=Šu–è™ñÌ:´T’¹!Qm’êuï¯ß¬%² ¨B@w¸EªÉLd"óCf"úcñÓâÅ_— ‹­â êWÂ`ÎíB[…‰b‹åóâ?¿§˜,èbù°øö»ëï¿¿ùð‹åÿ,®–ˆ`nÍâ­(Ð…QX*Ù~ûî¹ü=¦ÖX-Ï †áÕÛ/ž·è'ß ŒÅRŠãA|{ûîÒñõ|1¥±æôtܬ·Àáï.˜6˜Y†ŽÙ}7ôy#11údx—N'¾Ï[Š©>g9$ |Žsé¥ï'ð9z]¦(×€x‚‡543 hh©‡€?\ñ@SMVB~Nó†H5ͳDH¾á¶Èt¼+=#ÛàB`*„?EKX`¨Ö!PØß­·x ÓmÎ —ï+å„A•¸Ô¬ö‡õî" Õ˜ 9(MˬØÞ'ä¶œ˜ÒžÆåJÚ´bÒ&ÚÃìÒ–æ¥J¦,A@ñFx(Á›ÿ@Š$,‹¢<±"8Ö†÷(#_6Í`„„\[4?ú9Ò­C˜†è¼mr4ýhaLjØÃ4ƒ“ç{ʶ!Ô¿ÔaGõª9Ó2k&ÁÍ8'à$èJH,©›†Õöñ©hàm>æ0¸Ð’Uìvð£H‘2ih¬t›í]>&d—ŒB¢NŸ„÷›ýç§õ]®¦.Œ@¾^Y šÀµVãJ°2l¢¬oZNXV¨…$žÊüËÊáØ0^k®àA&³táfÒ8ºÝµbÜyEI˱µááFõµÏ0ZöVðYÒ!‹œ¥¯—õe/Yôí,^Q\nÊ4;S± "árÃ+R±Šu®aÖýä¾kÄj¶u aÔO÷fÙšs ÿàÇ|–NZ×ðÓkl­køUBðLss®Q“E3 ÃkoÎ5J˜Õöغ†Ÿ¨g¨1©bëáùJY5t‡ç_5Z‹‰…4š:Ô­,TIlÒVšr.ck]Ã?`’ºjÄ‘¼jøÈ&¯~ͦ®yë\r?CÕV aÝ×´ê.EQO²]äq¶™dC©/ÓDÆ‘¯0RȤ…à²Õ–ã‰ëPnõ¶Î ;K¹­³ù‰ÎÔ­ó HtL/–œ½^8§@>º'ý‰³"Ô×~Úþ9‹ÈYœK©ÎZ{œG8ª(ËÒã"0V5/„´å™žhµ¢HA›ÌjuV+6g sZ‹9=ÁÃ'Äg££3ÜY”`cÎrQÔh'¬<Îtýd/–³ÂG0WrH¹hÖa1-c‘šl®ØÑÙ/‡©£z<‰uáÖ~ý„û}ÊÓwtµµò šÃIÿÀçÆ|­µÅ‘ÏŠk¤ôQMIЍ¬ÉfKŠ]ÜWµue”‚X#Æ{RЄ}ßÑvWfÖBÜìÊ4´ÑÀ®Lt‹. é¤l^2q-ºñÛÊC˜Èá"tÝWêöMêìÛ#ì`ý˜YÝ´–°ab¦ÔØé6[0ƒ]ÕLµ:lžS¶M´ÄTÒ)}[]O(€ #à=ØyJT$5†e«'Ŭq(,rÁ-åÞÚXgiø‰²¹'-7¦´öÓMÉišÍmÒ‚µú‚² "–”ü…ñ¿ãcÃ!å´R î¡ry|¨\ºCåÁ#éM+†ÚíÕAôöDûÛ¯º_çÌbqøÛ‘xä;¿‰w@L³ãñ£Îøe•¥öÅW:æí ˆ9‡€KêÐasÿ¶CùhM$‡±1PþØ!yf±ca`úJ=×,F—›ðéÒ.ÃÈ´úêœ÷.>h†@Ž~{ˆ~2ë Ñv)J™.ÇzðL}—óPËÀT™ëƒö(–s¹ÇžEàá“÷]¾Ç›ÏIb‹²Yºcç(¾ñ(Ö·5c¡#óÁ-èf+ÊGJ…®¨v¢“UÕ¶ Ygy<Ý/ ¦Žb'Jðë@ŸVÊL»‰¨ ±þÖ|j'Â/ËɾçœyvÑ’G&blšÛ‰ðßB0î(v"ü :Ûk 3.8¬ï¶½óùwÙ|»¿$™<"p™B>h i‡ÔýLz‘¯  s‚v”'Îp—zÓ‚9°Yǵsà¿ybÂò€FæÀÏàtóÍu„fjhš™Ž:›¿¡ýT'hïá8—Ô Ð´*øD'ð ‘Ë :ÔÑH•yª øo&Éè~:n†õ a”Û„ Þà’º4a²ç2‘o¼ÝëÑñoª~ýk°1<6úmRCϰǒÀxxoA Ÿ@™˜)ö¯zÑC† '{c°Ð²ð_ZR³8¹Ñ,!™}»Tõ™¼n>›¤=œÐ§À=#͵LŸ‹íý~õ²Í19Í-#þÉùRݪðoúkR,O ´ úè>“0'ök<ê(™R&IÂR¤µ ɳû7ÿÕ»M4ub:÷° c!^öÅ!vbBxë&ÆãË 'ö«w·yêÄ´œP€S ´ã—çÐW"žXè(/eª%D´ÂÇÏ eÕ-§]VÎÄB§Ã§Ä<Íbæñe»yy.]𨂇- Ï<$NY½$`$ƒ '@›¦„ûô¯H;Õ(ª#+R'’øvRˆ#YyÛT÷l•puH!8I!¢¼˜×žÅHZŸõ_ãu$;:El|¶f…b}vJä|Ö/ÇgçÔÆœÏ¶L¦1¸ÆšürŒãçxd þ«T™y2 %˜¶9ªÞRRÈKUV„à0Ío¤ûƒ× âÃ$õ49E€CNpK1“"¤˜$¤àÖbˆôÇŒ‚aqÆŠªC‰’ÍY1Â'‡wUG³â„JƇã5¡ÆŸ ã› £ËdY_°©¦)µ©eY¥r„Q*$€F†cͬÈ$ÇN°ä‹~'¥2Mi¤KÍÇ‚·¢šäX–í+1㞪‡L`Ñ¿/÷öãÏ7ï®Rì¤EšA‹m±[?¥ÕÒ$V2(Âþåuwç?ãÒ‰êÒ¡>”:· Ön;I‚GXžT™#ÆÓŽV‰$ðaB*¡)*‘Ä@L C:ÁÉysÄÓŽ× +›æÄY̤qS$©Ä²_üûáæòï×Ë_’JWÎOýNýt8?­9ô`·þ²9$…¶˜²  IASy«£¨nõÒ&I[n.Êðkæ"©§¤q§ÁÏ/œ; (|vîÜɯ”´<VRûY ¥]Q‰Â’ËÛÜsÄÖ5“®r»õvÿ4)ÀF½#QÜUÄ))x»´,Pê,¿E’ÎòýÃÏcù´“-ß?¹4‹åŸC'`ùæ\:‘rmÒI–&&a5–ý­¨3™hºÇv™ Ù;Ôd¥ç±3qäø)W³·1Ò€Ã=FãVZ×`Ä­B?Þê&¯çÂÔ–[XCãž­]>jNžG'”I!B:Ióܦø)Ê'(Ú¼:iQÁ¬úÍhG½>Öñ†É™×ñ€(9×ñ7ÞçÀ¤ÒTðK±ú% *ø‰Ó,¨àŸd’üã΃ ´“Qá :iQAÃOÅ΃ ŠceåûÏ2ÔŒÎR?w°à—Å, Ù°Ð²8,ø¥îÅŒ†?ñ<Á‚†ó ãN†…sèÄÁ‚_'y`AJ¬™<,€½èþYÖæÉ0«›Ë,˜Ps9w´à—%k´Ð²8,ø¥>.¾Üë\¬ÇÍß;u1|Ò¶@ëb~Ú4E'­‹qƒµÉ«WïÓN×IÓ†04šÚ=!˜Å†±®JZd¸ü.©ûÌ!CË(2 égɺ\ÐHuaRÍ®A¿ N]Ië—C?‹DŒv…ª†zÞ`_šª)$0rš£S @;qU¯z΢’¦[`hØ©­U‚Qld^•¸^„²1ÙÒÈËû£ë™u/BC{Âþhê)þ> Ô>­nu»¼ùùÝò盫Õ×·Ëg¸ØJs š3ÜHlî7¢W?Üv¯w‡×]±zÚìoODÌВµƾó>¾›í}ñgŽó\Ldÿô¾—ëýæ¹ØîGBËØc8\Ö—lDqþ¼+îŠûb{Wdð™2+4ð>ä"*eœÐÕ% ûâzQC}”PFM¯ø:ðTɉ74 ².I\C8¢l8)ïSÉ‘N”“”€ Fª(;0úê ëýfû˜•O³ä=&§Ï#]Ý~º¾¹ü1i– SÁ:Ë3Ú9ïœiXx½ ³Z­r8äÄëçÙN2«0g< ÏŽîi %Ãá-f4æ2nÍ(ßDí2€Ï3QxWWÐäл‚”‘‰ z?¹…&‡âÁbšâ·¯OëÝêóæp÷{õKŠ…¥ô¿[ßoÖOÍ2,lL0,Y¯P8úFŽt6Œ†*{)`HB'í*žª}•†$ÈÒ  ßÖ2)›®OÔ‚st}°² Í"Þ‚&úkkAFUzNy,È/NÚ,7uŸmªav’±¦S¹¡Ÿ·Õ¯9ßûd2G5)@?K‘€Q‰Sg)4´ÏY$è³8*´~vý¯«!*# +yžk´¿§EŠb«¸£Þå5,¡i$Ü9µÀð?oþ,žöI$ªdGzT½Þ)Ç_×A³Ððë5&e…¯Ð͆èÿö5í:€úìÈñÎõkT’´îîº^üósŽ0Z•å^ŸšmO5´»Vÿ"É⥮®G üqó¥H.L"ŸŠVV}Íܽ¬wûwÇ Ì`[=éÐ;þp©M¿£Ë£‰z~/vEÚ¡8g›梿~…õ:±2KµÅZ2œâ©yxçæÿŠ·zp†ì’–Ú³¡ìò„m]Îáå°•+Gð,ÿÊ‘½Q ‚¢ç+K6 ÎP– Q–¤¸PYL€ÃÊÁÌY‚¾†ö9ƒ¾>‹£ ïúÃòêÃíõòúê6GÌG™„ŠMÆ€hÏ åÞh¨r_^»pyØû¼@ &ý²=\Ûl×»¯™JjÖbâ¹LºÏõi³-Ö»òÈ^amyC¿Šõq½É²c(¦1R–üVÅ>ÏuÙ S%"„|ùRìž^ÖYæSqL­Žô’˜ÓûÕ—õÓk|—å½Eg„÷šþÐÝO¸¶ø¤JÑÍ} >ÅБZD\\Ç£'˜%Üñ]/q&Ê/§ÝhW—)ýªñ&I[ÛyàBõl÷À…ò =p¡}`,Xš/ÆžbØP=ÆÂÖª_–ûN†—ÊIco³~tÁÍOÿ‰%ƒ endstream endobj 115 0 obj 5025 endobj 116 0 obj << /ProcSet [ /PDF /Text ] /Font << /F2.0 10 0 R /F1.0 18 0 R /F4.0 9 0 R >> >> endobj 117 0 obj 66 endobj 118 0 obj << /Length 117 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»åšr¹ä Rgý endstream endobj 119 0 obj << /Type /Page /Parent 105 0 R /Resources 120 0 R /Contents 118 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 120 0 obj << /ProcSet [ /PDF ] /XObject << /Fm15 121 0 R >> >> endobj 121 0 obj << /Length 122 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 123 0 R /Filter /FlateDecode >> stream xÚÅ}[—·‘æ;~E¯çEš%1‰;`?P·=œYÙkŠÞ±g5‡§ÔlÖ¸»šªª¦¤ùõ‘UY•DV&€’<çŒh™õedd ˆ/ðãÍ_n~¼ùâíMàÁª› þïð'í¹RáÆË++oÞ>ÞüË7‚W7âæíû›Ïn×ï?¿yû_7_¿½©¸ žý(¢ù¹¸1kíN?½}ÄÏEðÁ™›ÇÉáOçñpóÈðÅ[6”ÀJ®•íJðÙúñ¾}lDd‡";Öý¿[ßNüBjÃCPý·”¼b‡·ÔÜò©_[Í+Ù—ðõ·ÿëË×ßàXüGª\y×ûÑWo^}ó6ö £N”²Ü¨þoþï×o¾{ýç 锓ÜTª§Ž?Mý}/¹&¸žx Ó8OÙÈW¯¿ùæMûDÖ1¥¹¯Ì´}Tb†…€N¸ º'òw_¾:½eç™Öp#Ú¿Èf?rôÎÆz®Ãé>òÕß^7~d»€|à•÷ã·´ŠWBŸþ;}¥ê˜Dó÷Yç—ð®VùîO?»]íëû§í/ßu(*Ë…ËëüìÕ›7¯þþî»·oþúåÛ¿¾ùzâ×­¸øÅ¬jüðôôñÝŒŸ°Çàšç½[m·«_ÞíöÛçÛýó¶æë»ÏÙEí8|ãèïëÍíÓÝzsÿnÿËÇz”òÜZǺ}zü¸­w»õÓf.œ Ü‚ÙEá~øe_¿{ÚÞÕÛ9@wJœ¿‰˜øþ`ºÊßûÑïvëûM}7õù¥äÞ Öý•’/Xï§~dÀûÙ{Ôz¦Vo7ñVDôBô~öquû±€×’"pQõŸõ°ÞO‰'•á^©Þ;=ÔïêÍÝzµ™øý¤«$ø©Ã×û§©o¤¹tà+ºŸZo¬»Þªÿ³ÃzûêÕÛW´tì Þíà=/­´ã/¼Þ:(õ7A(up/_Bôðò‹×zõæï/¿ùó›o_½}ùÝ×_¾}ýç?½|yY) vߣ„_>ÁêÙì_¾ÿòû³´l´‚„† Mö~»úøña †þé_žn÷õþ%8›zõø‡ ÍB´a5( ?ØãÁtŸ6Ÿê-z¹Ý÷óË/¿øæÝÿyõå¿}ýÕï.ëD(.”é¿ÉvµÙ½¯·/¿>ºâßO9Ø»<„™] /^}÷µÕ éøìJsøyó“¿½ü¢1É—ß­ÿ»«Æ‘‘þÞÙÞ•¯„’ú¢©˜`¸¬±Ä鯿úý”»vW®ýéÙ&'µj¼åRÙþ›}ýP?ö …Myè>¹°³ƒ6ÜBŒÜýÕÅÍ@‚MáX÷G§Íà¢6ãÒ†žé|û•™4–V›ŸVîá?¾ùôÍÿ\ýùöß½yý'÷¼{ð¯þøÇ‹‹Ð@úiÈÁ·¼úâÍ«Yÿ™€=ì=¡Ì9ŸPúQ Tû·ÿþÕ·_Ùþ/÷^ýùÛí¿ìïw»ÿúöõ¿~û·Wo¿ÚýÇÓÿ;T¯¾þÛ­þ·õý×—ßQ‚Ó8:‹I—5ÃiÞÑcüaF+ø6ÁÀ^5ŠƒM76Ý8˜Š£ØÔ¥8|ô{pÎð+>»I ´5ìÀŸN¨dCÇ=ínýþývónw»Úà–Ô¾V —õpoθBA˜ÙM¸¸7ÑGë'†mË5ÿ[ó ;§‡ £{Îy¿ÿlJX3p07ÖÃ4'Qÿ¼|||yww›°Uå›Ðw(ïûûÏG˜,úÑ¢å ¸'=}ûá“_0…AÉÂrÿû– `ÁêYÚà2p¢Æƒƒ"Ä]mæ)v(.ÁÜ@àHÀî×}qÙL54D”Q\öÙÓû%ÀzPB\J¹ûiº` X®"”P§êòW ~…€é€ÍÓƒÑkJ³‰:¸W)Òn7¶ øX«‘~ùŠÔŸž¦£Æ=ÑiEZÏe‹!‚`¼"X‹»Þ%)Xº "ÃyW¿Ì‡eXÈM‚“”~HS.–(ƒžð6'T¶@­Çõ·Ö 5[ïÀÛ$»GˆF„A彯7õ ï’”!¤åXf#Àïž·‰$Ùš0E{Ei$y-Ã^¤c„À¸–_$›’È àê÷OÛ˜Èìòꢉ¿ ä}ân ©Wæôé†^íã¶¾]ï)™KÿŽkIšÜhçœí×¼‡¿(Üή±déÉ‘¤s¥-í°¢™ƒs•MÙ8cfû¦ˆ‡HÅ:\ÅVR¨],Ñl…:áG°ì¼ØÒ1d=Þ:J·Kv¡î –øWHÕþcó”æ"•n"tö§Nì0¥ÛQÞkàŸÆÞh™Ÿ§üç¨Ûÿ×ɱþs¦:z kw$ ™¡²ÃüªhG<£~·Û¯¶û¶ê’Åõ€ eq=ÌÂYÜPÞ2YDƒÊ‹‚Yœ’R¶°%³8-„¢ÄÍÉâ ¤`³²8¶ÃÍÊâš &®Üô,ÌL“JØNêÖø+ž‚ÝîÓ²8ˆŒ·¥5‹ýÎ×lP¼Ò’ÔìåÜMùwˆJ¤‚Xjäûþ-÷ï'ï °Â‡‚3Ò¿¿ß®æo!,âßOÏè½Ãcýn}÷. ±ËÞb‹ÿìAw<æg³t2ÄTÜbDÜUÉÙÃß>ÝÕË÷ vò턤ŸÏZz¬Í6ÿãáOZq»ôŸ³ö Hp+c‹íŽÛ ú;\xŸ’–“(ª§d]=<×I ’8'p9ÇqSëR•æÎšeéu܃‚•”j;§½K· Õ„!„Öûú1±ê9½¤qw‰U?ȉ´§µ›^õg*w}WoöëïAMõ6­:¥ðèFÌ6µ™)2|ºŠVqj&' ¸Ì‘°Ç€úaµÛ'Vþ°)I0B\Øxë$íª |yEjw½IÒîÑCª€®”r-Ä|Aé,K®/ÿ„ÄbBÞ·R3åÊrç$¥‡Kþa¢šˆ'Ì–ÄÝ%©W( ° Ô»Jó¸M©öãžÈÏr lìÏ4meO á6è¡åŽ£=Ü1Þ5‹®Ó¸lA{ˆv´iÄ­;rC:”è윅7?én³l凘½þÜéÔ° Íú>jGÑ a©LË"ëÉÙib[• £—žj~‰a¼PFxÆ,™R’fe„hVF¨4ÄíB̵s'Øb¡§FÉš“jƒ&ÇÍȵ P!gI‹I*p ŽRkb’ÉšB§Ñ”f%™ÑdPKX¤q‚ÈÙ…Yä™@©65Õ† LÍ \ù°‚O&I%ÌL2étPîp›¿h½‹²A-š3§!j扩4Ž'!,ªa;/Ïd±<ÓIrÇòÌy ¹Í3)kÛdœß(…>½X/×)Ï<À¦×ª‰<“î噋2·6Ïà²u¨‰<“ò¦fÅmžG]¥¥Ä‡<“íä™,Å¥5yæ š]È3oææ™}Í^Ê3S[Aš<“ø„›ŒVKÜÜ…Ë3™Â¶Ï`fä™S°l˜gvQgæol:Ï$äìç™l®A´yfLN6/ϼ!òÌ$›•gÎiÇ<å™q Ü®Û1Oyf·“g.l‘kóÌ.[gR玬aè9i楰/žfV7ÒL¶•`š™r²yJ3Ï`£4s—´ÉY‹7}Á{éeJÛDCe˜Ž›w€ë% ¤ Ÿ'ålÇφn׸áVñ65 9¶’œP—ç£HÏa½_[3š²y­l°;âè¤|" ÈâZÝ'glÂqÁn\Öô„ â›@¡Fb±™™0ý JqØ]šbÁ² I!›˜¬yø\e›çÇ.Uü‰ø¹átí`ªÄ07–R7ýé1PvÈx»õq;“š_l“vj‘3G-Û _ŒŽ› ,å`º [´I¶ÞÐyìmn¼sÝa„~¤lÛÆúõöq½¿Ð©OÖ}8¯ðíjs?/ŽÍ³°ÊÄg×[ƤS<Çö-êawç8$”!›;R"I±ÈmÖ¸átAý ôŬžÿñ”Áò}P°å#èÿ˜åÇ cšNètFÝ9ªT%›‘=„RóN;z W8íÖC¨¨&O;Öw‹ÂEÖ;è=`n¸È¦O#z˜Äi›NµñâXR¶À*ˆÓˆ#(»x1gÿm¿™AÞ»F¤„5ÈJUÂS°Ÿ’¢ˆB…Õ2ÊæFa¨²ò¤¶¨iˆ<  «¯'+‘’%Vk°EËV’ÒñófýãsýðKR ƒ§Ê©6#Jèie=i$—iõêöCblr[ v~l2®aîÁà YV®ÖV±p&œóÌuñx ÙWVÜPøi­ Š 1ÁŒ¡²Ïžwõ]" K½¦Åe—[tæ´áÔGé`¿®ó¶ÀU U»ºOd@˜ÃÜ=B¹³o“ÚŒ¤t»zxHLÞŽ‘¡…ÄÝC‚ó´$êzóþiûØŒ J$\‹¦=„o[×~xzNí»4ÈÖ·ûõ§:Éj¥ôx¶·Ú۹ǡv%N²”»Ú®ëÝb­{”°Øì‘ d£ü»ÕÏëoþ4³Áw<èLqiTû°áöü"I5í Éu%'_àpjܾAÒr42>ßÚ9áÍ:6kAYÖ¹ÙÄ-4ûàÝt’¶ÙÏ%" ΰ‰Å©ÑCŽáÆý¶‰dÞ]šß@ž aM«¾èmÜr,,%¯û˜¦Û1äžV9‡h”°Y‡hØôUµŽå úêãÇíÓϋ缰ói’‚¯¨;ð%úO*®0P Ÿf­Àqú$!ÂÐÃŽ¸]Ý'r¶°ÇFH;ÛpG­=¸º¥¥´È&B¢³”ŽBÝÕ·O›»]ZQwG%(SKLP¥ÀdGÑjØ'&QÒ6™ÀE¿S'š„*MÚ…Ú ‹³< ¼§¾Ü¾þ˜8± <„ ‘Ê lºšHÔTÚZëÍ\hêoÅXkX; ñ8¥Ù £[TŒS9 XzÞ›ÑOXqìc  ·“tŒ £ ¶ÅÆZi¥sØæ q“—1ÎÖ²7¸Çð!­1›YŒ¦Œ-q&ú3#eiËÜCÚ+›ùW”©­¶ûõíóÃj›TÔı´:ŽÎ:Ÿž›ÇÔ2jmÏiß6¸Ç™ÓB,œÂG¶ùàYy(RI]>NãÕ $ì§õ]F‹¬CW,¡gbÐ)`I°ž¤z*ejFDÇ"øEëÐ9pc±%Ù߸—Wq+#´žXŠôŽ;oÈO™¸“JÔQ ušsS–K)®ßçœ×4íUÆÜäTÑYoÙ¹€²ÆaÑ÷ì’4 & ñîøÃ*mÄÑ—j„Ê2˜f7¢ví¥ÚÄ £™Œ/©÷Om€Âæ?ñ½Î´—…­ÇÈ ’R쬂’,Gгˆ°¨\‚׌xWï_ÎÇe#À®´Gá›û]’G°C(ŽÛ+:²Ù:ððêNÊ1hãV?')ÏAᓱ¸¤õ.I«ø•“®>O¸YÿŠ@í×FÙR=LqFØ#‰OÒ/&z^ B¿Ýì>&iX–ã­$tQß:j§æãN¬5å¹´”žÁÎXʆ8Ô@Dwe©vÖõÆsk<%é¶NóŽÙ”nW»Ýóc}—´‚Þv¡ÊÛ^Ÿ’ ÌBDgý“-©‘Ózu˜Ž)4°ŸÊ"…:£ëcóVl¾ s‰(î×Û§$ƒÅœ4tuÀFã3fº„Ñõ°+8 åýrN¬Àâ—Üê ¯‡ÂŽB6OX¼ü=(—–}v¿}zþØ4¤þ>EM‰FjÖ×hüöáy·þT¿k3ýF?F¬ijƒ'“à<[*ÿñSB®-F=Ö_Îúˆ/Éú¨Kb¾X‰©ýQÔÌÚG•;É•Æ+cu’¹AŒ£4^:†dŸý’ai!àÕÊ]ê}Ž)Z'ˆ­5¶èèËÂÿG´TïèQ7tž‹(l\â¨oq.)4…—QG´E…Ánfªã*Môþ)¸ôæÆ9ßÞ^=ùÆ´R;ÏbùRî…ï<«§]¾ÚÜ?ÔïÀql›ËwiÇ?~­~¦hðÞeçÚ±=‡4;A›¦Ãª÷—Z{ølZt°pÔÉd3E8¶ï £&ÞÉó½;{lVV'ôqy¦ý®dX;ã ‚àýáàlFrriÜo*O½ÁtcHÌþg³ X$|¯ƒƒ-ÿºx‹“9óى‰~j3ÕïH dßO›»$:–„$5óñœ±äÏÛÜv,Œ§Ì¶{£ªØ…*'ì?GC|7w†à xª_0Æ5³3 ÅÜoëz*Zž¡ˆÃC”ô¯³Tsòjxu¶‘ñ›.^äX޲xËcû„ñ`Æ<ÃÁÑÈ›#^à§õTׯ ý°KGêg…Ÿ7G9ZVͼkB;?­÷–î·çqwZŽþ¾+ûT¿Ó1,K$FºÄ$‡z9žãRO†«5XײŽ×ŸI¤è»çǬYŸ -ú’‰3„‡àG¢çn6•ƒˆœTû§OªO©@d¹ ­ Ôž’}ZíÓ‘§6ØŽúÐ3—Z–%µ«@ÁÃÔhêí䀗¼†¤ØuÄþ ܇Ñ×^Qo—qàŒ Ü8º¯Wlìë†B%=¿,òá%Nò ô÷I/ÌF –‡Ìùˆ9sÚÇYÞl¾ Í\¸ñX¢ ìmÚ° `„øûù©‹º)ÕÄaú(f ½ ²‡"éž].AÏHÒLÅmÐ7™š¡r44zE¢÷o-d‹·‡Pq绊a™»f§=ÂT8&Q/ÔÜaGo:?sÜ$„yæüQÙIНÄñ"ž6›IŽà‚$!lìÔ4ÇU"¡-ÈÍçxΈB±M¶"%¿_g©Å®Š%À³b-…]šÒIe-XgRŠþœ µ"góÀZ¨Ð!ò€fóxµy`ÒäaÒçnö0¾˜@_oîÖY›VXƒÁ³ç9kûÀ›{qŽz\úÕCÎîapF¹Ÿ´šœ zIWé>›In™±{@Øû6­— ™ËÅ Ä©I/oŸ¡ç¸SŠtSns W°’hÿõ¢È–Q‰óñfo•n²ö )¦¢x–îâ)ºhê2qÙ?eéÅ[®ÑZâØÍÅœr•Àɤ^–Å`ýÃ! ™’¢/ùäña¹D³µ&šFc¶°ˆxñ{دdhá—Ð9g|q‡ÌdKoëÛz—÷Ññ¾ž³øCílö_fÕe¤€]ESoµ0TÀ)vVå_몹¼†ÐK^O›A”¤Ï-ãòš´Èz³«È+MXS8Qÿ*Ú1Ók#®b2Æ(.ëŒPI¡§èjÅ”91Ê7×áõ/Wº0’{å)ôÇzµùþs¾Äb†MC'›µ`9£Õðïêí¢XkØü¥4bõ~tÅÓåŒD7þࣣ؋òó´M+K\+Ó³°g(ŸqÁ×»,¥àX¥”CE$Y+gU)B+Ÿ«¤3³¹&R¸¸ØõæEŽN4^ZTQàÇ%šª-—*)S5m/¶¬H ¥§Ì±¢y•¥H°Œ× ÈnxŽjŒ€zÑ>οmÂÿ\VÕ‰·`ZøÕ¯Ô‚y~V¬óÀÚÏn¿<>äí—=ù¯Ð~ÙÃ/Ý~i‘Õ}…öKÃՂϹègaŽû– þûíÓc^‚ŽC*¥›Ìj•ðu=©œæîùØið‚ÎTtÔθÑ#XK9Ù­“ް:%Zí±ŠþÓ žÃddsO¡š¸’³qL㟷ÎÊp$±0äÇý8ƒP7ã ¬jº!ˆï›Ô<Ú9–0^s£Ií¯79Ç'ǃQиð®Î9ÓV¼-:à,¯yté·Òã‘Ù¸çébzu1ÚoÓ«8þ!¿J÷Ûüê^6Þo¬¸à—2¬‹zi3¬8üz——S¬¸^î×YÓæXqɳÂýS’ÇÆ,+'¬m³¬¸Znƒ£€¿M³ƒ!ó,6[þ6Ï=¥šû0Ñb‰æ><Ö&3­)só[ç¤qÇTkÎæåZàÙ)×êÂ’­û™lÅUÓ϶Øò/{ʶNølfº•¶axðÏè–µD¶Õ<ŠÉÖn¿Ý7•ë%oEd\wšH¸Ø’\î˜puÏ—˜ÌÈ·&áÙ)ߊ þy‘¨§K=Ý^¿<ì]£ÊOèlÛmQÚ"›ÛP‰7X½ß×Y!¿Ö•»@á7|·œœl' íàÙ¢qé3ŽR*Ã-)|n6¤üK¡ãFœsÄd,÷žTÌDƲ O«µƒO¶x“/ö—@Â2Dg‹"RÎA â(Ñï²Z|›èBr¼—°°4B”ä2´ølÙí¢KÐ’;°(á[²[N%õõeóš·‘în%þ‡¥ÕÍq•òè½–Æåð]£dc]eRúiÝtaóä ¼„Ã-;Vï„(YÝ7Ö·"¥Ò ©°ê¿]1&Æ@6è¹LºöËàºp“‰2`S¸Þà…OÖNpGÅÄÑóº»=ÄW8%®–|&]Ó,á(Ùó˜t a[úW`ҵͪ„Ê^ä7ålýö¿MSŽƒ '´e bkK0>ííÊøÆ“‚5ö¨”e *ììáˆ]ÚXÃ¥–øjsŸÇðÀʬ'´òœÉlzB¥—A$ëú“øÃyHyü@m`Oò–%}Ô8'n–kAi&zÔ±ä$¥‚ÔJ¹1:Ë&6•$ÂuÔb”ㆴõæqI¡%vÂ$³,nàéx \¤±yz¹PhÁ6>éÄäÅR,…ü¾ØwÐYaj åààBþ\j N²ÚSð™Ô@ˆ‘YýôÁ¹v¼r¤ì›<ÅË•RøÏû¬Îv‡7²’zés±’ªOªÑO¿­â”6?]ÒˆÈX:Ù«ÓØ^ p qáó¼$Þ£-¹šž²öã`Kk¥aÏ>ÒUÍ}1„à3$©Ò„óÔ üSN%óR¥”:¯×:wéš]ÉëˆÑ£•Dc’QüUák}H„8£÷6݇§ç‡»¼4Rr…Áu\üúÇçÕCþL–ú¯8“Ã)e–Ý@9oP ºEw¥=²ÍLø²®…qBRÁwP”^6uî0c%ùÏû¼!`š{,ÆÁ„ö¬8Ä73äÕ¼~Ÿ[õÁÒ“‡XÁ½W¤É ¡=ëÌq¡,¥$´¯òB0m'¿mÞìÁŠË@ÚNV™ÏhÓœ¯ÊÉ.ó!í|JîôšðvN`#í¼D%/®•%¦Îáñ)x…(í<ÓÿúJMÀçÃëœC‹žÕN7RŒÇÑyÂ–Ç :à‰Ñqañ¼‰çCøYÄó‹Áç‘xN€·Äóœ³à#ñüø„«ω7(B<'° Ï%¥—2ÄsBðBÄsJ-‰çWÑNK<¿†É´Äs»ñ¼ˆbâg\¡ýmNÈUCE(Í<‡X}]÷ýJ1ϬfCAçÏ]s?_O)¥ˆçx½ÞÑм ñÜï§À òαÖiÄõˆçGüë0Ï ð"ÔsB1¥¸ç„èeÈçxö9¡˜"ôsBðBüs}a^AÐ)ƒ)Ç@Ÿ2÷\ :]ŠƒN(§ ½ ½_ž†N¨¦½'þ fK¡+œ¶«¸ª.§‘%ˆèÇgDôÙz6½÷Be‰è=ù¯@Dïá—&¢c£š7ŠeÑ—Ö·è× [7Azüˆ’dk¡¹4ÔKd² °X®Œ£Ð3‹dH먤¢>ï.ë Ì…@I^†k­=ÔçÍåZë€>HQïǵÆb¼«HÃÉãZãh2¼î ~%®5–gÔø>Îb\k¿ ×ú~®5!x)®5_†kMè¥ ×š¼ךÀ.ĵ&ÔRˆkML9®õø å¸Ö‰æ>—k=iî¹\ë!xa®u¾<ךPM1®õÿWàZk%¸¸PS-E¶>>k̶>^Õº µm˜M´ê¿Ì…l‚ÍMT47Íé´9µŠß>ÝÕÉë6•`”ÜŸ/Q ƶù;‡?Áb‚•,)¥üsÖ;­õø§öϧd)7ý,ÅyËbàËœ'c²nâЫ,•X½J*YXÖgU‡úq¹­°ULKMè$zƒ"[6=ÌË1x³Þ­öY}¡x¿¡–Ž}½¯³.ÒHÖ¢Àó®a2wa„ÍÒ;ûZ±þé)ÁïêÍþ f%Ó<u3e’,ƒ+"ñ´Á%æ5ó!§Ìj{“²–.÷cR4½–òî‚Eœô„VV?g)ň9(Á3ïAGÌtë5Ù³ÊsiK“,‚‹hÁGõ2Žòz` Ÿµ„”u;ì½d¶ ;d+JðŸ>¬o?äñr W4þ‘˜Õ®€ @,HÄÕ³Úæqs –ù,%ÿuœ¾¸àRnˆpk"ôs®õñÜqûÂiJIß>?ì×ò()Æ4ŒCâM"NmÑ`HX_alFlŽW»ÌIÁkÂ$%ùãê—Ä=W•šì­[N½€ÀF‡6KžqCõÌcç#ñ™ezlšGÖ$ž[¦¯¯ÂIC£2}&AM+Ù áó:•ã¢" 'ûŠ&ÈrL¥(Íd]Ñ;–­Ÿ4^‘àƒb[~Y^!H,žå´n«„þßæÎÑØoø#à{)OÊoš’ñžeN;èœÛ|š·«›%We^ôXqÅÇþø„Tç¼9ò{q’ž]&OÎïoDŠ(¦cùM7ãt}ìr‹;<©’”~k,ƒ`$´&Uó¡NŸ‚ü"¬G‚¿úÛëïòFª!hð·«¼Ës5n‚žÔÌýSÞˆ—)mõ<ç„§­Fc#¾òsú[2*Ä'׀døªý-¡}Ö¨¿ån½ûø°ºmæâ¤Mȉ·ºôÞ­l«KïU®ÐêÒÃ/Ýê¢ Y’"ou±Ü«|ì蘒lÙ,'Íè,ŠÛ­âU²!#oÐLÍ)nJ°Êà)øÞP–F"ñ•èÀ³\šr·ÕÅh® „Ï&úIÕ´ùQÖÆù‹;ëgtëÂ]ë‰ÖzKtÎ…ó˜ñ’k+S ›‹„b×ëÇz¿]ÐMâ.¹²¢S@ŸŒ)ˆ[¤‘C@—Ðî¬ä¸çG@×,¢Ý¡øø€0¸¼î,ì„#ݰœ)ƒÓ ¡há÷ÒÇxc×EÓ$u†¾L@Ê$†ÄËœh5XtNçÉp•€ÔOÔ‰Û±EGÏÔÙÄ'²E/<¨ƒ,«)ѳuBTª$…ž7¨‹dgÉËê„Á(ò£f ê” =ô¡—­¸SV¸¥UÑ™–8øµñ‚ìßΙŠ=šzÉÌÑ–­«ÃÁbáU£m£Ê8øjsßL Ì1Ñ·ñíØì” òdõyçÐX‘‘ÚOi?«‹Ýð %¥œ¼“hŸ y+%z^èŠ5fSIÒpòæÚùŠËÊPjÉ÷\ÓÞOˆ^o²êƒ8Ä×y;mé1ýáfíë(¦œéHÅôf\¦hÆb×§¦àÛ!—6ðT}T º4äòò q 6ZøÒq6p«,…¾Ê2Œc·ÅܯóF‹âüLA þ)ïtRðP) »Î«¶CvÝ´„VŽó²Ž'q^˜¤¤·3HÒ`ë&Àsw&‹NRPºiæ…åhÆ«¦¯Ÿ²™u–fBÕL¼!À›QdYͪ¹ rÊlòܰìz±²³KpÖ­ &v‰SðHÝdÍ®jÇ‘Q²OŸ±™ãÈô% ô<¥_}iÙ¬[‘U‹~…á÷UE¢ç¥Õ°å9Eêe•ÒëÍúd±¢geÕ8ß]Ø>ôÔ4²òIçɨ6’Œ®šIšIÖ v3ÉŽðËf’]¾hû0“Œog’e5f’Ú)6“Œxƒ3É…]d&¡—23ÉÁ Í$£ÔRp&ÙU´s˜I&¯b2íL2»ÀL2]F)ñyd63ÿ¡+TðÀÛ…ÐÊQx(® Œ,º/Yj(™…XÔK ;s*™« ù2}­”šJÖ\Ö1øòå‚–Ö®ðj°1Á´àX2©aŸQWšJÖÂ_g(Y»ÈL²¸VJ$‹ ^f"Y»Ä@2Mh¥È<²¸Ø…Æ‘ÅÁr°¨id„©”F6aæ¹³ÈâÐ¥F‘Å5SfY\òRƒÈºèåçÅõRl YWøY3Xz—¦Tška‡ ®Ò¥y~ÖD—ævµ¹¯ó;4ϺF‡fï5®Ð¡ÙÃ/Ý¡)¥„o"®0ŒÌá¾x@eÓÍ7ÍÊÖ%wVSøï·Oy='Á4×ÊÉ=í„·„ðy‡ Ö‘v;.ë€[Ô¥—›°¬/pa¾Üev¥‡èD‘†“y+\ܸp%»L—[OÊNsû–݇¨-hhlA…¦À!É©"í3s\sc4 þ¸~x™u#bë2…h }Ï‹{W§&ÁItVWšGâ—™w¿Ê$8BðR“àø2“པ˜§)É‹L‚#° M‚#ÔRhe0å&ÁŸPn\¢¹Ï7ià†à…'ÁõàËO‚#TSlÜÿW˜'‚àðç_a\hŸÅ¦³:ú¤ùùÑ1µë½Ü0µc‰Yã!µë½Ë¢ÔnºO¸Mí(Ñ?/Qjxk—Ó±nÿœÜè@¾;‚³Ùä»ESËä;âb]m‹¦–ÈwCt¶|G2U|(á{令ÁeòÝ,ݰå# ä»3:ËM`ºÔ¾#ùŽR͉|—ÁÑjÉwãg°DòÝ͈|LjX’1’|')ýŒ’#–B¾#Ì>…|MR½¦ä½)âÕ,^c;ê†:±ï²¨F ûîø–J¿›š#=%ÿ¥æ6“GÀxYÍx„rf3ð⃠ ¼žì ÏÜË\f-ø?ˆxË"$'‹Ýà”w)À^ÇXŒ\„ë¨ÅXÑ\WË%àå«êq5õEï·«—E|ŒÀæïøqfއ1D}¶…/N/t¢µÇ¥Ïžó)`))R7òB3dZJ3yuŒ*p¯,%ø&óÂzœO*)ðŸóhÌJr‡u͸V²‰bX›÷†ü¤Ûú!Nr˜_Þñ€µH–Êæê`ãHFÈž5  ÞR’52`rÉ(dQqoŜ͘½yñ¸^â#äytI×K¨YÄÁ?åÍU‡L>®”z“7‚€@ºÅÙ«ˆMe¤µô3–ÚÆ x´vÔÆ°ûðôü7ÚÂŽ*|çý…ô#²]“W™£Àh ‹þ+&®Ç Žg˶Ĺ“Upg¬”Y:ŒÍ Þ¡à7Yaš2¸+ÊœE7®œHDCHOHNãço,•ƒŒÄEÀ.ãçO­°Œü¬uα&SÖ“_u½¹Ë»ÎFr]5t¤ë¬³2£y’üÓúî‚«¸xZ[:Æ;Sf“5S[Xˆwº/ÀrÉå§‘Ú¸õš@Ê~±¸x9gó<®&«.ŠÜ?t’„+XåMFÆBgH_ð"K)ÍÍŠvÀu‘q0°‰8­MñmЇ½ìØä­9AaçÞ=ÐŒƒÑRL£3@8¢t_òÙÄø2UÒö»ãto̵˜ñGøë0ã ð‚ÌxB;…˜ñ†zƒ"Ìx»3žÐK f¼¢/ÄŒ§ÔRí´Ìøk˜LËŒ'°‹0ã‹(%~°f<¨Ýþ–§ôû̽h%)ÌÇFóú¯YŒÎÂ) ;—¯¸ ¶¯•ÂÜøžàÅâ´ãÞŽ¯"(ÈWð_+o®FŽ?â_‡O€¡ÇŠ)Å'D/C'ÀË0ä šȂâÈè §ðQ$yÊ`ʱä§Ì=—&O`—âÉÊ)C”'d/Å”ïÁ—§Êª)Æ•ï‰?ƒVÁæ< ÔL8ü¥Ã•ÐMª-<<}‚s~—¿ü‘ˆº_ endstream endobj 122 0 obj 11647 endobj 123 0 obj << /ProcSet [ /PDF /Text ] /Font << /F4.0 9 0 R /F2.0 10 0 R /F6.0 11 0 R /F5.0 12 0 R /F8.0 13 0 R /F8.1 86 0 R /F7.0 14 0 R /F9.0 78 0 R /F9.1 15 0 R /F10.0 16 0 R /F1.0 18 0 R >> >> endobj 124 0 obj 66 endobj 125 0 obj << /Length 124 0 R /Filter /FlateDecode >> stream xÚ+TT(T06׳P04×3T056Ó3Q07 ¥*„+ä¥ ô, @H#”&ç*è»åšq¹ä Roþ endstream endobj 126 0 obj << /Type /Page /Parent 105 0 R /Resources 127 0 R /Contents 125 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 27.36 0 612 792 ] >> endobj 127 0 obj << /ProcSet [ /PDF ] /XObject << /Fm16 128 0 R >> >> endobj 128 0 obj << /Length 129 0 R /Type /XObject /Subtype /Form /FormType 1 /BBox [ 0 0 595.276 841.89 ] /Resources 130 0 R /Filter /FlateDecode >> stream xÚÅ}k“#Çà÷ü¼o#‡œ—ïÇ}ÓÚV„>Ø–gc7âìPPÝ w»Ùã&g,ݯ? XEVVê…ê9o¬Õ¶YH$‰ÄÿÜýu÷ÏÝ¿½ße™ƒÝ)ø¿ë_.Ikó.æ U0»÷Ï»ÿù½–j§wï?ìÞýñ‡ï¿ÿñ/ßìÞÿ×îOï…’6§Ý¿® è] Òûúáÿ{©sÊÑïžwFÂ_÷ÿâi÷7ñ×!$R–Þ»6ïþö‡ïšu[ëi¥‰bþz»Áõ´QÒø,Ú ~÷Ÿ?ü­YpࢌV—„2R‰+¡œû6&i²)ö÷ÇûïEï÷ÉK•bñûïÆàg-utÅvÞþ>À¡ûAøbà÷VÁït.ñÿáïøßZ¥ÞuAÊU~üáOcTö.Jo+‰;>?ôyÂû$u‹Z¦S(=ƒ-|@:†ããó/ß߈ø–'%ÅÜ%Tý×õÂ#Á§Á…+#¹Ûz<~øðzúéü°?ý´ÿõØ…$®‹#$m3lɵ!½;ÃêçOOû‡Ãóátùé|Ù¿^Z ¢Ì±Â¥úù&ÚsÃäïïzîn:i0\ûKÿÒÚø²¿Ÿ[•dIR.º 3Â!¼ @è+«<ŒQ^7Æ_Td9ž~é®#îŸå$£*¿úôr>^Ž/§ì´µÒ*+ÚŸ}xyû8Þi],tùˆâï¥ö%fz¡P6ÄrÿŸG8¥pxC-Ã?ñ:\¿Äczy“,:I¯ËÅŽ§1Qg€Î¾<ÏçãÓÓñùpy=œÛR52®bÞë_ 'xL|½zÿññðzè²k> Àw!Ñþæô2ò0¨M>‹|iN÷÷I!c»â÷û§Ïƒ8‰ë_p•TP¡ø¤ qw ­”tþöAu,¿G?ðÀË›hÿ^´Ÿ¥* {8};¶€AT"tù8vÚ€3åž÷çóçç?Š¡¯óSßÇý÷BÃÃàgE³@Ô2SÞ?ïF ­Œ¹<íóaQðºøýß­qcKGùÚ ¢ºÉJøkìël¥6©}2… µÆË‘Ï…WÍ$¬žªZçù?§êüþ³·+Ÿ½]t˜×U¤zêvOÝís|êª-áß}¦”ÌðÏÖWÔ'º_Zð¤Ú_Þ¸‡—ÇùªÞ^7bÕöë–@†jÙê/Ÿ$¼Ú­mþnÆchµt9Ï{ ³Éå_Ft8¸!Wü¾s‰ºK€Na]¶Í'•4xù0öÌ(#£‹Å—m(õwgŠO÷—ýØ3”;´:^Ff¬—Zˆw‡ç±‚‚}”HõË–Š¡#òä;£­à ¢ÝÒ^â½ëc>¦gãdºŸäô±àå7FÓØõßr¿,÷ƒWtäTL4Ò¤òìÇõ%øµTÊÇò¯Ç‡3® pM}©†Ô˜ÖÉ ­ñìï_œ—Ëqdqô ZÜ?9ýre{¸[`–´±º*/”⶯ö¶ýÁχ%¶u}µ3p‹·T?9ÊiþéÛÛùóç§ËñÓÓa”ÉP^ø’Ò#âÈXЦ Áá<²ƒûQŹ<ïµÚáôÍâJ³QK݃”pÁF§a1P|š¡÷ Ðʳråã—”UÝ•ÛâÝyÿ|˜à1‡¶Bk‘/c }êkë÷û1ø ‰x|ꮿ¯è;þ:hÐ8¢)1j‹¡Î;¬-j"ÅÏ)cYG\F¡=gK@÷GYŽÅh'µ+>…WvÜ ² lhm­OŽ—Ñ×Ãx|nJ~€5FîXLÊÏ8«æî€¨­tîÖï?½O—ÑgŒY”RÅN./¤e__Pd0¦<.A×0›éƒ.ݽmÇqÜñmûÛÎÃÕá1´ÀÁ@nÿ¾ð{ö·©AL$•Äà>-éQoÓG´¹°íóäaxcl‰èÃþ2¦ïT”ÀhòËËë€ÈwÞ2¹’|sŒ„Èþ(:´ „»¯áÐ6ò»‡gQzuAˆ+íº¼Þ÷>ƒLµ•ÿ~™°­ÚÝÿ Pw¿Æµü Ø >RAf¡@ÁóÞúÈ È: :¯›Å,wõbmq ê|B #Öf§­ì*tšÏ8h‰A¿Q„Ç“¤×÷?~÷ç?µðsbúe À: :·d¸¨Î¡e,9_°¶ÀŠWNôá^… îó|ÀÅsªdm‚|‡*†ÑÕ” hKÒÒ¶#—L– ·A b„ŧàz­*6p%(烬ü™ø“Ø?Åô=®í f°¸]‡cˆŠé½§²7Rˆ^¯XÁ¯F£)J¢ÞWOŠ{ Œ…WF¸ýn,’ƃ|Æeîãáüðz¼«åKh‘}å‚ëÂC·a·PÒˆ`Ñ~ê"üzxÚcàüñøé¼Š"è‘ÕžåAøw}¸*fá¬5Ø.†ú #ŸŸö¯«xNûŠK¼/—«ˆ¬}–•ܦ2˜6+Ån U@pî]{]&usõ9@Q»¹+F9¸«?5šήËÀ˜{™{¡‚×EÑ…»ä2ù°A‰ÊV÷ñm྾|þô÷wç¿ó¿f1q?V$ªZmè®õb><}>¿~ªÖ™ÅÉC+xJ˜uÑôôÕZ]½Â_C æ<1èz†æôyŠÑó¤à繄ýnçÙ[ó߯b¾d@à'°†‘=¬"lòT‘ømë´˜Ä7g™B‡DHþÊ¥näaq0ª š†+‹UÿþÓÝ^n¯fµ’Ù;ѳ}0zÒú„íÓ²œ¼5}eÊòºnUç¾ôŒþ`ºDÉTôúÇ‚ ê}tðç<ù>.âZâ}¼.5ð>Ž©C«2ï¢ØÎè)æ>`MbFÚß|€íČկ£ ð^ò:ŠNjÇ®Ní `ÿnPoyÝî±JçºÎ»÷+$ô®ˆ…ÿƒ†9½NœÇöÏkÎ%0/3M +r&êÀ+Æ£ÎÐ/VKèvTŒÐá)ÜÛ,ó4æî›—Ò& |;Û¥°÷æ>^ÎÉt ¼èú¼WG´#•@~œ2“è®Újšð¬§ ŸFëàÝ—k(ÙfŽ|ìˆa•h¨=À¹¯¯3VŠí/,y LЕ÷™@ýª;0ôdi´§à—ºÃ Îo„¥Îp|—ñב¦lÄYÅ™7Øê¿îŸƒjÉæGî4:SKTy î×Nfoðb ÆÒjm¨²ì™rÁ¡\0ð=K×Ç쌨)ºtò(V‘&Ex Iì ¯õ,¿æñÔÆÛ ûÚ%>)µÇéøÈa¢kÎÍD§-œ ˜ÏcÓ.*é„Î.å(Ðu tµë¥Ê‹õ ôy‘ÐQÀM¾qR›H¢ýÝûstÀ,`÷‘Ë©¡MmÞ ‹~p”s@g’M&\€“¢&$™PŽ ƒ¯œñ)œ@{Ê¡ä•dµ9°»U3]ëÐý{¾î1»V,·6ëÛêн–픯{™F5l×Þ—¶kOŸŸ>¼®¿Æ&Ç*i»^G,òÿŽ_d«<`¹Ü‚oÉÍËú‹|5m;°»¦íÚ×±9åh¥·I,süNÝdô·£X®¡/²?§îqÔöÈìÊþdÜc,ËUð„az•‘6$ ÷)ûsRÄÁã IöÊþäˆ8¸®&kŠ4lES "‰=“4§I™¦<ÏM×b+‚2µüâ8OáMÇäýq®œ¢ÁÊ>߈6Æaæ"Eš…ë!y’*SVí$]"Y ü¿Žp_O,Ò€’¯c¤hà Ó4>écò·Ë”ÃÆÀoʵ9× ŒLk®—À8ÆIƒäÞfýÚ:é»Õ¢ÝÝ|ËŠ$# Å~Z¾^–pHQ¢§tôgžÌD#þ×aŠ/,¾Wh¡iïV¹ã:õìšxLÐû —P¥2oxÓl™f`7û/`¥hÔ ô^zóáõùx¹91ÿ„º«Î½5D£ž~9¬ð½ÜR¨ ƒõÔ– ûM8,Ö‡–ÀãݱSÀËNö £XDsĹPÂN Å Eƒ Ž:4=¹†ý?X41¹Š vé-Ö¤ÒõˆbÁ¸O‘âÉ!ÊÍ؆=îdäc6BÁ*ÙX%#Ö²ÀaÇÆaж^ª»­ƒÄÍ/¯UåÆOUÆÃXõÍjïi`ÝW«ØÙV‹álHo™åÎ'Ò[n ÅTvËì¨jÃA('ŒÛ:­ƒÍÚSЗòIÏ×X£qu¿m( 3Pœ‹îçÃÃËéñÌI,Âþ–X@LÄ$ç„T½Ö‚Ào+'Û«X(â  .”œ­ú*Èy‡/V¥ÿPî(0:m"¹þ|9|bé6ȤIð¼Œaãh°‰bz®]Xý–¤ ö`‘3 m¢å /â‘f -ˆ^hïüñåó+Õ *í¬kè«ø¬ì“„1ÃHçz¾Ñ1(Ò|z=<ϼdso«Ž¤úÜ4ü˜ªn¸xf>ö Ì$ux/‰Qºj$@†çƒR,·ðZ%ㆬÓmxq6ãóU­Fÿ°øÈsEaYIúkÙîï786éUÏ,¯*‚äg6aïæü`: dé U6ÑÐbmt¹èíÙ3ö_X¼Ic)ØEróš ^喇¾^0™¾Ý8 ô⤅;;¸ ¶¥!ÀsƒËر -\‚å¹Áec¯ñ_{ò ŸÍò&Úª Áò?³òù1¿6h+ìïd×$ôcv šS ïU×2ƒ¹CPåpâPå*$…iì]šW°<“&MV0û×OOLJãåé7Ž5÷Ie°Fîk”ý^^Y^zx›rHÔ¸O ÆVŽ$tv1Z“ RÃߺ´3Âu2äér#œ³‚=ýxúpx}=°²u±WŽu Èóáõ噫>)©0 M  5 ú–›t•QHñM¿8iaš !ú²4œÁ.|6ºêmšÈpŠEÜðgõº›¦­6[ n[`:{½5êØý[«=ú·ØR½†èå­‰-‰²­ Æ–ˆ=,ÓרØR¼[Z5lbKa‡kšØRwšÇ‘“41JÚ˜(‚+MŒ•)ø’&i]ȽGƒm„c‰7[J륦¸dYŽqt‹ÄSl²IN|ø[çÄ[o±IÎdÿ—-Bb÷µ:1±¦Í‚ƒ.õ®WØ6v-õ.îÁ¿>V_›OÄšüŽ£Š7Ìã4(mvë`÷ha CgiS`Òª„oìöÖÚTvÒàÈ,uŽ6…Ö²®½º;Ôl­ÜË”-E®Vò™U‡ úsöš"[W;Ks’á»>·Š{¨†ã»kî‚U#ݯ—Óeޝ,Ê`–VÒüÿ{x}á\& —)8Š4•ÏŽ)ppnJ6þ?|ø–u£pŒ ¥€×Ùeëµ³PE (¾9±èâ¼Ì`•¨ó3ï«"ûšI¹š*ÁJ£ÈÛôeÅã-ŠKžçh&å4U’Á >¯àÛúíºªÕ`êô\u§—SuW,“pF:¾M×–ä„O'W%·‘‚½çpL 7iKQæéóø«:)ÁF3$UöŸ>=±.“v ¬›@ÁGÑ¿pU5ŠÇaÚðdŒFÃÌ‘‡Ê#KÄÉ<$ìÑš¢iªàoë)ª0í¾ªí¬Nê>71cÆvÎ!ÀO„ç½J&S´9³äo5¬¼KGžü­êBHàëf®rÁ º°}) Û°e {®/ÅbÉt5ÿí¦Á¡¯¡™^Î,ÊàÈéLÓg)H-OÀÞWoGü*:¦h3Yõ:-k¬­òXˆ ü|à=M¡¯Dçéy3Ê™d–ž§}’É$ qžž§Aà 8‹(ÀìÁ‘D¹–ÌðÞ&ŒX’È_xº :Ês&¹ñ*ßWÆÈ”h1s<óì%PÃàgêSâ}úq UWê*7Ξñ8EU¤ˆ3^ê3M›Œ0É4ã¥>“¤iž•eˆý¢Âãó§'möŸ¿ÁT%Çs‹=+"µƒÁB¢EÞìXÕŒvÁ‹õ‚ò^ìP©ÑêûÙ¶z !kòp …O, ù¨Ô¨ “edrûðÂ(Ì’³%ø¥!V1óSIšä)štB¬ ©‚m5½Ó=´ÅêÈð=ƒÍIk¬ Ð^’§0<+ݧ$Š*rd.Ÿ9iÚ(Ì9Õ³'Mσ.šÅ]ð35÷©®eÍœb |9wZ¬ÛD3~º^DLŒŸfl§™B•ð؉tl µX}(Í‘c›Í{•«Ž\ôgR×à¹Æuäøÿæt=¡š¢Ìš› ºƒª ¼éAÕ³)SÏ«.«Høiÿëñ|ïË`¨zxµŽSXÄÌ•ñß&X÷s;¬Û¹ƒ½ÔC}mÊﲘÎ]LŸójª–Ê“‚ïUÄì&‰NSÙ«É1Æ>¼õZ]27T=ýò4¨å2ý)§/ÂSlhÞ”Îþº á Àa ïS:'NÀ{X8O¢þÍ,Є²v;è,ßiÊ+1}´è.Êb ºH‡YBš^a9ÎG ‘Â,Æ«IZ‚û'€v›&ŽÃøôò=7Q+±a×÷e?F’>xµè¢§{ ;Ø>x1íÜ.:]àÙ"pÌú£MJHèân?c3É—cn‘i¶÷6€ªC²}]§Åà|œd­,Åùï'П.Xñ2xòdy´¹ÉKï«Ù‘ÛŠ뮞ݺNäÉKÔ,…ÿø;5-/ᑟž·!NŽ Iœ›Â!Ó~)ìyO‰3QƜ߈4ΙjhAšñö²3(ã£4$Ï7= ÉœÖø§XÕ’÷WM¯J¹d]sývk“¹_ùû¯‹“®¡`&l9 þée‰Õî¯îû;p13h2[Ô°ƒ®æˆª÷¹¾‡:¨ÆXjF€?ŽLd™A—ªxæF± ·\´‡ë#2ŒùU2üÀ öáôíYÐLƒU È2šç0M§U£†Ì ³ñíCÛ!–ëÙý;còŠXÉî]e»Þ™ðc÷a‡æ Ü=È0Õ§K3‚ÁÇ‘$–àá°o-~¤âHHÁ¢¤ì½\¢n÷àg-S ¥+ ­¼ ÿXfA>‹ñŽ­2XNlX•LW‹õ|QwÉOÇÓÃëáùpº,Ùá-ioô–ˆÞŒ»·¤ Ú·Øx+o ú6Þc@OI[{K<&5†ôNåã’s¥T9…ƒ¢µƒ ³tRËÅÊu<ÜaèãéX3ÔDP“¹‘°‹8U'‹øFÄñÚJƒö E– €F{´$m@4Œ7¿žaWG¸`šÄŒÓßobYWù$¹ß¯~l$æœËrG¥¼XdÝM[ÕNjIÜ?X”É8¿ÂQÐÏsJ æÙÑ9Š@=OáÒ»2N‡¡61î)3ìGÌ4'€?–Ø=àH~k)ÂTžBɺXØ;=Ø¿çq‡W%%’y>?shã1©:ç7ºUDPg’n|©°èݰ¿ÐUé3$M0 çÐbYzÍ ªà\Ô1_æ¥êtÒ5Vjô´ ÏwV9ÎËU½+$½NK•Aqo|XsP@‹;éE[jéќ͡£¤jX䌞Çr{›Ý¦Tˆ™‚Þhì“q¦4йò6!µ1ƒG‚8P¥c¢ÀU«ÌQWpðÓ 8Ó‹Ó×Wà­·ŽB}ê­ŸVX4P†$üþÂzŽ•ªZ(¿ eœö2õø4š¶Œôʼ Ë8œmž M^@WU”]XT§g]°«èG±Efw$]èðÅ|9\Eò-hžy‚ÞåHÚV Î1#Î9£Ù†ùFyxEhÚLLšh¤|HUk§Ž¿x~l‡ŠÕ±>ü~lgy਎íÀ¿,ñ³õ`×±.l±ÜÙ=H—:¶C >“kÄxl‡^Äv–ÔêØÎø†µ:¶C ޱF䨉íкzÐëØN }q¿Ñ£:¶3‹Ý—ÒæÛ¡`WìÎ!NÛ!ˆ³LHöèRÇvܧb;“¤©c;øNl‡Cš:¶C¦Œí¬¡NÛ)ПÛa„[n ªáÉM§þrIMl§^l7Ûy=_^/•eºdwÃÁboó¦P E'¸SìdÁLï)EÜ)àÏd0ÃäjÎÜá”Ä,–¹á&M.ï¥q¹ÞWr©àŽXbyé½é­Ñ¼øF{eÏHÈ´îj× ïa¶ªH¥dztgX |1D¬±ÐÌhƒ³M˜É±í^›HÔ¹‘#'³ 4Ý\ÀGCñ}åçáYYF ÷=0uHŠ^981£F"ट^);ÌÞjà'®c©€ÑìÚE"yë ]SƒTÙ*oÔ-^žÁ°ÓÖÁ¼P±GŸM²Ö½³+{s^Òº¯ê‡¨síD¢Ö$­»ïw wQ¾€éÑÔÍŽÀGì @ñJáZË*7`àíëW8¬ˆpµxÅz¶î_èˤ²U’²X úYR’ÎdYåj«X†Òq÷™dLnBW¦6©ý5â\é:fº^W µãY§vßx3Lús¾J˜+^cEW 6 âùªÝMZ·»u)”‘&Ûm£xÖ90ÿr|ë8wðU7"úž™Uƒu¢ÃM9BU£b«aäéz˜ù•6Uŧý[¼Wùj!±îd'U$¬Iâpu$Ôc”=ðbN¥Ðô„ŠP•Ã0)#F,ŒølST ­Q“°]©-ø‚™õÒÖ“’‚çɽ•8¨%™Ï4=·u¬ eÒOf³Hþ׉ôc”ÊÚøu"ýõbD¤¿îÆðë*ÐYli«?(?Ý øÖòÇ?º__ÝOUC üÍõ/¸Xp« E”ßqºñÜxÃ'Él\Àc]¨LÞaà_xYæºjxZÃŒzøá4søAvêÜæ\ð†ÑDçÖšbÑ"$H3>Ða^ž¹ $öÕ@V¢9\J|à ðgn¢9:†)ÃvcDx‰ùãD´˜‘iž¼†®ynœÈf#E^MœW×LêJ˜™æXŸÆ/ìjãÓ‚^õF\ãAFæ@ ɱù}ó*(±ðë2ù¤×¤œa:+g2)$·q&cÃ8c-~^Í6NelÀoLR["ÿ×ÇãÃG^Hx úm,GΘ$•Nyö¯<9\·#6ðóY=ç€ïºÑÝÓˆx­U”ÊyŠHþüt9~zZB)ÑOšÁè$# Èž)ÑÜ?1=;tF.X0K…ùóþ7V.!ê–æ V¯”Fô€Åé‚ëu–]ž…6t´(#ðdo‹t'òlc¸ÊŸp11VxNv°d‚Fœx¶»O;Š,箑¼49Ëݲï+œvý´"L[Šê³ *ƒÙ%ÐŒ ¾PýÄ2£#p!w@·†<ôü÷è¬;|ÍY"6$·È¬Ãìf¯|÷œWµmçÖ¹,1”Û>ÓÀšÌ­ ùʤø3K¸aú.FoÀEopæÚô0™« âÕtÞ¯ ”y4µÂu¨³XåÙr&TChkÐÃ]ÐŽ,‘ïB¼:—‰ƒ=± 4"öCOË/4‚ÊÆgX‚`½¡ŸÕ2'õt´j‡Á³²Ö¤Ô€0°&Q,?>]cF¿l´¥°—,Ÿ{ã´V8økú¬ñÈÝWrY_×öX?ÏŸžö‹³H‡ëÒÚ»Ú¶,­½‡7¨Jkƒè8(8™§Ø®Þk¿uQš‹RƒZCƒüJÔrµ×+l_‰áÝäµ ÐçæWb&èŠqz&†X—ì"uÀì¶kXd”µ fÛµ€ók5üùøôt|>\^g^n¹¯&5âzÈà‚…@î΃ãT=yÃ6˜¥€¹ähÁLNoäNòaãa ­1MçÎ ðVªèo1L!©ÁÆ ðgS@µÂÚ7"ŽS8æ7‘ÄaSM];’o˜Ãl¨¦¡¿i0(š5Eö0…$<\ò[LSÈðª+3°Â¶ÓœOU2À[MS ào3Má|ûi â[MS Ào3M¡þ6ÓÌ7™¦@ÀÞhšA–¦)P ³Ý4…þ ÛMSXÉîs§)Œ²;wšBøÆÓ ðÛOS H³Ù4…BH~i èB÷:}i õbbÒ«1o¨Â¼r,9ôÞUXçµ°ŸlsZ,÷pLôÑ+ÆxK¢þÍY•s—È Àà〰Åìž;KüÅ nºÃØÛ¦ó9ú„6C°ÅºÆŒE¬ÊIAz"¾d”UœªPE,ëÇn\Ÿ_ÄÚ<¢N]jB‡ØÞ…›sƒ®5ƒ‹4M¹]¬ªF¶Noß´ÆVýqkð[·­Q2¢/f8{~ –ŽZŠ2[5®…K™Lía‹«Ø2» ~£«±ŠŽ¸·üy’7_ÔIcµÌ{f;+ÔY¼#ùó3/¡î:ðàmø¿¹»êZ÷¹õpÑ,5Þ®+t±Ä›Ì€±²£0Ÿl3g²¨B7ê0üe‰©Ý)c§õ’*ÓEª#oX3ü »1±ºqÊ="ܰ“ÍVFcw+¶¶Qw°†llðØxB•áZîqóWd¿8.Ä€ÃBbÒÍ oá¤Î˜!S{`zbm³rpf£ìç(Ò0Ë ¦Sòd™œCÇŽ%Áóƒ ¬@V„á`àØìD)wB†Iqœ9“šP˜¾ a¼¨4¯OŦk/bÕŠßÄXšQ–Ö“²fªyÊIîl¹qÔ›(ŽZ&å7/÷¢Ñ4àÅÜæó]à þ À'·hBf³ ÉþW šX޳øu‚&õb3‚&­æ›ì¨‰:õçn5©A¿YÔ„B}“¨‰5 ¸-oìDkâ&5ô7œ;àF êØIº`Œµj»J¯Ñùåi׃ñ“Y´kì$Œ Ü¡ ®Ôε¯c(îÛzÎÈ^5<²]>ÔÜ/eÊ»µaAß/ £ Cïød–ÖUÕQ”lÁ9Ü;Yê Ê0â3c(sòû0†2¼Hå›áä÷Õ!”+t±(#zÒyRGP†1  ˆ¥}!1€2|Âï™!Ð:~Bœðçg^=á5|ò&|ßÜXú˜Õ[3~ÕË9ö /2ÉbBUur&`—ѱ&òé¥6ºŸÑ¯¸Ñ¡Äµ"¿#·´Q_>Ù §~½üôÔ7@»ÍÿÇàI!ªy“ùØðÿRi·j“ÛtØ÷€òQÉÆö›m¢èýæ“äuÕmœ€¾E]ìS¯ðA"¬‹×!Q{`‰Àòa‚ú«}þøGŠ6ìú©ìd&9‡Wá4²FÃlí²%™†[áAÝH³=eš¾EoCš›<Vª¼y…GÝ¿†þuüÁĺ8N¿ ¾ ð_Po'Fšàл²X,bü.t1§ þ¤Í_7Á'PŸÙ=[Œ7Á§¨Î3øë&øwàbAüiƒÿÚŸ@}Ï‹7Mð èu|–‚um‚OHƒÉ&ø3U,hgãWW\¶Y}ëÚYà.§roÖÎZW•ùà™­ðAHë¤)Ê0[á{x{¡0ß®¾qZê˜Þ¬~þ†­ð à›´ÂïÂÞ¸>ú6­ð à۴¿ß¾>øF­ð èµÂ¯¡¿a+üYì¾rè={«Vøq¶i…Oà¾U+üüö­ð ÒlÖ ¿@ÿë´2Vƒ"”&S¡Ym…p¾§NÍZÝíÕZЭ…»~±§m{á[غ~|ë^øQ6é…oôu˜ûÖ½ð±;[¢ 3›áƒ²v½}/|=†9·¾‘N“Àù½ðáÒ&G‘†ß ?ɈªÉ0öü^ø¹RÂ)ðÌ^øIº;î›çb[i2:6Ão:Ö3G}fçzËl2㽜Uü‚âMÞ¨OwHÎ/ó0Öô%Ä@}0-ø‚k@·='!Vó& ìù=Èa¬ˆ6·u$Ýb»[cðoQ¼ö–AÉ3¼vM™GÝ™ Î+³Ú R”™ìž>¯¶ÔäÁÝÓYÕ¦®Ê±é.#VwOï»U¦ÊÓ"Y”a%:GÌœÜg€‰ÄÏížNN´m8“¨ÿ|àN´Hi÷leÑ9Jc¶îÛg˜¦ö}ó˜.æ ú™;Ø"âªL‘†WŠ›\5ú‡@}i=E?:÷UY <§×i<Ò’(cžòYΧ4¢îCò‘äù˜ƒ´> >> endobj 131 0 obj 1635 endobj 132 0 obj 19248 endobj 133 0 obj 540 endobj 134 0 obj << /Length 135 0 R /Length1 131 0 R /Length2 132 0 R /Length3 133 0 R /Filter /FlateDecode >> stream xÚ¬·ctfm´%ÛN*xc۬ضmÛ¶mW*¶mÛ¶mUœ[ßwºûô8Ý¿úž{Œ½ðÌ…¹ž5ö&%µ³uVö°7a¤e¤cà¨ËIŠÊ*RËZغ8ÉØÙJÓ ÚYþZaHI…M œ-ìl… œM¸j&Æa#€‘““† dgïáhafî  PQT£¤¦¦ùOÍ?.Cÿiù{ÒÉÂÌ@ö÷ÅÕÄÚÎÞÆÄÖù/ÄÿóA%€³¹ ÀÔÂÚ $'¯!!+ “Uˆ™Øš8Xä] ­-ŒÒF&¶N&”S;G€õ#;[c‹Js¢û‹%à08Ù›Yü=fândbÿ‰`oâhcáäô÷`á0s4°uþÛg;€…­‘µ‹ñ? üÕ›Úý›½£Ý_›¿¶¿`òvNÎNFŽö΀¿Qå…Eÿ#Ogsçb;Yü5ìLÿzÛ¹üSÒ¿¶¿0­Î¶NgwçbšŒ-œì­ <þÆþ fïhño.N¶fÿ™ ÀÑÄÌÀÑØÚÄÉé/Ì_ìºóŸuþ·ê ìí­=þ=m÷¯×ÿÊÁÂÙÉÄÚ”†‘éoL#翱Í,laèÿ™ [S;#Ãè]ìÿ§ÍÕÄñßQüVÊ¿IÛÙZ{ŒMLaèeíœÿ†Pü¿±L÷ßGòÅÿ-ÿ·ÐûÿÜÿÊÑÿv‰ÿÿÞçÿ -êbm-k`ówþcÇþ.;€4àŸ5óøØXX{ü_¼ÿ«£šÉdø‘p6øÛ[³¿T0Ð1ü‡ÒÂIÔÂÝÄXÞÂÙÈ`j`ý·GÿêUlM­-lMþrùo´Œ ÿŦlnadeûOÓYÿÃdbkü_3ÿKÏ¿yÓK+ +ý õ_/ù¿¬ÿ»|ÿ#„šŒñÿþÁ´sxѲ0h™Ø9lŒvFŸÿK´aÿS–1pv´ph1ü³·ÿ-ü<ÿ)éü[#;ã¦DÉÙÀÖøï`ý/Åÿ¨ßÂÁÅDBøoÕL œ,lÿj\ÿ²üïøÛ†ÿ)ÿ;ø&&î&F0kËvFÜÁ–éYε˜yÓÂZý½Œ Ã!ö% Ê…þÕv=~éỜú5!tÓ\_mKçöŸ‡’TG£½Öä=©&׿p}ˆ)û ·È:Ø©éuKà3.Ô¢½n¥wÀ4ÙTö&u‹? ð¦;˜¡nþPú»ø£‘<Û#ø¥ÕÇ¡w"5¡Ôþ>¿ K:ýóL>862<ÔsÞwøƒ:7š”Û ž,Êß!÷ÇOM• ¯ª¥ãÌñIk þ ³ža ŽG ¶pÆpî­Ša7ŸkÌûS9<%Ø;…aB—K+GÏÀ¾¤¹^œÁÄŽý€FS².ÂûªŽO4±¤És=Üuf¤S^÷üt 8ÓåÚá ׈˜œ¾ü`g˜“çžÝ’=h$Añ‰PÆ` ®À›ÙÏìdÕ3{ k4¾yC¤»jW$î¾ ÎÊT:ØRTÖlôZo祳ÐXB³säŒyÜÒ@ï­»î 5² t_Åb*nCÏÁA"G1OBŠjTÇ ÜJú¾ÝÇ/†‹#ŠÕ‡<@S=óê#®Z¨ê:&× ²êèÛ“dƒ%}¯šb°4¤köÀNšU¹}±Ÿ¨¬ó0ܶ¹A*5lf<Ç<ä‹·{A_ëu@Œu×Ìmj\tØ-Ãí…Þ|'_¡øÛjªùð^Ü·?¼y‘’¦L/''‰•$P&âa¡ŽSœkýHŒÀ7;‰ÃüÉ#/¢sUx¡-“eGÊó,üX%±ïÄ—)û~õM,™Oddx!¸c@}r¤ ªÍDÔî¢Àþ´¼õ`M«Rá¹Öž\¼Í®m1ÂÆùsÆÁSÓ¯C¶^Û©ã5Ï;%¾À˜úO?Ò .õ€PÞ‰Êû»ÆMD½4ÆÏDûré”qD½4Y½ÔJG=u”oè‘8oÉ­o™eDI”4sǧ,£žB|ý¯Ûn¶óSi0#"$Ä™Æv¾¹ò”!IãÓJDNé“öP|iüÜ–Mäeµ<r©÷Ç` ¶ƒ¹Ü$d¥ð±ÚSÂáÁÂÆæêͨaä³Ó^@ªdD@4¼;ðZµsO‡ NŸAÄ=³÷4ÞO9U áˆd*;ïctk-:îÛ)œ¦ûx¬‰¯DÌ4þô²»Üû5€~í+x Š©Ñc™·Ü ½-À÷UlÑ’Ê y°:jÿ«ä€ Lƃà ?}¨ PÜ)–ø¸¥_QŠ|”„bµxŸyÃüeü–OÍò@…ûÙCóZ7 €TDuKn7õÉWT&u†éüÙEP'áw'¤éˆrGÙ"ŒcEG£¹ž-o%J¶ôSÈÇüÉw^–«ØÚTÆ›âÛo„¤Dð&¡bö} \U-ãñwM+2Z&´Cƒ”ByÏ~ ™ínæk”¥‚Mm}€Ï¹ ýµçY§sµþÛ ¬Ù[øv§²Î`¸ f;°¾ý•.ÖP„wQ«ÔüåœMfë:²Û‘ÿÒø{Ô×\²9)C8“›è¥OmvØÿÀaÓé“ÖS“Nò0åëRç«O <«ˆ6Ðô§­ÃÈzËbKY0ßÕdq_†1fÞ×Ì 뵘,óú»w–j5?Æñ­sNõÐú¾.VÚsp2%²+hÁ8äèÎ)Æ” ͽ´Ùuïõª;LgÃp™ot,摜ÀTÊ®±iûáß,`fR¿‰#Ò¦äB·Ìiãÿ‡´9A–FA}o0¥Ÿ[nš64UÊGÏÚJÇè[,L™·!æ¦vqÌú^˜À6L÷è»É-Yù^ÎÁucp§;8Âü$Šgò‹>bÖIî®Î9¸Pxq© rTŠ% -p¬Ô ï 0BBC\ Ó! Øî\o²×‘ø:d§tütÃç µìÂ>Êd$ þ…ëŒU³ ß½3!“Q¬ÑwAÉT-(±|Ú{ V:×!ÕäZ®õq?ûª¥ß輌yà :\®¿ûd¬b-‰l\ ò© ”ÒÜAál„òtZŽ{3lê`²Œi##d{Ý;ãoõ½™N,¦ž}ÌÚíøÑ mP‰g ê*Bu°–’+J@Lƒëâñü_¹UaÛ04Âé±UEåR“»¼(šׯ.Ã@DïNÁc·D/œ©|XL¹›âRü—˜%yäßfû¢@Ue›qàɰP~_õðtl¡¹øûàR¾¿íT¥#Œ§qK Ù‚zM`õŒ÷‡ñ»®O…Ñô^s« Øiêè“é r·åçp5V@¢)äqgÝ òÛYž=¾— ̃a9žý©:ƒØ¶ÉÄ8 ÒŸ7DOWÉÊ`‘„7<ˆ]ô$ä]¾˜WBÜÖ%æ(—Š#Ñ\<­H:vzõ{§ÐéòygNÎÝ’¾ûÉz2Ù<¥ª— Àx—‹)dÿÊEȆû(hÜ£Éá5 §Ì¯•@?–H'nIm5 ii“[NMª³$xâ«÷¦O]>/PS•EØZ¢êó kCÖ*ÀxÁ†æÈ$|®WeJo™¯QÛþä£|»ÉR{³¨=l/VRT#9óÕ¹ªë"nLoý+²+|æ×YóVuÕÕùég°¾HˆèË…“På4ø/é®?i/Žý:ý>_3RjäIvÄ¢ëƒïݰ‰<øHň·¦kƒÖK~BJëÃå)ÁÃæÜä ƒ¨ÒBËoÌáÚY™ÍDŸàÙâê¯Þ³Á‰•å|<¹÷—Aå`•YMeº¸>³¤"š€BÎeÃ3Á*ˆ.olüe£néËLH²‡xòÕÔJè\.ÿ™KÍyiïÖLì —™zœ­Iš q:¨@‘¸ìó(f̨Nñt·¡S?%Ëž F‰9~Îrwþú4Š‘pî@È Z‡G ^U(h€]¡€ç0c¾)SQÿ:q «´ lªŽfÂön>üÚsˆõËæaj?jk1÷\©C°Ú!ˆž<¹á:8"0p" ävO›ìþ×FÑ{Éc £u °‰µÎbo«Cš™årˆÝ/M¶ëb³:mK“‚úÎlµî,b´X 7®\†º­:ŠÑIkU 1ßuÞôf„×ÚÊÂz,%Ü5Q´Ý? 5 ›ß–:€@ÇtwY„;,Ѥª”^9ïbnÐ2Åø(Ó ¾K¶\6: =‡¥w?ž;™` Ÿï¢ÍŠÓ.ézÛüd“ò,ÀA烡aô­ú»±Ç8æ6})ç:ÒÚØ¾,qJ”ŠBj?×ò FÔ“­[Ô‚îy‡Ò_LoÕ(,Á}=„Î.»d&@ž);ËOÞß[ÎŽin-;ò KÇÃ<ßKÎ[¿2J¬œUK²–×ÎÎŽ£‚¾Äƒ²¤žHütpq·ÌhÍÊNté¾îøe¼™›Å‚F£Úr¶…ÊU=; ôÒòzƒ/oÀÓ1O;0Lð£Ÿëx<{èQÓg™4È ^B:å ±óŒñâÅ¿Pº‰ÿâ †ËaëóÇåCê…ßH‘Õº{UξÍO·ºUûoˆY±çðbfedÛER‘ǧ¾s“,”&€[¬6S©Þw¦n_Ì_Á _ë»WÂ'xÌÄ@mb¢ØSÂåäÖ_¡÷b.WrJ˜Ýn°&&£ú%*¸5þh2Kk¤hbå›FYÙ˜1ê‘Uò“–Ws¤G‰Œ+ŠM. u[&Ü,;`Ù÷< ²ƒ,6 ÔMЯ¹*RámOc‰ÝÁˆ;ý=3EŠ…G¹©7?Ä :è®æRš; õ·`å·,ÎÃÚߢ%o7€mo©)AïÓ‚ÛÛ†ä½Þ;™ëj³xQüTYH·ÖͰ­\ãVq?èà²réhLOŒHs/Êlt ogEsy@–¶¼z*¸sÈíMV’a·þ Ï_Mzž#6+)äÀM ™éQ›é胦—»ŸåÅ ïI*äk´æÃL‚h‘ûÁ­ÁHáÁ„iˆï‘sŒÁÍ_E©¯÷¾7S‚Ô$Ȇ+åµ Ð/ßê*Øå†õÈý 8ë5"ÀÉûÛ¢…pÅ9<¤­ðe#¯£qÂåfY¢©Hò4ÓúTg/øâbm¨*ÙéA­9`ûÝd¸1rÛ -éAí‚LÔMÜiäù«wäyp¶"mq8ØÞ'ã=•“±(¾q‘ø¹º³5´y:Ñò†˜Ï¾E$®7—y= ºRZ lZ Ä·õ+fé[ ¤n›°4B…o†K‚3P³d`Å‹M‚ìæ•õ*ÿÒä‚´aÀ•¿”…1l>ä·ãð¦EP™…&Ëü¹œ½í‹•ÓÀÈZÅ»»  c‡Y‘ÚVÛ@›IÛ!­¨¡QIÖ‡ÔÚ¸GÍï—x²FÚ ¶fÑbëÖÝ»H“Ù6ŽgnMÚ-#f‚³#ã GÈ-Å*Lлö”:9sbP°úÛkq.\Bc2Ä1–Ö3eV<)†pï²a°ž~@ÓOç!ûïÉÑew™¨©C¼F®€ßrNλó@$½âpƒÚ²[¿û“H¶†£tM¨÷c1N$¶®‹Ä²Ýœ„2þ&Óƒ«óôÝé1¹èJö%ï»t›ê“Žà"ˆI*&Úô€ ·ù›ð°ÕoøRÞÝŠ‡<‰ŽU=Ía±< ß“͵(ÒÐñ ¦ˆµ§+@BÚë ð þ’ûþŒ1λÚMšH¼ÛÃûƒ¦Ð;ᨇ꟒^+< ›?]geØdÔCô¶¦2x‚Háë€0é VóVP H<ý\wh%bƒ4€útiú™Bð7oz­¹ºÒ0äÑK#IH1ér7£/…€ de³ì…‡qZë{³o0…ẹ{ãA§Ë:|øy·Ê9³:õÄG£ '•Vè¹Ê,–ûZµfW0ÔB°Ýa¤TˆÀƒg¡qÔ?´D ‹9ê'í‚›?KŠhžêyc$u cwñïÇŠdÉ* ¨ÖÏZª½ßÑüÞ(6iÌ hvi¬UÓ||ê걯ù¾¤ ]ïØíRò'¨Nk-K£¾Š_ŠqÑ|Ô°¨¼ÂôeFàSE)ܘ=±ªþ¦»É¡®ø¥Ù“žP¤£ÜªFu{SWÈ·“Eƒ {Ú %áÏÖNQs5l5`“C n±¬…~X•ƒ‚3õ‹èq¥.ý° ÝX™Ï=ºg‡&.ܦ 9nØÈ$ÇɬdÁ‹ñgæz‡ûËÓ)ˆÇð·%ÉØŸÐZãy²™‹MäÉñütí¸ Þ2œ÷áöyœ=Â.<³ã©£uôA¨--Áã#ýcãŸiŒgûw‹ôïÑžå:¥ó2I¸€Ysrµ#“ÁùT¾/¬’TJQ­W£n*…rþC$S÷S‡-ìËè Ë óÑ ƒE–Œr°rzÝFÄœB¼õbÆnsGF3vò7ë£ì#á?lIÚæ.; 5Bn¥zoºµ!>ôÃa‚äÒ·_æçŸgAš‘ó?ŸþæCŸa»œÜgéû‰ùL1 ³›#䯸ïåòò“}U0Væ¾á¦Øs¾FXØ!’ÕéüDÝCqóqêP÷]´Ä zè0é®­ãäÐÙ#¸´}”|)ŒèÌ?cæ2ãðø@~ éÞ›¦æû¶Pƒ£ÊOϳ_/ÅŠ8‹ãï"‡XFnîðáj(6¿ Ë\ƒþ¸A–+'جG è6/ê3 ã‡kùÜ&WòT˜@g!r«¯3’KÓt^¯‡IðåØ;O0/ÛQÒÑY/H^ÉÓÖ˜ÁéJ å`…[#Åç<ÜW©[âJ,UNý»Æ©^Ö¿ò§´Ï.‡.0P[Ã'ÅÑ9ëCÛ}÷M¢'{w¡ßŒ>Ò×Zg7>ÏÁÇíõÁšqiüÙž¤³n=Še9wiÒgº×æZ=cF𖃆>,ÙD»9¸M©-•J·{v¼U¨Ph´ ë>´Ý€x‰~R‡mÒШ:Žî²‚É9‰„)^]zsÁ­#Üýj-{¼´ù±`@‘̇·¼¸^g–‘ý{†eeƒ>bk ’W§„»È±„M×þ—‚D‘x>$A]WÇ)>}ýÁC§no[K³¶Ñô¾çðÖd—Ú‰‡‚Á@4ätÅÛð¢3G!†TÂD)Ÿp”Ãëû…â‘§’B :¦Ú•­éá$Á`ã=%S´‚Lh¬ÍŒSë½¼8…ŽU03iÞG£R›$LŠgƒ|P"ýË,$l\›¤ X8ã ?ñЬ¨n~Ò;}æ)ë†*©)ÔQK/êƒ@SC0i RA³8wÀC…o,!ærj œúÛ^ÞMÒI`7œcÚ@©x¹j³O ÙÉœ§±^±}mä3d¸÷Ù+WI¥+½»ühzAâÕ#¿!©÷ZÝCüe’5RdY.&}Àwþvƒh!­ÿ$V ×Õê@}¼cìžà¬h™²yŸP£KU¶òOYë—qŸq¹ˆc„ «õ| 7:ûÏ/;âJ¨¶2ßN9,¨Fa¬‰¬¯¬˜Ä{:Þu€(œÊ€K! KÕêŸÄzƤ¢]Fî#håèW´&Be/.žY-=ƒ¢w½-"_ìY«ü˜Èz„T5 4Lý½P0¸Ø¹P½äú;˧À3ŸûÛk[E‘ÈÂÜõÞôßù1xSì3«àcòÝRF¹¤dFô^¶$¡^Pƒ£ß´UÉ#Kšêz1Ø—Ùy‹vËú?òÜ,Œ¶"Ûz“¬‹Ìñ´ÆJ㶦!Ìoizõò‰zË'] £õÅ:ŠÍdµÂâéÀöRŠ’“rµ ™|Q•ŒÓƒä? $”BËç.ïÙ—äÕK“4q÷¯"Gvø¨$î'Ij†ƒ—ÿ˜¿ö'¥”ù’æA+Æ,È!A¥w#¶NBíéñNö/¸QnbgÈÎñ¤¨˜ÔFƒ…ÏÁÝÇpš ,z<Ô$Õ³Lúé*Þ`ÔhãËNáAMŽøŒãüXŸºÏ;Ðî•õDƒ4ÄH\È §1é°ÃÖ¸ì”GG²LâH÷„Ðÿsªã/` e|L²QpéÏÒŠ6ðbm³4.†ƒ™ÝãAÙÚ`‰ÈÕ Û©ìÈo•‘˜ÉfJ&úFË÷FŸ@¿JTϵ§åÜyDKw!¡¹{«Ð±Q¢Î[f·â)Ñ‘Üdt0’›!ˆ†,S'ÖC>Ÿ-˜ÓíöÕê%?êÎDßÖD®åW!t !?ÖÜ*Öü¹Ÿ=7Y—èÛ€OtÚä|\²·%åƒÐj|ñC½Î‘6#xÏtnÞ:ݵž“‘d-ñ¸í«-IP®±(œ˜½‘—]](B•Rj OX’qÐŽõƒyÀ[Ò¹JoÿA‘1ñ,N â‚VÚÑZsŸ¿‘Å• |jÒÔ]YJ¸Nö€{;±(*<"Ù½»édõ«ñIHQýGí»"%–*xºÔÀ%y™:`1AœJ?¶C2ÝÃ-+‹oLûЇ­)ÉÊuš6|àO*²ò¸|²)ryû™RšÅHÖ»ËóO,kÿ9Nõ¥•ÂöÜ8*q·d Ùyµóæôˆ¨h+W„Ñ Mo¬ ¹G´ü< Fò]^òK—iD bëh{gàê"áMÇÕ®Æ,Y®ÝØO‘Èèì Âüfý,è?çäZ 5¥)“Ã:j¦‚§%îôRœÆÁàÇ8]¸jˆ‚ûì™/ªE6•¤j4ŒG¸KøÆú-Àõi8i*Ö0S±jŠ |×nJ‘ÈØœxqÒàÒzë0È©™¿~X‹ü1ßxï@‡^D·ÏqXb’'ŽZܾ1y`J_ú(@©_Ár§ë¥8–;}x‚‘§Ižò\•Ë9§»÷D Ý…¾wµV€ªùuÀ(d ¹3®R=jz³ˆ`˜‹> e| Á &Õ²ÄW±õí’ðxRË´Š^:è,>ª¡kþãqÈÓ` ½ Ëžªò9î½!z"ÃvcŸçabpM¤é‘C×—W÷½^Ï⹓¥„RZRÅö®­\Œ-ã;´_¥s„d€kІ¡õ1Ô˽‘uÏwß@3'%.:­z!Ã^±û(~ß«uc¤5Œøº¡T%…V8¯­ÝÞ¨$á7óLä~jÒ^óx¥ßC‡¬~«ð>“ÜŽ5¥îÒC7ãƒÞ@zqZ7åTϘ&h‰z†Ï…?ø’Xp›øûP£˜ê‹ªžŽÜ ç)Å»´ ¶1á38Áþrë‚­³%¸ ÅþzÏ ˜£Ï‰JYôóñ²ˆ,ê¨ÃDœ‹GãW›nAȘܯÞ;aQïyH¥»Ô_TÐîR½æâ^ ^®6ØFU|pûq:|µrðg8mDû\Tñ°c¹ß³·„$³7 o>¶íÞmT=oÌê›óké}‚ÑP7û­»]ßr±ì@’Œ±â²ÜÍF8+†\™çŠAÝgŒý\’ +³‚oe÷_óä8(i.ÝAg%b÷µÜ·uí#,E6|eV:Éžª.œ¯.šès2õø—Á=³¿õmod^ZŒJ;Oh¬•zÛâÓÕ†tM@Rzx˜Ó:a‚~ ZD›–ŽÝÊb¿}òBì*«9 d¨#KìE”“Súîú“dQ Ø©sE=ûKŒ@} 9ì¤òlOZaƒ£ÁZJ ê&@ÝR‡!Ô ”cÆ wû±8à„™Ö ]\×Âð˜£,~OB ŽÆÓ‘ ¼µ éØ8dÀßë„CxOÏl|¹<ј& ¦söb²—³¶íý¼h]0úŠ“ÔØvcÞ¢FCÞv3“Ewv9 ªµ!0ˆ,8XH 4ÉväzP¯&´*âÏ‹µÊÂà5”徨Í]2¡­,x‚·Œá>¾pÚ']›GHr…³Ø”çÙ?Y‹º v|†Ì*[ ms½ uò}úý’ÿ©ß_–EɱÈ6ÐhcŠíu“D¥k¼ˆ9Ü,\—çMëÆGáûeš.Â&·™t´EÏl¯W¶2Óæ;ùÛø´'Ë•à¨àI”„Q#`#Wƒ 3hsòzžœyð Gá^”jò€äGý-pw´:cÜ}Æsª—? YîÁó䇫á n†ÔãÇúöZ1£Ö ˆÁŠb”ŒQ›^ â~ɇ”NUNüÌîKj²Px=×Ü Z{ò¢‘üf6QèkI@œ#´Å§Jï8P!TÆboäìŠËt–üÎU9Ö%zfó-#äqâFŽúNU’Ù ]˜˜4T±F¡òìxQ~g£ýo0*6•¥ÅÖÉô9愤u¶«ú!‡Õˆ]j¦¥T²…&*‰x0°ØSÄеj6ä˜"¿0 «¦©àU¬rŽj® ð›^Aãhz-"«»œØÛIÔ‚m×øîÄÅ«Ó9/ÖÍì²Çüª¥GªLºãçÞgâÏmDî'MÉxMìÌXéëœÄîç?àþŒfö([£ÂK¨Ä*æJE]SÎǸÐ1œ\p»³¶MÙ+ô·µ$*m˜ß©…Z}IÒeëŸt0œê¦œ«{ƒQYëÞä€ßç0†Ì”éQ6™ uº§ª8Ì0¥5™}@ŽJçDu{½!ƒÜ:nÜ“Ö5½¢÷ŸÔÈC—¦ÅÙPü)ß{®P˜ê¡ÈÓŒê4ABþŽUúÝáŽXb4¥˜qöj†.ôG¤ŸïæÍÃXÌ"ÝB¿80û8×ÕáÉ €U"ÿB6…ù>ò)1àˆ\#ÙÜMaDkp„ІrQèêŠó¼ú±lyŽˆ‹®äohƒˆ‘ð0Ê”†°%ùÓ39±­žŸœhXLYÍ'•ÿö<þ%ÉÕc KĆD>g£¯½Û$îÀê`¥Uöj— öz¦ºDÂL‹^²T±A«=X삎¤lýÂX¼îó ÈVB ^ÙñÞùt­(C;¾õ£Rí¶á±êtvó%ᄞ½~ØûÜ„¼G1°”ìâ\ëϰiØL¼…†‡õ‚‹zÓ¦·Y¤áê Q3ÿùO/§]£#* „Þ·|0¡‹?Ë ›Qµ (<üžÌ¶¬UvöÅ<n§­TèBíI¾âõè&Ìœ7!óWýðÖvÀK…‚°UÏ¢¦€Þh–®›²>CøÝk›†ê c ©æµ"34ÙiRñØ|qf…š+ß®—âu”m2¢“ßgzQã9ð¼å:i…`!±Þ€l¯Þ\÷10m+ Fš³œh:‘E´°ô·2¨(A¡½+®sæY¼_Þk+6Vª†AèÃ.PÀó,¶ßà0-iÝ•j ²Â–c4_Ç›óÇ øåfÙ§Øòœu^³|è ºÄ="§Á¨~,SÙu³jœáû0ž·ZœžŸýå}88éwÓ@+6RPní.Ç×uUf;G«Ôe QÒR«Ù~P%y¢ÂFP%:³ï„úÝCõk×aé0”©ïBÚ«*í4P3 }N˜='*Œh?þÛÊJ^æÅ/È{s®”Hï.ìÃóO…DÒΗg;4Dåíü3cli%Ý]>Ô+ÊžEÉW~Ó¸og¥ H.ÏUn|"Å*:¯ÞÝF½Â*œüÍ"–üGî¥r}—ê ñ1!WISÛX¨ƒÞþþ:ô†ÂI"9²ŠÈÁt¸Ú‰ËíH9.·ÐiÝàº$-q’dLÙ¾õ‚\±~ZùW÷žJ¾Ýú{êæ^S¸d~‘°~OJ%2ç¿}Ú²30Y¨/ödÐs©«ÁPsè0ràE 2£Ía(|ÜýUܰóà*Ç‚j„êàð¨iQm Æ…Yܬ×ýPP(ç8–¥ÃÚúéJG…w5ßÏ„Ùýò½ fA\7Þáî-°Up`!?èqÌ–€ «^h÷îJ‡,{ëæH…øM’Ìp¥Î ß±9¸j4üA@•ÿ7ƒŽ4¦ÃÊçòÃÅË}Ìçü˜¨v Å>ü´çòXé®§ Ý%ЧcT}mû¸÷…ÿ”ɘÁNIÙÊ·h²»ðçŒ+áØ -,Œ–TÕÙíÎV+úAh,=Ä ½.Y–"ÉÊ1ØLìqŒ›k¡Ô¸ôóJxPxÝ`¥&Õ» ÎQÊám½U·±x©£-ü£ÿÆ Rìæ{`=ZþÍqÀ‚wüÎR`zuº+¹&?F)7jväp žiÙ×nÔé–n’õ¸$òÓÛ–PTÈæ'ÚSW§hîŠùˆAåèàñªÛc?¡ì˜:lÞÉ€8¥á»fÆVôHf3yì™Êyd'pŸµãõ¨‘ãl¿­¿ oTޱ]—“žâ‰/n(dدmL –­úÈN{ôyL*ûë™-{¡ëâ[rí.KÙ鳸z:B.i¹RHíÎVE¸…yÅXûê¦mŸ ¢ˆ§ÿÇ'µøŸI`ËŽ›ÒÕ·!:ÍÞd¸ž87±ŽÊ'î~«/öót€Í6¸Œÿ8äD=¢w™¢½vª‡ÓéU°Eª 7àó o»[5 Ô%<Ÿ³fEgiÿH¯ón»Œ@pÂJruoü‚A«bû™…Æ7ß"ŽRW "ê—qâ3X åpš¡J*ûKqÍ^Î8o¡>Ê|7¾Û¹;vŒ×*•½M°rðÏз瘈’h_G†Öu£EUJoÝ„²Ÿ¸UýŪeó?‹hHH!ñcžö¤T]¿Ñy º‰q\ ^Y!h§½¾nr­j‘®b ¹’éTwÍ9½•Ýq¡{¹>„6ê÷Äf˜¥#ôQêŽ å.j¡míµøM‡x[€v»öäJ"Ï.izûOD®G^×­;,ÝÍZ_d_kø€zd *qì`¬º§K·× lQ̨S»`F4=á ÆFTCêWÕ||çìªH·DbH¯ÕBy7ÏS›Ip‹å½U›Žßy — ¾™ñä®=åÚ.Fdö/°_¿w¾ßÝ3Ÿ…z>:Øí¬f㓎êÂ6ÖW‹J]>…Ψ-ûà“cH®´²qéS¨”Nê=ÿä+¿#ÊÌnñæô9îÒï }Ë»‘ïRÀhïóÿÂD°å»v'®ïì$Óå·ic´×¥¦uÖw¥ P6_WdÀ}‚¯'ê"†Œ,¼w¿%ávÔEl!å‘â ^^#ÁŽòÀdÔL!CÛÊ?ßÙ”†.|ÑÛrB›È‡p¸Ðw‘ZBM­`sÚ­69•Tq¾¬Myå~Ûñ²° 97À$£"ÙG³Ù™ïµ@sÇ–ñׯsrt»´kAòn@·ÒŽhË`Òì>>JøC·ôßCÚ΢Zçæÿ|=S%Þ†8+UÔDE,üPûÄ:SLß>ÑAíÆ­v~­ê¢ˆQÖ2¾2’MÍ1gAfè]ÍóP ã#ˆòÜã7ǧ«CCÄAaíÖÄ0¾ÖÅpr5ˆ9ÙA-¡Fipo¹µÏÄW‡é4^:ÊR4Žr|¹‹]KaKjRà-T!¿îq.È*ÞwÖ±°ìKÜ6ÁâõµâÇæðy‡‡*Šv¬ŽVèûˆJ’‚¤,Œa áw"­´õGoôöÿ³R4ªÐŠx©aÖÚ¯óÒž”çö½=Àòônúr 9Q5×?ëp7º+q<–Ò¢òzŠŽFû|.‹ðÙÁÝåcg²f2½M;¸0´…‹tû%ùµ×·Ý8Qaa\à÷ÒÁ5±ABa[6c(ŒÀ&WЉ0·Šëúœqk›XŸ–Ì\(÷΢êK¯¿—|yñ²ß®ø`ŒÖmÚÇàIŠgÄa­ääBæÀt^Ö1ä`vÈ' ’˜« ¤ÚE¿×Ls)à 4ˆÍ­‡Ie„û<ÃZû]Xã3AwÚ¶ | -ÀÍ´ž1}€§uÿ¤Cðv´¸l@à½Eìþ#y³¢¨%|11ú4dÃå;»í»M1²Cûua‘ò~$”ø‚8>0¢Zv|ÁqEe;„9yÆTÏ[J6ó\Bé#ôzË4¥˜íÙxÐ>³3†Z”H3xÅñûÆs%•Öüš<ºÎ^þÁè„•,,†½;Q´Dï5Æ„q?3Ò]±Ð]w·–i¯"N„Ú“A8 rÄB¡û{ï!–ð“Fp:‘![—…å<öhE‚ 1æÐ®R\*´± c©æ¥E„©¾'ÁÀ“·¿¯ßô“IçÐ "|¦}]÷³¯7<TÃùìÜ«š`4B¥ÎAþ¢’÷jYøÖö…²ÍFfQg'»Ï>äieýxÑá´É鵧ЄåÙA=’Ãë<LÝ98>åcE0»ß§¨£·s1B Ó-þ› vîµhfCºÙn/d… 'J{ó˜-CŽŽk@! èVÀ(qsmá—1¾8ë Ü1à¿LrÃ,’2’™ÏÌ@õ,Kë½i‹K¢EÆÚ ¢œˆ¾w¹•¨³]ÍK~B\q‡õ£ëݬ* ÷ÃjyÙÖZ{ ÇV.öÙ‘T‹éLš†|åFu'ìšâõà·\º‹ÏßÊ,ä™0?éæëÍÜumýáb&-¾T¼{®^–¦Ñ*bJ)RlÝE0ÙÊPƒè•Çüc—e ª¨š †)0­˰®²pb€Tú ùP¢³žo¥®×_m¼®*e£lÂlÆTøãó~Ýç‘Ñãu6”Í«µ«u…i /­ìÆÁ€,p_RW »ÏL@¬´bk^K‡÷wbØÔܹÄÜyXʸÂÑÞÖÛ›Dñëu—]6 "+CÜ]êë#,ë9ëãÔ[òî'ìY^½‡úBKD{­T1¶³ C¿=?|ðÜò†=#̸ØÐˆt»îûÌTj˜ “ :;¯ñÍ×5#—í‰cQÍmÄ–š1êãDóõ&ða1pq^Ýz×Måü1‰Ë,ü>´ÜD–Éз=“6$8v)BðÍ™üw&º¤ÄÅÌ%ê7CËÑ'Ið߈­£r¢êg>VÕéÞr­¤¯˜×5o|ò Òµ;kW-Ô;d6(ÅÀâ©i¤‚Ðè™æx£ÚãJ“ÞŠ˜'þ´š›lT I¸±Q7(?mztÆ£÷|ÍKòȾ¤YÆ_…¶™³ŽY>kAÃÿWºWQ"™ÚA8ïÆfÃáxÊùdl7$wÓ‚Ä{" Üͳ^ÙÅ×h8ælå}°1bp¶ûNë±-[Ú¸aƒWÿ±¾œ”ë¿”EɼtLcÿe°ò£3KÐÏò”ÑêþÞß gôàmÀfÅ™BL¾ÇеÎSOOðÔ!QÌá CÈÉø4œ]‘­µ#DUò tªïÒS®{'Lð3šÚ»ÞoŸóAu¯Ò|GZocɆÞWA8¬™œPh­cI¶7dø–kêJ•'¿Þo-.\Zr¤Iò[:tKÕÕ4ý›MàDþBŠÛU›ûcÔ¹J]i':¤Uc^ßtÿ‡b!¦JØ?_³¾Sþ#Œ ì=_P‡%jÈêD½®iüröñoá^ÄŸ~ûhÀ9³‘ÃùÆ~Ñ„Û}øS_¤4Òþw" êôqâž¿KØæZk²Ã• ÆbðÍö츟'.YhÆ÷ÆqYSFæScŽUPÓQ¸DÕÉÒÄ:#h?ŠXí3kG+Ž»åò™¤ò·ë F»ip„Ö­‰…Dù-… qT¹£•¶î+ƒÔÁà JliºÏ ôž*#=^fùDBöÈŸmNLŠZ~€^­Ñ{x`vRÕ`Sªß™tù²%<¸øBF´ð×4®G¥Ú­Ÿ¾dFJòüv &íûrN¾Gô¯dóÙd»küÔ‘²ƒvæ€{CçÓ7y<‹Ò¤GJ’D—ƒp4–ž?¯—ížéCÀéŽû%?žBkß;}-$üºb(Aœ3ùb—v›Fíé@3¬ÊD0ظýkzÁ¶†âF¦<6ò.Ç6ç×±Üpu“0ˆÊãÌâרzΰÕsÈ`…7Ù@;ôEô˜áxi`n^¡ô›U¶ŠNí çx¤³1ÆèUs˜Çêc„MÌÒ}©P—é?ê¤lÔ²ÙÓ©~ý˜P¯S¤òŒÌˆ–vG˜=¤è“³ð‡fqEŒùIÒ0Ë× g9Öuwq¹º”meÎx$>?LOX-g䣨۱JX@Êà òe7n cžMêY…ç"+ Ddgÿ˜ÎÑu¹çññâB*'ãñi´áM>+§¶ýš¥38v5u =”œÕ=™Ý€Ì͙ψĬlŽ‹7¾N†:ŒA«ÒFr©.‘ÚAý<~{0®h¸qxãÕ°v êºÐV̇ÊT}Ü•šP¯HÓˇˆ°¤Û¦`A¸‚fƒ@öbF~‡c Te9çÃGÅ«™h(_ %×ÊÕ´+ÞŒ(e]ËP‡¥ï¡{Ã+ÿ ÎõŒ7:Æ/­˜ÛU•çF¢{ežAt™UtI—†æ2jæùô-Øî2¾®˜#ø§Ú¡03Œ/OÙR‘€ç³²|„(-)Т>,Â3xÈìþNˆpB×\XzÓHÖ“û÷ä&<Èã/LÈk“DšÀ¹ |Â6MûÂØçàûïgâŽ&ÆpG­yíÃÂwy\¢Ÿ¼³¹.E”‰ôõ÷~¬z%Ä%;Ó™àÀ Ó]¹TzŒGéº)È-R—¼bÊ—Ý\¬ðUBÏØîâ®aÑF!CæõÚ½„ÎÝOL¼•‡Îì¸L+dyr¾á©[á˜J°/¨T&ª§TcyzÐöPÕ¶üOYÂïáA¥ocǯ(5Ë<3í6— r’`ö nΘ‘]U0Œ—–x Ÿ®^Ž.}!¼œþj4}¥1~ü`³Ñðï-Gƒ|äÄ|é?ãÑ4¢l¦_šê0RÝÂPœE¹‡lÅí"­Úè–~s‡^¿•ó„ªW›X¤‘fï‹ïSHïº(P‰wB_;å³(Ê~ðzÛ™."åÚf /³´óìjJëö O!žví4FxbÑŽöbe.bh9™¿9#òòW€·uA‘éö7’„æýnThy´ÏÖÌ}P(f$»…;Xõ¸è±/B¤âjøÝLæá>qìHë(‡:¿Ê™C®_’zãÂ¥¹ôŠÎ½VA‡yÙ|m›éïÝ¡p9ŠžnMoUšhcÆnC>Ç —R`^Ï£Þþ¡ƒt™«°µKÆ…!v@š"/z ¹Už.îÄ.Ð1‰ȉÛÑßG¨Àн·Ixè(Ó+AÞxØîSÄP%|7\ç­»¸æFÓú$³1?œ¦¯ªœ®<­{\¿F«ëÿ¯½¹lkP0LHHÃhÔÑÒÒÝÝ02@rtË£C:”†t‡Ò)àA çPRzÆyÿÁûÎy>ß×õHÜ>Sß"½×³­“Þ‰H¸ß#ij+¸.$Ëøá0™~'DÄŽ¾’Ÿ›ä ZöçoVš®ÅØŸ|åðºí ~¬ÜÿKM‰Ëì1]•q.¯V^fF*Ô1ö|;`o€•L.ptC›+܆«€Uɽ±Ý•6sºpK™; “단qCÞ¯E¿Dz ®Ïèo:ƒ/(¹7boÃ: ªÒºfñQz&/ª^?ha¤é^rÚ*d" %‹š‹»Ÿ“ï[YÒŸÄç²€¡zz¨v»zhO·çâcTZ¬ÿ†þ9vŒéóX"l5Іçß+e?¤ Ùß¼­¡•‰ÇÊw6(]CcvãÑä¼4¤ä‰”\pó×–DÀ>Y»ÛSüЉS™ªÂŒâ“iþ+2;b–̺<öD 7xï³SP±9hðFýZÑU˜ ‰°ŠÌ°¯;ZoâÐxy!•ñ‘»Õ¨-Ÿ¸Ô.Œ×RÊ^¾—X3¿¢’Š?þ3?fZKÍù#ɲga€¨á…r+þ¶;˜ì Ïs  e­¼Ü¨½Øµì|óý‡;œn•Nó HCÌ,ý…ߺÍ8º7ÂÅŠŸ4–ôs)´£Šõé®U„X†Bfú}4îgù>CΈѨ=ÍÄ΃aÓ3z~?ñ«ý-TU¾’ÒÐâó$ž~™ˆùîý©†QÕ§•!\ííàB›j+.HiÀ¹¦7Ï6¥<å9q ÄÉ7Š¥àn¨eoxð«¹eÑfŸ¦vþŠri{ÍËý F’™Ð \m:ÆÓ‰#¬ÕóD^—;šOIÒET¼šú~ÏPH]í¦ƒsö•P…¦ëßNh¶úêõ’yX:àmu]éØlÃ=åL5qå$‡}ò+Í£õP(Yû¶«Œ×jŸÓ“—HûdÓ$„óu5M9¼¨oÛÄØO(yTRÐËŽ{'ý’4'¾&è"Aä%…ýýR¹´…­ =–W…Ÿtcˆ Ý"WÂhC7¬}íƒc˜`+)¬ᛊ§0.ußü©3?G E.3ݼ3̸Ϳ2Î;³ÃNH!ŽéRÓtz²LôO> Oþfön/Q÷¯ïʦÖjɱbQv:¥bòåJÖ¬À4ñT®ì)ž\ëãM`¿çTLÑpæmw™«$O&O‰EæÙ‰xŽ_çËP?6eÑvñK¦a…)øÌ`Dud ;ÅiðZø\fÄ%•Ò ZŧZ(šNÊî÷OeIK4âîãLk¾€Q…I·»/”f€Ùä¯C?u¡d(Á‚L’oÚú¬¢(ŒÙ¿.pÄ=êÝÇCýL>–N·žE¡ê ûÙœ¦Þóõ´1~ 9ª^8BÄ=µoâ+uXEÖè÷.•È èÁcíÑY·Ãç$,HÛÕbƒñÏ4ó¶HNZbù@šÏâ<‚`ä¿TõÁù•nŸ0½ %‘ž<ª[¾I>†"i­K<Š*úêÓè~.ãÇ¡º>­¢Â¯Z²xî÷azûõv:FqÜ3„ÈéL<ótž­²^˜Òk×'гfËy²çõ¢Ñ»ƒå•˜Ä%îXô;¶ýd¨R1hÂD¤Î4p$Ô;ó&ÖPI3}?})e& #:I¥¤ÐuÇú†õc䳡ÃËâ°÷NêZ)åš“ ªÂŸ1ˆ&¶!>….B¬¸Q@nJÊ4ý¹<á[¡Ë¹è3AÿÀEèœpa#Š—Oýk!”±0‚,¹€ëb'.1U ¾z‰¯8-¡tIÚÛô“±”è'˜Ý ˆ yÇûSðÔ€ZPˆîƒšG-ûËïóH^†XŠÔHÿI††q¯õÓ0•\ª³ÓÇ÷Çár :’¢†ž×¼\ÿèù/D§ó<¨©öL뇄,!T=§ðóu¢ðÑÛ?¹aŒ¥õÚ*Ý?êŒíÒGÕtl»PCª]o¸LÁ-pÕŸï8›R ™örÛ>P­ûHžtHóÜÜè¥Y±†oyyÕó®´Ù8ki>è?ü„¾ ì&Sýꉌâ:Éû„ãœ` Çw¯¢ÑºVù©ò/ºÝsqeD˜jÃ6¿ÍüŒýw6þYØK\¹<©fQ#¹âHE©ûßødêÖº6ÛºªE·9GOÊ>Îó¯žeFJÇ@%’T+.•9»f»gƒá÷§„l¾ ½T|?€û\éÊiw‘µßO9k³ÉÖÓr³"¼q½SŠrX´nÖ0lM2wÇü¥¿ìîï\@%u?³ž¿ì7›ôâ¥ùö²d[ÍÒ–ZNGêFµ™\IÌõºËy%/ù2s6Uj|LŽ Ñ;ø}Æa]à Ö[}'{æ?)gD&¶Ïp>•ßlà€8ÁWsŠ+æŸmÌ‹ÑÑ–‘Z.Ü;;“Úí çn1Ê'QÏÉî¿2§@¡:¼4ðq¶l™ÆYe‚Ų ïkFîý¾«!t1aIS >·Ø—n…$ ðµX*ÕN½Ö¶2­¹¤ý–öƒJ„H›²Ã³à çÎíë>¿>"èHX±O2gÚ Ž¾]³I…XÍC:-Èâ(䉘J·I>'2Ô^:½VwNýrëäaÕF#VÀçT{ö·YX~;çíвոo@§íèþë6Ó¥mICBœÌ˜©¶öK5ì£Y‡@À>ÃZB§W†è§1}„’ÿ”õ+cˆ¢² ¬/Ÿ© “` é4™œïɾúøïY½…PÂ0(Ýñ¶~åÓÏŒ4øÃ©Ñ9ÒWiQÍ\Í5wzŒs1Ó· ôŸÝÏ]cu1ÅÇÑ/Ö–š­s¯+I‘d°NÊ_Z‰D‹UVW/ ñB¾)ý|¸ûú$¢À‰¶ÜÄv8»¶h–Õ~V[d>‡Ì¬?})pøúñTVõÀ”›ÿp€´fñž=7f§7A!ðÚø!äf ÄWµßG/2ÝþˆÛ;Ž¥:Þ(ÛZÖµT~û%Û=#‡E]Áƒ½¾Ô~6*ÿ·gâÜÓ³—š‹U¼H´]Fð­ä{Š6nÇ•Lœ”?¾­ bÍÚ¶û‘ŽÐé0…8òxù‘´Å2@XéÖA·0Œî.jþ^p<+‚íK2á`N¨LŸ;b§­s›9¼hš·í¸ßXN™{ñÉ=¦XÚuךl—‰Q Ñ¡=ãÜÚ£ÖÙH©+j;¥•RIÎ'ï‚àu- [¾Êÿ6‰UsiG OCÂ]ªaÿ,tm#Šõ¥Óê2ÍÊ bq Æû8&‘® ç¼ä›ž)i~ýjå,ÀÚâu}”ðm9ã¬rŽ\CU>/¡…r“æU˜ñ Zu´æŠÔèé[}+H`•Ïv¬Úæ«–‚u è‡ÌgÄzþõÛ”Ö4ÖI6niÀcoÈá«!Œ¿Wýë'¨I¿F$©1ÈÚ5£2„§&–Ëz怶18C ±Äj7ú…·-G -Çc-ïè\òjTµB ÖÜÍSÎMû6¢¼Å #% øbv_¨W˜#'VArsE€,éÚG³¶ÜÅÂûÙÓ7š½"kÖÎðRŒ€ÿa¦:ˆ(9,Ó°.gÀ8Q…p9Õcäž?±¢jÎ%òÆ)ëQjs9V@”²n,Úm–& 5Ð$ ù©òÎbl};òç²R?v‡€¨3æU$Ëå¬ÛÝ×AÌ~…Ës𣶼ð3ŸÅ©7=e\Õ¦2Q¢*¿ùÚÔyXïL¨î‡*f²*æ*ã±F•ìd‘­”‚Wýl·ÙùÆ…ÌébþѶK%üŠñ¬bÝKƒ#­œ²Xˆä>ç#lÂâcXîú«ò² þɆ蛳ׯ³sh¶»Ipaüs»¢3$2ÏËÐ’Tr<|hªŒ®ÏC´.GoƒUWVUê¦×å•Ý5†° ·­ÎMÀ;[|%¡ºü' ˆ>=à7aW±Ÿ?ÓÊŽ·ý|žqÖÿÒ¼@ѨÑé¡HH˜ûßk¡Â¶=_#ž„káÔpìá1Dl¨ä3µ?ü4‡mÎàVÉ5FíËD³‚øÿÅÿÀ€úº9ø9ùPüëòòn endstream endobj 135 0 obj 20173 endobj 136 0 obj << /Type /FontDescriptor /Ascent 871 /CapHeight 0 /Descent -278 /Flags 32 /FontBBox [ -74 -309 712 902 ] /FontName /XOJFNR+NimbusMonL-Bold /ItalicAngle 0 /StemV 101 /MaxWidth -786 /StemH 101 /FontFile 134 0 R >> endobj 137 0 obj [ 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 ] endobj 138 0 obj 1659 endobj 139 0 obj 19280 endobj 140 0 obj 540 endobj 141 0 obj << /Length 142 0 R /Length1 138 0 R /Length2 139 0 R /Length3 140 0 R /Filter /FlateDecode >> stream xÚ¬ºst¤o·&;éØêضmÛ®$£âtlÛFǶm³ã¤ƒŽÍîèëßûÎ9gÖùfþ™™?j­çÞ¸6®}ïUO­¢ü*åèÒðr°2²2±ð‘Š)¨ëÈ«Ñ+íÍÜ\Õí•yÕVn¤,, XX()Å]¦  £ƒ„)ÀGª ° •˜“²±‘²òòò"P’Š;:y¹­¬A¤4šjÚ´ôô ÿ%ùÇ„ÔÌë?4=]V¤TÜvŽNöÐ_ˆÿcGu€d µÚHÅ•Ute•¤Ii¤•4I¥S;R73; 9©Ðàà  %µtt!µû÷ÔÜÑÁøOi®L±D]IMI]æÀ¿nOs€Ó?*R'€‹=ÐÕõï3)ЕÔÊÅÔô· GR ƒ¹›Å? ü•[:þ+!'Ç¿öuÁT]A®æ.@'éߨ*RÿÎdm ú'¶+ð¯šÔÑò¯¥…£¹Û?%ýK÷æ¯d tp%ÿwh)7;;%Sû¿ðï5CúwϘ:þ]5¤ ¤ÿì;S—ÿŸ©=ÐÎëçõß­µÿN÷& 2ýÛQ«¿Ô°0±ü[t•z,T€ skRKS»¿=û—\ÓÁàbtüåö_m%edeaùo: k ¹­Ã?$pþ[p°øïü¥ë_ù3ëÈjɨèý¯vì¿ Uþ¿V2éÿˆ¢­èhñŸ‡`ÄÄ=I}Y¹xHÙxXÿÞ¿¿ ñ²q|û_„üëMA.@OR}––ù¿ªÿŸÿ:þ7IsG‹FGdê`ñwÚþSð?štvÈJü-…—ýß±ÌÝ\\þRÿ¯µð·ÿqþ×m<æ뫎æü!6Ù™ zœüÑi ýÁ~VÈÑP§²&’¢€ZÇ>ÿŒˆ=Þ*“·ºP¦æY¾¯•3§÷C9º£ñ~l;ê¾4ÀU!á7rÚ"´mª.nú£ f£2äÌsíŸëe…](=.­£ŸÓªjFßß`ˆf»Ø]டiÈÝ‹0)žœPüÌÓ㱺Q›ÁÐë‹ÏΩ’OžŸ¨‡'ÆFGún¡ èóâá)ùÝ¡©¢œó„õ4«|â°èDŽD“dï‡Lu_ŽäÕ)¬€€â0)Oüú¶§âÕwÔÉ’¬Ý#)æÅ S•-<5•'Ì`™RÓšX&ê¯×/¥NSìR ý$»ˆd¨þtõÁñõ“©[öGí#n Á&Ä~ù®»–0 ½5>lûŠÞÈ;æ³y*@ÚÇ–n¶¤8t–Aô£Õœ+Dv´B×(4÷¾9*{íÔ˜²Q_~´®žß«ªÃpC5Z´$Eˆ“½_ÜÌï·2›òY²±²}yttbmj“œHÇE\µ0 µVHˆ’"Ìït1Áú…XÜåAñªyµ÷Jñ·Vï4R›HšYã«ÛÏ%‚ilD7OcUtÎëí KHëƒà=— ñ$BÑ «Ï¸pÿÏåMðù6'¿ë¯~)e¿CQ/©×Nê៯í;£ÿ÷XÇ¡6meùîœHW*Ž_xRë R]x›MU‹jÕ)pæ÷Líµó“®.Èä­´¯¶,Ê44», èPŽ;²ïWãßb0~ÿ(üôÎ5~®çµòº%Ì‹a/‚”i%ˆ¨g…j3†·Ò×Ì)aa#>A¦wÍéG%ïS&ùÝOɤ;]6h‚־׺˜3˜?Fô^z¼²÷;>·3 )M]7G#̨*ìKÑÞêØ°¼¦P5hÅÈË ¤(ôùºõëUÐÓM èbÊÛXß;¿i%ÝÕ[J¬ ^C·Ô>V¤:áÕ“Œ ç†Ôsà•~Š@t:²áQ0[ñ É¥ Pèý¢"®‡‚¾5Ñ)*×åJÿZKîþ¨½SzêÒ ÇS<6qîV)\PJÛóÙ—€6d¢¥¼à 1aRgv½¼?@im—e„¦”:F2žex:ÙwT 0÷ŒÍ¡X7Úøåû&®ßç-³\½™¸g,•ƒ‰÷ƒÏ¶pºÁõÅÝa ¢A-Ñ4£x[äÁþEȈ¬‹sšç ÞD-*DQyWr¨“þ«V˜ÞzÒõD˜sн ¢_L?©~s˜c$ ¬ ÚúÚµ„ô„N“vbÖ,u Qn&¢+ Ì‘B¼Þ( #°f'¸-Òµ\¡„ds€©üƵ( š×”Ýdzt¹Mn —âlÒ9Iíèè\°55犹Áh§ûWo3•M°!'€x6¿ó-£¾9=rÊ–TcýÖw‘3¹õu ŠÈùð+‚)«æh½–îåëÔâ±fåÅ…¿©-¤æ<¡ËO¯Y ,þú àÍé^ŸøõEêõι±á" ˜¡_£³e2`Y‹¨ 8`ÅÞ iá$ Of&H©á¸Ú”úûfñÉ™È Âv$(×ãå|ßqõÌ0fö™<-°i]&ƒÜæ”ù>‘ á#¤ul/c@§U¤¹v²å®Œæ×7ö]ÖfÓ¢Çàux¯.2Ó8:œ‘ÝWÝ?ôË[¶/ºÞ ÜÉ´5MV¿éï²²ÒyãHop&sÛ:›:ÛèÃËZû”ÏçYÙ~ÃP“jÀ§í†@n%JaP>¡Ïa~½‡Ï™ñÊa€OI¾qf·Ï0@âBdÖÓñxkýͤ‹¶½ÛD„óœâ*öûÔF ž½ß2 ”)в+r3£^›Õé(¥ø>€ƒU¹º̶FŠ9„a÷4ž e´ŠsB3ß©11ù2ŽvˆV4^¿C;ãFéÜpÊÙæ=Xg{Œ«èqSaû!$<Å °Ø´"T‘†37XY ‹žœøß ‘hçô Öâ\<ÿ}*t`Î-ôæÍþÄ(|XœÐÊç~Ú¨Žël»’aúH E4¦šôýlAO g÷»­%ÒM\®Õq:¥¥ný§E—a|ÂДN1n âXVâÑÃËú&þ]yOÕú;³ü¦A‡¼ò¢¤S³H-¨}â0Ηñº^½0O_ñ>«OÙqÑxºNŒŽ%qò˜ªáŒˆ”_xXÔU Q*ã²7ð|‘°¥ÅyߌfÒ¨7ýÎQ'{‘nBå‚/C2@µDë»ÚwÌ:ÒŒ˜ ‰FBâpþªE3¡ùøVûÑb–“ÄãÐya"ˆ¨ÆÌÿN•UÚÃø7»áblh!Á­¦»[“_án8†üÚG’˜k¦êþÀh¢ú%™½thïCÀÓˆ]ëCS˜@‰šg.^Â\p±nÌÉLÏ¢±‡tùÉÅ õha¥q[…B= À!ž¤ ÍïŽû»Ýçé\VZùM"¼O6Ñ[î"³Ý9Ê{*"èfQBÜ™2¯VŠ B‚Ë~ÿ¯ ¢DÑq±@Ý›¯hìÜ䛞ƒƒáV†®XL£ìégfc°ZÜ{èâÑag öÎ¥ö`¿ªO×>-l¡×h·nbg™/ñq–‚Ë&ŽK'ÏyzÊ!~m«pJŽVGÌGÅVt¢h%I¢‘V¬aÔ±¼žûò{)•*PÕS ¶W“Û-{p…Ï´ë°\PÄFwÔ@ýÎ#Hhr# ’ÌW` |”®]IâQûZ9OñÏq ÕÕ›ë¸Å`ÐC$8žØì¶ ºèLÖÞþHê$ü$i¾·]wvÁÆ#ö—ª»ržÒÉíÑùY‘šk=}¶e®ó–’ûI³Të»ò=Ê‚¤_MCy¨ƒ}ƒýÙÅt£S£¶†j½Z¼Hn+Ù>4 *–¤`ní<Ìw<†²¦LŽ8õ¨¿‡O:|ù!'oðy¶k3ßÞÓŸþ ˜µ6C쫜îÕØˆ?…iy¤1ä½xŽG >,‡¥ØàS^έ´ìå€(’ApŒ°ààãÊ£”~7Ö)ºpŒ‰Yk|Ôæ1Z}ª—}¿Ï·v"·R]¿&Cýмö}£Ê-úÇŸoÖ0PG}¡ A–h q‘d…Ë6ãê=“ÜÏ‹‹žàLrñN=¡J%‘g@^x[-ì¨ótüÊ‚IKgî2+Ó©¢×ÏÙºƒÓXÍ„MÁn‰¦ßË×Px“û,a‘ÑzdLgxe&Î#¯+Chiv‹ºg:ñ Áj¬ÆúٽୟFüÊ;¾³³zElyU=K¨ILÛ¬e½IÏbÿ8£QÀp÷E~F¿ŽWøOGÉ*ˆ•”}Ñ׳åTФ>;›¡²Êi¶©®4ž=JÊ„6®¥õÄ»>NMëJݖļWÝ0$cY)`‚Û×>/ Øîó„ÅŒAÀ ßìbøZ$„‘[($–‰ùüèÌ–l®[0 8ʨSK`v6´k¶_D@׸[#˜†ê¡cHqòÚ²Wß{:¬’MÎE4o³MéîÉÞQæä‰ÈJbSë½½FëMåò•ùdÎ߸ÛÌóO'å<çŸïP HåƒPÎ(§ævO,ƒJfeâ•6I.ï§6bQLÌ,v¨m²é*ý`ÿ†ÌUÊÂì.1#m—x˜\K›S¡BF [•û€WF‚24Êuˆ*˜:é\£BȆºñð)aÅ{­û5—&nÔ¬Â[rÖêB²¨@Ù™>8÷ƒ¹?|*F¯‹ÁXíˆWãGèóhî$å hm-?‹e–›¬IŸ»ÈtŸ‚Ç,½0—\-‘®Ã!Dœ*H*:ˆž¸=³ïµïÜuØ`ß‚å&aß^‚j†½(ƒ+»¨S½v­DŸ¸g^tã[‚Üh<0%ê+ƒ¶ÀŽQvþ€  ×ʼ|®!ðÕ;­Ç>­&”1’@z ï¾.1¦èî6L_wo ò$KG,ã£á”Éflì^¡ín Êø Ђt9™>í­Ã} ¸WØÂî—+Ü!ú· ªÁj›çLH›µ4#y«Ò:~ÚP€%Ç’™h©õjÃÎ!„y¶(9ð¡ò3}"¶±Øûú «ñÓ]Py g’ÆÆMTQ¯ê :šІTé)~•¶ÝòП6µæÁÊ*DÖ_x‹f v¨5Zxµß¤ ä3+lËè+%€‰¶Žh³'co}EóRÆ6Ó˜âŸkU˰Ü<…ÿ5Ï™¥ý–jTbù%)¡6HújÀ2&Î+8cEH­ÔZ¡RwØ·)&¾¼½X®ËÜòD¬ˆ„D½ÿ†é¡zúL¥è`q[¯zÉAÝõ JBè®óüKÇÁíÀ€J×xMá@ Úßhñò¤3ªxˆ?FpþãkfºPEËÞÚúÙs©<™€²ÈoU$¾èØJ§:OßJ@™‹¯ðú|ÿW_h¯ðð"ØÙðTÜéí²c˜Špœ™r$Ãʺ{ÏÅ–5ÕÞ )W|;ÚËí©„ÈƒÁíÖ´¥¶~«K5ï}†Z³Ðmüe&8ø+@ ™õbœ3th’Ù)W_Ù;ìò·£3ÍÄ$#­à°¥ï$S'.)zÔ n<ò?Oô©*ᥡœñ´w¸‹Þ÷µ}ŠCÁaáÞcÕ¸6‚b.|ÛV)± άE ”ÍJão\žà |H_ÓdçýÁe”™‚iQØÄ•g±ªoœ¢¯„OSbù~Š‚²¥¡u~éRsŒ;¸õ‚0礨LÑ æÅ/LéÚSg÷rË"1+ÃC¢˜WŠþU Ü­Å„í´ÃÛP eðß.(FÅr0d¨¬Ðd¿•¶2w4 ¿'sÑ.zü¤¡í–rÀ˜ÏmY¯S‘?<Ó=”Ì;Óõ<øÃ2ó¦×®¹b‡¿Æ­œüÞâV¸sTYÙüŒ½u¾÷¥*Q“ŒVá[9DÊ*ÚûSÿ!Ál¶4ÞÀ?RïX="QÝÄòEÔññ@ûcšcµ5ª—¹qD¤ ¿/aÑŠ ªŸ6³ÐÀ‘Ö¥"P©0#°i@°eXÞ8”Û.‡ xšó­8¥z8Ý‚x½&ê›Yµqœí´Ç‡ÅJ '/w¡6R£>y›t#×ý‰ðÓaxY°Àú¸£ü”UÃPŒ"yh¿×êøÈå^ʨÙ`n’ôî÷ñ-{‹Æ¿âTê~Ì@éÃ@“ÙC¿d½|Ÿ<ÖV&r5d„’Wÿ:ËŽ¯òÅ7 ¹¦I‰tø…6dvdÅm*å¥1I¡¢¤®Ñ{.šÙ #lá3þcÕm݉žÒ@ߘ4=]þÜÜnŒW¸QWþ¡ Øãóœ¤$¤“ÜÜo)«ÄÐmt“ÑoÞÙo¡ìïƒ^jõQzPƒîáÂ8ŸºSÐ×=xÌa…#›;ÚÅÉ?àðL¸˜+B->,OË‘±G—ÛÛÞûE1·E_|\IxW‰äðÛ&RQ†RV{9ú‰Éqþ ÄŸ¯y¡EÞ->6¯®T â†Bã¨D¼À“Ê®8rìsš™¤Q­ø¤TÐ\JàÓÞ|~FÍ€³1àÀÕÃU~¡áÐ7lØ1Ñ8 º‚ã›CLí¸EGsGîxúcüZ9'ä!#Î|wx5?Œ ™„ ¾ª3:òàß¼¶©8æÇ3(˜È>µK‘š¿:#/RU»;ÞîÞ>b0¿ äy‰K#o¢{ÌIŦ€mYÕ.CzŽ|8ß}?&G¥·&¥²25$z”1Òð\Â{á…2N ò­ãGè‰yÏf$\«æ÷€”,ÍyÀ"‡*3h$UB¥.öûªÔÝN[‹ß3dÀWs¥3š}­Ö¨Â$˜ã™ý†3T$I½KV}Ú,*wìBÆ&˜ñ„鱎Õä°Ä~ü’;Àl¯2’wò1ñ·×Å8Xª•7ÖYÃmKRB+_šbÔÁ¾M@çwÝ-Ùò¼Ù¿Ñ¿ƒšJéÄbãYè»/5¹0`œ'(Ü ùë(nMøøÍD%uÔÔŽfõ:áÀQö˜­¡]¤[Ýí–Õ%I)óÆ@íû9 ;è¾?3Q» ‡¯ñ›è·îúNÁŒb|Z¨¾½_âo~²7Dcqƒsz¼¢Eæø½hLJ àgùcF–Wó}F7å^Š´XAîÃUÖÒVc«è–T©=Ã`rBη¶y")[Ô!fÓËæ£³š^ͯ(dQä}=šÎ‰Ž¬ãòé#|Ûkz¬li4YHŸXç;- ÑYG3MùX§f#¤µÔG}Ñ3³üúTA~=ªs»åæøÉv..ñšé4KvW\­ý'lÉ®þ½9¾`VçlÙcè—OД*=llÒ‘ß¼;¡/Oì{±¦C€â^î€äv´³w—©6)7„¼%Ì'Ëþ¬Ýó±vèažšÞ¨‘¸.ë‹È­HyÖïLjA; ¾Æyƒ‰ñv_–ÒZôû˜Ì£6ãcRÉž’DÆúÎýÜI…-u>.1/ ¸ÂW“÷9ë:oý+ΰ5°vÔDïCPtº”ðÞž _8‹³Z ‡öS--µÐ5‡Ÿh®€€VÎRýE óµ?ûÑ<‹˜u˜Ë“Û¼!Šp¬zN@iæX¥'%ºh³íÍÆ"ÇàgwÏV±Ÿ'äþZùA労¯.[^:…„N-f†Þ°”cñÎéz’¸üÅ4QËéLˆ~m‹¢,9èE¨r.»j`Ö–jjU k_ƺü-Îê™>§mð€Q4a{1:Oþ {4hsç·@=±ï»zÅ ÒÈ“ð4™ò4„:êá(Ì>!¶Û²(…”YjÌY¯?œ·h[`“ÆÅLØ$E~#¢­S-RfÌ­œý¶^AbîË+ÁìÃõÏàÓµ÷SY=êßaÛ§…& ëH;CýÄ”3ÊÔéDDÊí:¡2—zí R¤ç ÆátÞrÃOà³)«)\u!%(Žä Ö÷0“§üâŸ+kYnVëø“qaKŠ¡ˆå³õ áR†Y‘±½ÔS×ÊÞ’Û !D2–Á5વ"÷ÝÔ`ÛYÕÕÎmé 'y*kÚýzfqúj§œ‡bæ÷5ÇÙß¡½ócÄÄÝJ\-§a3+B¤blWØ·Êx¹±8 ‡™½ˆå ºÍ©’êý…W»X‘óÄ‚l‹ÞÉ­tê;Mîé!í¿˜u‚½‡cà¼ïöã3''9 wg=é)]Ì"\æ €¿ŒQPZcЬTž‰s¸ÐÚQ'Ùb^?#¯¿r‰$ï‚?«ž\1;›KGs‡¿„Ø^©˜–L‚Ø"›êéˆhëC¤µ"Ú&ÐEž‡Õ™7 ƒ&Ö[åGßH1Ip ‹©oJa©7y²õÚ_°IݧçÙªn¡èˆ¥oï¸OU‰ÿ7¦£Ù O¼à¶Ç|!¿€¥•S¾4‘Ûø_æúAL€‘¡¤Fs#}b~Ûâ•D¢´&¢{í×—RÁvÕ´"Û;¤q,<àBÓ÷ÃÔvá:\Bx .dnë_c|,1†$M>:‚È8Œ>™eÑ9úTm­…+1:”ÔÎZšs”é}dJWø¶t5ž3öÔ# Ù°…_úÇr+/8¯‰.2hê‰Äêb( Öݸ&l|ÁGò1‡á—·æRÓ¥B"¥š1W÷™/ð­`[a¦4ó åjƒ!§ô[çOˆ¨‚†#–·í­ù’“èã¾H{ާ¥¶Õ6è‚#¾xþTä}@úoçqJÅíÒÞ¶lm¢äÌb–:ç†ËRŽUpã€#vÔÑ€îþÁs¯cØêz?êÓn¤z$bV@÷¡Õrø4¯JÔˆ0‡½^ô T)WÙ,_Púöf8âUì7v}™&Pg$°ÿIý„Ê_Ç…¶-mŽS/ïþ†¦ óÓ,ç#p>£ðç:Ö£XoêXv-ëàÐå©´m:¸$Šòȹg› ÆHiwׯ»`#µòÊE}8[ýXáÖ¥ðWÇ#—·L=ú¾ Õ#αü(Æ—Äý [U5ë!;ϤéY%\ôš`=‡nDPô ™7â5Ûi³þ4Ú9ëŠƧó§ÈPïx”«‹úˆw–³iª¾¼d8T?~,ü×€&Õ´Q²zå™MàƒîFipò 1߇ü/ø¨—v£8eꂬr88ðßÝîh[N_Öú’àúœy­ü,d$¼Æø¶œ>‹~|Ò&7:OõTÝãÁ‚`.¯wÉ×§ŠØ{¯*_ÙpDgp£šT|”­*àe¼ïÕ²x£ë¤3šÆ•Bã?p<%uõÕ°üŠæQ÷Œ¤Ü5'om‡¼ëRá§¡íQ•wHD×8¦}”‘”‘ÈëGԖРauöè©»€×’@ï ®bK ‡Ë¥>û\;öQ_ɇ7Ί81Û"WbJÅ­iN8B÷ï,ŽXrGó^‹ï¯IXfÏ?[ô+!#Žá’s1rx‰{uZôµ;¹ÖM“’K’Zâ¹+ŒóÐmdÓðêˈª-=W •µ—¾ Š3ïÿËø\Òhdü5‡s¿~·žÆ n<}ûdÇíéCÀL$%¬GƒDDlùõmÚ‡oäÍJZ|Šå)9:] #íQÕ¢Ô{9/MSoFð)Ô@8¿Pe´è'€ŠŽÍÞ¥`_I˜aæór_d9˜%™…Ï o±£„®®þ«œ|jqoJ{“ ¤iZ0ö·Ôy&Yú ˆ'b‰ª]‰,ü†ì¯Ëjù ó~õà ½ÑNþó].À?R?sD›ÍbºFÛÕ(MÆÈž³›ÒŠz©|!oAÂGW4uXZí÷rp'&\à•Î6× ÈN¿íãò äw°Mû‰rõ„ßoª4Ü `;ÊVŠ¥þ#^Ÿ¬ÎñÏ"—È{„‘|+Ø ÓŒw…‡•‚Yǃٗ^>CBèDËUAdd¾Õ_!`<[~­`Š_jZÆ,ßu‰Z²7.úÃ{¸ùU'Ï¢—ï/¦fùxgÈfs˜õ! OÿàÜåö£¤WŠ †N»li"~l\Õˆ­e±ME%ñ]hGBÇ É9ê±cTsØ×Ewe¦g?Œ¦ Pôs¨§,V—ã±ßO$ñßÉÔ¤è¼îJUÃ{×ô=A}/tùK¯“೉ -!Ý{õíÂ÷ÅÆ÷/“úŽ@«Í“R5’ÕÖé3ôÉ”Õ@ž÷°F¯à½§hC17‚5œØ˜àA[Ëpwç%†²ÆW?¹ÝíÞº}„ë¨:¬¤Ë­¤è4b‡+oó÷}Hº¢ÎÂ5£¿HuïqHQ¡Z.kŽl»xSDVðO… N뻋n¤3XphUš¨£IyÌÄ‹µ7I'ÆÈ’Ž¥\> *y2’œ˜Wi6É,í ”4iÙ‡B¬©m‹ù¨i––’J ´ŸpI\ ›Ž%£š¦!ÀÄl {O"¿É‡@cù2“Òû|Á=;èÖìq°R\ü Mò$a‹4ÎÏÙØÊØìÜ =wwÔ‹  §ZaÝÕ³÷ÔhQtõµ¿O£Omn^ƒµ©/Ù$LbNŸòr²â¿ïVmÅUûºcio?ª‰@ >LHáÄ¡W÷v„+‚‚øPúŒä¯zɤoŠš‡–_y Ñ÷Gk–x³ ã™Í€mÒg`@b{@§¦Э$ Ž:aÞ“Åjd}×÷`G+E^¶‰$|øí}!¶R0ÍJ’Ñ#@ŒÛ;Vâœ:-ùöÉ`–*iJÍû§/Lýd”!6W$ÜŽxå6é|Åysç%´%<8[Ë/W>5~bãèýùಇ‘-së›YLƒŒ ^)ü+õÇÂãR0X¥5̬BHt´¡oÔÀi€uNi/ÖП´Ée7”£Ê†­*'Ÿ£Hk´Ûk´'ÁJ]|M T\·÷Géàû[rvêí/ ¶… ¶ˆ{´Âç7m1Ö_ôßî¸õ ú’Š:u «é«oÕîÊ?@†uÕ.†?%uœðs,në|Ó³ùý í1úÆBÝò¹‡o‘¿M¬ôO²ú¼’꽿³ñ;NÂEoÍ7].}›P®{š¢Ü£ëô‹o§ïu7X\‚Ó@AHEÜOƒX°räòhfÖwîWêÍ>{{ƒ'OïBqº¶p¢>ëwšeé¯6.ƒÜ\Äz¥¯±ƒ ô¦09‡µTðmbUfORÖàE[X¼êævj&9ñœØVذ`òÄÕEè=n+ð®P²œÌÓP²é‚LÑß´ ÝûONóé˜~®ÞÒAäjµn¿-ß%îuáçzÐþlU<%d± <Ï·¬µHª…Ð'ŒzCuy~…€ÙíOí—ŠÉ,÷ÀÓé‡Û ý’Ô‡É$Ü>œeþ:Â'¥¾€3›™½ô±åsf¯‘J[“f›3AQ=ûvº'F¥š§™ã†£¥æÿ\¬^ ¢UùH<Ä‚Z:Q-°Ôk?qÔÀ§^µª –K3µA–†-äñô<)ý°FIµ1/ûõõéçÙè']»ö½‰žTe¯Ãz‡OÌå2꾄`%0 +Ó–¨Áxßk™P^eV”EL-UeÏ@5½ˆqPJRf×w_5¶G‰Þùb 3£[Ïë­åU‘£Ÿè‡fpQ¡Øœí®–Ú¦ ˆªQ*‘ä^kcÞ]K±¿î5m)¬ c6&y ]ék¯F¬ð P§Õªs=NòØ’ž|û)´WÊ« zYu¼æBLÊg0þXûh´”¬ûV¼'@i3ðJa—ÀŽLJ‡ú¤ qÂa±.Yë>o(DJc#EXóYe c–\¸TjœÐyϵ«2Ô#'ÉKD¶o¶€w·þy(#n/‰¹géGßSƒQ’$`ëM9˜ xvÙè ™˜Åôˆhlä·™± EÒØÁª£%^u£ð“ L‹N­;]ÂøyºLÙ|èGør(ûò¿Í¾?^¹²§áÊqR¸á4ÆÀR9ဠ«!F=ýó­¨÷øTâÇjMw"¾¯Æ¾+ÊW™.A¿P\cÍXeÕºÍî‡@;‘uÞò®ÕÉøþ/,´f·~í× $B¬’Úaˆ2.ÜûÐty²!nr+ŸE…E¹×Þ÷±RjÒÓpè¾&r¸Dn¯˜ßRCV>4ýʹ¡¦Ùa-Ï b Þ%üa#eÄ–ñ‚ð”¡!Ú~¡n¹Nƒˆb)y|Íøü”îbðîs±dÓ*¸¹Í,äØîeo«µ65Ù!A»t-ÞçQ›9ŹþT kúþ¶@í\»‡ðºqà>*ŒCéÃÝ-10Qk3ìô²æ%›8§ähÏF{7øEÁçé2_Ñp`MÚ+â4ÌFŸZñ«ã–×€E¼ƒ€ËÖ-›“Ùæ±O¬ñˆB×çó ú]ƒ}‰|oW£©×]ef$3Ò¯c¹B Fò%;ÛÊ`žjÆŒ ~«ø±1ÓNSœÑRC½¥”ÅÂ*cDú¯Pá8Èp¶“+cƒ]9¸rÆÂ‰ag„䢉L·ÏHC‘Æ’¥]^û‚:úR}]¢â\lE‹³¨Û%Æ/ŠmÑçXuüEbÑAð+_,ê÷?²ÜΤŸÉVvºÕ^©­<{f¢ÍrÕiÒïM$žUSl$³”MðŽ]sè5î„Æ$ë‰hº±ZÑ&*´ ¯gÈ9|§kàÊ%M «g›®ÀuÜ}_Wà h±´ ÛYæU\´HbuŒÔ ìÌ x5¸Á„^q Þol’‹çwK„SÁEB`ì™UÌ„–¹D«Ek8»œ¨Ô´ë¬×ø¥˜û{P‰âUu•º{U\`”é&—½­àÍ×äÄ·Ôù´õÙ~Uð:$£¤#ª¬>øå£öv,—Aˆv‹Bn,ƒ]úMp7ï×Héâl²†/#1[Hu½§ZªEH·­f7åØÝ·Õ}nç7ÅBòw1•/!šöÅQ,T_¸¿Gû×~‚¹°Z>±„hÂöë(:ŽJ"Ò,qæýQ—P2ŠÇ‹Aè75šÜúÞó•cñÕºíÏÖÞ1CÛ—U?±‡*VÇ!;ßRv–k©u­k´[W†Vl9VO“¿Å’eˆ‡„6  Š^U<†ç«µ¦§ÚóO_ oÌÔÓÎwÊ@a˜¸Å«m³õÛÖdÍÞîTæâÛX¦_ö¸`OÀì.æå¡„¼%KAë“­¸yê’E×$Ùq„fᲬçE¾«fÚ‘ePZ&B‘`¬F·-Ðvyбcò‡²nlß#×àÃÕv ý®,'Ü0®áÇ’úÿ RÃy¸Åôÿ,¡G7A×ZP8Ëú%¼»åN–«àvêFzEåЪ݆÷ǘléìî=@œ6cÚ+5%¦mzŸ Ò‹þ…³¸±úê:˜Ð§¸µš¢L³\”ä%þ²Fƒ˜*Õ.–ÖM*Äp¥×goÚ``O/[æ?Þ=ªÖóJì"L†ÃáÖ@ ódž\/eìŠÑ¡DÂ'—p>2Yà©iá{6ár¨ø+½ù%“Uy`WáJ¼ 2Eç@Ux¢ãËÒ±•ý6ý”/”ÒÙõ,‹†5 ¼ÁoŽNL¤ßUy¹7´„=¡¨)ÅDè÷Î$¼Ú#î·ÌCŸAn!h—8Þf ›ìÜ­¼ÒïËRëİƂZ#€”°%ŒµØ_< hc.F3<ãpšKšäåŸñ(¹4Ü|¹Û‡÷yóWˆû«ª‰ ñÎ ÀÖ!é¿£ÞœªÆ¢EÄèªÚmºŠ„gò`R•t’GÊcl\ýØ%[Bcõ/˜+RAä ~i{]Cli[ÈÖ¼ÀÇÿY=P¹à kAnSÑ+rˆ=×[ªXÍÊEpÇÜê¥VT^ž(¤6 ×'唺Osᯅ¨Þ$Çóû¶Bê?xeŽÃå]ó<ÚJÓž NÛˆþƒb‰š’陀¤JBE/rv©#ò¾÷;ZD?uìd>XÕH[2ÜÜQ0´ÛyB×ä©Kä áy³R¤è Úô ÚŠ—7ôv¥U¹‹47é ÷&È3P]ÇH÷íJpµÂ¯¼nƒ†@9R”©wpXÛì]ÁE1—ñ?,x0š‡_8&y˶¾ñÀ* Ξš½á°~Pg.%5'^Z|•M3Zûxï¼4­føžv„r¾PoJ]v¼ªeÛŠr¾‰2(”^éq2¸{B'Ĺz§å¦7YZ‹eñö r™:¸úU™û[*”舂ʢùSïO²•VøxwÄH* ì8âÀùÞõf•¦¼ðÂíeì{žÂ‘ݨ†G@’oõ(q¢~… ›¿%3gœÈü¾ c*j‡¤n·@›«š©6^ïBŒ;w‚658}t²~‘ÃÅ¢ÎÇzv¬ÿÉ?žíEØFƒÍ,ÚZ:ÊïGàku2|ôN”ʱ²zŽ“Ìèð™ZTWµÃNk•°„ÆÄ¢ŸNl@V“|¿wRðè¾BövàÕÁd ©5a«<[˜¼Û‘éb‹vŠWüizj™YÌHLMZßÔ/ºì^ŸË®ÃhW2‡DÕbñÒ›zÁì¡’¥Œy7Sðk§ù2®Ã|µ=wØl)Øîð”x¥x<•Š6÷´Øh ÌF9Jûh0• L÷ð‹¦ùÓÖì«ß>^Cϲ^"ïBX™P—þÀKÙÝýh@éófô "äFZ5.‚œß‘ýÀî)'µx¡¾×E+¡´LG@À“1±>sžDMy¬EXµ/ž"sÙg01Êga[ÈàÝd£ùÌ:þ¥ºPYãr°Öš½alMéÊÿã‹òšøbYZrLÕ>n̬LiMöËÛ¡`®f–¾ëúdùqM¾Nü:i‰vÝ ÁaûÜÈTW‚|{ÕŸ2£3g:öõ)ŸôŽƒtz ÷´o Žù±ù1å…‚’Ô0/`ë%¾pÞ Yw`Ö…bªƒ;;rªé´O¢®Šá…·p«*ì'ï{2x|sSdù!½-DšÁr"¨5AwÈ^~7ÙðÒSjZ®òæÜƲ^â§ÿ²}Á·˜kM²û«;ã#*×jÆ>[iQe±Uw&¬ÀÄCMŠŽ·ákµR‘Bsž;Ü,Ï´úƒ°CfÇÇ'£LãƒÔÇœ«×Êêè0`Þe¾º‹é­q½ ÇAÜÂ2Ø-õÚÔ„¡¸­noØ'r¥Xµ4ÉFI³2ÙgMG %Zër·IjqPmTŽðÞËÅ„¦}ˆ}±„¼‹Ã7–‹ÏоÎlî BFÁ€t”>[qDЀŸ&ò6ò3¬yÊú7$yšÍª¶½b "æ+rs¶“h#LsÐBÜ;j-{òÃ}N.þ-ü‹CNÊZC;ø¾ÞÑ!"Yr!Nd§Š݆¦ôó¡ékRE%þ±—çRòQžu¹m¢î›@i G¢B[¿àË–s‹€×‚-œaH—— 12v ] )PëçMpå×÷øŒ‡ñÖ&}šß>¹@›g©HFu„ ­ðôÕf>ž‰§™à7àö»”Mµaû-÷ïsè„HD„³}½ ÔHxÉ%AfɇªŽ\®UÖ1ð°Üœnå&\2 ³Áé(ÀlU×k›«@ì/Ÿï“BCã_ÌЮÙ6túÀ11ÔS HaHi냓Ñ=´9 Äò=ÛN:ÛûJ6 ®môÅ™ÜJŒ8Ä3 –?ýŸ.?þíÖw#ãÀñ3³gœîŒ ™©3Î%[2NÙ²·³Ê8Žl‡CÂÙe“½EöÙ#+ÉuVÆó{¿ð<ß¿?/à{¯«9)¼dÝ KD%[àþÕˆ.cÿ°®Q=û¡9ü˜Ñ)‚GY]”Ö®§×§§F àèmñÔ|n^Ƀ£È&Qot§}âO^AuS[Ç׎™†B2õLËWéR:ãwbc`-Uxó@‰€Ð¥gk—adgðyGs*A`6àÈÙ AW·-Êõ4P_Š©ï[ްª$F5’S#r«tŠ(»}‘)h1°`ÖuLm¾†˜âËŸñÆ;Ï)îÆ^Ï;?b:] Z~kCi¸L¥‚~¤QNÔ ‰3Ž•7whžýQa!ž ˜iô”AÁR¶)l©›uÜXWŠû M¸…ü”]­MU©Î;&‚Ž¥D¾g PÀKôCâ}0³Oürc ƒŸ ™Hs«“+RèL)-‰÷úÑÇÈïŠ?³ä``3ÆB(½Ì§ú ¾úˆƒ«„ƒõäÂá8w§Ç×”Uœ4›T~6臿<# ¬¿6àéÁ‚7{$=B Ö“.O)>°¹Jß"8îŠÍu‘ÊÒ=zÑi©(#£ø.Š#OœáfH”iÙzÃ:|³'ɲDêÕ9H­V7ÃÌTG+ã™3¢TÙüh :Oê½sD•îI‡ù{¦ú¼Ê¥0‰*|é$J*BdB ÜéÔÞÎuí˜æ¼Õó\6UæñÝBŠž7Ǩø5ËŸ#y_¢!Ú.÷Su©ç¬Ñ1˜Ë¼š‰FÐuh2ãö¥3§Ü­1bË”·b¾&#óŸø6OïÍò–o²æî‹¯¿ŸO© »}¡ìm^ŒŠ×ÓÀîÔnÖþ¸ TĨŸŠðK×áPkÏ¢=½/¼¸¼*É›ä…ëu)¬œJÒkhÅ#ŒrG5ÝÐ|ïƒì(9rHU¯©í¼ö',£TsÏ ÷Ômbì½Rx“õTÂg‹ûdëqMS šÅqiÁàqýöKœæÙ žêh»‹(ÊGæKG!+4´tÍ“e-ÄR™¶Û¯Ï£›ËF‡Î¿þxLrÞô9)R¦\òùð˜Á"ËT®B*«U t4=¬ùm±lI˶hô°áöuÐ]·Y|‰GGõÆLªõšƒÕdB²–ja#¿qô'GíÝÚêþŒJn‹b ´$Ç©š>³ù ÷Ž"ùò°â47UNdë·/Nmœ°íb*ƒ÷ÊšI‡´k0 š…¸["=ÏÿÝk¹‡qçþ8pŸåUœb Ó~òÕÄ8X= xPvE)Ç]1ì`$¶ÁBYÐmRn¨[/ÍGø™Ž~Ö¨!Fó‰|$ͧ¶?ÜynzËåÊnSÈh³:OqÓ±áó>ÏòèèÆŠ•ú¹Ý Sv§ ¹w£PÁH\¼ÑMr`Ý(Ò³GCJsKµ’ÉýŸJïZÒ’]“jš.²ÛäÏŸÈýнÞLPik2‚âÑáÅêóstÍ(øjjyüM%tHi’¾ÝQ IÊR;§£YA{Zc@šécÓE-ÂÛfÏôj 3c‘Ûxz¡^ßl³!ÊåÈ%€Zƒóײ>о¡0ê,5 £íC©6C`“i*ºQ˜öb`øŠ!Ýå¼ÊV%Ï&É,öÞ¡¿uµ‹V¥{Sžßþçï–GF LZuk@1[LÁ/UY»ìDr¦·¦^?ØÂ O·­âà÷“¿©–:/2SêøªËcp‘ [FÇŸÚBÚ«X`*£=<ç³ÚÂÎôbjÍW´+Ì:ðo.¦ÐÌg#ÂVfïfÌ^mM.,èLM“[«¸WŠû8†·Ä™zuûx~"øò8Jo^J$™Ù¾î%(òºÕ±ƒ©)€Èàå«n®ðÛn…ÜnL%/}/Æ~‡UÖÔÏèb%2øÿ=LÈ'^c‡cËL$-m^îª}f*’¾«Ê~â“›vø7âMiÆë@f©Ýü‘YôãÑMHÑÊŽ7=cÚñû&_j$Òé›$G^ªÄ×pÎvç髼Ât{Fvó´³v‚¿«à(ƒCk¾¥:VŽQ¹¡yüM4ž›÷l͉bÛ§IíÄâ ¾ò† µ‘Ï þÓù–¦Û­‚£ðN)žà”àqµ˜Ä{ÅsFÆÎ†_ùÂh»¢ö¨P>=UÔî•\6·¤†ãkÙ§œ%LÓq³Eȸ±ÙãÐnMYƒ_Ù«À©G¤Æ N߯œIBý¸Ž£¬‘–^ðŸzhÏ"å˜æg¶ßê#YqêüÍ(×ü»5cýÜ×ûƒ'îYˆë…"b€úÑö|f íÈJæøäCÏä8O]ÈÅ] ÇÈ#ûãSA"’ì§Éj„‰:¿à¿pÃH‘\RBœ3&´;z§Ù¤/ ëiÔK »°!ST+›x¤XÁXÍoïlÜðÏujCøøŠQ'àµý •¨EQñ‡Š9ÃÖ/!zÜJѱ˜j•òì;+9óáV{§`E_ÛN…â¼µÛ~˜•þ@Á¯­èÚ*Òõž@w 5ªÐ9]±{ 1°Ã‰Ë§0¬äêÕl¶)Q È1 #G)¥Ë¼ºm7Ìõ›“‘˃p㜴«”6k’Ì[l>Z Äy~Ê­Æ$uÙ·HwÑfÐ÷û­}+ÛPàì·$‚ó=öîÎÏÐ ­7 —4W¢»S¼°g5»p™hOàúEÓ_*&ùÅ ½:ÅXÅİ“ŒR¨Ý›ÃܱùŠ||cn¿°nÂ/ÕgDyä8_Ê“çwÍi_|Cë’Hû´QFp¯$xògì˜z·nËhh¡a~ITI’¡ Ölš]bcû\íx'WcËœâ$ù&œVîàWñó>e¿þÍ¢WA'éQd¤[iýKûËïs•BÎVy=!™’å{—{ª5”Û¤@IÙE¸Ô¾~X³ír¹¿TÂRú”‹4±sx—÷½S2±àöf.VçÇQ¨±Ÿ²0Õk‰~1Éÿ'šÿÿ*ðÆÕÎáãáfp¡ùŒ ÿÀ endstream endobj 142 0 obj 20209 endobj 143 0 obj << /Type /FontDescriptor /Ascent 924 /CapHeight 0 /Descent -281 /Flags 32 /FontBBox [ -199 -312 1031 955 ] /FontName /BLSXKR+NimbusRomNo9L-Regu /ItalicAngle 0 /StemV 85 /MaxWidth -1230 /StemH 30 /FontFile 141 0 R >> endobj 144 0 obj [ 833 778 250 333 333 500 250 250 333 250 278 500 500 500 500 500 500 500 500 500 500 278 278 250 564 250 250 250 722 667 667 722 611 556 722 722 333 389 722 611 889 722 722 556 722 667 556 611 722 722 944 722 722 611 333 250 333 250 250 250 444 500 444 500 444 333 500 500 278 278 500 278 778 500 500 500 500 333 389 278 500 500 722 500 500 444 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 333 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 500 250 250 250 333 333 250 250 250 250 250 250 250 250 556 556 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 333 ] endobj 145 0 obj 1653 endobj 146 0 obj 7713 endobj 147 0 obj 540 endobj 148 0 obj << /Length 149 0 R /Length1 145 0 R /Length2 146 0 R /Length3 147 0 R /Filter /FlateDecode >> stream xÚíweP\í–.œ`Á%4ÖÁÝ%¸'Xðh¬¡»!8Ipw·àn N H€à‚‚[°!ùæœ3õÝ©ºU3çß½»ªwíwɳäYïªj&:¨BÇÃÌÃÁÃÉ- Г3Ð0TgS‡8Z¸ÂÕ Nª2P+ €›ûÁ‚››‰I! P'9, Ð[äÀ–^^ˆˆ6@êìƒØØ"̺Úú,llìÿ’ü6XxüCóà ‡Ø8€n`¨³#Ø ññ?v| ¶`€5Ä ÕÐ|¥¬®`VT×(‚À0@Óõ¡K€*Ä쳬¡0€Ã_€%ÔÉ ò»48ç–4ÀÁ–7°»%Øù·Šà †9Bàð‡o°œ=@@'KW«ß <È­¡r†A,t`šP8n ƒ8#Q5åþÊa BüŽ ‡<¨PëK+¨¥ëï’þè`´Ä @€Ý¿cY€V¸³Èã!ö˜3 ò' W8ÄÉæ_°``ÌÊ ‡?À<`ÿîοêü—êAÎμ¡¬þ™;Xsbóð>Ä´D<Ķ8asýže'k(€‡û/¹•«ó?tn`ØŸ1? ËC +¨“ƒÀ lÍ¥E<„0ÿÏXæü÷‘üo øßBð¿…Þÿ¹çè¿\âÿí}þ;´‚«ƒƒ:ÈñaþÚ3€‡E¨~¯Àï]ãâ þ?|@ŽÿÆëï†úà¿2ý öw2ôÐi'›J8xx9¹ÿCà w°•&ai °9ÌÀŸu øÏ0újP«~ãÈÈ@Ý^‚<^!a€0?7@XˆÇ翉ø†ç_g5qqÿÞ ÷?~ÿ:™ü FÞÉjõ{f^"@NVcöOÁöà7SÊr•ór‹ð ÿ‘ZºÂ`œÿÙ­øÇùÏ5ƒÝÁ–Øß¦¡–bAv)驈j²ìÞ!9£®NÔÞ`ç¢:‚<ÿJh‡_JÈŠH™ùMU0gý°è]“ÇÔ®óíú ÖþNR‡gIàŸ¹Ô> ,Ÿò-Bl\¦ES÷ô#¼&U— rëm¬ii›Þ Ó ·ðÁ0.XüÜòü‰Ïñ|-“k£IZ ꑈªów÷€ñÛçÏ>éëíé8Bû´NÅ–Å$æöè10Üß%‹JÒP·Ì+”ñ¹ü—ABãxéaúy¯Ç¾¡n"È´óüZ9g„c%O*“bÃVž`<'0Ð`nïW¢:Eb\!úOy˾ ™pÝÝ­¯J¯”äɤ"ÃëJ²Xü’ ¦˜Yó·úN~zUº¢à£âðþÉÍUýS›Ÿ½ÝJm÷óîYJÁn[ü™ü<ÜÓ@‚ ‹ïyOi•fL[ù˜ïck‚ èÝñ«O8¢&¨z”2”2õŽ QeønÅÔ‹ “nGüî òxKºU‚¾÷SvëUd”rð5ªÛ°_i5¨ÍU¹ÏAosŒq¢±:3XȨnØÈhªÎ@»%E]Ò©-c%sBþÅ‚’ô˜£Èò•|vߨ¤†ßÒÖ¶tÐ<ßÒ·ˆ$vãuE`Nüq~‹DÆZë­q”œú¤\péòuI¸r×±é ›ÌŸõBBõÍå å/uÊ0[ߦqPo5Ö]0=¥ž1Ð „ubŸ[§¢Þv×S$ÄF–L—(è­~bü Ov =ø¥ç­¥¸4è°$w¼]loR÷tÐF3µêãü„¹çØs$_C33Üiááæ–¶J5èÝÑJf"éÍÕɽœPºš§•šB!^0ÉÙ;Y8÷N€t ‘3SÐ:ž0¢eëu‹‘§lk_p =ev!Ÿ:ƾ­ž¸_»ðsxutiOàj E‡‰fi‰ZDnó¬y> —‚æ"‹m.Ðln€Kÿåã=¿‹ÈëÔÁŒ²gÉ"M• ¹ß4WÕ‰Çbsv±’ÑÆz=ûäè$JƒâЫ¬œÄ~Çá„=Oëñ¹EÛüeyOç½zm¢x¼æ†›~¼@öê§MÕ—êG/ ]¼E¥|b.oà!§Rß½2÷Êk‡†¶½ ó×›efæV´¶÷Ï’Fd­15VîИ"ü‡ïë6œ÷z²l–SQr‚¤L^à>{Áò“«“š)V쳤®ŠkíkCà\íÍz5í’t ®Ý®æ@½ž•huK¨LiõKœÜþÄàv¥6hÅ€4F¤©6&†nßL™øŽçÚé<$C‰uPñCØPÏKP k™#ìµ?¼sË >½„zш·fÁÔ›s¬hß¹ k 3’­›Ø`#ŒË›Ž õ ls÷©]ª±zãFÚìE‘lS¥eŽŠz6v¡Çå{q×°‰Òê2ÒôTc!ÇÙŒ»#ÖÐü¢óÙ§—Hxɦ®OFIìeBªï Œô¨&~îvo·$¶Qƒ“ZMC{äñl{ÈÏ–¾$I# êÏRßMõŒÏ…ùëJ¢q%§Dª<´æg÷1q˜©uoë7ðãF¨“Jaä)zv,&¯Ñ%Ä,\W‰d׊1–’ÔΔ|*UC%ãšÝ{¢}nU۱΅ØÈ0þA ·ýYÉ—öìÔ(M[ó}²FàÞ©jÓKÛ\cg‹¬orÎ^=åE“%hÂm3Š Ì7÷ºNÙXðbwÀPöy©­bÊš†òOÅ-7ŽÖ©o3ñçQ"ñ8ñE€¦»lwü-žH½vz¦bÎʘgL~toG\l_îôeŽõ|U2GdPDßÏ­Š¼}X©lB/ù”ÐëHßkœ¸Ï¡|?·LªS2 ™-ƒ#ÖƒwäF4‰Ùpƒ>°±8doq lÀžÙ¥ëÊR$hN.\ê~5ö~Êô%*.9^º8ØÛœWÆQô‰ý{„‰§c×›ÊÖ Q6“—äDµ(Ë3÷ù7t]Ê¿–¯!Ç,ŽÙ0YåyuÝZܧé3†gömkÒXµ5‚(qÕŸÅX¾Z0¿¬tÛ·½äðöø:0ƒµ;í͹uö>Â÷«íÉw_3þfÇQCñ#&%ú:£v{µ½>ÖNÇÆÉxæoPºØÊúÉ}g‘W uþ¤ì×êPJ/š KÕvó•¬ió÷p˯øñ©yþF‹oj•ÔÑ0Z¾-øóÅ DB›E-SBç.óËà™¶fuv•¹[Ybí;GÎâ7›ÁóÅ çÉ>÷¤asÛ¹.öCDè©SZ¡/Ãß`°¡ fæä ŒŠ¹«5í×þ˜IC§—­¨Ûó Ú)Ê^½~ŒGµˆSù!åãRE†€åH‰Yð=2i<·Ù2GÒÛÛ£C"ÖGÑiÉ‹Åa$¾;Éí4åèŒ 6¯Uº:ÍÿoænÆ]Ù¢o¸_ĵc„ôV÷ª9¡0w›½cvT„äÚ (vƒ4|U)žñ'k’ç±KÞYrÔßèd—öÔ„ú}´õ(·‰Û&’¡„ e­Ñ ël’Œ²Å[¨³–ÛcÆöÅmny¿À«Þ BêuvdY¾HMÔ›Y¿mŽRG[}œP "‹By2ÆçÃ]Fâ'þ™ëzjÑòq;õøè§0iJ·9PÌÆ?þ]ðZÿ2ª¢™ñÂ/ýóF0 #§O`Ø›×ÝLÏ4¤!iÒ•xÔÂ+H”,AQO•¿WK^«_×RXÄBšRnm<nôH–f:à ²qu–ê ŸÄ@­ø^±íæD©sÜ;mKž)ªd|Û=Šãzí!Cªå‘ç1ÑÛZè ®í&¦Ÿ)/0xðþKj:P‡V‚;­Wó®Jlñ½ „8›•*"§?om²(lØáÐÏŠ|¥ï,pÏŸ|ØaþyÔY©õDÉ£1°6Èœ‚ÙûKOoAÐÜì1v¨³ÄÎ@òÅt‡| þ*¬[{®ùÕ88Åq#m¹I´Ä %EoaióPá “¤˜Üs3‹ª˜–¤ëfr^JƒZG×6,ÍÐû¥ øÒø™[’’—Ôê$‹/}Œ)–ƒbTí,Y3}gç°ØC'£0óô'Z)«†‰þì/Jj,Ë¥/L¸æü"ŠßZÎϹæNÆvý}0ŽœbuQ÷fÅÈ$ì˜Å5 œÎø9Etˆ(?E«å•<¸ª½[D;‘R}UŽAŠlÉUÎ8/{¸¸hçæ©÷t7*ZÀ¯îrÈMkn®.f¥]ØççŽäp¯™ƒš{ÚWÕ2-EÛq2ôç½7´Aú‘½¡È=ô1”y‚‹Ê{'qèþgÆsÑ­ï¼–l¶Wäì”zs”òÎs½ekr> ÇG}Ù7ò!Æ"€5$œW@×ùõµ|:Tê\sÏ2ÉŒrì©z¡wW;Y C·êéªé©LÎJ®Ð/¶–¶ç­¥lÐ8Ã^äqH.ó-éé®ã|´A^i ®oŸª)Ͼ¾ Éñç0Îìüæ:o3w@Xz1ÉÄî»d˜ ËîëÒŒ¡{ JýAÉ1c˜Êü©ŠŸe¿ÌÇjѪžwYJæ«w+´G«¹Þ¤5y¡‹^4–pËÌdÏÕ$}Ún<ÜU?Ð!/²Œ¥ÁŸ—Çl—6±ç³pð­°÷Ú#¥_ÊJÁçND‰÷WäZÎO= 5Wl2rÛkKIBl׫lûò?¼-ÒùfƒTSÌŸ¦y·AäÄûH»%ÆN*ÞØÞŒ`èAQu ðÉ%Î[·Ô›è8'¯)HÖº+žQI’×4²ý”lÑÛÅ!{vþ¤L­7É çùm1Jõbsëòyaÿd¤7D+{*G<Š‹Ûýrñëýªéjv ŽnœB¤J‘BäÝcÌÇs¢¯·…eç*œëA6¢ %éuÜ×7júc/1ïŽR âz2I2 ^Oצ¹)i [L𫨤KY”ÊÊ´(Åß¼»Þ:gÙ#}lËáÿ• ®^¸>‘;ŸøUçOâfìLjÌÝr=W)S'¥2úYé„Åu…Q‹4Ua5>c8¢¥QYñçSÕ¶Â|xE*DWÓ6Ј,ØÇP퟾$Žz?LòQRöl•Ô•NdÑyuÛÖ’Â¥è´0‘£Tا…ë{(×^ÐÄØ™¿‚zŸŠs”ZtEãG‚J¡NåPræÖcßÌ}lTý%¼œc±5ø9^n|ßY‘gÜ=ºœN©©xãÙ—îè3žL³ìÂÃnŒ6 öP ÷Ò¿.31EFOÒ¬² g‘gX›”+2è³âö`l8¿v¬yêÃŒ"$¥Ú¾‚FË<¼jhvéâ¬lyFùâ Ro¯6ÿ´Â|fš•O4«j:M%ŒÊÚˆ m[Ñl#';1 rUäÇ D©õß“và¼Ô`(×aówÆB“2Gë~m1cÿ¡¦Œe² ¢/àó”*=Ba9¾ã‹N•1Ö#µ{¦’µ¯=Œ.­ÅäÉè+×ÍÐàïq¿AaåPâî¡/㘴‡Ú%¸ÚðZ {på%Ëb¬2z"Tµ]åã,™ÊVörOW@õô–Y-#›}v)3‘û(ÃZþéTõÝ]'¾¢l!l¦‚xoêt[gß"Ä6ΙéÉË÷Aï8Ãw\Aå•SgµJ+¤tÚ}ò¤èéÌ3£è;áÞájjÑ­ê0ð¸ÌøÚ¿ê¹ù <¢~]¹ýœF’k×”'õWÑ^.°Ș|¨ù¹Á€ð›ØyJSwå|Ó±L½cw%.3Š ž1̨_~¥Ö•4ÙB‰{ì¾åòýë·L ·á\ŒÕÅ»Ë{‡g¼v¤#-mv•öS^™ù‰}üdW)U(ZIQù´[¦hj¯(u¨ôôN³Þ䑳kwíùÆÖjÜæ«Ömzn“ߟ³¼aw’çÊáÚÚ¸[Ðë7Íx} ,@ÙJavÌÈÈ* –ÏšfÖS¨ª³üpžÿ틜¶½ìÇQ³TåTËð)[À÷®·à÷çˆ[ñ9ìîã|€NqÞÂí@­ÖIyí4ó6$PÑCO¦ÁAÛµ\«°¿¯µ×8©³ç¤ûmAÓ!Ê› ц›œ6n>½·_CL¿:˜µ_8*¤ñWwtô”æþd{Eï%.µŠsÇ>4{äæ9l-жx,ܧAÌn'ïÁýh±Ílyމ̦ÂÚ.OÙô⟯GÐú»kÑYå\<5˜½#ýzžoâ,{Œ_i¨¾/ÌØ|2ÏER×–x%7>ËËaõé]ö˜Êc»=N§WÚÐ}Ì&K£åÊãœ6 5ë==v~÷rÒ7ÜÌ£˜QðaùדNÞBÒŠñÏ…^«EeˆuÞ~‰|b?‚ LeCÛ¡¬~ÄЯóC= … ¹.ž}¤<ØZ3WÕhBqÞúñxß)‰ÓèSÛç6oÿÈ®Øq¹]°Uª‡Gœçv&ÿqæG>InÂê]ïn$\)¦9—®ÇÅÁû_•PÇUt¾(Pœ\ z‹öó’1Yuj¸Yè¡ÝÓxÍi~–UÔxJZ!¨øÖf¡zU„I8²XñÎK»¿Óºn¢úáŸÙæìhG5s£Žç-þ{I·GC[´ ðG<Æ$Þ¾ÃÛ¾ÓsV‡å\R³4ð*BˆÂ¦eIK¬D—öe!m‰wx•ë^ÕÇyŸ¢ó‹‹çUæ?öMcÏÔ¬œ»†ªL-š;Î7½r`jîD[Cïm¹p£?ô(:“- dXÎ3ÅËÏVàThYÖ¥0æÃcܲ9u§¦CøëS²…\aíbr~® ÈcâIÉ lÊ· KÕJrì:YIßдN˜ðc‹Z»sÿ ’ªS?*æÌ$%éõT Bÿ ¶L1ÔŒ:HOùµ'|Æ¥f¬((Ù_î0Λž„a„µN´Œ"SÒÈŽÕu‰f8Äï™íÈbˆ êHÈÌR `âÓ«@“kzCNx5Í)¶³JÑÉ| ãÉÒ‘I»À@sXR%PI~Gç54¬3¤€²®Ó.ËhG(G0{·Y²½ ¢DnVUçA¸qLw©SIo2_ŒC„®ùÓO3R¯qó2áê;ÜK[N’ã•[«½N™cKÆe«XªûFªvuºcT®Oi ¿ý¨”¾ÜöU«KL¥õ±<¯.=@>C›ÜͰÃ(¼r‘g%9²¶‘ûþ¤J!cíp’ñcÚ è¢è†×gpLDžXþ©Ô΋•¤ìËû‘„ïŒSe«’œ‰ï"ñ>½»*jÜÍ”“Å& IQŽ,f·í` âóã,y2úš.7Ì<§ÀgàºNb›Žß¯ôEéÃdµOUöEîwïz;–½a)Âm<{–eWõYTG™yº0Cäƒïâ«–¬¬hOÛ1NÏÃû~i-Ô={ä¨ÁÖ,I¢z3Gu½,s{'c==™JáIP'] è‘Ö ²ª‘À‘t\ôm ÿè£õ·dy½Sh¢,ee]0±µÖÑE4]{ÕH¦çóßÙQ›F9w€iȦáÌäˆã…gbü΢:áégЕKçiCnÒ¥êŠÌ÷å¤;âWõŽº¨ƒÒÙ:Rø¥³ƒb_"×è§k]>æ¡Yo|†lW•-e§*¥Q¿«œù)Ó¨œLÚ‹3Å(òkÒ7䲎ûz`:´#‹ƒ´ q¡X°ü²®äfï £¯Ý,Ή…ÃIšò õQË©œp‚6-\ÚHÎWdkž…J¿?6ñ4@AÝô—x­jJƒ¼À)_VÙ =ÎB®<äõ ¡O8£o%ÆÃ¨C”îM=PóWô“ª„Šoêå²pÁÐhÓÇÈö=8 ÂÝu“ç?ùFÌ/zI"W«‡j’ ,òúǨ6œõéŽårˆSÒ*ÐW²Ìˆ%B×/¥aȇã_oªÊÑÝì*vií ‹¸¤é ½­P­ÝÆ.z Ñ£x}Ãê…›Z4îÌ\ù÷†ì6–+³­a8§Œ!Šƒùçþ9nʃ8}ņŸ%3IÂ3ò®½p/n*)‘͈QÖÌ´·vý7K%µÏã…÷ÐÚšÕ??ò3>šÊ¡©ì¨Ån©¢ºÞË‚mˆ\{~,Ó£QÚ]NÌÄŸë-Û*ús¼ù’~9VŽ>Þu¥/2Àr×ðƒ 4å]ÏzFľYÝä—D™‰Ðlo:ê;¹†5â¦æˆ(³Æ´á†˜zqíW_ ‹L•6NÂÚ=#dâ³Þ]Òéh˜‘–íc;™"/¤NNJ¼PVM¢9©¸ðSšN4œ¿¬¨É1{ Æt¥Vª¥kŠáQGë%! {OM;Û±"êÈÌ[yÓGí˜\_.€âp>$‘„µù¦af¬JEéÇù#ðåQnàtxe†¡‘¹­žáë_¤C'¢<‰;x³qï–Wг쿊e ¶ûˆH9/-Ü WÂt’*&Ppº¨,̃óbÚØoÛJ¢ßéÕÖäXSì;H*²™°–æv|ã|Þ<±ÖJEݺä Nd< abŒ1ž:ö½ÍRŸ+å£ÌïÊöQT!:ù¾™·â1 Ìý– (#}Ovú¢>µö© hµºWF®NÉ4]0ÿ²itYÓçÎ3©væ23ß°M\¯¤ù>ƒ`û|Í-œd¤’%xòD`=þæÄI#GUl{ÈO“±lÈ}Fâ¶ëKë,¼œÝßîs¹u!tþzØ zbr“ ¬ˆ'\MYÿblóÚCõgÍòôvÖä©:YéLw!»+Çnz°)Ñ÷Úå_Á³$o×î²åíŸAÄ fºÍèÃd׸HóØ(QÓ|Ñfž¤®ž¤ÚõÑÎb0Øõ…(u—÷4–¶á|Ûu§6!*ŠˆGå·ì(mjª%Ó4à+Iàj‡‹[ qºRÏ~Üi¬bP}æ¸=…øcy$dü¾Z¡$|‚•Ûíñcâ™WçeÉ\e z?¼8 ëJ}ç“‘ž¯*Ø_?M¬ÉbM÷O‡»V^/»Ñ=Cêe6ÏÑH+h¥TJ6=ÍÁñMè¤òä14WÕ=2î_9û§1ŠÜ»‹ôë\¸¯ w¤¡a·JîáTfêØùOɲE¥°þÈ•òP³=jõºš¾†œµîœD4ÌDk¾£jBÄÖ&|]½z¿ø¬f⑇‡Â=C‹E;ŽNX¹ >®aI¢+(>ªý%?fטË€t*¹™àSè&$ÃÚpžW0Bµ¦ã€6;›wmˆû‚ê>Yo‰_“|3Ú›ÖXRÔRêL,Ùû¼[­„qŒôˆŠ 6¨…"e¶EskbØ*6Τ•‡Á,KÞH¦D®êÛ–BùEÑ¥³= ‹ºr5>ù…î•¶„رd"îr¶'›fq­}ñþ(^çæTצ1Öùt«#|iHBá Ï³ËÚL¤â!¦Îpfkk-pÁÒ>³0Z¤ê«!OÛÀð´Ë y$œ–5G{uJØû˜¬o8˜Ò¡oôÊsÃàyÂç»6ëï·7¿¬±Æ x~º ‡®ê–ï­•B"“ÜÄ«çkÉ óª6;/›€„_ \™òCè3€F]Ú¸ óM¯ø§¤O)¨b#ç,: sIÓ43rÁâ™ J©é2Ö“˜ðùÒœz>Œ““Ï7ªj™#ÞzÜ+#öÊN¯T_r»¦N¯,g¢ýZD„Éϱ_BëóL(iÆ¢ó”4/ž÷rœŽô#ZéðÜuUF`-Þ3€1?ȘM§!Ù“¤ØÏ>+ ¯Y¹ò7w¬A/)idô‹=…kü÷t“Yš¯5÷ˆËÄ(¶>­.£áî̉G—ÿØð;aÐ(4…©†\¾M¸›,èøN>ö\‡NE¶ÏŸÃõ9”ÔŽ¦‰ º².Áxû܇ŠRxR4¢Me3ûÓуÛXøª0 aJ‹º¸ƒw{ŒÖUzT²_ïšëúú\ÃÓM§VF½W]Mô9ŠÞ ™^>ã ŠI8ž„N9óœ?ÜñüÜ*Äa}±ö^[xò­Uøb)p$^3þ‘ê7 ´Ã‰´@Å%bÜÞ ç¬’ ?JGж³™ã‡|º2Á^ Èn0Ù¸+Y‰nÐm.!Z·¦ ”ìÚÈeõѺæùí FBW›>`ó»<_ž§bÐJ²+HR?ÒDÓ?ç°i#üºSß#Ó\ÂZnQtC³nvpZÆÝÛõ‰Ä›=´êèF!¥}ãÆT¤î»¾ê™wBYG¶ áŽÎ„Ò$*ußø“>Æ9ï+ž@Ôj†¦«¼9ø€¬ëhóìËy~ð$Œ÷m6„*ªFQΑs[‡”í_K¿?Æ,Oèì áxu<!p÷!Zˆö«ñ"’Ï4Z%®h¨å¶º°–ö÷þŽÅH5"Ú h‘Qâ+ßày!±’ªI.@•vo(ì}mia«ÆÍ{ ]T”Lº”çzF?¥¹t–\ëÔ’5×àƒ‘ÃØÉ2jÏGL} «[\^àÙÉXucéH™ €×D;#½›ÅZ‚Wr´ÁAù’L¨.k7Åž"Vm“äX“†½ß<$aÈ©Ú`™‚ösÉ(¡·ŠOkXKW[DéÝOò¾P±E«¢ºxO1ES^6¾¸K8!^:„GlçWMóx5¹ǵ磰-ߺ"ŒÖo3åéïµkkŒ›í"ÂjŒ\e‰Ûv‡IA­¯ÇÒåÛb Ò:^)…PÏãWIè¬]å1ð¿ËWk75ɺ#¼°Ìvˆ—PIñ›¸€pôùòÜ?& ʹçé§ dÍ–A#¼ë¹›ÙËÖýò=À¿¯",˜ÃÙk,ùAÜ#á …¹fÅëhd¾Â­Þý.‰•¢T{‡Óÿzk,ß1Ó°eøS!B!wókœ¢Ì¦:Þ°;Û89t<ñ£õu¥4Åq/ÎëYϾ÷VèŒl'UH(tÕIŸ1tò‹áÜ›û}è~,|³+Ùn|³Ò…Ô4§íxŲ@1b#CÖ¾k„—̇Þk7=ÊÅü±¯‰Z¥á{€;á¼2àðãQ¸¸pÅIE\ «p¢@ÎéÈdÊjñL—·Úx@žN;øâêW{{Ù”óþâK¿Ufí]¢Õà3]îÿ˃ýÿ þŸ2°tƒ`¨#fý•Æ endstream endobj 149 0 obj 8596 endobj 150 0 obj << /Type /FontDescriptor /Ascent 871 /CapHeight 0 /Descent -278 /Flags 96 /FontBBox [ -92 -309 871 902 ] /FontName /VDXOZN+NimbusMonL-BoldObli /ItalicAngle -12 /StemV 103 /MaxWidth -963 /StemH 101 /FontFile 148 0 R >> endobj 151 0 obj [ 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 ] endobj 152 0 obj 825 endobj 153 0 obj 1374 endobj 154 0 obj 540 endobj 155 0 obj << /Length 156 0 R /Length1 152 0 R /Length2 153 0 R /Length3 154 0 R /Filter /FlateDecode >> stream xÚíRYXim‘ˆÆ†f‘OiDLR·$ì$4M…¶H TR¤H4t@6Ü@@!(²Úˆ+*"¨8 hXE7ºã‡Ò(¶Îi§¿¡æeÞfª^êž{þ{Oó›.sÆDŸ¨Z‘(ö€ééïèénÁâpÜl…¢Æ(ÑÔ”…#°D€‰a b ;;à.EÕ Pèö4+{š5Ѱ°ˆ(\*«YæS$:`\ÀƒE€KB¡zFã I 0PxOˆÞH$‚ï@ø$"¾€'AHˆ@D$O tc€> ó¥_Z;ŒóÿLµyRGD’Ï÷Mmé—:X NAd¨ìÄx aÇ/&ïrRÜ/!˜G.Î,J¸W—x>ÓôªÏA¿¿ÔꃘŒé%ê… JuÓñ('óƒiOŒ.2¢›ä\râc½&íæùY\-ïÕ¶@Ûyõßsö>S.Џd¡êZ1Þ¿£Žp–ý¢ý’¢Yü¨óã›]á»ÿþD9?ƒ¿b8WÃNCüž÷jžuÁ˜òÔí…Û²Æ >)ê{ÛÂ{´3íöåqfwžy½Õålšjuñ-¸»'£!zÜÛkÖ£6¢‹ ×Ùë~]¤?Ø¡´;¹ûUh-ßÕÃ:|§ßQ#ñòï†9:í¦©·dGz'¸|ËŽUÅa-] K]^y?oÁñc#Âe–ŸnåaÌ莊lŸ¦‰Ô ›˜[UýðÈwüz~Ýãè¯_̼á>²èÁ'c½âÖ¼’¥TX¾eÿ0a¡ŠòÃÓÕdDwcyfcÌ¥1Vkd‹÷¯e–ìŒI.zØÒö2ämüüªfÚ³.[R\﹟çõò¸–’ÁºÀ[¾'\­ «2ŽKz$&éÁ’Òãçà——yžÐÚx#¬ŸøÑ¥áh*&m¼{xH˜Ü·r$®¯ÁcÓË”wž›Úýœµ¨^-=¼škæÛdRáøYoÚíÔuàVÝéfvVÍ2üMž£:¤«ÎaÕ¾Ÿl õ¬3<+k lª[F`SîÃ-6Ÿ¨Ê±å,îX!JÛ¬Z†…ŸShVOx×Ú48Î÷ S¾õ©Ž®)âÊ›u_ÕëºXÙïÝkÃÈIŒVŽçVƒŸÊjwm«4«pv—Çi'cÇ bRY[ziL|u1êªì7ñÇ*d©~óúÖº¶ÿ2/Ú'&ca¹}t‹ÅÎE¬Î¼$íBB–Øù·ëågrÀ¸°Ôl6Y£4Á,æò×U7È›SµowC)[ÃÝ×™”ÄUÝíÕç.˜u4‚PŒF‘]‘Ÿì7EGüÒl.&’¨Š‹)x¦AB°æù‡Áµ:Æåª¢½ n+Œ¶?2ë"åç¼}×ÍôC/Ù^YvT˜?ŸCl#ìI~&>:wóòí¦â×iwt.4†‚¹•œzç‡â¸%~о]›úÐËCµWßì®ô^zì໺ÁÖÉ›Ð"¶”§2Þ‡u<8èøÚÝæÒ훿Á¼ÄÛñº”>¿m‰Q\ýâ U†ÏI_6sý¤oci]ÖãF å×»ä&¾û¿Íšdüx!×·ïž«P9 iDgW*šòMR—gª†CNŠ>œê9âÑbWjÀFš"ÝOý¦c´¾ÃigyÖùu±õð{WûùZO †3CZÇGÉ–9¡7žÇÔy–-Ô*¯Y}èàï‹&4×oa¼ÿ :k'ËçÈL„m|{btUlÎ7JF÷9o2&ÎÎ~&íÞ•­³ËìZcàÞBÍ»lÍ„‚ølmÆsÚ3ósÛ©Œv¼hmóÛ×ìo×â¯SúHwnç®lK§–Î8¥×ÚkRîÒËx=Yæ:¾"§ýû®Œ(n‚¯Ý#ÛÑÓ„fú `âš÷iì [ÜýžÜÔ§òø|Ã'ôøøÆð2±8}øüã³ÛOµ– tÄSÄøSð*ܧ*ùêÖ»˜­é† ‹†~ˆ4‰`Å”o.ò®.¤ð’aW‘÷ ¿6Sþ?6£õ+¡!¾ø«s¥ëíæ|z“×õø^bºÉœJ„þå?<Äÿþ§<q &„ñpâ?Tù endstream endobj 156 0 obj 1970 endobj 157 0 obj << /Type /FontDescriptor /Ascent 750 /CapHeight 0 /Descent -250 /Flags 68 /FontBBox [ -55 -281 1141 781 ] /FontName /BNZDNJ+CMMI8 /ItalicAngle -14.03999 /StemV 78 /MaxWidth -1196 /StemH 32 /FontFile 155 0 R >> endobj 158 0 obj [ 682 596 ] endobj 159 0 obj << /Type /Encoding /Differences [ 33 /alpha /beta ] >> endobj 160 0 obj 1676 endobj 161 0 obj 17859 endobj 162 0 obj 540 endobj 163 0 obj << /Length 164 0 R /Length1 160 0 R /Length2 161 0 R /Length3 162 0 R /Filter /FlateDecode >> stream xÚ¬·ctem·&Û¨°’Û6+¶mgǶmÛ¶mWP±+¶ÍŠºž÷íÓ§Çù¾þÓ}~ì=Ö=qM\óžc-2"1;[g{S&:&zFn€š’´Œ–"œ¥‘‹“’œ— ’©¹‹¤³!ÀÈø×ˆ‘ ŽŒLÄÑÔÐÙÒÎVÔÐÙ” nj5503˜¸¸¸àÈ"vöŽ–æÎJU%u*Úÿ”üc0òøÍ_O'Ks[ùßWS ½©­ó_ˆÿkGeSS€³…)ÀÌh ‘WД”PŠË©ÄMmMÿÖ¡àb´4ÈX›Ú:™RÌìÀÆv¶&–ÿ”æDÿKÈ `p²75¶üëfênljÿŠ`oêhcéäô÷`é0w4´uþÛg;€¥­1ÐÅäŸþÊÍìþ•½£Ý_ ›¿º¿` vNÎNÆŽ–ö΀¿QDÅþ§³…¡ó?±,ÿªvf-MìŒ]þ)é_º¿0µÎ†–¶NgSwçb™L,ì†cÿ³w´üW.N–¶æÿ™-ÀÑÔÜÐÑhêäôæ/ö?ÝùÏ:ÿ[õ†öö@yÛýËêå`éìd 4£‡cbþÓØùolsK[8†ÆGÒÖÌÀÄøo¹‰‹ýè\MÿÕ Ê¿CÃFõ7 C;[ ÀÄÔ ŽAÎÎùoHåÿËôÿ}$ÿ7PüßBð ½ÿoäþWŽþ·KüÿzŸÿ+´˜ (ghówþ½jw¡-àïºÈþÙ7@CGÀ?;ÇÒøÿãjhc ôø?9ÿWkuÓgý?1ÿ«úß!„lÍÿ2DÇÄFÏöo±¥“˜¥»©‰‚¥³±ÀÌø·yÿ’«Úš˜:-mMÿ’ü¯þþubdü/: KckÛØ`û·ÊÔÖä¿Öð—·UÀ ¥*+¤"ñZ¸ÿ2Vø;ÿÚÑ€ÿI]ÖÎäþ¶sxÑ1±sè˜9ÿ^ƿב‹™Õçÿ'ì¿€˜þó,kèìhéÐfüg³þþÿÇï?Oºÿ懭±É?s¤ìlhkòwôþ—à6ÂÒÁÅTRôoùÌŒ\,ÿ’»8:þƒ툿ýøó¿®†©©»©1ÜÚ²1O°UzV†s=VÞ蔨ö`?øhˆ}Y“Jq¡­]Ÿ_zøW•Á{]}ó4÷g‡ÇÒ™ýÇõáÏþo@оTÓ«|ªBÔMò.šÃ@½2ÄŒsõh¯ëE™m-vFµÃÝ)E%½Òw¨ïÓ],Ž0×ÏTþ$®…þ¤OöH¾Æiq˜Ý(Í hõEgçäI'ÏOÃãc£#}·x4¹q°d<®ˆäQþ¹xZªU^±è²2-UÓ ™£lë ¬ée¯— ”åz™;DÛ«gE]<Ò2º€$p¯%lØOÙpX†«Föêr¯¼§ó£ŽäR¸Çeï)á57*VÛæQš ‚;úŸÊ5Êí6VÕ›„{R˜KÆg, î;Op‡HL[[/[yú7ÞUºßªž¼3?5j=Ÿ¯/#D…AÂ"Ö)üb -4'z…¯ç6é–¥„EQ©»]?ÛD-1‘ë[ÒË’?üç`ìa¤Â*hYÕ¯ÙlyCù£ BÎ5ßšLÍêð¶ s”>r‰z,œü³ºa‹!¡Géo#KF—9‘°ü•x„Œ`¤u€Aò³ g52‡õà¦Ùïþ £_âPcÖ]Ô è;UÉ7ƒbœóŽ}ò€?Á'9κÇ]å!S°Ž;Œ—rÏs¡Ò¼æ ¾ká ”Âl pöãh{!¸o/hß´c^Ñ~á‚òS³z˜‡-je„ ¯#çníŒPÀe̸¤rÒð,ÞÞQ™öýÜÏÓójÖVúû’åL©œd_Ê®U$´‹8t†r™#Dœx{Øh´¡~j¿I¥f'ŒQ#Õ¿"ã‘΢é·Ø¨}éò,ÛüL‘¬kC ˆÆ0ÈÛÊÄ LÜGs‘Ÿgnɤ†è·®ò<@ŠÛÔlgu æÂw ó§SQö&€×'¦;Í¿ª»ÂYIýâÐ" ¸©½Ä›~y¯Ý¼ÐÐÅÍñÀvØ,Ö¿&¨ ‰`ÂN÷:—ÍeÕ¡Ê;Ò“Pn†äX%Þ—¿Ýé¡Ä™'x‚NGÓ<ÉC,\YãÔ¨TpÉÎyØÜj„-tÿ4è!ƒ©Î°"Í„lU:ëÃ3·ù5lÜ-âå¸ïìÕrù¾òsW*Ö^wgU›]ÐùƾŇŔ;­Tœ_ ÿdøv:NÏÔÍ…õ.:µ/`ÏûÊEWh‡.ïU'¼(X=FØïŒ’HYnKÓß½ÏTÒó*wé;51Ø cŒ×ÆÝ &Vtg´ATÝøo¨[ŒuLñWoußQàuϽF¤A³fÇÄ»ÕÔ{)ÖaMç¼ÝûºÎ=«<¼µFÇÕ x&FËú§Ò™·ñPvÌx«~ŽêúŒ/$ÍÛÏdO¦2ãçu[œ¬1¢õDÇLŸRdR+¡ZiÇððƒ º5!mˆãyLß|Є3%Œ}š°Î˜I| xª8OÕ³q6g!ϵž à íÚvûsa‹\8¶>G"ïz…O2qH dðg˜G)ŸðÛ˶w£z~Éü¡©€]¨ 7¦z¢ßÝUÒˆÆ伫$5Rc'd C,ðᔑ~wìÑ»DˆÖ*Ùvƒõ’µüœ’pÔãT½1§²'çT3ù¾%0Ÿ8YlÒæCWWË9š î÷bQë숃ñ±¦êW/–D°ÄñE—Â>Õ÷×˰@Î->Ó‚ òï~|R·˜’´qà:‚¿ö¡W˜Ã¯q³%Rù´¾Fõ¤Œ¯ÄmIr\3—#óy­BœrA’ù;¼ÎäqÃ6`¤@ é‚ç ¯0êz8˜ýÝH4I邬×HâT{g©D}¦ÌŠ ›sà“á›ôÕÆ·¨¯ñsí <ý*Xëø=K¨¹þ‡ySýKP•-ê·±ýC¥*ÖÁé(%F¬fí†s6½ÖÇá˜ô`q £ò3-þMÓ¶°‚ÌzH0¯H,wë+DÓemò‡(¦\ÁÐ{vF´<­¸Ëæ0©øÊ …G|nÐàÞ —#lUôÔë¢Ü/ªc8lrw…€M N~ )þa ÿf¨õo¼_Úßkó) ;7aíÝLÊÜ™-ÍN¯;Ü=ÅtÎöE…u _&$ý:b,l…±0uÎÄL¸\d‰`µcf„Ž3YCäíiŸ!4ÉÚX½¥ ñ·)j‡FælWé².Ëýá,|xWû?ºúîœqËcê°¤N- Ÿ;T­1Ú6S“©#p†¶JÃ3!½m¨0³ÕÒØ& ;4 0 sd‹<,ì#Àµå$Mp¨g¤A •uð9Ôû¨–üdqMЧQ':/Â>²‚?ŸÖ¦ ¹žñ7,Íg7¾3Á9õª< š); 'âìÈ:Ú¼Øã^ÈîZt×-Ço\±ŸxwyÈŠÄóuL ™âoÏe{è)]rO|·C¡<¤Aº £ S å'·Rªs?¹™ ôÝÊÕ‡Ú¾•3 ^k¥ñ€ùtîþÜqQÊiŽžK¹íµkÁd¢fÕGü8@ƒ-ƃlÐ'¬ü¥–ShËb?OG‡y®…:"¥4d%­€o-|­¿,¶ ëû‹ÄáOãjÇ|í\¸ÖR!d@FÓ÷äþ8ZøÿCÎL•öß\Lï¶ì-±=–]8sL—QÉ{-•s,.˜*»—è­DóJŸª Ê»°Û·Œ›Õ¶WaJBc¥»Ê‰M;²$~s àÌTe6R³P&ȺOÕücà[câ8Õlbà'vø Bª€k áÌö?™úE«¡ KíÁqÊrÔËyµyS&P_Ó¨ßsR•zf•¿vÃIÛ¯’Žë;^˜~À«._\yÔ9Ô&+ÅÖR–ë”q½L.V;t*ä^_ãŒ8ç&ºAƒ&¤7eº©o™…l„ óïHÝÀÝE4S˜M¹JQùzg»êƒo óæ (PɃEÂÞõ˜­hõ…*¨h¹¢—áëÖ[°ö9âïãjéjL4Íì/ž¬¦È2¯,Щ‡#Úº7c4ÏÚ«þtžGZµ°” ^é˕íü÷\rDŽÇ´¢ÊM¸oWýo<^ß“]½ùª¬ÞwÎÛ$üì¹.úN”p™Z‡û,çºLž½G1µîJpb±ŠÒ÷þ꯭Ðc2\žÜ5*ùX¯;‡>æÓ ™£$›žÃ.UÃx#à V×eà·x:0ìvŠ4Jjßè’m, (V¼`—äøóc¥lïý›ËY”-ùŸv]Ñ•dŽÕÂp¨ ˜G‡#YYªúÀqÄúO䮾P 2á±Ì¼Ûíùk#È”ƒ·9Ç«½Pæ3̇Hæ±È/àj¬Ð%_ýÐ=Wã.‹P¯dvpcGçŽ,•ý6ú­‚+göÀW¸ÏÇê´h9cûPjü„,ìt@µè¨ú`mŒŠô8£À¢™¹¢È?¸^0{% QÛtÿÀdI>ZÜÿÊ©¤Vº"›IèÅwA%ôÎtÑ×:Z>Œ²–jµ»Y¾®7>BNÌè{£np@:·"-ÿÅ8¦D‰Ø´$Z8Aœbª= ©Þ3éc,ŠŒ›­—ãyO,?PTNo׉­AG©êû¹?Þ³]ü¨¸WzkÌÅΤWàãÅ >ê((Ÿ.óúvvk–´42ÆÇM+(úQ/ŵߩÚW:Ï:¨Mó"¶—A!¥ e¶-›YšÛq£ nãF†ãw%}zàÜLƒ*±ˆA1šwQA ǰâù^O~ËKûþHªWœ F¨>ìÚ¦?ÈJb=5ðcN¾—Ô õ—x¹âº›r:DWšÛÙÞCÅLýN|ß’ýlï¿OþÚʤp‰eDTGëõî4J; +0|¦ S³ & «hìÃ^DBø˜kä.×bf6'À:ÕŠÅ îD^,íCZ©k.xSʾ^‡q³¸-O*³Å•º ï0Û;VýJ·ÎêZ³³¥ï$\ì[‹¸Ï“•DX¬Nßà^‰‰k—¿a§;¿$˜“ }ÔAÊjt°I›{Èj^²™Üõ}‰÷NCeòô°¶ëµÆ I‡h€ànE¹½8¢Â>ìl•»6œ<9I律ätN”qÓßÀyƒWô_@#•XË«qúæ^¯4¸NŠùzYÔzE\†qÀï‡Õ½`ÓQÎ4×X¨ËJc–®üJ$Ë?Ɉ]<¹ß.­Û•‚ê—Õ¯i²x}%O„0ôpôãÉ¥–Ø’ JÚbÐðØU›íŽ0°€ÃÀw9À«¥Ãçè©JVN$öœPßåÖÀ'ñK$×eÍ– šYõÔÕsN€ö•çZ²Ì€¾\¨Nbc|åûLGqv›I&¸z[a‰xoõl_oòj?.-E$H~â w¬ÞêÑ«×ÕÛO˜ª|GjJc ¹z±¨LŠI-}§¡¤‹ÈH¹†½i‰I/¼glÏÏl娗¸‘T©êÒçöxæÙª'°¹9"¦mûS… s û­äOÆßsi?¦#5øŠÆê³wRˆ©!ázHs’ËoÇÄIO3~¬ü—úbùøwq~½¼_Ù:5ø-¸·­åsVˆœ–ÏÇsŸèÌ] 1xÇÈg¼?ú§7U²÷ÑR$G’x·à472G”mYˆiœ(½'jP_Õ†`·¹OÛ›jLj æ*:»ƒ Ý»L÷)”yŠ®¥I¶“OÊ׳pIó‚´T¬ÞY¤…ßzS‚©Ÿf{˜‘õxK¡²6vúk~ODT Jop"=,§Æ§70Èv8øVvß•ÌÍ”Œ< Þv1‡Xж}ú‡+³Â2ÈÔQs,D¶ÎšXêá!ä‹Ú0 ™,B&ÝÂô†D-€Åa8·9aŒÌ¾Wx;í¢u&‹”í‰äd•V½*Êûû…óL~»Ç+ lÀ±++\X¦ÊîÍBw;z;/§ƒ‚™§Ú¼š‰G§=.ÐFS0çñÍÈF5‹@l1D|hÍ3²hœÀ3;éJÚ²wqªPÉ–2¨¿ôk¯Ñ¥ï|‡ìþÚ¥6#8ËücúPëM‹Ý Ÿqs6QBßæð­(;|"/˜:©#\çKžð{²þ¸½ßîi߬ï—=:2,w2(ÍÅ\‡7å~N8æ™f* è¼±‰ £ÕÀC[û$%<;)+1"v“CXÆÒ‰e»E™=ôȼÂP‰µ3Lø®[Æò•ÍÌZÍáOôuÕT&³à^d¿~¿ÈX¥¸Ï—~½XàÑGH·ÑMæ+k¹Çÿ†h*½²F‡s ógš uÛæãÖ¬×ìÐøâX /?yëV’äYD?¤%ÃFX¬ýÞ‘Î/Põ&цŠ\ òCŽŒ@©^½¨blTƒx+Ø”€m;÷Ê(,çÓ C þŽƒéR§–¶å+`Rª~Â^ž'’0ª(í@HÍdM7ËÀìú¸––µP¯! ü\Å6:žÍálÝà $Í.d{Ž;-)*“8÷ʦ2^ØÂ).¯¢¨`º¦£(àÊt?`/°™Ž¸×it/çà—–“q²bB0áÍ]”½ G÷jg `r'ÆOÃ&ù÷v·ñµ÷¨¥eiSõzÀ½½š¦Ïñ·>Û&gÖ‘tÏúxø-½]”öFÌ£‹ª4D8—šaï¢ÞžxöäîL,XÄ8ÿ®¦ûVÁræ0{ïc/¯ n 1X_ÔãšYœÐ½ç¦eĉþ%$u .%Wi¥"l¸¾XßËØ7ÐdœÇ/QróÂÔuEl VîÇw•”q%ʬýàÂÂI óÔs­™µÔ¶Øz. a­Õæ$¦/Uí’ýWhïj®pÈOךÃu!%1ÊHîvß?ä_lÕTTU·òB ÏÛ/Rj¥.—]à×ù„£VÛ‡ð8Ñ;(#àñ&!0³‚"Σ>@ßìº÷»µ\—œ>ƒ÷lÄ+õ8;ª`âÙQdJä­t©þð|-Üý©‘ áË>P®{7íú4T½îVºwÀ99׋˫Þ2¿:«$ÓTVOÉ0æoFÎò§ý½¸ªqûà½=]Š_8«+g³ÌN‚.¶Ê·[È*„ݯØÍ ŒÇ¿}iÎõs³_+¨´„¥I»?)ÉÂϺ!à„ÁÝœXsWÙÛhІ$£A“õó1·u’í·!šÊtJ™¾w!„ÛÜ8õîZ橞¾çònr7—'â`ì&_£6(FVÏanfÝ*x$ãà †c-A6 KQƒ¨Š™ÏÔÁx+h1B˜<.©Z¬cÇ3aù¸ÿ6xh[á&»™©ƒk°!4t³ìIŒlŽhÂ.ë9¾DžÃt˜TÙ+Ib5ZȽPô³#²ÆqcÙ…MÃ5à ó]h7©8·Ú&9•N|2?§ùœb¡Žh0¾û­9³ót?Çä±f€±E†%´ Y#8Y&ú~dK–+¶fû£zÚÖøDÂL½y=;\s8$Wù3^Ѧ¶‘H“½3ï¼+kø›ßþNÑšíš‘jâŽåq»íü@èDÌk’ÛÚÀìAÆKï:î5sëÝ¥2™ö/Ê•é —•L.»H†~¤D>´Dæ}*ÿ ÕEÈTžKH(ÀƤïÀàÖÀ{‘Ï¥ÜïïÅŒ”ú›"ÇІ bÄήk”Ûm–akêæCFƒŠâè&ö…áÊ)^Ì+Z˜ïâØÏéØ1 šÂë¢#uÙŠûMÌ„qôÅË4e¬!À¸K”.û®µ?­V:ZH×®ÞÉ»>U0a…Ìn¬VÖÙŸoÝG¿æšÑç|zÙƒûÏ!È¢Pê®ß¾÷$]($á1ƒIÕͶe:ArâÍÀ^Ù¬ëtí‡ûÏÒáåXñ¦ 8MÞþ,…(Èrl*T^ìRàï÷AæQô"ZÌ!¨Û·ã ß°lûôÍÜ%OQ\¾£-›¾µrïw +˜Hø¾Ð )Éc³cÞ¼¦k×"‰ú^à£p2Žù»Ì[V/úõCIŸwݧÃ~v½pŽÍ”€$# yF†áe¹1?8ºÏSü"&¨UGRUî6ŸsZä*Ú07(9·íõ].ç¿_^w~!ju.<Ÿg‘¼ÑýTExfÞ(|B!É2‹¯HÊÝG˜ž­øxz w/Ç÷òÆj‡Lx¼1‚æ†d#ÃÆ¨h2EU&UÓ‡-š•“Ñ[yÐ?Ë?ózÞi‘Îù& ‚ä¿~03`ÞÎÞlc+ËÔ¿i•X)S lŽà V½y©RV2>ÿ8šE ‰ÀWÐÔEâ ¢ž1~‘϶q_¼@“­%U„àP¿ †Ð“ §Ow_ħ„$…^œ”.ù‘¬;ŠøŒEtj⾯6[Æ–À÷ô‘ijá¹î[mÍ¥³×C8ËÑC«§ŒkšFžŸšy™Ú–‘H¥lËp…,gŸŠ~ù„—vôFº[rúÔ»ïìY|g£Æ ²çJÁYD-‘öïåÏ^ê2˜|^a²à¼)ý‡ àiþ_ä•5ïXr»3+-*ûŸc‰±Ú??s/'gs‘+”Ò:Ô¨EI­¼ja~\0ÈÄ.¶ ŸÅ+‘:|Wp™ ÍãASol °¾ÞÇ7?¸KÝœ”¥ pŠÞñµÛÏW .8‘(þbªÒ ÑMWhôìU·U ù¾m&«AcQùê&”vØ2WPÙ_÷ÄD ÿ­Ó½wë#.9ì~èãÑ+À¤åô¹óB馧kO’¬–|¬úE…§*qùs%ü:~ãØÆkú½9Ñsa 4×&‡np´jý>ºŽ2ê*uåŒ$’«»Š_ÞyŸÐ$‹O׿J¹lY©fÖŒŽ) !ØŒTcå÷]-Å¿‘Òµµ«w<§­`“ÜJÏIî®ç’œ—¸^[½¸˜>jF£ÀãB!(Î¹ÒÆ¶®ÿëuRárï+ˆ]šTn7#·\ë›Ôà}lyg†äIà ­õ!n…Ãc '»8½Îi²ž¤ÃAk&ц¦ºø£Æ{Póhfâ/°p•nn_Ô ÞÛ´œËŽRÕ« ;rûœ’˜Á¶5r…Eýb‹"›²5<ßòŸ™Øi·ÀyÅ’YŠjÖ <’iÕé”ràó 2e Ën_å<œÕ.$¯¨ñ®Ýc8|Ô5_ gš‚|à)ˆ_²k6·> )•¸ít}ø¡¸?¤öû—¦Ci}«‹GçlšSƒ¢Þ²¿_ßêãµÉÕ£T|^ÁÀdpÕZ 1ÛºŠæhè.€Œ;šÇ·lÇoën™µÞHC–Ä>蔺rë…¶ñ¹ÚsÇá‘ ,ªøÛcrY#j~•'Wf÷sé ßwÙdu {’Nˆüì*õ± ÿÔ`œv§Ø¹‚]ôˆ›SÊs>s’#Fh@cÅÎFœTð¿ÈR°?‘xÉ'Ë7š»¹üÇ øÝ5—£·á7lô·kd3óoòQÀ´<4µHÚ¥–ÌA{FNQÐMÊã_r“½¥ƒ÷/— 9ë;DŒ¶£Pn0O$ >SËÎUÛø” ÙƒUãË"kEm±Vµ›öÊ`ïï„ï´w ̸.0N 8€ÓŠELÛ:Γª?U|§¿µZå|óRî£Öi‰#¥ï"R,˸y Q%—²>ËÎêõ1¬?~l«º¥ãŽïÄýˆï±´È£v`þžg䞌ˆHqšâê_S©·_@ÕR°r›­-åôVF‚PørÌ28fPtce|TÍ÷·È9*ö­k®c*ݪuVбÌQºM'ËZM¢f"&QºùÕÜûà $ÆÈTÿÜjdé¢;¹Çÿ»B6¨wÐÞbÝ5KìÏ|“áfî|OfLŠJÿ[7ÉÐyP¬„°˜òŸQutª«eì ¢›¢M“<ŸÌ½ôþ®9'`é7Utß,©:ðýÚQ}3H‚Ú Ã÷,¿Ÿ\ÌÓ0DˆñÉ$e˜oˆ]^Ì£ T]³ÌOž…–h\Ç *çë—-FGÜÒ¨I¥½µe€ NŒASÜÉ´„ô .½þðö'²)Z¸ŒyÉjÄÕ¸q–/òGǪ JÜEŠxª‰è*I»÷±Ž æÎÌ  ÏáœÅi‘z©Å¥¸B•Å„;QHõ„]óØíã´…E'w‡Rƒð5‰ó-£›ô©Ó›\¥c™öVOòT‹ežžîÜ*}ßšÈ901¡´;,ý˜c"|×b³Xv cÀ uàM*á]Œ\gÈÝ’£TN0Ž×ïò#ÄòlY\¡£á÷e;›ILÀyq¹àØÏ·k®¸‹æoËl ¨uWù4£s!„ ,Ðø_nOm]â·e:Ý1<çQ’wT>B6Ô¬ ëµ.(]'ø®ŸÈ%Àú`É:îGÏé­üæ¹¶ù^4k«µžòb»Wr$•j6×^(9åÇR·ï—MD§ó’¡þ «˜J©¿U š©×@¡¥ühp±åEÕ‚–zy¶“(†Ñ ‰Rw0Û&hÑhÅ ÛÅï%¤³îlP¤sx $Ѿ‹[¦š*ã™ôKó\ÆûM‘+Ь-2LÚ}§HNpؾ¡½ÁدO DAÆŒ ÐŒ÷Y¿YAih}3ÆÄYS8휸¾0ìþú%ÇÀå2rö–jH,(¿ãï ©†„ªàøaWvn·ËÌ(]Ìî[Ñö£zj=1¥S¹­å¦$ÜjËG.Ú_BË‚þj±êAÃ5o™«»{ÙõՈǘÉÖ/ v:3ã2RÈ0úòe/TÝ;ÔSÞ<˜?šä ykTj®P‚°IèX-kŒ&˜8‡e4Æõ ‘zMÈ¢qyÑEÜ©}­X×\vü>ëC…ÏÁöæ£èÍ*õ9Lj·50·ØO^¡kîŠ5q%SÜøs·=Ð3Ì®/êñóbx¬Êæn„‚’ßÝ6Ì¥Síšá;Ìz×ß×¼w­—kz°ßYØñ®SïÚ‹ äWò,ŒB'üw ›úÚ¡©L%lý—"ìïÎ÷¡:=9÷íð»aDýÌ¡ûªT$†[œHíÖ"4FägöÅ÷:èÙ=òï·{´í4í¦íóÔõR޲—<ùÇi]öeLš©^Yó]ÂÛ@[÷ef±( Ĭè»K‘Ø K½e—AûÇMQÚīѴx'vÙ¸Úü~CˆÝZ»Óz“¬ÖÂa~×uÄåB (êw-„ÃìAT½.xaô4H^¯V“{!+eò— bä¯2§1…dn¯þQÆt¶¹ô®†ùÚ  La΀óð¥Gäñåu4êJ¨­xA=p‰dí]âL¡B(â½ÚÖ´r 9'N6ïÎÒöäõ*”¦ïJ’‘KÛ]Ûó5-Ç>š‚%ǘĒR˜ª“~i«UÂý Q¹ódkËY¦Hqsëà ªz®í‡ÉÙ˜õ¾9¾/f½}tŸôëNšô?çDýƒ³BÞ¥P‚fp™ÐÎ 5qæº X>>ò” k@ ›0¿™ätl£òiO ‰P©:'ɲéѱíóxȯÊPHÉf“‹œ_ æ2dG¡B8¾ê/Mï–]P»'ã~À£Ðw•Mð–é~g+bûоLIÃÒe*Ùã\YÎT¨dµã„Sº68}¦ZÞkUyäš÷ºNSÖòý\á®s+¨h{yKh€OJÄúÞ—aÒu*À,½Ø°É{°H`ã}k›  >iã,¶"Â^/4my¾Å]Ó0rã MHξBéÈ¡ökzù¸ÁÁÅëñ~›V4Ñ”´JZ•ø‚ÏšŠæÄ&ÏŠèaãȯÕbwI4]W4OÕ¯éÁpYj“ƒ·ŽìB5ãDfÎxZ¾Ød+ëÔaXEHîÁ‚_3ƒ 5}é ©œ:ë]çŠÔ8ß²X\}9 ³×¥«ÿH¥ÜNg¯;qðrŠT§¢fW©„\‚eD0SÀÜ­HìIs¹u˜CÆqšp\$8êjGô¼b‚´'xU+ê¿ß:})‡‘»p¯ðæô€0‚žsÎêÓŒv÷ÓÑ|[ZŠ,>Œ?îݧÉDdG !ŠáÁŽÀßc]ÿÏd6=þaNòž…Æý Pê’m&âíÒLJû#l±U¢^TîØD Çî¡]·ß¼9ì•iøã×å¥Ý.1=ÉO¿/½èêšR«"Ô½¾ïÊÊÙWͽ6÷ò½ñú‹ßd?Wß=¾s ¤z«S‘›k@N¤TÜ?h¼žyè&Ôl|æ¥F!°xÆÛÝ'þÑrëo½*–íÄý™Ïû¸¢2]jáþ3ra;B;ˆÔKù²ü”¸(¾{ò|Px!¨³_°[ôÒèdÍÇ2ì‹Nú³ÛÊÛ«$W‰„qνnQ³®Ãø^ºþK*%7;GzV ˆ»Ï3Ž@‰75NTHŸ¨G×é&¥N«¼j½‘®PÊò çH}•ñâ×ׯäR,"»‹j­Ê÷gx51ÊÌ ¸]ÁŠ#‚¯Ár‘¾àAê­ª¥ÐX¨ÃA7¢‹?’mØîÇØÆQ‘`ñ£3VêZ´¨Á±°x÷1N`ßÐòÖ3Y9ºÍ|KÞ&UYk,Ö„õð¸ÈŸÏ¿éÀÈá<Þ…A€”ŒHÂÀÁl(Gί\93rT'&å 3É?Ìõ5Vvó¿N†Y'ff“¹îø7‚Ày37âè|y˜‘8´ŸpœÜ0Ž´ôг&ÎU7á‡UË¥^íi @­<Ó%¸QëS!T°NDÙê0¸Üܪ0úÑaìsH}é«=÷0=þèÎ`Í«ªgeÞ›Û £›‹=òžúØ Öeß$bŒF:¶ÏE5dk¹ÅÏ$kvSrÑ×ò*üX?8ª¸ ßxØ~܇ åQÎU]ÍцҗâÿFÞ UgÔèOIçµÎ" ôÇvtœÇßòGÁêý…C“$óPw`xXx=]¢ç‘…Y]^æOû36—Ü[ÁI¬ž;~4ø«Â+¢®Uc®®¨BëW M!{ç,ÓQÑ«ßhsÝšâÂ!SoÔ<¢J!ì£cøHwé!Q*©†xzX’a¾í^·Ôƒ–²“þ1ý±¶ÏÔjÆ^ÇB lý8'~ôª%jíH2†*¤ï °… ß>sf»ªñj4¦ÂZºT94–ŸÁþ š2è8¬.Cµ-@yÒÈ_~(ìö%—±¿1ª÷½¤!àÙ¢öƒoHärÊex·NußkÐf¯hÃöÑM±Q¢¹Ü“rö„DP—í— ï»}ófŽ4w»n:G@Õ?—ÒÍ—2´V\‘d¤wîš´µ·Bhª­åXá›L®uC<²ŠÐùaˆÚÚ¡‚¼ ;ËQ¾Ý«æ 9rЇpœ•ýi²Ž´&‚¡ZaÍFƒ'Ñ{ ž=Öå¯|½V¡§”ïüjLÁЇó- ÈAUc·;ã·£¡‹‚H§å2.)Â0?›Aý[ä׺¡ƒyåjG؆Ûpöƒ#Ic×=$nÛyƒ½^8œâÑB¬7>O-~aZFX–æÿø‚%‰uùu¹T"oÐ3ˆAËŸ 1ñ†ÍÚ¢ü"^x-Ú czãñ4AF ¨"»ä,î1±o0½¨¶œ *ŠÞÜ(ö7&ÔVhßÅŸ´ŸïŒ[Õ*[òEŒ²;Ç1F¨¥§¿Ä%í§œ²@¦ñŘ0¾ßImŸ‘ÅšÄ1P´AÁ™lùuàM…š‚Âg„P›`þQ/ -o«-âíÀØeÛ|¦£• ùl%~lI:²ôÚÆjÿ£(“stðÈs®ÇW™7Ų gÝ0¤œ SÊßÕUZ=äØF1ÑðR¹Š‡ˆl Ï à…=uNE iæƒtÔ¯æN_x Câ Æ9»,:Ak»ldꑞÏ1_æ[9):ákùêôaÈBð80~É+ü¨±þjl øìþëžN–_^ù¥¬‹ùy>«Y&è·(|jë¡B½”së]7Ÿ4gM){¼F®B-óÎ_‚o÷‹ú«ØUŽŸL÷‚øÏjd¥Ñ‚¡õÀOtaÁ×]ú.iðoÙ‘Ó²J-uS5’ÍÞ}½tcöäÁZƼãÂÞ‘ Ñ[]‘¤Îj×ÐÀWxVÙ´æKEî14tÄ?;±^tö"ÚÒóÂ= —i,ž³—>/Að’×#5ê¥ü1 T-ͼíû×Ã¥ƒÉ=êïáÂ…êÄ5(þ, þ B¥ë½g­A<µÛËúqùô4 ?òùïä&¡¹jmÄë?ѵåb¶ã¯ŠŸkõÇM@`£W~P qI3Œ­âh„Ë9F[FdŸ#R$Í-–»±ó’I¾wϨ$HðÊd•¡4Ø•`>ö´æˆ=×#¶‹ak%±œkL>ïF:n&Ìámäþ(³‚õ8-ì=ït=oYæ÷K,sšµ²È“ÖBñ@2`çÕ=«F}õüÊkØêÁÎï8ŠFuý¥D½¼Èn&·ÜsZYÜðxfàÕož]W ÅXFBÐ1§ª0Î’-uy§ã…ŽD&{Ÿ%{ˆH¹3{ìl³©…ôyÝA þÊ ’Å vs’Ë ¦kT´$›§†F“§<ø *m¼Ér^X,tJù‹d­ajmFû‰ÑT®OÚiTòÓf(*•ÿµm¡>BÈXAà†xtÈ‚Ë|qZãéÌQä“ÇjÙ(Ú}\T乼¯âW${Ûëòœ†lfÈà"O‚àò9yÅ?9g£OØ\µÄJ¶îEíäžôÞûn¿RTœ7oS>¨7b8<8­.‹y—ÅŒi^a N·…( ‚VþÌ®«5H v²EWBaÕüÅ/îà¤3qýËMÄóý(–¿É­Luà&{éµvÖ‹q4*¾™ÛznîììP«1ÝÅs™R¨6rÏQïˆ3ºŽ¨ðFb\I”@cYu#'¤¦ǃ¹g*¤“jĺ,ÁÁº•Ï?ˆ}þhFÐ LJå8-5¹øñ˜ºîªÐ m,Üw8È1ÝÔôï¶à7ˆ¾ƒåù1ðÖ ù9æÒòƒ4'Nçé°×zûw±h±ªÂçè·¢’NÌ4Ãî…ÙYqgdŽ^L,}H‹pŸŒ\ä»CE»æL q%J©/%QŠœ€.9YŠJ0rcA n]uù-[ìÏf¾§ƒ—X²äbÁµ¿ÄåT> a Z £gQðu´fÄïå¼>‰8ܱ<œ`e£ dÌK©ªs{؇;†CûÔÒŽ±Ú^¹R^ìašæ”F€g€Ÿ‰Ùÿ_º¢e×ο`G¿|Žõ±m$2Ö•—‚Q[br]ýÏpÒ.ôTÍÝò‘+ñOÛ–Ü #æ3žð6ZýÅ]ª @¯20ircÖU3NT¿aé«`ëß Ýá³:Ë3c7_ñ™`I®C…{u†‚}‹»Í£TcY›¯Œf§áp-B ôÕµ2®èª(¶‡ܶ½Áä ’ñ‘:vB˜õTÐékxІšw¿šëßãýçÝõš6a4°1Ìĸ ¨ÖÝ–aן¾ñÑïûß1§¬±àáœÊƒW³»þy¦$I4¶Óv]^y2£‹1æ…ÄSsǽ‹’á§õóõò;3‚ó<[^ÒÖmŽTðõ,Ü:vûîðéè$×*×ü)|çõè6ª–F:>H‘ƒ»WœÒÈëÏc×1<Œ$í°³†W0ßúRÕy |.a‡„”Q"|VÊVýÜz¬Î.BÛS§Ã!6Wu;ã“w!'Úݲ¤X޳>+˜C„k/i8ZyÀŒ¦‘'&õûRq!×K‰†¯õ{à˜Z^ùó+žU‰o¢sX ’cÄ ˜hó\½; ÿèW(Ñëcøèê#³ÊÔ‡ñZƵ[¥=ƒi´p\êpá¤öÞä©‚ß63óû Ì­'îÈ^(”d`ƒM•Á~ò!Ùˆôný…Ž×ËÛrAR·oÂ>‰bXJôj-‡‚¤¤g/½‘ý¿N,P±LŴ߈”ÆVù³”î 9I;Óz…Qã ¡€Ås4nƒ*AƒêÜõƒÖ I4¸*Î0{1d×C]? ê¤hRånSˆ9T_º(™6ßÐdʨJ4Z¡Ÿ¶úr—þ…Ï7 kÖ¶ÆÉ'Ž^t4àNЬ•s"óy„Ç ×îx–ûx9ÚäaÑ ßö†ùZa¤ N­ÿ|DЖ:ógÕ»~ä)ŸÍ2qÂH\xüLí9E—ö¤\¯ÔÕo[ði¯M ôÿ\[ƦuŒ‚rÏd…‘÷¼ØÚ"`¿ê<&H˜bd^²³CJ<ëj¼ŸOÕ†R“KÏü=ïôÈz`¸säþŠjŽ—O>ÁéT‰#ñ¾í¨¡‚düXSfÑØú"UH½dáÈSgÿ8NI6“¡•9ónHigt•Ó𵮃አ?¯ârô¶r—ò!úFÚƒ ß&dðAƒ±e"U…J>•ùÓ9’¿,%‘Ú%â/˜B—Š/϶]ƒÈ{פR8·ã˜Úec ˆoÔX‡žœFô¤Åxò&—ŽÿôvÍ¢u/óÃñ¼Óa:;¾QÇgwÍ2ÕD1œuÃø%  VgRmU¬ˆçDŸWÑB}GŒÈÝÓ´] ¼t íN;ák•g ‘é‚ ~"`@3ö(0Ï:ž-*šh2ŒŠÂ°%ðM+Æ4ãgº0ÕwÝ!ΕõÙ ý­ ¨ìä2„2™ÜŒ!#Ùzüî:˜€F@_ÏCõŽ N+”ÍMÊý.à‘kHkÒCÊ nHês2ÂúúéXKÓ»Í7Ô&1t‘ Íû‹4ùø«üì,=‘ߎGgò×áZŸV>òÛȯÆÐÆ•úçŒ1ÃlŸ"šÁÔV¯ã½bùNO’~„“$Óœ‚~2Z:6¥©Ûavk‰K8Y¼x,nª—g›ô‡‰´2ujstkÝ/Ôl™­)SaÃeÞ‹ù‡$FMÕMm ëå§e& Êß,ÔZÁ/_·s¨NxÒP¬ä«[_p¹ "Ô½r#ˆˆâ@†ØŒ]„MÔ:†$Ѓץ,ÕfÑ § V6H‘¼ªZ%H/Í:¶"“Ãä—¸; `(8ý6ÌÓ 5¶ÑÎ-xS†ø÷ƒÆÌ¿°Pð_/×k`®¾’µ®L8nñh+«çŸ3)¿¨b«Üóðuà~'ÅŽs×à£!Ƀ.÷u²ô>UC×!CIégÍÍ€‚з*y/̤èÏVÑ.UgsLØLëX%ë^ž´v_µM:ÂÝqp‡?R­¦bU|eÈ#2¶èýDs†Œ¢.îž4 }*o}à—ØGŠ#Êg{xòÝê†Æ‰ƒ_20#Pý©„Ö¹é=ÍõôĪ]Îøôhº±j2ÈЄvÞ›>œºwÑÄ]±GÕR°øÂV5Q³„”B²àÜ52Žü»t}SÇ(Š6 pÄ©C7ïÐîx_þTnßXÔ<éLr$­%&.bö[Û¨‚^#¹6½… 5O3x*8xšþ4ÔxVf1_–ß߆¦‹ÎEÌ<$ÁÛHfHçÛö źq}W߇Jþ;ØU¦hÆrA©˜ ×£µˆ›¤[Î?Åíi¹‡ÒHäòçV¡/e3MåìsÊ) 9qˆ!Bûî1ä]¢ ¸Ÿ×£{?¬xÅÏÇ;X}*òs%KžPe«ï䣋¯ù/ÚLâgrµÊW XûVñëÁC8o‹µÐUÏ¡d…sn@øîj1%Œ+Ul~쨿d,gh…åÿh·Î™`ŽK®ÛüÎcíðLÞ(ºŸ»ò¤k€ýëÊâzQ%/½õàÒ(ù7] ƒ¿ó1Ìsršrø‹ßÄ¢]S„2_éå;R—!IS *Ò.x©ËÄl*§f ×yL­ËswtÛ•ÇÒyàꜩ ?s´·Ñ¹Ì¶z —?åºM¹©@’»^€O­sÇ›=!AÅdèÂ\í•Ñ)MÁoCOWˆß;5PÓjñîÁ®Â>(&Ó<´AiØž °¨”·µèäÞïõÁ}ñ|¤ŒvhÄ=K]> —' ,KaoïºÝèfphm©Ö¼©-'µýéÌçxÛ”Êã|­›‹å É3Ùî‰É%›ÌœZsÕ%HAú—8ݾ‹Æ°a7ÔN¸põÊgpŸ žlYþK ‚84.H#>×TjŒÜ›êðxkÚë«Ñ ‡Ù)ðÜEŠWzS¼‚ÿê¨OfÚê¸Ä"Àà(úÉå©ÅÚ¨$އ…Úlaû¹’´éGp™ÂäúI}·ˆq:^[Xómå—èw¸,pB7Rá qÍvŒg=“d³ªN]Ég^º­¿®…ÚƒÈJ‡ÿlïý}›sc¨zúð#¬[˜Ôu]5Š¿+©ˆ³ñ(:FR’ãÈznn¸‚Þ«¼_>»iÐ`"»¾1düûxØŒrÀõôÒ5õ?QŠ*i«.¦} é ¾Yr‹™¯L|Ÿë+‘µz¦bâFšaoª8ž‚?c€Ð„ÏcgË5Ué“Õ–1ó{t¤¬™{k¼y eñâ ŒrÎÿV±Lê5Ð+ß!di‰ S†w2SÖ5‹§V.w­óE>’‘[W_X|/ž.cÆ(ó¦ŽðZëÏéˆôˆ·ÒdÒ’à?ç¢mèÕC¿ü ³ Ê7ôð)Œ T]Õ¯^‘}-|ìÄ•ó~xfú&#sߨ÷Î;¿Ž—`ì€ÐÒÈØÃæÁ½Drg‚nµÅ宨Uƒ[”ÅÊ{¨t^ù5knÏÍ(µ¹~Ÿê™Ö+1ìSÍÃM»'N`·XžiZ~s`²Ëæ‚­Ã|®|¨ ,I£KÄ$ÁûAÏù ì‰À^=ŸŸ1Ö!Šêù™À*<ñÛaØB’§{êSÁœäIãìô¤¤œ¿žò_4¶ ߤTÎŒÏ ÎåŠçÞ„ÇâÛ¾¦žBX÷Fô¿5Ug½T³v,¨ñudB6âÍÑ®~’}\ŠXý81u_)‹3º%Öså 0`PBåg&XH*Œ %]1(‘°¹÷{ºH`Wÿ¹¶.Ïñ%&袄Nõ6´ËÑ#À]Àò íL…(ñzªðkp„Fku²ÏYmTÒŽæVê…p˜pó¸ÿ’€¦Åk؈¯óÜ gUZ··e05*‡TIö‹à–P ÃBÒ½¸íÍë&ZöhÕ¬'¾NãÔ¤Ï-VÃ;ê:N[ᄺá¤Èב2`É4Á—Fì:Wêžk춦cí²7Ô\”>Èe’¸'1G5êN¤ÚàÝ:A4•³‰?=†ÉŸ"H¡*\èce œbOípüZID÷QúÚâSu“½†§®wÿÑ%kÖ֣Ѕ÷+ôx¹JÔ<²qÚ‡½PEWý €¹¼V¨:߬𔵗ad¯`ŸNI¢ñËjuÐXTDˆ²¤žÄeÿ澃­:(ÎëÑ¥é9Þý£]LTù/þþ§€wÆ+4ìøíw*u endstream endobj 164 0 obj 18816 endobj 165 0 obj << /Type /FontDescriptor /Ascent 924 /CapHeight 0 /Descent -270 /Flags 96 /FontBBox [ -200 -301 1041 955 ] /FontName /VRKLZQ+NimbusRomNo9L-ReguItal /ItalicAngle -15.5 /StemV 78 /MaxWidth -1241 /StemH 23 /FontFile 163 0 R >> endobj 166 0 obj [ 778 250 333 333 500 250 250 333 250 250 500 500 500 500 500 500 500 500 500 500 333 250 250 675 250 250 250 611 611 667 722 611 611 722 722 333 444 667 556 833 667 722 611 250 611 500 556 722 611 833 611 556 556 389 250 389 250 250 250 500 500 444 500 444 278 500 500 278 278 444 278 722 500 500 500 500 389 389 278 500 444 667 444 444 389 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 250 500 389 250 250 250 250 250 250 250 250 250 250 250 250 250 250 500 250 250 250 333 333 250 250 250 250 250 250 250 250 500 500 ] endobj 167 0 obj 900 endobj 168 0 obj 1591 endobj 169 0 obj 540 endobj 170 0 obj << /Length 171 0 R /Length1 167 0 R /Length2 168 0 R /Length3 169 0 R /Filter /FlateDecode >> stream xÚíR{“¹Pø  €%‘€§€à, Ñoiƒ'"€3‡+‚™ŒX>`âŒZG63© Sø± [ÖƒJa*ä‹,G ð_8ÁüAïi, 1©|`;È`Bô‚CˆÎˆŸiš€û¥´ „y2S€ Ö‹Á ™Ib‰HG }8²Û@™—ÿ†­¥ÍÝ,–…½Ð~qV«SØL–è_ ›+àƒ0@æÐ@Z* ?›#ƒ4¦€½´êÁ§°˜TGˆÁs¬•Æê3Ïä¹1… ͗ɧÆt ‹.ò D[êD6¿EhÏ OÇР/á.})ÌÏù˜¯êEŒýŠeC‚™B ³° 2¡ìýò¹ä2WˆÊ¡1!€Ã SDŒ¬°¢BÊ£- _vMf@çÀˆ…\qxÍe.p‹o-ƒ²¤8´¯ @S9l6å/†€Ð,ÇûJ`4EáÅ~epš±°Á² ¸¿Èɉ#L0·Äæ8¼Ì0ÆÊ â1{þ]1w @±&ZZã—ürŸÑ(0í/b¡LÀ0ñ7W–ÍLgÊâA!HEH»8TÛ”ÇjÓÊ“\KÛ+Q<ýü²”{×Skòm-^õÛj<„¯´‚†ãê©ê;˜çÕòÞx]@Óèøßtk[Щ=ê-ªZ¨’ߌR_EDÉß)ºÝ´Š]øÃˆôû!î³ÑÇÆSOw]W¬ô~%žÒ}sP¡¼»ëãDRÜÞû¿IUŽÓŒ‡ó‘E×¼sÁmÏŸfÿ2÷ÚSÊ‘ž¹³:âÄ”æRݦ¾Ž¸^Õ|Rfyù£|»ù”>p-ˆû^òO’g€²>áá¶â|@nQ~ˆ}Ä‹üVyðŠ4h”¿²Ã#yOÞ–` i½Š j¹ËÎýŒî2°ª)¬‘mÝHªòKÖˆ«jÇÙå`¹Wr‘þ1³‘ãë)LF~øÐÿþS¦nã(5ÁHNç¢|°™uÃ.³W¨{]ÅÎŒ£PJìѾ£Ã–~•Í™·Ù¿: $ÖÍÒ£}Z]ç2Œ¥8Ä ›Yö±âä0³K’–#\…r¤Ð›Ð¦Sc/o6fà¢ÜœÃûcê»Íîˆ/ÿ\ê¢)NWˆl‘¸¹•®“(szVÙkêÛj«9F ±YÒÂì×± ‰ø¹Yƒó6„ÂŽyÛá¶¼ –+oÊIŠÃôâ²,^š&X¿]~ÝK#j·W·´~·á-0ÑÜïXÜùr¯ò4¶èiEn©j »¼8±aÒQr‹^g•&^{§LQ·‘ÑwÅïøjÙ¾NÅXÀ¡õM ]œMØ…«ß·`üÑa_æúLÂὣﺭ ~ˆFب ô ’t¹®ñyIŸR¦{Ü*ê®’{áRh¤"¿¯õ7&ið@Ãiu±]È…õöº•?ÿ>³ÙϧNLÀ°BÍ.˜CÒêN±ÅZHšÖÐ' ÃDªÓBÖlö˜ÔZ긙in|äÙÕ¥yÛÐIC=›kF|ï™S6PÀzZ–©œ|ŸÂÌDžÎм¿°s ñrqÍ¡·Ä7lºdÎîéƒ9Á>Í»oÞrÍ’L' ÈYMçɹ6IÇ ›_õGíîíIö7 ú)°ÔºÎml%ãr†ß~çÎØ‹å%™Á¬ä¡Á¸ÒûöNë÷±®ÓHowíÔ©M|Cz†cVXë,R=³ä“ÿqŽ`C/qþªc—H[µÿìÐáׄ¹O̺KÂÚ‰ç¶Òˆ î?©=[•| ¸>Y¿>ÒøAn³†®öŠ Þ”òq3×}QDbÅÊÏ èÝ_Ÿ–³;ÖB •õqú~þ­Õg†ß3›Ÿ®ÓòñÐ÷½e/χÚSj{Y·£o*•FkºGÏÉÕó1øñÅãþ|ÓƒEçۉр'³'RA3“’ZT¾¬Ü;²[8J~­œvm'â-W•&/[›¼ò$*ÑjuP~[›ðYš ‹Q’–>¼Jù£ª$Æ)jMì!\M äÚÁÍJÝo›h°pHa">o¿=eô’«¡¥ßÜ(:mô$lìIzÅš$|üEƒG:Qç¢É‘•&A¿¼¼cÍH92˜x?gOÒÔ$µæ®xÛEßô{³e8;U³_•¿ÕZf2Ë0õe¢¸Õ„­Œò>ŸléÌ€Óè/ܿɉh®&øWïÓ9©ðëd@ÒZæÎ~ûê[Ý-R‹ Mœ¢¥ïö‹sMÇ[ÍõìG.qkÀMÉë©$IޱÑs/‘Otf{Ègï«–^jŒ};×î±Ô¸÷ÜPÛ¨lØtèÉU½I‡®±ËüII„—*ÞùA\†!6´ªÎ<ßO+‚˽œÍب×;~÷Yú*²2¥>¼£À°Šùþ™UÎn÷­jã¾> endobj 173 0 obj [ 278 333 278 500 333 333 333 333 333 333 333 333 333 333 333 333 778 333 778 ] endobj 174 0 obj [ 570 ] endobj 175 0 obj << /Type /Encoding /Differences [ 33 /pi ] >> endobj 176 0 obj 897 endobj 177 0 obj 1467 endobj 178 0 obj 540 endobj 179 0 obj << /Length 180 0 R /Length1 176 0 R /Length2 177 0 R /Length3 178 0 R /Filter /FlateDecode >> stream xÚíR{ š©ÍOl‘0) ‚Ä€¾íª)’` ¢ l®8 Å4x\!àŠð P,5l„B€3•!8 D#@¾1žBøO €Æ“¦ ÚÁ`6 ó%a_C *ÂLúS6«Ì$…R€âINvˆyùoØúQœ% ¸¡SòS¥úK˜ ¥_Hh˜D ¢áƒ(ü#ÕœöÆù$ôǨ˜+„x6°@äi± Hï‰yA@ W(?ã ÌÿÑV¹ÏHÌ-ÎŽÎv_ºú9æÂ…¦ûþUõë”?ÏXuP(ð!OMFÄÞ¯;¿îbÂ<„ÁÀ„F¸(Ê•âɘ” DS惑‰&ÈK°šÄŠŸj¨) …qQ‚â©Ð4Jù‚N·ïLÅ`¡Dô 0Çx(—Š¿Ë7§~ÃÿTøk $2ÚÈ„F°sM&›ætóØï™î0.í642™l†Iÿß®b.Ìç¢üoÀT˜'A1÷âÏs‹õçë9º ‚‘ ÿè³L άI*ŽcÞ-Q1PfÎíw:s±íïs¦+ ‹n8„tUy~<%_ ¦PQ,ß>¦-Ú]³ùkpgøþ¬ûŠˆm yÔymÏwr¶ôE˜î ó.Ô´¼¦);·vÝ,Îð:våÈÐÕ|ý n}³Ÿê(5úDœmÌI¤›y²äB÷äߪVRu8„¬ðâÓäÎ턌³:ï$Ä'«Ö>Fê%ó?ªæÉ&|ÿÐܧΫ_Nåôhpú¬^Ÿ<–L˜W9Ùt­Ü:¸¢€Bå±*ç†]Bò#QK˜þ÷†´n3S؃«Ï×{êŒé~]E½þTCÿ cö“‡"¥{Ušè}0/¨wíXÑ?3O&Îß»Åw•·ŠÎÏçƒõ´¼¯ÈsîjDQÔF»/±‰Ãë†YeLFK¬å~6±E"<ôœð1˜±j,Î9`즫k]^åjåV/sthâh¡¤eiÖÃÿd¤IË»}½]ÚR9êì±V¶ÛŒ˜âüNud¯Ëšsâ´kMAÜÎÞ‘‰·iÚvšVù¹xƒ¤¹Ñ\÷¤pò:ESM ¡¸pÖ@¾¢´~}Åè(ˉ“ÎoÌ[>…ºùTÕ7ån]˜ÉŸ}êH†»°}HuÅ GNRÍS‹òÄ9VWÕGéi– q'î½|Õ¨mÛŒ¶¬ Yê¬vèPÞžÂQžñFIvüè1Ò-!l,ï²^*×–©ÏË2;ôbç0NÃnó3É,“òxaµÄ{Mu_¦Á©F=\Þ’ì±‹Ž„×>9èR×xø|LCsË!»´Ùž%Z„š00ö•^‘דdh ü&œH¿ïùèåØE)U‰ûm•™s»ë5ßö+õ¦Þ⥼[û[ä È놣:ËÕb—-2R÷>-[¼ÝÄ»-½ÏØpA !Íle#!»G §·hwÉõ÷=Ô¢eçüF¯¢`õõ¸€5ªÁ5¦Þ £j[Û>B—ˆ6YÚ†c™„²ß«ñ{ªM)ÍgÛâ;tx¹J~!¬”· Fmû®¿øäs%eý/K+Lõ3-ü‡Ü/߬±ªª½8ü&=NqĮʾ`h'´yVaŠš‡ZêÝ‹ÐOžaɯ”tÿ•üÀ…v­Ð Óƒ>øº)ákä®ùë&^º¬M(teödãø™fE[ÇsÿÐÍ[ û–›ž£ êU%3²ÒÁø×µ­}¡¬¼ãïµ·ÀÄ…‚»aóˆY){t£ùÅaÛŒÜÙ÷t ­-«*M^îØ›øjoþ3)•ÖÎÌïLñ f»k*5õ"n1Õ$¤AÓÈ+]û¦ñl›ƒ#Û·£æ·,~6\q}´ÍÚݹÇ^°Tî,›ÑCÔB†œ~¾oñºõsáA‹òd©ãðQëóã÷™°îR¥_j¢º¤iu^XœU.›ª˜¸³¼gæÛÒ]îWéY;„ã“Õ‡î6Ȭ®€k±‡M’ÛÝî¨Ø–{žSŸÀKÿ1ÉÐ Ò ÐPÕzVØø;)GÖ_&«ÈÙ[·«o®c“ëxet—^^g}¸{Ñíø¿J‚QÍ·x õaPºÛ¶ÙîÛ ²Êþ}t[«¡÷æ­e#/½Ï©…1Ûé-¥r+zG™×Œk¿hwÕYJ³/í¨EÕ 26!é*•Fì:îµáç ïð/“^öç§|GZ–êJ?žÞЖ[©+ýÔzkÈ»ÁgæßZò*º}·wHÚêf[×âRݾ¸™IÙÄ·ìUr4³åd¯^ýW|ÉŽ.ˆßåôzœ^åz½?é1ËÛ÷þÓ•ä«ÈÒ:a‰á¢GÆ„‰ý«†ëcOµ¯½ 0·¨§Ò¨É¢dÇ{ [<¨Íý­EÆ—Ú³bH*޶½Ûg™ÛÆ(Ý}¢çÜ0Íø\í‡LË>Ê|çLm‡ßÕ z±ó.¤ê¦¾i¾¼©FW@ï#ÿ‡ÿÂÿ'¹¨ å¢!ø.ƒVö endstream endobj 180 0 obj 2086 endobj 181 0 obj << /Type /FontDescriptor /Ascent 969 /CapHeight 0 /Descent -250 /Flags 32 /FontBBox [ -282 -281 1040 1000 ] /FontName /JXODNJ+CMR10 /ItalicAngle 0 /StemV 69 /MaxWidth -1322 /StemH 31 /FontFile 179 0 R >> endobj 182 0 obj [ 389 389 333 778 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 333 278 333 278 ] endobj 183 0 obj 871 endobj 184 0 obj 1004 endobj 185 0 obj 540 endobj 186 0 obj << /Length 187 0 R /Length1 183 0 R /Length2 184 0 R /Length3 185 0 R /Filter /FlateDecode >> stream xÚíRmXåN‰¯…ФӆJ¾àµA*»3 ±ˆÄ.b(ì²v(‡™ØÁÙYÚUXÍ(rýèRÒ]D5¿ÑLɃ^àAò+ÌES<Šb‰žY̺¢çÏùW3æ¹ïûyÞ{îçùD34—hÌ…h*Fd qŽ:J9{ª".!E‚ð ‚ D" qŽbè(œƒ2€††¢ RŸ P !2)"ÃB" `r,•™ÅÅ›vQˆÔB–"pÄá\Ôò3\‚‚œQ "50×Þ¡s¡²y PÁt˜IщÝa Á€§0©Ï}FåAVÇ›þ¼Í7o‘dh0C Q2üYwòÿ05zx´^£QâZûø‘¤þÄãZJcüUÁhsõdACB–-M†OÍÅA’ÒkG³1®¡ˆH:SA$F±§¥‹¦ Œ§8" dàÁ!M޶ÂÇ7bD¢LI”'%?ÛíSO×ßÕ#5ú{ͧÄRð.b¿ ¼Ÿ}¥:l&M0$Eg) p–Å„%Å0°MB€Þ±DL3ßøh @à ìkE€DKÑz¤o‰êtZ=ßó $™öûÙ?à( $é8;ü9¹œ1,à›BƒyS( BB°‚? “hj¡ÆD A·¤È¨ßJàpšÄYò7ÀNz–…47r9ùüŸÕ¿3 ´_dˆ°ÙŸ.ÜišYyv—£ÄõaãžÛ¿N9b²RdAV¦öÉä¶Ý¬è¬Y]/Ìi{m6¶Á“=äeV®zïÞVÏÝ5ÅåÛSÖ.ÅêÄß%Ë‹K^x<ÕïfLýÂyKWvNÕ±]–'Ok¿7yI£{yC>¿òÄƒŽ‹nã¦ÌýtŠïøöζ1¯ ¶Þs“þsdÉg áDÿ™Ë±1ñB]t±_[Æ ·ô{øýë‚´Œ¼¶¶©êžÈ“çot~ðùÈCµªî]Ãmï|‹DwN%l7 ›&,¾Ô”ë,üö£[æŠÁ|•« Î[~Úv¶~EC§dÍÒY'¼c'6vfý2¾qª²ä•L¤#pìÁž#^ÍÙדìC‹žÜpÿ¹ih;žSZ»Þ;êö¢…UÇÂ$ Íâ9‡7¦l;VïvñØ?PψóíŠ5·¸*[œŠ¥qúšû%G²Vß’»û‚Z.žµ­k©ö9w¯Íùê´ZY…G?v2Ÿìîøät.²»{‘ýÆÚwP]~{A$«[.M2yÀ_ª½+ vÖ¸9®ä.~V~TñNËD¿;ëÛ‡ÓÎ9 ›•ãÒ¯|ªl jß#˜èДð¤Ñ1‰§ÿªéеËê;±{©–BK»×Øãiµgøž{NÅÖÔÏ)27J¦ï»ÅU^xƒúw’C­M;cýpZòÐÉjÏg®ZÖñm—æpüê|¡vøÂ]£Þ1__ѱuwìМ ƒuëÖz¾×µ¨äÀÛÑ—Ò}'å›_ô¯êÃ×p»ÛOd¹jk˜S!RÕ“t³þ•*ʘxT•»Y4Ùã…/ØÖÔyÖ'¶µ?¿Úê2@ÙîŽÉYzãÞºó.oÒzÓÁ{Kã/XÄÌš]Òìn«ãÆÙa‰.{±æAц™WMhJrÔ®sv-sÙVÖ»ÓÝ<›/¸PŽe­tP9ÏtDÝ=ª¥â¯“‹Ã] ye úç^RÛ\•pâKÚÉ¥ãZÝ÷¡E;îÎ%®Küûœ#ö‡Ö6X¿šTùCaeS`Ê¥EýO,WŒ×"Z››DÒÁ3œúè‡VyÕj5Ý»l¹¡gúq÷ÔaãÐK«³–½}ì`ú’D¢oKY…›wgb+ñºßâY±Žk{”^ÙCÞÿ2¼8àdNN7 v_ûfKoöå\µA¨h^P2¡ßš#|èñhZë?«ßÿ±ÀGVj¸_ ‹ËI•õãÎüCSä§ê¯8祖‡¯¿ÿkþ©†Ó–Æé'fˆ ÿIÝ4®¬­òÔcË~ÿ•¿¬2=Œß×oN©ž¼…⎺ßÚ…É„ïû/ö]¢RŒñüb|ÙâswÜ'=hÛÖªçÅ›>Á^ÏÉ'_pU7/9©—°ý„üGð·à/% 4g9F‹³9‚ÿn¤r1 endstream endobj 187 0 obj 1619 endobj 188 0 obj << /Type /FontDescriptor /Ascent 775 /CapHeight 0 /Descent -960 /Flags 68 /FontBBox [ -60 -991 1147 806 ] /FontName /TKQDNJ+CMSY10 /ItalicAngle -14.035 /StemV 85 /MaxWidth -1207 /StemH 40 /FontFile 186 0 R >> endobj 189 0 obj [ 278 ] endobj 190 0 obj [ 1000 1000 778 ] endobj 191 0 obj << /Type /Encoding /Differences [ 33 /greatermuch /lessmuch /minus ] >> endobj 192 0 obj 850 endobj 193 0 obj 856 endobj 194 0 obj 540 endobj 195 0 obj << /Length 196 0 R /Length1 192 0 R /Length2 193 0 R /Length3 194 0 R /Filter /FlateDecode >> stream xÚíRiTWQ°(RY¤Õ§A!ÉL „åHe7T(jËaÈL`J2“ ’¦Y±( E eµ@ (k‹¬¨`ñˆA‘Å£´ í·SüÑ?ý×¾÷çÝïûÞ}ß»÷Z­ô! :D‡Ál˜¹€€!^~¶žþÁ[‚ ‚YVVž†Ð8Ix!4æ`gg¸Ë£ÌÀ…»ðy,+àIÆ)(<:†6žkÔ"p—b.BàÐ1˜”É!B$ ˜á­àw‰lRßM˜ £0”Âa€â"DaÑ8Á⪠1 /aT÷šJÀ(c Ø06ׯ"J@11‹@2oaŒ“ÃÔÜä>r‰$‘ªÓ« õHq‰â•€”ÆÉiŒþ$ŠQÄ\iöÒ›?†âré\VH#\äNDK0À†8=ÿ%Ë|ðD ÄiQ #6‹c:× S½Y#\ßàp/ïWåüeïôV<Ãoc¦Fž¶AêI`„Ì~}úlÎ[Þ„ˆDq"ðøŽ¡(DÁ‚˜T<>(a€(–°DÆ0—C4s0•Ib’b©› ®'ä25: 88.Nˆq§o@ftQˆ(V&Ad1³ð»?öð •lf:ÙÎ|À<>œxI†x¼z>AN°`Î'‚i„@ }¨i‘œ¢0‚žD¦Ø¯c1Î4Ã1«¯—¹¦~ž2ýØï²®ïpu§;«Gú´›ÂvÂѤ`~QÐÊhº|´d þ«VÓØn3?‘k®1uÂ|_@VÄd©qU}æwáûSøg8¿›*veæ<·µ¶Æoþº0mÀÂå 5X°ÇÒ®oÒ2¹S¿öØZÖøçÍ^½%k7å¬]µLÐwT»_ÓÄTÑïrpùìXVñ@í¥}ÔÖ8sa¶ß‹!§Óµ–é¶e½œR³žº€¡%--‹Zjï3í+ÉÛy~¶ÊB¶i³¼T¯8bgFÞÕ0 ãgÂèÉó&®¼0ŒJ;×ЇéÞm+æµ쾄”±ÛÓÌîíì%Ð*£ù~êλ;Ée–Cý»wgJny7L­á‡é4gќ۹Æ] %7ÁöS‚âòìê@¯¶ëv]‰^9Ö¹:#öæ¹=ªÐÙ/¡0íŸíw)Ž;“ iK²Ÿ_sœï×a¯ÊšÖ;±áãfÉ…ç,"nyHúëùm¦.úP÷¸ ¥yÓëuxדUŽŒ™sAÁ'þ¿º©ÎUØœ´W~Sä^ßžKúÉ6ßF»ÙÅSG§¤ðÀ(Zú¸#ê‰#«§àdkÛàUàæúd鼌žHdz?µ"iò°Å­mUë3ÞkÒo,·]~bD¨õÃÕí=ÁHV婞…•×ÚTh÷õV4± zѰ¡IQd»rí ¤²Ø“s^ìºoÐR§xüvTeq—¬Å¨§½ƒÿѰ²«7-åàÈUu7·tWgäE}yŽFzQ+YCZS»¾Œ5{Ø0£sگ仆ÊÜ?Öe>¥<‚Öµqïׄþa±þü§" †P4)E¨XÖ_M!a endstream endobj 196 0 obj 1452 endobj 197 0 obj << /Type /FontDescriptor /Ascent 782 /CapHeight 0 /Descent -951 /Flags 68 /FontBBox [ -46 -982 1283 813 ] /FontName /NLTDNJ+CMSY7 /ItalicAngle -14.035 /StemV 93 /MaxWidth -1329 /StemH 49 /FontFile 195 0 R >> endobj 198 0 obj [ 585 ] endobj 199 0 obj [ 1139 893 ] endobj 200 0 obj << /Type /Encoding /Differences [ 33 /infinity /minus ] >> endobj 201 0 obj 1641 endobj 202 0 obj 16227 endobj 203 0 obj 540 endobj 204 0 obj << /Length 205 0 R /Length1 201 0 R /Length2 202 0 R /Length3 203 0 R /Filter /FlateDecode >> stream xÚ¬¸ctem·&ÛfeWlÛ6+6w’›[•Tl£bÛ¶mÛ£’¯Þç=ݧÇéþþtŸkŒuO\×¼çXcQ|•´·sQót²0°02óD%•D¤èA¶&®Î övò ߀®fæ¿Zf 1' ± ÈÞNÜØÈ ÐšĦVV @ÌÞÁÓ daé Vÿ¦ICGGÿŸ’™L<ÿ‡æ¯§3ÈÂ@ù÷Å hcï` ´sù ñí¨ \,s  ¦¤¬-£( –RTHí€NÆ6eW)@d ´sÒÌí6ÿ>LííÌ@ÿ*Í™ñ/–ˆ3Ààì4ýuz˜þ¥¢8lAÎÎß g€…“±Ë߸Ø@v¦6®fÿJà¯ÜÜþŸ„œìÿZØþÕýS¶wvq6u9¸þFU—üwž.–Æ.ÿŠí ú«Ø›ÿµ4³7uýWIÿèþÂüÕºƒìœ.@—Å2Ì@Î6Æžcÿspý“†«3ÈÎâ?3 8-ŒÌl€ÎÎaþbÿ«;ÿY'à©ÞØÁÁÆóoû¬þg g 9# ëߘ¦.c[€ì˜þ572væöæËÍ\þ‡Î èôOƒ¨ÿ Íß$ŒÍìíl<f@s&E{—¿!Ôÿw,3þ÷‘üß@ñ Áÿ-ôþ¿‘û_9ú_.ñÿë}þ¯Ð’®66ŠÆ¶àß;ðwÉØäÿZ36ÆNÿ›¹±-ÈÆóÿàð_ 5ÿNòÿGÆÅøo3Dì,þÂÌÈüo!ÈYä4S¹˜ZÌmþv깺ÐÉdüËè?Í0°03ÿš%ÈÔÚî_­çø· hgö_“ÿKÒ?©3iêhÈjKþokõ+å¿Üÿ³‚ÿBSÁÞìþ…!*jïðfø{XÙ¸œr³°øü¢ýÃòŸgc'@—ù_ÛûŸÂÿãùÏ“þ‘°3µ7û׬¨ºÛ™ý¯ÿ)øúAŽ®@ñ¿U³2ó°sü#5uurúËõ?{àoþÇùŸñ=€¦«Kö¦|ÁV©i.5¸9Câº}=,C!%õj…ùþUöÝ~©á;<åFïÕ!Œ S¼­ž‹gdiGzpl¨º“WyD>d4½ùè›”í\t‡L%ÈiçšÑÞ× òÛP:œÌ‡»*ß Šßaˆ§ÚٜடhüÉÜòý±ÈP|MSêb±;ÐÀ0j ÎÎ)Nž©F‡‡»o¡{é²cá)øÜ )£ü³ …tÔ˽#h`Ò‘oÛ®?H4»¼ r)È È#må_•-òÖìÚäß¡ÓÚ„øœ¤[*´pn榢øE¦xfs>×])$œqù‰&ƒú~ÏX“MgÀÖ}z€¸¡îs÷®±­¢}íEÉ™žVé(©so†9 `fŽp­@kqp¦ðÒ[•³¾ÿÊ ·‹Mx\Ð4h®>—7ËÑwªÉÀSfmä,0n¸ j¼ÑQ—&+:Wñl÷½Šrë#$ÿYê÷È¥¥‹X™zÏÔP¢ÞÑ,?¯ö”8ÒUÔŠÚjI¸œ%AîË“€NG†‚c2Ÿ9¦ûyÖœî±e‡‘Z~àuê:€CŠ03_ô¿b¢Å-Ë#·±Õ*dj§,»kzÒb«þÁ[šü5¦ºÈñmxle*3œ?@ 'Ú ´ýA¯ÞŽƒá`,÷yžÔÏiÚúMwÌúeÒ EÜ!†¿#ÿÎs,¦Ñ‘D%2Úô•`Iòj®Ú¤À,j¦c ’õÈyè8¸þ¼à÷ñ—´„VßHîgeéߤX¢•w;s4i5c´W’GôV³$8"(5†§›­!üèà MK¯Ô˜YXN‘Td»³†´Ï7ì¤ÓÕë®íE÷N»° r#"-Ò<©ãOÁÈgu“ Ä7\Òl{ûXÒX¾yX²)¨+,f$ÒU5uåµÏ®]IÜzŸ0œú7F…² bR$gñ `Tk«x`Ðý$¸8lÐe(.2¬ñU…ó®1œw[h´"n*UòÐη PžþŽêxÉ¿»·6þ Û} бM DFª·;±ÞQÞç"$ªjºn ßWÏft Î/IÐO=Y/3P¾™ŽN 9”Ïv­¨°=IG¥ Ä@ŽQ5ŒÉ¢!ÄÆ_§xF&{е:ƒêyvòõ=Ò~–ÎÑIèiÁ^1κ° „Rq˜9tžIÁKâ¶£¼ø»LãT\›B Ìã˦œµ»1u3ÃÊ9ò˜ÊÝ“xL%=ÛÕìÔK`„GYLIÓŠ‡G®eúÊ/ôŠ'Q!å[.¤{ªƒSIó¼$£"´úMÌœ¦÷¨9*Øö_'|8æcËÏð÷ÔÄüÙͺN60 Å„Ü ñ,œµóÿþlöã‡í×Ô9—ÊÞU/4æëVÐf ºzO „­­M9B\qÑPÏT÷fêÓ×Y/T¿$%n$Õ¼ L96n¤sJ2‡ÍÜÕ™u‰„ÀuÍfûdh¥„ ¿xÛ™Ïä—&Në,Ôdôyèç/aÛ«®RQ$p‡¶™ìa! *VßaæÈãâ@ÍòÓ«¯Çˆœj1PCa ¡Ä“Äz§>ŠF»¼cú#ïùç‹ö;œí;.»/¸|L€d¯j²|^BéMü²í½oKžãáÌy¹)ñ:d¦µ¿ºÍFHÜßQ|CHh zÆ¥ø‰÷ótF©²ÝTìúf(c8øIXA*& O‚X2)œ’k*åbàÕtŸêÓ3ÊcnŒ„»´ „s­Ù¸éBè2pNê5Ð\œ¼gr— ó{‹~½p3ø´ZüÝÓf ×b_þÌߣŒÀOd42¦À¥  ‚I÷V‡˜ô.…/Œ´˜\qx¨—AªO¯ð ¹¢£ÖÂeÓòвðOM?â—fß,…¤øT+ñ`v}4˱ ÓT)Uª%ziG¸uJÕ¯R Ű²»cÙF,¡!^‚g4ôÀa˶é“Ûyn„KT+WPÀý‰ÅÉoYI»¢GŒAÒÑrbZ"laÆ Êý‰9/ã,?ztA‹]E³ÊNÝ[ò 0<äþÎR~­e0„ôUù·dâðØ’næ?í."Î.Ê÷Ï&©Ö>}˜ö?Ö’’%·Xˆ¢¸vŠ ®¡1¹–+ØÃ> ­Õæ™u$QC£W´Ø®ö+øÓ`Û½-™á‡Ìmª´™ÿt…þÀaÀŒ·êÂ<Û¶5T Gøé-Öüg¥•v]/äÅÓ6÷>âœ#ÚäæO×ÏáÙ&UN:²ZGËD6­øtZrjéÍ2_sê=ʼfB ']R¬¤ ìáÊ4“g…³'¹ÙŒ~/_ý^`¢‘zµ¬ÝRM^ˆM]?Åúyˆ*f‰8900tc]ûÚ&Oc°wN-oU7Œ«¬J­ÐV™Š«ÀÍxy˜šv8s¸ÕYq¦ÈÓï6s1äkêîê`5œ–îšÓY¤7ë¾n¾Îðÿ®öåÚ凸ØHDcQ¢Â> ª­Fß›¬ݳïÎoÚ“Iûy»3Æ-”&€Ó,YõØ…ä'É;ÊWçùC·csa™G¥eœÒ”«"÷{±[øW*žN‹¹õUXœKyBƒ… CHØAý—‘CªÁÝ×@ü¸îÖ¾'Ø­7Ý‹ò—WgóV×ÇÀ“]CN›ÓHf’·ÕP3|ÑX™®Ð"Ú'«³çô\gº¨ꥩ®1î§WKèùZ«ÚSg|×Ã/Ú,±Â˜ÅÛiϳ“»ÜcÉwî¡©p?.ÑsBKº¤žmó¬^àªÀа¬E ±Ë³¢(JC'Ä Ù‹™D–Pˆ ë`\@B–JðYíÝ’:t§F(8Í„f4áPëb ñOÐ`Øë7:·Ýܦ´saöW*Æ6ªû ®ÁmõŠOãNøqŒÜvŒZ¼eãÙ{aÎõ°ÇŒ £ÃÅF{¦}®ëß«ïÑ¢8^bSwV©>Žß0 {„>ŠƒJt¢&:C˜cé$Ńì†iõ8q|ÃJÀ‰¡àz³ÝÜÛ×öGtmò É&¥$ã<âúu N“Îè²eÌ2‘ÐXÙ¤ƒó9_`™Wºà–úIQû6 (gã÷1˜ïÇ,—04k ôÍ ·€íêƒæ^7„ä²ËcÒÜ<ɾo9õÜ–l±u8N4KHF¼ßès“í)¹œ M`œÈ nÇÌ«€€¾~éÍc%ߺäó þ*+J˜€f}Y±gl¬°­=WÍ/N*Ã:g€Ò|:”»–Ú _¤©Jüj/4¸J&ö bÙ¶Úønq覆?xýÖ9»3aJ•ìj÷ôúÍYÔ„ä>¥ÄO…9ÕÈ£nó<Ù”* r˪ŠëxL8®äÛôøG\áæÉdÌMUHγ)‘e=èÁbºJp ùùàÏìY¿ÌsÚù„î?rÙ´‹ Ï>>()N0‚¯ù¦kE³+4ÜJƒ³»-²ÕQû«ÔÞ®;K¤D§+_°cì|A;rP×c§æ\rD«[§,iº²o_7 m&ï¦á³´vóî‘e²GÉÇ‘PçSm¶™odiÒò¼Ò6úu™éH^JOãžæåò¾áÄêšOeׄÇšÜÓ'#Îcï—Á~Ý1bNáãѼ[åì.Nc‚HÇ*‘•ÆmÜÜc´ˆð*9ñÍÊø. q~ùç,»‘_¶ðŸ®°?öHBïgíï½õSKËAzjy™¸]O4œx?„W¶&¯ÚIoâzâ=·Ëo¤]ü½/Ú›³¤7Oï~+Ø¿ž¯å¤Ê›—s ôÈ(â‹O6µ ~¬ Õb3ÖxMÀió~*®E`2^ R݆‹¤3NÖœÆT§Êþ¡h±ë;|*û€ÕÖÆK/Þiþ«’X£†ã}é趪H„éRÞ§¦¼½`ŠTïõ‘n»ÑƘR8ו{‹„âQu½qžé¹èøÁž˜pItö3¡EÞ¹:-°Aê.ãëÕ—×'RÁ,oòAŸ¥•dìuòcöz€!¿De«•¶Þ»Ëþx”\d9<›çOd.Ç|Éå!Ÿxл)Æëõ{êË0 «¥ÕiœO ÊM%ìâ ´itN÷ÊÆcŠò“”Ç`éCq–ŒhËç§;??–/ê1«cûŒÄeE2¼KÑ1´¡¤ƒ’&îªl=yÂCXIØÓùB…9¶¡_yîlšL¶î˜Yô&–'ƒÚ(DKGyúTpð O¥…–oï;òçËj·%ò&üþèSÛàדÌî×ú¯/Ïò*,g ­¹z9^æ -çÅJýÄlG)æïòñ´Œz™75¥‡zA’>ä¦kü¢Ú¿ZR”ØLu)Æ&›c‰k󄤯j//½8QìF ø¸<ùÚ—Çwy¦`|ie1Ù|è’¶HÜáFª‚œIuGXO0»*¶§Š;ž’ òyIÄ´“ðR8mÆ” »ÛOí±i§$˜ R°Õy8:`³%ÅŸã³K´`oA˜ôþøÁ²(åöòùÄ쌅N:Þ¸Fe$›¢ÇЄJ»4î)Íù–"Ð/co»³© Sj{C3óA`R[õEüõf0Dñ^™¾¶¼p´Ê5ö;Mÿ[ ]|7<Ól¼xOËð»EˆŽñ=þ ’4a%MòßSª*¯~;(¢ò ¤:HÒ¥ëQ”fMà ¸k3lí¼4»fß¹œ[Á|S¨áðYðÈÂ~ø{í,’½Ä«¹óãQTZš@#\Ñîî ³Ñkø7( ‡ g´\Z•^ÃÝiX;9ûRBº~»¤‚'!3*õlo™òî‹f>djë!14à&ãP‡e–œš^l’†«úOmº ¥Çi1ˆ[uT¦@Lq¾nÚá¥Å¯§3%È­ù¿òtŒ½¦6/)f5¥"œõ2kkœ×3– e¥ÄÞ}ó¬úáju´– ܯ\ò1½V÷¶äs Ká¤QζÔo„SöØÃ3Pu¹–ÆI†®²[ ¹fÇ9’sí"½ÀÏOoké#™ñÅõg„)öpµ à»œŒJ:Q™Ê(ž¹ÉɽpÖZ¼F"À1±u°¢Ï€ö•ž ¾•]Á`¢sÿâwjÂ’ ŽÆ”{Að·C«:~2cŪ‰ç|óãÜ 'Š œQ4ÍŒdöOdO­»~BŒÜKUŠ„5-'=ãa‚6 ¸E¯ èá¨òÓ{³£ÄØmk:¾º°É-¾r£ç™|…¾=(9ZrwÁJ%€ñhÿÊ= ì Lä9'ƒ/©¶Ã¶Ã4üE€Q9¼YŵǯB|äØFëÇ<,ë®ðAËϱ‰Ùb™neÔ:o¢ûlÈãºqçÏ6ù.烖GÃu¶ÚqÞy–d£¯x.böÃò(Tò¤ø:Çë­¡¶±þÇñk)Õ~²^åÎûýæÚzÆò-5»Pµ› Å>, ò—.¿éöE‹N°8Ò×Nd+°µ¢åf#=Ðe$p3Rñ穼œõÛèon”—&t-úÐhšÌÙSò¿•%7ïJPšú¥Ïd߱쟷£¡•H¼}=åƒpz w+`¸W¡…¡£É»[ ]]ü`,Ùü²Ti½Ø£è×+¬…ÛÊ&ZŠÇÅi[9‘P1p¾ \UòC…9ü‰ÕMw;}1#-;ýµÍ’%£he(´ݳïòË£½àüöQI‹þË[àñþpª•ÖèƒÂïôÎö d52ÉÑš)Ú–“ ˆðKŠ©}òðÆŽÙGÑÂß1lS´õrÖ'+Ø~qzh ØaÜ|éÀ¶û¤ûµ‹†‰F¡¦‹Xƺ€*×^ îlÂà ’~…<¹NãiiÞƒ7ë»}hJÂwþªÔvnäÑ€–PuqNn¿ái¥š².:zâþ²'½Z‚Ëäpü¸Á¨ó';õðÍëG¥¿R'®|‡É‹Z©º²›N–œŒ8pno<Âkwë9®™¦÷-MCð+Wà 0Oªš<Ô'‰œ3µªi/yJÌMZ˜ÆÁ»/ò‹º¼ái'^¶*ʪ8ôIÐ} ´ÖX«1Ž~§˜ù†“)¨ö™&iËSèM“ää†ú ý»{©4*Ž^tc Í»èÞÖ¥u>L‘\;Ø3n|ì\¶ÑÍùÉQyþÍè´~±~¿oèWÐR‚8Ò˜¨£‚£ˆOA°Á´cgÁÀ“Û7ØpÖ›–a÷¨­0‚dÕƒ¬%[>ÔË¿²&NÓUD­³ÿøIR؉mä`ù“ĺüî •€¦N÷ùØx‚¸Ð¯9+”}CúñZÛéX5._èP yŸæ·ÕOLOSŠÕzÂIí=} ã.¢¤“¶qD¨6É—!]œíðYû3ËkÑ»·‰Üí²±¹†Ð{69'L8‰iJXEË$TÊ|ÂbBÅþ(šxß@ÈÏ;ߘ1è_MžÅÒŠãþÄ(w/©ogúeßö.!à=ÍÈpJËy ´’Òù·îXA¥[1<—‘ô-@O9aŸrP,à[é”0iù’jïS/œ:¨ð§¯‚#í;'¾Ò3txÈá—·($Îúz‰mËEC\ϰ†(KöÔY±æºû¯öå'Ö¿¡­Øív¯<—2§Zî`)´=JL×íó)ØwB‡928ñ)‚MšÍ¨õ*ÕOõ›J¼úx‹^Uµ‘ŠØÚDÈŠÕèËù'íJŒF¼Zócˆ0zFÃõØ‘ ×Ô°õN毓H(ZU]?.]‘Õ„ÖJ¢™ú¨‚5Ô¼ÀânØäÌù_oæâ¿¢%)àƒU gŠ=Ö¬Òc™'exÁs”‰œ6Ed¤ÇÝîfŽyV“†àVB˜ýdc#I…oþè/Óµ¶Â‡/1ÁGg¦gg˜`­Û2hOâúaŸP–‰7ïÃÿ;i†bìϲ;çÒÀN„‚øíUPåÛgþz=8Á r¨Ú ý/öWïɯýÚJ4!mæƒe>î÷$¯"”î’¥©‹?i1K ÅËDò†‘£–]ü³[ÃtÔ7‡PªpRnÕºæÜѪl_ªÚh¯®‹};÷ÒÕ¥SÇÑxb5ØK²Ø"—6?;¤ÂiÊ(¯öÙº æõl°ä$&r°ÈÉ3”MW+ÊYsßq=\JÉúBA h$´z¡ßüâQto”´Àƒ:Ýâo­“abÜүൻK-b”Yʱd+êx5‚…ÃMj:Îð5nÆ+ˆ…¿†´àÄIZÂ0ünû?Ý9 Fªži‚Ž,zP$Û©rbLG +c¬}YWäݹO†1ãw=ݪsúUáÞ³G-íÍÂ9›A,Ä.yÅX¢qàÄ%m‰lÚ~ÒvÙð“4È„Ø[7?HéªMCÕ.z™˜8O…nmðhŒ5ãLáÆÅÕ…b_C¬¡å)réJ b1ÓZòÙ9` w| °íæ8Sð°H’ûκëˆ:®“~A¯‘É{ö’N$WçŽ Vá:G×»š‚/¯±²£¿¼"ƒ÷Æ‹OÓá¥F«ÄÖ]î2Ê$UðüRÁ"DS ?9lÿàçÇÏ„èU¿ÐÚ…$¢e—eùyh9 µâyDÜü€ÆfgQþYà´Û©„©b+)´ÉwºLú¥\.Œœêíä‘ùðÕBGbt0æ2¹XïKØô¾½[¼öÌ”R¬9ºÐ)Éx1˜w,Û-ÅŽÜ—P­;ËæUP²(eCŒ˜$íÎzâ0'ħ¬r¦{¼AÙyf–I”JËžPlâËe‚[ÿÀ\(Sì$ÞÙCà¹î›9ʆÁòž‹„13µ¥:®±[¤.Þ;-ßCA<Ô&Zƒ¦wÞƒa‰òégåa!…tël¥ä`âÍ­Kí0G¨µÕÓ™ïDå`,x‹f°reÈ.ž<5ˆ€Ý™|n1ÅQHÝk'Ï‹*¹I¥•B ›o’fÉpíkÞÆùSÿTçt¥6úi·y ô8Ù©‚Ìn¥ãp÷À¬OêÚ!0&…úËO¦@ƒ} <¸m×(' ~”‹U°Ù#Ïìùwêõ4äO½Ú!¨xüwˆüÒÖgyˆ™ò›ã«A,kÒ”WACöâ‘HéJŸp¼¤«œK,ŸéÉAˆŒíÁ£+<Óß·³]U%éªwV‘ÁhÉ,|¼ jK%](†°S¯¼w‰ºm Q=Åßù2$ƒº¶ú–WØqjzfP5Dž¯•ôƒ[Æ(†ž=Ò=`2óœF,:ŸŸG Õ âFßxD@&”¿GhãS5#”zÞø† ëY5cá嵯qÿ°†3Ìw7ެlˆr$Þ\)P€Ø.Ô`ÍÈÆ>Ñr?Vîäæ,晓—£´ïÇC*uv¦”…Û<ä ¬K£âÏ"JüΟ•ÐÐ;ÀBp\{/e«f¿œ°Ãz-M÷øY‘ÊSëuìòõјðLôйðÐô­NÉP.ÎöçÍ*ÕEq^÷Ûç½Z&!ÔÁVŸmWaˆÙ»Oªx¦´BÈžiÒhîÄÎÏ.°47Xu1öU>¡·}.Tï#ÒyeuƒQ„ÙëüM†s…?(ý8.å¬z«—dNâÐâ?­É˜ø÷êI߆¾X‡Ä&$T§åxfƒÏƒ7I­©ÿ®„âTí¥á-ÿ+¾AšŽ ®Õ‹Áeu=èúzEh0@¿ÙC5\6ˆUH'©ª×±Â?·†BP$È…1ô`M¯¶ˆVžºJÚo&‚Ê9ß7G³ya+1 ~Ú4Ð}´^'e&X{£Dž|bwD$ñ94=gtñß8Ó$f¼R¤³^$ÎnnOÓ'# /îá1°¼Ø§õ$'ÿ ‚âȧHGt©G¿FŸ0…° —úh?/lRzD9;|s1Ô4¹d¶kÖøÄaéÜ’H’Ñá4“}z»M }PØ|øè"XZç_êênÓæß—ñW<Óùùg£ Z‰Ræ|‰|úŽùüÉ|“¹]9€§ÎGMã­ddÕ¢4˜I ÕÕñm›{œå½„-–žêðwìs=Æûpqˆ;8< #¤æâŠ_]xãQà —ãcÏ$}z¬Cí–„Î85áÊ{`Yiœ«õgÜ ›n b,KøÐ‹œÂç.Ä:ÜEô]z 8"õj¦•”æÆEuþ-|1x“­8õ4&ê4ö×ìZ49C:˜u®_]œÉ1Ôœ¢ó0%FÛþÄùžÁg©RíøCåMaW~7)O æ†s–4(o!“É(]F=žZoÙyú9"«ý. æ· ¸—d‡9­¦¢-¼ q©nX~Ï{ŽÞ?Õ%C”™ÛAÀUBë;GƒðÕ°ï0}mªo 1MÎufíªÑ†¶œ©=Ùy¼åâœLà~àÊñ ;ÒÐož>’mNJ Úëv/xF«ú…òøE‡„ûöªœ“…VºÅ²4W&×°_ ãö¯£ËÓÂýÍ’ÑlRZªÔ¶9 ]ÚV„½Ÿ Ô$ZÀŽŸ¹ìÌÛ$›ž’Ouº×€îé5˜ŠEˇ'œJ­#9ÛGïbØg‡µJâi(¢ÚºB@òË›ÔoîwÛ+ÿmNµT¢²5WM9º­9ÕhÈÍqºpí‹m‰ø]ÔÄ…Œ® v 3­Cu]ÏŸ¤Ù@<Çð Äv/²Q¯wÕm¼üÇN1áø­"dã»w[wU« A¼›•Ðý¦Ó3i‘âUÝœQ5Î,$÷ØŠá®Ä‚°µ<¥<¯³8a]—õ–F<»P„À§F_µ€Z‡!Ô3û(ÜX…IQ§ãRÐgü%&å×ê Æ*qBŸð‹Ü;,òœÅ.OÉmÈ9c¥³¹W(q6ö߬zÚ"/´ÛYwëD©l )´V %?³!C¥"72dãícÂÙàcô¿ÙÏ(x¸—Ÿ¯{Üúa*Ú ,í¾]ðï€7'x>­|67Ú~õ`òºbpÅð™]¹‹Ž*ä\°`žp¤X)^ÅêápoY²«`D}·rªrð¡ù‰¼ ê_o·÷ZXúΗ~]M€ aϘÝrèïAÊÜYOã/RìC“é<7¥(iD|×ý†¤zq(OÖ1óHY¨IX[*úÑPiž÷éIóþ+ ™þÐÎMøÔs†òk*3dï&ÐlíïsB*žp? ðõ´ý¤Ó„ä^(Ú=\XÜpoï™ì°²½t#h²{èòÌ3õ’;ª—œ–kx'^<¤'›XzGwk¸°ÅØb··Yâ„ØÜŠçô Þ´êø5 ñ©BÂv‚YYf¡ô©ãÎ:$ *¥‘ˆ‰O. Á-$Pzû¡¯ùP›É-1¨ BŽ!$bÕ'K[`Ðä¾B¡-úBiÉ 2ZP0vƒ{ÇßòD·ÁâÖŠ€¹ܸ¬]u­Z”mÛÍgª[b¯DÓPy)­ß&ÙÉ,A¸šÔ Èa­àþpÁ¢;¡©Ãö¡i›@¦Ó=â~ ›.Æå«êÌzyÙöÆðAIÁ²´…ý°H®Ð™ÒšièÈZ5”Ý1<Õ‚IdÁy5øc=ìÅz3R]MÁjkÖËÛ{õøì°k¹òkhð/ÿŸ¾:øÈ$oµÞ…_–±ÐßÁ(•úˆ»W ¿÷mºæþT0­mŸS{ª(ð4ñJ«§¡AÔÎ|ßžDÙóú†G9 G3á?É¿´—Å¥]w!ŽÊCâå~³ÿFMûóó>»³×OÆ_¡0ÁÖ•@“tÃdA£Â,‰µÙzJ{ÓŠ'D7ýóÖ7 "âÒE¼a¾¬ûï‡jÞþpý‰^uïÏiÊùèq¡mí¦7t¹~ñKcÈ)]àfF‘G@ž<~O=üP&Ëj sŒÕÖÖÎâ²UGm ¬ª[²š¾÷ÚùïœÃÉÉc)i0×Jyñ/Qšc ý+i’ô§ï‹xÒ5êfì¯õì­- ßçÎïlØ=VÝW”ì/œ~^žWVèÝŸ‘»86+ï\gÊ×ÀA Yéºm"¾Þ ’d7:4H`n›Ë©"”B·Â’Ô_g >Ì1džf `œ^ð›.NKÃCe‘áð}ã["C‹¾½¨òmÎV-÷å±'ïÑAša-]h~DÂ{‘u`Í¿üJ´PNýTW!¸8 JÎ×{&,ú4µh¤%Fþp¬ë•F¬FëÈFú8„* hÆåáYJœú8b9;‘Oé†tFã%Pt9\·¨íþ™ÉÍÒbÜ;TWÂ=‚ãã.¤g Skø‡N†½Äò9÷ g¹ê…¼¸‚7ÖóÉrÇI%„c™^Þüå‹Cr“µ‚ÑKýÕÛ3PC(ŠùÌP¿}P‘(*žêàw.¼Ç˜Äذ\cÀ´²˜©ÌÞ¡úè³&Ðc$ªËøE‘à”!E5@G¡ëHŽð5 S{Ûö!±°üÔnvoV}§Jøôû}÷ÏÕÄIÁ[ÓžLÜmùÔ¤Ú\Õa³‚¡ß© œÅÆF:žxüèkgyÊÇ‘÷°‹•L–j>Ê?“uñ#º–0†~|ßÈÞ–ìN'‘ ºQëè7OXAN!¢ül¸}¾Eß´Lò"JWqìA[A¨i*Á"Œ(º ºÞ²Ð=á],‹ïÈ8CÍC™¶ÿ®oôZpè„ú™÷{¯mø*JSÇ~ö*åtÉÇhË„]•2ž·¤÷ÎÌŒÕÅ׳ÓÂñ5|‚Öª}ž)¥,“]R¹ÙC@LäôÈqeM…–»(Ë‚K1Ý«QMWL”ya¿i³- Ψ¡Ÿ]ð—תm$L,I9«¨zJ«Œïr˜UIÉÔµQkÏ‹{4ÆHÂ(.~H¯ªž‚Ê›Û×í“Ch¶oTAŸ—[ƒ‚´2¤¹»²|3Ó³n‰¯`Á虋W`ç°uƵ£ƒ'”¨©.ð¼=šdfO,Ì”:… ’e¨µA•PõXqÆÍzàÚO~c[2š$:–%pŽvÚ¤ŸˆÚUÃ0ÉXÐÜîhYfäݔأïÅ]%Rã‚]ß™á0'DC®e·k01+ïtC3êÐâ%ÈgÏ/4o¶ ¸kà;J»jŒŠóÂkK<ꮞßÏCünþ±fËôþ°˶ÖÚ^¸d¦I­d¾ftp2½ÑooŸK61 ©Éçò5ŽDOgÚ¡¾T…­éäNS#v.ß~6ÖËB—ø§jƵX¾o{Žd°ñ`»¯btê/ŸV?üˆÙç-Tþµy7v(…­ÑEB€zß9¢½z¶gJrä4É㈇3¨ÿ^¶Z˜k+šl‡Ñ¿ÝNº1¹Žú¢ª} ÖõâdbÔ5Ô³¥ñ¹¦;UáKMÛŠ±¦|†Ä6§[¬Òpò›¼ŠàN¡×8²eÒþ`‹`œr™õZ§¨EZé/‰"v½$®ÆZOF2p…üq<1Fl,sQá¶ ÐÃB_QW×x‘‰†ÊîÏV÷¶6Ý`üá"žÓ °¯’3óÓ$¥²áÑzÊ&åV­}Iõ^x`lLìiGê”Bž ËKÜÀä]oÁ@B †ÖB_£Y%›×gÚÌš¹xÑ4Í”¤ù4ƒT[÷ª1¼K÷פ³½óo*ž­T6©t%3'œ¯å;[e¸û¥~Ññt^ˆx#Q×ß{ýÕvuMA·™ša Ä|2 Å5bb.‹51½ý„F€ÉµkªóE…3[MœM4×,޲iž÷"4$N›|Ò^ªN'ëæ¦t˜ç×TNeÏŸÂÀ¾è"ãgT}.k¤,†”› MXæol?õÝô‰œàÔ®aiGKPZ}lG6­¤ü¾•QO%ìphY&¹CY¹„ÍiiµÙ²Eìöù¿Ñ'œ,‹H $:bU¾hG@êL\£1®Ú|£‚AŠŒ«A¿µÏ{3çîæžë”%à,c¾KÁm£äšwØ5™žE$ûQ»Ç¹‘#ôª˜<Ò%Á.ØÊtC™ uŰ»[¢åßÿ^‰Gí¢»Ñ9êgRq5ûÌö¹à}ðÍvgJˑ݌®Í¤BtëÅ6zl]ÐÙ7¹ºÇbÕtn­…×~¸R­<ÊàöT„2b{Cã'˜ÛXcD‡¼9Tf)]Æ-“C·mò*Ö»¢7B)`Ì…²Õ% V¯”ð‡Ö»´6òüI*Øæ¨Þ³úÄ_‘ƒÉQ/˜~Õ`c€¿,ï‚·àMJ÷; F‡e¹íhQ™Ô¸•£‡#Š¶Ê˜Ÿ-µ•O® âáÕïHeæhÁº>»©ÿ¸ d—‹´ÿòØû£¶pÍ8Æ: à]5Ž⼬¨Kf@ coòÛ°tا5¨úNi4ü±/¯'¦KÅ´»Ì$cFa¶ .›[W:êM²'À)ÓÀ° q¶}þ¢ÛÏËúõsP¥ì×`Õ*ì×ÅSGÄž­ž,—+ëž(1ÃòïƒS5EòLWÔØðÂ9‡+yÑ;4©S®Dpý•¡Naë¬H#5²Kï #EQÀëºÂtÅp§Sö‰ßEc§u4Ä,,5¦[5M¿s/­ÆglK*ûˆLdŸóGk³¹LÕHQüdôÀËžµåÕ¹ü2¾45¸Ùo……ÛòïEœûÏ·¹ï (âeOCGE¸oa¼A×Î5s( è¡x¨¸»x¿2ä»[{´r‡„ªüeÑsÔöqó˜)ÙìÉšÎÏ»ÉèˆóÆø>(ŸBåS™½S·¼åŸ|Â&O‘s¦t J¤!;ÑR|£ŽUä„Üva£¦ëÌC¤£‚„QéDéB·„tÍñoó7%Ai€®UáÇÕΤ èg34òþæ]gÙ!Ñ€$÷“Â>)ßÁ¨-î.B$ýTã_3¯XCÈ©¿ýc”Œ?PݤX]IÕ²‘,›VöÖê5ŒtyÎX¢­MS˜~± º/­ñóá”Úˆ†°°²œ)ÛÊü(Lw]òî˜Wü S^B S*âwó\?“=U æÛzð¶•¼›ß7l’Né¥h°rÁ9–kÂîý–„õ¤4Eìc‰|ç“Óß6WÑa½1Õ1£ÊŠ'¦¿¤úÝý=ÅÒÅà,ÈÿÔoK ûͨ¨žÜwXæ0RUòUmïZÉ5/¬<á0–‡iüÝsûΞ‚+E¡«Qt7Is^0àÏì`“À˜`Õ8›Ú®ÂÚdšìB'p–T¬Þö Ì ¶V%™ /‹®`ÐŒ{ƒ¦í¦;ûy©ãõÚÜ¡dtÄêö˺\hÊ5r—Ÿv¤w]ËÑHfÜMç>§C/–lÔD˜x* oa2Š•X˜žBx0NíÂŒ‹†º$KU-åݾú¦°³Ô¹­™u‚-À¦wP·Üãeȯ’Lahn—ž—«ùÙz\ÎX´éMÌÆÁS󦳦X<õô švÔÿ6Ÿl(èÛR)Ôì s¢ ûî—ž|–•èH!aáâÑ2ˆ³ƒ¢Z&æ-üU·%cÌ(PrÆQLU­ê¸@)âƒâaB&rb¸Zw›¼Q&1…±¥OSòE“Û¼é\ṫÉral‹«¤œ…¸êãâ ­ãö¹O8õ¤²3º™–8åjéʆtÞå3¾í4×È’-ÑŽÁ!r^y’˜ÜÅk5¬6º äíVÝšq¥dú(1„1áâM8rU»ê,NX†–þÓmn ºŒ¨ˆ¬h~šÜ²ÎßX‘pÃrl&Å—IÚ´?Ãg#¨j'ƒã–>#˜Îm3L¦ U-Ÿà£šÐ´U"߯Mc½«H°]÷ÄÐpƒáæÞ“±Ø'bÑv.ÐÕ§dƒø›‹¦–„ÒãõKmm¨¥æ/îˆNö¹¨¿dW W—…sƒ6‰¡†¦U‰B¦–*@¿œ°ÇñrFb墚Ùt°c|Ù¡F;çæW õAúB½¸¯Je‰¤þ”5»&Âèó†o)U5CŒXAW³³Är¯'ívòG`ÐŒ ä˱‰®ê{¡<ÅØïE;p Þ:ÉÌôst‰aåHŒHaäR2¶;ß“ï’MhB\ZŸKŽE_jE‘òbW¼Å¸i$p²-9’ÊÙm±û›s¶øö½‹ÖU¹ns ^'ȯü_S>O=E¼Áüôû@•†M·þ(Œ Š=ª Pýk÷cs¯¶òºI§ª ‡!UªûV‘„¼ÐþÝx (jUqíØzÐÕCA®–öΪ¡Ò TÅK«ù¨àLÉ.•ßcå ¹=6³&¡–¥Iå]ÿäìH<"ÆØÀ¶tPýÚ¬Šê˜BZGjäó¥KúdýF¥A•@Ý\€ùâ|ê¢[‘èZjl?‘8´i/îò_ÓúÎ;ç ô™wqž„wïB3¤mÊ‚xï}Æžå[-˜ƒ97—_DÞ}¿˜4ÓÞõ¿ÀºœÉÛ£)_‹aØiƒ¼U‹3ÓþÈTÊÌK¸6Ô7ËðObñkOÆ 3Ó]±gmê4³‘)îû!©ºŠ1oþ ¾88ÉE=u³ñ ÁÔLDÆw¢Né¾×ê¾ú9F-7xšhƒ]úf-v>úõ¦*kA<:99PÒļì@0ä$ eîrvs“7þAdØ\u?ó}š#"©$¥]ðˆeaŠFÃíeÕPÅÔvÿ„¬P©7ý&~Â9Éñ™nG¦®3qRÑÃ*høpÞ«ŸE&yàëty~fkQhˆ ‡Áˆ—ʇF}¥´á[Hƒ:A×ÅÔJ…MfÝâ ª¢àÊ!ûS/‹´2ììÈ£e·9â(ynXïÈ@ùPOi£RL(±õÕ2©íæÜŠÓ2§Wâxòϱã`¾ã01~jôè:+Bå P9Ö‡wÁÔyÈ]úYÁÏ=ƒó)¼qµº)ú?‰wgkp|…ˆß–>ÜBç*¾@³ö“~ߤoDÈ$A^?nÀ1³C>–“C"¤€âÒJW®UÅWç¬Jr/Bãêál,J'Sçä†yA¬ÜÈ ¥R®eOX)ö2½¤ß/—æ˜C1ý#=Ÿ#ÈÌK‹¢ÒÕ"ä'-OÚ? ¶A]B¯oÎÔØ¶Äš°Íù»j<¿ëøŽŠYBŽs„«î[ä=O&é†j£›é†UùY>ƒA­çšÀ¡w6Sw&ߤ YÚ1¤¼ÂÙËæT¸xFqÕ:v‡K÷fñy+Ý‚„D¯®YË[öD0ìÊRŸ%eÌ0‘fÕ_M]¨pªP@éMÒÉfÐfÀnýAÆh¤q._ªÅ1B—enˆ«`j™°…Ìk›ŽÞDrU°uSÉ—P/”˜ha†•ZÜ!s-Ó H,}PK"ÑtÃ|µ Å ™ìµ³à•TÜCƒó’LŒqe%ƒ¥+ѳ4mŠ\‹Ê.\šG–ÎgÙÜ Fìs¹ÒÌ­ZQ%šN <žèó „4¢Íxã¾`&´Ä¹?š ¼eë¼ÉŠìjõ†Â%Šá°0Ãí•(þ1 ºy²!ÏŸZ%B2q~Í.‰Ä™KoÕÆ°Ü´‘Âê†ón¼¹“¯ù2¦#¸åýÄ£—>ÝÙÏä)F¹Hºu÷Ú¯Sû&«@t«ÄrŽîåØ/3=‰÷x:N FÃ÷ôJ4ÓL4m\йÊÔe,mëU°i™MåÁD¾Õ4aˆqQŸQÍ#`Q[n±ÑA~¹Õo¾X%¢ló{HæÛ+·q-±zµO·Ì´~ þ~]4›Õ•uˆŠ$E’{µ}Ã܃ˆ8*Ž–Ã‹~ÙtH æ4:‡nÄlv•ó9¶–`ÞæïêÑ%ÚƒéDpĘwýñLÙbm…ˆ.F͸TUu-×ø?TýÉé÷r&//aH}SaÓÔßOc"7íÁxq¬+,̤ÅÌÞ¦3 Ði ZÜçvj­Ã“šG­oëÕ·ÿØ¢M‹tAúEfI±#OÇÌ Õð-—#𱲫°¢¥’ÂB”šEð*ùB~Ø8-°­É!B‹xÑ3ÁϼÂ6Üšzº ñH°úÒZÉq·zµÈŸ‘0IaÒ¹µL2Dè¤{™ÐöÖ~¶Ž¯ :kªÙÌl1 œ’,î†ô09(®|)‹”Œ‚‰ÐnGŠœœf# _ŠÐ–0NZäP©¶òð(¬ãý´âÊ…x!Ñ×­©··ÃÉAÝ5%>à ]S“‹ŒE=8W¿CÀšˆ)\C°ó8-u>»œE¨Ð‹ÕåËœÉ3Y§e¡°j±ší²ˆ,ÁÙÒ5ðP65L§ó˜Â,ÇcSï½åUJ;œFÕ¾›ý( ~°šÞÌG(Í8ÛEQÅL5ôC8 +7 Ú-ï%¾: }“ëÄqøx{S Ýþÿ¶»,ðì—W½ï"x?d6.—Ö{róû%é­Kü«í—.x¾õä7Ï j‹ïÏVnÑõ™?ÙìœÓ3IÿëËåUHZìH{º]ûÙ_݈-Œ_¦n<¿çI¤ç”å{xNÿ±ÿ$í²Ø®YVW6WpÅë~i% gÇ‚ ª¥ ?l?r‘×äÏÑœêH1 ­_™e[5ë²ïü¨âø±©GÕú`ÃIÏìûÒ˜ªJ>vLx‘~ÂÝRÑdþ¿ ñ&õ’“¸"ݔޯ-MÌÚ|<%§0F\»n}ZÁ ý2jßÏH“õ¹:1h²DMYã¹ë$£åü$¦Æ\6œþá’ ÉÈ2¹äŸ„ç»N^¨è0ÑSÈ»Ê;?‘iµŸàÁu-üßU,žÜ˜ v•µM?ÝË.û߯; ×ÙÿÝ*8aùï‹DÑgΉ»2æ/jX~ì¯Í—¨ÝN¶$\ßV»Ý¬ä0OvûÍ9±ów|/ðù»Bœ~½â+Ÿö¤ Ýÿ¨¤éÌy‘u¯ª‚öoðbœœö®q‡‹À5ª`D)HÎIM,*ÉÏM,ÊæT±Ý endstream endobj 205 0 obj 17128 endobj 206 0 obj << /Type /FontDescriptor /Ascent 811 /CapHeight 0 /Descent -237 /Flags 32 /FontBBox [ -43 -268 681 842 ] /FontName /BFPMAG+NimbusMonL-Regu /ItalicAngle 0 /StemV 41 /MaxWidth -724 /StemH 43 /FontFile 204 0 R >> endobj 207 0 obj [ 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 600 ] endobj 208 0 obj 1671 endobj 209 0 obj 2622 endobj 210 0 obj 540 endobj 211 0 obj << /Length 212 0 R /Length1 208 0 R /Length2 209 0 R /Length3 210 0 R /Filter /FlateDecode >> stream xÚíWy4”ý—J5ö5´=e‰ìckÃP2†û:f<ŒyÆÌØ %BZÄkʼEHŠÈ!´ˆdi·”tM´è•­Ü‡îûvO÷ÞsϹ÷ýïÞçœyÎóû.Ÿïòùþ¾çŒÂv+˜Æ"FÑA-5-uMC€€'âûTPˆ_Ó!À¼š-H¬Y$* ©‰ij¡, ‰Á4‰. Àd´0 J°€éQ ( (99¸(«¨¨þ,›~Q¿kO&@‘p ÓC@ øA`‚€?D ;{7kÂ@iÁ ØÒ@R‡}˜"xˆ Ò˜ 2à3ê÷@†ih¹4¦:‚…e$€IÉâF’Aú²J ƒŒˆÉD¾ˆ 0H4Ò @425Œ²œ"÷‡W¢3`Ä"Ñ!`ö0“Å$3 : @¢Ú㬾çÉ $±–c3!D Àþˆ%&‡-—´¢C`-‹ј Œd-Çò ĤSIQHlŒÎ€VÒcB´€¨ 0€Ä PA&A°—»ó£Nàïª'ÑéÔ¨oxÅê ¤ú«£´ÐHL2 ‰ÑPËãcMó‡-ÍïrJýw]8ÈXi24ºÊH$ L£FÐ¥A€YHH@é?cYýÏ#ùO øO!øO¡÷¿#÷gŽþîÿ·÷ùgh«0*•@ Aàûª]C¢ȺðÀò¾ –WDþORDúW¾?[»€ß“6‡©”Ÿußñ±´„5-]uíïbˆiE‚{ˆEüIT¤q+r'dP!ˆ¼Ò[ÄISó'1"Ó–™Ðý®i”Ÿ @8[I_çŽÝïdó¯–튱=2+ûø[$[˜òÇaÊÜŽª¡‘TÔ´Ñ:£`ôtbþIÔ­g[‹EšËK@Þ¿ÿ~œ¼~‚±¤‘aÊò9²H4 2uþÖ(4 ´Æ!Õ£51Ú˜)9ŒÁ@F`e= íøý¼r+@0$£ž Àd£„ ö™ÖÕ¿¶ßÇy´4k­n?J/¾F¼¸ n:ÄNÆ”ú.–U¯z`ø­.ª‚þõõ¾]cÍRÔMYàÔùÍ1rÊ·òE_(6諌Ñð.Ìẜ8ø¾?´Æ]OÓyläþ~ï¢E¾-´ëßQ>,žXB~†.KήL•¼!RÅ#vµ`‚«øËÛ/3;Ûît´ßnú¸öÖëM*œÔ Fákål2sw*=xj‹Suþ‘ã«ÊÇ-ÜL7E¼ÕŽW²2Od//ÞtÛK€?M&º“ l·¿KÍÖñV˜ÍU7~NÉ4d>Rõ]Cx|{£WônQšT#¯Çn½Ù 'wÓ3N9ªÔ&Z`Ω^&í"Ÿ¡f¼“3.ÚÛâ@?ó¤SXèÄëŸæöøeZ—ô¹x ÀòÆ SÒæj{‘&HáÜ:Nz¤OÂ0‡Yš]cÚþ­u œªÃ\m¹ Ä[¹9|(o.Ƨ‡ßVT›~7®&ä¼ö@Ћ™ºšG36md½ÎÙReÊ~צ¤ÃZ±© ;îaÚŽÈõò‰I‚-iKz„°A…=YT›XªøÖó_6÷¨PDìÂÄëE]Þx/:2­ÍêSpô²ö¶˜Œž´J%%˜ÉÍ‹¬ßf2õŠÛ(r}¼ªâÚÆšJQ6Q1lVöuôopšàBÒ1ŇðÃdâÁ rMë¸LqWñz§ç Áì®ø§uRiÐV…_L]ûDÔ•  ö¶zwÈo¬J9¥‡rnJCŸd·uW[çeñXˆVÑcfðŸõåå5®§$ß­6Q?ÄÊ;f²¨æn~¸-Gc@ 1oO„¤m¶·c7§‘1ãO(7ú½ –žÊ îÌC]Ÿƒ9b`Ó7,ôÉÍ{r¦†N{¹;$LôÕùÒR8[üL :ìæLŠ…º‹uÁdü(¦°*‘°×¡fêbïÄガ6ùªGÒõïR.Ÿ})MÖŽf·ˆä¦µ¼×¼£~Þ KÖ'ž@N¢‹ê£óÅ}y_Ò^Á«’O¬ºVŽ_Üçj„;"yÍŽ¤v•D:f~MºôÕ"°x ¦úöU„òÅü¸í«»ÏlCÝùhKÔáÆœìï±ä£Ä*õMëú骑¯ ¼!ôrìFÜÝÍh÷û1úž/‹^„Zúhð9–µto~þÜlÁ­(c>bC+pÛ³`΄(µ¿‹7æYûÎ@ð7~cì–©ðÂñÚÊ/ãF&¤îoôv¯<-ÎÖÂÙ¯Êøß °—êôdi}oJ”&æô±éþ†ûS¿…«eG^%“¼a}»'$ˆŽÌžÏ¬Í“ÅäìÖ3× › ÆM$§Þ9x‚­ŸY1;iá1ë¹h}ÝÙÌ—3a攫ڼÁò|³8.cA¢/EÐVJ¶Oiºa0]>@¡Šc\.–Ýßš7^Ìgž±Ô[¼A{Sž”Åq£uü>û죨¢&;$Uî]qõÔ_õh5ÍØùëW2§8ñîh=¿ £‘fyÑE?—îïK8«[Ø#ÿ-v¬Ûõú:ëjà4ºÝ8Ö&ðùºÍ]ø t=! +Æ3Š6ÝáyäLØöSojsƒ2­“y¶¼usÜz:¯v´Z#ø«‚{Á’‹v^oÉ(å—Æšh¿ö‚¤àÓg`ãèMƳpî £ƒ]«|XÞânü•ÂMà ÷·fåqNÍ ½ÞçÙâôÊxW|R¥5÷S«ìDžÌ|£cçaA£þT/܇ jrùù³\“yoRíúí|ú"tJF”Å*óÁ—*Êåáû xÏ1ãªdÃt`:o®âx|ñÃzÛ×k}ëYÚÀYŸS%hÉèKx\½`íãèÅ€Ò㌛NšUN®¢NŠV‰ ³Æ;Ñž;: 6Š—˜úðŽyÿvŠÁá«Ç:h6{&ŸêG•ù nTº»g7:¾©_íeËàÓ‹­UŠÉÊ;ç_~k„EØ`V½óeã…ôÎ 1ÝcHЖÕÒ]·eÌÕ Œð&^žIرeþ’)ÿa8æXIfÆÈÓÂÁNåc‚Áh8±÷-K”.’è;‘ÚÎêjá%Úû{æ@]xÔau@’}1|RºÆûq·â¶Öx›Pç*™6§îEØßþt¦«ËÖ([Ý©ÿP§gïíònÞ¡œ%´ ß´c阎û”Yš8Pª}“¼ö[ø¹KáOù·Çq΂3VÚ¶¬|zÑ4‡ÛÍáo:zÇŠ1éDí‘ +ìóé¼¾­TCáFÚ)ý¬ªåŽÌv‡õPâq|ëà¯'±iÖ†ºëööl®®¿’d˜¨*¯í3—  rC0íOð[™Ñ²rR¾<صkàóºWη׋äf–ä‘=ˆ¸œ>TQMº‹]ÉÛJq³Âq³ƒ'mB NNæ“b†s õÛ.Ï´¬—6ϦŸ>kR´è=ö8fSo›yÌùR¸P“/%Tg ò9™\ƒ²øÇü':>§†*º&¼{ø½ÈÀ5(XŸ½f™®õ::=_xÕÀ¯xkzë¬ö®•É[øL-}]ªÀ™vÔ­Æ Á¹3ã–ç:}lKõË©ܪ¡GfCØüš§øÍ‚)uÏ6äB™©Ä[{çoqqœÒ†¸ý+UŽö7‚jÛfÛŠêŠÙd64ß®Xr8 úK©PµHß´\ûG3+Çè{XÑj'ß.×h[ìÈÖO÷bß”%Ó¸ÊÍ\Íê̸-lÆšª§ð«…Šã¾3ŠŸ¸ŸÖü7êÿÿSd*Hb°ÿ„Œ`Ô_µ›N endstream endobj 212 0 obj 3470 endobj 213 0 obj << /Type /FontDescriptor /Ascent 964 /CapHeight 0 /Descent -324 /Flags 96 /FontBBox [ -231 -355 1027 995 ] /FontName /NLTDNJ+NimbusRomNo9L-MediItal /ItalicAngle -15.3 /StemV 120 /MaxWidth -1258 /StemH 27 /FontFile 211 0 R >> endobj 214 0 obj [ 722 250 250 250 250 250 250 250 250 889 250 250 250 250 250 250 250 250 250 250 250 611 ] endobj 215 0 obj 1655 endobj 216 0 obj 13581 endobj 217 0 obj 540 endobj 218 0 obj << /Length 219 0 R /Length1 215 0 R /Length2 216 0 R /Length3 217 0 R /Filter /FlateDecode >> stream xÚítuPÜí–&îîk ¸»»»{pšàÒHpww‡àÁ݃»Kp îlù¾;3wêîlmÕîü·ÛU]õ;öyÎ{(H%ííœÕÝ€, ,ŒÌ¼Qy9YeI:EK['U{[E{y ™%€™ùÙ‚B 4v¶´·7vò´€fq )€•ÀÂÃÃ@³wpY~µpPk¨jÑÐÑÑÿSó— ÀÄýß-‘N–_í”®@{[ óÄÿq p¶Ì-m€1%eE)µ”¢@ hÛ”]Ll,Mò–¦@;' Àܰù‡0µ·3³ü«5'Æ,'€1ÀÉhjùt3:üe¢8A¶–NNßK'ÀW±óÇ œí–v¦6.fð¡7·ÿ» ý‡‡í‡íLÙÞÉÙÉdéà øÈª,.ù:-ŒÿÊídùaØ›xšÙ›ºüÕÒß¶˜«³±¥ÀèæüW. ÀÌÒÉÁÆØý#÷˜Èòï2\œ,í¾þ³zøÕdftrú€ùÀþk:ÿìðŸº7vp°qÿ;Úþo¯ÿ¨ÁÒÙ hcΈÀÂú‘ÓÔù#÷WK;¦¿VGÆÎÜÀÂü½™‹Ã¿Û\ ¿Dý±44E›ÙÛٸ̀æLŠöÎ)Ôÿg,3þ÷‘üß@ñ Áÿ-ôþß‘û¯ý§GüûžÿZÒÅÆFÑØöcþqfwÆØðqjò€¿n‹íÿblkiãþ¿ úWo-à?ªµ·1ûW›Œ³ñÇHDì¾~ÐÂÌÈü¥¥“¤¥ÐLÙÒÙÔ`nló1¯¿õvf@¥ðƒ×¿G ``afþ›º…¥©µÝ_püô3û×ò?¨ú»x&5U9%©ÿê¾þí¨ü±ŸcÀ¿eÑR°7ûá/QQ{7€' '7€åãí}ÄÃÉìý_¤üˆåŸ²‚±3ÈÒ  Çü×!ÿ»ûûÿSÒÿ ;S{³¿ÖFÍÙØÎìcÓþCñoC°ttʈ´ÎÊÌÃÆö·ÖÔú ýï“ð1‹—ÿ~ @ ÐaeÑÞ”/È*-3ݹ÷ûุ^_ ä`°CI½za¾_µ}·oZØO…ÑË`ƆIÞ·V÷…c‡×=YÚýáªîày¡79Mo>ú:e;Ý~“A rú‰V”çżü&”.'³æþö¸ŠªAñ Ñd;îâÆÜ5ßëó½Šij],vZFMÁñ eâáÃ=UÿÈÐà@÷tï]N,<Ÿ+2e¤Ÿc®F…g n(k ¦á72ìcŸæcW‘9lˆíöペC—ê#(0ÌXÚ²!!C‚åâû£ _¿!`ùyV¦ÖÉÆ<£P}5º½#Âàë°žÊ`’±Šù 5¿†Âš2[K|…Q+sC½…ofŸ*‘ǘÀF„dMŽR\N|6AHJ– BWífbèv›ÁY8§”·ÛÝþŒ†w—,>¾/¨{Š!?¡àí­B<žñ*cWµN4©@¨7ƒµÉ`f¹Òig›jrz£@ÈOeh‡‚Œñ#“ôJM[Kô(=ñ\àÝ~" %¦]x¥ÏrB ([ñ•uC$ ösð+S»íKýë{ÉptR`D±œ6 ÛRNOrm j÷{CWVbbÐ.5Á¸5\qqÿžgS%V-ô{É™ÕQan½ÑLQŸ"j»Æ ½6zÑ PRˆï^ÚÿÓ ŽG86!:³2Z®·84aPZ–;ȳ –Ä<‰wÛÌó‹úS7ÝŽ«¾ø­idmÂvÎóúÃ7ŸPæ?Þ=@‚ }‹g~••ÉuH"‰¯ Ÿp:’PýRHòPiï¶aw-™C™ÓD±¬²À ì/TøóDͽhä`«šÓ´!jÓz×91;´ ¦ÚŠ$µ_¿À³ÇÌî§u*x“ë"“Ä”¡FJ;…ZPè²·v™§9ÉxW€ Ô‚¶Ã~ù˜àÁ=j”‰“Bʾª ^£™[zïÉ©Uw3ý¬=HˆÈ1}£Aœzr7;hzál†B›]¹>‡¦ôÝrƒê»‡ÁÑuúWeªÂY9ÂòÉÇM#Ï(| âüX«J”¯@îlèá?ÉÆ Všì”i$ºjO-j‡:zÈÉ.-ûhꢶ§ÇzÀ Ÿ¾Nr Ò¨EüÁœ'’VpÊ‘ö–ñ>^¾7òÐXòŽ'͘2·ÓTMà–¢Þù$§%ÈÞ€Y\¤ÜŸNã;%f)ßUnŒ?¬bhðkwBš/÷†Jì /Ü!âr̾­Žvøšêýt‹{˜[оa£Nª‚HöizV­Ø}÷Ͼ${ÇvQ‰ç]ú*38Ý!—JLú)ªQy)Ò{OÓFîH\ &ìýMçñ¦‘³]Ø¥0‹TÔ­ RH.`ñÃQ®Úm5–Ž,+“á¨å÷Xùõ(cÞRFg#Ø‘Ye…<á×'¾±ŽQ'¹«çêP¿”@–ÓO½@J%t¯<üŽK6uâø‚ñö#Ïéjß(öB¦çBzå†yðøwÑ ÕiíÓ±¯'Ëæ®?°5âr±+õ­ #u±¢¢^ðW%¼òÏ%¸ î5ôtIÓP_­Û—›ì?~­ù…‰› Ú,'–K(GP—c¼—ìØu³làÕ’bSj½bD»uÇS9­Òú߈h)ù ì…8!W+ã‘çZʆ\äÈJ1úΧÒgMÚx'¤‰ˆ-w²Ù´=¨{a0ãT5’š8µÊnùŽJˆÏ•`!—™“þtA0—˜¥H¿u]F)ÉmŸö;WÞ×ÄÝ|WH‡´‹D=ãÅЮ 4g ç„PcôèÈõ”¥Ñ.šY‘sQg¬õrË3ÅqMÄF\é?DuB€aûGÍõ 3_›ø^{Ñ(€f™j¶A‹sTß †ÍöÏt•û_ãbnŒS°MÏ;²ÓBV÷!ä ~âÁÊyÖO”Mgu@BöætÑ‚és!*zM^‘/gúfä¢3YÀ~N Ò!ÛìÕ? ²³ƒqðè‹.SlÆžß6(v_WÓXÈØ/ú+Œ*c©.Çðô¡e‡ÎMÔÖaU\QP¨EÝäqc«ðõ â~# g§¼üáà‡¯¼RÕYWD¾ôˆ7…ìHç˜"‘ÎB3®dµƒr ±ôâ¿XÖZ@ †¸»øò–s4ƒÖ™±ZÄI·ÀC öÛd»9­ÅôÛgó<žiq_W´/%è!µ¥ÑŽyÎaTaóε¶µS½( ì9tzØ“Iäy³skÄ¢Íym¿qŒ`Žšø>ƒ†c¸+áµÞ—)8Ê=,D)•{i¥Ðºu¯P(zMççög²0?~ê_}Õ Ó’Q‰=^Ññô±†ªcˆ‹ª³R •X"þ. Æh̵lð••zaT9éŠ t6õõ¡Ì±ö'oÉv3¢z¹Ì´!ưÅΗdjÄþôoð_¨3|·Þ×qáÇ›B>‰Ì©´ˆ'½Àõà@Ê QR€‰¯éX¹b~ßz4º]Ø#NÁ¼lîû}ÿò<­Z™ØMØŽÊ]Y¶’¶¯¢a&¤ï®ú6ÞI…§×„;‚Ú‡š£Ï§  û%ÿ6gÏ£nœõ~9j¹€HU\ vQ|æ¢ô³(òÖ-róNÂÉr€T[¸Æ$‘ªîVô‘©\‹ëÙ/–p[|å:G³mPQ^“vŸáÆÏŽ*SÿßÁPw›8ÖJå]…x];´^X·ø¨,L¬‹=éüîgˆÒ2ý¸ÚQ¤RàQp÷"Κ¯î\#.wË?éGÖ,ŸÛóm9˜iÞSF†ˆXÓ5žµl”Æ“p»Ÿ’É_ql~ÐóiJ̵b¬M_i´Ôàý Ð]B;¡94‚áêŽvpo+@hŒ™%Âc7Å^0ž)ÂäQ™!P9W"Ê.:}ÏÇfÄ%å(8ýT´=R&§EÈZ,´â{fËëæD!ZÜ#B5ø6O¾q¦úmßGþ,ÊPdz49ö 1d;Eãyúì‘ØÐ@—Vþˆ…Q¤ú½yb7/w5mZ?üm˜±cQq.Úýô‚’p»+ì£Xã0#Äs[Çü£;¹wqõ'ù}È1r%Ü2,¦Cð*˜8óO £ªƒ¸úüU°£aÑ ^¯‰z¼Õ j妽3PÜ'&®£=cŽÛ«t¤w5ªTRÁfòWÇÃu×ÕOÓ å0÷ìbe¦K¤ð ¨9“CÏ)CÚœj¢ 4îMf ¼¤üLtMºš7u —ÈažOWÔ©vÜ5«¼¯x‰C0?v1Ò¢ -žž³$8—ˆö‚|ð¢%f¶›çp–·8µ’JÆ(þ±a„Zk1¯õúíNÃÚ>BûÚC|•Å>R §n3ihS‡Q§q“{)7ÛbÏžA /|ÑÖz2µÏPíR~–(#Ã4ö¾X¿eŒØÐÛ@IN'ìw$ú¬eGçl;¸xY8ÝM®¿D°x÷:=c6ï½l1A×Q+s4\äâï –%ªyD1\‰á‚VfÑ:cQó{1Éø&ïΨU…®Uç˜2YƒtYÏ5kž½%7]¦ëUÞï=ϼI„ܽ–Ô¶ Âû­¨àÄa #Aªc¸æ~ Öî`ògð*V#/gÃÂ×Í©ð‚¨lóbj¤X‹q×#jµ–²¨GbóüÊI‘V%±˜ïpÞÑTõ'‰Ž 7—#†Î'½<žœ.c䯗 ªn3¸S|”€?tAúe@‰{9`ýp0Yõd™Ö=_pÉéûY¨hÿýL '[xCMe/tÁDc ŠŽÕúæ¦ß?§ûêúNÉzËÚúdâÏKã„\»´‡Ô¥B-•®-Ø“#âÝݽø1ù_¨‚Í©Q»ßÎT澸±·.%·Sïf¼c‘°ÃÓå`AvŽÇN&Žƒ\S3?ÇÒ•¹Ú²ÐIåú cPR©™ŒU7õ•LÁì²J^ãAøR;¹H¶c6q¢€å6ÖÍüZ¹w¶ê7ÈYëα†}5lj½›±‘i¦‰ŸÈ°4ÀKH®ˆu~JO*ËñRsŸ‚n…[ÛQ^§S4±?ëõ6Cºé8ÏÕ8N7i˜Û#ø­æÎ¡En©OФ8­) ý‰:ÄžŠî™²'ÒÝaë-3Ü 3âŠÀv$yËšé›–õ;ipŰJ‘Lu;—H¼!¹ ŸØ ‚ ÜòIçépF›æ½xEË?Õá“2ŒÇ-Œ¶Iðµµ½nãÂ9£⨥¾ô¦û²éGY®!1}g9Ê”2Ã3˜à"Ã*vnä5p8”)cF†®Á)ÊÆ/!5­Ί^ùé,:!3:Wþ¡¼Ëhlu‘o•Ó2&¬¤¸ç(CÈ;T»°Œæ6¡xb|ûô5a¦“æQå¤ß³ÝjÈ4-òÔuÍÈó‡­RÑ0‡LãlLÄcäg+ÑSáb¡¹ †×K¶ûåQqŸ FÔ™9"[]D›2m˜e2ÏbmåûÔoS¯ÌÂX'$Ú( ÐzjeeÍç.—Ñém,î¸aG"uãŠØ^Ñž^,µ=úc—s­^È-í´‹Ÿ?¯ÜöÁjb4Q×qU¨C”Ãlö{zQåX³gUaª¤ïk Ab‰oÎǤúü mË:ø´ž½Ia {S£”99ùÞ´Xý•ÍŒá$ß[ õ€‰š#Ó¼næk+1´¹F™ˆTG©}ÉÚˆÇy,Îüˆà"$ì õwÙhº¦¸çÉk†Å$ÒÔ—’¼tÖwá“ö“ l_#îFi/vÓ! ç¨àåù¢û©•éA‹Âæ¿&¸g¦ÎÃ?Ïü®Íg2Iìf6:ÝWÀ$K7öPŸ>QSë’Z¨Y^ »®ObÞÐ=†->¥KIûö5‰Áq¡0Ñ-:tÍ€‘„ChNžLH̦!:øÈ.òP|¦;]€#ÃSŒ.ÁúÈò(ukóG}O®Ð¥qúš“¸|ÕŹS3tQñíŠð÷þ‚Ä»e×4#SÁ¥+cêi7Ðmì™uw'Í6ýìQMåÍ:¬áa8-ŒÉLÖñä"–HÍ27’y¸6æ›m¼gjàÊnòˆœŸÝÁˆwr,dÂhuXÐÙös®1 e=§HC’¦Á0…:›t\LÙS¦÷É&cB Ó~ú±‰1ç\=—”ú÷êxìð5»ž›×˃›{½jÒ…?†ò­-IÈrxå³P=`ßEâ˜háj êkÚ q2zIÏ>Y:Rü{­ŸµÒšçXoëÉd=ÅBŸ´Yþí²õH°ÞdA乂î-£X\S¶9·bl© 9RûM«Iˆ$­‘§ÛúщMq¨ •ì>©¬¶ zL™µ×déª9šßä2»Ö ¯èª û§·`}ONžZÍ ް3ÛK©íÐIBÝä{Ââo}1Yø&¥ØR>) F/¡ëžrgºd©¶Ôº¬hhf•R¤ZÞÆ¬Â¡üWñ¸¥â‡ ><äÏ( «…óA×á½1²¦ªÙŽîÔE^õnO`!ŸO~—LÃøðáÇÍ@Tµþ‚gEw§†žŠµÎ5x:³XÍM•ò\ƒ¬Þyá)µ÷ôi[£ð©¬ÐäCæ~Óû§êÌqå=’gBÙ¨tñ¹Ãlz!¾Ô_к”ü±Üz ȕҙÇÁ&íþʃù©2½ùÏBå÷nn>6³Fdm££<3«„2a“6ΆÒþÅO)ý0›ò7¥bØÙ|å_¬œ`Yb&ý¾yÑ@"ºëæNF;ïÓÔ¸žH'ö3&¹PSb~÷EšôùäY(WHš¿:Oëôöº’W¸ì;j8 `Íø¾wôð±äù<é\脦¤za—%t#¦ˆ¶×CĺŸ¢Í6®n“Æ„D¢©˜}”‘J{¿B7Ìßwä.OI¼Ž› N þ:x3¸ßÚê«z¬Rê®Ü­:S‹\dBÑlbæf\žònV9²Ã=æóÑ‹ÁÃ[w±$Ê tÞg£º$î¸8¿ÅÂÊdÆ›:‘g&ÖØjm{àT¿B9hï!or!ó»îÍ$¾:žÖi4` s(Û´w0FóX˜èõ’“Ñ&²ækÛkþã{4÷÷`FC¶uUËuß\Fd¸^tQ—Ùäb´ÏŸ":éH´fÁš®js7V¾]8³ÌRJQý®´X@püQíG‘è¢ö,ÈçJG¢&¿UæEÅQÉ80Ìnhc¡(?gZ‰Ý«¼fœ×L¿ú•«—s´š¿{Úܘª¿'Ù©Ù Ø÷ÊåbÓg³œSj&ï³CØt’&®Pæ(‰j§Š˜ÀŒÞ^_>÷Ø£Çý:a»£ØåT}s`óð9ÙÂH•[›¾Ô6kUôIsZì³ì cÕ2D"3­Õg™2 ²dlgûvä;žµ0Ú>aÜÐØ€~†Ï#ÂÀž3qÇÇ1/T¢¯ÖÜŸ(ç<€6J]‡åº‹èÛéi“Õ³qye*A^òy%êÛ[$À¨&§<¦ÛÉ~/~ÖìꞃwBÑnixƒ‚j!Jè`[ þèyÓ9 s,àÈ 'Z뫉ùÃêv \q)0§ìx@ΨšLÍ„öòk¼¾âÉQ­+¼ …Eó'Ý#ië 6–í¨&dxË×M#éllv5€m2×YçcE[Óʺhø›¬Ê7½M¯)q†Õ üf›/ǹ+7B^"ù™#î;à ƒ8«óìAêŸùÞÙ«`uêÜîl¶ôÇ~á¾/i–G?{|Œìó˜È<™ÓÊS&-2M+ö4·°vh+gSr8ytVƒ²ß’FÊoø&… •Y}Ê>#ìq| -i}´Î¨ÔºùêÃNa½xѤÈ]%Û®UB0áÄ“!èf`8J ›Šn‘·}Í7Ž}/|ÈÓlx _}Ù¢PžL 0p Ðé‹p˜…žÇoø9X%HPLO¿ÐÇXH!1Ý>2AoAë¨éwú¹Ø¬ ,ÀÈÆ— ¡^8Köèþ ë¾RÔ¨ùŒ±;ˆ¢Â4ic+ÐhãZV‹ÎŠuÚ°Œr(*bùNeú‹{ÛïÙꌘSw×õ½b[TjqD¯ÔUsõ9*ãÓo§1í® ŒÞ¥ÅÇঈ™Îœ]ÎÀÒr'O=Ýïüeg¢‘:÷ ›®uŒ$iÒG¨{MmñtØ:ê=¸þh iÉÅ”²[Ž€T'Ü Ÿ%˜ûšÏÀ?ö}ÉÉ¿WBÚ⫹ì.®Çæ V Á9Ö¤ãDâ…]†"Åå²ëš5Ødä:8ߘïÞ¥’èh ¡½>—rnÚwK-˜ÕZY{ú †TM>)‰Tà ‚¯3r@)Ô®éÌð¶àùvxI)o àD²3¨µ¦lÛû>­Ý>ÉÝI ·u:L¡©ã¨L@x3T*UÈ…*‡“1.Pýâ^å©Ûñ/âyŒãN‚ÿ¡ð‹:ÔÓ:Ä“bè6­¥¢bk%ÀH)"à%Îk,²õÃÔѬ¡ÏöèŒr²“jW»í5ßË ¿ý6}}ÕkWAÒzÐ>rζ9‘ ]%ö²÷‹Hhc©Î0>\³.)RÆ1åœxT1±ôÅDaâRa˜–yð7ójEº(A±³åâP´ËÚn_ʤ}Dg% ‰ê®A“«±ôl5#M|Âۜáð²ßÄ$?WËçÑQŸ`úÜ礌=::J””Ôò9[ˇÝCþFÊm¼e•ªÉ÷Ëcõµ³I¬ïϺA•q{ ޭ׸‡.Þ©ÍVø¤ì¬.7xößÔ[âX¾qÝsM’·úÓª·Gìп\ÐÁ)1JR„ÉØ©ŽÎm[Æ–¦©K‹æÍèþŠ3w¿@d Ǧn£\6ÙÍ\±åØÌßAïKö³\zñó“!cxìA‹žÍ+.˹}n//‚Øk×üJÆ´º#ú\ßV˃Xc@®Óÿ“tšâk±÷ t2Á÷Áô§Þ+Ágõïáo昈„¥™\ÄÍ奦ŸZÇÕfÊÑí ÍCf6¤ Ù‡¶]Ïἃ ZíLú^táÚ„,ånů£ó†é ÈDsÓs˜¯EÍ6¥5*t(Í%¶ÙÚ:b0©+Њ5Õl;u¾÷»G¼ÌÑFB0 ÏŒO3‹WTG¢nei1*R#˜u;›×ÚŒ>"Q)%Éõ‰ÄÔ¬Ž;¯GK¥¹k}QjeØMq#ð\sùÖŒÈûÓEØp½?Ø|ÓúáÂO\ߘe#_$v}bqDaûí!fù¼L*¯%Pw‚(©éÓc¥S‰ˆSnã 1‡´NBbDìØÜ½©,´Ýæ”ÃbæƒøV æ™|SïÁ¾K?Œ û³âÝ3‰1¿–Ç"L’üs•»`6kÄwª_7_å4WÀ®¾Ö—¦3@Ù^‹¥l_iÌuB,ÿÏ ¬†¯HŠ™%’˜Ëbš?mC@±e]¡ÁćܻV ÒÜè”h[)sø^Ì4¹3nK|¬u­Äã$Š(£nôj¿¾'ÈNäzžš›Xhª¡Z&Üuel³V}AcøNjĦ01xΰ`âç^8on:À€ÄX2ä4N—-Öz°KÉTù}G@Ù=ú3^‡µlÔ£usìØ‹q!‰oPˆ¾å2ÖîIùP¤=£êNU`L¦ $µ×MGÄ¿=béµi÷±‡@ñK!"Z\Bø*v¨TŒŠ&ºÙø:´ È¿ÊEd Æ¥8º†‚­#R¨è˳_¬¬ÁU1Ü×È9フ®6ûé‹ÕCb”plšA/«âPÅ^ ß³ÃxÑj­ÒÛ°y^Ámøøí¦o)ËãJdñ÷­¥”´ÓÍ)ë‹\û‚â‚´;3;+j œf?ÄÒÓ®OF-OßåÑjGÑS:`¡ ÷;{´¥¾@wÀD€5k->­åW«Ã¢Ÿ¹1XÐiè¾2q{ƒïÝÙôþæ<ú!¾ÞQ=l>™®º¤úÐFßí‡èúŒŒJ3+VÔ ¬¢_O¥älihpC,.n ypIÓcP» !=ìúœ§Ãd…(E[æê{±ãur Hü&óãw„§uyíáW4@œ“/9Ø“M‰rAöÈ£ÉzëÁ‹Yd•Ž¡¶c9ÖwÃ^'…Àz«ÄÆÆ:V༳“ó®äÂIоg OL»3º@ÓV¢‹Ü2Z§õÕ¬Š'«…½!ú%x)íÛÂ9vüŸÔÝO¿aH[g³Â;1ˆ3]1[b$-¹c÷ÍöÃTQ”7¤5$™’ˆ¶à‚ÐèÆQ’ ¨ã•‹ö»ýõñ±!=ñ…¿í¹êtú0ßÖ¦¾ž²pâ]ŽðLxˉ<˜¾ O×å:E& kq)·b†LNÈbˆ-Vt¨§Cpà Ù_•T§`¿¦x*ðoë:»àЧÐ$iuNp +¤zI×áØûÉ^JUÔ^yaªƒ Áᆡ½5¸âÌ_¢”’ÂCjQ^“cårÐ0‚§#H^ýJ$G»,yÒƒ–f ûe=8äLp7Cºî—‰@üÒ9¾T!]ªDÂü¢¿PØ7=&3³ÖůÏm¼ÞïÇרÓAjs’¼Ýý`ë©êJŒ'QLóBôæþÁå¦è"ò¼á½÷ßævêÑ4¯qëڳ칽ºLŠÍGõHk׃hX–"Ooä^n‰ †ŽKu˜¥…yö.m.­^ô¨ÙâÍuÆÄ?•á _’ ›*’dxÅÆ™ôå‹¿ý)e7eÓaq¦¦7{.V˜µèÓ[¿E³l€·!ˆoºªö2¶3-tw:èQ5oµX¼Ð(Óc¿¬~áø!Nɘ®——1‚ºÂÁEöåú,Œ{_K6µ  fMìN°ŠŠCXœX/›1…J¾uZ½$„ó…'M)Ž0Ü8·®”å ¦,ì—¥HÎJeyé ß éZ¬(Í!¶Âb§oÑ(×¢DÐþÀͼ„úa‘n ×}k7³Æ´4¦ÂjdÉ;žå™–µ°‡ÓW†cA^XNTùÊéÊÚ`ˆEÍ©»OÎ;Ù¼Š}Žïüq6Zñ2@²ý)èA}û ¿è¶ÓCH˜§^¬K=V"«Gæ®<Ž&9r½Àó›éÉ`›l°ÅVxuÚ>¹ÛÇ&úÎ)2=¦*tÚÇ ”X›ÕB:ŹôoNÀŸMHµñUÄY™LY—ÞˆHÐkIÇT¢øë“HJ—[ÓENy¯Œàcè©é(›AâãW?<=òá^)£±Õ€ŸÅDµ;´nT`lÛxë¿÷÷Æ?”ò³Ê^šdPfŽ wI)±ŒòÓÍ«÷ð’Žsq䘳­ÑÈ1_i&ÏÚBè4¹³=€ÓØ\°³:ÿ²˜pù‚fPZ <‰ÂÊC+|œÁp¥ ¦ÛåÆW«‰ ÁÍf°Ëç™g1úËÙ“E†…ö˜mÐ:©Ä%µFhË‹]zðóǨL2¡˜‰û¤(ï9ÑvÝæÎ6¿&Ï4Þ=)'lFÈRþ@Óv6Óž«ËiM›=½¥žk‘Îä8/Ã#?B)“§‹ÈB.‡ïˬ}s0RÇL‰eÛ•ãÁŽ´ÉÕÃPeµdp.Ís1­®Æ^7À5¡,ž Xh]ê‹ 3‰Ž¥kÌ©YS9·n7B·'awKâć8ÐZÐb…NÝ9ƒ®={fÐ¥é >Ã^JDSóp…´üÂÕ<çÒvQZ~Æ ËŽ I°žEÔý½QÆ´"V;½Ãw~]ÍfAöd¶£'d«ÄŸµû¹ZI «%‘O½RžýûŸU5ÜNÙDðƒ\z‘,a€t`SsŠà‹¸jHð »PIŠ5ÁâVä½ßÞô¿`Ó ¯zSÛ#ºaûÚ¯Þ=Ã¥µÞIe’9ûéѪyw1dŠàRŠv5Ánx<ó}×›×Sdtr“ò¤š6Îñz›»x'+Žl] €‡cOõütijËg¹‹jEx.k&Þ}Ëéti†ê—ì;ÇÍ-ÂÜÈ1­• ò®"NñVßËDº| ½«–ãÏàk|ФËš&ˆ®b3bÀ²gR‹eªL8ðÅøŸu)Æqá»üÙ6Ñ7 Í‘ÓõEãŠH+2©ª»}óMŸaG¦ê—ÊÂ’}ýé# ç8ü>³ÇðºöÇ8²ÃÁ EÚÀ–£[v„=lRYJÊÀþæ8óÃn†5?”wb”íL¨Cáè°º¢ß.œé‹ nðÕh–oY “­þ·†]¬´ÑaéФ'‚—„›´]­hÚµ—unÇÑ ôJ ¯ZŽrsÂÄ„2$3œP__+]¡#ž}§"H7ª$")KÇ‹‹OÜÄ„ê:øÂH¤“RT¶^išƒ_&Ÿ‘Eļ¯'T3H ah Úüˆf5jŸJõtõ† ¡Güzø]Õ( +°Äi•…d$ýSE,ýä´³üÏ&ÄØ/. w®#f`ŸØ$•¼. ”¸o''ܧþä³ì¶B?Ö,IeSD7Òøz–®Q@¶Ý3hûBe’ñí2öN;» ܲL~‘z )½ÖäýݲicW‡öjŒ-CE‡K0ZWZó–o‘B¤ÉÊOùgo(óÁ:¿¢j¼JQF;WÄvYqc¶NO}*SšOøû7ÜšÚ¡ çFU«êámäÏ×ÒœI·<]|Y!‘eÍÄÉÜ s€dqoäžGK{¥“ M`#w¢lR¯<×&ùüºº=0õJ‡±K‚s:™L[HlâÇMaÛû¤ðXšÖºŠiBÞP“^T¯1*˜]©«¯íª¥(ãèÙg‚TVœîœÜ´™q «v y®£ÖN ·KOEÙÆøt8ofCùŒ@¡±u€(ïÂE$K‡›„á©‚¶“Ÿba$ß~õWœnÇð™…¶Èš””slúà4!û×"b™¹4ïoSѳA¿¨§U=QQøë¥-û9å{ĤìÔlêvò5§QŠ#l-±ìf<¬Ì…¿ *8MüëUâKj œÎ'gî hœ¢cœUÜN-WΘèO<Á4<Ý@ÿ ]ކxÅʪ5’90:qÍžƨso_t™­åúÞ9Bá;øcÅZXÂótc¢ÆoŸbt9–Ù ÂÏÊ’Úª!Ûç˜çfßÊžî¬UdÔÄùá]€qªŽZ2»o-â—ÆÐé›â§/ÌöÉIÉzSuýαêäU‹^8I•Y}©Íù.´A`™UÃG ,þXàЂÁ àÒÑâìÍòYiÔßI:B¥l8o[òM‚}nñ­«ÈÁ¦¹äï`‚WNNñ<ÞõžäÍ‚¹i}?i7ò…°I¦»'¿íòý°“Øh˜Îÿѧå8Ïî .x¿ ‹/* Á<Ÿ 'Yœ7ç#>d‰çn‚F ^í!{öòƒºäí­ùu¦Î?ÝÛí2ì·Ú“qÞV£´*£ œ«Y˜‰/ÄîúÃëÝ»-w£>þåQZN§¼÷w„ÏNK`;Ð’G{÷xvG8Ì_FXi£ZQ¾‚•$„ Ó¹.¬€m¯°ZSW}š"ºQÎòÀ¶ÄRè ½tQþFÞ® Wx9þk‰Óô»h½æœyéi´–QÝ–ª‰h=f½Þš>ðxÀuʆ³u*K)]š‡ßÈ+K/XŠ` &‹Á}‹ÁKMpGÙ¿ìéïtŽë–˜Ëša˜;ÑTœõ–î»ä … ·c¸¶'M2"ÌÞ”õg_xnÚ#À|g½hÒ·+õ É>v:ÿÔþ†ÍüôŠöȰžBÄÇQ;Qî4Ìì´v³™4‚QáÿÈw±ãVÓ 4ª¿Î¬ÉZðœ:Þ-¤Ûí€ôf&´h úfŠy„£}…*«ÍùcÅ”Ëï ƒÛµ¨GÖê¤è8ûŸÞKw˜Ášâ;Sûäk@ÊXð6FÊæ?ܤµT¶ñ« V§šÜ{鮓+ä9ãÛ—¾‰ 8gxzGä)B§©ã—™öº p¤=óÛ½a-ÿÜ™a—61–Øt,¯ºÊâ­ïK+ß*­Ö2B³bÌ„!OàÖÑÈðqÜãó.£ê`VÁWülm»w”5Óï‹$æL?ïB"½¡òÊ ÀˆŠxÔ)š}bˆ4ä$Ÿ=‚k,·˜ÎüßU8É7àúO+ôž€¸—$½;̸ÞsÖ­69Žè“û Øùv¯›iydîY¶^Ë®Žü63þÃíìåÝšä$„‡ž¸þ¥#:%[ͦĴÙþz,=!̯ö\¨ÀK¡ç(<´NŒbqá Ke¼gÒÂ@³.¸æsÑ…M’¼z…ÃÓ‰µI’Œ_Ãø^Ћý©ÝWZC©~ÇÅ ¹hUXQºdQÆ¡¯Ê¾±)ªŸˆUV†Áoíü 0ȃU7ç63@~F»‚˜¥…Tŵq]¡€Çä‰2Ì’œè¹/ô0¿®É“!SI¿l§ÁxQ¶vþµ9o°ºkû£­›PËœ-,æ–Ú5Óc¸žºÈ$¹hU»„Ö¥³úc‹«àÙàð']à£I¸«Oòtåe‰•HTŠÍ¶g†èÔ)QSÿrïW9n¼öåK½Ê5d*'iŽ¥VݦC-ÐêßÜäŽèVŠ9#‘u(ÊØ¨ô'KgŬ[;*ue3Æp› *ñ¢ï–”ªÜ¸ ‡àrËžæ­àQàµuuHäÉ|!Î*šê “ïj¬ã¿Xê½:ë‡/#­Òa^¡ØB[Ž÷ÂWƒì°M…­?‰ çêG*ž þŒ/¨T²Ÿ/õ=]16¹$­4YÝˉ¬önUÇàðµÛ3}¾öÃÜ…hWbq[‹Brõ¿À0œ(“¹˜,Éõ‚31?qÇ»äÝœEEüŒp–$ƒ“W .%üX4ë’)‘–Ìête8q›üÉ€vÕ/€4õ÷ž !’» ߟ9, \ö¸‰[[=зdœÄcAµºåˆ^hãh}Pßžý&3Aœñ-åN ’áþdîVô$@L»gˆz>õÇöóÌ5­ ÔPau£.E$ýÐOi7¡‘T•z ]^¹3§2û5'¾·”_j‘T xfÙ<*>ó;Þ$„ÊL—d¾éýTXðqa…ÂËh䌽Åò_¤V^ᢄ4H^N€Ô.0ªnš¿CQ×*m¤˜Õƒ³²¾LMåÙÅ8Òó¼9²h€mí‚*­Uh€ö#eÈÙÖ¸ |y4C´¿c¾æ`©Y`h¸¢¾%ò ÷w Œä Uxá9%Bß'ƒÇdáúŒºç²Y«ö‰ûÄÈx E¯+ôÕÐÎCþ˜ç² •Kºäru4»ÁIÎ<«Rv·àŠ‘§³]ÕúÉÃr‡õ–OO1Ùâ€F b¬òwJZýönî ub8{ ¡sæ‹!îM”ÕI’¸y=BRtƃûw¶ëŸdXšÅ»žñò/äéá/7¬}ê âwi#[‚Ä:ÑÓOÕ©½\’O|ý5¿šM‘vúÏ~VÝ»•‹š ¯^ŠUÅüô?K×#(¨ˆ–PnË>/áeL 2Gtàé'ê «ç$2'ÍÖ‹•L´õ’ÚÃ{¶R(ª¹WÈ<½ÆïLÌìCœ^uaß(÷pVæW»@ÚˆÐ÷3£”6¬(ìMÛQ†¢~†í®°Hˆ(AT;.¿Væ?QµÛ…tNp2Ý7C1e÷×½rÁMaiøï¾NjžN.“N—A\*[—p È;>û¬÷Š~9˜ ç4¶šÈöŸN‚ÌvÙ {ÞŸÁÐxWxÓ«â‚Kp胑v³óÁœ5bƒù} Õ“â$EÑ× †¦]=Ž˜dqŠ1)ho sZÐaõ’ß+IC§SÅœª7F”³¼öÈ}ƒ¸GFß—óÌ• P‰lð©$ˆˆ#6º‡B¶ÒJÈéOÈ›\£Ûã±úÑ-~«wÜ)F¸çål+ö–B¢+´EÍAiCMBñôh‹ga²{¾G‘›Ämr¿Þ­<Å< Ídê ÕnÆ{zé™Ûcêë­åyØ,µyRÚÄÔÊ-Re: ¦™âé.ê,ÓÅ’’}Æ#ªÀ šaFF óYÓe½PµÁÐã„Ù JV L<é5‹|ˆÔÝòmëîë«áÏæ„Oz¾f­xÄw_ ?û^Þ-3ixP&ÌÇãÖ'Urç J>n|Ǭ¢Í—‘ßt(ÚÊVÔ::aŠ©žM¬Ÿƒ/)·•„}@<ú~Ø{YI»zÐD¡þâûòÇÖû’rüŠlÖóZ7нñô(^(¦”üâ-¡Ð¤:ïsèñí`û™¦÷S¨RO¸?ÎŒØoµA¥A-D,+•q™4Hg_Áh‚˜ú)0}zÓ|ýô‚>ô·Jí7RaÒb˾k¼Q-€©e‡ws©fEné¢*Ú¯¯¼¶õ• Go~wZ{EÜf ̨˜àÝÒæn° 'ÔTç-²ízÑ%dÓ0º°½Œxè\„¢tìåýÇçûî|ß—;|ÙjxœšƒE¥†èQäU~÷f¡€Ÿxaㆲø$}Œ2ÁPÒ£rà„¢óì’B&É¥ÿ.3®Ç€“i^êÖ™«Â¼EeĺwCNIŠ«W,Ó® >òò\ÁF^ƒ2Ÿº±p½Ú’Š.@êÄ·»ðù{Ëü6ÆõN˜ñ œ*6?úT˜\t.nL¹ð¯æ@ÉÎx‹ÌÉ”Ýé(³A-Þ†W)Z©H!)ˆo_êïš(ÚÉê(´ýHVD¿”\Öê¿þÙñ`þßüþ¿ÃÿS¦6@c³½­1Èáõ÷ endstream endobj 219 0 obj 14472 endobj 220 0 obj << /Type /FontDescriptor /Ascent 960 /CapHeight 0 /Descent -341 /Flags 32 /FontBBox [ -199 -372 1031 991 ] /FontName /BLKJPF+NimbusRomNo9L-Medi /ItalicAngle 0 /StemV 140 /MaxWidth -1230 /StemH 33 /FontFile 218 0 R >> endobj 221 0 obj [ 333 250 250 250 500 500 250 500 250 500 500 250 250 333 250 250 250 250 250 930 722 250 722 722 667 611 778 250 389 250 250 667 944 722 778 250 250 722 556 667 722 722 1000 722 722 667 250 250 250 250 250 250 500 556 444 556 444 333 500 556 278 333 250 278 833 556 500 556 250 444 389 333 556 500 722 250 500 ] endobj 222 0 obj << /Type /Pages /Count 16 /Kids [ 4 0 R 59 0 R 105 0 R ] >> endobj 223 0 obj << /Type /Catalog /Pages 222 0 R /Metadata 226 0 R >> endobj 224 0 obj << /CreationDate (D:20060705162337-04'00') /Creator (TeXShop) /ModDate (D:20060705191930-04'00') /Producer (Mac OS X 10.3.9 Quartz PDFContext) >> endobj 226 0 obj << /Type /Metadata /Subtype /XML /Length 872 >> stream 2006-07-05T16:23:37-04:00 TeXShop 2006-07-05T19:19:30-04:00 Mac OS X 10.3.9 Quartz PDFContext 2006-07-05T16:23:37-04:00 2006-07-05T19:19:30-04:00 2006-07-05T19:19:30-04:00 endstream endobj xref 0 227 0000000225 65535 f 0000000016 00000 n 0000000035 00000 n 0000000176 00000 n 0000000319 00000 n 0000000435 00000 n 0000000504 00000 n 0000012638 00000 n 0000012660 00000 n 0000012852 00000 n 0000013041 00000 n 0000013234 00000 n 0000013428 00000 n 0000013625 00000 n 0000013805 00000 n 0000013984 00000 n 0000014153 00000 n 0000014343 00000 n 0000014539 00000 n 0000014732 00000 n 0000014752 00000 n 0000014895 00000 n 0000015039 00000 n 0000015110 00000 n 0000030041 00000 n 0000030064 00000 n 0000030245 00000 n 0000030427 00000 n 0000030597 00000 n 0000030617 00000 n 0000030760 00000 n 0000030906 00000 n 0000030977 00000 n 0000045036 00000 n 0000045059 00000 n 0000045226 00000 n 0000045246 00000 n 0000045389 00000 n 0000045535 00000 n 0000045606 00000 n 0000057804 00000 n 0000057827 00000 n 0000058007 00000 n 0000058027 00000 n 0000058170 00000 n 0000058316 00000 n 0000058387 00000 n 0000072358 00000 n 0000072381 00000 n 0000072508 00000 n 0000072528 00000 n 0000072671 00000 n 0000072817 00000 n 0000072888 00000 n 0000085234 00000 n 0000085257 00000 n 0000085398 00000 n 0000085418 00000 n 0000085561 00000 n 0000085708 00000 n 0000085826 00000 n 0000085897 00000 n 0000099013 00000 n 0000099036 00000 n 0000099216 00000 n 0000099236 00000 n 0000099379 00000 n 0000099526 00000 n 0000099597 00000 n 0000112199 00000 n 0000112222 00000 n 0000112363 00000 n 0000112383 00000 n 0000112526 00000 n 0000112673 00000 n 0000112744 00000 n 0000124280 00000 n 0000124303 00000 n 0000124496 00000 n 0000124675 00000 n 0000124695 00000 n 0000124839 00000 n 0000124986 00000 n 0000125058 00000 n 0000141086 00000 n 0000141109 00000 n 0000141344 00000 n 0000141514 00000 n 0000141534 00000 n 0000141678 00000 n 0000141825 00000 n 0000141897 00000 n 0000151376 00000 n 0000151398 00000 n 0000151619 00000 n 0000151788 00000 n 0000151808 00000 n 0000151952 00000 n 0000152099 00000 n 0000152171 00000 n 0000158846 00000 n 0000158869 00000 n 0000158996 00000 n 0000159017 00000 n 0000159163 00000 n 0000159314 00000 n 0000159423 00000 n 0000159497 00000 n 0000167068 00000 n 0000167091 00000 n 0000167218 00000 n 0000167239 00000 n 0000167385 00000 n 0000167536 00000 n 0000167610 00000 n 0000172806 00000 n 0000172829 00000 n 0000172930 00000 n 0000172951 00000 n 0000173097 00000 n 0000173248 00000 n 0000173322 00000 n 0000185140 00000 n 0000185164 00000 n 0000185371 00000 n 0000185392 00000 n 0000185538 00000 n 0000185689 00000 n 0000185763 00000 n 0000196929 00000 n 0000196953 00000 n 0000197147 00000 n 0000197170 00000 n 0000197194 00000 n 0000197216 00000 n 0000217521 00000 n 0000217545 00000 n 0000217788 00000 n 0000218542 00000 n 0000218565 00000 n 0000218589 00000 n 0000218611 00000 n 0000238952 00000 n 0000238976 00000 n 0000239223 00000 n 0000240119 00000 n 0000240142 00000 n 0000240165 00000 n 0000240187 00000 n 0000248915 00000 n 0000248938 00000 n 0000249187 00000 n 0000249522 00000 n 0000249544 00000 n 0000249567 00000 n 0000249589 00000 n 0000251691 00000 n 0000251714 00000 n 0000251955 00000 n 0000251986 00000 n 0000252062 00000 n 0000252085 00000 n 0000252109 00000 n 0000252131 00000 n 0000271079 00000 n 0000271103 00000 n 0000271358 00000 n 0000272136 00000 n 0000272158 00000 n 0000272181 00000 n 0000272203 00000 n 0000274556 00000 n 0000274579 00000 n 0000274821 00000 n 0000274921 00000 n 0000274948 00000 n 0000275015 00000 n 0000275037 00000 n 0000275060 00000 n 0000275082 00000 n 0000277300 00000 n 0000277323 00000 n 0000277558 00000 n 0000277800 00000 n 0000277822 00000 n 0000277845 00000 n 0000277867 00000 n 0000279618 00000 n 0000279641 00000 n 0000279881 00000 n 0000279908 00000 n 0000279945 00000 n 0000280038 00000 n 0000280060 00000 n 0000280082 00000 n 0000280104 00000 n 0000281688 00000 n 0000281711 00000 n 0000281950 00000 n 0000281977 00000 n 0000282009 00000 n 0000282089 00000 n 0000282112 00000 n 0000282136 00000 n 0000282158 00000 n 0000299418 00000 n 0000299442 00000 n 0000299683 00000 n 0000300563 00000 n 0000300586 00000 n 0000300609 00000 n 0000300631 00000 n 0000304233 00000 n 0000304256 00000 n 0000304512 00000 n 0000304624 00000 n 0000304647 00000 n 0000304671 00000 n 0000304693 00000 n 0000319297 00000 n 0000319321 00000 n 0000319569 00000 n 0000319905 00000 n 0000319987 00000 n 0000320063 00000 n 0000000000 00001 f 0000320228 00000 n trailer << /Size 227 /Info 224 0 R /Root 223 0 R /ID[<9411fe9b73231f0f34f91086b51a3dfa><66082f7c77d9852fa600ce40b0c10aab>] >> startxref 321185 %%EOF 3 0 obj << /Type /Page /Parent 4 0 R /Resources 5 0 R /Contents 2 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 30 0 obj << /Type /Page /Parent 4 0 R /Resources 31 0 R /Contents 29 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 37 0 obj << /Type /Page /Parent 4 0 R /Resources 38 0 R /Contents 36 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 44 0 obj << /Type /Page /Parent 4 0 R /Resources 45 0 R /Contents 43 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 51 0 obj << /Type /Page /Parent 4 0 R /Resources 52 0 R /Contents 50 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 58 0 obj << /Type /Page /Parent 59 0 R /Resources 60 0 R /Contents 57 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 66 0 obj << /Type /Page /Parent 59 0 R /Resources 67 0 R /Contents 65 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 73 0 obj << /Type /Page /Parent 59 0 R /Resources 74 0 R /Contents 72 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 81 0 obj << /Type /Page /Parent 59 0 R /Resources 82 0 R /Contents 80 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 89 0 obj << /Type /Page /Parent 59 0 R /Resources 90 0 R /Contents 88 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 97 0 obj << /Type /Page /Parent 59 0 R /Resources 98 0 R /Contents 96 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 104 0 obj << /Type /Page /Parent 105 0 R /Resources 106 0 R /Contents 103 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 112 0 obj << /Type /Page /Parent 105 0 R /Resources 113 0 R /Contents 111 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 119 0 obj << /Type /Page /Parent 105 0 R /Resources 120 0 R /Contents 118 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 126 0 obj << /Type /Page /Parent 105 0 R /Resources 127 0 R /Contents 125 0 R /MediaBox [ 0 0 612 792 ] /CropBox [ 36 18 612 774 ] >> endobj 223 0 obj << /Type /Catalog /Pages 222 0 R /Metadata 225 1 R >> endobj 224 0 obj << /CreationDate (D:20060705162337-04'00') /Creator (TeXShop) /ModDate (D:20060705192139-04'00') /Producer (Mac OS X 10.3.9 Quartz PDFContext) >> endobj 225 1 obj << /Type /Metadata /Subtype /XML /Length 872 >> stream 2006-07-05T16:23:37-04:00 TeXShop 2006-07-05T19:21:39-04:00 Mac OS X 10.3.9 Quartz PDFContext 2006-07-05T16:23:37-04:00 2006-07-05T19:21:39-04:00 2006-07-05T19:21:39-04:00 endstream endobj xref 0 1 0000000000 65535 f 3 1 0000325888 00000 n 30 1 0000326029 00000 n 37 1 0000326173 00000 n 44 1 0000326317 00000 n 51 1 0000326461 00000 n 58 1 0000326605 00000 n 66 1 0000326750 00000 n 73 1 0000326895 00000 n 81 1 0000327040 00000 n 89 1 0000327185 00000 n 97 1 0000327330 00000 n 104 1 0000327475 00000 n 112 1 0000327624 00000 n 119 1 0000327773 00000 n 126 1 0000327922 00000 n 223 3 0000328071 00000 n 0000328147 00000 n 0000328312 00001 n trailer << /Size 227 /Info 224 0 R /Root 223 0 R /Prev 321185 /ID[<9411fe9b73231f0f34f91086b51a3dfa><90c0724dbce351cf1d6ac7f413181478>] >> startxref 329269 %%EOF ./CBFlib-0.9.2.2/lib/0000755000076500007650000000000011603703065012351 5ustar yayayaya./CBFlib-0.9.2.2/lib/.keepme0000644000076500007650000000000011603702115013601 0ustar yayayaya./CBFlib-0.9.2.2/src/0000755000076500007650000000000011603703065012372 5ustar yayayaya./CBFlib-0.9.2.2/src/cbf_compress.c0000644000076500007650000006450011603702106015203 0ustar yayayaya/********************************************************************** * cbf_compress -- compression and decompression * * * * Version 0.8.0 20 July 2008 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifdef __cplusplus extern "C" { #endif #include #include #include #include #include "cbf.h" #include "cbf_alloc.h" #include "cbf_file.h" #include "cbf_compress.h" #include "cbf_canonical.h" #include "cbf_packed.h" #include "cbf_byte_offset.h" #include "cbf_predictor.h" #include "cbf_uncompressed.h" /* Compress an array */ int cbf_compress (void *source, size_t elsize, int elsign, size_t nelem, unsigned int compression, cbf_file *file, size_t *compressedsize, int *bits, char *digest, int realarray, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding) { int errorcode; size_t size; /* Discard any bits in the buffers */ cbf_failnez (cbf_reset_bits (file)) if (compressedsize) *compressedsize = 0; /* Start a digest? */ if (digest) cbf_failnez (cbf_start_digest (file)) errorcode = 0; size = 0; switch (compression&CBF_COMPRESSION_MASK) { case CBF_CANONICAL: errorcode = cbf_compress_canonical (source, elsize, elsign, nelem, compression, file, &size, bits, realarray, byteorder, dimfast, dimmid, dimslow, padding); break; case CBF_PACKED: case CBF_PACKED_V2: case 0: errorcode = cbf_compress_packed (source, elsize, elsign, nelem, compression, file, &size, bits, realarray, byteorder, dimfast, dimmid, dimslow, padding); break; case CBF_BYTE_OFFSET: errorcode = cbf_compress_byte_offset (source, elsize, elsign, nelem, compression, file, &size, bits, realarray, byteorder, dimfast, dimmid, dimslow, padding); break; case CBF_PREDICTOR: errorcode = cbf_compress_predictor (source, elsize, elsign, nelem, compression, file, &size, bits, realarray, byteorder, dimfast, dimmid, dimslow, padding); break; case CBF_NONE: errorcode = cbf_compress_none (source, elsize, elsign, nelem, compression, file, &size, bits, realarray, byteorder, dimfast, dimmid, dimslow, padding); break; default: errorcode = CBF_ARGUMENT; } /* Add the compressed size */ if (compressedsize) *compressedsize += size; /* Flush the buffers */ errorcode |= cbf_flush_bits (file); /* Get the digest? */ if (digest) errorcode |= cbf_end_digest (file, digest); /* Done */ return errorcode; } /* Get the parameters of an array (read up to the start of the table) */ int cbf_decompress_parameters (int *eltype, size_t *elsize, int *elsigned, int *elunsigned, size_t *nelem, int *minelem, int *maxelem, unsigned int compression, cbf_file *file) { unsigned int nelem_file; int errorcode, minelement_file, maxelement_file, elsigned_file, elunsigned_file; /* Discard any bits in the buffers */ file->bits [0] = 0; file->bits [1] = 0; /* Check compression type */ if (compression != CBF_CANONICAL && (compression&CBF_COMPRESSION_MASK) != CBF_PACKED && (compression&CBF_COMPRESSION_MASK) != CBF_PACKED_V2 && compression != CBF_BYTE_OFFSET && compression != CBF_PREDICTOR && compression != CBF_NONE) return CBF_FORMAT; if (compression == CBF_NONE || compression == CBF_BYTE_OFFSET ) { nelem_file = 0; minelement_file = maxelement_file = 0; } else { /* Read the number of elements (64 bits) */ cbf_failnez (cbf_get_integer (file, (int *) &nelem_file, 0, 64)) /* Read the minimum element (64 bits) */ errorcode = cbf_get_integer (file, &minelement_file, 1, 64); if (errorcode && errorcode != CBF_OVERFLOW) return errorcode; /* Read the maximum element (64 bits) */ errorcode = cbf_get_integer (file, &maxelement_file, 1, 64); if (errorcode && errorcode != CBF_OVERFLOW) return errorcode; } /* Update the element sign, type, minimum, maximum and number */ elsigned_file = !(((unsigned) minelement_file) <= ((unsigned) maxelement_file) && ((signed) minelement_file) > ((signed) maxelement_file)); elunsigned_file = !(((signed) minelement_file) <= ((signed) maxelement_file) && ((unsigned) minelement_file) > ((unsigned) maxelement_file)); if (elsigned) *elsigned = elsigned_file; if (elunsigned) *elunsigned = elunsigned_file; if (eltype) *eltype = CBF_INTEGER; if (elsize) { /* Calculate the minimum number of bytes needed to hold the elements */ if (minelement_file == 0 && maxelement_file == 0) { *elsize = 0; } else { if ((!elsigned_file || ((signed) minelement_file == (signed short) minelement_file && (signed) maxelement_file == (signed short) maxelement_file)) || (!elunsigned_file || ((unsigned) minelement_file == (unsigned short) minelement_file && (unsigned) maxelement_file == (unsigned short) maxelement_file))) { if ((!elsigned_file || ((signed) minelement_file == (signed char) minelement_file && (signed) maxelement_file == (signed char) maxelement_file)) || (!elunsigned_file || ((unsigned) minelement_file == (unsigned char) minelement_file && (unsigned) maxelement_file == (unsigned char) maxelement_file))) { *elsize = sizeof (char); } else { *elsize = sizeof (short); } } else { *elsize = sizeof (int); } } } if (minelem) *minelem = minelement_file; if (maxelem) *maxelem = maxelement_file; if (nelem) *nelem = nelem_file; /* Success */ return 0; } /* Decompress an array (from the start of the table) */ int cbf_decompress (void *destination, size_t elsize, int elsign, size_t nelem, size_t *nelem_read, size_t compressedsize, unsigned int compression, int bits, int sign, cbf_file *file, int realarray, const char *byteorder, size_t dimover, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding) { switch (compression&CBF_COMPRESSION_MASK) { case CBF_CANONICAL: return cbf_decompress_canonical (destination, elsize, elsign, nelem, nelem_read, compressedsize, compression, bits, sign, file, realarray, byteorder, dimover, dimfast, dimmid, dimslow, padding); case CBF_PACKED: case CBF_PACKED_V2: case 0: return cbf_decompress_packed (destination, elsize, elsign, nelem, nelem_read, compressedsize, compression, bits, sign, file, realarray, byteorder, dimover, dimfast, dimmid, dimslow, padding); case CBF_BYTE_OFFSET: return cbf_decompress_byte_offset (destination, elsize, elsign, nelem, nelem_read, compressedsize, compression, bits, sign, file, realarray, byteorder, dimover, dimfast, dimmid, dimslow, padding); case CBF_PREDICTOR: return cbf_decompress_predictor (destination, elsize, elsign, nelem, nelem_read, compressedsize, compression, bits, sign, file, realarray, byteorder, dimover, dimfast, dimmid, dimslow, padding); case CBF_NONE: return cbf_decompress_none (destination, elsize, elsign, nelem, nelem_read, compressedsize, compression, bits, sign, file, realarray, byteorder, dimover, dimfast, dimmid, dimslow, padding); } /* Fail */ return CBF_ARGUMENT; } #ifdef __cplusplus } #endif ./CBFlib-0.9.2.2/src/fcb_nblen_array.f900000644000076500007650000000136711603702106016022 0ustar yayayaya INTEGER FUNCTION FCB_NBLEN_ARRAY(ARRAY, ARRAYLEN) !----------------------------------------------------------------------- ! Returns the non-blank length of an array !----------------------------------------------------------------------- IMPLICIT NONE INTEGER, INTENT(IN):: ARRAYLEN INTEGER(1), INTENT(IN):: ARRAY(ARRAYLEN) INTEGER I,J !----------------------------------------------------------------------- FCB_NBLEN_ARRAY = 0 DO I = ARRAYLEN,1,-1 IF (FCB_NBLEN_ARRAY.NE.0)EXIT J=ARRAY(I) IF ((J.NE.IACHAR(' ')).AND.(J.NE.Z'09').AND.(J.NE.Z'0A').AND. & (J.NE.Z'0D').AND.(J.NE.0)) FCB_NBLEN_ARRAY = I END DO RETURN END FUNCTION FCB_NBLEN_ARRAY ./CBFlib-0.9.2.2/src/fcb_ci_strncmparr.f900000644000076500007650000000175111603702106016371 0ustar yayayaya INTEGER FUNCTION FCB_CI_STRNCMPARR(STRING, ARRAY, N, LIMIT) !----------------------------------------------------------------------- ! Compares up to LIMIT characters of STRING and ARRAY case insensitive !----------------------------------------------------------------------- IMPLICIT NONE CHARACTER(LEN=*),INTENT(IN):: STRING INTEGER, INTENT(IN):: N,LIMIT INTEGER(1), INTENT(IN):: ARRAY(N) INTEGER I,J,K,IA,IZ,UP !----------------------------------------------------------------------- IA=IACHAR('a') IZ=IACHAR('z') UP=IACHAR('A')-IA FCB_CI_STRNCMPARR = 0 DO I = 1,LIMIT J=0 IF (I.LE.LEN(STRING)) THEN J=IACHAR(STRING(I:I)) IF ((J.GE.IA).AND.(J.LE.IZ))J=J+UP ENDIF K=0 IF (I.LE.N) THEN K=ARRAY(I) IF ((K.GE.IA).AND.(K.LE.IZ))K=K+UP ENDIF FCB_CI_STRNCMPARR = J-K IF (J.NE.K)EXIT ENDDO RETURN END FUNCTION FCB_CI_STRNCMPARR ./CBFlib-0.9.2.2/src/cbf.c0000644000076500007650000063440111603702106013273 0ustar yayayaya/********************************************************************** * cbf -- cbflib API functions * * * * Version 0.8.0 20 July 2008 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifdef __cplusplus extern "C" { #endif #include "cbf.h" #include "cbf_alloc.h" #include "cbf_binary.h" #include "cbf_write.h" #include "cbf_string.h" #include "cbf_ascii.h" #include #include #include #include int cbf_parse (void *context); /* Create a handle */ int cbf_make_handle (cbf_handle *handle) { int errorcode; cbf_failnez (cbf_alloc ((void **) handle, NULL, sizeof (cbf_handle_struct), 1)) errorcode = cbf_make_node (&(*handle)->node, CBF_ROOT, NULL, NULL); if (errorcode) return errorcode | cbf_free ((void **) handle, NULL); (*handle)->row = 0; (*handle)->search_row = 0; (*handle)->refcount = 1; (*handle)->dictionary = NULL; (*handle)->file = NULL; (*handle)->commentfile = NULL; (*handle)->logfile = stderr; (*handle)->warnings = 0; (*handle)->errors = 0; (*handle)->startline = 0; (*handle)->startcolumn = 0; return 0; } int cbf_set_cbf_logfile (cbf_handle handle, FILE * logfile) { handle ->logfile = logfile; if (handle->file) handle->file->logfile = logfile; return 0; } /* Free a handle */ int cbf_free_handle (cbf_handle handle) { int errorcode; void *memblock; cbf_node *node; errorcode = 0; memblock = (void *) handle; if (handle && (--(handle->refcount) <= 0) ) { if (handle->dictionary) { errorcode |= cbf_free_handle ((cbf_handle) handle->dictionary); handle->dictionary = NULL; } if( handle->commentfile) errorcode |= cbf_free_file (&(handle->commentfile)); errorcode |= cbf_find_parent (&node, handle->node, CBF_ROOT); if (!errorcode) errorcode |= cbf_free_node (node); return errorcode | cbf_free (&memblock, NULL); } return 0; } /* Read a file or a wide file */ static int cbf_read_anyfile (cbf_handle handle, FILE *stream, int flags, const char * buffer, size_t buffer_size) { cbf_file *file; cbf_node *node, *tnode; void *parse [4]; int errorcode; unsigned int children; const char *name; /* Check the arguments */ if (!handle) { if (stream) fclose (stream); return CBF_ARGUMENT; } if (((flags & (MSG_DIGEST | MSG_DIGESTNOW | MSG_DIGESTWARN)) && (flags & MSG_NODIGEST))) { if (stream) fclose (stream); return CBF_ARGUMENT; } if (!stream && (!buffer || !buffer_size)) return CBF_ARGUMENT; /* Delete the old datablocks */ if( handle->commentfile) cbf_onfailnez (cbf_free_file (&(handle->commentfile)), fclose(stream)); cbf_onfailnez (cbf_find_parent (&node, handle->node, CBF_ROOT), fclose(stream)) cbf_onfailnez (cbf_set_children (node, 0), if (stream) fclose(stream)) handle->node = node; cbf_onfailnez (cbf_reset_refcounts(handle->dictionary), if (stream) fclose(stream)) /* Create the input file */ if (flags&CBF_PARSE_WIDE) { cbf_onfailnez (cbf_make_widefile (&file, stream), if (stream) fclose(stream)) file->logfile = handle->logfile; } else { cbf_onfailnez (cbf_make_file (&file, stream), if (stream) fclose(stream)) file->logfile = handle->logfile; } handle->file = file; if (buffer && buffer_size != 0) { cbf_onfailnez (cbf_set_io_buffersize(file, buffer_size+1), if (stream) fclose(stream)) memmove((void *)file->characters_base,(const void *)buffer,buffer_size); file->characters = file->characters_base; file->characters_used = buffer_size; if (stream) { file->characters[file->characters_used++] = '\n'; } } /* Defaults */ if ((flags & (MSG_DIGEST | MSG_NODIGEST | MSG_DIGESTNOW | MSG_DIGESTWARN )) == 0) flags |= (HDR_DEFAULT & (MSG_DIGEST | MSG_NODIGEST | MSG_DIGESTNOW | MSG_DIGESTWARN)); if (flags & (MSG_DIGESTNOW | MSG_DIGESTWARN) ) flags |= MSG_DIGEST; /* Copy the flags */ file->read_headers = flags; /* Parse the file */ parse [0] = file; parse [1] = handle->node; parse [2] = handle; parse [3] = 0; errorcode = cbf_parse (parse); /* Validate the last category, save frame and data block and do overall checks */ cbf_failnez(cbf_validate(handle, handle->node, CBF_ROOT, (cbf_node *)NULL) ) /* Delete the first datablock if it's empty */ if (!errorcode) { errorcode = cbf_get_child (&tnode, node, 0); if (!errorcode) { errorcode = cbf_get_name (&name, tnode); if (!errorcode && !name) { errorcode = cbf_count_children (&children, tnode); if (!errorcode && !children) errorcode = cbf_free_node (tnode); } } else if (errorcode == CBF_NOTFOUND) errorcode = 0; } cbf_onfailnez (cbf_find_parent (&node, handle->node, CBF_ROOT), cbf_delete_fileconnection (&file)) errorcode = cbf_count_children (&children, node); if (!errorcode && !children) { cbf_log(handle, "no data blocks found", CBF_LOGWARNING|CBF_LOGWOLINE); } /* Disconnect the file */ handle->file = NULL; return errorcode |(handle->errors?CBF_FORMAT:0) | cbf_delete_fileconnection (&file); } /* Read a file */ int cbf_read_file (cbf_handle handle, FILE *stream, int flags) { return cbf_read_anyfile (handle, stream, flags, NULL, 0); } /* Read a wide file */ int cbf_read_widefile (cbf_handle handle, FILE *stream, int flags) { return cbf_read_anyfile (handle, stream, flags|CBF_PARSE_WIDE, NULL, 0); } /* Read a pre-read buffered file */ int cbf_read_buffered_file (cbf_handle handle, FILE *stream, int flags, const char * buffer, size_t buffer_len) { return cbf_read_anyfile (handle, stream, flags, buffer, buffer_len); } /* Write a file */ int cbf_write_file (cbf_handle handle, FILE *stream, int isbuffer, int ciforcbf, int flags, int encoding) { cbf_file *file; cbf_node *node; int errorcode; /* CIF or CBF? */ if (ciforcbf == CIF) { encoding = encoding & ~ENC_NONE; if ((encoding &(ENC_CRTERM | ENC_LFTERM)) ==0 ) encoding |= ENC_LFTERM; } else { encoding = (encoding & ~(ENC_BASE8 | ENC_BASE10 | ENC_BASE16 | ENC_BASE64 | ENC_BASE32K | ENC_QP | ENC_FORWARD | ENC_BACKWARD)) | ENC_NONE; if ((encoding &(ENC_CRTERM | ENC_LFTERM)) ==0 ) encoding |= ENC_CRTERM|ENC_LFTERM; } /* Check the arguments */ if (!handle) return CBF_ARGUMENT; if (((flags & MIME_HEADERS) && (flags & PLAIN_HEADERS)) || ((flags & MSG_DIGEST) && (flags & MSG_NODIGEST)) || ((flags & MSG_DIGEST) && (flags & PLAIN_HEADERS)) || ((flags & MSG_DIGESTNOW) && (flags & MSG_NODIGEST)) || ((flags & MSG_DIGESTNOW) && (flags & PLAIN_HEADERS)) || ((encoding & ENC_FORWARD) && (encoding & ENC_BACKWARD))) return CBF_ARGUMENT; if (((encoding & ENC_NONE) > 0) + ((encoding & ENC_BASE8) > 0) + ((encoding & ENC_BASE10) > 0) + ((encoding & ENC_BASE16) > 0) + ((encoding & ENC_BASE64) > 0) + ((encoding & ENC_BASE32K) > 0) + ((encoding & ENC_QP) > 0) > 1) return CBF_ARGUMENT; /* Find the root node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_ROOT)) /* Create the file */ cbf_failnez (cbf_make_file (&file, stream)) file->logfile = handle->logfile; /* Defaults */ if (flags & (MSG_DIGEST | MSG_DIGESTNOW)) flags |= MIME_HEADERS; else if ((flags & (MIME_HEADERS | PLAIN_HEADERS)) == 0) flags |= (HDR_DEFAULT & (MIME_HEADERS | PLAIN_HEADERS)); if (flags & PLAIN_HEADERS) flags |= MSG_NODIGEST; else if ((flags & (MSG_DIGEST | MSG_NODIGEST | MSG_DIGESTNOW)) == 0) flags |= (HDR_DEFAULT & (MSG_DIGEST | MSG_NODIGEST | MSG_DIGESTNOW)); if (flags & MSG_DIGESTNOW) flags |= MSG_DIGEST; if ((encoding & (ENC_NONE | ENC_BASE8 | ENC_BASE10 | ENC_BASE16 | ENC_BASE64 | ENC_BASE32K | ENC_QP)) == 0) encoding |= (ENC_DEFAULT & (ENC_NONE | ENC_BASE8 | ENC_BASE10 | ENC_BASE16 | ENC_BASE64 | ENC_BASE32K | ENC_QP)); if ((encoding & (ENC_CRTERM | ENC_LFTERM)) == 0) encoding |= (ENC_DEFAULT & (ENC_CRTERM | ENC_LFTERM)); if ((encoding & (ENC_FORWARD | ENC_BACKWARD)) == 0) encoding |= (ENC_DEFAULT & (ENC_FORWARD | ENC_BACKWARD)); /* Copy the flags */ file->write_headers = flags; file->write_encoding = encoding; /* Reset the reference counts */ cbf_failnez( cbf_reset_refcounts(handle->dictionary) ) /* Write the file */ errorcode = cbf_write_node (handle, node, file, isbuffer); /* Free the file structure but don't close the file? */ if (!isbuffer) file->stream = NULL; /* Disconnect the file */ return errorcode | cbf_delete_fileconnection (&file); } /* Write a file, starting from the local node */ int cbf_write_local_file (cbf_handle handle, FILE *stream, int isbuffer, int ciforcbf, int flags, int encoding) { cbf_file *file; cbf_node *node; int errorcode; /* CIF or CBF? */ if (ciforcbf == CIF) { encoding = encoding & ~ENC_NONE; if ((encoding &(ENC_CRTERM | ENC_LFTERM))==0 ) encoding |= ENC_LFTERM; } else { encoding = (encoding & ~(ENC_BASE8 | ENC_BASE10 | ENC_BASE16 | ENC_BASE64 | ENC_BASE32K | ENC_QP | ENC_FORWARD | ENC_BACKWARD)) | ENC_NONE; if ((encoding &(ENC_CRTERM | ENC_LFTERM)) ==0 ) encoding |= ENC_CRTERM|ENC_LFTERM; } /* Check the arguments */ if (!handle) return CBF_ARGUMENT; if (((flags & MIME_HEADERS) && (flags & PLAIN_HEADERS)) || ((flags & MSG_DIGEST) && (flags & MSG_NODIGEST)) || ((flags & MSG_DIGEST) && (flags & PLAIN_HEADERS)) || ((flags & MSG_DIGESTNOW) && (flags & MSG_NODIGEST)) || ((flags & MSG_DIGESTNOW) && (flags & PLAIN_HEADERS)) || ((encoding & ENC_FORWARD) && (encoding & ENC_BACKWARD))) return CBF_ARGUMENT; if (((flags & MIME_HEADERS) && (flags & PLAIN_HEADERS)) || ((flags & MSG_DIGEST) && (flags & MSG_NODIGEST)) || ((flags & MSG_DIGEST) && (flags & PLAIN_HEADERS)) || ((flags & MSG_DIGESTNOW) && (flags & MSG_NODIGEST)) || ((flags & MSG_DIGESTNOW) && (flags & PLAIN_HEADERS)) || ((encoding & ENC_FORWARD) && (encoding & ENC_BACKWARD))) return CBF_ARGUMENT; if (((encoding & ENC_NONE) > 0) + ((encoding & ENC_BASE8) > 0) + ((encoding & ENC_BASE10) > 0) + ((encoding & ENC_BASE16) > 0) + ((encoding & ENC_BASE64) > 0) + ((encoding & ENC_BASE32K) > 0) + ((encoding & ENC_QP) > 0) > 1) return CBF_ARGUMENT; /* Create the file */ cbf_failnez (cbf_make_file (&file, stream)) file->logfile = handle->logfile; /* Defaults */ if (flags & (MSG_DIGEST | MSG_DIGESTNOW)) flags |= MIME_HEADERS; else if ((flags & (MIME_HEADERS | PLAIN_HEADERS)) == 0) flags |= (HDR_DEFAULT & (MIME_HEADERS | PLAIN_HEADERS)); if (flags & PLAIN_HEADERS) flags |= MSG_NODIGEST; else if ((flags & (MSG_DIGEST | MSG_NODIGEST | MSG_DIGESTNOW)) == 0) flags |= (HDR_DEFAULT & (MSG_DIGEST | MSG_NODIGEST | MSG_DIGESTNOW)); if (flags & MSG_DIGESTNOW) flags |= MSG_DIGEST; if ((encoding & (ENC_NONE | ENC_BASE8 | ENC_BASE10 | ENC_BASE16 | ENC_BASE64 | ENC_BASE32K | ENC_QP)) == 0) encoding |= (ENC_DEFAULT & (ENC_NONE | ENC_BASE8 | ENC_BASE10 | ENC_BASE16 | ENC_BASE64 | ENC_BASE32K | ENC_QP)); if ((encoding & (ENC_CRTERM | ENC_LFTERM)) == 0) encoding |= (ENC_DEFAULT & (ENC_CRTERM | ENC_LFTERM)); if ((encoding & (ENC_FORWARD | ENC_BACKWARD)) == 0) encoding |= (ENC_DEFAULT & (ENC_FORWARD | ENC_BACKWARD)); /* Copy the flags */ file->write_headers = flags; file->write_encoding = encoding; node = handle->node; /* Write the file */ errorcode = cbf_write_node (handle, node, file, isbuffer); /* Free the file structure but don't close the file? */ if (!isbuffer) file->stream = NULL; /* Disconnect the file */ return errorcode | cbf_delete_fileconnection (&file); } /* Write a wide file */ int cbf_write_widefile (cbf_handle handle, FILE *stream, int isbuffer, int ciforcbf, int flags, int encoding) { cbf_file *file; cbf_node *node; int errorcode; /* CIF or CBF? */ if (ciforcbf == CIF) { encoding = encoding & ~ENC_NONE; if ((encoding &(ENC_CRTERM | ENC_LFTERM)) ==0 ) encoding |= ENC_LFTERM; } else { encoding = (encoding & ~(ENC_BASE8 | ENC_BASE10 | ENC_BASE16 | ENC_BASE64 | ENC_BASE32K | ENC_QP | ENC_FORWARD | ENC_BACKWARD)) | ENC_NONE; if ((encoding &(ENC_CRTERM | ENC_LFTERM)) ==0 ) encoding |= ENC_CRTERM|ENC_LFTERM; } /* Check the arguments */ if (!handle) return CBF_ARGUMENT; if (((flags & MIME_HEADERS) && (flags & PLAIN_HEADERS)) || ((flags & MSG_DIGEST) && (flags & MSG_NODIGEST)) || ((flags & MSG_DIGEST) && (flags & PLAIN_HEADERS)) || ((flags & MSG_DIGESTNOW) && (flags & MSG_NODIGEST)) || ((flags & MSG_DIGESTNOW) && (flags & PLAIN_HEADERS)) || ((encoding & ENC_FORWARD) && (encoding & ENC_BACKWARD))) return CBF_ARGUMENT; if (((flags & MIME_HEADERS) && (flags & PLAIN_HEADERS)) || ((flags & MSG_DIGEST) && (flags & MSG_NODIGEST)) || ((flags & MSG_DIGEST) && (flags & PLAIN_HEADERS)) || ((flags & MSG_DIGESTNOW) && (flags & MSG_NODIGEST)) || ((flags & MSG_DIGESTNOW) && (flags & PLAIN_HEADERS)) || ((encoding & ENC_FORWARD) && (encoding & ENC_BACKWARD))) return CBF_ARGUMENT; if (((encoding & ENC_NONE) > 0) + ((encoding & ENC_BASE8) > 0) + ((encoding & ENC_BASE10) > 0) + ((encoding & ENC_BASE16) > 0) + ((encoding & ENC_BASE64) > 0) + ((encoding & ENC_BASE32K) > 0) + ((encoding & ENC_QP) > 0) > 1) return CBF_ARGUMENT; /* Find the root node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_ROOT)) /* Create the file */ cbf_failnez (cbf_make_widefile (&file, stream)) /* Defaults */ if (flags & (MSG_DIGEST | MSG_DIGESTNOW)) flags |= MIME_HEADERS; else if ((flags & (MIME_HEADERS | PLAIN_HEADERS)) == 0) flags |= (HDR_DEFAULT & (MIME_HEADERS | PLAIN_HEADERS)); if (flags & PLAIN_HEADERS) flags |= MSG_NODIGEST; else if ((flags & (MSG_DIGEST | MSG_NODIGEST | MSG_DIGESTNOW)) == 0) flags |= (HDR_DEFAULT & (MSG_DIGEST | MSG_NODIGEST | MSG_DIGESTNOW)); if (flags & MSG_DIGESTNOW) flags |= MSG_DIGEST; if ((encoding & (ENC_NONE | ENC_BASE8 | ENC_BASE10 | ENC_BASE16 | ENC_BASE64 | ENC_BASE32K | ENC_QP)) == 0) encoding |= (ENC_DEFAULT & (ENC_NONE | ENC_BASE8 | ENC_BASE10 | ENC_BASE16 | ENC_BASE64 | ENC_BASE32K | ENC_QP)); if ((encoding & (ENC_CRTERM | ENC_LFTERM)) == 0) encoding |= (ENC_DEFAULT & (ENC_CRTERM | ENC_LFTERM)); if ((encoding & (ENC_FORWARD | ENC_BACKWARD)) == 0) encoding |= (ENC_DEFAULT & (ENC_FORWARD | ENC_BACKWARD)); /* Copy the flags */ file->write_headers = flags; file->write_encoding = encoding; /* Write the file */ errorcode = cbf_write_node (handle, node, file, isbuffer); /* Free the file structure but don't close the file? */ if (!isbuffer) file->stream = NULL; /* Disconnect the file */ return errorcode | cbf_delete_fileconnection (&file); } /* Add a data block */ int cbf_new_datablock (cbf_handle handle, const char *datablockname) { cbf_node *node; int errorcode; if (!handle) return CBF_ARGUMENT; /* Find the root node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_ROOT)) /* Copy the name */ if (datablockname) { datablockname = cbf_copy_string (NULL, datablockname, 0); if (!datablockname) return CBF_ALLOC; } /* Add a datablock */ errorcode = cbf_make_child (&node, node, CBF_DATABLOCK, datablockname); if (errorcode) { cbf_free_string (NULL, datablockname); return errorcode; } /* Success */ handle->node = node; return 0; } /* Add a save frame */ int cbf_new_saveframe (cbf_handle handle, const char *saveframename) { cbf_node *node; int errorcode; if (!handle) return CBF_ARGUMENT; /* Find the root node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_DATABLOCK)) /* Copy the name */ if (saveframename) { saveframename = cbf_copy_string (NULL, saveframename, 0); if (!saveframename) return CBF_ALLOC; } /* Add a save frame */ errorcode = cbf_make_child (&node, node, CBF_SAVEFRAME, saveframename); if (errorcode) { cbf_free_string (NULL, saveframename); return errorcode; } /* Success */ handle->node = node; return 0; } /* Add a data block, allowing for duplicates */ int cbf_force_new_datablock (cbf_handle handle, const char *datablockname) { cbf_node *node; int errorcode; if (!handle) return CBF_ARGUMENT; /* Find the root node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_ROOT)) /* Copy the name */ if (datablockname) { datablockname = cbf_copy_string (NULL, datablockname, 0); if (!datablockname) return CBF_ALLOC; } /* Add a datablock */ errorcode = cbf_make_new_child (&node, node, CBF_DATABLOCK, datablockname); if (errorcode) { cbf_free_string (NULL, datablockname); return errorcode; } /* Success */ handle->node = node; return 0; } /* Add a save frame, allowing for duplicates */ int cbf_force_new_saveframe (cbf_handle handle, const char *saveframename) { cbf_node *node; int errorcode; if (!handle) return CBF_ARGUMENT; /* Find the DATABLOCK */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_DATABLOCK)) /* Copy the name */ if (saveframename) { saveframename = cbf_copy_string (NULL, saveframename, 0); if (!saveframename) return CBF_ALLOC; } /* Add a save frame */ errorcode = cbf_make_new_child (&node, node, CBF_SAVEFRAME, saveframename); if (errorcode) { cbf_free_string (NULL, saveframename); return errorcode; } /* Success */ handle->node = node; return 0; } /* Add a category to the current data block or save frame*/ int cbf_new_category (cbf_handle handle, const char *categoryname) { cbf_node *node; int errorcode; if (!handle) return CBF_ARGUMENT; /* Find the save frame or data block node */ if (cbf_find_parent (&node, handle->node, CBF_SAVEFRAME)) { cbf_failnez (cbf_find_parent (&node, handle->node, CBF_DATABLOCK)) } /* Copy the name */ if (categoryname) { categoryname = cbf_copy_string (NULL, categoryname, 0); if (!categoryname) return CBF_ALLOC; } /* Add a category */ errorcode = cbf_make_child (&node, node, CBF_CATEGORY, categoryname); if (errorcode) { cbf_free_string (NULL, categoryname); return errorcode; } /* Success */ handle->node = node; return 0; } /* Add a category to the current data block, allowing for duplicates */ int cbf_force_new_category (cbf_handle handle, const char *categoryname) { cbf_node *node; int errorcode; if (!handle) return CBF_ARGUMENT; /* Find the data block node */ if (cbf_find_parent (&node, handle->node, CBF_SAVEFRAME)) { cbf_failnez (cbf_find_parent (&node, handle->node, CBF_DATABLOCK)) } /* Copy the name */ if (categoryname) { categoryname = cbf_copy_string (NULL, categoryname, 0); if (!categoryname) return CBF_ALLOC; } /* Add a category */ errorcode = cbf_make_new_child (&node, node, CBF_CATEGORY, categoryname); if (errorcode) { cbf_free_string (NULL, categoryname); return errorcode; } /* Success */ handle->node = node; return 0; } /* Add a column to the current category */ int cbf_new_column (cbf_handle handle, const char *columnname) { cbf_node *node; int errorcode; unsigned int rows; if (!handle) return CBF_ARGUMENT; /* Find the category node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_CATEGORY)) /* How many rows does this category have? */ cbf_failnez (cbf_count_rows (handle, &rows)) /* Copy the name */ if (columnname) { columnname = cbf_copy_string (NULL, columnname, 0); if (!columnname) return CBF_ALLOC; } /* Add a column */ errorcode = cbf_make_child (&node, node, CBF_COLUMN, columnname); if (errorcode) { cbf_free_string (NULL, columnname); return errorcode; } /* Set the number of rows */ errorcode = cbf_set_children (node, rows); if (errorcode) return errorcode | cbf_free_node (node); /* Success */ handle->node = node; handle->row = 0; handle->search_row = 0; return 0; } /* Add a row to the current category */ int cbf_new_row (cbf_handle handle) { cbf_node *node, *columnnode; int errorcode [2]; unsigned int rows, columns, column; if (!handle) return CBF_ARGUMENT; /* Find the category node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_CATEGORY)) /* How many rows and columns does this category have? */ cbf_failnez (cbf_count_rows (handle, &rows)) cbf_failnez (cbf_count_columns (handle, &columns)) /* Add a row to each column */ for (column = 0; column < columns; column++) { errorcode [0] = cbf_get_child (&columnnode, node, column); if (!errorcode [0]) errorcode [0] = cbf_add_columnrow (columnnode, NULL); if (errorcode [0]) { /* Set the columns back to the original number of rows */ while (column) { column--; errorcode [1] = cbf_get_child (&columnnode, node, column); if (!errorcode [1]) errorcode [1] |= cbf_set_children (columnnode, rows); errorcode [0] |= errorcode [1]; } return errorcode [0]; } } /* Success */ handle->row = rows; handle->search_row = rows; return 0; } /* Insert a row in the current category */ int cbf_insert_row (cbf_handle handle, const int rownumber) { cbf_node *node, *columnnode; int errorcode [2]; unsigned int rows, columns, column; if (!handle) return CBF_ARGUMENT; /* Find the category node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_CATEGORY)) /* How many rows and columns does this category have? */ cbf_failnez (cbf_count_rows (handle, &rows)) cbf_failnez (cbf_count_columns (handle, &columns)) /* Insert a row into each column */ for (column = 0; column < columns; column++) { errorcode [0] = cbf_get_child (&columnnode, node, column); if (!errorcode [0]) errorcode [0] = cbf_insert_columnrow (columnnode, rownumber, NULL); if (errorcode [0]) { /* Set the columns back to the original number of rows */ while (column) { column--; errorcode [1] = cbf_get_child (&columnnode, node, column); if (!errorcode [1]) errorcode [1] |= cbf_delete_columnrow (columnnode, rownumber); errorcode [0] |= errorcode [1]; } return errorcode [0]; } } /* Success */ handle->row = rownumber; handle->search_row = rownumber; return 0; } /* Delete a row from the current category */ int cbf_delete_row (cbf_handle handle, const int rownumber) { cbf_node *node, *columnnode; int errorcode [2]; unsigned int rows, columns, column; if (!handle) return CBF_ARGUMENT; /* Find the category node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_CATEGORY)) /* How many rows and columns does this category have? */ cbf_failnez (cbf_count_rows (handle, &rows)) cbf_failnez (cbf_count_columns (handle, &columns)) /* Delete a row from each column */ errorcode [0] = 0; for (column = 0; column < columns; column++) { errorcode [1] = cbf_get_child (&columnnode, node, column); if (!errorcode [1]) errorcode [1] = cbf_delete_columnrow (columnnode, rownumber); errorcode [0] |= errorcode [1]; } rows--; if (handle->row > rownumber) handle->row--; if (handle->search_row > rownumber) handle->search_row--; return errorcode [0]; } /* Change the name of the current data block */ int cbf_set_datablockname (cbf_handle handle, const char *datablockname) { cbf_node *node; int errorcode; if (!handle) return CBF_ARGUMENT; /* Find the data block node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_DATABLOCK)) /* Copy the name */ if (datablockname) { datablockname = cbf_copy_string (NULL, datablockname, 0); if (!datablockname) return CBF_ALLOC; } /* Change the name */ errorcode = cbf_name_node (node, datablockname); if (errorcode) { cbf_free_string (NULL, datablockname); return errorcode; } /* Success */ handle->node = node; return 0; } /* Change the name of the current save frame */ int cbf_set_saveframename (cbf_handle handle, const char *saveframename) { cbf_node *node; int errorcode; if (!handle) return CBF_ARGUMENT; /* Find the save frame node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_SAVEFRAME)) /* Copy the name */ if (saveframename) { saveframename = cbf_copy_string (NULL, saveframename, 0); if (!saveframename) return CBF_ALLOC; } /* Change the name */ errorcode = cbf_name_node (node, saveframename); if (errorcode) { cbf_free_string (NULL, saveframename); return errorcode; } /* Success */ handle->node = node; return 0; } /* Delete all categories from all the data blocks */ int cbf_reset_datablocks (cbf_handle handle) { cbf_node *node, *datablocknode; unsigned int datablocks, datablock; int errorcode; if (!handle) return CBF_ARGUMENT; /* Find the data block node */ errorcode = cbf_find_parent (&datablocknode, handle->node, CBF_DATABLOCK); if (errorcode && errorcode != CBF_NOTFOUND) return errorcode; /* Find the root node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_ROOT)) if (errorcode) handle->node = node; else handle->node = datablocknode; /* Delete all grandchildren */ cbf_failnez (cbf_count_children (&datablocks, node)) for (datablock = 0; datablock < datablocks; datablock++) { cbf_failnez (cbf_get_child (&node, handle->node, datablock)) cbf_failnez (cbf_set_children (node, 0)) } /* Success */ return 0; } /* Delete all categories from the current data block */ int cbf_reset_datablock (cbf_handle handle) { cbf_node *node; if (!handle) return CBF_ARGUMENT; /* Find the data block node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_DATABLOCK)) handle->node = node; /* Delete the children */ return cbf_set_children (node, 0); } /* Delete all categories from the current save frame */ int cbf_reset_saveframe (cbf_handle handle) { cbf_node *node; if (!handle) return CBF_ARGUMENT; /* Find the data block node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_SAVEFRAME)) handle->node = node; /* Delete the children */ return cbf_set_children (node, 0); } /* Delete all columns and rows from the current category */ int cbf_reset_category (cbf_handle handle) { cbf_node *node; if (!handle) return CBF_ARGUMENT; /* Find the category node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_CATEGORY)) handle->node = node; /* Delete the children */ return cbf_set_children (node, 0); } /* Delete the current data block */ int cbf_remove_datablock (cbf_handle handle) { cbf_node *node, *parent; if (!handle) return CBF_ARGUMENT; /* Find the data block node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_DATABLOCK)) /* Find the root node */ cbf_failnez (cbf_find_parent (&parent, node, CBF_ROOT)) handle->node = parent; /* Delete the datablock */ return cbf_free_node (node); } /* Delete the current save frame */ int cbf_remove_saveframe (cbf_handle handle) { cbf_node *node, *parent; if (!handle) return CBF_ARGUMENT; /* Find the save frame node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_SAVEFRAME)) /* Find the data block */ cbf_failnez (cbf_find_parent (&parent, node, CBF_DATABLOCK)) handle->node = parent; /* Delete the save frame */ return cbf_free_node (node); } /* Delete the current category */ int cbf_remove_category (cbf_handle handle) { cbf_node *node, *parent; if (!handle) return CBF_ARGUMENT; /* Find the category node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_CATEGORY)) /* Find the save frame or data block node */ if (cbf_find_parent (&parent, node, CBF_SAVEFRAME)) { cbf_failnez (cbf_find_parent (&parent, node, CBF_DATABLOCK)) } handle->node = parent; /* Delete the column */ return cbf_free_node (node); } /* Delete the current column */ int cbf_remove_column (cbf_handle handle) { cbf_node *node, *parent; if (!handle) return CBF_ARGUMENT; /* Find the column node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_COLUMN)) /* Find the category node */ cbf_failnez (cbf_find_parent (&parent, node, CBF_CATEGORY)) handle->node = parent; /* Delete the column */ return cbf_free_node (node); } /* Delete the current row */ int cbf_remove_row (cbf_handle handle) { if (!handle) return CBF_ARGUMENT; return cbf_delete_row (handle, handle->row); } /* Make the first data block the current data block */ int cbf_rewind_datablock (cbf_handle handle) { cbf_node *node; if (!handle) return CBF_ARGUMENT; /* Find the root node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_ROOT)) /* Find the first child */ cbf_failnez (cbf_get_child (&node, node, 0)) handle->node = node; /* Success */ return 0; } /* Make the first save frame in the current data block the current saveframe */ int cbf_rewind_saveframe (cbf_handle handle) { cbf_node *node; cbf_node *child_node; int i; if (!handle) return CBF_ARGUMENT; /* Find the save frame or data block node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_DATABLOCK)) /* Find the first child that is a save frame*/ for (i = 0; (unsigned int)i < node->children; i++) { cbf_failnez (cbf_get_child (&child_node, node, i)) if (child_node && child_node->type == CBF_SAVEFRAME) { handle->node = child_node; /* Success */ return 0; } } return CBF_NOTFOUND; } /* Make the first category in the current data block the current category */ int cbf_rewind_category (cbf_handle handle) { cbf_node *node; cbf_node *child_node; int i; if (!handle) return CBF_ARGUMENT; /* Find the save frame or data block node */ if (cbf_find_parent (&node, handle->node, CBF_SAVEFRAME)) { cbf_failnez (cbf_find_parent (&node, handle->node, CBF_DATABLOCK)) } /* Find the first child that is a category*/ for (i = 0; (unsigned int)i < node->children; i++) { cbf_failnez (cbf_get_child (&child_node, node, i)) if (child_node && child_node->type == CBF_CATEGORY) { handle->node = child_node; /* Success */ return 0; } } return CBF_NOTFOUND; } /* Make the first save frame or category in the current data block the current save frame or category */ int cbf_rewind_blockitem (cbf_handle handle, CBF_NODETYPE * type) { cbf_node *node; cbf_node *child_node; if (!handle) return CBF_ARGUMENT; /* Find the data block node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_DATABLOCK)) /* Find the first child */ cbf_failnez (cbf_get_child (&child_node, node, 0)) handle->node = child_node; *type = child_node->type; /* Success */ return 0; } /* Make the first column in the current category the current column */ int cbf_rewind_column (cbf_handle handle) { cbf_node *node; if (!handle) return CBF_ARGUMENT; /* Find the category node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_CATEGORY)) /* Find the first child */ cbf_failnez (cbf_get_child (&node, node, 0)) handle->node = node; /* Success */ return 0; } /* Make the first row in the current category the current row */ int cbf_rewind_row (cbf_handle handle) { if (!handle) return CBF_ARGUMENT; handle->row = 0; handle->search_row = 0; /* Success */ return 0; } /* Make the next data block the current data block */ int cbf_next_datablock (cbf_handle handle) { cbf_node *parent, *node; unsigned int index; if (!handle) return CBF_ARGUMENT; /* Find the data block node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_DATABLOCK)) /* Find the root node */ cbf_failnez (cbf_find_parent (&parent, node, CBF_ROOT)) /* Which child is this? */ cbf_failnez (cbf_child_index (&index, node)) /* Get the next data block */ cbf_failnez (cbf_get_child (&node, parent, index + 1)) handle->node = node; /* Success */ return 0; } /* Make the next category in the current save frame or data block the current category */ int cbf_next_category (cbf_handle handle) { cbf_node *parent, *node; int i; unsigned int index; if (!handle) return CBF_ARGUMENT; /* Find the category node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_CATEGORY)) /* Find the save frame or data block node */ if (cbf_find_parent (&parent, node, CBF_SAVEFRAME)) { cbf_failnez (cbf_find_parent (&parent, node, CBF_DATABLOCK)) } /* Which child is this? */ cbf_failnez (cbf_child_index (&index, node)) /* Get the next category */ for (i = index+1; (unsigned int)ichildren; i++) { cbf_failnez (cbf_get_child (&node, parent, i)) if (node->type == CBF_CATEGORY) { handle->node = node; /* Success */ return 0; } } return CBF_NOTFOUND; } /* Make the next save frame in the current data block the current save frame */ int cbf_next_saveframe (cbf_handle handle) { cbf_node *parent, *node; int i; unsigned int index; if (!handle) return CBF_ARGUMENT; /* Find the category node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_SAVEFRAME)) /* Find the data block node */ cbf_failnez (cbf_find_parent (&parent, node, CBF_DATABLOCK)) /* Which child is this? */ cbf_failnez (cbf_child_index (&index, node)) /* Get the next save frame */ for (i = index+1; (unsigned int)ichildren; i++) { cbf_failnez (cbf_get_child (&node, parent, i)) if (node->type == CBF_SAVEFRAME) { handle->node = node; /* Success */ return 0; } } return CBF_NOTFOUND; } /* Make the next save frame or category the current data block or category */ int cbf_next_blockitem (cbf_handle handle, CBF_NODETYPE * type) { cbf_node *parent, *node; unsigned int index; if (!handle) return CBF_ARGUMENT; /* Discover if we are in a save frame or just in a data block */ if (cbf_find_parent (&node, handle->node, CBF_SAVEFRAME)) { /* There is no save frame look for a category */ cbf_failnez(cbf_find_parent (&node, handle->node, CBF_CATEGORY)) } /* Find the root node */ cbf_failnez (cbf_find_parent (&parent, node, CBF_DATABLOCK)) /* Which child is this? */ cbf_failnez (cbf_child_index (&index, node)) /* Get the next data block */ cbf_failnez (cbf_get_child (&node, parent, index + 1)) handle->node = node; *type = handle->node->type; /* Success */ return 0; } /* Make the next column in the current category the current column */ int cbf_next_column (cbf_handle handle) { cbf_node *parent, *node; unsigned int index; if (!handle) return CBF_ARGUMENT; /* Find the column node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_COLUMN)) /* Find the category node */ cbf_failnez (cbf_find_parent (&parent, node, CBF_CATEGORY)) /* Which child is this? */ cbf_failnez (cbf_child_index (&index, node)) /* Get the next column */ cbf_failnez (cbf_get_child (&node, parent, index + 1)) handle->node = node; /* Success */ return 0; } /* Make the next row in the current category the current row */ int cbf_next_row (cbf_handle handle) { cbf_node *node; unsigned int rows; if (!handle) return CBF_ARGUMENT; /* Find the column node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_COLUMN)) cbf_failnez (cbf_count_children (&rows, node)) /* Is the row valid? */ if (handle->row >= rows) return CBF_NOTFOUND; handle->row++; handle->search_row = handle->row; /* Success */ return 0; } /* Make the specified data block the current data block */ int cbf_select_datablock (cbf_handle handle, unsigned int datablock) { cbf_node *node; if (!handle) return CBF_ARGUMENT; /* Find the root node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_ROOT)) /* Select the data block */ cbf_failnez (cbf_get_child (&node, node, datablock)) handle->node = node; /* Success */ return 0; } /* Make the specified save frame the current save frame */ int cbf_select_saveframe (cbf_handle handle, unsigned int saveframe) { cbf_node *node; cbf_node *child_node; unsigned int isf, jsf; if (!handle) return CBF_ARGUMENT; /* Find the data block node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_DATABLOCK)) /* Select the save frame */ isf = 0; jsf = 0; while (jsf < saveframe+1 && isf < node->children) { cbf_failnez (cbf_get_child (&child_node, node, isf++)) if (child_node->type == CBF_SAVEFRAME) jsf++; } if (jsf == saveframe+1) { handle->node = child_node; /* Success */ return 0; } return CBF_NOTFOUND; } /* Make the specified category the current category */ int cbf_select_category (cbf_handle handle, unsigned int category) { cbf_node *node; cbf_node *child_node; unsigned int icat, jcat; if (!handle) return CBF_ARGUMENT; /* Find the data block node */ if (cbf_find_parent (&node, handle->node, CBF_SAVEFRAME)) { cbf_failnez (cbf_find_parent (&node, handle->node, CBF_DATABLOCK)) } /* Select the category */ icat = 0; jcat = 0; while (jcat < category+1 && icat < node->children) { cbf_failnez (cbf_get_child (&child_node, node, icat++)) if (child_node->type == CBF_CATEGORY) jcat++; } if (jcat == category+1) { handle->node = child_node; /* Success */ return 0; } return CBF_NOTFOUND; } /* Make the specified category or save frame the current block item */ int cbf_select_blockitem (cbf_handle handle, unsigned int item, CBF_NODETYPE * type) { cbf_node *node; cbf_node *child_node; if (!handle) return CBF_ARGUMENT; /* Find the data block node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_DATABLOCK)) /* Select the item */ cbf_failnez (cbf_get_child (&child_node, node, item)) handle->node = child_node; *type = child_node->type; /* Success */ return 0; } /* Make the specified column the current column */ int cbf_select_column (cbf_handle handle, unsigned int column) { cbf_node *node; if (!handle) return CBF_ARGUMENT; /* Find the category node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_CATEGORY)) /* Select the column */ cbf_failnez (cbf_get_child (&node, node, column)) handle->node = node; /* Success */ return 0; } /* Make the specified row the current row */ int cbf_select_row (cbf_handle handle, unsigned int row) { cbf_node *node; unsigned int rows; if (!handle) return CBF_ARGUMENT; /* Find the column node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_COLUMN)) cbf_failnez (cbf_count_children (&rows, node)) /* Is the row valid? */ if (row >= rows) return CBF_NOTFOUND; handle->row = row; handle->search_row = row; /* Success */ return 0; } /* Make the named data block the current data block */ int cbf_find_datablock (cbf_handle handle, const char *datablockname) { cbf_node *node; if (!handle) return CBF_ARGUMENT; /* Find the root node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_ROOT)) /* Find the data block */ cbf_failnez (cbf_find_child (&node, node, datablockname)) handle->node = node; /* Success */ return 0; } /* Make the named save frame in the current data block the current save frame */ int cbf_find_saveframe (cbf_handle handle, const char *saveframename) { cbf_node *node; if (!handle) return CBF_ARGUMENT; /* Find the data block node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_DATABLOCK)) /* Find the save frame */ cbf_failnez (cbf_find_typed_child (&node, node, saveframename, CBF_SAVEFRAME)) handle->node = node; handle->row = 0; handle->search_row = 0; /* Success */ return 0; } /* Make the named category in the current save frame or data block the current category */ int cbf_find_category (cbf_handle handle, const char *categoryname) { cbf_node *node; if (!handle) return CBF_ARGUMENT; /* Find the data block node */ if (cbf_find_parent (&node, handle->node, CBF_SAVEFRAME)) { cbf_failnez (cbf_find_parent (&node, handle->node, CBF_DATABLOCK)) } /* Find the category */ cbf_failnez (cbf_find_typed_child (&node, node, categoryname, CBF_CATEGORY)) handle->node = node; handle->row = 0; handle->search_row = 0; /* Success */ return 0; } /* Make the named column in the current category the current column */ int cbf_find_column (cbf_handle handle, const char *columnname) { cbf_node *node; if (!handle) return CBF_ARGUMENT; /* Find the category node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_CATEGORY)) /* Find the column */ cbf_failnez (cbf_find_child (&node, node, columnname)) handle->node = node; /* Success */ return 0; } /* Make the first row with matching value the current row */ int cbf_find_row (cbf_handle handle, const char *value) { cbf_failnez (cbf_rewind_row (handle)) return cbf_find_nextrow (handle, value); } /* Make the first row with matching value the current row creating it if necessary */ int cbf_require_row (cbf_handle handle, const char *value) { if (cbf_rewind_row (handle)) { cbf_failnez(cbf_new_row (handle)) return cbf_set_value (handle, value); } return cbf_require_nextrow (handle, value); } /* Make the next row with matching value the current row */ int cbf_find_nextrow (cbf_handle handle, const char *value) { cbf_node *node; unsigned int row, rows; const char *text; if (!handle) return CBF_ARGUMENT; /* Find the column node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_COLUMN)) /* Count the rows */ cbf_failnez (cbf_count_children (&rows, node)) for (row = handle->search_row; row < rows; row++) { /* Is the value ascii? */ if (cbf_is_binary (node, row)) continue; /* Get the value of the current row */ cbf_failnez (cbf_get_columnrow (&text, node, row)) /* Compare the values */ if (text && value) { if (strcmp (text + 1, value)) continue; } else if (text != value) continue; /* Found a match */ handle->row = row; handle->search_row = row + 1; return 0; } return CBF_NOTFOUND; } /* Make the next row with matching value the current row, creating the row if necessary */ int cbf_require_nextrow (cbf_handle handle, const char *value) { if (cbf_find_nextrow(handle, value)) { cbf_failnez( cbf_new_row(handle)) return cbf_set_value(handle, value); } return 0; } /* Count the data blocks */ int cbf_count_datablocks (cbf_handle handle, unsigned int *datablocks) { cbf_node *node; if (!handle) return CBF_ARGUMENT; /* Find the root node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_ROOT)) /* Count the data blocks */ return cbf_count_children (datablocks, node); } /* Count the save frames in the current data block */ int cbf_count_saveframes (cbf_handle handle, unsigned int *saveframes) { cbf_node *node; if (!handle) return CBF_ARGUMENT; /* Find the data block node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_DATABLOCK)) /* Count the save frames */ return cbf_count_typed_children (saveframes, node, CBF_SAVEFRAME); } /* Count the categories in the current save frame or data block */ int cbf_count_categories (cbf_handle handle, unsigned int *categories) { cbf_node *node; if (!handle) return CBF_ARGUMENT; /* Find the data block node */ if (cbf_find_parent (&node, handle->node, CBF_SAVEFRAME)) { cbf_failnez (cbf_find_parent (&node, handle->node, CBF_DATABLOCK)) } /* Count the categories */ return cbf_count_typed_children (categories, node, CBF_CATEGORY); } /* Count the items in the current data block */ int cbf_count_blockitems (cbf_handle handle, unsigned int *blockitems) { cbf_node *node; if (!handle) return CBF_ARGUMENT; /* Find the data block node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_DATABLOCK)) /* Count the categories */ return cbf_count_children (blockitems, node); } /* Count the columns in the current category */ int cbf_count_columns (cbf_handle handle, unsigned int *columns) { cbf_node *node; if (!handle) return CBF_ARGUMENT; /* Find the category node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_CATEGORY)) /* Count the columns */ return cbf_count_children (columns, node); } /* Count the rows in the current category */ int cbf_count_rows (cbf_handle handle, unsigned int *rows) { cbf_node *node, *parent; unsigned int columns, column, columnrows, categoryrows; if (!handle) return CBF_ARGUMENT; /* Find the category node */ cbf_failnez (cbf_find_parent (&parent, handle->node, CBF_CATEGORY)) /* Count the columns */ cbf_failnez (cbf_count_children (&columns, parent)) /* Get the size of each column */ categoryrows = 0; for (column = 0; column < columns; column++) { /* Get the column */ cbf_failnez (cbf_get_child (&node, parent, column)) /* Count the number of rows */ cbf_failnez (cbf_count_children (&columnrows, node)) /* Is it the same size as the other columns? */ if (column == 0) categoryrows = columnrows; else if (categoryrows != columnrows) return CBF_FORMAT; } if (rows) *rows = categoryrows; /* Success */ return 0; } /* Get the name of the current data block */ int cbf_datablock_name (cbf_handle handle, const char **datablockname) { cbf_node *node; if (!handle) return CBF_ARGUMENT; /* Find the data block node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_DATABLOCK)) /* Get the name */ return cbf_get_name (datablockname, node); } /* Get the name of the current save frame */ int cbf_saveframe_name (cbf_handle handle, const char **saveframename) { cbf_node *node; if (!handle) return CBF_ARGUMENT; /* Find the data block node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_SAVEFRAME)) /* Get the name */ return cbf_get_name (saveframename, node); } /* Get the name of the current category */ int cbf_category_name (cbf_handle handle, const char **categoryname) { cbf_node *node; if (!handle) return CBF_ARGUMENT; /* Find the category node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_CATEGORY)) /* Get the name */ return cbf_get_name (categoryname, node); } /* Get the name of the current column */ int cbf_column_name (cbf_handle handle, const char **columnname) { cbf_node *node; if (!handle) return CBF_ARGUMENT; /* Find the column node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_COLUMN)) /* Get the name */ return cbf_get_name (columnname, node); } /* Change the name of the current column */ int cbf_set_column_name (cbf_handle handle, const char *columnname) { cbf_node *node; int errorcode; if (!handle) return CBF_ARGUMENT; /* Find the column node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_COLUMN)) /* Copy the name */ if (columnname) { columnname = cbf_copy_string (NULL, columnname, 0); if (!columnname) return CBF_ALLOC; } /* Change the name */ errorcode = cbf_name_node (node, columnname); if (errorcode) { cbf_free_string (NULL, columnname); return errorcode; } /* Success */ handle->node = node; return 0; } /* Get the number of the current row */ int cbf_row_number (cbf_handle handle, unsigned int *row) { if (!handle) return CBF_ARGUMENT; if (row) *row = handle->row; /* Success */ return 0; } /* Get the number of the current column */ int cbf_column_number (cbf_handle handle, unsigned int *column) { cbf_node *parent, *node; if (!handle) return CBF_ARGUMENT; /* Find the column node */ cbf_failnez (cbf_find_parent (&node, handle->node, CBF_COLUMN)) /* Find the category node */ cbf_failnez (cbf_find_parent (&parent, node, CBF_CATEGORY)) /* Which child is this? */ cbf_failnez (cbf_child_index (column, node)) /* Success */ return 0; } /* Get the number of the current block item */ int cbf_blockitem_number (cbf_handle handle, unsigned int *blockitem) { cbf_node *parent, *node; if (!handle) return CBF_ARGUMENT; /* Discover if we are in a save frame or just in a data block */ if (cbf_find_parent (&node, handle->node, CBF_SAVEFRAME)) { /* There is no save frame look for a category */ cbf_failnez(cbf_find_parent (&node, handle->node, CBF_CATEGORY)) } /* Find the root node */ cbf_failnez (cbf_find_parent (&parent, node, CBF_DATABLOCK)) /* Which child is this? */ cbf_failnez (cbf_child_index (blockitem, node)) /* Success */ return 0; } /* Get the ascii value of the current (row, column) entry */ int cbf_get_value (cbf_handle handle, const char **value) { const char *text; /* Check the arguments */ if (!handle) return CBF_ARGUMENT; /* Is the value binary? */ if (cbf_is_binary (handle->node, handle->row)) return CBF_BINARY; /* Get the value */ cbf_failnez (cbf_get_columnrow (&text, handle->node, handle->row)) if (value) { if (text) { *value = text + 1; } else { *value = NULL; } } /* Success */ return 0; } /* Set the ascii value of the current (row, column) entry */ int cbf_set_value (cbf_handle handle, const char *value) { int errorcode; /* Check the arguments */ if (!handle) return CBF_ARGUMENT; /* Copy the string */ if (value) { value = cbf_copy_string (NULL, value, '\200'); if (!value) return CBF_ALLOC; } /* Set the new value */ errorcode = cbf_set_columnrow (handle->node, handle->row, value, 1); if (errorcode) { cbf_free_string (NULL, value); return errorcode; } /* Success */ return 0; } /* Get the ascii value of the current (row, column) entry, setting it to a default value if necessary */ int cbf_require_value (cbf_handle handle, const char **value, const char *defaultvalue) { if (cbf_get_value (handle, value) || !*value) { cbf_failnez (cbf_set_value(handle, defaultvalue)) return (cbf_get_value(handle, value)); } return 0; } /* Set the ascii type value of the current (row, column) entry */ int cbf_set_typeofvalue (cbf_handle handle, const char *typeofvalue) { char *text; /* Check the arguments */ if (!handle) return CBF_ARGUMENT; /* Is the value binary? */ if (cbf_is_binary (handle->node, handle->row)) return CBF_BINARY; /* Get the value */ cbf_failnez (cbf_get_columnrow ((const char **)(&text), handle->node, handle->row)) cbf_failnez (cbf_set_value_type(handle, text, typeofvalue)) /* Success */ return 0; } /* Get the ascii type of value of the current (row, column) entry */ int cbf_get_typeofvalue (cbf_handle handle, const char **typeofvalue) { const char *text; /* Check the arguments */ if (!handle) return CBF_ARGUMENT; /* Is the value binary? */ if (cbf_is_binary (handle->node, handle->row)) { *typeofvalue = "bnry"; return 0; } /* Get the value */ cbf_failnez (cbf_get_columnrow (&text, handle->node, handle->row)) if (typeofvalue) { if (text) { cbf_failnez (cbf_get_value_type(text, typeofvalue)) } else { *typeofvalue = NULL; } } /* Success */ return 0; } /* Get the (int) numeric value of the current (row, column) entry */ int cbf_get_integervalue (cbf_handle handle, int *number) { const char *value; /* Get the value */ cbf_failnez (cbf_get_value (handle, &value)) /* Convert it into an integer */ if (!value) return CBF_NOTFOUND; if (number) *number = atoi (value); /* Success */ return 0; } /* Get the (double) numeric value of the current (row, column) entry */ int cbf_get_doublevalue (cbf_handle handle, double *number) { const char *value; char buffer[80]; char *endptr; /* Get the value */ cbf_failnez (cbf_get_value (handle, &value)) /* Convert it into a double */ if (!value) return CBF_NOTFOUND; if (number) { *number = strtod(value,&endptr); if (!*endptr) return 0; strncpy(buffer,value,79); buffer[79] = '\0'; if (*endptr == '.') *(buffer+(endptr-value)) = ','; if (!cbf_cistrncmp(buffer,",",80) || !cbf_cistrncmp(buffer,"?",80)) { *number = 0; return 0; } *number = strtod(buffer,&endptr); if (!*endptr || *endptr==' ') return 0; return CBF_FORMAT; } /* Success */ return 0; } /* Set the ascii value of the current (row, column) entry from an int */ int cbf_set_integervalue (cbf_handle handle, int number) { char value [64]; /* Write the value */ sprintf (value, "%d", number); /* Save it */ return cbf_set_value (handle, value); } /* Set the ascii value of the current (row, column) entry from a double */ int cbf_set_doublevalue (cbf_handle handle, const char *format, double number) { char value [64]; int lopos, hipos, ic; /* Write the value */ sprintf (value, format, number); /* strip the leading and trailing blanks */ for (lopos=0; (value[lopos]==' '||value[lopos]=='\t'); lopos++); for (hipos=strlen(value+lopos); hipos>0&&(value[lopos+hipos-1]==' '||value[lopos+hipos-1]=='\t'); hipos--); *(value+lopos+hipos) = '\0'; /* undo locale conversions of '.' to ',' */ for (ic = 0; ic < strlen(value+lopos); ic++) if (value[lopos+ic] == ',') value[lopos+ic] = '.'; /* Save it */ return cbf_set_value (handle, value+lopos); } /* Get the integer value of the current (row, column) entry, setting it to a default value if necessary */ int cbf_require_integervalue (cbf_handle handle, int *number, int defaultvalue) { if (cbf_get_integervalue (handle, number)) { cbf_failnez (cbf_set_integervalue(handle, defaultvalue)) return (cbf_get_integervalue(handle, number)); } return 0; } /* Get the integer value of the current (row, column) entry, setting it to a default value if necessary */ int cbf_require_doublevalue (cbf_handle handle, double *number, double defaultvalue) { if (cbf_get_doublevalue (handle, number)) { cbf_failnez (cbf_set_doublevalue(handle, "%-.15g", defaultvalue)) return (cbf_get_doublevalue(handle, number)); } return 0; } /* Get the parameters of the current (row, column) array entry */ int cbf_get_arrayparameters (cbf_handle handle, unsigned int *compression, int *id, size_t *elsize, int *elsigned, int *elunsigned, size_t *nelem, int *minelem, int *maxelem, int *realarray) { /* Check the arguments */ if (!handle) return CBF_ARGUMENT; /* Is the value binary? */ if (!cbf_is_binary (handle->node, handle->row)) return CBF_ASCII; /* Get the parameters */ return cbf_binary_parameters (handle->node, handle->row, compression, id, NULL, elsize, elsigned, elunsigned, nelem, minelem, maxelem, realarray, NULL, NULL, NULL, NULL, NULL); } /* Get the parameters of the current (row, column) array entry */ int cbf_get_arrayparameters_wdims (cbf_handle handle, unsigned int *compression, int *id, size_t *elsize, int *elsigned, int *elunsigned, size_t *nelem, int *minelem, int *maxelem, int *realarray, const char **byteorder, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding) { /* Check the arguments */ if (!handle) return CBF_ARGUMENT; /* Is the value binary? */ if (!cbf_is_binary (handle->node, handle->row)) return CBF_ASCII; /* Get the parameters */ return cbf_binary_parameters (handle->node, handle->row, compression, id, NULL, elsize, elsigned, elunsigned, nelem, minelem, maxelem, realarray, byteorder, dimfast, dimmid, dimslow, padding); } /* Get the dimensions of the current (row, column) array entry from the CBF tags */ int cbf_get_arraydimensions(cbf_handle handle, size_t * dimover, size_t * dimfast, size_t * dimmid, size_t * dimslow) { cbf_node *column; unsigned int row; cbf_node *category; cbf_node *asl_category; cbf_node *asl_array_id_col; cbf_node *asl_precedence_col; cbf_node *asl_dimension_col; cbf_node *datablock; cbf_node *array_id_column; const char * array_id; const char * asl_array_id; const char * asl_dimension; const char * asl_precedence; long precedence; unsigned int asl_row, asl_rows; size_t asl_dims[3]; asl_dims[0] = asl_dims[1] = asl_dims[2] = 0; /* Check the arguments */ if (!handle) return CBF_ARGUMENT; /* Is the value binary? */ if (!cbf_is_binary (handle->node, handle->row)) return CBF_ASCII; column = handle->node; row = handle->row; /* Follow any links */ column = cbf_get_link (column); /* Check the arguments */ if (!column) return CBF_ARGUMENT; /* Check the node type */ if (column->type != CBF_COLUMN) return CBF_ARGUMENT; if (!column) return CBF_ARGUMENT; /* Check the node type */ if (column->type != CBF_COLUMN) return CBF_ARGUMENT; /* Find the parent category */ cbf_failnez(cbf_find_parent(&category,column,CBF_CATEGORY)) if (!(category->name) || cbf_cistrncmp(category->name,"array_data",11) ) return CBF_ARGUMENT; /* Find the array id */ cbf_failnez (cbf_find_child (&array_id_column, category, "array_id")) if (cbf_is_binary(array_id_column,row)) return CBF_FORMAT; cbf_failnez(cbf_get_columnrow(&array_id, array_id_column,row )) if (!array_id) return CBF_FORMAT; array_id++; /* Find the parent save frame or data block node */ if (cbf_find_parent (&datablock, category, CBF_SAVEFRAME)) { cbf_failnez (cbf_find_parent (&datablock, category, CBF_DATABLOCK)) } /* Find the array_structure_list category and extract the dimensions with their precedence for the given array_id */ cbf_failnez(cbf_find_typed_child (&asl_category, datablock, "array_structure_list", CBF_CATEGORY)) cbf_failnez(cbf_find_typed_child (&asl_array_id_col, asl_category, "array_id", CBF_COLUMN)) cbf_failnez(cbf_find_typed_child (&asl_precedence_col, asl_category, "precedence", CBF_COLUMN)) cbf_failnez(cbf_find_typed_child (&asl_dimension_col, asl_category, "dimension", CBF_COLUMN)) cbf_failnez (cbf_count_children (&asl_rows, asl_array_id_col)) for (asl_row = 0; asl_row < asl_rows; asl_row++) { /* Is the value ascii? */ if (cbf_is_binary (asl_array_id_col, asl_row) || cbf_is_binary (asl_precedence_col, asl_row) || cbf_is_binary (asl_dimension_col, asl_row)) continue; /* Get the value of the current row */ cbf_failnez (cbf_get_columnrow (&asl_array_id, asl_array_id_col, asl_row)) /* Compare the values If the array_id matches, then store the dimension according to the precedence */ if (asl_array_id && !strcmp(asl_array_id+1,array_id)) { cbf_failnez(cbf_get_columnrow (&asl_precedence, asl_precedence_col, asl_row)) cbf_failnez(cbf_get_columnrow (&asl_dimension, asl_dimension_col, asl_row)) if (asl_precedence && asl_dimension) { precedence = atol(asl_precedence+1); if (precedence > 0 && precedence < 4) asl_dims[precedence-1] = atol(asl_dimension+1); } } } if (dimover) *dimover = 1; for (precedence = 0; precedence < 3; precedence++) { if (asl_dims[precedence] > 0) { if (dimover) *dimover *= asl_dims[precedence]; switch (precedence) { case 0: if (dimfast) *dimfast = asl_dims[precedence]; break; case 1: if (dimmid) *dimmid = asl_dims[precedence]; break; case 2: if (dimslow) *dimslow = asl_dims[precedence]; break; } } } return 0; } /* Get the parameters of the current (row, column) integer array entry */ int cbf_get_integerarrayparameters (cbf_handle handle, unsigned int *compression, int *id, size_t *elsize, int *elsigned, int *elunsigned, size_t *nelem, int *minelem, int *maxelem) { int realarray; /* Check the arguments */ if (!handle) return CBF_ARGUMENT; /* Is the value binary? */ if (!cbf_is_binary (handle->node, handle->row)) return CBF_ASCII; /* Get the parameters */ return cbf_binary_parameters (handle->node, handle->row, compression, id, NULL, elsize, elsigned, elunsigned, nelem, minelem, maxelem, &realarray, NULL, NULL, NULL, NULL, NULL); } /* Get the parameters of the current (row, column) integer array entry */ int cbf_get_integerarrayparameters_wdims (cbf_handle handle, unsigned int *compression, int *id, size_t *elsize, int *elsigned, int *elunsigned, size_t *nelem, int *minelem, int *maxelem, const char **byteorder, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding) { int realarray; /* Check the arguments */ if (!handle) return CBF_ARGUMENT; /* Is the value binary? */ if (!cbf_is_binary (handle->node, handle->row)) return CBF_ASCII; /* Get the parameters */ return cbf_binary_parameters (handle->node, handle->row, compression, id, NULL, elsize, elsigned, elunsigned, nelem, minelem, maxelem, &realarray, byteorder,dimfast,dimmid,dimslow,padding); } /* Get the parameters of the current (row, column) array entry */ int cbf_get_realarrayparameters (cbf_handle handle, unsigned int *compression, int *id, size_t *elsize, size_t *nelem) { /* Check the arguments */ if (!handle) return CBF_ARGUMENT; /* Is the value binary? */ if (!cbf_is_binary (handle->node, handle->row)) return CBF_ASCII; /* Get the parameters */ return cbf_binary_parameters (handle->node, handle->row, compression, id, NULL, elsize, NULL, NULL, nelem, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL); } /* Get the parameters of the current (row, column) array entry */ int cbf_get_realarrayparameters_wdims (cbf_handle handle, unsigned int *compression, int *id, size_t *elsize, size_t *nelem, const char **byteorder, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding) { /* Check the arguments */ if (!handle) return CBF_ARGUMENT; /* Is the value binary? */ if (!cbf_is_binary (handle->node, handle->row)) return CBF_ASCII; /* Get the parameters */ return cbf_binary_parameters (handle->node, handle->row, compression, id, NULL, elsize, NULL, NULL, nelem, NULL, NULL, NULL, byteorder,dimfast,dimmid,dimslow,padding); } /* Get the integer value of the current (row, column) array entry */ int cbf_get_integerarray (cbf_handle handle, int *id, void *value, size_t elsize, int elsign, size_t nelem, size_t *nelem_read) { int realarray; const char *byteorder; size_t dimover, dimfast, dimmid, dimslow, padding; if (!handle) return CBF_ARGUMENT; return cbf_get_binary (handle->node, handle->row, id, value, elsize, elsign, nelem, nelem_read, &realarray, &byteorder,&dimover, &dimfast, &dimmid, &dimslow, &padding); } /* Get the real value of the current (row, column) array entry */ int cbf_get_realarray (cbf_handle handle, int *id, void *value, size_t elsize, size_t nelem, size_t *nelem_read) { int realarray; const char *byteorder; size_t dimover, dimfast, dimmid, dimslow, padding; if (!handle) return CBF_ARGUMENT; return cbf_get_binary (handle->node, handle->row, id, value, elsize, 1, nelem, nelem_read, &realarray, &byteorder, &dimover, &dimfast, &dimmid, &dimslow, &padding); } /* Set the integer value of the current (row, column) array entry */ int cbf_set_integerarray (cbf_handle handle, unsigned int compression, int id, void *value, size_t elsize, int elsign, size_t nelem) { if (!handle) return CBF_ARGUMENT; return cbf_set_binary (handle->node, handle->row, compression, id, value, elsize, elsign, nelem, 0, "little_endian", nelem, 0, 0, 0, 0); } /* Set the integer value of the current (row, column) array entry */ int cbf_set_integerarray_wdims (cbf_handle handle, unsigned int compression, int id, void *value, size_t elsize, int elsign, size_t nelem, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding) { if (!handle) return CBF_ARGUMENT; return cbf_set_binary (handle->node, handle->row, compression, id, value, elsize, elsign, nelem, 0, byteorder, nelem, dimfast, dimmid, dimslow, padding); } /* Set the real value of the current (row, column) array entry */ int cbf_set_realarray (cbf_handle handle, unsigned int compression, int id, void *value, size_t elsize, size_t nelem) { if (!handle) return CBF_ARGUMENT; return cbf_set_binary (handle->node, handle->row, compression, id, value, elsize, 1, nelem, 1, "little_endian", nelem, 0, 0, 0, 0); } /* Set the real value of the current (row, column) array entry with dimensions */ int cbf_set_realarray_wdims (cbf_handle handle, unsigned int compression, int id, void *value, size_t elsize, size_t nelem, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding) { if (!handle) return CBF_ARGUMENT; return cbf_set_binary (handle->node, handle->row, compression, id, value, elsize, 1, nelem, 1, byteorder, nelem, dimfast, dimmid, dimslow, padding); } /* Issue a warning message */ void cbf_warning (const char *message) { fprintf (stderr, " CBFlib: warning -- %s\n", message); } /* Issue an error message */ void cbf_error (const char *message) { fprintf (stderr, " CBFlib: error -- %s\n", message); } /* Issue a log message for a cbf */ void cbf_log (cbf_handle handle, const char *message, int logflags) { char * buffer; void * memblock; int line=0, column=0; if (cbf_alloc(&memblock, NULL, 1, strlen(message)+80) ) { if (handle->logfile) { fprintf (handle->logfile, "CBFlib: memory allocation error\n"); } else { exit(CBF_ALLOC); } return; } buffer = (char *)memblock; if (logflags & CBF_LOGCURRENTLOC) { line = (handle->file->line); column = (handle->file->column); logflags &= (~CBF_LOGWOLINE); } else if (logflags & CBF_LOGSTARTLOC) { line = (handle->startline); column = (handle->startcolumn); logflags &= (~CBF_LOGWOLINE); } else { logflags |= CBF_LOGWOLINE; } if (logflags&CBF_LOGERROR) handle->errors++; else if (logflags&CBF_LOGWARNING) handle->warnings++; if ( !handle->logfile ) return; if ( handle->file) { if (logflags&CBF_LOGWOLINE) sprintf (buffer, "CBFlib: %s -- %s\n", (logflags&CBF_LOGERROR)?"error": ((logflags&CBF_LOGWARNING)?("warning"):""), message); else if (logflags&CBF_LOGWOCOLUMN || column==0) sprintf (buffer, "CBFlib: %s input line %d -- %s\n", (logflags&CBF_LOGERROR)?"error": ((logflags&CBF_LOGWARNING)?("warning"):""), line+1, message); else sprintf (buffer, "CBFlib: %s input line %d (%d) -- %s\n", (logflags&CBF_LOGERROR)?"error": ((logflags&CBF_LOGWARNING)?("warning"):""), line+1, column, message); } else { sprintf (buffer, "CBFlib: %s -- %s\n", (logflags&CBF_LOGERROR)?"error": ((logflags&CBF_LOGWARNING)?("warning"):""), message); } fprintf (handle->logfile, "%s", buffer); cbf_free(&memblock, NULL ); return; } /* Issue a log message for a cbf_file */ void cbf_flog (cbf_file *file, const char *message, int logflags) { char * buffer; void * memblock; int line=0, column=0; if (cbf_alloc(&memblock, NULL, 1, strlen(message)+80) ) { if (file->logfile) { fprintf (file->logfile, "CBFlib: memory allocation error\n"); } else { exit(CBF_ALLOC); } return; } buffer = (char *)memblock; if (logflags & CBF_LOGCURRENTLOC) { line = (file->line); column = (file->column); logflags &= (~CBF_LOGWOLINE); } else { logflags |= CBF_LOGWOLINE; } if (logflags&CBF_LOGERROR) file->errors++; else if (logflags&CBF_LOGWARNING) file->warnings++; if ( !file->logfile ) return; if (logflags&CBF_LOGWOLINE) sprintf (buffer, "CBFlib: %s -- %s\n", (logflags&CBF_LOGERROR)?"error": ((logflags&CBF_LOGWARNING)?("warning"):""), message); else if (logflags&CBF_LOGWOCOLUMN || column==0) sprintf (buffer, "CBFlib: %s input line %d -- %s\n", (logflags&CBF_LOGERROR)?"error": ((logflags&CBF_LOGWARNING)?("warning"):""), line+1, message); else sprintf (buffer, "CBFlib: %s input line %d (%d) -- %s\n", (logflags&CBF_LOGERROR)?"error": ((logflags&CBF_LOGWARNING)?("warning"):""), line+1, column, message); fprintf (file->logfile, "%s", buffer); cbf_free(&memblock, NULL ); return; } /* Find a datablock, creating it if necessary */ int cbf_require_datablock (cbf_handle handle, const char *datablockname) { if (cbf_find_datablock(handle, datablockname)) { cbf_failnez(cbf_new_datablock(handle, datablockname)) } return 0; } /* Find a category, creating it if necessary */ int cbf_require_category (cbf_handle handle, const char *categoryname) { if (cbf_find_category(handle, categoryname)) { const char * datablockname; if (cbf_datablock_name(handle, &datablockname)) cbf_failnez(cbf_require_datablock(handle,"(null)")) cbf_failnez(cbf_new_category(handle, categoryname)) } return 0; } /* Find a column, creating it if necessary */ int cbf_require_column (cbf_handle handle, const char *columnname) { unsigned int currow, rows; if (cbf_row_number(handle,&currow)) currow = 0; if (cbf_count_rows(handle,&rows)) rows = 0; if (cbf_find_column(handle, columnname)) { cbf_failnez(cbf_count_rows(handle, &rows)) cbf_failnez(cbf_new_column(handle, columnname)) if (currow < rows) cbf_failnez(cbf_select_row(handle, currow)) } return 0; } /* Find a column value, return a default if necessary */ int cbf_require_column_value (cbf_handle handle, const char *columnname, const char **value, const char *defaultvalue) { if (!cbf_require_column(handle, columnname) && !cbf_get_value(handle, value)) { return 0; } else { cbf_failnez (cbf_set_value(handle, defaultvalue)) return cbf_get_value(handle, value); } } /* Find a column integer value, return a default if necessary */ int cbf_require_column_integervalue (cbf_handle handle, const char *columnname, int *number, const int defaultvalue) { if (!cbf_require_column(handle, columnname) && !cbf_get_integervalue(handle, number)) { return 0; } else { cbf_failnez (cbf_set_integervalue(handle, defaultvalue)) return cbf_get_integervalue(handle, number); } } /* Find a column double value, return a default if necessary */ int cbf_require_column_doublevalue (cbf_handle handle, const char *columnname, double *number, const double defaultvalue) { if (!cbf_require_column(handle, columnname) && !cbf_get_doublevalue(handle, number)) { return 0; } else { cbf_failnez (cbf_set_doublevalue(handle, "%.15g", defaultvalue)) return cbf_get_doublevalue(handle, number); } } /* Get the local byte order of the default integer type */ int cbf_get_local_integer_byte_order (char ** byte_order) { static char le[14] = "little_endian"; static char be[11] = "big_endian"; int *test; int probe = 1; test = (int *)&probe; if (*(char*)test) *byte_order = le; else *byte_order = be; return 0; } /* Get the local byte order of the default real type */ int cbf_get_local_real_byte_order (char ** byte_order) { static char le[14] = "little_endian"; static char be[11] = "big_endian"; double *test; double probe = 1.; test = (double *)&probe; if (*(char*)test) *byte_order = be; else *byte_order = le; return 0; } /* Get the local real format */ int cbf_get_local_real_format (char ** real_format ) { static char ieee[14] = "ieee 754-1985"; static char other[6] = "other"; union ftest { float fltest; int itest; long ltest; } test; *real_format = other; test.fltest = 1.; if (sizeof (float) == sizeof (long) ) { if ( test.ltest == 1065353216L ) *real_format = ieee; } else { if (sizeof (float) == sizeof (int ) ) { if (test.itest == 1065353216 ) *real_format = ieee; } } return 0; } /* Get the dictionary for a cbf */ int cbf_get_dictionary (cbf_handle handle, cbf_handle * dictionary) { if (handle && (*dictionary = (cbf_handle)(handle->dictionary)) ) return 0; return CBF_NOTFOUND; } /* Set the dictionary for a cbf */ int cbf_set_dictionary (cbf_handle handle, cbf_handle dictionary) { if (!handle) return CBF_ARGUMENT; if (handle->dictionary) { cbf_failnez(cbf_free_handle((cbf_handle)(handle->dictionary))) } * ((cbf_handle *)(&handle->dictionary)) = dictionary; (dictionary->refcount)++; return 0; } /* Get the dictionary for a cbf, or create one */ int cbf_require_dictionary (cbf_handle handle, cbf_handle * dictionary) { if (!handle) return CBF_ARGUMENT; if (!cbf_get_dictionary(handle, dictionary)) return 0; cbf_failnez (cbf_make_handle((cbf_handle *)&(handle->dictionary))) *dictionary = (cbf_handle)(handle->dictionary); return 0; } /* Put the value into the named column, updating the hash table links If valuerow >= 0, the value is to be stored into the row of that number. If valuerow < 0, the value is to be stored into a newly created row. For a given category of name , the hash table is held in a category of name (hash_table), e.g. if the category is "atom", the hastable is "atom(hash_table)". For each column of name the hashtable links, as integer row numbers are held in columns of name (hash_index), e.g. if the column name is "label", the hash index column name is "label(hash_index)". The same column name is used in both the hash table category and the original category. */ int cbf_set_hashedvalue(cbf_handle handle, const char * value, const char * columnname, int valuerow) { char colhashnext[91]; char * category; const char * ovalue; int ohashnext; char categoryhashtable[91]; unsigned int hashcode, ohashcode; int orownum, rownum, nrownum=0, catrownum; int colnamelen, catnamelen; if ( !columnname ) return CBF_ARGUMENT; if ( (colnamelen = strlen(columnname)) > 80 ) return CBF_ARGUMENT; cbf_failnez(cbf_category_name (handle, (const char * *)&category)); if ( (catnamelen = strlen(category)) > 80 ) return CBF_ARGUMENT; strcpy (categoryhashtable,category); strcpy (categoryhashtable + catnamelen, "(hash_table)"); strcpy (colhashnext, columnname); strcpy (colhashnext+colnamelen, "(hash_next)"); cbf_failnez( cbf_compute_hashcode(value, &hashcode)) cbf_failnez( cbf_require_column(handle, columnname)) /* If we are going to hash an exisiting row, we need to undo any existing hash to the same row */ if (valuerow >= 0) { cbf_failnez( cbf_select_row (handle, valuerow)) if (!cbf_get_value(handle,&ovalue) && ovalue && !cbf_find_column(handle, colhashnext) && !cbf_get_integervalue(handle, &ohashnext)) { cbf_failnez( cbf_compute_hashcode(ovalue, &ohashcode)) if (hashcode != ohashcode) { cbf_failnez( cbf_require_category (handle, categoryhashtable)) cbf_failnez( cbf_require_column (handle, colhashnext)) cbf_failnez( cbf_select_row (handle, ohashcode)) if ( ! cbf_get_integervalue (handle, &rownum)) { if (rownum == valuerow) { cbf_failnez(cbf_set_integervalue(handle,ohashnext)) } else { cbf_failnez( cbf_find_category (handle, category)) cbf_failnez( cbf_find_column (handle, colhashnext)) while ( rownum >=0 && rownum != valuerow) { cbf_failnez( cbf_select_row (handle, rownum)) orownum = -1; if (cbf_get_integervalue (handle,&orownum) || orownum <= rownum) { break; } else { if (orownum == valuerow) { cbf_failnez(cbf_set_integervalue(handle,ohashnext)) break; } } rownum = orownum; } } } } } } if ( valuerow < 0 ) { cbf_failnez( cbf_new_row (handle)) } else { cbf_failnez( cbf_select_row (handle, valuerow)) } cbf_failnez( cbf_set_value (handle, value)) cbf_failnez( cbf_row_number (handle, (unsigned int *)&nrownum)) cbf_failnez( cbf_require_column (handle, (const char *) colhashnext)) cbf_failnez( cbf_set_integervalue (handle, -1)) cbf_failnez( cbf_require_category (handle, categoryhashtable)) cbf_failnez( cbf_require_column (handle, colhashnext)) cbf_failnez( cbf_count_rows (handle, (unsigned int *)&catrownum)) if (catrownum < hashcode+1) { for (rownum = catrownum; rownum < hashcode+1; rownum++) { cbf_failnez(cbf_new_row(handle)) } } cbf_failnez( cbf_find_column (handle, colhashnext)) cbf_failnez( cbf_select_row (handle, hashcode)) if ( cbf_get_integervalue (handle, &rownum) || rownum == -1) { cbf_failnez( cbf_set_integervalue (handle, nrownum)) cbf_failnez( cbf_find_category (handle, category)) cbf_failnez( cbf_find_column (handle, colhashnext)) cbf_failnez( cbf_select_row (handle, nrownum)) cbf_failnez( cbf_set_integervalue (handle, -1)) cbf_failnez( cbf_find_column (handle, columnname)) return 0; } /* nrownum is the row number of the value rownum is the row number of pointed to the by the hash table If the hash table points higher up, reset the hashtable to point to the new row. We will still have to relink the chain by having this row point to rownum If the hash table point higher up, the hash table remains as is, and the new link is inserted only in the main category */ if (nrownum < rownum) { cbf_failnez( cbf_set_integervalue(handle,nrownum)) } cbf_failnez( cbf_find_category (handle, category)) cbf_failnez( cbf_find_column (handle, colhashnext)) if (rownum >= nrownum) { cbf_failnez( cbf_select_row (handle, nrownum)) if (rownum > nrownum) { cbf_failnez( cbf_set_integervalue(handle, rownum)) } if (cbf_get_integervalue (handle, &orownum)) { cbf_failnez(cbf_set_integervalue (handle, -1)) } cbf_failnez( cbf_find_column (handle, columnname)) return 0; } while ( rownum >=0 ) { cbf_failnez( cbf_select_row (handle, rownum)) orownum = -1; if (cbf_get_integervalue (handle,&orownum) || orownum < 0 || orownum >= nrownum) { cbf_failnez( cbf_set_integervalue (handle, nrownum)) cbf_failnez( cbf_select_row (handle, nrownum)) if ( orownum < 0 || orownum > nrownum) { cbf_failnez( cbf_set_integervalue (handle, orownum)) } if (cbf_get_integervalue (handle, &orownum)) { cbf_failnez(cbf_set_integervalue (handle, -1)) } cbf_failnez( cbf_find_column (handle, columnname)) return 0; } rownum = orownum; } return CBF_NOTFOUND; } /* Find value in the named column, using the hash table links, if available*/ int cbf_find_hashedvalue(cbf_handle handle, const char * value, const char * columnname, int caseinsensitive) { char colhashnext[91]; char * category; char categoryhashtable[91]; char hashcodestring[81]; unsigned int hashcode; int rownum, catrownum; const char * rowvalue; int colnamelen, catnamelen; if (!columnname) return CBF_ARGUMENT; if ( (colnamelen = strlen(columnname)) > 80 ) return CBF_ARGUMENT; cbf_failnez(cbf_category_name (handle, (const char **)&category)); if ( (catnamelen = strlen(category)) > 80 ) return CBF_ARGUMENT; /* Compute the hashcode value (0-255) */ cbf_failnez (cbf_compute_hashcode(value, &hashcode)) sprintf (hashcodestring,"%d",hashcode); /* Save the category of the primary search */ strcpy (categoryhashtable,category); /* Compute the names (hash_table) (hash_next) */ strcpy (categoryhashtable + catnamelen, "(hash_table)"); strcpy (colhashnext, columnname); strcpy (colhashnext+colnamelen, "(hash_next)"); /* Switch the the hash table and make sure it has enough rows */ cbf_failnez( cbf_require_category (handle, categoryhashtable)) cbf_failnez( cbf_require_column (handle, colhashnext)) cbf_failnez( cbf_count_rows (handle, (unsigned int *)&catrownum)) if (catrownum < hashcode+1) { for (rownum = catrownum; rownum < hashcode+1; rownum++) { cbf_failnez( cbf_new_row(handle)) } } /* examine the row in the hash table given by the hash code to see if it points to a row */ if ( ! cbf_select_row(handle, hashcode) && !cbf_get_integervalue(handle, (int *) &rownum) && rownum >= 0 ) { /* If we have a start point, trace the chain until we find a match to the probe, or fail */ cbf_failnez( cbf_find_category (handle, category)) while ( rownum >=0 ) { cbf_failnez( cbf_find_column (handle, columnname)) cbf_failnez( cbf_select_row (handle, rownum)) if (caseinsensitive) { if ( !cbf_get_value(handle, &rowvalue) && !cbf_cistrcmp(rowvalue, value)) { return 0; } }else { if ( !cbf_get_value(handle, &rowvalue) && !strcmp(rowvalue, value)) { return 0; } } cbf_failnez( cbf_find_column (handle, colhashnext)) if (cbf_get_integervalue (handle,&rownum)) break; } } cbf_failnez( cbf_find_category (handle, category)) cbf_failnez( cbf_find_column (handle, columnname)) return CBF_NOTFOUND; } int cbf_convert_dictionary_definition(cbf_handle cbfdictionary, cbf_handle dictionary, const char * name) { const char *category_id; const char *mandatory_code; const char *itemname; const char *expression; const char *columnname; const char *categoryname, *ocategoryname; int colno; const char *type_code; const char *default_value; const char *parent_name; const char *child_name; const char *alias_name; const char *key, *oldkey; const char *value, *value2, *value_type; const char *keytype; char buffer[255]; cbf_node * base_node, * local_node; int rownum, numrows, numrow; int nextkeyrow; int haveitemname; int haveitemcategory; haveitemname = haveitemcategory = 0; /* Save the base data block or save frame to come back to */ base_node = dictionary->node; local_node = base_node; /* Find the name for this defintion */ if (!cbf_find_local_tag(dictionary,"_name") || !cbf_find_local_tag(dictionary,"_item.name") || !cbf_find_local_tag(dictionary,"_definition.id")) { haveitemname = 1; local_node = dictionary->node; cbf_failnez(cbf_column_name(dictionary, &columnname) ) } if (!haveitemname && (!cbf_find_category(dictionary,"item") || !cbf_find_category(dictionary,"name"))) haveitemcategory = 1; if (haveitemname || haveitemcategory) { cbf_failnez( cbf_count_rows (dictionary,(unsigned int *)&numrows)) cbf_failnez( cbf_rewind_row (dictionary)) for (numrow=0; numrow < numrows; numrow++) { cbf_failnez( cbf_require_category (cbfdictionary, "items")) if (haveitemname && !cbf_find_column(dictionary,columnname)) { cbf_failnez( cbf_select_row(dictionary, numrow) ) cbf_failnez( cbf_get_value(dictionary, &itemname)) } else { itemname = name; } if (cbf_find_hashedvalue(cbfdictionary, itemname, "name", CBF_CASE_INSENSITIVE)) { cbf_failnez( cbf_set_hashedvalue (cbfdictionary, itemname, "name", -1)) } cbf_failnez( cbf_row_number (cbfdictionary, (unsigned int*)&rownum)) if (!cbf_find_column(dictionary,"category_id") || !cbf_find_column(dictionary,"_category")){ cbf_failnez( cbf_select_row(dictionary, (unsigned int)numrow) ) if (!cbf_get_value(dictionary, &category_id)) { cbf_failnez( cbf_find_column(cbfdictionary, "category_id")); if (cbf_get_value(cbfdictionary, &categoryname) || !categoryname || !strcmp(categoryname," ")) cbf_failnez(cbf_set_hashedvalue(cbfdictionary, category_id, "category_id", rownum)) } } else { dictionary->node = base_node; if (!cbf_find_local_tag(dictionary,"_category") ||!cbf_find_local_tag(dictionary,"_item.category_id") ) { if (!cbf_get_value(dictionary, &category_id)) { cbf_failnez( cbf_find_column(cbfdictionary, "category_id")); if (cbf_get_value(cbfdictionary, &categoryname) || !categoryname || !strcmp(categoryname," ")) cbf_failnez(cbf_set_hashedvalue(cbfdictionary, category_id, "category_id", rownum)) } } } dictionary->node = local_node; if (!cbf_find_column(dictionary,"mandatory_code") ) { cbf_failnez( cbf_select_row(dictionary, numrow) ) if (!cbf_get_value(dictionary, &mandatory_code)) { cbf_failnez( cbf_find_column(cbfdictionary, "mandatory_code")); cbf_failnez( cbf_set_value(cbfdictionary, mandatory_code)) } } dictionary->node = base_node; if ( !cbf_find_local_tag(dictionary,"_type") || !cbf_find_local_tag(dictionary,"_item_type.code") || !cbf_find_local_tag(dictionary,"_type.contents") ) { if (!cbf_get_value(dictionary, &type_code)) { cbf_failnez( cbf_find_column(cbfdictionary, "type_code")); cbf_failnez( cbf_set_value(cbfdictionary, type_code)) } } dictionary->node = base_node; if (!cbf_find_local_tag(dictionary,"_enumeration_default") || !cbf_find_local_tag(dictionary,"_item_default.value") || !cbf_find_local_tag(dictionary,"_enumeration.default")) { if (!cbf_get_value(dictionary, &default_value)) { cbf_failnez( cbf_find_column(cbfdictionary, "default_value")); cbf_failnez( cbf_set_value(cbfdictionary, default_value)) } } dictionary->node = base_node; if (!cbf_find_local_tag(dictionary,"_method.expression")) { if (!cbf_get_value(dictionary, &expression)) { cbf_failnez( cbf_require_column(cbfdictionary, "method_expression")); cbf_failnez( cbf_set_value(cbfdictionary, expression)) } } dictionary->node = base_node; if ( !cbf_find_local_tag(dictionary,"_item_aliases.alias_name") ) { if (!cbf_get_value(dictionary, &alias_name)) { cbf_failnez(cbf_find_category(cbfdictionary, "item_aliases")) if (cbf_find_hashedvalue(cbfdictionary, alias_name, "item_alias", CBF_CASE_INSENSITIVE)) { cbf_failnez( cbf_set_hashedvalue (cbfdictionary, alias_name, "item_alias", -1)) } cbf_failnez( cbf_row_number (cbfdictionary, (unsigned int *)&rownum)) cbf_failnez( cbf_set_hashedvalue (cbfdictionary, itemname, "item_root", rownum)) } } } } /* extract enumerations */ dictionary->node = base_node; value_type = "value"; if (!cbf_find_local_tag(dictionary, "_item_enumeration.value") || !cbf_find_local_tag(dictionary, "_enumeration")) { cbf_failnez( cbf_column_number(dictionary, (unsigned int *)&colno)) cbf_failnez( cbf_count_rows (dictionary, (unsigned int *)&numrows)) cbf_failnez( cbf_rewind_row (dictionary)) cbf_failnez( cbf_require_category (cbfdictionary, "items_enumerations")) for (numrow=0; numrow < numrows; numrow++) { cbf_failnez( cbf_select_row(dictionary, numrow)) cbf_failnez( cbf_select_column(dictionary, colno)) cbf_failnez( cbf_get_value (dictionary, &value)) if (!haveitemname) { cbf_failnez (cbf_find_column(dictionary,"name")) cbf_failnez (cbf_get_value(dictionary,&itemname)) } cbf_failnez( cbf_set_hashedvalue (cbfdictionary, itemname, "name", -1)) cbf_failnez( cbf_require_column (cbfdictionary, "value")) cbf_failnez( cbf_set_value (cbfdictionary, value)) cbf_failnez( cbf_require_column (cbfdictionary, "value_type") ) cbf_failnez( cbf_set_value (cbfdictionary, value_type)) } } dictionary->node = base_node; if (!cbf_find_local_tag(dictionary, "_item_range.minimum") || !cbf_find_local_tag(dictionary, "_enumeration_range") || !cbf_find_local_tag(dictionary, "_enumeration.range")) { cbf_failnez( cbf_column_number(dictionary, (unsigned int *)&colno)) cbf_failnez( cbf_count_rows (dictionary, (unsigned int *)&numrows)) cbf_failnez( cbf_rewind_row (dictionary)) cbf_failnez( cbf_require_category (cbfdictionary, "items_enumerations")) for (numrow=0; numrow < numrows; numrow++) { cbf_failnez( cbf_select_row(dictionary, numrow) ) cbf_failnez( cbf_select_column(dictionary, colno)) cbf_failnez( cbf_get_value (dictionary, &value)) if (!haveitemname) { cbf_failnez (cbf_find_column(dictionary,"name")) cbf_failnez (cbf_get_value(dictionary,&itemname)) } value_type = "closed_range"; if (!cbf_find_column(dictionary, "maximum")) { cbf_failnez( cbf_get_value (dictionary, &value2)) if (value && value2 && strlen(value)+strlen(value2) < 255) { if (strcmp(value,value2)) value_type = "open_range"; strcpy(buffer,value); buffer[strlen(value)]=':'; strcpy(buffer+strlen(value)+1,value2); value = buffer; } else { value = "invalid"; sprintf(buffer,"dictionary: invalid range of values for %s",itemname); cbf_log(dictionary,buffer,CBF_LOGWARNING|CBF_LOGSTARTLOC); } } cbf_failnez( cbf_set_hashedvalue (cbfdictionary, itemname, "name", -1)) cbf_failnez( cbf_require_column (cbfdictionary, "value")) cbf_failnez( cbf_set_value (cbfdictionary, value)) cbf_failnez( cbf_require_column (cbfdictionary, "value_type") ) cbf_failnez( cbf_set_value (cbfdictionary, value_type)) } } dictionary->node = base_node; if (!cbf_find_local_tag(dictionary, "_item_linked.parent_name") || !cbf_find_local_tag(dictionary, "_item_link_parent") || !cbf_find_local_tag(dictionary, "_category.parent_id")) { cbf_failnez( cbf_count_rows (dictionary,(unsigned int *)&numrows)) cbf_failnez( cbf_rewind_row (dictionary)) for (numrow=0; numrow < numrows; numrow++) { cbf_failnez( cbf_require_category (cbfdictionary, "items")) cbf_failnez( cbf_select_row(dictionary, numrow) ) parent_name = NULL; if (!cbf_find_column(dictionary,"parent_name") || !cbf_find_column(dictionary,"_list_link_parent") || !cbf_find_column(dictionary,"parent_id") ) if (cbf_get_value(dictionary,&parent_name)) parent_name = NULL; child_name = NULL; if (!cbf_find_column(dictionary,"child_name") || !cbf_find_column(dictionary,"_list_link_child") ) if (cbf_get_value(dictionary,&child_name)) child_name = NULL; if ((numrows==1) && (child_name == NULL)) { child_name = itemname; } if (parent_name && child_name) { if (cbf_find_hashedvalue(cbfdictionary, child_name, "name", CBF_CASE_INSENSITIVE)) { cbf_failnez( cbf_set_hashedvalue (cbfdictionary, child_name, "name", -1)) } cbf_failnez(cbf_find_column(cbfdictionary, "parent")) cbf_failnez(cbf_set_value(cbfdictionary,parent_name)) } } } dictionary->node = base_node; if (!cbf_find_local_tag(dictionary,"_category") || !cbf_find_local_tag(dictionary,"_category.id") ) { cbf_failnez( cbf_count_rows (dictionary,(unsigned int *)&numrows)) cbf_failnez( cbf_rewind_row (dictionary)) local_node = dictionary->node; for (numrow=0; numrow < numrows; numrow++) { cbf_failnez( cbf_require_category (cbfdictionary, "categories")) dictionary->node = local_node; cbf_failnez( cbf_select_row(dictionary, numrow) ) cbf_failnez( cbf_get_value (dictionary, &categoryname)) if (cbf_find_hashedvalue(cbfdictionary, categoryname, "id", CBF_CASE_INSENSITIVE)) { cbf_failnez( cbf_set_hashedvalue (cbfdictionary, categoryname, "id", -1)) } key = NULL; mandatory_code = "no"; if (!cbf_find_column(dictionary,"mandatory_code") && !cbf_get_value(dictionary,&mandatory_code)) { cbf_failnez(cbf_require_column(cbfdictionary,"mandatory_code")) cbf_failnez(cbf_set_value(cbfdictionary,mandatory_code)) } dictionary->node = base_node; if (!cbf_find_local_tag(dictionary,"_list_reference") || !cbf_find_local_tag(dictionary,"_category_key.name") || !cbf_find_local_tag(dictionary,"_category_key.primitive") || !cbf_find_local_tag(dictionary,"_category_key.generic")) { if (!cbf_get_value(dictionary, &key) && key) { cbf_failnez( cbf_get_typeofvalue(dictionary,&keytype)) cbf_failnez( cbf_require_column(cbfdictionary, "key")) while (cbf_get_value(cbfdictionary, &oldkey) || !oldkey || strcmp(oldkey," ")) { if (key && oldkey && !strcmp(oldkey,key)) break; cbf_failnez( cbf_find_column (cbfdictionary, "id(hash_next)")) cbf_failnez( cbf_get_integervalue (cbfdictionary, &nextkeyrow)) cbf_failnez( cbf_find_column(cbfdictionary, "key")) if (nextkeyrow < 0) { cbf_failnez( cbf_set_hashedvalue (cbfdictionary, categoryname, "id", -1)) cbf_failnez( cbf_find_column (cbfdictionary, "key")) break; } cbf_failnez( cbf_select_row (cbfdictionary, (unsigned int)nextkeyrow)) } cbf_failnez(cbf_set_value(cbfdictionary,key)) if ( keytype != NULL ) { cbf_failnez(cbf_set_typeofvalue(cbfdictionary,keytype)) } cbf_failnez(cbf_require_column(cbfdictionary,"mandatory_code")) cbf_failnez(cbf_set_value(cbfdictionary,mandatory_code)) } } cbf_failnez( cbf_require_category (cbfdictionary, "items")) cbf_failnez (cbf_require_column(cbfdictionary,"name")) if (key) { if (cbf_find_hashedvalue(cbfdictionary,key,"name",CBF_CASE_INSENSITIVE)) { cbf_failnez(cbf_set_hashedvalue(cbfdictionary,key,"name", -1)) cbf_failnez(cbf_require_column(cbfdictionary,"mandatory_code")) cbf_failnez(cbf_set_value(cbfdictionary,"yes")) } else { cbf_failnez(cbf_require_column(cbfdictionary,"mandatory_code")) if (cbf_get_value(cbfdictionary,&mandatory_code) || !mandatory_code) { cbf_failnez(cbf_set_value(cbfdictionary,"yes")) } } cbf_failnez(cbf_row_number(cbfdictionary, (unsigned int *)&rownum)) cbf_failnez(cbf_require_column(cbfdictionary,"category_id")) if (cbf_get_value(cbfdictionary, &ocategoryname) || !ocategoryname || !strcmp(ocategoryname," ")) cbf_failnez(cbf_set_hashedvalue(cbfdictionary, categoryname, "category_id", rownum)) } dictionary->node = base_node; if (!cbf_find_local_tag(dictionary,"_category_aliases.alias_name") ) { if (!cbf_get_value(dictionary, &alias_name)) { cbf_failnez(cbf_find_category(cbfdictionary, "category_aliases")) if (cbf_find_hashedvalue(cbfdictionary, alias_name, "category_alias", CBF_CASE_INSENSITIVE)) { cbf_failnez( cbf_set_hashedvalue (cbfdictionary, alias_name, "category_alias", -1)) } cbf_failnez( cbf_row_number (cbfdictionary, (unsigned int *)&rownum)) cbf_failnez( cbf_set_hashedvalue (cbfdictionary, categoryname, "category_root", rownum)) } } } } return 0; } /* Increment a column */ int cbf_increment_column( cbf_handle handle, const char* columnname, int * count ) { cbf_failnez(cbf_find_column(handle, columnname)) if (!cbf_get_integervalue(handle, count)) { (*count)++; return cbf_set_integervalue(handle, *count); } *count = 1; return cbf_set_integervalue(handle, 1); } /* Reset a column */ int cbf_reset_column( cbf_handle handle, const char* columnname) { if (!cbf_find_column(handle, columnname )) { cbf_failnez( cbf_remove_column(handle)) } return cbf_new_column( handle, columnname); } /* Reset reference counts for a dictionary */ int cbf_reset_refcounts( cbf_handle dictionary ) { if ( dictionary && !cbf_find_tag(dictionary,"_items.name")) { cbf_failnez(cbf_reset_column(dictionary, "CBF_wide_refcounts") ) cbf_failnez(cbf_reset_column(dictionary, "DB_wide_refcounts") ) cbf_failnez(cbf_reset_column(dictionary, "DBcat_wide_refcounts") ) cbf_failnez(cbf_reset_column(dictionary, "SF_wide_refcounts") ) cbf_failnez(cbf_reset_column(dictionary, "SFcat_wide_refcounts") ) } return 0; } /* Convert a DDL1 or DDL2 dictionary and add it to a CBF dictionary */ int cbf_convert_dictionary (cbf_handle handle, cbf_handle dictionary ) { cbf_handle dict; unsigned int blocks, frames, blockitems; int blocknum, itemnum; unsigned int numrows, rownum, parent_row; CBF_NODETYPE itemtype; const char *datablock_name; const char *saveframe_name; const char *parent_name, *child_name; const char *type_code, *otype_code; char buffer[255]; if (!handle || !dictionary ) return CBF_ARGUMENT; cbf_failnez( cbf_require_dictionary(handle, &dict)) cbf_failnez( cbf_require_datablock (dict, "cbf_dictionary")) cbf_failnez( cbf_require_category (dict, "category_aliases(hash_table)")) cbf_failnez( cbf_require_column (dict, "category_root(hash_next)")) cbf_failnez( cbf_require_column (dict, "category_alias(hash_next)")) cbf_failnez( cbf_require_category (dict, "category_aliases")) cbf_failnez( cbf_require_column (dict, "category_root")) cbf_failnez( cbf_require_column (dict, "category_alias")) cbf_failnez( cbf_require_column (dict, "category_root(hash_next)")) cbf_failnez( cbf_require_column (dict, "category_alias(hash_next)")) cbf_failnez( cbf_require_category (dict, "item_aliases(hash_table)")) cbf_failnez( cbf_require_column (dict, "item_root(hash_next)")) cbf_failnez( cbf_require_column (dict, "item_alias(hash_next)")) cbf_failnez( cbf_require_category (dict, "item_aliases")) cbf_failnez( cbf_require_column (dict, "item_root")) cbf_failnez( cbf_require_column (dict, "item_alias")) cbf_failnez( cbf_require_column (dict, "item_root(hash_next)")) cbf_failnez( cbf_require_column (dict, "item_alias(hash_next)")) cbf_failnez( cbf_require_category (dict, "categories(hash_table)")) cbf_failnez( cbf_require_column (dict, "id(hash_next)")) cbf_failnez( cbf_require_category (dict, "categories")) cbf_failnez( cbf_require_column (dict, "id")) cbf_failnez( cbf_require_column (dict, "id(hash_next)")) cbf_failnez( cbf_require_column (dict, "key")) cbf_failnez( cbf_require_category (dict, "items(hash_table)")) cbf_failnez( cbf_require_column (dict, "name(hash_next)")) cbf_failnez( cbf_require_column (dict, "category_id(hash_next)")) cbf_failnez( cbf_require_category (dict, "items")) cbf_failnez( cbf_require_column (dict, "name")) cbf_failnez( cbf_require_column (dict, "name(hash_next)")) cbf_failnez( cbf_require_column (dict, "type_code")) cbf_failnez( cbf_require_column (dict, "category_id")) cbf_failnez( cbf_require_column (dict, "category_id(hash_next)")) cbf_failnez( cbf_require_column (dict, "sub_category_id")) cbf_failnez( cbf_require_column (dict, "mandatory_code")) cbf_failnez( cbf_require_column (dict, "default_value")) cbf_failnez( cbf_require_column (dict, "parent")) cbf_failnez( cbf_require_column (dict, "method_expression")) cbf_failnez( cbf_require_category (dict, "items_enumerations(hash_table)")) cbf_failnez( cbf_require_column (dict, "name(hash_next)")) cbf_failnez( cbf_require_category (dict, "items_enumerations")) cbf_failnez( cbf_require_column (dict, "name")) cbf_failnez( cbf_require_column (dict, "name(hash_next)")) cbf_failnez( cbf_require_column (dict, "value")) cbf_failnez( cbf_require_column (dict, "value_type")) cbf_failnez (cbf_rewind_datablock (dictionary)) cbf_failnez (cbf_count_datablocks (dictionary, &blocks)) for (blocknum = 0; blocknum < blocks; blocknum++ ) { cbf_failnez (cbf_select_datablock(dictionary, blocknum)) cbf_failnez (cbf_datablock_name(dictionary, &datablock_name)) if ( !cbf_rewind_blockitem(dictionary, &itemtype) ) { if (cbf_count_saveframes(dictionary, &frames) || frames == 0) { cbf_failnez( cbf_convert_dictionary_definition(dict, dictionary, datablock_name)) } else { cbf_failnez (cbf_count_blockitems(dictionary, &blockitems)) for (itemnum = 0; itemnum < blockitems; itemnum++) { cbf_select_blockitem(dictionary, itemnum, &itemtype); if (itemtype == CBF_SAVEFRAME) { cbf_failnez( cbf_saveframe_name(dictionary, &saveframe_name)) cbf_failnez( cbf_convert_dictionary_definition(dict, dictionary, saveframe_name)) } } } } } /* Update unfilled-in items for children */ if( !cbf_find_tag(dict,"_items.parent")) { cbf_failnez(cbf_count_rows(dict,&numrows)) for (rownum = 0; rownum < numrows; rownum++) { cbf_failnez(cbf_find_column(dict,"parent")) if (!cbf_select_row(dict,rownum)) { if (!cbf_get_value(dict,&parent_name) && parent_name) { if (!cbf_find_hashedvalue(dict, parent_name, "name", CBF_CASE_INSENSITIVE)) { cbf_failnez(cbf_row_number(dict,&parent_row)) cbf_failnez(cbf_find_column(dict,"type_code")) if (!cbf_get_value(dict,&type_code) && type_code) { cbf_failnez(cbf_select_row(dict,rownum)) if (cbf_get_value(dict,&otype_code)) otype_code = NULL; cbf_failnez(cbf_set_value(dict,type_code)) if (otype_code && !cbf_cistrcmp(otype_code, type_code)) { cbf_failnez(cbf_find_column(dict,"name")) if (!cbf_get_value(dict,&child_name)) { sprintf(buffer," inconsistent data type %s for %s", otype_code, child_name); } } } } } } } } if (getenv("CBFLIB_DEBUG") ) cbf_failnez(cbf_write_file(dict,stderr,0,0,0,0)) return 0; } /* Find the requested tag anywhere in the cbf, make it the current column */ int cbf_find_tag (cbf_handle handle, const char *tag) { cbf_node *node; size_t catlen, collen; char categoryname[81]; char columnname[81]; char *colstart; if (!handle || !tag) return CBF_ARGUMENT; if (strlen(tag)>80) return CBF_ARGUMENT; if (tag[0] == '_') tag++; if (!(colstart = strchr(tag,'.'))) { colstart=(char *)tag-1; catlen = 0; } else { catlen = colstart-tag; } if (catlen) strncpy(categoryname,tag,catlen); categoryname[catlen] = '\0'; collen = (tag+strlen(tag))-colstart; columnname[0] = '_'; if (collen) strncpy(columnname+(catlen?0:1),colstart+1,collen); columnname[collen+(catlen?0:1)] = '\0'; cbf_failnez (cbf_find_parent (&node, handle->node, CBF_ROOT)) cbf_failnez(cbf_srch_tag(handle, node, categoryname, columnname)) return 0; } /* Find the requested tag in the cbf within the current save frame or data block, make it the current column */ int cbf_find_local_tag (cbf_handle handle, const char *tag) { cbf_node *node; size_t catlen, collen; char categoryname[81]; char columnname[81]; char *colstart; if (!handle || !tag) return CBF_ARGUMENT; if (strlen(tag)>80) return CBF_ARGUMENT; if (tag[0] == '_') tag++; if (!(colstart = strchr(tag,'.'))) { colstart=(char *)tag-1; catlen = 0; } else { catlen = colstart-tag; } if (catlen) strncpy(categoryname,tag,catlen); categoryname[catlen] = '\0'; collen = (tag+strlen(tag))-colstart; columnname[0] = '_'; if (collen) strncpy(columnname+(catlen?0:1),colstart+1,collen); columnname[collen+(catlen?0:1)] = '\0'; if (cbf_find_parent (&node, handle->node, CBF_SAVEFRAME)) { cbf_failnez (cbf_find_parent (&node, handle->node, CBF_DATABLOCK)) } cbf_failnez(cbf_srch_tag(handle, node, categoryname, columnname)) return 0; } /* Find the requested category and column anywhere in the cbf, make it the current column */ int cbf_srch_tag (cbf_handle handle, cbf_node *node, const char *categoryname, const char *columnname) { unsigned int children, child; if (!node) return CBF_NOTFOUND; node = cbf_get_link(node); if (node->type == CBF_CATEGORY) { if (((!(node->name) || (node->name[0] == '_')) &&(categoryname[0]=='\0')) || ((node->name)&&!cbf_cistrcmp(node->name,categoryname))) { cbf_failnez (cbf_find_child(&node,node,columnname)) handle->node = node; handle->row = 0; handle->search_row = 0; return 0; } else { return CBF_NOTFOUND; } } children = node->children; for (child = 0; child < children; child++) { if(! cbf_srch_tag(handle, (node->child)[child], categoryname, columnname)) return 0; } return CBF_NOTFOUND; } /* Find the root alias of a given category */ int cbf_find_category_root (cbf_handle handle, const char* categoryname, const char** categoryroot) { cbf_handle dictionary; const char * tempcatname; if (!handle || !categoryname || !categoryroot ) return CBF_ARGUMENT; dictionary = (cbf_handle) handle->dictionary; if (!dictionary) return CBF_NOTFOUND; if (categoryname[0] == '_') { if (!cbf_find_tag(dictionary,"_items.name") && !cbf_find_hashedvalue(dictionary,categoryname,"name",CBF_CASE_INSENSITIVE) && !cbf_find_column(dictionary,"category_id") && !cbf_get_value(dictionary,&tempcatname) && tempcatname) categoryname = tempcatname; else return CBF_NOTFOUND; } cbf_failnez( cbf_find_tag(dictionary, "_category_aliases.alias_id")) cbf_failnez( cbf_rewind_row(dictionary)) cbf_failnez( cbf_find_hashedvalue(dictionary, categoryname,"alias_id",CBF_CASE_INSENSITIVE)) cbf_failnez( cbf_find_column(dictionary, "root_id")) return cbf_get_value(dictionary,categoryroot); } /* Find the root alias of a given category, defaulting to the current one */ int cbf_require_category_root (cbf_handle handle, const char* categoryname, const char** categoryroot) { cbf_handle dictionary; const char * tempcatname; if (!handle || !categoryname || !categoryroot ) return CBF_ARGUMENT; dictionary = (cbf_handle) handle->dictionary; if (categoryname[0] == '_') { if (!cbf_find_tag(dictionary,"_items.name") && !cbf_find_hashedvalue(dictionary,categoryname,"name",CBF_CASE_INSENSITIVE) && !cbf_find_column(dictionary,"category_id") && !cbf_get_value(dictionary,&tempcatname) && tempcatname) categoryname = tempcatname; else { * categoryroot = categoryname; return 0; } } if (cbf_find_category_root(handle,categoryname,categoryroot)) * categoryroot = categoryname; return 0; } /* Set the root alias of a given category */ int cbf_set_category_root (cbf_handle handle, const char* categoryname, const char* categoryroot) { cbf_handle dictionary; unsigned int rownum; if (!handle || !categoryname || !categoryroot ) return CBF_ARGUMENT; cbf_failnez( cbf_require_dictionary(handle, &dictionary)) if (!dictionary) return CBF_NOTFOUND; if ( cbf_find_tag(dictionary, "_category_aliases.alias_id")) { cbf_failnez( cbf_require_datablock(dictionary, "dictionary")) cbf_failnez( cbf_require_category(dictionary, "category_aliases")) cbf_failnez( cbf_require_column(dictionary, "alias_id")) } if (cbf_find_hashedvalue(dictionary, categoryname, "alias_id", CBF_CASE_INSENSITIVE)) { cbf_failnez( cbf_set_hashedvalue(dictionary, categoryname, "alias_id", -1)) } cbf_failnez( cbf_row_number(dictionary, &rownum)) cbf_failnez( cbf_set_hashedvalue(dictionary, categoryroot, "root_id", rownum)) return 0; } /* Find the root alias of a given tag */ int cbf_find_tag_root (cbf_handle handle, const char* tagname, const char** tagroot) { cbf_handle dictionary; if (!handle || !tagname || !tagroot ) return CBF_ARGUMENT; dictionary = (cbf_handle) handle->dictionary; if (!dictionary) return CBF_NOTFOUND; if ( cbf_find_tag(dictionary, "_item_aliases.alias_name") && cbf_find_tag(dictionary, "_aliases.definition_id")) { return CBF_NOTFOUND; } cbf_failnez( cbf_find_hashedvalue(dictionary,tagname,"alias_name", CBF_CASE_INSENSITIVE)) cbf_failnez( cbf_find_column(dictionary, "root_name")) return cbf_get_value(dictionary,tagroot); } /* Find the root alias of a given tag, defaulting to the current one */ int cbf_require_tag_root (cbf_handle handle, const char* tagname, const char** tagroot) { if (!handle || !tagname || !tagroot ) return CBF_ARGUMENT; if (cbf_find_tag_root(handle,tagname,tagroot)) * tagroot = tagname; return 0; } /* Set the root alias of a given tag */ int cbf_set_tag_root (cbf_handle handle, const char* tagname, const char* tagroot) { cbf_handle dictionary; unsigned int rownum; if (!handle || !tagname || !tagroot ) return CBF_ARGUMENT; cbf_failnez( cbf_require_dictionary(handle, &dictionary)) if (!dictionary) return CBF_NOTFOUND; if ( cbf_find_tag(dictionary, "_item_aliases.alias_name")) { cbf_failnez( cbf_require_datablock(dictionary, "dictionary")) cbf_failnez( cbf_require_category(dictionary, "item_aliases")) cbf_failnez( cbf_require_column(dictionary, "alias_name")) } if (cbf_find_hashedvalue(dictionary, tagname, "alias_name", CBF_CASE_INSENSITIVE)) { cbf_failnez( cbf_set_hashedvalue(dictionary, tagname, "alias_name", -1)) } cbf_failnez( cbf_row_number(dictionary, &rownum)) cbf_failnez( cbf_set_hashedvalue(dictionary, tagroot, "root_name", rownum)) return 0; } /* Find the category of a given tag */ int cbf_find_tag_category (cbf_handle handle, const char* tagname, const char** categoryname) { cbf_handle dictionary; if (!handle || !tagname || !categoryname ) return CBF_ARGUMENT; dictionary = (cbf_handle) handle->dictionary; if (!dictionary) return CBF_NOTFOUND; cbf_failnez( cbf_find_tag(dictionary, "_item.name")) cbf_failnez( cbf_rewind_row(dictionary)) cbf_failnez( cbf_find_row(dictionary, tagname)) cbf_failnez( cbf_find_column(dictionary, "category_id")) return cbf_get_value(dictionary,categoryname); } /* Set category of a given tag */ int cbf_set_tag_category (cbf_handle handle, const char* tagname, const char* categoryname) { cbf_handle dictionary; char * tempcat; if (!handle || !tagname || !categoryname ) return CBF_ARGUMENT; cbf_failnez( cbf_require_dictionary(handle, &dictionary)) if (!dictionary) return CBF_NOTFOUND; if ( cbf_find_tag(dictionary, "_item.name")) { cbf_failnez( cbf_require_datablock(dictionary, "dictionary")) cbf_failnez( cbf_require_category(dictionary, "item")) cbf_failnez( cbf_require_column(dictionary, "name")) } cbf_failnez( cbf_require_column(dictionary, "category_id")) cbf_failnez( cbf_rewind_row(dictionary)) cbf_failnez( cbf_find_column(handle, "name")) while (!cbf_find_nextrow(dictionary,tagname)) { cbf_failnez( cbf_require_column(dictionary, "category_id")) if (!cbf_get_value(dictionary,(const char **)&tempcat)) { if (tempcat && !cbf_cistrcmp(tempcat,categoryname))return 0; } if (!tempcat) return cbf_set_value(dictionary,categoryname); cbf_failnez( cbf_find_column(dictionary, "name")) } cbf_failnez( cbf_new_row(dictionary)) cbf_failnez( cbf_set_value(dictionary,tagname)) cbf_failnez( cbf_find_column(dictionary, "category_id")) return cbf_set_value(dictionary,categoryname); } /* check a category for all required tags and for parent tags */ int cbf_check_category_tags(cbf_handle handle, cbf_node* category, cbf_node* parent) { int rownum; long refcount; char *endptr; char buffer[512]; const char* refcount_column, *mandatory_code, *item_name, *category_id, *parent_name, *refcountval, *block_name; if (parent->type == CBF_SAVEFRAME) refcount_column = "SF_wide_refcounts"; else refcount_column = "DB_wide_refcounts"; block_name = parent->name?parent->name:"(null)"; if (handle->dictionary && category->name && category->name[0]) { if (getenv("CBFLIB_DEBUG")) cbf_write_file(handle->dictionary, stderr, 0, 0, 0, 0); if (!cbf_find_tag(handle->dictionary,"_items.name") && !cbf_find_hashedvalue(handle->dictionary,category->name,"category_id", CBF_CASE_INSENSITIVE) ) { cbf_failnez(cbf_row_number(handle->dictionary,(unsigned int *)&rownum)) do { cbf_failnez(cbf_select_row(handle->dictionary,rownum)) cbf_failnez(cbf_find_column(handle->dictionary,"name")) cbf_failnez(cbf_get_value(handle->dictionary,&item_name)) if (!item_name) item_name = "(null)"; if (!cbf_find_column(handle->dictionary,"category_id") && !cbf_get_value(handle->dictionary, &category_id) && category_id && !cbf_cistrcmp(category_id, category->name)) { refcount = 0; if(!cbf_find_column(handle->dictionary,refcount_column) && !cbf_get_value(handle->dictionary, &refcountval) && refcountval) { refcount = strtol(refcountval,&endptr,10); } if (!cbf_find_column(handle->dictionary,"mandatory_code") && !cbf_get_value(handle->dictionary, &mandatory_code) && mandatory_code && !cbf_cistrcmp(mandatory_code,"yes")) { if( refcount <= 0) { sprintf(buffer, "required tag %s in %s not given", item_name, block_name); cbf_log(handle,buffer, CBF_LOGWARNING|CBF_LOGWOLINE); } } if (refcount > 0) { if (!cbf_find_column(handle->dictionary,"parent") && !cbf_get_value(handle->dictionary, &parent_name) && parent_name && !cbf_find_hashedvalue(handle->dictionary,parent_name,"name", CBF_CASE_INSENSITIVE) && !cbf_find_column(handle->dictionary,refcount_column) && (cbf_get_value(handle->dictionary, &refcountval) || !refcountval || strtol(refcountval,&endptr,10) <=0)) { sprintf(buffer, "required parent tag %s for %s in %s not given", parent_name?parent_name:"(null)", item_name, block_name); cbf_log(handle,buffer, CBF_LOGWARNING|CBF_LOGWOLINE); } } } cbf_failnez(cbf_select_row(handle->dictionary, rownum)) cbf_failnez(cbf_find_column(handle->dictionary, "category_id(hash_next)")) if (cbf_get_integervalue(handle->dictionary, &rownum)) rownum = 1; } while (rownum >= 0); } } return 0; } /* Validate portion of CBF */ int cbf_validate (cbf_handle handle, cbf_node * node, CBF_NODETYPE type, cbf_node * auxnode) { cbf_node * tnode; cbf_node * colnode; cbf_node * ttnode; cbf_handle functions_dict; const char * dictype; const char * catname, * catroot, * functionname; const char * diccat, * diccatroot; const char * loopname; const char * expression; unsigned int children, columns, rows; cbf_file * file; char buffer[512]; char itemname[82]; cbf_node *dbp; int lcolumn=0, litemname=0; int count; int column, minrows, maxrows; file = handle->file; if ( type == CBF_ROOT ) { /* we come here at the end of the parse 'node' points to the cbf up to the point prior to the end of the parse, so that at the beginning, it is the ROOT, but after that is at a lower level, somewhere within a CBF_DATABLOCK node, if we have has any data. We need to check any pending category, save frame or data block. We do this recursively. If there is a dictionary, we need to scan the CBF checking all parent-child relationships. This is done in the data block scan. Code is needed to report the cases where the relationships are satisfied across data blocks. Code is needed to insert category names for DDL1 tags. */ cbf_failnez(cbf_validate(handle, node, CBF_DATABLOCK, NULL)) } else if ( type == CBF_DATABLOCK ) { /* we come here at the start of a new datablock or at the end of the parse. 'node' points to the cbf up to the point prior to the new datablock, so that at the beginning, it is the ROOT, but after that is at a lower level, somewhere within a CBF_DATABLOCK node We need to check: 1. Does the prior data block have any content 2. If there is a dictionary, we need to check 2.1. If a tag is given within the prior datablock, then the parent of that tag is given in the same data block 2.2. For each category in the prior datablock that each mandatory tag for that category is given, and that for each implicit tag that is not explicitly given, that the parent, if any, of that tag is given in the same data block */ /* First validate the last category before the termination */ cbf_failnez(cbf_validate(handle, node, CBF_CATEGORY, NULL)) /* Now check if the parent data block has any content */ if (!cbf_find_parent(&tnode, node, CBF_DATABLOCK)) { cbf_failnez(cbf_count_children(&children, tnode)) if ( children == 0 ) { if (file != (cbf_file *)NULL) { if ((tnode->name) != (char *)NULL) { sprintf(buffer, "data block %s ends with no content",tnode->name); } else { sprintf(buffer, "data block (null) ends with no content"); } cbf_log (handle, buffer, CBF_LOGWARNING|CBF_LOGSTARTLOC); } else { return CBF_FORMAT; } } else { /* We have content, now check each category for required tags */ if (handle->dictionary) { cbf_node *child_node; unsigned int child; for (child = 0; child < children; child++) { cbf_failnez (cbf_get_child (&child_node, tnode, child)) if (child_node->type == CBF_CATEGORY) { cbf_failnez(cbf_check_category_tags(handle, child_node, tnode)) } else if (child_node->type == CBF_SAVEFRAME) { cbf_node *sfchild_node; unsigned int sfchild, sfchildren; cbf_failnez(cbf_count_children(&sfchildren, child_node)) for (sfchild = 0; sfchild < sfchildren; sfchild++) { cbf_failnez (cbf_get_child (&sfchild_node, child_node, sfchild)) if (sfchild_node->type == CBF_CATEGORY) { cbf_failnez(cbf_check_category_tags(handle, sfchild_node, child_node)) } } } } } } } if (handle->dictionary) { if (!cbf_find_tag(handle->dictionary, "_items.name") || !cbf_find_tag(handle->dictionary, "_definition.id")) { cbf_failnez(cbf_reset_column(handle->dictionary, "DB_wide_refcounts") ) cbf_failnez(cbf_reset_column(handle->dictionary, "DBcat_wide_refcounts") ) cbf_failnez(cbf_reset_column(handle->dictionary, "SF_wide_refcounts") ) cbf_failnez(cbf_reset_column(handle->dictionary, "SFcat_wide_refcounts") ) } } } else if (type == CBF_SAVEFRAME) { /* we come here at the end of a save frame 'node' points to the cbf up to the point prior to the save frame end. 1. Does the save frame have any content 2. If there is a dictionary, we need to check 2.1. If a tag is given within the save frame, then the parent of that tag is given in the same save frame 2.2. For each category in the save frame that each mandatory tag for that category is given, and that for each implicit tag that is not explicitly given, that the parent, if any, of that tag is given in the same data block 3. We need to reset the counters for the save frame. */ /* Now check if the save frame has any content */ if (!cbf_find_parent(&tnode, node, CBF_SAVEFRAME)) { cbf_failnez(cbf_count_children(&children, tnode)) if ( children == 0 ) { if (file != (cbf_file *)NULL) { if ((tnode->name) != (char *)NULL) { sprintf(buffer, "save frame %s ends with no content",tnode->name); } else { sprintf(buffer, "save frame (null) ends with no content"); } cbf_log (handle, buffer, CBF_LOGWARNING|CBF_LOGSTARTLOC); } else { return CBF_FORMAT; } } else { /* We have content, now check each category for required tags */ if (handle->dictionary) { cbf_node *child_node; unsigned int child; for (child = 0; child < children; child++) { cbf_failnez (cbf_get_child (&child_node, tnode, child)) if (child_node->type == CBF_CATEGORY) { cbf_failnez(cbf_check_category_tags(handle, child_node, tnode)) } } } } } if (handle->dictionary) { if (!cbf_find_tag(handle->dictionary, "_items.name") || !cbf_find_tag(handle->dictionary, "_definition.id")) { cbf_failnez(cbf_reset_column(handle->dictionary, "SF_wide_refcounts") ) cbf_failnez(cbf_reset_column(handle->dictionary, "SFcat_wide_refcounts") ) } } } else if (type == CBF_FUNCTION) { /* We come here at the start of a function declaration We need to check if there is a function definition place declaration in functions dictionary */ if (!cbf_find_parent (&tnode, node, CBF_DATABLOCK)) { catname = tnode->name; if (!cbf_count_children (&columns, tnode)) { if (columns == 0) cbf_log(handle,"function definition is missing",CBF_LOGWARNING|CBF_LOGSTARTLOC); else { char location[255]; cbf_find_child (&node, node, catname); functionname = node->name; cbf_failnez(cbf_require_dictionary(handle, &functions_dict)) cbf_failnez(cbf_require_datablock(functions_dict, "cbf_functions")) cbf_failnez( cbf_require_category (functions_dict, "function_definitions")) cbf_failnez( cbf_require_column (functions_dict, "function_location")) cbf_failnez( cbf_require_column (functions_dict, "function_expression")) strcpy(location, catname); strcat(location, "."); strcat(location, functionname); if (!cbf_find_local_tag(functions_dict,"function_location")) { cbf_failnez( cbf_set_value(functions_dict, (const char *)location)) } /*cbf_construct_functions_dictionary(functions_dict, catname, functionname);*/ } } } } else if (type == CBF_CATEGORY ) { /* We come here at the start of a new datablock element or save frame element in the form of an assignment, a loop assignment or (if a data block) a save frame. Alternatively, we may come here at the start of a new save frame element. 'node' will be pointing to the data block the save frame or to a node somehere within the prior category In the third case, we need to check 1. If there are any columns at all within the prior category 2. If the columns in the prior category are all the same length 3. If there is a dictionary ... */ /* Find the category node */ if (!cbf_find_parent (&tnode, node, CBF_CATEGORY)) { catname = tnode->name; if (!cbf_count_children (&columns, tnode)) { if (columns == 0) cbf_log(handle,"no columns in category",CBF_LOGWARNING|CBF_LOGSTARTLOC); else { maxrows = minrows = 0; for (column = 0; column < columns; column++) { rows = 0; if ( !cbf_get_child(&ttnode,tnode, column) ) { if ( !cbf_count_children (&rows, ttnode)) { if (column == 0) { maxrows = minrows = rows; } if (rows > maxrows) maxrows = rows; if (rows < minrows) minrows = rows; } } } if ( maxrows != minrows ) { sprintf(buffer, "incomplete row in category %s", (tnode->name)?(tnode->name):"(null)"); cbf_log(handle,buffer,CBF_LOGWARNING|CBF_LOGSTARTLOC); } if ( maxrows == 0 ) { sprintf(buffer, "no rows in category %s", (tnode->name)?(tnode->name):"(null)"); cbf_log(handle,buffer,CBF_LOGWARNING|CBF_LOGSTARTLOC); } } } } else { if (!cbf_find_parent (&tnode, node, CBF_SAVEFRAME)) { if (!cbf_count_children (&columns, tnode)) { if (columns == 0) cbf_log(handle,"no categories in save frame",CBF_LOGWARNING|CBF_LOGSTARTLOC); } } } if (handle->dictionary) { if (!cbf_find_tag(handle->dictionary, "_items.name") || !cbf_find_tag(handle->dictionary, "_definition.id")) { cbf_failnez(cbf_reset_column(handle->dictionary, "DBcat_wide_refcounts") ) cbf_failnez(cbf_reset_column(handle->dictionary, "SFcat_wide_refcounts") ) } } } else if (type == CBF_COLUMN) { if (!cbf_find_parent(&tnode, node, CBF_CATEGORY)) { lcolumn = 0; if (node->name) lcolumn = strlen(node->name); if (!tnode->name|| !(tnode->name[0]) || !cbf_cistrcmp("(none)",tnode->name) || (node->name && node->name[0]=='_') ) { litemname = lcolumn; if (litemname > 75) cbf_log(handle, "item name longer than 75 characters", CBF_LOGWARNING|CBF_LOGSTARTLOC); } else { litemname = 1 + strlen(tnode->name) + 1 + lcolumn; if (litemname > 75) cbf_log(handle, "category name + column name longer than 75 characters", CBF_LOGWARNING|CBF_LOGSTARTLOC); } if (tnode->name && auxnode->name) { sprintf(buffer,"item category name %s inconsistent with category %s", tnode->name, auxnode->name); if (cbf_cistrcmp(tnode->name,auxnode->name)) cbf_log(handle, buffer,CBF_LOGWARNING|CBF_LOGSTARTLOC); } if (handle->dictionary) { loopname = NULL; if ((!cbf_find_tag(handle->dictionary, "_items.name") || !cbf_find_tag(handle->dictionary, "_definition.id")) && !cbf_compose_itemname(handle, node, itemname, 80)) { if (cbf_find_hashedvalue(handle->dictionary, itemname, "name",CBF_CASE_INSENSITIVE) ) { sprintf(buffer,"item name %s not found in the dictionary",itemname); cbf_log(handle, buffer, CBF_LOGWARNING|CBF_LOGSTARTLOC); } else { if (auxnode->name && auxnode->name[0]) { loopname = auxnode->name; } else { cbf_failnez (cbf_get_child (&colnode, auxnode, 0)) loopname = colnode->name; } if (loopname && loopname[0] == '_') { if (!cbf_find_hashedvalue(handle->dictionary, loopname, "name",CBF_CASE_INSENSITIVE) && ! cbf_find_column(handle->dictionary, "category_id")) { cbf_get_value(handle->dictionary, &loopname); } } cbf_failnez(cbf_find_hashedvalue(handle->dictionary, itemname, "name",CBF_CASE_INSENSITIVE)) if (!cbf_find_column(handle->dictionary, "category_id") && ! cbf_get_value(handle->dictionary, &diccat) && diccat && loopname && ! cbf_require_category_root(handle->dictionary, diccat, &diccatroot) && ! cbf_require_category_root(handle->dictionary, loopname, &catroot)) { if (cbf_cistrcmp(diccatroot,catroot)) { sprintf(buffer,"dictionary item %s, category name %s inconsistent with %s" , itemname, diccatroot, catroot); cbf_log(handle, buffer, CBF_LOGWARNING|CBF_LOGSTARTLOC); } } cbf_failnez(cbf_increment_column(handle->dictionary, "CBF_wide_refcounts", &count )) if (!cbf_find_parent(&ttnode,tnode,CBF_SAVEFRAME)) { int count, countcat; cbf_failnez(cbf_increment_column(handle->dictionary, "SF_wide_refcounts", &count )) cbf_failnez(cbf_increment_column(handle->dictionary, "SFcat_wide_refcounts", &countcat )) if (count > 1 && countcat <= 1) { sprintf(buffer,"item name %s appears more than once in a save frame, count %d", itemname, count ); cbf_log(handle, buffer, CBF_LOGWARNING|CBF_LOGSTARTLOC); } if (countcat > 1 ) { sprintf(buffer,"item name %s appears more than once in a save frame category, count %d", itemname, countcat); cbf_log(handle, buffer, CBF_LOGWARNING|CBF_LOGSTARTLOC); } } else { int count, countcat; cbf_failnez(cbf_increment_column(handle->dictionary, "DB_wide_refcounts", &count )) cbf_failnez(cbf_increment_column(handle->dictionary, "DBcat_wide_refcounts", &countcat )) if (count > 1 && countcat <= 1 ) { sprintf(buffer,"item name %s appears more than once in a data block, count %d", itemname, count); cbf_log(handle, buffer, CBF_LOGWARNING|CBF_LOGSTARTLOC); } if (countcat > 1 ) { sprintf(buffer,"item name %s appears more than once in a data block category, count %d", itemname, countcat); cbf_log(handle, buffer, CBF_LOGWARNING|CBF_LOGSTARTLOC); } } } } } } } else if (type == CBF_VALUE) { /* */ int tokentype; char * valuestring; char fline[2049]; char * flptr; int goodmatch; int nullvalue; int generated; #ifdef CBF_USE_PYCIFRW FILE *fout; char output[255]; #endif long ltest; double dtest; char * endptr; char loval[255], hival[255]; char * colonpos; char * callpos; char functionname[255]; long symop, xlate; long yyyy, mm, dd, hr, mi, se, sf, tz; valuestring = ((char *)node)+1; tokentype = (((char *)node)[0]); nullvalue = 0; generated = 0; if (handle->dictionary && (tnode = cbf_get_link(auxnode)) && (tnode->name) ){ if (!cbf_compose_itemname(handle, tnode, itemname, 80)) { if (!cbf_find_tag(handle->dictionary, "_items.name") || !cbf_find_tag(handle->dictionary, "_definition.id")) { if (!cbf_find_hashedvalue(handle->dictionary, itemname, "name",CBF_CASE_INSENSITIVE)) { if (!cbf_find_column(handle->dictionary, "type_code") && !cbf_get_value(handle->dictionary, &dictype)) { goodmatch = 0; if (tokentype==CBF_TOKEN_SCSTRING) { if (valuestring[0]=='\\') { flptr = valuestring+1; if (cbf_foldtextline((const char **)&flptr, fline, 2048, 1, 0, ';')) { tokentype = CBF_TOKEN_SQSTRING; valuestring = fline; } } } if (tokentype==CBF_TOKEN_TSQSTRING || tokentype==CBF_TOKEN_TDQSTRING || tokentype==CBF_TOKEN_PRNSTRING || tokentype==CBF_TOKEN_BRCSTRING || tokentype==CBF_TOKEN_BKTSTRING ) { if (valuestring[0]=='\\') { flptr = valuestring+1; if (cbf_foldtextline((const char **)&flptr, fline, 2048, 1, 0, '\0')) { tokentype = CBF_TOKEN_SQSTRING; valuestring = fline; } } } if (tokentype==CBF_TOKEN_SQSTRING || tokentype== CBF_TOKEN_DQSTRING) { if (strchr(valuestring,'\n')) tokentype=CBF_TOKEN_SCSTRING; else if(!strchr(valuestring,' ') && !strchr(valuestring,'\t') && !strchr(valuestring,'\v') && !strchr(valuestring,'\f') && !strchr(valuestring,'\r')) tokentype = CBF_TOKEN_WORD; } switch (tokentype) { case 0: case CBF_TOKEN_NULL: nullvalue = 1; goodmatch = 1; break; case CBF_TOKEN_WORD: if ( !cbf_cistrncmp(dictype,"implied",8) ) { goodmatch = 1; break; } if ( !cbf_cistrncmp(dictype,"uchar3",7) ) { if (strlen(valuestring)==3 || (strlen(valuestring)==4 && *(valuestring)=='+')) goodmatch = 1; break; } if ( !cbf_cistrncmp(dictype,"uchar1",7) ) { if (strlen(valuestring)==1 || (strlen(valuestring)==2 && *(valuestring)=='+')) goodmatch = 1; break; } if ( !cbf_cistrncmp(dictype,"symo",4) ) { symop = strtol(valuestring, &endptr, 10); xlate = 0; if ( *endptr=='_') xlate = strtol(endptr+1, &endptr, 10); if ( *endptr=='\0' && symop >=1 && symop <=192 && xlate >=0 && xlate <1000) goodmatch = 1; break; } if( !cbf_cistrncmp(dictype,"yyyy-",5) || !cbf_cistrncmp(dictype,"date",4) ) { mm=-1, dd=-1, hr=0, mi =0, se=0, sf=0, tz = 0; yyyy=strtol(valuestring, &endptr, 10); if (*endptr=='-') { mm=strtol(endptr+1, &endptr, 10); if (*endptr=='-') { dd=strtol(endptr+1, &endptr, 10); if ( *endptr=='T' || *endptr=='t' || *endptr==':') { hr=strtol(endptr+1, &endptr, 10); if ( *endptr==':') { mi=strtol(endptr+1, &endptr, 10); if ( *endptr==':') { se=strtol(endptr+1, &endptr, 10); if ( *endptr=='.') { sf=strtol(endptr+1, &endptr, 10); } } } } } } if (*endptr=='-'||*endptr=='+') tz=strtol(endptr+1, &endptr, 10); if (*endptr=='\0' && yyyy>=0 && yyyy<10000 && mm > 0 && mm < 13 && dd > 0 && dd < 32 && hr >=0 && hr <25 && mi >=0 && mi <61 && se >=0 && se <61 && sf >=0 && tz >=0 && tz <25 ) goodmatch = 1; break; } if ( !cbf_cistrncmp(dictype,"char",4) || !cbf_cistrncmp(dictype,"ucha",4) || !cbf_cistrncmp(dictype,"code",4) || !cbf_cistrncmp(dictype,"name",4) || !cbf_cistrncmp(dictype,"idna",4) || !cbf_cistrncmp(dictype,"alia",4) || !cbf_cistrncmp(dictype,"ucod",4) || !cbf_cistrncmp(dictype,"line",4) || !cbf_cistrncmp(dictype,"ulin",4) || !cbf_cistrncmp(dictype,"any", 3) || !cbf_cistrncmp(dictype,"atco",4) || !cbf_cistrncmp(dictype,"phon",4) || !cbf_cistrncmp(dictype,"emai",4) || !cbf_cistrncmp(dictype,"fax", 3) || !cbf_cistrncmp(dictype,"text",4) || !cbf_cistrncmp(dictype,"tag",3) || !cbf_cistrncmp(dictype,"ctag",4) || !cbf_cistrncmp(dictype,"otag",4) ) { goodmatch = 1; break; } /*Check if valuestring is a function call*/ if (!cbf_cistrncmp(valuestring,"::",2)) { callpos = strchr(valuestring,':'); strcpy(functionname, callpos+2); cbf_failnez(cbf_find_parent (&dbp, handle->node, CBF_DATABLOCK)) sprintf(buffer, "this is a function call to %s.%s", dbp->name,functionname); cbf_log(handle,buffer,CBF_LOGWARNING|CBF_LOGSTARTLOC); } if ( cbf_cistrncmp(dictype,"numb",4) || cbf_cistrncmp(dictype,"int",3) || cbf_cistrncmp(dictype,"floa",4)) { ltest = strtol(valuestring, &endptr, 10); if (*endptr=='\0') { goodmatch = 1; break; } if (*endptr == '(') { ltest = strtol(endptr+1, &endptr, 10); if (*endptr==')') { goodmatch = 1; break; } } if ( !cbf_cistrncmp(dictype,"numb",4) || !cbf_cistrncmp(dictype,"floa",4)) { dtest = strtod(valuestring, &endptr); if (*endptr=='\0') { goodmatch = 1; break; } if (*endptr == '(') { ltest = strtol(endptr+1, &endptr, 10); if (*endptr==')') { goodmatch = 1; break; } } } } if (!cbf_check_type_contents(dictype,valuestring)) { goodmatch = 1; break; } break; case CBF_TOKEN_SQSTRING: case CBF_TOKEN_DQSTRING: if ( !cbf_cistrncmp(dictype,"implied",8) ) { goodmatch = 1; break; } if(!cbf_cistrncmp(dictype,"text",4) || !cbf_cistrncmp(dictype,"any",3) || !cbf_cistrncmp(dictype,"line",4) || !cbf_cistrncmp(dictype,"ulin",4) || !cbf_cistrncmp(dictype,"name",4) || !cbf_cistrncmp(dictype,"idna",4) || !cbf_cistrncmp(dictype,"alia",4) || !cbf_cistrncmp(dictype,"atco",4) || !cbf_cistrncmp(dictype,"char",4) || !cbf_cistrncmp(dictype,"ucha",4)) { goodmatch = 1; break; } if (!cbf_check_type_contents(dictype,valuestring)) { goodmatch = 1; break; } break; case CBF_TOKEN_SCSTRING: if ( !cbf_cistrncmp(dictype,"implied",8) ) { goodmatch = 1; break; } if(!cbf_cistrncmp(dictype,"text",4) || !cbf_cistrncmp(dictype,"any",3) || !cbf_cistrncmp(dictype,"char",4) || !cbf_cistrncmp(dictype,"ucha",4)) { goodmatch = 1; break; } if (!cbf_check_type_contents(dictype,valuestring)) { goodmatch = 1; break; } break; } if (!cbf_cistrcmp(dictype,"binary")) { if ( (((char *)node)) == NULL || (((char *)node)[0]) == CBF_TOKEN_NULL || (((char *)node)[0]) == CBF_TOKEN_TMP_BIN || (((char *)node)[0]) == CBF_TOKEN_BIN || (((char *)node)[0]) == CBF_TOKEN_MIME_BIN ) goodmatch = 1; } if (nullvalue) { /* We come here if we come upon a missing value We need to generate a value if there is a given method in the dictionary */ int nextrow; const char *nextitem; char mainitemname[81]; mainitemname[80] = '\0'; cbf_failnez(cbf_row_number(handle->dictionary, (unsigned int *) &nextrow)) strncpy(mainitemname, itemname, 80); if(!cbf_find_tag(handle->dictionary, "_items.method_expression")) { while ( nextrow >=0 ) { cbf_failnez( cbf_find_column (handle->dictionary, "name")) cbf_failnez( cbf_select_row (handle->dictionary, nextrow)) cbf_failnez( cbf_get_value (handle->dictionary, &nextitem)) cbf_failnez( cbf_find_column (handle->dictionary, "method_expression")) cbf_failnez( cbf_get_value(handle->dictionary, &expression)) if (nextitem && !cbf_cistrcmp(nextitem, itemname)) { #ifdef CBF_USE_PYCIFRW if (expression!=NULL) { cbf_failnez(cbf_find_parent (&dbp, handle->node, CBF_DATABLOCK)) cbf_drel(handle, handle->dictionary, mainitemname, dbp->name, expression); fout = fopen("method_output", "r"); fscanf(fout, "%s", output); fclose(fout); sprintf(buffer, "%s value missing - CBFlib generated value: %s", mainitemname, output); cbf_log(handle, buffer,CBF_LOGWARNING|CBF_LOGSTARTLOC); valuestring = output; tokentype = CBF_VALUE; generated = 1; } #endif break; } } } } else { /* We come here to check if there is a given method in the dictionary to validate our given value against it */ int nextrow; const char *nextitem; char mainitemname[81]; /* TODO: replace the use of preprocessing script with cbf_set_columname() char columnname[81]; char* columnnametemp; char columnnamelocal[81]; */ mainitemname[80] = '\0'; cbf_failnez(cbf_row_number(handle->dictionary, (unsigned int *) &nextrow)) strncpy(mainitemname, itemname, 80); if(!cbf_find_tag(handle->dictionary, "_items.method_expression")) { while ( nextrow >=0 ) { cbf_failnez( cbf_find_column (handle->dictionary, "name")) cbf_failnez( cbf_select_row (handle->dictionary, nextrow)) cbf_failnez( cbf_get_value (handle->dictionary, &nextitem)) cbf_failnez( cbf_find_column (handle->dictionary, "method_expression")) cbf_failnez( cbf_get_value(handle->dictionary, &expression)) if (nextitem && !cbf_cistrcmp(nextitem, itemname)) { #ifdef CBF_USE_PYCIFRW if (expression!=NULL){ /* cbf_falinez(cbf_column_name(handle, &columnnametemp)) strcpy(columnnametemp, columnname); fprintf(stderr, "Column Name Temp: %s", columnnametemp); strcpy(columnnamelocal, columnname); strcat(columnnamelocal, "_local"); fprintf(stderr, "Column Name Local: %s", columnnamelocal); */ cbf_failnez(cbf_find_parent (&dbp, handle->node, CBF_DATABLOCK)) /* cbf_failnez(cbf_set_columnname(handle, columnnamelocal)) */ cbf_drel(handle, handle->dictionary, mainitemname, dbp->name, expression); /*cbf_falinez(cbf_set_columnname(handle, columnname))*/ fout = fopen("method_output", "r"); if (fout) { fscanf(fout, "%s", output); fclose(fout); if (cbf_cistrcmp(valuestring,output)) { sprintf(buffer, "%s value provided conflicts with generated value. CBFlib generated value %s: ", mainitemname, output); cbf_log(handle, buffer,CBF_LOGWARNING|CBF_LOGSTARTLOC); } } } #endif break; } } } } if (!goodmatch) { sprintf(buffer," %s type conflicts with dictionary type %s", itemname, dictype ); cbf_log(handle, buffer,CBF_LOGWARNING|CBF_LOGSTARTLOC); } else { if (tokentype != CBF_TOKEN_NULL && !cbf_find_tag(handle->dictionary,"_items_enumerations.name")) { if (!cbf_find_hashedvalue(handle->dictionary,itemname,"name", CBF_CASE_INSENSITIVE)) { int nextrow, valok, numb; double doubleval=0.0; const char *nextitem, *enumvalue, *enumvaluetype; char * endptr; cbf_failnez(cbf_row_number(handle->dictionary, (unsigned int *) &nextrow)) valok = numb = 0; if ( cbf_cistrncmp(dictype,"numb",4) || cbf_cistrncmp(dictype,"int",3) || cbf_cistrncmp(dictype,"floa",4) || cbf_cistrncmp(dictype,"real",4)) { numb = 1; doubleval = strtod(valuestring, &endptr); } while ( nextrow >=0 ) { cbf_failnez( cbf_find_column (handle->dictionary, "name")) cbf_failnez( cbf_select_row (handle->dictionary, nextrow)) cbf_failnez( cbf_get_value (handle->dictionary, &nextitem)) cbf_failnez( cbf_find_column (handle->dictionary, "name(hash_next)")) cbf_failnez( cbf_get_integervalue(handle->dictionary, &nextrow)) if (nextitem && !cbf_cistrcmp(nextitem, itemname)) { cbf_failnez( cbf_find_column (handle->dictionary, "value_type")) cbf_failnez( cbf_get_value (handle->dictionary, &enumvaluetype)) cbf_failnez( cbf_find_column (handle->dictionary, "value")) cbf_failnez( cbf_get_value (handle->dictionary, &enumvalue)) if (!cbf_cistrcmp(enumvaluetype,"value")) { if (!strcmp(enumvalue,valuestring) || (numb && doubleval == strtod(enumvalue, &endptr))) { valok = 1; break; } } else { colonpos = strchr(enumvalue,':'); if (colonpos) { strncpy(loval, enumvalue, (size_t)(colonpos-enumvalue)); loval[colonpos-enumvalue] = '\0'; strcpy(hival, colonpos+1); if (numb) { if (loval[0]!= '\0' && !strcmp(loval,",") && cbf_match(loval, "^-?(([0-9]+)|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?")){ sprintf(buffer,"illegal lower range value %s", loval); cbf_log(handle, buffer, CBF_LOGWARNING|CBF_LOGSTARTLOC); } if (hival[0]!= '\0' && !strcmp(hival,",") && cbf_match(hival, "^-?(([0-9]+)|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?")){ sprintf(buffer,"illegal higher range value %s", hival); cbf_log(handle, buffer, CBF_LOGWARNING|CBF_LOGSTARTLOC); } if (loval[0] == '\0' || !strcmp(loval,".")) { if ((!strcmp(enumvaluetype,"open_range") && doubleval < strtod(hival,&endptr)) || (!strcmp(enumvaluetype,"closed_range") && doubleval <= strtod(hival,&endptr))) { valok = 1; break; } else continue; } else { if (hival[0] == '\0' || !strcmp(hival,".")) { if ((!strcmp(enumvaluetype,"open_range") && doubleval > strtod(loval,&endptr)) || (!strcmp(enumvaluetype,"closed_range") && doubleval >= strtod(loval,&endptr))) { valok = 1; break; } else continue; } else { if ((!strcmp(enumvaluetype,"open_range") && doubleval > strtod(loval,&endptr) && doubleval < strtod(hival,&endptr)) || (!strcmp(enumvaluetype,"closed_range") && doubleval >= strtod(loval,&endptr) && doubleval <= strtod(hival,&endptr))) { valok = 1; break; } } } } else { if ( (loval[0] == '\0' && ( (!strcmp(enumvaluetype,"open_range") && cbf_cistrcmp(valuestring,hival) < 0) || cbf_cistrcmp(valuestring,hival) <= 0 ) ) || (hival[0] == '\0' && ( (!strcmp(enumvaluetype,"open_range") && cbf_cistrcmp(valuestring,loval) > 0) || cbf_cistrcmp(valuestring,loval) >= 0 ) ) || ((!strcmp(enumvaluetype,"open_range") && cbf_cistrcmp(valuestring,hival) < 0 && cbf_cistrcmp(valuestring,loval) > 0) || (cbf_cistrcmp(valuestring,hival) <= 0 && cbf_cistrcmp(valuestring,loval) >= 0))) { valok = 1; break; } else continue; } } } } } /* while ( nextrow >=0 ) */ if (!valok) { if (!generated) { sprintf(buffer,"%s value out of dictionary range", itemname); cbf_log(handle, buffer,CBF_LOGWARNING|CBF_LOGSTARTLOC); } else { sprintf(buffer,"%s generated value is out of dictionary range", itemname); cbf_log(handle, buffer,CBF_LOGWARNING|CBF_LOGSTARTLOC); } } } } } } } } } } } return 0; } /* WARNING -- THIS VERSION IS FOR TWO'S COMPLEMENT SYSTEMS */ /* Load mpint accumulator acc[1..acsize] with the contents of source containing an element of size elsize. If elsize if greater than sizeof (size of int) it must be a multiple of sizeof (unsigned int)*/ /* Load accumulator */ int cbf_mpint_load_acc(unsigned int * acc, size_t acsize, void * source, size_t elsize, int elsign, const char * border) { size_t bits; unsigned char * unsigned_char_data; int iint, numints; unsigned int sign; unsigned int sextend; bits = elsize * CHAR_BIT; numints = (bits + CHAR_BIT*sizeof (unsigned int) -1)/(CHAR_BIT*sizeof (unsigned int)); if (numints > acsize) return CBF_ARGUMENT; if (numints > 1 && numints*sizeof(int)*CHAR_BIT != bits) return CBF_ARGUMENT; sign = elsign?(1<<(bits-(numints-1)*sizeof(unsigned int)*CHAR_BIT-1)):0; sextend = 0; if (elsize < sizeof(unsigned int)) { sextend = (-(1 << (elsize * CHAR_BIT))); } unsigned_char_data = (unsigned char *)source; switch (elsize) { case (sizeof(char)): acc[0] = *unsigned_char_data; break; case (sizeof(short)): acc[0] = *((unsigned short *) unsigned_char_data); break; case (sizeof(int)): acc[0] = *((unsigned int *) unsigned_char_data); break; default: if (*border == 'b' || *border == 'B') { for (iint = numints; iint; iint--) { acc[iint-1] = *((unsigned int *)unsigned_char_data); unsigned_char_data += sizeof(unsigned int); } } else { for (iint = 0; iint < numints; iint++) { acc[iint] = *((unsigned int *)unsigned_char_data); unsigned_char_data += sizeof(unsigned int); } } break; } if (acc[numints-1] & sign) { acc[numints-1] |= sextend; if ( numints < acsize ) { for (iint = numints; iint < acsize; iint++) acc[iint] = ~0; } } else { if ( numints < acsize ) { for (iint = numints; iint < acsize; iint++) acc[iint] = 0; } } return 0; } /* Store accumulator */ int cbf_mpint_store_acc(unsigned int * acc, size_t acsize, void * dest, size_t elsize, int elsign, const char *border) { size_t bits; unsigned char * unsigned_char_data; int iint, numints; bits = elsize * CHAR_BIT; numints = (bits + CHAR_BIT*sizeof (unsigned int) -1)/(CHAR_BIT*sizeof (unsigned int)); if (numints > acsize) return CBF_FORMAT; unsigned_char_data = (unsigned char *)dest; switch (elsize) { case (sizeof(char)): *unsigned_char_data = acc[0]; break; case (sizeof(short)): *((unsigned short *) unsigned_char_data) = acc[0]; break; case (sizeof(int)): *((unsigned int *) unsigned_char_data) = acc[0]; break; default: if (*border == 'b' || *border == 'B') { for (iint = numints; iint; iint--) { *((unsigned int *)unsigned_char_data) = acc[iint-1]; unsigned_char_data += sizeof(unsigned int); } } else { for (iint = 0; iint < numints; iint++) { *((unsigned int *)unsigned_char_data) = acc[iint]; unsigned_char_data += sizeof(unsigned int); } } break; } return 0; } /* Clear accumulator */ int cbf_mpint_clear_acc(unsigned int * acc, size_t acsize) { int iint; for (iint=0; iint acsize) { if (add[acsize-1] &sign ) { for (iint = acsize; iint < acsize; iint++) if ( add[iint] != -1) return CBF_ARGUMENT; } else { for (iint = acsize; iint < acsize; iint++) if ( add[iint] != 0) return CBF_ARGUMENT; } } else if (acsize > addsize){ for (iint = addsize; iint < acsize; iint++) { if (carry) { cbf_failnez(cbf_mpint_increment_acc(acc+iint,acsize-iint)); } if ( acc[iint] & sign ) precarry++; carry = 0; if (precarry == 1 && !(acc[iint] &sign) ) carry = 1; precarry = 0; } } return 0; } /* Shift accumulator right */ int cbf_mpint_rightshift_acc(unsigned int * acc, size_t acsize, int shift) { int iint; size_t bigshift; unsigned int extrabits, xextrabits, mask; unsigned int sign; sign = 1 << (sizeof(unsigned int)*CHAR_BIT-1); if (shift < 0) return cbf_mpint_leftshift_acc(acc, acsize, -shift); bigshift = 0; if (shift >= sizeof(unsigned int)*CHAR_BIT) { extrabits = 0; if ((int)(acc[acsize-1])<0) extrabits = ~0; bigshift = shift/(sizeof(unsigned int)*CHAR_BIT); shift -= bigshift*sizeof(unsigned int)*CHAR_BIT; if (bigshift > acsize*sizeof(unsigned int)*CHAR_BIT) { return cbf_mpint_clear_acc(acc, acsize); } else { for (iint = acsize; iint-bigshift > 0; iint--) acc[iint-bigshift-1] = acc[iint-1]; for (iint = acsize; iint > acsize-bigshift+1; iint--) acc[iint-1] = extrabits; } } if (shift == 0) return 0; extrabits = 0; if (acc[acsize-1]&sign) extrabits = (~0)<<(sizeof(unsigned int)*CHAR_BIT-shift); mask = ~((~0)<<(sizeof(unsigned int)*CHAR_BIT-shift)); for (iint = acsize; iint; iint--) { xextrabits = acc[iint-1]<<(sizeof(unsigned int)*CHAR_BIT-shift); acc[iint-1] = ((acc[iint-1]>>shift)&mask)|extrabits; extrabits = xextrabits; } return 0; } /* Shift accumulator left */ int cbf_mpint_leftshift_acc(unsigned int * acc, size_t acsize, int shift) { int iint; size_t bigshift; unsigned int extrabits, xextrabits, mask; unsigned int sign; sign = 1 << (sizeof(unsigned int)*CHAR_BIT-1); if (shift < 0) return cbf_mpint_rightshift_acc(acc, acsize, -shift); bigshift = 0; if (shift >= sizeof(unsigned int)*CHAR_BIT) { extrabits = 0; bigshift = shift/(sizeof(unsigned int)*CHAR_BIT); shift -= bigshift*sizeof(unsigned int)*CHAR_BIT; if (bigshift > acsize*sizeof(unsigned int)*CHAR_BIT) { return cbf_mpint_clear_acc(acc, acsize); } else { for (iint = 0; iint+bigshift < acsize; iint++) acc[iint+bigshift] = acc[iint]; for (iint = 0; iint < bigshift; iint++) acc[iint] = extrabits; } } if (shift == 0) return 0; extrabits = 0; mask = -(1<>(sizeof(unsigned int)*CHAR_BIT-shift))&(~mask); acc[iint] = ((acc[iint]<> boffset) & 1) ^ tbit ) break; if (boffset == 0) { word --; testword = acc[word]; if ( word == 0 && testword == 0) { *bitlength = 1; return 0; } boffset = sizeof (int) * CHAR_BIT; } bcount --; boffset --; } *bitlength = bcount + 2; if (bcount > acsize * sizeof (int) * CHAR_BIT -2) *bitlength = acsize * sizeof (int) * CHAR_BIT; return 0; } /* Check value of type validity */ int cbf_check_type_contents (const char *type, const char *value){ if (!cbf_cistrcmp(type,"Achar")) { return cbf_match(value,"^[A-Za-z]$"); }else if (!cbf_cistrcmp(type,"ANchar")) { return cbf_match(value,"^[A-Za-z0-9]$"); }else if (!cbf_cistrcmp(type,"Element")) { /*Achar +*/ return cbf_match(value,"^[A-Za-z]+$"); }else if (!cbf_cistrcmp(type,"Tag")) { /*_ Ctag [._] Otag*/ return cbf_match(value,"^[_][A-Za-z0-9]+[_][._][A-Za-z0-9]+[_]$"); }else if (!cbf_cistrcmp(type,"Otag") || !cbf_cistrcmp(type,"Ctag") || !cbf_cistrcmp(type,"Filename")) { /* ANchar [_] +*/ return cbf_match(value,"^[A-Za-z0-9]+[_]$"); }else if (!cbf_cistrcmp(type,"Savename")) { /*$ Otag*/ return cbf_match(value,"[$][A-Za-z0-9]+[_]"); }else if (!cbf_cistrcmp(type,"Date")) { /*[0-9][0-9][0-9][0-9]-[0-1]?[0-9]-[0-3][0-9]*/ return cbf_match(value,"^[0-9][0-9][0-9][0-9]-[0-1]?[0-9]-[0-3][0-9]$"); }else if (!cbf_cistrcmp(type,"Version")) { /*Count [.] Count [.] Count*/ return cbf_match(value,"^[0-9]+[.][0-9]+[.][0-9]+$"); }else if (!cbf_cistrcmp(type,"Range")) { /*Integer ? : Integer ?*/ return cbf_match(value,"([+-]?[0-9]+)?:([+-]?[0-9]+)?"); }else if (!cbf_cistrcmp(type,"Digit")) { /*[0-9]*/ return cbf_match(value,"^[0-9]$"); }else if (!cbf_cistrcmp(type,"Count")) { /*[0-9]+*/ return cbf_match(value,"^[0-9]+$"); }else if (!cbf_cistrcmp(type,"Index")) { /*[1-9] Digit +*/ return cbf_match(value,"^[1-9]+[0-9]+"); }else if (!cbf_cistrcmp(type,"Integer")) { /*[+-]? Count*/ return cbf_match(value,"^[+-]?[0-9]+$"); }else if (!cbf_cistrcmp(type,"Binary")) { /*0b[0-1]+*/ return cbf_match(value,"^0b[0-1]+"); }else if (!cbf_cistrcmp(type,"Hexadecimal")) { /*0x[0-7a-fA-F]+*/ return cbf_match(value,"^0x[0-9a-fA-F]+$"); }else if (!cbf_cistrcmp(type,"Octal")) { /*0o[0-7]+*/ return cbf_match(value,"^0o[0-7]+$"); }else if (!cbf_cistrcmp(type,"Symop")) { /*[0-1]?[0-9]?[0-9]_[0-9][0-9][0-9]*/ return cbf_match(value,"^[0-1]?[0-9]?[0-9]_[0-9][0-9][0-9]$"); }else if (!cbf_cistrcmp(type,"YesorNo")) { return cbf_match(value,"^y(es)?$|^n(o)?$"); }else if (!cbf_cistrcmp(type,"Pchar") ||!cbf_cistrcmp(type,"Uri")) { /*[()\[\]_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*/ return cbf_match(value,""); }else if (!cbf_cistrcmp(type,"Text")) { /*[][ \n\t()_,.;:"&<>/\{}'`~!@#$%?+=*A-Za-z0-9|^-]*/ return cbf_match(value,""); }else if (!cbf_cistrcmp(type,"Code")) { /*[()\[\]_&<>{}~!@#$%?+=*A-Za-z0-9|^-]+*/ return cbf_match(value,""); }else if (!cbf_cistrcmp(type,"Dimension")) { /*[[] Count [,]? + []]*/ return cbf_match(value,""); }else if (!cbf_cistrcmp(type,"Float") || !cbf_cistrcmp(type,"Real")) { /*-?(([0-9]+)|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eE][+-]?[0-9]+)?*/ return cbf_match(value,"^-?(([0-9]+)|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eEdDqQ][+-]?[0-9]+)?"); }else if (!cbf_cistrcmp(type,"Imag")) { /*Real[jJ]*/ return cbf_match(value,"^-?((([0-9]+)|([0-9]*[.][0-9]+))([(][0-9]+[)])?([eEdDqQ][+-]?[0-9]+)?)?[iIjJ]"); }else if (!cbf_cistrcmp(type,"Label")) { /*[()\[\]_&<>{}~!@#$%?+=*A-Za-z0-9|^-]+*/ return cbf_match(value,""); }else if (!cbf_cistrcmp(type,"Formula")) { /*[()\[\]+-=*A-Za-z0-9]+*/ return cbf_match(value,""); } return 1; } /* Regex Match function */ int cbf_match(const char *string, char *pattern) { int status; regex_t re; if(regcomp(&re, pattern, REG_EXTENDED|REG_NOSUB) != 0) { return 1; } status = regexec(&re, string, (size_t)0, NULL, 0); regfree(&re); if(status != 0) { return 1; } return 0; } #ifdef CBF_USE_PYCIFRW /* Interpreter for dREL method expression */ int cbf_drel(cbf_handle handle, cbf_handle dict, const char *mainitemname, const char *datablock, const char *expression) { /* TODO: replace system calls with pipes */ FILE *f, *fdic, *fdata; char preprocess[512] = "python ~/bin/drel_prep.py "; char evaluate[512] = "python ~/bin/drelc.py "; f = fopen("method_expression", "w"); fprintf(f, "%s", expression); fclose(f); fdic = fopen("cbf_dictionary_debug", "w"); if (fdic) { cbf_failnez(cbf_write_widefile(dict,fdic,0,0,0,0)) } fdata = fopen("cbf_data_debug", "w"); if (fdata) { cbf_failnez(cbf_write_widefile(handle,fdata,0,0,0,0)) } strcat(preprocess, mainitemname); system(preprocess); strcat(evaluate, mainitemname); strcat(evaluate, " "); strcat(evaluate, datablock); system(evaluate); rename("method_expression", "method_expression.old"); return 0; } #endif /* Construct functions dictionary */ int cbf_construct_functions_dictionary(cbf_handle dict, const char *datablockname, const char *functionname) { char location[2049]; FILE * ffuncs; cbf_failnez( cbf_require_datablock (dict, "cbf_functions")) cbf_failnez( cbf_require_category (dict, "function_definitions")) cbf_failnez( cbf_require_column (dict, "function_location")) cbf_failnez( cbf_require_column (dict, "function_expression")) strcpy(location, datablockname); strcat(location, "."); strcat(location, functionname); if (!cbf_find_local_tag(dict,"function_location")) { cbf_failnez( cbf_set_value(dict, location)) } ffuncs = fopen("cbf_functions_debug","w"); cbf_failnez(cbf_write_widefile(dict,ffuncs,0,0,0,0)) return 0; } #ifdef __cplusplus } #endif ./CBFlib-0.9.2.2/src/cbf.i0000644000076500007650000000511711603702106013275 0ustar yayayaya// swig -Iinclude -java -package org.iucr.cbflib -outdir java cbf.i // javac -d . java/*.java // jar cf cbflib-0.8.0.jar org // gcc4 -fPIC -fpic -c cbf_wrap.c -I/dls_sw/dasc/jdk/jdk1.6.0_11/include -I/dls_sw/dasc/jdk/jdk1.6.0_11/include/linux -Iinclude // gcc4 -shared cbf_wrap.o -o solib/libcbf_wrap.so -Lsolib -lcbf %module cbf %{ /* Includes the header in the wrapper code */ #include "cbf_tree.h" #include "cbf.h" %} // Include support for C pointers %include "cpointer.i" // Wrap some C pointers in classes %pointer_class(size_t, sizetP); %pointer_class(int, intP); %pointer_class(unsigned int, uintP); %pointer_class(double, doubleP); // Wrap char** in functions %pointer_functions(const char *, charPP); // Cast to void * %pointer_cast(int *, void *, int_void); %pointer_cast(double *, void *, double_void); // Don't expose the memory allocation/de-allocation functions %ignore cbf_make_handle(cbf_handle *ppchs); %ignore cbf_free_handle(cbf_handle pchs); // Include support for C arrays %include "carrays.i" // Wrap some arrays in classes %array_class(int, intArray); %array_class(double, doubleArray); /* Parse the header file to generate wrappers */ %include "cbf_tree.h" %include "typemaps.i" %apply int *OUTPUT { CBF_NODETYPE *type }; %include "cbf.h" // Add in a custom proxy constructor and destructor %extend cbf_handle_struct { cbf_handle_struct() { cbf_handle_struct *pchs = 0; cbf_make_handle(&pchs); return pchs; } ~cbf_handle_struct() { cbf_free_handle(self); } } // File I/O functions FILE *fopen(char *name, char *mode); void fclose(FILE *); // swig -Iinclude -java -package org.iucr.cbflib -outdir java cbf.i // javac -d . java/*.java // jar cf cbflib-0.8.0.jar org // gcc4 -fPIC -fpic -c cbf_wrap.c -I/dls_sw/dasc/jdk/jdk1.6.0_11/include -I/dls_sw/dasc/jdk/jdk1.6.0_11/include/linux -Iinclude // gcc4 -shared cbf_wrap.o -o solib/libcbf_wrap.so -Lsolib -lcbf %module cbf %{ /* Includes the header in the wrapper code */ #include "cbf.h" %} %include "cpointer.i" // wrap some C pointers in classes %pointer_class(unsigned int, uintp) %pointer_class(double, doublep) // wrap char** in functions %pointer_functions(const char *, charpp) // Don't expose the memory allocation/de-allocation functions %ignore cbf_make_handle(cbf_handle *ppchs); %ignore cbf_free_handle(cbf_handle pchs); /* Parse the header file to generate wrappers */ %include "cbf.h" // Add in a custom proxy constructor and destructor %extend cbf_handle_struct { cbf_handle_struct() { cbf_handle_struct *pchs = 0; cbf_make_handle(&pchs); return pchs; } ~cbf_handle_struct() { cbf_free_handle(self); } } ./CBFlib-0.9.2.2/src/cbf_getopt.c0000644000076500007650000005221111603702106014646 0ustar yayayaya/********************************************************************** * cbf_getopt.c * * * * * * Created by Herbert J. Bernstein on 6/8/09. * * (C) Copyright 2009 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ #ifdef __cplusplus extern "C" { #endif #include #include #include #include #include static const char * cbf_getopt_locate_option(const char * options, char * optchar, const char * * longopt, int * hasvalue) { char c; if (optchar) *optchar = '\0'; if (longopt) *longopt = NULL; if (hasvalue) *hasvalue = 0; if (*options != '(' && *options != ':' && optchar)*optchar = *options; while ((c=*options)) { if (c=='(') { ++options; if (longopt) *longopt = options; while ((c=*options) && (c!=')')) { options++; } if (!c) { return options; } } else if (c==':') { if (hasvalue) *hasvalue = 1; options ++; if ((c=*options) && (c==':')) { if (hasvalue) *hasvalue = -1; options ++; } return options; } else if (c) { options ++; if ((c=*options) && (c=='(' || c==':')) continue; return options; } } return options; } /* create a cbf_getopt handle */ int cbf_make_getopt_handle(cbf_getopt_handle * handle) { *handle = NULL; cbf_failnez (cbf_alloc ((void **) handle, NULL, sizeof (cbf_getopt_struct), 1)) (*handle)->optstructs = NULL; cbf_onfailnez (cbf_alloc ((void **) &((*handle)->optstructs), &((*handle)->optstructs_capacity),sizeof(cbf_getopt_optstruct), 10), cbf_free((void **) handle, NULL)) (*handle)->optstructs_size = 0; (*handle)->optind = 0; /* ordinal of option in options */ (*handle)->options = NULL; return 0; } /* clear the data in a cbf_getopt handle */ static int cbf_clear_getopt_handle(cbf_getopt_handle handle) { cbf_getopt_optstruct * optstruct; size_t index; for (index = 0; index < handle->optstructs_size; index++) { optstruct = &(handle->optstructs[index]); if (optstruct->optstr) { cbf_failnez(cbf_free_text(&(optstruct->optstr),NULL)) } if (optstruct->optval) { cbf_failnez(cbf_free_text(&(optstruct->optval),NULL)) } } handle-> optstructs_size = 0; handle->optind = 0; if (handle->options) { cbf_failnez(cbf_free_text(&(handle->options),NULL)) } return 0; } /* free a cbf_getopt handle */ int cbf_free_getopt_handle(cbf_getopt_handle handle) { void *memblock; cbf_failnez( cbf_clear_getopt_handle(handle) ) memblock = (void *) handle; if (handle) { return cbf_free(&memblock, NULL); } return 0; } /* parse argc and argv into a newly created cbf_getopt */ int cbf_getopt_parse(cbf_getopt_handle handle, int argc, char ** argv, const char * options) { int ii, iii, ios; void * voptstructs; cbf_getopt_optstruct * optstruct; const char * opts; int hasvalue; const char * longopt; char optchar; size_t optlen; int optord; int foundopt; if (handle == NULL || argv == NULL ) return CBF_ARGUMENT; cbf_failnez( cbf_clear_getopt_handle(handle) ) /* Allocate as many opstruct slots as we have arguments */ if (handle->optstructs) { voptstructs = (void *)(handle->optstructs); cbf_failnez(cbf_realloc((void **) &voptstructs, &(handle->optstructs_capacity),sizeof(cbf_getopt_optstruct),argc)) } else { cbf_failnez(cbf_alloc((void **) &voptstructs, &(handle->optstructs_capacity),sizeof(cbf_getopt_optstruct),argc)) } handle->optstructs = (cbf_getopt_optstruct *)voptstructs; if (handle->options != NULL) { cbf_failnez(cbf_free_text((const char * *)&(handle->options),NULL)) } /* If options have been specified, use them. Otherwise default to "-" */ if (options) { handle->options = cbf_copy_string(NULL,options,0); } else { handle->options = cbf_copy_string(NULL,"-",0); } handle->optind = 0; for ( ii=1; ii < argc; ii++) { /* Prepare the next slot */ optstruct = &((handle->optstructs)[(handle->optind)++]); (handle->optstructs_size)++; optstruct->optopt = 0; optstruct->optord = -1; optstruct->optstr = NULL; optstruct->optval = NULL; /* on --, end the options scan */ if ( !strcmp(argv[ii],"--") ) { /* copy all remaining arguments as unflagged values */ break; } /* process a --option case */ if (!strncmp("--",argv[ii],2)) { optstruct->optstr = cbf_copy_string(NULL,2+argv[ii],0); opts = options; if (*opts=='-' || *opts =='+') opts++; optlen = strlen(argv[ii]+2); optord = -1; foundopt = 0; do { opts= cbf_getopt_locate_option(opts, &optchar, &longopt, &hasvalue); optord++; if (longopt && !strncmp(longopt,argv[ii]+2,optlen) && longopt[optlen]==')') { optstruct->optopt = optchar; optstruct->optord = optord; optstruct->optval = NULL; if (ii+1 < argc && (hasvalue >0 || (*(argv[ii+1])!='-'&& hasvalue < 0) )) { optstruct->optval = cbf_copy_string(NULL,argv[ii+1],0); ii++; foundopt++; break; } } } while (*opts); if (foundopt) continue; if (*options == '-') { optstruct->optopt = '\1'; optstruct->optord = -1; optstruct->optval = NULL; if (ii+1 < argc && *(argv[ii+1])!='-' ) { optstruct->optval = cbf_copy_string(NULL,argv[ii+1],0); ii++; break; } continue; } /* this is not an expected long option and the option string does not have a leading '-', therefore this is simply a non-option value */ if (*options=='+') break; optstruct->optval = cbf_copy_string(NULL,argv[ii],0); optstruct->optopt = 0; optstruct->optord = -1; cbf_failnez(cbf_free_text(&(optstruct->optstr),NULL)) optstruct->optstr = NULL; continue; } /* now for the single '-' case marking a lone letter option */ if (*(argv[ii]) == '-' && strlen(argv[ii]) > 1 ) { char xc[2]; xc[0] = argv[ii][1]; xc[1] = '\0'; optstruct->optstr = cbf_copy_string(NULL,xc,0); opts = options; if (*opts=='-' || *opts =='+') opts++; optlen = 1; optord = -1; foundopt = 0; do { opts= cbf_getopt_locate_option(opts, &optchar, &longopt,&hasvalue); optord++; if (xc[0] == optchar) { optstruct->optopt = optchar; optstruct->optord = optord; optstruct->optval = NULL; if ((strlen(argv[ii]+2) > 0) || (ii+1 < argc && (hasvalue >0 || (*(argv[ii+1])!='-'&& hasvalue < 0) ))) { if (strlen(argv[ii]+2) > 0) { optstruct->optval = cbf_copy_string(NULL,argv[ii]+2,0); } else { optstruct->optval = cbf_copy_string(NULL,argv[ii+1],0); ii++; } } foundopt++; break; } } while (*opts); if (foundopt) continue; if (*options == '-') { optstruct->optopt = '\1'; optstruct->optord = -1; optstruct->optval = NULL; if (ii+1 < argc && *(argv[ii+1])!='-' ) { optstruct->optval = cbf_copy_string(NULL,argv[ii+1],0); ii++; break; } continue; }; /* this is not an expected short option and the option string does not have a leading '-', therefore this is simply a non-option value */ if (*options=='+') break; optstruct->optval = cbf_copy_string(NULL,argv[ii],0); optstruct->optopt = 0; optstruct->optord = -1; cbf_failnez(cbf_free_text(&(optstruct->optstr),NULL)) optstruct->optstr = NULL; continue; } /* All that is left is to treat this as a non-option value */ optstruct->optval = cbf_copy_string(NULL,argv[ii],0); optstruct->optopt = 0; optstruct->optord = -1; optstruct->optstr = NULL; if (*options=='+') break; } /* ii is the last argument processed, the remaining arguments get added at the end */ ios = handle->optstructs_size; for (iii = ii+1; iii < argc; iii++) { optstruct = &((handle->optstructs)[(handle->optind)++]); (handle->optstructs_size)++; optstruct->optval = cbf_copy_string(NULL,argv[iii],0); optstruct->optopt = 0; optstruct->optord = -1; optstruct->optstr = NULL; } /* if *options is not '-', then all non-options in obstructs need to be sorted to the end of the list */ iii = ios-1; while (iii >= 0) { cbf_getopt_optstruct temp; optstruct = &((handle->optstructs)[iii]); /* Any option with no option ordinal moves up to index ios-1 */ if (optstruct->optord < 0) { if (iii < ios-1) { memmove((void *)(&temp),(void *)optstruct,sizeof(cbf_getopt_optstruct)); for (ii = iii; ii < ios-1; ii++) { memmove((void *)(&((handle->optstructs)[ii])), (void *)(&((handle->optstructs)[ii+1])), sizeof(cbf_getopt_optstruct)); } memmove((void *)(&((handle->optstructs)[ios-1])),(void *)(&temp),sizeof(cbf_getopt_optstruct)); } ios --; } iii--; } return 0; } /* Get first option from a cbf_getopt handle */ int cbf_rewind_getopt_option ( cbf_getopt_handle handle ) { if ( !handle ) return CBF_ARGUMENT; handle->optind = 0 ; if ( handle->optind >= handle->optstructs_size) return CBF_NOTFOUND; return 0; } /* Get next option from a cbf_getopt handle */ int cbf_next_getopt_option ( cbf_getopt_handle handle ){ if ( !handle ) return CBF_ARGUMENT; handle->optind++; if ( handle->optind >= handle->optstructs_size) return CBF_NOTFOUND; return 0; } /* Get option by number (0 ... ) from a cbf_getopt handle */ int cbf_select_getopt_option ( cbf_getopt_handle handle, unsigned int option ) { if ( !handle ) return CBF_ARGUMENT; if ( option < 0 || option >= handle->optstructs_size) return CBF_ARGUMENT; handle->optind = option; return 0; } /* Count the options in a cbf_getopt handle */ int cbf_count_getopt_options ( cbf_getopt_handle handle, unsigned int * options ) { if ( !handle ) return CBF_ARGUMENT; if ( options ) *options = handle->optstructs_size; return 0; } /* Get the data for an option */ int cbf_get_getopt_data ( cbf_getopt_handle handle, int * optopt, int * optord, const char * * optstr, const char * * optval) { cbf_getopt_optstruct * optstruct; if ( !handle ) return CBF_ARGUMENT; if ( handle->optind < 0 || handle->optind >= handle->optstructs_size) return CBF_NOTFOUND; optstruct = &(handle->optstructs[handle->optind]); if (optopt) *optopt = optstruct->optopt; if (optord) *optord = optstruct->optord; if (optstr) *optstr = optstruct->optstr; if (optval) *optval = optstruct->optval; return 0; } #ifdef __cplusplus } #endif ./CBFlib-0.9.2.2/src/cbf_copy.c0000644000076500007650000030522311603702106014322 0ustar yayayaya/********************************************************************** * cbf_copy.c -- cbflib copy functions * * * * Version 0.9.1 23 February 2010 * * * * (C) Copyright 2010 Herbert J. Bernstein * * * * Part of the CBFlib API * * by * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term ‘this software’, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifdef __cplusplus extern "C" { #endif #include "cbf.h" #include "cbf_copy.h" #include "cbf_alloc.h" #include "cbf_string.h" #include #include #include /* cbf_copy_cbf -- copy cbfin to cbfout */ int cbf_copy_cbf(cbf_handle cbfout, cbf_handle cbfin, const int compression, const int dimflag) { unsigned int blocknum, blocks; const char * datablock_name; cbf_failnez (cbf_rewind_datablock(cbfin)) cbf_failnez (cbf_count_datablocks(cbfin, &blocks)) for (blocknum = 0; blocknum < blocks; blocknum++ ) { cbf_failnez (cbf_select_datablock(cbfin, blocknum)) cbf_failnez (cbf_datablock_name(cbfin, &datablock_name)) cbf_failnez (cbf_copy_datablock(cbfout, cbfin, datablock_name, compression, dimflag)) } return 0; } /* cbf_copy_category -- copy the current category from cbfin specified category in cbfout */ int cbf_copy_category(cbf_handle cbfout, cbf_handle cbfin, const char * category_name, const int compression, const int dimflag) { unsigned int rows, columns; unsigned int rownum, colnum; const char * column_name; const char * value; cbf_failnez(cbf_force_new_category(cbfout,category_name)) cbf_failnez(cbf_count_rows(cbfin,&rows)); cbf_failnez(cbf_count_columns(cbfin,&columns)); /* Transfer the column names from cbfin to cbfout */ if ( ! cbf_rewind_column(cbfin) ) { do { cbf_failnez(cbf_column_name(cbfin, &column_name)) cbf_failnez(cbf_new_column(cbfout, column_name)) } while ( ! cbf_next_column(cbfin) ); cbf_failnez(cbf_rewind_column(cbfin)) cbf_failnez(cbf_rewind_row(cbfin)) } /* Transfer to rows from cbfin to cbfout */ for (rownum = 0; rownum < rows; rownum++ ) { cbf_failnez (cbf_select_row(cbfin, rownum)) cbf_failnez (cbf_new_row(cbfout)) cbf_rewind_column(cbfin); for (colnum = 0; colnum < columns; colnum++ ) { const char *typeofvalue; cbf_failnez (cbf_select_column(cbfin, colnum)) cbf_failnez (cbf_column_name(cbfin, &column_name)) if ( ! cbf_get_value(cbfin, &value) ) { if (compression && value && column_name && !cbf_cistrcmp("compression_type",column_name)) { cbf_failnez (cbf_select_column(cbfout, colnum)) switch (compression&CBF_COMPRESSION_MASK) { case (CBF_NONE): cbf_failnez (cbf_set_value (cbfout,"none")) cbf_failnez (cbf_set_typeofvalue(cbfout,"word")) break; case (CBF_CANONICAL): cbf_failnez (cbf_set_value (cbfout,"canonical")) cbf_failnez (cbf_set_typeofvalue(cbfout,"word")) break; case (CBF_PACKED): cbf_failnez (cbf_set_value (cbfout,"packed")) cbf_failnez (cbf_set_typeofvalue(cbfout,"word")) break; case (CBF_PACKED_V2): cbf_failnez (cbf_set_value (cbfout,"packed_v2")) cbf_failnez (cbf_set_typeofvalue(cbfout,"word")) break; case (CBF_BYTE_OFFSET): cbf_failnez (cbf_set_value (cbfout,"byte_offsets")) cbf_failnez (cbf_set_typeofvalue(cbfout,"word")) break; case (CBF_PREDICTOR): cbf_failnez (cbf_set_value (cbfout,"predictor")) cbf_failnez (cbf_set_typeofvalue(cbfout,"word")) break; default: cbf_failnez (cbf_set_value (cbfout,".")) cbf_failnez (cbf_set_typeofvalue(cbfout,"null")) break; } if (compression&CBF_FLAG_MASK) { if (compression&CBF_UNCORRELATED_SECTIONS) { cbf_failnez (cbf_require_column (cbfout, "compression_type_flag")) cbf_failnez (cbf_set_value (cbfout, "uncorrelated_sections")) cbf_failnez (cbf_set_typeofvalue (cbfout, "word")) } else if (compression&CBF_FLAT_IMAGE) { cbf_failnez (cbf_require_column (cbfout, "compression_type_flag")) cbf_failnez (cbf_set_value (cbfout, "flat")) cbf_failnez (cbf_set_typeofvalue (cbfout, "word")) } } else { if (!cbf_find_column(cbfout, "compression_type_flag")) { cbf_failnez (cbf_set_value (cbfout,".")) cbf_failnez (cbf_set_typeofvalue(cbfout,"null")) } } } else if (compression && value && column_name && !cbf_cistrcmp("compression_type_flag",column_name)) { if (compression&CBF_FLAG_MASK) { if (compression&CBF_UNCORRELATED_SECTIONS) { cbf_failnez (cbf_require_column (cbfout, "compression_type_flag")) cbf_failnez (cbf_set_value (cbfout, "uncorrelated_sections")) cbf_failnez (cbf_set_typeofvalue (cbfout, "word")) } else if (compression&CBF_FLAT_IMAGE) { cbf_failnez (cbf_require_column (cbfout, "compression_type_flag")) cbf_failnez (cbf_set_value (cbfout, "flat")) cbf_failnez (cbf_set_typeofvalue (cbfout, "word")) } } else { if (!cbf_find_column(cbfout, "compression_type_flag")) { cbf_failnez (cbf_set_value (cbfout,".")) cbf_failnez (cbf_set_typeofvalue(cbfout,"null")) } } } else { cbf_failnez (cbf_get_typeofvalue(cbfin, &typeofvalue)) cbf_failnez (cbf_select_column(cbfout, colnum)) cbf_failnez (cbf_set_value(cbfout, value)) cbf_failnez (cbf_set_typeofvalue(cbfout, typeofvalue)) } } else { void * array; int binary_id, elsigned, elunsigned; size_t elements,elements_read, elsize; int minelement, maxelement; unsigned int cifcompression; int realarray; const char *byteorder; size_t dim1, dim2, dim3, padding; cbf_failnez(cbf_get_arrayparameters_wdims_fs( cbfin, &cifcompression, &binary_id, &elsize, &elsigned, &elunsigned, &elements, &minelement, &maxelement, &realarray, &byteorder, &dim1, &dim2, &dim3, &padding)) if ((array=malloc(elsize*elements))) { cbf_failnez (cbf_select_column(cbfout,colnum)) if (!realarray) { cbf_failnez (cbf_get_integerarray( cbfin, &binary_id, array, elsize, elsigned, elements, &elements_read)) if (dimflag == CBF_HDR_FINDDIMS && dim1==0) { cbf_get_arraydimensions(cbfin,NULL,&dim1,&dim2,&dim3); } cbf_failnez(cbf_set_integerarray_wdims_fs( cbfout, compression, binary_id, array, elsize, elsigned, elements, "little_endian", dim1, dim2, dim3, 0)) } else { cbf_failnez (cbf_get_realarray( cbfin, &binary_id, array, elsize, elements, &elements_read)) if (dimflag == CBF_HDR_FINDDIMS && dim1==0) { cbf_get_arraydimensions(cbfin,NULL,&dim1,&dim2,&dim3); } cbf_failnez(cbf_set_realarray_wdims_fs( cbfout, compression, binary_id, array, elsize, elements, "little_endian", dim1, dim2, dim3, 0)) } free(array); } else { return CBF_ALLOC; } } } } return 0; } /* cbf_copy_datablock -- copy the current datablock from cbfin to the next datablock in cbfout */ int cbf_copy_datablock (cbf_handle cbfout, cbf_handle cbfin, const char * datablock_name, const int compression, const int dimflag) { CBF_NODETYPE itemtype; const char *category_name; const char *saveframe_name; unsigned int itemnum, blockitems,catnum,categories; cbf_failnez (cbf_force_new_datablock(cbfout, datablock_name)) if ( !cbf_rewind_blockitem(cbfin, &itemtype) ) { cbf_failnez (cbf_count_blockitems(cbfin, &blockitems)) for (itemnum = 0; itemnum < blockitems; itemnum++) { cbf_failnez(cbf_select_blockitem(cbfin, itemnum, &itemtype)) if (itemtype == CBF_CATEGORY) { cbf_failnez(cbf_category_name(cbfin,&category_name)) cbf_failnez(cbf_copy_category(cbfout,cbfin,category_name, compression, dimflag)) } else { cbf_failnez(cbf_saveframe_name(cbfin,&saveframe_name)) cbf_force_new_saveframe(cbfout, saveframe_name); if ( !cbf_rewind_category(cbfin) ) { cbf_failnez (cbf_count_categories(cbfin, &categories)) for (catnum = 0; catnum < categories; catnum++) { cbf_select_category(cbfin, catnum); cbf_category_name(cbfin,&category_name); cbf_failnez(cbf_copy_category(cbfout,cbfin,category_name, compression, dimflag)) } } } } } return 0; } /* cbf_copy_value -- copy the current value from cbfin to cbfout, specifying the target category, column, rownum, compression, dimension details, element type, size and sign */ int cbf_copy_value(cbf_handle cbfout, cbf_handle cbfin, const char * category_name, const char * column_name, const unsigned int rownum, const int compression, const int dimflag, const int eltype, const int elsize, const int elsign, const double cliplow, const double cliphigh) { unsigned int rows; const char * value; char * border; #ifndef CBF_USE_LONG_LONG size_t lobyte, hibyte; double vallow, valhigh; #endif cbf_get_local_integer_byte_order(&border); if ( ! (eltype==0 || eltype==CBF_CPY_SETINTEGER || eltype==CBF_CPY_SETREAL)) return CBF_ARGUMENT; if ( ! (elsign==0 || elsign==CBF_CPY_SETUNSIGNED || elsign==CBF_CPY_SETSIGNED)) return CBF_ARGUMENT; if (elsize != 0 && elsize != sizeof (long int) && #ifdef CBF_USE_LONG_LONG elsize != sizeof(long long int) && #else elsize != 2* sizeof (long int) && #endif elsize != sizeof (short int) && elsize != sizeof (char)) return CBF_ARGUMENT; cbf_failnez(cbf_require_category(cbfout,category_name)) cbf_failnez(cbf_count_rows(cbfout,&rows)); while (rows < rownum+1) { cbf_failnez(cbf_new_row(cbfout)) rows++; } cbf_failnez(cbf_require_column(cbfout,column_name)) cbf_failnez(cbf_select_row(cbfout,rownum)) if ( ! cbf_get_value(cbfin, &value) ) { if (compression && value && !cbf_cistrcmp("compression_type",column_name)) { switch (compression&CBF_COMPRESSION_MASK) { case (CBF_NONE): cbf_failnez (cbf_set_value (cbfout,"none")) cbf_failnez (cbf_set_typeofvalue(cbfout,"word")) break; case (CBF_CANONICAL): cbf_failnez (cbf_set_value (cbfout,"canonical")) cbf_failnez (cbf_set_typeofvalue(cbfout,"word")) break; case (CBF_PACKED): cbf_failnez (cbf_set_value (cbfout,"packed")) cbf_failnez (cbf_set_typeofvalue(cbfout,"word")) break; case (CBF_PACKED_V2): cbf_failnez (cbf_set_value (cbfout,"packed_v2")) cbf_failnez (cbf_set_typeofvalue(cbfout,"word")) break; case (CBF_BYTE_OFFSET): cbf_failnez (cbf_set_value (cbfout,"byte_offsets")) cbf_failnez (cbf_set_typeofvalue(cbfout,"word")) break; case (CBF_PREDICTOR): cbf_failnez (cbf_set_value (cbfout,"predictor")) cbf_failnez (cbf_set_typeofvalue(cbfout,"word")) break; default: cbf_failnez (cbf_set_value (cbfout,".")) cbf_failnez (cbf_set_typeofvalue(cbfout,"null")) break; } if (compression&CBF_FLAG_MASK) { if (compression&CBF_UNCORRELATED_SECTIONS) { cbf_failnez (cbf_require_column (cbfout, "compression_type_flag")) cbf_failnez (cbf_set_value (cbfout, "uncorrelated_sections")) cbf_failnez (cbf_set_typeofvalue (cbfout, "word")) } else if (compression&CBF_FLAT_IMAGE) { cbf_failnez (cbf_require_column (cbfout, "compression_type_flag")) cbf_failnez (cbf_set_value (cbfout, "flat")) cbf_failnez (cbf_set_typeofvalue (cbfout, "word")) } } else { if (!cbf_find_column(cbfout, "compression_type_flag")) { cbf_failnez (cbf_set_value (cbfout,".")) cbf_failnez (cbf_set_typeofvalue(cbfout,"null")) } } } else if (compression && value && !cbf_cistrcmp("compression_type_flag",column_name)) { if (compression&CBF_FLAG_MASK) { if (compression&CBF_UNCORRELATED_SECTIONS) { cbf_failnez (cbf_require_column (cbfout, "compression_type_flag")) cbf_failnez (cbf_set_value (cbfout, "uncorrelated_sections")) cbf_failnez (cbf_set_typeofvalue (cbfout, "word")) } else if (compression&CBF_FLAT_IMAGE) { cbf_failnez (cbf_require_column (cbfout, "compression_type_flag")) cbf_failnez (cbf_set_value (cbfout, "flat")) cbf_failnez (cbf_set_typeofvalue (cbfout, "word")) } } else { if (!cbf_find_column(cbfout, "compression_type_flag")) { cbf_failnez (cbf_set_value (cbfout,".")) cbf_failnez (cbf_set_typeofvalue(cbfout,"null")) } } } else { const char *typeofvalue; cbf_failnez (cbf_get_typeofvalue(cbfin, &typeofvalue)) cbf_failnez (cbf_set_value(cbfout, value)) cbf_failnez (cbf_set_typeofvalue(cbfout, typeofvalue)) } } else { void * array; int binary_id, elsigned, elunsigned; size_t elements,elements_read, oelsize; int minelement, maxelement; unsigned int cifcompression; int realarray; const char *byteorder; size_t dim1, dim2, dim3, padding; cbf_failnez(cbf_get_arrayparameters_wdims_fs( cbfin, &cifcompression, &binary_id, &oelsize, &elsigned, &elunsigned, &elements, &minelement, &maxelement, &realarray, &byteorder, &dim1, &dim2, &dim3, &padding)) if (oelsize != sizeof (long int) && #ifdef CBF_USE_LONG_LONG oelsize != sizeof(long long int) && #else oelsize != 2* sizeof (long int) && #endif oelsize != sizeof (short int) && oelsize != sizeof (char)) return CBF_ARGUMENT; if ((array=malloc(oelsize*elements))) { size_t nelsize; int nelsigned, nelunsigned; int icount, jcount, fill; size_t xelsize; nelsize = oelsize; if (elsize != 0) nelsize = elsize; xelsize = nelsize; if (oelsize < nelsize) xelsize = oelsize; nelsigned = elsigned; nelunsigned = elunsigned; if (elsign & CBF_CPY_SETSIGNED) nelsigned = 1; if (elsign & CBF_CPY_SETUNSIGNED) nelunsigned = 1; if (!realarray) { cbf_onfailnez (cbf_get_integerarray( cbfin, &binary_id, array, elsize, elsigned, elements, &elements_read), {free(array);}) if (dimflag == CBF_HDR_FINDDIMS && dim1==0) { cbf_get_arraydimensions(cbfin,NULL,&dim1,&dim2,&dim3); } if (((eltype &(CBF_CPY_SETINTEGER)) || eltype == 0) && (elsize == 0 || elsize==oelsize) && (elsign == 0 || ((elsign & CBF_CPY_SETSIGNED) && elsigned) || ((elsign & CBF_CPY_SETUNSIGNED) && elunsigned)) && cliplow >= cliphigh) { cbf_onfailnez(cbf_set_integerarray_wdims_fs( cbfout, compression, binary_id, array, oelsize, elsigned, elements, "little_endian", dim1, dim2, dim3, 0),{free(array);} ) free(array); } else { void * narray; int loword, hiword; unsigned long maxlonguint; double onemore; maxlonguint = ~0; onemore = ((double)maxlonguint)+1.; if (toupper(border[0])=='L') { loword = 0; hiword = 1; } else { loword = 1; hiword = 0; } if ((narray=malloc(nelsize*elements))) { if (cliplow < cliphigh) { double doval; for (icount = 0; icount < elements; icount++) { switch (oelsize) { case (sizeof(char)): if (elsigned) doval = (double)((signed char *)array)[icount]; else doval = (double)((unsigned char *)array)[icount]; if (doval < cliplow) doval = cliplow; if (doval > cliphigh) doval = cliphigh; if (elsigned) ((signed char *)array)[icount] = (signed char)doval; else ((unsigned char *)array)[icount] = (unsigned char)doval; break; case (sizeof(short int)): if (elsigned) doval = (double)((signed short int *)array)[icount]; else doval = (double)((unsigned short int *)array)[icount]; if (doval < cliplow) doval = cliplow; if (doval > cliphigh) doval = cliphigh; if (elsigned) ((signed char *)array)[icount] = (signed short int)doval; else ((unsigned char *)array)[icount] = (unsigned short int)doval; break; case (sizeof(long int)): if (elsigned) doval = (double)((signed long int *)array)[icount]; else doval = (double)((unsigned long int *)array)[icount]; if (doval < cliplow) doval = cliplow; if (doval > cliphigh) doval = cliphigh; if (elsigned) ((signed char *)array)[icount] = (signed long int)doval; else ((unsigned char *)array)[icount] = (unsigned long int)doval; break; #ifdef CBF_USE_LONG_LONG case (sizeof(long long int)): if (elsigned) doval = (double)((signed long long int *)array)[icount]; else doval = (double)((unsigned long long int *)array)[icount]; if (doval < cliplow) doval = cliplow; if (doval > cliphigh) doval = cliphigh; if (elsigned) ((signed char *)array)[icount] = (signed long long int)doval; else ((unsigned char *)array)[icount] = (unsigned long long int)doval; break; #endif default: free(narray); free(array); return CBF_ARGUMENT; } } } if ((eltype & CBF_CPY_SETINTEGER) || eltype == 0 ) { /* integer to integer conversion */ if (toupper(border[0])=='L') { for (icount = 0; icount < elements; icount++ ) { memmove(((unsigned char *)narray)+icount*elsize,((unsigned char *)array)+icount*oelsize,xelsize); if (xelsize < nelsize) { fill = 0; if (nelsigned) fill = (((signed char *)array)[icount*oelsize+oelsize-1]<0)?(~0):0; if (nelunsigned) for(jcount=0;jcount<=nelsize-oelsize;jcount++) ((signed char *)narray)[icount*elsize+xelsize+jcount]=fill; } } } else { for (icount = 0; icount < elements; icount++ ) { for (jcount = xelsize-1; jcount>=0; jcount--) { ((unsigned char *)narray)[icount*elsize+jcount] = ((unsigned char *)array)[icount*oelsize+jcount]; if (xelsize < nelsize) { fill = 0; if (nelsigned) fill = (((signed char *)array)[icount*oelsize]<0)?(~0):0; if (nelunsigned) for(jcount=0;jcount<=nelsize-oelsize;jcount++) ((signed char *)narray)[icount*elsize+jcount]=fill; } } } } cbf_onfailnez(cbf_set_integerarray_wdims_fs( cbfout, compression, binary_id, narray, elsize, nelsigned, elements, "little_endian", dim1, dim2, dim3, 0), {free(array); free(narray);}) free(narray); free(array); } else { /* integer to real conversion */ double xvalue; switch (oelsize) { case sizeof(char): if (elsigned) { for (icount = 0; icount < elements; icount++) { xvalue = ((signed char *)array)[icount]; if (elsize == sizeof(double)) ((double *)narray)[icount] = xvalue; else if (elsize == sizeof(float)) ((float *)narray)[icount] = xvalue; else { free(narray); free(array); return CBF_ARGUMENT;} } } else { for (icount = 0; icount < elements; icount++) { xvalue = ((unsigned char *)array)[icount]; if (elsize == sizeof(double)) ((double *)narray)[icount] = xvalue; else if (elsize == sizeof(float)) ((float *)narray)[icount] = xvalue; else { free(narray); free(array); return CBF_ARGUMENT;} } } break; case sizeof(short int): if (elsigned) { for (icount = 0; icount < elements; icount++) { xvalue = ((signed short int *)array)[icount]; if (elsize == sizeof(double)) ((double *)narray)[icount] = xvalue; else if (elsize == sizeof(float)) ((float *)narray)[icount] = xvalue; else { free(narray); free(array); return CBF_ARGUMENT;} } } else { for (icount = 0; icount < elements; icount++) { xvalue = ((unsigned short int *)array)[icount]; if (elsize == sizeof(double)) ((double *)narray)[icount] = xvalue; else if (elsize == sizeof(float)) ((float *)narray)[icount] = xvalue; else { free(narray); free(array); return CBF_ARGUMENT;} } } break; case sizeof(long int): if (elsigned) { for (icount = 0; icount < elements; icount++) { xvalue = ((signed long int *)array)[icount]; if (elsize == sizeof(double)) ((double *)narray)[icount] = xvalue; else if (elsize == sizeof(float)) ((float *)narray)[icount] = xvalue; else { free(narray); free(array); return CBF_ARGUMENT;} } } else { for (icount = 0; icount < elements; icount++) { xvalue = ((unsigned long int *)array)[icount]; if (elsize == sizeof(double)) ((double *)narray)[icount] = xvalue; else if (elsize == sizeof(float)) ((float *)narray)[icount] = xvalue; else { free(narray); free(array); return CBF_ARGUMENT;} } } break; #ifdef CBF_USE_LONG_LONG case sizeof(long long int): if (elsigned) { for (icount = 0; icount < elements; icount++) { xvalue = ((signed long long int *)array)[icount]; if (elsize == sizeof(double)) ((double *)narray)[icount] = xvalue; else if (elsize == sizeof(float)) ((float *)narray)[icount] = xvalue; else { free(narray); free(array); return CBF_ARGUMENT;} } } else { for (icount = 0; icount < elements; icount++) { xvalue = ((unsigned long long int *)array)[icount]; if (elsize == sizeof(double)) ((double *)narray)[icount] = xvalue; else if (elsize == sizeof(float)) ((float *)narray)[icount] = xvalue; else { free(narray); free(array); return CBF_ARGUMENT;} } } break; #else case 2* sizeof(long int): if (elsigned) { unsigned long yvalue[2]; for (icount = 0; icount < 2* elements; icount++) { yvalue[0] = ((unsigned long int *)array)[2*icount]; yvalue[1] = ((unsigned long int *)array)[2*icount+1]; if ((long)yvalue[hiword]>0) { xvalue = ((double)yvalue[hiword])*onemore+(double)yvalue[loword]; } else { xvalue = -((double)(-yvalue[hiword])*onemore-(double)yvalue[loword]); } if (elsize == sizeof(double)) ((double *)narray)[icount] = xvalue; else if (elsize == sizeof(float)) ((float *)narray)[icount] = xvalue; else { free(narray); free(array); return CBF_ARGUMENT;} } } else { unsigned long yvalue[2]; for (icount = 0; icount < 2* elements; icount++) { yvalue[0] = ((unsigned long int *)array)[2*icount]; yvalue[1] = ((unsigned long int *)array)[2*icount+1]; xvalue = ((double)yvalue[hiword])*onemore+(double)yvalue[loword]; if (elsize == sizeof(double)) ((double *)narray)[icount] = xvalue; else if (elsize == sizeof(float)) ((float *)narray)[icount] = xvalue; else { free(narray); free(array); return CBF_ARGUMENT;} } } break; #endif default: free(narray); free(array); return CBF_ARGUMENT; } cbf_onfailnez(cbf_set_realarray_wdims_fs( cbfout, compression, binary_id, narray, elsize, elements, "little_endian", dim1, dim2, dim3, 0), { free(narray); free(array);}) free(narray); free(array); } } else { free(array); return CBF_ALLOC; } } } else { cbf_onfailnez (cbf_get_realarray( cbfin, &binary_id, array, oelsize, elements, &elements_read), {free(array);}) if (dimflag == CBF_HDR_FINDDIMS && dim1==0) { cbf_get_arraydimensions(cbfin,NULL,&dim1,&dim2,&dim3); } if (((eltype &(CBF_CPY_SETREAL)) || eltype == 0) && (elsize == 0 || elsize==oelsize) && cliplow >= cliphigh) { cbf_failnez(cbf_set_realarray_wdims_fs( cbfout, compression, binary_id, array, oelsize, elements, "little_endian", dim1, dim2, dim3, 0)) free(array); } else { void * narray; double valtemp; if ((narray=malloc(nelsize*elements))) { if (cliplow < cliphigh) { double doval; for (icount = 0; icount < elements; icount++) { switch (oelsize) { case (sizeof(float)): doval = (double)((float *)array)[icount]; if (doval < cliplow) doval = cliplow; if (doval > cliphigh) doval = cliphigh; ((float *)array)[icount] = (float)doval; break; case (sizeof(double)): doval = ((double *)array)[icount]; if (doval < cliplow) doval = cliplow; if (doval > cliphigh) doval = cliphigh; ((double *)array)[icount] = doval; break; default: free(narray); free(array); return CBF_ARGUMENT; } } } if ((eltype & CBF_CPY_SETINTEGER) || eltype == 0 ) { /* real to integer conversion */ double maxval, minval; #ifndef CBF_USE_LONG_LONG double onemore; unsigned long int maxlongval; maxlongval = ~0L; onemore = ((double)maxlongval)+1.; #endif if (nelunsigned) { minval = 0.; switch( nelsize ) { case 1: maxval = (double)(0xFF); break; case 2: maxval = (double)(0xFFFFU); break; case 4: maxval = (double)(0xFFFFFFFFUL); break; case 8: maxval = ((double)(0xFFFFFFFFUL))*(2.+((double)(0xFFFFFFFFUL))); break; default: free(array); free(narray); return CBF_ARGUMENT; } } else if (nelsigned) { switch( nelsize ) { case 1: maxval = (double)(0x7F); break; case 2: maxval = (double)(0x7FFFU); break; case 4: maxval = (double)(0x7FFFFFFFUL); break; case 8: maxval = ((double)(0xFFFFFFFFUL)) + ((double)(0x7FFFFFFFL))*(1.+((double)(0xFFFFFFFFUL))); break; default: free(array); free(narray); return CBF_ARGUMENT; } minval = -maxval; if ((int)(~0)+1 == 0) minval = minval -1; } else {free(array); free(narray); return CBF_ARGUMENT;} switch( nelsize ) { case (sizeof(char)): if (oelsize == sizeof(float)) { if (nelsigned) { for (icount = 0; icount < elements; icount++) { valtemp = ((float *)array)[icount]; if (valtemp < minval || valtemp > maxval) { free(array); free(narray); return CBF_OVERFLOW; } ((signed char *)narray)[icount] = (signed char)valtemp; } } else { for (icount = 0; icount < elements; icount++) { valtemp = ((float *)array)[icount]; if (valtemp < minval || valtemp > maxval) { free(array); free(narray); return CBF_OVERFLOW; } ((unsigned char *)narray)[icount] = (unsigned char)valtemp; } } } else if (oelsize == sizeof(double)) { if (nelsigned) { for (icount = 0; icount < elements; icount++) { valtemp = ((double *)array)[icount]; if (valtemp < minval || valtemp > maxval) { free(array); free(narray); return CBF_OVERFLOW; } ((signed char *)narray)[icount] = (signed char)valtemp; } } else { for (icount = 0; icount < elements; icount++) { valtemp = ((double *)array)[icount]; if (valtemp < minval || valtemp > maxval) { free(array); free(narray); return CBF_OVERFLOW; } ((unsigned char *)narray)[icount] = (unsigned char)valtemp; } } } else { free(narray); free(array); return CBF_ARGUMENT;} break; case (sizeof(short int)): if (oelsize == sizeof(float)) { if (nelsigned) { for (icount = 0; icount < elements; icount++) { valtemp = ((float *)array)[icount]; if (valtemp < minval || valtemp > maxval) { free(array); free(narray); return CBF_OVERFLOW; } ((signed short int *)narray)[icount] = (signed short int)valtemp; } } else { for (icount = 0; icount < elements; icount++) { valtemp = ((float *)array)[icount]; if (valtemp < minval || valtemp > maxval) { free(array); free(narray); return CBF_OVERFLOW; } ((unsigned short int *)narray)[icount] = (unsigned short int)valtemp; } } } else if (oelsize == sizeof(double)) { if (nelsigned) { for (icount = 0; icount < elements; icount++) { valtemp = ((double *)array)[icount]; if (valtemp < minval || valtemp > maxval) { free(array); free(narray); return CBF_OVERFLOW; } ((signed short int *)narray)[icount] = (signed short int)valtemp; } } else { for (icount = 0; icount < elements; icount++) { valtemp = ((double *)array)[icount]; if (valtemp < minval || valtemp > maxval) { free(array); free(narray); return CBF_OVERFLOW; } ((unsigned short int *)narray)[icount] = (unsigned short int)valtemp; } } } else { free(narray); free(array); return CBF_ARGUMENT;} break; case (sizeof(long int)): if (oelsize == sizeof(float)) { if (nelsigned) { for (icount = 0; icount < elements; icount++) { valtemp = ((float *)array)[icount]; if (valtemp < minval || valtemp > maxval) { free(array); free(narray); return CBF_OVERFLOW; } ((signed long int *)narray)[icount] = (signed long int)valtemp; } } else { for (icount = 0; icount < elements; icount++) { valtemp = ((float *)array)[icount]; if (valtemp < minval || valtemp > maxval) { free(array); free(narray); return CBF_OVERFLOW; } ((unsigned long int *)narray)[icount] = (unsigned long int)valtemp; } } } else if (oelsize == sizeof(double)) { if (nelsigned) { for (icount = 0; icount < elements; icount++) { valtemp = ((double *)array)[icount]; if (valtemp < minval || valtemp > maxval) { free(array); free(narray); return CBF_OVERFLOW; } ((signed long int *)narray)[icount] = (signed long int)valtemp; } } else { for (icount = 0; icount < elements; icount++) { valtemp = ((double *)array)[icount]; if (valtemp < minval || valtemp > maxval) { free(array); free(narray); return CBF_OVERFLOW; } ((unsigned long int *)narray)[icount] = (unsigned long int)valtemp; } } } else { free(narray); free(array); return CBF_ARGUMENT;} break; #ifdef CBF_USE_LONG_LONG case (sizeof(long long int)): if (oelsize == sizeof(float)) { if (nelsigned) { for (icount = 0; icount < elements; icount++) { valtemp = ((float *)array)[icount]; if (valtemp < minval || valtemp > maxval) { free(array); free(narray); return CBF_OVERFLOW; } ((signed long long int *)narray)[icount] = (signed long long int)valtemp; } } else { for (icount = 0; icount < elements; icount++) { valtemp = ((float *)array)[icount]; if (valtemp < minval || valtemp > maxval) { free(array); free(narray); return CBF_OVERFLOW; } ((unsigned long long int *)narray)[icount] = (unsigned long long int)valtemp; } } } else if (oelsize == sizeof(double)) { if (nelsigned) { for (icount = 0; icount < elements; icount++) { valtemp = ((double *)array)[icount]; if (valtemp < minval || valtemp > maxval) { free(array); free(narray); return CBF_OVERFLOW; } ((signed long long int *)narray)[icount] = (signed long long int)valtemp; } } else { for (icount = 0; icount < elements; icount++) { valtemp = ((double *)array)[icount]; if (valtemp < minval || valtemp > maxval) { free(array); free(narray); return CBF_OVERFLOW; } ((unsigned long long int *)narray)[icount] = (unsigned long long int)valtemp; } } } else { free(narray); free(array); return CBF_ARGUMENT;} break; #else case (2* sizeof(long int)): if (toupper(border[0])=='L') { lobyte = 0; hibyte = 1; } else { lobyte = 1; hibyte = 0; } if (oelsize == sizeof(float)) { if (nelsigned) { for (icount = 0; icount < elements; icount++) { valtemp = ((float *)array)[icount]; if (valtemp < minval || valtemp > maxval) { free(array); free(narray); return CBF_OVERFLOW; } vallow = fmod(valtemp,onemore); valhigh = (valtemp-vallow)/onemore; ((unsigned long int *)narray)[2*icount+lobyte] = (unsigned long int)vallow; ((signed long int *)narray)[2*icount+hibyte] = (signed long int)valhigh; } } else { for (icount = 0; icount < elements; icount++) { valtemp = ((float *)array)[icount]; if (valtemp < minval || valtemp > maxval) { free(array); free(narray); return CBF_OVERFLOW; } vallow = fmod(valtemp,onemore); valhigh = (valtemp-vallow)/onemore; ((unsigned long int *)narray)[2*icount+lobyte] = (unsigned long int)vallow; ((unsigned long int *)narray)[2*icount+hibyte] = (unsigned long int)valhigh; } } } else if (oelsize == sizeof(double)) { if (nelsigned) { for (icount = 0; icount < elements; icount++) { valtemp = ((double *)array)[icount]; if (valtemp < minval || valtemp > maxval) { free(array); free(narray); return CBF_OVERFLOW; } vallow = fmod(valtemp,onemore); valhigh = (valtemp-vallow)/onemore; ((unsigned long int *)narray)[2*icount+lobyte] = (unsigned long int)vallow; ((signed long int *)narray)[2*icount+hibyte] = (signed long int)valhigh; } } else { for (icount = 0; icount < elements; icount++) { valtemp = ((double *)array)[icount]; if (valtemp < minval || valtemp > maxval) { free(array); free(narray); return CBF_OVERFLOW; } vallow = fmod(valtemp,onemore); valhigh = (valtemp-vallow)/onemore; ((unsigned long int *)narray)[2*icount+lobyte] = (unsigned long int)vallow; ((unsigned long int *)narray)[2*icount+hibyte] = (signed long int)valhigh; } } } else { free(narray); free(array); return CBF_ARGUMENT;} break; #endif default: free(array); free(narray); return CBF_ARGUMENT; } cbf_failnez(cbf_set_integerarray_wdims_fs( cbfout, compression, binary_id, narray, nelsize, nelsigned, elements, "little_endian", dim1, dim2, dim3, 0)) free(narray); free(array); } else { /* real to real conversion */ switch (oelsize) { case sizeof(float): if (nelsize == sizeof(float)) { for (icount = 0; icount < elements; icount++) { ((float *)narray)[icount] = ((float *)array)[icount]; } } else if (nelsize == sizeof(double)) { for (icount = 0; icount < elements; icount++) { ((double *)narray)[icount] = ((float *)array)[icount]; } } else {free(array); free(narray); return CBF_ARGUMENT;} break; case sizeof(double): if (nelsize == sizeof(float)) { for (icount = 0; icount < elements; icount++) { ((float *)narray)[icount] = ((double *)array)[icount]; } } else if (nelsize == sizeof(double)) { for (icount = 0; icount < elements; icount++) { ((double *)narray)[icount] = ((double *)array)[icount]; } } else {free(array); free(narray); return CBF_ARGUMENT;} break; default: free(array); free(narray); return CBF_ARGUMENT; } cbf_failnez(cbf_set_realarray_wdims_fs( cbfout, compression, binary_id, narray, nelsize, elements, "little_endian", dim1, dim2, dim3, 0)) free(array); free(narray); return 0; } } else { return CBF_ALLOC; } } } } else { return CBF_ALLOC; } } return 0; } #ifdef __cplusplus } #endif ./CBFlib-0.9.2.2/src/cbf_read_binary.c0000644000076500007650000004506411603702106015633 0ustar yayayaya/********************************************************************** * read_binary -- read a binary header * * * * Version 0.7.6 14 July 2006 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifdef __cplusplus extern "C" { #endif #include "cbf.h" #include "cbf_file.h" #include "cbf_context.h" #include "cbf_binary.h" #include "cbf_codes.h" #include /* Parse a binary header looking for the size and id */ int cbf_parse_binaryheader (cbf_file *file, size_t *size, long *id, unsigned int *compression, int mime) { unsigned int file_size, file_compression; int file_id, c; /* Skip ASCII characters */ do c = cbf_get_character (file); while (isspace (c) || isgraph (c)); /* Skip the separators: Byte -1? Ctrl-L 12 (FF) 0 Ctrl-Z 26 (SUB) 1 Ctrl-D 4 (EOT) 2 213 3-6 id 7-14 size */ while (c == 12 || c == 26 || c == 4) c = cbf_get_character (file); /* OK? */ if (c != 213) return CBF_FORMAT; /* Discard any bits in the buffer */ cbf_failnez (cbf_reset_in_bits (file)) /* If there was a mime header, there is no id, size or compression */ if (mime) return 0; /* id */ cbf_failnez (cbf_get_integer (file, &file_id, 1, 64)) if (id) *id = file_id; /* Size */ cbf_failnez (cbf_get_integer (file, (int *) &file_size, 0, 64)) if (size) *size = file_size; /* Compression Type */ cbf_failnez (cbf_get_integer (file, (int *) &file_compression, 0, 64)) if (compression) *compression = file_compression; /* Success */ return 0; } #ifdef __cplusplus } #endif ./CBFlib-0.9.2.2/src/cbf_predictor.c0000644000076500007650000004606611603702106015352 0ustar yayayaya/********************************************************************** * cbf_predictor -- Predictor-Huffman compression (not implemented) * * * * Version 0.8.0 20 July 2008 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifdef __cplusplus extern "C" { #endif #include #include #include #include #include "cbf_predictor.h" /* Compress and array with the Predictor-Huffman algorithm */ int cbf_compress_predictor (void *source, size_t elsize, int elsign, size_t nelem, unsigned int compression, cbf_file *file, size_t *compressedsize, int *storedbits, int realarray, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding) { fprintf (stderr, "\n*** Predictor-Huffman Algorithm Not Implemented Yet -- Abort ***\n"); exit (1); return 1; } /* Decompress an array with the Predictor-Huffman algorithm */ int cbf_decompress_predictor (void *destination, size_t elsize, int elsign, size_t nelem, size_t *nelem_read, size_t compressedsize, unsigned int compression, int data_bits, int data_sign, cbf_file *file, int realarray, const char *byteorder, size_t dimover, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding) { fprintf (stderr, "\n*** Predictor-Huffman Algorithm Not Implemented Yet -- Abort ***\n"); exit (1); return 1; } #ifdef __cplusplus } #endif ./CBFlib-0.9.2.2/src/fcb_read_line.f900000644000076500007650000000312711603702106015444 0ustar yayayaya INTEGER FUNCTION FCB_READ_LINE(TAPIN,LAST_CHAR,FCB_BYTES_IN_REC, & BYTE_IN_FILE,REC_IN_FILE,BUFFER,LINE,N,LINELEN) !----------------------------------------------------------------------- ! Reads successive bytes into byte array LINE(N), stopping at N, ! error or first CR(Z'0D') or LF(Z'0A'), discarding a LF after a CR. !----------------------------------------------------------------------- IMPLICIT NONE INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC,N INTEGER, INTENT(INOUT):: BYTE_IN_FILE,REC_IN_FILE INTEGER, INTENT(OUT):: LINELEN INTEGER(1),INTENT(INOUT):: LAST_CHAR,BUFFER(FCB_BYTES_IN_REC) INTEGER(1), INTENT(OUT):: LINE(N) INTEGER I,FCB_READ_BYTE !----------------------------------------------------------------------- LINELEN=0 DO I = 1,N BYTE_IN_FILE=BYTE_IN_FILE+1 FCB_READ_LINE=FCB_READ_BYTE(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,LINE(I)) IF(FCB_READ_LINE.NE.0)EXIT IF (I.EQ.1.AND.LAST_CHAR.EQ.Z'0D'.AND.LINE(I).EQ.Z'0A') THEN BYTE_IN_FILE=BYTE_IN_FILE+1 FCB_READ_LINE=FCB_READ_BYTE(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,LINE(I)) ENDIF IF(FCB_READ_LINE.NE.0)EXIT LAST_CHAR=LINE(I) IF (LINE(I).EQ.Z'0A' .OR. LINE(I).EQ.Z'0D')EXIT LINELEN=LINELEN+1 END DO ! *** DEBUG *** WRITE(*,'(I5,1X,80A1)')LINELEN,LINE(1:LINELEN) RETURN END FUNCTION FCB_READ_LINE ./CBFlib-0.9.2.2/src/cbf_file.c0000644000076500007650000014651311603702106014274 0ustar yayayaya/********************************************************************** * cbf_file -- file access (characterwise and bitwise) * * * * Version 0.7.7 19 February 2006 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifdef __cplusplus extern "C" { #endif #include "cbf.h" #include "cbf_alloc.h" #include "cbf_codes.h" #include "cbf_file.h" #include #include #include #include /* Create and initialise a file */ int cbf_make_file (cbf_file **file, FILE *stream) { char ** fc; /* Allocate the memory */ cbf_failnez (cbf_alloc ((void **) file, NULL, sizeof (cbf_file), 1)) fc = &((*file)->characters); cbf_onfailnez (cbf_alloc ( (void **)fc, NULL, CBF_INIT_WRITE_BUFFER, 1), cbf_free((void **)file,NULL)) /* Initialise */ (*file)->stream = stream; (*file)->logfile = stderr; (*file)->errors = 0; (*file)->warnings = 0; (*file)->connections = 1; (*file)->temporary = stream?0:1; (*file)->bits [0] = 0; (*file)->bits [1] = 0; (*file)->characters_base = (*file)->characters; (*file)->characters_size = CBF_INIT_WRITE_BUFFER; (*file)->characters_used = 0; (*file)->last_read = 0; (*file)->line = 0; (*file)->column = 0; (*file)->columnlimit = CBF_LINELENGTH_10; (*file)->buffer_size = 0; (*file)->buffer_used = 0; (*file)->buffer = NULL; (*file)->digest = NULL; (*file)->read_headers = 0; (*file)->write_headers = 0; (*file)->write_encoding = 0; /* Success */ return 0; } /* Create and initialise a wide file */ int cbf_make_widefile (cbf_file **file, FILE *stream) { cbf_failnez(cbf_make_file (file, stream)) (*file)->columnlimit = CBF_LINELENGTH_11; return 0; } /* Free a file */ int cbf_free_file (cbf_file **file) { int errorcode; void *vbuffer; void *vdigest; void *vcharacters; errorcode = 0; if (file) if (*file) { if ((*file)->stream) if (fclose ((*file)->stream)) errorcode = CBF_FILECLOSE; vbuffer = (void *)(*file)->buffer; vdigest = (void *)(*file)->digest; vcharacters = (void *)(*file)->characters; if ((*file)->characters_base) vcharacters = (void *)(*file)->characters_base; errorcode |= cbf_free ((void **) &vbuffer, &(*file)->buffer_size); errorcode |= cbf_free ((void **) &vcharacters, &(*file)->characters_size); errorcode |= cbf_free ((void **) &vdigest, NULL); errorcode |= cbf_free ((void **) file, NULL); } /* Success? */ return errorcode; } /* Add a file connection */ int cbf_add_fileconnection (cbf_file **file, FILE *stream) { /* Does the file pointer exist? */ if (!file) return CBF_ARGUMENT; /* Does the file exist? */ if (*file) { /* Does the stream match? */ if (stream && (*file)->stream != stream) return CBF_NOTFOUND; else { (*file)->connections++; return 0; } } /* Create a new file */ return cbf_make_file (file, stream); } /* Remove a file connection */ int cbf_delete_fileconnection (cbf_file **file) { /* Does the file pointer exist? */ if (!file) return CBF_ARGUMENT; /* Does the file exist? */ if (!*file) return CBF_ARGUMENT; /* Remove a connection */ (*file)->connections--; /* Delete the file? */ if ((*file)->connections == 0) return cbf_free_file (file); /* Success */ return 0; } /* Count the connections */ int cbf_file_connections (cbf_file *file) { if (!file) return 0; return file->connections; } /* Set the size of the buffer */ int cbf_set_buffersize (cbf_file *file, size_t size) { void * vbuffer; /* Does the file exist? */ if (!file) return CBF_ARGUMENT; /* Is the size already close enough? */ if (size > 0 && file->buffer_size >= size && file->buffer_size < 2*size) return 0; /* Reallocate the buffer */ vbuffer = (void *)file->buffer; cbf_failnez(cbf_realloc ((void **) &vbuffer, &file->buffer_size, sizeof (char), size)) file->buffer = (char *)vbuffer; return 0; } /* Empty the buffer */ int cbf_reset_buffer (cbf_file *file) { /* Does the file exist? */ if (!file) return CBF_ARGUMENT; /* Empty the buffer */ file->buffer_used = 0; /* success */ return 0; } /* Set input/output buffer size */ int cbf_set_io_buffersize (cbf_file *file, size_t size) { size_t old_data, old_size, target_size; char ** fc; /* if insufficient space, increase to at least double the old space, but certainly to the requested size */ if (file->characters_size < CBF_INIT_WRITE_BUFFER || file->characters_size < size ) { fc = &(file->characters_base); old_data = file->characters-file->characters_base; old_size = old_data + file->characters_size; target_size = old_data + size; if (target_size < old_size) target_size = old_size*2; if (cbf_realloc ((void **)fc, &old_size, 1, target_size)) { file->temporary = 0; file->characters = file->characters_base; file->characters_used = old_data; file->characters_size = old_size; if (file->characters_size < size) return CBF_ALLOC; return 0; } else { file->characters = file->characters_base + old_data; file->characters_size = old_size - old_data; } } return 0; } /* Set output buffer size */ int cbf_set_output_buffersize (cbf_file *file, size_t size) { /* try to get the needed space by flushing the current output buffer */ cbf_failnez (cbf_flush_characters(file)) cbf_failnez (cbf_set_io_buffersize(file, size)) return 0; } /* Add a character to the buffer */ int cbf_save_character (cbf_file *file, int c) { unsigned int new_size; /* Does the file exist? */ if (!file) return CBF_ARGUMENT; /* Expand the buffer? */ if (file->buffer_size < file->buffer_used+3) { new_size = (file->buffer_used+3)*2; if (new_size >= file->buffer_size) cbf_failnez (cbf_set_buffersize (file, new_size)) } /* Add the character */ file->buffer [file->buffer_used] = (char) c; file->buffer_used++; file->buffer [file->buffer_used] = '\0'; /* Success */ return 0; } /* Add a character to the buffer, trim lines */ int cbf_save_character_trim (cbf_file *file, int c) { unsigned int new_size; /* Does the file exist? */ if (!file) return CBF_ARGUMENT; /* Expand the buffer? */ if (file->buffer_size < file->buffer_used+3) { new_size = (file->buffer_used+3)*2; if (new_size >= file->buffer_size) cbf_failnez (cbf_set_buffersize (file, new_size)) } /* Check for end of line, if so, trim */ if ((char)c == '\n') { while (file->buffer_used > 0 && file->buffer[file->buffer_used-1] != '\n' && file->buffer[file->buffer_used-1] != '\r' && isspace(file->buffer[file->buffer_used-1])) { file->buffer_used--; } } /* Add the character */ file->buffer [file->buffer_used] = (char) c; file->buffer_used++; file->buffer [file->buffer_used] = '\0'; /* Success */ return 0; } /* Add a character to the buffer at a given position */ int cbf_save_character_at (cbf_file *file, int c, size_t position) { unsigned int new_size; size_t ii; /* Does the file exist? */ if (!file) return CBF_ARGUMENT; if (position >= file->buffer_used) { if (file->buffer_size < position-2 ) { new_size = (position+2)*2; if (new_size >= file->buffer_size) { cbf_failnez (cbf_set_buffersize (file, new_size)) } file->buffer [position] = (char) c; file->buffer [position+1] = '\0'; for (ii = file->buffer_used; ii < position; ii++ ) { file->buffer [ii] = ' '; } file->buffer_used = position+1; } } else { file->buffer [position] = (char) c; } /* Success */ return 0; } /* Retrieve the buffer */ int cbf_get_buffer (cbf_file *file, const char **buffer, size_t *buffer_size) { /* Does the file exist? */ if (!file) return CBF_ARGUMENT; /* Copy the buffer */ if (buffer) { if (file->buffer_used <= 0) *buffer = NULL; else *buffer = file->buffer; } if (buffer_size) *buffer_size = file->buffer_used; /* Success */ return 0; } /* Get the file coordinates */ int cbf_get_filecoordinates (cbf_file *file, unsigned int *line, unsigned int *column) { /* Does the file exist? */ if (!file) return CBF_ARGUMENT; /* Read the coordinates */ if (line) *line = file->line; if (column) *column = file->column; /* Success */ return 0; } /* Set the file coordinates */ int cbf_set_filecoordinates (cbf_file *file, unsigned int line, unsigned int column) { /* Does the file exist? */ if (!file) return CBF_ARGUMENT; /* Set the coordinates */ file->line = line; file->column = column; /* Success */ return 0; } /* Read the next bit */ int cbf_get_bit (cbf_file *file) { int bit; if (file->bits [0] == 0) { if (file->temporary) { if (file->characters_used) { file->bits [1] = *((file->characters)++); file->bits [1] &= 0xFF; file->characters_used--; file->characters_size--; } else { file->bits [1] = EOF; } } else { if (file->characters_used) { file->bits [1] = *((file->characters)++); file->bits [1] &= 0xFF; file->characters_used--; file->characters_size--; } else { file->bits [1] = getc (file->stream); } } if (file->bits [1] == EOF) return EOF; file->bits [0] = 8; } bit = file->bits [1] & 1; file->bits [1] >>= 1; file->bits [0]--; /* Success */ return bit; } /* Read the next bits (signed) */ int cbf_get_bits (cbf_file *file, int *bitslist, int bitcount) { int bitcode, count, m, maxbits; /* Number of bits in an integer */ maxbits = sizeof (int) * CHAR_BIT; /* Read the bits in int-sized blocks */ while (bitcount > maxbits) { cbf_failnez (cbf_get_bits (file, bitslist, maxbits)) bitslist++; bitcount -= maxbits; } /* Read the bits into an int */ count = file->bits [0]; bitcode = file->bits [1] & 0x0ff; while (count < bitcount) { if (file->temporary) { if (file->characters_used) { file->bits [1] = *((file->characters)++); file->bits [1] &= 0xFF; file->characters_used--; file->characters_size--; } else { file->bits [1] = EOF; } } else { if (file->characters_used) { file->bits [1] = *((file->characters)++); file->bits [1] &= 0xFF; file->characters_used--; file->characters_size--; } else { file->bits [1] = getc (file->stream); } } if (file->bits [1] == EOF) return CBF_FILEREAD; file->bits [0] = 8; bitcode |= (file->bits [1] << count) & -(1 << count); count += 8; } file->bits [1] = (file->bits [1] >> (file->bits [0] - (count - bitcount))); file->bits [0] = count - bitcount; /* Sign-extend */ m = 1 << (bitcount - 1); if (bitcode & m) *bitslist = bitcode | -m; else *bitslist = bitcode & ~-m; /* Success */ return 0; } /* Write bits */ int cbf_put_bits (cbf_file *file, int *bitslist, int bitcount) { int resultcode, maxbits, bits0, bits1; /* Number of bits in an integer */ maxbits = sizeof (int) * CHAR_BIT; /* Write the bits in int-sized blocks */ while (bitcount > maxbits) { cbf_failnez (cbf_put_bits (file, bitslist, maxbits)) bitslist++; bitcount -= maxbits; } bits0 = file->bits [0]; bits1 = file->bits [1]; /* Get the first 8 bits */ bits1 |= (*bitslist & 0x0ff) << bits0; bits0 += bitcount; /* Write 8 bits? */ if (bits0 >= 8) { /* Add the character to the character buffer */ file->characters [file->characters_used] = bits1 & 0xff; file->characters_used++; if (file->characters_used == file->characters_size) { resultcode = cbf_flush_characters (file); if (resultcode) { file->bits [0] = bits0; file->bits [1] = bits1; return resultcode; } } bits0 -= 8; /* Get the remaining bits */ bits1 = *bitslist >> (bitcount - bits0); /* Write the remaining bits */ while (bits0 >= 8) { file->characters [file->characters_used] = bits1 & 0xff; file->characters_used++; if (file->characters_used == file->characters_size) { resultcode = cbf_flush_characters (file); if (resultcode) { file->bits [0] = bits0; file->bits [1] = bits1; return resultcode; } } bits1 >>= 8; bits0 -= 8; } } bits1 &= ~-(1 << bits0); file->bits [0] = bits0; file->bits [1] = bits1; /* Success */ return 0; } /* Read an integer as a series of bits */ int cbf_get_integer (cbf_file *file, int *val, int valsign, int bitcount) { int maxbits, signbits, valbits, sign, errorcode; int deval; int *tval = &deval; /* Any bits to read? */ if (bitcount <= 0) { if (val) *val = 0; return 0; } /* Number of bits in an integer */ maxbits = sizeof (int) * CHAR_BIT; /* Number of bits in the value and sign parts */ signbits = bitcount - sizeof (int) * CHAR_BIT; if (signbits > 0) valbits = bitcount - signbits; else valbits = bitcount; /* Read the value */ cbf_failnez (cbf_get_bits (file, (int *)tval, valbits)) /* Fix the sign */ if (valbits < maxbits && valsign == 0) deval &= ~-(1 << valbits); /* Read the sign bits */ errorcode = 0; while (signbits > 0) { if (signbits < maxbits) cbf_failnez (cbf_get_bits (file, &sign, signbits)) else cbf_failnez (cbf_get_bits (file, &sign, maxbits)) signbits -= maxbits; /* Overflow? */ if (sign != -(deval < 0 && valsign)) { errorcode = CBF_OVERFLOW; if (valsign) deval = -(sign >= 0) ^ (1 << (maxbits - 1)); else deval = -1; } } if (val) { *val = deval; } return errorcode; } /* Write an integer as a series of bits */ int cbf_put_integer (cbf_file *file, int val, int valsign, int bitcount) { int maxbits, signbits, valbits, sign; /* Any bits to write? */ if (bitcount <= 0) return 0; /* Number of bits in an integer */ maxbits = sizeof (int) * CHAR_BIT; /* Number of bits in the value and sign parts */ signbits = bitcount - maxbits; if (signbits > 0) valbits = bitcount - signbits; else valbits = bitcount; /* Sign value */ sign = -(val < 0 && valsign); /* Write the value */ cbf_failnez (cbf_put_bits (file, &val, valbits)) /* Write the sign part */ while (signbits >= maxbits) { cbf_failnez (cbf_put_bits (file, &sign, maxbits)) signbits -= maxbits; } if (signbits > 0) cbf_failnez (cbf_put_bits (file, &sign, signbits)) /* Success */ return 0; } /* Initialize a message digest */ int cbf_start_digest (cbf_file *file) { void *vdigest; if (!file) return CBF_ARGUMENT; /* Flush the buffers */ cbf_failnez (cbf_flush_characters (file)) /* Allocate the md5 context */ if (!file->digest) { vdigest = (void *)file->digest; cbf_failnez (cbf_alloc ((void **)&vdigest, NULL, sizeof (MD5_CTX), 1)) file->digest = (MD5_CTX *)vdigest; } /* Initialize */ MD5Init (file->digest); /* Success */ return 0; } /* Get the message digest */ int cbf_end_digest (cbf_file *file, char *digest) { unsigned char raw_digest [16]; void *vdigest; if (!file || !digest) return CBF_ARGUMENT; if (!file->digest) return CBF_ARGUMENT; /* Flush the buffers */ cbf_failnez (cbf_flush_characters (file)) /* Get the raw digest */ MD5Final (raw_digest, file->digest); /* Free the md5 context */ vdigest = (void *)file->digest; cbf_failnez (cbf_free ((void **) &vdigest, NULL)) file->digest = NULL; /* Encode the digest in base-64 */ cbf_md5digest_to64 (digest, raw_digest); /* Success */ return 0; } /* Flush the bit buffer */ int cbf_flush_bits (cbf_file *file) { if (!file) return CBF_ARGUMENT; /* Flush any partial bytes into the character buffer */ cbf_failnez (cbf_put_integer (file, 0, 0, 7)) /* Reset the bit buffers */ file->bits [0] = 0; file->bits [1] = 0; /* Write the characters */ return cbf_flush_characters (file); } /* Flush the character buffer */ int cbf_flush_characters (cbf_file *file) { int done; if (!file) return CBF_ARGUMENT; /* Write the characters */ if (file->characters_used == 0) return 0; /* Update the message digest */ if (file->digest) MD5Update (file->digest, file->characters, file->characters_used); while (file->temporary) { file->characters += file->characters_used; file->characters_size -= file->characters_used; file->characters_used = 0; /* Attempt to expand the character buffer if it has fallen below the initial write buffer size. If it fails, revert to disk I/O */ if (file->characters_size < CBF_INIT_WRITE_BUFFER ) { size_t old_data, old_size; char ** fc; fc = &(file->characters_base); old_data = file->characters-file->characters_base; old_size = old_data + file->characters_size; if (cbf_realloc ((void **)fc, &old_size, 1, old_size*2)) { file->temporary = 0; file->characters = file->characters_base; file->characters_used = old_data; file->characters_size = old_size; break; } else { file->characters = file->characters_base + old_data; file->characters_size = old_size - old_data; } } return 0; } done = fwrite (file->characters, 1, file->characters_used, file->stream); /* Make sure the file is really updated */ if (done > 0) fflush (file->stream); /* Remove the characters written */ if (done < file->characters_used) { if (done > 0) { memmove (file->characters, file->characters + done, file->characters_size - done); file->characters_used = file->characters_size - done; } return CBF_FILEWRITE; } file->characters_used = 0; /* Success */ return 0; } /* Discard any bits in the bits buffers */ int cbf_reset_bits (cbf_file *file) { if (!file) return CBF_ARGUMENT; file->bits [0] = 0; file->bits [1] = 0; return cbf_reset_characters (file); } /* Discard any bits in the bits buffers for input */ int cbf_reset_in_bits (cbf_file *file) { if (!file) return CBF_ARGUMENT; file->bits [0] = 0; file->bits [1] = 0; return 0; } /* Discard any characters in the character buffers */ int cbf_reset_characters (cbf_file *file) { if (!file) return CBF_ARGUMENT; file->characters_used = 0; /* Success */ return 0; } /* Get the next character */ int cbf_get_character (cbf_file *file) { if (file->characters_used) { file->last_read = *(file->characters++); file->last_read &= 0xff; (file->characters_used)--; (file->characters_size)--; return file->last_read; } if (file->temporary) { file->last_read = EOF; return file->last_read; } file->last_read = EOF; if (file->stream) { size_t increment; if (!file->characters_base) { cbf_failnez(cbf_set_io_buffersize(file,CBF_INIT_READ_BUFFER)) } increment = file->characters - file->characters_base; file->characters_size += increment; file->characters = file->characters_base; if (!file->characters_size) { cbf_failnez(cbf_set_io_buffersize(file,CBF_INIT_READ_BUFFER)) } if (feof(file->stream) || ferror(file->stream)) return EOF; file->characters_used = fread(file->characters_base,1,file->characters_size,file->stream); if (file->characters_used) { file->last_read = *(file->characters++); file->last_read &= 0xff; (file->characters_used)--; (file->characters_size)--; } else { if (ferror(file->stream)) return CBF_FILEREAD; else return EOF; } } return file->last_read; } /* Read the next character (convert end-of-line and update line and column) */ int cbf_read_character (cbf_file *file) { int last, current; /* Does the file exist? */ if (!file) return EOF; /* Read the next character */ last = file->last_read; while ( (current = cbf_get_character (file)) == 0); if ((current == '\n' && last == '\r') || (current == '\r' && last == '\n')) while ( (current = cbf_get_character (file)) == 0); /* Convert the end-of-line character and update line and column */ if (current == '\n' || current == '\r') { current = '\n'; file->column = 0; file->line++; } else if (current == '\t') file->column = (file->column & ~0x07) + 8; else if (current != EOF)file->column++; return current; } /* Put a character */ int cbf_put_character (cbf_file *file, int c) { /* Does the file exist? */ if (!file) return EOF; /* Flush the buffer? */ if (file->characters_used == file->characters_size) cbf_failnez (cbf_flush_characters (file)) /* Add the character */ file->characters [file->characters_used] = c & 0xff; file->characters_used++; /* Success */ return 0; } /* Write a character (convert end-of-line and update line and column) */ int cbf_write_character (cbf_file *file, int c) { /* Does the file exist? */ if (!file) return EOF; /* Write the next character */ if (c == '\n') { /* Line termination */ if (file->write_encoding & ENC_CRTERM) cbf_failnez (cbf_put_character (file, '\r')) if (file->write_encoding & ENC_LFTERM) cbf_failnez (cbf_put_character (file, '\n')) /* Update line and column */ if (c == '\n') { file->column = 0; file->line++; } } else { cbf_failnez (cbf_put_character (file, c)) /* Update column */ if (c == '\t') file->column = (file->column & ~0x07) + 8; else file->column++; } /* Success */ return 0; } /* Put a string */ int cbf_put_string (cbf_file *file, const char *string) { /* Does the string exist? */ if (!string) return CBF_ARGUMENT; /* Write the string one character at a time */ while (*string) { cbf_failnez (cbf_put_character (file, *string)) string++; } /* Success */ return 0; } /* Write a string (convert end-of-line and update line and column) */ int cbf_write_string (cbf_file *file, const char *string) { /* Does the string exist? */ if (!string) return CBF_ARGUMENT; /* Write the string */ while (*string) { cbf_failnez (cbf_write_character (file, *string)) string++; } /* Success */ return 0; } /* Read a (CR/LF)-terminated line into the buffer */ int cbf_read_line (cbf_file *file, const char **line) { int c; char buffer[80]; /* Does the file exist? */ if (!file) return CBF_ARGUMENT; /* Empty the buffer */ file->buffer_used = 0; file->column = 0; /* Read the characters */ do { c = cbf_read_character (file); if (c == EOF) return CBF_FILEREAD; if (file->column == file->columnlimit+1) { sprintf(buffer, "input line %u over size limit",1+file->line); cbf_flog(file, buffer, CBF_LOGWARNING|CBF_LOGCURRENTLOC); } cbf_failnez (cbf_save_character (file, c)) } while (c != '\n'); /* Copy the pointer */ if (line) *line = file->buffer; /* Success */ return 0; } /* Read nelem characters into the buffer */ int cbf_get_block (cbf_file *file, size_t nelem) { size_t done; /* Does the file exist? */ if (!file) return CBF_ARGUMENT; /* Set the buffer size */ cbf_failnez (cbf_set_buffersize (file, nelem)) /* Read the characters */ file->buffer_used = 0; while (file->buffer_used < nelem) { if (file->temporary) { if (file->characters_used >= nelem-file->buffer_used) { memmove(file->buffer + file->buffer_used, file->characters, nelem-file->buffer_used); done = nelem-file->buffer_used; } else if (file->characters_used) { memmove(file->buffer + file->buffer_used, file->characters, file->characters_used); done = file->characters_used; } else done = 0; file->characters_used -= done; file->characters_size -= done; file->characters += done; file->buffer_used += done; return 0; } if (file->stream) { done = 0; if (file->characters_used >= nelem-file->buffer_used) { memmove(file->buffer + file->buffer_used, file->characters, nelem-file->buffer_used); done = nelem-file->buffer_used; } else if (file->characters_used) { memmove(file->buffer + file->buffer_used, file->characters, file->characters_used); done = file->characters_used; } file->characters_used -= done; file->characters_size -= done; file->characters += done; file->buffer_used += done; done = 0; if (nelem > file->buffer_used) done = fread (file->buffer + file->buffer_used, 1, nelem - file->buffer_used, file->stream); if ( done < nelem - file->buffer_used ) return CBF_FILEREAD; file->buffer_used += done; return 0; } else { done = 0; } if (done <= 0) return CBF_FILEREAD; file->buffer_used += done; } /* Success */ return 0; } /* Write nelem characters from the buffer */ int cbf_put_block (cbf_file *file, size_t nelem) { size_t done; /* Does the file exist? */ if (!file) return CBF_ARGUMENT; /* Are there enough characters in the buffer? */ if (nelem > file->buffer_size) return CBF_ARGUMENT; /* Flush the buffers */ cbf_failnez (cbf_flush_characters (file)) if (nelem && file->digest) MD5Update (file->digest, file->buffer, nelem); while (file->temporary) { if (file->characters_used + nelem > file->characters_size) { size_t old_data, old_size; char ** fc; fc = &(file->characters_base); old_data = file->characters-file->characters_base; old_size = old_data + file->characters_size; if (cbf_realloc ((void **)fc, &old_size, 1, old_size+nelem)) { file->temporary = 0; file->characters = file->characters_base; file->characters_used = old_data; file->characters_size = old_size; cbf_failnez (cbf_flush_characters (file)) break; } else { file->characters = file->characters_base + old_data; file->characters_size = old_size-old_data; } } memmove(file->characters+file->characters_used,file->buffer,nelem); file->characters_used += nelem; file->characters_size -= nelem; cbf_failnez(cbf_flush_characters(file)) return 0; } /* Write the characters */ if (file->stream && nelem) done = fwrite (file->buffer, 1, nelem, file->stream); else done = 0; /* Fail? */ if (done < nelem) return CBF_FILEWRITE; /* Success */ return 0; } /* Copy characters between files */ int cbf_copy_file (cbf_file *destination, cbf_file *source, size_t nelem) { size_t done=0, todo; /* Do the files exist? */ if (!destination || !source) return CBF_ARGUMENT; if (!destination->stream || !source->stream) return CBF_ARGUMENT; /* Flush the buffers */ cbf_failnez (cbf_flush_characters (destination)) if (source->temporary && !(destination->temporary)) { if (source->characters_used < nelem) { if ( source->characters_used ) done = fwrite (source->characters, 1, source->characters_used, destination->stream); source->characters += source->characters_used; source->characters_size -= source->characters_used; source->characters_used = 0; return CBF_FILEREAD; } done = fwrite (source->characters, 1, nelem, destination->stream); source->characters += nelem; source->characters_size -= nelem; source->characters_used -= nelem; if (done < nelem) return CBF_FILEWRITE; return 0; } /* Copy the characters in blocks of up to CBF_TRANSFER_BUFFER */ while (nelem > 0) { if (nelem >= CBF_TRANSFER_BUFFER) todo = CBF_TRANSFER_BUFFER; else todo = nelem; cbf_failnez (cbf_get_block (source, todo)) /* Update the message digest */ if (todo > 0 && destination->digest) MD5Update (destination->digest, source->buffer, todo); while (destination->temporary) { if (destination->characters_used + todo > destination->characters_size) { size_t old_data, old_size; char ** fc; fc = &(destination->characters_base); old_data = destination->characters-destination->characters_base; old_size = old_data + destination->characters_size; if (cbf_realloc ((void **)fc, &old_size, 1, old_size+todo)) { destination->temporary = 0; destination->characters = destination->characters_base; destination->characters_used = old_data; destination->characters_size = old_size; cbf_failnez (cbf_flush_characters (destination)) break; } else { destination->characters = destination->characters_base + old_data; destination->characters_size = old_size-old_data; } } memmove(destination->characters+destination->characters_used,source->buffer,todo); destination->characters_used += todo; destination->characters_size -= todo; done = todo; break; } if (!(destination->temporary)) done = fwrite (source->buffer, 1, todo, destination->stream); /* Fail? */ if (done < todo) return CBF_FILEWRITE; nelem -= done; } if (destination->temporary) { cbf_failnez(cbf_flush_characters(destination)) } /* Success */ return 0; } /* Get the file position */ int cbf_get_fileposition (cbf_file *file, long int *position) { long int file_position; /* Does the file exist? */ if (!file) return CBF_ARGUMENT; /* if (!file->stream) return CBF_ARGUMENT; */ /* Get the position */ if (file->temporary || !file->stream) { file_position = (long int)(file->characters - file->characters_base); } else { file_position = ftell (file->stream); if (file_position == -1L) return CBF_FILETELL; if (file->characters) { file_position -= file->characters_used; if (file_position < 0 ) return CBF_FILETELL; } } if (position) *position = file_position; /* Success */ return 0; } /* Set the file position */ int cbf_set_fileposition (cbf_file *file, long int position, int whence) { /* Does the file exist? */ if (!file) return CBF_ARGUMENT; /* if (!file->stream) return CBF_ARGUMENT; */ /* Set the position */ if (file->temporary || !file->stream) { if (whence == SEEK_CUR) position += file->characters-file->characters_base; if (whence == SEEK_END) position += file->characters-file->characters_base+file->characters_used; if (position < 0 || position > file->characters-file->characters_base+file->characters_used) return CBF_FILESEEK; file->characters_used += file->characters-file->characters_base-position; file->characters_size += file->characters-file->characters_base-position; file->characters = file->characters_base + position; } else { if (file->characters && whence == SEEK_CUR && ((position >= 0 && file->characters_used > position) || (position < 0 && file->characters - file->characters_base > -position))) { file->characters += position; file->characters_used -= position; file->characters_size -= position; } else { if (whence == SEEK_CUR) { position -= file->characters_used; } if (fseek (file->stream, position, whence) < 0) return CBF_FILESEEK; file->characters_used = 0; file->characters_size += (file->characters-file->characters_base); file->characters = file->characters_base; } } file->bits [0] = 0; file->bits [1] = 0; /* Success */ return 0; } #ifdef __cplusplus } #endif ./CBFlib-0.9.2.2/src/cbf_lex.c0000644000076500007650000025105211603702106014140 0ustar yayayaya/********************************************************************** * cbf_lex -- lexical scanner for CBF tokens * * * * Version 0.9.0 18 October 2009 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifdef __cplusplus extern "C" { #endif #include "cbf.h" #include "cbf_compress.h" #include "cbf_lex.h" #include "cbf_codes.h" #include "cbf_file.h" #include "cbf_string.h" #include "cbf_read_binary.h" #include "cbf_read_mime.h" #include "cbf_alloc.h" #include "cbf_ws.h" #include #include #include /* Return an error code */ #define cbf_errornez(f,v) { if (((v)->errorcode = (f)) != 0) return ERROR; } #define cbf_onerrornez(f,v,c) { if (((v)->errorcode = (f)) != 0) { { c; } return ERROR; } } /* Return a copy of the text */ int cbf_return_text (int code, YYSTYPE *val, const char *text, char type) { val->text = cbf_copy_string (NULL, text, type); if (!val->text) { val->errorcode = CBF_ALLOC; return ERROR; } return code; } /* Back up one character in the file */ int cbf_lex_unget (cbf_file *file, YYSTYPE *val, int c[5]) { if ( file->temporary || file->characters ) { if (file->characters > file->characters_base) { file->characters--; file->characters_used++; file->characters_size++; } else { if (file->characters_used >= file->characters_size) { cbf_errornez(cbf_set_io_buffersize(file,file->characters_size+1),val) } if (file->characters_used) memmove(file->characters_base,file->characters_base+1,file->characters_used); file->characters_used++; *(file->characters) = c[0]; } } else { ungetc(c[0],file->stream); } c[0] = c[1]; c[1] = c[2]; c[2] = c[3]; c[3] = c[4]; c[4] = ' '; file->column--; file->last_read='\0'; return 0; } /* Get the next token */ int cbf_lex (cbf_handle handle, YYSTYPE *val ) { int data, define, save, loop, item, column, comment, string, ascii, cqueue[5], reprocess, errorcode, mime, encoding, bits, sign, checked_digest, real, depth, q3; long id, position; unsigned int file_column, compression; size_t size, length=0, code_size, dimover, dimfast, dimmid, dimslow, padding, ii; const char *line; cbf_file *file; char out_line [(((sizeof (void *) + sizeof (long int) * 2 + sizeof (int) * 3) * CHAR_BIT) >> 2) + 57 +15+((5*sizeof (size_t)*3*CHAR_BIT)>>2)]; char digest [25], new_digest [25]; const char * byteorder; file = handle->file; cbf_errornez (cbf_reset_buffer (file), val) if (file->read_headers & CBF_PARSE_WS) { if (handle->commentfile == NULL){ cbf_errornez(cbf_make_file(&(handle->commentfile),NULL), val) } /* The commentfile buffer will contain a copy of the whitespace and comments constructed as raw material for components of a bracketed construct. Each component begins with the ascii-encoded 1-based column number followed by a colon. White space may follow, then an optional comment, which is always followed by a newline. see cbf_apply_ws for the code that processes this buffer */ if (handle->commentfile->buffer_used > 0 ) { cbf_errornez (cbf_save_character (handle->commentfile, ','), val) } cbf_errornez (cbf_set_ws_column (handle->commentfile, file->column+1), val) } cqueue[0] = file->last_read; cqueue[4] = cqueue[3] = cqueue[2] = cqueue[1] = ' '; if (file->column == 0) cqueue[0] = '\n'; column = cqueue[0] == '.'; comment = cqueue[0] == '#'; reprocess = (column || comment); data = define = save = loop = item = string = !reprocess; comment = !column; do { cbf_errornez (cbf_get_buffer (file, &line, &length), val) if (reprocess) { reprocess = 0; } else { cqueue[4] = cqueue[3]; cqueue[3] = cqueue[2]; cqueue[2] = cqueue[1]; cqueue[1] = cqueue[0]; cqueue[0] = cbf_read_character (file); if (cqueue[1] == '\\' && cqueue[2] == '\\') cqueue[1] += 0x100; if (file->column == file->columnlimit+1) { cbf_log(handle, "over line size limit", CBF_LOGWARNING|CBF_LOGCURRENTLOC); } if (isspace (cqueue[0])) { if (cqueue[0]== '\013' || cqueue[0] == '\014') cbf_log(handle,"invalid space character",CBF_LOGWARNING|CBF_LOGCURRENTLOC); } else { if (!(file->read_headers & CBF_PARSE_UTF8)) { if ( cqueue[0] != EOF && ((unsigned char)cqueue[0] > 126 || (unsigned char )cqueue[0] < 32 ) ) { cbf_log(handle,"invalid character",CBF_LOGWARNING|CBF_LOGCURRENTLOC); } } else { if ( cqueue[0] != EOF && ( ((unsigned char)cqueue[0] < 32) || ((unsigned char)cqueue[0] == 127) ) ){ cbf_log(handle,"invalid character",CBF_LOGWARNING|CBF_LOGCURRENTLOC); } } } } /* Discard spaces ([[:space:]]+) and mark starting point */ if (length == 0) { if (isspace (cqueue[0])) { if (cqueue[0]== '\013' || cqueue[0] == '\014') cbf_log(handle,"invalid space character",CBF_LOGWARNING|CBF_LOGCURRENTLOC); if (file->read_headers & CBF_PARSE_WS) { cbf_errornez (cbf_save_character_trim (handle->commentfile, (cqueue[0]&0xFF)), val) } continue; } handle->startline = file->line; handle->startcolumn = file->column; } /* DATA ([Dd][Aa][Tt][Aa][_][^[:space:]]*) */ if (data) { if (length < 5) { data = toupper (cqueue[0]) == "DATA_" [length]; } else { if ( length == 81 ) cbf_log(handle, "data block name exceeds 75 characters", CBF_LOGERROR|CBF_LOGSTARTLOC); if ((file->read_headers & CBF_PARSE_CIF2_DELIMS) && (cqueue[0] == '{' || cqueue[0] == '}' || cqueue[0] == '\'' || cqueue[0] == '"' || cqueue[0] == ',' || cqueue[0] == ':')) { cbf_log(handle,"invalid separator ",CBF_LOGWARNING|CBF_LOGCURRENTLOC); if (cqueue[0] != ',' && cqueue[0] != ':' ) { cbf_errornez(cbf_lex_unget(file,val,cqueue), val) } return cbf_return_text (DATA, val, &line [5], 0); } if (isspace (cqueue[0]) || cqueue[0] == EOF) return cbf_return_text (DATA, val, &line [5], 0); } } /* DEFINE ([Dd][Ee][Ff][Ii][Nn][Ee]_[^[:space:]]*) */ if (define && (file->read_headers & CBF_PARSE_DEFINES)) { if (length < 8) { define = toupper (cqueue[0]) == "DEFINE_" [length]; } else { if ( length == 84 ) cbf_log(handle, "function name exceeds 75 characters", CBF_LOGERROR|CBF_LOGSTARTLOC); if (cqueue[0] == EOF) cbf_log(handle, "function has no definition", CBF_LOGERROR|CBF_LOGSTARTLOC); if ((file->read_headers & CBF_PARSE_CIF2_DELIMS) && (cqueue[0] == '{' || cqueue[0] == '}' || cqueue[0] == '\'' || cqueue[0] == '"' || cqueue[0] == ',' || cqueue[0] == ':')) { cbf_log(handle,"invalid separator ",CBF_LOGWARNING|CBF_LOGCURRENTLOC); if (cqueue[0] != ',' && cqueue[0] != ':' ) { cbf_errornez(cbf_lex_unget(file,val,cqueue), val) }; return cbf_return_text (DEFINE, val, &line [8], 0); } if (isspace (cqueue[0]) || cqueue[0] == EOF) if (isspace (cqueue[0])) return cbf_return_text (DEFINE, val, &line [8], 0); } } /* SAVE ([Ss][Aa][Vv][Ee][_][^[:space:]]*) */ if (save) { if (length < 5) { save = toupper (cqueue[0]) == "SAVE_" [length]; } else { if ( length == 81 ) cbf_log(handle, "save frame name exceeds 75 characters", CBF_LOGERROR|CBF_LOGSTARTLOC); if ((file->read_headers & CBF_PARSE_CIF2_DELIMS) && (cqueue[0] == '{' || cqueue[0] == '}' || cqueue[0] == '\'' || cqueue[0] == '"' || cqueue[0] == ',' || cqueue[0] == ':')) { cbf_log(handle,"invalid separator ",CBF_LOGWARNING|CBF_LOGCURRENTLOC); if (cqueue[0] != ',' && cqueue[0] != ':' ) { cbf_errornez(cbf_lex_unget(file,val,cqueue), val) } if (length==5) return SAVEEND; return cbf_return_text (SAVE, val, &line [5], 0); } if (isspace (cqueue[0]) || cqueue[0] == EOF) { if (length==5) return SAVEEND; return cbf_return_text (SAVE, val, &line [5], 0); } } } /* LOOP ([Ll][Oo][Oo][Pp][_]) */ if (loop) { loop = 0; if (length < 5) loop = (toupper (cqueue[0]) == "LOOP_" [length]); if ((!loop) && (length == 5)) { if ((file->read_headers & CBF_PARSE_CIF2_DELIMS) && (cqueue[0] == '{' || cqueue[0] == '}' || cqueue[0] == '\'' || cqueue[0] == '"' || cqueue[0] == ',' || cqueue[0] == ':')) { cbf_log(handle,"invalid separator ",CBF_LOGWARNING|CBF_LOGCURRENTLOC); if (cqueue[0] != ',' && cqueue[0] != ':' ) { cbf_errornez(cbf_lex_unget(file,val,cqueue), val) } return LOOP; } if (isspace(cqueue[0]) || cqueue[0] == EOF) return LOOP; cbf_log(handle, "\"loop_\" must be followed by white space", CBF_LOGERROR|CBF_LOGSTARTLOC ); cbf_errornez(cbf_lex_unget(file,val,cqueue), val) return LOOP; } } /* ITEM ([_][^[:space:]\.]+) */ if (item) { if (length == 0) { item = cqueue[0] == '_'; } else { item = !isspace (cqueue[0]) && cqueue[0] != '.' && cqueue[0] != EOF; if (item && (file->read_headers & CBF_PARSE_CIF2_DELIMS) && (cqueue[0] == '{' || cqueue[0] == '}' || cqueue[0] == '\'' || cqueue[0] == '"' || cqueue[0] == ',' || cqueue[0] == ':')) { cbf_log(handle,"invalid separator ",CBF_LOGWARNING|CBF_LOGCURRENTLOC); if (cqueue[0] != ',' && cqueue[0] != ':' ) { cbf_errornez(cbf_lex_unget(file,val,cqueue), val) } item = 0; } if (length >= 2 && !item) { if (cqueue[0] == '.') { if ( length > 74 ) cbf_log(handle, "category name exceeds 73 characters", CBF_LOGERROR|CBF_LOGSTARTLOC); return cbf_return_text (CATEGORY, val, &line [1], 0); } else { /* if ( length > 75 ) cbf_log(handle, "data item name exceeds 75 characters", CBF_LOGERROR|CBF_LOGSTARTLOC); */ return cbf_return_text (ITEM, val, &line [0], 0); } } } } /* COLUMN (\.[^[:space:]]+) */ if (column) { column = (!isspace(cqueue[0]) && cqueue[0] != EOF); if (column && (file->read_headers & CBF_PARSE_CIF2_DELIMS) && (cqueue[0] == '{' || cqueue[0] == '}' || cqueue[0] == '\'' || cqueue[0] == '"' || cqueue[0] == ',' || cqueue[0] == ':')) { cbf_log(handle,"invalid separator ",CBF_LOGWARNING|CBF_LOGCURRENTLOC); if (cqueue[0] != ',' && cqueue[0] != ':' ) { cbf_errornez(cbf_lex_unget(file,val,cqueue), val) } column = 0; } if (!column) return cbf_return_text (COLUMN, val, &line [1], 0); } /* STRING ([\'][^'\n]*[\':space:]) | ([\"][^"\n]*[\":space:]) | or any of the bracketed constructs The parse is controlled by the variables depth and index. depth 0 top level depth 1, 2, ... within a bracketed construct state 0 looking for the next item state 1 found the first item, looking for then end of the item on entry, the commentfile buffer has all the leading whitespace. This can be left as is to be picked up by the parser, except for the bracketed constructs. For the bracketed constructs, we need to bracket the possible internal comments and whitespace. */ if (string && length==0 && (cqueue[0] == '\'' || cqueue[0] == '"' || ((file->read_headers & CBF_PARSE_BRC) && cqueue[0]=='{') || ((file->read_headers & CBF_PARSE_PRN) && cqueue[0]=='(') || ((file->read_headers & CBF_PARSE_BKT) && cqueue[0]=='[') ) ) { int *tokentype; int **vtokentype; size_t tokentype_size; int *state; int **vstate; size_t state_size; int *index; int **vindex; size_t index_size; tokentype_size = state_size = index_size = 0; vtokentype = &tokentype; vstate = &state; vindex = &index; /* Add the boundary character to the text */ cbf_errornez (cbf_save_character_trim (file, (cqueue[0]&0xFF)), val); /* initialize depth */ depth = 0; /* for the bracketed constructs, set up the stacks */ if (((file->read_headers & CBF_PARSE_BRC) && cqueue[0]=='{') || ((file->read_headers & CBF_PARSE_PRN) && cqueue[0]=='(') || ((file->read_headers & CBF_PARSE_BKT) && cqueue[0]=='[')) { depth = 1; tokentype_size = state_size = index_size = 100; cbf_errornez(cbf_alloc((void **)vtokentype, NULL, sizeof(int), tokentype_size), val) cbf_onerrornez(cbf_alloc((void **)vstate, NULL, sizeof(int), state_size), val, cbf_free((void **)vtokentype, NULL)) cbf_onerrornez(cbf_alloc((void **)vindex, NULL, sizeof(int), index_size), val, {cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL);}) state[depth-1] = index[depth-1] = 0; switch(cqueue[0]) { case ('[') : tokentype[depth-1]=CBF_TOKEN_BKTSTRING; break; case ('{') : tokentype[depth-1]=CBF_TOKEN_BRCSTRING; break; case ('(') : tokentype[depth-1]=CBF_TOKEN_PRNSTRING; break; } } /* now loop though the characters until the terminator */ do { int savechar=1; /* flag to save the character */ int breakout=0; /* flag to break out of the loop */ /* refresh the line array in case the buffer expanded */ cbf_errornez (cbf_get_buffer (file, &line, &length), val) cqueue[4] = cqueue[3]; cqueue[3] = cqueue[2]; cqueue[2] = cqueue[1]; cqueue[1] = cqueue[0]; cqueue[0] = cbf_read_character (file); if (cqueue[1] == '\\' && cqueue[2] == '\\') cqueue[1] += 0x100; /* check for a triple quote */ q3 = (((file->read_headers & CBF_PARSE_TQ ) != 0) && length > 3 && (line[0]=='\'' || line[0]=='"') && line[1] == line[0] && line[2] == line[1]); if (file->column == file->columnlimit+1) { cbf_log(handle, "over line size limit", CBF_LOGWARNING|CBF_LOGCURRENTLOC); } /* report invalid characters */ if (isspace (cqueue[0])) { if (cqueue[0]== '\013' || cqueue[0] == '\014') cbf_log(handle,"invalid space character",CBF_LOGWARNING|CBF_LOGCURRENTLOC); if ((file->read_headers & CBF_PARSE_WS) && depth > 0) { cbf_errornez (cbf_save_character_trim (handle->commentfile, (cqueue[0]&0xFF)), val) } } else { if ( cqueue[0] != EOF && ((unsigned char)cqueue[0] > 126 || (unsigned char )cqueue[0] < 32 ) ) cbf_log(handle,"invalid character",CBF_LOGWARNING|CBF_LOGCURRENTLOC); } if (depth == 0) { /* handle the non-bracketed case */ if ((file->read_headers & CBF_PARSE_CIF2_DELIMS)) { string = !(!q3 && cqueue[0] == line[0] && cqueue[1]!='\\' && length > 1) && !( q3 && length > 5 && cqueue[0] == line[0] && cqueue[1] == line[1] && cqueue[2] == line[2] && (cqueue[3] != '\\' )); if (!string) { cbf_errornez (cbf_save_character_trim (file, (cqueue[0]&0xFF)), val) cqueue[4] = cqueue[3]; cqueue[3] = cqueue[2]; cqueue[2] = cqueue[1]; cqueue[1] = cqueue[0]; cqueue[0] = cbf_read_character (file); if (cqueue[1] == '\\' && cqueue[2] == '\\') cqueue[1] += 0x100; if (!isspace(cqueue[0])) { cbf_log(handle,"invalid separator ",CBF_LOGWARNING|CBF_LOGCURRENTLOC); } } } else { string = !(!q3 && cqueue[1] == line[0] && length > 1 && isspace(cqueue[0])) && !( q3 && length > 5 && cqueue[1] == line[0] && cqueue[2] == line[1] && cqueue[3] == line[2] && isspace(cqueue[0])); } if ( string && ( (cqueue[0] == '\n' && !q3) || cqueue[0] == EOF ) ) { if (line[0] == '\'' && !q3) cbf_log(handle,"premature end of single-quoted string", CBF_LOGWARNING|CBF_LOGSTARTLOC); else { if (line[0] == '"' && !q3) cbf_log(handle,"premature end of double-quoted string", CBF_LOGWARNING|CBF_LOGSTARTLOC); else if (q3) cbf_log(handle,"premature end of triple-quoted string", CBF_LOGWARNING|CBF_LOGSTARTLOC); } string = 0; } if ( !string ) { if ( cqueue[1] == line[0] && file->buffer_used > 0 ) { file->buffer_used--; file->buffer [file->buffer_used] = '\0'; if (q3 && cqueue[2] == line[0] && file->buffer_used > 0 ) { file->buffer_used--; file->buffer [file->buffer_used] = '\0'; if (q3 && cqueue[3] == line[0] && file->buffer_used > 0 ) { file->buffer_used--; file->buffer [file->buffer_used] = '\0'; } } } if (line [0] == '\'') return cbf_return_text (STRING, val, &line [1], CBF_TOKEN_SQSTRING); else return cbf_return_text (STRING, val, &line [1], CBF_TOKEN_DQSTRING); } cbf_errornez (cbf_save_character_trim (file, (cqueue[0]&0xFF)), val); continue; } else { /* handle the bracketed cases */ savechar = 0; breakout = 0; switch (state[depth-1]) { /* In state 1 we have started an item and are looking for the end of the item. The possibilities are that the item we are parsing is 1. A single-quoted string 2. A double-quoted string 3. A triple-single-quoted string (only if CBF_PARSE_TQ is set) 4. A triple-double-quoted string (only if CBF_PARSE_TQ is set) 5. A parenthesis-bracketed string 6. A brace-bracketed string 7. A bracket-bracketed string 8. A blank-bracketed string (requires a warning) 9. A bracket-bracketed item (requires a warning) In all cases, the depth will have been increased by 1 and the appropriate token type stored in tokentype[depth-1], and index[depth-1] will accumulate the number of characters It is important that this code come before the code for state 2 so that we can fall through. */ case (1): /* See if we are looking for a terminal quote mark */ if (cbf_token_term(tokentype[depth-1])=='\'' || cbf_token_term(tokentype[depth-1])=='"' ) { string = ( cqueue[1] != cbf_token_term(tokentype[depth-1]) || index[depth-1] < 1 || !(isspace(cqueue[0])||cqueue[0]==','||cqueue[0]==cbf_token_term(tokentype[depth-2]) ) ); if (index[depth-1] == 2 && cqueue[0]==cqueue[1] && cqueue[1]==cqueue[2] && (cqueue[3] != '\\') && (file->read_headers & CBF_PARSE_TQ ) != 0) { tokentype[depth-1] = tokentype[depth-1]==CBF_TOKEN_SQSTRING?CBF_TOKEN_TSQSTRING:CBF_TOKEN_TDQSTRING; } if (tokentype[depth-1]==CBF_TOKEN_TSQSTRING || tokentype[depth-1]==CBF_TOKEN_TDQSTRING) { string = !(cqueue[1] == cbf_token_term(tokentype[depth-1]) && cqueue[2] == cqueue[1] && cqueue[3]==cqueue[2] && index[depth-1] > 5 && (isspace(cqueue[0])||cqueue[0]==','||cqueue[0]==cbf_token_term(tokentype[depth-2]) )); if (string && cqueue[0] == EOF) { if (cbf_token_term(tokentype[depth-1]) == '\'') { cbf_log(handle,"ended before end of triple single-quoted string", CBF_LOGWARNING|CBF_LOGSTARTLOC); } else { cbf_log(handle,"ended before end of triple double-quoted string", CBF_LOGWARNING|CBF_LOGSTARTLOC); } string = 0; } } else { /* not treble-quoted, just ' or " single quoted */ if ( string && ( cqueue[0] == '\n' || cqueue[0] == EOF ) ) { if (cbf_token_term(tokentype[depth-1]) == '\'') { cbf_log(handle,"ended before end of single-quoted string", CBF_LOGWARNING|CBF_LOGSTARTLOC); } else { cbf_log(handle,"ended before end of double-quoted string", CBF_LOGWARNING|CBF_LOGSTARTLOC); } string = 0; } } if ( !string ) { depth--; /* drop down from this level */ state[depth-1]++; if (depth==1 && cqueue[0]==cbf_token_term(tokentype[0])) { int ttype=tokentype[0]; cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL); /* trim all trailing whitespace in bracketed constructs */ for (ii=length-1; ii >=0 && isspace(line[ii]); ii--); file->buffer[ii+1] = '\0'; return cbf_return_text (STRING, val, (line[1]=='\\'&&line[2]=='\n')?(&line[3]):(&line [1]), ttype); } savechar = 0; if (cqueue[0] == EOF || cqueue[0] == '\n') { if (cqueue[0] == EOF) breakout = 1; break; } if (!isspace(cqueue[0])) savechar = 1; /* intentionally fail to do a break */ } else { savechar = 1; breakout = 0; index[depth-1]++; break; } } else { /* We are not looking for a terminal quote mark */ /* on a blank-delimited item we may end on a blank, comma or the next level terminator, or to handle such constructs as [*[5]] on the starting delimiter of an embedded bracketed structure*/ if (cbf_token_term(tokentype[depth-1])==' ') { /* we are still in a blank-delimited item if the character is not a space, not a comma and not an opening bracket and not a closing bracket bracket from the next level. The string also ends at eol or eof */ string = ( !isspace(cqueue[0])) && !(cqueue[0]==','|| cqueue[0]=='('|| cqueue[0]=='['|| cqueue[0]=='{'|| cqueue[0]==cbf_token_term(tokentype[depth-2]) ); if ( string && ( cqueue[0] == '\n' || cqueue[0] == EOF ) ) { string = 0; } if ( !string ) { if (file->read_headers & CBF_PARSE_WS) { if(cqueue[0]==')' || cqueue[0]=='}' || cqueue[0]==']'){ cbf_onerrornez (cbf_save_character_trim (handle->commentfile, ')'), val, { cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL);}) } if(cqueue[0]=='[' || cqueue[0]=='{' || cqueue[0]=='['){ cbf_onerrornez (cbf_save_character_trim (handle->commentfile, ','), val, { cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL);}) cbf_onerrornez (cbf_save_character_trim (handle->commentfile, '('), val, { cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL);}) cbf_errornez (cbf_set_ws_column (handle->commentfile, file->column+1), val) } } if(cqueue[0]=='(' || cqueue[0]=='{' || cqueue[0]=='['){ savechar = 0; index[depth-2]++; index[depth-1] = state[depth-1] = 0; switch(cqueue[0]) { case ('[') : tokentype[depth-1]=CBF_TOKEN_BKTSTRING; break; case ('{') : tokentype[depth-1]=CBF_TOKEN_BRCSTRING; break; case ('(') : tokentype[depth-1]=CBF_TOKEN_PRNSTRING; break; } cbf_onerrornez (cbf_save_character_trim (file, (cqueue[0]&0xFF)), val, {cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL);}) breakout = 0; break; } if (!isspace(cqueue[0])&&depth>1&&cqueue[0]!=',') depth--; depth--; state[depth-1]++; savechar = 1; breakout = 0; if (depth==0 && cqueue[0]==cbf_token_term(tokentype[0])) { int ttype=tokentype[0]; cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL); /* trim all trailing whitespace in bracketed constructs */ for (ii=length-1; ii >=0 && isspace(line[ii]); ii--); file->buffer[ii+1] = '\0'; return cbf_return_text (STRING, val, (line[1]=='\\'&&line[2]=='\n')?(&line[3]):(&line [1]), ttype); } if (cqueue[0] == EOF) breakout = 1; break; } else { savechar = 1; breakout = 0; index[depth-1]++; break; } } else { if (cbf_token_term(tokentype[depth-1])==';') { string = ( cqueue[2] != '\n' || cqueue[1] != cbf_token_term(tokentype[depth-1]) || index[depth-1] < 3 || !(isspace(cqueue[0]) || cqueue[0]==','||cqueue[0]==cbf_token_term(tokentype[depth-2])||(file->read_headers & CBF_PARSE_CIF2_DELIMS) ) ); if ( cqueue[0] == EOF ) { string = 0; } if ( !string ) { if (file->read_headers & CBF_PARSE_WS) { cbf_onerrornez (cbf_save_character_trim (handle->commentfile, ')'), val, { cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL);}) } depth--; state[depth-1]++; savechar = 0; breakout = 0; if (depth==1 && cqueue[0]==cbf_token_term(tokentype[0])) { int ttype=tokentype[0]; cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL); /* trim all trailing whitespace in bracketed constructs */ for (ii=length-1; ii >=0 && isspace(line[ii]); ii--); file->buffer[ii+1] = '\0'; return cbf_return_text (STRING, val, (line[1]=='\\'&&line[2]=='\n')?(&line[3]):(&line [1]), ttype); } if (cqueue[0] == EOF) breakout = 1; break; } else { savechar = 1; breakout = 0; index[depth-1]++; break; } } else { cbf_log(handle,"unrecognized bracketed construct item", CBF_LOGWARNING|CBF_LOGSTARTLOC); } } } /* In state 2 we have completed an item and need to scan for a comma or a terminator. Since we are not breaking out the items, we merge this case with state 0. */ case (2): /* In state 0 we are looking for an item for the construct We may encounter a comment, a space, a comma, a terminator for the construct or the beginning of an item If we are parsing whitespace, comments and space simply get appended to the whitespace. */ case (0): if (cqueue[0]=='#') { /* if we are parsing whitespace and encounter a comment the entire comment including the '\n' gets appended to the whitespace, converting an EOF to a '\n' */ if (file->read_headers & CBF_PARSE_WS) { cbf_onerrornez (cbf_save_character_trim (handle->commentfile, (cqueue[0]&0xFF)), val, { cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL);}) } do { cqueue[4] = cqueue[3]; cqueue[3] = cqueue[2]; cqueue[2] = cqueue[1]; cqueue[1] = cqueue[0]; cqueue[0] = cbf_read_character (file); if (cqueue[1] == '\\' && cqueue[2] == '\\') cqueue[1] += 0x100; if (file->column == file->columnlimit+1) { cbf_log(handle, "over line size limit", CBF_LOGWARNING|CBF_LOGCURRENTLOC); } if (file->read_headers & CBF_PARSE_WS) { if (cqueue[0] == EOF) { cbf_onerrornez (cbf_save_character_trim (handle->commentfile, '\n'), val, { cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL);}) } else { cbf_onerrornez (cbf_save_character_trim (handle->commentfile, (cqueue[0]&0xFF)), val, { cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL);}) } } if (isspace (cqueue[0])) { if (cqueue[0]== '\013' || cqueue[0] == '\014') cbf_log(handle,"invalid space character",CBF_LOGWARNING|CBF_LOGCURRENTLOC); } if ( cqueue[0] != EOF && ((unsigned char)cqueue[0] > 126 || (unsigned char )cqueue[0] < 32 ) ) cbf_log(handle,"invalid character",CBF_LOGWARNING|CBF_LOGCURRENTLOC); } while (cqueue[0] != '\n' && cqueue[0] != EOF); } if (cqueue[0]==EOF) { int ttype=tokentype[0]; cbf_log(handle,"file ended before end of bracketed construct", CBF_LOGWARNING|CBF_LOGSTARTLOC); cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL); if (file->read_headers & CBF_PARSE_WS) { cbf_errornez (cbf_save_character_trim (handle->commentfile, '\n'), val) } return cbf_return_text (STRING, val, (line[1]=='\\'&&line[2]=='\n')?(&line[3]):(&line [1]), ttype); } if (isspace(cqueue[0])) { if (file->read_headers & CBF_PARSE_WS) { cbf_errornez (cbf_save_character_trim (handle->commentfile, (cqueue[0]&0xFF)), val) } savechar = 0; breakout = 0; break; } if (cqueue[0]==',' ) { savechar = 1; /* Keep the comma */ breakout = 0; /* depth--; */ /* Stay at this level */ index[depth-1]++; state[depth-1] = 0; /* Search for a non-blank */ /* If we encounter a comma, it is time to break up the whitespace as well */ if (file->read_headers & CBF_PARSE_WS) { cbf_errornez (cbf_save_character_trim (handle->commentfile, ','), val) cbf_errornez (cbf_set_ws_column (handle->commentfile, file->column+1), val) } break; } if (cqueue[0]==cbf_token_term(tokentype[depth-1]) && (cbf_token_term(tokentype[depth-1])==';'?'\n':cqueue[1])==cqueue[1]) { savechar = 1; breakout = 0; if (depth > 0)depth--; /* end the bracket */ if (depth==0) { int ttype=tokentype[0]; cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL); /* trim all trailing whitespace in bracketed constructs */ for (ii=length-1; ii >=0 && isspace(line[ii]); ii--); file->buffer[ii+1] = '\0'; return cbf_return_text (STRING, val, (line[1]=='\\'&&line[2]=='\n')?(&line[3]):(&line [1]), ttype); } /* If we encounter the closing bracket, it is time to break up the whitespace as well */ if (file->read_headers & CBF_PARSE_WS) { cbf_errornez (cbf_save_character_trim (handle->commentfile, ')'), val) } state[depth-1]++; break; } if ( !isspace(cqueue[0])) { if (file->read_headers & CBF_PARSE_WS) { cbf_onerrornez (cbf_save_character_trim (handle->commentfile, ','), val, { cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL);}) if (cqueue[0] == '[' || cqueue[0] == '(' || cqueue[0] == '{') { cbf_onerrornez (cbf_save_character_trim (handle->commentfile, '('), val, { cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL);}) } cbf_onerrornez (cbf_set_ws_column (handle->commentfile, file->column+1), val, { cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL);}) } if (state[depth-1]==2) { /* if (!(length==3 && line[1]=='\\' && line[2]=='\n')) { cbf_onerrornez (cbf_save_character_trim (file, ' '), val, { cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL);}) } */ state[depth-1]=0; } state[depth-1]++; savechar = 0; depth++; if (depth > tokentype_size) { cbf_onerrornez(cbf_realloc((void **)vtokentype, NULL, sizeof(int),tokentype_size*2), val,{cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL);}) tokentype_size *= 2; } if (depth > state_size) { cbf_onerrornez(cbf_realloc((void **)vstate, NULL, sizeof(int),state_size*2), val,{cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL);}) state_size *= 2; } if (depth > index_size) { cbf_onerrornez(cbf_realloc((void **)vindex, NULL, sizeof(int),index_size*2), val,{cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL);}) index_size *= 2; } index[depth-1] = state[depth-1] = 0; switch(cqueue[0]) { case ('\'') : tokentype[depth-1]=CBF_TOKEN_SQSTRING; state[depth-1] = 1; break; case ('"') : tokentype[depth-1]=CBF_TOKEN_DQSTRING; state[depth-1] = 1; break; case ('[') : tokentype[depth-1]=CBF_TOKEN_BKTSTRING; break; case ('{') : tokentype[depth-1]=CBF_TOKEN_BRCSTRING; break; case ('(') : tokentype[depth-1]=CBF_TOKEN_PRNSTRING; break; case (';') : if (cqueue[1]=='\n') { tokentype[depth-1]=CBF_TOKEN_SCSTRING; state[depth-1] = 1; cbf_onerrornez (cbf_save_character_trim (file, '\n'), val, {cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL);}) break; } default: tokentype[depth-1]= CBF_TOKEN_WORD; state[depth-1] = 1; break; } cbf_onerrornez (cbf_save_character_trim (file, (cqueue[0]&0xFF)), val, {cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL);}) breakout = 0; break; } savechar = 1; breakout = 0; break; } if (savechar) { cbf_onerrornez (cbf_save_character_trim (file, (cqueue[0]&0xFF)), val, {cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL);}) if (cqueue[0]=='\n' && line[1]=='\\' && file->buffer_used > 3 && line[2]=='\n' && file->buffer[file->buffer_used-2]=='\\') { file->buffer_used -=2; cqueue[0] = file->buffer[file->buffer_used-1]; file->buffer[file->buffer_used] = '\0'; } } if (breakout) break; } } while (cqueue[0] != EOF); } else { string = 0; } /* COMMENT ([#][^\n]*) */ if (comment) { if (length == 0) { comment = cqueue[0] == '#'; } else { comment = (cqueue[0] != '\n' && cqueue[0]!= EOF); if ((! comment) && !(file->read_headers & CBF_PARSE_WS)) { return cbf_return_text (COMMENT, val, &line [1], 0); } } if (!comment && length != 0) { cbf_errornez (cbf_get_buffer (file, &line, &length), val) for (ii = 0; ii < length; ii++) { cbf_errornez (cbf_save_character_trim (handle->commentfile, line[ii]), val) } cbf_errornez (cbf_save_character_trim (handle->commentfile, '\n'), val) cbf_errornez (cbf_reset_buffer (file), val) cbf_errornez (cbf_get_buffer (file, &line, &length), val) cqueue[4] = cqueue[3] = cqueue[2] = cqueue[1] = ' '; column = reprocess = 0; data = save = loop = item = string = comment = 1; continue; } } /* CBFWORD ([^[:space:]]+) */ if (!data && !loop && !item && !comment && !string && !column) { if (length && (file->read_headers & CBF_PARSE_CIF2_DELIMS) && (cqueue[0] == '{' || cqueue[0] == '}' || cqueue[0] == '\'' || cqueue[0] == '"' || cqueue[0] == ',' || cqueue[0] == ':')) { cbf_log(handle,"invalid separator ",CBF_LOGWARNING|CBF_LOGCURRENTLOC); if (cqueue[0] != ',' && cqueue[0] != ':' ) { cbf_errornez(cbf_lex_unget(file,val,cqueue), val) } cqueue[0] = ' '; } if (length && (isspace (cqueue[0]) || cqueue[0] == EOF)) { /* Missing value? */ if (length == 1 && (line [0] == '?' || line [0] == '.')) return cbf_return_text (CBFWORD, val, &line [0], CBF_TOKEN_NULL); else return cbf_return_text (CBFWORD, val, &line [0], CBF_TOKEN_WORD); } } /* semicolon-delimited STRING (^;[^\n]*[\n])([^;][^\n]*[\n])*(;) */ if (length == 0 && cqueue[0] == ';') { cbf_errornez (cbf_get_filecoordinates (file, NULL, &file_column), val) if (file_column == 1) { /* Save the position */ cbf_errornez (cbf_get_fileposition (file, &position), val) mime = 0; do { /* Save the character */ cbf_errornez (cbf_save_character_trim (file, (cqueue[0]&0xFF)), val) /* Check for a Mime boundary */ if (cqueue[0] == '-') { cbf_errornez (cbf_get_buffer (file, &line, &length), val) cbf_nblen (line, &length); if (length > 29) mime = cbf_cistrcmp (&line [length - 30], "\n--CIF-BINARY-FORMAT-SECTION--") == 0; } /* Read the next character */ cqueue[4] = cqueue[3]; cqueue[3] = cqueue[2]; cqueue[2] = cqueue[1]; cqueue[1] = cqueue[0]; cqueue[0] = cbf_read_character (file); if (cqueue[1] == '\\' && cqueue[2] == '\\') cqueue[1] += 0x100; ascii = isgraph (cqueue[0]) || isspace (cqueue[0]); if (!ascii && (unsigned char)cqueue[0]!=12 && (unsigned char)cqueue[0]!=26 && (unsigned char)cqueue[0]!=4 && cqueue[0] != EOF) { cbf_log(handle,"invalid character in text field", CBF_LOGWARNING|CBF_LOGCURRENTLOC); ascii = 1; } if (ascii) { if (file->column == file->columnlimit+1) { cbf_log(handle, "over line size limit", CBF_LOGWARNING|CBF_LOGCURRENTLOC); } } } while ((cqueue[2] != '\n' || cqueue[1] != ';' || file->buffer_used < 3 || !(isspace(cqueue[0]) || cqueue[0]==EOF ||(file->read_headers & CBF_PARSE_CIF2_DELIMS))) && !mime && ascii && cqueue[0] != EOF); if ( cqueue[0] == EOF && (cqueue[1] != ';' || cqueue[2] != '\n')) { cbf_log(handle, "text field terminated by EOF", CBF_LOGERROR|CBF_LOGCURRENTLOC); } /* Plain ASCII string or terminated by EOF */ if ((!mime && ascii) || cqueue[0]==EOF) { cbf_errornez (cbf_get_buffer (file, &line, &length), val) ((char *) line) [(length>2)?(length - 2):1] = '\0'; return cbf_return_text (STRING, val, &line [1], CBF_TOKEN_SCSTRING); } encoding = ENC_NONE; bits = 0; sign = -1; real = -1; checked_digest = 0; /* Mime header */ if (mime) { /* Position */ cbf_errornez (cbf_get_fileposition (file, &position), val) /* Read the header */ dimover=dimfast=dimmid=dimslow=padding = 0; byteorder="little_endian"; cbf_errornez (cbf_parse_mimeheader (file, &encoding, &size, &id, digest, &compression, &bits, &sign, &real, &byteorder, &dimover, &dimfast, &dimmid, &dimslow, &padding), val); /* Attempt recovery from missing size */ if (size == 0) { cbf_log(handle, "binary size missing, attempting recovery", CBF_LOGWARNING|CBF_LOGCURRENTLOC); size = (dimover*bits+7)/8; switch (compression) { case CBF_CANONICAL: case CBF_PACKED: case CBF_PACKED_V2: size /= 4; break; case CBF_BYTE_OFFSET: if (bits < 32) size /= 2; else size /=4; break; } } /* Check the digest? */ if ((file->read_headers & (MSG_DIGESTNOW|MSG_DIGESTWARN) ) && cbf_is_base64digest (digest)) { /* Recalculate the digest (note that this will decode the binary section but not save the result so this section is not very efficient) */ code_size = 0; switch (encoding) { case ENC_QP: cbf_errornez (cbf_fromqp (file, NULL, size, &code_size, new_digest), val) break; case ENC_BASE64: cbf_errornez (cbf_frombase64 (file, NULL, size, &code_size, new_digest), val) break; case ENC_BASE32K: cbf_errornez (cbf_frombase32k (file, NULL, size, &code_size, new_digest), val) break; case ENC_BASE8: case ENC_BASE10: case ENC_BASE16: cbf_errornez (cbf_frombasex (file, NULL, size, &code_size, new_digest),val) break; case ENC_NONE: cbf_errornez (cbf_parse_binaryheader (file, NULL, \ NULL, \ NULL, \ mime), val) code_size = size; cbf_errornez (cbf_get_fileposition (file, &position), val) cbf_errornez (cbf_md5digest (file, code_size, new_digest), val) break; default: cbf_errornez (CBF_FORMAT, val) } /* Check the number of characters read */ if ((size && (size != code_size)) || code_size == 0) { cbf_log(handle, "size required to process digest", CBF_LOGERROR|CBF_LOGCURRENTLOC); cbf_errornez (CBF_FORMAT, val) } /* Compare the old digest to the new one */ if (strcmp (digest, new_digest) != 0) { if((file->read_headers & MSG_DIGESTWARN) ) { char buffer[80]; sprintf(buffer, "digest mismatch file %s data %s", digest, new_digest ); cbf_log(handle, buffer, CBF_LOGWARNING|CBF_LOGCURRENTLOC); } else { cbf_errornez (CBF_FORMAT | 2, val) } } checked_digest = 1; } else { /* Calculate the minimum number of characters in the data */ if (encoding == ENC_NONE) { cbf_errornez (cbf_parse_binaryheader (file, NULL, NULL, NULL, \ mime), val) cbf_errornez (cbf_get_fileposition (file, &position), val) code_size = size; } else if (encoding == ENC_QP) code_size = size; else if (encoding == ENC_BASE64) code_size = size * 8 / 6; else if (encoding == ENC_BASE32K) code_size = size * 16 / 15; else code_size = size / 4; /* Skip to the end of the data */ cbf_errornez (cbf_set_fileposition (file, code_size, SEEK_CUR), val) } } else { /* Simple binary */ cbf_errornez (cbf_parse_binaryheader (file, &size, \ &id, \ &compression, mime), val) cbf_errornez (cbf_get_fileposition (file, &position), val) code_size = size; /* Skip to the end of the data */ cbf_errornez (cbf_set_fileposition (file, code_size, SEEK_CUR), val) } /* Find the terminating semi-colon */ cqueue[3] = cqueue[2] = cqueue[1] = cqueue[0] = 0; if (mime) { do { if (cqueue[0]==EOF) break; cqueue[4] = cqueue[3]; cqueue[3] = cqueue[2]; cqueue[2] = cqueue[1]; cqueue[1] = cqueue[0]; cqueue[0] = cbf_read_character (file); if (cqueue[1] == '\\' && cqueue[2] == '\\') cqueue[1] += 0x100; if (cqueue[0] == EOF && (cqueue[2] != '\n' || cqueue[1] != ';')) { cbf_log(handle, "text field terminated by EOF", CBF_LOGERROR|CBF_LOGCURRENTLOC); cbf_errornez (CBF_FILEREAD, val) } } while ( !(cqueue[3] == '-' && cqueue[2] == '-' && cqueue[1] =='-' && cqueue[0]=='-')); } do { if (cqueue[0]==EOF) break; cqueue[4] = cqueue[3]; cqueue[3] = cqueue[2]; cqueue[2] = cqueue[1]; cqueue[1] = cqueue[0]; cqueue[0] = cbf_read_character (file); if (cqueue[1] == '\\' && cqueue[2] == '\\') cqueue[1] += 0x100; if (cqueue[0] == EOF && (cqueue[2] != '\n' || cqueue[1] != ';')) { cbf_log(handle, "text field terminated by EOF", CBF_LOGERROR|CBF_LOGCURRENTLOC); cbf_errornez (CBF_FILEREAD, val) } } while ( !(cqueue[2] == '\n' && cqueue[1] ==';' && (isspace(cqueue[0]) || cqueue[0]==EOF || (file->read_headers & CBF_PARSE_CIF2_DELIMS)))); /* Check the element size and sign */ if (bits < 0 || bits > 64) cbf_errornez (CBF_FORMAT, val) if (bits == 0) bits = 32; if (sign == -1) sign = 1; /* Add a connection */ cbf_errornez (cbf_add_fileconnection (&file, NULL), val) /* Code the id, file, position, size and digest */ if (!cbf_is_base64digest (digest)) strcpy (digest, "------------------------"); sprintf (out_line, "%lx %p %lx %lx %d %s %x %d %d %s %ld %ld %ld %ld %ld %u", id, (void *)file, position, (unsigned long) size, checked_digest, digest, bits, sign, real<1?0:1, byteorder, (unsigned long)dimover, (unsigned long)dimfast, (unsigned long)dimmid, (unsigned long)dimslow, (unsigned long)padding, compression); if (encoding == ENC_NONE) errorcode = cbf_return_text (BINARY, val, out_line, CBF_TOKEN_BIN); else errorcode = cbf_return_text (BINARY, val, out_line, CBF_TOKEN_MIME_BIN); if (errorcode == ERROR) val->errorcode |= cbf_delete_fileconnection (&file); return errorcode; } } /* Add the character to the text */ errorcode = cbf_save_character_trim (file, (cqueue[0]&0xFF)); cbf_errornez (errorcode, val); } while (cqueue[0] != EOF); return 0; } #ifdef __cplusplus } #endif ./CBFlib-0.9.2.2/src/cbf_stx.c0000644000076500007650000036050311603702106014170 0ustar yayayaya/* A Bison parser, made by GNU Bison 2.3. */ /* Skeleton implementation for Bison's Yacc-like parsers in C Copyright (C) 1984, 1989, 1990, 2000, 2001, 2002, 2003, 2004, 2005, 2006 Free Software Foundation, Inc. This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* As a special exception, you may create a larger work that contains part or all of the Bison parser skeleton and distribute that work under terms of your choice, so long as that work isn't itself a parser generator using the skeleton or a modified version thereof as a parser skeleton. Alternatively, if you modify or redistribute the parser skeleton itself, you may (at your option) remove this special exception, which will cause the skeleton and the resulting Bison output files to be licensed under the GNU General Public License without this special exception. This special exception was added by the Free Software Foundation in version 2.2 of Bison. */ /* C LALR(1) parser skeleton written by Richard Stallman, by simplifying the original so-called "semantic" parser. */ /* All symbols defined below should begin with yy or YY, to avoid infringing on user name space. This should be done even for local variables, as they might otherwise be expanded by user macros. There are some unavoidable exceptions within include files to define necessary library symbols; they are noted "INFRINGES ON USER NAME SPACE" below. */ /* Identify Bison output. */ #define YYBISON 1 /* Bison version. */ #define YYBISON_VERSION "2.3" /* Skeleton name. */ #define YYSKELETON_NAME "yacc.c" /* Pure parsers. */ #define YYPURE 1 /* Using locations. */ #define YYLSP_NEEDED 0 /* Tokens. */ #ifndef YYTOKENTYPE # define YYTOKENTYPE /* Put the tokens into the symbol table, so that GDB and other debuggers know about them. */ enum yytokentype { DATA = 258, DEFINE = 259, SAVE = 260, SAVEEND = 261, LOOP = 262, ITEM = 263, CATEGORY = 264, COLUMN = 265, STRING = 266, CBFWORD = 267, BINARY = 268, UNKNOWN = 269, COMMENT = 270, ERROR = 271 }; #endif /* Tokens. */ #define DATA 258 #define DEFINE 259 #define SAVE 260 #define SAVEEND 261 #define LOOP 262 #define ITEM 263 #define CATEGORY 264 #define COLUMN 265 #define STRING 266 #define CBFWORD 267 #define BINARY 268 #define UNKNOWN 269 #define COMMENT 270 #define ERROR 271 /* Copy the first part of user declarations. */ /********************************************************************** * cbf.stx -- cbf parser * * * * Version 0.7.7 19 February 2007 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifdef __cplusplus extern "C" { #endif #include #include #include #include "cbf.h" #include "cbf_tree.h" #include "cbf_alloc.h" #include "cbf_context.h" #include "cbf_ws.h" #define yyparse cbf_parse #define yylex cbf_lex_wrapper #define yyerror(x) cbf_syntax_error(((cbf_handle)(((void **)context)[2])),(x)) #define YYLEX_PARAM context #define YYPARSE_PARAM context typedef union { int errorcode; const char *text; cbf_node *node; } YYSTYPE; #define YYSTYPE_IS_DECLARED #ifdef alloca #undef alloca #endif #define alloca(x) (NULL) #define YYINITDEPTH 200 #define YYMAXDEPTH 200 int cbf_lex (cbf_handle handle, YYSTYPE *val ); /* vcontext[0] -- (void *)file vcontext[1] -- (void *)handle->node vcontext[2] -- (void *)handle vcontext[3] -- (void *)node */ int cbf_lex_wrapper (void *val, void *vcontext) { int token; cbf_handle cbfhandle; cbf_file *cbffile; do { cbffile = (cbf_file*)((void **) vcontext) [0]; cbfhandle = (cbf_handle)((void **) vcontext) [2]; token = cbf_lex (cbfhandle, (YYSTYPE *)val); if ( token == COMMENT && ((YYSTYPE *)val)->text ) { cbf_free_text(&(((YYSTYPE *)val)->text),NULL); } } while (token == COMMENT); return token; } int cbf_syntax_error (cbf_handle handle, const char *message) { cbf_log( handle, message, CBF_LOGERROR|CBF_LOGSTARTLOC ); return 0; } /* Enabling traces. */ #ifndef YYDEBUG # define YYDEBUG 0 #endif /* Enabling verbose error messages. */ #ifdef YYERROR_VERBOSE # undef YYERROR_VERBOSE # define YYERROR_VERBOSE 1 #else # define YYERROR_VERBOSE 0 #endif /* Enabling the token table. */ #ifndef YYTOKEN_TABLE # define YYTOKEN_TABLE 0 #endif #if ! defined YYSTYPE && ! defined YYSTYPE_IS_DECLARED typedef union YYSTYPE { int errorcode; const char *text; cbf_node *node; } /* Line 193 of yacc.c. */ YYSTYPE; # define yystype YYSTYPE /* obsolescent; will be withdrawn */ # define YYSTYPE_IS_DECLARED 1 # define YYSTYPE_IS_TRIVIAL 1 #endif /* Copy the second part of user declarations. */ /* Line 216 of yacc.c. */ #ifdef short # undef short #endif #ifdef YYTYPE_UINT8 typedef YYTYPE_UINT8 yytype_uint8; #else typedef unsigned char yytype_uint8; #endif #ifdef YYTYPE_INT8 typedef YYTYPE_INT8 yytype_int8; #elif (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) typedef signed char yytype_int8; #else typedef short int yytype_int8; #endif #ifdef YYTYPE_UINT16 typedef YYTYPE_UINT16 yytype_uint16; #else typedef unsigned short int yytype_uint16; #endif #ifdef YYTYPE_INT16 typedef YYTYPE_INT16 yytype_int16; #else typedef short int yytype_int16; #endif #ifndef YYSIZE_T # ifdef __SIZE_TYPE__ # define YYSIZE_T __SIZE_TYPE__ # elif defined size_t # define YYSIZE_T size_t # elif ! defined YYSIZE_T && (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) # include /* INFRINGES ON USER NAME SPACE */ # define YYSIZE_T size_t # else # define YYSIZE_T unsigned int # endif #endif #define YYSIZE_MAXIMUM ((YYSIZE_T) -1) #ifndef YY_ # if YYENABLE_NLS # if ENABLE_NLS # include /* INFRINGES ON USER NAME SPACE */ # define YY_(msgid) dgettext ("bison-runtime", msgid) # endif # endif # ifndef YY_ # define YY_(msgid) msgid # endif #endif /* Suppress unused-variable warnings by "using" E. */ #if ! defined lint || defined __GNUC__ # define YYUSE(e) ((void) (e)) #else # define YYUSE(e) /* empty */ #endif /* Identity function, used to suppress warnings about constant conditions. */ #ifndef lint # define YYID(n) (n) #else #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static int YYID (int i) #else static int YYID (i) int i; #endif { return i; } #endif #if ! defined yyoverflow || YYERROR_VERBOSE /* The parser invokes alloca or malloc; define the necessary symbols. */ # ifdef YYSTACK_USE_ALLOCA # if YYSTACK_USE_ALLOCA # ifdef __GNUC__ # define YYSTACK_ALLOC __builtin_alloca # elif defined __BUILTIN_VA_ARG_INCR # include /* INFRINGES ON USER NAME SPACE */ # elif defined _AIX # define YYSTACK_ALLOC __alloca # elif defined _MSC_VER # include /* INFRINGES ON USER NAME SPACE */ # define alloca _alloca # else # define YYSTACK_ALLOC alloca # if ! defined _ALLOCA_H && ! defined _STDLIB_H && (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) # include /* INFRINGES ON USER NAME SPACE */ # ifndef _STDLIB_H # define _STDLIB_H 1 # endif # endif # endif # endif # endif # ifdef YYSTACK_ALLOC /* Pacify GCC's `empty if-body' warning. */ # define YYSTACK_FREE(Ptr) do { /* empty */; } while (YYID (0)) # ifndef YYSTACK_ALLOC_MAXIMUM /* The OS might guarantee only one guard page at the bottom of the stack, and a page size can be as small as 4096 bytes. So we cannot safely invoke alloca (N) if N exceeds 4096. Use a slightly smaller number to allow for a few compiler-allocated temporary stack slots. */ # define YYSTACK_ALLOC_MAXIMUM 4032 /* reasonable circa 2006 */ # endif # else # define YYSTACK_ALLOC YYMALLOC # define YYSTACK_FREE YYFREE # ifndef YYSTACK_ALLOC_MAXIMUM # define YYSTACK_ALLOC_MAXIMUM YYSIZE_MAXIMUM # endif # if (defined __cplusplus && ! defined _STDLIB_H \ && ! ((defined YYMALLOC || defined malloc) \ && (defined YYFREE || defined free))) # include /* INFRINGES ON USER NAME SPACE */ # ifndef _STDLIB_H # define _STDLIB_H 1 # endif # endif # ifndef YYMALLOC # define YYMALLOC malloc # if ! defined malloc && ! defined _STDLIB_H && (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) void *malloc (YYSIZE_T); /* INFRINGES ON USER NAME SPACE */ # endif # endif # ifndef YYFREE # define YYFREE free # if ! defined free && ! defined _STDLIB_H && (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) void free (void *); /* INFRINGES ON USER NAME SPACE */ # endif # endif # endif #endif /* ! defined yyoverflow || YYERROR_VERBOSE */ #if (! defined yyoverflow \ && (! defined __cplusplus \ || (defined YYSTYPE_IS_TRIVIAL && YYSTYPE_IS_TRIVIAL))) /* A type that is properly aligned for any stack member. */ union yyalloc { yytype_int16 yyss; YYSTYPE yyvs; }; /* The size of the maximum gap between one aligned stack and the next. */ # define YYSTACK_GAP_MAXIMUM (sizeof (union yyalloc) - 1) /* The size of an array large to enough to hold all stacks, each with N elements. */ # define YYSTACK_BYTES(N) \ ((N) * (sizeof (yytype_int16) + sizeof (YYSTYPE)) \ + YYSTACK_GAP_MAXIMUM) /* Copy COUNT objects from FROM to TO. The source and destination do not overlap. */ # ifndef YYCOPY # if defined __GNUC__ && 1 < __GNUC__ # define YYCOPY(To, From, Count) \ __builtin_memcpy (To, From, (Count) * sizeof (*(From))) # else # define YYCOPY(To, From, Count) \ do \ { \ YYSIZE_T yyi; \ for (yyi = 0; yyi < (Count); yyi++) \ (To)[yyi] = (From)[yyi]; \ } \ while (YYID (0)) # endif # endif /* Relocate STACK from its old location to the new one. The local variables YYSIZE and YYSTACKSIZE give the old and new number of elements in the stack, and YYPTR gives the new location of the stack. Advance YYPTR to a properly aligned location for the next stack. */ # define YYSTACK_RELOCATE(Stack) \ do \ { \ YYSIZE_T yynewbytes; \ YYCOPY (&yyptr->Stack, Stack, yysize); \ Stack = &yyptr->Stack; \ yynewbytes = yystacksize * sizeof (*Stack) + YYSTACK_GAP_MAXIMUM; \ yyptr += yynewbytes / sizeof (*yyptr); \ } \ while (YYID (0)) #endif /* YYFINAL -- State number of the termination state. */ #define YYFINAL 25 /* YYLAST -- Last index in YYTABLE. */ #define YYLAST 82 /* YYNTOKENS -- Number of terminals. */ #define YYNTOKENS 17 /* YYNNTS -- Number of nonterminals. */ #define YYNNTS 33 /* YYNRULES -- Number of rules. */ #define YYNRULES 72 /* YYNRULES -- Number of states. */ #define YYNSTATES 85 /* YYTRANSLATE(YYLEX) -- Bison symbol number corresponding to YYLEX. */ #define YYUNDEFTOK 2 #define YYMAXUTOK 271 #define YYTRANSLATE(YYX) \ ((unsigned int) (YYX) <= YYMAXUTOK ? yytranslate[YYX] : YYUNDEFTOK) /* YYTRANSLATE[YYLEX] -- Bison symbol number corresponding to YYLEX. */ static const yytype_uint8 yytranslate[] = { 0, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16 }; #if YYDEBUG /* YYPRHS[YYN] -- Index of the first RHS symbol of rule number YYN in YYRHS. */ static const yytype_uint8 yyprhs[] = { 0, 0, 3, 5, 7, 8, 11, 14, 16, 18, 20, 22, 24, 26, 28, 31, 34, 37, 39, 41, 43, 46, 49, 52, 55, 58, 61, 64, 67, 70, 73, 76, 79, 82, 85, 88, 91, 94, 97, 100, 103, 106, 109, 112, 115, 118, 121, 124, 127, 130, 133, 136, 139, 142, 145, 148, 151, 154, 157, 160, 163, 166, 169, 173, 175, 177, 179, 181, 183, 185, 187, 189, 191 }; /* YYRHS -- A `-1'-separated list of the rules' RHS. */ static const yytype_int8 yyrhs[] = { 18, 0, -1, 19, -1, 22, -1, -1, 18, 43, -1, 23, 43, -1, 19, -1, 20, -1, 27, -1, 32, -1, 24, -1, 41, -1, 28, -1, 22, 44, -1, 23, 44, -1, 21, 44, -1, 35, -1, 40, -1, 36, -1, 23, 6, -1, 22, 45, -1, 21, 45, -1, 25, 45, -1, 26, 45, -1, 25, 46, -1, 26, 47, -1, 22, 47, -1, 21, 47, -1, 26, 49, -1, 27, 49, -1, 28, 49, -1, 29, 49, -1, 22, 42, -1, 21, 42, -1, 29, 42, -1, 29, 45, -1, 31, 45, -1, 29, 47, -1, 31, 47, -1, 30, 46, -1, 31, 49, -1, 32, 49, -1, 23, 45, -1, 33, 45, -1, 34, 45, -1, 33, 46, -1, 23, 47, -1, 34, 47, -1, 34, 49, -1, 35, 49, -1, 36, 49, -1, 37, 49, -1, 23, 42, -1, 37, 42, -1, 37, 45, -1, 39, 45, -1, 37, 47, -1, 39, 47, -1, 38, 46, -1, 39, 49, -1, 40, 49, -1, 22, 48, 49, -1, 7, -1, 3, -1, 5, -1, 9, -1, 10, -1, 8, -1, 4, -1, 11, -1, 12, -1, 13, -1 }; /* YYRLINE[YYN] -- source line where rule number YYN was defined. */ static const yytype_uint16 yyrline[] = { 0, 397, 397, 400, 408, 413, 441, 475, 489, 492, 504, 516, 527, 539, 553, 567, 591, 606, 614, 622, 632, 647, 657, 669, 685, 703, 714, 734, 748, 766, 779, 790, 801, 815, 820, 825, 836, 851, 867, 887, 905, 925, 937, 952, 959, 973, 987, 995, 1008, 1030, 1043, 1052, 1060, 1073, 1078, 1088, 1099, 1115, 1131, 1147, 1164, 1174, 1186, 1204, 1207, 1212, 1217, 1222, 1227, 1232, 1237, 1240, 1243 }; #endif #if YYDEBUG || YYERROR_VERBOSE || YYTOKEN_TABLE /* YYTNAME[SYMBOL-NUM] -- String name of the symbol SYMBOL-NUM. First, the terminals, then, starting at YYNTOKENS, nonterminals. */ static const char *const yytname[] = { "$end", "error", "$undefined", "DATA", "DEFINE", "SAVE", "SAVEEND", "LOOP", "ITEM", "CATEGORY", "COLUMN", "STRING", "CBFWORD", "BINARY", "UNKNOWN", "COMMENT", "ERROR", "$accept", "cbf", "cbfstart", "CbfThruDBName", "ErrorCbfWODBName", "CbfThruDBElement", "CbfThruSFElement", "CbfThruSaveFrame", "CbfThruCategory", "CbfThruColumn", "CbfThruAssignment", "ErrorCbfThruExtraValue", "CbfThruLoopStart", "CbfThruLoopCategory", "CbfThruLoopColumn", "CbfThruLoopAssignment", "CbfThruSFCategory", "CbfThruSFColumn", "CbfThruSFAssignment", "ErrorCbfThruExtraSFValue", "CbfThruSFLoopStart", "CbfThruSFLoopCategory", "CbfThruSFLoopColumn", "CbfThruSFLoopAssignment", "CbfThruFunction", "Loop", "DataBlockName", "SaveFrameName", "CategoryName", "ColumnName", "ItemName", "FunctionName", "Value", 0 }; #endif # ifdef YYPRINT /* YYTOKNUM[YYLEX-NUM] -- Internal token number corresponding to token YYLEX-NUM. */ static const yytype_uint16 yytoknum[] = { 0, 256, 257, 258, 259, 260, 261, 262, 263, 264, 265, 266, 267, 268, 269, 270, 271 }; # endif /* YYR1[YYN] -- Symbol number of symbol that rule YYN derives. */ static const yytype_uint8 yyr1[] = { 0, 17, 18, 18, 19, 20, 20, 21, 22, 22, 22, 22, 22, 22, 23, 23, 23, 23, 23, 23, 24, 25, 25, 25, 25, 26, 26, 26, 26, 27, 28, 28, 28, 29, 29, 29, 30, 30, 31, 31, 31, 32, 32, 33, 33, 33, 34, 34, 34, 35, 36, 36, 36, 37, 37, 38, 38, 39, 39, 39, 40, 40, 41, 42, 43, 44, 45, 46, 47, 48, 49, 49, 49 }; /* YYR2[YYN] -- Number of symbols composing right hand side of rule YYN. */ static const yytype_uint8 yyr2[] = { 0, 2, 1, 1, 0, 2, 2, 1, 1, 1, 1, 1, 1, 1, 2, 2, 2, 1, 1, 1, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 3, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1 }; /* YYDEFACT[STATE-NAME] -- Default rule to reduce with in state STATE-NUM when YYTABLE doesn't specify something else to do. Zero means the default is an error. */ static const yytype_uint8 yydefact[] = { 4, 0, 7, 8, 0, 3, 0, 11, 0, 0, 9, 13, 0, 0, 0, 10, 0, 0, 17, 19, 0, 0, 0, 18, 12, 1, 64, 5, 65, 63, 68, 66, 34, 16, 22, 28, 69, 33, 14, 21, 27, 0, 20, 53, 6, 15, 43, 47, 67, 23, 25, 70, 71, 72, 24, 26, 29, 30, 31, 35, 36, 38, 32, 40, 37, 39, 41, 42, 44, 46, 45, 48, 49, 50, 51, 54, 55, 57, 52, 59, 56, 58, 60, 61, 62 }; /* YYDEFGOTO[NTERM-NUM]. */ static const yytype_int8 yydefgoto[] = { -1, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 32, 27, 33, 34, 50, 35, 41, 56 }; /* YYPACT[STATE-NUM] -- Index in YYTABLE of the portion describing STATE-NUM. */ #define YYPACT_NINF -11 static const yytype_int8 yypact[] = { -11, 3, 11, -11, 70, 59, 46, -11, 29, 61, 69, 69, 49, 13, 61, 69, 29, 61, 69, 69, 49, 13, 61, 69, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, 69, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11 }; /* YYPGOTO[NTERM-NUM]. */ static const yytype_int8 yypgoto[] = { -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, -11, 23, 15, 41, 10, 4, 28, -11, -10 }; /* YYTABLE[YYPACT[STATE-NUM]]. What to do in state STATE-NUM. If positive, shift that token. If negative, reduce the rule which number is the opposite. If zero, do what YYDEFACT says. If YYTABLE_NINF, syntax error. */ #define YYTABLE_NINF -3 static const yytype_int8 yytable[] = { 57, 58, 62, 25, 66, 67, 26, 72, 73, 74, 78, -2, 82, 83, -2, 39, 46, 63, 49, 54, 69, 44, 60, 48, 64, 79, 68, 70, 37, 43, 76, 84, 80, 40, 47, 59, 0, 55, 31, 48, 61, 0, 65, 75, 0, 71, 38, 45, 77, 26, 81, 28, 42, 29, 30, 31, 29, 30, 31, 0, 51, 52, 53, 36, 28, 0, 29, 30, 31, 30, 31, 0, 51, 52, 53, 28, 0, 29, 30, 31, 51, 52, 53 }; static const yytype_int8 yycheck[] = { 10, 11, 12, 0, 14, 15, 3, 17, 18, 19, 20, 0, 22, 23, 3, 5, 6, 13, 8, 9, 16, 6, 12, 10, 14, 21, 16, 17, 5, 6, 20, 41, 22, 5, 6, 12, -1, 9, 9, 10, 12, -1, 14, 20, -1, 17, 5, 6, 20, 3, 22, 5, 6, 7, 8, 9, 7, 8, 9, -1, 11, 12, 13, 4, 5, -1, 7, 8, 9, 8, 9, -1, 11, 12, 13, 5, -1, 7, 8, 9, 11, 12, 13 }; /* YYSTOS[STATE-NUM] -- The (internal number of the) accessing symbol of state STATE-NUM. */ static const yytype_uint8 yystos[] = { 0, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, 32, 33, 34, 35, 36, 37, 38, 39, 40, 41, 0, 3, 43, 5, 7, 8, 9, 42, 44, 45, 47, 4, 42, 44, 45, 47, 48, 6, 42, 43, 44, 45, 47, 10, 45, 46, 11, 12, 13, 45, 47, 49, 49, 49, 42, 45, 47, 49, 46, 45, 47, 49, 49, 45, 46, 45, 47, 49, 49, 49, 42, 45, 47, 49, 46, 45, 47, 49, 49, 49 }; #define yyerrok (yyerrstatus = 0) #define yyclearin (yychar = YYEMPTY) #define YYEMPTY (-2) #define YYEOF 0 #define YYACCEPT goto yyacceptlab #define YYABORT goto yyabortlab #define YYERROR goto yyerrorlab /* Like YYERROR except do call yyerror. This remains here temporarily to ease the transition to the new meaning of YYERROR, for GCC. Once GCC version 2 has supplanted version 1, this can go. */ #define YYFAIL goto yyerrlab #define YYRECOVERING() (!!yyerrstatus) #define YYBACKUP(Token, Value) \ do \ if (yychar == YYEMPTY && yylen == 1) \ { \ yychar = (Token); \ yylval = (Value); \ yytoken = YYTRANSLATE (yychar); \ YYPOPSTACK (1); \ goto yybackup; \ } \ else \ { \ yyerror (YY_("syntax error: cannot back up")); \ YYERROR; \ } \ while (YYID (0)) #define YYTERROR 1 #define YYERRCODE 256 /* YYLLOC_DEFAULT -- Set CURRENT to span from RHS[1] to RHS[N]. If N is 0, then set CURRENT to the empty location which ends the previous symbol: RHS[0] (always defined). */ #define YYRHSLOC(Rhs, K) ((Rhs)[K]) #ifndef YYLLOC_DEFAULT # define YYLLOC_DEFAULT(Current, Rhs, N) \ do \ if (YYID (N)) \ { \ (Current).first_line = YYRHSLOC (Rhs, 1).first_line; \ (Current).first_column = YYRHSLOC (Rhs, 1).first_column; \ (Current).last_line = YYRHSLOC (Rhs, N).last_line; \ (Current).last_column = YYRHSLOC (Rhs, N).last_column; \ } \ else \ { \ (Current).first_line = (Current).last_line = \ YYRHSLOC (Rhs, 0).last_line; \ (Current).first_column = (Current).last_column = \ YYRHSLOC (Rhs, 0).last_column; \ } \ while (YYID (0)) #endif /* YY_LOCATION_PRINT -- Print the location on the stream. This macro was not mandated originally: define only if we know we won't break user code: when these are the locations we know. */ #ifndef YY_LOCATION_PRINT # if YYLTYPE_IS_TRIVIAL # define YY_LOCATION_PRINT(File, Loc) \ fprintf (File, "%d.%d-%d.%d", \ (Loc).first_line, (Loc).first_column, \ (Loc).last_line, (Loc).last_column) # else # define YY_LOCATION_PRINT(File, Loc) ((void) 0) # endif #endif /* YYLEX -- calling `yylex' with the right arguments. */ #ifdef YYLEX_PARAM # define YYLEX yylex (&yylval, YYLEX_PARAM) #else # define YYLEX yylex (&yylval) #endif /* Enable debugging if requested. */ #if YYDEBUG # ifndef YYFPRINTF # include /* INFRINGES ON USER NAME SPACE */ # define YYFPRINTF fprintf # endif # define YYDPRINTF(Args) \ do { \ if (yydebug) \ YYFPRINTF Args; \ } while (YYID (0)) # define YY_SYMBOL_PRINT(Title, Type, Value, Location) \ do { \ if (yydebug) \ { \ YYFPRINTF (stderr, "%s ", Title); \ yy_symbol_print (stderr, \ Type, Value); \ YYFPRINTF (stderr, "\n"); \ } \ } while (YYID (0)) /*--------------------------------. | Print this symbol on YYOUTPUT. | `--------------------------------*/ /*ARGSUSED*/ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static void yy_symbol_value_print (FILE *yyoutput, int yytype, YYSTYPE const * const yyvaluep) #else static void yy_symbol_value_print (yyoutput, yytype, yyvaluep) FILE *yyoutput; int yytype; YYSTYPE const * const yyvaluep; #endif { if (!yyvaluep) return; # ifdef YYPRINT if (yytype < YYNTOKENS) YYPRINT (yyoutput, yytoknum[yytype], *yyvaluep); # else YYUSE (yyoutput); # endif switch (yytype) { default: break; } } /*--------------------------------. | Print this symbol on YYOUTPUT. | `--------------------------------*/ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static void yy_symbol_print (FILE *yyoutput, int yytype, YYSTYPE const * const yyvaluep) #else static void yy_symbol_print (yyoutput, yytype, yyvaluep) FILE *yyoutput; int yytype; YYSTYPE const * const yyvaluep; #endif { if (yytype < YYNTOKENS) YYFPRINTF (yyoutput, "token %s (", yytname[yytype]); else YYFPRINTF (yyoutput, "nterm %s (", yytname[yytype]); yy_symbol_value_print (yyoutput, yytype, yyvaluep); YYFPRINTF (yyoutput, ")"); } /*------------------------------------------------------------------. | yy_stack_print -- Print the state stack from its BOTTOM up to its | | TOP (included). | `------------------------------------------------------------------*/ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static void yy_stack_print (yytype_int16 *bottom, yytype_int16 *top) #else static void yy_stack_print (bottom, top) yytype_int16 *bottom; yytype_int16 *top; #endif { YYFPRINTF (stderr, "Stack now"); for (; bottom <= top; ++bottom) YYFPRINTF (stderr, " %d", *bottom); YYFPRINTF (stderr, "\n"); } # define YY_STACK_PRINT(Bottom, Top) \ do { \ if (yydebug) \ yy_stack_print ((Bottom), (Top)); \ } while (YYID (0)) /*------------------------------------------------. | Report that the YYRULE is going to be reduced. | `------------------------------------------------*/ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static void yy_reduce_print (YYSTYPE *yyvsp, int yyrule) #else static void yy_reduce_print (yyvsp, yyrule) YYSTYPE *yyvsp; int yyrule; #endif { int yynrhs = yyr2[yyrule]; int yyi; unsigned long int yylno = yyrline[yyrule]; YYFPRINTF (stderr, "Reducing stack by rule %d (line %lu):\n", yyrule - 1, yylno); /* The symbols being reduced. */ for (yyi = 0; yyi < yynrhs; yyi++) { fprintf (stderr, " $%d = ", yyi + 1); yy_symbol_print (stderr, yyrhs[yyprhs[yyrule] + yyi], &(yyvsp[(yyi + 1) - (yynrhs)]) ); fprintf (stderr, "\n"); } } # define YY_REDUCE_PRINT(Rule) \ do { \ if (yydebug) \ yy_reduce_print (yyvsp, Rule); \ } while (YYID (0)) /* Nonzero means print parse trace. It is left uninitialized so that multiple parsers can coexist. */ int yydebug; #else /* !YYDEBUG */ # define YYDPRINTF(Args) # define YY_SYMBOL_PRINT(Title, Type, Value, Location) # define YY_STACK_PRINT(Bottom, Top) # define YY_REDUCE_PRINT(Rule) #endif /* !YYDEBUG */ /* YYINITDEPTH -- initial size of the parser's stacks. */ #ifndef YYINITDEPTH # define YYINITDEPTH 200 #endif /* YYMAXDEPTH -- maximum size the stacks can grow to (effective only if the built-in stack extension method is used). Do not make this value too large; the results are undefined if YYSTACK_ALLOC_MAXIMUM < YYSTACK_BYTES (YYMAXDEPTH) evaluated with infinite-precision integer arithmetic. */ #ifndef YYMAXDEPTH # define YYMAXDEPTH 10000 #endif #if YYERROR_VERBOSE # ifndef yystrlen # if defined __GLIBC__ && defined _STRING_H # define yystrlen strlen # else /* Return the length of YYSTR. */ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static YYSIZE_T yystrlen (const char *yystr) #else static YYSIZE_T yystrlen (yystr) const char *yystr; #endif { YYSIZE_T yylen; for (yylen = 0; yystr[yylen]; yylen++) continue; return yylen; } # endif # endif # ifndef yystpcpy # if defined __GLIBC__ && defined _STRING_H && defined _GNU_SOURCE # define yystpcpy stpcpy # else /* Copy YYSRC to YYDEST, returning the address of the terminating '\0' in YYDEST. */ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static char * yystpcpy (char *yydest, const char *yysrc) #else static char * yystpcpy (yydest, yysrc) char *yydest; const char *yysrc; #endif { char *yyd = yydest; const char *yys = yysrc; while ((*yyd++ = *yys++) != '\0') continue; return yyd - 1; } # endif # endif # ifndef yytnamerr /* Copy to YYRES the contents of YYSTR after stripping away unnecessary quotes and backslashes, so that it's suitable for yyerror. The heuristic is that double-quoting is unnecessary unless the string contains an apostrophe, a comma, or backslash (other than backslash-backslash). YYSTR is taken from yytname. If YYRES is null, do not copy; instead, return the length of what the result would have been. */ static YYSIZE_T yytnamerr (char *yyres, const char *yystr) { if (*yystr == '"') { YYSIZE_T yyn = 0; char const *yyp = yystr; for (;;) switch (*++yyp) { case '\'': case ',': goto do_not_strip_quotes; case '\\': if (*++yyp != '\\') goto do_not_strip_quotes; /* Fall through. */ default: if (yyres) yyres[yyn] = *yyp; yyn++; break; case '"': if (yyres) yyres[yyn] = '\0'; return yyn; } do_not_strip_quotes: ; } if (! yyres) return yystrlen (yystr); return yystpcpy (yyres, yystr) - yyres; } # endif /* Copy into YYRESULT an error message about the unexpected token YYCHAR while in state YYSTATE. Return the number of bytes copied, including the terminating null byte. If YYRESULT is null, do not copy anything; just return the number of bytes that would be copied. As a special case, return 0 if an ordinary "syntax error" message will do. Return YYSIZE_MAXIMUM if overflow occurs during size calculation. */ static YYSIZE_T yysyntax_error (char *yyresult, int yystate, int yychar) { int yyn = yypact[yystate]; if (! (YYPACT_NINF < yyn && yyn <= YYLAST)) return 0; else { int yytype = YYTRANSLATE (yychar); YYSIZE_T yysize0 = yytnamerr (0, yytname[yytype]); YYSIZE_T yysize = yysize0; YYSIZE_T yysize1; int yysize_overflow = 0; enum { YYERROR_VERBOSE_ARGS_MAXIMUM = 5 }; char const *yyarg[YYERROR_VERBOSE_ARGS_MAXIMUM]; int yyx; # if 0 /* This is so xgettext sees the translatable formats that are constructed on the fly. */ YY_("syntax error, unexpected %s"); YY_("syntax error, unexpected %s, expecting %s"); YY_("syntax error, unexpected %s, expecting %s or %s"); YY_("syntax error, unexpected %s, expecting %s or %s or %s"); YY_("syntax error, unexpected %s, expecting %s or %s or %s or %s"); # endif char *yyfmt; char const *yyf; static char const yyunexpected[] = "syntax error, unexpected %s"; static char const yyexpecting[] = ", expecting %s"; static char const yyor[] = " or %s"; char yyformat[sizeof yyunexpected + sizeof yyexpecting - 1 + ((YYERROR_VERBOSE_ARGS_MAXIMUM - 2) * (sizeof yyor - 1))]; char const *yyprefix = yyexpecting; /* Start YYX at -YYN if negative to avoid negative indexes in YYCHECK. */ int yyxbegin = yyn < 0 ? -yyn : 0; /* Stay within bounds of both yycheck and yytname. */ int yychecklim = YYLAST - yyn + 1; int yyxend = yychecklim < YYNTOKENS ? yychecklim : YYNTOKENS; int yycount = 1; yyarg[0] = yytname[yytype]; yyfmt = yystpcpy (yyformat, yyunexpected); for (yyx = yyxbegin; yyx < yyxend; ++yyx) if (yycheck[yyx + yyn] == yyx && yyx != YYTERROR) { if (yycount == YYERROR_VERBOSE_ARGS_MAXIMUM) { yycount = 1; yysize = yysize0; yyformat[sizeof yyunexpected - 1] = '\0'; break; } yyarg[yycount++] = yytname[yyx]; yysize1 = yysize + yytnamerr (0, yytname[yyx]); yysize_overflow |= (yysize1 < yysize); yysize = yysize1; yyfmt = yystpcpy (yyfmt, yyprefix); yyprefix = yyor; } yyf = YY_(yyformat); yysize1 = yysize + yystrlen (yyf); yysize_overflow |= (yysize1 < yysize); yysize = yysize1; if (yysize_overflow) return YYSIZE_MAXIMUM; if (yyresult) { /* Avoid sprintf, as that infringes on the user's name space. Don't have undefined behavior even if the translation produced a string with the wrong number of "%s"s. */ char *yyp = yyresult; int yyi = 0; while ((*yyp = *yyf) != '\0') { if (*yyp == '%' && yyf[1] == 's' && yyi < yycount) { yyp += yytnamerr (yyp, yyarg[yyi++]); yyf += 2; } else { yyp++; yyf++; } } } return yysize; } } #endif /* YYERROR_VERBOSE */ /*-----------------------------------------------. | Release the memory associated to this symbol. | `-----------------------------------------------*/ /*ARGSUSED*/ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static void yydestruct (const char *yymsg, int yytype, YYSTYPE *yyvaluep) #else static void yydestruct (yymsg, yytype, yyvaluep) const char *yymsg; int yytype; YYSTYPE *yyvaluep; #endif { YYUSE (yyvaluep); if (!yymsg) yymsg = "Deleting"; YY_SYMBOL_PRINT (yymsg, yytype, yyvaluep, yylocationp); switch (yytype) { default: break; } } /* Prevent warnings from -Wmissing-prototypes. */ #ifdef YYPARSE_PARAM #if defined __STDC__ || defined __cplusplus int yyparse (void *YYPARSE_PARAM); #else int yyparse (); #endif #else /* ! YYPARSE_PARAM */ #if defined __STDC__ || defined __cplusplus int yyparse (void); #else int yyparse (); #endif #endif /* ! YYPARSE_PARAM */ /*----------. | yyparse. | `----------*/ #ifdef YYPARSE_PARAM #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) int yyparse (void *YYPARSE_PARAM) #else int yyparse (YYPARSE_PARAM) void *YYPARSE_PARAM; #endif #else /* ! YYPARSE_PARAM */ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) int yyparse (void) #else int yyparse () #endif #endif { /* The look-ahead symbol. */ int yychar; /* The semantic value of the look-ahead symbol. */ YYSTYPE yylval; /* Number of syntax errors so far. */ int yynerrs; int yystate; int yyn; int yyresult; /* Number of tokens to shift before error messages enabled. */ int yyerrstatus; /* Look-ahead token as an internal (translated) token number. */ int yytoken = 0; #if YYERROR_VERBOSE /* Buffer for error messages, and its allocated size. */ char yymsgbuf[128]; char *yymsg = yymsgbuf; YYSIZE_T yymsg_alloc = sizeof yymsgbuf; #endif /* Three stacks and their tools: `yyss': related to states, `yyvs': related to semantic values, `yyls': related to locations. Refer to the stacks thru separate pointers, to allow yyoverflow to reallocate them elsewhere. */ /* The state stack. */ yytype_int16 yyssa[YYINITDEPTH]; yytype_int16 *yyss = yyssa; yytype_int16 *yyssp; /* The semantic value stack. */ YYSTYPE yyvsa[YYINITDEPTH]; YYSTYPE *yyvs = yyvsa; YYSTYPE *yyvsp; #define YYPOPSTACK(N) (yyvsp -= (N), yyssp -= (N)) YYSIZE_T yystacksize = YYINITDEPTH; /* The variables used to return semantic value and location from the action routines. */ YYSTYPE yyval; /* The number of symbols on the RHS of the reduced rule. Keep to zero when no symbol should be popped. */ int yylen = 0; YYDPRINTF ((stderr, "Starting parse\n")); yystate = 0; yyerrstatus = 0; yynerrs = 0; yychar = YYEMPTY; /* Cause a token to be read. */ /* Initialize stack pointers. Waste one element of value and location stack so that they stay on the same level as the state stack. The wasted elements are never initialized. */ yyssp = yyss; yyvsp = yyvs; goto yysetstate; /*------------------------------------------------------------. | yynewstate -- Push a new state, which is found in yystate. | `------------------------------------------------------------*/ yynewstate: /* In all cases, when you get here, the value and location stacks have just been pushed. So pushing a state here evens the stacks. */ yyssp++; yysetstate: *yyssp = yystate; if (yyss + yystacksize - 1 <= yyssp) { /* Get the current used size of the three stacks, in elements. */ YYSIZE_T yysize = yyssp - yyss + 1; #ifdef yyoverflow { /* Give user a chance to reallocate the stack. Use copies of these so that the &'s don't force the real ones into memory. */ YYSTYPE *yyvs1 = yyvs; yytype_int16 *yyss1 = yyss; /* Each stack pointer address is followed by the size of the data in use in that stack, in bytes. This used to be a conditional around just the two extra args, but that might be undefined if yyoverflow is a macro. */ yyoverflow (YY_("memory exhausted"), &yyss1, yysize * sizeof (*yyssp), &yyvs1, yysize * sizeof (*yyvsp), &yystacksize); yyss = yyss1; yyvs = yyvs1; } #else /* no yyoverflow */ # ifndef YYSTACK_RELOCATE goto yyexhaustedlab; # else /* Extend the stack our own way. */ if (YYMAXDEPTH <= yystacksize) goto yyexhaustedlab; yystacksize *= 2; if (YYMAXDEPTH < yystacksize) yystacksize = YYMAXDEPTH; { yytype_int16 *yyss1 = yyss; union yyalloc *yyptr = (union yyalloc *) YYSTACK_ALLOC (YYSTACK_BYTES (yystacksize)); if (! yyptr) goto yyexhaustedlab; YYSTACK_RELOCATE (yyss); YYSTACK_RELOCATE (yyvs); # undef YYSTACK_RELOCATE if (yyss1 != yyssa) YYSTACK_FREE (yyss1); } # endif #endif /* no yyoverflow */ yyssp = yyss + yysize - 1; yyvsp = yyvs + yysize - 1; YYDPRINTF ((stderr, "Stack size increased to %lu\n", (unsigned long int) yystacksize)); if (yyss + yystacksize - 1 <= yyssp) YYABORT; } YYDPRINTF ((stderr, "Entering state %d\n", yystate)); goto yybackup; /*-----------. | yybackup. | `-----------*/ yybackup: /* Do appropriate processing given the current state. Read a look-ahead token if we need one and don't already have one. */ /* First try to decide what to do without reference to look-ahead token. */ yyn = yypact[yystate]; if (yyn == YYPACT_NINF) goto yydefault; /* Not known => get a look-ahead token if don't already have one. */ /* YYCHAR is either YYEMPTY or YYEOF or a valid look-ahead symbol. */ if (yychar == YYEMPTY) { YYDPRINTF ((stderr, "Reading a token: ")); yychar = YYLEX; } if (yychar <= YYEOF) { yychar = yytoken = YYEOF; YYDPRINTF ((stderr, "Now at end of input.\n")); } else { yytoken = YYTRANSLATE (yychar); YY_SYMBOL_PRINT ("Next token is", yytoken, &yylval, &yylloc); } /* If the proper action on seeing token YYTOKEN is to reduce or to detect an error, take that action. */ yyn += yytoken; if (yyn < 0 || YYLAST < yyn || yycheck[yyn] != yytoken) goto yydefault; yyn = yytable[yyn]; if (yyn <= 0) { if (yyn == 0 || yyn == YYTABLE_NINF) goto yyerrlab; yyn = -yyn; goto yyreduce; } if (yyn == YYFINAL) YYACCEPT; /* Count tokens shifted since error; after three, turn off error status. */ if (yyerrstatus) yyerrstatus--; /* Shift the look-ahead token. */ YY_SYMBOL_PRINT ("Shifting", yytoken, &yylval, &yylloc); /* Discard the shifted token unless it is eof. */ if (yychar != YYEOF) yychar = YYEMPTY; yystate = yyn; *++yyvsp = yylval; goto yynewstate; /*-----------------------------------------------------------. | yydefault -- do the default action for the current state. | `-----------------------------------------------------------*/ yydefault: yyn = yydefact[yystate]; if (yyn == 0) goto yyerrlab; goto yyreduce; /*-----------------------------. | yyreduce -- Do a reduction. | `-----------------------------*/ yyreduce: /* yyn is the number of a rule to reduce with. */ yylen = yyr2[yyn]; /* If YYLEN is nonzero, implement the default value of the action: `$$ = $1'. Otherwise, the following line sets YYVAL to garbage. This behavior is undocumented and Bison users should not rely upon it. Assigning to YYVAL unconditionally makes the parser a bit smaller, and it avoids a GCC warning that YYVAL may be used uninitialized. */ yyval = yyvsp[1-yylen]; YY_REDUCE_PRINT (yyn); switch (yyn) { case 2: { (yyval.node) = (yyvsp[(1) - (1)].node); ((void **)context)[3] = NULL; ;} break; case 3: { (yyval.node) = (yyvsp[(1) - (1)].node); cbf_failnez (cbf_undo_links (&((yyval.node)))) cbf_failnez (cbf_find_parent (&((yyval.node)), (yyval.node), CBF_ROOT)) ;} break; case 4: { (yyval.node) = ((void **) context) [1]; ;} break; case 5: { cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyvsp[(1) - (2)].node), CBF_DATABLOCK, (cbf_node *) NULL)) if (strlen((yyvsp[(2) - (2)].text))==0) { cbf_log((cbf_handle)(((void **)context)[2]),"empty data block name", CBF_LOGWARNING|CBF_LOGSTARTLOC); } if (!cbf_find_last_child(&((yyval.node)),(yyvsp[(1) - (2)].node),(yyvsp[(2) - (2)].text)) ){ cbf_log((cbf_handle)(((void **)context)[2]),"duplicate data block name", CBF_LOGWARNING|CBF_LOGSTARTLOC); } cbf_failnez (cbf_make_child (&((yyval.node)), (yyvsp[(1) - (2)].node), CBF_DATABLOCK, (yyvsp[(2) - (2)].text))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) ;} break; case 6: { cbf_log((cbf_handle)(((void **)context)[2]),"prior save frame not terminated", CBF_LOGWARNING|CBF_LOGSTARTLOC); cbf_failnez (cbf_find_parent (&((yyval.node)), (yyvsp[(1) - (2)].node), CBF_ROOT)) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyvsp[(1) - (2)].node), CBF_DATABLOCK, (cbf_node *) NULL)) if (strlen((yyvsp[(2) - (2)].text))==0) { cbf_log((cbf_handle)(((void **)context)[2]),"empty data block name", CBF_LOGWARNING|CBF_LOGSTARTLOC); } if (!cbf_find_last_child(&((yyval.node)),(yyval.node),(yyvsp[(2) - (2)].text)) ){ cbf_log((cbf_handle)(((void **)context)[2]),"duplicate data block name", CBF_LOGWARNING|CBF_LOGSTARTLOC); } cbf_failnez (cbf_make_child (&((yyval.node)), (yyvsp[(1) - (2)].node), CBF_DATABLOCK, (yyvsp[(2) - (2)].text))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) ;} break; case 7: { cbf_failnez (cbf_make_child (&((yyval.node)), (yyvsp[(1) - (1)].node), CBF_DATABLOCK, NULL)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_log((cbf_handle)(((void **)context)[2]),"no data block", CBF_LOGWARNING|CBF_LOGSTARTLOC); ;} break; case 8: { (yyval.node) = (yyvsp[(1) - (1)].node); ((void **)context)[3] = NULL; ;} break; case 9: { cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyvsp[(1) - (1)].node), CBF_CATEGORY, NULL)) (yyval.node) = (yyvsp[(1) - (1)].node); cbf_failnez (cbf_undo_links (&((yyval.node)))) cbf_failnez (cbf_find_parent (&((yyval.node)), (yyval.node), CBF_DATABLOCK)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); ((void **)context)[3] = NULL; ;} break; case 10: { cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyvsp[(1) - (1)].node), CBF_CATEGORY, NULL)) (yyval.node) = (yyvsp[(1) - (1)].node); cbf_failnez (cbf_undo_links (&((yyval.node)))) cbf_failnez (cbf_find_parent (&((yyval.node)), (yyval.node), CBF_DATABLOCK)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); ((void **)context)[3] = NULL; ;} break; case 11: { cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyvsp[(1) - (1)].node), CBF_CATEGORY, NULL)) (yyval.node) = (yyvsp[(1) - (1)].node); cbf_failnez (cbf_undo_links (&((yyval.node)))) cbf_failnez (cbf_find_parent (&((yyval.node)), (yyval.node), CBF_DATABLOCK)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); ((void **)context)[3] = NULL; ;} break; case 12: { cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyvsp[(1) - (1)].node), CBF_FUNCTION, NULL)) (yyval.node) = (yyvsp[(1) - (1)].node); cbf_failnez (cbf_undo_links (&((yyval.node)))) cbf_failnez (cbf_find_parent (&((yyval.node)), (yyval.node), CBF_DATABLOCK)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); ((void **)context)[3] = NULL; ;} break; case 13: { cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyvsp[(1) - (1)].node), CBF_CATEGORY, NULL)) (yyval.node) = (yyvsp[(1) - (1)].node); cbf_failnez (cbf_undo_links (&((yyval.node)))) cbf_failnez (cbf_find_parent (&((yyval.node)), (yyval.node), CBF_DATABLOCK)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); ((void **)context)[3] = NULL; ;} break; case 14: { cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyvsp[(1) - (2)].node), CBF_CATEGORY, NULL)) cbf_failnez (cbf_make_child (&((yyval.node)), (cbf_node *) (yyvsp[(1) - (2)].node), CBF_SAVEFRAME, (yyvsp[(2) - (2)].text))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) ((void **)context)[3] = NULL; ;} break; case 15: { cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyvsp[(1) - (2)].node), CBF_CATEGORY, NULL)) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyvsp[(1) - (2)].node), CBF_SAVEFRAME, NULL)) cbf_log((cbf_handle)(((void **)context)[2]),"save frame not terminated", CBF_LOGWARNING|CBF_LOGSTARTLOC); (yyval.node) = (yyvsp[(1) - (2)].node); cbf_failnez (cbf_undo_links (&((yyval.node)))) cbf_failnez (cbf_find_parent (&((yyval.node)), (yyval.node), CBF_DATABLOCK)) cbf_failnez (cbf_make_child (&((yyval.node)), (yyval.node), CBF_SAVEFRAME, (yyvsp[(2) - (2)].text))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) ((void **)context)[3] = NULL; ;} break; case 16: { cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyvsp[(1) - (2)].node), CBF_CATEGORY, NULL)) cbf_failnez (cbf_make_child (&((yyval.node)), (yyvsp[(1) - (2)].node), CBF_SAVEFRAME, (yyvsp[(2) - (2)].text))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) ((void **)context)[3] = NULL; ;} break; case 17: { cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyvsp[(1) - (1)].node), CBF_CATEGORY, NULL)) (yyval.node) = (yyvsp[(1) - (1)].node); cbf_failnez (cbf_undo_links (&((yyval.node)))) cbf_failnez (cbf_find_parent (&((yyval.node)), (yyval.node), CBF_SAVEFRAME)) ;} break; case 18: { cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyvsp[(1) - (1)].node), CBF_CATEGORY, NULL)) (yyval.node) = (yyvsp[(1) - (1)].node); cbf_failnez (cbf_undo_links (&((yyval.node)))) cbf_failnez (cbf_find_parent (&((yyval.node)), (yyval.node), CBF_SAVEFRAME)) ;} break; case 19: { cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyvsp[(1) - (1)].node), CBF_CATEGORY, NULL)) (yyval.node) = (yyvsp[(1) - (1)].node); cbf_failnez (cbf_undo_links (&((yyval.node)))) cbf_failnez (cbf_find_parent (&((yyval.node)), (yyval.node), CBF_SAVEFRAME)) ;} break; case 20: { cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyvsp[(1) - (2)].node), CBF_CATEGORY, NULL)) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyvsp[(1) - (2)].node), CBF_SAVEFRAME, NULL)) (yyval.node) = (yyvsp[(1) - (2)].node); cbf_failnez (cbf_undo_links (&((yyval.node)))) cbf_failnez (cbf_find_parent (&((yyval.node)), (yyval.node), CBF_SAVEFRAME)) ;} break; case 21: { cbf_failnez (cbf_make_child (&((yyval.node)), (yyvsp[(1) - (2)].node), CBF_CATEGORY, (yyvsp[(2) - (2)].text))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) ((void **)context)[3] = (void *)(yyval.node); ;} break; case 22: { cbf_failnez (cbf_make_child (&((yyval.node)), (yyvsp[(1) - (2)].node), CBF_CATEGORY, (yyvsp[(2) - (2)].text))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) ((void **)context)[3] = (void *)(yyval.node); ;} break; case 23: { cbf_log ((cbf_handle)(((void **)context)[2]),"data name with no value1", CBF_LOGERROR|CBF_LOGSTARTLOC); (yyval.node) = (yyvsp[(1) - (2)].node); cbf_failnez (cbf_undo_links (&((yyval.node)))) cbf_failnez (cbf_find_parent (&((yyval.node)), (yyval.node), CBF_DATABLOCK)) cbf_failnez (cbf_make_child (&((yyval.node)), (yyval.node), CBF_CATEGORY, (yyvsp[(2) - (2)].text))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) ((void **)context)[3] = (void *)(yyval.node); ;} break; case 24: { cbf_log ((cbf_handle)(((void **)context)[2]),"data name with no value", CBF_LOGERROR|CBF_LOGSTARTLOC); (yyval.node) = (yyvsp[(1) - (2)].node); cbf_failnez (cbf_undo_links (&((yyval.node)))) cbf_failnez (cbf_find_parent (&((yyval.node)), (yyval.node), CBF_DATABLOCK)) cbf_failnez (cbf_make_child (&((yyval.node)), (yyval.node), CBF_CATEGORY, (yyvsp[(2) - (2)].text))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) ((void **)context)[3] = (void *)(yyval.node); ;} break; case 25: { cbf_failnez (cbf_make_child (&((yyval.node)), (yyvsp[(1) - (2)].node), CBF_COLUMN, (yyvsp[(2) - (2)].text))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyval.node), CBF_COLUMN, (cbf_node *)(((void **)context)[3]))) ;} break; case 26: { cbf_log ((cbf_handle)(((void **)context)[2]),"data name with no value",CBF_LOGERROR|CBF_LOGSTARTLOC); (yyval.node) = (yyvsp[(1) - (2)].node); cbf_failnez (cbf_undo_links (&((yyval.node)))) cbf_failnez (cbf_find_parent (&((yyval.node)), (yyval.node), CBF_DATABLOCK)) cbf_failnez (cbf_make_new_child (&((yyval.node)), (yyval.node), CBF_CATEGORY, (yyvsp[(2) - (2)].text))) ((void **)context)[3] = (void *)(yyval.node); cbf_failnez (cbf_make_child (&((yyval.node)), (yyval.node), CBF_COLUMN, cbf_copy_string(NULL,(yyvsp[(2) - (2)].text),0))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyval.node), CBF_COLUMN, (cbf_node *)(((void **)context)[3]))) ;} break; case 27: { cbf_failnez (cbf_make_new_child (&((yyval.node)), (yyvsp[(1) - (2)].node), CBF_CATEGORY, (yyvsp[(2) - (2)].text))) ((void **)context)[3] = (void *)(yyval.node); cbf_failnez (cbf_make_child (&((yyval.node)), (yyval.node), CBF_COLUMN, cbf_copy_string(NULL,(yyvsp[(2) - (2)].text),0))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyval.node), CBF_COLUMN, (cbf_node *)(((void **)context)[3]))) ;} break; case 28: { cbf_failnez (cbf_make_new_child (&((yyval.node)), (yyvsp[(1) - (2)].node), CBF_CATEGORY, (yyvsp[(2) - (2)].text))) ((void **)context)[3] = (void *)(yyval.node); cbf_failnez (cbf_make_child (&((yyval.node)), (yyval.node), CBF_COLUMN, cbf_copy_string(NULL,(yyvsp[(2) - (2)].text),0))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyval.node), CBF_COLUMN, (cbf_node *)(((void **)context)[3]))) ;} break; case 29: { (yyval.node) = (yyvsp[(1) - (2)].node); cbf_failnez (cbf_set_columnrow ((yyval.node), 0, (yyvsp[(2) - (2)].text), 1)) cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyvsp[(2) - (2)].text), CBF_VALUE, (cbf_node *) (yyval.node))) ;} break; case 30: { (yyval.node) = (yyvsp[(1) - (2)].node); cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_log ((cbf_handle)(((void **)context)[2]),"value without tag",CBF_LOGERROR|CBF_LOGSTARTLOC); cbf_failnez(cbf_free_text(&((yyvsp[(2) - (2)].text)),NULL)) ;} break; case 31: { (yyval.node) = (yyvsp[(1) - (2)].node); cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_log ((cbf_handle)(((void **)context)[2]),"value without tag",CBF_LOGERROR|CBF_LOGSTARTLOC); cbf_failnez(cbf_free_text(&((yyvsp[(2) - (2)].text)),NULL)) ;} break; case 32: { (yyval.node) = (yyvsp[(1) - (2)].node); cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_log ((cbf_handle)(((void **)context)[2]),"loop value without tag",CBF_LOGERROR|CBF_LOGSTARTLOC); cbf_failnez(cbf_free_text(&((yyvsp[(2) - (2)].text)),NULL)) ;} break; case 33: { cbf_failnez (cbf_make_node (&((yyval.node)), CBF_LINK, NULL, NULL)) cbf_failnez (cbf_set_link ((yyval.node), (yyvsp[(1) - (2)].node))) ;} break; case 34: { cbf_failnez (cbf_make_node (&((yyval.node)), CBF_LINK, NULL, NULL)) cbf_failnez (cbf_set_link ((yyval.node), (yyvsp[(1) - (2)].node))) ;} break; case 35: { cbf_log ((cbf_handle)(((void **)context)[2]),"redundant \"loop_\" ",CBF_LOGERROR|CBF_LOGSTARTLOC); cbf_failnez (cbf_make_node (&((yyval.node)), CBF_LINK, NULL, NULL)) cbf_failnez (cbf_set_link ((yyval.node), (yyvsp[(1) - (2)].node))) ;} break; case 36: { cbf_failnez (cbf_make_child (&((yyval.node)), (yyvsp[(1) - (2)].node), CBF_CATEGORY, (yyvsp[(2) - (2)].text))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); ((void **)context)[3] = (void *)(yyval.node); cbf_failnez (cbf_set_link ((yyvsp[(1) - (2)].node), (yyval.node))) ((void **)context)[3] = (void *)(yyval.node); cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) (yyval.node) = (yyvsp[(1) - (2)].node); ;} break; case 37: { cbf_failnez (cbf_find_parent (&((yyval.node)), (yyvsp[(1) - (2)].node), CBF_DATABLOCK)) cbf_failnez (cbf_make_child (&((yyval.node)), (yyval.node), CBF_CATEGORY, (yyvsp[(2) - (2)].text))) cbf_failnez (cbf_set_link ((yyvsp[(1) - (2)].node), (yyval.node))) ((void **)context)[3] = (void *)(yyval.node); cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) (yyval.node) = (yyvsp[(1) - (2)].node); ;} break; case 38: { cbf_failnez (cbf_make_new_child (&((yyval.node)), (yyvsp[(1) - (2)].node), CBF_CATEGORY, (yyvsp[(2) - (2)].text))) ((void **)context)[3] = (void *)(yyval.node); cbf_failnez (cbf_make_child (&((yyval.node)), (yyval.node), CBF_COLUMN, cbf_copy_string(NULL,(yyvsp[(2) - (2)].text),0))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyval.node), CBF_COLUMN, (cbf_node *)(((void **)context)[3]))) cbf_failnez (cbf_set_link ((yyvsp[(1) - (2)].node), (yyval.node))) cbf_failnez (cbf_add_link ((yyvsp[(1) - (2)].node), (yyval.node))) (yyval.node) = (yyvsp[(1) - (2)].node); ;} break; case 39: { (yyval.node) = ((void **)context)[3]; cbf_failnez (cbf_make_child (&((yyval.node)), (yyval.node), CBF_COLUMN, (yyvsp[(2) - (2)].text))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyval.node), CBF_COLUMN, (cbf_node *)(((void **)context)[3]))) cbf_failnez (cbf_set_link ((yyvsp[(1) - (2)].node), (yyval.node))) cbf_failnez (cbf_add_link ((yyvsp[(1) - (2)].node), (yyval.node))) (yyval.node) = (yyvsp[(1) - (2)].node); ;} break; case 40: { cbf_failnez (cbf_make_child (&((yyval.node)), (yyvsp[(1) - (2)].node), CBF_COLUMN, (yyvsp[(2) - (2)].text))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyval.node), CBF_COLUMN, (cbf_node *)(((void **)context)[3]))) cbf_failnez (cbf_set_link ((yyvsp[(1) - (2)].node), (yyval.node))) cbf_failnez (cbf_add_link ((yyvsp[(1) - (2)].node), (yyval.node))) (yyval.node) = (yyvsp[(1) - (2)].node); ;} break; case 41: { (yyval.node) = (yyvsp[(1) - (2)].node); cbf_failnez (cbf_shift_link ((yyval.node))) cbf_failnez (cbf_add_columnrow ((yyval.node), (yyvsp[(2) - (2)].text))) cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyvsp[(2) - (2)].text), CBF_VALUE, (cbf_node *) (yyval.node))) ;} break; case 42: { (yyval.node) = (yyvsp[(1) - (2)].node); cbf_failnez (cbf_shift_link ((yyval.node))) cbf_failnez (cbf_add_columnrow ((yyval.node), (yyvsp[(2) - (2)].text))) cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyvsp[(2) - (2)].text), CBF_VALUE, (cbf_node *) (yyval.node))) ;} break; case 43: { cbf_failnez (cbf_make_child (&((yyval.node)), (yyvsp[(1) - (2)].node), CBF_CATEGORY, (yyvsp[(2) - (2)].text))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); ((void **)context)[3] = (void *)(yyval.node); ;} break; case 44: { cbf_log((cbf_handle)(((void **)context)[2]), "data name with no value", CBF_LOGERROR|CBF_LOGSTARTLOC); (yyval.node) = (yyvsp[(1) - (2)].node); cbf_failnez (cbf_undo_links (&((yyval.node)))) cbf_failnez (cbf_find_parent (&((yyval.node)), (yyval.node), CBF_SAVEFRAME)) cbf_failnez (cbf_make_child (&((yyval.node)), (yyval.node), CBF_CATEGORY, (yyvsp[(2) - (2)].text))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); ((void **)context)[3] = (void *)(yyval.node); ;} break; case 45: { cbf_log((cbf_handle)(((void **)context)[2]), "data name with no value", CBF_LOGERROR|CBF_LOGSTARTLOC); (yyval.node) = (yyvsp[(1) - (2)].node); cbf_failnez (cbf_undo_links (&((yyval.node)))) cbf_failnez (cbf_find_parent (&((yyval.node)), (yyval.node), CBF_SAVEFRAME)) cbf_failnez (cbf_make_child (&((yyval.node)), (yyval.node), CBF_CATEGORY, (yyvsp[(2) - (2)].text))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); ((void **)context)[3] = (void *)(yyval.node); ;} break; case 46: { cbf_failnez (cbf_make_child (&((yyval.node)), (yyvsp[(1) - (2)].node), CBF_COLUMN, (yyvsp[(2) - (2)].text))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyval.node), CBF_COLUMN, (cbf_node *)(((void **)context)[3]))) ;} break; case 47: { cbf_failnez (cbf_make_new_child (&((yyval.node)), (yyvsp[(1) - (2)].node), CBF_CATEGORY, (yyvsp[(2) - (2)].text))) ((void **)context)[3] = (void *)(yyval.node); cbf_failnez (cbf_make_child (&((yyval.node)), (yyval.node), CBF_COLUMN, cbf_copy_string(NULL,(yyvsp[(2) - (2)].text),0))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyval.node), CBF_COLUMN, (cbf_node *)(((void **)context)[3]))) ;} break; case 48: { cbf_log((cbf_handle)(((void **)context)[2]), "data name with no value", CBF_LOGERROR|CBF_LOGSTARTLOC); (yyval.node) = (yyvsp[(1) - (2)].node); cbf_failnez (cbf_undo_links (&((yyval.node)))) cbf_failnez (cbf_find_parent (&((yyval.node)), (yyval.node), CBF_SAVEFRAME)) cbf_failnez (cbf_make_new_child (&((yyval.node)), (yyval.node), CBF_CATEGORY, (yyvsp[(2) - (2)].text))) ((void **)context)[3] = (void *)(yyval.node); cbf_failnez (cbf_make_child (&((yyval.node)), (yyval.node), CBF_COLUMN, cbf_copy_string(NULL,(yyvsp[(2) - (2)].text),0))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyval.node), CBF_COLUMN, (cbf_node *)(((void **)context)[3]))) ;} break; case 49: { (yyval.node) = (yyvsp[(1) - (2)].node); cbf_failnez (cbf_set_columnrow ((yyval.node), 0, (yyvsp[(2) - (2)].text), 1)) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyvsp[(2) - (2)].text), CBF_VALUE, (cbf_node *) (yyval.node))) ;} break; case 50: { (yyval.node) = (yyvsp[(1) - (2)].node); cbf_log ((cbf_handle)(((void **)context)[2]),"value without tag",CBF_LOGERROR|CBF_LOGSTARTLOC); cbf_failnez(cbf_free_text(&((yyvsp[(2) - (2)].text)), NULL)) ;} break; case 51: { (yyval.node) = (yyvsp[(1) - (2)].node); cbf_log ((cbf_handle)(((void **)context)[2]),"value without tag",CBF_LOGERROR|CBF_LOGSTARTLOC); cbf_failnez(cbf_free_text(&((yyvsp[(2) - (2)].text)), NULL)) ;} break; case 52: { (yyval.node) = (yyvsp[(1) - (2)].node); cbf_log ((cbf_handle)(((void **)context)[2]),"loop value without tag",CBF_LOGERROR|CBF_LOGSTARTLOC); cbf_failnez(cbf_free_text(&((yyvsp[(2) - (2)].text)), NULL)) ;} break; case 53: { cbf_failnez (cbf_make_node (&((yyval.node)), CBF_LINK, NULL, NULL)) cbf_failnez (cbf_set_link ((yyval.node), (yyvsp[(1) - (2)].node))) ;} break; case 54: { cbf_log ((cbf_handle)(((void **)context)[2]),"redundant \"loop_\" ",CBF_LOGERROR|CBF_LOGSTARTLOC); cbf_failnez (cbf_make_node (&((yyval.node)), CBF_LINK, NULL, NULL)) cbf_failnez (cbf_set_link ((yyval.node), (yyvsp[(1) - (2)].node))) ;} break; case 55: { cbf_failnez (cbf_make_child (&((yyval.node)), (yyvsp[(1) - (2)].node), CBF_CATEGORY, (yyvsp[(2) - (2)].text))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); cbf_failnez (cbf_set_link ((yyvsp[(1) - (2)].node), (yyval.node))) ((void **)context)[3] = (void *)(yyval.node); (yyval.node) = (yyvsp[(1) - (2)].node); ;} break; case 56: { cbf_failnez (cbf_find_parent (&((yyval.node)), (yyvsp[(1) - (2)].node), CBF_SAVEFRAME)) cbf_failnez (cbf_make_child (&((yyval.node)), (yyval.node), CBF_CATEGORY, (yyvsp[(2) - (2)].text))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); cbf_failnez (cbf_set_link ((yyvsp[(1) - (2)].node), (yyval.node))) ((void **)context)[3] = (void *)(yyval.node); (yyval.node) = (yyvsp[(1) - (2)].node); ;} break; case 57: { cbf_failnez (cbf_make_new_child (&((yyval.node)), (yyvsp[(1) - (2)].node), CBF_CATEGORY, (yyvsp[(2) - (2)].text))) cbf_failnez (cbf_make_child (&((yyval.node)), (yyval.node), CBF_COLUMN, cbf_copy_string(NULL,(yyvsp[(2) - (2)].text),0))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyval.node), CBF_COLUMN, (cbf_node *)(((void **)context)[3]))) cbf_failnez (cbf_set_link ((yyvsp[(1) - (2)].node), (yyval.node))) cbf_failnez (cbf_add_link ((yyvsp[(1) - (2)].node), (yyval.node))) (yyval.node) = (yyvsp[(1) - (2)].node); ;} break; case 58: { (yyval.node) = ((void **)context)[3]; cbf_failnez (cbf_make_child (&((yyval.node)), (yyval.node), CBF_COLUMN, (yyvsp[(2) - (2)].text))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyval.node), CBF_COLUMN, (cbf_node *)(((void **)context)[3]))) cbf_failnez (cbf_set_link ((yyvsp[(1) - (2)].node), (yyval.node))) cbf_failnez (cbf_add_link ((yyvsp[(1) - (2)].node), (yyval.node))) (yyval.node) = (yyvsp[(1) - (2)].node); ;} break; case 59: { cbf_failnez (cbf_make_child (&((yyval.node)), (yyvsp[(1) - (2)].node), CBF_COLUMN, (yyvsp[(2) - (2)].text))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyval.node), CBF_COLUMN, (cbf_node *)(((void **)context)[3]))) cbf_failnez (cbf_set_link ((yyvsp[(1) - (2)].node), (yyval.node))) cbf_failnez (cbf_add_link ((yyvsp[(1) - (2)].node), (yyval.node))) (yyval.node) = (yyvsp[(1) - (2)].node); ;} break; case 60: { (yyval.node) = (yyvsp[(1) - (2)].node); cbf_failnez (cbf_shift_link ((yyval.node))) cbf_failnez (cbf_add_columnrow ((yyval.node), (yyvsp[(2) - (2)].text))) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyvsp[(2) - (2)].text), CBF_VALUE, (cbf_node *) (yyval.node))) ;} break; case 61: { (yyval.node) = (yyvsp[(1) - (2)].node); cbf_failnez (cbf_shift_link ((yyval.node))) cbf_failnez (cbf_add_columnrow ((yyval.node), (yyvsp[(2) - (2)].text))) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyvsp[(2) - (2)].text), CBF_VALUE, (cbf_node *) (yyval.node))) ;} break; case 62: { cbf_failnez (cbf_make_new_child (&((yyval.node)), (yyvsp[(1) - (3)].node), CBF_FUNCTION, (yyvsp[(2) - (3)].text))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)(yyval.node); cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) ((void **)context)[3] = (void *)(yyval.node); cbf_failnez (cbf_make_child (&((yyval.node)), (yyvsp[(1) - (3)].node), CBF_COLUMN, (yyvsp[(2) - (3)].text))) cbf_failnez (cbf_set_columnrow ((yyval.node), 0, (yyvsp[(3) - (3)].text), 1)) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) (yyvsp[(3) - (3)].text), CBF_VALUE, (cbf_node *) (yyval.node))) ;} break; case 64: { (yyval.text) = (yyvsp[(1) - (1)].text); ;} break; case 65: { (yyval.text) = (yyvsp[(1) - (1)].text); ;} break; case 66: { (yyval.text) = (yyvsp[(1) - (1)].text); ;} break; case 67: { (yyval.text) = (yyvsp[(1) - (1)].text); ;} break; case 68: { (yyval.text) = (yyvsp[(1) - (1)].text); ;} break; case 69: { (yyval.text) = (yyvsp[(1) - (1)].text); ;} break; case 70: { (yyval.text) = (yyvsp[(1) - (1)].text); ;} break; case 71: { (yyval.text) = (yyvsp[(1) - (1)].text); ;} break; case 72: { (yyval.text) = (yyvsp[(1) - (1)].text); ;} break; /* Line 1267 of yacc.c. */ default: break; } YY_SYMBOL_PRINT ("-> $$ =", yyr1[yyn], &yyval, &yyloc); YYPOPSTACK (yylen); yylen = 0; YY_STACK_PRINT (yyss, yyssp); *++yyvsp = yyval; /* Now `shift' the result of the reduction. Determine what state that goes to, based on the state we popped back to and the rule number reduced by. */ yyn = yyr1[yyn]; yystate = yypgoto[yyn - YYNTOKENS] + *yyssp; if (0 <= yystate && yystate <= YYLAST && yycheck[yystate] == *yyssp) yystate = yytable[yystate]; else yystate = yydefgoto[yyn - YYNTOKENS]; goto yynewstate; /*------------------------------------. | yyerrlab -- here on detecting error | `------------------------------------*/ yyerrlab: /* If not already recovering from an error, report this error. */ if (!yyerrstatus) { ++yynerrs; #if ! YYERROR_VERBOSE yyerror (YY_("syntax error")); #else { YYSIZE_T yysize = yysyntax_error (0, yystate, yychar); if (yymsg_alloc < yysize && yymsg_alloc < YYSTACK_ALLOC_MAXIMUM) { YYSIZE_T yyalloc = 2 * yysize; if (! (yysize <= yyalloc && yyalloc <= YYSTACK_ALLOC_MAXIMUM)) yyalloc = YYSTACK_ALLOC_MAXIMUM; if (yymsg != yymsgbuf) YYSTACK_FREE (yymsg); yymsg = (char *) YYSTACK_ALLOC (yyalloc); if (yymsg) yymsg_alloc = yyalloc; else { yymsg = yymsgbuf; yymsg_alloc = sizeof yymsgbuf; } } if (0 < yysize && yysize <= yymsg_alloc) { (void) yysyntax_error (yymsg, yystate, yychar); yyerror (yymsg); } else { yyerror (YY_("syntax error")); if (yysize != 0) goto yyexhaustedlab; } } #endif } if (yyerrstatus == 3) { /* If just tried and failed to reuse look-ahead token after an error, discard it. */ if (yychar <= YYEOF) { /* Return failure if at end of input. */ if (yychar == YYEOF) YYABORT; } else { yydestruct ("Error: discarding", yytoken, &yylval); yychar = YYEMPTY; } } /* Else will try to reuse look-ahead token after shifting the error token. */ goto yyerrlab1; /*---------------------------------------------------. | yyerrorlab -- error raised explicitly by YYERROR. | `---------------------------------------------------*/ yyerrorlab: /* Pacify compilers like GCC when the user code never invokes YYERROR and the label yyerrorlab therefore never appears in user code. */ if (/*CONSTCOND*/ 0) goto yyerrorlab; /* Do not reclaim the symbols of the rule which action triggered this YYERROR. */ YYPOPSTACK (yylen); yylen = 0; YY_STACK_PRINT (yyss, yyssp); yystate = *yyssp; goto yyerrlab1; /*-------------------------------------------------------------. | yyerrlab1 -- common code for both syntax error and YYERROR. | `-------------------------------------------------------------*/ yyerrlab1: yyerrstatus = 3; /* Each real token shifted decrements this. */ for (;;) { yyn = yypact[yystate]; if (yyn != YYPACT_NINF) { yyn += YYTERROR; if (0 <= yyn && yyn <= YYLAST && yycheck[yyn] == YYTERROR) { yyn = yytable[yyn]; if (0 < yyn) break; } } /* Pop the current state because it cannot handle the error token. */ if (yyssp == yyss) YYABORT; yydestruct ("Error: popping", yystos[yystate], yyvsp); YYPOPSTACK (1); yystate = *yyssp; YY_STACK_PRINT (yyss, yyssp); } if (yyn == YYFINAL) YYACCEPT; *++yyvsp = yylval; /* Shift the error token. */ YY_SYMBOL_PRINT ("Shifting", yystos[yyn], yyvsp, yylsp); yystate = yyn; goto yynewstate; /*-------------------------------------. | yyacceptlab -- YYACCEPT comes here. | `-------------------------------------*/ yyacceptlab: yyresult = 0; goto yyreturn; /*-----------------------------------. | yyabortlab -- YYABORT comes here. | `-----------------------------------*/ yyabortlab: yyresult = 1; goto yyreturn; #ifndef yyoverflow /*-------------------------------------------------. | yyexhaustedlab -- memory exhaustion comes here. | `-------------------------------------------------*/ yyexhaustedlab: yyerror (YY_("memory exhausted")); yyresult = 2; /* Fall through. */ #endif yyreturn: if (yychar != YYEOF && yychar != YYEMPTY) yydestruct ("Cleanup: discarding lookahead", yytoken, &yylval); /* Do not reclaim the symbols of the rule which action triggered this YYABORT or YYACCEPT. */ YYPOPSTACK (yylen); YY_STACK_PRINT (yyss, yyssp); while (yyssp != yyss) { yydestruct ("Cleanup: popping", yystos[*yyssp], yyvsp); YYPOPSTACK (1); } #ifndef yyoverflow if (yyss != yyssa) YYSTACK_FREE (yyss); #endif #if YYERROR_VERBOSE if (yymsg != yymsgbuf) YYSTACK_FREE (yymsg); #endif /* Make sure YYID is used. */ return YYID (yyresult); } #ifdef __cplusplus } #endif ./CBFlib-0.9.2.2/src/drel_lex.py0000777000076500007650000000000011603745057021021 2../dREL-ply-0.5/drel_lex.pyustar yayayaya./CBFlib-0.9.2.2/src/cbf_write_binary.c0000644000076500007650000007307511603702106016055 0ustar yayayaya/********************************************************************** * cbf_write_binary -- write binary sections * * * * Version 0.8.0 20 July 2008 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifdef __cplusplus extern "C" { #endif #include "cbf.h" #include "cbf_tree.h" #include "cbf_compress.h" #include "cbf_context.h" #include "cbf_binary.h" #include "cbf_codes.h" #include "cbf_string.h" #include #include #include #include #include "cbf_write_binary.h" /* Write a binary value */ int cbf_write_binary (cbf_node *column, unsigned int row, cbf_file *file, int isbuffer) { cbf_file *infile; char digest [25], text [100]; long start; size_t size; unsigned int compression; int id, bits, sign, type, checked_digest, elsize, realarray; const char *byteorder; size_t dimover, dimfast, dimmid, dimslow; size_t padding, ip; /* Check the arguments */ if (!file) return CBF_ARGUMENT; if (((file->write_encoding & ENC_QP) > 0) + ((file->write_encoding & ENC_BASE64) > 0) + ((file->write_encoding & ENC_BASE32K)> 0) + ((file->write_encoding & ENC_BASE8) > 0) + ((file->write_encoding & ENC_BASE10) > 0) + ((file->write_encoding & ENC_BASE16) > 0) + ((file->write_encoding & ENC_NONE) > 0) != 1) return CBF_ARGUMENT; if (!cbf_is_binary (column, row)) return CBF_ARGUMENT; if (cbf_is_mimebinary (column, row)) return CBF_ARGUMENT; /* Parse the value */ cbf_failnez (cbf_get_bintext (column, row, &type, &id, &infile, &start, &size, &checked_digest, digest, &bits, &sign, &realarray, &byteorder, &dimover, &dimfast, &dimmid, &dimslow, &padding, &compression)) if (padding == 0) { if (file->write_headers & PAD_1K ) padding=1023; if (file->write_headers & PAD_2K ) padding=2047; if (file->write_headers & PAD_4K ) padding=4095; } /* Position the file at the start of the binary section */ cbf_failnez (cbf_set_fileposition (infile, start, SEEK_SET)) /* Calculate the digest if necessary */ if (!cbf_is_base64digest (digest) && (file->write_headers & MSG_DIGEST)) { /* Compute the message digest */ cbf_failnez (cbf_md5digest (infile, size, digest)) /* Go back to the start of the binary data */ cbf_failnez (cbf_set_fileposition (infile, start, SEEK_SET)) /* Update the entry */ checked_digest = 1; cbf_failnez (cbf_set_bintext (column, row, type, id, infile, start, size, checked_digest, digest, bits, sign, realarray, byteorder, dimover, dimfast, dimmid, dimslow, padding, compression)) } /* Discard any bits in the buffers */ infile->bits [0] = 0; infile->bits [1] = 0; /* Do we need MIME headers? */ if (compression == CBF_NONE && (file->write_headers & MIME_NOHEADERS)) return CBF_ARGUMENT; /* Write the header */ cbf_failnez (cbf_write_string (file, "\n;\n")) /* MIME header? */ if (file->write_headers & MIME_HEADERS) { cbf_failnez (cbf_write_string (file, "--CIF-BINARY-FORMAT-SECTION--\n")) if (compression == CBF_NONE) cbf_failnez (cbf_write_string (file, "Content-Type: application/octet-stream\n")) else { cbf_failnez (cbf_write_string (file, "Content-Type: application/octet-stream;\n")) switch (compression&CBF_COMPRESSION_MASK) { case CBF_PACKED: cbf_failnez (cbf_write_string (file, " conversions=\"x-CBF_PACKED\"")) if (compression&CBF_UNCORRELATED_SECTIONS) { cbf_failnez (cbf_write_string (file, "; \"uncorrelated_sections\"")) } if (compression&CBF_FLAT_IMAGE) { cbf_failnez (cbf_write_string (file, "; \"flat\"")) } cbf_failnez (cbf_write_string (file, "\n")) break; case CBF_PACKED_V2: cbf_failnez (cbf_write_string (file, " conversions=\"x-CBF_PACKED_V2\"")) if (compression&CBF_UNCORRELATED_SECTIONS) { cbf_failnez (cbf_write_string (file, "; \"uncorrelated_sections\"")) } if (compression&CBF_FLAT_IMAGE) { cbf_failnez (cbf_write_string (file, "; \"flat\"")) } cbf_failnez (cbf_write_string (file, "\n")) break; case CBF_CANONICAL: cbf_failnez (cbf_write_string (file, " conversions=\"x-CBF_CANONICAL\"\n")) break; case CBF_BYTE_OFFSET: cbf_failnez (cbf_write_string (file, " conversions=\"x-CBF_BYTE_OFFSET\"\n")) break; case CBF_PREDICTOR: cbf_failnez (cbf_write_string (file, " conversions=\"x-CBF_PREDICTOR\"\n")) break; default: cbf_failnez (cbf_write_string (file, " conversions=\"x-CBF_UNKNOWN\"\n")) } } if (file->write_encoding & ENC_QP) cbf_failnez (cbf_write_string (file, "Content-Transfer-Encoding: QUOTED-PRINTABLE\n")) else if (file->write_encoding & ENC_BASE64) cbf_failnez (cbf_write_string (file, "Content-Transfer-Encoding: BASE64\n")) else if (file->write_encoding & ENC_BASE32K) cbf_failnez (cbf_write_string (file, "Content-Transfer-Encoding: X-BASE32K\n")) else if (file->write_encoding & ENC_BASE8) cbf_failnez (cbf_write_string (file, "Content-Transfer-Encoding: X-BASE8\n")) else if (file->write_encoding & ENC_BASE10) cbf_failnez (cbf_write_string (file, "Content-Transfer-Encoding: X-BASE10\n")) else if (file->write_encoding & ENC_BASE16) cbf_failnez (cbf_write_string (file, "Content-Transfer-Encoding: X-BASE16\n")) else cbf_failnez (cbf_write_string (file, "Content-Transfer-Encoding: BINARY\n")) sprintf (text, "X-Binary-Size: %lu\n", (long)size); cbf_failnez (cbf_write_string (file, text)) sprintf (text, "X-Binary-ID: %d\n", id); cbf_failnez (cbf_write_string (file, text)) if (realarray) { sprintf (text, "X-Binary-Element-Type: \"signed %d-bit real IEEE\"\n", bits); } else { if (sign) sprintf (text, "X-Binary-Element-Type: \"signed %d-bit integer\"\n", bits); else sprintf (text, "X-Binary-Element-Type: \"unsigned %d-bit integer\"\n", bits); } cbf_failnez (cbf_write_string (file, text)) if ( !cbf_cistrncmp(byteorder,"big_endian",11) ) { sprintf (text, "X-Binary-Element-Byte-Order: %s\n", "BIG_ENDIAN"); cbf_failnez (cbf_write_string (file, text)) } else if ( !cbf_cistrncmp(byteorder,"little_endian",14) ) { sprintf (text, "X-Binary-Element-Byte-Order: %s\n", "LITTLE_ENDIAN"); cbf_failnez (cbf_write_string (file, text)) } else return CBF_FORMAT; /* Save the digest if we have one */ if (cbf_is_base64digest (digest)) { sprintf (text, "Content-MD5: %24s\n", digest); cbf_failnez (cbf_write_string (file, text)) } if (dimover > 0) { sprintf (text, "X-Binary-Number-of-Elements: %ld\n", (unsigned long)dimover); cbf_failnez (cbf_write_string (file, text)) } if (dimfast > 0) { sprintf (text, "X-Binary-Size-Fastest-Dimension: %ld\n", (unsigned long)dimfast); cbf_failnez (cbf_write_string (file, text)) } if (dimmid > 0) { sprintf (text, "X-Binary-Size-Second-Dimension: %ld\n", (unsigned long)dimmid); cbf_failnez (cbf_write_string (file, text)) } if ((long)dimslow > 0) { sprintf (text, "X-Binary-Size-Third-Dimension: %ld\n", (unsigned long)dimslow); cbf_failnez (cbf_write_string (file, text)) } else if ((long)dimslow < 0 ) { sprintf (text, "X-Binary-Size-Third-Dimension: %ld\n", (unsigned long)(-(long)dimslow) ); cbf_failnez (cbf_write_string (file, text)) } if (padding > 0) { sprintf (text, "X-Binary-Size-Padding: %ld\n", (unsigned long)padding); cbf_failnez (cbf_write_string (file, text)) } cbf_failnez (cbf_write_string (file, "\n")) } else /* Simple header */ cbf_failnez (cbf_write_string (file, "START OF BINARY SECTION\n")) /* Copy the binary section to the output file */ if (file->write_encoding & ENC_NONE) { /* Write the separators */ cbf_failnez (cbf_put_character (file, 12)) cbf_failnez (cbf_put_character (file, 26)) cbf_failnez (cbf_put_character (file, 4)) cbf_failnez (cbf_put_character (file, 213)) /* Flush any bits in the buffers */ cbf_failnez (cbf_flush_bits (file)) /* If no MIME header, write the necessary data here */ if ( !(file->write_headers & MIME_HEADERS) ) { /* Write the binary identifier (64 bits) */ cbf_failnez (cbf_put_integer (file, id, 1, 64)) /* Write the size of the binary section (64 bits) */ cbf_failnez (cbf_put_integer (file, size, 0, 64)) /* Write the compression type (64 bits) */ cbf_failnez (cbf_put_integer (file, compression, 0, 64)) } /* Get the current point in the new file */ cbf_failnez (cbf_get_fileposition (file, &start)) /* Copy the binary section to the output file */ cbf_failnez (cbf_copy_file (file, infile, size)) /* If padding requested, pad with zero */ if (padding > 0) { for (ip = 0; ip < 100; ip++) text[ip] = 0; for (ip = 0; ip < padding; ip+=100) { cbf_failnez(cbf_put_bits(file, (int *)text,CHAR_BIT*(ip+100 8) elsize = 8; } else elsize = 4; /* Go back to the start of the binary data */ cbf_failnez (cbf_set_fileposition (infile, start, SEEK_SET)) if (file->write_encoding & ENC_QP) cbf_failnez (cbf_toqp (infile, file, size)) else if (file->write_encoding & ENC_BASE64) cbf_failnez (cbf_tobase64 (infile, file, size)) else if(file->write_encoding & ENC_BASE32K) cbf_failnez(cbf_tobase32k (infile, file, size)) else if (file->write_encoding & ENC_BASE8) cbf_failnez (cbf_tobasex (infile, file, size, elsize, 8)) else if (file->write_encoding & ENC_BASE10) cbf_failnez (cbf_tobasex (infile, file, size, elsize, 10)) else cbf_failnez (cbf_tobasex (infile, file, size, elsize, 16)) } /* Write the MIME footer */ if (file->write_headers & MIME_HEADERS) cbf_failnez (cbf_write_string (file, "\n--CIF-BINARY-FORMAT-SECTION----\n;\n")) else cbf_failnez (cbf_write_string (file, "\nEND OF BINARY SECTION\n;\n")) /* Flush the buffer */ cbf_failnez (cbf_flush_characters (file)) /* Replace a connection to a temporary file? */ if (start != 0 && isbuffer && type == CBF_TOKEN_TMP_BIN && (file->write_encoding & ENC_NONE)) cbf_failnez (cbf_set_bintext (column, row, CBF_TOKEN_BIN, id, file, start, size, checked_digest, digest, bits, sign, realarray, byteorder, dimover, dimfast, dimmid, dimslow, padding, compression)) /* Success */ return 0; } #ifdef __cplusplus } #endif ./CBFlib-0.9.2.2/src/fcb_atol_wcnt.f900000644000076500007650000000254011603702106015512 0ustar yayayaya INTEGER(8) FUNCTION FCB_ATOL_WCNT(ARRAY,N,CNT) !----------------------------------------------------------------------- ! Converts bytes in ARRAY to an INTEGER(8), consuming CNT bytes !----------------------------------------------------------------------- IMPLICIT NONE INTEGER, INTENT(OUT):: CNT INTEGER, INTENT(IN):: N INTEGER(1),INTENT(IN):: ARRAY(N) INTEGER, PARAMETER :: I0=Z'30',& !IACHAR('0') I9=Z'39',& !IACHAR('9') IM=Z'2D',& !IACHAR('-') IP=Z'2B',& !IACHAR('+') SP=Z'20',& !IACHAR(' ') HT=Z'09' !tab position in the ASCII code INTEGER I,K,BLANK,VORZEICHEN !----------------------------------------------------------------------- FCB_ATOL_WCNT = 0 CNT = 0 BLANK = 0 VORZEICHEN = 0 DO I = 1,N K=ARRAY(I) IF (K.GE.I0 .AND. K.LE.I9 ) THEN FCB_ATOL_WCNT = FCB_ATOL_WCNT*10+(K-I0) BLANK = -1 IF (VORZEICHEN.EQ.0) VORZEICHEN=1 ELSE IF (K.EQ.IM .OR. K.EQ.IP ) THEN IF (VORZEICHEN.NE.0) EXIT IF (K.EQ.IM) VORZEICHEN =-1 IF (K.EQ.IP) VORZEICHEN = 1 ELSE IF (K.EQ.SP .OR. K.EQ.HT ) THEN IF (BLANK.LT.0) EXIT BLANK = BLANK+1 ELSE EXIT END IF CNT = CNT+1 END DO IF (VORZEICHEN.LT.0) FCB_ATOL_WCNT = -FCB_ATOL_WCNT RETURN END FUNCTION FCB_ATOL_WCNT ./CBFlib-0.9.2.2/src/cbf_byte_offset.c0000644000076500007650000022531311603702106015662 0ustar yayayaya/********************************************************************** * cbf_byte_offset -- byte-offset compression * * * * Version 0.8.0 20 July 2008 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifdef __cplusplus extern "C" { #endif #include #include #include #include #include #include "cbf.h" #include "cbf_file.h" #include "cbf_byte_offset.h" /* Compress and array with the byte-offset algorithm */ int cbf_compress_byte_offset (void *source, size_t elsize, int elsign, size_t nelem, unsigned int compression, cbf_file *file, size_t *compressedsize, int *storedbits, int realarray, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding) { unsigned int count, borrow, element[4], prevelement[4], unsign, sign, limit, bits; unsigned char *unsigned_char_data; unsigned char *unsigned_char_dest=NULL; int delta[4]; int numints, iint, kint; char * border; char * rformat; size_t csize; int bflag=0x800080; int bbflag=0x80000000; int byte0, byte1, byte2, byte3; int sbyte0, sbyte1; unsigned char fixup0; unsigned char fixup1; /* Is the element size valid? */ if (elsize != sizeof (int) && elsize != 2* sizeof (int) && elsize != 4* sizeof (int) && elsize != sizeof (short) && elsize != sizeof (char)) return CBF_ARGUMENT; /* check for compatible real format */ if ( realarray ) { cbf_failnez (cbf_get_local_real_format(&rformat) ) if ( strncmp(rformat,"ieee",4) ) return CBF_ARGUMENT; } bits = elsize * CHAR_BIT; if (bits < 1 || bits > 64) return CBF_ARGUMENT; if (bits != 8 && bits != 16 && bits != 32 && bits != 64) return CBF_ARGUMENT; numints = (bits + CHAR_BIT*sizeof (int) -1)/(CHAR_BIT*sizeof (int)); /* Maximum limits */ sign = 1 << ((elsize-(numints-1)*sizeof(int))* CHAR_BIT - 1); if (elsize == sizeof (int) || elsize == numints*sizeof(int) ) limit = ~0; else if (numints == 1) { limit = ~-(1 << (elsize * CHAR_BIT)); } else { limit = ~-(1 << ((elsize-(numints-1)*sizeof(int)) * CHAR_BIT)); } if (storedbits) *storedbits = bits; /* Offset to make the value unsigned */ if (elsign) unsign = sign; else unsign = 0; /* Get the local byte order */ if (realarray) { cbf_get_local_real_byte_order(&border); } else { cbf_get_local_integer_byte_order(&border); } fixup0 = 0x00; fixup1 = 0x80; sbyte0 = byte0 = 0; sbyte1 = byte1 = 1; byte2 = 2; byte3 = 3; if (toupper(border[0]) != toupper(byteorder[0])) { byte0 = 3; byte1 = 2; sbyte0 = byte2 = 1; sbyte1 = byte3 = 0; } if (toupper(byteorder[0]) == 'B'){ fixup0 = 0x80; fixup1 = 0x0; } /* Initialise the pointer */ unsigned_char_data = (unsigned char *) source; /* Set up the previous element for comparison */ prevelement[0] = prevelement[1] = prevelement[2] = prevelement[3] = 0; prevelement[numints-1] = unsign; csize = 0; /* Write the elements */ #ifndef CBF_NOFAST_BYTE_OFFSET /* First try a fast memory-memory transfer */ switch (elsize) { case (1): /* Doing byte_offset with elsize 1 does not make much sense, but we can at least do it quickly */ if (!cbf_set_output_buffersize(file,nelem*2)) { unsigned_char_dest = (unsigned char *)(file->characters+file->characters_used); if (elsign) { char pc = 0; int delta; for (count = 0; count < nelem; count++) { delta = *unsigned_char_data - pc; if (delta < -127 || delta > 127) { *unsigned_char_dest++ = 0x80; *unsigned_char_dest++ = delta & 0xff; *unsigned_char_dest++ = (delta >> 8) & 0xff; csize += 3; } else { *unsigned_char_dest++ = delta; csize++; } pc = *unsigned_char_data++; } } else { unsigned char pc = 0; int delta; for (count = 0; count < nelem; count++) { delta = *unsigned_char_data - pc; if (delta < -127 || delta > 127) { *unsigned_char_dest++ = 0x80; *unsigned_char_dest++ = delta & 0xff; *unsigned_char_dest++ = (delta >> 8) & 0xff; csize += 3; } else { *unsigned_char_dest++ = delta; csize++; } pc = *unsigned_char_data++; } } file->characters_used+=csize; if (compressedsize) *compressedsize = csize; return 0; } break; case (2): /* We are compressing 16-bit data, which should compress to about half. We allow up to the full size of the original data */ if (!cbf_set_output_buffersize(file,nelem*elsize)) { short int pint; long int dint; short int *sint; if (sizeof(short int) != 2) break; pint = 0; unsigned_char_dest = (unsigned char *)(file->characters+file->characters_used); sint = (short int *) unsigned_char_data; for (count = 0; 3*count < 2*nelem; count++) { dint = (long int)sint[count] - (long int) pint; pint = sint[count]; if (dint <= 127 && dint >= -127) { *unsigned_char_dest++ = (unsigned char)dint; csize ++; } else { if (dint <= 32767 && dint >= -32767) { *unsigned_char_dest++ = 0x80; *unsigned_char_dest++ = ((unsigned char *)&dint)[sbyte0]; *unsigned_char_dest++ = ((unsigned char *)&dint)[sbyte1]; csize += 3; } else { *unsigned_char_dest++ = 0x80; *unsigned_char_dest++ = fixup0; *unsigned_char_dest++ = fixup1; *unsigned_char_dest++ = ((unsigned char *)&dint)[byte0]; *unsigned_char_dest++ = ((unsigned char *)&dint)[byte1]; *unsigned_char_dest++ = ((unsigned char *)&dint)[byte2]; *unsigned_char_dest++ = ((unsigned char *)&dint)[byte3]; csize +=7; } } } /* At this point nelem-count elements remain and file->characters_size-(csize+file->characters_used) characters remain in the buffer */ if (elsize*(nelem-count) > file->characters_size-(csize+file->characters_used)) { if (compression&CBF_NO_EXPAND) break; if (cbf_set_output_buffersize(file,1024+(nelem*elsize*3)/2)) break; unsigned_char_dest = (unsigned char *)(file->characters+file->characters_used+csize); } for (; count < nelem; count++) { dint = (long int)sint[count] - (long int)pint; pint = sint[count]; if (dint <= 127 && dint >= -127) { *unsigned_char_dest++ = (unsigned char)dint; csize ++; } else { if (dint <= 32767 && dint >= -32767) { if (csize > nelem*elsize-3 ) { if (compression&CBF_NO_EXPAND) return CBF_NOCOMPRESSION; } if (elsize*(nelem-count) > file->characters_size-(csize+file->characters_used)) { if (cbf_set_output_buffersize(file,1024+nelem*elsize*2)) break; unsigned_char_dest = (unsigned char *)(file->characters+file->characters_used+csize); } *unsigned_char_dest++ = 0x80; *unsigned_char_dest++ = ((unsigned char *)&dint)[byte0]; *unsigned_char_dest++ = ((unsigned char *)&dint)[byte1]; csize += 3; } else { if (csize > nelem*elsize-7 ) { if (compression&CBF_NO_EXPAND) return CBF_NOCOMPRESSION; } if (elsize*(nelem-count) > file->characters_size-(csize+file->characters_used)) { if (cbf_set_output_buffersize(file,1024+nelem*elsize*2)) break; unsigned_char_dest = (unsigned char *)(file->characters+file->characters_used+csize); } *unsigned_char_dest++ = 0x80; *unsigned_char_dest++ = fixup0; *unsigned_char_dest++ = fixup1; *unsigned_char_dest++ = ((unsigned char *)&dint)[byte0]; *unsigned_char_dest++ = ((unsigned char *)&dint)[byte1]; *unsigned_char_dest++ = ((unsigned char *)&dint)[byte2]; *unsigned_char_dest++ = ((unsigned char *)&dint)[byte3]; csize +=7; } } } file->characters_used+=csize; if (compressedsize) *compressedsize = csize; return 0; } break; case (4): /* We are compressing 32-bit data, which should compress to about one quarter. We allow up to the full size of the original data */ if (!cbf_set_output_buffersize(file,nelem*elsize)) { int pint, dint; short int sint; int *oint; if (sizeof(short int) != 2) break; if (sizeof(int) != 4) break; pint = 0; unsigned_char_dest = (unsigned char *)(file->characters+file->characters_used); oint = (int *) unsigned_char_data; for (count = 0; 7*count < 4*nelem; count++) { dint = oint[count] - pint; pint = oint[count]; if (dint <= 127 && dint >= -127) { *unsigned_char_dest++ = (unsigned char)dint; csize ++; } else if (dint <= 32767 && dint >= -32767) { *unsigned_char_dest++ = 0x80; sint = dint; *unsigned_char_dest++ = ((unsigned char *)&sint)[sbyte0]; *unsigned_char_dest++ = ((unsigned char *)&sint)[sbyte1]; csize += 3; } else { *unsigned_char_dest++ = 0x80; *unsigned_char_dest++ = fixup0; *unsigned_char_dest++ = fixup1; *unsigned_char_dest++ = ((unsigned char *)&dint)[byte0]; *unsigned_char_dest++ = ((unsigned char *)&dint)[byte1]; *unsigned_char_dest++ = ((unsigned char *)&dint)[byte2]; *unsigned_char_dest++ = ((unsigned char *)&dint)[byte3]; csize +=7; } } /* At this point nelem-count elements remain and file->characters_size-(csize+file->characters_used) characters remain in the buffer */ if (elsize*(nelem-count) > file->characters_size-(csize+file->characters_used)) { if (compression&CBF_NO_EXPAND) break; if (cbf_set_output_buffersize(file,1024+(nelem*elsize*7)/4)) break; unsigned_char_dest = (unsigned char *)(file->characters+file->characters_used+csize); } for (; count < nelem; count++) { dint = oint[count] - pint; pint = oint[count]; if (dint <= 127 && dint >= -127) { *unsigned_char_dest++ = (unsigned char)dint; csize ++; } else if (dint <= 32767 && dint >= -32767) { *unsigned_char_dest++ = 0x80; sint = dint; *unsigned_char_dest++ = ((unsigned char *)&sint)[sbyte0]; *unsigned_char_dest++ = ((unsigned char *)&sint)[sbyte1]; csize += 3; } else { if (csize > nelem*elsize-7 ) { if (compression&CBF_NO_EXPAND) return CBF_NOCOMPRESSION; } if (elsize*(nelem-count) > file->characters_size-(csize+file->characters_used)) { if (cbf_set_output_buffersize(file,1024+nelem*elsize*2)) break; unsigned_char_dest = (unsigned char *)(file->characters+file->characters_used+csize); } *unsigned_char_dest++ = 0x80; *unsigned_char_dest++ = fixup0; *unsigned_char_dest++ = fixup1; *unsigned_char_dest++ = ((unsigned char *)&dint)[byte0]; *unsigned_char_dest++ = ((unsigned char *)&dint)[byte1]; *unsigned_char_dest++ = ((unsigned char *)&dint)[byte2]; *unsigned_char_dest++ = ((unsigned char *)&dint)[byte3]; csize +=7; } } file->characters_used+=csize; if (compressedsize) *compressedsize = csize; return 0; } break; default: break; } #endif /* If we got here, we will do it the slow, painful way */ for (count = 0; count < nelem; count++) { /* Get the next element */ if (numints > 1) { if (border[0] == 'b') { for (iint = numints; iint; iint--) { element[iint-1] = *((unsigned int *) unsigned_char_data); unsigned_char_data += sizeof (int); } } else { for (iint = 0; iint < numints; iint++) { element[iint] = *((unsigned int *) unsigned_char_data); unsigned_char_data += sizeof (int); } } } else { if (elsize == sizeof (int)) element[0] = *((unsigned int *) unsigned_char_data); else if (elsize == sizeof (short)) element[0] = *((unsigned short *) unsigned_char_data); else element[0] = *unsigned_char_data; unsigned_char_data += elsize; } /* Make the element unsigned */ element[numints-1] += unsign; element[numints-1] &= limit; /* Compute the delta */ borrow = 0; kint = 0; if (numints > 1) { for (iint = 0; iint < numints; iint++) delta[iint] = prevelement[iint]; cbf_failnez(cbf_mpint_negate_acc((unsigned int *)delta,numints)); cbf_failnez(cbf_mpint_add_acc((unsigned int *)delta, numints, element, numints)) if (delta[numints-1] & sign) delta[numints-1] |= (~limit); } else { delta[0] = element[0] - prevelement[0]; if (delta[0] & sign) delta[0] |= (~limit); } prevelement[0] = element[0]; for (iint = 1; iint < numints; iint++) { prevelement[iint] = element[iint]; if ((delta[0] >= 0 && delta[iint] != 0 ) || (delta[0] < 0 && (delta[iint]+1)!=0) ) kint = iint; } if (kint == 0) { if (delta[0] <= 127 && delta[0] >= -127) { cbf_failnez(cbf_put_bits(file,&delta[0],8)) csize++; } else if (sizeof(int) > 1 && delta[0] <= 32767 && delta[0] >= -32767) { cbf_failnez(cbf_put_bits(file,&bflag,8)) cbf_failnez (cbf_put_integer (file, delta[0], 1, 16)) csize +=3; } else if ( sizeof(int) > 2 && (sizeof(int) < 5 || (delta[0] <= 2147483647L && delta[0] >= -2147483647L ) ) ){ cbf_failnez(cbf_put_bits(file,&bflag,24)) cbf_failnez(cbf_put_integer (file, delta[0], 1, 32)) csize +=7; } else if (sizeof(int) > 4 ) { cbf_failnez(cbf_put_bits(file,&bflag,24)) cbf_failnez(cbf_put_bits(file,&bbflag,32)) cbf_failnez (cbf_put_integer (file, delta[0], 1, 64)) csize += 15; } else { return CBF_ARGUMENT; } } else { if ((kint+1)*sizeof(int) < 5 ) { cbf_failnez(cbf_put_bits(file,&bflag,24)) for (iint = 0; iint < kint+1; iint++) { cbf_failnez (cbf_put_integer (file, delta[iint], iint==numints-1?1:0, iint<(numints-1)?(CHAR_BIT*sizeof (int)): bits-(CHAR_BIT*sizeof (int))*iint )) } csize += 7; } else if ((kint+1)*sizeof(int) < 9 ) { cbf_failnez(cbf_put_bits(file,&bflag,24)) cbf_failnez(cbf_put_bits(file,&bbflag,32)) for (iint = 0; iint < kint+1; iint++) { cbf_failnez (cbf_put_integer (file, delta[iint], iint==numints-1?1:0, iint<(numints-1)?(CHAR_BIT*sizeof (int)): bits-(CHAR_BIT*sizeof (int))*iint )) } csize += 15; } else return CBF_ARGUMENT; } } /* Return the number of characters written */ if (compressedsize) *compressedsize = csize; /* Success */ return 0; } /* Decompress an array with the byte-offset algorithm */ int cbf_decompress_byte_offset_slow (void *destination, size_t elsize, int elsign, size_t nelem, size_t *nelem_read, size_t compressedsize, unsigned int compression, int data_bits, int data_sign, cbf_file *file, int realarray, const char *byteorder, size_t dimover, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding) { unsigned int element[4], prevelement[4], sign, unsign, limit; unsigned int data_unsign; unsigned char *unsigned_char_data; int errorcode, overflow, numints, iint, carry; int delta[4]; char * border; char * rformat; size_t numread; /* prepare the errorcode */ errorcode = 0; /* Is the element size valid? */ if (elsize != sizeof (int) && elsize != 2* sizeof (int) && elsize != 4* sizeof (int) && elsize != sizeof (short) && elsize != sizeof (char)) return CBF_ARGUMENT; /* check for compatible real format */ if ( realarray ) { cbf_failnez (cbf_get_local_real_format(&rformat) ) if ( strncmp(rformat,"ieee",4) ) return CBF_ARGUMENT; } /* Check the stored element size */ if (data_bits < 1 || data_bits > 64) return CBF_ARGUMENT; numints = (data_bits + CHAR_BIT*sizeof (int) -1)/(CHAR_BIT*sizeof (int)); /* Initialise the pointer */ unsigned_char_data = (unsigned char *) destination; /* Maximum limits */ sign = 1 << ((elsize-(numints-1)*sizeof(int))* CHAR_BIT - 1); if (elsize == sizeof (int) || elsize == numints*sizeof(int)) limit = ~0; else if (numints == 1 ) { limit = ~(-(1 << (elsize * CHAR_BIT))); } else { limit = ~(-(1 << ((elsize-(numints-1)*sizeof(int)) * CHAR_BIT))); } /* Offsets to make the value unsigned */ if (data_sign) data_unsign = sign; else data_unsign = 0; if (elsign) unsign = sign; else unsign = 0; /* Get the local byte order */ if (realarray) { cbf_get_local_real_byte_order(&border); } else { cbf_get_local_integer_byte_order(&border); } /* Set up the previous element for increments */ prevelement[0] = prevelement[1] = prevelement[2] = prevelement[3] = 0; prevelement[numints-1] = data_unsign; /* Read the elements */ overflow = 0; numread = 0; while (numread < nelem) { for (iint=0; iint < numints; iint++){ element[iint] = prevelement[iint]; delta[iint] = 0; } carry = 0; cbf_failnez(cbf_get_bits(file,delta,8)) if ((delta[0]&0xFF) == 0x80) { cbf_failnez(cbf_get_bits(file,delta,16)) if ( (delta[0]& 0xFFFF) == 0x8000) { cbf_failnez(cbf_get_bits(file,delta,32)) if ( (sizeof(int)==2 && delta[0] == 0 && delta[1] == 0x8000) || (sizeof(int)> 3 && (delta[0]&0xFFFFFFFF)==0x80000000) ) { cbf_failnez(cbf_get_bits(file,delta,64)) } else { if (sizeof(int) == 2) { if (delta[1] & 0x8000) { for (iint = 2; iint < numints; iint++) delta[iint] = ~0; } } else { if (delta[0] & 0x80000000) { delta[0] |= ~0xFFFFFFFF; for (iint = 1; iint < numints; iint++) { delta[iint] = ~0; } } } } } else { if (delta[0] & 0x8000) { delta[0] |= ~0xFFFF; for (iint = 1; iint < numints; iint++) { delta[iint] = ~0; } } } } else { if (delta[0]&0x80) { delta[0] |= ~0xFF; for (iint = 1; iint < numints; iint++) { delta[iint] = ~0; } } } if (numints > 1) { for (iint = 0; iint < numints; iint++) element[iint] = prevelement[iint]; cbf_failnez(cbf_mpint_add_acc(element,numints, (unsigned int *)delta,numints)) } else { element[0] = prevelement[0] + delta[0]; element[0] &= limit; } for (iint = 0; iint < numints; iint++) { prevelement[iint] = element[iint]; } /* Make the element signed? */ element[numints-1] -= unsign; #if DEBUGPRINT == 1 fprintf(stderr, "i: %d, 1", numread); fprintf(stderr, " = %d", element[0]); for (iint = 1; iint < numints; iint++) fprintf(stderr, ", %d", element[iint]); fprintf(stderr, "\n"); #endif /* Save the element */ if (numints > 1) { if (border[0] == 'b') { for (iint = numints; iint; iint--) { *((unsigned int *) unsigned_char_data) = element[iint-1]; unsigned_char_data += sizeof (int); } } else { for (iint = 0; iint < numints; iint++) { *((unsigned int *) unsigned_char_data) = element[iint]; unsigned_char_data += sizeof (int); } } } else { if (elsize == sizeof (int)) *((unsigned int *) unsigned_char_data) = element[0]; else if (elsize == sizeof (short)) *((unsigned short *) unsigned_char_data) = element[0]; else *unsigned_char_data = element[0]; unsigned_char_data += elsize; } numread++; } /* Number read */ if (nelem_read) *nelem_read = numread; /* Success */ return overflow; } /* * this fast version assumes chars are 8 bits * and signed integers are represented in two's complement format */ int cbf_decompress_byte_offset_fast(void *destination, size_t elsize, int elsign, size_t nelem, size_t *nelem_read, size_t compressedsize, unsigned int compression, int data_bits, int data_sign, cbf_file *file, int realarray, const char *byteorder, size_t dimover, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding) { unsigned char *unsigned_char_data; char * border; char * rformat; size_t numread; CBF_sll_type delta; int i = 0; unsigned char *rawdata = NULL; /* Is the element size valid? */ if (elsize != sizeof (int) && elsize != 2* sizeof (int) && elsize != 4* sizeof (int) && elsize != sizeof (short) && elsize != sizeof (char)) { return CBF_ARGUMENT; } if (elsize != 1 && elsize != 2 && elsize != 4 && elsize !=8 ) { return CBF_ARGUMENT; } /* check for compatible real format */ if ( realarray ) { cbf_failnez (cbf_get_local_real_format(&rformat) ) if ( strncmp(rformat,"ieee",4) ) return CBF_ARGUMENT; } /* Check the stored element size */ if (data_bits < 1 || data_bits > 64) return CBF_ARGUMENT; /* Initialise the pointer */ unsigned_char_data = (unsigned char *) destination; /* Get the local byte order */ if (realarray) { cbf_get_local_real_byte_order(&border); } else { cbf_get_local_integer_byte_order(&border); } /* get all compressed data */ if (file->characters_used >= compressedsize) { rawdata = (unsigned char *) file->characters; file->characters += compressedsize; file->characters_size -= compressedsize; file->characters_used -= compressedsize; } else { if (file->temporary == 0) { rawdata = malloc(compressedsize); if (rawdata == NULL) { fprintf(stderr, "Out of memory\n"); return CBF_OVERFLOW; } if (file->stream == NULL) { fprintf(stderr, "No file stream associated with handle\n"); return CBF_NOTFOUND; } if (fread(rawdata, 1, compressedsize, file->stream) != compressedsize) { rawdata = NULL; } } } if (rawdata == NULL) return CBF_FILEREAD; /* cannot find data */ numread = 0; if (elsign) { #ifdef CBF_USE_LONG_LONG long long base = 0; unsigned char *baseaddr; if (border[0] == 'b') { baseaddr = (unsigned char *) &base + sizeof(CBF_sll_type) - elsize; } else { baseaddr = (unsigned char *) &base; } #else unsigned int sign, precarry; size_t el0, el1; #if CBF_SLL_INTS == 2 CBF_sll_type base = {0,0}; #else CBF_sll_type base = {0,0,0,0}; size_t el2, el3, fl0, fl1; #endif sign = 1 << (sizeof(unsigned int)*CHAR_BIT-1); if (border[0] == 'b') { #if CBF_SLL_INTS > 2 el0 = 3; el1 = 2; el2 = 1; el3 = 0; fl0 = 1; fl1 = 0; #else el0 = 1; el1 = 0; #endif } else { el0 = 0; el1 = 1; #if CBF_SLL_INTS > 2 el2 = 2; el3 = 3; fl0 = 0; fl1 = 1; #endif } #endif #ifdef CBF_USE_LONG_LONG while (i < compressedsize) { int j; delta = (signed char) rawdata[i++]; if (delta == (signed char) 0x80) { delta = rawdata[i++]; delta |= (signed char) rawdata[i++] << 8; if (delta == (short) 0x8000) { delta = rawdata[i++]; delta |= rawdata[i++] << 8; delta |= rawdata[i++] << 16; delta |= (signed char) rawdata[i++] << 24; if ((long) (delta & 0xffffffff) == (long) 0x80000000) { delta = rawdata[i++]; delta |= rawdata[i++] << 8; delta |= rawdata[i++] << 16; delta |= (unsigned long long) rawdata[i++] << 24; delta |= (unsigned long long) rawdata[i++] << 32; delta |= (unsigned long long) rawdata[i++] << 40; delta |= (unsigned long long) rawdata[i++] << 48; delta |= (signed long long) rawdata[i++] << 56; } } } base += delta; for (j = 0; j < elsize; j++) *unsigned_char_data++ = baseaddr[j]; numread++; } #else #if CBF_SLL_INTS==2 while (i < compressedsize) { delta.el1 = 0; delta.el0 = (signed char) rawdata[i++]; if (delta.el0 == (signed char) 0x80) { delta.el0 = rawdata[i++]; delta.el0 |= (signed char) rawdata[i++] << 8; if (delta.el0 & 0x8000L) { delta.el0 |= ~0x7FFFL; delta.el1 = ~0L; } if ((delta.el0 & 0xffffL) == 0x8000) { delta.el1 = 0; delta.el0 = rawdata[i++]; delta.el0 |= rawdata[i++] << 8; delta.el0 |= rawdata[i++] << 16; delta.el0 |= (signed char) rawdata[i++] << 24; if (delta.el0 & 0x80000000L) { delta.el0 |= ~0x7FFFFFFFL; delta.el1 = ~0L; } if ((delta.el0 & 0xffffffffL) == 0x80000000L) { delta.el0 = 0; delta.el0 = rawdata[i++]; delta.el0 |= rawdata[i++] << 8; delta.el0 |= rawdata[i++] << 16; delta.el0 |= rawdata[i++] << 24; delta.el1 = rawdata[i++]; delta.el1 |= rawdata[i++] << 8; delta.el1 |= rawdata[i++] << 16; delta.el1 |= (signed char) rawdata[i++] << 24; } } } precarry = 0; if (base.el0 & sign) precarry++; if (delta.el0 & sign) precarry++; base.el0 += delta.el0; if (precarry == 2 || (precarry == 1 && !(base.el0&sign) ) ) base.el1++; base.el1+= delta.el1; switch (elsize) { case (sizeof(unsigned int) *2): ((unsigned int *)unsigned_char_data)[el0] = base.el0; ((unsigned int *)unsigned_char_data)[el1] = base.el1; break; case (sizeof(unsigned int) ): ((unsigned int *)unsigned_char_data)[0] = base.el0; break; case (sizeof(unsigned short) ): ((unsigned short *)unsigned_char_data)[0] = (unsigned short)base.el0; break; case (sizeof(unsigned char) ): ((unsigned char *)unsigned_char_data)[0] = (unsigned char)base.el0; break; } unsigned_char_data+= elsize; numread++; } #else while (i < compressedsize) { delta.el1 = delta.el2 = delta.el3 = 0; delta.el0 = (signed char) rawdata[i++]; if (delta.el0 == (signed char) 0x80) { delta.el0 = rawdata[i++]; delta.el0 |= (signed char) rawdata[i++] << 8; if (delta.el0 & 0x8000) delta.el1 = delta.el2 = delta.el3 = ~0; if ((delta.el0 & 0xffff) == 0x8000) { delta.el2 = delta.el3 = 0; delta.el0 = rawdata[i++]; delta.el0 |= rawdata[i++] << 8; delta.el1 = rawdata[i++]; delta.el1 |= (signed char) rawdata[i++] << 8; if (delta.el1 & 0x8000) delta.el2 = delta.el3 = ~0; if (delta.el0 == 0 && (delta.el1 & 0x8000) == 0x8000) { delta.el0 = rawdata[i++]; delta.el0 |= rawdata[i++] << 8; delta.el1 = rawdata[i++]; delta.el1 |= rawdata[i++] << 8; delta.el2 = rawdata[i++]; delta.el2 |= rawdata[i++] << 8; delta.el3 = rawdata[i++]; delta.el3 |= (signed char)rawdata[i++] << 8; } } } precarry = 0; if (base.el0 & sign) precarry++; if (delta.el0 & sign) precarry++; base.el0 += delta.el0; if (precarry == 2 || (precarry == 1 && !(base.el0&sign) ) ) base.el1++; precarry = 0; if (base.el1 & sign) precarry++; if (delta.el1 & sign) precarry++; base.el1+= delta.el1; if (precarry == 2 || (precarry == 1 && !(base.el1&sign) ) ) base.el2++; precarry = 0; if (base.el2 & sign) precarry++; if (delta.el2 & sign) precarry++; base.el2+= delta.el2; if (precarry == 2 || (precarry == 1 && !(base.el1&sign) ) ) base.el3++; base.el1+= delta.el1; switch (elsize) { case (sizeof(unsigned int) *4): ((unsigned int *)unsigned_char_data)[el0] = base.el0; ((unsigned int *)unsigned_char_data)[el1] = base.el1; ((unsigned int *)unsigned_char_data)[el2] = base.el2; ((unsigned int *)unsigned_char_data)[el3] = base.el3; break; case (sizeof(unsigned int) *2 ): ((unsigned int *)unsigned_char_data)[fl0] = base.el0; ((unsigned int *)unsigned_char_data)[fl1] = base.el1; break; case (sizeof(unsigned char) ): ((unsigned char *)unsigned_char_data)[0] = base.el0; break; } unsigned_char_data+= elsize; numread++; } #endif #endif } else { #ifdef CBF_USE_LONG_LONG unsigned long long base = 0; unsigned long long basemask = 0; unsigned char *baseaddr; int j; for (j = 0; j < elsize*8; j++) { basemask <<= 1; basemask |= 1; } if (border[0] == 'b') { baseaddr = (unsigned char *) &base + sizeof(CBF_ull_type) - elsize; } else { baseaddr = (unsigned char *) &base; } #else unsigned int sign, precarry; size_t el0, el1; #if CBF_ULL_INTS == 2 CBF_ull_type base = {0,0}; #else CBF_ull_type base = {0,0,0,0}; size_t el2, el3, fl0, fl1; #endif sign = 1 << (sizeof(unsigned int)*CHAR_BIT-1); if (border[0] == 'b') { #if CBF_ULL_INTS > 2 el0 = 3; el1 = 2; el2 = 1; el3 = 0; fl0 = 1; fl1 = 2; #else el0 = 1; el1 = 0; #endif } else { el0 = 0; el1 = 1; #if CBF_SLL_INTS > 2 el2 = 2; el3 = 3; fl0 = 0; fl1 = 1; #endif } #endif #ifdef CBF_USE_LONG_LONG while (i < compressedsize) { delta = (signed char) rawdata[i++]; if (delta == (signed char) 0x80) { delta = rawdata[i++]; delta |= (signed char) rawdata[i++] << 8; if (delta == (short) 0x8000) { delta = rawdata[i++]; delta |= rawdata[i++] << 8; delta |= rawdata[i++] << 16; delta |= (signed char) rawdata[i++] << 24; if ((long) (delta & 0xffffffff) == (long) 0x80000000) { delta = rawdata[i++]; delta |= rawdata[i++] << 8; delta |= rawdata[i++] << 16; delta |= (unsigned long long) rawdata[i++] << 24; delta |= (unsigned long long) rawdata[i++] << 32; delta |= (unsigned long long) rawdata[i++] << 40; delta |= (unsigned long long) rawdata[i++] << 48; delta |= (signed long long) rawdata[i++] << 56; } } } base += delta; base &= basemask; for (j = 0; j < elsize; j++) *unsigned_char_data++ = baseaddr[j]; numread++; } #else #if CBF_SLL_INTS==2 while (i < compressedsize) { delta.el1 = 0; delta.el0 = (signed char) rawdata[i++]; if (delta.el0 == (signed char) 0x80) { delta.el0 = rawdata[i++]; delta.el0 |= (signed char) rawdata[i++] << 8; if (delta.el0 & 0x8000L) { delta.el0 |= ~0x7FFFL; delta.el1 = ~0L; } if ((delta.el0 & 0xffff) == 0x8000) { delta.el1 = 0; delta.el0 = rawdata[i++]; delta.el0 |= rawdata[i++] << 8; delta.el0 |= rawdata[i++] << 16; delta.el0 |= (signed char) rawdata[i++] << 24; if (delta.el0 & 0x80000000L) delta.el1 = ~0; if ((delta.el0 & 0xffffffff) == 0x80000000) { delta.el0 = rawdata[i++]; delta.el0 |= rawdata[i++] << 8; delta.el0 |= rawdata[i++] << 16; delta.el0 |= rawdata[i++] << 24; delta.el1 = rawdata[i++]; delta.el1 |= rawdata[i++] << 8; delta.el1 |= rawdata[i++] << 16; delta.el1 |= (signed char) rawdata[i++] << 24; } } } precarry = 0; if (base.el0 & sign) precarry++; if (delta.el0 & sign) precarry++; base.el0 += delta.el0; if (precarry == 2 || (precarry == 1 && !(base.el0&sign) ) ) base.el1++; base.el1+= delta.el1; base.el1 &= 0xffffffffL; switch (elsize) { case (sizeof(unsigned int) *2): ((unsigned int *)unsigned_char_data)[el0] = base.el0; ((int *)unsigned_char_data)[el1] = (int)base.el1; break; case (sizeof(int) ): ((int *)unsigned_char_data)[0] = (int)base.el0; break; case (sizeof(short) ): ((short *)unsigned_char_data)[0] = (short)base.el0; break; case (sizeof(char) ): ((char *)unsigned_char_data)[0] = (char)base.el0; break; } unsigned_char_data+= elsize; numread++; } #else while (i < compressedsize) { delta.el1 = delta.el2 = delta.el3 = 0; delta.el0 = (signed char) rawdata[i++]; if (delta.el0 == (signed char) 0x80) { delta.el0 = rawdata[i++]; delta.el0 |= (signed char) rawdata[i++] << 8; if (delta.el0 & 0x8000) delta.el1 = delta.el2 = delta.el3 = ~0; if (delta.el0&0xffff == 0x8000) { delta.el2 = delta.el3 = 0; delta.el0 = rawdata[i++]; delta.el0 |= rawdata[i++] << 8; delta.el1 = rawdata[i++]; delta.el1 |= (signed char) rawdata[i++] << 8; if (delta.el1 & 0x8000) delta.el2 = delta.el3 = ~0; if (delta.el0 == 0 && delta.el1&0x8000 == 0x8000) { delta.el0 = rawdata[i++]; delta.el0 |= rawdata[i++] << 8; delta.el1 = rawdata[i++]; delta.el1 |= rawdata[i++] << 8; delta.el2 = rawdata[i++]; delta.el2 |= rawdata[i++] << 8; delta.el3 = rawdata[i++]; delta.el3 |= (signed char)rawdata[i++] << 8; } } } precarry = 0; if (base.el0 & sign) precarry++; if (delta.el0 & sign) precarry++; base.el0 += delta.el0; if (precarry == 2 || (precarry == 1 && !(base.el0&sign) ) ) base.el1++; precarry = 0; if (base.el1 & sign) precarry++; if (delta.el1 & sign) precarry++; base.el1+= delta.el1; if (precarry == 2 || (precarry == 1 && !(base.el1&sign) ) ) base.el2++; precarry = 0; if (base.el2 & sign) precarry++; if (delta.el2 & sign) precarry++; base.el2+= delta.el2; if (precarry == 2 || (precarry == 1 && !(base.el1&sign) ) ) base.el3++; base.el3+= delta.el3; base.el3 &= 0xffff; switch (elsize) { case (sizeof(unsigned int) *4): ((unsigned int *)unsigned_char_data)[el0] = base.el0; ((unsigned int *)unsigned_char_data)[el1] = base.el1; ((unsigned int *)unsigned_char_data)[el2] = base.el2; ((int *)unsigned_char_data)[el3] = base.el3; break; case (sizeof(unsigned int) *2 ): ((unsigned int *)unsigned_char_data)[fl0] = base.el0; ((int *)unsigned_char_data)[fl1] = base.el1; break; case (sizeof( char) ): (( char *)unsigned_char_data)[0] = (char)base.el0; break: } unsigned_char_data+= elsize; numread++; } #endif #endif } if (file->temporary == 0) free(rawdata); /* Number read */ if (nelem_read) *nelem_read = numread; /* Success */ return 0; } int cbf_decompress_byte_offset(void *destination, size_t elsize, int elsign, size_t nelem, size_t *nelem_read, size_t compressedsize, unsigned int compression, int data_bits, int data_sign, cbf_file *file, int realarray, const char *byteorder, size_t dimover, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding) { /* test for bits left in buffer, element size, chars are 8-bit, and signed integers are represented in two's complement */ if (file->bits[0] != 0 || elsize > sizeof(CBF_ull_type) || CHAR_BIT != 8 || ~0 != -1 || (elsize != 1 && elsize != 2 && elsize != 4 && elsize !=8 ) ) { return cbf_decompress_byte_offset_slow(destination, elsize, elsign, nelem, nelem_read, compressedsize, compression, data_bits, data_sign, file, realarray, byteorder, dimover, dimfast, dimmid, dimslow, padding); } return cbf_decompress_byte_offset_fast(destination, elsize, elsign, nelem, nelem_read, compressedsize, compression, data_bits, data_sign, file, realarray, byteorder, dimover, dimfast, dimmid, dimslow, padding); } #ifdef __cplusplus } #endif ./CBFlib-0.9.2.2/src/TestDrel.py0000777000076500007650000000000011603745057020701 2../dREL-ply-0.5/TestDrel.pyustar yayayaya./CBFlib-0.9.2.2/src/cbf_tree.c0000644000076500007650000011777411603702106014323 0ustar yayayaya/********************************************************************** * cbf_tree -- handle cbf nodes * * * * Version 0.7.7 19 February 2007 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifdef __cplusplus extern "C" { #endif #include #include #include #include #include "cbf.h" #include "cbf_alloc.h" #include "cbf_tree.h" #include "cbf_context.h" #include "cbf_binary.h" /* Make a new node */ int cbf_make_node (cbf_node **node, CBF_NODETYPE type, cbf_context *context, const char *name) { int errorcode; if (!node) return CBF_ARGUMENT; /* Create the new node */ cbf_failnez (cbf_alloc ((void **) node, NULL, sizeof (cbf_node), 1)) /* Initialise the node */ (*node)->type = type; (*node)->name = NULL; (*node)->link = NULL; (*node)->parent = NULL; (*node)->children = 0; (*node)->child_size = 0; (*node)->child = NULL; /* Add the context? */ if (type == CBF_LINK) (*node)->context = NULL; else { /* Does the context exist? */ if (context) (*node)->context = context; else (*node)->context = NULL; /* Add a context connection */ cbf_onfailnez (cbf_add_contextconnection (&(*node)->context), cbf_free ((void **) node, NULL)) /* Name the node */ errorcode = cbf_name_node (*node, name); if (errorcode) { errorcode |= cbf_free_context (&(*node)->context); return errorcode | cbf_free_node (*node); } } /* Success */ return 0; } /* Make a new node allowing for duplicates */ int cbf_make_new_node (cbf_node **node, CBF_NODETYPE type, cbf_context *context, const char *name) { int errorcode; if (!node) return CBF_ARGUMENT; /* Create the new node */ cbf_failnez (cbf_alloc ((void **) node, NULL, sizeof (cbf_node), 1)) /* Initialise the node */ (*node)->type = type; (*node)->name = NULL; (*node)->link = NULL; (*node)->parent = NULL; (*node)->children = 0; (*node)->child_size = 0; (*node)->child = NULL; /* Add the context? */ if (type == CBF_LINK) (*node)->context = NULL; else { /* Does the context exist? */ if (context) (*node)->context = context; else (*node)->context = NULL; /* Add a context connection */ cbf_onfailnez (cbf_add_contextconnection (&(*node)->context), cbf_free ((void **) node, NULL)) /* Name the node */ errorcode = cbf_name_new_node (*node, name); if (errorcode) { errorcode |= cbf_free_context (&(*node)->context); return errorcode | cbf_free_node (*node); } } /* Success */ return 0; } /* Undo the links leading to a node */ int cbf_undo_links (cbf_node **node) { cbf_node *snode; cbf_node *pnode; snode = *node; pnode = NULL; while (*node) { if ((*node)->type == CBF_LINK) { pnode = *node; if ((*node)->children) { cbf_failnez(cbf_set_children(*node,0)) } *node = (*node)->link; } else break; } if (!*node) { *node = snode; return 0; } if (pnode) { pnode->link = NULL; } if (snode->type == CBF_LINK) { cbf_failnez(cbf_free_node (snode)) } return 0; } /* Free a node */ int cbf_free_node (cbf_node *node) { unsigned int count; void *memblock; void *vchild; /* Check the arguments */ if (!node) return CBF_ARGUMENT; /* Check for a category */ if (node->type == CBF_CATEGORY) { unsigned int column; for (column = 0; column < node->children; column++) { while(node->child[column]->children) { cbf_failnez (cbf_delete_columnrow(node->child [column],node->child[column]->children-1)) } } } /* Disconnect the node from its parent? */ if (node->parent) for (count = 0; count < node->parent->children; count++) if (node->parent->child [count] == node) { node->parent->children--; if (node->parent->children == 0) { vchild = (void *)node->parent->child; cbf_failnez (cbf_free ((void **) &vchild, &node->parent->child_size)) node->parent->child = (cbf_node **)vchild; } else if (node->parent->children > count) memmove (node->parent->child + count, node->parent->child + count + 1, (node->parent->children - count) * sizeof (cbf_node *)); break; } /* Free the children */ cbf_failnez (cbf_set_children (node, 0)) /* Free the link */ if (node->link) { cbf_failnez(cbf_free_node(node->link)) node->link = NULL; } /* Free the name */ cbf_free_string (NULL, node->name); /* Free the context connection */ if (node->context) { cbf_failnez (cbf_delete_contextconnection (&node->context)) } /* Free the node */ memblock = (void *)node; return cbf_free ( &memblock, NULL); } /* Set the number of children */ int cbf_set_children (cbf_node *node, unsigned int children) { unsigned int count, new_size, kblock; void *vchild; int errorcode; /* Check the arguments */ if (!node) return CBF_ARGUMENT; /* Is the current size correct? */ if (children == node->children) return 0; /* Compute a target new size */ kblock = 16; if (children > 128*2) kblock = 128; if (children > 512*2) kblock = 512; new_size = (((int)((children -1)/kblock)))*kblock+kblock; if (new_size < children) new_size = children; /* Decrease the number of children? */ if (children < node->children) { errorcode = 0; for (count = children; count < node->children; count++) /* Free the child */ if (node->type == CBF_COLUMN) errorcode |= cbf_set_columnrow (node, count, NULL, 1); else if (node->type != CBF_LINK) if (node->child [count]) { node->child [count]->parent = NULL; errorcode |= cbf_free_node (node->child [count]); node->child [count] = NULL; } if (children == 0) { vchild = (void *)node->child; errorcode = cbf_free ((void **) &vchild, &node->child_size); node->child = NULL; } node->children = children; if (new_size < node->child_size ) { vchild = (void *)node->child; cbf_failnez (cbf_realloc ((void * *) &vchild, &node->child_size, sizeof (cbf_node *), new_size)) node->child = (cbf_node **)vchild; } return errorcode; } /* Increase the number of children */ if (new_size > node->child_size) { vchild = (void *)node->child; cbf_failnez (cbf_realloc ((void **) &vchild, &node->child_size, sizeof (cbf_node *), new_size)) node->child = (cbf_node **)vchild; } node->children = children; /* Success */ return 0; } /* Trace a link */ cbf_node *cbf_get_link (const cbf_node *node) { while (node) if (node->type == CBF_LINK) node = node->link; else return (cbf_node *) node; /* Fail */ return NULL; } /* Find a child node */ int cbf_find_child (cbf_node **child, const cbf_node *node, const char *name) { unsigned int count; const char *namec, *nodenamec; /* Follow any links */ node = cbf_get_link (node); /* Check the arguments */ if (!node) return CBF_ARGUMENT; /* Is it a normal node? */ if (node->type == CBF_COLUMN) return CBF_ARGUMENT; /* Search the children */ for (count = 0; count < node->children; count++) if (name) { if (node->child [count]->name) { for (namec = name, nodenamec = node->child [count]->name; *namec && toupper (*nodenamec) == toupper (*namec); namec++, nodenamec++); if (!*namec && !*nodenamec) { if (child) *child = node->child [count]; return 0; } } } else if (name == node->child [count]->name) { if (child) *child = node->child [count]; return 0; } /* Fail */ return CBF_NOTFOUND; } /* Find a child node by name and type */ int cbf_find_typed_child (cbf_node **child, const cbf_node *node, const char *name, CBF_NODETYPE type) { unsigned int count; const char *namec, *nodenamec; /* Follow any links */ node = cbf_get_link (node); /* Check the arguments */ if (!node) return CBF_ARGUMENT; /* Is it a normal node? */ if (node->type == CBF_COLUMN) return CBF_ARGUMENT; /* Search the children */ for (count = 0; count < node->children; count++) { if (name) { if ((node->child [count])->name && (node->child [count])->type == type) { for (namec = name, nodenamec = node->child [count]->name; *namec && toupper (*nodenamec) == toupper (*namec); namec++, nodenamec++); if (!*namec && !*nodenamec) { if (child) *child = node->child [count]; return 0; } } } else { if (name == (node->child [count])->name && (node->child [count])->type == type) { if (child) *child = node->child [count]; return 0; } } } /* Fail */ return CBF_NOTFOUND; } /* Find a child node, accepting the last match */ int cbf_find_last_child (cbf_node **child, const cbf_node *node, const char *name) { int count; const char *namec, *nodenamec; /* Follow any links */ node = cbf_get_link (node); /* Check the arguments */ if (!node) return CBF_ARGUMENT; /* Is it a normal node? */ if (node->type == CBF_COLUMN) return CBF_ARGUMENT; /* Search the children */ for (count = ((int) node->children) - 1; count >= 0; count--) if (name) { if (node->child [count]->name) { for (namec = name, nodenamec = node->child [count]->name; *namec && toupper (*nodenamec) == toupper (*namec); namec++, nodenamec++); if (!*namec && !*nodenamec) { if (child) *child = node->child [count]; return 0; } } } else if (name == node->child [count]->name) { if (child) *child = node->child [count]; return 0; } /* Fail */ return CBF_NOTFOUND; } /* Find a child node by name and type, accepting the last match */ int cbf_find_last_typed_child (cbf_node **child, const cbf_node *node, const char *name, CBF_NODETYPE type) { int count; const char *namec, *nodenamec; /* Follow any links */ node = cbf_get_link (node); /* Check the arguments */ if (!node) return CBF_ARGUMENT; /* Is it a normal node? */ if (node->type == CBF_COLUMN) return CBF_ARGUMENT; /* Search the children */ for (count = ((int) node->children) - 1; count >= 0; count--) if (name) { if (node->child [count]->name) { for (namec = name, nodenamec = node->child [count]->name; *namec && toupper (*nodenamec) == toupper (*namec); namec++, nodenamec++); if (!*namec && !*nodenamec && node->child [count]->type == type) { if (child) *child = node->child [count]; return 0; } } } else if (name == node->child [count]->name && node->child [count]->type == type) { if (child) *child = node->child [count]; return 0; } /* Fail */ return CBF_NOTFOUND; } /* Find a parent node */ int cbf_find_parent (cbf_node **parent, const cbf_node *node, CBF_NODETYPE type) { /* Follow any links */ node = cbf_get_link (node); /* Check the arguments */ if (!node) return CBF_ARGUMENT; /* Find the parent */ while (node) { if (node->type == type) { if (parent) *parent = (cbf_node *) node; return 0; } node = node->parent; } /* Fail */ return CBF_NOTFOUND; } /* Count the number of children */ int cbf_count_children (unsigned int *children, const cbf_node *node) { /* Follow any links */ node = cbf_get_link (node); /* Check the arguments */ if (!children || !node) return CBF_ARGUMENT; /* Success */ *children = node->children; return 0; } /* Count the number of children of a given type */ int cbf_count_typed_children (unsigned int *children, const cbf_node *node, CBF_NODETYPE type) { int i; /* Follow any links */ node = cbf_get_link (node); /* Check the arguments */ if (!children || !node || node->type == CBF_COLUMN) return CBF_ARGUMENT; /* Run through the children */ *children = 0; for (i=0; i < node->children; i++) { if ( (node->child[i])->type == type ) (*children)++; } /* Success */ return 0; } /* Get the index of a child */ int cbf_child_index (unsigned int *index, const cbf_node *node) { cbf_node *parent; unsigned int child; /* Follow any links */ node = cbf_get_link (node); /* Check the arguments */ if (!node) return CBF_ARGUMENT; /* Get the parent */ parent = node->parent; if (!parent) return CBF_NOTFOUND; /* Find the child */ for (child = 0; child < parent->children; child++) if (parent->child [child] == node) { if (index) *index = child; return 0; } /* Fail */ return CBF_NOTFOUND; } /* Get the specified child */ int cbf_get_child (cbf_node **child, const cbf_node *node, unsigned int index) { /* Follow any links */ node = cbf_get_link (node); /* Check the arguments */ if (!node) return CBF_ARGUMENT; /* Is it a normal node? */ if (node->type == CBF_COLUMN) return CBF_ARGUMENT; /* Does the child exists? */ if (index < node->children) { if (child) *child = node->child [index]; return 0; } /* Fail */ return CBF_NOTFOUND; } /* Get the name of a node */ int cbf_get_name (const char **name, cbf_node *node) { /* Follow any links */ node = cbf_get_link (node); /* Check the arguments */ if (!node) return CBF_ARGUMENT; /* Set the name */ if (name) *name = node->name; /* Success */ return 0; } /* All of the following functions assume that all of the strings have been created using cbf_copy_string and that no pointers to the strings are retained by the calling functions */ /* Name a node */ int cbf_name_node (cbf_node *node, const char *name) { /* Follow any links */ node = cbf_get_link (node); /* Check the arguments */ if (!node) return CBF_ARGUMENT; /* Is there a sibling with this name? */ if (node->parent) if (cbf_find_child (NULL, node->parent, name) == 0) return CBF_IDENTICAL; /* Replace the old name */ cbf_free_string (NULL, node->name); node->name = name; /* Success */ return 0; } /* Name a node allowing for duplicates */ int cbf_name_new_node (cbf_node *node, const char *name) { /* Follow any links */ node = cbf_get_link (node); /* Check the arguments */ if (!node) return CBF_ARGUMENT; /* Replace the old name */ cbf_free_string (NULL, node->name); node->name = (char *) name; /* Success */ return 0; } /* Add a child to a node */ int cbf_add_child (cbf_node *node, cbf_node *child) { /* Follow any links */ node = cbf_get_link (node); /* Check the first argument */ if (!node) return CBF_ARGUMENT; /* Follow any links */ child = cbf_get_link (child); /* Check the second argument */ if (!child) return CBF_ARGUMENT; /* Is there already a child with this name? */ if (cbf_find_child (NULL, node, child->name) == 0) return CBF_IDENTICAL; /* Add the child */ cbf_failnez (cbf_set_children (node, node->children + 1)) child->parent = node; node->child [node->children - 1] = child; /* Success */ return 0; } /* Add a child to a node with duplicates allowed */ int cbf_add_new_child (cbf_node *node, cbf_node *child) { /* Follow any links */ node = cbf_get_link (node); /* Check the first argument */ if (!node) return CBF_ARGUMENT; /* Follow any links */ child = cbf_get_link (child); /* Check the second argument */ if (!child) return CBF_ARGUMENT; /* Add the child */ cbf_failnez (cbf_set_children (node, node->children + 1)) child->parent = node; node->child [node->children - 1] = child; /* Success */ return 0; } /* Make a new child node */ int cbf_make_child (cbf_node **child, cbf_node *node, CBF_NODETYPE type, const char *name) { cbf_node *newchild; int errorcode; /* Check the type */ if (type == CBF_LINK) return CBF_ARGUMENT; /* Follow any links */ node = cbf_get_link (node); /* Does the child already exist? */ errorcode = cbf_find_last_typed_child (child, node, name, type); if (errorcode == 0) { cbf_free_string (NULL, name); return 0; } if (errorcode != CBF_NOTFOUND) return errorcode; /* Make a new node */ cbf_failnez (cbf_make_node (&newchild, type, node->context, name)) errorcode = cbf_add_new_child (node, newchild); if (errorcode) { newchild->name = NULL; cbf_free_node (newchild); return errorcode; } /* Success */ if (child) *child = newchild; return 0; } /* Make a new child node, with duplicates allowed */ int cbf_make_new_child (cbf_node **child, cbf_node *node, CBF_NODETYPE type, const char *name) { cbf_node *newchild; int errorcode; /* Check the type */ if (type == CBF_LINK) return CBF_ARGUMENT; /* Follow any links */ node = cbf_get_link (node); /* Make a new node */ cbf_failnez (cbf_make_new_node (&newchild, type, node->context, name)) errorcode = cbf_add_new_child (node, newchild); if (errorcode) { newchild->name = NULL; cbf_free_node (newchild); return errorcode; } /* Success */ if (child) *child = newchild; return 0; } /* Change a link */ int cbf_set_link (cbf_node *link, cbf_node *node) { /* Check the arguments */ if (!link) return CBF_ARGUMENT; /* Check the type */ if (link->type != CBF_LINK) return CBF_ARGUMENT; /* Change the link */ link->link = node; /* Success */ return 0; } /* Add a child link */ int cbf_add_link (cbf_node *link, cbf_node *child) { /* Check the arguments */ if (!link) return CBF_ARGUMENT; /* Check the type */ if (link->type != CBF_LINK) return CBF_ARGUMENT; /* Add the child */ cbf_failnez (cbf_set_children (link, link->children + 1)) link->child [link->children - 1] = child; /* Success */ return 0; } /* Set a link successively to each child link */ int cbf_shift_link (cbf_node *link) { /* Check the arguments */ if (!link) return CBF_ARGUMENT; /* Check the type */ if (link->type != CBF_LINK) return CBF_ARGUMENT; /* Do the children exist? */ if (link->children == 0) return CBF_ARGUMENT; /* Change the link */ link->link = link->child [0]; /* Shift the children */ memmove (link->child, link->child + 1, (link->children - 1) * sizeof (cbf_node *)); link->child [link->children - 1] = link->link; /* Success */ return 0; } /* Set the value of a row */ int cbf_set_columnrow (cbf_node *column, unsigned int row, const char *value, int free) { /* Follow any links */ column = cbf_get_link (column); /* Check the arguments */ if (!column) return CBF_ARGUMENT; /* Check the node type */ if (column->type != CBF_COLUMN) return CBF_ARGUMENT; /* Increase the column size? */ if (row + 1 > column->children) cbf_failnez (cbf_set_children (column, row + 1)) /* Remove the old value */ if (free && column->child [row]) cbf_failnez (cbf_free_value (column->context, column, row)) /* Set the new value */ column->child [row] = (cbf_node *) value; /* Success */ return 0; } /* Get the value of a row */ int cbf_get_columnrow (const char **value, const cbf_node *column, unsigned int row) { /* Follow any links */ column = cbf_get_link (column); /* Check the arguments */ if (!column) return CBF_ARGUMENT; /* Check the node type */ if (column->type != CBF_COLUMN) return CBF_ARGUMENT; /* Is the value in the column? */ if (row + 1 > column->children) return CBF_NOTFOUND; /* Success */ if (value) *value = (const char *) column->child [row]; return 0; } /* Inset a value into a column */ int cbf_insert_columnrow (cbf_node *column, unsigned int row, const char *value) { /* Follow any links */ column = cbf_get_link (column); /* Check the arguments */ if (!column) return CBF_ARGUMENT; if (row > column->children) return CBF_NOTFOUND; /* Increase the column size */ cbf_failnez (cbf_set_children (column, column->children + 1)) /* Move any values further down the column */ if (row < column->children - 1) memmove (column->child + row + 1, column->child + row, sizeof (cbf_node *) * (column->children - row - 1)); /* Set the value */ column->child [row] = (cbf_node *) value; /* Success */ return 0; } /* Delete a row from a column */ int cbf_delete_columnrow (cbf_node *column, unsigned int row) { /* Follow any links */ column = cbf_get_link (column); /* Check the arguments */ if (!column) return CBF_ARGUMENT; if (row >= column->children) return CBF_NOTFOUND; /* Free the value */ cbf_failnez (cbf_set_columnrow (column, row, NULL, 1)) /* Move any values further down the column */ if (row < column->children - 1) memmove (column->child + row, column->child + row + 1, sizeof (cbf_node *) * (column->children - row - 1)); column->child [column->children - 1] = NULL; /* Decrease the column size */ return cbf_set_children (column, column->children - 1); } /* Add a value to a column */ int cbf_add_columnrow (cbf_node *column, const char *value) { /* Follow any links */ column = cbf_get_link (column); /* Check the arguments */ if (!column) return CBF_ARGUMENT; /* Add the value */ return cbf_set_columnrow (column, column->children, value, 1); } /* compute a hash code for a string */ int cbf_compute_hashcode(const char *string, unsigned int *hashcode) { int i; *hashcode = 0; for (i = 0; i>1); } *hashcode &= 255; return 0; } #ifdef __cplusplus } #endif ./CBFlib-0.9.2.2/src/drelc.py0000777000076500007650000000000011603745057017607 2../dREL-ply-0.5/drelc.pyustar yayayaya./CBFlib-0.9.2.2/src/cbff.c0000644000076500007650000077073611603702106013455 0ustar yayayaya/********************************************************************** * cbff -- cbflib C rouitnes for fortran access * * * * Version 0.8.1 1 March 2009 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2009 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term ‘this software’, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifdef __cplusplus extern "C" { #endif #include #include #include "cbf.h" #include "cbf_simple.h" #include "cbff.h" /* Return the bit pattern of a FILE * pointer as a size_t opaque handle */ size_t cbff_file(FILE * file) { return (size_t)file; } /* Return the FILE * pointer for a size_t opaque handle */ FILE * cbff_file_handle(const size_t cbffFile) { return (FILE *)cbffFile; } /* Return the bit pattern of a cbf_handle as a size_t opaque handle */ size_t cbff_handle(cbf_handle cbfHandle) { return (size_t)cbfHandle; } /* Return the cbf_handle for a size_t opaque handle */ cbf_handle cbff_cbf_handle(size_t CBFFhandle) { return (cbf_handle)CBFFhandle; } /* Return the bit pattern of a goniometer as a size_t opaque handle */ size_t cbff_goniometer_handle(cbf_goniometer cbfGoniometer) { return (size_t)cbfGoniometer; } /* Return the goniometer handle for a size_t opaque handle */ cbf_goniometer cbff_cbf_goniometer(size_t CBFFgoniometerhandle) { return (cbf_goniometer)CBFFgoniometerhandle; } /* Return the bit pattern of a detector as a size_t opaque handle */ size_t cbff_detector_handle(cbf_detector cbfDetector) { return (size_t)cbfDetector; } /* Return the detector handle for a size_t opaque handle */ cbf_detector cbff_cbf_detector_handle(size_t CBFFdetector) { return (cbf_detector)CBFFdetector; } /* Return the bit pattern of a node handle as a size_t opaque handle */ size_t cbff_cbf_node(cbf_node * cbfNode) { return (size_t)cbfNode; } /* Return the node handle for a size_t opaque handle */ cbf_node * cbff_cbf_node_handle(size_t cbffNode) { return (cbf_node *)cbffNode; } CBF_NODETYPE cbff_cbf_nodetype(char * str) { CBF_NODETYPE nodetype; if (!strcasecmp(str,"CBF_UNDEFNODE")) { nodetype = CBF_UNDEFNODE; } else if (!strcasecmp(str,"CBF_LINK")) { nodetype = CBF_LINK; } else if (!strcasecmp(str,"CBF_ROOT")) { nodetype = CBF_ROOT; } else if (!strcasecmp(str,"CBF_DATABLOCK")) { nodetype = CBF_DATABLOCK; } else if (!strcasecmp(str,"CBF_SAVEFRAME")) { nodetype = CBF_SAVEFRAME; } else if (!strcasecmp(str,"CBF_CATEGORY")) { nodetype = CBF_CATEGORY; } else if (!strcasecmp(str,"CBF_COLUMN")) { nodetype = CBF_COLUMN; } else if (!strcasecmp(str,"CBF_VALUE")) { nodetype = CBF_VALUE; } else nodetype = CBF_UNDEFNODE; return nodetype; } int cbff_nodetype(CBF_NODETYPE nodetype, char * nodetypestring, int start_nodetypestring, int end_nodetypestring, int * status_nodetypestring) { char rstring[14]; size_t length; size_t index; switch(nodetype) { case CBF_UNDEFNODE: /* Undefined */ strcpy(rstring,"CBF_UNDEFNODE"); break; case CBF_LINK: /* Link */ strcpy(rstring,"CBF_LINK"); break; case CBF_ROOT: /* Root */ strcpy(rstring,"CBF_ROOT"); break; case CBF_DATABLOCK: /* Datablock */ strcpy(rstring,"CBF_DATABLOCK"); break; case CBF_SAVEFRAME: /* Saveframe */ strcpy(rstring,"CBF_SAVEFRAME"); break; case CBF_CATEGORY: /* Category */ strcpy(rstring,"CBF_CATEGORY"); break; case CBF_COLUMN: /* Column */ strcpy(rstring,"CBF_COLUMN"); break; case CBF_VALUE: /* Value */ /* Not a visible node type */ strcpy(rstring,"CBF_UNDEFNODE"); break; default: strcpy(rstring,"CBF_UNDEFNODE"); break; } length = strlen(rstring); for (index = 0; index < length-start_nodetypestring+1 && index < end_nodetypestring-start_nodetypestring+1; index++) { nodetypestring[index] = rstring[index+start_nodetypestring-1]; } if (index < end_nodetypestring-start_nodetypestring+1) { for (; index < end_nodetypestring-start_nodetypestring+1; index++) { nodetypestring[index] = ' '; } *status_nodetypestring = 0; /* transfer complete */ } else { if (length > end_nodetypestring) { *status_nodetypestring = 1; /* more to transfer */ } else { *status_nodetypestring = 0; /* transfer complete */ } } return 0; } /* Return a size_t opaque handle from an fopen */ size_t cbff_fopen(const char * filename, const char * mode) { return cbff_file(fopen(filename,mode)); } int cbff_fclose(const size_t cbffFile) { return fclose(cbff_file_handle(cbffFile)); } /* Create a handle */ int cbff_make_handle(size_t * CBFFhandle) { int errorcode; cbf_handle handle; if (!CBFFhandle) return CBF_ARGUMENT; errorcode = cbf_make_handle(&handle); *CBFFhandle = cbff_handle(handle); return errorcode; } /* Free a handle */ int cbff_free_handle( size_t CBFFhandle){ return cbf_free_handle( cbff_cbf_handle(CBFFhandle)); } /* Read a file */ int cbff_read_file( size_t CBFFhandle, size_t CBFFstream, int flags){ return cbf_read_file( cbff_cbf_handle(CBFFhandle), cbff_file_handle(CBFFstream), flags); } /* Read a wide file */ int cbff_read_widefile( size_t CBFFhandle, size_t CBFFstream, int flags){ return cbf_read_widefile( cbff_cbf_handle(CBFFhandle), cbff_file_handle(CBFFstream), flags); } /* Read a pre-read buffered file */ int cbff_read_buffered_file( size_t CBFFhandle, size_t CBFFstream, int flags, const char * buffer, size_t buffer_len){ return cbf_read_buffered_file( cbff_cbf_handle(CBFFhandle), cbff_file_handle(CBFFstream), flags, buffer, buffer_len); } /* Write a file */ int cbff_write_file( size_t CBFFhandle, size_t CBFFstream, int isbuffer, int ciforcbf, int headers, int encoding){ return cbf_write_file( cbff_cbf_handle(CBFFhandle), cbff_file_handle(CBFFstream), isbuffer, ciforcbf, headers, encoding); } /* Write a file, starting at the local node */ int cbff_write_local_file( size_t CBFFhandle, size_t CBFFstream, int isbuffer, int ciforcbf, int headers, int encoding){ return cbf_write_local_file( cbff_cbf_handle(CBFFhandle), cbff_file_handle(CBFFstream), isbuffer, ciforcbf, headers, encoding); } /* Write a wide file */ int cbff_write_widefile( size_t CBFFhandle, size_t CBFFstream, int isbuffer, int ciforcbf, int headers, int encoding){ return cbf_write_widefile( cbff_cbf_handle(CBFFhandle), cbff_file_handle(CBFFstream), isbuffer, ciforcbf, headers, encoding); } /* Add a data block */ int cbff_new_datablock( size_t CBFFhandle, const char * datablockname){ return cbf_new_datablock( cbff_cbf_handle(CBFFhandle), datablockname); } /* Add a save frame block */ int cbff_new_saveframe( size_t CBFFhandle, const char * saveframename){ return cbf_new_saveframe( cbff_cbf_handle(CBFFhandle), saveframename); } /* Add a data block, allowing for duplicates */ int cbff_force_new_datablock( size_t CBFFhandle, const char * datablockname){ return cbf_force_new_datablock( cbff_cbf_handle(CBFFhandle), datablockname); } /* Add a save frame, allowing for duplicates */ int cbff_force_new_saveframe( size_t CBFFhandle, const char * saveframename){ return cbf_force_new_saveframe( cbff_cbf_handle(CBFFhandle), saveframename); } /* Add a category to the current data block */ int cbff_new_category( size_t CBFFhandle, const char * categoryname){ return cbf_new_category( cbff_cbf_handle(CBFFhandle), categoryname); } /* Add a category to the current data block, allowing for duplicates */ int cbff_force_new_category( size_t CBFFhandle, const char * categoryname){ return cbf_force_new_category( cbff_cbf_handle(CBFFhandle), categoryname); } /* Add a column to the current category */ int cbff_new_column( size_t CBFFhandle, const char * columnname){ return cbf_new_column( cbff_cbf_handle(CBFFhandle), columnname); } /* Add a row to the current category */ int cbff_new_row( size_t CBFFhandle){ return cbf_new_row( cbff_cbf_handle(CBFFhandle)); } /* Insert a row in the current category */ int cbff_insert_row( size_t CBFFhandle, const int rownumber){ return cbf_insert_row( cbff_cbf_handle(CBFFhandle), rownumber); } /* Delete a row from the current category */ int cbff_delete_row( size_t CBFFhandle, const int rownumber){ return cbf_delete_row( cbff_cbf_handle(CBFFhandle), rownumber); } /* Change the name of the current data block */ int cbff_set_datablockname( size_t CBFFhandle, const char * datablockname){ return cbf_set_datablockname( cbff_cbf_handle(CBFFhandle), datablockname); } /* Change the name of the current save frame */ int cbff_set_saveframename( size_t CBFFhandle, const char * saveframename){ return cbf_set_saveframename( cbff_cbf_handle(CBFFhandle), saveframename); } /* Delete all categories from all the data blocks */ int cbff_reset_datablocks( size_t CBFFhandle){ return cbf_reset_datablocks( cbff_cbf_handle(CBFFhandle)); } /* Delete all categories from the current data block */ int cbff_reset_datablock( size_t CBFFhandle){ return cbf_reset_datablock( cbff_cbf_handle(CBFFhandle)); } /* Delete all categories from the current save frame */ int cbff_reset_saveframe( size_t CBFFhandle){ return cbf_reset_saveframe( cbff_cbf_handle(CBFFhandle)); } /* Delete all columns and rows from the current category */ int cbff_reset_category( size_t CBFFhandle){ return cbf_reset_category( cbff_cbf_handle(CBFFhandle)); } /* Delete the current data block */ int cbff_remove_datablock( size_t CBFFhandle){ return cbf_remove_datablock( cbff_cbf_handle(CBFFhandle)); } /* Delete the current save frame */ int cbff_remove_saveframe( size_t CBFFhandle){ return cbf_remove_saveframe( cbff_cbf_handle(CBFFhandle)); } /* Delete the current category */ int cbff_remove_category( size_t CBFFhandle){ return cbf_remove_category( cbff_cbf_handle(CBFFhandle)); } /* Delete the current column */ int cbff_remove_column( size_t CBFFhandle){ return cbf_remove_column( cbff_cbf_handle(CBFFhandle)); } /* Delete the current row */ int cbff_remove_row( size_t CBFFhandle){ return cbf_remove_row( cbff_cbf_handle(CBFFhandle)); } /* Make the first data block the current data block */ int cbff_rewind_datablock( size_t CBFFhandle){ return cbf_rewind_datablock( cbff_cbf_handle(CBFFhandle)); } /* Make the first category in the current data block the current category */ int cbff_rewind_category( size_t CBFFhandle){ return cbf_rewind_category( cbff_cbf_handle(CBFFhandle)); } /* Make the first save frame in the current data block the current category */ int cbff_rewind_saveframe( size_t CBFFhandle){ return cbf_rewind_saveframe( cbff_cbf_handle(CBFFhandle)); } /* Make the first category or save frame in the current data block the current category */ int cbff_rewind_blockitem( size_t CBFFhandle, char * copy_type, size_t start_type, size_t end_type, int * status_type){ CBF_NODETYPE type; int errorcode; errorcode = cbf_rewind_blockitem( cbff_cbf_handle(CBFFhandle), &type); cbff_nodetype (type, copy_type, start_type, end_type, status_type); return errorcode; } /* Make the first column in the current category the current column */ int cbff_rewind_column( size_t CBFFhandle){ return cbf_rewind_column( cbff_cbf_handle(CBFFhandle)); } /* Make the first row in the current category the current row */ int cbff_rewind_row( size_t CBFFhandle){ return cbf_rewind_row( cbff_cbf_handle(CBFFhandle)); } /* Make the next data block the current data block */ int cbff_next_datablock( size_t CBFFhandle){ return cbf_next_datablock( cbff_cbf_handle(CBFFhandle)); } /* Make the next save frame in the current data block the current save frame */ int cbff_next_saveframe( size_t CBFFhandle){ return cbf_next_saveframe( cbff_cbf_handle(CBFFhandle)); } /* Make the next category in the current data block the current category */ int cbff_next_category( size_t CBFFhandle){ return cbf_next_category( cbff_cbf_handle(CBFFhandle)); } /* Make the next save frame or category the current data block or category */ int cbff_next_blockitem( size_t CBFFhandle, char * copy_type, size_t start_type, size_t end_type, int * status_type){ CBF_NODETYPE type; int errorcode; errorcode = cbf_next_blockitem( cbff_cbf_handle(CBFFhandle), &type); cbff_nodetype (type, copy_type, start_type, end_type, status_type); return errorcode; } /* Make the next column in the current category the current column */ int cbff_next_column( size_t CBFFhandle){ return cbf_next_column( cbff_cbf_handle(CBFFhandle)); } /* Make the next row in the current category the current row */ int cbff_next_row( size_t CBFFhandle){ return cbf_next_row( cbff_cbf_handle(CBFFhandle)); } /* Make the named data block the current data block */ int cbff_find_datablock( size_t CBFFhandle, const char * datablockname){ return cbf_find_datablock( cbff_cbf_handle(CBFFhandle), datablockname); } /* Make the named save frame in the current data block the current save frame */ int cbff_find_saveframe( size_t CBFFhandle, const char * saveframe){ return cbf_find_saveframe( cbff_cbf_handle(CBFFhandle), saveframe); } /* Make the named category in the current data block or save frame the current category */ int cbff_find_category( size_t CBFFhandle, const char * categoryname){ return cbf_find_category( cbff_cbf_handle(CBFFhandle), categoryname); } /* Make the named column in the current category the current column */ int cbff_find_column( size_t CBFFhandle, const char * columnname){ return cbf_find_column( cbff_cbf_handle(CBFFhandle), columnname); } /* Make the first row with matching value the current row */ int cbff_find_row( size_t CBFFhandle, const char * value){ return cbf_find_row( cbff_cbf_handle(CBFFhandle), value); } /* Make the first row with matching value the current row creating it if necessary */ int cbff_require_row( size_t CBFFhandle, const char * value){ return cbf_require_row( cbff_cbf_handle(CBFFhandle), value); } /* Make the next row with matching value the current row */ int cbff_find_nextrow( size_t CBFFhandle, const char * value){ return cbf_find_nextrow( cbff_cbf_handle(CBFFhandle), value); } /* Make the next row with matching value the current row, creating the row if necessary */ int cbff_require_nextrow( size_t CBFFhandle, const char * value){ return cbf_require_nextrow( cbff_cbf_handle(CBFFhandle), value); } /* Count the data blocks */ int cbff_count_datablocks( size_t CBFFhandle, unsigned int * datablocks){ return cbf_count_datablocks( cbff_cbf_handle(CBFFhandle), datablocks); } /* Count the save frames in the current data block */ int cbff_count_saveframes( size_t CBFFhandle, unsigned int * saveframes){ return cbf_count_saveframes( cbff_cbf_handle(CBFFhandle), saveframes); } /* Count the categories in the current data block */ int cbff_count_categories( size_t CBFFhandle, unsigned int * categories){ return cbf_count_categories( cbff_cbf_handle(CBFFhandle), categories); } /* Count the items in the current data block */ int cbff_count_blockitems( size_t CBFFhandle, unsigned int * blockitems){ return cbf_count_blockitems( cbff_cbf_handle(CBFFhandle), blockitems); } /* Count the columns in the current category */ int cbff_count_columns( size_t CBFFhandle, unsigned int * columns){ return cbf_count_columns( cbff_cbf_handle(CBFFhandle), columns); } /* Count the rows in the current category */ int cbff_count_rows( size_t CBFFhandle, unsigned int * rows){ return cbf_count_rows( cbff_cbf_handle(CBFFhandle), rows); } /* Make the specified data block the current data block */ int cbff_select_datablock( size_t CBFFhandle, unsigned int datablock){ return cbf_select_datablock( cbff_cbf_handle(CBFFhandle), datablock); } /* Make the specified save frame the current save frame */ int cbff_select_saveframe( size_t CBFFhandle, unsigned int saveframe){ return cbf_select_saveframe( cbff_cbf_handle(CBFFhandle), saveframe); } /* Make the specified category the current category */ int cbff_select_category( size_t CBFFhandle, unsigned int category){ return cbf_select_category( cbff_cbf_handle(CBFFhandle), category); } /* Make the specified category or save frame the current block item */ int cbff_select_blockitem( size_t CBFFhandle, unsigned int item, char * copy_type, size_t start_type, size_t end_type, int * status_type){ CBF_NODETYPE type; int errorcode; errorcode = cbf_select_blockitem( cbff_cbf_handle(CBFFhandle), item, &type); cbff_nodetype (type, copy_type, start_type, end_type, status_type); return errorcode; } /* Make the specified column the current column */ int cbff_select_column( size_t CBFFhandle, unsigned int column){ return cbf_select_column( cbff_cbf_handle(CBFFhandle), column); } /* Make the specified row the current row */ int cbff_select_row( size_t CBFFhandle, unsigned int row){ return cbf_select_row( cbff_cbf_handle(CBFFhandle), row); } /* Get the name of the current data block */ int cbff_datablock_name( size_t CBFFhandle, char * copy_datablockname, size_t start_datablockname, size_t end_datablockname, int * status_datablockname){ const char * datablockname; int index; int length; int errorcode; errorcode = cbf_datablock_name( cbff_cbf_handle(CBFFhandle), &datablockname); if (datablockname) { length = strlen(datablockname); for (index = 0; index < length-start_datablockname+1 && index < end_datablockname-start_datablockname+1; index++) { copy_datablockname[index] = datablockname[index+start_datablockname-1]; } if (index < end_datablockname-start_datablockname+1) { for (; index < end_datablockname-start_datablockname+1; index++) { copy_datablockname[index] = ' '; } *status_datablockname = 0; /* transfer complete */ } else { if (length > end_datablockname) { *status_datablockname = 1; /* more to transfer */ } else { *status_datablockname = 0; /* transfer complete */ } } } else { for (index = 0; index < end_datablockname-start_datablockname+1; index++) { copy_datablockname[index] = ' '; } *status_datablockname = -1; /* null string case */ } return errorcode; } /* Get the name of the current save frame */ int cbff_saveframe_name( size_t CBFFhandle, char * copy_saveframename, size_t start_saveframename, size_t end_saveframename, int * status_saveframename){ const char * saveframename; int index; int length; int errorcode; errorcode = cbf_saveframe_name( cbff_cbf_handle(CBFFhandle), &saveframename); if (saveframename) { length = strlen(saveframename); for (index = 0; index < length-start_saveframename+1 && index < end_saveframename-start_saveframename+1; index++) { copy_saveframename[index] = saveframename[index+start_saveframename-1]; } if (index < end_saveframename-start_saveframename+1) { for (; index < end_saveframename-start_saveframename+1; index++) { copy_saveframename[index] = ' '; } *status_saveframename = 0; /* transfer complete */ } else { if (length > end_saveframename) { *status_saveframename = 1; /* more to transfer */ } else { *status_saveframename = 0; /* transfer complete */ } } } else { for (index = 0; index < end_saveframename-start_saveframename+1; index++) { copy_saveframename[index] = ' '; } *status_saveframename = -1; /* null string case */ } return errorcode; } /* Get the name of the current category */ int cbff_category_name( size_t CBFFhandle, char * copy_categoryname, size_t start_categoryname, size_t end_categoryname, int * status_categoryname){ const char * categoryname; int index; int length; int errorcode; errorcode = cbf_category_name( cbff_cbf_handle(CBFFhandle), &categoryname); if (categoryname) { length = strlen(categoryname); for (index = 0; index < length-start_categoryname+1 && index < end_categoryname-start_categoryname+1; index++) { copy_categoryname[index] = categoryname[index+start_categoryname-1]; } if (index < end_categoryname-start_categoryname+1) { for (; index < end_categoryname-start_categoryname+1; index++) { copy_categoryname[index] = ' '; } *status_categoryname = 0; /* transfer complete */ } else { if (length > end_categoryname) { *status_categoryname = 1; /* more to transfer */ } else { *status_categoryname = 0; /* transfer complete */ } } } else { for (index = 0; index < end_categoryname-start_categoryname+1; index++) { copy_categoryname[index] = ' '; } *status_categoryname = -1; /* null string case */ } return errorcode; } /* Get the name of the current column */ int cbff_column_name( size_t CBFFhandle, char * copy_columnname, size_t start_columnname, size_t end_columnname, int * status_columnname){ const char * columnname; int index; int length; int errorcode; errorcode = cbf_column_name( cbff_cbf_handle(CBFFhandle), &columnname); if (columnname) { length = strlen(columnname); for (index = 0; index < length-start_columnname+1 && index < end_columnname-start_columnname+1; index++) { copy_columnname[index] = columnname[index+start_columnname-1]; } if (index < end_columnname-start_columnname+1) { for (; index < end_columnname-start_columnname+1; index++) { copy_columnname[index] = ' '; } *status_columnname = 0; /* transfer complete */ } else { if (length > end_columnname) { *status_columnname = 1; /* more to transfer */ } else { *status_columnname = 0; /* transfer complete */ } } } else { for (index = 0; index < end_columnname-start_columnname+1; index++) { copy_columnname[index] = ' '; } *status_columnname = -1; /* null string case */ } return errorcode; } /* Get the number of the current row */ int cbff_row_number( size_t CBFFhandle, unsigned int * row){ return cbf_row_number( cbff_cbf_handle(CBFFhandle), row); } /* Get the number of the current column */ int cbff_column_number( size_t CBFFhandle, unsigned int * column){ return cbf_column_number( cbff_cbf_handle(CBFFhandle), column); } /* Get the number of the current block item */ int cbff_blockitem_number( size_t CBFFhandle, unsigned int * blockitem){ return cbf_blockitem_number( cbff_cbf_handle(CBFFhandle), blockitem); } /* Get the ascii value of the current (row, column) entry */ int cbff_get_value( size_t CBFFhandle, char * copy_value, size_t start_value, size_t end_value, int * status_value){ const char * value; int index; int length; int errorcode; errorcode = cbf_get_value( cbff_cbf_handle(CBFFhandle), &value); if (value) { length = strlen(value); for (index = 0; index < length-start_value+1 && index < end_value-start_value+1; index++) { copy_value[index] = value[index+start_value-1]; } if (index < end_value-start_value+1) { for (; index < end_value-start_value+1; index++) { copy_value[index] = ' '; } *status_value = 0; /* transfer complete */ } else { if (length > end_value) { *status_value = 1; /* more to transfer */ } else { *status_value = 0; /* transfer complete */ } } } else { for (index = 0; index < end_value-start_value+1; index++) { copy_value[index] = ' '; } *status_value = -1; /* null string case */ } return errorcode; } /* Set the ascii value of the current (row, column) entry */ int cbff_set_value( size_t CBFFhandle, const char * value){ return cbf_set_value( cbff_cbf_handle(CBFFhandle), value); } /* Get the ascii value of the current (row, column) entry, setting it to a default value if necessary */ int cbff_require_value( size_t CBFFhandle, char * copy_value, size_t start_value, size_t end_value, int * status_value, const char * defaultvalue){ const char * value; int index; int length; int errorcode; errorcode = cbf_require_value( cbff_cbf_handle(CBFFhandle), &value, defaultvalue); if (value) { length = strlen(value); for (index = 0; index < length-start_value+1 && index < end_value-start_value+1; index++) { copy_value[index] = value[index+start_value-1]; } if (index < end_value-start_value+1) { for (; index < end_value-start_value+1; index++) { copy_value[index] = ' '; } *status_value = 0; /* transfer complete */ } else { if (length > end_value) { *status_value = 1; /* more to transfer */ } else { *status_value = 0; /* transfer complete */ } } } else { for (index = 0; index < end_value-start_value+1; index++) { copy_value[index] = ' '; } *status_value = -1; /* null string case */ } return errorcode; } /* Get the ascii type of value of the current (row, column) entry */ int cbff_get_typeofvalue( size_t CBFFhandle, char * copy_typeofvalue, size_t start_typeofvalue, size_t end_typeofvalue, int * status_typeofvalue){ const char * typeofvalue; int index; int length; int errorcode; errorcode = cbf_get_typeofvalue( cbff_cbf_handle(CBFFhandle), &typeofvalue); if (typeofvalue) { length = strlen(typeofvalue); for (index = 0; index < length-start_typeofvalue+1 && index < end_typeofvalue-start_typeofvalue+1; index++) { copy_typeofvalue[index] = typeofvalue[index+start_typeofvalue-1]; } if (index < end_typeofvalue-start_typeofvalue+1) { for (; index < end_typeofvalue-start_typeofvalue+1; index++) { copy_typeofvalue[index] = ' '; } *status_typeofvalue = 0; /* transfer complete */ } else { if (length > end_typeofvalue) { *status_typeofvalue = 1; /* more to transfer */ } else { *status_typeofvalue = 0; /* transfer complete */ } } } else { for (index = 0; index < end_typeofvalue-start_typeofvalue+1; index++) { copy_typeofvalue[index] = ' '; } *status_typeofvalue = -1; /* null string case */ } return errorcode; } /* Set the ascii type of value of the current (row, column) entry */ int cbff_set_typeofvalue( size_t CBFFhandle, const char * typeofvalue){ return cbf_set_typeofvalue( cbff_cbf_handle(CBFFhandle), typeofvalue); } /* Get the (int) numeric value of the current (row, column) entry */ int cbff_get_integervalue( size_t CBFFhandle, int * number){ return cbf_get_integervalue( cbff_cbf_handle(CBFFhandle), number); } /* Get the (double) numeric value of the current (row, column) entry */ int cbff_get_doublevalue( size_t CBFFhandle, double * number){ return cbf_get_doublevalue( cbff_cbf_handle(CBFFhandle), number); } /* Set the ascii value of the current (row, column) entry from an int */ int cbff_set_integervalue( size_t CBFFhandle, int number){ return cbf_set_integervalue( cbff_cbf_handle(CBFFhandle), number); } /* Set the ascii value of the current (row, column) entry from a double */ int cbff_set_doublevalue( size_t CBFFhandle, const char * format, double number){ return cbf_set_doublevalue( cbff_cbf_handle(CBFFhandle), format, number); } /* Get the (integer) numeric value of the current (row, column) entry, setting it if necessary */ int cbff_require_integervalue( size_t CBFFhandle, int * number, int defaultvalue){ return cbf_require_integervalue( cbff_cbf_handle(CBFFhandle), number, defaultvalue); } /* Get the (double) numeric value of the current (row, column) entry, setting it if necessary */ int cbff_require_doublevalue( size_t CBFFhandle, double * number, double defaultvalue){ return cbf_require_doublevalue( cbff_cbf_handle(CBFFhandle), number, defaultvalue); } /* Get the parameters of the current (row, column) array entry */ int cbff_get_arrayparameters( size_t CBFFhandle, unsigned int * compression, int * id, size_t * elsize, int * elsigned, int * elunsigned, size_t * nelem, int * minelem, int * maxelem, int * realarray){ return cbf_get_arrayparameters( cbff_cbf_handle(CBFFhandle), compression, id, elsize, elsigned, elunsigned, nelem, minelem, maxelem, realarray); } /* Get the parameters of the current (row, column) array entry */ int cbff_get_arrayparameters_wdims( size_t CBFFhandle, unsigned int * compression, int * id, size_t * elsize, int * elsigned, int * elunsigned, size_t * nelem, int * minelem, int * maxelem, int * realarray, char * copy_byteorder, size_t start_byteorder, size_t end_byteorder, int * status_byteorder, size_t * dimfast, size_t * dimmid, size_t * dimslow, size_t * padding){ const char * byteorder; int index; int length; int errorcode; errorcode = cbf_get_arrayparameters_wdims( cbff_cbf_handle(CBFFhandle), compression, id, elsize, elsigned, elunsigned, nelem, minelem, maxelem, realarray, &byteorder, dimfast, dimmid, dimslow, padding); if (byteorder) { length = strlen(byteorder); for (index = 0; index < length-start_byteorder+1 && index < end_byteorder-start_byteorder+1; index++) { copy_byteorder[index] = byteorder[index+start_byteorder-1]; } if (index < end_byteorder-start_byteorder+1) { for (; index < end_byteorder-start_byteorder+1; index++) { copy_byteorder[index] = ' '; } *status_byteorder = 0; /* transfer complete */ } else { if (length > end_byteorder) { *status_byteorder = 1; /* more to transfer */ } else { *status_byteorder = 0; /* transfer complete */ } } } else { for (index = 0; index < end_byteorder-start_byteorder+1; index++) { copy_byteorder[index] = ' '; } *status_byteorder = -1; /* null string case */ } return errorcode; } int cbff_get_arrayparameters_wdims_fs( size_t CBFFhandle, unsigned int * compression, int * id, size_t * elsize, int * elsigned, int * elunsigned, size_t * nelem, int * minelem, int * maxelem, int * realarray, char * copy_byteorder, size_t start_byteorder, size_t end_byteorder, int * status_byteorder, size_t * dimfast, size_t * dimmid, size_t * dimslow, size_t * padding){ const char * byteorder; int index; int length; int errorcode; errorcode = cbf_get_arrayparameters_wdims( cbff_cbf_handle(CBFFhandle), compression, id, elsize, elsigned, elunsigned, nelem, minelem, maxelem, realarray, &byteorder, dimfast, dimmid, dimslow, padding); if (byteorder) { length = strlen(byteorder); for (index = 0; index < length-start_byteorder+1 && index < end_byteorder-start_byteorder+1; index++) { copy_byteorder[index] = byteorder[index+start_byteorder-1]; } if (index < end_byteorder-start_byteorder+1) { for (; index < end_byteorder-start_byteorder+1; index++) { copy_byteorder[index] = ' '; } *status_byteorder = 0; /* transfer complete */ } else { if (length > end_byteorder) { *status_byteorder = 1; /* more to transfer */ } else { *status_byteorder = 0; /* transfer complete */ } } } else { for (index = 0; index < end_byteorder-start_byteorder+1; index++) { copy_byteorder[index] = ' '; } *status_byteorder = -1; /* null string case */ } return errorcode; } int cbff_get_arrayparameters_wdims_sf( size_t CBFFhandle, unsigned int * compression, int * id, size_t * elsize, int * elsigned, int * elunsigned, size_t * nelem, int * minelem, int * maxelem, int * realarray, char * copy_byteorder, size_t start_byteorder, size_t end_byteorder, int * status_byteorder, size_t * dimslow, size_t * dimmid, size_t * dimfast, size_t * padding){ const char * byteorder; int index; int length; int errorcode; errorcode = cbf_get_arrayparameters_wdims( cbff_cbf_handle(CBFFhandle), compression, id, elsize, elsigned, elunsigned, nelem, minelem, maxelem, realarray, &byteorder, dimfast, dimmid, dimslow, padding); if (byteorder) { length = strlen(byteorder); for (index = 0; index < length-start_byteorder+1 && index < end_byteorder-start_byteorder+1; index++) { copy_byteorder[index] = byteorder[index+start_byteorder-1]; } if (index < end_byteorder-start_byteorder+1) { for (; index < end_byteorder-start_byteorder+1; index++) { copy_byteorder[index] = ' '; } *status_byteorder = 0; /* transfer complete */ } else { if (length > end_byteorder) { *status_byteorder = 1; /* more to transfer */ } else { *status_byteorder = 0; /* transfer complete */ } } } else { for (index = 0; index < end_byteorder-start_byteorder+1; index++) { copy_byteorder[index] = ' '; } *status_byteorder = -1; /* null string case */ } return errorcode; } /* Get the dimensions of the current (row, column) array entry from the CBF tags */ int cbff_get_arraydimensions(size_t CBFFhandle, size_t * dimover, size_t * dimfast, size_t * dimmid, size_t * dimslow) { return cbf_get_arraydimensions(cbff_cbf_handle(CBFFhandle), dimover, dimfast, dimmid, dimslow); } /* Get the parameters of the current (row, column) integer array entry */ int cbff_get_integerarrayparameters( size_t CBFFhandle, unsigned int * compression, int * id, size_t * elsize, int * elsigned, int * elunsigned, size_t * nelem, int * minelem, int * maxelem){ return cbf_get_integerarrayparameters( cbff_cbf_handle(CBFFhandle), compression, id, elsize, elsigned, elunsigned, nelem, minelem, maxelem); } /* Get the parameters of the current (row, column) integer array entry */ int cbff_get_integerarrayparameters_wdims( size_t CBFFhandle, unsigned int * compression, int * id, size_t * elsize, int * elsigned, int * elunsigned, size_t * nelem, int * minelem, int * maxelem, char * copy_byteorder, size_t start_byteorder, size_t end_byteorder, int * status_byteorder, size_t * dimfast, size_t * dimmid, size_t * dimslow, size_t * padding){ const char * byteorder; int index; int length; int errorcode; errorcode = cbf_get_integerarrayparameters_wdims( cbff_cbf_handle(CBFFhandle), compression, id, elsize, elsigned, elunsigned, nelem, minelem, maxelem, &byteorder, dimfast, dimmid, dimslow, padding); if (byteorder) { length = strlen(byteorder); for (index = 0; index < length-start_byteorder+1 && index < end_byteorder-start_byteorder+1; index++) { copy_byteorder[index] = byteorder[index+start_byteorder-1]; } if (index < end_byteorder-start_byteorder+1) { for (; index < end_byteorder-start_byteorder+1; index++) { copy_byteorder[index] = ' '; } *status_byteorder = 0; /* transfer complete */ } else { if (length > end_byteorder) { *status_byteorder = 1; /* more to transfer */ } else { *status_byteorder = 0; /* transfer complete */ } } } else { for (index = 0; index < end_byteorder-start_byteorder+1; index++) { copy_byteorder[index] = ' '; } *status_byteorder = -1; /* null string case */ } return errorcode; } int cbff_get_integerarrayparameters_wdims_fs( size_t CBFFhandle, unsigned int * compression, int * id, size_t * elsize, int * elsigned, int * elunsigned, size_t * nelem, int * minelem, int * maxelem, char * copy_byteorder, size_t start_byteorder, size_t end_byteorder, int * status_byteorder, size_t * dimfast, size_t * dimmid, size_t * dimslow, size_t * padding){ const char * byteorder; int index; int length; int errorcode; errorcode = cbf_get_integerarrayparameters_wdims( cbff_cbf_handle(CBFFhandle), compression, id, elsize, elsigned, elunsigned, nelem, minelem, maxelem, &byteorder, dimfast, dimmid, dimslow, padding); if (byteorder) { length = strlen(byteorder); for (index = 0; index < length-start_byteorder+1 && index < end_byteorder-start_byteorder+1; index++) { copy_byteorder[index] = byteorder[index+start_byteorder-1]; } if (index < end_byteorder-start_byteorder+1) { for (; index < end_byteorder-start_byteorder+1; index++) { copy_byteorder[index] = ' '; } *status_byteorder = 0; /* transfer complete */ } else { if (length > end_byteorder) { *status_byteorder = 1; /* more to transfer */ } else { *status_byteorder = 0; /* transfer complete */ } } } else { for (index = 0; index < end_byteorder-start_byteorder+1; index++) { copy_byteorder[index] = ' '; } *status_byteorder = -1; /* null string case */ } return errorcode; } int cbff_get_integerarrayparameters_wdims_sf( size_t CBFFhandle, unsigned int * compression, int * id, size_t * elsize, int * elsigned, int * elunsigned, size_t * nelem, int * minelem, int * maxelem, char * copy_byteorder, size_t start_byteorder, size_t end_byteorder, int * status_byteorder, size_t * dimslow, size_t * dimmid, size_t * dimfast, size_t * padding){ const char * byteorder; int index; int length; int errorcode; errorcode = cbf_get_integerarrayparameters_wdims( cbff_cbf_handle(CBFFhandle), compression, id, elsize, elsigned, elunsigned, nelem, minelem, maxelem, &byteorder, dimfast, dimmid, dimslow, padding); if (byteorder) { length = strlen(byteorder); for (index = 0; index < length-start_byteorder+1 && index < end_byteorder-start_byteorder+1; index++) { copy_byteorder[index] = byteorder[index+start_byteorder-1]; } if (index < end_byteorder-start_byteorder+1) { for (; index < end_byteorder-start_byteorder+1; index++) { copy_byteorder[index] = ' '; } *status_byteorder = 0; /* transfer complete */ } else { if (length > end_byteorder) { *status_byteorder = 1; /* more to transfer */ } else { *status_byteorder = 0; /* transfer complete */ } } } else { for (index = 0; index < end_byteorder-start_byteorder+1; index++) { copy_byteorder[index] = ' '; } *status_byteorder = -1; /* null string case */ } return errorcode; } /* Get the integer value of the current (row, column) array entry */ int cbff_get_integerarray( size_t CBFFhandle, int * id, void * value, size_t elsize, int elsign, size_t nelem, size_t * nelem_read){ return cbf_get_integerarray( cbff_cbf_handle(CBFFhandle), id, value, elsize, elsign, nelem, nelem_read); } /* Get the real value of the current (row, column) array entry */ int cbff_get_realarray( size_t CBFFhandle, int * id, void * value, size_t elsize, size_t nelem, size_t * nelem_read){ return cbf_get_realarray( cbff_cbf_handle(CBFFhandle), id, value, elsize, nelem, nelem_read); } /* Get the parameters of the current (row, column) array entry */ int cbff_get_realarrayparameters( size_t CBFFhandle, unsigned int * compression, int * id, size_t * elsize, size_t * nelem){ return cbf_get_realarrayparameters( cbff_cbf_handle(CBFFhandle), compression, id, elsize, nelem); } /* Get the parameters of the current (row, column) array entry */ int cbff_get_realarrayparameters_wdims( size_t CBFFhandle, unsigned int * compression, int * id, size_t * elsize, size_t * nelem, char * copy_byteorder, size_t start_byteorder, size_t end_byteorder, int * status_byteorder, size_t * dimfast, size_t * dimmid, size_t * dimslow, size_t * padding){ const char * byteorder; int index; int length; int errorcode; errorcode = cbf_get_realarrayparameters_wdims( cbff_cbf_handle(CBFFhandle), compression, id, elsize, nelem, &byteorder, dimfast, dimmid, dimslow, padding); if (byteorder) { length = strlen(byteorder); for (index = 0; index < length-start_byteorder+1 && index < end_byteorder-start_byteorder+1; index++) { copy_byteorder[index] = byteorder[index+start_byteorder-1]; } if (index < end_byteorder-start_byteorder+1) { for (; index < end_byteorder-start_byteorder+1; index++) { copy_byteorder[index] = ' '; } *status_byteorder = 0; /* transfer complete */ } else { if (length > end_byteorder) { *status_byteorder = 1; /* more to transfer */ } else { *status_byteorder = 0; /* transfer complete */ } } } else { for (index = 0; index < end_byteorder-start_byteorder+1; index++) { copy_byteorder[index] = ' '; } *status_byteorder = -1; /* null string case */ } return errorcode; } int cbff_get_realarrayparameters_wdims_fs( size_t CBFFhandle, unsigned int * compression, int * id, size_t * elsize, size_t * nelem, char * copy_byteorder, size_t start_byteorder, size_t end_byteorder, int * status_byteorder, size_t * dimfast, size_t * dimmid, size_t * dimslow, size_t * padding){ const char * byteorder; int index; int length; int errorcode; errorcode = cbf_get_realarrayparameters_wdims( cbff_cbf_handle(CBFFhandle), compression, id, elsize, nelem, &byteorder, dimfast, dimmid, dimslow, padding); if (byteorder) { length = strlen(byteorder); for (index = 0; index < length-start_byteorder+1 && index < end_byteorder-start_byteorder+1; index++) { copy_byteorder[index] = byteorder[index+start_byteorder-1]; } if (index < end_byteorder-start_byteorder+1) { for (; index < end_byteorder-start_byteorder+1; index++) { copy_byteorder[index] = ' '; } *status_byteorder = 0; /* transfer complete */ } else { if (length > end_byteorder) { *status_byteorder = 1; /* more to transfer */ } else { *status_byteorder = 0; /* transfer complete */ } } } else { for (index = 0; index < end_byteorder-start_byteorder+1; index++) { copy_byteorder[index] = ' '; } *status_byteorder = -1; /* null string case */ } return errorcode; } int cbff_get_realarrayparameters_wdims_sf( size_t CBFFhandle, unsigned int * compression, int * id, size_t * elsize, size_t * nelem, char * copy_byteorder, size_t start_byteorder, size_t end_byteorder, int * status_byteorder, size_t * dimslow, size_t * dimmid, size_t * dimfast, size_t * padding){ const char * byteorder; int index; int length; int errorcode; errorcode = cbf_get_realarrayparameters_wdims( cbff_cbf_handle(CBFFhandle), compression, id, elsize, nelem, &byteorder, dimfast, dimmid, dimslow, padding); if (byteorder) { length = strlen(byteorder); for (index = 0; index < length-start_byteorder+1 && index < end_byteorder-start_byteorder+1; index++) { copy_byteorder[index] = byteorder[index+start_byteorder-1]; } if (index < end_byteorder-start_byteorder+1) { for (; index < end_byteorder-start_byteorder+1; index++) { copy_byteorder[index] = ' '; } *status_byteorder = 0; /* transfer complete */ } else { if (length > end_byteorder) { *status_byteorder = 1; /* more to transfer */ } else { *status_byteorder = 0; /* transfer complete */ } } } else { for (index = 0; index < end_byteorder-start_byteorder+1; index++) { copy_byteorder[index] = ' '; } *status_byteorder = -1; /* null string case */ } return errorcode; } /* Set the integer value of the current (row, column) array entry */ int cbff_set_integerarray( size_t CBFFhandle, unsigned int compression, int id, void * value, size_t elsize, int elsign, size_t nelem){ return cbf_set_integerarray( cbff_cbf_handle(CBFFhandle), compression, id, value, elsize, elsign, nelem); } /* Set the integer value of the current (row, column) array entry */ int cbff_set_integerarray_wdims( size_t CBFFhandle, unsigned int compression, int id, void * value, size_t elsize, int elsign, size_t nelem, const char * byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding){ return cbf_set_integerarray_wdims( cbff_cbf_handle(CBFFhandle), compression, id, value, elsize, elsign, nelem, byteorder, dimfast, dimmid, dimslow, padding); } int cbff_set_integerarray_wdims_fs( size_t CBFFhandle, unsigned int compression, int id, void * value, size_t elsize, int elsign, size_t nelem, const char * byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding){ return cbf_set_integerarray_wdims( cbff_cbf_handle(CBFFhandle), compression, id, value, elsize, elsign, nelem, byteorder, dimfast, dimmid, dimslow, padding); } int cbff_set_integerarray_wdims_sf( size_t CBFFhandle, unsigned int compression, int id, void * value, size_t elsize, int elsign, size_t nelem, const char * byteorder, size_t dimslow, size_t dimmid, size_t dimfast, size_t padding){ return cbf_set_integerarray_wdims( cbff_cbf_handle(CBFFhandle), compression, id, value, elsize, elsign, nelem, byteorder, dimfast, dimmid, dimslow, padding); } /* Set the real value of the current (row, column) array entry */ int cbff_set_realarray( size_t CBFFhandle, unsigned int compression, int id, void * value, size_t elsize, size_t nelem){ return cbf_set_realarray( cbff_cbf_handle(CBFFhandle), compression, id, value, elsize, nelem); } /* Set the real value of the current (row, column) array entry with dimensions */ int cbff_set_realarray_wdims( size_t CBFFhandle, unsigned int compression, int id, void * value, size_t elsize, size_t nelem, const char * byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding){ return cbf_set_realarray_wdims( cbff_cbf_handle(CBFFhandle), compression, id, value, elsize, nelem, byteorder, dimfast, dimmid, dimslow, padding); } int cbff_set_realarray_wdims_fs( size_t CBFFhandle, unsigned int compression, int id, void * value, size_t elsize, size_t nelem, const char * byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding){ return cbf_set_realarray_wdims( cbff_cbf_handle(CBFFhandle), compression, id, value, elsize, nelem, byteorder, dimfast, dimmid, dimslow, padding); } int cbff_set_realarray_wdims_sf( size_t CBFFhandle, unsigned int compression, int id, void * value, size_t elsize, size_t nelem, const char * byteorder, size_t dimslow, size_t dimmid, size_t dimfast, size_t padding){ return cbf_set_realarray_wdims( cbff_cbf_handle(CBFFhandle), compression, id, value, elsize, nelem, byteorder, dimfast, dimmid, dimslow, padding); } /* Issue a warning message */ void cbff_warning (const char *message) { cbf_warning(message); } /* Issue an error message */ void cbff_error (const char *message) { cbf_error(message); } /* issue a log message for a cbf */ void cbff_log (size_t CBFFhandle, const char *message, int logflags) { cbf_log(cbff_cbf_handle(CBFFhandle), message, logflags); } /* Find a datablock, creating it if necessary */ int cbff_require_datablock( size_t CBFFhandle, const char * datablockname){ return cbf_require_datablock( cbff_cbf_handle(CBFFhandle), datablockname); } /* Find a category, creating it if necessary */ int cbff_require_category( size_t CBFFhandle, const char * categoryname){ return cbf_require_category( cbff_cbf_handle(CBFFhandle), categoryname); } /* Find a column, creating it if necessary */ int cbff_require_column( size_t CBFFhandle, const char * columnname){ return cbf_require_column( cbff_cbf_handle(CBFFhandle), columnname); } /* Find a column value, return a default if necessary */ int cbff_require_column_value( size_t CBFFhandle, const char * columnname, char * copy_value, size_t start_value, size_t end_value, int * status_value, const char * defaultvalue){ const char * value; int index; int length; int errorcode; errorcode = cbf_require_column_value( cbff_cbf_handle(CBFFhandle), columnname, &value, defaultvalue); if (value) { length = strlen(value); for (index = 0; index < length-start_value+1 && index < end_value-start_value+1; index++) { copy_value[index] = value[index+start_value-1]; } if (index < end_value-start_value+1) { for (; index < end_value-start_value+1; index++) { copy_value[index] = ' '; } *status_value = 0; /* transfer complete */ } else { if (length > end_value) { *status_value = 1; /* more to transfer */ } else { *status_value = 0; /* transfer complete */ } } } else { for (index = 0; index < end_value-start_value+1; index++) { copy_value[index] = ' '; } *status_value = -1; /* null string case */ } return errorcode; } /* Find a column integer value, return a default if necessary */ int cbff_require_column_integervalue( size_t CBFFhandle, const char * columnname, int * number, const int defaultvalue){ return cbf_require_column_integervalue( cbff_cbf_handle(CBFFhandle), columnname, number, defaultvalue); } /* Find a column double value, return a default if necessary */ int cbff_require_column_doublevalue( size_t CBFFhandle, const char * columnname, double * number, const double defaultvalue){ return cbf_require_column_doublevalue( cbff_cbf_handle(CBFFhandle), columnname, number, defaultvalue); } /* Get the local byte order of the default integer type */ int cbff_get_local_integer_byte_order( char * copy_byte_order, size_t start_byte_order, size_t end_byte_order, int * status_byte_order){ char * byte_order; int index; int length; int errorcode; errorcode = cbf_get_local_integer_byte_order( &byte_order); if (byte_order) { length = strlen(byte_order); for (index = 0; index < length-start_byte_order+1 && index < end_byte_order-start_byte_order+1; index++) { copy_byte_order[index] = byte_order[index+start_byte_order-1]; } if (index < end_byte_order-start_byte_order+1) { for (; index < end_byte_order-start_byte_order+1; index++) { copy_byte_order[index] = ' '; } *status_byte_order = 0; /* transfer complete */ } else { if (length > end_byte_order) { *status_byte_order = 1; /* more to transfer */ } else { *status_byte_order = 0; /* transfer complete */ } } } else { for (index = 0; index < end_byte_order-start_byte_order+1; index++) { copy_byte_order[index] = ' '; } *status_byte_order = -1; /* null string case */ } return errorcode; } /* Get the local byte order of the default real type */ int cbff_get_local_real_byte_order( char * copy_byte_order, size_t start_byte_order, size_t end_byte_order, int * status_byte_order){ char * byte_order; int index; int length; int errorcode; errorcode = cbf_get_local_real_byte_order( &byte_order); if (byte_order) { length = strlen(byte_order); for (index = 0; index < length-start_byte_order+1 && index < end_byte_order-start_byte_order+1; index++) { copy_byte_order[index] = byte_order[index+start_byte_order-1]; } if (index < end_byte_order-start_byte_order+1) { for (; index < end_byte_order-start_byte_order+1; index++) { copy_byte_order[index] = ' '; } *status_byte_order = 0; /* transfer complete */ } else { if (length > end_byte_order) { *status_byte_order = 1; /* more to transfer */ } else { *status_byte_order = 0; /* transfer complete */ } } } else { for (index = 0; index < end_byte_order-start_byte_order+1; index++) { copy_byte_order[index] = ' '; } *status_byte_order = -1; /* null string case */ } return errorcode; } /* Get the local real format */ int cbff_get_local_real_format( char * copy_real_format, size_t start_real_format, size_t end_real_format, int * status_real_format){ char * real_format; int index; int length; int errorcode; errorcode = cbf_get_local_real_format( &real_format); if (real_format) { length = strlen(real_format); for (index = 0; index < length-start_real_format+1 && index < end_real_format-start_real_format+1; index++) { copy_real_format[index] = real_format[index+start_real_format-1]; } if (index < end_real_format-start_real_format+1) { for (; index < end_real_format-start_real_format+1; index++) { copy_real_format[index] = ' '; } *status_real_format = 0; /* transfer complete */ } else { if (length > end_real_format) { *status_real_format = 1; /* more to transfer */ } else { *status_real_format = 0; /* transfer complete */ } } } else { for (index = 0; index < end_real_format-start_real_format+1; index++) { copy_real_format[index] = ' '; } *status_real_format = -1; /* null string case */ } return errorcode; } /* Get the dictionary for a cbf */ int cbff_get_dictionary( size_t CBFFhandle, size_t * CBFFdictionary){ cbf_handle dictionary; int errorcode; errorcode = cbf_get_dictionary( cbff_cbf_handle(CBFFhandle), &dictionary); *CBFFdictionary = cbff_handle(dictionary); return errorcode; } /* Set the dictionary for a cbf */ int cbff_set_dictionary( size_t CBFFhandle, size_t CBFFdictionary){ return cbf_set_dictionary( cbff_cbf_handle(CBFFhandle), cbff_cbf_handle(CBFFdictionary)); } /* Get the dictionary for a cbf, or create one */ int cbff_require_dictionary( size_t CBFFhandle, size_t * CBFFdictionary){ cbf_handle dictionary; int errorcode; errorcode = cbf_require_dictionary( cbff_cbf_handle(CBFFhandle), &dictionary); *CBFFdictionary = cbff_handle(dictionary); return errorcode; } /* Put the value into the named column, updating the hash table links */ int cbff_set_hashedvalue( size_t CBFFhandle, const char * value, const char * columnname, int valuerow){ return cbf_set_hashedvalue( cbff_cbf_handle(CBFFhandle), value, columnname, valuerow); } /* Find value in the named column, using the hash table links */ int cbff_find_hashedvalue( size_t CBFFhandle, const char * value, const char * columnname, int caseinsensitive){ return cbf_find_hashedvalue( cbff_cbf_handle(CBFFhandle), value, columnname, caseinsensitive); } /* Take a definition from a dictionary and insert it into the hash tables of a cbf dictionary */ int cbff_convert_dictionary_definition( size_t CBFFcbfdictionary, size_t CBFFdictionary, const char * name){ return cbf_convert_dictionary_definition( cbff_cbf_handle(CBFFcbfdictionary), cbff_cbf_handle(CBFFdictionary), name); } /* Increment a column */ int cbff_increment_column( size_t CBFFhandle, const char* columnname, int * count){ return cbf_increment_column( cbff_cbf_handle(CBFFhandle), columnname, count); } /* Reset a column */ int cbff_reset_column( size_t CBFFhandle, const char* columnname){ return cbf_reset_column( cbff_cbf_handle(CBFFhandle), columnname); } /* Reset reference counts for a dictionary */ int cbff_reset_refcounts( size_t CBFFdictionary){ return cbf_reset_refcounts( cbff_cbf_handle(CBFFdictionary)); } /* Convert a DDL1 or DDL2 dictionary and add it to a CBF dictionary */ int cbff_convert_dictionary( size_t CBFFhandle, size_t CBFFdictionary){ return cbf_convert_dictionary( cbff_cbf_handle(CBFFhandle), cbff_cbf_handle(CBFFdictionary)); } /* Find the requested tag anywhere in the cbf, make it the current column */ int cbff_find_tag( size_t CBFFhandle, const char * tag){ return cbf_find_tag( cbff_cbf_handle(CBFFhandle), tag); } /* Find the requested tag in the cbf within the current save frame or data block, make it the current column */ int cbff_find_local_tag( size_t CBFFhandle, const char * tag){ return cbf_find_local_tag( cbff_cbf_handle(CBFFhandle), tag); } /* Find the requested category and column anywhere in the cbf, make it the current column */ int cbff_srch_tag( size_t CBFFhandle, size_t CBFFnode, const char * categoryname, const char * columnname){ return cbf_srch_tag( cbff_cbf_handle(CBFFhandle), cbff_cbf_node_handle(CBFFnode), categoryname, columnname); } /* Find the root alias of a given category */ int cbff_find_category_root( size_t CBFFhandle, const char* categoryname, char * copy_categoryroot, size_t start_categoryroot, size_t end_categoryroot, int * status_categoryroot){ const char * categoryroot; int index; int length; int errorcode; errorcode = cbf_find_category_root( cbff_cbf_handle(CBFFhandle), categoryname, &categoryroot); if (categoryroot) { length = strlen(categoryroot); for (index = 0; index < length-start_categoryroot+1 && index < end_categoryroot-start_categoryroot+1; index++) { copy_categoryroot[index] = categoryroot[index+start_categoryroot-1]; } if (index < end_categoryroot-start_categoryroot+1) { for (; index < end_categoryroot-start_categoryroot+1; index++) { copy_categoryroot[index] = ' '; } *status_categoryroot = 0; /* transfer complete */ } else { if (length > end_categoryroot) { *status_categoryroot = 1; /* more to transfer */ } else { *status_categoryroot = 0; /* transfer complete */ } } } else { for (index = 0; index < end_categoryroot-start_categoryroot+1; index++) { copy_categoryroot[index] = ' '; } *status_categoryroot = -1; /* null string case */ } return errorcode; } /* Find the root alias of a given category, defaulting to the current one */ int cbff_require_category_root( size_t CBFFhandle, const char* categoryname, char * copy_categoryroot, size_t start_categoryroot, size_t end_categoryroot, int * status_categoryroot){ const char * categoryroot; int index; int length; int errorcode; errorcode = cbf_require_category_root( cbff_cbf_handle(CBFFhandle), categoryname, &categoryroot); if (categoryroot) { length = strlen(categoryroot); for (index = 0; index < length-start_categoryroot+1 && index < end_categoryroot-start_categoryroot+1; index++) { copy_categoryroot[index] = categoryroot[index+start_categoryroot-1]; } if (index < end_categoryroot-start_categoryroot+1) { for (; index < end_categoryroot-start_categoryroot+1; index++) { copy_categoryroot[index] = ' '; } *status_categoryroot = 0; /* transfer complete */ } else { if (length > end_categoryroot) { *status_categoryroot = 1; /* more to transfer */ } else { *status_categoryroot = 0; /* transfer complete */ } } } else { for (index = 0; index < end_categoryroot-start_categoryroot+1; index++) { copy_categoryroot[index] = ' '; } *status_categoryroot = -1; /* null string case */ } return errorcode; } /* Set the root alias of a given category */ int cbff_set_category_root( size_t CBFFhandle, const char* categoryname, const char* categoryroot){ return cbf_set_category_root( cbff_cbf_handle(CBFFhandle), categoryname, categoryroot); } /* Find the root alias of a given tag */ int cbff_find_tag_root( size_t CBFFhandle, const char* tagname, char * copy_tagroot, size_t start_tagroot, size_t end_tagroot, int * status_tagroot){ const char * tagroot; int index; int length; int errorcode; errorcode = cbf_find_tag_root( cbff_cbf_handle(CBFFhandle), tagname, &tagroot); if (tagroot) { length = strlen(tagroot); for (index = 0; index < length-start_tagroot+1 && index < end_tagroot-start_tagroot+1; index++) { copy_tagroot[index] = tagroot[index+start_tagroot-1]; } if (index < end_tagroot-start_tagroot+1) { for (; index < end_tagroot-start_tagroot+1; index++) { copy_tagroot[index] = ' '; } *status_tagroot = 0; /* transfer complete */ } else { if (length > end_tagroot) { *status_tagroot = 1; /* more to transfer */ } else { *status_tagroot = 0; /* transfer complete */ } } } else { for (index = 0; index < end_tagroot-start_tagroot+1; index++) { copy_tagroot[index] = ' '; } *status_tagroot = -1; /* null string case */ } return errorcode; } /* Find the root alias of a given tag, defaulting to the current one */ int cbff_require_tag_root( size_t CBFFhandle, const char* tagname, char * copy_tagroot, size_t start_tagroot, size_t end_tagroot, int * status_tagroot){ const char * tagroot; int index; int length; int errorcode; errorcode = cbf_require_tag_root( cbff_cbf_handle(CBFFhandle), tagname, &tagroot); if (tagroot) { length = strlen(tagroot); for (index = 0; index < length-start_tagroot+1 && index < end_tagroot-start_tagroot+1; index++) { copy_tagroot[index] = tagroot[index+start_tagroot-1]; } if (index < end_tagroot-start_tagroot+1) { for (; index < end_tagroot-start_tagroot+1; index++) { copy_tagroot[index] = ' '; } *status_tagroot = 0; /* transfer complete */ } else { if (length > end_tagroot) { *status_tagroot = 1; /* more to transfer */ } else { *status_tagroot = 0; /* transfer complete */ } } } else { for (index = 0; index < end_tagroot-start_tagroot+1; index++) { copy_tagroot[index] = ' '; } *status_tagroot = -1; /* null string case */ } return errorcode; } /* Set the root alias of a given tag */ int cbff_set_tag_root( size_t CBFFhandle, const char* tagname, const char* tagroot){ return cbf_set_tag_root( cbff_cbf_handle(CBFFhandle), tagname, tagroot); } /* Find the category of a given tag */ int cbff_find_tag_category( size_t CBFFhandle, const char* tagname, char * copy_categoryname, size_t start_categoryname, size_t end_categoryname, int * status_categoryname){ const char * categoryname; int index; int length; int errorcode; errorcode = cbf_find_tag_category( cbff_cbf_handle(CBFFhandle), tagname, &categoryname); if (categoryname) { length = strlen(categoryname); for (index = 0; index < length-start_categoryname+1 && index < end_categoryname-start_categoryname+1; index++) { copy_categoryname[index] = categoryname[index+start_categoryname-1]; } if (index < end_categoryname-start_categoryname+1) { for (; index < end_categoryname-start_categoryname+1; index++) { copy_categoryname[index] = ' '; } *status_categoryname = 0; /* transfer complete */ } else { if (length > end_categoryname) { *status_categoryname = 1; /* more to transfer */ } else { *status_categoryname = 0; /* transfer complete */ } } } else { for (index = 0; index < end_categoryname-start_categoryname+1; index++) { copy_categoryname[index] = ' '; } *status_categoryname = -1; /* null string case */ } return errorcode; } /* Set category of a given tag */ int cbff_set_tag_category( size_t CBFFhandle, const char* tagname, const char* categoryname){ return cbf_set_tag_category( cbff_cbf_handle(CBFFhandle), tagname, categoryname); } /* Validate portion of CBF */ int cbff_validate( size_t CBFFhandle, size_t CBFFnode, char * CBFFtype, size_t CBFFcatnode){ return cbf_validate( cbff_cbf_handle(CBFFhandle), cbff_cbf_node_handle(CBFFnode), cbff_cbf_nodetype(CBFFtype), cbff_cbf_node_handle(CBFFcatnode)); } /* Load accumulator */ int cbff_mpint_load_acc( unsigned int * acc, size_t acsize, void * source, size_t elsize, int elsign, const char * border){ return cbf_mpint_load_acc( acc, acsize, source, elsize, elsign, border); } /* Store accumulator */ int cbff_mpint_store_acc( unsigned int * acc, size_t acsize, void * dest, size_t elsize, int elsign, const char * border){ return cbf_mpint_store_acc( acc, acsize, dest, elsize, elsign, border); } /* Clear accumulator */ int cbff_mpint_clear_acc( unsigned int * acc, size_t acsize){ return cbf_mpint_clear_acc( acc, acsize); } /* Increment accumulator */ int cbff_mpint_increment_acc( unsigned int * acc, size_t acsize){ return cbf_mpint_increment_acc( acc, acsize); } /* Decrement accumulator */ int cbff_mpint_decrement_acc( unsigned int * acc, size_t acsize){ return cbf_mpint_decrement_acc( acc, acsize); } /* Negate accumulator */ int cbff_mpint_negate_acc( unsigned int * acc, size_t acsize){ return cbf_mpint_negate_acc( acc, acsize); } /* Add to accumulator */ int cbff_mpint_add_acc( unsigned int * acc, size_t acsize, unsigned int * add, size_t addsize){ return cbf_mpint_add_acc( acc, acsize, add, addsize); } /* Shift accumulator right */ int cbff_mpint_rightshift_acc( unsigned int * acc, size_t acsize, int shift){ return cbf_mpint_rightshift_acc( acc, acsize, shift); } /* Shift accumulator left */ int cbff_mpint_leftshift_acc( unsigned int * acc, size_t acsize, int shift){ return cbf_mpint_leftshift_acc( acc, acsize, shift); } /* Check value of type validity */ int cbff_check_type_contents( const char * type, const char * value){ return cbf_check_type_contents( type, value); } /* Regex Match function */ int cbff_match( const char * string, char * pattern){ return cbf_match( string, pattern); } /* Read a template file */ int cbff_read_template( size_t CBFFhandle, size_t CBFFstream){ return cbf_read_template( cbff_cbf_handle(CBFFhandle), cbff_file_handle(CBFFstream)); } /* Get the diffrn.id entry */ int cbff_get_diffrn_id( size_t CBFFhandle, char * copy_diffrn_id, size_t start_diffrn_id, size_t end_diffrn_id, int * status_diffrn_id){ const char * diffrn_id; int index; int length; int errorcode; errorcode = cbf_get_diffrn_id( cbff_cbf_handle(CBFFhandle), &diffrn_id); if (diffrn_id) { length = strlen(diffrn_id); for (index = 0; index < length-start_diffrn_id+1 && index < end_diffrn_id-start_diffrn_id+1; index++) { copy_diffrn_id[index] = diffrn_id[index+start_diffrn_id-1]; } if (index < end_diffrn_id-start_diffrn_id+1) { for (; index < end_diffrn_id-start_diffrn_id+1; index++) { copy_diffrn_id[index] = ' '; } *status_diffrn_id = 0; /* transfer complete */ } else { if (length > end_diffrn_id) { *status_diffrn_id = 1; /* more to transfer */ } else { *status_diffrn_id = 0; /* transfer complete */ } } } else { for (index = 0; index < end_diffrn_id-start_diffrn_id+1; index++) { copy_diffrn_id[index] = ' '; } *status_diffrn_id = -1; /* null string case */ } return errorcode; } /* Change the diffrn.id entry in all the categories */ int cbff_set_diffrn_id( size_t CBFFhandle, const char * diffrn_id){ return cbf_set_diffrn_id( cbff_cbf_handle(CBFFhandle), diffrn_id); } /* Change the diffrn.id entry, creating it if necessary */ int cbff_require_diffrn_id( size_t CBFFhandle, char * copy_diffrn_id, size_t start_diffrn_id, size_t end_diffrn_id, int * status_diffrn_id, const char * default_id){ const char * diffrn_id; int index; int length; int errorcode; errorcode = cbf_require_diffrn_id( cbff_cbf_handle(CBFFhandle), &diffrn_id, default_id); if (diffrn_id) { length = strlen(diffrn_id); for (index = 0; index < length-start_diffrn_id+1 && index < end_diffrn_id-start_diffrn_id+1; index++) { copy_diffrn_id[index] = diffrn_id[index+start_diffrn_id-1]; } if (index < end_diffrn_id-start_diffrn_id+1) { for (; index < end_diffrn_id-start_diffrn_id+1; index++) { copy_diffrn_id[index] = ' '; } *status_diffrn_id = 0; /* transfer complete */ } else { if (length > end_diffrn_id) { *status_diffrn_id = 1; /* more to transfer */ } else { *status_diffrn_id = 0; /* transfer complete */ } } } else { for (index = 0; index < end_diffrn_id-start_diffrn_id+1; index++) { copy_diffrn_id[index] = ' '; } *status_diffrn_id = -1; /* null string case */ } return errorcode; } /* Get the diffrn.crystal_id entry */ int cbff_get_crystal_id( size_t CBFFhandle, char * copy_crystal_id, size_t start_crystal_id, size_t end_crystal_id, int * status_crystal_id){ const char * crystal_id; int index; int length; int errorcode; errorcode = cbf_get_crystal_id( cbff_cbf_handle(CBFFhandle), &crystal_id); if (crystal_id) { length = strlen(crystal_id); for (index = 0; index < length-start_crystal_id+1 && index < end_crystal_id-start_crystal_id+1; index++) { copy_crystal_id[index] = crystal_id[index+start_crystal_id-1]; } if (index < end_crystal_id-start_crystal_id+1) { for (; index < end_crystal_id-start_crystal_id+1; index++) { copy_crystal_id[index] = ' '; } *status_crystal_id = 0; /* transfer complete */ } else { if (length > end_crystal_id) { *status_crystal_id = 1; /* more to transfer */ } else { *status_crystal_id = 0; /* transfer complete */ } } } else { for (index = 0; index < end_crystal_id-start_crystal_id+1; index++) { copy_crystal_id[index] = ' '; } *status_crystal_id = -1; /* null string case */ } return errorcode; } /* Change the diffrn.crystal_id entry */ int cbff_set_crystal_id( size_t CBFFhandle, const char * crystal_id){ return cbf_set_crystal_id( cbff_cbf_handle(CBFFhandle), crystal_id); } /* Get the wavelength */ int cbff_get_wavelength( size_t CBFFhandle, double * wavelength){ return cbf_get_wavelength( cbff_cbf_handle(CBFFhandle), wavelength); } /* Set the wavelength */ int cbff_set_wavelength( size_t CBFFhandle, double wavelength){ return cbf_set_wavelength( cbff_cbf_handle(CBFFhandle), wavelength); } /* Get the polarization */ int cbff_get_polarization( size_t CBFFhandle, double * polarizn_source_ratio, double * polarizn_source_norm){ return cbf_get_polarization( cbff_cbf_handle(CBFFhandle), polarizn_source_ratio, polarizn_source_norm); } /* Set the polarization */ int cbff_set_polarization( size_t CBFFhandle, double polarizn_source_ratio, double polarizn_source_norm){ return cbf_set_polarization( cbff_cbf_handle(CBFFhandle), polarizn_source_ratio, polarizn_source_norm); } /* Get the divergence */ int cbff_get_divergence( size_t CBFFhandle, double * div_x_source, double * div_y_source, double * div_x_y_source){ return cbf_get_divergence( cbff_cbf_handle(CBFFhandle), div_x_source, div_y_source, div_x_y_source); } /* Set the divergence */ int cbff_set_divergence( size_t CBFFhandle, double div_x_source, double div_y_source, double div_x_y_source){ return cbf_set_divergence( cbff_cbf_handle(CBFFhandle), div_x_source, div_y_source, div_x_y_source); } /* Get the number of elements */ int cbff_count_elements( size_t CBFFhandle, unsigned int * elements){ return cbf_count_elements( cbff_cbf_handle(CBFFhandle), elements); } /* Get the element id */ int cbff_get_element_id( size_t CBFFhandle, unsigned int element_number, char * copy_element_id, size_t start_element_id, size_t end_element_id, int * status_element_id){ const char * element_id; int index; int length; int errorcode; errorcode = cbf_get_element_id( cbff_cbf_handle(CBFFhandle), element_number, &element_id); if (element_id) { length = strlen(element_id); for (index = 0; index < length-start_element_id+1 && index < end_element_id-start_element_id+1; index++) { copy_element_id[index] = element_id[index+start_element_id-1]; } if (index < end_element_id-start_element_id+1) { for (; index < end_element_id-start_element_id+1; index++) { copy_element_id[index] = ' '; } *status_element_id = 0; /* transfer complete */ } else { if (length > end_element_id) { *status_element_id = 1; /* more to transfer */ } else { *status_element_id = 0; /* transfer complete */ } } } else { for (index = 0; index < end_element_id-start_element_id+1; index++) { copy_element_id[index] = ' '; } *status_element_id = -1; /* null string case */ } return errorcode; } /* Get the detector id */ int cbff_get_detector_id( size_t CBFFhandle, unsigned int element_number, char * copy_detector_id, size_t start_detector_id, size_t end_detector_id, int * status_detector_id){ const char * detector_id; int index; int length; int errorcode; errorcode = cbf_get_detector_id( cbff_cbf_handle(CBFFhandle), element_number, &detector_id); if (detector_id) { length = strlen(detector_id); for (index = 0; index < length-start_detector_id+1 && index < end_detector_id-start_detector_id+1; index++) { copy_detector_id[index] = detector_id[index+start_detector_id-1]; } if (index < end_detector_id-start_detector_id+1) { for (; index < end_detector_id-start_detector_id+1; index++) { copy_detector_id[index] = ' '; } *status_detector_id = 0; /* transfer complete */ } else { if (length > end_detector_id) { *status_detector_id = 1; /* more to transfer */ } else { *status_detector_id = 0; /* transfer complete */ } } } else { for (index = 0; index < end_detector_id-start_detector_id+1; index++) { copy_detector_id[index] = ' '; } *status_detector_id = -1; /* null string case */ } return errorcode; } /* Get the array id for a given detector element */ int cbff_get_array_id( size_t CBFFhandle, unsigned int element_number, char * copy_array_id, size_t start_array_id, size_t end_array_id, int * status_array_id){ const char * array_id; int index; int length; int errorcode; errorcode = cbf_get_array_id( cbff_cbf_handle(CBFFhandle), element_number, &array_id); if (array_id) { length = strlen(array_id); for (index = 0; index < length-start_array_id+1 && index < end_array_id-start_array_id+1; index++) { copy_array_id[index] = array_id[index+start_array_id-1]; } if (index < end_array_id-start_array_id+1) { for (; index < end_array_id-start_array_id+1; index++) { copy_array_id[index] = ' '; } *status_array_id = 0; /* transfer complete */ } else { if (length > end_array_id) { *status_array_id = 1; /* more to transfer */ } else { *status_array_id = 0; /* transfer complete */ } } } else { for (index = 0; index < end_array_id-start_array_id+1; index++) { copy_array_id[index] = ' '; } *status_array_id = -1; /* null string case */ } return errorcode; } /* Get the pixel size of a detector element in a given direction */ int cbff_get_pixel_size( size_t CBFFhandle, unsigned int element_number, int axis_number, double * psize){ return cbf_get_pixel_size( cbff_cbf_handle(CBFFhandle), element_number, axis_number, psize); } int cbff_get_pixel_size_fs( size_t CBFFhandle, unsigned int element_number, int axis_number, double * psize){ return cbf_get_pixel_size( cbff_cbf_handle(CBFFhandle), element_number, -axis_number, psize); } int cbff_get_pixel_size_sf( size_t CBFFhandle, unsigned int element_number, int axis_number, double * psize){ return cbf_get_pixel_size( cbff_cbf_handle(CBFFhandle), element_number, -axis_number, psize); } /* Set the pixel size of a detector element in a given direction */ int cbff_set_pixel_size( size_t CBFFhandle, unsigned int element_number, int axis_number, double psize){ return cbf_set_pixel_size( cbff_cbf_handle(CBFFhandle), element_number, axis_number, psize); } int cbff_set_pixel_size_fs( size_t CBFFhandle, unsigned int element_number, int axis_number, double psize){ return cbf_set_pixel_size( cbff_cbf_handle(CBFFhandle), element_number, -axis_number, psize); } int cbff_set_pixel_size_sf( size_t CBFFhandle, unsigned int element_number, int axis_number, double psize){ return cbf_set_pixel_size( cbff_cbf_handle(CBFFhandle), element_number, axis_number, psize); } /* Get the gain of a detector element */ int cbff_get_gain( size_t CBFFhandle, unsigned int element_number, double * gain, double * gain_esd){ return cbf_get_gain( cbff_cbf_handle(CBFFhandle), element_number, gain, gain_esd); } /* Set the gain of a detector element */ int cbff_set_gain( size_t CBFFhandle, unsigned int element_number, double gain, double gain_esd){ return cbf_set_gain( cbff_cbf_handle(CBFFhandle), element_number, gain, gain_esd); } /* Get the bin sizes of a detector element */ int cbff_get_bin_sizes( size_t CBFFhandle, unsigned int element_number, double * slowbinsize, double * fastbinsize){ return cbf_get_bin_sizes( cbff_cbf_handle(CBFFhandle), element_number, slowbinsize, fastbinsize); } /* Set the bin sizes of a detector element */ int cbff_set_bin_sizes( size_t CBFFhandle, unsigned int element_number, double slowbinsize, double fastbinsize){ return cbf_set_bin_sizes( cbff_cbf_handle(CBFFhandle), element_number, slowbinsize, fastbinsize); } /* Get the overload value of a detector element */ int cbff_get_overload( size_t CBFFhandle, unsigned int element_number, double * overload){ return cbf_get_overload( cbff_cbf_handle(CBFFhandle), element_number, overload); } /* Set the overload value of a detector element */ int cbff_set_overload( size_t CBFFhandle, unsigned int element_number, double overload){ return cbf_set_overload( cbff_cbf_handle(CBFFhandle), element_number, overload); } /* Get the integration time */ int cbff_get_integration_time( size_t CBFFhandle, unsigned int reserved, double * time){ return cbf_get_integration_time( cbff_cbf_handle(CBFFhandle), reserved, time); } /* Set the integration time */ int cbff_set_integration_time( size_t CBFFhandle, unsigned int reserved, double time){ return cbf_set_integration_time( cbff_cbf_handle(CBFFhandle), reserved, time); } /* Convert gregorian to julian date (in days) */ double cbff_gregorian_julian (int year, int month, int day, int hour, int minute, double second) { return cbf_gregorian_julian (year, month, day, hour, minute, second); } /* Get the collection date and time (1) as seconds since January 1 1970 */ int cbff_get_timestamp( size_t CBFFhandle, unsigned int reserved, double * time, int * timezone){ return cbf_get_timestamp( cbff_cbf_handle(CBFFhandle), reserved, time, timezone); } /* Get the collection date and time (2) as individual fields */ int cbff_get_datestamp( size_t CBFFhandle, unsigned int reserved, int * year, int * month, int * day, int * hour, int * minute, double * second, int * timezone){ return cbf_get_datestamp( cbff_cbf_handle(CBFFhandle), reserved, year, month, day, hour, minute, second, timezone); } /* Set the collection date and time (1) as seconds since January 1 1970 */ int cbff_set_timestamp( size_t CBFFhandle, unsigned int reserved, double time, int timezone, double precision){ return cbf_set_timestamp( cbff_cbf_handle(CBFFhandle), reserved, time, timezone, precision); } /* Set the collection date and time (2) as individual fields */ int cbff_set_datestamp( size_t CBFFhandle, unsigned int reserved, int year, int month, int day, int hour, int minute, double second, int timezone, double precision){ return cbf_set_datestamp( cbff_cbf_handle(CBFFhandle), reserved, year, month, day, hour, minute, second, timezone, precision); } /* Set the collection date and time (3) as current time to the second */ int cbff_set_current_timestamp( size_t CBFFhandle, unsigned int reserved, int timezone){ return cbf_set_current_timestamp( cbff_cbf_handle(CBFFhandle), reserved, timezone); } /* Get the image size */ int cbff_get_image_size( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, size_t * ndimslow, size_t * ndimfast){ return cbf_get_image_size( cbff_cbf_handle(CBFFhandle), reserved, element_number, ndimslow, ndimfast); } int cbff_get_image_size_fs( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, size_t * ndimfast, size_t * ndimslow){ return cbf_get_image_size( cbff_cbf_handle(CBFFhandle), reserved, element_number, ndimslow, ndimfast); } int cbff_get_image_size_sf( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, size_t * ndimslow, size_t * ndimfast){ return cbf_get_image_size( cbff_cbf_handle(CBFFhandle), reserved, element_number, ndimslow, ndimfast); } /* Read a binary section into an image. ndimslow is the slow dimension, ndimfast is fast dimension.*/ int cbff_get_image( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast){ return cbf_get_image( cbff_cbf_handle(CBFFhandle), reserved, element_number, array, elsize, elsign, ndimslow, ndimfast); } int cbff_get_image_fs( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, void * array, size_t elsize, int elsign, size_t ndimfast, size_t ndimslow){ return cbf_get_image( cbff_cbf_handle(CBFFhandle), reserved, element_number, array, elsize, elsign, ndimslow, ndimfast); } int cbff_get_image_sf( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast){ return cbf_get_image( cbff_cbf_handle(CBFFhandle), reserved, element_number, array, elsize, elsign, ndimslow, ndimfast); } /* Read a binary section into a real image. ndimslow is the slow dimension, ndimfast is fast dimension.*/ int cbff_get_real_image( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, void * array, size_t elsize, size_t ndimslow, size_t ndimfast){ return cbf_get_real_image( cbff_cbf_handle(CBFFhandle), reserved, element_number, array, elsize, ndimslow, ndimfast); } int cbff_get_real_image_fs( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, void * array, size_t elsize, size_t ndimfast, size_t ndimslow){ return cbf_get_real_image( cbff_cbf_handle(CBFFhandle), reserved, element_number, array, elsize, ndimslow, ndimfast); } int cbff_get_real_image_sf( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, void * array, size_t elsize, size_t ndimslow, size_t ndimfast){ return cbf_get_real_image( cbff_cbf_handle(CBFFhandle), reserved, element_number, array, elsize, ndimslow, ndimfast); } /* Get the 3D image size. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_get_3d_image_size( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, size_t * ndimslow, size_t * ndimmid, size_t * ndimfast){ return cbf_get_3d_image_size( cbff_cbf_handle(CBFFhandle), reserved, element_number, ndimslow, ndimmid, ndimfast); } int cbff_get_3d_image_size_fs( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, size_t * ndimfast, size_t * ndimmid, size_t * ndimslow){ return cbf_get_3d_image_size( cbff_cbf_handle(CBFFhandle), reserved, element_number, ndimslow, ndimmid, ndimfast); } int cbff_get_3d_image_size_sf( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, size_t * ndimslow, size_t * ndimmid, size_t * ndimfast){ return cbf_get_3d_image_size( cbff_cbf_handle(CBFFhandle), reserved, element_number, ndimslow, ndimmid, ndimfast); } /* Read a 3D binary section into an image. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_get_3d_image( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_get_3d_image( cbff_cbf_handle(CBFFhandle), reserved, element_number, array, elsize, elsign, ndimslow, ndimmid, ndimfast); } int cbff_get_3d_image_fs( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, void * array, size_t elsize, int elsign, size_t ndimfast, size_t ndimmid, size_t ndimslow){ return cbf_get_3d_image( cbff_cbf_handle(CBFFhandle), reserved, element_number, array, elsize, elsign, ndimslow, ndimmid, ndimfast); } int cbff_get_3d_image_sf( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_get_3d_image( cbff_cbf_handle(CBFFhandle), reserved, element_number, array, elsize, elsign, ndimslow, ndimmid, ndimfast); } /* Read a 3D binary section into a real image. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_get_real_3d_image( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, void * array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_get_real_3d_image( cbff_cbf_handle(CBFFhandle), reserved, element_number, array, elsize, ndimslow, ndimmid, ndimfast); } int cbff_get_real_3d_image_fs( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, void * array, size_t elsize, size_t ndimfast, size_t ndimmid, size_t ndimslow){ return cbf_get_real_3d_image( cbff_cbf_handle(CBFFhandle), reserved, element_number, array, elsize, ndimslow, ndimmid, ndimfast); } int cbff_get_real_3d_image_sf( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, void * array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_get_real_3d_image( cbff_cbf_handle(CBFFhandle), reserved, element_number, array, elsize, ndimslow, ndimmid, ndimfast); } /* Save an image. ndimslow is the slow dimension, ndimfast is fast. */ int cbff_set_image( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, unsigned int compression, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast){ return cbf_set_image( cbff_cbf_handle(CBFFhandle), reserved, element_number, compression, array, elsize, elsign, ndimslow, ndimfast); } int cbff_set_image_fs( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, unsigned int compression, void * array, size_t elsize, int elsign, size_t ndimfast, size_t ndimslow){ return cbf_set_image( cbff_cbf_handle(CBFFhandle), reserved, element_number, compression, array, elsize, elsign, ndimslow, ndimfast); } int cbff_set_image_sf( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, unsigned int compression, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast){ return cbf_set_image( cbff_cbf_handle(CBFFhandle), reserved, element_number, compression, array, elsize, elsign, ndimslow, ndimfast); } /* Save a real image. ndimslow is the slow dimension, ndimfast is fast. */ int cbff_set_real_image( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, unsigned int compression, void * array, size_t elsize, size_t ndimslow, size_t ndimfast){ return cbf_set_real_image( cbff_cbf_handle(CBFFhandle), reserved, element_number, compression, array, elsize, ndimslow, ndimfast); } int cbff_set_real_image_fs( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, unsigned int compression, void * array, size_t elsize, size_t ndimfast, size_t ndimslow){ return cbf_set_real_image( cbff_cbf_handle(CBFFhandle), reserved, element_number, compression, array, elsize, ndimslow, ndimfast); } int cbff_set_real_image_sf( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, unsigned int compression, void * array, size_t elsize, size_t ndimslow, size_t ndimfast){ return cbf_set_real_image( cbff_cbf_handle(CBFFhandle), reserved, element_number, compression, array, elsize, ndimslow, ndimfast); } /* Save a 3D image. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension. */ int cbff_set_3d_image( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, unsigned int compression, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_set_3d_image( cbff_cbf_handle(CBFFhandle), reserved, element_number, compression, array, elsize, elsign, ndimslow, ndimmid, ndimfast); } int cbff_set_3d_image_fs( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, unsigned int compression, void * array, size_t elsize, int elsign, size_t ndimfast, size_t ndimmid, size_t ndimslow){ return cbf_set_3d_image( cbff_cbf_handle(CBFFhandle), reserved, element_number, compression, array, elsize, elsign, ndimslow, ndimmid, ndimfast); } int cbff_set_3d_image_sf( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, unsigned int compression, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_set_3d_image( cbff_cbf_handle(CBFFhandle), reserved, element_number, compression, array, elsize, elsign, ndimslow, ndimmid, ndimfast); } /* Save a real 3D image. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_set_real_3d_image( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, unsigned int compression, void * array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_set_real_3d_image( cbff_cbf_handle(CBFFhandle), reserved, element_number, compression, array, elsize, ndimslow, ndimmid, ndimfast); } int cbff_set_real_3d_image_fs( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, unsigned int compression, void * array, size_t elsize, size_t ndimfast, size_t ndimmid, size_t ndimslow){ return cbf_set_real_3d_image( cbff_cbf_handle(CBFFhandle), reserved, element_number, compression, array, elsize, ndimslow, ndimmid, ndimfast); } int cbff_set_real_3d_image_sf( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, unsigned int compression, void * array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_set_real_3d_image( cbff_cbf_handle(CBFFhandle), reserved, element_number, compression, array, elsize, ndimslow, ndimmid, ndimfast); } /* Get the array_id for a map segment or map segment mask. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension. */ int cbff_get_map_array_id( size_t CBFFhandle, unsigned int reserved, const char * segment_id, char * copy_array_id, size_t start_array_id, size_t end_array_id, int * status_array_id, int ismask, int require, size_t ndimslow, size_t ndimmid, size_t ndimfast){ const char * array_id; int index; int length; int errorcode; errorcode = cbf_get_map_array_id( cbff_cbf_handle(CBFFhandle), reserved, segment_id, &array_id, ismask, require, ndimslow, ndimmid, ndimfast); if (array_id) { length = strlen(array_id); for (index = 0; index < length-start_array_id+1 && index < end_array_id-start_array_id+1; index++) { copy_array_id[index] = array_id[index+start_array_id-1]; } if (index < end_array_id-start_array_id+1) { for (; index < end_array_id-start_array_id+1; index++) { copy_array_id[index] = ' '; } *status_array_id = 0; /* transfer complete */ } else { if (length > end_array_id) { *status_array_id = 1; /* more to transfer */ } else { *status_array_id = 0; /* transfer complete */ } } } else { for (index = 0; index < end_array_id-start_array_id+1; index++) { copy_array_id[index] = ' '; } *status_array_id = -1; /* null string case */ } return errorcode; } int cbff_get_map_array_id_fs( size_t CBFFhandle, unsigned int reserved, const char * segment_id, char * copy_array_id, size_t start_array_id, size_t end_array_id, int * status_array_id, int ismask, int require, size_t ndimfast, size_t ndimmid, size_t ndimslow){ const char * array_id; int index; int length; int errorcode; errorcode = cbf_get_map_array_id( cbff_cbf_handle(CBFFhandle), reserved, segment_id, &array_id, ismask, require, ndimslow, ndimmid, ndimfast); if (array_id) { length = strlen(array_id); for (index = 0; index < length-start_array_id+1 && index < end_array_id-start_array_id+1; index++) { copy_array_id[index] = array_id[index+start_array_id-1]; } if (index < end_array_id-start_array_id+1) { for (; index < end_array_id-start_array_id+1; index++) { copy_array_id[index] = ' '; } *status_array_id = 0; /* transfer complete */ } else { if (length > end_array_id) { *status_array_id = 1; /* more to transfer */ } else { *status_array_id = 0; /* transfer complete */ } } } else { for (index = 0; index < end_array_id-start_array_id+1; index++) { copy_array_id[index] = ' '; } *status_array_id = -1; /* null string case */ } return errorcode; } int cbff_get_map_array_id_sf( size_t CBFFhandle, unsigned int reserved, const char * segment_id, char * copy_array_id, size_t start_array_id, size_t end_array_id, int * status_array_id, int ismask, int require, size_t ndimslow, size_t ndimmid, size_t ndimfast){ const char * array_id; int index; int length; int errorcode; errorcode = cbf_get_map_array_id( cbff_cbf_handle(CBFFhandle), reserved, segment_id, &array_id, ismask, require, ndimslow, ndimmid, ndimfast); if (array_id) { length = strlen(array_id); for (index = 0; index < length-start_array_id+1 && index < end_array_id-start_array_id+1; index++) { copy_array_id[index] = array_id[index+start_array_id-1]; } if (index < end_array_id-start_array_id+1) { for (; index < end_array_id-start_array_id+1; index++) { copy_array_id[index] = ' '; } *status_array_id = 0; /* transfer complete */ } else { if (length > end_array_id) { *status_array_id = 1; /* more to transfer */ } else { *status_array_id = 0; /* transfer complete */ } } } else { for (index = 0; index < end_array_id-start_array_id+1; index++) { copy_array_id[index] = ' '; } *status_array_id = -1; /* null string case */ } return errorcode; } /* Get the map segment size. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_get_map_segment_size( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, size_t * ndimslow, size_t * ndimmid, size_t * ndimfast){ return cbf_get_map_segment_size( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, ndimslow, ndimmid, ndimfast); } int cbff_get_map_segment_size_fs( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, size_t * ndimfast, size_t * ndimmid, size_t * ndimslow){ return cbf_get_map_segment_size( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, ndimslow, ndimmid, ndimfast); } int cbff_get_map_segment_size_sf( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, size_t * ndimslow, size_t * ndimmid, size_t * ndimfast){ return cbf_get_map_segment_size( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, ndimslow, ndimmid, ndimfast); } /* Read a map segment. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_get_map_segment( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_get_map_segment( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, array, elsize, elsign, ndimslow, ndimmid, ndimfast); } int cbff_get_map_segment_fs( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, void * array, size_t elsize, int elsign, size_t ndimfast, size_t ndimmid, size_t ndimslow){ return cbf_get_map_segment( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, array, elsize, elsign, ndimslow, ndimmid, ndimfast); } int cbff_get_map_segment_sf( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_get_map_segment( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, array, elsize, elsign, ndimslow, ndimmid, ndimfast); } /* Read a map segment mask. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_get_map_segment_mask( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_get_map_segment_mask( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, array, elsize, elsign, ndimslow, ndimmid, ndimfast); } int cbff_get_map_segment_mask_fs( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, void * array, size_t elsize, int elsign, size_t ndimfast, size_t ndimmid, size_t ndimslow){ return cbf_get_map_segment_mask( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, array, elsize, elsign, ndimslow, ndimmid, ndimfast); } int cbff_get_map_segment_mask_sf( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_get_map_segment_mask( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, array, elsize, elsign, ndimslow, ndimmid, ndimfast); } /* Read a real map segment. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_get_real_map_segment( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, void * array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_get_real_map_segment( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, array, elsize, ndimslow, ndimmid, ndimfast); } int cbff_get_real_map_segment_fs( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, void * array, size_t elsize, size_t ndimfast, size_t ndimmid, size_t ndimslow){ return cbf_get_real_map_segment( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, array, elsize, ndimslow, ndimmid, ndimfast); } int cbff_get_real_map_segment_sf( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, void * array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_get_real_map_segment( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, array, elsize, ndimslow, ndimmid, ndimfast); } /* Read a real map segment mask. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_get_real_map_segment_mask( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, void * array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_get_real_map_segment_mask( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, array, elsize, ndimslow, ndimmid, ndimfast); } int cbff_get_real_map_segment_mask_fs( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, void * array, size_t elsize, size_t ndimfast, size_t ndimmid, size_t ndimslow){ return cbf_get_real_map_segment_mask( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, array, elsize, ndimslow, ndimmid, ndimfast); } int cbff_get_real_map_segment_mask_sf( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, void * array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_get_real_map_segment_mask( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, array, elsize, ndimslow, ndimmid, ndimfast); } /* Save a map segment. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_set_map_segment( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, unsigned int compression, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_set_map_segment( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, compression, array, elsize, elsign, ndimslow, ndimmid, ndimfast); } int cbff_set_map_segment_fs( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, unsigned int compression, void * array, size_t elsize, int elsign, size_t ndimfast, size_t ndimmid, size_t ndimslow){ return cbf_set_map_segment( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, compression, array, elsize, elsign, ndimslow, ndimmid, ndimfast); } int cbff_set_map_segment_sf( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, unsigned int compression, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_set_map_segment( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, compression, array, elsize, elsign, ndimslow, ndimmid, ndimfast); } /* Save a map segment mask. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_set_map_segment_mask( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, unsigned int compression, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_set_map_segment_mask( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, compression, array, elsize, elsign, ndimslow, ndimmid, ndimfast); } int cbff_set_map_segment_mask_fs( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, unsigned int compression, void * array, size_t elsize, int elsign, size_t ndimfast, size_t ndimmid, size_t ndimslow){ return cbf_set_map_segment_mask( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, compression, array, elsize, elsign, ndimslow, ndimmid, ndimfast); } int cbff_set_map_segment_mask_sf( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, unsigned int compression, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_set_map_segment_mask( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, compression, array, elsize, elsign, ndimslow, ndimmid, ndimfast); } /* Save a real map segment. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_set_real_map_segment( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, unsigned int compression, void * array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_set_real_map_segment( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, compression, array, elsize, ndimslow, ndimmid, ndimfast); } int cbff_set_real_map_segment_fs( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, unsigned int compression, void * array, size_t elsize, size_t ndimfast, size_t ndimmid, size_t ndimslow){ return cbf_set_real_map_segment( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, compression, array, elsize, ndimslow, ndimmid, ndimfast); } int cbff_set_real_map_segment_sf( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, unsigned int compression, void * array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_set_real_map_segment( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, compression, array, elsize, ndimslow, ndimmid, ndimfast); } /* Save a real map segment mask. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_set_real_map_segment_mask( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, unsigned int compression, void * array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_set_real_map_segment_mask( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, compression, array, elsize, ndimslow, ndimmid, ndimfast); } int cbff_set_real_map_segment_mask_fs( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, unsigned int compression, void * array, size_t elsize, size_t ndimfast, size_t ndimmid, size_t ndimslow){ return cbf_set_real_map_segment_mask( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, compression, array, elsize, ndimslow, ndimmid, ndimfast); } int cbff_set_real_map_segment_mask_sf( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, unsigned int compression, void * array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_set_real_map_segment_mask( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, compression, array, elsize, ndimslow, ndimmid, ndimfast); } /* Get the 3D array size. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_get_3d_array_size( size_t CBFFhandle, unsigned int reserved, const char * array_id, size_t * ndimslow, size_t * ndimmid, size_t * ndimfast){ return cbf_get_3d_array_size( cbff_cbf_handle(CBFFhandle), reserved, array_id, ndimslow, ndimmid, ndimfast); } int cbff_get_3d_array_size_fs( size_t CBFFhandle, unsigned int reserved, const char * array_id, size_t * ndimfast, size_t * ndimmid, size_t * ndimslow){ return cbf_get_3d_array_size( cbff_cbf_handle(CBFFhandle), reserved, array_id, ndimslow, ndimmid, ndimfast); } int cbff_get_3d_array_size_sf( size_t CBFFhandle, unsigned int reserved, const char * array_id, size_t * ndimslow, size_t * ndimmid, size_t * ndimfast){ return cbf_get_3d_array_size( cbff_cbf_handle(CBFFhandle), reserved, array_id, ndimslow, ndimmid, ndimfast); } /* Read a 3D array. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_get_3d_array( size_t CBFFhandle, unsigned int reserved, const char * array_id, int * binary_id, void * array, int eltype, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_get_3d_array( cbff_cbf_handle(CBFFhandle), reserved, array_id, binary_id, array, eltype, elsize, elsign, ndimslow, ndimmid, ndimfast); } int cbff_get_3d_array_fs( size_t CBFFhandle, unsigned int reserved, const char * array_id, int * binary_id, void * array, int eltype, size_t elsize, int elsign, size_t ndimfast, size_t ndimmid, size_t ndimslow){ return cbf_get_3d_array( cbff_cbf_handle(CBFFhandle), reserved, array_id, binary_id, array, eltype, elsize, elsign, ndimslow, ndimmid, ndimfast); } int cbff_get_3d_array_sf( size_t CBFFhandle, unsigned int reserved, const char * array_id, int * binary_id, void * array, int eltype, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_get_3d_array( cbff_cbf_handle(CBFFhandle), reserved, array_id, binary_id, array, eltype, elsize, elsign, ndimslow, ndimmid, ndimfast); } /* Save a 3D array. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_set_3d_array( size_t CBFFhandle, unsigned int reserved, const char * array_id, int * binary_id, unsigned int compression, void * array, int eltype, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_set_3d_array( cbff_cbf_handle(CBFFhandle), reserved, array_id, binary_id, compression, array, eltype, elsize, elsign, ndimslow, ndimmid, ndimfast); } int cbff_set_3d_array_fs( size_t CBFFhandle, unsigned int reserved, const char * array_id, int * binary_id, unsigned int compression, void * array, int eltype, size_t elsize, int elsign, size_t ndimfast, size_t ndimmid, size_t ndimslow){ return cbf_set_3d_array( cbff_cbf_handle(CBFFhandle), reserved, array_id, binary_id, compression, array, eltype, elsize, elsign, ndimslow, ndimmid, ndimfast); } int cbff_set_3d_array_sf( size_t CBFFhandle, unsigned int reserved, const char * array_id, int * binary_id, unsigned int compression, void * array, int eltype, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_set_3d_array( cbff_cbf_handle(CBFFhandle), reserved, array_id, binary_id, compression, array, eltype, elsize, elsign, ndimslow, ndimmid, ndimfast); } /* Get the setting of an axis */ int cbff_get_axis_setting( size_t CBFFhandle, unsigned int reserved, const char * axis_id, double * start, double * increment){ return cbf_get_axis_setting( cbff_cbf_handle(CBFFhandle), reserved, axis_id, start, increment); } /* Get the reference setting of an axis */ int cbff_get_axis_reference_setting( size_t CBFFhandle, unsigned int reserved, const char * axis_id, double * refsetting){ return cbf_get_axis_reference_setting( cbff_cbf_handle(CBFFhandle), reserved, axis_id, refsetting); } /* Change the setting of an axis */ int cbff_set_axis_setting( size_t CBFFhandle, unsigned int reserved, const char * axis_id, double start, double increment){ return cbf_set_axis_setting( cbff_cbf_handle(CBFFhandle), reserved, axis_id, start, increment); } /* Change the reference setting of an axis */ int cbff_set_axis_reference_setting( size_t CBFFhandle, unsigned int reserved, const char * axis_id, double refsetting){ return cbf_set_axis_reference_setting( cbff_cbf_handle(CBFFhandle), reserved, axis_id, refsetting); } /* Construct a goniometer */ int cbff_construct_goniometer( size_t CBFFhandle, size_t * CBFFgoniometer){ int errorcode; cbf_goniometer goniometer; if (!CBFFgoniometer) return CBF_ARGUMENT; errorcode = cbf_construct_goniometer(cbff_cbf_handle(CBFFhandle),&goniometer); *CBFFgoniometer = cbff_goniometer_handle(goniometer); return errorcode; } /* Free a goniometer */ int cbff_free_goniometer( size_t CBFFgoniometer){ return cbf_free_goniometer( cbff_cbf_goniometer(CBFFgoniometer)); } /* Get the rotation axis */ int cbff_get_rotation_axis( size_t CBFFgoniometer, unsigned int reserved, double * vector1, double * vector2, double * vector3){ return cbf_get_rotation_axis( cbff_cbf_goniometer(CBFFgoniometer), reserved, vector1, vector2, vector3); } /* Get the rotation range */ int cbff_get_rotation_range( size_t CBFFgoniometer, unsigned int reserved, double * start, double * increment){ return cbf_get_rotation_range( cbff_cbf_goniometer(CBFFgoniometer), reserved, start, increment); } /* Reorient a vector */ int cbff_rotate_vector( size_t CBFFgoniometer, unsigned int reserved, double ratio, double initial1, double initial2, double initial3, double * final1, double * final2, double * final3){ return cbf_rotate_vector( cbff_cbf_goniometer(CBFFgoniometer), reserved, ratio, initial1, initial2, initial3, final1, final2, final3); } /* Convert a vector to reciprocal space */ int cbff_get_reciprocal( size_t CBFFgoniometer, unsigned int reserved, double ratio, double wavelength, double real1, double real2, double real3, double * reciprocal1, double * reciprocal2, double * reciprocal3){ return cbf_get_reciprocal( cbff_cbf_goniometer(CBFFgoniometer), reserved, ratio, wavelength, real1, real2, real3, reciprocal1, reciprocal2, reciprocal3); } /* Construct a detector positioner */ int cbff_construct_detector( size_t CBFFhandle, size_t * CBFFdetector, unsigned int element_number){ int errorcode; cbf_detector detector; if (!CBFFdetector) return CBF_ARGUMENT; errorcode = cbf_construct_detector( cbff_cbf_handle(CBFFhandle), &detector, element_number); *CBFFdetector = cbff_detector_handle(detector); return errorcode; } /* Construct a reference detector positioner */ int cbff_construct_reference_detector( size_t CBFFhandle, size_t * CBFFdetector, unsigned int element_number){ int errorcode; cbf_detector detector; if (!CBFFdetector) return CBF_ARGUMENT; errorcode = cbf_construct_reference_detector( cbff_cbf_handle(CBFFhandle), &detector, element_number); *CBFFdetector = cbff_detector_handle(detector); return errorcode; } /* Construct a detector positioner, creating the necessary categories, and columns */ int cbff_require_detector( size_t CBFFhandle, size_t * CBFFdetector, unsigned int element_number){ int errorcode; cbf_detector detector; if (!CBFFdetector) return CBF_ARGUMENT; errorcode = cbf_require_detector( cbff_cbf_handle(CBFFhandle), & detector, element_number); *CBFFdetector = cbff_detector_handle(detector); return errorcode; } /* Construct a reference detector positioner, creating the necessary categories, and columns */ int cbff_require_reference_detector( size_t CBFFhandle, size_t * CBFFdetector, unsigned int element_number){ int errorcode; cbf_detector detector; if (!CBFFdetector) return CBF_ARGUMENT; errorcode = cbf_require_reference_detector( cbff_cbf_handle(CBFFhandle), & detector, element_number); *CBFFdetector = cbff_detector_handle(detector); return errorcode; } /* Free a detector */ int cbff_free_detector( size_t CBFFdetector){ return cbf_free_detector( cbff_cbf_detector_handle(CBFFdetector)); } /* Get the beam center */ int cbff_get_beam_center( size_t CBFFdetector, double * indexslow, double * indexfast, double * centerslow, double * centerfast){ return cbf_get_beam_center( cbff_cbf_detector_handle(CBFFdetector), indexslow, indexfast, centerslow, centerfast); } int cbff_get_beam_center_fs( size_t CBFFdetector, double * indexfast, double * indexslow, double * centerfast, double * centerslow){ return cbf_get_beam_center( cbff_cbf_detector_handle(CBFFdetector), indexslow, indexfast, centerslow, centerfast); } int cbff_get_beam_center_sf( size_t CBFFdetector, double * indexslow, double * indexfast, double * centerslow, double * centerfast){ return cbf_get_beam_center( cbff_cbf_detector_handle(CBFFdetector), indexslow, indexfast, centerslow, centerfast); } /* Set the beam center */ int cbff_set_beam_center( size_t CBFFdetector, double * indexslow, double * indexfast, double * centerslow, double * centerfast){ return cbf_set_beam_center( cbff_cbf_detector_handle(CBFFdetector), indexslow, indexfast, centerslow, centerfast); } int cbff_set_beam_center_fs( size_t CBFFdetector, double * indexfast, double * indexslow, double * centerfast, double * centerslow){ return cbf_set_beam_center( cbff_cbf_detector_handle(CBFFdetector), indexslow, indexfast, centerslow, centerfast); } int cbff_set_beam_center_sf( size_t CBFFdetector, double * indexslow, double * indexfast, double * centerslow, double * centerfast){ return cbf_set_beam_center( cbff_cbf_detector_handle(CBFFdetector), indexslow, indexfast, centerslow, centerfast); } /* Set the reference beam center */ int cbff_set_reference_beam_center( size_t CBFFdetector, double * indexslow, double * indexfast, double * centerslow, double * centerfast){ return cbf_set_reference_beam_center( cbff_cbf_detector_handle(CBFFdetector), indexslow, indexfast, centerslow, centerfast); } int cbff_set_reference_beam_center_fs( size_t CBFFdetector, double * indexfast, double * indexslow, double * centerfast, double * centerslow){ return cbf_set_reference_beam_center( cbff_cbf_detector_handle(CBFFdetector), indexslow, indexfast, centerslow, centerfast); } int cbff_set_reference_beam_center_sf( size_t CBFFdetector, double * indexslow, double * indexfast, double * centerslow, double * centerfast){ return cbf_set_reference_beam_center( cbff_cbf_detector_handle(CBFFdetector), indexslow, indexfast, centerslow, centerfast); } /* Get the detector distance */ int cbff_get_detector_distance( size_t CBFFdetector, double * distance){ return cbf_get_detector_distance( cbff_cbf_detector_handle(CBFFdetector), distance); } /* Get the detector normal */ int cbff_get_detector_normal( size_t CBFFdetector, double * normal1, double * normal2, double * normal3){ return cbf_get_detector_normal( cbff_cbf_detector_handle(CBFFdetector), normal1, normal2, normal3); } /* Calcluate the coordinates of a pixel */ int cbff_get_pixel_coordinates( size_t CBFFdetector, double indexslow, double indexfast, double * coordinate1, double * coordinate2, double * coordinate3){ return cbf_get_pixel_coordinates( cbff_cbf_detector_handle(CBFFdetector), indexslow, indexfast, coordinate1, coordinate2, coordinate3); } int cbff_get_pixel_coordinates_fs( size_t CBFFdetector, double indexfast, double indexslow, double * coordinate1, double * coordinate2, double * coordinate3){ return cbf_get_pixel_coordinates( cbff_cbf_detector_handle(CBFFdetector), indexslow, indexfast, coordinate1, coordinate2, coordinate3); } int cbff_get_pixel_coordinates_sf( size_t CBFFdetector, double indexslow, double indexfast, double * coordinate1, double * coordinate2, double * coordinate3){ return cbf_get_pixel_coordinates( cbff_cbf_detector_handle(CBFFdetector), indexslow, indexfast, coordinate1, coordinate2, coordinate3); } /* Get the pixel normal */ int cbff_get_pixel_normal( size_t CBFFdetector, double indexslow, double indexfast, double * normal1, double * normal2, double * normal3){ return cbf_get_pixel_normal( cbff_cbf_detector_handle(CBFFdetector), indexslow, indexfast, normal1, normal2, normal3); } int cbff_get_pixel_normal_fs( size_t CBFFdetector, double indexfast, double indexslow, double * normal1, double * normal2, double * normal3){ return cbf_get_pixel_normal( cbff_cbf_detector_handle(CBFFdetector), indexslow, indexfast, normal1, normal2, normal3); } int cbff_get_pixel_normal_sf( size_t CBFFdetector, double indexslow, double indexfast, double * normal1, double * normal2, double * normal3){ return cbf_get_pixel_normal( cbff_cbf_detector_handle(CBFFdetector), indexslow, indexfast, normal1, normal2, normal3); } /* Calcluate the area of a pixel */ int cbff_get_pixel_area( size_t CBFFdetector, double indexslow, double indexfast, double * area, double * projected_area){ return cbf_get_pixel_area( cbff_cbf_detector_handle(CBFFdetector), indexslow, indexfast, area, projected_area); } int cbff_get_pixel_area_fs( size_t CBFFdetector, double indexfast, double indexslow, double * area, double * projected_area){ return cbf_get_pixel_area( cbff_cbf_detector_handle(CBFFdetector), indexslow, indexfast, area, projected_area); } int cbff_get_pixel_area_sf( size_t CBFFdetector, double indexslow, double indexfast, double * area, double * projected_area){ return cbf_get_pixel_area( cbff_cbf_detector_handle(CBFFdetector), indexslow, indexfast, area, projected_area); } /* Calcluate the size of a pixel from the detector element axis displacements */ int cbff_get_inferred_pixel_size( size_t CBFFdetector, int axis_number, double * psize){ return cbf_get_inferred_pixel_size( cbff_cbf_detector_handle(CBFFdetector), axis_number, psize); } int cbff_get_inferred_pixel_size_fs( size_t CBFFdetector, int axis_number, double * psize){ return cbf_get_inferred_pixel_size( cbff_cbf_detector_handle(CBFFdetector), -axis_number, psize); } int cbff_get_inferred_pixel_size_sf( size_t CBFFdetector, int axis_number, double * psize){ return cbf_get_inferred_pixel_size( cbff_cbf_detector_handle(CBFFdetector), axis_number, psize); } /* Get the unit cell parameters */ int cbff_get_unit_cell( size_t CBFFhandle, double cell[6], double cell_esd[6]){ return cbf_get_unit_cell( cbff_cbf_handle(CBFFhandle), cell, cell_esd); } /* Set the unit cell parameters */ int cbff_set_unit_cell( size_t CBFFhandle, double cell[6], double cell_esd[6]){ return cbf_set_unit_cell( cbff_cbf_handle(CBFFhandle), cell, cell_esd); } /* Get the reciprocal cell parameters */ int cbff_get_reciprocal_cell( size_t CBFFhandle, double cell[6], double cell_esd[6]){ return cbf_get_reciprocal_cell( cbff_cbf_handle(CBFFhandle), cell, cell_esd); } /* Set the reciprocal cell parameters */ int cbff_set_reciprocal_cell( size_t CBFFhandle, double cell[6], double cell_esd[6]){ return cbf_set_reciprocal_cell( cbff_cbf_handle(CBFFhandle), cell, cell_esd); } /* Compute a cell volume */ int cbff_compute_cell_volume( double cell[6], double * volume){ return cbf_compute_cell_volume( cell, volume); } /* Compute a reciprocal cell */ int cbff_compute_reciprocal_cell( double cell[6], double rcell[6]){ return cbf_compute_reciprocal_cell( cell, rcell); } /* Get the orientation matrix entry */ int cbff_get_orientation_matrix( size_t CBFFhandle, double ub_matrix[9]){ return cbf_get_orientation_matrix( cbff_cbf_handle(CBFFhandle), ub_matrix); } /* Set the orientation matrix entry */ int cbff_set_orientation_matrix( size_t CBFFhandle, double ub_matrix[9]){ return cbf_set_orientation_matrix( cbff_cbf_handle(CBFFhandle), ub_matrix); } #ifdef __cplusplus } #endif ./CBFlib-0.9.2.2/src/cbf_ws.c0000644000076500007650000021526011603702106014002 0ustar yayayaya/********************************************************************** * cbf_ws.c * * * * Version 0.9.0 26 April 2009 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term ‘this software’, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ /* 1. The prefix ws is reserved for special whitespace categories and tags. 2. For any given tag, , in a category, , whitespace and comments for the tag and its value(s) will be given by _ws_.. The category ws_ is distinct from and from ws__category. For DDL1 and DDLm when tags not respecting the dotted category notation of DDL2 are used, with a tag of the form the tag for whitepace is _ws_ 3. For any given category, , whitespace and comments for the category as a whole will be given by _ws__.ws_ (note the double underscore). This category ws__ is distinct from . 4. For any given data block or save frame, whitespace and comments for the data block or save frame as whole will be given by _ws_.ws_ 5. Whitespace and comments may be given as a prologue (intended to be presented before the element), zero or more emlogues (intended to be presented between the initial sub-element, e.g. "loop_" or the tag name and the rest of the element) or an epilogue (intended to be presented after the element as a whole). We use the term "-logues" for prologues, emlogues and epilogue The -logues for an element may be given as a single string, in which case only an epilogue is intended or as a bracketed construct (using parentheses) with multiple -logues. If only one -logue is given, it is the epilogue. If two -logues are given, the first is the prologue and the second id the epilogue. If more emlogues are given than there are breaks in the element, the extra emolgues are prepended to the epilogue. The emlogues for a bracketed construct may also be bracketed constructs to provide whitespace and comments within bracketed constructs. 6. A prologue, emlogue or epilogue is a string of one or more lines starting with a optional colon-terminated column position for that line, followed by optional whitespace, followed by an optional comment. If no column position is given the whitespace begins at the next syntactically valid location. If a column position is given, then, on writing, a new line will be started if necessary to align to that column. A column position with no whitespace and no comment simply provides alignment for the next sub-element. If the end of a -logue line is a comment, whatever follows will be forced to a new line */ #ifdef __cplusplus extern "C" { #endif #include "cbf_alloc.h" #include "cbf_ws.h" /* create a handle to a bracket_tree */ /* A bracket tree is a pointer to a cbf_node of type CBF_BKT, CBF_BRC or CBF_PRN Each child, in order is one of the following: a bracket tree a value of type CBF_VALUE, in which case the name is a string following the CBF value conventions */ int cbf_create_bracket_tree(cbf_node * * brackettree, CBF_NODETYPE brackettype) { if (brackettype == CBF_BKT || brackettype == CBF_BRC || brackettype == CBF_PRN) { cbf_failnez(cbf_make_node(brackettree, brackettype, NULL, NULL)) return 0; } return CBF_ARGUMENT; } /* insert a column number into the buffer for the commentfile */ int cbf_set_ws_column (cbf_file * commentfile, size_t columnnumber) { int ii; char numberstring[21]; if (columnnumber < 1 || columnnumber >= 999999999) return CBF_ARGUMENT; sprintf (numberstring,"%ld:",(long int)columnnumber); for (ii=0; ii < strlen(numberstring); ii++) { cbf_failnez(cbf_save_character (commentfile, numberstring[ii])) } return 0; } /* Apply pending whitespace to new node */ int cbf_apply_ws(cbf_handle handle) { cbf_file * file; cbf_node * node; cbf_node * datablock; cbf_node * category; cbf_node * column; const char* catname; const char* colname; char * value; char * tvalue; void * vvalue; void * vtvalue; size_t value_size, value_used, ii, iii, start, end; int have_single_quote, have_double_quote, doas_scq, doas_scqfold; if ( !handle ) return CBF_ARGUMENT; if ( !(node=handle->node) ) return CBF_ARGUMENT; if ( ! (file=handle->commentfile) || !(file->buffer) || (file->buffer_used == 0)) return 0; /* swap out the whitespace buffer */ value = file->buffer; fprintf(stderr," cbf_apply_ws: \n(%s)\n",value); value_size = file->buffer_size; value_used = file->buffer_used; file->buffer = NULL; file->buffer_size = 0; file->buffer_used = 0; /* Scan the whitespace and comment string looking for quote marks or comments */ start = 0; end = value_used-1; while (start < value_used) { have_single_quote = have_double_quote = doas_scq = doas_scqfold = 0; for (ii=start; ii < value_used; ii++) { if (value[ii] == '\'' && (ii==value_used-1 || !value[ii+1] || (isspace(value[ii+1])) || value[ii+1] == ',' || value[ii+1] == ')' || value[ii+1] == '}' || value[ii+1] == ']' )) have_single_quote = 1; if (value[ii] == '"' && (ii==value_used-1 || !value[ii+1] || (isspace(value[ii+1])) || value[ii+1] == ',' || value[ii+1] == ')' || value[ii+1] == '}' || value[ii+1] == ']' )) { have_double_quote = 1; if ( have_single_quote ) doas_scq = 1; } if (value[ii]=='\n') doas_scq = 1; if (ii > start && value[ii] == ';' && value[ii-1]=='\n') { doas_scq = doas_scqfold = 1; } if (value[ii] == ',' || value[ii] == ')' || value[ii] == '}' || value[ii] == ']') { break; } if (value[ii] == '#') { doas_scq = 1; for (iii=ii+1; iii < value_used; iii++) { if (value[iii] == '\n') break; } ii = iii; end = iii; continue; } end = ii; } if (value[end] != '\n' && doas_scq) doas_scqfold = 1; if (doas_scq) { cbf_failnez(cbf_save_character(file,'\n')) cbf_failnez(cbf_save_character(file,';')) if (doas_scqfold) { cbf_failnez(cbf_save_character(file,'\\')) cbf_failnez(cbf_save_character(file,'\n')) } } else { if (have_double_quote) { cbf_failnez(cbf_save_character(file,'\'')) } else { cbf_failnez(cbf_save_character(file,'"')) } } for (ii=start; ii<=end; ii++) { cbf_failnez(cbf_save_character(file,value[ii])) if (value[ii] == '\n' && ii > start && ii < end) { cbf_failnez (cbf_set_ws_column (file, 1)) } if (doas_scqfold && ii > start && value[ii]==';' && value[ii-1]=='\n') { cbf_failnez(cbf_save_character(file,'\\')) cbf_failnez(cbf_save_character(file,'\n')) } } if (doas_scq) { if (doas_scqfold ) { cbf_failnez(cbf_save_character(file,'\\')) cbf_failnez(cbf_save_character(file,'\n')) cbf_failnez(cbf_save_character(file,';')) cbf_failnez(cbf_save_character(file,'\n')) } else { if (value[end]!='\n') { cbf_failnez(cbf_save_character(file,'\n')) } cbf_failnez(cbf_save_character(file,';')) } } else { if (have_double_quote) { cbf_failnez(cbf_save_character(file,'\'')) } else { cbf_failnez(cbf_save_character(file,'"')) } } start = end+1; end = value_used-1; if (start < value_used) { cbf_failnez(cbf_save_character(file,value[start])) start++; continue; } } vvalue = (void *)value; cbf_failnez(cbf_free ((void **) &vvalue, &value_size)) fprintf(stderr," cbf_apply_ws (converted): \n(%s)\n",file->buffer); /* construct the value On entry file->buffer[0] is ' ' for a single prologue string or '(' if there embedded emlogues and epilogues. file->buffer[1] is ' ' for a single line or '\\' for multiline string, or for a string with embedded double quote marks. For a single prologue, one line string with no embedded double quote marks, the result will be ("string",,) For a single prologue, one line string with no embedded single quote marks, the result will be ('string',,) For a single prologue, multiline string, or string with embedded quote marks, the result will be (\n;\\\nstring\\\n;\n,,) with internal ;'s and \'s protected by trailing \\\n sequences. If there are emlogues the same transformations will be applied. */ if (node->type == CBF_DATABLOCK || node->type == CBF_SAVEFRAME) { fprintf(stderr,"in CBF_DATABLOCK or CBF_SAVEFRAME\n"); catname = cbf_copy_string(NULL,"ws_",0); colname = cbf_copy_string(NULL,"ws_",0); if (!catname || !colname) return CBF_ALLOC; cbf_failnez(cbf_make_child(&category,node,CBF_CATEGORY,catname)) cbf_failnez(cbf_make_child(&column,category,CBF_COLUMN,colname)) value = (char *)cbf_copy_string(NULL,file->buffer,CBF_TOKEN_PRNSTRING); if (!value) return CBF_ALLOC; cbf_failnez(cbf_set_columnrow(column,0,value,1)) cbf_failnez(cbf_reset_buffer(file)) return 0; } if (node->type == CBF_CATEGORY) { fprintf(stderr,"in CBF_CATEGORY\n"); catname = cbf_copy_strings(NULL,"ws__",(node->name),0); if (!catname) return CBF_ALLOC; /* Find the save frame or data block node */ if (cbf_find_parent (&datablock, node, CBF_SAVEFRAME)) { cbf_failnez (cbf_find_parent (&datablock, node, CBF_DATABLOCK)) } cbf_failnez(cbf_make_child(&category,datablock,CBF_CATEGORY,catname)) colname = cbf_copy_string(NULL,"ws_",0); if (!colname) return CBF_ALLOC; cbf_failnez(cbf_make_child(&column,category,CBF_COLUMN,colname)) value = (char *)cbf_copy_string(NULL,file->buffer,CBF_TOKEN_PRNSTRING); if (!value) return CBF_ALLOC; cbf_failnez(cbf_set_columnrow(column,0,value,1)) cbf_failnez(cbf_reset_buffer(file)) return 0; } if (node->type == CBF_COLUMN) { unsigned int row, rows; fprintf(stderr,"in CBF_COLUMN\n"); if (node->name[0] != '_') { colname = cbf_copy_string(NULL,node->name,0); } else { colname = cbf_copy_strings(NULL,"_ws",node->name,0); } if (!colname) return CBF_ALLOC; rows = node->children; row = rows>0?rows-1:0; /* Find the category and pick up the name */ cbf_failnez(cbf_find_parent(&category, node, CBF_CATEGORY)) catname = cbf_copy_strings(NULL,"ws_",(node->name),0); if (!catname) return CBF_ALLOC; /* Find the save frame or data block node */ if (cbf_find_parent (&datablock, node, CBF_SAVEFRAME)) { cbf_failnez (cbf_find_parent (&datablock, node, CBF_DATABLOCK)) } cbf_failnez(cbf_make_child(&category,datablock,CBF_CATEGORY,catname)) cbf_failnez(cbf_make_child(&column,category,CBF_COLUMN,colname)) if (column->children > row && column->child[row]) { /* Prior ws loaded, need to combine with the new string */ if (((char *)(column->child[row]))[0] != CBF_TOKEN_PRNSTRING) return CBF_FORMAT; tvalue = (char *)cbf_copy_strings(NULL,((char *)(column->child[row]))+1,",",0); if (!tvalue) return CBF_ALLOC; value = (char *)cbf_copy_strings(NULL,tvalue,file->buffer,CBF_TOKEN_PRNSTRING); vtvalue = (void *)tvalue; cbf_failnez(cbf_free ((void **) &vtvalue, NULL)) if (!value) return CBF_ALLOC; } else { value = (char *)cbf_copy_string(NULL,file->buffer,CBF_TOKEN_PRNSTRING); if (!value) return CBF_ALLOC; } cbf_failnez(cbf_set_columnrow(column,row,value,1)) cbf_failnez(cbf_reset_buffer(file)) return 0; } return 0; } /* Write an ascii whitespace value */ int cbf_write_ws_ascii (const char *string, cbf_file *file) { int ii, iii, istart; char initc=' ', termc=' '; /* Check the arguments */ if (!string) return CBF_ARGUMENT; else if (*string != CBF_TOKEN_WORD && *string != CBF_TOKEN_SQSTRING && *string != CBF_TOKEN_DQSTRING && *string != CBF_TOKEN_SCSTRING && *string != CBF_TOKEN_TSQSTRING && *string != CBF_TOKEN_TDQSTRING && *string != CBF_TOKEN_BKTSTRING && *string != CBF_TOKEN_BRCSTRING && *string != CBF_TOKEN_PRNSTRING && *string != CBF_TOKEN_NULL) return CBF_ARGUMENT; /* Write the value */ /* First check if anything other than whitespace appears */ switch (*string) { case CBF_TOKEN_WORD: case CBF_TOKEN_NULL: case CBF_TOKEN_SQSTRING: case CBF_TOKEN_DQSTRING: case CBF_TOKEN_SCSTRING: case CBF_TOKEN_TSQSTRING: case CBF_TOKEN_TDQSTRING: istart = 0; for (ii=0; ii < strlen(string+1); ii++) { if ((string+1)[ii] == ' ' || (string+1)[ii] == '\t') { if (file->column+ii >= file->columnlimit) { cbf_failnez (cbf_write_character (file, '\n')) istart = ii+1; continue; } } if ((string+1)[ii] != '#') { if (file->column+ii >= file->columnlimit) { cbf_failnez (cbf_write_character (file, '\n')) istart = ii; continue; } cbf_failnez (cbf_write_character (file, '#')) } for (iii=istart; iii< ii; iii++) { cbf_failnez (cbf_write_character (file, (string+1)[iii])) if (file->column == 0) { cbf_failnez (cbf_write_character (file, '#')) } } for (iii=ii; iii< strlen(string+1); iii++) { if (file->column >= file->columnlimit) { cbf_failnez (cbf_write_character (file, '\n')) if ((string+1)[iii] != '#') { cbf_failnez (cbf_write_character (file, '#')) } } cbf_failnez (cbf_write_character (file, (string+1)[iii])) if (file->column == 0) { cbf_failnez (cbf_write_character (file, '#')) } } if (file->column > 0) { cbf_failnez (cbf_write_character (file, '\n')) } return 0; } for (iii=istart; iii< ii; iii++) { cbf_failnez (cbf_write_character (file, (string+1)[iii])) } break; case CBF_TOKEN_PRNSTRING: case CBF_TOKEN_BRCSTRING: case CBF_TOKEN_BKTSTRING: switch (*string) { case CBF_TOKEN_PRNSTRING: initc = '('; termc = ')'; break; case CBF_TOKEN_BRCSTRING: initc = '{'; termc = '}'; break; case CBF_TOKEN_BKTSTRING: initc = '['; termc = ']'; break; } istart = 0; for (ii=0; ii < strlen(string+1); ii++) { if ((string+1)[ii] == ' ' || (string+1)[ii] == '\t') { if (file->column+ii >= file->columnlimit) { cbf_failnez (cbf_write_character (file, '\n')) istart = ii+1; continue; } } for (iii=istart; iii< ii; iii++) { cbf_failnez (cbf_write_character (file, (string+1)[iii])) if (file->column == 0) { cbf_failnez (cbf_write_character (file, '#')) } } if (file->column+ii >= file->columnlimit-1) { cbf_failnez (cbf_write_character (file, '\n')) continue; } cbf_failnez (cbf_write_character (file, '#')) cbf_failnez (cbf_write_character (file, initc)) for (iii=ii; iii< strlen(string+1); iii++) { if (file->column >= file->columnlimit) { cbf_failnez (cbf_write_character (file, '\n')) if ((string+1)[iii] != '#') { cbf_failnez (cbf_write_character (file, '#')) } } if (file->column == 0) { cbf_failnez (cbf_write_character (file, '#')) } if (file->column >= file->columnlimit) { cbf_failnez (cbf_write_character (file, '\n')) if ((string+1)[iii] != '#') { cbf_failnez (cbf_write_character (file, '#')) } } cbf_failnez (cbf_write_character (file, (string+1)[iii])) } if (file->column >= file->columnlimit-1) { cbf_failnez (cbf_write_character (file, '\n')) if ((string+1)[iii] != '#') { cbf_failnez (cbf_write_character (file, '#')) } cbf_failnez (cbf_write_character (file, termc)) } if (file->column > 0) { cbf_failnez (cbf_write_character (file, '\n')) } return 0; } for (iii=istart; iii< ii; iii++) { cbf_failnez (cbf_write_character (file, (string+1)[iii])) } break; } return 0; } /* scan a string for a bracketed substring at level targetdepth and index targetindex */ int cbf_find_bracketstring(const char * string, const char * stringlimit, const char * stringtype, char * * bracketstring, char * * bracketstringlimit, int * more, size_t targetdepth, size_t targetindex ) { int *tokentype; int **vtokentype; size_t tokentype_size; int * state; int ** vstate; size_t state_size; int * index; int ** vindex; int depth; size_t index_size; const char * cptr; const char * line; char c, cprev, cprevprev, cprevprevprev; size_t length; cptr = string; tokentype_size = state_size = index_size = 0; vtokentype = &tokentype; vstate = &state; vindex = &index; depth = 0; /* validate arguments */ if ((!string) || (!stringlimit) || (!stringtype) || (string > stringlimit) || (!bracketstring) || (!bracketstringlimit) || (!more) ) return CBF_ARGUMENT; /* determine if this is a simple string or a bracketed string */ switch (*stringtype) { case CBF_TOKEN_WORD: case CBF_TOKEN_SQSTRING: case CBF_TOKEN_DQSTRING: case CBF_TOKEN_SCSTRING: case CBF_TOKEN_TSQSTRING: case CBF_TOKEN_TDQSTRING: *more = 0; if (targetindex > 0 || targetdepth > 1) { *bracketstring = *bracketstringlimit = NULL; } else { *bracketstring = (char *)string; *bracketstringlimit = (char *)stringlimit; } return 0; break; case CBF_TOKEN_BKTSTRING: case CBF_TOKEN_BRCSTRING: case CBF_TOKEN_PRNSTRING: tokentype[depth-1]= *stringtype; break; default: *bracketstring = *bracketstringlimit = NULL; return CBF_ARGUMENT; } /* strip any initial space characters */ cprev = cprevprev = cprevprevprev = 0; while (cptr < stringlimit && isspace(*cptr)) { cprevprev= cprev; cprev = *cptr; cptr++; } c = *cptr; line = cptr; depth = 1; tokentype_size = state_size = index_size = 100; cbf_failnez(cbf_alloc((void **)vtokentype, NULL, sizeof(int), tokentype_size)) cbf_onfailnez(cbf_alloc((void **)vstate, NULL, sizeof(int), state_size), cbf_free((void **)vtokentype,NULL)) cbf_onfailnez(cbf_alloc((void **)vindex, NULL, sizeof(int), index_size), {cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate,NULL);}) state[depth-1] = index[depth-1] = 0; length = 0; while (cptr < stringlimit) { int q3; /* flag for treble quote */ int savechar=1; /* flag to save the character */ int breakout=0; /* flag to break out of the loop */ int string; q3 = (length > 3 && (line[0]=='\'' || line[0]=='"') && line[1] == line[0] && line[2] == line[1]); if (depth == 0) { string = !(!q3 && cprev == line[0] && length > 1 && isspace(c)) && !( q3 && length > 5 && cprev == line[0] && cprevprev == line[1] && cprevprevprev == line[2] && isspace(c)); if ( string && ( (c == '\n' && !q3) ) ) { string = 0; } /* handle the bracketed cases */ savechar = 0; breakout = 0; switch (state[depth-1]) { /* In state 1 we have started an item and are looking for the end of the item. The possibilities are that the item we are parsing is 1. A single-quoted string 2. A double-quoted string 3. A triple-single-quoted string (only if PARSE_TRIPLE_QUOTES is set) 4. A triple-double-quoted string (only if PARSE_TRIPLE_QUOTES is set) 5. A parenthesis-bracketed string 6. A brace-bracketed string 7. A bracket-bracketed string 8. A blank-bracketed string (only if PARSE_LIBERAL_BRACKETS is set) 9. A bracket-bracketed item (only if PARSE_LIBERAL_BRACKETS is not set) In all cases, the depth will have been increased by 1 and the appropriate token type stored in tokentype[depth-1], and index[depth-1] will accumulate the number of characters It is important that this code come before the code for state 2 so that we can fall through. */ case (1): /* See if we are looking for a terminal quote mark */ if (cbf_token_term(tokentype[depth-1])=='\'' || cbf_token_term(tokentype[depth-1])=='"' ) { string = ( cprev != cbf_token_term(tokentype[depth-1]) || index[depth-1] < 1 || !(isspace(c)||c==','||c==cbf_token_term(tokentype[depth-2]) ) ); if (index[depth-1] == 2 && c==cprev && cprev==cprevprev ) { tokentype[depth-1] = tokentype[depth-1]==CBF_TOKEN_SQSTRING?CBF_TOKEN_TSQSTRING:CBF_TOKEN_TDQSTRING; } if (tokentype[depth-1]==CBF_TOKEN_TSQSTRING || tokentype[depth-1]==CBF_TOKEN_TDQSTRING) { string = !(cprev == cbf_token_term(tokentype[depth-1]) && cprevprev == cprev && cprevprevprev==cprevprev && index[depth-1] > 5 && (isspace(c)||c==','||c==cbf_token_term(tokentype[depth-2]) )); } else { if ( string && ( c == '\n') ) { string = 0; } } if ( !string ) { depth--; /* drop down from this level */ state[depth-1]++; savechar = 0; if (c == '\n') { break; } if (!isspace(c)) savechar = 1; /* intentionally fail to do a break */ } else { savechar = 1; breakout = 0; index[depth-1]++; break; } } else { /* We are not looking for a terminal quote mark */ /* on a blank-delimited item we may end on a blank, comma or the next level terminator */ if (cbf_token_term(tokentype[depth-1])==' ') { /* we are still in a blank-delimited item if the character is not a space, not a comma and not the bracket from the next level. The string also ends at eol or eof */ string = ( !isspace(c)) && !(c==','||c==cbf_token_term(tokentype[depth-2]) ); if ( string && ( c == '\n' ) ) { string = 0; } if ( !string ) { depth--; state[depth-1]++; savechar = 0; breakout = 0; break; } else { savechar = 1; breakout = 0; index[depth-1]++; break; } } else { if (cbf_token_term(tokentype[depth-1])==';') { string = ( cprevprev != '\n' || cprev != cbf_token_term(tokentype[depth-1]) || index[depth-1] < 3 || !(isspace(c) || c==','||c==cbf_token_term(tokentype[depth-2]) ) ); if ( !string ) { depth--; state[depth-1]++; savechar = 0; breakout = 0; break; } else { savechar = 1; breakout = 0; index[depth-1]++; break; } } } } /* In state 2 we have completed an item and need to scan for a comma or a terminator. Since we are not breaking out the items, we merge this case with state 0. */ case (2): /* In state 0 we are looking for an item for the construct We may encounter a comment, a space, a comma, a terminator for the construct or the beginning of an item */ case (0): if (c=='#') do { cprevprevprev = cprevprev; cprevprev = cprev; cprev = c; c = *(++cptr); if (cptr >= stringlimit) c = EOF; } while (c != '\n' && c != EOF); if (c==EOF) { /* int ttype=tokentype[0]; */ /*cbf_log(handle,"file ended before end of bracketed construct", CBF_LOGWARNING|CBF_LOGSTARTLOC); */ cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL); /* return cbf_return_text (STRING, val, &line [1], ttype ); */ } if (isspace(c)) { savechar = 0; breakout = 0; break; } if (c==',' ) { savechar = 1; /* Keep the comma */ breakout = 0; /* depth--; */ /* Stay at this level */ index[depth-1]++; state[depth-1] = 0; /* Search for a non-blank */ break; } if (c==cbf_token_term(tokentype[depth-1]) && (cbf_token_term(tokentype[depth-1])==';'?'\n':cprev)==cprev) { savechar = 1; breakout = 0; /* depth--; */ /* end the token */ if (depth > 0)depth--; /* end the bracket */ if (depth==0) { /* int ttype=tokentype[0]; */ cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL); /* return cbf_return_text (STRING, val, &line [1], ttype); */ } state[depth-1]++; break; } if ( !isspace(c)) { if (state[depth-1]==2) { /* cbf_onfailnez (cbf_save_character_trim (file, ' '), { cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL);}) */ state[depth-1]=0; } state[depth-1]++; /* cbf_onfailnez (cbf_save_character_trim (file, c), { cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL);}) */ savechar = 0; depth++; if (depth > tokentype_size) { cbf_onfailnez(cbf_realloc((void **)vtokentype, NULL, sizeof(int),tokentype_size*2), {cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL);}) tokentype_size *= 2; } if (depth > state_size) { cbf_onfailnez(cbf_realloc((void **)vstate, NULL, sizeof(int),state_size*2), {cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL);}) state_size *= 2; } if (depth > index_size) { cbf_onfailnez(cbf_realloc((void **)vindex, NULL, sizeof(int),index_size*2), {cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL);}) index_size *= 2; } index[depth-1] = state[depth-1] = 0; switch(c) { case ('\'') : tokentype[depth-1]=CBF_TOKEN_SQSTRING; state[depth-1] = 1; break; case ('"') : tokentype[depth-1]=CBF_TOKEN_DQSTRING; state[depth-1] = 1; break; case ('[') : tokentype[depth-1]=CBF_TOKEN_BKTSTRING; break; case ('{') : tokentype[depth-1]=CBF_TOKEN_BRCSTRING; break; case ('(') : tokentype[depth-1]=CBF_TOKEN_PRNSTRING; break; case (';') : if (cprev=='\n') { tokentype[depth-1]=CBF_TOKEN_SCSTRING; state[depth-1] = 1; break; } default: tokentype[depth-1]= CBF_TOKEN_WORD; state[depth-1] = 1; break; } breakout = 0; break; } savechar = 1; breakout = 0; break; } if (savechar) { /* cbf_onerrornez (cbf_save_character_trim (file, c), val, {cbf_free((void **)vtokentype, NULL); cbf_free((void **)vstate, NULL); cbf_free((void **)vindex, NULL);}) */ } if (breakout) break; } } return 0; } /* Write a ws and comment value to a file */ int cbf_write_ws_value (cbf_node *column, unsigned int row, cbf_file *file, int isbuffer, logue whichlogue) { const char *text; /* Check the arguments */ if (!column) return CBF_ARGUMENT; if (row >= column->children) return CBF_NOTFOUND; /* Get the value */ cbf_failnez (cbf_get_columnrow (&text, column, row)) /* Missing value? */ if (!text) return 0; /* Plain ASCII? */ cbf_failnez (cbf_value_type ((char *) text)) if (*text == CBF_TOKEN_WORD || *text == CBF_TOKEN_SQSTRING || *text == CBF_TOKEN_DQSTRING || *text == CBF_TOKEN_SCSTRING || *text == CBF_TOKEN_TSQSTRING || *text == CBF_TOKEN_TDQSTRING || *text == CBF_TOKEN_PRNSTRING || *text == CBF_TOKEN_BKTSTRING || *text == CBF_TOKEN_BRCSTRING || *text == CBF_TOKEN_NULL) return cbf_write_ws_ascii (text, file); /* Fail */ return CBF_ARGUMENT; } int cbf_write_ws_prologue(const cbf_node *node, cbf_file *file, int isbuffer) { unsigned int row; cbf_node *subnode; /* Check the arguments */ if (!node || !file) return CBF_ARGUMENT; /* Check if white space is to be processed */ if ( (file->write_headers & CBF_PARSE_WS) == 0 ) return 0; /* Follow any links */ node = cbf_get_link (node); /* Node type */ switch (node->type) { case CBF_ROOT: return 0; break; case CBF_DATABLOCK: case CBF_SAVEFRAME: if (!cbf_find_typed_child(&subnode, node,"ws_",CBF_CATEGORY)) { if (!cbf_find_child( &subnode, subnode,"ws_")) { for (row = 0; row < subnode->children; row++) { cbf_failnez(cbf_write_ws_value(subnode,row,file,isbuffer,pro)) } } } return 0; break; case CBF_CATEGORY: if (!cbf_cistrcmp(node->name,"ws_")) {return 0;} if (!cbf_find_child( &subnode, node,"ws__prologue")) { for (row = 0; row < subnode->children; row++) { cbf_failnez(cbf_write_ws_value(subnode,row,file,isbuffer,pro)) } } return 0; break; default: return CBF_ARGUMENT; } } int cbf_write_ws_emlogue(const cbf_node *node, cbf_file *file, int isbuffer) { unsigned int row; cbf_node *subnode; /* Check the arguments */ if (!node || !file) return CBF_ARGUMENT; /* Check if white space is to be processed */ if ( (file->write_headers & CBF_PARSE_WS) == 0 ) return 0; /* Follow any links */ node = cbf_get_link (node); /* Node type */ switch (node->type) { case CBF_ROOT: return 0; break; case CBF_DATABLOCK: case CBF_SAVEFRAME: if (!cbf_find_typed_child(&subnode, node,"ws_",CBF_CATEGORY)) { if (!cbf_find_child( &subnode, subnode,"emlogue")) { for (row = 0; row < subnode->children; row++) { cbf_failnez(cbf_write_ws_value(subnode,row,file,isbuffer, em)) } } } return 0; break; case CBF_CATEGORY: if (!cbf_cistrcmp(node->name,"ws_")) {return 0;} if (!cbf_find_child( &subnode, node,"ws__emlogue")) { for (row = 0; row < subnode->children; row++) { cbf_failnez(cbf_write_ws_value(subnode,row,file,isbuffer, em)) } } return 0; break; default: return CBF_ARGUMENT; } } int cbf_write_ws_epilogue(const cbf_node *node, cbf_file *file, int isbuffer) { unsigned int row; cbf_node *subnode; /* Check the arguments */ if (!node || !file) return CBF_ARGUMENT; /* Check if white space is to be processed */ if ( (file->write_headers & CBF_PARSE_WS) == 0 ) return 0; /* Follow any links */ node = cbf_get_link (node); /* Node type */ switch (node->type) { case CBF_ROOT: return 0; break; case CBF_DATABLOCK: case CBF_SAVEFRAME: if (!cbf_find_typed_child(&subnode, node,"ws_",CBF_CATEGORY)) { if (!cbf_find_child( &subnode, subnode,"epilogue")) { for (row = 0; row < subnode->children; row++) { cbf_failnez(cbf_write_ws_value(subnode,row,file,isbuffer, epi)) } } } return 0; break; case CBF_CATEGORY: if (!cbf_cistrcmp(node->name,"ws_")) {return 0;} if (!cbf_find_child( &subnode, node,"ws_")) { for (row = 0; row < subnode->children; row++) { cbf_failnez(cbf_write_ws_value(subnode,row,file,isbuffer, epi)) } } return 0; break; default: return CBF_ARGUMENT; } } #ifdef __cplusplus } #endif ./CBFlib-0.9.2.2/src/cbf_alloc.c0000644000076500007650000005073611603702106014450 0ustar yayayaya/********************************************************************** * cbf_alloc -- memory allocation * * * * Version 0.7.6 14 July 2006 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifdef __cplusplus extern "C" { #endif #include "cbf.h" #include "cbf_alloc.h" #include #include #ifdef CBFLIB_MEM_DEBUG size_t memory_allocated; #endif #ifdef DMALLOC #include #endif /* Reallocate a block of memory (never lose the old block on failure) */ int cbf_realloc (void **old_block, size_t *old_nelem, size_t elsize, size_t nelem) { void *new_block; /* Are the arguments valid? */ if (!old_block || elsize == 0) return CBF_ARGUMENT; /* Is the size alread correct? */ if (old_nelem) if (*old_nelem == nelem) return 0; /* Allocate the memory */ if (nelem > 0) { #ifdef CBFLIB_MEM_DEBUG char * cnew_block; #endif new_block = malloc (nelem * elsize + sizeof(size_t)); if (!new_block) return CBF_ALLOC; *(size_t *)new_block = nelem * elsize; #ifdef CBFLIB_MEM_DEBUG fprintf(stderr, "allocated %ld size %ld\n",(long)new_block,(long)(nelem * elsize)); cnew_block = (char *)new_block; cnew_block += sizeof(size_t); new_block = (void *)cnew_block; memory_allocated += nelem * elsize; #endif } else new_block = NULL; /* Copy the old data */ if (old_nelem) if (*old_block && *old_nelem > 0 && nelem > 0) { if (*old_nelem > nelem) *old_nelem = nelem; memcpy (new_block, *old_block, *old_nelem * elsize); } /* Free the old memory */ if (*old_block) { #ifdef CBFLIB_MEM_DEBUG char * cold_block; cold_block = (void *)(*old_block); (cold_block) -= sizeof(size_t); *old_block = (char *)cold_block; memory_allocated -= *(size_t *)(*old_block); fprintf(stderr, "freeing %ld size %ld\n",(long)(*old_block),(long)(*(size_t *)(*old_block))); #endif free (*old_block); } /* Clear the new data */ if (!old_nelem) memset (new_block, 0, nelem * elsize); else if (nelem > 0 && nelem > *old_nelem) memset (((char *) new_block) + *old_nelem * elsize, 0, (nelem - *old_nelem) * elsize); /* Replace the old data */ *old_block = new_block; if (old_nelem) *old_nelem = nelem; /* Success */ return 0; } /* Allocate a block of memory */ int cbf_alloc (void **new_block, size_t *new_nelem, size_t elsize, size_t nelem) { /* Are the arguments valid? */ if (!new_block) return CBF_ARGUMENT; /* Initialise */ *new_block = NULL; if (new_nelem) *new_nelem = 0; /* Allocate the memory */ return cbf_realloc (new_block, new_nelem, elsize, nelem); } /* Free a block of memory as a string */ int cbf_free_text(const char **old_block, size_t *old_nelem) { void * vold_block; vold_block = (void *)*old_block; cbf_failnez(cbf_free(&vold_block, old_nelem)) *old_block = NULL; return 0; } /* Free a block of memory */ int cbf_free (void **old_block, size_t *old_nelem) { /* Are the arguments valid? */ if (!old_block) return CBF_ARGUMENT; /* Free the memory */ if (*old_block) { #ifdef CBFLIB_MEM_DEBUG char * cold_block; cold_block = (void *)(*old_block); (cold_block) -= sizeof(size_t); *old_block = (char *)cold_block; memory_allocated -= *(size_t *)(*old_block); fprintf(stderr,"freeing %ld size %ld\n",(long)(*old_block),(long)(*(size_t *)(*old_block))); #endif free (*old_block); } *old_block = NULL; if (old_nelem) *old_nelem = 0; /* Success */ return 0; } #ifdef __cplusplus } #endif ./CBFlib-0.9.2.2/src/cbf.stx.y0000644000076500007650000021741111603702106014134 0ustar yayayaya%{ /********************************************************************** * cbf.stx -- cbf parser * * * * Version 0.7.7 19 February 2007 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifdef __cplusplus extern "C" { #endif #include #include #include #include "cbf.h" #include "cbf_tree.h" #include "cbf_alloc.h" #include "cbf_context.h" #include "cbf_ws.h" #define yyparse cbf_parse #define yylex cbf_lex_wrapper #define yyerror(x) cbf_syntax_error(((cbf_handle)(((void **)context)[2])),(x)) #define YYLEX_PARAM context #define YYPARSE_PARAM context typedef union { int errorcode; const char *text; cbf_node *node; } YYSTYPE; #define YYSTYPE_IS_DECLARED #ifdef alloca #undef alloca #endif #define alloca(x) (NULL) #define YYINITDEPTH 200 #define YYMAXDEPTH 200 int cbf_lex (cbf_handle handle, YYSTYPE *val ); /* vcontext[0] -- (void *)file vcontext[1] -- (void *)handle->node vcontext[2] -- (void *)handle vcontext[3] -- (void *)node */ int cbf_lex_wrapper (void *val, void *vcontext) { int token; cbf_handle cbfhandle; cbf_file *cbffile; do { cbffile = (cbf_file*)((void **) vcontext) [0]; cbfhandle = (cbf_handle)((void **) vcontext) [2]; token = cbf_lex (cbfhandle, (YYSTYPE *)val); if ( token == COMMENT && ((YYSTYPE *)val)->text ) { cbf_free_text(&(((YYSTYPE *)val)->text),NULL); } } while (token == COMMENT); return token; } int cbf_syntax_error (cbf_handle handle, const char *message) { cbf_log( handle, message, CBF_LOGERROR|CBF_LOGSTARTLOC ); return 0; } %} %union { int errorcode; const char *text; cbf_node *node; } %token DATA %token DEFINE %token SAVE %token SAVEEND %token LOOP %token ITEM %token CATEGORY %token COLUMN %token STRING %token CBFWORD %token BINARY %token UNKNOWN %token COMMENT %token ERROR %type cbf %type cbfstart %type CbfThruDBName %type ErrorCbfWODBName %type CbfThruDBElement %type CbfThruSaveFrame %type CbfThruCategory %type CbfThruColumn %type CbfThruAssignment %type ErrorCbfThruExtraValue %type CbfThruLoopStart %type CbfThruLoopCategory %type CbfThruLoopColumn %type CbfThruLoopAssignment %type CbfThruSFElement %type CbfThruSFCategory %type CbfThruSFColumn %type CbfThruSFAssignment %type ErrorCbfThruExtraSFValue %type CbfThruSFLoopStart %type CbfThruSFLoopCategory %type CbfThruSFLoopColumn %type CbfThruSFLoopAssignment %type CbfThruFunction %type DataBlockName %type FunctionName %type SaveFrameName %type CategoryName %type ColumnName %type ItemName %type Value %pure_parser %no_lines %expect 0 %% cbf: cbfstart { $$ = $1; ((void **)context)[3] = NULL; } | CbfThruDBElement { $$ = $1; cbf_failnez (cbf_undo_links (&($$))) cbf_failnez (cbf_find_parent (&($$), $$, CBF_ROOT)) } ; cbfstart: { $$ = ((void **) context) [1]; } ; CbfThruDBName: cbf DataBlockName { cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $1, CBF_DATABLOCK, (cbf_node *) NULL)) if (strlen($2)==0) { cbf_log((cbf_handle)(((void **)context)[2]),"empty data block name", CBF_LOGWARNING|CBF_LOGSTARTLOC); } if (!cbf_find_last_child(&($$),$1,$2) ){ cbf_log((cbf_handle)(((void **)context)[2]),"duplicate data block name", CBF_LOGWARNING|CBF_LOGSTARTLOC); } cbf_failnez (cbf_make_child (&($$), $1, CBF_DATABLOCK, $2)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) } | CbfThruSFElement DataBlockName { cbf_log((cbf_handle)(((void **)context)[2]),"prior save frame not terminated", CBF_LOGWARNING|CBF_LOGSTARTLOC); cbf_failnez (cbf_find_parent (&($$), $1, CBF_ROOT)) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $1, CBF_DATABLOCK, (cbf_node *) NULL)) if (strlen($2)==0) { cbf_log((cbf_handle)(((void **)context)[2]),"empty data block name", CBF_LOGWARNING|CBF_LOGSTARTLOC); } if (!cbf_find_last_child(&($$),$$,$2) ){ cbf_log((cbf_handle)(((void **)context)[2]),"duplicate data block name", CBF_LOGWARNING|CBF_LOGSTARTLOC); } cbf_failnez (cbf_make_child (&($$), $1, CBF_DATABLOCK, $2)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) } ; ErrorCbfWODBName: cbfstart { cbf_failnez (cbf_make_child (&($$), $1, CBF_DATABLOCK, NULL)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_log((cbf_handle)(((void **)context)[2]),"no data block", CBF_LOGWARNING|CBF_LOGSTARTLOC); } ; CbfThruDBElement: CbfThruDBName { $$ = $1; ((void **)context)[3] = NULL; } | CbfThruAssignment { cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $1, CBF_CATEGORY, NULL)) $$ = $1; cbf_failnez (cbf_undo_links (&($$))) cbf_failnez (cbf_find_parent (&($$), $$, CBF_DATABLOCK)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; ((void **)context)[3] = NULL; } | CbfThruLoopAssignment { cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $1, CBF_CATEGORY, NULL)) $$ = $1; cbf_failnez (cbf_undo_links (&($$))) cbf_failnez (cbf_find_parent (&($$), $$, CBF_DATABLOCK)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; ((void **)context)[3] = NULL; } | CbfThruSaveFrame { cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $1, CBF_CATEGORY, NULL)) $$ = $1; cbf_failnez (cbf_undo_links (&($$))) cbf_failnez (cbf_find_parent (&($$), $$, CBF_DATABLOCK)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; ((void **)context)[3] = NULL; } | CbfThruFunction { cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $1, CBF_FUNCTION, NULL)) $$ = $1; cbf_failnez (cbf_undo_links (&($$))) cbf_failnez (cbf_find_parent (&($$), $$, CBF_DATABLOCK)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; ((void **)context)[3] = NULL; } | ErrorCbfThruExtraValue { cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $1, CBF_CATEGORY, NULL)) $$ = $1; cbf_failnez (cbf_undo_links (&($$))) cbf_failnez (cbf_find_parent (&($$), $$, CBF_DATABLOCK)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; ((void **)context)[3] = NULL; } ; CbfThruSFElement: CbfThruDBElement SaveFrameName { cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $1, CBF_CATEGORY, NULL)) cbf_failnez (cbf_make_child (&($$), (cbf_node *) $1, CBF_SAVEFRAME, $2)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) ((void **)context)[3] = NULL; } | CbfThruSFElement SaveFrameName { cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $1, CBF_CATEGORY, NULL)) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $1, CBF_SAVEFRAME, NULL)) cbf_log((cbf_handle)(((void **)context)[2]),"save frame not terminated", CBF_LOGWARNING|CBF_LOGSTARTLOC); $$ = $1; cbf_failnez (cbf_undo_links (&($$))) cbf_failnez (cbf_find_parent (&($$), $$, CBF_DATABLOCK)) cbf_failnez (cbf_make_child (&($$), $$, CBF_SAVEFRAME, $2)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) ((void **)context)[3] = NULL; } | ErrorCbfWODBName SaveFrameName { cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $1, CBF_CATEGORY, NULL)) cbf_failnez (cbf_make_child (&($$), $1, CBF_SAVEFRAME, $2)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) ((void **)context)[3] = NULL; } | CbfThruSFAssignment { cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $1, CBF_CATEGORY, NULL)) $$ = $1; cbf_failnez (cbf_undo_links (&($$))) cbf_failnez (cbf_find_parent (&($$), $$, CBF_SAVEFRAME)) } | CbfThruSFLoopAssignment { cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $1, CBF_CATEGORY, NULL)) $$ = $1; cbf_failnez (cbf_undo_links (&($$))) cbf_failnez (cbf_find_parent (&($$), $$, CBF_SAVEFRAME)) } | ErrorCbfThruExtraSFValue { cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $1, CBF_CATEGORY, NULL)) $$ = $1; cbf_failnez (cbf_undo_links (&($$))) cbf_failnez (cbf_find_parent (&($$), $$, CBF_SAVEFRAME)) } ; CbfThruSaveFrame: CbfThruSFElement SAVEEND { cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $1, CBF_CATEGORY, NULL)) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $1, CBF_SAVEFRAME, NULL)) $$ = $1; cbf_failnez (cbf_undo_links (&($$))) cbf_failnez (cbf_find_parent (&($$), $$, CBF_SAVEFRAME)) } ; CbfThruCategory: CbfThruDBElement CategoryName { cbf_failnez (cbf_make_child (&($$), $1, CBF_CATEGORY, $2)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) ((void **)context)[3] = (void *)$$; } | ErrorCbfWODBName CategoryName { cbf_failnez (cbf_make_child (&($$), $1, CBF_CATEGORY, $2)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) ((void **)context)[3] = (void *)$$; } | CbfThruCategory CategoryName { cbf_log ((cbf_handle)(((void **)context)[2]),"data name with no value1", CBF_LOGERROR|CBF_LOGSTARTLOC); $$ = $1; cbf_failnez (cbf_undo_links (&($$))) cbf_failnez (cbf_find_parent (&($$), $$, CBF_DATABLOCK)) cbf_failnez (cbf_make_child (&($$), $$, CBF_CATEGORY, $2)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) ((void **)context)[3] = (void *)$$; } | CbfThruColumn CategoryName { cbf_log ((cbf_handle)(((void **)context)[2]),"data name with no value", CBF_LOGERROR|CBF_LOGSTARTLOC); $$ = $1; cbf_failnez (cbf_undo_links (&($$))) cbf_failnez (cbf_find_parent (&($$), $$, CBF_DATABLOCK)) cbf_failnez (cbf_make_child (&($$), $$, CBF_CATEGORY, $2)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) ((void **)context)[3] = (void *)$$; } ; CbfThruColumn: CbfThruCategory ColumnName { cbf_failnez (cbf_make_child (&($$), $1, CBF_COLUMN, $2)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $$, CBF_COLUMN, (cbf_node *)(((void **)context)[3]))) } | CbfThruColumn ItemName { cbf_log ((cbf_handle)(((void **)context)[2]),"data name with no value",CBF_LOGERROR|CBF_LOGSTARTLOC); $$ = $1; cbf_failnez (cbf_undo_links (&($$))) cbf_failnez (cbf_find_parent (&($$), $$, CBF_DATABLOCK)) cbf_failnez (cbf_make_new_child (&($$), $$, CBF_CATEGORY, $2)) ((void **)context)[3] = (void *)$$; cbf_failnez (cbf_make_child (&($$), $$, CBF_COLUMN, cbf_copy_string(NULL,$2,0))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $$, CBF_COLUMN, (cbf_node *)(((void **)context)[3]))) } | CbfThruDBElement ItemName { cbf_failnez (cbf_make_new_child (&($$), $1, CBF_CATEGORY, $2)) ((void **)context)[3] = (void *)$$; cbf_failnez (cbf_make_child (&($$), $$, CBF_COLUMN, cbf_copy_string(NULL,$2,0))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $$, CBF_COLUMN, (cbf_node *)(((void **)context)[3]))) } | ErrorCbfWODBName ItemName { cbf_failnez (cbf_make_new_child (&($$), $1, CBF_CATEGORY, $2)) ((void **)context)[3] = (void *)$$; cbf_failnez (cbf_make_child (&($$), $$, CBF_COLUMN, cbf_copy_string(NULL,$2,0))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $$, CBF_COLUMN, (cbf_node *)(((void **)context)[3]))) } ; CbfThruAssignment: CbfThruColumn Value { $$ = $1; cbf_failnez (cbf_set_columnrow ($$, 0, $2, 1)) cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $2, CBF_VALUE, (cbf_node *) $$)) } ; ErrorCbfThruExtraValue: CbfThruAssignment Value { $$ = $1; cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_log ((cbf_handle)(((void **)context)[2]),"value without tag",CBF_LOGERROR|CBF_LOGSTARTLOC); cbf_failnez(cbf_free_text(&($2),NULL)) } | ErrorCbfThruExtraValue Value { $$ = $1; cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_log ((cbf_handle)(((void **)context)[2]),"value without tag",CBF_LOGERROR|CBF_LOGSTARTLOC); cbf_failnez(cbf_free_text(&($2),NULL)) } | CbfThruLoopStart Value { $$ = $1; cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_log ((cbf_handle)(((void **)context)[2]),"loop value without tag",CBF_LOGERROR|CBF_LOGSTARTLOC); cbf_failnez(cbf_free_text(&($2),NULL)) } ; CbfThruLoopStart: CbfThruDBElement Loop { cbf_failnez (cbf_make_node (&($$), CBF_LINK, NULL, NULL)) cbf_failnez (cbf_set_link ($$, $1)) } | ErrorCbfWODBName Loop { cbf_failnez (cbf_make_node (&($$), CBF_LINK, NULL, NULL)) cbf_failnez (cbf_set_link ($$, $1)) } | CbfThruLoopStart Loop { cbf_log ((cbf_handle)(((void **)context)[2]),"redundant \"loop_\" ",CBF_LOGERROR|CBF_LOGSTARTLOC); cbf_failnez (cbf_make_node (&($$), CBF_LINK, NULL, NULL)) cbf_failnez (cbf_set_link ($$, $1)) } ; CbfThruLoopCategory: CbfThruLoopStart CategoryName { cbf_failnez (cbf_make_child (&($$), $1, CBF_CATEGORY, $2)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; ((void **)context)[3] = (void *)$$; cbf_failnez (cbf_set_link ($1, $$)) ((void **)context)[3] = (void *)$$; cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) $$ = $1; } | CbfThruLoopColumn CategoryName { cbf_failnez (cbf_find_parent (&($$), $1, CBF_DATABLOCK)) cbf_failnez (cbf_make_child (&($$), $$, CBF_CATEGORY, $2)) cbf_failnez (cbf_set_link ($1, $$)) ((void **)context)[3] = (void *)$$; cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) $$ = $1; } ; CbfThruLoopColumn: CbfThruLoopStart ItemName { cbf_failnez (cbf_make_new_child (&($$), $1, CBF_CATEGORY, $2)) ((void **)context)[3] = (void *)$$; cbf_failnez (cbf_make_child (&($$), $$, CBF_COLUMN, cbf_copy_string(NULL,$2,0))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $$, CBF_COLUMN, (cbf_node *)(((void **)context)[3]))) cbf_failnez (cbf_set_link ($1, $$)) cbf_failnez (cbf_add_link ($1, $$)) $$ = $1; } | CbfThruLoopColumn ItemName { $$ = ((void **)context)[3]; cbf_failnez (cbf_make_child (&($$), $$, CBF_COLUMN, $2)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $$, CBF_COLUMN, (cbf_node *)(((void **)context)[3]))) cbf_failnez (cbf_set_link ($1, $$)) cbf_failnez (cbf_add_link ($1, $$)) $$ = $1; } | CbfThruLoopCategory ColumnName { cbf_failnez (cbf_make_child (&($$), $1, CBF_COLUMN, $2)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $$, CBF_COLUMN, (cbf_node *)(((void **)context)[3]))) cbf_failnez (cbf_set_link ($1, $$)) cbf_failnez (cbf_add_link ($1, $$)) $$ = $1; } ; CbfThruLoopAssignment: CbfThruLoopColumn Value { $$ = $1; cbf_failnez (cbf_shift_link ($$)) cbf_failnez (cbf_add_columnrow ($$, $2)) cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $2, CBF_VALUE, (cbf_node *) $$)) } | CbfThruLoopAssignment Value { $$ = $1; cbf_failnez (cbf_shift_link ($$)) cbf_failnez (cbf_add_columnrow ($$, $2)) cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $2, CBF_VALUE, (cbf_node *) $$)) } ; CbfThruSFCategory: CbfThruSFElement CategoryName { cbf_failnez (cbf_make_child (&($$), $1, CBF_CATEGORY, $2)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; ((void **)context)[3] = (void *)$$; } | CbfThruSFCategory CategoryName { cbf_log((cbf_handle)(((void **)context)[2]), "data name with no value", CBF_LOGERROR|CBF_LOGSTARTLOC); $$ = $1; cbf_failnez (cbf_undo_links (&($$))) cbf_failnez (cbf_find_parent (&($$), $$, CBF_SAVEFRAME)) cbf_failnez (cbf_make_child (&($$), $$, CBF_CATEGORY, $2)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; ((void **)context)[3] = (void *)$$; } | CbfThruSFColumn CategoryName { cbf_log((cbf_handle)(((void **)context)[2]), "data name with no value", CBF_LOGERROR|CBF_LOGSTARTLOC); $$ = $1; cbf_failnez (cbf_undo_links (&($$))) cbf_failnez (cbf_find_parent (&($$), $$, CBF_SAVEFRAME)) cbf_failnez (cbf_make_child (&($$), $$, CBF_CATEGORY, $2)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; ((void **)context)[3] = (void *)$$; } ; CbfThruSFColumn: CbfThruSFCategory ColumnName { cbf_failnez (cbf_make_child (&($$), $1, CBF_COLUMN, $2)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $$, CBF_COLUMN, (cbf_node *)(((void **)context)[3]))) } | CbfThruSFElement ItemName { cbf_failnez (cbf_make_new_child (&($$), $1, CBF_CATEGORY, $2)) ((void **)context)[3] = (void *)$$; cbf_failnez (cbf_make_child (&($$), $$, CBF_COLUMN, cbf_copy_string(NULL,$2,0))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $$, CBF_COLUMN, (cbf_node *)(((void **)context)[3]))) } | CbfThruSFColumn ItemName { cbf_log((cbf_handle)(((void **)context)[2]), "data name with no value", CBF_LOGERROR|CBF_LOGSTARTLOC); $$ = $1; cbf_failnez (cbf_undo_links (&($$))) cbf_failnez (cbf_find_parent (&($$), $$, CBF_SAVEFRAME)) cbf_failnez (cbf_make_new_child (&($$), $$, CBF_CATEGORY, $2)) ((void **)context)[3] = (void *)$$; cbf_failnez (cbf_make_child (&($$), $$, CBF_COLUMN, cbf_copy_string(NULL,$2,0))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $$, CBF_COLUMN, (cbf_node *)(((void **)context)[3]))) } ; CbfThruSFAssignment: CbfThruSFColumn Value { $$ = $1; cbf_failnez (cbf_set_columnrow ($$, 0, $2, 1)) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $2, CBF_VALUE, (cbf_node *) $$)) } ; ErrorCbfThruExtraSFValue: CbfThruSFAssignment Value { $$ = $1; cbf_log ((cbf_handle)(((void **)context)[2]),"value without tag",CBF_LOGERROR|CBF_LOGSTARTLOC); cbf_failnez(cbf_free_text(&($2), NULL)) } | ErrorCbfThruExtraSFValue Value { $$ = $1; cbf_log ((cbf_handle)(((void **)context)[2]),"value without tag",CBF_LOGERROR|CBF_LOGSTARTLOC); cbf_failnez(cbf_free_text(&($2), NULL)) } | CbfThruSFLoopStart Value { $$ = $1; cbf_log ((cbf_handle)(((void **)context)[2]),"loop value without tag",CBF_LOGERROR|CBF_LOGSTARTLOC); cbf_failnez(cbf_free_text(&($2), NULL)) } ; CbfThruSFLoopStart: CbfThruSFElement Loop { cbf_failnez (cbf_make_node (&($$), CBF_LINK, NULL, NULL)) cbf_failnez (cbf_set_link ($$, $1)) } | CbfThruSFLoopStart Loop { cbf_log ((cbf_handle)(((void **)context)[2]),"redundant \"loop_\" ",CBF_LOGERROR|CBF_LOGSTARTLOC); cbf_failnez (cbf_make_node (&($$), CBF_LINK, NULL, NULL)) cbf_failnez (cbf_set_link ($$, $1)) } ; CbfThruSFLoopCategory: CbfThruSFLoopStart CategoryName { cbf_failnez (cbf_make_child (&($$), $1, CBF_CATEGORY, $2)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; cbf_failnez (cbf_set_link ($1, $$)) ((void **)context)[3] = (void *)$$; $$ = $1; } | CbfThruSFLoopColumn CategoryName { cbf_failnez (cbf_find_parent (&($$), $1, CBF_SAVEFRAME)) cbf_failnez (cbf_make_child (&($$), $$, CBF_CATEGORY, $2)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; cbf_failnez (cbf_set_link ($1, $$)) ((void **)context)[3] = (void *)$$; $$ = $1; } ; CbfThruSFLoopColumn: CbfThruSFLoopStart ItemName { cbf_failnez (cbf_make_new_child (&($$), $1, CBF_CATEGORY, $2)) cbf_failnez (cbf_make_child (&($$), $$, CBF_COLUMN, cbf_copy_string(NULL,$2,0))) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $$, CBF_COLUMN, (cbf_node *)(((void **)context)[3]))) cbf_failnez (cbf_set_link ($1, $$)) cbf_failnez (cbf_add_link ($1, $$)) $$ = $1; } | CbfThruSFLoopColumn ItemName { $$ = ((void **)context)[3]; cbf_failnez (cbf_make_child (&($$), $$, CBF_COLUMN, $2)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $$, CBF_COLUMN, (cbf_node *)(((void **)context)[3]))) cbf_failnez (cbf_set_link ($1, $$)) cbf_failnez (cbf_add_link ($1, $$)) $$ = $1; } | CbfThruSFLoopCategory ColumnName { cbf_failnez (cbf_make_child (&($$), $1, CBF_COLUMN, $2)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $$, CBF_COLUMN, (cbf_node *)(((void **)context)[3]))) cbf_failnez (cbf_set_link ($1, $$)) cbf_failnez (cbf_add_link ($1, $$)) $$ = $1; } ; CbfThruSFLoopAssignment: CbfThruSFLoopColumn Value { $$ = $1; cbf_failnez (cbf_shift_link ($$)) cbf_failnez (cbf_add_columnrow ($$, $2)) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $2, CBF_VALUE, (cbf_node *) $$)) } | CbfThruSFLoopAssignment Value { $$ = $1; cbf_failnez (cbf_shift_link ($$)) cbf_failnez (cbf_add_columnrow ($$, $2)) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $2, CBF_VALUE, (cbf_node *) $$)) } ; CbfThruFunction: CbfThruDBElement FunctionName Value { cbf_failnez (cbf_make_new_child (&($$), $1, CBF_FUNCTION, $2)) ((cbf_handle)(((void **)context)[2]))->node=(cbf_node *)$$; cbf_failnez(cbf_apply_ws((cbf_handle)(((void **)context)[2]))) ((void **)context)[3] = (void *)$$; cbf_failnez (cbf_make_child (&($$), $1, CBF_COLUMN, $2)) cbf_failnez (cbf_set_columnrow ($$, 0, $3, 1)) cbf_failnez (cbf_validate ((cbf_handle)(((void **)context)[2]), (cbf_node *) $3, CBF_VALUE, (cbf_node *) $$)) } ; Loop: LOOP ; DataBlockName: DATA { $$ = $1; } ; SaveFrameName: SAVE { $$ = $1; } ; CategoryName: CATEGORY { $$ = $1; } ; ColumnName: COLUMN { $$ = $1; } ; ItemName: ITEM { $$ = $1; } ; FunctionName: DEFINE { $$ = $1; } ; Value: STRING { $$ = $1; } | CBFWORD { $$ = $1; } | BINARY { $$ = $1; } ; %% #ifdef __cplusplus } #endif ./CBFlib-0.9.2.2/src/md5c.c0000644000076500007650000002455611603702106013375 0ustar yayayaya/* MD5C.C - RSA Data Security, Inc., MD5 message-digest algorithm */ /* Copyright (C) 1991-2, RSA Data Security, Inc. Created 1991. All rights reserved. License to copy and use this software is granted provided that it is identified as the "RSA Data Security, Inc. MD5 Message-Digest Algorithm" in all material mentioning or referencing this software or this function. License is also granted to make and use derivative works provided that such works are identified as "derived from the RSA Data Security, Inc. MD5 Message-Digest Algorithm" in all material mentioning or referencing the derived work. RSA Data Security, Inc. makes no representations concerning either the merchantability of this software or the suitability of this software for any particular purpose. It is provided "as is" without express or implied warranty of any kind. These notices must be retained in any copies of any part of this documentation and/or software. */ #include "global.h" #include "md5.h" /* Constants for MD5Transform routine. */ #define S11 7 #define S12 12 #define S13 17 #define S14 22 #define S21 5 #define S22 9 #define S23 14 #define S24 20 #define S31 4 #define S32 11 #define S33 16 #define S34 23 #define S41 6 #define S42 10 #define S43 15 #define S44 21 static void MD5Transform PROTO_LIST ((UINT4 [4], unsigned char [64])); static void Encode PROTO_LIST ((unsigned char *, UINT4 *, unsigned int)); static void Decode PROTO_LIST ((UINT4 *, unsigned char *, unsigned int)); static void MD5_memcpy PROTO_LIST ((POINTER, POINTER, unsigned int)); static void MD5_memset PROTO_LIST ((POINTER, int, unsigned int)); static unsigned char PADDING[64] = { 0x80, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0 }; /* F, G, H and I are basic MD5 functions. */ #define F(x, y, z) (((x) & (y)) | ((~x) & (z))) #define G(x, y, z) (((x) & (z)) | ((y) & (~z))) #define H(x, y, z) ((x) ^ (y) ^ (z)) #define I(x, y, z) ((y) ^ ((x) | (~z))) /* ROTATE_LEFT rotates x left n bits. */ /* #define ROTATE_LEFT(x, n) (((x) << (n)) | ((x) >> (32-(n)))) */ #define ROTATE_LEFT(x, n) (((x) << (n)) | (((x) & 0x0FFFFFFFF) >> (32 - (n)))) /* FF, GG, HH, and II transformations for rounds 1, 2, 3, and 4. Rotation is separate from addition to prevent recomputation. */ #define FF(a, b, c, d, x, s, ac) { \ (a) += F ((b), (c), (d)) + (x) + (UINT4)(ac); \ (a) = ROTATE_LEFT ((a), (s)); \ (a) += (b); \ } #define GG(a, b, c, d, x, s, ac) { \ (a) += G ((b), (c), (d)) + (x) + (UINT4)(ac); \ (a) = ROTATE_LEFT ((a), (s)); \ (a) += (b); \ } #define HH(a, b, c, d, x, s, ac) { \ (a) += H ((b), (c), (d)) + (x) + (UINT4)(ac); \ (a) = ROTATE_LEFT ((a), (s)); \ (a) += (b); \ } #define II(a, b, c, d, x, s, ac) { \ (a) += I ((b), (c), (d)) + (x) + (UINT4)(ac); \ (a) = ROTATE_LEFT ((a), (s)); \ (a) += (b); \ } /* MD5 initialization. Begins an MD5 operation, writing a new context. */ void MD5Init (context) MD5_CTX *context; /* context */ { context->count[0] = context->count[1] = 0; /* Load magic initialization constants. */ context->state[0] = 0x67452301; context->state[1] = 0xefcdab89; context->state[2] = 0x98badcfe; context->state[3] = 0x10325476; } /* MD5 block update operation. Continues an MD5 message-digest operation, processing another message block, and updating the context. */ void MD5Update (context, input, inputLen) MD5_CTX *context; /* context */ unsigned char *input; /* input block */ unsigned int inputLen; /* length of input block */ { unsigned int i, index, partLen; UINT4 I1, I2, S; /* Compute number of bytes mod 64 */ index = (unsigned int)((context->count[0] >> 3) & 0x3F); /* Update number of bits */ I1 = ((UINT4) inputLen) << 3; I2 = ((UINT4) context->count [0]); context->count[0] = S = I1 + I2; if (((~S & (I1 | I2)) | (I1 & I2)) & 0x080000000) context->count[1]++; context->count[1] += ((UINT4) inputLen >> 29); partLen = 64 - index; /* Transform as many times as possible. */ if (inputLen >= partLen) { MD5_memcpy ((POINTER)&context->buffer[index], (POINTER)input, partLen); MD5Transform (context->state, context->buffer); for (i = partLen; i + 63 < inputLen; i += 64) MD5Transform (context->state, &input[i]); index = 0; } else i = 0; /* Buffer remaining input */ MD5_memcpy ((POINTER)&context->buffer[index], (POINTER)&input[i], inputLen-i); } /* MD5 finalization. Ends an MD5 message-digest operation, writing the the message digest and zeroizing the context. */ void MD5Final (digest, context) unsigned char digest[16]; /* message digest */ MD5_CTX *context; /* context */ { unsigned char bits[8]; unsigned int index, padLen; /* Save number of bits */ Encode (bits, context->count, 8); /* Pad out to 56 mod 64. */ index = (unsigned int)((context->count[0] >> 3) & 0x3f); padLen = (index < 56) ? (56 - index) : (120 - index); MD5Update (context, PADDING, padLen); /* Append length (before padding) */ MD5Update (context, bits, 8); /* Store state in digest */ Encode (digest, context->state, 16); /* Zeroize sensitive information. */ MD5_memset ((POINTER)context, 0, sizeof (*context)); } /* MD5 basic transformation. Transforms state based on block. */ static void MD5Transform (state, block) UINT4 state[4]; unsigned char block[64]; { UINT4 a = state[0], b = state[1], c = state[2], d = state[3], x[16]; Decode (x, block, 64); /* Round 1 */ FF (a, b, c, d, x[ 0], S11, 0xd76aa478); /* 1 */ FF (d, a, b, c, x[ 1], S12, 0xe8c7b756); /* 2 */ FF (c, d, a, b, x[ 2], S13, 0x242070db); /* 3 */ FF (b, c, d, a, x[ 3], S14, 0xc1bdceee); /* 4 */ FF (a, b, c, d, x[ 4], S11, 0xf57c0faf); /* 5 */ FF (d, a, b, c, x[ 5], S12, 0x4787c62a); /* 6 */ FF (c, d, a, b, x[ 6], S13, 0xa8304613); /* 7 */ FF (b, c, d, a, x[ 7], S14, 0xfd469501); /* 8 */ FF (a, b, c, d, x[ 8], S11, 0x698098d8); /* 9 */ FF (d, a, b, c, x[ 9], S12, 0x8b44f7af); /* 10 */ FF (c, d, a, b, x[10], S13, 0xffff5bb1); /* 11 */ FF (b, c, d, a, x[11], S14, 0x895cd7be); /* 12 */ FF (a, b, c, d, x[12], S11, 0x6b901122); /* 13 */ FF (d, a, b, c, x[13], S12, 0xfd987193); /* 14 */ FF (c, d, a, b, x[14], S13, 0xa679438e); /* 15 */ FF (b, c, d, a, x[15], S14, 0x49b40821); /* 16 */ /* Round 2 */ GG (a, b, c, d, x[ 1], S21, 0xf61e2562); /* 17 */ GG (d, a, b, c, x[ 6], S22, 0xc040b340); /* 18 */ GG (c, d, a, b, x[11], S23, 0x265e5a51); /* 19 */ GG (b, c, d, a, x[ 0], S24, 0xe9b6c7aa); /* 20 */ GG (a, b, c, d, x[ 5], S21, 0xd62f105d); /* 21 */ GG (d, a, b, c, x[10], S22, 0x2441453); /* 22 */ GG (c, d, a, b, x[15], S23, 0xd8a1e681); /* 23 */ GG (b, c, d, a, x[ 4], S24, 0xe7d3fbc8); /* 24 */ GG (a, b, c, d, x[ 9], S21, 0x21e1cde6); /* 25 */ GG (d, a, b, c, x[14], S22, 0xc33707d6); /* 26 */ GG (c, d, a, b, x[ 3], S23, 0xf4d50d87); /* 27 */ GG (b, c, d, a, x[ 8], S24, 0x455a14ed); /* 28 */ GG (a, b, c, d, x[13], S21, 0xa9e3e905); /* 29 */ GG (d, a, b, c, x[ 2], S22, 0xfcefa3f8); /* 30 */ GG (c, d, a, b, x[ 7], S23, 0x676f02d9); /* 31 */ GG (b, c, d, a, x[12], S24, 0x8d2a4c8a); /* 32 */ /* Round 3 */ HH (a, b, c, d, x[ 5], S31, 0xfffa3942); /* 33 */ HH (d, a, b, c, x[ 8], S32, 0x8771f681); /* 34 */ HH (c, d, a, b, x[11], S33, 0x6d9d6122); /* 35 */ HH (b, c, d, a, x[14], S34, 0xfde5380c); /* 36 */ HH (a, b, c, d, x[ 1], S31, 0xa4beea44); /* 37 */ HH (d, a, b, c, x[ 4], S32, 0x4bdecfa9); /* 38 */ HH (c, d, a, b, x[ 7], S33, 0xf6bb4b60); /* 39 */ HH (b, c, d, a, x[10], S34, 0xbebfbc70); /* 40 */ HH (a, b, c, d, x[13], S31, 0x289b7ec6); /* 41 */ HH (d, a, b, c, x[ 0], S32, 0xeaa127fa); /* 42 */ HH (c, d, a, b, x[ 3], S33, 0xd4ef3085); /* 43 */ HH (b, c, d, a, x[ 6], S34, 0x4881d05); /* 44 */ HH (a, b, c, d, x[ 9], S31, 0xd9d4d039); /* 45 */ HH (d, a, b, c, x[12], S32, 0xe6db99e5); /* 46 */ HH (c, d, a, b, x[15], S33, 0x1fa27cf8); /* 47 */ HH (b, c, d, a, x[ 2], S34, 0xc4ac5665); /* 48 */ /* Round 4 */ II (a, b, c, d, x[ 0], S41, 0xf4292244); /* 49 */ II (d, a, b, c, x[ 7], S42, 0x432aff97); /* 50 */ II (c, d, a, b, x[14], S43, 0xab9423a7); /* 51 */ II (b, c, d, a, x[ 5], S44, 0xfc93a039); /* 52 */ II (a, b, c, d, x[12], S41, 0x655b59c3); /* 53 */ II (d, a, b, c, x[ 3], S42, 0x8f0ccc92); /* 54 */ II (c, d, a, b, x[10], S43, 0xffeff47d); /* 55 */ II (b, c, d, a, x[ 1], S44, 0x85845dd1); /* 56 */ II (a, b, c, d, x[ 8], S41, 0x6fa87e4f); /* 57 */ II (d, a, b, c, x[15], S42, 0xfe2ce6e0); /* 58 */ II (c, d, a, b, x[ 6], S43, 0xa3014314); /* 59 */ II (b, c, d, a, x[13], S44, 0x4e0811a1); /* 60 */ II (a, b, c, d, x[ 4], S41, 0xf7537e82); /* 61 */ II (d, a, b, c, x[11], S42, 0xbd3af235); /* 62 */ II (c, d, a, b, x[ 2], S43, 0x2ad7d2bb); /* 63 */ II (b, c, d, a, x[ 9], S44, 0xeb86d391); /* 64 */ state[0] += a; state[1] += b; state[2] += c; state[3] += d; /* Zeroize sensitive information. */ MD5_memset ((POINTER)x, 0, sizeof (x)); } /* Encodes input (UINT4) into output (unsigned char). Assumes len is a multiple of 4. */ static void Encode (output, input, len) unsigned char *output; UINT4 *input; unsigned int len; { unsigned int i, j; for (i = 0, j = 0; j < len; i++, j += 4) { output[j] = (unsigned char)(input[i] & 0xff); output[j+1] = (unsigned char)((input[i] >> 8) & 0xff); output[j+2] = (unsigned char)((input[i] >> 16) & 0xff); output[j+3] = (unsigned char)((input[i] >> 24) & 0xff); } } /* Decodes input (unsigned char) into output (UINT4). Assumes len is a multiple of 4. */ static void Decode (output, input, len) UINT4 *output; unsigned char *input; unsigned int len; { unsigned int i, j; for (i = 0, j = 0; j < len; i++, j += 4) output[i] = ((UINT4)input[j]) | (((UINT4)input[j+1]) << 8) | (((UINT4)input[j+2]) << 16) | (((UINT4)input[j+3]) << 24); } /* Note: Replace "for loop" with standard memcpy if possible. */ static void MD5_memcpy (output, input, len) POINTER output; POINTER input; unsigned int len; { unsigned int i; for (i = 0; i < len; i++) output[i] = input[i]; } /* Note: Replace "for loop" with standard memset if possible. */ static void MD5_memset (output, value, len) POINTER output; int value; unsigned int len; { unsigned int i; for (i = 0; i < len; i++) ((char *)output)[i] = (char)value; } ./CBFlib-0.9.2.2/src/cbf_string.c0000644000076500007650000004373311603702106014663 0ustar yayayaya/********************************************************************** * cbf_string -- case-insensitive string comparisons * * * * Version 0.8.0 20 July 2008 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifdef __cplusplus extern "C" { #endif #include #include #include "cbf.h" #include "cbf_string.h" /* Case-insensitive strcmp */ int cbf_cistrcmp (const char *s1, const char *s2) { while (*s1 && toupper (*s1) == toupper (*s2)) { s1++; s2++; } return toupper (*s1) - toupper (*s2); } /* Case-insensitive strncmp */ int cbf_cistrncmp (const char *s1, const char *s2, size_t n) { while (n > 0 && *s1 && toupper (*s1) == toupper (*s2)) { n--; s1++; s2++; } if (n == 0) return 0; return toupper (*s1) - toupper (*s2); } /* swap bytes in an array (local copy of swab to deal with systems that lack swab) */ int cbf_swab(const void * src, void * dst, size_t len) { #ifndef USE_SWAB unsigned char *p1; unsigned char *p2; #endif if (len&1) return CBF_ARGUMENT; #ifndef USE_SWAB p1 = (unsigned char *)src; p2 = (unsigned char *)dst; while (len) { p2[1] = p1[0]; p2[0] = p1[1]; p1+=2; p2+=2; len -=2; } #else swab(src,dst,len); #endif return 0; } #ifdef __cplusplus } #endif ./CBFlib-0.9.2.2/src/cbf_ascii.c0000644000076500007650000007606311603702106014447 0ustar yayayaya/********************************************************************** * cbf_ascii -- write plain ASCII values * * * * Version 0.7.6 14 July 2006 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifdef __cplusplus extern "C" { #endif #include "cbf.h" #include "cbf_ascii.h" #include "cbf_tree.h" #include "cbf_file.h" #include #include #include #include /* Format the next, possibly folded text line in fline, updating the pointer in string to be ready for the next pass. fline_size is the valid line length. fline must be one longer to allow for termination.*/ int cbf_foldtextline(const char** string, char* fline, int fline_size, int unfoldme, int foldme, char termc ) { const char *c; char *ofl; int ipos, left=fline_size; int savbpos, savbleft; c = *string; if (foldme && (termc == '\'' || termc == '\"') ) left -=2; ofl = fline; savbpos = -1; savbleft = left+1; /* protect folded lines that begin with ; */ if (c[0] == ';' && termc == ';' && (isspace(c[1])|| !c[1]) ){ *ofl++ = ';'; *ofl++ = '\\'; *ofl++ = '\n'; *string = c+1; return 0; } for (ipos=0; c[ipos]; ipos++) { /* save the last blank or tab to break on */ if(( c[ipos] == ' ' || c[ipos] == '\t' ) && left < fline_size) { savbpos = ipos; savbleft = left; } /* If this is a bracketed construct, break on ',' or the terminating character not at the beginning */ if ((termc==')' || termc==']' || termc==',') && ((c[ipos]==termc || c[ipos]==',') && left-1 < fline_size)) { savbpos = ipos+1; savbleft = left-1; } /* check for a backslash */ if ( foldme && c[ipos] == '\\') { /* if unfolding, ignore "\\\n" */ if (unfoldme) { if (c[ipos+1] == '\n' || c[ipos+1] == '\0') { ipos++; continue; } } /* if the backslash would be at the end of the line insert "\\" and end the line */ if ( foldme && left < 2) { *ofl++ = '\\'; *ofl = '\0'; *string = c+ipos; return 0; } } /* check if folding would bring "; " to the front of a line if so, end here */ if ( foldme && left == 2 && c[ipos+1]==';' && isspace(c[ipos+2]) ) { *ofl++ = '\\'; *ofl = '\0'; *string = c+ipos; return 0; } /* now, see if the line has ended by itself */ if ( c[ipos+1] == '\n' || !c[ipos+1]) { *ofl++ = c[ipos]; *ofl = '\0'; *string = c+ipos+1; if (c[ipos+1] == '\n') (*string)++; if (c[ipos+1]) return 0; return 1; } /* see if we must fold */ if ( foldme && left < 2) { if (savbleft > left && savbleft < fline_size) { ipos = savbpos; ofl = ofl+left-savbleft; } *ofl++ = '\\'; *ofl = '\0'; *string = c+ipos; return 0; } *ofl++ = c[ipos]; left--; } *ofl ='\0'; *string = c+ipos; return 1; } /* Write an ascii value */ int cbf_write_ascii (cbf_handle handle, const char *string, cbf_file *file) { static const char missing [] = { CBF_TOKEN_WORD, '?', '\0' }; int end, lw, lc, foldme=0, unfoldme=0; char initc=';', termc=';'; unsigned int column; const char *c; char delim, adelim; char buffer[80]; char fline[2049]; /* Check the arguments */ if (!string) string = missing; else if (*string != CBF_TOKEN_WORD && *string != CBF_TOKEN_SQSTRING && *string != CBF_TOKEN_DQSTRING && *string != CBF_TOKEN_SCSTRING && *string != CBF_TOKEN_TSQSTRING && *string != CBF_TOKEN_TDQSTRING && *string != CBF_TOKEN_BKTSTRING && *string != CBF_TOKEN_BRCSTRING && *string != CBF_TOKEN_PRNSTRING && *string != CBF_TOKEN_NULL) return CBF_ARGUMENT; /* Get the current column */ cbf_failnez (cbf_get_filecoordinates (file, NULL, &column)) /* Do we need to start a new line? */ if (column) { if (*string == CBF_TOKEN_SCSTRING) { cbf_failnez (cbf_write_character (file, '\n')) } else { if (*string == CBF_TOKEN_WORD || *string == CBF_TOKEN_NULL ) end = column + 3; else if (*string == CBF_TOKEN_TSQSTRING || *string == CBF_TOKEN_TDQSTRING) end = column + 6; else if (*string == CBF_TOKEN_PRNSTRING || *string == CBF_TOKEN_BKTSTRING || *string == CBF_TOKEN_BKTSTRING) end = column + 5; else end = column + 1; for (c = string + 1; *c && end <= (file->columnlimit); c++) { if (*c == '\t') end = (end & ~0x07) + 8; else end = end + 1; } if (end > (file->columnlimit)) cbf_failnez (cbf_write_character (file, '\n')) } } /* Write the value */ switch (*string) { /* Simple word? */ case CBF_TOKEN_WORD: case CBF_TOKEN_NULL: if (strlen(string+1) <= file->columnlimit && *(string+1)!='"' && *(string+1)!='\'' && !strpbrk(string+1," \t\n\r") && !(strlen(string+1) == file->columnlimit && *(string+1)==';') ) { if (strlen(string+1) != file->columnlimit) cbf_failnez (cbf_write_character (file, ' ')) cbf_failnez (cbf_write_string (file, string + 1)) break; } /* Single line? */ case CBF_TOKEN_SQSTRING: case CBF_TOKEN_DQSTRING: if (*string == CBF_TOKEN_SQSTRING) { delim = '\''; adelim = '"'; } else { delim = '"'; adelim = '\''; } if (strchr(string+1,delim) && !strchr(string+1,adelim)) { delim = adelim; } if (strlen(string+1)+2 < file->columnlimit && !strchr(string+1,delim)) { if (strlen(string+1)+3 < file->columnlimit) { cbf_failnez (cbf_write_character (file, ' ')) } cbf_failnez (cbf_write_character (file, delim)) cbf_failnez (cbf_write_string (file, string + 1)) cbf_failnez (cbf_write_character (file, delim)) } else { sprintf(buffer, "output line %u(%u) folded",1+file->line,1+file->column); cbf_log(handle, buffer, CBF_LOGWARNING|CBF_LOGSTARTLOC); if (file->column > 0) { cbf_failnez (cbf_write_character (file, '\n')) } cbf_failnez (cbf_write_string (file, ";\\\n")) end = 0; for (c = string + 1; *c; c++) { if (((file->column > file->columnlimit-10)&& (isspace(*c)||*c=='\\'))|| file->column > file->columnlimit-2) { cbf_failnez (cbf_write_string (file, "\\\n")) end = 0; } cbf_failnez (cbf_write_character (file, *c)) if (*c == ';' && end == 0 && (isspace(*(c+1))||!*(c+1))) { cbf_failnez (cbf_write_string (file, "\\\n")) end = 0; continue; } if (*c == '\n') end = 0; else end = 1; } cbf_failnez (cbf_write_string (file, "\\\n;\n")) end = 0; } break; /* Multiple lines? */ case CBF_TOKEN_SCSTRING: unfoldme = 0; foldme = 0; if (*(string+1)=='\\' && *(string+2)=='\n' ) unfoldme=2; lw = 0; lc = 1; end = 1; for (c = string +1+unfoldme; *c; c++) { if (*c == ';' && end == 0 && (isspace(*(c+1))|| !*(c+1))) foldme=1; if (*c == '\n') { if (!unfoldme || *(c-1) !='\\') { end = 0; if (lc > lw) lw = lc; lc = 0; } else { lc--; } } else { lc++; end = 1; } } if (lc > lw) lw = lc; if ( foldme || lw > file->columnlimit || (unfoldme && *(c-1)=='\\')) { sprintf(buffer, "output line %u(%u) folded",1+file->line,1+file->column); cbf_log(handle, buffer, CBF_LOGWARNING|CBF_LOGSTARTLOC); cbf_failnez (cbf_write_string (file, ";\\\n")) end = 0; foldme = 1; } else { cbf_failnez (cbf_write_character (file, ';')) end = 1; foldme = 0; } for (c = string + 1+ unfoldme; *c; ) { int done; done = cbf_foldtextline(&c, fline, file->columnlimit, unfoldme, foldme, ';'); cbf_failnez (cbf_write_string (file, fline)) if ( !done ) cbf_failnez (cbf_write_character (file, '\n')) } if (unfoldme && ((c > string+1+unfoldme && *(c-1)=='\\') || (c > string+2+unfoldme && *(c-1)=='\0' && *(c-2)=='\\'))) { cbf_failnez (cbf_write_string (file, "\\\n;\n")) } else { if (file->column) { cbf_failnez (cbf_write_character (file, '\n')) } cbf_failnez (cbf_write_string (file, ";\n")) } end = 0; break; case CBF_TOKEN_TSQSTRING: case CBF_TOKEN_TDQSTRING: case CBF_TOKEN_PRNSTRING: case CBF_TOKEN_BRCSTRING: case CBF_TOKEN_BKTSTRING: unfoldme = 0; foldme = 0; switch (*string) { case CBF_TOKEN_TSQSTRING: initc = termc = '\''; if (!(file->write_headers & CBF_PARSE_TQ)) {initc = termc = ';'; foldme= 1;} break; case CBF_TOKEN_TDQSTRING: initc = termc = '"'; if (!(file->write_headers & CBF_PARSE_TQ)) {initc = termc = ';'; foldme= 1;} break; case CBF_TOKEN_PRNSTRING: initc = '('; termc = ')'; if (!(file->write_headers & CBF_PARSE_PRN)) { if (file->write_headers & CBF_PARSE_BRC){ initc = '{'; termc = '}'; } else { initc = termc = ';'; foldme= 1; } } break; case CBF_TOKEN_BRCSTRING: initc = '{'; termc = '}'; if (!(file->write_headers & CBF_PARSE_BRC)) {initc = termc = ';'; foldme= 1;} break; case CBF_TOKEN_BKTSTRING: initc = '['; termc = ']'; if (!(file->write_headers & CBF_PARSE_PRN)) { if (file->write_headers & CBF_PARSE_BRC){ initc = '{'; termc = '}'; } else { initc = termc = ';'; foldme= 1; } } break; } if (*(string+1)=='\\' && *(string+2)=='\n' ) unfoldme=2; lw = 0; lc = 1; end = 1; for (c = string +1+unfoldme; *c; c++) { if (termc==';' && *c == ';' && end == 0 && (isspace(*(c+1))|| !*(c+1))) foldme=1; if (*c == '\n') { if (!unfoldme || *(c-1) !='\\') { end = 0; if (lc > lw) lw = lc; lc = 0; } else { lc--; } } else { lc++; end = 1; } } if (lc > lw) lw = lc; if ( foldme || lw > file->columnlimit || (unfoldme && *(c-1)=='\\')) { sprintf(buffer, "output line %u(%u) folded",1+file->line,1+file->column); cbf_log(handle, buffer, CBF_LOGWARNING|CBF_LOGSTARTLOC); if (initc==';') { if (file->column) cbf_failnez (cbf_write_character (file, '\n')) cbf_failnez (cbf_write_string (file, ";\\\n")) } else { if (file->column) cbf_failnez (cbf_write_character (file, ' ')) cbf_failnez (cbf_write_character (file, initc)) cbf_failnez (cbf_write_string (file, "\\\n")) } end = 0; foldme = 1; } else { if (file->column) cbf_failnez (cbf_write_character (file, ' ')) cbf_failnez (cbf_write_character (file, initc)) end = 1; foldme = 0; } for (c = string + 1+ unfoldme; *c; ) { int done; done = cbf_foldtextline(&c, fline, file->columnlimit -file->column, unfoldme, foldme, termc); cbf_failnez (cbf_write_string (file, fline)) if ( !done ) cbf_failnez (cbf_write_character (file, '\n')) } if (unfoldme && *(c-1)=='\\') { if (termc == ';') { cbf_failnez (cbf_write_string (file, "\\\n;\n")) } else { cbf_failnez (cbf_write_string (file, "\\\n")) cbf_failnez (cbf_write_character (file, termc )) if (*string==CBF_TOKEN_TSQSTRING || *string==CBF_TOKEN_TDQSTRING ) { cbf_failnez (cbf_write_character (file, termc )) cbf_failnez (cbf_write_character (file, termc )) } } } else { if (termc == ';') { if (file->column) { cbf_failnez (cbf_write_character (file, '\n')) } cbf_failnez (cbf_write_string (file, ";\n")) } else { cbf_failnez (cbf_write_character (file, termc )) if (*string==CBF_TOKEN_TSQSTRING || *string==CBF_TOKEN_TDQSTRING ) { cbf_failnez (cbf_write_character (file, termc )) cbf_failnez (cbf_write_character (file, termc )) } } } end = 0; break; } /* Flush the buffer */ return cbf_flush_characters (file); } #ifdef __cplusplus } #endif ./CBFlib-0.9.2.2/src/fcb_read_byte.f900000644000076500007650000000314311603702106015456 0ustar yayayaya INTEGER FUNCTION FCB_READ_BYTE(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,IBYTE) !----------------------------------------------------------------------- ! Get byte number BYTE_IN_FILE from file (first byte is BYTE_IN_FILE=1) !----------------------------------------------------------------------- IMPLICIT NONE INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE INTEGER, INTENT(INOUT):: REC_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) INTEGER(1), INTENT(OUT):: IBYTE INTEGER I,J,K,KREC !----------------------------------------------------------------------- IBYTE=0 FCB_READ_BYTE=0 I=(BYTE_IN_FILE-1)/FCB_BYTES_IN_REC J=BYTE_IN_FILE-I*FCB_BYTES_IN_REC I=I+1 IF (I.NE.REC_IN_FILE) THEN !Requested byte is not in BUFFER REC_IN_FILE = I READ(TAPIN,IOSTAT=FCB_READ_BYTE,REC=REC_IN_FILE)BUFFER ! *** DEBUG *** PRINT *,"REC_IN_FILE: ", REC_IN_FILE ! *** DEBUG *** PRINT *,"FCB_READ_BYTE: ", FCB_READ_BYTE ! *** DEBUG *** PRINT *,"BUFFER: ", BUFFER IF (FCB_READ_BYTE.GT.0) THEN INQUIRE(TAPIN,NEXTREC=KREC) IF (REC_IN_FILE.LT.KREC) THEN DO K = 1, FCB_BYTES_IN_REC BUFFER(K) = 0 END DO READ(TAPIN,IOSTAT=FCB_READ_BYTE,REC=REC_IN_FILE)BUFFER IF (FCB_READ_BYTE.GT.0) FCB_READ_BYTE=0 END IF END IF IF (FCB_READ_BYTE.NE.0) RETURN END IF IBYTE=BUFFER(J) RETURN END FUNCTION FCB_READ_BYTE ./CBFlib-0.9.2.2/src/cbf_context.c0000644000076500007650000006063211603702106015036 0ustar yayayaya/********************************************************************** * cbf_context -- handle cbf contexts * * * * Version 0.7.6 14 July 2006 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifdef __cplusplus extern "C" { #endif #include "cbf.h" #include "cbf_alloc.h" #include "cbf_context.h" #include #include #include /* Create and initialise a context */ int cbf_make_context (cbf_context **context) { /* Allocate the memory */ cbf_failnez (cbf_alloc ((void **) context, NULL, sizeof (cbf_context), 1)) /* Initialise */ (*context)->temporary = NULL; (*context)->connections = 1; /* Success */ return 0; } /* Free a context */ int cbf_free_context (cbf_context **context) { int errorcode; errorcode = 0; if (context) if (*context) { if ((*context)->temporary) errorcode = cbf_free_file (&(*context)->temporary); errorcode |= cbf_free ((void **) context, NULL); } /* Success? */ return errorcode; } /* Add a context connection */ int cbf_add_contextconnection (cbf_context **context) { /* Does the context pointer exist? */ if (!context) return CBF_ARGUMENT; /* Does the context exist? */ if (*context) { (*context)->connections++; return 0; } /* Create a new context */ return cbf_make_context (context); } /* Remove a context connection */ int cbf_delete_contextconnection (cbf_context **context) { /* Does the context pointer exist? */ if (!context) return CBF_ARGUMENT; /* Does the context exist? */ if (!*context) return CBF_ARGUMENT; /* Remove a connection */ (*context)->connections--; /* Delete the context? */ if ((*context)->connections == 0) return cbf_free_context (context); /* Success */ return 0; } /* Open a temporary file connection */ int cbf_open_temporary (cbf_context *context, cbf_file **temporary) { FILE *stream; int errorcode; /* Check the arguments */ if (!context || !temporary) return CBF_ARGUMENT; /* Does a temporary file already exist? */ if (context->temporary) { cbf_failnez (cbf_add_fileconnection (&context->temporary, NULL)) *temporary = context->temporary; return 0; } /* Create the temporary file */ stream = tmpfile (); if (!stream) return CBF_FILEOPEN; errorcode = cbf_make_file (&context->temporary, stream); context->temporary->temporary = 1; if (errorcode) { if (fclose (stream)) errorcode |= CBF_FILECLOSE; return errorcode; } /* Open a connection */ return cbf_open_temporary (context, temporary); } /* Close a temporary file connection */ int cbf_close_temporary (cbf_context *context, cbf_file **temporary) { /* Check the arguments */ if (!context || !temporary) return CBF_ARGUMENT; if (!*temporary) return CBF_ARGUMENT; /* Check that the temporary file matches */ if (context->temporary != *temporary) return CBF_NOTFOUND; /* Delete the connection */ cbf_failnez (cbf_delete_fileconnection (&context->temporary)) *temporary = NULL; /* Is there only one connection left? */ if (context->temporary) if (cbf_file_connections (context->temporary) == 1) cbf_failnez (cbf_free_file (&context->temporary)) /* Success */ return 0; } /* Copy a string */ const char *cbf_copy_string (cbf_context *context, const char *string, char type) { char *new_string; void *memblock; if (string) { if (type) { if (cbf_alloc (&memblock, NULL, sizeof (char), strlen (string) + 2) == 0) { new_string = (char *)memblock; *new_string = type; strcpy (new_string + 1, string); return new_string; } } else if (cbf_alloc (&memblock, NULL, \ sizeof (char), strlen (string) + 1) == 0) { new_string = (char *)memblock; strcpy (new_string, string); return new_string; } } /* Fail */ return NULL; } /* Copy two strings */ const char *cbf_copy_strings (cbf_context *context, const char *string1, const char *string2, char type) { char *new_string; void *memblock; if (!string1) return cbf_copy_string(context,string2,type); if (!string2) return cbf_copy_string(context,string2,type); if (type) { if (cbf_alloc (&memblock, NULL, sizeof (char), strlen (string1) + strlen(string2) + 2) == 0) { new_string = (char *)memblock; *new_string = type; strcpy (new_string + 1, string1); strcpy (new_string + 1 + strlen(string1),string2); return new_string; } } if (cbf_alloc (&memblock, NULL, sizeof (char), strlen (string1) + strlen(string2) + 1) == 0) { new_string = (char *)memblock; strcpy (new_string, string1); strcpy (new_string + strlen(string1), string2); return new_string; } return NULL; } /* Free a string */ void cbf_free_string (cbf_context *context, const char *string) { void * memblock; memblock = (void *)string; cbf_free (&memblock, NULL); } #ifdef __cplusplus } #endif ./CBFlib-0.9.2.2/src/cbf_binary.c0000644000076500007650000010365311603702106014637 0ustar yayayaya/********************************************************************** * cbf_binary -- handle simple binary values * * * * Version 0.9 04 August 2009 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006 -- 2009 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifdef __cplusplus extern "C" { #endif #include "cbf.h" #include "cbf_tree.h" #include "cbf_codes.h" #include "cbf_compress.h" #include "cbf_context.h" #include "cbf_binary.h" #include "cbf_read_mime.h" #include "cbf_string.h" #include #include #include #include static const char * big_endian = "big_endian"; static const char * little_endian = "little_endian"; static const char * unknown = "unknown"; /* Parse a binary text value */ int cbf_get_bintext (cbf_node *column, unsigned int row, int *type, int *id, cbf_file **file, long *start, size_t *size, int *checked_digest, char *digest, int *bits, int *sign, int *realarray, const char **byteorder, size_t *dimover, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding, unsigned int *compression) { void *file_text; unsigned long start_text, size_text; int id_text, type_text, checked_digest_text, bits_text, sign_text, realarray_text; size_t dimover_text, dimfast_text, dimmid_text, dimslow_text; size_t padding_text; unsigned int compression_text; char digest_text [25]; char byteorder_text [14]; const char *text; /* Check that the value is binary */ if (!cbf_is_binary (column, row)) return CBF_ASCII; /* Get the value */ cbf_failnez (cbf_get_columnrow (&text, column, row)) /* Parse it */ type_text = *text; sscanf (text + 1, " %x %p %lx %lx %d %24s %x %d %d %14s %lu %lu %lu %lu %lu %u", (unsigned int *)&id_text, &file_text, (unsigned long *)&start_text, (unsigned long *)&size_text, &checked_digest_text, digest_text, (unsigned int *)&bits_text, &sign_text, &realarray_text, byteorder_text, (unsigned long *)&dimover_text, (unsigned long *)&dimfast_text, (unsigned long *)&dimmid_text, (unsigned long *)&dimslow_text, (unsigned long *)&padding_text, &compression_text); /* Copy the values */ if (type) *type = type_text; if (id) *id = id_text; if (file) *file = (cbf_file *)file_text; if (start) *start = start_text; if (size) *size = size_text; if (checked_digest) *checked_digest = checked_digest_text; if (digest) strcpy (digest, digest_text); if (bits) *bits = bits_text; if (sign) *sign = sign_text; if (realarray) *realarray = realarray_text; if (byteorder) { if (byteorder_text[0]=='b'|| byteorder_text[0]=='B') { *byteorder = big_endian; } else if (byteorder_text[0]=='l'|| byteorder_text[0]=='L') { *byteorder = little_endian; } else *byteorder = unknown; } if (dimover) *dimover = dimover_text; if (dimfast) *dimfast = dimfast_text; if (dimmid) *dimmid = dimmid_text; if (dimslow) *dimslow = dimslow_text; if (padding) *padding = padding_text; if (compression) *compression = compression_text; /* Success */ return 0; } /* Set a binary text value */ int cbf_set_bintext (cbf_node *column, unsigned int row, int type, int id, cbf_file *file, long start, long size, int checked_digest, const char *digest, int bits, int sign, int realarray, const char *byteorder, size_t dimover, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding, unsigned int compression) { char text [(((sizeof (void *) + sizeof (long int) * 2 + sizeof (int) * 3) * CHAR_BIT) >> 2) + 57 +15+((5*sizeof (size_t)*3*CHAR_BIT)>>2)]; const char *new_text; int errorcode; /* Check that the digest has the correct format */ if (!cbf_is_base64digest (digest)) { digest = "------------------------"; checked_digest = 0; } /* Create the new text */ sprintf (text, "%x %p %lx %lx %1d %24s %x %d %d %14s %ld %ld %ld %ld %ld %u", (unsigned int)id, (void *)file, (unsigned long)start, (unsigned long)size, checked_digest != 0, digest, (unsigned int)bits, sign, realarray, byteorder, (unsigned long)dimover, (unsigned long)dimfast, (unsigned long)dimmid, (unsigned long)dimslow, (unsigned long)padding, compression); new_text = cbf_copy_string (NULL, text, (char) type); if (!new_text) return CBF_ALLOC; /* Add a new connection to the file */ cbf_onfailnez (cbf_add_fileconnection (&file, NULL), cbf_free_string (NULL, new_text)) /* Set the new value */ errorcode = cbf_set_columnrow (column, row, new_text, 1); if (errorcode) { cbf_free_string (NULL, new_text); return errorcode | cbf_delete_fileconnection (&file); } /* Success */ return 0; } /* Is this a binary value? */ int cbf_is_binary (cbf_node *column, unsigned int row) { const char *text; /* Get the value */ if (cbf_get_columnrow (&text, column, row)) return 0; if (text) return (*text == CBF_TOKEN_BIN || *text == CBF_TOKEN_TMP_BIN || *text == CBF_TOKEN_MIME_BIN); /* Fail */ return 0; } /* Is this an encoded binary value? */ int cbf_is_mimebinary (cbf_node *column, unsigned int row) { const char *text; /* Get the value */ if (cbf_get_columnrow (&text, column, row)) return 0; if (text) return (*text == CBF_TOKEN_MIME_BIN); /* Fail */ return 0; } /* Free a value */ int cbf_free_value (cbf_context *context, cbf_node *column, unsigned int row) { cbf_file *file; const char *text; int is_binary, type; /* Check the argument */ if (!column) return CBF_ARGUMENT; /* Is the value binary? */ is_binary = cbf_is_binary (column, row); /* Parse the (binary) value */ if (is_binary) cbf_failnez (cbf_get_bintext (column, row, &type, NULL, &file, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL)) /* Get the ASCII value */ cbf_failnez (cbf_get_columnrow (&text, column, row)) /* Set the value to null */ cbf_failnez (cbf_set_columnrow (column, row, NULL, 0)) /* And free it */ cbf_free_string (NULL, text); if (is_binary) { if (type == CBF_TOKEN_TMP_BIN) { cbf_failnez (cbf_close_temporary (context, &file)) } else { cbf_failnez (cbf_delete_fileconnection (&file)) } } /* Success */ return 0; } /* Set a binary value */ int cbf_set_binary (cbf_node *column, unsigned int row, unsigned int compression, int binary_id, void *value, size_t elsize, int elsign, size_t nelem, int realarray, const char *byteorder, size_t dimover, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding) { cbf_file *tempfile; char digest [25]; size_t size; long start; int bits; /* Remove the old value */ cbf_failnez (cbf_set_columnrow (column, row, NULL, 1)) /* Get the temporary file */ cbf_failnez (cbf_open_temporary (column->context, &tempfile)) /* Move to the end of the temporary file */ if (cbf_set_fileposition (tempfile, 0, SEEK_END)) return CBF_FILESEEK | cbf_delete_fileconnection (&tempfile); /* Get the starting location */ if (cbf_get_fileposition (tempfile, &start)) return CBF_FILETELL | cbf_delete_fileconnection (&tempfile); /* Add the binary data to the temporary file */ cbf_onfailnez (cbf_compress (value, elsize, elsign, nelem, compression, tempfile, &size, &bits, digest, realarray, "little_endian", dimfast, dimmid, dimslow, padding), cbf_delete_fileconnection (&tempfile)) /* Set the value */ /* We do not yet support writing of big_endian binary sections */ if (cbf_cistrncmp(byteorder,"little_endian",14)) { cbf_delete_fileconnection (&tempfile); return CBF_FORMAT; } cbf_onfailnez (cbf_set_bintext (column, row, CBF_TOKEN_TMP_BIN, binary_id, tempfile, start, size, 1, digest, bits, elsign != 0, realarray, "little_endian", dimover, dimfast, dimmid, dimslow, padding, compression), cbf_delete_fileconnection (&tempfile)) /* Success */ return 0; } /* Check the message digest */ int cbf_check_digest (cbf_node *column, unsigned int row) { cbf_file *file; long start; size_t size; char old_digest [25], new_digest [25]; const char *byteorder; int id, bits, sign, type, checked_digest, realarray; size_t dimover, dimfast, dimmid, dimslow; size_t padding; unsigned int compression; /* Parse the value */ cbf_failnez (cbf_get_bintext (column, row, &type, &id, &file, &start, &size, &checked_digest, old_digest, &bits, &sign, &realarray, &byteorder, &dimover, &dimfast, &dimmid, &dimslow, &padding, &compression)) /* Recalculate and compare the digest? */ if ((file->read_headers & (MSG_DIGEST|MSG_DIGESTNOW|MSG_DIGESTWARN) ) && !checked_digest) if (cbf_is_base64digest (old_digest)) { /* Is it encoded? */ if (cbf_is_mimebinary (column, row)) { /* Convert the value to a normal binary value */ cbf_failnez (cbf_mime_temp (column, row)) /* Rerun the function */ return cbf_check_digest (column, row); } /* Position the file */ cbf_failnez (cbf_set_fileposition (file, start, SEEK_SET)) /* Recalculate and check the digest */ cbf_failnez (cbf_md5digest (file, size, new_digest)) if (strcmp (old_digest, new_digest) != 0) return CBF_FORMAT; /* Change the text to show that the digest has been checked */ cbf_failnez (cbf_set_bintext (column, row, type, id, file, start, size, 1, new_digest, bits, sign, realarray, byteorder, dimover, dimfast, dimmid, dimslow, padding, compression)) } /* Success */ return 0; } /* Get the parameters of a binary value */ int cbf_binary_parameters (cbf_node *column, unsigned int row, unsigned int *compression, int *id, int *eltype, size_t *elsize, int *elsigned, int *elunsigned, size_t *nelem, int *minelem, int *maxelem, int *realarray, const char **byteorder, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding) { cbf_file *file; long start; size_t size, file_elsize, file_nelem; int text_bits, errorcode; size_t text_dimover; int text_sign; /* Check the digest (this will also decode it if necessary) */ cbf_failnez (cbf_check_digest (column, row)) /* Is it an encoded binary section? */ if (cbf_is_mimebinary (column, row)) { /* Convert the value to a normal binary value */ cbf_failnez (cbf_mime_temp (column, row)) /* Rerun the function */ return cbf_binary_parameters (column, row, compression, id, eltype, elsize, elsigned, elunsigned, nelem, minelem, maxelem, realarray, byteorder, dimfast, dimmid, dimslow, padding); } /* Parse the value */ cbf_failnez (cbf_get_bintext (column, row, NULL, id, &file, &start, &size, NULL, NULL, &text_bits, &text_sign, realarray, byteorder, &text_dimover, dimfast, dimmid, dimslow, padding, compression)) /* Position the file at the start of the binary section */ cbf_failnez (cbf_set_fileposition (file, start, SEEK_SET)) /* Get the parameters */ errorcode = cbf_decompress_parameters (eltype, &file_elsize, elsigned, elunsigned, &file_nelem, minelem, maxelem, *compression, file); if (!errorcode) { if (text_sign != -1 && elsigned) { *elsigned = text_sign?1:0; } if (text_sign != -1 && elunsigned) { *elunsigned = text_sign?0:1; } if (elsize) { if ( text_bits > 0) { *elsize = (text_bits + CHAR_BIT - 1) / CHAR_BIT; } else { if (file_elsize > 0) { *elsize = file_elsize; } } } if (nelem) { if (file_nelem > 0) *nelem = file_nelem; else { if (text_dimover > 0) *nelem = text_dimover; else *nelem = (size * 8) / text_bits; } } } return errorcode; } /* Get a binary value */ int cbf_get_binary (cbf_node *column, unsigned int row, int *id, void *value, size_t elsize, int elsign, size_t nelem, size_t *nelem_read, int *realarray, const char **byteorder, size_t *dimover, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding) { cbf_file *file; long start; int eltype_file, elsigned_file, elunsigned_file, minelem_file, maxelem_file, bits, sign; unsigned int compression; size_t nelem_file; size_t text_dimover; size_t size; /* Check the digest (this will also decode it if necessary) */ cbf_failnez (cbf_check_digest (column, row)) /* Is it an encoded binary section? */ if (cbf_is_mimebinary (column, row)) { /* Convert the value to a normal binary value */ cbf_failnez (cbf_mime_temp (column, row)) /* Rerun the function */ return cbf_get_binary (column, row, id, value, elsize, elsign, nelem, nelem_read, realarray, byteorder, dimover, dimfast, dimmid, dimslow, padding); } /* Parse the value */ cbf_failnez (cbf_get_bintext (column, row, NULL, id, &file, &start, &size, NULL, NULL, &bits, &sign, realarray, byteorder, &text_dimover, dimfast, dimmid, dimslow, padding, &compression)) if (dimover) *dimover = text_dimover; /* Position the file at the start of the binary section */ cbf_failnez (cbf_set_fileposition (file, start, SEEK_SET)) /* Get the parameters and position the file */ cbf_failnez (cbf_decompress_parameters (&eltype_file, NULL, &elsigned_file, &elunsigned_file, &nelem_file, &minelem_file, &maxelem_file, compression, file)) /* Decompress the binary data */ return cbf_decompress (value, elsize, elsign, nelem, nelem_read, size, compression, bits, sign, file, *realarray, *byteorder, text_dimover, *dimfast, *dimmid, *dimslow, *padding); } #ifdef __cplusplus } #endif ./CBFlib-0.9.2.2/src/cbf_read_mime.c0000644000076500007650000012006011603702106015264 0ustar yayayaya/********************************************************************** * cbf_read_mime -- read MIME-encoded binary sections * * * * Version 0.8.0 20 July 2008 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2007, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ /********************************************************************** * The following notice applies to some portions of this software * * which were derived in part from the routine decode.c in mpack * * * * (C) Copyright 1993,1994 by Carnegie Mellon University * * All Rights Reserved. * * * * Permission to use, copy, modify, distribute, and sell this * * softwareand its documentation for any purpose is hereby granted * * without fee, provided that the above copyright notice appear in * * all copies and that both that copyright notice and this permission * * notice appear in supporting documentation, and that the name of * * Carnegie Mellon University not be used in advertising or publicity * * pertaining to distribution of the software without specific, * * written prior permission. Carnegie Mellon University makes no * * representations about the suitability of this software for any * * purpose. It is provided "as is" without express or implied * * warranty. * * * * CARNEGIE MELLON UNIVERSITY DISCLAIMS ALL WARRANTIES WITH REGARD TO * * THIS SOFTWARE, INCLUDING ALL IMPLIED WARRANTIES OF MERCHANTABILITY * * AND FITNESS, IN NO EVENT SHALL CARNEGIE MELLON UNIVERSITY BE * * LIABLE FOR ANY SPECIAL, INDIRECT OR CONSEQUENTIAL DAMAGES OR ANY * * DAMAGES WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, * * WHETHER IN AN ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS * * ACTION, ARISING OUT OF OR IN CONNECTION WITH THE USE OR * * PERFORMANCE OF THIS SOFTWARE. * **********************************************************************/ #ifdef __cplusplus extern "C" { #endif #include "cbf.h" #include "cbf_file.h" #include "cbf_context.h" #include "cbf_binary.h" #include "cbf_codes.h" #include "cbf_read_mime.h" #include "cbf_string.h" #include #include static const char * big_endian = "big_endian"; static const char * little_endian = "little_endian"; /* Convert a MIME-encoded binary section to a temporary binary section */ int cbf_mime_temp (cbf_node *column, unsigned int row) { cbf_file *file; cbf_file *temp_file; long start, temp_start; size_t size; int id, bits, sign, type, checked_digest, realarray; unsigned int compression; char old_digest [25], *new_digest, digest [25]; const char *byteorder; size_t dimover, dimfast, dimmid, dimslow; size_t padding; /* Check the value */ if (!cbf_is_mimebinary (column, row)) return CBF_ASCII; /* Parse it */ size = 0; cbf_failnez (cbf_get_bintext (column, row, &type, &id, &file, &start, &size, &checked_digest, old_digest, &bits, &sign, &realarray, &byteorder, &dimover, &dimfast, &dimmid, &dimslow, &padding, &compression)) /* Position the file at the start of the mime section */ cbf_failnez (cbf_set_fileposition (file, start, SEEK_SET)) /* Get the temporary file */ cbf_failnez (cbf_open_temporary (column->context, &temp_file)) /* Move to the end of the temporary file */ cbf_onfailnez (cbf_set_fileposition (temp_file, 0, SEEK_END), cbf_delete_fileconnection (&temp_file)) /* Get the starting location */ cbf_onfailnez (cbf_get_fileposition (temp_file, &temp_start), cbf_delete_fileconnection (&temp_file)) /* Calculate a new digest if necessary */ if (cbf_is_base64digest (old_digest) && (file->read_headers & (MSG_DIGEST|MSG_DIGESTNOW|MSG_DIGESTWARN) ) && !checked_digest) new_digest = digest; else new_digest = NULL; /* Decode the binary data to the temporary file */ cbf_onfailnez (cbf_read_mime (file, temp_file, NULL, NULL, old_digest, new_digest), cbf_delete_fileconnection (&temp_file)) /* Check the digest */ if (new_digest) { if (strcmp (old_digest, new_digest) == 0) { checked_digest = 1; } else { return CBF_FORMAT | cbf_delete_fileconnection (&temp_file); } } /* Replace the connection */ cbf_onfailnez (cbf_set_bintext (column, row, CBF_TOKEN_TMP_BIN, id, temp_file, temp_start, size, checked_digest, old_digest, bits, sign, realarray, byteorder, dimover, dimfast, dimmid, dimslow, padding, compression), cbf_delete_fileconnection (&temp_file)) /* Success */ return 0; } /* Convert a MIME-encoded binary section to a normal binary section */ int cbf_read_mime (cbf_file *infile, cbf_file *outfile, size_t *size, long *id, char *old_digest, char *new_digest) { int encoding; size_t file_size; size_t dimover; unsigned int compression; /* Read the header */ encoding = 0; file_size = 0; cbf_failnez (cbf_parse_mimeheader (infile, &encoding, &file_size, id, old_digest, &compression, NULL, NULL, NULL, NULL, &dimover, NULL, NULL, NULL, NULL)) if (file_size <= 0) return CBF_FORMAT; /* Discard any bits in the buffers */ infile->bits [0] = 0; infile->bits [1] = 0; /* Decode the binary data */ switch (encoding) { case ENC_QP: cbf_failnez (cbf_fromqp (infile, outfile, file_size, NULL, new_digest)) break; case ENC_BASE64: cbf_failnez (cbf_frombase64 (infile, outfile, file_size, NULL, new_digest)) break; case ENC_BASE32K: cbf_failnez(cbf_frombase32k(infile, outfile, file_size, NULL, new_digest)) break; case ENC_BASE8: case ENC_BASE10: case ENC_BASE16: cbf_failnez (cbf_frombasex (infile, outfile, file_size, NULL, new_digest)) break; default: return CBF_FORMAT; } /* Flush the buffers */ cbf_failnez (cbf_flush_bits (outfile)) /* Size (excluding the encoding) */ if (size) *size = file_size; /* Success */ return 0; } /* Is the line blank? */ int cbf_is_blank (const char *line) { if (line) for (; *line; line++) if (!isspace (*line)) return 0; return 1; } /* Find non-blank length of a line */ int cbf_nblen (const char *line, size_t *nblen) { register char *myline; register size_t mylen; *nblen = mylen = 0; if (!(myline = (char *)line)) return 1; for (; *myline; myline++) if (!isspace (*myline)) mylen = myline-(char *)line+1; *nblen = mylen; return 0; } /* Skip whitespace and comments */ int cbf_skip_whitespace (cbf_file *file, const char **line, const char **curpoint, int *freshline) { static const char end = '\0'; const char *c; int comment_level; /* Repeating the end of a line? */ if (*freshline) { *curpoint = &end; return 0; } c = *curpoint; comment_level = 0; while (isspace (*c) || *c == '(' || *c == '\0') if (*c == '\0') { cbf_failnez (cbf_read_line (file, line)) c = *line; if (cbf_is_blank (c) || (*c != ' ' && *c != '\t')) { *freshline = 1; *curpoint = &end; return 0; } } else if (*c == '(') { c++; comment_level++; while (comment_level) { switch (*c) { case '\0': cbf_failnez (cbf_read_line (file, line)) c = *line; if (cbf_is_blank (c) || (*c != ' ' && *c != '\t')) { *freshline = 1; *curpoint = &end; return 0; } break; case '\\': c++; break; case '(': comment_level++; break; case ')': comment_level--; break; } c++; } } else c++; *freshline = 0; *curpoint = c; /* Success */ return 0; } /* Parse the MIME header looking for values of type: Content-Type: Content-Transfer-Encoding: Content-MD5: X-Binary-Size: X-Binary-ID: X-Binary-Element-Type: X-Binary-Element-Byte-Order: X-Binary-Number-of-Elements: X-Binary-Size-Fastest-Dimension: X-Binary-Size-Second-Dimension: X-Binary-Size-Third-Dimension: X-Binary-Size-Padding: Content-MD5: */ int cbf_parse_mimeheader (cbf_file *file, int *encoding, size_t *size, long *id, char *digest, unsigned int *compression, int *bits, int *sign, int *real, const char **byteorder, size_t *dimover, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding) { static const char *value [] = { "Content-Type:", /* State 0 */ "Content-Transfer-Encoding:", /* State 1 */ "Content-MD5:", /* State 2 */ "X-Binary-Size:", /* State 3 */ "X-Binary-ID:", /* State 4 */ "X-Binary-Element-Type:", /* State 5 */ "X-Binary-Element-Byte-Order:", /* State 6 */ "X-Binary-Size-Fastest-Dimension:", /* State 7 */ "X-Binary-Size-Second-Dimension:", /* State 8 */ "X-Binary-Size-Third-Dimension:", /* State 9 */ "X-Binary-Size-Padding:", /* State 10 */ "X-Binary-Number-of-Elements:" /* State 11 */ }; const char *line, *c; int state, continuation, item, line_count, fresh_line, quote, text_bits, count, failure=0; size_t nblen; /* Defaults */ if (encoding) *encoding = 0; if (size) *size = 0; if (id) *id = 0; if (digest) *digest = '\0'; if (compression) *compression = CBF_NONE; if (bits) *bits = 0; if (sign) *sign = -1; if (real) *real = -1; if (byteorder) *byteorder=little_endian; if (dimover) *dimover = 0; if (dimfast) *dimfast = 0; if (dimmid) *dimmid = 0; if (dimslow) *dimslow = 0; if (padding) *padding = 0; /* Read the file line by line */ state = -1; line_count = 0; fresh_line = 0; nblen = 1; while (nblen) { if (!fresh_line) cbf_failnez (cbf_read_line (file, &line)) cbf_nblen (line, &nblen); fresh_line = 0; line_count++; /* Check for premature terminations */ if ( (line[0] == ';') || ( cbf_cistrncmp(line,"--CIF-BINARY-FORMAT-SECTION--",29) == 0 ) ) return CBF_FORMAT; /* Check for a header continuation line */ continuation = line [0] == ' ' || line [0] == '\t'; /* Check for a new item */ if (continuation) item = 0; else { for (c = line; *c != ':' && *c > 32 && *c < 127; c++); item = c != line && *c == ':'; } /* Check for the end of the header */ if (line_count > 1 && cbf_is_blank (line)) return 0; /* Check for valid header-ness of line */ if (!item && (line_count == 1 || !continuation)) return CBF_FORMAT; /* Look for the entries we are interested in */ c = line; if (item) for (state = 11; state > -1; state--) if (cbf_cistrncmp (line, value [state], strlen (value [state])) == 0) { c = line + strlen (value [state]); break; } /* Skip past comments and whitespace */ cbf_failnez (cbf_skip_whitespace (file, &line, &c, &fresh_line)) /* Get the value */ switch (state) { case 0: /* Content */ if (cbf_cistrncmp (c, "application/", 12) != 0 && cbf_cistrncmp (c, "image/", 6) != 0 && cbf_cistrncmp (c, "text/", 5) != 0 && cbf_cistrncmp (c, "audio/", 6) != 0 && cbf_cistrncmp (c, "video/", 6) != 0) return CBF_FORMAT; while (*c) { /* Skip to the end of the section (a semicolon) */ while (*c) if (*c == '\"') { c++; while (*c) if (*c == '\"') { c++; break; } else { if (*c == '\\') c++; if (*c) c++; } } else if (*c == '(') cbf_failnez (cbf_skip_whitespace (file, &line, &c, &fresh_line)) else if (*c == ';') { c++; break; } else c++; /* We are at the end of the section or the end of the item */ cbf_failnez (cbf_skip_whitespace (file, &line, &c, &fresh_line)) if (cbf_cistrncmp (c, "conversions", 11) == 0) { c += 11; cbf_failnez (cbf_skip_whitespace (file, &line, &c, &fresh_line)) if (*c == '=') { c++; cbf_failnez (cbf_skip_whitespace (file, &line, &c, &fresh_line)) if (compression) { quote = 0; if (*c == '\"') quote = 1; *compression = CBF_NONE; if (cbf_cistrncmp (c + quote, "x-cbf_packed", 12) == 0) *compression = CBF_PACKED; if (cbf_cistrncmp (c + quote, "x-cbf_packed_v2", 15) == 0) *compression = CBF_PACKED_V2; if (cbf_cistrncmp (c + quote, "x-cbf_canonical", 15) == 0) *compression = CBF_CANONICAL; if (cbf_cistrncmp (c + quote, "x-cbf_byte_offset", 17) == 0) *compression = CBF_BYTE_OFFSET; if (cbf_cistrncmp (c + quote, "x-cbf_predictor", 15) == 0) *compression = CBF_PREDICTOR; if (*compression == CBF_PACKED_V2 || *compression == CBF_PACKED ) { while (*c) { while (*c) if (*c == '\"') { c++; while (*c) if (*c == '\"') { c++; break; } else { if (*c == '\\') c++; if (*c) c++; } } else if (*c == '(') { cbf_failnez (cbf_skip_whitespace (file, &line, &c, &fresh_line)) } else if (*c == ';') { c++; break; } else c++; /* We are at the end of the section or the end of the item */ cbf_failnez (cbf_skip_whitespace (file, &line, &c, &fresh_line)) quote = 0; if (*c == '\"') quote = 1; if (cbf_cistrncmp (c+quote, "uncorrelated_sections", 21) == 0) *compression |= CBF_UNCORRELATED_SECTIONS; if (cbf_cistrncmp (c+quote, "flat", 4) == 0) *compression |= CBF_FLAT_IMAGE; } } } } } } state = -1; break; case 1: /* Binary encoding */ if (encoding) { failure = 1; quote = 0; if (*c == '\"') quote = 1; if (cbf_cistrncmp (c+quote, "Quoted-Printable", 16) == 0) if (isspace (c [16]) || c [16] == '(' || (quote && c [16] == '\"')) { failure = 0; *encoding = ENC_QP; } if (cbf_cistrncmp (c+quote, "Base64", 6) == 0) if (isspace (c [6]) || c [6] == '(' || (quote && c [6] == '\"')) { failure = 0; *encoding = ENC_BASE64; } if (cbf_cistrncmp (c+quote, "X-Base32k", 9) ==0 ) if(isspace(c[9]) || c [9] == '(' || (quote && c[9] == '\"')) { failure =0; *encoding = ENC_BASE32K; } if (cbf_cistrncmp (c+quote, "X-Base8", 7) == 0) if (isspace (c [7]) || c [7] == '(' || (quote && c [7] == '\"')) { failure = 0; *encoding = ENC_BASE8; } if (cbf_cistrncmp (c+quote, "X-Base10", 8) == 0) if (isspace (c [8]) || c [8] == '(' || (quote && c [8] == '\"')) { failure = 0; *encoding = ENC_BASE10; } if (cbf_cistrncmp (c+quote, "X-Base16", 8) == 0) if (isspace (c [8]) || c [8] == '(' || (quote && c [8] == '\"')) { failure = 0; *encoding = ENC_BASE16; } if (cbf_cistrncmp (c+quote, "7bit", 4) == 0 || cbf_cistrncmp (c+quote, "8bit", 4) == 0) if (isspace (c [4]) || c [4] == '(' || (quote && c [4] == '\"')) { failure = 0; *encoding = ENC_NONE; } if (cbf_cistrncmp (c+quote, "Binary", 6) == 0) if (isspace (c [6]) || c [6] == '(' || (quote && c [6] == '\"')) { failure = 0; *encoding = ENC_NONE; } } if (failure) return CBF_FORMAT; break; case 2: /* Message digest */ if (digest) { strncpy (digest, c, 24); digest [24] = '\0'; } break; case 3: /* Binary size */ if (size) *size = atol (c); break; case 4: /* Binary ID */ if (id) *id = atol (c); break; case 5: /* Binary element type (signed/unsigned ?-bit integer) */ /* or (signed ?-bit real/complex IEEE) */ failure = 3; while (*c) { quote = 0; cbf_failnez (cbf_skip_whitespace (file, &line, &c, &fresh_line)) if (*c == '\"') { if (quote) break; c++; quote++; } if (failure == 3) { if (cbf_cistrncmp (c, "signed", 6) == 0) { c += 6; if (sign) *sign = 1; failure --; } if (cbf_cistrncmp (c, "unsigned", 8) == 0) { c += 8; if (sign) *sign = 0; failure --; } } if (failure == 2) { count = 0; sscanf (c, "%d-%n", &text_bits, &count); if (cbf_cistrncmp (c+count, "bit", 3 ) == 0) if (count && text_bits > 0 && text_bits <= 64) { c += count; if (bits) *bits = text_bits; if (*c == ' ') c++; failure --; } } if (failure == 1) { if (cbf_cistrncmp (c, "integer", 7 ) == 0) { failure--; if (real) *real = 0; } else { if (cbf_cistrncmp(c, "real", 4 ) == 0 ) { c+=4; if(*c == ' ') c++; if (cbf_cistrncmp(c, "ieee", 4 ) == 0 ) { failure--; if (real) *real = 1; } } else { if (cbf_cistrncmp(c, "complex", 7 ) == 0 ) { c+=7; if(*c == ' ') c++; if (cbf_cistrncmp(c, "ieee", 4 ) == 0 ) { failure--; if (real) *real = 1; } } } } } if (*c) c++; } if (failure) return CBF_FORMAT; break; case 6: /* Byte order of elements (only endian-ness is supported) */ if (byteorder) { if (!cbf_cistrncmp(c, "big_endian",10) ) { *byteorder=big_endian; } else if (!cbf_cistrncmp(c, "little_endian",13)){ *byteorder=little_endian; } else return CBF_FORMAT; } break; case 7: /* Size of fastest dimension */ if (dimfast) *dimfast = atol(c); break; case 8: /* Size of second-fastest dimension */ if (dimmid) *dimmid = atol(c); break; case 9: /* Size of third-fastest dimension */ if (dimslow) *dimslow = atol(c); break; case 10: /* Size of padding after the data */ if (padding) *padding = atol(c); break; case 11: /* Overall number of element */ if (dimover) *dimover = atol(c); break; } } /* Success */ return 0; } #ifdef __cplusplus } #endif ./CBFlib-0.9.2.2/src/cbf_uncompressed.c0000644000076500007650000006744011603702106016065 0ustar yayayaya/********************************************************************** * cbf_uncompressed -- uncompressed binary sections * * * * Version 0.8.0 20 July 2008 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifdef __cplusplus extern "C" { #endif #include #include #include #include #include #define __USE_XOPEN #define _XOPEN_SOURCE #include #include "cbf.h" #include "cbf_alloc.h" #include "cbf_compress.h" #include "cbf_file.h" #include "cbf_uncompressed.h" #include "cbf_string.h" #define CBF_SHIFT63 (sizeof (int) * CHAR_BIT > 64 ? 63 : 0) /* Copy an array without compression */ int cbf_compress_none (void *source, size_t elsize, int elsign, size_t nelem, unsigned int compression, cbf_file *file, size_t *compressedsize, int *storedbits, int realarray, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding) { unsigned int count, element[4], unsign, sign, limit, bits; unsigned char *unsigned_char_data; int numints, iint; char * border; char * rformat; /* Is the element size valid? */ if (elsize != sizeof (int) && elsize != 2* sizeof (int) && elsize != 4* sizeof (int) && elsize != sizeof (short) && elsize != sizeof (char)) return CBF_ARGUMENT; /* check for compatible real format */ if ( realarray ) { cbf_failnez (cbf_get_local_real_format(&rformat) ) if ( strncmp(rformat,"ieee",4) ) return CBF_ARGUMENT; } bits = elsize * CHAR_BIT; if (bits < 1 || bits > 64) return CBF_ARGUMENT; numints = (bits + CHAR_BIT*sizeof (int) -1)/(CHAR_BIT*sizeof (int)); /* Maximum limits */ sign = 1 << ((elsize-(numints-1)*sizeof(int))* CHAR_BIT - 1); if (elsize == sizeof (int) || elsize == numints*sizeof(int) ) limit = ~0; else if (numints == 1) { limit = ~-(1 << (elsize * CHAR_BIT)); } else { limit = ~-(1 << ((elsize-(numints-1)*sizeof(int)) * CHAR_BIT)); } if (storedbits) *storedbits = bits; /* Offset to make the value unsigned */ if (elsign) unsign = sign; else unsign = 0; /* Get the local byte order */ if (realarray) { cbf_get_local_real_byte_order(&border); } else { cbf_get_local_integer_byte_order(&border); } /* Initialise the pointer */ unsigned_char_data = (unsigned char *) source; /* Write the elements */ /* Try for a fast memory-memory transfer */ switch (elsize) { case (1): if (!cbf_set_output_buffersize(file,nelem)) { memmove((void *)(file->characters+file->characters_used), (void *)unsigned_char_data,nelem); file->characters_used+=nelem; if (compressedsize) *compressedsize = nelem; return 0; } break; case (2): case (4): case (8): if (!cbf_set_output_buffersize(file,nelem*elsize)) { if (toupper(border[0]) == toupper(byteorder[0])) { memmove((void *)(file->characters+file->characters_used), (void *)unsigned_char_data,nelem*elsize); } else { if ((elsize == 4 || elsize == 8) && sizeof(short int) !=2 ) break; if (elsize == 8 && sizeof(int) !=4 ) break; cbf_swab((void *)unsigned_char_data, (void *)(file->characters+file->characters_used), nelem*elsize); if (elsize == 4 || elsize == 8) { short int temp; short int *sint; sint = (short int *)(file->characters+file->characters_used); for (count = 0; count < elsize * nelem; count+= 4) { temp = *sint; *sint = sint[1]; sint[1] = temp; sint+=2; } } if (elsize == 8) { int temp; int *oint; oint = (int *)(file->characters+file->characters_used); for (count = 0; count < elsize * nelem; count+= 8) { temp = *oint; *oint = oint[1]; oint[1] = temp; oint+=2; } } } file->characters_used+=nelem*elsize; if (compressedsize) *compressedsize = nelem*elsize; return 0; } break; default: break; } /* If we got here, we will do it the slow, painful way */ for (count = 0; count < nelem; count++) { /* Get the next element */ if (numints > 1) { if (border[0] == 'b') { for (iint = numints; iint; iint--) { element[iint-1] = *((unsigned int *) unsigned_char_data); unsigned_char_data += sizeof (int); } } else { for (iint = 0; iint < numints; iint++) { element[iint] = *((unsigned int *) unsigned_char_data); unsigned_char_data += sizeof (int); } } } else { if (elsize == sizeof (int)) element[0] = *((unsigned int *) unsigned_char_data); else if (elsize == sizeof (short)) element[0] = *((unsigned short *) unsigned_char_data); else element[0] = *unsigned_char_data; unsigned_char_data += elsize; } /* Make the element unsigned */ element[numints-1] += unsign; element[numints-1] &= limit; /* Write the element to the file */ element[numints-1] -= unsign; if (numints > 1) { for (iint = 0; iint < numints; iint++) { cbf_failnez (cbf_put_integer (file, element[iint], 0, iint<(numints-1)?(CHAR_BIT*sizeof (int)): bits-(CHAR_BIT*sizeof (int))*iint )) } } else { cbf_failnez (cbf_put_integer (file, element[0], 0, bits)) } } /* Return the number of characters written */ if (compressedsize) *compressedsize = (nelem * bits + 7) / 8; /* Success */ return 0; } /* Recover an array without decompression */ int cbf_decompress_none (void *destination, size_t elsize, int elsign, size_t nelem, size_t *nelem_read, size_t compressedsize, unsigned int compression, int data_bits, int data_sign, cbf_file *file, int realarray, const char *byteorder, size_t dimover, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding) { unsigned int element[4], sign, unsign, limit, count; unsigned int data_unsign; unsigned char *unsigned_char_data; int errorcode, overflow, numints, iint; char * border; char * rformat; /* prepare the errorcode */ errorcode = 0; /* Is the element size valid? */ if (elsize != sizeof (int) && elsize != 2* sizeof (int) && elsize != 4* sizeof (int) && elsize != sizeof (short) && elsize != sizeof (char)) return CBF_ARGUMENT; /* check for compatible real format */ if ( realarray ) { cbf_failnez (cbf_get_local_real_format(&rformat) ) if ( strncmp(rformat,"ieee",4) ) return CBF_ARGUMENT; } /* Check the stored element size */ if (data_bits < 1 || data_bits > 64) return CBF_ARGUMENT; numints = (data_bits + CHAR_BIT*sizeof (int) -1)/(CHAR_BIT*sizeof (int)); /* Initialise the pointer */ unsigned_char_data = (unsigned char *) destination; /* Maximum limits */ sign = 1 << ((elsize-(numints-1)*sizeof(int))* CHAR_BIT - 1); if (elsize == sizeof (int) || elsize == numints*sizeof(int)) limit = ~0; else if (numints == 1 ) { limit = ~(-(1 << (elsize * CHAR_BIT))); } else { limit = ~(-(1 << ((elsize-(numints-1)*sizeof(int)) * CHAR_BIT))); } /* Offsets to make the value unsigned */ if (data_sign) data_unsign = sign; else data_unsign = 0; if (elsign) unsign = sign; else unsign = 0; /* Get the local byte order */ if (realarray) { cbf_get_local_real_byte_order(&border); } else { cbf_get_local_integer_byte_order(&border); } /* Read the elements */ count = 0; overflow = 0; while (count < nelem) { /* Get the next element */ if (numints > 1 ) { for (iint=0; iint < numints; iint++) { errorcode |= cbf_get_integer (file, (int *)&(element[iint]), iint<(numints-1)?0:data_sign, iint<(numints-1)?(CHAR_BIT*sizeof (int)): data_bits-(CHAR_BIT*sizeof (int))*iint); } } else { errorcode |= cbf_get_integer (file, (int *)&(element[0]), data_sign, data_bits); } if (errorcode) { if ((errorcode&CBF_OVERFLOW) == CBF_OVERFLOW) overflow = errorcode; else { if (nelem_read) *nelem_read = count; return errorcode | overflow; } } /* Make the element unsigned */ element[numints-1] += data_unsign; element[numints-1] &= limit; /* Make the element signed? */ element[numints-1] -= unsign; /* Save the element */ if (numints > 1) { if (border[0] == 'b') { for (iint = numints; iint; iint--) { *((unsigned int *) unsigned_char_data) = element[iint-1]; unsigned_char_data += sizeof (int); } } else { for (iint = 0; iint < numints; iint++) { *((unsigned int *) unsigned_char_data) = element[iint]; unsigned_char_data += sizeof (int); } } } else { if (elsize == sizeof (int)) *((unsigned int *) unsigned_char_data) = element[0]; else if (elsize == sizeof (short)) *((unsigned short *) unsigned_char_data) = element[0]; else *unsigned_char_data = element[0]; unsigned_char_data += elsize; } count++; } /* Number read */ if (nelem_read) *nelem_read = count; /* Success */ return overflow; } #ifdef __cplusplus } #endif ./CBFlib-0.9.2.2/src/cbf_write.c0000644000076500007650000012450711603702106014506 0ustar yayayaya/********************************************************************** * cbf_write -- write files * * * * Version 0.7.6 14 July 2006 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifdef __cplusplus extern "C" { #endif #include "cbf.h" #include "cbf_ascii.h" #include "cbf_binary.h" #include "cbf_compress.h" #include "cbf_file.h" #include "cbf_tree.h" #include "cbf_write.h" #include "cbf_write_binary.h" #include "cbf_read_mime.h" #include "cbf_string.h" #include "cbf_ws.h" #include #include #include #include int cbf_value_type (char *value); static char wordtok[5] = "word"; static char texttok[5] = "text"; static char dblqtok[5] = "dblq"; static char sglqtok[5] = "sglq"; static char nulltok[5] = "null"; static char tsqstok[5] = "tsqs"; static char tdqstok[5] = "tdqs"; static char prnstok[5] = "prns"; static char brcstok[5] = "brcs"; static char bktstok[5] = "bkts"; /* Get the value type of an ascii string */ int cbf_get_value_type(const char *value, const char **value_type) { /* Prepare an empty return */ *value_type = NULL; /* Is the value missing? */ if (!value) return 0; /* Is the value valid? */ if ((*value & '\200') != '\200') return CBF_ARGUMENT; /* Has the value already been checked? */ if ((value [0] & '\300') != '\300') { cbf_failnez(cbf_value_type((char *)value)) } if (*value == CBF_TOKEN_WORD) { *value_type = wordtok; return 0; } if (*value == CBF_TOKEN_SQSTRING) { *value_type = sglqtok; return 0; } if (*value == CBF_TOKEN_DQSTRING) { *value_type = dblqtok; return 0; } if (*value == CBF_TOKEN_SCSTRING) { *value_type = texttok; return 0; } if (*value == CBF_TOKEN_BKTSTRING) { *value_type = bktstok; return 0; } if (*value == CBF_TOKEN_BRCSTRING) { *value_type = brcstok; return 0; } if (*value == CBF_TOKEN_PRNSTRING) { *value_type = prnstok; return 0; } if (*value == CBF_TOKEN_TDQSTRING) { *value_type = tdqstok; return 0; } if (*value == CBF_TOKEN_TSQSTRING) { *value_type = tsqstok; return 0; } if (*value == CBF_TOKEN_NULL) { *value_type = nulltok; return 0; } return CBF_ARGUMENT; } /* Set the value type of an ascii string */ int cbf_set_value_type(cbf_handle handle,char *value, const char *value_type) { char *cptr; /* Is the value type missing? */ if (!value) return CBF_ARGUMENT; /* Is the value valid? */ if ((*value & '\200') != '\200') return CBF_ARGUMENT; /* Has the value already been checked? */ if ((value [0] & '\300') != '\300') { cbf_failnez(cbf_value_type(value)) } if (strcmp(value_type,wordtok) == 0) { if ( strcmp(&value[1],".") == 0 || strcmp(&value[1],"?") == 0 || *value == CBF_TOKEN_WORD ) { *value = CBF_TOKEN_WORD; return 0; } return CBF_ARGUMENT; } if (strcmp(value_type,nulltok) == 0) { if ( strcmp(&value[1],".") == 0 || strcmp(&value[1],"?") == 0) { *value = CBF_TOKEN_NULL; return 0; } return CBF_ARGUMENT; } if (strcmp(value_type,sglqtok) == 0) { if(strstr(&value[1],"' ") || strstr(&value[1],"'\t") || strstr(&value[1],"\n")) { return CBF_ARGUMENT; } *value = CBF_TOKEN_SQSTRING; return 0; } if (strcmp(value_type,dblqtok) == 0 ) { if(strstr(&value[1],"\" ") || strstr(&value[1],"\"\t") || strstr(&value[1],"\n")) { return CBF_ARGUMENT; } *value = CBF_TOKEN_DQSTRING; return 0; } if (strcmp(value_type,texttok) == 0 ) { cptr = &value[1]; while (*cptr && (cptr=strstr(cptr,"\n;")) ) { if (isspace(cptr[2])) { cbf_log(handle,"text field contains terminator, will be folded on output",CBF_LOGWARNING); break; } if (*cptr) cptr++; } *value = CBF_TOKEN_SCSTRING; return 0; } if (strcmp(value_type,tsqstok) == 0 ) { cptr = &value[1]; while (*cptr && (cptr=strstr(cptr,"'''")) ) { if (isspace(cptr[2])) { cbf_log(handle, "triple singled-quoted field contains terminator, will be folded on output",CBF_LOGWARNING); break; } if (*cptr) cptr++; } *value = CBF_TOKEN_TSQSTRING; return 0; } if (strcmp(value_type,tdqstok) == 0 ) { cptr = &value[1]; while (*cptr && (cptr=strstr(cptr,"\"\"\"")) ) { if (isspace(cptr[3])) { cbf_log(handle, "triple double-quoted field contains terminator, will be folded on output",CBF_LOGWARNING); break; } if (*cptr) cptr++; } *value = CBF_TOKEN_TDQSTRING; return 0; } if (strcmp(value_type,prnstok) == 0 ) { *value = CBF_TOKEN_PRNSTRING; return 0; } if (strcmp(value_type,brcstok) == 0 ) { *value = CBF_TOKEN_BRCSTRING; return 0; } if (strcmp(value_type,bktstok) == 0 ) { *value = CBF_TOKEN_BKTSTRING; return 0; } return CBF_ARGUMENT; } /* Check the value type */ int cbf_value_type (char *value) { int test [6], C, count; /* Is the value missing? */ if (!value) return 0; /* Is the value valid? */ if ((*value & '\200') != '\200') return CBF_ARGUMENT; /* Has the value already been checked? */ if ((value [0] & '\300') == '\300') return 0; /* Properties */ memset (test, 0, sizeof (test)); for (count = 1; value [count]; count++) { C = toupper (value [count]); test [0] |= isspace (C); test [1] |= C == '\n'; test [2] |= C == '\''; test [3] |= C == '"'; if (count <= 5) { test [4] |= C != " DATA_" [count]; test [5] |= C != " LOOP_" [count]; if (count <= 1) test [0] |= C == '_' || C == '\'' || C == '"' || C == '#'; } } if (count <= 5) test[4]=test[5]=1; test [0] |= strcmp (&value [1], "?") == 0; test [0] |= strcmp (&value [1], ".") == 0; /* Simple word? */ if (!test [0] && test [4] && test [5]) *value = CBF_TOKEN_WORD; else /* Single line? */ if (!test [1] && (!test [2] || !test [3])) { if (!test [2]) *value = CBF_TOKEN_SQSTRING; else *value = CBF_TOKEN_DQSTRING; } else /* Multiple lines */ *value = CBF_TOKEN_SCSTRING; /* Success */ return 0; } /* Write a datablock name to a file */ int cbf_write_datablockname (const cbf_node *datablock, cbf_file *file) { /* Does the node exist? */ if (!datablock) return CBF_ARGUMENT; /* Write the name */ if (datablock->name) { cbf_failnez (cbf_write_string (file, "\ndata_")) cbf_failnez (cbf_write_string (file, datablock->name)) cbf_failnez (cbf_write_character (file, '\n')) } else if (datablock->children) cbf_failnez (cbf_write_string (file, "\ndata_\n")) /* Success */ return 0; } /* Write a save frame name to a file */ int cbf_write_saveframename (const cbf_node *saveframe, cbf_file *file) { /* Does the node exist? */ if (!saveframe) return CBF_ARGUMENT; /* Write the name */ if (saveframe->name) { cbf_failnez (cbf_write_string (file, "\nsave_")) cbf_failnez (cbf_write_string (file, saveframe->name)) cbf_failnez (cbf_write_character (file, '\n')) } else if (saveframe->children) cbf_failnez (cbf_write_string (file, "\nsave_(none)\n")) /* Success */ return 0; } /* Compose an item name from a category and column */ int cbf_compose_itemname (cbf_handle handle, const cbf_node *column, char * itemname, size_t limit) { cbf_node *category; char column_fill[1] = "\0"; char * tempcat; char * tempcol; int ipos; itemname[0] = itemname[limit] = '\0'; /* Get the category */ cbf_failnez (cbf_find_parent (&category, column, CBF_CATEGORY)) /* Check that the name is valid */ if (!category->name && !column->name) { strncpy (itemname, "_(null)", limit ); return CBF_ARGUMENT; } /* construct the item name */ if (column->name) { tempcol = (char *)column->name; } else { tempcol = column_fill; } if (!category->name || !(category->name[0]) || !cbf_cistrcmp("(none)",category->name) || tempcol[0]=='_') { strncpy(itemname,tempcol,limit); if (strlen(tempcol) > limit) return CBF_ARGUMENT; } else { if(!category->name) return CBF_ARGUMENT; itemname[0] = '_'; cbf_failnez( cbf_require_category_root(handle,category->name,(const char **)&tempcat)) strncpy(itemname+1,tempcat,limit-1); if (strlen(tempcat) > 72 || strlen(tempcat) > limit-1) return CBF_ARGUMENT; ipos = strlen(itemname); if ( ipos < limit ) itemname[ipos++] = '.'; if ( limit-ipos > 0) strncpy(itemname+ipos,tempcol,limit-ipos); if (strlen(tempcol)+ipos+2 > 75 || strlen(tempcol)+ipos+2 > limit) return CBF_ARGUMENT; } return 0; } /* Write an item name to a file */ int cbf_write_itemname (cbf_handle handle, const cbf_node *column, cbf_file *file) { char itemname[81]; char buffer[255]; char * temptag; /* Compose the tag and get the root alias */ if ( cbf_compose_itemname (handle, column, itemname, (size_t )80)) { strcpy (itemname+77,"..."); sprintf (buffer, "output line %u(%u) column name too long or invalid\n converted to \"%s\"", 1+file->line, 1+file->column, itemname); cbf_log(handle,buffer,CBF_LOGWARNING|CBF_LOGCURRENTLOC); } cbf_failnez( cbf_require_tag_root(handle,(const char *)itemname,(const char **)&temptag)) /* Write the tag name */ cbf_failnez (cbf_write_string (file, temptag)) /* Success */ return 0; } /* Write a value to a file */ int cbf_write_value (cbf_handle handle, cbf_node *column, unsigned int row, cbf_file *file, int isbuffer) { const char *text; /* Check the arguments */ if (!column) return CBF_ARGUMENT; if (row >= column->children) return CBF_NOTFOUND; /* Get the value */ cbf_failnez (cbf_get_columnrow (&text, column, row)) /* Missing value? */ if (!text) return cbf_write_ascii (handle, text, file); /* Plain ASCII? */ cbf_failnez (cbf_value_type ((char *) text)) if (*text == CBF_TOKEN_WORD || *text == CBF_TOKEN_SQSTRING || *text == CBF_TOKEN_DQSTRING || *text == CBF_TOKEN_SCSTRING || *text == CBF_TOKEN_TSQSTRING || *text == CBF_TOKEN_TDQSTRING || *text == CBF_TOKEN_PRNSTRING || *text == CBF_TOKEN_BKTSTRING || *text == CBF_TOKEN_BRCSTRING || *text == CBF_TOKEN_NULL) return cbf_write_ascii (handle, text, file); /* Plain binary? */ if (*text == CBF_TOKEN_BIN || *text == CBF_TOKEN_TMP_BIN) return cbf_write_binary (column, row, file, isbuffer); /* Undecoded MIME? */ if (*text == CBF_TOKEN_MIME_BIN) { /* Convert the value to a normal binary section */ cbf_failnez (cbf_mime_temp (column, row)) return cbf_write_binary (column, row, file, isbuffer); } /* Fail */ return CBF_ARGUMENT; } /* Write a category to a file */ int cbf_write_category (cbf_handle handle, const cbf_node *category, cbf_file *file, int isbuffer) { unsigned int count, first, last=0, column, columns, row, maxrows, matrixcount; int loop, matrix, len; const char * column_name; /* Check the arguments */ if (!category) return CBF_ARGUMENT; /* Print out columns of the same length in loops unless the number of rows is 1 */ maxrows = 0; matrix = 0; for (first = 0, loop = 1; first < category->children; first = last) { columns = 1; if (category->child [first] && category->child [first]->children > maxrows) maxrows = category->child [first]->children; if (category->child [first]) { for (last = first + 1; last < category->children; last++) if (category->child [last]) { if (category->child [last]->children != category->child [first]->children) { if (category->child [last]->children > maxrows) maxrows = category->child [last]->children; break; } columns++; } /* check for a matrix */ matrix = 0; matrixcount = 0; for (count = first ; count < last; count++) { column_name = (category->child [count])->name; if (column_name) { len = strlen(column_name); if ((len > 0 && column_name[len-1]==']') || (len > 4 && !cbf_cistrncmp("]_esd",(char *)column_name+len-5,5))) { matrixcount++; if (matrixcount > ((last-first+1)>>1)+1) { matrix = 1; break; } } } } /* Make a loop? */ if ( matrix || (maxrows > 1 && (columns > 1 || category->child [first]->children > 1))) { cbf_failnez (cbf_write_string (file, "\nloop_\n")) loop = 1; } else { cbf_failnez (cbf_write_character (file, '\n')) loop = 0; } /* Write the items for a loop */ if (loop) for (count = first; count < last; count++) { cbf_failnez (cbf_write_itemname (handle, category->child [count], file)) cbf_failnez (cbf_write_character (file, '\n')) } /* Write the values */ for (row = 0; row < category->child [first]->children; row++) { unsigned int xcol; for (column = first; column < last; column++) { if (!loop) { cbf_failnez (cbf_write_itemname (handle, category->child [column], file)) } if (matrix) { column_name = (category->child [column])->name; if (column_name) { len = strlen(column_name); if ((len > 2 && !cbf_cistrncmp("[1]",(char *)column_name+len-3,3)) || (len > 6 && !cbf_cistrncmp("[1]_esd",(char *)column_name+len-7,7))) { cbf_failnez (cbf_write_character (file, '\n')) } } } cbf_failnez (cbf_write_value (handle, category->child [column], row, file, isbuffer)) if (!loop) { cbf_failnez (cbf_write_character (file, '\n')) } } cbf_failnez (cbf_get_filecoordinates (file, NULL, &xcol)) if (xcol) cbf_failnez (cbf_write_character (file, '\n')) } } } /* Success */ return 0; } /* Write a node to a file */ int cbf_write_node (cbf_handle handle, const cbf_node *node, cbf_file *file, int isbuffer) { unsigned int count; /* Follow any links */ node = cbf_get_link (node); /* Does the node exist? */ if (!node) return CBF_ARGUMENT; /* Write any appropriate white space prologue */ cbf_failnez(cbf_write_ws_prologue(node, file, isbuffer)) /* Node type */ switch (node->type) { /* For the root, suppress automatic comments if whitespace handling has been specified */ case CBF_ROOT: if ( (file->write_headers & CBF_PARSE_WS) == 0 ) { cbf_failnez (cbf_write_string (file, "###" CBF_DIC_VERSION "\n")) if (file->write_encoding & ENC_NONE) { cbf_failnez (cbf_write_string (file, "# CBF file written by " CBF_API_VERSION "\n")) } else { cbf_failnez (cbf_write_string (file, "# CIF file written by " CBF_API_VERSION "\n")) } } break; case CBF_DATABLOCK: cbf_failnez (cbf_write_datablockname (node, file)) break; case CBF_CATEGORY: cbf_failnez (cbf_write_category (handle, node, file, isbuffer)) break; case CBF_SAVEFRAME: cbf_failnez (cbf_write_saveframename (node, file)) break; default: return CBF_ARGUMENT; } /* Write any appropriate white space emlogue */ cbf_failnez(cbf_write_ws_emlogue(node, file, isbuffer)) /* Write the children */ if (node->type == CBF_ROOT || node->type == CBF_DATABLOCK || node->type == CBF_SAVEFRAME) for (count = 0; count < node->children; count++) cbf_failnez (cbf_write_node (handle, node->child [count], file, isbuffer)) if (node->type == CBF_SAVEFRAME ) cbf_failnez (cbf_write_string (file, "\nsave_\n")) /* Write any appropriate white space epilogue */ if ( (file->write_headers & CBF_PARSE_WS) != 0 ) { cbf_failnez(cbf_write_ws_epilogue(node, file, isbuffer)) } /* Flush the buffers */ return cbf_flush_characters (file); } #ifdef __cplusplus } #endif ./CBFlib-0.9.2.2/src/cbf_codes.c0000644000076500007650000017723111603702106014453 0ustar yayayaya/********************************************************************** * cbf_codes -- convert between encoded and unencoded binary * * calculate message digest * * * * Version 0.7.7 19 February 2007 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ /********************************************************************** * Substantial portions of this code were derived from the mpack * * routine codes.c, which contains the following two notices * **********************************************************************/ /********************************************************************** * First notice from mpack routine codes.c: * * * * (C) Copyright 1993,1994 by Carnegie Mellon University * * All Rights Reserved. * * * * Permission to use, copy, modify, distribute, and sell this * * software and its documentation for any purpose is hereby granted * * without fee, provided that the above copyright notice appear * * in all copies and that both that copyright notice and this * * permission notice appear in supporting documentation, and that * * the name of Carnegie Mellon University not be used in advertising * * or publicity pertaining to distribution of the software without * * specific, written prior permission. Carnegie Mellon University * * makes no representations about the suitability of this software * * for any purpose. It is provided "as is" without express or * * implied warranty. * * * * CARNEGIE MELLON UNIVERSITY DISCLAIMS ALL WARRANTIES WITH REGARD TO * * THIS SOFTWARE, INCLUDING ALL IMPLIED WARRANTIES OF MERCHANTABILITY * * AND FITNESS, IN NO EVENT SHALL CARNEGIE MELLON UNIVERSITY BE * * LIABLE FOR ANY SPECIAL, INDIRECT OR CONSEQUENTIAL DAMAGES OR ANY * * DAMAGES WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, * * WHETHER IN AN ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS * * ACTION, ARISING OUT OF OR IN CONNECTION WITH THE USE OR * * PERFORMANCE OF THIS SOFTWARE. * **********************************************************************/ /********************************************************************** * Second notice from mpack routine codes.c: * * * * Copyright (c) 1991 Bell Communications Research, Inc. (Bellcore) * * * * Permission to use, copy, modify, and distribute this material * * for any purpose and without fee is hereby granted, provided * * that the above copyright notice and this permission notice * * appear in all copies, and that the name of Bellcore not be * * used in advertising or publicity pertaining to this * * material without the specific, prior written permission * * of an authorized representative of Bellcore. BELLCORE * * MAKES NO REPRESENTATIONS ABOUT THE ACCURACY OR SUITABILITY * * OF THIS MATERIAL FOR ANY PURPOSE. IT IS PROVIDED "AS IS", * * WITHOUT ANY EXPRESS OR IMPLIED WARRANTIES. * **********************************************************************/ #ifdef __cplusplus extern "C" { #endif #include "cbf_codes.h" #include #include #include #include #include #include #include /* Check a 24-character base-64 MD5 digest */ int cbf_is_base64digest (const char *encoded_digest) { static char basis_64 [] = "ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/"; if (!encoded_digest) return 0; if (strlen (encoded_digest) != 24) return 0; return strspn (encoded_digest, basis_64) == 22 && encoded_digest [22] == '=' && encoded_digest [23] == '='; } /* Encode a 16-character MD5 digest in base-64 (25 characters) */ int cbf_md5digest_to64 (char *encoded_digest, const unsigned char *digest) { static char basis_64 [] = "ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/"; int todo; if (!encoded_digest || !digest) return CBF_ARGUMENT; /* Encode the 16 characters in base 64 */ for (todo = 0; todo < 18; todo += 3) { encoded_digest [0] = basis_64 [((digest [todo + 0] >> 2) & 0x03f)]; if (todo < 15) { encoded_digest [1] = basis_64 [((digest [todo + 0] << 4) & 0x030) | ((digest [todo + 1] >> 4) & 0x00f)]; encoded_digest [2] = basis_64 [((digest [todo + 1] << 2) & 0x03c) | ((digest [todo + 2] >> 6) & 0x003)]; encoded_digest [3] = basis_64 [((digest [todo + 2]) & 0x03f)]; } else { encoded_digest [1] = basis_64 [((digest [todo + 0] << 4) & 0x030)]; encoded_digest [2] = encoded_digest [3] = '='; } encoded_digest += 4; } *encoded_digest = '\0'; return 0; } /* Calculate the MD5 digest (25 characters) of a block of data */ int cbf_md5digest (cbf_file *file, size_t size, char *digest) { MD5_CTX context; unsigned char rawdigest [17]; unsigned int todo; const char *buffer; /* Initialise the MD5 context */ MD5Init (&context); /* Update the digest in blocks of CBF_TRANSFER_BUFFER */ while (size > 0) { if (size >= CBF_TRANSFER_BUFFER) todo = CBF_TRANSFER_BUFFER; else todo = size; cbf_failnez (cbf_get_block (file, todo)) cbf_failnez (cbf_get_buffer (file, &buffer, NULL)) MD5Update (&context, buffer, todo); size -= todo; } /* Get the final digest */ MD5Final (rawdigest, &context); cbf_md5digest_to64 (digest, rawdigest); /* Success */ return 0; } /* Convert binary data to quoted-printable text */ int cbf_toqp (cbf_file *infile, cbf_file *outfile, size_t size) { static char basis_16 [] = "0123456789ABCDEF"; int c; /* Check the arguments */ if (!infile || !outfile) return CBF_ARGUMENT; /* Copy the characters */ while (size > 0) { /* Read the next character */ c = cbf_get_character (infile); if (c == EOF) return CBF_FILEREAD; size--; if (outfile->column > 74) cbf_failnez (cbf_write_string (outfile, "=\n")) if ((c <= 31) || (c >= 39 && c <= 41) || (c >= 43 && c <= 47) || (c == 58) || (c == 61) || (c == 63) || (c >= 127) || (c == ';' && outfile->column == 0)) { /* Base-16 */ if (outfile->column > 72) cbf_failnez (cbf_write_string (outfile, "=\n")) cbf_failnez (cbf_write_character (outfile, '=')) cbf_failnez (cbf_write_character (outfile, basis_16 [(c >> 4) & 0x0f])) cbf_failnez (cbf_write_character (outfile, basis_16 [c & 0x0f])) } else /* Base-256 */ cbf_failnez (cbf_write_character (outfile, c)) } if (outfile->column) cbf_failnez (cbf_write_string (outfile, "=\n")) /* Flush the buffer */ cbf_failnez (cbf_flush_characters (outfile)) /* Success */ return 0; } /* Convert binary data to base-64 text */ int cbf_tobase64 (cbf_file *infile, cbf_file *outfile, size_t size) { static char basis_64 [] = "ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/"; int c [3]; int read; while (size > 0) { /* Read up to 3 characters */ c [1] = c [2] = 0; for (read = 0; read < 3 && read < size; read++) { c [read] = cbf_get_character (infile); if (c [read] == EOF) return CBF_FILEREAD; } size -= read; if (outfile->column > 71) cbf_failnez (cbf_write_character (outfile, '\n')) /* Write a 24-bit chunk in base-64 */ cbf_failnez (cbf_write_character (outfile, basis_64 [(c [0] >> 2) & 0x03f])) cbf_failnez (cbf_write_character (outfile, basis_64 [((c [0] << 4) & 0x030) | ((c [1] >> 4) & 0x00f)])) if (read == 1) cbf_failnez (cbf_write_string (outfile, "==")) else { cbf_failnez (cbf_write_character (outfile, basis_64 [((c [1] << 2) & 0x03c) | ((c [2] >> 6) & 0x003)])) if (read == 2) cbf_failnez (cbf_write_character (outfile, '=')) else cbf_failnez (cbf_write_character (outfile, basis_64 [c [2] & 0x03f])) } } if (outfile->column) cbf_failnez (cbf_write_character (outfile, '\n')) /* Flush the buffer */ cbf_failnez (cbf_flush_characters (outfile)) /* Success */ return 0; } int cbf_tobase32k(cbf_file *infile, cbf_file *outfile, size_t size) { #define maxlen 30 unsigned char *txt = NULL; /*text to be encoded null terminated*/ char *enc = NULL; /*encoded text */ size_t* pencsize; /*pointer to the size of enc null terminated*/ size_t encsize = 0; /*size of enc*/ size_t sz = 0; /*number of characters read*/ size_t encchars = 0; /*number of encoded characters altogether*/ int bigEndian = 0; unsigned char tmp[3]; int count_w = 0; int rav = 0; unsigned char b; int count_enc=0; int new_l =0; tmp[2] = '\0'; txt = (unsigned char *) malloc(sizeof(char) *maxlen + 1); txt[maxlen] = '\0'; /*freaky but makes me feel better*/ pencsize = &encsize; sz =0; while(sz 0) { if(sz <30) { rav = 15 - ((sz*8)%15); } enc = cbf_encode32k_bit_op(txt, sz, pencsize); cbf_endianFix(enc ,*pencsize, 0, bigEndian); count_w = 0; while(count_w<*pencsize) { cbf_put_character(outfile, enc[count_w]); count_w++; count_enc++; } if(new_l == 0) { new_l++; } else if(new_l == 3) { cbf_put_character(outfile, '\x00'); cbf_put_character(outfile, '\x0A'); new_l =0; } encchars += *pencsize; if(enc){ free(enc); *pencsize = 0; } sz =0; while(sz=8 && rav<15) { if(cbf_isBigEndian() !=0) { cbf_put_character(outfile, '\x3D'); cbf_put_character(outfile, '\x00'); } else { cbf_put_character(outfile, '\x00'); cbf_put_character(outfile, '\x3D'); } } cbf_put_character(outfile, '\xEF'); cbf_put_character(outfile, '\xBB'); cbf_put_character(outfile, '\xBF'); free(txt); return 0; } char * cbf_encode32k_bit_op(unsigned char *txt, size_t size, size_t *size2) { #define offset 1 /*Formula: * * First loop bits taken from index-1: form n-1 to >= 0 ,right shift by + (7-n) * Second loop bits taken from index: from 7 to > n, right shift by -(n+1) * Fourth loop bits taken from index+1: from 7 to > n right shift by -(n+1) */ size_t pair = 0; int shift = 0; size_t n = 0; size_t indx = 0; size_t index = 0; size_t pairs = 0; unsigned char first = 0; unsigned char second = 0; unsigned char mask = 1; unsigned char result = 0; char * res = NULL; /*the encoded string (result)*/ /*find out the number of pairs and the length of the string enc*/ pairs = ceil(((double)size *8.0)/15.0); /*On every 16 bits we have one bit lost so we use 16 bits for encoding 15 bits */ *size2 = pairs *2; res = (char *) malloc(sizeof(char)*(*size2)); memset(res, 0, *size2); /*loop through all pairs and encode them */ for(pair = 0; pair< pairs; pair++) { n = pair%8; indx = pair*2; index = indx - (pair/8); first = 0; second = 0; result = 0; /*encoding algorithm starts*/ /*First character*/ if(index <= size) { for(shift =n-1;shift >=0;shift--) { result = txt[index-1]>>shift; result = result & mask; first += result << (shift +(7 - n)); } if(index < size){ for(shift = 7; shift > n; shift--) { result = txt[index] >> shift; result = result & mask; first += result << (shift - (n + 1)); } /*fill in the second character*/ for(shift = n;shift >= 0; shift--) { result = txt[index] >> shift; result = result & mask; second += result << (shift + (7 -n)); } if((index + 1) < size){ for(shift = 7; shift > n; shift --) { result = txt[index+1] >> shift; result = result & mask; second += result << (shift - (n+1)); } } } } res[indx] = first + offset; res[indx+1] = second; } return res; } /*Determine whether the machine is little endian*/ int cbf_isBigEndian() { long tmp = 1; return !(*(char *)(&tmp)); } void cbf_endianFix(char *str, size_t size, int fromEndian, int toEndian) { size_t i = 0; if(fromEndian != toEndian){ for (i = 0; i < size; i+=2) { /*exchange the two bytes*/ /*since we are in bitwise mood use the triple xor trick*/ str[i] ^= str[i+1]; str[i+1] ^= str[i]; str[i] ^= str[i+1]; } } } /* Convert binary data to base-8/base-10/base-16 text */ int cbf_tobasex (cbf_file *infile, cbf_file *outfile, size_t size, size_t elsize, unsigned int base) { int c [8]; int count, read; long l; unsigned long block_count; char line [96], number [64]; /* Check the arguments */ if (elsize > 8 || (base != 8 && base != 10 && base != 16)) return CBF_ARGUMENT; block_count = 0; while (size > 0) { /* End of a 512-element block? */ if ((block_count % 512) == 0) { if (outfile->column) cbf_failnez (cbf_write_character (outfile, '\n')) if (block_count) cbf_failnez (cbf_write_string (outfile, "#\n")) if (base == 8) cbf_failnez (cbf_write_string (outfile, "# Octal encoding")) else if (base == 10) cbf_failnez (cbf_write_string (outfile, "# Decimal encoding")) else cbf_failnez (cbf_write_string (outfile, "# Hexadecimal encoding")) sprintf (line, ", byte %lu", (unsigned long) block_count * elsize); cbf_failnez (cbf_write_string (outfile, line)) if (outfile->write_encoding & ENC_FORWARD) cbf_failnez (cbf_write_string (outfile, ", byte order 1234...\n#\n")) else cbf_failnez (cbf_write_string (outfile, ", byte order ...4321\n#\n")) } /* Read up to elsize characters */ memset (c, 0, sizeof (c)); for (read = 0; read < elsize && read < size; read++) { c [read] = cbf_get_character (infile); if (c [read] == EOF) return CBF_FILEREAD; } size -= read; block_count++; /* Make the number */ number [0] = '\0'; if ((outfile->write_encoding & ENC_BACKWARD) && read < elsize) for (count = read; count < elsize; count++) strcat (number, "=="); l = 0; if (outfile->write_encoding & ENC_FORWARD) for (count = read - 1; count >= 0; count--) l = (l << 8) | (c [count] & 0x0ff); else for (count = 0; count < read; count++) l = (l << 8) | (c [count] & 0x0ff); if (base == 8) sprintf (number + strlen (number), "%lo", l); else if (base == 10) sprintf (number + strlen (number), "%lu", l); else sprintf (number + strlen (number), "%lX", l); if ((outfile->write_encoding & ENC_FORWARD) && read < elsize) for (count = read; count < elsize; count++) strcat (number, "=="); /* Write the number */ if (outfile->column + strlen (number) > 74) cbf_failnez (cbf_write_character (outfile, '\n')) if (outfile->column) cbf_failnez (cbf_write_character (outfile, ' ')) else { /* Start a new line */ if (base == 8) cbf_failnez (cbf_write_character (outfile, 'O')) else if (base == 10) cbf_failnez (cbf_write_character (outfile, 'D')) else cbf_failnez (cbf_write_character (outfile, 'H')) sprintf (line, "%1u", (unsigned int) elsize); cbf_failnez (cbf_write_string (outfile, line)) if (outfile->write_encoding & ENC_FORWARD) cbf_failnez (cbf_write_string (outfile, "> ")) else cbf_failnez (cbf_write_string (outfile, "< ")) } cbf_failnez (cbf_write_string (outfile, number)) } if (outfile->column) cbf_failnez (cbf_write_character (outfile, '\n')) /* Flush the buffer */ cbf_failnez (cbf_flush_characters (outfile)) /* Success */ return 0; } /* Convert quoted-printable text to binary data */ int cbf_fromqp (cbf_file *infile, cbf_file *outfile, size_t size, size_t *readsize, char *digest) { MD5_CTX context; unsigned char buffer [64], rawdigest [17]; int c, bufsize; char val [3], *end; size_t count; /* Initialise the MD5 context */ if (digest) MD5Init (&context); bufsize = 0; count = 0; val [2] = '\0'; while (count < size) { /* Read the (first) character */ c = cbf_read_character (infile); if (c == EOF) return CBF_FILEREAD; /* Decode it */ if (c == '=') { /* Get the second character */ c = cbf_read_character (infile); if (c == EOF) return CBF_FILEREAD; if (c != '\n') { /* Get the third character */ val [0] = c; c = cbf_read_character (infile); if (c == EOF) return CBF_FILEREAD; val [1] = c; /* Calculate the value */ c = strtoul (val, &end, 16); if (end != &val [2]) return CBF_FORMAT; } } /* Save it */ if (outfile) cbf_failnez (cbf_put_character (outfile, c)) if (digest) { buffer [bufsize] = c; bufsize++; if (bufsize > 63) { MD5Update (&context, buffer, 64); bufsize = 0; } } count++; } /* Get the digest */ if (digest) { if (bufsize) MD5Update (&context, buffer, bufsize); MD5Final (rawdigest, &context); cbf_md5digest_to64 (digest, rawdigest); } /* Flush the buffer */ if (outfile) cbf_failnez (cbf_flush_characters (outfile)) /* Save the number of characters read */ if (readsize) *readsize = count; /* Success */ return 0; } /* Convert base-64 text to binary data */ int cbf_frombase64 (cbf_file *infile, cbf_file *outfile, size_t size, size_t *readsize, char *digest) { static int decode_64 [256] = { -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, 62, -1, -1, -1, 63, 52, 53, 54, 55, 56, 57, 58, 59, 60, 61, -1, -1, -1, 64, -1, -1, -1, 0, 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, -1, -1, -1, -1, -1, -1, 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, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1, -1 }; MD5_CTX context; unsigned char buffer [64], rawdigest [17]; int c [4], d [3], bufsize; int read, write; size_t count; /* Initialise the MD5 context */ if (digest) MD5Init (&context); count = 0; bufsize = 0; while (count < size) { /* Read 4 characters */ for (read = 0; read < 4; read++) do { c [read] = cbf_read_character (infile); if (c [read] == EOF) return CBF_FILEREAD; } while (decode_64 [c [read] & 0x0ff] < 0); /* End of data? */ if (c [0] == '=' || c [1] == '=') break; /* Valid combinations: xxxx xxx= xx== */ c [0] = decode_64 [c [0] & 0x0ff]; c [1] = decode_64 [c [1] & 0x0ff]; c [2] = decode_64 [c [2] & 0x0ff]; c [3] = decode_64 [c [3] & 0x0ff]; d [0] = ((c [0] << 2) & 0x0fc) | ((c [1] >> 4) & 0x003); d [1] = ((c [1] << 4) & 0x0f0) | ((c [2] >> 2) & 0x00f); d [2] = ((c [2] << 6) & 0x0c0) | ((c [3] ) & 0x03f); if (c [2] == 64) read = 1; else if (c [3] == 64) read = 2; else read = 3; /* Save the data */ for (write = 0; write < read; write++) { if (outfile) cbf_failnez (cbf_put_character (outfile, d [write])) if (digest) { buffer [bufsize] = (unsigned char) d [write]; bufsize++; if (bufsize > 63) { MD5Update (&context, buffer, 64); bufsize = 0; } } } count += read; } /* Get the digest */ if (digest) { if (bufsize) MD5Update (&context, buffer, bufsize); MD5Final (rawdigest, &context); cbf_md5digest_to64 (digest, rawdigest); } /* Flush the buffer */ if (outfile) cbf_failnez (cbf_flush_characters (outfile)) /* Save the number of characters read */ if (readsize) *readsize = count; /* Success */ return 0; } int cbf_frombase32k(cbf_file *infile, cbf_file *outfile, size_t size, size_t *readsize, char *digest) { MD5_CTX context; unsigned char buffer[64], rawdigest [17]; int bufsize; char *enc = NULL; /*encoded text */ char *decoded = NULL; /*decoded text (should be the same as txt)*/ size_t sz = 0; int mah =0; /*the number of bytes that should be cut from the end*/ int clear; char b ='\0'; int a = 0; int sc; int count_w =0; int check_range =0; size_t all = 0; /* Initialize the MD5 context*/ if (digest) MD5Init(&context); bufsize =0; enc = (char *) malloc(32*sizeof(char)); decoded = (char *) malloc(30*sizeof(char)); sz =0; while(sz<2) { a =0; if((a = cbf_get_character(infile)) !=EOF) { b = a; enc[sz] =b; } else { break; } sz++; } if((enc[0] == '\xFF' && enc[1] == '\xFE' && cbf_isBigEndian() == 0) || (enc[0] == '\xFE' && enc[1] == '\xFF' && cbf_isBigEndian() !=0)) { sz =0; while(sz<32) { a =0; if((a = cbf_get_character(infile)) !=EOF) { if(sz%2 == 0) { b = a; check_range =a; } else if(sz%2 == 1) { check_range = check_range+256*a; if((check_range < 256 || check_range > 33023) && (check_range != 61 && check_range != 61371)) { sz--; continue; } else { enc[sz-1] =b; b =a; enc[sz] =b; } } } else { break; } sz++; } if(cbf_isBigEndian() == 0) /* it is big endian */ { cbf_endianFix(enc, sz, 1, 0); } else if(cbf_isBigEndian() != 0) { cbf_endianFix(enc, sz, 0, 1); } sc=0; while(sc0) { if(sz>0 && sz<18) { if(enc[sz-2] == '\x00' && enc[sz-1] == '\x3D') { cbf_decode32k_bit_op(enc, decoded, (sz-2)); count_w=0; while(count_w<(sz-4)) { if(outfile) cbf_failnez(cbf_put_character(outfile, decoded[count_w])); if (digest) { buffer[bufsize] = decoded[count_w]; bufsize++; if (bufsize >63) { MD5Update( &context, buffer, 64); bufsize = 0; } } count_w++; all++; } sz=0; } else{ size_t temp = sz; cbf_decode32k_bit_op(enc, decoded, temp); count_w=0; while(count_w<(temp-1)) { if(outfile) cbf_failnez(cbf_put_character(outfile, decoded[count_w])); if (digest) { buffer[bufsize] = decoded[count_w]; bufsize++; if (bufsize >63) { MD5Update( &context, buffer, 64); bufsize = 0; } } count_w++; all++; } } for (clear=0; clear<30; clear++) { decoded[clear]='\0'; } sz = 0; break; } else if(sz == 18) { if(enc[16] == '\x00' && enc[17] == '\x3D') { mah = 1; cbf_decode32k_bit_op(enc, decoded, (sz-2)); count_w=0; while(count_w<(sz-4)) { if(outfile) cbf_failnez(cbf_put_character(outfile, decoded[count_w])); if (digest) { buffer[bufsize] = decoded[count_w]; bufsize++; if (bufsize >63) { MD5Update( &context, buffer, 64); bufsize = 0; } } count_w++; all++; } } else { int temp = sz; cbf_decode32k_bit_op(enc, decoded, temp); count_w=0; while(count_w<(temp-2)) { if(outfile) cbf_failnez(cbf_put_character(outfile, decoded[count_w])); if (digest) { buffer[bufsize] = decoded[count_w]; bufsize++; if (bufsize >63) { MD5Update( &context, buffer, 64); bufsize = 0; } } count_w++; all++; } sz=-1; } for (clear=0; clear<30; clear++) { decoded[clear]='\0'; } sz=0; } else if(sz>18 && sz<32) { if(enc[sz-2]=='\x00' && enc[sz-1] =='\x3D') { cbf_decode32k_bit_op(enc, decoded, (sz-2)); count_w=0; while(count_w<(sz-5)) { if(outfile) cbf_failnez(cbf_put_character(outfile, decoded[count_w])); if (digest) { buffer[bufsize] = decoded[count_w]; bufsize++; if (bufsize >63) { MD5Update( &context, buffer, 64); bufsize = 0; } } count_w++; all++; } sz=0; } else{ int temp = sz; cbf_decode32k_bit_op(enc, decoded, temp); count_w=0; while(count_w<(temp-2)) { if(outfile) cbf_failnez(cbf_put_character(outfile, decoded[count_w])); if (digest) { buffer[bufsize] = decoded[count_w]; bufsize++; if (bufsize >63) { MD5Update( &context, buffer, 64); bufsize = 0; } } count_w++; all++; } } for (clear=0; clear<30; clear++) { decoded[clear]='\0'; } sz=0; } else if (sz == 32) { if(enc[30] == '\x00' && enc[31] == '\x3D') { cbf_decode32k_bit_op(enc, decoded, (sz-2)); count_w=0; while(count_w<(sz-5)) { if(outfile) cbf_failnez(cbf_put_character(outfile, decoded[count_w])); if (digest) { buffer[bufsize] = decoded[count_w]; bufsize++; if (bufsize >63) { MD5Update( &context, buffer, 64); bufsize = 0; } } count_w++; all++; } sz=0; } else { cbf_decode32k_bit_op(enc, decoded, 32); sz =0; while(sz<32) { a =0; if((a = cbf_get_character(infile)) !=EOF) { if(sz%2 == 0) { b = a; check_range = a; } else if (sz%2 == 1) { check_range = check_range + 256*a; if((check_range < 256 || check_range > 33023) && (check_range != 61 && check_range != 61371)) { sz--; continue; } else{ enc[sz-1] =b; b =a; enc[sz] =b; } } } else{ break; } sz++; } if(cbf_isBigEndian() == 0) /*it is big endian */ { cbf_endianFix(enc, sz, 1, 0); } else if(cbf_isBigEndian() != 0) { cbf_endianFix(enc, sz, 0, 1); } sc =0; while(sc63) { MD5Update( &context, buffer, 64); bufsize = 0; } } count_w++; all++; } for (clear=0; clear<30; clear++) { decoded[clear]='\0'; } sz=0; } else { count_w=0; while(count_w<30) { if(outfile) cbf_failnez(cbf_put_character(outfile, decoded[count_w])); if (digest) { buffer[bufsize] = decoded[count_w]; bufsize++; if (bufsize >63) { MD5Update( &context, buffer, 64); bufsize = 0; } } count_w++; all++; } for (clear=0; clear<30; clear++) { decoded[clear]='\0'; } } } } } /* Get the digest */ if (digest) { if (bufsize) MD5Update (&context, buffer, bufsize); MD5Final (rawdigest, &context); cbf_md5digest_to64 (digest, rawdigest); } /* Flush the buffer */ if (outfile) cbf_failnez (cbf_flush_characters (outfile)) /* Save the number of characters read */ if (readsize) *readsize = all; free(enc); free(decoded); return 0; } else if((enc[0] == '\xFF' && enc[1] == '\xFE') || (enc[0] == '\xFE' && enc[1] == '\xFF') ) { sz =0; while(sz<32) { a =0; if((a = cbf_get_character(infile)) !=EOF) { if(sz%2 == 0) { b = a; check_range =256*a; } else if(sz%2 == 1) { check_range = check_range+a; if((check_range < 256 || check_range > 33023) && (check_range != 61 && check_range != 61371)) { sz--; continue; } else { enc[sz-1] =b; b =a; enc[sz] =b; } } } else { break; } sz++; } sc=0; while(sc0) { if(sz>0 && sz<18) { if(enc[sz-2] == '\x00' && enc[sz-1] == '\x3D') { cbf_decode32k_bit_op(enc, decoded, (sz-2)); count_w=0; while(count_w<(sz-4)) { if(outfile) cbf_failnez(cbf_put_character(outfile, decoded[count_w])); if (digest) { buffer[bufsize] = decoded[count_w]; bufsize++; if (bufsize >63) { MD5Update( &context, buffer, 64); bufsize = 0; } } count_w++; all++; } sz=0; } else{ size_t temp = sz; cbf_decode32k_bit_op(enc, decoded, temp); count_w=0; while(count_w<(temp-1)) { if(outfile) cbf_failnez(cbf_put_character(outfile, decoded[count_w])); if (digest) { buffer[bufsize] = decoded[count_w]; bufsize++; if (bufsize >63) { MD5Update( &context, buffer, 64); bufsize = 0; } } count_w++; all++; } } for (clear=0; clear<30; clear++) { decoded[clear]='\0'; } sz = 0; break; } else if(sz == 18) { if(enc[16] == '\x00' && enc[17] == '\x3D') { mah = 1; cbf_decode32k_bit_op(enc, decoded, (sz-2)); count_w=0; while(count_w<(sz-4)) { if(outfile) cbf_failnez(cbf_put_character(outfile, decoded[count_w])); if (digest) { buffer[bufsize] = decoded[count_w]; bufsize++; if (bufsize >63) { MD5Update( &context, buffer, 64); bufsize = 0; } } count_w++; all++; } } else { int temp = sz; cbf_decode32k_bit_op(enc, decoded, temp); count_w=0; while(count_w<(temp-2)) { if(outfile) cbf_failnez(cbf_put_character(outfile, decoded[count_w])); if (digest) { buffer[bufsize] = decoded[count_w]; bufsize++; if (bufsize >63) { MD5Update( &context, buffer, 64); bufsize = 0; } } count_w++; all++; } sz=-1; } for (clear=0; clear<30; clear++) { decoded[clear]='\0'; } sz=0; } else if(sz>18 && sz<32) { if(enc[sz-2]=='\x00' && enc[sz-1] =='\x3D') { cbf_decode32k_bit_op(enc, decoded, (sz-2)); count_w=0; while(count_w<(sz-5)) { if(outfile) cbf_failnez(cbf_put_character(outfile, decoded[count_w])); if (digest) { buffer[bufsize] = decoded[count_w]; bufsize++; if (bufsize >63) { MD5Update( &context, buffer, 64); bufsize = 0; } } count_w++; all++; } sz=0; } else{ int temp = sz; cbf_decode32k_bit_op(enc, decoded, temp); count_w=0; while(count_w<(temp-2)) { if(outfile) cbf_failnez(cbf_put_character(outfile, decoded[count_w])); if (digest) { buffer[bufsize] = decoded[count_w]; bufsize++; if (bufsize >63) { MD5Update( &context, buffer, 64); bufsize = 0; } } count_w++; all++; } } for (clear=0; clear<30; clear++) { decoded[clear]='\0'; } sz=0; } else if (sz == 32) { if(enc[30] == '\x00' && enc[31] == '\x3D') { cbf_decode32k_bit_op(enc, decoded, (sz-2)); count_w=0; while(count_w<(sz-5)) { if(outfile) cbf_failnez(cbf_put_character(outfile, decoded[count_w])); if (digest) { buffer[bufsize] = decoded[count_w]; bufsize++; if (bufsize >63) { MD5Update( &context, buffer, 64); bufsize = 0; } } count_w++; all++; } sz=0; } else { cbf_decode32k_bit_op(enc, decoded, 32); sz =0; while(sz<32) { a =0; if((a = cbf_get_character(infile)) !=EOF) { if(sz%2 == 0) { b = a; check_range = 256*a; } else if (sz%2 == 1) { check_range = check_range + a; if((check_range < 256 || check_range > 33023) && (check_range != 61 && check_range != 61371)) { sz--; continue; } else{ enc[sz-1] =b; b =a; enc[sz] =b; } } } else{ break; } sz++; } sc =0; while(sc63) { MD5Update( &context, buffer, 64); bufsize = 0; } } count_w++; all++; } for (clear=0; clear<30; clear++) { decoded[clear]='\0'; } sz=0; } else { count_w=0; while(count_w<30) { if(outfile) cbf_failnez(cbf_put_character(outfile, decoded[count_w])); if (digest) { buffer[bufsize] = decoded[count_w]; bufsize++; if (bufsize >63) { MD5Update( &context, buffer, 64); bufsize = 0; } } count_w++; all++; } for (clear=0; clear<30; clear++) { decoded[clear]='\0'; } } } } } /* Get the digest */ if (digest) { if (bufsize) MD5Update (&context, buffer, bufsize); MD5Final (rawdigest, &context); cbf_md5digest_to64 (digest, rawdigest); } /* Flush the buffer */ if (outfile) cbf_failnez (cbf_flush_characters (outfile)) /* Save the number of characters read */ if (readsize) *readsize = all; free(enc); free(decoded); return 0; } else { printf("The file given for decoding was not correctly encoded!"); free(enc); free(decoded); return -1; } } int cbf_decode32k_bit_op(char *encoded, char *decoded, size_t size) { unsigned char tmp = '\0'; unsigned char result = '\0'; unsigned char mask = 1; size_t i = 0,j=0; int need= 7, have = -1; for(i = 0;i < size; i++) { result= '\0'; need = 7; /*zero based*/ /*make another loop form 0 to need and add bits to result until need is zero*/ while(need > -1) { /*if there are no more bits left take the next character*/ if(have == -1){ /*if this is the first character in a pair then subtract the offset *and record that it has only 7 bits */ if(j % 2== 0){ tmp = encoded[j] -offset; have = 6; } else { tmp = encoded[j]; have = 7; } j++; } result = tmp >>have; result = result & mask; result = result <') { direction = 1; c = ' '; } else if (c == '<') { direction = -1; c = ' '; } else if (c == '#') { /* Comment */ do c = cbf_read_character (infile); while (c != EOF && c != '\n'); if (c == EOF) return CBF_FORMAT; } switch (infile->column) { case 1: if (c == 'O' || c == 'o') base = 8; else if (c == 'D' || c == 'd') base = 10; else if (c == 'H' || c == 'h') base = 16; else return CBF_FORMAT; break; case 2: if (isdigit (c) && c != '0') elsize = c - '0'; case 3: break; default: if (!isspace (c)) if (c == '=') padding++; else { /* Save the character */ if (valcount > 78) return CBF_FORMAT; val [valcount] = c; valcount++; } else if (valcount) { /* Convert the number */ val [valcount] = '\0'; l = strtoul (val, &end, base); if (end != &val [valcount]) return CBF_FORMAT; /* Save the binary data */ if ((padding % 2) || padding > 6) return CBF_FORMAT; read = elsize - padding / 2; for (write = 0; write < read; write++) { if (direction < 0) c = (unsigned char) ((l >> ((read - write - 1) * 8)) & 0x0ff); else c = (unsigned char) ((l >> (write * 8)) & 0x0ff); if (outfile) cbf_failnez (cbf_put_character (outfile, c)) if (digest) { buffer [bufsize] = (unsigned char) c; bufsize++; if (bufsize > 63) { MD5Update (&context, buffer, 64); bufsize = 0; } } } count += read; valcount = 0; padding = 0; } } } /* Get the digest */ if (digest) { if (bufsize) MD5Update (&context, buffer, bufsize); MD5Final (rawdigest, &context); cbf_md5digest_to64 (digest, rawdigest); } /* Flush the buffer */ if (outfile) cbf_failnez (cbf_flush_characters (outfile)) /* Save the number of characters read */ if (readsize) *readsize = count; /* Success */ return 0; } #ifdef __cplusplus } #endif ./CBFlib-0.9.2.2/src/cbf_packed.c0000644000076500007650000014467411603702106014612 0ustar yayayaya/********************************************************************** * cbf_packed -- Packing compression * * * * Version 0.8.0 20 July 2008 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifdef __cplusplus extern "C" { #endif #include #include #include #include #include "cbf.h" #include "cbf_alloc.h" #include "cbf_compress.h" #include "cbf_file.h" #include "cbf_packed.h" #define CBF_SHIFT63 (sizeof (int) * CHAR_BIT > 64 ? 63 : 0) typedef struct { unsigned int offset [128][4]; unsigned int size [128]; unsigned int start; unsigned int offsets; } cbf_packed_data; #define CBF_PACKED_BITS1 4 #define CBF_PACKED_BITS2 5 #define CBF_PACKED_BITS3 6 #define CBF_PACKED_BITS4 7 #define CBF_PACKED_BITS5 8 #define CBF_PACKED_BITS6 16 #define CBF_PACKED_V2_BITS1 3 #define CBF_PACKED_V2_BITS2 4 #define CBF_PACKED_V2_BITS3 5 #define CBF_PACKED_V2_BITS4 6 #define CBF_PACKED_V2_BITS5 7 #define CBF_PACKED_V2_BITS6 8 #define CBF_PACKED_V2_BITS7 9 #define CBF_PACKED_V2_BITS8 10 #define CBF_PACKED_V2_BITS9 11 #define CBF_PACKED_V2_BITS10 12 #define CBF_PACKED_V2_BITS11 13 #define CBF_PACKED_V2_BITS12 14 #define CBF_PACKED_V2_BITS13 15 #define CBF_PACKED_V2_BITS14 16 #define CBF_PACKED_MASK1 ~15 #define CBF_PACKED_MASK2 ~31 #define CBF_PACKED_MASK3 ~63 #define CBF_PACKED_MASK4 ~127 #define CBF_PACKED_MASK5 ~255 #define CBF_PACKED_MASK6 ~65535 #define CBF_PACKED_V2_MASK1 ~7 #define CBF_PACKED_V2_MASK2 ~15 #define CBF_PACKED_V2_MASK3 ~31 #define CBF_PACKED_V2_MASK4 ~63 #define CBF_PACKED_V2_MASK5 ~127 #define CBF_PACKED_V2_MASK6 ~255 #define CBF_PACKED_V2_MASK7 ~511 #define CBF_PACKED_V2_MASK8 ~1023 #define CBF_PACKED_V2_MASK9 ~2047 #define CBF_PACKED_V2_MASK10 ~4095L #define CBF_PACKED_V2_MASK11 ~8191 #define CBF_PACKED_V2_MASK12 ~16383 #define CBF_PACKED_V2_MASK13 ~32767 #define CBF_PACKED_V2_MASK14 ~65535 static const unsigned int cbf_packed_bits [8] = { 0, CBF_PACKED_BITS1, CBF_PACKED_BITS2, CBF_PACKED_BITS3, CBF_PACKED_BITS4, CBF_PACKED_BITS5, CBF_PACKED_BITS6, 65 }; static const unsigned int cbf_packedv2_bits [16] = { 0, CBF_PACKED_V2_BITS1, CBF_PACKED_V2_BITS2, CBF_PACKED_V2_BITS3, CBF_PACKED_V2_BITS4, CBF_PACKED_V2_BITS5, CBF_PACKED_V2_BITS6, CBF_PACKED_V2_BITS7, CBF_PACKED_V2_BITS8, CBF_PACKED_V2_BITS9, CBF_PACKED_V2_BITS10, CBF_PACKED_V2_BITS11, CBF_PACKED_V2_BITS12, CBF_PACKED_V2_BITS13, CBF_PACKED_V2_BITS14, 65 }; /* Add an integer to the array of offsets to write (version 2) */ int cbf_add_offsetv2 (cbf_packed_data *data, unsigned int *element, unsigned int *last_element, int numints) { unsigned int offset[4] = {0, 0, 0, 0}; int i, issmall; unsigned int index, m; /* Save the offset */ index = (data->offsets + data->start) & 127; if (numints > 1) { for (i = 0; i < numints; i++) offset[i] = last_element[i]; cbf_failnez(cbf_mpint_negate_acc(offset,numints)) cbf_failnez(cbf_mpint_add_acc(offset,numints,element,numints)) } else{ offset[0] = element[0] - last_element[0]; if ((int)(offset[0])<0) for(i=1;ioffset [index][i] = offset[i]; /* How many bits do we need to save? */ issmall = 1; for (i = 1; i < numints; i++) { if (((int)offset[0]>=0 && (int)offset[i] != 0) || ((int)offset[0]<0 && 1+(int)offset[i] !=0 )) issmall = 0; } if (!issmall) { data->size [index] = 15; } else { if (offset[0] == 0) data->size [index] = 0; else if ((element[0] < last_element[0] && (int)offset[0] > 0) || (element[0] > last_element[0] && (int)offset[0] < 0)) { for (i = 1; i < 4; i++) data->offset[index][i] = (int)offset[0]<0?0:~0; data->size [index] = 15; } else { m = (offset[0] ^ (offset[0] << 1)); if ((m & CBF_PACKED_V2_MASK1) == 0) data->size [index] = 1; else if ((m & CBF_PACKED_V2_MASK2) == 0) data->size [index] = 2; else if ((m & CBF_PACKED_V2_MASK3) == 0) data->size [index] = 3; else if ((m & CBF_PACKED_V2_MASK4) == 0) data->size [index] = 4; else if ((m & CBF_PACKED_V2_MASK5) == 0) data->size [index] = 5; else if ((m & CBF_PACKED_V2_MASK6) == 0) data->size [index] = 6; else if ((m & CBF_PACKED_V2_MASK7) == 0) data->size [index] = 7; else if ((m & CBF_PACKED_V2_MASK8) == 0) data->size [index] = 8; else if ((m & CBF_PACKED_V2_MASK9) == 0) data->size [index] = 9; else if ((m & CBF_PACKED_V2_MASK10) == 0) data->size [index] = 10; else if ((m & CBF_PACKED_V2_MASK11) == 0) data->size [index] = 11; else if ((m & CBF_PACKED_V2_MASK12) == 0) data->size [index] = 12; else if ((m & CBF_PACKED_V2_MASK13) == 0) data->size [index] = 13; else if ((m & CBF_PACKED_V2_MASK14) == 0) data->size [index] = 14; else data->size [index] = 15; } } /* Success */ data->offsets++; return 0; } /* Add an integer to the array of offsets to write (version 1) */ int cbf_add_offset (cbf_packed_data *data, unsigned int *element, unsigned int *last_element, int numints) { unsigned int offset[4]; int i, issmall; unsigned int index, m; /* Save the offset */ index = (data->offsets + data->start) & 127; if (numints > 1) { for (i = 0; i < numints; i++) offset[i] = last_element[i]; cbf_failnez(cbf_mpint_negate_acc(offset,numints)) cbf_failnez(cbf_mpint_add_acc(offset,numints,element,numints)) } else { offset[0] = element[0] - last_element[0]; } for (i = 0; i < numints; i++) data->offset [index][i] = offset[i]; /* How many bits do we need to save? */ issmall = 1; for (i = 1; i < numints; i++) { if (((int)offset[0]>=0 && offset[i] != 0) || ((int)offset[0]<0 && 1+(int)offset[i] !=0 )) issmall = 0; } if (!issmall) { data->size [index] = 7; } else { if (offset[0] == 0) data->size [index] = 0; else if ((element[0] < last_element[0] && (int)offset[0] > 0) || (element[0] > last_element[0] && (int)offset[0] < 0)) { for (i = 1; i < 4; i++) data->offset[index][i] = (int)offset[0]<0?0:~0; data->size [index] = 7; } else { m = (offset[0] ^ (offset[0] << 1)); if ((m & CBF_PACKED_MASK1) == 0) data->size [index] = 1; else if ((m & CBF_PACKED_MASK2) == 0) data->size [index] = 2; else if ((m & CBF_PACKED_MASK3) == 0) data->size [index] = 3; else if ((m & CBF_PACKED_MASK4) == 0) data->size [index] = 4; else if ((m & CBF_PACKED_MASK5) == 0) data->size [index] = 5; else if ((m & CBF_PACKED_MASK6) == 0) data->size [index] = 6; else data->size [index] = 7; } } /* Success */ data->offsets++; return 0; } /* Pack 1 << chunk offsets in [size] bits each The flag v2flag selects version 1 (v2flag = 0) or version 2 (v2flag = 1) */ int cbf_pack_chunk (cbf_packed_data *data, int size, int chunk, cbf_file *file, unsigned long *bitcount, int v2flag, int clipbits) { unsigned int count, index, pbits, j; size_t numints; int zero[4] = { 0, 0, 0, 0}; /* Write the codes */ cbf_failnez (cbf_put_integer (file, (size << 3) | chunk, 0, 6+v2flag)) chunk = 1 << chunk; pbits = v2flag?cbf_packedv2_bits[size]:cbf_packed_bits[size]; if (clipbits && pbits==65) pbits = clipbits; numints = (pbits + CHAR_BIT*sizeof (int) -1)/(CHAR_BIT*sizeof (int)); if (!clipbits) numints=1; if (size > 0) { index = data->start; if (pbits == 65) { for (count = chunk; count; count--, index++) { for (j = 0; j < numints; j++) { cbf_failnez (cbf_put_bits (file, (int *)(j+(data->offset [index & 127])), sizeof(int)*CHAR_BIT)) } if (pbits > numints*sizeof(int)*CHAR_BIT) { cbf_failnez (cbf_put_bits (file, zero, pbits-numints*sizeof(int)*CHAR_BIT)) } } } else { for (count = chunk; count; count--, index++) cbf_failnez (cbf_put_bits (file, (int *)data->offset [index & 127], pbits)) } } /* Update the buffer count and start */ data->start = (data->start + chunk) & 127; data->offsets -= chunk; /* Calculate the number of bits written */ if (bitcount) { if (size) *bitcount = 6 + v2flag + chunk * pbits; else *bitcount = 6 + v2flag; } /* Success */ return 0; } /* Get the maximum size required to code 1 << chunk offsets */ unsigned int cbf_maximum_size (cbf_packed_data *data, unsigned int start, unsigned int chunk) { unsigned int maxsize, index, count; /* Get the maximum size */ maxsize = 0; index = data->start + start; for (count = 1 << chunk; count; count--) { if (data->size [index & 127] > maxsize) maxsize = data->size [index & 127]; index++; } return maxsize; } /* Write out a block as economically as possible The flag v2flag selects version 1 (v2flag = 0) or version 2 (v2flag = 1) */ int cbf_pack_nextchunk (cbf_packed_data *data, cbf_file *file, unsigned long *bitcount, int v2flag, int clipbits) { unsigned int bits, pbits, next_bits, chunk, size, next_size, combined_bits, combined_size; /* Number of bits to encode a single offset */ size = cbf_maximum_size (data, 0, 0); pbits = v2flag?cbf_packedv2_bits[size]:cbf_packed_bits[size]; bits = pbits + 6 + v2flag; chunk = 0; while (data->offsets >= (2 << chunk)) { next_size = cbf_maximum_size (data, 1 << chunk, chunk); pbits = v2flag?cbf_packedv2_bits[next_size]:cbf_packed_bits[next_size]; next_bits = (pbits << chunk) + 6 + v2flag; if (size > next_size) { combined_bits = bits * 2 - 6 - v2flag; combined_size = size; } else { combined_bits = next_bits * 2 - 6 - v2flag; combined_size = next_size; } if (combined_bits > bits + next_bits) return cbf_pack_chunk (data, size, chunk, file, bitcount, v2flag, clipbits); bits = combined_bits; size = combined_size; chunk++; } return cbf_pack_chunk (data, size, chunk, file, bitcount, v2flag, clipbits); } /* Update pointers for averaging in J. P. Abrahams CCP4 compression algorithm. On entry, trail_char_data[0] should point to the data element immediately prior to the next data element to be processed, either in the same row (fastest index) or, at the end of the prior row if the next data element to be processed is at the end of a row ndimfast, ndimmid, ndimslow should point to the indices of the same data element as trail_char_data[0] points to. These values will be incremented to be the indices of the next data element to be processed before populating trail_char_data. On exit, trail_char_data[0..7] will have been populated with pointers to the data elements to be used in forming the average. Elements that will not be used will be set to NULL. Note that trail_char_data[0] may be set to NULL. If we mark the next element to be processed with a "*" and the entries in trail_char_data with their array indices 0 .. 7, the possible patterns of settings in the general case are: current section: - - - - 0 * - - - - - - - - 3 2 1 - - - - - - - - - - - - - prior section: - - - - - 4 - - - - - - - - 7 6 5 - - - - - - - - - - - - - If there is no prior section (i.e. ndimslow is 0, or the CBF_UNCORRELATED_SECTIONS flag is set to indicate discontinuous sections), the values for trail_char_data[4..7] will all be NULL. When there is a prior section, trail_char_data[5..7] are pointers to the elements immediately below the elements pointed to by trail_char_data[1..3], but trail_char_data[4] is one element further along its row to be directly below the next element to be processed. The first element of the first row of the first section is a special case, with no averaging. This function should not be called for that case. In the first row of the first section (ndimmid == 0, and ndimslow == 0), after the first element (ndimfast > 0), only trail_char_data[0] is used current section: - - - - 0 * - - - - For subsequent rows of the first section (ndimmid > 0, and ndimslow == 0), for the first element (ndimfast == 0), two elements from the prior row are used: current section: * - - - - - - - - - 2 1 - - - - - - - - - - - - - - - - - - while for element after the first element, but before the last element of the row, a full set of 4 elements is used: current section: - - - - 0 * - - - - - - - - 3 2 1 - - - - - - - - - - - - - For the last element of a row (ndimfast == dimfast-1), two elements are used current section: - - - - - - - - 0 * - - - - - - - - - 2 - - - - - - - - - - For sections after the first section, provided the CBF_UNCORRELATED_SECTIONS flag is not set in compression, for each non-NULL entry in trail_char_data [0..3] an entry is made in trail_char_data [4..7], except for the first element of the first row of a section. In that case an entry is made in trail_char_data[4]. */ int cbf_update_jpa_pointers(unsigned char * trail_char_data[8], size_t *ndimfast, size_t *ndimmid, size_t *ndimslow, size_t dimfast, size_t dimmid, size_t dimslow, size_t elsize, unsigned int *average, unsigned int compression) { int i, j, k; int log2[4] = {1,2,0,3}; size_t numints; int mask, signbit; average[0] = 0; numints = (elsize + sizeof(unsigned int) -1)/sizeof(unsigned int); k = (elsize - (numints-1)*sizeof(unsigned int)); if (k == sizeof(unsigned int)) { mask = ~0; } else { mask = ~(-(1<<(k*CHAR_BIT))); } signbit = 1<<(CHAR_BIT*(elsize - (numints-1)*sizeof(unsigned int))-1); for (i = 1; i < numints; i++) average[i] = 0; (*ndimfast)++; if (*ndimfast == dimfast) { *ndimfast = 0; (*ndimmid)++; if (*ndimmid == dimmid) { *ndimmid = 0; (*ndimslow)++; } } for (i = 1 ; i < 8; i++ ) trail_char_data[i] = NULL; if (*ndimmid > 0) { /* Not in the first row */ trail_char_data[1] = trail_char_data[0]-elsize*(dimfast-2); /* down 1 right 2 */ trail_char_data[2] = trail_char_data[0]-elsize*(dimfast-1); /* down 1 right 1 */ if (*ndimfast > 0 ) { /* Not in the first column */ trail_char_data[3] = trail_char_data[0]-elsize*(dimfast); /* down 1 */ if (*ndimfast == dimfast-1) { /* Last column */ trail_char_data[1] = NULL; trail_char_data[3] = NULL; } } else { /* First column */ trail_char_data[0] = NULL; /* trail_char_data[3] = NULL; -- already done */ } if ( *ndimslow > 0 && (compression&CBF_UNCORRELATED_SECTIONS)== 0) { if (trail_char_data[0]) trail_char_data[4] = trail_char_data[0] - elsize*dimfast*dimmid + elsize; for (i = 1; i < 4; i++ ) { if (trail_char_data[i]) trail_char_data[i+4] = trail_char_data[i] - elsize*dimfast*dimmid; } } } else { /* First row of a section */ if ( *ndimfast == 0 ) { /* First element of first row of a section */ trail_char_data[4] = trail_char_data[0] - elsize*(dimfast*dimmid-1); trail_char_data[0] = NULL; } } j = 0; if (numints == 1) { for (i = 0; i < 8; i++) { if (trail_char_data[i]) { j++; if (elsize == sizeof (int)) average[0] += *((unsigned int *) (trail_char_data[i]) ); else if (elsize == sizeof (short)) average[0] += *((unsigned short *) (trail_char_data[i])); else average[0] += *(trail_char_data[i]); } } k = j>> 1; if (average[0] & signbit) average[0] |= ~mask; else average[0] &= mask; if (k > 0) average[0] = (unsigned int) (((int)average[0] + k) >> log2[k-1]); } else { for (i = 0; i < 8; i++) { if (trail_char_data[i]) { j++; cbf_failnez(cbf_mpint_add_acc(average, numints, (unsigned int *)(trail_char_data[i]), numints)) } } k = j >> 1; if (average[numints-1] & signbit) average[numints-1] |= ~mask; else average[numints-1] &= mask; if (k > 0) { cbf_failnez(cbf_mpint_add_acc(average,numints, (unsigned int *)&k , 1)) cbf_failnez(cbf_mpint_rightshift_acc(average,numints,log2[k-1])) } } return 0; } /* Compress an array with ccp4 compression as per J. P Abrahams. If dimensions are given, packing will be done with averaging to determine the base for offsets. */ int cbf_compress_packed (void *source, size_t elsize, int elsign, size_t nelem, unsigned int compression, cbf_file *file, size_t *compressedsize, int *storedbits, int realarray, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding) { unsigned int minelement, maxelement; unsigned int count, element[4], lastelement[4], unsign, sign, limit, bits; unsigned char *unsigned_char_data; unsigned char *trail_char_data[8]; unsigned long bitcount, chunkbits; unsigned int average[4]; size_t ndimfast, ndimmid, ndimslow; cbf_packed_data *data; void * memblock; int v2flag, avgflag, clipbits; int numints; int i, iint; char * border; char * rformat; /* Is the element size valid? */ if (elsize != sizeof (int) && elsize != 2* sizeof (int) && elsize != 4* sizeof (int) && elsize != sizeof (short) && elsize != sizeof (char)) return CBF_ARGUMENT; /* check for compatible real format */ if ( realarray ) { cbf_failnez (cbf_get_local_real_format(&rformat) ) if ( strncmp(rformat,"ieee",4) ) return CBF_ARGUMENT; } bits = elsize * CHAR_BIT; if (bits < 1 || bits > 64) return CBF_ARGUMENT; numints = (bits + CHAR_BIT*sizeof (int) -1)/(CHAR_BIT*sizeof (int)); /* Allocate memory */ cbf_failnez (cbf_alloc (&memblock, NULL, sizeof (cbf_packed_data), 1)) data = (cbf_packed_data *) memblock; data->start = 0; data->offsets = 0; /* Count the expected number of bits */ minelement = 0; maxelement = 0; /* Set flags */ v2flag = 0; if ((compression&CBF_COMPRESSION_MASK) == CBF_PACKED_V2) v2flag = 1; avgflag = 0; if (dimfast != 0 || dimmid != 0 || dimslow != 0) avgflag = 1; if (compression&CBF_FLAT_IMAGE) avgflag = 0; clipbits = 0; if (avgflag) clipbits = bits; if (dimslow == 0) dimslow = 1; if (dimmid == 0) dimmid = 1; if (dimfast == 0) dimfast = nelem/(dimmid*dimslow); if (dimfast * dimmid * dimslow != nelem) return CBF_ARGUMENT; /* Write the number of elements (64 bits) */ cbf_onfailnez (cbf_put_integer (file, nelem, 0, 64), cbf_free ((void **) data, NULL)) /* Write the minimum element (64 bits) */ cbf_onfailnez (cbf_put_integer (file, minelement, elsign, 64), cbf_free ((void **) data, NULL)) /* Write the maximum element (64 bits) */ cbf_onfailnez (cbf_put_integer (file, maxelement, elsign, 64), cbf_free ((void **) data, NULL)) /* Write the reserved word (64 bits) */ cbf_onfailnez (cbf_put_integer (file, 0, 0, 64), cbf_free ((void **) data, NULL)) bitcount = 4 * 64; /* Initialise the pointers */ unsigned_char_data = (unsigned char *) source; for (i = 0; i < 8; i++) trail_char_data[i] = NULL; /* Maximum limits */ sign = 1 << ((elsize-(numints-1)*sizeof(int))* CHAR_BIT - 1); if (elsize == sizeof (int) || elsize == numints*sizeof(int) ) limit = ~0; else if (numints == 1) { limit = ~-(1 << (elsize * CHAR_BIT)); } else { limit = ~-(1 << ((elsize-(numints-1)*sizeof(int)) * CHAR_BIT)); } if (storedbits) *storedbits = bits; /* Offset to make the value unsigned */ if (elsign) unsign = sign; else unsign = 0; /* Get the local byte order */ if (realarray) { cbf_get_local_real_byte_order(&border); } else { cbf_get_local_integer_byte_order(&border); } /* Start from 0 */ for (i = 0; i < numints-1; i++ ) lastelement[i] = 0; lastelement[numints-1] = unsign; ndimfast = ndimmid = ndimslow = 0; for (count = 0; count < nelem; count++) { /* Get the next element */ trail_char_data[0] = unsigned_char_data; if (numints > 1 ) { if (border[0] == 'b') { for (iint = numints; iint; iint--) { element[iint-1] = *((unsigned int *) unsigned_char_data); unsigned_char_data += sizeof (int); } } else { for (iint = 0; iint < numints; iint++) { element[iint] = *((unsigned int *) unsigned_char_data); unsigned_char_data += sizeof (int); } } } else { if (elsize == sizeof (int)) element[0] = *((unsigned int *) unsigned_char_data); else if (elsize == sizeof (short)) element[0] = *((unsigned short *) unsigned_char_data); else element[0] = *unsigned_char_data; unsigned_char_data += elsize; } /* Make the element unsigned */ element[numints-1] += unsign; element[numints-1] &= limit; if (element[numints-1] & sign) element[numints-1] |= (~limit); /* Add the offset to the buffer */ if (v2flag) cbf_add_offsetv2 (data, element, lastelement, numints); else cbf_add_offset (data, element, lastelement, numints); /* Is the buffer full? */ if (data->offsets == 128) { /* Write the next block as economically as possible */ cbf_onfailnez (cbf_pack_nextchunk (data, file, &chunkbits, v2flag, clipbits), cbf_free ((void **) data, NULL)) bitcount += chunkbits; } /* Update the previous element */ for (i = 0; i < numints; i++) lastelement[i] = element[i]; if (avgflag) { cbf_update_jpa_pointers(trail_char_data, &ndimfast, &ndimmid, &ndimslow, dimfast, dimmid, dimslow, elsize, average, compression); for (i = 0; i < numints; i++) lastelement[i] = average[i]; lastelement[numints-1] +=unsign; lastelement[numints-1] &=limit; if (lastelement[numints-1] & sign) lastelement[numints-1] |= (~limit); } } /* Flush the buffers */ while (data->offsets > 0) { cbf_onfailnez (cbf_pack_nextchunk (data, file, &chunkbits, v2flag, clipbits), cbf_free ((void **) data, NULL)) bitcount += chunkbits; } /* Return the number of characters written */ if (compressedsize) *compressedsize = (bitcount + 7) / 8; /* Free memory */ return cbf_free (&memblock, NULL); } /* Decompress an array */ int cbf_decompress_packed (void *destination, size_t elsize, int elsign, size_t nelem, size_t *nelem_read, size_t compressedsize, unsigned int compression, int data_bits, int data_sign, cbf_file *file, int realarray, const char *byteorder, size_t dimover, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding) { unsigned int next, pixel=0, pixelcount; unsigned int bits, iint, element[4], sign, unsign, limit, count; unsigned char *unsigned_char_data; unsigned char *trail_char_data[8]; unsigned int offset [4], last_element [4]; size_t numints; size_t ndimfast, ndimmid, ndimslow; int errorcode; int v2flag, avgflag, clipbits; int i; char * border; char * rformat; /* Is the element size valid? */ if (elsize != sizeof (int) && elsize != sizeof (short) && elsize != sizeof (char) && elsize != 2*sizeof(unsigned int) && elsize != 4*sizeof(unsigned int)) return CBF_ARGUMENT; /* check for compatible real format */ if ( realarray ) { cbf_failnez (cbf_get_local_real_format(&rformat) ) if ( strncmp(rformat,"ieee",4) ) return CBF_ARGUMENT; } bits = elsize * CHAR_BIT; if (bits < 1 || bits > 64) return CBF_ARGUMENT; numints = (bits + CHAR_BIT*sizeof (int) -1)/(CHAR_BIT*sizeof (int)); /* Initialise the pointers */ unsigned_char_data = (unsigned char *) destination; for (i = 0; i < 8; i++) trail_char_data[i] = NULL; /* Maximum limits */ sign = 1 << ((elsize-(numints-1)*sizeof(int))* CHAR_BIT - 1); if (elsize == numints*sizeof(int) ) limit = ~0; else if (numints == 1) { limit = ~-(1 << (elsize * CHAR_BIT)); } else { limit = ~-(1 << ((elsize-(numints-1)*sizeof(int)) * CHAR_BIT)); } /* Offset to make the value unsigned */ if (elsign) unsign = sign; else unsign = 0; /* Get the local byte order */ if (realarray) { cbf_get_local_real_byte_order(&border); } else { cbf_get_local_integer_byte_order(&border); } /* Initialise the first element */ for (count = 0; count < numints-1; count++) last_element [count] = 0; last_element [numints-1] = unsign; /* Discard the reserved entry (64 bits) */ cbf_failnez (cbf_get_integer (file, NULL, 0, 64)) /* Pick up the flags */ v2flag = 0; if ((compression&CBF_COMPRESSION_MASK) == CBF_PACKED_V2) v2flag = 1; avgflag = 1; if (dimfast == 0 && dimmid == 0 && dimslow == 0) avgflag = 0; if (compression&CBF_FLAT_IMAGE) avgflag = 0; clipbits = 0; if (avgflag) clipbits = bits; if (dimslow == 0) dimslow = 1; if (dimmid == 0) dimmid = 1; if (dimfast == 0) dimfast = nelem/(dimmid*dimslow); if (dimfast * dimmid * dimslow != nelem) return CBF_ARGUMENT; /* Read the elements */ count = 0; ndimfast = ndimmid = ndimslow = 0; while (count < nelem) { /* Get the next 6 bits of data */ errorcode = cbf_get_integer (file, (int *) &next, 0, 6+v2flag); if (errorcode) { if (nelem_read) *nelem_read = count + pixel; return errorcode; } /* Decode bits 0-5 (v2flag == 0) or 0-6 (v2flag == 1) */ pixelcount = 1 << (next & 7); if (v2flag) bits = cbf_packedv2_bits [(next >> 3) & 15]; else bits = cbf_packed_bits [(next >> 3) & 7]; if (avgflag && bits == 65) bits = clipbits; /* Read the offsets */ if (pixelcount + count > nelem) pixelcount = nelem - count; for (pixel = 0; pixel < pixelcount; pixel++) { for (i = 0; i < numints; i++) element[i] = last_element[i]; /* Read an offset */ for (i = 0; i < numints; i++) offset[i] = 0; if (bits) { errorcode = cbf_get_bits (file, (int *) offset, bits); if (errorcode) { if (nelem_read) *nelem_read = count + pixel; return errorcode; } } if (numints > 1) { iint = (bits+sizeof(unsigned int)*CHAR_BIT-1)/(sizeof(unsigned int)*CHAR_BIT); cbf_failnez(cbf_mpint_add_acc(element,numints,offset,iint)) } else { element[0] += (int)(offset[0]); element[0] &= limit; } /* Make the element signed? */ element[numints-1] -= unsign; /* Save the location of to which this element will be stored */ trail_char_data[0] = unsigned_char_data; /* Save the element */ if (numints > 1) { if (border[0] == 'b') { for (iint = numints; iint; iint--) { *((unsigned int *) unsigned_char_data) = element[iint-1]; unsigned_char_data += sizeof (int); } } else { for (iint = 0; iint < numints; iint++) { *((unsigned int *) unsigned_char_data) = element[iint]; unsigned_char_data += sizeof (int); } } } else { if (elsize == sizeof (int)) *((unsigned int *) unsigned_char_data) = element[0]; else if (elsize == sizeof (short)) *((unsigned short *) unsigned_char_data) = element[0]; else *unsigned_char_data = element[0]; unsigned_char_data += elsize; } if (avgflag) { cbf_failnez(cbf_update_jpa_pointers(trail_char_data, &ndimfast, &ndimmid, &ndimslow, dimfast, dimmid, dimslow, elsize, last_element, compression)) last_element[numints-1] += unsign; last_element[numints-1] &= limit; } else { for (i = 0; i < numints-1; i++ )last_element[i] = element[i]; last_element[numints-1] = element[numints-1]+unsign; } } count += pixelcount; } /* Number read */ if (nelem_read) *nelem_read = count; /* Success */ return 0; } #ifdef __cplusplus } #endif ./CBFlib-0.9.2.2/src/fcb_skip_whitespace.f900000644000076500007650000000567411603702106016715 0ustar yayayaya INTEGER FUNCTION FCB_SKIP_WHITESPACE(TAPIN,LAST_CHAR, & FCB_BYTES_IN_REC,BYTE_IN_FILE,REC_IN_FILE,BUFFER,& LINE,N,LINELEN,ICUR,FRESH_LINE) !----------------------------------------------------------------------- ! Skips forward on the current LINE of size N with data in ! LINE(1:LINELEN) from the current position ICUR moving over ! whitespace and comments, reading new lines into LINE if ! needed. The flag FRESH_LINE indicates that a fresh line ! should be read on entry. !----------------------------------------------------------------------- IMPLICIT NONE INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC,N INTEGER, INTENT(INOUT):: BYTE_IN_FILE,REC_IN_FILE,LINELEN,ICUR, & FRESH_LINE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC),LINE(N), & LAST_CHAR ! Local variables INTEGER IC,COMMENT_LEVEL ! External functions called INTEGER FCB_READ_LINE,FCB_NBLEN_ARRAY !----------------------------------------------------------------------- FCB_SKIP_WHITESPACE = 0 IF (FRESH_LINE.NE.0) THEN ICUR = LINELEN+1 RETURN END IF IC = ICUR COMMENT_LEVEL = 0 DO IF ((IC.LE.LINELEN).AND.(LINE(IC).NE.IACHAR(' ')).AND. & (LINE(IC).NE.Z'09').AND.(LINE(IC).NE.IACHAR('(')) )EXIT IF (IC.GT.LINELEN) THEN FCB_SKIP_WHITESPACE = FCB_READ_LINE (TAPIN,LAST_CHAR, & FCB_BYTES_IN_REC,BYTE_IN_FILE,REC_IN_FILE,BUFFER,& LINE,N,LINELEN) IF (FCB_SKIP_WHITESPACE.NE.0) RETURN IC = 1 IF ((LINELEN.EQ.0) & .OR.(FCB_NBLEN_ARRAY(LINE(1:LINELEN),LINELEN).EQ.0) & .OR.(FCB_NBLEN_ARRAY(LINE(1:1),1).NE.0)) THEN FRESH_LINE = 1 ICUR = LINELEN+1 RETURN END IF ELSE IF (LINE(IC) .EQ. IACHAR('(')) THEN IC = IC+1 COMMENT_LEVEL = COMMENT_LEVEL+1 DO IF (COMMENT_LEVEL.EQ.0)EXIT IF (IC.GT.LINELEN) THEN FCB_SKIP_WHITESPACE=FCB_READ_LINE(TAPIN,LAST_CHAR, & FCB_BYTES_IN_REC,BYTE_IN_FILE,REC_IN_FILE, & BUFFER,LINE,N,LINELEN) IF (FCB_SKIP_WHITESPACE.NE.0) RETURN IC = 1 IF ((LINELEN.EQ.0).OR. & (FCB_NBLEN_ARRAY(LINE(1:LINELEN),LINELEN).EQ.0) & .OR. FCB_NBLEN_ARRAY(LINE(1:1),1).NE.0) THEN FRESH_LINE = 1 ICUR = LINELEN+1 RETURN END IF ELSE SELECT CASE (LINE(IC)) CASE (Z'5C') ! backslash IC = IC+1 ! force skip of next character CASE (Z'28') ! open paren COMMENT_LEVEL = COMMENT_LEVEL+1; CASE (Z'29') ! close paren COMMENT_LEVEL = COMMENT_LEVEL-1; END SELECT IC = IC+1; END IF END DO ELSE IC = IC+1; END IF END IF END DO FRESH_LINE = 0 FCB_SKIP_WHITESPACE = 0 ICUR = IC RETURN END FUNCTION FCB_SKIP_WHITESPACE ./CBFlib-0.9.2.2/src/drel_prep.py0000777000076500007650000000000011603745057021355 2../dREL-ply-0.5/drel_prep.pyustar yayayaya./CBFlib-0.9.2.2/src/cbf_canonical.c0000644000076500007650000020375711603702106015310 0ustar yayayaya/********************************************************************** * cbf_canonical -- canonical-code compression * * * * Version 0.8.0 20 July 2008 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifdef __cplusplus extern "C" { #endif #include #include #include #include #include "cbf.h" #include "cbf_alloc.h" #include "cbf_canonical.h" #include "cbf_compress.h" #include "cbf_file.h" #define CBF_TABLEENTRYBITS 8 /* Bits in a table entry */ #define CBF_MAXBITS 15 /* Maximum bits in a simple code */ #define CBF_MAXMAXBITS 65 /* Bits in an coded integer */ #define CBF_MAXCODEBITS 64 /* Bits in a code */ #define CBF_SHIFT63 (sizeof (int) * CHAR_BIT > 64 ? 63 : 0) /* Create compression data */ int cbf_make_compressdata (cbf_compress_data **data, cbf_file *file) { /* Does the file exist? */ if (!file) return CBF_ARGUMENT; if (!file->stream) return CBF_ARGUMENT; /* Allocate memory */ cbf_failnez (cbf_alloc ((void **) data, NULL, sizeof (cbf_compress_data), 1)) /* Initialise */ (*data)->file = file; (*data)->bits = 0; (*data)->maxbits = 0; (*data)->endcode = 0; (*data)->nodes = 0; (*data)->nextnode = 0; (*data)->node = NULL; /* Success */ return 0; } /* Free data */ void cbf_free_compressdata (cbf_compress_data *data) { void * memblock; void * vnode; memblock = (void *)data; /* Free storage */ if (data) { vnode = (void *)data->node; cbf_free ((void **) &vnode, &data->nodes); data->node = NULL; cbf_free ((void **) &memblock, NULL); } } /* Initialise compression data arrays */ int cbf_initialise_compressdata (cbf_compress_data *data, unsigned int bits, unsigned int maxbits) { size_t count; cbf_compress_node *node; void *vnode; /* Coded bits */ if (bits > CBF_MAXBITS) return CBF_FORMAT; /* Codes must fit int + 1 bit */ if (maxbits > CBF_MAXMAXBITS) return CBF_FORMAT; if (maxbits < sizeof (int) * CHAR_BIT + 1) { maxbits = sizeof (int) * CHAR_BIT + 1; if (maxbits > CBF_MAXMAXBITS) maxbits = CBF_MAXMAXBITS; } if (maxbits < bits) return CBF_FORMAT; /* Update the values */ data->bits = bits; data->maxbits = maxbits; /* end-of-code code */ data->endcode = 1 << bits; /* Allocate memory for the nodes */ count = (data->endcode + maxbits) * 2 + 1; vnode = (void *)data->node; cbf_failnez (cbf_realloc ((void **) &vnode, &data->nodes, sizeof (cbf_compress_node), count)) data->node = (cbf_compress_node *)vnode; /* Initialise the nodes */ node = data->node; for (count = 0; count < data->nodes; count++, node++) { node->bitcount = 0; node->count = 0; node->next = node->child [0] = node->child [1] = NULL; if (count < data->endcode) node->code = count - ((count << 1) & data->endcode); else node->code = count; } data->nextnode = 0; /* Success */ return 0; } /* Write a compression table */ int cbf_put_table (cbf_compress_data *data, unsigned int *bitcount) { unsigned int count, codes, endcode, maxbits; /* Coded bits */ cbf_failnez (cbf_put_integer (data->file, data->bits, 0, CBF_TABLEENTRYBITS)) *bitcount = CBF_TABLEENTRYBITS; /* How many symbols do we actually use? */ endcode = 1 << data->bits; for (codes = endcode + data->maxbits; data->node [codes].bitcount == 0; codes--); codes++; /* Maximum bits used */ if (codes > endcode + data->bits) maxbits = codes - endcode - 1; else maxbits = data->bits; cbf_failnez (cbf_put_integer (data->file, maxbits, 0, CBF_TABLEENTRYBITS)) *bitcount += CBF_TABLEENTRYBITS; /* Minimum-redundancy code lengths */ for (count = 0; count < codes; count++) { if (count == endcode + 1) count = endcode + data->bits + 1; cbf_failnez (cbf_put_integer (data->file, data->node [count].bitcount, 0, CBF_TABLEENTRYBITS)) *bitcount += CBF_TABLEENTRYBITS; } /* Success */ return 0; } /* Read a compression table */ int cbf_get_table (cbf_compress_data *data) { unsigned int bits, maxbits, endcode, count, tbits; /* Coded bits */ cbf_failnez (cbf_get_integer (data->file, (int *) &bits, 0, CBF_TABLEENTRYBITS)) /* Maximum number of bits */ cbf_failnez (cbf_get_integer (data->file, (int *) &maxbits, 0, CBF_TABLEENTRYBITS)) /* Initialise the data */ cbf_failnez (cbf_initialise_compressdata (data, bits, maxbits)) /* Reserve nodes */ endcode = 1 << data->bits; data->nextnode = endcode + data->maxbits + 1; /* Read the table */ tbits = bits; for (count = 0; count <= endcode+maxbits; count++) { if (tbits == maxbits && count ==endcode+1) break; cbf_failnez (cbf_get_integer (data->file, (int *) &bits, 0, CBF_TABLEENTRYBITS)) if (count == endcode + 1) { count = endcode + data->bits + 1; } data->node [count].bitcount = bits; } /* Success */ return 0; } /* End the bitstream */ int cbf_put_stopcode (cbf_compress_data *data, unsigned int *bitcount) { unsigned int endcode; endcode = 1 << data->bits; cbf_failnez (cbf_put_bits (data->file, (int *) data->node [endcode].bitcode, data->node [endcode].bitcount)) *bitcount = data->node [endcode].bitcount; /* Success */ return 0; } /* Insert a node into a tree */ cbf_compress_node *cbf_insert_node (cbf_compress_node *tree, cbf_compress_node *node) { if (tree) { if (node->count > tree->count) tree->child [1] = cbf_insert_node (tree->child [1], node); else tree->child [0] = cbf_insert_node (tree->child [0], node); return tree; } return node; } /* Append a node to a list */ cbf_compress_node *cbf_append_node (cbf_compress_node *list, cbf_compress_node *node) { cbf_compress_node *next; if (list) { next = list; while (next->next) next = next->next; next->next = node; return list; } return node; } /* Convert an ordered tree into an ordered list */ cbf_compress_node *cbf_order_node (cbf_compress_node *tree) { if (tree) return cbf_append_node (cbf_append_node (cbf_order_node (tree->child [0]), tree), cbf_order_node (tree->child [1])); return NULL; } /* Create an ordered list */ cbf_compress_node *cbf_create_list (cbf_compress_data *data) { unsigned int count, endcode, codes; cbf_compress_node *tree, *list, *node; /* Sort the nodes */ endcode = 1 << data->bits; codes = endcode + data->maxbits + 1; node = data->node; tree = NULL; for (count = 0; count < codes; count++) if (node [count].count) tree = cbf_insert_node (tree, node + count); list = cbf_order_node (tree); /* Dismantle the tree */ for (count = 0; count < codes; count++) node [count].child [0] = node [count].child [1] = NULL; return list; } /* Combine the two nodes with minimum count */ cbf_compress_node *cbf_reduce_list (cbf_compress_data *data, cbf_compress_node *list) { cbf_compress_node *node, *next, *cnext; /* Construct a node */ node = data->node + data->nextnode; data->nextnode++; /* Attach the top nodes */ node->child [0] = list; node->child [1] = list->next; node->count = list->count + list->next->count; /* Put it at the top */ next = node->next = list->next->next; /* Order correct? */ if (next == NULL) return node; if (node->count <= next->count) return node; /* Otherwise move the node down to the correct position */ cnext = next; while (cnext->next) if (node->count < cnext->count || node->count > cnext->next->count) cnext = cnext->next; else break; node->next = cnext->next; cnext->next = node; return next; } /* Generate the minimum-redundancy code lengths */ int cbf_generate_codelengths (cbf_compress_node *tree, int bitcount) { if (tree) { tree->bitcount = bitcount; cbf_generate_codelengths (tree->child [0], bitcount + 1); cbf_generate_codelengths (tree->child [1], bitcount + 1); } /* Success */ return 0; } /* Reverse the order of the bits in the bit-codes */ int cbf_reverse_bitcodes (cbf_compress_data *data) { unsigned int node, endcode, codes, count, index [2][2], bit [2]; endcode = 1 << data->bits; codes = endcode + data->maxbits + 1; /* Reverse the order of the bits in the code */ for (node = 0; node < codes; node++) if (data->node [node].bitcount > 0) for (count = 0; count < data->node [node].bitcount - count - 1; count++) { bit [0] = count; bit [1] = data->node [node].bitcount - count - 1; index [0][0] = bit [0] % (sizeof (unsigned int) * CHAR_BIT); index [0][1] = bit [0] / (sizeof (unsigned int) * CHAR_BIT); index [1][0] = bit [1] % (sizeof (unsigned int) * CHAR_BIT); index [1][1] = bit [1] / (sizeof (unsigned int) * CHAR_BIT); bit [0] = (data->node [node].bitcode [index [0][1]] >> (index [0][0])) & 1; bit [1] = (data->node [node].bitcode [index [1][1]] >> (index [1][0])) & 1; data->node [node].bitcode [index [0][1]] ^= (bit [0] ^ bit [1]) << index [0][0]; data->node [node].bitcode [index [1][1]] ^= (bit [0] ^ bit [1]) << index [1][0]; } /* Success */ return 0; } /* Generate the canonical bit-codes */ int cbf_generate_canonicalcodes (cbf_compress_data *data) { unsigned int count [2], base [CBF_MAXCODEBITS], node, codes, endcode, bits; endcode = 1 << data->bits; codes = endcode + data->maxbits + 1; /* Count the number of symbols with the same number of bits */ memset (base, 0, sizeof (base)); for (node = 0; node < codes; node++) { bits = data->node [node].bitcount; if (bits > CBF_MAXCODEBITS) return CBF_ARGUMENT; if (bits > 0) { memset (data->node [node].bitcode, 0, 4 * sizeof (unsigned int)); data->node [node].bitcode [0] = base [bits - 1]; base [bits - 1]++; } } /* Generate the initial code values */ count [0] = 0; for (bits = CBF_MAXCODEBITS - 1; bits > 0; bits--) { count [1] = base [bits - 1]; base [bits - 1] = (base [bits] + count [0]) / 2; count [0] = count [1]; } /* Add the initial code to the count */ for (node = 0; node < codes; node++) { bits = data->node [node].bitcount; if (bits > 0) data->node [node].bitcode [0] += base [bits - 1]; } /* Reverse the order of the bits in the code */ return cbf_reverse_bitcodes (data); } /* Compare the bitcodes of two nodes */ int cbf_compare_bitcodes (const void *void1, const void *void2) { const cbf_compress_node *node1, *node2; const unsigned int *code1, *code2; unsigned int bit, bits; node1 = (const cbf_compress_node *) void1; node2 = (const cbf_compress_node *) void2; /* Get the codes */ code1 = node1->bitcode; code2 = node2->bitcode; bits = node1->bitcount; if (bits > node2->bitcount) bits = node2->bitcount; /* Is either node not used? */ if (bits == 0) { if (node1->bitcount == node2->bitcount) return 0; return 1 - ((node1->bitcount != 0) << 1); } /* Compare the codes bit-by-bit */ for (bit = 0; bits > 0; bit++, bits--) { if (bit == sizeof (int) * CHAR_BIT) { bit = 0; code1++; code2++; } if (((*code1 ^ *code2) >> bit) & 1) return ((*code1 >> bit) & 1) - ((*code2 >> bit) & 1); } /* Same code */ return 0; } /* Construct a tree from an ordered set of nodes */ int cbf_construct_tree (cbf_compress_data *data, cbf_compress_node **node, int bits, cbf_compress_node **root) { cbf_compress_node *nextnode; if (bits > CBF_MAXMAXBITS) { return CBF_ARGUMENT; } if (node == NULL) { nextnode = data->node; node = &nextnode; } /* Create the node */ *root = data->node + data->nextnode; data->nextnode++; /* Make the 0 branch then the 1 branch */ if ((*node)->bitcount == bits) { (*root)->child [0] = *node; (*node)++; } else { cbf_failnez (cbf_construct_tree (data, node, bits + 1, &(*root)->child [0])) } if ((*node)->bitcount == bits) { (*root)->child [1] = *node; (*node)++; } else { cbf_failnez (cbf_construct_tree (data, node, bits + 1, &(*root)->child [1])) } /* Success */ return 0; } /* Sort the nodes and set up the decoding arrays */ int cbf_setup_decode (cbf_compress_data *data, cbf_compress_node **start) { /* Generate the codes */ cbf_failnez (cbf_generate_canonicalcodes (data)) /* Sort the nodes in order of the codes */ qsort (data->node, data->nextnode, sizeof (cbf_compress_node), cbf_compare_bitcodes); /* Construct the tree */ return cbf_construct_tree (data, NULL, 1, start); } /* Calculate the expected bit count */ unsigned long cbf_count_bits (cbf_compress_data *data) { unsigned int endcode, codes, code; unsigned long bitcount; cbf_compress_node *node; endcode = 1 << data->bits; node = data->node; /* Basic entries */ bitcount = 4 * 64; /* How many symbols do we actually use? */ for (codes = endcode + data->maxbits; node [codes].bitcount == 0; codes--); codes++; /* Compression table */ if (codes > endcode + data->bits) { bitcount += 2 * CBF_TABLEENTRYBITS + (codes - data->bits) * CBF_TABLEENTRYBITS; } else { bitcount += 2 * CBF_TABLEENTRYBITS + (endcode + 1) * CBF_TABLEENTRYBITS; } /* Compressed data */ for (code = 0; code < endcode; code++, node++) bitcount += node->count * node->bitcount; for (; code < codes; code++, node++) bitcount += node->count * (node->bitcount + code - endcode); return bitcount; } /* Read a code */ int cbf_get_code (cbf_compress_data *data, cbf_compress_node *root, unsigned int *code, unsigned int *bitcount) { int bits0, bits1; /* Decode the bitstream */ bits0 = data->file->bits [0]; bits1 = data->file->bits [1]; while (*(root->child)) { if (bits0 == 0) { if (data->file->temporary) { if (data->file->characters_used) { bits1 = *((data->file->characters)++); bits1 &= 0xFF; data->file->characters_used--; data->file->characters_size--; } else { bits1 = EOF; } } else { bits1 = getc (data->file->stream); } if (bits1 == EOF) { data->file->bits [0] = data->file->bits [1] = 0; return CBF_FILEREAD; } bits0 = 8; } root = root->child [bits1 & 1]; bits1 >>= 1; bits0--; } data->file->bits [0] = bits0; data->file->bits [1] = bits1; *code = root->code; /* Simple coding? */ if ((int) *code < (int) data->endcode) { *bitcount = data->bits; return 0; } /* Coded bit count? */ *code -= data->endcode; if (*code) { if (*code > data->maxbits) return CBF_FORMAT; else { *bitcount = *code; return cbf_get_bits (data->file, (int *) code, *code); } } /* End code */ return CBF_ENDOFDATA; } /* Read a multi-precision integer code */ int cbf_get_mpint_code (cbf_compress_data *data, cbf_compress_node *root, unsigned int code[4], unsigned int *bitcount, int numints) { int bits0, bits1; /* Decode the bitstream */ bits0 = data->file->bits [0]; bits1 = data->file->bits [1]; code[0] = code[1] = code[2] = code[3] = 0; while (*(root->child)) { if (bits0 == 0) { if (data->file->temporary) { if (data->file->characters_used) { bits1 = *((data->file->characters)++); bits1 &= 0xFF; data->file->characters_used--; data->file->characters_size--; } else { bits1 = EOF; } } else { bits1 = getc (data->file->stream); } if (bits1 == EOF) { data->file->bits [0] = data->file->bits [1] = 0; return CBF_FILEREAD; } bits0 = 8; } root = root->child [bits1 & 1]; bits1 >>= 1; bits0--; } data->file->bits [0] = bits0; data->file->bits [1] = bits1; code[0] = root->code; /* Simple coding? */ if ((int) code[0] < (int) data->endcode) { *bitcount = data->bits; return 0; } /* Coded bit count? */ code[0] -= data->endcode; if (code[0]) { if (code[0] > data->maxbits) return CBF_FORMAT; else { *bitcount = code[0]; return cbf_get_bits (data->file, (int *) code, *bitcount); } } /* End code */ return CBF_ENDOFDATA; } /* Write a coded integer */ int cbf_put_code (cbf_compress_data *data, int code, unsigned int overflow, unsigned int *bitcount) { unsigned int bits, m, endcode; int overcode [2], *usecode; cbf_compress_node *node; endcode = 1 << data->bits; /* Does the number fit in an integer? */ if (!overflow) { /* Code direct? */ m = (code ^ (code << 1)); if ((m & -((int) endcode)) == 0) { /* Code the number */ node = data->node + (code & (endcode - 1)); bits = node->bitcount; cbf_put_bits (data->file, (int *) node->bitcode, bits); *bitcount = bits; return 0; } /* Count the number of bits */ bits = sizeof (int) * CHAR_BIT; while (((m >> (bits - 1)) & 1) == 0) bits--; usecode = &code; } else { /* Overflow */ overcode [0] = code; overcode [1] = -(code < 0); usecode = overcode; bits = sizeof (int) * CHAR_BIT; } /* Code the number of bits */ node = data->node + endcode + bits; cbf_put_bits (data->file, (int *) node->bitcode, node->bitcount); /* Write the number */ cbf_put_bits (data->file, usecode, bits); *bitcount = bits + node->bitcount; /* Success */ return 0; } /* Write a coded multi-precision integer */ int cbf_put_mpint_code (cbf_compress_data *data, int code[5], unsigned int overflow, unsigned int *bitcount, int numints) { unsigned int bits, kbits, m, endcode; int *usecode; int j; cbf_compress_node *node; endcode = 1 << data->bits; if (overflow) { usecode = code; bits = numints * sizeof( int ) * CHAR_BIT; } else { /* Code direct? */ if (numints == 1) { size_t xbc; m = (code[0] ^ (code[0] << 1)); cbf_mpint_get_acc_bitlength((unsigned int *)code,numints,&xbc); if ((m & -((int) endcode)) == 0) { /* Code the number */ node = data->node + (code[0] & (endcode - 1)); bits = node->bitcount; cbf_put_bits (data->file, (int *) node->bitcode, bits); *bitcount = bits; return 0; } /* Count the number of bits */ bits = sizeof (int) * CHAR_BIT; while (((m >> (bits - 1)) & 1) == 0) bits--; } else { size_t xbc; cbf_mpint_get_acc_bitlength((unsigned int *)code,numints,&xbc); if (xbc < data->bits) { node = data->node + (code[0] & (endcode - 1)); bits = node->bitcount; cbf_put_bits (data->file, (int *) node->bitcode, bits); *bitcount = bits; return 0; } bits = xbc; } usecode = code; } /* Code the number of bits */ node = data->node + endcode + bits; cbf_put_bits (data->file, (int *) node->bitcode, node->bitcount); /* Write the number */ for (j = 0; j < bits; j += sizeof(int)*CHAR_BIT) { kbits = sizeof(int)*CHAR_BIT; if (j+kbits > bits) kbits = bits - j; cbf_put_bits (data->file,usecode, kbits); usecode++; } *bitcount = bits + node->bitcount; /* Success */ return 0; } /* Count the values */ int cbf_count_values (cbf_compress_data *data, void *source, size_t elsize, int elsign, size_t nelem, int *minelem, int *maxelem, char *border) { int code[5] = {0,0,0,0,0}; unsigned int bits, count, element[4], lastelement[4], minelement[4], maxelement[4], iint, unsign, sign, bitcount, m, endcode, limit; unsigned char *unsigned_char_data; size_t numints; cbf_compress_node *node; /* Is the element size valid? */ if (elsize != sizeof (int) && elsize != sizeof (short) && elsize != sizeof (char) && elsize != 2*sizeof(unsigned int) && elsize != 4*sizeof(unsigned int)) return CBF_ARGUMENT; bits = elsize * CHAR_BIT; if (bits < 1 || bits > 64) return CBF_ARGUMENT; numints = (bits + CHAR_BIT*sizeof (int) -1)/(CHAR_BIT*sizeof (int)); /* Initialise the pointers */ unsigned_char_data = (unsigned char *) source; node = data->node; /* Maximum limit (unsigned) is 64 bits */ sign = 1 << ((elsize-(numints-1)*sizeof(int))* CHAR_BIT - 1); if (elsize == numints*sizeof(int) ) limit = ~0; else if (numints == 1) { limit = ~-(1 << (elsize * CHAR_BIT)); } else { limit = ~-(1 << ((elsize-(numints-1)*sizeof(int)) * CHAR_BIT)); } /* Offset to make the value unsigned */ if (elsign) unsign = sign; else unsign = 0; /* Initialise the minimum and maximum elements */ minelement[0] = minelement[1] = minelement[2] = minelement[3] = ~0; maxelement[0] = maxelement[1] = maxelement[2] = maxelement[3] = 0; /* Start from 0 */ for (iint = 0; iint < numints; iint++) lastelement [iint] = 0; lastelement [numints-1] = unsign; endcode = 1 << data->bits; for (count = 0; count < nelem; count++) { /* Get the next element */ if (numints > 1 ) { if (border[0] == 'b') { for (iint = numints; iint; iint--) { element[iint-1] = ((unsigned int *) unsigned_char_data)[numints-iint]; } } else { for (iint = 0; iint < numints; iint++) { element[iint] = ((unsigned int *) unsigned_char_data)[iint]; } } } else { if (elsize == sizeof (int)) element[0] = *((unsigned int *) unsigned_char_data); else if (elsize == sizeof (short)) element[0] = *((unsigned short *) unsigned_char_data); else element[0] = *unsigned_char_data; } unsigned_char_data += elsize; /* Make the element unsigned */ element[numints-1] += unsign; /* Limit the value to 64 bits */ if (element[numints-1] > limit) { if (elsign && (int) (element[numints-1] - unsign) < 0) { for (iint = 0; iint < numints; iint++) element[iint] = 0; } else { element[numints-1] = limit; for (iint = 0; iint < numints-1 ; iint++) element[iint] = ~0; } } /* Update the minimum and maximum values */ if (numints == 1) { if (element[0] < minelement[0]) minelement[0] = element[0]; if (element[0] > maxelement[0]) maxelement[0] = element[0]; /* Calculate the offset to save */ code[0] = element[0] - lastelement[0]; code[1] = 0; } else { for (iint = 0; iint < numints; iint++) ((unsigned int *)code)[iint] = minelement[iint]; code[numints] = 0; cbf_mpint_negate_acc((unsigned int *)code,numints+1); cbf_mpint_add_acc((unsigned int *)code,numints+1,element,numints); if (code[numints] < 0) for (iint = 0; iint < numints; iint++) ((unsigned int *)minelement)[iint] = element[iint]; for (iint = 0; iint < numints; iint++) ((unsigned int *)code)[iint] = maxelement[iint]; code[numints] = 0; cbf_mpint_negate_acc((unsigned int *)code,numints+1); cbf_mpint_add_acc((unsigned int *)code,numints+1,element,numints); if (code[numints] > 0) for (iint = 0; iint < numints; iint++) ((unsigned int *)maxelement)[iint] = element[iint]; for (iint = 0; iint < numints; iint++) ((unsigned int *)code)[iint] = lastelement[iint]; code[numints] = 0; cbf_mpint_negate_acc((unsigned int *)code,numints+1); cbf_mpint_add_acc((unsigned int *)code,numints+1,element,numints); } /* code is the signed difference element - lastelement if code is negative and element is > lastelement as unsigned values, or code is non-negative and element is <- lastelement as unsigned values, we have an overflow */ if ((numints==1 && ((element[0] < lastelement[0])^(code[0] < 0)))|| (numints > 1 && ((code[numints]<0) ^ (code[numints-1]<0)))) { bitcount = numints * sizeof( int ) * CHAR_BIT; node [endcode + bitcount].count++; } else { /* Encode the offset */ if (numints == 1) { m = (code[0] ^ (code[0] << 1)); if ((m & -((int) endcode)) == 0) { /* Simple code */ node [code[0] & (endcode - 1)].count++; } else { /* Count the number of bits */ bitcount = sizeof (int) * CHAR_BIT; while (((m >> (bitcount - 1)) & 1) == 0) bitcount--; node [endcode + bitcount].count++; } } else { size_t xbc; cbf_mpint_get_acc_bitlength((unsigned int *)code,numints,&xbc); if ( xbc >= sizeof (int) * CHAR_BIT ) { node [endcode + xbc].count++; } else { m = (code[0] ^ (code[0] << 1)); if ((m & -((int) endcode)) == 0) { /* Simple code */ node [code[0] & (endcode - 1)].count++; } else { node [endcode + xbc].count++; } } } } /* Update the previous element */ for (iint=0; iint < numints; iint++) lastelement[iint] = element[iint]; } /* Make the minimum and maxium signed? */ minelement[numints-1] -= unsign; maxelement[numints-1] -= unsign; if (numints == 1) { int minsign, maxsign; minsign = -(((int)minelement[0])<0 && elsign); maxsign = -(((int)maxelement[0])<0 && elsign); minelement[1] = minelement[2] = minelement[3] = minsign; maxelement[1] = maxelement[2] = maxelement[3] = maxsign; } /* Save the minimum and maximum */ if (nelem) for (iint=0; iint < 4; iint++) { minelem[iint] = (int) minelement[iint]; maxelem[iint] = (int) maxelement[iint]; } /* End code */ node [endcode].count = 1; data->nextnode = endcode + data->maxbits + 1; /* Success */ return 0; } /* Compress an array */ int cbf_compress_canonical (void *source, size_t elsize, int elsign, size_t nelem, unsigned int compression, cbf_file *file, size_t *binsize, int *storedbits, int realarray, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding) { int code[5], minelement[4], maxelement[4]; unsigned int count, i, iint, element[4], lastelement[4], bits, unsign, sign, limit, endcode; unsigned long bitcount, expected_bitcount; unsigned char *unsigned_char_data; cbf_compress_node *node, *start; cbf_compress_data *data; int numints; char * border; char * rformat; /* Is the element size valid? */ if (elsize != sizeof (int) && elsize != sizeof (short) && elsize != sizeof (char) && elsize != 2*sizeof (int) && elsize != 4*sizeof (int) ) return CBF_ARGUMENT; /* check for compatible real format */ if ( realarray ) { cbf_failnez (cbf_get_local_real_format(&rformat) ) if ( strncmp(rformat,"ieee",4) ) return CBF_ARGUMENT; } /* Get the local byte order */ if (realarray) { cbf_get_local_real_byte_order(&border); } else { cbf_get_local_integer_byte_order(&border); } bits = elsize * CHAR_BIT; if (bits < 1 || bits > 64) return CBF_ARGUMENT; numints = (bits + CHAR_BIT*sizeof (int) -1)/(CHAR_BIT*sizeof (int)); /* Create and initialise the compression data */ cbf_failnez (cbf_make_compressdata (&data, file)) cbf_onfailnez (cbf_initialise_compressdata (data, 8, bits+1), cbf_free_compressdata (data)) /* Count the symbols */ cbf_onfailnez (cbf_count_values (data, source, elsize, elsign, nelem, minelement, maxelement, border), cbf_free_compressdata (data)) /* Generate the code lengths */ start = cbf_create_list (data); while (start->next) start = cbf_reduce_list (data, start); cbf_generate_codelengths (start, 0); /* Count the expected number of bits */ expected_bitcount = cbf_count_bits (data); /* Write the number of elements (64 bits) */ cbf_onfailnez (cbf_put_integer (file, nelem, 0, 64), cbf_free_compressdata (data)) /* Write the minimum element (64 bits) */ cbf_onfailnez (cbf_put_bits (file, minelement, 64), cbf_free_compressdata (data)) /* Write the maximum element (64 bits) */ cbf_onfailnez (cbf_put_bits (file, maxelement, 64), cbf_free_compressdata (data)) /* Write the reserved entry (64 bits) */ cbf_onfailnez (cbf_put_integer (file, 0, 0, 64), cbf_free_compressdata (data)) bitcount = 4 * 64; /* Write the table */ cbf_onfailnez (cbf_put_table (data, &bits), cbf_free_compressdata (data)) bitcount += bits; /* Generate the canonical bitcodes */ cbf_onfailnez (cbf_generate_canonicalcodes (data), \ cbf_free_compressdata (data)) /* Initialise the pointers */ unsigned_char_data = (unsigned char *) source; node = data->node; /* Maximum limit (unsigned) is 64 bits */ sign = 1 << ((elsize-(numints-1)*sizeof(int))* CHAR_BIT - 1); if (elsize == sizeof (int) || elsize == numints*sizeof(int) ) limit = ~0; else if (numints == 1) { limit = ~-(1 << (elsize * CHAR_BIT)); } else { limit = ~-(1 << ((elsize-(numints-1)*sizeof(int)) * CHAR_BIT)); } if (storedbits) *storedbits = (numints > 1)?(numints*sizeof(int)*CHAR_BIT):(elsize*CHAR_BIT); /* Offset to make the value unsigned */ if (elsign) unsign = sign; else unsign = 0; /* Start from 0 */ for (i = 0; i < numints-1; i++ ) lastelement[i] = 0; lastelement[numints-1] = unsign; endcode = 1 << data->bits; for (count = 0; count < nelem; count++) { /* Get the next element */ if (numints > 1 ) { if (border[0] == 'b') { for (iint = numints; iint; iint--) { element[iint-1] = *((unsigned int *) unsigned_char_data); unsigned_char_data += sizeof (int); } } else { for (iint = 0; iint < numints; iint++) { element[iint] = *((unsigned int *) unsigned_char_data); unsigned_char_data += sizeof (int); } } } else { if (elsize == sizeof (int)) element[0] = *((unsigned int *) unsigned_char_data); else if (elsize == sizeof (short)) element[0] = *((unsigned short *) unsigned_char_data); else element[0] = *unsigned_char_data; unsigned_char_data += elsize; } /* Make the element unsigned */ element[numints-1] += unsign; /* Limit the value to 64 bits */ if (element[numints-1] > limit) { if (elsign && (int) (element[numints-1] - unsign) < 0) { for(i=0; i 64) return CBF_ARGUMENT; numints = (bits + CHAR_BIT*sizeof (int) -1)/(CHAR_BIT*sizeof (int)); /* Discard the reserved entry (64 bits) */ cbf_failnez (cbf_get_integer (file, NULL, 0, 64)) /* Create and initialise the compression data */ cbf_failnez (cbf_make_compressdata (&data, file)) /* Read the compression table */ cbf_onfailnez (cbf_get_table (data), cbf_free_compressdata (data)) /* Set up the decode data */ cbf_onfailnez (cbf_setup_decode (data, &start), cbf_free_compressdata (data)) /* Initialise the pointer */ unsigned_char_data = (unsigned char *) destination; /* Maximum limit (unsigned) is 64 bits */ sign = 1 << ((elsize-(numints-1)*sizeof(int))* CHAR_BIT - 1); if (elsize == numints*sizeof(int) ) limit = ~0; else limit = ~-(1 << ((elsize-(numints-1)*sizeof(int)) * CHAR_BIT)); /* Offset to make the value unsigned */ if (elsign) unsign = sign; else unsign = 0; /* Get the local byte order */ if (realarray) { cbf_get_local_real_byte_order(&border); } else { cbf_get_local_integer_byte_order(&border); } /* How many ints do we need to hold 64 bits? */ count64 = (64 + sizeof (int) * CHAR_BIT - 1) / (sizeof (int) * CHAR_BIT); /* Initialise the first element */ for (iint = 0; iint < numints-1; iint++) last_element [iint] = 0; last_element [numints-1] = unsign; /* Read the elements */ for (count = 0; count < nelem; count++) { /* Read the offset */ errorcode = cbf_get_mpint_code (data, start, offset, &bits, numints); if (errorcode) { if (nelem_read) *nelem_read = count; cbf_free_compressdata (data); return errorcode; } /* Update the current element */ if (numints == 1) { last_element [0] += offset [0]; element[0] = last_element [0]; } else { cbf_mpint_add_acc(last_element,numints,offset,(bits+sizeof(int)*CHAR_BIT-1)/(sizeof(int)*CHAR_BIT)); for (i=0; i < numints; i++) element[i] = last_element[i]; } /* Limit the value to fit the element size */ if (element[numints-1] > limit) { if (elsign && (int) (element[numints-1] - unsign) < 0) element[numints-1] = 0; else element[numints-1] = limit; } /* Make the element signed? */ element[numints-1] -= unsign; /* Save the element */ if (elsize == sizeof (int)) *((unsigned int *) unsigned_char_data) = element[0]; else if (elsize == sizeof (short)) *((unsigned short *) unsigned_char_data) = element[0]; else if (elsize == sizeof (char)) { *unsigned_char_data = element[0]; } else { if (border[0] == 'b') { for (iint = numints; iint; iint--) { ((unsigned int *) unsigned_char_data)[numints-iint] = element[iint-1]; } } else { for (iint = 0; iint < numints; iint++) { ((unsigned int *) unsigned_char_data)[iint] = element[iint]; } } } unsigned_char_data += elsize; } /* Number read */ if (nelem_read) *nelem_read = count; /* Free memory */ cbf_free_compressdata (data); /* Success */ return 0; } #ifdef __cplusplus } #endif ./CBFlib-0.9.2.2/src/cbf_simple.c0000644000076500007650000055126711603702106014654 0ustar yayayaya/********************************************************************** * cbf_simple -- cbflib simplified API functions * * * * Version 0.8.0 20 July 2008 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifdef __cplusplus extern "C" { #endif #include #include #include #include #include "cbf.h" #include "cbf_alloc.h" #include "cbf_binary.h" #include "cbf_simple.h" #include "cbf_string.h" #ifdef CBFLIB_MEM_DEBUG extern size_t memory_allocated; #endif /* Read a template file */ int cbf_read_template (cbf_handle handle, FILE *stream) { /* Read the file */ cbf_failnez (cbf_read_widefile (handle, stream, MSG_NODIGEST)) /* Find the first datablock */ cbf_failnez (cbf_select_datablock (handle, 0)) return 0; } /* Get the diffrn.id entry */ int cbf_get_diffrn_id (cbf_handle handle, const char **diffrn_id) { cbf_failnez (cbf_find_category (handle, "diffrn")); cbf_failnez (cbf_find_column (handle, "id")); cbf_failnez (cbf_get_value (handle, diffrn_id)) return 0; } /* Get the diffrn.id entry, creating it if necessary */ int cbf_require_diffrn_id (cbf_handle handle, const char **diffrn_id, const char *default_id) { cbf_failnez (cbf_require_category (handle, "diffrn")); cbf_failnez (cbf_require_column (handle, "id")); cbf_failnez (cbf_require_value (handle, diffrn_id, default_id)) return 0; } /* Change the diffrn.id entry in all the categories */ int cbf_set_diffrn_id (cbf_handle handle, const char *diffrn_id) { int code; static char *categories [] = { "diffrn_source", "diffrn_radiation", "diffrn_detector", "diffrn_measurement", "diffrn_orient_matrix", 0 }, **category; cbf_failnez (cbf_find_category (handle, "diffrn")) cbf_failnez (cbf_find_column (handle, "id")) cbf_failnez (cbf_set_value (handle, diffrn_id)) for (category = categories; *category; category++) { code = cbf_find_category (handle, *category); if (code != CBF_NOTFOUND) { if (code) return code; cbf_failnez (cbf_find_column (handle, "diffrn_id")) do cbf_failnez (cbf_set_value (handle, diffrn_id)) while (cbf_next_row (handle)); } } if (!cbf_find_category (handle, "cell")) { cbf_failnez (cbf_find_column (handle, "entry_id")) cbf_failnez (cbf_set_value (handle, diffrn_id)) } return 0; } /* Get the diffrn.crystal_id entry */ int cbf_get_crystal_id (cbf_handle handle, const char **crystal_id) { cbf_failnez (cbf_find_category (handle, "diffrn")); cbf_failnez (cbf_find_column (handle, "crystal_id")); cbf_failnez (cbf_get_value (handle, crystal_id)) return 0; } /* Change the diffrn.crystal_id entry */ int cbf_set_crystal_id (cbf_handle handle, const char *crystal_id) { cbf_failnez (cbf_find_category (handle, "diffrn")) cbf_failnez (cbf_find_column (handle, "crystal_id")) cbf_failnez (cbf_set_value (handle, crystal_id)) return 0; } /* Get the wavelength */ int cbf_get_wavelength (cbf_handle handle, double *wavelength) { const char *diffrn_id, *wavelength_id; /* Get the diffrn.id */ cbf_failnez (cbf_get_diffrn_id (handle, &diffrn_id)) /* Get the wavelength id */ cbf_failnez (cbf_find_category (handle, "diffrn_radiation")) cbf_failnez (cbf_find_column (handle, "wavelength_id")) cbf_failnez (cbf_get_value (handle, &wavelength_id)) /* Get the wavelength */ cbf_failnez (cbf_find_category (handle, "diffrn_radiation_wavelength")) cbf_failnez (cbf_find_column (handle, "id")) cbf_failnez (cbf_find_row (handle, wavelength_id)) cbf_failnez (cbf_find_column (handle, "wavelength")) cbf_failnez (cbf_get_doublevalue (handle, wavelength)) return 0; } /* Set the wavelength */ int cbf_set_wavelength (cbf_handle handle, double wavelength) { /* Get the wavelength id */ const char *wavelength_id; cbf_failnez (cbf_find_category (handle, "diffrn_radiation")) cbf_failnez (cbf_find_column (handle, "wavelength_id")) cbf_failnez (cbf_get_value (handle, &wavelength_id)) /* Update the diffrn_radiation_wavelength category */ cbf_failnez (cbf_find_category (handle, "diffrn_radiation_wavelength")) cbf_failnez (cbf_find_column (handle, "id")) cbf_failnez (cbf_find_row (handle, wavelength_id)) cbf_failnez (cbf_find_column (handle, "wavelength")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", wavelength)) cbf_failnez (cbf_find_column (handle, "wt")) cbf_failnez (cbf_set_value (handle, "1.0")) return 0; } /* Get the polarization */ int cbf_get_polarization (cbf_handle handle, double *polarizn_source_ratio, double *polarizn_source_norm) { const char *diffrn_id; /* Get the diffrn.id */ cbf_failnez (cbf_get_diffrn_id (handle, &diffrn_id)) /* Get the polarization */ cbf_failnez (cbf_find_category (handle, "diffrn_radiation")) cbf_failnez (cbf_find_column (handle, "diffrn_id")) cbf_failnez (cbf_find_row (handle, diffrn_id)) cbf_failnez (cbf_find_column (handle, "polarizn_source_ratio")) cbf_failnez (cbf_get_doublevalue (handle, polarizn_source_ratio)) cbf_failnez (cbf_find_column (handle, "polarizn_source_norm")) cbf_failnez (cbf_get_doublevalue (handle, polarizn_source_norm)) return 0; } /* Set the polarization */ int cbf_set_polarization (cbf_handle handle, double polarizn_source_ratio, double polarizn_source_norm) { const char *diffrn_id; /* Get the diffrn.id */ cbf_failnez (cbf_get_diffrn_id (handle, &diffrn_id)) /* Update the diffrn_radiation category */ cbf_failnez (cbf_find_category (handle, "diffrn_radiation")) cbf_failnez (cbf_find_column (handle, "diffrn_id")) cbf_failnez (cbf_find_row (handle, diffrn_id)) cbf_failnez (cbf_find_column (handle, "polarizn_source_ratio")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", polarizn_source_ratio)) cbf_failnez (cbf_find_column (handle, "polarizn_source_norm")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", polarizn_source_norm)) return 0; } /* Get the divergence */ int cbf_get_divergence (cbf_handle handle, double *div_x_source, double *div_y_source, double *div_x_y_source) { const char *diffrn_id; /* Get the diffrn.id */ cbf_failnez (cbf_get_diffrn_id (handle, &diffrn_id)) /* Get the divergence */ cbf_failnez (cbf_find_category (handle, "diffrn_radiation")) cbf_failnez (cbf_find_column (handle, "diffrn_id")) cbf_failnez (cbf_find_row (handle, diffrn_id)) cbf_failnez (cbf_find_column (handle, "div_x_source")) cbf_failnez (cbf_get_doublevalue (handle, div_x_source)) cbf_failnez (cbf_find_column (handle, "div_y_source")) cbf_failnez (cbf_get_doublevalue (handle, div_y_source)) cbf_failnez (cbf_find_column (handle, "div_x_y_source")) cbf_failnez (cbf_get_doublevalue (handle, div_x_y_source)) return 0; } /* Set the divergence */ int cbf_set_divergence (cbf_handle handle, double div_x_source, double div_y_source, double div_x_y_source) { const char *diffrn_id; /* Get the diffrn.id */ cbf_failnez (cbf_get_diffrn_id (handle, &diffrn_id)) /* Update the diffrn_radiation category */ cbf_failnez (cbf_find_category (handle, "diffrn_radiation")) cbf_failnez (cbf_find_column (handle, "diffrn_id")) cbf_failnez (cbf_find_row (handle, diffrn_id)) cbf_failnez (cbf_find_column (handle, "div_x_source")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", div_x_source)) cbf_failnez (cbf_find_column (handle, "div_y_source")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", div_y_source)) cbf_failnez (cbf_find_column (handle, "div_x_y_source")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", div_x_y_source)) return 0; } /* Get the number of elements */ int cbf_count_elements (cbf_handle handle, unsigned int *elements) { const char *diffrn_id, *id; int errorcode; unsigned int count; /* Get the diffrn.id */ cbf_failnez (cbf_get_diffrn_id (handle, &diffrn_id)) cbf_failnez (cbf_find_category (handle, "diffrn_detector")) cbf_failnez (cbf_find_column (handle, "diffrn_id")) cbf_failnez (cbf_find_row (handle, diffrn_id)) cbf_failnez (cbf_find_column (handle, "id")) cbf_failnez (cbf_get_value (handle, &id)) cbf_failnez (cbf_find_category (handle, "diffrn_detector_element")) cbf_failnez (cbf_find_column (handle, "detector_id")) for (count = 0, errorcode = 0; !errorcode; count++) errorcode = cbf_find_nextrow (handle, id); count--; if (errorcode != CBF_NOTFOUND) return errorcode; if (elements) *elements = count; return 0; } /* Get the element id */ int cbf_get_element_id (cbf_handle handle, unsigned int element_number, const char **element_id) { const char *diffrn_id, *id; /* Get the diffrn.id */ cbf_failnez (cbf_get_diffrn_id (handle, &diffrn_id)) cbf_failnez (cbf_find_category (handle, "diffrn_detector")) cbf_failnez (cbf_find_column (handle, "diffrn_id")) cbf_failnez (cbf_find_row (handle, diffrn_id)) cbf_failnez (cbf_find_column (handle, "id")) cbf_failnez (cbf_get_value (handle, &id)) cbf_failnez (cbf_find_category (handle, "diffrn_detector_element")) cbf_failnez (cbf_find_column (handle, "detector_id")) do cbf_failnez (cbf_find_nextrow (handle, id)) while (element_number--); cbf_failnez (cbf_find_column (handle, "id")) cbf_failnez (cbf_get_value (handle, element_id)) return 0; } /* Get the detector id */ int cbf_get_detector_id (cbf_handle handle, unsigned int element_number, const char **detector_id) { const char *diffrn_id, *id; /* Get the diffrn.id */ cbf_failnez (cbf_get_diffrn_id (handle, &diffrn_id)) cbf_failnez (cbf_find_category (handle, "diffrn_detector")) cbf_failnez (cbf_find_column (handle, "diffrn_id")) cbf_failnez (cbf_find_row (handle, diffrn_id)) cbf_failnez (cbf_find_column (handle, "id")) cbf_failnez (cbf_get_value (handle, &id)) cbf_failnez (cbf_find_category (handle, "diffrn_detector_element")) cbf_failnez (cbf_find_column (handle, "detector_id")) do cbf_failnez (cbf_find_nextrow (handle, id)) while (element_number--); cbf_failnez (cbf_get_value (handle, detector_id)) return 0; } /* Get the array id for a given detector element */ int cbf_get_array_id (cbf_handle handle, unsigned int element_number, const char **array_id) { const char *element_id; cbf_failnez (cbf_get_element_id (handle, element_number, &element_id)) if ( cbf_find_category (handle, "diffrn_data_frame") ) { cbf_failnez (cbf_find_category (handle, "diffrn_frame_data")) } cbf_failnez (cbf_find_column (handle, "detector_element_id")) cbf_failnez (cbf_find_row (handle, element_id)) cbf_failnez (cbf_find_column (handle, "array_id")) cbf_failnez (cbf_get_value (handle, array_id)) return 0; } /* Get the pixel size of a detector element in a given direction axis numbering is 1-based, fast to slow */ int cbf_get_pixel_size(cbf_handle handle, unsigned int element_number, int axis_number, double * psize) { const char *array_id; int aid, precedence, max_precedence, axis_index; cbf_failnez (cbf_get_array_id (handle, element_number, &array_id)) cbf_failnez (cbf_find_category (handle, "array_structure_list")) cbf_failnez (cbf_find_column (handle, "array_id")) precedence = max_precedence = axis_index = 0; while (cbf_find_nextrow (handle, array_id) == 0) { cbf_failnez (cbf_find_column (handle, "precedence")) cbf_failnez (cbf_get_integervalue (handle, &precedence)) if (precedence < 1 ) return CBF_FORMAT; if (precedence > max_precedence) max_precedence = precedence; if (precedence == axis_number) { cbf_failnez (cbf_find_column (handle, "index")) cbf_failnez (cbf_get_integervalue (handle, &axis_index)) if (axis_index < 1) return CBF_FORMAT; } cbf_failnez (cbf_find_column (handle, "array_id")) } if (axis_index == 0 && axis_number < 0 ) { cbf_failnez (cbf_rewind_row (handle) ) while (cbf_find_nextrow (handle, array_id) == 0) { cbf_failnez (cbf_find_column (handle, "precedence")) cbf_failnez (cbf_get_integervalue (handle, &precedence)) if (precedence == max_precedence+1+axis_number) { cbf_failnez (cbf_find_column (handle, "index")) cbf_failnez (cbf_get_integervalue (handle, &axis_index)) if (axis_index < 1) return CBF_FORMAT; break; } cbf_failnez (cbf_find_column (handle, "array_id")) } } if (axis_index == 0 ) return CBF_NOTFOUND; if ( cbf_find_category (handle, "array_element_size") == 0 ) { cbf_failnez (cbf_rewind_row (handle)) cbf_failnez (cbf_find_column (handle, "array_id")) while (!cbf_find_nextrow (handle, array_id)) { cbf_failnez (cbf_find_column (handle, "index")) cbf_failnez (cbf_get_integervalue (handle, &aid)) if (aid == axis_index) { cbf_failnez (cbf_find_column (handle, "size")) cbf_failnez (cbf_get_doublevalue(handle, psize)) *psize *= 1.e3; return 0; } cbf_failnez (cbf_find_column (handle, "array_id")) } } return CBF_NOTFOUND; } /* Set the pixel size of a detector element in a given direction axis numbering is 1-based, fast to slow */ int cbf_set_pixel_size(cbf_handle handle, unsigned int element_number, int axis_number, double psize) { const char *array_id; int aid, precedence, max_precedence, axis_index; cbf_failnez (cbf_get_array_id (handle, element_number, &array_id)) cbf_failnez (cbf_find_category (handle, "array_structure_list")) cbf_failnez (cbf_find_column (handle, "array_id")) precedence = max_precedence = axis_index = 0; while (cbf_find_nextrow (handle, array_id) == 0) { cbf_failnez (cbf_find_column (handle, "precedence")) cbf_failnez (cbf_get_integervalue (handle, &precedence)) if (precedence < 1 ) return CBF_FORMAT; if (precedence > max_precedence) max_precedence = precedence; if (precedence == axis_number) { cbf_failnez (cbf_find_column (handle, "index")) cbf_failnez (cbf_get_integervalue (handle, &axis_index)) if (axis_index < 1) return CBF_FORMAT; } cbf_failnez (cbf_find_column (handle, "array_id")) } if (axis_index == 0 && axis_number < 0 ) { cbf_failnez (cbf_rewind_row (handle) ) while (cbf_find_nextrow (handle, array_id) == 0) { cbf_failnez (cbf_find_column (handle, "precedence")) cbf_failnez (cbf_get_integervalue (handle, &precedence)) if (precedence == max_precedence+1+axis_number) { cbf_failnez (cbf_find_column (handle, "index")) cbf_failnez (cbf_get_integervalue (handle, &axis_index)) if (axis_index < 1) return CBF_FORMAT; break; } cbf_failnez (cbf_find_column (handle, "array_id")) } } if (axis_index == 0 ) return CBF_NOTFOUND; if ( cbf_find_category (handle, "array_element_size") != 0 ) { cbf_failnez (cbf_new_category (handle, "array_element_size" )) cbf_failnez (cbf_new_column (handle, "array_id" )) cbf_failnez (cbf_set_value (handle, array_id )) cbf_failnez (cbf_new_column (handle, "index" )) cbf_failnez (cbf_set_integervalue (handle, axis_index )) cbf_failnez (cbf_new_column (handle, "size" )) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", psize*1.e-3)) return 0; } else { cbf_failnez (cbf_rewind_row (handle)) cbf_failnez (cbf_find_column (handle, "array_id")) while (!cbf_find_nextrow (handle, array_id)) { cbf_failnez (cbf_find_column (handle, "index")) cbf_failnez (cbf_get_integervalue (handle, &aid)) if (aid == axis_index) { cbf_failnez (cbf_find_column (handle, "size")) cbf_failnez (cbf_set_doublevalue(handle, "%-.15g", psize*1.e-3)) return 0; } cbf_failnez (cbf_find_column (handle, "array_id")) } } cbf_failnez (cbf_new_row (handle)) cbf_failnez (cbf_find_column (handle, "array_id" )) cbf_failnez (cbf_set_value (handle, array_id )) cbf_failnez (cbf_find_column (handle, "index" )) cbf_failnez (cbf_set_integervalue (handle, (int)axis_index )) cbf_failnez (cbf_find_column (handle, "size" )) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", psize*1.e-3 )) return 0; } /* Get the bin sizes of a detector element */ int cbf_get_bin_sizes(cbf_handle handle, unsigned int element_number, double * slowbinsize, double * fastbinsize) { const char *array_id; cbf_failnez (cbf_get_array_id (handle, element_number, &array_id)) /* Update the array_intensities category */ cbf_failnez (cbf_find_category (handle, "array_intensities")) cbf_failnez (cbf_find_column (handle, "array_id")) cbf_failnez (cbf_find_row (handle, array_id)) cbf_failnez (cbf_find_column (handle, "pixel_slow_bin_size")) cbf_failnez (cbf_get_doublevalue (handle, slowbinsize )) cbf_failnez (cbf_find_column (handle, "pixel_fast_bin_size")) cbf_failnez (cbf_get_doublevalue (handle, fastbinsize )) return 0; } /* Set the bin sizes of a detector element */ int cbf_set_bin_sizes(cbf_handle handle, unsigned int element_number, double slowbinsize, double fastbinsize) { const char *array_id; cbf_failnez (cbf_get_array_id (handle, element_number, &array_id)) /* Update the array_intensities category */ cbf_failnez (cbf_find_category (handle, "array_intensities")) cbf_failnez (cbf_require_column (handle, "array_id")) cbf_failnez (cbf_require_row (handle, array_id)) cbf_failnez (cbf_require_column (handle, "pixel_slow_bin_size")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", slowbinsize )) cbf_failnez (cbf_require_column (handle, "pixel_fast_bin_size")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", fastbinsize )) return 0; } /* Get the gain of a detector element */ int cbf_get_gain (cbf_handle handle, unsigned int element_number, double *gain, double *gain_esd) { const char *array_id; cbf_failnez (cbf_get_array_id (handle, element_number, &array_id)); /* Get the gain */ cbf_failnez (cbf_find_category (handle, "array_intensities")) cbf_failnez (cbf_find_column (handle, "array_id")) cbf_failnez (cbf_find_row (handle, array_id)) cbf_failnez (cbf_find_column (handle, "gain")) cbf_failnez (cbf_get_doublevalue (handle, gain)) cbf_failnez (cbf_find_column (handle, "gain_esd")) cbf_failnez (cbf_get_doublevalue (handle, gain_esd)) return 0; } /* Set the gain of a detector element */ int cbf_set_gain (cbf_handle handle, unsigned int element_number, double gain, double gain_esd) { const char *array_id; cbf_failnez (cbf_get_array_id (handle, element_number, &array_id)); /* Update the array_intensities category */ cbf_failnez (cbf_require_category (handle, "array_intensities")) cbf_failnez (cbf_require_column (handle, "array_id")) cbf_failnez (cbf_require_row (handle, array_id)) cbf_failnez (cbf_require_column (handle, "gain")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", gain)) cbf_failnez (cbf_require_column (handle, "gain_esd")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", gain_esd)) return 0; } /* Get the overload value of a detector element */ int cbf_get_overload (cbf_handle handle, unsigned int element_number, double *overload) { const char *array_id; cbf_failnez (cbf_get_array_id (handle, element_number, &array_id)); /* Get the overload value */ cbf_failnez (cbf_find_category (handle, "array_intensities")) cbf_failnez (cbf_find_column (handle, "array_id")) cbf_failnez (cbf_find_row (handle, array_id)) cbf_failnez (cbf_find_column (handle, "overload")) cbf_failnez (cbf_get_doublevalue (handle, overload)) return 0; } /* Set the overload value of a detector element */ int cbf_set_overload (cbf_handle handle, unsigned int element_number, double overload) { const char *array_id; cbf_failnez (cbf_get_array_id (handle, element_number, &array_id)); /* Update the array_intensities category */ cbf_failnez (cbf_require_category (handle, "array_intensities")) cbf_failnez (cbf_require_column (handle, "array_id")) cbf_failnez (cbf_require_row (handle, array_id)) cbf_failnez (cbf_require_column (handle, "overload")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", overload)) return 0; } /* Get the integration time */ int cbf_get_integration_time (cbf_handle handle, unsigned int reserved, double *time) { if (reserved != 0) return CBF_ARGUMENT; /* Update the diffrn_scan_frame category */ cbf_failnez (cbf_find_category (handle, "diffrn_scan_frame")) cbf_failnez (cbf_find_column (handle, "integration_time")) cbf_failnez (cbf_rewind_row (handle)) cbf_failnez (cbf_get_doublevalue (handle, time)) return 0; } /* Set the integration time */ int cbf_set_integration_time (cbf_handle handle, unsigned int reserved, double time) { if (reserved != 0) return CBF_ARGUMENT; /* Update the diffrn_scan_frame category */ cbf_failnez (cbf_require_category (handle, "diffrn_scan_frame")) cbf_failnez (cbf_require_column (handle, "integration_time")) cbf_failnez (cbf_rewind_row (handle)) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", time)) return 0; } /* Convert gregorian to julian date (in days) */ double cbf_gregorian_julian (int year, int month, int day, int hour, int minute, double second) { static int days [] = { 0, 31, 59, 90, 120, 151, 181, 212, 243, 273, 304, 334, 365 }; second += minute * 60.0 + hour * 3600.0 + (day - 1) * 86400.0; second += days [month - 1] * 86400.0; if (month > 2 && (year % 4) == 0 && year != 1900 && year != 2100) second += 86400.0; second += ((365 * (year - 1)) + floor ((year - 1) / 4) - floor ((year - 1) / 100) + floor ((year - 1) / 400)) * 86400.0; return second / 86400.0 + 1721425.5; } /* Get the collection date and time (1) as seconds since January 1 1970 */ int cbf_get_timestamp (cbf_handle handle, unsigned int reserved, double *time, int *timezone) { int year, month, day, hour, minute; double second; if (reserved != 0) return CBF_ARGUMENT; cbf_failnez (cbf_get_datestamp (handle, reserved, &year, &month, &day, &hour, &minute, &second, timezone)) if (time) *time = (cbf_gregorian_julian (year, month, day, hour, minute, second) - 2440587.5) * 86400.0; return 0; } /* Get the collection date and time (2) as individual fields */ int cbf_get_datestamp (cbf_handle handle, unsigned int reserved, int *year, int *month, int *day, int *hour, int *minute, double *second, int *timezone) { const char *date; char ftzsign; int fyear, fmonth, fday, fhour, fminute, ftzhour, ftzminute, parsed; double fsecond; if (reserved != 0) return CBF_ARGUMENT; /* Read the diffrn_scan_frame category */ cbf_failnez (cbf_find_category (handle, "diffrn_scan_frame")) cbf_failnez (cbf_find_column (handle, "date")) cbf_failnez (cbf_rewind_row (handle)) cbf_failnez (cbf_get_value (handle, &date)) /* Parse the string */ fsecond = fyear = fmonth = fday = fhour = fminute = ftzsign = ftzhour = ftzminute = 0; parsed = sscanf (date, "%d-%d-%d%*c%d:%d:%lf%c%d:%d", &fyear, &fmonth, &fday, &fhour, &fminute, &fsecond, &ftzsign, &ftzhour, &ftzminute); if (parsed < 3 || (parsed == 7 && strchr (" \t\n", ftzsign) == NULL) || (parsed > 7 && strchr ("+-", ftzsign) == NULL)) return CBF_FORMAT; if (fyear < 0 || fyear > 9999 || fmonth < 1 || fmonth > 12 || fday < 1 || fday > 31 || fhour < 0 || fhour > 23 || fminute < 0 || fminute > 59 || fsecond < 0 || fsecond >= 60 || ftzhour < 0 || ftzhour > 13 || ftzminute < 0 || ftzminute > 59) return CBF_FORMAT; if (year) *year = fyear; if (month) *month = fmonth; if (day) *day = fday; if (hour) *hour = fhour; if (minute) *minute = fminute; if (second) *second = fsecond; if (timezone) { if (parsed > 7) { *timezone = ftzhour * 60 + ftzminute; if (ftzsign == '-') *timezone = -*timezone; } else *timezone = CBF_NOTIMEZONE; } return 0; } /* Set the collection date and time (1) as seconds since January 1 1970 */ int cbf_set_timestamp (cbf_handle handle, unsigned int reserved, double time, int timezone, double precision) { int month, monthstep, year, day, hour, minute; double second, date; if (reserved != 0) return CBF_ARGUMENT; date = time / 86400.0 + 2440587.5; if (date < 1721060.5 || date > 5373484.5) return CBF_ARGUMENT; /* Find the year and month with a binary search */ for (monthstep = 65536, month = 0; monthstep; monthstep >>= 1) { month += monthstep; if (cbf_gregorian_julian (month / 12, (month % 12) + 1, 1, 0, 0, 0) > date) month -= monthstep; } /* Calculate the day, hour, minute and second */ year = month / 12; month = (month % 12) + 1; date -= cbf_gregorian_julian (year, month, 1, 0, 0, 0); day = (int) floor (date) + 1; date -= (day - 1); hour = (int) floor (date * 24.0); date -= hour / 24.0; minute = (int) floor (date * 1440.0); date -= minute / 1440.0; second = date * 86400.0; /* Set the new date */ cbf_failnez (cbf_set_datestamp (handle, reserved, year, month, day, hour, minute, second, timezone, precision)) return 0; } /* Set the collection date and time (2) as individual fields */ int cbf_set_datestamp (cbf_handle handle, unsigned int reserved, int year, int month, int day, int hour, int minute, double second, int timezone, double precision) { char date [256]; int nsf; if (reserved != 0) return CBF_ARGUMENT; /* Print the date in CIF format */ if (year < 0 || year > 9999 || month < 1 || month > 12 || day < 1 || day > 31 || hour < 0 || hour > 23 || minute < 0 || minute > 59 || second < 0 || second >= 60) return CBF_ARGUMENT; if (timezone != CBF_NOTIMEZONE) if (timezone < -780 || timezone > 780) return CBF_ARGUMENT; nsf = 0; if (precision > 0 && precision < 1) nsf = (int) (-log10 (precision) + 0.5); sprintf (date, "%04d-%02d-%02dT%02d:%02d:%0*.*f", year, month, day, hour, minute, nsf == 0 ? 2 : nsf + 3, nsf, second); if (timezone != CBF_NOTIMEZONE) sprintf (date + strlen (date), "%c%02d:%02d", timezone < 0 ? '-' : '+', abs (timezone) / 60, abs (timezone) % 60); /* Update the diffrn_scan_frame category */ cbf_failnez (cbf_require_category (handle, "diffrn_scan_frame")) cbf_failnez (cbf_require_column (handle, "date")) cbf_failnez (cbf_rewind_row (handle)) cbf_failnez (cbf_set_value (handle, date)) return 0; } /* Set the collection date and time (3) as current time to the second */ int cbf_set_current_timestamp (cbf_handle handle, unsigned int reserved, int timezone) { time_t timer; if (reserved != 0) return CBF_ARGUMENT; timer = time (NULL); if (timezone != CBF_NOTIMEZONE) timer += timezone * 60; cbf_failnez (cbf_set_timestamp (handle, reserved, timer, timezone, 1)) return 0; } /* Get the image size. ndimslow is the slow dimension, ndimfast is fast. */ int cbf_get_image_size (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimslow, size_t *ndimfast) { const char *array_id; size_t ndim0; cbf_failnez (cbf_get_array_id (handle, element_number, &array_id)); cbf_failnez (cbf_get_3d_array_size (handle, reserved, array_id, &ndim0, ndimslow, ndimfast)); if (ndim0 != 1) return CBF_ARGUMENT; return 0; } /* Read a binary section into an image. ndimslow is the slow dimension, ndimfast is fast.*/ int cbf_get_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast) { const char *array_id; int binary_id; binary_id = 1; cbf_failnez (cbf_get_array_id (handle, element_number, &array_id)); cbf_failnez (cbf_get_3d_array (handle, reserved, array_id, &binary_id, array, CBF_INTEGER, elsize, elsign, 1, ndimslow, ndimfast)); return 0; } /* Read a binary section into a real image. ndimslow is the slow dimension, ndimfast is fast. */ int cbf_get_real_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimslow, size_t ndimfast) { const char *array_id; int binary_id; binary_id = 1; cbf_failnez (cbf_get_array_id (handle, element_number, &array_id)); cbf_failnez (cbf_get_3d_array (handle, reserved, array_id, &binary_id, array, CBF_FLOAT, elsize, 1, 1, ndimslow, ndimfast)); return 0; } /* Get the 3D image size. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_get_3d_image_size (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimslow, size_t *ndimmid, size_t *ndimfast) { const char *array_id; cbf_failnez (cbf_get_array_id (handle, element_number, &array_id)); cbf_failnez (cbf_get_3d_array_size (handle, reserved, array_id, ndimslow, ndimmid, ndimfast)); return 0; } /* Read a 3D binary section into an image. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_get_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast) { const char *array_id; int binary_id; cbf_failnez (cbf_get_array_id (handle, element_number, &array_id)); cbf_failnez (cbf_get_3d_array (handle, reserved, array_id, &binary_id, array, CBF_INTEGER, elsize, elsign, ndimslow, ndimmid, ndimfast)); return 0; } /* Read a 3D binary section into a real image. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_get_real_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast) { const char *array_id; int binary_id; cbf_failnez (cbf_get_array_id (handle, element_number, &array_id)); cbf_failnez (cbf_get_3d_array (handle, reserved, array_id, &binary_id, array, CBF_FLOAT, elsize, 1, ndimslow, ndimmid, ndimfast)); return 0; } /* Save an image. ndimslow is the slow dimension, ndimfast is fast. */ int cbf_set_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast) { const char *array_id; int binary_id=1; cbf_failnez (cbf_get_array_id (handle, element_number, &array_id)); cbf_failnez (cbf_set_3d_array(handle, reserved, array_id, &binary_id, compression, array, CBF_INTEGER, elsize, elsign, 1, ndimslow, ndimfast)); return 0; } /* Save a real image. ndimslow is the slow dimension, ndimfast is fast. */ int cbf_set_real_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, size_t ndimslow, size_t ndimfast) { const char *array_id; int binary_id = 1; cbf_failnez (cbf_get_array_id (handle, element_number, &array_id)); cbf_failnez (cbf_set_3d_array(handle, reserved, array_id, &binary_id, compression, array, CBF_FLOAT, elsize, 1, 1, ndimslow, ndimfast)); return 0; } /* Save a 3D image. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension. */ int cbf_set_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast) { const char *array_id; int binary_id = 1; cbf_failnez (cbf_get_array_id (handle, element_number, &array_id)); cbf_failnez (cbf_set_3d_array(handle, reserved, array_id, &binary_id, compression, array, CBF_INTEGER, elsize, elsign, ndimslow, ndimmid, ndimfast)); return 0; } /* Save a real 3D image. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_set_real_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast) { const char *array_id; int binary_id = 1; cbf_failnez (cbf_get_array_id (handle, element_number, &array_id)); cbf_failnez (cbf_set_3d_array(handle, reserved, array_id, &binary_id,compression, array, CBF_FLOAT, elsize, 1, ndimslow, ndimmid, ndimfast)); return 0; } /* Get the array_id for a map segment or map segment mask. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension. */ int cbf_get_map_array_id (cbf_handle handle, unsigned int reserved, const char *segment_id, const char **array_id, int ismask, int require, size_t ndimslow, size_t ndimmid, size_t ndimfast) { if (require) { cbf_failnez (cbf_require_category (handle, "map_segment")); cbf_failnez (cbf_require_column (handle, "id")); } else { cbf_failnez (cbf_find_category (handle, "map_segment")); cbf_failnez (cbf_find_column (handle, "id")); } if (cbf_find_row(handle,segment_id)) { if (!require) return CBF_NOTFOUND; cbf_failnez(cbf_new_row(handle)); cbf_failnez(cbf_set_value(handle,segment_id)); } if (ismask) { cbf_failnez( cbf_require_column (handle, "mask_array_id") ) } else { cbf_failnez( cbf_require_column (handle, "array_id") ) } if (cbf_get_value (handle, array_id) || !*array_id || strlen(*array_id)==0) { if (!require) return CBF_NOTFOUND; /* If no array structure has been defined, use the segment_id */ cbf_failnez(cbf_set_value(handle,segment_id)); cbf_failnez(cbf_require_category(handle, "axis" ) ); cbf_failnez (cbf_require_column(handle,"system")) cbf_failnez (cbf_require_column(handle,"vector[1]")) cbf_failnez (cbf_require_column(handle,"vector[2]")) cbf_failnez (cbf_require_column(handle,"vector[3]")) cbf_failnez (cbf_require_column(handle, "id" )) if (cbf_find_row(handle,"CELL_A_AXIS") ) { cbf_failnez (cbf_new_row(handle)) cbf_failnez (cbf_set_value(handle, "CELL_A_AXIS")) cbf_failnez (cbf_set_typeofvalue(handle, "word")) cbf_failnez (cbf_find_column(handle, "system")) cbf_failnez (cbf_set_value(handle, "fractional")) cbf_failnez (cbf_set_typeofvalue(handle, "word")) cbf_failnez (cbf_find_column(handle, "vector[1]")) cbf_failnez (cbf_set_integervalue(handle, 1)) cbf_failnez (cbf_find_column(handle, "vector[2]")) cbf_failnez (cbf_set_integervalue(handle, 0)) cbf_failnez (cbf_find_column(handle, "vector[3]")) cbf_failnez (cbf_set_integervalue(handle, 0)) cbf_failnez (cbf_find_column(handle, "id")) } if (cbf_find_row(handle,"CELL_B_AXIS") ) { cbf_failnez (cbf_new_row(handle)) cbf_failnez (cbf_set_value(handle, "CELL_B_AXIS")) cbf_failnez (cbf_set_typeofvalue(handle, "word")) cbf_failnez (cbf_find_column(handle, "system")) cbf_failnez (cbf_set_value(handle, "fractional")) cbf_failnez (cbf_set_typeofvalue(handle, "word")) cbf_failnez (cbf_find_column(handle, "vector[1]")) cbf_failnez (cbf_set_integervalue(handle, 0)) cbf_failnez (cbf_find_column(handle, "vector[2]")) cbf_failnez (cbf_set_integervalue(handle, 1)) cbf_failnez (cbf_find_column(handle, "vector[3]")) cbf_failnez (cbf_set_integervalue(handle, 0)) cbf_failnez (cbf_find_column(handle, "id")) } if (cbf_find_row(handle,"CELL_C_AXIS") ) { cbf_failnez (cbf_new_row(handle)) cbf_failnez (cbf_set_value(handle, "CELL_C_AXIS")) cbf_failnez (cbf_set_typeofvalue(handle, "word")) cbf_failnez (cbf_find_column(handle, "system")) cbf_failnez (cbf_set_value(handle, "fractional")) cbf_failnez (cbf_set_typeofvalue(handle, "word")) cbf_failnez (cbf_find_column(handle, "vector[1]")) cbf_failnez (cbf_set_integervalue(handle, 0)) cbf_failnez (cbf_set_typeofvalue(handle, "word")) cbf_failnez (cbf_find_column(handle, "vector[2]")) cbf_failnez (cbf_set_integervalue(handle, 0)) cbf_failnez (cbf_find_column(handle, "vector[3]")) cbf_failnez (cbf_set_integervalue(handle, 1)) } cbf_failnez(cbf_require_category(handle, "array_structure_list_axis" ) ); cbf_failnez (cbf_require_column(handle,"array_id")) cbf_failnez (cbf_require_column(handle,"index")) cbf_failnez (cbf_require_column(handle,"dimension")) cbf_failnez (cbf_require_column(handle,"precedence")) cbf_failnez (cbf_require_column(handle,"direction")) cbf_failnez (cbf_require_column(handle,"axis_id")) if (cbf_find_row(handle,"CELL_A_AXIS")){ cbf_failnez (cbf_new_row(handle)); cbf_failnez (cbf_find_column(handle, "array_id")) cbf_failnez (cbf_set_value(handle, segment_id)) cbf_failnez (cbf_find_column(handle, "index")) cbf_failnez (cbf_set_integervalue(handle, 1)) cbf_failnez (cbf_set_typeofvalue(handle, "word")) cbf_failnez (cbf_find_column(handle, "dimension")) cbf_failnez (cbf_set_integervalue(handle, ndimfast)) cbf_failnez (cbf_find_column(handle, "precedence")) cbf_failnez (cbf_set_integervalue(handle, 1)) cbf_failnez (cbf_find_column(handle, "direction")) cbf_failnez (cbf_set_value(handle, "increasing")) cbf_failnez (cbf_find_column(handle, "axis_id")) cbf_failnez (cbf_set_value(handle, "CELL_A_AXIS")) } if (cbf_find_row(handle,"CELL_B_AXIS")){ cbf_failnez (cbf_new_row(handle)) cbf_failnez (cbf_find_column(handle, "array_id")) cbf_failnez (cbf_set_value(handle, segment_id)) cbf_failnez (cbf_find_column(handle, "index")) cbf_failnez (cbf_set_integervalue(handle, 2)) cbf_failnez (cbf_find_column(handle, "dimension")) cbf_failnez (cbf_set_integervalue(handle, ndimmid)) cbf_failnez (cbf_find_column(handle, "precedence")) cbf_failnez (cbf_set_integervalue(handle, 2)) cbf_failnez (cbf_find_column(handle, "direction")) cbf_failnez (cbf_set_value(handle, "increasing")) cbf_failnez (cbf_find_column(handle, "axis_id")) cbf_failnez (cbf_set_value(handle, "CELL_B_AXIS")) } if (cbf_find_row(handle,"CELL_C_AXIS")){ cbf_failnez (cbf_new_row(handle)) cbf_failnez (cbf_find_column(handle, "array_id")) cbf_failnez (cbf_set_value(handle, segment_id)) cbf_failnez (cbf_find_column(handle, "index")) cbf_failnez (cbf_set_integervalue(handle, 3)) cbf_failnez (cbf_find_column(handle, "dimension")) cbf_failnez (cbf_set_integervalue(handle, ndimslow)) cbf_failnez (cbf_find_column(handle, "precedence")) cbf_failnez (cbf_set_integervalue(handle, 3)) cbf_failnez (cbf_find_column(handle, "direction")) cbf_failnez (cbf_set_value(handle, "increasing")) cbf_failnez (cbf_find_column(handle, "axis_id")) cbf_failnez (cbf_set_value(handle, "CELL_C_AXIS")) } cbf_failnez (cbf_require_category(handle,"array_structure_list_axis")) cbf_failnez (cbf_require_column(handle,"fract_displacement")) cbf_failnez (cbf_require_column(handle,"fract_displacement_increment")) cbf_failnez (cbf_require_column(handle,"axis_id")) if (cbf_find_row(handle,"CELL_A_AXIS")) { cbf_failnez (cbf_new_row(handle)) cbf_failnez (cbf_set_value(handle, "CELL_A_AXIS")) cbf_failnez (cbf_set_typeofvalue(handle, "word")) cbf_failnez (cbf_find_column(handle, "fract_displacement")) cbf_failnez (cbf_set_doublevalue(handle, "%-.15g", (double)1./(double)(ndimfast*2))) cbf_failnez (cbf_find_column(handle, "fract_displacement_increment")) cbf_failnez (cbf_set_doublevalue(handle, "%-.15g", (double)1./(double)(ndimfast))) cbf_failnez (cbf_find_column(handle, "axis_id")) } if (cbf_find_row(handle,"CELL_B_AXIS")) { cbf_failnez (cbf_new_row(handle)) cbf_failnez (cbf_set_value(handle, "CELL_A_AXIS")) cbf_failnez (cbf_set_typeofvalue(handle, "word")) cbf_failnez (cbf_find_column(handle, "fract_displacement")) cbf_failnez (cbf_set_doublevalue(handle, "%-.15g", (double)1./(double)(ndimmid*2))) cbf_failnez (cbf_find_column(handle, "fract_displacement_increment")) cbf_failnez (cbf_set_doublevalue(handle, "%-.15g", (double)1./(double)(ndimmid))) cbf_failnez (cbf_find_column(handle, "axis_id")) } if (cbf_find_row(handle,"CELL_C_AXIS")) { cbf_failnez (cbf_new_row(handle)) cbf_failnez (cbf_set_value(handle, "CELL_A_AXIS")) cbf_failnez (cbf_set_typeofvalue(handle, "word")) cbf_failnez (cbf_find_column(handle, "fract_displacement")) cbf_failnez (cbf_set_doublevalue(handle, "%-.15g", (double)1./(double)(ndimslow*2))) cbf_failnez (cbf_find_column(handle, "fract_displacement_increment")) cbf_failnez (cbf_set_doublevalue(handle, "%-.15g", (double)1./(double)(ndimslow))) cbf_failnez (cbf_find_column(handle, "axis_id")) } } else { *array_id = segment_id; } return 0; } /* Get the map segment size. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_get_map_segment_size (cbf_handle handle, unsigned int reserved, const char *segment_id, int *binary_id, size_t *ndimslow, size_t *ndimmid, size_t *ndimfast) { const char *array_id; cbf_failnez (cbf_get_map_array_id (handle, reserved, segment_id, &array_id, 0, 0, *ndimslow, *ndimmid, *ndimfast) ) cbf_failnez (cbf_get_3d_array_size (handle, reserved, array_id, ndimslow, ndimmid, ndimfast)); return 0; } /* Read a map segment. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_get_map_segment (cbf_handle handle, unsigned int reserved, const char *segment_id, int *binary_id, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast) { const char *array_id; cbf_failnez (cbf_get_map_array_id (handle, reserved, segment_id, &array_id, 0, 0, ndimslow, ndimmid, ndimfast) ) cbf_failnez (cbf_get_3d_array (handle, reserved, array_id, binary_id, array, CBF_INTEGER, elsize, elsign, ndimslow, ndimmid, ndimfast)); return 0; } /* Read a map segment mask. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_get_map_segment_mask (cbf_handle handle, unsigned int reserved, const char *segment_id, int *binary_id, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast) { const char *array_id; cbf_failnez (cbf_get_map_array_id (handle, reserved, segment_id, &array_id, 1, 0, ndimslow, ndimmid, ndimfast) ) cbf_failnez (cbf_get_3d_array (handle, reserved, array_id, binary_id, array, CBF_INTEGER, elsize, elsign, ndimslow, ndimmid, ndimfast)); return 0; } /* Read a real map segment. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_get_real_map_segment (cbf_handle handle, unsigned int reserved, const char *segment_id, int *binary_id, void *array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast) { const char *array_id; cbf_failnez (cbf_get_map_array_id (handle, reserved, segment_id, &array_id, 0, 0, ndimslow, ndimmid, ndimfast) ) cbf_failnez (cbf_get_3d_array (handle, reserved, array_id, binary_id, array, CBF_FLOAT, elsize, 1, ndimslow, ndimmid, ndimfast)); return 0; } /* Read a real map segment mask. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_get_real_map_segment_mask (cbf_handle handle, unsigned int reserved, const char *segment_id, int *binary_id, void *array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast) { const char *array_id; cbf_failnez (cbf_get_map_array_id (handle, reserved, segment_id, &array_id, 1, 0, ndimslow, ndimmid, ndimfast) ) cbf_failnez (cbf_get_3d_array (handle, reserved, array_id, binary_id, array, CBF_FLOAT, elsize, 1, ndimslow, ndimmid, ndimfast)); return 0; } /* Save a map segment. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_set_map_segment (cbf_handle handle, unsigned int reserved, const char *segment_id, int *binary_id, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast) { const char *array_id; cbf_failnez (cbf_get_map_array_id (handle, reserved, segment_id, &array_id, 0, 1, ndimslow, ndimmid, ndimfast) ) cbf_failnez (cbf_set_3d_array(handle, reserved, array_id, binary_id, compression, array, CBF_INTEGER, elsize, elsign, ndimslow, ndimmid, ndimfast)); return 0; } /* Save a map segment mask. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_set_map_segment_mask (cbf_handle handle, unsigned int reserved, const char *segment_id, int *binary_id, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast) { const char *array_id; cbf_failnez (cbf_get_map_array_id (handle, reserved, segment_id, &array_id, 1, 1, ndimslow, ndimmid, ndimfast) ) cbf_failnez (cbf_set_3d_array(handle, reserved, array_id, binary_id, compression, array, CBF_INTEGER, elsize, elsign, ndimslow, ndimmid, ndimfast)); return 0; } /* Save a real map segment. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_set_real_map_segment (cbf_handle handle, unsigned int reserved, const char *segment_id, int *binary_id, unsigned int compression, void *array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast) { const char *array_id; cbf_failnez (cbf_get_map_array_id (handle, reserved, segment_id, &array_id, 0, 1, ndimslow, ndimmid, ndimfast) ) cbf_failnez (cbf_set_3d_array(handle, reserved, array_id, binary_id, compression, array, CBF_FLOAT, elsize, 1, ndimslow, ndimmid, ndimfast)); return 0; } /* Save a real map segment mask. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_set_real_map_segment_mask (cbf_handle handle, unsigned int reserved, const char *segment_id, int *binary_id, unsigned int compression, void *array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast) { const char *array_id; cbf_failnez (cbf_get_map_array_id (handle, reserved, segment_id, &array_id, 1, 1, ndimslow, ndimmid, ndimfast) ) cbf_failnez (cbf_set_3d_array(handle, reserved, array_id, binary_id, compression, array, CBF_FLOAT, elsize, 1, ndimslow, ndimmid, ndimfast)); return 0; } /* Get the 3D array size. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_get_3d_array_size (cbf_handle handle, unsigned int reserved, const char *array_id, size_t *ndimslow, size_t *ndimmid, size_t *ndimfast) { int done [4], precedence, dimension [4], kdim[4]; if (reserved != 0) return CBF_ARGUMENT; /* Get the dimensions from the array_structure_list category */ done [1] = done [2] = done [3] = 0; dimension [1] = dimension [2] = dimension [3] = 1; cbf_failnez (cbf_find_category (handle, "array_structure_list")) cbf_failnez (cbf_find_column (handle, "array_id")) while (cbf_find_nextrow (handle, array_id) == 0) { cbf_failnez (cbf_find_column (handle, "precedence")) cbf_failnez (cbf_get_integervalue (handle, &precedence)) if (precedence < 1 || precedence > 3) return CBF_FORMAT; cbf_failnez (cbf_find_column (handle, "dimension")) cbf_failnez (cbf_get_integervalue (handle, &dimension [precedence])) if (done [precedence]) return CBF_FORMAT; done [precedence] = 1; cbf_failnez (cbf_find_column (handle, "array_id")) } if (!done [1]) return CBF_NOTFOUND; if (!done [2]) { kdim [3] = dimension [1]; kdim [2] = 1; kdim [1] = 1; } else { kdim [1] = 1; kdim [2] = dimension [2]; kdim [3] = dimension [1]; } if (done[3]) { kdim [1] = dimension[3]; } if (ndimslow) *ndimslow = kdim [1]; if (ndimmid) *ndimmid = kdim [2]; if (ndimfast) *ndimfast = kdim [3]; return 0; } /* Read a 3D array. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_get_3d_array (cbf_handle handle, unsigned int reserved, const char *array_id, int *binary_id, void *array, int eltype, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast) { const char *direction_string; int code, done [4], precedence, direction [4], local_binary_id, dir1=1, dir2=1, dir3=1, index1, index2, index3, start1, end1, inc1, start2, end2, inc2, start3, end3, inc3; size_t nelem_read, dimslow, dimmid, dimfast; char tmp [32], *pixel, *pixel2; if (reserved != 0) return CBF_ARGUMENT; if ( eltype != CBF_FLOAT && eltype != CBF_INTEGER) return CBF_ARGUMENT; if ( eltype == CBF_FLOAT && elsize != 4 && elsize != 8 ) return CBF_ARGUMENT; if ( eltype == CBF_FLOAT && !elsign) return CBF_ARGUMENT; /* Get the index dimensions */ cbf_failnez (cbf_get_3d_array_size (handle, reserved, array_id, &dimslow, &dimmid, &dimfast)) /* Check that the fast dimensions correspond */ if (dimmid != ndimmid || dimfast != ndimfast) return CBF_ARGUMENT; /* Get the index directions from the array_structure_list category */ done [1] = done [2] = done[3] = 0; direction [1] = direction [2] = direction [3] = 1; cbf_failnez (cbf_find_category (handle, "array_structure_list")) cbf_failnez (cbf_find_column (handle, "array_id")) while (cbf_find_nextrow (handle, array_id) == 0) { cbf_failnez (cbf_find_column (handle, "precedence")) cbf_failnez (cbf_get_integervalue (handle, &precedence)) if (precedence < 1 || precedence > 3) return CBF_FORMAT; code = cbf_find_column (handle, "direction"); if (code == 0) { cbf_failnez (cbf_get_value (handle, &direction_string)) if (cbf_cistrcmp ("decreasing", direction_string) == 0) direction [precedence] = -1; } else if (code != CBF_NOTFOUND) return code; if (done [precedence]) return CBF_FORMAT; done [precedence] = 1; cbf_failnez (cbf_find_column (handle, "array_id")) } if (!done [1]) return CBF_NOTFOUND; if (!done [2]) { dir1 = direction [1]; dir2 = 1; } else { dir1 = direction [2]; dir2 = direction [1]; } if (!done [3]) { dir3 = 1; } else { dir3 = dir2; dir2 = dir1; dir1 = direction [3]; } /* Find the binary data */ cbf_failnez (cbf_find_category (handle, "array_data")) cbf_failnez (cbf_find_column (handle, "array_id")) cbf_failnez (cbf_find_row (handle, array_id)) if ( binary_id ) { if (cbf_find_column(handle, "binary_id")) { if ( *binary_id !=0 && *binary_id != 1 ) return CBF_NOTFOUND; } else { while (1) { if (cbf_get_integervalue( handle, &local_binary_id) || local_binary_id == 0) local_binary_id = 1; if (local_binary_id != *binary_id) { cbf_failnez (cbf_find_column (handle, "array_id")) if (cbf_find_nextrow (handle, array_id)) return CBF_NOTFOUND; cbf_failnez (cbf_find_column(handle, "binary_id")) } else break; } } } cbf_failnez (cbf_find_column (handle, "data")) /* Read the binary data */ if ( ndimslow <= 0 || ndimmid <= 0 || ndimfast <= 0) return CBF_ARGUMENT; if (eltype == CBF_INTEGER) { cbf_failnez (cbf_get_integerarray (handle, &local_binary_id, array, elsize, elsign, ndimslow * ndimmid * ndimfast, &nelem_read)) } else { cbf_failnez (cbf_get_realarray (handle, &local_binary_id, array, elsize, ndimslow * ndimmid * ndimfast, &nelem_read)) } if ( binary_id ) *binary_id = local_binary_id; /* Reorder the data if necessary */ #ifndef CBF_0721_READS if (dir1 < 0 || dir2 < 0 || dir3 < 0 ) { if (dir1 >= 0) { start1 = 0; end1 = ndimslow; inc1 = 1; } else { start1 = ndimslow - 1; end1 = -1; inc1 = -1; } if (dir2 >= 0) { start2 = 0; end2 = ndimmid; inc2 = 1; } else { start2 = ndimmid - 1; end2 = -1; inc2 = -1; } if (dir3 >= 0) { start3 = 0; end3 = ndimfast; inc3 = 1; } else { start3 = ndimfast - 1; end3 = -1; inc3 = -1; } pixel = (char *) array; for (index1 = start1; index1 != end1; index1 += inc1) for (index2 = start2; index2 != end2; index2 += inc2) for (index3 = start3; index3 != end3; index3 += inc3) { pixel2 = ((char *) array) + (index1*ndimmid*ndimfast + index2 * ndimfast + index3) * elsize; if (pixel < pixel2) { if (elsize == sizeof (int)) { *((int *) tmp) = *((int *) pixel); *((int *) pixel) = *((int *) pixel2); *((int *) pixel2) = *((int *) tmp); } else { memcpy (tmp, pixel, elsize); memcpy (pixel, pixel2, elsize); memcpy (pixel2, tmp, elsize); } } pixel += elsize; } } #endif if (ndimslow * ndimmid * ndimfast != nelem_read) return CBF_ENDOFDATA; return 0; } /* Save a 3D array. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_set_3d_array (cbf_handle handle, unsigned int reserved, const char *array_id, int *binary_id, unsigned int compression, void *array, int eltype, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast) { char enctype[30]; int local_binary_id, done [4], precedence, dimension [4]; if (reserved != 0) return CBF_ARGUMENT; if ( eltype != CBF_FLOAT && eltype != CBF_INTEGER) return CBF_ARGUMENT; if ( eltype == CBF_FLOAT && elsize != 4 && elsize != 8 ) return CBF_ARGUMENT; if ( eltype == CBF_FLOAT && !elsign) return CBF_ARGUMENT; /* Update the array_structure_list category */ if (ndimslow == 0) dimension [3] = 1; else dimension [3] = ndimslow; if (ndimmid == 0) dimension [2] = 1; else dimension [2] = ndimmid; if (ndimfast == 0) dimension [1] = 1; else dimension [1] = ndimfast; done [1] = dimension [1] == 1; done [2] = dimension [2] == 1; done [3] = dimension [3] == 1; cbf_failnez (cbf_find_category (handle, "array_structure_list")) cbf_failnez (cbf_find_column (handle, "array_id")) while (cbf_find_nextrow (handle, array_id) == 0) { cbf_failnez (cbf_find_column (handle, "precedence")) cbf_failnez (cbf_get_integervalue (handle, &precedence)) if (precedence < 1 || precedence > 3) return CBF_FORMAT; cbf_failnez (cbf_find_column (handle, "dimension")) cbf_failnez (cbf_set_integervalue (handle, dimension [precedence])) done [precedence] = 1; cbf_failnez (cbf_find_column (handle, "array_id")) } if (!done [1] || !done [2] || !done[3]) return CBF_NOTFOUND; /* Get the binary_id */ cbf_failnez (cbf_require_category (handle, "array_data")) cbf_failnez (cbf_require_column (handle, "array_id")) cbf_failnez (cbf_rewind_row (handle)) if (cbf_find_row (handle, array_id)) { cbf_failnez (cbf_new_row(handle)) cbf_failnez (cbf_set_value(handle,array_id)) } cbf_failnez (cbf_require_column (handle, "binary_id")) if (binary_id) { if (*binary_id == 0) *binary_id = 1; while (1) { if ( cbf_get_integervalue(handle,&local_binary_id) || local_binary_id == 0) local_binary_id = 1; if ( local_binary_id != *binary_id ) { cbf_failnez (cbf_find_column(handle, "array_id")) if (cbf_find_nextrow(handle, array_id)) { cbf_failnez (cbf_new_row( handle )) cbf_failnez (cbf_set_value(handle,array_id)) cbf_failnez (cbf_find_column (handle, "binary_id")) cbf_failnez (cbf_set_integervalue (handle, *binary_id)) break; } cbf_failnez (cbf_find_column(handle, "binary_id")) } else { break; } } } else { if (cbf_get_integervalue (handle, &local_binary_id)) { local_binary_id = 1; cbf_failnez (cbf_set_integervalue (handle, local_binary_id)) } } cbf_failnez (cbf_find_column (handle, "data")) /* Save the array */ if (eltype == CBF_INTEGER) { cbf_failnez (cbf_set_integerarray_wdims (handle, compression, *binary_id, array, elsize, elsign, dimension [1] * dimension [2] * dimension [3], "little_endian", dimension[1], (dimension[3]>1||dimension[2]>1)?dimension[2]:0, dimension[3]>1?dimension[3]:0,0 )) } else { cbf_failnez (cbf_set_realarray_wdims (handle, compression, *binary_id, array, elsize, dimension [1] * dimension [2] * dimension [3], "little_endian", dimension[1], (dimension[3]>1||dimension[2]>1)?dimension[2]:0, dimension[3]>1?dimension[3]:0,0 )) } /* Update the array_structure category */ cbf_failnez (cbf_require_category (handle, "array_structure")) cbf_failnez (cbf_require_column (handle, "id")) cbf_failnez (cbf_rewind_row (handle)) if (cbf_find_row (handle, array_id)) { cbf_failnez (cbf_new_row(handle)) cbf_failnez (cbf_set_value(handle,array_id)) cbf_failnez (cbf_set_typeofvalue(handle,"word")) } cbf_failnez (cbf_require_column (handle, "encoding_type")) if (eltype == CBF_INTEGER) { if (elsign) { sprintf(enctype,"signed %d-bit integer", ((int)elsize)*8); } else { sprintf(enctype,"unsigned %d-bit integer", ((int)elsize)*8); } } else { sprintf(enctype,"signed %d-bit real IEEE", ((int)elsize)*8); } cbf_failnez (cbf_set_value (handle,enctype)) cbf_failnez (cbf_set_typeofvalue (handle,"dblq")) cbf_failnez (cbf_require_column (handle, "compression_type")) switch (compression&CBF_COMPRESSION_MASK) { case (CBF_NONE): cbf_failnez (cbf_set_value (handle,"none")) cbf_failnez (cbf_set_typeofvalue(handle,"word")) break; case (CBF_CANONICAL): cbf_failnez (cbf_set_value (handle,"canonical")) cbf_failnez (cbf_set_typeofvalue(handle,"word")) break; case (CBF_PACKED): cbf_failnez (cbf_set_value (handle,"packed")) cbf_failnez (cbf_set_typeofvalue(handle,"word")) break; case (CBF_PACKED_V2): cbf_failnez (cbf_set_value (handle,"packed_v2")) cbf_failnez (cbf_set_typeofvalue(handle,"word")) break; case (CBF_BYTE_OFFSET): cbf_failnez (cbf_set_value (handle,"byte_offsets")) cbf_failnez (cbf_set_typeofvalue(handle,"word")) break; case (CBF_PREDICTOR): cbf_failnez (cbf_set_value (handle,"predictor")) cbf_failnez (cbf_set_typeofvalue(handle,"word")) break; default: cbf_failnez (cbf_set_value (handle,".")) cbf_failnez (cbf_set_typeofvalue(handle,"null")) break; } if (compression&CBF_FLAG_MASK) { if (compression&CBF_UNCORRELATED_SECTIONS) { cbf_failnez (cbf_require_column (handle, "compression_type_flag")) cbf_failnez (cbf_set_value (handle, "uncorrelated_sections")) cbf_failnez (cbf_set_typeofvalue(handle,"word")) } else if (compression&CBF_FLAT_IMAGE) { cbf_failnez (cbf_require_column (handle, "compression_type_flag")) cbf_failnez (cbf_set_value (handle, "flat")) cbf_failnez (cbf_set_typeofvalue(handle,"word")) } else return CBF_ARGUMENT; } cbf_failnez (cbf_require_column (handle, "byte_order")) cbf_failnez (cbf_set_value (handle, "little_endian")) return 0; } /* Get the type of an axis */ int cbf_get_axis_type (cbf_handle handle, const char *axis_id, cbf_axis_type *axis_type) { const char *type; /* Get the axis type */ cbf_failnez (cbf_find_category (handle, "axis")) cbf_failnez (cbf_find_column (handle, "id")) cbf_failnez (cbf_find_row (handle, axis_id)) cbf_failnez (cbf_find_column (handle, "type")) cbf_failnez (cbf_get_value (handle, &type)) if (!type) return CBF_NOTFOUND; if (toupper (*type) != 'T' && toupper (*type) != 'R' && toupper (*type) != 'G') return CBF_FORMAT; if (axis_type) { if (toupper (*type) == 'T') { *axis_type = CBF_TRANSLATION_AXIS; } else { if (toupper (*type) == 'R') { *axis_type = CBF_ROTATION_AXIS; } else { *axis_type = CBF_GENERAL_AXIS; } } } return 0; } /* Get an axis vector */ int cbf_get_axis_vector (cbf_handle handle, const char *axis_id, double *vector1, double *vector2, double *vector3) { /* Read from the axis category */ cbf_failnez (cbf_find_category (handle, "axis")) cbf_failnez (cbf_find_column (handle, "id")) cbf_failnez (cbf_find_row (handle, axis_id)) cbf_failnez (cbf_find_column (handle, "vector[1]")) cbf_failnez (cbf_get_doublevalue (handle, vector1)) cbf_failnez (cbf_find_column (handle, "vector[2]")) cbf_failnez (cbf_get_doublevalue (handle, vector2)) cbf_failnez (cbf_find_column (handle, "vector[3]")) cbf_failnez (cbf_get_doublevalue (handle, vector3)) return 0; } /* Get an axis offset */ int cbf_get_axis_offset (cbf_handle handle, const char *axis_id, double *offset1, double *offset2, double *offset3) { /* Read from the axis category */ cbf_failnez (cbf_find_category (handle, "axis")) cbf_failnez (cbf_find_column (handle, "id")) cbf_failnez (cbf_find_row (handle, axis_id)) cbf_failnez (cbf_find_column (handle, "offset[1]")) cbf_failnez (cbf_get_doublevalue (handle, offset1)) cbf_failnez (cbf_find_column (handle, "offset[2]")) cbf_failnez (cbf_get_doublevalue (handle, offset2)) cbf_failnez (cbf_find_column (handle, "offset[3]")) cbf_failnez (cbf_get_doublevalue (handle, offset3)) return 0; } /* Get the setting of an axis */ int cbf_get_axis_setting (cbf_handle handle, unsigned int reserved, const char *axis_id, double *start, double *increment) { cbf_axis_type type; if (reserved != 0) return CBF_ARGUMENT; /* Get the axis type */ cbf_failnez (cbf_get_axis_type (handle, axis_id, &type)) if (type != CBF_TRANSLATION_AXIS && type != CBF_ROTATION_AXIS) return CBF_FORMAT; /* Read from the diffrn_scan_axis and diffrn_scan_frame_axis categories */ if (type == CBF_TRANSLATION_AXIS) { cbf_failnez (cbf_find_category (handle, "diffrn_scan_frame_axis")) cbf_failnez (cbf_find_column (handle, "axis_id")) cbf_failnez (cbf_find_row (handle, axis_id)) cbf_failnez (cbf_find_column (handle, "displacement")) cbf_failnez (cbf_get_doublevalue (handle, start)) cbf_failnez (cbf_find_category (handle, "diffrn_scan_axis")) cbf_failnez (cbf_find_column (handle, "axis_id")) cbf_failnez (cbf_find_row (handle, axis_id)) cbf_failnez (cbf_find_column (handle, "displacement_increment")) cbf_failnez (cbf_get_doublevalue (handle, increment)) } else { cbf_failnez (cbf_find_category (handle, "diffrn_scan_frame_axis")) cbf_failnez (cbf_find_column (handle, "axis_id")) cbf_failnez (cbf_find_row (handle, axis_id)) cbf_failnez (cbf_find_column (handle, "angle")) cbf_failnez (cbf_get_doublevalue (handle, start)) cbf_failnez (cbf_find_category (handle, "diffrn_scan_axis")) cbf_failnez (cbf_find_column (handle, "axis_id")) cbf_failnez (cbf_find_row (handle, axis_id)) cbf_failnez (cbf_find_column (handle, "angle_increment")) cbf_failnez (cbf_get_doublevalue (handle, increment)) } return 0; } /* Get the reference setting of an axis */ int cbf_get_axis_reference_setting (cbf_handle handle, unsigned int reserved, const char *axis_id, double *refsetting) { cbf_axis_type type; if (reserved != 0) return CBF_ARGUMENT; /* Get the axis type */ cbf_failnez (cbf_get_axis_type (handle, axis_id, &type)) if (type != CBF_TRANSLATION_AXIS && type != CBF_ROTATION_AXIS) return CBF_FORMAT; /* Read from the diffrn_scan_axis and diffrn_scan_frame_axis categories */ if (type == CBF_TRANSLATION_AXIS) { cbf_failnez (cbf_find_category (handle, "diffrn_scan_frame_axis")) cbf_failnez (cbf_find_column (handle, "axis_id")) cbf_failnez (cbf_find_row (handle, axis_id)) *refsetting = 0.; if (!cbf_find_column (handle, "reference_displacement")) { if (cbf_get_doublevalue (handle, refsetting)) { if (!cbf_find_column (handle, "displacement")) { if (cbf_get_doublevalue (handle, refsetting)) { *refsetting = 0.; } } } } else { if (!cbf_find_column (handle, "displacement")) { if (cbf_get_doublevalue (handle, refsetting)) { *refsetting = 0.; } } else { cbf_failnez (cbf_find_category (handle, "diffrn_scan_axis")) cbf_failnez (cbf_find_column (handle, "axis_id")) cbf_failnez (cbf_find_row (handle, axis_id)) if (!cbf_find_column (handle, "reference_displacement")) { if (cbf_get_doublevalue (handle, refsetting)) { if (!cbf_find_column (handle, "displacement")) { if (cbf_get_doublevalue (handle, refsetting)) { *refsetting = 0.; } } } } else { if (!cbf_find_column (handle, "displacement")) { if (cbf_get_doublevalue (handle, refsetting)) { *refsetting = 0.; } } } } } } else { cbf_failnez (cbf_find_category (handle, "diffrn_scan_frame_axis")) cbf_failnez (cbf_find_column (handle, "axis_id")) cbf_failnez (cbf_find_row (handle, axis_id)) *refsetting = 0.; if (!cbf_find_column (handle, "reference_angle")) { if (cbf_get_doublevalue (handle, refsetting)) { *refsetting = 0.; } } else { cbf_failnez (cbf_find_category (handle, "diffrn_scan_axis")) cbf_failnez (cbf_find_column (handle, "axis_id")) cbf_failnez (cbf_find_row (handle, axis_id)) if (!cbf_find_column (handle, "reference_angle")) { if (cbf_get_doublevalue (handle, refsetting)) { *refsetting = 0.; } } } } return 0; } /* Change the setting of an axis */ int cbf_set_axis_setting (cbf_handle handle, unsigned int reserved, const char *axis_id, double start, double increment) { cbf_axis_type type; if (reserved != 0) return CBF_ARGUMENT; /* Get the axis type */ cbf_failnez (cbf_get_axis_type (handle, axis_id, &type)) if (type != CBF_TRANSLATION_AXIS && type != CBF_ROTATION_AXIS) return CBF_FORMAT; /* Update the diffrn_scan_axis and diffrn_scan_frame_axis categories */ if (type == CBF_TRANSLATION_AXIS) { cbf_failnez (cbf_require_category (handle, "diffrn_scan_frame_axis")) cbf_failnez (cbf_require_column (handle, "axis_id")) cbf_failnez (cbf_require_row (handle, axis_id)) cbf_failnez (cbf_require_column (handle, "displacement")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", start)) if (!cbf_find_column( handle, "displacement_increment")) { cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", increment)) } cbf_failnez (cbf_require_category (handle, "diffrn_scan_axis")) cbf_failnez (cbf_require_column (handle, "axis_id")) cbf_failnez (cbf_require_row (handle, axis_id)) cbf_failnez (cbf_require_column (handle, "displacement_start")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", start)) cbf_failnez (cbf_require_column (handle, "displacement_increment")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", increment)) cbf_failnez (cbf_require_column (handle, "displacement_range")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", increment)) } else { cbf_failnez (cbf_require_category (handle, "diffrn_scan_frame_axis")) cbf_failnez (cbf_require_column (handle, "axis_id")) cbf_failnez (cbf_require_row (handle, axis_id)) cbf_failnez (cbf_require_column (handle, "angle")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", start)) if (!cbf_find_column (handle, "angle_increment")) { cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", increment)) } cbf_failnez (cbf_require_category (handle, "diffrn_scan_axis")) cbf_failnez (cbf_require_column (handle, "axis_id")) cbf_failnez (cbf_require_row (handle, axis_id)) cbf_failnez (cbf_require_column (handle, "angle_start")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", start)) cbf_failnez (cbf_require_column (handle, "angle_increment")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", increment)) cbf_failnez (cbf_require_column (handle, "angle_range")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", increment)) } return 0; } /* Change the reference setting of an axis */ int cbf_set_axis_reference_setting (cbf_handle handle, unsigned int reserved, const char *axis_id, double refsetting) { cbf_axis_type type; if (reserved != 0) return CBF_ARGUMENT; /* Get the axis type */ cbf_failnez (cbf_get_axis_type (handle, axis_id, &type)) if (type != CBF_TRANSLATION_AXIS && type != CBF_ROTATION_AXIS) return CBF_FORMAT; /* Update the diffrn_scan_axis and diffrn_scan_frame_axis categories */ if (type == CBF_TRANSLATION_AXIS) { cbf_failnez (cbf_require_category (handle, "diffrn_scan_frame_axis")) cbf_failnez (cbf_require_column (handle, "axis_id")) cbf_failnez (cbf_require_row (handle, axis_id)) cbf_failnez (cbf_require_column (handle, "reference_displacement")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", refsetting)) cbf_failnez (cbf_require_category (handle, "diffrn_scan_axis")) cbf_failnez (cbf_require_column (handle, "axis_id")) cbf_failnez (cbf_require_row (handle, axis_id)) cbf_failnez (cbf_require_column (handle, "reference_displacement")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", refsetting)) } else { cbf_failnez (cbf_require_category (handle, "diffrn_scan_frame_axis")) cbf_failnez (cbf_require_column (handle, "axis_id")) cbf_failnez (cbf_require_row (handle, axis_id)) cbf_failnez (cbf_require_column (handle, "reference_angle")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", refsetting)) cbf_failnez (cbf_require_category (handle, "diffrn_scan_axis")) cbf_failnez (cbf_require_column (handle, "axis_id")) cbf_failnez (cbf_require_row (handle, axis_id)) cbf_failnez (cbf_require_column (handle, "reference_angle")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", refsetting)) } return 0; } /* Create a positioner */ int cbf_make_positioner (cbf_positioner *positioner) { cbf_failnez (cbf_alloc ((void **) positioner, NULL, sizeof (cbf_positioner_struct), 1)) (*positioner)->matrix [0][0] = 1; (*positioner)->matrix [0][1] = 0; (*positioner)->matrix [0][2] = 0; (*positioner)->matrix [0][3] = 0; (*positioner)->matrix [1][0] = 0; (*positioner)->matrix [1][1] = 1; (*positioner)->matrix [1][2] = 0; (*positioner)->matrix [1][3] = 0; (*positioner)->matrix [2][0] = 0; (*positioner)->matrix [2][1] = 0; (*positioner)->matrix [2][2] = 1; (*positioner)->matrix [2][3] = 0; (*positioner)->axis = NULL; (*positioner)->axes = 0; (*positioner)->matrix_is_valid = 1; (*positioner)->axes_are_connected = 1; return 0; } /* Free a positioner */ int cbf_free_positioner (cbf_positioner positioner) { int errorcode; void *memblock; void *vaxis; void *vname; void *adon; size_t i; memblock = (void *) positioner; if (positioner) { errorcode = 0; for (i = 0; i < positioner->axes; i++) { vname = (void *)(positioner->axis [i].name); errorcode |= cbf_free ((void **) &vname, NULL); positioner->axis [i].name = NULL; if (positioner->axis [i].depends_on) { adon = (void *)(positioner->axis [i].depends_on); errorcode |= cbf_free ((void **) &adon, NULL); positioner->axis [i].depends_on = NULL; } } vaxis = (void *)positioner->axis; errorcode |= cbf_free ((void **) &vaxis, &positioner->axes); positioner->axis = NULL; return errorcode | cbf_free (&memblock, NULL); } return 0; } /* Add a positioner axis */ int cbf_add_positioner_axis (cbf_positioner positioner, const char *name, const char *depends_on, cbf_axis_type type, double vector1, double vector2, double vector3, double offset1, double offset2, double offset3, double start, double increment) { int errorcode = 0; cbf_axis_struct axis; void *vaxis; void *vname; double length; /* Check the arguments */ if (!name || !positioner || (type != CBF_TRANSLATION_AXIS && type != CBF_ROTATION_AXIS)) return CBF_ARGUMENT; length = vector1 * vector1 + vector2 * vector2 + vector3 * vector3; if (length <= 0.0) return CBF_ARGUMENT; /* Allocate memory and copy the axis names */ axis.name = NULL; axis.name = (char *)cbf_copy_string(NULL,name,0); axis.depends_on = NULL; if (depends_on) { axis.depends_on = (char *)cbf_copy_string(NULL,depends_on,0); } if (errorcode) { vname = (void *)axis.name; errorcode |= cbf_free (&vname, NULL); axis.name = NULL; return errorcode; } vaxis = (void *)(positioner->axis); errorcode = cbf_realloc ((void **) &vaxis, &(positioner->axes), sizeof (cbf_axis_struct), positioner->axes + 1); positioner->axis = (cbf_axis_struct *)vaxis; if (errorcode) { int nerrorcode; void * vdepends_on; vname = (void *)axis.name; vdepends_on = (void *)axis.depends_on; nerrorcode = cbf_free (&vname, NULL) | cbf_free (&vdepends_on, NULL); axis.name = NULL; axis.depends_on = NULL; return nerrorcode; } length = sqrt (length); axis.type = type; axis.vector [0] = vector1 / length; axis.vector [1] = vector2 / length; axis.vector [2] = vector3 / length; axis.offset [0] = offset1; axis.offset [1] = offset2; axis.offset [2] = offset3; axis.start = start; axis.increment = increment; axis.setting = 0; positioner->axis [positioner->axes - 1] = axis; positioner->matrix_is_valid = 0; positioner->axes_are_connected = 0; return 0; } /* Add a goniometer axis from a file */ int cbf_read_positioner_axis (cbf_handle handle, unsigned int reserved, cbf_positioner positioner, const char *axis_id, int read_setting) { const char *next_id; cbf_axis_type axis_type; double vector1, vector2, vector3, offset1, offset2, offset3; double start, increment; cbf_failnez (cbf_find_category (handle, "axis")) cbf_failnez (cbf_find_column (handle, "id")) cbf_failnez (cbf_find_row (handle, axis_id)) cbf_failnez (cbf_find_column (handle, "depends_on")) cbf_failnez (cbf_get_value (handle, &next_id)) cbf_failnez (cbf_get_axis_type (handle, axis_id, &axis_type)) cbf_failnez (cbf_get_axis_vector (handle, axis_id, &vector1, &vector2, &vector3)) cbf_failnez (cbf_get_axis_offset (handle, axis_id, &offset1, &offset2, &offset3)) start = increment = 0; if (read_setting) { cbf_failnez (cbf_get_axis_setting (handle, reserved, axis_id, &start, &increment)) if (read_setting < 0) { cbf_failnez (cbf_get_axis_reference_setting (handle, reserved, axis_id, &start)) } } cbf_failnez (cbf_add_positioner_axis (positioner, axis_id, next_id, axis_type, vector1, vector2, vector3, offset1, offset2, offset3, start, increment)) return 0; } /* Connect a set of positioner axes */ int cbf_connect_axes (cbf_positioner positioner) { if (!positioner) return CBF_ARGUMENT; if (!positioner->axes_are_connected) { /* Arrange the axes in order of their connection */ cbf_axis_struct axis; const char *depends_on = "."; int dest, search, found; for (dest = ((int) positioner->axes) - 1; dest >= 0; dest--) { for (search = 0; search <= dest; search++) { if (positioner->axis [search].depends_on) found = cbf_cistrcmp (positioner->axis [search].depends_on, depends_on) == 0; else found = cbf_cistrcmp (".", depends_on) == 0; if (found) { depends_on = positioner->axis [search].name; if (dest != search) { axis = positioner->axis [dest]; positioner->axis [dest] = positioner->axis [search]; positioner->axis [search] = axis; } if (!depends_on && dest > 0) return CBF_NOTFOUND; break; } } if (search > dest) return CBF_NOTFOUND; } positioner->axes_are_connected = 1; } return 0; } /* Calculate a position given initial coordinates */ int cbf_calculate_position (cbf_positioner positioner, unsigned int reserved, double ratio, double initial1, double initial2, double initial3, double *final1, double *final2, double *final3) { size_t i; double setting; if (!positioner) return CBF_ARGUMENT; if (reserved != 0) return CBF_ARGUMENT; for (i = 0; i < positioner->axes; i++) { setting = positioner->axis [i].start + ratio * positioner->axis [i].increment; if (positioner->axis [i].setting != setting) { positioner->matrix_is_valid = 0; positioner->axis [i].setting = setting; } } if (!positioner->matrix_is_valid) { positioner->matrix [0][0] = 1; positioner->matrix [0][1] = 0; positioner->matrix [0][2] = 0; positioner->matrix [0][3] = 0; positioner->matrix [1][0] = 0; positioner->matrix [1][1] = 1; positioner->matrix [1][2] = 0; positioner->matrix [1][3] = 0; positioner->matrix [2][0] = 0; positioner->matrix [2][1] = 0; positioner->matrix [2][2] = 1; positioner->matrix [2][3] = 0; if (!positioner->axes_are_connected) cbf_failnez (cbf_connect_axes (positioner)) for (i = 0; i < positioner->axes; i++) { setting = positioner->axis [i].setting; if (positioner->axis [i].type == CBF_TRANSLATION_AXIS) { positioner->matrix [0][3] += setting * positioner->axis [i].vector [0]; positioner->matrix [1][3] += setting * positioner->axis [i].vector [1]; positioner->matrix [2][3] += setting * positioner->axis [i].vector [2]; /* fprintf(stderr," calculate position, axis %d, translate [%g, %g, %g]\n", i, setting * positioner->axis [i].vector [0], setting * positioner->axis [i].vector [1], setting * positioner->axis [i].vector [2]); */ } else { double s, x, y, z, w, xx, yy, zz, xy, xz, xw, yz, yw, zw; double rotation [3][3], product [3][4]; int r1, c1r2, c2; s = sin (setting * 0.00872664625997164788461845384244); x = positioner->axis [i].vector [0] * s; y = positioner->axis [i].vector [1] * s; z = positioner->axis [i].vector [2] * s; w = cos (setting * 0.00872664625997164788461845384244); xx = x * x; yy = y * y; zz = z * z; xy = x * y; xz = x * z; xw = x * w; yz = y * z; yw = y * w; zw = z * w; rotation [0][0] = 1 - 2 * (yy + zz); rotation [0][1] = 2 * (xy - zw); rotation [0][2] = 2 * (xz + yw); rotation [1][0] = 2 * (xy + zw); rotation [1][1] = 1 - 2 * (xx + zz); rotation [1][2] = 2 * (yz - xw); rotation [2][0] = 2 * (xz - yw); rotation [2][1] = 2 * (yz + xw); rotation [2][2] = 1 - 2 * (xx + yy); /* fprintf(stderr," calculate position, axis %d, rotate [%g + i*%g + j*%g + k*%g]\n", i, w, x, y, z); */ for (r1 = 0; r1 < 3; r1++) for (c2 = 0; c2 < 4; c2++) { product [r1][c2] = 0; for (c1r2 = 0; c1r2 < 3; c1r2++) product [r1][c2] += rotation [r1][c1r2] * positioner->matrix [c1r2][c2]; } for (r1 = 0; r1 < 3; r1++) for (c2 = 0; c2 < 4; c2++) positioner->matrix [r1][c2] = product [r1][c2]; } positioner->matrix [0][3] += positioner->axis [i].offset [0]; positioner->matrix [1][3] += positioner->axis [i].offset [1]; positioner->matrix [2][3] += positioner->axis [i].offset [2]; } positioner->matrix_is_valid = 1; } /* fprintf(stderr," Overall matrix [[%g %g %g]] + %g\n" " [[%g %g %g]] + %g\n" " [[%g %g %g]] + %g\n", positioner->matrix [0][0], positioner->matrix [0][1], positioner->matrix [0][2], positioner->matrix [0][3], positioner->matrix [1][0], positioner->matrix [1][1], positioner->matrix [1][2], positioner->matrix [1][3], positioner->matrix [2][0], positioner->matrix [2][1], positioner->matrix [2][2], positioner->matrix [2][3]); */ if (final1) *final1 = positioner->matrix [0][0] * initial1 + positioner->matrix [0][1] * initial2 + positioner->matrix [0][2] * initial3 + positioner->matrix [0][3]; if (final2) *final2 = positioner->matrix [1][0] * initial1 + positioner->matrix [1][1] * initial2 + positioner->matrix [1][2] * initial3 + positioner->matrix [1][3]; if (final3) *final3 = positioner->matrix [2][0] * initial1 + positioner->matrix [2][1] * initial2 + positioner->matrix [2][2] * initial3 + positioner->matrix [2][3]; return 0; } /* Calculate the initial position given final coordinates */ int cbf_calculate_initial_position (cbf_positioner positioner, unsigned int reserved, double ratio, double final1, double final2, double final3, double *initial1, double *initial2, double *initial3) { double delta [3]; if (reserved != 0) return CBF_ARGUMENT; /* Update the matrix */ cbf_failnez (cbf_calculate_position (positioner, reserved, ratio, 0, 0, 0, NULL, NULL, NULL)) delta [0] = final1 - positioner->matrix [0][3]; delta [1] = final2 - positioner->matrix [1][3]; delta [2] = final3 - positioner->matrix [2][3]; if (initial1) *initial1 = positioner->matrix [0][0] * delta [0] + positioner->matrix [1][0] * delta [1] + positioner->matrix [2][0] * delta [2]; if (initial2) *initial2 = positioner->matrix [0][1] * delta [0] + positioner->matrix [1][1] * delta [1] + positioner->matrix [2][1] * delta [2]; if (initial3) *initial3 = positioner->matrix [0][2] * delta [0] + positioner->matrix [1][2] * delta [1] + positioner->matrix [2][2] * delta [2]; return 0; } /* Construct a goniometer */ int cbf_construct_goniometer (cbf_handle handle, cbf_goniometer *goniometer) { const char *diffrn_id, *id, *this_id, *axis_id; unsigned int row; int errorcode; if (!goniometer) return CBF_ARGUMENT; /* Get the measurement id */ cbf_failnez (cbf_get_diffrn_id (handle, &diffrn_id)) cbf_failnez (cbf_find_category (handle, "diffrn_measurement")) cbf_failnez (cbf_find_column (handle, "diffrn_id")) cbf_failnez (cbf_find_row (handle, diffrn_id)) cbf_failnez (cbf_find_column (handle, "id")) cbf_failnez (cbf_get_value (handle, &id)) /* Construct the goniometer */ cbf_failnez (cbf_make_positioner (goniometer)) for (row = errorcode = 0; !errorcode; row++) { errorcode = cbf_find_category (handle, "diffrn_measurement_axis"); if (!errorcode) { /* allow for aliases _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.id (deprecated) */ errorcode = cbf_find_column (handle, "measurement_id"); if (errorcode) errorcode = cbf_find_column (handle, "id"); } if (!errorcode) { errorcode = cbf_select_row (handle, row); if (errorcode == CBF_NOTFOUND) { errorcode = 0; break; } } if (!errorcode) errorcode = cbf_get_value (handle, &this_id); if (!errorcode) if (cbf_cistrcmp (id, this_id) == 0) { errorcode = cbf_find_column (handle, "axis_id"); if (!errorcode) errorcode = cbf_get_value (handle, &axis_id); if (!errorcode) errorcode = cbf_read_positioner_axis (handle, 0, /* reserved */ *goniometer, axis_id, 1); } } if (!errorcode) errorcode = cbf_connect_axes (*goniometer); if (errorcode) { errorcode |= cbf_free_positioner (*goniometer); *goniometer = NULL; } return errorcode; } /* Free a goniometer */ int cbf_free_goniometer (cbf_goniometer goniometer) { return cbf_free_positioner (goniometer); } /* Get the rotation axis */ int cbf_get_rotation_axis (cbf_goniometer goniometer, unsigned int reserved, double *vector1, double *vector2, double *vector3) { size_t axis; if (!goniometer) return CBF_ARGUMENT; if (reserved != 0) return CBF_ARGUMENT; /* Currently just return the first rotation axis */ for (axis = 0; axis < goniometer->axes; axis++) if (goniometer->axis [axis].type == CBF_ROTATION_AXIS) if (goniometer->axis [axis].increment) { if (vector1) *vector1 = goniometer->axis [axis].vector [0]; if (vector2) *vector2 = goniometer->axis [axis].vector [1]; if (vector3) *vector3 = goniometer->axis [axis].vector [2]; return 0; } return CBF_NOTFOUND; } /* Get the rotation range */ int cbf_get_rotation_range (cbf_goniometer goniometer, unsigned int reserved, double *start, double *increment) { size_t axis; if (!goniometer) return CBF_ARGUMENT; if (reserved != 0) return CBF_ARGUMENT; /* Currently just return the range of the first rotation axis */ for (axis = 0; axis < goniometer->axes; axis++) if (goniometer->axis [axis].type == CBF_ROTATION_AXIS) if (goniometer->axis [axis].increment) { if (start) *start = goniometer->axis [axis].start; if (increment) *increment = goniometer->axis [axis].increment; return 0; } return CBF_NOTFOUND; } /* Reorient a vector */ int cbf_rotate_vector (cbf_goniometer goniometer, unsigned int reserved, double ratio, double initial1, double initial2, double initial3, double *final1, double *final2, double *final3) { double transformed [3], origin [3]; if (reserved != 0) return CBF_ARGUMENT; cbf_failnez (cbf_calculate_position (goniometer, reserved, ratio, 0, 0, 0, &origin [0], &origin [1], &origin [2])) cbf_failnez (cbf_calculate_position (goniometer, reserved, ratio, initial1, initial2, initial3, &transformed [0], &transformed [1], &transformed [2])) if (final1) *final1 = transformed [0] - origin [0]; if (final2) *final2 = transformed [1] - origin [1]; if (final3) *final3 = transformed [2] - origin [2]; return 0; } /* Convert a vector to reciprocal space (assumes beam along -z) */ int cbf_get_reciprocal (cbf_goniometer goniometer, unsigned int reserved, double ratio, double wavelength, double real1, double real2, double real3, double *reciprocal1, double *reciprocal2, double *reciprocal3) { double length, ewald [3]; if (reserved != 0) return CBF_ARGUMENT; if (wavelength <= 0.0) return CBF_ARGUMENT; length = real1 * real1 + real2 * real2 + real3 * real3; if (length <= 0.0) return CBF_ARGUMENT; /* Project the vector onto the sphere */ length = sqrt (length) * wavelength; ewald [0] = real1 / length; ewald [1] = real2 / length; ewald [2] = real3 / length + 1 / wavelength; /* Rotate the vector back to the 0 position of the goniometer */ cbf_failnez (cbf_calculate_initial_position (goniometer, reserved, ratio, ewald [0], ewald [1], ewald [2], reciprocal1, reciprocal2, reciprocal3)) return 0; } /* Construct a detector positioner */ int cbf_construct_detector (cbf_handle handle, cbf_detector *detector, unsigned int element_number) { int errorcode, precedence; unsigned int row, axis; const char *diffrn_id, *id, *this_id, *axis_id, *array_id; const char *surface_axis [2]; /* fast, slow */ double displacement [2], increment [2]; cbf_positioner positioner; if (!detector) return CBF_ARGUMENT; /* Get the detector id */ cbf_failnez (cbf_get_diffrn_id (handle, &diffrn_id)) cbf_failnez (cbf_find_category (handle, "diffrn_detector")) cbf_failnez (cbf_find_column (handle, "diffrn_id")) cbf_failnez (cbf_find_row (handle, diffrn_id)) cbf_failnez (cbf_find_column (handle, "id")) cbf_failnez (cbf_get_value (handle, &id)) /* Construct the detector surface */ cbf_failnez (cbf_get_array_id (handle, element_number, &array_id)) cbf_failnez (cbf_find_category (handle, "array_structure_list")) cbf_failnez (cbf_find_column (handle, "array_id")) surface_axis [0] = surface_axis [1] = NULL; while (cbf_find_nextrow (handle, array_id) == 0) { cbf_failnez (cbf_find_column (handle, "precedence")) cbf_failnez (cbf_get_integervalue (handle, &precedence)) if (precedence < 1 || precedence > 2) return CBF_FORMAT; if (surface_axis [precedence - 1]) return CBF_FORMAT; cbf_failnez (cbf_find_column (handle, "axis_set_id")) cbf_failnez (cbf_get_value (handle, &surface_axis [precedence - 1])) cbf_failnez (cbf_find_column (handle, "array_id")) } if (!surface_axis [0]) return CBF_FORMAT; cbf_failnez (cbf_find_category (handle, "array_structure_list_axis")) cbf_failnez (cbf_find_column (handle, "axis_set_id")) cbf_failnez (cbf_find_row (handle, surface_axis [0])) cbf_failnez (cbf_find_column (handle, "axis_id")) cbf_failnez (cbf_get_value (handle, &surface_axis [0])) cbf_failnez (cbf_find_column (handle, "displacement")) cbf_failnez (cbf_get_doublevalue (handle, &displacement [0])) cbf_failnez (cbf_find_column (handle, "displacement_increment")) cbf_failnez (cbf_get_doublevalue (handle, &increment [0])) if (surface_axis [1]) { cbf_failnez (cbf_find_column (handle, "axis_set_id")) cbf_failnez (cbf_find_row (handle, surface_axis [1])) cbf_failnez (cbf_find_column (handle, "axis_id")) cbf_failnez (cbf_get_value (handle, &surface_axis [1])) cbf_failnez (cbf_find_column (handle, "displacement")) cbf_failnez (cbf_get_doublevalue (handle, &displacement [1])) cbf_failnez (cbf_find_column (handle, "displacement_increment")) cbf_failnez (cbf_get_doublevalue (handle, &increment [1])) } /* Construct the positioner */ cbf_failnez (cbf_make_positioner (&positioner)) errorcode = cbf_alloc ((void **) detector, NULL, sizeof (cbf_detector_struct), 1); for (row = errorcode = 0; !errorcode; row++) { errorcode = cbf_find_category (handle, "diffrn_detector_axis"); if (!errorcode) { /* allow for aliases _diffrn_detector_axis.detector_id _diffrn_detector_axis.id (deprecated) */ errorcode = cbf_find_column (handle, "detector_id"); if (errorcode) errorcode = cbf_find_column (handle, "id"); } if (!errorcode) { errorcode = cbf_select_row (handle, row); if (errorcode == CBF_NOTFOUND) { errorcode = 0; break; } } if (!errorcode) errorcode = cbf_get_value (handle, &this_id); if (!errorcode) if (cbf_cistrcmp (id, this_id) == 0) { errorcode = cbf_find_column (handle, "axis_id"); if (!errorcode) errorcode = cbf_get_value (handle, &axis_id); if (!errorcode) errorcode = cbf_read_positioner_axis (handle, 0, positioner, axis_id, 1); } } /* Add the surface axes */ if (!errorcode) errorcode = cbf_read_positioner_axis (handle, 0, positioner, surface_axis [0], 0); if (!errorcode && surface_axis [1]) errorcode = cbf_read_positioner_axis (handle, 0, positioner, surface_axis [1], 0); /* Connect the axes */ if (!errorcode) errorcode = cbf_connect_axes (positioner); if (errorcode) { errorcode |= cbf_free_positioner (positioner); return errorcode | cbf_free ((void **) detector, NULL); } /* Insert the cbf handle and element into the dectector */ (*detector)->handle = handle; (*detector)->element = element_number; /* Copy the start and increment values into the surface axes */ (*detector)->displacement [0] = displacement [0]; (*detector)->displacement [1] = displacement [1]; (*detector)->increment [0] = increment [0]; (*detector)->increment [1] = increment [1]; if (surface_axis [1]) (*detector)->axes = 2; else (*detector)->axes = 1; for (axis = 0; axis < (*detector)->axes; axis++) for (row = 0; row < positioner->axes; row++) if (cbf_cistrcmp (positioner->axis [row].name, surface_axis [axis]) == 0) { (*detector)->index [axis] = row; positioner->axis [row].increment = 0; break; } (*detector)->positioner = positioner; return 0; } /* Construct a detector positioner, creating the necessary categories, and columns */ int cbf_require_detector (cbf_handle handle, cbf_detector *detector, unsigned int element_number) { int errorcode, precedence; unsigned int row, axis; const char *diffrn_id, *id, *this_id, *axis_id, *array_id; const char *surface_axis [2]; double displacement [2], increment [2]; cbf_positioner positioner; if (!detector) return CBF_ARGUMENT; /* Get the detector id */ cbf_failnez (cbf_require_diffrn_id (handle, &diffrn_id, "DIFFRN_ID")) cbf_failnez (cbf_require_category (handle, "diffrn_detector")) cbf_failnez (cbf_require_column (handle, "diffrn_id")) if (cbf_find_row (handle, diffrn_id)) { cbf_failnez(cbf_new_row(handle)) cbf_failnez(cbf_set_value(handle,diffrn_id)) } cbf_failnez (cbf_require_column (handle, "id")) cbf_failnez (cbf_require_value (handle, &id, diffrn_id)) /* Construct the detector surface */ cbf_failnez (cbf_get_array_id (handle, element_number, &array_id)) cbf_failnez (cbf_require_category (handle, "array_structure_list")) cbf_failnez (cbf_require_column (handle, "array_id")) surface_axis [0] = surface_axis [1] = NULL; while (cbf_find_nextrow (handle, array_id) == 0) { cbf_failnez (cbf_find_column (handle, "precedence")) cbf_failnez (cbf_get_integervalue (handle, &precedence)) if (precedence < 1 || precedence > 2) return CBF_FORMAT; if (surface_axis [precedence - 1]) return CBF_FORMAT; cbf_failnez (cbf_find_column (handle, "axis_set_id")) cbf_failnez (cbf_get_value (handle, &surface_axis [precedence - 1])) cbf_failnez (cbf_find_column (handle, "array_id")) } if (!surface_axis[0]) { cbf_failnez (cbf_require_column (handle, "array_id")) cbf_failnez (cbf_new_row (handle)) cbf_failnez (cbf_set_value (handle, array_id)) cbf_failnez (cbf_require_column (handle, "precedence")) cbf_failnez (cbf_set_integervalue(handle,1)) cbf_failnez (cbf_require_column (handle, "axis_set_id")) cbf_failnez (cbf_require_value (handle, &surface_axis [0], "ELEMENT_X")) } if (!surface_axis[1]) { cbf_failnez (cbf_require_column (handle,"array_id")) cbf_failnez (cbf_new_row (handle)) cbf_failnez (cbf_set_value (handle, array_id)) cbf_failnez (cbf_require_column (handle, "precedence")) cbf_failnez (cbf_set_integervalue(handle,2)) cbf_failnez (cbf_require_column (handle, "axis_set_id")) cbf_failnez (cbf_require_value (handle, &surface_axis [1], "ELEMENT_Y")) } if (!surface_axis [0]) return CBF_FORMAT; cbf_failnez (cbf_require_category (handle, "array_structure_list_axis")) cbf_failnez (cbf_require_column (handle, "axis_set_id")) cbf_failnez (cbf_require_row (handle, surface_axis [0])) cbf_failnez (cbf_require_column (handle, "axis_id")) cbf_failnez (cbf_require_value (handle, &surface_axis [0], surface_axis[0])) cbf_failnez (cbf_require_column (handle, "displacement")) cbf_failnez (cbf_require_doublevalue(handle, &displacement [0], 0.0)) cbf_failnez (cbf_require_column (handle, "displacement_increment")) cbf_failnez (cbf_require_doublevalue(handle, &(increment [0]), 0.0)) if (surface_axis [1]) { cbf_failnez (cbf_require_column (handle, "axis_set_id")) cbf_failnez (cbf_require_row (handle, surface_axis [1])) cbf_failnez (cbf_require_column (handle, "axis_id")) cbf_failnez (cbf_require_value (handle, &surface_axis [1], surface_axis[1])) cbf_failnez (cbf_require_column (handle, "displacement")) cbf_failnez (cbf_require_doublevalue(handle, &displacement [1], 0.0)) cbf_failnez (cbf_require_column (handle, "displacement_increment")) cbf_failnez (cbf_require_doublevalue(handle, &(increment [1]), 0.0)) } /* Construct the positioner */ cbf_failnez (cbf_make_positioner (&positioner)) errorcode = cbf_alloc ((void **) detector, NULL, sizeof (cbf_detector_struct), 1); for (row = errorcode = 0; !errorcode; row++) { errorcode = cbf_require_category (handle, "diffrn_detector_axis"); if (!errorcode) { /* allow for aliases _diffrn_detector_axis.detector_id _diffrn_detector_axis.id (deprecated) */ errorcode = cbf_find_column (handle, "detector_id"); if (errorcode) errorcode = cbf_find_column (handle, "id"); if (errorcode) errorcode = cbf_require_column (handle, "detector_id"); } if (!errorcode) { errorcode = cbf_select_row (handle, row); if (errorcode == CBF_NOTFOUND) { errorcode = 0; break; } } if (!errorcode) errorcode = cbf_get_value (handle, &this_id); if (!errorcode) if (cbf_cistrcmp (id, this_id) == 0) { errorcode = cbf_find_column (handle, "axis_id"); if (!errorcode) errorcode = cbf_get_value (handle, &axis_id); if (!errorcode) errorcode = cbf_read_positioner_axis (handle, 0, positioner, axis_id, 1); } } /* Add the surface axes */ if (!errorcode) errorcode = cbf_read_positioner_axis (handle, 0, positioner, surface_axis [0], 0); if (!errorcode && surface_axis [1]) errorcode = cbf_read_positioner_axis (handle, 0, positioner, surface_axis [1], 0); /* Connect the axes */ if (!errorcode) errorcode = cbf_connect_axes (positioner); if (errorcode) { errorcode |= cbf_free_positioner (positioner); return errorcode | cbf_free ((void **) detector, NULL); } /* Insert the cbf handle and element into the dectector */ (*detector)->handle = handle; (*detector)->element = element_number; /* Copy the start and increment values into the surface axes */ (*detector)->displacement [0] = displacement [0]; (*detector)->displacement [1] = displacement [1]; (*detector)->increment [0] = increment [0]; (*detector)->increment [1] = increment [1]; if (surface_axis [1]) (*detector)->axes = 2; else (*detector)->axes = 1; for (axis = 0; axis < (*detector)->axes; axis++) for (row = 0; row < positioner->axes; row++) if (cbf_cistrcmp (positioner->axis [row].name, surface_axis [axis]) == 0) { (*detector)->index [axis] = row; positioner->axis [row].increment = 0; break; } (*detector)->positioner = positioner; return 0; } /* Construct a reference detector positioner */ int cbf_construct_reference_detector (cbf_handle handle, cbf_detector *detector, unsigned int element_number) { int errorcode, precedence; unsigned int row, axis; const char *diffrn_id, *id, *this_id, *axis_id, *array_id; const char *surface_axis [2]; double displacement [2], increment [2]; cbf_positioner positioner; if (!detector) return CBF_ARGUMENT; /* Get the detector id */ cbf_failnez (cbf_get_diffrn_id (handle, &diffrn_id)) cbf_failnez (cbf_find_category (handle, "diffrn_detector")) cbf_failnez (cbf_find_column (handle, "diffrn_id")) cbf_failnez (cbf_find_row (handle, diffrn_id)) cbf_failnez (cbf_find_column (handle, "id")) cbf_failnez (cbf_get_value (handle, &id)) /* Construct the detector surface */ cbf_failnez (cbf_get_array_id (handle, element_number, &array_id)) cbf_failnez (cbf_find_category (handle, "array_structure_list")) cbf_failnez (cbf_find_column (handle, "array_id")) surface_axis [0] = surface_axis [1] = NULL; while (cbf_find_nextrow (handle, array_id) == 0) { cbf_failnez (cbf_find_column (handle, "precedence")) cbf_failnez (cbf_get_integervalue (handle, &precedence)) if (precedence < 1 || precedence > 2) return CBF_FORMAT; if (surface_axis [precedence - 1]) return CBF_FORMAT; cbf_failnez (cbf_find_column (handle, "axis_set_id")) cbf_failnez (cbf_get_value (handle, &surface_axis [precedence - 1])) cbf_failnez (cbf_find_column (handle, "array_id")) } if (!surface_axis [0]) return CBF_FORMAT; cbf_failnez (cbf_find_category (handle, "array_structure_list_axis")) cbf_failnez (cbf_find_column (handle, "axis_set_id")) cbf_failnez (cbf_find_row (handle, surface_axis [0])) cbf_failnez (cbf_find_column (handle, "axis_id")) cbf_failnez (cbf_get_value (handle, &surface_axis [0])) if (cbf_find_column(handle,"reference_displacement")) { cbf_failnez(cbf_find_column(handle,"displacement")) } cbf_failnez (cbf_get_doublevalue (handle, &displacement [0])) cbf_failnez (cbf_get_doublevalue (handle, &displacement [0])) cbf_failnez (cbf_find_column (handle, "displacement_increment")) cbf_failnez (cbf_get_doublevalue (handle, &increment [0])) if (surface_axis [1]) { cbf_failnez (cbf_find_column (handle, "axis_set_id")) cbf_failnez (cbf_find_row (handle, surface_axis [1])) cbf_failnez (cbf_find_column (handle, "axis_id")) cbf_failnez (cbf_get_value (handle, &surface_axis [1])) if (cbf_find_column(handle,"reference_displacement")) { cbf_failnez(cbf_find_column(handle,"displacement")) } cbf_failnez (cbf_get_doublevalue (handle, &displacement [1])) cbf_failnez (cbf_find_column (handle, "displacement_increment")) cbf_failnez (cbf_get_doublevalue (handle, &increment [1])) } /* Construct the positioner */ cbf_failnez (cbf_make_positioner (&positioner)) errorcode = cbf_alloc ((void **) detector, NULL, sizeof (cbf_detector_struct), 1); for (row = errorcode = 0; !errorcode; row++) { errorcode = cbf_find_category (handle, "diffrn_detector_axis"); if (!errorcode) { /* allow for aliases _diffrn_detector_axis.detector_id _diffrn_detector_axis.id (deprecated) */ errorcode = cbf_find_column (handle, "detector_id"); if (errorcode) errorcode = cbf_find_column (handle, "id"); } if (!errorcode) { errorcode = cbf_select_row (handle, row); if (errorcode == CBF_NOTFOUND) { errorcode = 0; break; } } if (!errorcode) errorcode = cbf_get_value (handle, &this_id); if (!errorcode) if (cbf_cistrcmp (id, this_id) == 0) { errorcode = cbf_find_column (handle, "axis_id"); if (!errorcode) errorcode = cbf_get_value (handle, &axis_id); if (!errorcode) errorcode = cbf_read_positioner_axis (handle, 0, positioner, axis_id, -1); } } /* Add the surface axes */ if (!errorcode) errorcode = cbf_read_positioner_axis (handle, 0, positioner, surface_axis [0], 0); if (!errorcode && surface_axis [1]) errorcode = cbf_read_positioner_axis (handle, 0, positioner, surface_axis [1], 0); /* Connect the axes */ if (!errorcode) errorcode = cbf_connect_axes (positioner); if (errorcode) { errorcode |= cbf_free_positioner (positioner); return errorcode | cbf_free ((void **) detector, NULL); } /* Insert the cbf handle and element into the dectector */ (*detector)->handle = handle; (*detector)->element = element_number; /* Copy the start and increment values into the surface axes */ (*detector)->displacement [0] = displacement [0]; (*detector)->displacement [1] = displacement [1]; (*detector)->increment [0] = increment [0]; (*detector)->increment [1] = increment [1]; if (surface_axis [1]) (*detector)->axes = 2; else (*detector)->axes = 1; for (axis = 0; axis < (*detector)->axes; axis++) for (row = 0; row < positioner->axes; row++) if (cbf_cistrcmp (positioner->axis [row].name, surface_axis [axis]) == 0) { (*detector)->index [axis] = row; positioner->axis [row].increment = 0; break; } (*detector)->positioner = positioner; return 0; } /* Construct a reference detector positioner, creating the necessary categories, and columns */ int cbf_require_reference_detector (cbf_handle handle, cbf_detector *detector, unsigned int element_number) { int errorcode, precedence; unsigned int row, axis; const char *diffrn_id, *id, *this_id, *axis_id, *array_id; const char *surface_axis [2]; double displacement [2], increment [2]; cbf_positioner positioner; if (!detector) return CBF_ARGUMENT; /* Get the detector id */ cbf_failnez (cbf_require_diffrn_id (handle, &diffrn_id, "DIFFRN_ID")) cbf_failnez (cbf_require_category (handle, "diffrn_detector")) cbf_failnez (cbf_require_column (handle, "diffrn_id")) if (cbf_find_row (handle, diffrn_id)) { cbf_failnez(cbf_new_row(handle)) cbf_failnez(cbf_set_value(handle,diffrn_id)) } cbf_failnez (cbf_require_column (handle, "id")) cbf_failnez (cbf_require_value (handle, &id, diffrn_id)) /* Construct the detector surface */ cbf_failnez (cbf_get_array_id (handle, element_number, &array_id)) cbf_failnez (cbf_require_category (handle, "array_structure_list")) cbf_failnez (cbf_require_column (handle, "array_id")) surface_axis [0] = surface_axis [1] = NULL; while (cbf_find_nextrow (handle, array_id) == 0) { cbf_failnez (cbf_find_column (handle, "precedence")) cbf_failnez (cbf_get_integervalue (handle, &precedence)) if (precedence < 1 || precedence > 2) return CBF_FORMAT; if (surface_axis [precedence - 1]) return CBF_FORMAT; cbf_failnez (cbf_find_column (handle, "axis_set_id")) cbf_failnez (cbf_get_value (handle, &surface_axis [precedence - 1])) cbf_failnez (cbf_find_column (handle, "array_id")) } if (!surface_axis[0]) { cbf_failnez (cbf_require_column (handle, "array_id")) cbf_failnez (cbf_new_row (handle)) cbf_failnez (cbf_set_value (handle, array_id)) cbf_failnez (cbf_require_column (handle, "precedence")) cbf_failnez (cbf_set_integervalue(handle,1)) cbf_failnez (cbf_require_column (handle, "axis_set_id")) cbf_failnez (cbf_require_value (handle, &surface_axis [0], "ELEMENT_X")) } if (!surface_axis[1]){ cbf_failnez (cbf_require_column (handle,"array_id")) cbf_failnez (cbf_new_row (handle)) cbf_failnez (cbf_set_value (handle, array_id)) cbf_failnez (cbf_require_column (handle, "precedence")) cbf_failnez (cbf_set_integervalue(handle,2)) cbf_failnez (cbf_require_column (handle, "axis_set_id")) cbf_failnez (cbf_require_value (handle, &surface_axis [1], "ELEMENT_Y")) } if (!surface_axis [0]) return CBF_FORMAT; cbf_failnez (cbf_require_category (handle, "array_structure_list_axis")) cbf_failnez (cbf_require_column (handle, "axis_set_id")) cbf_failnez (cbf_require_row (handle, surface_axis [0])) cbf_failnez (cbf_require_column (handle, "axis_id")) cbf_failnez (cbf_require_value (handle, &surface_axis [0], surface_axis[0])) if (!cbf_find_column(handle, "reference_displacement") || !cbf_require_column (handle, "displacement")){ cbf_failnez (cbf_require_doublevalue(handle, &displacement [0], 0.0)) } else return CBF_NOTFOUND; cbf_failnez (cbf_require_column (handle, "displacement_increment")) cbf_failnez (cbf_require_doublevalue(handle, &(increment [0]), 0.0)) if (surface_axis [1]) { cbf_failnez (cbf_require_column (handle, "axis_set_id")) cbf_failnez (cbf_require_row (handle, surface_axis [1])) cbf_failnez (cbf_require_column (handle, "axis_id")) cbf_failnez (cbf_require_value (handle, &surface_axis [1], surface_axis[1])) if (!cbf_find_column(handle, "reference_displacement") || !cbf_require_column (handle, "displacement")){ cbf_failnez (cbf_require_doublevalue(handle, &displacement [1], 0.0)) } else return CBF_NOTFOUND; cbf_failnez (cbf_require_column (handle, "displacement_increment")) cbf_failnez (cbf_require_doublevalue(handle, &(increment [1]), 0.0)) } /* Construct the positioner */ cbf_failnez (cbf_make_positioner (&positioner)) errorcode = cbf_alloc ((void **) detector, NULL, sizeof (cbf_detector_struct), 1); for (row = errorcode = 0; !errorcode; row++) { errorcode = cbf_require_category (handle, "diffrn_detector_axis"); if (!errorcode) { /* allow for aliases _diffrn_detector_axis.detector_id _diffrn_detector_axis.id (deprecated) */ errorcode = cbf_find_column (handle, "detector_id"); if (errorcode) errorcode = cbf_find_column (handle, "id"); if (errorcode) errorcode = cbf_require_column (handle, "detector_id"); } if (!errorcode) { errorcode = cbf_select_row (handle, row); if (errorcode == CBF_NOTFOUND) { errorcode = 0; break; } } if (!errorcode) errorcode = cbf_get_value (handle, &this_id); if (!errorcode) if (cbf_cistrcmp (id, this_id) == 0) { errorcode = cbf_find_column (handle, "axis_id"); if (!errorcode) errorcode = cbf_get_value (handle, &axis_id); if (!errorcode) errorcode = cbf_read_positioner_axis (handle, 0, positioner, axis_id, -1); } } /* Add the surface axes */ if (!errorcode) errorcode = cbf_read_positioner_axis (handle, 0, positioner, surface_axis [0], 0); if (!errorcode && surface_axis [1]) errorcode = cbf_read_positioner_axis (handle, 0, positioner, surface_axis [1], 0); /* Connect the axes */ if (!errorcode) errorcode = cbf_connect_axes (positioner); if (errorcode) { errorcode |= cbf_free_positioner (positioner); return errorcode | cbf_free ((void **) detector, NULL); } /* Insert the cbf handle and element into the dectector */ (*detector)->handle = handle; (*detector)->element = element_number; /* Copy the start and increment values into the surface axes */ (*detector)->displacement [0] = displacement [0]; (*detector)->displacement [1] = displacement [1]; (*detector)->increment [0] = increment [0]; (*detector)->increment [1] = increment [1]; if (surface_axis [1]) (*detector)->axes = 2; else (*detector)->axes = 1; for (axis = 0; axis < (*detector)->axes; axis++) for (row = 0; row < positioner->axes; row++) if (cbf_cistrcmp (positioner->axis [row].name, surface_axis [axis]) == 0) { (*detector)->index [axis] = row; positioner->axis [row].increment = 0; break; } (*detector)->positioner = positioner; return 0; } /* Free a detector */ int cbf_free_detector (cbf_detector detector) { int errorcode = 0; void * memblock; memblock = (void *)detector; if (detector) errorcode = cbf_free_positioner (detector->positioner); return errorcode | cbf_free (&memblock, NULL); } /* Update the pixel settings */ int cbf_update_pixel (cbf_detector detector, double index1, double index2) { if (!detector) return CBF_ARGUMENT; detector->positioner->axis [detector->index [0]].start = index2 * detector->increment [0] + detector->displacement [0]; if (detector->axes == 2) detector->positioner->axis [detector->index [1]].start = index1 * detector->increment [1] + detector->displacement [1]; return 0; } /* Get the beam center */ int cbf_get_beam_center (cbf_detector detector, double *index1, double *index2, double *center1, double *center2) { double pixel00 [3], pixel01 [3], pixel10 [3], m [2][2], det, index [2]; if (!detector) return CBF_ARGUMENT; if (detector->axes < 2) return CBF_NOTIMPLEMENTED; cbf_failnez (cbf_get_pixel_coordinates (detector, 0, 0, &pixel00 [0], &pixel00 [1], &pixel00 [2])) cbf_failnez (cbf_get_pixel_coordinates (detector, 0, 1, &pixel01 [0], &pixel01 [1], &pixel01 [2])) cbf_failnez (cbf_get_pixel_coordinates (detector, 1, 0, &pixel10 [0], &pixel10 [1], &pixel10 [2])) m [0][0] = pixel10 [0] - pixel00 [0]; m [0][1] = pixel01 [0] - pixel00 [0]; m [1][0] = pixel10 [1] - pixel00 [1]; m [1][1] = pixel01 [1] - pixel00 [1]; det = m [0][0] * m [1][1] - m [1][0] * m [0][1]; if (det == 0.0) return CBF_UNDEFINED; index [0] = (-m [1][1] * pixel00 [0] + m [0][1] * pixel00 [1]) / det; index [1] = (m [1][0] * pixel00 [0] - m [0][0] * pixel00 [1]) / det; if (index1) *index1 = index [0]; if (index2) *index2 = index [1]; if (center1) *center1 = index [0] * detector->increment [0]; if (center2) *center2 = index [1] * detector->increment [1]; return 0; /* a * delta01 + b * delta10 + pixel00 = (0 0 ?) a * delta01[0] + b * delta10[0] + pixel00[0] = 0 a * delta01[1] + b * delta10[1] + pixel00[1] = 0 (d01[0] d10[0]) (a) = -(p00[0]) (d01[1] d10[1]) (b) (p00[1]) (a) = -(d01[0] d10[0])-1 (p00[0]) (b) (d01[1] d10[1]) (p00[1]) */ } /* Set the beam center */ int cbf_set_beam_center (cbf_detector detector, double *index1, double *index2, double *center1, double *center2) { double oindex1, oindex2, ocenter1, ocenter2; double nindex1, nindex2, ncenter1, ncenter2; double psize1, psize2; unsigned int naxis1, naxis2; int sign1, sign2; cbf_handle handle; unsigned int element; const char *element_id; if (!detector) return CBF_ARGUMENT; if (detector->axes < 2) return CBF_NOTIMPLEMENTED; handle = detector->handle; element = detector->element; cbf_failnez(cbf_get_element_id(handle,element, &element_id)) naxis1 = detector->index[1]; naxis2 = detector->index[0]; sign1 = detector->increment[1]>0.0?1.0:-1.0; sign2 = detector->increment[0]>0.0?1.0:-1.0; psize1 = detector->increment[1]; if (psize1 < 0.) psize1 = -psize1; psize2 = detector->increment[0]; if (psize1 < 0.) psize2 = -psize2; if (index1) { nindex1 = *index1; } else { if (center1 && psize1 != 0.) nindex1 = sign1*(*center1)/psize1; else return CBF_ARGUMENT; } if (index2) { nindex2 = *index2; } else { if (center2 && psize2 != 0.) nindex2 = sign2*(*center2)/psize2; else return CBF_ARGUMENT; } if (center1) { ncenter1 = *center1; } else { if (index1 && psize1 != 0.) ncenter1 = sign1*(*index1)*psize1; else return CBF_ARGUMENT; } if (center2) { ncenter2 = *center2; } else { if (index2 && psize2 != 0.) ncenter2 = sign2*(*index2)*psize2; else return CBF_ARGUMENT; } cbf_failnez(cbf_get_beam_center(detector, &oindex1, &oindex2, &ocenter1, &ocenter2)) cbf_failnez(cbf_find_category(handle, "array_structure_list_axis")) cbf_failnez(cbf_find_column(handle, "axis_id")) if ( nindex1 < oindex1-1.e-6 || nindex1 > oindex1+1.e-6 ) { double olddisp; cbf_failnez(cbf_rewind_row(handle)) cbf_failnez(cbf_find_row(handle,detector->positioner->axis[naxis1].name)) cbf_failnez(cbf_require_column(handle, "displacement")) cbf_failnez(cbf_require_doublevalue(handle,&olddisp,0.0)) cbf_failnez(cbf_set_doublevalue(handle, "%-f", -(nindex1-oindex1)*detector->increment[1] + detector->displacement[1])) } cbf_failnez(cbf_find_column(handle, "axis_id")) if ( nindex2 < oindex2-1.e-6 || nindex2 > oindex2+1.e-6 ) { double olddisp; cbf_failnez(cbf_rewind_row(handle)) cbf_failnez(cbf_find_row(handle,detector->positioner->axis[naxis2].name)) cbf_failnez(cbf_require_column(handle, "displacement")) cbf_failnez(cbf_require_doublevalue(handle,&olddisp,0.0)) cbf_failnez(cbf_set_doublevalue(handle, "%-f", -(nindex2-oindex2)*detector->increment[0] + detector->displacement[0])) } if (!cbf_find_category(handle,"diffrn_data_frame") && !cbf_find_column(handle,"detector_element_id") && !cbf_find_row(handle,element_id)) { cbf_failnez(cbf_require_column(handle,"center_slow")) cbf_failnez(cbf_set_doublevalue(handle, "%-f", nindex1*detector->increment[1])) cbf_failnez(cbf_require_column(handle,"center_fast")) cbf_failnez(cbf_set_doublevalue(handle, "%-f", nindex2*detector->increment[0])) cbf_failnez(cbf_require_column(handle,"center_units")) cbf_failnez(cbf_set_value(handle, "mm")) } return 0; } /* Set the reference beam center */ int cbf_set_reference_beam_center (cbf_detector detector, double *index1, double *index2, double *center1, double *center2) { double oindex1, oindex2, ocenter1, ocenter2; double nindex1, nindex2, ncenter1, ncenter2; double psize1, psize2; unsigned int naxis1, naxis2; int sign1, sign2; cbf_handle handle; unsigned int element; const char *element_id; if (!detector) return CBF_ARGUMENT; if (detector->axes < 2) return CBF_NOTIMPLEMENTED; handle = detector->handle; element = detector->element; cbf_failnez(cbf_get_element_id(handle,element, &element_id)) naxis1 = detector->index[1]; naxis2 = detector->index[0]; sign1 = detector->increment[1]>0.0?1.0:-1.0; sign2 = detector->increment[0]>0.0?1.0:-1.0; psize1 = detector->increment[1]; if (psize1 < 0.) psize1 = -psize1; psize2 = detector->increment[0]; if (psize1 < 0.) psize2 = -psize2; if (index1) { nindex1 = *index1; } else { if (center1 && psize1 != 0.) nindex1 = sign1*(*center1)/psize1; else return CBF_ARGUMENT; } if (index2) { nindex2 = *index2; } else { if (center2 && psize2 != 0.) nindex2 = sign2*(*center2)/psize2; else return CBF_ARGUMENT; } if (center1) { ncenter1 = *center1; } else { if (index1 && psize1 != 0.) ncenter1 = sign1*(*index1)*psize1; else return CBF_ARGUMENT; } if (center2) { ncenter2 = *center2; } else { if (index2 && psize2 != 0.) ncenter2 = sign2*(*index2)*psize2; else return CBF_ARGUMENT; } cbf_failnez(cbf_get_beam_center(detector, &oindex1, &oindex2, &ocenter1, &ocenter2)) cbf_failnez(cbf_find_category(handle, "array_structure_list_axis")) cbf_failnez(cbf_find_column(handle, "axis_id")) if ( nindex1 < oindex1-1.e-6 || nindex1 > oindex1+1.e-6 ) { double olddisp; cbf_failnez(cbf_rewind_row(handle)) cbf_failnez(cbf_find_row(handle,detector->positioner->axis[naxis1].name)) cbf_failnez(cbf_require_column(handle, "reference_displacement")) cbf_failnez(cbf_require_doublevalue(handle,&olddisp,0.0)) cbf_failnez(cbf_set_doublevalue(handle, "%-f", -(nindex1-oindex1)*detector->increment[1] + detector->displacement[1])) } cbf_failnez(cbf_find_column(handle, "axis_id")) if ( nindex2 < oindex2-1.e-6 || nindex2 > oindex2+1.e-6 ) { double olddisp; cbf_failnez(cbf_rewind_row(handle)) cbf_failnez(cbf_find_row(handle,detector->positioner->axis[naxis2].name)) cbf_failnez(cbf_require_column(handle, "reference_displacement")) cbf_failnez(cbf_require_doublevalue(handle,&olddisp,0.0)) cbf_failnez(cbf_set_doublevalue(handle, "%-f", -(nindex2-oindex2)*detector->increment[0] + detector->displacement[0])) } if (!cbf_find_category(handle,"diffrn_detector_element") && !cbf_find_column(handle,"id") && !cbf_find_row(handle,element_id)) { cbf_failnez(cbf_require_column(handle,"reference_center_slow")) cbf_failnez(cbf_set_doublevalue(handle, "%-f", nindex1*detector->increment[1])) cbf_failnez(cbf_require_column(handle,"reference_center_fast")) cbf_failnez(cbf_set_doublevalue(handle, "%-f", nindex2*detector->increment[0])) cbf_failnez(cbf_require_column(handle,"reference_center_units")) cbf_failnez(cbf_set_value(handle, "mm")) } return 0; } /* Get the detector distance: shortest distance to the plane */ int cbf_get_detector_distance (cbf_detector detector, double *distance) { double normal [3], pixel00 [3]; cbf_failnez (cbf_get_detector_normal (detector, &normal [0], &normal [1], &normal [2])) cbf_failnez (cbf_get_pixel_coordinates (detector, 0, 0, &pixel00 [0], &pixel00 [1], &pixel00 [2])) if (distance) *distance = fabs (normal [0] * pixel00 [0] + normal [1] * pixel00 [1] + normal [2] * pixel00 [2]); return 0; } /* Get the detector normal */ int cbf_get_detector_normal (cbf_detector detector, double *normal1, double *normal2, double *normal3) { cbf_failnez (cbf_get_pixel_normal (detector, 0, 0, normal1, normal2, normal3)) return 0; } /* Calcluate the coordinates of a pixel */ int cbf_get_pixel_coordinates (cbf_detector detector, double index1, double index2, double *coordinate1, double *coordinate2, double *coordinate3) { cbf_failnez (cbf_update_pixel (detector, index1, index2)) cbf_failnez (cbf_calculate_position (detector->positioner, 0, 0, 0, 0, 0, coordinate1, coordinate2, coordinate3)) return 0; } /* Calcluate the slow axis of a detector */ int cbf_get_detector_axis_slow (cbf_detector detector, double *slowaxis1, double *slowaxis2, double *slowaxis3) { double pixel00[3], pixel10[3], length; cbf_failnez (cbf_get_pixel_coordinates (detector, - 0.5, - 0.5, &pixel00 [0], &pixel00 [1], &pixel00 [2])) cbf_failnez (cbf_get_pixel_coordinates (detector, 0.5, - 0.5, &pixel10 [0], &pixel10 [1], &pixel10 [2])) pixel10 [0] -= pixel00 [0]; pixel10 [1] -= pixel00 [1]; pixel10 [2] -= pixel00 [2]; length = pixel10 [0]* pixel10 [0] + pixel10 [1]* pixel10 [1] + pixel10 [2]* pixel10 [2]; if (length <= 0.0) return CBF_UNDEFINED; length = sqrt (length); if (slowaxis1) *slowaxis1 = pixel10 [0] / length; if (slowaxis2) *slowaxis2 = pixel10 [1] / length; if (slowaxis3) *slowaxis3 = pixel10 [2] / length; return 0; } /* Calcluate the fast axis of a detector */ int cbf_get_detector_axis_fast (cbf_detector detector, double *fastaxis1, double *fastaxis2, double *fastaxis3) { double pixel00[3], pixel01[3], length; cbf_failnez (cbf_get_pixel_coordinates (detector, -0.5, -0.5, &pixel00 [0], &pixel00 [1], &pixel00 [2])) cbf_failnez (cbf_get_pixel_coordinates (detector, -0.5, 0.5, &pixel01 [0], &pixel01 [1], &pixel01 [2])) pixel01 [0] -= pixel00 [0]; pixel01 [1] -= pixel00 [1]; pixel01 [2] -= pixel00 [2]; length = pixel01 [0]* pixel01 [0] + pixel01 [1]* pixel01 [1] + pixel01 [2]* pixel01 [2]; if (length <= 0.0) return CBF_UNDEFINED; length = sqrt (length); if (fastaxis1) *fastaxis1 = pixel01 [0] / length; if (fastaxis2) *fastaxis2 = pixel01 [1] / length; if (fastaxis3) *fastaxis3 = pixel01 [2] / length; return 0; } /* Calcluate the axes of a detector */ int cbf_get_detector_axes (cbf_detector detector, double *slowaxis1, double *slowaxis2, double *slowaxis3, double *fastaxis1, double *fastaxis2, double *fastaxis3) { cbf_failnez (cbf_get_detector_axis_slow (detector, slowaxis1, slowaxis2, slowaxis3) ) cbf_failnez (cbf_get_detector_axis_fast (detector, fastaxis1, fastaxis2, fastaxis3) ) return 0; } /* Get the pixel normal */ int cbf_get_pixel_normal (cbf_detector detector, double index1, double index2, double *normal1, double *normal2, double *normal3) { double pixel00 [3], pixel01 [3], pixel10 [3], normal [3], length; cbf_failnez (cbf_get_pixel_coordinates (detector, index1 - 0.5, index2 - 0.5, &pixel00 [0], &pixel00 [1], &pixel00 [2])) cbf_failnez (cbf_get_pixel_coordinates (detector, index1 - 0.5, index2 + 0.5, &pixel01 [0], &pixel01 [1], &pixel01 [2])) cbf_failnez (cbf_get_pixel_coordinates (detector, index1 + 0.5, index2 - 0.5, &pixel10 [0], &pixel10 [1], &pixel10 [2])) pixel01 [0] -= pixel00 [0]; pixel01 [1] -= pixel00 [1]; pixel01 [2] -= pixel00 [2]; pixel10 [0] -= pixel00 [0]; pixel10 [1] -= pixel00 [1]; pixel10 [2] -= pixel00 [2]; normal [0] = pixel01 [1] * pixel10 [2] - pixel10 [1] * pixel01 [2]; normal [1] = pixel01 [2] * pixel10 [0] - pixel10 [2] * pixel01 [0]; normal [2] = pixel01 [0] * pixel10 [1] - pixel10 [0] * pixel01 [1]; length = normal [0] * normal [0] + normal [1] * normal [1] + normal [2] * normal [2]; if (length <= 0.0) return CBF_UNDEFINED; length = sqrt (length); if (normal1) *normal1 = normal [0] / length; if (normal2) *normal2 = normal [1] / length; if (normal3) *normal3 = normal [2] / length; return 0; } /* Calcluate the area of a pixel */ int cbf_get_pixel_area (cbf_detector detector, double index1, double index2, double *area, double *projected_area) { double pixel00 [3], pixel01 [3], pixel10 [3], normal [3]; double length, length00; if (!detector) return CBF_ARGUMENT; if (detector->axes < 2) return CBF_NOTIMPLEMENTED; cbf_failnez (cbf_get_pixel_coordinates (detector, index1 - 0.5, index2 - 0.5, &pixel00 [0], &pixel00 [1], &pixel00 [2])) cbf_failnez (cbf_get_pixel_coordinates (detector, index1 - 0.5, index2 + 0.5, &pixel01 [0], &pixel01 [1], &pixel01 [2])) cbf_failnez (cbf_get_pixel_coordinates (detector, index1 + 0.5, index2 - 0.5, &pixel10 [0], &pixel10 [1], &pixel10 [2])) pixel01 [0] -= pixel00 [0]; pixel01 [1] -= pixel00 [1]; pixel01 [2] -= pixel00 [2]; pixel10 [0] -= pixel00 [0]; pixel10 [1] -= pixel00 [1]; pixel10 [2] -= pixel00 [2]; normal [0] = pixel01 [1] * pixel10 [2] - pixel10 [1] * pixel01 [2]; normal [1] = pixel01 [2] * pixel10 [0] - pixel10 [2] * pixel01 [0]; normal [2] = pixel01 [0] * pixel10 [1] - pixel10 [0] * pixel01 [1]; length = normal [0] * normal [0] + normal [1] * normal [1] + normal [2] * normal [2]; if (length <= 0.0) return CBF_UNDEFINED; length = sqrt (length); if (area) *area = length; if (projected_area) { length00 = pixel00 [0] * pixel00 [0] + pixel00 [1] * pixel00 [1] + pixel00 [2] * pixel00 [2]; if (length00 <= 0.0) return CBF_UNDEFINED; length00 = sqrt (length00); *projected_area = fabs (pixel00 [0] * normal [0] + pixel00 [1] * normal [1] + pixel00 [2] * normal [2]) / length00; } return 0; } /* Calcluate the size of a pixel from the detector element axis displacements */ int cbf_get_inferred_pixel_size (cbf_detector detector, int axis_number, double *psize) { if (axis_number < 0) axis_number = detector->axes+1+axis_number; if (!detector || axis_number < 1 || detector-> axes < axis_number ) return CBF_ARGUMENT; *psize = fabs( (detector-> increment)[axis_number-1] ); return 0; } /* Get the unit cell parameters */ int cbf_get_unit_cell (cbf_handle handle, double cell[6], double cell_esd[6]) { cbf_failnez(cbf_find_category (handle, "cell")) cbf_failnez(cbf_rewind_row (handle)) if (cell) { cbf_failnez (cbf_require_column_doublevalue (handle, "length_a", &(cell[0]),0.)) cbf_failnez (cbf_require_column_doublevalue (handle, "length_b", &(cell[1]),0.)) cbf_failnez (cbf_require_column_doublevalue (handle, "length_c", &(cell[2]),0.)) cbf_failnez (cbf_require_column_doublevalue (handle, "angle_alpha", &(cell[3]),0.)) cbf_failnez (cbf_require_column_doublevalue (handle, "angle_beta", &(cell[4]),0.)) cbf_failnez (cbf_require_column_doublevalue (handle, "angle_gamma", &(cell[5]),0.)) } if (cell_esd) { cbf_failnez (cbf_require_column_doublevalue (handle, "length_a_esd", &(cell_esd[0]),0.)) cbf_failnez (cbf_require_column_doublevalue (handle, "length_b_esd", &(cell_esd[1]),0.)) cbf_failnez (cbf_require_column_doublevalue (handle, "length_c_esd", &(cell_esd[2]),0.)) cbf_failnez (cbf_require_column_doublevalue (handle, "angle_alpha_esd", &(cell_esd[3]),0.)) cbf_failnez (cbf_require_column_doublevalue (handle, "angle_beta_esd", &(cell_esd[4]),0.)) cbf_failnez (cbf_require_column_doublevalue (handle, "angle_gamma_esd", &(cell_esd[5]),0.)) } return 0; } /* Set the unit cell parameters */ int cbf_set_unit_cell (cbf_handle handle, double cell[6], double cell_esd[6]) { const char * diffrn_id; const char * entry_id; if (!(cbf_get_diffrn_id (handle, &diffrn_id))) diffrn_id = NULL; cbf_failnez(cbf_require_category (handle, "cell")) cbf_failnez(cbf_rewind_row (handle)) cbf_failnez(cbf_require_column (handle, "entry_id")) entry_id = NULL; if (diffrn_id && (cbf_get_value(handle, &entry_id) || !entry_id || *entry_id == '\0')) { cbf_failnez(cbf_set_value (handle, diffrn_id)) } if (cell) { cbf_failnez (cbf_require_column (handle, "length_a")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", cell[0])) cbf_failnez (cbf_require_column (handle, "length_b")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", cell[1])) cbf_failnez (cbf_require_column (handle, "length_c")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", cell[2])) cbf_failnez (cbf_require_column (handle, "angle_alpha")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", cell[3])) cbf_failnez (cbf_require_column (handle, "angle_beta")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", cell[4])) cbf_failnez (cbf_require_column (handle, "angle_gamma")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", cell[5])) } if (cell_esd) { cbf_failnez (cbf_require_column (handle, "length_a_esd")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", cell_esd[0])) cbf_failnez (cbf_require_column (handle, "length_b_esd")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", cell_esd[1])) cbf_failnez (cbf_require_column (handle, "length_c_esd")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", cell_esd[2])) cbf_failnez (cbf_require_column (handle, "angle_alpha_esd")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", cell_esd[3])) cbf_failnez (cbf_require_column (handle, "angle_beta_esd")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", cell_esd[4])) cbf_failnez (cbf_require_column (handle, "angle_gamma_esd")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", cell_esd[5])) } return 0; } /* Get the reciprocal cell parameters */ int cbf_get_reciprocal_cell (cbf_handle handle, double cell[6], double cell_esd[6]) { cbf_failnez(cbf_find_category (handle, "cell")) cbf_failnez(cbf_rewind_row (handle)) if (cell) { cbf_failnez (cbf_require_column_doublevalue (handle, "reciprocal_length_a", &(cell[0]),0.)) cbf_failnez (cbf_require_column_doublevalue (handle, "reciprocal_length_b", &(cell[1]),0.)) cbf_failnez (cbf_require_column_doublevalue (handle, "reciprocal_length_c", &(cell[2]),0.)) cbf_failnez (cbf_require_column_doublevalue (handle, "reciprocal_angle_alpha", &(cell[3]),0.)) cbf_failnez (cbf_require_column_doublevalue (handle, "reciprocal_angle_beta", &(cell[4]),0.)) cbf_failnez (cbf_require_column_doublevalue (handle, "reciprocal_angle_gamma", &(cell[5]),0.)) } if (cell_esd) { cbf_failnez (cbf_require_column_doublevalue (handle, "reciprocal_length_a_esd", &(cell_esd[0]),0.)) cbf_failnez (cbf_require_column_doublevalue (handle, "reciprocal_length_b_esd", &(cell_esd[1]),0.)) cbf_failnez (cbf_require_column_doublevalue (handle, "reciprocal_length_c_esd", &(cell_esd[2]),0.)) cbf_failnez (cbf_require_column_doublevalue (handle, "reciprocal_angle_alpha_esd", &(cell_esd[3]),0.)) cbf_failnez (cbf_require_column_doublevalue (handle, "reciprocal_angle_beta_esd", &(cell_esd[4]),0.)) cbf_failnez (cbf_require_column_doublevalue (handle, "reciprocal_angle_gamma_esd", &(cell_esd[5]),0.)) } return 0; } /* Set the reciprocal cell parameters */ int cbf_set_reciprocal_cell (cbf_handle handle, double cell[6], double cell_esd[6]) { const char * diffrn_id; const char * entry_id; if (!(cbf_get_diffrn_id (handle, &diffrn_id))) diffrn_id = NULL; cbf_failnez(cbf_require_category (handle, "cell")) cbf_failnez(cbf_rewind_row (handle)) cbf_failnez(cbf_require_column (handle, "entry_id")) entry_id = NULL; if (diffrn_id && (cbf_get_value(handle, &entry_id) || !entry_id || *entry_id == '\0')) { cbf_failnez(cbf_set_value (handle, diffrn_id)) } if (cell) { cbf_failnez (cbf_require_column (handle, "reciprocal_length_a")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", cell[0])) cbf_failnez (cbf_require_column (handle, "reciprocal_length_b")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", cell[1])) cbf_failnez (cbf_require_column (handle, "reciprocal_length_c")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", cell[2])) cbf_failnez (cbf_require_column (handle, "reciprocal_angle_alpha")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", cell[3])) cbf_failnez (cbf_require_column (handle, "reciprocal_angle_beta")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", cell[4])) cbf_failnez (cbf_require_column (handle, "reciprocal_angle_gamma")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", cell[5])) } if (cell_esd) { cbf_failnez (cbf_require_column (handle, "reciprocal_length_a_esd")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", cell_esd[0])) cbf_failnez (cbf_require_column (handle, "reciprocal_length_b_esd")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", cell_esd[1])) cbf_failnez (cbf_require_column (handle, "reciprocal_length_c_esd")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", cell_esd[2])) cbf_failnez (cbf_require_column (handle, "reciprocal_angle_alpha_esd")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", cell_esd[3])) cbf_failnez (cbf_require_column (handle, "reciprocal_angle_beta_esd")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", cell_esd[4])) cbf_failnez (cbf_require_column (handle, "reciprocal_angle_gamma_esd")) cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", cell_esd[5])) } return 0; } /* Compute a cell volume */ int cbf_compute_cell_volume (double cell[6], double *volume) { double degtorad; degtorad = atan2(1.,1.)/45.; *volume = cell[0]*cell[1]*cell[2]* sqrt(1. - cos(cell[3]*degtorad)*cos(cell[3]*degtorad) - cos(cell[4]*degtorad)*cos(cell[4]*degtorad) - cos(cell[5]*degtorad)*cos(cell[5]*degtorad) + 2.*cos(cell[3]*degtorad)*cos(cell[4]*degtorad)*cos(cell[5]*degtorad)); return 0; } /* Compute a reciprocal cell */ int cbf_compute_reciprocal_cell (double cell[6], double rcell[6]){ double volume, degtorad, radtodeg; #define acos_deg(x) (atan2(sqrt(1.-(x)*(x)),(x))*radtodeg) cbf_compute_cell_volume (cell, &volume); degtorad = atan2(1.,1.)/45.; radtodeg = 1./degtorad; if (volume <= 0. ) return CBF_ARGUMENT; rcell[0] = cell[1]*cell[2]*sin(cell[3]*degtorad)/volume; rcell[1] = cell[2]*cell[0]*sin(cell[4]*degtorad)/volume; rcell[2] = cell[0]*cell[1]*sin(cell[5]*degtorad)/volume; rcell[3] = acos_deg((cos(cell[4]*degtorad)*cos(cell[5]*degtorad) - cos(cell[3]*degtorad))/(sin(cell[4]*degtorad)*sin(cell[5]*degtorad))); rcell[4] = acos_deg((cos(cell[5]*degtorad)*cos(cell[3]*degtorad) - cos(cell[4]*degtorad))/(sin(cell[5]*degtorad)*sin(cell[3]*degtorad))); rcell[5] = acos_deg((cos(cell[3]*degtorad)*cos(cell[4]*degtorad) - cos(cell[5]*degtorad))/(sin(cell[3]*degtorad)*sin(cell[4]*degtorad))); return 0; } /* Get the orientation matrix entry */ int cbf_get_orientation_matrix (cbf_handle handle, double ub_matrix[9]) { cbf_failnez(cbf_find_category (handle, "diffrn_orient_matrix")); cbf_failnez(cbf_rewind_row (handle)); if (ub_matrix) { cbf_failnez (cbf_find_column (handle, "UB[1][1]")); cbf_failnez (cbf_get_doublevalue (handle, &(ub_matrix[0]))); cbf_failnez (cbf_find_column (handle, "UB[1][2]")); cbf_failnez (cbf_get_doublevalue (handle, &(ub_matrix[1]))); cbf_failnez (cbf_find_column (handle, "UB[1][3]")); cbf_failnez (cbf_get_doublevalue (handle, &(ub_matrix[2]))); cbf_failnez (cbf_find_column (handle, "UB[2][1]")); cbf_failnez (cbf_get_doublevalue (handle, &(ub_matrix[3]))); cbf_failnez (cbf_find_column (handle, "UB[2][2]")); cbf_failnez (cbf_get_doublevalue (handle, &(ub_matrix[4]))); cbf_failnez (cbf_find_column (handle, "UB[2][3]")); cbf_failnez (cbf_get_doublevalue (handle, &(ub_matrix[5]))); cbf_failnez (cbf_find_column (handle, "UB[3][1]")); cbf_failnez (cbf_get_doublevalue (handle, &(ub_matrix[6]))); cbf_failnez (cbf_find_column (handle, "UB[3][2]")); cbf_failnez (cbf_get_doublevalue (handle, &(ub_matrix[7]))); cbf_failnez (cbf_find_column (handle, "UB[3][3]")); cbf_failnez (cbf_get_doublevalue (handle, &(ub_matrix[8]))); } return 0; } /* Set the orientation matrix entry */ int cbf_set_orientation_matrix (cbf_handle handle, double ub_matrix[9]) { const char * diffrn_id; const char * UBdiffrn_id; cbf_failnez(cbf_get_diffrn_id (handle, &diffrn_id)) cbf_failnez(cbf_require_category (handle, "diffrn_orient_matrix")) cbf_failnez(cbf_rewind_row (handle)) cbf_failnez(cbf_require_column (handle, "diffrn_id")) UBdiffrn_id = 0; if (cbf_get_value(handle, &UBdiffrn_id) || !UBdiffrn_id || *UBdiffrn_id == '\0') { cbf_failnez(cbf_set_value (handle, diffrn_id)) } if (ub_matrix) { cbf_failnez (cbf_require_column (handle, "UB[1][1]")); cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", ub_matrix[0])); cbf_failnez (cbf_require_column (handle, "UB[1][2]")); cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", ub_matrix[1])); cbf_failnez (cbf_require_column (handle, "UB[1][3]")); cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", ub_matrix[2])); cbf_failnez (cbf_require_column (handle, "UB[2][1]")); cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", ub_matrix[3])); cbf_failnez (cbf_require_column (handle, "UB[2][2]")); cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", ub_matrix[4])); cbf_failnez (cbf_require_column (handle, "UB[2][3]")); cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", ub_matrix[5])); cbf_failnez (cbf_require_column (handle, "UB[3][1]")); cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", ub_matrix[6])); cbf_failnez (cbf_require_column (handle, "UB[3][2]")); cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", ub_matrix[7])); cbf_failnez (cbf_require_column (handle, "UB[3][3]")); cbf_failnez (cbf_set_doublevalue (handle, "%-.15g", ub_matrix[8])); } return 0; } #ifdef __cplusplus } #endif ./CBFlib-0.9.2.2/src/drel_yacc.py0000777000076500007650000000000011603745057021277 2../dREL-ply-0.5/drel_yacc.pyustar yayayaya./CBFlib-0.9.2.2/jcbf/0000755000076500007650000000000011603703065012507 5ustar yayayaya./CBFlib-0.9.2.2/jcbf/jcbf.i0000644000076500007650000000215011603702106013556 0ustar yayayaya// swig -Iinclude -java -package org.iucr.jcbf.ib -outdir java cbf.i // javac -d . java/*.java // jar cf cbflib-0.8.0.jar org // gcc -fPIC -fpic -c cbf_wrap.c -I/dls_sw/dasc/jdk/jdk1.6.0_11/include -I/dls_sw/dasc/jdk/jdk1.6.0_11/include/linux -Iinclude // gcc -shared cbf_wrap.o -o solib/libcbf_wrap.so -Lsolib -lcbf %module cbf %{ /* Includes the header in the wrapper code */ #include "cbf.h" %} %include "cpointer.i" // wrap some C pointers in classes %pointer_class(unsigned int, uintp) %pointer_class(double, doublep) // wrap char** in functions %pointer_functions(const char *, charpp) // Don't expose the memory allocation/de-allocation functions %ignore cbf_make_handle(cbf_handle *ppchs); %ignore cbf_free_handle(cbf_handle pchs); /* Parse the header file to generate wrappers */ %include "cbf.h" // Add in a custom proxy constructor and destructor %extend cbf_handle_struct { cbf_handle_struct() { cbf_handle_struct *pchs = 0; cbf_make_handle(&pchs); return pchs; } ~cbf_handle_struct() { cbf_free_handle(self); } } // File I/O functions FILE *fopen(char *name, char *mode); void fclose(FILE *); ./CBFlib-0.9.2.2/html_graphics/0000755000076500007650000000000011603703065014427 5ustar yayayaya./CBFlib-0.9.2.2/html_graphics/CBFbutton.jpg0000755000076500007650000000537011603702104016760 0ustar yayayayaÿØÿàJFIFHHÿþ AppleMark ÿÛ„   % #!,!#'(***.1-)1%)*(  (((((((((((((((((((((((((((((((((((((((((((((((((((ÿÄ¢  }!1AQa"q2‘¡#B±ÁRÑð$3br‚ %&'()*456789:CDEFGHIJSTUVWXYZcdefghijstuvwxyzƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚáâãäåæçèéêñòóôõö÷øùúw!1AQaq"2B‘¡±Á #3RðbrÑ $4á%ñ&'()*56789:CDEFGHIJSTUVWXYZcdefghijstuvwxyz‚ƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚâãäåæçèéêòóôõö÷øùúÿÀ#X"ÿÚ ?ô­GTЫBzw„¥)ÅÊéífú[[[ÞשÁÜøóB‘$n•¯Îa”¤²›xÝIû­Éž¤`döÁ’_éðø}5á©%ͧš#d†Ôù›Ž>L>VžOLž3Íèn¯w±ö r=>©´g1&N0üãnH€Êð*-fµÈ—áÝÔ`úÞá⑆âe&H[z±ÎzsÊŽWŒ‘Ÿ&¦?R´aN¯*¾¶Šz.né½ZµÕ’×M.ý:™F $›´éÅÚRûV½Õ’^VoñÓªƒÄª¼cNÕ]J±dÒÈ Á>onI#§#Ímêv·>¶›Y…à¸{uùm]"9`ÒY¼³‚F@ ÷}sü?/ˆ ¸³[­f‹@‰‹X,]œ«#2µI?(<ƒÆÁ’y¦Ö­¡Õ´†·.íËD»à9%K¯ ý9Ïnµó¸Œß2–&•,D¿u6“÷RR‹jëáŽêÛti¦x˜ü RÃÙ¸­ù¥+5{o³9ÍJ9ôÛ©u=2îÚ8zÝC,sZÙàî rªáF0sÚ àã&ºÍ6Â+ýE­dµšÄFPâá]”nC€˜Rrz1û‚qšÊ›Q×¼7&©ëV¤¬0ÝZyq܆v‘ÈŒcL–b¥”€z”kG’ó×’Ãz«`ïh³XEmtJÛ/›±¡,@V ‘0@åyULú¹nkZXÓ­.h·d¯ÌÝôV¼“Ih奞ë{mj¦œéék_¦‹åò_%±éðŠØÿÏ[ûéÂøElç­Çýô¿áLÐ5©n+-IáKá ›ˆË\6_s* ¸PÝ?ˆá&·«í£(Ê*QwOf¶fQ’’þ´<ÿâ›ýàÝORÓ¦œ]B©°œ‘UNÀ“í^ÿ Ÿˆ¿è-qù𢯱/€~k °^!99ÿžÑñ_-S,úÊ×ÃÚWˆü>,õkî 2–VʰÁŒd™ÇOøÃþ™çÓ,ÊJùämí‚s€O =9<Õï ijqŒ»˜Ïè3úý{ j¦•Y)N7kúÿ†ìtG^Ýͨ½ÕݾãÎ|AðÃÂVû."ÑÔ=ÅÀV_>`y;@`ðp=3€ËÜǦÁ¨ëz?•s=……´lÖ1ªBJÉ!G«Í‚Xôr=[ÄÑÈöâ’P—»¬h\í®Ñ’yÇð·8?/ß_*Ô4mJë]ñEÏö]ñ‚òÈ-®lXùî"UÚAL9àŽ Žµòù ”ñð©Ë“—t›÷œ¬Òéw¶šy¾S ´ñŸº“嵜uWÚÚÙ­Vº‘Çã; d°ZÝyrD‘Ú‰tÂÑHfUM¢RÌÄÈÊ1ÝGÖ¶ãñ†ugv“Ç{k&“%»Ü¥ìj²`H§~;‡8çÜW0šmÁƒÂP IÝ…Ìl Qn‚S‚ONK‘žz1ÐÇâ+ˆ%ñn£?Ú"±º¶‚8îîc+¹‡—‘·oå#€à/UåW‹¯R”js{®. ¥ºŽ–KuËÝ.emoÛ,&\ý¤oËu+¾kí5»´îû?#kZø§jp@º~¡šöÒKy%Œm–$¶wÓ&¼qKYÕ¦ñGˆä].èÛXè‘“.£m™&\€ê§=8çýÆ<ð+#UÕîõ_ø~Þ= Kh–òÜ„+²iQ¸*=±·žµ~kKýÄw÷:lZ†³k~âcj3q€rAePUI`r¼m+؃\¸|'´¨š‡¼¯Öê×IÞÊÊñ½¯eåÛº¥X¹A%6¥Ê›RM¦­kèݯ§WòEÿ?Äž²Ôb’HZÚÙ]¬5c Ê`?|‘¼†ÉmØ)©xÇÄCž—ûtØM©\KÍÑTû»Ôlç… OUã“éš?е]+\¸—OÈÖÎÚDi6m;‡ç $ºäœª3xcRºðǬåÒ/8oŸí°›b<µiPàr2 ôïœb¾‚5kS¡¤î—3æZslù­ë竾ËE̓§ANøˆAK™]+4½Éi®—½®—»{%®òø¦æð޵%ÇÄ+OÛÇ y–p,däÊX”bFmx­}ñ/Â:à=nëNÓ-l§d‰L‘¦ hC·Sý;œ«èð´êÓ‹U]ÝûßôGÍc+S­SššÓü1á?SkVñ±.¥v[T»Ç˜éµfeP¹Æp8ª‡]ÕËn:¥élç&áóž=ÿÙ_ÈzT:—ü„nÿë³ÿèF«WYÆ_Jê— ¨H¸~ÈçÜþf…×utÆÝRõvœŒ\8ÁÆ=}8úU (fÇ_Õæ¾¶IuKÉQ¥ VIÙå<èHükÕ,ïîµ/_é·“4öo_îì>`*=3å¦qéõ¯Ó¿ä!iÿ]“ÿBëš7ü”ËÏ÷›ùÏ^fmJ›À՛пP©gmV‘Ùœ°œ£Ž‚OMæeE¥ÚYèž± möí-"’ÎG‘œBÛº…bW°ê; àˆu–µ¯B‚QpáFFp1ÛÒ½*Où¼Iÿ\aÿÐy%yÙ¯ßIÛådíévþóé3š“t¤Û²[ù¤ßã© uýa‰-«_q’n_±ÈïØóIý»«…+ý©{´¨B>Ðø*:½9<{Õ +é¹>³©ÝE$7ÜÑHAt’veb1Œ‚yè?!T袀?ÿÙ./CBFlib-0.9.2.2/html_graphics/CBFbackground.jpg0000755000076500007650000001125111603702104017557 0ustar yayayayaÿØÿàJFIFHHÿþ AppleMark ÿÛ„   % #!,!#'(***.1-)1%)*(  (((((((((((((((((((((((((((((((((((((((((((((((((((ÿÄ¢  }!1AQa"q2‘¡#B±ÁRÑð$3br‚ %&'()*456789:CDEFGHIJSTUVWXYZcdefghijstuvwxyzƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚáâãäåæçèéêñòóôõö÷øùúw!1AQaq"2B‘¡±Á #3RðbrÑ $4á%ñ&'()*56789:CDEFGHIJSTUVWXYZcdefghijstuvwxyz‚ƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚâãäåæçèéêòóôõö÷øùúÿÀ¼ "ÿÚ ?úFŠ( Š( Š( Š( Š( Š( Š( Š(,RQEQEQEQEQEQEQEQEQEQEQEQEQEQEQEŒÁFOò¥¨g<íþÏÿ¨´®É“²¹0`Ý?J*¹I#9çÓüÿŸæô˜1¸÷ÿ?çôËqì%.Œ‘Ûj“ŒÕl4™lg×üÿŸÇøœìe|Gltÿ?çë8Pn8ô§ð“ñ¿!±HÜΟUÛ0¿ÊsŸ_óþœÞb€ 8ÈÈïI®ÅEôc¨¨ ÌÜ ÇÓŸóþ}²‘å$œzóþ}Ïs”9ÕËQEIaEPEPEPEPEPEPEPEPNÐO ÍG篡ÿ?çüàáïÂ7ÐÔp¨+ÈO§øúº V± »Ù 篡ÿ?çüààó×ÐÿŸóþppýŠ?„~_çÐQ±GðËüú 4 K¸Ï=}ùÿ?çž¾‡üÿŸóƒ‡ìQü#òÿ>‚Š?„~_çÐQ Z]ÆyëèÏùÿ88<õô?çüÿœ?bá—ùôlQü#òÿ>‚Òî3Ï_CþÏùÁÄLàÉ»œþϹô5cbá—ùôlQü#òÿ>‚„ÒŒ˜Ï=}ùÿ?ç¹³€AÏ<ŸóŸzŸbá—ùôlQü#òÿ>‚„Ò‹{¤‰=IõÇù÷ÿ9©ÊHŒœsÇùÿ>ôíŠ?„~_çÐT1.ËÐßÔŸ^ÏFK¼Q;¨u#ô¨„'qãÛüÿŸÏ'—*ã8ìùÿ?¢ ]~ðãÜcüÿŸ| ý´Þ¨™T/AІ_–@G×üÿŸç‚áp;©çüÿp’‘ yÇQƒþÏàDšzŽM5¡5™º ñëþÏó<¹XO„ÿŸóøårù›ÈžŠ‚ î'¶:ÿŸóüÌôš°âî®QE"‚Š( Š( Š( Š( Š( Š( ~¾†™Ü?_óþ—@÷áèi}Ãõÿ?çùtЇñ!ûÔÿüÿϨ 2žŒÐÔF$ÎsþÏùÎK¢•‡×üÿŸþ¹BRnÄ»”núÿŸQFõ?Ä??óê*Pó?çóþO#(IT õÏ?_óþO%s2z(¢¤Ð(¢Š(¢Š*âNG·øŸ^ÓÕw!fÉ8çáþ}{THžÅŠ(‡4T–#F­Ô~5]•¡`Aúóþö[4`ôªNÄÊ7[rƒI!Â7~1Q|Ð7ªŸóþã¥mÑ‚ãüÿŸÏ¥Ô\Ú>án8'ÔÿŸçþz™jæ ‘øŽÏ_ÿ^EL$Cчùÿ"‰'p‹V°´QEIaEPEPEPEPEPEP?ßCLƒî¯ùÿ?Ë {ðô4È>áúÿŸóüº èCøÛâü?Ïùÿë’?õÏøÿ?óþy …ÇFñÿ?çñË£‘‰$tÿ?çÿ®KvÔ”žŠÃåãüúŸóÔ“ýr~Ïüÿž ¼L_r‘íþÏ_®PDû,©ÿ?þ¿®MÏkQE¡EPEPP:ã?áÿÖÿ8âz‡þ^?ϧùÿ=*$O ÒvôõÇçüý$IƒgwËõ?çüþ8’£hýß—üÿŸóŒOqY­‰(ªáÞ,>QÛüÿŸèöœüÿÏùüðr±ó®£¤Ua󧱨¶œm<zŸóþëÄnü±#Ž ÿ?çòÂÉT{uÿ?‡ÿ«¨¥e¡ïÞ±!Uçüþ¦˜`SПǟóþ}NdFÜ€ÔS9$ éßßüÿŸC*÷±råµÈÆwa[’x õïÿ×ÿ?5ª¯µÓnÐsÔ÷ÿ?çêi‰þçüôíM\ˆ¾]ËR.JŒõÅ-flQEQEQEQEQE#ðô4È>áúÿŸóüº¿ßCLƒî¯ùÿ?Ë ®„?‰QE%»¿˜UOПóý ÒUcÔûžßç±ÿ/çÓüÿž„Ÿë“ðþçüò42×{õ3²cçüÿžC¥A–8‡ùíÿêì·ÃøÿŸóÿןî¯ùÿ?˨K ;ÝŠÌD[³Îùÿ8ü*0ÒíÝž~?ÏoÿWg¿z`óþqøPœAé€óø~tÕü…‰‹),sÏùÿ?þª}GÜ?_óþ—A%Kܨìü¼ŸOóþzMPÿËÇùôÿ?ç£]E.„ÔQEI`@aƒÒ¡AÝ8Çùý?OÀMPÛÿáþÏÿXRÙþ$MH˹H¥¢¤²IÃ(àãóþ b0Fù”“ŸËüçõ÷åÇ城çùÿŸÓÛ‰^5~£œc5£fI7·AÀ‚2A¨'ûãéþÏÿ¬&#»ß_óþ}åIN1Ï\V¶£o™Yˆ'^2õöÿ?ç¡ÃÕƒ åPI‚ÁP8àwÿ#ôöÈ"ŒzÒiXqm» ET–QEQEQEQE#ðô4È>áúÿŸóüº¿ßCLƒî¯ùÿ?Ë ®„?‰QE%;l˜¶?Î?Ïåù!}ò)Æ9çüñíÄ­*«m þçüþ"N¤ƒÏùÿ?ýq›ùY_q·ÃøÿŸóÿ× ’]ãÆzÿŸóéÎ&yc9çқ篡ÿ?çüäd[lµÞ üAé€?ÏùÇáQ‰v¦ÜvÆsþ}ý?q`ÀQš Ú ô¥~…8õLޏ~¿çüÿ.‚JÏ_CþÏùÁÃ’@ùÆxõ¡§¸âÖêùxÿ>Ÿçüôš¡ÿ—óéþÏAuºQE%…Coü_‡ùÿ?ýa1`½HZ†*x'§ùÿ==°)lÈ& IÀS&m©éž:ÿŸóéÖ’Ô¦ì®Eß&H÷ÿ?ç·å;¸Lg¿aQ +ê}?ÏùôíL„äöüÿÎ_|›jæi´¬ºŠYå<Ž˜íþÏÖXâØIÎIÿ?çÿ×O(ÀéEK}J=Y ¨T—RqßžŸçüö!c—vºúÿŸóúáŒí) =³ßüÿŸBßùÿëbªÚjB~ö…Š(¢³6 (¢€ (¢€ (¢€ (¢€øFúdpýÏùþ]ß„o¡¦A÷×üÿŸåÐWBĉ(¢Š’ÈH|‘ÿÖÿ?ŸæH•p1ÿëÿëþ¿ häÿœõÿ_~G`eR=9çßõ÷ÁÐÇ£õ áüÏùÿë™@^äúŸ_ÿ_B—ÃøÿŸóÿÖ+3+ ÁžßçßõïÐ¥Ðo©"r‹ô¡øFú”_¥Â7ÐÔõ4èG ‚¼Áôú‡ÿ« Kâü?Ïùÿë…•PäÏóíúvèßø¿óþúŸS5К¡ÿ—óéþÏIª`“?çóþG %K¡=Fóȑ߷ùÿ>¸Œ³ËÀ9Àÿ?çùH…Á<‘Û·ùÿ=† %¸¹œ¶ä9bFR?Ïùý ÀùIÈÿ?çÿÕ‰¨£™‘ÖF‹å#þÏÿ¯­½€^ϧâ$˜€¼Œ“ÐúTp¡-’8¿çüþ‚•·!Þü¥€6€=* P«n{v?çüö3–©£y#e#$çÓüÿŸÆ¥^åÊÖŽdR’É8«ÀÄ>=Ïùúþ%ÓŽAöÿ?çÿÖ]l.ovãeÆòAϯ·ùÇéíÖŒÈïÏóþN §üÿŸò2pP?Ïù÷ü 'ЉEêÙ$Dl\ägó§Õto-‡=zúcüÿž¦¬TÉYšÅÝQRPQEQEQEÂ7ÐÓ û‡ëþÏòèü#} 2¸~¿çüÿ.‚ºþ$IET–1¢W$’yÿ?çÿ®h¨ äðs×üÿŸ©§ÑNìžT5ãŒçŠo¾§üÿŸó“™(¢ìn)€ ŒŒQE!‘ù êÏùÿ8rF#Î3Í:ŠwbQH*PÓàñŸóý?Î8ž¡ÿ—óéþÏGeИ(^€¥QRXR;„4"¨' ã°?çÒ ù¥óÇùÿ?ìÒ]È”­°åV™·7Ÿóþ=.UÞ9Ççüûô2´è1M”f‹ê²dÍìÝ{c¯ùçüç/E‰½O8Ã~?ý×Þ£› »ŒÿžŸŸøõ4}Óž?Ïùÿëbß›3]ÒÊR™ÿ>ùÿ=ÈoQþÏéôÃpü¶>¸ÿ?çò¤!—ƒ‘‘ùÿŸóŸâ¦í7ÕCqÐUpwø÷9ÿ?çñ_-É AÆ~½Ïùþ%¹öüzÿž¿þ¾²»è1FXSÏùÿ'n-ÓQ˜8çšuLÍ! ¢Š*K (¢€ (¢€ (¢€2é‘UÖ9@W>ÿOóø}1bŠiØ—È6Lzä~?çÔþ_L&=r?óê/¦'¢Ÿ0¹r “¹ùõ?—ÓÉ\ÇüúŸËé‰è£˜9r³y‹ÄŒûÿ‡×üäa;t,}qÏòüɵE>ary•Âʼ>§üúŸËé|Çm»ˆ=òϯùÈÅŠ¾Y†2Ïóÿ=Äî' åËýÿÔÿŸóôÀc—{>Ùÿ?çðÄÕÎ6sþÏùÆRm¤·D£®ïÀÿŸóéü-U·w÷ÿ?çß,ñÈ`ýïçO§Ímйoªd¥lŒŸlŸóøTÉ?™ÿ?çÓŒI$…1’Ïùÿ"‘& €x'¿oóþ{Œ—vº +Ù±¸XþŸóí„så©Ç¯Ïø} Õ e§ÓüÿŸ¯æ'}Ç$’ÐÊ:©?‡ùÿ?ª4¯‚¬½F:Ÿóøfz)]v+îCoÎ}ºŸóýLÔQI»”••‚£9ÀÏ­RQEQEQEQEQEQEQEQEQEQET3¯CbÏùþFj †êúÓNÌRWV+æIztÆ:Ÿóõ•"sÔÿŸóÿë4ðè1E6ÉQ¶¬¯"má=Goóþ}æ)]Ùâœ@#dªÈU¶žÿ¯ùÏùþ&½íÄïPäl„‘•ïŸóþœl‘Á=»ŸóÜåè›Ï­-'-tŽš$Œ‡œ_óþšÅóH[uúŸóêet0i0™Æyõ§uar»Ž¢Š* Š( Š( Š( Š( Š( Š( Š( Š( Š( Š( Š( Š( Š( Š( Š( Š( Š( Š( Š( Š( Š( Š( Š( Š( Š( ÿÙ./CBFlib-0.9.2.2/html_graphics/cbflibbutton.jpg0000755000076500007650000000475711603702104017617 0ustar yayayayaÿØÿàJFIFHHÿþ AppleMark ÿÛ„   % #!,!#'(***.1-)1%)*(  (((((((((((((((((((((((((((((((((((((((((((((((((((ÿÄ¢  }!1AQa"q2‘¡#B±ÁRÑð$3br‚ %&'()*456789:CDEFGHIJSTUVWXYZcdefghijstuvwxyzƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚáâãäåæçèéêñòóôõö÷øùúw!1AQaq"2B‘¡±Á #3RðbrÑ $4á%ñ&'()*56789:CDEFGHIJSTUVWXYZcdefghijstuvwxyz‚ƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚâãäåæçèéêòóôõö÷øùúÿÀ#X"ÿÚ ?ö½/Ãö·Ö1\I$Áß9 Ã==ªßü"¶?óÖãþú_ð¦[j ¤xJmI£2­¼Ó”‚nlgßä¾ ðyøª—Ú爵kÖ‘.|¥HX¿('r c¾xäÄb}Œ£Ç™Ëdz˜< kÒz³ä„l¯k»¿-Gñ™«[ÜyfiÊ<—2¢ˆÝÉÀÛýÏZÄ£U×4âÒÿ«>_œqûÎy}EfXø3Ä>k÷PûVŽâEÓ¥'˜Ü(s°l2Ž2;ñ^_á'CÔ[QNfU]ÓˆþLÇt'’T}yǃ˜c1>ÒÔg(8¥x¨Åïͪºw^ŸÊúíÛ…Ê)Uu¤ê§8Ù¤Ýù¼”•š¶«]ûoí‡E»v}ì%RD“ lA;X63¼úU û[í1uiqf&šX-bŒÚ•…ZIdþóåS¸‚2Uzžø¨Å¤ø‡TÓ,oÚûE†ÛÏ2ùL9]»œ(õb ôPs…ÈxSFѵf¸¾¤¶!^8âÌÉÞÝ—ùÈ]£#޽s€|Ï1­R_ZªåMr«r%Ìž®/Eki~ªéèv<ƒIJväQiò¶ýëÛKÝ5Øõ[øotk'¹Ôt{CH%ՅùŽ%!ÉØÉò À!bÜà­tšššÜñNëåER#Á&ï7y›$|£äû¿7_¼kÊõíËÃÔ[E¿MNÃSh ¸‘n‘Œ2$žb *üÃo‘‚Tàîùr'Ômí|!£Ú^[ܶÿßÛK ëm³L$Lí9 û²282ç8ùO§€Çâ(+ÊNq“z=Û²Öí¶­k5¦Šö9–AN§,¨OG>O‡—ì¹^×]vOógÐÿðŠØÿÏ[ûéÂøElç­Çýô¿á^'ñXºâ‹y}Ö²KvÛlY˪ÊÍX.æäLþ5é^ø­g«ë«¢_éWš=ܧâä}þ¸`$cGQž™ú*¯WdÒk]ïþ_©ËW'¯<1ýäÓoM¬íÞïî0¾2ÙŸøN9l.&Fº»[iwm;£hä$tã;E|ÿ_D|ÿ‘6ËþÂqÿè©kçzôúåt÷Õ¼u§Dê’^ZO³tRû”íÍy‡ÃOé~¶Õt/ÉqeuÓH…™IÚ«œœg1Íz÷‡ÿäoÿÿÐ;Rðþ¬²¾¥¥ÙÞº®ÕyàWeÎ# W-z2”£R›÷£}ög©ƒÆS§Fxzñn³ÑÙ¦»\óÇ7þ6ÕÝÍ´6Ú-µÛ 9mæÌþ[€îÀù còñÀϯ”xgþo³±×÷™~ÕОg1`îÉ^1œ™ãÈú;ZÓÞÚÀiÖd[Ú+tƒŠ08þ'Ã98‘ËÏáMêT™ü$YÕ·)j›ÉÁù‡ç+÷ºn9ÆÙ6üž:–:ž)ÊpE(­`¾9û½;ߣ×Ðôð¹¶Š­§N2q·,­/w«o¿SÍ|‹'ˆµ?ìE˜iBÊd”³ù`«+ìHç¿ÇËš­ðëÃún¸·çP²^TÖȤ¼‹å«³8B3Ðuéמ‡ÕãK-*Â]ºUô6²$±8óHÀW9%·(d‚;#mÂÔ-t‹=9m¬4¨`715Á‹N‘™ãÛÊ¥ÛåÎ1È=Ö¸ªb1?ëJp»Vº²IY·¾úZÉj­wÐu3¸¸V•iJ0JJ^õâÞí-[½¯ø÷àÐ-<5s§øZÍ傤žòæ&2CB™XÏ–Q±IÆI!{òš­¥Ô¾Ñ/f ¶°n‚Øvgyfi8H@ÝÏ €Iõ]jêïPÑ›NÓt)­íd¸º¶ˆÇºRÝ›s>à¡‘FJ“ÀÁ¿§x>;Û³ÛÙˆtÛ+tX!¿µ 'ptU`»·YÛqÉïžWF.+’›²“|Ï^›9-íß–ú7kºyä0±„*ÞsçæßV¹Zë¿ùöéçß'µÒþ ifFhàÏ8\¦&f#ñÆûÖ—ˆõk?|RÐgÐ.æ("„<ˆŒ¿uÞFàýÒÔãÚ»ñànf‰¯d´f‰Ð‹­$çËû¬ }Æ9'…#ø·tÚw‡t"F–ÃO·¶vÏÍJ§œg2sާ&¾‚žSˆ§‡t\ÓºI·vôë׻ѽtØŠ9åN¥%(EÅj­¯•¯§õsÏþ?ÿÈ›eÿa8ÿôTµó½}ñÿþDÛ/û Çÿ¢¥¯ëé™$¸¹šîy..$if‘·;±É&£¢Š(¢Š±¥jZn»¤Ëi1‰ÚíTÈÁ8 û€ ì¼âÍrokVòê2IGs€áXþî5)’FN­p¶ÿòÒ?ëõô®‹À¿ò£k wóeØ5½Jm?^Ód½•¬áfÂ[åQóœ}2z}=qç¥tVŸó1ÿ¼ßû5s§¡§Zƒ¼U®›~ošJïÎÉ+öK±Ë€œœj&öQ·—¹ù¶ý]Å¢Š)ÐQEÿÙ./CBFlib-0.9.2.2/html_graphics/noticeButton.jpg0000644000076500007650000000451711603702104017606 0ustar yayayayaÿØÿàJFIFHHÿþ AppleMark ÿÛ„   % #!,!#'(***.1-)1%)*(  (((((((((((((((((((((((((((((((((((((((((((((((((((ÿÄ¢  }!1AQa"q2‘¡#B±ÁRÑð$3br‚ %&'()*456789:CDEFGHIJSTUVWXYZcdefghijstuvwxyzƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚáâãäåæçèéêñòóôõö÷øùúw!1AQaq"2B‘¡±Á #3RðbrÑ $4á%ñ&'()*56789:CDEFGHIJSTUVWXYZcdefghijstuvwxyz‚ƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚâãäåæçèéêòóôõö÷øùúÿÀ#X"ÿÚ ?ö'ö—ú|W2É2»îÈVáˆôö«ŸðˆØÏ[ûéøš³áöTÑ w`ª¡É$à¸×Ï^øªZøâ RûP»–ÂâêD’3+¶»€§€°l\˜œTpÉ9+úy¶_•ÕǬ©¿_×}?ß?á°ÿž·÷Òÿñ4Â#aÿ=n?ï¥ÿâkΟU½Õþ7ý’+ë…±²P¾RLQN"ùI¾wìGb¹5Ôx—⾑áýQ´›{;½Vú2|Øí"< Ì9$/'FAuJi»(Û^÷¾ßpç”â©Â𿔢¥eÑ>æïü"6óÖãþú_þ&øDl?ç­Çýô¿üMeøOâf“â騅 {«kÛ(|ɬä@Ò6Íå€rø#äp3\ñVÕþ%°êcMóB}‚<¿ÙøXÙœ·n¹ãܯ¡FŸ´nëËúô,Ÿ9UŒ£Êà®ïø%ë÷§ÿ‡üõ¸ÿ¾—ÿ‰£þùëqÿ}/ÿ\?ˆ®´ýo⥆”o58.ìDÇ †·m£Ï¾`Aû£¡Ûô­ß|TÒ¼9ªdCgwª_¨Ý,VŠ–ÜsÎrœŒu"šÆÓç©h£m}oóèfòÊÒöq¤œ¥(óZÖ²èﵼͿøDl?ç­Çýô¿üMðˆØÏ[ûéøš§àψW­n&´Žkg´ çÇq´mÈÎAåx<œté\ÕçÇM ‰…¦—¨ÞÙ[È#–ò5Pƒ,@#ž„#;IÇâ5xª*<ÎJÄC+ÆÎ¬©F›æ®»_o¿§ro‰:t~ð­ÅÝÅÂNò$AòÐÇ“88Ï?×âÚú§ýuü “ÿНjø‡¯Øø“á’jº{HÖ÷SG´:ÊCÊñéèNF|*µ\³WZœRŒéIÂZ5£^gÑšö¢ºWÃJè’Ù%‰H8!¤bŠ6åvÞ {j1G)¹·»{àݱñê6¨nyùN8#>á¤ØÚj>†ÚöÚ+˜~èæ@ê~fìkN+H-¤VÐ¥³ *€!¨ÇL×+ ,EhIÛ–7ûì×ë–DZÍ^ ‚…5ïs©7ÒÉmóÔñP\_ë:Öµ3ù×–r2ìä³z;¾Õ›ð»Äú/…µ nçÄ­$:«¶ÕY >a`Xºg#Æw éÇ¿Yi–:j²XÙÁjŒÅŠÃ@I9'¹ª·žÐõ ¯¶^hÖ7YÏ–Ùøéóž+’9lÔ5µù¹­ÓN[tþêèwTÎè׫_ÚÓ|•V&”zmשå? í§»×|Eã{‹Y!µ¸3<_.w†vw 3ÎQîràÔ§¶ŸUÖ¥žd7÷ Hˆr_h'{däà™_NøãÛ#¶‚¼p¢Âo–mÆ1Œ}*•‡‡tm*v¸Óô«;9˜ažÞŒ°÷À§¾²Qri¾u'Ûìí§D»-{_L+g0­ D\çQQ·E×©äŸ ëÿ¼I®.$·GFÍÉäùÉÎv¡éÛÐq\ÿ€<]¦x_Sñ¯â%kN[e»ÂáÞMÌΙçi/·;ºc¿o l´« 5¥{+8-Œ¸ßåF8úU{Ÿ hw—FîçG±–äÿËw·Bÿ÷Ö3ÿë4¥—TjRm99su¶–²n×Ý_n¬ÙçT*J¤jS|’Œb¬ÕÒKÚÚõ<Êîâ [á·ˆµÝ#ÂÃF{¤Â›w¦ˆ?Ï!FѵåÏû9çWži×ÚT>ŽÅ¼S©£Ý–Ž}&ÖÄ> l†Ë2©(à6NGNqõª Ú (€¬¸<- ÚÜý®ÛF±·¸É>t6êŽsוóÜw¢®]VQ‹Msnú/Á=—ßä<.yJŒgSvræZ¦ôVI¹'µ–«S̼G¢Gáÿ„0YÆ÷{Zá$Ûp¸q¹‹me‚ã=P;œW×Ðÿ·Â>ínÈÎF{zsŠùâ½\5aJ4ï{~{¾ý|ÙóuëJ½YUžòw4$×õydiS»˜± ;(Éö{TcXÔ€EØýÀ'o—ŒqÏqT讃çöΨ #S¼ÉK}¡ò@éÎsÜþt.±©) ºØ#8"vîr{÷<Õ:(èÖuER«©^($Ÿ–áÇ'’zÐuPN¥xH9Ü9ÁÆ8çŽ?R¢€..±©) ºØ#8"vîr{÷<кƤ›vê7k±v®'o”qÀçÀüªquI6íÔn×bí\Nß(ãÏùPºÆ¤›vê7k±v®'o”qÀçÀüª<××w¬s]M,h0ªò =éÐ~UPÿÙ./CBFlib-0.9.2.2/html_graphics/cbflibbig.jpg0000755000076500007650000003423111603702104017033 0ustar yayayayaÿØÿàJFIFHHÿþ AppleMark ÿÛ„   % #!,!#'(***.1-)1%)*(  (((((((((((((((((((((((((((((((((((((((((((((((((((ÿÄ¢  }!1AQa"q2‘¡#B±ÁRÑð$3br‚ %&'()*456789:CDEFGHIJSTUVWXYZcdefghijstuvwxyzƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚáâãäåæçèéêñòóôõö÷øùúw!1AQaq"2B‘¡±Á #3RðbrÑ $4á%ñ&'()*56789:CDEFGHIJSTUVWXYZcdefghijstuvwxyz‚ƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚâãäåæçèéêòóôõö÷øùúÿÀ 8"ÿÚ ?úFŠ( Š( Š( Š( Š( Š( Š( É"CË+¬q¢–gc€ u$öÛ{˜.áYí¦Žx[;d‰Ã)ÁÁÁõÍ|E¿û…î4Š÷N°+!ÇS¹ç¡Uaø×a¦ëþXµBÂXck‹W1 e”©ëÎGa¸ÜÖ’–Œ ñU76Ôy´NÖ¾½7<ºøÚ´ñ:nqŠNVÝ^öӮǮÑ\nñÊþQgªÆ4ÛµÈf‘± ŒžTç<Ld“Š­ãÿÌHðÖ›–îéGœÈü¢žvpx$ œñ´÷Ï}V¢Ÿ,ýÕk¶öK«¾ÖEK3ÃûZ›æée»}·»0£²h\ÆëäHpÀàŒ…õ¨¿áaxcþ‚ù//ÿ\Ž“ekyâ}¦ÚöÞ¶ß60ØËÉœf·?±´¿úÚß…ÿ ðón#Ëò¼dðu)NN<º§k.Þg„Žc‹¢«BPI·º•ômwò4¿áaxcþ‚ù//ÿGü,/ ÐOÿ%åÿâk7ûKÿ m§ýø_ð£ûKÿ m§ýø_ð¯/ýuÊÿçÅOü ?äu}O3þzt¿ù#Kþ†?è'ÿ’òÿñ4ÂÂðÇýÿò^_þ&³±´¿úÚß…ÿ ?±´¿úÚß…ÿ ?×\¯þ|TÿÀ£þAõ<ÏùéýÒÿä/øX^ÿ ŸþKËÿÄÑÿ ÃôÿÉyøšÍþÆÒÿèiÿ~ü(þÆÒÿèiÿ~ü(ÿ]r¿ùñSÿùÔó?ç§÷Kÿ’0¼{â}7_]6ÎÇPÝl%g¹>K · €_þ¡ÿ ~‡ÿ?ßù Oþ&®ÿciô ´ÿ¿ þciô ´ÿ¿ þåfüC“fñ¥ ôª¥Nöå”Åk·x¾Ëî#€Ì°õjUŒàÜí{©tVV÷Œ [Q𮲹º"EYcÜãîàþ õ5KA—ú,ïpú˜¹”ŒFÆÖEòúçzñþMuŸØÚ_ým?ïÂÿ…ØÚ_ým?ïÂÿ…cO?Ëi`¥€„±Ê[ÇžžÛÙ7 ¤ú¤Ò}w&yf.x…‰”is®¼³ü}ë7Ù½ºañNq4pÅyºI")ÆI8«NhRâ!•wG"”aœdƒ^mñrÊÖÓÃÓýšÚ7Y]nò£ œ ÆqXO௞µº]#ÅÖú´+.ø£žA%Ä •Psp„' í6 'œ±X\67YÓöœÍ*]8Ê×RŒR[_o™Û„Åâ*T­C“pi{©ÙÝ_fßs·Á7†Gµ—Q)¦ L«¹bO@HÀPÛxÝÏÒºM7E±ÒS°|a¥n]ºg'ðjò‹Ÿ¼+öÖñ_€ Cn#&âÓÌŠƒc–—÷¨Ù,€`Œ9'oMý¡¼};Epu5Ý[V9(ò™ÎyÏLpyé3züK˜ÒQ¬Üéÿq¦Ÿ›QÕ¿_`òì¿ .jq´»½×¥öùO-„šd2Ï ØÜ3ò«œþ!ɯL²»Kû;{ȃ,w,ªrF}ù¯6—YÑügáëÏì=RÚÿ÷))[géŸU“ï);HÃzñÆ)4Ÿx¶ÞÊ×O¶ÑѾÍÏ2ê&]À ¨ávŒrx'éõ\+ˆƒÉý†"j¥9i7ËhÉ'zÝoý3ÌÆO까§ÊÚ©ü*ú¦×O#Ô(¯7þÑñåìÒIö›]=xÛÄeéÛ‡=³ÉïÅAáyü@þ6—ºŒ÷K ¼· 'o+8œ nuà>‚¾“<&&s§G Ê1æj.úiÕiÕ-äK0”e*JRå»Vü/=–‡§ÑE'ªQEQEQEQEQEQEQEUmKR³ÑìgÔ5 „¶µ·]ÒJýþd“€ä’æ¼ÃWøû¤ÚÍåéZMΠªÌ­,Ò€~V^y<…#Ž=2©Z?ØîÂeø¬gð åç²ûÞ‡¬Q_>ÂüñGüøi÷æ_þ9WtïÚT‹ÌþÒÑ-.s/ìÒ´zç;·ç·¦0zçŽu¢úž´¸g2Jê)ü×ëc«Ðäañ7ý~ŸýJè«€ðwŒ4}O\Ö\\}•ïî|Ëx®pŒà»`H-ó€s×§‡í|IãmFÎòI£-ÖPa`@Œw˜×Éf<3î#ÄÁU䊄eÍËÍ{FœZµ×Wߥ”‹ÅdøTêÑ|òœ•›åÞRiÞÏ¢üN²Šäçðý¯†üm§YÙÉ4‘½»JLÌ ÉÀqòŠ¥ñúÓO}"[õ­L®²}œû~\ãmG/xŸv¤ùù-kséËͯÃÝoätá³ F&„åN…êFJ**[¿w­¿½Û¡ÜÑ^+ªø›Âg_숵¿´o¾Ø°ìÛƒœm9Îqú×Wÿ Ãÿóç©ߨÿøºçÍøi`•7ƒ­í¹¯w—–Ö·Úw½ßÜ{x<mZR|+…­mo{ßÉmúýÀÂãðÿüùê_÷ê?þ.ø\~ÿŸ=KþýGÿÅ׃ý—ÿŸLô?²ñ¿óéýÇéß<1¨mWº–ÊF“b¥ÔDg8ä²å@ç©#9âºØ¥Žx’hdY"‘C#¡Ê°<‚ê+’¶µj±kÕ•°õ¨;U‹^¨}U{ûÈôë›Ùƒ4VмÎeˆPIÆ{ñX¤ä쌒rvGñ—þEéëÊïÿ@ê)ÆÞØÁôÇÜç¶>¼}MxWüu¦x¯J{;.ã‘­çˆÑ@˨£8æ»%øÓáÑ·ý S#¤Qñ÷yÿX=;`ûšý½ ’Éð4÷àªs.×ÕýV§>$ÌcŒÄÎT]¤ão;E'øž†œmíŒL}Î{cëÇÔÖ6±áøqÖ4K é š{u2¬g+à2}æ ‚¸$Ù®U~4øtmÿBÔÆé|}ÞÖNØ>æ…øÓáÑ·ý S#¤Qñ÷yÿX=;`ûšòa„ÅA©F-?ëüÿ­OIå8çÿ.™ÁxßáÆ¥ð¿PÆÿD©imûvžÌÒˆãÂîc“¹âoâ•8`p2ž­à¯YøßöºÕšy>nRks v‚E8d$~dU”àgƒ7Æ ]Û½­Ö™=¼ªc–)-âdu Áã9äšñ˜µ±ðÛÄ÷÷ƒZs Ë³í:]ó`°-‚€‚ÙÚNQÏ̹ÁÜ7ošP䪭Z? ŸÚ_Êß~Íúw2–Yç7Mò­_—™õ%b|;XïõýwS¼…HŽ"O‰yà"ãÐUy|g`þ _YîšÖ[u–%Yƒ1 °ØÊ±Ãx Ž¢¹¯|[м7¥Mgyi¨É#Ü4 Ãd`ªŽî9ùMz<aibêV|²|°KÑÞ_¡ãb²Ìn?BT)¹B.Mµµì’[ùÜ÷+Â3Ó|kc=暳İKåÖnt{ÛMFK‹m»Úã(w a‚\Œ;UÎq‚¼Ž\>¶*nbä÷Ó±ÝÑ^w¦|lðæ«©YéÐYj‹5Üém$Q… ì‰ ÆO¥z%© šÅÜxœ%|+Q¯û…QVr…Q@Q@gëÚÝŸ‡4‹­Zýœ[[(fò×s1$P=I sÏ$kB¼㧉åºÕáðä2¡µ³TžtCyìcÔ`F8ùÎr@Æêû*nG©•`?=7~‹ò8xËQñ¦¨ooO—y[kUl¤ {V8nþÀ9ê+ؾøÖÞÆß[Ôí–[ÉXOj îX“+`q¸ç<ç/Cšøü~>Jn­][éÝŸªb+áòÌ2²²Z$¿¯½ž[m k°-Å®“}q çl‘[;+`ààƒÈ"ªÜÚÜYNÖ÷PKo2ctr¡V\ŒŒƒÏB+ë‹m cuÁ9àíSüÿúÔšŸ†4}bÑí/ìc¸…³Ãäí8#ržÇàŽEm„¡™Ö´©J1O£“æüšûíò>aqlTí:zy?êÿòz§ÂOÃo®K±s$·—)å[Ï+’dÉ\£1<Ÿ”m霑Ÿº+‚ñFŽš¿§DÎðA;¤O!™3Žü{}+.)d‚Tš9#`ÈèHe#A uTUèJQ„œ&®¯ú>;/]û3è1lwƒŒ´”]¥Ùôkª}]Ó>ñ#ø¤ºœ«Xäûû\_ÆøðÒ¿ë´ŸÈWY¦'öúh>"Äeß¾’WæC•^N6¹as“‘\ÇÆ[vm#N¸lŽä¡òÊHÿÐOé^#5¥Íð•¶q¥(Iv—ïU¾wVòk­ÏÌò<l6:Tæ·¬šô÷+?¸ñê(¯\øS¢éz‡®f½Óm.¤[ÖPóÀ®ÀlCŒ‘Ó“ù×f7k%sõŒn.8:>ÖJç‘Ñ_JÂ-áÿúi¿øøS%ð—‡f‰âmO êT”¶ElB ûŽkÂÿY(ÿÏ·øúÉGþ}¿Àùºº_xÊï·¨ ’ɦÉ&ë‹eÇÍÁ—#‚8k¢Šî>ØYê>!¹†öÒ ¨Öɘ$ñ‡Pw ÎëÉüëôÌMu‡£*­^ÇéxšëFUZ½ŽŠúa<#áçÿbi£žÐãàdO~øõæ~9ñ¾šy.¾Ø]éH߻Ԡ’3O—À„˜‰.«†À-¥€Íy˜lΦ*J4h¶ß÷¢¿6š—ÐŽðg™×UðÓþGm3þÚÿè§®š‰àÑ¢ÔÅ­œÏ'`‹LCr²@QýK;X+1¦øyâK¿É©§|8Ó´›åF¦÷h„à…-VÌp[ÑIVRÀÑŒÄb~©QÔ àšjòqZµÒí7ò¹…~$Ã×¥:Qƒ¼“_z±ƒñŦŸãX¼?û´ÍOIˆÍòÒiX:u¾@¨ê8R8zöÿ‰Ú—&ƒ¨ërXA&¦‘A wN›ž4tB~î|ÇÉ'89ÀLjUäÕ©UÁÇÙÆÜº?6’×î²ùÜ6šÂNÿÌÿ(žÕðwþE›¯úÿý>âã[ÐuK=7M×n®®XÒß»Bß*®Öb¿˜àýðwþE›¯úÿý:ê6Vjì²µÿž²° æÉîVÜ7>AÊœðÜàƒW…qðù¦*Uë(Á¸Ç•¥ïI©rêõJ6w·u}ËxÞJ˜§ì Ü“o™6¹Rå¾Ú]ékög‰×ðwþFk¯úðýkøBiWÏðÞS•ƒMPèœ`î#p[# ÐsÎcàKï kòíÑâ´²Õ<–y ‚È«$aÀûûTr‡þÕ–oźr¡F*jJ×S†þœ×üÐ+ç%…« ­å $¶êãoÆç¡iŸñåãüÍ|ÙñwþJ±ÿlôDuôÅ´fbÝ»nyÆ;æ¾gø»ÿ%Xÿ¶?ú":õ}”èåÔ)TV”TSõQ³<ÞiæþWÿ¥Dçü-ÿ#6ÿ_ðèůªt_ùoÿþµò·…¿äfÑ¿ëþýµô«x“GðÕ¼·¾¡ š66$»óƒµY±¸gã95ó©¥á›í/ý%žBu'A]µ²ÕîuW˜ÿÂüð¿üøjÿ÷æ/þ9]‡¾'ø[ÄÚ‡Ù®åû¶·‹å¹;¶…*±<ôàãîc^””‘òr¬uóΔ’ô:ê(¢¶<ТŠ(¯‘©E}÷ÿ#CAÓµõ« <¬¬—¢?”2Á ùˆàô\œöÅ}O¤À%¸.Ã+ÏãÛú×Î_ ?ävÓ?í¯þŠzú_FP ‘ñóÁ?@?Ä×ȺKaéOáŠrüÿTŠâª­TŒ;/ÍÿÀ4h¢Šýø3ÇãðΑâ/ëÿÚ–Ÿiò/_Ëýã¦ÝÎùû¤g ëWáYøKþ?ù37ÿV4ù|Mÿ_§ÿC’º*ü·ŒqxŠyåh¤’´4M¯ùw«‡ñxŠyt# ’JóÑ6¾ÜŠšf™i£ÙEac“mv&âØÉ$òI=I® ã-Ã.‘§[€6Ir\žùU èGô¯H¯2øÏÿWýv“ù ñr%ís(:šé7¯~Y;ýúžö¤¾¹JMêåÅ«žG^¹ð§ZÒôï\Ã{©ZZÈ׬Á'QˆØƒ8'§ò¯#¢¾×„Ž2²“±ú.7 ee'cÛá6Ô>Ïö´h;6oÇÛâߌgîy»³íŒöÅmi2Òo4èg½Õ´Ø.vøþÒ‹Œ1‚ÙéŠùâŠyŽŒ¢©Ò¡M;Þ7½¬ôÕ¾÷ù#…à凩Ï,Tæ­kJÛ鮉Œ¼yqâ{X´ó¥yˆŒ¤°c“Ó Ï^F(¤žT†ÚI$`¨ˆ f'€M2»¯†··½ ¬ šŠÈd¶žá€·Œ(ãœã~K°Çʸ õx‰Ã JU(Ҳߖ+OønçÒÒ¡ §©ÒRŸ*묛îöùÙiÑt=_šKh~Óô÷ ²E2«0%]‰g`3=½iþ)ÿ‘gYÿ¯ ÿô[V­ex§þEgþ¼'ÿÑm_™Âr©ˆS–îWûÙ𛩈S–îWûÙó]wÿäfºÿ¯ÿÑ‘×E~Š¡õŠ¥{]n~™Š¡õŠ¥{]n}aùWžž½9^zñõãëÚ’kh.íÞÖêç·•6KªX(!ãã>¦¾P¢¼xd¼±Qö›yÁ>Yð¿ý>ÿÉûc±Ð¼áÃñçÄ:SèÖ²iö– u¤‰º‘ÒÇaã½|) {Å|­^ÿðÓþD3þÚÿè×®"ÃÏ–yM»%z-^ýmÿó1Ù*˨ªžÓšîÛ[»îûÄ¿ùu?ûeÿ£R¼½ÿâ_ü‰:Ÿý²ÿÑ©^]œ9þé/ñ?ÉEÿî’ÿü‘í_äYºÿ¯÷ÿÑq× Áqñ¤°ÌPñ8`:r¤Oò<ûàïü‹7_õþÿú.:µ6¬øIÍÖ—;ÜÙ&çhߢtä¨<œù†:s\ôrú†;FU•:·\ŠZ)ouÍÑíË}Þ›Ù¯‚â<]L&6u7(]ó5¼v³·U½û^ƒðjGÄ÷eýÆTãþZG^}]ÿÁßù®¿ëÁÿôduíærqÁÔqvv?NÍܪúCiwq\Bb ,ñ­@á2N7£#¦kæÿ‹¿òPõûcÿ¢#¯¢´K­£žåB÷n@ÎJ‚ (Ú:dõ>¼ |ëñwþJ±ÿlôDuîÅß,ûß݇ß˯â|7 shTæþY}ÜÊßÊéw¿Ùš÷—æý–t›fìnÚÀã=³ŠeõýÖ§w-íìÍ=Ä͹än¤ÿAØÀ«×¿xÀ–º¥¼’[,Ú¼ <’:©hXŽQ ƒÏ'¦ð1غx;O—šrÑ%»þ¿Èû|ÃGk5y=ü?Eßäx õv¯àm'Ä6-kªÇæ’¤$¨xIÇ(Ä@ö8äÅ|ËâM  k·ÚEÁÜö²•€7©åœeH8ÏÅzTéâ%:ôùétÿ#Ÿ+Îhæ.PŠ´–¶òî`øSñ6çTa¡kR™®#Œ˜.]†éTu žY€ç<’'Kzð!€ ‚ ŽõñÆ™©\i…¶¡jÛf·:ò@8ê8# Žàšú×H¸Ü꼯ӿëüêð˜ùPÅÇ UÞ5å¿F·^mÙè´µ¾?‰2Úxjªµ%e.žkÍTQE}Aò!_êvéZ•æ;#Mi;Á#FIRÈÅIã#Ҿȯ™~.è‹¢øÞñ£TXoÕoU˜_!󞄺¹Àã}›˜FðRì}Ÿ WQÄT¢þÒOîÿ‡2|y‡Œ4©¥ ÊÓ@QÎdRƒðË ûWÔ:?üz¿ýt?ÈWÇñK$¤ÐÈÑÉGBC)‚èkéÿ‡Þ$‹Ä:Lƒh–dÛ2/ðJ¿yq“Üdçz×ÌA*9­ òÚIÃÑ»µ÷½þ+ÃIÆ5ÖÛ?ÏüΊ(¯¹?=<ÓAÿ‘‡Äßõúô9+¢¯Ÿ~ Þ}§Åº´J~H/gQþ÷˜sþ…sð|E”C1ÌêâaVÉò­¯ðÅEõî¯È8bªËi:Óå“»µ¯e)6º­lÕ×G¡õMy—ÆøðÒ¿ë´ŸÈWqá3ûÃÚu‡É’(ÍMÛ±!~rˆ·N=8®GãȾ²„·ïð:Œuý~uñÙ4½–gEÍñ/“Œ•úìµýz™àéÇëÔ⥢’×½žŸyã5è^ð—âkÛÙîã’;–„Bà*žêyùyí{WÁßùn¿ëýÿô\uõYÍj”0ŽtÝÑöùÍj”0ŽtÝщÿ_€ÿè3©~_ýªµ,þxbþÝ.m¯õ)!|ímè3ƒƒÁ=EuŸð—èóýÿ¤ÿâkNÎò ût¹¶2ÎÖÁÁÁàóÔW•™ÕÆá¨©û ôµµê;§£Ñ~êõßdôê¿6ÁçØÚÕ~¹ é´wõøå§Ëæ|õâ?[観Ô×Q‚NÄ-#zsGp{ãŒáW¼üP¹†ÞG#í{‰"Ž!‚w0pØöùU>•àÕï`1‘ÆÑö‹ŠNÞóRoÎê0^[t?Eȱ8¬NŸÔ¤›WK•5§K¿MÏyøkâµï»›Í¼³Ã#3†w\eY‡^„®Ns°œç5·âŸùuŸúðŸÿEµyÿÁ_ùÿÛý©^âŸùuŸúðŸÿEµ|F:”hæNÛ™?¾Ïõ>WJ4s'mÌŸßgúŸ5×Aàï ÿÂ[©Ëaöϲyp·ù^fpÊ1Œï~•Ï×ðwþFk¯úðý}Î>¬èágRÍ-¹ÇÕ,êAÙ¤k‚DäxœrкäJ_øR,3ÿÓÀÉÿBíëþ³ÜW­@~Uç£g¯NWž¼}xúö§§{cÓsžØúñõ5òÐÇã¥ý®þQÿ#àž{˜ÏÏÂ?äxª|)Ó¤Ô¥Ò£ñu«ê0 ’[5…LÑ©†dó2y#ø‡­z_†´OøGtK]+íiò7þ÷fÍÛœ·LœuÇZójR~Ñ^'ÙwyºjÁÙç•ÛzV]‘Ôllô5ì•ÏUÄEÂIóEÆ2Ù-ZòH櫙ⱔù+Jé>ËôG+ñ/þDOþÙèÔ¯¯ø—ÿ"N§ÿl¿ôjW€W·ÃŸî’ÿü‘ö;þé/ñ?ÉÕðwþE›¯úÿýhê+¸¾›ìZ/4‡iûFÌàgœ)@ÜÜuö5ðwþE›¯úÿýwf—g¤B±Zı«¾A‚íŒ|Äç–äñÛÓhó¥è¥ðäQÏâ&£Y#’ötq•`\=E}O£DY$8ùǯÓõ¯”4»ßìÍNÎûËó~Ë:M³v7m`qžÙÅ}_ Mñ¼‘H’$Š®ŒŒe9ÁuŽ}ëå5,ã æ½ß{ïIµøØú+RJégù£b¾yøí QxÊÝã¥ÓãyTí¾EÉõ8Uôv¯¡«æÏŒÚ¼Z¯æŠ…l KRé `ì2íÓ¡Ê‘Ï*~ƒìqÍ{/™ãð´dñ÷[(»þ_Px Êèº ùôøAÿ¿j¥|¿_Tø^Àé°éö!Ì¿d·XŒ›q»jmÎ9Æ­|^:n8ÌŽüëæ}µì!çùMQ_¡šq¼ÿ –…þŠ›µ[,½ždØ­’7¡Ï0^3Ž@ä ×iEDà§lÎŒ6"¦´kSv”¯Çf|c42ÛM$ÆñM’9«#‚<‚jÐÐ|E©øjú;Í6å¢eufŒ’c—ÀuèG'éž0kèˆ? ,üdÃP´•,5eRR™K€Ê‚ñ’8ñ-gá׊t;&ãHžu,Ê’Ú©™âr@9Üöà×Îâ¨{ûχ¹ú¦ 7Áf4¹fÒ“ZÅÿÁÝåŸít–è·¾†{òAtbCÏR¬Gþ#ý+ÄÿS†<ÿtc Vü;ð“Q»ŸÌ×[ì6ËbŠEi\à`‚2 sדÆ1Îk×,l-tË8¬¬¡X-á]©ôúžäžIä×Çæ¹Å(Ótpò¼ŸU²^½Î×8§nŽW“ê¶K×¹b¼Ëã?üxi_õÚOä+ÓkÎ>/ZÜ^ÛiZÁ-ÄÏ;…Ž$,Ä =H¯#‡yœí?ý"GÈa§b)JNËš;ÿ‰;]G†¼}ªxZÆK+(-$ŠIŒÄÎŒ[$Ù‡(¬æðŸˆ‘оƒ©« ÙÈò¦ÿÂ-âúj_ø'øWÚ×úµTéÖi®ÍŸ¥ÕxZðä¨Ó^¨ßÿ…™yýöì ýO“ö±·÷q¿vÿ½ß>´í;⦷¥ÙGg ­ƒGp^7'’OgµÏÂ-âúj_ø'øQÿ·ˆ?è©àŸá]¼\1Ôý–&¢œo{7×UÅžM,›$£>zt ­§o¿È‹W×u=zq>§{-Ë¯Ý p©ÀjŒÎp9Åg×QcðçÅ닦4JØßpëAœÊNà;ôÎ:f½#Â? ¬ôKˆ/o$:†¡̈«û¨Û:±8cŽÇh#5åÖ̰˜XrSi½”cß¶›xŒÏƒ§h´í²ü ©à?Íá¯GksÅÔÒ4ó¨`Á€‚eUÏ^s‚F+CÅ?ò,ë?õá?þ‹j“ûMÿá"ŸG0í6ðy’19%ŽÒÇl7çôå¾#ŠIü=«C m$’YL¨ˆ f%Ôׯâ¨b¨c"ñqå”­+y=½4éºê~yCf!ÖNþõŸªzýÛ4×ðwþFk¯úðýr¿ð‹xƒþ€Z—þÉþÜ|)ÑuM;Ä73^é·v±µ“(yàdRw¡ÆHëÁü«ì³:Ô僨”–ÝÏÐó:Ô僨”–ÝÏCñGŽtéÑÞë—¾O˜Ïöx#RòÌÊŠ?¸í‘–ã3ëŸþ74šm“øoÂìøšå]±"ØáŸåóÆUÆÄP2À9à0ï/þèº×ŽnüY¬N÷ÂW…âÓÊ„Œ'ï:™*­”qƒ¸Woo ¤[ÛÄÁ Ž(Ô*¢€ ŒWÎÃ2Âà¨AaãÏVÊò’Ò.Û%Õ®ïNÚ˜:r›|Ú#Çn?f¿¾µ¾­}¦¼µëªº9;r \a~VÚdo9fÀ‘cãÿü(’=7Æú\ú¾•æ•R™†c÷f9ÂÈÂ7Úø#%@½ö²üG6‹m¢^Oâ!jt˜=À»ŒI‚2¤Çv00I8Ç8¬¨çU«¿c¶‹{?‰7ü­j½6é Ý$µ†‡Ÿxóâ?‡5¯ G‹©Zê/©\,>Z˲hUw9v‰†üf ¼÷ÁÏLù]RѼ/7еíO_ð–qiáë ,Ï+’T&ÕûÅœçÌa’¿wwEÿ·ˆ?è©àŸá_a‡Ãárø{sójM]7ÑÛK¥m´>熫Çêrçi{ÏòGªüÿ‘fëþ¿ßÿEÇ]žƒ¬G¬iñ]!(ëòÊ ±ÆÜ•Éç=~Ÿ§'ð¦ÂóNðõÌ7¶“ÚÈ׬Á'‘ˆØƒ8#§òªúF£m¤ø™WK”Ícvé2àÇ–óŒ•9ÆsÁë“‘æ`ò¸æ³ÇªiûHZqfÊ÷‹–ÉËGÚî;«\ø>%Ì>©™ÆM®II§®ºÚÍ.©lýO®ÿàïüŒ×_õàÿú2:åáñýµ/ü“ü+¸øS¢êšwˆnf½Óníck&PóÀȤïCŒ‘׃ùWVgZœ°u’Û¹úŽgZœ°u’Û¹Ýêö¶„O|²N³ÁyœŸ‘IòAÈÙòónŒçøÀ¯ñœóÜø†y®d’YžrÏ.K7î’«ž;ãño¼}óYh-ôñ+Û£æå¶â†6Ê&àFÀ,œq¿µxw‰ü?«>¬f‡J»’màhäŠÝŠ>bˆpB~fPzòÀÄäûÙ~"XŒ†’•ß,’W³ÑCTºÙ=uÚèü×…Õ<6VR’ŠtÛ}5s¯}/oÔå«Ñüñ^o $VZ¬ÞÙGò¤‘°óbL}Ð 3Œr03ÉÐ|-¬néŸkЯ¾Íö¸¼ï:ÍölÞ7nÈÆ1œæµ|WðËWÓ.fºÒ¬ÞÿOy––¨òIž@eäàr7dôç^SÄa爅+ÞKÞ»¯ëæ¯}Ò±“ÀâÙ± 4ÕÖ¿¯GùŸˆ¾=ÛÉbðøwO¹ŽêE+ö‹À€BxÃ*ÁÎ3Ô€8a‘^-4ÒÜÍ$óÈòÍ+’I³;’I<’Oz޶ôOk~ xþÅa/“'"æE)¶“¸ðp{ žW~'§=i$—É…Á`òÊoÙÚ)îÛßæÿ"×<=7ˆ #sc»·ã¿jŸµƒà/6ÞL­þ¢„‘ŽŒá˜rù ¹çõoxFÏÁµÑlßÎò²ó\Â4ò1Ë9ð$ª£'¯§£N9=ˆª“¯/‚/ì¯æk¿dýziƒ~Õò­º–,´ˆ|3á„ÒôˆÊ¥¡Ž "–f ~b³7'ŽI'½cøqµÝn öxÄ»HòÉ8À8Çp=Ϲì+ÎtRÿNµºÑ¢ßæäe¢ÃJ™!ˆçÈ@ÿhä`ô+†©˜á1TéB·44ã;I¾m$žŠÉ½:ôvgÎçU£‡ÄÑIK’ÒÒ-«´•¶kWvvºeÕ¤÷Rð×Ïè|²a”ªÇ±8Ï<ôÉÖ­à±¹Óôý-mì&œª¼ð¾É£]ñª°!ÁbI9= ã­ðÜ 6Ímï>ϨC°³£HbGÜ¥äA»!ð g¡Û÷W‚¼ûØøš}VÕïì.âÖHö(š$!£;Ñ‘‚l1mÅTy~ËÃT°ØõˆÃWNšNñiFòI¨»E(É]·ª\»{Ú[ÍÆc1 ì«Ñ|ÎÖ’mèÝÚ»»NÊÞ{«±h~ ¶r°kÑI±XÌÌc ™9?1Ëdö=6ìÚy–º|O«Kn²Æ*±XÎJ€Nìc9ÿddðz Àiµí*xuøgŽ•[ ߺŒ°„G ’Ü7–x ÈÔß²x•mmm§µ»‘gheV»‚<Ž J†$,‚¤ùÎyq<9‹Çr,S¥ou¹F1R}$®–¼«äì¶ÔÚŽaK ÍìaRúÙ6ÚWÖ.Ïk¿žþD³ÏyªëÙv×j-÷¤ÊG8P-ßvWæÇ-Œyy$íÀ¦A§G¥1†ÖàÌ–Ë,j‹¸ùh €ç;‡÷ï1†ÞçNÜZ4qÇäÈ&_0¶8 ~\À\§ a·a?O¤é §&÷æäî"ÈÄ8-‘ÁüùɘîbÌÍô´)PÀÐ -8(¤â¢—3ÙÉú¥þwéÏ5|MWR²jWní·eü«ÒåìËOùåÿñ©`¶†Ûw”›wuäš–Šò)eø:3S¥F1’ꢓûÒ>•ÎMY²¬úm¼ìX©V'$©ëQ ÜKHqØ‘ÏéWè®z™>_Vn¤èÅ·ä5ViY1Á ¶$ ;ã©üiôQ^•:p¥ i$¶KDCmêŠ(«QEQEQEå·^ñ…®³ª\é–»a»ºyyË¹Šœ1ãƒIý™ñþyãÖÿã^§EkWêµçí+aiNZ]Ê ·eevü9_&¯R+]¬µwÚÇ–f|Cÿž_øõ¿øÑý™ñþyãÖÿã^§Eeìrÿú£ÿ‚âWölÿè&¯þÿòÏìψóËÿ·ÿ­¨/Žt«9/oG•o7¿î OR+×(¦¨å××Fßõî?äL²Ú¶|¸ª·ÿü7æx¦»â­CØÅÖÌoòmUöç¦p¼t?•jZ[øþö3$Vó*†Û‰£Š#Ÿ£€qÏZõª*çK,’õ„_èŒé嘕üL]Gé&¿Vxü“øÂßUƒJº¸Kk™ÐÈÖ&~nr ÿtÖ‡Ø|aÿA[Oûäñº½ñ2ßìwš>¶oòeòåmøÎt\~r×µlׯñ^&cÃÔÃah¨T‹ÑÒƒ÷¢õóÙ¯ëmòì$«U­F­jÁ«>ylÖŸŠg1öÐVÓþùün¹MKÅ<Ò`Yî<=­HŒáµ·µ¸làžV'bHÇOQ^ƒªë–Z<{®dËœm…0]ïŒôàòxâ©h^*·Ö¤h?³\R2ûƒcÏ·§ã Ìå„–?û6Œ¨Çw좾k«]Ýš]ltÔ¡‚…u†x©©½—´—ôŸe»<_VøÎÖš”+«éš¨½ÓÜH¶·VénÀü¬s•烜Ü_Šÿ¼BöKῇn—\M~²¼2©PÊË!"Œg’NìŒ{ûUW¿¾‡M´–îà‘C'hÉ<àõ$W+?¥™Ê(àcÍv)_–ò{(FËY;úùêzT0PÀÆu=£³ÖNNïEÕ¾Èñ—Ð~9ø–Öè]ë–:rÊql²¬n‹Ãd£°^ܾâÎAæÇü3ßö¥÷Ú¼QãMSZÛ–·l«Î@ß#IòŒ·ËÉÎ}}Fñ}ž© ‚dû$ìÛcFmÁþƒì}±šèkŸ0ÅæùUg‡©IP—hÆ*뺖·õOɳ\-l.2Ÿ´£>uýnº|ÑÂi^Ñ>èw-¡Ç#]\²#Íw#HÓÌWpQ…gÆôÉ­8uŸ †i¼>÷0O ˵F9 È$ÀqØàò)÷vÀìO¯ÉMÅ*,‘º•daÀõw¥•­„f+;hm£-¸¤1„úàwà~Uu)á1£ U%S‘óFû]«j¶kÉž]|iâ=­® JÒ¶îÎú>Ìã´†ö–¤]ën5 ÂåŠn& r' ßÏÐÔ%sVÒÜ’Š‚+†wÚÀ úŸó¨ÐÓ[Š2RWAER((¢Š(¢Š(¢Š(¢Š(¢Š(¢Š(¢Š(¢Š(¢Š(¢Š(¢Š(¢› Ìl1Ÿ”ÿžôETŠ5KnÇ>™ÿ=Oçß'sþÉêÿ§ù÷ÿ9͸¥ÔÍJOT‹U²z¿éþ}ÿÎr}“ÕÿOóïþs•h÷iv,QUþÉêÿ§ù÷ÿ9ÉöOWý?Ï¿ùÎKG¸sK±bНöOWý?Ï¿ùÎO²z¿éþ}ÿÎrZ=Ú]†ÍóÜ=8güÿú½²¶5|nÇJ‡ìž¯úŸóœŸdõÓüûÿœæ´Ô”¥­ÖãL2DC'88ÿóøqµÐE¸—“9ÏB?_åþ@û'«þŸçßüç'Ù=_ôÿ>ÿç9wVÜ•žß‰b¡¸‹pÞ Žç·ùÿ=€ƒ¸_˜¯=?úÇ×õ휴«wÓrýHÿ?OóŒ®VµE9ÆJÒ#,€"q´t^?ÃéÛð?vXí@åÎxè8Çùãü‡¥ÄoœÓ?çüñê)êÊÃ*AƇ'è8Æ/­ÊÏû©ÁUã§aþGéíòÚª×c[ëßüÿ‘íát¸åH=ÿ_ðÿ88m&(µ4ÉèªÆìàü˜>ç§ùçòíÎ Í#@³ëþ/¨ÊÒ¹jqnÈšŠ(©,(¢Š(¢Š(¢Š(¢Š(¢Š(¢Š(¢Š(¢Š(¢Š(¦yÉÎ ltf—{Ï6üÇøÓ°ìÇSd†3òŸóÞ3”qøgùR3¬‘¾Òåè9ÿåBBiØe©ÌgŸâÿ?çùõ3T6§1ž‹üÿŸçÔÆ’NùÚs޽?úÞŸþ¯á¦®Ù”eh¢Õí!W9ÀÿëŸÇè,ⲫco_óÏýò¹]ìW=ÕÒ,ÑUÎCH1žpAïþ?ûæÏ›üô_·ŠM¾ƒ¨¦ù±ÿÏEüèócÿž‹ùÒ±Vc¨ à ‚=E„QEUq›‘ÆpÃßÓëëí×¶y²Ê¬0Àî*¬¤ ‘¸ŒnÉþŸ‡{>lóÑ:¹lŒàÞƒÚ2:øçùÿž¾¦£{SÎÖϱÿ?_Ïë™üØÿç¢þty±ÿÏEüèR’)ÓO¡U\ƒ¶]Ì3ÈÉÈ?ç§|²‘D0Ê ƒÐõ‡éùJŽa£!Ð7ÔsþÏp[ÀûŽ~„Ÿóþ[Õ]¸»4N@Ž6*àg§*UûÍ`qþ}¿ÏÓȦ#‚N2ã¿ùþAlQcÆáœ’Gcüþ·J_dÆ‘5ß6?ùè¿(‘à:“è E¬Å¢Š ÀÉàP ¢›æÇÿ=ó¥#R}¢Ã³Š(''@‚Šo›üô_ΔHŒpIô‹ÌZ(¢Q@Q@Q@0PYލ°\n“åN¡Çü)Äo“§ÊŸ©¥1ÝØtÿ™I­ì­€dôùTtévüýy¤w íEËc>ÃëM!æCŸEQÿשqŠW—âö/÷GåQË 2·OåFéS’»ÇÓŸþ½9™d‰ŠÀ©ÿ?äU%è„î•Èm¤Ú6·BI œçüÿõùëKiü‡ùÿ#ü‰!`OñdCë×üûõ,Šc±(Iã'§æ?¯ùI´ßfe¥£!ðóq'ãüÿúß§¶¤âå¹éþýoÓ¿e·;¦f#’áÏÿ[ôö¶FÅÃcžß˜ÿ?—¶UÏgèL~Ÿê>_õè:ôëÛ¯ÿ¯ðöÈŸiþñý*©“Í™1‚:÷ÿë~žß-ìA!W‘Ë{ý*%’¿æ\ïaÛO÷éFÓýãúS|ÆôOûïÿ­He+ÕAì¶k?s¿âkf žAÃzƒFöˆ!È=üiêÁÆGJ$]è@ëÛëWnÁ~ŒPAäsE18=Œã=)ô¢ï¾âe9A7Aè@?Ïøt/[†‰7ìùÿ?L£ô–ã·ôÿ?Ÿló<¤ŸxsŒgüÿžO­[³•Ÿdegvâ*Ã+&G¶)vŸïÒªm’/™OHúÿúÏÿ\œÊ—p=Îp3þsþHÌÊ]Ó{4M´ÿxþ• ñó»A¿Î3ô/2°á8ôoþµB÷avz÷þŸ_Ëé•[ïø„––cQÃ)W'Ôõ8ýnç·±+%±U$0 üŸþ·Ó òÊíc÷˜ä€zžÇ’ §mÐ3… ý*Ô’—ºôÿ‡%Físæá9'>Çüÿž™ö‡Ü twäÿŸjz¨QïÜúÐyqì3KI{Òrbl*B7€¤†ôÇ~£šš› Ìl1Ÿ”ÿžõM_A^Ȋ݈B6±ù§õ?ãß©x+¤|Û€'üûÓ-€hÉ ~½‡ùÿ¦m‹ýÑùRŸ3M4…¹t iUE äŸè?Ïÿ¬TõU‡úKqÛúŸÏ¶y¦½×è ÛbU¹F yú{ùÈÊo  òÌxèÔÉ@YÓ=»ÿõÿ_|1r‹òƒœIÿŸ_Oð5(¦¬B“IÜxºCÙ¿Î?ÇüäeæUXćîàÕ Ðª®v‘“Ž =sþ'ÿ¯œ×t*ÍÏCÄþCÿ×øÒæŽ›ýÌjê÷`&L’©c‘úuÿ?Ìfd•] ô¯åQ"l €Hãœóõõ>¿6 È›Êç,Aý?Ïæz”’»v°Óm«“ ÂDÒŸMûÍì¿ÎQvÙlªÃý%¸íý?ÏçÛ<Úª¬?Ò[ŽßÓüþ}³Íª·ñ|—êJê1~çü ÿèTÙmÕÁ*0Ý}ùþ§ÔåÆ2Úí×8ãÖŒ7÷Ÿÿ©æå“eJ*[•¢‹ÎÏÍ€=³Ÿóý{‚K[TTû£ý굸?6NWþŸãø™[z€w9äuÛëW)ÝÛôftà­qÓ&øÈÇ#‘ÆÏùëPÄÙ·zÛÔŸþ¿S`œ`Ѝtò)èAŸËùþ¾ùgÌ´¤Ó?}!ÜväçŒÿœzvìFi"BѼg `ñL’ßòúvý?ÏéÔq†¬ä²è§“c×üŽŸP«mZ"ché!³¨WÚ«~çüzûõ÷ÃY|y ´äl89Îx¦4+33ïŽ0~¿×üç0M•Æì’3Ó×Üþ~ÿ1 I[×óxÊöдcL€?ïšiŒ+!AÏeö4@,ÙÈ$sž8ÿ?ãÔ½þôïCYÚòzÿV6Œ›B©<籤—ýSÿºiW«} ¤—ýSÿºh†À·ýáô?Ò›(c³ow_N 8ýáô?Ò”œ žÝÿ]b%P®Ü|õ=ª@»~TÀÌùe¯«w Kƒ‡ÆF O.¾ó)݇oÍÚß¡úÒÇ.òU†ÖE>£‘~enÇå?ÐþΩ§otW¾Œ’ŠE$ŽzŽ -4 l¿êŸýÓN ŒŒE0B¼>‡úRJp™< ÃùŠlv>ØHÿ?J{®å+Ó#1øŸ¯ù³÷ÐZZb>ìÁ<èE>ˆõBaMf6ÏÊÏzuDä¸äìŒc¯¯j´+] jsçø¿Ïùþ}LÕ^`‡ÇžØþ¾½ýjDvÀN Çùõ©”Ö¬Q¢IU\pÄñÿêÿëþ½³Íª¢Vy“{}?Ïù&›v‹ô›ØlŒ­: Ž9üúþ¾ød¹pÅTdõ=Àþ¿ç¡•mÑX0-s×üÿŸ©ÊĉÉ#æaùœU¹(«ö!A´ïÔdò¤ˆœœúõ½Ççß¡W•M°äò£¨<ÿŸÇñ§›d9äóŸOñÿ<ÓÚ0ÊT“‚1Ö§™é§ãÿ|©Ý²$eû9RFpx?äú^½û¶÷ÄH8lðsô>¿çß© ¸Üã¨#ñÏçÔúšž4T\)$žMIÞ ¢ã$ĉò ƒÿ]>£ñü-‘ϰ'úÔ•œt|¦ŒªÃý%¸íý?ÏçÛ<Úª¬?Ò[ŽßÓüþ}³Íª·ñ|—êJê4Ȁ຃õ£Íþz/çH¿pã˜ÿèTí§ûÇô¤ågk¡ZÙÕKî`¹úÿž¿âfy€ÔÀ}ÅGkÈnÝ9ÿÏ_Çñ3í?Þ?¥T¤ù¶üŒéÙEûÇè?­Sù²1±ÁèùüýþkRˆÍ’N0:Ux†"•χúU[—BØU%¿ÏÓÛ§^y'àG8þ¿óì~ì‹¡p·~\õ‡åô‚QnÿÖw=Án® …ÇCþþ¯§a À¬Œ_<çþ_Ïüçæ¸½[ëýW¹• mc×9éþsúû€Jm·÷þ`╵&IM¬¾‡ðéJÿz?÷¿¡ªÖ ;îÎqþ©ç>½y&ËýèÿÞþ†¦Ö“_ÖÅÁó$Å^­õþ‚’_õOþé¥^­õþ‚’_õOþ驇õ÷”·ýáô?Ò›/ /÷Ž=ºÿJqûÃè¥#œ=·CDw×@@~fÇaÖ–EÞ„½¾´/VúÿAJHPIè9¥¬!û½ƒ éK/ú¶9Á#ðæ‘ x8þ”³Dùþé§fÒî>¢ôsÇQKH~ðúéKJ:]QEX±˜c†;—ŽýÇéRƒ‘šG@ãð#µDŽcm’`g¡ìj˜­Ðé#l–CÏ\æ”J:e>›sü©ô Ôf›]P¯Üag~üÌ?¥5†"(™àu&Áß'êi²í‘ÀÈÀ´š”´{zhE í„‘É-€3ÔŸÇüûõ2…Úª}Iýjl2À'÷ïþ\æ¬(ÏÌzŸÐUUw|‹¨¡¤RªH7\0'üã?Óüã"ÝUcþ’ÜöþŸçòïŽøeèɆ?.d\ç‘Ûßÿ­ú{|«6T¨ ¯-ógŽ¿Qüû~!Ósqáüÿúß§¶Tºãiéןóþ?â4w’±š´S"x¼±“‘ÏÀþGÛôí‹Ïå XÈ;GÞÀoð¦Ü€±‚ý;Ÿþ·Q"((¤¨Îr?úÕSkUý}ÅÅEI¤†° ’w3œ.J†8DÀ¶ì ôÀ?ç©üû‚wXðÚ{TfE1Ž›¾cŸÓ¯ù÷êH'¬˜ä¹¤¯°[}ÉO·ùþâmUkUÈ$}Üþçü穳RÝæÚü(ªÃý%¸íý?ÏçÛ<Úª¬?Ò[ŽßÓüþ}³Ëä¹_ÌOóþ#ÔM7-;/Ô\Ê7¿õ°ðq>Œzöª'¸g Dã=2¯ùüF‘´¿9+Ïý_çÿ¶‘ªghÆzѤfÿ®àù¥¶…P%€‡Ç^>¿çùúŸ½ÿç?4³LÈåW¿~ý¿Ï~¿@XñÌÀ³ð'“Óóþs¹ÒVW~˜¤ï$—AªÍ#o#ŽAõëíÿêvÈ,Â"ñãð5Ëå…]ù r3õ9ëþq׸!ƒ· >Uϰ#ëžGÿXð¯wýlL+³-/VúÿAI/ú§ÿtÒ¯VúÿAI/ú§ÿtÖPþ¾óu¸§ï¡þ”:ïR¹Æ{úP~ðúéI$‚=¤ô'J#»þºò²mlIòù¥)o;å_¹üMëì*Bi6ÿ´qF±ÙèO¼ÞËüé$?uxÉaúsý)Ĭk“Šbç™_#Ј®TÜwÕÏ=-"‚OSÍ-(mrBŠ(« €Ã= P~S/ú· zqFdî@ÿ€çúÔ”TÙôe\æ'— ²ŸãšB‹´ü¬xÆæäãõþU-6A˜Øc?)ÿ=è´ŸQ7¡° „ó÷ºœŸþ¿=Lõ ©ÌgŸâÿ?çùõ3Ur¨·b ï^H¤3\àûûŸÈ~(££C+yS3«78÷çÿÔ?–'“-ÇsŽ?/ÏðQbŠ=îÿYZÅfŽwfãê8ÿ?Ó߉X(aÐmÀý*Z);¾¿Öš‘Ãvlþ5¤ê¥TŸö‡¿ùö'žöh¢Ïfî)+‘@Ž¥‹ŒóþúæZ(¦ YX§*–¸!sœŽŸAþûêD¶ÇÞ,Çè=9ëøþgÔÑÖïüúõÿ^Ùù¬UJúYô&:ÞýÆB…Á뜜zæŸEšVw¹¥ÂªÊþ{„A;úÿõ¿ÇÐá‰çßò/Ýõõÿë?È4ðÆ#^Ÿ1ëžµ²\º³ùß*ØgËl™ÆâO'8÷ÿëÜÔM$Ò©H#þ?çéÎÙîb'Óž¿çü÷j¹—0ˆÀ`sƒÇž?L q×Rdù]¯aL3>rÍùûŸóø›ƒ ¹½§Ø—°¥,ßœÿçùúŸ¼ ?xe ‘ŸQþzgÿ¬2Jåwnú|…ξbI!“Áúwíþzõïœ5±ûȆOÞ^qUþÔÜåG··ùü:vçj4Ï&džõÿ<ÿõ¹Úr;Xji;Ük1”¹ÃtÇùǹü;`á£%”‡ä·ãþ½ÓœV+‚¼côöþ^ƒ¨**Ä0tv>„`ýÏ__r[-Ýÿ!)9;®y$c&•—r•=ÅV)Y 6AÞçòÿ M¤‘»{Øâ¤¢•ôîD#eÉŒíçî‘‘K™;?àüjJ(³[1ÜŒ(È,YÈõœ'-Û §QIÅ¿‰ŠáEUˆ(¢Š(¢Š(¢Š)² ÆÃùOùïN¢€eH§òÔ»²s×ÿ×íù÷È,ÿµú'ëþ}¿Î30D^=¾Ÿà?*h:"ñíôÿùU·ÐÉFkDÈ~×蟯ùöÿ8Éö¿DýÏ·ùÆf è‹Ç·Óüå@D^=¾Ÿà?*/Ái÷!û_¢~¿çÛüã'Úýõÿ>ßç˜Fƒ¢/ßOð•5 FÇqýÞ=?ÃüàQxö O¹Úýõÿ>ßç>×蟯ùöÿ8ËÖÚ0:øãùžžƒF½~_çÐ~BáØ©Ü‡í~‰úÿŸoóŒŸkôO×üûœe©û«½_ÿWéíòÚ¡ò®‚3êWû_¢~¿çÛüã'Úýõÿ>ßçšFE_œ§Ži¾\R€ÛA—çúþgÔÒ¼{ÓÙ2”4þaà~}¸þ¯¿Í+] ÎÐXöô?ç?ç#!µCÝ¿?¯øÿœœ«G c,7?ç¿ëïM¸±%4ˆÍÛ6¨Ç¿?çÿ¯ôÊ>@TƒŽùŸ×ñþ+(T®W¡öüéis%²#{²²ªÀÈ cœOþ¿ÿ_ÜÔ‚æ2NI_¨ÿ?ç>‡͆WžÀÿŸóÓÛ+/Ùâþî>„ÿŸÿPôÝ·b5Úˆ,nŒ3Π玟—ùÒ¡·Œ3g¡^Ý>Ÿ×ùqÈ©´dŒ¿CþÎ=K;Iç×üÿŸÊ‹¤¬‡Ë'$ä<€Ad Ôg‹û¼úäçóý~¼õ©(¨»F'¹[«0#åóÛòúaÞLy`tÇùú~CÒŸEbåaª’@ž¸´QH ¢Š(¢Š(¢Š(¢Š(¢Š(¢Š(¢Š(¢Š(¢Š(¢Š(¢Š(¢Š(¢Š(µÈØêã—qþOl«¤º„ã©ãçŸò$–/4pG|ŸoóÍ$p,}~cêGOóù{ iumLœewb†I Ç^O?ýoóíµªæÞB?‡¸[,$\äïEQ·<žI8 ¬ ûbGr–ò U.ŠÑ;£ªÉòäg2™@€ùd.v »[,)ö”S˜$Øâ pp«»øˆÞXŒ€RKà%Vò Om ŽæÞ70†6àYÁÚwã*¡9,û|²ÌjÉ©´­ÓòëëßúqO­Ioq$&ÆÝ9R&Iø |Ë¿ƒòœŒñ¹½·<Œ4ûyYWqHI bpÝ0¬OûÍÓµ 'KûÍÁbŽ9[-•I ʇj¬pF ® …ÁÅ–¶6˲-ΪÆU(‰v°Ï%\|¼²E\çq&‘ÇÏYÍ«èŸd9ﮦ¿{[X¡}¬QHèBõrw•±;ŠŽNqV¹efè¢Øj$0óËEÂwváØŽ)L³¸òN®åcŸÊ°Ž&Y>tm²ÀŒ3¹²88*Gb»x·cIѯUa¶šø2Ç2µÉUŽ¡Ôm àó6W¨(E¼Ó‚çRK^ºÛV•–·ÙôûºïÉ̶±Ü[øyç…HZ™Dcò².Bÿ–S¹y˻ۋ}’GåMm.|©B‘œuR3ò°ÈÈ÷'NHl¤Óc{”¸»Ó÷Ípu´*Jó²'îÊa¶’@Äòàíªm]ë:À»ò]E¼r¯îWpe–4R\ìB³.Y‰Á9&™Ñˆ”Zµìíuo%wÑiÑ?zû§½ìÙéÚ­êÛÖq\]£Imk)q,Ê£;†  œzsX¿Û7Ü‹ò?ã["»Ñu+›A/$u0Å•ŒHÈ`€C’»B©åL䞣“Xš}Οä}¦//í¬ñ|ÀîFèx©s{0†F(ˆ*‹À$ާÔóþy¬ ÓÖÿãîOªÿè"³)ÔtÓg²ê©«g°¬Ò:H°«–C…W~ÓópXà` ¥[ÆÌöñÙ¤3~ësI7”ÁIin2ãi >q˜pK†ÍÝP¼pÛ•Y Ù$Š‹#2É´‚Á“c!¹FÛ¾òb¡’s$‹·­#Ë„“ÍvrNùaÃyA°ìÊÀq¹±*T1ªÒ¨öéÓ]»ÿVßÕ¦dWŠV’;y#Då÷.<Å-ò¦Ò #–A]¨$¾Z=¶ÉÛùOûÿ ߉ò£cØbÌxÎJ¡FÊÔÉvð•ž7š8¶É2ˆO–©2œC·vðcªchEËQîahâG¸IUö(mÅÞaUUýÖwFß(•Þ¡Håé·×ð]àiÙùì¤0K6¡«YDd¹º¹³AÊ ÎÁ¢‘•Fl‚wvg$3gk¿ñûýyÚÿé¯iiut¯.G— b‰Ñ´øw¬zë'{-Ã:}ͽÃÜj_é·Ö6Ù’"ì`ÊF[iäž3@a’©JP›´W¼ßw´VÏ«}6ló/ÛOi¨ÍÌ2A*•ÝŠU†T}«´õ¿øû“ê¿ú¬Êg§BÞÍXÔñåÅÆ³æÌí¶Wˆ ð[…ǧýyëYæâbI3HI,I,y,0Çñ}jÖµÿ!Cþ¾¤ÿÐQ Þì\L"iH!Fþ§¥âa&“ù  ~D¡ÅGEæ}Ç3³œ³8$ç€0åB;FêèÅYNU”àƒëM¢_©uukÔ;„£ÌÁqLœŒ}ò7tã­U–Y'É,#·Vv$ŸÄÓ( ©NrVnáEP@ìŸ,ŽÀŠm8}ÃõÖ›@‘ÿÙ./CBFlib-0.9.2.2/html_graphics/CBFbig.jpg0000755000076500007650000004056111603702104016207 0ustar yayayayaÿØÿàJFIFHHÿþ AppleMark ÿÛ„   % #!,!#'(***.1-)1%)*(  (((((((((((((((((((((((((((((((((((((((((((((((((((ÿÄ¢  }!1AQa"q2‘¡#B±ÁRÑð$3br‚ %&'()*456789:CDEFGHIJSTUVWXYZcdefghijstuvwxyzƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚáâãäåæçèéêñòóôõö÷øùúw!1AQaq"2B‘¡±Á #3RðbrÑ $4á%ñ&'()*56789:CDEFGHIJSTUVWXYZcdefghijstuvwxyz‚ƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚâãäåæçèéêòóôõö÷øùúÿÀ¥X"ÿÚ ?úFŠ( Š( Š( Š( Š( Š( Š( Š( Š( Šæü}¨gø^ïl¾\·>\îÜ~aÓ7?×Ã釈|'oÌ oô¹aI&$¬`üÍœ¡ûß7Ýç$gº§O’.u\›QONf­³Úú躞^#0T+û>G$•äÖ¶½íu¿M{hzåÎøwÆÚ_ˆ™ šÞô®M¼½N'kta×ÐðNQñïŠJ¶U‰—ûJñFƈsŒƒŽXàŽG\Ž3K WÚû)+?>Ýý §ÃÇñ•ãåÕöõ0|Wâ«íkSþÎðíÜ¢ dg’[bÊdu8eä¯@:Ç¿º¯ø›þ=/÷í›ël-ÆhlçkÜÏNAà V‡4a£iêŒ?Ò%ÃÌHw#°úõÉïXúŸŸáz~É7Á3ž#!Ù²X}QÔ:tâนfË)$’þ¿šJ÷¾ßÙôó±çʆ/ãë6ù¾8ëî§µ¿Ã×Õúž±ECe{o¨ÚÅwi*Í«¹zýb;V½ã­Cß›ö»µÈò í<Œ3t^FäŒô¯ZjT—$bÛ=j¸š4iûJ’J=ÿ˹ÒQ^ieãzç_ÓæÜ[i׳c· ðÄÛˆ,q½NFÇnkÒéÕ¢é¤îš}övkÕ=Ìð¸Êx¥'ÕŸUn—OÑ…QXEPEPEPEPEPEPEPEPEak~7ð߇ǪkÐL¬¡Rd•I†Q`1ÎHÇ#ÔWÿ óÂÿóá«ÿߘ¿øåe*Ôàí)… ·ˆ5*M®ö=:Šá4ŸŒžÕ6¬—³iò¼¢5Žò¹Î0Å—rªóÔ‘Œàs]Ä3Es sÁ"K ª9#`ÊêFApAê¡Rø]Ì+á+á«AÇÕ¢ŠÅñ‹ô? }ŸûjûìŸiÝå~æGÝ·¾êœcpëëT䢮݌©ÒY(S‹môJìÚ¢¸¿ø[þÿ ßþJOÿÄQÿ ÀÿôÿÉIÿøŠÏÛRþe÷Ù¸ïùñ?üÿ‘ÑÂI¡ÿÐgOÿÀ¤ÿ?á$Ðÿè3§ÿàRx†ƒ®ø/ìoý¯qþ‘æ¿$ÿwtc®k«Òl¼®(:kÁpÅKykpâ@Á% }Gqë^~??Êð5§Np«%nhÆ./Ñó+žM<y**´è('üÜé¯_tôOøI4?ú éÿøŸãGü$šýtÿü Oñ®;þ þ|ò,ŸüUðˆhóãÿ‘dÿâ«Íÿ\rOå«ÿ€Ãÿ“'êù¯jø¿ù±ÿ„“Cÿ ÎŸÿIþ4ÂI¡ÿÐgOÿÀ¤ÿò›­Oáå•ÔÖ·lš 9mÁÚÊpF@ÁäT_Û¿ ¿çãÿ¹ÿ ë\I—5uB¿þþLëYN~ÕÕÿäÿü‰ëð’hôÓÿð)?ÆøI4?ú éÿøŸã^Iý»ðÛþ~?ñËŸð£ûwá·üüã—?áOýcË¿çÅü?üÿ²3ÿùóüŸÿ:_ˆúÅ®§™§Y_YM³—’E˜0Œ€KNÎÙÈííZ_Û:_ý­?ïúÿrZe×€u‹Ø¬,_ι—; œO' 5ÐÂ!¡ÿÏþE“ÿНŸÏól—2X…^Ÿ³æ·¹ ¾f®õŸ’G%,¿8ÁW©Rp‚”í£sVJé[Ýõ3µ3ÃÚ³SR´µ¸îñʘbNIažO^r<æ Ñ-m­u5-W[³»ºÀÉöÍç¦ bØ'ŒøûVÇü"üøÿäY?øª?áÐÿçÇÿ"ÉÿÅV0â,0Ëþ³]Ó’¶°§tº¤ùïg³[[C–YV*X•‰öT”“¿Å;7ѵËk®ŒÐ‡S°¸E í¼²7DIU‰ü§ÞZE}k-¬Ã1Ê¥O#Üg¸ê=ëǾ0)ðÆ™q.‰4útËN²ÛÌêêL»N9pi¬üuðݭɺЬuØâ—å¹HÒWªqÂèÌ97Ç8?ñ¤°ø¬º¶“JQçj2½úZëM:ž¦Ë«iš}Õ•ýåªÛÌ$ˆÜ« uqó"†WE!ñ äÂ61­“+8h%ЀO©Ú#é^ªÁy©ø²ÇJ·Ô§±IíÉ-6Îv‚3÷q_7f9¼°”f ¹\®ÖŠÊïD|ÏV§–×r§ ÝÅ$¬µ—àx—ŠäfÖëþýÕVËJÔ5=ÿa±¹»òñ¿È…¤Ûœã8gò«$·k?jÖÏ1὚6•º¹Ac×®3^ƒðWþcöÃÿjWÐcj¼S¼áeëªGèUqRÃe꺎©GO[/Ôà?áñýµ/ü“ü(ÿ„[ÄôÔ¿ðOð¯¥(¯˜ÿY*ÿϵ÷³çÿÖJ¿óí}ìñ‡Ú±eâý:âëI¾·…<ÝÒKl꫘œ ’1Ô^ßEâãñÒÇUU$­eoÏüÏ–6ª©%k+~æQEyçžxÏÇßù]×´?ú>½Á9Ûß8¹ûœwÏÓŸ ¯øûÿ ‹¯úö‡ÿG׸';{ç×?sŽùúsôúNkÿ"¬»þ½¿Ìð2ßãb¿ëãü¢W»°³ÕmMý¤¶ÓmÄbD|  ƒ‚Ç8# ®;Xø3à=w-.¤Ï’’X3[ìéóC°¸,y*Ý\ Wrœíïœ\ýÎ;çéÏÐPœíïœ\ýÎ;çéÏÐWÏÒÄV¢ïNmz3×qOt|å­ø_]ø «ÇâO Ë>©á«‘^ÛÎFGO–B£–;$å'kpþßáÏXø«D³Ö´Öv´»BÉæ&ÖR VR=C8Èã‚G5­}am«X\i÷‘™mo!6ó b»Ñ•U— ç¡= #ÐWÏLšïì÷â ªø+S—¯‘°3ì³(ú v#÷}uèÿlSéõˆìöç]Ÿ÷—GÕiæJ~Éÿwò>ƒ¬_!¿ñF»©™Ä‚1ä®ÐefùH#ÐF¾;i«[Üh«¬Y·Ú-¤µûT'|Ä)¹zŒŒŒu¬Ï†Úî¦XMkyu µä÷ƒH¥A@ƒ|` îÀ'¿½}àæ©c1º¥m®­¹y­—ô 8­Oëxjs’KÞ–®ÚÚÑü[þ™étQE}©ØQEQEQEQEQEQEr?ï'±ð³-»ìv‰"'ü¯"£Ž}Uˆükåºú‡âÄ2Ü|>ÖRÞV •E$…YQ˜ñØI=€&¾^¯üEè~—ÂI}Jo¯3ü‘ô§€ì!ú%¼(7µŽV‰ÉeÞÿ™'ó®ú¸o‡w0ÝèZ>ô[EŒœó"maÏ£)…w5äð­4¨×¨×¼ê4þI›>3rúÌ”·»üØSe‰&Cƒrž£4ê+ë§Î.2WOFŸSÍNÅ_ìËOùåÿñ¯ý ”"øqaT\€?ïÕ{Ux·í ÿ2ïý¼ÿí*ójàðØz2tiÆ-Ûd—_#è8zR–iJïù¿ô–xå­ÌÖWPÝ[¾É ‘d°ÖSpx<Šê ø«ã;mÞV³·w_ôXOþÉ\æg£¬iöSXînc…Ê0 Àg¿5ìP|ÑnwyW:“mëûè‡þÉ_5[FŽ" •ºŽü¶W~v¶»~è9–'E¥‹Šwî“üÏ.µñ·ˆlm%´¶ÔšeÉ`‘ l‘‚Cc àA¬}Íwuºâã4™’y‹7$òÌ@$úž ú×­X|.𮩠Mg¨êRÆ­°è¼àñQ^âÿ ÜxKPŽÚI¾Ó ÑïŠq@ݘc‘{x*{â”1´jâ§NIÆ«ø¹“RoÎúßÔÃ*Æåub©àbšÓ•$šò¶‡®|;ðõ†‹¡¥ÍÒÞÉ~«$·“±±œ*ƒÐ.XrÎsŽƒB?ù(ÚGý{?þƒ-y7ÃOÍ¥x†ÚÆI@²½s+©m®Ãå+Ž„°@{Œôz–«o¬[øŽÓWÒ­#¸kx65€\àän£V9"Ž=”ñURS„ýé5ª²Wzžq†JjRN~üe¢mÙ>Ét·O#Å|gÿ#†¿ÿa+ŸýÕ/…üe¨xKí_a†Ú_µlßç«mÝŒa‡÷Qñ³ÏâV[¤Xî$½™¥Eè¬\’'Œç½lx+Á?ð˜ý·þ&cû'—ÿ,|ÍÛ·´1¿­wcå‡T§*í8uê·Óo;¨9PX˽ÎXÞéù[M÷5áqøƒþ|ôßûõ'ÿGü.?Ïž›ÿ~¤ÿâëWþ§ýGÿòOÿ¶Qÿ Sþ£ÿù'ÿÛ+ç}¶EÙ}Òÿ#ÉöÙe÷KüŽ·À^%¼ñN5íìpG$w-+ÀU=Éçæ5ÔW?àï ÿÂ%¦Kaöϵù“™·ù[1•QŒdÿwõ®‚¾Oé:ót~è|ž-Òuæèü7Ð(¢Šå9O>ñï…âñ¦­‡æ¸{e½´ &wege8î7(Èà‘ë\'öŸÄ_ÓÆºŽÿxP!T`ÌV%52c Fgt1 –ɯr3ãí(c?¸ñKÝI¯^¾—e9ÇmÌM/Æ:¯Á vóÁºÑ‹^ÑWE†U/ 9°S¤©$ÂØùˆ €Å›Ý®|£\ű…Üç|NF9Ïäʼ{Zø‘à]VÔoÿµ|Iå}´ÝHò*E³0“#0 Î9Êð¼šô/ƒ^ _ü=Ò›rìì,hÊÇ€ƒž¤Çå±#Œ±éÐtcñÓ§Ic²ÊÒŒ”¹j8Þ*NÉ©Y;[uªÕôïÏ,-ÿ»ÄSR].“±¢ž»°36“­ÜÚä®â™HîOn3QMâoø~òÒÒ[øu @K+yq÷W'hbIô9$s×ígY·ÑmLÓÎÜG<¹þƒÔöü…q‘Yj0-¿‰nÉ2›”4Á¶Æ7!Y\($Æy?wö|%™f™‚öÙDè·ËhÆóž‰¤›µ®Þ÷Ó½¾K7¡†ÁËÙày£5ïK–NÑ÷jö×¢Û«è{=“Ü=»ÞF±Ü´JfE诸OÏsSWuññ­Þ[MÁ˜í^aHí*ò*§FW‰úñž³ÃÚ”ú¾‹gsoöy§M̜㩌ö d{Éë_IWRç’I^Û­ÏWŽ¡^~Êœ›i_géÙ_3JŠ(®c¼(¢Š(¢Š(¢Š(¢Š­©ØEªé·štìë Ü‚º•$dœJøööÎ}>òâÊé<»‹iZ)S íe$‘Áä•ö]yWÅφóëÙñ™ An-Që…\á—,àqƒœ€äÜÚ.¤T£º>¯†³(a+JWhÎÚöðÈÂø9â¨Ä_Ø—3–ÞC-¨Î ˆI.ƒŽH9<œÇ²×¹ òï_Í ¶ÓIñ¼SDÅ$ŽE*ÈÀà‚ ƒÚº«/Š~3Óícµƒ]”ÇB™¢ŽVëžYÔ±ëÜñÒ¼l½GV¬¾ÌÝíÙõûÿ?ÃÜ͸vXÊ¾ß $¯º{z¦“Üú7Å#³ð®‹sªÞ:‘LÛLÒ`íŒpNI‡$ð |—{y>¡yq{tþeÅÌ­,¯€73IÀàrOJµ«ëú¶¿7ªê77¬™DÒ¨X嶯E€àzV¿‚üuâ˽ÌZ :Ä÷rO]‰êß žÀÞ?i7hÄïË2êY5 Ô­$ÛÝùtKúÔô߃Vͤxn[õŽ#.£1mùb|´Êª‘Ða¼ÃÇfö¿h-Û|9¿±sœtÏî«Òô{ ÇŠÞÜŠŠŒc a^kûBÌ»ÿo?ûJ¼ìž¦+…­‰¬ß$Ÿ¸»+ëþ_&|Þ±9ä*õn_úK²ù#Êü-ÿ#6ÿ_ðèůªt_ùoÿþµò$RÉ©424rFÁ‘ÐÊG ‚:ÕOx’,ù~ ÕS=vÞÈ3ÿSTÌ)bï¤ÓÕ5úŸMœeÌ\y$•—_SÚ¼ÿ y¿ëå¿ô®ã&¥o>¡§iñ¶é­cw—»öír8=™}k…·ñ³h…-õkèPœ•ŽåÔë€k>²Ä`Õ|Þ®c}$ÛKÕ[VyÜ?ÃsÊ¡MU¨¤à­¢6üm5ߊ´ˆàMî·qÈF@ùQ·1çÑTŸÂ½ãYÖ'Ó&µ‚ÛO’úkûcˆß(àsÁý+økàY´|kZ¢l¼–2°[²ŒÂ§«6yG òHTnÇ⎅‰E·…Ï”“'€ü…r`©asŒî4j®zpŒ›Wjí'Õ4ôvÛ³>sŒs''†•ãeg«–»èôÐð/HòëÚ¤’ÂÐH÷’³DÝP—9Sî:W¡üÿ˜ßý°ÿÚ•ÃxÏþG þÂW?ú5«¹ø+ÿ1¿ûaÿµ+Lò1ޤb¬•­ÿ#í³ ÿdjîíÍ–¡âMGNiÞOÝ}š'*.X²£ à6vcŒsÞµ¿´âOý¥åË·Ÿåîÿgv3×wÆÿò#Ý×8ôbV/üÊ÷ ÿÚUYÆO–ÑÂ`ªÐ£Êç5{ÒwV‹êÝ·écñÊ8ŒT15©Î§2PæZ%gvº-vêR·ñF«w Ïmá›Éálí’-ì§'­iè:Ïöå›ÜùFÉL{wîÎ9έlü>ÿ‘COÿ¶¿ú5ë“ðüæÿ¯–ÿÐV½(Èr¬]Z®‡$á8¤ù¦ôm­œšèseجd«ÐUªó*‘m«EYÙ>‰>§OEWägÖœÕÈÏ´¡ŒþàñŒÿÏOcü«¯Nv÷ή~çóôçè+¹ñö”1ŸÜ1Ÿùéì•uéÎÞùÀõÏÜã¾~œý}æeþíÿ¯1ÿÒæxywñ1?õñÿé1ço|àzçîqß?N~‚©êšE†¿¦Ï¥êvÉwev‚)b|áÇÉÐŽA’E\Nv÷ή~çóôçè(Nv÷ή~çóôçè+ÆMÅÝnz§Í:/Âÿ Ü|h×<5<ͤXY‹¸­ÌädºÂvS¸ª™Ž9Ïʹ'œý cag¥ÚÇgai´yÙ¼b4\’NI'êkÊôŸÚ/Å|çþ$ñwÿbÓÜÿŸN•ë•\Aˆ­R­(Nm®H;7Õ­_«îb’m.¬+Ã~;x3âŠ<pî°3™ì„÷*I r¸QÁw‰ÕÎ0@‘ÇËîUá¿Ѽñ Âþ<·GXĦ e$…8l±à»Äìƒ8 GÁãåÇ&ýÿ¶Á?ù{?Åz?¨êéiö;Yî’ûÅ…5«omk)$‘å 6‚<0Á$ðG¶1è@cc?0ÎÞœž9ßää꺖±Û˜ðãfLP;g9<9®i%ּʎ¢ûMRÌ08RHÆN ^qÁÈä㜚ú©n®QV¤ëÇžœÝÜÕÛ^R]’Ù­»joø²V‡GÂÆy£ $‰¹a”ïq´îL€1âïÐôz¯¥Á¢YBÚ•¨kkH„›äòÈ*†!ðÁI#ÃÔV-î—â+`ѬW hçŒ1‰°9`Aã’8Èë×¾6»£hÚU‚4Vb)ƒ†Û/åd¦dÛ£è1ƒ÷±Õ²}nÇÑÂB9>"”ãYÏ¢]RZݦ¬’ÙZÚÛFƒíTå˜Q”eO—«}K&·}zé~Þ¡ErÞÐ_EÒL³G$3Ýíw†P»£ÀÇ$yå°~îqŒäž¦¾Â´#N£Œ]ÒêtaêJ­(Ôœy[éýX(¢ŠÈÜ(¢Š(¢Š(¢Š(¢ŠçõÿxsÄ¥¤Ôt¨$¸bÜ )+072XcŒŽ ®_€º2«½ÔdõÖ0T¯Y¢¼ìV_K­Ü_x»šùÚ祇Í1˜hòÓ¨ÒíÓþæ:wÁÍOÚϧË{"ɽ^êpqŒpUp¤qЃœœñ]µ¦‚°"DJE j#„``ÅlQ^Zἦ§^S©n’–ŸrHšùŽ'üI¶$q¬H*Ž€V7ˆ|!¡ø¯ìÿÛV?kû6ï+÷Ò&ÝØÝ÷Xg;G_JÚ¢¾‹ÙÁG’ÊݺtêÔ¥>zrj]Ó³ûÏ=“àß…ÌŒSKŒ!'h7Sð;7þ߆¿èþOÿÅW¢Q^$²<<›|ó×ûìô?µñÿóö_{ÿ3Çtx+Z¶k‹}DEr„Iq(9Î}k¤Ó<1¢hþQ±Òí¡’,ì—Ë (Îsóœ·r:ôã¥fø þ@ó×Ëè+]=~oÄ1ž2¯„…I8FVIɰËó<^7N¥z¹+½]¾ãÄ> ëúÅ—‹õ{]ZúÞò¶Ç˪®bBpÇRksá÷º–µqªß_Ü]¾ž*Ï#9`ë ÀbxÇZÔñ/ü+¿í»¯íßù |žwü|qvýÏ—îíéW¼%{à‹?µÿÂ?s ¶yþl’.q»n<ß«tü{W©‡Ìkáð±x*S^T”¹Z«>÷M_§™õ9…L5\©R«E¤”3VWN->kõkNûu(øƒJð&­âìmɽ¸•¯ˆy×{¹OÌF>bOËþ¶ã°Ð|m%ÅŒ¥ÓªH#v±ˆûíÇ~žµ%Ö¡áM*{+鱬$ñ";)È€ ž¤tª¼v./ã™ÈY,å`® WFm§ÅQ’ÂÕ$­8íÍ«wÑZúî×EØù<3¬FªgRïKsJ1²ZZï²vîïÔÕñW‹´=GÂ×}¥øšå–0¨!gk©<• 4Ì¡ÿpßý¥Yš¾½à½¹|’23$Vð,ŒØíòŒ ôˆüÌ‹â׆$ jÖw±@ØŒï<µ^œ€Ç€;xí]y®iõê8zXl-HªSæ÷­wd•–‹±Ëȳî¦&IIN<©Å;nõÕ»ïÐê¼ã Jðå•í÷•qýéäÈØË±…#¡à/ùÍÿ_-ÿ ­iXÚhZœW¶V–3ÛÌ»’EpGåÁìAä s÷ÿ|)áù>Ëkþ“’K:4(§’Ù r= 郊¼ëˆég8Z¸L.jr’“½šVo²Ó~§>Y‘f OšÒöQq²Nû%­ß—‘ÚÑ\~‘ñ?Ú´æž[þzªŠÜ~`HÇr:Œf» üâ¶­ rÕ‹OÌú:Øz´%ËV-?3š¹ñö”1ŸÜ1Ÿùéì•uéÎÞùÀõÏÜã¾~œýr#>>Ò†3ûƒÆ3ÿ==ò­-ÆZ'†.¥w‰Þ-éo—wod @Üqx8û|Â2–¢®ýŠÿÒ¦xU)Õ­ˆ…8¶ý£Ñ†&ês·¾p=s÷8?ABs·¾p=s÷8?A^Æo É4q¼ŒJÅU¥’*£+’päà`žìµÓÅâÝ]µÕ¿VÓ£`’M±ÎÒp[©`ðAÀ5æO Z¹¢õ=ê¸ U+sÓjú-:öõ<ËA9ý¢üWÎâOö-=Ïùôé^¹^!¤øK¶øÑâMtWH¼Óc‚ “îÜ·‡1¿$Ǹ¯o®LúU©¶´ä‚ù¤®¾]L¾¯Z‚ýìnÞé¯Ì¯}k¦YË{{2Áo îy ÔörIÀ¯Ÿþ!øŽ×Ç·–M&œ#·ÓÌžG˜ä³n+’ÀqÑåçòs]OÅï}¦ö ýÝ®&ŸŽ²0ùG#²œðpwúŠâÇ+Ë(Cõ¬RNúë²]íøýÝJW7W³µÅÔòÜLøÝ$®Y›$òxRÛ^]Y3µ­Ì¶í"ÜÄåK)ê§AÀâ½çGð7…´—û ÙCwpéæ;Þ ™öÆâ1…`88[øu ë6m XÁ§ÎùsÛE°Çœa™W‡NbqŒæº?¶¨©E:mEìôZwK¶ŸƒìÍ?Ö,äér·žß—éÛ§CÉ|)ã6е8.¯ {Èâà`s€IÈ!ð»¸8É#æ¯WÕmW_þÏÖô¿³ßÚª«(eÊŒ0%¤w:pTÆ>`z ’†k:EÞƒ©Üi·ª«q¶œ‚H>„}yí]ÿÂo]¤·Zœ˜Zk%þUuP1’w:mcŽI¯kÅQ¯O3¥.iArûÚ®Gž—¾û|>᜾¶sÂÁE7ÌùtOmRÛ·ü9Úø§ÇR_øSh%¸Ó5¨b†FX‹ÆB™bчE`ãŒç¸äøÇü&~(ÿ¡“WÿÀéøªë¼aotúMä÷Å£—å}².Î|Œ‚Ø^0à„ŠcG-^m_GœÅS­¤¢žŽëVöz]vv2à)}o,©*ñMÆ£ÚWiF;­lõÕXø3T–ÿÃúGž^IŽŸ É4ŽY¶.I'’I9ÍywÆ¿k:WŠ­ Óµkë([OG1Û\¼j[Ìg @ÎçÚ½á÷ü€´ŸûÃÿ %y_ǯù,¿ìŸú6Zñ2ü]lN^êU•ß3]´OMŒòŠTÿ¶%=ã‹ÿ„ÏÅô2jÿø/ÿGü&~(ÿ¡“WÿÀéøª—Àúe¦±â‹ è|ëi|Í鸮qÈ õ½ª„>¸‰eM-·LÝMž¿ïW%Ltã_êð„§+s{¶Úöê×Sê±øìj©î¯¢^~ÿ„ÏÅô2jÿø/ÿGü&~(ÿ¡“WÿÀéøª÷?øS~ÿ d_ø?ÿGü)¿ Ð2/ü ŸÿŠªúÆ+þê}Ëÿ’<ÿíü§þ}ÿä±ÿ3º²½ûfÿÝìÙâÎsŸð«UKO³’ÓÌó ØÆÓéš»^þS,TðPxÏâk}êí¶›Xüæ§/3åØ(¢ŠôÌŠ( Š( Š( Š( /ðüæÿ¯–ÿÐVºzæ<ÿ y¿ëå¿ô®ž¿âÏùb¿Ä^Gÿ"Ú>‡€|Kÿ‘ÛSÿ¶_ú)+¤ø;ekyý³ö›hgÛämóc Œù™Æ~•ÍüKÿ‘ÛSÿ¶_ú)+ªø+ÿ1¿ûaÿµ+ØÄÔ<ž3ƒi¨ÃU£û'êXèÆy"Œ•×,?8š|=¥è:U¯öm¯‘çoó?xÍ» >ñ>¦¼b½çãÇü‚´ÿûiÿ¡E^ _wœNS)IÝòÿíÒþ? ®LElrÂám®yI«é~]®¯ÐíÎóye•c QW–¯MÞ¿¢>H–) •áš6ŽHØ«£‚Hà‚C^Ùð£[mKÃÏc4»æÓäòÀ;‰0Êdž!€ Qǯ™ü@ÿ‘Û]ÿ¯Ù?v?æ7ÿl?ö¥cÄXxÇ R2ÕÁïó±¾>ªÆäðÅIYµ [·5´üM_kÍá­rÛSŽ$–hí¶Ä’}ÒÇÌ>Ã9Ç|c#5ã2Ë$ò¼ÓHÒI#wrK1<’IêkÐ>1Ë~Ê}Û0ÙÏ\»ý–³¾é‘ê>,ŠIv•³…î2n F}.Uükxbẕf¾ izÚïóm|?ƒ†W€­‹’÷ªJS~›E|ÒOÕë°ý;áOˆõ U¸u¶²ÝÊÇu# €rB©Ç\`àŒŠÀ¾·Ö¼2×zEÚËgö¸ÓÏ€VU NFAã¦õìž$ð®±âÝR;kÝWì‡K;O©eHt™ÆÝ‘òÅݸ$ƒ·n_Ä/ éºwaƒM¶†ÎßHt0F‰“µ›k.ãÏ%ƒrX®NIÍxØ\áά!VIóµ¢_ öÖú½´³·tÓBÁg•«âU:ñ\²i/'}?óÕ¥âK›«4OhþC$©¾Vˆ”7°(K.Hà óøÝ3Âïª[ØÝê:„ó&Å–(ŽÙ »ydå™Nå }ͧÇ<–Œ»,\$qXÌO%gUÌÛ²»–Šûk²oE¢=LNs„Þ ¥'ËŠÑIéÕê¼­®ÝÚçüq7ÞÕ5¤žHšcf ãØç›r£ ß*‡æ9 Í^5^ëãý6ËFø{mjŒŠï>oß}Ñ䟘nà}Ñœv®2<*¾‰baˆKÙ9:q÷aÍkò­Óóz÷gÝðeRËæ¦’“›rµíwßÓCê?‡ßòÒìþ€•å¿äp²ÿ°jèÙkÕ>È Iÿ°l?úW•üzÿ‘ÂËþÁ©ÿ£e¬2ùKürüÏ?(ÿ‘Ô½$rÔí4XßßMäÛEæo}¥±˜Ø'©îÖ?¼ ¬qÉ­maœ²Ïêد›í­n/g[{X%¸™ó¶8³6Näð _ÿ„[ÄôÔ¿ðOð§NTðø¿¬ó{ܼ¶oK^þ·¿™ôùžU„ÇTR¯7—F—~é÷>‰ÿ…¿àú ÿä¤ÿüEjh;ðçŠ/ËGÔ~ÕqFVO"D‚9e«ξbÿ„[ÄôÔ¿ðOð®ëá6“«é^#¹žêÂöÉÉÐI,/'|g ztö®ºÙähSu%f—DõüÏžÆðþŽu)UnIi¬D}EGlK[ÄI$”“ߊ’¾Š”ÕHFkªOï>«;QZ(¢Š(¢Š(¢Š(¢ŠòÿÈoúùoýk§®cÀ_ò›þ¾[ÿAZéëñÎ,ÿ‘æ+üEäò-£èxÄ¿ùµ?ûeÿ¢’º¯‚¿óÿ¶ûR¹_‰ò;jöËÿE%u_æ7ÿl?ö¥z¸Ïù¯ðÃÿm?TÆÈ•†ûiwÇþ¾‹ÃWW·ºÝÅÿÙölIƒn‘Á,qÛò¯¯ø—ÿ"N§ÿl¿ôjW€W¥—f˜ÌÒ‹­ŒŸ4“²Ñ-4v´R[¶rpžŽ8QVNmîÞ¼±][ì¤õÝ}f‚=BKXF|ØÔ²òÜ23‚8Îz×|]·ûŸ‡m·oòb–=ØÆp"Çá^·^Uñ«þ`Ÿößÿi×Ìe9Ž*µL> r½:nN*ËFÓo[]ïÕ³çr,-fÑÄE{òºnïem6_#•øiÿ#¶™ÿmôS×±ÞèzŒ×³ÜYë×V1ÌÁŒ0î!Bç†?(í^9ðÓþGm3þÚÿ觯®üÇ4Ååy‚­„Ÿ,œ,ôONfö’kt޾,ÂQÅâ! Êé$÷k[Étk¹ó·Ž,ÞÃÅ:…¼· s df™‡.Y‰<žyõ®Óà¯üÆÿí‡þÔ®Wâ_üŽÚŸý²ÿÑI]WÁ_ùÿÛý©]™¥z˜œ©×ªï)(¶ö»m7¶›ö=ìE8ÒÈ¡N(A/EÊeübV$´l¦Å@8àŸ1ÿÄT?îaƒÅOµî-8† ÜÁ•±íò«}+Sã ×v× á|˜|Çîr1õÎ+Îloî´Ë¸¯l¦h.!mÉ"õúŽÄà×T0R–UNŸóÂëçÿ”W†g•ÎŒ½(?&µ_ziüϨkø¡s  ¼ŽGÚ÷ECî`á±íò«}+NøË§µªÿié×1ÜŽì»]ÈÜÀŽsÇ8ã“\/‹üm}âÙã'Ùl¢æ;U}Ãv9f8\qÀéÔ“òù~OŠŽ*2«(´ïéØó°F*8¨Ê¤l¢ïNÇ5^¯ñ¦ßÄ~ MÁÚH鬼¯xî¼G- ÍÎÄ à’I ]­åõMzùÎ'ê•ðõÔTœy¬ž×²³ù=~GOG™R_âÿÛO™5ãÃú•Æ•u'5«l2í æŒ73Æq]×Â]IKêº#]I·‘o¶;¾U`b£#æÁSÇd<ñZŸ¼"×QYDÍ4Jî4AÊ þð÷$p^1Ð)¯+±¿ºÓ.â½²™ ¸…·$‹Ôê;x#ƒ]”ª¬ËxµÍ§ÊK]»_ð=X¨fÙk§}Z³òkñÿ€{´~ ŠòêA¨kS^IÊ8xÁRÙÝòN¾~©©hÖú4Ú|:M™³²ªÜËûÁ êÈøäAÇ®Û|BPò^<Ú_—Þ ¦ß-Ý›,[wÍ· £Ë%%Ž@ùJëeÔîbº·³OkäIòü’ fヅ'#¯;¾®LW·£W‹ç¢¢ï rûܺEÆMs;õZkucò p®;šxzX>ZœÊÓæMZúÉJM´íÛÞ×K;¥{Å~>ÖtÛë̲¼H¼¯1ÝP$Y€*‘‚¬0G©:ß |o­k:”4Éflíág–FæìɨÁ |W’K,“ÊóM#I$ŒYÝÉ,ÄòI'©¯nøqá·ð΋%í÷›ÕþÆxyŒB($±ÝÓ®HÈçæ3LG²ÁûÅ^rMF*ÉÎÊ7Q^]ºÛ«?EÆåYvW‚S”oS——šM¶ú·wÛWå¢#ø•¬Îú«§íaù93mkvÆIà±èXã*š¼J½³â&…}eáÍNöî'ódHüÇŒ“úØÔóœíʦÕb@*£s|N¾‡ƒ¥ƒ*4Òº‚æk¬º¿™R­\ iU¿ñedú.XÙQü>ÿ“ÿ`Øô¯+øõÿ#…—ýƒSÿFË^©ðûþ@ZOýƒaÿм¯ã×üŽ_ö Oý-yy?ü‹%þ9~g&Qÿ#©zHæ¾Èí¦Û_ýõôµ¼Ö±É${˜ç'qõ5óOÃOù´Ïûkÿ¢ž¾žÓ?ãÊ/ÇùšÃ ‡£ˆÎ\kAI{+Ù¤þߘø®N8ˆYý•ùÈ?³-?ç—þ<ÆìËOùåÿñ«TWÔeeÿóâø ÈøÏi>ìDPЍ£ £RÑEz («-ˆ (¢˜Q@Q@Q@Q@1¤?Š4[f··Ðn]Ë“%œ¤ä€;cÒ¯ÿmx¿þ…ùð oñ¯X¢–# –bªÊµl$%)jÛ¾§K/ÄÑ‚§O%²ÐùÇZðGŠø7Pð—öÛ¦¶—í^VÏ!˜ãnüç*?¼+ר¯žÍ2E^Ë5J’ååæÙßGue²·‘ö³œjÁ¬%is¤’½¬ì­ož›ž'â3âïh×:chS"Ï·,,æmpÞþž•ÉÛ|"ñÄ +ÉilÍœÅpÒ#¯8älã×é_LTwÐ]ÂÐ\Ãð¶7G*†Sƒ‘}ë¿–áåMCAÞîË™?“k]µ¿C›)Í3 ®œ©ª¼éÝûÉo§^Úsâ~ëCû/Ù£…üíû¼ÐN1·ÁµÁxž×Ä><ŽÎ[}8É£H»íàŒ¶Ü‚Fîx{õ¦›c§ïû½®üoòbTÝŽ™Àç©üêÍ,»&ËpXXR•%:‘¿ï>îÛÚîÚ;o±æR«˜QÇ,e*ü¶Ú6ºZ[­¯ßmÏð‡Ã]cÃþ"³Ôî®l^7îX¤rÇr2ŒeêGzìu¿E{"XiöóZŒlw` àgøÇ|ö©>#GýŸ¬hÚÐíSåJÉÐ*¶à>¬ø'>µµ_áêäÕèâk¨WU"Òæ‹I5-tRÝ_{ìö=Fe[<«RY:r¦Ò¼ZÕ4ÚÝy¿»sÇõ߇þ(ñ&½>¡,–ßhÛ’Òü«µôðûõ®¯áïƒu hýºki~ÕålòŽ6ïÎr£ûºÛÛûm6qw0Š0@ÉÉÉ=€š§¤x‚ËZó±t’>Lr€£äžâ¼|N'2Çà§Zu²n1|«]5mí¢ßM;ž£Îe QËjÖMÙ$¹šV¶ÖíÛ]O ñŽU¹²Ô$¹Éiuk)†ÞÞE.‘\$øÀn¤VtÞ!ð‹¼E¯‡íu=îÒg1½—œ‚@¡•R8K8S‡É¶ñ…Ævú—Å/ [Ýé²k–V‘%ô é∞<˹b€.2puxôRÉ©424rFÁ‘ÐÊG ‚:ûf|ÒŒ+Q§ìÜ"à”^‹w³Nú»£ÒἎ¶”«a±OšRnWŠz龩mnš\ïâø7®PM}§¤e†öGv`; ŒŸl­jëþÓ|àMLyë=ýÓF†â@œyªÁrp0¤ 'ž½·Æ›„VëEŠY†wŽ,Ö½h¬CJ ¦ímlïÓS¯¤õ~ íÅÄR:L< íìqëëÚ¼Sáþ‡u¬ø–ÊHU„S%ÄóÊ S¹AärÄcשÁÁ¯¦txöÂòAvÇ=0?ýf»çCÍhá«GšRrIÙê´×¦¶g‰Åõ¤ãtgË5Ö×µÚéè»õ¹À§4¦uSÒ@,ȸ_s†'ò®>ÁâÝwQ‹Eº†Ô,r\D¾[yoó «Ž }ìt cëô%Ý•­üb+Ëhnc ¸$чúà÷äÔVšNa!–ÏOµ¶®Òð¨HôÈ8•}†%ʰq©õxI9+k$í­ÓWW¿án‡ÀáqyÆ ®¬ž¶Vºµ¬ÕÚkµõOk5^|*ñmÃB4ôF’9ÑU¸ì©öäv¢ÏáWŠ.¥)5´j>dó©R}>MÇ?†8¯§ÙÔ«¨e=AÙmÿç„_÷À¯&®Y½©U¼âïùÛðùh¸³Ëgß½ŸùžGàÿ…–º=Ì7·nu B?™."‰¸äÉ ç p9€kÕ,,°ó$ÊñÚºPÀµx,Š4k¬V&§´¨¶º²^‹úô¹àc3øÉsTg?ã­ëÅ¿Ñ줆;‹Ÿ/cNÄ Û"±ÉžŠ{WˆOð[ÄVò´O{¦^¸–Lèºú>Šô±Ø9âRöSä—{_Mtµ×ÞtåùÎ'MÓ¥k7ž‹ô9ÙɧXÙYLU¤¶²H\¡%IP ã=¸®Kâ‡Ã]cÅúÔ:¥…ÍŒPAd°²ÜHêÄ«»„c ;תQX`r¿ªáÏ™¶Ýím_•ßæsÑÌ«PÄýfž’ÿ3Áü!ð×Xðÿˆ¬õ;«›† û–)±ÜŒ£@:‘Þ½»Lÿ(¿æjÕ†)«†Å¼UZ¼ï—–ܶêŸvVa™UÇÉJªÕÁÿ0¢Š+è,(¢Š(¢Š(¢Š(¢Š(¢Š(¢Š(¢Š(¢Š(¢Š(¢Šå¾"Ø}»Â÷F{WYÕPg¡ÚÄñÐ+1ü3\l^/™í,¬ôÛIoµ„ܬÇrŽx¶@'¯§¸¯soݼ¶Ó®øfC®HÊ‘‚2=ªŽ•áÝ'CÜtû(àfÎ_–r8ÜÄœp8Î)WÂà1´¡ m7>I9E^ËUk>¶ën½tÐòëa±_YupÕ’R{½N—é~‡¤|;ºÔdþ'º•¥,ÑUÁ8Ý @æùW¦G#¥3ƾm ê/hÐÁPag…T*‚~]ÀtÁ)¿rG£Ód&â•HÝJ²0È`z‚;ŠìX¦ýÉÅ{;8¸ZÑåz5nÖ"YMd㠩¹–Îç¥ê0ê¶Q]BÃæ:ƒÝOÓÿ¯Þ¸]SÁþ×Ò(·N¤_ïÚ˵ô÷ºvÝnÿn£Æu–9þí–ïå%ü+ðþŠGöî¯,’©ó|¬¬ã¶rÇ$•#Ðr+ݪ¦§¥Yk6¦ÒþÝg„°m¤A#~ž¤w¤òINv–&j>J7û쪯ÄY¤©µ ®oK/Á\át­ÛS´ðö‘i™,öàlŒœ–þ6€IÏ^NF+Ñ#b@ˆ¡Tt¹_ ø<3ªÏ}ûO‘4KE‚ ²‘–Ï'åÇAøWW^¦(Àe¯ý–òm.i=Ûëéè¿ç(b1¸ˆÊxÍ$ÛÓ²õÖþ¬(¢Ší7 (¢€ (¢€ (¢€ (¢€ (¢€ (¢€ (¢€ (¢€ (¢€ (¢€ (¢€ (¢€ (¢€ (¢€ (¢€ (¢€ (¢€ (¢€!»²µ¿ŒEym Ìa·š0à\üššŠ)ÝÚ²NöÔ(¢ŠC (¢€ (¢€ (¢€ (¢€ (¢€ (¢€ (¢€ (¢€ (¢€?ÿÙ./CBFlib-0.9.2.2/html_graphics/iucrhome.jpg0000644000076500007650000000314011603702104016733 0ustar yayayayaÿØÿàJFIFHHÿþ AppleMark ÿÛ„   % #!,!#'(***.1-)1%)*(  (((((((((((((((((((((((((((((((((((((((((((((((((((ÿÄ¢  }!1AQa"q2‘¡#B±ÁRÑð$3br‚ %&'()*456789:CDEFGHIJSTUVWXYZcdefghijstuvwxyzƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚáâãäåæçèéêñòóôõö÷øùúw!1AQaq"2B‘¡±Á #3RðbrÑ $4á%ñ&'()*56789:CDEFGHIJSTUVWXYZcdefghijstuvwxyz‚ƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚâãäåæçèéêòóôõö÷øùúÿÀ#X"ÿÚ ?õ-JïPŽæá,ÙH‰U¶É9ÎqùtªX¿{ºK¨‹!ãòù\œéúúTÚ·ÛSUš[?›di½:îžúvçšÍ’ò8ç’FG‹Ï'·#d}áÆ??SëL“q^ý”2߯TŒ‚ ?­%üjY¯ÿNÿýz‚Òî!cÖVqùIÆ1Á'Ð?΢wyX»†G^û~î{ã‚8rHû£=Ö¯ui£µ×îä™1Ê@'v:þ×*üAuöNØáÿMÛæeOÛÓŸö­VÕ|;1Ø‘ò€?x;ŸNÝùªZ“ùÚ Ë+âU,T{!Ç׃ùP3s\Ö®4ËDš‰™¤C‚F0Ob=)5Mz{I"´´f¼—•Rõ<ûæ}ðuÝ^ÛT¶†ÚÔHòWÆÞø#o¹ätãÞ­j· eâ;©ƒD[KŸïÓ"€6tÛíR_7ûBÚq›9Ï\ÿö«ßiE¬ CX†}*îK ‚^0 °R î`;LÓô]5aHïÞyf¸ž¹œä`àý{×µrßµ ‹–ÎØ†Tª/BJ“êyÿ<×]Ÿ¿ãê_úêŸúq”„{^­%Äz¬ÞCL¹3åB$õë“ÅgÜ ›¥Û7ÚÜ™²\¡ÏsZHŸU—Íqcq×ýµþµGÈ´þä?÷ÐÿãÔ$SGEØU$ö1Á=úõ÷ê)ên‘•»ÊŒ)6jHõ<ž§<žýéžE§÷!ÿ¾‡ÿ£È´þä?÷ÐÿãÔ¿eå 4±,¨¨ìQ†C`“ý*äËÛÇFÊÅSÉÆW¨è1Èžª”o.ˆ‘GÒ„žÀ±þ&¬µœQÜ[´È›\–tUHǯR+¢ƒå¾¿‚ýHnWÐPº}Œ™ mo!^ÁP‘þSæ–ÑâÛ;ÂÑ0TƒÈëôý)‘™¡ÞŸgi›ÌÜ¡NOç< ¸Í6 g¶û’GÅA½Usøe‰ü…W³‚Z¿Åkþ_0æ±Å¦óikûÀ Büã¨ã¿­L²Û£‹t’5uŸJŠ;S´‰@Ù$°ÉÛŽžû‰ü=ê¼0\/—¬Î7î³F9ÜX`nûÜǽ?gMÝ©Zÿ–Þ{‹šKtq>ÿ©ëªèÆWgãïøú—þº§þ\erŸ‰Þëw¯q‰Y&xÔ²•UˆV_Ù ÿž1ÿß"´µ¯ù êõõ'þ„j•1‘}šùãýò(û4óÆ?ûäT´P*ªª¡@ì)h¢€ (¢€ (¢€*êŒMð%übÖΩÿöÕ“V5!ÿÙ./CBFlib-0.9.2.2/Makefile0000644000076500007650000020016411603702122013237 0ustar yayayaya ###################################################################### # Makefile - command file for make to create CBFlib # # # # Version 0.9.2 12 Feb 2011 # # # # Paul Ellis and # # Herbert J. Bernstein (yaya@bernstein-plus-sons.com) # # # # (C) Copyright 2006 - 2011 Herbert J. Bernstein # # # ###################################################################### ###################################################################### # # # YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL # # # # ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS # # OF THE LGPL # # # ###################################################################### ########################### GPL NOTICES ############################## # # # This program is free software; you can redistribute it and/or # # modify it under the terms of the GNU General Public License as # # published by the Free Software Foundation; either version 2 of # # (the License, or (at your option) any later version. # # # # This program is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # # GNU General Public License for more details. # # # # You should have received a copy of the GNU General Public License # # along with this program; if not, write to the Free Software # # Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA # # 02111-1307 USA # # # ###################################################################### ######################### LGPL NOTICES ############################### # # # This library is free software; you can redistribute it and/or # # modify it under the terms of the GNU Lesser General Public # # License as published by the Free Software Foundation; either # # version 2.1 of the License, or (at your option) any later version. # # # # This library is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # # Lesser General Public License for more details. # # # # You should have received a copy of the GNU Lesser General Public # # License along with this library; if not, write to the Free # # Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, # # MA 02110-1301 USA # # # ###################################################################### ###################################################################### # # # Stanford University Notices # # for the CBFlib software package that incorporates SLAC software # # on which copyright is disclaimed # # # # This software # # ------------- # # The term "this software", as used in these Notices, refers to # # those portions of the software package CBFlib that were created by # # employees of the Stanford Linear Accelerator Center, Stanford # # University. # # # # Stanford disclaimer of copyright # # -------------------------------- # # Stanford University, owner of the copyright, hereby disclaims its # # copyright and all other rights in this software. Hence, anyone # # may freely use it for any purpose without restriction. # # # # Acknowledgement of sponsorship # # ------------------------------ # # This software was produced by the Stanford Linear Accelerator # # Center, Stanford University, under Contract DE-AC03-76SFO0515 with # # the Department of Energy. # # # # Government disclaimer of liability # # ---------------------------------- # # Neither the United States nor the United States Department of # # Energy, nor any of their employees, makes any warranty, express or # # implied, or assumes any legal liability or responsibility for the # # accuracy, completeness, or usefulness of any data, apparatus, # # product, or process disclosed, or represents that its use would # # not infringe privately owned rights. # # # # Stanford disclaimer of liability # # -------------------------------- # # Stanford University makes no representations or warranties, # # express or implied, nor assumes any liability for the use of this # # software. # # # # Maintenance of notices # # ---------------------- # # In the interest of clarity regarding the origin and status of this # # software, this and all the preceding Stanford University notices # # are to remain affixed to any copy or derivative of this software # # made or distributed by the recipient and are to be affixed to any # # copy of software made or distributed by the recipient that # # contains a copy or derivative of this software. # # # # Based on SLAC Software Notices, Set 4 # # OTT.002a, 2004 FEB 03 # ###################################################################### ###################################################################### # NOTICE # # Creative endeavors depend on the lively exchange of ideas. There # # are laws and customs which establish rights and responsibilities # # for authors and the users of what authors create. This notice # # is not intended to prevent you from using the software and # # documents in this package, but to ensure that there are no # # misunderstandings about terms and conditions of such use. # # # # Please read the following notice carefully. If you do not # # understand any portion of this notice, please seek appropriate # # professional legal advice before making use of the software and # # documents included in this software package. In addition to # # whatever other steps you may be obliged to take to respect the # # intellectual property rights of the various parties involved, if # # you do make use of the software and documents in this package, # # please give credit where credit is due by citing this package, # # its authors and the URL or other source from which you obtained # # it, or equivalent primary references in the literature with the # # same authors. # # # # Some of the software and documents included within this software # # package are the intellectual property of various parties, and # # placement in this package does not in any way imply that any # # such rights have in any way been waived or diminished. # # # # With respect to any software or documents for which a copyright # # exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. # # # # Even though the authors of the various documents and software # # found here have made a good faith effort to ensure that the # # documents are correct and that the software performs according # # to its documentation, and we would greatly appreciate hearing of # # any problems you may encounter, the programs and documents any # # files created by the programs are provided **AS IS** without any * # warranty as to correctness, merchantability or fitness for any # # particular or general use. # # # # THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF # # PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE # # PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS # # OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE # # PROGRAMS OR DOCUMENTS. # ###################################################################### ###################################################################### # # # The IUCr Policy # # for the Protection and the Promotion of the STAR File and # # CIF Standards for Exchanging and Archiving Electronic Data # # # # Overview # # # # The Crystallographic Information File (CIF)[1] is a standard for # # information interchange promulgated by the International Union of # # Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the # # recommended method for submitting publications to Acta # # Crystallographica Section C and reports of crystal structure # # determinations to other sections of Acta Crystallographica # # and many other journals. The syntax of a CIF is a subset of the # # more general STAR File[2] format. The CIF and STAR File approaches # # are used increasingly in the structural sciences for data exchange # # and archiving, and are having a significant influence on these # # activities in other fields. # # # # Statement of intent # # # # The IUCr's interest in the STAR File is as a general data # # interchange standard for science, and its interest in the CIF, # # a conformant derivative of the STAR File, is as a concise data # # exchange and archival standard for crystallography and structural # # science. # # # # Protection of the standards # # # # To protect the STAR File and the CIF as standards for # # interchanging and archiving electronic data, the IUCr, on behalf # # of the scientific community, # # # # # holds the copyrights on the standards themselves, * # # # # owns the associated trademarks and service marks, and * # # # # holds a patent on the STAR File. * # # # These intellectual property rights relate solely to the # # interchange formats, not to the data contained therein, nor to # # the software used in the generation, access or manipulation of # # the data. # # # # Promotion of the standards # # # # The sole requirement that the IUCr, in its protective role, # # imposes on software purporting to process STAR File or CIF data # # is that the following conditions be met prior to sale or # # distribution. # # # # # Software claiming to read files written to either the STAR * # File or the CIF standard must be able to extract the pertinent # # data from a file conformant to the STAR File syntax, or the CIF # # syntax, respectively. # # # # # Software claiming to write files in either the STAR File, or * # the CIF, standard must produce files that are conformant to the # # STAR File syntax, or the CIF syntax, respectively. # # # # # Software claiming to read definitions from a specific data * # dictionary approved by the IUCr must be able to extract any # # pertinent definition which is conformant to the dictionary # # definition language (DDL)[3] associated with that dictionary. # # # # The IUCr, through its Committee on CIF Standards, will assist # # any developer to verify that software meets these conformance # # conditions. # # # # Glossary of terms # # # # [1] CIF: is a data file conformant to the file syntax defined # # at http://www.iucr.org/iucr-top/cif/spec/index.html # # # # [2] STAR File: is a data file conformant to the file syntax # # defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html # # # # [3] DDL: is a language used in a data dictionary to define data # # items in terms of "attributes". Dictionaries currently approved # # by the IUCr, and the DDL versions used to construct these # # dictionaries, are listed at # # http://www.iucr.org/iucr-top/cif/spec/ddl/index.html # # # # Last modified: 30 September 2000 # # # # IUCr Policy Copyright (C) 2000 International Union of # # Crystallography # ###################################################################### # Version string VERSION = 0.9.2 # # Comment out the next line if scratch test files sould be retain # CLEANTESTS = yes # # Definition to get a version of tifflib to support tiff2cbf # TIFF = tiff-3.9.4-rev-6Feb11 TIFFPREFIX = $(PWD) # # Definitions to get a stable version of regex # REGEX = regex-20090805 REGEXDIR = /usr/lib REGEXDEP = # Program to use to retrieve a URL DOWNLOAD = wget # Flag to control symlinks versus copying SLFLAGS = --use_ln # # Program to use to pack shars # SHAR = /usr/bin/shar #SHAR = /usr/local/bin/gshar # # Program to use to create archives # AR = /usr/bin/ar # # Program to use to add an index to an archive # RANLIB = /usr/bin/ranlib # # Program to use to decompress a data file # DECOMPRESS = /usr/bin/bunzip2 # # Program to use to compress a data file # COMPRESS = /usr/bin/bzip2 # # Program to use to generate a signature # SIGNATURE = /usr/bin/openssl dgst -md5 # # Extension for compressed data file (with period) # CEXT = .bz2 # # Extension for signatures of files # SEXT = .md5 # call to time a command #TIME = #TIME = time # # Program to display differences between files # DIFF = diff -u -b # # Program to generate wrapper classes for Python # PYSWIG = swig -python # # Program to generate wrapper classes for Java # JSWIG = swig -java # # Program to generate LaTex and HTML program documentation # NUWEB = nuweb # # Compiler for Java # JAVAC = javac # # Java archiver for compiled classes # JAR = jar # # Java SDK root directory # ifeq ($(JDKDIR),) JDKDIR = /usr/lib/java endif ifneq ($(CBF_DONT_USE_LONG_LONG),) NOLLFLAG = -DCBF_DONT_USE_LONG_LONG else NOLLFLAG = endif # # PYCBF definitions # PYCBFEXT = so PYCBFBOPT = SETUP_PY = setup.py # # Set the compiler and flags # ######################################################### # # Appropriate compiler definitions for default (Linux) # ######################################################### CC = gcc C++ = g++ CFLAGS = -g -O2 -Wall -D_USE_XOPEN_EXTENDED -fno-strict-aliasing F90C = gfortran F90FLAGS = -g -fno-range-check F90LDFLAGS = SOCFLAGS = -fPIC SOLDFLAGS = -shared -Wl,-rpath,$(INSTALLDIR)/lib JAVAINCLUDES = -I$(JDKDIR)/include -I$(JDKDIR)/include/linux LDPREFIX = LD_LIBRARY_PATH=$(SOLIB) EXTRALIBS = -lm M4FLAGS = -Dfcb_bytes_in_rec=131072 TIME = time ifneq ($(NOFORTRAN),) F90C = endif # # Directories # ROOT = . LIB = $(ROOT)/lib SOLIB = $(ROOT)/solib JCBF = $(ROOT)/jcbf JAVADIR = $(ROOT)/java BIN = $(ROOT)/bin SRC = $(ROOT)/src INCLUDE = $(ROOT)/include M4 = $(ROOT)/m4 PYCBF = $(ROOT)/pycbf EXAMPLES = $(ROOT)/examples DECTRIS_EXAMPLES = $(EXAMPLES)/dectris_cbf_template_test DOC = $(ROOT)/doc GRAPHICS = $(ROOT)/html_graphics DATADIRI = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Input DATADIRO = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Output DATADIRS = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only INSTALLDIR = $(HOME) # # URLs from which to retrieve the data directories # DATAURLBASE = http://downloads.sf.net/cbflib/ DATAURLI = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Input.tar.gz DATAURLO = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Output.tar.gz DATAURLS = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz # # URLs from which to retrieve needed external package snapshots # REGEXURL = http://downloads.sf.net/cbflib/$(REGEX).tar.gz TIFFURL = http://downloads.sf.net/cbflib/$(TIFF).tar.gz # # Include directories # INCLUDES = -I$(INCLUDE) -I$(SRC) ###################################################################### # You should not need to make modifications below this line # ###################################################################### # # Suffixes of files to be used or built # .SUFFIXES: .c .o .f90 .m4 .m4.f90: m4 -P $(M4FLAGS) $< > $@ ifneq ($(F90C),) .f90.o: $(F90C) $(F90FLAGS) -c $< -o $@ endif # # Common dependencies # COMMONDEP = Makefile # # Source files # SOURCE = $(SRC)/cbf.c \ $(SRC)/cbf_alloc.c \ $(SRC)/cbf_ascii.c \ $(SRC)/cbf_binary.c \ $(SRC)/cbf_byte_offset.c \ $(SRC)/cbf_canonical.c \ $(SRC)/cbf_codes.c \ $(SRC)/cbf_compress.c \ $(SRC)/cbf_context.c \ $(SRC)/cbf_copy.c \ $(SRC)/cbf_file.c \ $(SRC)/cbf_getopt.c \ $(SRC)/cbf_lex.c \ $(SRC)/cbf_packed.c \ $(SRC)/cbf_predictor.c \ $(SRC)/cbf_read_binary.c \ $(SRC)/cbf_read_mime.c \ $(SRC)/cbf_simple.c \ $(SRC)/cbf_string.c \ $(SRC)/cbf_stx.c \ $(SRC)/cbf_tree.c \ $(SRC)/cbf_uncompressed.c \ $(SRC)/cbf_write.c \ $(SRC)/cbf_write_binary.c \ $(SRC)/cbf_ws.c \ $(SRC)/md5c.c F90SOURCE = $(SRC)/fcb_atol_wcnt.f90 \ $(SRC)/fcb_ci_strncmparr.f90 \ $(SRC)/fcb_exit_binary.f90 \ $(SRC)/fcb_nblen_array.f90 \ $(SRC)/fcb_next_binary.f90 \ $(SRC)/fcb_open_cifin.f90 \ $(SRC)/fcb_packed.f90 \ $(SRC)/fcb_read_bits.f90 \ $(SRC)/fcb_read_byte.f90 \ $(SRC)/fcb_read_image.f90 \ $(SRC)/fcb_read_line.f90 \ $(SRC)/fcb_read_xds_i2.f90 \ $(SRC)/fcb_skip_whitespace.f90 \ $(EXAMPLES)/test_fcb_read_image.f90 \ $(EXAMPLES)/test_xds_binary.f90 # # Header files # HEADERS = $(INCLUDE)/cbf.h \ $(INCLUDE)/cbf_alloc.h \ $(INCLUDE)/cbf_ascii.h \ $(INCLUDE)/cbf_binary.h \ $(INCLUDE)/cbf_byte_offset.h \ $(INCLUDE)/cbf_canonical.h \ $(INCLUDE)/cbf_codes.h \ $(INCLUDE)/cbf_compress.h \ $(INCLUDE)/cbf_context.h \ $(INCLUDE)/cbf_copy.h \ $(INCLUDE)/cbf_file.h \ $(INCLUDE)/cbf_getopt.h \ $(INCLUDE)/cbf_lex.h \ $(INCLUDE)/cbf_packed.h \ $(INCLUDE)/cbf_predictor.h \ $(INCLUDE)/cbf_read_binary.h \ $(INCLUDE)/cbf_read_mime.h \ $(INCLUDE)/cbf_simple.h \ $(INCLUDE)/cbf_string.h \ $(INCLUDE)/cbf_stx.h \ $(INCLUDE)/cbf_tree.h \ $(INCLUDE)/cbf_uncompressed.h \ $(INCLUDE)/cbf_write.h \ $(INCLUDE)/cbf_write_binary.h \ $(INCLUDE)/cbf_ws.h \ $(INCLUDE)/global.h \ $(INCLUDE)/cbff.h \ $(INCLUDE)/md5.h # # m4 macro files # M4FILES = $(M4)/fcblib_defines.m4 \ $(M4)/fcb_exit_binary.m4 \ $(M4)/fcb_next_binary.m4 \ $(M4)/fcb_open_cifin.m4 \ $(M4)/fcb_packed.m4 \ $(M4)/fcb_read_bits.m4 \ $(M4)/fcb_read_image.m4 \ $(M4)/fcb_read_xds_i2.m4 \ $(M4)/test_fcb_read_image.m4 \ $(M4)/test_xds_binary.m4 # # Documentation files # DOCUMENTS = $(DOC)/CBFlib.html \ $(DOC)/CBFlib.txt \ $(DOC)/CBFlib_NOTICES.html \ $(DOC)/CBFlib_NOTICES.txt \ $(DOC)/ChangeLog \ $(DOC)/ChangeLog.html \ $(DOC)/MANIFEST \ $(DOC)/gpl.txt $(DOC)/lgpl.txt # # HTML Graphics files # JPEGS = $(GRAPHICS)/CBFbackground.jpg \ $(GRAPHICS)/CBFbig.jpg \ $(GRAPHICS)/CBFbutton.jpg \ $(GRAPHICS)/cbflibbackground.jpg \ $(GRAPHICS)/cbflibbig.jpg \ $(GRAPHICS)/cbflibbutton.jpg \ $(GRAPHICS)/cifhome.jpg \ $(GRAPHICS)/iucrhome.jpg \ $(GRAPHICS)/noticeButton.jpg # # Default: instructions # default: @echo ' ' @echo '***************************************************************' @echo ' ' @echo ' PLEASE READ README and doc/CBFlib_NOTICES.txt' @echo ' ' @echo ' Before making the CBF library and example programs, check' @echo ' that the C compiler name and flags are correct:' @echo ' ' @echo ' The current values are:' @echo ' ' @echo ' $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG)' @echo ' ' @echo ' Before installing the CBF library and example programs, check' @echo ' that the install directory is correct:' @echo ' ' @echo ' The current value :' @echo ' ' @echo ' $(INSTALLDIR) ' @echo ' ' @echo ' To compile the CBF library and example programs type:' @echo ' ' @echo ' make clean' @echo ' make all' @echo ' ' @echo ' To compile the CBF library as a shared object library, type:' @echo ' ' @echo ' make shared' @echo ' ' @echo ' To compile the Java wrapper classes for CBF library, type:' @echo ' ' @echo ' make javawrapper' @echo ' ' @echo ' To run a set of tests type:' @echo ' ' @echo ' make tests' @echo ' ' @echo ' To run some java tests type:' @echo ' ' @echo ' make javatests' @echo ' ' @echo ' The tests assume that several data files are in the directories' @echo ' $(DATADIRI) and $(DATADIRO)' @echo ' ' @echo ' Alternatively tests can be run comparing MD5 signatures only by' @echo ' ' @echo ' make tests_sigs_only' @echo ' ' @echo ' These signature only tests save space and download time by' @echo ' assuming that input data files and the output signatures' @echo ' are in the directories' @echo ' $(DATADIRI) and $(DATADIRS)' @echo ' ' @echo ' These directory can be obtained from' @echo ' ' @echo ' $(DATAURLI) ' @echo ' $(DATAURLO) ' @echo ' $(DATAURLS) ' @echo ' ' @echo ' To clean up the directories type:' @echo ' ' @echo ' make clean' @echo ' ' @echo ' To install the library and binaries type:' @echo ' ' @echo ' make install' @echo ' ' @echo '***************************************************************' @echo ' ' # # Compile the library and examples # all:: $(BIN) $(SOURCE) $(F90SOURCE) $(HEADERS) \ symlinksdone $(REGEXDEP) \ $(LIB)/libcbf.a \ $(LIB)/libfcb.a \ $(LIB)/libimg.a \ $(BIN)/adscimg2cbf \ $(BIN)/cbf2adscimg \ $(BIN)/convert_image \ $(BIN)/convert_minicbf \ $(BIN)/sequence_match \ $(BIN)/arvai_test \ $(BIN)/makecbf \ $(BIN)/img2cif \ $(BIN)/adscimg2cbf \ $(BIN)/cif2cbf \ $(BIN)/testcell \ $(BIN)/cif2c \ $(BIN)/testreals \ $(BIN)/testflat \ $(BIN)/testflatpacked ifneq ($(F90C),) all:: $(BIN)/test_xds_binary \ $(BIN)/test_fcb_read_image endif shared: $(SOLIB)/libcbf.so $(SOLIB)/libfcb.so $(SOLIB)/libimg.so javawrapper: shared $(JCBF) $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf_wrap.so ifneq ($(CBFLIB_USE_PYCIFRW),) PYCIFRWDEF = -Dcbf_use_pycifrw=yes else PYCIFRWDEF = endif Makefiles: Makefile \ Makefile_LINUX \ Makefile_LINUX_64 \ Makefile_LINUX_gcc42 \ Makefile_LINUX_DMALLOC \ Makefile_LINUX_gcc42_DMALLOC \ Makefile_OSX \ Makefile_OSX_gcc42 \ Makefile_OSX_gcc42_DMALLOC \ Makefile_AIX \ Makefile_MINGW \ Makefile_IRIX_gcc Makefile_LINUX: $(M4)/Makefile.m4 -cp Makefile_LINUX Makefile_LINUX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX $(M4)/Makefile.m4 > Makefile_LINUX Makefile_LINUX_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_LINUX Makefile_LINUX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_DMALLOC $(M4)/Makefile.m4 > Makefile_LINUX_DMALLOC Makefile_LINUX_64: $(M4)/Makefile.m4 -cp Makefile_LINUX_64 Makefile_LINUX_64_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_64 $(M4)/Makefile.m4 > Makefile_LINUX_64 Makefile_LINUX_gcc42: $(M4)/Makefile.m4 -cp Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_gcc42 $(M4)/Makefile.m4 > Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_gcc42_DMALLOC $(M4)/Makefile.m4 > Makefile_LINUX_gcc42_DMALLOC Makefile_OSX: $(M4)/Makefile.m4 -cp Makefile_OSX Makefile_OSX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX $(M4)/Makefile.m4 > Makefile_OSX Makefile_OSX_gcc42: $(M4)/Makefile.m4 -cp Makefile_OSX_gcc42 Makefile_OSX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX_gcc42 $(M4)/Makefile.m4 > Makefile_OSX_gcc42 Makefile_OSX_gcc42_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_OSX_gcc42 Makefile_OSX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX_gcc42_DMALLOC $(M4)/Makefile.m4 > Makefile_OSX_gcc42_DMALLOC Makefile_AIX: $(M4)/Makefile.m4 -cp Makefile_AIX Makefile_AIX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=AIX $(M4)/Makefile.m4 > Makefile_AIX Makefile_MINGW: $(M4)/Makefile.m4 -cp Makefile_MINGW Makefile_MINGW_old m4 -P $(PYCIFRWDEF) -Dcbf_system=MINGW $(M4)/Makefile.m4 > Makefile_MINGW Makefile_IRIX_gcc: $(M4)/Makefile.m4 -cp Makefile_IRIX_gcc Makefile_IRIX_gcc_old m4 -P $(PYCIFREDEF) -Dcbf_system=IRIX_gcc $(M4)/Makefile.m4 > Makefile_IRIX_gcc Makefile: $(M4)/Makefile.m4 -cp Makefile Makefile_old m4 -P $(PYCIFRWDEF) -Dcbf_system=default $(M4)/Makefile.m4 > Makefile symlinksdone: chmod a+x .symlinks chmod a+x .undosymlinks chmod a+x doc/.symlinks chmod a+x doc/.undosymlinks chmod a+x libtool/.symlinks chmod a+x libtool/.undosymlinks ./.symlinks $(SLFLAGS) touch symlinksdone install: all $(INSTALLDIR) $(INSTALLDIR)/lib $(INSTALLDIR)/bin \ $(INSTALLDIR)/include $(INSTALLDIR)/include/cbflib \ $(PYSOURCE) -chmod -R 755 $(INSTALLDIR)/include/cbflib -chmod 755 $(INSTALLDIR)/lib/libcbf.a -cp $(INSTALLDIR)/lib/libcbf.a $(INSTALLDIR)/lib/libcbf_old.a cp $(LIB)/libcbf.a $(INSTALLDIR)/lib/libcbf.a -cp $(INSTALLDIR)/lib/libimg.a $(INSTALLDIR)/lib/libimg_old.a cp $(LIB)/libimg.a $(INSTALLDIR)/lib/libimg.a -cp $(INSTALLDIR)/bin/adscimg2cbf $(INSTALLDIR)/bin/adscimg2cbf_old cp $(BIN)/adscimg2cbf $(INSTALLDIR)/bin/adscimg2cbf -cp $(INSTALLDIR)/bin/cbf2adscimg $(INSTALLDIR)/bin/cbf2adscimg_old cp $(BIN)/cbf2adscimg $(INSTALLDIR)/bin/cbf2adscimg -cp $(INSTALLDIR)/bin/convert_image $(INSTALLDIR)/bin/convert_image_old cp $(BIN)/convert_image $(INSTALLDIR)/bin/convert_image -cp $(INSTALLDIR)/bin/convert_minicbf $(INSTALLDIR)/bin/convert_minicbf_old cp $(BIN)/convert_minicbf $(INSTALLDIR)/bin/convert_minicbf -cp $(INSTALLDIR)/bin/makecbf $(INSTALLDIR)/bin/makecbf_old cp $(BIN)/makecbf $(INSTALLDIR)/bin/makecbf -cp $(INSTALLDIR)/bin/img2cif $(INSTALLDIR)/bin/img2cif_old cp $(BIN)/img2cif $(INSTALLDIR)/bin/img2cif -cp $(INSTALLDIR)/bin/cif2cbf $(INSTALLDIR)/bin/cif2cbf_old cp $(BIN)/cif2cbf $(INSTALLDIR)/bin/cif2cbf -cp $(INSTALLDIR)/bin/sequence_match $(INSTALLDIR)/bin/sequence_match_old cp $(BIN)/sequence_match $(INSTALLDIR)/bin/sequence_match -cp $(INSTALLDIR)/bin/arvai_test $(INSTALLDIR)/bin/arvai_test_old cp $(BIN)/arvai_test $(INSTALLDIR)/bin/arvai_test -cp $(INSTALLDIR)/bin/cif2c $(INSTALLDIR)/bin/cif2c_old cp $(BIN)/cif2c $(INSTALLDIR)/bin/cif2c -cp $(INSTALLDIR)/bin/testreals $(INSTALLDIR)/bin/testreals_old cp $(BIN)/testreals $(INSTALLDIR)/bin/testreals -cp $(INSTALLDIR)/bin/testflat $(INSTALLDIR)/bin/testflat_old cp $(BIN)/testflat $(INSTALLDIR)/bin/testflat -cp $(INSTALLDIR)/bin/testflatpacked $(INSTALLDIR)/bin/testflatpacked_old cp $(BIN)/testflatpacked $(INSTALLDIR)/bin/testflatpacked chmod -R 755 $(INSTALLDIR)/include/cbflib -rm -rf $(INSTALLDIR)/include/cbflib_old -cp -r $(INSTALLDIR)/include/cbflib $(INSTALLDIR)/include/cbflib_old -rm -rf $(INSTALLDIR)/include/cbflib cp -r $(INCLUDE) $(INSTALLDIR)/include/cbflib chmod 644 $(INSTALLDIR)/lib/libcbf.a chmod 755 $(INSTALLDIR)/bin/convert_image chmod 755 $(INSTALLDIR)/bin/convert_minicbf chmod 755 $(INSTALLDIR)/bin/makecbf chmod 755 $(INSTALLDIR)/bin/img2cif chmod 755 $(INSTALLDIR)/bin/cif2cbf chmod 755 $(INSTALLDIR)/bin/sequence_match chmod 755 $(INSTALLDIR)/bin/arvai_test chmod 755 $(INSTALLDIR)/bin/cif2c chmod 755 $(INSTALLDIR)/bin/testreals chmod 755 $(INSTALLDIR)/bin/testflat chmod 755 $(INSTALLDIR)/bin/testflatpacked chmod 644 $(INSTALLDIR)/include/cbflib/*.h # # REGEX # ifneq ($(REGEXDEP),) $(REGEXDEP): $(REGEX) (cd $(REGEX); ./configure; make install) endif $(REGEX): $(DOWNLOAD) $(REGEXURL) tar -xvf $(REGEX).tar.gz -rm $(REGEX).tar.gz # # TIFF # $(TIFF): $(DOWNLOAD) $(TIFFURL) tar -xvf $(TIFF).tar.gz -rm $(TIFF).tar.gz (cd $(TIFF); ./configure --prefix=$(TIFFPREFIX); make install) # # Directories # $(INSTALLDIR): mkdir -p $(INSTALLDIR) $(INSTALLDIR)/lib: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/lib $(INSTALLDIR)/bin: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/bin $(INSTALLDIR)/include: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/include $(INSTALLDIR)/include/cbflib: $(INSTALLDIR)/include mkdir -p $(INSTALLDIR)/include/cbflib $(LIB): mkdir $@ $(BIN): mkdir $@ $(SOLIB): mkdir $@ $(JCBF): mkdir $@ # # Parser # $(SRC)/cbf_stx.c: $(SRC)/cbf.stx.y bison $(SRC)/cbf.stx.y -o $(SRC)/cbf.stx.tab.c -d mv $(SRC)/cbf.stx.tab.c $(SRC)/cbf_stx.c mv $(SRC)/cbf.stx.tab.h $(INCLUDE)/cbf_stx.h # # CBF library # $(LIB)/libcbf.a: $(SOURCE) $(HEADERS) $(COMMONDEP) $(LIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG) $(INCLUDES) $(WARNINGS) -c $(SOURCE) $(AR) cr $@ *.o mv *.o $(LIB) ifneq ($(RANLIB),) $(RANLIB) $@ endif $(SOLIB)/libcbf.so: $(SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(SOURCE) $(CC) -o $@ *.o $(SOLDFLAGS) $(EXTRALIBS) rm *.o # # IMG library # $(LIB)/libimg.a: $(EXAMPLES)/img.c $(HEADERS) $(COMMONDEP) $(LIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) -c $(EXAMPLES)/img.c $(AR) cr $@ img.o ifneq ($(RANLIB),) $(RANLIB) $@ endif rm img.o $(SOLIB)/libimg.so: $(SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(EXAMPLES)/img.c $(CC) -o $@ img.o $(SOLDFLAGS) rm img.o # # CBF and IMG libraries # CBF_IMG_LIBS: $(LIB)/libcbf.a $(LIB)/libimg.a # # FCB library # $(LIB)/libfcb.a: $(F90SOURCE) $(COMMONDEP) $(LIB) ifneq ($(F90C),) $(F90C) $(F90FLAGS) -c $(F90SOURCE) $(AR) cr $@ *.o ifneq ($(RANLIB),) $(RANLIB) $@ endif rm *.o else echo "Define F90C to build $(LIB)/libfcb.a" endif $(SOLIB)/libfcb.so: $(F90SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) ifneq ($(F90C),) $(F90C) $(F90FLAGS) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(F90SOURCE) $(F90C) $(F90FLAGS) -o $@ *.o $(SOLDFLAGS) rm *.o else echo "Define F90C to build $(SOLIB)/libfcb.so" endif # # Python bindings # $(PYCBF)/_pycbf.$(PYCBFEXT): $(PYCBF) $(LIB)/libcbf.a \ $(PYCBF)/$(SETUP_PY) \ $(LIB)/libfcb.a \ $(LIB)/libimg.a \ $(PYCBF)/pycbf.i \ $(PYCBF)/cbfhandlewrappers.i \ $(PYCBF)/cbfdetectorwrappers.i \ $(PYCBF)/cbfgenericwrappers.i \ $(PYCBF)/cbfgoniometerwrappers.i (cd $(PYCBF); python $(SETUP_PY) build $(PYCBFBOPT); cp build/lib.*/_pycbf.$(PYCBFEXT) .) $(PYCBF)/setup.py: $(M4)/setup_py.m4 (m4 -P -Dregexlib=NOREGEXLIB -Dregexlibdir=NOREGEXLIBDIR $(M4)/setup_py.m4 > $@) $(PYCBF)/setup_MINGW.py: m4/setup_py.m4 (m4 -P -Dregexlib=regex -Dregexlibdir=$(REGEXDIR) $(M4)/setup_py.m4 > $@) $(LIB)/_pycbf.$(PYCBFEXT): $(PYCBF)/_pycbf.$(PYCBFEXT) cp $(PYCBF)/_pycbf.$(PYCBFEXT) $(LIB)/_pycbf.$(PYCBFEXT) $(PYCBF)/pycbf.pdf: $(PYCBF)/pycbf.w (cd $(PYCBF); \ $(NUWEB) pycbf; \ latex pycbf; \ $(NUWEB) pycbf; \ latex pycbf; \ dvipdfm pycbf ) $(PYCBF)/CBFlib.txt: $(DOC)/CBFlib.html links -dump $(DOC)/CBFlib.html > $(PYCBF)/CBFlib.txt $(PYCBF)/cbfhandlewrappers.i \ $(PYCBF)/cbfdetectorwrappers.i \ $(PYCBF)/cbfgenericwrappers.i \ $(PYCBF)/cbfgoniometerwrappers.i: $(PYCBF)/CBFlib.txt $(PYCBF)/make_pycbf.py (cd $(PYCBF); python make_pycbf.py; $(PYSWIG) pycbf.i; python setup.py build) # # Java bindings # $(JCBF)/cbflib-$(VERSION).jar: $(JCBF) $(JCBF)/jcbf.i $(JSWIG) -I$(INCLUDE) -package org.iucr.cbflib -outdir $(JCBF) $(JCBF)/jcbf.i $(JAVAC) -d . $(JCBF)/*.java $(JAR) cf $@ org $(SOLIB)/libcbf_wrap.so: $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf.so $(CC) $(CFLAGS) $(NOLLFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) $(JAVAINCLUDES) -c $(JCBF)/jcbf_wrap.c $(CC) -o $@ jcbf_wrap.o $(SOLDFLAGS) -L$(SOLIB) -lcbf rm jcbf_wrap.o # # F90SOURCE # $(SRC)/fcb_exit_binary.f90: $(M4)/fcb_exit_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_exit_binary.m4) > $(SRC)/fcb_exit_binary.f90 $(SRC)/fcb_next_binary.f90: $(M4)/fcb_next_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_next_binary.m4) > $(SRC)/fcb_next_binary.f90 $(SRC)/fcb_open_cifin.f90: $(M4)/fcb_open_cifin.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_open_cifin.m4) > $(SRC)/fcb_open_cifin.f90 $(SRC)/fcb_packed.f90: $(M4)/fcb_packed.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_packed.m4) > $(SRC)/fcb_packed.f90 $(SRC)/fcb_read_bits.f90: $(M4)/fcb_read_bits.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_bits.m4) > $(SRC)/fcb_read_bits.f90 $(SRC)/fcb_read_image.f90: $(M4)/fcb_read_image.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_image.m4) > $(SRC)/fcb_read_image.f90 $(SRC)/fcb_read_xds_i2.f90: $(M4)/fcb_read_xds_i2.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_xds_i2.m4) > $(SRC)/fcb_read_xds_i2.f90 $(EXAMPLES)/test_fcb_read_image.f90: $(M4)/test_fcb_read_image.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) test_fcb_read_image.m4) > $(EXAMPLES)/test_fcb_read_image.f90 $(EXAMPLES)/test_xds_binary.f90: $(M4)/test_xds_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) test_xds_binary.m4) > $(EXAMPLES)/test_xds_binary.f90 # # convert_image example program # $(BIN)/convert_image: $(LIB)/libcbf.a $(EXAMPLES)/convert_image.c $(EXAMPLES)/img.c \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/convert_image.c $(EXAMPLES)/img.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # convert_minicbf example program # $(BIN)/convert_minicbf: $(LIB)/libcbf.a $(EXAMPLES)/convert_minicbf.c \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/convert_minicbf.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # makecbf example program # $(BIN)/makecbf: $(LIB)/libcbf.a $(EXAMPLES)/makecbf.c $(LIB)/libimg.a $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/makecbf.c -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # adscimg2cbf example program # $(BIN)/adscimg2cbf: $(LIB)/libcbf.a $(EXAMPLES)/adscimg2cbf.c $(EXAMPLES)/adscimg2cbf_sub.c $(CC) $(CFLAGS) $(NOLLFLAG) -D_SVID_SOURCE $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/adscimg2cbf.c $(EXAMPLES)/adscimg2cbf_sub.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # cbf2adscimg example program # $(BIN)/cbf2adscimg: $(LIB)/libcbf.a $(EXAMPLES)/cbf2adscimg.c $(EXAMPLES)/cbf2adscimg_sub.c $(CC) $(CFLAGS) $(NOLLFLAG) -D_SVID_SOURCE $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cbf2adscimg.c $(EXAMPLES)/cbf2adscimg_sub.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # changtestcompression example program # $(BIN)/changtestcompression: $(LIB)/libcbf.a $(EXAMPLES)/changtestcompression.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/changtestcompression.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # img2cif example program # $(BIN)/img2cif: $(LIB)/libcbf.a $(EXAMPLES)/img2cif.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOTPINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/img2cif.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # cif2cbf example program # $(BIN)/cif2cbf: $(LIB)/libcbf.a $(EXAMPLES)/cif2cbf.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cif2cbf.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # dectris cbf_template_t program # $(BIN)/cbf_template_t: $(DECTRIS_EXAMPLES)/cbf_template_t.c \ $(DECTRIS_EXAMPLES)/mx_cbf_t_extras.h \ $(DECTRIS_EXAMPLES)/mx_parms.h $(CC) $(CFLAGS) $(NOLLFLAG) -I $(DECTRIS_EXAMPLES) $(WARNINGS) \ $(DECTRIS_EXAMPLES)/cbf_template_t.c -o $@ # # testcell example program # $(BIN)/testcell: $(LIB)/libcbf.a $(EXAMPLES)/testcell.C $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testcell.C -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # cif2c example program # $(BIN)/cif2c: $(LIB)/libcbf.a $(EXAMPLES)/cif2c.c $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cif2c.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # sauter_test example program # $(BIN)/sauter_test: $(LIB)/libcbf.a $(EXAMPLES)/sauter_test.C $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/sauter_test.C -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # sequence_match example program # $(BIN)/sequence_match: $(LIB)/libcbf.a $(EXAMPLES)/sequence_match.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/sequence_match.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # tiff2cbf example program # $(BIN)/tiff2cbf: $(LIB)/libcbf.a $(EXAMPLES)/tiff2cbf.c \ $(GOPTLIB) $(GOPTINC) $(TIFF) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ -I$(TIFFPREFIX)/include $(EXAMPLES)/tiff2cbf.c $(GOPTLIB) -L$(LIB) \ -lcbf -L$(TIFFPREFIX)/lib -ltiff $(EXTRALIBS) -limg -o $@ # # Andy Arvai's buffered read test program # $(BIN)/arvai_test: $(LIB)/libcbf.a $(EXAMPLES)/arvai_test.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/arvai_test.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # testreals example program # $(BIN)/testreals: $(LIB)/libcbf.a $(EXAMPLES)/testreals.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testreals.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testflat example program # $(BIN)/testflat: $(LIB)/libcbf.a $(EXAMPLES)/testflat.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testflat.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testflatpacked example program # $(BIN)/testflatpacked: $(LIB)/libcbf.a $(EXAMPLES)/testflatpacked.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testflatpacked.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ ifneq ($(F90C),) # # test_xds_binary example program # $(BIN)/test_xds_binary: $(LIB)/libfcb.a $(EXAMPLES)/test_xds_binary.f90 $(F90C) $(F90FLAGS) $(F90LDFLAGS) $(EXAMPLES)/test_xds_binary.f90 \ -L$(LIB) -lfcb -o $@ # # test_fcb_read_image example program # $(BIN)/test_fcb_read_image: $(LIB)/libfcb.a $(EXAMPLES)/test_fcb_read_image.f90 $(F90C) $(F90FLAGS) $(F90LDFLAGS) $(EXAMPLES)/test_fcb_read_image.f90 \ -L$(LIB) -lfcb -o $@ endif # # testcbf (C) # $(BIN)/ctestcbf: $(EXAMPLES)/testcbf.c $(LIB)/libcbf.a $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testcbf.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testcbf (Java) # $(BIN)/testcbf.class: $(EXAMPLES)/testcbf.java $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf_wrap.so $(JAVAC) -cp $(JCBF)/cbflib-$(VERSION).jar -d $(BIN) $(EXAMPLES)/testcbf.java # # Data files for tests # $(DATADIRI): (cd ..; $(DOWNLOAD) $(DATAURLI)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Input.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Input.tar.gz) $(DATADIRO): (cd ..; $(DOWNLOAD) $(DATAURLO)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Output.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Output.tar.gz) $(DATADIRS): (cd ..; $(DOWNLOAD) $(DATAURLS)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz) # Input Data Files TESTINPUT_BASIC = example.mar2300 DATADIRI_INPUT_BASIC = $(DATADIRI)/example.mar2300$(CEXT) TESTINPUT_EXTRA = 9ins.cif mb_LP_1_001.img insulin_pilatus6m.cbf testrealin.cbf \ testflatin.cbf testflatpackedin.cbf XRD1621.tif DATADIRI_INPUT_EXTRA = $(DATADIRI)/9ins.cif$(CEXT) $(DATADIRI)/mb_LP_1_001.img$(CEXT) \ $(DATADIRI)/insulin_pilatus6m.cbf$(CEXT) $(DATADIRI)/testrealin.cbf$(CEXT) \ $(DATADIRI)/testflatin.cbf$(CEXT) $(DATADIRI)/testflatpackedin.cbf$(CEXT) \ $(DATADIRI)/XRD1621.tif$(CEXT) # Output Data Files TESTOUTPUT = adscconverted_flat_orig.cbf \ adscconverted_orig.cbf converted_flat_orig.cbf converted_orig.cbf \ insulin_pilatus6mconverted_orig.cbf \ mb_LP_1_001_orig.cbf testcell_orig.prt \ test_xds_bin_testflatout_orig.out \ test_xds_bin_testflatpackedout_orig.out test_fcb_read_testflatout_orig.out \ test_fcb_read_testflatpackedout_orig.out \ XRD1621_orig.cbf XRD1621_I4encbC100_orig.cbf NEWTESTOUTPUT = adscconverted_flat.cbf \ adscconverted.cbf converted_flat.cbf converted.cbf \ insulin_pilatus6mconverted.cbf \ mb_LP_1_001.cbf testcell.prt \ test_xds_bin_testflatout.out \ test_xds_bin_testflatpackedout.out test_fcb_read_testflatout.out \ test_fcb_read_testflatpackedout.out \ XRD1621.cbf XRD1621_I4encbC100.cbf DATADIRO_OUTPUT = $(DATADIRO)/adscconverted_flat_orig.cbf$(CEXT) \ $(DATADIRO)/adscconverted_orig.cbf$(CEXT) \ $(DATADIRO)/converted_flat_orig.cbf$(CEXT) \ $(DATADIRO)/converted_orig.cbf$(CEXT) \ $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(CEXT) \ $(DATADIRO)/mb_LP_1_001_orig.cbf$(CEXT) \ $(DATADIRO)/testcell_orig.prt$(CEXT) \ $(DATADIRO)/test_xds_bin_testflatout_orig.out$(CEXT) \ $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(CEXT) \ $(DATADIRO)/test_fcb_read_testflatout_orig.out$(CEXT) \ $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(CEXT) \ $(DATADIRO)/XRD1621_orig.cbf$(CEXT) \ $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(CEXT) DATADIRO_OUTPUT_SIGNATURES = $(DATADIRO)/adscconverted_flat_orig.cbf$(SEXT) \ $(DATADIRO)/adscconverted_orig.cbf$(SEXT) \ $(DATADIRO)/converted_flat_orig.cbf$(SEXT) \ $(DATADIRO)/converted_orig.cbf$(SEXT) \ $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(SEXT) \ $(DATADIRO)/mb_LP_1_001_orig.cbf$(SEXT) \ $(DATADIRO)/testcell_orig.prt$(SEXT) \ $(DATADIRO)/test_xds_bin_testflatout_orig.out$(SEXT) \ $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(SEXT) \ $(DATADIRO)/test_fcb_read_testflatout_orig.out$(SEXT) \ $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(SEXT) \ $(DATADIRO)/XRD1621_orig.cbf$(SEXT) \ $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(SEXT) # Output Data File Signatures TESTOUTPUTSIGS = adscconverted_flat_orig.cbf$(SEXT) \ adscconverted_orig.cbf$(SEXT) converted_flat_orig.cbf$(SEXT) converted_orig.cbf$(SEXT) \ insulin_pilatus6mconverted_orig.cbf$(SEXT) \ mb_LP_1_001_orig.cbf$(SEXT) testcell_orig.prt$(SEXT) \ test_xds_bin_testflatout_orig.out$(SEXT) \ test_xds_bin_testflatpackedout_orig.out$(SEXT) test_fcb_read_testflatout_orig.out$(SEXT) \ test_fcb_read_testflatpackedout_orig.out$(SEXT) \ XRD1621_orig.cbf$(SEXT) DATADIRS_OUTPUT_SIGNATURES = $(DATADIRS)/adscconverted_flat_orig.cbf$(SEXT) \ $(DATADIRS)/adscconverted_orig.cbf$(SEXT) \ $(DATADIRS)/converted_flat_orig.cbf$(SEXT) \ $(DATADIRS)/converted_orig.cbf$(SEXT) \ $(DATADIRS)/insulin_pilatus6mconverted_orig.cbf$(SEXT) \ $(DATADIRS)/mb_LP_1_001_orig.cbf$(SEXT) \ $(DATADIRS)/testcell_orig.prt$(SEXT) \ $(DATADIRS)/test_xds_bin_testflatout_orig.out$(SEXT) \ $(DATADIRS)/test_xds_bin_testflatpackedout_orig.out$(SEXT) \ $(DATADIRS)/test_fcb_read_testflatout_orig.out$(SEXT) \ $(DATADIRS)/test_fcb_read_testflatpackedout_orig.out$(SEXT) \ $(DATADIRS)/XRD1621_orig.cbf$(SEXT) \ $(DATADIRS)/XRD1621_I4encbC100_orig.cbf$(SEXT) # Fetch Input Data Files $(TESTINPUT_BASIC): $(DATADIRI) $(DATADIRI_INPUT_BASIC) $(DECOMPRESS) < $(DATADIRI)/$@$(CEXT) > $@ cp $(DATADIRI)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) $(TESTINPUT_EXTRA): $(DATADIRI) $(DATADIRI_INPUT_EXTRA) $(DECOMPRESS) < $(DATADIRI)/$@$(CEXT) > $@ cp $(DATADIRI)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) # Fetch Output Data Files and Signatures $(TESTOUTPUT): $(DATADIRO) $(DATADIRO_OUTPUT) $(DATADIRO_OUTPUT_SIGNATURES) $(DECOMPRESS) < $(DATADIRO)/$@$(CEXT) > $@ cp $(DATADIRO)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) # Fetch Output Data File Signatures $(TESTOUTPUTSIGS): $(DATADIRS) $(DATADIRS_OUTPUT_SIGNATURES) cp $(DATADIRS)/$@ $@ # # Tests # tests: $(LIB) $(BIN) symlinksdone basic extra dectristests pycbftests tests_sigs_only: $(LIB) $(BIN) symlinksdone basic extra_sigs_only restore_output: $(NEWTESTOUTPUT) $(DATADIRO) $(SIGNATURE) < adscconverted_flat.cbf > $(DATADIRO)/adscconverted_flat_orig.cbf$(SEXT) $(SIGNATURE) < adscconverted.cbf > $(DATADIRO)/adscconverted_orig.cbf$(SEXT) $(SIGNATURE) < converted_flat.cbf > $(DATADIRO)/converted_flat_orig.cbf$(SEXT) $(SIGNATURE) < converted.cbf > $(DATADIRO)/converted_orig.cbf$(SEXT) $(SIGNATURE) < insulin_pilatus6mconverted.cbf > $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(SEXT) $(SIGNATURE) < mb_LP_1_001.cbf$ > $(DATADIRO)/mb_LP_1_001_orig.cbf$(SEXT) $(SIGNATURE) < testcell.prt > $(DATADIRO)/testcell_orig.prt$(SEXT) $(SIGNATURE) < test_xds_bin_testflatout.out > $(DATADIRO)/test_xds_bin_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_xds_bin_testflatpackedout.out > $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatout.out > $(DATADIRO)/test_fcb_read_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatpackedout.out > $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < XRD1621.cbf > $(DATADIRO)/XRD1621_orig.cbf$(SEXT) $(SIGNATURE) < XRD1621_I4encbC100.cbf > $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(SEXT) $(COMPRESS) < adscconverted_flat.cbf > $(DATADIRO)/adscconverted_flat_orig.cbf$(CEXT) $(COMPRESS) < adscconverted.cbf > $(DATADIRO)/adscconverted_orig.cbf$(CEXT) $(COMPRESS) < converted_flat.cbf > $(DATADIRO)/converted_flat_orig.cbf$(CEXT) $(COMPRESS) < converted.cbf > $(DATADIRO)/converted_orig.cbf$(CEXT) $(COMPRESS) < insulin_pilatus6mconverted.cbf > $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(CEXT) $(COMPRESS) < mb_LP_1_001.cbf$ > $(DATADIRO)/mb_LP_1_001_orig.cbf$(CEXT) $(COMPRESS) < testcell.prt > $(DATADIRO)/testcell_orig.prt$(CEXT) $(COMPRESS) < test_xds_bin_testflatout.out > $(DATADIRO)/test_xds_bin_testflatout_orig.out$(CEXT) $(COMPRESS) < test_xds_bin_testflatpackedout.out > $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(CEXT) $(COMPRESS) < test_fcb_read_testflatout.out > $(DATADIRO)/test_fcb_read_testflatout_orig.out$(CEXT) $(COMPRESS) < test_fcb_read_testflatpackedout.out > $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(CEXT) $(COMPRESS) < XRD1621.cbf > $(DATADIRO)/XRD1621_orig.cbf$(CEXT) $(COMPRESS) < XRD1621_I4encbC100.cbf > $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(CEXT) restore_sigs_only: $(NEWTESTOUTPUT) $(DATADIRS) $(SIGNATURE) < adscconverted_flat.cbf > $(DATADIRS)/adscconverted_flat_orig.cbf$(SEXT) $(SIGNATURE) < adscconverted.cbf > $(DATADIRS)/adscconverted_orig.cbf$(SEXT) $(SIGNATURE) < converted_flat.cbf > $(DATADIRS)/converted_flat_orig.cbf$(SEXT) $(SIGNATURE) < converted.cbf > $(DATADIRS)/converted_orig.cbf$(SEXT) $(SIGNATURE) < insulin_pilatus6mconverted.cbf > $(DATADIRS)/insulin_pilatus6mconverted_orig.cbf$(SEXT) $(SIGNATURE) < mb_LP_1_001.cbf$ > $(DATADIRS)/mb_LP_1_001_orig.cbf$(SEXT) $(SIGNATURE) < testcell.prt > $(DATADIRS)/testcell_orig.prt$(SEXT) $(SIGNATURE) < test_xds_bin_testflatout.out > $(DATADIRS)/test_xds_bin_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_xds_bin_testflatpackedout.out > $(DATADIRS)/test_xds_bin_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatout.out > $(DATADIRS)/test_fcb_read_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatpackedout.out > $(DATADIRS)/test_fcb_read_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < XRD1621.cbf > $(DATADIRS)/XRD1621_orig.cbf$(SEXT) $(SIGNATURE) < XRD1621_I4encbC100.cbf > $(DATADIRS)/XRD1621_I4encbC100_orig.cbf$(SEXT) restore_signatures: restore_output restore_sigs_only # # Basic Tests # basic: $(BIN)/makecbf $(BIN)/img2cif $(BIN)/cif2cbf $(TESTINPUT_BASIC) $(BIN)/makecbf example.mar2300 makecbf.cbf $(BIN)/img2cif -c flatpacked -m headers -d digest \ -e base64 example.mar2300 img2cif_packed.cif $(BIN)/img2cif -c canonical -m headers -d digest \ -e base64 example.mar2300 img2cif_canonical.cif $(BIN)/img2cif -c flatpacked -m headers -d digest \ -e none example.mar2300 img2cif_packed.cbf $(BIN)/img2cif -c canonical -m headers -d digest \ -e none example.mar2300 img2cif_canonical.cbf $(BIN)/cif2cbf -e none -c flatpacked \ img2cif_canonical.cif cif2cbf_packed.cbf $(BIN)/cif2cbf -e none -c canonical \ img2cif_packed.cif cif2cbf_canonical.cbf -cmp cif2cbf_packed.cbf makecbf.cbf -cmp cif2cbf_packed.cbf img2cif_packed.cbf -cmp cif2cbf_canonical.cbf img2cif_canonical.cbf # # Extra Tests # ifneq ($(F90C),) extra: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/test_xds_binary $(BIN)/test_fcb_read_image $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg \ $(BIN)/changtestcompression $(BIN)/tiff2cbf \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUT) else extra: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUT) endif $(TIME) $(BIN)/cif2cbf -e hex -c none \ makecbf.cbf cif2cbf_ehcn.cif $(TIME) $(BIN)/cif2cbf -e none -c flatpacked \ cif2cbf_ehcn.cif cif2cbf_encp.cbf; rm cif2cbf_ehcn.cif -cmp makecbf.cbf cif2cbf_encp.cbf $(TIME) $(BIN)/cif2cbf -i 9ins.cif -o 9ins.cbf -cmp 9ins.cif 9ins.cbf $(TIME) $(BIN)/convert_image -F example.mar2300 converted_flat.cbf -cmp converted_flat.cbf converted_flat_orig.cbf $(TIME) $(BIN)/convert_image example.mar2300 converted.cbf -cmp converted.cbf converted_orig.cbf -$(TIME) $(BIN)/testcell < testcell.dat > testcell.prt -cmp testcell.prt testcell_orig.prt $(TIME) $(BIN)/convert_image -F -d adscquantum315 mb_LP_1_001.img adscconverted_flat.cbf -cmp adscconverted_flat.cbf adscconverted_flat_orig.cbf $(TIME) $(BIN)/convert_image -d adscquantum315 mb_LP_1_001.img adscconverted.cbf -cmp adscconverted.cbf adscconverted_orig.cbf $(TIME) $(BIN)/adscimg2cbf --no_pad --cbf_packed,flat mb_LP_1_001.img -cmp mb_LP_1_001.cbf mb_LP_1_001_orig.cbf ifneq ($(CLEANTESTS),) mv mb_LP_1_001.cbf nmb_LP_1_001.cbf else cp mb_LP_1_001.cbf nmb_LP_1_001.cbf endif $(TIME) $(BIN)/cbf2adscimg nmb_LP_1_001.cbf -cmp nmb_LP_1_001.img mb_LP_1_001.img rm nmb_LP_1_001.cbf ifneq ($(CLEANTESTS),) rm nmb_LP_1_001.img endif $(TIME) $(BIN)/convert_minicbf -d pilatus6m insulin_pilatus6m.cbf insulin_pilatus6mconverted.cbf -cmp insulin_pilatus6mconverted.cbf insulin_pilatus6mconverted_orig.cbf $(TIME) $(BIN)/testreals -cmp testrealin.cbf testrealout.cbf $(TIME) $(BIN)/testflat -cmp testflatin.cbf testflatout.cbf $(TIME) $(BIN)/testflatpacked -cmp testflatpackedin.cbf testflatpackedout.cbf ifneq ($(F90C),) echo testflatout.cbf | $(TIME) $(BIN)/test_xds_binary > test_xds_bin_testflatout.out -$(DIFF) test_xds_bin_testflatout.out test_xds_bin_testflatout_orig.out echo testflatpackedout.cbf | $(TIME) $(BIN)/test_xds_binary > test_xds_bin_testflatpackedout.out -$(DIFF) test_xds_bin_testflatpackedout.out test_xds_bin_testflatpackedout_orig.out echo testflatout.cbf | $(TIME) $(BIN)/test_fcb_read_image > test_fcb_read_testflatout.out -$(DIFF) test_fcb_read_testflatout.out test_fcb_read_testflatout_orig.out echo testflatpackedout.cbf | $(TIME) $(BIN)/test_fcb_read_image > test_fcb_read_testflatpackedout.out -$(DIFF) test_fcb_read_testflatpackedout.out test_fcb_read_testflatpackedout_orig.out endif $(TIME) $(BIN)/sauter_test $(TIME) $(BIN)/changtestcompression $(TIME) (export LD_LIBRARY_PATH=$(LIB);$(BIN)/tiff2cbf XRD1621.tif XRD1621.cbf) -$(DIFF) XRD1621.cbf XRD1621_orig.cbf $(TIME) $(BIN)/cif2cbf -I 4 -C 100. -L 0. -e n -c b -i XRD1621.cbf -o XRD1621_I4encbC100.cbf -$(DIFF) XRD1621_I4encbC100.cbf XRD1621_I4encbC100_orig.cbf ifneq ($(F90C),) extra_sigs_only: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/test_xds_binary $(BIN)/test_fcb_read_image $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg $(BIN)/tiff2cbf \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) else extra_sigs_only: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf\ basic $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) endif $(TIME) $(BIN)/cif2cbf -e hex -c none \ makecbf.cbf cif2cbf_ehcn.cif $(TIME) $(BIN)/cif2cbf -e none -c packed \ cif2cbf_ehcn.cif cif2cbf_encp.cbf; rm cif2cbf_ehcn.cif -cmp makecbf.cbf cif2cbf_encp.cbf $(TIME) $(BIN)/cif2cbf -i 9ins.cif -o 9ins.cbf -cmp 9ins.cif 9ins.cbf $(TIME) $(BIN)/convert_image -F example.mar2300 converted_flat.cbf -$(SIGNATURE) < converted_flat.cbf | $(DIFF) - converted_flat_orig.cbf$(SEXT); rm converted_flat.cbf $(TIME) $(BIN)/convert_image example.mar2300 converted.cbf -$(SIGNATURE) < converted.cbf | $(DIFF) - converted_orig.cbf$(SEXT); rm converted.cbf -$(TIME) $(BIN)/testcell < testcell.dat | \ $(SIGNATURE) | $(DIFF) - testcell_orig.prt$(SEXT) $(TIME) $(BIN)/convert_image -F -d adscquantum315 mb_LP_1_001.img adscconverted_flat.cbf -$(SIGNATURE) < adscconverted_flat.cbf | $(DIFF) - adscconverted_flat_orig.cbf$(SEXT) $(TIME) $(BIN)/convert_image -d adscquantum315 mb_LP_1_001.img adscconverted.cbf -$(SIGNATURE) < adscconverted.cbf | $(DIFF) - adscconverted_orig.cbf$(SEXT); rm adscconverted.cbf $(TIME) $(BIN)/adscimg2cbf --cbf_packed,flat mb_LP_1_001.img -$(SIGNATURE) < mb_LP_1_001.cbf | $(DIFF) - mb_LP_1_001_orig.cbf$(SEXT) mv mb_LP_1_001.cbf nmb_LP_1_001.cbf $(TIME) $(BIN)/cbf2adscimg nmb_LP_1_001.cbf -cmp nmb_LP_1_001.img mb_LP_1_001.img rm nmb_LP_1_001.cbf rm nmb_LP_1_001.img $(TIME) $(BIN)/convert_minicbf -d pilatus6m insulin_pilatus6m.cbf insulin_pilatus6mconverted.cbf -$(SIGNATURE) < insulin_pilatus6mconverted.cbf | $(DIFF) - insulin_pilatus6mconverted_orig.cbf$(SEXT); rm insulin_pilatus6mconverted.cbf $(TIME) $(BIN)/testreals -cmp testrealin.cbf testrealout.cbf $(TIME) $(BIN)/testflat -cmp testflatin.cbf testflatout.cbf $(TIME) $(BIN)/testflatpacked -cmp testflatpackedin.cbf testflatpackedout.cbf ifneq ($(F90C),) echo testflatout.cbf | $(TIME) $(BIN)/test_xds_binary | \ $(SIGNATURE) | $(DIFF) - test_xds_bin_testflatout_orig.out$(SEXT) echo testflatpackedout.cbf | $(TIME) $(BIN)/test_xds_binary | \ $(SIGNATURE) | $(DIFF) - test_xds_bin_testflatpackedout_orig.out$(SEXT) echo testflatout.cbf | $(TIME) $(BIN)/test_fcb_read_image | \ $(SIGNATURE) | $(DIFF) - test_fcb_read_testflatout_orig.out$(SEXT) echo testflatpackedout.cbf | $(TIME) $(BIN)/test_fcb_read_image | \ $(SIGNATURE) | $(DIFF) - test_fcb_read_testflatpackedout_orig.out$(SEXT) endif $(TIME) $(BIN)/sauter_test $(TIME) $(BIN)/tiff2cbf XRD1621.tif XRD1621.cbf $(TIME) $(BIN)/cif2cbf -I 4 -C 100. -L 0. -e n -c b -i XRD1621.cbf -o XRD1621_I4encbC100.cbf -$(SIGNATURE) < XRD1621.cbf | $(DIFF) - XRD1621_orig.cbf$(SEXT); rm XRD1621.cbf -$(SIGNATURE) < XRD1621_I4encbC100.cbf | $(DIFF) - XRD1621_I4encbC100_orig.cbf$(SEXT); rm XRD1621_I4encbC100.cbf @-rm -f adscconverted_flat.cbf @-rm -f $(TESTINPUT_BASIC) $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) @-rm -f cif2cbf_packed.cbf makecbf.cbf \ cif2cbf_packed.cbf img2cif_packed.cbf \ cif2cbf_canonical.cbf img2cif_canonical.cbf @-rm -f testrealout.cbf testflatout.cbf testflatpackedout.cbf \ cif2cbf_encp.cbf img2cif_canonical.cif img2cif_packed.cif 9ins.cbf pycbftests: $(PYCBF)/_pycbf.$(PYCBFEXT) (cd $(PYCBF); python pycbf_test1.py) (cd $(PYCBF); python pycbf_test2.py) (cd $(PYCBF); python pycbf_test3.py) javatests: $(BIN)/ctestcbf $(BIN)/testcbf.class $(SOLIB)/libcbf_wrap.so $(BIN)/ctestcbf > testcbfc.txt $(LDPREFIX) java -cp $(JCBF)/cbflib-$(VERSION).jar:$(BIN) testcbf > testcbfj.txt $(DIFF) testcbfc.txt testcbfj.txt dectristests: $(BIN)/cbf_template_t $(DECTRIS_EXAMPLES)/cbf_test_orig.out (cd $(DECTRIS_EXAMPLES); ../../bin/cbf_template_t; diff -a -u cbf_test_orig.out cbf_template_t.out) # # Remove all non-source files # empty: @-rm -f $(LIB)/*.o @-rm -f $(LIB)/libcbf.a @-rm -f $(LIB)/libfcb.a @-rm -f $(LIB)/libimg.a @-rm -f $(LIB)/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/build/*/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/build/src/cbf_simple.o @-rm -f $(PYCBF)/build/*/pycbf_wrap.o @-rm -rf $(BIN)/adscimg2cbf* @-rm -rf $(BIN)/cbf2adscimg* @-rm -rf $(BIN)/makecbf* @-rm -rf $(BIN)/img2cif* @-rm -rf $(BIN)/cif2cbf* @-rm -rf $(BIN)/convert_image* @-rm -rf $(BIN)/convert_minicbf* @-rm -rf $(BIN)/test_fcb_read_image* @-rm -rf $(BIN)/test_xds_binary* @-rm -rf $(BIN)/testcell* @-rm -rf $(BIN)/cif2c* @-rm -rf $(BIN)/testreals* @-rm -rf $(BIN)/testflat* @-rm -rf $(BIN)/testflatpacked* @-rm -rf $(BIN)/cbf_template_t* @-rm -rf $(BIN)/sauter_test* @-rm -rf $(BIN)/arvai_test* @-rm -rf $(BIN)/changtestcompression* @-rm -rf $(BIN)/tiff2cbf* @-rm -f makecbf.cbf @-rm -f img2cif_packed.cif @-rm -f img2cif_canonical.cif @-rm -f img2cif_packed.cbf @-rm -f img2cif_canonical.cbf @-rm -f img2cif_raw.cbf @-rm -f cif2cbf_packed.cbf @-rm -f cif2cbf_canonical.cbf @-rm -f converted.cbf @-rm -f adscconverted.cbf @-rm -f converted_flat.cbf @-rm -f adscconverted_flat.cbf @-rm -f adscconverted_flat_rev.cbf @-rm -f mb_LP_1_001.cbf @-rm -f cif2cbf_ehcn.cif @-rm -f cif2cbf_encp.cbf @-rm -f 9ins.cbf @-rm -f 9ins.cif @-rm -f testcell.prt @-rm -f example.mar2300 @-rm -f converted_orig.cbf @-rm -f adscconverted_orig.cbf @-rm -f converted_flat_orig.cbf @-rm -f adscconverted_flat_orig.cbf @-rm -f adscconverted_flat_rev_orig.cbf @-rm -f mb_LP_1_001_orig.cbf @-rm -f insulin_pilatus6mconverted_orig.cbf @-rm -f insulin_pilatus6mconverted.cbf @-rm -f insulin_pilatus6m.cbf @-rm -f testrealin.cbf @-rm -f testrealout.cbf @-rm -f testflatin.cbf @-rm -f testflatout.cbf @-rm -f testflatpackedin.cbf @-rm -f testflatpackedout.cbf @-rm -f CTC.cbf @-rm -f test_fcb_read_testflatout.out @-rm -f test_fcb_read_testflatpackedout.out @-rm -f test_xds_bin_testflatpackedout.out @-rm -f test_xds_bin_testflatout.out @-rm -f test_fcb_read_testflatout_orig.out @-rm -f test_fcb_read_testflatpackedout_orig.out @-rm -f test_xds_bin_testflatpackedout_orig.out @-rm -f test_xds_bin_testflatout_orig.out @-rm -f mb_LP_1_001.img @-rm -f 9ins.cif @-rm -f testcell_orig.prt @-rm -f $(DECTRIS_EXAMPLES)/cbf_template_t.out @-rm -f XRD1621.cbf @-rm -f XRD1621_orig.cbf @-rm -f XRD1621_orig.cbf @-rm -f XRD1621_I4encbC100.cbf @-rm -f $(SRC)/fcb_exit_binary.f90 @-rm -f $(SRC)/fcb_next_binary.f90 @-rm -f $(SRC)/fcb_open_cifin.f90 @-rm -f $(SRC)/fcb_packed.f90 @-rm -f $(SRC)/fcb_read_bits.f90 @-rm -f $(SRC)/fcb_read_image.f90 @-rm -f $(SRC)/fcb_read_xds_i2.f90 @-rm -f $(EXAMPLES)/test_fcb_read_image.f90 @-rm -f $(EXAMPLES)/test_xds_binary.f90 @-rm -f symlinksdone @-rm -f $(TESTOUTPUT) *$(SEXT) @-rm -f $(SOLIB)/*.o @-rm -f $(SOLIB)/libcbf_wrap.so @-rm -f $(SOLIB)/libjcbf.so @-rm -f $(SOLIB)/libimg.so @-rm -f $(SOLIB)/libfcb.so @-rm -rf $(JCBF)/org @-rm -f $(JCBF)/*.java @-rm -f $(JCBF)/jcbf_wrap.c @-rm -f $(SRC)/cbf_wrap.c @-rm -f $(BIN)/ctestcbf $(BIN)/testcbf.class testcbfc.txt testcbfj.txt @-rm -rf $(REGEX) @-rm -rf $(TIFF) ./.undosymlinks # # Remove temporary files # clean: @-rm -f core @-rm -f *.o @-rm -f *.u # # Restore to distribution state # distclean: clean empty # # Create a Tape Archive for distribution # tar: $(DOCUMENTS) $(SOURCE) $(SRC)/cbf.stx $(HEADERS) $(M4FILES)\ $(EXAMPLES) \ README.html README Makefile \ $(JPEGS) -/bin/rm -f CBFlib.tar* tar cvBf CBFlib.tar \ $(DOCUMENTS) $(SOURCE) $(SRC)/cbf.stx $(HEADERS) $(M4FILES)\ $(EXAMPLES) \ README.html README Makefile \ $(JPEGS) gzip --best CBFlib.tar ./CBFlib-0.9.2.2/mswin/0000755000076500007650000000000011603703065012740 5ustar yayayaya./CBFlib-0.9.2.2/mswin/lib/0000755000076500007650000000000011603703070013502 5ustar yayayaya./CBFlib-0.9.2.2/mswin/lib/CBFlib_prj.xml0000644000076500007650000046632311603702116016176 0ustar yayayaya ]> CBFlib_debug.lib UserSourceTrees AlwaysSearchUserPathstrue InterpretDOSAndUnixPathstrue RequireFrameworkStyleIncludesfalse SourceRelativeIncludestrue UserSearchPaths SearchPath Path PathFormatWindows PathRootProject Recursivetrue FrameworkPathfalse HostFlagsAll SearchPath Path../../src PathFormatUnix PathRootProject Recursivetrue FrameworkPathfalse HostFlagsAll SearchPath Path../../include PathFormatUnix PathRootProject Recursivetrue FrameworkPathfalse HostFlagsAll SystemSearchPaths SearchPath PathMSL PathFormatWindows PathRootCodeWarrior Recursivetrue FrameworkPathfalse HostFlagsAll SearchPath PathWin32-x86 Support\ PathFormatWindows PathRootCodeWarrior Recursivetrue FrameworkPathfalse HostFlagsAll MWRuntimeSettings_WorkingDirectory MWRuntimeSettings_CommandLine MWRuntimeSettings_HostApplication Path PathFormatGeneric PathRootAbsolute MWRuntimeSettings_EnvVars LinkerWin32 x86 Linker PreLinker PostLinker TargetnameCBFlib_debug.lib OutputDirectory Path PathFormatWindows PathRootProject SaveEntriesUsingRelativePathsfalse FileMappings FileTypeTEXT FileExtension.c CompilerMW C/C++ x86 EditLanguageC/C++ Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileTypeTEXT FileExtension.c++ CompilerMW C/C++ x86 EditLanguageC/C++ Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileTypeTEXT FileExtension.cc CompilerMW C/C++ x86 EditLanguageC/C++ Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileTypeTEXT FileExtension.cp CompilerMW C/C++ x86 EditLanguageC/C++ Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileTypeTEXT FileExtension.cpp CompilerMW C/C++ x86 EditLanguageC/C++ Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileTypeTEXT FileExtension.cxx CompilerMW C/C++ x86 EditLanguageC/C++ Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileTypeTEXT FileExtension.def Compiler EditLanguage Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileTypeTEXT FileExtension.h CompilerMW C/C++ x86 EditLanguageC/C++ Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMaketrue FileTypeTEXT FileExtension.h++ CompilerMW C/C++ x86 EditLanguageC/C++ Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMaketrue FileTypeTEXT FileExtension.hpp CompilerMW C/C++ x86 EditLanguageC/C++ Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMaketrue FileTypeTEXT FileExtension.hxx CompilerMW C/C++ x86 EditLanguageC/C++ Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMaketrue FileTypeTEXT FileExtension.ord Compiler EditLanguage Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileTypeTEXT FileExtension.pch CompilerMW C/C++ x86 EditLanguageC/C++ Precompiletrue Launchablefalse ResourceFilefalse IgnoredByMakefalse FileTypeTEXT FileExtension.pch++ CompilerMW C/C++ x86 EditLanguageC/C++ Precompiletrue Launchablefalse ResourceFilefalse IgnoredByMakefalse FileTypeTEXT FileExtension.rc CompilerMW WinRC EditLanguageBalloon Help Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileTypeiLIB FileExtension CompilerLib Import x86 EditLanguage Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileTypeiOBJ FileExtension CompilerObj Import x86 EditLanguage Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileExtension.a CompilerLib Import x86 EditLanguage Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileExtension.dll CompilerDLL Import x86 EditLanguage Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileExtension.doc Compiler EditLanguage Precompilefalse Launchabletrue ResourceFilefalse IgnoredByMaketrue FileExtension.exe CompilerDLL Import x86 EditLanguage Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileExtension.lib CompilerLib Import x86 EditLanguage Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileExtension.o CompilerObj Import x86 EditLanguage Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileExtension.obj CompilerObj Import x86 EditLanguage Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileExtension.pl CompilerPerl Tool EditLanguagePerl Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileExtension.psh CompilerShell Tool EditLanguage Precompiletrue Launchablefalse ResourceFilefalse IgnoredByMakefalse FileExtension.res CompilerWinRes Import EditLanguageBalloon Help Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileExtension.sh CompilerShell Tool EditLanguage Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse CacheModDatestrue DumpBrowserInfofalse CacheSubprojectstrue UseThirdPartyDebuggerfalse BrowserGenerator2 DebuggerAppPath Path PathFormatGeneric PathRootAbsolute DebuggerCmdLineArgs DebuggerWorkingDir Path PathFormatGeneric PathRootAbsolute CodeCompletionPrefixFileName CodeCompletionMacroFileNameWin32_C_Macros.h ConsoleEncoding0 LogSystemMessagesfalse AutoTargetDLLsPopUp0 StopAtWatchpointstrue PauseWhileRunningfalse PauseInterval5 PauseUIFlags0 AltExePath Path PathFormatGeneric PathRootAbsolute StopAtTempBPOnLaunchtrue CacheSymbolicstrue TempBPFunctionNamemain TempBPType0 Enabledfalse ConnectionName DownloadPath LaunchRemoteAppfalse RemoteAppPath CoreID0 JTAGClockSpeed8000 IsMultiCorefalse OSDownloadfalse UseGlobalOSDownloadfalse OSDownloadConnectionName OSDownloadPath AltDownloadfalse AltDownloadConnectionName OtherExecutables AnalyzerConnectionName CustomColor1 Red0 Green32767 Blue0 CustomColor2 Red0 Green32767 Blue0 CustomColor3 Red0 Green32767 Blue0 CustomColor4 Red0 Green32767 Blue0 MWFrontEnd_C_cplusplus0 MWFrontEnd_C_checkprotos1 MWFrontEnd_C_arm0 MWFrontEnd_C_trigraphs0 MWFrontEnd_C_onlystdkeywords0 MWFrontEnd_C_enumsalwaysint1 MWFrontEnd_C_ansistrict0 MWFrontEnd_C_wchar_type1 MWFrontEnd_C_enableexceptions0 MWFrontEnd_C_dontreusestrings0 MWFrontEnd_C_poolstrings0 MWFrontEnd_C_dontinline1 MWFrontEnd_C_useRTTI0 MWFrontEnd_C_unsignedchars0 MWFrontEnd_C_autoinline0 MWFrontEnd_C_booltruefalse1 MWFrontEnd_C_inlinelevel0 MWFrontEnd_C_ecplusplus0 MWFrontEnd_C_defer_codegen0 MWFrontEnd_C_templateparser0 MWFrontEnd_C_c990 MWFrontEnd_C_bottomupinline1 MWFrontEnd_C_gcc_extensions0 MWFrontEnd_C_instance_manager1 C_CPP_Preprocessor_EmitFiletrue C_CPP_Preprocessor_EmitLinefalse C_CPP_Preprocessor_EmitFullPathfalse C_CPP_Preprocessor_KeepCommentsfalse C_CPP_Preprocessor_PCHUsesPrefixTextfalse C_CPP_Preprocessor_EmitPragmastrue C_CPP_Preprocessor_KeepWhiteSpacefalse C_CPP_Preprocessor_MultiByteEncodingencASCII_Unicode C_CPP_Preprocessor_PrefixText MWWarning_C_warn_illpragma1 MWWarning_C_warn_emptydecl1 MWWarning_C_warn_possunwant1 MWWarning_C_warn_unusedvar1 MWWarning_C_warn_unusedarg1 MWWarning_C_warn_extracomma1 MWWarning_C_pedantic1 MWWarning_C_warningerrors0 MWWarning_C_warn_hidevirtual1 MWWarning_C_warn_implicitconv0 MWWarning_C_warn_notinlined0 MWWarning_C_warn_structclass1 MWWarning_C_warn_missingreturn0 MWWarning_C_warn_no_side_effect0 MWWarning_C_warn_resultnotused0 MWWarning_C_warn_padding0 MWWarning_C_warn_impl_i2f_conv0 MWWarning_C_warn_impl_f2i_conv0 MWWarning_C_warn_impl_s2u_conv0 MWWarning_C_warn_illtokenpasting0 MWWarning_C_warn_filenamecaps0 MWWarning_C_warn_filenamecapssystem0 MWWarning_C_warn_undefmacro0 MWWarning_C_warn_ptrintconv0 MWMerge_MacOS_projectTypeApplication MWMerge_MacOS_outputNameMerge Out MWMerge_MacOS_outputCreator???? MWMerge_MacOS_outputTypeAPPL MWMerge_MacOS_suppressWarning0 MWMerge_MacOS_copyFragments1 MWMerge_MacOS_copyResources1 MWMerge_MacOS_flattenResource0 MWMerge_MacOS_flatFileNamea.rsrc MWMerge_MacOS_flatFileOutputPath Path: PathFormatMacOS PathRootProject MWMerge_MacOS_skipResources XGLD dikc jorP CPSW FileLockedfalse ResourcesMapIsReadOnlyfalse PrinterDriverIsMultiFinderCompatiblefalse Invisiblefalse HasBundlefalse NameLockedfalse Stationeryfalse HasCustomIconfalse Sharedfalse HasBeenInitedfalse Label0 Comments HasCustomBadgefalse HasRoutingInfofalse MWCodeGen_PPC_structalignmentMC68K MWCodeGen_PPC_tracebacktablesNone MWCodeGen_PPC_processorGeneric MWCodeGen_PPC_function_align4 MWCodeGen_PPC_tocdata1 MWCodeGen_PPC_largetoc0 MWCodeGen_PPC_profiler0 MWCodeGen_PPC_vectortocdata0 MWCodeGen_PPC_poolconst0 MWCodeGen_PPC_peephole1 MWCodeGen_PPC_readonlystrings0 MWCodeGen_PPC_linkerpoolsstrings0 MWCodeGen_PPC_volatileasm0 MWCodeGen_PPC_schedule0 MWCodeGen_PPC_altivec0 MWCodeGen_PPC_altivec_move_block0 MWCodeGen_PPC_strictIEEEfp0 MWCodeGen_PPC_fpcontract1 MWCodeGen_PPC_genfsel0 MWCodeGen_PPC_orderedfpcmp0 MWCodeGen_MachO_structalignmentPPC_mw MWCodeGen_MachO_profiler_enumOff MWCodeGen_MachO_processorGeneric MWCodeGen_MachO_function_align4 MWCodeGen_MachO_common0 MWCodeGen_MachO_boolisint0 MWCodeGen_MachO_peephole1 MWCodeGen_MachO_readonlystrings1 MWCodeGen_MachO_linkerpoolsstrings1 MWCodeGen_MachO_volatileasm0 MWCodeGen_MachO_schedule0 MWCodeGen_MachO_altivec0 MWCodeGen_MachO_vecmove0 MWCodeGen_MachO_fp_ieee_strict0 MWCodeGen_MachO_fpcontract1 MWCodeGen_MachO_genfsel0 MWCodeGen_MachO_fp_cmps_ordered0 MWDisassembler_PPC_showcode1 MWDisassembler_PPC_extended1 MWDisassembler_PPC_mix0 MWDisassembler_PPC_nohex0 MWDisassembler_PPC_showdata1 MWDisassembler_PPC_showexceptions1 MWDisassembler_PPC_showsym0 MWDisassembler_PPC_shownames1 GlobalOptimizer_PPC_optimizationlevelLevel0 GlobalOptimizer_PPC_optforSpeed MWLinker_PPC_linksym1 MWLinker_PPC_symfullpath1 MWLinker_PPC_linkmap0 MWLinker_PPC_nolinkwarnings0 MWLinker_PPC_dontdeadstripinitcode0 MWLinker_PPC_permitmultdefs0 MWLinker_PPC_linkmodeFast MWLinker_PPC_code_foldingNone MWLinker_PPC_initname MWLinker_PPC_mainname__start MWLinker_PPC_termname MWLinker_MacOSX_linksym1 MWLinker_MacOSX_symfullpath0 MWLinker_MacOSX_nolinkwarnings0 MWLinker_MacOSX_linkmap0 MWLinker_MacOSX_dontdeadstripinitcode0 MWLinker_MacOSX_permitmultdefs0 MWLinker_MacOSX_use_objectivec_semantics0 MWLinker_MacOSX_strip_debug_symbols0 MWLinker_MacOSX_prebind_all_twolevel_modules0 MWLinker_MacOSX_data_before_text_segment0 MWLinker_MacOSX_report_msl_overloads0 MWLinker_MacOSX_objects_follow_linkorder0 MWLinker_MacOSX_linkmodeFast MWLinker_MacOSX_exportsReferencedGlobals MWLinker_MacOSX_sortcodeNone MWLinker_MacOSX_mainname MWLinker_MacOSX_initname MWLinker_MacOSX_code_foldingNone MWLinker_MacOSX_stabsgenNone MWProject_MacOSX_typeExecutable MWProject_MacOSX_outfile MWProject_MacOSX_filecreator???? MWProject_MacOSX_filetypeMEXE MWProject_MacOSX_vmaddress4096 MWProject_MacOSX_usedefaultvmaddr1 MWProject_MacOSX_flatrsrc0 MWProject_MacOSX_flatrsrcfilename MWProject_MacOSX_flatrsrcoutputdir Path: PathFormatMacOS PathRootProject MWProject_MacOSX_installpath./ MWProject_MacOSX_dont_prebind0 MWProject_MacOSX_flat_namespace0 MWProject_MacOSX_frameworkversionA MWProject_MacOSX_currentversion0 MWProject_MacOSX_flat_oldimpversion0 MWProject_MacOSX_AddrMode1 MWPEF_exportsNone MWPEF_libfolder0 MWPEF_sortcodeNone MWPEF_expandbss0 MWPEF_sharedata0 MWPEF_olddefversion0 MWPEF_oldimpversion0 MWPEF_currentversion0 MWPEF_fragmentname MWPEF_collapsereloads0 MWProject_PPC_typeApplication MWProject_PPC_outfilea.out MWProject_PPC_filecreator???? MWProject_PPC_filetypeAPPL MWProject_PPC_size384 MWProject_PPC_minsize384 MWProject_PPC_stacksize64 MWProject_PPC_flags22720 MWProject_PPC_symfilename MWProject_PPC_rsrcname MWProject_PPC_rsrcheaderNative MWProject_PPC_rsrctype???? MWProject_PPC_rsrcid0 MWProject_PPC_rsrcflags0 MWProject_PPC_rsrcstore0 MWProject_PPC_rsrcmerge0 MWProject_PPC_flatrsrc0 MWProject_PPC_flatrsrcoutputdir Path: PathFormatMacOS PathRootProject MWProject_PPC_flatrsrcfilename MWAssembler_PPC_auxheader0 MWAssembler_PPC_symmodeMac MWAssembler_PPC_dialectPPC MWAssembler_PPC_prefixfile MWAssembler_PPC_typecheck0 MWAssembler_PPC_warnings0 MWAssembler_PPC_casesensitive0 PList_OutputTypeFile PList_OutputEncodingUTF-8 PList_PListVersion0.9 PList_Prefix PList_FileFilenameInfo.plist PList_FileDirectory Path: PathFormatMacOS PathRootProject PList_ResourceTypets PList_ResourceID0 PList_ResourceName MWRez_Language_maxwidth80 MWRez_Language_scriptRoman MWRez_Language_alignmentAlign1 MWRez_Language_filtermodeFilterSkip MWRez_Language_suppresswarnings0 MWRez_Language_escapecontrolchars1 MWRez_Language_prefixname MWRez_Language_filteredtypes'CODE' 'DATA' 'PICT' MWWinRC_prefixnameResourcePrefix.h MWCodeGen_X86_processorGeneric MWCodeGen_X86_alignmentbytes8 MWCodeGen_X86_exceptionsZeroOverhead MWCodeGen_X86_name_manglingMWWin32 MWCodeGen_X86_use_extinst0 MWCodeGen_X86_extinst_mmx0 MWCodeGen_X86_extinst_3dnow0 MWCodeGen_X86_use_mmx_3dnow_convention0 MWCodeGen_X86_extinst_cmov0 MWCodeGen_X86_extinst_sse0 MWCodeGen_X86_extinst_sse20 MWCodeGen_X86_intrinsics0 MWCodeGen_X86_optimizeasm0 MWCodeGen_X86_disableopts0 MWCodeGen_X86_profile0 MWLinker_X86_runtimeStaticMultiThreadDebug MWCodeGen_X86_readonlystrings0 MWCodeGen_X86_vectorize0 MWCodeGen_X86_relaxieee0 MWLinker_X86_subsysmajorid4 MWLinker_X86_subsysminorid0 MWCOFF_X86_opsysmajorid4 MWCOFF_X86_opsysminorid0 MWLinker_X86_usrmajorid0 MWLinker_X86_usrminorid0 MWProject_X86_maxstacksize1024 MWProject_X86_minstacksize4 MWProject_X86_size1024 MWProject_X86_minsize4 MWCOFF_X86_coff_flags0 MWCOFF_X86_dll_flags0 MWProject_X86_baseaddress4194304 MWCOFF_X86_filealign4096 MWCOFF_X86_sectionalign4096 PDisasmX86_showHeaderstrue PDisasmX86_showSectHeaderstrue PDisasmX86_showSymTabtrue PDisasmX86_showCodetrue PDisasmX86_showDatatrue PDisasmX86_showDebugfalse PDisasmX86_showExceptionsfalse PDisasmX86_showRawfalse PDisasmX86_showAllRawfalse PDisasmX86_showSourcetrue PDisasmX86_showRelocationfalse PDisasmX86_showHextrue PDisasmX86_showCommentsfalse PDisasmX86_showSymDefstrue PDisasmX86_unmanglefalse PDisasmX86_verbosefalse PDisasmX86_resolveRelocstrue PDisasmX86_resolveLocalsfalse MWDebugger_X86_Exceptions 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 GlobalOptimizer_X86_optimizationlevelLevel0 GlobalOptimizer_X86_optforSpeed MWLinker_X86_entrypointusageDefault MWLinker_X86_entrypoint MWLinker_X86_subsystemWinCUI MWLinker_X86_commandfile MWLinker_X86_generatemap0 MWLinker_X86_linksym0 MWLinker_X86_linkCV1 MWLinker_X86_symfullpathtrue MWLinker_X86_linkdebugtrue MWLinker_X86_checksumfalse MWLinker_X86_zero_init_bssfalse MWLinker_X86_mergedatafalse MWLinker_X86_usedefaultlibstrue MWLinker_X86_adddefaultlibsfalse MWLinker_X86_nowarningsfalse MWLinker_X86_verbosefalse MWLinker_X86_linkformemfalse MWLinker_X86_codefoldingNone MWLinker_X86_debuginlinefalse MWProject_X86_typeLibrary MWProject_X86_outfileCBFlib_debug.lib MWProject_X86_importlib MWProject_X86_setimportlibdirfalse MWProject_X86_dontgenerateimportlibtrue MWProject_X86_oldformatlibfalse MWProject_X86_replaceobjextensionfalse MWProject_X86_copyallfilesfalse Name cbf_canonical.c Unix Text Debug Name cbf_byte_offset.c Unix Text Debug Name cbf_binary.c Unix Text Debug Name cbf_ascii.c Unix Text Debug Name cbf_alloc.c Unix Text Debug Name cbf_stx.c Unix Text Debug Name cbf_string.c Unix Text Debug Name cbf_simple.c Unix Text Debug Name cbf_read_mime.c Unix Text Debug Name cbf_read_binary.c Unix Text Debug Name cbf_predictor.c Unix Text Debug Name cbf_packed.c Unix Text Debug Name cbf_lex.c Unix Text Debug Name cbf_file.c Unix Text Debug Name cbf_context.c Unix Text Debug Name cbf_compress.c Unix Text Debug Name cbf_codes.c Unix Text Debug Name cbf.c Unix Text Debug Name cbf_write.c Unix Text Debug Name cbf_uncompressed.c Unix Text Debug Name cbf_tree.c Unix Text Debug Name cbf_write_binary.c Unix Text Debug Name md5c.c Unix Text Debug Name cbf_canonical.c Unix Name cbf_byte_offset.c Unix Name cbf_binary.c Unix Name cbf_ascii.c Unix Name cbf_alloc.c Unix Name cbf_stx.c Unix Name cbf_string.c Unix Name cbf_simple.c Unix Name cbf_read_mime.c Unix Name cbf_read_binary.c Unix Name cbf_predictor.c Unix Name cbf_packed.c Unix Name cbf_lex.c Unix Name cbf_file.c Unix Name cbf_context.c Unix Name cbf_compress.c Unix Name cbf_codes.c Unix Name cbf.c Unix Name cbf_write.c Unix Name cbf_uncompressed.c Unix Name cbf_tree.c Unix Name cbf_write_binary.c Unix Name md5c.c Unix CBFlib.lib UserSourceTrees AlwaysSearchUserPathstrue InterpretDOSAndUnixPathstrue RequireFrameworkStyleIncludesfalse SourceRelativeIncludestrue UserSearchPaths SearchPath Path PathFormatWindows PathRootProject Recursivetrue FrameworkPathfalse HostFlagsAll SearchPath Path../../src PathFormatUnix PathRootProject Recursivetrue FrameworkPathfalse HostFlagsAll SearchPath Path../../include PathFormatUnix PathRootProject Recursivetrue FrameworkPathfalse HostFlagsAll SystemSearchPaths SearchPath PathMSL PathFormatWindows PathRootCodeWarrior Recursivetrue FrameworkPathfalse HostFlagsAll SearchPath PathWin32-x86 Support\ PathFormatWindows PathRootCodeWarrior Recursivetrue FrameworkPathfalse HostFlagsAll MWRuntimeSettings_WorkingDirectory MWRuntimeSettings_CommandLine MWRuntimeSettings_HostApplication Path PathFormatGeneric PathRootAbsolute MWRuntimeSettings_EnvVars LinkerWin32 x86 Linker PreLinker PostLinker TargetnameCBFlib.lib OutputDirectory Path PathFormatWindows PathRootProject SaveEntriesUsingRelativePathsfalse FileMappings FileTypeTEXT FileExtension.c CompilerMW C/C++ x86 EditLanguageC/C++ Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileTypeTEXT FileExtension.c++ CompilerMW C/C++ x86 EditLanguageC/C++ Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileTypeTEXT FileExtension.cc CompilerMW C/C++ x86 EditLanguageC/C++ Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileTypeTEXT FileExtension.cp CompilerMW C/C++ x86 EditLanguageC/C++ Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileTypeTEXT FileExtension.cpp CompilerMW C/C++ x86 EditLanguageC/C++ Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileTypeTEXT FileExtension.cxx CompilerMW C/C++ x86 EditLanguageC/C++ Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileTypeTEXT FileExtension.def Compiler EditLanguage Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileTypeTEXT FileExtension.h CompilerMW C/C++ x86 EditLanguageC/C++ Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMaketrue FileTypeTEXT FileExtension.h++ CompilerMW C/C++ x86 EditLanguageC/C++ Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMaketrue FileTypeTEXT FileExtension.hpp CompilerMW C/C++ x86 EditLanguageC/C++ Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMaketrue FileTypeTEXT FileExtension.hxx CompilerMW C/C++ x86 EditLanguageC/C++ Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMaketrue FileTypeTEXT FileExtension.ord Compiler EditLanguage Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileTypeTEXT FileExtension.pch CompilerMW C/C++ x86 EditLanguageC/C++ Precompiletrue Launchablefalse ResourceFilefalse IgnoredByMakefalse FileTypeTEXT FileExtension.pch++ CompilerMW C/C++ x86 EditLanguageC/C++ Precompiletrue Launchablefalse ResourceFilefalse IgnoredByMakefalse FileTypeTEXT FileExtension.rc CompilerMW WinRC EditLanguageBalloon Help Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileTypeiLIB FileExtension CompilerLib Import x86 EditLanguage Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileTypeiOBJ FileExtension CompilerObj Import x86 EditLanguage Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileExtension.a CompilerLib Import x86 EditLanguage Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileExtension.dll CompilerDLL Import x86 EditLanguage Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileExtension.doc Compiler EditLanguage Precompilefalse Launchabletrue ResourceFilefalse IgnoredByMaketrue FileExtension.exe CompilerDLL Import x86 EditLanguage Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileExtension.lib CompilerLib Import x86 EditLanguage Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileExtension.o CompilerObj Import x86 EditLanguage Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileExtension.obj CompilerObj Import x86 EditLanguage Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileExtension.pl CompilerPerl Tool EditLanguagePerl Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileExtension.psh CompilerShell Tool EditLanguage Precompiletrue Launchablefalse ResourceFilefalse IgnoredByMakefalse FileExtension.res CompilerWinRes Import EditLanguageBalloon Help Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse FileExtension.sh CompilerShell Tool EditLanguage Precompilefalse Launchablefalse ResourceFilefalse IgnoredByMakefalse CacheModDatestrue DumpBrowserInfofalse CacheSubprojectstrue UseThirdPartyDebuggerfalse BrowserGenerator0 DebuggerAppPath Path PathFormatGeneric PathRootAbsolute DebuggerCmdLineArgs DebuggerWorkingDir Path PathFormatGeneric PathRootAbsolute CodeCompletionPrefixFileName CodeCompletionMacroFileNameWin32_C_Macros.h ConsoleEncoding0 LogSystemMessagesfalse AutoTargetDLLsPopUp0 StopAtWatchpointstrue PauseWhileRunningfalse PauseInterval5 PauseUIFlags0 AltExePath Path PathFormatGeneric PathRootAbsolute StopAtTempBPOnLaunchtrue CacheSymbolicstrue TempBPFunctionNamemain TempBPType0 Enabledfalse ConnectionName DownloadPath LaunchRemoteAppfalse RemoteAppPath CoreID0 JTAGClockSpeed8000 IsMultiCorefalse OSDownloadfalse UseGlobalOSDownloadfalse OSDownloadConnectionName OSDownloadPath AltDownloadfalse AltDownloadConnectionName OtherExecutables AnalyzerConnectionName CustomColor1 Red0 Green32767 Blue0 CustomColor2 Red0 Green32767 Blue0 CustomColor3 Red0 Green32767 Blue0 CustomColor4 Red0 Green32767 Blue0 MWFrontEnd_C_cplusplus0 MWFrontEnd_C_checkprotos1 MWFrontEnd_C_arm0 MWFrontEnd_C_trigraphs0 MWFrontEnd_C_onlystdkeywords0 MWFrontEnd_C_enumsalwaysint1 MWFrontEnd_C_ansistrict0 MWFrontEnd_C_wchar_type1 MWFrontEnd_C_enableexceptions0 MWFrontEnd_C_dontreusestrings0 MWFrontEnd_C_poolstrings0 MWFrontEnd_C_dontinline0 MWFrontEnd_C_useRTTI0 MWFrontEnd_C_unsignedchars0 MWFrontEnd_C_autoinline1 MWFrontEnd_C_booltruefalse1 MWFrontEnd_C_inlinelevel0 MWFrontEnd_C_ecplusplus0 MWFrontEnd_C_defer_codegen0 MWFrontEnd_C_templateparser0 MWFrontEnd_C_c990 MWFrontEnd_C_bottomupinline1 MWFrontEnd_C_gcc_extensions0 MWFrontEnd_C_instance_manager1 C_CPP_Preprocessor_EmitFiletrue C_CPP_Preprocessor_EmitLinefalse C_CPP_Preprocessor_EmitFullPathfalse C_CPP_Preprocessor_KeepCommentsfalse C_CPP_Preprocessor_PCHUsesPrefixTextfalse C_CPP_Preprocessor_EmitPragmastrue C_CPP_Preprocessor_KeepWhiteSpacefalse C_CPP_Preprocessor_MultiByteEncodingencASCII_Unicode C_CPP_Preprocessor_PrefixText MWWarning_C_warn_illpragma1 MWWarning_C_warn_emptydecl1 MWWarning_C_warn_possunwant1 MWWarning_C_warn_unusedvar1 MWWarning_C_warn_unusedarg1 MWWarning_C_warn_extracomma1 MWWarning_C_pedantic1 MWWarning_C_warningerrors0 MWWarning_C_warn_hidevirtual1 MWWarning_C_warn_implicitconv0 MWWarning_C_warn_notinlined0 MWWarning_C_warn_structclass1 MWWarning_C_warn_missingreturn0 MWWarning_C_warn_no_side_effect0 MWWarning_C_warn_resultnotused0 MWWarning_C_warn_padding0 MWWarning_C_warn_impl_i2f_conv0 MWWarning_C_warn_impl_f2i_conv0 MWWarning_C_warn_impl_s2u_conv0 MWWarning_C_warn_illtokenpasting0 MWWarning_C_warn_filenamecaps0 MWWarning_C_warn_filenamecapssystem0 MWWarning_C_warn_undefmacro0 MWWarning_C_warn_ptrintconv0 MWMerge_MacOS_projectTypeApplication MWMerge_MacOS_outputNameMerge Out MWMerge_MacOS_outputCreator???? MWMerge_MacOS_outputTypeAPPL MWMerge_MacOS_suppressWarning0 MWMerge_MacOS_copyFragments1 MWMerge_MacOS_copyResources1 MWMerge_MacOS_flattenResource0 MWMerge_MacOS_flatFileNamea.rsrc MWMerge_MacOS_flatFileOutputPath Path: PathFormatMacOS PathRootProject MWMerge_MacOS_skipResources XGLD dikc jorP CPSW FileLockedfalse ResourcesMapIsReadOnlyfalse PrinterDriverIsMultiFinderCompatiblefalse Invisiblefalse HasBundlefalse NameLockedfalse Stationeryfalse HasCustomIconfalse Sharedfalse HasBeenInitedfalse Label0 Comments HasCustomBadgefalse HasRoutingInfofalse MWCodeGen_PPC_structalignmentMC68K MWCodeGen_PPC_tracebacktablesNone MWCodeGen_PPC_processorGeneric MWCodeGen_PPC_function_align4 MWCodeGen_PPC_tocdata1 MWCodeGen_PPC_largetoc0 MWCodeGen_PPC_profiler0 MWCodeGen_PPC_vectortocdata0 MWCodeGen_PPC_poolconst0 MWCodeGen_PPC_peephole1 MWCodeGen_PPC_readonlystrings0 MWCodeGen_PPC_linkerpoolsstrings0 MWCodeGen_PPC_volatileasm0 MWCodeGen_PPC_schedule0 MWCodeGen_PPC_altivec0 MWCodeGen_PPC_altivec_move_block0 MWCodeGen_PPC_strictIEEEfp0 MWCodeGen_PPC_fpcontract1 MWCodeGen_PPC_genfsel0 MWCodeGen_PPC_orderedfpcmp0 MWCodeGen_MachO_structalignmentPPC_mw MWCodeGen_MachO_profiler_enumOff MWCodeGen_MachO_processorGeneric MWCodeGen_MachO_function_align4 MWCodeGen_MachO_common0 MWCodeGen_MachO_boolisint0 MWCodeGen_MachO_peephole1 MWCodeGen_MachO_readonlystrings1 MWCodeGen_MachO_linkerpoolsstrings1 MWCodeGen_MachO_volatileasm0 MWCodeGen_MachO_schedule0 MWCodeGen_MachO_altivec0 MWCodeGen_MachO_vecmove0 MWCodeGen_MachO_fp_ieee_strict0 MWCodeGen_MachO_fpcontract1 MWCodeGen_MachO_genfsel0 MWCodeGen_MachO_fp_cmps_ordered0 MWDisassembler_PPC_showcode1 MWDisassembler_PPC_extended1 MWDisassembler_PPC_mix0 MWDisassembler_PPC_nohex0 MWDisassembler_PPC_showdata1 MWDisassembler_PPC_showexceptions1 MWDisassembler_PPC_showsym0 MWDisassembler_PPC_shownames1 GlobalOptimizer_PPC_optimizationlevelLevel0 GlobalOptimizer_PPC_optforSpeed MWLinker_PPC_linksym1 MWLinker_PPC_symfullpath1 MWLinker_PPC_linkmap0 MWLinker_PPC_nolinkwarnings0 MWLinker_PPC_dontdeadstripinitcode0 MWLinker_PPC_permitmultdefs0 MWLinker_PPC_linkmodeFast MWLinker_PPC_code_foldingNone MWLinker_PPC_initname MWLinker_PPC_mainname__start MWLinker_PPC_termname MWLinker_MacOSX_linksym1 MWLinker_MacOSX_symfullpath0 MWLinker_MacOSX_nolinkwarnings0 MWLinker_MacOSX_linkmap0 MWLinker_MacOSX_dontdeadstripinitcode0 MWLinker_MacOSX_permitmultdefs0 MWLinker_MacOSX_use_objectivec_semantics0 MWLinker_MacOSX_strip_debug_symbols0 MWLinker_MacOSX_prebind_all_twolevel_modules0 MWLinker_MacOSX_data_before_text_segment0 MWLinker_MacOSX_report_msl_overloads0 MWLinker_MacOSX_objects_follow_linkorder0 MWLinker_MacOSX_linkmodeFast MWLinker_MacOSX_exportsReferencedGlobals MWLinker_MacOSX_sortcodeNone MWLinker_MacOSX_mainname MWLinker_MacOSX_initname MWLinker_MacOSX_code_foldingNone MWLinker_MacOSX_stabsgenNone MWProject_MacOSX_typeExecutable MWProject_MacOSX_outfile MWProject_MacOSX_filecreator???? MWProject_MacOSX_filetypeMEXE MWProject_MacOSX_vmaddress4096 MWProject_MacOSX_usedefaultvmaddr1 MWProject_MacOSX_flatrsrc0 MWProject_MacOSX_flatrsrcfilename MWProject_MacOSX_flatrsrcoutputdir Path: PathFormatMacOS PathRootProject MWProject_MacOSX_installpath./ MWProject_MacOSX_dont_prebind0 MWProject_MacOSX_flat_namespace0 MWProject_MacOSX_frameworkversionA MWProject_MacOSX_currentversion0 MWProject_MacOSX_flat_oldimpversion0 MWProject_MacOSX_AddrMode1 MWPEF_exportsNone MWPEF_libfolder0 MWPEF_sortcodeNone MWPEF_expandbss0 MWPEF_sharedata0 MWPEF_olddefversion0 MWPEF_oldimpversion0 MWPEF_currentversion0 MWPEF_fragmentname MWPEF_collapsereloads0 MWProject_PPC_typeApplication MWProject_PPC_outfilea.out MWProject_PPC_filecreator???? MWProject_PPC_filetypeAPPL MWProject_PPC_size384 MWProject_PPC_minsize384 MWProject_PPC_stacksize64 MWProject_PPC_flags22720 MWProject_PPC_symfilename MWProject_PPC_rsrcname MWProject_PPC_rsrcheaderNative MWProject_PPC_rsrctype???? MWProject_PPC_rsrcid0 MWProject_PPC_rsrcflags0 MWProject_PPC_rsrcstore0 MWProject_PPC_rsrcmerge0 MWProject_PPC_flatrsrc0 MWProject_PPC_flatrsrcoutputdir Path: PathFormatMacOS PathRootProject MWProject_PPC_flatrsrcfilename MWAssembler_PPC_auxheader0 MWAssembler_PPC_symmodeMac MWAssembler_PPC_dialectPPC MWAssembler_PPC_prefixfile MWAssembler_PPC_typecheck0 MWAssembler_PPC_warnings0 MWAssembler_PPC_casesensitive0 PList_OutputTypeFile PList_OutputEncodingUTF-8 PList_PListVersion0.9 PList_Prefix PList_FileFilenameInfo.plist PList_FileDirectory Path: PathFormatMacOS PathRootProject PList_ResourceTypets PList_ResourceID0 PList_ResourceName MWRez_Language_maxwidth80 MWRez_Language_scriptRoman MWRez_Language_alignmentAlign1 MWRez_Language_filtermodeFilterSkip MWRez_Language_suppresswarnings0 MWRez_Language_escapecontrolchars1 MWRez_Language_prefixname MWRez_Language_filteredtypes'CODE' 'DATA' 'PICT' MWWinRC_prefixnameResourcePrefix.h MWCodeGen_X86_processorGeneric MWCodeGen_X86_alignmentbytes8 MWCodeGen_X86_exceptionsZeroOverhead MWCodeGen_X86_name_manglingMWWin32 MWCodeGen_X86_use_extinst0 MWCodeGen_X86_extinst_mmx0 MWCodeGen_X86_extinst_3dnow0 MWCodeGen_X86_use_mmx_3dnow_convention0 MWCodeGen_X86_extinst_cmov0 MWCodeGen_X86_extinst_sse0 MWCodeGen_X86_extinst_sse20 MWCodeGen_X86_intrinsics1 MWCodeGen_X86_optimizeasm0 MWCodeGen_X86_disableopts0 MWCodeGen_X86_profile0 MWLinker_X86_runtimeStaticMultiThread MWCodeGen_X86_readonlystrings0 MWCodeGen_X86_vectorize0 MWCodeGen_X86_relaxieee0 MWLinker_X86_subsysmajorid4 MWLinker_X86_subsysminorid0 MWCOFF_X86_opsysmajorid4 MWCOFF_X86_opsysminorid0 MWLinker_X86_usrmajorid0 MWLinker_X86_usrminorid0 MWProject_X86_maxstacksize1024 MWProject_X86_minstacksize4 MWProject_X86_size1024 MWProject_X86_minsize4 MWCOFF_X86_coff_flags0 MWCOFF_X86_dll_flags0 MWProject_X86_baseaddress4194304 MWCOFF_X86_filealign4096 MWCOFF_X86_sectionalign4096 PDisasmX86_showHeaderstrue PDisasmX86_showSectHeaderstrue PDisasmX86_showSymTabtrue PDisasmX86_showCodetrue PDisasmX86_showDatatrue PDisasmX86_showDebugfalse PDisasmX86_showExceptionsfalse PDisasmX86_showRawfalse PDisasmX86_showAllRawfalse PDisasmX86_showSourcetrue PDisasmX86_showRelocationfalse PDisasmX86_showHextrue PDisasmX86_showCommentsfalse PDisasmX86_showSymDefstrue PDisasmX86_unmanglefalse PDisasmX86_verbosefalse PDisasmX86_resolveRelocstrue PDisasmX86_resolveLocalsfalse MWDebugger_X86_Exceptions 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 GlobalOptimizer_X86_optimizationlevelLevel4 GlobalOptimizer_X86_optforSpeed MWLinker_X86_entrypointusageDefault MWLinker_X86_entrypoint MWLinker_X86_subsystemWinCUI MWLinker_X86_commandfile MWLinker_X86_generatemap0 MWLinker_X86_linksym0 MWLinker_X86_linkCV1 MWLinker_X86_symfullpathtrue MWLinker_X86_linkdebugfalse MWLinker_X86_checksumfalse MWLinker_X86_zero_init_bssfalse MWLinker_X86_mergedatafalse MWLinker_X86_usedefaultlibstrue MWLinker_X86_adddefaultlibsfalse MWLinker_X86_nowarningsfalse MWLinker_X86_verbosefalse MWLinker_X86_linkformemfalse MWLinker_X86_codefoldingNone MWLinker_X86_debuginlinefalse MWProject_X86_typeLibrary MWProject_X86_outfileCBFlib.lib MWProject_X86_importlib MWProject_X86_setimportlibdirfalse MWProject_X86_dontgenerateimportlibtrue MWProject_X86_oldformatlibfalse MWProject_X86_replaceobjextensionfalse MWProject_X86_copyallfilesfalse Name cbf_canonical.c Unix Text Debug Name cbf_byte_offset.c Unix Text Debug Name cbf_binary.c Unix Text Debug Name cbf_ascii.c Unix Text Debug Name cbf_alloc.c Unix Text Debug Name cbf_stx.c Unix Text Debug Name cbf_string.c Unix Text Debug Name cbf_simple.c Unix Text Debug Name cbf_read_mime.c Unix Text Debug Name cbf_read_binary.c Unix Text Debug Name cbf_predictor.c Unix Text Debug Name cbf_packed.c Unix Text Debug Name cbf_lex.c Unix Text Debug Name cbf_file.c Unix Text Debug Name cbf_context.c Unix Text Debug Name cbf_compress.c Unix Text Debug Name cbf_codes.c Unix Text Debug Name cbf.c Unix Text Debug Name cbf_write.c Unix Text Debug Name cbf_uncompressed.c Unix Text Debug Name cbf_tree.c Unix Text Debug Name cbf_write_binary.c Unix Text Debug Name md5c.c Unix Text Debug Name cbf_canonical.c Unix Name cbf_byte_offset.c Unix Name cbf_binary.c Unix Name cbf_ascii.c Unix Name cbf_alloc.c Unix Name cbf_stx.c Unix Name cbf_string.c Unix Name cbf_simple.c Unix Name cbf_read_mime.c Unix Name cbf_read_binary.c Unix Name cbf_predictor.c Unix Name cbf_packed.c Unix Name cbf_lex.c Unix Name cbf_file.c Unix Name cbf_context.c Unix Name cbf_compress.c Unix Name cbf_codes.c Unix Name cbf.c Unix Name cbf_write.c Unix Name cbf_uncompressed.c Unix Name cbf_tree.c Unix Name cbf_write_binary.c Unix Name md5c.c Unix CBFlib_debug.lib CBFlib.lib src CBFlib_debug.lib Name cbf_canonical.c Unix CBFlib_debug.lib Name cbf_byte_offset.c Unix CBFlib_debug.lib Name cbf_binary.c Unix CBFlib_debug.lib Name cbf_ascii.c Unix CBFlib_debug.lib Name cbf_alloc.c Unix CBFlib_debug.lib Name cbf_stx.c Unix CBFlib_debug.lib Name cbf_string.c Unix CBFlib_debug.lib Name cbf_simple.c Unix CBFlib_debug.lib Name cbf_read_mime.c Unix CBFlib_debug.lib Name cbf_read_binary.c Unix CBFlib_debug.lib Name cbf_predictor.c Unix CBFlib_debug.lib Name cbf_packed.c Unix CBFlib_debug.lib Name cbf_lex.c Unix CBFlib_debug.lib Name cbf_file.c Unix CBFlib_debug.lib Name cbf_context.c Unix CBFlib_debug.lib Name cbf_compress.c Unix CBFlib_debug.lib Name cbf_codes.c Unix CBFlib_debug.lib Name cbf.c Unix CBFlib_debug.lib Name cbf_write.c Unix CBFlib_debug.lib Name cbf_uncompressed.c Unix CBFlib_debug.lib Name cbf_tree.c Unix CBFlib_debug.lib Name cbf_write_binary.c Unix CBFlib_debug.lib Name md5c.c Unix ./CBFlib-0.9.2.2/pycbf/0000755000076500007650000000000011603703065012706 5ustar yayayaya./CBFlib-0.9.2.2/pycbf/xmas/0000755000076500007650000000000011603703070013652 5ustar yayayaya./CBFlib-0.9.2.2/pycbf/xmas/readmarheader.py0000644000076500007650000003556111603702117017023 0ustar yayayaya#!/usr/bin/env python import struct # Convert mar c header file types to python struct module types mar_c_to_python_struct = { "INT32" : "i", "UINT32" : "I", "char" : "c", "UINT16" : "H" } # Sizes (bytes) of mar c header objects mar_c_sizes = { "INT32" : 4, "UINT32" : 4, "char" : 1, "UINT16" : 2 } # This was worked out by trial and error from a trial image I think MAXIMAGES=9 def make_format(cdefinition): """ Reads the header definition in c and makes the format string to pass to struct.unpack """ lines = cdefinition.split("\n") fmt = "" names = [] expected = 0 for line in lines: if line.find(";")==-1: continue decl = line.split(";")[0].lstrip().rstrip() try: [type, name] = decl.split() except: #print "skipping:",line continue # print "type:",type," name:",name if name.find("[")>-1: # repeated ... times try: num = name.split("[")[1].split("]")[0] num = num.replace("MAXIMAGES",str(MAXIMAGES)) num = num.replace("sizeof(INT32)","4") times = eval(num) except: print "Please decode",decl raise else: times=1 try: fmt += mar_c_to_python_struct[type]*times names += [name]*times expected += mar_c_sizes[type]*times except: #print "skipping",line continue #print "%4d %4d"%(mar_c_sizes[type]*times,expected),name,":",times,line #print struct.calcsize(fmt),expected return names, fmt def read_mar_header(filename): """ Get the header from a binary file """ f = open(filename,"rb") f.seek(1024) header=f.read(3072) f.close() return header def interpret_header(header, fmt, names): """ given a format and header interpret it """ values = struct.unpack(fmt,header) dict = {} i=0 for name in names: if dict.has_key(name): if type(values[i]) == type("string"): dict[name] = dict[name]+values[i] else: try: dict[name].append(values[i]) except: dict[name] = [dict[name],values[i]] else: dict[name] = values[i] i=i+1 return dict # Now for the c definition (found on mar webpage) # The following string is therefore copyrighted by Mar I guess cdefinition = """ typedef struct frame_header_type { /* File/header format parameters (256 bytes) */ UINT32 header_type; /* flag for header type (can be used as magic number) */ char header_name[16]; /* header name (MMX) */ UINT32 header_major_version; /* header_major_version (n.) */ UINT32 header_minor_version; /* header_minor_version (.n) */ UINT32 header_byte_order;/* BIG_ENDIAN (Motorola,MIPS); LITTLE_ENDIAN (DEC, Intel) */ UINT32 data_byte_order; /* BIG_ENDIAN (Motorola,MIPS); LITTLE_ENDIAN (DEC, Intel) */ UINT32 header_size; /* in bytes */ UINT32 frame_type; /* flag for frame type */ UINT32 magic_number; /* to be used as a flag - usually to indicate new file */ UINT32 compression_type; /* type of image compression */ UINT32 compression1; /* compression parameter 1 */ UINT32 compression2; /* compression parameter 2 */ UINT32 compression3; /* compression parameter 3 */ UINT32 compression4; /* compression parameter 4 */ UINT32 compression5; /* compression parameter 4 */ UINT32 compression6; /* compression parameter 4 */ UINT32 nheaders; /* total number of headers */ UINT32 nfast; /* number of pixels in one line */ UINT32 nslow; /* number of lines in image */ UINT32 depth; /* number of bytes per pixel */ UINT32 record_length; /* number of pixels between succesive rows */ UINT32 signif_bits; /* true depth of data, in bits */ UINT32 data_type; /* (signed,unsigned,float...) */ UINT32 saturated_value; /* value marks pixel as saturated */ UINT32 sequence; /* TRUE or FALSE */ UINT32 nimages; /* total number of images - size of each is nfast*(nslow/nimages) */ UINT32 origin; /* corner of origin */ UINT32 orientation; /* direction of fast axis */ UINT32 view_direction; /* direction to view frame */ UINT32 overflow_location;/* FOLLOWING_HEADER, FOLLOWING_DATA */ UINT32 over_8_bits; /* # of pixels with counts 255 */ UINT32 over_16_bits; /* # of pixels with count 65535 */ UINT32 multiplexed; /* multiplex flag */ UINT32 nfastimages; /* # of images in fast direction */ UINT32 nslowimages; /* # of images in slow direction */ UINT32 background_applied; /* flags correction has been applied - hold magic number ? */ UINT32 bias_applied; /* flags correction has been applied - hold magic number ? */ UINT32 flatfield_applied; /* flags correction has been applied - hold magic number ? */ UINT32 distortion_applied; /* flags correction has been applied - hold magic number ? */ UINT32 original_header_type; /* Header/frame type from file that frame is read from */ UINT32 file_saved; /* Flag that file has been saved, should be zeroed if modified */ char reserve1[(64-40)*sizeof(INT32)-16]; /* Data statistics (128) */ UINT32 total_counts[2]; /* 64 bit integer range = 1.85E19*/ UINT32 special_counts1[2]; UINT32 special_counts2[2]; UINT32 min; UINT32 max; UINT32 mean; UINT32 rms; UINT32 p10; UINT32 p90; UINT32 stats_uptodate; UINT32 pixel_noise[MAXIMAGES]; /* 1000*base noise value (ADUs) */ char reserve2[(32-13-MAXIMAGES)*sizeof(INT32)]; /* More statistics (256) */ UINT16 percentile[128]; /* Goniostat parameters (128 bytes) */ INT32 xtal_to_detector; /* 1000*distance in millimeters */ INT32 beam_x; /* 1000*x beam position (pixels) */ INT32 beam_y; /* 1000*y beam position (pixels) */ INT32 integration_time; /* integration time in milliseconds */ INT32 exposure_time; /* exposure time in milliseconds */ INT32 readout_time; /* readout time in milliseconds */ INT32 nreads; /* number of readouts to get this image */ INT32 start_twotheta; /* 1000*two_theta angle */ INT32 start_omega; /* 1000*omega angle */ INT32 start_chi; /* 1000*chi angle */ INT32 start_kappa; /* 1000*kappa angle */ INT32 start_phi; /* 1000*phi angle */ INT32 start_delta; /* 1000*delta angle */ INT32 start_gamma; /* 1000*gamma angle */ INT32 start_xtal_to_detector; /* 1000*distance in mm (dist in um)*/ INT32 end_twotheta; /* 1000*two_theta angle */ INT32 end_omega; /* 1000*omega angle */ INT32 end_chi; /* 1000*chi angle */ INT32 end_kappa; /* 1000*kappa angle */ INT32 end_phi; /* 1000*phi angle */ INT32 end_delta; /* 1000*delta angle */ INT32 end_gamma; /* 1000*gamma angle */ INT32 end_xtal_to_detector; /* 1000*distance in mm (dist in um)*/ INT32 rotation_axis; /* active rotation axis */ INT32 rotation_range; /* 1000*rotation angle */ INT32 detector_rotx; /* 1000*rotation of detector around X */ INT32 detector_roty; /* 1000*rotation of detector around Y */ INT32 detector_rotz; /* 1000*rotation of detector around Z */ char reserve3[(32-28)*sizeof(INT32)]; /* Detector parameters (128 bytes) */ INT32 detector_type; /* detector type */ INT32 pixelsize_x; /* pixel size (nanometers) */ INT32 pixelsize_y; /* pixel size (nanometers) */ INT32 mean_bias; /* 1000*mean bias value */ INT32 photons_per_100adu; /* photons / 100 ADUs */ INT32 measured_bias[MAXIMAGES]; /* 1000*mean bias value for each image*/ INT32 measured_temperature[MAXIMAGES]; /* Temperature of each detector in milliKelvins */ INT32 measured_pressure[MAXIMAGES]; /* Pressure of each chamber in microTorr */ /* Retired reserve4 when MAXIMAGES set to 9 from 16 and two fields removed, and temp and pressure added char reserve4[(32-(5+3*MAXIMAGES))*sizeof(INT32)] */ /* X-ray source and optics parameters (128 bytes) */ /* X-ray source parameters (8*4 bytes) */ INT32 source_type; /* (code) - target, synch. etc */ INT32 source_dx; /* Optics param. - (size microns) */ INT32 source_dy; /* Optics param. - (size microns) */ INT32 source_wavelength; /* wavelength (femtoMeters) */ INT32 source_power; /* (Watts) */ INT32 source_voltage; /* (Volts) */ INT32 source_current; /* (microAmps) */ INT32 source_bias; /* (Volts) */ INT32 source_polarization_x; /* () */ INT32 source_polarization_y; /* () */ char reserve_source[4*sizeof(INT32)]; /* X-ray optics_parameters (8*4 bytes) */ INT32 optics_type; /* Optics type (code)*/ INT32 optics_dx; /* Optics param. - (size microns) */ INT32 optics_dy; /* Optics param. - (size microns) */ INT32 optics_wavelength; /* Optics param. - (size microns) */ INT32 optics_dispersion; /* Optics param. - (*10E6) */ INT32 optics_crossfire_x; /* Optics param. - (microRadians) */ INT32 optics_crossfire_y; /* Optics param. - (microRadians) */ INT32 optics_angle; /* Optics param. - (monoch. 2theta - microradians) */ INT32 optics_polarization_x; /* () */ INT32 optics_polarization_y; /* () */ char reserve_optics[4*sizeof(INT32)]; char reserve5[((32-28)*sizeof(INT32))]; /* File parameters (1024 bytes) */ char filetitle[128]; /* Title */ char filepath[128]; /* path name for data file */ char filename[64]; /* name of data file */ char acquire_timestamp[32]; /* date and time of acquisition */ char header_timestamp[32]; /* date and time of header update */ char save_timestamp[32]; /* date and time file saved */ char file_comments[512]; /* comments, use as desired */ char reserve6[1024-(128+128+64+(3*32)+512)]; /* Dataset parameters (512 bytes) */ char dataset_comments[512]; /* comments, used as desired */ /* pad out to 3072 bytes */ char pad[3072-(256+128+256+(3*128)+1024+512)]; } frame_header; """ class marheaderreader: """ Class to sit and read a series of images (makes format etc only once) """ def __init__(self): """ Initialise internal stuff """ self.names , self.fmt = make_format(cdefinition) def get_header(self,filename): """ Reads a header from file filename """ h=read_mar_header(filename) dict = interpret_header(h,self.fmt,self.names) # Append ESRF formatted stuff items = self.readesrfstring(dict["dataset_comments[512]"]) for pair in items: dict[pair[0]]=pair[1] items = self.readesrfstring(dict["file_comments[512]"]) for pair in items: dict[pair[0]]=pair[1] dict["pixelsize_x_mm"]= str(float(dict["pixelsize_x"])/1e6) dict["pixelsize_y_mm"]= str(float(dict["pixelsize_y"])/1e6) dict["integration_time_sec"]= str(float(dict["integration_time"])/1e3) dict["beam_y_mm"]= str(float(dict["pixelsize_y_mm"])* float(dict["beam_y"])/1000.) dict["beam_x_mm"]= str(float(dict["pixelsize_x_mm"])* float(dict["beam_x"])/1000.) return dict def readesrfstring(self,s): """ Interpret the so called "esrf format" header lines which are in comment sections """ s=s.replace("\000","") items = filter(None, [len(x)>1 and x or None for x in [ item.split("=") for item in s.split(";")]]) return items if __name__=="__main__": """ Make a little program to process files """ import sys print "Starting" names,fmt = make_format(cdefinition) print "Names and format made" h = read_mar_header(sys.argv[1]) print "Read header, interpreting" d = interpret_header(h,fmt,names) printed = {} for name in names: if printed.has_key(name): continue print name,":",d[name] printed[name]=1 ./CBFlib-0.9.2.2/pycbf/xmas/xmasheaders.py0000644000076500007650000001732411603702117016540 0ustar yayayaya#!/usr/bin/env python import pycbf # Some cbf helper functions - obj would be a cbf_handle_struct object def writewavelength(obj,wavelength): obj.set_wavelength(float(wavelength)) def writecellpar(obj,cifname,value): obj.find_category("cell") obj.find_column(cifname) obj.set_value(value) def writecell(obj,cell): """ call with cell = (a,b,c,alpha,beta,gamma) """ obj.find_category("cell") obj.find_column("length_a") obj.set_value(str(cell[0])) obj.find_column("length_b") obj.set_value(str(cell[1])) obj.find_column("length_c") obj.set_value(str(cell[2])) obj.find_column("angle_alpha") obj.set_value(str(cell[3])) obj.find_column("angle_beta") obj.set_value(str(cell[4])) obj.find_column("angle_gamma") obj.set_value(str(cell[5])) def writeUB(obj,ub): """ call with ub that can be indexed ub[i][j] """ obj.find_category("diffrn_orient_matrix") for i in (1,2,3): for j in (1,2,3): obj.find_column("UB[%d][%d]"%(i,j)) obj.set_value(str(ub[i-1][j-1])) def writedistance(obj,distance): obj.set_axis_setting("DETECTOR_Z",float(distance),0.) def writebeam_x_mm(obj,cen): obj.set_axis_setting("DETECTOR_X",float(cen),0.) def writebeam_y_mm(obj,cen): obj.set_axis_setting("DETECTOR_Y",float(cen),0.) def writeSPECcmd(obj,s): obj.find_category("diffrn_measurement") obj.find_column("details") obj.set_value(s) def writeSPECscan(obj,s): obj.find_category("diffrn_scan") obj.find_column("id") obj.set_value("SCAN%s"%(s)) obj.find_category("diffrn_scan_axis") obj.find_column("scan_id") obj.rewind_row() for i in range(obj.count_rows()): obj.select_row(i) obj.set_value("SCAN%s"%(s)) obj.find_category("diffrn_scan_frame") obj.find_column("scan_id") obj.rewind_row() obj.set_value("SCAN%s"%(s)) def writepixelsize_y_mm(obj,s): """ Units are mm for cif """ # element number = assume this is first and only detector element_number = 0 # axis number = faster or slower... ? Need to check precedence ideally... obj.find_category("array_structure_list") obj.find_column("axis_set_id") obj.find_row("ELEMENT_Y") obj.find_column("precedence") axis_number = obj.get_integervalue() obj.set_pixel_size(element_number, axis_number, float(s) ) obj.find_category("array_structure_list_axis") obj.find_column("axis_id") obj.find_row("ELEMENT_Y") obj.find_column("displacement") obj.set_doublevalue("%.6g",float(s)/2.0) obj.find_column("displacement_increment") obj.set_doublevalue("%.6g",float(s)) def writepixelsize_x_mm(obj,s): # element number = assume this is first and only detector element_number = 0 # axis number = faster or slower... ? Need to check precedence ideally... obj.find_category("array_structure_list") obj.find_column("axis_set_id") obj.find_row("ELEMENT_X") obj.find_column("precedence") axis_number = obj.get_integervalue() obj.set_pixel_size(element_number, axis_number, float(s) ) obj.find_category("array_structure_list_axis") obj.find_column("axis_id") obj.find_row("ELEMENT_X") obj.find_column("displacement") obj.set_doublevalue("%.6g",float(s)/2.0) obj.find_column("displacement_increment") obj.set_doublevalue("%.6g",float(s)) def writeintegrationtime(obj,s): obj.find_category("diffrn_scan_frame") obj.find_column("integration_time") obj.set_value(str(s).replace("\000","")) def writenfast(obj,s): obj.find_category("array_structure_list") obj.find_column("index") obj.find_row("1") obj.find_column("dimension") obj.set_value(str(s)) def writenslow(obj,s): obj.find_category("array_structure_list") obj.find_column("index") obj.find_row("2") obj.find_column("dimension") obj.set_value(str(s)) functiondict = { "lambda" : writewavelength, "beam_x_mm" : writebeam_x_mm, "beam_y_mm" : writebeam_y_mm, "distance" : writedistance, "UB" : writeUB, "cell" : writecell, "cmd" : writeSPECcmd, "scan" : writeSPECscan, "nfast" : writenfast, "nslow" : writenslow, "pixelsize_y_mm" : writepixelsize_y_mm, "pixelsize_x_mm" : writepixelsize_x_mm, "integration_time_sec" : writeintegrationtime, "tth" : lambda obj,value : obj.set_axis_setting( "DETECTOR_TWO_THETA_VERTICAL",float(value),0.), "chi" : lambda obj,value : obj.set_axis_setting( "GONIOMETER_CHI",float(value),0.), "th" : lambda obj,value : obj.set_axis_setting( "GONIOMETER_THETA",float(value),0.), "phi" : lambda obj,value : obj.set_axis_setting( "GONIOMETER_PHI",float(value),0.), "lc_a" : lambda obj,value : writecellpar(obj,"length_a",value), "lc_b" : lambda obj,value : writecellpar(obj,"length_b",value), "lc_c" : lambda obj,value : writecellpar(obj,"length_c",value), "lc_al" : lambda obj,value : writecellpar(obj,"angle_alpha",value), "lc_be" : lambda obj,value : writecellpar(obj,"angle_beta",value), "lc_ga" : lambda obj,value : writecellpar(obj,"angle_gamma",value) } """ # # Not implementing these for now lc_ra lc_rc 0.4742 lc_rb 1.16 energy 13 cp_phi -180 alpha 7.3716 lc_ral 90 cp_tth -180 lc_rga 90 beta 17.572 omega -2.185 h 0.21539 k 0.01957 l 5.9763 cp_chi -180 lc_rbe 90 cp_th -180 azimuth 0 """ # Finally a class for creating header files. # It reads a template and then offers a processfile command # for running over a file series class cifheader: def __init__(self,templatefile): self.cbf=pycbf.cbf_handle_struct() self.cbf.read_template(templatefile) from readmarheader import marheaderreader self.marheaderreader = marheaderreader() def processfile(self,filename, outfile=None, format="mccd", **kwds): outfile=outfile.replace(format,"cif") if format == "mccd": items = self.marheaderreader.get_header(filename) if format == "bruker": pass if format == "edf": pass self.items=items # Take the image header items as default self.updateitems(items) # Allow them to be overridden self.updateitems(kwds) # Write the file self.writefile(outfile) def writefile(self,filename): self.cbf.write_file(filename,pycbf.CIF,pycbf.MIME_HEADERS, pycbf.ENC_BASE64) def updateitems(self,dict): names = dict.keys() for name in names: value = dict[name] # use a dictionary of functions if functiondict.has_key(name): # print "calling",functiondict[name],value apply(functiondict[name],(self.cbf,value)) else: #print "ignoring",name,value pass if __name__=="__main__": import sys obj=cifheader("xmas_cif_template.cif") ub = [[0.11, 0.12, 0.13] , [0.21, 0.22, 0.23], [0.31, 0.32, 0.33]] for filename in sys.argv[1:]: fileout = filename.split("/")[-1] obj.processfile(filename, outfile=fileout, UB=ub, distance=123.456) ./CBFlib-0.9.2.2/pycbf/xmas/xmas_cif_template.cif0000644000076500007650000001356711603702117020036 0ustar yayayaya ###CBF: VERSION 0.6 # CBF file written by cbflib v0.6 data_image_1 loop_ _diffrn.id _diffrn.crystal_id DS1 DIFFRN_CRYSTAL_ID loop_ _cell.length_a 5.959(1) _cell.length_b 14.956(1) _cell.length_c 19.737(3) _cell.angle_alpha 90 _cell.angle_beta 90 _cell.angle_gamma 90 loop_ _diffrn_orient_matrix.id 'DS1' _diffrn_orient_matrix.type ; reciprocal axis matrix, multiplies hkl vector to generate diffractometer xyz vector and diffractometer angles ; _diffrn_orient_matrix.UB[1][1] 0.11 _diffrn_orient_matrix.UB[1][2] 0.12 _diffrn_orient_matrix.UB[1][3] 0.13 _diffrn_orient_matrix.UB[2][1] 0.21 _diffrn_orient_matrix.UB[2][2] 0.22 _diffrn_orient_matrix.UB[2][3] 0.23 _diffrn_orient_matrix.UB[3][1] 0.31 _diffrn_orient_matrix.UB[3][2] 0.32 _diffrn_orient_matrix.UB[3][3] 0.33 loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.current _diffrn_source.type DS1 synchrotron 200.0 'XMAS beamline bm28 ESRF' loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.probe _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source _diffrn_radiation.collimation DS1 WAVELENGTH1 x-ray 'Si 111' 0.8 0.0 0.08 0.01 0.00 '0.20 mm x 0.20 mm' loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 1.73862 1.0 loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.details _diffrn_detector.number_of_axes DS1 MAR 'MAR XMAS' 'slow mode' 5 loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR DETECTOR_TWO_THETA_VERTICAL MAR DETECTOR_X MAR DETECTOR_Y MAR DETECTOR_Z MAR DETECTOR_PITCH loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method _diffrn_measurement.details DS1 GONIOMETER 3 rotation 'i0=1.000 i1=1.000 i2=1.000 ib=1.000 beamstop=20 mm 0% attenuation' loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_CHI GONIOMETER GONIOMETER_THETA loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_THETA 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_CHI 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI 185 1 1 0.0 0.0 0.0 SCAN1 DETECTOR_TWO_THETA_VERTICAL 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 103.750 0 0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 360 SCAN1 1997-12-04T10:23:48 loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_THETA 0.0 0.0 FRAME1 GONIOMETER_CHI 0.0 0.0 FRAME1 GONIOMETER_PHI 185 0.0 FRAME1 DETECTOR_TWO_THETA_VERTICAL 185 0.0 FRAME1 DETECTOR_Z 0.0 103.750 FRAME1 DETECTOR_Y 0.0 0.0 FRAME1 DETECTOR_X 0.0 0.0 FRAME1 DETECTOR_PITCH 0.0 0.0 loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_THETA rotation goniometer . 1 0 0 . . . GONIOMETER_CHI rotation goniometer GONIOMETER_THETA 0 0 1 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_PHI 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_TWO_THETA_VERTICAL rotation goniometer . 1 0 0 . . . DETECTOR_Z translation detector DETECTOR_TWO_THETA_VERTICAL 0 0 -1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 -94.0032 94.0032 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 2049 1 increasing ELEMENT_X ARRAY1 2 2049 2 increasing ELEMENT_Y loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.0408 0.0816 ELEMENT_Y ELEMENT_Y -0.0408 -0.0816 loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 0.30 0.03 65000 0 loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian ./CBFlib-0.9.2.2/pycbf/pycbf_test1.py0000644000076500007650000000421311603702120015472 0ustar yayayaya import pycbf object = pycbf.cbf_handle_struct() # FIXME object.read_file("../img2cif_packed.cif",pycbf.MSG_DIGEST) object.rewind_datablock() print "Found",object.count_datablocks(),"blocks" object.select_datablock(0) print "Zeroth is named",object.datablock_name() object.rewind_category() categories = object.count_categories() for i in range(categories): print "Category:",i, object.select_category(i) category_name = object.category_name() print "Name:",category_name, rows=object.count_rows() print "Rows:",rows, cols = object.count_columns() print "Cols:",cols loop=1 object.rewind_column() while loop is not 0: column_name = object.column_name() print "column name \"",column_name,"\"", try: object.next_column() except: break print for j in range(rows): object.select_row(j) object.rewind_column() print "row:",j for k in range(cols): name=object.column_name() print "col:",name, object.select_column(k) typeofvalue=object.get_typeofvalue() print "type:",typeofvalue if typeofvalue.find("bnry") > -1: print "Found the binary!!", s=object.get_integerarray_as_string() print type(s) print dir(s) print len(s) try: import Numeric d = Numeric.fromstring(s,Numeric.UInt32) # Hard wired Unsigned Int32 print d.shape print d[0:10],d[d.shape[0]/2],d[-1] d=Numeric.reshape(d,(2300,2300)) # from matplotlib import pylab # pylab.imshow(d,vmin=0,vmax=1000) # pylab.show() except ImportError: print "You need to get Numeric and matplotlib to see the data" else: value=object.get_value() print "Val:",value,i print del(object) # print dir() #object.free_handle(handle) ./CBFlib-0.9.2.2/pycbf/pycbf_test2.py0000644000076500007650000000070611603702120015476 0ustar yayayaya import pycbf obj = pycbf.cbf_handle_struct() obj.read_file("../adscconverted.cbf",0) obj.select_datablock(0) g = obj.construct_goniometer() print "Rotation axis is",g.get_rotation_axis() d = obj.construct_detector(0) print "Beam center is",d.get_beam_center() print "Detector slow axis is", d.get_detector_axis_slow() print "Detector fast axis is", d.get_detector_axis_fast() print "Detector axes (fast, slow) are", d.get_detector_axes_fs() ./CBFlib-0.9.2.2/pycbf/pycbf_test3.py0000644000076500007650000000133711603702120015500 0ustar yayayaya import pycbf, unittest class GenericTests(unittest.TestCase): def test_get_local_integer_byte_order(self): self.assertEqual( pycbf.get_local_integer_byte_order(), 'little_endian') def test_get_local_real_byte_order(self): self.assertEqual( pycbf.get_local_real_byte_order() , 'little_endian') def test_get_local_real_format(self): self.assertEqual( pycbf.get_local_real_format(), 'ieee 754-1985') def test_compute_cell_volume(self): self.assertEqual( pycbf.compute_cell_volume((2.,3.,4.,90.,90.,90.)), 24.0) if __name__=="__main__": unittest.main() ./CBFlib-0.9.2.2/pycbf/pycbf.i0000644000076500007650000003070511603702120014157 0ustar yayayaya /* File: pycbf.i */ // Indicate that we want to generate a module call pycbf %module pycbf %pythoncode %{ __author__ = "Jon Wright " __date__ = "14 Dec 2005" __version__ = "CBFlib 0.9" __credits__ = """Paul Ellis and Herbert Bernstein for the excellent CBFlib!""" __doc__=""" pycbf - python bindings to the CBFlib library A library for reading and writing ImageCIF and CBF files which store area detector images for crystallography. This work is a derivative of the CBFlib version 0.7.7 library by Paul J. Ellis of Stanford Synchrotron Radiation Laboratory and Herbert J. Bernstein of Bernstein + Sons See: http://www.bernstein-plus-sons.com/software/CBF/ Licensing is GPL based, see: http://www.bernstein-plus-sons.com/software/CBF/doc/CBFlib_NOTICES.html These bindings were automatically generated by SWIG, and the input to SWIG was automatically generated by a python script. We very strongly recommend you do not attempt to edit them by hand! Copyright (C) 2007 Jonathan Wright ESRF, Grenoble, France email: wright@esrf.fr Revised, August 2010 Herbert J. Bernstein Add defines from CBFlib 0.9.1 """ %} // Used later to pass back binary data %include "cstring.i" // Attempt to autogenerate what SWIG thinks the call looks like // Typemaps are a SWIG mechanism for many things, not least multiple // return values %include "typemaps.i" // Arrays are needed %include "carrays.i" %array_class(double, doubleArray) %array_class(int, intArray) %array_class(short, shortArray) %array_class(long, longArray) // Following the SWIG 1.3 documentation at // http://www.swig.org/Doc1.3/Python.html // section 31.9.5, we map sequences of // PyFloat, PyLong and PyInt to // C arrays of double, long and int // // But with the strict checking of being a float // commented out to allow automatic conversions %{ static int convert_darray(PyObject *input, double *ptr, int size) { int i; if (!PySequence_Check(input)) { PyErr_SetString(PyExc_TypeError,"Expecting a sequence"); return 0; } if (PyObject_Length(input) != size) { PyErr_SetString(PyExc_ValueError,"Sequence size mismatch"); return 0; } for (i =0; i < size; i++) { PyObject *o = PySequence_GetItem(input,i); /*if (!PyFloat_Check(o)) { Py_XDECREF(o); PyErr_SetString(PyExc_ValueError,"Expecting a sequence of floats"); return 0; }*/ ptr[i] = PyFloat_AsDouble(o); Py_DECREF(o); } return 1; } %} %typemap(in) double [ANY](double temp[$1_dim0]) { if ($input == Py_None) $1 = NULL; else if (!convert_darray($input,temp,$1_dim0)) { return NULL; } $1 = &temp[0]; } %{ static long convert_larray(PyObject *input, long *ptr, int size) { int i; if (!PySequence_Check(input)) { PyErr_SetString(PyExc_TypeError,"Expecting a sequence"); return 0; } if (PyObject_Length(input) != size) { PyErr_SetString(PyExc_ValueError,"Sequence size mismatch"); return 0; } for (i =0; i < size; i++) { PyObject *o = PySequence_GetItem(input,i); /*if (!PyLong_Check(o)) { Py_XDECREF(o); PyErr_SetString(PyExc_ValueError,"Expecting a sequence of long integers"); return 0; }*/ ptr[i] = PyLong_AsLong(o); Py_DECREF(o); } return 1; } %} %typemap(in) long [ANY](long temp[$1_dim0]) { if (!convert_larray($input,temp,$1_dim0)) { return NULL; } $1 = &temp[0]; } %{ static int convert_iarray(PyObject *input, int *ptr, int size) { int i; if (!PySequence_Check(input)) { PyErr_SetString(PyExc_TypeError,"Expecting a sequence"); return 0; } if (PyObject_Length(input) != size) { PyErr_SetString(PyExc_ValueError,"Sequence size mismatch"); return 0; } for (i =0; i < size; i++) { PyObject *o = PySequence_GetItem(input,i); /*if (!PyInt_Check(o)) { Py_XDECREF(o); PyErr_SetString(PyExc_ValueError,"Expecting a sequence of long integers"); return 0; }*/ ptr[i] = (int)PyInt_AsLong(o); Py_DECREF(o); } return 1; } %} %typemap(in) int [ANY](int temp[$1_dim0]) { if (!convert_iarray($input,temp,$1_dim0)) { return NULL; } $1 = &temp[0]; } %{ // Here is the c code needed to compile the wrappers, but not // to be wrapped #include "../include/cbf.h" #include "../include/cbf_simple.h" // Helper functions to generate error message static int error_status = 0; static char error_message[1024] ; // hope that is long enough /* prototype */ void get_error_message(void); void get_error_message(){ sprintf(error_message,"%s","CBFlib Error(s):"); if (error_status & CBF_FORMAT ) sprintf(error_message,"%s %s",error_message,"CBF_FORMAT "); if (error_status & CBF_ALLOC ) sprintf(error_message,"%s %s",error_message,"CBF_ALLOC "); if (error_status & CBF_ARGUMENT ) sprintf(error_message,"%s %s",error_message,"CBF_ARGUMENT "); if (error_status & CBF_ASCII ) sprintf(error_message,"%s %s",error_message,"CBF_ASCII "); if (error_status & CBF_BINARY ) sprintf(error_message,"%s %s",error_message,"CBF_BINARY "); if (error_status & CBF_BITCOUNT ) sprintf(error_message,"%s %s",error_message,"CBF_BITCOUNT "); if (error_status & CBF_ENDOFDATA ) sprintf(error_message,"%s %s",error_message,"CBF_ENDOFDATA "); if (error_status & CBF_FILECLOSE ) sprintf(error_message,"%s %s",error_message,"CBF_FILECLOSE "); if (error_status & CBF_FILEOPEN ) sprintf(error_message,"%s %s",error_message,"CBF_FILEOPEN "); if (error_status & CBF_FILEREAD ) sprintf(error_message,"%s %s",error_message,"CBF_FILEREAD "); if (error_status & CBF_FILESEEK ) sprintf(error_message,"%s %s",error_message,"CBF_FILESEEK "); if (error_status & CBF_FILETELL ) sprintf(error_message,"%s %s",error_message,"CBF_FILETELL "); if (error_status & CBF_FILEWRITE ) sprintf(error_message,"%s %s",error_message,"CBF_FILEWRITE "); if (error_status & CBF_IDENTICAL ) sprintf(error_message,"%s %s",error_message,"CBF_IDENTICAL "); if (error_status & CBF_NOTFOUND ) sprintf(error_message,"%s %s",error_message,"CBF_NOTFOUND "); if (error_status & CBF_OVERFLOW ) sprintf(error_message,"%s %s",error_message,"CBF_OVERFLOW "); if (error_status & CBF_UNDEFINED ) sprintf(error_message,"%s %s",error_message,"CBF_UNDEFINED "); if (error_status & CBF_NOTIMPLEMENTED) sprintf(error_message,"%s %s",error_message,"CBF_NOTIMPLEMENTED"); if (error_status & CBF_NOCOMPRESSION) sprintf(error_message,"%s %s",error_message,"CBF_NOCOMPRESSION"); } %} // End of code which is not wrapped but needed to compile // The actual wrappers // Constants needed from header files /* Constants used for compression */ #define CBF_INTEGER 0x0010 /* Uncompressed integer */ #define CBF_FLOAT 0x0020 /* Uncompressed IEEE floating-point */ #define CBF_CANONICAL 0x0050 /* Canonical compression */ #define CBF_PACKED 0x0060 /* Packed compression */ #define CBF_PACKED_V2 0x0090 /* CCP4 Packed (JPA) compression V2 */ #define CBF_BYTE_OFFSET 0x0070 /* Byte Offset Compression */ #define CBF_PREDICTOR 0x0080 /* Predictor_Huffman Compression */ #define CBF_NONE 0x0040 /* No compression flag */ #define CBF_COMPRESSION_MASK \ 0x00FF /* Mask to separate compression type from flags */ #define CBF_FLAG_MASK 0x0F00 /* Mask to separate flags from compression type */ #define CBF_UNCORRELATED_SECTIONS \ 0x0100 /* Flag for uncorrelated sections */ #define CBF_FLAT_IMAGE 0x0200 /* Flag for flat (linear) images */ #define CBF_NO_EXPAND 0x0400 /* Flag to try not to expand */ /* Constants used for headers */ #define PLAIN_HEADERS 0x0001 /* Use plain ASCII headers */ #define MIME_HEADERS 0x0002 /* Use MIME headers */ #define MSG_NODIGEST 0x0004 /* Do not check message digests */ #define MSG_DIGEST 0x0008 /* Check message digests */ #define MSG_DIGESTNOW 0x0010 /* Check message digests immediately */ #define MSG_DIGESTWARN 0x0020 /* Warn on message digests immediately*/ #define PAD_1K 0x0020 /* Pad binaries with 1023 0's */ #define PAD_2K 0x0040 /* Pad binaries with 2047 0's */ #define PAD_4K 0x0080 /* Pad binaries with 4095 0's */ /* Constants used to control CIF parsing */ #define CBF_PARSE_BRC 0x0100 /* PARSE DDLm/CIF2 brace {,...} */ #define CBF_PARSE_PRN 0x0200 /* PARSE DDLm parens (,...) */ #define CBF_PARSE_BKT 0x0400 /* PARSE DDLm brackets [,...] */ #define CBF_PARSE_BRACKETS \ 0x0700 /* PARSE ALL brackets */ #define CBF_PARSE_TQ 0x0800 /* PARSE treble quotes """...""" and '''...''' */ #define CBF_PARSE_CIF2_DELIMS \ 0x1000 /* Do not scan past an unescaped close quote do not accept {} , : " ' in non-delimited strings'{ */ #define CBF_PARSE_DDLm 0x0700 /* For DDLm parse (), [], {} */ #define CBF_PARSE_CIF2 0x1F00 /* For CIF2 parse {}, treble quotes, stop on unescaped close quotes */ #define CBF_PARSE_DEFINES \ 0x2000 /* Recognize DEFINE_name */ #define CBF_PARSE_WIDE 0x4000 /* PARSE wide files */ #define CBF_PARSE_UTF8 0x10000 /* PARSE UTF-8 */ #define HDR_DEFAULT (MIME_HEADERS | MSG_NODIGEST) #define MIME_NOHEADERS PLAIN_HEADERS /* CBF vs CIF */ #define CBF 0x0000 /* Use simple binary sections */ #define CIF 0x0001 /* Use MIME-encoded binary sections */ /* Constants used for encoding */ #define ENC_NONE 0x0001 /* Use BINARY encoding */ #define ENC_BASE64 0x0002 /* Use BASE64 encoding */ #define ENC_BASE32K 0x0004 /* Use X-BASE32K encoding */ #define ENC_QP 0x0008 /* Use QUOTED-PRINTABLE encoding */ #define ENC_BASE10 0x0010 /* Use BASE10 encoding */ #define ENC_BASE16 0x0020 /* Use BASE16 encoding */ #define ENC_BASE8 0x0040 /* Use BASE8 encoding */ #define ENC_FORWARD 0x0080 /* Map bytes to words forward (1234) */ #define ENC_BACKWARD 0x0100 /* Map bytes to words backward (4321) */ #define ENC_CRTERM 0x0200 /* Terminate lines with CR */ #define ENC_LFTERM 0x0400 /* Terminate lines with LF */ #define ENC_DEFAULT (ENC_BASE64 | ENC_LFTERM | ENC_FORWARD) // Exception handling /* Convenience definitions for functions returning error codes */ %exception { error_status=0; $action if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } /* Retain notation from cbf lib but pass on as python exception */ #define cbf_failnez(x) {(error_status = x);} /* printf("Called \"x\", status %d\n",error_status);} */ #define cbf_onfailnez(x,c) {int err; err = (x); if (err) { fprintf (stderr, \ "\nCBFlib error %d in \"x\"\n", err); \ { c; } return err; }} %include "cbfgenericwrappers.i" // cbf_goniometer object %include "cbfgoniometerwrappers.i" %include "cbfdetectorwrappers.i" // cbfhandle object %include "cbfhandlewrappers.i" ./CBFlib-0.9.2.2/pycbf/pycbf.w0000644000076500007650000014041411603702120014174 0ustar yayayaya% pycbf.w % nuweb source file used to create pycbf documentation % % pycbf - python binding to the CBFlib library % % Copyright (C) 2005 Jonathan Wright % ESRF, Grenoble, France % email: wright@@esrf.fr % % Revised for CBFlib 0.9 releases, Herbert J. Bernstein, 23 Aug 2010 % %###################################################################### %# # %# YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE INCLUDING PYCBF UNDER THE # %# TERMS OF THE GPL # %# # %# ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API INCLUDING PYCBF # %# UNDER THE TERMS OF THE LGPL # %# # %###################################################################### % %########################### GPL NOTICES ############################## %# # %# This program is free software; you can redistribute it and/or # %# modify it under the terms of the GNU General Public License as # %# published by the Free Software Foundation; either version 2 of # %# (the License, or (at your option) any later version. # %# # %# This program is distributed in the hope that it will be useful, # %# but WITHOUT ANY WARRANTY; without even the implied warranty of # %# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # %# GNU General Public License for more details. # %# # %# You should have received a copy of the GNU General Public License # %# along with this program; if not, write to the Free Software # %# Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA # %# 02111-1307 USA # %# # %###################################################################### % %######################### LGPL NOTICES ############################### %# # %# This library is free software; you can redistribute it and/or # %# modify it under the terms of the GNU Lesser General Public # %# License as published by the Free Software Foundation; either # %# version 2.1 of the License, or (at your option) any later version. # %# # %# This library is distributed in the hope that it will be useful, # %# but WITHOUT ANY WARRANTY; without even the implied warranty of # %# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # %# Lesser General Public License for more details. # %# # %# You should have received a copy of the GNU Lesser General Public # %# License along with this library; if not, write to the Free # %# Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, # %# MA 02110-1301 USA # %# # %###################################################################### % % Nuweb formatted latex file % Most of this is standard latex with code rolled in % Anything to do with @@ characters is probably specific to nuweb % % % The word FIXME anywhere in this document indicates % an area where more attention is still needed. % % Note that this file (pycbf.w) does not copy and paste from CBFlib % (or anywhere) except in the hand wrapped function prototypes. % % % \documentclass[10pt,a4paper,twoside,notitlepage]{article} \usepackage{graphics} % For the pictures \usepackage{anysize} % Try to circumvent Latex default margins \usepackage{fancyhdr} \usepackage[dvipdfm,bookmarks=true,backref,bookmarksnumbered=true, bookmarkstype=toc]{hyperref} \newcommand{\var}[1]{\textbf{\textsf{#1}}} % highlight variables in text \newcommand{\code}[1]{\textbf{\textsf{#1}}} % highlight code in text \newcommand{\param}[1]{\textbf{\textsf{#1}}} % ... parameters ... \newcommand{\mb} [1] {\mathbf{#1}} \begin{document} \marginsize{1.5cm}{1.5cm}{1.5cm}{1.5cm} % Needs anysize %\pagestyle{headings} % These are ugly - fix them somehow? \pagestyle{fancy} %$\renewcommand{\chaptermark}[1]{ %$ \markboth{\chaptername %$ \ \thechapter.\ #1} {} } \renewcommand{\sectionmark}[1]{ \markright { \ \thesection.\ #1} {} } \fancyhead[LE,RO]{\rightmark} \fancyhead[LO,RE]{\leftmark} \fancyfoot[C]{\today} \fancyfoot[LE,RO]{\thepage} \fancyfoot[LO,RE]{J. P. Wright} \renewcommand{\footrulewidth}{0.4pt} \pagenumbering{arabic} % Page numbers \title{\textbf{\textsf{PyCBF}} \\ A python binding to the CBFlib library} \author{Jon P. Wright \\ Anyone who wishes to contribute, please do!} \date{Started Dec 12, 2005, already it is \today} \maketitle \abstract{ Area detectors at synchrotron facilities can result in huge amounts of data being generated very rapidly. The IUCr (International Union of Crystallography) has devised a standard file format for storing and annotating such data, in order that it might be more easily interchanged and exploited. A c library which gives access to this file format has been developed by Paul Ellis and Herbert Bernstein (Version 0.7.4, http://www.bernstein-plus-sons.com/software/CBF/). In this document a python interface is developed using the SWIG (http://www.swig.org) package in order to give the author easy access to binary cif files. } \tableofcontents \markboth{}{} \section*{Index of file names} @f \section*{Index of macro names} @m \section*{Things to do} \begin{itemize} \item Write test code to test each and every function for good and bad args etc \end{itemize} \section{Introduction} The CBFlib library (version 0.7.4) is written in the C language, offering C (and C++) programmers a convenient interface to such files. The current author uses a different language (python) from day to day and so a python interface was desired. After a short attempt to make a quick and dirty SWIG interface it was decided that in the long run it would be better to write a proper interface for python. All of the functions in the library return an integer reflecting error status. Usually these integers seem to be zero, and a non-zero return value appears to mean an error occurred. Actual return values are returned via pointers in argument lists. In order to simplify the authors life (as a user) all of those integers have been made to disappear if they are zero, and cause an ``exception'' to be generated if they are not zero. This solution might not be the best thing to do, and it can always be changed where the return value is intended to normally be used. Actual return values which were passed back via pointer arguments are now just passed back as (perhaps multiple) return values. We must look out for INOUT arguments, none seem to have been found yet, but there might be exceptions. The author has a vague suspicion that python functions generally do not modify their arguments, but this might be wrong. The library appears to define (at least) three objects. The one we started on was the cbf\_handle\_struct defined in cbf.h. Many of the functions have their first argument as a pointer to one of these structures. Therefore we make this structure an object and then everything which uses it as first argument is a member function for that object. In order to pass image data back and forth there is a difficulty that python seems to lack a good way to represent large arrays. The standard library offers an "array" object which claims to efficiently hold homogenous numerical data. Sadly this seems to be limited to one-dimensional arrays. The builtin string object can hold binary data and this was chosen as the way to pass the actual binary back and forth between python and CBFlib. Unfortunately this means the binary data are pretty useless when they arrive on the python side, so helper functions are provided to convert the data to a python (standard library) 1D array and also to a "Numeric" array or a "Numarray" array. The latter two are popular extension modules for manipulating large arrays. \section{Installation prerequisites} The document you are reading was generated from a nuweb source file. This is something very similar to latex with a few extensions for writing out source code files. As such it keeps together the whole package in a single file and makes it easier to write documentation. You will need a to obtain the preprocessing tool nuweb (perhaps from http://nuweb.sourceforge.net) in order to build from scratch with the file pycbf.w. Preproccessed output is hopefully also available to you. We do not recommend editing the SWIG generated wrappers!! Only python version 2.4 has been targetted originally (other versions?) so that you will probably want to have that version of python installed. We are building binary extensions, so you also need a working c compiler. The compiler used by the author was gcc (for both windows and unix) with the mingw version under windows. Finally, you need a copy of swig (from www.swig.org) in order to (re)generate the c wrappers. In case all that sounds scary, then fear not, it is likely that a single download for windows will just work with the right version of python. Unix systems come with many of those things available anyway. @i pycbf_i.w Despite the temptation to just throw everything from the c header files into the interface, a short experience suggested we are better off to pull out only the parts we want and make the calls more pythonic The input files "CBFhandlewrappers.i", etc. are created by the make\_pycbf.py script. \subsection{Exceptions} We attempt to catch the errors and pass them back to python as exceptions. This could still do with a little work to propagage back the calls causing the errors. Currently there are two global constants defined, called error\_message and error\_status. These are filled out when an error occurred, converting the numerical error value into something the author can read. There is an implicit assumption that if the library is used correctly you will not normally get exceptions. This should be addressed further in areas like file opening, proper python exceptions should be returned. See the section on exception handling in pycbf.i, above. Currently you get a meaningful string back. Should perhaps look into defining these as python exception classes? In any case - the SWIG exception handling is defined via the following. It could have retained the old style if(status = action) but then harder to see what to return... \section{Docstrings} The file doc/CBFlib.html is converted to a file CBFlib.txt to generate the docstrings and many of the wrappers. The conversion was done by the text-based browser, links. This text document is then parsed by a python script called make\_pycbf.py to generate the .i files which are included by the swig wrapper generator. Unfortunately this more complicated for non-python users but seemed less error prone and involved less typing for the author. @i make_pycbf.w \section{Building python extensions - the setup file} Based on the contents of the makefile for CBFlib we will just pull in all of the library for now. We use the distutils approach. @O setup.py @{ # Import the things to build python binary extensions from distutils.core import setup, Extension # Make our extension module e = Extension('_pycbf', sources = ["pycbf_wrap.c","../src/cbf_simple.c"], extra_compile_args=["-g"], library_dirs=["../lib/"], libraries=["cbf"], include_dirs = ["../include"] ) # Build it setup(name="_pycbf",ext_modules=[e],) @} \section{Building and testing the resulting package} Aim to build and test in one go (so that the source and the binary match!!) @o win32.bat @{ nuweb pycbf latex pycbf nuweb pycbf latex pycbf dvipdfm pycbf nuweb pycbf C:\python24\python make_pycbf.py > TODO.txt "C:\program files\swigwin-1.3.31\swig.exe" -python pycbf.i C:\python24\python setup.py build --compiler=mingw32 copy build\lib.win32-2.4\_pycbf.pyd . REM C:\python24\python pycbf_test1.py C:\python24\python pycbf_test2.py C:\python24\python pycbf_test3.py C:\python24\lib\pydoc.py -w pycbf C:\python24\python makeflatascii.py pycbf_ascii_help.txt @} @o linux.sh @{ nuweb pycbf latex pycbf nuweb pycbf latex pycbf dvipdfm pycbf nuweb pycbf lynx -dump CBFlib.html > CBFlib.txt python make_pycbf.py swig -python pycbf.i python setup.py build rm _pycbf.so cp build/lib.linux-i686-2.4/_pycbf.so . python pycbf_test1.py python pycbf_test2.py pydoc -w pycbf python makeflatascii.py pycbf_ascii_help.txt @} This still gives bold in the ascii (=sucks) @O makeflatascii.py @{ import pydoc, pycbf, sys f = open(sys.argv[1],"w") pydoc.pager=lambda text: f.write(text) pydoc.TextDoc.bold = lambda self,text : text pydoc.help(pycbf) @} \section{Debugging compiled extensions} Since it can be a bit of a pain to see where things go wrong here is a quick recipe for poking around with a debugger: \begin{verbatim} amber $> gdb /bliss/users//blissadm/python/bliss_python/suse82/bin/python GNU gdb 5.3 Copyright 2002 Free Software Foundation, Inc. GDB is free software, covered by the GNU General Public License, and you are welcome to change it and/or distribute copies of it under certain conditions. Type "show copying" to see the conditions. There is absolutely no warranty for GDB. Type "show warranty" for details. This GDB was configured as "i586-suse-linux"... (gdb) br _PyImport_LoadDynamicModule Breakpoint 1 at 0x80e4199: file Python/importdl.c, line 28. \end{verbatim} This is how to get a breakpoint when loading the module \begin{verbatim} (gdb) run Starting program: /mntdirect/_bliss/users/blissadm/python/bliss_python/suse82/bin/python [New Thread 16384 (LWP 18191)] Python 2.4.2 (#3, Feb 17 2006, 09:12:13) [GCC 3.3 20030226 (prerelease) (SuSE Linux)] on linux2 Type "help", "copyright", "credits" or "license" for more information. >>> import pycbf [Switching to Thread 16384 (LWP 18191)] Breakpoint 1, _PyImport_LoadDynamicModule (name=0xbfffd280 "_pycbf.so", pathname=0xbfffd280 "_pycbf.so", fp=0x819e208) at Python/importdl.c:28 28 if ((m = _PyImport_FindExtension(name, pathname)) != NULL) { (gdb) finish Run till exit from #0 _PyImport_LoadDynamicModule ( name=0xbfffd280 "_pycbf.so", pathname=0xbfffd280 "_pycbf.so", fp=0x819e208) at Python/importdl.c:28 load_module (name=0xbfffd710 "_pycbf", fp=0x819e208, buf=0xbfffd280 "_pycbf.so", type=3, loader=0x405b44f4) at Python/import.c:1678 1678 break; Value returned is $1 = (PyObject *) 0x405662fc (gdb) break cbf_read_file Breakpoint 2 at 0x407f0508: file ../src/cbf.c, line 221. (gdb) cont Continuing. \end{verbatim} We now have a breakpoint where we wanted inside the dynamically loaded file. \begin{verbatim} >>> o=pycbf.cbf_handle_struct() >>> o.read_file("../img2cif_packed.cif",pycbf.MSG_DIGEST) Breakpoint 2, cbf_read_file (handle=0x81f7c08, stream=0x8174f58, headers=136281096) at ../src/cbf.c:221 221 if (!handle) (gdb) \end{verbatim} Now you can step through the c... \section{Things which are currently missing} This is the to do list. Obviously we could benefit a lot from more extensive testing and checking of the docstrings etc. \input "TODO.txt" \section{Testing} Some test programs to see if anything appears to work. Eventually it would be good to write a proper unit test suite. \subsection{Read a file based on cif2cbf.c} This is a pretty ugly translation of the program cif2cbf.c skipping all of the writing parts. It appeared to work with the file img2cif\_packed.cif which is built when you build CBFlib, hence that file is hardwired in. @O pycbf_test1.py @{ import pycbf object = pycbf.cbf_handle_struct() # FIXME object.read_file("../img2cif_packed.cif",pycbf.MSG_DIGEST) object.rewind_datablock() print "Found",object.count_datablocks(),"blocks" object.select_datablock(0) print "Zeroth is named",object.datablock_name() object.rewind_category() categories = object.count_categories() for i in range(categories): print "Category:",i, object.select_category(i) category_name = object.category_name() print "Name:",category_name, rows=object.count_rows() print "Rows:",rows, cols = object.count_columns() print "Cols:",cols loop=1 object.rewind_column() while loop is not 0: column_name = object.column_name() print "column name \"",column_name,"\"", try: object.next_column() except: break print for j in range(rows): object.select_row(j) object.rewind_column() print "row:",j for k in range(cols): name=object.column_name() print "col:",name, object.select_column(k) typeofvalue=object.get_typeofvalue() print "type:",typeofvalue if typeofvalue.find("bnry") > -1: print "Found the binary!!", s=object.get_integerarray_as_string() print type(s) print dir(s) print len(s) try: import Numeric d = Numeric.fromstring(s,Numeric.UInt32) # Hard wired Unsigned Int32 print d.shape print d[0:10],d[d.shape[0]/2],d[-1] d=Numeric.reshape(d,(2300,2300)) # from matplotlib import pylab # pylab.imshow(d,vmin=0,vmax=1000) # pylab.show() except ImportError: print "You need to get Numeric and matplotlib to see the data" else: value=object.get_value() print "Val:",value,i print del(object) # print dir() #object.free_handle(handle) @} \subsection{Try to test the goniometer and detector} Had some initial difficulties but then downloaded an input cbf file which defines a goniometer and detector. The file was found in the example data which comes with CBFlib. This test is clearly minimalistic for now - it only checks the objects for apparent existence of a single member function. @O pycbf_test2.py @{ import pycbf obj = pycbf.cbf_handle_struct() obj.read_file("../adscconverted.cbf",0) obj.select_datablock(0) g = obj.construct_goniometer() print "Rotation axis is",g.get_rotation_axis() d = obj.construct_detector(0) print "Beam center is",d.get_beam_center() @} It appears to work - eventually. Surprising \subsection{Test cases for the generics} @O pycbf_test3.py @{ import pycbf, unittest class GenericTests(unittest.TestCase): def test_get_local_integer_byte_order(self): self.assertEqual( pycbf.get_local_integer_byte_order(), 'little_endian') def test_get_local_real_byte_order(self): self.assertEqual( pycbf.get_local_real_byte_order() , 'little_endian') def test_get_local_real_format(self): self.assertEqual( pycbf.get_local_real_format(), 'ieee 754-1985') def test_compute_cell_volume(self): self.assertEqual( pycbf.compute_cell_volume((2.,3.,4.,90.,90.,90.)), 24.0) if __name__=="__main__": unittest.main() @} \section{Worked example 1 : xmas beamline + mar ccd detector at the ESRF} Now for the interesting part. We will attempt to actually use pycbf for a real dataprocessing task. Crazy you might think. The idea is the following - we want to take the header information from some mar ccd files (and eventually also the user or the spec control system) and pass this information into cif headers which can be read by fit2d (etc). \subsection{Reading marccd headers} Some relatively ugly code which parses a c header and then tries to interpret the mar ccd header format. FIXME : byteswapping and ends??? @O xmas/readmarheader.py @{#!/usr/bin/env python import struct # Convert mar c header file types to python struct module types mar_c_to_python_struct = { "INT32" : "i", "UINT32" : "I", "char" : "c", "UINT16" : "H" } # Sizes (bytes) of mar c header objects mar_c_sizes = { "INT32" : 4, "UINT32" : 4, "char" : 1, "UINT16" : 2 } # This was worked out by trial and error from a trial image I think MAXIMAGES=9 def make_format(cdefinition): """ Reads the header definition in c and makes the format string to pass to struct.unpack """ lines = cdefinition.split("\n") fmt = "" names = [] expected = 0 for line in lines: if line.find(";")==-1: continue decl = line.split(";")[0].lstrip().rstrip() try: [type, name] = decl.split() except: #print "skipping:",line continue # print "type:",type," name:",name if name.find("[")>-1: # repeated ... times try: num = name.split("[")[1].split("]")[0] num = num.replace("MAXIMAGES",str(MAXIMAGES)) num = num.replace("sizeof(INT32)","4") times = eval(num) except: print "Please decode",decl raise else: times=1 try: fmt += mar_c_to_python_struct[type]*times names += [name]*times expected += mar_c_sizes[type]*times except: #print "skipping",line continue #print "%4d %4d"%(mar_c_sizes[type]*times,expected),name,":",times,line #print struct.calcsize(fmt),expected return names, fmt def read_mar_header(filename): """ Get the header from a binary file """ f = open(filename,"rb") f.seek(1024) header=f.read(3072) f.close() return header def interpret_header(header, fmt, names): """ given a format and header interpret it """ values = struct.unpack(fmt,header) dict = {} i=0 for name in names: if dict.has_key(name): if type(values[i]) == type("string"): dict[name] = dict[name]+values[i] else: try: dict[name].append(values[i]) except: dict[name] = [dict[name],values[i]] else: dict[name] = values[i] i=i+1 return dict # Now for the c definition (found on mar webpage) # The following string is therefore copyrighted by Mar I guess cdefinition = """ typedef struct frame_header_type { /* File/header format parameters (256 bytes) */ UINT32 header_type; /* flag for header type (can be used as magic number) */ char header_name[16]; /* header name (MMX) */ UINT32 header_major_version; /* header_major_version (n.) */ UINT32 header_minor_version; /* header_minor_version (.n) */ UINT32 header_byte_order;/* BIG_ENDIAN (Motorola,MIPS); LITTLE_ENDIAN (DEC, Intel) */ UINT32 data_byte_order; /* BIG_ENDIAN (Motorola,MIPS); LITTLE_ENDIAN (DEC, Intel) */ UINT32 header_size; /* in bytes */ UINT32 frame_type; /* flag for frame type */ UINT32 magic_number; /* to be used as a flag - usually to indicate new file */ UINT32 compression_type; /* type of image compression */ UINT32 compression1; /* compression parameter 1 */ UINT32 compression2; /* compression parameter 2 */ UINT32 compression3; /* compression parameter 3 */ UINT32 compression4; /* compression parameter 4 */ UINT32 compression5; /* compression parameter 4 */ UINT32 compression6; /* compression parameter 4 */ UINT32 nheaders; /* total number of headers */ UINT32 nfast; /* number of pixels in one line */ UINT32 nslow; /* number of lines in image */ UINT32 depth; /* number of bytes per pixel */ UINT32 record_length; /* number of pixels between succesive rows */ UINT32 signif_bits; /* true depth of data, in bits */ UINT32 data_type; /* (signed,unsigned,float...) */ UINT32 saturated_value; /* value marks pixel as saturated */ UINT32 sequence; /* TRUE or FALSE */ UINT32 nimages; /* total number of images - size of each is nfast*(nslow/nimages) */ UINT32 origin; /* corner of origin */ UINT32 orientation; /* direction of fast axis */ UINT32 view_direction; /* direction to view frame */ UINT32 overflow_location;/* FOLLOWING_HEADER, FOLLOWING_DATA */ UINT32 over_8_bits; /* # of pixels with counts 255 */ UINT32 over_16_bits; /* # of pixels with count 65535 */ UINT32 multiplexed; /* multiplex flag */ UINT32 nfastimages; /* # of images in fast direction */ UINT32 nslowimages; /* # of images in slow direction */ UINT32 background_applied; /* flags correction has been applied - hold magic number ? */ UINT32 bias_applied; /* flags correction has been applied - hold magic number ? */ UINT32 flatfield_applied; /* flags correction has been applied - hold magic number ? */ UINT32 distortion_applied; /* flags correction has been applied - hold magic number ? */ UINT32 original_header_type; /* Header/frame type from file that frame is read from */ UINT32 file_saved; /* Flag that file has been saved, should be zeroed if modified */ char reserve1[(64-40)*sizeof(INT32)-16]; /* Data statistics (128) */ UINT32 total_counts[2]; /* 64 bit integer range = 1.85E19*/ UINT32 special_counts1[2]; UINT32 special_counts2[2]; UINT32 min; UINT32 max; UINT32 mean; UINT32 rms; UINT32 p10; UINT32 p90; UINT32 stats_uptodate; UINT32 pixel_noise[MAXIMAGES]; /* 1000*base noise value (ADUs) */ char reserve2[(32-13-MAXIMAGES)*sizeof(INT32)]; /* More statistics (256) */ UINT16 percentile[128]; /* Goniostat parameters (128 bytes) */ INT32 xtal_to_detector; /* 1000*distance in millimeters */ INT32 beam_x; /* 1000*x beam position (pixels) */ INT32 beam_y; /* 1000*y beam position (pixels) */ INT32 integration_time; /* integration time in milliseconds */ INT32 exposure_time; /* exposure time in milliseconds */ INT32 readout_time; /* readout time in milliseconds */ INT32 nreads; /* number of readouts to get this image */ INT32 start_twotheta; /* 1000*two_theta angle */ INT32 start_omega; /* 1000*omega angle */ INT32 start_chi; /* 1000*chi angle */ INT32 start_kappa; /* 1000*kappa angle */ INT32 start_phi; /* 1000*phi angle */ INT32 start_delta; /* 1000*delta angle */ INT32 start_gamma; /* 1000*gamma angle */ INT32 start_xtal_to_detector; /* 1000*distance in mm (dist in um)*/ INT32 end_twotheta; /* 1000*two_theta angle */ INT32 end_omega; /* 1000*omega angle */ INT32 end_chi; /* 1000*chi angle */ INT32 end_kappa; /* 1000*kappa angle */ INT32 end_phi; /* 1000*phi angle */ INT32 end_delta; /* 1000*delta angle */ INT32 end_gamma; /* 1000*gamma angle */ INT32 end_xtal_to_detector; /* 1000*distance in mm (dist in um)*/ INT32 rotation_axis; /* active rotation axis */ INT32 rotation_range; /* 1000*rotation angle */ INT32 detector_rotx; /* 1000*rotation of detector around X */ INT32 detector_roty; /* 1000*rotation of detector around Y */ INT32 detector_rotz; /* 1000*rotation of detector around Z */ char reserve3[(32-28)*sizeof(INT32)]; /* Detector parameters (128 bytes) */ INT32 detector_type; /* detector type */ INT32 pixelsize_x; /* pixel size (nanometers) */ INT32 pixelsize_y; /* pixel size (nanometers) */ INT32 mean_bias; /* 1000*mean bias value */ INT32 photons_per_100adu; /* photons / 100 ADUs */ INT32 measured_bias[MAXIMAGES]; /* 1000*mean bias value for each image*/ INT32 measured_temperature[MAXIMAGES]; /* Temperature of each detector in milliKelvins */ INT32 measured_pressure[MAXIMAGES]; /* Pressure of each chamber in microTorr */ /* Retired reserve4 when MAXIMAGES set to 9 from 16 and two fields removed, and temp and pressure added char reserve4[(32-(5+3*MAXIMAGES))*sizeof(INT32)] */ /* X-ray source and optics parameters (128 bytes) */ /* X-ray source parameters (8*4 bytes) */ INT32 source_type; /* (code) - target, synch. etc */ INT32 source_dx; /* Optics param. - (size microns) */ INT32 source_dy; /* Optics param. - (size microns) */ INT32 source_wavelength; /* wavelength (femtoMeters) */ INT32 source_power; /* (Watts) */ INT32 source_voltage; /* (Volts) */ INT32 source_current; /* (microAmps) */ INT32 source_bias; /* (Volts) */ INT32 source_polarization_x; /* () */ INT32 source_polarization_y; /* () */ char reserve_source[4*sizeof(INT32)]; /* X-ray optics_parameters (8*4 bytes) */ INT32 optics_type; /* Optics type (code)*/ INT32 optics_dx; /* Optics param. - (size microns) */ INT32 optics_dy; /* Optics param. - (size microns) */ INT32 optics_wavelength; /* Optics param. - (size microns) */ INT32 optics_dispersion; /* Optics param. - (*10E6) */ INT32 optics_crossfire_x; /* Optics param. - (microRadians) */ INT32 optics_crossfire_y; /* Optics param. - (microRadians) */ INT32 optics_angle; /* Optics param. - (monoch. 2theta - microradians) */ INT32 optics_polarization_x; /* () */ INT32 optics_polarization_y; /* () */ char reserve_optics[4*sizeof(INT32)]; char reserve5[((32-28)*sizeof(INT32))]; /* File parameters (1024 bytes) */ char filetitle[128]; /* Title */ char filepath[128]; /* path name for data file */ char filename[64]; /* name of data file */ char acquire_timestamp[32]; /* date and time of acquisition */ char header_timestamp[32]; /* date and time of header update */ char save_timestamp[32]; /* date and time file saved */ char file_comments[512]; /* comments, use as desired */ char reserve6[1024-(128+128+64+(3*32)+512)]; /* Dataset parameters (512 bytes) */ char dataset_comments[512]; /* comments, used as desired */ /* pad out to 3072 bytes */ char pad[3072-(256+128+256+(3*128)+1024+512)]; } frame_header; """ class marheaderreader: """ Class to sit and read a series of images (makes format etc only once) """ def __init__(self): """ Initialise internal stuff """ self.names , self.fmt = make_format(cdefinition) def get_header(self,filename): """ Reads a header from file filename """ h=read_mar_header(filename) dict = interpret_header(h,self.fmt,self.names) # Append ESRF formatted stuff items = self.readesrfstring(dict["dataset_comments[512]"]) for pair in items: dict[pair[0]]=pair[1] items = self.readesrfstring(dict["file_comments[512]"]) for pair in items: dict[pair[0]]=pair[1] dict["pixelsize_x_mm"]= str(float(dict["pixelsize_x"])/1e6) dict["pixelsize_y_mm"]= str(float(dict["pixelsize_y"])/1e6) dict["integration_time_sec"]= str(float(dict["integration_time"])/1e3) dict["beam_y_mm"]= str(float(dict["pixelsize_y_mm"])* float(dict["beam_y"])/1000.) dict["beam_x_mm"]= str(float(dict["pixelsize_x_mm"])* float(dict["beam_x"])/1000.) return dict def readesrfstring(self,s): """ Interpret the so called "esrf format" header lines which are in comment sections """ s=s.replace("\000","") items = filter(None, [len(x)>1 and x or None for x in [ item.split("=") for item in s.split(";")]]) return items if __name__=="__main__": """ Make a little program to process files """ import sys print "Starting" names,fmt = make_format(cdefinition) print "Names and format made" h = read_mar_header(sys.argv[1]) print "Read header, interpreting" d = interpret_header(h,fmt,names) printed = {} for name in names: if printed.has_key(name): continue print name,":",d[name] printed[name]=1 @} \subsection{Writing out cif files for fit2d/xmas} A script which is supposed to pick up some header information from the mar images, some more infomation from the user and the create cif files. This relies on a "template" cif file to get it started (avoids me programming everything). @O xmas/xmasheaders.py @{#!/usr/bin/env python import pycbf # Some cbf helper functions - obj would be a cbf_handle_struct object def writewavelength(obj,wavelength): obj.set_wavelength(float(wavelength)) def writecellpar(obj,cifname,value): obj.find_category("cell") obj.find_column(cifname) obj.set_value(value) def writecell(obj,cell): """ call with cell = (a,b,c,alpha,beta,gamma) """ obj.find_category("cell") obj.find_column("length_a") obj.set_value(str(cell[0])) obj.find_column("length_b") obj.set_value(str(cell[1])) obj.find_column("length_c") obj.set_value(str(cell[2])) obj.find_column("angle_alpha") obj.set_value(str(cell[3])) obj.find_column("angle_beta") obj.set_value(str(cell[4])) obj.find_column("angle_gamma") obj.set_value(str(cell[5])) def writeUB(obj,ub): """ call with ub that can be indexed ub[i][j] """ obj.find_category("diffrn_orient_matrix") for i in (1,2,3): for j in (1,2,3): obj.find_column("UB[%d][%d]"%(i,j)) obj.set_value(str(ub[i-1][j-1])) def writedistance(obj,distance): obj.set_axis_setting("DETECTOR_Z",float(distance),0.) def writebeam_x_mm(obj,cen): obj.set_axis_setting("DETECTOR_X",float(cen),0.) def writebeam_y_mm(obj,cen): obj.set_axis_setting("DETECTOR_Y",float(cen),0.) def writeSPECcmd(obj,s): obj.find_category("diffrn_measurement") obj.find_column("details") obj.set_value(s) def writeSPECscan(obj,s): obj.find_category("diffrn_scan") obj.find_column("id") obj.set_value("SCAN%s"%(s)) obj.find_category("diffrn_scan_axis") obj.find_column("scan_id") obj.rewind_row() for i in range(obj.count_rows()): obj.select_row(i) obj.set_value("SCAN%s"%(s)) obj.find_category("diffrn_scan_frame") obj.find_column("scan_id") obj.rewind_row() obj.set_value("SCAN%s"%(s)) def writepixelsize_y_mm(obj,s): """ Units are mm for cif """ # element number = assume this is first and only detector element_number = 0 # axis number = faster or slower... ? Need to check precedence ideally... obj.find_category("array_structure_list") obj.find_column("axis_set_id") obj.find_row("ELEMENT_Y") obj.find_column("precedence") axis_number = obj.get_integervalue() obj.set_pixel_size(element_number, axis_number, float(s) ) obj.find_category("array_structure_list_axis") obj.find_column("axis_id") obj.find_row("ELEMENT_Y") obj.find_column("displacement") obj.set_doublevalue("%.6g",float(s)/2.0) obj.find_column("displacement_increment") obj.set_doublevalue("%.6g",float(s)) def writepixelsize_x_mm(obj,s): # element number = assume this is first and only detector element_number = 0 # axis number = faster or slower... ? Need to check precedence ideally... obj.find_category("array_structure_list") obj.find_column("axis_set_id") obj.find_row("ELEMENT_X") obj.find_column("precedence") axis_number = obj.get_integervalue() obj.set_pixel_size(element_number, axis_number, float(s) ) obj.find_category("array_structure_list_axis") obj.find_column("axis_id") obj.find_row("ELEMENT_X") obj.find_column("displacement") obj.set_doublevalue("%.6g",float(s)/2.0) obj.find_column("displacement_increment") obj.set_doublevalue("%.6g",float(s)) def writeintegrationtime(obj,s): obj.find_category("diffrn_scan_frame") obj.find_column("integration_time") obj.set_value(str(s).replace("\000","")) def writenfast(obj,s): obj.find_category("array_structure_list") obj.find_column("index") obj.find_row("1") obj.find_column("dimension") obj.set_value(str(s)) def writenslow(obj,s): obj.find_category("array_structure_list") obj.find_column("index") obj.find_row("2") obj.find_column("dimension") obj.set_value(str(s)) functiondict = { "lambda" : writewavelength, "beam_x_mm" : writebeam_x_mm, "beam_y_mm" : writebeam_y_mm, "distance" : writedistance, "UB" : writeUB, "cell" : writecell, "cmd" : writeSPECcmd, "scan" : writeSPECscan, "nfast" : writenfast, "nslow" : writenslow, "pixelsize_y_mm" : writepixelsize_y_mm, "pixelsize_x_mm" : writepixelsize_x_mm, "integration_time_sec" : writeintegrationtime, "tth" : lambda obj,value : obj.set_axis_setting( "DETECTOR_TWO_THETA_VERTICAL",float(value),0.), "chi" : lambda obj,value : obj.set_axis_setting( "GONIOMETER_CHI",float(value),0.), "th" : lambda obj,value : obj.set_axis_setting( "GONIOMETER_THETA",float(value),0.), "phi" : lambda obj,value : obj.set_axis_setting( "GONIOMETER_PHI",float(value),0.), "lc_a" : lambda obj,value : writecellpar(obj,"length_a",value), "lc_b" : lambda obj,value : writecellpar(obj,"length_b",value), "lc_c" : lambda obj,value : writecellpar(obj,"length_c",value), "lc_al" : lambda obj,value : writecellpar(obj,"angle_alpha",value), "lc_be" : lambda obj,value : writecellpar(obj,"angle_beta",value), "lc_ga" : lambda obj,value : writecellpar(obj,"angle_gamma",value) } """ # # Not implementing these for now lc_ra lc_rc 0.4742 lc_rb 1.16 energy 13 cp_phi -180 alpha 7.3716 lc_ral 90 cp_tth -180 lc_rga 90 beta 17.572 omega -2.185 h 0.21539 k 0.01957 l 5.9763 cp_chi -180 lc_rbe 90 cp_th -180 azimuth 0 """ # Finally a class for creating header files. # It reads a template and then offers a processfile command # for running over a file series class cifheader: def __init__(self,templatefile): self.cbf=pycbf.cbf_handle_struct() self.cbf.read_template(templatefile) from readmarheader import marheaderreader self.marheaderreader = marheaderreader() def processfile(self,filename, outfile=None, format="mccd", **kwds): outfile=outfile.replace(format,"cif") if format == "mccd": items = self.marheaderreader.get_header(filename) if format == "bruker": pass if format == "edf": pass self.items=items # Take the image header items as default self.updateitems(items) # Allow them to be overridden self.updateitems(kwds) # Write the file self.writefile(outfile) def writefile(self,filename): self.cbf.write_file(filename,pycbf.CIF,pycbf.MIME_HEADERS, pycbf.ENC_BASE64) def updateitems(self,dict): names = dict.keys() for name in names: value = dict[name] # use a dictionary of functions if functiondict.has_key(name): # print "calling",functiondict[name],value apply(functiondict[name],(self.cbf,value)) else: #print "ignoring",name,value pass if __name__=="__main__": import sys obj=cifheader("xmas_cif_template.cif") ub = [[0.11, 0.12, 0.13] , [0.21, 0.22, 0.23], [0.31, 0.32, 0.33]] for filename in sys.argv[1:]: fileout = filename.split("/")[-1] obj.processfile(filename, outfile=fileout, UB=ub, distance=123.456) @} \subsection{A template cif file for the xmas beamline} This was sort of copied and modified from an example file. It has NOT been checked. Hopefully the four circle geometry at least vaguely matches what is at the beamline. @O xmas/xmas_cif_template.cif @{ ###CBF: VERSION 0.6 # CBF file written by cbflib v0.6 data_image_1 loop_ _diffrn.id _diffrn.crystal_id DS1 DIFFRN_CRYSTAL_ID loop_ _cell.length_a 5.959(1) _cell.length_b 14.956(1) _cell.length_c 19.737(3) _cell.angle_alpha 90 _cell.angle_beta 90 _cell.angle_gamma 90 loop_ _diffrn_orient_matrix.id 'DS1' _diffrn_orient_matrix.type ; reciprocal axis matrix, multiplies hkl vector to generate diffractometer xyz vector and diffractometer angles ; _diffrn_orient_matrix.UB[1][1] 0.11 _diffrn_orient_matrix.UB[1][2] 0.12 _diffrn_orient_matrix.UB[1][3] 0.13 _diffrn_orient_matrix.UB[2][1] 0.21 _diffrn_orient_matrix.UB[2][2] 0.22 _diffrn_orient_matrix.UB[2][3] 0.23 _diffrn_orient_matrix.UB[3][1] 0.31 _diffrn_orient_matrix.UB[3][2] 0.32 _diffrn_orient_matrix.UB[3][3] 0.33 loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.current _diffrn_source.type DS1 synchrotron 200.0 'XMAS beamline bm28 ESRF' loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.probe _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source _diffrn_radiation.collimation DS1 WAVELENGTH1 x-ray 'Si 111' 0.8 0.0 0.08 0.01 0.00 '0.20 mm x 0.20 mm' loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 1.73862 1.0 loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.details _diffrn_detector.number_of_axes DS1 MAR 'MAR XMAS' 'slow mode' 5 loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR DETECTOR_TWO_THETA_VERTICAL MAR DETECTOR_X MAR DETECTOR_Y MAR DETECTOR_Z MAR DETECTOR_PITCH loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method _diffrn_measurement.details DS1 GONIOMETER 3 rotation 'i0=1.000 i1=1.000 i2=1.000 ib=1.000 beamstop=20 mm 0% attenuation' loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_CHI GONIOMETER GONIOMETER_THETA loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_THETA 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_CHI 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI 185 1 1 0.0 0.0 0.0 SCAN1 DETECTOR_TWO_THETA_VERTICAL 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 103.750 0 0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 360 SCAN1 1997-12-04T10:23:48 loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_THETA 0.0 0.0 FRAME1 GONIOMETER_CHI 0.0 0.0 FRAME1 GONIOMETER_PHI 185 0.0 FRAME1 DETECTOR_TWO_THETA_VERTICAL 185 0.0 FRAME1 DETECTOR_Z 0.0 103.750 FRAME1 DETECTOR_Y 0.0 0.0 FRAME1 DETECTOR_X 0.0 0.0 FRAME1 DETECTOR_PITCH 0.0 0.0 loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_THETA rotation goniometer . 1 0 0 . . . GONIOMETER_CHI rotation goniometer GONIOMETER_THETA 0 0 1 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_PHI 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_TWO_THETA_VERTICAL rotation goniometer . 1 0 0 . . . DETECTOR_Z translation detector DETECTOR_TWO_THETA_VERTICAL 0 0 -1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 -94.0032 94.0032 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 2049 1 increasing ELEMENT_X ARRAY1 2 2049 2 increasing ELEMENT_Y loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.0408 0.0816 ELEMENT_Y ELEMENT_Y -0.0408 -0.0816 loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 0.30 0.03 65000 0 loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian @} \end{document} ./CBFlib-0.9.2.2/pycbf/make_pycbf.w0000644000076500007650000034440411603702120015176 0ustar yayayaya% make_pycbf.w % nuweb source file used to create % make_pycbf.py and to document it in pycbf.w % % pycbf - python binding to the CBFlib library % % Copyright (C) 2005 Jonathan Wright % ESRF, Grenoble, France % email: wright@@esrf.fr % % Revised for CBFlib 0.9 releases, Herbert J. Bernstein, 23 Aug 2010 % %###################################################################### %# # %# YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE INCLUDING PYCBF UNDER THE # %# TERMS OF THE GPL # %# # %# ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API INCLUDING PYCBF # %# UNDER THE TERMS OF THE LGPL # %# # %###################################################################### % %########################### GPL NOTICES ############################## %# # %# This program is free software; you can redistribute it and/or # %# modify it under the terms of the GNU General Public License as # %# published by the Free Software Foundation; either version 2 of # %# (the License, or (at your option) any later version. # %# # %# This program is distributed in the hope that it will be useful, # %# but WITHOUT ANY WARRANTY; without even the implied warranty of # %# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # %# GNU General Public License for more details. # %# # %# You should have received a copy of the GNU General Public License # %# along with this program; if not, write to the Free Software # %# Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA # %# 02111-1307 USA # %# # %###################################################################### % %######################### LGPL NOTICES ############################### %# # %# This library is free software; you can redistribute it and/or # %# modify it under the terms of the GNU Lesser General Public # %# License as published by the Free Software Foundation; either # %# version 2.1 of the License, or (at your option) any later version. # %# # %# This library is distributed in the hope that it will be useful, # %# but WITHOUT ANY WARRANTY; without even the implied warranty of # %# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # %# Lesser General Public License for more details. # %# # %# You should have received a copy of the GNU Lesser General Public # %# License along with this library; if not, write to the Free # %# Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, # %# MA 02110-1301 USA # %# # %###################################################################### % \section{Wrappers} The program that does the conversion from CBFlib.txt to the SWIG input files is a python script named make\_pycbf.py. @O make_pycbf.py @{ print "\\begin{verbatim}" print "This output comes from make_pycbf.py which generates the wrappers" print "pycbf Copyright (C) 2005 Jonathan Wright, no warranty, LGPL" ###################################################################### # # # YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE INCLUDING PYCBF UNDER THE # # TERMS OF THE GPL # # # # ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API INCLUDING PYCBF # # UNDER THE TERMS OF THE LGPL # # # ###################################################################### ########################### GPL NOTICES ############################## # # # This program is free software; you can redistribute it and/or # # modify it under the terms of the GNU General Public License as # # published by the Free Software Foundation; either version 2 of # # (the License, or (at your option) any later version. # # # # This program is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # # GNU General Public License for more details. # # # # You should have received a copy of the GNU General Public License # # along with this program; if not, write to the Free Software # # Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA # # 02111-1307 USA # # # ###################################################################### ######################### LGPL NOTICES ############################### # # # This library is free software; you can redistribute it and/or # # modify it under the terms of the GNU Lesser General Public # # License as published by the Free Software Foundation; either # # version 2.1 of the License, or (at your option) any later version. # # # # This library is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # # Lesser General Public License for more details. # # # # You should have received a copy of the GNU Lesser General Public # # License along with this library; if not, write to the Free # # Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, # # MA 02110-1301 USA # # # ###################################################################### # Get the ascii text as a list of strings lines = open("CBFlib.txt","r").readlines() # Variables to hold the useful things we find in the file docstring = "\n" name="" # Flag to indicate we have not read anything useful yet on=0 # Dictionary of function prototypes and documentation, keyed by name in C. name_dict = {} i=-1 debug = 0 # Parse the text prototypes = "" while i=0 and on==1: on=10 # Only try for ten lines after it say PROTOTYPE continue if line.find("#include")>=0: # why? continue if line.find("int cbf_")>=0: # We found a function # keep going up to DESCRIPTION prototypes+=""+lines[i].rstrip()+" " # print lines[i].rstrip() check=0 while lines[i+1].find("DESCRIPTION")==-1 and lines[i+1].find("int cbf_")==-1: i=i+1 prototypes+=lines[i].rstrip()+" " # lose the \n # print lines[i].rstrip() check+=1 if check>20: raise Exception("Runaway prototype "+prototypes) on=1 # Keep reading docstring continue if on > 1: # why? on=on-1 if line.find("3. File format")>=0 and on==1: # Stop processing at section 3 i=len(lines) if on==1: # Docstring ends at 2.xxx for next function or see also # We are losing the see also information for now (needed the section # breaks in the rtf file) if len(line.strip())==0: docstring+="\n" continue else: if docstring[-1]=="\n": docstring += line.lstrip().rstrip() else: docstring =docstring+" "+line.lstrip().rstrip() if line.strip()[0] in [str(j) for j in range(9)] or \ line.find("SEE ALSO")>=0 or \ line.find("________")>=0 or \ line.find("--------")>=0: if len(docstring)>0: # print "Prototypes: ",prototypes docstring = docstring.replace("\"", " \\\"") # escape the quotes for prototype in prototypes.strip().split(";")[:-1]: name = prototype.split("(")[0].strip() cname = name.split()[1].strip() prototype = prototype.strip()+";" name_dict[cname]=[prototype,docstring] # print "Prototype: ","::",cname,"::",name,"::", prototype prototypes = "" # print "Found ",prototype docstring="\n" prototype="" cname="" on=0 else: raise Exception("bad docstring") # End of CBFlib.txt file - now generate wrapper code for swig def myformat(s,l,indent=0,breakon=" "): """ Try to pretty print lines - this is a pain... """ lines = s.rstrip().split("\n") out="" for line in lines: if len(line)==0: continue # skip blank lines if len(line)>l: words = line.split(breakon) newline=words[0] if len(words)>1: for word in words[1:]: if len(newline)+len(word)+1 < l: newline=newline+breakon+word else: out = out+newline+breakon+"\n"+indent*" " newline=word out += newline+"\n" else: out += "\n" else: out += line+"\n" # Last one if out == "": return "\n" else: return out def docstringwrite(pyfunc,input,output,prototype,cbflibdoc): doc = "%feature(\"autodoc\", \"\nReturns : " returns = "" for out in output: returns += out+"," if len(returns)>0: doc += myformat(returns[:-1],70,indent = 10,breakon=",") else: doc += "\n" doc += "*args : " takes = "" for inp in input: takes += inp+"," if len(takes)>0: doc += myformat(takes[:-1],70,indent = 10,breakon=",") else: doc += "\n" doc += "\nC prototype: "+myformat(prototype,65,indent=16,breakon=",") doc += "\nCBFLib documentation:\n"+myformat(cbflibdoc,70)+"\")" doc += pyfunc+";\n" return doc cbfhandle_specials = { "cbf_get_integerarrayparameters":[""" %apply int *OUTPUT {int *compression,int *binary_id, int *elsize, int *elsigned, int *elunsigned, int *elements, int *minelement, int *maxelement} get_integerarrayparameters; void get_integerarrayparameters(int *compression,int *binary_id, int *elsize, int *elsigned, int *elunsigned, int *elements, int *minelement, int *maxelement){ unsigned int comp; size_t elsiz, elem; cbf_failnez(cbf_get_integerarrayparameters(self, &comp,binary_id, &elsiz, elsigned, elunsigned, &elem, minelement, maxelement)); *compression = comp; /* FIXME - does this convert in C? */ *elsize = elsiz; *elements = elem; } ""","get_integerarrayparameters",[],["int compression","int binary_id", "int elsize", "int elsigned", "int elunsigned", "int elements", "int minelement", "int maxelement"]], "cbf_get_integerarrayparameters_wdims":[""" %cstring_output_allocate_size(char **bo, int *bolen, free(*$1)); %apply int *OUTPUT {int *compression,int *binary_id, int *elsize, int *elsigned, int *elunsigned, int *elements, int *minelement, int *maxelement, int *dimfast, int *dimmid, int *dimslow, int *padding} get_integerarrayparameters_wdims; void get_integerarrayparameters_wdims(int *compression,int *binary_id, int *elsize, int *elsigned, int *elunsigned, int *elements, int *minelement, int *maxelement, char **bo, int *bolen, int *dimfast, int *dimmid, int *dimslow, int *padding ){ unsigned int comp; size_t elsiz, elem, df,dm,ds,pd; const char * byteorder; char * bot; cbf_failnez(cbf_get_integerarrayparameters_wdims(self, &comp,binary_id, &elsiz, elsigned, elunsigned, &elem, minelement, maxelement, &byteorder,&df,&dm,&ds,&pd )); *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)} strncpy(bot,byteorder,*bolen); *bo = bot; *compression = comp; *elsize = elsiz; *elements = elem; *dimfast = df; *dimmid = dm; *dimslow = ds; *padding = pd; } ""","get_integerarrayparameters_wdims",[],["int compression","int binary_id", "int elsize", "int elsigned", "int elunsigned", "int elements", "int minelement", "int maxelement", "char **bo", "int *bolen", "int dimfast", "int dimmid", "int dimslow", "int padding"]], "cbf_get_integerarrayparameters_wdims_fs":[""" %cstring_output_allocate_size(char **bo, int *bolen, free(*$1)); %apply int *OUTPUT {int *compression,int *binary_id, int *elsize, int *elsigned, int *elunsigned, int *elements, int *minelement, int *maxelement, int *dimfast, int *dimmid, int *dimslow, int *padding} get_integerarrayparameters_wdims_fs; void get_integerarrayparameters_wdims_fs(int *compression,int *binary_id, int *elsize, int *elsigned, int *elunsigned, int *elements, int *minelement, int *maxelement, char **bo, int *bolen, int *dimfast, int *dimmid, int *dimslow, int *padding ){ unsigned int comp; size_t elsiz, elem, df,dm,ds,pd; const char * byteorder; char * bot; cbf_failnez(cbf_get_integerarrayparameters_wdims_fs(self, &comp,binary_id, &elsiz, elsigned, elunsigned, &elem, minelement, maxelement, &byteorder,&df,&dm,&ds,&pd )); *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)} strncpy(bot,byteorder,*bolen); *bo = bot; *compression = comp; *elsize = elsiz; *elements = elem; *dimfast = df; *dimmid = dm; *dimslow = ds; *padding = pd; } ""","get_integerarrayparameters_wdims_fs",[],["int compression","int binary_id", "int elsize", "int elsigned", "int elunsigned", "int elements", "int minelement", "int maxelement", "char **bo", "int *bolen", "int dimfast", "int dimmid", "int dimslow", "int padding"]], "cbf_get_integerarrayparameters_wdims_sf":[""" %cstring_output_allocate_size(char **bo, int *bolen, free(*$1)); %apply int *OUTPUT {int *compression,int *binary_id, int *elsize, int *elsigned, int *elunsigned, int *elements, int *minelement, int *maxelement, int *dimslow, int *dimmid, int *dimfast, int *padding} get_integerarrayparameters_wdims_sf; void get_integerarrayparameters_wdims_sf(int *compression,int *binary_id, int *elsize, int *elsigned, int *elunsigned, int *elements, int *minelement, int *maxelement, char **bo, int *bolen, int *dimslow, int *dimmid, int *dimfast, int *padding ){ unsigned int comp; size_t elsiz, elem, df,dm,ds,pd; const char * byteorder; char * bot; cbf_failnez(cbf_get_integerarrayparameters_wdims_sf(self, &comp,binary_id, &elsiz, elsigned, elunsigned, &elem, minelement, maxelement, &byteorder,&ds,&dm,&df,&pd )); *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)} strncpy(bot,byteorder,*bolen); *bo = bot; *compression = comp; *elsize = elsiz; *elements = elem; *dimfast = df; *dimmid = dm; *dimslow = ds; *padding = pd; } ""","get_integerarrayparameters_wdims_sf",[],["int compression","int binary_id", "int elsize", "int elsigned", "int elunsigned", "int elements", "int minelement", "int maxelement", "char **bo", "int *bolen", "int dimslow", "int dimmid", "int dimfast", "int padding"]], "cbf_get_realarrayparameters":[""" %apply int *OUTPUT {int *compression,int *binary_id, int *elsize, int *elements} get_realarrayparameters; void get_realarrayparameters(int *compression,int *binary_id, int *elsize, int *elements){ unsigned int comp; size_t elsiz, elem; cbf_failnez(cbf_get_realarrayparameters(self, &comp ,binary_id, &elsiz, &elem )); *compression = comp; /* FIXME - does this convert in C? */ *elsize = elsiz; *elements = elem; } ""","get_realarrayparameters",[],["int compression","int binary_id", "int elsize", "int elements"]], "cbf_get_realarrayparameters_wdims":[""" %cstring_output_allocate_size(char **bo, int *bolen, free(*$1)); %apply int *OUTPUT {int *compression,int *binary_id, int *elsize, int *elements, int *dimslow, int *dimmid, int *dimfast, int *padding} get_realarrayparameters_wdims; void get_realarrayparameters_wdims(int *compression,int *binary_id, int *elsize, int *elements, char **bo, int *bolen, int *dimfast, int *dimmid, int *dimslow, int *padding ){ unsigned int comp; size_t elsiz, elem, df,dm,ds,pd; const char * byteorder; char * bot; cbf_failnez(cbf_get_realarrayparameters_wdims(self, &comp,binary_id, &elsiz, &elem, &byteorder,&ds,&dm,&ds,&pd )); *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)} strncpy(bot,byteorder,*bolen); *bo = bot; *compression = comp; *elsize = elsiz; *elements = elem; *dimfast = df; *dimmid = dm; *dimslow = ds; *padding = pd; } ""","get_realarrayparameters_wdims",[],["int compression","int binary_id", "int elsize", "int elements", "char **bo", "int *bolen", "int dimfast", "int dimmid", "int dimslow", "int padding"]], "cbf_get_realarrayparameters_wdims_fs":[""" %cstring_output_allocate_size(char **bo, int *bolen, free(*$1)); %apply int *OUTPUT {int *compression,int *binary_id, int *elsize, int *elements, int *dimslow, int *dimmid, int *dimfast, int *padding} get_realarrayparameters_wdims_fs; void get_realarrayparameters_wdims_fs(int *compression,int *binary_id, int *elsize, int *elements, char **bo, int *bolen, int *dimfast, int *dimmid, int *dimslow, int *padding ){ unsigned int comp; size_t elsiz, elem, df,dm,ds,pd; const char * byteorder; char * bot; cbf_failnez(cbf_get_realarrayparameters_wdims_fs(self, &comp,binary_id, &elsiz, &elem, &byteorder,&ds,&dm,&ds,&pd )); *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)} strncpy(bot,byteorder,*bolen); *bo = bot; *compression = comp; *elsize = elsiz; *elements = elem; *dimfast = df; *dimmid = dm; *dimslow = ds; *padding = pd; } ""","get_realarrayparameters_wdims_fs",[],["int compression","int binary_id", "int elsize", "int elements", "char **bo", "int *bolen", "int dimfast", "int dimmid", "int dimslow", "int padding"]], "cbf_get_realarrayparameters_wdims_sf":[""" %cstring_output_allocate_size(char **bo, int *bolen, free(*$1)); %apply int *OUTPUT {int *compression,int *binary_id, int *elsize, int *elements, int *dimslow, int *dimmid, int *dimfast, int *padding} get_realarrayparameters_wdims_sf; void get_realarrayparameters_wdims_sf(int *compression,int *binary_id, int *elsize, int *elements, char **bo, int *bolen, int *dimslow, int *dimmid, int *dimfast, int *padding ){ unsigned int comp; size_t elsiz, elem, df,dm,ds,pd; const char * byteorder; char * bot; cbf_failnez(cbf_get_realarrayparameters_wdims_sf(self, &comp,binary_id, &elsiz, &elem, &byteorder,&ds,&dm,&df,&pd )); *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)} strncpy(bot,byteorder,*bolen); *bo = bot; *compression = comp; *elsize = elsiz; *elements = elem; *dimfast = df; *dimmid = dm; *dimslow = ds; *padding = pd; } ""","get_realarrayparameters_wdims_sf",[],["int compression","int binary_id", "int elsize", "int elements", "char **bo", "int *bolen", "int dimslow", "int dimmid", "int dimfast", "int padding"]], "cbf_get_integerarray":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_integerarray_as_string; // Get the length correct void get_integerarray_as_string(char **s, int *slen){ int binary_id, elsigned, elunsigned; size_t elements, elements_read, elsize; int minelement, maxelement; unsigned int compression; void * array; *slen = 0; /* Initialise in case of problems */ cbf_failnez(cbf_get_integerarrayparameters(self, &compression, &binary_id, &elsize, &elsigned, &elunsigned, &elements, &minelement, &maxelement)); if ((array=malloc(elsize*elements))) { /* cbf_failnez (cbf_select_column(cbf,colnum)) */ cbf_failnez (cbf_get_integerarray(self, &binary_id, (void *)array, elsize, elsigned, elements, &elements_read)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*elements; *s = (char *) array; } ""","get_integerarray_as_string",[],["(Binary)String"] ], "cbf_get_image":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_image_as_string; // Get the length correct void get_image_as_string(int element_number, char **s, int *slen, int elsize, int elsign, int ndimslow, int ndimfast){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimslow))) { cbf_failnez (cbf_get_image(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, elsign, (size_t) ndimslow, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimslow; *s = (char *) array; } ""","get_image_as_string",["int element_number", "int elsize", "int elsign", "int ndimslow", "int ndimfast"],["(Binary)String"] ], "cbf_get_image_fs":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_image_fs_as_string; // Get the length correct void get_image_fs_as_string(int element_number, char **s, int *slen, int elsize, int elsign, int ndimfast, int ndimslow){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimslow))) { cbf_failnez (cbf_get_image_fs(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, elsign, (size_t) ndimfast, (size_t)ndimslow)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimslow; *s = (char *) array; } ""","get_image_fs_as_string",["int element_number", "int elsize", "int elsign", "int ndimfast", "int ndimslow"],["(Binary)String"] ], "cbf_get_image_sf":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_image_fs_as_string; // Get the length correct void get_image_sf_as_string(int element_number, char **s, int *slen, int elsize, int elsign, int ndimslow, int ndimfast){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimslow))) { cbf_failnez (cbf_get_image_sf(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, elsign, (size_t) ndimslow, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimslow; *s = (char *) array; } ""","get_image_sf_as_string",["int element_number", "int elsize", "int elsign", "int ndimslow", "int ndimfast"],["(Binary)String"] ], "cbf_get_real_image":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_real_image_as_string; // Get the length correct void get_real_image_as_string(int element_number, char **s, int *slen, int elsize, int ndimslow, int ndimfast){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimslow))) { cbf_failnez (cbf_get_real_image(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, (size_t) ndimslow, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimslow; *s = (char *) array; } ""","get_real_image_as_string",["int element_number", "int elsize", "int ndimslow", "int ndimfast"],["(Binary)String"] ], "cbf_get_real_image_fs":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_real_image_fs_as_string; // Get the length correct void get_real_image_fs_as_string(int element_number, char **s, int *slen, int elsize, int ndimfast, int ndimslow){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimslow))) { cbf_failnez (cbf_get_real_image_fs(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, (size_t) ndimfast, (size_t)ndimslow)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimslow; *s = (char *) array; } ""","get_real_image_fs_as_string",["int element_number", "int elsize", "int ndimfast", "int ndimslow"],["(Binary)String"] ], "cbf_get_real_image_sf":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_real_image_sf_as_string; // Get the length correct void get_real_image_sf_as_string(int element_number, char **s, int *slen, int elsize, int ndimslow, int ndimfast){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimslow))) { cbf_failnez (cbf_get_real_image_sf(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, (size_t) ndimslow, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimslow; *s = (char *) array; } ""","get_real_image_sf_as_string",["int element_number", "int elsize", "int ndimslow", "int ndimfast"],["(Binary)String"] ], "cbf_get_3d_image":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_3d_image_as_string; // Get the length correct void get_3d_image_as_string(int element_number, char **s, int *slen, int elsize, int elsign, int ndimfast, int ndimmid, int ndimslow){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) { cbf_failnez (cbf_get_3d_image(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, elsign, (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimmid*ndimslow; *s = (char *) array; } ""","get_3d_image_as_string",["int element_number", "int elsize", "int elsign", "int ndimslow", "int ndimmid", "int ndimfast"],["(Binary)String"] ], "cbf_get_3d_image_fs":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_3d_image_fs_as_string; // Get the length correct void get_3d_image_fs_as_string(int element_number, char **s, int *slen, int elsize, int elsign, int ndimfast, int ndimmid, int ndimslow){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) { cbf_failnez (cbf_get_3d_image_fs(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, elsign, (size_t) ndimfast, (size_t)ndimmid, (size_t)ndimslow)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimmid*ndimslow; *s = (char *) array; } ""","get_3d_image_fs_as_string",["int element_number", "int elsize", "int elsign", "int ndimfast", "int ndimmid", "int ndimslow"],["(Binary)String"] ], "cbf_get_3d_image_sf":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_3d_image_sf_as_string; // Get the length correct void get_3d_image_sf_as_string(int element_number, char **s, int *slen, int elsize, int elsign, int ndimfast, int ndimmid, int ndimslow){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) { cbf_failnez (cbf_get_3d_image_sf(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, elsign, (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimmid*ndimslow; *s = (char *) array; } ""","get_3d_image_sf_as_string",["int element_number", "int elsize", "int elsign", "int ndimslow", "int ndimmid", "int ndimfast"],["(Binary)String"] ], "cbf_get_real_3d_image":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_real_3d_image_as_string; // Get the length correct void get_real_3d_image_as_string(int element_number, char **s, int *slen, int elsize, int ndimslow, int ndimmid, int ndimfast){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) { cbf_failnez (cbf_get_real_3d_image(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimmid*ndimslow; *s = (char *) array; } ""","get_real_3d_image_as_string",["int element_number", "int elsize", "int ndimslow", "int ndimmid", "int ndimfast"],["(Binary)String"] ], "cbf_get_real_3d_image_fs":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_real_3d_image_fs_as_string; // Get the length correct void get_real_3d_image_fs_as_string(int element_number, char **s, int *slen, int elsize, int ndimfast, int ndimmid, int ndimslow){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) { cbf_failnez (cbf_get_real_3d_image_fs(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, (size_t) ndimfast, (size_t)ndimmid, (size_t)ndimslow)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimmid*ndimslow; *s = (char *) array; } ""","get_real_3d_image_fs_as_string",["int element_number", "int elsize", "int ndimfast", "int ndimmid", "int ndimslow"],["(Binary)String"] ], "cbf_get_real_3d_image_sf":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_real_3d_image_sf_as_string; // Get the length correct void get_real_3d_image_sf_as_string(int element_number, char **s, int *slen, int elsize, int ndimslow, int ndimmid, int ndimfast){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) { cbf_failnez (cbf_get_real_3d_image_sf(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimmid*ndimslow; *s = (char *) array; } ""","get_real_3d_image_sf_as_string",["int element_number", "int elsize", "int ndimslow", "int ndimmid", "int ndimfast"],["(Binary)String"] ], "cbf_get_realarray":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_realarray_as_string; // Get the length correct void get_realarray_as_string(char **s, int *slen){ int binary_id; size_t elements, elements_read, elsize; unsigned int compression; void * array; *slen = 0; /* Initialise in case of problems */ cbf_failnez(cbf_get_realarrayparameters(self, &compression, &binary_id, &elsize, &elements)); if ((array=malloc(elsize*elements))) { /* cbf_failnez (cbf_select_column(cbf,colnum)) */ cbf_failnez (cbf_get_realarray(self, &binary_id, (void *)array, elsize, elements, &elements_read)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*elements; *s = (char *) array; } ""","get_realarray_as_string",[],["(Binary)String"] ], "cbf_set_integerarray":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_integerarray; void set_integerarray(unsigned int compression, int binary_id, char *data, int len, int elsize, int elsigned, int elements){ /* safety check on args */ size_t els, ele; void *array; if(len == elsize*elements){ array = data; els = elsize; ele = elements; cbf_failnez(cbf_set_integerarray (self, compression, binary_id, (void *) data, (size_t) elsize, elsigned, (size_t) elements)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_integerarray", [ "int compression", "int binary_id","(binary) String data", "int elsize", "int elsigned","int elements"],[]], "cbf_set_integerarray_wdims":[""" /* CBFlib must NOT modify the data string nor the byteorder string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_integerarray_wdims; %apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_integerarray_wdims; void set_integerarray_wdims(unsigned int compression, int binary_id, char *data, int len, int elsize, int elsigned, int elements, char *bo, int bolen, int dimfast, int dimmid, int dimslow, int padding){ /* safety check on args */ size_t els, ele; void *array; char byteorder[15]; if(len == elsize*elements && elements==dimfast*dimmid*dimslow){ array = data; els = elsize; ele = elements; strncpy(byteorder,bo,bolen<15?bolen:14); byteorder[bolen<15?14:bolen] = 0; cbf_failnez(cbf_set_integerarray_wdims (self, compression, binary_id, (void *) data, (size_t) elsize, elsigned, (size_t) elements, (const char *)byteorder, (size_t)dimfast, (size_t)dimmid, (size_t)dimslow, (size_t)padding)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_integerarray_wdims", [ "int compression", "int binary_id","(binary) String data", "int elsize","int elements", "String byteorder", "int dimfast", "int dimmid", "int dimslow", "int padding"],[]], "cbf_set_integerarray_wdims_sf":[""" /* CBFlib must NOT modify the data string nor the byteorder string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_integerarray_wdims_sf; %apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_integerarray_wdims_sf; void set_integerarray_wdims_sf(unsigned int compression, int binary_id, char *data, int len, int elsize, int elsigned, int elements, char *bo, int bolen, int dimslow, int dimmid, int dimfast, int padding){ /* safety check on args */ size_t els, ele; void *array; char byteorder[15]; if(len == elsize*elements && elements==dimfast*dimmid*dimslow){ array = data; els = elsize; ele = elements; strncpy(byteorder,bo,bolen<15?bolen:14); byteorder[bolen<15?14:bolen] = 0; cbf_failnez(cbf_set_integerarray_wdims_sf (self, compression, binary_id, (void *) data, (size_t) elsize, elsigned, (size_t) elements, (const char *)byteorder, (size_t)dimslow, (size_t)dimmid, (size_t)dimfast, (size_t)padding)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_integerarray_wdims_sf", [ "int compression", "int binary_id","(binary) String data", "int elsize","int elements", "String byteorder", "int dimslow", "int dimmid", "int dimfast", "int padding"],[]], "cbf_set_integerarray_wdims_fs":[""" /* CBFlib must NOT modify the data string nor the byteorder string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_integerarray_wdims_fs; %apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_integerarray_wdims_fs; void set_integerarray_wdims_fs(unsigned int compression, int binary_id, char *data, int len, int elsize, int elsigned, int elements, char *bo, int bolen, int dimfast, int dimmid, int dimslow, int padding){ /* safety check on args */ size_t els, ele; void *array; char byteorder[15]; if(len == elsize*elements && elements==dimfast*dimmid*dimslow){ array = data; els = elsize; ele = elements; strncpy(byteorder,bo,bolen<15?bolen:14); byteorder[bolen<15?14:bolen] = 0; cbf_failnez(cbf_set_integerarray_wdims_fs (self, compression, binary_id, (void *) data, (size_t) elsize, elsigned, (size_t) elements, (const char *)byteorder, (size_t)dimfast, (size_t)dimmid, (size_t)dimslow, (size_t)padding)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_integerarray_wdims_fs", [ "int compression", "int binary_id","(binary) String data", "int elsize","int elements", "String byteorder", "int dimfast", "int dimmid", "int dimslow", "int padding"],[]], "cbf_set_realarray":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_realarray; void set_realarray(unsigned int compression, int binary_id, char *data, int len, int elsize, int elements){ /* safety check on args */ size_t els, ele; void *array; if(len == elsize*elements){ array = data; els = elsize; ele = elements; cbf_failnez(cbf_set_realarray (self, compression, binary_id, (void *) data, (size_t) elsize, (size_t) elements)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_realarray", [ "int compression", "int binary_id","(binary) String data", "int elsize","int elements"],[]], "cbf_set_realarray_wdims":[""" /* CBFlib must NOT modify the data string nor the byteorder string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_realarray_wdims; %apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_realarray_wdims; void set_realarray_wdims(unsigned int compression, int binary_id, char *data, int len, int elsize, int elements, char *bo, int bolen, int dimfast, int dimmid, int dimslow, int padding){ /* safety check on args */ size_t els, ele; void *array; char byteorder[15]; if(len == elsize*elements && elements==dimfast*dimmid*dimslow){ array = data; els = elsize; ele = elements; strncpy(byteorder,bo,bolen<15?bolen:14); byteorder[bolen<15?14:bolen] = 0; cbf_failnez(cbf_set_realarray_wdims (self, compression, binary_id, (void *) data, (size_t) elsize, (size_t) elements, (const char *)byteorder, (size_t)dimfast, (size_t)dimmid, (size_t)dimslow, (size_t)padding)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_realarray_wdims", [ "int compression", "int binary_id","(binary) String data", "int elsize","int elements", "String byteorder", "int dimfast", "int dimmid", "int dimslow", "int padding"],[]], "cbf_set_realarray_wdims_sf":[""" /* CBFlib must NOT modify the data string nor the byteorder string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_realarray_wdims_sf; %apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_realarray_wdims_sf; void set_realarray_wdims_sf(unsigned int compression, int binary_id, char *data, int len, int elsize, int elements, char *bo, int bolen, int dimslow, int dimmid, int dimfast, int padding){ /* safety check on args */ size_t els, ele; void *array; char byteorder[15]; if(len == elsize*elements && elements==dimfast*dimmid*dimslow){ array = data; els = elsize; ele = elements; strncpy(byteorder,bo,bolen<15?bolen:14); byteorder[bolen<15?14:bolen] = 0; cbf_failnez(cbf_set_realarray_wdims_sf (self, compression, binary_id, (void *) data, (size_t) elsize, (size_t) elements, (const char *)byteorder, (size_t) dimslow, (size_t) dimmid, (size_t) dimfast, (size_t)padding)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_realarray_wdims_sf", [ "int compression", "int binary_id","(binary) String data", "int elsize","int elements", "String byteorder", "int dimslow", "int dimmid", "int dimfast", "int padding"],[]], "cbf_set_realarray_wdims_fs":[""" /* CBFlib must NOT modify the data string nor the byteorder string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_realarray_wdims_fs; %apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_realarray_wdims_fs; void set_realarray_wdims_fs(unsigned int compression, int binary_id, char *data, int len, int elsize, int elements, char *bo, int bolen, int dimfast, int dimmid, int dimslow, int padding){ /* safety check on args */ size_t els, ele; void *array; char byteorder[15]; if(len == elsize*elements && elements==dimfast*dimmid*dimslow){ array = data; els = elsize; ele = elements; strncpy(byteorder,bo,bolen<15?bolen:14); byteorder[bolen<15?14:bolen] = 0; cbf_failnez(cbf_set_realarray_wdims_fs (self, compression, binary_id, (void *) data, (size_t) elsize, (size_t) elements, (const char *)byteorder, (size_t) dimfast, (size_t) dimmid, (size_t) dimslow, (size_t)padding)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_realarray_wdims_fs", [ "int compression", "int binary_id","(binary) String data", "int elsize","int elements", "String byteorder", "int dimfast", "int dimmid", "int dimslow", "int padding"],[]], "cbf_set_image":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_image; void set_image(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int elsign, int ndimslow, int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_image (self, reserved, element_number, compression, (void *) data, (size_t) elsize, elsign, (size_t) ndimslow, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_image", [ "int element_number","int compression","(binary) String data", "int elsize", "int elsign", "int dimslow", "int dimfast"],[]], "cbf_set_image_fs":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_image; void set_image_fs(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int elsign, int ndimfast, int ndimslow){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_image (self, reserved, element_number, compression, (void *) data, (size_t) elsize, elsign, (size_t) ndimfast, (size_t)ndimslow)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_image_fs", [ "int element_number","int compression","(binary) String data", "int elsize", "int elsign", "int dimfast", "int dimslow"],[]], "cbf_set_image_sf":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_image_sf; void set_image_sf(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int elsign, int ndimslow, int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_image_sf (self, reserved, element_number, compression, (void *) data, (size_t) elsize, elsign, (size_t) ndimslow, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_image_sf", [ "int element_number","int compression","(binary) String data", "int elsize", "int elsign", "int dimslow", "int dimfast"],[]], "cbf_set_real_image":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_real_image; void set_real_image(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int ndimslow, int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_real_image (self, reserved, element_number, compression, (void *) data, (size_t) elsize, (size_t) ndimslow, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_real_image", [ "int element_number","int compression","(binary) String data", "int elsize", "int dimslow", "int dimfast"],[]], "cbf_set_real_image_fs":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_real_image; void set_real_image_fs(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int ndimfast, int ndimslow){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_real_image_fs (self, reserved, element_number, compression, (void *) data, (size_t) elsize, (size_t) ndimfast, (size_t)ndimslow)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_real_image_fs", [ "int element_number","int compression","(binary) String data", "int elsize", "int dimfast", "int dimslow"],[]], "cbf_set_real_image_sf":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_real_image_sf; void set_real_image_sf(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int ndimslow, int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_real_image_sf (self, reserved, element_number, compression, (void *) data, (size_t) elsize, (size_t) ndimslow, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_real_image_sf", [ "int element_number","int compression","(binary) String data", "int elsize", "int dimslow", "int dimfast"],[]], "cbf_set_3d_image":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_3d_image; void set_3d_image(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int elsign, int ndimslow, int ndimmid, int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimmid*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_3d_image (self, reserved, element_number, compression, (void *) data, (size_t) elsize, elsign, (size_t) ndimslow, (size_t) ndimmid, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_3d_image", [ "int element_number","int compression","(binary) String data", "int elsize", "int elsign", "int dimslow", "int dimmid", "int dimfast"],[]], "cbf_set_3d_image_fs":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_3d_image; void set_3d_image_fs(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int elsign, int ndimfast, int ndimmid, int ndimslow){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimmid*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_3d_image_fs (self, reserved, element_number, compression, (void *) data, (size_t) elsize, elsign, (size_t) ndimfast, (size_t) ndimmid, (size_t)ndimslow)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_3d_image_fs", [ "int element_number","int compression","(binary) String data", "int elsize", "int elsign", "int dimfast", "int dimmid", "int dimslow"],[]], "cbf_set_3d_image_sf":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_3d_image; void set_3d_image_sf(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int elsign, int ndimslow, int ndimmid, int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimmid*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_3d_image_sf (self, reserved, element_number, compression, (void *) data, (size_t) elsize, elsign, (size_t) ndimslow, (size_t) ndimmid, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_3d_image_sf", [ "int element_number","int compression","(binary) String data", "int elsize", "int elsign", "int dimslow", "int dimmid", "int dimfast"],[]], "cbf_set_real_3d_image":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_real_3d_image_sf; void set_real_3d_image(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int ndimslow, int ndimmid, int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimmid*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_real_3d_image (self, reserved, element_number, compression, (void *) data, (size_t) elsize, (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_real_3d_image", [ "int element_number","int compression","(binary) String data", "int elsize", "int dimslow", "int dimmid", "int dimfast"],[]], "cbf_set_real_3d_image_fs":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_real_3d_image_fs; void set_real_3d_image_fs(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int ndimfast, int ndimmid, int ndimslow){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimmid*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_real_3d_image_fs (self, reserved, element_number, compression, (void *) data, (size_t) elsize, (size_t) ndimfast, (size_t)ndimmid, (size_t)ndimslow)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_real_3d_image_fs", [ "int element_number","int compression","(binary) String data", "int elsize", "int dimfast", "int dimmid", "int dimslow"],[]], "cbf_set_real_3d_image_sf":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_real_3d_image_sf; void set_real_3d_image_sf(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int ndimslow, int ndimmid, int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimmid*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_real_3d_image_sf (self, reserved, element_number, compression, (void *) data, (size_t) elsize, (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_real_3d_image_sf", [ "int element_number","int compression","(binary) String data", "int elsize", "int dimslow", "int dimmid", "int dimfast"],[]], "cbf_get_image_size": [""" %apply int *OUTPUT {int *ndimslow, int *ndimfast} get_image_size; void get_image_size(unsigned int element_number, int *ndimslow, int *ndimfast){ unsigned int reserved; size_t inslow, infast; reserved = 0; cbf_failnez(cbf_get_image_size(self,reserved,element_number,&inslow,&infast)); *ndimslow = (int)inslow; *ndimfast = (int)infast; } ""","get_image_size",["Integer element_number"],["size_t ndim1","size_t ndim2"]], "cbf_get_image_size_fs": [""" %apply int *OUTPUT {int *ndimfast, int *ndimslow} get_image_size_fs; void get_image_size_fs(unsigned int element_number, int *ndimfast, int *ndimslow){ unsigned int reserved; size_t infast, inslow; reserved = 0; cbf_failnez(cbf_get_image_size_fs(self,reserved,element_number,&infast,&inslow)); *ndimfast = (int)infast; /* FIXME - is that how to convert? */ *ndimslow = (int)inslow; } ""","get_image_size_fs",["Integer element_number"],["size_t ndimfast","size_t ndimslow"]], "cbf_get_image_size_sf": [""" %apply int *OUTPUT {int *ndimslow, int *ndimfast} get_image_size_sf; void get_image_size_sf(unsigned int element_number, int *ndimslow, int *ndimfast){ unsigned int reserved; size_t inslow, infast; reserved = 0; cbf_failnez(cbf_get_image_size(self,reserved,element_number,&inslow,&infast)); *ndimslow = (int)inslow; *ndimfast = (int)infast; } ""","get_image_size_sf",["Integer element_number"],["size_t ndimslow","size_t ndimfast"]], "cbf_get_3d_image_size": [""" %apply int *OUTPUT {int *ndimslow, int *ndimmid, int *ndimfast} get_3d_image_size; void get_3d_image_size(unsigned int element_number, int *ndimslow, int *ndimmid, int *ndimfast){ unsigned int reserved; size_t inslow, inmid, infast; reserved = 0; cbf_failnez(cbf_get_3d_image_size(self,reserved,element_number,&inslow,&inmid,&infast)); *ndimslow = (int)inslow; /* FIXME - is that how to convert? */ *ndimmid = (int)inmid; *ndimfast = (int)infast; } ""","get_3d_image_size",["Integer element_number"],["size_t ndimslow","size_t ndimmid","size_t ndimfast"]], "cbf_get_3d_image_size_fs": [""" %apply int *OUTPUT {int *ndimslow, int *ndimmid, int *ndimfast} get_3d_image_size; void get_3d_image_size_fs(unsigned int element_number, int *ndimfast, int *ndimmid, int *ndimslow){ unsigned int reserved; size_t inslow, inmid, infast; reserved = 0; cbf_failnez(cbf_get_3d_image_size_fs(self,reserved,element_number,&infast,&inmid,&inslow)); *ndimslow = (int)inslow; /* FIXME - is that how to convert? */ *ndimmid = (int)inmid; *ndimfast = (int)infast; } ""","get_3d_image_size",["Integer element_number"],["size_t ndimfast","size_t ndimmid","size_t ndimslow"]], "cbf_get_3d_image_size_sf": [""" %apply int *OUTPUT {int *ndimslow, int *ndimmid, int *ndimfast} get_3d_image_size_sf; void get_3d_image_size_sf(unsigned int element_number, int *ndimslow, int *ndimmid, int *ndimfast){ unsigned int reserved; size_t inslow, inmid, infast; reserved = 0; cbf_failnez(cbf_get_3d_image_size_sf(self,reserved,element_number,&inslow,&inmid,&infast)); *ndimslow = (int)inslow; /* FIXME - is that how to convert? */ *ndimmid = (int)inmid; *ndimfast = (int)infast; } ""","get_3d_image_size_sf",["Integer element_number"],["size_t ndimslow","size_t ndimmid","size_t ndimfast"]], "cbf_get_pixel_size" : [""" %apply double *OUTPUT {double *psize} get_pixel_size; void get_pixel_size(unsigned int element_number, unsigned int axis_number, double *psize){ cbf_failnez(cbf_get_pixel_size(self, element_number, axis_number, psize)); } ""","get_pixel_size",["Int element_number","Int axis_number"], ["Float pixel_size"]] , "cbf_get_pixel_size_fs" : [""" %apply double *OUTPUT {double *psize} get_pixel_size; void get_pixel_size_fs(unsigned int element_number, unsigned int axis_number, double *psize){ cbf_failnez(cbf_get_pixel_size_fs(self, element_number, axis_number, psize)); } ""","get_pixel_size_fs",["Int element_number","Int axis_number"], ["Float pixel_size"]] , "cbf_get_pixel_size_sf" : [""" %apply double *OUTPUT {double *psize} get_pixel_size; void get_pixel_size_sf(unsigned int element_number, unsigned int axis_number, double *psize){ cbf_failnez(cbf_get_pixel_size_sf(self, element_number, axis_number, psize)); } ""","get_pixel_size_sf",["Int element_number","Int axis_number"], ["Float pixel_size"]] , "cbf_set_pixel_size":[""" void set_pixel_size (unsigned int element_number, unsigned int axis_number, double psize){ cbf_failnez(cbf_set_pixel_size(self, element_number, axis_number, psize)); } ""","set_pixel_size", ["Int element_number","Int axis_number","Float pixel size"],[]], "cbf_set_pixel_size_fs":[""" void set_pixel_size_fs (unsigned int element_number, unsigned int axis_number, double psize){ cbf_failnez(cbf_set_pixel_size_fs(self, element_number, axis_number, psize)); } ""","set_pixel_size_fs", ["Int element_number","Int axis_number","Float pixel size"],[]], "cbf_set_pixel_size_sf":[""" void set_pixel_size_sf (unsigned int element_number, unsigned int axis_number, double psize){ cbf_failnez(cbf_set_pixel_size_sf(self, element_number, axis_number, psize)); } ""","set_pixel_size_sf", ["Int element_number","Int axis_number","Float pixel size"],[]], "cbf_write_file" : [""" void write_file(const char* filename, int ciforcbf, int headers, int encoding){ FILE *stream; int readable; /* Make the file non-0 to make CBFlib close the file */ readable = 1; if ( ! ( stream = fopen (filename, "w+b")) ){ cbf_failnez(CBF_FILEOPEN); } else{ cbf_failnez(cbf_write_file(self, stream, readable, ciforcbf, headers, encoding)); } } ""","write_file",["String filename","Integer ciforcbf","Integer Headers", "Integer encoding"],[]], "cbf_write_widefile" : [""" void write_widefile(const char* filename, int ciforcbf, int headers, int encoding){ FILE *stream; int readable; /* Make the file non-0 to make CBFlib close the file */ readable = 1; if ( ! ( stream = fopen (filename, "w+b")) ){ cbf_failnez(CBF_FILEOPEN); } else{ cbf_failnez(cbf_write_widefile(self, stream, readable, ciforcbf, headers, encoding)); } } ""","write_widefile",["String filename","Integer ciforcbf","Integer Headers", "Integer encoding"],[]], "cbf_read_template":[""" void read_template(char* filename){ /* CBFlib needs a stream that will remain open hence DO NOT open from python */ FILE *stream; if ( ! ( stream = fopen (filename, "rb")) ){ cbf_failnez(CBF_FILEOPEN); } else{ cbf_failnez(cbf_read_template (self, stream)); } } ""","read_template",["String filename"],[]], "cbf_read_file" : [""" void read_file(char* filename, int headers){ /* CBFlib needs a stream that will remain open hence DO NOT open from python */ FILE *stream; if ( ! ( stream = fopen (filename, "rb")) ){ cbf_failnez(CBF_FILEOPEN); } else{ cbf_failnez(cbf_read_file(self, stream, headers)); } } ""","read_file",["String filename","Integer headers"],[]], "cbf_read_widefile" : [""" void read_widefile(char* filename, int headers){ /* CBFlib needs a stream that will remain open hence DO NOT open from python */ FILE *stream; if ( ! ( stream = fopen (filename, "rb")) ){ cbf_failnez(CBF_FILEOPEN); } else{ cbf_failnez(cbf_read_widefile(self, stream, headers)); } } ""","read_widefile",["String filename","Integer headers"],[]], "cbf_set_doublevalue":[""" void set_doublevalue(const char *format, double number){ cbf_failnez(cbf_set_doublevalue(self,format,number));} ""","set_doublevalue",["String format","Float number"],[]], "cbf_require_integervalue":[""" %apply int *OUTPUT {int *number} require_integervalue; void require_integervalue(int *number, int thedefault){ cbf_failnez(cbf_require_integervalue(self,number,thedefault)); } ""","require_integervalue", ["Int thedefault"],["Int number"]], "cbf_require_doublevalue":[""" %apply double *OUTPUT {double *number} require_doublevalue; void require_doublevalue(double *number, double defaultvalue){ cbf_failnez(cbf_require_doublevalue(self,number,defaultvalue)); } ""","require_doublevalue",["Float Default"],["Float Number"]], "cbf_require_column_value":[""" const char* require_column_value(const char *columnname, const char *defaultvalue){ const char * result; cbf_failnez(cbf_require_column_value(self,columnname, &result,defaultvalue)); return result; } ""","require_column_value", ["String columnnanme","String Default"],["String Name"]], "cbf_require_column_doublevalue":[""" %apply double *OUTPUT { double *number} require_column_doublevalue; void require_column_doublevalue(const char *columnname, double * number, const double defaultvalue){ cbf_failnez(cbf_require_column_doublevalue(self, columnname,number,defaultvalue)); } ""","require_column_doublevalue",["String columnname","Float Value"], ["Float defaultvalue"]], "cbf_require_column_integervalue":[""" %apply int *OUTPUT {int *number} require_column_integervalue; void require_column_integervalue(const char *columnname, int *number, const int defaultvalue){ cbf_failnez(cbf_require_column_integervalue(self, columnname, number,defaultvalue)); } ""","require_column_integervalue",["String Columnvalue","Int default"], ["Int Value"]], "cbf_require_value" : [""" const char* require_value(const char* defaultvalue){ const char * result; cbf_failnez(cbf_require_value(self, &result, defaultvalue)); return result; } ""","require_value",["String defaultvalue"],['String Value']], "cbf_require_diffrn_id":[""" const char* require_diffrn_id(const char* defaultid){ const char * id; cbf_failnez(cbf_require_diffrn_id(self,&id,defaultid)); return id; } ""","require_diffrn_id", ["String Default_id"],["String diffrn_id"]], "cbf_get_polarization":[""" /* Returns a pair of double values */ %apply double *OUTPUT { double *in1, double *in2 }; void get_polarization(double *in1,double *in2){ cbf_failnez(cbf_get_polarization (self, in1, in2)); } ""","get_polarization",[], ["float polarizn_source_ratio","float polarizn_source_norm"]], "cbf_set_polarization":[""" void set_polarization (double polarizn_source_ratio, double polarizn_source_norm){ cbf_failnez(cbf_set_polarization(self, polarizn_source_ratio, polarizn_source_norm)); } ""","set_polarization", ["Float polarizn_source_ratio","Float polarizn_source_norm"],[]], "cbf_get_divergence":[""" %apply double *OUTPUT {double *div_x_source, double *div_y_source, double *div_x_y_source } get_divergence; void get_divergence(double *div_x_source, double *div_y_source, double *div_x_y_source){ cbf_failnez(cbf_get_divergence(self, div_x_source, div_y_source, div_x_y_source)); } ""","get_divergence",[], ["Float div_x_source","Float div_y_source","Float div_x_y_source"]], "cbf_set_divergence":[""" void set_divergence ( double div_x_source, double div_y_source, double div_x_y_source){ cbf_failnez(cbf_set_divergence (self, div_x_source, div_y_source,div_x_y_source)); } ""","set_divergence", ["Float div_x_source","Float div_y_source","Float div_x_y_source"],[]], "cbf_get_gain":[""" %apply double *OUTPUT {double *gain, double *gain_esd} get_gain; void get_gain (unsigned int element_number, double *gain, double *gain_esd){ cbf_failnez(cbf_get_gain (self, element_number, gain, gain_esd)); } ""","get_gain", [],["Float gain", "Float gain_esd"]], "cbf_set_gain":[""" void set_gain (unsigned int element_number, double gain, double gain_esd){ cbf_failnez(cbf_set_gain (self, element_number, gain, gain_esd)); } ""","set_gain",["Float gain", "Float gain_esd"],[]], "cbf_get_element_id":[""" const char * get_element_id(unsigned int element_number){ const char * result; cbf_failnez(cbf_get_element_id (self, element_number, &result)); return result; } ""","get_element_id", ["Integer element_number"],["String"]], "cbf_set_axis_setting":[""" void set_axis_setting(const char *axis_id, double start, double increment){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_set_axis_setting(self,reserved, axis_id,start,increment)); } ""","set_axis_setting",["String axis_id", "Float start", "Float increment"], []], "cbf_get_axis_setting":[""" %apply double *OUTPUT {double *start, double *increment} get_axis_setting; void get_axis_setting(const char *axis_id, double *start, double *increment){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_get_axis_setting(self,reserved,axis_id, start,increment)); } ""","get_axis_setting",["String axis_id"],["Float start", "Float increment"],], "cbf_get_datestamp":[""" %apply int *OUTPUT {int *year, int *month, int *day, int *hour, int *minute, double *second, int *timezone} get_datestamp; void get_datestamp(int *year, int *month, int *day, int *hour, int *minute, double *second, int *timezone){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_get_datestamp(self,reserved, year,month,day,hour,minute,second,timezone)); } ""","get_datestamp",[],["int year", "int month", "int day", "int hour", "int minute", "double second", "int timezone"]], "cbf_set_datestamp":[""" void set_datestamp(int year, int month, int day, int hour, int minute, double second, int timezone, double precision){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_set_datestamp(self,reserved, year,month,day,hour,minute,second,timezone,precision)); } ""","set_datestamp",["int year", "int month", "int day", "int hour", "int minute", "double second", "int timezone","Float precision"],[]], "cbf_get_timestamp":[""" %apply double *OUTPUT {double *time} get_timestamp; %apply int *OUTPUT {int *timezone} get_timestamp; void get_timestamp(double *time, int *timezone){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_get_timestamp(self,reserved,time,timezone)); } ""","get_timestamp",[],["Float time","Integer timezone"]], "cbf_set_timestamp":[""" void set_timestamp(double time, int timezone, double precision){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_set_timestamp(self,reserved,time,timezone,precision)); } ""","set_timestamp",["Float time","Integer timezone","Float precision"],[]], "cbf_set_current_timestamp":[""" void set_current_timestamp(int timezone){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_set_current_timestamp(self,reserved,timezone)); } ""","set_current_timestamp",["Integer timezone"],[]], "cbf_get_overload":[""" %apply double *OUTPUT {double *overload} get_overload; void get_overload(unsigned int element_number, double *overload){ cbf_failnez(cbf_get_overload(self,element_number,overload)); } ""","get_overload",["Integer element_number"],["Float overload"]], "cbf_set_overload":[""" void set_overload(unsigned int element_number, double overload){ cbf_failnez(cbf_set_overload(self,element_number,overload)); } ""","set_overload",["Integer element_number","Float overload"],[]], "cbf_set_integration_time":[""" void set_integration_time(double time){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_set_integration_time(self,reserved,time)); } ""","set_integration_time",["Float time"],[]], "cbf_get_integration_time":[""" %apply double *OUTPUT {double *time} get_integration_time; void get_integration_time( double *time ){ unsigned int reserved; double tim; reserved = 0; cbf_failnez(cbf_get_integration_time(self,reserved,&tim)); *time = tim; } ""","get_integration_time",[],["Float time"]], "cbf_get_orientation_matrix":[""" %apply double *OUTPUT {double *m0,double *m1,double *m2, double *m3,double *m4, double *m5,double *m6, double *m7,double *m8 } get_orientation_matrix; void get_orientation_matrix( double *m0,double *m1, double *m2,double *m3,double *m4,double *m5,double *m6, double *m7,double *m8){ double m[9]; cbf_failnez(cbf_get_orientation_matrix(self,m)); *m0 = m[0]; *m1=m[1] ; *m2=m[2] ; *m3 = m[3]; *m4=m[4] ; *m5=m[5] ; *m6 = m[6]; *m7=m[7] ; *m8=m[8] ; } ""","get_orientation_matrix", [],[ "Float matrix_%d"%(ind) for ind in range(9) ]], "cbf_get_unit_cell":[""" %apply double *OUTPUT {double *a, double *b, double *c, double *alpha, double *beta, double *gamma} get_unit_cell; void get_unit_cell(double *a, double *b, double *c, double *alpha, double *beta, double *gamma) { double cell[6]; cbf_failnez(cbf_get_unit_cell(self,cell,NULL)); *a = cell[0]; *b = cell[1]; *c = cell[2]; *alpha = cell[3]; *beta = cell[4]; *gamma = cell[5]; } ""","get_unit_cell", [],["Float a", "Float b", "Float c", "Float alpha", "Float beta", "Float gamma" ] ], "cbf_get_unit_cell_esd":[""" %apply double *OUTPUT {double *a_esd, double *b_esd, double *c_esd, double *alpha_esd, double *beta_esd, double *gamma_esd} get_unit_cell_esd; void get_unit_cell_esd(double *a_esd, double *b_esd, double *c_esd, double *alpha_esd, double *beta_esd, double *gamma_esd) { double cell_esd[6]; cbf_failnez(cbf_get_unit_cell(self,NULL,cell_esd)); *a_esd = cell_esd[0]; *b_esd = cell_esd[1]; *c_esd = cell_esd[2]; *alpha_esd = cell_esd[3]; *beta_esd = cell_esd[4]; *gamma_esd = cell_esd[5]; } ""","get_unit_cell", [],["doubleArray cell"] ], "cbf_get_reciprocal_cell":[""" %apply double *OUTPUT {double *astar, double *bstar, double *cstar, double *alphastar, double *betastar, double *gammastar} get_reciprocal_cell; void get_reciprocal_cell(double *astar, double *bstar, double *cstar, double *alphastar, double *betastar, double *gammastar) { double rcell[6]; cbf_failnez(cbf_get_reciprocal_cell(self,rcell,NULL)); *astar = rcell[0]; *bstar = rcell[1]; *cstar = rcell[2]; *alphastar = rcell[3]; *betastar = rcell[4]; *gammastar = rcell[5]; } ""","get_reciprocal_cell", [],["Float astar", "Float bstar", "Float cstar", "Float alphastar", "Float betastar", "Float gammastar"] ], "cbf_get_reciprocal_cell_esd":[""" %apply double *OUTPUT {double *a_esd, double *b_esd, double *c_esd, double *alpha_esd, double *beta_esd, double *gamma_esd} get_reciprocal_cell_esd; void get_reciprocal_cell_esd(double *a_esd, double *b_esd, double *c_esd, double *alpha_esd, double *beta_esd, double *gamma_esd) { double cell_esd[6]; cbf_failnez(cbf_get_reciprocal_cell(self,NULL,cell_esd)); *a_esd = cell_esd[0]; *b_esd = cell_esd[1]; *c_esd = cell_esd[2]; *alpha_esd = cell_esd[3]; *beta_esd = cell_esd[4]; *gamma_esd = cell_esd[5]; } ""","get_reciprocal_cell", [],["doubleArray cell"] ], "cbf_set_unit_cell":[""" void set_unit_cell(double cell[6]) { cbf_failnez(cbf_set_unit_cell(self,cell,NULL)); } ""","set_unit_cell", ["double cell[6]"],[] ], "cbf_set_unit_cell_esd":[""" void set_unit_cell_esd(double cell_esd[6]) { cbf_failnez(cbf_set_unit_cell(self,NULL,cell_esd)); } ""","set_unit_cell_esd", ["double cell_esd[6]"],[] ], "cbf_set_reciprocal_cell":[""" void set_reciprocal_cell(double cell[6]) { cbf_failnez(cbf_set_reciprocal_cell(self,cell,NULL)); } ""","set_reciprocal_cell", ["double cell[6]"],[] ], "cbf_set_reciprocal_cell_esd":[""" void set_reciprocal_cell_esd(double cell_esd[6]) { cbf_failnez(cbf_set_reciprocal_cell(self,NULL,cell_esd)); } ""","set_reciprocal_cell_esd", ["double cell_esd[6]"],[] ], "cbf_set_tag_category":[""" void set_tag_category(const char *tagname, const char* categoryname_in){ cbf_failnez(cbf_set_tag_category(self,tagname, categoryname_in)); } ""","set_tag_category",["String tagname","String categoryname_in"],[] ], "cbf_find_tag_category":[""" const char * find_tag_category(const char *tagname){ const char * result; cbf_failnez(cbf_find_tag_category(self,tagname, &result)); return result; } ""","find_tag_category",["String tagname"],["String categoryname"] ], "cbf_require_tag_root":[""" const char* require_tag_root(const char* tagname){ const char* result; cbf_failnez(cbf_require_tag_root(self,tagname,&result)); return result; } ""","require_tag_root",["String tagname"],["String tagroot"]], "cbf_find_tag_root":[""" const char * find_tag_root(const char* tagname){ const char* result; cbf_failnez(cbf_find_tag_root(self,tagname,&result)); return result; } ""","find_tag_root",["String tagname"],["String tagroot"]], "cbf_set_tag_root":[""" void set_tag_root(const char* tagname, const char* tagroot_in){ cbf_failnez(cbf_set_tag_root(self,tagname,tagroot_in)); } ""","set_tag_root",["String tagname","String tagroot_in"],[]], "cbf_set_category_root":[""" void set_category_root(const char* categoryname, const char* categoryroot){ cbf_failnez(cbf_set_category_root(self,categoryname,categoryroot)); } ""","set_category_root",["String categoryname","String categoryroot"],[]], "cbf_find_category_root":[""" const char* find_category_root(const char* categoryname){ const char * result; cbf_failnez(cbf_find_category_root(self,categoryname,&result)); return result; } ""","find_category_root",["String categoryname"],["String categoryroot"]], "cbf_require_category_root":[""" const char* require_category_root (const char* categoryname){ const char* result; cbf_failnez(cbf_require_category_root(self,categoryname, &result)); return result; } ""","cbf_require_category_root",["String Categoryname"],["String categoryroot"]], "cbf_set_orientation_matrix":[""" void set_orientation_matrix( double m0,double m1, double m2,double m3,double m4,double m5,double m6, double m7,double m8){ double m[9]; m[0] = m0; m[1]=m1 ; m[2]=m2 ; m[3] = m3; m[4]=m4 ; m[5]=m5 ; m[6] = m6; m[7]=m7 ; m[8]=m8 ; cbf_failnez(cbf_get_orientation_matrix(self,m)); } ""","set_orientation_matrix", [ "Float matrix_%d"%(ind) for ind in range(9) ] ,[]], "cbf_set_bin_sizes":[""" void set_bin_sizes( int element_number, double slowbinsize_in, double fastbinsize_in) { cbf_failnez(cbf_set_bin_sizes(self,element_number,slowbinsize_in,fastbinsize_in)); } ""","set_bin_sizes",["Integer element_number","Float slowbinsize_in","Float fastbinsize_in"],[] ], "cbf_get_bin_sizes":[""" %apply double *OUTPUT {double *slowbinsize,double *fastbinsize}; void get_bin_sizes(int element_number, double *slowbinsize, double *fastbinsize) { cbf_failnez(cbf_get_bin_sizes (self, (unsigned int)element_number, slowbinsize, fastbinsize)); } ""","get_bin_sizes",["Integer element_number"],["Float slowbinsize","Float fastbinsize"] ], # cbfhandle dict functions UNTESTED "cbf_require_dictionary":[""" cbf_handle require_dictionary(){ cbf_handle temp; cbf_failnez(cbf_require_dictionary(self,&temp)); return temp; } ""","require_dictionary",[],["CBFHandle dictionary"]], "cbf_get_dictionary":[""" cbf_handle get_dictionary(){ cbf_handle temp; cbf_failnez(cbf_get_dictionary(self,&temp)); return temp; } ""","get_dictionary",[],["CBFHandle dictionary"]], "cbf_set_dictionary":[""" void set_dictionary(cbf_handle other){ cbf_failnez(cbf_set_dictionary(self,other)); } ""","set_dictionary",["CBFHandle dictionary"],[]], "cbf_convert_dictionary":[""" void convert_dictionary(cbf_handle other){ cbf_failnez(cbf_convert_dictionary(self,other)); } ""","convert_dictionary",["CBFHandle dictionary"],[]], "cbf_construct_detector":[""" cbf_detector construct_detector(unsigned int element_number){ cbf_detector detector; cbf_failnez(cbf_construct_detector(self,&detector,element_number)); return detector; } ""","construct_detector",["Integer element_number"],["pycbf detector object"]], "cbf_construct_reference_detector":[""" cbf_detector construct_reference_detector(unsigned int element_number){ cbf_detector detector; cbf_failnez(cbf_construct_reference_detector(self,&detector,element_number)); return detector; } ""","construct_reference_detector",["Integer element_number"],["pycbf detector object"]], "cbf_require_reference_detector":[""" cbf_detector require_reference_detector(unsigned int element_number){ cbf_detector detector; cbf_failnez(cbf_require_reference_detector(self,&detector,element_number)); return detector; } ""","require_reference_detector",["Integer element_number"],["pycbf detector object"]], # Prelude to the next section of the nuweb doc "cbf_construct_goniometer":[""" cbf_goniometer construct_goniometer(){ cbf_goniometer goniometer; cbf_failnez(cbf_construct_goniometer(self,&goniometer)); return goniometer; } ""","construct_goniometer",[],["pycbf goniometer object"]], } class cbfhandlewrapper: def __init__(self): self.code = """ // Tell SWIG not to make constructor for these objects %nodefault cbf_handle; %nodefault cbf_handle_struct; %nodefault cbf_node; // A couple of blockitem functions return CBF_NODETYPE typedef enum { CBF_UNDEFNODE, /* Undefined */ CBF_LINK, /* Link */ CBF_ROOT, /* Root */ CBF_DATABLOCK, /* Datablock */ CBF_SAVEFRAME, /* Saveframe */ CBF_CATEGORY, /* Category */ CBF_COLUMN /* Column */ } CBF_NODETYPE; // Tell SWIG what the object is, so we can build the class typedef struct { cbf_node *node; int row, search_row; } cbf_handle_struct; typedef cbf_handle_struct *cbf_handle; typedef cbf_handle_struct handle; %feature("autodoc","1"); %extend cbf_handle_struct{ // Tell SWIG to attach functions to the structure cbf_handle_struct(){ // Constructor cbf_handle handle; cbf_failnez(cbf_make_handle(&handle)); return handle; } ~cbf_handle_struct(){ // Destructor cbf_failnez(cbf_free_handle(self)); } """ self.tail = """ }; // End of cbf_handle_struct """ # End of init function def get_code(self): return self.code+self.tail def wrap(self,cfunc,prototype,args,docstring): # print "cfunc: ", cfunc pyfunc = cfunc.replace("cbf_","") # Insert a comment for debugging this script code = "\n/* cfunc %s pyfunc %s \n"%(cfunc,pyfunc) for a in args: code += " arg %s "%(a) code += "*/\n\n" # Make and free handle are done in the header so skip if cfunc.find("cbf_make_handle")>-1 or cfunc.find("cbf_free_handle")>-1: # Constructor and destructor done in headers return if args[0] != "cbf_handle handle": # Must be for cbfhandle print "problem",cfunc,pyfunc,args return if len(args)==1: # Only takes CBFhandle arg code+= docstringwrite(pyfunc,[],[],prototype,docstring) code+= " void %s(void){\n"%(pyfunc) code+= " cbf_failnez(%s(self));}\n"%(cfunc) self.code=self.code+code return # Now case by case rather than writing a proper parser # Special cases ... not_found=0 try: code, pyname, input, output = cbfhandle_specials[cfunc] self.code += docstringwrite(pyname,input,output, prototype,docstring)+ code return except KeyError: not_found = 1 # print "KeyError" except ValueError: print "problem in",cfunc for item in cbfhandle_specials[cfunc]: print "***",item raise if len(args)==2: if args[1].find("const char")>-1 and \ args[1].find("*")>-1 and \ args[1].find("**")==-1 : # 1 input string code += docstringwrite(pyfunc,[],["string"],prototype,docstring) code += " void %s(const char* arg){\n"%(pyfunc) code +=" cbf_failnez(%s(self,arg));}\n"%(cfunc) self.code=self.code+code return if args[1].find("const char")>-1 and \ args[1].find("**")>-1 :# return string code += docstringwrite(pyfunc,["string"],[],prototype,docstring) code += " const char* %s(void){\n"%(pyfunc) code += " const char* result;\n" code += " cbf_failnez(%s(self, &result));\n"%(cfunc) code += " return result;}\n" self.code=self.code+code return if args[1].find("unsigned int")>-1 and args[1].find("*")==-1: # set uint if args[1].find("reserved")>-1: raise Exception("Setting reserved??? %s %s %s"%(pyfunc, cfunc,str(args))) code += docstringwrite(pyfunc,["Integer"],[],prototype,docstring) code +=" void %s(unsigned int arg){\n"%(pyfunc) code +=" cbf_failnez(%s(self,arg));}\n"%(cfunc) self.code=self.code+code return if args[1].find("unsigned int *")>-1 and args[1].find("**")==-1: # output uint if args[1].find("reserved")>-1: raise Exception("Setting reserved??? %s %s %s"%(pyfunc, cfunc,str(args))) code += docstringwrite(pyfunc,[],["Integer"],prototype,docstring) code +=" unsigned int %s(void){\n"%(pyfunc) code +=" unsigned int result;\n" code +=" cbf_failnez(%s(self,&result));\n"%(cfunc) code +=" return result;}\n" self.code=self.code+code return # For the rest attempt to guess if args[1].find("cbf")==-1: # but do not try the goniometer constructor if args[1].find("*")>-1 and args[1].find("cbf")==-1: # pointer used for returning something type = args[1].split(" ")[0] code += docstringwrite(pyfunc,[],[type.replace("*","")], prototype,docstring) code+= " "+type+" "+pyfunc+"(void){\n" code+= " "+type+" result;\n" code+= " cbf_failnez(%s(self,&result));\n"%(cfunc) code+= " return result;}\n" self.code=self.code+code return else: var = args[1].split(" ")[-1] code += docstringwrite(pyfunc,[],[args[1]],prototype,docstring) code+= " void %s(%s){\n"%(pyfunc,args[1]) code +=" cbf_failnez(%s(self,%s));}\n"%(cfunc,var) self.code=self.code+code return if not_found: code+= " void %s(void){\n"%(pyfunc) code +=" cbf_failnez(CBF_NOTIMPLEMENTED);}\n" self.code=self.code+code print "Have not implemented: cbfhandle.%s"%(pyfunc) print " ",cfunc print " args:" for a in args: print " ",a print return cbf_handle_wrapper = cbfhandlewrapper() cbf_goniometer_specials = { "cbf_get_rotation_range":[""" %apply double *OUTPUT {double *start,double *increment}; void get_rotation_range(double *start,double *increment){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_get_rotation_range (self,reserved, start,increment)); } ""","get_rotation_range",[],["Float start","Float increment"]], "cbf_rotate_vector":[""" %apply double *OUTPUT {double *final1, double *final2, double *final3}; void rotate_vector (double ratio, double initial1,double initial2, double initial3, double *final1, double *final2, double *final3){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_rotate_vector (self, reserved, ratio, initial1, initial2, initial3, final1, final2, final3)); } """, "rotate_vector", [ "double ratio", "double initial1","double initial2", "double initial3" ] , [ "double final1" ,"double final2" , "double final3" ] ], "cbf_get_reciprocal":[""" %apply double *OUTPUT {double *reciprocal1,double *reciprocal2, double *reciprocal3}; void get_reciprocal (double ratio,double wavelength, double real1, double real2, double real3, double *reciprocal1,double *reciprocal2, double *reciprocal3){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_get_reciprocal(self,reserved, ratio, wavelength, real1, real2, real3,reciprocal1, reciprocal2,reciprocal3)); } """, "get_reciprocal", ["double ratio","double wavelength", "double real1","double real2","double real3"], ["double reciprocal1","double reciprocal2", "double reciprocal3" ]], "cbf_get_rotation_axis":[""" %apply double *OUTPUT {double *vector1,double *vector2, double *vector3}; void get_rotation_axis (double *vector1, double *vector2, double *vector3){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_get_rotation_axis (self, reserved, vector1, vector2, vector3)); } ""","get_rotation_axis", [] , ["double vector1", "double vector2", "double vector3"] ], } class cbfgoniometerwrapper: def __init__(self): self.code = """ // Tell SWIG not to make constructor for these objects %nodefault cbf_positioner_struct; %nodefault cbf_goniometer; %nodefault cbf_axis_struct; // Tell SWIG what the object is, so we can build the class typedef struct { double matrix [3][4]; cbf_axis_struct *axis; size_t axes; int matrix_is_valid, axes_are_connected; } cbf_positioner_struct; typedef cbf_positioner_struct *cbf_goniometer; %feature("autodoc","1"); %extend cbf_positioner_struct{// Tell SWIG to attach functions to the structure cbf_positioner_struct(){ // Constructor // DO NOT CONSTRUCT WITHOUT A CBFHANDLE cbf_failnez(CBF_ARGUMENT); return NULL; /* Should never be executed */ } ~cbf_positioner_struct(){ // Destructor cbf_failnez(cbf_free_goniometer(self)); } """ self.tail = """ }; // End of cbf_positioner """ def wrap(self,cfunc,prototype,args,docstring): if cfunc.find("cbf_free_goniometer")>-1: return try: code, pyname, input, output = cbf_goniometer_specials[cfunc] self.code += docstringwrite(pyname,input,output, prototype,docstring)+ code except KeyError: print "TODO: Goniometer:",prototype def get_code(self): return self.code+self.tail cbf_goniometer_wrapper = cbfgoniometerwrapper() cbf_detector_specials = { "cbf_get_pixel_normal":[""" %apply double *OUTPUT {double *normal1,double *normal2, double *normal3}; void get_pixel_normal ( double index1, double index2, double *normal1,double *normal2, double *normal3){ cbf_failnez(cbf_get_pixel_normal(self, index1,index2,normal1,normal2,normal3)); } ""","get_pixel_normal",["double index1","double index2"] , ["double normal1","double normal2", "double normal3" ] ], "cbf_get_pixel_normal_fs":[""" %apply double *OUTPUT {double *normalfast,double *normalslow, double *normal3}; void get_pixel_normal_fs ( double indexfast, double indexslow, double *normal1,double *normal2, double *normal3){ cbf_failnez(cbf_get_pixel_normal_fs(self, indexfast,indexslow,normal1,normal2,normal3)); } ""","get_pixel_normal_fs",["double indexfast","double indexslow"] , ["double normal1","double normal2", "double normal3" ] ], "cbf_get_pixel_normal_sf":[""" %apply double *OUTPUT {double *normalslow,double *normalfast, double *normal3}; void get_pixel_normal_sf ( double indexslow, double indexfast, double *normal1,double *normal2, double *normal3){ cbf_failnez(cbf_get_pixel_normal_sf(self, indexslow,indexfast,normal1,normal2,normal3)); } ""","get_pixel_normal_sf",["double indexslow","double indexfast"] , ["double normal1","double normal2", "double normal3" ] ], "cbf_get_pixel_area":[""" %apply double *OUTPUT{double *area,double *projected_area}; void get_pixel_area(double index1, double index2, double *area,double *projected_area){ cbf_failnez(cbf_get_pixel_area (self, index1, index2, area,projected_area)); } ""","get_pixel_area",["double index1", "double index2"], ["double area","double projected_area"] ], "cbf_get_pixel_area_fs":[""" %apply double *OUTPUT{double *area,double *projected_area}; void get_pixel_area_fs(double indexfast, double indexslow, double *area,double *projected_area){ cbf_failnez(cbf_get_pixel_area_fs (self, indexfast, indexslow, area,projected_area)); } ""","get_pixel_area_fs",["double indexfast", "double indexslow"], ["double area","double projected_area"] ], "cbf_get_pixel_area_sf":[""" %apply double *OUTPUT{double *area,double *projected_area}; void get_pixel_area_sf(double indexslow, double indexfast, double *area,double *projected_area){ cbf_failnez(cbf_get_pixel_area_sf (self, indexslow, indexfast, area,projected_area)); } ""","get_pixel_area_sf",["double indexslow", "double indexfast"], ["double area","double projected_area"] ], "cbf_get_detector_distance":[""" %apply double *OUTPUT {double *distance}; void get_detector_distance (double *distance){ cbf_failnez(cbf_get_detector_distance(self,distance)); } ""","get_detector_distance",[],["double distance"]], "cbf_get_detector_normal":[""" %apply double *OUTPUT {double *normal1, double *normal2, double *normal3}; void get_detector_normal(double *normal1, double *normal2, double *normal3){ cbf_failnez(cbf_get_detector_normal(self, normal1, normal2, normal3)); } ""","get_detector_normal",[], ["double normal1", "double normal2", "double normal3"]], "cbf_get_pixel_coordinates":[""" %apply double *OUTPUT {double *coordinate1, double *coordinate2, double *coordinate3}; void get_pixel_coordinates(double index1, double index2, double *coordinate1, double *coordinate2, double *coordinate3){ cbf_failnez(cbf_get_pixel_coordinates(self, index1, index2, coordinate1, coordinate2, coordinate3)); } ""","get_pixel_coordinates",["double index1","double index2"], ["double coordinate1", "double coordinate2", "double coordinate3"] ], "cbf_get_pixel_coordinates_fs":[""" %apply double *OUTPUT {double *coordinate1, double *coordinate2, double *coordinate3}; void get_pixel_coordinates_fs(double indexfast, double indexslow, double *coordinate1, double *coordinate2, double *coordinate3){ cbf_failnez(cbf_get_pixel_coordinates_fs(self, indexfast, indexslow, coordinate1, coordinate2, coordinate3)); } ""","get_pixel_coordinates_fs",["double indexfast","double indexslow"], ["double coordinate1", "double coordinate2", "double coordinate3"] ], "cbf_get_pixel_coordinates_sf":[""" %apply double *OUTPUT {double *coordinate1, double *coordinate2, double *coordinate3}; void get_pixel_coordinates_sf(double indexslow, double indexfast, double *coordinate1, double *coordinate2, double *coordinate3){ cbf_failnez(cbf_get_pixel_coordinates_sf(self, indexslow, indexfast, coordinate1, coordinate2, coordinate3)); } ""","get_pixel_coordinates_sf",["double indexslow","double indexfast"], ["double coordinate1", "double coordinate2", "double coordinate3"] ], "cbf_get_beam_center":[""" %apply double *OUTPUT {double *index1, double *index2, double *center1,double *center2}; void get_beam_center(double *index1, double *index2, double *center1,double *center2){ cbf_failnez(cbf_get_beam_center(self, index1, index2, center1, center2)); } ""","get_beam_center",[], ["double index1", "double index2", "double center1","double center2"]], "cbf_get_beam_center_fs":[""" %apply double *OUTPUT {double *indexfast, double *indexslow, double *centerfast,double *centerslow}; void get_beam_center_fs(double *indexfast, double *indexslow, double *centerfast,double *centerslow){ cbf_failnez(cbf_get_beam_center_fs(self, indexfast, indexslow, centerfast, centerslow)); } ""","get_beam_center_fs",[], ["double indexfast", "double indexslow", "double centerfast","double centerslow"]], "cbf_get_beam_center_sf":[""" %apply double *OUTPUT {double *indexslow, double *indexfast, double *centerslow,double *centerfast}; void get_beam_center_sf(double *indexslow, double *indexfast, double *centerslow,double *centerfast){ cbf_failnez(cbf_get_beam_center_sf(self, indexslow, indexfast, centerslow, centerfast)); } ""","get_beam_center_sf",[], ["double indexslow", "double indexfast", "double centerslow","double centerfast"]], "cbf_set_beam_center":[""" void set_beam_center(double *indexslow, double *indexfast, double *centerslow,double *centerfast){ cbf_failnez(cbf_set_beam_center(self, indexslow, indexfast, centerslow, centerfast)); } ""","set_beam_center", ["double indexslow", "double indexfast", "double centerslow","double centerfast"],[]], "cbf_set_beam_center_fs":[""" void set_beam_center_fs(double *indexfast, double *indexslow, double *centerfast,double *centerslow){ cbf_failnez(cbf_set_beam_center_fs(self, indexfast, indexslow, centerfast, centerslow)); } ""","set_beam_center_fs", ["double indexfast", "double indexslow", "double centerfast","double centerslow"],[]], "cbf_set_beam_center_sf":[""" void set_beam_center_sf(double *indexslow, double *indexfast, double *centerslow,double *centerfast){ cbf_failnez(cbf_set_beam_center_sf(self, indexslow, indexfast, centerslow, centerfast)); } ""","set_beam_center_sf", ["double indexslow", "double indexfast", "double centerslow","double centerfast"],[]], "cbf_set_reference_beam_center":[""" void set_reference_beam_center(double *indexslow, double *indexfast, double *centerslow,double *centerfast){ cbf_failnez(cbf_set_reference_beam_center(self, indexslow, indexfast, centerslow, centerfast)); } ""","set_reference_beam_center", ["double indexslow", "double indexfast", "double centerslow","double centerfast"],[]], "cbf_set_reference_beam_center_fs":[""" void set_reference_beam_center_fs(double *indexfast, double *indexslow, double *centerfast,double *centerslow){ cbf_failnez(cbf_set_reference_beam_center_fs(self, indexfast, indexslow, centerfast, centerslow)); } ""","set_reference_beam_center_fs", ["double indexfast", "double indexslow", "double centerfast","double centerslow"],[]], "cbf_set_reference_beam_center_sf":[""" void set_reference_beam_center_sf(double *indexslow, double *indexfast, double *centerslow,double *centerfast){ cbf_failnez(cbf_set_reference_beam_center_sf(self, indexslow, indexfast, centerslow, centerfast)); } ""","set_reference_beam_center_sf", ["double indexslow", "double indexfast", "double centerslow","double centerfast"],[]], "cbf_get_inferred_pixel_size" : [""" %apply double *OUTPUT { double *psize } get_inferred_pixel_size; void get_inferred_pixel_size(unsigned int axis_number, double* psize){ cbf_failnez(cbf_get_inferred_pixel_size(self, axis_number, psize)); } ""","get_inferred_pixel_size",["Int axis_number"],["Float pixel size"] ], "cbf_get_inferred_pixel_size_fs" : [""" %apply double *OUTPUT { double *psize } get_inferred_pixel_size; void get_inferred_pixel_size_fs(unsigned int axis_number, double* psize){ cbf_failnez(cbf_get_inferred_pixel_size_fs(self, axis_number, psize)); } ""","get_inferred_pixel_size_fs",["Int axis_number"],["Float pixel size"] ], "cbf_get_inferred_pixel_size_sf" : [""" %apply double *OUTPUT { double *psize } get_inferred_pixel_size; void get_inferred_pixel_size_sf(unsigned int axis_number, double* psize){ cbf_failnez(cbf_get_inferred_pixel_size_sf(self, axis_number, psize)); } ""","get_inferred_pixel_size_sf",["Int axis_number"],["Float pixel size"] ] } class cbfdetectorwrapper: def __init__(self): self.code = """ // Tell SWIG not to make constructor for these objects %nodefault cbf_detector_struct; %nodefault cbf_detector; // Tell SWIG what the object is, so we can build the class typedef struct { cbf_positioner positioner; double displacement [2], increment [2]; size_t axes, index [2]; } cbf_detector_struct; typedef cbf_detector_struct *cbf_detector; %feature("autodoc","1"); %extend cbf_detector_struct{// Tell SWIG to attach functions to the structure cbf_detector_struct(){ // Constructor // DO NOT CONSTRUCT WITHOUT A CBFHANDLE cbf_failnez(CBF_ARGUMENT); return NULL; /* Should never be executed */ } ~cbf_detector_struct(){ // Destructor cbf_failnez(cbf_free_detector(self)); } """ self.tail = """ }; // End of cbf_detector """ def wrap(self,cfunc,prototype,args,docstring): if cfunc.find("cbf_free_detector")>-1: return try: code, pyname, input, output = cbf_detector_specials[cfunc] self.code += docstringwrite(pyname,input,output, prototype,docstring)+ code except KeyError: print "TODO: Detector:",prototype def get_code(self): return self.code+self.tail cbf_detector_wrapper = cbfdetectorwrapper() cbfgeneric_specials = { "cbf_get_local_integer_byte_order":[""" %cstring_output_allocate_size(char **bo, int *bolen, free(*$1)); %inline { void get_local_integer_byte_order(char **bo, int *bolen) { char * byteorder; char * bot; error_status = cbf_get_local_integer_byte_order(&byteorder); *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)} strncpy(bot,byteorder,*bolen); *bo = bot; } } ""","get_local_integer_byte_order",[],["char **bo", "int *bolen"]], "cbf_get_local_real_format":[""" %cstring_output_allocate_size(char **rf, int *rflen, free(*$1)); %inline { void get_local_real_format(char **rf, int *rflen) { char * real_format; char * rft; error_status = cbf_get_local_real_format(&real_format); *rflen = strlen(real_format); if (!(rft = (char *)malloc(*rflen))) {cbf_failnez(CBF_ALLOC)} strncpy(rft,real_format,*rflen); *rf = rft; } } ""","get_local_real_format",[],["char **rf", "int *rflen"]], "cbf_get_local_real_byte_order":[""" %cstring_output_allocate_size(char **bo, int *bolen, free(*$1)); %inline { void get_local_real_byte_order(char **bo, int *bolen) { char * byteorder; char * bot; error_status = cbf_get_local_real_byte_order(&byteorder); *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)} strncpy(bot,byteorder,*bolen); *bo = bot; } } ""","get_local_real_byte_order",[],["char **bo", "int *bolen"]], "cbf_compute_cell_volume":[""" %apply double *OUTPUT {double *volume}; %inline { void compute_cell_volume(double cell[6], double *volume) { cbf_failnez(cbf_compute_cell_volume(cell,volume)); } } ""","compute_cell_volume",["double cell[6]"],["Float volume"]], "cbf_compute_reciprocal_cell":[""" %apply double *OUTPUT {double *astar, double *bstar, double *cstar, double *alphastar, double *betastar, double *gammastar}; %inline { void compute_reciprocal_cell(double cell[6], double *astar, double *bstar, double *cstar, double *alphastar, double *betastar, double *gammastar) { double rcell[6]; cbf_failnez(cbf_compute_reciprocal_cell(cell,rcell)); *astar = rcell[0]; *bstar = rcell[1]; *cstar = rcell[2]; *alphastar = rcell[3]; *betastar = rcell[4]; *gammastar = rcell[5]; } } ""","compute_reciprocal_cell",["double cell[6]"], ["Float astar", "Float bstar", "Float cstar", "Float alphastar", "Float betastar", "Float gammastar"] ] } class genericwrapper: def __init__(self): self.code = """ // Start of generic functions %feature("autodoc","1"); """ self.tail = "// End of generic functions\n" def get_code(self): return self.code + self.tail def wrap(self,cfunc,prototype,args,docstring): pyfunc = cfunc.replace("cbf_","") # Insert a comment for debugging this script code = "\n/* cfunc %s pyfunc %s \n"%(cfunc,pyfunc) for a in args: code += " arg %s "%(a) code += "*/\n\n" self.code+=code code = "" not_found = 0 try: code, pyname, input, output = cbfgeneric_specials[cfunc] self.code += docstringwrite(pyname,input,output, prototype,docstring)+ code return except KeyError: not_found = 1 # print "KeyError" except ValueError: print "problem in generic",cfunc for item in cbfgeneric_specials[cfunc]: print "***",item raise if len(args)==1 and args[0].find("char")>-1 and \ args[0].find("**")>-1 :# return string # first write the c code and inline it code += docstringwrite(pyfunc,[],["string"],prototype,docstring) code += "%%inline %%{\n char* %s(void);\n"%(pyfunc) code += " char* %s(void){\n"%(pyfunc) code += " char *r;\n" code += " error_status = %s(&r);\n"%(cfunc) code += " return r; }\n%}\n" # now the thing to wrap is: code += "char* %s(void);"%(pyfunc) self.code=self.code+code return # code+= " void %s(void){\n"%(pyfunc) # code +=" cbf_failnez(CBF_NOTIMPLEMENTED);}\n" # self.code=self.code+code print "Have not implemented:" for s in [cfunc, pyfunc] + args: print "\t",s print return generic_wrapper = genericwrapper() def generate_wrappers(name_dict): names = name_dict.keys() for cname in names: prototype = name_dict[cname][0] docstring = name_dict[cname][1] # print "Generate wrappers: ", "::",cname,"::", prototype,"::", docstring # Check prototype begins with "int cbf_" if prototype.find("int cbf_")!=0: print "problem with:",prototype # Get arguments from prototypes try: args = prototype.split("(")[1].split(")")[0].split(",") args = [ s.lstrip().rstrip() for s in args ] # strip spaces off ends # print "Args: ", args except: # print cname # print prototype raise if args[0].find("cbf_handle")>=0: # This is for the cbfhandle object cbf_handle_wrapper.wrap(cname,prototype,args,docstring) if (cname=="cbf_get_unit_cell"): cbf_handle_wrapper.wrap("cbf_get_unit_cell_esd",prototype,args,docstring) if (cname=="cbf_get_reciprocal_cell"): cbf_handle_wrapper.wrap("cbf_get_reciprocal_cell_esd",prototype,args,docstring) if (cname=="cbf_set_unit_cell"): cbf_handle_wrapper.wrap("cbf_set_unit_cell_esd",prototype,args,docstring) if (cname=="cbf_set_reciprocal_cell"): cbf_handle_wrapper.wrap("cbf_set_reciprocal_cell_esd",prototype,args,docstring) continue if args[0].find("cbf_goniometer")>=0: # This is for the cbfgoniometer cbf_goniometer_wrapper.wrap(cname,prototype,args,docstring) continue if args[0].find("cbf_detector")>=0: # This is for the cbfdetector cbf_detector_wrapper.wrap(cname,prototype,args,docstring) continue generic_wrapper.wrap(cname,prototype,args,docstring) generate_wrappers(name_dict) open("cbfgoniometerwrappers.i","w").write(cbf_goniometer_wrapper.get_code()) open("cbfdetectorwrappers.i","w").write(cbf_detector_wrapper.get_code()) open("cbfhandlewrappers.i","w").write(cbf_handle_wrapper.get_code()) open("cbfgenericwrappers.i","w").write(generic_wrapper.get_code()) print "End of output from make_pycbf.py" print "\\end{verbatim}" @} ./CBFlib-0.9.2.2/pycbf/pycbf.aux0000644000076500007650000000763611603702120014533 0ustar yayayaya\relax \ifx\hyper@anchor\@undefined \global \let \oldcontentsline\contentsline \gdef \contentsline#1#2#3#4{\oldcontentsline{#1}{#2}{#3}} \global \let \oldnewlabel\newlabel \gdef \newlabel#1#2{\newlabelxx{#1}#2} \gdef \newlabelxx#1#2#3#4#5#6{\oldnewlabel{#1}{{#2}{#3}}} \AtEndDocument{\let \contentsline\oldcontentsline \let \newlabel\oldnewlabel} \else \global \let \hyper@last\relax \fi \@writefile{toc}{\contentsline {section}{\numberline {1}Introduction}{2}{section.1}} \@writefile{toc}{\contentsline {section}{\numberline {2}Installation prerequisites}{2}{section.2}} \@writefile{toc}{\contentsline {section}{\numberline {3}Generating the c interface - the SWIG file}{3}{section.3}} \newlabel{scrap1}{{3}{3}{Generating the c interface - the SWIG file\relax }{section.3}{}} \newlabel{scrap2}{{3}{3}{Generating the c interface - the SWIG file\relax }{section.3}{}} \newlabel{scrap3}{{3}{4}{Generating the c interface - the SWIG file\relax }{section.3}{}} \newlabel{scrap4}{{3}{4}{Generating the c interface - the SWIG file\relax }{section.3}{}} \@writefile{toc}{\contentsline {subsection}{\numberline {3.1}Exceptions}{5}{subsection.3.1}} \newlabel{scrap5}{{3.1}{5}{Exceptions\relax }{subsection.3.1}{}} \newlabel{scrap6}{{3.1}{5}{Exceptions\relax }{subsection.3.1}{}} \newlabel{scrap7}{{3.1}{9}{Exceptions\relax }{subsection.3.1}{}} \@writefile{toc}{\contentsline {subsection}{\numberline {3.2}Exceptions}{9}{subsection.3.2}} \@writefile{toc}{\contentsline {section}{\numberline {4}Docstrings}{10}{section.4}} \@writefile{toc}{\contentsline {section}{\numberline {5}Wrappers}{10}{section.5}} \newlabel{scrap8}{{5}{10}{Wrappers\relax }{section.5}{}} \@writefile{toc}{\contentsline {section}{\numberline {6}Building python extensions - the setup file}{58}{section.6}} \newlabel{scrap9}{{6}{58}{Building python extensions - the setup file\relax }{section.6}{}} \@writefile{toc}{\contentsline {section}{\numberline {7}Building and testing the resulting package}{59}{section.7}} \newlabel{scrap10}{{7}{59}{Building and testing the resulting package\relax }{section.7}{}} \newlabel{scrap11}{{7}{59}{Building and testing the resulting package\relax }{section.7}{}} \newlabel{scrap12}{{7}{59}{Building and testing the resulting package\relax }{section.7}{}} \@writefile{toc}{\contentsline {section}{\numberline {8}Debugging compiled extensions}{59}{section.8}} \@writefile{toc}{\contentsline {section}{\numberline {9}Things which are currently missing}{60}{section.9}} \@writefile{toc}{\contentsline {section}{\numberline {10}Testing}{60}{section.10}} \@writefile{toc}{\contentsline {subsection}{\numberline {10.1}Read a file based on cif2cbf.c}{60}{subsection.10.1}} \newlabel{scrap13}{{10.1}{61}{Read a file based on cif2cbf.c\relax }{subsection.10.1}{}} \@writefile{toc}{\contentsline {subsection}{\numberline {10.2}Try to test the goniometer and detector}{62}{subsection.10.2}} \newlabel{scrap14}{{10.2}{62}{Try to test the goniometer and detector\relax }{subsection.10.2}{}} \@writefile{toc}{\contentsline {subsection}{\numberline {10.3}Test cases for the generics}{62}{subsection.10.3}} \newlabel{scrap15}{{10.3}{62}{Test cases for the generics\relax }{subsection.10.3}{}} \@writefile{toc}{\contentsline {section}{\numberline {11}Worked example 1 : xmas beamline + mar ccd detector at the ESRF}{62}{section.11}} \@writefile{toc}{\contentsline {subsection}{\numberline {11.1}Reading marccd headers}{63}{subsection.11.1}} \newlabel{scrap16}{{11.1}{63}{Reading marccd headers\relax }{subsection.11.1}{}} \@writefile{toc}{\contentsline {subsection}{\numberline {11.2}Writing out cif files for fit2d/xmas}{68}{subsection.11.2}} \newlabel{scrap17}{{11.2}{68}{Writing out cif files for fit2d/xmas\relax }{subsection.11.2}{}} \@writefile{toc}{\contentsline {subsection}{\numberline {11.3}A template cif file for the xmas beamline}{72}{subsection.11.3}} \newlabel{scrap18}{{11.3}{72}{A template cif file for the xmas beamline\relax }{subsection.11.3}{}} ./CBFlib-0.9.2.2/pycbf/pycbf.dvi0000644000076500007650000042756011603702120014522 0ustar yayayaya÷ƒ’À;è TeX output 2007.06.05:1916‹ÿÿÿÿïlpdf:docinfo<> ½¥ ý0à‘âh½ï3pdf:dest (page.1) [@thispage /XYZ @xpos @ypos null]ŽŽ ±<`‘âh½ ýgàò¨pdf:obj @OBJpdfdocencoding<>ïLpdf:obj @OBJZaDb<>ïepdf:obj @OBJHelv<>ïApdf:outline 1<>>>ïOpdf:outline 1<>>>ï_pdf:outline 1<>>>ïEpdf:outline 2<>>>ïFpdf:outline 2<>>>ïFpdf:outline 2<>>>ïMpdf:outline 2<>>>ïFpdf:outline 2<>>>ïopdf:outline 3<>>>ïJpdf:outline 2<>>>ïHpdf:outline 2<>>>ï`pdf:outline 1<>>>ï_pdf:outline 1<>>>ïRpdf:outline 1<>>>ïWpdf:outline 1<>>>ï>>>ïZpdf:outline 2<>>>ïcpdf:outline 2<>>>ïWpdf:outline 2<>>>ïupdf:outline 1<>>>ïRpdf:outline 2<>>>ï`pdf:outline 2<>>>ïepdf:outline 2<>>>ï=pdf:docview<>ï6pdf:dest (Doc-Start) [@thispage /XYZ @xpos @ypos null]Ÿ4Á’ÇŠ¼óñkAHG® cmssbx10»PyCBFŽŸ‘YwøóDÓítG®G®cmr17¹A–7tpŒqython“binding“to“the“CBFlib“libraryŽŸÁ’¿…óX«Q cmr12¼Jon–ê¨P›ÿV.“W˜righ¬rtŽŽŸ‘qtZAn•¬ry“one–ê¨who“wishes“to“con¬rtribute,“please“do!ŽŽŽŽŽŸ&Iš‘i\1Started–ê¨Dec“12,“2005,“already“it“is“June“5,“2007ŽŸ';’Ï@Šót ‰: cmbx9ÆAbstractŽŸ± ‘&ßüóo´‹Ç cmr9ÅArea–=detectors“at“syncš¾9hrotron“facilities“can“result“in‘=h˜uge“amoun˜ts“of“data“bAÇeing“generated“v˜eryޤ ‘rapidly‘ÿ:«.‘½çh•¾9ttp://www.bšAÇernstein-plus-sons.com/soft“w“are/CBF/).‘€6In–6–this“do˜cumen¾9t“aŽ¡‘p•¾9ython›¶¥in“terface˜is˜dev“elopAÇed‘¶¦using˜the˜SWIG‘¶{(h“ttp://www.swig.org)˜pac“k‘ÿ|rage˜in‘¶¦order˜to˜giv“e˜theŽ¡‘author–Teasy“access“to“binary“cif“ les.ŽŸ#="‘óÂÖN ff cmbx12ÈCon•ŒÌten“tsŽŸ 6ï7pdf:dest (section*.1) [@thispage /XYZ @xpos @ypos null]Ÿ Bã‘ïUpdf:bann<>>>Æ1Ž‘ ßúIn´CtroK¼ductionïpdf:eann’GWõ2ŽŽŸÂ‘ïUpdf:bann<>>>2Ž‘ ßúInstallation‘ŒÊprerequisitesïpdf:eann’?!3ŽŽ©Â‘ïUpdf:bann<>>>3Ž‘ ßúGenerating–ŒÊthe“c“in´Cterface“-“the“SWIG“ leïpdf:eann’»ðÃ3ŽŽ¤ ç«‘&ßüïZpdf:bann<>>>Å3.1Ž‘F_Constan¾9tsïpdf:eann‘‹¸‘Oÿ.ŽŽ–1Ä‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ‘Pè5ŽŽ¡‘&ßüïZpdf:bann<>>>3.2Ž‘F_Exceptionsïpdf:eann‘*‘Oÿ.ŽŽ–1Ä‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ‘Pè6ŽŽ¡‘&ßüïZpdf:bann<>>>3.3Ž‘F_DoAÇcstringsïpdf:eann‘¯‘Oÿ.ŽŽ–1Ä‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ‘Pé7ŽŽ¡‘&ßüïZpdf:bann<>>>3.4Ž‘F_A–Tgeneric“wrappAÇerïpdf:eann‘`-‘Oÿ.ŽŽ–1Ä‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ‘°é10ŽŽ¡‘&ßüïZpdf:bann<>>>3.5Ž‘F_CBFHandlesïpdf:eann‘ïÑ‘Oÿ.ŽŽ–1Ä‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ‘°é11ŽŽ¡‘<&[ï_pdf:bann<>>>3.5.1Ž‘™ŠMan¾9ually–TwrappAÇed“things“for“cbfhandle“ob‘ƒŽjectïpdf:eann‘Õß‘Oÿ.ŽŽ–1Ä‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ‘°ê14ŽŽ¡‘&ßüïZpdf:bann<>>>3.6Ž‘F_CBF¾9Goniometersïpdf:eann‘¼r‘Oÿ.ŽŽ–1Ä‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ‘°ê24ŽŽ¡‘&ßüïZpdf:bann<>>>3.7Ž‘F_CBFDetectorsïpdf:eann‘à‘Oÿ.ŽŽ–1Ä‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ‘°ê26ŽŽ¦‘ïUpdf:bann<>>>Æ4Ž‘ ßúBuilding–ŒÊp´Cython“extensions“-“the“setup“ leïpdf:eann’µüö28ŽŽ¦‘ïUpdf:bann<>>>5Ž‘ ßúBuilding–ŒÊand“testing“the“resulting“pac´Ck‘ÿh‰ageïpdf:eann’·G×29ŽŽ¦‘ïUpdf:bann<>>>6Ž‘ ßúDebugging–ŒÊcompiled“extensionsïpdf:eann’êDD30ŽŽŸÂ‘ïUpdf:bann<>>>7Ž‘ ßúThings–ŒÊwhicš´Ch“are“curren˜tly“missingïpdf:eann’ØQq30ŽŽ¦‘ïUpdf:bann<>>>8Ž‘ ßúT‘ÿÌestingïpdf:eann’ZÅ35ŽŽ¡‘&ßüïZpdf:bann<>>>Å8.1Ž‘F_Read–Ta“ le“based“on“cif2cbf.cïpdf:eann‘Aó‘Oÿ.ŽŽ–1Ä‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ‘°ê35ŽŽ¡‘&ßüïZpdf:bann<>>>8.2Ž‘F_T‘ÿ:«ry–Tto“test“the“goniometer“and“detectorïpdf:eann‘Ìr‘Oÿ.ŽŽ–1Ä‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ‘°ê36ŽŽ¡‘&ßüïZpdf:bann<>>>8.3Ž‘F_T‘ÿ:«est–Tcases“for“the“genericsïpdf:eann‘ ˆ‘Oÿ.ŽŽ–1Ä‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ‘°ê36ŽŽ¦‘ïUpdf:bann<>>>Æ9Ž‘ ßúW‘ÿÌork´Ced–ŒÊexample“1“:‘»¸xmas“bK¼eamline“+“mar“ccd“detector“at“the“ESRF“ïpdf:eann‘4´â37ŽŽ¡‘&ßüïZpdf:bann<>>>Å9.1Ž‘F_Reading–Tmarccd“headersïpdf:eann‘¥ƒ‘Oÿ.ŽŽ–1Ä‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ‘°ë37ŽŽ¡‘&ßüïZpdf:bann<>>>9.2Ž‘F_W‘ÿ:«riting–Tout“cif“ les“for“ t2d/xmasïpdf:eann‘ 1‘Oÿ.ŽŽ–1Ä‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ‘°ê42ŽŽ¡‘&ßüïZpdf:bann<>>>9.3Ž‘F_A–Ttemplate“cif“ le“for“the“xmas“bAÇeamlineïpdf:eann‘'w‘Oÿ.ŽŽ–1Ä‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ“‘Oÿ.ŽŽ‘°ê47ŽŽŽŸ’ßûãóKñ`y cmr10²1ŽŽŒ‹* Ú ýO¸‘âh½ï3pdf:dest (page.2) [@thispage /XYZ @xpos @ypos null]Ÿüfd–UU²1.“In¸ãtroGductionŽŽŽ’ÇX CONTENTSŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘ûh¿ÈIndex–ffof“ le“namesŽ‘âh½©é˜ï7pdf:dest (section*.2) [@thispage /XYZ @xpos @ypos null]¤ ‘ó ߤN cmtt9Ë"linux.sh"‘Tó|{Ycmr8½De ned–ÕXbÃŽy“29b.Ž¡‘Ë"makeflatascii.py"‘T½De ned–ÕXbÃŽy“29c.Ž¡‘Ë"make_pycbf.py"‘T½De ned–ÕXbÃŽy“7b.Ž¡‘Ë"pycbf.i"‘T½De ned–ÕXbÃŽy“3.Ž¡‘Ë"pycbf_test1.py"‘T½De ned–ÕXbÃŽy“35.Ž¡‘Ë"pycbf_test2.py"‘T½De ned–ÕXbÃŽy“36a.Ž¡‘Ë"pycbf_test3.py"‘T½De ned–ÕXbÃŽy“36b.Ž¡‘Ë"setup.py"‘T½De ned–ÕXbÃŽy“28.Ž¡‘Ë"win32.bat"‘T½De ned–ÕXbÃŽy“29a.Ž¡‘Ë"xmas/readmarheader.py"‘T½De ned–ÕXbÃŽy“37.Ž¡‘Ë"xmas/xmasheaders.py"‘T½De ned–ÕXbÃŽy“42.Ž¡‘Ë"xmas/xmas_cif_template.cif"‘T½De ned–ÕXbÃŽy“47.ŽŸD\‘ÈIndex–ffof“macro“namesަï7pdf:dest (section*.3) [@thispage /XYZ @xpos @ypos null]¡‘ó©±Ê cmsy9Êh–ŠªÅcbfdetectorwrappAÇer›T½26“Êi˜½Referenced–ÕXin“7b.Ž¡‘Êh–ŠªÅcbfgoniometerwrappAÇer›T½24“Êi˜½Referenced–ÕXin“7b.Ž¡‘Êh–ŠªÅcbfhandlespAÇecials›T½14“Êi˜½Referenced–ÕXin“11.Ž¡‘Êh–ŠªÅcbfhandlewrappAÇer›T½11“Êi˜½Referenced–ÕXin“7b.Ž¡‘Êh–ŠªÅcbfselectedconstan¾9ts›T½5“Êi˜½Referenced–ÕXin“3.Ž¡‘Êh–ŠªÅdoAÇcstringwrite›T½9“Êi˜½Referenced–ÕXin“7b.Ž¡‘Êh–ŠªÅexceptionhandlingno¾9wrap›T½6“Êi˜½Referenced–ÕXin“3.Ž¡‘Êh–ŠªÅexceptionhandlingto¾9wrap›T½7a“Êi˜½Referenced–ÕXin“3.Ž¡‘Êh–ŠªÅgenericwrappAÇer›T½10b“Êi˜½Referenced–ÕXin“7b.Ž¡‘Êh–ŠªÅm¾9yformat›T½10a“Êi˜½Referenced–ÕXin“9.ŽŸD\‘ÈThings–ffto“doŽŸ ¶dï7pdf:dest (section*.4) [@thispage /XYZ @xpos @ypos null]Ÿ34‘%`ÊŽŽŽ‘/Åget‘މffÆgŽ›Tyimage–Tand“set‘މffÆgŽ˜image“not“implemenš¾9ted“y˜et“(decide“ho˜w“that“should“bAÇe“done)ŽŸ<Ô‘%`ÊŽŽŽ‘/ÅW‘ÿ:«rite–Ttest“coAÇde“to“test“eacš¾9h“and“ev˜ery“function“for“go•AÇo“d–Tand“bad“args“etcŽŸ\ï6pdf:dest (section.1) [@thispage /XYZ @xpos @ypos null]Ÿ@‘È1Ž‘1LÍInŒÌtros3ductionŽŸ阑ÅThe–ÍãCBFlib›Íâlibrary“(v¾9ersion˜0.7.4)“is˜written“in˜the“c“language,‘Ü,o ering“c˜(and“C++)˜programmers“aŽ¡‘con•¾9v“enien“t›ôin“terface˜to˜suc“h˜ les.‘UThe˜curren“t˜author˜uses˜a˜di eren“t‘ôlanguage˜(p“ython)˜from˜da“y˜toŽ¡‘daš¾9y–O\and“so‘O[a“p˜ython“in˜terface“w˜as–O[desired.‘ʈAfter“a–O\short“attempt“to‘O[mak˜e“a“quic˜k“and‘O[dirt˜y“SWIGŽ¡‘in•¾9terface›® it‘® w“as˜decided˜that–® in˜the“long˜run˜it“w¾9ould˜b•AÇe˜b“etter–® to˜write“a˜propAÇer˜in¾9terface“for˜p¾9ython.Ž¡‘&ßüAll–¡of“the“functions“in“the“library“return‘¢an“inš¾9teger“re ecting“error“status.‘ßUsually“these“in˜tegersŽ¡‘seem–ˆfto“bšAÇe“zero,‘¤–and“a“non-zero“return“v‘ÿ|ralue‘ˆeapp˜ears“to“mean“an“error“o˜ccurred.‘ívActual“return“v‘ÿ|raluesŽ¡‘are–„Íreturned“via“pAÇoinš¾9ters‘„Ìin“argumen˜t“lists.‘ìCIn“order“to›„Ìsimplify“the“authors“life“(as“a˜user)“all“of“thoseŽ¡‘in•¾9tegers›e/ha“v“e˜b•AÇeen˜made˜to˜disapp“ear˜if˜they˜are˜zero,‘y%and˜cause˜an˜\exception"˜to˜b“e˜generated˜ifŽ¡‘they–§$are“not–§%zero.‘ÑàThis“solution–§$migh¾9t“not“bšAÇe‘§%the“b˜est“thing“to›§%do,‘˘and“it“can˜alw•¾9a“ys–§$bAÇe“c¾9hangedŽ¡‘where–Tthe“return“v‘ÿ|ralue“is“in¾9tended“to“normally“bAÇe“used.Ž¡‘&ßüActual–<®return‘<¯v‘ÿ|ralues“whicš¾9h“w˜ere‘<¯passed“bac˜k“via‘<¯pAÇoin˜ter“argumen˜ts“are‘<¯no˜w“just“passed‘<¯bac˜k“asŽ¡‘(pAÇerhaps–¼mš¾9ultiple)“return“v‘ÿ|ralues.‘#©W‘ÿ:«e“m˜ust“loAÇok“out‘½for“INOUT‘»argumen˜ts,‘Vnone‘½seem“to“ha˜v˜e“bAÇeenŽ¡‘found–p}yš¾9et,‘‡Gbut“there‘p|migh˜t“bAÇe“exceptions.‘-êThe“author“has“a“v‘ÿ|rague“suspicion‘p|that“p˜ython“functionsŽ¡‘generally–Tdo“not“moAÇdify“their“argumenš¾9ts,“but“this“migh˜t“bAÇe“wrong.Ž¡‘&ßüThe–8library“appAÇears“to“de ne“(at“least)“three“ob‘ƒŽjects.‘ļThe“one“wš¾9e“started“on“w˜as“the“cbf‘މffÆgŽ–Tyhandle‘މffÆgŽ“structŽ¡‘de ned›>èin–>çcbf.h.‘™,Man¾9y“of˜the˜functions“ha•¾9v“e˜their˜ rst‘>çargumen“t˜as˜a˜pAÇoin“ter–>çto˜one˜of“these˜struc-Ž¡‘tures.‘í.Therefore›‡w•¾9e‘‡mak“e˜this–‡structure˜an“ob‘ƒŽject˜and“then˜evš¾9erything“whic˜h›‡uses“it˜as“ rst˜argumen¾9tŽ¡‘is–Ta“mem¾9bAÇer“function“for“that“ob‘ƒŽject.Ž¡‘&ßüIn–NÈorder“to“pass“image‘NÉdata“bacš¾9k“and“forth“there“is“a“dicult˜y“that‘NÉp˜ython“seems“to“lac˜k“aŽ¡‘go•AÇo“d›}w•¾9a“y˜to˜represen“t˜large˜arra“ys.‘´ëThe‘~standard˜library˜o ers˜an˜"arra“y"˜ob‘ƒŽject˜whic“h˜claims˜toŽ¡‘ecienš¾9tly–mÛhold‘mÚhomogenous“n˜umerical›mÚdata.‘äSadly“this˜seems“to“bAÇe˜limited“to˜one-dimensional“arra¾9ys.Ž¡‘The–Î builtin›Î string“ob‘ƒŽject˜can“hold˜binary“data˜and“this“w•¾9as˜c“hosen–Î as˜the“w•¾9a“y˜to–Î pass˜the“actualŽ¡‘binary–‘Øbacš¾9k“and“forth“bAÇet˜w˜een“p˜ython“and“CBFlib.‘‘ûUnfortunately“this“means“the“binary“data“areŽ¡‘prettš¾9y–k9useless‘k:when“they“arriv˜e›k:on“the˜p¾9ython“side,‘€²so˜helpAÇer“functions˜are“pro¾9vided“to˜con•¾9v“ert‘k9theŽ¡‘data–ï€to“a“pš¾9ython“(standard“library)“1D‘ïvarra˜y“and“also“to“a“"Numeric"“arra˜y“or“a“"Numarra˜y"“arra˜y‘ÿ:«.Ž¡‘The–Tlatter“t•¾9w“o–Tare“pšAÇopular“extension“mo˜dules“for“manipulating“large“arra¾9ys.ŽŽŸ‘âh½Ÿô‰ff&NŸ ²2ŽŽŽ’ä\June–UU5,“2007ŽŽ’Ê‚¸J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽŽŽŽŽŽŒ‹5P Ú ýO¸‘âh½ï3pdf:dest (page.3) [@thispage /XYZ @xpos @ypos null]Ÿüfd²CONTENTSŽŽŽ’‰ Ë2.–UUInstallation“prerequisitesŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH‘âh½ ýKO¸ï6pdf:dest (section.2) [@thispage /XYZ @xpos @ypos null]Ÿ ‘È2Ž‘1LÍInstallation‘ffprerequisitesŽŸìß‘ÅThe–wªdoAÇcumenš¾9t“y˜ou‘w«are“reading“w˜as“generated“from‘w«a“n˜u˜w˜eb“source“ le.‘çâThis“is‘w«something“v˜ery“similarޤ ‘to–7%latex“with›7&a“few“extensions“for“writing˜out“source“coAÇde“ les.‘äAs“sucš¾9h“it“k˜eeps‘7&together“the“wholeŽ¡‘pac¾9k‘ÿ|rage–™Çin›™Æa“single˜ le“and˜mak¾9es“it˜easier“to“write˜doAÇcumen¾9tation.‘©ÈY‘ÿ:«ou˜will“need˜a“to˜obtain“theŽ¡‘prepro•AÇcessing›±"to“ol‘±#n•¾9u“w“eb˜(pAÇerhaps˜from˜h“ttp://n“u“w“eb.sourceforge.net)–±#in˜order˜to˜build“from˜scratc¾9hŽ¡‘with–Á"the“ le“p¾9ycbf.w.‘_PreprošAÇccessed“output“is“hop˜efully‘Á#also“aš¾9v‘ÿ|railable“to“y˜ou.‘_W‘ÿ:«e“do“not“recommendŽ¡‘editing–Tthe“SWIG“generated“wrappAÇers!!Ž© Ù‘&ßüOnly–æïpš¾9ython“v˜ersion“2.4“has“bAÇeen“targetted“originally“(other“v˜ersions?)‘ ùso“that“y˜ou“will“probablyŽ¡‘w•¾9an“t–Tto“ha•¾9v“e–Tthat“vš¾9ersion“of“p˜ython“installed.ަ‘&ßüW‘ÿ:«e–?are“building›>binary“extensions,‘ºso˜yš¾9ou“also“need“a“w˜orking›>c“compiler.‘.1The˜compiler“used“b¾9yŽ¡‘the–Tauthor“wš¾9as“gcc“(for“bAÇoth“windo˜ws“and“unix)“with“the“mingw“v˜ersion“under“windo˜ws.ŽŸ Ø‘&ßüFinally‘ÿ:«,–Tyš¾9ou“need“a“cop˜y“of“swig“(from“www.swig.org)“in“order“to“(re)generate“the“c“wrappAÇers.ަ‘&ßüIn–“scase›“rall“that˜sounds“scary‘ÿ:«,›²ùthen“fear“not,˜it“is›“rlik¾9ely“that˜a“single“do¾9wnload˜for“windo¾9ws˜willŽ¡‘just–J)wš¾9ork“with‘J*the“righ˜t“v˜ersion“of‘J*p˜ython.‘ºïUnix“systems‘J*come“with“man˜y“of‘J*those“things“a˜v‘ÿ|railableŽ¡‘an•¾9yw“a“y‘ÿ:«.ŽŸW$ï6pdf:dest (section.3) [@thispage /XYZ @xpos @ypos null]ŸAÙ‘È3Ž‘1LÍGenerating–ffthe“c“inŒÌterface“-“the“SWIG“ leŽŸìß‘ÅEssenš¾9tially–ôthe“swig‘ó le“starts“b˜y“sa˜ying›ówhat“to“include“to“build˜the“wrappAÇers,‘œand“then˜goAÇes“on“toŽ¡‘de ne–Tthe“pš¾9ython“in˜terface“for“eac˜h“function“w˜e“w˜an˜t“to“call.ަ‘&ßüThe–÷'library›÷&appAÇears“to˜de ne“at˜least“three˜\ob‘ƒŽjects";‘ha˜CBF‘öíhandle,‘/ša“cbf‘މffÆgŽ‘Tygoniometer“and˜aŽ¡‘cbf‘މffÆgŽ‘Tydetector.‘pW‘ÿ:«e–Twill“attempt“to“map“these“onš¾9to“p˜ython“classes.ŽŸ Ø‘&ßüFIXME‘5-–5decide›5 whether“in¾9troAÇduce“a˜"binary“arra¾9y"“class˜with“con•¾9v“erters–5to“more˜common“rep-Ž¡‘resen¾9tations?ަ‘&ßüAll–JÆof“the›JÇfunctions“in“the“library“appAÇear“to˜return“0“on“success“and“a˜meaningful“error“coAÇde“onŽ¡‘failure.‘pW‘ÿ:«e–Ttry“to“propagate“that“error“coAÇde“across“the“language“barrier“via“exceptions.ަ‘&ßüSo–Tthe“SWIG“ le“will“start“o “b¾9y“including“the“header“ les“needed“for“compilation:ŽŸ <‘Ë"pycbf.i"‘T½3‘ÕXÊŽŸ %‹¡‘/Ë/*–¹–File:“pycbf.i“*/Ž¡¡‘///–¹–Indicate“that“we“want“to“generate“a“module“call“pycbfŽ¡‘/%module‘¹–pycbfŽ¡¡‘/%pythoncode‘¹–%{Ž¡‘/__author__–¹–=“"Jon“Wright“"Ž¡‘/__date__–¹–=“"14“Dec“2005"Ž¡‘/__version__–¹–=“"still_being_written"Ž¡‘/__credits__–¹–=“"""Paul“Ellis“and“Herbert“Bernstein“for“the“excellent“CBFlib!"""Ž¡‘/__doc__="""–¹–pycbf“-“python“bindings“to“the“CBFlib“libraryŽ¡¡‘3¹˜A–¹–library“for“reading“and“writing“ImageCIF“and“CBF“filesŽ¡‘3¹˜which–¹–store“area“detector“images“for“crystallography.Ž¡¡‘3¹˜This–¹–work“is“a“derivative“of“the“CBFlib“version“0.7.7“libraryŽ¡‘3¹˜by‘ s,Paul–¹–J.“Ellis“of“Stanford“Synchrotron“Radiation“LaboratoryŽ¡‘3¹˜and–¹–Herbert“J.“Bernstein“of“Bernstein“+“SonsŽ¡‘3¹˜See:Ž¡‘=,Ähttp://www.bernstein-plus-sons.com/software/CBF/Ž¡¡‘3¹˜Licensing–¹–is“GPL“based,“see:Ž¡‘=,Ähttp://www.bernstein-plus-sons.com/software/CBF/doc/CBFlib_NOTICES.htmlŽ¡¡‘3¹˜These–¹–bindings“were“automatically“generated“by“SWIG,“and“theŽ¡‘3¹˜input–¹–to“SWIG“was“automatically“generated“by“a“python“script.Ž¡‘3¹˜We–¹–very“strongly“recommend“you“do“not“attempt“to“edit“themŽ¡‘3¹˜by‘¹–hand!Ž¡¡¡¡‘3¹˜Copyright–¹–(C)“2007‘æXJonathan“WrightŽŽŸ‘âh½Ÿô‰ff&NŸ ²J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽ’ä\June–UU5,“2007ŽŽ’û&J3ŽŽŽŽŽŽŽŽŒ‹J… Ú ýO¸‘âh½ï3pdf:dest (page.4) [@thispage /XYZ @xpos @ypos null]Ÿüfd–UU²3.“Generating“the“c“in¸ãterface“-“the“SWIG“ leŽŽŽ’ÇX CONTENTSŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘~9ËESRF,–¹–Grenoble,“Franceޤ ‘]email:‘¹–wright@esrf.frŽ¡‘h¿"""Ž¡‘h¿%}Ž¡¡¡¡¡‘h¿//–¹–Used“later“to“pass“back“binary“dataŽ¡‘h¿%include‘¹–"cstring.i"Ž¡¡‘h¿//–¹–Attempt“to“autogenerate“what“SWIG“thinks“the“call“looks“likeŽ¡¡‘h¿//–¹–Typemaps“are“a“SWIG“mechanism“for“many“things,“not“least“multipleŽ¡‘h¿//–¹–return“valuesŽ¡‘h¿%include‘¹–"typemaps.i"Ž¡¡¡‘h¿%{‘ s,//–¹–Here“is“the“c“code“needed“to“compile“the“wrappers,“but“notŽ¡‘$O//–¹–to“be“wrappedŽ¡¡‘h¿#include‘¹–"../include/cbf.h"Ž¡‘h¿#include‘¹–"../include/cbf_simple.h"Ž¡¡‘h¿//–¹–Helper“functions“to“generate“error“messageŽ¡‘h¿Êh–ŠªÅexceptionhandlingno¾9wrap‘T½6“ÊiŽŽ¡¡‘h¿Ë%}–¹–//“End“of“code“which“is“not“wrapped“but“needed“to“compileŽ¡¡¡¡‘h¿//–¹–REMOVE“MEŽ¡‘h¿/*Ž¡‘h¿//–¹–Type“mapping“for“grabbing“a“FILE“*“from“PythonŽ¡‘h¿//%typemap(python,in)–¹–FILE“*“{Ž¡‘h¿//–¹–if“(!PyFile_Check($input))“{Ž¡‘h¿//‘Y„PyErr_SetString(PyExc_TypeError,–¹–"Need“a“file!");Ž¡‘h¿//‘Y„return‘¹–NULL;Ž¡‘h¿//‘ s,}Ž¡‘h¿//‘ s,$1–¹–=“PyFile_AsFile($input);Ž¡‘h¿//}Ž¡‘h¿*/Ž¡‘h¿//–¹–Gives“an“IO“error“when“file“is“closed“-“check“CBFlib“API“on“that...Ž¡¡¡¡‘h¿//–¹–The“actual“wrappersŽ¡¡‘h¿//–¹–Constants“needed“from“header“filesŽ¡‘h¿Êh–ŠªÅcbfselectedconstan¾9ts‘T½5“ÊiŽŽ¡¡‘h¿Ë//–¹–Exception“handlingŽ¡‘h¿Êh–ŠªÅexceptionhandlingto¾9wrap‘T½7a“ÊiŽŽ¡¡‘h¿Ë%include‘¹–"cbfgenericwrappers.i"Ž¡¡‘h¿//–¹–cbf_goniometer“objectŽ¡¡‘h¿%include‘¹–"cbfgoniometerwrappers.i"Ž¡¡‘h¿%include‘¹–"cbfdetectorwrappers.i"Ž¡¡‘h¿//–¹–cbfhandle“objectŽŽŸ‘âh½Ÿô‰ff&NŸ ²4ŽŽŽ’ä\June–UU5,“2007ŽŽ’Ê‚¸J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽŽŽŽŽŽŒ‹[/ Ú ýO¸‘âh½ï3pdf:dest (page.5) [@thispage /XYZ @xpos @ypos null]Ÿüfd²CONTENTSŽŽŽ’½¦B3.1‘ Constan¸ãtsŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘h¿Ë%include‘¹–"cbfhandlewrappers.i"ޤ ¡‘h¿ÊŽŽŸm®‘ûh¿ÅDespite–´the“temptation“to“just“throš¾9w“ev˜erything“from“the“c“header“ les“in˜to“the“in˜terface,‘ÛÃa“shortŽ¡‘ûh¿expšAÇerience–~usuggested‘~vw¾9e“are“b˜etter“o ›~vto“pull“out˜only“the“parts“w•¾9e˜w“an“t–~uand“mak¾9e“the˜calls“moreŽ¡‘ûh¿p¾9ythonicŽŸ Üñ‘ H¹The–»€other“parts“of“this‘»došAÇcumen¾9t“should“generate“the“input“ les“"cbfhandlewrapp˜ers.i",‘% etcŽ¡‘ûh¿FIXMEŽ‘âh½Ÿð%ï;pdf:dest (subsection.3.1) [@thispage /XYZ @xpos @ypos null]ŸÜò‘ó!ÂÖN  cmbx12Ì3.1Ž‘7ÀConstan tsŽŸX*‘ÅHere–Tcome“the“constanš¾9ts“needed“to“pass“as“argumen˜ts“to“the“v‘ÿ|rarious“functions.ŽŸ Üò‘&ßüIf–8yš¾9ou“sa˜y“impAÇort“\p˜ycbf‘´q"“in“p˜ython“y˜ou“should“ev˜en˜tually“ nd“them“via“p˜ycbf.CONST‘ÿ:«ANT‘މffÆgŽ‘TyNAME.ŽŸPº‘Êh–ŠªÅcbfselectedconstan¾9ts‘T½5“Êi‘‘ÆŽŸ ¶×¡‘8s.Ë/*–¹–Constants“used“for“compression“*/Ž¡¡‘/#define–¹–CBF_INTEGER‘Ÿî0x0010‘ s,/*“Uncompressed“integer‘FßÊ*/Ž¡‘/#define–¹–CBF_FLOAT‘!0x0020‘ s,/*“Uncompressed“IEEE“floating-point‘,Â*/Ž¡‘/#define–¹–CBF_CANONICAL‘,Â0x0050‘ s,/*“Canonical“compression‘B&4*/Ž¡‘/#define–¹–CBF_PACKED‘Y„0x0060‘ s,/*“Packed“compression‘PRö*/Ž¡‘/#define–¹–CBF_BYTE_OFFSET“0x0070‘ s,/*“Byte“Offset“Compression‘8³*/Ž¡‘/#define–¹–CBF_PREDICTOR‘,Â0x0080‘ s,/*“Predictor_Huffman“Compression‘Y„*/Ž¡‘/#define–¹–CBF_NONE‘%̰0x0040‘ s,/*“No“compression“flag‘K™`*/Ž¡¡¡‘8s./*–¹–Constants“used“for“headers“*/Ž¡¡‘/#define–¹–PLAIN_HEADERS‘,Â0x0001‘ s,/*“Use“plain“ASCII“headers‘8³*/Ž¡‘/#define–¹–MIME_HEADERS‘æX0x0002‘ s,/*“Use“MIME“headers‘YÆ"*/Ž¡‘/#define–¹–MSG_NODIGEST‘æX0x0004‘ s,/*“Do“not“check“message“digests‘!*/Ž¡‘/#define–¹–MSG_DIGEST‘Y„0x0008‘ s,/*“Check“message“digests‘B&4*/Ž¡‘/#define–¹–MSG_DIGESTNOW‘,Â0x0010› s,/*“Check“message“digests“immediately˜*/Ž¡¡‘/#define–¹–HDR_DEFAULT“(MIME_HEADERS“|“MSG_NODIGEST)Ž¡¡‘/#define‘¹–MIME_NOHEADERS‘ s,PLAIN_HEADERSŽ¡¡‘8s./*–¹–CBF“vs“CIF“*/Ž¡¡‘/#define–¹–CBF‘=lž0x0000‘ s,/*“Use“simple“binary“sections‘*†F*/Ž¡‘/#define–¹–CIF‘=lž0x0001‘ s,/*“Use“MIME-encoded“binary“sections‘,Â*/Ž¡¡‘8s./*–¹–Constants“used“for“encoding“*/Ž¡¡‘/#define–¹–ENC_NONE‘%̰0x0001‘ s,/*“Use“BINARY“encoding‘PRö*/Ž¡‘/#define–¹–ENC_BASE64‘Y„0x0002‘ s,/*“Use“BASE64“encoding‘PRö*/Ž¡‘/#define–¹–ENC_QP‘/?Ü0x0004‘ s,/*“Use“QUOTED-PRINTABLE“encoding‘!*/Ž¡‘/#define–¹–ENC_BASE10‘Y„0x0008‘ s,/*“Use“BASE10“encoding‘PRö*/Ž¡‘/#define–¹–ENC_BASE16‘Y„0x0010‘ s,/*“Use“BASE16“encoding‘PRö*/Ž¡‘/#define–¹–ENC_BASE8‘!0x0020› s,/*“Use“BASE8˜encoding‘PRö*/Ž¡‘/#define–¹–ENC_FORWARD‘Ÿî0x0040‘ s,/*“Map“bytes“to“words“forward“(1234)‘,Â*/Ž¡‘/#define–¹–ENC_BACKWARD‘æX0x0080› s,/*“Map“bytes“to“words“backward“(4321)˜*/Ž¡‘/#define–¹–ENC_CRTERM‘Y„0x0100‘ s,/*“Terminate“lines“with“CR‘=lž*/Ž¡‘/#define–¹–ENC_LFTERM‘Y„0x0200‘ s,/*“Terminate“lines“with“LF‘=lž*/Ž¡¡‘/#define–¹–ENC_DEFAULT“(ENC_BASE64“|“ENC_LFTERM“|“ENC_FORWARD)Ž¡¡‘/ÊŽŽŸ[命Macro–ÕXreferenced“in“3.ŽŽŸ‘âh½Ÿô‰ff&NŸ ²J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽ’ä\June–UU5,“2007ŽŽ’û&J5ŽŽŽŽŽŽŽŽŒ‹b£ Ú ýO¸‘âh½ï3pdf:dest (page.6) [@thispage /XYZ @xpos @ypos null]Ÿüfd²3.2‘ ExceptionsŽŽŽ’ÇX CONTENTSŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH‘âh½ ýKO¸ï;pdf:dest (subsection.3.2) [@thispage /XYZ @xpos @ypos null]Ÿ ‘Ì3.2Ž‘7ÀExceptionsŽŸÝÚ‘ÅW‘ÿ:«e–Îéattempt›Îêto“catc¾9h˜the“errors˜and“pass˜them“bac¾9k˜to“p¾9ython˜as“exceptions.‘÷This˜could“still˜do“withޤ ‘a–Tlittle“wš¾9ork“to“propagage“bac˜k“the“calls“causing“the“errors.Ž© (C‘&ßüCurrenš¾9tly–ÑTthere‘ÑUare“t˜w˜o‘ÑUglobal“constan˜ts–ÑUde ned,‘Tcalled“error‘މffÆgŽ›Tymessage‘ÑTand“error‘މffÆgŽ˜status.‘PqTheseŽ¡‘are–À. lled›À/out“when˜an“error˜oAÇccurred,‘Ñ6con•¾9v“erting˜the‘À.n“umerical˜error‘À.v‘ÿ|ralue˜in“to–À.something˜the“authorŽ¡‘can‘Tread.ަ‘&ßüThere–ñ¸is›ñ¹an“implicit“assumption“that˜if“the“library“is˜used“correctly“y¾9ou“will˜not“normally“getŽ¡‘exceptions.‘Ë»This›únshould–úmbAÇe“addressed“further“in“areas“lik¾9e˜ le“op•AÇening,‘3³prop“er–úmp¾9ython“exceptionsŽ¡‘should–TbAÇe“returned.ŽŸÉP‘Êh–ŠªÅexceptionhandlingno¾9wrap‘T½6“Êi‘‘ÆŽŸ˜Ë¡¡‘/Ëstatic–¹–int“error_status“=“0;Ž¡‘/static–¹–char“error_message[1024]“;“//“hope“that“is“long“enoughŽ¡¡‘//*–¹–prototype“*/Ž¡‘/void‘¹–get_error_message(void);Ž¡¡¡‘/void‘¹–get_error_message(){Ž¡‘8s.sprintf(error_message,"%s","CBFlib‘¹–Error(s):");Ž¡‘8s.if–¹–(error_status“&“CBF_FORMAT‘%̰)Ž¡‘AæZsprintf(error_message,"%s‘¹–%s",error_message,"CBF_FORMAT‘!");Ž¡‘8s.if–¹–(error_status“&“CBF_ALLOC‘*†F)Ž¡‘AæZsprintf(error_message,"%s‘¹–%s",error_message,"CBF_ALLOC‘%̰");Ž¡‘8s.if–¹–(error_status“&“CBF_ARGUMENT‘Y„)Ž¡‘AæZsprintf(error_message,"%s‘¹–%s",error_message,"CBF_ARGUMENT‘Ÿî");Ž¡‘8s.if–¹–(error_status“&“CBF_ASCII‘*†F)Ž¡‘AæZsprintf(error_message,"%s‘¹–%s",error_message,"CBF_ASCII‘%̰");Ž¡‘8s.if–¹–(error_status“&“CBF_BINARY‘%̰)Ž¡‘AæZsprintf(error_message,"%s‘¹–%s",error_message,"CBF_BINARY‘!");Ž¡‘8s.if–¹–(error_status“&“CBF_BITCOUNT‘Y„)Ž¡‘AæZsprintf(error_message,"%s‘¹–%s",error_message,"CBF_BITCOUNT‘Ÿî");Ž¡‘8s.if–¹–(error_status“&“CBF_ENDOFDATA‘Ÿî)Ž¡‘AæZsprintf(error_message,"%s‘¹–%s",error_message,"CBF_ENDOFDATA‘æX");Ž¡‘8s.if–¹–(error_status“&“CBF_FILECLOSE‘Ÿî)Ž¡‘AæZsprintf(error_message,"%s‘¹–%s",error_message,"CBF_FILECLOSE‘æX");Ž¡‘8s.if–¹–(error_status“&“CBF_FILEOPEN‘Y„)Ž¡‘AæZsprintf(error_message,"%s‘¹–%s",error_message,"CBF_FILEOPEN‘Ÿî");Ž¡‘8s.if–¹–(error_status“&“CBF_FILEREAD‘Y„)Ž¡‘AæZsprintf(error_message,"%s‘¹–%s",error_message,"CBF_FILEREAD‘Ÿî");Ž¡‘8s.if–¹–(error_status“&“CBF_FILESEEK‘Y„)Ž¡‘AæZsprintf(error_message,"%s‘¹–%s",error_message,"CBF_FILESEEK‘Ÿî");Ž¡‘8s.if–¹–(error_status“&“CBF_FILETELL‘Y„)Ž¡‘AæZsprintf(error_message,"%s‘¹–%s",error_message,"CBF_FILETELL‘Ÿî");Ž¡‘8s.if–¹–(error_status“&“CBF_FILEWRITE‘Ÿî)Ž¡‘AæZsprintf(error_message,"%s‘¹–%s",error_message,"CBF_FILEWRITE‘æX");Ž¡‘8s.if–¹–(error_status“&“CBF_IDENTICAL‘Ÿî)Ž¡‘AæZsprintf(error_message,"%s‘¹–%s",error_message,"CBF_IDENTICAL‘æX");Ž¡‘8s.if–¹–(error_status“&“CBF_NOTFOUND‘Y„)Ž¡‘AæZsprintf(error_message,"%s‘¹–%s",error_message,"CBF_NOTFOUND‘Ÿî");Ž¡‘8s.if–¹–(error_status“&“CBF_OVERFLOW‘Y„)Ž¡‘AæZsprintf(error_message,"%s‘¹–%s",error_message,"CBF_OVERFLOW‘Ÿî");Ž¡‘8s.if–¹–(error_status“&“CBF_UNDEFINED‘Ÿî)Ž¡‘AæZsprintf(error_message,"%s‘¹–%s",error_message,"CBF_UNDEFINED‘æX");Ž¡‘8s.if–¹–(error_status“&“CBF_NOTIMPLEMENTED)Ž¡‘AæZsprintf(error_message,"%s‘¹–%s",error_message,"CBF_NOTIMPLEMENTED");Ž¡‘8s.}Ž¡‘/ÊŽŽŸÍ‘½Macro–ÕXreferenced“in“3.ŽŽŸ‘âh½Ÿô‰ff&NŸ ²6ŽŽŽ’ä\June–UU5,“2007ŽŽ’Ê‚¸J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽŽŽŽŽŽŒ‹oàÚ ýO¸‘âh½ï3pdf:dest (page.7) [@thispage /XYZ @xpos @ypos null]Ÿüfd²CONTENTSŽŽŽ’ºû˜3.3‘ DoGcstringsŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘ûh¿ÅCurren•¾9tly›b'y“ou˜get˜a˜meaningful˜string˜bac“k.‘éShould˜p•AÇerhaps˜lo“ok˜in•¾9to˜de ning˜these˜as˜p“ythonޤ ‘ûh¿exception–IXclasses?‘¸|In“an¾9y“case›IW-“the“SWIG‘IKexception“handling“is“de ned˜via“the“follo¾9wing.‘¸|It“couldŽ¡‘ûh¿ha•¾9v“e–Tretained“the“old“st¾9yle“if(status“=“action)“but“then“harder“to“see“what“to“return...Ž©µ‘ûh¿Êh–ŠªÅexceptionhandlingto¾9wrap‘T½7a“Êi‘‘ÆŽŸ  ¡‘ÛëË/*–¹–Convenience“definitions“for“functions“returning“error“codes“*/Ž¡‘h¿%exception‘¹–{Ž¡‘•error_status=0;Ž¡‘•$actionŽ¡‘•if‘¹–(error_status){Ž¡‘)­get_error_message();Ž¡‘)­PyErr_SetString(PyExc_Exception,error_message);Ž¡‘)­return‘¹–NULL;Ž¡‘•}Ž¡‘h¿}Ž¡¡‘h¿/*–¹–Retain“notation“from“cbf“lib“but“pass“on“as“python“exception“*/Ž¡¡‘h¿#define–¹–cbf_failnez(x)“{(error_status“=“x);}Ž¡¡‘h¿/*–¹–printf("Called“\"x\",“status“%d\n",error_status);}“*/Ž¡¡‘h¿#define–¹–cbf_onfailnez(x,c)“{int“err;“err“=“(x);“if“(err)“{“fprintf“(stderr,“\Ž¡‘y[£"\nCBFlib–¹–error“%d“in“\"x\"\n",“err);“\Ž¡’‡ˆe{–¹–c;“}“return“err;“}}Ž¡‘h¿ÊŽŽŸ ãW‘ûh¿½Macro–ÕXreferenced“in“3.Ž‘âh½Ÿ „£ï;pdf:dest (subsection.3.3) [@thispage /XYZ @xpos @ypos null]Ÿ‘Ì3.3Ž‘7ÀDo`cstringsŽŸÏþ‘ÅW‘ÿ:«e–çattempt›çto“parse˜the“text˜in“CBFlib.rtf˜automatically“to˜generate“the˜doAÇcstrings“and˜most“ofŽ¡‘the–J®wrappAÇers.‘¼€In“order›J¯to“do˜this“w¾9e˜made“a“ le˜called“CBFlib.txt˜via“a˜cop¾9y+paste“of˜the“rtfŽ¡‘ le–ëSto›ëTget“it˜in“ascii“format.‘žoThat“ le˜w¾9as“edited“to˜put“a˜";"“on“the˜end“the˜function“de nitionŽ¡‘(cbf‘މffÆgŽ–Tyset‘މffÆgŽ“curren¾9t‘މffÆgŽ“timestamp),‘úäalso–ôGto“add›ôHa“*“for˜the“last“argumen¾9t˜of“cbf‘މffÆgŽ–Tyget‘މffÆgŽ“rotation‘މffÆgŽ“axis.‘lReplacedŽ¡‘the–Æangstrom“symš¾9bAÇol“b˜y‘Æthe“w˜ord“angstrom“to“suppress“a“p˜ython‘Æw˜arning“abAÇout“c˜haracter“encoAÇdingsŽ¡‘and–Talso“replaced“all“the“nice“quote“marks“(\\"")“with“normal“ones.Ž¡‘&ßüThis–ýétext“doAÇcumenš¾9t“is“then“parsed“b˜y“a‘ýèp˜ython“script“called“mak˜e‘މffÆgŽ‘Typ˜ycbf.p˜y“to“generate“the“.iŽ¡‘ les–>whicš¾9h‘?are“included“b˜y“the›?swig“wrappAÇer“generator.‘à/Unfortunately“this“more˜complicated“forŽ¡‘non-pš¾9ython–Tusers“but“seemed“less“error“prone“and“in˜v˜olv˜ed“less“t˜yping“for“the“author.Ž¡‘&ßüThe– 9actual“co•AÇde› 8wrapp“ers– 9and“doAÇcstrings“are“generated˜in“later“sections“via“a˜class“o ering“aŽ¡‘"wrap"–TmethošAÇd“and“a“"get‘މffÆgŽ‘Tyco˜de"“metho˜d.ަ‘Ë"make_pycbf.py"‘T½7b‘ÕXÊŽŸ  ¡‘/Ëprint‘¹–"\\begin{verbatim}"Ž¡‘/print–¹–"This“output“comes“from“make_pycbf.py“which“generates“the“wrappers"Ž¡¡‘/#–¹–Get“the“ascii“text“as“a“list“of“stringsŽ¡‘/lines–¹–=“open("CBFlib.txt","r").readlines()Ž¡¡‘/#–¹–Variables“to“hold“the“useful“things“we“find“in“the“fileŽ¡‘/docstring–¹–=“"\n"Ž¡‘/name=""Ž¡¡‘/#–¹–Flag“to“indicate“we“have“not“read“anything“useful“yetŽ¡‘/on=0Ž¡¡‘/#–¹–Dictionary“of“function“prototypes“and“documentation,“keyed“by“name“in“C.Ž¡‘/name_dict–¹–=“{}Ž¡‘/i=-1Ž¡‘/debug–¹–=“0Ž¡‘/#–¹–Parse“the“textŽ¡‘/while‘¹–i=0“and“on==1:Ž¡‘-ÂCon=10–¹–#“Only“try“for“ten“lines“after“it“say“PROTOTYPEŽ¡‘-ÂCcontinueŽ¡‘•if–¹–line.find("#include")>=0:“#“why?Ž¡‘-ÂCcontinueŽ¡‘•if–¹–line.find("int“cbf_")>=0:“#“We“found“a“functionŽ¡‘-ÂC#–¹–keep“going“up“to“DESCRIPTIONŽ¡‘-ÂCprototypes=""+lines[i].rstrip()+"‘¹–"Ž¡‘-ÂCcheck=0Ž¡‘-ÂCwhile‘¹–lines[i+1].find("DESCRIPTION")==-1:Ž¡‘;ïi=i+1Ž¡‘;ïprototypes+=lines[i].rstrip()+"–¹–"“#“lose“the“\nŽ¡‘;ïcheck+=1Ž¡‘;ïif‘¹–check>20:Ž¡‘JÇraise–¹–Exception("Runaway“prototype“"+prototypes)Ž¡‘-ÂCon=1–¹–#“Keep“reading“docstringŽ¡‘-ÂCcontinueŽ¡‘•if–¹–on“>“1:“#“why?Ž¡‘-ÂCon=on-1Ž¡‘•if–¹–line.find("3.“File“format")>=0“and“on==1:Ž¡‘-ÂC#–¹–Stop“processing“at“section“3Ž¡‘-ÂCi=len(lines)Ž¡‘•if‘¹–on==1:Ž¡‘-ÂC#–¹–Docstring“ends“at“2.xxx“for“next“function“or“see“alsoŽ¡‘-ÂC#–¹–We“are“losing“the“see“also“information“for“now“(needed“the“sectionŽ¡‘-ÂC#–¹–breaks“in“the“rtf“file)Ž¡‘-ÂCif‘¹–len(line.strip())==0:Ž¡‘;ïdocstring+="\n"Ž¡‘;ïcontinueŽ¡‘-ÂCelse:Ž¡‘;ïif‘¹–docstring[-1]=="\n":Ž¡‘JÇdocstring–¹–+=“line.lstrip().rstrip()Ž¡‘;ïelse:Ž¡‘JÇdocstring–¹–=docstring+"“"+line.lstrip().rstrip()Ž¡‘-ÂCif–¹–line.strip()[0]“in“[str(j)“for“j“in“range(9)]“or“\Ž¡‘JÇline.find("SEE–¹–ALSO")>=0“or\Ž¡‘JÇline.find("________")>=0:Ž¡‘;ïif‘¹–len(docstring)>0:Ž¡‘JÇdocstring–¹–=“docstring.replace("\"",“"\\\"")“#“escape“the“quotesŽ¡‘JÇfor–¹–prototype“in“prototypes.strip().split(";")[:-1]:Ž¡‘]name–¹–=“prototype.split("(")[0].strip()Ž¡‘]cname–¹–=“name.split()[1].strip()Ž¡‘]prototype–¹–=“prototype.strip()+";"Ž¡‘]name_dict[cname]=[prototype,docstring]Ž¡‘-ÂC#‘ s,print–¹–"Found“",prototypeŽ¡‘JÇdocstring="\n"Ž¡‘JÇprototype=""Ž¡‘JÇcname=""Ž¡‘JÇon=0Ž¡‘;ïelse:Ž¡‘JÇraise–¹–Exception("bad“docstring")Ž¡¡¡¡‘h¿#–¹–End“of“CBFlib.txt“file“-“now“generate“wrapper“code“for“swigŽ¡¡‘h¿Êh–ŠªÅdoAÇcstringwrite‘T½9“ÊiŽŽ¡‘h¿h–ŠªÅcbfhandlewrappAÇer‘T½11“ÊiŽŽ¡¡‘h¿Ëcbf_handle_wrapper–¹–=“cbfhandlewrapper()ŽŽŸ‘âh½Ÿô‰ff&NŸ ²8ŽŽŽ’ä\June–UU5,“2007ŽŽ’Ê‚¸J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽŽŽŽŽŽŒ‹ ‹ð Ú ýO¸‘âh½ï3pdf:dest (page.9) [@thispage /XYZ @xpos @ypos null]Ÿüfd²CONTENTSŽŽŽ’ºû˜3.3‘ DoGcstringsŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸¤ ‘h¿Êh–ŠªÅcbfgoniometerwrappAÇer‘T½24“ÊiŽŽ¡¡‘h¿Ëcbf_goniometer_wrapper–¹–=“cbfgoniometerwrapper()Ž¡¡‘h¿Êh–ŠªÅcbfdetectorwrappAÇer‘T½26“ÊiŽŽ¡¡‘h¿Ëcbf_detector_wrapper–¹–=“cbfdetectorwrapper()Ž¡¡‘h¿Êh–ŠªÅgenericwrappAÇer‘T½10b“ÊiŽŽ¡¡‘h¿Ëgeneric_wrapper–¹–=“genericwrapper()Ž¡¡‘h¿def‘¹–generate_wrappers(name_dict):Ž¡‘•names–¹–=“name_dict.keys()Ž¡‘•for–¹–cname“in“names:Ž¡‘-ÂCprototype–¹–=“name_dict[cname][0]Ž¡‘-ÂCdocstring–¹–=“name_dict[cname][1]Ž¡‘-ÂC#–¹–Check“prototype“begins“with“"int“cbf_"Ž¡‘-ÂCif–¹–prototype.find("int“cbf_")!=0:Ž¡‘;ïprint–¹–"problem“with:",prototypeŽ¡‘-ÂC#–¹–Get“arguments“from“prototypesŽ¡‘-ÂCtry:Ž¡‘;ïargs–¹–=“prototype.split("(")[1].split(")")[0].split(",")Ž¡‘;ïargs–¹–=“[“s.lstrip().rstrip()“for“s“in“args“]“#“strip“spaces“off“endsŽ¡‘-ÂCexcept:Ž¡‘;ïprint‘¹–cnameŽ¡‘;ïprint‘¹–prototypeŽ¡‘;ïraiseŽ¡‘-ÂCif–¹–args[0].find("cbf_handle")>=0:“#“This“is“for“the“cbfhandle“objectŽ¡‘;ïcbf_handle_wrapper.wrap(cname,prototype,args,docstring)Ž¡‘;ïcontinueŽ¡‘-ÂCif–¹–args[0].find("cbf_goniometer")>=0:“#“This“is“for“the“cbfgoniometerŽ¡‘;ïcbf_goniometer_wrapper.wrap(cname,prototype,args,docstring)Ž¡‘;ïcontinueŽ¡‘-ÂCif–¹–args[0].find("cbf_detector")>=0:“#“This“is“for“the“cbfdetectorŽ¡‘;ïcbf_detector_wrapper.wrap(cname,prototype,args,docstring)Ž¡‘;ïcontinueŽ¡‘-ÂCgeneric_wrapper.wrap(cname,prototype,args,docstring)Ž¡¡¡‘h¿generate_wrappers(name_dict)Ž¡‘h¿open("cbfgoniometerwrappers.i","w").write(cbf_goniometer_wrapper.get_code())Ž¡‘h¿open("cbfdetectorwrappers.i","w").write(cbf_detector_wrapper.get_code())Ž¡‘h¿open("cbfhandlewrappers.i","w").write(cbf_handle_wrapper.get_code())Ž¡‘h¿open("cbfgenericwrappers.i","w").write(generic_wrapper.get_code())Ž¡¡‘h¿print–¹–"End“of“output“from“make_pycbf.py"Ž¡‘h¿print‘¹–"\\end{verbatim}"Ž¡¡‘h¿ÊŽŽŸ«‘ûh¿ÅA–™little“helpšAÇer–šfunction“called‘™do˜cstringwriter“is“used›™to“try“to˜format“the“doAÇcumen¾9tation˜giving“theŽ¡‘ûh¿p¾9ython–Tcalling“sequence“and“return“v‘ÿ|ralue(s).ŽŸ.ô‘ûh¿Êh–ŠªÅdoAÇcstringwrite‘T½9“Êi‘‘ÆŽŸ ÕÇ¡‘h¿h–ŠªÅm¾9yformat‘T½10a“ÊiŽŽ¡¡‘h¿Ëdef‘¹–docstringwrite(pyfunc,input,output,prototype,cbflibdoc):Ž¡‘•doc–¹–=“"%feature(\"autodoc\",“\"\nReturns“:“"Ž¡‘•returns–¹–=“""Ž¡‘•for–¹–out“in“output:Ž¡‘-ÂCreturns–¹–+=“out+","ŽŽŸ‘âh½Ÿô‰ff&NŸ ²J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽ’ä\June–UU5,“2007ŽŽ’û&J9ŽŽŽŽŽŽŽŽŒ‹ •K Ú ýO¸‘âh½ï4pdf:dest (page.10) [@thispage /XYZ @xpos @ypos null]Ÿüfd²3.4‘ A–UUgeneric“wrappGerŽŽŽ’ÇX CONTENTSŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘•Ëif‘¹–len(returns)>0:ޤ ‘-ÂCdoc–¹–+=“myformat(returns[:-1],70,indent“=“10,breakon=",")Ž¡‘•else:Ž¡‘-ÂCdoc–¹–+=“"\n"Ž¡‘•doc–¹–+=“"*args‘,Â:“"Ž¡‘•takes–¹–=“""Ž¡‘•for–¹–inp“in“input:Ž¡‘-ÂCtakes–¹–+=“inp+","Ž¡‘•if‘¹–len(takes)>0:Ž¡‘-ÂCdoc–¹–+=“myformat(takes[:-1],70,indent“=“10,breakon=",")Ž¡‘•else:Ž¡‘-ÂCdoc–¹–+=“"\n"Ž¡‘•doc–¹–+=“"\nC“prototype:“"+myformat(prototype,65,indent=16,breakon=",")Ž¡‘•doc–¹–+=“"\nCBFLib“documentation:\n"+myformat(cbflibdoc,70)+"\")"Ž¡‘•doc–¹–+=“pyfunc+";\n"Ž¡‘•return‘¹–docŽ¡‘h¿ÊŽŽŸ Ûú‘ûh¿½Macro–ÕXreferenced“in“7b.ŽŸ‘ûh¿ÅFinally–4Ra›4Slittle“function“to“break˜lines“at“the“ rst˜space“bAÇefore“n“c¾9haracters˜is“hit“as“the˜p¾9ython“doAÇcŽ¡‘ûh¿formatting–TtoAÇols“don't“seem“to“do“that.Ž ºm> ÿVxâ‘ûh¿Êh–ŠªÅm¾9yformat‘T½10a“Êi‘‘ÆŽŸ ¡‘hÁËdef–¹–myformat(s,l,indent=0,breakon="“"):Ž¡‘"•ƒ"""Ž¡‘"•ƒTry–¹–to“pretty“print“lines“-“this“is“a“pain...Ž¡‘"•ƒ"""Ž¡‘"•ƒlines–¹–=“s.rstrip().split("\n")Ž¡‘"•ƒout=""Ž¡‘"•ƒfor–¹–line“in“lines:Ž¡‘0ÂEif‘¹–len(line)==0:Ž¡‘>ïcontinue–¹–#“skip“blank“linesŽ¡‘0ÂEif‘¹–len(line)>l:Ž¡‘>ïwords–¹–=“line.split(breakon)Ž¡‘>ïnewline=words[0]Ž¡‘>ïif‘¹–len(words)>1:Ž¡‘MÉfor–¹–word“in“words[1:]:Ž¡‘[H‹if–¹–len(newline)+len(word)+1“<“l:Ž¡‘iuMnewline=newline+breakon+wordŽ¡‘[H‹else:Ž¡‘iuMout–¹–=“out+newline+breakon+"\n"+indent*"“"Ž¡‘iuMnewline=wordŽ¡‘MÉout–¹–+=“newline+"\n"Ž¡‘>ïelse:Ž¡‘MÉout–¹–+=“"\n"Ž¡‘0ÂEelse:Ž¡‘>ïout–¹–+=“line+"\n"“#“Last“oneŽ¡‘"•ƒif–¹–out“==“"":Ž¡‘0ÂEreturn‘¹–"\n"Ž¡‘"•ƒelse:Ž¡‘0ÂEreturn‘¹–outŽ¡‘hÁÊŽŽŸ .:‘ûh¿½Macro–ÕXreferenced“in“9.ŽŽŽ‘âh½ ºÿyï;pdf:dest (subsection.3.4) [@thispage /XYZ @xpos @ypos null]Ÿ œô‘Ì3.4Ž‘7ÀA–€generic“wrapp`erŽŸO ‘ÅThere–”ýare›”üa“few“utilit¾9y˜functions“whic¾9h“do˜not“w¾9ork“on“one˜of“the“three˜expAÇosed“ob‘ƒŽjects“in˜the“library‘ÿ:«,Ž¡‘these–Tare“wrappAÇed“here:ŽŸf!‘Êh–ŠªÅgenericwrappAÇer‘T½10b“Êi‘‘ÆŽŸ öá¡¡‘/Ëclass‘¹–genericwrapper:ŽŽŸ‘âh½Ÿô‰ff&NŸ ²10ŽŽŽ’ä\June–UU5,“2007ŽŽ’Ê‚¸J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽŽŽŽŽŽŒ‹ Ÿ¨ Ú ýO¸‘âh½ï4pdf:dest (page.11) [@thispage /XYZ @xpos @ypos null]Ÿüfd²CONTENTSŽŽŽ’±Â²3.5‘ CBFHandlesŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘•Ëdef‘¹–__init__(self):ޤ ‘2{Ùself.code–¹–=“"//“Start“of“generic“functions\n"Ž¡‘2{Ùself.tail–¹–=“"//“End“of“generic“functions\n"Ž¡‘•def‘¹–get_code(self):Ž¡‘2{Ùreturn–¹–self.code“+“self.tailŽ¡‘•def‘¹–wrap(self,cfunc,prototype,args,docstring):Ž¡‘2{Ùpyfunc–¹–=“cfunc.replace("cbf_","")Ž¡‘2{Ù#–¹–Insert“a“comment“for“debugging“this“scriptŽ¡‘2{Ùcode–¹–=“"\n/*“cfunc“%s‘,Âpyfunc“%s‘ s,\n"%(cfunc,pyfunc)Ž¡‘2{Ùfor–¹–a“in“args:Ž¡‘Eb1code–¹–+=“"‘,Âarg“%s“"%(a)Ž¡‘2{Ùcode–¹–+=“"*/\n\n"Ž¡‘2{Ùself.code+=codeŽ¡‘2{Ùcode–¹–=“""Ž¡‘2{Ùif–¹–len(args)==1“and“args[0].find("char")>-1“and“\Ž¡’û‘args[0].find("**")>-1‘K™`:#–¹–return“stringŽ¡‘Eb1#–¹–first“write“the“c“code“and“inline“itŽ¡‘Eb1code–¹–+=“docstringwrite(pyfunc,[],["string"],prototype,docstring)Ž¡‘Eb1code–¹–+=“"%%inline“%%{\n‘,Âchar*“%s(void);\n"%(pyfunc)Ž¡‘Eb1code–¹–+=“"‘,Âchar*“%s(void){\n"%(pyfunc)Ž¡‘Eb1code–¹–+=“"‘Y„char“*r;\n"Ž¡‘Eb1code–¹–+=“"‘Y„error_status“=“%s(&r);\n"%(cfunc)Ž¡‘Eb1code–¹–+=“"‘Y„return“r;“}\n%}\n"Ž¡‘Eb1#–¹–now“the“thing“to“wrap“is:Ž¡‘Eb1code–¹–+=“"char*“%s(void);"%(pyfunc)Ž¡‘Eb1self.code=self.code+codeŽ¡‘Eb1returnŽ¡¡‘h¿#‘!code+=–¹–"‘Ÿîvoid“%s(void){\n"%(pyfunc)Ž¡‘h¿#‘!code‘¹–+="‘%̰cbf_failnez(CBF_NOTIMPLEMENTED);}\n"Ž¡‘h¿#‘!self.code=self.code+codeŽ¡‘2{Ùprint–¹–"Have“not“implemented:"Ž¡‘2{Ùfor–¹–s“in“[cfunc,“pyfunc]“+“args:Ž¡‘Eb1print‘¹–"\t",sŽ¡‘2{ÙprintŽ¡‘2{ÙreturnŽ¡¡‘h¿ÊŽŽŸ R‘ûh¿½Macro–ÕXreferenced“in“7b.Ž‘âh½Ÿ |ï;pdf:dest (subsection.3.5) [@thispage /XYZ @xpos @ypos null]Ÿ:Ù‘Ì3.5Ž‘7ÀCBFHandlesŽŸ8r‘ÅA‘ÿFcif–ÿL le“seems“to“bšAÇe“represen¾9ted“and“accessed“in“the“library“via“a“p˜oin¾9ter“to“a“cbf‘މffÆgŽ–Tyhandle‘މffÆgŽ“structure.ŽŸ :Ú‘&ßüThere–@are›@lots“of“functions˜whicš¾9h“ha˜v˜e“suc˜h›@a“thing“as“their˜ rst“argumen¾9t.‘ž"They“are˜brok¾9en“upŽ¡‘here–Taccording“to“there“input“and“output“argumen¾9ts.ŽŸ&>‘Êh–ŠªÅcbfhandlewrappAÇer‘T½11“Êi‘‘ÆŽŸ С¡‘/h–ŠªÅcbfhandlespAÇecials‘T½14“ÊiŽŽ¡¡‘/Ëclass‘¹–cbfhandlewrapper:Ž¡‘=,Ädef‘¹–__init__(self):Ž¡‘KY†self.code–¹–=“"""Ž¡‘///–¹–Tell“SWIG“not“to“make“constructor“for“these“objectsŽ¡‘/%nodefault‘¹–cbf_handle;Ž¡‘/%nodefault‘¹–cbf_handle_struct;Ž¡‘/%nodefault‘¹–cbf_node;Ž¡¡‘///–¹–A“couple“of“blockitem“functions“return“CBF_NODETYPEŽ¡‘/typedef‘¹–enumŽ¡‘/{Ž¡‘8s.CBF_UNDEFINED,‘%̰/*–¹–Undefined“*/ŽŽŸ‘âh½Ÿô‰ff&NŸ ²J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽ’ä\June–UU5,“2007ŽŽ’ö&J11ŽŽŽŽŽŽŽŽŒ‹ ¨Ë Ú ýO¸‘âh½ï4pdf:dest (page.12) [@thispage /XYZ @xpos @ypos null]Ÿüfd²3.5‘ CBFHandlesŽŽŽ’ÇX CONTENTSŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘ÛëËCBF_LINK,‘=lž/*‘¹–Link‘Y„*/ޤ ‘ÛëCBF_ROOT,‘=lž/*‘¹–Root‘Y„*/Ž¡‘ÛëCBF_DATABLOCK,‘%̰/*–¹–Datablock“*/Ž¡‘ÛëCBF_SAVEFRAME,‘%̰/*–¹–Saveframe“*/Ž¡‘ÛëCBF_CATEGORY,‘*†F/*‘¹–Category‘ s,*/Ž¡‘ÛëCBF_COLUMN‘8³/*‘¹–Column‘æX*/Ž¡‘h¿}Ž¡‘h¿CBF_NODETYPE;Ž¡¡¡‘h¿//–¹–Tell“SWIG“what“the“object“is,“so“we“can“build“the“classŽ¡¡‘h¿typedef‘¹–structŽ¡‘h¿{Ž¡‘Ûëcbf_node‘¹–*node;Ž¡¡‘Ûëint–¹–row,“search_row;Ž¡‘h¿}‘ s,cbf_handle_struct;Ž¡¡‘h¿typedef–¹–cbf_handle_struct“*cbf_handle;Ž¡¡‘h¿typedef–¹–cbf_handle_struct“handle;Ž¡‘h¿%feature("autodoc","1");Ž¡¡‘h¿%extend–¹–cbf_handle_struct{‘,Â//“Tell“SWIG“to“attach“functions“to“the“structureŽ¡¡‘$Ocbf_handle_struct(){‘ s,//‘¹–ConstructorŽ¡‘2{Ùcbf_handle‘¹–handle;Ž¡‘2{Ùcbf_failnez(cbf_make_handle(&handle));Ž¡‘2{Ùreturn‘¹–handle;Ž¡‘2{Ù}Ž¡¡‘$O~cbf_handle_struct(){–¹–//“DestructorŽ¡‘2{Ùcbf_failnez(cbf_free_handle(self));Ž¡‘2{Ù}Ž¡‘h¿"""Ž¡‘-ÂCself.tail–¹–=“"""Ž¡‘h¿};–¹–//“End“of“cbf_handle_structŽ¡‘h¿"""Ž¡‘•#–¹–End“of“init“functionŽ¡‘•def‘¹–get_code(self):Ž¡‘2{Ùreturn‘¹–self.code+self.tailŽ¡‘•def‘¹–wrap(self,cfunc,prototype,args,docstring):Ž¡‘2{Ùpyfunc–¹–=“cfunc.replace("cbf_","")Ž¡‘2{Ù#–¹–Insert“a“comment“for“debugging“this“scriptŽ¡‘2{Ùcode–¹–=“"\n/*“cfunc“%s‘,Âpyfunc“%s‘ s,\n"%(cfunc,pyfunc)Ž¡‘2{Ùfor–¹–a“in“args:Ž¡‘@¨›code–¹–+=“"‘,Âarg“%s“"%(a)Ž¡‘2{Ùcode–¹–+=“"*/\n\n"Ž¡‘2{Ù#–¹–Make“and“free“handle“are“done“in“the“header“so“skipŽ¡‘2{Ùif–¹–cfunc.find("cbf_make_handle")>-1“or“cfunc.find("cbf_free_handle")>-1:Ž¡‘@¨›#–¹–Constructor“and“destructor“done“in“headersŽ¡‘@¨›returnŽ¡‘2{Ùif–¹–args[0]“!=“"cbf_handle“handle":“#“Must“be“for“cbfhandleŽ¡‘@¨›print‘¹–"problem",cfunc,pyfunc,argsŽ¡‘@¨›returnŽ¡‘2{Ùif–¹–len(args)==1:“#“Only“takes“CBFhandle“argŽ¡‘@¨›code+=‘¹–docstringwrite(pyfunc,[],[],prototype,docstring)Ž¡‘@¨›code+=–¹–"‘æXvoid“%s(void){\n"%(pyfunc)Ž¡‘@¨›code+=‘¹–"‘Y„cbf_failnez(%s(self));}\n"%(cfunc)Ž¡‘@¨›self.code=self.code+codeŽ¡‘@¨›returnŽ¡‘2{Ù#–¹–Now“case“by“case“rather“than“writing“a“proper“parserŽŽŸ‘âh½Ÿô‰ff&NŸ ²12ŽŽŽ’ä\June–UU5,“2007ŽŽ’Ê‚¸J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽŽŽŽŽŽŒ‹ ³t Ú ýO¸‘âh½ï4pdf:dest (page.13) [@thispage /XYZ @xpos @ypos null]Ÿüfd²CONTENTSŽŽŽ’±Â²3.5‘ CBFHandlesŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘2{ÙË#–¹–Special“cases“...ޤ ‘2{Ùnot_found=0Ž¡‘2{Ùtry:Ž¡‘Eb1code,–¹–pyname,“input,“output“=“cbfhandle_specials[cfunc]Ž¡‘Eb1self.code‘¹–+=‘ s,docstringwrite(pyname,input,output,Ž¡’êÁ³prototype,docstring)+‘¹–codeŽ¡‘Eb1returnŽ¡‘2{Ùexcept‘¹–KeyError:Ž¡‘Eb1not_found–¹–=“1Ž¡‘2{Ùexcept‘¹–ValueError:Ž¡‘Eb1print–¹–"problem“in",cfuncŽ¡‘Eb1for–¹–item“in“cbfhandle_specials[cfunc]:Ž¡‘SŽóprint‘¹–"***",itemŽ¡‘Eb1raiseŽ¡‘2{Ùif‘¹–len(args)==2:Ž¡‘@¨›if–¹–args[1].find("const“char")>-1“and“\Ž¡‘NÕ]args[1].find("*")>-1‘/?Üand‘¹–\Ž¡‘NÕ]args[1].find("**")==-1‘8³:Ž¡‘NÕ]#–¹–1“input“stringŽ¡‘NÕ]code–¹–+=“docstringwrite(pyfunc,[],["string"],prototype,docstring)Ž¡‘NÕ]code–¹–+=“"‘æXvoid“%s(const“char*“arg){\n"%(pyfunc)Ž¡‘NÕ]code‘¹–+="‘Y„cbf_failnez(%s(self,arg));}\n"%(cfunc)Ž¡‘NÕ]self.code=self.code+codeŽ¡‘NÕ]returnŽ¡‘@¨›if–¹–args[1].find("const“char")>-1“and“\Ž¡‘NÕ]args[1].find("**")>-1‘K™`:#–¹–return“stringŽ¡‘NÕ]code–¹–+=“docstringwrite(pyfunc,["string"],[],prototype,docstring)Ž¡‘NÕ]code–¹–+=“"‘æXconst“char*“%s(void){\n"%(pyfunc)Ž¡‘NÕ]code–¹–+=“"‘æXconst“char*“result;\n"Ž¡‘NÕ]code–¹–+=“"‘æXcbf_failnez(%s(self,“&result));\n"%(cfunc)Ž¡‘NÕ]code–¹–+=“"‘æXreturn“result;}\n"Ž¡‘NÕ]self.code=self.code+codeŽ¡‘NÕ]returnŽ¡‘@¨›if–¹–args[1].find("unsigned“int")>-1“and“args[1].find("*")==-1:Ž¡‘NÕ]#–¹–set“uintŽ¡‘NÕ]if‘¹–args[1].find("reserved")>-1:Ž¡‘]raise–¹–Exception("Setting“reserved???“%s“%s“%s"%(pyfunc,Ž¡’(.Qcfunc,str(args)))Ž¡‘NÕ]code–¹–+=“docstringwrite(pyfunc,["Integer"],[],prototype,docstring)Ž¡‘NÕ]code–¹–+="‘æXvoid“%s(unsigned“int“arg){\n"%(pyfunc)Ž¡‘NÕ]code‘¹–+="‘Y„cbf_failnez(%s(self,arg));}\n"%(cfunc)Ž¡‘NÕ]self.code=self.code+codeŽ¡‘NÕ]returnŽ¡‘@¨›if–¹–args[1].find("unsigned“int“*")>-1“and“args[1].find("**")==-1:Ž¡‘NÕ]#–¹–output“uintŽ¡‘NÕ]if‘¹–args[1].find("reserved")>-1:Ž¡‘]raise–¹–Exception("Setting“reserved???“%s“%s“%s"%(pyfunc,Ž¡’(.Qcfunc,str(args)))Ž¡‘NÕ]code–¹–+=“docstringwrite(pyfunc,[],["Integer"],prototype,docstring)Ž¡‘NÕ]code–¹–+="‘æXunsigned“int“%s(void){\n"%(pyfunc)Ž¡‘NÕ]code–¹–+="‘Y„unsigned“int“result;\n"Ž¡‘NÕ]code‘¹–+="‘Y„cbf_failnez(%s(self,&result));\n"%(cfunc)Ž¡‘NÕ]code–¹–+="‘Y„return“result;}\n"Ž¡‘NÕ]self.code=self.code+codeŽ¡‘NÕ]returnŽ¡‘@¨›#–¹–For“the“rest“attempt“to“guessŽ¡‘@¨›if–¹–args[1].find("cbf")==-1:“#“but“do“not“try“the“goniometer“constructorŽ¡‘NÕ]if–¹–args[1].find("*")>-1“and“args[1].find("cbf")==-1:Ž¡‘]#–¹–pointer“used“for“returning“somethingŽ¡‘]type–¹–=“args[1].split("“")[0]Ž¡‘]code–¹–+=“docstringwrite(pyfunc,[],[type.replace("*","")],Ž¡’#t»prototype,docstring)Ž¡‘]code+=–¹–"‘æX"+type+"“"+pyfunc+"(void){\n"ŽŽŸ‘âh½Ÿô‰ff&NŸ ²J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽ’ä\June–UU5,“2007ŽŽ’ö&J13ŽŽŽŽŽŽŽŽŒ‹¼» Ú ýO¸‘âh½ï4pdf:dest (page.14) [@thispage /XYZ @xpos @ypos null]Ÿüfd²3.5‘ CBFHandlesŽŽŽ’ÇX CONTENTSŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘]Ëcode+=–¹–"‘Ÿî"+type+"“result;\n"ޤ ‘]code+=‘¹–"‘!cbf_failnez(%s(self,&result));\n"%(cfunc)Ž¡‘]code+=–¹–"‘!return“result;}\n"Ž¡‘]self.code=self.code+codeŽ¡‘]returnŽ¡‘NÕ]else:Ž¡‘]var–¹–=“args[1].split("“")[-1]Ž¡‘]code–¹–+=“docstringwrite(pyfunc,[],[args[1]],prototype,docstring)Ž¡‘]code+=–¹–"‘Ÿîvoid“%s(%s){\n"%(pyfunc,args[1])Ž¡‘]code‘¹–+="‘%̰cbf_failnez(%s(self,%s));}\n"%(cfunc,var)Ž¡‘]self.code=self.code+codeŽ¡‘]returnŽ¡‘2{Ùif‘¹–not_found:Ž¡‘NÕ]code+=–¹–"‘Ÿîvoid“%s(void){\n"%(pyfunc)Ž¡‘NÕ]code‘¹–+="‘%̰cbf_failnez(CBF_NOTIMPLEMENTED);}\n"Ž¡‘NÕ]self.code=self.code+codeŽ¡‘NÕ]print–¹–"Have“not“implemented:“cbfhandle.%s"%(pyfunc)Ž¡‘NÕ]print‘¹–"‘,Â",cfuncŽ¡‘NÕ]print‘¹–"‘æXargs:"Ž¡‘NÕ]for–¹–a“in“args:Ž¡‘a»µprint‘¹–"‘!",aŽ¡‘NÕ]printŽ¡‘NÕ]returnŽ¡¡‘h¿ÊŽŽŸ5/‘ûh¿½Macro–ÕXreferenced“in“7b.Ž‘âh½Ÿ ç%ï@pdf:dest (subsubsection.3.5.1) [@thispage /XYZ @xpos @ypos null]Ÿ V~‘ó"ò"V cmbx10Í3.5.1Ž‘<#„Man®9ually–ÕTwrappQÇed“things“for“cbfhandle“ob‘£ŽjectŽŸi„‘ÅThe–Ôsimple›Õcases“whic•¾9h˜co“v“er–Ôa“lot˜of“the˜library“w¾9ere“wrappAÇed˜automatically‘ÿ:«.‘EThings˜whic¾9h“seemedŽ¡‘more–Wcomplicated“or“required“more“thoughš¾9t“are“done“here.‘á‹This“is“a“dictionary“of“coAÇde“follo˜w˜ed“b˜yŽ¡‘argumen¾9ts–Tto“the“doAÇcstringwrite“function.ŽŸ°w‘Êh–ŠªÅcbfhandlespAÇecials‘T½14“Êi‘‘ÆŽŸ #{¡‘/Ëcbfhandle_specials–¹–=“{Ž¡¡‘/"cbf_get_integerarrayparameters":["""Ž¡‘/%apply–¹–int“*OUTPUT“{int“*compression,int“*binary_id,Ž¡’ºint–¹–*elsize,“int“*elsigned,“int“*elunsigned,Ž¡’ºint–¹–*elements,“int“*minelement,“int“*maxelement}Ž¡’„ Žget_integerarrayparameters;Ž¡¡‘AæZvoid–¹–get_integerarrayparameters(int“*compression,int“*binary_id,Ž¡’ fint–¹–*elsize,“int“*elsigned,“int“*elunsigned,Ž¡’ fint–¹–*elements,“int“*minelement,“int“*maxelement){Ž¡‘T̲unsigned‘¹–int‘ s,comp;Ž¡‘T̲size_t–¹–elsiz,“elem;Ž¡‘T̲cbf_failnez(cbf_get_integerarrayparameters(self,Ž¡‘Y†H&comp,binary_id,–¹–&elsiz,“elsigned,“elunsigned,“&elem,Ž¡‘^?Þminelement,‘¹–maxelement));Ž¡‘T̲*compression–¹–=“comp;“/*“FIXME“-“does“this“convert“in“C?“*/Ž¡‘T̲*elsize–¹–=“elsiz;Ž¡‘T̲*elements–¹–=“elem;Ž¡‘T̲}Ž¡‘/""","get_integerarrayparameters",[],["int–¹–compression","int“binary_id",Ž¡‘FŸð"int–¹–elsize",“"int“elsigned",“"int“elunsigned",Ž¡‘FŸð"int–¹–elements",“"int“minelement",“"int“maxelement"]],Ž¡¡¡‘/"cbf_get_realarrayparameters":["""Ž¡‘/%apply–¹–int“*OUTPUT“{int“*compression,int“*binary_id,Ž¡’ºint–¹–*elsize,“int“*elements}“get_realarrayparameters;ŽŽŸ‘âh½Ÿô‰ff&NŸ ²14ŽŽŽ’ä\June–UU5,“2007ŽŽ’Ê‚¸J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽŽŽŽŽŽŒ‹Èm Ú ýO¸‘âh½ï4pdf:dest (page.15) [@thispage /XYZ @xpos @ypos null]Ÿüfd²CONTENTSŽŽŽ’±Â²3.5‘ CBFHandlesŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸¤ ¡‘$OËvoid–¹–get_realarrayparameters(int“*compression,int“*binary_id,Ž¡’­Uint–¹–*elsize,“int“*elements){Ž¡‘75ounsigned‘¹–int‘ s,comp;Ž¡‘75osize_t–¹–elsiz,“elem;Ž¡‘75ocbf_failnez(cbf_get_realarrayparameters(self,Ž¡’­U&comp–¹–,binary_id,“&elsiz,“&elem“));Ž¡‘75o*compression–¹–=“comp;“/*“FIXME“-“does“this“convert“in“C?“*/Ž¡‘75o*elsize–¹–=“elsiz;Ž¡‘75o*elements–¹–=“elem;Ž¡‘75o}Ž¡‘h¿""","get_realarrayparameters",[],["int–¹–compression","int“binary_id",Ž¡‘)­"int–¹–elsize",“"int“elements"]],Ž¡¡¡¡‘h¿"cbf_get_integerarray":["""Ž¡‘h¿//–¹–Ensure“we“free“the“local“temporaryŽ¡¡‘h¿%cstring_output_allocate_size(char–¹–**“s,“int“*slen,“free(*$1))Ž¡‘2{Ùget_integerarray_as_string;Ž¡¡‘h¿//–¹–Get“the“length“correctŽ¡¡‘$Ovoid–¹–get_integerarray_as_string(char“**s,“int“*slen){Ž¡‘75oint–¹–binary_id,“elsigned,“elunsigned;Ž¡‘75osize_t–¹–elements,“elements_read,“elsize;Ž¡‘75oint–¹–minelement,“maxelement;Ž¡‘75ounsigned–¹–int“compression;Ž¡‘75ovoid–¹–*“array;Ž¡‘75o*slen–¹–=“0;“/*“Initialise“in“case“of“problems“*/Ž¡‘75ocbf_failnez(cbf_get_integerarrayparameters(self,‘¹–&compression,Ž¡‘XH‰&binary_id,–¹–&elsize,“&elsigned,“&elunsigned,Ž¡‘XH‰&elements,–¹–&minelement,“&maxelement));Ž¡¡‘75oif–¹–((array=malloc(elsize*elements)))“{Ž¡‘SŽó/*–¹–cbf_failnez“(cbf_select_column(cbf,colnum))“*/Ž¡‘XH‰cbf_failnez–¹–(cbf_get_integerarray(self,“&binary_id,Ž¡’•µ'(void–¹–*)array,“elsize,“elsigned,Ž¡’•µ'elements,‘¹–&elements_read));Ž¡¡‘;ï}else{Ž¡‘XH‰cbf_failnez(CBF_ALLOC);Ž¡‘;ï}Ž¡‘75o*slen–¹–=“elsize*elements;Ž¡‘75o*s–¹–=“(char“*)“array;Ž¡‘-ÂC}Ž¡‘h¿""","get_integerarray_as_string",[],["(Binary)String"]‘¹–],Ž¡¡‘h¿"cbf_set_integerarray":["""Ž¡‘$O/*–¹–CBFlib“must“NOT“modify“the“data“string“which“belongs“to“the“scriptingŽ¡‘2{Ùlanguage–¹–we“will“get“and“check“the“length“via“a“typemap“*/Ž¡¡‘h¿%apply–¹–(char“*STRING,“int“LENGTH)“{“(char“*data,“int“len)“}“set_integerarray;Ž¡¡‘$Ovoid–¹–set_integerarray(unsigned“int“compression,“int“binary_id,Ž¡‘NÕ]char–¹–*data,“int“len,“int“elsize,“int“elsigned,“int“elements){Ž¡‘75o/*–¹–safety“check“on“args“*/Ž¡‘75osize_t–¹–els,“ele;Ž¡‘75ovoid‘¹–*array;Ž¡‘75oif(len–¹–==“elsize*elements){Ž¡‘Eb1array–¹–=“data;ŽŽŸ‘âh½Ÿô‰ff&NŸ ²J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽ’ä\June–UU5,“2007ŽŽ’ö&J15ŽŽŽŽŽŽŽŽŒ‹ÓÇ Ú ýO¸‘âh½ï4pdf:dest (page.16) [@thispage /XYZ @xpos @ypos null]Ÿüfd²3.5‘ CBFHandlesŽŽŽ’ÇX CONTENTSŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘Eb1Ëels–¹–=“elsize;ޤ ‘Eb1ele–¹–=“elements;Ž¡‘Eb1cbf_failnez(cbf_set_integerarray–¹–(self,“compression,“binary_id,Ž¡‘Eb1(void–¹–*)“data,‘ s,(size_t)“elsize,“elsigned,“(size_t)“elements));Ž¡‘75o}else{Ž¡‘Eb1cbf_failnez(CBF_ARGUMENT);Ž¡‘75o}Ž¡‘$O}Ž¡‘h¿""","set_integerarray",Ž¡‘h¿[–¹–"int“compression",“"int“binary_id","(binary)“String“data",Ž¡‘"U"int–¹–elsize",“"int“elsigned","int“elements"],[]],Ž¡¡¡‘h¿"cbf_get_image_size":‘¹–["""Ž¡‘h¿%apply–¹–int“*OUTPUT“{int“*ndim1,“int“*ndim2}“get_image_size;Ž¡‘)­void–¹–get_image_size(unsigned“int“element_number,“int“*ndim1,“int“*ndim2){Ž¡‘75ounsigned–¹–int“reserved;Ž¡‘75osize_t–¹–in1,“in2;Ž¡‘75oreserved–¹–=“0;Ž¡‘75ocbf_failnez(cbf_get_image_size(self,reserved,element_number,&in1,&in2));Ž¡‘75o*ndim1–¹–=“in1;“/*“FIXME“-“is“that“how“to“convert?“*/Ž¡‘75o*ndim2–¹–=“in2;Ž¡‘75o}Ž¡‘h¿""","get_image_size",["Integer–¹–element_number"],["size_t“ndim1","size_t“ndim2"]],Ž¡¡¡¡‘h¿"cbf_get_pixel_size"–¹–:“["""Ž¡‘h¿%apply–¹–double“*OUTPUT“{double“*psize}“get_pixel_size;Ž¡‘$Ovoid–¹–get_pixel_size(unsigned“int“element_number,Ž¡’‚ÎÏunsigned–¹–int“axis_number,“double“*psize){Ž¡‘75ocbf_failnez(cbf_get_pixel_size(self,Ž¡’É®™element_number,Ž¡’É®™axis_number,Ž¡’É®™psize));Ž¡‘$O}Ž¡‘h¿""","get_pixel_size",["Int–¹–element_number","Int“axis_number"],Ž¡‘t¢ ["Float–¹–pixel_size"]]“,Ž¡¡¡¡‘h¿"cbf_set_pixel_size":["""Ž¡‘)­void–¹–set_pixel_size“(unsigned“int“element_number,Ž¡’ŒAûunsigned–¹–int“axis_number,“double“psize){Ž¡‘;ïcbf_failnez(cbf_set_pixel_size(self,Ž¡’Îh/element_number,Ž¡’Îh/axis_number,Ž¡’Îh/psize));Ž¡‘)­}Ž¡‘h¿""","set_pixel_size",Ž¡‘•["Int–¹–element_number","Int“axis_number","Float“pixel“size"],[]],Ž¡¡¡¡¡‘h¿"cbf_write_file"–¹–:“["""Ž¡‘$Ovoid–¹–write_file(const“char*“filename,“int“ciforcbf,“int“headers,Ž¡‘oèwint‘¹–encoding){Ž¡‘2{ÙFILE‘¹–*stream;Ž¡‘2{Ùint‘¹–readable;Ž¡‘2{Ù/*–¹–Make“the“file“non-0“to“make“CBFlib“close“the“file“*/Ž¡‘2{Ùreadable–¹–=“1;Ž¡‘2{Ùif–¹–(“!“(“stream“=“fopen“(filename,“"w+b"))“){ŽŽŸ‘âh½Ÿô‰ff&NŸ ²16ŽŽŽ’ä\June–UU5,“2007ŽŽ’Ê‚¸J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽŽŽŽŽŽŒ‹ݬ Ú ýO¸‘âh½ï4pdf:dest (page.17) [@thispage /XYZ @xpos @ypos null]Ÿüfd²CONTENTSŽŽŽ’±Â²3.5‘ CBFHandlesŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘;ïËcbf_failnez(CBF_FILEOPEN);ޤ ‘75o}Ž¡‘75oelse{Ž¡‘75ocbf_failnez(cbf_write_file(self,–¹–stream,“readable,Ž¡‘oèwciforcbf,–¹–headers,“encoding));Ž¡¡‘75o}Ž¡‘2{Ù}Ž¡‘h¿""","write_file",["String–¹–filename","Integer“ciforcbf","Integer“Headers",Ž¡‘fuK"Integer‘¹–encoding"],[]],Ž¡¡¡‘h¿"cbf_read_template":["""Ž¡‘$Ovoid–¹–read_template(char*“filename){Ž¡‘2{Ù/*–¹–CBFlib“needs“a“stream“that“will“remain“openŽ¡‘75ohence–¹–DO“NOT“open“from“python“*/Ž¡‘2{ÙFILE‘¹–*stream;Ž¡‘2{Ùif–¹–(“!“(“stream“=“fopen“(filename,“"rb"))“){Ž¡‘;ïcbf_failnez(CBF_FILEOPEN);Ž¡‘75o}Ž¡‘75oelse{Ž¡‘75ocbf_failnez(cbf_read_template–¹–(self,“stream));“}Ž¡‘$O}Ž¡¡‘h¿""","read_template",["String‘¹–filename"],[]],Ž¡¡¡‘h¿"cbf_read_file"–¹–:“["""Ž¡‘$Ovoid–¹–read_file(char*“filename,“int“headers){Ž¡‘2{Ù/*–¹–CBFlib“needs“a“stream“that“will“remain“openŽ¡‘@¨›hence–¹–DO“NOT“open“from“python“*/Ž¡‘2{ÙFILE‘¹–*stream;Ž¡‘2{Ùif–¹–(“!“(“stream“=“fopen“(filename,“"rb"))“){Ž¡‘;ïcbf_failnez(CBF_FILEOPEN);Ž¡‘75o}Ž¡‘75oelse{Ž¡‘;ïcbf_failnez(cbf_read_file(self,–¹–stream,“headers));Ž¡‘$O}Ž¡‘2{Ù}Ž¡‘h¿""","read_file",["String–¹–filename","Integer“headers"],[]],Ž¡¡¡‘h¿"cbf_set_doublevalue":["""Ž¡‘)­void–¹–set_doublevalue(const“char“*format,“double“number){Ž¡‘75ocbf_failnez(cbf_set_doublevalue(self,format,number));}Ž¡‘h¿""","set_doublevalue",["String–¹–format","Float“number"],[]],Ž¡¡¡‘h¿"cbf_require_integervalue":["""Ž¡‘h¿%apply–¹–int“*OUTPUT“{int“*number}“require_integervalue;Ž¡¡‘)­void–¹–require_integervalue(int“*number,“int“thedefault){Ž¡¡‘)­cbf_failnez(cbf_require_integervalue(self,number,thedefault));Ž¡¡‘)­}Ž¡‘h¿""","require_integervalue",–¹–["Int“thedefault"],["Int“number"]],Ž¡¡¡‘h¿"cbf_require_doublevalue":["""Ž¡‘h¿%apply–¹–double“*OUTPUT“{double“*number}“require_doublevalue;Ž¡‘h¿void–¹–require_doublevalue(double“*number,“double“defaultvalue){Ž¡‘•cbf_failnez(cbf_require_doublevalue(self,number,defaultvalue));ŽŽŸ‘âh½Ÿô‰ff&NŸ ²J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽ’ä\June–UU5,“2007ŽŽ’ö&J17ŽŽŽŽŽŽŽŽŒ‹æä Ú ýO¸‘âh½ï4pdf:dest (page.18) [@thispage /XYZ @xpos @ypos null]Ÿüfd²3.5‘ CBFHandlesŽŽŽ’ÇX CONTENTSŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘h¿Ë}ޤ ‘h¿""","require_doublevalue",["Float–¹–Default"],["Float“Number"]],Ž¡¡¡‘h¿"cbf_require_column_value":["""Ž¡‘"Uconst–¹–char*“require_column_value(const“char“*columnname,Ž¡’²«const–¹–char“*defaultvalue){Ž¡‘•const–¹–char“*“result;Ž¡‘•cbf_failnez(cbf_require_column_value(self,columnname,Ž¡’»×&result,defaultvalue));Ž¡‘•return‘¹–result;Ž¡‘h¿}Ž¡‘h¿""","require_column_value",Ž¡‘$O["String–¹–columnnanme","String“Default"],["String“Name"]],Ž¡¡¡‘h¿"cbf_require_column_doublevalue":["""Ž¡‘h¿%apply–¹–double“*OUTPUT“{“double“*number}“require_column_doublevalue;Ž¡‘h¿void–¹–require_column_doublevalue(const“char“*columnname,“double“*“number,Ž¡‘NÕ]const–¹–double“defaultvalue){Ž¡‘$Ocbf_failnez(cbf_require_column_doublevalue(self,Ž¡‘fuKcolumnname,number,defaultvalue));Ž¡‘$O}Ž¡‘h¿""","require_column_doublevalue",["String–¹–columnname","Float“Value"],Ž¡’­U["Float‘¹–defaultvalue"]],Ž¡¡¡‘h¿"cbf_require_column_integervalue":["""Ž¡‘h¿%apply–¹–int“*OUTPUT“{int“*number}‘ s,require_column_integervalue;Ž¡‘h¿void–¹–require_column_integervalue(const“char“*columnname,Ž¡‘~9int–¹–*number,“const“int“defaultvalue){Ž¡‘$Ocbf_failnez(cbf_require_column_integervalue(self,Ž¡‘Eb1columnname,‘¹–number,defaultvalue));Ž¡‘$O}Ž¡‘h¿""","require_column_integervalue",["String–¹–Columnvalue","Int“default"],Ž¡‘"U["Int‘¹–Value"]],Ž¡¡¡¡¡‘h¿"cbf_require_value"–¹–:“["""Ž¡¡‘•const–¹–char*“require_value(const“char*“defaultvalue){Ž¡‘)­const–¹–char“*“result;Ž¡‘)­cbf_failnez(cbf_require_value(self,–¹–&result,“defaultvalue));Ž¡‘)­return‘¹–result;Ž¡‘$O}Ž¡‘h¿""","require_value",["String–¹–defaultvalue"],['String“Value']],Ž¡¡¡‘h¿"cbf_require_diffrn_id":["""Ž¡‘•const–¹–char*“require_diffrn_id(const“char*“defaultid){Ž¡‘)­const–¹–char“*“id;Ž¡‘)­cbf_failnez(cbf_require_diffrn_id(self,&id,defaultid));Ž¡‘)­return‘¹–id;Ž¡‘)­}Ž¡‘h¿""","require_diffrn_id",–¹–["String“Default_id"],["String“diffrn_id"]],Ž¡¡¡¡‘h¿"cbf_get_polarization":["""Ž¡‘)­/*–¹–Returns“a“pair“of“double“values“*/Ž¡‘h¿%apply–¹–double“*OUTPUT“{“double“*in1,“double“*in2“};ŽŽŸ‘âh½Ÿô‰ff&NŸ ²18ŽŽŽ’ä\June–UU5,“2007ŽŽ’Ê‚¸J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽŽŽŽŽŽŒ‹ïÊ Ú ýO¸‘âh½ï4pdf:dest (page.19) [@thispage /XYZ @xpos @ypos null]Ÿüfd²CONTENTSŽŽŽ’±Â²3.5‘ CBFHandlesŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘)­Ëvoid–¹–get_polarization(double“*in1,double“*in2){ޤ ‘75ocbf_failnez(cbf_get_polarization–¹–(self,“in1,“in2));Ž¡‘)­}Ž¡‘h¿""","get_polarization",[],Ž¡‘$O["float–¹–polarizn_source_ratio","float“polarizn_source_norm"]],Ž¡¡¡‘h¿"cbf_set_polarization":["""Ž¡‘)­void–¹–set_polarization“(double“polarizn_source_ratio,Ž¡’•µ'double‘¹–polarizn_source_norm){Ž¡‘;ïcbf_failnez(cbf_set_polarization(self,Ž¡’‡ˆepolarizn_source_ratio,Ž¡’‡ˆepolarizn_source_norm));Ž¡‘)­}Ž¡‘h¿""","set_polarization",Ž¡‘•["Float–¹–polarizn_source_ratio","Float“polarizn_source_norm"],[]],Ž¡¡¡‘h¿"cbf_get_divergence":["""Ž¡‘h¿%apply–¹–double“*OUTPUT“{double“*div_x_source,“double“*div_y_source,Ž¡‘~9double–¹–*div_x_y_source“}“get_divergence;Ž¡‘$Ovoid–¹–get_divergence(double“*div_x_source,“double“*div_y_source,Ž¡‘2{Ùdouble‘¹–*div_x_y_source){Ž¡‘2{Ùcbf_failnez(cbf_get_divergence(self,Ž¡’À;mdiv_x_source,Ž¡’À;mdiv_y_source,Ž¡’À;mdiv_x_y_source));Ž¡‘2{Ù}Ž¡‘h¿""","get_divergence",[],Ž¡‘)­["Float–¹–div_x_source","Float“div_y_source","Float“div_x_y_source"]],Ž¡¡¡‘h¿"cbf_set_divergence":["""Ž¡‘•void–¹–set_divergence“(“double“div_x_source,“double“div_y_source,Ž¡’‚ÎÏdouble‘¹–div_x_y_source){Ž¡‘-ÂCcbf_failnez(cbf_set_divergence–¹–(self,“div_x_source,Ž¡’Ÿ(Sdiv_y_source,div_x_y_source));Ž¡‘-ÂC}Ž¡‘h¿""","set_divergence",Ž¡‘$O["Float–¹–div_x_source","Float“div_y_source","Float“div_x_y_source"],[]],Ž¡¡‘h¿"cbf_get_gain":["""Ž¡‘h¿%apply–¹–double“*OUTPUT“{double“*gain,“double“*gain_esd}“get_gain;Ž¡‘$Ovoid–¹–get_gain“(unsigned“int“element_number,“double“*gain,Ž¡‘k.ádouble‘¹–*gain_esd){Ž¡‘75ocbf_failnez(cbf_get_gain–¹–(self,“element_number,“gain,“gain_esd));Ž¡‘75o}Ž¡‘h¿""","get_gain",Ž¡‘$O[],["Float–¹–gain",“"Float“gain_esd"]],Ž¡¡¡‘h¿"cbf_set_gain":["""Ž¡‘$Ovoid–¹–set_gain“(unsigned“int“element_number,“double“gain,“double“gain_esd){Ž¡‘75ocbf_failnez(cbf_set_gain–¹–(self,“element_number,“gain,“gain_esd));Ž¡‘75o}Ž¡‘h¿""","set_gain",["Float–¹–gain",“"Float“gain_esd"],[]],Ž¡¡‘h¿"cbf_get_element_id":["""Ž¡‘•const–¹–char“*“get_element_id(unsigned“int“element_number){Ž¡‘2{Ùconst–¹–char“*“result;Ž¡‘2{Ùcbf_failnez(cbf_get_element_id–¹–(self,“element_number,“&result));Ž¡‘2{Ùreturn‘¹–result;Ž¡‘2{Ù}ŽŽŸ‘âh½Ÿô‰ff&NŸ ²J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽ’ä\June–UU5,“2007ŽŽ’ö&J19ŽŽŽŽŽŽŽŽŒ‹ùJ Ú ýO¸‘âh½ï4pdf:dest (page.20) [@thispage /XYZ @xpos @ypos null]Ÿüfd²3.5‘ CBFHandlesŽŽŽ’ÇX CONTENTSŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘h¿Ë""","get_element_id",–¹–["Integer“element_number"],["String"]],ޤ ¡¡‘h¿"cbf_set_axis_setting":["""Ž¡‘•void–¹–set_axis_setting(const“char“*axis_id,Ž¡‘oèwdouble–¹–start,“double“increment){Ž¡‘75ounsigned–¹–int“reserved;Ž¡‘75oreserved–¹–=“0;Ž¡‘75ocbf_failnez(cbf_set_axis_setting(self,reserved,Ž¡’‡ˆeaxis_id,start,increment));Ž¡‘75o}Ž¡‘h¿""","set_axis_setting",["String–¹–axis_id",“"Float“start",“"Float“increment"],Ž¡‘"U[]],Ž¡¡¡‘h¿"cbf_get_axis_setting":["""Ž¡‘h¿%apply–¹–double“*OUTPUT“{double“*start,“double“*increment}“get_axis_setting;Ž¡‘•void–¹–get_axis_setting(const“char“*axis_id,Ž¡‘oèwdouble–¹–*start,“double“*increment){Ž¡‘75ounsigned–¹–int“reserved;Ž¡‘75oreserved–¹–=“0;Ž¡‘75ocbf_failnez(cbf_get_axis_setting(self,reserved,axis_id,Ž¡’‡ˆestart,increment));Ž¡‘75o}Ž¡‘h¿""","get_axis_setting",["String–¹–axis_id"],["Float“start",“"Float“increment"],],Ž¡¡¡¡‘h¿"cbf_get_datestamp":["""Ž¡‘h¿%apply–¹–int“*OUTPUT“{int“*year,“int“*month,“int“*day,“int“*hour,Ž¡‘oèwint–¹–*minute,“double“*second,“int“*timezone}“get_datestamp;Ž¡‘•void–¹–get_datestamp(int“*year,“int“*month,“int“*day,“int“*hour,Ž¡‘y[£int–¹–*minute,“double“*second,“int“*timezone){Ž¡‘75ounsigned–¹–int“reserved;Ž¡‘75oreserved–¹–=“0;Ž¡‘75ocbf_failnez(cbf_get_datestamp(self,reserved,Ž¡‘SŽóyear,month,day,hour,minute,second,timezone));Ž¡‘75o}Ž¡‘h¿""","get_datestamp",[],["int–¹–year",“"int“month",“"int“day",“"int“hour",Ž¡‘h¿"int–¹–minute",“"double“second",“"int“timezone"]],Ž¡¡¡¡‘h¿"cbf_set_datestamp":["""Ž¡‘•void–¹–set_datestamp(int“year,“int“month,“int“day,“int“hour,Ž¡‘y[£int–¹–minute,“double“second,“int“timezone,Ž¡‘y[£double‘¹–precision){Ž¡‘75ounsigned–¹–int“reserved;Ž¡‘75oreserved–¹–=“0;Ž¡‘75ocbf_failnez(cbf_set_datestamp(self,reserved,Ž¡‘SŽóyear,month,day,hour,minute,second,timezone,precision));Ž¡‘75o}Ž¡‘h¿""","set_datestamp",["int–¹–year",“"int“month",“"int“day",“"int“hour",Ž¡‘h¿"int–¹–minute",“"double“second",“"int“timezone","Float“precision"],[]],Ž¡¡¡‘h¿"cbf_get_timestamp":["""Ž¡‘h¿%apply–¹–double“*OUTPUT“{double“*time}“get_timestamp;Ž¡‘h¿%apply–¹–int“*OUTPUT“{int“*timezone}“get_timestamp;Ž¡‘$Ovoid–¹–get_timestamp(double“*time,“int“*timezone){Ž¡‘75ounsigned–¹–int“reserved;Ž¡‘75oreserved–¹–=“0;Ž¡‘75ocbf_failnez(cbf_get_timestamp(self,reserved,time,timezone));ŽŽŸ‘âh½Ÿô‰ff&NŸ ²20ŽŽŽ’ä\June–UU5,“2007ŽŽ’Ê‚¸J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽŽŽŽŽŽŒ‹_ Ú ýO¸‘âh½ï4pdf:dest (page.21) [@thispage /XYZ @xpos @ypos null]Ÿüfd²CONTENTSŽŽŽ’±Â²3.5‘ CBFHandlesŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘75oË}ޤ ‘h¿""","get_timestamp",[],["Float–¹–time","Integer“timezone"]],Ž¡¡¡¡‘h¿"cbf_set_timestamp":["""Ž¡‘$Ovoid–¹–set_timestamp(double“time,“int“timezone,“double“precision){Ž¡‘75ounsigned–¹–int“reserved;Ž¡‘75oreserved–¹–=“0;Ž¡‘75ocbf_failnez(cbf_set_timestamp(self,reserved,time,timezone,precision));Ž¡‘75o}Ž¡‘h¿""","set_timestamp",["Float–¹–time","Integer“timezone","Float“precision"],[]],Ž¡¡¡‘h¿"cbf_set_current_timestamp":["""Ž¡‘$Ovoid–¹–set_current_timestamp(int“timezone){Ž¡‘75ounsigned–¹–int“reserved;Ž¡‘75oreserved–¹–=“0;Ž¡‘75ocbf_failnez(cbf_set_current_timestamp(self,reserved,timezone));Ž¡‘75o}Ž¡‘h¿""","set_current_timestamp",["Integer‘¹–timezone"],[]],Ž¡¡¡¡‘h¿"cbf_get_overload":["""Ž¡‘h¿%apply–¹–double“*OUTPUT“{double“*overload}“get_overload;Ž¡‘•void–¹–get_overload(unsigned“int“element_number,“double“*overload){Ž¡‘75ocbf_failnez(cbf_get_overload(self,element_number,overload));Ž¡‘75o}Ž¡‘h¿""","get_overload",["Integer–¹–element_number"],["Float“overload"]],Ž¡¡‘h¿"cbf_set_overload":["""Ž¡‘•void–¹–set_overload(unsigned“int“element_number,“double“overload){Ž¡‘75ocbf_failnez(cbf_set_overload(self,element_number,overload));Ž¡‘75o}Ž¡‘h¿""","set_overload",["Integer–¹–element_number","Float“overload"],[]],Ž¡¡¡‘h¿"cbf_set_integration_time":["""Ž¡‘•void–¹–set_integration_time(double“time){Ž¡‘75ounsigned–¹–int“reserved;Ž¡‘75oreserved–¹–=“0;Ž¡‘75ocbf_failnez(cbf_set_integration_time(self,reserved,time));Ž¡‘75o}Ž¡‘h¿""","set_integration_time",["Float‘¹–time"],[]],Ž¡¡¡¡‘h¿"cbf_get_integration_time":["""Ž¡‘h¿%apply–¹–double“*OUTPUT“{double“*time}“get_integration_time;Ž¡‘•void–¹–get_integration_time(double“*time){Ž¡‘75ounsigned–¹–int“reserved;Ž¡‘75oreserved–¹–=“0;Ž¡‘75ocbf_failnez(cbf_get_integration_time(self,reserved,time));Ž¡‘75o}Ž¡‘h¿""","get_integration_time",[],["Float‘¹–time"]],Ž¡¡‘h¿"cbf_get_orientation_matrix":["""Ž¡‘h¿%apply–¹–double“*OUTPUT“{double“*m0,double“*m1,double“*m2,Ž¡‘h¿double–¹–*m3,double“*m4,“double“*m5,double“*m6,Ž¡‘h¿double–¹–*m7,double“*m8‘ s,}“get_orientation_matrix;Ž¡‘•void–¹–get_orientation_matrix(‘ s,double“*m0,double“*m1,Ž¡‘h¿double–¹–*m2,double“*m3,double“*m4,double“*m5,double“*m6,ŽŽŸ‘âh½Ÿô‰ff&NŸ ²J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽ’ä\June–UU5,“2007ŽŽ’ö&J21ŽŽŽŽŽŽŽŽŒ‹ Á Ú ýO¸‘âh½ï4pdf:dest (page.22) [@thispage /XYZ @xpos @ypos null]Ÿüfd²3.5‘ CBFHandlesŽŽŽ’ÇX CONTENTSŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘h¿Ëdouble–¹–*m7,double“*m8){ޤ ‘75odouble‘¹–m[9];Ž¡‘75ocbf_failnez(cbf_get_orientation_matrix(self,m));Ž¡‘75o*m0–¹–=“m[0];“*m1=m[1]“;“*m2=m[2]“;Ž¡‘75o*m3–¹–=“m[3];“*m4=m[4]“;“*m5=m[5]“;Ž¡‘75o*m6–¹–=“m[6];“*m7=m[7]“;“*m8=m[8]“;Ž¡‘75o}Ž¡‘h¿""","get_orientation_matrix",Ž¡‘$O[],[–¹–"Float“matrix_%d"%(ind)“for“ind“in“range(9)“]],Ž¡¡¡‘h¿"cbf_set_tag_category":["""Ž¡‘•void–¹–set_tag_category(const“char“*tagname,“const“char*“categoryname_in){Ž¡‘)­cbf_failnez(cbf_set_tag_category(self,tagname,‘¹–categoryname_in));Ž¡‘)­}Ž¡‘h¿""","set_tag_category",["String–¹–tagname","String“categoryname_in"],[]“],Ž¡¡¡¡‘h¿"cbf_find_tag_category":["""Ž¡¡‘•const–¹–char“*“find_tag_category(const“char“*tagname){Ž¡‘)­const–¹–char“*“result;Ž¡‘)­cbf_failnez(cbf_find_tag_category(self,tagname,‘¹–&result));Ž¡‘)­return‘¹–result;Ž¡‘)­}Ž¡‘h¿""","find_tag_category",["String–¹–tagname"],["String“categoryname_in"]“],Ž¡¡¡‘h¿"cbf_require_tag_root":["""Ž¡‘h¿const–¹–char*“require_tag_root(const“char*“tagname){Ž¡‘"Uconst–¹–char*“result;Ž¡‘"Ucbf_failnez(cbf_require_tag_root(self,tagname,&result));Ž¡‘"Ureturn‘¹–result;Ž¡‘"U}Ž¡‘h¿""","require_tag_root",["String–¹–tagname"],["String“tagroot"]],Ž¡¡‘h¿"cbf_find_tag_root":["""Ž¡‘h¿const–¹–char“*“find_tag_root(const“char*“tagname){Ž¡‘•const–¹–char*“result;Ž¡‘•cbf_failnez(cbf_find_tag_root(self,tagname,&result));Ž¡‘•return‘¹–result;Ž¡‘h¿}Ž¡‘h¿""","find_tag_root",["String–¹–tagname"],["String“tagroot"]],Ž¡¡¡‘h¿"cbf_set_tag_root":["""Ž¡‘h¿void‘ s,set_tag_root(const–¹–char*“tagname,“const“char*“tagroot_in){Ž¡‘•cbf_failnez(cbf_set_tag_root(self,tagname,tagroot_in));Ž¡‘h¿}Ž¡‘h¿""","set_tag_root",["String–¹–tagname","String“tagroot_in"],[]],Ž¡¡‘h¿"cbf_set_category_root":["""Ž¡‘h¿void‘ s,set_category_root(const–¹–char*“categoryname,“const“char*“categoryroot){Ž¡‘•cbf_failnez(cbf_set_category_root(self,categoryname,categoryroot));Ž¡‘h¿}Ž¡‘h¿""","set_category_root",["String–¹–categoryname","String“categoryroot"],[]],Ž¡¡¡‘h¿"cbf_find_category_root":["""Ž¡‘h¿const–¹–char*‘ s,find_category_root(const“char*“categoryname){Ž¡‘•const–¹–char“*“result;Ž¡‘•cbf_failnez(cbf_find_category_root(self,categoryname,&result));ŽŽŸ‘âh½Ÿô‰ff&NŸ ²22ŽŽŽ’ä\June–UU5,“2007ŽŽ’Ê‚¸J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽŽŽŽŽŽŒ‹³ Ú ýO¸‘âh½ï4pdf:dest (page.23) [@thispage /XYZ @xpos @ypos null]Ÿüfd²CONTENTSŽŽŽ’±Â²3.5‘ CBFHandlesŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘•Ëreturn‘¹–result;ޤ ‘h¿}Ž¡‘h¿""","find_category_root",["String–¹–categoryname"],["String“categoryroot"]],Ž¡¡¡¡¡¡¡‘h¿"cbf_require_category_root":["""Ž¡‘h¿const–¹–char*“require_category_root“(const“char*“categoryname){Ž¡‘Ûëconst–¹–char*“result;Ž¡‘Ûëcbf_failnez(cbf_require_category_root(self,categoryname,‘¹–&result));Ž¡‘Ûëreturn‘¹–result;Ž¡‘h¿}Ž¡‘h¿""","cbf_require_category_root",["String–¹–Categoryname"],["String“categoryroot"]],Ž¡¡¡‘h¿"cbf_set_orientation_matrix":["""Ž¡‘•void–¹–set_orientation_matrix(‘ s,double“m0,double“m1,Ž¡‘h¿double– s,m2,double“m3,double“m4,double–¹–m5,double“m6,Ž¡‘h¿double– s,m7,double“m8){Ž¡‘75odouble‘¹–m[9];Ž¡‘75om[0]–¹–=“m0;“m[1]=m1“;“m[2]=m2“;Ž¡‘75om[3]–¹–=“m3;“m[4]=m4“;“m[5]=m5“;Ž¡‘75om[6]–¹–=“m6;“m[7]=m7“;“m[8]=m8“;Ž¡‘75ocbf_failnez(cbf_get_orientation_matrix(self,m));Ž¡‘75o}Ž¡‘h¿""","set_orientation_matrix",Ž¡‘$O[–¹–"Float“matrix_%d"%(ind)“for“ind“in“range(9)“]“,[]],Ž¡¡¡‘h¿#–¹–cbfhandle“dict“functions“UNTESTEDŽ¡¡¡‘h¿"cbf_require_dictionary":["""Ž¡‘h¿cbf_handle‘¹–require_dictionary(){Ž¡‘•cbf_handle‘¹–temp;Ž¡‘•cbf_failnez(cbf_require_dictionary(self,&temp));Ž¡‘•return‘¹–temp;Ž¡‘h¿}Ž¡‘h¿""","require_dictionary",[],["CBFHandle‘¹–dictionary"]],Ž¡¡¡‘h¿"cbf_get_dictionary":["""Ž¡‘h¿cbf_handle‘¹–get_dictionary(){Ž¡‘•cbf_handle‘¹–temp;Ž¡‘•cbf_failnez(cbf_get_dictionary(self,&temp));Ž¡‘•return‘¹–temp;Ž¡‘h¿}Ž¡‘h¿""","get_dictionary",[],["CBFHandle‘¹–dictionary"]],Ž¡¡¡¡‘h¿"cbf_set_dictionary":["""Ž¡‘h¿void–¹–set_dictionary(cbf_handle“other){Ž¡‘•cbf_failnez(cbf_set_dictionary(self,other));Ž¡‘h¿}Ž¡‘h¿""","set_dictionary",["CBFHandle‘¹–dictionary"],[]],Ž¡¡¡¡‘h¿"cbf_convert_dictionary":["""ŽŽŸ‘âh½Ÿô‰ff&NŸ ²J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽ’ä\June–UU5,“2007ŽŽ’ö&J23ŽŽŽŽŽŽŽŽŒ‹!µ Ú ýO¸‘âh½ï4pdf:dest (page.24) [@thispage /XYZ @xpos @ypos null]Ÿüfd²3.6‘ CBF¸ãGoniometersŽŽŽ’ÇX CONTENTSŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘h¿Ëvoid–¹–convert_dictionary(cbf_handle“other){ޤ ‘•cbf_failnez(cbf_convert_dictionary(self,other));Ž¡‘h¿}Ž¡‘h¿""","convert_dictionary",["CBFHandle‘¹–dictionary"],[]],Ž¡¡¡¡¡‘h¿#–¹–Prelude“to“the“next“but“one“section“of“the“nuweb“docŽ¡¡¡‘h¿"cbf_construct_detector":["""Ž¡‘"Ucbf_detector–¹–construct_detector(unsigned“int“element_number){Ž¡‘$Ocbf_detector‘¹–detector;Ž¡‘$Ocbf_failnez(cbf_construct_detector(self,&detector,element_number));Ž¡‘$Oreturn‘¹–detector;Ž¡‘$O}Ž¡‘h¿""","construct_detector",["Integer–¹–element_number"],["pycbf“detector“object"]],Ž¡¡¡‘h¿#–¹–Prelude“to“the“next“section“of“the“nuweb“docŽ¡¡‘h¿"cbf_construct_goniometer":["""Ž¡‘"Ucbf_goniometer‘¹–construct_goniometer(){Ž¡‘$Ocbf_goniometer‘¹–goniometer;Ž¡‘$Ocbf_failnez(cbf_construct_goniometer(self,&goniometer));Ž¡‘$Oreturn‘¹–goniometer;Ž¡‘$O}Ž¡‘h¿""","construct_goniometer",[],["pycbf–¹–goniometer“object"]],Ž¡¡‘h¿}Ž¡‘h¿ÊŽŽŸ  k‘ûh¿½Macro–ÕXreferenced“in“11.Ž‘âh½Ÿ ‡ï;pdf:dest (subsection.3.6) [@thispage /XYZ @xpos @ypos null]Ÿ=³‘Ì3.6Ž‘7ÀCBF GoniometersŽŸ=‘ÅThere–B*are›B+relativ¾9ely“few“functions˜taking“a˜cbf‘މffÆgŽ‘Tygoniometer“as“the˜ rst“argumen¾9t,‘M`but“this˜is“sligh¾9tlyŽ¡‘less–Ù©ob¾9vious“to“wrap“as“it‘Ùªcan“only“bAÇe“constructed“from“a“cbfhandle“ob‘ƒŽject.‘The“constructor“is“in“theŽ¡‘CBFhandle–Tsubsection“(FIXME“latex“xref‘´q).ŽŸ4~‘Êh–ŠªÅcbfgoniometerwrappAÇer‘T½24“Êi‘‘ÆŽŸ Ù¡¡¡‘/Ëcbf_goniometer_specials–¹–=“{Ž¡‘/"cbf_get_rotation_range":["""Ž¡‘/%apply–¹–double“*OUTPUT“{double“*start,double“*increment};Ž¡¡‘AæZvoid–¹–get_rotation_range(double“*start,double“*increment){Ž¡‘Punsigned–¹–int“reserved;Ž¡‘Preserved–¹–=“0;Ž¡‘Pcbf_failnez(cbf_get_rotation_range–¹–(self,reserved,“start,increment));Ž¡‘AæZ}Ž¡‘/""","get_rotation_range",[],["Float–¹–start","Float“increment"]],Ž¡¡‘/"cbf_rotate_vector":["""Ž¡¡‘/%apply–¹–double“*OUTPUT“{double“*final1,“double“*final2,“double“*final3};Ž¡¡‘AæZvoid–¹–rotate_vector“(double“ratio,“double“initial1,double“initial2,Ž¡‘Y†Hdouble–¹–initial3,“double“*final1,“double“*final2,“double“*final3){Ž¡‘Punsigned–¹–int“reserved;Ž¡‘Preserved–¹–=“0;ŽŽŸ‘âh½Ÿô‰ff&NŸ ²24ŽŽŽ’ä\June–UU5,“2007ŽŽ’Ê‚¸J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽŽŽŽŽŽŒ‹)³ Ú ýO¸‘âh½ï4pdf:dest (page.25) [@thispage /XYZ @xpos @ypos null]Ÿüfd²CONTENTSŽŽŽ’©Î3.6‘ CBF¸ãGoniometersŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘2{ÙËcbf_failnez(cbf_rotate_vector–¹–(self,“reserved,“ratio,“initial1,ޤ ‘;ïinitial2,–¹–initial3,“final1,“final2,“final3));Ž¡‘$O}Ž¡‘h¿""",‘¹–"rotate_vector",Ž¡‘"U[–¹–"double“ratio",“"double“initial1","double“initial2",“"double“initial3"“]“,Ž¡‘fuK[–¹–"double“final1"› s,,"double“final2"˜,“"double“final3"“]“],Ž¡¡¡¡‘h¿"cbf_get_reciprocal":["""Ž¡‘h¿%apply–¹–double“*OUTPUT“{double“*reciprocal1,double“*reciprocal2,Ž¡‘SŽódouble‘¹–*reciprocal3};Ž¡¡‘$Ovoid–¹–get_reciprocal“(double“ratio,double“wavelength,Ž¡’‡ˆedouble–¹–real1,“double“real2,“double“real3,Ž¡’‡ˆedouble–¹–*reciprocal1,double“*reciprocal2,Ž¡’‡ˆedouble‘¹–*reciprocal3){Ž¡‘75ounsigned–¹–int“reserved;Ž¡‘75oreserved–¹–=“0;Ž¡‘75ocbf_failnez(cbf_get_reciprocal(self,reserved,–¹–ratio,“wavelength,Ž¡’‡ˆereal1,–¹–real2,“real3,reciprocal1,Ž¡’‡ˆereciprocal2,reciprocal3));Ž¡‘$O}Ž¡‘h¿""",‘¹–"get_reciprocal",Ž¡‘$O["double–¹–ratio","double“wavelength",Ž¡‘)­"double–¹–real1","double“real2","double“real3"],Ž¡‘$O["double–¹–reciprocal1","double“reciprocal2",“"double“reciprocal3"“]],Ž¡¡‘h¿"cbf_get_rotation_axis":["""Ž¡‘h¿%apply–¹–double“*OUTPUT“{double“*vector1,double“*vector2,“double“*vector3};Ž¡¡‘h¿void–¹–get_rotation_axis“(double“*vector1,“double“*vector2,“double“*vector3){Ž¡‘)­unsigned–¹–int“reserved;Ž¡‘)­reserved–¹–=“0;Ž¡‘)­cbf_failnez(cbf_get_rotation_axis–¹–(self,“reserved,Ž¡’Îh/vector1,–¹–vector2,“vector3));Ž¡‘$O}Ž¡‘h¿""","get_rotation_axis",–¹–[]“,Ž¡‘"U["double–¹–vector1",“"double“vector2",“"double“vector3"]“],Ž¡¡‘h¿}Ž¡¡¡¡‘h¿class‘¹–cbfgoniometerwrapper:Ž¡‘•def‘¹–__init__(self):Ž¡‘-ÂCself.code–¹–=“"""Ž¡‘h¿//–¹–Tell“SWIG“not“to“make“constructor“for“these“objectsŽ¡‘h¿%nodefault‘¹–cbf_positioner_struct;Ž¡‘h¿%nodefault‘¹–cbf_goniometer;Ž¡‘h¿%nodefault‘¹–cbf_axis_struct;Ž¡¡‘h¿//–¹–Tell“SWIG“what“the“object“is,“so“we“can“build“the“classŽ¡‘h¿typedef‘¹–structŽ¡‘h¿{Ž¡‘Ûëdouble–¹–matrix“[3][4];Ž¡¡‘Ûëcbf_axis_struct‘¹–*axis;Ž¡¡‘Ûësize_t‘¹–axes;Ž¡¡‘Ûëint–¹–matrix_is_valid,“axes_are_connected;Ž¡‘h¿}ŽŽŸ‘âh½Ÿô‰ff&NŸ ²J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽ’ä\June–UU5,“2007ŽŽ’ö&J25ŽŽŽŽŽŽŽŽŒ‹3ž Ú ýO¸‘âh½ï4pdf:dest (page.26) [@thispage /XYZ @xpos @ypos null]Ÿüfd²3.7‘ CBFDetectorsŽŽŽ’ÇX CONTENTSŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘h¿Ëcbf_positioner_struct;ޤ ¡‘h¿typedef–¹–cbf_positioner_struct“*cbf_goniometer;Ž¡¡¡‘h¿%feature("autodoc","1");Ž¡¡‘h¿%extend–¹–cbf_positioner_struct{//“Tell“SWIG“to“attach“functions“to“the“structureŽ¡¡‘$Ocbf_positioner_struct(){‘ s,//‘¹–ConstructorŽ¡‘2{Ù//–¹–DO“NOT“CONSTRUCT“WITHOUT“A“CBFHANDLEŽ¡‘2{Ùcbf_failnez(CBF_ARGUMENT);Ž¡‘2{Ùreturn–¹–NULL;“/*“Should“never“be“executed“*/Ž¡‘2{Ù}Ž¡¡‘$O~cbf_positioner_struct(){–¹–//“DestructorŽ¡‘2{Ùcbf_failnez(cbf_free_goniometer(self));Ž¡‘2{Ù}Ž¡‘h¿"""Ž¡‘-ÂCself.tail–¹–=“"""Ž¡‘h¿};–¹–//“End“of“cbf_positionerŽ¡‘h¿"""Ž¡‘•def‘¹–wrap(self,cfunc,prototype,args,docstring):Ž¡‘)­if‘¹–cfunc.find("cbf_free_goniometer")>-1:Ž¡‘75oreturnŽ¡‘)­try:Ž¡‘75ocode,–¹–pyname,“input,“output“=“cbf_goniometer_specials[cfunc]Ž¡‘75oself.code‘¹–+=‘ s,docstringwrite(pyname,input,output,Ž¡’À;mprototype,docstring)+‘¹–codeŽ¡‘)­except‘¹–KeyError:Ž¡‘75oprint–¹–"TODO:“Goniometer:",prototypeŽ¡‘•def‘¹–get_code(self):Ž¡‘)­return‘¹–self.code+self.tailŽ¡‘h¿ÊŽŽŸ  k‘ûh¿½Macro–ÕXreferenced“in“7b.Ž‘âh½Ÿ ‡ï;pdf:dest (subsection.3.7) [@thispage /XYZ @xpos @ypos null]Ÿ=³‘Ì3.7Ž‘7ÀCBFDetectorsŽŸ=‘ÅThis–Ùsubsection“is›Úprett¾9y“similar“to“the“one˜abAÇout“goniometers,‘Lòbut“wrapping˜the“detector“functionalit¾9yŽ¡‘instead.‘pThe–Tconstructor“can“bAÇe“found“in“the“CBFhandle“subsection“(FIXME“latex“xref‘´q).ŽŸ4~‘Êh–ŠªÅcbfdetectorwrappAÇer‘T½26“Êi‘‘ÆŽŸ Ù¡¡‘/Ëcbf_detector_specials–¹–=“{Ž¡‘/"cbf_get_pixel_normal":["""Ž¡‘/%apply–¹–double“*OUTPUT“{double“*normal1,double“*normal2,“double“*normal3};Ž¡‘=,Ävoid–¹–get_pixel_normal“(“double“index1,“double“index2,Ž¡’©Ù>double–¹–*normal1,double“*normal2,“double“*normal3){Ž¡‘Pcbf_failnez(cbf_get_pixel_normal(self,Ž¡’Ùindex1,index2,normal1,normal2,normal3));Ž¡‘=,Ä}Ž¡¡‘/""","get_pixel_normal",["double–¹–index1","double“index2"]“,Ž¡‘3¹˜["double–¹–normal1","double“normal2",“"double“normal3"“]“],Ž¡¡‘/"cbf_get_pixel_area":["""Ž¡‘/%apply–¹–double“*OUTPUT{double“*area,double“*projected_area};Ž¡‘AæZvoid–¹–get_pixel_area(double“index1,“double“index2,Ž¡’ fdouble–¹–*area,double“*projected_area){Ž¡‘Pcbf_failnez(cbf_get_pixel_area‘¹–(self,Ž¡’çEÜindex1,–¹–index2,“area,projected_area));Ž¡‘KY†}ŽŽŸ‘âh½Ÿô‰ff&NŸ ²26ŽŽŽ’ä\June–UU5,“2007ŽŽ’Ê‚¸J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽŽŽŽŽŽŒ‹<û Ú ýO¸‘âh½ï4pdf:dest (page.27) [@thispage /XYZ @xpos @ypos null]Ÿüfd²CONTENTSŽŽŽ’ªí^3.7‘ CBFDetectorsŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘h¿Ë""","get_pixel_area",["double–¹–index1",“"double“index2"],ޤ ‘)­["double–¹–area","double“projected_area"]“],Ž¡¡‘h¿"cbf_get_detector_distance":["""Ž¡‘h¿%apply–¹–double“*OUTPUT“{double“*distance};Ž¡‘"Uvoid–¹–get_detector_distance“(double“*distance){Ž¡‘Ûëcbf_failnez(cbf_get_detector_distance(self,distance));Ž¡‘Ûë}Ž¡‘h¿""","get_detector_distance",[],["double‘¹–distance"]],Ž¡¡‘h¿"cbf_get_detector_normal":["""Ž¡‘h¿%apply–¹–double“*OUTPUT“{double“*normal1,“double“*normal2,“double“*normal3};Ž¡‘•void–¹–get_detector_normal(double“*normal1,Ž¡’•µ'double‘¹–*normal2,Ž¡’•µ'double‘¹–*normal3){Ž¡‘)­cbf_failnez(cbf_get_detector_normal(self,Ž¡‘oèwnormal1,–¹–normal2,“normal3));Ž¡‘•}Ž¡‘h¿""","get_detector_normal",[],Ž¡‘h¿["double–¹–normal1",“"double“normal2",“"double“normal3"]],Ž¡¡‘h¿"cbf_get_pixel_coordinates":["""Ž¡‘h¿%apply–¹–double“*OUTPUT“{double“*coordinate1,Ž¡‘;ïdouble–¹–*coordinate2,“double“*coordinate3};Ž¡‘•void–¹–get_pixel_coordinates(double“index1,“double“index2,Ž¡‘NÕ]double‘¹–*coordinate1,Ž¡‘NÕ]double‘¹–*coordinate2,Ž¡‘NÕ]double‘¹–*coordinate3){Ž¡‘-ÂCcbf_failnez(cbf_get_pixel_coordinates(self,index1,index2,Ž¡‘NÕ]coordinate1,coordinate2,coordinate3));Ž¡‘•}Ž¡‘h¿""","get_pixel_coordinates",["double–¹–index1","double“index2"],Ž¡‘h¿["double–¹–coordinate1",“"double“coordinate2",“"double“coordinate3"]“],Ž¡¡‘h¿"cbf_get_beam_center":["""Ž¡‘h¿%apply–¹–double“*OUTPUT“{double“*index1,“double“*index2,Ž¡‘"Udouble–¹–*center1,double“*center2};Ž¡‘$Ovoid–¹–get_beam_center(double“*index1,“double“*index2,Ž¡’‡ˆedouble–¹–*center1,double“*center2){Ž¡‘75ocbf_failnez(cbf_get_beam_center(self,–¹–index1,“index2,Ž¡’É®™center1,‘¹–center2));Ž¡‘75o}Ž¡‘h¿""","get_beam_center",[],Ž¡‘h¿["double–¹–index1",“"double“index2",“"double“center1","double“center2"]],Ž¡¡¡¡‘h¿"cbf_get_inferred_pixel_size"–¹–:“["""Ž¡‘h¿%apply–¹–double“*OUTPUT“{“double“*psize“}“get_inferred_pixel_size;Ž¡‘h¿void–¹–get_inferred_pixel_size(unsigned“int“axis_number,“double*“psize){Ž¡‘•cbf_failnez(cbf_get_inferred_pixel_size(self,–¹–axis_number,“psize));Ž¡‘•}Ž¡‘h¿""","get_inferred_pixel_size",["Int–¹–axis_number"],["Float“pixel“size"]“]Ž¡¡¡‘h¿}Ž¡¡¡¡‘h¿class‘¹–cbfdetectorwrapper:Ž¡‘•def‘¹–__init__(self):Ž¡‘-ÂCself.code–¹–=“"""Ž¡‘h¿//–¹–Tell“SWIG“not“to“make“constructor“for“these“objectsŽŽŸ‘âh½Ÿô‰ff&NŸ ²J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽ’ä\June–UU5,“2007ŽŽ’ö&J27ŽŽŽŽŽŽŽŽŒ‹G" Ú ýO¸‘âh½ï4pdf:dest (page.28) [@thispage /XYZ @xpos @ypos null]Ÿüfd–UU²4.“Building“p¸ãython“extensions“-“the“setup“ leŽŽŽ’ÇX CONTENTSŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘h¿Ë%nodefault‘¹–cbf_detector_struct;ޤ ‘h¿%nodefault‘¹–cbf_detector;Ž¡¡‘h¿//–¹–Tell“SWIG“what“the“object“is,“so“we“can“build“the“classŽ¡‘h¿typedef‘¹–structŽ¡‘h¿{Ž¡‘Ûëcbf_positioner‘¹–positioner;Ž¡¡‘Ûëdouble–¹–displacement“[2],“increment“[2];Ž¡¡‘Ûësize_t–¹–axes,“index“[2];Ž¡‘h¿}Ž¡‘h¿cbf_detector_struct;Ž¡¡‘h¿typedef–¹–cbf_detector_struct“*cbf_detector;Ž¡¡‘h¿%feature("autodoc","1");Ž¡¡‘h¿%extend–¹–cbf_detector_struct{//“Tell“SWIG“to“attach“functions“to“the“structureŽ¡¡‘$Ocbf_detector_struct(){‘ s,//‘¹–ConstructorŽ¡‘2{Ù//–¹–DO“NOT“CONSTRUCT“WITHOUT“A“CBFHANDLEŽ¡‘2{Ùcbf_failnez(CBF_ARGUMENT);Ž¡‘2{Ùreturn–¹–NULL;“/*“Should“never“be“executed“*/Ž¡‘2{Ù}Ž¡¡‘$O~cbf_detector_struct(){–¹–//“DestructorŽ¡‘2{Ùcbf_failnez(cbf_free_detector(self));Ž¡‘2{Ù}Ž¡‘h¿"""Ž¡‘-ÂCself.tail–¹–=“"""Ž¡‘h¿};–¹–//“End“of“cbf_detectorŽ¡‘h¿"""Ž¡‘•def‘¹–wrap(self,cfunc,prototype,args,docstring):Ž¡‘)­if‘¹–cfunc.find("cbf_free_detector")>-1:Ž¡‘75oreturnŽ¡‘)­try:Ž¡‘75ocode,–¹–pyname,“input,“output“=“cbf_detector_specials[cfunc]Ž¡‘75oself.code‘¹–+=‘ s,docstringwrite(pyname,input,output,Ž¡’À;mprototype,docstring)+‘¹–codeŽ¡‘)­except‘¹–KeyError:Ž¡‘75oprint–¹–"TODO:“Detector:",prototypeŽ¡‘•def‘¹–get_code(self):Ž¡‘)­return‘¹–self.code+self.tailŽ¡‘h¿ÊŽŽŸ üБûh¿½Macro–ÕXreferenced“in“7b.Ž‘âh½Ÿ Aï6pdf:dest (section.4) [@thispage /XYZ @xpos @ypos null]Ÿ‘È4Ž‘1LÍBuilding–ffpŒÌython“extensions“-“the“setup“ leŽŸ阑ÅBased–V on“the“con•¾9ten“ts–V of“the“makš¾9e le“for“CBFlib“w˜e“will“just‘V pull“in“all“of“the“library“for“no˜w.‘Þ•W‘ÿ:«eŽ¡‘use–Tthe“distutils“approac¾9h.ŽŸΖ‘Ë"setup.py"‘T½28‘ÕXÊŽŸ º3¡¡‘/Ë#–¹–Import“the“things“to“build“python“binary“extensionsŽ¡¡‘/from–¹–distutils.core“import“setup,“ExtensionŽ¡¡‘/#–¹–Make“our“extension“moduleŽ¡¡‘/e–¹–=“Extension('_pycbf',Ž¡‘q&6sources–¹–=“["pycbf_wrap.c","../src/cbf_simple.c"],ŽŽŸ‘âh½Ÿô‰ff&NŸ ²28ŽŽŽ’ä\June–UU5,“2007ŽŽ’Ê‚¸J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽŽŽŽŽŽŒ‹Q¤ Ú ýO¸‘âh½ï4pdf:dest (page.29) [@thispage /XYZ @xpos @ypos null]Ÿüfd²CONTENTSŽŽŽ’< ¿5.–UUBuilding“and“testing“the“resulting“pac¸ãk‘ÿqÇageŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘;ïËextra_compile_args=["-g"],ޤ ‘;ïlibrary_dirs=["../lib/"],Ž¡‘;ïlibraries=["cbf"],Ž¡‘;ïinclude_dirs–¹–=“["../include"]“)Ž¡¡‘h¿#–¹–Build“itŽ¡‘h¿setup(name="_pycbf",ext_modules=[e],)Ž¡‘h¿ÊŽŽ‘âh½Ÿ6ï6pdf:dest (section.5) [@thispage /XYZ @xpos @ypos null]ŸBc‘È5Ž‘1LÍBuilding–ffand“testing“the“resulting“pacŒÌk‘ÿ™ageŽŸ%Ô‘ÅAim–Tto“build“and“test“in“one“go“(so“that“the“source“and“the“binary“matc¾9h!!)ŽŸp;òŸ¤Ïþ‘Ë"win32.bat"‘T½29a‘ÕXÊŽŸ ¡‘2Ënuweb‘¹–pycbfŽ¡‘2latex‘¹–pycbfŽ¡‘2nuweb‘¹–pycbfŽ¡‘2latex‘¹–pycbfŽ¡‘2dvipdfm‘¹–pycbfŽ¡‘2nuweb‘¹–pycbfŽ¡‘2C:\python24\python–¹–make_pycbf.py“>“TODO.txtŽ¡‘2"C:\program–¹–files\swigwin-1.3.31\swig.exe"“-python“pycbf.iŽ¡‘2C:\python24\python–¹–setup.py“build“--compiler=mingw32Ž¡‘2copy–¹–build\lib.win32-2.4\_pycbf.pyd“.Ž¡‘2REM–¹–C:\python24\python“pycbf_test1.pyŽ¡‘2C:\python24\python‘¹–pycbf_test2.pyŽ¡‘2C:\python24\python‘¹–pycbf_test3.pyŽ¡‘2C:\python24\lib\pydoc.py–¹–-w“pycbfŽ¡‘2C:\python24\python–¹–makeflatascii.py“pycbf_ascii_help.txtŽ¡‘2ÊŽŽŽŽ Ò矟W‘Ë"linux.sh"‘T½29b‘ÕXÊŽŸ ¡‘2Ënuweb‘¹–pycbfŽ¡‘2latex‘¹–pycbfŽ¡‘2nuweb‘¹–pycbfŽ¡‘2latex‘¹–pycbfŽ¡‘2dvipdfm‘¹–pycbfŽ¡‘2nuweb‘¹–pycbfŽ¡‘2lynx–¹–-dump“CBFlib.html“>“CBFlib.txtŽ¡‘2python‘¹–make_pycbf.pyŽ¡‘2swig–¹–-python“pycbf.iŽ¡‘2python–¹–setup.py“buildŽ¡‘2rm‘¹–_pycbf.soŽ¡‘2cp–¹–build/lib.linux-i686-2.4/_pycbf.so“.Ž¡‘2python‘¹–pycbf_test1.pyŽ¡‘2python‘¹–pycbf_test2.pyŽ¡‘2pydoc–¹–-w“pycbfŽ¡‘2python–¹–makeflatascii.py“pycbf_ascii_help.txtŽ¡‘2ÊŽŽŽŽŸx÷‘ÅThis–Tstill“givš¾9es“bAÇold“in“the“ascii“(=suc˜ks)ŽŸKñ‘Ë"makeflatascii.py"‘T½29c‘ÕXÊŽŸç+¡‘/Ëimport–¹–pydoc,“pycbf,“sysŽ¡‘/f–¹–=“open(sys.argv[1],"w")Ž¡‘/pydoc.pager=lambda–¹–text:“f.write(text)Ž¡‘/pydoc.TextDoc.bold–¹–=“lambda“self,text“:“textŽ¡‘/pydoc.help(pycbf)Ž¡‘/ÊŽŽŽŸ‘âh½Ÿô‰ff&NŸ ²J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽ’ä\June–UU5,“2007ŽŽ’ö&J29ŽŽŽŽŽŽŽŽŒ‹Z Ú ýO¸‘âh½ï4pdf:dest (page.30) [@thispage /XYZ @xpos @ypos null]Ÿüfd–UU²6.“Debugging“compiled“extensionsŽŽŽ’ÇX CONTENTSŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH‘âh½ ýKO¸ï6pdf:dest (section.6) [@thispage /XYZ @xpos @ypos null]Ÿ ‘È6Ž‘1LÍDebugging–ffcompiled“extensionsŽŸ+º‘ÅSince– 9it› :can“bAÇe˜a“bit˜of“a˜pain“to˜see“where˜things“go˜wrong“here˜is“a˜quic¾9k“recipAÇe˜for“pAÇoking˜aroundޤ ‘with–Ta“debugger:ŽŸºJ‘Ëamber–¹–$>“gdb“/bliss/users//blissadm/python/bliss_python/suse82/bin/pythonŽ¡‘GNU–¹–gdb“5.3Ž¡‘Copyright–¹–2002“Free“Software“Foundation,“Inc.Ž¡‘GDB–¹–is“free“software,“covered“by“the“GNU“General“Public“License,“and“you“areŽ¡‘welcome–¹–to“change“it“and/or“distribute“copies“of“it“under“certain“conditions.Ž¡‘Type–¹–"show“copying"“to“see“the“conditions.Ž¡‘There–¹–is“absolutely“no“warranty“for“GDB.‘ s,Type“"show“warranty"“for“details.Ž¡‘This–¹–GDB“was“configured“as“"i586-suse-linux"...Ž¡‘(gdb)–¹–br“_PyImport_LoadDynamicModuleŽ¡‘Breakpoint–¹–1“at“0x80e4199:“file“Python/importdl.c,“line“28.ŽŸ•‘&ßüÅThis–Tis“hoš¾9w“to“get“a“breakpAÇoin˜t“when“loading“the“moAÇduleŽ©•‘Ë(gdb)‘¹–runŽ¡‘Starting–¹–program:“/mntdirect/_bliss/users/blissadm/python/bliss_python/suse82/bin/pythonŽ¡‘[New–¹–Thread“16384“(LWP“18191)]Ž¡‘Python–¹–2.4.2“(#3,“Feb“17“2006,“09:12:13)Ž¡‘[GCC–¹–3.3“20030226“(prerelease)“(SuSE“Linux)]“on“linux2Ž¡‘Type–¹–"help",“"copyright",“"credits"“or“"license"“for“more“information.Ž¡‘>>>–¹–import“pycbfŽ¡‘[Switching–¹–to“Thread“16384“(LWP“18191)]Ž¡¡‘Breakpoint–¹–1,“_PyImport_LoadDynamicModule“(name=0xbfffd280“"_pycbf.so",Ž¡‘+æZpathname=0xbfffd280–¹–"_pycbf.so",“fp=0x819e208)“at“Python/importdl.c:28Ž¡‘28‘B&4if–¹–((m“=“_PyImport_FindExtension(name,“pathname))“!=“NULL)“{Ž¡‘(gdb)‘¹–finishŽ¡‘Run–¹–till“exit“from“#0‘ s,_PyImport_LoadDynamicModule“(Ž¡‘+æZname=0xbfffd280–¹–"_pycbf.so",“pathname=0xbfffd280“"_pycbf.so",“fp=0x819e208)Ž¡‘+æZat‘¹–Python/importdl.c:28Ž¡‘load_module–¹–(name=0xbfffd710“"_pycbf",“fp=0x819e208,Ž¡‘+æZbuf=0xbfffd280–¹–"_pycbf.so",“type=3,“loader=0x405b44f4)Ž¡‘+æZat‘¹–Python/import.c:1678Ž¡‘1678‘^¸break;Ž¡‘Value–¹–returned“is“$1“=“(PyObject“*)“0x405662fcŽ¡‘(gdb)–¹–break“cbf_read_fileŽ¡‘Breakpoint–¹–2“at“0x407f0508:“file“../src/cbf.c,“line“221.Ž¡‘(gdb)‘¹–contŽ¡‘Continuing.ŽŸoÆ‘&ßüÅW‘ÿ:«e–Tnoš¾9w“ha˜v˜e“a“breakpAÇoin˜t“where“w˜e“w˜an˜ted“inside“the“dynamically“loaded“ le.ަ‘Ë>>>‘¹–o=pycbf.cbf_handle_struct()Ž¡‘>>>‘¹–o.read_file("../img2cif_packed.cif",pycbf.MSG_DIGEST)Ž¡¡‘Breakpoint–¹–2,“cbf_read_file“(handle=0x81f7c08,“stream=0x8174f58,Ž¡‘+æZheaders=136281096)–¹–at“../src/cbf.c:221Ž¡‘221‘!if‘¹–(!handle)Ž¡‘(gdb)ŽŸoÆ‘&ßüÅNo•¾9w›Ty“ou˜can˜step˜through˜the˜c...ŽŸà\ï6pdf:dest (section.7) [@thispage /XYZ @xpos @ypos null]ŸeA‘È7Ž‘1LÍThings–ffwhicšŒÌh“are“curren˜tly“missingŽŸ+º‘ÅThis–E›is›Eœthe“to“do˜list.‘­FObš¾9viously“w˜e›Eœcould“bAÇene t“a˜lot“from“more˜extensiv¾9e“testing“and˜c•¾9hec“king‘E›ofŽ¡‘the–TdoAÇcstrings“etc.ŽŸºJ‘ËThis–¹–output“comes“from“make_pycbf.py“which“generates“the“wrappersŽ¡‘Have–¹–not“implemented:“cbfhandle.set_imageŽ¡‘+æZcbf_set_imageŽ¡‘+æZargs:Ž¡‘>̲cbf_handle‘¹–handleŽŽŸ‘âh½Ÿô‰ff&NŸ ²30ŽŽŽ’ä\June–UU5,“2007ŽŽ’Ê‚¸J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽŽŽŽŽŽŒ‹c| Ú ýO¸‘âh½ï4pdf:dest (page.31) [@thispage /XYZ @xpos @ypos null]Ÿüfd²CONTENTSŽŽŽ’[-W7.–UUThings“whicš¸ãh“are“curren˜tly“missingŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘!5oËunsigned–¹–int“reservedޤ ‘!5ounsigned‘æXint‘¹–element_numberŽ¡‘!5ounsigned–¹–int“compressionŽ¡‘!5ovoid‘¹–*arrayŽ¡‘!5osize_t‘æXelsizeŽ¡‘!5oint‘¹–elsignŽ¡‘!5osize_t‘¹–ndim1Ž¡‘!5osize_t‘¹–ndim2Ž¡¡‘ûh¿Have–¹–not“implemented:“cbfhandle.set_bin_sizesŽ¡‘Ocbf_set_bin_sizesŽ¡‘Oargs:Ž¡‘!5ocbf_handle‘¹–handleŽ¡‘!5ounsigned–¹–int“element_numberŽ¡‘!5odouble‘¹–slowbinsize_inŽ¡‘!5odouble‘¹–fastbinsize_inŽ¡¡‘ûh¿Have–¹–not“implemented:“cbfhandle.get_unit_cellŽ¡‘Ocbf_get_unit_cellŽ¡‘Oargs:Ž¡‘!5ocbf_handle‘¹–handleŽ¡‘!5odouble‘¹–cell[6]Ž¡‘!5odouble‘æXcell_esd[6]Ž¡¡‘ûh¿Have–¹–not“implemented:“cbfhandle.set_reciprocal_cellŽ¡‘Ocbf_set_reciprocal_cellŽ¡‘Oargs:Ž¡‘!5ocbf_handle‘¹–handleŽ¡‘!5odouble‘¹–cell[6]Ž¡‘!5odouble‘æXcell_esd[6]Ž¡¡‘ûh¿Have–¹–not“implemented:“cbfhandle.read_widefileŽ¡‘Ocbf_read_widefileŽ¡‘Oargs:Ž¡‘!5ocbf_handle‘¹–handleŽ¡‘!5oFILE‘¹–*fileŽ¡‘!5oint‘¹–headersŽ¡¡‘ûh¿Have–¹–not“implemented:Ž¡‘ûh¿cbf_compute_cell_volumeŽ¡‘ûh¿compute_cell_volumeŽ¡‘ûh¿double‘¹–cell[6]Ž¡‘ûh¿double‘¹–*volumeŽ¡¡‘ûh¿Have–¹–not“implemented:“cbfhandle.set_realarray_wdimsŽ¡‘Ocbf_set_realarray_wdimsŽ¡‘Oargs:Ž¡‘!5ocbf_handle‘¹–handleŽ¡‘!5ounsigned‘¹–int‘æXcompressionŽ¡‘!5oint‘¹–binary_idŽ¡‘!5ovoid‘¹–*arrayŽ¡‘!5osize_t‘¹–elsizeŽ¡‘!5osize_t‘æXelementsŽ¡‘!5oconst–¹–char“*byteorderŽ¡‘!5osize_t‘¹–dim1Ž¡‘!5osize_t‘¹–dim2Ž¡‘!5osize_t‘æXdim3Ž¡‘!5osize_t‘¹–paddingŽ¡¡‘ûh¿problem–¹–cbf_set_saveframename“set_saveframename“['cbf_handle“handle.“const“char‘æX*saveframename']Ž¡‘ûh¿Have–¹–not“implemented:“cbfhandle.get_integerarrayparameters_wdimsŽ¡‘Ocbf_get_integerarrayparameters_wdimsŽ¡‘Oargs:ŽŽŸ‘âh½Ÿô‰ff&NŸ ²J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽ’ä\June–UU5,“2007ŽŽ’ö&J31ŽŽŽŽŽŽŽŽŒ‹ q Ú ýO¸‘âh½ï4pdf:dest (page.32) [@thispage /XYZ @xpos @ypos null]Ÿüfd–UU²7.“Things“whicš¸ãh“are“curren˜tly“missingŽŽŽ’ÇX CONTENTSŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘!5oËcbf_handle‘¹–handleޤ ‘!5ounsigned‘æXint‘¹–*compressionŽ¡‘!5oint‘¹–*binary_idŽ¡‘!5osize_t‘¹–*elsizeŽ¡‘!5oint‘¹–*elsignedŽ¡‘!5oint‘æX*elunsignedŽ¡‘!5osize_t‘¹–*elementsŽ¡‘!5oint‘¹–*minelementŽ¡‘!5oint‘¹–*maxelementŽ¡‘!5oconst‘æXchar‘¹–**byteorderŽ¡‘!5osize_t‘¹–*dim1Ž¡‘!5osize_t‘¹–*dim2Ž¡‘!5osize_t‘¹–*dim3Ž¡‘!5osize_t‘æX*paddingŽ¡¡‘ûh¿Have–¹–not“implemented:“cbfhandle.set_real_3d_imageŽ¡‘Ocbf_set_real_3d_imageŽ¡‘Oargs:Ž¡‘!5ocbf_handle‘¹–handleŽ¡‘!5ounsigned–¹–int“reservedŽ¡‘!5ounsigned–¹–int“element_numberŽ¡‘!5ounsigned–¹–int“compressionŽ¡‘!5ovoid‘æX*arrayŽ¡‘!5osize_t‘¹–elsizeŽ¡‘!5osize_t‘¹–ndim1Ž¡‘!5osize_t‘¹–ndim2Ž¡‘!5osize_t‘¹–ndim3Ž¡¡‘ûh¿Have–¹–not“implemented:“cbfhandle.get_realarrayŽ¡‘Ocbf_get_realarrayŽ¡‘Oargs:Ž¡‘!5ocbf_handle‘¹–handleŽ¡‘!5oint‘¹–*binary_idŽ¡‘!5ovoid‘¹–*arrayŽ¡‘!5osize_t‘¹–elsizeŽ¡‘!5osize_t‘¹–elementsŽ¡‘!5osize_t‘¹–*elements_readŽ¡¡‘ûh¿Have–¹–not“implemented:“cbfhandle.get_bin_sizesŽ¡‘Ocbf_get_bin_sizesŽ¡‘Oargs:Ž¡‘!5ocbf_handle‘¹–handleŽ¡‘!5ounsigned–¹–int“element_numberŽ¡‘!5odouble–¹–*“slowbinsizeŽ¡‘!5odouble–¹–*“fastbinsizeŽ¡¡‘ûh¿Have–¹–not“implemented:“cbfhandle.set_3d_imageŽ¡‘Ocbf_set_3d_imageŽ¡‘Oargs:Ž¡‘!5ocbf_handle‘¹–handleŽ¡‘!5ounsigned–¹–int“reservedŽ¡‘!5ounsigned–¹–int“element_numberŽ¡‘!5ounsigned–¹–int“compressionŽ¡‘!5ovoid‘¹–*arrayŽ¡‘!5osize_t‘¹–elsizeŽ¡‘!5oint‘¹–elsignŽ¡‘!5osize_t‘¹–ndim1Ž¡‘!5osize_t‘¹–ndim2Ž¡‘!5osize_t‘æXndim2=3Ž¡¡‘ûh¿Have–¹–not“implemented:“cbfhandle.set_integerarray_wdimsŽ¡‘Ocbf_set_integerarray_wdimsŽ¡‘Oargs:ŽŽŸ‘âh½Ÿô‰ff&NŸ ²32ŽŽŽ’ä\June–UU5,“2007ŽŽ’Ê‚¸J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽŽŽŽŽŽŒ‹!xñ Ú ýO¸‘âh½ï4pdf:dest (page.33) [@thispage /XYZ @xpos @ypos null]Ÿüfd²CONTENTSŽŽŽ’[-W7.–UUThings“whicš¸ãh“are“curren˜tly“missingŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘!5oËcbf_handle‘¹–handleޤ ‘!5ounsigned‘¹–int‘æXcompressionŽ¡‘!5oint‘¹–binary_idŽ¡‘!5ovoid‘¹–*arrayŽ¡‘!5osize_t‘¹–elsizeŽ¡‘!5oint‘¹–elsignedŽ¡‘!5osize_t‘¹–elementsŽ¡‘!5oconst–¹–char“*byteorderŽ¡‘!5osize_t‘¹–dim1Ž¡‘!5osize_t‘¹–dim2Ž¡‘!5osize_t‘¹–dim3Ž¡‘!5osize_t‘¹–paddingŽ¡¡‘ûh¿Have–¹–not“implemented:“cbfhandle.get_real_imageŽ¡‘Ocbf_get_real_imageŽ¡‘Oargs:Ž¡‘!5ocbf_handle‘¹–handleŽ¡‘!5ounsigned–¹–int“reservedŽ¡‘!5ounsigned–¹–int“element_numberŽ¡‘!5ovoid‘¹–*arrayŽ¡‘!5osize_t‘¹–elsizeŽ¡‘!5osize_t‘¹–ndim1Ž¡‘!5osize_t‘¹–ndim2Ž¡¡‘ûh¿TODO:–¹–Detector:“int“cbf_set_beam_center“(cbf_detector“detector,“double“*index1,“double‘æX*index2,“double“*center1,“double“*center2);Ž¡‘ûh¿Have–¹–not“implemented:“cbfhandle.get_realarrayparameters_wdimsŽ¡‘Ocbf_get_realarrayparameters_wdimsŽ¡‘Oargs:Ž¡‘!5ocbf_handle‘¹–handleŽ¡‘!5ounsigned‘¹–int‘æX*compressionŽ¡‘!5oint‘¹–*binary_idŽ¡‘!5osize_t‘¹–*elsizeŽ¡‘!5osize_t‘¹–*elementsŽ¡‘!5oconst‘æXchar‘¹–**byteorderŽ¡‘!5osize_t‘¹–*dim1Ž¡‘!5osize_t‘¹–*dim2Ž¡‘!5osize_t‘¹–*dim3Ž¡‘!5osize_t‘æX*paddingŽ¡¡‘ûh¿Have–¹–not“implemented:“cbfhandle.get_reciprocal_cellŽ¡‘Ocbf_get_reciprocal_cellŽ¡‘Oargs:Ž¡‘!5ocbf_handle‘¹–handleŽ¡‘!5odouble‘¹–cell[6]Ž¡‘!5odouble‘æXcell_esd[6]Ž¡¡‘ûh¿Have–¹–not“implemented:“cbfhandle.get_3d_image_sizeŽ¡‘Ocbf_get_3d_image_sizeŽ¡‘Oargs:Ž¡‘!5ocbf_handle‘¹–handleŽ¡‘!5ounsigned–¹–int“reservedŽ¡‘!5ounsigned–¹–int“element_numberŽ¡‘!5osize_t‘¹–*ndim1Ž¡‘!5osize_t‘¹–*ndim2Ž¡‘!5osize_t‘æX*ndim3Ž¡¡‘ûh¿Have–¹–not“implemented:“cbfhandle.set_real_imageŽ¡‘Ocbf_set_real_imageŽ¡‘Oargs:Ž¡‘!5ocbf_handle‘¹–handleŽ¡‘!5ounsigned–¹–int“reservedŽ¡‘!5ounsigned–¹–int“element_numberŽ¡‘!5ounsigned–¹–int“compressionŽŽŸ‘âh½Ÿô‰ff&NŸ ²J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽ’ä\June–UU5,“2007ŽŽ’ö&J33ŽŽŽŽŽŽŽŽŒ‹"€ Ú ýO¸‘âh½ï4pdf:dest (page.34) [@thispage /XYZ @xpos @ypos null]Ÿüfd–UU²7.“Things“whicš¸ãh“are“curren˜tly“missingŽŽŽ’ÇX CONTENTSŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘!5oËvoid‘æX*arrayޤ ‘!5osize_t‘¹–elsizeŽ¡‘!5osize_t‘¹–ndim1Ž¡‘!5osize_t‘¹–ndim2Ž¡¡‘ûh¿Have–¹–not“implemented:“cbfhandle.get_3d_imageŽ¡‘Ocbf_get_3d_imageŽ¡‘Oargs:Ž¡‘!5ocbf_handle‘¹–handleŽ¡‘!5ounsigned–¹–int“reservedŽ¡‘!5ounsigned–¹–int“element_numberŽ¡‘!5ovoid‘¹–*arrayŽ¡‘!5osize_t‘¹–elsizeŽ¡‘!5oint‘¹–elsignŽ¡‘!5osize_t‘¹–ndim1Ž¡‘!5osize_t‘¹–ndim2Ž¡‘!5osize_t‘¹–ndim3Ž¡¡‘ûh¿Have–¹–not“implemented:Ž¡‘ûh¿cbf_compute_reciprocal_cellŽ¡‘ûh¿compute_reciprocal_cellŽ¡‘ûh¿double‘¹–cell[6]Ž¡‘ûh¿double‘¹–rcell[6]Ž¡¡‘ûh¿Have–¹–not“implemented:“cbfhandle.get_imageŽ¡‘Ocbf_get_imageŽ¡‘Oargs:Ž¡‘!5ocbf_handle‘¹–handleŽ¡‘!5ounsigned–¹–int“reservedŽ¡‘!5ounsigned‘æXint‘¹–element_numberŽ¡‘!5ovoid‘¹–*arrayŽ¡‘!5osize_t‘¹–elsizeŽ¡‘!5oint‘¹–elsignŽ¡‘!5osize_t‘æXndim1Ž¡‘!5osize_t‘¹–ndim2Ž¡¡‘ûh¿Have–¹–not“implemented:“cbfhandle.write_widefileŽ¡‘Ocbf_write_widefileŽ¡‘Oargs:Ž¡‘!5ocbf_handle‘¹–handleŽ¡‘!5oFILE‘¹–*fileŽ¡‘!5oint‘¹–readableŽ¡‘!5oint‘¹–ciforcbfŽ¡‘!5oint‘¹–headersŽ¡‘!5oint‘¹–encodingŽ¡¡‘ûh¿Have–¹–not“implemented:“cbfhandle.get_real_3d_imageŽ¡‘Ocbf_get_real_3d_imageŽ¡‘Oargs:Ž¡‘!5ocbf_handle‘¹–handleŽ¡‘!5ounsigned–¹–int“reservedŽ¡‘!5ounsigned–¹–int“element_numberŽ¡‘!5ovoid‘¹–*arrayŽ¡‘!5osize_t‘¹–elsizeŽ¡‘!5osize_t‘¹–ndim1Ž¡‘!5osize_t‘¹–ndim2Ž¡‘!5osize_t‘¹–ndim3Ž¡¡‘ûh¿Have–¹–not“implemented:“cbfhandle.set_realarrayŽ¡‘Ocbf_set_realarrayŽ¡‘Oargs:Ž¡‘!5ocbf_handle‘¹–handleŽ¡‘!5ounsigned–¹–int“compressionŽŽŸ‘âh½Ÿô‰ff&NŸ ²34ŽŽŽ’ä\June–UU5,“2007ŽŽ’Ê‚¸J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽŽŽŽŽŽŒ‹#ˆÇ Ú ýO¸‘âh½ï4pdf:dest (page.35) [@thispage /XYZ @xpos @ypos null]Ÿüfd²CONTENTSŽŽŽ’Õ ×8.‘UUT‘ÿ*ªestingŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘!5oËint‘¹–binary_idޤ ‘!5ovoid‘¹–*arrayŽ¡‘!5osize_t‘¹–elsizeŽ¡‘!5osize_t‘¹–elementsŽ¡¡‘ûh¿Have–¹–not“implemented:“cbfhandle.set_unit_cellŽ¡‘Ocbf_set_unit_cellŽ¡‘Oargs:Ž¡‘!5ocbf_handle‘¹–handleŽ¡‘!5odouble‘¹–cell[6]Ž¡‘!5odouble‘æXcell_esd[6]Ž¡¡‘ûh¿End–¹–of“output“from“make_pycbf.pyŽ‘âh½Ÿ`ãï6pdf:dest (section.8) [@thispage /XYZ @xpos @ypos null]Ÿ‘È8Ž‘1LÍT‘þ¦festingŽŸ阑ÅSome–~Btest›~Aprograms“to“see“if˜anš¾9ything“appAÇears“to“w˜ork.‘êEv˜en˜tually“it“w˜ould‘~AbšAÇe“go˜o˜d“to“write‘~Aa“prop˜erŽ¡‘unit–Ttest“suite.ŽŸ häï;pdf:dest (subsection.8.1) [@thispage /XYZ @xpos @ypos null]Ÿ‘Ì8.1Ž‘7ÀRead–€a“ le“based“on“cif2cbf.cŽŸÏþ‘ÅThis–‚†is›‚‡a“prett¾9y˜ugly“translation˜of“the˜program“cif2cbf.c“skipping˜all“of˜the“writing˜parts.‘ëIt“appAÇearedŽ¡‘to–C|wš¾9ork“with‘C}the“ le“img2cif‘މffÆgŽ‘Typac˜k˜ed.cif“whic˜h“is‘C}built“when“y˜ou“build–C}CBFlib,‘hence“that–C| le“isŽ¡‘hardwired‘Tin.ŽŸI¯‘Ë"pycbf_test1.py"‘T½35‘ÕXÊŽŸ ã<¡‘/Ëimport‘¹–pycbfŽ¡‘/object–¹–=“pycbf.cbf_handle_struct()“#“FIXMEŽ¡‘/object.read_file("../img2cif_packed.cif",pycbf.MSG_DIGEST)Ž¡‘/object.rewind_datablock()Ž¡‘/print‘¹–"Found",object.count_datablocks(),"blocks"Ž¡‘/object.select_datablock(0)Ž¡‘/print–¹–"Zeroth“is“named",object.datablock_name()Ž¡‘/object.rewind_category()Ž¡‘/categories–¹–=“object.count_categories()Ž¡‘/for–¹–i“in“range(categories):Ž¡‘AæZprint‘¹–"Category:",i,Ž¡‘AæZobject.select_category(i)Ž¡‘AæZcategory_name–¹–=“object.category_name()Ž¡‘AæZprint‘¹–"Name:",category_name,Ž¡‘AæZrows=object.count_rows()Ž¡‘AæZprint‘¹–"Rows:",rows,Ž¡‘AæZcols–¹–=“object.count_columns()Ž¡‘AæZprint‘¹–"Cols:",colsŽ¡‘AæZloop=1Ž¡‘AæZobject.rewind_column()Ž¡‘AæZwhile–¹–loop“is“not“0:Ž¡‘T̲column_name–¹–=“object.column_name()Ž¡‘T̲print–¹–"column“name“\"",column_name,"\"",Ž¡‘T̲try:Ž¡‘bùtobject.next_column()Ž¡‘T̲except:Ž¡‘bùtbreakŽ¡‘AæZprintŽ¡‘AæZfor–¹–j“in“range(rows):Ž¡‘T̲object.select_row(j)Ž¡‘T̲object.rewind_column()Ž¡‘T̲print‘¹–"row:",jŽ¡‘T̲for–¹–k“in“range(cols):Ž¡‘g³ name=object.column_name()Ž¡‘g³ print‘¹–"col:",name,Ž¡‘g³ object.select_column(k)ŽŽŸ‘âh½Ÿô‰ff&NŸ ²J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽ’ä\June–UU5,“2007ŽŽ’ö&J35ŽŽŽŽŽŽŽŽŒ‹$ Ú ýO¸‘âh½ï4pdf:dest (page.36) [@thispage /XYZ @xpos @ypos null]Ÿüfd²8.2‘ T‘ÿ*ªry–UUto“test“the“goniometer“and“detectorŽŽŽ’ÇX CONTENTSŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘JÇËtypeofvalue=object.get_typeofvalue()ޤ ‘JÇprint‘¹–"type:",typeofvalueŽ¡‘JÇif–¹–typeofvalue.find("bnry")“>“-1:Ž¡‘]print–¹–"Found“the“binary!!",Ž¡‘]s=object.get_integerarray_as_string()Ž¡‘]print‘¹–type(s)Ž¡‘]print‘¹–dir(s)Ž¡‘]print‘¹–len(s)Ž¡‘]try:Ž¡‘k.áimport‘¹–NumericŽ¡‘k.ád–¹–=“Numeric.fromstring(s,Numeric.UInt32)Ž¡‘k.á#–¹–Hard“wired“Unsigned“Int32Ž¡‘k.áprint‘¹–d.shapeŽ¡‘k.áprint‘¹–d[0:10],d[d.shape[0]/2],d[-1]Ž¡‘k.ád=Numeric.reshape(d,(2300,2300))Ž¡‘h¿#‘YÆ"from–¹–matplotlib“import“pylabŽ¡‘h¿#‘YÆ"pylab.imshow(d,vmin=0,vmax=1000)Ž¡‘h¿#‘YÆ"pylab.show()Ž¡‘]except‘¹–ImportError:Ž¡‘k.áprint–¹–"You“need“to“get“Numeric“and“matplotlib“to“see“the“data"Ž¡‘JÇelse:Ž¡‘]value=object.get_value()Ž¡‘]print‘¹–"Val:",value,iŽ¡‘$OprintŽ¡‘h¿del(object)Ž¡‘h¿#Ž¡‘h¿print‘¹–dir()Ž¡‘h¿#object.free_handle(handle)Ž¡‘h¿ÊŽŽ‘âh½Ÿfïï;pdf:dest (subsection.8.2) [@thispage /XYZ @xpos @ypos null]Ÿ‘Ì8.2Ž‘7ÀT‘þàry–€to“test“the“goniometer“and“detectorŽ©Ïþ‘ÅHad–šŒsome“initial“diculties“but“then“doš¾9wnloaded“an“input“cbf“ le“whic˜h“de nes“a“goniometer“andŽ¡‘detector.‘pThe–T le“wš¾9as“found“in“the“example“data“whic˜h“comes“with“CBFlib.Ž¡‘&ßüThis–ŽŽtest“is“clearly“minimalistic“for“noš¾9w“-“it‘Žonly“c˜hec˜ks“the“ob‘ƒŽjects“for“apparen˜t“existence“of“aŽ¡‘single–Tmem¾9bAÇer“function.ŽŸ@è‘Ë"pycbf_test2.py"‘T½36a‘ÕXÊŽŸ àO¡‘/Ëimport‘¹–pycbfŽ¡‘/obj–¹–=“pycbf.cbf_handle_struct()Ž¡‘/obj.read_file("../adscconverted.cbf",0)Ž¡‘/obj.select_datablock(0)Ž¡‘/g–¹–=“obj.construct_goniometer()Ž¡‘/print–¹–"Rotation“axis“is",g.get_rotation_axis()Ž¡‘/d–¹–=“obj.construct_detector(0)Ž¡‘/print–¹–"Beam“center“is",d.get_beam_center()Ž¡‘/ÊŽŽŸ A8‘ÅIt–TappAÇears“to“wš¾9ork“-“ev˜en˜tually‘ÿ:«.‘pSurprisingŽŸ&Ÿï;pdf:dest (subsection.8.3) [@thispage /XYZ @xpos @ypos null]Ÿ @‘Ì8.3Ž‘7ÀT‘þàest–€cases“for“the“genericsަ‘Ë"pycbf_test3.py"‘T½36b‘ÕXÊŽŸ àO¡‘/Ëimport–¹–pycbf,“unittestŽ¡‘/class‘¹–GenericTests(unittest.TestCase):Ž¡¡‘AæZdef‘¹–test_get_local_integer_byte_order(self):Ž¡‘T̲self.assertEqual(‘¹–pycbf.get_local_integer_byte_order(),Ž¡’©Ù>'little_endian')Ž¡¡‘AæZdef‘¹–test_get_local_real_byte_order(self):Ž¡‘T̲self.assertEqual(–¹–pycbf.get_local_real_byte_order()“,Ž¡’©Ù>'little_endian')ŽŽŸ‘âh½Ÿô‰ff&NŸ ²36ŽŽŽ’ä\June–UU5,“2007ŽŽ’Ê‚¸J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽŽŽŽŽŽŒ‹%™Õ Ú ýO¸‘âh½ï4pdf:dest (page.37) [@thispage /XYZ @xpos @ypos null]Ÿüfd²CONTENTSŽŽŽ’ÁÐÓ9.–UUW‘ÿ*ªork¸ãed“example“1“:‘qÇxmas“bGeamline“+“mar“ccd“detector“at“the“ESRFŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘$OËdef‘¹–test_get_local_real_format(self):ޤ ‘75oself.assertEqual(‘¹–pycbf.get_local_real_format(),Ž¡’ŒAû'ieee‘¹–754-1985')Ž¡‘h¿if‘¹–__name__=="__main__":Ž¡‘$Ounittest.main()Ž¡¡‘h¿ÊŽŽ‘âh½Ÿ Nbï6pdf:dest (section.9) [@thispage /XYZ @xpos @ypos null]ŸA‘È9Ž‘1LÍW‘þ¦forkŒÌed–:example“1“:‘Nxmas“bs3eamline“+“mar“ccd“detec-ŽŸ‘tor–ffat“the“ESRFŽŸ] ‘ÅNoš¾9w–v‚for“the“in˜teresting›vpart.‘?úW‘ÿ:«e“will“attempt˜to“actually“use“p¾9ycbf“for“a˜real“dataproAÇcessing“task.Ž¡‘Crazy–Tyš¾9ou“migh˜t“think.Ž© A‘&ßüThe–(idea›(is“the“follo¾9wing“-˜wš¾9e“w˜an˜t“to‘(tak˜e“the“header“information›(from“some“mar“ccd˜ les“(andŽ¡‘ev•¾9en“tually– }also“the“user“or“the“spAÇec“conš¾9trol‘ |system)“and“pass“this“information“in˜to“cif“headers“whic˜hŽ¡‘can–TbAÇe“read“b¾9y“ t2d“(etc).ŽŸÔ3ï;pdf:dest (subsection.9.1) [@thispage /XYZ @xpos @ypos null]Ÿ ‘Ì9.1Ž‘7ÀReading–€marccd“headersŽŸC†‘ÅSome–Ê-relativ¾9ely›Ê,ugly“coAÇde˜whic¾9h“parses˜a“c˜header“and˜then“tries˜to“in¾9terpret˜the“mar“ccd˜headerŽ¡‘format.ަ‘&ßüFIXME–T:“b•¾9ytesw“apping–Tand“ends???ŽŸEq‘Ë"xmas/readmarheader.py"‘T½37‘ÕXÊŽŸ ãD‘/Ë#!/usr/bin/env‘¹–pythonŽ¡‘/import‘¹–structŽ¡¡‘/#–¹–Convert“mar“c“header“file“types“to“python“struct“module“typesŽ¡‘/mar_c_to_python_struct–¹–=“{Ž¡‘AæZ"INT32"‘ s,:‘¹–"i",Ž¡‘AæZ"UINT32"–¹–:“"I",Ž¡‘AæZ"char"‘,Â:‘¹–"c",Ž¡‘AæZ"UINT16"–¹–:“"H"Ž¡‘AæZ}Ž¡¡‘/#–¹–Sizes“(bytes)“of“mar“c“header“objectsŽ¡‘/mar_c_sizes–¹–=“{Ž¡‘AæZ"INT32"‘ s,:‘¹–4,Ž¡‘AæZ"UINT32"–¹–:“4,Ž¡‘AæZ"char"‘,Â:‘¹–1,Ž¡‘AæZ"UINT16"–¹–:“2Ž¡‘AæZ}Ž¡¡‘/#–¹–This“was“worked“out“by“trial“and“error“from“a“trial“image“I“thinkŽ¡‘/MAXIMAGES=9Ž¡¡¡¡‘/def‘¹–make_format(cdefinition):Ž¡‘AæZ"""Ž¡‘AæZReads–¹–the“header“definition“in“c“and“makes“the“formatŽ¡‘AæZstring–¹–to“pass“to“struct.unpackŽ¡‘AæZ"""Ž¡‘AæZlines–¹–=“cdefinition.split("\n")Ž¡‘AæZfmt–¹–=“""Ž¡‘AæZnames–¹–=“[]Ž¡‘AæZexpected–¹–=“0Ž¡‘AæZfor–¹–line“in“lines:Ž¡‘T̲if‘¹–line.find(";")==-1:Ž¡‘g³ continueŽ¡‘T̲decl‘ s,=‘¹–line.split(";")[0].lstrip().rstrip()Ž¡‘T̲try:ŽŽŸ‘âh½Ÿô‰ff&NŸ ²J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽ’ä\June–UU5,“2007ŽŽ’ö&J37ŽŽŽŽŽŽŽŽŒ‹&¤a Ú ýO¸‘âh½ï4pdf:dest (page.38) [@thispage /XYZ @xpos @ypos null]Ÿüfd²9.1‘ Reading–UUmarccd“headersŽŽŽ’ÇX CONTENTSŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘JÇË[type,–¹–name]“=“decl.split()ޤ ‘75oexcept:Ž¡‘JÇ#print‘¹–"skipping:",lineŽ¡‘JÇcontinueŽ¡‘75o#‘%̰print‘¹–"type:",type,"‘ s,name:",nameŽ¡¡‘75oif‘¹–name.find("[")>-1:Ž¡‘JÇ#–¹–repeated“...“timesŽ¡‘JÇtry:Ž¡‘]num–¹–=“name.split("[")[1].split("]")[0]Ž¡‘]num–¹–=“num.replace("MAXIMAGES",str(MAXIMAGES))Ž¡‘]num–¹–=“num.replace("sizeof(INT32)","4")Ž¡‘]times–¹–=“eval(num)Ž¡‘JÇexcept:Ž¡‘]print–¹–"Please“decode",declŽ¡‘]raiseŽ¡‘75oelse:Ž¡‘JÇtimes=1Ž¡‘75otry:Ž¡‘JÇfmt‘,Â+=‘¹–mar_c_to_python_struct[type]*timesŽ¡‘JÇnames–¹–+=“[name]*timesŽ¡‘JÇexpected–¹–+=“mar_c_sizes[type]*timesŽ¡‘75oexcept:Ž¡‘JÇ#print‘¹–"skipping",lineŽ¡‘JÇcontinueŽ¡‘75o#print–¹–"%4d“%4d"%(mar_c_sizes[type]*times,expected),name,":",times,lineŽ¡‘$O#print‘¹–struct.calcsize(fmt),expectedŽ¡‘$Oreturn–¹–names,“fmtŽ¡¡‘h¿def‘¹–read_mar_header(filename):Ž¡‘$O"""Ž¡‘$OGet–¹–the“header“from“a“binary“fileŽ¡‘$O"""Ž¡‘$Of–¹–=“open(filename,"rb")Ž¡‘$Of.seek(1024)Ž¡‘$Oheader=f.read(3072)Ž¡‘$Of.close()Ž¡‘$Oreturn‘¹–headerŽ¡¡¡‘h¿def–¹–interpret_header(header,“fmt,“names):Ž¡‘$O"""Ž¡‘$Ogiven–¹–a“format“and“header“interpret“itŽ¡‘$O"""Ž¡‘$Ovalues–¹–=“struct.unpack(fmt,header)Ž¡‘$Odict–¹–=“{}Ž¡‘$Oi=0Ž¡‘$Ofor–¹–name“in“names:Ž¡‘75oif‘¹–dict.has_key(name):Ž¡‘JÇif–¹–type(values[i])“==“type("string"):Ž¡‘a»µdict[name]–¹–=“dict[name]+values[i]Ž¡‘JÇelse:Ž¡‘a»µtry:Ž¡‘t¢ dict[name].append(values[i])Ž¡‘a»µexcept:Ž¡‘t¢ dict[name]–¹–=“[dict[name],values[i]]Ž¡‘75oelse:Ž¡‘JÇdict[name]–¹–=“values[i]Ž¡‘75oi=i+1Ž¡¡‘$Oreturn‘¹–dictŽ¡¡ŽŸ‘âh½Ÿô‰ff&NŸ ²38ŽŽŽ’ä\June–UU5,“2007ŽŽ’Ê‚¸J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽŽŽŽŽŽŒ‹'®- Ú ýO¸‘âh½ï4pdf:dest (page.39) [@thispage /XYZ @xpos @ypos null]Ÿüfd²CONTENTSŽŽŽ’~tv9.1‘ Reading–UUmarccd“headersŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘h¿Ë#–¹–Now“for“the“c“definition“(found“on“mar“webpage)ޤ ‘h¿#–¹–The“following“string“is“therefore“copyrighted“by“Mar“I“guessŽ¡¡‘h¿cdefinition–¹–=“"""Ž¡‘h¿typedef–¹–struct“frame_header_type“{Ž¡‘;ï/*–¹–File/header“format“parameters“(256“bytes)“*/Ž¡‘;ïUINT32‘%̰header_type;‘Y„/*–¹–flag“for“header“typeŽ¡’Ü”ñ(can–¹–be‘ s,used“as“magic“number)“*/Ž¡‘;ïchar–¹–header_name[16];‘3ùr/*“header“name“(MMX)“*/Ž¡‘;ïUINT32‘%̰header_major_version;‘Ÿî/*–¹–header_major_version‘ s,(n.)“*/Ž¡‘;ïUINT32‘%̰header_minor_version;‘Ÿî/*–¹–header_minor_version‘ s,(.n)“*/Ž¡‘;ïUINT32‘%̰header_byte_order;/*–¹–BIG_ENDIAN“(Motorola,MIPS);Ž¡’áN‡LITTLE_ENDIAN–¹–(DEC,“Intel)“*/Ž¡‘;ïUINT32‘%̰data_byte_order;‘ s,/*–¹–BIG_ENDIAN“(Motorola,MIPS);Ž¡’áN‡LITTLE_ENDIAN–¹–(DEC,“Intel)“*/Ž¡‘;ïUINT32‘%̰header_size;‘Y„/*–¹–in“bytes‘c9N*/Ž¡‘;ïUINT32‘%̰frame_type;‘!/*–¹–flag“for“frame“type“*/Ž¡‘;ïUINT32‘%̰magic_number;‘Ÿî/*–¹–to“be“used“as“a“flag“-Ž¡’áN‡usually‘ s,to–¹–indicate“new“file“*/Ž¡‘;ïUINT32‘%̰compression_type;–¹–/*“type“of“image“compression‘æX*/Ž¡‘;ïUINT32‘%̰compression1;‘Ÿî/*–¹–compression“parameter“1“*/Ž¡‘;ïUINT32‘%̰compression2;‘Ÿî/*–¹–compression“parameter“2“*/Ž¡‘;ïUINT32‘%̰compression3;‘Ÿî/*–¹–compression“parameter“3“*/Ž¡‘;ïUINT32‘%̰compression4;‘Ÿî/*–¹–compression“parameter“4“*/Ž¡‘;ïUINT32‘%̰compression5;‘Ÿî/*–¹–compression“parameter“4“*/Ž¡‘;ïUINT32‘%̰compression6;‘Ÿî/*–¹–compression“parameter“4“*/Ž¡‘;ïUINT32‘%̰nheaders;‘*†F/*–¹–total“number“of“headers‘Y„*/Ž¡‘;ïUINT32‘%̰nfast;‘8³/*–¹–number“of“pixels“in“one“line“*/Ž¡‘;ïUINT32‘%̰nslow;‘8³/*–¹–number“of“lines“in“image‘Ÿî*/Ž¡‘;ïUINT32‘%̰depth;‘8³/*–¹–number“of“bytes“per“pixel‘æX*/Ž¡‘;ïUINT32‘%̰record_length;‘æX/*–¹–number“of“pixels“betweenŽ¡’áN‡succesive–¹–rows“*/Ž¡‘;ïUINT32‘%̰signif_bits;‘Y„/*–¹–true“depth“of“data,“in“bits‘ s,*/Ž¡‘;ïUINT32–%̰data_type;“/*–¹–(signed,unsigned,float...)“*/Ž¡‘;ïUINT32‘%̰saturated_value;‘ s,/*–¹–value“marks“pixel“as“saturated“*/Ž¡‘;ïUINT32‘%̰sequence;‘*†F/*–¹–TRUE“or“FALSE“*/Ž¡‘;ïUINT32‘%̰nimages;‘/?Ü/*–¹–total“number“of“images“-“size“ofŽ¡’áN‡each–¹–is“nfast*(nslow/nimages)“*/Ž¡‘;ïUINT32‘%̰origin;‘3ùr/*–¹–corner“of“origin‘=lž*/Ž¡‘;ïUINT32‘%̰orientation;‘Y„/*–¹–direction“of“fast“axis‘!*/Ž¡‘;ïUINT32‘%̰view_direction;‘,Â/*–¹–direction“to“view“frame‘Y„*/Ž¡‘;ïUINT32‘%̰overflow_location;/*–¹–FOLLOWING_HEADER,‘ s,FOLLOWING_DATA“*/Ž¡‘;ïUINT32‘%̰over_8_bits;‘Y„/*–¹–#“of“pixels“with“counts‘ s,255“*/Ž¡‘;ïUINT32‘%̰over_16_bits;‘Ÿî/*–¹–#“of“pixels“with“count‘ s,65535“*/Ž¡‘;ïUINT32‘%̰multiplexed;‘Y„/*–¹–multiplex“flag“*/Ž¡‘;ïUINT32‘%̰nfastimages;‘Y„/*–¹–#“of“images“in“fast“direction“*/Ž¡‘;ïUINT32‘%̰nslowimages;‘Y„/*–¹–#“of“images“in“slow“direction“*/Ž¡‘;ïUINT32‘%̰background_applied;–¹–/*“flags“correction“has“been“applied“-Ž¡’êÁ³hold–¹–magic“number“?“*/Ž¡‘;ïUINT32‘%̰bias_applied;‘!/*–¹–flags“correction“has“been“applied“-Ž¡’êÁ³hold–¹–magic“number“?“*/Ž¡‘;ïUINT32‘%̰flatfield_applied;‘ s,/*–¹–flags“correction“has“been“applied“-Ž¡’êÁ³hold–¹–magic“number“?“*/Ž¡‘;ïUINT32‘%̰distortion_applied;–¹–/*“flags“correction“has“been“applied“-Ž¡’êÁ³hold–¹–magic“number“?“*/Ž¡‘;ïUINT32‘%̰original_header_type;‘Ÿî/*–¹–Header/frame“type“from‘ s,fileŽ¡’7that–¹–frame“is“read“from“*/Ž¡‘;ïUINT32‘%̰file_saved;‘*†F/*–¹–Flag“that“file“has“been‘ s,saved,Ž¡’êÁ³should–¹–be“zeroed“if“modified“*/Ž¡‘;ïchar‘¹–reserve1[(64-40)*sizeof(INT32)-16];Ž¡¡‘;ï/*–¹–Data“statistics“(128)“*/Ž¡‘;ïUINT32‘%̰total_counts[2];‘ s,/*–¹–64“bit“integer“range“=“1.85E19*/ŽŽŸ‘âh½Ÿô‰ff&NŸ ²J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽ’ä\June–UU5,“2007ŽŽ’ö&J39ŽŽŽŽŽŽŽŽŒ‹(µ¯ Ú ýO¸‘âh½ï4pdf:dest (page.40) [@thispage /XYZ @xpos @ypos null]Ÿüfd²9.1‘ Reading–UUmarccd“headersŽŽŽ’ÇX CONTENTSŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘;ïËUINT32‘%̰special_counts1[2];ޤ ‘;ïUINT32‘%̰special_counts2[2];Ž¡‘;ïUINT32‘%̰min;Ž¡‘;ïUINT32‘%̰max;Ž¡‘;ïUINT32‘%̰mean;Ž¡‘;ïUINT32‘%̰rms;Ž¡‘;ïUINT32‘%̰p10;Ž¡‘;ïUINT32‘%̰p90;Ž¡‘;ïUINT32‘%̰stats_uptodate;Ž¡‘;ïUINT32‘%̰pixel_noise[MAXIMAGES];–¹–/*“1000*base“noise“value“(ADUs)“*/Ž¡‘;ïchar‘¹–reserve2[(32-13-MAXIMAGES)*sizeof(INT32)];Ž¡¡‘;ï/*–¹–More“statistics“(256)“*/Ž¡‘;ïUINT16‘¹–percentile[128];Ž¡¡¡‘;ï/*–¹–Goniostat“parameters“(128“bytes)“*/Ž¡‘;ïINT32–¹–xtal_to_detector;‘ s,/*“1000*distance“in“millimeters“*/Ž¡‘;ïINT32–¹–beam_x;‘8³/*“1000*x“beam“position“(pixels)“*/Ž¡‘;ïINT32–¹–beam_y;‘8³/*“1000*y“beam“position“(pixels)“*/Ž¡‘;ïINT32–¹–integration_time;› s,/*“integration“time“in˜milliseconds“*/Ž¡‘;ïINT32–¹–exposure_time;‘Ÿî/*“exposure“time“in“milliseconds“*/Ž¡‘;ïINT32–¹–readout_time;‘Y„/*“readout“time“in“milliseconds“*/Ž¡‘;ïINT32–¹–nreads;‘8³/*“number“of“readouts“to“get“this‘ s,image“*/Ž¡‘;ïINT32–¹–start_twotheta;‘æX/*“1000*two_theta“angle“*/Ž¡‘;ïINT32–¹–start_omega;‘!/*“1000*omega“angle“*/Ž¡‘;ïINT32–¹–start_chi;‘*†F/*“1000*chi“angle“*/Ž¡‘;ïINT32–¹–start_kappa;‘!/*“1000*kappa“angle“*/Ž¡‘;ïINT32–¹–start_phi;‘*†F/*“1000*phi“angle“*/Ž¡‘;ïINT32–¹–start_delta;‘!/*“1000*delta“angle“*/Ž¡‘;ïINT32–¹–start_gamma;‘!/*“1000*gamma“angle“*/Ž¡‘;ïINT32–¹–start_xtal_to_detector;“/*“1000*distance“in“mm“(dist“in“um)*/Ž¡‘;ïINT32–¹–end_twotheta;‘3ùr/*“1000*two_theta“angle“*/Ž¡‘;ïINT32–¹–end_omega;‘B&4/*“1000*omega“angle“*/Ž¡‘;ïINT32–¹–end_chi;‘K™`/*“1000*chi“angle“*/Ž¡‘;ïINT32–¹–end_kappa;‘B&4/*“1000*kappa“angle“*/Ž¡‘;ïINT32–¹–end_phi;‘K™`/*“1000*phi“angle“*/Ž¡‘;ïINT32–¹–end_delta;‘B&4/*“1000*delta“angle“*/Ž¡‘;ïINT32–¹–end_gamma;‘B&4/*“1000*gamma“angle“*/Ž¡‘;ïINT32–¹–end_xtal_to_detector;‘,Â/*“1000*distance“in“mm“(dist“in“um)*/Ž¡‘;ïINT32–¹–rotation_axis;‘/?Ü/*“active“rotation“axis“*/Ž¡‘;ïINT32–¹–rotation_range;‘*†F/*“1000*rotation“angle“*/Ž¡‘;ïINT32–¹–detector_rotx;‘/?Ü/*“1000*rotation“of“detector‘ s,around“X“*/Ž¡‘;ïINT32–¹–detector_roty;‘/?Ü/*“1000*rotation“of“detector‘ s,around“Y“*/Ž¡‘;ïINT32–¹–detector_rotz;‘/?Ü/*“1000*rotation“of“detector‘ s,around“Z“*/Ž¡‘;ïchar‘¹–reserve3[(32-28)*sizeof(INT32)];Ž¡¡‘;ï/*–¹–Detector“parameters“(128“bytes)“*/Ž¡‘;ïINT32–¹–detector_type;‘8³/*“detector“type“*/Ž¡‘;ïINT32–¹–pixelsize_x;‘B&4/*“pixel“size“(nanometers)“*/Ž¡‘;ïINT32–¹–pixelsize_y;‘B&4/*“pixel“size“(nanometers)“*/Ž¡‘;ïINT32–¹–mean_bias;‘qf/*“1000*mean“bias“value“*/Ž¡‘;ïINT32–¹–photons_per_100adu;‘!/*“photons“/“100“ADUs“*/Ž¡‘;ïINT32–¹–measured_bias[MAXIMAGES];“/*“1000*mean“bias“value“for“each“image*/Ž¡‘;ïINT32–¹–measured_temperature[MAXIMAGES];‘ s,/*“Temperature“of“eachŽ¡’7detector–¹–in“milliKelvins“*/Ž¡‘;ïINT32–¹–measured_pressure[MAXIMAGES];“/*“Pressure“of“each‘ s,chamberŽ¡’ï{Iin–¹–microTorr“*/Ž¡‘;ï/*–¹–Retired“reserve4“when“MAXIMAGES“set“to“9“from“16“andŽ¡‘JÇtwo–¹–fields“removed,“and“temp“and“pressure“addedŽ¡‘@¨›char‘¹–reserve4[(32-(5+3*MAXIMAGES))*sizeof(INT32)]Ž¡‘;ï*/Ž¡ŽŸ‘âh½Ÿô‰ff&NŸ ²40ŽŽŽ’ä\June–UU5,“2007ŽŽ’Ê‚¸J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽŽŽŽŽŽŒ‹)Å7 Ú ýO¸‘âh½ï4pdf:dest (page.41) [@thispage /XYZ @xpos @ypos null]Ÿüfd²CONTENTSŽŽŽ’~tv9.1‘ Reading–UUmarccd“headersŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘;ïË/*–¹–X-ray“source“and“optics“parameters“(128“bytes)“*/ޤ ‘;ï/*–¹–X-ray“source“parameters“(8*4“bytes)“*/Ž¡‘;ïINT32–¹–source_type;‘B&4/*“(code)“-“target,“synch.“etc“*/Ž¡‘;ïINT32–¹–source_dx;‘K™`/*“Optics“param.“-“(size‘ s,microns)“*/Ž¡‘;ïINT32–¹–source_dy;‘K™`/*“Optics“param.“-“(size‘ s,microns)“*/Ž¡‘;ïINT32–¹–source_wavelength;‘%̰/*“wavelength‘ s,(femtoMeters)“*/Ž¡‘;ïINT32–¹–source_power;‘=lž/*“(Watts)“*/Ž¡‘;ïINT32–¹–source_voltage;‘3ùr/*“(Volts)“*/Ž¡‘;ïINT32–¹–source_current;‘3ùr/*“(microAmps)“*/Ž¡‘;ïINT32–¹–source_bias;‘B&4/*“(Volts)“*/Ž¡‘;ïINT32–¹–source_polarization_x;‘æX/*“()“*/Ž¡‘;ïINT32–¹–source_polarization_y;‘æX/*“()“*/Ž¡‘;ïchar‘¹–reserve_source[4*sizeof(INT32)];Ž¡¡‘;ï/*–¹–X-ray“optics_parameters“(8*4“bytes)“*/Ž¡‘;ïINT32–¹–optics_type;‘B&4/*“Optics“type“(code)*/Ž¡‘;ïINT32–¹–optics_dx;‘K™`/*“Optics“param.“-“(size‘ s,microns)“*/Ž¡‘;ïINT32–¹–optics_dy;‘K™`/*“Optics“param.“-“(size‘ s,microns)“*/Ž¡‘;ïINT32–¹–optics_wavelength;‘%̰/*“Optics“param.“-“(size‘ s,microns)“*/Ž¡‘;ïINT32–¹–optics_dispersion;‘%̰/*“Optics“param.“-“(*10E6)“*/Ž¡‘;ïINT32–¹–optics_crossfire_x;‘!/*“Optics“param.“-“(microRadians)“*/Ž¡‘;ïINT32–¹–optics_crossfire_y;‘!/*“Optics“param.“-“(microRadians)“*/Ž¡‘;ïINT32–¹–optics_angle;‘=lž/*“Optics“param.“-“(monoch.Ž¡’72theta–¹–-“microradians)“*/Ž¡‘;ïINT32–¹–optics_polarization_x;‘æX/*“()“*/Ž¡‘;ïINT32–¹–optics_polarization_y;‘æX/*“()“*/Ž¡‘;ïchar‘¹–reserve_optics[4*sizeof(INT32)];Ž¡¡‘;ïchar‘¹–reserve5[((32-28)*sizeof(INT32))];Ž¡¡‘;ï/*–¹–File“parameters“(1024“bytes)“*/Ž¡‘;ïchar‘¹–filetitle[128];‘8³/*‘ s,Title‘U Œ*/Ž¡‘;ïchar–¹–filepath[128];‘=lž/*“path“name“for“data– s,file“*/Ž¡‘;ïchar–¹–filename[64];‘B&4/*“name“of“data– s,file“*/Ž¡‘;ïchar–¹–acquire_timestamp[32];‘Ÿî/*“date“and“time“of‘ s,acquisition“*/Ž¡‘;ïchar–¹–header_timestamp[32];‘Y„/*“date“and“time“of“header– s,update“*/Ž¡‘;ïchar–¹–save_timestamp[32];‘%̰/*“date“and“time“file‘ s,saved“*/Ž¡‘;ïchar–¹–file_comments[512];‘%̰/*“comments,“use“as“desired‘,Â*/Ž¡‘;ïchar‘¹–reserve6[1024-(128+128+64+(3*32)+512)];Ž¡¡‘;ï/*–¹–Dataset“parameters“(512“bytes)“*/Ž¡‘;ïchar–¹–dataset_comments[512];‘Ÿî/*“comments,“used“as“desired‘,Â*/Ž¡‘;ï/*–¹–pad“out“to‘ s,3072“bytes“*/Ž¡‘;ïchar‘¹–pad[3072-(256+128+256+(3*128)+1024+512)];Ž¡¡‘;ï}‘¹–frame_header;Ž¡‘h¿"""Ž¡¡¡¡‘h¿class‘¹–marheaderreader:Ž¡‘$O"""Ž¡‘$OClass–¹–to“sit“and“read“a“series“of“images“(makes“format“etc“only“once)Ž¡‘$O"""Ž¡‘$Odef‘¹–__init__(self):Ž¡‘75o"""Ž¡‘75oInitialise–¹–internal“stuffŽ¡‘75o"""Ž¡‘75oself.names–¹–,“self.fmt“=“make_format(cdefinition)Ž¡‘$Odef‘¹–get_header(self,filename):Ž¡‘75o"""Ž¡‘75oReads–¹–a“header“from“file“filenameŽ¡‘75o"""ŽŽŸ‘âh½Ÿô‰ff&NŸ ²J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽ’ä\June–UU5,“2007ŽŽ’ö&J41ŽŽŽŽŽŽŽŽŒ‹*Ò‚ Ú ýO¸‘âh½ï4pdf:dest (page.42) [@thispage /XYZ @xpos @ypos null]Ÿüfd²9.2‘ W‘ÿ*ªriting–UUout“cif“ les“for“ t2d/xmasŽŽŽ’ÇX CONTENTSŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘75oËh=read_mar_header(filename)ޤ ‘75odict–¹–=“interpret_header(h,self.fmt,self.names)Ž¡‘75o#–¹–Append“ESRF“formatted“stuffŽ¡‘75oitems–¹–=“self.readesrfstring(dict["dataset_comments[512]"])Ž¡‘75ofor–¹–pair“in“items:Ž¡‘JÇdict[pair[0]]=pair[1]Ž¡‘75oitems–¹–=“self.readesrfstring(dict["file_comments[512]"])Ž¡‘75ofor–¹–pair“in“items:Ž¡‘JÇdict[pair[0]]=pair[1]Ž¡‘75odict["pixelsize_x_mm"]=‘¹–str(float(dict["pixelsize_x"])/1e6)Ž¡‘75odict["pixelsize_y_mm"]=‘¹–str(float(dict["pixelsize_y"])/1e6)Ž¡‘75odict["integration_time_sec"]=‘¹–str(float(dict["integration_time"])/1e3)Ž¡‘75odict["beam_y_mm"]=‘¹–str(float(dict["pixelsize_y_mm"])*Ž¡’Ó!Åfloat(dict["beam_y"])/1000.)Ž¡‘75odict["beam_x_mm"]=‘¹–str(float(dict["pixelsize_x_mm"])*Ž¡’Ó!Åfloat(dict["beam_x"])/1000.)Ž¡¡‘75oreturn‘¹–dictŽ¡¡‘$Odef‘¹–readesrfstring(self,s):Ž¡‘75o"""Ž¡‘75oInterpret–¹–the“so“called“"esrf“format"“header“linesŽ¡‘75owhich–¹–are“in“comment“sectionsŽ¡‘75o"""Ž¡‘75os=s.replace("\000","")Ž¡‘75oitems–¹–=“filter(None,“[len(x)>1“and“x“or“None“for“x“in“[Ž¡‘JÇitem.split("=")–¹–for“item“in“s.split(";")]])Ž¡‘75oreturn‘¹–itemsŽ¡¡¡‘h¿if‘¹–__name__=="__main__":Ž¡‘$O"""Ž¡‘$OMake–¹–a“little“program“to“process“filesŽ¡‘$O"""Ž¡‘$Oimport‘¹–sysŽ¡‘$Oprint‘¹–"Starting"Ž¡‘$Onames,fmt–¹–=“make_format(cdefinition)Ž¡‘$Oprint–¹–"Names“and“format“made"Ž¡‘$Oh–¹–=“read_mar_header(sys.argv[1])Ž¡‘$Oprint–¹–"Read“header,“interpreting"Ž¡‘$Od–¹–=“interpret_header(h,fmt,names)Ž¡‘$Oprinted–¹–=“{}Ž¡‘$Ofor–¹–name“in“names:Ž¡‘75oif‘¹–printed.has_key(name):Ž¡‘JÇcontinueŽ¡‘75oprint‘¹–name,":",d[name]Ž¡‘75oprinted[name]=1Ž¡¡‘h¿ÊŽŽ‘âh½Ÿ‚ï;pdf:dest (subsection.9.2) [@thispage /XYZ @xpos @ypos null]Ÿ‘Ì9.2Ž‘7ÀW‘þàriting–€out“cif“ les“for“ t2d/xmasŽŸÏþ‘ÅA‘è`script–è—whic¾9h›è–is“suppAÇosed˜to“pic¾9k˜up“some“header˜information“from˜the“mar“images,‘fsome“moreŽ¡‘infomation–Tfrom“the“user“and“the“create“cif“ les.Ž¡‘&ßüThis–Trelies“on“a“"template"“cif“ le“to“get“it“started“(a•¾9v“oids–Tme“programming“ev¾9erything).ŽŸn²‘Ë"xmas/xmasheaders.py"‘T½42‘ÕXÊŽŸ ï’‘/Ë#!/usr/bin/env‘¹–pythonŽ¡¡¡‘/import‘¹–pycbfŽ¡¡‘/#–¹–Some“cbf“helper“functions“-“obj“would“be“a“cbf_handle_struct“objectŽ¡ŽŸ‘âh½Ÿô‰ff&NŸ ²42ŽŽŽ’ä\June–UU5,“2007ŽŽ’Ê‚¸J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽŽŽŽŽŽŒ‹+Þˆ Ú ýO¸‘âh½ï4pdf:dest (page.43) [@thispage /XYZ @xpos @ypos null]Ÿüfd²CONTENTSŽŽŽ’R_9.2‘ W‘ÿ*ªriting–UUout“cif“ les“for“ t2d/xmasŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘h¿Ëdef‘¹–writewavelength(obj,wavelength):ޤ ‘$Oobj.set_wavelength(float(wavelength))Ž¡¡‘h¿def‘¹–writecellpar(obj,cifname,value):Ž¡‘$Oobj.find_category("cell")Ž¡‘$Oobj.find_column(cifname)Ž¡‘$Oobj.set_value(value)Ž¡¡‘h¿def‘¹–writecell(obj,cell):Ž¡‘$O"""Ž¡‘$Ocall–¹–with“cell“=“(a,b,c,alpha,beta,gamma)Ž¡‘$O"""Ž¡‘$Oobj.find_category("cell")Ž¡‘$Oobj.find_column("length_a")Ž¡‘$Oobj.set_value(str(cell[0]))Ž¡‘$Oobj.find_column("length_b")Ž¡‘$Oobj.set_value(str(cell[1]))Ž¡‘$Oobj.find_column("length_c")Ž¡‘$Oobj.set_value(str(cell[2]))Ž¡‘$Oobj.find_column("angle_alpha")Ž¡‘$Oobj.set_value(str(cell[3]))Ž¡‘$Oobj.find_column("angle_beta")Ž¡‘$Oobj.set_value(str(cell[4]))Ž¡‘$Oobj.find_column("angle_gamma")Ž¡‘$Oobj.set_value(str(cell[5]))Ž¡¡‘h¿def‘¹–writeUB(obj,ub):Ž¡‘$O"""Ž¡‘$Ocall–¹–with“ub“that“can“be“indexed“ub[i][j]Ž¡‘$O"""Ž¡‘$Oobj.find_category("diffrn_orient_matrix")Ž¡‘$Ofor–¹–i“in“(1,2,3):Ž¡‘75ofor–¹–j“in“(1,2,3):Ž¡‘JÇobj.find_column("UB[%d][%d]"%(i,j))Ž¡‘JÇobj.set_value(str(ub[i-1][j-1]))Ž¡¡‘h¿def‘¹–writedistance(obj,distance):Ž¡‘$Oobj.set_axis_setting("DETECTOR_Z",float(distance),0.)Ž¡¡¡‘h¿def‘¹–writebeam_x_mm(obj,cen):Ž¡‘$Oobj.set_axis_setting("DETECTOR_X",float(cen),0.)Ž¡¡‘h¿def‘¹–writebeam_y_mm(obj,cen):Ž¡‘$Oobj.set_axis_setting("DETECTOR_Y",float(cen),0.)Ž¡¡‘h¿def‘¹–writeSPECcmd(obj,s):Ž¡‘$Oobj.find_category("diffrn_measurement")Ž¡‘$Oobj.find_column("details")Ž¡‘$Oobj.set_value(s)Ž¡¡‘h¿def‘¹–writeSPECscan(obj,s):Ž¡‘$Oobj.find_category("diffrn_scan")Ž¡‘$Oobj.find_column("id")Ž¡‘$Oobj.set_value("SCAN%s"%(s))Ž¡‘$Oobj.find_category("diffrn_scan_axis")Ž¡‘$Oobj.find_column("scan_id")Ž¡‘$Oobj.rewind_row()Ž¡‘$Ofor–¹–i“in“range(obj.count_rows()):Ž¡‘75oobj.select_row(i)Ž¡‘75oobj.set_value("SCAN%s"%(s))Ž¡‘$Oobj.find_category("diffrn_scan_frame")Ž¡‘$Oobj.find_column("scan_id")ŽŽŸ‘âh½Ÿô‰ff&NŸ ²J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽ’ä\June–UU5,“2007ŽŽ’ö&J43ŽŽŽŽŽŽŽŽŒ‹,è¶ Ú ýO¸‘âh½ï4pdf:dest (page.44) [@thispage /XYZ @xpos @ypos null]Ÿüfd²9.2‘ W‘ÿ*ªriting–UUout“cif“ les“for“ t2d/xmasŽŽŽ’ÇX CONTENTSŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘$OËobj.rewind_row()ޤ ‘$Oobj.set_value("SCAN%s"%(s))Ž¡¡¡‘h¿def‘¹–writepixelsize_y_mm(obj,s):Ž¡‘$O"""Ž¡‘$OUnits–¹–are“mm“for“cifŽ¡‘$O"""Ž¡‘$O#–¹–element“number‘ s,=“assume“this“is“first“and“only“detectorŽ¡‘$Oelement_number–¹–=“0Ž¡‘$O#–¹–axis“number“=“faster“or“slower...“?“Need“to“check“precedence“ideally...Ž¡‘$Oobj.find_category("array_structure_list")Ž¡‘$Oobj.find_column("axis_set_id")Ž¡‘$Oobj.find_row("ELEMENT_Y")Ž¡‘$Oobj.find_column("precedence")Ž¡‘$Oaxis_number–¹–=“obj.get_integervalue()Ž¡¡‘$Oobj.set_pixel_size(element_number,–¹–axis_number,“float(s)“)Ž¡¡‘$Oobj.find_category("array_structure_list_axis")Ž¡‘$Oobj.find_column("axis_id")Ž¡‘$Oobj.find_row("ELEMENT_Y")Ž¡‘$Oobj.find_column("displacement")Ž¡‘$Oobj.set_doublevalue("%.6g",float(s)/2.0)Ž¡‘$Oobj.find_column("displacement_increment")Ž¡‘$Oobj.set_doublevalue("%.6g",float(s))Ž¡¡‘h¿def‘¹–writepixelsize_x_mm(obj,s):Ž¡‘$O#–¹–element“number‘ s,=“assume“this“is“first“and“only“detectorŽ¡‘$Oelement_number–¹–=“0Ž¡‘$O#–¹–axis“number“=“faster“or“slower...“?“Need“to“check“precedence“ideally...Ž¡‘$Oobj.find_category("array_structure_list")Ž¡‘$Oobj.find_column("axis_set_id")Ž¡‘$Oobj.find_row("ELEMENT_X")Ž¡‘$Oobj.find_column("precedence")Ž¡‘$Oaxis_number–¹–=“obj.get_integervalue()Ž¡¡‘$Oobj.set_pixel_size(element_number,–¹–axis_number,“float(s)“)Ž¡¡‘$Oobj.find_category("array_structure_list_axis")Ž¡‘$Oobj.find_column("axis_id")Ž¡‘$Oobj.find_row("ELEMENT_X")Ž¡‘$Oobj.find_column("displacement")Ž¡‘$Oobj.set_doublevalue("%.6g",float(s)/2.0)Ž¡‘$Oobj.find_column("displacement_increment")Ž¡‘$Oobj.set_doublevalue("%.6g",float(s))Ž¡¡‘h¿def‘¹–writeintegrationtime(obj,s):Ž¡‘$Oobj.find_category("diffrn_scan_frame")Ž¡‘$Oobj.find_column("integration_time")Ž¡‘$Oobj.set_value(str(s).replace("\000",""))Ž¡¡‘h¿def‘¹–writenfast(obj,s):Ž¡‘$Oobj.find_category("array_structure_list")Ž¡‘$Oobj.find_column("index")Ž¡‘$Oobj.find_row("1")Ž¡‘$Oobj.find_column("dimension")Ž¡‘$Oobj.set_value(str(s))Ž¡¡‘h¿def‘¹–writenslow(obj,s):Ž¡‘$Oobj.find_category("array_structure_list")Ž¡‘$Oobj.find_column("index")Ž¡‘$Oobj.find_row("2")ŽŽŸ‘âh½Ÿô‰ff&NŸ ²44ŽŽŽ’ä\June–UU5,“2007ŽŽ’Ê‚¸J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽŽŽŽŽŽŒ‹-ñy Ú ýO¸‘âh½ï4pdf:dest (page.45) [@thispage /XYZ @xpos @ypos null]Ÿüfd²CONTENTSŽŽŽ’R_9.2‘ W‘ÿ*ªriting–UUout“cif“ les“for“ t2d/xmasŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘$OËobj.find_column("dimension")ޤ ‘$Oobj.set_value(str(s))Ž¡¡¡‘h¿functiondict–¹–=“{Ž¡‘$O"lambda"‘,Â:‘¹–writewavelength,Ž¡‘$O"beam_x_mm"‘,Â:‘¹–writebeam_x_mm,Ž¡‘$O"beam_y_mm"‘,Â:‘¹–writebeam_y_mm,Ž¡‘$O"distance"–¹–:“writedistance,Ž¡‘$O"UB"‘!:‘¹–writeUB,Ž¡‘$O"cell"‘Ÿî:‘¹–writecell,Ž¡‘$O"cmd"‘Y„:‘¹–writeSPECcmd,Ž¡‘$O"scan"‘Ÿî:‘¹–writeSPECscan,Ž¡‘$O"nfast"‘æX:‘¹–writenfast,Ž¡‘$O"nslow"‘æX:‘¹–writenslow,Ž¡‘$O"pixelsize_y_mm"–¹–:“writepixelsize_y_mm,Ž¡‘$O"pixelsize_x_mm"–¹–:“writepixelsize_x_mm,Ž¡‘$O"integration_time_sec"–¹–:“writeintegrationtime,Ž¡‘$O"tth"‘Y„:–¹–lambda“obj,value“:“obj.set_axis_setting(Ž¡’¨›"DETECTOR_TWO_THETA_VERTICAL",float(value),0.),Ž¡‘$O"chi"‘Y„:–¹–lambda“obj,value“:“obj.set_axis_setting(Ž¡’À;m"GONIOMETER_CHI",float(value),0.),Ž¡‘$O"th"‘!:–¹–lambda“obj,value“:“obj.set_axis_setting(Ž¡’À;m"GONIOMETER_THETA",float(value),0.),Ž¡‘$O"phi"‘Y„:–¹–lambda“obj,value“:“obj.set_axis_setting(Ž¡’À;m"GONIOMETER_PHI",float(value),0.),Ž¡‘$O"lc_a"‘Ÿî:–¹–lambda“obj,value“:“writecellpar(obj,"length_a",value),Ž¡‘$O"lc_b"‘Ÿî:–¹–lambda“obj,value“:“writecellpar(obj,"length_b",value),Ž¡‘$O"lc_c"‘Ÿî:–¹–lambda“obj,value“:“writecellpar(obj,"length_c",value),Ž¡‘$O"lc_al"‘æX:–¹–lambda“obj,value“:“writecellpar(obj,"angle_alpha",value),Ž¡‘$O"lc_be"‘æX:–¹–lambda“obj,value“:“writecellpar(obj,"angle_beta",value),Ž¡‘$O"lc_ga"‘æX:–¹–lambda“obj,value“:“writecellpar(obj,"angle_gamma",value)Ž¡‘$O}Ž¡¡‘h¿"""Ž¡‘$O#Ž¡‘$O#–¹–Not“implementing“these“for“nowŽ¡‘$Olc_raŽ¡‘$Olc_rc‘¹–0.4742Ž¡‘$Olc_rb‘¹–1.16Ž¡‘$Oenergy‘¹–13Ž¡‘$Ocp_phi‘¹–-180Ž¡‘$Oalpha‘¹–7.3716Ž¡‘$Olc_ral‘¹–90Ž¡‘$Ocp_tth‘¹–-180Ž¡‘$Olc_rga‘¹–90Ž¡‘$Obeta‘¹–17.572Ž¡‘$Oomega‘¹–-2.185Ž¡‘$Oh‘¹–0.21539Ž¡‘$Ok‘¹–0.01957Ž¡‘$Ol‘¹–5.9763Ž¡‘$Ocp_chi‘¹–-180Ž¡‘$Olc_rbe‘¹–90Ž¡‘$Ocp_th‘¹–-180Ž¡‘$Oazimuth‘¹–0Ž¡‘h¿"""Ž¡¡‘h¿#–¹–Finally“a“class“for“creating“header“files.Ž¡‘h¿#–¹–It“reads“a“template“and“then“offers“a“processfile“commandŽ¡‘h¿#–¹–for“running“over“a“file“seriesŽ¡¡‘h¿class‘¹–cifheader:Ž¡ŽŸ‘âh½Ÿô‰ff&NŸ ²J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽ’ä\June–UU5,“2007ŽŽ’ö&J45ŽŽŽŽŽŽŽŽŒ‹.ûU Ú ýO¸‘âh½ï4pdf:dest (page.46) [@thispage /XYZ @xpos @ypos null]Ÿüfd²9.2‘ W‘ÿ*ªriting–UUout“cif“ les“for“ t2d/xmasŽŽŽ’ÇX CONTENTSŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘$OËdef‘¹–__init__(self,templatefile):ޤ ‘75oself.cbf=pycbf.cbf_handle_struct()Ž¡‘75oself.cbf.read_template(templatefile)Ž¡‘75ofrom–¹–readmarheader“import“marheaderreaderŽ¡‘75oself.marheaderreader–¹–=“marheaderreader()Ž¡¡¡‘$Odef–¹–processfile(self,filename,“outfile=None,Ž¡‘oèwformat="mccd",Ž¡‘oèw**kwds):Ž¡‘75ooutfile=outfile.replace(format,"cif")Ž¡¡‘75oif–¹–format“==“"mccd":Ž¡‘JÇitems–¹–=“self.marheaderreader.get_header(filename)Ž¡¡‘75oif–¹–format“==“"bruker":Ž¡‘JÇpassŽ¡‘75oif–¹–format“==“"edf":Ž¡‘JÇpassŽ¡¡‘75oself.items=itemsŽ¡¡‘75o#–¹–Take“the“image“header“items“as“defaultŽ¡‘75oself.updateitems(items)Ž¡¡‘75o#–¹–Allow“them“to“be“overriddenŽ¡‘75oself.updateitems(kwds)Ž¡¡‘75o#–¹–Write“the“fileŽ¡‘75oself.writefile(outfile)Ž¡¡¡¡‘$Odef‘¹–writefile(self,filename):Ž¡‘75oself.cbf.write_file(filename,pycbf.CIF,pycbf.MIME_HEADERS,Ž¡’•µ'pycbf.ENC_BASE64)Ž¡¡¡‘$Odef‘¹–updateitems(self,dict):Ž¡‘75onames–¹–=“dict.keys()Ž¡‘75ofor–¹–name“in“names:Ž¡‘JÇvalue–¹–=“dict[name]Ž¡‘JÇ#–¹–use“a“dictionary“of“functionsŽ¡‘JÇif‘¹–functiondict.has_key(name):Ž¡‘]#–¹–print“"calling",functiondict[name],valueŽ¡‘]apply(functiondict[name],(self.cbf,value))Ž¡‘JÇelse:Ž¡‘]#print‘¹–"ignoring",name,valueŽ¡‘]passŽ¡¡¡‘h¿if‘¹–__name__=="__main__":Ž¡‘$Oimport‘¹–sysŽ¡¡‘$Oobj=cifheader("xmas_cif_template.cif")Ž¡¡‘$Oub–¹–=“[[0.11,“0.12,“0.13]“,“[0.21,“0.22,“0.23],“[0.31,“0.32,“0.33]]Ž¡¡‘$Ofor–¹–filename“in“sys.argv[1:]:Ž¡‘75ofileout–¹–=“filename.split("/")[-1]Ž¡‘75oobj.processfile(filename,–¹–outfile=fileout,“UB=ub,“distance=123.456)Ž¡‘h¿ÊŽŽŽŸ‘âh½Ÿô‰ff&NŸ ²46ŽŽŽ’ä\June–UU5,“2007ŽŽ’Ê‚¸J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽŽŽŽŽŽŒ‹/ë Ú ýO¸‘âh½ï4pdf:dest (page.47) [@thispage /XYZ @xpos @ypos null]Ÿüfd²CONTENTSŽŽŽ’5Þ9.3‘ A–UUtemplate“cif“ le“for“the“xmas“bGeamlineŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH‘âh½ ýKO¸ï;pdf:dest (subsection.9.3) [@thispage /XYZ @xpos @ypos null]Ÿ ‘Ì9.3Ž‘7ÀA–€template“cif“ le“for“the“xmas“b`eamlineŽŸÏþ‘ÅThis–ü|w¾9as“sort“of“copied“and“mošAÇdi ed“from“an“example“ le.‘(It“has‘ü{NOT‘üvb˜een“c•¾9hec“k“ed.‘(Hop˜efully‘ü|theޤ ‘four–Tcircle“geometry“at“least“v‘ÿ|raguely“matc¾9hes“what“is“at“the“bAÇeamline.ŽŸÐ7‘Ë"xmas/xmas_cif_template.cif"‘T½47‘ÕXÊŽŸ ¡‘/Ë###CBF:–¹–VERSION“0.6Ž¡‘/#–¹–CBF“file“written“by“cbflib“v0.6Ž¡¡¡¡‘/data_image_1Ž¡¡¡¡‘/loop_Ž¡‘/_diffrn.idŽ¡‘/_diffrn.crystal_idŽ¡‘3¹˜DS1‘¹–DIFFRN_CRYSTAL_IDŽ¡¡‘/loop_Ž¡‘/_cell.length_a‘c9N5.959(1)Ž¡‘/_cell.length_b‘c9N14.956(1)Ž¡‘/_cell.length_c‘c9N19.737(3)Ž¡‘/_cell.angle_alpha‘U Œ90Ž¡‘/_cell.angle_beta‘YÆ"90Ž¡‘/_cell.angle_gamma‘U Œ90Ž¡¡¡‘/loop_Ž¡‘/_diffrn_orient_matrix.id‘¹–'DS1'Ž¡‘/_diffrn_orient_matrix.typeŽ¡‘/;–¹–reciprocal“axis“matrix,“multiplies“hkl“vector“to“generateŽ¡‘8s.diffractometer–¹–xyz“vector“and“diffractometer“anglesŽ¡‘/;Ž¡‘/_diffrn_orient_matrix.UB[1][1]‘8³0.11Ž¡‘/_diffrn_orient_matrix.UB[1][2]‘8³0.12Ž¡‘/_diffrn_orient_matrix.UB[1][3]‘8³0.13Ž¡‘/_diffrn_orient_matrix.UB[2][1]‘8³0.21Ž¡‘/_diffrn_orient_matrix.UB[2][2]‘8³0.22Ž¡‘/_diffrn_orient_matrix.UB[2][3]‘8³0.23Ž¡‘/_diffrn_orient_matrix.UB[3][1]‘8³0.31Ž¡‘/_diffrn_orient_matrix.UB[3][2]‘8³0.32Ž¡‘/_diffrn_orient_matrix.UB[3][3]‘8³0.33Ž¡¡¡¡¡‘/loop_Ž¡‘/_diffrn_source.diffrn_idŽ¡‘/_diffrn_source.sourceŽ¡‘/_diffrn_source.currentŽ¡‘/_diffrn_source.typeŽ¡‘3¹˜DS1–¹–synchrotron“200.0“'XMAS“beamline“bm28“ESRF'Ž¡¡‘/loop_Ž¡‘/_diffrn_radiation.diffrn_idŽ¡‘/_diffrn_radiation.wavelength_idŽ¡‘/_diffrn_radiation.probeŽ¡‘/_diffrn_radiation.monochromatorŽ¡‘/_diffrn_radiation.polarizn_source_ratioŽ¡‘/_diffrn_radiation.polarizn_source_normŽ¡‘/_diffrn_radiation.div_x_sourceŽŽŸ‘âh½Ÿô‰ff&NŸ ²J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽ’ä\June–UU5,“2007ŽŽ’ö&J47ŽŽŽŽŽŽŽŽŒ‹0 ˆ Ú ýO¸‘âh½ï4pdf:dest (page.48) [@thispage /XYZ @xpos @ypos null]Ÿüfd²9.3‘ A–UUtemplate“cif“ le“for“the“xmas“bGeamlineŽŽŽ’ÇX CONTENTSŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘h¿Ë_diffrn_radiation.div_y_sourceޤ ‘h¿_diffrn_radiation.div_x_y_sourceŽ¡‘h¿_diffrn_radiation.collimationŽ¡‘"UDS1–¹–WAVELENGTH1“x-ray“'Si“111'“0.8“0.0“0.08“0.01“0.00“'0.20“mm“x“0.20“mm'Ž¡¡‘h¿loop_Ž¡‘h¿_diffrn_radiation_wavelength.idŽ¡‘h¿_diffrn_radiation_wavelength.wavelengthŽ¡‘h¿_diffrn_radiation_wavelength.wtŽ¡‘"UWAVELENGTH1–¹–1.73862“1.0Ž¡¡‘h¿loop_Ž¡‘h¿_diffrn_detector.diffrn_idŽ¡‘h¿_diffrn_detector.idŽ¡‘h¿_diffrn_detector.typeŽ¡‘h¿_diffrn_detector.detailsŽ¡‘h¿_diffrn_detector.number_of_axesŽ¡‘"UDS1–¹–MAR“'MAR“XMAS'“'slow“mode'“5Ž¡¡‘h¿loop_Ž¡‘h¿_diffrn_detector_axis.detector_idŽ¡‘h¿_diffrn_detector_axis.axis_idŽ¡‘"UMAR‘¹–DETECTOR_TWO_THETA_VERTICALŽ¡‘"UMAR‘¹–DETECTOR_XŽ¡‘"UMAR‘¹–DETECTOR_YŽ¡‘"UMAR‘¹–DETECTOR_ZŽ¡‘"UMAR‘¹–DETECTOR_PITCHŽ¡¡‘h¿loop_Ž¡‘h¿_diffrn_detector_element.idŽ¡‘h¿_diffrn_detector_element.detector_idŽ¡‘"UELEMENT1‘¹–MARŽ¡¡‘h¿loop_Ž¡‘h¿_diffrn_data_frame.idŽ¡‘h¿_diffrn_data_frame.detector_element_idŽ¡‘h¿_diffrn_data_frame.array_idŽ¡‘h¿_diffrn_data_frame.binary_idŽ¡‘"UFRAME1–¹–ELEMENT1“ARRAY1“1Ž¡¡‘h¿loop_Ž¡‘h¿_diffrn_measurement.diffrn_idŽ¡‘h¿_diffrn_measurement.idŽ¡‘h¿_diffrn_measurement.number_of_axesŽ¡‘h¿_diffrn_measurement.methodŽ¡‘h¿_diffrn_measurement.detailsŽ¡‘"UDS1–¹–GONIOMETER“3“rotationŽ¡‘"U'i0=1.000–¹–i1=1.000“i2=1.000“ib=1.000“beamstop=20“mm“0%“attenuation'Ž¡¡‘h¿loop_Ž¡‘h¿_diffrn_measurement_axis.measurement_idŽ¡‘h¿_diffrn_measurement_axis.axis_idŽ¡‘"UGONIOMETER‘¹–GONIOMETER_PHIŽ¡‘"UGONIOMETER‘¹–GONIOMETER_CHIŽ¡‘"UGONIOMETER‘¹–GONIOMETER_THETAŽ¡¡¡‘h¿loop_Ž¡‘h¿_diffrn_scan.idŽ¡‘h¿_diffrn_scan.frame_id_startŽ¡‘h¿_diffrn_scan.frame_id_endŽ¡‘h¿_diffrn_scan.framesŽ¡‘"USCAN1–¹–FRAME1“FRAME1“1ŽŽŸ‘âh½Ÿô‰ff&NŸ ²48ŽŽŽ’ä\June–UU5,“2007ŽŽ’Ê‚¸J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽŽŽŽŽŽŒ‹1C Ú ýO¸‘âh½ï4pdf:dest (page.49) [@thispage /XYZ @xpos @ypos null]Ÿüfd²CONTENTSŽŽŽ’5Þ9.3‘ A–UUtemplate“cif“ le“for“the“xmas“bGeamlineŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸¤ ‘h¿Ëloop_Ž¡‘h¿_diffrn_scan_axis.scan_idŽ¡‘h¿_diffrn_scan_axis.axis_idŽ¡‘h¿_diffrn_scan_axis.angle_startŽ¡‘h¿_diffrn_scan_axis.angle_rangeŽ¡‘h¿_diffrn_scan_axis.angle_incrementŽ¡‘h¿_diffrn_scan_axis.displacement_startŽ¡‘h¿_diffrn_scan_axis.displacement_rangeŽ¡‘h¿_diffrn_scan_axis.displacement_incrementŽ¡‘"USCAN1–¹–GONIOMETER_THETA“0.0“0.0“0.0“0.0“0.0“0.0Ž¡‘"USCAN1–¹–GONIOMETER_CHI“0.0“0.0“0.0“0.0“0.0“0.0Ž¡‘"USCAN1–¹–GONIOMETER_PHI“185“1“1“0.0“0.0“0.0Ž¡‘"USCAN1–¹–DETECTOR_TWO_THETA_VERTICAL“0.0“0.0“0.0“0.0“0.0“0.0Ž¡‘"USCAN1–¹–DETECTOR_Z“0.0“0.0“0.0“103.750“0“0Ž¡‘"USCAN1–¹–DETECTOR_Y“0.0“0.0“0.0“0.0“0.0“0.0Ž¡‘"USCAN1–¹–DETECTOR_X“0.0“0.0“0.0“0.0“0.0“0.0Ž¡‘"USCAN1–¹–DETECTOR_PITCH“0.0“0.0“0.0“0.0“0.0“0.0Ž¡¡‘h¿loop_Ž¡‘h¿_diffrn_scan_frame.frame_idŽ¡‘h¿_diffrn_scan_frame.frame_numberŽ¡‘h¿_diffrn_scan_frame.integration_timeŽ¡‘h¿_diffrn_scan_frame.scan_idŽ¡‘h¿_diffrn_scan_frame.dateŽ¡‘"UFRAME1–¹–1“360“SCAN1“1997-12-04T10:23:48Ž¡¡‘h¿loop_Ž¡‘h¿_diffrn_scan_frame_axis.frame_idŽ¡‘h¿_diffrn_scan_frame_axis.axis_idŽ¡‘h¿_diffrn_scan_frame_axis.angleŽ¡‘h¿_diffrn_scan_frame_axis.displacementŽ¡‘"UFRAME1–¹–GONIOMETER_THETA“0.0“0.0Ž¡‘"UFRAME1–¹–GONIOMETER_CHI“0.0“0.0Ž¡‘"UFRAME1–¹–GONIOMETER_PHI“185“0.0Ž¡‘"UFRAME1–¹–DETECTOR_TWO_THETA_VERTICAL“185“0.0Ž¡‘"UFRAME1–¹–DETECTOR_Z“0.0“103.750Ž¡‘"UFRAME1–¹–DETECTOR_Y“0.0“0.0Ž¡‘"UFRAME1–¹–DETECTOR_X“0.0“0.0Ž¡‘"UFRAME1–¹–DETECTOR_PITCH“0.0“0.0Ž¡¡‘h¿loop_Ž¡‘h¿_axis.idŽ¡‘h¿_axis.typeŽ¡‘h¿_axis.equipmentŽ¡‘h¿_axis.depends_onŽ¡‘h¿_axis.vector[1]Ž¡‘h¿_axis.vector[2]Ž¡‘h¿_axis.vector[3]Ž¡‘h¿_axis.offset[1]Ž¡‘h¿_axis.offset[2]Ž¡‘h¿_axis.offset[3]Ž¡‘"UGONIOMETER_THETA–¹–rotation“goniometer“.“1“0“0“.“.“.Ž¡‘"UGONIOMETER_CHI–¹–rotation“goniometer“GONIOMETER_THETA“0“0“1“.“.“.Ž¡‘"UGONIOMETER_PHI–¹–rotation“goniometer“GONIOMETER_PHI“1“0“0“.“.“.Ž¡‘"USOURCE–¹–general“source“.“0“0“1“.“.“.Ž¡‘"UGRAVITY–¹–general“gravity“.“0“-1“0“.“.“.Ž¡‘"UDETECTOR_TWO_THETA_VERTICAL–¹–rotation“goniometer“.“1“0“0“.“.“.Ž¡‘"UDETECTOR_Z–¹–translation“detector“DETECTOR_TWO_THETA_VERTICAL“0“0“-1“0“0“0Ž¡‘"UDETECTOR_Y–¹–translation“detector“DETECTOR_Z“0“1“0“0“0“0Ž¡‘"UDETECTOR_X–¹–translation“detector“DETECTOR_Y“1“0“0“0“0“0Ž¡‘"UDETECTOR_PITCH–¹–rotation“detector“DETECTOR_X“0“1“0“0“0“0Ž¡‘"UELEMENT_X–¹–translation“detector“DETECTOR_PITCH“1“0“0“-94.0032“94.0032“0ŽŽŸ‘âh½Ÿô‰ff&NŸ ²J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽ’ä\June–UU5,“2007ŽŽ’ö&J49ŽŽŽŽŽŽŽŽŒ‹2{ Ú ýO¸‘âh½ï4pdf:dest (page.50) [@thispage /XYZ @xpos @ypos null]Ÿüfd²9.3‘ A–UUtemplate“cif“ le“for“the“xmas“bGeamlineŽŽŽ’ÇX CONTENTSŽŽŽŽŸ‰ff&NŽŽŽŽ ͰH ýUO¸‘"UËELEMENT_Y–¹–translation“detector“ELEMENT_X“0“1“0“0“0“0ޤ ¡‘h¿loop_Ž¡‘h¿_array_structure_list.array_idŽ¡‘h¿_array_structure_list.indexŽ¡‘h¿_array_structure_list.dimensionŽ¡‘h¿_array_structure_list.precedenceŽ¡‘h¿_array_structure_list.directionŽ¡‘h¿_array_structure_list.axis_set_idŽ¡‘"UARRAY1–¹–1“2049“1“increasing“ELEMENT_XŽ¡‘"UARRAY1–¹–2“2049“2“increasing“ELEMENT_YŽ¡¡‘h¿loop_Ž¡‘h¿_array_structure_list_axis.axis_set_idŽ¡‘h¿_array_structure_list_axis.axis_idŽ¡‘h¿_array_structure_list_axis.displacementŽ¡‘h¿_array_structure_list_axis.displacement_incrementŽ¡‘"UELEMENT_X–¹–ELEMENT_X“0.0408“0.0816Ž¡‘"UELEMENT_Y–¹–ELEMENT_Y“-0.0408“-0.0816Ž¡¡‘h¿loop_Ž¡‘h¿_array_intensities.array_idŽ¡‘h¿_array_intensities.binary_idŽ¡‘h¿_array_intensities.linearityŽ¡‘h¿_array_intensities.gainŽ¡‘h¿_array_intensities.gain_esdŽ¡‘h¿_array_intensities.overloadŽ¡‘h¿_array_intensities.undefined_valueŽ¡‘"UARRAY1–¹–1“linear“0.30“0.03“65000“0Ž¡¡‘h¿loop_Ž¡‘h¿_array_structure.idŽ¡‘h¿_array_structure.encoding_typeŽ¡‘h¿_array_structure.compression_typeŽ¡‘h¿_array_structure.byte_orderŽ¡‘"UARRAY1–¹–"signed“32-bit“integer"“packed“little_endianŽ¡‘h¿ÊŽŽŽŸ‘âh½Ÿô‰ff&NŸ ²50ŽŽŽ’ä\June–UU5,“2007ŽŽ’Ê‚¸J.–UUP›ÿ*ª.“W˜righ¸ãtŽŽŽŽŽŽŽŽŒø(Dƒ’À;èݲ¡â 2ó"ò"V cmbx10ó!ÂÖN  cmbx12ó ߤN cmtt9ó©±Ê cmsy9óÂÖN ff cmbx12ót ‰: cmbx9óo´‹Ç cmr9ó|{Ycmr8óX«Q cmr12óñkAHG® cmssbx10óDÓítG®G®cmr17óKñ`y cmr10ù.Hßßßßß./CBFlib-0.9.2.2/pycbf/pycbf.log0000644000076500007650000011453611603702120014515 0ustar yayayayaThis is pdfTeXk, Version 3.1415926-1.40.9 (Web2C 7.5.7) (format=latex 2008.8.22) 24 AUG 2010 21:19 entering extended mode %&-line parsing enabled. **pycbf (./pycbf.tex LaTeX2e <2005/12/01> Babel and hyphenation patterns for english, usenglishmax, dumylang, noh yphenation, german-x-2008-06-18, ngerman-x-2008-06-18, ancientgreek, ibycus, ar abic, basque, bulgarian, catalan, pinyin, coptic, croatian, czech, danish, dutc h, esperanto, estonian, farsi, finnish, french, galician, german, ngerman, mono greek, greek, hungarian, icelandic, indonesian, interlingua, irish, italian, la tin, mongolian, mongolian2a, bokmal, nynorsk, polish, portuguese, romanian, rus sian, sanskrit, serbian, slovak, slovenian, spanish, swedish, turkish, ukenglis h, ukrainian, uppersorbian, welsh, loaded. (/usr/local/texlive/2008/texmf-dist/tex/latex/base/article.cls Document Class: article 2005/09/16 v1.4f Standard LaTeX document class (/usr/local/texlive/2008/texmf-dist/tex/latex/base/size10.clo File: size10.clo 2005/09/16 v1.4f Standard LaTeX file (size option) ) \c@part=\count79 \c@section=\count80 \c@subsection=\count81 \c@subsubsection=\count82 \c@paragraph=\count83 \c@subparagraph=\count84 \c@figure=\count85 \c@table=\count86 \abovecaptionskip=\skip41 \belowcaptionskip=\skip42 \bibindent=\dimen102 ) (/Users/yaya/Library/texmf/tex/latex/iucr/utilities/graphics/graphics.sty Package: graphics 1999/02/16 v1.0l Standard LaTeX Graphics (DPC,SPQR) (/Users/yaya/Library/texmf/tex/latex/iucr/utilities/graphics/trig.sty Package: trig 1999/03/16 v1.09 sin cos tan (DPC) ) (/usr/local/texlive/2008/texmf/tex/latex/config/graphics.cfg File: graphics.cfg 2007/01/18 v1.5 graphics configuration of teTeX/TeXLive ) Package graphics Info: Driver file: dvips.def on input line 80. (/Users/yaya/Library/texmf/tex/latex/iucr/utilities/graphics/dvips.def File: dvips.def 1999/02/16 v3.0i Driver-dependant file (DPC,SPQR) )) (/usr/local/texlive/2008/texmf-dist/tex/latex/anysize/anysize.sty Package: anysize 1994/08/13 setting margin sizes document style option `anysize' loaded Michael Salzenberg, Thomas Esser, Dirk Hillbrecht Version 1.0, Aug 13, 1994 \@Leftmargin=\dimen103 \@Rightmargin=\dimen104 \@Topmargin=\dimen105 \@Bottommargin=\dimen106 ) (/usr/local/texlive/2008/texmf-dist/tex/latex/fancyhdr/fancyhdr.sty \fancy@headwidth=\skip43 \f@ncyO@elh=\skip44 \f@ncyO@erh=\skip45 \f@ncyO@olh=\skip46 \f@ncyO@orh=\skip47 \f@ncyO@elf=\skip48 \f@ncyO@erf=\skip49 \f@ncyO@olf=\skip50 \f@ncyO@orf=\skip51 ) (/Users/yaya/Library/texmf/tex/latex/hyperref/hyperref.sty Package: hyperref 2003/11/30 v6.74m Hypertext links for LaTeX (/Users/yaya/Library/texmf/tex/latex/iucr/utilities/graphics/keyval.sty Package: keyval 1999/03/16 v1.13 key=value parser (DPC) \KV@toks@=\toks14 ) \@linkdim=\dimen107 \Hy@linkcounter=\count87 \Hy@pagecounter=\count88 (/Users/yaya/Library/texmf/tex/latex/hyperref/pd1enc.def File: pd1enc.def 2003/11/30 v6.74m Hyperref: PDFDocEncoding definition (HO) ) (/usr/local/texlive/2008/texmf/tex/latex/config/hyperref.cfg File: hyperref.cfg 2002/06/06 v1.2 hyperref configuration of TeXLive ) Package hyperref Info: Option `bookmarks' set `true' on input line 1830. Package hyperref Info: Option `bookmarksnumbered' set `true' on input line 1830 . Package hyperref Info: Hyper figures OFF on input line 1880. Package hyperref Info: Link nesting OFF on input line 1885. Package hyperref Info: Hyper index ON on input line 1888. Package hyperref Info: Plain pages ON on input line 1893. Package hyperref Info: Backreferencing ON on input line 1898. Implicit mode ON; LaTeX internals redefined Package hyperref Info: Bookmarks ON on input line 2004. (/Users/yaya/Library/texmf/tex/latex/hyperref/backref.sty Package: backref 2003/03/20 v1.23 Bibliographical back referencing ) (/usr/local/texlive/2008/texmf-dist/tex/latex/ltxmisc/url.sty \Urlmuskip=\muskip10 Package: url 2006/04/12 ver 3.3 Verb mode for urls, etc. ) LaTeX Info: Redefining \url on input line 2143. \Fld@menulength=\count89 \Field@Width=\dimen108 \Fld@charsize=\dimen109 \Choice@toks=\toks15 \Field@toks=\toks16 Package hyperref Info: Hyper figures OFF on input line 2618. Package hyperref Info: Link nesting OFF on input line 2623. Package hyperref Info: Hyper index ON on input line 2626. Package hyperref Info: backreferencing ON on input line 2631. Package hyperref Info: Link coloring OFF on input line 2638. \c@Item=\count90 \c@Hfootnote=\count91 ) *hyperref using driver hdvipdfm* (/Users/yaya/Library/texmf/tex/latex/hyperref/hdvipdfm.def File: hdvipdfm.def 2003/11/30 v6.74m Hyperref driver for dvipdfm \pdfm@box=\box26 \Fld@listcount=\count92 \@outlinefile=\write3 ) (./pycbf.aux) \openout1 = `pycbf.aux'. LaTeX Font Info: Checking defaults for OML/cmm/m/it on input line 97. LaTeX Font Info: ... okay on input line 97. LaTeX Font Info: Checking defaults for T1/cmr/m/n on input line 97. LaTeX Font Info: ... okay on input line 97. LaTeX Font Info: Checking defaults for OT1/cmr/m/n on input line 97. LaTeX Font Info: ... okay on input line 97. LaTeX Font Info: Checking defaults for OMS/cmsy/m/n on input line 97. LaTeX Font Info: ... okay on input line 97. LaTeX Font Info: Checking defaults for OMX/cmex/m/n on input line 97. LaTeX Font Info: ... okay on input line 97. LaTeX Font Info: Checking defaults for U/cmr/m/n on input line 97. LaTeX Font Info: ... okay on input line 97. LaTeX Font Info: Checking defaults for PD1/pdf/m/n on input line 97. LaTeX Font Info: ... okay on input line 97. Package hyperref Info: Link coloring OFF on input line 97. (/Users/yaya/Library/texmf/tex/latex/hyperref/nameref.sty Package: nameref 2003/12/03 v2.21 Cross-referencing by name of section \c@section@level=\count93 ) LaTeX Info: Redefining \ref on input line 97. LaTeX Info: Redefining \pageref on input line 97. (./pycbf.out) (./pycbf.out) \openout3 = `pycbf.out'. LaTeX Font Info: External font `cmex10' loaded for size (Font) <12> on input line 127. LaTeX Font Info: External font `cmex10' loaded for size (Font) <8> on input line 127. LaTeX Font Info: External font `cmex10' loaded for size (Font) <6> on input line 127. (./pycbf.toc LaTeX Font Info: External font `cmex10' loaded for size (Font) <9> on input line 4. LaTeX Font Info: External font `cmex10' loaded for size (Font) <5> on input line 4. ) \tf@toc=\write4 \openout4 = `pycbf.toc'. [1 ] LaTeX Font Info: Try loading font information for OMS+cmr on input line 177. (/usr/local/texlive/2008/texmf-dist/tex/latex/base/omscmr.fd File: omscmr.fd 1999/05/25 v2.5h Standard LaTeX font definitions ) LaTeX Font Info: Font shape `OMS/cmr/m/n' in size <9> not available (Font) Font shape `OMS/cmsy/m/n' tried instead on input line 177. Overfull \hbox (10.09409pt too wide) in paragraph at lines 206--212 []\OT1/cmr/m/n/9 The li-brary ap-pears to de-fine (at least) three ob-jects. Th e one we started on was the cbf[]handle[]struct [] [2] [3] Overfull \hbox (27.82617pt too wide) in paragraph at lines 402--402 [][][]\OT1/cmtt/m/n/9 #define CBF_PARSE_TQ 0x0800 /* PARSE treble quotes "" "...""" and '''...''' */ [] Overfull \hbox (4.20145pt too wide) in paragraph at lines 414--414 [][][]\OT1/cmtt/m/n/9 #define CBF_PARSE_WIDE 0x4000 /* PARSE wide files */ [] Overfull \hbox (4.20145pt too wide) in paragraph at lines 416--416 [][][]\OT1/cmtt/m/n/9 #define CBF_PARSE_UTF8 0x10000 /* PARSE UTF-8 */ [] [4] [5] Underfull \vbox (badness 10000) has occurred while \output is active [] [6] Overfull \hbox (42.001pt too wide) in paragraph at lines 642--642 [][][] \OT1/cmtt/m/n/9 PyErr_SetString(PyExc_ValueError,"Expecti ng a sequence of long integers"); [] Underfull \vbox (badness 10000) has occurred while \output is active [] [7] Overfull \hbox (42.001pt too wide) in paragraph at lines 674--674 [][][] \OT1/cmtt/m/n/9 PyErr_SetString(PyExc_ValueError,"Expecti ng a sequence of long integers"); [] Underfull \vbox (badness 10000) has occurred while \output is active [] [8] [9] [10] Overfull \hbox (8.92639pt too wide) in paragraph at lines 993--993 [][][] \OT1/cmtt/m/n/9 while lines[i+1].find("DESCRIPTION")==-1 and lines[ i+1].find("int cbf_")==-1: [] Underfull \vbox (badness 10000) has occurred while \output is active [] [11] Underfull \vbox (badness 10000) has occurred while \output is active [] [12] Underfull \vbox (badness 10000) has occurred while \output is active [] [13] Overfull \hbox (8.92639pt too wide) in paragraph at lines 1158--1158 [][][] \OT1/cmtt/m/n/9 "int elements", "int minelement", "int maxelement", "char **bo", "int *bolen", [] Overfull \hbox (8.92639pt too wide) in paragraph at lines 1198--1198 [][][] \OT1/cmtt/m/n/9 "int elements", "int minelement", "int maxelement", "char **bo", "int *bolen", [] Underfull \vbox (badness 10000) has occurred while \output is active [] [14] Overfull \hbox (8.92639pt too wide) in paragraph at lines 1238--1238 [][][] \OT1/cmtt/m/n/9 "int elements", "int minelement", "int maxelement", "char **bo", "int *bolen", [] Underfull \vbox (badness 10000) has occurred while \output is active [] [15] Underfull \vbox (badness 10000) has occurred while \output is active [] [16] Underfull \vbox (badness 10000) has occurred while \output is active [] [17] Overfull \hbox (18.37628pt too wide) in paragraph at lines 1440--1440 [][][] \OT1/cmtt/m/n/9 "int elsize", "int elsign", "int ndimslow", "int ndim fast"],["(Binary)String"] ], [] Underfull \vbox (badness 10000) has occurred while \output is active [] [18] Overfull \hbox (18.37628pt too wide) in paragraph at lines 1468--1468 [][][] \OT1/cmtt/m/n/9 "int elsize", "int elsign", "int ndimfast", "int ndim slow"],["(Binary)String"] ], [] Overfull \hbox (18.37628pt too wide) in paragraph at lines 1496--1496 [][][] \OT1/cmtt/m/n/9 "int elsize", "int elsign", "int ndimslow", "int ndim fast"],["(Binary)String"] ], [] Underfull \vbox (badness 10000) has occurred while \output is active [] [19] Underfull \vbox (badness 10000) has occurred while \output is active [] [20] Overfull \hbox (89.25046pt too wide) in paragraph at lines 1608--1608 [][][] \OT1/cmtt/m/n/9 "int elsize", "int elsign", "int ndimslow", "int ndim mid", "int ndimfast"],["(Binary)String"] ], [] Overfull \hbox (89.25046pt too wide) in paragraph at lines 1636--1636 [][][] \OT1/cmtt/m/n/9 "int elsize", "int elsign", "int ndimfast", "int ndim mid", "int ndimslow"],["(Binary)String"] ], [] Underfull \vbox (badness 10000) has occurred while \output is active [] [21] Overfull \hbox (89.25046pt too wide) in paragraph at lines 1664--1664 [][][] \OT1/cmtt/m/n/9 "int elsize", "int elsign", "int ndimslow", "int ndim mid", "int ndimfast"],["(Binary)String"] ], [] Overfull \hbox (23.10123pt too wide) in paragraph at lines 1692--1692 [][][] \OT1/cmtt/m/n/9 "int elsize", "int ndimslow", "int ndimmid", "int ndi mfast"],["(Binary)String"] ], [] Underfull \vbox (badness 10000) has occurred while \output is active [] [22] Overfull \hbox (23.10123pt too wide) in paragraph at lines 1720--1720 [][][] \OT1/cmtt/m/n/9 "int elsize", "int ndimfast", "int ndimmid", "int ndi mslow"],["(Binary)String"] ], [] Overfull \hbox (23.10123pt too wide) in paragraph at lines 1747--1747 [][][] \OT1/cmtt/m/n/9 "int elsize", "int ndimslow", "int ndimmid", "int ndi mfast"],["(Binary)String"] ], [] Underfull \vbox (badness 10000) has occurred while \output is active [] [23] Overfull \hbox (8.92639pt too wide) in paragraph at lines 1814--1814 [][][]\OT1/cmtt/m/n/9 %apply (char *STRING, int LENGTH) { (char *data, int len) } set_integerarray_wdims; [] Overfull \hbox (8.92639pt too wide) in paragraph at lines 1815--1815 [][][]\OT1/cmtt/m/n/9 %apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_integerarray_wdims; [] Overfull \hbox (18.37628pt too wide) in paragraph at lines 1819--1819 [][][] \OT1/cmtt/m/n/9 char *bo, int bolen, int dimfast, int dimmid , int dimslow, int padding){ [] Overfull \hbox (75.07562pt too wide) in paragraph at lines 1831--1831 [][][] \OT1/cmtt/m/n/9 (void *) data, (size_t) elsize, elsigned, (si ze_t) elements, (const char *)byteorder, [] Underfull \vbox (badness 10000) has occurred while \output is active [] [24] Overfull \hbox (150.67474pt too wide) in paragraph at lines 1839--1839 [][][] \OT1/cmtt/m/n/9 "int elsize","int elements", "String byteorder", "int di mfast", "int dimmid", "int dimslow", "int padding"],[]], [] Overfull \hbox (23.10123pt too wide) in paragraph at lines 1847--1847 [][][]\OT1/cmtt/m/n/9 %apply (char *STRING, int LENGTH) { (char *data, int len) } set_integerarray_wdims_sf; [] Overfull \hbox (23.10123pt too wide) in paragraph at lines 1848--1848 [][][]\OT1/cmtt/m/n/9 %apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_integerarray_wdims_sf; [] Overfull \hbox (18.37628pt too wide) in paragraph at lines 1852--1852 [][][] \OT1/cmtt/m/n/9 char *bo, int bolen, int dimslow, int dimmid , int dimfast, int padding){ [] Overfull \hbox (8.92639pt too wide) in paragraph at lines 1863--1863 [][][] \OT1/cmtt/m/n/9 cbf_failnez(cbf_set_integerarray_wdims_sf (sel f, compression, binary_id, [] Overfull \hbox (75.07562pt too wide) in paragraph at lines 1864--1864 [][][] \OT1/cmtt/m/n/9 (void *) data, (size_t) elsize, elsigned, (si ze_t) elements, (const char *)byteorder, [] Overfull \hbox (150.67474pt too wide) in paragraph at lines 1872--1872 [][][] \OT1/cmtt/m/n/9 "int elsize","int elements", "String byteorder", "int di mslow", "int dimmid", "int dimfast", "int padding"],[]], [] Overfull \hbox (23.10123pt too wide) in paragraph at lines 1879--1879 [][][]\OT1/cmtt/m/n/9 %apply (char *STRING, int LENGTH) { (char *data, int len) } set_integerarray_wdims_fs; [] Overfull \hbox (23.10123pt too wide) in paragraph at lines 1880--1880 [][][]\OT1/cmtt/m/n/9 %apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_integerarray_wdims_fs; [] Overfull \hbox (18.37628pt too wide) in paragraph at lines 1884--1884 [][][] \OT1/cmtt/m/n/9 char *bo, int bolen, int dimfast, int dimmid , int dimslow, int padding){ [] Overfull \hbox (8.92639pt too wide) in paragraph at lines 1895--1895 [][][] \OT1/cmtt/m/n/9 cbf_failnez(cbf_set_integerarray_wdims_fs (sel f, compression, binary_id, [] Overfull \hbox (75.07562pt too wide) in paragraph at lines 1896--1896 [][][] \OT1/cmtt/m/n/9 (void *) data, (size_t) elsize, elsigned, (si ze_t) elements, (const char *)byteorder, [] Underfull \vbox (badness 10000) has occurred while \output is active [] [25] Overfull \hbox (150.67474pt too wide) in paragraph at lines 1904--1904 [][][] \OT1/cmtt/m/n/9 "int elsize","int elements", "String byteorder", "int di mfast", "int dimmid", "int dimslow", "int padding"],[]], [] Overfull \hbox (18.37628pt too wide) in paragraph at lines 1943--1943 [][][] \OT1/cmtt/m/n/9 char *bo, int bolen, int dimfast, int dimmid , int dimslow, int padding){ [] Overfull \hbox (27.82617pt too wide) in paragraph at lines 1955--1955 [][][] \OT1/cmtt/m/n/9 (void *) data, (size_t) elsize, (size_t) elem ents, (const char *)byteorder, [] Underfull \vbox (badness 10000) has occurred while \output is active [] [26] Overfull \hbox (150.67474pt too wide) in paragraph at lines 1963--1963 [][][] \OT1/cmtt/m/n/9 "int elsize","int elements", "String byteorder", "int di mfast", "int dimmid", "int dimslow", "int padding"],[]], [] Overfull \hbox (8.92639pt too wide) in paragraph at lines 1971--1971 [][][]\OT1/cmtt/m/n/9 %apply (char *STRING, int LENGTH) { (char *data, int len) } set_realarray_wdims_sf; [] Overfull \hbox (8.92639pt too wide) in paragraph at lines 1972--1972 [][][]\OT1/cmtt/m/n/9 %apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_realarray_wdims_sf; [] Overfull \hbox (18.37628pt too wide) in paragraph at lines 1976--1976 [][][] \OT1/cmtt/m/n/9 char *bo, int bolen, int dimslow, int dimmid , int dimfast, int padding){ [] Overfull \hbox (27.82617pt too wide) in paragraph at lines 1988--1988 [][][] \OT1/cmtt/m/n/9 (void *) data, (size_t) elsize, (size_t) elem ents, (const char *)byteorder, [] Overfull \hbox (4.20145pt too wide) in paragraph at lines 1989--1989 [][][] \OT1/cmtt/m/n/9 (size_t) dimslow, (size_t) dimmid, (size_t) di mfast, (size_t)padding)); [] Overfull \hbox (150.67474pt too wide) in paragraph at lines 1996--1996 [][][] \OT1/cmtt/m/n/9 "int elsize","int elements", "String byteorder", "int di mslow", "int dimmid", "int dimfast", "int padding"],[]], [] Overfull \hbox (8.92639pt too wide) in paragraph at lines 2004--2004 [][][]\OT1/cmtt/m/n/9 %apply (char *STRING, int LENGTH) { (char *data, int len) } set_realarray_wdims_fs; [] Overfull \hbox (8.92639pt too wide) in paragraph at lines 2005--2005 [][][]\OT1/cmtt/m/n/9 %apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_realarray_wdims_fs; [] Overfull \hbox (18.37628pt too wide) in paragraph at lines 2009--2009 [][][] \OT1/cmtt/m/n/9 char *bo, int bolen, int dimfast, int dimmid , int dimslow, int padding){ [] Overfull \hbox (27.82617pt too wide) in paragraph at lines 2021--2021 [][][] \OT1/cmtt/m/n/9 (void *) data, (size_t) elsize, (size_t) elem ents, (const char *)byteorder, [] Overfull \hbox (4.20145pt too wide) in paragraph at lines 2022--2022 [][][] \OT1/cmtt/m/n/9 (size_t) dimfast, (size_t) dimmid, (size_t) di mslow, (size_t)padding)); [] Underfull \vbox (badness 10000) has occurred while \output is active [] [27] Overfull \hbox (150.67474pt too wide) in paragraph at lines 2029--2029 [][][] \OT1/cmtt/m/n/9 "int elsize","int elements", "String byteorder", "int di mfast", "int dimmid", "int dimslow", "int padding"],[]], [] Overfull \hbox (23.10123pt too wide) in paragraph at lines 2040--2040 [][][] \OT1/cmtt/m/n/9 char *data, int len, int elsize, int elsign, int ndimslow, int ndimfast){ [] Overfull \hbox (4.20145pt too wide) in paragraph at lines 2049--2049 [][][] \OT1/cmtt/m/n/9 cbf_failnez(cbf_set_image (self, reserved, ele ment_number, compression, [] Overfull \hbox (42.001pt too wide) in paragraph at lines 2050--2050 [][][] \OT1/cmtt/m/n/9 (void *) data, (size_t) elsize, elsign, (size _t) ndimslow, (size_t)ndimfast)); [] Overfull \hbox (23.10123pt too wide) in paragraph at lines 2068--2068 [][][] \OT1/cmtt/m/n/9 char *data, int len, int elsize, int elsign, int ndimfast, int ndimslow){ [] Overfull \hbox (4.20145pt too wide) in paragraph at lines 2077--2077 [][][] \OT1/cmtt/m/n/9 cbf_failnez(cbf_set_image (self, reserved, ele ment_number, compression, [] Overfull \hbox (42.001pt too wide) in paragraph at lines 2078--2078 [][][] \OT1/cmtt/m/n/9 (void *) data, (size_t) elsize, elsign, (size _t) ndimfast, (size_t)ndimslow)); [] Underfull \vbox (badness 10000) has occurred while \output is active [] [28] Overfull \hbox (23.10123pt too wide) in paragraph at lines 2096--2096 [][][] \OT1/cmtt/m/n/9 char *data, int len, int elsize, int elsign, int ndimslow, int ndimfast){ [] Overfull \hbox (18.37628pt too wide) in paragraph at lines 2105--2105 [][][] \OT1/cmtt/m/n/9 cbf_failnez(cbf_set_image_sf (self, reserved, element_number, compression, [] Overfull \hbox (42.001pt too wide) in paragraph at lines 2106--2106 [][][] \OT1/cmtt/m/n/9 (void *) data, (size_t) elsize, elsign, (size _t) ndimslow, (size_t)ndimfast)); [] Overfull \hbox (27.82617pt too wide) in paragraph at lines 2133--2133 [][][] \OT1/cmtt/m/n/9 cbf_failnez(cbf_set_real_image (self, reserved , element_number, compression, [] Overfull \hbox (4.20145pt too wide) in paragraph at lines 2134--2134 [][][] \OT1/cmtt/m/n/9 (void *) data, (size_t) elsize, (size_t) ndim slow, (size_t)ndimfast)); [] Underfull \vbox (badness 10000) has occurred while \output is active [] [29] Overfull \hbox (42.001pt too wide) in paragraph at lines 2161--2161 [][][] \OT1/cmtt/m/n/9 cbf_failnez(cbf_set_real_image_fs (self, reser ved, element_number, compression, [] Overfull \hbox (4.20145pt too wide) in paragraph at lines 2162--2162 [][][] \OT1/cmtt/m/n/9 (void *) data, (size_t) elsize, (size_t) ndim fast, (size_t)ndimslow)); [] Overfull \hbox (42.001pt too wide) in paragraph at lines 2189--2189 [][][] \OT1/cmtt/m/n/9 cbf_failnez(cbf_set_real_image_sf (self, reser ved, element_number, compression, [] Overfull \hbox (4.20145pt too wide) in paragraph at lines 2190--2190 [][][] \OT1/cmtt/m/n/9 (void *) data, (size_t) elsize, (size_t) ndim slow, (size_t)ndimfast)); [] Overfull \hbox (84.52551pt too wide) in paragraph at lines 2208--2208 [][][] \OT1/cmtt/m/n/9 char *data, int len, int elsize, int elsign, int ndimslow, int ndimmid, int ndimfast){ [] Underfull \vbox (badness 10000) has occurred while \output is active [] [30] Overfull \hbox (18.37628pt too wide) in paragraph at lines 2217--2217 [][][] \OT1/cmtt/m/n/9 cbf_failnez(cbf_set_3d_image (self, reserved, element_number, compression, [] Overfull \hbox (127.05002pt too wide) in paragraph at lines 2218--2218 [][][] \OT1/cmtt/m/n/9 (void *) data, (size_t) elsize, elsign, (size _t) ndimslow, (size_t) ndimmid, (size_t)ndimfast)); [] Overfull \hbox (84.52551pt too wide) in paragraph at lines 2236--2236 [][][] \OT1/cmtt/m/n/9 char *data, int len, int elsize, int elsign, int ndimfast, int ndimmid, int ndimslow){ [] Overfull \hbox (32.55112pt too wide) in paragraph at lines 2245--2245 [][][] \OT1/cmtt/m/n/9 cbf_failnez(cbf_set_3d_image_fs (self, reserve d, element_number, compression, [] Overfull \hbox (127.05002pt too wide) in paragraph at lines 2246--2246 [][][] \OT1/cmtt/m/n/9 (void *) data, (size_t) elsize, elsign, (size _t) ndimfast, (size_t) ndimmid, (size_t)ndimslow)); [] Overfull \hbox (84.52551pt too wide) in paragraph at lines 2264--2264 [][][] \OT1/cmtt/m/n/9 char *data, int len, int elsize, int elsign, int ndimslow, int ndimmid, int ndimfast){ [] Overfull \hbox (32.55112pt too wide) in paragraph at lines 2273--2273 [][][] \OT1/cmtt/m/n/9 cbf_failnez(cbf_set_3d_image_sf (self, reserve d, element_number, compression, [] Overfull \hbox (127.05002pt too wide) in paragraph at lines 2274--2274 [][][] \OT1/cmtt/m/n/9 (void *) data, (size_t) elsize, elsign, (size _t) ndimslow, (size_t) ndimmid, (size_t)ndimfast)); [] Underfull \vbox (badness 10000) has occurred while \output is active [] [31] Overfull \hbox (27.82617pt too wide) in paragraph at lines 2292--2292 [][][] \OT1/cmtt/m/n/9 char *data, int len, int elsize, int ndimslo w, int ndimmid, int ndimfast){ [] Overfull \hbox (42.001pt too wide) in paragraph at lines 2301--2301 [][][] \OT1/cmtt/m/n/9 cbf_failnez(cbf_set_real_3d_image (self, reser ved, element_number, compression, [] Overfull \hbox (84.52551pt too wide) in paragraph at lines 2302--2302 [][][] \OT1/cmtt/m/n/9 (void *) data, (size_t) elsize, (size_t) ndim slow, (size_t)ndimmid, (size_t)ndimfast)); [] Overfull \hbox (27.82617pt too wide) in paragraph at lines 2320--2320 [][][] \OT1/cmtt/m/n/9 char *data, int len, int elsize, int ndimfas t, int ndimmid, int ndimslow){ [] Overfull \hbox (56.17584pt too wide) in paragraph at lines 2329--2329 [][][] \OT1/cmtt/m/n/9 cbf_failnez(cbf_set_real_3d_image_fs (self, re served, element_number, compression, [] Overfull \hbox (84.52551pt too wide) in paragraph at lines 2330--2330 [][][] \OT1/cmtt/m/n/9 (void *) data, (size_t) elsize, (size_t) ndim fast, (size_t)ndimmid, (size_t)ndimslow)); [] Underfull \vbox (badness 10000) has occurred while \output is active [] [32] Overfull \hbox (27.82617pt too wide) in paragraph at lines 2348--2348 [][][] \OT1/cmtt/m/n/9 char *data, int len, int elsize, int ndimslo w, int ndimmid, int ndimfast){ [] Overfull \hbox (56.17584pt too wide) in paragraph at lines 2357--2357 [][][] \OT1/cmtt/m/n/9 cbf_failnez(cbf_set_real_3d_image_sf (self, re served, element_number, compression, [] Overfull \hbox (84.52551pt too wide) in paragraph at lines 2358--2358 [][][] \OT1/cmtt/m/n/9 (void *) data, (size_t) elsize, (size_t) ndim slow, (size_t)ndimmid, (size_t)ndimfast)); [] Overfull \hbox (13.65134pt too wide) in paragraph at lines 2370--2370 [][][] \OT1/cmtt/m/n/9 void get_image_size(unsigned int element_number, int *ndimslow, int *ndimfast){ [] Overfull \hbox (23.10123pt too wide) in paragraph at lines 2374--2374 [][][] \OT1/cmtt/m/n/9 cbf_failnez(cbf_get_image_size(self,reserved,elem ent_number,&inslow,&infast)); [] Overfull \hbox (27.82617pt too wide) in paragraph at lines 2383--2383 [][][] \OT1/cmtt/m/n/9 void get_image_size_fs(unsigned int element_number, int *ndimfast, int *ndimslow){ [] Overfull \hbox (37.27606pt too wide) in paragraph at lines 2387--2387 [][][] \OT1/cmtt/m/n/9 cbf_failnez(cbf_get_image_size_fs(self,reserved,e lement_number,&infast,&inslow)); [] Overfull \hbox (42.001pt too wide) in paragraph at lines 2391--2391 [][][]\OT1/cmtt/m/n/9 ""","get_image_size_fs",["Integer element_number"],["size _t ndimfast","size_t ndimslow"]], [] Overfull \hbox (27.82617pt too wide) in paragraph at lines 2396--2396 [][][] \OT1/cmtt/m/n/9 void get_image_size_sf(unsigned int element_number, int *ndimslow, int *ndimfast){ [] Overfull \hbox (23.10123pt too wide) in paragraph at lines 2400--2400 [][][] \OT1/cmtt/m/n/9 cbf_failnez(cbf_get_image_size(self,reserved,elem ent_number,&inslow,&infast)); [] Underfull \vbox (badness 10000) has occurred while \output is active [] [33] Overfull \hbox (42.001pt too wide) in paragraph at lines 2404--2404 [][][]\OT1/cmtt/m/n/9 ""","get_image_size_sf",["Integer element_number"],["size _t ndimslow","size_t ndimfast"]], [] Overfull \hbox (4.20145pt too wide) in paragraph at lines 2408--2408 [][][]\OT1/cmtt/m/n/9 %apply int *OUTPUT {int *ndimslow, int *ndimmid, int *ndi mfast} get_3d_image_size; [] Overfull \hbox (93.9754pt too wide) in paragraph at lines 2409--2409 [][][] \OT1/cmtt/m/n/9 void get_3d_image_size(unsigned int element_number, int *ndimslow, int *ndimmid, int *ndimfast){ [] Overfull \hbox (70.35068pt too wide) in paragraph at lines 2413--2413 [][][] \OT1/cmtt/m/n/9 cbf_failnez(cbf_get_3d_image_size(self,reserved,e lement_number,&inslow,&inmid,&infast)); [] Overfull \hbox (122.32507pt too wide) in paragraph at lines 2418--2418 [][][]\OT1/cmtt/m/n/9 ""","get_3d_image_size",["Integer element_number"],["size _t ndimslow","size_t ndimmid","size_t ndimfast"]], [] Overfull \hbox (4.20145pt too wide) in paragraph at lines 2422--2422 [][][]\OT1/cmtt/m/n/9 %apply int *OUTPUT {int *ndimslow, int *ndimmid, int *ndi mfast} get_3d_image_size; [] Overfull \hbox (108.15024pt too wide) in paragraph at lines 2423--2423 [][][] \OT1/cmtt/m/n/9 void get_3d_image_size_fs(unsigned int element_numbe r, int *ndimfast, int *ndimmid, int *ndimslow){ [] Overfull \hbox (84.52551pt too wide) in paragraph at lines 2427--2427 [][][] \OT1/cmtt/m/n/9 cbf_failnez(cbf_get_3d_image_size_fs(self,reserve d,element_number,&infast,&inmid,&inslow)); [] Overfull \hbox (122.32507pt too wide) in paragraph at lines 2432--2432 [][][]\OT1/cmtt/m/n/9 ""","get_3d_image_size",["Integer element_number"],["size _t ndimfast","size_t ndimmid","size_t ndimslow"]], [] Overfull \hbox (18.37628pt too wide) in paragraph at lines 2436--2436 [][][]\OT1/cmtt/m/n/9 %apply int *OUTPUT {int *ndimslow, int *ndimmid, int *ndi mfast} get_3d_image_size_sf; [] Overfull \hbox (108.15024pt too wide) in paragraph at lines 2437--2437 [][][] \OT1/cmtt/m/n/9 void get_3d_image_size_sf(unsigned int element_numbe r, int *ndimslow, int *ndimmid, int *ndimfast){ [] Overfull \hbox (84.52551pt too wide) in paragraph at lines 2441--2441 [][][] \OT1/cmtt/m/n/9 cbf_failnez(cbf_get_3d_image_size_sf(self,reserve d,element_number,&inslow,&inmid,&infast)); [] Overfull \hbox (136.49991pt too wide) in paragraph at lines 2446--2446 [][][]\OT1/cmtt/m/n/9 ""","get_3d_image_size_sf",["Integer element_number"],["s ize_t ndimslow","size_t ndimmid","size_t ndimfast"]], [] Underfull \vbox (badness 10000) has occurred while \output is active [] [34] Underfull \vbox (badness 10000) has occurred while \output is active [] [35] Underfull \vbox (badness 10000) has occurred while \output is active [] [36] Underfull \vbox (badness 10000) has occurred while \output is active [] [37] Underfull \vbox (badness 10000) has occurred while \output is active [] [38] Underfull \vbox (badness 10000) has occurred while \output is active [] [39] Underfull \vbox (badness 10000) has occurred while \output is active [] [40] Underfull \vbox (badness 10000) has occurred while \output is active [] [41] Overfull \hbox (32.55112pt too wide) in paragraph at lines 2910--2910 [][][] \OT1/cmtt/m/n/9 [],["Float a", "Float b", "Float c", "Float alpha", " Float beta", "Float gamma" ] ], [] Overfull \hbox (141.22485pt too wide) in paragraph at lines 2945--2945 [][][] \OT1/cmtt/m/n/9 [],["Float astar", "Float bstar", "Float cstar", "Flo at alphastar", "Float betastar", "Float gammastar"] ], [] Overfull \hbox (4.20145pt too wide) in paragraph at lines 2949--2949 [][][] \OT1/cmtt/m/n/9 double *alpha_esd, double *beta_esd, double *gamma_esd} get_reciprocal_cell_esd; [] Underfull \vbox (badness 10000) has occurred while \output is active [] [42] Underfull \vbox (badness 10000) has occurred while \output is active [] [43] Overfull \hbox (42.001pt too wide) in paragraph at lines 3080--3080 [][][] \OT1/cmtt/m/n/9 void set_bin_sizes( int element_number, double slowbin size_in, double fastbinsize_in) { [] Overfull \hbox (27.82617pt too wide) in paragraph at lines 3081--3081 [][][] \OT1/cmtt/m/n/9 cbf_failnez(cbf_set_bin_sizes(self,element_number,sl owbinsize_in,fastbinsize_in)); [] Overfull \hbox (79.80057pt too wide) in paragraph at lines 3083--3083 [][][]\OT1/cmtt/m/n/9 ""","set_bin_sizes",["Integer element_number","Float slow binsize_in","Float fastbinsize_in"],[] ], [] Overfull \hbox (13.65134pt too wide) in paragraph at lines 3088--3088 [][][] \OT1/cmtt/m/n/9 void get_bin_sizes(int element_number, double *slowbins ize, double *fastbinsize) { [] Overfull \hbox (79.80057pt too wide) in paragraph at lines 3089--3089 [][][] \OT1/cmtt/m/n/9 cbf_failnez(cbf_get_bin_sizes (self, (unsigned int)el ement_number, slowbinsize, fastbinsize)); [] Overfull \hbox (46.72595pt too wide) in paragraph at lines 3091--3091 [][][]\OT1/cmtt/m/n/9 ""","get_bin_sizes",["Integer element_number"],["Float sl owbinsize","Float fastbinsize"] ], [] Underfull \vbox (badness 10000) has occurred while \output is active [] [44] Overfull \hbox (37.27606pt too wide) in paragraph at lines 3146--3146 [][][]\OT1/cmtt/m/n/9 ""","construct_reference_detector",["Integer element_numb er"],["pycbf detector object"]], [] Overfull \hbox (27.82617pt too wide) in paragraph at lines 3154--3154 [][][]\OT1/cmtt/m/n/9 ""","require_reference_detector",["Integer element_number "],["pycbf detector object"]], [] Underfull \vbox (badness 10000) has occurred while \output is active [] [45] Underfull \vbox (badness 10000) has occurred while \output is active [] [46] Underfull \vbox (badness 10000) has occurred while \output is active [] [47] Underfull \vbox (badness 10000) has occurred while \output is active [] [48] Underfull \vbox (badness 10000) has occurred while \output is active [] [49] Underfull \vbox (badness 10000) has occurred while \output is active [] [50] Overfull \hbox (4.20145pt too wide) in paragraph at lines 3477--3477 [][][] \OT1/cmtt/m/n/9 indexfast,indexslow,n ormal1,normal2,normal3)); [] Overfull \hbox (4.20145pt too wide) in paragraph at lines 3489--3489 [][][] \OT1/cmtt/m/n/9 indexslow,indexfast,n ormal1,normal2,normal3)); [] Overfull \hbox (8.92639pt too wide) in paragraph at lines 3512--3512 [][][] \OT1/cmtt/m/n/9 indexfast, indexsl ow, area,projected_area)); [] Overfull \hbox (8.92639pt too wide) in paragraph at lines 3523--3523 [][][] \OT1/cmtt/m/n/9 indexslow, indexfa st, area,projected_area)); [] Underfull \vbox (badness 10000) has occurred while \output is active [] [51] Overfull \hbox (160.12463pt too wide) in paragraph at lines 3570--3570 [][][] \OT1/cmtt/m/n/9 cbf_failnez(cbf_get_pixel_coordinates_fs(self, inde xfast, indexslow, coordinate1, coordinate2, coordinate3)); [] Overfull \hbox (160.12463pt too wide) in paragraph at lines 3583--3583 [][][] \OT1/cmtt/m/n/9 cbf_failnez(cbf_get_pixel_coordinates_sf(self, inde xslow, indexfast, coordinate1, coordinate2, coordinate3)); [] Underfull \vbox (badness 10000) has occurred while \output is active [] [52] Overfull \hbox (8.92639pt too wide) in paragraph at lines 3610--3610 [][][]\OT1/cmtt/m/n/9 ["double indexfast", "double indexslow", "double centerfa st","double centerslow"]], [] Overfull \hbox (8.92639pt too wide) in paragraph at lines 3622--3622 [][][]\OT1/cmtt/m/n/9 ["double indexslow", "double indexfast", "double centersl ow","double centerfast"]], [] Overfull \hbox (23.10123pt too wide) in paragraph at lines 3632--3632 [][][]\OT1/cmtt/m/n/9 ["double indexslow", "double indexfast", "double centersl ow","double centerfast"],[]], [] Overfull \hbox (23.10123pt too wide) in paragraph at lines 3642--3642 [][][]\OT1/cmtt/m/n/9 ["double indexfast", "double indexslow", "double centerfa st","double centerslow"],[]], [] Overfull \hbox (23.10123pt too wide) in paragraph at lines 3652--3652 [][][]\OT1/cmtt/m/n/9 ["double indexslow", "double indexfast", "double centersl ow","double centerfast"],[]], [] Overfull \hbox (23.10123pt too wide) in paragraph at lines 3662--3662 [][][]\OT1/cmtt/m/n/9 ["double indexslow", "double indexfast", "double centersl ow","double centerfast"],[]], [] Underfull \vbox (badness 10000) has occurred while \output is active [] [53] Overfull \hbox (23.10123pt too wide) in paragraph at lines 3672--3672 [][][]\OT1/cmtt/m/n/9 ["double indexfast", "double indexslow", "double centerfa st","double centerslow"],[]], [] Overfull \hbox (23.10123pt too wide) in paragraph at lines 3682--3682 [][][]\OT1/cmtt/m/n/9 ["double indexslow", "double indexfast", "double centersl ow","double centerfast"],[]], [] Underfull \vbox (badness 10000) has occurred while \output is active [] [54] Underfull \vbox (badness 10000) has occurred while \output is active [] [55] Overfull \hbox (46.72595pt too wide) in paragraph at lines 3829--3829 [][][] \OT1/cmtt/m/n/9 void compute_reciprocal_cell(double cell[6], double *as tar, double *bstar, double *cstar, [] Overfull \hbox (103.4253pt too wide) in paragraph at lines 3843--3843 [][][]\OT1/cmtt/m/n/9 ["Float astar", "Float bstar", "Float cstar", "Float alph astar", "Float betastar", "Float gammastar"] ] [] Underfull \vbox (badness 10000) has occurred while \output is active [] [56] Underfull \vbox (badness 10000) has occurred while \output is active [] [57] Overfull \hbox (13.65134pt too wide) in paragraph at lines 3928--3928 [][][] \OT1/cmtt/m/n/9 cbf_handle_wrapper.wrap("cbf_get_unit_cell_esd ",prototype,args,docstring) [] Overfull \hbox (42.001pt too wide) in paragraph at lines 3930--3930 [][][] \OT1/cmtt/m/n/9 cbf_handle_wrapper.wrap("cbf_get_reciprocal_ce ll_esd",prototype,args,docstring) [] Overfull \hbox (13.65134pt too wide) in paragraph at lines 3932--3932 [][][] \OT1/cmtt/m/n/9 cbf_handle_wrapper.wrap("cbf_set_unit_cell_esd ",prototype,args,docstring) [] Overfull \hbox (42.001pt too wide) in paragraph at lines 3934--3934 [][][] \OT1/cmtt/m/n/9 cbf_handle_wrapper.wrap("cbf_set_reciprocal_ce ll_esd",prototype,args,docstring) [] [58] [59] (./TODO.txt) [60] [61] [62] [63] Underfull \vbox (badness 10000) has occurred while \output is active [] [64] Underfull \vbox (badness 10000) has occurred while \output is active [] [65] Underfull \vbox (badness 10000) has occurred while \output is active [] [66] Underfull \vbox (badness 10000) has occurred while \output is active [] [67] [68] Underfull \vbox (badness 10000) has occurred while \output is active [] [69] Underfull \vbox (badness 10000) has occurred while \output is active [] [70] Underfull \vbox (badness 10000) has occurred while \output is active [] [71] [72] Underfull \vbox (badness 10000) has occurred while \output is active [] [73] Underfull \vbox (badness 10000) has occurred while \output is active [] [74] Underfull \vbox (badness 10000) has occurred while \output is active [] [75] [76] (./pycbf.aux) ) Here is how much of TeX's memory you used: 2347 strings out of 493887 31811 string characters out of 1151122 98008 words of memory out of 3000000 5629 multiletter control sequences out of 10000+50000 9575 words of font info for 34 fonts, out of 3000000 for 5000 714 hyphenation exceptions out of 8191 25i,11n,43p,220b,365s stack positions out of 5000i,500n,10000p,200000b,50000s Output written on pycbf.dvi (76 pages, 214632 bytes). ./CBFlib-0.9.2.2/pycbf/pycbf.pdf0000644000076500007650000072166011603702120014507 0ustar yayayaya%PDF-1.2 7 0 obj [5 0 R/XYZ 42.52 737.53] endobj 12 0 obj << /Title(1 Introduction) /A<< /S/GoTo /D(section.1) >> /Parent 11 0 R /Next 13 0 R >> endobj 13 0 obj << /Title(2 Installation prerequisites) /A<< /S/GoTo /D(section.2) >> /Parent 11 0 R /Prev 12 0 R /Next 14 0 R >> endobj 15 0 obj << /Title(3.1 Exceptions) /A<< /S/GoTo /D(subsection.3.1) >> /Parent 14 0 R /Next 16 0 R >> endobj 16 0 obj << /Title(3.2 Exceptions) /A<< /S/GoTo /D(subsection.3.2) >> /Parent 14 0 R /Prev 15 0 R >> endobj 14 0 obj << /Title(3 Generating the c interface - the SWIG file) /A<< /S/GoTo /D(section.3) >> /Parent 11 0 R /Prev 13 0 R /First 15 0 R /Last 16 0 R /Count -2 /Next 17 0 R >> endobj 17 0 obj << /Title(4 Docstrings) /A<< /S/GoTo /D(section.4) >> /Parent 11 0 R /Prev 14 0 R /Next 18 0 R >> endobj 18 0 obj << /Title(5 Wrappers) /A<< /S/GoTo /D(section.5) >> /Parent 11 0 R /Prev 17 0 R /Next 19 0 R >> endobj 19 0 obj << /Title(6 Building python extensions - the setup file) /A<< /S/GoTo /D(section.6) >> /Parent 11 0 R /Prev 18 0 R /Next 20 0 R >> endobj 20 0 obj << /Title(7 Building and testing the resulting package) /A<< /S/GoTo /D(section.7) >> /Parent 11 0 R /Prev 19 0 R /Next 21 0 R >> endobj 21 0 obj << /Title(8 Debugging compiled extensions) /A<< /S/GoTo /D(section.8) >> /Parent 11 0 R /Prev 20 0 R /Next 22 0 R >> endobj 22 0 obj << /Title(9 Things which are currently missing) /A<< /S/GoTo /D(section.9) >> /Parent 11 0 R /Prev 21 0 R /Next 23 0 R >> endobj 24 0 obj << /Title(10.1 Read a file based on cif2cbf.c) /A<< /S/GoTo /D(subsection.10.1) >> /Parent 23 0 R /Next 25 0 R >> endobj 25 0 obj << /Title(10.2 Try to test the goniometer and detector) /A<< /S/GoTo /D(subsection.10.2) >> /Parent 23 0 R /Prev 24 0 R /Next 26 0 R >> endobj 26 0 obj << /Title(10.3 Test cases for the generics) /A<< /S/GoTo /D(subsection.10.3) >> /Parent 23 0 R /Prev 25 0 R >> endobj 23 0 obj << /Title(10 Testing) /A<< /S/GoTo /D(section.10) >> /Parent 11 0 R /Prev 22 0 R /First 24 0 R /Last 26 0 R /Count -3 /Next 27 0 R >> endobj 28 0 obj << /Title(11.1 Reading marccd headers) /A<< /S/GoTo /D(subsection.11.1) >> /Parent 27 0 R /Next 29 0 R >> endobj 29 0 obj << /Title(11.2 Writing out cif files for fit2d/xmas) /A<< /S/GoTo /D(subsection.11.2) >> /Parent 27 0 R /Prev 28 0 R /Next 30 0 R >> endobj 31 0 obj [5 0 R/XYZ 42.52 712.62] endobj 32 0 obj << /Type/Encoding /Differences[0/Gamma/Delta/Theta/Lambda/Xi/Pi/Sigma/Upsilon/Phi/Psi/Omega/ff/fi/fl/ffi/ffl/dotlessi/dotlessj/grave/acute/caron/breve/macron/ring/cedilla/germandbls/ae/oe/oslash/AE/OE/Oslash/suppress/exclam/quotedblright/numbersign/dollar/percent/ampersand/quoteright/parenleft/parenright/asterisk/plus/comma/hyphen/period/slash/zero/one/two/three/four/five/six/seven/eight/nine/colon/semicolon/exclamdown/equal/questiondown/question/at/A/B/C/D/E/F/G/H/I/J/K/L/M/N/O/P/Q/R/S/T/U/V/W/X/Y/Z/bracketleft/quotedblleft/bracketright/circumflex/dotaccent/quoteleft/a/b/c/d/e/f/g/h/i/j/k/l/m/n/o/p/q/r/s/t/u/v/w/x/y/z/endash/emdash/hungarumlaut/tilde/dieresis/suppress 160/space/Gamma/Delta/Theta/Lambda/Xi/Pi/Sigma/Upsilon/Phi/Psi 173/Omega/ff/fi/fl/ffi/ffl/dotlessi/dotlessj/grave/acute/caron/breve/macron/ring/cedilla/germandbls/ae/oe/oslash/AE/OE/Oslash/suppress/dieresis] >> endobj 35 0 obj << /Encoding 32 0 R /Type/Font /Subtype/Type1 /Name/F1 /FontDescriptor 34 0 R /BaseFont/XLTFMO+CMSSBX10 /FirstChar 33 /LastChar 196 /Widths[366.7 558.3 916.7 550 1029.1 830.6 305.6 427.8 427.8 550 855.6 305.6 366.7 305.6 550 550 550 550 550 550 550 550 550 550 550 305.6 305.6 366.7 855.6 519.4 519.4 733.3 733.3 733.3 702.8 794.4 641.7 611.1 733.3 794.4 330.6 519.4 763.9 580.6 977.8 794.4 794.4 702.8 794.4 702.8 611.1 733.3 763.9 733.3 1038.9 733.3 733.3 672.2 343.1 558.3 343.1 550 305.6 305.6 525 561.1 488.9 561.1 511.1 336.1 550 561.1 255.6 286.1 530.6 255.6 866.7 561.1 550 561.1 561.1 372.2 421.7 404.2 561.1 500 744.4 500 500 476.4 550 1100 550 550 550 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 580.6 916.7 855.6 672.2 733.3 794.4 794.4 855.6 794.4 855.6 0 0 794.4 641.7 586.1 586.1 891.7 891.7 255.6 286.1 550 550 550 550 550 733.3 488.9 565.3 794.4 855.6 550 947.2 1069.5 855.6 255.6 550] >> endobj 38 0 obj << /Encoding 32 0 R /Type/Font /Subtype/Type1 /Name/F2 /FontDescriptor 37 0 R /BaseFont/FTROCH+CMR17 /FirstChar 33 /LastChar 196 /Widths[249.6 458.6 772.1 458.6 772.1 719.8 249.6 354.1 354.1 458.6 719.8 249.6 301.9 249.6 458.6 458.6 458.6 458.6 458.6 458.6 458.6 458.6 458.6 458.6 458.6 249.6 249.6 249.6 719.8 432.5 432.5 719.8 693.3 654.3 667.6 706.6 628.2 602.1 726.3 693.3 327.6 471.5 719.4 576 850 693.3 719.8 628.2 719.8 680.5 510.9 667.6 693.3 693.3 954.5 693.3 693.3 563.1 249.6 458.6 249.6 458.6 249.6 249.6 458.6 510.9 406.4 510.9 406.4 275.8 458.6 510.9 249.6 275.8 484.7 249.6 772.1 510.9 458.6 510.9 484.7 354.1 359.4 354.1 510.9 484.7 667.6 484.7 484.7 406.4 458.6 917.2 458.6 458.6 458.6 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 576 772.1 719.8 641.1 615.3 693.3 667.6 719.8 667.6 719.8 0 0 667.6 525.4 499.3 499.3 748.9 748.9 249.6 275.8 458.6 458.6 458.6 458.6 458.6 693.3 406.4 458.6 667.6 719.8 458.6 837.2 941.7 719.8 249.6 458.6] >> endobj 41 0 obj << /Encoding 32 0 R /Type/Font /Subtype/Type1 /Name/F3 /FontDescriptor 40 0 R /BaseFont/EWNEZM+CMR12 /FirstChar 33 /LastChar 196 /Widths[272 489.6 816 489.6 816 761.6 272 380.8 380.8 489.6 761.6 272 326.4 272 489.6 489.6 489.6 489.6 489.6 489.6 489.6 489.6 489.6 489.6 489.6 272 272 272 761.6 462.4 462.4 761.6 734 693.4 707.2 747.8 666.2 639 768.3 734 353.2 503 761.2 611.8 897.2 734 761.6 666.2 761.6 720.6 544 707.2 734 734 1006 734 734 598.4 272 489.6 272 489.6 272 272 489.6 544 435.2 544 435.2 299.2 489.6 544 272 299.2 516.8 272 816 544 489.6 544 516.8 380.8 386.2 380.8 544 516.8 707.2 516.8 516.8 435.2 489.6 979.2 489.6 489.6 489.6 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 611.8 816 761.6 679.6 652.8 734 707.2 761.6 707.2 761.6 0 0 707.2 571.2 544 544 816 816 272 299.2 489.6 489.6 489.6 489.6 489.6 734 435.2 489.6 707.2 761.6 489.6 883.8 992.6 761.6 272 489.6] >> endobj 44 0 obj << /Encoding 32 0 R /Type/Font /Subtype/Type1 /Name/F4 /FontDescriptor 43 0 R /BaseFont/MQGGGN+CMBX9 /FirstChar 33 /LastChar 196 /Widths[360.2 617.6 986.1 591.7 986.1 920.4 328.7 460.2 460.2 591.7 920.4 328.7 394.4 328.7 591.7 591.7 591.7 591.7 591.7 591.7 591.7 591.7 591.7 591.7 591.7 328.7 328.7 360.2 920.4 558.8 558.8 920.4 892.9 840.9 854.6 906.6 776.5 743.7 929.9 924.4 446.3 610.8 925.8 710.8 1121.6 924.4 888.9 808 888.9 886.7 657.4 823.1 908.6 892.9 1221.6 892.9 892.9 723.1 328.7 617.6 328.7 591.7 328.7 328.7 575.2 657.4 525.9 657.4 543 361.6 591.7 657.4 328.7 361.6 624.5 328.7 986.1 657.4 591.7 657.4 624.5 488.1 466.8 460.2 657.4 624.5 854.6 624.5 624.5 525.9 591.7 1183.3 591.7 591.7 591.7 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 710.8 986.1 920.4 827.2 788.9 924.4 854.6 920.4 854.6 920.4 0 0 854.6 690.3 657.4 657.4 986.1 986.1 328.7 361.6 591.7 591.7 591.7 591.7 591.7 892.9 525.9 616.8 854.6 920.4 591.7 1071 1202.5 920.4 328.7 591.7] >> endobj 47 0 obj << /Encoding 32 0 R /Type/Font /Subtype/Type1 /Name/F5 /FontDescriptor 46 0 R /BaseFont/THQWSW+CMR9 /FirstChar 33 /LastChar 196 /Widths[285.5 513.9 856.5 513.9 856.5 799.4 285.5 399.7 399.7 513.9 799.4 285.5 342.6 285.5 513.9 513.9 513.9 513.9 513.9 513.9 513.9 513.9 513.9 513.9 513.9 285.5 285.5 285.5 799.4 485.3 485.3 799.4 770.7 727.9 742.3 785 699.4 670.8 806.5 770.7 371 528.1 799.2 642.3 942 770.7 799.4 699.4 799.4 756.5 571 742.3 770.7 770.7 1056.2 770.7 770.7 628.1 285.5 513.9 285.5 513.9 285.5 285.5 513.9 571 456.8 571 457.2 314 513.9 571 285.5 314 542.4 285.5 856.5 571 513.9 571 542.4 402 405.4 399.7 571 542.4 742.3 542.4 542.4 456.8 513.9 1027.8 513.9 513.9 513.9 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 642.3 856.5 799.4 713.6 685.2 770.7 742.3 799.4 742.3 799.4 0 0 742.3 599.5 571 571 856.5 856.5 285.5 314 513.9 513.9 513.9 513.9 513.9 770.7 456.8 513.9 742.3 799.4 513.9 927.8 1042 799.4 285.5 513.9] >> endobj 50 0 obj << /Encoding 32 0 R /Type/Font /Subtype/Type1 /Name/F6 /FontDescriptor 49 0 R /BaseFont/LFNUIM+CMBX12 /FirstChar 33 /LastChar 196 /Widths[342.6 581 937.5 562.5 937.5 875 312.5 437.5 437.5 562.5 875 312.5 375 312.5 562.5 562.5 562.5 562.5 562.5 562.5 562.5 562.5 562.5 562.5 562.5 312.5 312.5 342.6 875 531.3 531.3 875 849.5 799.8 812.5 862.3 738.4 707.2 884.3 879.6 419 581 880.8 675.9 1067.1 879.6 844.9 768.5 844.9 839.1 625 782.4 864.6 849.5 1162 849.5 849.5 687.5 312.5 581 312.5 562.5 312.5 312.5 546.9 625 500 625 513.3 343.8 562.5 625 312.5 343.8 593.8 312.5 937.5 625 562.5 625 593.8 459.5 443.8 437.5 625 593.8 812.5 593.8 593.8 500 562.5 1125 562.5 562.5 562.5 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 675.9 937.5 875 787 750 879.6 812.5 875 812.5 875 0 0 812.5 656.3 625 625 937.5 937.5 312.5 343.8 562.5 562.5 562.5 562.5 562.5 849.5 500 574.1 812.5 875 562.5 1018.5 1143.5 875 312.5 562.5] >> endobj 51 0 obj [5 0 R/XYZ 42.52 392.79] endobj 52 0 obj << /Rect[66.43 378.86 140.73 387.08] /Type/Annot /Subtype/Link /Border[0 0 1] /C[1 0 0] /A<< /S/GoTo /D(section.1) >> >> endobj 53 0 obj << /Rect[66.43 354.26 197.61 364.23] /Type/Annot /Subtype/Link /Border[0 0 1] /C[1 0 0] /A<< /S/GoTo /D(section.2) >> >> endobj 54 0 obj << /Rect[66.43 331.42 279.61 341.39] /Type/Annot /Subtype/Link /Border[0 0 1] /C[1 0 0] /A<< /S/GoTo /D(section.3) >> >> endobj 55 0 obj << /Rect[80.25 318.85 147.4 328.72] /Type/Annot /Subtype/Link /Border[0 0 1] /C[1 0 0] /A<< /S/GoTo /D(subsection.3.1) >> >> endobj 56 0 obj << /Rect[80.25 306.29 147.4 316.16] /Type/Annot /Subtype/Link /Border[0 0 1] /C[1 0 0] /A<< /S/GoTo /D(subsection.3.2) >> >> endobj 57 0 obj << /Rect[66.43 283.44 131.71 293.41] /Type/Annot /Subtype/Link /Border[0 0 1] /C[1 0 0] /A<< /S/GoTo /D(section.4) >> >> endobj 58 0 obj << /Rect[66.43 260.59 127.37 270.49] /Type/Annot /Subtype/Link /Border[0 0 1] /C[1 0 0] /A<< /S/GoTo /D(section.5) >> >> endobj 59 0 obj << /Rect[66.43 237.74 280.24 247.71] /Type/Annot /Subtype/Link /Border[0 0 1] /C[1 0 0] /A<< /S/GoTo /D(section.6) >> >> endobj 60 0 obj << /Rect[66.43 214.89 278.95 224.87] /Type/Annot /Subtype/Link /Border[0 0 1] /C[1 0 0] /A<< /S/GoTo /D(section.7) >> >> endobj 61 0 obj << /Rect[66.43 192.05 228.16 202.02] /Type/Annot /Subtype/Link /Border[0 0 1] /C[1 0 0] /A<< /S/GoTo /D(section.8) >> >> endobj 62 0 obj << /Rect[66.43 169.2 246.04 179.17] /Type/Annot /Subtype/Link /Border[0 0 1] /C[1 0 0] /A<< /S/GoTo /D(section.9) >> >> endobj 63 0 obj << /Rect[66.43 146.35 116.07 156.32] /Type/Annot /Subtype/Link /Border[0 0 1] /C[1 0 0] /A<< /S/GoTo /D(section.10) >> >> endobj 64 0 obj << /Rect[80.25 135.53 220.87 143.76] /Type/Annot /Subtype/Link /Border[0 0 1] /C[1 0 0] /A<< /S/GoTo /D(subsection.10.1) >> >> endobj 65 0 obj << /Rect[80.25 121.22 264.34 131.19] /Type/Annot /Subtype/Link /Border[0 0 1] /C[1 0 0] /A<< /S/GoTo /D(subsection.10.2) >> >> endobj 66 0 obj << /Rect[80.25 108.66 208.66 118.63] /Type/Annot /Subtype/Link /Border[0 0 1] /C[1 0 0] /A<< /S/GoTo /D(subsection.10.3) >> >> endobj 67 0 obj << /Rect[66.43 85.81 405.5 95.78] /Type/Annot /Subtype/Link /Border[0 0 1] /C[1 0 0] /A<< /S/GoTo /D(section.11) >> >> endobj 68 0 obj << /Rect[80.25 73.25 201.97 83.22] /Type/Annot /Subtype/Link /Border[0 0 1] /C[1 0 0] /A<< /S/GoTo /D(subsection.11.1) >> >> endobj 69 0 obj << /Rect[80.25 60.19 242.59 71.15] /Type/Annot /Subtype/Link /Border[0 0 1] /C[1 0 0] /A<< /S/GoTo /D(subsection.11.2) >> >> endobj 70 0 obj << /Rect[80.25 48.12 269.16 58.09] /Type/Annot /Subtype/Link /Border[0 0 1] /C[1 0 0] /A<< /S/GoTo /D(subsection.11.3) >> >> endobj 73 0 obj << /Encoding 32 0 R /Type/Font /Subtype/Type1 /Name/F7 /FontDescriptor 72 0 R /BaseFont/UEBJWX+CMR10 /FirstChar 33 /LastChar 196 /Widths[277.8 500 833.3 500 833.3 777.8 277.8 388.9 388.9 500 777.8 277.8 333.3 277.8 500 500 500 500 500 500 500 500 500 500 500 277.8 277.8 277.8 777.8 472.2 472.2 777.8 750 708.3 722.2 763.9 680.6 652.8 784.7 750 361.1 513.9 777.8 625 916.7 750 777.8 680.6 777.8 736.1 555.6 722.2 750 750 1027.8 750 750 611.1 277.8 500 277.8 500 277.8 277.8 500 555.6 444.4 555.6 444.4 305.6 500 555.6 277.8 305.6 527.8 277.8 833.3 555.6 500 555.6 527.8 391.7 394.4 388.9 555.6 527.8 722.2 527.8 527.8 444.4 500 1000 500 500 500 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 625 833.3 777.8 694.4 666.7 750 722.2 777.8 722.2 777.8 0 0 722.2 583.3 555.6 555.6 833.3 833.3 277.8 305.6 500 500 500 500 500 750 444.4 500 722.2 777.8 500 902.8 1013.9 777.8 277.8 500] >> endobj 75 0 obj << /Filter[/FlateDecode] /Length 1793 >> stream xÚíXK“ã4¾ó+ÂÍ.ˆÆ’%?¸í›å´ÅÌá q”DµŽ$›Ùü{ºÕrâL²°EqX(.Q[îÖ×Oe‘±,[lax³x~{óš/xÉ_Ü®¼¨™(Ë"c &^þ’¼;¼xþ:ýõö‡›×â´oɳšùb)8«iã³t™g<Ù§B%‡aÛwôý`»•í6ø!’¡ãÖ¼[û@4N»ÉÊ8« SÆYQ-`"ˆú!0Eò.­xˆ¾CÚÙÍ6e2 —Ų,YYƒ²9«%)Ùáêúue·¨ÌÁTyÛïÉÏV´ÿÒÐ’ ÐzliåUÛÚI•nE\¾7.òuÃ¥ýžƒ[ùÁ ð¶ŸÓJÂVoû8ñÊBDƒCSÚößÝÜ<>>2ä[&‡å¾ýÒ÷gM¿»ñýzÀí)ÈÖÎÜ@½¹OÁÓe]£S÷2¢ƒÔªZ6ãÎtGkCÚ¹4Ï—cö–œk‡`7q QàŸ€æG|Sò˜æqîýÝÛ74uÿô¢þÑnXï6!š€ý^'ø‚ÞzcŽj>Ñ—‘ >À£›”I܈/.¥G¸†€ ®| jr¨\3¡XwÄõÆ®i’|Ë3ʣłK–KL¤ $/'k¿ÈrPÀÐàƒ¯nC=åè¥d Ro.¡üÒ9ž.kŒ–`.”d56˜N<y³Rž³å‰o!XUÇÕÈ7¤­Þ€u­’½3Îü6Zê¯I˜ó¸”P)Væa5' o(1SBþTÛk‰1Žß–n6¹ˆI–Ov’{ ãøŠVs¹3hOe ûêŠ Ò>g€-ÏT–¼úؘ="0¿oŒÅÙˆžù×ÃçïügÎ}ÇyÅJÍ@$Ð%ÄZ¥"èâ3@ŸøôϽþÓ|"sÀ5À))(_bÉ“:@̳0¯*&åüu’ça.UÁµÌŠ8Þ¥u‰m${ÈoPÅ®ñ<ºÊ´¬YN½qALŸ¶]3ÇÅôt€4a>B6õÁƒÂú’rDL*ñf÷ŸÊ“J'™ªºTIebzT”×T¢ž…%ÅQ§çe¨]·´(BíºTg&OÕWÔŠeT´ªhHó0n6GÉPý÷¶5Q©@WDx]%ËéåV“¨Ûmp• 'ôb`-YB»y3:g(¡‡†ÖvÖ‡ŠEƒ“ˆâŠ;¨ú5y t$Ur›ÖØñ Ÿàw:0çwY¤™œGÎX<~„'V¬üóº ¿;®ïƒ)¨ÿ¢yX³f¦ WŠå噀ÿL®¹rùÙ¹é"¾µbÕ”<0á#¾·øØšš'j¨D›Øbm#Ô›^W;xgÆŽŒBLæÇ·ço(Îï“À¿¼ã‡>¡(.P,2pë|B1Ÿ¡AƒÜÒ¹¦v$6^¶™Ç>‡Ç&ÏXÿ'óz|Šó•BYäÿß ˜sÊ9w˜sz÷!…zyJ¬z·oc’ç4|‚D‘|Üé˜#B‰5z×Ú.ný†VvÚŸ‰ ¾MUexRÉ^½ÿñõ•„7Óöü^O^!sVEWâó„G…ÜT"eÀq¶°p^À94UuÆçßgÿH˜æ—a MM^OØÆdw’ŽøöãpýÙHëéý‰³ƒXÝ7š ,0ÁÍ…ý½k~¡°V—°ÕôtXcö{6U ˆ>=˜c!~Z°/Ó¡˜Sÿë‰y,2ÅT~&úß–ÞJAÿB”€bü×·dªXÀ…1€éºñW_“3 endstream endobj 77 0 obj [52 0 R 53 0 R 54 0 R 55 0 R 56 0 R 57 0 R 58 0 R 59 0 R 60 0 R 61 0 R 62 0 R 63 0 R 64 0 R 65 0 R 66 0 R 67 0 R 68 0 R 69 0 R 70 0 R] endobj 78 0 obj << /F1 35 0 R /F2 38 0 R /F3 41 0 R /F4 44 0 R /F5 47 0 R /F6 50 0 R /F7 73 0 R >> endobj 6 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 78 0 R >> endobj 81 0 obj [79 0 R/XYZ 42.52 737.53] endobj 82 0 obj [79 0 R/XYZ 42.52 693.64] endobj 83 0 obj << /Type/Encoding /Differences[0/Gamma/Delta/Theta/Lambda/Xi/Pi/Sigma/Upsilon/Phi/Psi/Omega/arrowup/arrowdown/quotesingle/exclamdown/questiondown/dotlessi/dotlessj/grave/acute/caron/breve/macron/ring/cedilla/germandbls/ae/oe/oslash/AE/OE/Oslash/visiblespace/exclam/quotedbl/numbersign/dollar/percent/ampersand/quoteright/parenleft/parenright/asterisk/plus/comma/hyphen/period/slash/zero/one/two/three/four/five/six/seven/eight/nine/colon/semicolon/less/equal/greater/question/at/A/B/C/D/E/F/G/H/I/J/K/L/M/N/O/P/Q/R/S/T/U/V/W/X/Y/Z/bracketleft/backslash/bracketright/asciicircum/underscore/quoteleft/a/b/c/d/e/f/g/h/i/j/k/l/m/n/o/p/q/r/s/t/u/v/w/x/y/z/braceleft/bar/braceright/asciitilde/dieresis/visiblespace 160/space/Gamma/Delta/Theta/Lambda/Xi/Pi/Sigma/Upsilon/Phi/Psi 173/Omega/arrowup/arrowdown/quotesingle/exclamdown/questiondown/dotlessi/dotlessj/grave/acute/caron/breve/macron/ring/cedilla/germandbls/ae/oe/oslash/AE/OE/Oslash/visiblespace/dieresis] >> endobj 86 0 obj << /Encoding 83 0 R /Type/Font /Subtype/Type1 /Name/F8 /FontDescriptor 85 0 R /BaseFont/XXOQUS+CMTT9 /FirstChar 33 /LastChar 196 /Widths[525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 525 525 525 525 525 525 525 525 525 525 0 0 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525 525] >> endobj 89 0 obj << /Encoding 32 0 R /Type/Font /Subtype/Type1 /Name/F9 /FontDescriptor 88 0 R /BaseFont/WFLZGO+CMR8 /FirstChar 33 /LastChar 196 /Widths[295.1 531.3 885.4 531.3 885.4 826.4 295.1 413.2 413.2 531.3 826.4 295.1 354.2 295.1 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 531.3 295.1 295.1 295.1 826.4 501.7 501.7 826.4 795.8 752.1 767.4 811.1 722.6 693.1 833.5 795.8 382.6 545.5 825.4 663.6 972.9 795.8 826.4 722.6 826.4 781.6 590.3 767.4 795.8 795.8 1091 795.8 795.8 649.3 295.1 531.3 295.1 531.3 295.1 295.1 531.3 590.3 472.2 590.3 472.2 324.7 531.3 590.3 295.1 324.7 560.8 295.1 885.4 590.3 531.3 590.3 560.8 414.1 419.1 413.2 590.3 560.8 767.4 560.8 560.8 472.2 531.3 1062.5 531.3 531.3 531.3 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 663.6 885.4 826.4 736.8 708.3 795.8 767.4 826.4 767.4 826.4 0 0 767.4 619.8 590.3 590.3 885.4 885.4 295.1 324.7 531.3 531.3 531.3 531.3 531.3 795.8 472.2 531.3 767.4 826.4 531.3 958.7 1076.8 826.4 295.1 531.3] >> endobj 90 0 obj [79 0 R/XYZ 42.52 520.6] endobj 91 0 obj << /Type/Encoding /Differences[0/minus/periodcentered/multiply/asteriskmath/divide/diamondmath/plusminus/minusplus/circleplus/circleminus/circlemultiply/circledivide/circledot/circlecopyrt/openbullet/bullet/equivasymptotic/equivalence/reflexsubset/reflexsuperset/lessequal/greaterequal/precedesequal/followsequal/similar/approxequal/propersubset/propersuperset/lessmuch/greatermuch/precedes/follows/arrowleft/arrowright/arrowup/arrowdown/arrowboth/arrownortheast/arrowsoutheast/similarequal/arrowdblleft/arrowdblright/arrowdblup/arrowdbldown/arrowdblboth/arrownorthwest/arrowsouthwest/proportional/prime/infinity/element/owner/triangle/triangleinv/negationslash/mapsto/universal/existential/logicalnot/emptyset/Rfractur/Ifractur/latticetop/perpendicular/aleph/A/B/C/D/E/F/G/H/I/J/K/L/M/N/O/P/Q/R/S/T/U/V/W/X/Y/Z/union/intersection/unionmulti/logicaland/logicalor/turnstileleft/turnstileright/floorleft/floorright/ceilingleft/ceilingright/braceleft/braceright/angbracketleft/angbracketright/bar/bardbl/arrowbothv/arrowdblbothv/backslash/wreathproduct/radical/coproduct/nabla/integral/unionsq/intersectionsq/subsetsqequal/supersetsqequal/section/dagger/daggerdbl/paragraph/club/diamond/heart/spade/arrowleft 161/minus/periodcentered/multiply/asteriskmath/divide/diamondmath/plusminus/minusplus/circleplus/circleminus 173/circlemultiply/circledivide/circledot/circlecopyrt/openbullet/bullet/equivasymptotic/equivalence/reflexsubset/reflexsuperset/lessequal/greaterequal/precedesequal/followsequal/similar/approxequal/propersubset/propersuperset/lessmuch/greatermuch/precedes/follows/arrowleft/spade] >> endobj 94 0 obj << /Encoding 91 0 R /Type/Font /Subtype/Type1 /Name/F10 /FontDescriptor 93 0 R /BaseFont/FHLGUL+CMSY9 /FirstChar 33 /LastChar 196 /Widths[1027.8 513.9 513.9 1027.8 1027.8 1027.8 799.4 1027.8 1027.8 628.1 628.1 1027.8 1027.8 1027.8 799.4 279.3 1027.8 685.2 685.2 913.6 913.6 0 0 571 571 685.2 513.9 742.3 742.3 799.4 799.4 628.1 821.1 673.6 542.6 793.8 542.4 736.3 610.9 871 562.7 696.6 782.2 707.9 1229.2 842.1 816.3 716.8 839.3 873.9 622.4 563.2 642.3 632.1 1017.5 732.4 685 742 685.2 685.2 685.2 685.2 685.2 628.1 628.1 456.8 456.8 456.8 456.8 513.9 513.9 399.7 399.7 285.5 513.9 513.9 628.1 513.9 285.5 856.5 770.7 856.5 428.2 685.2 685.2 799.4 799.4 456.8 456.8 456.8 628.1 799.4 799.4 799.4 799.4 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 799.4 285.5 799.4 513.9 799.4 513.9 799.4 799.4 799.4 799.4 0 0 799.4 799.4 799.4 1027.8 513.9 513.9 799.4 799.4 799.4 799.4 799.4 799.4 799.4 799.4 799.4 799.4 799.4 799.4 1027.8 1027.8 799.4 799.4 1027.8 799.4] >> endobj 95 0 obj [79 0 R/XYZ 42.52 421.49] endobj 96 0 obj [79 0 R/XYZ 42.52 397.19] endobj 97 0 obj [79 0 R/XYZ 42.52 70.01] endobj 98 0 obj << /Filter[/FlateDecode] /Length 3192 >> stream xÚ½]“Û¶ñ½¿BsO¼‰!ÁïGlj3ÎLÓN}™<ô:ˆ„$Æ©¤åë¯ï~¤D]ìŽ;}9‹Å.v±ŸÐm?6û }~Ü|÷øíÛlSøEºyÜmTê‡ÉF…~n¿ÿ§ú÷QyïÚ{•yCßÝ?À·Ë¡îÚû=þ´ùáHÅ›3ì-ü8Û„™©ÍqçŸ*™6›÷Ä)Ý„±ÅÄ*ö“ló€ë1±z×VæpËb¯Ûá7ñžT’5†Ç­>ë8"­|“»S3©(óã‚HÝ5u;~òíá7|û¶Ød~‘!jøa´ ë{ƒô[Sƒ$ò¶÷*÷žyœ[Ÿ·.¸ðÞ‡0 ²9êf×èAÛ²®ýÓóŠ]žùYþ%ìÊ5;ÞKì’™Ýo§çr»»Å+‹ü4ý¦¿%Z†~~^¶4Zó”½KSüÃíM–AèçÅÜÚ uÊÞ•œøç·²FS9ž ž&kÎh)þ¼°™ÎËh+›àò¢ð¥x{Ô%Fø›á6 ®ã­1âœh˜a2¡$~èÂÄ›®µƒn1: ˆÇÊ-;޼]×3¨ìާÞX+iåRîÀw†i^]œ†¼V_oLç€ø³3½iK§¯ºÅo2ŧ¥ta¢üà"ò~½xÀSgáUu»_[q6{h¼½!!&Ö—…Ln ‹ñm!£Â²¥)~½â5·œtŠ Ñ/ÞŸßáKâÅÓ~¥xCç,ÔÕ@ BïÍ»·ŒqÒ½½u­Qœâÿ‡áf…Ÿ_j¸?|*͉Ê8¾<ÝVÍ )òÐWÎÀ’ÿ©óÍ]ª òƒˆ•¢Ý8–åH5HxªºbM lR?Ëh÷“JÕµ ?qü×û<ñúz0|§˜«ùR¿V[A4!€KëíáÀA{Œ`>b(6ý3cíÆ¶tJ^¸Êž©ãßÜ“BBy[í =ÉT‡r)𺎎ÀŸ®~Ã{Èm*Æš= ¸f‡ï¢f_ª"€8`ÍÏšFiáDo¾{ÛÔ[ zMâÀäÉñ,ËãÀ‡ºûéž×kËÀ3¨t0­å;0ùÂ{ÃHn÷£Þ¬#åuÑRÓ£ ÎXÈ’ƒÇúæÇèÔwû^oPŽÙ×5›™xìGôkÓÖ†|2AtfÓïtiDW ViÇe<0”{ }P\„¢!@*ǾG‚¹#¨Çá@· ‹<,4ªše»ØáÄg”'ï„'z*- ™€ñôÝQhZ\ŠÊWF‡BBà pÆK«ŠŽÓ™΃•tFˆ¶<©Œ­{S¡ìqì½Þ¦0`²$2`í20Ü $'¤eÓcMúýpuÖªZ$$a¿ÿõÝë›­YîĪH½zÀo>Ÿ•)ë à ® -8h‰ ¡Í™×thmêGY[Ð˽nl*ÆÜ’Ú‹É@ !‚/œ9” Hó õD^îP¯”ާ¥°@ÈÓQd„ÒÇϱW‚~œ›ä× &Ÿ(å’ ¾ìSQ6ËSò¹åúìÆ0é¡WèC·ÓRíž.z(1ÓÀUòH@1}ßÉ"äËa$¯€dô‹uÓmàh #9Q÷ÎKœ@“ýZcލžUßYÑ0ù·é»WˆÙP†ŠÍ•×ví.3ÐI„ã÷ ˆÕŒBCŸä MóVÇêhtË-[EBr„.ÉÑÉ@ ×å’ò–›o£Ï‘²Œ2¼µæ®›ÌÂ26™*,CSÜÀ•¦¶ƒ•½¬®¯È¾`™… <[C/QïžyÆô(NYžÀº€ŸØurrS$1¬Ç8D ¦6;G­ƒ;^£… Q¾N¡ª@ç †ÈõRnÈ2”aaÄ©=ƒ8`ùÆ ¼1†Õ;Á9´²,g­"H,$ÊS %+õhe™¬🞌«wî.ùMö†“½iM X5ñ]Ý'Ÿ!>C¤`Šð0p3iœaÕbÍvÍÈ%¢ëýnšek2‘è¶p°e˵ƒƒ“/Ò°ão…ÒÇJ±ô©…b©…¥n86Ò½ÁŽó¤#{%ïù`zWd0Å(MÞ†…P-‹³ç¶âB:œJ¨¶ë.°Ø™Ô/U÷*òEùÄõ¢¤˜ÙÃxáz4?ê©.K$+°0;iËu}@•5¥!$ƒîˆàkwä“fÜ!À¶@´‚ÏŒøûHõ!z‘—^CVõ“çRÅAŸDG$>6C}j Õ»©~ÆW´fÚœ{£+i):?ð´ »ª*ÆŸÿöËãTzοâÛˆk‘£6ŽÜ¥ô\j1DL×´ë8±ëFrUˆœÏt?r€òjKGÊÉÒH½0\8L$éƒIe±ói>¾€ë3 è®˱µ±ä]¬²=Y,P´£=Õ%׳ÄZË!NTRI¹”«EŠ]9 Çɨ«ÎiLTtÝÿîyr¥º¿Ru>«šAxΡX\=^û͹‡:æ…’T¢°ÜvN®’¢’¼Ýˆ¼,1ò ۶e<Ä¡7‚ÑmQõÞïP( †Å̲kep–:PÁJ‡ž",ín”‚T&É  åvwù#TÅô*ž„ ÛÌ#?I&ÿа€F~È} õ·æŠZÔÔ’Zžà“Ö5µ :Q³Cý»qT~,í»Z<Î¥×biˆÒø4Ô0ðþª[W즜WñËP—ÕÀ¯¼‹1É~yõ.ê,ývŠ6„¦ùs+¾ñåã*{8æY‘Ì7âØW<¢ßB<‘Òë,‰k†¹à ¢¶ŒÃªÝW‰-ÌÊ-HýGrÕÚGŽîÏ’‘0ÇjßpÊ­"׎ŽÌ'µp©¶u]#Bš?GCAyK¿…ñâ}‰&ng^ðT,æb¨U¤˜Ã!ey¨Æ0™ð¨>Rˈ‹•4çü‚p® §Bˆ*QJZ¨@oš†%¤1Ș -<6q^ADÇÐ/øpØÇSÆýÀ[õ ÉmÏÓ“G ½ Ù‡ë\ã ”ªËy| žì8††°;2¼M÷=÷ÃhviqÀÁ}øŒWé^ÈO'ò¼`‘k#åÝM´î˜Í…ÝÑgƒÂe£kR÷¹+[1¤ÍZâ9&•Þ¡£>’FDzE7Rx$"Ø^_—ÔY Þ+ù“òÞëŠHd“ÇÀH®€€§¬ˆ“¦>Ö`àÙU 6Ž/7Ä) .¹òkVªÂdTCý Sº+× *ºÒ`rÉ +,/޶uËWc1Ø©XK…#¶+„¨„ëÐ` <’ÂxÂv–£¸§Ã¯xÊWs鸺*w´ZðE…V¸Núyñ žÿ^ÉÛ÷0Erù¬ói7?£¡BRü¥Ebc Ý• Eæ’;ÇNÔ: †Óñ2Ñްì\]8Ë0¸ nÞc-OÎ/#nŸy_to3rf \ÈDl]Ñ;]^ð£ L3¿l `™´ˆ‡£M:vü"IäÀz¡sý!=%eüL¸’P ÞKí |ÒË" –Ÿ1Ñ$ð»aê…ßó—-Ÿ¦Ü…ã !ñT*|RÇçîgvÒ»å~NàÀ•Âý%ò2° ÊÌêsm®¹j4¿+QúàÖ‚ŸŠ)¹^Œ;äî46Z2ù4°wK–’’slŒ¤/IJPJê¶Æò²ƒ­Wæp^|rNÓÔù÷?5=9ƒò$Ìv“ eöæ±¶‘ìçŸUQñŒ//Ï1v øÇ8ò¨{ø1ç~˜ÌE$ ,Zy\ã·TÑGâíUËÞ¼åm¶ûRˆóÛ/…âXzóû£q•€ç‡¢A¯f].Ñ3sŠ×L¿¿b“ZSIبá³3ÒNNwjeŸ˜ù¡‘o&Üɺ;<KÉ´ÒúÎïØ d±×BoùÖQ‰„ßÞN‚4@ÂÂúAfap† onþÐC&~°ø/ pÿ´ü#Ù¡2W[ƒ1©0I•÷zÜsï ÚWñ+þO$„X[š…÷“üwÒßï¡;óùW„_qÜO½ï/ÿrtŸ endstream endobj 99 0 obj << /F7 73 0 R /F6 50 0 R /F8 86 0 R /F9 89 0 R /F10 94 0 R /F5 47 0 R >> endobj 80 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 99 0 R >> endobj 102 0 obj [100 0 R/XYZ 42.52 737.53] endobj 103 0 obj [100 0 R/XYZ 42.52 566.46] endobj 104 0 obj << /Filter[/FlateDecode] /Length 2778 >> stream xÚ­Y[sÚH~ß_Ád_ÄT,ë~Ù}˜"{ÈÄØÈf¦Ö[.Y4  H”$BüïçÜZH`'LÕ>©é>}î—O¢g™–Õ[öèqÓ{7»¼{±½Ù¢çD¾=Ç6m»7»ú¯ášý ×u•«2©³|É¿ë•âEŠÏÈò¾µ*IJ'ŽqÁ' åôóø†WŽ®Uÿ³÷½Ñ ñzûÞ…›^سCÓuz›žYfàÈÏuoJzú½Hô¼ðL?ì]à±Gzn“´ïDÆ—¾É%Æ1*uáY–‘ð£íA,­E>Îç¼Ø$_‰ªøgVóS%U¦J^×?÷eVËõ9lÁ­t·QìpS‘ƒßØý£ùF±“KÙzÍ«\©yG7Í·xª­6z}d¡ކ–j[ŠDUUl­y¯. @Cv}'6ödÒREƃ±Å…¡ÊU²­øæ¢,6¼Z!i]oÿuyyr߬Š]™ªEQ.•™«ú¡ÏQY¼[”sôQ£ <ŸvÙz~,£J!RôÓªmœOÆí³z…úû’5VÐ ×[¼öœ>-Ì=¸×ó\ã^{#6Rtz)‹]½ÝÕ¼Î*~® ±}±[¯Ÿy/YW…¬Ð̯”>Ù:yb‘>Ù‚ÇÏ(ºØ‰ØÏýÈ3„b.y!òJ•È…ùiðÔ<“ò1RÀwÉUFVÀÏ}™l·VUV?ýDül׌àÉåy—“%Žƒ¾‰ŒçzUäüûkŸ¯e¼aŽéáÂ5VIÅ$Oì%7êB[³p +Êl™åÉZ x0 иäÃ÷êLσÐ|X¯’šïˆ×XÎ~Òµ,žÀÅÏdÐ…¶¨ñe\’còÕ⪂Ÿ«~Å¥˜ÍWóZ}«UN^x‹û–{žÎ2Øæº'æüØ]ùE¸{ÔOaRh›­U‰ xÆŒs%hö™jWivOdä+m2-ÙJ^“dJðÕ2MÙYÆ‚ \Jƒ.ɘåê°³¯„Y>çÅ.Ͼa0•¦o„nÀ¶=ïu“’®Î•Ö‡ù‡Àÿ(0¦Å±¹–t„½å;-/Ûo]ö­¾â†ÑM‡jŸ-[©-‘ôýÞÄú›¶%%¥µ‘Q…¾Zª‡¾.×N=óHD–R½ØmÅ$«É³1òŽ!žIEà žª#uJà Zn>¯ø¸J1é`˜€éžMÃ!gª…JJ¦D§6.<Ëäö:ãÉFÅ bµŒˆ|…¢d6âZ¯‹dÎäœpÔ ŸPQ¿œuî*”ø\Ðäò‹S$ÐM>€–™-yöð~7M`ƒbOŽ'–2Ô…ïxÆ'H=fQ=WµÚTLU"œÂ6I®³ Š9¢# i>¨xûtœÌª„Fäó›QÂÕ‰ijTƒx%èÙ”` b3tYõ!À„² µS`‘ò²ÐµZÈ*ôYµ)e€ÀꀬÚh õ„çÜLIR½Î¤¹r×kªÃ; ^Ü…ÙPWº-èš‚ZbÃ¥yAõK7Ö…‚¸0]ïæÂFo 0hu ¯[-o¥o檜·–<ì•(Sä ç“a;WhB®Ž¦í!‡¸/#W Yè©A*D¹Øåi-­Ë\ÔôÒH¢fZÝ(RðñKs†ºçYP™O%üѸ )ƒ <9ƒ»èeº дÂU©äôá¡€Þ ¹û§JëêÍ¿a7Š hÂáðÝ5ß]w× ûEàëC€V]Tî:À€sèÂâr× MÛk6™wv6pYäTaMÀÙÓ uçvẶÚíx°ñ_8Žcº!ˆÊ0l~‹äÖ&Ô‡½³ šœàƒÏØ3ENÀ9›m'WaP%Û&Ý*‰lÁÙQ0ƒnîÀ„Y'PMÒÜ/lÓïΫñï·# ô}ªXPf®ÒŒŠÁ‡Î´R‚§à ãÜ`?ߥB”ðãMƒ9°#•%—ÝæMJð‘t;qB~€J%D¡bb²(7E©4åfCöø]·'ÝœÛ]©t۠כꗗgô€<Ü´ìàÐãuõH‹¦áÚ>o ú¯Æ½4Ú¬I¡ê])W-‘$?«½j{•äЦúó%U–…°N¹¥ÌUÃîe,`ìJEy´ò zKùÜÍ$¸Ûd)ÈÀmT-;ƒÄZh’´,ªê:­“|¹ã×Yì¼ùLÃ¥¯Y»ê[ª¶äØW`Ó[ˆ+žÆ \5oÁn¨_Na—º=o@ð® LZsW§¶ßâ R%•¼+þØŒÞxˆº+n2–ÕoË¡“¢V–/‡A:!O°c¬iÚóaÕ~wÐpV\¹Mä]q¬x^øþpW#@ìâU¶bælÚ/øz:¼›Lg˜ ƒÉl2€&@Ù¶:ZfL­ŽçµoÚàÙP7JiÐïæz²Ä¯œ¼—×q/4ãyÙ®eºÂÌMN%ŸeèŒZà1QtøØb;®éS+6툨//Ñó i½KÖ¼¦QŽGF²c›±Ý¹&V¡ExAg®’ãJ'íf˜JÈ/6=»Ãòg¦8bÉN¢«…ðh;‰6~¾ä;°d„ôϹZd¹Uß]?Ž'³ÑÍè#x(€kÖ7˲¡÷Ø–o5â?åš½–›åµZ¢þa6²:òDÎõ‡»Á »PÈRœKF#±à:¢È‹m¢á¢"6xYìp0¹›Œ‡ƒr EûÇ¢‡I=Õ1î83tð, ïÃßFW`¢ 7PNp,ç>I¿hã:B¢Ø9Óòø§eO|bÏðÞ;•ø`¼¿àûß‹ Óp> endobj 101 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 105 0 R >> endobj 108 0 obj [106 0 R/XYZ 42.52 737.53] endobj 109 0 obj << /Filter[/FlateDecode] /Length 1490 >> stream xÚÅX]sÚ8}ß_áé>ÄtbG’å¯}3`R Ô8“Ý)ÆA< vj;›f³ýï+Y²1ÒÎì¾  £«s¯®$i%åÅ¥Ôö/z¦d«¶!ùKIA† u ABÉï~–5µ¥hš&_’ˆ$AF+ÞÎî ¯ÌYå0j!SÎH² æù$+üK9rrÛ¿äµ)ÒÍ5i}ñ?J®O‰`é‰"Û*6%hª’6¶€j Ñ\K“œ§%Y‚'ëÇ’Â Æó×Y†EÒ–‡“ËY·éNü[ǵt ƒo ïÙH]¾ ’ˆ×bQnHš+‹pEÒ,åp³!‹0ÈÈúùýENP g´Ï`ìtgð*ÿßäq°à•»0 ’§0»ç5ÆkàŒ~Ä&­íâê‡qQ¿l6ãY/®âZoÆÅÀÖã^ô (w~gíS„ >–LÕ6¹„¡jC:JW±•ó$¦ÊÓ59!K’hN¬­3ÙÒ˶zÈV!_ì=ÿ¬—_u":„}ëÄQšTÿ¶Ì¤¢a$?¦9¦~óžyÌ$‰×¬Ê~x’”¹ÕÞ2 n© ÔèÑ*ÿ¶dÔ惶^¢@ U‹Úiª™.vCp.¤Íù²ãËJÊ—sÍG3®¬RpÍB õ[È­ŽêÂè´{³±ãMÜYÛëPIè¦ÎôAMl¯v»ƒÍÅDB0IRXõå\UÕï-ŰNq†-ö8½†]®•DÔ>È ©Ì§­ƒÐF㲯ü-4> š­øOÂ6'ÿãg†ýåí«n{NçÊõ'|Òé4ÿ#„Hµq•8åe6ñrƒ-Ì­ªS6ò?QsÒ­gVd–»µØó¯qVD‹wïÞQSÐ_Þ "¡Ú³³3ÚO©Kæ›ö‡élÖuýáDði0å¾Ïº+&Š3^IçAT((Í ¢ÂÏ"B??Î6_Çiu•9®UÓ¬ssÎ%B0Ÿ“QùÎËs^ü&ì$Ì"®¨ ) ²7aFÔ ”f õíôì…Õ»k`Õ„'ì.×oqÖÖ%Õ‹“>V`*O[bŸ¿œogQŸyë~–,`ï8‹m€©°xù~~Lç\kf‹8‰ø´]fZ6«îs²Ý^äR™j°Y¦¨.SÌãUþ-ˆð©fQ°¡†¶5qéÌR-³‰Ím¿ë *àMîü.î2\³õC î„2~d7€Ýø=«c^ø|ÀèPÅ⑼ñ¡ë1»:7¿Ðá°?tg\§ëz"tþà –VŽ®ybI‚æ‰óYF×å<¹mƧ?*çflO¸{@·Å‘ûWºw×ÝÖçKÆj{sS2 7…ÌóÄìYô“yÆÑÉù_În‹á1«(4ÿŠdÑ„šŸ{dz?ã¤ìÏüß³¿% 6¬‹-™ž}6½QHõè5jEªww Õck©d{ú‘l@z•Ê“=xZ¶·,‚a¾% ™Ý‰¹£Õ÷ˆzFüHoØ÷växìcYö) j;—®¸ˆ …C_…2ŽCiì•'~9>†õ»RŽÞ…35œ÷i\¹5ëÒ§›kßí*c¯?òöÀÝ<ö4˜‚Š)!h2%?gJhT P3”ñs±„Þ{w 3ÿÈ¢z×Þ­ãu+ú¨Ýu‡ÁƒnÏeêZ\¬žâd‘–Þ÷$‹âÜHÃì†Q‰}¯Ú·s%¸ˆ¬º~¯:‘ËMí«d°†`NÔ„|d:žïzÃífׯY>I64Úgb#ÖôïµW€Žwê‹az»˜ø‡0½fCÌÛ˪ѩ’+TÙíu ñ â?{Û¨½´)&TÞÚŠŽâµ­ú*(þèAÅOUÌ4§HvWìšÃžú>ç|ˆðmù£xA·,$«üið–Õ“pußB–œ z¿ü ˜ ; endstream endobj 110 0 obj << /F7 73 0 R /F8 86 0 R /F10 94 0 R /F9 89 0 R /F5 47 0 R >> endobj 107 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 110 0 R >> endobj 113 0 obj [111 0 R/XYZ 42.52 737.53] endobj 114 0 obj [111 0 R/XYZ 42.52 712.62] endobj 115 0 obj << /Filter[/FlateDecode] /Length 2099 >> stream xÚXmoã¸þÞ_¡º _cZ/”doºíÝæ’kÛbqI±ê eÚV– ‰Š× òß;Ã!eIÎ^û!ÑÎëÃÒŽÇ<ÏÙ:úó‹óáizŸ8s6§Ã}ñÐ |æûÎÓÏÿrCæ'¾çyîÝ·TTVõøßO»'À£3 æŒ'ŽŸ°0pöŸy,Ì0wµ‚Øñ}6Pij(q&¸Î;ü€4Lï#gfÌò`CÌæ‰Þðe<‹\9ž„¾ï ¥äþ p¸ª¤o*T:fîŽxÔNÒ¼¬ª²ª‰Åšˆƒ¨Íðí‰Z ØŸ¸_Í~#ö€2OjWF·Ù'[³ÙxÂyâ>í2³”–MnôÔ*Ës"×Fà1S;KtÏÓ®‚{yàæ™R¹$úˆÖ”ÚÃ=£Äyc¬Ê(5%ɨ˽T;#2¶"#W4€üª W Cªm@UR¬/P4×K4V;¡ˆ?ÛØIDž­*QŒ#µ©5Š`&-!^)†'}‚²á¨O"N¥²Dµ žHÌV*Ê¥õ¤õ¶wÖ“ˆ›³ÎÁÿzG‡é•Nš¤X¯+À¢4k›¦Â#Dƒ¬0<=#'Ͼ¢±z³O1‚ʈ…Œ<8q¢ké2»E ÷Ë~ÕîUkqh,ž¹¦$TR5œÎï…G)E¦†Pë¤ánûmUÏÎ`nÊO¨ÉÞÄ=¥« Ë®©¼ ^yF8kMo5¨Kál~N10ƒ“pîëj Ÿ½µM“Ó¸V™2÷Új¡Ï=Ú¨À’íNjÚ˜—:PåWfdCI즬ɺóÔ’–„ÙOþêüü„ Å3‡3!뿎'Q¹z6r©šž ‹ÐJ`zBJ _~!ª'5îæu·‚o[•iøœ‰¼M™ƒÿXêa/C“B÷Aѵº Œí„ÉãÜ•¶N(‘‘’n*-kÝLN¶÷e›…)µ4~OìBn16èÕ¥”ëædзÕ…Vb:fm{ÔuEo([«òŒ1ºzø^ïî‘àE»3¼™DÌ€×w½cî$úþ²qf> "³%ꀤµ †=#æÄ4ky& g<†›ô¤@3O§˜ ÞµñÒµîxÚ\íætµ›þ@L·eñ 5E©¤‰µÜdEFECOl°sh¢)ÒÎ<M㇦Š™–ki˜~˜ÒIýW²k+w_¨Øp h‡M ]Þ{7— è…KèaË@Á‹žŒÅø¥³¨Kâ3‡…»ß\Jý|º«ªå£Tº„,pâ[ºlÝò– ÷~út3 Yôj*Ä0"¯Vâ0•ÜýUŸ-Š;ô6qF¦*÷&5« ÐA‰Ð§ º #e· 3>˜–¢ÓÜǘÉoÏž?hI2 .7"Ë ùŸ…û ,n{é§…&ßÓ˜n~ÃË^AYÝšk#îY,FßàïšF]¡WëÅ¢]÷AòÿëËâlÿuÚzV´À¿i©ž'Úa³–mìpµBLzÈ'ËP+¨]ÕµõŒN†²(ìa~Ý~¸oóØ9W&* &::-sk™Õ0DÚ‹ a{ížú¡ç¯¯¥ úuÂ⨋éEÀãaA4‘Ÿø£æþw‘VX–#¼‰làê• ›CDþ„píš³aM¤2ÍIÍè@WŠÑP°bšâ»º,¾>Kb³üfá #$½Âk0yŸåò=+Z÷÷ñe‹õC±†û¹2U—îºHÍÌQX€a—ÂïV²jwúìËu“›)|Hu¬¸¬–WgnÞçAûȧ+:íXÉïêåRÐrI/‚å’x àGm]øReÛ±ÿÏG=øQÖÕ†mª¿Œ.‹âr¹džÒ|NÄÏ2%"ð¼hô–5ϲª¡& tÏp¿©8…—U¦êáÖÑè³hL4ïò<3åD?%‘ø›¬Vðú¢ÁYÁ+WÚóÖvL}¿±Uª•Í(Ùõ{Pòf(Êt¹|‹<é}“Ëz¼ÊGŶîC¥UÜ€}4¡JÎ’Þuà'ÒÕ¾«znàã®íóm «ª}ØC¿»}¸ð€z# NH}™¹ã.Kw¤ºVee¡ íeDÁãÂÚ‘¡’á­$­NPÖájº­Äawb—ˆ¦Wê8êŸQ´¨ºwŠ àfÏÐ0Ÿåæ7âhÀfa•°ä2¾=/W'üÏÝ3¤>² hYJà‰àã©HwU©*«ðWÈE§µ«ŠBÙ×k~z 4ð>X­êh­úÁôŸŒƒ7ddß‚ï÷)sñWêðn:=leåMySOj|=§å~Z—u„LO!´Ó7Tœ$~ļÎÏŠvÂþ°xþå²Ý$̧Ë:º†¡ûy< ]CA‹‘þÍ’Çó™ûS³mjE¿6„ç{p÷£8t#cÞïþ N¬” endstream endobj 116 0 obj << /F7 73 0 R /F6 50 0 R /F5 47 0 R /F10 94 0 R /F9 89 0 R /F8 86 0 R >> endobj 112 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 116 0 R >> endobj 119 0 obj [117 0 R/XYZ 42.52 737.53] endobj 120 0 obj << /Filter[/FlateDecode] /Length 1329 >> stream xÚ•WioÛ6þ¾_¡( §6­ËWºK;K¬Fí-æÁ eÚâ"‹*IÕÕŠþ÷Q O¸‚òM¶Ë7v»NKˆî9ö¯ˆ ëów@=o ¤Ïbÿf£Ó°A[œ Œ-%{E)œ+Z0‰j–ö¹Ã" 5û...Nsñú«9äY·«¼þŒÅn´™ä2f 8|ÖN Ôrx ¼×8 ãl£áw ؉r¸´¬0×kXqsbEY˜:ÐA~\E<ÂÉ3«jPE%i¯1·1~Fu܆ ‹<hHMI–MáXß…’˜éÄl‰ŽÙ&yeÑŽµª(FÐ@eŸÅ§1: 1†"žQûO0Î;“Õf˜¹¶ÿ(ÎM'o(…ù±‹ B‚ï)¡d®É¯¥\Þ­ÂXf):Hfê/Ð/R±(ñS% NœpÍ&¨3<ç´±ˆPÃ%éÔ‹^¨Ù òˆë4vSÇä g\ k4\à›f¢³rX ZÓDOí1’kƒðºëÞ‘PˆëÎd§¯æÚY´0VŠ|a8èµÍp3àLÍðý˜!Ñ5Èöe«fù4&kI³ü‘×Ë™7Ë’ªh_”46€«À'ëHeU«ŽO5œõûE]·™6è€yt”©¢…ú:ŒPø\&Ó˜³Få‘.ümƒ—C¯Fh9§IvÜà ÌMymIÄdfå&ÖDê—Ó3Æ ³¬Žº¾ÚÈà.EFÞ¯ÿAÆÉK¹´ë¡Ö)§í*Â*:ø_d†ð—³Cªü¿=³êè.íW³|®a¶a^ª=hÙjŠ/†—_—?Ë'”®æˆÏåÄ(¼ëêªèÌâ‚ÐöÅäsZ`Ýì™° ê‹eëŒaU/ lçm57ª¿~Ë!ÔÕ#Jv<*ÝQ÷¯®_Š_MKÿ[þQtxí¡‰œ®l!SW°˜8‡Ñ±½ñ±ê£â+§—ðIׂ]åX=~®œ3oÞ|×Í „}©KáÚôŒ÷ˆ?ˆ¹¯ãÙÆÆµNn£¸/U2….Ù— ´È9X5v¢Y¾úón2þ0™Ê¯Ï„ïòÒ@^ïyÍ."{+3uüÕ¸=àÔþ²ÌùÏ:ùë ¼pÕâÖ/–ã^ß+—Oßl/h„o¶Ð~_üê›gq6k =[ÒžýTÐÅ¢Ûò†6׿ýô¶âf endstream endobj 121 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 118 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 121 0 R >> endobj 124 0 obj [122 0 R/XYZ 42.52 737.53] endobj 125 0 obj << /Filter[/FlateDecode] /Length 826 >> stream xÚåW[oÚ0~߯p«vJ(Ií\A]XK«U¨CƒÝ(J©o°Älͦþ÷9±¹ÒN•&mO ¶ÏåûÎ9þ€*„` ’Ç%xÝ?¾°ASmZ ?‚ª¡ ©þù@ÒU$+B(µïÆxI‰ï…ò¨Ú}æÁ?€¢5UÃÈVu ,€Ñ€ª¥‰ŸsÐK4@C0›ªÕJ¼m$LW'+¦fJð$q­ #ÏÂ&FìÐ}í8Ù|ÑL—4QliH§ÜA7º˜û.uZṿº™ã¡ä哬)÷לóöÙ»öE怂jCϸ/f³EÂŽÁG;Ì×kŒÙ&göFK¼p—C‰xC™Ã¸M²æî­ëÏ£an‰âÅrp€œ[²€#ncJ¿×qòZ6$™ðí¡t@¼åŠò_§k¢œkßé$¶ùãú}§sR&ÏC\ƶ ´7ö½ï8 Î­n”F®Çi×EÚC9Ÿ7#OÛN°‘IC٫一áeBeŠ»ÝC¦"T†Ô¥dÌÝÎ}oÊßR°s¶½½ù‚Ç‚è‡^4ª±¦‹ÄGCò—‹©ç8æg ‰l) /€ õð·öÆØ9›áñ׸·XEÒK»Q;œ¦=oƒaãîôY‡² ?¨ï·ï– Iq¸"um¿0efõhCßWuT (åÔé`oJgk8ÜçÞéCæª]ðƒ;_¥Sæ6>ùÛ‚„ —Žgû[o’+»uâ)H"ú–™óÆàW›DÒ££uÌõ Ÿ›ˆLs\bú†Í‡à³N¶–︖ínÔaMœv•¿­£ô û©tÅÂ'–$×tF±éø/Rœ16,xŠƒpWÁŒ\Áò7^o¬‚Þd(MXi…ñãÉb£=ZlŒµØTˆTy®+9Þ„àlþLnöŠã#T „ªBJmö×t`}{§hÉnXÛîÓ…ôó~óÿam¡Ù*²“l®TYÑu]êÊ ]ïã÷€Lg²fK,OdY͆ÔZMW!å'4£.^ ‚2NÓÒ%[¤÷â7a‰aH endstream endobj 126 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 123 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 126 0 R >> endobj 129 0 obj [127 0 R/XYZ 42.52 737.53] endobj 130 0 obj << /Filter[/FlateDecode] /Length 1006 >> stream xÚµWm“šHþ~¿‚óvS°¥‚—º®bÎÄè–²—K‰E±8*†d·Rù‡|ÙÜ–ú ˜î~úéWN%‰[rÙãwkÕ{:×[MÎZp5¥%ª:§È¢,sVwÊ7DY¨µZ-Þ|ôP„ý0H„™õž3- rßr Y ·áTC› û\s“ ßà †¯7DCæjT¬føõ!Ô4Eãmþ÷»§~€Î y_l>´[Ñ÷Ì¥lˆFƒØJ±½{rþíš±ÙË´ßfZhhLÃŒcg‚ðÇ~°´éÁ£çüã®SD$a\­˜ò0RW*ï‚Çý—¢ÀCð2ŠëÔ4Þ0Z¢8©ì¸b1Âi òZ=pûqSß·Œp<õgà㯼 öc?30½’Kez“E!Í~™õ†":$é»@Ô_¯Æß(fç',5+và±G8gBs4gZa.ÝDþí˜~‹Ý("½Z…χ”¥=ñnŽ!²œNûPš—Ü–ü?ðÖ)ÐSùŠ(ÖÙAÝ{Xˆ«Ê~×½há$þ&Z£‚áÖTI¾Ö$0 ·HÖS‰û(v1‹Ñ™‡× Jw‰ö«’`ûÞNËf†¥I©ìÒñ/"x+7.B0·SYRT6çoá‘g}FÏtq¹¶ aº\HÍ øâ‡tA½¼k Ì_CÊK„=;vÌÖÁ‹V¶sF~äRF"²~ñÂ.'¡Z¹N*ÕJç¶·ö€g¶”m>±…?¯Öíüï—ä <žÓ?¶-¡¦*’DXíÒ~A p(¹QºÑÔ5þ™dm7äÿI´=Œ:„§NUÏÊ3G¦8æøÝýGsHÖµmžÄô\i*‡sª½Šì¤ÓïËéiLò±œ¾ŠæmØ>Ö£'ñÌ¡ÏÓ£·}«3º?^|í4ª9øÑ⿊¬9ìŽzݶÕf€çe[D—Ï1X½þÀì Fó"t‹èg£;º3‡Ù[ðóìŠ76ÛÝ‹‘ðó‘˜æ‡‹‘ðó ųÌÁà"a ~>²ŸÆ}ër#–£—Fl÷†\ÓeM” wäü ¿%ïÝÂkº¢‹2ü+5(¼ÖTøvºLò·°ÑPyE­Ò—¯H²DîÍ&¹¨¿áìN0>{WøOô=öÉFÅà1£÷ÛOW‰ endstream endobj 131 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 128 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 131 0 R >> endobj 134 0 obj [132 0 R/XYZ 42.52 737.53] endobj 135 0 obj [132 0 R/XYZ 42.52 172.02] endobj 136 0 obj << /Filter[/FlateDecode] /Length 1990 >> stream xÚµX[oã¶~?¿B°… Ä\I¤n(Šƒ6q »É¢I»'Å‚–i[, µiúß;álÙNN·ØôIäp8óq®¤¼€·öìçG·W©—³<ñîVž&¸…, ½»ËÿùœE“i?û£P­)›º›üv÷“7» Â{ô¦QÎDê…)ã‘·õD°$rÓÊ»µ 2/s ¢„¥±7Åea”«É4ŽbÿÞWZ7úSg¤é;¢}CŸ‹®>Í/g×wó‹ïßM¦Q‚ì‹T‡ -°ÒAZ×ê²6«AØVu\«ó³7Nâ›îìühéX:Ö?»Ÿ|kåO÷ â÷úæîêæ—ëËÉ”‡qðÊh÷­)¾ìͯ³Ÿ¯ÞÝ|üWÀî…¿X8÷ìj~=»üWa,ý¥@Hþa Ìßx7{6»<eŒd¿Ô‹›÷~žÝÞÎo®_éHôh˜±,#ýÓÒoÊ#–¥–ôæO”,ü·oIì^Ò q§*š¥¢Ñã¦,64,žº1nM˶Unë¢wÔZ©å@4Í oÛ–•B$o¯Â`W¹‚±î#‘Gî¥,O‘"†åh­Å™åºB9Ss©î£8­QÀ$Êý'ZŠç8~ÎHbv 2a1©ÞNs$¥ÇØÇI[¯@¼Ics'”ø-¤)Ú†xèü@·w¾ŽÆäe´²s$àÛÒh! ôüƒÛïÄîýêt»}j]"Rpoé–Š¦¯œžÎ”6La¸tK³9ÍIf¬Jc*çZ¤~ G Ú®nZ¹†ë«s¹´‡~8pz´ Wà(doûôaTUØó‘zÑk­¨ `F‰ˆãF 9“ÃÀ ÀG ‚†˜ÖU³-C›Nm›Æå]¥Äê!b CÙ-ž£M"Àµ Î3¢‰`Ùn>DèžèÔ]ïØúeœç,IG ÀBLˆc cªSAÏp|„˜×r—W‘âífT(Qƒ˜2ÝgT³‚ª¦‘¬i‰€ZÝ`ŠÝFã!§ Yæ»Roȳpž…Mv¹ßbïG_‰ü<ÁêQõ•+ê Éè°‹oœÈdû²‡ø×§A[HwÁ"´<‰¥x¨z6^xj_>‚çö¤‚g~¹m«²( Í #û­»4áÜl¤!~|$EÑ *Zê''ÅI¥K RŠìUPèr,ˆ˜G=ax´ùˆdûþ¢ÞB$>‘˜µ2Ãï(+2>…®N/°úm(åqìšMär‰/åÖV½ÆD¢IY;°ž“S•CóòÔh¥qí ï`ú$©­¤Ë —*ܯ‹¸n@ÌâÌw…A+ÓkÈÑÜy«ÔQ©éÀÔî¦Ëýá«^¸ÛÅÒQ[<+½Ï©ÈI2^³pv ý¨:aKÞ¹'èÁ)ÏC[Sá³U­¶ê+šwF”<ØÕ|ðhþí`Xl»‘mG«Æªy éþž„쮸9ɶÿtŠ–¤ÛOçµþ9ްø0€?ZAN¨î¿tá[jìSM}r,Ò*ò”>äÜ~œÿH£©ÉØ ýÀïø ÓÏ¥<’·j*8?|ØË÷ç†Ö¨á8j#s_ uÂÈ’”Œ›Q3Dbg[ÊÓÐËÕ½?üÂùwÄ.mÀÝO\ôÒ]ʶ(}©íÕÖ*q}³÷ÑÖ•ñ—Bž1öìßãiÆ,ý?Ãäý/êÝx‡‡ôNø LÅ9÷?L2î»ñGër½±µ®AI’gþ÷ýÚ^ì‘#çn„þï‹N?PÞþ»ÿ: endstream endobj 137 0 obj << /F7 73 0 R /F8 86 0 R /F10 94 0 R /F9 89 0 R /F5 47 0 R /F6 50 0 R >> endobj 133 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 137 0 R >> endobj 140 0 obj [138 0 R/XYZ 42.52 737.53] endobj 141 0 obj [138 0 R/XYZ 42.52 712.62] endobj 142 0 obj [138 0 R/XYZ 42.52 623.66] endobj 143 0 obj << /Filter[/FlateDecode] /Length 1762 >> stream xÚíYëoâFÿÞ¿ÂÊ}1RØØëÖ}" Éq%$Ó(jªÊ€ÁÖÙ&ªú¿wvg–gžw¹«T•/ìÎî¼3cŒf0ÃЦšüºÔNƒ“ Oó™ïjÁD«s—™ŽÆMfšZpþ»n³Zݲ,ý<¯Õ¹§ÊªH²iYû#ø¬µbkKàò™íi¦Ç,®Í4»a0—Ó6ÕúR‡«™6³l©ÄfާÕŹJjuÓä¶Tbñ%'ŽÖ ã àñYÑ ©ÖFÛßs×>ÐçZ̰¡H93°8çЛ!š`áè>Ãhšd=DÅ0¬’ÙßG‡my›[ŸÃ=_T2-b U3,V;~!Iô‚—ª©›L»¼"° 9:LܶR.rœåóU‘Lc²å^?»¯á’†€½áúç:C HÜÊûǸÉrÒE˜U+"w.o:k#,Ξ4âû|ƒŒ$‹ÛÌ3)ŸHªm+0w×4õªy‡‹^ë¼ÝzíÓAÐBJð‰Poö)®ošg¿6/é Ý=ë ÎÛÝK:»ƒ›¸tÏ[½-12š.Í Z½«>^¿¾ØÓ±„Fázž£¿ïͨë6ƒöo­9ÿÍáhÞ´Ÿ Å nïGI.ž EcaÆžTç ±p_…qôYº œé^í³¹úzȃ«„±uûY$±IÖÍ'¢6Ræ“ :úˆÛU¾ N¥Z@ñœ ³œXj 0¨Oä¸5'2$M™åãd²Úe]dcñ|²ÓЪ¨˜©–9Ù;»ìd/e7L w‹!<¢Z’Q”•t]<Ür—;Ï q.xËX 8Á1\íi¼XG¨O"z¶ÃÈ3ŠX”ùò F¸lª_^°å~£–Ü ÖšªU‡Õ:?DËçÂÕÁÃŒHaTìZ#žûûýäGkƒ l’í6Îç*á±òJÁb™¤”Ú!݇ÉÉ"=Æ>ð ȆjÂÞ¶ƒO׃€V—Üm³×kvƒ»J<ý(Žè!Ú·1ϾÊ5î^ΫVïìhkž¶;íàn7•í ÛêS#¸¸¦†ØTó¦mbÐiùfл¹î·õÖ~mzXv;V¼±d&Ê@ü sUa’ŠŸ•&7Þ @wªÃ”‚”b‡‘j7£(yP±ÕcÓ|õýáp>í@(Lsñ+BáCéÙƒ;!(™¨g"õt´,Õ «üÍÄæÆséÛô’ßÎFŒ–ŽO£2œ’à›4©¶Ñ_¬M±,ƒˆ§yY­…] ÀyOåT`pÓ4ë¦ex¹A¿)^ñXO™ýoŽãä¢Go™Æßëê~ׄßrEX¬þ#ã¸?Äç£h{϶ʃ©-+í½G³å>‹ôÝ©ÍÌ'œþ1£ÙáŽþS0öÿdþi“y]"/Lœ«çS´½­7ï¿ ¯{¦ÃŒ­WôŠ ^Òoÿ@Üc¦§Þº0¸\o.¦‹R¼ú³lÛÇø7ÄÓu}_ÿLÿÜÔ\—k®ßеx߀o…Ѿ_þ* endstream endobj 144 0 obj << /F7 73 0 R /F6 50 0 R /F5 47 0 R /F8 86 0 R /F9 89 0 R /F10 94 0 R >> endobj 139 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 144 0 R >> endobj 147 0 obj [145 0 R/XYZ 42.52 737.53] endobj 148 0 obj << /Filter[/FlateDecode] /Length 1279 >> stream xÚ­Wío›8þ~J¿¥pB’î.=­/©ºíÖ¨Ínššj"Ä$V©À,‰N÷¿Ÿ_€Ýn:¾`ŒýóïåyÛ†c;ޱ1Š×q±øu66Î쳑±ˆŒ¡;¶GcÃ6ÆâêÑôí¾åyžù¹?ñÌ4H’¾åŽM˜fý§Å;ãzÁÌ a¹göpl€±í¹Æ‹1œ8öÈ•Ÿ±ñP¬21&rÞ?4,ñ⫝̸ô-ßš_Hξ™mI¯E{|ƒ¢•¢oPöâ’ä Z$oº•ão>~0Ë`*;!†i‹y¾ŠQØ·€?ö™<$‡ùå~–~}@!Ä™´ÄoDs‡èV­‰2ÑŠÑ* ÒÃoâ IŸ0¡§rNЍ´Dɑó²Öpì9ãWy Ý©šBr¼("XÚ¿Å¡-›>Pfü#,¾”'3)÷g1!©ì¾ -¬¹Àq^IÊŸoYÞß1ÇždǧöËõÝãé* Þå¹C{ ØŸ²Ë’}Õ¥þ—Gùà¹öd\ áÒ£ Yˆìƒ{ª:kˆ‹QFëˆËhŠð&kÆÊ’3±ÖTNI ^š½Ë‹ŠM÷´wÚK{˾Â`] _šË¾²Äxxªÿ¤(XÅ0«#hK[t$y£<Öèäî üÉÿÂrІž¡6˾&¡ˆ³Oo¹Ä½æ`¼Ài¯×Ç,6õ˜;( 5”—%ùƒ” J𡈬ð¶Q ‚§N'®PÈIĘ[/m”ãâ‡øJRB =$*ÿÊ!KNþ1­2ñ”V­¤Už–zÒ/íöä}eÙ µLÿýO3$4µ@K¥à*¯WÉéT“y*aÓõ/ß°Z½@Kõw[Ž bú=æ€Èfú𦠆6pë AK$|Ú´˜ûˆžš1`^î@… !ÁÖÍQÏè7¿¿[Ü-¾Ì¯óÎ*êÅd@™6)G<£ïp,«Kx"’ªLb¥Xc&¢j/BÒY 'j¿š±†S„sAL«áW[”'‡q¾†"È7b éõn{ø£½?±Â2p}m[í³R¾[ÕÄTó«Õ Òg1|CJ¾'u¹º~¸¼¿/nï>¾Þ“¥‚”rIK¸äzb­^熗¤:Ζù-ÛÂðyê¼JihžT.+a°LN9ÁëèlN9N?ŸTÂüϪééÌ ãz­¨1i(Û :Òçÿ\úSÐÅh_Œ8wMI¤¼Þ‡0á0cÙºÏq°S„ÓËe&¤O–;±]ïXj ð^ÓïM å†Ùˆ “c~cjÛ9/ð} k –;C·õ*ƒ=[ cMÕô% ÿYÕ!•’Dg8dÇo•@i¬ì«^ÛÖVÝ8¾#F?àÑUõøâ›¯³ºC®½ßïôë3`ý þgP_ 2Ò¹Ç*õÓ‡vÆíˆæNÝ–<$ˆ*èuKÇÈN2Žù×pÝ0Vªj›–­RŸ³Žó_J£ò ØFM U![ó˜«ÓŸ£$Óàöcc“5õ‚q;l+MÐkßÉëõœ_¯kWm´ÙöÙM›ÁŒFgóm¾Éù½ƒp‡§²áðû¨<éß/ÿ*žW endstream endobj 149 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 146 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 149 0 R >> endobj 152 0 obj [150 0 R/XYZ 42.52 737.53] endobj 153 0 obj << /Filter[/FlateDecode] /Length 1133 >> stream xÚ•Wm¯›6þ¾_¨&ÁÏy{αmùÈ÷­£%Yï׿>̬ZDÖú`yA„phal­ÿÜ8!r½ÉdâüëÎ'N•–¥ë3‡Tµ»]°Vk€™Z'[ éÌÂ34 ¬Wk:÷Q¨×ÜzZæÖ\i (ZXÿ<ZH^“¥@ÄS„øä‹¥ði_ìjVeôèza:±~ÙrÆå%(ç³eâ$.ªôP@zÁ‰ ÌìÀE§ŽÔ‹7þV"fT>7ð)q¾Œx=•|1—U)=’ÄY$®’o×%‰ÐßQ/]jÝ'Žý¸ZÉÅï>>þm'îÛØñ»öw>«ß÷eûÊ=õ“²2^'Ýh…NNhrIˆø7RöF®/aS9úT¬`ç’ÔK53.õTßÈë¤Ë‡žE)ótA·“Ä¶Ç ²ušÿl»M›²†Ô»´$rÌžÕàkS0S¿tY§Zi¦übû…>¨.óŒI¿êÍÒÃ[ž9šé§é+‘ü‹¯Ð4ÿs>"“Ɇ»Ÿh!@ß—Vž ™ÒŠŽÀ¡¾8×õyŸíØFر7Zt¬ó´í[ýFª䆦†½\Úc+‡—ÑuV$c¯#Ü¡V—?¶}Ó«EC÷=–Þ!i ,¤ØZ6¶"(üüRP(äáZ¼Ó(«4«MWßv¤dYõj?¥û«ê±Û¾F¼g{Ð츛œUë~¡*ÿ÷yö„Ø7¢C–+Mžb^q’ƒ#¡¤J™úzâQ¥´+öäª‘Ö§ìØº? Ð|&ãJT{~=ÃÊר\ó1´,BYìŸ*’¾@ŒÚþŸ¸½ˆÈ`ÙCÁ]Wg‰ÎŠ6õ„±s¼OÖ†“ì9Sí3URiFB}]öã4°.ºº³c]ZPj¨n‹†ÅC°*¨rS3»•Ðxƒ5z+äÍ/LÜ8î4vl´œ‚²Œ6Äh¬õKVÊÑSžÒ—nô4‡ñwT¾Í{åÚSQíÍ"–{¶ ’bÂPw¤äÄWÆ€ïì½@ÛšXvàTÒ”å ÍèJ x¹ý?VfAWÕjaŒ%ÒïÊ @­Kê9RÞ„I?Ü.€G á}t,H8’…÷K[n÷c}9qM´…Ψݫ”ªKëôz&Zãupzç-ßÅéÕ%ùÇ´V Jn¨i­1c½ïÜð:OSQ)õÈz\q7ü¼¥FfKÕ›À©ÊœŸÊó¡¡;è­eÃÆ Ï—|÷t€¾2-Vï‹ìŸ$‹Î`ià .´7ŒÀÍ„ͪ¬—´êºf¶Ê»O¾-MéÐÝÈ)øQ§ àüq÷$¬JYÉ_ÎÁ×—!o†Cäw®CíD{!ê^»”D0CXî‚8€›ö£Ày×ξÉdêÓ±¼>†Ã>Ž¢ÅÂù îhŸÜyàˆqÀïkSeÇg7˜;LÙ÷ÓF?·Ì endstream endobj 154 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 151 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 154 0 R >> endobj 157 0 obj [155 0 R/XYZ 42.52 737.53] endobj 158 0 obj << /Filter[/FlateDecode] /Length 1114 >> stream xÚíX[£6~ï¯@¨A 7C2Ñ´êÎîT]µêJͪ•B9ÁÉ ƒ€ì4[õ¿×`Ì@’ÍÌ[Ÿ Ççæï;>ÇA2 Ó”öRýøYz»¸ºó¥™1ó¤ÅNrmßð|ɶ Ë’ï– 0TÝqåOuê(9Ì2U·}å…ºZ|Þ/ˆWzt{f¸¾dù†cK‰äNMóÙÏXú£Ž2•¦< 0ÀTÒ«e·Ž¦[U¶«Lnª'P’ã.ÍXJŽÊCŽ‹åµn­4ßÔ""\R-¦l™Ú&GðsŠodMÔ:5Ýr Ë&³J‚ ¸@×õš°†ãËA€å~úÊc˜ï U·€”k&«M1H ?£‚ZrÃŽõNöMu"œQ­ógv(Ol@ðͳ"êljMD;ª#Pë@ýÁìy÷.ÑS›>‹pšï)äœaò–¾fyZ¦å1Cœ£I»fMóÛÆå ¤n^Líöíݯцþ& ‡„ø‚e”âë*o!æv³‹£ Q!Ðê„Ø’ ò7DÉŽ»ÞNäyD§Ðè‘¡&•­ˆ”cS¿Ö"Ñï!c´.2´`ܭ͸_Ò f´ÈÄd½Gå:Â%Ú£æ9ò¢fÕ1þýÓâã§‹ÕŠ·i’å¨(\Z+ÝDæÇujµûÙcÖ™¦«ŒIE_‘ÆwP‰÷… Ì—z™‹nQEcѳO"ÌÖúKðo¶ô/¥€´HKÌú4”sjàc:£ صŗ4 ©÷Ó¶òBh‚×A<Í@¥µ©ûÀ°gbâ<¸Pk– L¥‚aÞO¨ÚÛš1\ï”­â ¨WÕ¿ƒQŒÑ×úì®ÏqP xG1p _ÌqT%£ Ô!GÝøxEP¹2Jç–˜ã#]E„-PçÃ…(ÖI§ Pàê׫1}Þýò×oïé«Î{=@)â/(/»ìöGÆåU\VjèµhÞïoMý<Òd=‡Ük€('­J“Ï43m¹Ò–rÓ„ˆ]S– 2åÃv àˆ¹¶èeÆa낳=´Â‰—Ž“è™ÂÑ÷ЖÃÀZSòjEýë,ývH\hùë‡0J?Ýû›mQæÞ¯ÓCI®.kÇé–dà Ⱥ‡ìª3oÒÞߤän¤»ƒñ÷V[Äÿ˜NS<ëš´ƒEߜȓ(qúГg0 Ožf´Jú3Íúæ™F=4½§Mcpq³×p§…‰ZÍç¼[·¨±>},Qš‡(ŸŸ†Øm”Ór ¿'Œ^®—ïU/àÒ%€7xh#ꈠ:"°Ž2vÛ6ûø¾î[À0…ÿø\Àÿå·ß Û7,:N>°¯ «¯ / Ñþ^µ}¥ªÏ›M•ŸûCÅf¥a»{1-S%­ÃôÅrX~ßý.ã¬) endstream endobj 159 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 156 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 159 0 R >> endobj 162 0 obj [160 0 R/XYZ 42.52 737.53] endobj 163 0 obj << /Filter[/FlateDecode] /Length 985 >> stream xÚÕX[›8~ß_Á¢mdFàƒ¹tÔ‡¶ÛVª*µRSõa!&˜‰›€tšVýïµ± &mfwf´«yHæøÜ8ç;Ç_PLhšÊVé?Þ(/Ö¾ö”®²N¹Ð ² e)ë¿®†šaÛ6ø¬ù6hâºÖ äÒ´Úõú­òjMÝ8Ê-µ  ã)–m¤Šã›ÐEâß\ùØGñ_DÁ Å`ÇNåâ¦ÊI©9àûÀ í* Á;#U“&Ô.û˜&54{GÔ0K¹Q~§ªUÇm…‹l¾Ä ÿ~jEœçÕ&ÁBýñÛ›4Jã,/É÷¼|ñ:zþîÝû—¡öSŽˆûˆ4¯rSïûhú!9}pº#=š<5¼œû½ØTEݶͪi!˜|É+ÉÛì;™¨ö¢%ß$')»öH›KŽ“¬Hã¶›è&é Í"K¦ŠÅR|ªØæÕíT³]rYÇI’•Û‰f4)0LÞÃö ‹eªªêê–tQVvdKš¸iâ}7qA: Ûè–å¢êW×ú•JUx ©öÔZˆi§²2nöQ–¨z ÙÛòƒx7¨^o8º`òmI’¥“]y8›BöÌ{7÷Pd¥8\8‹¿ŸIÃ@!97áž&sü˜sc…E9ëüü@4Z½¾æ Q\AßãQÙTþ]'£´UŸ^ѦÏKødCg•†ˆª]Wﺨÿ¸#ëÔ¸œ¾"¿£biÚjpñ‡ÅVƾŸÐ½˜ï¹³ÑÃûOëŸÖbÃŒb kºn€¯Fà@ MÝÐ1÷³| - 8[è¬ì–Ãlf?¢l~tÙ‚G×43sŽ™%1ƒÌL.#ŸÞ7–î  ðÎ.†~ ¯’¯_bø'!øç­œÔß[+Ý™Û{nåtsœ•SàÂ÷€y‚¡öƒ÷ÖÃrCÁ¤á´LlžºUY?"y¥ëã]©W¡žzÒêÒµ4ÆÛTåpuJU×ÉÀ.O—Ø9(±¡&•3÷cZ’§¼?ôälW¬ ºØ>ôjúä0Ê”Yi„óÉHÁÍ2ȸñH V´®+ZØ­ìªó8î[iÞñÿ‡2ºw¦Œø,ÊèÞ‘2â;PF÷a(#>—2ºgSFü˜”‘ÍÝcø?Á7ÀãG"çîıMçÄ?qtž8â{&ŽÇ?ö ÏÂД~î‚á¿üZAX Z¼I–£ÑÑ4]žï¶;¶;lÛÈÑùûdZ&½ª]7À[ñâƒæ#ÐGì}M¶ý¢!t"¿ß~ç­& endstream endobj 164 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 161 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 164 0 R >> endobj 167 0 obj [165 0 R/XYZ 42.52 737.53] endobj 168 0 obj << /Filter[/FlateDecode] /Length 1076 >> stream xÚ½W[oÛ6~߯ЄÍ™u÷Œah³fXÑ¡æb¢@-Ê $¹™[ä¿)‰ éÄÚ=Yæ¹ò\¾Ã£˜À4•½Òÿü¦¼Þ\^ûÊ ¬k¡^Äy^íBfŒxê”øe–‰«××Ñ«wïÞ_…úƒ˜[ìW¹«½5cºñ TR ˜4»™¼xü™± ÅÍ´R¼™±öG2݈<âF…L1kØo’žà,²dÎXÈì3Șs¶2•*ðœ\oN8Ï&‡G­ËkPUÕPÏh$Õ¸¹5nÔq°qáÇ F˜ÛI¥maÙÀµù»MhBTÖ “Š¡éd”¡ÿT âòšiúD SWJhcƒŽ´9ö‹"´ŠU9Lþ°tŠò´ ¤ç¤¤DK·z{Km.­XN«ŸZ€±Aqþ(™êO78Ýbä~ÄO¬üÈM‰þnï?n>|ܰŽÿïsßÞZ'æ>ÍÙÃô‘Ü`=N:›¿ôü#‘{ñÃÚpù“ó©ÙÜ— dïÙ|î|”cš‰¼ÜX¤6ŸŽýðF•¨ð¤î?/Ùà¿þýï?ÞÐÏ%k… µô«»ËÚA°ü„šnHý½ú…åáR èg€¿÷ðwÏCUYþHÊpp‚ ªä<¸ Ø4vx´c,ŠªCWº¨-ÄŠˆ/!ÿ¦{âÙÜÿI„.~€SÍ‚üMáéTs?±ÒM+Æ©=äÛï}Þ¸÷LÜZº-/}è“Û—‡ƒacžöòQïç–Ë[¶™ ›ùlKÏöw:^Ò ¢yÞ*Ð^öò("–c°šx—‡¦gkÐeþ}÷/°¸~¥ endstream endobj 169 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 166 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 169 0 R >> endobj 172 0 obj [170 0 R/XYZ 42.52 737.53] endobj 173 0 obj << /Filter[/FlateDecode] /Length 936 >> stream xÚ½W[o›0~߯ðÐAl¦=ìÖIU¥MZ¦=” Ñ`2$n²*›ößgl'1…´i¤õ 0ß¹øŸs>Ú6Xþø Þ/^û €‹Xˆ@ä@Ç‹W:††åº®þØ»z×µa!_§Mk\/.À§Sã[&@ÏŽ] àÍmHüÌÁ7neæÒŠËŒ`õ¿=nåW•%†…ÖW´‹çqÓÄ›:nâ‚vÌZt›dEêYÙ ÜÙ²*ꆶmV•æ~õ&+ãfe‰Éý <è fÈæ†™¡=’æmö› ˜- x¡-»vz–?ãF¢În*S¼*nT9-ïÕͶ“Æm7’dëEïýx¹Í«ÛÑz'IV®Æ†Æ¾hù¢@õa]¶Ùª¤<ÞžP娨Öû€¾+ê£uÌc&}èƒ#_“ÔL 3iÍ:™P°¬ÊVÊ+Q›MG«&¡Í›q¬¶`o®º)õ7i”ÆY^Òß!ÿxàµ4OEf<è«öf}Låq£3uÏ3±é‘³Ý>Ì ÃŒEƒ?ky¨C#4„ëÖΨ'Eló­·]ÖÂ}l¶²Ã“” ¡Pö‘²RE¨F:4Š8Ï«e(õ΄†øùg½ïÏ£w——_>„Æß‰ƒÐ5å²Þpkæ~Ã[¥>²_ƒM'P­ä|t ¥VQ¹(_šÒ½-á;hZLeM°I:储Ò!ðʾn‡ÈvJå¶’U¤RO¬#ˆ#Ej,ׇ«4M3µ{¿f^]›Wšìž®ž‰îšÊ®4qÔ‘ ±«îj¯A¤B›èt*F¤@“E¤ {çnùN÷Ô&êl¯T¦j,,23¹Þ'büCÆ]»¾-¹]Á¹/¬>ØU¢´Õ^_±ŒãðrÉê†éªuW¯»ˆ—bÜѨ\¨6¹{æÿHÊÎ^8ûn2ÎK6œóÒÕ¹†/ß_¿/dµŸ>=ãË›œžd98=÷ Csí𜜚2‰²4qT·ÊlÍÃy *Íy +aþ31!Ç|1!OFLðAbBž˜˜à‰ 9Ž˜àˆ ?DÜ„œÎMðÓsòäÜ?𛣏 ~$7!ÿ‹›à£¹ 9–›à‡¹ÉÝ‹å;ÚÊÕn»°½Ü©WH)|èˆ êvktl‚ôwëպ߅ëz:òLq·D¶c³Z'$ô yßüjÌ‘ÎßQ÷Dz“­~h®wÒ¿gÿÂLß endstream endobj 174 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 171 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 174 0 R >> endobj 177 0 obj [175 0 R/XYZ 42.52 737.53] endobj 178 0 obj << /Filter[/FlateDecode] /Length 1068 >> stream xÚµWÛŽ›H}߯èE ,èáj`­}H²I¤(R"ÅQ†bLãAâ&À™õDù÷íИöÌd/O@Q]§êTWu50¡i‚ wàÕîê­BnÀ.®íÃl ZØýy­zP3ÇQ¿j£¶IÓh†í«¨í´›Ý{ðf‡Í¸àv]X>tlP70áÆæŸøLQpÏ…a òÛ¥(ë&IÓ¼:h†g»êäá©Mº¥ &¶nÁùóƒŠ »éa &µˆåŠ¢èÊõq‹’"iÛäÔ$mR¢»ß§yÙÅY§è×7úµ’W=Ú×eÓ¢®Ëë ¯æbO½Í«¤=ÅyªèÍv ç00PÑåˆë™3‡T¢ªÇè̼²¿KZöº^ßÖ£xÄÇÂUܨ }KŽƒÊ’®_®Ç?JêüRÞõýòg_¹¹a˜†@ÛÅ,Û0ðêþ6‹§·Ë”߯q–T¼Øw}‹íÇõ±oŽ}œE½Ozî"u Ã¥tpçÎÈàÒ¬ExÁú7+Ò"m+"1r^à Zœ˜±ÉÂÇ/»O_vìãû$²¯ pCò¡ -[ f¤Ír/I½¨ÂR¯/]”xZ³4ÊÄ$í 9O"/\Ž–èÓS¹cd¡Xoßê> endobj 176 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 179 0 R >> endobj 182 0 obj [180 0 R/XYZ 42.52 737.53] endobj 183 0 obj << /Filter[/FlateDecode] /Length 1014 >> stream xÚÝW[›8~ß_Ðnep€ÀŽúÐé¶ÕV•v¥FÚ‡a„˜Ä0H`"›t:­æ¿¯ñ%8Œz™n¥UŒãï\¾s‘ ßó}£2øòƸ\/^¯ŒÔKcc].Œ½ 2`à±þã Džå.—Kð•,)v;Ë…+€µ®×oWkwì^ê…+#XyKh´F˜ø^ å¶1Þs-‰‘H-Q襩áÇ!×bÓaË`žKü ±.l±þ‰ë¾.šš"±¯±X7…’t¥Xw¤»iPKÅÎ^pC}¦ÍçÚ™¶ÍM™—EÝ`ô)ã› õy{T!RRÜï R´¨g^f€¢¦t„iÏ6]»#ˆÒºÃ‡]B/ tÄ¡ŸÝÔ¸ ÷y½UwPCëOÈÖð]…ÑvÜï±’Ììd§¨E¸§ «­±©ûmñQJ2+³.8†+­b$¦‚ĺûqŸ·EÓt› ël¥hÉ,ý™ƒÁăKÝCEˆD!¡dáB›>ßt;Å\ä°o¼oG`IIè­‚3¬(kOq£1…{ÀŒYÞ&:h>tõVàÙ™ÅäÝ#bF^4„ÃSÔ>'¨ØjQOX@=ê Q ϦàËË×ù‹wïþzyÀšýÿAÈYÌtÓæe3áóbžT6=ºÀ‚|[IŒbˆ‡IšÂ¼ tg,4MÓ1§dåÍiOj\™ÎÕµsefà’3–Yï…øZXs}6Aàœ ºê'"Ñ÷ ‘!Î —o"ñW‘è'> endobj 181 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 184 0 R >> endobj 187 0 obj [185 0 R/XYZ 42.52 737.53] endobj 188 0 obj << /Filter[/FlateDecode] /Length 890 >> stream xÚÝW[o›0~߯°Ð&wȪ>´][­ª´I´‡R!š‚D ²I«¶ÚŸÁv€@Úum¤jO_¾s?ŸÐ5] ¨?çàx:>óÀD›¸`Ûô4צ¡˜~»†Ž&«–eÁ_²oA­V²jza"ßL/Àé”ÂØà¨æD³=`xše‚%°}]sMþ›«ZŠ|.Å÷´‰ÔêØ®¥`D¾Có‘¬:¦ ¸ÎIšäh^ý;0ÍË@FZ¢¼ óõòáQ-_§ z JAxW¤s† r„qô0b$é# k”jÅ·«Ÿ$ï@9JÜgpù<]Æ){pÕÉŠû@äƒG5}Í´Ûzý¦bÐS}Ø:c‚f·qGi–£ÇžŸ…G——?NžÁbû¶æµQ’¡œizØXöˆ¡·"ô<è»M!—œ-"ÌÖ ³ßµ/¹N4ÐÆ€J=Ó$II *Ãt%(ŒI‘”8Íit-ј2¹Ý¸J,†¯ùf[Џ/L“x(ºûIÞß>>©œ"ÝP}xœæ~ä+¦ã »tÃR¹F–©ùÓ¨Š]c‰¥¯×Ôæ~2ÇÌÐÓœ¬1b¨÷ücÄWå‚/²be|-W¦J PZ—V—_fÌ•a±.Wë2Œ²ê]Iõ ÎibH+AaXd´©%Ü*iFT>Uר“Næ G’ç¿Ý¨'l>Gå¶y(OÊ[Ï ŒÑ¬lG¼ÅìÀ¶“Ñl…¾Ûx“ÆÊ.ã{Ű•eÛÏDÃèîŠ<Ú¯2/Ÿ6&ZíÌhõ«V… )doZ$ƒæÅªÖóv3 ·êÂ÷<-Ó(K  sEb§ˆÙw…‹[ê[Â6î'w‹–°.q¸¬S1ØÙ‚ª}åi8×Z]Q omÁ(‹Z÷Ç¡w'•´’¥K%,[†Ú¿ó •¸¯¤gJÜ·P‰³'*q‡¨¤Ý^E%Î;PIM»IæmT‚Q”1#ûdâþdâlȤ±õ9:1÷C'CÂß™Pœ¿!” ÷eêp>8u¸û ç%êhb>@î{‡ózòØ_|ÔÑc{bT=ÃÑôÖÌ(6ÄÔØÌ¦›tF5Xã¼àÓéÏj:íLªi²é J+Àp݉ÖÉš”ì†iøB7t:ϺkAcÂõûôé1y endstream endobj 189 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 186 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 189 0 R >> endobj 192 0 obj [190 0 R/XYZ 42.52 737.53] endobj 193 0 obj << /Filter[/FlateDecode] /Length 893 >> stream xÚÕWQkÛ0~߯fÙ$Ž­XŽ½Ò‡¶kËJaƒöPã¦rbpœ 9-mÙŸ,ɵ;ÝBÓAɃYw§ûô>8¶ã€Ã98ÎF ´CŒSÐG¾íb€\ÛuÁøÛ5ĶÙ‡ð— !MV+³FPfNÆàtÌÝxàžÛ…¶7îÈ"°^àØ>Rsp%¢ PQ°g‡!èWŸ=Åbf#V†œÎ*çVdÊIBiòp Âöy0—Û;·ÿ-—Q`#O®c±nFϘ‘2¦$Éãl‘ÌHœ°˜•4+fFïÚÈŠRF&9Y¢Œ‹õâ†P£'º =N½óý,{$|Ÿø×¬·Ù‚åËûî/iÂJcÂãFð8+ú™Wò,¹i"÷Uä!²yz“Æ™¤ÌøzÍS&Ž~ÎÁ@fuZ°5%Òõ½SJÔ¬œ«I¾œ&¹Z#‹Õ’ò“ÕN9BI…/S‰[¼\—«u'yeW’¸B¢¹2Z–ôÅÏX,'E¯9F­Ïndò®‚ñdCOÏ¢•nswŠʤ9cø9)7s$ŬœËùtI)™–ú7.î–Ù­ÜöJüjLЙ£²Óøkmƒ¡ukäÚ4« Ôµ^Q.2Ÿž3êUPgÄoF+¢®Ð¤„zGªX•,OâEÕò]b¨ëÿ^de–ä#õ6I½²L帢ËŽ"Sð :ΗÊPÿ‰‚~‘ÂʪÁ±4±„ǧn~U%•&Y^ÇÚ{g•E‘<íµ1¨ÁêÕæë‚e³¢Fƒ™›ôh¥é÷™"»^ýV¹Å‹dDëÍéaƒ$Íg—ƒÖs©žQ†H°Zß4°"xr|]^þ8éò…õ'Ù³Gº—6k¶Ý_'åö­þV•Ћ}'¡À;…ƒí²£PŒ¶ KÛBßC(Ðÿ Ü%,}g¡@¯ …ÏBÿU(*m¡ðÿ.xg¡ð?¾Pà„‚¥BáïC(ð›„Âß*I^ …dÉ+û^„Âï ü¡ðß(xg¡Ð‹ýcvÃ[™Š¦›}]äbÛÑ:»z¡îíôRY ‘íJIBo]ÇGðh=[³²ê(=ˆ¼žl-‘ãò ®ï‡!¼PíæO3@PÌQÕz"H³ÙÜD,Õù>ý:³ endstream endobj 194 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 191 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 194 0 R >> endobj 197 0 obj [195 0 R/XYZ 42.52 737.53] endobj 198 0 obj << /Filter[/FlateDecode] /Length 876 >> stream xÚÝW[kÛ0~߯fÛØŽïvVúÐv]Y)lÐÀªbÜDv ¾ËiiËþûdI®¯YW–u£äAʱtÎw>éã]Óu:œãÅì³æÚÜ‹ئ§¹0 Í0ÀâÓ•èh’jY–ø]ò-± 7I5=•Xº^œƒÓqcƒ; šsÍö€ái– 2`ûºæšüo .iøÑ ´Ù†î’¹Áñ½û µ±]1 endstream endobj 199 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 196 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 199 0 R >> endobj 202 0 obj [200 0 R/XYZ 42.52 737.53] endobj 203 0 obj << /Filter[/FlateDecode] /Length 908 >> stream xÚíX[kÛ0~߯fÙÄŽ-_³Ñ‡¶kËJaƒöPã&²c° 9-íØŸlɉoé…ÞÆyslËw.Ð5]1¨–p0»`¢M0€ŠͰ24ÃÓ¯ÐÖdÕ4MøSöLHÂÕJV‘ 1¡òåôM™ ܰ}Íráj&°<]sø›‚óÊŠT>դ茞ž^¸Ûd‹Ê[¶>ÖŸà¢#Îãb!†á’<+šE±UÑf­ö߃·:#å1 ÅJ¡œ‡Ê~2C9oÊPök2”óCµªb€£ìwâ¨Ý¯JKö=´ä<‘–ì×£%ç™´dï %§MK;fÅ“ˆÉ~$1ý%D´ÏAÎ?ÁAöŠè}4„Þ‚†š.¼0Ùe¢—9+9ÿÏJÏ;+u £IFÝs¼ê¶¦7Nòµ >Ë7o Ääjɬ> endobj 201 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 204 0 R >> endobj 207 0 obj [205 0 R/XYZ 42.52 737.53] endobj 208 0 obj << /Filter[/FlateDecode] /Length 1016 >> stream xÚåWÛŠÜ8}߯&lãvûnwB2Ù$ll û0Œ§[îøÒHî ɰÿ¾².m¹íÎÌÂBòdY¶ªN•ªÎ¡€çzØþx.×Ëw)X¹«¬K©›¤ ð]ßë?¯ÌصašÿXYh’b¿·Aj"B­ëõðvÍÌDà,‚•¥ÀOÝ05ˆ2ÏMùZÏÜK2é%KÝUýçˆ{!ˆ"òmk‘ ÍCCñ®AÛþ=6qÓA U¨FM—7‡ú‡û÷˜eF ù¥Å[aÁ†VAHñÕ Iñ7”s+ýjt:–§Õ/ÂB³ÅuYÐnb¡ÿPãíì>­Ú;hAë%·¿27ˆtˆÿ2÷èžÔ¾ ››2/ \5è4ß\¾Ë_üø÷›ïØû‘›êVlZ¡FDðJ Û*[â·Þ—ÓLÚtdš›Û‚ˆµ-ò›<½»{Ú$DÃ0c‡ºœ ¢ÊÃmŽëb‡ò’æÍiGp³3œ+ƒ]·ð?¾rCÜšŸ¹Y {Sÿ«P y5þŠ}þ KÆü‡>;Æ5ÍKÜä+´> ×â§kh!!±®Y‰®1úËœJKãÅKÂ4ãË¥ˆømC ëwòY$WÝ­\Tí¦¨äª÷-aà”ÑÅóÈiÞºý¡Ë‹ª?×1,KÃ¥²n±…-êûMÞv_MΚö3¿/pî, ÜÕè~ç"®V‹<5ÀT±¿GÝi˜¨Ùu·b½i A›N/ÞDÀM¨Æ€M­VÆt"œ unŸKÆ„9NÊïô˜ª¤¹ýG&µ ­ûc¬¡^*Éi=8‡(:òª0-ÛÙ›íøSÚ`ñçRÖÆ_ îpQaŠ`™²Bí´¥xîI{Ã’KeÖ–So¸T<¼ªymÂɪ¯=Å@÷óE¨ñ¨òr®y£ªœ‘’Ô£ø‡ô(9«GZ=ND!ýÆzŸÑ£ä{z¤3ÆOÓ#..OÓ#.aOÐ#ÖY2Õ#ž©_Uˆ’‘ñP²ùgèÄ7|„¸œåücÞð{Ïñv†õEã*U¹Q¯=°­£çL·é\ 7m½g¼HqÛÌ8רnÒÿ£ÒŒHlÒû‚5êØ4£”€ãºÐBuæEæâxêÌY"¿PÉ׈xR*¢nd,€=«ŠEåñDc)„,PVÅù¦­u÷¶f”6–™dTî?AY9n-‘ñ(K½Á„•Ù#G¶³ƒÚ¨´£!½¼¶‡ŸŽ¦‹Ô]ONÕ†O‡!øx‚ Ã~Ê~cð§~ Äxwk±‰˜5‰Ÿ$«Ì|}Øh'þ"G.<ßcƒ³ï%lJ|üÑ&[B endstream endobj 209 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 206 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 209 0 R >> endobj 212 0 obj [210 0 R/XYZ 42.52 737.53] endobj 213 0 obj << /Filter[/FlateDecode] /Length 1109 >> stream xÚíX[o£F~ï¯@H]… C¶QµÙfÓ®Òlµ¡êƒ±,lÆxT CÖòFùï˜{€ñî¦Mö©Oæ\øÎÕ£X¦e)™Ò>®•ËèìÝD ÍÐW¢•2¾i{ °MÛV¢_¦šgêcÇq´¿ôÀѪd»ÕÇ`¢Á ë³è½r5®²#r¡éN{b:@Ù(n`™>`?s宵(³â…¦™ÀtZ#0Çð¡ÕHxÀUƶe†^ûn¹XÍW Ê ø9ÖÞ^¾›¿¹¹ùð6Ö_·ÇÇÂyŸê¢|לˆZF8‡…>ö€«]4O#&Ñg8‚9ÜÀ¢ÆT%jáŽ@¬-×IEéQ¬S"©ªdÏ\!Ø¢ÍǪªj¨¬çLòVÁ<Ás\W¨ÈTc:3¦j¬]¢"©ö±~GÙ3êÊÌàn:À &T]ƒ&êPQà V­Fõ|JÌ´‡íÀ €è×ÙˆúNÀÌтқ{\SêöCÄXeŠV{J×kH‰4©JQ)½[£åš’ ˜—E†™XÙÇË mëF®õÌ5m "“'EvŸdìðŽ?QžSŠ€Æ`/RJ,×pùwωtV3w>!æ.{Ôû-Ü$[Å3!‚eH"D’>¤Iÿ#Éó|O!ï„ý.úøÛíµA¼)qsu{ýÊSâA’. l})â&ydèô‚øZŒßÑ»O%Jå±v_`”0íÙZ–›m1FeÑwcÑ&Ú¥4µ\`:¾þîɯè³heɸgC>-ÀX`õ☞3ÌWWÃÉ ÖûAÜË‚—"O;×N17.Íkªˆ¸bŒK ŸL>Yˆƒ%ú„V±vì(ò–¿hæ­ÒNoi•X! %=Kâ11Ù;x²«uú©¬uð´Ç0_§Ò§—5¯c@žâ,wl˳Ým4ø»NÂôòdx–ƒ{|…q"¼;5N>^ÿùûÕmôuŒOêÐ9Áï˜hûû !ÃPL)Fª¬LUöýê°P‰ö˜ýâ¨Ü ͸AšY#C°3‘¸2—A>4ÂÑ'6ª’É4chLUe Íw)Ú`ù,ò_heÕ;·Ø×°¬RXuK³ã_2ëÿ!vrˆÑ4¢g÷oQf[ù4ÿž0j©Øó\ï»\ICLŸ³Ï$ ¬\KØ”J¸8/w}ö6ISRI²ÀŽÀ{‰àÕ¡½Lmo&Qö-«e¾zÕÐŃwDñ1%‹…÷­‹…ÿ‹¸®Šå–ì @ ’DmÖüd{?·Ä¹íò9Û1sÄðpÞvÏ[zÖ±oÉBñµ†ÖêØküï·×^/Ë‚ÁÎÿÎ#º2¹R±.Ý.ÿX˜¶P™Gþ¡4eÛ‘÷…eËú²%þiîß+Œ'¶gZÂÍgð»ñƒI€‰iÓݸ:éé–´7÷Y»\8ŽK¸½Ú–m‘ú~jïÙuÇz´–ÍÕÐ*”­uh5óï‡ '»D endstream endobj 214 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 211 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 214 0 R >> endobj 217 0 obj [215 0 R/XYZ 42.52 737.53] endobj 218 0 obj << /Filter[/FlateDecode] /Length 1059 >> stream xÚíX[›F~ï¯Yj–a®ö¦«*i7ÛFí¶ÊRõÁX6ƒÅ°±œhÿ{‡¹p÷vÓ›š&O ‡3çœùÎ…O Ý0@Øã¼ô/^y`¡/\àÇÀ6=Ýõ€ uÿíRqtU³,KùU[Jªfz *ˆºò_ƒkŸš±ÁhæB·==Ý2ÁØsCwMñš‚;æeæÂ‹åêÐZõÙf^˜5 Îõ¹IÓ£òÉd2›T®qV¢aQ„§õ1Â{2™±=Ww˜úRÕÓV&T»Z9Ê6ß DÎ3ªÏDÍÇ ÎÂâ´Æõˆ·@åßîÊg _Ga o¶îÁN|˜­ ”àwˆZªÍ£íQV’ÚqÛææT¢¼ˆP1 ‹.I9úa_;"'i~~8„QD=NV³åjÅ ñX¦>'Ønâõ8ÂkO.—4lç 7Sîå›—¯R¼áëý=¾oò…(p|âër‡HùŠ´@Éò¢§WÃÔQfáØ:ì„sÜáíNìBiž%DØÊ{6ɶÀ‡RÚéÔOfÉ}˜Å£|â4嫉ӅY$ l‡¶¿õ¤(KJÊ[,Î)åé€öá¿L/xNh66m!¨/xÓ}Iû,=ñ ¨Pœzç¿ùþöF$ºÎó×·7þw²tßóGg_…w SnyÈœ+ƒçm¨Ü&ÄMÞß³É?8DQ¤ ’osýÁÎ@¹ÏN2õü·†Ç 49:ÄX0uËm£#ÏeŸ…¾/âócLZE6”óÙ22[®Ï@ÚŠù1"ÞãhDZM§¾XŒš@}ÏKÚ´tÇN [!aŒÊÓ yòL´I!ûV4GçlDëfàÎj0F TfžâÀò=¢Ò@UÏ™%tVχŽ1­ŠW¾ºj§l*sÁ…Ïžu3tu%›r<§m‰Ô`ޱ`…£fXŽÄDÝwÔx8#Ǥ¡ôyh#ªtÀfÛÃ)h™Ñ"bUót¾f‹KhêH< †µ>´/ÙzÕñoŒ¥‚þ…â§z(þ’äÈ!(gçµ×Ÿ8ƒviÈñ"ºŽQÙfu&¿uZ³×‘C]Ù˜rÂå™ü%¶†] 6ÁhŒ¶[ÓîÊ›Þìˆ[ÍÙÈëÓe÷@†%é “C÷ëon~ùñúÖÄ\C謶©?Aô*ò?æzãÔí®7NÏs½ægø׋ÉGÁõœ¿ë¹Ÿ¹ÞY:“ÿ<ד!~8׋Ég®7NßÎr½1bø‘q=çÉ\ÏýD¸žó¸žûïq½˜|j\¯nͧq½Vs>‘ë9}®×¿ÀÓ<èèFë O ä%^sUXï0=zÌðkqYøsuYع8ÄÉN5=…¢]w1W^Ü'Œ>T¦= *è†K׎ˆï‹ßìãÂÐ endstream endobj 219 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 216 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 219 0 R >> endobj 222 0 obj [220 0 R/XYZ 42.52 737.53] endobj 223 0 obj << /Filter[/FlateDecode] /Length 1060 >> stream xÚíXÝ›8¿¿Eº ¢Ä ²{«S{·Ý^u·Wu©ú¢ˆC¬#¶QZõ?ƒ ˜´›ª·êÃ=aÆóåßÌxFVt ëJ¤”Ÿ[å…{ñr¦ÌÁÜVÜP™BH0 Åý}¡" MMÓTßkŽ©R¿×¦p¦bšiK÷µrã25–r`rs`ÍcL¨ìËÑ Åo¬Ü—VÅVìy¡~Zl[¥•Í:\…>‰üÑS{ñrõüíí»¿nî\O»* M }ôRù,èpLNG]z‹4MFÎW$Éq„©O©\²ËVa6š”bº¬i¡M´Ô(VHݤ»=ÅYFÒ„ñ—¤fsMŸW$`f<ñçi|ï>§$‰ø:ðs_X³ÀÌh¹(”Y*Ž3ò3MµzãNò¬6,ë\sœÒÓ¾[ì|¡Ÿåƒ»ÂÙz§‡þÆÞfq´œ,–K~€)? 3ã'(Y€L±—. ù’[ øbÌ5³€ÇdÍ×»‡LØ»ûÛ¤4 ᑯó-n`ä«Lâ°%›­ÀÇieB,íˆgJöy!WzÖM®ØO¢?̇êK☯",œô“@äÆoþé‰qåÂD¸+>ùqwþžÿŒ/8œ ȹÅjÉs^}?³‚‹<'$‰t¬HÅÓu .Q˜¶Êë¤ÿ]¯Ÿ>•×§}âxC ³Ÿ‘–šù!νȦ‰ˆ!­KDN—Ý-L¯šBžÔƯúwL…";švK ½âˆœëúZ>à¸{¢^"—J…hS8Ž0…-6n`Àf²ÃÈ]ÐÙºÕ{7C•ÕŽÃÉ©é¤FËOF¯Ê`‘ †ŽôBwŠj¯•ýÍ Ê/ô¦÷FOÞšÛu–'l[èñmë¼®ÁûòÓöŽ$¥¾º­¶˜ëìþÓn:<î”ïîÜ:íµ£ô 社¿Ô¹Ì÷íŽè?éŽWŠdâ\]¢;È»â =j1rvÉbàü!ºµýõnÝF}{, ´üƾΉϞµ#t}-às<ÇÀ)=v °; ÇOàœ&›= k@&,‰Ê¬ùÅ@¿–‹KêÚdK¶Á°æ7¬Ër½lÙ×Ï?xAþ CH½½I“ª§Iw–§5XöÏÝ(•«ÐjÓ›2l‘¥:lèu!ž;ÙçOFèÄddŸ˜ŒÐ‰ÉHL“ÁgŠéÌ@@—**BõT!?ˆ 8W ­±û^·¡úü!*GÓ´ThMøK Ô ÅÞ¶çsõµx=y£9P-×°xI*%ÑVƒŽš ÿ~ú*;ÌŽ endstream endobj 224 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 221 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 224 0 R >> endobj 227 0 obj [225 0 R/XYZ 42.52 737.53] endobj 228 0 obj << /Filter[/FlateDecode] /Length 1084 >> stream xÚÝX[£6~ﯰº‚ˆ0Ü ÉlGÕn;;ÛU;­vRõ!D † ˆ0³Qv5ÿ½Û\4ÓUiŸ0Çö¹|>çø“®é:ˆ@õ¹ogWï\0Õ¦˜…À6]Íqih†f?Îe¨)c˲ä?”‰%çþn§ŒMWF9V³àvFÔØ`ÆæT³]`¸še‚-°'ºæ˜ì7•• ˜0+¥Ücú)­Ì•14mYŠÓ¢Aymw9Â8ÎRI¥¢fr§~~XƤJûó:÷PäqÑqà>Ù]:jk®A ê•Ä WfË(ÁñgD4ÕêQ‚¶(-pm¸­su(P–(ºÄÛÐÇ…pb[:+ã$Û'v~‹ÒB/4€1À2µ ‹`½ —Ëù‰Ÿçþa¹/.q(]Ï%Iª¶mb¶¿Q?¼}—Ä+:Þ>bføþ×eAè¸Ø O:Â-DÒ,ï­«1ê,®Ü±5ƒ¹+wö›x½a»P’¥fº²žN¼Îã]Áõèí?ýˆ-Üóoœ$t!Ÿ,»6hýgÏ@‚Ò¨`®|ŠYœìSvhëïèÏèŠ9Š)IbR*SZ*ß’êH4«°Ç¼ßÊǼÎÃ^mÓ• †ãL'ò›Ç¨âå ÓVÙ@7t…ôyÝ!c—ù÷Í_fž endstream endobj 229 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 226 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 229 0 R >> endobj 232 0 obj [230 0 R/XYZ 42.52 737.53] endobj 233 0 obj << /Filter[/FlateDecode] /Length 1000 >> stream xÚíX[oÛ6~߯ ›‘(‘–ô¡—4mѦE£aQ`È%ÓÅån‘ÿ^ФbÝœ9];`ÞH“çÆïœÃÏ”fÓÔM Ú ÿôõ\ó€‡5?Öf iЖ¥ù¯®uŒ™mÛú†këe¸Ù38×IÉŒÿvîs3ŽvÇõ<àÌ5kl¨ešãšCõ3Õ®„Ws•äÏÓfõ¶#¼Ü k3Ë®ÍSÈuס\Gb}2™L'ŒT‹’„iX–ánqÑŒ-b6™ ³mæÚ˜!èèšWõ é«"Û”„1Zä\^,í7—4ËÝ‚FÜG ~†Ü»ªJš'r…U¨¼9`nuâSƤŒ~!ÜÒƒy’’Œä{pܶ¹ÜU¤(#RÃâç‹CVndu°#ë,-0ЏÇÉÍôúæF`&O`CàÎå VËxQ#L³0!“ß®9äB²• î鉴úòÅë”.å<Û2åëò£¯–ŠˆÆ;9¯Öd¡œ±wkºZ+Öl#½ÙË9x¬é –º¥ÆV“l®š`l½î¦Àø*“m€ìöadY;: cRíåQäªʦ:Uú;‡«]ìo‚³¶Ä£˜q¼HyK¢³¡Í&m0qóˆÐ8¨“RÏžµa;i9éC0ha]ÙØ·ëˆ;n¹#&=¶9UGÚ±X_>qHÓœ| ôÎMÔt#i<íb5/Õ#j0hƒÚt‘ªFËDfíOd²Ùë”`§òú’½ÜoïáŒ3Esý ÜsÓdˆøÝ»xþùâ÷ç—þ#æŽfYÜeYÉÓaBÄÚ¿M{Ê}:¯â¼Úç6™Œ'aC«ãdˆGȰþ“ñ/ãCü?>ƇÖ!>ä©þ^JÄßC‰è¢ÄºâQå%âA‰è/)ÿ JD?„ñ±”ˆŽ¥D|,%¢ÿ %¶ °K‰²Ç8 ?B‰è锈P"z%ûÜüi¬ˆþ>+|S ºl±bÿ­?›[˜­×~³Ð¼÷Û_”œK¾/¡kð«×ÄP¾M;Ú¶£Cg*?7@Ó2y¡aìyú;õ â“áB]Ìaý9ê%MÖtõJÅ÷Ë7•*’­ endstream endobj 234 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 231 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 234 0 R >> endobj 237 0 obj [235 0 R/XYZ 42.52 737.53] endobj 238 0 obj << /Filter[/FlateDecode] /Length 923 >> stream xÚíX[o›0~߯°&A”›¬êC»uݪ-›Z¦=„("‰!Ö€D@Z¥Uÿû 6ãš.­ªî¢>ùàœ›¿s|¾È@‘ XÎÀ‰sðÞCyhdžfɦ4UVUà¼óP$]×ùï‚­ó‰·^ ’fñ(I…‰sNâÆ×@Ò†²aÕ’u DÀ°ÙÔØg.‹(6°Y”|ß]ò(Ü|æOS”MqähšúÜ›1ÇqE Õ–m(+…1Q>Ô ÿöä}ˆgTŽ6iF¥Ñ‡m­ØßR9["*,¼Ì£Rš%8¨|½Äó%g(\ÅAÊÌV-ótžàu–Û™²Ê2ƒEf¡ræµ\qR)@,I/^Pa¾Dó­ !ŠƒŒ¥s…Yºlɶkykú18(ÒtM8Iц´h¯IÂâèï’^ .‹£3‘~á˜eóéttæ|púuK—†][ÛŠ¤YšÜ1tj<¬×®Êìj…]e—ßÄ)b´hÅ@!ŠPœMãM4C‰Xø44Y7ëýP·5*Ûù*Z'(Mñ*¦†Jݨ<œ±ópb'—ß ¾Ý £/p”†«ë¾}ßK3W¸¥¥Ótêõ¢Ímð©ç£lÛi’UÌÚ!){”5Aãpy¢ÓŒ:" Ö5à}˜¼Pr…‡]Ÿeå`^’xÛL I€£ZGGuØ%"ƒ6KTxg>ªKÛŽxn¨ÑH=‡-OÕÐVz<æSÈ÷p£—o¤ò:¥(ôÅ&\b·ÞÛ†45·ŽkyXCª TòxE1Ëß]Øh¾¶f««Ÿ« ¸Aª"qG\£NzP"Cxz|qöíóéÈésGyÇöÉ8Ðaªý†>™ý"×àƒž+<¦°q;¦ñÐ7 ȶËÏpì%Û©Ë䨳`†l©õx¥;ƒcÈr­aÐÝg•èý!¯7Ç“ *Ѱd¦Ûf“ä…Ív¤„W•p/~¬ÔËðÏ3äc¸Ð| .„¿åBóÁ\Ÿ‹ Í}¹îË…æ¾\wsaÕŎæ°á3 |8š;î @³I€µ¡ßó÷áï£ÀGRµ‹ê¦~ÚÏvð…íþ[¶#Eᵟ!$K…²R{ˆ(7ʧˆêÁã—…fÉ*íÂsöäñ5òh<à`)hO2QMshóÇ› èµ\C3D&(ª"C*&‘‡,¿W?iVÁú endstream endobj 239 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 236 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 239 0 R >> endobj 242 0 obj [240 0 R/XYZ 42.52 737.53] endobj 243 0 obj << /Filter[/FlateDecode] /Length 964 >> stream xÚÕ˜ïo›8ÇßﯰN‚(¸`°!WíÅv×u›îºÓÊ´¥ŠHbˆ5 VÙÔÿ}Û ÒeS®·{…cüüð×ϧ5° e4Kð28{å œÄÀDÚ Ú6þ¼Ñ14LÇqô†ïèE´^&òtZ”Æmð\Ü î¹Ýº°=è ×· Aòg ®›(>ðeχ³~í6Q6yÉ’œ. #WgyU°>_eë‚–%[åã&žÅ¬Æ 7š/£BŒQ…Í7ã”æý)š–ì3íÏæ –ÅQY Í—éê>4¾4ÁMä@ìˆ p“ÁÙHÄ/£˜V[™ó’Î?‰á*ϨHJ1ío£NiZ G<Áóö ü˜:\ZÜÑÅù¾Ï»“«GQQDÛ§,k‰ÄªçÏÛÔÎGJ%íBµ5Þ¥á¢>ŠŒ¸çÎ2i /µ«ÎjkÀã|O㈥9ý6?JZM ¥S–E Æ2`¨—4Ç]ÍÆ* šÑ¼šæ›lF‹ñãU'ò Ûâ†ÆnÓÜÚ¶°UÇkNT½ë]ÿe¯öv¯wÅbóæžøÜ5=p0uþxùjúâý凿/®‚!wbgrÞ‡¾Ó ³›ï¬×4m¬í‰® |©7B.­õ!¶uçn†>y>ê3–GÅVÉu],OvšË`.ôìNfÒ+Åפ¼»0RöÁµìÚíøæöVx7…{AßŒµßo¸"â4vR‘V£ÀõA¤l&ÆÙ¦”1¯Þrjµ`±ì#Õ’îö)Fek÷÷K6_ŠáŒ¦«\u˜jÕ3/ç[Wµ]¯N„Ti”'¾éU=YšŠQBe’Q¾Økpß‚ðF’T2;&Ó•j»¦Y´î4ÀZ̉Ë;ª '¨Éã7Ž–t«¾XÕÚ¹ÁuðþÍÕe¿7ÿuqu¼VeñE}=-»HP&Rþ)ž·°NÏî4Ô‹°ÓŸ;´é6—¦RtȽýéÈWWû!"‘œ‚|ø»ä#?L>ü}ò‘“Ÿœ|äXòá£ÈWÆ'&ù—Èת½.ù„ò êTä#ȇ$ÀÀ_ OG>r<ùÀDâQäsbÛÃÐÿ,ôÈ/=û¿†ž:À£x§ÿ,êÈÏ Ÿuõl’ÿ3¶xr.þ?þ#äÊìñ±`z6†Vë.@M¨Û€öƒ´@´EŸq,ƒ£Eþb“4-Ãq\¹cq,›/° ™Lô·ò‚âÃGz3FõeÒ –, äë•ÌïÙWV£< endstream endobj 244 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 241 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 244 0 R >> endobj 247 0 obj [245 0 R/XYZ 42.52 737.53] endobj 248 0 obj << /Filter[/FlateDecode] /Length 977 >> stream xÚí˜Ýo›0Àß÷WXH“ —O“¬ÚÃ>ºnÕÖM+ÓJ‘Äk@" ­Òiÿû ¶CèG¶¬ÚCŸbŸ}öùî|¿``BÓ h~ŽÁëààFp„@×ö!òmAËÁÛsÕƒšá8Žú]:j-—šaû*.Jí"8G]ÆWÀ°GÐõåCÇp‡&D6ï¦à¬Ùe†|4ª—7êa·Ù%*Šh­žíª/ëOEUtØìaÒ‰f£H'â´lM£}r[½fbK\\âYk¶Ù³ât㈤9¾›N‰«±3“,J0ÓÕ§±ÎÖ ëœá¼ç«l‚ .œ.²%W’E®o›ª—  „Úæ¼TÛ2=³Þj\‰1vH}ÓIrÞéÎÌg$+ÓÅÕÙmÖò8*i+Ô˜‹ Ë…–-ûéÝÿl¥1oÛ‡o^¿¿úzüíÓÑipÇr\>„Cçyk EQtE¢oÇòœ9U!yÕºÂ͈"*Õ É£b-uV$O6‘᛹зZFñå\"…{V6 ŽÖ¶œÇ©w€F¨W^GH¹ÐÏ/.˜53DZáÐgætÓw—Ê‹sê:¶O™»lm±”LX;[•|ÇÓÏ-f$^³v5ǯ°V)ùêjN¦sÖœàt‘'%W[tÔËiA–U­×›Pi”'+~ÿèªâ—¤)k%˜å3Ï9žþèl’â<©¸9—„›ËªõgÑ’u̡ԕ#—Ö2 ŽXõ{N ^ºU`: ®p|ýpzÌ£t¤G§ÇÁ{‘D?Å5“ôø5oiQ3…Ê/î)†‡rìjËìÆ2QBÚ“iÀCu•×9‡gmº•ªIh:Hv¼¬ëª}·¥çÚ‰ó¹·žOß²EªhËÒ•ŠâÔ'ß³–¸¾Z¡ÆŠ•a;Ðsä3²´wÕ2ŠqµÞJŸEÎ¥ÙËÓ£ufV:o.Xnq¥àG³$,4@ìY”ÄaíONµâäî™Á¦¬ßR·÷‰]ôPìz÷c—¦ñžÉ‹ƒ¼R–îB^–­}¨ôî /Ú¼ÞŽäEýä­©Òó·æñà‹þ¾ KwoCëÝà[Æýðõþ[ø¢'øÞ_ë.ø–ñŸÂý |½G‚¯ôAñøÊÄ‘á‹ö_ïÀÝ_o¯ðE…¯·wø>à›—¦ñÓgï~>{»Ï#†oyДH„@<‘lbn4lZŒ0'ü)æKýÓz–!É\³}•&¹…Ðh¨¾Z% Iê¶«ó†i™-b&rTÇâö=û 'ñ endstream endobj 249 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 246 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 249 0 R >> endobj 252 0 obj [250 0 R/XYZ 42.52 737.53] endobj 253 0 obj << /Filter[/FlateDecode] /Length 977 >> stream xÚíX]o£8}Ÿ_aEZÉD‰ Øjæ£Ó™j·»š²Ú‡RE$b “V™QÿûÚØ´@h'­º+UÚ';×¾¾×çžËQ Ldš õp ÞGŸfÀG>A¦˜ ËØB–‚—ÐEÆÔ¶mø·áÙ°Œ6cŠg–ܸ ÎÀI ŽqÀðó‘3Ö ÙäÀñLD°þ™‹:Š<Åu\vê(·õiSËCž-³Þ×µcewkûh4šŒ8­ævÎ8ûNŶڥgi±oYγõÍàBÎâA{ñjt5¹¼ºRÙLU:6FÞL¥³\$s SI£ì«Ñ¯—¿Ú£¬ìh¬NÿðþSÆjžo¹ŽyþG Më˜%;5¯Vô5ã-´nVl¹RÓÍÖEʵۺçΗ%ÛTÒ¯ÎÌAV§äYT¤[‘½>µY–©YJu’Q늮èò[/HF‹´Òé\3®ªÝ†æÑFý)H˜¾#èm!_5Ä/¢²*r(bD¥v¸¾~9?Õuº+Óo'ç§Áç†F?ÔÐñ“°õ½DšË­F§_EÁøãv e†¸ÎðzÍâœB¸-$ÿhÜ Øí MnŒlÒ.AÛ×C3ЂÍMo:ÙËE¶NßZ貋2ËþªØF®Ý¾¢ºy”Ðj·G™u¡ÉQ6ŒÕ”èÜNf:¿oùãöŽGA€ÑòšÆÇûg6õˆEeí¶°$”È©]oß¶q7@52ã>{­UGÑgÝ·ò@X¡³ME¸ts»ÎnsàDùJ"–ô{¿VM§qš%“.v“aî@ʰ rÓišž–éš2^]Ùf­ÃÉþbš÷Ë]nvíª"¡q¬%®_”[’îl5ñ©ž¿ûzú×ï'çÁ#Ǭ°¤«°]é˜ì×ú¿ÓXr Æ¾°–’G´tžð×&§ä9’Ó„ïÉ©õ39NÏUTòEu_\Q%ퟠ¨²­†•¼„¢º?UTòo(ªû¢ŠJUT÷PE%‡*ª{ ¢ Ö¾Qm±ó0QUüRAòˆ¨ºOUò€¨ºÏU©!¯â¿k#“OÑÕZˆ[ºÚ1˜Î,™­7ƒÆÐ¼´ß&´ž!KýÁµ±!¾Ô&ÁðÝ6­uÕ¶ˆ‰z´À¦e îâûðL?düixÖs,50,Yº2°+ß›¹ô°ü endstream endobj 254 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 251 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 254 0 R >> endobj 257 0 obj [255 0 R/XYZ 42.52 737.53] endobj 258 0 obj << /Filter[/FlateDecode] /Length 1132 >> stream xÚÕXmo›HþÞ_ZeïØªS_’4Õ5­¢žd" Ûk¼*ÆàDn”ÿ~ ³kX¼¸Î5ªtŸX/;;Ï>3ÏŒYÉÐ CŠ¥êq!½ NÎ}i¨=)˜KŽåëž/Y¦nšRða¤¸ºªÙ¶­|W¶’E뵪Y¾‚²\½ >IgÙÆ‘î%ÍêŽ/™¾n[ÒRr†îYôg"]W^Ò€z)çIƒGéEžNæãã EÉØžñ2ŠÑ8ŸË¯G²,W¾Ì>°ˆ‘QmBŒNzªæZ®òþÝy‚'0^nòFW_:µšáùÆÅÁ`Œò"Ãi ãûž.`8AÉ*sj¶j™çÓ ¯‹Ò®Bæè&EæVÈ’(7ätWöÄI£QQ:ƒÁt¦?ZN”Æ…s‡)\ú(¶k´ŒÖð£wRÁÐlKZIð†¼—$^IutG ‰(£×Á·Ë«‹>üÂ)Eó÷ÙÕEð1Tá×<8»’¶¶ÉL);‚@ž6cX#¼[áY·Q¨lÒÇ)šµ|¢-QZŒÓÍr‚²~µ·cé¶×̦­SÛNWËu†ò¯R04šFì°Nçaû{XrüµgÓ^æÉê^4¿Ä3Ñô<Ê‹P}€XZ¶îÚÍœ‚lw”<š£b»—5«”æGÆ’–fwº鸀îÓæ ÷i„0”Ý¡Ùéþž,„„±(Ë¢­` &‘$ÌÁª7oš¼õQ=ÊL¯MÅžº*/t¯ZÍ·Ä· < ÍNÇ­6;–ejá$E?C¥«f1½å(™÷yúúâô=˜—1lòÌôF3Ô4\£ôW—½ãÒ²ý²•õk>=ùyJ¨/Z#.@Î#q‰öb& ŽìñÛo7ŸÏ®ÑvpâG:OJ†Í¹©ç¹õ¤OôeaÈ|LÊ…ì$ªd:T&8²-còºÑ>ÊpPgŽî›Ml;‡ÆE¦ ×nhD„/HD„óeDäÛþèö¼jà–ôW÷UÒm¥ç×€c×W9^šcç©÷å&øzCÛéC=ÝUãv~ܵ»ˆw£¾µË¿üè Àp\g}yz l–Uœr^KOÏZqÚìTUfW_Z¤¼¢h^Z½˜Wš°ƒM°úÞdgaùº ¹ý‰Þœ|-oN¸[/TËWÓó†åí&®®-Ê–Ó§Ã4Tò¥lx¶bÛß‹C‘F endstream endobj 259 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 256 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 259 0 R >> endobj 262 0 obj [260 0 R/XYZ 42.52 737.53] endobj 263 0 obj << /Filter[/FlateDecode] /Length 858 >> stream xÚåXkkÛ0ý¾_! +v±U[¶ühccíha¬°” âÒFN Žl§íZúß§—ÛqíBi·/Qô¸÷Ý{Lhš` xó|î{ € º0 - - t¿ôT 5ömõ§æÛj6œÍ4y*Ér­ß=G]êÆ7Ô.€Ž,ÚL€ã›ÐE²›€<Š|;0€Á¦å{3lº˜Ž›|WEWƤēᘠòøŽþDŠÞSNÒ‚ŒI¦9*IÈ„¤Å O.H¦ôé<_Z°i¬¦£x’'Óê«9 óBé÷uߤôeèË‹hÀBÛ£JtåPDìQd¥Íî{ÊOò[¬ˆSfÿûy÷ì¼+:÷‹á•.úõ‰I.ü˜•³™Øš…z9ScK‘YPï5©î)ÇÉt(]U"ôû‡03¤ÝÚŒdÙµI‰_ )ݵIù”«i#/ñ®ò²ùâax†fåÍ£(_=ªo+ÒyÐç`;š,ÓEê§ùxÎ$ж9ºxtA¦ej4ÙÜ POåCÌ™æ#•ÿGìQ©Y<¾Ò¯ß»?%#˜ endstream endobj 264 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 261 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 264 0 R >> endobj 267 0 obj [265 0 R/XYZ 42.52 737.53] endobj 268 0 obj << /Filter[/FlateDecode] /Length 724 >> stream xÚÕ—ßo›0Çß÷WXH“ ƒÍæiÓš©Õ¤UÕ’("‰!–D¬]«þï3Ø!d]'5{ æî|_ΟØg`BÓ1¨~¾€OÁ‡¾ |è; ˆ¶\è¸ÀB!|¨j†mÛêͳÕ<\.5ÃrUšÚ(¸WŸƒ{`X>Ä.@.´-°Ø3¡cÉa¾WY<àÉ,CßFiÆU–é$G!KRú8¬1]—ì&ã‚=ÒqT Õ‚&‘^eE˜@Ïãñf5§ ]Ðt5N׋ Í…—)Hå>°¢Ë*—e’¡6Ôz•Í@†.jÆ?Kƒ=«©(Š®ì‰Uôr®4ƒXxGw—Ò¥Œ„,Ÿ'°›‰J?ÉB9Õ6‰2‰9D˜!ãl z®ÖQÅ"RÄ<—"vÀÕïã=_ää—pœeëIB…÷Å·»àö.ƒ§–¥ªß³´sŠ‚6Ê&¾êgÆf]î\âP]§‹S*ئZ]kìcˆZëq ¶µüÕ›}ýCíIÔÒ%Ðò›“ž¢³ÝM'9E§s”Nr’Nçä ‚A§óz:‹–0å²ÆÑ²!±»pÁj;F$y1»ŸÐŒÅJL¾Ù™è(0mÙ{´øoAK£Ê½lgQ6"ë¿ÙfWz!@ú"@‚}0’„2ÕQTÊö/háaÿ)0]çßÙ2Sg‰ ßú:±qŽcSD¯Ã†¼6ÓùbSLçÍ}ÎVc–ÐýÒ^¸íg¶±|E²´"¦ó0¿¥- Tß¡hÊ¢,çéwßÏi8ãý¶PÌ{“U¬.L:Íf,kXÞ·zäþõ×+Ù﫜†‹ÞþŠÖI¹}r {m¾á"ÍF£¿y±iõ·Š:‚_,¨ñ¼RÜ–WŠÖõ‚Åsß.¸ä8¾§~\Ç벂¥‡…uù`"“_BéØªM¤¾w¿"ì¤J endstream endobj 269 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 266 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 269 0 R >> endobj 272 0 obj [270 0 R/XYZ 42.52 737.53] endobj 273 0 obj << /Filter[/FlateDecode] /Length 857 >> stream xÚÝWßo›0~ß_áñ]p±ù™V{X×vkµµ•iIÑÆ$h"BmÕþ÷Ùø&Ð.“ZuÛÆÜù¾;ß# [š¡òñ öO}ÔÇ} "dRQ‚ Aƒã¡îbôm[ÿb¶ž‡Ë¥aR_gùÊÎÑÉ€/ã 5÷ëcÇGÄÇ6E äö(¼&躌 ¢¸¦2Åg§Œ²¿g˜.uõÏáW&GÅQœÀ(ÍRÓ‚¯™|.6öïN“øFŽo“lõð2{û%t‹Ç·J<<~ÎÂixSY¼•r¨º¥aÉo#]>_7_W_iÑX%Ê–,­¬Š4\°žœÐÖon´‘12à»q_Fä¥$*ºÛ›h…q’²#‘èäôìÓÉåÕÉÅÈMû*ÊŸí Y²b÷í|K‹—ul"pŽôK¢©‰ìªZ½r=×;¯Â£,çkëœ[s¾€/Ko³iœÎDÖàœë¾HªQ˜¶)î;jš¦õ´·Öj×EÎcÈøU͹ÑYZ°Ë%s{þ£Ä«Éì‚mª±³IG÷†ã±t1Á‡ |éSWvOY‰RúȘCžCéKP5¹oY<•6M¾[Yº* •y˜ïÕq±¥Ü“ª‰ê¦¤ÞÇÀƒú˜ÈŸIÛãW0byTw7»¿€¶íèÔéÉ‹µÿ5"ž×ïëçpy»2ª—c*.rTÏãÙÜ ^¾W¿ÿ’º endstream endobj 274 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 271 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 274 0 R >> endobj 277 0 obj [275 0 R/XYZ 42.52 737.53] endobj 278 0 obj << /Filter[/FlateDecode] /Length 1009 >> stream xÚ­W[oÛ6~߯àl‰Ñ]rƒ=¬kR´(’u·+0䘶ÈR&K Ú"ÿ}”i“"å®@ŸDQç~¾ïPD.v]´EÃã-z=¿¼IÐ Ïb4ß ÐOpœ ßÞ‡æof„-'ó+ Ì&z²?1Is°æïÑõœš Ñ3rüä%8ðÑ…©‹cŸ½–èãà%E)óÒï‡È‰\ìƒãqµY6$_/Ÿ‹5Ù%1,'òCóUÿˆÌ…aƒC/Å©ÏųhÐü\k‘Ô3óq—7ð¥ß¨ò=±áµ¨ZXì¨Í$³¾í{Ìv<ؾdú½¾)‹¬+BÖXæð8´ÔóÖí.g¶Ÿ‹²äqíó¢‚uýDª±/ÈcGªG9¿¹áÛ»¹ ™45óôô¥ÝÕl÷âr°é( ܼûpÍD Ê«AÐeŠ Hd&<•_Åìþ`AœâÉÆµ5š•‘Y™Å>³ÊRlxb²}·7yQVäkÖWwÙzw}›Y¡âD òEŒlò@ÀúHV2®à*3¤ÜØbrö Ç üG†Ò;ØvÏBQœ‚Ö6dTÛ ãcÛÕZÍ«GåÞU-Ù’FŠÅx°6Ož:Hã_¤]®ënU’ÏyÙãÕ‘%Jàœ%¡9R¢ª«ÃlO—MÝìó–Uäþ»ýŠ4“”QНøÊÏÌsc´â¼†tüDbm‡Ž3Wq°FånÊšóLk ˜ˆçß®hȲ€Ò«(Ñä7:úÊ/àï8@.î>Íï?1–~;mƒóÎÕË•Ø&:lgÞ¨M:¥Ì{´vG(Îò®lyƒ\Ѽ†:/C‡˜Ñ"ç…dóe‚* ûšÛá¢Gü8ì¾_§}ÞÃIpûzLöOijÜBé‹¶‹‚+Í0U(a_c^C1V ÐQ‰ï¥J6æH6{r …5³Vj戈GÎуKh¢@Å[m5<|¬Ën_-Ç}¤óÝ“f ŸX¡xÈëŒLM7ck¨na&•W«§ë -`„ÓôL€L™‡y 4Йl¨œÐÐÑïÇÿ;ø™lº îÒvMű{ŠÑ™8íÜI²K]´õmâü¦féTÃA(~%îßög&”ÃÌŸGÕO›*aõ“Bõ{¥2KªÚÿA±“8B¡N1ý©ŸÂé÷æú8ˆ¯ê‚ (YFL;fq~P šâ rpéÐxæïá€üñ÷ Ì06¾è8‰aW¸êð ~Ù9]©Žôjå>ß³KÕ}©’.XÅvgÑû Á‹ãYjþÙm»¾G½„Úláz.½†yn˜AÂâûå?tY— endstream endobj 279 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 276 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 279 0 R >> endobj 282 0 obj [280 0 R/XYZ 42.52 737.53] endobj 283 0 obj << /Filter[/FlateDecode] /Length 974 >> stream xÚ¥WÑŽ›8}ïWXHÛš<Ø` §Ý¶Su^¶jÓ݇d1‰I‘LM˜n[Í¿×`l ‰Fû‰}ï9¾çøyØöñüµ¸º‰ÀÍC°HKB„) a o—"Ûõ}þkÇ>äÉÃí’2^Ùw‹[ðn!Ò່›£ 8B>{Ä ‰ú™ƒÏ-J b…‚#‚¸ÍxÐÂ,­›¼L¶KI·,Mêüð˜ä5³îîœÊÅ”"¸>AqÔÆX›ûtÍÙ·:ãl½)óz_¬³âÀvŒËÐ×K˲Ú`O„{hNÛ¸?Ä*òJÌo^(œýýeññËBþøÕÿ]Ôû{ÆŸlO=xíZ [ Ç2ÛJ˜3q+¸)‹JÁm¾&\Ë©E²grýØ‹ ôu(’AGÒQ9útÇeè]Ù¿dAc!Ñù6õL“,/ØÏ¼PܬXžJjBAIO¤qo*‚&•-kæjñreOJñÅA!§cSÜYZŸ<+vöM;E YÕ°”³a}ÙÍ à?¦åL*ñØFƽ–@Gÿáa±±­æXUH‰´šÏä|#ÕȳÓZ %±)€‘^Yª©Dø„]OÊoÞ&})“8SŒ:Y=ÇÙ¡æE·zn_üð„ôt,ý¤Øf×p–¯úA*…|Õ él#Û,M¹0ÕVkJ¼“ÕˆwLqA@1a¤½¨^¶}Žr—V½—ÙÖÑàR…#©hÆî$>¢þÉÝÙRYF‹Â·’D3~ç˜C}¤&Wà7~8ʵc‡õC™'<û™²²ÐÔѺšIŸÚuU$‘‡$Så-S…^Ö÷9“ï­•TÀìj´êñi¢›Ê8ù,+°3ù7‘oO×ÓëéO•aVc€aêÎrš§é´…†É%¤Öšã߈ÖÏGæ¬cFZ:K¥û¨ ,­´ûJÚɘb]•5ß°5o¢E¾3SŠ’ïµ ™~Ð ªgX«—¢š¨…¦ “„Oî}`0¹ŒgœâÕÈ&ýѵßT=ìŽF“˜¦ttÀ|h¯³•Ü™î»ÆGâ)ùo.É/ìut€DhšÍe›=2¾cÅfâ+2|ƾ7FDÒõŠÌÔÖoÆLJ¾G¾P »Õ6äÃ\ÄõÈ+Ô0ðpþ þ_âCí&òu•½‹ýH'Ø{xx q#L‘§]Cº?º‹ˆ~ÝQ$BX6?7ì…þYïêæöý’À‘÷ âaO\Âp>‡·ênôÑŽ lßIsO"g»¯6‰áAñ{ñŸðæ endstream endobj 284 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 281 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 284 0 R >> endobj 287 0 obj [285 0 R/XYZ 42.52 737.53] endobj 288 0 obj << /Filter[/FlateDecode] /Length 898 >> stream xÚÅW[o›0~߯°6A<›;«ö°i­/«ÔT{Hª(M\ŠDIÅ¥kWõ¿ÏØl0i¦nÚSÇ>ç;çûÎ1"À~¾‚ó·_BÃ8ó+à9! Bà`ˆ1˜Z˜>´l×uÍVäšÅúöÖ²Ð$Ei]ÌOÀç9uãŸÀvbè…‡ÐuÀ ð"GüÍÀ‹HDÁ1†^ìÆî±0Ûônu¿*wu±!3æQ3bë…ùAgö¥Ýí‚¥µ´ŽÙ"{4‘HöôÄ ®cOvaÆÌHHµ¢¾H‘|CŒÙâ‚s\軲—…ñ%Û­+ËöOÁNt_=¶ôˆ È‘(¼(ä¸6—W«RÅõnAѲõ؃ؑӸۥ[ŽJÝã.M}W_fDFÒ–VkV+G0rrFÞz&yZ‘Cf“ÔÕ:ÍròkiŽ3ä,iÙÕL“åŽ{5*™ÖÄhŸÐ„Ag¬‰AíEìa cr_&ª½V"íÉ÷šh´š¬Ó\RƒÒ¯i¯fB¡CGßÏç§çsþçQ±4î4`ïW¤Ü>ñÿmäc})Z ö [ñÕy™&9Ö4©“ŒÜ¼ZåõÍ%)¦ðb„úñ”ø: î| Ã`¯ðdŒÉiqI5ꣵÚBºICª¯4Œ½)=QÈòkÙóð}ƒÁªE3Aj‘búâÊ¿DÜ„ †45H”ñªÿ¥®j3eà?OFß½HÛ¸-èt«æ¢ »¼!7×ëBˆ¼ï­ÞËÉW¨ï"ùãH)ë¬Ò”NÛK=¦V<Ïqõ†˜à§ U]ä“Hü‰C=P[Mª÷Œta|Ë+’B‡¬!Ð8«Š4O ‰HMO­ïÓ²y¨š¥ŸËò®åDñÙšt˃GH?ó¨»j]TšKóMÁRêgaÐ|¡I˜dÉx½dh•IqG¶Z2¸‰ïxÏ×£C¤1Κɢu¨fÉáµàJùt'yôg¬pÕÌsÁt]Íâë $CH„~ä`uˆ·C™[úI¦õóÒ“|JGfé,—1ë'Q/ßä%òõGò=©NÀÁ¿ðžï„}ÞÓ®Ï XžbÃ+•b"éRÕ¾h¯Uýå­ÛA/q˜ íD\ßN›ë›r•K“k‹ÞähÍpÄ‘ù¡Nê†Çf…ãÍĈ^ø0 \Ó¾W¿¤û endstream endobj 289 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 286 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 289 0 R >> endobj 292 0 obj [290 0 R/XYZ 42.52 737.53] endobj 293 0 obj << /Filter[/FlateDecode] /Length 837 >> stream xÚÕW[oÓ0~çWX‘”˜Ø¹–‰ ±&­m5eÛEj“*NÛ´ÿŽçâÔé¶±‰§&'ö¹}ß9§8ÈqÀT?ßÀçñûãŒÐ(ã°I€°Fƒñ— ô‘i»® š‘ ‹x³1mBZ0s6>_Ç\~ñ{#ä…‡È%` ¼ÈA©_Wଲ¨¶"ä°å°b†e,iyÿNÙ£e™fKÚgeÁŸLÛ'¬¾¥‰1ãòãU—BìCVÆEiXòEýfó‚®iVò3«ò׶碈H£óËÅ…0šÄ%åZÖãÄ{ÒœÄNå.?ù–ǽº‘^¤Y­þÝóñéùX¾ÜuâVãA#\çYy¥I“øF“]åÛB:;ò&Ò ¿r£>äqui¶-i}7É·—+Z_gtžg‰¦µL×ô6Ïè½|ïE}TY³£^È×yšHc½³Sø8w°j\Q÷Ü@§æ +ðQ©YÜf,]f4Ù³ Œ×49Òáo>Éåy§wPª„ZÄé*£·S¨±k ]-¬F›ŒDˆ¸ª±*«2‹"kU–ê,Ô!w!NÍ;M˽”»! |ÕöÐ:Î[QP-·„ý¶šÚìTébî¡..–žÆÎ†Œ§½©â*cÔ•6A³½¥Ìö”2îêh—Ûl·‡¨=ÈìbòÚïóz/­‡YÝ?Tõò¦ ó”¥yöÂä†ÉÏ!¿ ù-%Øg–Û)ƒÿ§,u̵‰ƒQ©— (ì:¡`Ï óµA×ë¶½Y×û"t*S¥5qô—ct`bíèÆ‘(Åû¦®wNO¡æð£cCèî1饧†â}¿p*÷õàÔý;"ÈîßÒÉ«HÆO}ÏJº¤ÅÃÍ×í7ß!z=ÛÒF]Ôº¦Öø^>ödø†š˜sPÿR|2ŠÏiÂØ|[üïôc88kW§:°àù¯Þ€³:ˆ•_ÐGMO$GOÁÊS*®ewÙ²Cì#GY·A³p©k]}ƒ„KT=‡orØ ü´]nY)Ö<Ï’ûq0?€ƒ`4‚'õxjFVÏDìƒéòÊ$,kÿÞün5Ò endstream endobj 294 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 291 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 294 0 R >> endobj 297 0 obj [295 0 R/XYZ 42.52 737.53] endobj 298 0 obj << /Filter[/FlateDecode] /Length 947 >> stream xÚ­W[o›0~߯°:A ›kVõaÓ.ZUm•–j ŠHãP$ îRõ¿ÏØ\ ˜$Mû>œ‹ÏwÎùŒ¡}|gᄌ`ªO0Û ¹ºãuÁìÓ\¶uE3MSþ¥x¦œ÷÷І\g¹âÏ.Áçqcß@CSÝrtuXž¡;¨ZÆà'⯊RÊ- ±GEº]m–!.–ÛœÅÛ`-½ŸK’DcDÑ †DñŒì þ«h6²äõv·ŠqùnË“7³ë›[Îqö€×˜êOÌâ‚é‚®Vh¸UZ©Ú©Ê6{d}œn}òÝnQzU°LÝC]ÒÚS…—’WéŽ#®~¤£lˆŸ€¢Êìu”¤žSw¶6…ò´ÎØÃ‡:ã-Žðc“pU¼Á½Š;È5Ñ(]R2Î"BÌIYôç{(1ÔîöÖHÆáK7IÌž…%:å»§å¨û[b’¸= O!ª¶!ógõšóCü&6+Ûž:?«ø`¨º;G=³!BÏÁÆ9›z0lÆÛ%ó© ±ŽaD(¡S‚Vgd’¹A‚ÕÀ]$sè³U#DDˆáp ³çÐlZÄÖê;´‰Ð9¬wèô:­C—غ}‡zãο`tYi¡Wœ«’Xþ°g6˳µt¶ ¤Jþ4˜|³Íê æO¨"Ü ÕMkÍšZ´*¢€_viT,oqiÅ>•V¬DÂ[¶?rC€â¶-½Å÷wb¸Êà IŽ'š¢‡F{!¿,©}èŒfø"ÅÕPж5¹*"¡GŠÝPÙz-ñêZ•nÿžª¹ÐÖ î¦Z ê»j{#n,ÈͲßïËêN|]Þ‰;÷ã(¼SÈõ˜Œ6tœ©'Ø…»¼`¨<4é‹ "h8¦lÁjoþG}Y– endstream endobj 299 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 296 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 299 0 R >> endobj 302 0 obj [300 0 R/XYZ 42.52 737.53] endobj 303 0 obj << /Filter[/FlateDecode] /Length 837 >> stream xÚÝX[o›0~߯°&™*xØØ@6í¡ÓÖIUµUZ¢=$QD(I#Ñ&‚dS7õ¿ÏØár¨š,ÝÞÎ9>·Ï —¸.Z uùŒ> Þ\¨Oú>Ì‘Ã|Bb”PŠGXÛñ<·CgÑzm;,ÀI–Û“Á%ú4f8ú)õú„ˆÄcèñÐ%>3)ú¦¼„(4^¸KÂ9…˜+/g‹èî.²Á8~_\Ž“4‰É;åǑ֩Tp•©ð¨—)'”éu¡Ö-ËêY‹d3ÝÞ/7Ó†ÕS¯Ò„¬ja4鬋tm´¿H¾¨nª‹3h1†£t} ›H6ຊØÒ÷s陨ô^eúºV<›OkQM“üÆz;’á*·šƒ×²JéƒNæÍj;Kmþìëpp=è‡ß5ITØ3›¬ f]‚X çÍÚÔ-yé´.sÓ%Sù)„&_ÍðugT:@{ÿ±ZÞèØ[c|º Û­wâ°Ç¶)æ^‰ã]|#ߌK­ŠÞ™GËô>ù5Æ­Fã> endobj 301 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 304 0 R >> endobj 307 0 obj [305 0 R/XYZ 42.52 737.53] endobj 308 0 obj << /Filter[/FlateDecode] /Length 739 >> stream xÚ­—[o›0†ï÷+,.&˜ÀÃ`Ù®6í UÕ4©™vPD'E¢Ð9°i›úßg°0Æ ]{u¿ãûø‹1p¡ë‚=èŸÁûåëOXÀE–;€½†ðD,?¬ÌZŽïûæw+öMšÝÝYŽ™„¬ty>.Y ~Ç[@Aß·Ç. =ñg®º,1ˆE–v‡?Ú,†aØÆÔë¦Ìëõ†…aw P cYº'³\Ûª¹.ˆå^`¶–«05R{•ò•”û9‘5²à›ëÝZJ±&‡­ñfÅróT"‘*è<~Vù¶ ŠMÅ-1ÇU´«¬’ÄâK»L4,¾-a—åEIþ$¦ROÂò;ûË·ËKû˜ÈJ¬·¼£>/ï^4Ú—j´ì­§èD¯©ïÁ8”5¥d“ßÑj“Þ¤ªá„ª#GU×ÿÓT Û)Û¾vò>EÕq«Š®Á3íÓQ"ýn¡ësïÙi}ŸmçNµ>[çYû7’µ®³ýz“Õd_ÑßóEz1mªòP‹2n2Êß^1›2»%¶ø‡lóJ¼Š­á:/kL"Гkè0 Sb5øwؘ@âù0ð'‘H Ù+㪦y¹ç)DBfÙ¯*]©é>êû«Ãу]!ïíB\¾¶—é"‘ïo,v`%¡0\Äæ»fß´¶¶Å‹‹\vÝ@nè›Øõ½øyج# endstream endobj 309 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 306 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 309 0 R >> endobj 312 0 obj [310 0 R/XYZ 42.52 737.53] endobj 313 0 obj << /Filter[/FlateDecode] /Length 1038 >> stream xÚWKœ8¾ï¯@D³2#`Á¼w”Ãîf²J»‘†Q4jÑÝn‰G–†ÍKùï1¶yؘQ''pÙUõ¹¾ª²­X¦e)¹B>+Æ¿½”ÈŒ|%>+ôMÛS mÚ¶¿J€gj†ã8à½: Í>|Ð Ô^´4~«ÜÇØŒ«|Äz‘銘T*Å -Ó‡lX*ÄK¨„Ì‹c›®¯ôK¼çý9+Ê}Ù‘Áuû.Ë÷mÓt;pAåYÇÃ:«Ðð¤û¢Þi;íŽà0l×´!þXĶøÈ-*òˆHUU]]VõD}èÚ¢Î5Ã.`ðªYêÙŸšêIšê£e¤ˆI!³åMû™šÿ=Á.—8(´ÿ›â¤á±•Þ}S_:êùø”µ·ì—-"`¢gcÚWâ}o;ÜsÎ-oúÊÐû|èù ñ_zHXúhp ú3 ç¢>]ÇÃ@w  myX¸†I¬¥^¨&3ТK_vwëT]$µfèWjp&‡Ûo‹º¾­)”¥gc•[ Jbû…)7)’83ø¦Í ¶è¿¾hÑÏ’H+1A§~„LÜÓlŽ©¦„E_΢–ŒHjx‹NO “‡`̨Ÿ¯ÇíX ¤þõ3¤ e9Өhê}•aŸ¬® ‡¶ÉÁ¿\wXÁžšþP"Ц²tnhë)>®"m¸‚ú<Æ+G»¼Uúú:¼ý@°Žæ¦ïÉô†}WI”Jˆ¯+¥ ^Ž›¾c?‰¾¬l:˜dËà([­G°æLš.Ötk–yk#6_°æOšÖ k!–…›ØV”od© j£ïÑü7¡î’¼¤ŒÚ¡r9™P¨êë²ÉX#  û›“z³¸?î4*?7¬×cÙøÃŠ5«s´Ѹ2¥ŸùP3˜_ÉãPÔûKñ]®¯œIe(ŠƒAG%ªðÆ÷u_PËšÎ2³/eó«Úøú#YpÎ.ݼ`ÜÐFó”]:à‡$€ènºƒÈ[Þºê'Êç8âvö¦Æ- µ4d<¼|Á5‡Ÿã±‘; £—k‰ÁÌg¾Á'—¼7øÊ]~¦Ð–‘¿ý÷1~÷³€s3 ”\Ÿº]@üv'åhÌä<9×ç ç^2½±•/Ïÿi<ÌIÖŒƒ›Ík4Õ>:¥x×9T’´ZÞ‹VÙF²*ÿ‘¬Qy^m&•ºJ'׺Äà»ÎOY}C}*Ž£™¾>ÝEíñŸøþ!¾%}Âí™Öâ7 ÆgÜò±È4``Ú4±]|\@Ûò!ø£Ïûá²ä8.€®N_‘в-|ú~·ìeùN ! ÿpxeBÐù“CÐ1|¿|ü³JÅ endstream endobj 314 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 311 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 314 0 R >> endobj 317 0 obj [315 0 R/XYZ 42.52 737.53] endobj 318 0 obj << /Filter[/FlateDecode] /Length 684 >> stream xÚ½–]o›0†ï÷+,&M ‡Ù®ÖmÝÖ«J‹´‹U 9I˜ÈŒi×MýïãÃ4@\BÚ®WÁÄç=ÇÏk›ƒLlšh…ÊŸ/èlüöÜC#½˜½žÅ‹ hµõ02PíoHL¬*˜Jƒ9lwïå9–³hß@•—¨)l–ú›B!Э¥R%cÀ3w¢ªlw‡ä+× }2Õ'Êdzó¯E4þŸNõZ̶°ï?n;J Ö–ÊÁvô@uB¥½P;NêØØ·ö@ÓA@¯“hQ‰¦•¶‰Q5ák`½·.•5¸á[-íRéC’3{J˜Ä×ÀN#sód:2ÉG¢{B’…@©8Œ^‹RÊYærÀ!ä kPr°GºG«žv¬¨YœF«®(æÕl` 1¿Š³í¼ t6sPµ ¹eõT¹ëÝ:Ž\˜½ùï„u~±óº;Y‚6÷é[Ìa_»–Â)ew›¯£Xì»ùÏ|Ô¼òÏãˆÈ¬d°qý¦Ò£¦ =Þ^÷Yí•Uö¢FS™ÑðÿÕòú»<Ðð‡NñÃ2/d7íïužn¶;ÌlzüT÷ ^«÷õëJî’Á&[ˆ¯OÄïZ¼ˆá·°&…òêºËî¼ì梂$”¶Ï†G(6 tý¢n¡÷ú}DÞ°“ªÚ Ѫ_­z«mVk-ïÚó2‰ëŽ|õC¶ÊR^Ͱ]<˜ÄÌ›{bº¶êPQß«ª¾§™ endstream endobj 319 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 316 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 319 0 R >> endobj 322 0 obj [320 0 R/XYZ 42.52 737.53] endobj 323 0 obj << /Filter[/FlateDecode] /Length 1002 >> stream xÚV]o›:¾?¿1m‚)p Eç"MÒj[ÛL-Ý45rˆI8%YNOÕýölÂGO¯°ßç}Þo šªiÂF(>™Ó?·„‘: Ž/(`¨ê¦tU×gv/™ª¬ é‡l¤î÷², %©üà|æ1„‘©†%è–:ÂN0lM¶ …ÛB‹-ØLK~n ýäZDoå»^¥8É<ìnâ(ˆw£Düt/Šb¡ËP-Èh‘ÉEÊ‹²bCjƒXJKù¹@ÐܪÂì€0¥r?.„´ºNa„þ[J]œ—RŠB¿÷¡r"/å4ª>A8K¢7¨})ŽÝVmP ®é‰­nëÝ?ôîÅýáH=S73^ýƒ<,><ô¸:ó¨¨#G ÚÌð¦)óñÊßÂh¢Cž(ùtô-¨r^#¦Ùuƒ(À®Kݲ”;îç?U/^#*õ7¥Éƒ¯[FÕö~Ÿ^tPÒ»·?>_ÐUcºÀ1ýîà#¢«£·bæŸ/ð¥¨êœ´ˆ÷!èÃ,ÄG_¸Ô-áí¾ìR ã·)ÈÆÕ(é'˜pò}Èùûô» cï1ÀhÇLÍ"Ät[M¿éÙ¹{½˜ÍŸßæMVøiŽñDQ¶kK+Œ4“Íaï®góó»'+Ð4©ÿ‘꼋f¡5Ý~ì7QsùËÏ×_‰èÐ&w¸èe=’¾¤›ZM¬T{³X8u±›8OŒWÅfgrv¹˜~­³A ¾Îövò}~~3¹jX{ !?;Ô&_êŸNœùÅâæg.nU¨O!F›8y’ÉýýRýtqywuMÌTTOã0Û‘@];J*õP½´óáI1nö„×*ð°…øXVÕ¢¢ë íÑEÊ ôÀ˲„\eA¸®!Ð&Ô(„“줕մ¥=?yy±˜tTZ1ÚI|à¼L¼­KÆuwšÌdcŒ^)ú²ßžÐ`ÜZZM‡ :ºû” éh)‰0Ãñ:öÈTÑÅÊÈ*©¾Gÿb­;=£MËd™a¶foÉcèm[¿r °ÅÿüN|ÜS†¥¿» ÍѸ3Ôef{?A%{:¢[©3V¤þGFèÊ„®LtLT½q¢¿ŒéEnÉ¡™°TÝ*”âù4É6YšÏ !£GßÖ@Ó5’­Ãáh$}aïío² ¤b ò·7’`³•-aÆï¯?2E-ÿ endstream endobj 324 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 321 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 324 0 R >> endobj 327 0 obj [325 0 R/XYZ 42.52 737.53] endobj 328 0 obj << /Filter[/FlateDecode] /Length 1252 >> stream xÚµX[o£F~ﯠ¬¶îØY¹Qw›­ºU/R¬ö!X1c-4À¦nµÿ½s9Œ7Q·J$ù_¾3Œb™–¥ìöóƒòv}ù>T–æ2PÖ;ÅsB3Ç6m[Y§ù¦>w]WûC_¸ŽËRŸ;¡†p¥oÖ”›5ã)OÊÜYš^¨Ø¡é:ÊAñ–8ð˜)·LËBY€×6½@™Ó×Ó’ >÷OÛ£ú~[$(Ò*”í"ýŠ©±æÂ!ôã'ôÕ Î)‹ÏMÊsÁVuœfŒiÞãòe-OÄ®ÁØîš|k”¸¨‹úX"#ÆûÊHŠmUã4ßOðŠë. QÍ—*“tÿe{L‚Õ7¤<²}F²êQš•Y¼%ޫۇݽj¨j¤÷Ù%å?æ =)ÅငE»óE‚šýž¸ÃëÇ´‚ÐmqZÖCûh4%ëÔ(Ê/g}ŸØò5‘cû¡/9Ä6-ßÒú:Ò ÂŒbÌ›ÖLð!…¼ÒL@ô=Ó–¢/ìó´ a B˜:+Ø bA jç=A§Ž¶‚f—ÄnjúdÜŽ?Sœ'jŒ`ë‘ìeâ5†ERäHv®~ô(N *à÷cZ“’îú•²KóÊä@ì¹çzI¹|;·9뀞+ÑODùñ»"'ÍÐlë6OÂëÉ/†nrïªa(¡Ç³"<¥pgmøÃ×"AÔ…~”Áè<‘£¦‚.x@'Ý@ø}Ôë¶¥=M%°ð¡ƒjôk˜AÄ0=’GÊ#æV¤¯V¶lò¯yv„â …ò}÷ö½\QûS«»Bæ%ìi-z=á´&Xfßmè‡t=æ§/ô–c[–ö©HÑ\{Šô¿¡É§ÛûD’kd`UHp:GELûHó¹²8îh‹ö«÷Y¿¬Ä æ¿OPq!~8žîà˜t+}CiÓà¶‹qP”‚²Œ1çI¹-Ñ6³N$Ü4Í!O^Ô÷»¢É“•5ŒHÝrOCoðÈ—Ç<> CtgÙÔ°.šš<È£H4È}ŬîX:6g²Ñ¡1ƒþa 2õ\1Wip›Ï åö©Ï 1Ý Ïó›”ì.ÜJôç•àãOèxƒq'BÖFš;±‡ž8öB´:0#˜ñ{œ5hÜ †DòŽ&'©§‘˜d žÌi‡ýö( Ò‰8›©Ùö’-!_œVhÂçQàs®ÆA,…ãÃ}{ÓÎ,:€ÀÇ÷g\;Š¢hÍODÍ:fo9à¶ÎqRÖÕŠòÎr©]M–„Ýk2˜ç¬ŒÇ¡Q>Æœn•¿PŸáþô!iÈOÂ;k'ÍsÑ](9‹îxáƒg#ü³Gî*&²$÷Â¥È.}›üçÌwi¿û™ÏõKÇùKdcT5Yýfü@}FØh qšo¸LVMÿv\˜ÖÐOùyÜÊÿ· ›¼J÷9JjÔ£%9‚cŒÎŸÜ+ùh(˜O|P "Á@øJÎ~pÌgì7l¬¥xõÕÝ¡Hº¾¾–¿Éºß®ÖøqÀ±Óõ¥²—¤ÖÅø £wóÐöM«wû 6ÄýCwËÑr8¡i‡LϸçøÞsHwéþQwB„Ò‚åBû®Ù³ Jáx,,Ûb…¸š‚}_ýõl½ endstream endobj 329 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 326 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 329 0 R >> endobj 332 0 obj [330 0 R/XYZ 42.52 737.53] endobj 333 0 obj << /Filter[/FlateDecode] /Length 1154 >> stream xÚ­Wko£FýÞ_X¥‚¦0<Œc¹Q·ë´»êîFZ¯úÁXÁc‰†¤é*ÿ½ó‰wÓæ1çž¹÷œ;3Š,KÙ)üò‡òvñËÕX™€‰¯,¶Š }`{ ´m+‹wKͺé8Žö·8ŽŠB7áXC¸ÔW‹Ê|Aa\厛w¬Øcà@åNq øPÞ¦Ê%Pe*&{íò(q¾AºéAWÍØÕÓ6y\œd»œjÅã¶Êbc©¾ÏÚ!¬®ŒåÊ(pNròX cÿ}¨sf…·x¸#x•NÀ¶,í>O6"ÔYjUV&» É'IFÄŸS¼oa˜©g5…6¾×‡ïØž¥Å7Ûõ6JÒ ýò%J· õé“ÄŒ»‚2û0ÜÙþ߈‡éLjT8ãÏMÛ6lÂ$[Á‹Æ-—ö l“ljêÀtÏÕPÿÕ´åܳÍ> ͱçì«ÙÌ´/xÌFHÁ爘W¤¨$nÅ"t¦8À £á{´\:AÄX%¥LùüŸ$É3:ö "„j@D­.//ëB_e5xhAàx­Òò—TZ!çÉŠ'ËEeä3Íèìy¯ZJ~QÆÞ Œ*ÉÇþ¼zýAõÀÒ”V)™2ÈÓpú]ð³ÀáN6°·¤ä›”žú9ýO6’š¾Ê±JnÑ>zÝ*Aw…¼!¹¸î*T–ÝXʧÉÚ[‹#.7µ66Ëë8øñˆÐ.Ï’ü$™ÆyFUÅ„RïuÒ—“ZA“p/¸Ì[‘SÕŒª²–Õ¶N§ÈýÞ¸%›À-»ídŽ™D`ÎÚŒÊ"M¥$žRVKkõ¼D_4(‹0*Ò(F<#†JqW¢SØ“1ð[bØÄfóãAÁÕj+«#6zTOa$¨ŒÔ–“ûçÔ„òùà&Ô€k½¾áŽ?ö^åZõ×z'»ÖÙµ(-ÑÀ"uáedÚ¯Õ‘Äþ®6\Ðön…þŽúº!ƒœÐß]h õå³²»91hªúXþX\º¾úÝöÃ[Úz›WÙF ºß—”\îºéøýíÕúÓçÅû×Í?Î?-æïꜼ& –«(åÿgtŽ:yrW¤èÑ6¹‘ÍŸrº¥7E ¹Oé›QZ7mzM5xñº„Ûßò¾Ã¤sÑÓXd{¦KC½ 8xEÚ*ìE÷ö®WHÚóðq“ö³rñé9$ ªqØP^> endobj 331 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 334 0 R >> endobj 337 0 obj [335 0 R/XYZ 42.52 737.53] endobj 338 0 obj << /Filter[/FlateDecode] /Length 1047 >> stream xÚ½WKœ8¾çWXH‘ óèŒö°«ÝD›ËFJG9t·Óíî!a`ôôîFóßc(06£Lå”íz|Uõ™B.v]tBýã-úc}õ&F+¼ŠÐúˆˆã(F¾‡=­ÿܘ!¶œ ÌOV˜uvo9~lÒº±vëwè¯5SCÐ9þ “y1|t‡HââÈçŸúÐ[IP­tr‚xtV ðmÓºj³6¯Ê´ÎÊ5ìÍÎÞoŠ*k-'ô‰Ù´Yݲ½ƒ(4ór_Ó;Z¶Æng÷^¹Ì¯ csµ4} û¶ª×fOÝù’EWüvÕù¦ `àÕ?×ï?®áã«´rÌˬðløRWüÅ•àñºwÀKpâOx¨òl”|ÑVÒTwHi,äeÞæ[¡ù–·O3«Ù,:ÿCo­¯½i‡Š75}.›üTÒƒ0ÎÓZÓ†Öôp-Õûb 6þWÚª»Ô³¼(éÿ[S©iC‹£-µU„T{3càÒ¯B 5 (ÍÖ÷%3 ç…2Ê»–Z5äê Ž%7|¯R@÷ÄЕë4]=u&0àsð&‘Ò¢ó bg=7tM[]ó‡5m€Q¶ÌÉÀI tŒÐ“ Ýç÷uµÏ ™FO€F¥rNxF!N’i޶ ®pHŒÝHOr8Ël1•\²ZÐòÔÞòšf%¶@ „u†¾ï;¹¿ lÑ©Îg`åêq’tŒ#—Û”`ȳ †<‹`ä±ù‹ë¹lªõÜ(0ÉŠû÷â2ã endstream endobj 339 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 336 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 339 0 R >> endobj 342 0 obj [340 0 R/XYZ 42.52 737.53] endobj 343 0 obj << /Filter[/FlateDecode] /Length 1139 >> stream xÚ¥W[o£8~ß_*A HHª®Ô™v:—N3šRõ!‰“"@Æ´éTÝß¾66:#í>áËñù¾sÅ– `ÒZª?WÒoôi"MÁt,y±¤Ã10 šÀ4%ïb¡8@Õ-ËRîU×RpPª' Â¥ºò¾J—UcKÏôÜØÉœ JÉv 0†bšJ·5Š+¹…­Û’Î? …¼(B±ª;ÐVJ‚«Ôú *dÔ‡¨Ðk½DqL¾êÔ«Q^=¤ˆt”M@p²åã…µZØ«ÓF µhÊ- b?Ø&¥/pjéc¶2 \&¿/d‚-ÚµH’‘.ºO5?iií)?ÀÈó,C!AסòÖ·˜Q-ò2!Iž!,°Üsßà!a%Û[çY’oAx§É‚ÀÔšŽb £¥"É£<”5Ù”—êêÚ”E¿A}8°‡Ò”nï¿\ñÉ…ƒ ÂG>Ž«,dÊ}ò(ÌÕR~5Ó.< mÄRYª¯*õªc( Ÿ¢ÞÌ1×dv=ß^Ìù÷fó›[ïçÝG1½ÿâ}žß‰É¹ùðéóùÍÅõe7 ÎŽ`$i†~-™œþóêîûå×qpK#jj&Ü]_ŸòáèX¸ò1¯Òˆ3ô„0>_¡- +šn"ô£>žqº0¾Íè~çÇšAãôžÌ­'¡N.•¥ñR´^°£¹9µ»JeY®w   Ý=ÀtBáxFžqŽ¸Þ“;å‚5—™ðUóï¾úþkT÷²gW‹Ï´cr#µå¶Vàœä¬\µ¯KÖõ`’­—êl°»%MQ³Ó N²ˆVæ€'i…þ­›³a:"ºÁn~yçX˜GHãðÅKlèhIVTDŒóŠÐ Ÿµ^k‰ùeÂ$HËEmªç:l ‹Cœ‰ZÝùæ'„6$Á£s\·ÆìßÓ±©õrÇÁ'‚Câ®p àL»TÐ6Dá<¾¡—KŒs<N틾o+²7¿˜Ï¸ö«á3¹ ¶H@ 8Ö`š¬ñ¯¦sá°Ø­ÓNڬŽÞþC:á`YðVaw"ÖJVíM¬l ¸ÖNYD¥XÉï"»§ëu Lj ÔÄ"Ù¢ÔÏr¼ Ry¶hÊg/Ž(zúÂUvíÇ´ËþhíëÞWhj‹P¤éÀ–õv:Ù§<‰Ú°t9óóK¥¯“Ö%ÚšÚ;Pä©qØZIû?›Ášry—æ <¼=ìußC{Dgz§ˆ„M‚†]Ch‡ÞônZN€ÓÞù¿˜MßÔä^Bh ¹ëOûî”W|Æ™Û`²W&ûjï= Yøu`Ï’ùL@­8–ÎÁ:¦ ùÕË~z;ÿ/½ã $C©Q¦ùóŸ“üðž®OL›z³ÐÜÕ»/qN€É/‰ŽA¦1†Êyµ®JÂ^¶m? aRs<žN•¯âùðCu¡R!{J@'ëGº üþúl‰ endstream endobj 344 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 341 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 344 0 R >> endobj 347 0 obj [345 0 R/XYZ 42.52 737.53] endobj 348 0 obj << /Filter[/FlateDecode] /Length 800 >> stream xÚÍ—[oÓ0ÇßùV$¤%Ævâ\à ÄEÚ “ÈÄC[UY›”¢¬­šŒMûî8¾47§-…=µŽ“sþÇçgû€ B`øÏgð>~ý)Œ|gÀ#ô@0ÄÄF&…–㺮ùÍ ]s›l6–C3ÝÖ$¾cfÆwÀ!ô€èp¼AŸÈa¾r/!¥CÏN5íq/?×˹åP♋´œn–÷i>]­·7I>ÍŠj‚šcSüÎ×·×y*þ/Wóô>KŠÒ˜+òõÍ•bBâ1Ÿˆk`>ë—=ó•p†í¦ùhŒË)wl=rëNÈÂ'Â:åÖg×Ù4K–ù*}ó&°±Y¤y&õ¹~µ€ }upu(J¦R¶“1¶Þ !˜RH¢¦’'9áA̲ÌF"³†a؆F•aŒæÚìt°×µ lLÄˆÜ £mLÐ1%Ã1äJkæ\CŒ¤«‰ðåg.a bÒ®t‘oF,\þ j®ÍKtþKHkå÷ËU|y‹Á£&ó<šç0*^žD–d.êEÚÑà_0¾oo> endobj 346 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 349 0 R >> endobj 352 0 obj [350 0 R/XYZ 42.52 737.53] endobj 353 0 obj << /Filter[/FlateDecode] /Length 814 >> stream xÚݘ]o›0…ï÷+,¤I¦ 66ÛÕ¦}H½Y¥Qí"DQš@‰†*е[Õÿ>c;‰ ¦i«N­z•`ûû<‚à#ßK ~¾O黯HP‚´ f€`„1H?!C®üéÆÜÌ..\D0ßÔî$=_R> Wü¾Ñàœû($ê²?Ä*1ˆÕ*m;žüiWqægÅt™7ÓEÞäó¦ÚL×Õæ|V:ïǎ㈥|>Þ÷óño¹òë1Bᢺ<+óö?ƒGßOÓ“ÓT^Ü=rB<’—–.2ÜÜ~0E˜HLèø]­R…E|íÄLÜ{ÈtKû±TS¤9gCÂ̽ù°ªÏÚîk1[•ëüo69ƒu^r­ÈG,Ñ×Ó·Bs§vËg®Ü/6NéV©ÚïšlçG:rl§=O,–ÇŽnZ r”Gßc%À™ì—Š#3«ë¼œÎ«j³X­gM^?a÷³ªP‚f?\c¸5™ûîm:=ÂO?ÐEšñìy3ºZ/òk¢Ce‘FÈóØsè&ÜpwwÊ5§»¤ó£KÝâXF]LlÖMö'×}‰{û‡c¨ÜÑÛ¯ƒLô82²ùèþ9‡ñѬX1ÑŒèç(ɦ‡5-^5SÜž«bV7CdÕeuÕƒ+¼?\ìþp…†‹=.a½Ë—æ\sÛ‰îµÜMUž>UìUm m`µzmlµº;x…/¯ºèãÅþ^á³àUÙBv¼d_Á³KXïâ¥9ïâö¼xñÚðYðؽ¼B¯³|v>çë&ß<áCkðMëÈxÕBŽ Ð„G&_¢‘hÅ ¶+ v¬eðò’ÅÁ£ôí@ˆýƒCå}ÞÝ0e(Ž º”•€­-íÝ;T܃}‰Ö‰»‹nÍb‹íö•Í’Hõâf «ÞÁEØÕ1ÝÜ‹0C¾V„o¶e¸^ì«;H„°|°0Âë{ì‡~¼\^ÖM[üSHèH~ >ö]‡a’ÀcõeàÄ ÿIû•€ÀÍjùË%1l”¾7ÿ}NºÌ endstream endobj 354 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 351 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 354 0 R >> endobj 357 0 obj [355 0 R/XYZ 42.52 737.53] endobj 358 0 obj << /Filter[/FlateDecode] /Length 645 >> stream xÚÕ—KÚ0ÇïýV¤JÎ*qã8§=µêCÚKWjV=„x8) + ݶ«ýîuì,8S H,'Û3óÏÌ/LxÈóÀÈŸ/àCúæs ”D ÍAàÇ(ŠÆ ý؃!²]BünS—Ãû{ÛõcÈ–Üî§×àS*Üà¸~‚‚àÜ€z(ò«Û|“Q( U”r=6ÄòÁ”­#6¼ŒÙ|Å–ƒœ[o{–eÉ@p±‡’P-d¿m7ô8Y¬G+¯Cxõõ6½¹MÕÍcmg6Ÿ°_ù¯µÐÞäÅâÁ‘±c.’á¶gx¥ÄIO5j½tòôNzÁA™BMõÏÅl¢·Ÿ4ƒG«M(¢ä?äfö£ôãÒZŽËŠäÃY1g2Ø]ž rV䎊ԔÜP‰ƒQªËÔ”) ]Rf«$ºm»'µA§¡.XâX 9½¾£#¤¼ô,=MñV¥ÅÒ“µy”ÎÝísˆøí i×ßJ >¢±zžŸzUF*ý{B/=uPT:9zžgðhµû@¿Kî±Ð—¢›Ðk’*MÐkº¤SA/Úz#Ö»_ mÇô6˜¡çuÁñXÔÕïæ§atð´¿8rš…8?3Ü:6‘›ú‚FN´›œËh·üìí64ðù‘íöì½ö„jíö„.¢yñ³7¯#*›WûãçÜÿBæµd9[²ù˜ý»u‘Ôi~ Â“™2h‘\u—é%áÕœŸÝ‡ÈÓ&èç…çz;©o,ÄÄŽŸ×Õ¬~SÎêµ¹}6ýa‹±}e»8Š ߯§k¾R'üÀ©.<ì‰é{!©ô½ú »Å2 endstream endobj 359 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 356 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 359 0 R >> endobj 362 0 obj [360 0 R/XYZ 42.52 737.53] endobj 363 0 obj << /Filter[/FlateDecode] /Length 935 >> stream xÚÕ—ßo›0Çß÷WXH“  .6?BZíaÓÖi}Ù¤¦êC!LÊF Âdé6õŸáLê¦êÔjO1¶ïî{öÇvYزÐÕ?ŸÑ‡áéE ðÀCÙÔÃÄE”`BÐðãHw±aÚ¶­ß¾­ári˜´¯³‚“á%ú4n´vìôéc›¢r| {T~¦èªŽâ#_F©údÚLÝ:Š6›ÆgeP°˜,›±`ÊÂE0cYÉŠ æÚÙHÓ´:&ñ±O‘I¬Ú™0þ™'‘aºÔÕyëQ¾š¦ fž$YÄîâ—=èØäi¾îÕ"¢ AîÃdG?µ«-'Ð_yj?¦o©º«œã0I3ö{¬?¶c‘\÷ f[|K/q\ìûª`E#X¨âÆÆ9ÈSí@â= Ø}ì¹j¿Ø‹žvp¿@‰¥ŠiêºmrФ$M]½MF{GÒ2vj»Io4™lTØûýcPãñsQãñ¸“¦Ô`cŽE­vµµÊËóQ«ä·QSÄ·ôv¡¦X¨âž„š{ jb¿¶PóºPë„é0ˆ Q½.¢6Ò“LH/X,“;–<ùÍ4vÎ6Äm˜·âºMÁÄ­ýþz=üv=„?{ ZV }?*Îw—®AÜé²뫌'óŒEÍú•Ðïd«Å”[¤ŸÀG-ªá“8˜Ðƒ„vFWàÜ(ƒ4œm-ç}ƒ^+tMX×6õFÚHp+\µçÚEš‡2÷ÚBÞ •ÙÚO¥¢º9ÿ[0êWêß²á>‰ö3y,^î£xÔ/ÝË".¼ƒ„x¯Aˆ{$!Õãòš·Gûu{Bªêy„ìr¿Û5KCÎ!„È?b%›•y±®þ±³âlÿ¹ŠX Pž”Ak36Îö¯r5ˆgy$ŸÕwò¹”ü™ÔÇÔQýŸžÂÄ!Ke^W7_>C+ËeÖe¿‹ðGó²æ/‹U¥:â¦QÞ2.'åÓï"C¾‡üLŒÃUZnV#h–#¿çO³ÚLUÑ€<šÙú¶ÙP!W+ç’4._7i‡4¦«$Z`{wN\ùkÉ6»ÉíægFÔg¤}d–9OÊ$Ϙ\߇ï=9«×D”ðeÎØ‚5ÇwD'›ˆ³b{à|o­hö‰‹-¥Zl:šzQ­J¥íc¼»Ž(D‰åQýýj¾âeU¥::uzP®R‹X†I> endobj 361 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 364 0 R >> endobj 367 0 obj [365 0 R/XYZ 42.52 737.53] endobj 368 0 obj << /Filter[/FlateDecode] /Length 1157 >> stream xÚ­Wmo›Hþ~¿‚C—  €ÁoQNJ7m/Ÿ¢|0"xp eÝÄr¿ývÙƒ¨•N‘â…yæ™y­ kº.l„âçJøèœ| Sm:œP°Ì±6 ¦¡†à\.%[“Õáp(ÝË“¡„ü,“Us,Êå•óU˜;Ä%< ª9Õ¬±`Œµ¡)< ÖD×F&Œ…Û"ÊD˜ð(æHÛ‚J·­"Jý˪mÚ’ÿ¹Â–Q²†¶\š«Ó"¤Jä¬^ø"gߊ×:{e¯‚‡Ð[†§ÈË1Úø´´"©MYjx—ÁBêßê:Âê;^ŽBðñ+‰þ§ë4Ñ]¹ak2[xÁ¬{#¾žœ° Ä1[ÝÞ¹b+œr~0öƒG¶·I€£4É›&øØ‚¹%è ,ÆD›˜uì\É•_eÂ¥­K%š  ØLóci†Yç»4¼\°ß›…ÃO.nnowüñþ‹óyqÇιÉÇOŸÏo.¯çõ2Ž*x¡Å üp©wþíêîïùS#wo€$špw××§ly2àD>¦ÛxÍÖ |Ä–œ)x`‹ NÚMÅúLåÉïIü·ŸÅ"~É ôqØ‘lñ€*¿®”CºòAæ dCS›Zu—¢(;æD3Ô—†I0Ö‰g ai®Öìy€SfXæ2O8OiÈ~ë´+S:nõM¥¾g2YXŠJ@{ZÉPŠS*PÅG›\!ª"ìEÉÆ•g…«Ã!•2¦§µ ¢Ç‹D•ªÆ¬»¼êEÞ#Åh×s,H× °àÙ.ñŸ š]ÙóuºÅä­ÏÚŒyyAäÇù²€¿jW¸(ÄŸq…V¼<£“İØ,ªÂ`Gt>×pﮑ{ÌÁÑHŒ[×ìiý¼a†ã/ØÍJѬ»¼qÊ-Egq¹˜•J`iÏÄ}™yã 5{XV5ȰGQ•:8ìû`X{ÊŽ÷Ý^BÔ2·§ íÄŒ «V«rŸoS}—Uj8Ú@( ªŠ6ü¼¶ [ô(M.N?ö_°ä=ì0x)ZgËR> Mñšy¬ÊžSäý”’òè󃇴jÉò›öÆð·T!®4øÃØO—CuEI%ЛÅ÷4âá½Tö¨ìwPbkaZ£«–àÄá¾c0¶SÜñåÚÃdr“ïx~XxïýŒ>Tá;¿I,¥†OR6š¥ÔwÐnÌ3WúÝ¥¨³£A¤+?µw+þèç°ý½¾^\¸ò[*Á•Ù®ˆ¦Tà”ÒiF²ÕȬ"WmUí­÷£uØj¤Ùñ]A(Ë•²› .ò^šI\­”¶ND‡€ü Sôäã¶Úì_U [}ÂÿIm£^µÕrhʬN¯Ìz”S ÐÑçmówtÌO ­‘̇úgìðÚ¡Ž [ÓkòEyõØ_pªä¢c°vøÊ¯8ÿÐ+NãºmerÛ!Ä£Ñt"o7Û3 ÓRøB7tr)2ôÑP²mŽï·ÿˆ2¾P endstream endobj 369 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 366 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 369 0 R >> endobj 372 0 obj [370 0 R/XYZ 42.52 737.53] endobj 373 0 obj << /Filter[/FlateDecode] /Length 991 >> stream xÚ­W[“@~÷WŒÄ5C,L‚ÆokbL4±Æ‡B°C—„2Í”jVÓÿî03P(ƒ—¬éC[Îí;ß¹0l˶Áð¯wàÕúúfB+ôÁº&ò-Çȱ¬ßl géær¹„_õ` iºßë&ZALz¼~Þ®™|gv¡å®€³²–ì€Ø–äß |æQÈ(žk…!0[±Ë£,hQáZ7=äÂí— e"HqZ%¡»´‰ôç<ªÍLm–…0‹àc¦\4ÂZ:‰`~—Rñ{é»´ªHÉp‘Þ~„ðgžI‘–UDðõ«›äå‡_GúiÑã²:ßßóhƞѹU d¢QvÌTh™(°;tšZ‹G&£Øjjšfh[Ü$,)†bE36±±Ñºä]¸`4CÄÖÊZ²$kqlt1—È VÂyËÈ…óì¾Á ¡·˜jÏ6,úéUÎØ)ëmBŽÍþØ$œð”YÊø\PF$ž3œŒ08òiA13Xíc_ô¡ˆ.òQÚœ¡bÌä¿3IÞÇŒE3zpFçT5deÖ3kNJ¦ˆ72vÈs0´Œ(ƒþÍ ådÇÆ'9®ªä©Ž;<1¶‘C±‘¯Ø®îE´[rÌ*9‹_ÖŸ¾¬%Ñ#‰pxzè)@F#­`ãÇ2}„ñ ÂŒ:c†’ˆG0:_ÊÿÇõ©"žôŒÝí²ÒÚBßT$•5•Ê®)Åy¹§¼{ZW³«óßëš²ý@Ulgs‚\T}0ö\íïæ½ãfV¶Mw;.<)t¾Õ¼™V»àî¯ÛíAÌŒ0ÿgZÆp¹l†6T¦§z‡ÌÍÊ„.>/ÜÓd\äÎä¨úm¾t<[F¶cåûcN݉UÞó9u¤TïùíM»7YªIÖÏÞª#ÏUék¡ âI“ɶøÓ^9/èÑ^¹þÙÝ2u?Ø6.ä€ûË` es‚|NГ¬t'éTÉzâ´X<ˆ§o§ÓtæUzg˜-®1-óïíEÓg\×q-–g$)ë²I’pUDºÔ¬ yj…VNnñèLÒíØH8:`__ ÷ŸY&23RtçDŽOž@uÞ”¤V_uÌ•ãYöà²Ó=è®;ÃK•´@+Ëœx>»G9¶àËãöxhÚK– ‘kˆÛ²›µ¥ï‡!|/o`ŸôAþµ·1i¹½ÓQ‰ïÑ/æØz endstream endobj 374 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 371 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 374 0 R >> endobj 377 0 obj [375 0 R/XYZ 42.52 737.53] endobj 378 0 obj << /Filter[/FlateDecode] /Length 1288 >> stream xÚ•W[¯›F~ﯠT®°ææbûÈ•šÄI“6i¤Z탱,^|Pl@ ŽãFùïÝîÆ§ybÙÝ™ùæ²ßìJº¦ëÒ^âŸ7Ò‹ÕýkWši3GZ…’eºšãJ¦¡†´zµVlm8žL&Ê?ÃéD¡~šǦ«š 7«wÒrj,é,Í™f¹’ájS:JÖT×Ò_ÜÊTš¢6oIcñaV!ñó%ž"û§<Ù%¬Ê†ì ¸öê\öʲÌ''¦6³Ä‚Í2rµÜñmÚÊB|äû{1XÆ;1HBñÝ“˜Ð(?á)ò(‰3Ï‹…þ±1Õ¦fÝòŽpI $ómì.³é ç\ ¶_¢|Š…~ŽÉˆß»Ú,‡üŒÅ3„^XSUMi’'ù%%ªO÷™ ËrÅû^0é…É5BÃ5i”¤?`¡Ã-ÄÂÞúOBämœš‹±Z’ã‘Ä8&T väñ´ß ñ›?EºÐ(Í»ªØ‰ƒLÜjHÅpz ÛµñIÝÖ–½§`ŒøŽ¦7"%Lô!Â,±XVñ›\Ãg)w@B ¾|4;®)²[Ž–ŠF÷€»,¼FXʺ¹[pÁÿ7¹ëoœäÛ09'wê]m9½tü¯`«"é%ö⇅.=å8NN9ü4kì1Äs¶ÍRDþ![óìlnøZÅ™'µ,î3r(T´/, ›ªíXšÛ(úò”ÔÈ]Q·ÎqMÌ©ÜvþÄ"ùü\–”&´'f°[EHŒžÓ€¨Y.TË=eT‡ñ·8‘ë@Œ*¶bòx ÇfácŽdÁ.]€x`,ÐíÏ0‚±X/i$¥òr4É*×)¼¬öb&ü(#=ˆÇ$öøÉõ†‹…¹(u6¿Ö7ZÅ;FqO>~ûeÜÞçyÜÊ 4¸%pQzjéº2GZl0=/3Ùµ5sv%ÑaD3 ¯é‚$qÔ*´ 3ŠQŒ“QÞ=è]–êÎ뺖ł¼Q¯ž“~®©qà`P‡4|C^d±Ìè)Ÿ“h ºŸ›û‰öªÂ¯7Þ`î‰ÄŠ™}hó¯ýŒ0açm›åpqÉ”ǰýL+WƒïV¯'ú ¾ß@ÝàÛõ.e'çV%Aß-[pRœŸba¯{Îá뉼ô’ËUk70»C¶¶¡¹ÀÄpýœ™…cǵÑË ™|Žï©»£±hàÑ2á8³ P·±˜üë)/_¼Þ~øsõöýÇ?–ï—VËWàtü¹Ò›^w.¬u"üÍÿŒp i`zŽ)ð4\­Èn.÷R2N“ùbGqØ4.7.9õ>áy¹¬f=Ü+6v0Õs‰îÂg*‹.Á 0%´Ñq —<¥Ê“wÛ×oØìç¤ÐÙg‚í. òòþÛ&r¶#kØ,e´Oä’Õmv.ŠP.lw3Ð\cµ’P¯[\suh,Ý– |[ÔØ\­íö5â Æª:û,`s\Å*‘çsèüüRŇX;eS¨MVèúHèå >µ4ˆßG¬Ös”?¡ñ,t½ŠÂÂ-ÔV4㦠7üq¡Ï¯>KÇ®akzíaZLOÓê\JÀCØu÷ŸÀÙ¸ñŽöOCx  ÃqfSå×ÓþÄú:ÛaZ*tCÆ2tg¢Ø.âûá?˜(ü endstream endobj 379 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 376 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 379 0 R >> endobj 382 0 obj [380 0 R/XYZ 42.52 737.53] endobj 383 0 obj [380 0 R/XYZ 42.52 275.8] endobj 384 0 obj << /Filter[/FlateDecode] /Length 1302 >> stream xÚµXmoÛ6þ¾_!¸*-Qï< Ùš¢ X€}ˆC–h›, 5×ößw|‘eIqR,i„äéøÜ ïŽÇrcgÈá“q{¿¸‹Œ%¡q¿5l"70°‹\׸ÿõÁ ‘e{žgÞ¶´Èi¹S«Ú‘yâûªTkò“²¡UÙ¨µ­¾'bâ› ám­h+D±ï¿ïA ß8‚Ôù‘áFÈÃÆÁðc…X/ ã©clÄZÇ AabØâ³/u¬-¹e80g5«69¨Õ‘òýÍl4^ñS­¤Ú®/Œ³]GâÁþw‚Û7? ’²]{ %oÔrË*wj$’£@ ÂÙéFR'ð§‘–#ÔÔå+s&~­÷±'X‚àô„9¬§B'ÐjhPÑpF땹²;Oµ=Ó\j åÙlMyTÃ;Í&¶ëifD3UÛ­š2øã©Áàl>€€=Ÿ_ÈŸŠ²|ËHͯøtŠž•é|Ãh¸“¥´¹$t«¢Dh,fKËÎ%Ûl×û´Ì ôóÒ¹¸î~O;'7#çËÜŠo¶ @»uó•d|lµÒ¯¶>²´® Cb\)ãû8Ÿ %çy•‰£+wÃȹ4'0õÞåRZ²#|Ý–”¯3R`ò>$'¾Ü{U)Æš4ùì%Åì^@ð‚rŒdв´x­Š#¤·T´y/6?ʋ͛y±y½µ˜ªä´lÉ•BðLæíª’V {Eöõ Oך¡ Wd^ð¼µ/Ö™äg¼z­ÄuK;Žm玔„Ñìÿˆ±qŒ°oØFqÔƒ¥ü¦ÍÊ@ëœfü)ݪš”Ê©ýÁv[…Ëö>•('«kç/ŠHVåD\¬OUØ^FçÒg%Lü~lƒJÑgÑGYüýºëcº >>Ƨ‘¡ŸLÜa¯æ›³eÞµzlyÝòq×uHÿ"ëúÊ ú4›*{ ¹‚èGþù›°MÊéá_É¿¸ssû8pâ ûa׋Š.3I!ÚJh…}Dð7ÄÈŪ¶l×)½pý„å9ç^8ò‡½0|·Õ za˜t½0Lû^xq\*ˆ¡9÷¤ÌÛ´!¹àvL%Àí‘a¢qNLÞh¶íˆ ü'؈–f{a¢Šƒàúåö® 5?Z86õ¦#- EýÚ6\Ñê¶£Q­Jª¡®  ,e'õõ,­¬„ˆ#¼)ß1ÿ´bp×4²ÛF€øX£Á$§ o9-„‰¾gB¨±*ÍÖ)÷ŃóK¨™ôv7‹»ÄˆPÉW„ƒ\˜WO¢ÄuNôçý±ÛKPÍóç]¾">êŠñQåå{]—y¥Æˆ"Ý’êð‘dZJ¿Éκ¥I"uùá÷ÎAYÅ´@z¡…tî·?vˆS@­ÿom]6²‘:«¼-È€(€åHÒÊ|¯²÷ý\î Ç—ùÛ€ ó«¢{ÇÌäYVP5¡Eò…ì;À¸‚õq®¯ÞðéÀY eèPS(zâY>Ìì]·aP=t ÂUÁÈÊâVJ(2âÑÍJ™mN$ÜÈ"€Ö_gúÕÝg>F^ðÄYÜö!BùTy°ê¦[Δgs°}­NÔ$s-cüÖ¶#7@ÎÅk»#tïíËÿ è8BnÔ% hë„ØüÐîT}€W>öçê×Z†Ib~Ñÿ@øÝб)çX$>6ÝíEs­ßOÿøÚÌ4 endstream endobj 385 0 obj << /F7 73 0 R /F8 86 0 R /F10 94 0 R /F6 50 0 R /F5 47 0 R /F9 89 0 R >> endobj 381 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 385 0 R >> endobj 388 0 obj [386 0 R/XYZ 42.52 737.53] endobj 389 0 obj [386 0 R/XYZ 42.52 692] endobj 390 0 obj [386 0 R/XYZ 42.52 111.27] endobj 391 0 obj << /Filter[/FlateDecode] /Length 1246 >> stream xÚµWYoÜ6~ï¯P}ÐW¢n.ÄqmŠz‹>D!íRa]Õáõþû9ÔÞÃk }‘Èápær>r¨™Ä4µL“¿ÏÚ‡ùìÎ×BzÚ<Õhà[£±,m~û]÷ÉÔ°m[ÿ0ðbÉ« {qµÄFϺ^I½ÏJ[Ö E¿ÑnâÅ”zúãÔõô8cÓó¯Ú§9øw´•fÐ8¾fùĦZ©9I<ªº…v/áY¦(|bÀÑ ü €u¼Ñ¢Ðõ4Ë‘c©f8ÄõáëÓÇ`¦†eQg7ßUÁ@cŒèÈ` ± tE0¶ Áxt fvçnð™IpíÞóæ8Tïkü'¯hŽ+èà â(¯PRW Y‚HïT«Ïc¥Œð@ÔÕC»P¶FÇÑ„Wq»ÆÑ2îa|=÷.š"î`·å×t²â•MI÷Ô 5Ÿ„¾ÐsØ -ÔÜ0ÆáÝýq‰;ŽGÔs^ú1ðâÁ"QbÚR«V,™.ìK³^$©ÜLÇ”S@£ˆ{ö|V㜠÷BË'Þ,Óò¬•×±~¼Ž¢fÝçuE±…Êø‘=ÈY¤Y ‘«ÿ†¿ù·Ûo¤î­M¤¹¶ÎÚXKyÁº(êV<ƒM2,bÛÂ>aÏl‚­c‘~Íi¬ë‡fS¥­4l,ê² íM ”XÙôô¢Æ‰NŒ¢‚'Df”A 8Ú,‚²I‘ýõéw´p ¢ŠêA°Ç@ß°Û™ôÅL÷â™ö>!lÑ]Ö 2.ˆ±ÚÿÖäI!‡ãnÁùfc”=ä¬hÆ$Úcä^lãi¹GIê”B‘‘“‚WÃ3éòCöÃѶerŒýax–ý¡Ùïüö»?ÍÆyö{—úYWʱÊwéã‡;Á€¼/‹=Ú+ù â#œÓÇOA}åó"Ö¿Æó­Z…î¢CÊ7;„Ÿ‰¨d Ü W¥5þ–r-Y{}–V¬Å ùUöÙ2ÁÆ,)x×Í†ŽµÝ ;ñ²œááƒýÕé@) 3¨áÕðarþãoô³±Ï·#…”d-ÏrE;jšµïZ±þ¢u_§ý*nUïN¬GÜC^(F~©äèÃÍðŰótããmû¶ÜÌ >±ðEöU=/ÿœ¶®Úÿˆ¶@+ö[žúû!äK 4¨s¥¦eÂ^Z¦gÃé¤ðýòoïG endstream endobj 392 0 obj << /F7 73 0 R /F10 94 0 R /F6 50 0 R /F5 47 0 R /F8 86 0 R /F9 89 0 R >> endobj 387 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 392 0 R >> endobj 395 0 obj [393 0 R/XYZ 42.52 737.53] endobj 396 0 obj [393 0 R/XYZ 42.52 222.4] endobj 397 0 obj [393 0 R/XYZ 42.52 134.01] endobj 398 0 obj [393 0 R/XYZ 42.52 75.13] endobj 399 0 obj << /Filter[/FlateDecode] /Length 2075 >> stream xÚX[oã¸~ï¯Ðzû ±,Q².)2@g& f‘ 6ÞÎÃxaèBYldI¨8Fÿ|yHŶœIºO¼“ß¹ŸCölÛØ²¹5>.ç7Y‘o,scF|ËYıÇX~þnFÖt溮¹,Xµé°¿+X:%Yà0n)vÒ¾mi%Vx¹SÄܲ®ƒƒÓ?—¿×KxÓ3vðHdyá–KŒ­á…¶å5, )4B ɳ1Ëž„tûùãt¶ žÉ:Ñ.̼¥{]óà¹ÀaZ?Ñ–f8HöØòBm¾ýú‡êЊ¶q‰ƒû>)<Ù¿c)­:}[\©›öu¯f€rA™ ðl àíh™Ö[Šy­qµQï2>Ü7¯[ìg¬ã-KzN5ò†QE^Ÿë«Œªc)myÌ*}¦ÊguÕY‡¨Õrß(H“®¨wÃ+{ÎD1Faí47N½r3Ò»,hK']]-¥by¥nÑ´qÅÕl®‰‚–9öÂ`.aêc““sâ˳ÔÅÓÊ".ébr¶é½Ðó¶ýY×wtV²ªžXÖjWæ&KVS¼|PîFZiöi’ŸÝÃŽñ´Fû¸ÿ_#ç¼_¼íÔí0E¯ìç$Ï󌄶âÇZ‚·º'^sB4‹â&æÅÛG‘› lè”Ø¡µv-#rIBùàlô",Ì׋L–kì+s‹Ý«SroX•]?s) ‰Th4ðÕTcùIþúÇÝžûïXnGŽ g늱"üÞ+sâ¬TÑ›>ë(™·µÂû³­‚Ë;tÊDóNÞÿu1Hû "îw½¨ñNÔ-pŽÁœCrqžü¤ÏßA·p¥]™C[8åÙ‹ÄórïÝD‰ŽŒ‰D(r Æ^aHúçøÚÇe¯XÐRÞ·•Žô:=ù»s¤È+ð[ò8þ‡ÖK‰Þ÷Iž¾™•]$ùZ¸–µŒÛorü=;ÈAWÃQô·¬yצsÁó3¼Ó!íác<Ÿ`Ü<øÇW3h"¹÷Û4ôMб¾:ÌŠX ž¦¨åw$ ­Úºg)^$ûq%.âBh2K¯’Ñ£¤‚˜Ún\Ê:V¤¾©+²Jj½m ¤¾BeƒD=+éÒñ>åàõ¦c¦½œ³Q¯LÈA…7$eùº‰ÓGšYÐ\àÕ¿>Ü®?¹½~X¾ÜøzH!ç´Ii+"”V›©°ZLÛ9ìÜÊéÀËá+±¤ Â2»+ÇõIèØ‘%íëµ+3×¼ƒñB;Ç3­‹¯+Êäk-ÔD)Ö^èƒ(¶Ä +”uÇiƒ’æE[÷›â$ãLuâ§(%}Ãñdí8Ô’ xÏG\xGfvª¾ Xߺ¶¬o>¬oa^Õ·°‚õ-¬Ô·‡d Ò#+t3nß5u‹P}LGÄDVãSn nÚæo‰`Ä«ûN>»vb†b?­û2Ãn" jX¡øçbu_­Æ ÅfYbŽbÈ~ÒèCi‡ÉµØ)ë]ÑIÅ»M…]>ªeW”¥#ób ˜õ§¢ªE¾‚`(OGVicmâ”muÏ›žë‚mK»Ó ¾© Aª'…Ø ìndEÏõ±¡ÝµqÓ€ö‘_cqï Õö!‚מý¡’ù¶cF-[kÙ4"¦âñTæA~ À—½@×:Ž„æˆVë¢#¬P´±ü€ˆ*%®’¥0hÜž–þ¶nAå<×3¯Ÿ¤‚¡£îÑ¹Š ¶‡&ê˜Vz‡kx-粓gZÆÕ¶x ÃmÇ®¢¯˜ H¼èu=\qjÕŽ<ñÂðEhù®b¸å(–ÿ.ó|a¾16°Ÿ@A¤VEÕ#œåDú¾sò­à°Š&Ahb!e‘(´8|Úãr¿A.BDkãª+eQƒu® ªÏJ ãà‡¼§{dM£D ‰|÷ì‚×öjåN wa~áêh£8‹ó…̼@ùP 5b¼=ÍF±¬ÂÞñ/ŸÜ"!ˆ%ô-Ç5¶0Y¶7LàOßѬëªrGzœG©2ŠŠgÈá¿£|µÃ6éYÉ~FˆÞuõeG†óŸ>Þ”,!ÓöÁ§U)ÕtÅü aŠ~†sFã6Û±ö%K±ÎþqÎðnöÁ/§žÐÿœ‡_¯ê ,ý†~ƒ868æõ›^Ú˜)ñ.ð¿•ØÒ±ø>$ÿ¨ÚûiHL ?_¿‰¾¨È1óB|ûuªÚÖ endstream endobj 400 0 obj << /F7 73 0 R /F8 86 0 R /F5 47 0 R /F6 50 0 R >> endobj 394 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 400 0 R >> endobj 403 0 obj [401 0 R/XYZ 42.52 737.53] endobj 404 0 obj << /Filter[/FlateDecode] /Length 1152 >> stream xÚ•Wmo£8þ~¿‚å¾€®ÍkR)'Ýݶݮ´«Ó6»{w¥Šp·!ÛæßŸßH î 6xæ™gÆ3cl@¡±6äpgü1¿º)˜FÆ|eø^`hx dÌß?Zd»Bh}!8³]ß÷-¬†Ä 㜈y`-qMôjY¨1¥+/]®@j?Í?7sn10^ ×›‚ 6P |ÏØÁ‚ÈÓ¯¹ñ MŒ‰&ä Œ W,’Yí9è¢!uƒ@µ7øÕíÔˆÁ4 ñø‘¥l„Ô*‚<„€7ÕˉJ c/ŠAp’ˆ¤ÝV%kl7ôKš–Þ@N ‚i(EÊå3IµÈL ¡’‚èYNuÃvi“X‰­~UÃíýߟnºˆQ0ñÅŠæ$±L®èvíñ .*œ¾ ð©é(CŸîïïïnæÿ ?ŽöJ‹l‘á/ó2}‘d¦+F í‹y[îŠÌt´~Êßš£z-ôSÍͳ>Ô$çC×*ãØ5û/ae³Q¢µ ¼%G*´…ø>îHßë7d]²ý©¬²®W)©{»Øsü(3noU2¥L5óB kN±£n_Km4o4ô¡eþ©ù^›uÎn©îÑ9:Ƭ]–ÁRø'vÆ#Ôåö™Kq^=-gh–•¯õ¬Bñå2ü.Åá…ðjZæõ¨j“Ê|·-ê ©-âËa„mÀ&/Ëj†.¦”´5îÏë†æ:Ôì$—KÍÁ?ñ‘#¶k˜‡åË5¬„E¤fIbJç[Ç”_†Ž4<É o$ykNCáv„ yKIÕœAZò>÷¢}Oh \ÐÒÅZÏ£Å&Í>Ý~ípÑÄz¾Ü6Çw{oŽÇóêù,åÀzï<Ïv±E³ÿ½û¡Ü}ÎfP £MD;ø2†Ùì+R®~à|wà±&Í¢óùr] aN¦£3´CWJ¸#V<üü\lo¶ÇçojpÑ™=œbv£óI ÌöïÞ¥|ÝõÃ5a˜1¼_àZœã´X_LÁ?±ê ']FÙ@h•“â R¯6Q/Œ‡Ÿ–Ðú¼ÛFÓ¡¬×FµX±rÛ:Y;íׯ÷Eã{c$ôÌÌ4Þ+eDO¿5]후øiºf ÞàŠü4²Gxà““=jéGøtå‰w=89k]`DŠ'Væ$–çCèˆGb·=kÂK{AäžM§q`‰ˆ(Û[ÜTyÙät©K¸æjŸãåhx$ˆ\t[oD¿Éœ[ZÌ ðÛLü]%A_Wij¹8þ°¿ª„¹—¬n+Ù™ôèVå?åN¤Ý¨¦T#Ïÿ~ ÉÜÓi4Zµš“j¿kæ±Á].$¯É ˆ•Sƒv3Úh†ÿ ‹¦'…ªÌ†&ÃŒR‡Õi·ÍHžèæ¨M^^Ü…v®/í‡ös¼Q4¼ Xâê‚ô—=ñ-=ÿ.挮7¶[ÜEÓ‰õûn½«%᎞@m×C0òõ ‡óûå?¾oÚ± endstream endobj 405 0 obj << /F7 73 0 R /F8 86 0 R /F9 89 0 R /F10 94 0 R >> endobj 402 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 405 0 R >> endobj 408 0 obj [406 0 R/XYZ 42.52 737.53] endobj 409 0 obj [406 0 R/XYZ 42.52 656.83] endobj 410 0 obj [406 0 R/XYZ 42.52 423.84] endobj 411 0 obj [406 0 R/XYZ 42.52 124.72] endobj 412 0 obj << /Filter[/FlateDecode] /Length 1657 >> stream xÚµXÝÛ6 ß_adU°XgùÛú°v½m}†6@–ÁPl%ñΙ­4—ýõ#E9u.éö‡;KEþH‘ÇãžçlóùÑy½¼»OœŒg±³Ü8®Ÿñ0q|Á…p–?üÆ„Çý¹›e[ÎSŸõ§¹>Ó~C¦Õ q0½S4ØvmÕ5J«žXd[ÒB ´Bwýü÷å;çí„ÎqÔ(øNã„©ÇcßNkçƒÁ—:©Å‡ôÐqéƒø¾5Ò< y†Hû¾jT䇬¬ú[ͧ<mëÖ¾é•Êw±V+f¿†ýî^xg­âW~& ¸Øˆï…£Nc²­!à†1=<‘.÷{ÙÃÉ‚ M»Ô# Pm1îÝi,tGϹ2Tívôw£ÔÚà¿ Q nm¡«®åšé44}ÈròÔl‚€ÉÑM>ߟfÄœ9» 2')bØ‚¼±/¯’PD< ì:qøT™›@¦ 1ä‚€W;ëm%0ʯc Ê­¿ÂODlqR1ÈÝ }»ˆÀfÞ+Yæ› ËÇŒó;YEѵŸT¯U‰rf ïrëY/T Ç•c0®ë®xX±›¬Û €¸¬üsÝF8)…³÷–xJ$G>b”â¨f‹-ß*÷–#ÇŧmN>fÌ×+;®±¼V²!…jM‘”ÉÖsZq|½ O‹¢ 7X&Le Ãõ³¦`…t à•½ÍtSŒ1ã1²»þø\ú¨O˜8˜>ÓYC6¦1³%éá«0?ž¿/Åд7B0½ì²B¦ô$cê^\ ªU}U 7L¤O³+øzv­¯³+~6µ|FϦւŽð—)„WÇ_ÔrhÃdÍø ÌÆ-çoÀ «ùKªµ©)Dx’¾½6¤ÙsŒHYçWj«ú|}Ò*ïúƒ’k3\T4Xä²ôíŸp¨+6±„?/x5_¡iÈ1 Ã5ØCµe%Û6€!àQ8äsf@)©ÿ{®¤0£ý5B¸‘ú‹&ÄÿÜ„Qâ ÿ“C^TJ)D¡+²4º‰þV,Á½]‚’S×ù§®>4ê_¹ÿ¦¼óù"à‹/2ïü·šŸ-‚Føâ( ݼ³~½xŠ ÚÆm®ß~x£k=*£¿Pç Üi`ëp:•° ·8«>áÈe¯áBˆR4˜‘U]ÓH‚Ó›½¶²:úÊÂ^'fv¬†=*0½ŠÙj!„Ø8ã2¦°mØ÷ .¦B ÃŽ–ÿ¾¹ßôò¯Ýi'sÑlGWmwƨ±a®Ú‡/öº2‚7@©O$¨Õ<ë¡{ðº& XsiÅ\¯V€ËvÔ‹:û•æÂE4Ùg±;h³L»‰:[ª¦—1:û®¡ÝôêAš‰˜hÁ5z6 D]Ÿ×ý.^ùéå•ïWÀ[æÕ;Â[O¤®¿XÊØ`ÛŒ‚¦Ð&kû®¦­Ã zð‹1.ÛGrÁ„·$2hzYíÒ`C0²:b,° ™œd7ÑË^ סPHû:²m<µ?ØÉÒhmbXÐkÚ/í„)]¬æüæ úïˆ{“7üH_ñW¿2@[‘p‘Øž°/öÙ÷‡í~T¡.è·ß”–8†'å;N´_ñ N¿G|4?NœC™ð}ó7d®” endstream endobj 413 0 obj << /F7 73 0 R /F8 86 0 R /F10 94 0 R /F6 50 0 R /F5 47 0 R /F9 89 0 R >> endobj 407 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 413 0 R >> endobj 416 0 obj [414 0 R/XYZ 42.52 737.53] endobj 417 0 obj [414 0 R/XYZ 42.52 712.62] endobj 418 0 obj << /Filter[/FlateDecode] /Length 1204 >> stream xÚWÛnã6}ïW¨Ê‹X´¨«•" Ò6Ùf‹ÆE°Œ@‘i›nÐ%‰[ôßKrHÙ²ì Ð'Ž4ÃÃ3g†¤¤Ùȶµ&†OÚOóé]¨E( ´ùZs½y¡æ`„±6ÿea`f™VEÆï$YÑbcZ®ëyR§éŠÛ®±eR7ærþY»3\O{Ó,'â@8D®£åš7³QàÈÇL{ËC|¾®å!?Ô,î÷ÖÅØñýýÂÌ>Xxzçk3™ƒÍpÎc™ÓòÛ¨I–´ôÕtBƒd;x×mÀÂFZš–33V"Ø1Þ¶45Ùó⪤nH‘‰œpžb³Û-)àU[S5¯-a¤nI]Õ¤x>–DO%”ÄçÚò¼l‘#Ëk]ÖyÒ"áÀ.š9‡Î»û¯·L#Ï1.axæiïZÒ¼™Nd$U‚2 Í R¬šëëkPsÖ«i)ô^Rý=Oši͈1ºÀU;&FZˆ¢OĬ„.f¬ùœÀ7¶{`ævfÒ;7^Øf=3c#F¶#Â.¾ŸvM=}¦Å”¯¦å³î¨ví¶,ÆѼ*ëbš¶îÒVŰ掠¹/ÀýsY¼ˆõ¡ÜHaPæöšf¬vWñº ³„Q¶\ËU7œvÀÕ<ØšOéS[>ÆÓ~ºg\ÁÌ Ò³£Jë÷¿Í]Gg;Åöm^l«S}2DÿCÅòz? >zºMjê‡ûÈô,(Ž@ÕǘÿŠW–Ì`TƒGú·46žy§Æ&<–ë S>ÿEÒ¶óeþ¿äôN)tJLï”@'¤Äç…tÆxÈ8ßR©â[¢Œ²~!+©S'›òy'²¦I¦8¸AêºT _—¹ôŽâižld[ßKç–/cÊ7_ïn>Ý>^EÊé‰3…;Wd Ìóä…<Á©){M ÚÒ²ˆÍË3µÒOt¿+Ծܒq£ìqeÅ §z 8›c 7ÎíVqšƒ¤9:`O£®¨’ôåDý‡ÙrF ÅBöí0¨©2Ê´Òã¸ÐÙf_y;˜{J¯"ÉVX,ÇHä½bÛK5‘ ´ÇhkÕ7œøP`‘ʾ’îਖ-ÀcKoÅ’ú¥tueá3ÅOË¢¥EG»aOdEÒŒob/Rl¶RŒƒ/ì%ÊxéªØˆMT÷æ8ý¶ÞhÀ: ~ O`.år g¡Ö”¸Ö(òž’ª=ƒQ±Ö’UÔ›*îíK}"ôñ<+J Ž³¹CLΟá‰4Ô±Çaïø0¾2U­¸WÕjÁäüñD©üýÉä³Ï¯Š$}!„äö 9i>|Ð,E—NrAD–3Yàeÿ¼„BŸèûc”.GŒa–¤„MëO,}ÂÚ"ÞŸ`±yª?¾ Æ/ŸrâˆM}¢{GÛ(‡8ä5ÉbŽvØ<î·šgàìëìú—Œ$ éÛ²\}"6ɈFÐFv¢À,—5äL•û+|¦õúrÿX!öù×]ÿ‡ ^¨„ý¯I?à ìg _Ì™kHûOn×t³å_¼,}Ñ̸é6]ÓB„Ãîi0ll³¯~l®ü@eü¾ûmR\à endstream endobj 419 0 obj << /F7 73 0 R /F6 50 0 R /F5 47 0 R /F8 86 0 R /F9 89 0 R /F10 94 0 R >> endobj 415 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 419 0 R >> endobj 422 0 obj [420 0 R/XYZ 42.52 737.53] endobj 423 0 obj << /Filter[/FlateDecode] /Length 1228 >> stream xÚÅW[›8}ß_¨*Á 0`nIGyh·ÓQªÎ¨Úfµ+ #ä'a‡3Ótµÿ}mlsɶ}Ú'ŒÏwÎw³Ql˶•Ò>n•w««¡2·æ²Ú*&˜[^¨ÇreõþAsÈH7çó¹ö‚›4ßé¦ëzÚVI²¡cWÛ“TÕúãê£r³"¸žò"€œÐrrP¼™m€¿fÊ—ÖìL™q³¡kÍŤË^kv{Àºéø¡¯].tÓ>µ'1.âòˆ÷E׸jü€%z¼Àé16A±[T‚’C:Ýn0tnbƒßn@_K”`´éïa¦ëôªGöLgfÍ€l}MP‰ß´«Ò"3ðª¬Ò3Xµ~JË’¸T5²4GcúI‘ã4oÐÈÐËÓÔ×'MêëègC(ŒtƒzÂPߨ[é8´–\™ˆÌšùÝJ`–Pôˆ†Š€už©¨nªœmnb°1 ±,ŒäÜœåÜm™ªŠdVL•°#¶Ò QŒH?ã_UUÇ nçŽ÷ˆ çQ6‚ì±NsXù"18Xa¦·lÏ™¢Dù‰¯¡Vk5ÒÇH[«Fè)Òxýuʈ.¶uE¤¹v¦a’¬¨I0¦0äpá²ß]`;ßI°QU’}ãÙó9CŠçD0þÃM»ôå=o‹êy„`¾G¨£Ã_ñw#Â&ŸaÖˆú_ô²·ÉK˜<µ¹kp‰ŽÛ¤ îíþûŸ±‘taOäBQ$DH.;9¬Wg)÷?5lía?¡c¤Ixy ImRãWü>9ŒøB^V‰|Úop-ß*f²§û4}ÙY`9$!ðî—Õè 8®ŽgtŸð-X’ÂÙô• ›’?ÙgÏ 2Šîš7: \J@NºÙ´”Q›9ã§sÆÁZ¤—NOΩéÉUÚ&Þt¾bzî‹—®x½-áh›æ)N ŽI’½hDu‰IÒ[Ùà­K¸CSUÀ-®þ¶È²â¥½ ðŠêÆiÝq©a&å±Jwûî`]óîz'Ì/ÙcG¼×ÊÔ5€ƒ}-]4'û Íô®‘±r}žÄ‹7´˜~Åkº…ð€åúr¨®.ØòÒÁ¯zÇ…Ô­JH11½üp?1íŒìåâjÌó÷åýʺéÛÖ$V×äRåøvG`›ÁÝ Ô2VH›£¹Ð9²„HK wØšˆul‚ÚÔ"°)°KyÊäÍaÝvB™´)3êÉö˜Ä´œà‘p÷CrgÜe¢§NiwwN»&8ëšü«¨âgâj’ÄÀÐNÿ.˜´Oë§m¥ù÷mÉßt¶¬ügCNó$.*2¼Þ-oã›û÷Ë·÷¿ \TE»åç/‘~ÍîYa/àŸ–«Õ§›ÁÞ÷7¿òÃzIŽÑlÝÊË ÄPæÈ•þïTÏ^J‡5$ÎÞ¶(‰rÛú±†!j2òz¢&Û¥’ü±„k‹/fu7L4\pÒl\ºpÈÆy›ÉjêfÙ‘O§99g æð9z‘®¼2ýá?:¾eKubBü×~'Í„–ðÀ#:;ÚÛf×Ô˜ýOÏ`?“ÀvlÂ3ÈçG‹Í}Ög@kÇ@ûƒŽéa¢ƒ™†9¿_þçùõñ endstream endobj 424 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 421 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 424 0 R >> endobj 427 0 obj [425 0 R/XYZ 42.52 737.53] endobj 428 0 obj << /Filter[/FlateDecode] /Length 1399 >> stream xÚÍX[›8~ß_´/Éh`ÀÜU«UV“™¶š¶«NF]i2B8‰UÀ,†IÚ__ÛØH˜ÕÎjŸ0Ÿïœãï\lÍ4LSÛhâq«ý±¸ºñµ©1õ´ÅZ³Ïp| X†ei‹ëÇ‘ÅFc}:Ž>#át3ÖmÛ%0ÈíÑ–}@9?-Þkó“ëh;MS.Èò h‰æLLÃò5ÖîìD›HXwjxSMçŸûðîãÂcݦ9 I’åˆRLÒ ø–¡7cÝîèê¢zò©jDÖÕ'p#§kÇ:°˜´‹+¡©ÉàLÎbPÀk`µÄñ‰ æ0AÊ«W«z´1ܳà¥àÆy;ì—bØ/·Ãy)†ór;Üã¼ÞkÙ‘Ê@aò¿É_RÀ¸¦e²Rb™Uxé¶å`oº†´`žÍ^Ä)¹Þ£˜Ê€‘–‘T†MŒÕ¨×u)Én —ÙÁ“*ÜÝkY„²b;hõ­P@™ú&¬=™N˜”£äQ£t#Ū¡¾\¡b‡P* ,Ï1|«i-ÃQü,½›“mùY?^ÒRâMŠ×Á œG‚5òRJžjkÁ^¶ÏeŒŽ;À#|¹Ê½bB.…F(º,S9Xdža,Çã‚¢Ìa¢àÆ%G:)1Y YÕùJ[ûɇPNÕr—¢¿K”†¨‹Ïsé<¹Í7³»ûùÐ(œ¦U2‡yµ¨ëÒüýPÖºdªÌA0”ÛŒåZýË*(¯¤.è£Éñ§ÜßofÁ<íj]ýÉ"r2Ä3ìo”°`y´Kݳ+ê«äscäï¹…¶çØ×gŒvA-‘ÓÉmØÑ*ˆd[$AyršmÉ3ÊáwALÂÊ2…sóéîîÓ—woƒ·óÙõüó¥¤õaþz¶˜ ¤*‡ &'£þןg¢VY $eZ;pÝ\°–§p[Uq8®„õ\× œ”q³íQÔµ·þ$w+†›¡…ŠÓ©ŽÎsNlF£Ê–.vÔŸx,þc\¾xî {W0üºÉÙD̲ _6gî;ZGwKøÖÕ É))Cå(‘‘|ǰ@Óð-‰#•«78Š¿ËÑìúž;½Q0jÛ@·l½†>&y›áV‹áHŽ~Æpàz} ·¼ú´²›%G@¿xKRL8VçF£WÃô9oÈ]àŸ÷<¾ DLTÈêF7„ÿyIìØÕnsǸ©Â)[P+“`ß½ ûÃÒ:Bñ¡,-e¯Ú±©{s©û–k˜»K5¡n/—¦õ àVåç÷Fu7úçxbäø ³b´Ä»bÏ›NF³rSòÎ’ÿœK90-S\;x6뛥~¿ü$š¨ endstream endobj 429 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 426 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 429 0 R >> endobj 432 0 obj [430 0 R/XYZ 42.52 737.53] endobj 433 0 obj << /Filter[/FlateDecode] /Length 1331 >> stream xÚµXÛrÛ6}ïWð‘rCš÷Ëäɧ™¤“6“¨MZÓ£IX”$8 $Kþú ñ¦ŠRì'’Xðœ³ËÅbAÍ2-K[jÍå½öËüú×P‹Í8ÐæšáĦjŽmÚ¶6¿½Ómv73â8Ö¿@¡r93\×Ó @Ò4ã÷®¾bHêÙýü£önÎp=íIÙ¡é:Z¡y‘eŽ|̵¯ m¤E’ÖÍ Ö nöÚ¿Ï]gføŽ¯?@P,vogFàZ–~}%Fm˲®v‡â®Â5¢—â)Ñ+´…yÌÄóÕu£ÑbDVCÜ%B%…Køû Š È(mË?P¶ìb€OR&9·@yŽj˜â2«ÇHý>)Ü2Ík£°AŨŒctüzŠmà"aŸ ¯©"sí–{Òv)×À³’ÖýïV®‹HÄ=~ì0KXŠÅu •–ªexQ–p’§5„ùù„é RÀk÷³‡UŒr™ÃIž l\À%vƒÐï7– G§+Ä ½ÐéA²ñËÿU5®²±\æzuDeu©Ê æt\ec¹LåÅ8hc¹Lé–‚|A1SLaJ1y+Œ]͈Í-Óþ*TUâö®m]$³ô°ÌÚéì‡}§.Ngެ’9t}ë’™CŠT޼þ²;Ê£ U"NIäQ…Õ…Õe UNIâQ…*…‡¥0‡I`Û_!ƒ1"˜ŠÍlQ-ÖÍÁ)R´Ý‰Ò²E77…OXDàhê!Oþ¼*X °íKAV;›zOn_€àu™ Ó÷I>µ‰w/Cü÷ÙÄÏ/CüÏñP§+@T/PC²î]¢»ŽáD,«jô ñc"Ô%³û·ê}֥ƢKUÂn÷ìM7(Ø©UÞÚN$[Æ…SûÂ}(讂ý~&ë0ò“0EcÊ[lûË»1É-‡MPÒKPbá̸lÿ8Åî…(^”‹øj¶ _G¹Y†›Íw¯§­¹j…).ëEÉ‚ÁlÝßËå ¹ï‰ÅÍÍíŸõT'x5ŽÜ}ºùþáÓÍûw_ïÇvö=ª<€ ]ÉúÈ;ÖžîPX0oe]!sÈü0«»öVNäXŽém»iÚééƒù•ÝXC„1½[­õ@l;jŸåŒ¡Â)¶ò›gµÃÈŒÜvBS‚瘮Êö A§|1…šâ‰§§”¨{Õr)ìò˯J°Üøì@m™ì™¶ÓÖËz0ù‚¹:'Xà ÌÞÞ,ì3ö†ªN´@–AÁc°³´ÝvSÕKo—‰îÿì^íýJf#åS zfØA<¤è°ª~7Gí¯‰j ö²qEQZÿHÍõ§ð ¡£+ïür. U1ïÔÅDOqŽ!¿ ì(*¿^½+Ó•)³˜¦çfÛ~³ùG?nf‡8‘ÅYþX`+ œZûåîÕ(yù60‡å’®xæ´¨‰Ÿè° øÓ9›šd©ðäkµjM¢”ž©wƒYkÞt‹U¢ÿÅ gªJׄÀ’±šHÞÕ™ÚäÎÚKÑÿ WzÝñ¶ÿ3$ÑÏ ~ m7-oôôÎ;§ÍkQ{/T$ÚXmh¯œC›§*ƉÈIÜW,Ç\yÅpÌËã%àÇ©ûÿ—ÐöM«õ‡Y ¨̃_ÛF脦6Úƒ IÞÀÑoÖË5?ÒòÛŽ÷FüØv,›5“vıþÑcŸg‘£7÷Žþß´\ÍœH§RßOÿóâ/ endstream endobj 434 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 431 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 434 0 R >> endobj 437 0 obj [435 0 R/XYZ 42.52 737.53] endobj 438 0 obj << /Filter[/FlateDecode] /Length 1218 >> stream xÚµWKoÛF¾÷Wê…²Eš\>ÕÀ‡´±‹æÐŽ€(ØP+iQ¾Ê]¥V€þ÷Î>hReSz°9w¾ï›Ù™áÒplÇ1¶†¼üjü¼¸{ŒŒ¹=ÅÆðüÐö#¹¶ë‹‰é‚5µæó¹ùDðš–Û©åy¾Yà&ËÖÂöÌ< ›®‡àúÆß†…æÈl…áÇŽ"}›_$mlÄš6˜ÛáܰÄc_ÒþöûÂCS+@YÕœf,]SV ­ÊwSËGŽcÞݨŸäe׸Á…­lK]–æë<„Ë©º½¹“B`s$û [ÖTŒmhCÒg óÂ(OWPð~‚dá’ ³o²þÖK±âr›à ct _UVÙΖÈA¶öcC|G8>r‘›AVà’̺ÊqC¿c% w¹½"Xš×¥úí0MiËv¸QOÂHó¤ 4ñoýNªÍR.§«w­7tÔÜö 3=d¡x9=EÆhu>Òœôöˆpч:×A¾²¿8aãÚ §<'‰‹â•( O§ÅuÇ\ˆG0|°ßª1ß½àô‹K> endobj 436 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 439 0 R >> endobj 442 0 obj [440 0 R/XYZ 42.52 737.53] endobj 443 0 obj [440 0 R/XYZ 42.52 376.37] endobj 444 0 obj << /Filter[/FlateDecode] /Length 1339 >> stream xÚ•WYoã6~ï¯Pµ/ Óº,Ù)R`‹v‹.ÐEÑ °Q (2m©« $•lPô¿wFC)²­,’›Î|spÒp™ëGcøûÝøåfý!6vl7cåïX¾Ç<ϸùõÖò<æÛ«Ýng}±·¾%JU6G{¾Õö ¡•—\VâoâŠKú8´‚¶‘ªüýú[Iûîæ£ñÛ (ÇQ›³À7j#ܺ,òõge|lÛ[m[1/2V¸¶í9èÝøKðlÏ¥8H%ÀºÄ’¼:82±¯uÞ–ms3MsØp‰¸ˆ4Š‹Np…¡¥ Nز¥ÿ<«*¾§µ‰Êh ^Ö™2é£@;­«²ár®†t?e^ŠLhe£U´uÍ¥õò\•m#/-=3Ÿpåµd‚wU–óÄ2“Äu]Ó1Íľ”/¯%™p­(+p>±>µ wˆt[ñ&±¾%öϲF;ÿþZí'ÊL¡8áݺNÁŸ[Œf0ÙU¥ƒ¯ÑÒSÜ?’ûOÀ~w§[]@Ã)ö¢!ÉÛ/ˆY´?Ÿmµ âIÓ&«yš^_›iZge“¦æÕ²Õ‹Áÿ3ûªc‡¯T¥Ih"Ó®¨v"æ\Ê)üüµç\Ö]+ÆyZê ô¾ùYeëu–Ρ֬:jp$¥”N¬ê«lJÌÂ¥4š+ú„hgyB0#îž/Qœ(Ç*†è‹”Ê(AÿX&Ž·ÞݩхƒÈ¼1stQŸ\؟蟘' 3„êEø)È¿ÿ]ª™R‘NSzÀ~¡MÙ©Õ°"“éWþ” Bóæv’ yÛ€·=¿(³S Ǽ2ý-.ï^t¶¯=dXðÜ©#ãbGã"ñÃhìñؽ#ªæmbÙÄ,ÜÎf‹ç-_ìÝl¸Ä¡.ñFX<—Xw‰‘:.ë›É<ô%b1 ‹÷ö*„©$sQv ×›¡ÛþÓ·JIdÙw½z+ñp‘„eÂ(ëHà+}õýËWãÀuÙP@ùÈA´5m Ãí´WÖÙê>6ñ ¯n_è€<¡¯q5a`õÍÀÕP'{9šâD¤è†Óèf”TÁYÖܼ*¹^“þ›þ™Ðia)¨ô%lmEK´#Z$”Š{ßk À„8?àO[î}žUktG­)Yƒclqñ¤ œÿ6£Lx¾:¬F"ÄÔ\1a†¬¡3“¬{2IlgÄl£˜çzl»ƒà£D´½ÈLàq;ñ£ðBíâ!ƒ\ï~\÷R¬ïËfÍ›]ß`6„R3N§ø¬Õ#O~YžËíí~nǾ‚\º VÝx9ô¾K Ÿ+=Àïÿ¡ÅcÛWº‰ÝŸŽ1@K H Š§pµês5IÂåäÒ} ­G¨dþ˜=p¸DU‘ „3û~©w“Ð碇ªÅa4—>›û/óªê2AÚ!‡~÷U=ÿ®0óöii|l4[aïQÏÌmÕ×p[Ò:–FÅè©·´¯vCû€+ûu2/­úK¥§-¢œŒ,(6çÞɬê Xq•9G¨®lÉE-¯ŒZ´5“Ž5ÍÌWÒ0<¸uï¦Døþ©Œø÷oÃ÷ÞŠŸ¿ ߯?­boÃÜÙ‹h$Œo¢‹÷Ú*öcæÅcŸ‚\r#ßzß{©ßh~èгÌw=†nÁ“î##Ú_ø´côªÓϼc½Wiû~ø•ÌÞ@ endstream endobj 445 0 obj << /F7 73 0 R /F8 86 0 R /F10 94 0 R /F6 50 0 R /F5 47 0 R /F9 89 0 R >> endobj 441 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 445 0 R >> endobj 448 0 obj [446 0 R/XYZ 42.52 737.53] endobj 449 0 obj << /Filter[/FlateDecode] /Length 966 >> stream xÚ­W[â6~﯈RäHàÍ…X©ZíÌÒJ«vºê0ê… È$xšËÈv ô×׎ Û}|œñ9ç;wÛ°¡mk£^~2nçï~S8 Œyjx¶ ýÀpè8ÆüÓ8t­¡cÛ6øÝšx€Nе5ô<”WDLRE„®?Î0“›HKÚ~ånòn—#f-çŸÙ\h[cèNáhl8cè¹FnŒ&6 \½ÍŒ‡ÜĘ4àèÆPþ{Tƒ+WO0%EÅeVåELT¬3¡ìyƒÌЪ•قî%h†yôÊ*Æibœe oZ/ü‹*V˜_©at¥†5Êó+Uø­Š¡3W8ØSÉ‹ ùîlE ñãm(å ªUh½¯94C«Æ4ÍS´1Ê2)Æ[Â7ŠªVjåÄ£B+¬VaÞá¤9¿ ËÅÓòÔ²N•­ƒÇë’î…‹’¦´ˆJJpÁ£qJv¾ª“°FÐQkœ;ðŽ÷:øFàéM>÷r4o7ÉRþ™7! ƒ§×ip>¨ÒQCG¸Jü´‘õY3g#›ÆQcßÃî`©í‹!Ë[ þ4›Ïîæ¿þýeÒ¬D<­¨ _¥™çÂɸÌ £<ÚEy®Ðĸ8›noù㤖rŠáœCj ûo‚áϯÅððevç‰BÀzdÏIªç±Šâ\äûÙ¦ð2ñÑ¢HÆzµ+Ì`¢¸ÿ‡’½§$1Ï5Ì#ìæÃÝÇû&‹‹/­ hêh÷„TŸ¿€‹â­Sã‹£ M°¸n쥌^·D)ÚGbtV1½2ÊÄÄêYØMÇ¿TÜé!SÍÙϳ_f÷s1ú‰o-ëd¨µwøU ZKP…°S]­„¶O7uRçz$“=|çAÇ—_ôD“3@]q¬ÎKúpìøÐ>º¦7š‹zûŠ8p¸c訊ü Õ[à‹|DhZ?(ÖË‘ÈNL'àcµ®˜~X¸£&lǶ„¹và`ªñ}÷Nó¤ endstream endobj 450 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 447 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 450 0 R >> endobj 453 0 obj [451 0 R/XYZ 42.52 737.53] endobj 454 0 obj << /Filter[/FlateDecode] /Length 940 >> stream xÚÕWkËÛ6þ¾_a< $z-%¶“Â(}»lP¶RhÊVêa[NÔúòbÉM²ýùéæ&v”¬l°Oºçœ££GG:Ž|ßÙ8ªùÙy\=ü9 °UîLÐÌ"A¡³úñ£!@£Éb±ð~Í‘×PN«Íh2"¯n¹ì̼”æ²3õbDaz×^–³eû³Ñ«×Îr%ŒÏœ]g F`ŠœÒ™Í}"3,œwÊ·¹37¾MCCg"—gÊ·zý ä´Ê’s²©›C칸ið!a¼iSÞ6$)(ã ÞSæÆ#eÜ|¥±§¡.Ú²’x!šÐl ô¥›z'D—¿,]¾Y%nTQöTà””¤âõ3“¬n×ù‚‹–Ø3nÜq^ԘNjGø÷Lh•6ßjÚ 'pæHœ ¤à ÐÌÛ ‚'º'£’dŸ”e,•ú¹ìÑô÷x¤PÞéAÕ–k"èýÀ÷~Ðs˜±¶$ºÏ·”é^׿´aŒ«Lwêª8è^F8I¹ äYԌ٤³(¥Aÿ5$%©R³eš\©ãÊÑ_¿÷ÜɆûîÁï7ª?î̪]Y·ÄU*ÚH§*±GÒŽ5H6™IÄxpÎãã9ögŽ\×ã¾zôÍi'¸+í„÷„;¸?í„ÿÛ´-iG£ÁœÖ§%¹œw._šŒæyS%,ÅU’7¸$7RúÄt"m_ݬ٦ ‹Úhˆ —PǾï»c×½yÏ•Ì6ÿd§7¤‡àâf3²¿…©ðæ‡Q„‰ØÝ¶[$Sï¿ ðŽY3'ú4E`)ù¼­RÉÔŒ¦\GÊdØ¿ìÑq \®3ìŠç8ˆï¹VÑÝá/"±V¾Ÿûå® .ÕÀýº8>€F®!C¤±)’ÇòiÑ€S\·d3øþQ¦áÀÒûG›lJŠBH£p _ÎÛ\JËL*‡â+s*þîíò•X²YùÇfABäšÍŠÊý¾µ`³¢®†!lˆãÇΜÍ0Ä}››ý¿áU—È1L¶â«’Z ž›3œo'£©þõÃ1Vwª§»»mÝ'IÖC±g­k& €RÙt]msVwM"¨¯iä«£ ‘÷²Ý´ÌÔZh6Öåò¡€a(J³×@Ͻ•%ÐÕ™)×6Ûš{Üø÷ÝßÈxX endstream endobj 455 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 452 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 455 0 R >> endobj 458 0 obj [456 0 R/XYZ 42.52 737.53] endobj 459 0 obj << /Filter[/FlateDecode] /Length 1053 >> stream xÚ½W[oÛ6~߯Ô¹°X’ºÐ à‡,uÛ]RdÂú0-S—EC’›v@ÿ{I‘²dKq,Û‹M‘‡çûÎÇÃCRƒB-ÖÚ¿÷Ú¯þ›wDó€çj~¤YÇÕ0iþÛ? „ž™Bh|™-,£J›´ˆg¦eYF¹od#L#ÙXc‡d¬¶•UßÛàí›o9­gùµ•ÏÑmíA3±l¢!,¬åš½€ÀÅê3Ó~oÉ-´…"‡\?Wº, (g‡]ü ñxš³eÙŽVëÖFÏX7 ÷5ï`[Dx ¶yA°Í4˜s _,|*2š 4^ þ-âŒq_»„>݆½à†5O.]L_/¦yÞŽñ~¨|]€æeOÖ[]×å&½ ¯Æ>^I7e#i¾ËXÎ Y¡EO“°Zn«±håÃXn}EÇ¢;”ÓxÁ&6ž6ÙH~h¸c׬`Uü]YXcá.àDŽs=àØC›,Ò€W~r Ò³ ™´ñà$HÓ$ç@„‡˜>îA$ ‚‡à±‡2g´pÆN’NKŒËßwãy™ )ÇàwZÊð¼”íj±ó:•‰þ“æûÎ%ñ`3©$†ÃÌn³Õ6Þ¥Í2•J®0£u}’¦aÅhŸÈ £[¦F¢”_1À#ÛÁ6®Õnàó·õLÃø¡ ŸÛÃ&)Ô"VÏÙUeÈêZ`*^%ߨ|êH ÚÅùµcOû d«fUÊê¡^X.E'Š-îWR€‹amè¥Ý²Hú ‚´H› Xs¯Y4ï`ëY?ùèt– ÜDËÝwþ+ZAÂä5¬nª}ÈÏÙ©úÕÍBæ ZÇãyQUæ2(11§Õpey++µ|‡¡JŒônœZµž—“q˜J ƒ9Öo°ÚJBÑ,hÎæj÷èYÞ”“§9¹¬ðõÏi³Ôó0ÜêÍë×÷Ûº[ ÓqÅx0Þ!¨®/×3ät¤ã¹Î“Aï•í“  Èí$Ý¥’B²¹˜>Yø –«¤_v)9–Äü¶–(%;U†Šâaòž%³©ö÷¬zŒÎN¤ýt]9ë•m£']ž>> endobj 457 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 460 0 R >> endobj 463 0 obj [461 0 R/XYZ 42.52 737.53] endobj 464 0 obj [461 0 R/XYZ 42.52 233.91] endobj 465 0 obj << /Filter[/FlateDecode] /Length 1241 >> stream xÚ}VÝoâ8¿¿"¢/A".qœ¯J<ÐnYívO-w« È€\%¡,ÿý=(ûOìùøÍx>ltI·k¬ µüi<Žï‡¾’Ð3Æ+â!a¾AmbÛÆøybÚ6qÚV†f¿m93+‘æ ¯„üsÌE¼BbJ]?È²Ê Ü¬6šíWÊK<›·-ꛂ§I¼íÙø«1fìkÛ¶Oj¤ ºÄ£ú71ÞÒÀ4R—‘0™€8 h)’‰]ÙS_¥» 6 Ñ•»¶åRfŽù»”‹ð$§|­ÉàKQèm¥G‘\¯K±â»¤ª•Û]º'ó»| ‘QbS”ž¶oâè'I¶?I5•á:×p²Qñr)¶M“Þ “ïûåï,þ,âêÒõUœˆª÷’]žOÍlW)u[v@ǰ˜Cªø!,¨®!#ut$¹å)H>(Q-yai1×Ö"­¥:ùA=†šú>ú>ˆ¾ úσ׷ŽR2bÓæE ãàå)zì¿ #؈êæKà§u^éXˆ»ùYÂL&]häü’žHg†¤ÞFzb¤'FêÌN,ΉÅ9±8Îlví„Îz÷XÍ癎^¬?&öÃìÆ=IAè|C·é ­‰©ñê»Íñ 8^8ŽW q¼úº‰KBW àúÚ¯÷C÷ˆUFÇ#>w¼‰ÕH¶Í}›&×?¥ÊL”d+\Y‹%Ò|«‰æH-c ¬>]YZóá*~qpG jô´-æ2sTáæ Sóålj¹Ò,„V±hÃ{a#` Íw‰T,• j~Érd]í’ä€Ü2$Ÿôߌeq±Pp€^‹,•ì‹sL^áš^VÈðÑv=“¯wB)‡”W ‰`#Û¿ÜØo¸æU±l¨Á«aèMX_Á .nÄÁN¢ÊüþóZGÁÐðIèKAÛa$` /}z•–X4ÐÇSê±K伪×@wÅ»»§ÇáÖÆ?0`G?^ê ÷nÌf‚Hã!q|TB—ù\ÏhÙI¬›ÓGC¡|Càf0ÔK,²›§ØØ’,Ë£ë–ñjUlI¼¼FXŸ-Š”qiF|»©âùÍFWžGÃáëKôôúïÛ¸ÿ-=ú<µ|Û%ÝÆµÞ¨Ÿ¨Wi˧>±ýúª ä]šýÝz§2 Å”uðL»vúçÁ{û+Á½¿Ú5 ¦÷OIñz#Ó°ÒøþøüC%Ä endstream endobj 466 0 obj << /F7 73 0 R /F8 86 0 R /F10 94 0 R /F6 50 0 R /F5 47 0 R /F9 89 0 R >> endobj 462 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 466 0 R >> endobj 469 0 obj [467 0 R/XYZ 42.52 737.53] endobj 470 0 obj << /Filter[/FlateDecode] /Length 867 >> stream xÚV]Ú8}ï¯ðÛ$RãõGȇö‰ªÓ®ªmµ*´]©SE&°Ö‰‘ 3Ð_¿Nì(a&©„”cûž{/×ö"Ö ù¼o漋A ÓÌW€Ä&1 b æo¿{Cê!äMý€RêU¼ØJVq;ÊŪ¡÷@&±t“+¥í†ÛÕCÁvvjá$ñ8+¤(¹ÿcþÜÏ–<€¤0ŒŽ!% a‚`DÜP‚Y#5‰“Zχ†“@Ú(•Jm³Æ!F0L'Ít–s)¡äåºÚdÌl#z³œ>xøÁ?gD׌EËÀ¡¡DW”ž yGIaLãÞŽÂʵä“Û‘–†aê¥è–{k»àUmšÆá/¦×n׬(®ÝRRÿÃÏel)V+]fJ ^VYÁ*-P,ý`b6u÷v†ïzâö’ªã–_Ûþi=iž‹­V9“õxⱃØYdÙ¯Ý`/+±•‚»ÅÍÎþ‘çU]h5®”ý®yÉu]œuPSMø|cDfH¯¸#Ž?¯½±riA£Éí® œ"´;˜Í/o¾ãæçIS™ã64§–JΨd\TzF¥#¢’ Á£ž &c“ ÁdŒ`z!˜âQé…`JÆE=L;Á“ÆIÿ¹»ô¸S{sèFæÜÝ”í,íçE‡ù^k#õEwÝ¡5‚/ªÛœ|{rwÇ2ßhUiUÚ3AyM,¼û÷ãtfᢽåí¨ ‰E÷³ÏïìØæ¹IñÔh¶¬ª’“ñ{äîr¾$Üòn®¥â¹P¥ªSaþ~sy ñ¬$Óâg›l³b¦‡X*] Q¸Ù!{©D.í=öÏû?Žˆ+)EÑàçËìÛôëýß÷ŸÞÏÿÂî²4;º2› 06ÏQƒLZ€:pšÂj+Õ\'… ÐÚœ†êüd§Úƒƒjïœp‚##=U½™ý%¡¦C1 J—Iˆ~ëP.ÍÛX¿CÎdgû\.:£þöá:®i‰„Ü ˆZî‹×™ZeìàÞð›Õ÷qúÙÕI‡ê«ÍÛÝNª'W#jÉÝ줷¡ b<謥m'Ú¦öÔw Cl»´Ð6Îÿø õþVc-ÖŸÄ^eúÍ(Joº_ïw•µ ák6µL0ЍS§ïÕÿ6—rR endstream endobj 471 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 468 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 471 0 R >> endobj 474 0 obj [472 0 R/XYZ 42.52 737.53] endobj 475 0 obj << /Filter[/FlateDecode] /Length 768 >> stream xÚµW]o›0}߯ðËT" ÉCXJÛLMQ´®ûr'Eâ£Gkÿý †Ö u³õ%¶oŽï=÷ÜkËXƒj¸_‚ÏçÂa+ ã!´€Dg?5„ ÙӇáæötÓ´4F“‡˜0Z®Lm­Ä䶘 È*Ë…‘Ý×°Ç„â¿yOÇŽFIG)íý¾/àT,ð§‰hbk`À>®—1¸©˜À fZÚ- ‹¡dgÙCXy4¸Ù¨`Ü.£Õ*OÃ%etÁ²<$QŸWÑRÞbwl)¸$™¸~O·±¥y7 ¦~ÜNÃàÒ Üð›çã‘{ÕŽÓÞõ½Í¿ ºSñôCÅÓlŒ.+ .2âu¢7©IcšÐ”A%ð®ú»rzWÞÄ» [ò>Š#a$\å$¡Ýì^`»Dwºã {’çä)T 2R’?JýÜw'^¸,ƒ­¹¾ïÞÕst” %Å&¯K L]œex—2.Ý$sš‡ÙŠŸZ¨íI(»Ïyð ‘(.öJwvSëv1½O'¼É}¡–)†ü‰Çy endstream endobj 476 0 obj << /F7 73 0 R /F8 86 0 R >> endobj 473 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 476 0 R >> endobj 479 0 obj [477 0 R/XYZ 42.52 737.53] endobj 480 0 obj << /Filter[/FlateDecode] /Length 930 >> stream xÚµWÛ’›8}߯Ð#®Z´’À\òÆ:$ãTf<åa“q²SÙQ^³3¿a`®Sµ/èB÷9Ý-©Õ"v h>‚?½?>˜À†¶¼- ¦- 1Þûï ÆP›©!¤83UÓ4EÐý!•£mO]ù›Ì͸œÜ&i)û“Ê¿Ïû “S?f*±ìcÆéìÉû\/·Eÿ•ØP76¡FÀè‚)‡1x(Lµ€Ušzš×*›“©q’üåÓ¨˧ýˆm·)÷³0àþ6 ö_ŸEUáy¿0?îÐt:ã‚îÒ@°„û‚íé(–¢[·¨“ :Eÿ$¨CWq?¬[ÏÔ9Ñ•¢™+šdçaáÜ•sضMéFïˆöN· 8Uâå‹o“öˆv™ïÏ,k «Ñ«qúŒ\‡Rïb:?bY¾WCº§\4"f\Eìãên¹ºu=wí{7®çÈ`åÇäµseg‡þâfÙ¯ÝË~ÖÆÖ|$÷û\qá­rË¿®¤õþwí-Îç~(£ê[ÃŒ4hÎDz™€‹æã›5ï—Þâ¦C»²¹qïæ.6Në&.þˆ—íúGÿ9²Ãe¯µÀFô@y”ù ï‚øEC‘¤ßñSD)@ž´Nd»Í¨è¡(ÈBIÑÌBmçHWÒD)Q®Ê.á,ÙS‘§Ôb Ë-V®Y­æÊ¨ëƒ7D×qÔk d¿r÷~2ûëQ“ç«¿Ö Wrî(§iKÙ,9¦!­©Oõ®ŒíÚù²ô6-ù÷‹‰—6uC†p {ý¯›§žîtE¤Ïâ [”N” &ZÔ‰KÓ‚Í43¾µ­*$møþ8t3†mô’­›ëÛÁúø6We|ÝÏî­{çMõ´r£´ª¶ž—Ñ‘£Ú Åõ³ãÖ¸fò¿‡oºs.OÓàÅÏDz Å1¥~Ì2ådkMÖ*ÏxDŸÇ‚Gy9Ì3V¿þúÐ) iDyHÇSä*bEQƒæ×ÙÙçf‰è¬×Φ^T¤ÛµÕ`> endobj 478 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 481 0 R >> endobj 484 0 obj [482 0 R/XYZ 42.52 737.53] endobj 485 0 obj << /Filter[/FlateDecode] /Length 470 >> stream xÚTMoÜ ½÷W œ°TàìãVùrªRKUÔDk³Š-ŒÓ vwÛdÓ=1/´_­ü·m€‡R´Ò2xÊïÀu>Y‰ÀÏ57å8d QJp–m¾9§)H§3MgR:£M×õ…$Q‚³ØÁ…0Fì ¥­Ôƒ²JxAªcrrмUZ˜Ù'¥çK £ìþ,íZ(}–ìL,äpžãîUš¦ç‘G]ÉÝdº*^E3ú†D˜ÓcC›ûûÍ PÌ"è–ú{ú˜à¬ }”Ä„¬ ÓD^tzW}¿]Y¬K;‰?hÓ$uÙUJ×…Ý÷òdEü²k{#‡AuúÍ‘)¶{+‹ÎTÒü·Fƒª§Šúë‡ m•õñ\øZš ¿ëEù²²em# ©+%Ü“¸¼¡äÏSG‡lÞÝ#‹’wgqcr4=+°ÎÏ›IGœqL¹“åÉ4œ”$ nÆz¬ŸX}öCÌzJ“dúÜa} R]Ìà÷96ª~X íâïÓo=¢ endstream endobj 486 0 obj << /F7 73 0 R /F8 86 0 R /F10 94 0 R >> endobj 483 0 obj << /ProcSet[/PDF/Text/ImageC] /Font 486 0 R >> endobj 34 0 obj << /Type/FontDescriptor /CapHeight 850 /Ascent 850 /Descent -200 /FontBBox[-71 -250 1099 780] /FontName/XLTFMO+CMSSBX10 /ItalicAngle 0 /StemV 136 /FontFile 33 0 R /Flags 4 >> endobj 33 0 obj << /Filter[/FlateDecode] /Length1 722 /Length2 1680 /Length3 533 /Length 2215 >> stream xÚí”k8”ëÇ©‰ ¢m¥7‡AN3ƒ$ͳŒX.£f”Ó˜y1™3£Æa(r–S–„…J«Tr\ZYV*¡U®²•ó1í©V­k×þ²¯ým_û}¿¼÷}ÿŸÿý{îç¹^].$#,ã ÚsØ|#„1 À;‘H8  ŒáP<¤ò¶-•ZKK€ ñâ:ÊÊÌÔ Ž‚Bu<'(”Ëðàzxý*4€e\Êœ¨ü%6¡Q™‰Cc€üPcÀ2™€ëÇ%<ÀäÜ£ Ý E :ƒÆ|AjòËíÇПÓô /¥£ —'æôÄœú€˜’Îa3C:è5q戻b–ÿëßP}knÂd:SYíÿÕw *‹Á ýKÃa…ðA.àÄ¡ƒ\ö·R2øÇa~×ÈOe2hX¶?àŸS ž=CÒ]|ZàGeòÀOyMÿA<¸O&”ýnöN?|=ÖÏu*ƒÍw úêüqÁ§ñw,—!Ãáp„X(~¿|y~ÓÏŽMãÐl€Ä§²éT.ýkâ{.Ž#7B##¤¹øÁ--´\ø¯ÂlFpè` ˜Ãáp 8êS–Âå‚lþ§« Þó—Ø!ž @4/_…!ém¸Ã`Ág¾¥W“|»{$æâ=KKI]éë‘r;/õˆÏÎI^8ÓÇm(¿‹·Heµô µe0„M2Ê‹^«ÒèšXuƒ2¥KçeQ„¥ µú@]mÁå˜Ùº0k/ЯârÓÐ݃¬‹Þ½çÄ5Alo`ãydžÅáx…ÉjŸH½õ¡£~ŠÏ7_.%*†ËBð…Å É)­™Èú˜%Æ¡Û'¦ar½ÚÉôü~‰†k:ö§ ñïìó}(„XÃÃíÍ[°zc“ˆ .n…eORÁ„ŹHþ±ð®ÜÉ:”Ÿ ©ß÷¬ãdÓEQÒòjÿ7³°ÙÙTnóFýg½èèì @Æ,qÉ« Fñ•?ÈI˜°—EP¬ûC&éñTZÍ¢Y¼iFL„öÁ™-ÉœÝÛîÎÛxnÚ¯®¾tªÍn$ºHTW–‚°»,Õ>´é=@zÐÅ“§Ÿ½m[Ÿ xX˜LîSÐ$×á7’Š&Ï÷TÍn}ˆS8HÍIûÉС9 ªW!ãÅ]&GàC:À¤èF)L¢ªýÆ«tó㨢d,q"Âeg‰v¼šnÎÒ@’—“Ö—ª,r¯¸÷à¶âýz'[Jg½¬EÖ#ÿ':¬ÇFÿÉåüä.óbúp¢ªWâˆ| B0Ÿ5'É:ƒÞLX¢÷õ.wH­<þ®ŸðÙ?{Õfýú”&I\æ»-&hwa=ûÖÓk°Y‰·÷oyDÚõ0¡SH¥WuíÛ˜;äò´MÆ#ɳs%‡ §Ç\}eO™Zï[Ä!ÈÕö™»¨ñfŸ (+®bCŽ\²ý.Zíˆ æÁ½w*°6ÔàÂÅ”+Z‰²=Ã˾ÒGŽ}вÔ5 ILeÉ”q0n­*£yýzÁtåÂGåäàd…ý9G©ºH7ˆÿÙ±_za÷ÏYÌ@~¾…ÆzÛy›ŠäO%»Gwý¶-Œ©DªDæ]UaøêŸ:­)‘¨zUx®Éª9KsrÝÀ†´uÚê«ç»EŽã6ê÷ޙK%œr@.—H'nó Öw6PëZк£0-+"yWß#ÜÔü6ÆÆÜ_rÜŸØPM¿Â<Õw»…·*+\¼¢¼#F"<Ò£{ðT¼ÈVòlËs顪øûO!Ê¡!‘vévó墲È)\.£%ÕSüv$#R‹‹»¸WB}=.}hÏ:f“ÓúaïÞ:Û½Jä`}D÷½£Ò˜Ú×És •ýš/£®l{¶Òf†;]9tgJåXÝ1jzRøò&A œ¡°Žì,ÐnvÇ稆Âá^þ^¢é(õ‰“Z®¡¦Îõ&ɦ¥ xÈÛ}¹-Áé Q/i.BdŠÿÆsç„k)eù–_FÔ¥«ÒFU21ĽUD)¥@O›•Ñ]ÇÊ ŠtkooÀ M˨\ÔSˆJæÊÃ)è«ë!e‚;ÛÆÅ¥Ä1ãb{›§©X¤z ¥çn”ÒU$JËSiÈÔ`åúš{ïy•_‘pHfŸçVí­Ý&jMý’9}K^CëLºÚõ";ž©•[mR‹Ðû<‡u ùf«³ÞÈÙ¹¹š„ñù®*o)kpYyi,¬<~ª}ÛÞõ%L–äÿ/èÿ þ' hLÊåsXTn úO&;‚e endstream endobj 37 0 obj << /Type/FontDescriptor /CapHeight 850 /Ascent 850 /Descent -200 /FontBBox[-33 -250 945 749] /FontName/FTROCH+CMR17 /ItalicAngle 0 /StemV 53 /FontFile 36 0 R /Flags 4 >> endobj 36 0 obj << /Filter[/FlateDecode] /Length1 714 /Length2 3806 /Length3 533 /Length 4356 >> stream xÚí—g4\}»ÆÃ(1B”DIae0Ú ‚Ñ¢›(B3Æ cˆÞ Ñ#DôÞ‚‰š‡ˆ=ºAè]ôhòÊóœ÷=ë<ïùrÖùvÖÙû˾¯ûÚ×ÿ·ï½×ÚëÏË7ÃاH5,†CdAÊ:ú(", äåUÆ!­ð(,FÅ ”Add ˜«-HL‘’—–“yAÊX'ÊÖº£ÌÿÛÁ‘8”µ¤c…·C:ž‡X[¡AXkï! ÁÐhþï[\@úH$Î ‰!e=EÚ¢0@‘ßL,ú—ŒpuúgË ‰s9çÝ9çäS"°´´ŠèbÏWCž³ü±þª¿‡«¹¢ÑºVŽ¿ãÏéßÚVŽ(´Ç°ŽN®x$¤ƒE q˜¿[‘±é (WÇ¿w5ðVh”5 c‹F‚Dÿ’P.j(w$ŽÂ[Ûl¬Ð.È?u$ñwˆó¹ý‰ ¢f¨¯§¬.ø×+ý« ·Bað†NÿŠýíþ³†üg}>ÊôXTXTrnåây‘h°Ïz@mбÑâ zæÊS_ QÄ7wqêrÂԇǃ`Öô¥×´DsŠâä´× B>™Ò[¾ßÍ;ºHî´öÈpż¾Éjnßïæµ@W~xvÑSÚ¸jøË0eÜCB·†…8£ô¸éë¶AãÔàN†Ÿá –õT#Çr8áð‹c}r9ôéÈïc(ŸrRèà²ø0ÐåùØSØXDܽ$þÞHÈOhª•°½9ôË 75§A8Ô{ô kì°d+W_ O«æU£!# 7(f_í¿-ô4Mw#^©ûüD`¨™Ñ7oŽûS÷;üŒ´.‹Ê‹YÔ#Ö©²Ï$ºðº}ÄfR»žYsÀrÍ”Îýå;¬ Çã„4pIB)sܱˆ´>™Ö)˜ç§¥»6«íi–g5ÖEIÕ&7Lƒ.çHN5^}BÊMX—x¡ÉîæŸ¿UšÙÀõœ{ƒéǸÚ.LýÙñ÷渒·b‰þõð 8M¿˜~‰Û3&iM}õg4¦/„Çç§Íê\,Â<ú¢¶‹ANªü¶W»Ø‰K|vO™šjÚ{†æ¨ïÈ©¦]/óú=uý6ò²·îßÔh¦¤8õlà}n…f%Ó´*åï…ëËŸ<¼Ø“Ê› :K%”'Ø—Ð7Rñ2ÃW£°»ü,îP ž®ÞPϹû²¯e›GOC_´ÀȶgQ)õ(© æBL™E 7¡ÞÚËÑeml¬¯œ¢÷¨}ùÚ%GkJ£«Pœ5ÆÊ“zº6zvàšÆ¶ã>XÜ»NÛ½1ÚrŠª^j‘ä`…Tþ-Bkº±ôV†ÜR½%¨F½=]$"¹OÙVdÀ[.’1à~§iùm¯EÑKà1uu÷ ‡B–ÿήxJÆHœ¯×­„HŒ‹"ÝÏpû6 3Dë3£¡¸¤LeÛŠ/ÉS^¦˜ô±ïPK¢ñÂíÎ0z€O·3 ïIÑ—ô[™¥›·V#k¾>öH@Ò}wló*â)þÂ3zA±áHï O®"»‰g2š×àÚA LÉHž!”g;ï·ü´’­¤ÌDg'còk:uïlƒ(¸­‚ëËTÈŠÐܪz ykî3=ºMà&éSx<…³Ç2' Áµ„L™S•úå!£ã‹K‰Ò:eaݽ®3KQøã:7zV¨&?OÓÍ+芸uË7Çkõl¤¬íÔ"Ô |¢36¦úKì1º&û§*)þŠ®P½”{Àà'*¥ßDÖ¶Ô0yŠ ÙÇÕ6œÔq†]¹~DoMQÆp`g0C§\=`ŒîºE9E<¶tk`»M›“ã)ÏÒK„ Î\˜qPŒò¶Qg㻥 qS»Yã>p¿©õËÚú}>ßæ0[†KãþY3b'ÿÙßpÉIÝbäéiŠ Ðùã>äó2÷Τ“¼ïÉžib¼nàº.2k4 ú3”lŒFá^8,Šm£ýÜ´L«à˜°L.tcÀ ô‡°T¿Ø½+Cã-ï°+nÔü– ZÕìÀõ òŸÎæ6ïYj–éU}Âï-÷Tn®Ç}ÝXTâw¿áéúiø5fØ¿“ä5ÈqëÑP ÿÛÂPî±³èæ‰µŽ¶Áø£ÚÛ„”&Ÿ\HÄ/ û1£(6}¡Ž…\{Tð°æÏŠoÅäc•4¶Ñ=—´€Cƒé§¶GåäJ©ï²ø"y¡uQ….¬2©Iü‰r1˜Rb@ûkæÆY%£ÄÀ^2Ÿu‡<»¶æ8èÑ›×õýw¤›8®®&küÀµ„Ó÷?~³³Æ¢Øv§JÚÅ™øÎ[10Üz2©"ªfµr5@PçZü]ögÈ®[MvB³Ö‚Èù¯ó rˆk _ÉG<zÑqèâÀ7CÃùµ)ár5ïÐ’ÌvÌxFݯçÇÄ^Ã|=÷L™ÝéJñ ƒÌ˜…€÷RwÐÚk!Þì—tÝ, aÒüõbYQߊÿô«×£œ˜Êá4y¸Ýõ¾ÜbPûx,êË[hÖ5˜5ÙŒô¡º!,µ"½%"h\,S.IÖ.-;ñ öm¡*Ì}›¥1vÙ‹>ƒœr¾Êµ9Gò2²–¼ £´+ùŠ`·tü¬<™Ž^ÁæèÃú;ËUÚ;;RߣÖræ5²{]Ü3|ãkíHD ÁÜòh&®Ã èrÇM‰Îv²-´ÿ«¨w30NËB•>§Ë§vû‡¡]àÜD\F‹Zx‚N0–³tˆ`u~pÂ6Ïc…$Þ»+ÑX¬4Œå,–œŽ¹RKEFæGÕ|A@lú"™Ëå±ùr×Ù̸ôŠ €è›EŒ¿„8–Ð&Rˆ2NàËÇ%T®ÓK‡ÊùR³ å^®œ"ãc vä¼Ëc{²yì.gHíùžØg(•ÍlׇÌ5pí m£aªÁ†>²\IÅìïK2U,Ý 4Kíî!(‹#vÇ%mõÉßD:øÃè®rÁ -&äéá+Ïë.ê‚tNÞr¥ùÝ›lMu$ñ‚æEñ…£}‡Ï^p Ø0 ”IÚWç+5†¨$懲·ê»Âð«,Ú©d¯‹ØÞó½vZ<5Ç^W>5“ 6¾©¢’“Øâ¾8”Nx«`Ñn߉Áйå¤Ô„qÄL:}ßÛÊ­¤éÍ2Ü ‹[K>bH"nµš]_*6}½FØVÅ=³/üæßx¹bMAiôÒïÍvÜk‹ ‘›»ºí)Füã6ÛD{Ž›‡ZmjÒÌ6ðM‡ÐU•Œs[ßã}c dƘU`u} 9•êOí–q\Í˳﮽còUÑp*^³Ѿ€6¯=Cu/$é?Cm½ìÆBvÕÖR>|Eâb±Ädr^| ô ‹yX™´CÓ¯“¢—­`Oæ`–¾ë—°a…bŠ¢À'Q•&Æã‹ÉBÃþ²Ã#UgylPxê°Që Ÿ•MN½R†7,:o¿aá©“à8Ï»48ÏŽ‹œo ³ 2ÊžÉ,;CWŸïô+ÞfrB‘'Q+O0äýÉWƒ›VÔÙ»¶˜d™ÜÄø·nÝZmÝÎ-4c:—ÄoŸo’ÉT6wÝw¹6©f[UIG/ø5ÙŸHÚFÔIkIö¶fŠÓ3‰±gÑ&tKBT‹“£š·&Ûla4÷˜—ª>û/¯Ä´Ä –¥aXQëñN1¡júEJ÷Æýhð"¸Ëàï§@ˆ´#Æ?¡$ýx_7ûɴ«¶#–W¤ƒUÍnûòqå(¢kkŠ™ÝSëaxÞƒ!®{Ùc>Ç40T0=墤†sLÕˆ¡~ù¦ßÝf€p?ÄÿóýdV}m9ÙGÝ9Ýœ”Ùã½ÞÝÅ¢–2ø´¯“ ¦$Íà:øÕ.Yýéj%[ç?¸™,% â&»^/Ìþ¸$åvÃMSuBçqÔ6åŽo°š.*—ëæB‹ù‚îzÜ››|Õz‚¿Ðô\×’åu°GqšÇq³HËbU]c©öo-ö÷> endobj 39 0 obj << /Filter[/FlateDecode] /Length1 714 /Length2 6014 /Length3 533 /Length 6566 >> stream xÚí’UT\[·­‘„Âa#!ŠÁ¡pK p'x!A‹ ¨ îîîNp < îÁ-Üådï}þÿ´»Ï}9í¼Ýv×|Y£>ûüæX‹VUƒ]ÜÌÖ&c‹tdçâàJ*«sq¹8@IÌÄn‹”2q„ ¹„„¸€âN@n‹_˜GPÄ0%mí\Qp KG “$óŸ. 8†‚CM@eGKâwÔĨa …Ã]9€@q úŸ[€ê0ÊfÆpqÍàPG )ÌŽpþÉ$4· ü-›9Ùý«å C9üæ2ýædþ¦4³EÚ¸Í`æNÛß§Á~³ü±þ/Tÿ —q²±Q1Aüÿçœþ[Û·qýOƒ-ÂÎɆ*ÛšÁPÈZ!°¿Ù”afp'Ä?»òŽ&6p¨8ÒÂý-Ádà.03U¸#ÔhnbãûK‡!Íþ ñ{n!pJCT¤õ”Yÿþ¤7UMàHGMW»Çþéþ«æú¯ú÷xPp >ˆâúmü½þõfðä‘P[38Ò¨áh‚43A™ý[øïP¶.îì<¼@vn>.   P€äùú´p{'˜¼ ñþ¥BP(Òñ¯¿à÷}ÿU›ÃOsAé¤pt#6*Ö3ãÓÎÉ—æÁ)U@[Á~ ßyÙpï!ŽÍcŽi«à@kÕÓ¼ë=ÕˆäK&±^Ê"1ç†_]])ËÈXÌû[õWÏ„+"·ØGIêõ08;`ŸŒôkYsøÜ ,›å8ÚµuÓ>k¸™ìñjŸ5+×cm]ÛhA†NJ¿WŒcÍ4:¯ÆBIšé‘P¸Vs“x"üxïµNÀìZÞãur–:5ês8žŸ®~ÈÙ’“{-2l°îÑý œäQnW”¯R/IúŒê]Ö;7Iæàøëý TôKl8RH.í…§Ò TPÇßy(?^3,³ýð?ùI0PPknàã>·ÓGg7J^WŒCMdX | {• ñÿ2]a2PsnîNiJÂzzCVÙ! ý\qoEs‹«Q[>;jùS˜1zâh¶:pý×&;ø €Œ,®ŽEºÅ _²nFhÑØRO·ôCö·w3«,ïÊyÉY(³Á“'Qqô’Ï“Î-€”àðÑ™,¾Ó²”Õóó_Ÿõî )f{¥g°'.x“RäÚ—)#iíÊŸf5þ’ÙKöTνþZK"ÒHÑêƒÍQY¬ë¨rl^K…ëåJ#ÛOø¡EžO ÝRjKZ0¨6?.àzƒð~*£Ý–!ùq¨óDøm£íú¦#3§s²“…Wöxðó™™o 5ï«w¯Æ¹ÊÅÛú{º©¯ö—Y3(2Ô5.·$ü¦5¦Gý+ÉwÉ [ÁÔc”Ù»$-'-$:=$E:’µiðRVJ÷d#‡—£ "ËnƒäU¹s´Úþ„ßüÄk©Þ`v€Çqª2>g8}ÒiÝ"5Âìǽg«Äd,hÀdRPóxµäÔôí¼´d©]á'öwE3„‹ Zù¼”~½aÿ:÷‡2¡ô(JÙ§›èôÜhšÁ…ÉewNßw?øœ•Ä„#„9¼à.Ü®åijåp¡§3‚L÷_v™Â`^®›a_¥)­?ö¦d¨±ç˜O-¼'•;žqy¹zyŒ×Î`õó%|}Ô† :¡ùÕð¡¿5_ûÇß#M¯?Zbe‘S„¾WÄ Ec(–Œ$qá²eöÑCF”®©-¶¦éoâ÷2ã¸.¶î’¦Õm9!’Üoí•O&ÙÅ&"Y¯î}÷ÜãC­á8X_û…DÎ5¢Ë©¢¿M)¾~”G…ø½`·É÷2F<ÎÉäµkÛM!‚¹tr¯—¡÷Úƒ22CDœªqŒ‘ÎxãŒòІN¸p«ÝÖ ÁSÛÙAxz¡zpú\ëÝ4°ž‰”<“Îç±9äjÚ8.f~ö‹|´™}ÊXšhVö96gNVa¹ï<£(á&î¾]´Kjƒsº±áKƒé8‹ZéÎkÂ}ß›âÌ:µ2µp™ÊdØÒ¦RÕŠ² ÝÚYá,Iòp[4x•¡7¡y=QÉ~2‰^³¶IXyépZˆn}ó´ûÌé$yÎ}ˆÞN8ò¼¿xhQI‡ÜÔáû…¢÷Û¤]°s–©®Šbkl©ªÔ×ïy‡ &NþÔ FUp*Î×yæèˆš£¼*tfŸ?¼¾9|˜|¢¸¹ˆ3ÜPÁ¦¸¤g€E½@-eK,ª#Úâ`Aúp™sàÞ˜J">¯Ù.Ãú”LâákTµ•ÇDýÆP ”¨8Hq„Ítâ„Q?!%ÿò5ì9³Ë|nžCû„Ò¶¬™…‘c ­jTÝÁù&aqÕ*» .Ž!WÊ=õ%¯·;úVУbÍÀ÷Û|tÉå7†ƒTü±4ÛP‡[Q ÷Î/ñ5AA‚»_uˆNB©ÇÄO®Ü ô³&ü:¶p‚By?Ê„·þøI/“¢ÐtöÍhž‡>+<¥_F3Ų)Î&&FîÙTþê€Ù[óÝL›(4$Ãy…‰û㈕ñMPsG.,½ö&2i.Ÿ±n­[TKG‰¥ŸÔ@þ!ÇÀGhOú-}÷eÏ_,ê@’Ý2:4âÕÖÉø050Øì«-xêÞãQ-V®4Ñ,.íÓF›`wÿRÊî_e0P ö ‹œ,‰Ö*7Z½×1džõÖ¾PÁ‹ª†ñ0WuÊ„•Wùb¤Ý£å¤;B)£î‡hˆÌ»›s¹ùoJ+]äðšŽlGu×éô—²hʇÁn½™ßv “ÿ”½ ¨Ã~µ »»I"Ó©?¢;ßµ[¢{­µQ¨ºý¢ŠÎKmþÑSë”ǚ°îXŽË'¤8iIj!˜CiJ `OíñÂæÛÞÎe€…Œ›ÿrnŽžÏ}„þ¬¨ëK×qþ4ËjÆÖ{ûü»â³íg¥F?öWéóÞ˜{F`n²¥S ùêsån5. ø:—ÅpEY‚¨–MYŠ¢)é ãòµ ´Óè¼ß *X+ž¤qVŒ­ _ñjÁ½î? R0æ›Gy¾ öÞR åUjiLìà %3‚¤é¥‘-ñíö(Dé³iÚV}]5¨x|¢#(/º½w×éÆmNl°PÏ!@Õ£]ü!—à”L 6å¿#>áŒá#-‘éÂ:™`Þû&u?“o@v[ðG\í³À P[g]–ÄÒ\ê`¥ëvÌt÷²VÛ)ª „Û…´‘›:uw?bP¢1èh­óÞãâ9ÂM(H6bžh›‹‡/Mó{šH âä>xÀâÀ"¾-²úÕ¤Ùº³àÝgLxføZ3Ü/¯¤×ði±0[ñt3t}"*ÀR¡§¾‘~ÂãØ½oËðëã+¿Ëu¼x¹œÜÞ7‰@z ÀRF›¼“é~lõê6ÃóÐÑ÷¼ð¤ég\¶ø¸tȽ¡P\Œ_’³·ã]­´È燫#Ÿ½ÎÄ5 ªwŠAÝñÔ•z˜ž,e6Â4OîCO/âö´ÏoÁ3hN £’Èïøœn^~üokf̉~’ÓýÜæä·›ÈNѸPæ|ï&“ÆÑƒÛ)®`,ûá<w‡áWË`?;9&û¥É]Z´![Ñ÷x}­×¸/Ûn® ¡§œ{ƒ>Ùí·dÁŸ%'À¿ïßoˆ³fÊæX)ój¸¾;ÈbŠï5IR€åáÐ\9Q=¾:&í½œ½D󄮨„yy¬Ä—Í,ïœ5ÍN—`Ô‹)Ù¬9»ˆ‹ùÝ_Ù¢pÅ|Æb©zH.">¶”„˜ÄT@’Íy‹*¤ë…/––d@¢r3ʸ:3‘žf¶>-=ȼ®1G¥çWò¥áðy{ ¶Ï)ïœË™žÁcëkŸCõ&ƒXNÏýÍ8YîL»ïWáKâèÏÇ‹‚¨fú2šõVoR|¤Τºû'äs³ aøl‚t'ÂZqßÌÀô³h/Ü_ÎcÆ-£H\¨*S}‰ØE›ˆ •˜0%¢ßytØ•4û‹rƒž_:ð¿ï)E“ân6Q:ë*Êqô5néøÞÏ}5Ã{1"K„]©XÎqAGQ·(´`¤sâZ;WÚ­ÓÜ•ÇûÀPúHcþ^Ã[kŽ8x ì¹)Wwò‘³ÕÖì»­ÆqÏ$UÓ²e2ÚÙHV¯i©3Ã?ÜfÇ.`kCÀXÁUñ±·˜““/rÑ™ömÑú"£á«*uÇÜ"KzØëã’®MQÄ’œî-¨Û¾]<Šýyu¬õ¹:oÂoà “”Õ£ú!»;ÄqÂFSNŸ}Émíe®ÆÄàKÅ<1Hss1r÷ìÚôë@›°ÚAÕÀ§v2—ú²”®äÌ—áȸ FÄpQ‚G=¶îMù½³Z‡‰ß&—øºÖÆ„bl&øý|zlÃÙËÛ·)¶–ªSµOß§4Ë3¶‹lLýkÝ‘wF+cba'ÏË‚M›löÞy|‡Yxå<%zC­ cwõÛÎý¶u”–µp©ÚÙ¿v÷Œ®ÔVëG¸l²ü»Wï1R2‰Rö@›5Bc¹šIf6ºõ^†\ùJÑïmÕ«Úr¯–BD?jú'_ÝÇ÷o+,÷á\÷þ¡Ïe ÞË÷«ŽXó>ž“èð/`FH\Á‘j]¦Mm5½‡ïÝJ|¦£¾xÊ!¤å± é3æf ô v| Ñ‹ŠB?(âŬY«_ì?DKÔ}¤=Dëöß^9‚à{~TNØ+á¿B½J )K´÷ü5Í ×€Ë–ø-Ùeíoe DñŒz n›Ù‹iÌêñÐÍ5ÂI|€0ÏÜigú4Jª}"$™‘˜ízÃôfé“ë*<Àð… õî웪Æèý¹¡.lÃWPŸ¼ØJ‡³ÛªëqÞ¬ž†e†Ìp”|øªpzÿ!xÜ o¯âžŒÑwK ;c3Ë`)›ŽÍg¥>ô·Ì}¶ìçe"v)±‘¹ÒiQsÁ±]ð:xV¿”Ž{øn¬‚ÁL,˜ÔøÅŠ#fqQ8/ÁôÅ#PˆS]\áý¨²D ìc£UrP¨,¸'•ÛôèPüĽÓóaæ¾ï ö -ãW­—Sf8ýR·“¹‹OÛâçÈÅõ ÍÜñ\ ‹q…=yáN×ev35@9‹ý`Æ$³u °Ã$„‰köøU3ÈI‘—ù°žàF‘øÐÓÃi™>Ü烲#rà‚Áöëm#[F½¡«øH4s÷G¿vÑâRÃãn\?Ûãöó©r†Í§ê^¾&^Ù3Õ˜Y¨ÞÀgJ Æp4œñeZ¢—ú‡3ñ\å߈Ö"üå„^[-|2X 祒7yöc(þÉÛ±PÞ<¦Ñ“ˆ¾{æ£E9äÚ#æ!cÛƒö3ÑÐ1gC6!énBØû%ïRêE¤ûæ„a¿8Ûd¯ÔànÏ·GÍF›'ŒQmPS¹§ü­nŠ×WûÏ.ȉ€ à|.:GpqCL5;OõÝ,áÞsZ¬£³Ê¹è۳Цh_œüdüCjWLl‹F0^ÂhâB±À+ Ãß eÅ¿'TÉÇÀ•ÁœºCŠ-õ‹ŠBé©;F½¶¤”nìÄ/s?á“8¾³u]+–éMî…mEàk{¯–]ìæÊ5Àì̬Îy´ª&QzÒ|õ‡ß›$";Fî;Ÿ;22®ÃÒ Éé.žÂõ儺ÏkAr:õ¨ëÈqðŸZ˜äA™AtÑý7ZE®÷â\ŽóŽŽÓ‘:ÕMS²McL#ËäýíÚ‰W©k‘üj—Cxi°ÜHk†g®{iÜåSz˜‹cWÍ  ×6æ/ª Fânïäè:Â>ó¡ãçÑ>*sVøÝ 7$&ég.ÞdŸlK|ŽlEÓ€BiÔóÇ+¯ìÝ}FX¨]•¹Öˆ4P0nò6 î‘Ï )ç]fcmuE}ý0§c±,uÆÕw€ÃUk:ò:ëiÊåÄÔØ©šý_¤iˆ/‡3íí#óDãQAYá(ƒwˆæ_T8Œ={ŽÈ‘‡üm¢.OÈñÆ­¯™JÇc•Ћܖû¾[½·r¾ÏœãÿnE÷² ²¦‘jZÄÒÈ©™Ó«!œ*Tfì;”t£KÀ [ MKm0/S•µÆ/ÄÉšúÙê‹-D =¢è*¶D@ÿËðÿþŸ€ÚÀLP޶”5ð-T endstream endobj 43 0 obj << /Type/FontDescriptor /CapHeight 850 /Ascent 850 /Descent -200 /FontBBox[-58 -250 1195 750] /FontName/MQGGGN+CMBX9 /ItalicAngle 0 /StemV 117 /FontFile 42 0 R /Flags 4 >> endobj 42 0 obj << /Filter[/FlateDecode] /Length1 713 /Length2 8405 /Length3 533 /Length 8960 >> stream xÚí–UT\Ѷ¦q‚»[á$¸{ ¸·àP@AQ8\‚w Np‚îÜÝÝ]ÃÍ9§ïíÑçöK~ëÑ{¿ì9ç¿ÿù­¹ÖÃb¤U×bÿ`é`’s€º²ssp‹¤U¤> ¸9¸Ð¥A@W°Tè p s>¸Yx¸Ü"¼"<üèèŒiGOg°µ+€Eúí?T‚€ö g° PºÚ€ìÿšX!- 0ÈÕ“ø4ÿñ‹ @ärvYr £ss,Á®s5ŠÎù&E¨•@ð_iK7Çÿ,¹ƒœ]þrXþr¾ü¥´t€B<– +tNU‡¿Ý@Yþ±þ7Tÿn.ç¨íÿaÿ9ý·2Ð ñü{G7W3@ÅÁä ýw©è_lRÿÖEÑ[|€ZC@®¥À.r`ÈRìja°B\@ÿ̃ –ÿŽðwjÿàTÑ——Weý׆þ«¨C]µ=ÿËöêÆÜÿ3þ;g0 `ÈÅÁÅÅýWø÷ýÏ/ãk& µp°C­Z®@¨%ÐÙò¿ÿJJÊæÍÎ/`çáÿ{€¸…ù‚ü\>ÿ«P vr)Êø¹¸¸ÿ™µpsvA]ÿyþ.ø?c+ðßñ€@0zF&Þ”ŠõÆìºc†N¯ù÷¬:zkáI*ÿmñØÀ9™cÎöKˆúõ<Öã‘ú×”{‰°j_ÑØŽ[“nOOòòeâwVÿ 7oD*¢öØ'ê 8ÛOA_šÖ²æð{› ã¬\Zæ¸:¶]ôÒ’5<Íôû¶-X–°¶ Î×nGì´À‰XÌÈz(dzf™Þþ@ŽJ[zþà!ð±ä ù£s%É®ã7U§`·‹7qÓ^iD#Ý=7©ž:bJûT¨‰—R‹ÿ<:ê'ÓŠˆ1G4ÿºHõ[V™DÕ‹<¥>{Ïq×A#++ƒ~–¼#˜aÆtz%Oqì¼Þ.[äõ`|•Ö¡ð]¿“ΫÝ×f£YK»|nF¥ÞˆQz²(3=w“·ý¹½ÁÏyœ²ƒ‡Ñr\‚ ƒáJvWÒ‰ÔDýo¼®í¶2îHÀ e^WŠÞŸHã¯óý/èXø«jÃÚ—ÖEJÎá`É(ñXŽtTŒw·¿HòE¤ „ô: k¯»áŒÎá/ºš§vãÔç =Œ2ïòùk3)~Rô¡¥$é³ë…bF›ï ½®[8žh"gnF ll'·®-‚Ð$ZöìCïéz£´j¾¾_D¹éëíµ(CïmºÊeõ‹²»9dD ¢²o5URäBŒ‚³2lþ¶*:—hIãk¬µ¢=RqÜBB~¦”qÚ}¶ÏBƒÔ s f?À8s0MÅZQ˜Œ‰ÃižÕ¬¶s¸<@SÁÝïŠETÕÂË=Ï¢ÝOǃշäšoÔBxÔÐÕZáFºØy¶ Ø´&>"‰Ê#ʨ—+‹_ÈÆîÐS+²âMçÀáuÏî^ù2ñœ´C^…fß¶7=¾¡“|>“püqzHeÀÉïÊ_éÔ¸¾¨jLõ•+ñÁ%Rm:ïhJ¨ëërK]ÑA‚ ï¡Ux1µ6.©ô¾ ¦2çí2Äm8¹J°BÆø¼\ñ>e/ÄþÌ¢X½ÏL7 ¨¯^g`¥j-iQG8F½¹nì9 õ; ­GË»zŒJDƒü8fzj!0 *Ô‚ß©Ô,±%zü}²ô¼ÑÝöªÏ×@UÄ̧à$Ù¡5_gkgå²½IãË,ñL|2!ù¶1Óu…Í<ôkàþe‡B§á,“{AñmH³R÷ ¬S„lB¿`%÷CƇ—¾ÊïÎ8æÆ$ž‰¼]¶$ïâ¬KÙõ”O§½²s\&V}ö­±»aÏ/½@ïšþ Ó/ÓA8ªB˜+7ÃÄ Æ(m‹xï ÚOÙ‘èÃêhxÈ“ò,1,Ä^Þó‹e©Ìì›ä· ÀAw›IÆžºqÝõò»"Xëßð%ˬ￿ƈ?ÍÏUÇ—.}ä•…¢ÀŒ¥{Z%‘Dcõ<°ˆè¸@g¯ÏoInÃAvvät‘ÞZXíá¯-ÜÞdLx£2‰Íù®œj¢Ë§Ÿà¢î­#¼êYC‚¯X⃸{^c$zCV’zžG¥˜Ql±p"wËÞ{ýsïÇ&ÚW§˜Æš².÷ HEÁUJ<Æaaò®z²É[-¿ 6û­C&{å÷ÀOãK´dÄf?XÉ|-¿ l¾~ïFL%(3J*ö ¨Çô §à㽉qì¸ ü’U{lìW‹)° ,i{PÜ<…í†] 9ëKZ(n½Ój5º>û—jÒ¸5þο£)vøî™@ŸÎl–È“Ž÷¤9}™ŠÅŠè‘Â=Õ Ø[5yçþ 2ºß,à,o— çnMBȕ懄#.2ǹܪVÒÞM¦Plå)üñoŸíQo—욃Š8'ü*Ž <H?$ª²l™°Av‹“dÒ1aé~ß£ËÆœáÍ“^-ñÑ&¥AÅCý¼ïÚôY|sàôhxÈÇÄïרÛÌPqò“ÕÓa†"­'ì¸û$?I²³Ò…R­i¨ÔVxmPܲÛ"çéåqãßɱ^F` ²¨2ÄÙjs#„ݾQý&"9Ò«Xkv¬K ŸÅì52ƒÄcÐÈ;ˆë5_HBË…/×^Gýi›È±oG»û”{øÉß$ùÕ rGañ«¾L'Å¥™¸4%üJ$zBló]7³-BÝh~ï:oUÚˆæì V[GÏÅÄÊC=ÁM Ùcæ°LÅ+Ç›Ö`{fÒµ—d6á{6ã*éøgÛ"­?ËG‡¹ü©¬& ÊVœ ‰Âê霈¯Ùïýv{ñ—Ö5Š˜5Cc}8å½àIÉ®$#É$˜ã‹óûë6ŸG9N.}.:Ϊ|]ËFª#£Ïßëd4|"{>…ªD&.é/"Q«‡#Ô³ÿü³*%Jé@¨a–ááíZΆ ŸŒÌÒü¨ u¦ë!ú81k(óI•ß=eKSòH¯oÆyOôõ³Yê8ÿqÍãhÑøƒÝ…@ê'_—6è¸ A¤ñ £gÔôŒ¹gN16>\ Ù\¬;bXÄ€ÈÕJÍkSÁX6yÆ«Æ,!ZŽìŠEŽ•s¢X·¨8Ó\ˆU@rl›Ý4µwn¯`?׬®€C  é·h³ñ¸H‘ºmæ|ÈŸo³v0ƒ”ƒlDRß!Eµ'üÄ`âªS…aA“_5«Cô:«1 Ár-½ñÝ(º½ú\È ‘¨÷œXí`m›Ç9j—kw½¼SɒͯƺBÏçǣ×pa!Þ«Ki»!®yÏ_ˆ¸:ò¾M}¯„tU²v„vÜhŒ©ŸÌkÀ5š›é„ó«, &Ôp E%ŽróM{o Q›SçÀöcf)?lnoëjO€&øV^ÈdÌÜkØä¨&„xv‚&À üÖq!…ÞjbaôÓx{ߎaó „I†˜OŠžËÖ%uy³˜-,žL?Æ­QK0qΓñÐO¨»î3)Oôœå;;zpQÑ\‹Hê‰&~N”Z$ö£Qì¾;9Ü%®MZvCd ì±3Kñ‘‹òÈl\8ÒòÚL@‹`²n¤4ù›•e[ð{înIF2ƒ™Ès)Å«Ÿx†´Œ¿ôË©ÄgiDè%„7¶ãF5¤áð¿5CÎ"H³XÔ¥ŠTï?>îðȼhÃåXR¤RÙžÄ4IăŽà¥=rQÑ{W輓ŒBçB)Ó®ÜåÔsORcæªSêgN9aÖ5uõ"¥È6Ê…,jMŒs'Ó¹*çËÍ;u,Þìñ±»Û +·îv:¿UÛ2ÆÂ ;ƒÃ‡KŸhfØpyÛQÃ4SžTg#¤ôÚ) è| »j+ ™¯è—¨:"Êú·“gjÛ„Ù?EŽ_4Áqq´³p•c²O𳉼9äÌ‹²\a™`.0ÉRûtá±Qv,Òøžl¶¸fœ?Z5lã> ­þ™÷XK¹L^L“…ïã¿n^©¨@Iº8('0þâ*¤o¢Üèä(m‚Š ï+î³Ï=ÕXÎãÒs{¢aåŠ<òGÀ5êd~­Ä1ט$‹Y‘åÑ7¿'Ìà!|a²ÞÁH M.÷ ×)0‰û°}“*DŽ»ô8kÈl0ì c­0Õƒ©r>Ó´Çùt ë¾Ô~²À3€»a—“ðcü®’ô^fß,z@Ä»k'üuƒvÉt/f0fø(|G(Püç–Œ¨ª(…ns‰’*ný…rq¨ý©Ô0éo-2ýEv=a|ÿáHÛ¾h6ª tˆ^\}--Ôè$#*WuÁ–Ò É•)~" 7 `îL:[ýõs¡ðÊ@¢èî,8:íõ€ÌuÈ8Ç8MšÃŧh0£†aeÈ™“ßmnLP^¢€Sà›»ÓøîyvÞÛf˜5®R-ìã=ôhxj‡Â—›W§Œ‚¹Ì?“Y$NVº„Ùâ¿t!3T¡ößU†á0Sã™äç±6ðH>˜²ØÝ„*B€×=õå£Ú­TeoU¨IšÌ»¯Ç(‡ð~·ÌH¸ˆWú˿ԭ#)2ú}pã©jŒZýé5Ÿ²µóVÅ%«ÀR‰hžsµ)Îñ=êäÄdæögŒá¹ê»¬¶sVµwUd!kk³¦ †ØÃÊšØì4ï0ü¬‚†P]Ôù>~Òýë¸g»·ží0䆲 jZC*w -M“òêQ2ÓïYÙ¾Má¤I[±ûQz³lozpÍÒn½äeŠö´–Sv/ņ>Ò›9ÆÃü‹òRW&ÜOCÜ€Å']÷Qswß¿QeœKtKxzÔÖ‹8ëëvSzS™5‹›ø"|]ÃB‚7í¾ELI _¥è(åu‘&¸˜L˵VÿYCañ£ß¶”´Î.§Št 5«˜Ä3OÂBwgÎâ®dä¾®àxJŽ+zïi`ÎÿAIÙus²‚‡½á‹¨ÓžÈŸ-®®>˜L¿-£›sÊÛë«P'"¦èï]šŠ•seàXñî*¾2 \ÇHM…ù²&œöñ˜‚ÇUâJ0Çò·Jøv½ÎBúâÇ¡gÁqª³èEx\Œ¡ 9u%©¾‹%> &Ü;R‚j˜òº7‹S p„èO¿‰³{¢Z†_™É{×ê‰Ô~ Ý6_TcHÇnZÕíuúvB¡½ÞÊ#AcŸsÀzî<[ÌÙÃR\áèiN¸„ ºÎSCÙÆç¨•~CeÂc¦^zX\=ò¬7©Cïô`’GJãM>±õÞ¥÷+S0BÞ¶ŸÊ²êê±Ø5’Û -8è§cµ¼±]ºð,¹""Ýý‹ï—ƒ¼¥:}G8‡g–ÌÏtq½ˆËÛôôÃF8ÃmÎõßÛ$Z£àë+rª¬¸Ì{‡˜yé&Ze¯ÎBÔàuö ­>Ú&`^t e[+@³v³6žº·˜€¥ “ÝUIHÓä¥Ì—šŽöR”Tˆã¾ô¼&nçKý¢›3l#œNDNîõ…Í»Ûwse¥o§> q›2è,Œ_æ}­84Å{Ú¾ë2O(¨±H_q󸂝¯©A•âͷZ"¦r©@ ·~õ—¼"©ó)ÊIŒ™x~ƒ‹ÿý†©VÿÕ$5 gÁ•;þFJ ¥ú[Í»+³ä†g –¦gÑÎWR$Çk¥†Žåà$†|‘ÇèÞ†béQ;­ë¥»µl´Wï·®§¶f7Ȉ³|ª–‚rS‘ȶGàçšÛôø«¤SZª[”ð9EøY¼«%1¤öc9?Gçkn*yk }oÌ æ·++¹ÛÜwaí—P‚Í`c‚Çéj±Ú lÒ±qJÒé1cU>¥‰¼ÓUª}E刣DM¦Åo:µ%ÃWþ¥ó`å¤ú<šéTV;ÝèÄ”ðúfùn'¦Z€Î3¢ø/üº*@NÄl‘·Mìú3î«wSbfqlÒ‚³KSsÊbºHÀjlÑQ0HŽ^ssp)¹-½ÖÖ„À¿›ç=ârX< .ºõ¦|ÐÇý H~YúkX)' „[Îê´±Å9¿&ù³Ìî7UœŽÑµS}þp5ºðá¨×…Õµ¢z]Ý+¨/怯†UIÛ(;¾·è0A°¿…Yõ3çs0¡¦†›tf† :ÌŒn‘Åèœÿ™ SÖ´h}´“±,$FDÊžÈyøŠý®ôgŒú9õªÉM±·Ÿ Ÿ#ÛÂ[šnIXÈœRC”RñbZËö9öYW-ÚÇUá4¤yºK»gÙÛcÚ­½ðnU­áo]î:?(%ÙâºÔJu -¥\¡è_²0”îÜ?¢MüÈÃËóm&?2Îû˜PbŠÕ0Á#n‘Pôþ*=‰p¥E8t¢\g×ë“æƒnðIDç‚s“ N¡K${iѼ†­&[_Ì+L-õ¡¡½ëwÇDÝS>É2±­ý ¶¥†hHÂŒ…5iœqŠ\8‰üNÂrAvðÐ*Ž€Ùô€y‰cÉb/¬9¯9_Ôx n©º¸ÈÚîŸ*›Â^îÿƒ.ÚðÈ ‚jl’¯ûÊRP{ýÓëí±*¥DÁçÓd‘|~HmqÇÏ_U ú©ôÔ)oÿ$²‘ÉI÷¾º ?¦— ÂY,ž<µ"yiü>’›†WÂçËne8ÑC˜:z«†¯om•hÀŰ®Ü<†Ë[x‰xP’ªG<6T%5·û'> ”Ö³iRXèU‹hWâT3!({i²åõòýÖ.æ,í%}[­üË`iP{$òŠå|¤hjÜ—-d’k‰£ºìW¾Rß[¨&Üwôí¸ý#q‹ 2/‹^Fi»NH.=Ùg¸+âí¨D’¨5ù»H¶\ËlHªÕ9·ó„Õëç {“B¢À9wK[Z­dLܵXã¡—áÀæ¼ùeÝ–évå¶ê…väûiÂS¶–%Ç;óîš=Pࢠ»ˆWù¸Ezl"þ#¡o9¨shÈàÙZ‰¥KÝí™°¤` Ý׌ –Ò)EýQ³Ø(9>¾Ù™ ·³¬þ­ÈÓH•§/4RV ü§F?‘V¤"*gÜ}Hw„Ñý§K¯‰“;¡ÍÊV°Û‚ôÜȨVmF¤”R¯yŠÑZ‹ÙŒk­çM rħކ¬{»sV4–Òµ>Õ‡ÚhCº9ìæ&ù´@0YŸPúVwD˜j¿Gç^MÇÙ*Ž’¯Ë:Ç’âQ[Šh>ÅÄÂù_Ër¿2@‹Ó”Ê«´E0’¦íH;D 󪔓5 aÅ#{9Lù6 «Ëm_›PCÔO±c-&gݳ´rÕ©Çü}ƒÝÖ¦ó%d"vD(î}6¤¥%îx`µ *üwÓŸSj½ÇK!ø-€†RÉga’½çV ¬A7ш™eü&,ë4nv)¿§…΀ÉæßÍ"óH3”9Þ)ºà’¡#åQ[’É4Ôön_V™R)ÐT;†OÄwNdæ‘§¯Do\¤qQÎ#[/ã¹£5Øì:’…¥ÂV\¤QjŸâI:{Ê£GÖ`÷3Hò/à7§¾ÏãBå½Î]ú¼~7G½{›ÄÞ[†ÐGMÿÉžs¸Ûx_‰­¤CöryÀË^]úÓH°¢ô½‰v[û‰Ômà-+^eÁ´ ÃÄN_•[;ÊVP¼Ä™L¡Ã<!18Þû«ê:\@è_›píàd.IÉÁËñBÏ‚Â(¼äþ†lým…B£ï׌#ÙK¥›x¡o5˜Ҍ℔K£ñÃúeN'N/†?êôäØß L…'hÀôÛ²íRÏ O‹ŒvñKʨ!cKf§üLÄ%–XIO²o‡¤ð² pûeI–ÇqšSL›ÓÓÍø¤LŽr %HðAÍ'Mëë·µÎTT»†_³- ‡²»<ˆaÌ~Ö†~ƒoÓ¯³zZy:©·_ÍÌÁ(ô9¸~~l;¸{‹´¬È1Yê¤ÝV©¼\w.âé ššª|ïdº.ë¬ÈYÎðÞ-\¡Éø™D£mM29œ· Pô2haä/$©3ßÑÜ¥{ˆhºà,Ñ1%ˆ‘Õ^Dr彉~Ìöeì |àçl©£ Þ¶CïÙô›©2Õ²ð6J’pO`NG`‹ÊݼéqYYöúb5äÇe̤“¤•êŒþ‰;œ¼­ûäSCi‹=Z°uï"ÓUrzp‡ü·"»"Á)HP‰"Rú­4fµLET³êƒ·¾Z€¾N‹<íîËK«R⟶ù[žÚ‡Þ6˜^ùÕ|?u{Œ¬a¬«,qìóFnÑ»y'RAÒ|D÷ );STâ¤jÇgß]©ÊÛf æš–Štßл ºñ•ñ„räîàS±,TP¼ó,gFF²²çb®2ƒ×æl!÷« ‹ø±XYßȹZøn"h´Óûó+¾Á/¡fsý›¦l °vÃl\6ëþ‡_üªmYöŸIäùÞ¶[-Nñ2xaF˜tLò‹|Ê3ÌôxÙÜ•Á‹lõne3Ò°ìÒâ䥳§ï—nIÙ‚l¿û–³×'sÁ&ñ ‘¹©˜3rÑΫ׼ì[®ÿËýÿü?a`]ìÎvèèÿd£¤Þ endstream endobj 46 0 obj << /Type/FontDescriptor /CapHeight 850 /Ascent 850 /Descent -200 /FontBBox[-39 -250 1036 750] /FontName/THQWSW+CMR9 /ItalicAngle 0 /StemV 74 /FontFile 45 0 R /Flags 4 >> endobj 45 0 obj << /Filter[/FlateDecode] /Length1 712 /Length2 13103 /Length3 533 /Length 13654 >> stream xÚí²S”nÝÖ¥Æ;lÛ6w8b‡mÛ¶mÛ¶mÛvì°m;¿sþú³Z¬›lyW­ÖºY£÷±ú|易”PN‘VÀÈÖÀXÔÖÆ‰–‘Ž‘‹@HZ“€‘Ž@J*ä`¬ïdnk#¬ïdÌEÀÈÉÉH àlJÀÄ@ÀÈÆÅÌÉÅÊ ÙÚ¹;˜›š9PQþ«‹@ÀÚØÁÜP߆@ZßÉÌØúŸC}+E[Csc'w:++…ýâH `ìhìàblD02™:›šÛèÿ…$ncbKÀþ_²‘³Ý[.ÆŽÿpPüÃII𥑭•;‘± €^ÆöŸÕŒÿaù߯ú¡úÏpQg++}ëÅÿ3¦ÿÅÕ·6·rÿ¿|[k;g'ci[#c›ÿlU5þ/4ic#sgëÿtÅô­Ì lL­Œ þK2w5w36’3w24#0Ñ·r4þ·nlcôŸÿŒíßôJbòªŠªÔÿ>ÐÿòäôÍmœ”Üíþg꿚ÿ]3þßõ?Ãq0w#Ðd c``ü§ñŸ÷¿¿´ÿc-C[#sSE'}#}£ÿ)ü¯L‚‚¶nž´Ìœ´L¬ÿ\ f6vVïÿg£²¹½³±¸0+;'Ó¿UCgc§_‚öûßµ‰ù?Ó16v36df¡šëÒàR?é=ö-©vL¯Èº‹¯ÒXŸóÐfÇna¬ÀéV-Bƒ-å×`ß/ä¢R_)ðùÂê}¤¹ãúžuÝݱª6ѨL&»4÷Ÿ¸ª£Ohç‘›5@è{¯£Úu5©óX=uÀá·îòœìzî† 1[>–G}zÖª4¨{Æ×#Ž:¸ —E\%¨³uŸë lf„Œ41Ü똽­˜ƒ¿•øi•}›ÄÌ4·.À—Oô™¸ÔKÑ! 7C±´Axrž¼™ ÖïW‹ø;Í{™tÑçnYÞª®~ƒO¹ˆe¢¼Gë%-qÔÙL]˜ßŸ·Ïg¤¾q¾)ÅXiˆx`’ÃP qCã~*;ŠÆTðzH0½‚QįéHbÀON2Ä/øÁ)yÍdU›™7Wtöüyüeæž–¸@í¢¼wœÃ\é³Yä73ÿpñzüÁé—BÖ®1œ«øVG„º&!èY 3¯5+'‹Ë,g¬.Ë=F¢Îï?5‰8»d¤]›ò &ñ.´nÖAY¨¯>¼V›LÒ Ä†ëX´êN$äÒ‘‚ñàx–zzŸæàêyƒXÞÈ_žL™þñ­S⽫*˜ÜÜÜÅÁhnzNzsß=]M'Òºk@}w|Cþ3•‹©Xµbß–®Tß­ýÀ†ázu«†(¡ïdÐ@'±¦ŒqxPÃÚî¡bW,,˜U8kí(°À^Ãú÷).ƒ$³ÛûkBä\JH(ÿǯúM±ñ”›xEø[7Ûj"Öð'=SBZ.ã‹~àŒ˜Ë HÎ<÷?XÀ{rZèÆQ ð5L÷N_cc®’°JƒAùóvf›uªZ*ô›„.z™Õ4¤:‚B¤EŸ Š£ô¬/ãrȺ DÌzïô½À Iõ Y:TEáß!ð{eî:å÷Ð c"]rD`ö•öØ%{Qûˆwt=Æ_ßÙoç8ßÅß»ŸH|±b÷æÊO~¹1·Ù½Î¨£×l8'bjè shYÝ\Á‰¡*IÃòо±ŽV¿ ,‹“ÐYªˆÖ=•ÑìÎlÝZQBÝXžEî™+Q¹f!§Gº?žTúnÌÎöhù¹íƒ7ûï¾OºJêÀ/¢rŠÂ²-ÆÍ& Z¾º™û—”38­¥P:Ð’{à~(—ÃyÝ­,‹@½ø¨|•fùdöï {v›zÙ¦m:$i9‘ˆÇŽÁJ34_c-L/ឪ?Wuû_y^9´•!¸',a"çtä]®=ò’ÌÝè`ž£™lN…ñI:Íéí–4ÙÊæº‡x¨ÐÓZ\Ö$÷­^ h,˜×æ !'lq"J*Õ ŽiÃÚ`nm5¡­ñ²0Ĩ-8¡)püMƒØwŸ‹ºj£0ê˜Âz¯Î ã÷ÍBn©Ó9§Q‚¿>¥ŠÝœ ¥ºh¯ªa.þF9'›Jí#Qz\ñ PFÇHŸË«ŠÂå×`Û–0ÝHð‘±8D?XqÌo¡4}¿ÅT]´ÌŒK˜@û²s?½¤6šÊÇ„ªY °lHÒߤk£L® Vö!˜ÞAoÕ"ÉCíÍË.ia=û]XŸÕðVÀPDó£EÖš§ó;˜J.SwépKŠÞ¯1q$©aSâ1e¬¹ ÜQôxô©Í\Wªyéwš OiwEß‚f_®4µüüë:?½{(»ãù־™K†Ö)·ÛáñÖ#Ø: ˆ\“ÈB :c-JyxñÈ+CS‘~ßé#Ê’Ÿ¢‘—FÄpQ¦Ô mØYÛ²;ŽCãá¸\Ì«Žàíf{Í©nñFý­kaŠˆ¤ß&cËmA›Å%Ú6ï¬rxm:ÎPìÔòošúvcåÕ‚’*‰¢³TÛQO}ϰŠ#2Æî¤«„]u 5Ÿ] ^Ç&à Ÿ¼nÕš6©B70¥Š|/ᡎím$O-;C˜˜8:Ora×= »ñ&k˜·,¼wž5¾=kStö÷ÎYÚ>B4sµéH™-ˆç¸l ê—X92¬¤oõZ}&Áe ²„äÆjyàÿŒSÜ ÖÒ“•ØÚë?Añ­p {N«íA´5µ«ø{®ñº ü¥¦ê¶«FÝ•Bdà~Òz…j'¶žlS8¶lŽJY);íú­¿)úË/¡C&[vH®dªsß³»Š ¦ÕÝZDºk”ÍÏé—à æqºÍ¢I3§B#Ø?Ö#ø“ÇgI=ó_•a«ˆ‚ü ʾø4ŸèñØfâú©‘°Îõ+ê"Ö)šD<™‘×ûrh¸²KJÍÏÉK‚-réK é™L×}×ôwIùsز< ’©«åÕvÈ17ëбU™Ì X\vÏ¡SÕP fÑ´/é´v0V‰ßØhÈ£%LGÁ—,O½ >&)º;WÏïȳ³2‰Ò5|ÐNênÀŽÙ#¬Bî8c–Ê(vÆoß%f˜_Nüj¦‚‹´~§ õV{Qk¡çØë— ¢¡Ä9eá<ʬ€+‘ ‘ü õQ\ãÓ,EK)á¦öw_Œ ű.Öm#ç^¸šÃµ‚z(c¾ÊyãMKePŒ%„hÚÍBUe$•éý(%ÙKÿnÃëˆË)?@™(qÈ ‚nÀ6ϽçÅY…gÜÊߢ%)ѯ1(tá;:½S: ŸBIMç’e#8ÌiP]‹ƒ#Òô;a†kЧñ§´ÍÇÞJXøõü×SX‹U]ÜñiÐ+{‚Â8+3'ø(±à&ŒäñOe‰¤39TÎ+þùÃæSWWû‚ÿ KCdû§ðlÈþùÁ$Æ?ƒ˜ÓË–.û¬kWËÍ—˜×‚êŽõ FžÝÓ•ïé^óW©Aq,'G÷ ëiÉüÛô(9¿Åõ(Å(ïËvbàìL Ûû‹xøµ1ðA¿qJ¨Â@³–v¼fŸy¦ÒLVMsãXj·#2ÉÙÖ=0Q‹Ø|Ð~Çd×”?¥ïv0©[·iÓp'ãç^¢êÊ%0"M¨k»që)Vý.ža?›­Ð‰I«Áœ¢‹án {ˆŠClTZ¶qXþÓnF$kž¨ðÞ¬Gª›ÖóòŽHÒç… &~ª8~ïreÅ’›u¥¡ ‘£öžw”ìæ\:Ô³]¦¼ý]/UöìÒ̓·MFR5¾ x‡ñ±g‚‘竃2P'÷š~ëÎéÆ-Gb …D4ËR7¬¼ËFŸc&d,EpgRÄ{—Qðì0ª³Qö%‹—KìÊåD„YgØÈQâãͰìeg •¬Fyœm/,’¾àëÚ }J;D¥œæ.]´¿\\í‚ц´ÑëZLÎX85¤‰•£èj\r?oh@®­Ÿs ÎÚm3rP˜ºµLò+ò†RXgÄZѺ“$VHÑQ`‡:Âm@Ó.M©ÛƒA,ÇìôÐ'@/dSþ]ÒVÇæDùÍ*Àva™V# ’ý7àêš®¿pòfmðìÉÁ1n-ÿF8³õ ±2 4ÿî«·Ó|‹ úT“kÎãnù®ö÷Z‹þ]Þœ£øo~â 5‡ÄšÙ7ô¬¹þ÷ªÉ“×WŸ‰¬ðxuƒ¢ØÕ—¨–’gö@)…ìxȳ‹V¢\òWHÇãVPú—þL„@¨À.dކÐË:®uxp$_CC¸¦T¾,ÎægU8}ü’zû“~ôûÖjŠó S°zjÿ#(ê Bôë­Ö¨Í¦Uþ˜ü ³ÃÓ3ÁUѱæ×ߊã퀾³›gåí f_á@d³þ©/ÈÀUÑü «æ§+—µL%¢;¶VR\[§â탗A=,(ÆL|†·krÜÄ•;ô3ä²GÑ› ÀÚ©6¾`¸÷™ÈÅ`È ¾Bz6ÒE&×VÁ9öšç_Ç_»ÈËbû„ÛB–@Â$?¦"Û”úaÔ' ÁµWSØþüØè°¬ IKpe¯ óUAª}O ~*ÅðƒðZñôj̈©l»÷—ùÛ1,Á7´Ì²ï ,O`ÚÇF/tNjÕGu’1" ¥Æ¼ª¶gÌM ò·ËØøi*ENÔþjChÚ¹Öå¹²ƒp…˜D*JƒÆëµÓ8OÙ‹O]6eὬVËqXH =Ç”ŽeH³(¤ÆJnq0ÄQ*oªÇèç.l6¶õoýæ6óXå~©@C?Æ÷_—Ž8W?ß¾»dtÚ pÌ"Ä5–fÝM¨É:ã§ÑocXÊ¿CËšÆ Æu2Fmõ>‚¦5Ó#$GdK·£>u0(€crª©¨÷"È2‡År¥·¹£w`½Ò tð[VÙ1ÇÓ{“¥ŠtÒ†ÇàÿTl8üQVÑ`záúì9FŠ©$^•ëÏ ˜{„òQˆFPN‡6ÜITâq÷ćÁ'V(S!EpW¤Ý6w{Ã%ŒoÐðpݹBŠ.ÝwÔkÛ P1ɘ•ËG2¢¯å6JšèÇm'jÏ„Q@ò-˜äãÁ¹Õr¦ßÌ´Wm§v^œ uOº·– ê´RSV7D¾W‚¢‹Ú:oá³=½­ËëfRì<ªC“ø’È0Y86ý0ªò3ß-ï¬ê3Ÿ²BèÕÃçš+¶ŠMR²Àô^Þò’Åe°!«iË L‡3rëž2IýÖb_o„Y«ßpNä™!º—K.;~(ÿŽ©½à?ʇÞl’QjÈ2¯œRØøÑ‡Ñ)ê7¥ªcøÞòîÛ*¯®Öït¢bÜ+u^úStí¥¦÷¥ýr @²ÄýýõÞR|ªitåó2"³Ã}!;vቌòõ>˜§ Jº6 ñ–bz•ú×Þ¥ÛÊô e‘–9Ý¥»LP®òÀe- ‰ß¼_ Œc‰÷¦?Íæ}n w¡ÒBu¤äáÌå±þîxo!“4ñÑ/ùì:…b2Æ£¹üȺ°E†íö &Ý7S¬½Š/™Õ죘ÍóôØI¾ý™WŸ…B¢ë1ÞÕr%UBòÆô‡ƒmö†l¼Nkã.î¡êj¼CÓO¹=õ{.%ÊÛ/çaó·[ÙÎHçg&ׯ!â*ì*Õë¨1­VÌòþG·Ìå±ò8¡we0 ±1.mCÌg±`PˆGðÑîU‹| R‘Ç A̳KÜòíåí_óú¸èí [‹¯û܈šm‰Ã“L–-;½æ*øv2•h G}4J0,‰×Û›‘ùÂõB\åŽxÕi#5x¸²|¥zj5¨@ò-Ù¸¹¥1«ªê€«ÌÄÎoßN„Ïæ2½_ÒW–ƒ# g‡y”Wñ4Ù6eóøØ>²_űݛ¡£0ø©ªG±e0|E¹‹¢ ¤ÔHÕ"ŒAª¯Õ‡É0zÅ©;øZƒ±›Nþú“ŠvܘdLŒv5× éÔÂ`´P%ˆFŒv7:s& M¸Ø[°pCݤ I+!D2CX"î¼ÒÕs•\íÓ!H²!"_MOÊݽnò—Éõû¼‘Ó͈ì5§{ü/µ å-sÙßÕÌï¤ñ$ÃE¥ zíõíe ZC©¶žQT!ŠýºéØÅ<? 6¡0&ØCŽ ={”Ü]£/ô5¾ª#Íèt¹,¸ VI3î&x¹I#5,êrzŒvYÉ4Æ/NJ¨nÞß„‘1ânÇ5ÿº &êš³OªÉÝ(Ïß&Æù|ps%~Lѳ½™ÁCC@€]é¸pÁF/ïׯWwæŽ0óÏDŽ œ¡tŒÕDú<KjÿLY¾s»¹‘—\GlF®oF¤B>½i*f~Y}tƒà|<²ÈaÖí&/‘O3óG¢!.¼Ã5‰öÑ!{¯U™XÓÖ•`á¸|DzÓ5Ã;0ûõ@ªj}¸i.œJn=Œ'‹sñî,“&·'h¼ÏnkiRùŒ,ž0;ñœj„@§I3í.sHh°õ`{·3å€mnÓ¶#äC:æí¯–Li…›óƒ¹í-5Ë×{+óþf"rðŠGä…£>Ôùiìä&wÔ¶A‹ØW[íc¨bûi’™¤Mɰ‹›®C‹M¾îSxÓ>8}œ%B›à„Ï(î¼ÐOEGÆØ~,`У‘iÿÖÝo/mô–€ëùUGà#¾eKÒËOç¶‘Rb]À0<9H`þÇd)òF[†`„¡\ÍÏ‚Òh!9xuÉî~³¬Lj©j1£TÄQ?øp+5®—e‚x BISÓÅ3/¾†‡ëœÆ•m 0aPµÓ<[e)B‹ú¦F…bÞnab€ˆñFÉîUqq­u½Þ0¶§ ¡¨ª‘© dtWjZLî·¤ˆMwÖøV&‘"K¤|ÛÌ\oÌÎ= ò—ß™Eq@úìMh…}ÅÌ96„c‹e¿$ds¦iÿ¨}óN€ºàòK¥(½yïÿhåíÖ‘_Ù>ó@ݸj{³Æxýf¨ÆNGгyΨcƒ­˜A™FùZG÷v-»cù9w·É…./øà¢-g ¯áò Ç#z÷=AF–ðdË )r=%þÀ•=ÙŠk9޾ع­Š+§øzšX»5_QlM±³«¹šý2¼ ¢=cpϳ;yÞú"X‰ÂÍ›¼•ù†õW t³Ä¼7:<辄ôä•À0è>w.?Þ:/F5]N•ÛÔÄV8TÂòVÿÝÎæà²¬ôîÛ†Òp®éÂ/1íÆË>¢@Éoj%0H«kØGíC²m˜ÿBY“þÜWñž9ßpÝj®l›¬º •Æ1ѯT@ÝªÒ ª½ ¿et¬òÌ`¢ÉèÛ{KDrëNé,øB-±p“ñœ(¢°á{«WQN0ˆdNa{ú£©m"±jm%¥½8Âh«°Q¡¨—TÐgú}‘a€9 ›&_å~ÇNV4ðœ‘ΆdËJYíê’è£÷­({ b|¯ Ù²éýädÚÔ !‡rÙ'‚öŠ’,ôM³ç© VKÆ'b´(0–;¥—vZÃò¸†lt¥gç|dH½H'ÑtÉê+`©[qˆ°Ê­¡b&%2Ÿ#×'½(LÅÓGyÓŸæ@ߥPÃΕ^e”G`P÷(صü!OwþœºJ (‰×I„%™™F¯cî’–Û5Waœè¤6nÑÔ4Ñ£_Óª™ àÅ<)2üÞ`'÷ÃOÄ¿Õõ¡ˆÎE†Â3‰DfÁâ ßÖìÉú‰[‰Ô¢Û)†KC~IôŠ+åK}¿‹ˆ~Ú×»†áxVïþv·á<ùÐuÈ´wn2qy+„܆„æ—'ókÅÃc\u›©õÙñÍl#ˆ¶¯ÀZ]0ñ‹ecÛÊMH¦²\ãÝWNˆq!‰xºÀÔ5ò óÜ ŒGP­ˆ”••Ú ¡ëU.äŒvB[Ç‚î]Éñ•ÛÉ’ÄZÜ!ZxåÃfÕÅâqÉÖ/CôþÆ×ÐôZ% Þ„ó°Cˆè ÿC_;Û®uè™Í|pthpÉY*·Éîʲ4‡A®Ò´‚>ìró:Ú(†óô³1?…ÿ+>¬éʶ66͵;Éù|RWÙµÞuÒñ/ôrJþm$B'Cƒ›BaöÄq99_e,v²¿2Wbyéj ÿ2{#-0½ ÂѤþ ´`ruTbë,>­7NFVìó.ïð6øv~Í d ªn©°¥8¼ª×‡>>\Z LÛp –qà|5tT½¹ÉY#%}·OÂ!ž<:üÎ÷s\Gå¯{ŒÃÒ$“¸5Ü`‡îgg<ÔPâ& 7&­^kµumÉõì|ÚP¯áíø0^rÚ£ð<Œñô·&¨Üz‹qŠhü8c–x¦À#ªQÌrë±âù¾é-¿þdâ16ú G9Æ×³¹¢ÕcÛ@¸f¾8 ý[V]4mp‹"ÎñðÀ}ä[üùÅîSõ!VêÐÇîf´¿< y…ä7í§ö9nP „`½®Ñ¯‰ð¶û…[·…b!á8"ÃäeB3§gµ•'­€…cß*½eôÐ%§æbl±ùø’w=Íx“Ú tbãj bÇ–¦TªÏH™4 5ŠÙÙÁ*ö¦Fî™û=‘~‹Ê— ¼N¡0mޏžBNß]Z xƒÛÍçZ Q°ý€2 h ·¹2³Ðx5×ø›ö¢¥ê¡ƒt-¯¬B:æŠ:ˆ¤Sûo ðuNp¾„ ¤·CâÀªšä”b¥$#„İ䪰" Äu·þîX ¸»¾^îäQ¬ÃHác£ExU…)¨ ´²ÉC™mM¨J#J\£*@œ·)µðf`…q¢¸¹s"ò hœéøÜÈÇob u©<\²º•M±e H£챤ýÉBØu—D†öawÞoAq®[äó8v wòõº&)Î\Ôè¯LÛ³M^¬X¶ÒÄLܺ‡ušÜ–$¹1çQÀJlqwÞlWúêýEÐÝ[96ÖÑH±l6(!ÙR÷´g—, É1¼Š08Xàÿæ)€ÁíhP}=Û{–O“¢Í±¹ØJžÿ£^ŽS²ÁË=«éû§ÃÔâÙÿ§%Nõ]áý}Ì›5Ë¥é7ä/söçáY Ý»dÖE_H@å/ÂÜãªæC&‚™ú¼ý…Ù œ{Rê5¤XˆÔч™„Tß {ËŽ~Óùv5Z‘² N0wCõQ¦üᾺnÆvƒ¨Ií+%Š—, UëÁb½8 )ªø#&sm‹+ƒ€M–•@âG¥t–€vª# $RûÁqóï…_~ ~Eoyý¬k¸éÅN¶>p ¹Ož‡€­VFiit.‘BeQè hÏAãJ*絈u–w¶A®žPLvÿ 51‰éDy1«¼nh4¨‘V|ÝðIOŽEïÝPt’ T”ÁOp&LAÅx•É|CTgs—l%[*Íîh¢»˜s|Ž¥g+ÃÀµbð}]Ääßr¯ Þ·w*›¤ Fîfö]….žìQÈZÇE÷ BNûN=ds¬ÍÄ*Ú̲†±7q¼ü}6tLqã4ƒNžx¯á Îë’µ!íë†j“wcOÕZ¹a8vxºlkHÒr®öTÆëi<Ì3s³ýE¡´¨Õ™dòÖQ}˜èæ©¿Tæ]ïg™‡­8Fˆ!}z× …¾µ0yë›RœßÆA—ãkOç ÉC=÷!!eÝŽ“Œ¼ g©Cî ïãrß\œ¢ ºò†%åI-o1=Bp$7†Ô§¦"Þ&¯9ç%™çQ#Ï!‘Ô$ "U»~–ä^D꽑ð‰Çh ¥ŽzÎöH\ip¨úW$g³yeÅ1r}ê,CùHÀ(Á>Ò&%‹Èù*ó}U È#ÉeA­ç÷`&ºàUî=$>ÃS‹Q%ó¨ðâ£|Ø'Ãá_ŽNÀðt¤3s‹¹ßđÌ=ïß}p½ãjþVCjËÒ…,‚i©ºØwùüÑr™£ˆµáAMš¦ÀïY)­Øñ–8Lcå ž3´}¢ÚXg;= jß´“•l‹•›A±‡l²Ôq¡Ô§ªwÂÍ¢ ÛEøÈ~Ûd sêî%7|^Ž®ºã"9óž¢i¬Ü¾ÙªôÂ9”™ßÉÄwöÀ‹$Ìx G'Ép1º§·Šv/ÈU‹³çUÁqK§©H |‚èä>Q8ßQÇþH™/Šlˆ´¡•t'ž#W…r$¢U®ê㺗”bS¬ôÛìÁ¼¿0;»Û/qö6BSÞû·øu”šÎ2-U†{AãþÃŽ ½â"‚írêÏz¢?r¶ÕqŽHƒxS¹«½ú uè‘›óN„@¯O4E$£åsÀžåTë«¿Ù…0xÛ6“‹)ô~’?ùB·ã *ê’Å XìÖñ®`D¯ï×S;&1=b®nuá0a`­­²·25qã#Nó„Ñ/™Ê‰ç´ÖY£0ÎàRY±±¾}ÿ:â¼o—dé&•¡(UÀ…ëÚšHºŒî4.%'ü(mÖåüø¶:xôËÐìÚÏŽØ­{$µ©¹)W €«³igß˯ õ­ðywÁ-’0U°!úÙFñA|-Àšü\ì6¤¸QgIr¨îGkàÕ/ܧš>Þâé§œ ú§Ñhæð&4N‚3hv 0õêˆÖ3Âk˜5¦±›!Ú˜ýG±m¤ aÖ‹Øvx*­‹Ø\aÌ ©«w€‘öÎô?Άù½|¸iñ‘¢ÚÌ|yG‚M³ÃP¯­~°øÃN6ïG¥}Òtj™tŸ—Ê ­FÕÄðú Ì@Ôë[‹£¹ c¾>~™£AÆÏÝÚˆÕAjð; CÐiµµ' f“Äã‚°–äü0¥8H8$™æÉçýZU€†~wæ,ìΆš8O!l˲Œçb„¶«:¯*GGÍÈô8q>U;"1$Ü=h~$¯Êº©¿G¬à˜„†3MúÂfI!Èä žçvhZÄÖæq±Ë¨³Dÿh/ð›øÃÙCÑ)nÚÆÁ÷×ïÜÍî¸Ð¢:1Úí^âÓQŠ×Rq…þM¥”ã¯l᫸¦VM$¾LK9i<Æ1(= ¢nÌÆÊJdÀ£µçŠŠ—ë ס9qÕ ˜o8•ä‚x¥é¥õúº†Æ®²ÉÅdrRò‘ "=q¦ùË™Cô ÷€öµv_Ÿ$J% Þ7B£ÁR¾«- jåÇÍð‚j)lZ¶¶ÅBrô2ÆBwÂ_.(Q- è£FŠFúÍú÷¬ªÁU§y ¢PÌfâ½¶÷2«u]N%Uid1â4ý‰éfÕöý¢T¹œ,¨â¢dd-¥Ã•3àŒè;ð[¯O…ü²ÅÏ( z;©¿¢¹%6kðº9¼ñÛyÊyÓ qßÛ¾@D䨦³T©5QI‰¨=á’äúHZp#¶Ô°/·~ÀŸWõ•”$ÓP5CM1SÇÄ*Fˆäåy‘ÓM WúŘ—IáÕú¦öi¦°š&ÕÏ¢¿Q²ÝñiÒz¬¼ü+0ôÞšDO8¬mS+ß„‡%öA:M`àb"âýßVëãÈ+â÷­G”Gƒ$ã Ô3Ãb®H zûä8fò™,d¼‚ÇdËs+QÄ„¥ÕëçnpѤٟãt„§Ä™ˆ¸Ó¾0óRüpæ¼Rׂ€Áü½SˆNóŽÞ¬Ë«UÅOT€Ç»-]ÖB_ËØ8qYµn&Ÿ>ô·´¤àèmæ³­)Õ”OLDöú†/b ~y¦œÍ@0×ë/°êt7ÌCn‚@ç”*e5HL‰˜\Û\¦e6£RjáDƒ±PB÷ Œ‰Œ »ìŒ%·ŒAªˆ·*éïRóìݳ™$ª„ ®\¡·H ÛÂËùDû¿ð_GAKª2ú€Z6 »˜:rŠ8áÙ…Ä]Áv“¤(‡&ïÇÄKV½ˆo ûT^ÄY•#ÐwÉjÛ*gœ¤Ð(Öú/ƒ™¡É¢¡‚ë5ë™>Ž­(5dS`Cµœ8„?‰¶¦³Ãv¢*V¿Ó÷ü?ˆ—›-‚DyOá-O‹ô‘ÅöÕ43®^ àTG'<4ô>éëЦ°¬P:˜ðë=@BqJEï>°~6Ï~g¶Ú\„Ró§/òyÝÇÒ]A; ó41Õ°ó$^¥¦vgô貫“ýš-LKÃ÷’OÛXX)Çdñ· ŇyNŽ"ó¨oT»LléôϵÆ<ÒL†>*`9iŒ(ä‡T0Tȃ¬0 ð–´"Ya¿Ïê<¬%.s~?ùQ.>oû î5À!^_4S“9<Ô[ÍÛE…>&ƒŽ œ)h)àÈ?—Äæ²—÷ñM´ûi¯Ù*`L™¼_ª­ä›^'YTæ É)S ñ?®¤g¢:rû+ 9[ [ï:H*u§Ž1e³tͦ²½Jb…ú<3ǹ)a¡¥Ïy†äÍ}ÎÇx壸ÑÝySî½ /Ü¡üEà«-q 3ø|Ãþň»T“7;Å´–j»˜ i½ÖŸÝ»ø£ö…aìHZä\ÅôË« ßß¶¼VÆá.ÞB D]ÎcþºQÀ/zX‹¹JEú1r¤o넃S|á¸@^2Å;òäà!<øÏîõÍIÇþþkðiâF>“ÛXÐb²UÅß^}¿Ž¥‡™-Òœè¬?*±C"¸_.ÝrkÀœ?}pZµ$[,è“_"ÓÈêÕ·Î#‹ÎÜÐ ¹žOOú™ÜÚm\|¹RÌ+ÑÐI”}Îɼ<š¬Üà*çQ%XÏ5rê°"I?¤–¯ñƒÕ[·s;’<}n*‚¶«TIOò …–½ó6;Ü1Òýö î7®PåÚáí¥“$v˧~†Ñ3ï°çïÍl=É6g‡¶g¹iš/ŒÂp/¹׈žé°óš> ^˜†mì–Ìm»'Âý1˜õ&N¸,÷Ó³LH¢²©$X ÿ šàPúªT…Ã{Ê4ôÔ 8ö4²Ö¢»møÈÞÊŸ§Ä̹ô’=>¨b~]5”§Húc”ÀÕì3¦6‰LΣEišiH½W.>å Ë@ãw17šCmã*ÅWVE³”æŽþMæÈà–'¬¨÷FG‚fÖèóRûR qùÙ|*qï\«4 álž’©•ð¸êä¼KŒqùÛØ·ž ò¼zS¹/+õWQ, 7LÔ¥µ± |H–||Ý‘0”Xú`ˆT½ÈúwaÞA¯©¿äv8ì>†r:’ˆçœL ™ÇX[¨›ƒÿM;H,ÓgA<© ¼ö_™ê· ­ÖY÷ÅCàý·ušwLãL¿s ©áEÛà5FOÖÚý2iØÕo¶/²]YD±ˆ«v²:[bç6³KN©”yX>*r$]»I ¨çÉV´wq‘õÅîØg0žÇâáÞ›ñWü@äŸnÍñbO µ8‰Ñj·PéëØ^/TË‹$}ípgL]Ÿ†?jÒ¶üºôhjj.<œ¥CÝðÙ}à|rtaô|¥fe÷гxÍ«“ý¢2ÀÀ‹'Árz rÛDGRFQ#d¦nz/~ …r±’À1òr÷“ýt­kf÷´uo7ññMìlÛˆ–’þÊ#oÅÓ¼òAHõO*äØs¢˜êÌAQôâ~°Ä›»;€;RGrV™l‘Rr»Îá͉,ìªélï@áØrÆ‘EèßX`Hó4i¬âÄ@ïdƒþÎ…>Ç`³úH£nö~ 0ô~Ùp»( šAb¶§‡zMäiwNYß9Îú–—þÆømŶ¯z‹eFÈvDÈ6w.ô]\fSòÆ:‹;vFYJÔñW ­f“|ÂL2ɧ¿²Íš`¾<ýÊÕÇ+ éBMƒHoi™ƒHs71AÉâ•CM]ÉÉÔÔù¶Å„<¿[E˿䘧¾·×d¢³aÀUOÛ´<â”@í7Ì’U—úc¬¬›×0²Gu´0Ñ©K ? %”Ò-_hýïãÎ]YAÒ݉MȵãYòAT&Ž3ÿ ½›Œ‰á)eA†ÿÃðÿü"ÀÐÊXßÁÉÖZßÁøqßÍ$ endstream endobj 49 0 obj << /Type/FontDescriptor /CapHeight 850 /Ascent 850 /Descent -200 /FontBBox[-53 -251 1139 750] /FontName/LFNUIM+CMBX12 /ItalicAngle 0 /StemV 109 /FontFile 48 0 R /Flags 4 >> endobj 48 0 obj << /Filter[/FlateDecode] /Length1 716 /Length2 8574 /Length3 533 /Length 9125 >> stream xÚí–UT¶¦qw4Þ¸K£Á5¸Kp§Fk‚k œà®ÁÝ‚w î’à>9çÜ{g͹ó2kÞfMÕKíÿõï¯vÕC1ÐhhsHY;[‚圡0'H(£*­â‚8¹1dÜÀ0ˆ3TÖ‚„„@@)[ 7$ ÌË'ÌχÁ”qvñqƒØÚÁ€Ì2,ÿp ¥œÀn+ (PÕfvúbeáÔv¶‚€a>œ@ ”£#Pë·¸µÀî`7O°5'´†XÁ€–`[ƒëPŠPg à¿dk—ÿly‚ÝÜÿr™ÿr²ÿRZ;C}€Ö` .5ç¿ÓÀYþ±þ7Tÿ.çáè¨fáôø.ê¿õ-œ Ž>ÿápvrñ€Ý€ªÎÖ`7è¿[õÀÿ‚“vvüocaŽ+)¨­#Èý/ â.ñ[k@`Vv@ Gwð?u0Ôúßþ®íŸ\*rjºŠªlÿñJÿÕÕ°€@a:>.ÿ•ûû?kÐÿ¬ÿ®Ç â 4âæäæý5þ=ÿóÊäߦ½ƒZ9[C ¶@m˜ÔÚÂÍú¿„ÿN%-íìíÇÁÏ äàáA ^!  ?wÀÿjÔ…B\=Àв@~nnnA¡ªVnn`(쟟Áß'þÏÚòw?`°7Ø #3ë ÞŒ’íÚüª{ŽV¯u|^££è4ÿ&øçð¦#2ç‚}d¸ƒÆÕ"öñFlÚ3µDTíU‘„îÓ>²ŠUbV›Ñv£­káʸ}Ž)ÂFC®®3pl‹™Q=[¿Ÿ)2îÚë<˜KçïҦǹ¡KÖ†l#‹õ;1»mpÂVsï¼”Ù²ÍnjP 2Ö†„Ÿ§ÞðÝKIÝÀ™‡ýü©ë®*cjyèÞ…iíôcÆ ýÚd-ü´z‚§‰Ùˆ@ÑøDÌ…7‹¯Ë”ãï”IÔ|ÉÒs÷]ö¼4³³3éæÉºÃèçtéYcób«.á’M2Z2J²öªž÷è®äx]e¹ÀtE7¤ÃB%hÝ „œ´ƒ©Ãc•;ïƒvI]£'ï?b›¥˜ò ¹Ô'þÔÆ°{_ƒh²Ñtä†u£ ­¶¸ï±<ú±•´îbù©¥lx±øYÒNÄw­7hsÛtܯÆjÇàµK¶2J 2!SM´µ?ŸôYóõI¹ý–¢ÂÕ£Âå+Ƨ†¦¸Ém—þ9…ç.‚Gçis¤št—z…²õ »ýÝGG¥uò’Øñ41 ©•†Ð¨+ ¦zL’Äc?ÖQLc§È ÛO¡2{¨¨¡IŠ’x´ï¼nT¡'¥·ººñû[ëñ‰°8ý›njÖÂÚSGó°Ji?¼OÇ0Ùf9÷²\Ω…ξ‹Ç·™Ôƒë™ØØ«bquÒ± ,_·CÐÊ»Îk"•›ým¦™Lú 3ö#ÅóËKKY¬r*ìé[5ÄÁ挡r«e0ÙÈþJɯ±Þi!36Kâ-ÃÐÞowG/‰£Óß2¬I~{ýtº¹§”· ÝËÕ¯c¥LŠPûoqÈ ¶ºW3ãLyŒù°€¿;ópÊHý÷«U1…Ã>ÅPpú›§ÿ@žoVþîô½8È3ùæÿÅR-ábS3Õ¸uæ5ãð„~êçJÈýuϹ¾› »?]K„Æç¬V•;>%C‹Îé—›÷’aº¯k_5.Éî±\“Ü• }DØ8“÷nOe%}C?×U;óÙæÂw~ã}pÑ#"Yx!U™ È0@G•G©((Ö¼ˆÀ|Êvï«Cµå>ç!½ÿ*È# Þ˜a-Q¥]D0|>È?š¶”PúèfÑæ(óS6^:&6”дzûŽœ¥¥`·o—[G o°)eŠ|onñÈáE_•®ð°p>AÎÚ :éæÞAdØ:1”mÒ2­áê'M‰• ·|™´2¸Ø:äÂe鉛òQ4`‡J‰kó#š·ÍLܦtÔÙ`³ßŸèÝ‘›ßq˜bÓsYRð¶?<Ä•0ëœkë58o7Égõõ¾ý*ëˆÔìPNîCXWi÷î\;§þ¤ÜAÁELÔ_Ö’úø-è Ù¢ø8~ííÙCÜPBwjÁ©8ŸaÀ ^v8B̈:NéÀ›«E¾{ÖMS©í>ТåÒ‹½P}v–žã73þBJÿšb$+äZØ[ÆßÏBKØR&F£Ô"þje=”BW÷óèv'LßïÙ_úÅÒ~Ìù­]±açŒæ§È‹ýUŒr¤9Øuq·¿–оÉ"é6r4¦Š)'Ý:r|IË€G冠Ķ[AÄïð#ÒY¨Ö×ѯã…ÓÎòt*utëOãÁåæïzè²¢µÔ,®X™¿e=¹Ñžáëá­fN±$ö!Û·RæÄ¯/zBù}/swø† ¯ ÅÀg@ÑgÙÀÎÙQš!¿ÐÞq½nïF…Ka0åÞŸ7i2‰sº\W£§!|WL´V…ú÷ßé4zÓïlÒ_Ej‰*Ç'Cjuy_òŸUŒ1«øAû• ŽÏ t?~R½lÀÁR'hO³ìéú*ðX•uÅïÅ‹tÝh’¶HRßðÃd%ÒT¶¸ylð‘|g g_Ÿ½ý´†ð\$.tÆ»uðÔL²à(€Ðs5dÁ$++Ôy¬ zPô-ÖÍô`Ó–…ó˜Òò¶OR€%û=Ùtõ*÷¦NGšÖ¾ î²:qÜWÎÖ ~Ãé»?,ª­P­” Ô9³F¥as™#S{ßæëÈ?$ ^½}—dG§Æw4Ü»üºn+Áëîõ;jŽ^»š_Õ0óÂz“‡x¶¢.p•ïÏX@#ôÝ ‚ r|Ý\§L†Ët¼‡ï]OJÞ“K@Së@Ð4Î¥Á¨,…±û¸Ž$4š'ŠðwY¬Û5@8º•Š@8\U+½cwíËiOa(]b™”gZ¼õ²xlË8ÏM¨8­(ÑZs€¹GYÑ2˜žÊÌr›ŽQ:šI¡òÇk¾Ü`¥Òb)OŠJÑtE.úŠb²4@ÿÔƒ—ëÖåÙàÞ” ˜/`ûeúVÑîT®¥6ôûW?É>ËpöLB@TÕ ´Y]‚/~D®_Ò㕚֩êfU>H µj#d|øÌÇp4‰ûéL)o$[×ÅŽ[ øxéÄ(„ÜÛX; fhc#á?õ›ÖyÙß8Û6ä“<ÒlÌ‚Ÿ4–ýNßà _g=z4ÙÌÂÝO#oÄùžØÆ°,Õ¬«ïtS ½«¨ºÑ»;ʡͣ*•O£«ÊkÔú<Óƒb—éÔN/œÄýR·hôþú$ [Y@AUÛ†þ°jÐSÐc•‹c'»'É8!A’˜bÿŽNš»>ÈwÊĬ±(îU 0ßHŠ»b+,ŽûÔê„w:öë5± ¢ |áZýéšû3SyïpAB2†úÝ>¸¾rC»‡>øO[ò¨ÔKž-ux:xƒzÁóà>0¦ iûÚ5Û¢]`q̾֘A€èŸux†QNŒ9±2À†KÑóíW…ñgœŒÒcÍaMñŸqÇZa•HÀù6×jjëª+…Ä÷`?–L!H -Ü#ÊSŽ¿,r >S[©èC½k°é¶€€Š)šp%ldJ¡?<àôy"öË»ƒÑw¬´îË,ÎÎÔNW•„j¦Ã³©}xƯSZ‘åâùÉ—Õ¯BÍŠD.ˆ,ßÊtË=*£Óï•80_ª(V묧JLýðžh™J\T£þùéÂ! ¯š©í‰-Žø¸ýaéÄà:¥Þl;>î|S?ÄkT°ë³ } ü>íæ¨ªÑaª€é-ŽtF•Ž{£¿ça·<èX¥¶ùñ²Øã*{ÒÓŒ`œ ³©OgCA0¢’aõþ=GÏ*üôgwé†į_’q¯g®^häJ†ú<h"™Ú­v"¸Æ°†à_’jÕìfΞÝ,~F'ÊC•±ù¯ÈÛk'1VÐ"bcÏm–Qdka @ò‡Ý[F¡¦Ójryí›4Ìîo8Jòäq¢Âmš”DcÀ‡Äæ½À;ƒ6 ŸÎÌ>—W}E­­é<*DåŠÏv³«Š lQM™ûù*Ûw¦Ä_ÈKK…ÍÔEAä Dâ"~nrµUÊO±,(œ«¼ì¼±O¶azÏ­ZBÊÌZóXÛ†I9TUt²WA¤È²×p_¼ÉCQ/ø…-D¸¤ #vW7yÌ5kÕŽëY,‚uíùîÇÊkÒ&¶ NðVqXZI×8L4}Ú64™úweUXœêK¯·3ÚÙ5ÖËQ¿¯ ¶‡¢È’¿¦q¡x)xiÈžIÌgëìª|M,{kîš1šG¦·Ak¶6›öûá ç1Ľ Ž£wâd³ÛzŽ)Ùו±‡×óÂxœ|x–™ú!7ÆÕ7ÂÂi!žfdãvŸpÆ[¨WM[„X¹DóvÞë#>ò7ô£IõúŸŒl¸ŠèPÛ‡Ú\§’¡EÊÎNÊäô©¬ØI1$oõ½_ð;BŸ4Ž_Puåû¬É=ï3»_ºDìUÌ1M±ÏUk0üÎ!*x¦œÜ¬;ÏÎ[ÁØ®(™+>Žbûƒâž 'ƒ`úÊÚ;æ¾_²<–î²}_¥ZC/;v]õã1\`ßÃ: : (qŸ‚0â¸@y@Z²,q_5É^°Ê¡‰žPÌJ '|9=fA;Qq:QëÈ"`ð¤ãÜSÜ…XLrÓ]Ÿ[éøöÏÁÆ—”bLJ, Ê^Ba@u?Qúúœ‚d~ïÌÀ¸ˆÈçÎoæÐûr6ôGò±¹“Í‚æ9Ù4ª4ZõËçcѺ´mƤš†­fiÑJ–ßn~!“5ÒÄ•9p›œ Ê9L Cý%¹€ ·RGéÍßuž4‘}€ßeÚ.øGT¡=³fîW}Ÿvû ²¹Âê=ÉßUô?¼JTÔ'Jä¦/Ö8é¼à]m_[êuAïxWí#µM<ƒ6t{cšè“ÎÄ}ZvFÃùfÓ¦Â|™ó{bw=N²u´L ~¨+”L1ù§Õ.}à0Äľ‡éÆiÞ¾7áä Í¢ÉÐî&¢ñ½›ÑEUðŒØûˆdUÏVõaÝUêcšÐÎ!(<è³ }ÈÏïBq².0åOHÎA©AGê)S?&†Q¦91‡¡ è^‘ *¸øÊg  ~î¨ =«3)”,¤ÐŸ5ž7sÛ–ZeAJÍûÌ!Örd;’­+Ù0ÄÀŽÇ㘿¡îi,þò“ls®àU[ÚÍ!‚UO–…ÃÔã‡5 cãSÇË?>¡ ›l«se„ÞQ, vºÛM°†¦ÒM×€>S’ö:}µmÛEMR\I(,ßD†œµ½N{ã€ÜüpW+e›ó ‰Ãªã§®=¯Îµòƒnj±éïUª*mñ£S]T¸¾|öy¾uÛ·|ôÍ¢"œ”DI‡=%c"L4ÌáX]â7€¹=m‡UïÅrÏIS»?¯Ed QÔÚá¶ÓUîE©<à1áÌušÀnDc¹N>ž¥…ø•?}çÜ|×u…ÎǘØ^ ˆAȤ%PÅ>¯…iŒØé‡7†h^‡Á…1ñ°˜qc—$³ýE§6“jê—%z¿UvßÛ¶cå“#?ô“È*Řv=§$œ¼òN[¾Á4^e%_ÈË¡l3”Ó;íÓùÐÆxÉ™U ÓØãáZÛDW*3¢Ë‡·‘±‡°™¬þ.[ô´À#[LèjøÍqÞ«y®¬Zn˜‰ÄT¸gr$ßO0 ÏÓ¦&Æ€âÆ2£½ºe/†> Gú « xø¬ÕYÓ§Æœ“?6'9³eThƒK; m¨æŸ_¢ÊHxƤÓã{gÄÑqbºP܂҈Üïj†›®áhÏOÙê²Óí,ÒKÖZEåç?±[JË뤰)fR‘ ×V8™Äcœo™°Ë•©f$ȨȆ¬~V›–IÒšá‹ ºÜ«Ç+v‹†¿'@ìbÎRâ¬40m† nW9ïDíRåÏtN,:ßéC˜c4ƒ.æñ¦oÆ¢†ÒÏJ?êREíø§1)vq·¡¡tæK~@öÝ]ß•ŠK1ç¦ííOýп¾ÉÏE†c­Š( KO!ò`†ð/êL/+e1s?J:ñƒŠò:D-2Žg4³½BÙu-~+Ë¢‡ÔT\šÅ–Ÿ?c“Nª“U˜ñöDO4ŠÚD(R¾¶mHí徉¼Q,%ŸÇTÓPõkÔO÷ÜéG3 I7ˆ±ôQçù1T€âkuƒ²Ë D®nèÆ¦´÷ŸJ–T®_4$bHTµ¶(‹&´ŽÛ‡od ôð jøéoLçSË=Í_Àó#.5¢Ÿ¦æÚK­ÂÇ?} ™Y ÔBÜ~› ä{¶K”=%yéCS‰2!–Ä­~ò"h•¿·&f¡4ýQw)èzÔšUfåX£Qf´cy\].ÇJÐl×HŒ\ÐFd±§­ÂbC©ý0/ éµ£Um{‚©”°Ë?oõÊÕ,÷‡° ø]½,Pضir¡.ý©VýŸ‹TUÌªŠ‡›Þ0Æ|r‚è8š;(PŒ³sòdÔŒ}d° QTô†l8Û’gï`¢YªuðM›e­¡ù#+ZU8¹·+½}A¸ˆPÉít¸¡5{"Ú 6pKz ìoG­ÏOGQ»±Ïµùéu‘Úâ€Ó%­þ "ù®É›º7hœ jÍ‹\HA׊5Kuw6·ÚÚ[´`ÛÇÜäýF±'2½3†u å—iq.ØkR¤ žû•Ñ|C+>3be¢E˦&È=?ãvuh„GŠtKñ’1Æw SŠ aú³”¨ÛÇ|RCF›zq²@I4äIá*Ýú#ÁÿÁ/ë2:ê6óûE±hÈ%ŸÙ|P£²Ù1~ZœöcBb*ûÁsý«QzL<mÍÀ®(¨·lºw}Æ^v¹zˆFVÎÒ3® òÔ»‘Ð8¥þH+oyü¡ÿœ«ÏAzH%Þ !¸æj%)ßeVHNŽÎíÑÇW€®Q¯ÖFTÝ4ÁÕ÷²£È‘±ßÄeHiᶯþmÇä &eåÊÌ„ä/IΓB”õ°½&›ˆÿ{lÔ¸¹vÑeÙ*íÍûøæ4žHq³0ÂB7¼g³®ºãš<Ñoe”µòËf›-ðߨµíÙ#C"…ÍÙ2&ŠÃ:WÜk›ÝÊuŽoÛôÐ\r™Ãg²K^6¾}•å_±œåàksÌn®ˆ.hU½ÏÏ!<€Õ§h–—ÖÆ§™"Lõ 5,‡ýU‰Ý²n u(ÔW«¢ÐÇ}-—YZ¬&O¹3Â-´{ ŠžE_ÁQ•@þ­ïÖF8ìµ½1È(ç&v?x¤ütÇôšÌl@£Õm²‚¯Fê…^&oÃuDž˜¦7:ÆöxÖNZýDd݉¸ï)&‰ÍÑÊýàø6¿á‡Aõ“p¾GD†qªÌvXn;±”×k'¾Ç´qE(ÌHw—#…Gñ\ß»¼§³ŸïtÑ/Š/KÂ\6HI5©¨nSƒP²¤cŸt_^>ºIýÒb}”‚3w6œD„¥|áÿþ‹²6™!aLÏ¡ÉË[/O9¾‰. Tž9µ}QI,õoÐ4…@ý· ’­Ïââ“a>|EÄ&H>Í"ô›h¥SpœÍCà<ÒNT9ÚõuV ‹OA±ÿË@TºŠÂ6жWÙ¼(kuHFIé¬ÛË'¿½¢[€–»ëmp¯'?B¬Á_ þ^,i@o„Sž .ìîWúµ£$Fäpëû9”1êÔ™NF T¨k$l¡+Y‹ñ<~,»ý²Š/8–©„~‡êÀýB¯/ÁXŸÉõé8âТ[Î=% k!Ë@‹%þ_§øtrbû‰=øÐìØe­û®Þ )R#,(«ìvÁR+á6‚,îf•€õóšÜáKoC¡ÜÖI„,hcÎðXƒ`>l€{‘„Wdœ&ÇÕé_a2QÒ8W}ˆ€Uã?E²«û cm÷%ÙRĈœý!Íý#6®­Î&²ƒõ5!krø/Â*ôú–´}=Æ`w7þu‡ûS $”ˆ›±dÆ Ø¥ƒŠMl½åQucÖSêa;Kα¦oŠŒÜZJÒªüè(¬ŠœK›*Õ9 ŠúJ·:EÀ!HÛY——´³èæ¼›6Uk”°-ÿiÓà§¥ðKú®Ð‘nOáQªµ®Øo]‹Z¥#C ô•2ðj¨)阿Dgf¿®ùâ(az#àQõûвxèî×(ÞXÙ²Vð,T"]Òð‡€^úuµMË[Î>œ{wá™@À¬œ.ùïÑÚN.ÊœöÚ³®FÆ©t€sëdàt¡ÛæÞA÷ L\zEñª¼d‚Å1R^zƒeÏJ̱{‘dûÔAáN.$»]ø¯|HõEÌŠEB !‚kmþ·ÑÄcº9„‚G.¬ŠÑDÖ>Št®zÄ9Ž9Ëè`29Ž•{ô>Abæ ÙzÛT^.•”ôù \rÇOR~·ã›<÷O VTÑ¦ææØÎ³7Uâ–¢xØå¯Ü©âΩ—{\ ßÅ? ½—§0éhªõÁ=)Òê@?¨&+A®hû^;6Ž£™TYæ²¼§bËwÍ;Y@q4´hŒçË£d䶨w,Yx¸µÑó[ÔãR9xPìïH¿áào×Ȉ o†é¯¦šVÇÖ>tH'ÏöaV …5°h2¾“»¿Å3.^tø¢óçi M ÙÛßÃ1>úª\_ $›”‹Ð©œ$òôs›h³U'çP!>³ï*Ü {„‹0z8äI¡&®ß`7Cº-·Sn²¤N¹†ßæX°c¡8,9ŠýQü¼Vw­2Ký ÷eq¡å{· ¹f}YÂoøÃ¡SŠŸ¬ªH³ú&”B7ŤÌv rÍç <òêLpÌXƒïó€²?g¼ÓÍ!aL«zß½ã…0Mˆ~‰jã–UD—ÃJMÎÁõâmknž½sánlÞÑy™ÝFÓጪµx·èè NÞÁRtÀ ¾WÖ­Oóµb³s?\ DýØ gwóÊ43v™çÖª³"±¯¢‚ASs”ÿÛëwÏJàgYÖ·¿êX‘x¦V ûè#3+xéÉÂÈÆ»r^ÔùªÏ1xùÚ·_d¶®†µÍ\’W_òû4í„§– HË»4÷3NíŠã©¶ñ½t0qbµ¥ºðD õ4½Â˜KÝt•U­‹xç¿vûºt°¡%°×ò( ‡ocj¥éØ¢hÊ"¸¦Ì9sqµ¦ äÿè™Å\HÁ5ˆ]çÓN—õ¢Ÿ% º©'kÛÄé\!þTs+Ûó)Iz#¸POô'ï"·¥›âO½9÷~³¡#Övfq—ËCy¯Ä~ØÆJÀäm†í…ól:è‰ý2¡Ö,­¨s(½½’¼ ³ ê."¹Ö¬‘>{Àñƒ=§ëÝyj2 ¿ÿYòÒ†nµfR¸"Ò–ùìŸá¥ÊëO’ÙÚÑìh$ŽÅMÔXGG¯­.rKT'šÁRœä(˜ò!»Ê~–³j±²_¤a›"cð:iµ|ïÖ*5O[ØÇZí(ÇãdmHÆïàõ¡•7üÊÖ³Ùƒu>^ojm¾ûêÈ>õVerwÒ%¢<µ¨U]t‘y¶öˆk†@nyŠÚ5Кv¹è„2Jçãß<êÒUÕ$—›ÜYâÀ‡R/¯[£cy¹ådÏ–|^m=2I î¿Ú{~̯rœæ¾D€£ª/`Ö¾½úõáç¯Eœ;1¯d‡¥ƒº”aÎË.¹roþwVV ï Ü3ÌtÊãq·•—'\C>±kö;ºuÚˆÜп£Õzs2àœuyGsM%gkõ}¹z«è ‰š/kÓôL £h[uVfÀ~=·ñwîÿËãÿü?`å¶pƒ9;Y¸9``ü¥þò endstream endobj 72 0 obj << /Type/FontDescriptor /CapHeight 850 /Ascent 850 /Descent -200 /FontBBox[-251 -250 1009 969] /FontName/UEBJWX+CMR10 /ItalicAngle 0 /StemV 69 /FontFile 71 0 R /Flags 4 >> endobj 71 0 obj << /Filter[/FlateDecode] /Length1 720 /Length2 10451 /Length3 533 /Length 11005 >> stream xÚí’ctfѶ¦+N…Vló‹mÛ6¾ØùbÛ¶]±mW¬ŠQ±ÍŠ“[眾·GŸÛzô¿½×{¬9ç»ßõ¬¹9±¢ ½©½1PÜÞDÏÄÀÄM$"§Ì bb„áÈÉEœ€F K{;Q#›ˆ‰‹‹™Hhüwò÷åfcåfc†ƒ#'±wðp²4·Q‰PÿCÅA$d t²41²#’3Ymÿš˜Ù©Ø›XA DDB66DÊÿøÅ™Hè trš2ÀÁ11™Zš€ˆŒæ–vpŒÿ ’²3³'âøWÚÔÅá?K®@'ç¿\DTÿ$¥&úËijogãAd 4ƒc”·ÿ»ð/Íÿ1Øÿ†ëßÍÅ]llälÿaÿ^ý·²‘­¥ÇÿØÛ:¸€€NDrö¦@'»—jÿÅ&4µt±ý÷ªÈÈÆÒDÈÎÜHøWÊÒYÜÒhªh 2± 23²qþ3´3ýwˆ¿û'£š˜°´†&í¿Žõ_EE#K;ª‡ÃÙþCýϘéÆÛãdéN¤øÛ_¦¿Â¿ã?gzÿ¶˜˜‰½©¥9‘ ÈÈÎÔÈÉô¿ÿJXØÞÝ‹ž™‰èïçï=¸ˆ¸Ø¹|þW¥š¥£ PJ”ˆ pp±ü3kââä´ýó&üÝñÆf–ûºMàüU”ä¨Î©Ö0˜•Tóo¥á¼j6|k±mi;Þu”#ëÍÖpÞäol¨ÍÇwU¯Ÿ“~Òœô“qó>¼§RkÝã‰Áž×êð‚ò(¬uw«¬o9ðò†D(í3mê)q¼ÚŒ=HOš>„ °lfy¥·ªðV2 ÅeA‚öø…»ÒZ¥ta’ ñþ–)QÛõ‰UŒõ¬Ïð`ywYëGÎtˆU1xb+0gh1o_ãþ_–wÐݬà»f›o<ú>‘1Œ:×¶¿g¶ª¥ ±6v3iã,i©oÁ¹½‘Ì6cWtÑož¤ˆÍÙü”Je‡W/åfüºb輚…!¸’žû¢™´;6cº¤‚w„ç{04P§"‹¼Å2õ­ý”-âÝ+‹zÄ… p†bàuƒÈcûbesõý.Ò¬ÔWsQD³² dåÇ4HRŠ2“®’þ`e´B×%ö@î³o—¿hØD*ùFõ[²?}ÊU½d«ö,Uð—ÔS¤ö˜P‰´·t%´`hâ¤ë5[€^ZŽ'Îèž2¬Íï@¯°±†“"ÛÕãhìf㢾|ÓÀ‚ù’å\‰Z6ƒ>nãxÍK#9üåy‰Ä¬CÚÄåÓ1«JjšÞ¼4%`˜å»uÊ3»9ƒ¨Id¦/C¹©<Ó)æ@5uü)˰ Øö(†íq¥•œ`)šW¡Ë]JÄGáîz zu?ÄÒó$„?G±oÜ‚åðs¤>/F·ô´à¼ XÞ§ÁJe]•FssáœRŠWêÊEëÚAí{B±mRÜv‹Éü`¹ Ò›K[Í)vY‰2“”ŠnÈEÇ<Á×a$ ª?µë¯ô¡Ä/¢ƒÆ‡½ÜÆÅª—I›äÓªBßârs\Fv­‚eV7¹/‘q†Ãža4hƒTK1õO}£h‹÷Xü‰™ ›pâ,c9GÂÕzÖ¤–h^GÕŒŒ,éPEtzeø#|^êdŽ!O£ˆxíü~»î*1‡WåI-Å £˜íÿ¢ÝÝno‡ð8^Á”æ]†GùDàè ÐÂízÒ B=MAÞŠ2áõœCzNÛ|yÕÖ_ÔDRmäÅW¼ò.:I\ð¡!„Éݸ£%¶Äë›îï&.!â6ô„y§÷º¸þᦠ•àÙni’îk÷F/ñ¢~^cJ¢‘®¬î?¿ekï8è@¤ê¶K É¡[Æ«A+F§0*2=Ÿ<ãêjì=·ì%ÈÛêB¹H;7_q?•[/!yÿ™DÿH܆óÄQ©Þ,±à‘(Ä„h–˜7)Ž•é¾dYíÝ$N:wž †¦ŒÉÂK²L±Þ®2Ú?+$ã¿kæ\ÑÅ/Nkµ«°D;OXô÷@…³è-„Ïà‹†@K÷m·b¨ C™Yá<¬,˵ݼ{Ù)¨sïI CwP³JÝuÒŽ¾©UNŠøâ ¦ZóYU–OêÆ•ÓèAF¼¨£É®Giˆ±ò4¬„%wšÖ”F +Æ9߉Óì*³¦<õ%±R”ö52ñ‚¢ÃâDv€·ÿOj2¯oœBßðøìcóѳ•ç YˆJ¶Ñ“zu¿f.œûb×zaĨ›Íˆ"¯âç»6ðó™˜0æ–(C®Úö›v⢇ìm…²5±È|IpasÚŸt2ˆU€ó´µzVÕ³^¾Œ0x7TfL÷üEdùqeø]{Žš×ˆH? Á—÷«w†€M&á辋®uSÁ®saCjÝÓ©E™Ù]뜕—!B1žIçïn;‡UµeßcPzp/–,°0î/cÈà½Oêfj!‰í)6¨(_‘4…좖ì:?’ÜÃÉ&í”Ð â$s3ÕòŸ #3Šª÷É )?CÏý˜åÆšY—Ñô·ç¸¶IËë ©JÛ€²ÀÛ­by˜7%še$ȼ%0oV÷0L=`”+– &ŠûˆOã^ìÐwÈÈeSÕÚ+CÃo¨\õœ&aÀ!»:èǧßL¤=° œ¨NoWÝ Ö†ó¯Q"&@M« Jâ|Ú›•—(hÚËBÝÊŸ_Ógä8›2d&8ˆÓ RÇÎlo'2µB"wQ!ð2—_ÛO7Å6Æ• ¹ïŒ¨½ø‡aFkg°ÚÍc;Qúðr‡Þ™X‡‹¶¬íe]ÎÓU͆ ‚ýÐ]Æô‚~ôºHr¬?[œ!.Û ÍãE¬²U;ïLd %vÂ…$;Q BËÇ%r'°\Ž ÓÛQ[ä,*³´;P°¿®xë ݺc†)æ«x†è¦Ç`mÚí,x{³œT“ø.ƒß8˜z~ÜAé¹ Š_Î[Ahª•SÁÊj8cF¶‡l–N¹z»Ã% n‡O$-pK&ˆA€o"áÒ÷¤Èߣ·«Çñà©P?¼õœPV21|{fͲ©>ÊŸËJ6ÔÝl˺1ò¢£ö|0NÖ$5ÀNyè¥?k”+ùrbf8«;—\¡zOûÍ~ÔÛªn¢‹,Cq¾tPe)aÙ+ŸiTpôž›á ”½'K™ðÛØ;äÂeòë -YÊV­fÌþ]òô½!/²+&!‰~±Žx¶!sÅ넽fM j<ÜùRεٛ‘›gq0t(Û */=b5‚5¸ª ¯Uu›q3Yƒ6MM7qk»×ÍÝ"9G›«°—䕆ûýÁe¤"çu@¥oEä£RVnxqÒMY;Ñ]ÈCŸîZ¶23I¿H¼í:¶ˆ®ëÈaC¬˜•rŠ1ùæäBˆ¾ÛÊ€‚•tÍÞu1{ûtzíLÑ›6èÒ:xBÅK-Öç«ÿÉ'g[òp$Åy…WŒ›€L^ÆH Ú?¹‰Ïé!¾ŒýÂOÙ&+Ò˜·+Ѷ“ÂiGfˬ¢Q(ή“E‹¶a1µ¼/—±bcJ¬ã°ePù"Ùàé-ÚðJŽ{,»óÁLûÈe×7ÙYLf$¹^„Á†[³³mâŠUÉ}tßš¢×OR[—gÞv–«Žõ€½rÃŒùLóm|[Œ?¤±gepÁަp­aÒvb:”0X³¯£Å _O/Wò"^ˆƒ.]áYÞÛì„EI·ÇþøX"«²Äfˆó(Ó¶)ZX|×s U>å™±?°'?­vèZÊœ£8 \·TÎ×͉…䢸ðè^‰©Jð`«-¾Ô~Íi™ó!úâÇzîZ\*Æ/¼è¯q¶/µR¯wh$jw_VIœí§V´ ¶ÆšbÅmJH^ü…¥Ž]N/g’ý½ê>†’ú%DÓ2Þ»oɵÐUßÃH";W&“æÄQ+ Óá‚“ «¢i Æ®Ïwˆ²]ĉ$OÊÄ'&©½wµ]£ F\s+)'zV¥‘2xrB Ïe=Ÿ“úÀêìå¬ÇäÃ7¥ô¨'p5AWžüCø£R¬÷2爛qëxºMT[8ð´W >¾¶_±C›ž*j«éñ¼h´&ÀŽ ×ãþŽìŒDÐ =ÀºB/ô D%7ÑUEËULLãZWOøºá5ý#¥dÉb`WìmŒ? ‰Ëí²ã„OEw]:ÇlŠ\pŸ:ÖœSð>Yûá(À‡íýµCÒùhœõ+v9­AlX'Ä~…}´·ù:Ü0]ãý½÷ûà—"²×ÐQ7My>>k$~y‘;}Šêº.šP'[=ú(Iºîà`dÄdc™ÑþÆ.EŸ1›è–V9pþâëúòi?@cI" ͧTä {¦–?CŸ.-Ìêó§Q]J„•`òíðŸ>6™¬ ð;ýÉI‚roW×½ÁþÊË]§‰8î&3‡ò¦¸IâB4§t·FÏ@e'e˜"p)´†áú¬˜F«I¬¦th2Æo‘Ù_ó`§ÄÛ[Šš’·Ê23¹1ìM^%\›¹œFLªEU=#sô¯]/E•Y€°›Û<#™´¯f®®\fo{áu©zh¢[ª¶*}»ìš bVÔ8ÒÚù_åYèèãØ>‡y†ßCø¶½(·ê¢=N½œ…N†-Ðe<m¥fá&ʽ7\߇ ´GBáæ±ºA&™9Ç)Ùnñh¦d§£ŸŸ@Yk5Yø¶l„¯ð”¡‘îhi%£­¹{8m ?<`oÑMÒ†T¿GhzUMÄ£$±ÄS”U²Ò†Ë[ ùqj„±ìJðª*2‰ƒÄˆÝm’Öò‹5z±ïÂß“¦ ‚evéåгD‰(ïÉ3Ü|¬¢uD.ÁÔÇCU#¡í»wö}\»é-˜R³‰¡œÁ´™ø+|FϘ>œÍÑ+½ø¦í;Œ¶7+ ¼WDZä:J\!Å4x»U[\m­ôÈ{hñÖ8±Ð7W¡Ù``‹£uŸÞQÀºr• ç[”—ÿ{7¯gàŽ‡;hwaÜYes£èÇ­–&"kûJ3PZöµnU¾‡T¹óàB©ÿÐþUƒƒ>¯ 1ö+Åü}+C˺ŽMu `z¶‚À(ˆMóÍ©²$üÖïdVÒÀk ¡”8Þ¸^û¦JÀÚ*e€W[ÚÔ$ÑÁðWÕTF±| þûfl'ÜefÆŠ™ÑÙfŸ>2'¶õÃlü±¼·zÐÕë' Ù€Éñá¹zÀÉ5s -ˆ÷ ~ˆƒ"8Þú|÷ÆUON~g­Þ<—!g×xYøÝÍúq/4·J.ÜUŒ°IòOñÅjLX¾Í^¡L£ýJèñi}têmJQ·yÝIˆËR!d#”“°Z÷Êg@ÜCÌ0n‚Âú…»þp²C|î}²þlTк\/DZQ‹]ìêN Ô—ܹ±·¯°ÝuÎþÙâÓ­ÿ¹½ÚîÒš$¾»ç‰#}EÉ÷ÎPÎùÝ`˜¾cÂéÛ¯˜Æ)ã&þªea»ù©µo$>Oç‹¿Y# H¹µJí^ˉœ~~+"Î‘Žºù½½÷ü# “Íngã‘S؉Þk ¿P±‚ÿ 4£ÓQ|Oö<‰]®1º9Má1Ðû'ÇdHÛ‡{!‡ã›íÁÞ«Æ;Z3£ÓÄšˆLðÛ⨠|ËÀyØ#,díႪî:&r~€ò÷aYÝÂÚŒT¨L¡ |YŒ¾)„ï`è.ðªžX£3š‡åÇЄ\ÏÑŽ‰‹û\Ÿ¢…‘ÅžÚ@·àyÚåqWÅ)e”иâcªP«Ž.`"`á‰Yü„q8; Œxi´ó‰~ëuZ »×p÷ÄŒAɽ¥ã”Sÿ¥…Bwöè&¬(P—­˜}|s½ŒÚ¡Q˜A€‹7p Oª„x ½¬º>åÏAyÀñR´PMvrR†à 9Ì7™Ô¾>ƒÚˆ^h"a¾£zV˜¸ìumìyy ŸTÑÞyiu©â¬.Èüfw…ÑÌn>¨ŽýÚ®Õj¥³†èíQö8mD EùÐ~èp¢P8ªÑ-_¾Î¬,¸P¹ „Q×j¬G¤?ŸMç“¥­épvKäê¥e±¾ÃÙYÚ#¾)MIjËÈÖ‹Èk'%׎¹s ¶YKÈdŽñª’EßAD€þ+µ‘šýw@@©›ïï6/v”:ŒÑH²_©Ó¡ÉbïNíµAþ_XË ¥‘¯¯wÔ XÔ2¼ÉƯcÁÍÐOV†Kבð=!žÞ:Œ.(‡~a‘.Yz?/´¯Š¯›½ý¾#-ZeH¼Q†Õ[ Ì %”grdQhÀ´Ê*x«wÊ$CJ¿eøïD¿Ô%î »œ£}V#`I‰“pÖneQôñ´EËZ¦3í£þ±kA+MŽPEçT¬ÈbVÇ™ÂøÖµü8g©MDöL/’=¸ðûßßË:é_{ÉÃP¾ û0®Õ¼èSxß·1Ðt/–~LT4%LÈj(?²{.¨»Å/¿v*Ê£Ò­ÿÙ±Øz…ÔNU0îÀ ÀÁÍ‘š.l³.$¶]P‹@S]8ÊÆÕ i·i“FEÌ‘” µücƒóŸ¦Â„ýAÙßRCR“„µUÕ'7ûÙY6œZÆFú§ÕM`ÚºGL0v±rô]óÜXŠó›ä›ØVÊ‹¶A@Ž„»€—™Ç:Á‚0”5™´Ôã õjÉ´.ÂK†t”t¯8«íN–>"Ɇ4¡X£ ©ïèîšÔ'9â¬J¤†ùÀuÞA3V5~¨ÊŒ+þ[- ÃLðv˜LÂú‹aÅoy• ¯œ’¹TÉDk¨<Àìþã ÿÞ~ÊŠÝQ½}ëÏíB=ç± õ¹…k>Ä‘Éãî·.–̦K¸¡§W>Ò¯sPÒÏíÍøŽK·0J@yº¯°ÆY§g¡?Y¶ÑÔ¹RiÝÚÝ„¬1jhAÏáëbfq>w« ænCÀ*¼­X%ÉÃ&âså&#ÿ‹3½Xʼ¨‘¬qÓ Á²€¶µ\ Å%>„2›jJãNÉñ<æžÁñéFPF×Èi‡®p¼ïC®"¨›.r,£ cÝ åšÖlꞃt„5?án]7™ðÐEGÅ·* H#ä%vMèÕœ¢Qäêa•@€˜Êå]JËÂühv®ÉM€5n¦ÀÆm—[S ¼­]y!5ù}X_Π1¨AÁÛ›×ë; }Ìq²Æñö"ƮռƒYËË©=ý’éµ-õ%}?Ê|>ó]ÝÏ–,:h‚Nį¥kä_ÂÙPIÏ©œ×N;°µ½p˜GŽÏ/U'¡U‘d«HÈVØbRºƒ"1’7ôÂ(òp%ó¬AÆe@ùÞˆdoÕ¡ÂÌ8Rßk‹×NbBR9-Åy©à;«Þp í¸ë ¾;=õvPœŠ.Nʲ¯m㨡pˆ€Ûþh“L’åÎW•Æái{y¢Ø éà×t›6ó>%0ùÅ¡z“M¹ýDH„†*6Ÿ?"O›¿²U)4H¥ïCQN3;þÇÉì6'±‹”Û-[ò)øcÙÔ F@1ÁKl™ÿ‘ ¢[>øYb?h ‚f*ȶ#z×Û§„ÃýB7~Ê£W€­‡+÷øêµÕ  ÃK ¨vzM{ó°Œ@Öõû|cC]RK¶¦ªoØ¡EýUÖW#Jgë;AyN`îY§X‚„þ™Ë ½…#ÄÉ¥OÒB%D–½Íö#·ªq±™ZÑÌ9áÕNµºâgÃkØk5É nÖ‚þ´WAóØ1Nm1mÊîTJ¼Û£êÎã°Ý8-Ri'Ï ÐŒ¶Ó¤ÓÎ ø³wW0e¹ªsyôã3ýoLýC{_ ÄË›±=;2.õå»îEH¿­Â´à’ÁofN À"åçë Ë- Y|÷W|Õù¦c«Ñ6 *BIÓÏÅÁÇSNk\êúÑ#Á€¢I uh]g«úºt§½£®S؉BgÏßþ´»ïê÷u‡]󥯹 Õ8çÍ\HûBrD]ž®ÇJHCU*êú­§„WJ– ÚÈü6m Ñ®¸o¡‚iàõR-ÉÀ©à BÞú])-ÿÐXþíþ¨”8Ýgû$” A(»Eºñ°ÉÓÛ=çÉ‘uw…‘wVÜ1C@U&”¦`êbœBP CÊ['ô™|¨xãU>’4yEI0j`wÊÓl·=ÁØGh“nf#`Ÿ§Wßݼ3áõ6MÌË~eFC×âmßqOçk ø˜¼øŒÊVSQSY$„§¡¨î³zåuŠûÕm8dÔܸä©MÌzü)KÕw»Ò9Ø™’xý/e…`‘ß"Pü0À[ôxÜIÔs`­é¸Q€_ûsïV°‘U Ô¸YZeÑwJ’Q–E“uG†K~ì²íŒÅ[‡B¥3e¥´;$``žñgZ~2a<2iJÆH3(VžúÊŸJ«Ÿ|l]þÉðÂð)…íº‘’bÄ{˜ä§ÆýÐÊÆÓ3Ý…»^¤_Ç’'¹:÷©{ÝÖùR`ôÕlWø¼z®t –ÍFƒ ÇZÉjØVƒKó 1õÃ!i|ëU½Š¢Ùè»—KÄ> s6s;ÄÒ›„þiùcÄ…ï‡,ÌÔFM‹Ã%F"Z%Ì]åS‰}â=×Mck @—j}t±½\_±;±ª·dÇ;dœw¯í⹯á¥/·h"טÊÒ¿²ŸiìQ^{Éeq ”Â_'2ìpžoþ\÷'½¯úR»é’Ž‹xº3¢‰(£5ÞÕ,Ê·ÌÄ9ꊼ`E6US*µøÁRöaÙ=‘œfØnAÆßT¢Ï€SÕaÁ[뎛ÈuçHrÈΜ{Ïr°^ßæ;x 7ý0â­U³B¦É¿mÇæùQS° ëöB&$ß–ûÃTK27èÞBÕñvd1£#IY%üžq²š1f©œƒŸoäfÜ!›õçÕÛ ºÉ7œ’Œ´ìÅzáÃÍ)~y¦áÑd©à‡ã™*Þwš8)[|…N¨© †§PÍq‚gÒ01è…Óßí.Ù¾ˆ_õ¯_Cέ‹xÜ‚O d®úÜ»Ga¶ÝZVî~Ú'ù$åàÍ qõô‡^­9r? MÆ œk(øl8™¨“¸×³`C{2è |~WøÒæý;Â?±¬4ÐÓ¿¬uŸWÄpx—C|œßNûóæéæ‡ßøî§ŽY]¸`q}K‡HÄÎ;¥+T¦ÕFç‹°¨åe‰ÜÚtAàdxxR ;¯Y–A½ùmjØqC€XÕÊýûà‘ZÌ9÷´`ÎVéö·ztcȹ"UÁ·2GØ@r?ù<šÏ?X?ÐN¿y” Êû2¶9ììMrbf„rý î…¶jÑuiµ¤úB¤0æ Î%D‘Ú°ýji\¾†#‹¦æÂ®r¢M†ñ•ÝEâéSƒí ÝZüê,íéðøvMÖ5îc,lx³X½’_¡÷êZÎËW]§™'¯ö®•Ü›9p¡Ñ†QßoR"õk±g|÷FT¢þ ø4¯WH;TWmà-gfé^0„åà›FM­[M}²¢ô” CV’JÑ­*§ºÈý£w²¨‹~Mç› ¥+¶¢±ÅQJ…éÆlüJAQKJ±.HކŠ5î¨ê×ìÙ ¬FD:•Õ`T:®J|òùn‘Võ¦4ÉtFCŠ@à¾(‰ÔiÔivIýiŠBøÓmÞ­æ¢ëǤ낖È k!}+´|Eæ}ŠwUÈÒúPáÙÅ)JH`)UžGQmçêÁZƒ<ñ÷y?ö­Ò"m5o $òÆÙ0á£xCûU÷¾Éã ËÒØúéøsvIÚ qw<ÖÀÔ§Ê/¶XŒbq¤Å‹dcQ4…‚´W®h3%o‰óàÔøU =T¶×¡«M-!$>å›12¸¯ùïŠ6Ñ×´ž[ZoŠ”Bº eoÒˆçRcã‹ÐñGM¨TÑCÙ\Ggsø]æsmFZzF‰vˈW¶÷w^Þ;!ªì´æ‚Õ´á3J¤·ŠøJ¬Ç›pYùAÅЮ|²ÒƒÄÏR[rØ/[Û n™a÷˜b·¾hóæùîq«ÞøS›âj»n6Qžøiœ·`&n©Ùˆ ظ–bß퓨Q}æÙäÚ„I1ûŒòðTm83ßæÒj¸%11—KØ’öÐ:ŒFÇqþA(ɹ¢ ÕÁ&_Ç–Šö†õíÕÅlj èƒ¤Ž«\èD÷Ücár¹¤k?Ã{){ý“}Û=ÏÍuãŽãÖòü±Ñ´ìq\@ƒCõ‹~§ô¾s™ôtü—8Å%H³$2Œ7ν-.æOå(¥øöæíè#ŠBÜàæÝ=i¸ØÂ—ç )†¼Šœ«pÌ}î‰#ÉáóÄCðþj{Ð4ãÔ¹Sça¾¾ßk khkMLÅ‘c4aèwß)—5â²æ(NQ*1á!]Ýä—æo:™¬.»ž†`¡’¹¦¯Zè)Œ†›ƒ3¼óš™ÓçZÌ1s^½ŠÌÝ1îx¿ÇÆ™³GßäG´¦®67ËSÒQ°&±°¬”NÝTŸõ:Ú†«Ìjµq7ÀééKÛÓÑêu•©vóÏdq!Á9$‡·©2("¦‹Ýãûå0Uûl—øÎäÏ /Œ²/k$êÉÝiáF3‡ÌP:M(a¡E04žöîÛ\·¡H¯5Ë"*¹ªÝyÅyV°d²%<·ªS‘ÆI?Âú~ÆD¤&¸N¯^i~@’Q“dL˜Ðö’•õ‘“ˆ0ªKêÛ`|C[JWn)† `à>ë –¤z  `",ÜôÈCîS]ŸJÜ/…õ§N?`þ>eragzÖ$XoxžHkäfcÑ“‚æMªeP@}†r4áÓ ¦ =ÃäënôÁR;DRÒKœÕŸ©âRhýY šG "<÷¸!Vhn§æZ®´œOH´Ã†&› á ‹M>à‘©Ò ¿=伩à÷ÀâB¬S>¼oSUá_[« ‚4¥0GÎÅ$„˜n÷ÈJ±\tÒ`£TŸjßI§x¾Ž3Þ8ë캌7MAv kZ|™¾ O´÷‚Îh2`Ué:ßý?+’`«¸ç§ã×d1knd}DT±gùƒ±rùWˆ[ÌíMe|ïdCñ\g1| *ŠÀɾœÚ¿UØØ:ñÏi†p†#œ)v‚W¡‡Yׯ’kd·Lwüe`ȸñŠìUl'¸žôý³·î˜åé×tZÕaJŠ«æÓ|è)­~Ù;˜ô•{å>ì÷Qwä?ÏX=ø«Éˆuª Ñ 9_íâxMPv:_žŒùК Gòn“lóÝ*TÕ}¥‹Õ>à:Ú‚Þ‹ëN#œŒ´\ x8ø ó (õöÇSäo}ëH}mÐË„-è€úÂW)0«ÇÄp_blÏ£iy×÷ûVÀ—Öà ©¦u†½ÉãÛÎ6xlNÿ%VÙOÿ½çËýÓc{¹Ô É.mpZû÷‚à·Í¼Ñˆ"—L¦G?Œ”Ò‡Äú¸ŸUNù;¸ìUØO€åØïË9wu ˜eR[…~c¤½WÝȺ_+ãv‚Míñ=0pû×ä§`tìsž|Œ©X‰ð‹º¯Ñ¬Š9çGo)«AJ7ø¿¥;:3ü°’6Æ„#äûƒr#“_ ¶©‹æ7ç8|Á:ûi}±ð—¸+¨&Vtz†Ô#Ô×Ìr`Õ7=8ž«Pí¼¨¦þ5sðSâç’à¡I#Öç±§ï ¤Ê¬ë’&nÊÌ-´« >O1¦8ýî¤,£v‰E¼1Åí^«m+fïìÔ¢ŠL?Í÷§@%”ÃqÒ‚’GK†;ië—~äB@ó•»±C¯îV–(튥a 3𨉠£ž™Z&10{mÇöú'¦`ÛõÞ Z©)âïþFÁ½.]GŒGcØÍ6õWÓá<©´f¬º³AVþ¹­$̨÷÷[Ò£§Xñ‚XÞ4`ù0Öçr)dаRã³îMjËÞG:ÒS.A7S=Éä›S[בj 5JsX MäÚp¿^1ú^Ì+:н½œm„0!ÂÞ`Ü¢¢ÉûƒÚöŸiýCnᆡ«‘IùŒ­5»B“…¦~¦”Â;’Œ9Êæú?Dx½Û>ÿH ¸H¹¢z‰ƒ9ô½}s »QÑG‡(„ÎïÊL-7W>fâd4ˆ¾Ð?6÷Iã–~pßlåYq‘Ô¿y*YyPZÆô§HxE¡á""k°voD /´äl†€äP†ê j8{Ü’ï¢. Š=ý´BÂ0Š|tm/ÎT‹EYØ¿»ÁÝ=|ûêÞ¹Ó2$äó!Â42ŸŸûõ§Äý“kÝ(Eoà+ ŠcA2µ+¤¿Åž¾òO §jÅx¨Ö!škÔå®”žÚ¾’ëí´%N7…_.W/}øÌ`~åÆOÈ …ñZ¬ë’Ž'ÄËGÓ³ôÄÛyµÝúªdUHËŠi'ìp(IœŸÉ•èÒ. (ÅÚÚ­>Â4bˆ3n«bçÕi©½oÈ«@Ò§ó:ö¯–¦ëÏë1ð4¡A€ÿËîÿü?a`b4rÙÛ9YÃÁýy®º endstream endobj 85 0 obj << /Type/FontDescriptor /CapHeight 850 /Ascent 850 /Descent -200 /FontBBox[-6 -233 542 698] /FontName/XXOQUS+CMTT9 /ItalicAngle 0 /StemV 74 /FontFile 84 0 R /Flags 4 >> endobj 84 0 obj << /Filter[/FlateDecode] /Length1 712 /Length2 14094 /Length3 533 /Length 14647 >> stream xÚí·S”fÏÖî™ÎJÛzÓ¶mÛv¾i[•6*mÛ••¶mÛÎJÛ8ÿýíþNÞ§oÎ8w=:ÖMÌ9ŸõÄoÍcÄrb%Uza3 „ƒ½+=33@T^MÀÌÀKN.ê 4vµr°3vò˜¹¹™Ân&3 ,,9@ÔÁÑËÙÊÂÒ@%Jý/'@Øèlejl7vµÚýcbjl Pu0µºz1¶¶•½âPºÝf °°ÌÌ3+SW€ ÐÂÊ–ñ_LÒöæÎ§ÍÜÿ»ätvù‡ @õ'5àJ3{[/€Ð–QÁáŸÕ€ÿ°üocý¿Pý§¹„›­­‚±Ý¿ìÿÕ§ÿ¥llgeëõ ìÝ\Îy3 ³ýJ5ÿf“šY¹ÙýgUÚÕØÖÊTØÞÂ`úwÊÊEÂÊh¦dåjj puvþWhoöŸ ÿ´í¿µ´•ÕUiÿýGÿ]T2¶²wUórüŸ®ÿRÿWÌüÇÿtÇÙÊ ËÄÀÄÄüðŸç¿gúÿ±˜¸½©ƒ™•½@ÕÕØÞÌØÙì&þW(Oz= ++€ÀÁÍõóÿ)S··rrJ‹Ø™˜˜¸XÿÍdêæì ´wý¯=ðÏçþwlnõOo€@O )lV6†¨!í£ÑCï‰fûÔ²lWÉe:ûS>æÌè œ-$Êux¨ÒÃ*ÂÛ¹RLÚ ‘`DŸz¯(Õ$5ûÀ¾³ Á1»75!z˜ -:Ф@¾+$-Sqß5x‹¼E0ôÞØHåwœKšªgÛvçÂSe3E‘qw€å0âíaYÇÃu!~?t¹FŸ6éÊŸp;Ã3W>õ»Žg†(ã Ýe~'ˆüÐÖ-à5h÷âßqðaP¹!ÃBCô°) úR3µËçË爫1¨¨1BÆ’Be¾b6^ô`É" 2úêíiˆ¯?§–Z¹ŸˆóUæ~èš/TƒQŽ„¹]žkeqÍ©x1ÁLèü8·À)–ŸÅ3–<µÙ¨˜æ§.ªÛ¡]y™`uoÜ£ûV-KZcg³=§ù`£šJBvºÀA!§ÃÙfÃÐÈȬuŪT ]/28ASýìYèß^¯ªkÍÊ8œP ÂÈîiÔ¡rˆµ¹¯ÚÞœØ<¯µJ®óÇÛý‰|ß.y÷þd‹dGE×ÔÉ×ÑÕÒÙq™ÍBÊQxwøª–¯/åµ°æ¾µÚb: v êWŒ›‘>Xx¨ç%tr(‘„?ÿÈ\fÙæþÎz&9Þ¥u¤ÞòjýÀcðqÇ©¼É#„JŽø3¸X¡G> «BºŒ]ÊöàôÌÙAL( ±\æ;3g¥€¦­Ó¿0´rý±èÁßÕ*"èŠ~G¡ªê4ð¸æDá”Ú¤þ1úZ;=reÌ|lr°eÍgRÕH!’%¦‚»pw XÂÆdl™7Ñ þ9%æsw·Å§OˆF´¬4~yùV ÎLV.0üëè[ÛÃGô¾™¯–À¤A® #߯C¿v ®„1‚v9Ÿ "}·w¿ËµÔ&вòk÷Zk¿YÆÜw¨£Uè¨y ¡+o‘nÊ®{W÷gbµivXÁåª#VuU˜3]zÂÁ‹\Þþ°çÌ÷ÂïÜ«‘¾Á³cöÃŒ‹öS;G¢#ÏÚÏì2 °·T™8Éœ4+âºV¬t—Md!‘–ƒq¯¶zèÚœÀuCÓ¿ÄLÓ¡9U%éÐU†ÝS“¾¶#úËÚ¥[Ü·“µxœ Ž• Åí%/õFÍËB‘çð&o ÃRðô5m‚•†fuéáÁ¨–º§î€K¡Þa‡Í|ÜÆå(h^97WLìÁ¿ pzß„™;Ù€ÃÍÌ5Õ[[à0û½Ïr’ÛÍ/fŒ’Ø‘,0²ÿ×µ&c{óäýpÉÑë¦Däò~5Rˆ_5iáyd0ÉEd qΤƒÐŒž}Âܧê<íX½jð¨ºÂ–­ª¥BU7&*4 gt0ÛHk¿3uP@°¢dþæ€ü×Yôƒžâûp¢_Á@¨«óVüð oéóQO(sÎ|ýM1Œòìb+Š» M+h(¦•a›@¬Ž}Ÿf~-nƒý¦šŽéW-hºãÛ!H5/+.—a­üÂX§h̻龌óv¨Ÿ+ùCé<7ÃP~ëÃA/¾ìm$9öÙw¯ryØ@™X×¾§¹ô¨m¢þ˜¿MfbGÐ,îïÊ9ì‘Ïf3Û|L´¦r]‰IýªÅú™…MÚ]Ãï<¡ÈßøAvzTlñø+ßjAÚon2ìuœLf¾–‚ëeZ¨^8~7¡Ç\°ÁªËq¡×MÍ–ó$âüRÁ/>º7^ºÝùu¡eÈ$?0 É\8éÓ” 2ÒCûýx¡ÌØGú‹½M”÷ê ÿkòEŽ•6e»Ù4ƒM6xÊn~,î$˜Ž¾–AU†HJ VÕ(þu%RÙv>S28ù¬Çá­ ¢êL`YÝ je âÕŽ¡O%¤ž CRŸvFr«:÷àÕwMDÏ\"í騹š5ÒEŽ7f¬ø&`klœ°§ª«£ô4ÇTQ7ÚæŒ~"²ÖÞ'ƒÇ]60ù)ej5''tÞ˜Zúû-©Ùë£%çÚžc§¦Í‚ÄÔéç}ÖÁU°§Ø¹'…ö)†”xháeåW¼ám.ØÏ€,7tÛÔó“:ŽWT•·jµᛚ0 €žöûOǧ”9Ìl¤at‡yn”¿ ˆo7@zs©]Ÿ”†ø>$cÑ#¡¥¨²Ã[§|J§‹/Own½J¦zæ+„sN| SVÇ(rze½?%˜å??Õ]qP‹/ö">›i½¹àlV 0YÓüDcÁÁ•.®@A]Ÿ³åò³ÜxÎ#ñµi™Ír³]’ÙâS§sŠVcí{ˆÔª¹L³ìVŽzK'6 ø5Ô¦}t|(PtÉü@¢ Õÿ+jJ‹÷°ÞIÜý@ubl©$Z]¥x`Hç_| aJpLÑ阿ËR%·Íž¬I9ðœ2¾œŒÎèoÉ!Ã;äJÓØîPUï8×Ç;ŽžŠ#-d4Îqá9ö’¾Ó4 Ù#Œ× W¢çd^þ=˜9ô_cÄ;Ð8/2@ÁÛÄlà sëªwªÕRå‰ß(ÈÌðZŒuòx| L®¿m¸[%Y¤Œží«¶Û§»ãfÁ©`£ÖÌâÀj¦àA鎾óÞýeMlív0ÈYEv‘}4alÕ3fµûw"?¿lw%[nõvôÍ]©¿/è”䬔Pñ‚ôï/î Ϥ‘ÏÈÚEÚ{­[_þdGŠü.­¸¿Xaއ(LÐÁwûrEù[Êè@Qµ=q0m”¤æpÚJŒYƒ6lá‡×\ôaµê)ªÌjƽڤChViù¢‡¥ž r\xÞvÔÝÜ®yËuB”z@¾!p2ÊåæïÏ{•;ož/Aµù¸`Œ¢¤ʃ'JCôCÅK^G.ZîoÊà©®~| ËU¤A6ŠMúÒBÎæÌ F†¯Ÿ]“mAÈØ2Šø±üãÙd~…4÷Êz½ön¿¶¤ •âí¿sòpa;½6äFtJòCè»r’µÞIºÑHš¬¾Ñ% Ú»V{¶õÅ<Ír)&œž­¡öõGíjÊÇHùU_žñ‘5²…StéVvÏ:c; *kKÄ»]S§n]ê¢W¨2|k:ÃAR6bûù×Tç“9BõLüO3Ÿ¿©öX)Ûs)ç¡g¯ Îëtªç/†ÙMlƺ2㱕óR¶uíðM!ñT ˜3ÀÌð@ޏËÿÆU\—ÚBnˆ{X&'‚u¶=J~0]dMªÚæ.}Šp#òéR™ë…½7²êF¾–¡åfÌíkÀûéöë kë°0*Ÿ¨i-ÁÔºášã§k²D7Mµó*$[°Èˆ\}ÛLx·)ÈYH%5¨´âqÔX¦Ð'6¹9yP¸w<íÜÝó|wÓç´'bãP(ã%qfon”Y¨›³±1 d·›G´,øâ’]ìPLQ$>¿| ¤!CbdêœU‚gØäÎØÂŒ±E¿Z9î|þ*;d=ø¤Þ Ê)ª¯!߂ўh®Û>†GWFzÇÆwå»:lôcÚì¥Òö ´Fý3EÍa6ãVœ¾ 1­ ¾ãU58ÂF{¥ÑoßÊÝ‹|yª*ÆEµ¯Wv¦V„W Dz½ž/…0á†ÙÄnäÃòáÌEöFŽ®)LK÷ôáß(€¥7Q EjG•Å{á8`r¼ú¸ƒ9Äj÷gMèBï‚—à´%`xáÉN÷ªh;VüLG·B¶=eá™hï¦,?3¡øù[,ôâªjЪ` %7ÄmZ‚ÃÂŒõ¬«y¶ÇÞÏò,‰ƒÒñ}p¢ðT —ªõ˜üçè‚ω þÞ’€C­û –ýQˆlp¥…ââ/¾«}SçS/ÅáJ{΢‰Þ£qÙ¥iE˜×9ʳ½„{Oy,`s¯ ,$-K `Ý3ŠÕu³ó 5˜ërº–•W©p*º“@Jp¹€4=ÉÏ›*ž+üœ C`­}!°áܧPixE˜Ø¿ >ÜÉ ½4ÇÙ—ó©€HÏéÉ:e,å1+í4¼pø‚GÖV4(tö<$U[«Ñœ3ÔîvNȧ~ßy‡Þ#w`o™E³$ùÊ›Lú¯uWÇA¶Áp†’'ÍãÆµº¦‚!È»aAnØÛÀ‰£éCö×D£ê"ü²qŒ —B5ˆÎw1Þšü÷±H+`ö EÚéÇ!Niè¹põìáMÊÕ!ñ›ŽÙ©š9@ºci+N”ïÑ"®â4^{‹6.†q=Èm÷CTß0þOuúâÜÄàb1b6òO|6K¨äµkÐÒÀ ­ÃX³åuæ=]›¸Ö¯eÕbs2ù¸ãö33ÜÂym¤$ûyy÷¬N>ðÉ—?×@¬ŸDz¤±ýë-¨y™/¶§ß{š¥ðùú· ôÈ~LHÈÓûþðVÚˆPjõ' ‰ÑÏÀ¡aÅõ¹D)Úð4i¥aIù¦¢ò²ÐÜqű GâB9š×‚#¢k>²KHЕ|±Ï³q©Œ?ˆhÍJOá»=Ÿ|xïBÿv¶@!¯iú ‡-2•“b;LjllåŸÐûoW}ð+æ>7ü~í•  –žj èîk¦˜b#Á­OàÕqx¥™IŒ¯ª(a0˜vÜ "åÞ d÷ª §Ê_hçš­Eæwäõ_çdA˜J¬×0—^Ù¦“/}1ìÁÍŠÛt½Ïl¼ø7¾ÊSq¿<úzæ{a7I|+„¾M³¹lÚ x©_·CN,­°Ü6ŠÅ"è)çOáî<$õlesÍ ¯HÒ%†f·µ”öŠÓq`-^ëfx;’üŸ5Zˆþ^Ê*Ƨ+¡D¾ôè¶ ÝPøÇ\{É[J?gÔœu×3Ó$Ëã‡BÐÎð%Ì/ýüžHGæ5¿\VÑ–ÇŒm ¾Gca ì eEUÎs‚l'5Âo—ÆFØtY‘¦þ!n-F$W_¨”Óí&àHX\‘öýøuexC‹9d‡lµZ†Ø?qS¢­$øË-iŠ8ÕÚ hŽ-n2ðYVr–¡¶­ì¬é‹l¿Æ‡kzžÝáä`€mÊ÷$ŒU…×ç╬<3cý2»6l¹¢ßÞôÞÈð:®HªŽœ•D¡@N»å“{üû=ÖQ]ýIàöcÏw—~aÛ㜶lÐä&ˆ?ü¥ =¸ãúaÌém9!¹e}ôïú¶z'¡~^>ŒÖõ¥\´‚£×á´6ЧÆPXf ÈB¡h4šÙøn|ûy}ó8ut›Ù› ¨ÿ MJ»2©hQÂr‘á°vpÇŠ›Î1öFQ-bW/(‰š¾Ð"ì$étWìwÄw%HÐï°Â¡"ÄMþRù°À]"W9¨“.Ð4”iÜŠy£—é¿I’NÌ¿-èŠdj¢‡¿‘ë×”ì¡wÛøNk1:"úwŸU UÜL¼ª8ºÂñ ­þ’U>ˆ¥^¬“iR•‡f»x•ê–ÔÕ5>¯rZ2¶Õ*Ï>îÙÆÄ®ÿåäùúÍÍøÖ,í‘®µù!o›à=Å«_tÐÙˆo(•A¾¨šî˜Uöƒœ’nEà(:³ã@|o·"¿éiÕB06Áy1ë¸âʦ8ç*û/Q×ÌÉо Í´ë¾0|¬w~tLx’¬yaHÖŒHŽ‚–z5ôh7xÖÞ Äõ€ëÐÜâÖ´IÔÁå`†` džêä2‘¹„dI¢îÒCŇ¹ üôvKßâõ»Ò‹§)= ªæÕ+ $Çë(“álÞC‡T'ٹǀ<%) @u2•5JŠº¸h×¹WT'ÜÇÈõv’@f{¦6FOš5ÇKÝ|CØÍr·•âqv$¶³Èð™!—„ð,—YST®Ä’£8Csg´z†›‚åir6&@4^»•1ZÓh¢NMLØ¦Ý Sl–{Xâdòó—þÈØ$º¨Ú­n+›kdÕÌPzùr×åL–ŽQmFQŽx.¹B®øhz™M$®î«?Ï6ÚU¿ÀOt!Èt}cýµðÕPÓp°#‹q2»i(ˆÂŽú@D=1xš×“c}û{ÙmLÂ:ȸw¶˜Ûë7k¹Ô;À49§¿êêQeJº™Bú;ï:cÔˆiÝO„›í¥ì•‘ã¡¡mÄl¨Øx"'Äß) í„+lÙ™ŠÖêýØžfÞ§ Æ:á Æñš{bNMKêt­aÑæõ“a+½BÈ2銼 >Tå†ù»òÁǘánìÅHèoÆ+€DÔ%J"씇!#Í ¡áØÂ’¥»ïƒšÕjYÁéò—Ñ}Õ4<×ÇWߤ´fJþD\K9²Œˆµ¤y‡­@3ÓÖM0´À/Âhî/,ÏÌ©¤³û.f/Q¶ö¾¥Þö‘©Ô&¹õÞw¢Á2T+žµ}ßV‘"]0ñÁ„÷‘"ÖJÏÎéá¥hæ¤Î#¹ß`µ‰}ög£]— ϘQæ¦Éw tgíbÊÇ·äe–N­~œÜ*Áë¬×,|Éw¡ÚlJ(³Bþ0”Ë5Á×WQ“$ØŽ6„Ïü{4L ôMUn¡(w/Pârˆ`þþQ¸€>"Ó¥UœÝDÃràx~i ™£¡”\Ç1 ݇Whx¢œ÷ÏÇÙR¸°óðjÇ’¦LäLÞç •_Zz-,B‚ƒúeÅ.RÈ"DJýzÎßH!謚‘®¹ò€yej2ʘžC kîi7UìÞȘ“P—Ù™¥EtïÃc–αûŒ{amô->Í^=+ßþk¨T!21.rO7è#bS—ÓYé!~¡©1“5ä'曃0·µ$üanpÅÉ:ÉN ‰×*ßLÄáÒ—¡_½Ã‡Hè™dó=Õ(ßqòTzNìõ5a~™àÜu“Ž‚hã£ÌjÃeD mÍwMv;©,·îñÚ“Õ?ˆV1¦1¡ÚJJ*_핽qè Ã$p+¢}ÛY[¢É¢Lx¨a0§³1䜰˹6 6³­t°©:«®‡LhP¨`"Ñ”BÎOǘ۠•J,ÿö MdOËV—lU¾õÑÙK1Ì’ZJõ¤ŠáG5VÊÑwsÚÒ÷6þ7Bd%Vüô©Òâ`vޏœ.„çxò°ãr,tíÐYÖaÂï‚¿Z évØæ+}±œd„Æ\a¶.ÀéÝLa?’mêdä·x®"½Ðð6vK,Õ œS¶EÚDì wylâ˜÷ü‚ã¼áÚdÝ]#^œ!Ùpnáë~[ Ù~ɱæ¦wÔ©×§I”™ïí—»YοØòõÿpKÅwWjCœâä‹€ýîµFÔ¡>¢ÞŒãÙG[Ï/ ¯àò*ëÿo^c¬LÆ×qÖ¢…Ë´Š0¸0˜+þ W|» ?ósh1Ì3hª¬*Œ¹EÛ*PMïnNñxÚDü6_Böí´”oQÎe¢ùŸXdVG´fâRâ¨cÍßa¢óFîc³Qñq?)uPÄ™¯šË|™Ê¯5&‰fZŽö·Ä¸ˆ`ÊþÚ½šuŸÏe6¥;º<ÊúN_¸eX–ppê Άûå?·ÓÔi9ÝzÁÆ–×g)ĹÕ½«ÅHA}f©1"ÚÏfegmgG0eàrdTS½~xôžm¨WˆiaÿuÏùEÇÊÕiD§`ayJ˜O·tù„ñÆÆIìÐ.óÒÈi«Ù}!zyé–‡¥t(áE÷½F@ø1 1ÆDÓ'‚TcÁÇÇ['O+‘>vârл~W9Oø÷&Lm†ËvW8F©™‰àÖ/ UÎ5}*ŠyäIY1Y³“²Ù´›ÀòkjIÇÀ™÷HS¤ÂÇÐ>yGùÀq|x”RXKQÚs0t,#8ýÚú»ÇZMAÀå¸òwAùžEž¬ÀXßQ)þ¡uZ¦ý®tâ±Ô“ƒ¤^;Ó§Úf)þá0YZ–á¹Å0ø©X›Mäã^ú,~>ˆDòõ¸ÿ6+K·ûòƒ”,›Rw»£ïHØOIB†èƒ\<œ¦2 ÏzÇNgÖ Ý•²¨Ñ+¦y²Èä¾Ùõ:Ê_‘Ù¿@7Õ,+C,´÷„ÂðéŽk%ù{JUœ$F}^W»s—~Q¹]Å€ÍLÙs›”=Æ÷ úý[©¼8‘M†è䇺/j)ˆå¸øIwùr8‘¿…Ž¡ Ñ´{Xá÷WIçͺcÞQa^²…»Ø‰øØçú€ëßð‡Ñ•Öšù¼}pjzê4¤^ì‡ ¡PwIð.Ø¡·EŽA/D%R†Vy*pÕxÖÜáÛéjxV®Ô—è(z(ªÙäfø?‰ã¹ßÂZ‘êÕzüçÑw%/%ÉâÆø/äj'Þr]uÖ¡žçã Ìð›Î²¿ÙÛ®x Î'!üL8ùæ.w„lFáà|î…‹ÝŒ{™¨ÈÇ©Ön9Ë:g'7«xöeØ•Èü^xÐo™© ˆJŠ¿è€´Êaújv"CÞ=×ø Êrkdw=ÌHÐ4Çà#¼Õ+g†ÐM.àÝs·ØÚî‰ì›yºædŠ»›û·Â<öÑÁLî’ö"‚ý®K‹ ¦Ãt|¬?êË}a„[\ŠSµ¾§År@¹’ÙÏŽñ¹2¨4«´$Ÿ¾÷•-  0 ¸i©+?–‡Þ"˜nSJÀ¤0ÖPjYÞ 5#¤jÓ3äìJ„2Y3þöøÆð„h»f2„™±a>«ûK.ƒfé]±Ô4 SI˜H’Z¶ ëPáË>攜vYyTe¦˜âºãÚM|ß*×Z4’âÉó¡ÜKã`,¨É!RÛAˆnuF6¥DºãÜË—Lôd&¼ÄG?ƈdá Œ‘$úè.}Z §"§6óÃðžÑªrá1‰<:…k¤GèwÙoË âYòÇ;ß@A ,ÅjÚË#{ÑÍ8±íŸ˜3‡Ä•™@›ÓErùÙïÆl@ ½Æ¥Î—ÓBCÄ)KY32[Ä 1YvMô@b‹7˜x÷ÓJv¤Í +¢»ÏÅüîÄó@;\(=}C‘~±sBÑ•mðŸêÞ·._m9)0>kPDj)P)u7àÊf½ Êè…B·QgbuèØÔ Sk@ý‹ª%›;"ÛñÕÏP]MÌ©Ÿ-ßöIyGl[Nù«ÄKt2î[aü„¼ý+À@áñpúX¸¥‘ÛŽ¨Ûv²ùw-Daø­¬‚ŸrÐ=ž†ï âzmÐ@<'Îh£°ñG.ž·’Ÿ£k©)´þà6 ]Ÿ÷”û™{H %v¾ì9_²W×áôSØ/>UïBÙÈ–Lr—«!ß—j„”äinìêN¿ê¬Ø!ëHÏиyUp–LF˜×j|)|âZ²j/ÉÏœm|­Ñ‹:X_é¦ènA£`¶JÓþ¥M26"œ1Ïa‡è<Q·Qˆwù#ñ‹¨¤OM‡¼åeCBeT ¦jáƒŸŠš5€Þp¬˜Ž(Œâz›µjqü7ló§ò"ýw2PA¼ôKÅX©òº"*V8åÒKÊTW¦;±õ³äbn‚K=ú+¸4¶èôKkï>=°æbÞ‡­ :Xä‹jr.#mÙ:ƘŒÞøïzmSvÇý5¤r„Ìzåíís×h² }w¢Z*~³rñåg!ô3œjȇMÇýTãsê¸7@©v·ü8°Pþ[9ãBì‚ ÇK¥¬™\tFq§ØûZÅS…ÏÍ}Õ²^žØ)Dx´ðƹœØx’­<Ïž‹÷w´㳈nn¡/0í?o¾ ›+ÞwÅf›_u_¤£á2¸øä4é›§/¤ó4Œ¹…\XÏöŒ‹®OÖ!x}X~à†Ç6³5÷ÆÙ)à<ÿs1ÃÕ:Œ¥uób—fš™ ë(ë…!ª—‘·j8DÇê¢Ç\w­ø¾Ó• ÉßA‰OYÿ •ÙŠ[þ'шý·ŠINò_ò=KŸ;&I- ÛÕ¬a¤wуvÅDŒ½QLtã€\I—óåqÚÜó6¢°S½Q_ñ‚S™Æ²Ø¸)}ôÂv2¯LKDø,ù?J5×¹ž,ÊÝéØKŒ·ÍÑ´öF¶<ö+ÒÈð 2½×Ú)ÑÔñ¶—h÷¯±º=HzªVê>&I϶\ÔwêlÔnóª [öêG­†kˆð+SÙA¨Ý쓤Š=·Ê7ÝF/o6îKÇ85’Õ~vÇŒ<ù]¼|¦]Ú²)¥#î’Êž¥‰þLŽ;検޵ߦ"¿A)™}Æ[Èÿ>wÌjâ¾Â¼15Z,*•¾¢MB¡Êà<1}.ÀÐÀM#™¬áD%Ék °š‰à«A¹¬FK=»!ò'_pÜæMªš¦P拏l+ícµ.Ä@ëh%Ÿ×_¡’|m¿D@®ˆ³Ó°eŠŒzî üºKM€_þ4þRTVR€N™²gnÔwm´/1uú›-púm‰èEýú?ÌÕ òŠ#£>ÑσæÌ`BüÆÍ®ˆ rG—wÕ1!]0íqaØEiwlq ÑZ|¯ $|5 œˆ”"Ñú„qaÊEœ7†T¾Aü,´ôÍ Ÿ¤ë„Ý’:½“Å´Ìxw È?Ùœ#ð¯3ñµŒ`x  kíÑ£¶×½íe DXx†; `6â•éGTø¥ËzÐ ‹mZUç5y«S‘÷âÙî•¶oëÂ.ËÂo^TÉ#ïÀjæ«§µõÃÊm¿ô`Ç„+ûÎ¾Ž¦éÔÉ×n%l衊ãœ;»@‚ ,ª%RqmË… [ÛòRAáεdXÂ,üŸ¾ŠÀs*šÄšI?ˆóàhA“&} çqÒÚü¦?ÌáΕß{ t(`Ò½ÚTðÜ5i(ÙWzzBç½ ÷‹¿;ðK/ßïÓ™¹Z“iE¯=[Îth„^÷yyS¼Óø "ò©!=ˆŸ#ªVÅI~}Ýeß-ü$§õùÕÓÆ\/«:"q¶Ž0úưÖN°½h0›³ž[¬yÆËbuf¾"õ§ŠG~=0Ë šÿhU((«Þ‡yžÖ²â!}UÖˆ2vjó9œ í‹þè–Hâ‘Ë"J³u®™ÇÃ_#¶É9üC;CGÃÿšlýÓ¢KZTÊvÀ¡üËd²šÊ·kÇQå ¥E´,94G+ëÑÐŒ7˜“²³ÊÁ’vL…5ˆ¡ˆ.ðEêký ç«@dgдÜ\}”ûç]&©ç»Àþ-¬’¯s×kßiýÓI&Óì¶>Ø®<û ë15:SC8ÿ*Z4¹¢~½šx7 M<Ïìj­ºÆðçNcÏ… %ÜߪÏ´FÞª[A~~aÂ[„c!xI\zƒä€Šë0þØ}¢¬Õž*÷2œÑLµÙt“ ¦:0Dîé0«yŸ…ø½Ž˜^­NÞs˜†ºÒÅ ²åJ+„ïþÅZÞéé^ †«, H C4¡ÏU¶¯ñÕµñ²¡>骬Uio-££«‹ Ö¹˜É:ýOÅ‹kzî}Í9%–ŠÀþ¿u²‹ãÆ¢„±éáôåÖ2Ÿ8§vÊËÛPv‰– Ç´MøÊ_­wï¯yI¨ä_®[ùE^éöéH{Êæôr_º¢÷”Yðű`øQõ×MŸ]òCá" idUa$°l§­ºÝ±ª†—™ˆùù¿¼½Ô~؉wKÐàòLÒ‚°OÝ+™óÑJ« ̳õPf’›à¯ä2&5¾õW›óÜ­ú;‹ÀÌÓˆ[ò¢1gXHlÿs>¤ëÿ ºþBÌÊHk#Ò?LšÈb¥÷Åæ‡íkÁ‚¸x yªb]ãùöR¨äZõGWñÄ}ës¸=Q~¤GMŒQÕnzÒu'Ü0©v*­4þYóíž( Y©o®ø-/³n¾²¯=!ÑËÖiúqï˜H`"€‚*£ZËTñ·´BcOä‘}*2È NÆÍã._÷Ž EwÛÜpp,±ÔÓ¯ TîÖ•š€=ÌaÑMc¹ÚRŒ¹R7|~ijùÒCR·'6â‹)ˆxm!aøß˯oyêò¤Ñ“§òî“ôH§)pEÌ&ðáG½ŠðÕÃê‘eÅ&(--BZÄ?ÅQF¦¢:ñàú˜æƒiǺ¼ÔIásNE³Fâ0­ô÷2#²Ã_Ðæ–vŸxn÷aÓV_ÚgášX^iSãZê¹!î3IÚ cZ:4†/~PìêG•[nq¸Žd=u.nϳRe(²¼À’ï#Ãð2&¦yÑëC´fÈðv€¹ §¡Î{ó_¨è‚~öÁfÉÿ•ë„Ô6˜T0/²óŒÜä ZC]„³öóùdyœàxR%·Vç€yJ+ÚYªŸô·ÚqΖÚÙ „DSY&—H«Š ÊŠbî¸á·‹ixÃO‚2&Bã÷(»¦ßapU~¯ª n³T¥@œŒ¶p%Ë·ûÃðbjô»)ÅÔÔ[X©$´.“7—djåƒ0qc$í•e6wð¥é=´…Ùi‡ÐÖñH‡+ð÷àĘ̀B׋mRü¨˜©vq‘æ™3ð»ŠÝ`+å¾*E-ɲ9Ìms¬ÿË5ž‹,_8<êÒTö,a³ñOºO§8í¸[⼕ښa&gú³ÐrÉrjÄ{}ì/_ƒœïT OZ/ýŒúÕ‘´Ú‹dQŠ—TÐu‹7T¶q³ÝÀ¼Jhqg1ñÒY·ÔpˆCÀ¼ê‡P&áÝ • /—Ã<ÐeHdì§_ÜŸ™Ä(g4ïýO\Áí(kê^©’S£VI°Ëð¶êÆ®ˆÃ¯Sk֋ϼž:xtÑ_£ÏQúse,,Žø‡o®ÕtMw©)ûgc¿Ó•qˆv© î1-‡5€¢üžqS¶YÙ½ 6 æu'G"­jŸ@IŠµÛ®v ÓÞõÈÖè›–óW<3Úú觘ñ6þòò_‹N .Ç%è«k=T:nb"úÔØ¬} qЖ“|6ë™Ãe~fŒHÉܹà€nD»?>õðºÖIÊrh@_j÷`š›kb$÷44Ðx·é'mµ1Í. î/ÍäÙ:ZíKvIl(I sÄÀeLŒikbå<ij™¬cÊb mmµgP‘†¯Ð²žSÁ.ˆSbÎì'ÎNr“Ó2FØü,qdJ`QäöDμ`.èíU-a8VÉ÷ZìXÛo²9ÒxžLÄWvQí¬6O«¸y±·ÔEùGÿe0S´Hc¹Ô#¨|t»Y$Ú¦m‘™½¯£‰Ð?»`?ö’ð÷„1ïÓ@|øK›ÒŒ;Fê_õ4J‹ëˆØº¼2T5“zI@ðSîôÉOlÉ™–@=ŽsÑ!fô\_p‹iúÓïLÌsØD™þgå·ÓÜeòó=Ú´fèïGp5Ús  ™t©±‘´ãŠ\¬‘]Áð“¡|T_cSÕ_ß*^ïèŸWÁñ¿9vEXPÔ‚Y ?3¾E)L/Ⱥ>Ô±öhÜ„ÅÄBµÌ,Cl(ÑŸîEU5ÕZË›-z­ÂŽš‚½vö TáµHýé~—Wõ¦½ãî3·¶fgšý²­OÂqÑÇô„w#ò‰óȳɆÏ6׫H©U¤ ßÛNò7å¡Ð¥ÚÉè’S]^Ú¯WYa ŠhpèΧli”­®îrg&?–½º0±­¤‹|áPò0ç=*ÔÂ4¨qàíC{ãTl64\Ý€+¼$jrª©€š.‡"ÜëJXÂlS=äªSXꀈ¹ï“-D=÷ÀT²æv%mW,ÐëÖÿš‰³/ùN°ïH ¸9bùðÛ æÃ<7ËüxG9nœo+?‹‹>X³|].ÚYÆénPZñ±T¤Ÿ…9ÓM¡³n†pL ÿżø¨7ê® RÝâ°T˜‚¡ÓÚUÁùf¾WŸþ0F§{&F¡–·Ú玃¥½4,Š$Hð¡OlÿʵjÜ|ªñSFkÓÀ†›ò0Üp¿&˜DìŸÊ"UbKª³–&ØÌ!¾å.óÎÀßʃ|Ǫñ8bs!Uæn»d<”¸…ôæ»m:ÖNHÖèå;Ø*šÕ8ó«á¬Mv3nùf› 8ÏκMài–SÔ¢èbƒõjëô&i _¿«~u÷tïï$¼Ó%€wLJcŽ—g:¢ê:© º]ù§ öF"[-gï2cIøofƒ@âcYŒçFÆ&ÝPr†/mhxò­}"nŒÎìôÖ»ÀW{1¾,:ÏŠ9³$Åuáˆ]mE/Ü ž“:4íLûã™>w"³«4‰6ãò¼nÍŸ¶úÁy¢àéškJ®äSüfç¬xãÃGϧ&óölŒèeðýLzŽ DpN3ÀÐR_òñ6)/¬G"r*òþ‚ ý5QQg&-µ”œÞWGGòÄZ³r†h1ÌaDy>YF‚¨D…v/EêøC.NZl0ÐÖÆí!ïO{RÄÓä§ï¦!d‹Ø5¸´¾ýu@æYí10=Térwz:Vä þÜI¿UN‹»0V½59|_Í<(1ɺ‘Ø!%9Åñ‹¼*à4"Ù­aÚ'/¦Ð²þ¼ˆWþþž!*¸å¼(Ùq '”0ùc®0´ìP‰ô—ubk]âØ™Ë@Å×™ u7jï+ÿñÞGŠnˇtЋx0ÙõËEå¶Xd°ãcÞdSå‹Y# ñá4\ŽM”Ž AkJCÑ…]¤m\ñcÒ…ió¥º36‡ªk“ØÚ§ÞŠÛ¯ì<XîÆ,@Mì¯l¥”4ëq ‡wù þ£Å;Ý(2O//Ã"e©rôQŸÍîÓU7r°aÿ0no|Ö;艬®.™è×Aôùâô<=¼¼ííj±üA²λhÅ™æÉbFã6cƒÓ@þ¾ÿ¥É|cŒÍpžÕrw|F)U~Äòr¥È2Ÿ| óóî<—+ââóXò=Ç14›:&kè@¡-Wëæ[ò=ÕÌÃNóÒI™t Ç«ѵ&·y"µ@€},¢ÂUzl÷K1É4¥ ¶G¡eËå@-ÝŸP²q±œƒÅ3iëÏîðÜZ7G˰ä÷’dqšÐßâ›R„4û¡95RœÅª.ëSE„U ÓÌ¥:ìûàÏ©W—Vï§¶ÔZÇSÆ•åfÅö»Ãx(ø‚IÆð(Ò˜tðkƒíÉ{Gç'^}W5X"Z¬mš%8pŽ´½¤õw«Üúèî4ÛôX9Ž…näËÆüZ{…¯;¡¡äßdØ SYƒ5_sÇKòqIÆb Ωí¦Kó÷¶Sî߯·èäº>×ZœhVÜU©"í[ç}\ØðJ½F9¬öå£1ÑXÏWÄ6^}ñj®¿ÊÐê©x®š(u¯Q¹Óñáï¤ÕÃÃE‚ f„¢.eŽ <âcC“-°ÏÞáÖrƒÏ3'­ß®Zí8ºxÚåµ›t\"Ñ\Ídy`å™ßVÚ6v§dб1ºøA‡¡ôaé—‡ìgÙ çk Yjƒ®Áæ>´w÷w²×+ç{ ø%µ·Ðiõ% Þ&”bQ °Í–th­Ø(Õ¨'0*JÍôã£u1áñø¦ ˜ˆ v!TÒãYt´Èà ç¹ÕâÀ&ÐéÐJúE;æK 'b1$—wo+oÃRæGbLFHáæS~GI?›//¢[ùUeøñô¬iW¹9Qºmœéº>½)â(":d=2lЈçyAm´u“äê*Ìfh™lXÙ >šç>§?êz dF8J#oŠ]ŒÝn®)ß,;éwaƒwêw÷&lPŸfpbl@bØÈ_ÝÀ C¹‘°%@òÿlÚO8áÌ­ïå†çÐÕíëR¦ù „BŸzóRFÀr%A©“%ßšjñc}´ÎËîCrE)Í®¿Í¾EÕÑp²}64¾i‡Ç’¶ãj”ªkªöþ~IPö÷gUéTMÊöú'îO™=‚Æ».e’öu,a”ÐÖ{X9ÇŽ½wo¥dç«Ö;švR±¢¯v¿%ì¿}M·ž¡É„¦ˆÍý‡ññœéÿpÀþÿÿŸ00µ;»:Ø;ÛÀÂþFuÁ% endstream endobj 88 0 obj << /Type/FontDescriptor /CapHeight 850 /Ascent 850 /Descent -200 /FontBBox[-36 -250 1070 750] /FontName/WFLZGO+CMR8 /ItalicAngle 0 /StemV 76 /FontFile 87 0 R /Flags 4 >> endobj 87 0 obj << /Filter[/FlateDecode] /Length1 712 /Length2 5531 /Length3 533 /Length 6083 >> stream xÚí’g8œí»î½Dôž FoƒÌˆ’轆 Ff0Œ½GÑ QF‰ÞKD‹Þ‰h‰èè-¬¼ï»ÿkû¿ö—u¬oûØÏóå¹®ó|Îûw_÷ÍÅ®g $ÇX#T0hw!QaQ)€¢¶þ#€¨0ˆ”‹KÑsGbÐJ0w„@TRR ïaD!Râ’RA¤¤\EŒ³+ÒÎÞÀ«È÷—K ï„pEÚÀÐm˜»=ÂéOˆ 0ÀØ î>€< Ðÿë7€> áꉀ “’ŠŠàHw€5‰&ù Im‹HüÓ†{8ÿKòD¸ºýáðþáäü¡„cÐ(aK*¢ƒù³âËëÿBõïá*(”Ì靸?cú/*Ì ‰òù_:ÆÉÙÃá ÐÆÀ®è·#þAÓFÀ‘Nÿ®ª»ÃPHy´ ýÓBº© ½p=¤»=À†rCüÝG áÿñgl#ˆ«hAUuþ>Ð4=íþÌÇù?Sÿ2ÿ]‹þïúÏp\‘ÞS0$úÇøçý×—ù¿­¥Œ¶ÁÀ‘h;€; ‡¹Âÿ³ñ_™0Þ~Bâ€øÏI€`ЋÿÓhˆFºx Ô•`$!ù•‡«+íþ÷%ø³ßÕ¶È?ÓA ¼6¤™o鸖‚l'VÇSÆF¦õH[ vÓÀ§9ôcýd(ᇈ0G½ãYŠËm½˜ÔsÞ²‘ÕÚÒñ§]>>Ìeßèùm‡>š.H•Ç® MÐÔCñDÚ÷1Í–¦µ9`? Ê…CxŽ»sÛ¯v¦†«©¾€¶9xT m`¶våÕj Ž”Í”²—æ,ËÓ*Bô¨"JÃèS%FóÂ)D<ìÆðHNÈ0p²NÍþy ¶>gX˜åx ›³®¦&#=f¾âßÃM*•â_æ\”oY¯HÇĆÏYGhæ«È‘ã¸[.íZnó)! 0(Pè|h’(Ë)ï@|7ÌÞ·^áN6Ÿ“XºÖº9»ik¿:ac'ú3ŒÆ½Ç—­s!r9N +:Ëᨇ.WÏo~@¥½ø”¬ô­3Ü/$ t\\<„Zפ:3ëjñX7-êoì$ÉH*´³¿Ìàº+ž˜2”Í¥tž,r¬æÆ´ít‘rzJ …ÌŒÐk4¸1÷6ߑۤC¹‘E orn²×¼ŸÝ ¤(†Šw½2¿ø1¥x•.mÍT\³  ~1MCý€¨È²9>\ã ǶFˆBës|´¶.Á • OšõG¿’ÝecHäºâí™,ζâxøÎÊ)´ü•r8°(^=©iàkšˆýr‘é¯UXV~¥]`Ì…„™fI‡ÿnWoÊï ýÎÊuº=¹w•„mD/%E÷õâ9D꼨s©N[H”¬²vu¼=)K­îê”=ôì%Øú€KÙ/M> 6C]dlWå’ñÚG]j5:Ÿr¸Ï€Þ5Îm‚/)mñ{¤?yzõ{÷Ü™çòpCŠ_áuUŠ;;ŸÒŠ¿=Sgjät’R³&›ŒU+è z¬Ê¸šPÌ}”Až8§ñäsÒ ¨äÖÊ;9†ä\Ï©¾ÏTb=Þ˜ø ‰˜«’oßGq'—6(df k^iÅÈÎÍÎÄçž`zÑSÉ@3îàJ2¯ÍeÚ’€Mâüà[„Ë;¯I@1ÛñÕ4-Œûî[‡Ú!ŸØÅgBçk„yå=ß0á0ÛŸ0í#ÐàtÊr[wyûî› (2©qùM!ï$3ùž§Ú,åĵóÁÓà¾fV&5 ÿì‰ðç¼&ÍbV0š6DÃÌ¿|'d˜–4ðHDW7¤´ñÝò€É¾ëÐæNŽÚëˆøwU÷ÚŸSþƪhû™‡&†5³ç‘“Ćß%φ*[Ýÿ0µ¿¬ÊŒ3Îûnæ*õüþîü®Öϵ·®g64ä2ðë{D8ç¬Å¥oßL%”¥TüjÖ@™ÜRލ`nùh¥2[‚ a \rr o×fo=YßMv<š|YÑÇÆÆç§Úú¶)Š†Ý ¥èNÍo~Ðsá¿»-¸¸WKiÃN)¥µûA\ªH2lfw?%!¼€`|»§ÿEÕ­^Q‡¾ëÞ)AszêÓúù¤Ôü^±±¶‡ÒSuKåõ_inµøרT âÛkç.âCäãLºñˆ}ÆCÜUŸ,VYv·z"ÁY'¬@c€Lv¯ÄjPúH!‚¿èkú;>Mx4àêzØÞ«cµ7"ÇsšOktÏZÕ›Æ1ã)c= Ôt¯:þzÜKß™±bPcû¨à‚oPŠÿȇ¿ÞM+2Qf¿A¥tM¦È®)ä'u<{yLèràpZ!åÓ5óµRzbƲ$/^ŠïVDV O-¯¦Uó$#ÆÄ;"ù÷ülO]ïA•Œ¿\!•ß^XÈ)&Œ:ùØV;E~9ÝfUTd´š˜ÂÝû°îÍ”¬…‡qÀ x)¦vtmtî€1ð\Šä(’ÂTÆq¬cOÑkSõ\`DJÓO/Ò+C C“§¸¿´ÊI qxUŽý¾K‚Ÿ ›6ϱšó .…A†(gè{îÚºLynAÄ ÙÓQ*—U¤~ |˜–‘„ý@©ö‚»vn!‰Vå­xÿ¸óà Œ:Qˆ8½ ;%’–®rÇq!-¢ôfo™ ”JÁ$„ü½oÒYÐ} 7Ã9aîD*‘óá>Ób²vM¥òÚdÕÛ}@iÈE:~ïm|×Roú›+TœBØPk¦e˜¹¬/S²œ¿/'¡þ¦žAì×V´ Û,}‘Ïmõ6Þ3ªæq#ÎcÑ'ßÊX÷Õ§L×™nÓSÛîŸ,ÀS‰Ó$ÔBéÞíðnÿDñ|»uóùˆÊ8Ñ£æ8¾@º­ðE²¿[#²è>«B ª'È=­$Ÿ·ÈMòWLn§F—ëkA|ðÝÖ–)m1+ûeoWÉ2•­™£½˜†EèØŒ‰ö#i±Á€Ÿ„Ä·¹gfÃmAÕÏßGZÔ¤e%ÄYØ$P”¹õ®´<ŒùZ-ÎÅœVƒ;£_Ø» xåšò_PYòK?9˜,Û Ežud¸A:tó4wn·öi ¢”9²ú0‘™”#]e«ÁY!Sæ_fL£ÔÜÁ;ì5Ä2ØXùxÜ¿þZCà“jˆŸu@ clç/™UÝ™:ûÇV8"‰º<ÉCŸ©ªü¹Õ›Ì+Å$¬&Qiáiµ‹só|‚ÝqÊÚ kÇÔ²õƒ¢O¯¦ò^W–±Ø:¿q¨y.\ jãö¤±È±B”ËF‚Žb"gn ¤‘à±­]݈×Löèöúß¡ù¤”fY_qÊ/J‚÷‘ëêÞQÁ{nZ]oÕeº=Êš¾ûÛ4kEè‘RÕ™Í3|¶^ÓEÒ`‡ýŠ®.ÎNv¶VˆQAÍâ¼!%½_^ÇÊ >CçDÜÌ^oãÐ…B…,ã)N‹¡Bþ;3-û;áNã3E\'J–]#Ú ZÈj*Û3¿ä¸iù¬àòn‹z[÷Á"ÍËŸg˜1Úòsïh½µµW~Ï‹ˆ‘=µ^ÅšÆA^Ÿ×ßJvîÉ„“·çäz³<š³P=;oiWÚϰ:ÇÎìŠÂ|œ¼’i‰”§åÄf}_è|Ö w‹ˆMlT‚zŽ]¡­žþŸµKfíâÇÆJ•«Òyñl|I ;u1سñ‹¡QDdtofõ\f-Ħ)U…ñÅ(#6í—ÖÃàV“-R<ÕÌËêMP¸¹ &6îu?­ª3³æÊ.¯ß!jâ £•.N=C‰n;f[%Læ1ŸöÐÍî(f(¸aÂ$¹avÒ·¹7´àõyúd#>á&$êþ^s‰¯3•aqk‡ÌÙJ9{ŒÔk%žY1Qî±¾ª ]¼1œ}¾ª³ï6ŒÏÆòíä¼å‹T £ ðÂ|ìe6Ó©:Ó¿¯Lét‰ ÐWR¬úXõwÃsVÊÀÒžŒyXÝíÀOK9â ¾ñàvØS’3KÜDÌ—Éï‹Âè3Š|N]ÜZü¶Þ¯›x¸^PÏQÌ=1Ð%UÖ. hÊŸ€Ð~ÊÉîÏ´ý1Mew“XNt¿Æó4‹o%þcÛÕ!Ès6Zê ]‰… ¤ðkK”vêë$¿šÅ(ÆIÔö7ÚAí7ë#ñüMàjJÓZûÒe›q›Ÿ¡³6ua·ôA~ëã:ÙO^ÈË’5}¾¨àg=3ìæ…&ØOïXy?6ƒ…’8Ü-(pW?ᩪ;‘Ó.Ð¥C²°u…Æ@gÿlW°A<—IÑg1‘üGß*„ᾇl†%ø¬š n–[>?ɵÆáHtume`4àÛ›D!ƒsÍM!Ià{RR°PÞKµzžŸSó¡å»‚¶Olw¡…ø|t#û³¨ØÐìÕ™9·µxCóë¤eƒ«p%BïÜŠ2:ªì´ÞB²Fú´wëòܘO)0TE3 ¯>íäéì¼5´­Õ.¬þmñ˜|xø]{BIÔÍOMø Ï7gY95ñ›\Û÷ÞP ¯FÖó S¢ünd£,ÞsÆ6zªÀ)w—/dƒ`2lï§­ÊŸ¯á7»3,”ô„T¦e£“‰c·ÁvªîÌÃV—à p‹¹¡u-ãï+ûaïV`h»‚Só¯£;¿;*C­C"7®ÅÄì7YüÇ'ßñ¾ žJpÐÔP2~{Óô  Èƒºig ¥lš]D§%è&Z “MDû:Dæx+ÜÇyhqÙ.‘Ås‡‘Ë%}ð£ \È=Ôev­ó£ã@×µÏ0´\5Ïè/R¼ןòï”ïP{}’¡O.>™#âvò„€õµŸÄJ¢ì¡¨¨µmßH~«æÓÝ<>×€·=*4+*£»£•¯©zr`b!¶t§êQŸŸ2°q»¬çÓòM¿ïÉQ."Oô¦Äa¿ä?°½û¸oäáñ}OŸ¦,ꣴçà¯y2·‘ûû¢Œ™f"Tæ›5V渓AÂ/ê–öDöZ÷_z ®’IOñ´×šoõÔÔ—'*÷¿©œ—yÚkA 6ÈîLÔÛ€¹´…Ga~rHƒÂm2UVJz2YœÅ–ðf‹ánü²d ËAvqÅgìUou(ø¦+ùÓfÜ$©¹„%úÔ¨»þ©ñö=ÖCb•Wð>ø«·÷ƒ÷9M|>ºVGíg‘èfDábešlXY3Üåj3ïÄ.=Ós›¯¬(ÔGaêâ:# ª¬ììHµu9Wô ËÒ…5”ïÒê#×I]*»dù¢,}¤¢äO ¶¼±³·dÞ›¾•hk¤öÄÞpâÍ?·mÛÓÜúH O׋Öõ4Íò¨¬r4[N±M§âÊ kÜåÔ‚P›«ª¡³ØiòMsù†Mä5Gg;¹«lœíÒšÙ‡Ò´ŠN•owg^cÏU‰’'ž*\Fð€Öq;¤º\âL­÷RÂléJ–Û¯PQ5V÷˜0êÖÈPJ úÌôì Ó4~Žohˆº(qG ]˜V=sV¢Š+T3•1{>'s•Ä}§f[C=EB·:ª¹þ»Íb¯§¯»v-¯.ræ³6°µ¿‰ êšJ.Vs‹¦/6lêÎÁòzf„`Ž4`z:ÁºãW¬¹¬oUYQÙ%LI«û9²‘ ©þ†7¯…«Ü:ªI£’÷:3wæNúF:Ùô~éÊN)Ý9“!žë¹¶MEã¥o5Dð4€ ™ñ‡#Ðýw”*Mºóæ¼ÍDÂÑãÔ‰‡O êyTr ˜Ñ¬dĬðL¬‚½‹(d?<©RE†×ÒMà‘f"7ÉÅ+'.pa$;µ6ç:“o­Ü}I¯ÝT¦~Å’Žà×Á QdHìGÝY>Øð×éd›Kû›M‚m­ž3ý ‘Ó äR0_Ê#(—‘3i!lubR[²zþšfš)@ln¼"ARþ”ßqÄöýh´8 ãEm€æ›cÂ.±Þð󉨅0Ó¤è{le-Ëí/çîRFŒàh¯MPœ¨Jr€ë¿ Ž-T®Î:r\d’ɀʬE¯œÄ á_9Äš6);ÏK4‹ƒ~$N:–·íD³©:ºã µøê}è[=0æ=lV²ŒÎ »üùõKMãpi-ž½Øfh™ÿx#W¤*ÅÝw1!)èn÷î×&ë^/±<ÏíY½lîqÿMný´ñŸ¦¨pÚây¹Bú¦´UéwȽ0û¯VuwÝ|ÞŸè_ëuÝ'Õ÷ X9uø¸­þtÁ·ò;,Ævü«ªYåf¡áιl<õç¤óI¾à‡×ª%+¿×·üèâø+¨§öÞ>S+p ‰š›–Èì¬â£/ÃèõU—höZšuŒK~`*N “úh=.)‘è_ƒúùø €¾uK‡‡:f‘{TŸ] ®£_«Ü÷ø­þ-›•£°=P”é]K1vòZœN\õ ÞË76]óÝk|‘v.ðNbc!,þ0-Ÿ¿9xlAÖÖØ´O,aã2 WúvwMtøÒ±Ü<¤¤ö]Yìë>‚pûvwñíþP‹f‚;ÔÖÏÆÜö…ˆ·1t¥@Ôà§¶ `ö¤ýsHít\ôëf+Q''çO#ÉÒ–Mù ›%cNz™ã#¦Êh œ+ŸâªDG+Zê¶³°†8ÜûrÌq#­"\~Ø)YÙ‘ú¡oó£See\™m"-ru ‰£{§Œ aùóüò   ô?|HÿÀÿ6(ÌÕãsu$%ýæ endstream endobj 93 0 obj << /Type/FontDescriptor /CapHeight 850 /Ascent 850 /Descent -200 /FontBBox[-30 -958 1146 777] /FontName/FHLGUL+CMSY9 /ItalicAngle -14.035 /StemV 87 /FontFile 92 0 R /Flags 68 >> endobj 92 0 obj << /Filter[/FlateDecode] /Length1 721 /Length2 1148 /Length3 533 /Length 1690 >> stream xÚí’kT׆…bP,l­[*!ÃÅHÐ*D"F! ˆ± “d S“ Êe©ÑbMê (%(ˆ¢ EK…RQ숭DPTLm+‚ r©PO€ãé:´ºú¯«³ÿÌ÷½ï~÷³¿§E,Ž«¯PÊGèR w…HИœ-Þ"‘ NN49ã¨[ã@ÞÞðUDÈ )Twwª;…@p4it¼áÀ™æ2î¢_ "G0˜0.B$†,©Eðx¾b1`o‰l$‘Ç"BA@ˆ pÀG¢PŒà6δ‹”Êd[¨ˆ~+Å"òp6pº¥PЉã‰$¸J §!–?õTSÃé ±8–ŒÇÏéw2,AÅñÿ5H%Ñ ‘¦TˆÈ±©ÖÍÈ$¢ ÉTu‹Q/%F€+äI"{xM h C„,ˆ@$,ŽA&ú&œŠb˜Þˆ=`ÓúMË&?ì¤È‚Q çÆG#€ü›{¢†~« C’£q`+™D&C£a½}Û6å0L ¢Xàà0&„åÂÿ5~åç'Ktõ Wo¯•‚3Åu•«9|svvùÂŒØBwAƒYgsõ¦$ã§ÓNcø~Ó,ûoðô硹¾Ë}Ì‹Gzd‰Ïîg&$E\YÏ‹²»P¿j³¥ë’£òXŽ ùÔhÝõáhvÜá¨éßntÔc¿yãBKj;…Õ–^é×Þ!öóÉ!®îôЂÎYäQá¥Aö|ì Ç Úþñë‰Ë_¾ÏP—âë•’2Zê½gk]ÂôwúÌ7Ìýwa ëû‡èÕoŠÖ¶ÛÎùåEšåÕkaèÍBŸú"fžãbî‘£ÏDz{#øjHú.&Ó0ô¯üû>K¾÷,AÙ}vÉ·´æW'šÁÕ«ŒbPºûÄŽî|¼&ÿïFËí=e*.å`○ܩ]ô^÷¨s_mW•¶ôC“ŠƒÔ7ʃƒ¶gž]v6†*x }³"/pÓ­/—i¯ª~vªÚ§Ù%£{ >ý!u+ìͽÔObTýÆÛÖUª•^£‰KËus” Œ›Ë0WuŠhê!‹p~|7îŒgÕ2§ˆ 5ŕ׌z†‹œ¶œaçÉ~MgÎôÏ·Hɬ‚^ §.dÖ¸«µWª Æ{õI^¦u|9ÌêcNE£ßBsâíÈœ£·ËN§§%À¯IáK±=ìóš'ÊÕwÙËJË.E8Èü0WasŽæ5–œã~þúl`²ƒôÓ‚^ÛïZ ;-ìvðLÛ2¶vS댶S”Ïsn[X!ÏC™ü“·ËN3Ís¬)œCsˉ—Uµ;íOզʾ©,eõä½x×h¶ ½üXÇjáëÜ‚ÎhhVGð¢ZÂaWk…çýÎ6žË*Ùè²kL±f,_6$œ?¯I›“s¼%QîR³uÞ¶|_Jk€y¯>3ÌúXÃÝÌz—ˆ~óK|w•.Ê¢ùéYû’KïýúõÒÁ«[ªíŸ[ȸ6ût»nf=¨RòúRºÌW]4KÖvŽh‰Ú’Dؤ_…=NS¼š‡~nÚí“•g‡Ïyf3Þ)HÊ íŠíô_4}Z%°ºªm‡­[Õakîô¬à·Šß·Í¼VXÃ;«iç,¦d•œ/?¹¨ûÃöPpH7Þ†XaYùÕðsß56Q6Û"7]_3Î[_Ì@çwX)Jë5.#¶þiÑo8裼±VÅ?Ñg«¹ûr9%ô§X=;-fÈhHTØÕ—ªÛèwr¨^Íø*àê­v%À»Èñ!üð·ˆXŽK%°|ðÜQ endstream endobj 1 0 obj << /Creator(LaTeX with hyperref package) /Title() /Subject() /Author() /Producer(dvipdfm 0.13.2d, Copyright \251 1998, by Mark A. Wicks) /Keywords() /CreationDate(D:20100824211955-04'00') >> endobj 5 0 obj << /Type/Page /Resources 6 0 R /Contents[74 0 R 4 0 R 75 0 R 76 0 R] /Annots 77 0 R /Parent 488 0 R >> endobj 79 0 obj << /Type/Page /Resources 80 0 R /Contents[74 0 R 4 0 R 98 0 R 76 0 R] /Parent 488 0 R >> endobj 100 0 obj << /Type/Page /Resources 101 0 R /Contents[74 0 R 4 0 R 104 0 R 76 0 R] /Parent 488 0 R >> endobj 106 0 obj << /Type/Page /Resources 107 0 R /Contents[74 0 R 4 0 R 109 0 R 76 0 R] /Parent 488 0 R >> endobj 488 0 obj << /Type/Pages /Count 4 /Kids[5 0 R 79 0 R 100 0 R 106 0 R] /Parent 487 0 R >> endobj 111 0 obj << /Type/Page /Resources 112 0 R /Contents[74 0 R 4 0 R 115 0 R 76 0 R] /Parent 489 0 R >> endobj 117 0 obj << /Type/Page /Resources 118 0 R /Contents[74 0 R 4 0 R 120 0 R 76 0 R] /Parent 489 0 R >> endobj 122 0 obj << /Type/Page /Resources 123 0 R /Contents[74 0 R 4 0 R 125 0 R 76 0 R] /Parent 489 0 R >> endobj 127 0 obj << /Type/Page /Resources 128 0 R /Contents[74 0 R 4 0 R 130 0 R 76 0 R] /Parent 490 0 R >> endobj 132 0 obj << /Type/Page /Resources 133 0 R /Contents[74 0 R 4 0 R 136 0 R 76 0 R] /Parent 490 0 R >> endobj 490 0 obj << /Type/Pages /Count 2 /Kids[127 0 R 132 0 R] /Parent 489 0 R >> endobj 489 0 obj << /Type/Pages /Count 5 /Kids[111 0 R 117 0 R 122 0 R 490 0 R] /Parent 487 0 R >> endobj 138 0 obj << /Type/Page /Resources 139 0 R /Contents[74 0 R 4 0 R 143 0 R 76 0 R] /Parent 491 0 R >> endobj 145 0 obj << /Type/Page /Resources 146 0 R /Contents[74 0 R 4 0 R 148 0 R 76 0 R] /Parent 491 0 R >> endobj 150 0 obj << /Type/Page /Resources 151 0 R /Contents[74 0 R 4 0 R 153 0 R 76 0 R] /Parent 491 0 R >> endobj 155 0 obj << /Type/Page /Resources 156 0 R /Contents[74 0 R 4 0 R 158 0 R 76 0 R] /Parent 492 0 R >> endobj 160 0 obj << /Type/Page /Resources 161 0 R /Contents[74 0 R 4 0 R 163 0 R 76 0 R] /Parent 492 0 R >> endobj 492 0 obj << /Type/Pages /Count 2 /Kids[155 0 R 160 0 R] /Parent 491 0 R >> endobj 491 0 obj << /Type/Pages /Count 5 /Kids[138 0 R 145 0 R 150 0 R 492 0 R] /Parent 487 0 R >> endobj 165 0 obj << /Type/Page /Resources 166 0 R /Contents[74 0 R 4 0 R 168 0 R 76 0 R] /Parent 493 0 R >> endobj 170 0 obj << /Type/Page /Resources 171 0 R /Contents[74 0 R 4 0 R 173 0 R 76 0 R] /Parent 493 0 R >> endobj 175 0 obj << /Type/Page /Resources 176 0 R /Contents[74 0 R 4 0 R 178 0 R 76 0 R] /Parent 493 0 R >> endobj 180 0 obj << /Type/Page /Resources 181 0 R /Contents[74 0 R 4 0 R 183 0 R 76 0 R] /Parent 494 0 R >> endobj 185 0 obj << /Type/Page /Resources 186 0 R /Contents[74 0 R 4 0 R 188 0 R 76 0 R] /Parent 494 0 R >> endobj 494 0 obj << /Type/Pages /Count 2 /Kids[180 0 R 185 0 R] /Parent 493 0 R >> endobj 493 0 obj << /Type/Pages /Count 5 /Kids[165 0 R 170 0 R 175 0 R 494 0 R] /Parent 487 0 R >> endobj 487 0 obj << /Type/Pages /Count 19 /Kids[488 0 R 489 0 R 491 0 R 493 0 R] /Parent 3 0 R >> endobj 190 0 obj << /Type/Page /Resources 191 0 R /Contents[74 0 R 4 0 R 193 0 R 76 0 R] /Parent 496 0 R >> endobj 195 0 obj << /Type/Page /Resources 196 0 R /Contents[74 0 R 4 0 R 198 0 R 76 0 R] /Parent 496 0 R >> endobj 200 0 obj << /Type/Page /Resources 201 0 R /Contents[74 0 R 4 0 R 203 0 R 76 0 R] /Parent 496 0 R >> endobj 205 0 obj << /Type/Page /Resources 206 0 R /Contents[74 0 R 4 0 R 208 0 R 76 0 R] /Parent 496 0 R >> endobj 496 0 obj << /Type/Pages /Count 4 /Kids[190 0 R 195 0 R 200 0 R 205 0 R] /Parent 495 0 R >> endobj 210 0 obj << /Type/Page /Resources 211 0 R /Contents[74 0 R 4 0 R 213 0 R 76 0 R] /Parent 497 0 R >> endobj 215 0 obj << /Type/Page /Resources 216 0 R /Contents[74 0 R 4 0 R 218 0 R 76 0 R] /Parent 497 0 R >> endobj 220 0 obj << /Type/Page /Resources 221 0 R /Contents[74 0 R 4 0 R 223 0 R 76 0 R] /Parent 497 0 R >> endobj 225 0 obj << /Type/Page /Resources 226 0 R /Contents[74 0 R 4 0 R 228 0 R 76 0 R] /Parent 498 0 R >> endobj 230 0 obj << /Type/Page /Resources 231 0 R /Contents[74 0 R 4 0 R 233 0 R 76 0 R] /Parent 498 0 R >> endobj 498 0 obj << /Type/Pages /Count 2 /Kids[225 0 R 230 0 R] /Parent 497 0 R >> endobj 497 0 obj << /Type/Pages /Count 5 /Kids[210 0 R 215 0 R 220 0 R 498 0 R] /Parent 495 0 R >> endobj 235 0 obj << /Type/Page /Resources 236 0 R /Contents[74 0 R 4 0 R 238 0 R 76 0 R] /Parent 499 0 R >> endobj 240 0 obj << /Type/Page /Resources 241 0 R /Contents[74 0 R 4 0 R 243 0 R 76 0 R] /Parent 499 0 R >> endobj 245 0 obj << /Type/Page /Resources 246 0 R /Contents[74 0 R 4 0 R 248 0 R 76 0 R] /Parent 499 0 R >> endobj 250 0 obj << /Type/Page /Resources 251 0 R /Contents[74 0 R 4 0 R 253 0 R 76 0 R] /Parent 500 0 R >> endobj 255 0 obj << /Type/Page /Resources 256 0 R /Contents[74 0 R 4 0 R 258 0 R 76 0 R] /Parent 500 0 R >> endobj 500 0 obj << /Type/Pages /Count 2 /Kids[250 0 R 255 0 R] /Parent 499 0 R >> endobj 499 0 obj << /Type/Pages /Count 5 /Kids[235 0 R 240 0 R 245 0 R 500 0 R] /Parent 495 0 R >> endobj 260 0 obj << /Type/Page /Resources 261 0 R /Contents[74 0 R 4 0 R 263 0 R 76 0 R] /Parent 501 0 R >> endobj 265 0 obj << /Type/Page /Resources 266 0 R /Contents[74 0 R 4 0 R 268 0 R 76 0 R] /Parent 501 0 R >> endobj 270 0 obj << /Type/Page /Resources 271 0 R /Contents[74 0 R 4 0 R 273 0 R 76 0 R] /Parent 501 0 R >> endobj 275 0 obj << /Type/Page /Resources 276 0 R /Contents[74 0 R 4 0 R 278 0 R 76 0 R] /Parent 502 0 R >> endobj 280 0 obj << /Type/Page /Resources 281 0 R /Contents[74 0 R 4 0 R 283 0 R 76 0 R] /Parent 502 0 R >> endobj 502 0 obj << /Type/Pages /Count 2 /Kids[275 0 R 280 0 R] /Parent 501 0 R >> endobj 501 0 obj << /Type/Pages /Count 5 /Kids[260 0 R 265 0 R 270 0 R 502 0 R] /Parent 495 0 R >> endobj 495 0 obj << /Type/Pages /Count 19 /Kids[496 0 R 497 0 R 499 0 R 501 0 R] /Parent 3 0 R >> endobj 285 0 obj << /Type/Page /Resources 286 0 R /Contents[74 0 R 4 0 R 288 0 R 76 0 R] /Parent 504 0 R >> endobj 290 0 obj << /Type/Page /Resources 291 0 R /Contents[74 0 R 4 0 R 293 0 R 76 0 R] /Parent 504 0 R >> endobj 295 0 obj << /Type/Page /Resources 296 0 R /Contents[74 0 R 4 0 R 298 0 R 76 0 R] /Parent 504 0 R >> endobj 300 0 obj << /Type/Page /Resources 301 0 R /Contents[74 0 R 4 0 R 303 0 R 76 0 R] /Parent 504 0 R >> endobj 504 0 obj << /Type/Pages /Count 4 /Kids[285 0 R 290 0 R 295 0 R 300 0 R] /Parent 503 0 R >> endobj 305 0 obj << /Type/Page /Resources 306 0 R /Contents[74 0 R 4 0 R 308 0 R 76 0 R] /Parent 505 0 R >> endobj 310 0 obj << /Type/Page /Resources 311 0 R /Contents[74 0 R 4 0 R 313 0 R 76 0 R] /Parent 505 0 R >> endobj 315 0 obj << /Type/Page /Resources 316 0 R /Contents[74 0 R 4 0 R 318 0 R 76 0 R] /Parent 505 0 R >> endobj 320 0 obj << /Type/Page /Resources 321 0 R /Contents[74 0 R 4 0 R 323 0 R 76 0 R] /Parent 506 0 R >> endobj 325 0 obj << /Type/Page /Resources 326 0 R /Contents[74 0 R 4 0 R 328 0 R 76 0 R] /Parent 506 0 R >> endobj 506 0 obj << /Type/Pages /Count 2 /Kids[320 0 R 325 0 R] /Parent 505 0 R >> endobj 505 0 obj << /Type/Pages /Count 5 /Kids[305 0 R 310 0 R 315 0 R 506 0 R] /Parent 503 0 R >> endobj 330 0 obj << /Type/Page /Resources 331 0 R /Contents[74 0 R 4 0 R 333 0 R 76 0 R] /Parent 507 0 R >> endobj 335 0 obj << /Type/Page /Resources 336 0 R /Contents[74 0 R 4 0 R 338 0 R 76 0 R] /Parent 507 0 R >> endobj 340 0 obj << /Type/Page /Resources 341 0 R /Contents[74 0 R 4 0 R 343 0 R 76 0 R] /Parent 507 0 R >> endobj 345 0 obj << /Type/Page /Resources 346 0 R /Contents[74 0 R 4 0 R 348 0 R 76 0 R] /Parent 508 0 R >> endobj 350 0 obj << /Type/Page /Resources 351 0 R /Contents[74 0 R 4 0 R 353 0 R 76 0 R] /Parent 508 0 R >> endobj 508 0 obj << /Type/Pages /Count 2 /Kids[345 0 R 350 0 R] /Parent 507 0 R >> endobj 507 0 obj << /Type/Pages /Count 5 /Kids[330 0 R 335 0 R 340 0 R 508 0 R] /Parent 503 0 R >> endobj 355 0 obj << /Type/Page /Resources 356 0 R /Contents[74 0 R 4 0 R 358 0 R 76 0 R] /Parent 509 0 R >> endobj 360 0 obj << /Type/Page /Resources 361 0 R /Contents[74 0 R 4 0 R 363 0 R 76 0 R] /Parent 509 0 R >> endobj 365 0 obj << /Type/Page /Resources 366 0 R /Contents[74 0 R 4 0 R 368 0 R 76 0 R] /Parent 509 0 R >> endobj 370 0 obj << /Type/Page /Resources 371 0 R /Contents[74 0 R 4 0 R 373 0 R 76 0 R] /Parent 510 0 R >> endobj 375 0 obj << /Type/Page /Resources 376 0 R /Contents[74 0 R 4 0 R 378 0 R 76 0 R] /Parent 510 0 R >> endobj 510 0 obj << /Type/Pages /Count 2 /Kids[370 0 R 375 0 R] /Parent 509 0 R >> endobj 509 0 obj << /Type/Pages /Count 5 /Kids[355 0 R 360 0 R 365 0 R 510 0 R] /Parent 503 0 R >> endobj 503 0 obj << /Type/Pages /Count 19 /Kids[504 0 R 505 0 R 507 0 R 509 0 R] /Parent 3 0 R >> endobj 380 0 obj << /Type/Page /Resources 381 0 R /Contents[74 0 R 4 0 R 384 0 R 76 0 R] /Parent 512 0 R >> endobj 386 0 obj << /Type/Page /Resources 387 0 R /Contents[74 0 R 4 0 R 391 0 R 76 0 R] /Parent 512 0 R >> endobj 393 0 obj << /Type/Page /Resources 394 0 R /Contents[74 0 R 4 0 R 399 0 R 76 0 R] /Parent 512 0 R >> endobj 401 0 obj << /Type/Page /Resources 402 0 R /Contents[74 0 R 4 0 R 404 0 R 76 0 R] /Parent 512 0 R >> endobj 512 0 obj << /Type/Pages /Count 4 /Kids[380 0 R 386 0 R 393 0 R 401 0 R] /Parent 511 0 R >> endobj 406 0 obj << /Type/Page /Resources 407 0 R /Contents[74 0 R 4 0 R 412 0 R 76 0 R] /Parent 513 0 R >> endobj 414 0 obj << /Type/Page /Resources 415 0 R /Contents[74 0 R 4 0 R 418 0 R 76 0 R] /Parent 513 0 R >> endobj 420 0 obj << /Type/Page /Resources 421 0 R /Contents[74 0 R 4 0 R 423 0 R 76 0 R] /Parent 513 0 R >> endobj 425 0 obj << /Type/Page /Resources 426 0 R /Contents[74 0 R 4 0 R 428 0 R 76 0 R] /Parent 514 0 R >> endobj 430 0 obj << /Type/Page /Resources 431 0 R /Contents[74 0 R 4 0 R 433 0 R 76 0 R] /Parent 514 0 R >> endobj 514 0 obj << /Type/Pages /Count 2 /Kids[425 0 R 430 0 R] /Parent 513 0 R >> endobj 513 0 obj << /Type/Pages /Count 5 /Kids[406 0 R 414 0 R 420 0 R 514 0 R] /Parent 511 0 R >> endobj 435 0 obj << /Type/Page /Resources 436 0 R /Contents[74 0 R 4 0 R 438 0 R 76 0 R] /Parent 515 0 R >> endobj 440 0 obj << /Type/Page /Resources 441 0 R /Contents[74 0 R 4 0 R 444 0 R 76 0 R] /Parent 515 0 R >> endobj 446 0 obj << /Type/Page /Resources 447 0 R /Contents[74 0 R 4 0 R 449 0 R 76 0 R] /Parent 515 0 R >> endobj 451 0 obj << /Type/Page /Resources 452 0 R /Contents[74 0 R 4 0 R 454 0 R 76 0 R] /Parent 516 0 R >> endobj 456 0 obj << /Type/Page /Resources 457 0 R /Contents[74 0 R 4 0 R 459 0 R 76 0 R] /Parent 516 0 R >> endobj 516 0 obj << /Type/Pages /Count 2 /Kids[451 0 R 456 0 R] /Parent 515 0 R >> endobj 515 0 obj << /Type/Pages /Count 5 /Kids[435 0 R 440 0 R 446 0 R 516 0 R] /Parent 511 0 R >> endobj 461 0 obj << /Type/Page /Resources 462 0 R /Contents[74 0 R 4 0 R 465 0 R 76 0 R] /Parent 517 0 R >> endobj 467 0 obj << /Type/Page /Resources 468 0 R /Contents[74 0 R 4 0 R 470 0 R 76 0 R] /Parent 517 0 R >> endobj 472 0 obj << /Type/Page /Resources 473 0 R /Contents[74 0 R 4 0 R 475 0 R 76 0 R] /Parent 517 0 R >> endobj 477 0 obj << /Type/Page /Resources 478 0 R /Contents[74 0 R 4 0 R 480 0 R 76 0 R] /Parent 518 0 R >> endobj 482 0 obj << /Type/Page /Resources 483 0 R /Contents[74 0 R 4 0 R 485 0 R 76 0 R] /Parent 518 0 R >> endobj 518 0 obj << /Type/Pages /Count 2 /Kids[477 0 R 482 0 R] /Parent 517 0 R >> endobj 517 0 obj << /Type/Pages /Count 5 /Kids[461 0 R 467 0 R 472 0 R 518 0 R] /Parent 511 0 R >> endobj 511 0 obj << /Type/Pages /Count 19 /Kids[512 0 R 513 0 R 515 0 R 517 0 R] /Parent 3 0 R >> endobj 3 0 obj << /Type/Pages /Count 76 /Kids[487 0 R 495 0 R 503 0 R 511 0 R] /MediaBox[0 0 612 792] >> endobj 74 0 obj << /Length 1 >> stream endstream endobj 76 0 obj << /Length 1 >> stream endstream endobj 4 0 obj << /Length 30 >> stream 1.00028 0 0 1.00028 72 720 cm endstream endobj 27 0 obj << /Title(11 Worked example 1 : xmas beamline + mar ccd detector at the ESRF) /A<< /S/GoTo /D(section.11) >> /Parent 11 0 R /Prev 23 0 R /First 28 0 R /Last 30 0 R /Count -3 >> endobj 30 0 obj << /Title(11.3 A template cif file for the xmas beamline) /A<< /S/GoTo /D(subsection.11.3) >> /Parent 27 0 R /Prev 29 0 R >> endobj 11 0 obj << /First 12 0 R /Last 27 0 R /Count 11 >> endobj 519 0 obj << /Limits[(Doc-Start)(Doc-Start)] /Names[(Doc-Start) 31 0 R] >> endobj 520 0 obj << /Limits[(page.1)(page.10)] /Names[(page.1) 7 0 R(page.10) 140 0 R] >> endobj 521 0 obj << /Limits[(page.11)(page.11)] /Names[(page.11) 147 0 R] >> endobj 522 0 obj << /Limits[(page.12)(page.13)] /Names[(page.12) 152 0 R(page.13) 157 0 R] >> endobj 523 0 obj << /Limits[(Doc-Start)(page.13)] /Kids[519 0 R 520 0 R 521 0 R 522 0 R] >> endobj 524 0 obj << /Limits[(page.14)(page.14)] /Names[(page.14) 162 0 R] >> endobj 525 0 obj << /Limits[(page.15)(page.16)] /Names[(page.15) 167 0 R(page.16) 172 0 R] >> endobj 526 0 obj << /Limits[(page.17)(page.17)] /Names[(page.17) 177 0 R] >> endobj 527 0 obj << /Limits[(page.18)(page.19)] /Names[(page.18) 182 0 R(page.19) 187 0 R] >> endobj 528 0 obj << /Limits[(page.14)(page.19)] /Kids[524 0 R 525 0 R 526 0 R 527 0 R] >> endobj 529 0 obj << /Limits[(page.2)(page.2)] /Names[(page.2) 81 0 R] >> endobj 530 0 obj << /Limits[(page.20)(page.21)] /Names[(page.20) 192 0 R(page.21) 197 0 R] >> endobj 531 0 obj << /Limits[(page.22)(page.22)] /Names[(page.22) 202 0 R] >> endobj 532 0 obj << /Limits[(page.23)(page.24)] /Names[(page.23) 207 0 R(page.24) 212 0 R] >> endobj 533 0 obj << /Limits[(page.2)(page.24)] /Kids[529 0 R 530 0 R 531 0 R 532 0 R] >> endobj 534 0 obj << /Limits[(page.25)(page.25)] /Names[(page.25) 217 0 R] >> endobj 535 0 obj << /Limits[(page.26)(page.27)] /Names[(page.26) 222 0 R(page.27) 227 0 R] >> endobj 536 0 obj << /Limits[(page.28)(page.29)] /Names[(page.28) 232 0 R(page.29) 237 0 R] >> endobj 537 0 obj << /Limits[(page.3)(page.30)] /Names[(page.3) 102 0 R(page.30) 242 0 R] >> endobj 538 0 obj << /Limits[(page.25)(page.30)] /Kids[534 0 R 535 0 R 536 0 R 537 0 R] >> endobj 539 0 obj << /Limits[(Doc-Start)(page.30)] /Kids[523 0 R 528 0 R 533 0 R 538 0 R] >> endobj 540 0 obj << /Limits[(page.31)(page.31)] /Names[(page.31) 247 0 R] >> endobj 541 0 obj << /Limits[(page.32)(page.33)] /Names[(page.32) 252 0 R(page.33) 257 0 R] >> endobj 542 0 obj << /Limits[(page.34)(page.34)] /Names[(page.34) 262 0 R] >> endobj 543 0 obj << /Limits[(page.35)(page.36)] /Names[(page.35) 267 0 R(page.36) 272 0 R] >> endobj 544 0 obj << /Limits[(page.31)(page.36)] /Kids[540 0 R 541 0 R 542 0 R 543 0 R] >> endobj 545 0 obj << /Limits[(page.37)(page.37)] /Names[(page.37) 277 0 R] >> endobj 546 0 obj << /Limits[(page.38)(page.39)] /Names[(page.38) 282 0 R(page.39) 287 0 R] >> endobj 547 0 obj << /Limits[(page.4)(page.4)] /Names[(page.4) 108 0 R] >> endobj 548 0 obj << /Limits[(page.40)(page.41)] /Names[(page.40) 292 0 R(page.41) 297 0 R] >> endobj 549 0 obj << /Limits[(page.37)(page.41)] /Kids[545 0 R 546 0 R 547 0 R 548 0 R] >> endobj 550 0 obj << /Limits[(page.42)(page.42)] /Names[(page.42) 302 0 R] >> endobj 551 0 obj << /Limits[(page.43)(page.44)] /Names[(page.43) 307 0 R(page.44) 312 0 R] >> endobj 552 0 obj << /Limits[(page.45)(page.45)] /Names[(page.45) 317 0 R] >> endobj 553 0 obj << /Limits[(page.46)(page.47)] /Names[(page.46) 322 0 R(page.47) 327 0 R] >> endobj 554 0 obj << /Limits[(page.42)(page.47)] /Kids[550 0 R 551 0 R 552 0 R 553 0 R] >> endobj 555 0 obj << /Limits[(page.48)(page.48)] /Names[(page.48) 332 0 R] >> endobj 556 0 obj << /Limits[(page.49)(page.5)] /Names[(page.49) 337 0 R(page.5) 113 0 R] >> endobj 557 0 obj << /Limits[(page.50)(page.51)] /Names[(page.50) 342 0 R(page.51) 347 0 R] >> endobj 558 0 obj << /Limits[(page.52)(page.53)] /Names[(page.52) 352 0 R(page.53) 357 0 R] >> endobj 559 0 obj << /Limits[(page.48)(page.53)] /Kids[555 0 R 556 0 R 557 0 R 558 0 R] >> endobj 560 0 obj << /Limits[(page.31)(page.53)] /Kids[544 0 R 549 0 R 554 0 R 559 0 R] >> endobj 561 0 obj << /Limits[(page.54)(page.54)] /Names[(page.54) 362 0 R] >> endobj 562 0 obj << /Limits[(page.55)(page.56)] /Names[(page.55) 367 0 R(page.56) 372 0 R] >> endobj 563 0 obj << /Limits[(page.57)(page.57)] /Names[(page.57) 377 0 R] >> endobj 564 0 obj << /Limits[(page.58)(page.59)] /Names[(page.58) 382 0 R(page.59) 388 0 R] >> endobj 565 0 obj << /Limits[(page.54)(page.59)] /Kids[561 0 R 562 0 R 563 0 R 564 0 R] >> endobj 566 0 obj << /Limits[(page.6)(page.6)] /Names[(page.6) 119 0 R] >> endobj 567 0 obj << /Limits[(page.60)(page.61)] /Names[(page.60) 395 0 R(page.61) 403 0 R] >> endobj 568 0 obj << /Limits[(page.62)(page.62)] /Names[(page.62) 408 0 R] >> endobj 569 0 obj << /Limits[(page.63)(page.64)] /Names[(page.63) 416 0 R(page.64) 422 0 R] >> endobj 570 0 obj << /Limits[(page.6)(page.64)] /Kids[566 0 R 567 0 R 568 0 R 569 0 R] >> endobj 571 0 obj << /Limits[(page.65)(page.65)] /Names[(page.65) 427 0 R] >> endobj 572 0 obj << /Limits[(page.66)(page.67)] /Names[(page.66) 432 0 R(page.67) 437 0 R] >> endobj 573 0 obj << /Limits[(page.68)(page.68)] /Names[(page.68) 442 0 R] >> endobj 574 0 obj << /Limits[(page.69)(page.7)] /Names[(page.69) 448 0 R(page.7) 124 0 R] >> endobj 575 0 obj << /Limits[(page.65)(page.7)] /Kids[571 0 R 572 0 R 573 0 R 574 0 R] >> endobj 576 0 obj << /Limits[(page.70)(page.70)] /Names[(page.70) 453 0 R] >> endobj 577 0 obj << /Limits[(page.71)(page.72)] /Names[(page.71) 458 0 R(page.72) 463 0 R] >> endobj 578 0 obj << /Limits[(page.73)(page.74)] /Names[(page.73) 469 0 R(page.74) 474 0 R] >> endobj 579 0 obj << /Limits[(page.75)(page.76)] /Names[(page.75) 479 0 R(page.76) 484 0 R] >> endobj 580 0 obj << /Limits[(page.70)(page.76)] /Kids[576 0 R 577 0 R 578 0 R 579 0 R] >> endobj 581 0 obj << /Limits[(page.54)(page.76)] /Kids[565 0 R 570 0 R 575 0 R 580 0 R] >> endobj 582 0 obj << /Limits[(page.8)(page.8)] /Names[(page.8) 129 0 R] >> endobj 583 0 obj << /Limits[(page.9)(section*.1)] /Names[(page.9) 134 0 R(section*.1) 51 0 R] >> endobj 584 0 obj << /Limits[(section*.2)(section*.2)] /Names[(section*.2) 82 0 R] >> endobj 585 0 obj << /Limits[(section*.3)(section*.4)] /Names[(section*.3) 90 0 R(section*.4) 95 0 R] >> endobj 586 0 obj << /Limits[(page.8)(section*.4)] /Kids[582 0 R 583 0 R 584 0 R 585 0 R] >> endobj 587 0 obj << /Limits[(section.1)(section.1)] /Names[(section.1) 96 0 R] >> endobj 588 0 obj << /Limits[(section.10)(section.11)] /Names[(section.10) 397 0 R(section.11) 411 0 R] >> endobj 589 0 obj << /Limits[(section.2)(section.2)] /Names[(section.2) 97 0 R] >> endobj 590 0 obj << /Limits[(section.3)(section.4)] /Names[(section.3) 103 0 R(section.4) 141 0 R] >> endobj 591 0 obj << /Limits[(section.1)(section.4)] /Kids[587 0 R 588 0 R 589 0 R 590 0 R] >> endobj 592 0 obj << /Limits[(section.5)(section.5)] /Names[(section.5) 142 0 R] >> endobj 593 0 obj << /Limits[(section.6)(section.7)] /Names[(section.6) 383 0 R(section.7) 389 0 R] >> endobj 594 0 obj << /Limits[(section.8)(section.8)] /Names[(section.8) 390 0 R] >> endobj 595 0 obj << /Limits[(section.9)(subsection.10.1)] /Names[(section.9) 396 0 R(subsection.10.1) 398 0 R] >> endobj 596 0 obj << /Limits[(section.5)(subsection.10.1)] /Kids[592 0 R 593 0 R 594 0 R 595 0 R] >> endobj 597 0 obj << /Limits[(subsection.10.2)(subsection.10.2)] /Names[(subsection.10.2) 409 0 R] >> endobj 598 0 obj << /Limits[(subsection.10.3)(subsection.11.1)] /Names[(subsection.10.3) 410 0 R(subsection.11.1) 417 0 R] >> endobj 599 0 obj << /Limits[(subsection.11.2)(subsection.11.3)] /Names[(subsection.11.2) 443 0 R(subsection.11.3) 464 0 R] >> endobj 600 0 obj << /Limits[(subsection.3.1)(subsection.3.2)] /Names[(subsection.3.1) 114 0 R(subsection.3.2) 135 0 R] >> endobj 601 0 obj << /Limits[(subsection.10.2)(subsection.3.2)] /Kids[597 0 R 598 0 R 599 0 R 600 0 R] >> endobj 602 0 obj << /Limits[(page.8)(subsection.3.2)] /Kids[586 0 R 591 0 R 596 0 R 601 0 R] >> endobj 603 0 obj << /Limits[(Doc-Start)(subsection.3.2)] /Kids[539 0 R 560 0 R 581 0 R 602 0 R] >> endobj 604 0 obj null endobj 605 0 obj << /Dests 603 0 R >> endobj 2 0 obj << /Type/Catalog /OpenAction[5 0 R/Fit] /PageMode/UseOutlines /Pages 3 0 R /Outlines 11 0 R /Threads 604 0 R /Names 605 0 R >> endobj 8 0 obj << /Type/Encoding /Differences[24/breve/caron/circumflex/dotaccent/hungarumlaut/ogonek/ring/tilde 39/quotesingle 96/grave 128/bullet/dagger/daggerdbl/ellipsis/emdash/endash/florin/fraction/guilsinglleft/guilsinglright/minus/perthousand/quotedblbase/quotedblleft/quotedblright/quoteleft/quoteright/quotesinglbase/trademark/fi/fl/Lslash/OE/Scaron/Ydieresis/Zcaron/dotlessi/lslash/oe/scaron/zcaron 164/currency 166/brokenbar 168/dieresis/copyright/ordfeminine 172/logicalnot/.notdef/registered/macron/degree/plusminus/twosuperior/threesuperior/acute/mu 183/periodcentered/cedilla/onesuperior/ordmasculine 188/onequarter/onehalf/threequarters 192/Agrave/Aacute/Acircumflex/Atilde/Adieresis/Aring/AE/Ccedilla/Egrave/Eacute/Ecircumflex/Edieresis/Igrave/Iacute/Icircumflex/Idieresis/Eth/Ntilde/Ograve/Oacute/Ocircumflex/Otilde/Odieresis/multiply/Oslash/Ugrave/Uacute/Ucircumflex/Udieresis/Yacute/Thorn/germandbls/agrave/aacute/acircumflex/atilde/adieresis/aring/ae/ccedilla/egrave/eacute/ecircumflex/edieresis/igrave/iacute/icircumflex/idieresis/eth/ntilde/ograve/oacute/ocircumflex/otilde/odieresis/divide/oslash/ugrave/uacute/ucircumflex/udieresis/yacute/thorn/ydieresis] >> endobj 9 0 obj << /Type/Font /Subtype/Type1 /Name/ZaDb /BaseFont/ZapfDingbats >> endobj 10 0 obj << /Type/Font /Subtype/Type1 /Name/Helv /BaseFont/Helvetica /Encoding 8 0 R >> endobj xref 0 606 0000000000 65535 f 0000205014 00000 n 0000224807 00000 n 0000216404 00000 n 0000216609 00000 n 0000205220 00000 n 0000014735 00000 n 0000000009 00000 n 0000224949 00000 n 0000226134 00000 n 0000226215 00000 n 0000217022 00000 n 0000000049 00000 n 0000000152 00000 n 0000000498 00000 n 0000000282 00000 n 0000000390 00000 n 0000000681 00000 n 0000000795 00000 n 0000000907 00000 n 0000001054 00000 n 0000001200 00000 n 0000001333 00000 n 0000001880 00000 n 0000001471 00000 n 0000001601 00000 n 0000001753 00000 n 0000216688 00000 n 0000002030 00000 n 0000002152 00000 n 0000216881 00000 n 0000002301 00000 n 0000002342 00000 n 0000123879 00000 n 0000123688 00000 n 0000003247 00000 n 0000126394 00000 n 0000126208 00000 n 0000004191 00000 n 0000131050 00000 n 0000130864 00000 n 0000005186 00000 n 0000137918 00000 n 0000137730 00000 n 0000006104 00000 n 0000147178 00000 n 0000146992 00000 n 0000007104 00000 n 0000161137 00000 n 0000160948 00000 n 0000008073 00000 n 0000009020 00000 n 0000009061 00000 n 0000009198 00000 n 0000009335 00000 n 0000009472 00000 n 0000009613 00000 n 0000009754 00000 n 0000009891 00000 n 0000010028 00000 n 0000010165 00000 n 0000010302 00000 n 0000010439 00000 n 0000010575 00000 n 0000010713 00000 n 0000010856 00000 n 0000010999 00000 n 0000011142 00000 n 0000011277 00000 n 0000011418 00000 n 0000011559 00000 n 0000170564 00000 n 0000170376 00000 n 0000011700 00000 n 0000216509 00000 n 0000012618 00000 n 0000216559 00000 n 0000014485 00000 n 0000014636 00000 n 0000205338 00000 n 0000023738 00000 n 0000014796 00000 n 0000014838 00000 n 0000014880 00000 n 0000181870 00000 n 0000181685 00000 n 0000015857 00000 n 0000196819 00000 n 0000196633 00000 n 0000016600 00000 n 0000017601 00000 n 0000017642 00000 n 0000203210 00000 n 0000203016 00000 n 0000019258 00000 n 0000020258 00000 n 0000020300 00000 n 0000020342 00000 n 0000020383 00000 n 0000023649 00000 n 0000205443 00000 n 0000026831 00000 n 0000023800 00000 n 0000023844 00000 n 0000023888 00000 n 0000026741 00000 n 0000205551 00000 n 0000028583 00000 n 0000026895 00000 n 0000026939 00000 n 0000028504 00000 n 0000205755 00000 n 0000030999 00000 n 0000028647 00000 n 0000028691 00000 n 0000028735 00000 n 0000030909 00000 n 0000205863 00000 n 0000032556 00000 n 0000031063 00000 n 0000031107 00000 n 0000032511 00000 n 0000205971 00000 n 0000033609 00000 n 0000032620 00000 n 0000032664 00000 n 0000033564 00000 n 0000206079 00000 n 0000034843 00000 n 0000033673 00000 n 0000033717 00000 n 0000034798 00000 n 0000206187 00000 n 0000037150 00000 n 0000034907 00000 n 0000034951 00000 n 0000034995 00000 n 0000037060 00000 n 0000206477 00000 n 0000039273 00000 n 0000037214 00000 n 0000037258 00000 n 0000037302 00000 n 0000037346 00000 n 0000039183 00000 n 0000206585 00000 n 0000040780 00000 n 0000039337 00000 n 0000039381 00000 n 0000040735 00000 n 0000206693 00000 n 0000042141 00000 n 0000040844 00000 n 0000040888 00000 n 0000042096 00000 n 0000206801 00000 n 0000043483 00000 n 0000042205 00000 n 0000042249 00000 n 0000043438 00000 n 0000206909 00000 n 0000044695 00000 n 0000043547 00000 n 0000043591 00000 n 0000044650 00000 n 0000207199 00000 n 0000045999 00000 n 0000044759 00000 n 0000044803 00000 n 0000045954 00000 n 0000207307 00000 n 0000047162 00000 n 0000046063 00000 n 0000046107 00000 n 0000047117 00000 n 0000207415 00000 n 0000048458 00000 n 0000047226 00000 n 0000047270 00000 n 0000048413 00000 n 0000207523 00000 n 0000049700 00000 n 0000048522 00000 n 0000048566 00000 n 0000049655 00000 n 0000207631 00000 n 0000050817 00000 n 0000049764 00000 n 0000049808 00000 n 0000050772 00000 n 0000208019 00000 n 0000051937 00000 n 0000050881 00000 n 0000050925 00000 n 0000051892 00000 n 0000208127 00000 n 0000053040 00000 n 0000052001 00000 n 0000052045 00000 n 0000052995 00000 n 0000208235 00000 n 0000054175 00000 n 0000053104 00000 n 0000053148 00000 n 0000054130 00000 n 0000208343 00000 n 0000055419 00000 n 0000054239 00000 n 0000054283 00000 n 0000055374 00000 n 0000208550 00000 n 0000056756 00000 n 0000055483 00000 n 0000055527 00000 n 0000056711 00000 n 0000208658 00000 n 0000058043 00000 n 0000056820 00000 n 0000056864 00000 n 0000057998 00000 n 0000208766 00000 n 0000059331 00000 n 0000058107 00000 n 0000058151 00000 n 0000059286 00000 n 0000208874 00000 n 0000060643 00000 n 0000059395 00000 n 0000059439 00000 n 0000060598 00000 n 0000208982 00000 n 0000061871 00000 n 0000060707 00000 n 0000060751 00000 n 0000061826 00000 n 0000209272 00000 n 0000063021 00000 n 0000061935 00000 n 0000061979 00000 n 0000062976 00000 n 0000209380 00000 n 0000064212 00000 n 0000063085 00000 n 0000063129 00000 n 0000064167 00000 n 0000209488 00000 n 0000065416 00000 n 0000064276 00000 n 0000064320 00000 n 0000065371 00000 n 0000209596 00000 n 0000066620 00000 n 0000065480 00000 n 0000065524 00000 n 0000066575 00000 n 0000209704 00000 n 0000067980 00000 n 0000066684 00000 n 0000066728 00000 n 0000067935 00000 n 0000209994 00000 n 0000069065 00000 n 0000068044 00000 n 0000068088 00000 n 0000069020 00000 n 0000210102 00000 n 0000070016 00000 n 0000069129 00000 n 0000069173 00000 n 0000069971 00000 n 0000210210 00000 n 0000071100 00000 n 0000070080 00000 n 0000070124 00000 n 0000071055 00000 n 0000210318 00000 n 0000072337 00000 n 0000071164 00000 n 0000071208 00000 n 0000072292 00000 n 0000210426 00000 n 0000073538 00000 n 0000072401 00000 n 0000072445 00000 n 0000073493 00000 n 0000210814 00000 n 0000074663 00000 n 0000073602 00000 n 0000073646 00000 n 0000074618 00000 n 0000210922 00000 n 0000075727 00000 n 0000074727 00000 n 0000074771 00000 n 0000075682 00000 n 0000211030 00000 n 0000076901 00000 n 0000075791 00000 n 0000075835 00000 n 0000076856 00000 n 0000211138 00000 n 0000077965 00000 n 0000076965 00000 n 0000077009 00000 n 0000077920 00000 n 0000211345 00000 n 0000078931 00000 n 0000078029 00000 n 0000078073 00000 n 0000078886 00000 n 0000211453 00000 n 0000080197 00000 n 0000078995 00000 n 0000079039 00000 n 0000080152 00000 n 0000211561 00000 n 0000081108 00000 n 0000080261 00000 n 0000080305 00000 n 0000081063 00000 n 0000211669 00000 n 0000082338 00000 n 0000081172 00000 n 0000081216 00000 n 0000082293 00000 n 0000211777 00000 n 0000083818 00000 n 0000082402 00000 n 0000082446 00000 n 0000083773 00000 n 0000212067 00000 n 0000085200 00000 n 0000083882 00000 n 0000083926 00000 n 0000085155 00000 n 0000212175 00000 n 0000086475 00000 n 0000085264 00000 n 0000085308 00000 n 0000086430 00000 n 0000212283 00000 n 0000087842 00000 n 0000086539 00000 n 0000086583 00000 n 0000087797 00000 n 0000212391 00000 n 0000088869 00000 n 0000087906 00000 n 0000087950 00000 n 0000088824 00000 n 0000212499 00000 n 0000089910 00000 n 0000088933 00000 n 0000088977 00000 n 0000089865 00000 n 0000212789 00000 n 0000090782 00000 n 0000089974 00000 n 0000090018 00000 n 0000090737 00000 n 0000212897 00000 n 0000091944 00000 n 0000090846 00000 n 0000090890 00000 n 0000091899 00000 n 0000213005 00000 n 0000093329 00000 n 0000092008 00000 n 0000092052 00000 n 0000093284 00000 n 0000213113 00000 n 0000094547 00000 n 0000093393 00000 n 0000093437 00000 n 0000094502 00000 n 0000213221 00000 n 0000096063 00000 n 0000094611 00000 n 0000094655 00000 n 0000096018 00000 n 0000213609 00000 n 0000097681 00000 n 0000096127 00000 n 0000096171 00000 n 0000096214 00000 n 0000097591 00000 n 0000213717 00000 n 0000099285 00000 n 0000097745 00000 n 0000097789 00000 n 0000097830 00000 n 0000097874 00000 n 0000099195 00000 n 0000213825 00000 n 0000101740 00000 n 0000099349 00000 n 0000099393 00000 n 0000099436 00000 n 0000099480 00000 n 0000099523 00000 n 0000101673 00000 n 0000213933 00000 n 0000103143 00000 n 0000101804 00000 n 0000101848 00000 n 0000103075 00000 n 0000214140 00000 n 0000105205 00000 n 0000103207 00000 n 0000103251 00000 n 0000103295 00000 n 0000103339 00000 n 0000103383 00000 n 0000105115 00000 n 0000214248 00000 n 0000106726 00000 n 0000105269 00000 n 0000105313 00000 n 0000105357 00000 n 0000106636 00000 n 0000214356 00000 n 0000108182 00000 n 0000106790 00000 n 0000106834 00000 n 0000108137 00000 n 0000214464 00000 n 0000109809 00000 n 0000108246 00000 n 0000108290 00000 n 0000109764 00000 n 0000214572 00000 n 0000111368 00000 n 0000109873 00000 n 0000109917 00000 n 0000111323 00000 n 0000214862 00000 n 0000112814 00000 n 0000111432 00000 n 0000111476 00000 n 0000112769 00000 n 0000214970 00000 n 0000114470 00000 n 0000112878 00000 n 0000112922 00000 n 0000112966 00000 n 0000114380 00000 n 0000215078 00000 n 0000115663 00000 n 0000114534 00000 n 0000114578 00000 n 0000115618 00000 n 0000215186 00000 n 0000116830 00000 n 0000115727 00000 n 0000115771 00000 n 0000116785 00000 n 0000215294 00000 n 0000118111 00000 n 0000116894 00000 n 0000116938 00000 n 0000118066 00000 n 0000215584 00000 n 0000119669 00000 n 0000118175 00000 n 0000118219 00000 n 0000118263 00000 n 0000119579 00000 n 0000215692 00000 n 0000120763 00000 n 0000119733 00000 n 0000119777 00000 n 0000120718 00000 n 0000215800 00000 n 0000121758 00000 n 0000120827 00000 n 0000120871 00000 n 0000121713 00000 n 0000215908 00000 n 0000122915 00000 n 0000121822 00000 n 0000121866 00000 n 0000122870 00000 n 0000216016 00000 n 0000123624 00000 n 0000122979 00000 n 0000123023 00000 n 0000123567 00000 n 0000207921 00000 n 0000205659 00000 n 0000206378 00000 n 0000206295 00000 n 0000207100 00000 n 0000207017 00000 n 0000207822 00000 n 0000207739 00000 n 0000210716 00000 n 0000208451 00000 n 0000209173 00000 n 0000209090 00000 n 0000209895 00000 n 0000209812 00000 n 0000210617 00000 n 0000210534 00000 n 0000213511 00000 n 0000211246 00000 n 0000211968 00000 n 0000211885 00000 n 0000212690 00000 n 0000212607 00000 n 0000213412 00000 n 0000213329 00000 n 0000216306 00000 n 0000214041 00000 n 0000214763 00000 n 0000214680 00000 n 0000215485 00000 n 0000215402 00000 n 0000216207 00000 n 0000216124 00000 n 0000217081 00000 n 0000217163 00000 n 0000217253 00000 n 0000217330 00000 n 0000217424 00000 n 0000217516 00000 n 0000217593 00000 n 0000217687 00000 n 0000217764 00000 n 0000217858 00000 n 0000217948 00000 n 0000218021 00000 n 0000218115 00000 n 0000218192 00000 n 0000218286 00000 n 0000218375 00000 n 0000218452 00000 n 0000218546 00000 n 0000218640 00000 n 0000218732 00000 n 0000218822 00000 n 0000218914 00000 n 0000218991 00000 n 0000219085 00000 n 0000219162 00000 n 0000219256 00000 n 0000219346 00000 n 0000219423 00000 n 0000219517 00000 n 0000219591 00000 n 0000219685 00000 n 0000219775 00000 n 0000219852 00000 n 0000219946 00000 n 0000220023 00000 n 0000220117 00000 n 0000220207 00000 n 0000220284 00000 n 0000220376 00000 n 0000220470 00000 n 0000220564 00000 n 0000220654 00000 n 0000220744 00000 n 0000220821 00000 n 0000220915 00000 n 0000220992 00000 n 0000221086 00000 n 0000221176 00000 n 0000221250 00000 n 0000221344 00000 n 0000221421 00000 n 0000221515 00000 n 0000221604 00000 n 0000221681 00000 n 0000221775 00000 n 0000221852 00000 n 0000221944 00000 n 0000222033 00000 n 0000222110 00000 n 0000222204 00000 n 0000222298 00000 n 0000222392 00000 n 0000222482 00000 n 0000222572 00000 n 0000222646 00000 n 0000222743 00000 n 0000222828 00000 n 0000222932 00000 n 0000223024 00000 n 0000223106 00000 n 0000223212 00000 n 0000223294 00000 n 0000223396 00000 n 0000223490 00000 n 0000223573 00000 n 0000223675 00000 n 0000223758 00000 n 0000223872 00000 n 0000223972 00000 n 0000224073 00000 n 0000224199 00000 n 0000224325 00000 n 0000224447 00000 n 0000224552 00000 n 0000224648 00000 n 0000224747 00000 n 0000224769 00000 n trailer << /Size 606 /Root 2 0 R /Info 1 0 R >> startxref 226310 %%EOF ./CBFlib-0.9.2.2/pycbf/pycbf.out0000644000076500007650000000250211603702120014530 0ustar yayayaya\BOOKMARK [1][-]{section.1}{1 Introduction}{} \BOOKMARK [1][-]{section.2}{2 Installation prerequisites}{} \BOOKMARK [1][-]{section.3}{3 Generating the c interface - the SWIG file}{} \BOOKMARK [2][-]{subsection.3.1}{3.1 Exceptions}{section.3} \BOOKMARK [2][-]{subsection.3.2}{3.2 Exceptions}{section.3} \BOOKMARK [1][-]{section.4}{4 Docstrings}{} \BOOKMARK [1][-]{section.5}{5 Wrappers}{} \BOOKMARK [1][-]{section.6}{6 Building python extensions - the setup file}{} \BOOKMARK [1][-]{section.7}{7 Building and testing the resulting package}{} \BOOKMARK [1][-]{section.8}{8 Debugging compiled extensions}{} \BOOKMARK [1][-]{section.9}{9 Things which are currently missing}{} \BOOKMARK [1][-]{section.10}{10 Testing}{} \BOOKMARK [2][-]{subsection.10.1}{10.1 Read a file based on cif2cbf.c}{section.10} \BOOKMARK [2][-]{subsection.10.2}{10.2 Try to test the goniometer and detector}{section.10} \BOOKMARK [2][-]{subsection.10.3}{10.3 Test cases for the generics}{section.10} \BOOKMARK [1][-]{section.11}{11 Worked example 1 : xmas beamline + mar ccd detector at the ESRF}{} \BOOKMARK [2][-]{subsection.11.1}{11.1 Reading marccd headers}{section.11} \BOOKMARK [2][-]{subsection.11.2}{11.2 Writing out cif files for fit2d/xmas}{section.11} \BOOKMARK [2][-]{subsection.11.3}{11.3 A template cif file for the xmas beamline}{section.11} ./CBFlib-0.9.2.2/pycbf/pycbf.tex0000644000076500007650000101230511603702120014524 0ustar yayayaya\newcommand{\NWtarget}[2]{#2} \newcommand{\NWlink}[2]{#2} \newcommand{\NWtxtMacroDefBy}{Macro defined by} \newcommand{\NWtxtMacroRefIn}{Macro referenced in} \newcommand{\NWtxtMacroNoRef}{Macro never referenced} \newcommand{\NWtxtDefBy}{Defined by} \newcommand{\NWtxtRefIn}{Referenced in} \newcommand{\NWtxtNoRef}{Not referenced} \newcommand{\NWtxtFileDefBy}{File defined by} \newcommand{\NWsep}{${\diamond}$} % pycbf.w % nuweb source file used to create pycbf documentation % % pycbf - python binding to the CBFlib library % % Copyright (C) 2005 Jonathan Wright % ESRF, Grenoble, France % email: wright@esrf.fr % % Revised for CBFlib 0.9 releases, Herbert J. Bernstein, 23 Aug 2010 % %###################################################################### %# # %# YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE INCLUDING PYCBF UNDER THE # %# TERMS OF THE GPL # %# # %# ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API INCLUDING PYCBF # %# UNDER THE TERMS OF THE LGPL # %# # %###################################################################### % %########################### GPL NOTICES ############################## %# # %# This program is free software; you can redistribute it and/or # %# modify it under the terms of the GNU General Public License as # %# published by the Free Software Foundation; either version 2 of # %# (the License, or (at your option) any later version. # %# # %# This program is distributed in the hope that it will be useful, # %# but WITHOUT ANY WARRANTY; without even the implied warranty of # %# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # %# GNU General Public License for more details. # %# # %# You should have received a copy of the GNU General Public License # %# along with this program; if not, write to the Free Software # %# Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA # %# 02111-1307 USA # %# # %###################################################################### % %######################### LGPL NOTICES ############################### %# # %# This library is free software; you can redistribute it and/or # %# modify it under the terms of the GNU Lesser General Public # %# License as published by the Free Software Foundation; either # %# version 2.1 of the License, or (at your option) any later version. # %# # %# This library is distributed in the hope that it will be useful, # %# but WITHOUT ANY WARRANTY; without even the implied warranty of # %# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # %# Lesser General Public License for more details. # %# # %# You should have received a copy of the GNU Lesser General Public # %# License along with this library; if not, write to the Free # %# Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, # %# MA 02110-1301 USA # %# # %###################################################################### % % Nuweb formatted latex file % Most of this is standard latex with code rolled in % Anything to do with @ characters is probably specific to nuweb % % % The word FIXME anywhere in this document indicates % an area where more attention is still needed. % % Note that this file (pycbf.w) does not copy and paste from CBFlib % (or anywhere) except in the hand wrapped function prototypes. % % % \documentclass[10pt,a4paper,twoside,notitlepage]{article} \usepackage{graphics} % For the pictures \usepackage{anysize} % Try to circumvent Latex default margins \usepackage{fancyhdr} \usepackage[dvipdfm,bookmarks=true,backref,bookmarksnumbered=true, bookmarkstype=toc]{hyperref} \newcommand{\var}[1]{\textbf{\textsf{#1}}} % highlight variables in text \newcommand{\code}[1]{\textbf{\textsf{#1}}} % highlight code in text \newcommand{\param}[1]{\textbf{\textsf{#1}}} % ... parameters ... \newcommand{\mb} [1] {\mathbf{#1}} \begin{document} \marginsize{1.5cm}{1.5cm}{1.5cm}{1.5cm} % Needs anysize %\pagestyle{headings} % These are ugly - fix them somehow? \pagestyle{fancy} %$\renewcommand{\chaptermark}[1]{ %$ \markboth{\chaptername %$ \ \thechapter.\ #1} {} } \renewcommand{\sectionmark}[1]{ \markright { \ \thesection.\ #1} {} } \fancyhead[LE,RO]{\rightmark} \fancyhead[LO,RE]{\leftmark} \fancyfoot[C]{\today} \fancyfoot[LE,RO]{\thepage} \fancyfoot[LO,RE]{J. P. Wright} \renewcommand{\footrulewidth}{0.4pt} \pagenumbering{arabic} % Page numbers \title{\textbf{\textsf{PyCBF}} \\ A python binding to the CBFlib library} \author{Jon P. Wright \\ Anyone who wishes to contribute, please do!} \date{Started Dec 12, 2005, already it is \today} \maketitle \abstract{ Area detectors at synchrotron facilities can result in huge amounts of data being generated very rapidly. The IUCr (International Union of Crystallography) has devised a standard file format for storing and annotating such data, in order that it might be more easily interchanged and exploited. A c library which gives access to this file format has been developed by Paul Ellis and Herbert Bernstein (Version 0.7.4, http://www.bernstein-plus-sons.com/software/CBF/). In this document a python interface is developed using the SWIG (http://www.swig.org) package in order to give the author easy access to binary cif files. } \tableofcontents \markboth{}{} \section*{Index of file names} {\small\begin{list}{}{\setlength{\itemsep}{-\parsep}\setlength{\itemindent}{-\leftmargin}} \item \verb@"linux.sh"@ {\footnotesize {\NWtxtDefBy} \NWlink{nuweb59b}{59b}.} \item \verb@"makeflatascii.py"@ {\footnotesize {\NWtxtDefBy} \NWlink{nuweb59c}{59c}.} \item \verb@"make_pycbf.py"@ {\footnotesize {\NWtxtDefBy} \NWlink{nuweb10}{10}.} \item \verb@"pycbf.i"@ {\footnotesize {\NWtxtDefBy} \NWlink{nuweb5b}{5b}\NWlink{nuweb9}{, 9}. } \item \verb@"pycbf_test1.py"@ {\footnotesize {\NWtxtDefBy} \NWlink{nuweb61}{61}.} \item \verb@"pycbf_test2.py"@ {\footnotesize {\NWtxtDefBy} \NWlink{nuweb62a}{62a}.} \item \verb@"pycbf_test3.py"@ {\footnotesize {\NWtxtDefBy} \NWlink{nuweb62b}{62b}.} \item \verb@"setup.py"@ {\footnotesize {\NWtxtDefBy} \NWlink{nuweb58}{58}.} \item \verb@"win32.bat"@ {\footnotesize {\NWtxtDefBy} \NWlink{nuweb59a}{59a}.} \item \verb@"xmas/readmarheader.py"@ {\footnotesize {\NWtxtDefBy} \NWlink{nuweb63}{63}.} \item \verb@"xmas/xmasheaders.py"@ {\footnotesize {\NWtxtDefBy} \NWlink{nuweb68}{68}.} \item \verb@"xmas/xmas_cif_template.cif"@ {\footnotesize {\NWtxtDefBy} \NWlink{nuweb72}{72}.} \end{list}} \section*{Index of macro names} {\small\begin{list}{}{\setlength{\itemsep}{-\parsep}\setlength{\itemindent}{-\leftmargin}} \item $\langle\,$Constants used for compression\nobreak\ {\footnotesize \NWlink{nuweb3a}{3a}}$\,\rangle$ {\footnotesize {\NWtxtRefIn} \NWlink{nuweb9}{9}.} \item $\langle\,$Constants used for encoding\nobreak\ {\footnotesize \NWlink{nuweb4b}{4b}}$\,\rangle$ {\footnotesize {\NWtxtRefIn} \NWlink{nuweb9}{9}.} \item $\langle\,$Constants used for headers\nobreak\ {\footnotesize \NWlink{nuweb3b}{3b}}$\,\rangle$ {\footnotesize {\NWtxtRefIn} \NWlink{nuweb9}{9}.} \item $\langle\,$Constants used to control CIF parsing\nobreak\ {\footnotesize \NWlink{nuweb4a}{4a}}$\,\rangle$ {\footnotesize {\NWtxtRefIn} \NWlink{nuweb9}{9}.} \item $\langle\,$Exception handling\nobreak\ {\footnotesize \NWlink{nuweb5a}{5a}}$\,\rangle$ {\footnotesize {\NWtxtRefIn} \NWlink{nuweb9}{9}.} \end{list}} \section*{Things to do} \begin{itemize} \item Write test code to test each and every function for good and bad args etc \end{itemize} \section{Introduction} The CBFlib library (version 0.7.4) is written in the C language, offering C (and C++) programmers a convenient interface to such files. The current author uses a different language (python) from day to day and so a python interface was desired. After a short attempt to make a quick and dirty SWIG interface it was decided that in the long run it would be better to write a proper interface for python. All of the functions in the library return an integer reflecting error status. Usually these integers seem to be zero, and a non-zero return value appears to mean an error occurred. Actual return values are returned via pointers in argument lists. In order to simplify the authors life (as a user) all of those integers have been made to disappear if they are zero, and cause an ``exception'' to be generated if they are not zero. This solution might not be the best thing to do, and it can always be changed where the return value is intended to normally be used. Actual return values which were passed back via pointer arguments are now just passed back as (perhaps multiple) return values. We must look out for INOUT arguments, none seem to have been found yet, but there might be exceptions. The author has a vague suspicion that python functions generally do not modify their arguments, but this might be wrong. The library appears to define (at least) three objects. The one we started on was the cbf\_handle\_struct defined in cbf.h. Many of the functions have their first argument as a pointer to one of these structures. Therefore we make this structure an object and then everything which uses it as first argument is a member function for that object. In order to pass image data back and forth there is a difficulty that python seems to lack a good way to represent large arrays. The standard library offers an "array" object which claims to efficiently hold homogenous numerical data. Sadly this seems to be limited to one-dimensional arrays. The builtin string object can hold binary data and this was chosen as the way to pass the actual binary back and forth between python and CBFlib. Unfortunately this means the binary data are pretty useless when they arrive on the python side, so helper functions are provided to convert the data to a python (standard library) 1D array and also to a "Numeric" array or a "Numarray" array. The latter two are popular extension modules for manipulating large arrays. \section{Installation prerequisites} The document you are reading was generated from a nuweb source file. This is something very similar to latex with a few extensions for writing out source code files. As such it keeps together the whole package in a single file and makes it easier to write documentation. You will need a to obtain the preprocessing tool nuweb (perhaps from http://nuweb.sourceforge.net) in order to build from scratch with the file pycbf.w. Preproccessed output is hopefully also available to you. We do not recommend editing the SWIG generated wrappers!! Only python version 2.4 has been targetted originally (other versions?) so that you will probably want to have that version of python installed. We are building binary extensions, so you also need a working c compiler. The compiler used by the author was gcc (for both windows and unix) with the mingw version under windows. Finally, you need a copy of swig (from www.swig.org) in order to (re)generate the c wrappers. In case all that sounds scary, then fear not, it is likely that a single download for windows will just work with the right version of python. Unix systems come with many of those things available anyway. % pycbf_i.w % nuweb source file used to create % pycbf.i and to document it in pycbf.w % % pycbf - python binding to the CBFlib library % % Copyright (C) 2005 Jonathan Wright % ESRF, Grenoble, France % email: wright@esrf.fr % % Revised for CBFlib 0.9 releases, Herbert J. Bernstein, 23 Aug 2010 % %###################################################################### %# # %# YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE INCLUDING PYCBF UNDER THE # %# TERMS OF THE GPL # %# # %# ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API INCLUDING PYCBF # %# UNDER THE TERMS OF THE LGPL # %# # %###################################################################### % %########################### GPL NOTICES ############################## %# # %# This program is free software; you can redistribute it and/or # %# modify it under the terms of the GNU General Public License as # %# published by the Free Software Foundation; either version 2 of # %# (the License, or (at your option) any later version. # %# # %# This program is distributed in the hope that it will be useful, # %# but WITHOUT ANY WARRANTY; without even the implied warranty of # %# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # %# GNU General Public License for more details. # %# # %# You should have received a copy of the GNU General Public License # %# along with this program; if not, write to the Free Software # %# Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA # %# 02111-1307 USA # %# # %###################################################################### % %######################### LGPL NOTICES ############################### %# # %# This library is free software; you can redistribute it and/or # %# modify it under the terms of the GNU Lesser General Public # %# License as published by the Free Software Foundation; either # %# version 2.1 of the License, or (at your option) any later version. # %# # %# This library is distributed in the hope that it will be useful, # %# but WITHOUT ANY WARRANTY; without even the implied warranty of # %# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # %# Lesser General Public License for more details. # %# # %# You should have received a copy of the GNU Lesser General Public # %# License along with this library; if not, write to the Free # %# Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, # %# MA 02110-1301 USA # %# # %###################################################################### % \section{Generating the c interface - the SWIG file} Essentially the swig file starts by saying what to include to build the wrappers, and then goes on to define the python interface for each function we want to call. The library appears to define at least three ``objects''; a CBF handle, a cbf\_goniometer and a cbf\_detector. We will attempt to map these onto python classes. FIXME - decide whether introduce a "binary array" class with converters to more common representations? All of the functions in the library appear to return 0 on success and a meaningful error code on failure. We try to propagate that error code across the language barrier via exceptions. So the SWIG file will start off by including the header files needed for compilation. Note the defintion of constants to be passed as arguments in calls in the form pycbf.CONSTANTNAME \begin{flushleft} \small \label{scrap1} $\langle\,$Constants used for compression\nobreak\ {\footnotesize \NWtarget{nuweb3a}{3a}}$\,\rangle\equiv$ \vspace{-1ex} \begin{list}{}{} \item \mbox{}\verb@@\\ \mbox{}\verb@// The actual wrappers @\\ \mbox{}\verb@@\\ \mbox{}\verb@// Constants needed from header files@\\ \mbox{}\verb@@\\ \mbox{}\verb@ /* Constants used for compression */@\\ \mbox{}\verb@@\\ \mbox{}\verb@#define CBF_INTEGER 0x0010 /* Uncompressed integer */@\\ \mbox{}\verb@#define CBF_FLOAT 0x0020 /* Uncompressed IEEE floating-point */@\\ \mbox{}\verb@#define CBF_CANONICAL 0x0050 /* Canonical compression */@\\ \mbox{}\verb@#define CBF_PACKED 0x0060 /* Packed compression */@\\ \mbox{}\verb@#define CBF_PACKED_V2 0x0090 /* CCP4 Packed (JPA) compression V2 */@\\ \mbox{}\verb@#define CBF_BYTE_OFFSET 0x0070 /* Byte Offset Compression */@\\ \mbox{}\verb@#define CBF_PREDICTOR 0x0080 /* Predictor_Huffman Compression */@\\ \mbox{}\verb@#define CBF_NONE 0x0040 /* No compression flag */@\\ \mbox{}\verb@#define CBF_COMPRESSION_MASK \@\\ \mbox{}\verb@ 0x00FF /* Mask to separate compression@\\ \mbox{}\verb@ type from flags */@\\ \mbox{}\verb@#define CBF_FLAG_MASK 0x0F00 /* Mask to separate flags from@\\ \mbox{}\verb@ compression type */@\\ \mbox{}\verb@#define CBF_UNCORRELATED_SECTIONS \@\\ \mbox{}\verb@ 0x0100 /* Flag for uncorrelated sections */@\\ \mbox{}\verb@#define CBF_FLAT_IMAGE 0x0200 /* Flag for flat (linear) images */@\\ \mbox{}\verb@#define CBF_NO_EXPAND 0x0400 /* Flag to try not to expand */@\\ \mbox{}\verb@@{\NWsep} \end{list} \vspace{-1ex} \footnotesize\addtolength{\baselineskip}{-1ex} \begin{list}{}{\setlength{\itemsep}{-\parsep}\setlength{\itemindent}{-\leftmargin}} \item \NWtxtMacroRefIn\ \NWlink{nuweb9}{9}. \end{list} \end{flushleft} \begin{flushleft} \small \label{scrap2} $\langle\,$Constants used for headers\nobreak\ {\footnotesize \NWtarget{nuweb3b}{3b}}$\,\rangle\equiv$ \vspace{-1ex} \begin{list}{}{} \item \mbox{}\verb@@\\ \mbox{}\verb@ /* Constants used for headers */@\\ \mbox{}\verb@@\\ \mbox{}\verb@#define PLAIN_HEADERS 0x0001 /* Use plain ASCII headers */@\\ \mbox{}\verb@#define MIME_HEADERS 0x0002 /* Use MIME headers */@\\ \mbox{}\verb@#define MSG_NODIGEST 0x0004 /* Do not check message digests */@\\ \mbox{}\verb@#define MSG_DIGEST 0x0008 /* Check message digests */@\\ \mbox{}\verb@#define MSG_DIGESTNOW 0x0010 /* Check message digests immediately */@\\ \mbox{}\verb@#define MSG_DIGESTWARN 0x0020 /* Warn on message digests immediately*/@\\ \mbox{}\verb@#define PAD_1K 0x0020 /* Pad binaries with 1023 0's */@\\ \mbox{}\verb@#define PAD_2K 0x0040 /* Pad binaries with 2047 0's */@\\ \mbox{}\verb@#define PAD_4K 0x0080 /* Pad binaries with 4095 0's */@\\ \mbox{}\verb@@{\NWsep} \end{list} \vspace{-1ex} \footnotesize\addtolength{\baselineskip}{-1ex} \begin{list}{}{\setlength{\itemsep}{-\parsep}\setlength{\itemindent}{-\leftmargin}} \item \NWtxtMacroRefIn\ \NWlink{nuweb9}{9}. \end{list} \end{flushleft} \begin{flushleft} \small \label{scrap3} $\langle\,$Constants used to control CIF parsing\nobreak\ {\footnotesize \NWtarget{nuweb4a}{4a}}$\,\rangle\equiv$ \vspace{-1ex} \begin{list}{}{} \item \mbox{}\verb@@\\ \mbox{}\verb@ /* Constants used to control CIF parsing */@\\ \mbox{}\verb@ @\\ \mbox{}\verb@#define CBF_PARSE_BRC 0x0100 /* PARSE DDLm/CIF2 brace {,...} */@\\ \mbox{}\verb@#define CBF_PARSE_PRN 0x0200 /* PARSE DDLm parens (,...) */@\\ \mbox{}\verb@#define CBF_PARSE_BKT 0x0400 /* PARSE DDLm brackets [,...] */@\\ \mbox{}\verb@#define CBF_PARSE_BRACKETS \@\\ \mbox{}\verb@ 0x0700 /* PARSE ALL brackets */@\\ \mbox{}\verb@#define CBF_PARSE_TQ 0x0800 /* PARSE treble quotes """...""" and '''...''' */@\\ \mbox{}\verb@#define CBF_PARSE_CIF2_DELIMS \@\\ \mbox{}\verb@ 0x1000 /* Do not scan past an unescaped close quote@\\ \mbox{}\verb@ do not accept {} , : " ' in non-delimited@\\ \mbox{}\verb@ strings'{ */ @\\ \mbox{}\verb@#define CBF_PARSE_DDLm 0x0700 /* For DDLm parse (), [], {} */@\\ \mbox{}\verb@#define CBF_PARSE_CIF2 0x1F00 /* For CIF2 parse {}, treble quotes,@\\ \mbox{}\verb@ stop on unescaped close quotes */@\\ \mbox{}\verb@#define CBF_PARSE_DEFINES \@\\ \mbox{}\verb@ 0x2000 /* Recognize DEFINE_name */ @\\ \mbox{}\verb@ @\\ \mbox{}\verb@ @\\ \mbox{}\verb@#define CBF_PARSE_WIDE 0x4000 /* PARSE wide files */@\\ \mbox{}\verb@@\\ \mbox{}\verb@#define CBF_PARSE_UTF8 0x10000 /* PARSE UTF-8 */@\\ \mbox{}\verb@@\\ \mbox{}\verb@#define HDR_DEFAULT (MIME_HEADERS | MSG_NODIGEST)@\\ \mbox{}\verb@@\\ \mbox{}\verb@#define MIME_NOHEADERS PLAIN_HEADERS@\\ \mbox{}\verb@@\\ \mbox{}\verb@ /* CBF vs CIF */@\\ \mbox{}\verb@@\\ \mbox{}\verb@#define CBF 0x0000 /* Use simple binary sections */@\\ \mbox{}\verb@#define CIF 0x0001 /* Use MIME-encoded binary sections */@\\ \mbox{}\verb@@{\NWsep} \end{list} \vspace{-1ex} \footnotesize\addtolength{\baselineskip}{-1ex} \begin{list}{}{\setlength{\itemsep}{-\parsep}\setlength{\itemindent}{-\leftmargin}} \item \NWtxtMacroRefIn\ \NWlink{nuweb9}{9}. \end{list} \end{flushleft} \begin{flushleft} \small \label{scrap4} $\langle\,$Constants used for encoding\nobreak\ {\footnotesize \NWtarget{nuweb4b}{4b}}$\,\rangle\equiv$ \vspace{-1ex} \begin{list}{}{} \item \mbox{}\verb@@\\ \mbox{}\verb@ /* Constants used for encoding */@\\ \mbox{}\verb@@\\ \mbox{}\verb@#define ENC_NONE 0x0001 /* Use BINARY encoding */@\\ \mbox{}\verb@#define ENC_BASE64 0x0002 /* Use BASE64 encoding */@\\ \mbox{}\verb@#define ENC_BASE32K 0x0004 /* Use X-BASE32K encoding */@\\ \mbox{}\verb@#define ENC_QP 0x0008 /* Use QUOTED-PRINTABLE encoding */@\\ \mbox{}\verb@#define ENC_BASE10 0x0010 /* Use BASE10 encoding */@\\ \mbox{}\verb@#define ENC_BASE16 0x0020 /* Use BASE16 encoding */@\\ \mbox{}\verb@#define ENC_BASE8 0x0040 /* Use BASE8 encoding */@\\ \mbox{}\verb@#define ENC_FORWARD 0x0080 /* Map bytes to words forward (1234) */@\\ \mbox{}\verb@#define ENC_BACKWARD 0x0100 /* Map bytes to words backward (4321) */@\\ \mbox{}\verb@#define ENC_CRTERM 0x0200 /* Terminate lines with CR */@\\ \mbox{}\verb@#define ENC_LFTERM 0x0400 /* Terminate lines with LF */@\\ \mbox{}\verb@@\\ \mbox{}\verb@#define ENC_DEFAULT (ENC_BASE64 | ENC_LFTERM | ENC_FORWARD)@\\ \mbox{}\verb@@{\NWsep} \end{list} \vspace{-1ex} \footnotesize\addtolength{\baselineskip}{-1ex} \begin{list}{}{\setlength{\itemsep}{-\parsep}\setlength{\itemindent}{-\leftmargin}} \item \NWtxtMacroRefIn\ \NWlink{nuweb9}{9}. \end{list} \end{flushleft} \subsection{Exceptions} We attempt to catch the errors and pass them back to python as exceptions. This could still do with a little work to propagage back the calls causing the errors. Currently there are two global constants defined, called error\_message and error\_status. These are filled out when an error occurred, converting the numerical error value into something the author can read. There is an implicit assumption that if the library is used correctly you will not normally get exceptions. This should be addressed further in areas like file opening, proper python exceptions should be returned. See the section on exception handling in pycbf.i, above. Currently you get a meaningful string back. Should perhaps look into defining these as python exception classes? In any case - the SWIG exception handling is defined via the following. It could have retained the old style if(status = action) but then harder to see what to return... \begin{flushleft} \small \label{scrap5} $\langle\,$Exception handling\nobreak\ {\footnotesize \NWtarget{nuweb5a}{5a}}$\,\rangle\equiv$ \vspace{-1ex} \begin{list}{}{} \item \mbox{}\verb@@\\ \mbox{}\verb@// Exception handling@\\ \mbox{}\verb@@\\ \mbox{}\verb@ /* Convenience definitions for functions returning error codes */@\\ \mbox{}\verb@%exception {@\\ \mbox{}\verb@ error_status=0;@\\ \mbox{}\verb@ $action@\\ \mbox{}\verb@ if (error_status){@\\ \mbox{}\verb@ get_error_message();@\\ \mbox{}\verb@ PyErr_SetString(PyExc_Exception,error_message);@\\ \mbox{}\verb@ return NULL;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@}@\\ \mbox{}\verb@@\\ \mbox{}\verb@/* Retain notation from cbf lib but pass on as python exception */@\\ \mbox{}\verb@@\\ \mbox{}\verb@#define cbf_failnez(x) {(error_status = x);} @\\ \mbox{}\verb@@\\ \mbox{}\verb@/* printf("Called \"x\", status %d\n",error_status);} */@\\ \mbox{}\verb@@\\ \mbox{}\verb@#define cbf_onfailnez(x,c) {int err; err = (x); if (err) { fprintf (stderr, \@\\ \mbox{}\verb@ "\nCBFlib error %d in \"x\"\n", err); \@\\ \mbox{}\verb@ { c; } return err; }}@\\ \mbox{}\verb@@{\NWsep} \end{list} \vspace{-1ex} \footnotesize\addtolength{\baselineskip}{-1ex} \begin{list}{}{\setlength{\itemsep}{-\parsep}\setlength{\itemindent}{-\leftmargin}} \item \NWtxtMacroRefIn\ \NWlink{nuweb9}{9}. \end{list} \end{flushleft} \begin{flushleft} \small \label{scrap6} \verb@"pycbf.i"@\nobreak\ {\footnotesize \NWtarget{nuweb5b}{5b} }$\equiv$ \vspace{-1ex} \begin{list}{}{} \item \mbox{}\verb@@\\ \mbox{}\verb@/* File: pycbf.i */@\\ \mbox{}\verb@@\\ \mbox{}\verb@// Indicate that we want to generate a module call pycbf@\\ \mbox{}\verb@%module pycbf@\\ \mbox{}\verb@@\\ \mbox{}\verb@%pythoncode %{@\\ \mbox{}\verb@__author__ = "Jon Wright "@\\ \mbox{}\verb@__date__ = "14 Dec 2005"@\\ \mbox{}\verb@__version__ = "CBFlib 0.9"@\\ \mbox{}\verb@__credits__ = """Paul Ellis and Herbert Bernstein for the excellent CBFlib!"""@\\ \mbox{}\verb@__doc__=""" pycbf - python bindings to the CBFlib library@\\ \mbox{}\verb@@\\ \mbox{}\verb@ A library for reading and writing ImageCIF and CBF files @\\ \mbox{}\verb@ which store area detector images for crystallography.@\\ \mbox{}\verb@@\\ \mbox{}\verb@ This work is a derivative of the CBFlib version 0.7.7 library@\\ \mbox{}\verb@ by Paul J. Ellis of Stanford Synchrotron Radiation Laboratory@\\ \mbox{}\verb@ and Herbert J. Bernstein of Bernstein + Sons@\\ \mbox{}\verb@ See:@\\ \mbox{}\verb@ http://www.bernstein-plus-sons.com/software/CBF/@\\ \mbox{}\verb@@\\ \mbox{}\verb@ Licensing is GPL based, see:@\\ \mbox{}\verb@ http://www.bernstein-plus-sons.com/software/CBF/doc/CBFlib_NOTICES.html@\\ \mbox{}\verb@@\\ \mbox{}\verb@ These bindings were automatically generated by SWIG, and the@\\ \mbox{}\verb@ input to SWIG was automatically generated by a python script.@\\ \mbox{}\verb@ We very strongly recommend you do not attempt to edit them @\\ \mbox{}\verb@ by hand!@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@ Copyright (C) 2007 Jonathan Wright@\\ \mbox{}\verb@ ESRF, Grenoble, France@\\ \mbox{}\verb@ email: wright@{\tt @}\verb@esrf.fr@\\ \mbox{}\verb@ @\\ \mbox{}\verb@ Revised, August 2010 Herbert J. Bernstein@\\ \mbox{}\verb@ Add defines from CBFlib 0.9.1@\\ \mbox{}\verb@ @\\ \mbox{}\verb@"""@\\ \mbox{}\verb@%}@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@// Used later to pass back binary data@\\ \mbox{}\verb@%include "cstring.i"@\\ \mbox{}\verb@@\\ \mbox{}\verb@// Attempt to autogenerate what SWIG thinks the call looks like@\\ \mbox{}\verb@@\\ \mbox{}\verb@// Typemaps are a SWIG mechanism for many things, not least multiple @\\ \mbox{}\verb@// return values@\\ \mbox{}\verb@%include "typemaps.i"@\\ \mbox{}\verb@@\\ \mbox{}\verb@// Arrays are needed@\\ \mbox{}\verb@%include "carrays.i"@\\ \mbox{}\verb@%array_class(double, doubleArray)@\\ \mbox{}\verb@%array_class(int, intArray)@\\ \mbox{}\verb@%array_class(short, shortArray)@\\ \mbox{}\verb@%array_class(long, longArray)@\\ \mbox{}\verb@@\\ \mbox{}\verb@// Following the SWIG 1.3 documentation at@\\ \mbox{}\verb@// http://www.swig.org/Doc1.3/Python.html@\\ \mbox{}\verb@// section 31.9.5, we map sequences of@\\ \mbox{}\verb@// PyFloat, PyLong and PyInt to@\\ \mbox{}\verb@// C arrays of double, long and int@\\ \mbox{}\verb@//@\\ \mbox{}\verb@// But with the strict checking of being a float@\\ \mbox{}\verb@// commented out to allow automatic conversions@\\ \mbox{}\verb@%{@\\ \mbox{}\verb@static int convert_darray(PyObject *input, double *ptr, int size) {@\\ \mbox{}\verb@ int i;@\\ \mbox{}\verb@ if (!PySequence_Check(input)) {@\\ \mbox{}\verb@ PyErr_SetString(PyExc_TypeError,"Expecting a sequence");@\\ \mbox{}\verb@ return 0;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ if (PyObject_Length(input) != size) {@\\ \mbox{}\verb@ PyErr_SetString(PyExc_ValueError,"Sequence size mismatch");@\\ \mbox{}\verb@ return 0;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ for (i =0; i < size; i++) {@\\ \mbox{}\verb@ PyObject *o = PySequence_GetItem(input,i);@\\ \mbox{}\verb@ /*if (!PyFloat_Check(o)) {@\\ \mbox{}\verb@ @\\ \mbox{}\verb@ Py_XDECREF(o);@\\ \mbox{}\verb@ PyErr_SetString(PyExc_ValueError,"Expecting a sequence of floats");@\\ \mbox{}\verb@ return 0;@\\ \mbox{}\verb@ }*/@\\ \mbox{}\verb@ ptr[i] = PyFloat_AsDouble(o);@\\ \mbox{}\verb@ Py_DECREF(o);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ return 1;@\\ \mbox{}\verb@}@\\ \mbox{}\verb@%}@\\ \mbox{}\verb@@\\ \mbox{}\verb@%typemap(in) double [ANY](double temp[$1_dim0]) {@\\ \mbox{}\verb@ if ($input == Py_None) $1 = NULL;@\\ \mbox{}\verb@ else @\\ \mbox{}\verb@ if (!convert_darray($input,temp,$1_dim0)) {@\\ \mbox{}\verb@ return NULL;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ $1 = &temp[0];@\\ \mbox{}\verb@}@\\ \mbox{}\verb@@\\ \mbox{}\verb@%{@\\ \mbox{}\verb@ static long convert_larray(PyObject *input, long *ptr, int size) {@\\ \mbox{}\verb@ int i;@\\ \mbox{}\verb@ if (!PySequence_Check(input)) {@\\ \mbox{}\verb@ PyErr_SetString(PyExc_TypeError,"Expecting a sequence");@\\ \mbox{}\verb@ return 0;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ if (PyObject_Length(input) != size) {@\\ \mbox{}\verb@ PyErr_SetString(PyExc_ValueError,"Sequence size mismatch");@\\ \mbox{}\verb@ return 0;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ for (i =0; i < size; i++) {@\\ \mbox{}\verb@ PyObject *o = PySequence_GetItem(input,i);@\\ \mbox{}\verb@ /*if (!PyLong_Check(o)) {@\\ \mbox{}\verb@ Py_XDECREF(o);@\\ \mbox{}\verb@ PyErr_SetString(PyExc_ValueError,"Expecting a sequence of long integers");@\\ \mbox{}\verb@ return 0;@\\ \mbox{}\verb@ }*/@\\ \mbox{}\verb@ ptr[i] = PyLong_AsLong(o);@\\ \mbox{}\verb@ Py_DECREF(o);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ return 1;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@%}@\\ \mbox{}\verb@@\\ \mbox{}\verb@%typemap(in) long [ANY](long temp[$1_dim0]) {@\\ \mbox{}\verb@ if (!convert_larray($input,temp,$1_dim0)) {@\\ \mbox{}\verb@ return NULL;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ $1 = &temp[0];@\\ \mbox{}\verb@}@\\ \mbox{}\verb@@\\ \mbox{}\verb@%{@\\ \mbox{}\verb@ static int convert_iarray(PyObject *input, int *ptr, int size) {@\\ \mbox{}\verb@ int i;@\\ \mbox{}\verb@ if (!PySequence_Check(input)) {@\\ \mbox{}\verb@ PyErr_SetString(PyExc_TypeError,"Expecting a sequence");@\\ \mbox{}\verb@ return 0;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ if (PyObject_Length(input) != size) {@\\ \mbox{}\verb@ PyErr_SetString(PyExc_ValueError,"Sequence size mismatch");@\\ \mbox{}\verb@ return 0;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ for (i =0; i < size; i++) {@\\ \mbox{}\verb@ PyObject *o = PySequence_GetItem(input,i);@\\ \mbox{}\verb@ /*if (!PyInt_Check(o)) {@\\ \mbox{}\verb@ Py_XDECREF(o);@\\ \mbox{}\verb@ PyErr_SetString(PyExc_ValueError,"Expecting a sequence of long integers");@\\ \mbox{}\verb@ return 0;@\\ \mbox{}\verb@ }*/@\\ \mbox{}\verb@ ptr[i] = (int)PyInt_AsLong(o);@\\ \mbox{}\verb@ Py_DECREF(o);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ return 1;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@%}@\\ \mbox{}\verb@@\\ \mbox{}\verb@%typemap(in) int [ANY](int temp[$1_dim0]) {@\\ \mbox{}\verb@ if (!convert_iarray($input,temp,$1_dim0)) {@\\ \mbox{}\verb@ return NULL;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ $1 = &temp[0];@\\ \mbox{}\verb@}@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@%{ // Here is the c code needed to compile the wrappers, but not @\\ \mbox{}\verb@ // to be wrapped @\\ \mbox{}\verb@@\\ \mbox{}\verb@#include "../include/cbf.h" @\\ \mbox{}\verb@#include "../include/cbf_simple.h"@\\ \mbox{}\verb@@\\ \mbox{}\verb@// Helper functions to generate error message@\\ \mbox{}\verb@ @\\ \mbox{}\verb@@\\ \mbox{}\verb@static int error_status = 0;@\\ \mbox{}\verb@static char error_message[1024] ; // hope that is long enough@\\ \mbox{}\verb@@\\ \mbox{}\verb@/* prototype */@\\ \mbox{}\verb@void get_error_message(void);@\\ \mbox{}\verb@@\\ \mbox{}\verb@void get_error_message(){@\\ \mbox{}\verb@ sprintf(error_message,"%s","CBFlib Error(s):");@\\ \mbox{}\verb@ if (error_status & CBF_FORMAT )@\\ \mbox{}\verb@ sprintf(error_message,"%s %s",error_message,"CBF_FORMAT "); @\\ \mbox{}\verb@ if (error_status & CBF_ALLOC )@\\ \mbox{}\verb@ sprintf(error_message,"%s %s",error_message,"CBF_ALLOC ");@\\ \mbox{}\verb@ if (error_status & CBF_ARGUMENT )@\\ \mbox{}\verb@ sprintf(error_message,"%s %s",error_message,"CBF_ARGUMENT ");@\\ \mbox{}\verb@ if (error_status & CBF_ASCII )@\\ \mbox{}\verb@ sprintf(error_message,"%s %s",error_message,"CBF_ASCII ");@\\ \mbox{}\verb@ if (error_status & CBF_BINARY )@\\ \mbox{}\verb@ sprintf(error_message,"%s %s",error_message,"CBF_BINARY ");@\\ \mbox{}\verb@ if (error_status & CBF_BITCOUNT )@\\ \mbox{}\verb@ sprintf(error_message,"%s %s",error_message,"CBF_BITCOUNT ");@\\ \mbox{}\verb@ if (error_status & CBF_ENDOFDATA )@\\ \mbox{}\verb@ sprintf(error_message,"%s %s",error_message,"CBF_ENDOFDATA ");@\\ \mbox{}\verb@ if (error_status & CBF_FILECLOSE )@\\ \mbox{}\verb@ sprintf(error_message,"%s %s",error_message,"CBF_FILECLOSE ");@\\ \mbox{}\verb@ if (error_status & CBF_FILEOPEN )@\\ \mbox{}\verb@ sprintf(error_message,"%s %s",error_message,"CBF_FILEOPEN ");@\\ \mbox{}\verb@ if (error_status & CBF_FILEREAD )@\\ \mbox{}\verb@ sprintf(error_message,"%s %s",error_message,"CBF_FILEREAD ");@\\ \mbox{}\verb@ if (error_status & CBF_FILESEEK )@\\ \mbox{}\verb@ sprintf(error_message,"%s %s",error_message,"CBF_FILESEEK ");@\\ \mbox{}\verb@ if (error_status & CBF_FILETELL )@\\ \mbox{}\verb@ sprintf(error_message,"%s %s",error_message,"CBF_FILETELL ");@\\ \mbox{}\verb@ if (error_status & CBF_FILEWRITE )@\\ \mbox{}\verb@ sprintf(error_message,"%s %s",error_message,"CBF_FILEWRITE ");@\\ \mbox{}\verb@ if (error_status & CBF_IDENTICAL )@\\ \mbox{}\verb@ sprintf(error_message,"%s %s",error_message,"CBF_IDENTICAL ");@\\ \mbox{}\verb@ if (error_status & CBF_NOTFOUND )@\\ \mbox{}\verb@ sprintf(error_message,"%s %s",error_message,"CBF_NOTFOUND ");@\\ \mbox{}\verb@ if (error_status & CBF_OVERFLOW )@\\ \mbox{}\verb@ sprintf(error_message,"%s %s",error_message,"CBF_OVERFLOW ");@\\ \mbox{}\verb@ if (error_status & CBF_UNDEFINED )@\\ \mbox{}\verb@ sprintf(error_message,"%s %s",error_message,"CBF_UNDEFINED ");@\\ \mbox{}\verb@ if (error_status & CBF_NOTIMPLEMENTED)@\\ \mbox{}\verb@ sprintf(error_message,"%s %s",error_message,"CBF_NOTIMPLEMENTED");@\\ \mbox{}\verb@ if (error_status & CBF_NOCOMPRESSION)@\\ \mbox{}\verb@ sprintf(error_message,"%s %s",error_message,"CBF_NOCOMPRESSION");@\\ \mbox{}\verb@}@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@%} // End of code which is not wrapped but needed to compile@\\ \mbox{}\verb@@{\NWsep} \end{list} \vspace{-1ex} \footnotesize\addtolength{\baselineskip}{-1ex} \begin{list}{}{\setlength{\itemsep}{-\parsep}\setlength{\itemindent}{-\leftmargin}} \item \NWtxtFileDefBy\ \NWlink{nuweb5b}{5b}\NWlink{nuweb9}{, 9}. \end{list} \end{flushleft} \begin{flushleft} \small \label{scrap7} \verb@"pycbf.i"@\nobreak\ {\footnotesize \NWtarget{nuweb9}{9} }$\equiv$ \vspace{-1ex} \begin{list}{}{} \item \mbox{}\verb@@\\ \mbox{}\verb@@\hbox{$\langle\,$Constants used for compression\nobreak\ {\footnotesize \NWlink{nuweb3a}{3a}}$\,\rangle$}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\hbox{$\langle\,$Constants used for headers\nobreak\ {\footnotesize \NWlink{nuweb3b}{3b}}$\,\rangle$}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\hbox{$\langle\,$Constants used to control CIF parsing\nobreak\ {\footnotesize \NWlink{nuweb4a}{4a}}$\,\rangle$}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\hbox{$\langle\,$Constants used for encoding\nobreak\ {\footnotesize \NWlink{nuweb4b}{4b}}$\,\rangle$}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\hbox{$\langle\,$Exception handling\nobreak\ {\footnotesize \NWlink{nuweb5a}{5a}}$\,\rangle$}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@%include "cbfgenericwrappers.i"@\\ \mbox{}\verb@@\\ \mbox{}\verb@// cbf_goniometer object@\\ \mbox{}\verb@@\\ \mbox{}\verb@%include "cbfgoniometerwrappers.i"@\\ \mbox{}\verb@@\\ \mbox{}\verb@%include "cbfdetectorwrappers.i"@\\ \mbox{}\verb@@\\ \mbox{}\verb@// cbfhandle object@\\ \mbox{}\verb@%include "cbfhandlewrappers.i"@\\ \mbox{}\verb@@\\ \mbox{}\verb@@{\NWsep} \end{list} \vspace{-1ex} \footnotesize\addtolength{\baselineskip}{-1ex} \begin{list}{}{\setlength{\itemsep}{-\parsep}\setlength{\itemindent}{-\leftmargin}} \item \NWtxtFileDefBy\ \NWlink{nuweb5b}{5b}\NWlink{nuweb9}{, 9}. \end{list} \end{flushleft} Despite the temptation to just throw everything from the c header files into the interface, a short experience suggested we are better off to pull out only the parts we want and make the calls more pythonic The input files "CBFhandlewrappers.i", etc. are created by the make\_pycbf.py script. \subsection{Exceptions} We attempt to catch the errors and pass them back to python as exceptions. This could still do with a little work to propagage back the calls causing the errors. Currently there are two global constants defined, called error\_message and error\_status. These are filled out when an error occurred, converting the numerical error value into something the author can read. There is an implicit assumption that if the library is used correctly you will not normally get exceptions. This should be addressed further in areas like file opening, proper python exceptions should be returned. See the section on exception handling in pycbf.i, above. Currently you get a meaningful string back. Should perhaps look into defining these as python exception classes? In any case - the SWIG exception handling is defined via the following. It could have retained the old style if(status = action) but then harder to see what to return... \section{Docstrings} The file doc/CBFlib.html is converted to a file CBFlib.txt to generate the docstrings and many of the wrappers. The conversion was done by the text-based browser, links. This text document is then parsed by a python script called make\_pycbf.py to generate the .i files which are included by the swig wrapper generator. Unfortunately this more complicated for non-python users but seemed less error prone and involved less typing for the author. % make_pycbf.w % nuweb source file used to create % make_pycbf.py and to document it in pycbf.w % % pycbf - python binding to the CBFlib library % % Copyright (C) 2005 Jonathan Wright % ESRF, Grenoble, France % email: wright@esrf.fr % % Revised for CBFlib 0.9 releases, Herbert J. Bernstein, 23 Aug 2010 % %###################################################################### %# # %# YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE INCLUDING PYCBF UNDER THE # %# TERMS OF THE GPL # %# # %# ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API INCLUDING PYCBF # %# UNDER THE TERMS OF THE LGPL # %# # %###################################################################### % %########################### GPL NOTICES ############################## %# # %# This program is free software; you can redistribute it and/or # %# modify it under the terms of the GNU General Public License as # %# published by the Free Software Foundation; either version 2 of # %# (the License, or (at your option) any later version. # %# # %# This program is distributed in the hope that it will be useful, # %# but WITHOUT ANY WARRANTY; without even the implied warranty of # %# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # %# GNU General Public License for more details. # %# # %# You should have received a copy of the GNU General Public License # %# along with this program; if not, write to the Free Software # %# Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA # %# 02111-1307 USA # %# # %###################################################################### % %######################### LGPL NOTICES ############################### %# # %# This library is free software; you can redistribute it and/or # %# modify it under the terms of the GNU Lesser General Public # %# License as published by the Free Software Foundation; either # %# version 2.1 of the License, or (at your option) any later version. # %# # %# This library is distributed in the hope that it will be useful, # %# but WITHOUT ANY WARRANTY; without even the implied warranty of # %# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # %# Lesser General Public License for more details. # %# # %# You should have received a copy of the GNU Lesser General Public # %# License along with this library; if not, write to the Free # %# Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, # %# MA 02110-1301 USA # %# # %###################################################################### % \section{Wrappers} The program that does the conversion from CBFlib.txt to the SWIG input files is a python script named make\_pycbf.py. \begin{flushleft} \small \label{scrap8} \verb@"make_pycbf.py"@\nobreak\ {\footnotesize \NWtarget{nuweb10}{10} }$\equiv$ \vspace{-1ex} \begin{list}{}{} \item \mbox{}\verb@@\\ \mbox{}\verb@print "\\begin{verbatim}"@\\ \mbox{}\verb@print "This output comes from make_pycbf.py which generates the wrappers"@\\ \mbox{}\verb@print "pycbf Copyright (C) 2005 Jonathan Wright, no warranty, LGPL"@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@######################################################################@\\ \mbox{}\verb@# #@\\ \mbox{}\verb@# YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE INCLUDING PYCBF UNDER THE #@\\ \mbox{}\verb@# TERMS OF THE GPL #@\\ \mbox{}\verb@# #@\\ \mbox{}\verb@# ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API INCLUDING PYCBF #@\\ \mbox{}\verb@# UNDER THE TERMS OF THE LGPL #@\\ \mbox{}\verb@# #@\\ \mbox{}\verb@######################################################################@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@########################### GPL NOTICES ##############################@\\ \mbox{}\verb@# #@\\ \mbox{}\verb@# This program is free software; you can redistribute it and/or #@\\ \mbox{}\verb@# modify it under the terms of the GNU General Public License as #@\\ \mbox{}\verb@# published by the Free Software Foundation; either version 2 of #@\\ \mbox{}\verb@# (the License, or (at your option) any later version. #@\\ \mbox{}\verb@# #@\\ \mbox{}\verb@# This program is distributed in the hope that it will be useful, #@\\ \mbox{}\verb@# but WITHOUT ANY WARRANTY; without even the implied warranty of #@\\ \mbox{}\verb@# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the #@\\ \mbox{}\verb@# GNU General Public License for more details. #@\\ \mbox{}\verb@# #@\\ \mbox{}\verb@# You should have received a copy of the GNU General Public License #@\\ \mbox{}\verb@# along with this program; if not, write to the Free Software #@\\ \mbox{}\verb@# Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA #@\\ \mbox{}\verb@# 02111-1307 USA #@\\ \mbox{}\verb@# #@\\ \mbox{}\verb@######################################################################@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@######################### LGPL NOTICES ###############################@\\ \mbox{}\verb@# #@\\ \mbox{}\verb@# This library is free software; you can redistribute it and/or #@\\ \mbox{}\verb@# modify it under the terms of the GNU Lesser General Public #@\\ \mbox{}\verb@# License as published by the Free Software Foundation; either #@\\ \mbox{}\verb@# version 2.1 of the License, or (at your option) any later version. #@\\ \mbox{}\verb@# #@\\ \mbox{}\verb@# This library is distributed in the hope that it will be useful, #@\\ \mbox{}\verb@# but WITHOUT ANY WARRANTY; without even the implied warranty of #@\\ \mbox{}\verb@# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU #@\\ \mbox{}\verb@# Lesser General Public License for more details. #@\\ \mbox{}\verb@# #@\\ \mbox{}\verb@# You should have received a copy of the GNU Lesser General Public #@\\ \mbox{}\verb@# License along with this library; if not, write to the Free #@\\ \mbox{}\verb@# Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, #@\\ \mbox{}\verb@# MA 02110-1301 USA #@\\ \mbox{}\verb@# #@\\ \mbox{}\verb@######################################################################@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@# Get the ascii text as a list of strings @\\ \mbox{}\verb@lines = open("CBFlib.txt","r").readlines()@\\ \mbox{}\verb@@\\ \mbox{}\verb@# Variables to hold the useful things we find in the file@\\ \mbox{}\verb@docstring = "\n"@\\ \mbox{}\verb@name=""@\\ \mbox{}\verb@@\\ \mbox{}\verb@# Flag to indicate we have not read anything useful yet@\\ \mbox{}\verb@on=0@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@# Dictionary of function prototypes and documentation, keyed by name in C.@\\ \mbox{}\verb@name_dict = {}@\\ \mbox{}\verb@i=-1@\\ \mbox{}\verb@debug = 0@\\ \mbox{}\verb@# Parse the text@\\ \mbox{}\verb@prototypes = ""@\\ \mbox{}\verb@while i=0 and on==1:@\\ \mbox{}\verb@ on=10 # Only try for ten lines after it say PROTOTYPE@\\ \mbox{}\verb@ continue@\\ \mbox{}\verb@ if line.find("#include")>=0: # why?@\\ \mbox{}\verb@ continue @\\ \mbox{}\verb@ if line.find("int cbf_")>=0: # We found a function@\\ \mbox{}\verb@ # keep going up to DESCRIPTION@\\ \mbox{}\verb@ prototypes+=""+lines[i].rstrip()+" "@\\ \mbox{}\verb@ # print lines[i].rstrip()@\\ \mbox{}\verb@ check=0@\\ \mbox{}\verb@ while lines[i+1].find("DESCRIPTION")==-1 and lines[i+1].find("int cbf_")==-1:@\\ \mbox{}\verb@ i=i+1@\\ \mbox{}\verb@ prototypes+=lines[i].rstrip()+" " # lose the \n@\\ \mbox{}\verb@ # print lines[i].rstrip()@\\ \mbox{}\verb@ check+=1@\\ \mbox{}\verb@ if check>20:@\\ \mbox{}\verb@ raise Exception("Runaway prototype "+prototypes)@\\ \mbox{}\verb@ on=1 # Keep reading docstring@\\ \mbox{}\verb@ continue@\\ \mbox{}\verb@ if on > 1: # why?@\\ \mbox{}\verb@ on=on-1@\\ \mbox{}\verb@ if line.find("3. File format")>=0 and on==1:@\\ \mbox{}\verb@ # Stop processing at section 3@\\ \mbox{}\verb@ i=len(lines)@\\ \mbox{}\verb@ if on==1:@\\ \mbox{}\verb@ # Docstring ends at 2.xxx for next function or see also@\\ \mbox{}\verb@ # We are losing the see also information for now (needed the section@\\ \mbox{}\verb@ # breaks in the rtf file)@\\ \mbox{}\verb@ if len(line.strip())==0:@\\ \mbox{}\verb@ docstring+="\n"@\\ \mbox{}\verb@ continue@\\ \mbox{}\verb@ else:@\\ \mbox{}\verb@ if docstring[-1]=="\n":@\\ \mbox{}\verb@ docstring += line.lstrip().rstrip()@\\ \mbox{}\verb@ else:@\\ \mbox{}\verb@ docstring =docstring+" "+line.lstrip().rstrip()@\\ \mbox{}\verb@ if line.strip()[0] in [str(j) for j in range(9)] or \@\\ \mbox{}\verb@ line.find("SEE ALSO")>=0 or \@\\ \mbox{}\verb@ line.find("________")>=0 or \@\\ \mbox{}\verb@ line.find("--------")>=0:@\\ \mbox{}\verb@ if len(docstring)>0:@\\ \mbox{}\verb@ # print "Prototypes: ",prototypes@\\ \mbox{}\verb@ docstring = docstring.replace("\"", " \\\"") # escape the quotes@\\ \mbox{}\verb@ for prototype in prototypes.strip().split(";")[:-1]:@\\ \mbox{}\verb@ name = prototype.split("(")[0].strip()@\\ \mbox{}\verb@ cname = name.split()[1].strip()@\\ \mbox{}\verb@ prototype = prototype.strip()+";"@\\ \mbox{}\verb@ name_dict[cname]=[prototype,docstring]@\\ \mbox{}\verb@ # print "Prototype: ","::",cname,"::",name,"::", prototype@\\ \mbox{}\verb@ prototypes = ""@\\ \mbox{}\verb@ # print "Found ",prototype@\\ \mbox{}\verb@ docstring="\n"@\\ \mbox{}\verb@ prototype=""@\\ \mbox{}\verb@ cname=""@\\ \mbox{}\verb@ on=0@\\ \mbox{}\verb@ else:@\\ \mbox{}\verb@ raise Exception("bad docstring")@\\ \mbox{}\verb@@\\ \mbox{}\verb@# End of CBFlib.txt file - now generate wrapper code for swig@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@def myformat(s,l,indent=0,breakon=" "):@\\ \mbox{}\verb@ """@\\ \mbox{}\verb@ Try to pretty print lines - this is a pain...@\\ \mbox{}\verb@ """@\\ \mbox{}\verb@ lines = s.rstrip().split("\n")@\\ \mbox{}\verb@ out=""@\\ \mbox{}\verb@ for line in lines:@\\ \mbox{}\verb@ if len(line)==0:@\\ \mbox{}\verb@ continue # skip blank lines@\\ \mbox{}\verb@ if len(line)>l:@\\ \mbox{}\verb@ words = line.split(breakon)@\\ \mbox{}\verb@ newline=words[0]@\\ \mbox{}\verb@ if len(words)>1:@\\ \mbox{}\verb@ for word in words[1:]:@\\ \mbox{}\verb@ if len(newline)+len(word)+1 < l:@\\ \mbox{}\verb@ newline=newline+breakon+word@\\ \mbox{}\verb@ else:@\\ \mbox{}\verb@ out = out+newline+breakon+"\n"+indent*" "@\\ \mbox{}\verb@ newline=word @\\ \mbox{}\verb@ out += newline+"\n"@\\ \mbox{}\verb@ else:@\\ \mbox{}\verb@ out += "\n"@\\ \mbox{}\verb@ else:@\\ \mbox{}\verb@ out += line+"\n" # Last one@\\ \mbox{}\verb@ if out == "":@\\ \mbox{}\verb@ return "\n"@\\ \mbox{}\verb@ else:@\\ \mbox{}\verb@ return out@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@def docstringwrite(pyfunc,input,output,prototype,cbflibdoc):@\\ \mbox{}\verb@ doc = "%feature(\"autodoc\", \"\nReturns : "@\\ \mbox{}\verb@ returns = ""@\\ \mbox{}\verb@ for out in output:@\\ \mbox{}\verb@ returns += out+","@\\ \mbox{}\verb@ if len(returns)>0:@\\ \mbox{}\verb@ doc += myformat(returns[:-1],70,indent = 10,breakon=",")@\\ \mbox{}\verb@ else:@\\ \mbox{}\verb@ doc += "\n"@\\ \mbox{}\verb@ doc += "*args : "@\\ \mbox{}\verb@ takes = ""@\\ \mbox{}\verb@ for inp in input:@\\ \mbox{}\verb@ takes += inp+","@\\ \mbox{}\verb@ if len(takes)>0:@\\ \mbox{}\verb@ doc += myformat(takes[:-1],70,indent = 10,breakon=",") @\\ \mbox{}\verb@ else:@\\ \mbox{}\verb@ doc += "\n"@\\ \mbox{}\verb@ doc += "\nC prototype: "+myformat(prototype,65,indent=16,breakon=",")@\\ \mbox{}\verb@ doc += "\nCBFLib documentation:\n"+myformat(cbflibdoc,70)+"\")"@\\ \mbox{}\verb@ doc += pyfunc+";\n"@\\ \mbox{}\verb@ return doc@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@cbfhandle_specials = {@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_integerarrayparameters":["""@\\ \mbox{}\verb@%apply int *OUTPUT {int *compression,int *binary_id, @\\ \mbox{}\verb@ int *elsize, int *elsigned, int *elunsigned, @\\ \mbox{}\verb@ int *elements, int *minelement, int *maxelement} @\\ \mbox{}\verb@ get_integerarrayparameters;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void get_integerarrayparameters(int *compression,int *binary_id, @\\ \mbox{}\verb@ int *elsize, int *elsigned, int *elunsigned, @\\ \mbox{}\verb@ int *elements, int *minelement, int *maxelement){@\\ \mbox{}\verb@ unsigned int comp;@\\ \mbox{}\verb@ size_t elsiz, elem;@\\ \mbox{}\verb@ cbf_failnez(cbf_get_integerarrayparameters(self, @\\ \mbox{}\verb@ &comp,binary_id, &elsiz, elsigned, elunsigned, &elem, @\\ \mbox{}\verb@ minelement, maxelement));@\\ \mbox{}\verb@ *compression = comp; /* FIXME - does this convert in C? */@\\ \mbox{}\verb@ *elsize = elsiz;@\\ \mbox{}\verb@ *elements = elem;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_integerarrayparameters",[],["int compression","int binary_id", @\\ \mbox{}\verb@ "int elsize", "int elsigned", "int elunsigned", @\\ \mbox{}\verb@ "int elements", "int minelement", "int maxelement"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_integerarrayparameters_wdims":["""@\\ \mbox{}\verb@%cstring_output_allocate_size(char **bo, int *bolen, free(*$1));@\\ \mbox{}\verb@%apply int *OUTPUT {int *compression,int *binary_id, @\\ \mbox{}\verb@ int *elsize, int *elsigned, int *elunsigned, @\\ \mbox{}\verb@ int *elements, int *minelement, int *maxelement,@\\ \mbox{}\verb@ int *dimfast, int *dimmid, int *dimslow, int *padding} @\\ \mbox{}\verb@ get_integerarrayparameters_wdims;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void get_integerarrayparameters_wdims(int *compression,int *binary_id, @\\ \mbox{}\verb@ int *elsize, int *elsigned, int *elunsigned, @\\ \mbox{}\verb@ int *elements, int *minelement, int *maxelement,@\\ \mbox{}\verb@ char **bo, int *bolen,@\\ \mbox{}\verb@ int *dimfast, int *dimmid, int *dimslow, int *padding@\\ \mbox{}\verb@ ){@\\ \mbox{}\verb@ unsigned int comp;@\\ \mbox{}\verb@ size_t elsiz, elem, df,dm,ds,pd;@\\ \mbox{}\verb@ const char * byteorder;@\\ \mbox{}\verb@ char * bot;@\\ \mbox{}\verb@ cbf_failnez(cbf_get_integerarrayparameters_wdims(self, @\\ \mbox{}\verb@ &comp,binary_id, &elsiz, elsigned, elunsigned, &elem, @\\ \mbox{}\verb@ minelement, maxelement, &byteorder,&df,&dm,&ds,&pd ));@\\ \mbox{}\verb@ *bolen = strlen(byteorder);@\\ \mbox{}\verb@ if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)}@\\ \mbox{}\verb@ strncpy(bot,byteorder,*bolen);@\\ \mbox{}\verb@ *bo = bot;@\\ \mbox{}\verb@ *compression = comp;@\\ \mbox{}\verb@ *elsize = elsiz;@\\ \mbox{}\verb@ *elements = elem;@\\ \mbox{}\verb@ *dimfast = df;@\\ \mbox{}\verb@ *dimmid = dm;@\\ \mbox{}\verb@ *dimslow = ds;@\\ \mbox{}\verb@ *padding = pd;@\\ \mbox{}\verb@ @\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_integerarrayparameters_wdims",[],["int compression","int binary_id", @\\ \mbox{}\verb@ "int elsize", "int elsigned", "int elunsigned", @\\ \mbox{}\verb@ "int elements", "int minelement", "int maxelement", "char **bo", "int *bolen",@\\ \mbox{}\verb@ "int dimfast", "int dimmid", "int dimslow", "int padding"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_integerarrayparameters_wdims_fs":["""@\\ \mbox{}\verb@%cstring_output_allocate_size(char **bo, int *bolen, free(*$1));@\\ \mbox{}\verb@%apply int *OUTPUT {int *compression,int *binary_id, @\\ \mbox{}\verb@ int *elsize, int *elsigned, int *elunsigned, @\\ \mbox{}\verb@ int *elements, int *minelement, int *maxelement,@\\ \mbox{}\verb@ int *dimfast, int *dimmid, int *dimslow, int *padding} @\\ \mbox{}\verb@ get_integerarrayparameters_wdims_fs;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void get_integerarrayparameters_wdims_fs(int *compression,int *binary_id, @\\ \mbox{}\verb@ int *elsize, int *elsigned, int *elunsigned, @\\ \mbox{}\verb@ int *elements, int *minelement, int *maxelement,@\\ \mbox{}\verb@ char **bo, int *bolen,@\\ \mbox{}\verb@ int *dimfast, int *dimmid, int *dimslow, int *padding@\\ \mbox{}\verb@ ){@\\ \mbox{}\verb@ unsigned int comp;@\\ \mbox{}\verb@ size_t elsiz, elem, df,dm,ds,pd;@\\ \mbox{}\verb@ const char * byteorder;@\\ \mbox{}\verb@ char * bot;@\\ \mbox{}\verb@ cbf_failnez(cbf_get_integerarrayparameters_wdims_fs(self, @\\ \mbox{}\verb@ &comp,binary_id, &elsiz, elsigned, elunsigned, &elem, @\\ \mbox{}\verb@ minelement, maxelement, &byteorder,&df,&dm,&ds,&pd ));@\\ \mbox{}\verb@ *bolen = strlen(byteorder);@\\ \mbox{}\verb@ if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)}@\\ \mbox{}\verb@ strncpy(bot,byteorder,*bolen);@\\ \mbox{}\verb@ *bo = bot;@\\ \mbox{}\verb@ *compression = comp; @\\ \mbox{}\verb@ *elsize = elsiz;@\\ \mbox{}\verb@ *elements = elem;@\\ \mbox{}\verb@ *dimfast = df;@\\ \mbox{}\verb@ *dimmid = dm;@\\ \mbox{}\verb@ *dimslow = ds;@\\ \mbox{}\verb@ *padding = pd;@\\ \mbox{}\verb@ @\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_integerarrayparameters_wdims_fs",[],["int compression","int binary_id", @\\ \mbox{}\verb@ "int elsize", "int elsigned", "int elunsigned", @\\ \mbox{}\verb@ "int elements", "int minelement", "int maxelement", "char **bo", "int *bolen",@\\ \mbox{}\verb@ "int dimfast", "int dimmid", "int dimslow", "int padding"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_integerarrayparameters_wdims_sf":["""@\\ \mbox{}\verb@%cstring_output_allocate_size(char **bo, int *bolen, free(*$1));@\\ \mbox{}\verb@%apply int *OUTPUT {int *compression,int *binary_id, @\\ \mbox{}\verb@ int *elsize, int *elsigned, int *elunsigned, @\\ \mbox{}\verb@ int *elements, int *minelement, int *maxelement,@\\ \mbox{}\verb@ int *dimslow, int *dimmid, int *dimfast, int *padding} @\\ \mbox{}\verb@ get_integerarrayparameters_wdims_sf;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void get_integerarrayparameters_wdims_sf(int *compression,int *binary_id, @\\ \mbox{}\verb@ int *elsize, int *elsigned, int *elunsigned, @\\ \mbox{}\verb@ int *elements, int *minelement, int *maxelement,@\\ \mbox{}\verb@ char **bo, int *bolen,@\\ \mbox{}\verb@ int *dimslow, int *dimmid, int *dimfast, int *padding@\\ \mbox{}\verb@ ){@\\ \mbox{}\verb@ unsigned int comp;@\\ \mbox{}\verb@ size_t elsiz, elem, df,dm,ds,pd;@\\ \mbox{}\verb@ const char * byteorder;@\\ \mbox{}\verb@ char * bot;@\\ \mbox{}\verb@ cbf_failnez(cbf_get_integerarrayparameters_wdims_sf(self, @\\ \mbox{}\verb@ &comp,binary_id, &elsiz, elsigned, elunsigned, &elem, @\\ \mbox{}\verb@ minelement, maxelement, &byteorder,&ds,&dm,&df,&pd ));@\\ \mbox{}\verb@ *bolen = strlen(byteorder);@\\ \mbox{}\verb@ if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)}@\\ \mbox{}\verb@ strncpy(bot,byteorder,*bolen);@\\ \mbox{}\verb@ *bo = bot;@\\ \mbox{}\verb@ *compression = comp;@\\ \mbox{}\verb@ *elsize = elsiz;@\\ \mbox{}\verb@ *elements = elem;@\\ \mbox{}\verb@ *dimfast = df;@\\ \mbox{}\verb@ *dimmid = dm;@\\ \mbox{}\verb@ *dimslow = ds;@\\ \mbox{}\verb@ *padding = pd;@\\ \mbox{}\verb@ @\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_integerarrayparameters_wdims_sf",[],["int compression","int binary_id", @\\ \mbox{}\verb@ "int elsize", "int elsigned", "int elunsigned", @\\ \mbox{}\verb@ "int elements", "int minelement", "int maxelement", "char **bo", "int *bolen",@\\ \mbox{}\verb@ "int dimslow", "int dimmid", "int dimfast", "int padding"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_realarrayparameters":["""@\\ \mbox{}\verb@%apply int *OUTPUT {int *compression,int *binary_id, @\\ \mbox{}\verb@ int *elsize, int *elements} get_realarrayparameters;@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void get_realarrayparameters(int *compression,int *binary_id, @\\ \mbox{}\verb@ int *elsize, int *elements){@\\ \mbox{}\verb@ unsigned int comp;@\\ \mbox{}\verb@ size_t elsiz, elem;@\\ \mbox{}\verb@ cbf_failnez(cbf_get_realarrayparameters(self, @\\ \mbox{}\verb@ &comp ,binary_id, &elsiz, &elem ));@\\ \mbox{}\verb@ *compression = comp; /* FIXME - does this convert in C? */@\\ \mbox{}\verb@ *elsize = elsiz;@\\ \mbox{}\verb@ *elements = elem;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_realarrayparameters",[],["int compression","int binary_id", @\\ \mbox{}\verb@ "int elsize", "int elements"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_realarrayparameters_wdims":["""@\\ \mbox{}\verb@%cstring_output_allocate_size(char **bo, int *bolen, free(*$1));@\\ \mbox{}\verb@%apply int *OUTPUT {int *compression,int *binary_id, @\\ \mbox{}\verb@ int *elsize, @\\ \mbox{}\verb@ int *elements,@\\ \mbox{}\verb@ int *dimslow, int *dimmid, int *dimfast, int *padding} @\\ \mbox{}\verb@ get_realarrayparameters_wdims;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void get_realarrayparameters_wdims(int *compression,int *binary_id, @\\ \mbox{}\verb@ int *elsize, @\\ \mbox{}\verb@ int *elements, @\\ \mbox{}\verb@ char **bo, int *bolen,@\\ \mbox{}\verb@ int *dimfast, int *dimmid, int *dimslow, int *padding@\\ \mbox{}\verb@ ){@\\ \mbox{}\verb@ unsigned int comp;@\\ \mbox{}\verb@ size_t elsiz, elem, df,dm,ds,pd;@\\ \mbox{}\verb@ const char * byteorder;@\\ \mbox{}\verb@ char * bot;@\\ \mbox{}\verb@ cbf_failnez(cbf_get_realarrayparameters_wdims(self, @\\ \mbox{}\verb@ &comp,binary_id, &elsiz, &elem, @\\ \mbox{}\verb@ &byteorder,&ds,&dm,&ds,&pd ));@\\ \mbox{}\verb@ *bolen = strlen(byteorder);@\\ \mbox{}\verb@ if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)}@\\ \mbox{}\verb@ strncpy(bot,byteorder,*bolen);@\\ \mbox{}\verb@ *bo = bot;@\\ \mbox{}\verb@ *compression = comp;@\\ \mbox{}\verb@ *elsize = elsiz;@\\ \mbox{}\verb@ *elements = elem;@\\ \mbox{}\verb@ *dimfast = df;@\\ \mbox{}\verb@ *dimmid = dm;@\\ \mbox{}\verb@ *dimslow = ds;@\\ \mbox{}\verb@ *padding = pd;@\\ \mbox{}\verb@ @\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_realarrayparameters_wdims",[],["int compression","int binary_id", @\\ \mbox{}\verb@ "int elsize", @\\ \mbox{}\verb@ "int elements", "char **bo", "int *bolen",@\\ \mbox{}\verb@ "int dimfast", "int dimmid", "int dimslow", "int padding"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_realarrayparameters_wdims_fs":["""@\\ \mbox{}\verb@%cstring_output_allocate_size(char **bo, int *bolen, free(*$1));@\\ \mbox{}\verb@%apply int *OUTPUT {int *compression,int *binary_id, @\\ \mbox{}\verb@ int *elsize, @\\ \mbox{}\verb@ int *elements,@\\ \mbox{}\verb@ int *dimslow, int *dimmid, int *dimfast, int *padding} @\\ \mbox{}\verb@ get_realarrayparameters_wdims_fs;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void get_realarrayparameters_wdims_fs(int *compression,int *binary_id, @\\ \mbox{}\verb@ int *elsize, @\\ \mbox{}\verb@ int *elements, @\\ \mbox{}\verb@ char **bo, int *bolen,@\\ \mbox{}\verb@ int *dimfast, int *dimmid, int *dimslow, int *padding@\\ \mbox{}\verb@ ){@\\ \mbox{}\verb@ unsigned int comp;@\\ \mbox{}\verb@ size_t elsiz, elem, df,dm,ds,pd;@\\ \mbox{}\verb@ const char * byteorder;@\\ \mbox{}\verb@ char * bot;@\\ \mbox{}\verb@ cbf_failnez(cbf_get_realarrayparameters_wdims_fs(self, @\\ \mbox{}\verb@ &comp,binary_id, &elsiz, &elem, @\\ \mbox{}\verb@ &byteorder,&ds,&dm,&ds,&pd ));@\\ \mbox{}\verb@ *bolen = strlen(byteorder);@\\ \mbox{}\verb@ if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)}@\\ \mbox{}\verb@ strncpy(bot,byteorder,*bolen);@\\ \mbox{}\verb@ *bo = bot;@\\ \mbox{}\verb@ *compression = comp;@\\ \mbox{}\verb@ *elsize = elsiz;@\\ \mbox{}\verb@ *elements = elem;@\\ \mbox{}\verb@ *dimfast = df;@\\ \mbox{}\verb@ *dimmid = dm;@\\ \mbox{}\verb@ *dimslow = ds;@\\ \mbox{}\verb@ *padding = pd;@\\ \mbox{}\verb@ @\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_realarrayparameters_wdims_fs",[],["int compression","int binary_id", @\\ \mbox{}\verb@ "int elsize", @\\ \mbox{}\verb@ "int elements", "char **bo", "int *bolen",@\\ \mbox{}\verb@ "int dimfast", "int dimmid", "int dimslow", "int padding"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_realarrayparameters_wdims_sf":["""@\\ \mbox{}\verb@%cstring_output_allocate_size(char **bo, int *bolen, free(*$1));@\\ \mbox{}\verb@%apply int *OUTPUT {int *compression,int *binary_id, @\\ \mbox{}\verb@ int *elsize, @\\ \mbox{}\verb@ int *elements,@\\ \mbox{}\verb@ int *dimslow, int *dimmid, int *dimfast, int *padding} @\\ \mbox{}\verb@ get_realarrayparameters_wdims_sf;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void get_realarrayparameters_wdims_sf(int *compression,int *binary_id, @\\ \mbox{}\verb@ int *elsize, @\\ \mbox{}\verb@ int *elements, @\\ \mbox{}\verb@ char **bo, int *bolen,@\\ \mbox{}\verb@ int *dimslow, int *dimmid, int *dimfast, int *padding@\\ \mbox{}\verb@ ){@\\ \mbox{}\verb@ unsigned int comp;@\\ \mbox{}\verb@ size_t elsiz, elem, df,dm,ds,pd;@\\ \mbox{}\verb@ const char * byteorder;@\\ \mbox{}\verb@ char * bot;@\\ \mbox{}\verb@ cbf_failnez(cbf_get_realarrayparameters_wdims_sf(self, @\\ \mbox{}\verb@ &comp,binary_id, &elsiz, &elem, @\\ \mbox{}\verb@ &byteorder,&ds,&dm,&df,&pd ));@\\ \mbox{}\verb@ *bolen = strlen(byteorder);@\\ \mbox{}\verb@ if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)}@\\ \mbox{}\verb@ strncpy(bot,byteorder,*bolen);@\\ \mbox{}\verb@ *bo = bot;@\\ \mbox{}\verb@ *compression = comp;@\\ \mbox{}\verb@ *elsize = elsiz;@\\ \mbox{}\verb@ *elements = elem;@\\ \mbox{}\verb@ *dimfast = df;@\\ \mbox{}\verb@ *dimmid = dm;@\\ \mbox{}\verb@ *dimslow = ds;@\\ \mbox{}\verb@ *padding = pd;@\\ \mbox{}\verb@ @\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_realarrayparameters_wdims_sf",[],["int compression","int binary_id", @\\ \mbox{}\verb@ "int elsize", @\\ \mbox{}\verb@ "int elements", "char **bo", "int *bolen",@\\ \mbox{}\verb@ "int dimslow", "int dimmid", "int dimfast", "int padding"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_integerarray":["""@\\ \mbox{}\verb@// Ensure we free the local temporary@\\ \mbox{}\verb@@\\ \mbox{}\verb@%cstring_output_allocate_size(char ** s, int *slen, free(*$1))@\\ \mbox{}\verb@ get_integerarray_as_string;@\\ \mbox{}\verb@@\\ \mbox{}\verb@// Get the length correct@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void get_integerarray_as_string(char **s, int *slen){@\\ \mbox{}\verb@ int binary_id, elsigned, elunsigned;@\\ \mbox{}\verb@ size_t elements, elements_read, elsize;@\\ \mbox{}\verb@ int minelement, maxelement;@\\ \mbox{}\verb@ unsigned int compression;@\\ \mbox{}\verb@ void * array;@\\ \mbox{}\verb@ *slen = 0; /* Initialise in case of problems */@\\ \mbox{}\verb@ cbf_failnez(cbf_get_integerarrayparameters(self, &compression,@\\ \mbox{}\verb@ &binary_id, &elsize, &elsigned, &elunsigned,@\\ \mbox{}\verb@ &elements, &minelement, &maxelement));@\\ \mbox{}\verb@@\\ \mbox{}\verb@ if ((array=malloc(elsize*elements))) {@\\ \mbox{}\verb@ /* cbf_failnez (cbf_select_column(cbf,colnum)) */@\\ \mbox{}\verb@ cbf_failnez (cbf_get_integerarray(self, &binary_id, @\\ \mbox{}\verb@ (void *)array, elsize, elsigned,@\\ \mbox{}\verb@ elements, &elements_read));@\\ \mbox{}\verb@@\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ALLOC);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ *slen = elsize*elements;@\\ \mbox{}\verb@ *s = (char *) array;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_integerarray_as_string",[],["(Binary)String"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_image":["""@\\ \mbox{}\verb@// Ensure we free the local temporary@\\ \mbox{}\verb@@\\ \mbox{}\verb@%cstring_output_allocate_size(char ** s, int *slen, free(*$1))@\\ \mbox{}\verb@ get_image_as_string;@\\ \mbox{}\verb@@\\ \mbox{}\verb@// Get the length correct@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void get_image_as_string(int element_number, char **s, int *slen,@\\ \mbox{}\verb@ int elsize, int elsign, int ndimslow, int ndimfast){@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ int reserved = 0;@\\ \mbox{}\verb@ *slen = 0; /* Initialise in case of problems */@\\ \mbox{}\verb@ if ((array=malloc(elsize*ndimfast*ndimslow))) {@\\ \mbox{}\verb@ cbf_failnez (cbf_get_image(self, @\\ \mbox{}\verb@ reserved, (unsigned int)element_number,@\\ \mbox{}\verb@ (void *)array, (size_t)elsize, elsign,@\\ \mbox{}\verb@ (size_t) ndimslow, (size_t)ndimfast));@\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ALLOC);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ *slen = elsize*ndimfast*ndimslow;@\\ \mbox{}\verb@ *s = (char *) array;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_image_as_string",["int element_number", @\\ \mbox{}\verb@ "int elsize", "int elsign", "int ndimslow", "int ndimfast"],["(Binary)String"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_image_fs":["""@\\ \mbox{}\verb@// Ensure we free the local temporary@\\ \mbox{}\verb@@\\ \mbox{}\verb@%cstring_output_allocate_size(char ** s, int *slen, free(*$1))@\\ \mbox{}\verb@ get_image_fs_as_string;@\\ \mbox{}\verb@@\\ \mbox{}\verb@// Get the length correct@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void get_image_fs_as_string(int element_number, char **s, int *slen,@\\ \mbox{}\verb@ int elsize, int elsign, int ndimfast, int ndimslow){@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ int reserved = 0;@\\ \mbox{}\verb@ *slen = 0; /* Initialise in case of problems */@\\ \mbox{}\verb@ if ((array=malloc(elsize*ndimfast*ndimslow))) {@\\ \mbox{}\verb@ cbf_failnez (cbf_get_image_fs(self, @\\ \mbox{}\verb@ reserved, (unsigned int)element_number,@\\ \mbox{}\verb@ (void *)array, (size_t)elsize, elsign,@\\ \mbox{}\verb@ (size_t) ndimfast, (size_t)ndimslow));@\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ALLOC);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ *slen = elsize*ndimfast*ndimslow;@\\ \mbox{}\verb@ *s = (char *) array;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_image_fs_as_string",["int element_number", @\\ \mbox{}\verb@ "int elsize", "int elsign", "int ndimfast", "int ndimslow"],["(Binary)String"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_image_sf":["""@\\ \mbox{}\verb@// Ensure we free the local temporary@\\ \mbox{}\verb@@\\ \mbox{}\verb@%cstring_output_allocate_size(char ** s, int *slen, free(*$1))@\\ \mbox{}\verb@ get_image_fs_as_string;@\\ \mbox{}\verb@@\\ \mbox{}\verb@// Get the length correct@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void get_image_sf_as_string(int element_number, char **s, int *slen,@\\ \mbox{}\verb@ int elsize, int elsign, int ndimslow, int ndimfast){@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ int reserved = 0;@\\ \mbox{}\verb@ *slen = 0; /* Initialise in case of problems */@\\ \mbox{}\verb@ if ((array=malloc(elsize*ndimfast*ndimslow))) {@\\ \mbox{}\verb@ cbf_failnez (cbf_get_image_sf(self, @\\ \mbox{}\verb@ reserved, (unsigned int)element_number,@\\ \mbox{}\verb@ (void *)array, (size_t)elsize, elsign,@\\ \mbox{}\verb@ (size_t) ndimslow, (size_t)ndimfast));@\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ALLOC);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ *slen = elsize*ndimfast*ndimslow;@\\ \mbox{}\verb@ *s = (char *) array;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_image_sf_as_string",["int element_number", @\\ \mbox{}\verb@ "int elsize", "int elsign", "int ndimslow", "int ndimfast"],["(Binary)String"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_real_image":["""@\\ \mbox{}\verb@// Ensure we free the local temporary@\\ \mbox{}\verb@@\\ \mbox{}\verb@%cstring_output_allocate_size(char ** s, int *slen, free(*$1))@\\ \mbox{}\verb@ get_real_image_as_string;@\\ \mbox{}\verb@@\\ \mbox{}\verb@// Get the length correct@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void get_real_image_as_string(int element_number, char **s, int *slen,@\\ \mbox{}\verb@ int elsize, int ndimslow, int ndimfast){@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ int reserved = 0;@\\ \mbox{}\verb@ *slen = 0; /* Initialise in case of problems */@\\ \mbox{}\verb@ if ((array=malloc(elsize*ndimfast*ndimslow))) {@\\ \mbox{}\verb@ cbf_failnez (cbf_get_real_image(self, @\\ \mbox{}\verb@ reserved, (unsigned int)element_number,@\\ \mbox{}\verb@ (void *)array, (size_t)elsize,@\\ \mbox{}\verb@ (size_t) ndimslow, (size_t)ndimfast));@\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ALLOC);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ *slen = elsize*ndimfast*ndimslow;@\\ \mbox{}\verb@ *s = (char *) array;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_real_image_as_string",["int element_number", @\\ \mbox{}\verb@ "int elsize", "int ndimslow", "int ndimfast"],["(Binary)String"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_real_image_fs":["""@\\ \mbox{}\verb@// Ensure we free the local temporary@\\ \mbox{}\verb@@\\ \mbox{}\verb@%cstring_output_allocate_size(char ** s, int *slen, free(*$1))@\\ \mbox{}\verb@ get_real_image_fs_as_string;@\\ \mbox{}\verb@@\\ \mbox{}\verb@// Get the length correct@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void get_real_image_fs_as_string(int element_number, char **s, int *slen,@\\ \mbox{}\verb@ int elsize, int ndimfast, int ndimslow){@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ int reserved = 0;@\\ \mbox{}\verb@ *slen = 0; /* Initialise in case of problems */@\\ \mbox{}\verb@ if ((array=malloc(elsize*ndimfast*ndimslow))) {@\\ \mbox{}\verb@ cbf_failnez (cbf_get_real_image_fs(self, @\\ \mbox{}\verb@ reserved, (unsigned int)element_number,@\\ \mbox{}\verb@ (void *)array, (size_t)elsize,@\\ \mbox{}\verb@ (size_t) ndimfast, (size_t)ndimslow));@\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ALLOC);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ *slen = elsize*ndimfast*ndimslow;@\\ \mbox{}\verb@ *s = (char *) array;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_real_image_fs_as_string",["int element_number", @\\ \mbox{}\verb@ "int elsize", "int ndimfast", "int ndimslow"],["(Binary)String"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_real_image_sf":["""@\\ \mbox{}\verb@// Ensure we free the local temporary@\\ \mbox{}\verb@@\\ \mbox{}\verb@%cstring_output_allocate_size(char ** s, int *slen, free(*$1))@\\ \mbox{}\verb@ get_real_image_sf_as_string;@\\ \mbox{}\verb@@\\ \mbox{}\verb@// Get the length correct@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void get_real_image_sf_as_string(int element_number, char **s, int *slen,@\\ \mbox{}\verb@ int elsize, int ndimslow, int ndimfast){@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ int reserved = 0;@\\ \mbox{}\verb@ *slen = 0; /* Initialise in case of problems */@\\ \mbox{}\verb@ if ((array=malloc(elsize*ndimfast*ndimslow))) {@\\ \mbox{}\verb@ cbf_failnez (cbf_get_real_image_sf(self, @\\ \mbox{}\verb@ reserved, (unsigned int)element_number,@\\ \mbox{}\verb@ (void *)array, (size_t)elsize,@\\ \mbox{}\verb@ (size_t) ndimslow, (size_t)ndimfast));@\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ALLOC);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ *slen = elsize*ndimfast*ndimslow;@\\ \mbox{}\verb@ *s = (char *) array;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_real_image_sf_as_string",["int element_number", @\\ \mbox{}\verb@ "int elsize", "int ndimslow", "int ndimfast"],["(Binary)String"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_3d_image":["""@\\ \mbox{}\verb@// Ensure we free the local temporary@\\ \mbox{}\verb@@\\ \mbox{}\verb@%cstring_output_allocate_size(char ** s, int *slen, free(*$1))@\\ \mbox{}\verb@ get_3d_image_as_string;@\\ \mbox{}\verb@@\\ \mbox{}\verb@// Get the length correct@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void get_3d_image_as_string(int element_number, char **s, int *slen,@\\ \mbox{}\verb@ int elsize, int elsign, int ndimfast, int ndimmid, int ndimslow){@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ int reserved = 0;@\\ \mbox{}\verb@ *slen = 0; /* Initialise in case of problems */@\\ \mbox{}\verb@ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) {@\\ \mbox{}\verb@ cbf_failnez (cbf_get_3d_image(self, @\\ \mbox{}\verb@ reserved, (unsigned int)element_number,@\\ \mbox{}\verb@ (void *)array, (size_t)elsize, elsign,@\\ \mbox{}\verb@ (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast));@\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ALLOC);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ *slen = elsize*ndimfast*ndimmid*ndimslow;@\\ \mbox{}\verb@ *s = (char *) array;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_3d_image_as_string",["int element_number", @\\ \mbox{}\verb@ "int elsize", "int elsign", "int ndimslow", "int ndimmid", "int ndimfast"],["(Binary)String"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_3d_image_fs":["""@\\ \mbox{}\verb@// Ensure we free the local temporary@\\ \mbox{}\verb@@\\ \mbox{}\verb@%cstring_output_allocate_size(char ** s, int *slen, free(*$1))@\\ \mbox{}\verb@ get_3d_image_fs_as_string;@\\ \mbox{}\verb@@\\ \mbox{}\verb@// Get the length correct@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void get_3d_image_fs_as_string(int element_number, char **s, int *slen,@\\ \mbox{}\verb@ int elsize, int elsign, int ndimfast, int ndimmid, int ndimslow){@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ int reserved = 0;@\\ \mbox{}\verb@ *slen = 0; /* Initialise in case of problems */@\\ \mbox{}\verb@ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) {@\\ \mbox{}\verb@ cbf_failnez (cbf_get_3d_image_fs(self, @\\ \mbox{}\verb@ reserved, (unsigned int)element_number,@\\ \mbox{}\verb@ (void *)array, (size_t)elsize, elsign,@\\ \mbox{}\verb@ (size_t) ndimfast, (size_t)ndimmid, (size_t)ndimslow));@\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ALLOC);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ *slen = elsize*ndimfast*ndimmid*ndimslow;@\\ \mbox{}\verb@ *s = (char *) array;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_3d_image_fs_as_string",["int element_number", @\\ \mbox{}\verb@ "int elsize", "int elsign", "int ndimfast", "int ndimmid", "int ndimslow"],["(Binary)String"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_3d_image_sf":["""@\\ \mbox{}\verb@// Ensure we free the local temporary@\\ \mbox{}\verb@@\\ \mbox{}\verb@%cstring_output_allocate_size(char ** s, int *slen, free(*$1))@\\ \mbox{}\verb@ get_3d_image_sf_as_string;@\\ \mbox{}\verb@@\\ \mbox{}\verb@// Get the length correct@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void get_3d_image_sf_as_string(int element_number, char **s, int *slen,@\\ \mbox{}\verb@ int elsize, int elsign, int ndimfast, int ndimmid, int ndimslow){@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ int reserved = 0;@\\ \mbox{}\verb@ *slen = 0; /* Initialise in case of problems */@\\ \mbox{}\verb@ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) {@\\ \mbox{}\verb@ cbf_failnez (cbf_get_3d_image_sf(self, @\\ \mbox{}\verb@ reserved, (unsigned int)element_number,@\\ \mbox{}\verb@ (void *)array, (size_t)elsize, elsign,@\\ \mbox{}\verb@ (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast));@\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ALLOC);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ *slen = elsize*ndimfast*ndimmid*ndimslow;@\\ \mbox{}\verb@ *s = (char *) array;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_3d_image_sf_as_string",["int element_number", @\\ \mbox{}\verb@ "int elsize", "int elsign", "int ndimslow", "int ndimmid", "int ndimfast"],["(Binary)String"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_real_3d_image":["""@\\ \mbox{}\verb@// Ensure we free the local temporary@\\ \mbox{}\verb@@\\ \mbox{}\verb@%cstring_output_allocate_size(char ** s, int *slen, free(*$1))@\\ \mbox{}\verb@ get_real_3d_image_as_string;@\\ \mbox{}\verb@@\\ \mbox{}\verb@// Get the length correct@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void get_real_3d_image_as_string(int element_number, char **s, int *slen,@\\ \mbox{}\verb@ int elsize, int ndimslow, int ndimmid, int ndimfast){@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ int reserved = 0;@\\ \mbox{}\verb@ *slen = 0; /* Initialise in case of problems */@\\ \mbox{}\verb@ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) {@\\ \mbox{}\verb@ cbf_failnez (cbf_get_real_3d_image(self, @\\ \mbox{}\verb@ reserved, (unsigned int)element_number,@\\ \mbox{}\verb@ (void *)array, (size_t)elsize,@\\ \mbox{}\verb@ (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast));@\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ALLOC);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ *slen = elsize*ndimfast*ndimmid*ndimslow;@\\ \mbox{}\verb@ *s = (char *) array;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_real_3d_image_as_string",["int element_number", @\\ \mbox{}\verb@ "int elsize", "int ndimslow", "int ndimmid", "int ndimfast"],["(Binary)String"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_real_3d_image_fs":["""@\\ \mbox{}\verb@// Ensure we free the local temporary@\\ \mbox{}\verb@@\\ \mbox{}\verb@%cstring_output_allocate_size(char ** s, int *slen, free(*$1))@\\ \mbox{}\verb@ get_real_3d_image_fs_as_string;@\\ \mbox{}\verb@@\\ \mbox{}\verb@// Get the length correct@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void get_real_3d_image_fs_as_string(int element_number, char **s, int *slen,@\\ \mbox{}\verb@ int elsize, int ndimfast, int ndimmid, int ndimslow){@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ int reserved = 0;@\\ \mbox{}\verb@ *slen = 0; /* Initialise in case of problems */@\\ \mbox{}\verb@ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) {@\\ \mbox{}\verb@ cbf_failnez (cbf_get_real_3d_image_fs(self, @\\ \mbox{}\verb@ reserved, (unsigned int)element_number,@\\ \mbox{}\verb@ (void *)array, (size_t)elsize,@\\ \mbox{}\verb@ (size_t) ndimfast, (size_t)ndimmid, (size_t)ndimslow));@\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ALLOC);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ *slen = elsize*ndimfast*ndimmid*ndimslow;@\\ \mbox{}\verb@ *s = (char *) array;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_real_3d_image_fs_as_string",["int element_number", @\\ \mbox{}\verb@ "int elsize", "int ndimfast", "int ndimmid", "int ndimslow"],["(Binary)String"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_real_3d_image_sf":["""@\\ \mbox{}\verb@// Ensure we free the local temporary@\\ \mbox{}\verb@@\\ \mbox{}\verb@%cstring_output_allocate_size(char ** s, int *slen, free(*$1))@\\ \mbox{}\verb@ get_real_3d_image_sf_as_string;@\\ \mbox{}\verb@@\\ \mbox{}\verb@// Get the length correct@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void get_real_3d_image_sf_as_string(int element_number, char **s, int *slen,@\\ \mbox{}\verb@ int elsize, int ndimslow, int ndimmid, int ndimfast){@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ int reserved = 0;@\\ \mbox{}\verb@ *slen = 0; /* Initialise in case of problems */@\\ \mbox{}\verb@ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) {@\\ \mbox{}\verb@ cbf_failnez (cbf_get_real_3d_image_sf(self, @\\ \mbox{}\verb@ reserved, (unsigned int)element_number,@\\ \mbox{}\verb@ (void *)array, (size_t)elsize,@\\ \mbox{}\verb@ (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast));@\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ALLOC);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ *slen = elsize*ndimfast*ndimmid*ndimslow;@\\ \mbox{}\verb@ *s = (char *) array;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_real_3d_image_sf_as_string",["int element_number", @\\ \mbox{}\verb@ "int elsize", "int ndimslow", "int ndimmid", "int ndimfast"],["(Binary)String"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_realarray":["""@\\ \mbox{}\verb@// Ensure we free the local temporary@\\ \mbox{}\verb@@\\ \mbox{}\verb@%cstring_output_allocate_size(char ** s, int *slen, free(*$1))@\\ \mbox{}\verb@ get_realarray_as_string;@\\ \mbox{}\verb@@\\ \mbox{}\verb@// Get the length correct@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void get_realarray_as_string(char **s, int *slen){@\\ \mbox{}\verb@ int binary_id;@\\ \mbox{}\verb@ size_t elements, elements_read, elsize;@\\ \mbox{}\verb@ unsigned int compression;@\\ \mbox{}\verb@ void * array;@\\ \mbox{}\verb@ *slen = 0; /* Initialise in case of problems */@\\ \mbox{}\verb@ cbf_failnez(cbf_get_realarrayparameters(self, &compression,@\\ \mbox{}\verb@ &binary_id, &elsize,@\\ \mbox{}\verb@ &elements));@\\ \mbox{}\verb@@\\ \mbox{}\verb@ if ((array=malloc(elsize*elements))) {@\\ \mbox{}\verb@ /* cbf_failnez (cbf_select_column(cbf,colnum)) */@\\ \mbox{}\verb@ cbf_failnez (cbf_get_realarray(self, &binary_id, @\\ \mbox{}\verb@ (void *)array, elsize,@\\ \mbox{}\verb@ elements, &elements_read));@\\ \mbox{}\verb@@\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ALLOC);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ *slen = elsize*elements;@\\ \mbox{}\verb@ *s = (char *) array;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_realarray_as_string",[],["(Binary)String"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_integerarray":["""@\\ \mbox{}\verb@ /* CBFlib must NOT modify the data string which belongs to the scripting @\\ \mbox{}\verb@ language we will get and check the length via a typemap */@\\ \mbox{}\verb@@\\ \mbox{}\verb@%apply (char *STRING, int LENGTH) { (char *data, int len) } set_integerarray;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void set_integerarray(unsigned int compression, int binary_id, @\\ \mbox{}\verb@ char *data, int len, int elsize, int elsigned, int elements){@\\ \mbox{}\verb@ /* safety check on args */@\\ \mbox{}\verb@ size_t els, ele;@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ if(len == elsize*elements){@\\ \mbox{}\verb@ array = data;@\\ \mbox{}\verb@ els = elsize;@\\ \mbox{}\verb@ ele = elements;@\\ \mbox{}\verb@ cbf_failnez(cbf_set_integerarray (self, compression, binary_id, @\\ \mbox{}\verb@ (void *) data, (size_t) elsize, elsigned, (size_t) elements)); @\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ARGUMENT);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_integerarray",@\\ \mbox{}\verb@[ "int compression", "int binary_id","(binary) String data", @\\ \mbox{}\verb@ "int elsize", "int elsigned","int elements"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_integerarray_wdims":["""@\\ \mbox{}\verb@ /* CBFlib must NOT modify the data string nor the byteorder string@\\ \mbox{}\verb@ which belongs to the scripting @\\ \mbox{}\verb@ language we will get and check the length via a typemap */@\\ \mbox{}\verb@@\\ \mbox{}\verb@%apply (char *STRING, int LENGTH) { (char *data, int len) } set_integerarray_wdims;@\\ \mbox{}\verb@%apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_integerarray_wdims;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void set_integerarray_wdims(unsigned int compression, int binary_id, @\\ \mbox{}\verb@ char *data, int len, int elsize, int elsigned, int elements,@\\ \mbox{}\verb@ char *bo, int bolen, int dimfast, int dimmid, int dimslow, int padding){@\\ \mbox{}\verb@ /* safety check on args */@\\ \mbox{}\verb@ size_t els, ele;@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ char byteorder[15];@\\ \mbox{}\verb@ if(len == elsize*elements && elements==dimfast*dimmid*dimslow){@\\ \mbox{}\verb@ array = data;@\\ \mbox{}\verb@ els = elsize;@\\ \mbox{}\verb@ ele = elements;@\\ \mbox{}\verb@ strncpy(byteorder,bo,bolen<15?bolen:14);@\\ \mbox{}\verb@ byteorder[bolen<15?14:bolen] = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_set_integerarray_wdims (self, compression, binary_id, @\\ \mbox{}\verb@ (void *) data, (size_t) elsize, elsigned, (size_t) elements, (const char *)byteorder,@\\ \mbox{}\verb@ (size_t)dimfast, (size_t)dimmid, (size_t)dimslow, (size_t)padding)); @\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ARGUMENT);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_integerarray_wdims",@\\ \mbox{}\verb@[ "int compression", "int binary_id","(binary) String data", @\\ \mbox{}\verb@ "int elsize","int elements", "String byteorder", "int dimfast", "int dimmid", "int dimslow", "int padding"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_integerarray_wdims_sf":["""@\\ \mbox{}\verb@ /* CBFlib must NOT modify the data string nor the byteorder string@\\ \mbox{}\verb@ which belongs to the scripting @\\ \mbox{}\verb@ language we will get and check the length via a typemap */@\\ \mbox{}\verb@@\\ \mbox{}\verb@%apply (char *STRING, int LENGTH) { (char *data, int len) } set_integerarray_wdims_sf;@\\ \mbox{}\verb@%apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_integerarray_wdims_sf;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void set_integerarray_wdims_sf(unsigned int compression, int binary_id, @\\ \mbox{}\verb@ char *data, int len, int elsize, int elsigned, int elements,@\\ \mbox{}\verb@ char *bo, int bolen, int dimslow, int dimmid, int dimfast, int padding){@\\ \mbox{}\verb@ /* safety check on args */@\\ \mbox{}\verb@ size_t els, ele;@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ char byteorder[15];@\\ \mbox{}\verb@ if(len == elsize*elements && elements==dimfast*dimmid*dimslow){@\\ \mbox{}\verb@ array = data;@\\ \mbox{}\verb@ els = elsize;@\\ \mbox{}\verb@ ele = elements;@\\ \mbox{}\verb@ strncpy(byteorder,bo,bolen<15?bolen:14);@\\ \mbox{}\verb@ byteorder[bolen<15?14:bolen] = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_set_integerarray_wdims_sf (self, compression, binary_id, @\\ \mbox{}\verb@ (void *) data, (size_t) elsize, elsigned, (size_t) elements, (const char *)byteorder,@\\ \mbox{}\verb@ (size_t)dimslow, (size_t)dimmid, (size_t)dimfast, (size_t)padding)); @\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ARGUMENT);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_integerarray_wdims_sf",@\\ \mbox{}\verb@[ "int compression", "int binary_id","(binary) String data", @\\ \mbox{}\verb@ "int elsize","int elements", "String byteorder", "int dimslow", "int dimmid", "int dimfast", "int padding"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_integerarray_wdims_fs":["""@\\ \mbox{}\verb@ /* CBFlib must NOT modify the data string nor the byteorder string@\\ \mbox{}\verb@ which belongs to the scripting @\\ \mbox{}\verb@ language we will get and check the length via a typemap */@\\ \mbox{}\verb@@\\ \mbox{}\verb@%apply (char *STRING, int LENGTH) { (char *data, int len) } set_integerarray_wdims_fs;@\\ \mbox{}\verb@%apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_integerarray_wdims_fs;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void set_integerarray_wdims_fs(unsigned int compression, int binary_id, @\\ \mbox{}\verb@ char *data, int len, int elsize, int elsigned, int elements,@\\ \mbox{}\verb@ char *bo, int bolen, int dimfast, int dimmid, int dimslow, int padding){@\\ \mbox{}\verb@ /* safety check on args */@\\ \mbox{}\verb@ size_t els, ele;@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ char byteorder[15];@\\ \mbox{}\verb@ if(len == elsize*elements && elements==dimfast*dimmid*dimslow){@\\ \mbox{}\verb@ array = data;@\\ \mbox{}\verb@ els = elsize;@\\ \mbox{}\verb@ ele = elements;@\\ \mbox{}\verb@ strncpy(byteorder,bo,bolen<15?bolen:14);@\\ \mbox{}\verb@ byteorder[bolen<15?14:bolen] = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_set_integerarray_wdims_fs (self, compression, binary_id, @\\ \mbox{}\verb@ (void *) data, (size_t) elsize, elsigned, (size_t) elements, (const char *)byteorder,@\\ \mbox{}\verb@ (size_t)dimfast, (size_t)dimmid, (size_t)dimslow, (size_t)padding)); @\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ARGUMENT);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_integerarray_wdims_fs",@\\ \mbox{}\verb@[ "int compression", "int binary_id","(binary) String data", @\\ \mbox{}\verb@ "int elsize","int elements", "String byteorder", "int dimfast", "int dimmid", "int dimslow", "int padding"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_realarray":["""@\\ \mbox{}\verb@ /* CBFlib must NOT modify the data string which belongs to the scripting @\\ \mbox{}\verb@ language we will get and check the length via a typemap */@\\ \mbox{}\verb@@\\ \mbox{}\verb@%apply (char *STRING, int LENGTH) { (char *data, int len) } set_realarray;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void set_realarray(unsigned int compression, int binary_id, @\\ \mbox{}\verb@ char *data, int len, int elsize, int elements){@\\ \mbox{}\verb@ /* safety check on args */@\\ \mbox{}\verb@ size_t els, ele;@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ if(len == elsize*elements){@\\ \mbox{}\verb@ array = data;@\\ \mbox{}\verb@ els = elsize;@\\ \mbox{}\verb@ ele = elements;@\\ \mbox{}\verb@ cbf_failnez(cbf_set_realarray (self, compression, binary_id, @\\ \mbox{}\verb@ (void *) data, (size_t) elsize, (size_t) elements)); @\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ARGUMENT);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_realarray",@\\ \mbox{}\verb@[ "int compression", "int binary_id","(binary) String data", @\\ \mbox{}\verb@ "int elsize","int elements"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_realarray_wdims":["""@\\ \mbox{}\verb@ /* CBFlib must NOT modify the data string nor the byteorder string@\\ \mbox{}\verb@ which belongs to the scripting @\\ \mbox{}\verb@ language we will get and check the length via a typemap */@\\ \mbox{}\verb@@\\ \mbox{}\verb@%apply (char *STRING, int LENGTH) { (char *data, int len) } set_realarray_wdims;@\\ \mbox{}\verb@%apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_realarray_wdims;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void set_realarray_wdims(unsigned int compression, int binary_id, @\\ \mbox{}\verb@ char *data, int len, int elsize, int elements,@\\ \mbox{}\verb@ char *bo, int bolen, int dimfast, int dimmid, int dimslow, int padding){@\\ \mbox{}\verb@ /* safety check on args */@\\ \mbox{}\verb@ size_t els, ele;@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ char byteorder[15];@\\ \mbox{}\verb@ if(len == elsize*elements && elements==dimfast*dimmid*dimslow){@\\ \mbox{}\verb@ array = data;@\\ \mbox{}\verb@ els = elsize;@\\ \mbox{}\verb@ ele = elements;@\\ \mbox{}\verb@ strncpy(byteorder,bo,bolen<15?bolen:14);@\\ \mbox{}\verb@ byteorder[bolen<15?14:bolen] = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_set_realarray_wdims (self, compression, binary_id, @\\ \mbox{}\verb@ (void *) data, (size_t) elsize, (size_t) elements, (const char *)byteorder,@\\ \mbox{}\verb@ (size_t)dimfast, (size_t)dimmid, (size_t)dimslow, (size_t)padding)); @\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ARGUMENT);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_realarray_wdims",@\\ \mbox{}\verb@[ "int compression", "int binary_id","(binary) String data", @\\ \mbox{}\verb@ "int elsize","int elements", "String byteorder", "int dimfast", "int dimmid", "int dimslow", "int padding"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_realarray_wdims_sf":["""@\\ \mbox{}\verb@ /* CBFlib must NOT modify the data string nor the byteorder string@\\ \mbox{}\verb@ which belongs to the scripting @\\ \mbox{}\verb@ language we will get and check the length via a typemap */@\\ \mbox{}\verb@@\\ \mbox{}\verb@%apply (char *STRING, int LENGTH) { (char *data, int len) } set_realarray_wdims_sf;@\\ \mbox{}\verb@%apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_realarray_wdims_sf;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void set_realarray_wdims_sf(unsigned int compression, int binary_id, @\\ \mbox{}\verb@ char *data, int len, int elsize, int elements,@\\ \mbox{}\verb@ char *bo, int bolen, int dimslow, int dimmid, int dimfast, int padding){@\\ \mbox{}\verb@ /* safety check on args */@\\ \mbox{}\verb@ size_t els, ele;@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ char byteorder[15];@\\ \mbox{}\verb@ if(len == elsize*elements && elements==dimfast*dimmid*dimslow){@\\ \mbox{}\verb@ array = data;@\\ \mbox{}\verb@ els = elsize;@\\ \mbox{}\verb@ ele = elements;@\\ \mbox{}\verb@ strncpy(byteorder,bo,bolen<15?bolen:14);@\\ \mbox{}\verb@ byteorder[bolen<15?14:bolen] = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_set_realarray_wdims_sf (self, compression, binary_id, @\\ \mbox{}\verb@ (void *) data, (size_t) elsize, (size_t) elements, (const char *)byteorder,@\\ \mbox{}\verb@ (size_t) dimslow, (size_t) dimmid, (size_t) dimfast, (size_t)padding)); @\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ARGUMENT);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_realarray_wdims_sf",@\\ \mbox{}\verb@[ "int compression", "int binary_id","(binary) String data", @\\ \mbox{}\verb@ "int elsize","int elements", "String byteorder", "int dimslow", "int dimmid", "int dimfast", "int padding"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_realarray_wdims_fs":["""@\\ \mbox{}\verb@ /* CBFlib must NOT modify the data string nor the byteorder string@\\ \mbox{}\verb@ which belongs to the scripting @\\ \mbox{}\verb@ language we will get and check the length via a typemap */@\\ \mbox{}\verb@@\\ \mbox{}\verb@%apply (char *STRING, int LENGTH) { (char *data, int len) } set_realarray_wdims_fs;@\\ \mbox{}\verb@%apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_realarray_wdims_fs;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void set_realarray_wdims_fs(unsigned int compression, int binary_id, @\\ \mbox{}\verb@ char *data, int len, int elsize, int elements,@\\ \mbox{}\verb@ char *bo, int bolen, int dimfast, int dimmid, int dimslow, int padding){@\\ \mbox{}\verb@ /* safety check on args */@\\ \mbox{}\verb@ size_t els, ele;@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ char byteorder[15];@\\ \mbox{}\verb@ if(len == elsize*elements && elements==dimfast*dimmid*dimslow){@\\ \mbox{}\verb@ array = data;@\\ \mbox{}\verb@ els = elsize;@\\ \mbox{}\verb@ ele = elements;@\\ \mbox{}\verb@ strncpy(byteorder,bo,bolen<15?bolen:14);@\\ \mbox{}\verb@ byteorder[bolen<15?14:bolen] = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_set_realarray_wdims_fs (self, compression, binary_id, @\\ \mbox{}\verb@ (void *) data, (size_t) elsize, (size_t) elements, (const char *)byteorder,@\\ \mbox{}\verb@ (size_t) dimfast, (size_t) dimmid, (size_t) dimslow, (size_t)padding)); @\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ARGUMENT);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_realarray_wdims_fs",@\\ \mbox{}\verb@[ "int compression", "int binary_id","(binary) String data", @\\ \mbox{}\verb@ "int elsize","int elements", "String byteorder", "int dimfast", "int dimmid", "int dimslow", "int padding"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_image":["""@\\ \mbox{}\verb@ /* CBFlib must NOT modify the data string which belongs to the scripting @\\ \mbox{}\verb@ language we will get and check the length via a typemap */@\\ \mbox{}\verb@@\\ \mbox{}\verb@%apply (char *STRING, int LENGTH) { (char *data, int len) } set_image;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void set_image(unsigned int element_number,@\\ \mbox{}\verb@ unsigned int compression, @\\ \mbox{}\verb@ char *data, int len, int elsize, int elsign, int ndimslow, int ndimfast){@\\ \mbox{}\verb@ /* safety check on args */@\\ \mbox{}\verb@ size_t els;@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ if(len == elsize*ndimslow*ndimfast){@\\ \mbox{}\verb@ array = data;@\\ \mbox{}\verb@ els = elsize;@\\ \mbox{}\verb@ reserved = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_set_image (self, reserved, element_number, compression,@\\ \mbox{}\verb@ (void *) data, (size_t) elsize, elsign, (size_t) ndimslow, (size_t)ndimfast)); @\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ARGUMENT);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_image",@\\ \mbox{}\verb@[ "int element_number","int compression","(binary) String data", @\\ \mbox{}\verb@ "int elsize", "int elsign", "int dimslow", "int dimfast"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_image_fs":["""@\\ \mbox{}\verb@ /* CBFlib must NOT modify the data string which belongs to the scripting @\\ \mbox{}\verb@ language we will get and check the length via a typemap */@\\ \mbox{}\verb@@\\ \mbox{}\verb@%apply (char *STRING, int LENGTH) { (char *data, int len) } set_image;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void set_image_fs(unsigned int element_number,@\\ \mbox{}\verb@ unsigned int compression, @\\ \mbox{}\verb@ char *data, int len, int elsize, int elsign, int ndimfast, int ndimslow){@\\ \mbox{}\verb@ /* safety check on args */@\\ \mbox{}\verb@ size_t els;@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ if(len == elsize*ndimslow*ndimfast){@\\ \mbox{}\verb@ array = data;@\\ \mbox{}\verb@ els = elsize;@\\ \mbox{}\verb@ reserved = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_set_image (self, reserved, element_number, compression,@\\ \mbox{}\verb@ (void *) data, (size_t) elsize, elsign, (size_t) ndimfast, (size_t)ndimslow)); @\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ARGUMENT);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_image_fs",@\\ \mbox{}\verb@[ "int element_number","int compression","(binary) String data", @\\ \mbox{}\verb@ "int elsize", "int elsign", "int dimfast", "int dimslow"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_image_sf":["""@\\ \mbox{}\verb@ /* CBFlib must NOT modify the data string which belongs to the scripting @\\ \mbox{}\verb@ language we will get and check the length via a typemap */@\\ \mbox{}\verb@@\\ \mbox{}\verb@%apply (char *STRING, int LENGTH) { (char *data, int len) } set_image_sf;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void set_image_sf(unsigned int element_number,@\\ \mbox{}\verb@ unsigned int compression, @\\ \mbox{}\verb@ char *data, int len, int elsize, int elsign, int ndimslow, int ndimfast){@\\ \mbox{}\verb@ /* safety check on args */@\\ \mbox{}\verb@ size_t els;@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ if(len == elsize*ndimslow*ndimfast){@\\ \mbox{}\verb@ array = data;@\\ \mbox{}\verb@ els = elsize;@\\ \mbox{}\verb@ reserved = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_set_image_sf (self, reserved, element_number, compression,@\\ \mbox{}\verb@ (void *) data, (size_t) elsize, elsign, (size_t) ndimslow, (size_t)ndimfast)); @\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ARGUMENT);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_image_sf",@\\ \mbox{}\verb@[ "int element_number","int compression","(binary) String data", @\\ \mbox{}\verb@ "int elsize", "int elsign", "int dimslow", "int dimfast"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_real_image":["""@\\ \mbox{}\verb@ /* CBFlib must NOT modify the data string which belongs to the scripting @\\ \mbox{}\verb@ language we will get and check the length via a typemap */@\\ \mbox{}\verb@@\\ \mbox{}\verb@%apply (char *STRING, int LENGTH) { (char *data, int len) } set_real_image;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void set_real_image(unsigned int element_number,@\\ \mbox{}\verb@ unsigned int compression, @\\ \mbox{}\verb@ char *data, int len, int elsize, int ndimslow, int ndimfast){@\\ \mbox{}\verb@ /* safety check on args */@\\ \mbox{}\verb@ size_t els;@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ if(len == elsize*ndimslow*ndimfast){@\\ \mbox{}\verb@ array = data;@\\ \mbox{}\verb@ els = elsize;@\\ \mbox{}\verb@ reserved = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_set_real_image (self, reserved, element_number, compression,@\\ \mbox{}\verb@ (void *) data, (size_t) elsize, (size_t) ndimslow, (size_t)ndimfast)); @\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ARGUMENT);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_real_image",@\\ \mbox{}\verb@[ "int element_number","int compression","(binary) String data", @\\ \mbox{}\verb@ "int elsize", "int dimslow", "int dimfast"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_real_image_fs":["""@\\ \mbox{}\verb@ /* CBFlib must NOT modify the data string which belongs to the scripting @\\ \mbox{}\verb@ language we will get and check the length via a typemap */@\\ \mbox{}\verb@@\\ \mbox{}\verb@%apply (char *STRING, int LENGTH) { (char *data, int len) } set_real_image;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void set_real_image_fs(unsigned int element_number,@\\ \mbox{}\verb@ unsigned int compression, @\\ \mbox{}\verb@ char *data, int len, int elsize, int ndimfast, int ndimslow){@\\ \mbox{}\verb@ /* safety check on args */@\\ \mbox{}\verb@ size_t els;@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ if(len == elsize*ndimslow*ndimfast){@\\ \mbox{}\verb@ array = data;@\\ \mbox{}\verb@ els = elsize;@\\ \mbox{}\verb@ reserved = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_set_real_image_fs (self, reserved, element_number, compression,@\\ \mbox{}\verb@ (void *) data, (size_t) elsize, (size_t) ndimfast, (size_t)ndimslow)); @\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ARGUMENT);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_real_image_fs",@\\ \mbox{}\verb@[ "int element_number","int compression","(binary) String data", @\\ \mbox{}\verb@ "int elsize", "int dimfast", "int dimslow"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_real_image_sf":["""@\\ \mbox{}\verb@ /* CBFlib must NOT modify the data string which belongs to the scripting @\\ \mbox{}\verb@ language we will get and check the length via a typemap */@\\ \mbox{}\verb@@\\ \mbox{}\verb@%apply (char *STRING, int LENGTH) { (char *data, int len) } set_real_image_sf;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void set_real_image_sf(unsigned int element_number,@\\ \mbox{}\verb@ unsigned int compression, @\\ \mbox{}\verb@ char *data, int len, int elsize, int ndimslow, int ndimfast){@\\ \mbox{}\verb@ /* safety check on args */@\\ \mbox{}\verb@ size_t els;@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ if(len == elsize*ndimslow*ndimfast){@\\ \mbox{}\verb@ array = data;@\\ \mbox{}\verb@ els = elsize;@\\ \mbox{}\verb@ reserved = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_set_real_image_sf (self, reserved, element_number, compression,@\\ \mbox{}\verb@ (void *) data, (size_t) elsize, (size_t) ndimslow, (size_t)ndimfast)); @\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ARGUMENT);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_real_image_sf",@\\ \mbox{}\verb@[ "int element_number","int compression","(binary) String data", @\\ \mbox{}\verb@ "int elsize", "int dimslow", "int dimfast"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_3d_image":["""@\\ \mbox{}\verb@ /* CBFlib must NOT modify the data string which belongs to the scripting @\\ \mbox{}\verb@ language we will get and check the length via a typemap */@\\ \mbox{}\verb@@\\ \mbox{}\verb@%apply (char *STRING, int LENGTH) { (char *data, int len) } set_3d_image;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void set_3d_image(unsigned int element_number,@\\ \mbox{}\verb@ unsigned int compression, @\\ \mbox{}\verb@ char *data, int len, int elsize, int elsign, int ndimslow, int ndimmid, int ndimfast){@\\ \mbox{}\verb@ /* safety check on args */@\\ \mbox{}\verb@ size_t els;@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ if(len == elsize*ndimslow*ndimmid*ndimfast){@\\ \mbox{}\verb@ array = data;@\\ \mbox{}\verb@ els = elsize;@\\ \mbox{}\verb@ reserved = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_set_3d_image (self, reserved, element_number, compression,@\\ \mbox{}\verb@ (void *) data, (size_t) elsize, elsign, (size_t) ndimslow, (size_t) ndimmid, (size_t)ndimfast)); @\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ARGUMENT);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_3d_image",@\\ \mbox{}\verb@[ "int element_number","int compression","(binary) String data", @\\ \mbox{}\verb@ "int elsize", "int elsign", "int dimslow", "int dimmid", "int dimfast"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_3d_image_fs":["""@\\ \mbox{}\verb@ /* CBFlib must NOT modify the data string which belongs to the scripting @\\ \mbox{}\verb@ language we will get and check the length via a typemap */@\\ \mbox{}\verb@@\\ \mbox{}\verb@%apply (char *STRING, int LENGTH) { (char *data, int len) } set_3d_image;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void set_3d_image_fs(unsigned int element_number,@\\ \mbox{}\verb@ unsigned int compression, @\\ \mbox{}\verb@ char *data, int len, int elsize, int elsign, int ndimfast, int ndimmid, int ndimslow){@\\ \mbox{}\verb@ /* safety check on args */@\\ \mbox{}\verb@ size_t els;@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ if(len == elsize*ndimslow*ndimmid*ndimfast){@\\ \mbox{}\verb@ array = data;@\\ \mbox{}\verb@ els = elsize;@\\ \mbox{}\verb@ reserved = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_set_3d_image_fs (self, reserved, element_number, compression,@\\ \mbox{}\verb@ (void *) data, (size_t) elsize, elsign, (size_t) ndimfast, (size_t) ndimmid, (size_t)ndimslow)); @\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ARGUMENT);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_3d_image_fs",@\\ \mbox{}\verb@[ "int element_number","int compression","(binary) String data", @\\ \mbox{}\verb@ "int elsize", "int elsign", "int dimfast", "int dimmid", "int dimslow"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_3d_image_sf":["""@\\ \mbox{}\verb@ /* CBFlib must NOT modify the data string which belongs to the scripting @\\ \mbox{}\verb@ language we will get and check the length via a typemap */@\\ \mbox{}\verb@@\\ \mbox{}\verb@%apply (char *STRING, int LENGTH) { (char *data, int len) } set_3d_image;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void set_3d_image_sf(unsigned int element_number,@\\ \mbox{}\verb@ unsigned int compression, @\\ \mbox{}\verb@ char *data, int len, int elsize, int elsign, int ndimslow, int ndimmid, int ndimfast){@\\ \mbox{}\verb@ /* safety check on args */@\\ \mbox{}\verb@ size_t els;@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ if(len == elsize*ndimslow*ndimmid*ndimfast){@\\ \mbox{}\verb@ array = data;@\\ \mbox{}\verb@ els = elsize;@\\ \mbox{}\verb@ reserved = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_set_3d_image_sf (self, reserved, element_number, compression,@\\ \mbox{}\verb@ (void *) data, (size_t) elsize, elsign, (size_t) ndimslow, (size_t) ndimmid, (size_t)ndimfast)); @\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ARGUMENT);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_3d_image_sf",@\\ \mbox{}\verb@[ "int element_number","int compression","(binary) String data", @\\ \mbox{}\verb@ "int elsize", "int elsign", "int dimslow", "int dimmid", "int dimfast"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_real_3d_image":["""@\\ \mbox{}\verb@ /* CBFlib must NOT modify the data string which belongs to the scripting @\\ \mbox{}\verb@ language we will get and check the length via a typemap */@\\ \mbox{}\verb@@\\ \mbox{}\verb@%apply (char *STRING, int LENGTH) { (char *data, int len) } set_real_3d_image_sf;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void set_real_3d_image(unsigned int element_number,@\\ \mbox{}\verb@ unsigned int compression, @\\ \mbox{}\verb@ char *data, int len, int elsize, int ndimslow, int ndimmid, int ndimfast){@\\ \mbox{}\verb@ /* safety check on args */@\\ \mbox{}\verb@ size_t els;@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ if(len == elsize*ndimslow*ndimmid*ndimfast){@\\ \mbox{}\verb@ array = data;@\\ \mbox{}\verb@ els = elsize;@\\ \mbox{}\verb@ reserved = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_set_real_3d_image (self, reserved, element_number, compression,@\\ \mbox{}\verb@ (void *) data, (size_t) elsize, (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast)); @\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ARGUMENT);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_real_3d_image",@\\ \mbox{}\verb@[ "int element_number","int compression","(binary) String data", @\\ \mbox{}\verb@ "int elsize", "int dimslow", "int dimmid", "int dimfast"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_real_3d_image_fs":["""@\\ \mbox{}\verb@ /* CBFlib must NOT modify the data string which belongs to the scripting @\\ \mbox{}\verb@ language we will get and check the length via a typemap */@\\ \mbox{}\verb@@\\ \mbox{}\verb@%apply (char *STRING, int LENGTH) { (char *data, int len) } set_real_3d_image_fs;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void set_real_3d_image_fs(unsigned int element_number,@\\ \mbox{}\verb@ unsigned int compression, @\\ \mbox{}\verb@ char *data, int len, int elsize, int ndimfast, int ndimmid, int ndimslow){@\\ \mbox{}\verb@ /* safety check on args */@\\ \mbox{}\verb@ size_t els;@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ if(len == elsize*ndimslow*ndimmid*ndimfast){@\\ \mbox{}\verb@ array = data;@\\ \mbox{}\verb@ els = elsize;@\\ \mbox{}\verb@ reserved = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_set_real_3d_image_fs (self, reserved, element_number, compression,@\\ \mbox{}\verb@ (void *) data, (size_t) elsize, (size_t) ndimfast, (size_t)ndimmid, (size_t)ndimslow)); @\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ARGUMENT);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_real_3d_image_fs",@\\ \mbox{}\verb@[ "int element_number","int compression","(binary) String data", @\\ \mbox{}\verb@ "int elsize", "int dimfast", "int dimmid", "int dimslow"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_real_3d_image_sf":["""@\\ \mbox{}\verb@ /* CBFlib must NOT modify the data string which belongs to the scripting @\\ \mbox{}\verb@ language we will get and check the length via a typemap */@\\ \mbox{}\verb@@\\ \mbox{}\verb@%apply (char *STRING, int LENGTH) { (char *data, int len) } set_real_3d_image_sf;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void set_real_3d_image_sf(unsigned int element_number,@\\ \mbox{}\verb@ unsigned int compression, @\\ \mbox{}\verb@ char *data, int len, int elsize, int ndimslow, int ndimmid, int ndimfast){@\\ \mbox{}\verb@ /* safety check on args */@\\ \mbox{}\verb@ size_t els;@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ void *array;@\\ \mbox{}\verb@ if(len == elsize*ndimslow*ndimmid*ndimfast){@\\ \mbox{}\verb@ array = data;@\\ \mbox{}\verb@ els = elsize;@\\ \mbox{}\verb@ reserved = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_set_real_3d_image_sf (self, reserved, element_number, compression,@\\ \mbox{}\verb@ (void *) data, (size_t) elsize, (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast)); @\\ \mbox{}\verb@ }else{@\\ \mbox{}\verb@ cbf_failnez(CBF_ARGUMENT);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_real_3d_image_sf",@\\ \mbox{}\verb@[ "int element_number","int compression","(binary) String data", @\\ \mbox{}\verb@ "int elsize", "int dimslow", "int dimmid", "int dimfast"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_image_size": ["""@\\ \mbox{}\verb@%apply int *OUTPUT {int *ndimslow, int *ndimfast} get_image_size;@\\ \mbox{}\verb@ void get_image_size(unsigned int element_number, int *ndimslow, int *ndimfast){@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ size_t inslow, infast;@\\ \mbox{}\verb@ reserved = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_get_image_size(self,reserved,element_number,&inslow,&infast));@\\ \mbox{}\verb@ *ndimslow = (int)inslow;@\\ \mbox{}\verb@ *ndimfast = (int)infast; @\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_image_size",["Integer element_number"],["size_t ndim1","size_t ndim2"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_image_size_fs": ["""@\\ \mbox{}\verb@%apply int *OUTPUT {int *ndimfast, int *ndimslow} get_image_size_fs;@\\ \mbox{}\verb@ void get_image_size_fs(unsigned int element_number, int *ndimfast, int *ndimslow){@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ size_t infast, inslow;@\\ \mbox{}\verb@ reserved = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_get_image_size_fs(self,reserved,element_number,&infast,&inslow));@\\ \mbox{}\verb@ *ndimfast = (int)infast; /* FIXME - is that how to convert? */@\\ \mbox{}\verb@ *ndimslow = (int)inslow; @\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_image_size_fs",["Integer element_number"],["size_t ndimfast","size_t ndimslow"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_image_size_sf": ["""@\\ \mbox{}\verb@%apply int *OUTPUT {int *ndimslow, int *ndimfast} get_image_size_sf;@\\ \mbox{}\verb@ void get_image_size_sf(unsigned int element_number, int *ndimslow, int *ndimfast){@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ size_t inslow, infast;@\\ \mbox{}\verb@ reserved = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_get_image_size(self,reserved,element_number,&inslow,&infast));@\\ \mbox{}\verb@ *ndimslow = (int)inslow;@\\ \mbox{}\verb@ *ndimfast = (int)infast; @\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_image_size_sf",["Integer element_number"],["size_t ndimslow","size_t ndimfast"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_3d_image_size": ["""@\\ \mbox{}\verb@%apply int *OUTPUT {int *ndimslow, int *ndimmid, int *ndimfast} get_3d_image_size;@\\ \mbox{}\verb@ void get_3d_image_size(unsigned int element_number, int *ndimslow, int *ndimmid, int *ndimfast){@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ size_t inslow, inmid, infast;@\\ \mbox{}\verb@ reserved = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_get_3d_image_size(self,reserved,element_number,&inslow,&inmid,&infast));@\\ \mbox{}\verb@ *ndimslow = (int)inslow; /* FIXME - is that how to convert? */@\\ \mbox{}\verb@ *ndimmid = (int)inmid; @\\ \mbox{}\verb@ *ndimfast = (int)infast;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_3d_image_size",["Integer element_number"],["size_t ndimslow","size_t ndimmid","size_t ndimfast"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_3d_image_size_fs": ["""@\\ \mbox{}\verb@%apply int *OUTPUT {int *ndimslow, int *ndimmid, int *ndimfast} get_3d_image_size;@\\ \mbox{}\verb@ void get_3d_image_size_fs(unsigned int element_number, int *ndimfast, int *ndimmid, int *ndimslow){@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ size_t inslow, inmid, infast;@\\ \mbox{}\verb@ reserved = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_get_3d_image_size_fs(self,reserved,element_number,&infast,&inmid,&inslow));@\\ \mbox{}\verb@ *ndimslow = (int)inslow; /* FIXME - is that how to convert? */@\\ \mbox{}\verb@ *ndimmid = (int)inmid; @\\ \mbox{}\verb@ *ndimfast = (int)infast;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_3d_image_size",["Integer element_number"],["size_t ndimfast","size_t ndimmid","size_t ndimslow"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_3d_image_size_sf": ["""@\\ \mbox{}\verb@%apply int *OUTPUT {int *ndimslow, int *ndimmid, int *ndimfast} get_3d_image_size_sf;@\\ \mbox{}\verb@ void get_3d_image_size_sf(unsigned int element_number, int *ndimslow, int *ndimmid, int *ndimfast){@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ size_t inslow, inmid, infast;@\\ \mbox{}\verb@ reserved = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_get_3d_image_size_sf(self,reserved,element_number,&inslow,&inmid,&infast));@\\ \mbox{}\verb@ *ndimslow = (int)inslow; /* FIXME - is that how to convert? */@\\ \mbox{}\verb@ *ndimmid = (int)inmid; @\\ \mbox{}\verb@ *ndimfast = (int)infast;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_3d_image_size_sf",["Integer element_number"],["size_t ndimslow","size_t ndimmid","size_t ndimfast"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_pixel_size" : ["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *psize} get_pixel_size;@\\ \mbox{}\verb@ void get_pixel_size(unsigned int element_number, @\\ \mbox{}\verb@ unsigned int axis_number, double *psize){@\\ \mbox{}\verb@ cbf_failnez(cbf_get_pixel_size(self, @\\ \mbox{}\verb@ element_number, @\\ \mbox{}\verb@ axis_number, @\\ \mbox{}\verb@ psize));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_pixel_size",["Int element_number","Int axis_number"],@\\ \mbox{}\verb@ ["Float pixel_size"]] ,@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_pixel_size_fs" : ["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *psize} get_pixel_size;@\\ \mbox{}\verb@ void get_pixel_size_fs(unsigned int element_number, @\\ \mbox{}\verb@ unsigned int axis_number, double *psize){@\\ \mbox{}\verb@ cbf_failnez(cbf_get_pixel_size_fs(self, @\\ \mbox{}\verb@ element_number, @\\ \mbox{}\verb@ axis_number, @\\ \mbox{}\verb@ psize));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_pixel_size_fs",["Int element_number","Int axis_number"],@\\ \mbox{}\verb@ ["Float pixel_size"]] ,@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_pixel_size_sf" : ["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *psize} get_pixel_size;@\\ \mbox{}\verb@ void get_pixel_size_sf(unsigned int element_number, @\\ \mbox{}\verb@ unsigned int axis_number, double *psize){@\\ \mbox{}\verb@ cbf_failnez(cbf_get_pixel_size_sf(self, @\\ \mbox{}\verb@ element_number, @\\ \mbox{}\verb@ axis_number, @\\ \mbox{}\verb@ psize));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_pixel_size_sf",["Int element_number","Int axis_number"],@\\ \mbox{}\verb@ ["Float pixel_size"]] ,@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_pixel_size":["""@\\ \mbox{}\verb@ void set_pixel_size (unsigned int element_number, @\\ \mbox{}\verb@ unsigned int axis_number, double psize){@\\ \mbox{}\verb@ cbf_failnez(cbf_set_pixel_size(self, @\\ \mbox{}\verb@ element_number, @\\ \mbox{}\verb@ axis_number, @\\ \mbox{}\verb@ psize));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_pixel_size",@\\ \mbox{}\verb@ ["Int element_number","Int axis_number","Float pixel size"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_pixel_size_fs":["""@\\ \mbox{}\verb@ void set_pixel_size_fs (unsigned int element_number, @\\ \mbox{}\verb@ unsigned int axis_number, double psize){@\\ \mbox{}\verb@ cbf_failnez(cbf_set_pixel_size_fs(self, @\\ \mbox{}\verb@ element_number, @\\ \mbox{}\verb@ axis_number, @\\ \mbox{}\verb@ psize));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_pixel_size_fs",@\\ \mbox{}\verb@ ["Int element_number","Int axis_number","Float pixel size"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_pixel_size_sf":["""@\\ \mbox{}\verb@ void set_pixel_size_sf (unsigned int element_number, @\\ \mbox{}\verb@ unsigned int axis_number, double psize){@\\ \mbox{}\verb@ cbf_failnez(cbf_set_pixel_size_sf(self, @\\ \mbox{}\verb@ element_number, @\\ \mbox{}\verb@ axis_number, @\\ \mbox{}\verb@ psize));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_pixel_size_sf",@\\ \mbox{}\verb@ ["Int element_number","Int axis_number","Float pixel size"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_write_file" : ["""@\\ \mbox{}\verb@ void write_file(const char* filename, int ciforcbf, int headers, @\\ \mbox{}\verb@ int encoding){@\\ \mbox{}\verb@ FILE *stream;@\\ \mbox{}\verb@ int readable;@\\ \mbox{}\verb@ /* Make the file non-0 to make CBFlib close the file */@\\ \mbox{}\verb@ readable = 1;@\\ \mbox{}\verb@ if ( ! ( stream = fopen (filename, "w+b")) ){@\\ \mbox{}\verb@ cbf_failnez(CBF_FILEOPEN);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ else{@\\ \mbox{}\verb@ cbf_failnez(cbf_write_file(self, stream, readable, @\\ \mbox{}\verb@ ciforcbf, headers, encoding));@\\ \mbox{}\verb@@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","write_file",["String filename","Integer ciforcbf","Integer Headers", @\\ \mbox{}\verb@ "Integer encoding"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_write_widefile" : ["""@\\ \mbox{}\verb@ void write_widefile(const char* filename, int ciforcbf, int headers, @\\ \mbox{}\verb@ int encoding){@\\ \mbox{}\verb@ FILE *stream;@\\ \mbox{}\verb@ int readable;@\\ \mbox{}\verb@ /* Make the file non-0 to make CBFlib close the file */@\\ \mbox{}\verb@ readable = 1;@\\ \mbox{}\verb@ if ( ! ( stream = fopen (filename, "w+b")) ){@\\ \mbox{}\verb@ cbf_failnez(CBF_FILEOPEN);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ else{@\\ \mbox{}\verb@ cbf_failnez(cbf_write_widefile(self, stream, readable, @\\ \mbox{}\verb@ ciforcbf, headers, encoding));@\\ \mbox{}\verb@@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","write_widefile",["String filename","Integer ciforcbf","Integer Headers", @\\ \mbox{}\verb@ "Integer encoding"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_read_template":["""@\\ \mbox{}\verb@ void read_template(char* filename){@\\ \mbox{}\verb@ /* CBFlib needs a stream that will remain open @\\ \mbox{}\verb@ hence DO NOT open from python */@\\ \mbox{}\verb@ FILE *stream;@\\ \mbox{}\verb@ if ( ! ( stream = fopen (filename, "rb")) ){@\\ \mbox{}\verb@ cbf_failnez(CBF_FILEOPEN);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ else{@\\ \mbox{}\verb@ cbf_failnez(cbf_read_template (self, stream)); }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@@\\ \mbox{}\verb@""","read_template",["String filename"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_read_file" : ["""@\\ \mbox{}\verb@ void read_file(char* filename, int headers){@\\ \mbox{}\verb@ /* CBFlib needs a stream that will remain open @\\ \mbox{}\verb@ hence DO NOT open from python */@\\ \mbox{}\verb@ FILE *stream;@\\ \mbox{}\verb@ if ( ! ( stream = fopen (filename, "rb")) ){@\\ \mbox{}\verb@ cbf_failnez(CBF_FILEOPEN);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ else{@\\ \mbox{}\verb@ cbf_failnez(cbf_read_file(self, stream, headers)); @\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","read_file",["String filename","Integer headers"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_read_widefile" : ["""@\\ \mbox{}\verb@ void read_widefile(char* filename, int headers){@\\ \mbox{}\verb@ /* CBFlib needs a stream that will remain open @\\ \mbox{}\verb@ hence DO NOT open from python */@\\ \mbox{}\verb@ FILE *stream;@\\ \mbox{}\verb@ if ( ! ( stream = fopen (filename, "rb")) ){@\\ \mbox{}\verb@ cbf_failnez(CBF_FILEOPEN);@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ else{@\\ \mbox{}\verb@ cbf_failnez(cbf_read_widefile(self, stream, headers)); @\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","read_widefile",["String filename","Integer headers"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_doublevalue":["""@\\ \mbox{}\verb@ void set_doublevalue(const char *format, double number){@\\ \mbox{}\verb@ cbf_failnez(cbf_set_doublevalue(self,format,number));}@\\ \mbox{}\verb@""","set_doublevalue",["String format","Float number"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_require_integervalue":["""@\\ \mbox{}\verb@%apply int *OUTPUT {int *number} require_integervalue;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void require_integervalue(int *number, int thedefault){@\\ \mbox{}\verb@@\\ \mbox{}\verb@ cbf_failnez(cbf_require_integervalue(self,number,thedefault));@\\ \mbox{}\verb@@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","require_integervalue", ["Int thedefault"],["Int number"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_require_doublevalue":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *number} require_doublevalue;@\\ \mbox{}\verb@void require_doublevalue(double *number, double defaultvalue){@\\ \mbox{}\verb@ cbf_failnez(cbf_require_doublevalue(self,number,defaultvalue));@\\ \mbox{}\verb@}@\\ \mbox{}\verb@""","require_doublevalue",["Float Default"],["Float Number"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_require_column_value":["""@\\ \mbox{}\verb@ const char* require_column_value(const char *columnname,@\\ \mbox{}\verb@ const char *defaultvalue){@\\ \mbox{}\verb@ const char * result;@\\ \mbox{}\verb@ cbf_failnez(cbf_require_column_value(self,columnname,@\\ \mbox{}\verb@ &result,defaultvalue));@\\ \mbox{}\verb@ return result;@\\ \mbox{}\verb@}@\\ \mbox{}\verb@""","require_column_value",@\\ \mbox{}\verb@ ["String columnnanme","String Default"],["String Name"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_require_column_doublevalue":["""@\\ \mbox{}\verb@%apply double *OUTPUT { double *number} require_column_doublevalue;@\\ \mbox{}\verb@void require_column_doublevalue(const char *columnname, double * number,@\\ \mbox{}\verb@ const double defaultvalue){@\\ \mbox{}\verb@ cbf_failnez(cbf_require_column_doublevalue(self,@\\ \mbox{}\verb@ columnname,number,defaultvalue));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","require_column_doublevalue",["String columnname","Float Value"],@\\ \mbox{}\verb@ ["Float defaultvalue"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_require_column_integervalue":["""@\\ \mbox{}\verb@%apply int *OUTPUT {int *number} require_column_integervalue;@\\ \mbox{}\verb@void require_column_integervalue(const char *columnname, @\\ \mbox{}\verb@ int *number, const int defaultvalue){@\\ \mbox{}\verb@ cbf_failnez(cbf_require_column_integervalue(self,@\\ \mbox{}\verb@ columnname, number,defaultvalue));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","require_column_integervalue",["String Columnvalue","Int default"],@\\ \mbox{}\verb@ ["Int Value"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@ @\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_require_value" : ["""@\\ \mbox{}\verb@@\\ \mbox{}\verb@ const char* require_value(const char* defaultvalue){@\\ \mbox{}\verb@ const char * result;@\\ \mbox{}\verb@ cbf_failnez(cbf_require_value(self, &result, defaultvalue));@\\ \mbox{}\verb@ return result;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","require_value",["String defaultvalue"],['String Value']],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_require_diffrn_id":["""@\\ \mbox{}\verb@ const char* require_diffrn_id(const char* defaultid){@\\ \mbox{}\verb@ const char * id;@\\ \mbox{}\verb@ cbf_failnez(cbf_require_diffrn_id(self,&id,defaultid));@\\ \mbox{}\verb@ return id;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","require_diffrn_id", ["String Default_id"],["String diffrn_id"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_polarization":["""@\\ \mbox{}\verb@ /* Returns a pair of double values */@\\ \mbox{}\verb@%apply double *OUTPUT { double *in1, double *in2 };@\\ \mbox{}\verb@ void get_polarization(double *in1,double *in2){@\\ \mbox{}\verb@ cbf_failnez(cbf_get_polarization (self, in1, in2));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_polarization",[],@\\ \mbox{}\verb@ ["float polarizn_source_ratio","float polarizn_source_norm"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_polarization":["""@\\ \mbox{}\verb@ void set_polarization (double polarizn_source_ratio,@\\ \mbox{}\verb@ double polarizn_source_norm){@\\ \mbox{}\verb@ cbf_failnez(cbf_set_polarization(self,@\\ \mbox{}\verb@ polarizn_source_ratio,@\\ \mbox{}\verb@ polarizn_source_norm));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_polarization",@\\ \mbox{}\verb@ ["Float polarizn_source_ratio","Float polarizn_source_norm"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_divergence":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *div_x_source, double *div_y_source,@\\ \mbox{}\verb@ double *div_x_y_source } get_divergence;@\\ \mbox{}\verb@ void get_divergence(double *div_x_source, double *div_y_source,@\\ \mbox{}\verb@ double *div_x_y_source){@\\ \mbox{}\verb@ cbf_failnez(cbf_get_divergence(self, @\\ \mbox{}\verb@ div_x_source, @\\ \mbox{}\verb@ div_y_source,@\\ \mbox{}\verb@ div_x_y_source)); @\\ \mbox{}\verb@ } @\\ \mbox{}\verb@""","get_divergence",[],@\\ \mbox{}\verb@ ["Float div_x_source","Float div_y_source","Float div_x_y_source"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_divergence":["""@\\ \mbox{}\verb@ void set_divergence ( double div_x_source, double div_y_source,@\\ \mbox{}\verb@ double div_x_y_source){@\\ \mbox{}\verb@ cbf_failnez(cbf_set_divergence (self, div_x_source, @\\ \mbox{}\verb@ div_y_source,div_x_y_source));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_divergence",@\\ \mbox{}\verb@ ["Float div_x_source","Float div_y_source","Float div_x_y_source"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_gain":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *gain, double *gain_esd} get_gain;@\\ \mbox{}\verb@ void get_gain (unsigned int element_number, double *gain, @\\ \mbox{}\verb@ double *gain_esd){@\\ \mbox{}\verb@ cbf_failnez(cbf_get_gain (self, element_number, gain, gain_esd));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_gain",@\\ \mbox{}\verb@ [],["Float gain", "Float gain_esd"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_gain":["""@\\ \mbox{}\verb@ void set_gain (unsigned int element_number, double gain, double gain_esd){@\\ \mbox{}\verb@ cbf_failnez(cbf_set_gain (self, element_number, gain, gain_esd));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_gain",["Float gain", "Float gain_esd"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_element_id":["""@\\ \mbox{}\verb@ const char * get_element_id(unsigned int element_number){@\\ \mbox{}\verb@ const char * result;@\\ \mbox{}\verb@ cbf_failnez(cbf_get_element_id (self, element_number, &result));@\\ \mbox{}\verb@ return result;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_element_id", ["Integer element_number"],["String"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_axis_setting":["""@\\ \mbox{}\verb@ void set_axis_setting(const char *axis_id,@\\ \mbox{}\verb@ double start, double increment){@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ reserved = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_set_axis_setting(self,reserved,@\\ \mbox{}\verb@ axis_id,start,increment));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_axis_setting",["String axis_id", "Float start", "Float increment"],@\\ \mbox{}\verb@ []],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_axis_setting":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *start, double *increment} get_axis_setting;@\\ \mbox{}\verb@ void get_axis_setting(const char *axis_id,@\\ \mbox{}\verb@ double *start, double *increment){@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ reserved = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_get_axis_setting(self,reserved,axis_id,@\\ \mbox{}\verb@ start,increment));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_axis_setting",["String axis_id"],["Float start", "Float increment"],],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_datestamp":["""@\\ \mbox{}\verb@%apply int *OUTPUT {int *year, int *month, int *day, int *hour, @\\ \mbox{}\verb@ int *minute, double *second, int *timezone} get_datestamp;@\\ \mbox{}\verb@ void get_datestamp(int *year, int *month, int *day, int *hour, @\\ \mbox{}\verb@ int *minute, double *second, int *timezone){@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ reserved = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_get_datestamp(self,reserved,@\\ \mbox{}\verb@ year,month,day,hour,minute,second,timezone));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_datestamp",[],["int year", "int month", "int day", "int hour", @\\ \mbox{}\verb@"int minute", "double second", "int timezone"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_datestamp":["""@\\ \mbox{}\verb@ void set_datestamp(int year, int month, int day, int hour, @\\ \mbox{}\verb@ int minute, double second, int timezone, @\\ \mbox{}\verb@ double precision){@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ reserved = 0; @\\ \mbox{}\verb@ cbf_failnez(cbf_set_datestamp(self,reserved, @\\ \mbox{}\verb@ year,month,day,hour,minute,second,timezone,precision));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_datestamp",["int year", "int month", "int day", "int hour", @\\ \mbox{}\verb@"int minute", "double second", "int timezone","Float precision"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_timestamp":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *time} get_timestamp;@\\ \mbox{}\verb@%apply int *OUTPUT {int *timezone} get_timestamp;@\\ \mbox{}\verb@ void get_timestamp(double *time, int *timezone){@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ reserved = 0; @\\ \mbox{}\verb@ cbf_failnez(cbf_get_timestamp(self,reserved,time,timezone));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_timestamp",[],["Float time","Integer timezone"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_timestamp":["""@\\ \mbox{}\verb@ void set_timestamp(double time, int timezone, double precision){@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ reserved = 0; @\\ \mbox{}\verb@ cbf_failnez(cbf_set_timestamp(self,reserved,time,timezone,precision));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_timestamp",["Float time","Integer timezone","Float precision"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_current_timestamp":["""@\\ \mbox{}\verb@ void set_current_timestamp(int timezone){@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ reserved = 0; @\\ \mbox{}\verb@ cbf_failnez(cbf_set_current_timestamp(self,reserved,timezone));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_current_timestamp",["Integer timezone"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_overload":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *overload} get_overload;@\\ \mbox{}\verb@ void get_overload(unsigned int element_number, double *overload){@\\ \mbox{}\verb@ cbf_failnez(cbf_get_overload(self,element_number,overload));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_overload",["Integer element_number"],["Float overload"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_overload":["""@\\ \mbox{}\verb@ void set_overload(unsigned int element_number, double overload){@\\ \mbox{}\verb@ cbf_failnez(cbf_set_overload(self,element_number,overload));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_overload",["Integer element_number","Float overload"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_integration_time":["""@\\ \mbox{}\verb@ void set_integration_time(double time){@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ reserved = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_set_integration_time(self,reserved,time));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_integration_time",["Float time"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_integration_time":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *time} get_integration_time;@\\ \mbox{}\verb@ void get_integration_time( double *time ){@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ double tim;@\\ \mbox{}\verb@ reserved = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_get_integration_time(self,reserved,&tim));@\\ \mbox{}\verb@ *time = tim;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_integration_time",[],["Float time"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_orientation_matrix":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *m0,double *m1,double *m2,@\\ \mbox{}\verb@double *m3,double *m4, double *m5,double *m6,@\\ \mbox{}\verb@double *m7,double *m8 } get_orientation_matrix;@\\ \mbox{}\verb@ void get_orientation_matrix( double *m0,double *m1,@\\ \mbox{}\verb@double *m2,double *m3,double *m4,double *m5,double *m6,@\\ \mbox{}\verb@double *m7,double *m8){@\\ \mbox{}\verb@ double m[9];@\\ \mbox{}\verb@ cbf_failnez(cbf_get_orientation_matrix(self,m));@\\ \mbox{}\verb@ *m0 = m[0]; *m1=m[1] ; *m2=m[2] ;@\\ \mbox{}\verb@ *m3 = m[3]; *m4=m[4] ; *m5=m[5] ;@\\ \mbox{}\verb@ *m6 = m[6]; *m7=m[7] ; *m8=m[8] ;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_orientation_matrix",@\\ \mbox{}\verb@ [],[ "Float matrix_%d"%(ind) for ind in range(9) ]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_unit_cell":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *a, double *b, double *c,@\\ \mbox{}\verb@ double *alpha, double *beta, double *gamma} get_unit_cell;@\\ \mbox{}\verb@ void get_unit_cell(double *a, double *b, double *c,@\\ \mbox{}\verb@ double *alpha, double *beta, double *gamma) {@\\ \mbox{}\verb@ double cell[6];@\\ \mbox{}\verb@ cbf_failnez(cbf_get_unit_cell(self,cell,NULL));@\\ \mbox{}\verb@ *a = cell[0];@\\ \mbox{}\verb@ *b = cell[1];@\\ \mbox{}\verb@ *c = cell[2];@\\ \mbox{}\verb@ *alpha = cell[3];@\\ \mbox{}\verb@ *beta = cell[4];@\\ \mbox{}\verb@ *gamma = cell[5];@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_unit_cell",@\\ \mbox{}\verb@ [],["Float a", "Float b", "Float c", "Float alpha", "Float beta", "Float gamma" ] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_unit_cell_esd":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *a_esd, double *b_esd, double *c_esd,@\\ \mbox{}\verb@ double *alpha_esd, double *beta_esd, double *gamma_esd} get_unit_cell_esd;@\\ \mbox{}\verb@ void get_unit_cell_esd(double *a_esd, double *b_esd, double *c_esd,@\\ \mbox{}\verb@ double *alpha_esd, double *beta_esd, double *gamma_esd) {@\\ \mbox{}\verb@ double cell_esd[6];@\\ \mbox{}\verb@ cbf_failnez(cbf_get_unit_cell(self,NULL,cell_esd));@\\ \mbox{}\verb@ *a_esd = cell_esd[0];@\\ \mbox{}\verb@ *b_esd = cell_esd[1];@\\ \mbox{}\verb@ *c_esd = cell_esd[2];@\\ \mbox{}\verb@ *alpha_esd = cell_esd[3];@\\ \mbox{}\verb@ *beta_esd = cell_esd[4];@\\ \mbox{}\verb@ *gamma_esd = cell_esd[5];@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_unit_cell",@\\ \mbox{}\verb@ [],["doubleArray cell"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_reciprocal_cell":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *astar, double *bstar, double *cstar,@\\ \mbox{}\verb@ double *alphastar, double *betastar, double *gammastar} get_reciprocal_cell;@\\ \mbox{}\verb@ void get_reciprocal_cell(double *astar, double *bstar, double *cstar,@\\ \mbox{}\verb@ double *alphastar, double *betastar, double *gammastar) {@\\ \mbox{}\verb@ double rcell[6];@\\ \mbox{}\verb@ cbf_failnez(cbf_get_reciprocal_cell(self,rcell,NULL));@\\ \mbox{}\verb@ *astar = rcell[0];@\\ \mbox{}\verb@ *bstar = rcell[1];@\\ \mbox{}\verb@ *cstar = rcell[2];@\\ \mbox{}\verb@ *alphastar = rcell[3];@\\ \mbox{}\verb@ *betastar = rcell[4];@\\ \mbox{}\verb@ *gammastar = rcell[5];@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_reciprocal_cell",@\\ \mbox{}\verb@ [],["Float astar", "Float bstar", "Float cstar", "Float alphastar", "Float betastar", "Float gammastar"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_reciprocal_cell_esd":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *a_esd, double *b_esd, double *c_esd,@\\ \mbox{}\verb@ double *alpha_esd, double *beta_esd, double *gamma_esd} get_reciprocal_cell_esd;@\\ \mbox{}\verb@ void get_reciprocal_cell_esd(double *a_esd, double *b_esd, double *c_esd,@\\ \mbox{}\verb@ double *alpha_esd, double *beta_esd, double *gamma_esd) {@\\ \mbox{}\verb@ double cell_esd[6];@\\ \mbox{}\verb@ cbf_failnez(cbf_get_reciprocal_cell(self,NULL,cell_esd));@\\ \mbox{}\verb@ *a_esd = cell_esd[0];@\\ \mbox{}\verb@ *b_esd = cell_esd[1];@\\ \mbox{}\verb@ *c_esd = cell_esd[2];@\\ \mbox{}\verb@ *alpha_esd = cell_esd[3];@\\ \mbox{}\verb@ *beta_esd = cell_esd[4];@\\ \mbox{}\verb@ *gamma_esd = cell_esd[5];@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_reciprocal_cell",@\\ \mbox{}\verb@ [],["doubleArray cell"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_unit_cell":["""@\\ \mbox{}\verb@ void set_unit_cell(double cell[6]) {@\\ \mbox{}\verb@ cbf_failnez(cbf_set_unit_cell(self,cell,NULL));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_unit_cell",@\\ \mbox{}\verb@ ["double cell[6]"],[] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_unit_cell_esd":["""@\\ \mbox{}\verb@ void set_unit_cell_esd(double cell_esd[6]) {@\\ \mbox{}\verb@ cbf_failnez(cbf_set_unit_cell(self,NULL,cell_esd));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_unit_cell_esd",@\\ \mbox{}\verb@ ["double cell_esd[6]"],[] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_reciprocal_cell":["""@\\ \mbox{}\verb@ void set_reciprocal_cell(double cell[6]) {@\\ \mbox{}\verb@ cbf_failnez(cbf_set_reciprocal_cell(self,cell,NULL));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_reciprocal_cell",@\\ \mbox{}\verb@ ["double cell[6]"],[] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_reciprocal_cell_esd":["""@\\ \mbox{}\verb@ void set_reciprocal_cell_esd(double cell_esd[6]) {@\\ \mbox{}\verb@ cbf_failnez(cbf_set_reciprocal_cell(self,NULL,cell_esd));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_reciprocal_cell_esd",@\\ \mbox{}\verb@ ["double cell_esd[6]"],[] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_tag_category":["""@\\ \mbox{}\verb@ void set_tag_category(const char *tagname, const char* categoryname_in){@\\ \mbox{}\verb@ cbf_failnez(cbf_set_tag_category(self,tagname, categoryname_in));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_tag_category",["String tagname","String categoryname_in"],[] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_find_tag_category":["""@\\ \mbox{}\verb@@\\ \mbox{}\verb@ const char * find_tag_category(const char *tagname){@\\ \mbox{}\verb@ const char * result;@\\ \mbox{}\verb@ cbf_failnez(cbf_find_tag_category(self,tagname, &result));@\\ \mbox{}\verb@ return result;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","find_tag_category",["String tagname"],["String categoryname"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_require_tag_root":["""@\\ \mbox{}\verb@const char* require_tag_root(const char* tagname){@\\ \mbox{}\verb@ const char* result;@\\ \mbox{}\verb@ cbf_failnez(cbf_require_tag_root(self,tagname,&result));@\\ \mbox{}\verb@ return result;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","require_tag_root",["String tagname"],["String tagroot"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_find_tag_root":["""@\\ \mbox{}\verb@const char * find_tag_root(const char* tagname){@\\ \mbox{}\verb@ const char* result;@\\ \mbox{}\verb@ cbf_failnez(cbf_find_tag_root(self,tagname,&result));@\\ \mbox{}\verb@ return result;@\\ \mbox{}\verb@}@\\ \mbox{}\verb@""","find_tag_root",["String tagname"],["String tagroot"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_tag_root":["""@\\ \mbox{}\verb@void set_tag_root(const char* tagname, const char* tagroot_in){@\\ \mbox{}\verb@ cbf_failnez(cbf_set_tag_root(self,tagname,tagroot_in));@\\ \mbox{}\verb@}@\\ \mbox{}\verb@""","set_tag_root",["String tagname","String tagroot_in"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_category_root":["""@\\ \mbox{}\verb@void set_category_root(const char* categoryname, const char* categoryroot){@\\ \mbox{}\verb@ cbf_failnez(cbf_set_category_root(self,categoryname,categoryroot));@\\ \mbox{}\verb@}@\\ \mbox{}\verb@""","set_category_root",["String categoryname","String categoryroot"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_find_category_root":["""@\\ \mbox{}\verb@const char* find_category_root(const char* categoryname){@\\ \mbox{}\verb@ const char * result;@\\ \mbox{}\verb@ cbf_failnez(cbf_find_category_root(self,categoryname,&result));@\\ \mbox{}\verb@ return result;@\\ \mbox{}\verb@}@\\ \mbox{}\verb@""","find_category_root",["String categoryname"],["String categoryroot"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_require_category_root":["""@\\ \mbox{}\verb@const char* require_category_root (const char* categoryname){@\\ \mbox{}\verb@ const char* result;@\\ \mbox{}\verb@ cbf_failnez(cbf_require_category_root(self,categoryname, &result));@\\ \mbox{}\verb@ return result;@\\ \mbox{}\verb@}@\\ \mbox{}\verb@""","cbf_require_category_root",["String Categoryname"],["String categoryroot"]],@\\ \mbox{}\verb@ @\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_orientation_matrix":["""@\\ \mbox{}\verb@ void set_orientation_matrix( double m0,double m1,@\\ \mbox{}\verb@double m2,double m3,double m4,double m5,double m6,@\\ \mbox{}\verb@double m7,double m8){@\\ \mbox{}\verb@ double m[9];@\\ \mbox{}\verb@ m[0] = m0; m[1]=m1 ; m[2]=m2 ;@\\ \mbox{}\verb@ m[3] = m3; m[4]=m4 ; m[5]=m5 ;@\\ \mbox{}\verb@ m[6] = m6; m[7]=m7 ; m[8]=m8 ;@\\ \mbox{}\verb@ cbf_failnez(cbf_get_orientation_matrix(self,m));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_orientation_matrix",@\\ \mbox{}\verb@ [ "Float matrix_%d"%(ind) for ind in range(9) ] ,[]],@\\ \mbox{}\verb@ @\\ \mbox{}\verb@"cbf_set_bin_sizes":["""@\\ \mbox{}\verb@ void set_bin_sizes( int element_number, double slowbinsize_in, double fastbinsize_in) {@\\ \mbox{}\verb@ cbf_failnez(cbf_set_bin_sizes(self,element_number,slowbinsize_in,fastbinsize_in));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_bin_sizes",["Integer element_number","Float slowbinsize_in","Float fastbinsize_in"],[] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_bin_sizes":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *slowbinsize,double *fastbinsize};@\\ \mbox{}\verb@ void get_bin_sizes(int element_number, double *slowbinsize, double *fastbinsize) {@\\ \mbox{}\verb@ cbf_failnez(cbf_get_bin_sizes (self, (unsigned int)element_number, slowbinsize, fastbinsize));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_bin_sizes",["Integer element_number"],["Float slowbinsize","Float fastbinsize"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@# cbfhandle dict functions UNTESTED@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_require_dictionary":["""@\\ \mbox{}\verb@cbf_handle require_dictionary(){@\\ \mbox{}\verb@ cbf_handle temp;@\\ \mbox{}\verb@ cbf_failnez(cbf_require_dictionary(self,&temp));@\\ \mbox{}\verb@ return temp;@\\ \mbox{}\verb@}@\\ \mbox{}\verb@""","require_dictionary",[],["CBFHandle dictionary"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_dictionary":["""@\\ \mbox{}\verb@cbf_handle get_dictionary(){@\\ \mbox{}\verb@ cbf_handle temp;@\\ \mbox{}\verb@ cbf_failnez(cbf_get_dictionary(self,&temp));@\\ \mbox{}\verb@ return temp;@\\ \mbox{}\verb@}@\\ \mbox{}\verb@""","get_dictionary",[],["CBFHandle dictionary"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_dictionary":["""@\\ \mbox{}\verb@void set_dictionary(cbf_handle other){@\\ \mbox{}\verb@ cbf_failnez(cbf_set_dictionary(self,other));@\\ \mbox{}\verb@}@\\ \mbox{}\verb@""","set_dictionary",["CBFHandle dictionary"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_convert_dictionary":["""@\\ \mbox{}\verb@void convert_dictionary(cbf_handle other){@\\ \mbox{}\verb@ cbf_failnez(cbf_convert_dictionary(self,other));@\\ \mbox{}\verb@}@\\ \mbox{}\verb@""","convert_dictionary",["CBFHandle dictionary"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_construct_detector":["""@\\ \mbox{}\verb@ cbf_detector construct_detector(unsigned int element_number){@\\ \mbox{}\verb@ cbf_detector detector;@\\ \mbox{}\verb@ cbf_failnez(cbf_construct_detector(self,&detector,element_number));@\\ \mbox{}\verb@ return detector;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","construct_detector",["Integer element_number"],["pycbf detector object"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_construct_reference_detector":["""@\\ \mbox{}\verb@ cbf_detector construct_reference_detector(unsigned int element_number){@\\ \mbox{}\verb@ cbf_detector detector;@\\ \mbox{}\verb@ cbf_failnez(cbf_construct_reference_detector(self,&detector,element_number));@\\ \mbox{}\verb@ return detector;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","construct_reference_detector",["Integer element_number"],["pycbf detector object"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_require_reference_detector":["""@\\ \mbox{}\verb@ cbf_detector require_reference_detector(unsigned int element_number){@\\ \mbox{}\verb@ cbf_detector detector;@\\ \mbox{}\verb@ cbf_failnez(cbf_require_reference_detector(self,&detector,element_number));@\\ \mbox{}\verb@ return detector;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","require_reference_detector",["Integer element_number"],["pycbf detector object"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@# Prelude to the next section of the nuweb doc@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_construct_goniometer":["""@\\ \mbox{}\verb@ cbf_goniometer construct_goniometer(){@\\ \mbox{}\verb@ cbf_goniometer goniometer;@\\ \mbox{}\verb@ cbf_failnez(cbf_construct_goniometer(self,&goniometer));@\\ \mbox{}\verb@ return goniometer;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","construct_goniometer",[],["pycbf goniometer object"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@}@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@class cbfhandlewrapper:@\\ \mbox{}\verb@ def __init__(self):@\\ \mbox{}\verb@ self.code = """@\\ \mbox{}\verb@// Tell SWIG not to make constructor for these objects@\\ \mbox{}\verb@%nodefault cbf_handle;@\\ \mbox{}\verb@%nodefault cbf_handle_struct;@\\ \mbox{}\verb@%nodefault cbf_node;@\\ \mbox{}\verb@@\\ \mbox{}\verb@// A couple of blockitem functions return CBF_NODETYPE@\\ \mbox{}\verb@typedef enum@\\ \mbox{}\verb@{@\\ \mbox{}\verb@ CBF_UNDEFNODE, /* Undefined */@\\ \mbox{}\verb@ CBF_LINK, /* Link */@\\ \mbox{}\verb@ CBF_ROOT, /* Root */@\\ \mbox{}\verb@ CBF_DATABLOCK, /* Datablock */@\\ \mbox{}\verb@ CBF_SAVEFRAME, /* Saveframe */@\\ \mbox{}\verb@ CBF_CATEGORY, /* Category */@\\ \mbox{}\verb@ CBF_COLUMN /* Column */@\\ \mbox{}\verb@}@\\ \mbox{}\verb@CBF_NODETYPE;@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@// Tell SWIG what the object is, so we can build the class@\\ \mbox{}\verb@@\\ \mbox{}\verb@typedef struct@\\ \mbox{}\verb@{@\\ \mbox{}\verb@ cbf_node *node;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ int row, search_row;@\\ \mbox{}\verb@} cbf_handle_struct;@\\ \mbox{}\verb@@\\ \mbox{}\verb@typedef cbf_handle_struct *cbf_handle;@\\ \mbox{}\verb@@\\ \mbox{}\verb@typedef cbf_handle_struct handle;@\\ \mbox{}\verb@%feature("autodoc","1");@\\ \mbox{}\verb@@\\ \mbox{}\verb@%extend cbf_handle_struct{ // Tell SWIG to attach functions to the structure@\\ \mbox{}\verb@@\\ \mbox{}\verb@ cbf_handle_struct(){ // Constructor@\\ \mbox{}\verb@ cbf_handle handle;@\\ \mbox{}\verb@ cbf_failnez(cbf_make_handle(&handle));@\\ \mbox{}\verb@ return handle;@\\ \mbox{}\verb@ } @\\ \mbox{}\verb@@\\ \mbox{}\verb@ ~cbf_handle_struct(){ // Destructor@\\ \mbox{}\verb@ cbf_failnez(cbf_free_handle(self));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@"""@\\ \mbox{}\verb@ self.tail = """@\\ \mbox{}\verb@}; // End of cbf_handle_struct@\\ \mbox{}\verb@"""@\\ \mbox{}\verb@ # End of init function@\\ \mbox{}\verb@ def get_code(self):@\\ \mbox{}\verb@ return self.code+self.tail@\\ \mbox{}\verb@ def wrap(self,cfunc,prototype,args,docstring):@\\ \mbox{}\verb@ # print "cfunc: ", cfunc@\\ \mbox{}\verb@ pyfunc = cfunc.replace("cbf_","")@\\ \mbox{}\verb@ # Insert a comment for debugging this script@\\ \mbox{}\verb@ code = "\n/* cfunc %s pyfunc %s \n"%(cfunc,pyfunc)@\\ \mbox{}\verb@ for a in args:@\\ \mbox{}\verb@ code += " arg %s "%(a)@\\ \mbox{}\verb@ code += "*/\n\n"@\\ \mbox{}\verb@ # Make and free handle are done in the header so skip@\\ \mbox{}\verb@ if cfunc.find("cbf_make_handle")>-1 or cfunc.find("cbf_free_handle")>-1:@\\ \mbox{}\verb@ # Constructor and destructor done in headers@\\ \mbox{}\verb@ return@\\ \mbox{}\verb@ if args[0] != "cbf_handle handle": # Must be for cbfhandle@\\ \mbox{}\verb@ print "problem",cfunc,pyfunc,args@\\ \mbox{}\verb@ return@\\ \mbox{}\verb@ if len(args)==1: # Only takes CBFhandle arg@\\ \mbox{}\verb@ code+= docstringwrite(pyfunc,[],[],prototype,docstring)@\\ \mbox{}\verb@ code+= " void %s(void){\n"%(pyfunc)@\\ \mbox{}\verb@ code+= " cbf_failnez(%s(self));}\n"%(cfunc) @\\ \mbox{}\verb@ self.code=self.code+code@\\ \mbox{}\verb@ return@\\ \mbox{}\verb@ # Now case by case rather than writing a proper parser@\\ \mbox{}\verb@ # Special cases ...@\\ \mbox{}\verb@ not_found=0@\\ \mbox{}\verb@ try:@\\ \mbox{}\verb@ code, pyname, input, output = cbfhandle_specials[cfunc]@\\ \mbox{}\verb@ self.code += docstringwrite(pyname,input,output,@\\ \mbox{}\verb@ prototype,docstring)+ code@\\ \mbox{}\verb@ return@\\ \mbox{}\verb@ except KeyError:@\\ \mbox{}\verb@ not_found = 1@\\ \mbox{}\verb@ # print "KeyError"@\\ \mbox{}\verb@ except ValueError:@\\ \mbox{}\verb@ print "problem in",cfunc@\\ \mbox{}\verb@ for item in cbfhandle_specials[cfunc]:@\\ \mbox{}\verb@ print "***",item@\\ \mbox{}\verb@ raise@\\ \mbox{}\verb@ if len(args)==2:@\\ \mbox{}\verb@ if args[1].find("const char")>-1 and \@\\ \mbox{}\verb@ args[1].find("*")>-1 and \@\\ \mbox{}\verb@ args[1].find("**")==-1 :@\\ \mbox{}\verb@ # 1 input string@\\ \mbox{}\verb@ code += docstringwrite(pyfunc,[],["string"],prototype,docstring)@\\ \mbox{}\verb@ code += " void %s(const char* arg){\n"%(pyfunc)@\\ \mbox{}\verb@ code +=" cbf_failnez(%s(self,arg));}\n"%(cfunc)@\\ \mbox{}\verb@ self.code=self.code+code@\\ \mbox{}\verb@ return@\\ \mbox{}\verb@ if args[1].find("const char")>-1 and \@\\ \mbox{}\verb@ args[1].find("**")>-1 :# return string@\\ \mbox{}\verb@ code += docstringwrite(pyfunc,["string"],[],prototype,docstring)@\\ \mbox{}\verb@ code += " const char* %s(void){\n"%(pyfunc)@\\ \mbox{}\verb@ code += " const char* result;\n"@\\ \mbox{}\verb@ code += " cbf_failnez(%s(self, &result));\n"%(cfunc)@\\ \mbox{}\verb@ code += " return result;}\n"@\\ \mbox{}\verb@ self.code=self.code+code@\\ \mbox{}\verb@ return@\\ \mbox{}\verb@ if args[1].find("unsigned int")>-1 and args[1].find("*")==-1:@\\ \mbox{}\verb@ # set uint@\\ \mbox{}\verb@ if args[1].find("reserved")>-1:@\\ \mbox{}\verb@ raise Exception("Setting reserved??? %s %s %s"%(pyfunc,@\\ \mbox{}\verb@ cfunc,str(args)))@\\ \mbox{}\verb@ code += docstringwrite(pyfunc,["Integer"],[],prototype,docstring)@\\ \mbox{}\verb@ code +=" void %s(unsigned int arg){\n"%(pyfunc)@\\ \mbox{}\verb@ code +=" cbf_failnez(%s(self,arg));}\n"%(cfunc)@\\ \mbox{}\verb@ self.code=self.code+code@\\ \mbox{}\verb@ return@\\ \mbox{}\verb@ if args[1].find("unsigned int *")>-1 and args[1].find("**")==-1:@\\ \mbox{}\verb@ # output uint@\\ \mbox{}\verb@ if args[1].find("reserved")>-1:@\\ \mbox{}\verb@ raise Exception("Setting reserved??? %s %s %s"%(pyfunc,@\\ \mbox{}\verb@ cfunc,str(args)))@\\ \mbox{}\verb@ code += docstringwrite(pyfunc,[],["Integer"],prototype,docstring)@\\ \mbox{}\verb@ code +=" unsigned int %s(void){\n"%(pyfunc)@\\ \mbox{}\verb@ code +=" unsigned int result;\n"@\\ \mbox{}\verb@ code +=" cbf_failnez(%s(self,&result));\n"%(cfunc)@\\ \mbox{}\verb@ code +=" return result;}\n"@\\ \mbox{}\verb@ self.code=self.code+code@\\ \mbox{}\verb@ return@\\ \mbox{}\verb@ # For the rest attempt to guess@\\ \mbox{}\verb@ if args[1].find("cbf")==-1: # but do not try the goniometer constructor@\\ \mbox{}\verb@ if args[1].find("*")>-1 and args[1].find("cbf")==-1:@\\ \mbox{}\verb@ # pointer used for returning something@\\ \mbox{}\verb@ type = args[1].split(" ")[0]@\\ \mbox{}\verb@ code += docstringwrite(pyfunc,[],[type.replace("*","")],@\\ \mbox{}\verb@ prototype,docstring)@\\ \mbox{}\verb@ code+= " "+type+" "+pyfunc+"(void){\n"@\\ \mbox{}\verb@ code+= " "+type+" result;\n"@\\ \mbox{}\verb@ code+= " cbf_failnez(%s(self,&result));\n"%(cfunc)@\\ \mbox{}\verb@ code+= " return result;}\n"@\\ \mbox{}\verb@ self.code=self.code+code@\\ \mbox{}\verb@ return@\\ \mbox{}\verb@ else:@\\ \mbox{}\verb@ var = args[1].split(" ")[-1]@\\ \mbox{}\verb@ code += docstringwrite(pyfunc,[],[args[1]],prototype,docstring)@\\ \mbox{}\verb@ code+= " void %s(%s){\n"%(pyfunc,args[1])@\\ \mbox{}\verb@ code +=" cbf_failnez(%s(self,%s));}\n"%(cfunc,var)@\\ \mbox{}\verb@ self.code=self.code+code@\\ \mbox{}\verb@ return@\\ \mbox{}\verb@ if not_found:@\\ \mbox{}\verb@ code+= " void %s(void){\n"%(pyfunc)@\\ \mbox{}\verb@ code +=" cbf_failnez(CBF_NOTIMPLEMENTED);}\n"@\\ \mbox{}\verb@ self.code=self.code+code@\\ \mbox{}\verb@ print "Have not implemented: cbfhandle.%s"%(pyfunc)@\\ \mbox{}\verb@ print " ",cfunc@\\ \mbox{}\verb@ print " args:"@\\ \mbox{}\verb@ for a in args:@\\ \mbox{}\verb@ print " ",a @\\ \mbox{}\verb@ print@\\ \mbox{}\verb@ return@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@cbf_handle_wrapper = cbfhandlewrapper()@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@cbf_goniometer_specials = {@\\ \mbox{}\verb@"cbf_get_rotation_range":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *start,double *increment};@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void get_rotation_range(double *start,double *increment){@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ reserved = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_get_rotation_range (self,reserved, start,increment));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_rotation_range",[],["Float start","Float increment"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_rotate_vector":["""@\\ \mbox{}\verb@@\\ \mbox{}\verb@%apply double *OUTPUT {double *final1, double *final2, double *final3};@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void rotate_vector (double ratio, double initial1,double initial2, @\\ \mbox{}\verb@ double initial3, double *final1, double *final2, double *final3){@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ reserved = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_rotate_vector (self, reserved, ratio, initial1,@\\ \mbox{}\verb@ initial2, initial3, final1, final2, final3));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""", "rotate_vector",@\\ \mbox{}\verb@ [ "double ratio", "double initial1","double initial2", "double initial3" ] , @\\ \mbox{}\verb@ [ "double final1" ,"double final2" , "double final3" ] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_reciprocal":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *reciprocal1,double *reciprocal2, @\\ \mbox{}\verb@ double *reciprocal3};@\\ \mbox{}\verb@@\\ \mbox{}\verb@ void get_reciprocal (double ratio,double wavelength, @\\ \mbox{}\verb@ double real1, double real2, double real3, @\\ \mbox{}\verb@ double *reciprocal1,double *reciprocal2, @\\ \mbox{}\verb@ double *reciprocal3){@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ reserved = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_get_reciprocal(self,reserved, ratio, wavelength, @\\ \mbox{}\verb@ real1, real2, real3,reciprocal1,@\\ \mbox{}\verb@ reciprocal2,reciprocal3));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""", "get_reciprocal",@\\ \mbox{}\verb@ ["double ratio","double wavelength",@\\ \mbox{}\verb@ "double real1","double real2","double real3"],@\\ \mbox{}\verb@ ["double reciprocal1","double reciprocal2", "double reciprocal3" ]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_rotation_axis":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *vector1,double *vector2, double *vector3};@\\ \mbox{}\verb@@\\ \mbox{}\verb@void get_rotation_axis (double *vector1, double *vector2, double *vector3){@\\ \mbox{}\verb@ unsigned int reserved;@\\ \mbox{}\verb@ reserved = 0;@\\ \mbox{}\verb@ cbf_failnez(cbf_get_rotation_axis (self, reserved, @\\ \mbox{}\verb@ vector1, vector2, vector3));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_rotation_axis", [] , @\\ \mbox{}\verb@ ["double vector1", "double vector2", "double vector3"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@}@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@class cbfgoniometerwrapper:@\\ \mbox{}\verb@ def __init__(self):@\\ \mbox{}\verb@ self.code = """@\\ \mbox{}\verb@// Tell SWIG not to make constructor for these objects@\\ \mbox{}\verb@%nodefault cbf_positioner_struct;@\\ \mbox{}\verb@%nodefault cbf_goniometer;@\\ \mbox{}\verb@%nodefault cbf_axis_struct;@\\ \mbox{}\verb@@\\ \mbox{}\verb@// Tell SWIG what the object is, so we can build the class@\\ \mbox{}\verb@typedef struct@\\ \mbox{}\verb@{@\\ \mbox{}\verb@ double matrix [3][4];@\\ \mbox{}\verb@@\\ \mbox{}\verb@ cbf_axis_struct *axis;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ size_t axes;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ int matrix_is_valid, axes_are_connected;@\\ \mbox{}\verb@}@\\ \mbox{}\verb@cbf_positioner_struct;@\\ \mbox{}\verb@@\\ \mbox{}\verb@typedef cbf_positioner_struct *cbf_goniometer;@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@%feature("autodoc","1");@\\ \mbox{}\verb@@\\ \mbox{}\verb@%extend cbf_positioner_struct{// Tell SWIG to attach functions to the structure@\\ \mbox{}\verb@@\\ \mbox{}\verb@ cbf_positioner_struct(){ // Constructor@\\ \mbox{}\verb@ // DO NOT CONSTRUCT WITHOUT A CBFHANDLE@\\ \mbox{}\verb@ cbf_failnez(CBF_ARGUMENT);@\\ \mbox{}\verb@ return NULL; /* Should never be executed */@\\ \mbox{}\verb@ } @\\ \mbox{}\verb@@\\ \mbox{}\verb@ ~cbf_positioner_struct(){ // Destructor@\\ \mbox{}\verb@ cbf_failnez(cbf_free_goniometer(self));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@"""@\\ \mbox{}\verb@ self.tail = """@\\ \mbox{}\verb@}; // End of cbf_positioner@\\ \mbox{}\verb@"""@\\ \mbox{}\verb@ def wrap(self,cfunc,prototype,args,docstring):@\\ \mbox{}\verb@ if cfunc.find("cbf_free_goniometer")>-1:@\\ \mbox{}\verb@ return @\\ \mbox{}\verb@ try:@\\ \mbox{}\verb@ code, pyname, input, output = cbf_goniometer_specials[cfunc]@\\ \mbox{}\verb@ self.code += docstringwrite(pyname,input,output,@\\ \mbox{}\verb@ prototype,docstring)+ code@\\ \mbox{}\verb@ except KeyError:@\\ \mbox{}\verb@ print "TODO: Goniometer:",prototype@\\ \mbox{}\verb@ def get_code(self):@\\ \mbox{}\verb@ return self.code+self.tail@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@cbf_goniometer_wrapper = cbfgoniometerwrapper()@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@cbf_detector_specials = {@\\ \mbox{}\verb@"cbf_get_pixel_normal":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *normal1,double *normal2, double *normal3};@\\ \mbox{}\verb@ void get_pixel_normal ( double index1, double index2, @\\ \mbox{}\verb@ double *normal1,double *normal2, double *normal3){@\\ \mbox{}\verb@ cbf_failnez(cbf_get_pixel_normal(self,@\\ \mbox{}\verb@ index1,index2,normal1,normal2,normal3));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@@\\ \mbox{}\verb@""","get_pixel_normal",["double index1","double index2"] ,@\\ \mbox{}\verb@ ["double normal1","double normal2", "double normal3" ] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_pixel_normal_fs":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *normalfast,double *normalslow, double *normal3};@\\ \mbox{}\verb@ void get_pixel_normal_fs ( double indexfast, double indexslow, @\\ \mbox{}\verb@ double *normal1,double *normal2, double *normal3){@\\ \mbox{}\verb@ cbf_failnez(cbf_get_pixel_normal_fs(self,@\\ \mbox{}\verb@ indexfast,indexslow,normal1,normal2,normal3));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@@\\ \mbox{}\verb@""","get_pixel_normal_fs",["double indexfast","double indexslow"] ,@\\ \mbox{}\verb@ ["double normal1","double normal2", "double normal3" ] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_pixel_normal_sf":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *normalslow,double *normalfast, double *normal3};@\\ \mbox{}\verb@ void get_pixel_normal_sf ( double indexslow, double indexfast, @\\ \mbox{}\verb@ double *normal1,double *normal2, double *normal3){@\\ \mbox{}\verb@ cbf_failnez(cbf_get_pixel_normal_sf(self,@\\ \mbox{}\verb@ indexslow,indexfast,normal1,normal2,normal3));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@@\\ \mbox{}\verb@""","get_pixel_normal_sf",["double indexslow","double indexfast"] ,@\\ \mbox{}\verb@ ["double normal1","double normal2", "double normal3" ] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_pixel_area":["""@\\ \mbox{}\verb@%apply double *OUTPUT{double *area,double *projected_area};@\\ \mbox{}\verb@ void get_pixel_area(double index1, double index2,@\\ \mbox{}\verb@ double *area,double *projected_area){@\\ \mbox{}\verb@ cbf_failnez(cbf_get_pixel_area (self,@\\ \mbox{}\verb@ index1, index2, area,projected_area));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_pixel_area",["double index1", "double index2"],@\\ \mbox{}\verb@ ["double area","double projected_area"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_pixel_area_fs":["""@\\ \mbox{}\verb@%apply double *OUTPUT{double *area,double *projected_area};@\\ \mbox{}\verb@ void get_pixel_area_fs(double indexfast, double indexslow,@\\ \mbox{}\verb@ double *area,double *projected_area){@\\ \mbox{}\verb@ cbf_failnez(cbf_get_pixel_area_fs (self,@\\ \mbox{}\verb@ indexfast, indexslow, area,projected_area));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_pixel_area_fs",["double indexfast", "double indexslow"],@\\ \mbox{}\verb@ ["double area","double projected_area"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_pixel_area_sf":["""@\\ \mbox{}\verb@%apply double *OUTPUT{double *area,double *projected_area};@\\ \mbox{}\verb@ void get_pixel_area_sf(double indexslow, double indexfast,@\\ \mbox{}\verb@ double *area,double *projected_area){@\\ \mbox{}\verb@ cbf_failnez(cbf_get_pixel_area_sf (self,@\\ \mbox{}\verb@ indexslow, indexfast, area,projected_area));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_pixel_area_sf",["double indexslow", "double indexfast"],@\\ \mbox{}\verb@ ["double area","double projected_area"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_detector_distance":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *distance};@\\ \mbox{}\verb@ void get_detector_distance (double *distance){@\\ \mbox{}\verb@ cbf_failnez(cbf_get_detector_distance(self,distance));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_detector_distance",[],["double distance"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_detector_normal":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *normal1, double *normal2, double *normal3};@\\ \mbox{}\verb@ void get_detector_normal(double *normal1, @\\ \mbox{}\verb@ double *normal2,@\\ \mbox{}\verb@ double *normal3){@\\ \mbox{}\verb@ cbf_failnez(cbf_get_detector_normal(self,@\\ \mbox{}\verb@ normal1, normal2, normal3));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_detector_normal",[],@\\ \mbox{}\verb@["double normal1", "double normal2", "double normal3"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_pixel_coordinates":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *coordinate1, @\\ \mbox{}\verb@ double *coordinate2, double *coordinate3};@\\ \mbox{}\verb@ void get_pixel_coordinates(double index1, double index2, @\\ \mbox{}\verb@ double *coordinate1, @\\ \mbox{}\verb@ double *coordinate2, @\\ \mbox{}\verb@ double *coordinate3){@\\ \mbox{}\verb@ cbf_failnez(cbf_get_pixel_coordinates(self, index1, index2,@\\ \mbox{}\verb@ coordinate1, coordinate2, coordinate3));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_pixel_coordinates",["double index1","double index2"],@\\ \mbox{}\verb@["double coordinate1", "double coordinate2", "double coordinate3"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_pixel_coordinates_fs":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *coordinate1, @\\ \mbox{}\verb@ double *coordinate2, double *coordinate3};@\\ \mbox{}\verb@ void get_pixel_coordinates_fs(double indexfast, double indexslow, @\\ \mbox{}\verb@ double *coordinate1, @\\ \mbox{}\verb@ double *coordinate2, @\\ \mbox{}\verb@ double *coordinate3){@\\ \mbox{}\verb@ cbf_failnez(cbf_get_pixel_coordinates_fs(self, indexfast, indexslow, coordinate1, coordinate2, coordinate3));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_pixel_coordinates_fs",["double indexfast","double indexslow"],@\\ \mbox{}\verb@["double coordinate1", "double coordinate2", "double coordinate3"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_pixel_coordinates_sf":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *coordinate1, @\\ \mbox{}\verb@ double *coordinate2, double *coordinate3};@\\ \mbox{}\verb@ void get_pixel_coordinates_sf(double indexslow, double indexfast, @\\ \mbox{}\verb@ double *coordinate1, @\\ \mbox{}\verb@ double *coordinate2, @\\ \mbox{}\verb@ double *coordinate3){@\\ \mbox{}\verb@ cbf_failnez(cbf_get_pixel_coordinates_sf(self, indexslow, indexfast, coordinate1, coordinate2, coordinate3));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_pixel_coordinates_sf",["double indexslow","double indexfast"],@\\ \mbox{}\verb@["double coordinate1", "double coordinate2", "double coordinate3"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_beam_center":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *index1, double *index2, @\\ \mbox{}\verb@ double *center1,double *center2};@\\ \mbox{}\verb@ void get_beam_center(double *index1, double *index2, @\\ \mbox{}\verb@ double *center1,double *center2){@\\ \mbox{}\verb@ cbf_failnez(cbf_get_beam_center(self, index1, index2, @\\ \mbox{}\verb@ center1, center2));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_beam_center",[],@\\ \mbox{}\verb@["double index1", "double index2", "double center1","double center2"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_beam_center_fs":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *indexfast, double *indexslow, @\\ \mbox{}\verb@ double *centerfast,double *centerslow};@\\ \mbox{}\verb@ void get_beam_center_fs(double *indexfast, double *indexslow, @\\ \mbox{}\verb@ double *centerfast,double *centerslow){@\\ \mbox{}\verb@ cbf_failnez(cbf_get_beam_center_fs(self, indexfast, indexslow, @\\ \mbox{}\verb@ centerfast, centerslow));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_beam_center_fs",[],@\\ \mbox{}\verb@["double indexfast", "double indexslow", "double centerfast","double centerslow"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_beam_center_sf":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *indexslow, double *indexfast, @\\ \mbox{}\verb@ double *centerslow,double *centerfast};@\\ \mbox{}\verb@ void get_beam_center_sf(double *indexslow, double *indexfast, @\\ \mbox{}\verb@ double *centerslow,double *centerfast){@\\ \mbox{}\verb@ cbf_failnez(cbf_get_beam_center_sf(self, indexslow, indexfast, @\\ \mbox{}\verb@ centerslow, centerfast));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_beam_center_sf",[],@\\ \mbox{}\verb@["double indexslow", "double indexfast", "double centerslow","double centerfast"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_beam_center":["""@\\ \mbox{}\verb@ void set_beam_center(double *indexslow, double *indexfast, @\\ \mbox{}\verb@ double *centerslow,double *centerfast){@\\ \mbox{}\verb@ cbf_failnez(cbf_set_beam_center(self, indexslow, indexfast, @\\ \mbox{}\verb@ centerslow, centerfast));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_beam_center",@\\ \mbox{}\verb@["double indexslow", "double indexfast", "double centerslow","double centerfast"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_beam_center_fs":["""@\\ \mbox{}\verb@ void set_beam_center_fs(double *indexfast, double *indexslow, @\\ \mbox{}\verb@ double *centerfast,double *centerslow){@\\ \mbox{}\verb@ cbf_failnez(cbf_set_beam_center_fs(self, indexfast, indexslow, @\\ \mbox{}\verb@ centerfast, centerslow));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_beam_center_fs",@\\ \mbox{}\verb@["double indexfast", "double indexslow", "double centerfast","double centerslow"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_beam_center_sf":["""@\\ \mbox{}\verb@ void set_beam_center_sf(double *indexslow, double *indexfast, @\\ \mbox{}\verb@ double *centerslow,double *centerfast){@\\ \mbox{}\verb@ cbf_failnez(cbf_set_beam_center_sf(self, indexslow, indexfast, @\\ \mbox{}\verb@ centerslow, centerfast));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_beam_center_sf",@\\ \mbox{}\verb@["double indexslow", "double indexfast", "double centerslow","double centerfast"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_reference_beam_center":["""@\\ \mbox{}\verb@ void set_reference_beam_center(double *indexslow, double *indexfast, @\\ \mbox{}\verb@ double *centerslow,double *centerfast){@\\ \mbox{}\verb@ cbf_failnez(cbf_set_reference_beam_center(self, indexslow, indexfast, @\\ \mbox{}\verb@ centerslow, centerfast));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_reference_beam_center",@\\ \mbox{}\verb@["double indexslow", "double indexfast", "double centerslow","double centerfast"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_reference_beam_center_fs":["""@\\ \mbox{}\verb@ void set_reference_beam_center_fs(double *indexfast, double *indexslow, @\\ \mbox{}\verb@ double *centerfast,double *centerslow){@\\ \mbox{}\verb@ cbf_failnez(cbf_set_reference_beam_center_fs(self, indexfast, indexslow, @\\ \mbox{}\verb@ centerfast, centerslow));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_reference_beam_center_fs",@\\ \mbox{}\verb@["double indexfast", "double indexslow", "double centerfast","double centerslow"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_set_reference_beam_center_sf":["""@\\ \mbox{}\verb@ void set_reference_beam_center_sf(double *indexslow, double *indexfast, @\\ \mbox{}\verb@ double *centerslow,double *centerfast){@\\ \mbox{}\verb@ cbf_failnez(cbf_set_reference_beam_center_sf(self, indexslow, indexfast, @\\ \mbox{}\verb@ centerslow, centerfast));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","set_reference_beam_center_sf",@\\ \mbox{}\verb@["double indexslow", "double indexfast", "double centerslow","double centerfast"],[]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_inferred_pixel_size" : ["""@\\ \mbox{}\verb@%apply double *OUTPUT { double *psize } get_inferred_pixel_size;@\\ \mbox{}\verb@void get_inferred_pixel_size(unsigned int axis_number, double* psize){@\\ \mbox{}\verb@ cbf_failnez(cbf_get_inferred_pixel_size(self, axis_number, psize));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_inferred_pixel_size",["Int axis_number"],["Float pixel size"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_inferred_pixel_size_fs" : ["""@\\ \mbox{}\verb@%apply double *OUTPUT { double *psize } get_inferred_pixel_size;@\\ \mbox{}\verb@void get_inferred_pixel_size_fs(unsigned int axis_number, double* psize){@\\ \mbox{}\verb@ cbf_failnez(cbf_get_inferred_pixel_size_fs(self, axis_number, psize));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_inferred_pixel_size_fs",["Int axis_number"],["Float pixel size"] ],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_inferred_pixel_size_sf" : ["""@\\ \mbox{}\verb@%apply double *OUTPUT { double *psize } get_inferred_pixel_size;@\\ \mbox{}\verb@void get_inferred_pixel_size_sf(unsigned int axis_number, double* psize){@\\ \mbox{}\verb@ cbf_failnez(cbf_get_inferred_pixel_size_sf(self, axis_number, psize));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_inferred_pixel_size_sf",["Int axis_number"],["Float pixel size"] ]@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@}@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@class cbfdetectorwrapper:@\\ \mbox{}\verb@ def __init__(self):@\\ \mbox{}\verb@ self.code = """@\\ \mbox{}\verb@// Tell SWIG not to make constructor for these objects@\\ \mbox{}\verb@%nodefault cbf_detector_struct;@\\ \mbox{}\verb@%nodefault cbf_detector;@\\ \mbox{}\verb@@\\ \mbox{}\verb@// Tell SWIG what the object is, so we can build the class@\\ \mbox{}\verb@typedef struct@\\ \mbox{}\verb@{@\\ \mbox{}\verb@ cbf_positioner positioner;@\\ \mbox{}\verb@@\\ \mbox{}\verb@ double displacement [2], increment [2];@\\ \mbox{}\verb@@\\ \mbox{}\verb@ size_t axes, index [2];@\\ \mbox{}\verb@}@\\ \mbox{}\verb@cbf_detector_struct;@\\ \mbox{}\verb@@\\ \mbox{}\verb@typedef cbf_detector_struct *cbf_detector;@\\ \mbox{}\verb@@\\ \mbox{}\verb@%feature("autodoc","1");@\\ \mbox{}\verb@@\\ \mbox{}\verb@%extend cbf_detector_struct{// Tell SWIG to attach functions to the structure@\\ \mbox{}\verb@@\\ \mbox{}\verb@ cbf_detector_struct(){ // Constructor@\\ \mbox{}\verb@ // DO NOT CONSTRUCT WITHOUT A CBFHANDLE@\\ \mbox{}\verb@ cbf_failnez(CBF_ARGUMENT);@\\ \mbox{}\verb@ return NULL; /* Should never be executed */@\\ \mbox{}\verb@ } @\\ \mbox{}\verb@@\\ \mbox{}\verb@ ~cbf_detector_struct(){ // Destructor@\\ \mbox{}\verb@ cbf_failnez(cbf_free_detector(self));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@"""@\\ \mbox{}\verb@ self.tail = """@\\ \mbox{}\verb@}; // End of cbf_detector@\\ \mbox{}\verb@"""@\\ \mbox{}\verb@ def wrap(self,cfunc,prototype,args,docstring):@\\ \mbox{}\verb@ if cfunc.find("cbf_free_detector")>-1:@\\ \mbox{}\verb@ return @\\ \mbox{}\verb@ try:@\\ \mbox{}\verb@ code, pyname, input, output = cbf_detector_specials[cfunc]@\\ \mbox{}\verb@ self.code += docstringwrite(pyname,input,output,@\\ \mbox{}\verb@ prototype,docstring)+ code@\\ \mbox{}\verb@ except KeyError:@\\ \mbox{}\verb@ print "TODO: Detector:",prototype@\\ \mbox{}\verb@ def get_code(self):@\\ \mbox{}\verb@ return self.code+self.tail@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@cbf_detector_wrapper = cbfdetectorwrapper()@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@cbfgeneric_specials = {@\\ \mbox{}\verb@"cbf_get_local_integer_byte_order":["""@\\ \mbox{}\verb@%cstring_output_allocate_size(char **bo, int *bolen, free(*$1));@\\ \mbox{}\verb@ %inline {@\\ \mbox{}\verb@ void get_local_integer_byte_order(char **bo, int *bolen) {@\\ \mbox{}\verb@ char * byteorder;@\\ \mbox{}\verb@ char * bot;@\\ \mbox{}\verb@ error_status = cbf_get_local_integer_byte_order(&byteorder);@\\ \mbox{}\verb@ *bolen = strlen(byteorder);@\\ \mbox{}\verb@ if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)}@\\ \mbox{}\verb@ strncpy(bot,byteorder,*bolen);@\\ \mbox{}\verb@ *bo = bot;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_local_integer_byte_order",[],["char **bo", "int *bolen"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_local_real_format":["""@\\ \mbox{}\verb@%cstring_output_allocate_size(char **rf, int *rflen, free(*$1));@\\ \mbox{}\verb@ %inline {@\\ \mbox{}\verb@ void get_local_real_format(char **rf, int *rflen) {@\\ \mbox{}\verb@ char * real_format;@\\ \mbox{}\verb@ char * rft;@\\ \mbox{}\verb@ error_status = cbf_get_local_real_format(&real_format);@\\ \mbox{}\verb@ *rflen = strlen(real_format);@\\ \mbox{}\verb@ if (!(rft = (char *)malloc(*rflen))) {cbf_failnez(CBF_ALLOC)}@\\ \mbox{}\verb@ strncpy(rft,real_format,*rflen);@\\ \mbox{}\verb@ *rf = rft;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_local_real_format",[],["char **rf", "int *rflen"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_get_local_real_byte_order":["""@\\ \mbox{}\verb@%cstring_output_allocate_size(char **bo, int *bolen, free(*$1));@\\ \mbox{}\verb@ %inline {@\\ \mbox{}\verb@ void get_local_real_byte_order(char **bo, int *bolen) {@\\ \mbox{}\verb@ char * byteorder;@\\ \mbox{}\verb@ char * bot;@\\ \mbox{}\verb@ error_status = cbf_get_local_real_byte_order(&byteorder);@\\ \mbox{}\verb@ *bolen = strlen(byteorder);@\\ \mbox{}\verb@ if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)}@\\ \mbox{}\verb@ strncpy(bot,byteorder,*bolen);@\\ \mbox{}\verb@ *bo = bot;@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","get_local_real_byte_order",[],["char **bo", "int *bolen"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_compute_cell_volume":["""@\\ \mbox{}\verb@@\\ \mbox{}\verb@%apply double *OUTPUT {double *volume};@\\ \mbox{}\verb@ %inline {@\\ \mbox{}\verb@ void compute_cell_volume(double cell[6], double *volume) {@\\ \mbox{}\verb@ cbf_failnez(cbf_compute_cell_volume(cell,volume));@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@""","compute_cell_volume",["double cell[6]"],["Float volume"]],@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@"cbf_compute_reciprocal_cell":["""@\\ \mbox{}\verb@%apply double *OUTPUT {double *astar, double *bstar, double *cstar,@\\ \mbox{}\verb@ double *alphastar, double *betastar, double *gammastar};@\\ \mbox{}\verb@ %inline {@\\ \mbox{}\verb@ void compute_reciprocal_cell(double cell[6], double *astar, double *bstar, double *cstar,@\\ \mbox{}\verb@ double *alphastar, double *betastar, double *gammastar) {@\\ \mbox{}\verb@ double rcell[6];@\\ \mbox{}\verb@ cbf_failnez(cbf_compute_reciprocal_cell(cell,rcell));@\\ \mbox{}\verb@ *astar = rcell[0];@\\ \mbox{}\verb@ *bstar = rcell[1];@\\ \mbox{}\verb@ *cstar = rcell[2];@\\ \mbox{}\verb@ *alphastar = rcell[3];@\\ \mbox{}\verb@ *betastar = rcell[4];@\\ \mbox{}\verb@ *gammastar = rcell[5];@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@@\\ \mbox{}\verb@""","compute_reciprocal_cell",["double cell[6]"],@\\ \mbox{}\verb@["Float astar", "Float bstar", "Float cstar", "Float alphastar", "Float betastar", "Float gammastar"] ]@\\ \mbox{}\verb@@\\ \mbox{}\verb@}@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@class genericwrapper:@\\ \mbox{}\verb@ def __init__(self):@\\ \mbox{}\verb@ self.code = """@\\ \mbox{}\verb@// Start of generic functions@\\ \mbox{}\verb@%feature("autodoc","1");@\\ \mbox{}\verb@"""@\\ \mbox{}\verb@ self.tail = "// End of generic functions\n"@\\ \mbox{}\verb@ def get_code(self):@\\ \mbox{}\verb@ return self.code + self.tail@\\ \mbox{}\verb@ def wrap(self,cfunc,prototype,args,docstring):@\\ \mbox{}\verb@ pyfunc = cfunc.replace("cbf_","")@\\ \mbox{}\verb@ # Insert a comment for debugging this script@\\ \mbox{}\verb@ code = "\n/* cfunc %s pyfunc %s \n"%(cfunc,pyfunc)@\\ \mbox{}\verb@ for a in args:@\\ \mbox{}\verb@ code += " arg %s "%(a)@\\ \mbox{}\verb@ code += "*/\n\n"@\\ \mbox{}\verb@ self.code+=code@\\ \mbox{}\verb@ code = ""@\\ \mbox{}\verb@ not_found = 0@\\ \mbox{}\verb@ try:@\\ \mbox{}\verb@ code, pyname, input, output = cbfgeneric_specials[cfunc]@\\ \mbox{}\verb@ self.code += docstringwrite(pyname,input,output,@\\ \mbox{}\verb@ prototype,docstring)+ code@\\ \mbox{}\verb@ return@\\ \mbox{}\verb@ except KeyError:@\\ \mbox{}\verb@ not_found = 1@\\ \mbox{}\verb@ # print "KeyError"@\\ \mbox{}\verb@ except ValueError:@\\ \mbox{}\verb@ print "problem in generic",cfunc@\\ \mbox{}\verb@ for item in cbfgeneric_specials[cfunc]:@\\ \mbox{}\verb@ print "***",item@\\ \mbox{}\verb@ raise@\\ \mbox{}\verb@ if len(args)==1 and args[0].find("char")>-1 and \@\\ \mbox{}\verb@ args[0].find("**")>-1 :# return string@\\ \mbox{}\verb@ # first write the c code and inline it@\\ \mbox{}\verb@ code += docstringwrite(pyfunc,[],["string"],prototype,docstring)@\\ \mbox{}\verb@ code += "%%inline %%{\n char* %s(void);\n"%(pyfunc)@\\ \mbox{}\verb@ code += " char* %s(void){\n"%(pyfunc)@\\ \mbox{}\verb@ code += " char *r;\n"@\\ \mbox{}\verb@ code += " error_status = %s(&r);\n"%(cfunc)@\\ \mbox{}\verb@ code += " return r; }\n%}\n"@\\ \mbox{}\verb@ # now the thing to wrap is:@\\ \mbox{}\verb@ code += "char* %s(void);"%(pyfunc)@\\ \mbox{}\verb@ self.code=self.code+code@\\ \mbox{}\verb@ return@\\ \mbox{}\verb@ @\\ \mbox{}\verb@# code+= " void %s(void){\n"%(pyfunc)@\\ \mbox{}\verb@# code +=" cbf_failnez(CBF_NOTIMPLEMENTED);}\n"@\\ \mbox{}\verb@# self.code=self.code+code@\\ \mbox{}\verb@ print "Have not implemented:"@\\ \mbox{}\verb@ for s in [cfunc, pyfunc] + args:@\\ \mbox{}\verb@ print "\t",s @\\ \mbox{}\verb@ print@\\ \mbox{}\verb@ return@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@generic_wrapper = genericwrapper()@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@def generate_wrappers(name_dict):@\\ \mbox{}\verb@ names = name_dict.keys()@\\ \mbox{}\verb@ for cname in names:@\\ \mbox{}\verb@ prototype = name_dict[cname][0]@\\ \mbox{}\verb@ docstring = name_dict[cname][1]@\\ \mbox{}\verb@ # print "Generate wrappers: ", "::",cname,"::", prototype,"::", docstring@\\ \mbox{}\verb@ # Check prototype begins with "int cbf_"@\\ \mbox{}\verb@ if prototype.find("int cbf_")!=0:@\\ \mbox{}\verb@ print "problem with:",prototype@\\ \mbox{}\verb@ # Get arguments from prototypes@\\ \mbox{}\verb@ try:@\\ \mbox{}\verb@ args = prototype.split("(")[1].split(")")[0].split(",")@\\ \mbox{}\verb@ args = [ s.lstrip().rstrip() for s in args ] # strip spaces off ends@\\ \mbox{}\verb@ # print "Args: ", args@\\ \mbox{}\verb@ except:@\\ \mbox{}\verb@ # print cname@\\ \mbox{}\verb@ # print prototype@\\ \mbox{}\verb@ raise@\\ \mbox{}\verb@ if args[0].find("cbf_handle")>=0: # This is for the cbfhandle object@\\ \mbox{}\verb@ cbf_handle_wrapper.wrap(cname,prototype,args,docstring)@\\ \mbox{}\verb@ if (cname=="cbf_get_unit_cell"):@\\ \mbox{}\verb@ cbf_handle_wrapper.wrap("cbf_get_unit_cell_esd",prototype,args,docstring)@\\ \mbox{}\verb@ if (cname=="cbf_get_reciprocal_cell"):@\\ \mbox{}\verb@ cbf_handle_wrapper.wrap("cbf_get_reciprocal_cell_esd",prototype,args,docstring)@\\ \mbox{}\verb@ if (cname=="cbf_set_unit_cell"):@\\ \mbox{}\verb@ cbf_handle_wrapper.wrap("cbf_set_unit_cell_esd",prototype,args,docstring)@\\ \mbox{}\verb@ if (cname=="cbf_set_reciprocal_cell"):@\\ \mbox{}\verb@ cbf_handle_wrapper.wrap("cbf_set_reciprocal_cell_esd",prototype,args,docstring)@\\ \mbox{}\verb@ continue@\\ \mbox{}\verb@ if args[0].find("cbf_goniometer")>=0: # This is for the cbfgoniometer@\\ \mbox{}\verb@ cbf_goniometer_wrapper.wrap(cname,prototype,args,docstring)@\\ \mbox{}\verb@ continue@\\ \mbox{}\verb@ if args[0].find("cbf_detector")>=0: # This is for the cbfdetector@\\ \mbox{}\verb@ cbf_detector_wrapper.wrap(cname,prototype,args,docstring)@\\ \mbox{}\verb@ continue@\\ \mbox{}\verb@ generic_wrapper.wrap(cname,prototype,args,docstring)@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@generate_wrappers(name_dict)@\\ \mbox{}\verb@open("cbfgoniometerwrappers.i","w").write(cbf_goniometer_wrapper.get_code())@\\ \mbox{}\verb@open("cbfdetectorwrappers.i","w").write(cbf_detector_wrapper.get_code())@\\ \mbox{}\verb@open("cbfhandlewrappers.i","w").write(cbf_handle_wrapper.get_code())@\\ \mbox{}\verb@open("cbfgenericwrappers.i","w").write(generic_wrapper.get_code())@\\ \mbox{}\verb@@\\ \mbox{}\verb@print "End of output from make_pycbf.py"@\\ \mbox{}\verb@print "\\end{verbatim}"@\\ \mbox{}\verb@@{\NWsep} \end{list} \vspace{-2ex} \end{flushleft} \section{Building python extensions - the setup file} Based on the contents of the makefile for CBFlib we will just pull in all of the library for now. We use the distutils approach. \begin{flushleft} \small \label{scrap9} \verb@"setup.py"@\nobreak\ {\footnotesize \NWtarget{nuweb58}{58} }$\equiv$ \vspace{-1ex} \begin{list}{}{} \item \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@# Import the things to build python binary extensions@\\ \mbox{}\verb@@\\ \mbox{}\verb@from distutils.core import setup, Extension@\\ \mbox{}\verb@@\\ \mbox{}\verb@# Make our extension module@\\ \mbox{}\verb@@\\ \mbox{}\verb@e = Extension('_pycbf',@\\ \mbox{}\verb@ sources = ["pycbf_wrap.c","../src/cbf_simple.c"],@\\ \mbox{}\verb@ extra_compile_args=["-g"],@\\ \mbox{}\verb@ library_dirs=["../lib/"],@\\ \mbox{}\verb@ libraries=["cbf"],@\\ \mbox{}\verb@ include_dirs = ["../include"] )@\\ \mbox{}\verb@ @\\ \mbox{}\verb@# Build it@\\ \mbox{}\verb@setup(name="_pycbf",ext_modules=[e],)@\\ \mbox{}\verb@@{\NWsep} \end{list} \vspace{-2ex} \end{flushleft} \section{Building and testing the resulting package} Aim to build and test in one go (so that the source and the binary match!!) \begin{flushleft} \small \begin{minipage}{\linewidth} \label{scrap10} \verb@"win32.bat"@\nobreak\ {\footnotesize \NWtarget{nuweb59a}{59a} }$\equiv$ \vspace{-1ex} \begin{list}{}{} \item \mbox{}\verb@@\\ \mbox{}\verb@nuweb pycbf@\\ \mbox{}\verb@latex pycbf@\\ \mbox{}\verb@nuweb pycbf@\\ \mbox{}\verb@latex pycbf@\\ \mbox{}\verb@dvipdfm pycbf@\\ \mbox{}\verb@nuweb pycbf@\\ \mbox{}\verb@C:\python24\python make_pycbf.py > TODO.txt@\\ \mbox{}\verb@"C:\program files\swigwin-1.3.31\swig.exe" -python pycbf.i@\\ \mbox{}\verb@C:\python24\python setup.py build --compiler=mingw32@\\ \mbox{}\verb@copy build\lib.win32-2.4\_pycbf.pyd .@\\ \mbox{}\verb@REM C:\python24\python pycbf_test1.py@\\ \mbox{}\verb@C:\python24\python pycbf_test2.py@\\ \mbox{}\verb@C:\python24\python pycbf_test3.py@\\ \mbox{}\verb@C:\python24\lib\pydoc.py -w pycbf@\\ \mbox{}\verb@C:\python24\python makeflatascii.py pycbf_ascii_help.txt@\\ \mbox{}\verb@@{\NWsep} \end{list} \vspace{-2ex} \end{minipage}\\[4ex] \end{flushleft} \begin{flushleft} \small \begin{minipage}{\linewidth} \label{scrap11} \verb@"linux.sh"@\nobreak\ {\footnotesize \NWtarget{nuweb59b}{59b} }$\equiv$ \vspace{-1ex} \begin{list}{}{} \item \mbox{}\verb@@\\ \mbox{}\verb@nuweb pycbf@\\ \mbox{}\verb@latex pycbf@\\ \mbox{}\verb@nuweb pycbf@\\ \mbox{}\verb@latex pycbf@\\ \mbox{}\verb@dvipdfm pycbf@\\ \mbox{}\verb@nuweb pycbf@\\ \mbox{}\verb@lynx -dump CBFlib.html > CBFlib.txt@\\ \mbox{}\verb@python make_pycbf.py @\\ \mbox{}\verb@swig -python pycbf.i@\\ \mbox{}\verb@python setup.py build @\\ \mbox{}\verb@rm _pycbf.so@\\ \mbox{}\verb@cp build/lib.linux-i686-2.4/_pycbf.so .@\\ \mbox{}\verb@python pycbf_test1.py@\\ \mbox{}\verb@python pycbf_test2.py@\\ \mbox{}\verb@pydoc -w pycbf@\\ \mbox{}\verb@python makeflatascii.py pycbf_ascii_help.txt@\\ \mbox{}\verb@@{\NWsep} \end{list} \vspace{-2ex} \end{minipage}\\[4ex] \end{flushleft} This still gives bold in the ascii (=sucks) \begin{flushleft} \small \label{scrap12} \verb@"makeflatascii.py"@\nobreak\ {\footnotesize \NWtarget{nuweb59c}{59c} }$\equiv$ \vspace{-1ex} \begin{list}{}{} \item \mbox{}\verb@@\\ \mbox{}\verb@import pydoc, pycbf, sys@\\ \mbox{}\verb@f = open(sys.argv[1],"w")@\\ \mbox{}\verb@pydoc.pager=lambda text: f.write(text)@\\ \mbox{}\verb@pydoc.TextDoc.bold = lambda self,text : text@\\ \mbox{}\verb@pydoc.help(pycbf)@\\ \mbox{}\verb@@{\NWsep} \end{list} \vspace{-2ex} \end{flushleft} \section{Debugging compiled extensions} Since it can be a bit of a pain to see where things go wrong here is a quick recipe for poking around with a debugger: \begin{verbatim} amber $> gdb /bliss/users//blissadm/python/bliss_python/suse82/bin/python GNU gdb 5.3 Copyright 2002 Free Software Foundation, Inc. GDB is free software, covered by the GNU General Public License, and you are welcome to change it and/or distribute copies of it under certain conditions. Type "show copying" to see the conditions. There is absolutely no warranty for GDB. Type "show warranty" for details. This GDB was configured as "i586-suse-linux"... (gdb) br _PyImport_LoadDynamicModule Breakpoint 1 at 0x80e4199: file Python/importdl.c, line 28. \end{verbatim} This is how to get a breakpoint when loading the module \begin{verbatim} (gdb) run Starting program: /mntdirect/_bliss/users/blissadm/python/bliss_python/suse82/bin/python [New Thread 16384 (LWP 18191)] Python 2.4.2 (#3, Feb 17 2006, 09:12:13) [GCC 3.3 20030226 (prerelease) (SuSE Linux)] on linux2 Type "help", "copyright", "credits" or "license" for more information. >>> import pycbf [Switching to Thread 16384 (LWP 18191)] Breakpoint 1, _PyImport_LoadDynamicModule (name=0xbfffd280 "_pycbf.so", pathname=0xbfffd280 "_pycbf.so", fp=0x819e208) at Python/importdl.c:28 28 if ((m = _PyImport_FindExtension(name, pathname)) != NULL) { (gdb) finish Run till exit from #0 _PyImport_LoadDynamicModule ( name=0xbfffd280 "_pycbf.so", pathname=0xbfffd280 "_pycbf.so", fp=0x819e208) at Python/importdl.c:28 load_module (name=0xbfffd710 "_pycbf", fp=0x819e208, buf=0xbfffd280 "_pycbf.so", type=3, loader=0x405b44f4) at Python/import.c:1678 1678 break; Value returned is $1 = (PyObject *) 0x405662fc (gdb) break cbf_read_file Breakpoint 2 at 0x407f0508: file ../src/cbf.c, line 221. (gdb) cont Continuing. \end{verbatim} We now have a breakpoint where we wanted inside the dynamically loaded file. \begin{verbatim} >>> o=pycbf.cbf_handle_struct() >>> o.read_file("../img2cif_packed.cif",pycbf.MSG_DIGEST) Breakpoint 2, cbf_read_file (handle=0x81f7c08, stream=0x8174f58, headers=136281096) at ../src/cbf.c:221 221 if (!handle) (gdb) \end{verbatim} Now you can step through the c... \section{Things which are currently missing} This is the to do list. Obviously we could benefit a lot from more extensive testing and checking of the docstrings etc. \input "TODO.txt" \section{Testing} Some test programs to see if anything appears to work. Eventually it would be good to write a proper unit test suite. \subsection{Read a file based on cif2cbf.c} This is a pretty ugly translation of the program cif2cbf.c skipping all of the writing parts. It appeared to work with the file img2cif\_packed.cif which is built when you build CBFlib, hence that file is hardwired in. \begin{flushleft} \small \label{scrap13} \verb@"pycbf_test1.py"@\nobreak\ {\footnotesize \NWtarget{nuweb61}{61} }$\equiv$ \vspace{-1ex} \begin{list}{}{} \item \mbox{}\verb@@\\ \mbox{}\verb@import pycbf@\\ \mbox{}\verb@object = pycbf.cbf_handle_struct() # FIXME@\\ \mbox{}\verb@object.read_file("../img2cif_packed.cif",pycbf.MSG_DIGEST)@\\ \mbox{}\verb@object.rewind_datablock()@\\ \mbox{}\verb@print "Found",object.count_datablocks(),"blocks"@\\ \mbox{}\verb@object.select_datablock(0)@\\ \mbox{}\verb@print "Zeroth is named",object.datablock_name()@\\ \mbox{}\verb@object.rewind_category()@\\ \mbox{}\verb@categories = object.count_categories()@\\ \mbox{}\verb@for i in range(categories):@\\ \mbox{}\verb@ print "Category:",i,@\\ \mbox{}\verb@ object.select_category(i)@\\ \mbox{}\verb@ category_name = object.category_name()@\\ \mbox{}\verb@ print "Name:",category_name,@\\ \mbox{}\verb@ rows=object.count_rows()@\\ \mbox{}\verb@ print "Rows:",rows,@\\ \mbox{}\verb@ cols = object.count_columns()@\\ \mbox{}\verb@ print "Cols:",cols@\\ \mbox{}\verb@ loop=1@\\ \mbox{}\verb@ object.rewind_column()@\\ \mbox{}\verb@ while loop is not 0:@\\ \mbox{}\verb@ column_name = object.column_name()@\\ \mbox{}\verb@ print "column name \"",column_name,"\"",@\\ \mbox{}\verb@ try:@\\ \mbox{}\verb@ object.next_column()@\\ \mbox{}\verb@ except:@\\ \mbox{}\verb@ break@\\ \mbox{}\verb@ print@\\ \mbox{}\verb@ for j in range(rows):@\\ \mbox{}\verb@ object.select_row(j)@\\ \mbox{}\verb@ object.rewind_column()@\\ \mbox{}\verb@ print "row:",j@\\ \mbox{}\verb@ for k in range(cols):@\\ \mbox{}\verb@ name=object.column_name()@\\ \mbox{}\verb@ print "col:",name,@\\ \mbox{}\verb@ object.select_column(k)@\\ \mbox{}\verb@ typeofvalue=object.get_typeofvalue()@\\ \mbox{}\verb@ print "type:",typeofvalue@\\ \mbox{}\verb@ if typeofvalue.find("bnry") > -1:@\\ \mbox{}\verb@ print "Found the binary!!",@\\ \mbox{}\verb@ s=object.get_integerarray_as_string()@\\ \mbox{}\verb@ print type(s)@\\ \mbox{}\verb@ print dir(s)@\\ \mbox{}\verb@ print len(s)@\\ \mbox{}\verb@ try:@\\ \mbox{}\verb@ import Numeric@\\ \mbox{}\verb@ d = Numeric.fromstring(s,Numeric.UInt32) @\\ \mbox{}\verb@ # Hard wired Unsigned Int32@\\ \mbox{}\verb@ print d.shape@\\ \mbox{}\verb@ print d[0:10],d[d.shape[0]/2],d[-1]@\\ \mbox{}\verb@ d=Numeric.reshape(d,(2300,2300))@\\ \mbox{}\verb@# from matplotlib import pylab@\\ \mbox{}\verb@# pylab.imshow(d,vmin=0,vmax=1000)@\\ \mbox{}\verb@# pylab.show()@\\ \mbox{}\verb@ except ImportError:@\\ \mbox{}\verb@ print "You need to get Numeric and matplotlib to see the data"@\\ \mbox{}\verb@ else:@\\ \mbox{}\verb@ value=object.get_value()@\\ \mbox{}\verb@ print "Val:",value,i@\\ \mbox{}\verb@ print@\\ \mbox{}\verb@del(object)@\\ \mbox{}\verb@#@\\ \mbox{}\verb@print dir()@\\ \mbox{}\verb@#object.free_handle(handle) @\\ \mbox{}\verb@@{\NWsep} \end{list} \vspace{-2ex} \end{flushleft} \subsection{Try to test the goniometer and detector} Had some initial difficulties but then downloaded an input cbf file which defines a goniometer and detector. The file was found in the example data which comes with CBFlib. This test is clearly minimalistic for now - it only checks the objects for apparent existence of a single member function. \begin{flushleft} \small \label{scrap14} \verb@"pycbf_test2.py"@\nobreak\ {\footnotesize \NWtarget{nuweb62a}{62a} }$\equiv$ \vspace{-1ex} \begin{list}{}{} \item \mbox{}\verb@@\\ \mbox{}\verb@import pycbf@\\ \mbox{}\verb@obj = pycbf.cbf_handle_struct()@\\ \mbox{}\verb@obj.read_file("../adscconverted.cbf",0)@\\ \mbox{}\verb@obj.select_datablock(0)@\\ \mbox{}\verb@g = obj.construct_goniometer()@\\ \mbox{}\verb@print "Rotation axis is",g.get_rotation_axis()@\\ \mbox{}\verb@d = obj.construct_detector(0)@\\ \mbox{}\verb@print "Beam center is",d.get_beam_center()@\\ \mbox{}\verb@@{\NWsep} \end{list} \vspace{-2ex} \end{flushleft} It appears to work - eventually. Surprising \subsection{Test cases for the generics} \begin{flushleft} \small \label{scrap15} \verb@"pycbf_test3.py"@\nobreak\ {\footnotesize \NWtarget{nuweb62b}{62b} }$\equiv$ \vspace{-1ex} \begin{list}{}{} \item \mbox{}\verb@@\\ \mbox{}\verb@import pycbf, unittest@\\ \mbox{}\verb@class GenericTests(unittest.TestCase):@\\ \mbox{}\verb@@\\ \mbox{}\verb@ def test_get_local_integer_byte_order(self):@\\ \mbox{}\verb@ self.assertEqual( pycbf.get_local_integer_byte_order(),@\\ \mbox{}\verb@ 'little_endian')@\\ \mbox{}\verb@@\\ \mbox{}\verb@ def test_get_local_real_byte_order(self):@\\ \mbox{}\verb@ self.assertEqual( pycbf.get_local_real_byte_order() ,@\\ \mbox{}\verb@ 'little_endian')@\\ \mbox{}\verb@@\\ \mbox{}\verb@ def test_get_local_real_format(self):@\\ \mbox{}\verb@ self.assertEqual( pycbf.get_local_real_format(), @\\ \mbox{}\verb@ 'ieee 754-1985')@\\ \mbox{}\verb@@\\ \mbox{}\verb@ def test_compute_cell_volume(self):@\\ \mbox{}\verb@ self.assertEqual( pycbf.compute_cell_volume((2.,3.,4.,90.,90.,90.)),@\\ \mbox{}\verb@ 24.0)@\\ \mbox{}\verb@if __name__=="__main__":@\\ \mbox{}\verb@ unittest.main()@\\ \mbox{}\verb@@\\ \mbox{}\verb@@{\NWsep} \end{list} \vspace{-2ex} \end{flushleft} \section{Worked example 1 : xmas beamline + mar ccd detector at the ESRF} Now for the interesting part. We will attempt to actually use pycbf for a real dataprocessing task. Crazy you might think. The idea is the following - we want to take the header information from some mar ccd files (and eventually also the user or the spec control system) and pass this information into cif headers which can be read by fit2d (etc). \subsection{Reading marccd headers} Some relatively ugly code which parses a c header and then tries to interpret the mar ccd header format. FIXME : byteswapping and ends??? \begin{flushleft} \small \label{scrap16} \verb@"xmas/readmarheader.py"@\nobreak\ {\footnotesize \NWtarget{nuweb63}{63} }$\equiv$ \vspace{-1ex} \begin{list}{}{} \item \mbox{}\verb@#!/usr/bin/env python@\\ \mbox{}\verb@import struct@\\ \mbox{}\verb@@\\ \mbox{}\verb@# Convert mar c header file types to python struct module types@\\ \mbox{}\verb@mar_c_to_python_struct = {@\\ \mbox{}\verb@ "INT32" : "i",@\\ \mbox{}\verb@ "UINT32" : "I",@\\ \mbox{}\verb@ "char" : "c",@\\ \mbox{}\verb@ "UINT16" : "H"@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@@\\ \mbox{}\verb@# Sizes (bytes) of mar c header objects@\\ \mbox{}\verb@mar_c_sizes = {@\\ \mbox{}\verb@ "INT32" : 4,@\\ \mbox{}\verb@ "UINT32" : 4,@\\ \mbox{}\verb@ "char" : 1,@\\ \mbox{}\verb@ "UINT16" : 2@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@@\\ \mbox{}\verb@# This was worked out by trial and error from a trial image I think@\\ \mbox{}\verb@MAXIMAGES=9@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@def make_format(cdefinition):@\\ \mbox{}\verb@ """@\\ \mbox{}\verb@ Reads the header definition in c and makes the format @\\ \mbox{}\verb@ string to pass to struct.unpack@\\ \mbox{}\verb@ """@\\ \mbox{}\verb@ lines = cdefinition.split("\n")@\\ \mbox{}\verb@ fmt = ""@\\ \mbox{}\verb@ names = []@\\ \mbox{}\verb@ expected = 0@\\ \mbox{}\verb@ for line in lines:@\\ \mbox{}\verb@ if line.find(";")==-1:@\\ \mbox{}\verb@ continue@\\ \mbox{}\verb@ decl = line.split(";")[0].lstrip().rstrip()@\\ \mbox{}\verb@ try:@\\ \mbox{}\verb@ [type, name] = decl.split()@\\ \mbox{}\verb@ except:@\\ \mbox{}\verb@ #print "skipping:",line@\\ \mbox{}\verb@ continue@\\ \mbox{}\verb@ # print "type:",type," name:",name@\\ \mbox{}\verb@@\\ \mbox{}\verb@ if name.find("[")>-1:@\\ \mbox{}\verb@ # repeated ... times@\\ \mbox{}\verb@ try:@\\ \mbox{}\verb@ num = name.split("[")[1].split("]")[0]@\\ \mbox{}\verb@ num = num.replace("MAXIMAGES",str(MAXIMAGES))@\\ \mbox{}\verb@ num = num.replace("sizeof(INT32)","4")@\\ \mbox{}\verb@ times = eval(num)@\\ \mbox{}\verb@ except:@\\ \mbox{}\verb@ print "Please decode",decl@\\ \mbox{}\verb@ raise@\\ \mbox{}\verb@ else:@\\ \mbox{}\verb@ times=1@\\ \mbox{}\verb@ try:@\\ \mbox{}\verb@ fmt += mar_c_to_python_struct[type]*times@\\ \mbox{}\verb@ names += [name]*times@\\ \mbox{}\verb@ expected += mar_c_sizes[type]*times@\\ \mbox{}\verb@ except:@\\ \mbox{}\verb@ #print "skipping",line@\\ \mbox{}\verb@ continue@\\ \mbox{}\verb@ #print "%4d %4d"%(mar_c_sizes[type]*times,expected),name,":",times,line@\\ \mbox{}\verb@ #print struct.calcsize(fmt),expected@\\ \mbox{}\verb@ return names, fmt@\\ \mbox{}\verb@@\\ \mbox{}\verb@def read_mar_header(filename):@\\ \mbox{}\verb@ """@\\ \mbox{}\verb@ Get the header from a binary file@\\ \mbox{}\verb@ """@\\ \mbox{}\verb@ f = open(filename,"rb")@\\ \mbox{}\verb@ f.seek(1024)@\\ \mbox{}\verb@ header=f.read(3072)@\\ \mbox{}\verb@ f.close()@\\ \mbox{}\verb@ return header@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@def interpret_header(header, fmt, names):@\\ \mbox{}\verb@ """@\\ \mbox{}\verb@ given a format and header interpret it@\\ \mbox{}\verb@ """@\\ \mbox{}\verb@ values = struct.unpack(fmt,header)@\\ \mbox{}\verb@ dict = {}@\\ \mbox{}\verb@ i=0@\\ \mbox{}\verb@ for name in names:@\\ \mbox{}\verb@ if dict.has_key(name):@\\ \mbox{}\verb@ if type(values[i]) == type("string"): @\\ \mbox{}\verb@ dict[name] = dict[name]+values[i]@\\ \mbox{}\verb@ else:@\\ \mbox{}\verb@ try:@\\ \mbox{}\verb@ dict[name].append(values[i])@\\ \mbox{}\verb@ except:@\\ \mbox{}\verb@ dict[name] = [dict[name],values[i]]@\\ \mbox{}\verb@ else:@\\ \mbox{}\verb@ dict[name] = values[i]@\\ \mbox{}\verb@ i=i+1@\\ \mbox{}\verb@@\\ \mbox{}\verb@ return dict@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@# Now for the c definition (found on mar webpage)@\\ \mbox{}\verb@# The following string is therefore copyrighted by Mar I guess@\\ \mbox{}\verb@ @\\ \mbox{}\verb@cdefinition = """@\\ \mbox{}\verb@typedef struct frame_header_type {@\\ \mbox{}\verb@ /* File/header format parameters (256 bytes) */@\\ \mbox{}\verb@ UINT32 header_type; /* flag for header type @\\ \mbox{}\verb@ (can be used as magic number) */@\\ \mbox{}\verb@ char header_name[16]; /* header name (MMX) */@\\ \mbox{}\verb@ UINT32 header_major_version; /* header_major_version (n.) */@\\ \mbox{}\verb@ UINT32 header_minor_version; /* header_minor_version (.n) */@\\ \mbox{}\verb@ UINT32 header_byte_order;/* BIG_ENDIAN (Motorola,MIPS); @\\ \mbox{}\verb@ LITTLE_ENDIAN (DEC, Intel) */@\\ \mbox{}\verb@ UINT32 data_byte_order; /* BIG_ENDIAN (Motorola,MIPS); @\\ \mbox{}\verb@ LITTLE_ENDIAN (DEC, Intel) */@\\ \mbox{}\verb@ UINT32 header_size; /* in bytes */@\\ \mbox{}\verb@ UINT32 frame_type; /* flag for frame type */@\\ \mbox{}\verb@ UINT32 magic_number; /* to be used as a flag - @\\ \mbox{}\verb@ usually to indicate new file */@\\ \mbox{}\verb@ UINT32 compression_type; /* type of image compression */@\\ \mbox{}\verb@ UINT32 compression1; /* compression parameter 1 */@\\ \mbox{}\verb@ UINT32 compression2; /* compression parameter 2 */@\\ \mbox{}\verb@ UINT32 compression3; /* compression parameter 3 */@\\ \mbox{}\verb@ UINT32 compression4; /* compression parameter 4 */@\\ \mbox{}\verb@ UINT32 compression5; /* compression parameter 4 */@\\ \mbox{}\verb@ UINT32 compression6; /* compression parameter 4 */@\\ \mbox{}\verb@ UINT32 nheaders; /* total number of headers */@\\ \mbox{}\verb@ UINT32 nfast; /* number of pixels in one line */@\\ \mbox{}\verb@ UINT32 nslow; /* number of lines in image */@\\ \mbox{}\verb@ UINT32 depth; /* number of bytes per pixel */@\\ \mbox{}\verb@ UINT32 record_length; /* number of pixels between @\\ \mbox{}\verb@ succesive rows */@\\ \mbox{}\verb@ UINT32 signif_bits; /* true depth of data, in bits */@\\ \mbox{}\verb@ UINT32 data_type; /* (signed,unsigned,float...) */@\\ \mbox{}\verb@ UINT32 saturated_value; /* value marks pixel as saturated */@\\ \mbox{}\verb@ UINT32 sequence; /* TRUE or FALSE */@\\ \mbox{}\verb@ UINT32 nimages; /* total number of images - size of @\\ \mbox{}\verb@ each is nfast*(nslow/nimages) */@\\ \mbox{}\verb@ UINT32 origin; /* corner of origin */@\\ \mbox{}\verb@ UINT32 orientation; /* direction of fast axis */@\\ \mbox{}\verb@ UINT32 view_direction; /* direction to view frame */@\\ \mbox{}\verb@ UINT32 overflow_location;/* FOLLOWING_HEADER, FOLLOWING_DATA */@\\ \mbox{}\verb@ UINT32 over_8_bits; /* # of pixels with counts 255 */@\\ \mbox{}\verb@ UINT32 over_16_bits; /* # of pixels with count 65535 */@\\ \mbox{}\verb@ UINT32 multiplexed; /* multiplex flag */@\\ \mbox{}\verb@ UINT32 nfastimages; /* # of images in fast direction */@\\ \mbox{}\verb@ UINT32 nslowimages; /* # of images in slow direction */@\\ \mbox{}\verb@ UINT32 background_applied; /* flags correction has been applied - @\\ \mbox{}\verb@ hold magic number ? */@\\ \mbox{}\verb@ UINT32 bias_applied; /* flags correction has been applied - @\\ \mbox{}\verb@ hold magic number ? */@\\ \mbox{}\verb@ UINT32 flatfield_applied; /* flags correction has been applied - @\\ \mbox{}\verb@ hold magic number ? */@\\ \mbox{}\verb@ UINT32 distortion_applied; /* flags correction has been applied - @\\ \mbox{}\verb@ hold magic number ? */@\\ \mbox{}\verb@ UINT32 original_header_type; /* Header/frame type from file @\\ \mbox{}\verb@ that frame is read from */@\\ \mbox{}\verb@ UINT32 file_saved; /* Flag that file has been saved, @\\ \mbox{}\verb@ should be zeroed if modified */@\\ \mbox{}\verb@ char reserve1[(64-40)*sizeof(INT32)-16];@\\ \mbox{}\verb@@\\ \mbox{}\verb@ /* Data statistics (128) */@\\ \mbox{}\verb@ UINT32 total_counts[2]; /* 64 bit integer range = 1.85E19*/@\\ \mbox{}\verb@ UINT32 special_counts1[2];@\\ \mbox{}\verb@ UINT32 special_counts2[2];@\\ \mbox{}\verb@ UINT32 min;@\\ \mbox{}\verb@ UINT32 max;@\\ \mbox{}\verb@ UINT32 mean;@\\ \mbox{}\verb@ UINT32 rms;@\\ \mbox{}\verb@ UINT32 p10;@\\ \mbox{}\verb@ UINT32 p90;@\\ \mbox{}\verb@ UINT32 stats_uptodate;@\\ \mbox{}\verb@ UINT32 pixel_noise[MAXIMAGES]; /* 1000*base noise value (ADUs) */@\\ \mbox{}\verb@ char reserve2[(32-13-MAXIMAGES)*sizeof(INT32)];@\\ \mbox{}\verb@@\\ \mbox{}\verb@ /* More statistics (256) */@\\ \mbox{}\verb@ UINT16 percentile[128];@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@ /* Goniostat parameters (128 bytes) */@\\ \mbox{}\verb@ INT32 xtal_to_detector; /* 1000*distance in millimeters */@\\ \mbox{}\verb@ INT32 beam_x; /* 1000*x beam position (pixels) */@\\ \mbox{}\verb@ INT32 beam_y; /* 1000*y beam position (pixels) */@\\ \mbox{}\verb@ INT32 integration_time; /* integration time in milliseconds */@\\ \mbox{}\verb@ INT32 exposure_time; /* exposure time in milliseconds */@\\ \mbox{}\verb@ INT32 readout_time; /* readout time in milliseconds */@\\ \mbox{}\verb@ INT32 nreads; /* number of readouts to get this image */@\\ \mbox{}\verb@ INT32 start_twotheta; /* 1000*two_theta angle */@\\ \mbox{}\verb@ INT32 start_omega; /* 1000*omega angle */@\\ \mbox{}\verb@ INT32 start_chi; /* 1000*chi angle */@\\ \mbox{}\verb@ INT32 start_kappa; /* 1000*kappa angle */@\\ \mbox{}\verb@ INT32 start_phi; /* 1000*phi angle */@\\ \mbox{}\verb@ INT32 start_delta; /* 1000*delta angle */@\\ \mbox{}\verb@ INT32 start_gamma; /* 1000*gamma angle */@\\ \mbox{}\verb@ INT32 start_xtal_to_detector; /* 1000*distance in mm (dist in um)*/@\\ \mbox{}\verb@ INT32 end_twotheta; /* 1000*two_theta angle */@\\ \mbox{}\verb@ INT32 end_omega; /* 1000*omega angle */@\\ \mbox{}\verb@ INT32 end_chi; /* 1000*chi angle */@\\ \mbox{}\verb@ INT32 end_kappa; /* 1000*kappa angle */@\\ \mbox{}\verb@ INT32 end_phi; /* 1000*phi angle */@\\ \mbox{}\verb@ INT32 end_delta; /* 1000*delta angle */@\\ \mbox{}\verb@ INT32 end_gamma; /* 1000*gamma angle */@\\ \mbox{}\verb@ INT32 end_xtal_to_detector; /* 1000*distance in mm (dist in um)*/@\\ \mbox{}\verb@ INT32 rotation_axis; /* active rotation axis */@\\ \mbox{}\verb@ INT32 rotation_range; /* 1000*rotation angle */@\\ \mbox{}\verb@ INT32 detector_rotx; /* 1000*rotation of detector around X */@\\ \mbox{}\verb@ INT32 detector_roty; /* 1000*rotation of detector around Y */@\\ \mbox{}\verb@ INT32 detector_rotz; /* 1000*rotation of detector around Z */@\\ \mbox{}\verb@ char reserve3[(32-28)*sizeof(INT32)];@\\ \mbox{}\verb@@\\ \mbox{}\verb@ /* Detector parameters (128 bytes) */@\\ \mbox{}\verb@ INT32 detector_type; /* detector type */@\\ \mbox{}\verb@ INT32 pixelsize_x; /* pixel size (nanometers) */@\\ \mbox{}\verb@ INT32 pixelsize_y; /* pixel size (nanometers) */@\\ \mbox{}\verb@ INT32 mean_bias; /* 1000*mean bias value */@\\ \mbox{}\verb@ INT32 photons_per_100adu; /* photons / 100 ADUs */@\\ \mbox{}\verb@ INT32 measured_bias[MAXIMAGES]; /* 1000*mean bias value for each image*/@\\ \mbox{}\verb@ INT32 measured_temperature[MAXIMAGES]; /* Temperature of each @\\ \mbox{}\verb@ detector in milliKelvins */@\\ \mbox{}\verb@ INT32 measured_pressure[MAXIMAGES]; /* Pressure of each chamber @\\ \mbox{}\verb@ in microTorr */@\\ \mbox{}\verb@ /* Retired reserve4 when MAXIMAGES set to 9 from 16 and @\\ \mbox{}\verb@ two fields removed, and temp and pressure added@\\ \mbox{}\verb@ char reserve4[(32-(5+3*MAXIMAGES))*sizeof(INT32)]@\\ \mbox{}\verb@ */@\\ \mbox{}\verb@@\\ \mbox{}\verb@ /* X-ray source and optics parameters (128 bytes) */@\\ \mbox{}\verb@ /* X-ray source parameters (8*4 bytes) */@\\ \mbox{}\verb@ INT32 source_type; /* (code) - target, synch. etc */@\\ \mbox{}\verb@ INT32 source_dx; /* Optics param. - (size microns) */@\\ \mbox{}\verb@ INT32 source_dy; /* Optics param. - (size microns) */@\\ \mbox{}\verb@ INT32 source_wavelength; /* wavelength (femtoMeters) */@\\ \mbox{}\verb@ INT32 source_power; /* (Watts) */@\\ \mbox{}\verb@ INT32 source_voltage; /* (Volts) */@\\ \mbox{}\verb@ INT32 source_current; /* (microAmps) */@\\ \mbox{}\verb@ INT32 source_bias; /* (Volts) */@\\ \mbox{}\verb@ INT32 source_polarization_x; /* () */@\\ \mbox{}\verb@ INT32 source_polarization_y; /* () */@\\ \mbox{}\verb@ char reserve_source[4*sizeof(INT32)];@\\ \mbox{}\verb@@\\ \mbox{}\verb@ /* X-ray optics_parameters (8*4 bytes) */@\\ \mbox{}\verb@ INT32 optics_type; /* Optics type (code)*/@\\ \mbox{}\verb@ INT32 optics_dx; /* Optics param. - (size microns) */@\\ \mbox{}\verb@ INT32 optics_dy; /* Optics param. - (size microns) */@\\ \mbox{}\verb@ INT32 optics_wavelength; /* Optics param. - (size microns) */@\\ \mbox{}\verb@ INT32 optics_dispersion; /* Optics param. - (*10E6) */@\\ \mbox{}\verb@ INT32 optics_crossfire_x; /* Optics param. - (microRadians) */@\\ \mbox{}\verb@ INT32 optics_crossfire_y; /* Optics param. - (microRadians) */@\\ \mbox{}\verb@ INT32 optics_angle; /* Optics param. - (monoch. @\\ \mbox{}\verb@ 2theta - microradians) */@\\ \mbox{}\verb@ INT32 optics_polarization_x; /* () */@\\ \mbox{}\verb@ INT32 optics_polarization_y; /* () */@\\ \mbox{}\verb@ char reserve_optics[4*sizeof(INT32)];@\\ \mbox{}\verb@@\\ \mbox{}\verb@ char reserve5[((32-28)*sizeof(INT32))];@\\ \mbox{}\verb@@\\ \mbox{}\verb@ /* File parameters (1024 bytes) */@\\ \mbox{}\verb@ char filetitle[128]; /* Title */@\\ \mbox{}\verb@ char filepath[128]; /* path name for data file */@\\ \mbox{}\verb@ char filename[64]; /* name of data file */@\\ \mbox{}\verb@ char acquire_timestamp[32]; /* date and time of acquisition */@\\ \mbox{}\verb@ char header_timestamp[32]; /* date and time of header update */@\\ \mbox{}\verb@ char save_timestamp[32]; /* date and time file saved */@\\ \mbox{}\verb@ char file_comments[512]; /* comments, use as desired */@\\ \mbox{}\verb@ char reserve6[1024-(128+128+64+(3*32)+512)];@\\ \mbox{}\verb@@\\ \mbox{}\verb@ /* Dataset parameters (512 bytes) */@\\ \mbox{}\verb@ char dataset_comments[512]; /* comments, used as desired */@\\ \mbox{}\verb@ /* pad out to 3072 bytes */@\\ \mbox{}\verb@ char pad[3072-(256+128+256+(3*128)+1024+512)]; @\\ \mbox{}\verb@@\\ \mbox{}\verb@ } frame_header;@\\ \mbox{}\verb@"""@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@class marheaderreader:@\\ \mbox{}\verb@ """@\\ \mbox{}\verb@ Class to sit and read a series of images (makes format etc only once)@\\ \mbox{}\verb@ """@\\ \mbox{}\verb@ def __init__(self):@\\ \mbox{}\verb@ """@\\ \mbox{}\verb@ Initialise internal stuff@\\ \mbox{}\verb@ """@\\ \mbox{}\verb@ self.names , self.fmt = make_format(cdefinition)@\\ \mbox{}\verb@ def get_header(self,filename):@\\ \mbox{}\verb@ """@\\ \mbox{}\verb@ Reads a header from file filename@\\ \mbox{}\verb@ """@\\ \mbox{}\verb@ h=read_mar_header(filename)@\\ \mbox{}\verb@ dict = interpret_header(h,self.fmt,self.names)@\\ \mbox{}\verb@ # Append ESRF formatted stuff@\\ \mbox{}\verb@ items = self.readesrfstring(dict["dataset_comments[512]"])@\\ \mbox{}\verb@ for pair in items:@\\ \mbox{}\verb@ dict[pair[0]]=pair[1]@\\ \mbox{}\verb@ items = self.readesrfstring(dict["file_comments[512]"])@\\ \mbox{}\verb@ for pair in items:@\\ \mbox{}\verb@ dict[pair[0]]=pair[1]@\\ \mbox{}\verb@ dict["pixelsize_x_mm"]= str(float(dict["pixelsize_x"])/1e6)@\\ \mbox{}\verb@ dict["pixelsize_y_mm"]= str(float(dict["pixelsize_y"])/1e6)@\\ \mbox{}\verb@ dict["integration_time_sec"]= str(float(dict["integration_time"])/1e3)@\\ \mbox{}\verb@ dict["beam_y_mm"]= str(float(dict["pixelsize_y_mm"])*@\\ \mbox{}\verb@ float(dict["beam_y"])/1000.)@\\ \mbox{}\verb@ dict["beam_x_mm"]= str(float(dict["pixelsize_x_mm"])*@\\ \mbox{}\verb@ float(dict["beam_x"])/1000.)@\\ \mbox{}\verb@ @\\ \mbox{}\verb@ return dict@\\ \mbox{}\verb@ @\\ \mbox{}\verb@ def readesrfstring(self,s):@\\ \mbox{}\verb@ """@\\ \mbox{}\verb@ Interpret the so called "esrf format" header lines @\\ \mbox{}\verb@ which are in comment sections@\\ \mbox{}\verb@ """@\\ \mbox{}\verb@ s=s.replace("\000","")@\\ \mbox{}\verb@ items = filter(None, [len(x)>1 and x or None for x in [@\\ \mbox{}\verb@ item.split("=") for item in s.split(";")]])@\\ \mbox{}\verb@ return items@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@if __name__=="__main__":@\\ \mbox{}\verb@ """@\\ \mbox{}\verb@ Make a little program to process files@\\ \mbox{}\verb@ """@\\ \mbox{}\verb@ import sys@\\ \mbox{}\verb@ print "Starting"@\\ \mbox{}\verb@ names,fmt = make_format(cdefinition)@\\ \mbox{}\verb@ print "Names and format made"@\\ \mbox{}\verb@ h = read_mar_header(sys.argv[1])@\\ \mbox{}\verb@ print "Read header, interpreting"@\\ \mbox{}\verb@ d = interpret_header(h,fmt,names)@\\ \mbox{}\verb@ printed = {}@\\ \mbox{}\verb@ for name in names:@\\ \mbox{}\verb@ if printed.has_key(name):@\\ \mbox{}\verb@ continue@\\ \mbox{}\verb@ print name,":",d[name]@\\ \mbox{}\verb@ printed[name]=1@\\ \mbox{}\verb@@\\ \mbox{}\verb@@{\NWsep} \end{list} \vspace{-2ex} \end{flushleft} \subsection{Writing out cif files for fit2d/xmas} A script which is supposed to pick up some header information from the mar images, some more infomation from the user and the create cif files. This relies on a "template" cif file to get it started (avoids me programming everything). \begin{flushleft} \small \label{scrap17} \verb@"xmas/xmasheaders.py"@\nobreak\ {\footnotesize \NWtarget{nuweb68}{68} }$\equiv$ \vspace{-1ex} \begin{list}{}{} \item \mbox{}\verb@#!/usr/bin/env python@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@import pycbf@\\ \mbox{}\verb@@\\ \mbox{}\verb@# Some cbf helper functions - obj would be a cbf_handle_struct object@\\ \mbox{}\verb@@\\ \mbox{}\verb@def writewavelength(obj,wavelength):@\\ \mbox{}\verb@ obj.set_wavelength(float(wavelength))@\\ \mbox{}\verb@@\\ \mbox{}\verb@def writecellpar(obj,cifname,value):@\\ \mbox{}\verb@ obj.find_category("cell")@\\ \mbox{}\verb@ obj.find_column(cifname)@\\ \mbox{}\verb@ obj.set_value(value)@\\ \mbox{}\verb@@\\ \mbox{}\verb@def writecell(obj,cell):@\\ \mbox{}\verb@ """@\\ \mbox{}\verb@ call with cell = (a,b,c,alpha,beta,gamma)@\\ \mbox{}\verb@ """@\\ \mbox{}\verb@ obj.find_category("cell")@\\ \mbox{}\verb@ obj.find_column("length_a")@\\ \mbox{}\verb@ obj.set_value(str(cell[0]))@\\ \mbox{}\verb@ obj.find_column("length_b")@\\ \mbox{}\verb@ obj.set_value(str(cell[1]))@\\ \mbox{}\verb@ obj.find_column("length_c")@\\ \mbox{}\verb@ obj.set_value(str(cell[2]))@\\ \mbox{}\verb@ obj.find_column("angle_alpha")@\\ \mbox{}\verb@ obj.set_value(str(cell[3]))@\\ \mbox{}\verb@ obj.find_column("angle_beta")@\\ \mbox{}\verb@ obj.set_value(str(cell[4]))@\\ \mbox{}\verb@ obj.find_column("angle_gamma")@\\ \mbox{}\verb@ obj.set_value(str(cell[5]))@\\ \mbox{}\verb@@\\ \mbox{}\verb@def writeUB(obj,ub):@\\ \mbox{}\verb@ """@\\ \mbox{}\verb@ call with ub that can be indexed ub[i][j]@\\ \mbox{}\verb@ """@\\ \mbox{}\verb@ obj.find_category("diffrn_orient_matrix")@\\ \mbox{}\verb@ for i in (1,2,3):@\\ \mbox{}\verb@ for j in (1,2,3):@\\ \mbox{}\verb@ obj.find_column("UB[%d][%d]"%(i,j))@\\ \mbox{}\verb@ obj.set_value(str(ub[i-1][j-1]))@\\ \mbox{}\verb@ @\\ \mbox{}\verb@def writedistance(obj,distance):@\\ \mbox{}\verb@ obj.set_axis_setting("DETECTOR_Z",float(distance),0.)@\\ \mbox{}\verb@ @\\ \mbox{}\verb@@\\ \mbox{}\verb@def writebeam_x_mm(obj,cen):@\\ \mbox{}\verb@ obj.set_axis_setting("DETECTOR_X",float(cen),0.)@\\ \mbox{}\verb@@\\ \mbox{}\verb@def writebeam_y_mm(obj,cen):@\\ \mbox{}\verb@ obj.set_axis_setting("DETECTOR_Y",float(cen),0.)@\\ \mbox{}\verb@@\\ \mbox{}\verb@def writeSPECcmd(obj,s):@\\ \mbox{}\verb@ obj.find_category("diffrn_measurement")@\\ \mbox{}\verb@ obj.find_column("details")@\\ \mbox{}\verb@ obj.set_value(s)@\\ \mbox{}\verb@@\\ \mbox{}\verb@def writeSPECscan(obj,s):@\\ \mbox{}\verb@ obj.find_category("diffrn_scan")@\\ \mbox{}\verb@ obj.find_column("id")@\\ \mbox{}\verb@ obj.set_value("SCAN%s"%(s))@\\ \mbox{}\verb@ obj.find_category("diffrn_scan_axis")@\\ \mbox{}\verb@ obj.find_column("scan_id")@\\ \mbox{}\verb@ obj.rewind_row()@\\ \mbox{}\verb@ for i in range(obj.count_rows()):@\\ \mbox{}\verb@ obj.select_row(i)@\\ \mbox{}\verb@ obj.set_value("SCAN%s"%(s))@\\ \mbox{}\verb@ obj.find_category("diffrn_scan_frame")@\\ \mbox{}\verb@ obj.find_column("scan_id")@\\ \mbox{}\verb@ obj.rewind_row()@\\ \mbox{}\verb@ obj.set_value("SCAN%s"%(s))@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@def writepixelsize_y_mm(obj,s):@\\ \mbox{}\verb@ """@\\ \mbox{}\verb@ Units are mm for cif@\\ \mbox{}\verb@ """@\\ \mbox{}\verb@ # element number = assume this is first and only detector@\\ \mbox{}\verb@ element_number = 0@\\ \mbox{}\verb@ # axis number = faster or slower... ? Need to check precedence ideally...@\\ \mbox{}\verb@ obj.find_category("array_structure_list")@\\ \mbox{}\verb@ obj.find_column("axis_set_id")@\\ \mbox{}\verb@ obj.find_row("ELEMENT_Y")@\\ \mbox{}\verb@ obj.find_column("precedence")@\\ \mbox{}\verb@ axis_number = obj.get_integervalue()@\\ \mbox{}\verb@ @\\ \mbox{}\verb@ obj.set_pixel_size(element_number, axis_number, float(s) )@\\ \mbox{}\verb@ @\\ \mbox{}\verb@ obj.find_category("array_structure_list_axis")@\\ \mbox{}\verb@ obj.find_column("axis_id")@\\ \mbox{}\verb@ obj.find_row("ELEMENT_Y")@\\ \mbox{}\verb@ obj.find_column("displacement")@\\ \mbox{}\verb@ obj.set_doublevalue("%.6g",float(s)/2.0)@\\ \mbox{}\verb@ obj.find_column("displacement_increment")@\\ \mbox{}\verb@ obj.set_doublevalue("%.6g",float(s))@\\ \mbox{}\verb@@\\ \mbox{}\verb@def writepixelsize_x_mm(obj,s):@\\ \mbox{}\verb@ # element number = assume this is first and only detector@\\ \mbox{}\verb@ element_number = 0@\\ \mbox{}\verb@ # axis number = faster or slower... ? Need to check precedence ideally...@\\ \mbox{}\verb@ obj.find_category("array_structure_list")@\\ \mbox{}\verb@ obj.find_column("axis_set_id")@\\ \mbox{}\verb@ obj.find_row("ELEMENT_X")@\\ \mbox{}\verb@ obj.find_column("precedence")@\\ \mbox{}\verb@ axis_number = obj.get_integervalue()@\\ \mbox{}\verb@ @\\ \mbox{}\verb@ obj.set_pixel_size(element_number, axis_number, float(s) )@\\ \mbox{}\verb@ @\\ \mbox{}\verb@ obj.find_category("array_structure_list_axis")@\\ \mbox{}\verb@ obj.find_column("axis_id")@\\ \mbox{}\verb@ obj.find_row("ELEMENT_X")@\\ \mbox{}\verb@ obj.find_column("displacement")@\\ \mbox{}\verb@ obj.set_doublevalue("%.6g",float(s)/2.0)@\\ \mbox{}\verb@ obj.find_column("displacement_increment")@\\ \mbox{}\verb@ obj.set_doublevalue("%.6g",float(s))@\\ \mbox{}\verb@@\\ \mbox{}\verb@def writeintegrationtime(obj,s):@\\ \mbox{}\verb@ obj.find_category("diffrn_scan_frame")@\\ \mbox{}\verb@ obj.find_column("integration_time")@\\ \mbox{}\verb@ obj.set_value(str(s).replace("\000",""))@\\ \mbox{}\verb@@\\ \mbox{}\verb@def writenfast(obj,s):@\\ \mbox{}\verb@ obj.find_category("array_structure_list")@\\ \mbox{}\verb@ obj.find_column("index")@\\ \mbox{}\verb@ obj.find_row("1")@\\ \mbox{}\verb@ obj.find_column("dimension")@\\ \mbox{}\verb@ obj.set_value(str(s))@\\ \mbox{}\verb@@\\ \mbox{}\verb@def writenslow(obj,s):@\\ \mbox{}\verb@ obj.find_category("array_structure_list")@\\ \mbox{}\verb@ obj.find_column("index")@\\ \mbox{}\verb@ obj.find_row("2")@\\ \mbox{}\verb@ obj.find_column("dimension")@\\ \mbox{}\verb@ obj.set_value(str(s))@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@functiondict = {@\\ \mbox{}\verb@ "lambda" : writewavelength,@\\ \mbox{}\verb@ "beam_x_mm" : writebeam_x_mm,@\\ \mbox{}\verb@ "beam_y_mm" : writebeam_y_mm,@\\ \mbox{}\verb@ "distance" : writedistance,@\\ \mbox{}\verb@ "UB" : writeUB,@\\ \mbox{}\verb@ "cell" : writecell,@\\ \mbox{}\verb@ "cmd" : writeSPECcmd,@\\ \mbox{}\verb@ "scan" : writeSPECscan,@\\ \mbox{}\verb@ "nfast" : writenfast,@\\ \mbox{}\verb@ "nslow" : writenslow,@\\ \mbox{}\verb@ "pixelsize_y_mm" : writepixelsize_y_mm,@\\ \mbox{}\verb@ "pixelsize_x_mm" : writepixelsize_x_mm,@\\ \mbox{}\verb@ "integration_time_sec" : writeintegrationtime,@\\ \mbox{}\verb@ "tth" : lambda obj,value : obj.set_axis_setting(@\\ \mbox{}\verb@ "DETECTOR_TWO_THETA_VERTICAL",float(value),0.),@\\ \mbox{}\verb@ "chi" : lambda obj,value : obj.set_axis_setting(@\\ \mbox{}\verb@ "GONIOMETER_CHI",float(value),0.),@\\ \mbox{}\verb@ "th" : lambda obj,value : obj.set_axis_setting(@\\ \mbox{}\verb@ "GONIOMETER_THETA",float(value),0.),@\\ \mbox{}\verb@ "phi" : lambda obj,value : obj.set_axis_setting(@\\ \mbox{}\verb@ "GONIOMETER_PHI",float(value),0.),@\\ \mbox{}\verb@ "lc_a" : lambda obj,value : writecellpar(obj,"length_a",value),@\\ \mbox{}\verb@ "lc_b" : lambda obj,value : writecellpar(obj,"length_b",value),@\\ \mbox{}\verb@ "lc_c" : lambda obj,value : writecellpar(obj,"length_c",value),@\\ \mbox{}\verb@ "lc_al" : lambda obj,value : writecellpar(obj,"angle_alpha",value),@\\ \mbox{}\verb@ "lc_be" : lambda obj,value : writecellpar(obj,"angle_beta",value),@\\ \mbox{}\verb@ "lc_ga" : lambda obj,value : writecellpar(obj,"angle_gamma",value)@\\ \mbox{}\verb@ }@\\ \mbox{}\verb@@\\ \mbox{}\verb@"""@\\ \mbox{}\verb@ #@\\ \mbox{}\verb@ # Not implementing these for now@\\ \mbox{}\verb@ lc_ra@\\ \mbox{}\verb@ lc_rc 0.4742@\\ \mbox{}\verb@ lc_rb 1.16@\\ \mbox{}\verb@ energy 13@\\ \mbox{}\verb@ cp_phi -180@\\ \mbox{}\verb@ alpha 7.3716@\\ \mbox{}\verb@ lc_ral 90@\\ \mbox{}\verb@ cp_tth -180@\\ \mbox{}\verb@ lc_rga 90@\\ \mbox{}\verb@ beta 17.572@\\ \mbox{}\verb@ omega -2.185@\\ \mbox{}\verb@ h 0.21539@\\ \mbox{}\verb@ k 0.01957@\\ \mbox{}\verb@ l 5.9763@\\ \mbox{}\verb@ cp_chi -180@\\ \mbox{}\verb@ lc_rbe 90@\\ \mbox{}\verb@ cp_th -180@\\ \mbox{}\verb@ azimuth 0@\\ \mbox{}\verb@"""@\\ \mbox{}\verb@@\\ \mbox{}\verb@# Finally a class for creating header files.@\\ \mbox{}\verb@# It reads a template and then offers a processfile command @\\ \mbox{}\verb@# for running over a file series@\\ \mbox{}\verb@@\\ \mbox{}\verb@class cifheader:@\\ \mbox{}\verb@ @\\ \mbox{}\verb@ def __init__(self,templatefile):@\\ \mbox{}\verb@ self.cbf=pycbf.cbf_handle_struct()@\\ \mbox{}\verb@ self.cbf.read_template(templatefile)@\\ \mbox{}\verb@ from readmarheader import marheaderreader@\\ \mbox{}\verb@ self.marheaderreader = marheaderreader()@\\ \mbox{}\verb@@\\ \mbox{}\verb@ @\\ \mbox{}\verb@ def processfile(self,filename, outfile=None,@\\ \mbox{}\verb@ format="mccd",@\\ \mbox{}\verb@ **kwds):@\\ \mbox{}\verb@ outfile=outfile.replace(format,"cif")@\\ \mbox{}\verb@ @\\ \mbox{}\verb@ if format == "mccd":@\\ \mbox{}\verb@ items = self.marheaderreader.get_header(filename)@\\ \mbox{}\verb@@\\ \mbox{}\verb@ if format == "bruker":@\\ \mbox{}\verb@ pass@\\ \mbox{}\verb@ if format == "edf":@\\ \mbox{}\verb@ pass@\\ \mbox{}\verb@ @\\ \mbox{}\verb@ self.items=items@\\ \mbox{}\verb@ @\\ \mbox{}\verb@ # Take the image header items as default@\\ \mbox{}\verb@ self.updateitems(items)@\\ \mbox{}\verb@@\\ \mbox{}\verb@ # Allow them to be overridden@\\ \mbox{}\verb@ self.updateitems(kwds)@\\ \mbox{}\verb@@\\ \mbox{}\verb@ # Write the file@\\ \mbox{}\verb@ self.writefile(outfile)@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@ @\\ \mbox{}\verb@ def writefile(self,filename):@\\ \mbox{}\verb@ self.cbf.write_file(filename,pycbf.CIF,pycbf.MIME_HEADERS,@\\ \mbox{}\verb@ pycbf.ENC_BASE64)@\\ \mbox{}\verb@ @\\ \mbox{}\verb@@\\ \mbox{}\verb@ def updateitems(self,dict):@\\ \mbox{}\verb@ names = dict.keys()@\\ \mbox{}\verb@ for name in names:@\\ \mbox{}\verb@ value = dict[name]@\\ \mbox{}\verb@ # use a dictionary of functions@\\ \mbox{}\verb@ if functiondict.has_key(name):@\\ \mbox{}\verb@ # print "calling",functiondict[name],value@\\ \mbox{}\verb@ apply(functiondict[name],(self.cbf,value))@\\ \mbox{}\verb@ else:@\\ \mbox{}\verb@ #print "ignoring",name,value@\\ \mbox{}\verb@ pass@\\ \mbox{}\verb@@\\ \mbox{}\verb@ @\\ \mbox{}\verb@if __name__=="__main__":@\\ \mbox{}\verb@ import sys@\\ \mbox{}\verb@ @\\ \mbox{}\verb@ obj=cifheader("xmas_cif_template.cif")@\\ \mbox{}\verb@@\\ \mbox{}\verb@ ub = [[0.11, 0.12, 0.13] , [0.21, 0.22, 0.23], [0.31, 0.32, 0.33]]@\\ \mbox{}\verb@@\\ \mbox{}\verb@ for filename in sys.argv[1:]:@\\ \mbox{}\verb@ fileout = filename.split("/")[-1]@\\ \mbox{}\verb@ obj.processfile(filename, outfile=fileout, UB=ub, distance=123.456)@\\ \mbox{}\verb@@{\NWsep} \end{list} \vspace{-2ex} \end{flushleft} \subsection{A template cif file for the xmas beamline} This was sort of copied and modified from an example file. It has NOT been checked. Hopefully the four circle geometry at least vaguely matches what is at the beamline. \begin{flushleft} \small \label{scrap18} \verb@"xmas/xmas_cif_template.cif"@\nobreak\ {\footnotesize \NWtarget{nuweb72}{72} }$\equiv$ \vspace{-1ex} \begin{list}{}{} \item \mbox{}\verb@@\\ \mbox{}\verb@###CBF: VERSION 0.6@\\ \mbox{}\verb@# CBF file written by cbflib v0.6@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@data_image_1@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@loop_@\\ \mbox{}\verb@_diffrn.id@\\ \mbox{}\verb@_diffrn.crystal_id@\\ \mbox{}\verb@ DS1 DIFFRN_CRYSTAL_ID@\\ \mbox{}\verb@@\\ \mbox{}\verb@loop_@\\ \mbox{}\verb@_cell.length_a 5.959(1)@\\ \mbox{}\verb@_cell.length_b 14.956(1)@\\ \mbox{}\verb@_cell.length_c 19.737(3)@\\ \mbox{}\verb@_cell.angle_alpha 90@\\ \mbox{}\verb@_cell.angle_beta 90@\\ \mbox{}\verb@_cell.angle_gamma 90@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@loop_@\\ \mbox{}\verb@_diffrn_orient_matrix.id 'DS1'@\\ \mbox{}\verb@_diffrn_orient_matrix.type @\\ \mbox{}\verb@; reciprocal axis matrix, multiplies hkl vector to generate@\\ \mbox{}\verb@ diffractometer xyz vector and diffractometer angles@\\ \mbox{}\verb@;@\\ \mbox{}\verb@_diffrn_orient_matrix.UB[1][1] 0.11@\\ \mbox{}\verb@_diffrn_orient_matrix.UB[1][2] 0.12@\\ \mbox{}\verb@_diffrn_orient_matrix.UB[1][3] 0.13@\\ \mbox{}\verb@_diffrn_orient_matrix.UB[2][1] 0.21@\\ \mbox{}\verb@_diffrn_orient_matrix.UB[2][2] 0.22@\\ \mbox{}\verb@_diffrn_orient_matrix.UB[2][3] 0.23@\\ \mbox{}\verb@_diffrn_orient_matrix.UB[3][1] 0.31@\\ \mbox{}\verb@_diffrn_orient_matrix.UB[3][2] 0.32@\\ \mbox{}\verb@_diffrn_orient_matrix.UB[3][3] 0.33@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@loop_@\\ \mbox{}\verb@_diffrn_source.diffrn_id@\\ \mbox{}\verb@_diffrn_source.source@\\ \mbox{}\verb@_diffrn_source.current@\\ \mbox{}\verb@_diffrn_source.type@\\ \mbox{}\verb@ DS1 synchrotron 200.0 'XMAS beamline bm28 ESRF'@\\ \mbox{}\verb@@\\ \mbox{}\verb@loop_@\\ \mbox{}\verb@_diffrn_radiation.diffrn_id@\\ \mbox{}\verb@_diffrn_radiation.wavelength_id@\\ \mbox{}\verb@_diffrn_radiation.probe@\\ \mbox{}\verb@_diffrn_radiation.monochromator@\\ \mbox{}\verb@_diffrn_radiation.polarizn_source_ratio@\\ \mbox{}\verb@_diffrn_radiation.polarizn_source_norm@\\ \mbox{}\verb@_diffrn_radiation.div_x_source@\\ \mbox{}\verb@_diffrn_radiation.div_y_source@\\ \mbox{}\verb@_diffrn_radiation.div_x_y_source@\\ \mbox{}\verb@_diffrn_radiation.collimation@\\ \mbox{}\verb@ DS1 WAVELENGTH1 x-ray 'Si 111' 0.8 0.0 0.08 0.01 0.00 '0.20 mm x 0.20 mm'@\\ \mbox{}\verb@@\\ \mbox{}\verb@loop_@\\ \mbox{}\verb@_diffrn_radiation_wavelength.id@\\ \mbox{}\verb@_diffrn_radiation_wavelength.wavelength@\\ \mbox{}\verb@_diffrn_radiation_wavelength.wt@\\ \mbox{}\verb@ WAVELENGTH1 1.73862 1.0@\\ \mbox{}\verb@@\\ \mbox{}\verb@loop_@\\ \mbox{}\verb@_diffrn_detector.diffrn_id@\\ \mbox{}\verb@_diffrn_detector.id@\\ \mbox{}\verb@_diffrn_detector.type@\\ \mbox{}\verb@_diffrn_detector.details@\\ \mbox{}\verb@_diffrn_detector.number_of_axes@\\ \mbox{}\verb@ DS1 MAR 'MAR XMAS' 'slow mode' 5@\\ \mbox{}\verb@@\\ \mbox{}\verb@loop_@\\ \mbox{}\verb@_diffrn_detector_axis.detector_id@\\ \mbox{}\verb@_diffrn_detector_axis.axis_id@\\ \mbox{}\verb@ MAR DETECTOR_TWO_THETA_VERTICAL@\\ \mbox{}\verb@ MAR DETECTOR_X@\\ \mbox{}\verb@ MAR DETECTOR_Y@\\ \mbox{}\verb@ MAR DETECTOR_Z@\\ \mbox{}\verb@ MAR DETECTOR_PITCH@\\ \mbox{}\verb@@\\ \mbox{}\verb@loop_@\\ \mbox{}\verb@_diffrn_detector_element.id@\\ \mbox{}\verb@_diffrn_detector_element.detector_id@\\ \mbox{}\verb@ ELEMENT1 MAR@\\ \mbox{}\verb@@\\ \mbox{}\verb@loop_@\\ \mbox{}\verb@_diffrn_data_frame.id@\\ \mbox{}\verb@_diffrn_data_frame.detector_element_id@\\ \mbox{}\verb@_diffrn_data_frame.array_id@\\ \mbox{}\verb@_diffrn_data_frame.binary_id@\\ \mbox{}\verb@ FRAME1 ELEMENT1 ARRAY1 1@\\ \mbox{}\verb@@\\ \mbox{}\verb@loop_@\\ \mbox{}\verb@_diffrn_measurement.diffrn_id@\\ \mbox{}\verb@_diffrn_measurement.id@\\ \mbox{}\verb@_diffrn_measurement.number_of_axes@\\ \mbox{}\verb@_diffrn_measurement.method@\\ \mbox{}\verb@_diffrn_measurement.details@\\ \mbox{}\verb@ DS1 GONIOMETER 3 rotation@\\ \mbox{}\verb@ 'i0=1.000 i1=1.000 i2=1.000 ib=1.000 beamstop=20 mm 0% attenuation'@\\ \mbox{}\verb@@\\ \mbox{}\verb@loop_@\\ \mbox{}\verb@_diffrn_measurement_axis.measurement_id@\\ \mbox{}\verb@_diffrn_measurement_axis.axis_id@\\ \mbox{}\verb@ GONIOMETER GONIOMETER_PHI@\\ \mbox{}\verb@ GONIOMETER GONIOMETER_CHI@\\ \mbox{}\verb@ GONIOMETER GONIOMETER_THETA@\\ \mbox{}\verb@@\\ \mbox{}\verb@@\\ \mbox{}\verb@loop_@\\ \mbox{}\verb@_diffrn_scan.id@\\ \mbox{}\verb@_diffrn_scan.frame_id_start@\\ \mbox{}\verb@_diffrn_scan.frame_id_end@\\ \mbox{}\verb@_diffrn_scan.frames@\\ \mbox{}\verb@ SCAN1 FRAME1 FRAME1 1@\\ \mbox{}\verb@@\\ \mbox{}\verb@loop_@\\ \mbox{}\verb@_diffrn_scan_axis.scan_id@\\ \mbox{}\verb@_diffrn_scan_axis.axis_id@\\ \mbox{}\verb@_diffrn_scan_axis.angle_start@\\ \mbox{}\verb@_diffrn_scan_axis.angle_range@\\ \mbox{}\verb@_diffrn_scan_axis.angle_increment@\\ \mbox{}\verb@_diffrn_scan_axis.displacement_start@\\ \mbox{}\verb@_diffrn_scan_axis.displacement_range@\\ \mbox{}\verb@_diffrn_scan_axis.displacement_increment@\\ \mbox{}\verb@ SCAN1 GONIOMETER_THETA 0.0 0.0 0.0 0.0 0.0 0.0@\\ \mbox{}\verb@ SCAN1 GONIOMETER_CHI 0.0 0.0 0.0 0.0 0.0 0.0@\\ \mbox{}\verb@ SCAN1 GONIOMETER_PHI 185 1 1 0.0 0.0 0.0@\\ \mbox{}\verb@ SCAN1 DETECTOR_TWO_THETA_VERTICAL 0.0 0.0 0.0 0.0 0.0 0.0@\\ \mbox{}\verb@ SCAN1 DETECTOR_Z 0.0 0.0 0.0 103.750 0 0@\\ \mbox{}\verb@ SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.0 0.0 0.0@\\ \mbox{}\verb@ SCAN1 DETECTOR_X 0.0 0.0 0.0 0.0 0.0 0.0@\\ \mbox{}\verb@ SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0@\\ \mbox{}\verb@@\\ \mbox{}\verb@loop_@\\ \mbox{}\verb@_diffrn_scan_frame.frame_id@\\ \mbox{}\verb@_diffrn_scan_frame.frame_number@\\ \mbox{}\verb@_diffrn_scan_frame.integration_time@\\ \mbox{}\verb@_diffrn_scan_frame.scan_id@\\ \mbox{}\verb@_diffrn_scan_frame.date@\\ \mbox{}\verb@ FRAME1 1 360 SCAN1 1997-12-04T10:23:48@\\ \mbox{}\verb@@\\ \mbox{}\verb@loop_@\\ \mbox{}\verb@_diffrn_scan_frame_axis.frame_id@\\ \mbox{}\verb@_diffrn_scan_frame_axis.axis_id@\\ \mbox{}\verb@_diffrn_scan_frame_axis.angle@\\ \mbox{}\verb@_diffrn_scan_frame_axis.displacement@\\ \mbox{}\verb@ FRAME1 GONIOMETER_THETA 0.0 0.0@\\ \mbox{}\verb@ FRAME1 GONIOMETER_CHI 0.0 0.0@\\ \mbox{}\verb@ FRAME1 GONIOMETER_PHI 185 0.0@\\ \mbox{}\verb@ FRAME1 DETECTOR_TWO_THETA_VERTICAL 185 0.0@\\ \mbox{}\verb@ FRAME1 DETECTOR_Z 0.0 103.750@\\ \mbox{}\verb@ FRAME1 DETECTOR_Y 0.0 0.0@\\ \mbox{}\verb@ FRAME1 DETECTOR_X 0.0 0.0@\\ \mbox{}\verb@ FRAME1 DETECTOR_PITCH 0.0 0.0@\\ \mbox{}\verb@@\\ \mbox{}\verb@loop_@\\ \mbox{}\verb@_axis.id@\\ \mbox{}\verb@_axis.type@\\ \mbox{}\verb@_axis.equipment@\\ \mbox{}\verb@_axis.depends_on@\\ \mbox{}\verb@_axis.vector[1]@\\ \mbox{}\verb@_axis.vector[2]@\\ \mbox{}\verb@_axis.vector[3]@\\ \mbox{}\verb@_axis.offset[1]@\\ \mbox{}\verb@_axis.offset[2]@\\ \mbox{}\verb@_axis.offset[3]@\\ \mbox{}\verb@ GONIOMETER_THETA rotation goniometer . 1 0 0 . . .@\\ \mbox{}\verb@ GONIOMETER_CHI rotation goniometer GONIOMETER_THETA 0 0 1 . . .@\\ \mbox{}\verb@ GONIOMETER_PHI rotation goniometer GONIOMETER_PHI 1 0 0 . . .@\\ \mbox{}\verb@ SOURCE general source . 0 0 1 . . .@\\ \mbox{}\verb@ GRAVITY general gravity . 0 -1 0 . . .@\\ \mbox{}\verb@ DETECTOR_TWO_THETA_VERTICAL rotation goniometer . 1 0 0 . . .@\\ \mbox{}\verb@ DETECTOR_Z translation detector DETECTOR_TWO_THETA_VERTICAL 0 0 -1 0 0 0@\\ \mbox{}\verb@ DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0@\\ \mbox{}\verb@ DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0@\\ \mbox{}\verb@ DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0@\\ \mbox{}\verb@ ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 -94.0032 94.0032 0@\\ \mbox{}\verb@ ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0@\\ \mbox{}\verb@@\\ \mbox{}\verb@loop_@\\ \mbox{}\verb@_array_structure_list.array_id@\\ \mbox{}\verb@_array_structure_list.index@\\ \mbox{}\verb@_array_structure_list.dimension@\\ \mbox{}\verb@_array_structure_list.precedence@\\ \mbox{}\verb@_array_structure_list.direction@\\ \mbox{}\verb@_array_structure_list.axis_set_id@\\ \mbox{}\verb@ ARRAY1 1 2049 1 increasing ELEMENT_X@\\ \mbox{}\verb@ ARRAY1 2 2049 2 increasing ELEMENT_Y@\\ \mbox{}\verb@@\\ \mbox{}\verb@loop_@\\ \mbox{}\verb@_array_structure_list_axis.axis_set_id@\\ \mbox{}\verb@_array_structure_list_axis.axis_id@\\ \mbox{}\verb@_array_structure_list_axis.displacement@\\ \mbox{}\verb@_array_structure_list_axis.displacement_increment@\\ \mbox{}\verb@ ELEMENT_X ELEMENT_X 0.0408 0.0816@\\ \mbox{}\verb@ ELEMENT_Y ELEMENT_Y -0.0408 -0.0816@\\ \mbox{}\verb@@\\ \mbox{}\verb@loop_@\\ \mbox{}\verb@_array_intensities.array_id@\\ \mbox{}\verb@_array_intensities.binary_id@\\ \mbox{}\verb@_array_intensities.linearity@\\ \mbox{}\verb@_array_intensities.gain@\\ \mbox{}\verb@_array_intensities.gain_esd@\\ \mbox{}\verb@_array_intensities.overload@\\ \mbox{}\verb@_array_intensities.undefined_value@\\ \mbox{}\verb@ ARRAY1 1 linear 0.30 0.03 65000 0@\\ \mbox{}\verb@@\\ \mbox{}\verb@loop_@\\ \mbox{}\verb@_array_structure.id@\\ \mbox{}\verb@_array_structure.encoding_type@\\ \mbox{}\verb@_array_structure.compression_type@\\ \mbox{}\verb@_array_structure.byte_order@\\ \mbox{}\verb@ ARRAY1 "signed 32-bit integer" packed little_endian@\\ \mbox{}\verb@@{\NWsep} \end{list} \vspace{-2ex} \end{flushleft} \end{document} ./CBFlib-0.9.2.2/pycbf/pycbf.toc0000644000076500007650000000325111603702120014510 0ustar yayayaya\contentsline {section}{\numberline {1}Introduction}{2}{section.1} \contentsline {section}{\numberline {2}Installation prerequisites}{2}{section.2} \contentsline {section}{\numberline {3}Generating the c interface - the SWIG file}{3}{section.3} \contentsline {subsection}{\numberline {3.1}Exceptions}{5}{subsection.3.1} \contentsline {subsection}{\numberline {3.2}Exceptions}{9}{subsection.3.2} \contentsline {section}{\numberline {4}Docstrings}{10}{section.4} \contentsline {section}{\numberline {5}Wrappers}{10}{section.5} \contentsline {section}{\numberline {6}Building python extensions - the setup file}{58}{section.6} \contentsline {section}{\numberline {7}Building and testing the resulting package}{59}{section.7} \contentsline {section}{\numberline {8}Debugging compiled extensions}{59}{section.8} \contentsline {section}{\numberline {9}Things which are currently missing}{60}{section.9} \contentsline {section}{\numberline {10}Testing}{60}{section.10} \contentsline {subsection}{\numberline {10.1}Read a file based on cif2cbf.c}{60}{subsection.10.1} \contentsline {subsection}{\numberline {10.2}Try to test the goniometer and detector}{62}{subsection.10.2} \contentsline {subsection}{\numberline {10.3}Test cases for the generics}{62}{subsection.10.3} \contentsline {section}{\numberline {11}Worked example 1 : xmas beamline + mar ccd detector at the ESRF}{62}{section.11} \contentsline {subsection}{\numberline {11.1}Reading marccd headers}{63}{subsection.11.1} \contentsline {subsection}{\numberline {11.2}Writing out cif files for fit2d/xmas}{68}{subsection.11.2} \contentsline {subsection}{\numberline {11.3}A template cif file for the xmas beamline}{72}{subsection.11.3} ./CBFlib-0.9.2.2/pycbf/pycbf_i.w0000644000076500007650000004335411603702120014511 0ustar yayayaya% pycbf_i.w % nuweb source file used to create % pycbf.i and to document it in pycbf.w % % pycbf - python binding to the CBFlib library % % Copyright (C) 2005 Jonathan Wright % ESRF, Grenoble, France % email: wright@@esrf.fr % % Revised for CBFlib 0.9 releases, Herbert J. Bernstein, 23 Aug 2010 % %###################################################################### %# # %# YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE INCLUDING PYCBF UNDER THE # %# TERMS OF THE GPL # %# # %# ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API INCLUDING PYCBF # %# UNDER THE TERMS OF THE LGPL # %# # %###################################################################### % %########################### GPL NOTICES ############################## %# # %# This program is free software; you can redistribute it and/or # %# modify it under the terms of the GNU General Public License as # %# published by the Free Software Foundation; either version 2 of # %# (the License, or (at your option) any later version. # %# # %# This program is distributed in the hope that it will be useful, # %# but WITHOUT ANY WARRANTY; without even the implied warranty of # %# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # %# GNU General Public License for more details. # %# # %# You should have received a copy of the GNU General Public License # %# along with this program; if not, write to the Free Software # %# Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA # %# 02111-1307 USA # %# # %###################################################################### % %######################### LGPL NOTICES ############################### %# # %# This library is free software; you can redistribute it and/or # %# modify it under the terms of the GNU Lesser General Public # %# License as published by the Free Software Foundation; either # %# version 2.1 of the License, or (at your option) any later version. # %# # %# This library is distributed in the hope that it will be useful, # %# but WITHOUT ANY WARRANTY; without even the implied warranty of # %# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # %# Lesser General Public License for more details. # %# # %# You should have received a copy of the GNU Lesser General Public # %# License along with this library; if not, write to the Free # %# Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, # %# MA 02110-1301 USA # %# # %###################################################################### % \section{Generating the c interface - the SWIG file} Essentially the swig file starts by saying what to include to build the wrappers, and then goes on to define the python interface for each function we want to call. The library appears to define at least three ``objects''; a CBF handle, a cbf\_goniometer and a cbf\_detector. We will attempt to map these onto python classes. FIXME - decide whether introduce a "binary array" class with converters to more common representations? All of the functions in the library appear to return 0 on success and a meaningful error code on failure. We try to propagate that error code across the language barrier via exceptions. So the SWIG file will start off by including the header files needed for compilation. Note the defintion of constants to be passed as arguments in calls in the form pycbf.CONSTANTNAME @D Constants used for compression @{ // The actual wrappers // Constants needed from header files /* Constants used for compression */ #define CBF_INTEGER 0x0010 /* Uncompressed integer */ #define CBF_FLOAT 0x0020 /* Uncompressed IEEE floating-point */ #define CBF_CANONICAL 0x0050 /* Canonical compression */ #define CBF_PACKED 0x0060 /* Packed compression */ #define CBF_PACKED_V2 0x0090 /* CCP4 Packed (JPA) compression V2 */ #define CBF_BYTE_OFFSET 0x0070 /* Byte Offset Compression */ #define CBF_PREDICTOR 0x0080 /* Predictor_Huffman Compression */ #define CBF_NONE 0x0040 /* No compression flag */ #define CBF_COMPRESSION_MASK \ 0x00FF /* Mask to separate compression type from flags */ #define CBF_FLAG_MASK 0x0F00 /* Mask to separate flags from compression type */ #define CBF_UNCORRELATED_SECTIONS \ 0x0100 /* Flag for uncorrelated sections */ #define CBF_FLAT_IMAGE 0x0200 /* Flag for flat (linear) images */ #define CBF_NO_EXPAND 0x0400 /* Flag to try not to expand */ @} @D Constants used for headers @{ /* Constants used for headers */ #define PLAIN_HEADERS 0x0001 /* Use plain ASCII headers */ #define MIME_HEADERS 0x0002 /* Use MIME headers */ #define MSG_NODIGEST 0x0004 /* Do not check message digests */ #define MSG_DIGEST 0x0008 /* Check message digests */ #define MSG_DIGESTNOW 0x0010 /* Check message digests immediately */ #define MSG_DIGESTWARN 0x0020 /* Warn on message digests immediately*/ #define PAD_1K 0x0020 /* Pad binaries with 1023 0's */ #define PAD_2K 0x0040 /* Pad binaries with 2047 0's */ #define PAD_4K 0x0080 /* Pad binaries with 4095 0's */ @} @D Constants used to control CIF parsing @{ /* Constants used to control CIF parsing */ #define CBF_PARSE_BRC 0x0100 /* PARSE DDLm/CIF2 brace {,...} */ #define CBF_PARSE_PRN 0x0200 /* PARSE DDLm parens (,...) */ #define CBF_PARSE_BKT 0x0400 /* PARSE DDLm brackets [,...] */ #define CBF_PARSE_BRACKETS \ 0x0700 /* PARSE ALL brackets */ #define CBF_PARSE_TQ 0x0800 /* PARSE treble quotes """...""" and '''...''' */ #define CBF_PARSE_CIF2_DELIMS \ 0x1000 /* Do not scan past an unescaped close quote do not accept {} , : " ' in non-delimited strings'{ */ #define CBF_PARSE_DDLm 0x0700 /* For DDLm parse (), [], {} */ #define CBF_PARSE_CIF2 0x1F00 /* For CIF2 parse {}, treble quotes, stop on unescaped close quotes */ #define CBF_PARSE_DEFINES \ 0x2000 /* Recognize DEFINE_name */ #define CBF_PARSE_WIDE 0x4000 /* PARSE wide files */ #define CBF_PARSE_UTF8 0x10000 /* PARSE UTF-8 */ #define HDR_DEFAULT (MIME_HEADERS | MSG_NODIGEST) #define MIME_NOHEADERS PLAIN_HEADERS /* CBF vs CIF */ #define CBF 0x0000 /* Use simple binary sections */ #define CIF 0x0001 /* Use MIME-encoded binary sections */ @} @D Constants used for encoding @{ /* Constants used for encoding */ #define ENC_NONE 0x0001 /* Use BINARY encoding */ #define ENC_BASE64 0x0002 /* Use BASE64 encoding */ #define ENC_BASE32K 0x0004 /* Use X-BASE32K encoding */ #define ENC_QP 0x0008 /* Use QUOTED-PRINTABLE encoding */ #define ENC_BASE10 0x0010 /* Use BASE10 encoding */ #define ENC_BASE16 0x0020 /* Use BASE16 encoding */ #define ENC_BASE8 0x0040 /* Use BASE8 encoding */ #define ENC_FORWARD 0x0080 /* Map bytes to words forward (1234) */ #define ENC_BACKWARD 0x0100 /* Map bytes to words backward (4321) */ #define ENC_CRTERM 0x0200 /* Terminate lines with CR */ #define ENC_LFTERM 0x0400 /* Terminate lines with LF */ #define ENC_DEFAULT (ENC_BASE64 | ENC_LFTERM | ENC_FORWARD) @} \subsection{Exceptions} We attempt to catch the errors and pass them back to python as exceptions. This could still do with a little work to propagage back the calls causing the errors. Currently there are two global constants defined, called error\_message and error\_status. These are filled out when an error occurred, converting the numerical error value into something the author can read. There is an implicit assumption that if the library is used correctly you will not normally get exceptions. This should be addressed further in areas like file opening, proper python exceptions should be returned. See the section on exception handling in pycbf.i, above. Currently you get a meaningful string back. Should perhaps look into defining these as python exception classes? In any case - the SWIG exception handling is defined via the following. It could have retained the old style if(status = action) but then harder to see what to return... @D Exception handling @{ // Exception handling /* Convenience definitions for functions returning error codes */ %exception { error_status=0; $action if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } /* Retain notation from cbf lib but pass on as python exception */ #define cbf_failnez(x) {(error_status = x);} /* printf("Called \"x\", status %d\n",error_status);} */ #define cbf_onfailnez(x,c) {int err; err = (x); if (err) { fprintf (stderr, \ "\nCBFlib error %d in \"x\"\n", err); \ { c; } return err; }} @} @O pycbf.i @{ /* File: pycbf.i */ // Indicate that we want to generate a module call pycbf %module pycbf %pythoncode %{ __author__ = "Jon Wright " __date__ = "14 Dec 2005" __version__ = "CBFlib 0.9" __credits__ = """Paul Ellis and Herbert Bernstein for the excellent CBFlib!""" __doc__=""" pycbf - python bindings to the CBFlib library A library for reading and writing ImageCIF and CBF files which store area detector images for crystallography. This work is a derivative of the CBFlib version 0.7.7 library by Paul J. Ellis of Stanford Synchrotron Radiation Laboratory and Herbert J. Bernstein of Bernstein + Sons See: http://www.bernstein-plus-sons.com/software/CBF/ Licensing is GPL based, see: http://www.bernstein-plus-sons.com/software/CBF/doc/CBFlib_NOTICES.html These bindings were automatically generated by SWIG, and the input to SWIG was automatically generated by a python script. We very strongly recommend you do not attempt to edit them by hand! Copyright (C) 2007 Jonathan Wright ESRF, Grenoble, France email: wright@@esrf.fr Revised, August 2010 Herbert J. Bernstein Add defines from CBFlib 0.9.1 """ %} // Used later to pass back binary data %include "cstring.i" // Attempt to autogenerate what SWIG thinks the call looks like // Typemaps are a SWIG mechanism for many things, not least multiple // return values %include "typemaps.i" // Arrays are needed %include "carrays.i" %array_class(double, doubleArray) %array_class(int, intArray) %array_class(short, shortArray) %array_class(long, longArray) // Following the SWIG 1.3 documentation at // http://www.swig.org/Doc1.3/Python.html // section 31.9.5, we map sequences of // PyFloat, PyLong and PyInt to // C arrays of double, long and int // // But with the strict checking of being a float // commented out to allow automatic conversions %{ static int convert_darray(PyObject *input, double *ptr, int size) { int i; if (!PySequence_Check(input)) { PyErr_SetString(PyExc_TypeError,"Expecting a sequence"); return 0; } if (PyObject_Length(input) != size) { PyErr_SetString(PyExc_ValueError,"Sequence size mismatch"); return 0; } for (i =0; i < size; i++) { PyObject *o = PySequence_GetItem(input,i); /*if (!PyFloat_Check(o)) { Py_XDECREF(o); PyErr_SetString(PyExc_ValueError,"Expecting a sequence of floats"); return 0; }*/ ptr[i] = PyFloat_AsDouble(o); Py_DECREF(o); } return 1; } %} %typemap(in) double [ANY](double temp[$1_dim0]) { if ($input == Py_None) $1 = NULL; else if (!convert_darray($input,temp,$1_dim0)) { return NULL; } $1 = &temp[0]; } %{ static long convert_larray(PyObject *input, long *ptr, int size) { int i; if (!PySequence_Check(input)) { PyErr_SetString(PyExc_TypeError,"Expecting a sequence"); return 0; } if (PyObject_Length(input) != size) { PyErr_SetString(PyExc_ValueError,"Sequence size mismatch"); return 0; } for (i =0; i < size; i++) { PyObject *o = PySequence_GetItem(input,i); /*if (!PyLong_Check(o)) { Py_XDECREF(o); PyErr_SetString(PyExc_ValueError,"Expecting a sequence of long integers"); return 0; }*/ ptr[i] = PyLong_AsLong(o); Py_DECREF(o); } return 1; } %} %typemap(in) long [ANY](long temp[$1_dim0]) { if (!convert_larray($input,temp,$1_dim0)) { return NULL; } $1 = &temp[0]; } %{ static int convert_iarray(PyObject *input, int *ptr, int size) { int i; if (!PySequence_Check(input)) { PyErr_SetString(PyExc_TypeError,"Expecting a sequence"); return 0; } if (PyObject_Length(input) != size) { PyErr_SetString(PyExc_ValueError,"Sequence size mismatch"); return 0; } for (i =0; i < size; i++) { PyObject *o = PySequence_GetItem(input,i); /*if (!PyInt_Check(o)) { Py_XDECREF(o); PyErr_SetString(PyExc_ValueError,"Expecting a sequence of long integers"); return 0; }*/ ptr[i] = (int)PyInt_AsLong(o); Py_DECREF(o); } return 1; } %} %typemap(in) int [ANY](int temp[$1_dim0]) { if (!convert_iarray($input,temp,$1_dim0)) { return NULL; } $1 = &temp[0]; } %{ // Here is the c code needed to compile the wrappers, but not // to be wrapped #include "../include/cbf.h" #include "../include/cbf_simple.h" // Helper functions to generate error message static int error_status = 0; static char error_message[1024] ; // hope that is long enough /* prototype */ void get_error_message(void); void get_error_message(){ sprintf(error_message,"%s","CBFlib Error(s):"); if (error_status & CBF_FORMAT ) sprintf(error_message,"%s %s",error_message,"CBF_FORMAT "); if (error_status & CBF_ALLOC ) sprintf(error_message,"%s %s",error_message,"CBF_ALLOC "); if (error_status & CBF_ARGUMENT ) sprintf(error_message,"%s %s",error_message,"CBF_ARGUMENT "); if (error_status & CBF_ASCII ) sprintf(error_message,"%s %s",error_message,"CBF_ASCII "); if (error_status & CBF_BINARY ) sprintf(error_message,"%s %s",error_message,"CBF_BINARY "); if (error_status & CBF_BITCOUNT ) sprintf(error_message,"%s %s",error_message,"CBF_BITCOUNT "); if (error_status & CBF_ENDOFDATA ) sprintf(error_message,"%s %s",error_message,"CBF_ENDOFDATA "); if (error_status & CBF_FILECLOSE ) sprintf(error_message,"%s %s",error_message,"CBF_FILECLOSE "); if (error_status & CBF_FILEOPEN ) sprintf(error_message,"%s %s",error_message,"CBF_FILEOPEN "); if (error_status & CBF_FILEREAD ) sprintf(error_message,"%s %s",error_message,"CBF_FILEREAD "); if (error_status & CBF_FILESEEK ) sprintf(error_message,"%s %s",error_message,"CBF_FILESEEK "); if (error_status & CBF_FILETELL ) sprintf(error_message,"%s %s",error_message,"CBF_FILETELL "); if (error_status & CBF_FILEWRITE ) sprintf(error_message,"%s %s",error_message,"CBF_FILEWRITE "); if (error_status & CBF_IDENTICAL ) sprintf(error_message,"%s %s",error_message,"CBF_IDENTICAL "); if (error_status & CBF_NOTFOUND ) sprintf(error_message,"%s %s",error_message,"CBF_NOTFOUND "); if (error_status & CBF_OVERFLOW ) sprintf(error_message,"%s %s",error_message,"CBF_OVERFLOW "); if (error_status & CBF_UNDEFINED ) sprintf(error_message,"%s %s",error_message,"CBF_UNDEFINED "); if (error_status & CBF_NOTIMPLEMENTED) sprintf(error_message,"%s %s",error_message,"CBF_NOTIMPLEMENTED"); if (error_status & CBF_NOCOMPRESSION) sprintf(error_message,"%s %s",error_message,"CBF_NOCOMPRESSION"); } %} // End of code which is not wrapped but needed to compile @} @O pycbf.i @{ @< Constants used for compression @> @< Constants used for headers @> @< Constants used to control CIF parsing @> @< Constants used for encoding @> @< Exception handling @> %include "cbfgenericwrappers.i" // cbf_goniometer object %include "cbfgoniometerwrappers.i" %include "cbfdetectorwrappers.i" // cbfhandle object %include "cbfhandlewrappers.i" @} ./CBFlib-0.9.2.2/pycbf/_pycbf.pyd0000644000076500007650000117100011603702120014655 0ustar yayayayaMZÿÿ¸@€º´ Í!¸LÍ!This program cannot be run in DOS mode. $PEL‘šeFà# 8Êî à@[ àHðÀ¨&.textÉÊ``.dataÀàÎ@À.rdata@ÎÐæ@@.bssPЀÀ.edataHà¶@@.idataÀð¸@À.reloc¨&(Ê@BU‰åWVSƒì ‹} ƒÿ„«‰|$‹]‹M‰\$‰ $èõÃ‰Æƒì ƒÿ”Â1À…ö”À…Ât[‹Ð…ÒtE‹Ðë ƒë9Ór‹…ÀtóÿЋÐƒë9Ósët&‰$èXÀ1Ò‰ÐÇ$è4À…ÿu‹Ð…ÒuF1öt&‰ðeô[^_] t&Ç$€è4À£Ð…ÀtlÇ£ÐèKÄèÖÃé&ÿÿÿ‹Ðv¼'ƒë9Ór‹…ÀtóÿЋÐƒë9Ósët&‰$1ÿè¶¿‰=ÐÇ$蔿éoÿÿÿ調Ç 1Àé_ÿÿÿ¶¼'UºÐ‰åƒì¹Ð‹E‰T$‰L$‰$è=¿ɃøÀöU¹Ð‰åƒìºÐ‹E‰L$‰T$‰$è ¿ÉÃU‰å]éGÄU‰åWVS‹]‹} ‹M‹u9û•À9ñ•¶À…Âtr€; ”À9û•¶À…ÂtC€; ”À9û•¶À…Âuí€9 ”À9ñ•¶À…ÂtA€9 ”À9ñ•¶À…Âuí¶:t:ŸÀ¶ÀDÿëCA9û•À9ñ•¶À…Âuމú)Ú‰ð)È)‰Ð[^_]ÃU‰åWVSƒì‹U¾‹} ü¹ÿÿÿÿ°ò®÷Ñ‹E |ÿ‰Ó€:tBë‰Ú€;t €;|tC€;uõ‰|$ ‹E ‰D$‰\$‰$èÿÿÿ…À”À¶ð€;ƒÛÿ…öu€;uÀ‰ðƒÄ[^_]ÃU‰åWVSƒì‹U¾‹} ü¹ÿÿÿÿ°ò®÷Ñ‹E |ÿ‰Ó€:tBë‰Ú€;t €;|tC€;uõ‰|$ ‹E ‰D$‰\$‰$è‡þÿÿ…À”À¶ð€;ƒÛÿ…öu€;uÀ‰ðƒÄ[^_]ÃU‰åWVSƒì ‹u‹} …ÿt^‹_ …ÛtW‹‰t$‹‰$è<¾…Àu<‰Ø9_ tA‹S ‹C‰Bƒ{t‹C‰P ‹G ‰CÇC ƒ t‹G ‰X ‰_ ‰Øë ‹[…Ûu©¸ƒÄ [^_]ÃU‰åS‹E‹M …ÉtN‹Q …ÒtG9u<‰Ð9Q tA‹Z ‹B‰Cƒzt‹B‰X ‹A ‰BÇB ƒy t‹A ‰P ‰Q ‰Ðë ‹R…Òu¹¸[]ÃU‰åƒì‰]ø‰uü‹E‹u ‰Ã…Àt$ƒxt…Àtƒxt‰4$ÿP…Àt‰Ãƒxuî‰Ø‹]ø‹uü‰ì]ÃU‰å‹U¸…Òt"ƒzt‹B‰Â€8t€:|uBB€:uòë‹]ÃU‰åVSƒì‹E‹u ‹X ‰p…Ût!ƒ{u‹ƒxu ‰t$‰$èÎÿÿÿ‹[…Ûu߃Ä[^]ÃU‰åSƒì‹]‹E ‰D$‰$è§ÿÿÿÇCƒÄ[]ÃU‰åWVSƒì‹E‰Eð‹UðƒztSÇEì‹rN‹Eìð‰ÃÑë‹Uð‹‹<˜‹…Àt1‰D$‹E‰$è\¼…Àu‰øë/…Ày …Ûtsÿë…À~C‰]ì9uìv¸‹Uð‹R‰Uð‹E 9Âu”¸ƒÄ[^_]ÃU‰åWVSƒì ‹]‹}‰|$‹E ‰D$‰$èVÿÿÿ‰Â…ÀuJë‹‹°ëA¾ƒ{v)‹‹°ƒxt‰|$‹‹°‹@‰$èhüÿÿ…ÀuËF9sw׋[;] uĺ‰ÐƒÄ [^_]ÃU‰åVS‹M‹] ‰Þu9ót$¶‰ÐÁè¶€ˆAƒâ¶‚ˆAC9óu܉È[^]ÃU‰åWVS‹M‹u ‰÷}9þt[¶AˆÂ,0< wˆÃÀãëˆÐ,a<w ˆÐ,WˆÃÀãë¸ë0¶AˆÂ,0< wÃëˆÐ,a<wˆÐ,WÃë¸ë ˆF9þu¥‰È[^_]ÃU‰åƒì‰]ô‰uø‰}ü‹]‹u‰Ú¿ƒþ vLÆ_BÇD$E ‰D$‰$èÿÿÿ‰Â‹}ü¹ÿÿÿÿ°ò®÷щÐ)Ø)Æ¿9ñw‹E‰D$‰$èqº‰ß‰ø‹]ô‹uø‹}ü‰ì]ÃU‰åƒì‰]ô‰uø‰}ü‹E‹] €8_t)‰Æ¿¹üó¦—Â’À¹8Âu"Ç‹MëÇD$‰\$@‰$èµþÿÿ‰Á‰È‹]ô‹uø‹}ü‰ì]ÃU‰åƒì‰]ô‰uø‰}ü‹u‹]‹U¿…Ût‰ßü¹ÿÿÿÿ°ò®÷ÑyÿDw¹;Ew8Æ_B‰t$‹E ‰D$‰$èþÿÿ‰Â…ÿtG‰D$‰\$‰$èw¹ëÆ‹M‰È‹]ô‹uø‹}ü‰ì]ÃU‰åƒì‰]ô‰uø‰}ü‹E‹]€8_t:‰Æ¿¹üó¦—Â’À¹8Âu2‰\$ÇD$‹E ‰$蹋Më‰\$‹U ‰T$@‰$èµýÿÿ‰Á‰È‹]ô‹uø‹}ü‰ì]ÃU‰å‹EƒÀ ƒø wjÿ$…¡4ó‹ëa¡,ó‹ëX¡@ó‹ëO¡0ó‹ëF¡Ló‹ë=¡Tó‹ë4¡<ó‹ë+¡Dó‹ë"¡Pó‹ë¡Hó‹ë¡$ó‹ë¡@ó‹]ÃU‰åVSƒì ‹uÇEìÇEðÇEôÿó…ÀtEô‰D$Eð‰D$Eì‰$ÿóƒ}ðtl‹Eð‰$ÿÐó‰Ãÿ óƒ}ìt‹Eìÿ‰$ÿÔó‰t$ ‰D$ÇD$D‹Eì‰$ÿóÿ ƒ;u ‹C‰$ÿP‹Eðÿƒ8u"‹Eð‹P‰$ÿRë‰t$¡@ó‹‰$ÿóƒÄ [^]ÃU‰åSƒì‹] ‰\$‹E‰$ÿóÿ ƒ;u ‹C‰$ÿPƒÄ[]ÃU‰åƒì‹E ‰D$‹E‰$ÿ óÉÃU‰åSƒì‹]‰\$‹E ‰D$‹E‰$ÿóÿ ƒ;u ‹C‰$ÿPƒÄ[]ÃU‰åƒì‰]ô‰uø‰}ü‹u‹} …öu‰þéƒ95 ôuÿƒ>u ‹F‰4$ÿP‰þëg‹F;„ót?¡„ó‰D$‹F‰$ÿô…Àu&‰óÇ$ÿ|󉯉\$ÇD$‰$ÿ€ó‰|$‰4$ÿxóÿƒ?u ‹G‰<$ÿP‰ð‹]ô‹uø‹}ü‰ì]ÃU‰åƒì(‰]ô‰uø‰}ü‹]‹u‹}…ÛuN¸‰ò ú„;‰t$¸J9þt¸K‰D$ ‹u ‰t$ÇD$X¡Ló‹‰$ÿó¸éü‹S;üót8¡üó‰D$‰$ÿô…Àu"ÇD$€¡Hó‹‰$ÿ ó¸é¹‹S9ò}@‰T$‰t$¸J9þt¸K‰D$ ‹E ‰D$ÇD$¬¡Ló‹‰$ÿó¸ër9ú~@‰T$‰|$¸J9þt¸Ï‰D$ ‹U ‰T$ÇD$¬¡Ló‹‰$ÿó¸ë.¹9Ñ}‹D‹ ‹u‰ŽA9Ñ|ñ9ú}‹EÇB9ú|ñA‹]ô‹uø‹}ü‰ì]ÃU‰åSƒìƒ= Ðu%Ç$Jÿô‰Ãÿƒ8u ‹@‰$ÿP‰ С ЃÄ[]ÃU‰åVSƒì‹u¸…ö„ÝÇ$èÚ³‰Ã‰0‹B‰‹F;øòuÇC‰sB‰ëKÇD$Ø‹‰$ÿÀó‰C…Àt)ÿÇ$ÿôó‰C‰t$ÇD$‰$ÿøóë‰s‹CÿÇD$à‹‰$ÿÀó‰C ÿó…Àt ÿ óÇC ƒ{ t‹C ÿ‹C ‹@‹@Áèƒðƒà‰CëÇCÇC‰ØƒÄ[^]ÃU‰åSƒì‹]ƒ{t‹Cÿƒ8u ‹C‹P‰$ÿRƒ{t‹Cÿƒ8u ‹C‹P‰$ÿRƒ{ t‹C ÿƒ8u ‹C ‹P‰$ÿRƒÄ[]ÃU‰åƒì‹E‹@‰$ÿ˜óÉÃU‰åƒì‰]ô‰uø‰}ü¿Ç$ÿôó‰Ã…Àte‹E ‰$è·ÿÿÿ‰D$ÇD$‰$ÿøó…ÀuA‹E‰$ÿè󉯅Àt‰\$‰$ÿàó‰Çÿƒ>u ‹F‰4$ÿPÿ ƒ;u ‹C‰$ÿP‰ø‹]ô‹uø‹}ü‰ì]ÃU‰åƒì‹E‰D$Ç$ñèLÿÿÿÉÃU‰åƒì‹E‰D$Ç$ôè1ÿÿÿÉÃU‰åƒì(‰]ô‰uø‰}ü‹}‹G ‰$è+õÿÿ‰Ã‰<$è¾ÿÿÿ‰Æ‰$ÿÔó‰D$‰\$Ç$øÿäó‰Eðÿƒ>u ‹F‰4$ÿPƒt‹G‰$è•ÿÿÿ‰D$Eð‰$ÿÜó‹Eð‹]ô‹uø‹}ü‰ì]ÃU‰åSƒì‹E‰$ècÿÿÿ‰Ã¸…Ût-‰$ÿÔó‹U ‰T$‰$膱ÿ ƒ;u ‹C‰$ÿP¸ƒÄ[]ÃU‰åSì‹UÇD$ ‹B ‹‰D$‹B‰D$øûÿÿ‰$èŒöÿÿº…Àt ‰$ÿèó‰Â‰ÐÄ[]ÃU‰å‹E‹H‹E ‹P¸ÿÿÿÿ9Ñr—À¶À]ÃU‰åƒìƒ=0Ðu èS£0С0ÐÉÃU‰åƒì‰]ô‰uø‰}ü‹M‹yƒy„¬‹A º…Àt‹P»…Òt‹Z …ÛtuƒztBÇD$‰D$‹A‰$è>‰ÆÇD$‰D$‰$ÿ°ó‰Ãÿƒ>u"‹F‰4$ÿPë‹C‹P‹C ‹M‰L$‰$ÿ҉ÅÛt*ÿ ƒ;u#‹C‰$ÿPë‰$è óÿÿ‰D$Ç$èþ¯…ÿtÿƒ?u ‹G‰<$ÿP‹E‰$ÿ´ó‹]ô‹uø‹}ü‰ì]ÃU‰åƒì‰]ô‰uø‰}ü‹] ‹E‰EðÇEìèÄþÿÿ9Ct‹C‹p ¿c¹ üó¦—Â’À8ÂuÇE츃}ìt‹Eð‰Xÿè®úÿÿÿ‹]ô‹uø‹}ü‰ì]ÃU‰åƒì‹Uƒzt ‹Bÿ‹BëèúÿÿÿÉÃU‰åƒì‹EÇ@èhúÿÿÿÉÃU‰åƒì‹EÇ@èOúÿÿÿÉÃU‰åVSƒì ‹uÇEôEô‰D$ÇD$ ÇD$ÇD$p‹E ‰$ÿàòº…Àt8‹F‰$ÿäò‰Ãƒ}ôt"‹Eô‰$ÿÈó…Àt ‰4$èuÿÿÿë‰4$èRÿÿÿ‰Ú‰ÐƒÄ [^]ÃU‰åS씃=Ñ…-Ç…xþÿÿÇ…|þÿÿÇ…€þÿÿÇ…„þÿÿcÇ…ˆþÿÿÇ…ŒþÿÿÇ…þÿÿ· Ç…”þÿÿÕÇ…˜þÿÿÇ…œþÿÿÇ… þÿÿw Ç…¤þÿÿJÇ…¨þÿÿÀàÇ…¬þÿÿÇ…°þÿÿÇ…´þÿÿÇ…¸þÿÿÇ…¼þÿÿ% ¡¸ó‰…ÀþÿÿÇ…ÄþÿÿÇ…ÈþÿÿÇ…ÌþÿÿëÇ…Ðþÿÿ€àÇ…ÔþÿÿÇ…ØþÿÿÇ…ÜþÿÿÇ…àþÿÿÇ…äþÿÿÇ…èþÿÿÇ…ìþÿÿàÇ…ðþÿÿÇ…ôþÿÿÇ…øþÿÿÇ…üþÿÿÇ…ÿÿÿÇ…ÿÿÿÇ…ÿÿÿÇ… ÿÿÿÇ…ÿÿÿÇ…ÿÿÿÇ…ÿÿÿÇ…ÿÿÿÇ… ÿÿÿÇ…$ÿÿÿÇ…(ÿÿÿÇ…,ÿÿÿÇ…0ÿÿÿÇ…4ÿÿÿ8ÿÿÿ…xþÿÿÇD$À‰D$‰$è*¬ÇD$À‰\$Ç$@Ð謡ô£DÐÇѸ@ÐÄ”[]ÃU‰åSƒìè;ûÿÿ‰Ãè4ûÿÿ‹@‰$ÿÌó‰\$‰$ÿÄó‰Â…Àt‹E‰B‹E ‰B ‹E‰BÇB‰ÐƒÄ[]ÃU‰åì8‰]ô‰uø‰}ü‹u‹] ‰\$ ÇD$ ÇD$Ç$bè•«ÇD$ÇD$ ‹F‰D$‹F‰D$½èûÿÿ‰<$èÂñÿÿ…Àt,‰\$ ÇD$ÇD$Ç$pèE«‰\$‰<$èY«‰\$‹F ‹‰$èH«‰\$Ç$>諸‹]ô‹uø‹}ü‰ì]ÃU‰åVSì ‹]ÇD$ÇD$ ‹C‰D$‹C‰D$µøûÿÿ‰4$è%ñÿÿ…Àt‹C ‹‰D$‰t$Ç$tÿäóë‹C ‹‰D$Ç$ŠÿäóÄ [^]ÃU‰åVSì ‹]ÇD$ÇD$ ‹C‰D$‹C‰D$µøûÿÿ‰4$è«ðÿÿ…Àt‹C ‹‰D$‰t$Ç$›ÿäóë‹C ‹‰$ÿèóÄ [^]ÃU‰åƒì‰]ø‰uü‹]‹u ‹K‹V¸ÿÿÿÿ9Ñr—À¶À‰Â…Àu‹CÀ‰D$‹F‰D$‹C‰$販‰Â‰Ð‹]ø‹uü‰ì]ÃU‰åƒìƒ=Ñu èz£Ñ¡ÑÉÃU‰åƒì‰]ô‰uø‰}ü‹]ÇEðèP9Ct‹C‹p ¿ ¹ üó¦—Â’À8ÂuÇEðƒ}ðt ‹C‰$輨‰$ÿ´ó‹]ô‹uø‹}ü‰ì]ÃU‰å옉]ø‰uüƒ=àÑ…ÓµxþÿÿÇD$ÀÇD$‰4$è,©Ç…xþÿÿÇ…„þÿÿ Ç…ˆþÿÿÇ…þÿÿÌ'Ç…”þÿÿ£%Ç… þÿÿV'Ç…¤þÿÿj&Ç…¼þÿÿä&¡¸ó‰…ÀþÿÿÇ…ÌþÿÿëÇ…Ðþÿÿ`á8ÿÿÿÇD$À‰t$‰$èC¨ÇD$À‰\$Ç$ Ñè+¨¡ô£$ÑÇàѸ Ñ‹]ø‹uü‰ì]ÃU‰åƒì‰]ô‰uø‰}ü‹} è]þÿÿ‰ÃèVþÿÿ‹@‰$ÿÌó‰\$‰$ÿÄó‰Ã…Àt=‰<$胧‰Æ…Àt!‰|$‹E‰D$‰4$誧‰s‹E‰C ‰{ë‰$ÿ´ó»‰Ø‹]ô‹uø‹}ü‰ì]ÃU‰åƒì(‰]ô‰uø‰}ü‹]ÇEðè[þÿÿ9Ct‹C‹p ¿ ¹ üó¦—Â’À8ÂuÇEð¸ƒ}ðt$‹U9Su‹C‹U‰T$‰D$‹E ‰$è §‹C ‹]ô‹uø‹}ü‰ì]ÃU‰åƒìƒ=ðÑuÇ$­ÿèó£ðÑ¡ðÑÉÃU‰åƒì(‰]ô‰uø‰}ü‹]ÇEðè öÿÿ9Ct‹C‹p ¿c¹ üó¦—Â’À8ÂuÇEð‰Øƒ}ð…‹C;hóuèuÿÿÿ‰D$‰$ÿô‰Ã飉$ÿô…Àt%‹0»…ö„‡è@ÿÿÿ‰D$‰4$ÿüò‰Ãëq‹C;ôt;ôu‹S¸…Ò„™‰$è,ÿÿÿéŒèúþÿÿ‰D$‰$ÿ¼ó‰Ã…Àtÿƒ8u"‹@‰$ÿPëÿó…Àtÿ ó¸ëK…ÛtEÇEìèõÿÿ9Ct‹C‹p ¿c¹ üó¦—Â’À8ÂuÇEìƒ}ìu ‰$èŸþÿÿë‰Ø‹]ô‹uø‹}ü‰ì]ÃU‰åSƒì‹] …Ût‹E‰$èuþÿÿ‰Â…Àt‹@‰Z븃Ä[]ÃU‰åWVSƒì‹}¸ÿÿÿÿƒ}„¢è’ðÿÿ;Euƒ} t ‹E Ǹé‹U‰$èþÿÿ‰Ã…À„‰‹s…ÿtC‹C 9øu ƒ} tL‹E ‰0ëE‰|$‹‰$èÞæÿÿ‰Â…Àt(ƒ} t+‰ðƒzt‰4$ÿR‹U ‰ëƒ} t‹E ‰0ë ‹[…Ûu¢ë)…Ût%ƒ}t‹C‹U‰öEtÇC¸éáÇEìÿÿÿÿöE„Í»…ÿt‹_…Û„¹ƒ{…¯‹…À„¥ÇCÇD$‹U‰T$‰$ÿ°ó‰ÆÇCÿó…Àt ÿ ó¾…ötd‰4$èþüÿÿ‰Ã…ÀtFÇD$ÇD$ ‰|$Eð‰D$‰$èyþÿÿ‰Eì…Àxƒ} t‹Eð‹U ‰ÇCMìÿƒ>u ‹F‰4$ÿP‹EìƒÄ[^_]ÃU‰åVSƒì ‹U‹u ‹]‹B;èòt%ÇD$ÇD$ ‰\$‰t$‰$èÿýÿÿé–ÇEô‹B‹@ º…ÀtÇD$²‰$èô¢‰Â…Òt.…Ût‹‰D$Eô‰D$B ‰$èéÿÿ‰Â뺸ÿÿÿÿ…Òt<…Ût.‰\$‰$èêäÿÿ‰Â¸ÿÿÿÿ…Òt!‹Eô…Òt ƒzt‰$ÿR‰ë‹Eô‰¸ƒÄ [^]ÃU‰åSƒì‹]‹E‰D$‹E ‰D$‹E‰$èëúÿÿºÿÿÿÿ…Àt$…Ût9Øt‰\$‹‰$èuäÿÿºÿÿÿÿ…Àtº‰ÐƒÄ[]ÃU‰åƒì‰]ô‰uø‰}ü‹u‹V…ÒtWÇD$‹F‰D$‰$ÿ¬ó‰Ç…Àt|‰$ÿô‰Æ…Àtmƒ8uhÿó‰Ã‰èßúÿÿ‹U ‰T$‰D$‰$ÿóëCÿó‰Ãè¼úÿÿ‹U ‰T$‰D$‰$ÿó‰\$‹F‰$ÿdó‰Çÿ ƒ;u ‹C‰$ÿP‰ø‹]ô‹uø‹}ü‰ì]ÃU‰åƒì‰]ô‰uø‰}ü‹u‹} ‰4$ÿô‰Ã…Àt(‹0…öu ÿ󉯉è>úÿÿ‰|$‰D$‰4$ÿóë9ÇD$½‰4$ÿÀó‰Æèúÿÿ‰|$‰D$‰4$ÿóÿƒ>u ‹F‰4$ÿP‹]ô‹uø‹}ü‰ì]ÃU‰åƒì(Eø‰D$ÇD$ ÇD$ÇD$Æ‹E‰$èÀêÿÿº…Àt=‹Eø‰$èÉùÿÿ‰Â…Àt‹Eü‰D$‰$è÷ðÿÿë‹Eü‰D$‹Eø‰$èÿÿÿèñëÿÿÿ‰Â‰ÐÉÃU‰åƒì‰]ô‰uø‰}ü‹U‹u ‹}…Òu èÈëÿÿÿëU‰øƒà‰D$‰t$‰$è=ôÿÿ‰Ã¸…öt‹F…Àt,÷Çu$‰\$‰$èÒýÿÿ‰Æ…Àtÿ ƒ;u ‹C‰$ÿP‰ó‰Ø‹]ô‹uø‹}ü‰ì]ÃU‰åƒìƒ=Òu4ÇD$ÏÇ$Üÿôò£Òÿó…Àtÿ óÇÒ¡ÒÉÃU‰åWVSƒì ‹u‹>»ƒ~v‹Ÿƒxt‹@…Àt‰$è#ìÿÿC9^wâè^øÿÿÿƒ8uèRøÿÿ‰ÃèKøÿÿ‹@‰$ÿPƒÄ [^_]ÃU‰åSƒìÇD$ôÇD$ ÇD$ÇD$ÒÇ$Üÿ ô‰ÃÇD$ª1‹E‰$ÿðò‰Á…À•À…ە¶À…Ât‰L$ÇD$ω$ÿ óë…Étÿ ƒ9u ‹A‰ $ÿPƒÄ[]ÃU‰åƒìƒ= Òu ÿó£ Ò¡ ÒÉÃU‰åƒì(‰]ô‰uø‰}ü‹}èÈÿÿÿ‰Eð‰<$ÿè󉯉D$‹Eð‰$ÿüò…Àt ‰$ÿìò‰ÇëRè\þÿÿ‰|$‰D$‰$èŸâÿÿ‰Ç…Àt7ÇD$‰$ÿðò‰Ã‰D$‰t$‹Eð‰$ÿóÿ ƒ;u ‹C‰$ÿPÿƒ>u ‹F‰4$ÿP‰ø‹]ô‹uø‹}ü‰ì]ÃU‰åƒì(‰]ø‰uü‹uÿóº…À„¿ÇEìÇEðÇEôEô‰D$Eð‰D$Eì‰$ÿóƒ}ð„‹Eð‰$ÿÐó‰Ãƒ}ìt‹Eìÿÿ óƒ} t'‰$ÿÔó‰D$ ‰t$ÇD$D‹Eì‰$ÿóë%‰$ÿÔó‰t$ ‰D$ÇD$D‹Eì‰$ÿóÿ ƒ;u ‹C‰$ÿPº‰Ð‹]ø‹uü‰ì]ÃU‰åSìÿóº…Àt8‹E‰D$ ÇD$ïÇD$øþÿÿ‰$ÿ¨óÇD$‰$èÄþÿÿ‰Â‰ÐÄ[]ÃU‰åƒì(‰]ô‰uø‰}ü‹}‹U …ÿ„®¾…Òt‹B‹p …öt}‰$ÿÐó‰Ã¸…Ût ‰$ÿÔó…Àt&‰D$‰t$ ‰|$ÇD$¡Ló‹‰$ÿóë ‰t$ ‰|$ÇD$0¡Ló‹‰$ÿó…ÛtHÿ ƒ;uA‹C‰$ÿPë6‰|$ÇD$U¡Ló‹‰$ÿóëÇD$h¡Ló‹‰$ÿó‹]ô‹uø‹}ü‰ì]ÃU‰åƒìÇD$‹E‰D$ ‹E ‰D$Eü‰D$‹E‰$è9öÿÿƒøÿuÿ ó‹EüÉÃU‰åƒìǰÓCBFlÇ´Óib EǸÓrrorǼÓ(s):ÆÀÓö0Òt$ÇD$ „ÇD$°ÓÇD$DÇ$°Óèךö0Òt$ÇD$ –ÇD$°ÓÇD$DÇ$°Ó誚ö0Òt$ÇD$ ¨ÇD$°ÓÇD$DÇ$°Óè}šö0Òt$ÇD$ ºÇD$°ÓÇD$DÇ$°ÓèPšö0Òt$ÇD$ ÌÇD$°ÓÇD$DÇ$°Óè#šö0Ò t$ÇD$ ÞÇD$°ÓÇD$DÇ$°Óèö™ö0Ò@t$ÇD$ ðÇD$°ÓÇD$DÇ$°ÓèÉ™ö0Ò€t$ÇD$ ÇD$°ÓÇD$DÇ$°Ó蜙ö1Òt$ÇD$ ÇD$°ÓÇD$DÇ$°Óèo™ö1Òt$ÇD$ &ÇD$°ÓÇD$DÇ$°ÓèB™ö1Òt$ÇD$ 8ÇD$°ÓÇD$DÇ$°Óè™ö1Òt$ÇD$ JÇD$°ÓÇD$DÇ$°Óèè˜ö1Òt$ÇD$ \ÇD$°ÓÇD$DÇ$°Ó軘ö1Ò t$ÇD$ nÇD$°ÓÇD$DÇ$°Ó莘ö1Ò@t$ÇD$ €ÇD$°ÓÇD$DÇ$°Óèa˜ö1Ò€t$ÇD$ ’ÇD$°ÓÇD$DÇ$°Óè4˜ö2Òt$ÇD$ ¤ÇD$°ÓÇD$DÇ$°Óè˜ö2Òt$ÇD$ ¶ÇD$°ÓÇD$DÇ$°ÓèÚ—ÉÃU‰åƒìEü‰$è£0Ò‹EüÉÃU‰åƒìƒ=@Òu+ÇD$ÉÇD$áÇ$áè%Üÿÿ£PÒÇ@Ò¡PÒÉÃU‰åƒìEü‰$èÛ£0Ò‹EüÉÃU‰åƒìEü‰$è°£0Ò‹EüÉÃU‰åƒì‰]ø‰uü‹]‹u ‹S;`ót¡`ó‰D$‰$ÿô…Àt…öt ‰$ÿXóݸ鑋S;tót¡tó‰D$‰$ÿô…Àt…öt‰$ÿlóPÛ$d$ݸëR‹S;œót¡œó‰D$‰$ÿô…Àt,‰$ÿˆóÝ]ðÿó…Àu…ötÝEðݸë ÿ ó¸ûÿÿÿ‹]ø‹uü‰ì]ÃU‰åVSƒì‹]‹u ‹S;tót¡tó‰D$‰$ÿô…Àt!‰$ÿló‰Â¸ùÿÿÿ…Òx[…öt‰¸ëN‹S;œót¡œó‰D$‰$ÿô…Àt(‰$ÿó‰Ãÿó…Àu …öt‰¸ë ÿ ó¸ûÿÿÿƒÄ[^]ÃU‰åƒì‰]ø‰uü‹]‹u ‹S;tót¡tó‰D$‰$ÿô…Àt…öt ‰$ÿló‰¸ëN‹S;œót¡œó‰D$‰$ÿô…Àt(‰$ÿŒó‰Ãÿó…Àu …öt‰¸ë ÿ ó¸ûÿÿÿ‹]ø‹uü‰ì]ÃU‰åSƒì‹] Eø‰D$‹E‰$èCÿÿÿ‰Â…Àx …Ût‹Eø‰‰ÐƒÄ[]ÃU‰åÇ0Ò¸]ÃU‰åƒì‹E‰$èJ…£0ÒÉÃU‰åƒì‹E‰D$ ‹E ‰D$ÇD$‹E‰$èÝ…£0ÒÉÃU‰åƒì8‹E4‰D$0‹E0‰D$,‹E,‰D$(ÝE$Ý\$ ÝEÝ\$ÝEÝ\$ÝE Ý\$ÇD$‹E‰$è(†£0ÒÉÃU‰åƒìH‹E<‰D$8‹E8‰D$4‹E4‰D$0ÝE,Ý\$(ÝE$Ý\$ ÝEÝ\$ÝEÝ\$ÝE Ý\$ÇD$‹E‰$蹆£0ÒÉÃU‰åƒì‹E‰D$‹E‰D$ ‹E ‰D$ÇD$‹E‰$èQ„£0ÒÉÃU‰åÇ0Ò¸]ÃU‰åƒì‹E‰$èü¥£0ÒÉÃU‰åƒì(‹E$‰D$‹E ‰D$‹E‰D$ÝEÝ\$ ÝE Ý\$‹E‰$è~±£0ÒÉÃU‰åƒì(‹E ‰D$‹E‰D$ÝEÝ\$ ÝE Ý\$‹E‰$è³£0ÒÉÃU‰åƒì‹E ‰D$‹E‰$è°£0ÒÉÃU‰åƒì‹E‰D$ ‹E‰D$‹E ‰D$‹E‰$èc°£0ÒÉÃU‰åSƒì‹] Eø‰D$‹E‰$èLüÿÿ‰Â…Àx …Ût‹Eø‰‰ÐƒÄ[]ÃU‰åƒì‹E‰D$‹E ‰D$‹E‰$è–´£0ÒÉÃU‰åƒì(‹E$‰D$‹E ‰D$‹E‰D$ÝEÝ\$ ÝE Ý\$‹E‰$è°£0ÒÉÃU‰åƒì‹E‰D$‹E‰D$ ‹E‰D$‹E ‰D$‹E‰$è ¥£0ÒÉÃU‰åƒìEü‰$èÉ£0Ò‹EüÉÃU‰åƒì‹E‰$èãÉ£0ÒÉÃU‰åƒì‹E ‰D$‹E‰$èÔä£0ÒÉÃU‰åƒì8‰]ô‰uø‰}ü‹]‹u ‹S;ðót¡ðó‰D$‰$ÿô…À„Eð‰D$Eì‰D$‰$ÿØó…öt\ƒ}tK‹E8u0‹Eð@‰$è‘‹UðB‰T$‹Uì‰T$‰$èD‘‰‹UÇë‹E쉋}Çë ‰$ÿÔó‰ƒ}t ‹Eð@‹U‰¸é‚è!ùÿÿ…ÀttÇEèÇD$ÇD$ ‰D$Eè‰D$‰$è ëÿÿ…ÀuF…öt‹E艃}t!¸ƒ}èt‹Uèü¹ÿÿÿÿ‰×ò®‰È÷ЋU‰ƒ}t ‹}Ǹë¸ûÿÿÿ‹]ô‹uø‹}ü‰ì]ÃU‰åƒì‹E ‰D$‹E‰$èLΣ0ÒÉÃU‰åƒì‹E‰$èdØ£0ÒÉÃU‰åƒì‹E‰D$‹E ‰D$‹E‰$èN8£0ÒÉÃU‰åƒìEü‰D$‹E‰$è_ì£0Ò‹EüÉÃU‰åÇ0Ò]ÃU‰åÇ0Ò]ÃU‰åƒì‹E‰$è6Ó£0ÒÉÃU‰åƒì‹E‰$èNÜ£0ÒÉÃU‰åƒì(Eü‰D$Eø‰D$ ‹E‰D$Eô‰D$‹E‰$èºõ£0Ò‹Uô‹E ‰‹Uø‹E‰‹Uü‹E‰ÉÃU‰åƒì‹E ‰D$‹E‰$è“Ï£0ÒÉÃU‰åƒì‹E ‰D$‹E‰$èÔÍ£0ÒÉÃU‰åƒìEü‰D$‹E‰$èµè£0Ò‹EüÉÃU‰åƒì‹E ‰D$‹E‰$èSè£0ÒÉÃU‰åƒì‹E ‰D$‹E‰$èTä£0ÒÉÃU‰åƒì‹E ‰D$Eü‰D$‹E‰$è*‚£0Ò‹EüÉÃU‰åƒì‹E‰$è³Ü£0ÒÉÃU‰åƒìÝEÝ\$ ‹E‰D$‹E ‰D$‹E‰$èþ£0ÒÉÃU‰åƒì(‹E$‰D$ ‹E ‰D$‹E‰D$‹E‰D$‹E‰D$‹E‰D$ ‹E ‰D$ÇD$‹E‰$è`.£0ÒÉÃU‰åƒìEü‰D$‹E‰$èÆî£0Ò‹EüÉÃU‰åƒìEü‰D$‹E‰$èó£0Ò‹EüÉÃU‰åƒìEø‰D$‹E‰$èÒî£0ÒÝEøÉÃU‰åÇ0Ò]ÃU‰åƒì‹E‰$èÙ£0ÒÉÃU‰åƒìEü‰D$‹E‰$èÛ£0Ò‹EüÉÃU‰åƒìEü‰D$‹E‰$è×ê£0Ò‹EüÉÃU‰åÇ0Ò]ÃU‰åƒìEü‰D$‹E‰$èVç£0Ò‹EüÉÃU‰åÇ0Ò]ÃU‰åƒìÝE Ý\$‹E‰$èz£0ÒÉÃU‰åƒìEü‰D$‹E‰$è£0Ò‹EüÉÃU‰åƒìEü‰D$‹E‰$èôü£0Ò‹EüÉÃU‰åƒì‹E‰D$‹E ‰D$‹E‰$è£0ÒÉÃU‰åƒì‹E ‰D$‹E‰$è|à£0ÒÉÃU‰åƒìÇD$Ñ‹E ‰$èÌŒ‰Â…Àu Ç0Òë‹E‰D$‰T$‹E‰$èT\£0ÒÉÃU‰åƒìEü‰D$‹E‰$èç£0Ò‹EüÉÃU‰åÇ0Ò]ÃU‰åƒì‹E‰$è[Ú£0ÒÉÃU‰åƒì‹E‰D$‹E‰D$ ‹E ‰D$ÇD$‹E‰$èïa£0ÒÉÃU‰åƒì‹E ‰D$‹E‰$ègù£0ÒÉÃU‰åƒì‹E‰D$ ‹E ‰D$ÇD$‹E‰$èç*£0ÒÉÃU‰åƒì‹E ‰D$‹E‰$èšã£0ÒÉÃU‰åƒìEü‰D$‹E ‰D$‹E‰$è„0£0Ò‹EüÉÃU‰åƒì‹E‰$èùÓ£0ÒÉÃU‰åƒì‹E‰D$‹E ‰D$‹E‰$è3í£0ÒÉÃU‰åƒì8‹E(‰D$ ‹E$‰D$Eü‰D$‹E‰D$‹E‰D$Eø‰D$ ‹E‰D$Eô‰D$‹E‰$è3ï£0Ò‹Uô‹E ‰‹Uø‹E‰‹Uü‹E ‰ÉÃU‰åƒìÇD$Ô‹E ‰$èËŠ‰Â…Àu Ç0Òë1‹E‰D$‹E‰D$‹E‰D$ ÇD$‰T$‹E‰$èÝ£0ÒÉÃU‰åƒì(ÝEÝ\$ÝEÝ\$ ÝE Ý\$‹E‰$èå£0ÒÉÃU‰åƒì‹E‰$è¸Ó£0ÒÉÃU‰åƒìEü‰D$‹E‰$軣0Ò‹EüÉÃU‰åƒì‹E‰D$ ‹E‰D$‹E ‰D$‹E‰$膣0ÒÉÃU‰åƒì‹E‰$è±Ø£0ÒÉÃU‰åƒì‹E ‰D$‹E‰$è(£0ÒÉÃU‰åƒì(ÝEÝ\$‹E‰D$ÝE Ý\$ÇD$‹E‰$è¸+£0ÒÉÃU‰åƒìhE¨‰D$‹E‰$èﺣ0ÒÝE¨‹E ÝÝE°‹EÝÝE¸‹EÝÝEÀ‹EÝÝEÈ‹EÝÝEЋE ÝÝEØ‹E$ÝÝEà‹E(ÝÝEè‹E,ÝÉÃU‰åƒì‹E‰D$ ‹E‰D$‹E ‰D$‹E‰$è£0ÒÉÃU‰åƒì‹E‰$èaÕ£0ÒÉÃU‰åƒìÇD$Ñ‹E ‰$èÁˆ…Àu Ç0Òë‰D$‹E‰$è"£0ÒÉÃU‰åƒì‹E ‰D$‹E‰$èãÝ£0ÒÉÃU‰åƒìEü‰D$‹E‰$èäÊ£0Ò‹EüÉÃU‰åÇ0Ò]ÃU‰åƒì‹E‰D$ ‹E‰D$‹E ‰D$‹E‰$èd"£0ÒÉÃU‰åƒì‹E ‰D$‹E‰$è–Ä£0ÒÉÃU‰åƒìÝEÝ\$ ÝE Ý\$‹E‰$袣0ÒÉÃU‰åÇ0Ò]ÃU‰åƒì‹E ‰D$‹E‰$èâÌ£0ÒÉÃU‰åƒìEü‰D$‹E‰$èã£0Ò‹EüÉÃU‰åƒì‹E‰$èXÑ£0ÒÉÃU‰åƒì‹E ‰D$Eü‰D$‹E‰$è"æ£0Ò‹EüÉÃU‰åƒì‹E‰D$ ‹E‰D$‹E ‰D$‹E‰$è²õ£0ÒÉÃU‰åƒìÝEÝ\$ ‹E‰D$‹E ‰D$‹E‰$èÝ£0ÒÉÃU‰åƒì‹E‰$è-Ø£0ÒÉÃU‰åÇ0Ò]ÃU‰åÇ0Ò]ÃU‰åƒì‹E‰$èÇÏ£0ÒÉÃU‰åƒìEü‰D$‹E‰$èXt£0Ò‹EüÉÃU‰åƒì‹E ‰D$‹E‰$è†Ì£0ÒÉÃU‰åƒì‹E ‰D$‹E‰$è%£0ÒÉÃU‰åWVSƒìL‹u‹}ÇEð‰D$ Eì‰D$Eè‰D$Eä‰D$Eà‰D$E܉D$ E؉D$EÔ‰D$‰4$èê£0Ò‹EܯEè‰$è÷„‰Ã…Àt6EЉD$‹Eè‰D$‹Eà‰D$‹E܉D$ ‰\$E؉D$‰4$è¢ì£0Òë Ç0Ò‹EܯE艋E ‰ƒÄL[^_]ÃU‰åÇ0Ò]ÃU‰åƒì‹E ‰D$‹E‰$è4õ£0ÒÉÃU‰åƒìEü‰D$‹E ‰D$‹E‰$èþ+£0Ò‹EüÉÃU‰åƒì‹E ‰D$‹E‰$èLä£0ÒÉÃU‰åÇ0Ò]ÃU‰åƒìÝE Ý\$ÇD$‹E‰$èO"£0ÒÉÃU‰åƒì(ÝEÝ\$ÝEÝ\$ ‹E ‰D$ÇD$‹E‰$èá_£0ÒÉÃU‰åÇ0Ò]ÃU‰åƒì‹E‰D$‹E ‰D$‹E‰$èI £0ÒÉÃU‰åƒìEø‰D$‹E‰$èz £0ÒÝEøÉÃU‰åƒì‹E‰$èbÒ£0ÒÉÃU‰åÇ0Ò]ÃU‰åƒìhÝE Ý]¨ÝEÝ]°ÝEÝ]¸ÝE$Ý]ÀÝE,Ý]ÈÝE4Ý]ÐÝE<Ý]ØÝEDÝ]àÝELÝ]èE¨‰D$‹E‰$èOµ£0ÒÉÃU‰åƒì‹E ‰D$‹E‰$è£0ÒÉÃU‰åƒìÝEÝ\$ÝEÝ\$‹E ‰D$‹E‰$膣0ÒÉÃU‰åƒì‹E ‰D$‹E‰$èÓÚ£0ÒÉÃU‰åƒì‹E‰$è›Í£0ÒÉÃU‰åƒì‹E ‰D$‹E‰$è ð£0ÒÉÃU‰åÇ0Ò]ÃU‰åÇ0Ò]ÃU‰åƒìEü‰D$‹E ‰D$‹E‰$è'£0Ò‹EüÉÃU‰åƒìEü‰D$‹E ‰D$‹E‰$è$£0Ò‹EüÉÃU‰åƒì‹E ‰D$‹E‰$è}ã£0ÒÉÃU‰åƒìEü‰D$‹E‰$èžÝ£0Ò‹EüÉÃU‰åƒìEü‰D$‹E‰$è â£0Ò‹EüÉÃU‰åÇ0Ò]ÃU‰åÇ0Ò]ÃU‰åƒì‹E‰$èƒÍ£0ÒÉÃU‰åƒìÝEÝ\$‹E ‰D$‹E‰$èp£0ÒÉÃU‰åƒì(Eü‰D$Eø‰D$ ‹E ‰D$ÇD$‹E‰$èæ(£0Ò‹Uø‹E‰‹Uü‹E‰ÉÃU‰åÇ0Ò]ÃU‰åƒì‹E‰D$‹E ‰D$‹E‰$èã&£0ÒÉÃU‰åÇ0Ò]ÃU‰åƒìEü‰D$‹E‰$èåÁ£0Ò‹EüÉÃU‰åƒì‹E ‰D$‹E‰$èÃí£0ÒÉÃU‰åƒì(‹M‹U$‰È¯Â;Eu6‰T$‹E ‰D$‰L$‹E‰D$ ‹E‰D$‹E ‰D$‹E‰$è÷è£0Òë Ç0ÒÉÃU‰åƒì‹E ‰D$‹E‰$茼£0ÒÉÃU‰åƒì8ÝE,Ý\$(‹E(‰D$$ÝE Ý\$‹E‰D$‹E‰D$‹E‰D$‹E‰D$ ‹E ‰D$ÇD$‹E‰$è¤$£0ÒÉÃU‰åƒì‹E‰$è<Ò£0ÒÉÃU‰åƒì‹E‰D$‹E ‰D$‹E‰$èÖ"£0ÒÉÃU‰åƒì‹E ‰D$‹E‰$è÷ã0ÒÉÃU‰åƒì‹E ‰D$‹E‰$èXÁ£0ÒÉÃU‰åÇ0Ò]ÃU‰åƒì‹E ‰D$ÇD$‹E‰$èã0ÒÉÃU‰åÇ0Ò]ÃU‰åƒìEü‰D$‹E ‰D$‹E‰$è£0Ò‹EüÉÃU‰åƒì‹E ‰D$‹E‰$èÛÜ£0ÒÉÃU‰åƒìÝEÝ\$‹E ‰D$‹E‰$è…á£0ÒÉÃU‰åƒì‹E‰$è­Ê£0ÒÉÃU‰åƒì‹E‰D$ Eü‰D$‹E ‰D$‹E‰$èí£0Ò‹EüÉÃU‰åƒì‹E ‰D$‹E‰$èžÔ£0ÒÉÃU‰åƒì‹E‰$è†Ç£0ÒÉÃU‰åƒìÝEÝ\$‹E ‰D$‹E‰$è°ß£0ÒÉÃU‰åƒì‹E ‰D$‹E‰$èAÕ£0ÒÉÃU‰åƒìEü‰D$‹E ‰D$‹E‰$蛣0Ò‹EüÉÃU‰åÇ0Ò]ÃU‰åWSƒìÇD$Ø‹E ‰$ÿÜòº…À„žÇ0Òèbåÿÿƒ=0Òt$èóáÿÿÇD$°Ó¡(ó‹‰$ÿ óºëb‰Ã¸…Ût‰ßü¹ÿÿÿÿò®÷ÑAÿ…Ût;…Ày(è)åÿÿ…ÀtÇD$‰D$‰$è‡ÜÿÿëèiÈÿÿÿë‰D$‰$ÿìóëèQÈÿÿÿ‰Â‰ÐƒÄ[_]ÃU‰åWSƒìÇD$ö‹E ‰$ÿÜòº…À„žÇ0Òèîäÿÿƒ=0Òt$è#áÿÿÇD$°Ó¡(ó‹‰$ÿ óºëb‰Ã¸…Ût‰ßü¹ÿÿÿÿò®÷ÑAÿ…Ût;…Ày(èYäÿÿ…ÀtÇD$‰D$‰$è·Ûÿÿëè™Çÿÿÿë‰D$‰$ÿìóëèÇÿÿÿ‰Â‰ÐƒÄ[_]ÃU‰åWSƒìÇD$ ‹E ‰$ÿÜòº…À„žÇ0Òè9äÿÿƒ=0Òt$èSàÿÿÇD$°Ó¡(ó‹‰$ÿ óºëb‰Ã¸…Ût‰ßü¹ÿÿÿÿò®÷ÑAÿ…Ût;…Ày(è‰ãÿÿ…ÀtÇD$‰D$‰$èçÚÿÿëèÉÆÿÿÿë‰D$‰$ÿìóëè±Æÿÿÿ‰Â‰ÐƒÄ[_]ÃU‰åWVSƒì,ÇEèÇEäÇEìÇEðEð‰D$ Eì‰D$ÇD$(‹E ‰$ÿÜò…À„/ÇD$ÇD$ ¡ŒÓ‰D$Eè‰D$‹Eì‰$èxÕÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èÂÿÿÇD$L‰$è‹Ãÿÿé׋}èÇD$ÇD$ ¡tÓ‰D$Eä‰D$‹Eð‰$èÕÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$è¾ÁÿÿÇD$¨‰$è0Ãÿÿë‹]ä…ÛtQ¾‰ðÁàØtº µÝÃÝÇBƒúvñëÇ$÷ÿÿÿènÁÿÿÇD$ü‰$èàÂÿÿë/Fƒþv¶ëÇ$÷ÿÿÿèHÁÿÿÇD$ü‰$èºÂÿÿë è*Åÿÿÿ븃Ä,[^_]ÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$@‹E ‰$ÿÜò…ÀtsÇD$ÇD$ ¡ŒÓ‰D$Eø‰D$‹Eü‰$è Ôÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èªÀÿÿÇD$d‰$èÂÿÿëÇD$¡tÓ‰D$‹Eø‰$èŒØÿÿë¸ÉÃU‰åSƒì$ÇEðÇEìÇEôÇEøEø‰D$ Eô‰D$ÇD$À‹E ‰$ÿÜò…À„ÀÇD$ÇD$ ¡ŒÓ‰D$Eð‰D$‹Eô‰$èBÓÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èã¿ÿÿÇD$ä‰$èUÁÿÿëk‹]ðÇD$ÇD$ ¡xÓ‰D$Eì‰D$‹Eø‰$èêÒÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$è‹¿ÿÿÇD$@‰$èýÀÿÿë‹Eì…Ût‰C`ècÃÿÿÿ븃Ä$[]ÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$”‹E ‰$ÿÜò…ÀtvÇD$ÇD$ ¡ŒÓ‰D$Eø‰D$‹Eü‰$èDÒÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èå¾ÿÿÇD$¸‰$èWÀÿÿë!‹Eø‹P`ÇD$¡xÓ‰D$‰$èÄÖÿÿë¸ÉÃU‰åVSƒì0ÇEìÇEðÇEôEô‰D$ Eð‰D$ÇD$‹E ‰$ÿÜò…À„¿ÇD$ÇD$ ¡ŒÓ‰D$Eì‰D$‹Eð‰$è€Ñÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$è!¾ÿÿÇD$8‰$è“¿ÿÿëj‹]ìuèEä‰D$‹Eô‰$èïßÿÿ‰Á÷Ð…ö•ÂÁè…Ât‹E䉅Éy&‰Êƒùÿuºûÿÿÿ‰$èʽÿÿÇD$”‰$è<¿ÿÿë‹Eè…Ût‰Cdè¢Áÿÿÿ븃Ä0[^]ÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$Ü‹E ‰$ÿÜò…ÀtuÇD$ÇD$ ¡ŒÓ‰D$Eø‰D$‹Eü‰$è‚Ðÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$è#½ÿÿÇD$ ‰$蕾ÿÿë ‹Eø‹@d…Ày ‰$ÿ”óë‰$ÿpóë¸ÉÃU‰åSƒì$ÇEðÇEôÇEøEø‰D$ Eô‰D$ÇD$\ ‹E ‰$ÿÜò…À„§ÇD$ÇD$ ¡ŒÓ‰D$Eð‰D$‹Eô‰$èÀÏÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èa¼ÿÿÇD$Œ ‰$èÓ½ÿÿëR‹]ðEì‰D$‹Eø‰$èxßÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$è"¼ÿÿÇD$ð ‰$蔽ÿÿë‹Eì…Ût‰Chèú¿ÿÿÿ븃Ä$[]ÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$@ ‹E ‰$ÿÜò…ÀtfÇD$ÇD$ ¡ŒÓ‰D$Eø‰D$‹Eü‰$èÛÎÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$è|»ÿÿÇD$l ‰$èî¼ÿÿë‹Eø‹@h‰$ÿpóë¸ÉÃU‰åSƒì$ÇEðÇEôÇEøEø‰D$ Eô‰D$ÇD$Ð ‹E ‰$ÿÜò…À„§ÇD$ÇD$ ¡ŒÓ‰D$Eð‰D$‹Eô‰$è(Îÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èɺÿÿÇD$ ‰$è;¼ÿÿëR‹]ðEì‰D$‹Eø‰$èàÝÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$芺ÿÿÇD$h ‰$èü»ÿÿë‹Eì…Ût‰Clèb¾ÿÿÿ븃Ä$[]ÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$¼ ‹E ‰$ÿÜò…ÀtfÇD$ÇD$ ¡ŒÓ‰D$Eø‰D$‹Eü‰$èCÍÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èä¹ÿÿÇD$ì ‰$èV»ÿÿë‹Eø‹@l‰$ÿpóë¸ÉÃU‰åƒìÇD$S ‹E ‰$ÿÜòº…ÀtYÇ0ÒèùÜÿÿ‰Âƒ=0Òt$è–ÖÿÿÇD$°Ó¡(ó‹‰$ÿ óºëÇD$¡ŒÓ‰D$‰$èPÑÿÿ‰Â‰ÐÉÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$p ‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡ŒÓ‰D$Eø‰D$‹Eü‰$èÌÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èÀ¸ÿÿÇD$ ‰$è2ºÿÿëKÇ0Ò‹Eø‰$èÜÿÿƒ=0Òt$è©ÕÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëè`¼ÿÿÿë¸ÉÃU‰åWVSƒì<ÇEØÇEÜuè}àE܉D$ÇD$è ‹E ‰$ÿÜò…À„HÇD$ÇD$ ¡ŒÓ‰D$E؉D$‹E܉$è8Ëÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èÙ·ÿÿÇD$ ‰$èK¹ÿÿéðÇ0Ò‰|$‰t$‹E؉$èDÛÿÿƒ=0Òt'è·ÔÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸é¨èk»ÿÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$è"¹ÿÿ‰Ãë'ÇD$¡”Ó‰D$‰4$èAÏÿÿ‰D$‰$èù¸ÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$è׸ÿÿ‰Ãë'ÇD$¡”Ó‰D$‰<$èöÎÿÿ‰D$‰$许ÿÿ‰Ã‰Øë¸ƒÄ<[^_]ÃU‰åWVSìœÇEÀÇEÄÇEÈÇEÌÇEÐÇEÔuè}àEÔ‰D$EЉD$ẺD$EȉD$ EĉD$ÇD$x ‹E ‰$ÿÜò…À„ÈÇD$ÇD$ ¡ŒÓ‰D$EÀ‰D$‹Eĉ$èhÉÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è ¶ÿÿÇD$¤ ‰$è{·ÿÿép‹]ÀE¸‰D$‹Eȉ$èðÖÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èǵÿÿÇD$‰$è9·ÿÿé.ÝE¸Ý]˜E°‰D$‹Ẻ$è«Öÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$肵ÿÿÇD$T‰$èô¶ÿÿééÝE°Ý]E¨‰D$‹EЉ$èfÖÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è=µÿÿÇD$¤‰$诶ÿÿé¤ÝE¨Ý]ˆE ‰D$‹EÔ‰$è!Öÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èø´ÿÿÇD$ô‰$èj¶ÿÿé_Ç0ÒE؉D$,‰|$(‰t$$ÝE Ý\$ÝEˆÝ\$ÝEÝ\$ ÝE˜Ý\$‰$èqØÿÿƒ=0Òt'è¶ÑÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸é÷èj¸ÿÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$è!¶ÿÿ‰Ãë'ÇD$¡”Ó‰D$‰4$è@Ìÿÿ‰D$‰$èøµÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$èÖµÿÿ‰Ãë'ÇD$¡”Ó‰D$‰<$èõËÿÿ‰D$‰$è­µÿÿ‰Ã¸…ÀtÝEØÝ$ÿ\ó‰D$‰$芵ÿÿ‰Ãë*ÇD$¡”Ó‰D$E؉$è¦Ëÿÿ‰D$‰$è^µÿÿ‰Ã‰Øë¸Äœ[^_]ÃU‰åWVSì¼ÇE¼ÇEÀÇEÄÇEÈÇEÌÇEÐÇEÔuè}àEÔ‰D$EЉD$ẺD$EȉD$EĉD$ EÀ‰D$ÇD$D‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡ŒÓ‰D$E¼‰D$‹EÀ‰$èÆÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$訲ÿÿÇD$p‰$è´ÿÿéÈ‹]¼E°‰D$‹Eĉ$èÓÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èf²ÿÿÇD$Љ$èØ³ÿÿé†ÝE°Ý]ˆE¨‰D$‹Eȉ$èJÓÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è!²ÿÿÇD$ ‰$蓳ÿÿéAÝE¨Ý]€E ‰D$‹Ẻ$èÓÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èܱÿÿÇD$p‰$èN³ÿÿéüÝE ÝxÿÿÿE˜‰D$‹EЉ$è½Òÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è”±ÿÿÇD$À‰$è³ÿÿé´ÝE˜ÝpÿÿÿE‰D$‹EÔ‰$èuÒÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èL±ÿÿÇD$‰$è¾²ÿÿélÇ0ÒE؉D$4‰|$0‰t$,ÝEÝ\$$Ý…pÿÿÿÝ\$Ý…xÿÿÿÝ\$ÝE€Ý\$ ÝEˆÝ\$‰$è Õÿÿƒ=0Òt'èýÍÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸é÷è±´ÿÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$èh²ÿÿ‰Ãë'ÇD$¡”Ó‰D$‰4$è‡Èÿÿ‰D$‰$è?²ÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$è²ÿÿ‰Ãë'ÇD$¡”Ó‰D$‰<$è<Èÿÿ‰D$‰$èô±ÿÿ‰Ã¸…ÀtÝEØÝ$ÿ\ó‰D$‰$èѱÿÿ‰Ãë*ÇD$¡”Ó‰D$E؉$èíÇÿÿ‰D$‰$襱ÿÿ‰Ã‰Øë¸Ä¼[^_]ÃU‰åWVSƒì<ÇEÐÇEÔuè}àEÔ‰D$ÇD$`‹E ‰$ÿÜò…À„žÇD$ÇD$ ¡ŒÓ‰D$EЉD$‹EÔ‰$è—Âÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è8¯ÿÿÇD$Œ‰$誰ÿÿéFÇ0ÒE؉D$ ‰|$‰t$‹EЉ$èsÓÿÿƒ=0Òt'èÌÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸é÷èòÿÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$èz°ÿÿ‰Ãë'ÇD$¡”Ó‰D$‰4$è™Æÿÿ‰D$‰$èQ°ÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$è/°ÿÿ‰Ãë'ÇD$¡”Ó‰D$‰<$èNÆÿÿ‰D$‰$è°ÿÿ‰Ã¸…ÀtÝEØÝ$ÿ\ó‰D$‰$èã¯ÿÿ‰Ãë*ÇD$¡”Ó‰D$E؉$èÿÅÿÿ‰D$‰$è·¯ÿÿ‰Ã‰Øë¸ƒÄ<[^_]ÃU‰åƒìEü‰D$ÇD$î‹E ‰$ÿÜòº…Àt%‹Eü‰$èÔ±ÿÿ‰D$¡ŒÓ‰$èÆ©ÿÿè~±ÿÿÿ‰Â‰ÐÉÃU‰åSƒì$ÇEðÇEôÇEøEø‰D$ Eô‰D$ÇD$‹E ‰$ÿÜò…À„èÇD$ÇD$ ¡|Ó‰D$Eð‰D$‹Eô‰$èSÀÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èô¬ÿÿÇD$(‰$èf®ÿÿé‹]ðÇD$ÇD$ ¡ˆÓ‰D$Eì‰D$‹Eø‰$èø¿ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$虬ÿÿÇD$„‰$è ®ÿÿë8ƒ}ìuÇ$÷ÿÿÿèu¬ÿÿÇD$؉$èç­ÿÿë‹Eì‹…Ût‰èL°ÿÿÿ븃Ä$[]ÃU‰åSƒì$ÇEôÇEøEø‰D$ÇD$D‹E ‰$ÿÜò…À„„ÇD$ÇD$ ¡|Ó‰D$Eô‰D$‹Eø‰$è(¿ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èÉ«ÿÿÇD$l‰$è;­ÿÿë/‹Eô‹Ç$èÝc‰ÇD$‹ˆÓ‰T$‰$èšÃÿÿ븃Ä$[]ÃU‰åSƒì$ÇEðÇEìÇEôÇEøEø‰D$ Eô‰D$ÇD$È‹E ‰$ÿÜò…À„òÇD$ÇD$ ¡|Ó‰D$Eð‰D$‹Eô‰$èL¾ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èíªÿÿÇD$ð‰$è_¬ÿÿéš‹]ðÇD$ÇD$ ¡”Ó‰D$Eì‰D$‹Eø‰$èñ½ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$è’ªÿÿÇD$P‰$è¬ÿÿëB‹Uì…Òt¸ÝÂÝ\Ã@ƒøvóëÇ$÷ÿÿÿèYªÿÿÇD$¤‰$èË«ÿÿë è;®ÿÿÿ븃Ä$[]ÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$ì‹E ‰$ÿÜò…ÀtvÇD$ÇD$ ¡|Ó‰D$Eø‰D$‹Eü‰$è½ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$轩ÿÿÇD$‰$è/«ÿÿë!‹UøƒÂÇD$¡”Ó‰D$‰$èœÁÿÿë¸ÉÃU‰åSƒì$ÇEðÇEìÇEôÇEøEø‰D$ Eô‰D$ÇD$t‹E ‰$ÿÜò…À„òÇD$ÇD$ ¡|Ó‰D$Eð‰D$‹Eô‰$èR¼ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èó¨ÿÿÇD$œ‰$èeªÿÿéš‹]ðÇD$ÇD$ ¡”Ó‰D$Eì‰D$‹Eø‰$è÷»ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$蘨ÿÿÇD$ø‰$è ªÿÿëB‹Uì…Òt¸ÝÂÝ\Ã@ƒøvóëÇ$÷ÿÿÿè_¨ÿÿÇD$H‰$èÑ©ÿÿë èA¬ÿÿÿ븃Ä$[]ÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$Œ‹E ‰$ÿÜò…ÀtvÇD$ÇD$ ¡|Ó‰D$Eø‰D$‹Eü‰$è"»ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èçÿÿÇD$°‰$è5©ÿÿë!‹UøƒÂÇD$¡”Ó‰D$‰$袿ÿÿë¸ÉÃU‰åVSƒì0ÇEìÇEðÇEôEô‰D$ Eð‰D$ÇD$ ‹E ‰$ÿÜò…À„¿ÇD$ÇD$ ¡|Ó‰D$Eì‰D$‹Eð‰$è^ºÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èÿ¦ÿÿÇD$,‰$èq¨ÿÿëj‹]ìuèEä‰D$‹Eô‰$èÍÈÿÿ‰Á÷Ð…ö•ÂÁè…Ât‹E䉅Éy&‰Êƒùÿuºûÿÿÿ‰$訦ÿÿÇD$„‰$è¨ÿÿë‹Eè…Ût‰C(耪ÿÿÿ븃Ä0[^]ÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$Ì‹E ‰$ÿÜò…ÀtuÇD$ÇD$ ¡|Ó‰D$Eø‰D$‹Eü‰$è`¹ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$è¦ÿÿÇD$ì‰$ès§ÿÿë ‹Eø‹@(…Ày ‰$ÿ”óë‰$ÿpóë¸ÉÃU‰åSƒì$ÇEðÇEìÇEôÇEøEø‰D$ Eô‰D$ÇD$D‹E ‰$ÿÜò…À„òÇD$ÇD$ ¡|Ó‰D$Eð‰D$‹Eô‰$è—¸ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è8¥ÿÿÇD$h‰$誦ÿÿéš‹]ðÇD$ÇD$ ¡ Ó‰D$Eì‰D$‹Eø‰$è<¸ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èݤÿÿÇD$À‰$èO¦ÿÿëB‹Mì…Étº‹‘‰D“,BƒúvóëÇ$÷ÿÿÿ褤ÿÿÇD$ ‰$è¦ÿÿë 膨ÿÿÿ븃Ä$[]ÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$L‹E ‰$ÿÜò…ÀtvÇD$ÇD$ ¡|Ó‰D$Eø‰D$‹Eü‰$èg·ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$è¤ÿÿÇD$l‰$èz¥ÿÿë!‹UøƒÂ,ÇD$¡ Ó‰D$‰$èç»ÿÿë¸ÉÃU‰åƒìÇD$‹E ‰$ÿÜòº…ÀtYÇ0ÒèEÈÿÿ‰Âƒ=0Òt$èªÀÿÿÇD$°Ó¡(ó‹‰$ÿ óºëÇD$¡|Ó‰D$‰$èd»ÿÿ‰Â‰ÐÉÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$Û‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡|Ó‰D$Eø‰D$‹Eü‰$è3¶ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èÔ¢ÿÿÇD$ø‰$èF¤ÿÿëKÇ0Ò‹Eø‰$èjÇÿÿƒ=0Òt$轿ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëèt¦ÿÿÿë¸ÉÃU‰åWVSƒìlÇEÈÇEÌÇEÐÇEÔuè}àEÔ‰D$EЉD$ ẺD$ÇD$L‹E ‰$ÿÜò…À„0ÇD$ÇD$ ¡|Ó‰D$EȉD$‹Ẻ$è0µÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èÑ¡ÿÿÇD$x‰$èC£ÿÿ騋]ÈEÀ‰D$‹EЉ$è¸Âÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è¡ÿÿÇD$؉$è£ÿÿé–ÝEÀÝ]°E¸‰D$‹EÔ‰$èsÂÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èJ¡ÿÿÇD$(‰$è¼¢ÿÿéQÇ0ÒE؉D$‰|$‰t$ÝE¸Ý\$ ÝE°Ý\$‰$èÛÅÿÿƒ=0Òt'è¾ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸é÷èʤÿÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$è¢ÿÿ‰Ãë'ÇD$¡”Ó‰D$‰4$è ¸ÿÿ‰D$‰$èX¢ÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$è6¢ÿÿ‰Ãë'ÇD$¡”Ó‰D$‰<$èU¸ÿÿ‰D$‰$è ¢ÿÿ‰Ã¸…ÀtÝEØÝ$ÿ\ó‰D$‰$èê¡ÿÿ‰Ãë*ÇD$¡”Ó‰D$E؉$è¸ÿÿ‰D$‰$辡ÿÿ‰Ã‰Øë¸ƒÄl[^_]ÃU‰åWVSƒì\ÇEÐÇEÔÇEØÇEÜuè}àE܉D$E؉D$ EÔ‰D$ÇD$x‹E ‰$ÿÜò…À„ÚÇD$ÇD$ ¡|Ó‰D$EЉD$‹EÔ‰$è—²ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è8ŸÿÿÇD$ ‰$誠ÿÿé‚‹]ÐEȉD$‹E؉$èÀÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èöžÿÿÇD$ü‰$èh ÿÿé@ÝEÈÝ]¸EÀ‰D$‹E܉$èÚ¿ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$豞ÿÿÇD$H‰$è# ÿÿéûÇ0Ò‰|$‰t$ÝEÀÝ\$ ÝE¸Ý\$‰$è„Ãÿÿƒ=0Òt'è„»ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸é¨è8¢ÿÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$èïŸÿÿ‰Ãë'ÇD$¡”Ó‰D$‰4$è¶ÿÿ‰D$‰$èÆŸÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$褟ÿÿ‰Ãë'ÇD$¡”Ó‰D$‰<$èõÿÿ‰D$‰$è{Ÿÿÿ‰Ã‰Øë¸ƒÄ\[^_]ÃU‰åVSƒì0ÇEèÇEìuðEì‰D$ÇD$”‹E ‰$ÿÜò…À„öÇD$ÇD$ ¡|Ó‰D$Eè‰D$‹Eì‰$èt°ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èÿÿÇD$À‰$臞ÿÿéžÇ0Ò‰t$‹Eè‰$è+Âÿÿƒ=0Òt$è÷¹ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ë]è® ÿÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$èežÿÿ‰Ãë'ÇD$¡”Ó‰D$‰4$è„´ÿÿ‰D$‰$è<žÿÿ‰Ã‰Øë¸ƒÄ0[^]ÃU‰åWVSƒì<ÇEÐÇEÔuè}àEÔ‰D$ÇD$$‹E ‰$ÿÜò…À„žÇD$ÇD$ ¡|Ó‰D$EЉD$‹EÔ‰$è2¯ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èÓ›ÿÿÇD$P‰$èEÿÿéFÇ0ÒE؉D$ ‰|$‰t$‹EЉ$èýÀÿÿƒ=0Òt'誸ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸é÷è^Ÿÿÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$èÿÿ‰Ãë'ÇD$¡”Ó‰D$‰4$è4³ÿÿ‰D$‰$èìœÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$èÊœÿÿ‰Ãë'ÇD$¡”Ó‰D$‰<$èé²ÿÿ‰D$‰$衜ÿÿ‰Ã¸…ÀtÝEØÝ$ÿ\ó‰D$‰$è~œÿÿ‰Ãë*ÇD$¡”Ó‰D$E؉$èš²ÿÿ‰D$‰$èRœÿÿ‰Ã‰Øë¸ƒÄ<[^_]ÃU‰åVSƒì0ÇEäÇEèÇEìuðEì‰D$ Eè‰D$ÇD$°‹E ‰$ÿÜò…À„<ÇD$ÇD$ ¡|Ó‰D$Eä‰D$‹Eè‰$è=­ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èÞ™ÿÿÇD$à‰$èP›ÿÿéä‹]äEà‰D$‹Eì‰$èD¿ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$蜙ÿÿÇD$D‰$è›ÿÿé¢Ç0Ò‰t$‹Eà‰D$‰$è-¿ÿÿƒ=0Òt$èz¶ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ë]è1ÿÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$èèšÿÿ‰Ãë'ÇD$¡”Ó‰D$‰4$è±ÿÿ‰D$‰$迚ÿÿ‰Ã‰Øë¸ƒÄ0[^]ÃU‰åWVSƒìlÇEÈÇEÌÇEÐÇEÔuè}àEÔ‰D$EЉD$ ẺD$ÇD$ ‹E ‰$ÿÜò…À„0ÇD$ÇD$ ¡|Ó‰D$EȉD$‹Ẻ$虫ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è:˜ÿÿÇD$Љ$謙ÿÿ騋]ÈEÀ‰D$‹EЉ$è!¹ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èø—ÿÿÇD$4‰$èj™ÿÿé–ÝEÀÝ]°E¸‰D$‹EÔ‰$èܸÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è³—ÿÿÇD$ˆ‰$è%™ÿÿéQÇ0ÒE؉D$‰|$‰t$ÝE¸Ý\$ ÝE°Ý\$‰$èX½ÿÿƒ=0Òt'è´ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸é÷è3›ÿÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$èê˜ÿÿ‰Ãë'ÇD$¡”Ó‰D$‰4$è ¯ÿÿ‰D$‰$èÁ˜ÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$蟘ÿÿ‰Ãë'ÇD$¡”Ó‰D$‰<$è¾®ÿÿ‰D$‰$èv˜ÿÿ‰Ã¸…ÀtÝEØÝ$ÿ\ó‰D$‰$èS˜ÿÿ‰Ãë*ÇD$¡”Ó‰D$E؉$èo®ÿÿ‰D$‰$è'˜ÿÿ‰Ã‰Øë¸ƒÄl[^_]ÃU‰åWVSƒìLÇEÈÇEÌuè}àẺD$ÇD$Ü‹E ‰$ÿÜò…À„ôÇD$ÇD$ ¡|Ó‰D$EȉD$‹Ẻ$è©ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$轕ÿÿÇD$ ‰$è/—ÿÿéœÇ0ÒEЉD$E؉D$ ‰|$‰t$‹Eȉ$è¡»ÿÿƒ=0Òt'è²ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸éFèA™ÿÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$èø–ÿÿ‰Ãë'ÇD$¡”Ó‰D$‰4$è­ÿÿ‰D$‰$èÏ–ÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$è­–ÿÿ‰Ãë'ÇD$¡”Ó‰D$‰<$è̬ÿÿ‰D$‰$è„–ÿÿ‰Ã¸…ÀtÝEØÝ$ÿ\ó‰D$‰$èa–ÿÿ‰Ãë*ÇD$¡”Ó‰D$E؉$è}¬ÿÿ‰D$‰$è5–ÿÿ‰Ã¸…ÀtÝEÐÝ$ÿ\ó‰D$‰$è–ÿÿ‰Ãë*ÇD$¡”Ó‰D$EЉ$è.¬ÿÿ‰D$‰$èæ•ÿÿ‰Ã‰Øë¸ƒÄL[^_]ÃU‰åƒìEü‰D$ÇD$î‹E ‰$ÿÜòº…Àt%‹Eü‰$è˜ÿÿ‰D$¡|Ó‰$èõÿÿè­—ÿÿÿ‰Â‰ÐÉÃU‰åSƒì$ÇEðÇEìÇEôÇEøEø‰D$ Eô‰D$ÇD$` ‹E ‰$ÿÜò…À„¿ÇD$ÇD$ ¡€Ó‰D$Eð‰D$‹Eô‰$è{¦ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$è“ÿÿÇD$€ ‰$莔ÿÿëj‹]ðÇD$ÇD$ ¡„Ó‰D$Eì‰D$‹Eø‰$è#¦ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èÄ’ÿÿÇD$Ô ‰$è6”ÿÿë‹Eì…Ût‰è–ÿÿÿ븃Ä$[]ÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$!‹E ‰$ÿÜò…ÀtuÇD$ÇD$ ¡€Ó‰D$Eø‰D$‹Eü‰$è~¥ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$è’ÿÿÇD$tÿÿ‰D$‰$èö]ÿÿ‰Ã}Ðu ‹Ẻ$è#‰Øë}Ðu ‹Ẻ$è ¸ƒÄL[^_]ÃU‰åSƒì4ÇEðÇEèÇEìÇEôÇEøEø‰D$ Eô‰D$ÇD$ä<‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡€Ó‰D$Eð‰D$‹Eô‰$è¯nÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èP[ÿÿÇD$=‰$èÂ\ÿÿ鵋]ðEì‰D$ ÇD$Eè‰D$‹Eø‰$èÁÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èÿZÿÿÇD$`=‰$èq\ÿÿëgÇ0Ò‹Eè‰D$‰$è̇ÿÿƒ=0Òt$èäwÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ë:è›^ÿÿÿ‰Ã}ìu ‹Eè‰$衉Øë}ìu ‹Eè‰$艸ƒÄ4[]ÃU‰åWVSƒì<ÇEÜÇEàuè}äEà‰D$ÇD$°=‹E ‰$ÿÜò…À„HÇD$ÇD$ ¡€Ó‰D$E܉D$‹Eà‰$èCmÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èäYÿÿÇD$Ô=‰$èV[ÿÿéðÇ0Ò‰|$‰t$‹E܉$èɆÿÿƒ=0Òt'èÂvÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸é¨èv]ÿÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$è-[ÿÿ‰Ãë'ÇD$¡”Ó‰D$‰4$èLqÿÿ‰D$‰$è[ÿÿ‰Ã¸…Àt‹‰$ÿpó‰D$‰$èâZÿÿ‰Ãë'ÇD$¡˜Ó‰D$‰<$èqÿÿ‰D$‰$è¹Zÿÿ‰Ã‰Øë¸ƒÄ<[^_]ÃU‰åSƒì4ÇEðÇEèÇEìÇEôÇEøEø‰D$ Eô‰D$ÇD$,>‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡€Ó‰D$Eð‰D$‹Eô‰$èškÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è;XÿÿÇD$P>‰$è­Yÿÿ鵋]ðEì‰D$ ÇD$Eè‰D$‹Eø‰$è¬~ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èêWÿÿÇD$¨>‰$è\YÿÿëgÇ0Ò‹Eè‰D$‰$è…ÿÿƒ=0Òt$èÏtÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ë:è†[ÿÿÿ‰Ã}ìu ‹Eè‰$茉Øë}ìu ‹Eè‰$èt¸ƒÄ4[]ÃU‰åWSƒì0ÇEìÇEäÇEèÇEðÇEôEô‰D$ Eð‰D$ÇD$ø>‹E ‰$ÿÜò…À„lÇD$ÇD$ ¡€Ó‰D$Eì‰D$‹Eð‰$èjÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èºVÿÿÇD$ ?‰$è,Xÿÿé‹]ìEè‰D$ ÇD$Eä‰D$‹Eô‰$è+}ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èiVÿÿÇD$|?‰$èÛWÿÿéÃÇ0Ò‹Eä‰D$‰$蟃ÿÿƒ=0Òt'èKsÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸é“‰Ã¸…Ût‰ßü¹ÿÿÿÿò®÷ÑAÿ…Ût;…Ày(è~vÿÿ…ÀtÇD$‰D$‰$èÜmÿÿëè¾Yÿÿÿë‰D$‰$ÿìóëè¦Yÿÿÿ‰Ã}èu ‹Eä‰$è¬ ‰Øë}èu ‹Eä‰$è” ¸ƒÄ0[_]ÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$Ð?‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡€Ó‰D$Eø‰D$‹Eü‰$èVhÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$è÷TÿÿÇD$ô?‰$èiVÿÿëKÇ0Ò‹Eø‰$è]‚ÿÿƒ=0Òt$èàqÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëè—Xÿÿÿë¸ÉÃU‰åVSƒì0ÇEèÇEìÇEðuôEð‰D$ Eì‰D$ÇD$L@‹E ‰$ÿÜò…À„<ÇD$ÇD$ ¡€Ó‰D$Eè‰D$‹Eì‰$èegÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èTÿÿÇD$x@‰$èxUÿÿéä‹]èEä‰D$‹Eð‰$èwÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èÄSÿÿÇD$Ø@‰$è6Uÿÿé¢Ç0Ò‹Eä‰D$‰t$‰$è7ÿÿƒ=0Òt$è¢pÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ë]èYWÿÿÿ‰Ã¸…Àt‹‰$ÿpó‰D$‰$èUÿÿ‰Ãë'ÇD$¡˜Ó‰D$‰4$è/kÿÿ‰D$‰$èçTÿÿ‰Ã‰Øë¸ƒÄ0[^]ÃU‰åWVSƒìLÇEÌÇEÐuð}ìEЉD$ÇD$(A‹E ‰$ÿÜò…À„LÇD$ÇD$ ¡€Ó‰D$ẺD$‹EЉ$èÝeÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è~RÿÿÇD$XA‰$èðSÿÿéôÇ0ÒEÔ‰D$ E؉D$E܉D$Eà‰D$Eä‰D$Eè‰D$ ‰|$‰t$‹Ẻ$èíÿÿƒ=0Òt'è2oÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸é‚èæUÿÿÿ‰Ã¸…Àt‹‰$ÿpó‰D$‰$èSÿÿ‰Ãë'ÇD$¡˜Ó‰D$‰4$è¼iÿÿ‰D$‰$ètSÿÿ‰Ã¸…Àt‹‰$ÿpó‰D$‰$èRSÿÿ‰Ãë'ÇD$¡˜Ó‰D$‰<$èqiÿÿ‰D$‰$è)Sÿÿ‰Ã¸…Àt‹Eè‰$ÿpó‰D$‰$èSÿÿ‰Ãë*ÇD$¡˜Ó‰D$Eè‰$è"iÿÿ‰D$‰$èÚRÿÿ‰Ã¸…Àt‹Eä‰$ÿpó‰D$‰$è·Rÿÿ‰Ãë*ÇD$¡˜Ó‰D$Eä‰$èÓhÿÿ‰D$‰$è‹Rÿÿ‰Ã¸…Àt‹Eà‰$ÿpó‰D$‰$èhRÿÿ‰Ãë*ÇD$¡˜Ó‰D$Eà‰$è„hÿÿ‰D$‰$èlÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$è|EÿÿÇD$ÈG‰$èîFÿÿëgÇ0Ò‹Eè‰D$‰$èŽtÿÿƒ=0Òt$èabÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ë:èIÿÿÿ‰Ã}ìu ‹Eè‰$èý‰Øë}ìu ‹Eè‰$èý¸ƒÄ4[]ÃU‰åVSƒìPÇEäÇEèÇEìÇEðÇEôEô‰D$Eð‰D$Eì‰D$ Eè‰D$ÇD$H‹E ‰$ÿÜò…À„xÇD$ÇD$ ¡€Ó‰D$Eä‰D$‹Eè‰$èWÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è>DÿÿÇD$@H‰$è°Eÿÿé ‹uäE؉D$‹Eì‰$è%eÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èüCÿÿÇD$˜H‰$ènEÿÿéÞÝEØÝ]ÀEÔ‰D$‹Eð‰$è gÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è·CÿÿÇD$äH‰$è)Eÿÿ陋]ÔEȉD$‹Eô‰$èždÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èuCÿÿÇD$,I‰$èçDÿÿëZÇ0ÒÝEÈÝ\$‰\$ ÝEÀÝ\$‰4$è›rÿÿƒ=0Òt$èO`ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëèGÿÿÿ븃ÄP[^]ÃU‰åWVSƒì|ÇE ÇE¤uè}àE¤‰D$ÇD$xI‹E ‰$ÿÜò…À„¢ÇD$ÇD$ ¡€Ó‰D$E ‰D$‹E¤‰$èÙUÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èzBÿÿÇD$¤I‰$èìCÿÿéJÇ0ÒE¨‰D$$E°‰D$ E¸‰D$EÀ‰D$EȉD$EЉD$E؉D$ ‰|$‰t$‹E ‰$è¨qÿÿƒ=0Òt'è'_ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸éÑèÛEÿÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$è’Cÿÿ‰Ãë'ÇD$¡”Ó‰D$‰4$è±Yÿÿ‰D$‰$èiCÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$èGCÿÿ‰Ãë'ÇD$¡”Ó‰D$‰<$èfYÿÿ‰D$‰$èCÿÿ‰Ã¸…ÀtÝEØÝ$ÿ\ó‰D$‰$èûBÿÿ‰Ãë*ÇD$¡”Ó‰D$E؉$èYÿÿ‰D$‰$èÏBÿÿ‰Ã¸…ÀtÝEÐÝ$ÿ\ó‰D$‰$è¬Bÿÿ‰Ãë*ÇD$¡”Ó‰D$EЉ$èÈXÿÿ‰D$‰$è€Bÿÿ‰Ã¸…ÀtÝEÈÝ$ÿ\ó‰D$‰$è]Bÿÿ‰Ãë*ÇD$¡”Ó‰D$Eȉ$èyXÿÿ‰D$‰$è1Bÿÿ‰Ã¸…ÀtÝEÀÝ$ÿ\ó‰D$‰$èBÿÿ‰Ãë*ÇD$¡”Ó‰D$EÀ‰$è*Xÿÿ‰D$‰$èâAÿÿ‰Ã¸…ÀtÝE¸Ý$ÿ\ó‰D$‰$è¿Aÿÿ‰Ãë*ÇD$¡”Ó‰D$E¸‰$èÛWÿÿ‰D$‰$è“Aÿÿ‰Ã¸…ÀtÝE°Ý$ÿ\ó‰D$‰$èpAÿÿ‰Ãë*ÇD$¡”Ó‰D$E°‰$èŒWÿÿ‰D$‰$èDAÿÿ‰Ã¸…ÀtÝE¨Ý$ÿ\ó‰D$‰$è!Aÿÿ‰Ãë*ÇD$¡”Ó‰D$E¨‰$è=Wÿÿ‰D$‰$èõ@ÿÿ‰Ã‰Øë¸ƒÄ|[^_]ÃU‰åWVSƒì<ÇEÐÇEÔuè}àEÔ‰D$ÇD$J‹E ‰$ÿÜò…À„žÇD$ÇD$ ¡€Ó‰D$EЉD$‹EÔ‰$èêQÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è‹>ÿÿÇD$(J‰$èý?ÿÿéFÇ0ÒE؉D$ ‰|$‰t$‹EЉ$èJnÿÿƒ=0Òt'èb[ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸é÷èBÿÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$èÍ?ÿÿ‰Ãë'ÇD$¡”Ó‰D$‰4$èìUÿÿ‰D$‰$è¤?ÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$è‚?ÿÿ‰Ãë'ÇD$¡”Ó‰D$‰<$è¡Uÿÿ‰D$‰$èY?ÿÿ‰Ã¸…ÀtÝEØÝ$ÿ\ó‰D$‰$è6?ÿÿ‰Ãë*ÇD$¡”Ó‰D$E؉$èRUÿÿ‰D$‰$è ?ÿÿ‰Ã‰Øë¸ƒÄ<[^_]ÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$€J‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡€Ó‰D$Eø‰D$‹Eü‰$èPÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$è©<ÿÿÇD$¤J‰$è>ÿÿëKÇ0Ò‹Eø‰$è§lÿÿƒ=0Òt$è’YÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëèI@ÿÿÿë¸ÉÃU‰åSƒì4ÇEðÇEèÇEìÇEôÇEøEø‰D$ Eô‰D$ÇD$üJ‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡€Ó‰D$Eð‰D$‹Eô‰$è Oÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è®;ÿÿÇD$ K‰$è =ÿÿ鵋]ðEì‰D$ ÇD$Eè‰D$‹Eø‰$èbÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$è];ÿÿÇD$xK‰$èÏ<ÿÿëgÇ0Ò‹Eè‰D$‰$èokÿÿƒ=0Òt$èBXÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ë:èù>ÿÿÿ‰Ã}ìu ‹Eè‰$èÿò‰Øë}ìu ‹Eè‰$èçò¸ƒÄ4[]ÃU‰åSƒì$ÇEðÇEôÇEøEø‰D$ Eô‰D$ÇD$ÄK‹E ‰$ÿÜò…À„æÇD$ÇD$ ¡€Ó‰D$Eð‰D$‹Eô‰$è›Mÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è<:ÿÿÇD$äK‰$è®;ÿÿ鎋]ðEì‰D$‹Eø‰$è¢_ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èú9ÿÿÇD$8L‰$èl;ÿÿëOÇ0Ò‹Eì‰D$‰$èKjÿÿƒ=0Òt$èßVÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëè–=ÿÿÿ븃Ä$[]ÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$„L‹E ‰$ÿÜò…À„±ÇD$ÇD$ ¡€Ó‰D$Eø‰D$‹Eü‰$èsLÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$è9ÿÿÇD$¨L‰$è†:ÿÿë\Ç0Ò‹Eø‰$èˆiÿÿƒ=0Òt$èýUÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ë…Ày ‰$ÿ”óë‰$ÿpóë¸ÉÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$M‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡€Ó‰D$Eø‰D$‹Eü‰$è„Kÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$è%8ÿÿÇD$8M‰$è—9ÿÿëKÇ0Ò‹Eø‰$è»hÿÿƒ=0Òt$èUÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëèÅ;ÿÿÿë¸ÉÃU‰åWVSƒì<ÇEÔÇEØÇEÜuè}àE܉D$ E؉D$ÇD$¡M‹E ‰$ÿÜò…À„ŽÇD$ÇD$ ¡€Ó‰D$EÔ‰D$‹E؉$èJÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è07ÿÿÇD$ÀM‰$è¢8ÿÿé6‹]ÔEЉD$‹E܉$è–\ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èî6ÿÿÇD$N‰$è`8ÿÿéôÇ0Ò‰|$ ‰t$‹EЉD$‰$è„gÿÿƒ=0Òt'èÈSÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸é¨è|:ÿÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$è38ÿÿ‰Ãë'ÇD$¡”Ó‰D$‰4$èRNÿÿ‰D$‰$è 8ÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$èè7ÿÿ‰Ãë'ÇD$¡”Ó‰D$‰<$èNÿÿ‰D$‰$è¿7ÿÿ‰Ã‰Øë¸ƒÄ<[^_]ÃU‰åSƒì4ÇEðÇEèÇEìÇEôÇEøEø‰D$ Eô‰D$ÇD$`N‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡€Ó‰D$Eð‰D$‹Eô‰$è Hÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èA5ÿÿÇD$„N‰$è³6ÿÿ鵋]ðEì‰D$ ÇD$Eè‰D$‹Eø‰$è²[ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èð4ÿÿÇD$ÜN‰$èb6ÿÿëgÇ0Ò‹Eè‰D$‰$è¾eÿÿƒ=0Òt$èÕQÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ë:èŒ8ÿÿÿ‰Ã}ìu ‹Eè‰$è’ì‰Øë}ìu ‹Eè‰$èz츃Ä4[]ÃU‰åSƒìDÇEèÇEìÇEðÇEôEô‰D$Eð‰D$ Eì‰D$ÇD$,O‹E ‰$ÿÜò…À„2ÇD$ÇD$ ¡€Ó‰D$Eè‰D$‹Eì‰$è Gÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èÁ3ÿÿÇD$TO‰$è35ÿÿéÚ‹]èEà‰D$‹Eð‰$è¨Tÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è3ÿÿÇD$°O‰$èñ4ÿÿé˜ÝEàÝ]ÐE؉D$‹Eô‰$ècTÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$è:3ÿÿÇD$üO‰$è¬4ÿÿëVÇ0ÒÝEØÝ\$ ÝEÐÝ\$‰$è dÿÿƒ=0Òt$èPÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëèÏ6ÿÿÿ븃ÄD[]ÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$HP‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡€Ó‰D$Eø‰D$‹Eü‰$è¬Eÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èM2ÿÿÇD$pP‰$è¿3ÿÿëKÇ0Ò‹Eø‰$èdcÿÿƒ=0Òt$è6OÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëèí5ÿÿÿë¸ÉÃU‰åSƒì$ÇEðÇEôÇEøEø‰D$ Eô‰D$ÇD$ÌP‹E ‰$ÿÜò…À„æÇD$ÇD$ ¡€Ó‰D$Eð‰D$‹Eô‰$è¿Dÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è`1ÿÿÇD$ìP‰$èÒ2ÿÿ鎋]ðEì‰D$‹Eø‰$èÆVÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$è1ÿÿÇD$@Q‰$è2ÿÿëOÇ0Ò‹Eì‰D$‰$è@bÿÿƒ=0Òt$èNÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëèº4ÿÿÿ븃Ä$[]ÃU‰åWSƒì ÇEðÇEôEô‰D$ÇD$ŒQ‹E ‰$ÿÜò…À„üÇD$ÇD$ ¡€Ó‰D$Eð‰D$‹Eô‰$è•Cÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è60ÿÿÇD$¬Q‰$è¨1ÿÿé¤Ç0Ò‹Eð‰$èxaÿÿƒ=0Òt$èMÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëg‰Ã¸…Ût‰ßü¹ÿÿÿÿò®÷ÑAÿ…Ût;…Ày(èRPÿÿ…ÀtÇD$‰D$‰$è°Gÿÿë&è’3ÿÿÿë‰D$‰$ÿìóëèz3ÿÿÿë¸ƒÄ [_]ÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$R‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡€Ó‰D$Eø‰D$‹Eü‰$èVBÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$è÷.ÿÿÇD$(R‰$èi0ÿÿëKÇ0Ò‹Eø‰$è^`ÿÿƒ=0Òt$èàKÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëè—2ÿÿÿë¸ÉÃU‰åWSƒì0ÇEìÇEäÇEèÇEðÇEôEô‰D$ Eð‰D$ÇD$„R‹E ‰$ÿÜò…À„lÇD$ÇD$ ¡€Ó‰D$Eì‰D$‹Eð‰$èZAÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èû-ÿÿÇD$¨R‰$èm/ÿÿé‹]ìEè‰D$ ÇD$Eä‰D$‹Eô‰$èlTÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èª-ÿÿÇD$S‰$è/ÿÿéÃÇ0Ò‹Eä‰D$‰$è"_ÿÿƒ=0Òt'èŒJÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸é“‰Ã¸…Ût‰ßü¹ÿÿÿÿò®÷ÑAÿ…Ût;…Ày(è¿Mÿÿ…ÀtÇD$‰D$‰$èEÿÿëèÿ0ÿÿÿë‰D$‰$ÿìóëèç0ÿÿÿ‰Ã}èu ‹Eä‰$èí䉨ë}èu ‹Eä‰$èÕ七Ä0[_]ÃU‰åWVSƒì<ÇEàÇEØÇEÜÇEäÇEèÇEì}ðEì‰D$Eè‰D$ Eä‰D$ÇD$PS‹E ‰$ÿÜò…À„¨ÇD$ÇD$ ¡€Ó‰D$Eà‰D$‹Eä‰$èg?ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è,ÿÿÇD$„S‰$èz-ÿÿéP‹uàE܉D$ ÇD$E؉D$‹Eè‰$èyRÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è·+ÿÿÇD$èS‰$è)-ÿÿéÿ‹]ØEÔ‰D$‹Eì‰$èËNÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èu+ÿÿÇD$HT‰$èç,ÿÿé½Ç0Ò‹EÔ‰D$ ‰|$‰\$‰4$è]ÿÿƒ=0Òt'èOHÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸é…è/ÿÿÿ‰Ã¸…Àt‹‰$ÿpó‰D$‰$èº,ÿÿ‰Ãë'ÇD$¡˜Ó‰D$‰<$èÙBÿÿ‰D$‰$è‘,ÿÿ‰Ã}Üu ‹E؉$è¾â‰Øë}Üu ‹E؉$è¦â¸ƒÄ<[^_]ÃU‰åWVSƒìLÇEÜÇEàÇEäÇEèÇEìEì‰D$Eè‰D$Eä‰D$ Eà‰D$ÇD$œT‹E ‰$ÿÜò…À„rÇD$ÇD$ ¡€Ó‰D$E܉D$‹Eà‰$è:=ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èÛ)ÿÿÇD$ÄT‰$èM+ÿÿé‹}ÜE؉D$‹Eä‰$èAOÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è™)ÿÿÇD$U‰$è +ÿÿ騋uØEÔ‰D$‹Eè‰$èÿNÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èW)ÿÿÇD$lU‰$èÉ*ÿÿé–‹]ÔEȉD$‹Eì‰$è>Jÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$è)ÿÿÇD$¼U‰$è‡*ÿÿëWÇ0ÒÝEÈÝ\$ ‰\$‰t$‰<$èÞZÿÿƒ=0Òt$èòEÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëè©,ÿÿÿ븃ÄL[^_]ÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$V‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡€Ó‰D$Eø‰D$‹Eü‰$è„;ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$è%(ÿÿÇD$(V‰$è—)ÿÿëKÇ0Ò‹Eø‰$è'Zÿÿƒ=0Òt$èEÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëèÅ+ÿÿÿë¸ÉÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$|V‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡€Ó‰D$Eø‰D$‹Eü‰$è¦:ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èG'ÿÿÇD$ V‰$è¹(ÿÿëKÇ0Ò‹Eø‰$èaYÿÿƒ=0Òt$è0DÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëèç*ÿÿÿë¸ÉÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$øV‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡€Ó‰D$Eø‰D$‹Eü‰$èÈ9ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èi&ÿÿÇD$W‰$èÛ'ÿÿëKÇ0Ò‹Eø‰$è’Xÿÿƒ=0Òt$èRCÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëè *ÿÿÿë¸ÉÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$tW‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡€Ó‰D$Eø‰D$‹Eü‰$èê8ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$è‹%ÿÿÇD$˜W‰$èý&ÿÿëKÇ0Ò‹Eø‰$èÃWÿÿƒ=0Òt$ètBÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëè+)ÿÿÿë¸ÉÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$ðW‹E ‰$ÿÜò…À„´ÇD$ÇD$ ¡€Ó‰D$Eø‰D$‹Eü‰$è 8ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$è­$ÿÿÇD$X‰$è&ÿÿë_Ç0Ò‹Eø‰$èýVÿÿ‰Âƒ=0Òt$è”AÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ë ÇD$¡ŒÓ‰D$‰$èN<ÿÿë¸ÉÃU‰åSƒì4ÇEðÇEèÇEìÇEôÇEøEø‰D$ Eô‰D$ÇD$|X‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡€Ó‰D$Eð‰D$‹Eô‰$èý6ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èž#ÿÿÇD$¤X‰$è%ÿÿ鵋]ðEì‰D$ ÇD$Eè‰D$‹Eø‰$èJÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èM#ÿÿÇD$Y‰$è¿$ÿÿëgÇ0Ò‹Eè‰D$‰$è»Uÿÿƒ=0Òt$è2@ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ë:èé&ÿÿÿ‰Ã}ìu ‹Eè‰$èïÚ‰Øë}ìu ‹Eè‰$è×Ú¸ƒÄ4[]ÃU‰åSƒì4ÇEðÇEèÇEìÇEôÇEøEø‰D$ Eô‰D$ÇD$TY‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡€Ó‰D$Eð‰D$‹Eô‰$è}5ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è"ÿÿÇD$xY‰$è#ÿÿ鵋]ðEì‰D$ ÇD$Eè‰D$‹Eø‰$èHÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èÍ!ÿÿÇD$ÐY‰$è?#ÿÿëgÇ0Ò‹Eè‰D$‰$èZTÿÿƒ=0Òt$è²>ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ë:èi%ÿÿÿ‰Ã}ìu ‹Eè‰$èoÙ‰Øë}ìu ‹Eè‰$èWÙ¸ƒÄ4[]ÃU‰åWVSƒì,ÇEäÇEðÇEè}ðEè‰D$ÇD$ Z‹E ‰$ÿÜò…À„ÇD$ÇD$ ¡€Ó‰D$Eä‰D$‹Eè‰$è 4ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è® ÿÿÇD$PZ‰$è "ÿÿéÀÇ0ÒEì‰D$‰|$‹Eä‰$èPSÿÿƒ=0Òt$è‰=ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëxè@$ÿÿÿ‰Æƒ?ta‹‹Eìt;…Ày(èÈ@ÿÿ…ÀtÇD$‰D$‰$è&8ÿÿëè$ÿÿÿë‰D$‰$ÿìóëèð#ÿÿÿ‰D$‰4$è½!ÿÿ‰Æ‹‰$èô׉ð븃Ä,[^_]ÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$´Z‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡€Ó‰D$Eø‰D$‹Eü‰$è±2ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èRÿÿÇD$ØZ‰$èÄ ÿÿëKÇ0Ò‹Eø‰$èÇRÿÿƒ=0Òt$è;<ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëèò"ÿÿÿë¸ÉÃU‰åSƒì$ÇEðÇEìÇEôÇEøEø‰D$ Eô‰D$ÇD$0[‹E ‰$ÿÜò…À„ÿÇD$ÇD$ ¡€Ó‰D$Eð‰D$‹Eô‰$è½1ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è^ÿÿÇD$T[‰$èÐÿÿé§‹]ðÇD$ÇD$ ¡€Ó‰D$Eì‰D$‹Eø‰$èb1ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èÿÿÇD$¬[‰$èuÿÿëOÇ0Ò‹Eì‰D$‰$èƒQÿÿƒ=0Òt$èè:ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëèŸ!ÿÿÿ븃Ä$[]ÃU‰åWSƒì0ÇEìÇEäÇEèÇEðÇEôEô‰D$ Eð‰D$ÇD$ü[‹E ‰$ÿÜò…À„lÇD$ÇD$ ¡€Ó‰D$Eì‰D$‹Eð‰$è^0ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èÿÿÿÇD$$\‰$èqÿÿé‹]ìEè‰D$ ÇD$Eä‰D$‹Eô‰$èpCÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è®ÿÿÇD$€\‰$è ÿÿéÃÇ0Ò‹Eä‰D$‰$èJPÿÿƒ=0Òt'è9ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸é“‰Ã¸…Ût‰ßü¹ÿÿÿÿò®÷ÑAÿ…Ût;…Ày(èÃ<ÿÿ…ÀtÇD$‰D$‰$è!4ÿÿëè ÿÿÿë‰D$‰$ÿìóëèëÿÿÿ‰Ã}èu ‹Eä‰$èñÓ‰Øë}èu ‹Eä‰$èÙÓ¸ƒÄ0[_]ÃU‰åSƒì4ÇEðÇEèÇEìÇEôÇEøEø‰D$ Eô‰D$ÇD$Ô\‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡€Ó‰D$Eð‰D$‹Eô‰$è~.ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èÿÿÇD$ü\‰$è‘ÿÿ鵋]ðEì‰D$ ÇD$Eè‰D$‹Eø‰$èAÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èÎÿÿÇD$T]‰$è@ÿÿëgÇ0Ò‹Eè‰D$‰$è–Nÿÿƒ=0Òt$è³7ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ë:èjÿÿÿ‰Ã}ìu ‹Eè‰$èpÒ‰Øë}ìu ‹Eè‰$èXÒ¸ƒÄ4[]ÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$¨]‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡€Ó‰D$Eø‰D$‹Eü‰$è-ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$è¼ÿÿÇD$Ô]‰$è.ÿÿëKÇ0Ò‹Eø‰$è§Mÿÿƒ=0Òt$è¥6ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëè\ÿÿÿë¸ÉÃU‰åSƒì4ÇEìÇEðÇEôEô‰D$ Eð‰D$ÇD$4^‹E ‰$ÿÜò…À„æÇD$ÇD$ ¡€Ó‰D$Eì‰D$‹Eð‰$è.,ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èÏÿÿÇD$`^‰$èAÿÿ鎋]ìEà‰D$‹Eô‰$è¶9ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èÿÿÇD$À^‰$èÿÿÿëOÇ0ÒÝEàÝ\$‰$èƒLÿÿƒ=0Òt$èr5ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëè)ÿÿÿ븃Ä4[]ÃU‰åVSƒìPÇEäÇEÜÇEàÇEèÇEìÇEðÇEôEô‰D$Eð‰D$Eì‰D$ Eè‰D$ÇD$_‹E ‰$ÿÜò…À„ŸÇD$ÇD$ ¡€Ó‰D$Eä‰D$‹Eè‰$èÌ*ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èmÿÿÇD$8_‰$èßÿÿéG‹uäEà‰D$ ÇD$E܉D$‹Eì‰$èÞ=ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èÿÿÇD$”_‰$èŽÿÿéö‹]ÜEЉD$‹Eð‰$è8ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èÚÿÿÇD$è_‰$èLÿÿé´ÝEÐÝ]ÀEȉD$‹Eô‰$è¾7ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$è•ÿÿÇD$4`‰$èÿÿërÇ0ÒÝEÈÝ\$ÝEÀÝ\$‰\$‰4$è§Jÿÿƒ=0Òt$èo3ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ë:è&ÿÿÿ‰Ã}àu ‹E܉$è,ΉØë}àu ‹E܉$èθƒÄP[^]ÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$€`‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡€Ó‰D$Eø‰D$‹Eü‰$èÖ(ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èwÿÿÇD$¤`‰$èéÿÿëKÇ0Ò‹Eø‰$èÍIÿÿƒ=0Òt$è`2ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëèÿÿÿë¸ÉÃU‰åVSƒì0ÇEäÇEèÇEìuðEì‰D$ Eè‰D$ÇD$ü`‹E ‰$ÿÜò…À„<ÇD$ÇD$ ¡€Ó‰D$Eä‰D$‹Eè‰$èå'ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è†ÿÿÇD$ a‰$èøÿÿéä‹]äEà‰D$‹Eì‰$èì9ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èDÿÿÇD$xa‰$è¶ÿÿé¢Ç0Ò‰t$‹Eà‰D$‰$èžHÿÿƒ=0Òt$è"1ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ë]èÙÿÿÿ‰Ã¸…ÀtÝÝ$ÿ\ó‰D$‰$èÿÿ‰Ãë'ÇD$¡”Ó‰D$‰4$è¯+ÿÿ‰D$‰$ègÿÿ‰Ã‰Øë¸ƒÄ0[^]ÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$Èa‹E ‰$ÿÜò…À„¤ÇD$ÇD$ ¡€Ó‰D$Eø‰D$‹Eü‰$èf&ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èÿÿÇD$ìa‰$èyÿÿëOÇ0Ò‹Eø‰$è’Gÿÿƒ=0Òt&ÝØèî/ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëÝ$ÿ\óë¸ÉÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$Db‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡€Ó‰D$Eø‰D$‹Eü‰$è„%ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$è%ÿÿÇD$hb‰$è—ÿÿëKÇ0Ò‹Eø‰$èÒFÿÿƒ=0Òt$è/ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëèÅÿÿÿë¸ÉÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$Àb‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡€Ó‰D$Eø‰D$‹Eü‰$è¦$ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èGÿÿÇD$ôb‰$è¹ÿÿëKÇ0Ò‹Eø‰$è Fÿÿƒ=0Òt$è0.ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëèçÿÿÿë¸ÉÃU‰åSìÇEÌÇEÐÇEÔÇEØÇEÜÇEàÇEäÇEèÇEìÇEðÇEôEô‰D$,Eð‰D$(Eì‰D$$Eè‰D$ Eä‰D$Eà‰D$E܉D$E؉D$EÔ‰D$ EЉD$ÇD$\c‹E ‰$ÿÜò…À„yÇD$ÇD$ ¡€Ó‰D$ẺD$‹EЉ$èF#ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èçÿÿÇD$c‰$èYÿÿé!‹]ÌEÀ‰D$‹EÔ‰$èÎ0ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è¥ÿÿÇD$ðc‰$èÿÿéßÝEÀÝxÿÿÿE¸‰D$‹E؉$è†0ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è]ÿÿÇD$Dd‰$èÏÿÿé—ÝE¸ÝpÿÿÿE°‰D$‹E܉$è>0ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èÿÿÇD$˜d‰$è‡ÿÿéOÝE°ÝhÿÿÿE¨‰D$‹Eà‰$èö/ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èÍÿÿÇD$ìd‰$è?ÿÿéÝE¨Ý`ÿÿÿE ‰D$‹Eä‰$è®/ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è…ÿÿÇD$@e‰$è÷ÿÿé¿ÝE ÝXÿÿÿE˜‰D$‹Eè‰$èf/ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è=ÿÿÇD$”e‰$è¯ÿÿéwÝE˜ÝPÿÿÿE‰D$‹Eì‰$è/ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èõ ÿÿÇD$èe‰$ègÿÿé/ÝEÝHÿÿÿEˆ‰D$‹Eð‰$èÖ.ÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è­ ÿÿÇD$ÿÿƒ=0Òt$èŽ&ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëèE ÿÿÿ븃ÄP[^]ÃU‰åSƒì4ÇEðÇEèÇEìÇEôÇEøEø‰D$ Eô‰D$ÇD$øh‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡€Ó‰D$Eð‰D$‹Eô‰$èÿÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è¥ÿÿÇD$i‰$è ÿÿ鵋]ðEì‰D$ ÇD$Eè‰D$‹Eø‰$è/ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èTÿÿÇD$pi‰$èÆ ÿÿëgÇ0Ò‹Eè‰D$‰$èÅ=ÿÿƒ=0Òt$è9%ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ë:èð ÿÿÿ‰Ã}ìu ‹Eè‰$èö¿‰Øë}ìu ‹Eè‰$èÞ¿¸ƒÄ4[]ÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$Ài‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡€Ó‰D$Eø‰D$‹Eü‰$è¡ÿÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èBÿÿÇD$äi‰$è´ÿÿëKÇ0Ò‹Eø‰$èÖ<ÿÿƒ=0Òt$è+$ÿÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëèâ ÿÿÿë¸ÉÃU‰åSƒì4ÇEðÇEèÇEìÇEôÇEøEø‰D$ Eô‰D$ÇD$ôþÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èÓþÿÇD$‡‰$è‡ÔþÿëkÇ0ÒÝEØÝ\$‰\$‰4$èN ÿÿƒ=0Òt$èöïþÿÇD$°Ó¡(ó‹‰$ÿ ó¸ë:è­Öþÿÿ‰Ã}äu ‹Eà‰$賊‰Øë}äu ‹Eà‰$蛊¸ƒÄ@[^]ÃU‰åSƒì4ÇEðÇEèÇEìÇEôÇEøEø‰D$ Eô‰D$ÇD$\‡‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡€Ó‰D$Eð‰D$‹Eô‰$è@åþÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èáÑþÿÇD$€‡‰$èSÓþÿ鵋]ðEì‰D$ ÇD$Eè‰D$‹Eø‰$èRøþÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èÑþÿÇD$؇‰$èÓþÿëgÇ0Ò‹Eè‰D$‰$èó ÿÿƒ=0Òt$èuîþÿÇD$°Ó¡(ó‹‰$ÿ ó¸ë:è,Õþÿÿ‰Ã}ìu ‹Eè‰$è2‰‰Øë}ìu ‹Eè‰$艸ƒÄ4[]ÃU‰åWSƒì0ÇEìÇEäÇEèÇEðÇEôEô‰D$ Eð‰D$ÇD$(ˆ‹E ‰$ÿÜò…À„lÇD$ÇD$ ¡€Ó‰D$Eì‰D$‹Eð‰$è¿ãþÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$è`ÐþÿÇD$Pˆ‰$èÒÑþÿé‹]ìEè‰D$ ÇD$Eä‰D$‹Eô‰$èÑöþÿ…Ày)‰Âƒøÿuºûÿÿÿ‰$èÐþÿÇD$¬ˆ‰$èÑþÿéÃÇ0Ò‹Eä‰D$‰$èŽ ÿÿƒ=0Òt'èñìþÿÇD$°Ó¡(ó‹‰$ÿ ó¸é“‰Ã¸…Ût‰ßü¹ÿÿÿÿò®÷ÑAÿ…Ût;…Ày(è$ðþÿ…ÀtÇD$‰D$‰$è‚çþÿëèdÓþÿÿë‰D$‰$ÿìóëèLÓþÿÿ‰Ã}èu ‹Eä‰$èR‡‰Øë}èu ‹Eä‰$è:‡¸ƒÄ0[_]ÃU‰åƒì(ÇEøÇEüEü‰D$ÇD$‰‹E ‰$ÿÜò…À„ ÇD$ÇD$ ¡€Ó‰D$Eø‰D$‹Eü‰$èüáþÿ…Ày&‰Âƒøÿuºûÿÿÿ‰$èÎþÿÇD$$‰‰$èÐþÿëKÇ0Ò‹Eø‰$èL ÿÿƒ=0Òt$è†ëþÿÇD$°Ó¡(ó‹‰$ÿ ó¸ëè=Òþÿÿë¸ÉÃU‰åƒìEü‰D$ÇD$î‹E ‰$ÿÜòº…Àt%‹Eü‰$è=Òþÿ‰D$¡€Ó‰$è/ÊþÿèçÑþÿÿ‰Â‰ÐÉÃU‰åWVSƒìƒ=˜áuÇœá îÇ á ðǘááèHæþÿ‰Â¹…ÒuÇ$áèÛæþÿë,¹ë=átò‹@9Ðuò…É…K‹B£˜áÇBáÇEðƒ=”ᆿ=˜áát(¡œá‹Uð‹‹‰D$ÇD$ᡘá‰$èƒÉþÿ‰Ç…ÿt¡œá‹Uð‹ƒxt‹@‰Gë ¡œá‹Uð‹<¡ á‹Uð‹4ƒ>„‰»=˜áát‹‹‰D$ÇD$ᡘá‰$èÉþÿ‰Ã…Ût4¡œá‹Uð9…wÿÿÿ¡á‹Uð‰u ‹F‰4$ÿP¸ƒÄ[^]ÃU‰åVSƒì‹E‹p…öt‹^ ‹‰$莂‰4$膂‰Þ…ÛuåƒÄ[^]ÃU‰åWVSƒì ‹u ¿‹E‹X…Ût ‰t$‹‰$è@ƒ…ÀuÿS‰Çë‹[ …Ûuà…ÿu"ÿó…ÀuÇD$t¤¡8ó‹‰$ÿ ó‰øƒÄ [^_]ÃU‰åWVSƒì ‹u ¿‹E‹X…Ût&‰t$‹‰$èÕ‚…Àu ‹E‰$ÿS‰Çë‹[ …ÛuÚƒÿu"ÿó…ÀuÇD$t¤¡8ó‹‰$ÿ ó‰øƒÄ [^_]ÃU‰åSìÔƒ=PÓ…«8ÿÿÿÇD$ÀÇD$‰$è'‚Ç…8ÿÿÿÇ…DÿÿÿޤÇ…Hÿÿÿ Ç…Pÿÿÿ3NÇ…TÿÿÿÂMÇ…XÿÿÿgNÇ…\ÿÿÿÒNÇ…dÿÿÿ"MÇ…|ÿÿÿ7MÇEØðÇD$À‰\$Ç$ÒèN¡ô£”ÒÇPÓ¸ÒÄÔ[]ÃU‰åSƒìè$ÿÿÿ‰Ãèÿÿÿ‹@‰$ÿÌó‰\$‰$ÿÄó…ÀtÇ@ƒÄ[]ÃU‰åƒì‰]ô‰uø‰}ü‹uÇ$è‘€‰Ã…ÀtD‹} ü¹ÿÿÿÿ°ò®‰Ï÷׉<$èr€‰…Àt%‰|$‹U ‰T$‰$è ‹E‰C‹E‰C‹F‰C ‰^‹]ô‹uø‹}ü‰ì]ÃU‰åƒìƒ=`Óu è7ÿÿÿ£`Ó¡`ÓÉÃU‰åWVSƒì ‹} ¾ƒ?„µ‰ðÁà‹8ƒøtƒøt)ë[ÇD$‰òÁâ‹D:‹‰D$‹D:‰$èŸßþÿ‰Ãë9‰ðÁà‹T8‹L8‹D8‹…Òt‰D$‰L$‰$èÓ×þÿëèVËþÿÿ‰Ãë»…Ût-‰\$‰ðÁà‹D8‰D$‹E‰$ÿóÿ ƒ;u ‹C‰$ÿPF‰ðÁàƒ<8…KÿÿÿƒÄ [^_]ÃU‰åWVSƒì<ÇEð‹Eƒ8„“‹EðÁà‹U‹D ‰Eì…À„eÇD$²‰$è,‰Eì…À„JÇEèƒÀ ‰E介M ƒ9tK‰ÞÁæ‹E ‹D‰EЉÇü¹ÿÿÿÿ°ò®÷ÑI‰L$‹Uä‰T$‹MЉ $èó~…À„‡C‰ØÁà‹U ƒ<uµƒ}è„Û‹Mè‹A+EÁø‹U‹‚‰Eà‹EðÁà‹Uì‹M+T ‰UÜ‹Mà‹9ü¹ÿÿÿÿ°ò®÷уÁ ‰MØD ‰$è7~‰Ç…À„†‰ÆÇEÔ‹Eèƒ8u‹P‰UÔëu ‰uè뀃}Ôt_‹M܉L$‹]ðÁã‹U‹D ‰D$‰4$è–~uÜÇswigÇF_ptrfÇF: ƒÆ ‹M؉L$ ‹Uà‹‰D$‹MÔ‰L$‰4$è’Ãþÿ‹E‰| ÿEð‹EðÁà‹Uƒ<…mþÿÿƒÄ<[^_]ÃU‰åSƒìÇD$  îÇD$pÓÇD$`ÒÇ$ÀáèþÿÿÇD$ôÇD$ ÇD$ÇD$ÀáÇ$š¤ÿ ô‰$ÿ¤ó‰ÃÇ$èýöÿÿÇD$`Ò‰$èóüÿÿÇ$ÿpó‰D$ÇD$¡¤‰$èOÆþÿÇ$ ÿpó‰D$ÇD$­¤‰$è.ÆþÿÇ$Pÿpó‰D$ÇD$·¤‰$è ÆþÿÇ$`ÿpó‰D$ÇD$Ť‰$èìÅþÿÇ$pÿpó‰D$ÇD$Ф‰$èËÅþÿÇ$€ÿpó‰D$ÇD$उ$èªÅþÿÇ$@ÿpó‰D$ÇD$$è‰ÅþÿÇ$ÿpó‰D$ÇD$÷¤‰$èhÅþÿÇ$ÿpó‰D$ÇD$¥‰$èGÅþÿÇ$ÿpó‰D$ÇD$¥‰$è&ÅþÿÇ$ÿpó‰D$ÇD$¥‰$èÅþÿÇ$ÿpó‰D$ÇD$*¥‰$èäÄþÿÇ$ÿpó‰D$ÇD$8¥‰$èÃÄþÿÇ$ÿpó‰D$ÇD$D¥‰$è¢ÄþÿÇ$ÿpó‰D$ÇD$S¥‰$èÄþÿÇ$ÿpó‰D$ÇD$W¥‰$è`ÄþÿÇ$ÿpó‰D$ÇD$[¥‰$è?ÄþÿÇ$ÿpó‰D$ÇD$d¥‰$èÄþÿÇ$ÿpó‰D$ÇD$o¥‰$èýÃþÿÇ$ÿpó‰D$ÇD$v¥‰$èÜÃþÿÇ$ÿpó‰D$ÇD$¥‰$è»ÃþÿÇ$ ÿpó‰D$ÇD$Œ¥‰$èšÃþÿÇ$@ÿpó‰D$ÇD$–¥‰$èyÃþÿÇ$€ÿpó‰D$ÇD$¢¥‰$èXÃþÿÇ$ÿpó‰D$ÇD$¯¥‰$è7ÃþÿÇ$ÿpó‰D$ÇD$º¥‰$èÃþÿÇ$Bÿpó‰D$ÇD$Å¥‰$èõÂþÿÇ$ÿpó‰D$ÇD$Ñ¥‰$èÔÂþÿÇ$ÿpó‰D$ÇD$ߥ‰$è³ÂþÿÇ$ÿpó‰D$ÇD$襉$è’ÂþÿÇ$ÿpó‰D$ÇD$ñ¥‰$èqÂþÿÇ$ÿpó‰D$ÇD$ÿ¥‰$èPÂþÿÇ$ÿpó‰D$ÇD$ ¦‰$è/ÂþÿÇ$ÿpó‰D$ÇD$¦‰$èÂþÿƒÄ[]ÃU‰åSƒì‹]ÇD$‹E ‰D$‰$èïH‰Â…ÀuÇD$‰$è©Ë‰Â‰ÐƒÄ[]ÃU‰åSƒì‹]ÇD$0¦‰$èõω…Àu'ÇD$7¦‰$èЉ…Àu‹E ‰D$‰$èúՉ‰ЃÄ[]ÃU‰åSƒì‹]ÇD$0¦‰$è¶å‰Â…Àu.ÇD$7¦‰$è æ‰Â…Àu‹E‰D$‹E ‰D$‰$èt׉‰ЃÄ[]ÃU‰åVSƒì‹]‹u ÇD$0¦‰$èLω…À…øÇD$7¦‰$èÒω…À…Þ‰t$‰$èÌՉ…À…Èǰ×ñƒ=ñtf¡°×‹‰D$‰$èìÎ=@t8…À…‚ÇD$‘¦‰$èmÏ…Àur‰t$‰$èmÕ…Àuf‰$èÑÉ…Àuä‹°×B£°×ƒzušÇD$›¦‰$è‰Î…Àu6ÇD$ ¦‰$èω…Àu%‰t$‰$èՉ…Àuë ‰Âë ‰Âë ‰Â뺉ЃÄ[^]ÃU‰åSƒì‹]ÇD$0¦‰$è'Ή…Àu'ÇD$©¦‰$è±Î‰Â…Àu‹E ‰D$‰$è,ԉ‰ЃÄ[]ÃU‰åSƒì‹]ÇD$0¦‰$èØÍ‰Â…Àu'ÇD$©¦‰$èbΉ…Àu‹E ‰D$‰$è]ԉ‰ЃÄ[]ÃU‰åSƒì‹]Eø‰D$‰$è{ýÿÿ‰Â…À…­ÇD$H¦‰$èp͉…À…“ÇD$´¦‰$èö͉…Àu}Eô‰D$‰$èqӉ…ÀuhÇD$¦‰$è+͉…ÀuRÇD$7¦‰$èµÍ‰Â…Àu<‹Eô‰D$‰$èω…Àu'ÇD$Þ¦‰$èŠÍ‰Â…Àu‹E ‰D$‰$è•։‰ЃÄ[]ÃU‰åSƒì‹]ÇD$H¦‰$è±Ì‰Â…À…ÓÇD$´¦‰$è7͉…À…¹Eø‰D$‰$è®Ò‰Â…À… ÇD$¦‰$èd̉…À…†ÇD$7¦‰$èể…Àup‹Eø‰D$‰$è5Ή…Àu[ÇD$Þ¦‰$è¿Ì‰Â…ÀuEÝE Ý\$ÇD$馉$èR։…Àu(ÇD$ð¦‰$èŒÌ‰Â…ÀuÇD$ó¦‰$è†Ò‰Â‰ÐƒÄ[]ÃU‰åSƒì‹]Eø‰D$‰$è¤ûÿÿ‰Â…À…“ÇD$H¦‰$è™Ë‰Â…Àu}ÇD$‘¦‰$è#̉…Àug‹Eø‰D$‰$èn͉…ÀuRÇD$÷¦‰$èøË‰Â…Àu<‹E ‰D$‰$èՉ…Àu'ÇD$ §‰$èÍˉ…Àu‹E‰D$‰$èØÔ‰Â‰ÐƒÄ[]ÃU‰åSƒì‹]Eø‰D$‰$èæúÿÿ‰Â…À…§ÇD$H¦‰$èÛʉ…À…ÇD$‘¦‰$èaˉ…Àuw‹Eø‰D$‰$è¬Ì‰Â…ÀubÇD$÷¦‰$è6ˉ…ÀuLÝE Ý\$ÇD$馉$èÉԉ…Àu/ÇD$ §‰$èˉ…ÀuÝEÝ\$ÇD$馉$è–ԉ‰ЃÄ[]ÃU‰åSƒì‹]Eø‰D$‰$èúÿÿ‰Â…À…ÆÇD$H¦‰$è ʉ…À…¬ÇD$‘¦‰$èʉ…À…’‹Eø‰D$‰$èÖˉ…Àu}ÇD$"§‰$è`ʉ…Àug‹E ‰D$‰$èkӉ…ÀuRÇD$/§‰$è5ʉ…Àu<‹E‰D$‰$è@Ӊ…Àu'ÇD$<§‰$è ʉ…Àu‹E‰D$‰$èӉ‰ЃÄ[]ÃU‰åSƒì‹]Eø‰D$‰$è#ùÿÿ‰Â…À…âÇD$H¦‰$èɉ…À…ÈÇD$‘¦‰$èžÉ‰Â…À…®‹Eø‰D$‰$èåʉ…À…•ÇD$"§‰$èkɉ…ÀuÝE Ý\$ÇD$馉$èþ҉…ÀubÇD$/§‰$è8ɉ…ÀuLÝEÝ\$ÇD$馉$èË҉…Àu/ÇD$<§‰$èɉ…ÀuÝEÝ\$ÇD$馉$è˜Ò‰Â‰ÐƒÄ[]ÃU‰åƒì(‰]ô‰uø‰}ü‹]‹u Eð‰D$‰$è øÿÿ‰Â…À…ÒÇD$Y¦‰$èȉ…À…¸ÇD$‘¦‰$è†È‰Â…À…ž‹Eð‰D$‰$èÍɉ…À……ÇD$7¦‰$èSȉ…ÀuoEì‰D$‰$èÎ͉…ÀuZÇD$K§‰$èˆÇ‰Â…ÀuDÇD$c§‰$èȉ…Àu.¿‹Eì‰D$‰$èhÈG…ÀtìO‰Â=@u …öt‰>º‰Ð‹]ô‹uø‹}ü‰ì]ÃU‰åƒì‰]ø‰uü‹]‹u Eô‰D$‰$èÿöÿÿ‰Â…À…÷ÇD$Y¦‰$èôƉ…À…ÝÇD$‘¦‰$èzlj…À…ËEô‰D$‰$èÁȉ…À…ªÇD$7¦‰$èGlj…À…Eð‰D$‰$è¾Ì‰Â…Àu{ÇD$K§‰$èxƉ…ÀueÇD$c§‰$èlj…ÀuO‹Eð‰D$‰$è]Ç…Àu3NƒþÿuçÇD$7¦‰$èÓÆ‰Â…Àu ‹E‰D$‰$èN̉…Àu ë‰Â뺉Ћ]ø‹uü‰ì]ÃU‰åƒì‰]ø‰uü‹]‹u Eô‰D$‰$èÑõÿÿ‰Â…À…ÝÇD$Y¦‰$èÆÅ‰Â…À…ÃÇD$‘¦‰$èLƉ…À…©‹Eô‰D$‰$è“lj…À…ÇD$7¦‰$èƉ…ÀuzEð‰D$‰$è”ˉ…ÀueÇD$K§‰$èNʼn…ÀuOÇD$c§‰$èØÅ‰Â…Àu9‹Eð‰D$‰$è3Æ…ÀuNƒþÿuç‹E‰D$‰$è:ˉ…Àu ë‰Â뺉Ћ]ø‹uü‰ì]ÃU‰åSƒì‹]Eø‰D$‹E ‰D$‰$èžýÿÿ‰Â…Àu|ÇD$o§‰$è·Ä…ÀtÇD$§‰$è£Ä‰Â…ÀuRÇD$“§‰$è-ʼn…Àu<‹Eø‰D$‰$èxƉ…Àu'ÇD$§§‰$èʼn…Àu‹E‰D$‰$è}ʉ‰ЃÄ[]ÃU‰åƒì(‰]ô‰uø‰}ü‹]‹u‹}Eð‰D$‹E ‰D$‰$è(ÿÿÿ‰Â…À…ÇD$°§‰$èûɅÀ…úÇD$§§‰$èĉ…À…àÇEìéˆÇD$ŧ‰$è[Ä…À…ÞEì‰D$‰$èÍ…À…΋EìHƒø‡ÈÇD$Ч‰$èÄ…À…ºEè‰D$‰$èØÌ…À…ª9uìt=ÇD$§§‰$èëÃ…À…”‹Eð‰D$‰$èDÄ…À„aÿÿÿº@9uì…'ÇD$Ö§‰$èÃ…À… ‰$è.º‰Â…À…ýÇD$§§‰$è„ɅÀ…ãé‰Âé׉Âéк鯉Â鿉Â鸉Â鱉Â骉Â飉ÂéœÇD$Ч‰$è#Ã…Àu×Eä‰D$‰$èàË…ÀuË‹Eä;Eèu9ÇD$駉$èô‰…ÀuW‰|$‰$è̉…ÀuEÝØ ð§Ýºë4ÇD$§§‰$è»Â…À…yÿÿÿ‹Eð‰D$‰$èÃ…À„iÿÿÿº@‰Ð‹]ô‹uø‹}ü‰ì]ÃU‰åVSƒì ‹]‹uEô‰D$‹E ‰D$‰$è×üÿÿ‰Â…À…‚ÇD$°§‰$èªÁ‰Â…À…hÇD$§§‰$è0‰…À…NÇEðéˆÇD$ŧ‰$è Â…À…úEð‰D$‰$èÃÊ…À…ç‹EðHƒø‡ÞÇD$Ч‰$èÎÁ…À…ÍEì‰D$‰$è‡Ê…À…º9uðt=ÇD$§§‰$èšÁ…À…¡‹Eô‰D$‰$èóÁ…À„aÿÿÿº@9uð…•ÇD$Ö§‰$è½À…À„¾ÇD$Ö§‰$襨‰Â…À…cÇD$§§‰$è+«‰Â…À…I‹Eô‰D$‰$è"lj…À…0ÇD$Ч‰$èøª‰Â…À…‹Eì‰D$‰$èOʉ…À…ýÇD$駉$èŪ‰Â…À…ãÝEÜ ø§Ý\$ÇD$馉$èNʉÂ鿉$跉…À…­ÇD$§§‰$èuÀ‰Â…À…“é˜ÇD$Ч‰$èVÀ…À…aEè‰D$‰$èÉ…À…N‹Eè;EìuIÇD$駉$èÀ‰Â…À…=ÝEÜ ø§Ý\$ÇD$馉$è¨Éº…À„éÇD$§§‰$èÖ¿…À…í‹Eô‰D$‰$è/À…À„Qÿÿÿ‰$諉…À…ÍÇD$§§‰$è•¿‰Â…À…³‹Eô‰D$‰$èŒÅ‰Â…À…šÇD$Ч‰$èb¿‰Â…À…€‹Eì‰D$‰$è¹È‰Â…ÀukÇD$駉$è3¿‰Â…ÀuUÝEÜ ø§Ý\$ÇD$馉$èÀȉ…Àu2ë+‰Âë,‰Âë(ºë!‰Âë‰Âë‰Âë‰Âë‰Âë ‰Âë ‰Âëº‰ÐƒÄ [^]ÃU‰åSƒì‹]Eø‰D$‹E ‰D$‰$è"ùÿÿ‰Â…À…“ÇD$¨‰$èõ½‰Â…Àu}ÇD$§§‰$辉…Àug‹Eø‰D$‰$èÊ¿‰Â…ÀuRÇD$¨‰$èT¾‰Â…Àu<‹E‰D$‰$è_lj…Àu'ÇD$&¨‰$è)¾‰Â…Àu‹E‰D$‰$è4lj‰ЃÄ[]ÃU‰åSƒì‹]Eø‰D$‹E ‰D$‰$è]øÿÿ‰Â…À…§ÇD$¨‰$è0½‰Â…À…ÇD$§§‰$è¦Ó‰Â…Àuw‹Eø‰D$‰$è¡Ä‰Â…ÀubÇD$¨‰$è{Ӊ…ÀuLÝEÝ\$ÇD$馉$èlj…Àu/ÇD$&¨‰$èHӉ…ÀuÝEÝ\$ÇD$馉$èëÆ‰Â‰ÐƒÄ[]ÃU‰åSƒì‹]Eø‰D$‹E ‰D$‰$è„÷ÿÿ‰Â…À…“ÇD$¨‰$èW¼‰Â…Àu}ÇD$§§‰$èἉ…Àug‹Eø‰D$‰$è,¾‰Â…ÀuRÇD$:¨‰$è¶¼‰Â…Àu<‹E‰D$‰$èÁʼn…Àu'ÇD$?¨‰$苼‰Â…Àu‹E‰D$‰$è–ʼn‰ЃÄ[]ÃU‰åSƒì‹]Eø‰D$‹E ‰D$‰$è¿öÿÿ‰Â…À…§ÇD$¨‰$è¢Ñ‰Â…À…ÇD$§§‰$è҉…Àuw‹Eø‰D$‰$èɅÀubÇD$:¨‰$èÝщ…ÀuLÝEÝ\$ÇD$馉$è€Å‰Â…Àu/ÇD$?¨‰$èªÑ‰Â…ÀuÝEÝ\$ÇD$馉$èMʼn‰ЃÄ[]ÃU‰åSƒì‹]Eø‰D$‹E ‰D$‰$èæõÿÿ‰Â…ÀuhÇD$¨‰$轺‰Â…ÀuRÇD$§§‰$èG»‰Â…Àu<‹Eø‰D$‰$è’¼‰Â…Àu'ÇD$H¨‰$軉…Àu‹E‰D$‰$è'ĉ‰ЃÄ[]ÃU‰åSƒì‹]Eø‰D$‹E ‰D$‰$èPõÿÿ‰Â…ÀupÇD$¨‰$è7Љ…ÀuZÇD$§§‰$è¡Ð‰Â…ÀuD‹Eø‰D$‰$èœÁ‰Â…Àu/ÇD$H¨‰$èvЉ…ÀuÝEÝ\$ÇD$馉$èĉ‰ЃÄ[]ÃU‰åSƒì‹]ºƒ} uKÇD$Q¨‰$èš¹‰Â…Àu5ÇD$c¨‰$è$º‰Â…Àu‰$覰‰Â…Àu‹E‰D$‰$è!ɉЃÄ[]ÃU‰åSƒì‹]ºƒ} uSÇD$Q¨‰$èBω…Àu=ÇD$c¨‰$è¬Ï‰Â…Àu'‰$è>°‰Â…ÀuÝEÝ\$ÇD$馉$èAɉЃÄ[]ÃU‰åVSƒì0‹]‹U ÛEØ t¨ÛEØ x¨ÞÁ‹EHPÛ$d$Ù|¨ÜÉÙÊÞÁÜEÛ•ñØÊÞÁÝUðƒú~%öÔÀûl•¶À…Âtû4tÞÁÝ]ðëÝØÝØë ÝØÝØëÝØÝØÛÀ-mPÛ$d$Ý]è‰ØHyCÁøPÛ$d$Ý$èþaÜEèÝ]àK¸…ëQ÷ë‰Ö‰ÐÁøÁû)ØPÛ$d$Ý$èÔaÜmàÝ]؉ðÁø)ØPÛ$d$Ý$è·aÝEØÞÁÙ|¨ÜÉÙÉÜEðÝ]ðÜ}ðØ€¨ƒÄ0[^]ÃU‰åSƒìT‹M ‹]º…É…‹‹E‰D$ Eð‰D$Eì‰D$Eè‰D$Eä‰D$Eà‰D$ E܉D$‰L$‹E‰$èS‰Â…ÀuE…Ût<ÝEðÝ\$‹Eì‰D$‹Eè‰D$ ‹Eä‰D$‹Eà‰D$‹E܉$èIþÿÿØ%„¨Ø ˆ¨Ýº‰ÐƒÄT[]ÃU‰åƒìx‰]ô‰uø‰}ü‹]‹}‹u(ºƒ} …:ÇD$Q¨‰$èÞ¶‰Â…À… ÇD$Œ¨‰$èd·‰Â…À…‰$è⭉…À…ôEì‰D$‰$èɼ‰Â…À…ÛÇEèÇEäÆEãÇEÔÇEÐÇEÌÇEÈÇEÄÇEØÇEÜEè‰D$(Eä‰D$$Eã‰D$ E؉D$EÔ‰D$EЉD$ẺD$EȉD$ EĉD$ÇD$‘¨‹Eì‰$èº_‰Ãƒø~:ƒøu¾Eã‰D$Ç$­¨èŠ_…Àtƒû~"¾Eã‰D$Ç$±¨èm_…Àu ºéû}Ä'wgƒ}È~aƒ}È [ƒ}Ì~Uƒ}ÌOƒ}ÐxIƒ}ÐCƒ}Ôx=ƒ}Ô;7ÝEØÙîÝéßàžw)Ù´¨ÙÉÚéßàžsƒ}äxƒ}ä ƒ}èx ƒ}è;~ëÝØºé…ÿt‹Eĉƒ}t‹EÈ‹U‰ƒ}t‹EÌ‹U‰ƒ}t‹EЋU‰ƒ} t‹EÔ‹U ‰ƒ}$tÝEØ‹E$Ý…öt)ƒû~‹Eä‰ÂÁâ)‹E艀}ã-u ÷؉ëÇ º‰Ð‹]ô‹uø‹}ü‰ì]ÃU‰åWVSƒìL¸ƒ} …õÝEØ5¸¨Ø¼¨Ý]ØÙÀ¨ÝEØÙÉÝéßàžwÙĨÙÉÚéßàžvëÝØ¸é´»¿߸«ªª*÷ïÑú‰øÁø)ÂRÁà‰ù)Á‰È@ÇD$ÇD$ÇD$ÇD$ ÇD$‰D$‰$èûÿÿÝEØÙÉÚéßàžv)ßÑûu›¸«ªª*÷ïÑú‰øÁø)‰UäRÁà)ÇÇD$ÇD$ÇD$ÇD$ ÇD$‰|$‰$è¤úÿÿÜmØÝUØÝ$èM]Ù}î·Eîf f‰EìÙmìÛ]èÙmî‹]èCCÿPÛ$d$ÜmØÝUØÜ ȨÝ$è]Ù}î·Eîf f‰EìÙmìÛ]èÙmî‹uèVÛ$d$Ü5ȨÜmØÝUØÜ ШÝ$èÕ\Ù}î·Eîf f‰EìÙmìÛ]èÙmî‹UèRÛ$d$Ü5ШÜmØØ ¸¨ÝEÝ\$(‹E‰D$$Ý\$‰T$‰t$‰\$‰|$ ‹Eä‰D$‹U ‰T$‹E‰$èƒÄL[^_]ÃU‰åìX‰]ô‰uø‰}ü‹]‹u‹}ÝE0ºƒ} …/}'—À…۞ Шu]ƒû ŸÀ…öžÂ ШuPƒþŸÀ¶Ð‰øÁè ÂuBƒÿŸÀ¶Ð‹E Áè Âu3ƒ} ;1ÙîÝE$ÙÉÝéßàžw'Ù©ÙÉÚéßàžr&ÝØëÝØëÝØëÝØë ÝØëÝØëÝØÝØºé¡}, t‹E, º=‡~¹ÙîÙÉÝáßàÝÙžvIÙèÝéßàžvDÝ$è+[Ø-©Ù½æþÿÿ·…æþÿÿf f‰…äþÿÿÙ­äþÿÿÛàþÿÿÙ­æþÿÿ‹àþÿÿëÝØëÝØÝE$Ý\$$‰L$ º…ÉtQ‰T$‹E ‰D$‰|$‰t$‰\$ ‹E‰D$ÇD$بèþÿÿ‰$èrY}, ti‰ßü¹ÿÿÿÿ°ò®‰È÷Ð\ÿ‹E,Áø‹M,1Á)Á¸‰ˆˆˆ÷éÁú‰ÈÁø)‰ÐÁà)ÐÁà)Á‰L$‰T$ ‹E,ÁøƒàƒÀ+‰D$ÇD$ø¨‰$èYÇD$Q¨‹E‰$èÆ‰Â…ÀuIÇD$Œ¨‹E‰$èôƉ…Àu0‹E‰$胧‰Â…Àu…èþÿÿ‰D$‹E‰$è趉ÂëÝØëÝØ‰Ð‹]ô‹uø‹}ü‰ì]ÃU‰åVSƒì ‹u ‹]¸…öuOÇ$èŒY‰Âû t ‰ØÁà)Ø‚ÇD$ÇD$ð?‰\$RÛ$d$Ý\$‰t$‹E‰$èûÿÿƒÄ [^]ÃU‰åSƒì$‹]Eø‰D$‹E‰D$‰$è¥êÿÿ‰Â…ÀuB‹E‰D$‹E‰D$Eô‰D$ ‹Eø‰D$‹E ‰D$‰$è։…Àuƒ}ô•À¶À…‰ÐƒÄ$[]ÃU‰åSƒì4‹]ÇEôEø‰D$‹E‰D$‰$è.êÿÿ‰Â…ÀuR‹E$‰D$(‹E ‰D$$ÇD$ ‹E‰D$‹E‰D$ÇD$‹E‰D$Eô‰D$ ‹Eø‰D$‹E ‰D$‰$è‰Â‰ÐƒÄ4[]ÃU‰åSƒì4‹]ÇEôEø‰D$‹E‰D$‰$è§éÿÿ‰Â…ÀuS‹E ‰D$(‹E‰D$$ÇD$ ÇD$‹E‰D$ÇD$ ‹E‰D$Eô‰D$ ‹Eø‰D$‹E ‰D$‰$è{‰Â‰ÐƒÄ4[]ÃU‰åSƒì$‹]Eø‰D$‹E‰D$‰$è&éÿÿ‰Â…Àu-‹E‰D$‹E‰D$‹E‰D$ ‹Eø‰D$‹E ‰D$‰$èW‰Â‰ÐƒÄ$[]ÃU‰åSƒì4‹]Eø‰D$‹E‰D$‰$èËèÿÿ‰Â…ÀuQ‹E(‰D$(‹E$‰D$$‹E ‰D$ ‹E‰D$‹E‰D$ÇD$‹E‰D$Eô‰D$ ‹Eø‰D$‹E ‰D$‰$衉‰ЃÄ4[]ÃU‰åSƒì4‹]Eø‰D$‹E‰D$‰$èLèÿÿ‰Â…ÀuR‹E$‰D$(‹E ‰D$$‹E‰D$ ÇD$‹E‰D$ÇD$ ‹E‰D$Eô‰D$ ‹Eø‰D$‹E ‰D$‰$è!‰Â‰ÐƒÄ4[]ÃU‰åSƒìD‹]ÇEôEø‰D$‹E‰D$‰$èÅçÿÿ‰Â…ÀuY‹E(‰D$,‹E$‰D$(ÇD$$‹E ‰D$ ‹E‰D$ÇD$‹E‰D$‹E‰D$Eô‰D$ ‹Eø‰D$‹E ‰D$‰$è ‰Â‰ÐƒÄD[]ÃU‰åSƒìD‹]ÇEôEø‰D$‹E‰D$‰$è7çÿÿ‰Â…ÀuZ‹E$‰D$,‹E ‰D$(ÇD$$ÇD$ ‹E‰D$ÇD$ ‹E‰D$‹E‰D$Eô‰D$ ‹Eø‰D$‹E ‰D$‰$è{‰Â‰ÐƒÄD[]ÃU‰åSƒìD‹]ÇEôEø‰D$‹E‰D$‰$è¨æÿÿ‰Â…ÀuX‹E,‰D$,‹E(‰D$(‹E$‰D$$‹E ‰D$ ‹E‰D$ÇD$‹E‰D$‹E‰D$Eô‰D$ ‹Eø‰D$‹E ‰D$‰$èî‰Â‰ÐƒÄD[]ÃU‰åSƒìD‹]ÇEôEø‰D$‹E‰D$‰$èæÿÿ‰Â…ÀuY‹E(‰D$,‹E$‰D$(‹E ‰D$$ÇD$ ‹E‰D$ÇD$ ‹E‰D$‹E‰D$Eô‰D$ ‹Eø‰D$‹E ‰D$‰$è`‰Â‰ÐƒÄD[]ÃU‰åƒì(‰]ô‰uø‰}ü‹}‹u‹]…Ût6ÇD$ ©‰<$è…À‰Â…À…{ÇD$7¦‰<$èëÀ‰Â…À…aë4ÇD$ ©‰<$è?ª‰Â…À…EÇD$7¦‰<$èŪ‰Â…À…+‹E‰D$‰<$è ¬…Àt8º@…Û„ ‰<$èó•‰Â…À…ù ‹E‰D$‰<$芰‰Â…À…à ƒ}tÇD$©‰<$èJÀ‰Â…À…À ëÇD$§§‰<$è.À‰Â…À…¤ ‰t$‰<$踯…Àuƒ>t ‹€8…z º@…Û„w ‹E‰D$‰<$谉…À…^ ÇD$&©‰<$èN¿‰Â…À…D ÇD$+©‰<$è´¿‰Â…À…* ÇD$2©‰<$èš¿‰Â…À… ÇD$<©‰<$耿‰Â…À…ö ÇD$F©‰<$èf¿‰Â…À…Ü ÇD$7¦‰<$èL¿‰Â…À… ÇD$P©‰<$袪…À„J‰<$è’”‰Â…À…˜ ÇD$P©‰<$è(¯‰Â…À…~ ÇD$\©‰<$èΰ‰Â…À…d ÇD$+©‰<$è䨉…À…J ÇD$a©‰<$èÚ®‰Â…À…0 ÇD$\©‰<$耰‰Â…À… ÇD$2©‰<$è–¨‰Â…À…ü ÇD$‰<$è챉…À…â ÇD$<©‰<$èb¨‰Â…À…È ÇD$‰<$踱‰Â…À…® ÇD$F©‰<$è.¨‰Â…À…” ÇD$‰<$脱‰Â…À…z ÇD$7¦‰<$èú§‰Â…À…` ÇD$l©‰<$è@©…À„J‰<$è0“‰Â…À…6 ÇD$l©‰<$èÆ­‰Â…À… ÇD$\©‰<$èl¯‰Â…À… ÇD$+©‰<$è‚§‰Â…À…è ÇD$a©‰<$èx­‰Â…À…Î ÇD$\©‰<$诉…À…´ ÇD$2©‰<$è4§‰Â…À…š ÇD$‰<$芰‰Â…À…€ ÇD$<©‰<$觉…À…f ÇD$‰<$èV°‰Â…À…L ÇD$F©‰<$è̦‰Â…À…2 ÇD$‰<$è"°‰Â…À… ÇD$7¦‰<$蘦‰Â…À…þ ÇD$x©‰<$èÞ§…À„J‰<$èΑ‰Â…À…Ô ÇD$x©‰<$èd¬‰Â…À…º ÇD$\©‰<$è ®‰Â…À…  ÇD$+©‰<$è ¦‰Â…À…† ÇD$a©‰<$謉…À…l ÇD$\©‰<$è¼­‰Â…À…R ÇD$2©‰<$èÒ¥‰Â…À…8 ÇD$‰<$è(¯‰Â…À… ÇD$\©‰<$èn­‰Â…À… ÇD$<©‰<$è„¥‰Â…À…êÇD$‰<$èÚ®‰Â…À…ÐÇD$F©‰<$èP¥‰Â…À…¶ÇD$‰<$覮‰Â…À…œÇD$„©‰<$茺‰Â…À…‚ÇD$§§‰<$èòº‰Â…À…hÇD$Ч‰<$èØº‰Â…À…NÇD$ž©‰<$辺‰Â…À…4ÇD$ŧ‰<$褺‰Â…À…ÇD$¨©‰<$芺‰Â…À…ÇD$²©‰<$èpº‰Â…À…æÇD$P©‰<$èÆ¥…À„b‰<$趉…À…¼ÇD$§§‰<$è<¤‰Â…À…¢‹E‰D$‰<$è3ª‰Â…À…‰ÇD$Ч‰<$è ¤‰Â…À…oÇD$‰<$è_­‰Â…À…UÇD$\©‰<$襫‰Â…À…;ÇD$ž©‰<$軣‰Â…À…!‹E(‰D$‰<$證…À…ÇD$ŧ‰<$舣‰Â…À…îÇD$‰<$èÞ¬‰Â…À…ÔÇD$¨©‰<$èT£‰Â…À…ºÇD$º©‰<$èJ©‰Â…À… ÇD$²©‰<$è £‰Â…À…†ÇD$P©‰<$詉…À…lÇD$l©‰<$èL¤…À„H‰<$è<Ž‰Â…À…BÇD$§§‰<$袉…À…(‹E‰D$‰<$蹨‰Â…À…ÇD$Ч‰<$袉…À…õÇD$‰<$è嫉…À…ÛÇD$ž©‰<$è[¢‰Â…À…Á‹E$‰D$‰<$貫‰Â…À…¨ÇD$ŧ‰<$è(¢‰Â…À…ŽÇD$‰<$è~«‰Â…À…tÇD$¨©‰<$èô¡‰Â…À…ZÇD$º©‰<$è꧉…À…@ÇD$²©‰<$èÀ¡‰Â…À…&ÇD$l©‰<$è¶§‰Â…À… ÇD$x©‰<$è종À„H‰<$èÜŒ‰Â…À…âÇD$§§‰<$èb¡‰Â…À…È‹E‰D$‰<$èY§‰Â…À…¯ÇD$Ч‰<$è/¡‰Â…À…•ÇD$‰<$è…ª‰Â…À…{ÇD$ž©‰<$èû ‰Â…À…a‹E ‰D$‰<$èRª‰Â…À…HÇD$ŧ‰<$èÈ ‰Â…À….ÇD$‰<$誉…À…ÇD$¨©‰<$è” ‰Â…À…úÇD$º©‰<$芦‰Â…À…àÇD$²©‰<$è` ‰Â…À…ÆÇD$x©‰<$èV¦‰Â…À…¬ÇD$„©‰<$蜵‰Â…À…’ÇD$Å©‰<$趉…À…xÇD$Ø©‰<$è赉…À…^ÇD$²©‰<$èε‰Â…À…DÇD$P©‰<$è$¡…À„‰<$苉…À…ÇD$P©‰<$誥‰Â…À…ÇD$\©‰<$èP§‰Â…À…æÇD$Å©‰<$èfŸ‰Â…À…Ì‹E(ÀºRPß,$d$Ü=ø©Ý\$ÇD$馉<$èߨ‰Â…À…•ÇD$Ø©‰<$蟉…À…{‹E(ºRPß,$d$Ü=ø©Ý\$ÇD$馉<$訉…À…FÇD$²©‰<$èÆž‰Â…À…,ÇD$l©‰<$è  …À„‰<$èü‰‰Â…À…ÇD$P©‰<$è’¤‰Â…À…èÇD$\©‰<$è8¦‰Â…À…ÎÇD$Å©‰<$èNž‰Â…À…´‹E$ÀºRPß,$d$Ü=ø©Ý\$ÇD$馉<$èǧ‰Â…À…}ÇD$Ø©‰<$èý‰Â…À…c‹E$ºRPß,$d$Ü=ø©Ý\$ÇD$馉<$èx§‰Â…À….ÇD$²©‰<$讉…À…ÇD$x©‰<$èôž…À„÷‰<$è䈉…À…êÇD$P©‰<$èz£‰Â…À…ÐÇD$\©‰<$è ¥‰Â…À…¶ÇD$Å©‰<$è6‰Â…À…œ‹E ÀºRPß,$d$Ü=ø©Ý\$ÇD$馉<$详‰Â…ÀuiÇD$Ø©‰<$è霉…ÀuS‹E ºRPß,$d$Ü=ø©Ý\$ÇD$馉<$èh¦‰Â…Àu"ÇD$²©‰<$袜‰Â…Àu ë‹E‰º‰Ð‹]ô‹uø‹}ü‰ì]ÃU‰åƒì8‰]ô‰uø‰}ü‹}‹u‹] ‹‰D$ ‹‰D$‹‰D$ÇD$ÇD$Eð‰D$ ‹E‰D$‹E ‰D$‹E‰$èæðÿÿ‰Â…Àu'‰\$‰t$‰|$ ‹Eð‰D$‹E ‰D$‹E‰$èщ‰Ћ]ô‹uø‹}ü‰ì]ÃU‰åƒìH‰]ô‰uø‰}ü‹}$‹u(‹],‰\$ ‰t$‰|$ÇD$ÇD$Eð‰D$ ‹E‰D$‹E ‰D$‹E‰$èVðÿÿ‰Â…ÀuK‰\$(‰t$$‰|$ ‹E ‰D$‹E‰D$ÇD$‹E‰D$‹E‰D$ ‹Eð‰D$‹E ‰D$‹E‰$èæ‰Â‰Ð‹]ô‹uø‹}ü‰ì]ÃU‰åƒìH‰]ô‰uø‰}ü‹}$‹u(‹],‰\$ ‰t$‰|$ÇD$ÇD$Eð‰D$ ‹E‰D$‹E ‰D$‹E‰$è¢ïÿÿ‰Â…ÀuK‰\$(‰t$$‰|$ ‹E ‰D$‹E‰D$ÇD$‹E‰D$‹E‰D$ ‹Eð‰D$‹E ‰D$‹E‰$è2‰Â‰Ð‹]ô‹uø‹}ü‰ì]ÃU‰åƒìH‰]ô‰uø‰}ü‹} ‹u$‹](‰\$ ‰t$‰|$ÇD$ÇD$Eð‰D$ ‹E‰D$‹E ‰D$‹E‰$èîîÿÿ‰Â…ÀuL‰\$(‰t$$‰|$ ÇD$‹E‰D$ÇD$ ‹E‰D$‹E‰D$ ‹Eð‰D$‹E ‰D$‹E‰$è}‰Â‰Ð‹]ô‹uø‹}ü‰ì]ÃU‰åƒìH‰]ô‰uø‰}ü‹} ‹u$‹](‰\$ ‰t$‰|$ÇD$ÇD$Eð‰D$ ‹E‰D$‹E ‰D$‹E‰$è9îÿÿ‰Â…ÀuL‰\$(‰t$$‰|$ ÇD$‹E‰D$ÇD$ ‹E‰D$‹E‰D$ ‹Eð‰D$‹E ‰D$‹E‰$èȉ‰Ћ]ô‹uø‹}ü‰ì]ÃU‰åƒìH‰]ô‰uø‰}ü‹}(‹u,‹]0‰\$ ‰t$‰|$ÇD$ÇD$Eð‰D$ ‹E‰D$‹E ‰D$‹E‰$è„íÿÿ‰Â…ÀuR‰\$,‰t$(‰|$$‹E$‰D$ ‹E ‰D$ÇD$‹E‰D$‹E‰D$‹E‰D$ ‹Eð‰D$‹E ‰D$‹E‰$è„ ‰Â‰Ð‹]ô‹uø‹}ü‰ì]ÃU‰åƒìH‰]ô‰uø‰}ü‹}(‹u,‹]0‰\$ ‰t$‰|$ÇD$ÇD$Eð‰D$ ‹E‰D$‹E ‰D$‹E‰$èÉìÿÿ‰Â…ÀuR‰\$,‰t$(‰|$$‹E$‰D$ ‹E ‰D$ÇD$‹E‰D$‹E‰D$‹E‰D$ ‹Eð‰D$‹E ‰D$‹E‰$èÉ ‰Â‰Ð‹]ô‹uø‹}ü‰ì]ÃU‰åƒìH‰]ô‰uø‰}ü‹}$‹u(‹],‰\$ ‰t$‰|$ÇD$ÇD$Eð‰D$ ‹E‰D$‹E ‰D$‹E‰$èìÿÿ‰Â…ÀuS‰\$,‰t$(‰|$$ÇD$ ‹E ‰D$ÇD$ ‹E‰D$‹E‰D$‹E‰D$ ‹Eð‰D$‹E ‰D$‹E‰$è ‰Â‰Ð‹]ô‹uø‹}ü‰ì]ÃU‰åƒìH‰]ô‰uø‰}ü‹}$‹u(‹],‰\$ ‰t$‰|$ÇD$ÇD$Eð‰D$ ‹E‰D$‹E ‰D$‹E‰$èRëÿÿ‰Â…ÀuS‰\$,‰t$(‰|$$ÇD$ ‹E ‰D$ÇD$ ‹E‰D$‹E‰D$‹E‰D$ ‹Eð‰D$‹E ‰D$‹E‰$èQ‰Â‰Ð‹]ô‹uø‹}ü‰ì]ÃU‰åWVSƒì\‹]‹u‹}ºƒ} …žÇEäÇEàÇEÜÇEÔÇEÐÇEÌÇD$°§‰$è0•‰Â…À…ZÇD$§§‰$è¶•‰Â…À…@é‘ÇD$ŧ‰$è—•…À…¸E´‰D$‰$èPž…À…¥‹E´Hƒø‡œÇD$ž©‰$è[•…À…‹‹E´D…ȉD$‰$èž…Àux‹E´ƒ|…ØurÇD…ØÇD$§§‰$è•…Àu]‰t$‰$èz•…À„[ÿÿÿº@ƒ}Ü„‡ƒ}àu8‹ẺEÄÇEÀÇE¼ë5‰Âëg‰Âëcºë\‰ÂëX‰ÂëTºëM‰ÂëIÇE¼‹EЉEÀ‹ẺEă}äu‹EÔ‰E¼…ÿt‹E¼‰ƒ}t‹EÀ‹U‰ƒ}t‹EÄ‹U‰º‰ÐƒÄ\[^_]ÃU‰åWVSìÌ‹}‹M ‹]¾…É…Hƒû •Àƒû•¶À¾…Â…,ƒû ”Àƒ} •¶À…Ât¾ƒ} … ƒû ”Àƒ}$”¶À¾…Â…ìE¤‰D$E ‰D$Eœ‰D$ ‹E‰D$‰L$‰<$è‘ýÿÿ‰Æ…À…º‹U,9U u‹E09E¤t ¾é ÇEäÇEàÇEÜÇEÔÇEÐÇEÌÇD$°§‰<$è¾’‰Æ…À…\ÇD$§§‰<$èD“‰Æ…À…BéÄÇD$ŧ‰<$è%“…À…óE˜‰D$‰<$èÞ›…À…à‹E˜Hƒø‡×ÇD$¨©‰<$èé’…Àu;E”‰D$‰<$èf˜…À…³‹E”‰D$Ç$ªè …Àu‹E˜ÇD…Èÿÿÿÿë =@…ˆ‹E˜ƒ|…Ø…~ÇD…ØÇD$§§‰<$èy’…À…e‹U‰T$‰<$èÒ’…À„%ÿÿÿ¾@ƒ}Ü„Sƒ}àu‹ẺEˆÇE„ë ‹UЉUˆ‹ẺE„ÇE€ƒ}ät‹U„‰U€‹Eˆ‰E„‹UÔ‰UˆÇD$ ª‰<$è[‘‰Æ…À…ùÇD$§§‰<$èᑉƅÀ…ß‹E‰D$‰<$è(“‰Æ…À…ƃ}„›ÇD$ª‰<$褑…Àt¾@‹Uƒ:‡—ëtE‰D$‰<$èNš…Àuƒ}uÇE‹U‹;EtJÇD$§§‰<$èS‘…À…C‹E‰D$‰<$謑…À…0ÇD$ª‰<$è$‘…Àt“‰Æé!ÇD$ ª‰<$è ‘‰Æ…À…ƒ}(”Àƒ},” Шuƒ}0u ¾éãƒûuFEŒ‰D$‹E(¯E,¯E0‰D$‹U$‰T$‹E ‰D$ ‹U‰T$E‰D$‰<$è, ‰Æ…À…šë=EŒ‰D$‹E(¯E,¯E0‰D$‹E ‰D$ ‹U‰T$E‰D$‰<$èm ‰Æ…À…[ƒ}t‹E‹U‰‹E„ Eˆx ƒ}€‰òƒ}ˆx¸‹U(‰•tÿÿÿÇ…pÿÿÿë‹E(HÇ…tÿÿÿÿÿÿÿÇ…pÿÿÿÿÿÿÿƒ}„xÇ…lÿÿÿ‹U,‰•hÿÿÿÇ…dÿÿÿë‹U,J‰•lÿÿÿÇ…hÿÿÿÿÿÿÿÇ…dÿÿÿÿÿÿÿƒ}€xÇ…`ÿÿÿ‹U0‰•\ÿÿÿÇ…Xÿÿÿë‹U0J‰•`ÿÿÿÇ…\ÿÿÿÿÿÿÿÇ…Xÿÿÿÿÿÿÿ‹u‰…|ÿÿÿ‹•tÿÿÿ9Є‹…lÿÿÿ‰…xÿÿÿ‹•hÿÿÿ9Є勅|ÿÿÿ¯E,‰…Lÿÿÿ‹½`ÿÿÿ;½\ÿÿÿ„¥‹…Lÿÿÿ…xÿÿÿ¯E0‰…TÿÿÿU¨‰•Pÿÿÿ‹…Tÿÿÿø¯E ‹U9Þs[ƒ} u‹‰E¨‹‰‹E¨‰ëE‹E ‰D$‰t$‹•Pÿÿÿ‰$è®6‹E ‰D$‰\$‰4$è›6‹U ‰T$‹…Pÿÿÿ‰D$‰$è‚6u ½Xÿÿÿ;½\ÿÿÿ…zÿÿÿ‹•dÿÿÿ•xÿÿÿ‹…hÿÿÿ9…xÿÿÿ…+ÿÿÿ‹•pÿÿÿ•|ÿÿÿ‹…tÿÿÿ9…|ÿÿÿ…ãþÿÿ‹E(¯E,¯E0¾@;EŒu4ë-‰Æë.‰Æë*¾ë#‰Æë‰Æë¾ë‰Æë‰Æë ¾@뾉ðÄÌ[^_]ÃU‰åWVS쌋}‹M,‹]0‹u4ÇEœƒ} …7 ƒ} •Àƒ} •¶ÀÇEœ…Â… ƒ} ”Àƒ}$•¶À…ÂtÇEœƒ}$…ñƒ} ”Àƒ}(”¶ÀÇEœ…Â…Ñ…Éu ÇE´ë‰M´…Ûu ÇE°ë‰]°…öu ÇE¬ë‰u¬ƒ}¬”À¶À‰E¼ƒ}°”À¶À‰EÀƒ}´”À¶À‰EÄÇD$°§‰<$èUŒ‰Eœ…À…_ÇD$§§‰<$èÚŒ‰Eœ…À…Dé’ÇD$ŧ‰<$躌…À…ùE¤‰D$‰<$ès•…À…ç‹E¤Hƒø‡ßÇD$ž©‰<$è~Œ…À…ЋE¤‹D…¨‰D$‰<$èÓ•…À…º‹E¤ÇD…¸ÇD$§§‰<$è@Œ…À…œ‹E‰D$‰<$虌…À„Wÿÿÿƒ}¼t ƒ}Àtƒ}Äu ÇEœ@éxÇD$ ª‰<$èc¡‰Eœ…À…]ÇD$§§‰<$èÈ¡‰Eœ…À…B‰<$èU‚‰Eœ…À…/‹U‰T$‰<$è …Àt-‰<$èÿv‰Eœ…À… ‹E‰D$‰<$è•‘‰Eœ…À…ïÇD$ª‰<$èZ¡‰Eœ…À…Ôƒ}„í‹Uƒ:uÇE ‰D$‰<$è”…Àuƒ} uÇE ‹U‹;E „çÇD$§§‰<$è ‹…À…j‹E‰D$‰<$èb‹…Àtf‰<$èFv‰Eœ…À…P‹U‰T$‰<$è܉Eœ…À…6ÇD$ª‰<$豊‰Eœ…À…‹U‹‰D$‰<$蔉Eœ…À…ÿëVÇD$ª‰<$èxŠ…À„)ÿÿÿ‰EœéÝE ‰D$‰<$è)“…Àt#ÇE ¸‰D$‰<$è­“‰Eœ…À…§ÇD$ ª‰<$è"ЉEœ…À…Œƒ} …‡ÇD$,¸ƒ}´~‹E´‰D$(ƒ}´ ¸ƒ}°~‹E°‰D$$‹E¬‰D$ ÇD$%ª¯E°¯E´‰D$‹E(‰D$‹U$‰T$‹E‰D$ ‹U‹‰D$‹E‰D$‰<$賚‰Eœ…À…ýë~ÇD$(¸ƒ}´~‹E´‰D$$ƒ}´ ¸ƒ}°~‹E°‰D$ ‹E¬‰D$ÇD$%ª¯E°¯E´‰D$‹U$‰T$‹E‰D$ ‹U‹‰D$‹E‰D$‰<$è3›‰Eœ…À…}ÇD$3ª‰<$èhž‰Eœ…À…bÇD$7¦‰<$èÍž‰Eœ…À…G‰<$èZ‰Eœ…À…4‹U‰T$‰<$芅ÀtH‰<$èt‰Eœ…À…‹E‰D$‰<$蚎‰Eœ…À…ôÇD$\©‰<$è?‰Eœ…À…ÙÇD$Cª‰<$èDž‰Eœ…À…¾ƒ} uDƒ}(t‹E$Áà‰D$ÇD$QªEȉ$èð/ë<‹E$Áà‰D$ÇD$gªEȉ$èÑ/ë‹E$Áà‰D$ÇD$ªEȉ$è²/EȉD$‰<$èã‰Eœ…À…=ÇD$—ª‰<$舉Eœ…À…"ÇD$œª‰<$è‰Eœ…À…¶Eƒø`„ºƒø`wƒø@t:ƒøPtpéŒ=€„I=€wƒøp„él=„¶é\ÇD$­ª‰<$èA‰Eœ…À…›ÇD$\©‰<$èæŽ‰Eœ…À…€éWÇD$²ª‰<$è‰Eœ…À…`ÇD$\©‰<$諎‰Eœ…À…EéÇD$¼ª‰<$èËŒ‰Eœ…À…%ÇD$\©‰<$èpމEœ…À… éáÇD$ê‰<$茉Eœ…À…êÇD$\©‰<$è5މEœ…À…Ïé¦ÇD$ͪ‰<$èUŒ‰Eœ…À…¯ÇD$\©‰<$èú‰Eœ…À…”ënÇD$Úª‰<$茉Eœ…À…wÇD$\©‰<$è‰Eœ…À…\ë6ÇD$䪉<$è勉Eœ…À…?ÇD$檉<$芉Eœ…À…$÷E„¹÷EtSÇD$몉<$èy›‰Eœ…À…óÇD$«‰<$è~‹‰Eœ…À…ØÇD$\©‰<$è#‰Eœ…À…½ë]ÇEœ÷E„§ÇD$몉<$蛉Eœ…À…ŒÇD$«‰<$苉Eœ…ÀuuÇD$\©‰<$èÀŒ‰Eœ…Àu^ÇD$«‰<$èÉš‰Eœ…ÀuGÇD$%ª‰<$èÒŠ‰Eœ…Àu0ë'‰Eœë)‰Eœë$ÇEœë‰Eœë‰Eœë‰Eœë ‰EœëÇEœ‹EœÄŒ[^_]ÃU‰åƒì‰]ø‰uü‹]‹uÇD$&©‰$軃‰Â…À…îÇD$7¦‰$èA„‰Â…À…Ô‹E ‰D$‰$舅‰Â…À…»ÇD$'«‰$脉…À…¡Eô‰D$‰$è…‰‰Â…À…ˆº@ƒ}ôt}‹Eô¾‰$è²,ƒøTt+‹Eô¾‰$èŸ,ƒøRt‹Eô¾‰$èŒ,ºƒøGu?…öt6‹Eô¾‰$èp,ƒøTuÇë‹Eô¾‰$èU,ƒøR•À¶ÀÀ‰º‰Ð‹]ø‹uü‰ì]ÃU‰åSƒì‹]ÇD$&©‰$肉…À…¬ÇD$7¦‰$è#ƒ‰Â…À…’‹E ‰D$‰$èj„‰Â…Àu}ÇD$2©‰$èô‚‰Â…Àug‹E‰D$‰$èÿ‹‰Â…ÀuRÇD$<©‰$èÉ‚‰Â…Àu<‹E‰D$‰$èÔ‹‰Â…Àu'ÇD$F©‰$èž‚‰Â…Àu‹E‰D$‰$è©‹‰Â‰ÐƒÄ[]ÃU‰åSƒì‹]ÇD$&©‰$èʼn…À…¬ÇD$7¦‰$èK‚‰Â…À…’‹E ‰D$‰$è’ƒ‰Â…Àu}ÇD$,«‰$肉…Àug‹E‰D$‰$è'‹‰Â…ÀuRÇD$6«‰$èñ‰Â…Àu<‹E‰D$‰$èüŠ‰Â…Àu'ÇD$@«‰$èÆ‰Â…Àu‹E‰D$‰$èÑŠ‰Â‰ÐƒÄ[]ÃU‰åƒì(‰]ô‰uø‰}ü‹]‹u‹}ºƒ} …Eð‰D$‰t$‰$èðüÿÿ‰Â…À…ùºƒ}ð‡êƒ}ð…üÇD$J«‰$蚀‰Â…À…ÆÇD$²©‰$è ‰Â…À…¬‰t$‰$èj‚‰Â…À…–ÇD$a«‰$èð€‰Â…À…|‰|$‰$èú‰‰Â…À…fÇD$n«‰$è €‰Â…À…LÇD$²©‰$覀‰Â…À…2‰t$‰$èð‰Â…À…ÇD$«‰$èv€‰Â…À…‹E‰D$‰$è}‰‰Â…À…ééßÇD$J«‰$螉…À…ÊÇD$²©‰$è$€‰Â…À…°‰t$‰$èn‰Â…À…šÇD$–«‰$èô‰Â…À…€‰|$‰$èþˆ‰Â…ÀunÇD$n«‰$è(‰Â…ÀuXÇD$²©‰$貉…ÀuB‰t$‰$è‰Â…Àu0ÇD$œ«‰$芉…Àu‹E‰D$‰$蕈‰Â…Àuº‰Ð‹]ô‹uø‹}ü‰ì]ÃU‰åƒì(‰]ô‰uø‰}ü‹]‹u‹}ºƒ} …õEð‰D$‰t$‰$è¤úÿÿ‰Â…À…غƒ}ð‡Éƒ}ð…ÓÇD$J«‰$èN~‰Â…À…¥ÇD$²©‰$èÔ~‰Â…À…‹‰t$‰$耉…À…uÙîÝÇD$¬«‰$è ~…ÀuI‰|$‰$è°‡…À„DÇD$a«‰$èx~…À…,‰|$‰$脇…À„ÙîÝéÇD$a«‰$èC~…Àu&‰|$‰$èS‡…À„çÇÇGéÕÇD$n«‰$èi}‰Â…À…ÀÇD$²©‰$èï}‰Â…À…¦‰t$‰$è9‰Â…À…ÇD$¬«‰$è¿}…ÀuR‰|$‰$èφ…À„cÇD$a«‰$è—}…À…K‰|$‰$裆…À„7ÇÇGé%ÇD$a«‰$èY}…À… ‰|$‰$èe†…À„ùÇÇGéçÇD$J«‰$è{|‰Â…À…ÒÇD$²©‰$è}‰Â…À…¸‰t$‰$èK~‰Â…À…¢ÙîÝÇD$ë‰$èÍ|…Àu‰|$‰$èÝ……ÀtuÙîÝëoÇD$n«‰$è|‰Â…Àu^ÇD$²©‰$è|‰Â…ÀuH‰t$‰$èÛ}‰Â…Àu6ÇD$ë‰$èe|…Àu‰|$‰$èu……Àt ÇÇGº‰Ð‹]ô‹uø‹}ü‰ì]ÃU‰åVSƒì ‹]‹uºƒ} …–Eô‰D$‰t$‰$èƒ÷ÿÿ‰Â…À…yºƒ}ô‡jƒ}ô…ºÇD$J«‰$è=‘‰Â…À…FÇD$²©‰$裑‰Â…À…,‰t$‰$肉…À…ÇD$a«‰$ès‘‰Â…À…üÝEÝ\$ÇD$馉$腉…À…ÛÇD$«‰$èH{…Àu!ÝEÝ\$ÇD$馉$èÝ„‰Â…À…¦ÇD$n«‰$胉…À…ŒÇD$²©‰$èé‰Â…À…r‰t$‰$èã‰Â…À…\ÇD$Ó«‰$蹉…À…BÝEÝ\$ÇD$馉$èX„‰Â…À…!ÇD$«‰$è~‰Â…À…ÝEÝ\$ÇD$馉$脉…À…æÇD$櫉$èC‰Â…À…ÌÝEÝ\$ÇD$馉$è⃉…À…«é¡ÇD$J«‰$胉…À…ŒÇD$²©‰$èé‰Â…À…r‰t$‰$è〉…À…\ÇD$–«‰$蹉…À…BÝEÝ\$ÇD$馉$èXƒ‰Â…À…!ÇD$œ«‰$èŽy…Àu!ÝEÝ\$ÇD$馉$è#ƒ‰Â…À…ìÇD$n«‰$èÉŽ‰Â…À…ÒÇD$²©‰$è/‰Â…À…¸‰t$‰$è)€‰Â…À…¢ÇD$ù«‰$èÿŽ‰Â…À…ˆÝEÝ\$ÇD$馉$èž‚‰Â…ÀukÇD$œ«‰$èÈŽ‰Â…ÀuUÝEÝ\$ÇD$馉$èk‚‰Â…Àu8ÇD$¬‰$蕎‰Â…Àu"ÝEÝ\$ÇD$馉$è8‚‰Â…Àuº‰ÐƒÄ [^]ÃU‰åVSƒì ‹]‹uºƒ} …<Eô‰D$‰t$‰$èÇóÿÿ‰Â…À…ºƒ}ô‡ƒ}ô…ÇD$J«‰$è‰Â…À…ìÇD$²©‰$èç‰Â…À…Ò‰t$‰$èá~‰Â…À…¼ÇD$¬«‰$跉…À…¢ÝEÝ\$ÇD$馉$èV‰Â…À…ÇD$n«‰$èüŒ‰Â…À…gÇD$²©‰$èb‰Â…À…M‰t$‰$è\~‰Â…À…7ÇD$¬«‰$è2‰Â…À…ÝEÝ\$ÇD$馉$èÑ€‰Â…À…üéòÇD$J«‰$èrŒ‰Â…À…ÝÇD$²©‰$èØŒ‰Â…À…Ét$‰$èÒ}‰Â…À…­ÇD$ë‰$訌‰Â…À…“ÝEÝ\$ÇD$馉$èG€‰Â…ÀuvÇD$n«‰$èñ‹‰Â…Àu`ÇD$²©‰$è[Œ‰Â…ÀuJ‰t$‰$èY}‰Â…Àu8ÇD$ë‰$è3Œ‰Â…Àu"ÝEÝ\$ÇD$馉$è։…Àuº‰ÐƒÄ [^]ÃU‰åSƒì‹]ÇD$ ÇD$pÇD$‰$è¨ö‰Â…Àun‹ÙèÝ‹ÙîÝP‹ÝP‹ÝP‹ÝP ÙÉ‹ÝP(ÙÉ‹ÝP0‹ÝP8‹ÝP@‹ÝPHÙÉ‹ÝXP‹ÝXX‹Ç@`‹Ç@d‹Ç@h‹Ç@lº‰ÐƒÄ[]ÃU‰åWVSƒì‹}‰}踅ÿ„‚ÇE侃dv8‹G`¶^Á㋉EðÇD$Eð‰$èö Eä‹G`ÇF9wdwÈ‹G`‰EìGd‰D$Eì‰$èîõ EäÇG`ÇD$Eè‰$èÑõ EäƒÄ[^_]ÃU‰åWVS윋]‹u Ç…tÿÿÿ…ö”À…Û” Шuƒ}v ºé’ÝEØÈÝhÿÿÿÝE ØÈÜ…hÿÿÿÝhÿÿÿÝE(ØÈÜ…hÿÿÿÝhÿÿÿÙîÝ…hÿÿÿÙÉÚéßàžr ºéJÇEˆÇE„‰÷ü¹ÿÿÿÿ°ò®÷ÑÇD$ ‰L$ÇD$E„‰$èÇô‰Â…À…‹E„‰EˆÇEŒƒ}tAÇE€‹}ü¹ÿÿÿÿ°ò®÷ÑÇD$ ‰L$ÇD$E€‰$èuô‰…tÿÿÿ‹E€‰EŒƒ½tÿÿÿt-‹Eˆ‰E„ÇD$E„‰$è‡ôÇEˆ‹•tÿÿÿ Âé{‹C`‰…|ÿÿÿ‹Cd@‰D$ ÇD$XCd‰D$…|ÿÿÿ‰$è¥ò‰…tÿÿÿ‹…|ÿÿÿ‰C`ƒ½tÿÿÿtQ‹Eˆ‰E„‹EŒ‰…xÿÿÿÇD$E„‰$è ô‰ÃÇD$…xÿÿÿ‰$èóóÇEˆÇEŒ‰Ú Âéä‰t$‹Eˆ‰$è=ƒ}t‹E‰D$‹EŒ‰$è%Ý…hÿÿÿÙúÝàßàžztÝØëÝØÝ…hÿÿÿÝ$è`Ýhÿÿÿ‹E‰EØÝEܵhÿÿÿÝ]ÝE ܵhÿÿÿÝ]˜ÝE(ܵhÿÿÿÝ] ÝE0Ý]¨ÝE8Ý]°ÝE@Ý]¸ÝEHÝ]ÀÝEPÝ]ÈÇEÐÇEÔ‹Cd€PÁâS`ƒêXEˆÇD$X‰D$‰$èûÇChÇClº‰ÐÄœ[^_]ÃU‰å쨉]ô‰uø‰}ü‹]‹u‹}ÇD$&©‰$è q‰Â…À…„ÇD$7¦‰$è¦q‰Â…À…j‰t$‰$èðr‰Â…À…TÇD$¬‰$èvq‰Â…À…:Eì‰D$‰$èív‰Â…À…!Eè‰D$‰t$‰$èÃìÿÿ‰Â…À…Eà‰D$E؉D$ EЉD$‰t$‰$è¾íÿÿ‰Â…À…ÙEȉD$EÀ‰D$ E¸‰D$‰t$‰$èkîÿÿ‰Â…À…®ÙîÝU°Ý]¨…ÿtKE°‰D$E¨‰D$ ‰t$‹E ‰D$‰$è ïÿÿ‰Â…Àu{…ÿy E¨‰D$ ‰t$‹E ‰D$‰$è4ñÿÿ‰Â…ÀuWÝE°Ý\$HÝE¨Ý\$@ÝEÈÝ\$8ÝEÀÝ\$0ÝE¸Ý\$(ÝEàÝ\$ ÝEØÝ\$ÝEÐÝ\$‹Eè‰D$ ‹Eì‰D$‰t$‹E‰$ènûÿÿ‰Â‰Ð‹]ô‹uø‹}ü‰ì]ÃU‰åWVS쌸ƒ}„Xë ¸@éL‹Eƒxl…:ÇE„䪋xdOˆ¾9þÏ¿GÁà‰E€Uˆ‰•|ÿÿÿ‹M‹Q`¶FÁàƒ|t‹M„‰L$‹D‰$èçð…À”À¶Àë‹E„‰D$Ç$äªèÊð…À”À¶À…À„Ž‹U‹B`¶^Áã‹ ‰M„E€ÇD$X‰D$‹…|ÿÿÿ‰$è(‹U‹B`‹U€ÂÇD$X‰D$‰$è‹MY`ÇD$X‹…|ÿÿÿ‰D$‰$èæƒ}„”À…ÿŸÂ¶À…Ât¸@ë,F9þŽÿÿÿéÈþÿÿ9þÀþÿÿO‰áþÿÿ‹UÇBl¸ÄŒ[^_]ÃU‰åWVSì ÝEºƒ}„ñºƒ} …æÇ…Dÿÿÿ‹EƒxdvZ‹M‹Q`‹Dÿÿÿ‰A ÅÙÀÜL@ÜD8ÝDHÝéßàžzt‹EÇ@hÝ\HëÝØÿ…Dÿÿÿ‹•Dÿÿÿ‹M9QdwªÝØëÝØ‹Eƒxh…ëÙèÝÙîÝPÝPÝPÝP ÙÉÝP(ÙÉÝP0ÝP8ÝP@ÝPHÙÉÝXPÝXXƒxlu‰$èžýÿÿ‰Â…À…'Ç…Dÿÿÿ‹Uƒzd†…‹J`‰@ÿÿÿ‹•Dÿÿÿ’BÁà‹@ÿÿÿÝDHƒ|Pu*ÙÀÜL‹UÜBÝZÙÀÜLÜB8ÝZ8ÜLÜBXÝZXéçÜ ¬Ý•ÿÿÿÝ$èù‹M‹Q`‹Dÿÿÿ‰AÁàÙÀÜLÝ8ÿÿÿÙÀÜLÝ0ÿÿÿÜLÝ(ÿÿÿÝ…ÿÿÿÝ$è¤Ý…8ÿÿÿØÈÝ…0ÿÿÿØÈÝ…(ÿÿÿØÈÝ…8ÿÿÿÜ0ÿÿÿÝÿÿÿÝ…8ÿÿÿÜ(ÿÿÿÝ…8ÿÿÿØÍÝ ÿÿÿÝ…0ÿÿÿÜ(ÿÿÿÝ…0ÿÿÿØÎÝÿÿÿÝ…(ÿÿÿÞÎÙÃØÃØÀÙèÞáÝ]˜Ý…ÿÿÿØæØÀÝ] Ý…ÿÿÿØÂØÀÝ]¨Ý…ÿÿÿÞÆÙÍØÀÝ]°ÙÃÞÂÙÉØÀÙèÜáÙÉÝ]¸Ý… ÿÿÿØíØÀÝ]ÀÙÉÜ¥ÿÿÿØÀÝ]ÈÙËÜ… ÿÿÿØÀÝ]ÐÞÁØÀÞéÝ]ØÇ…ÿÿÿÙ…ÿÿÿ4@Ý”ÅHÿÿÿ¹‰ÇÝ„ÅHÿÿÿ‹ÝDŘ‹EÜ ÐÞÁAƒù~èÝœýHÿÿÿCƒû~Ãÿ…ÿÿÿƒ½ÿÿÿ~¦ÝØÇ…ÿÿÿ»‹µÿÿÿÁæ‹•ÿÿÿ RÝ„ÅHÿÿÿ‹EÝÐCƒû~çÿ…ÿÿÿƒ½ÿÿÿ~Á‹M‹Q`‹Dÿÿÿ‰AÁà‹MÝAÜD ÝYÝA8ÜD(ÝY8ÝAXÜD0ÝYXÿ…Dÿÿÿ‹…Dÿÿÿ9Ad‡„ýÿÿ‹UÇBhƒ}0t ÝE‹MÜ ÝE ÜIÞÁÝE(ÜIÞÁÜA‹E0݃}4t!ÝE‹UÜJ ÝE ÜJ(ÞÁÝE(ÜJ0ÞÁÜB8‹M4݃}8t!ÝE‹EÜH@ÝE ÜHHÞÁÝE(ÜHPÞÁÜ@X‹U8ݺëÝØëÝØ‰ÐÄ [^_]ÃU‰åWVSƒìl‹]‹E ‹u0‹}4º…À…·ÇD$0ÇD$,ÇD$(ÙîÝT$ ÝT$Ý\$ÝEÝ\$‰D$‰$èƒûÿÿ‰Â…ÀuxÝEÜcÝ]ÈÝE Üc8Ý]ÐÝE(ÜcXÝ]Ø…ötÝÜMÈÝC ÜMÐÞÁÝC@ÜMØÞÁÝ…ÿtÝCÜMÈÝC(ÜMÐÞÁÝCHÜMØÞÁ݃}8tÝCÜMÈÝC0ÜMÐÞÁÝCPÜMØÞÁ‹E8ݺ‰ÐƒÄl[^_]ÃU‰åƒì8‰]ô‰uø‰}ü‹]‹u º…ö„ÈEð‰D$‰$èÀ˜ÿÿ‰Â…À…¯ÇD$i¦‰$èµh‰Â…À…•ÇD$‘¦‰$è;i‰Â…À…{‹Eð‰D$‰$è‚j‰Â…À…bÇD$7¦‰$èi‰Â…À…HEì‰D$‰$èn‰Â…À…/‰4$èËòÿÿ‰Â…À…ÇEàÇD$(¬‰$èh‰Ç…À…ËÇD$@¬‰$è¢h…ÀtÇD$7¦‰$èŽh‰Ç…À…‹Eà‰D$‰$èef‰Ç=@„Ž…Àu}Eè‰D$‰$èåm‰Ç…Àuh‹Eè‰D$‹Eì‰$èé…ÀuRÇD$²©‰$è)h‰Ç…Àua‰Â…À….Eà‰D$‰$èEj‰Â…À…ÇD$«‰$è a‰Â…À…ûEЉD$‰$èj‰Â…À…âE¨‰$èËêÿÿ‰Â…À…ÍÇD$ ÇD$@ÇD$‰4$èsáÇEœÇD$l¬‰$èü_‰Ç…À…ÌÇD$c§‰$è‚`…ÀtÇD$7¦‰$èn`‰Ç…À…ž‹Uœ‰T$‰$èE^‰Ç=@„…Àu~E¤‰D$‰$èÅe‰Ç…Àui‹E¤‰D$‹EÀ‰$èmá…ÀuSÇD$²©‰$è `‰Ç…Àu=E ‰D$‰$è„e‰Ç…Àu(ÇD$‹E ‰D$ ‹E¨‰D$ÇD$‰$èÝíÿÿ‰ÇÿEœ…ÿ„ÿÿÿërÇD$‹E°‰D$ ‹E¨‰D$ÇD$‰$è¨íÿÿ‰Ç…ÀuFE°ƒxt(ÇD$‹@‰D$ ‹E¨‰D$ÇD$‰$èsíÿÿ‰Ç…ÿu‹E¨‰$è*ïÿÿ‰Ç…Àt&‹E¨‰$èÐéÿÿ ÇÇD$‰4$è*à‰Â ú鋉X4‹‹M‰H8‹ÝEØÝX‹ÝEàÝX‹ÝEÈÝX‹ÝEÐÝX ƒ}´tB‹Ç@(ë@‰ÂéÖ‰ÂéϺéź黉Âé´‰Âé­‰Â馋Ç@(¿‹ƒx(†€ÇEœ‹E¨‰Âƒxdvf½‰E˜‹M˜‹D °‰D$‹R`‹Mœ‰AÅ‹‰$èß…Àu!‹‹Uœ‰T¸,‹E¨‹@`ÇD@ÇDDëÿEœ‹U¨‹Mœ9Jdw¤G‹9x(w€‹‹E¨‰º‰Ð‹]ô‹uø‹}ü‰ì]ÃU‰å숉]ô‰uø‰}ü‹]‹u º…ö„kÇD$¬EĉD$‰$è[ÿÿ‰Â…À…JÇD$Y¦‰$ès‰Â…À…0ÇD$‘¦‰$èws‰Â…À…‹EĉD$‰$èÎ^…Àt+‰$èÂH‰Â…À…ñ‹EĉD$‰$èYc‰Â…À…ØÇD$7¦‰$ès‰Â…À…¾‹EĉD$EÀ‰D$‰$èod‰Â…À…žE¼‰D$‹E‰D$‰$èb—ÿÿ‰Â…À…~ÇD$°§‰$èEr‰Â…À…dÇD$§§‰$è«r‰Â…À…JÇE´ÇE°é•ÇD$ŧ‰$èŽ\…À…BE¬‰D$‰$èGe…À…2‹E¬Hƒø‡,‹E¬ƒ|…¬…(ÇD$`¬‰$èD\…À…‹E¬D…¬‰D$‰$è¹a…À…ÇD$§§‰$è\…À…õ‹E¼‰D$‰$èj\…À„Tÿÿÿƒ}°…´ÇD$§§‰$èÈq‰Â…À…g‰$è&G‰Â…À…U‹E¼‰D$‰$è½a‰Â…À…<ÇD$ŧ‰$èƒq‰Â…À…"ÇD$‰$èéd‰Â…À…ÇD$`¬‰$èOq‰Â…À…îÇD$‹¬E°‰D$‰$èžb‰Â…À…̓}´…´ÇD$§§‰$è q‰Â…À…©‰$èhF‰Â…À…—‹E¼‰D$‰$èÿ`‰Â…À…~ÇD$ŧ‰$èÅp‰Â…À…dÇD$‰$è+d‰Â…À…JÇD$`¬‰$è‘p‰Â…À…0ÇD$•¬E´‰D$‰$èàa‰Â…À…ºƒ}°„ÇD$„©‰$èÇo‰Â…À…æÇD$`¬‰$è-p‰Â…À…Ì‹E°‰D$‰$è$a‰Â…À…³ÇD$²©‰$èúo‰Â…À…™‹E°‰D$E°‰D$‰$èJa‰Â…À…yÇD$a«‰$èÀo‰Â…À…_ÇD$ÇD$ E؉D$‰$è‡d‰Â…À…6ÇD$«‰$è}o‰Â…À…ÇD$ÇD$ EȉD$‰$èDd‰Â…À…óƒ}´„óÇD$`¬‰$è0o‰Â…À…Ï‹E´‰D$‰$è'`‰Â…À…¶ÇD$²©‰$èýn‰Â…À…œ‹E´‰D$E´‰D$‰$èM`‰Â…À…|ÇD$a«‰$èÃn‰Â…À…bÇD$ÇD$ Eà‰D$‰$èŠc‰Â…À…9ÇD$«‰$è€n‰Â…À…ÇD$ÇD$ EЉD$‰$èGc‰Â…À…öE¨‰$è@âÿÿ‰Â…À…áÇD$ ÇD$@ÇD$‰4$èèØÇEœÇD$l¬‰$èm‰Ç…À…àÇD$c§‰$è÷W…Àt.ÇD$7¦‰$èãW…ÀtÇD$c§‰$è¿m‰Ç…À…ž‹Uœ‰T$‰$è¦U‰Ç=@„…Àu~E¤‰D$‰$è&]‰Ç…Àui‹E¤‰D$‹EÀ‰$èÎØ…ÀuSÇD$²©‰$èjW‰Ç…Àu=E ‰D$‰$èå\‰Ç…Àu(ÇD$‹E ‰D$ ‹E¨‰D$ÇD$‰$è>åÿÿ‰ÇÿEœ…ÿ„ûþÿÿërÇD$‹E°‰D$ ‹E¨‰D$ÇD$‰$è åÿÿ‰Ç…ÀuFE°ƒxt(ÇD$‹@‰D$ ‹E¨‰D$ÇD$‰$èÔäÿÿ‰Ç…ÿu‹E¨‰$è‹æÿÿ‰Ç…Àt&‹E¨‰$è1áÿÿ ÇÇD$‰4$è‹×‰Â ú鋉X4‹‹M‰H8‹ÝEØÝX‹ÝEàÝX‹ÝEÈÝX‹ÝEÐÝX ƒ}´tB‹Ç@(ë@‰ÂéÖ‰ÂéϺéź黉Âé´‰Âé­‰Â馋Ç@(¿‹ƒx(†€ÇEœ‹E¨‰Âƒxdvf½‰E˜‹M˜‹D °‰D$‹R`‹Mœ‰AÅ‹‰$èþÖ…Àu!‹‹Uœ‰T¸,‹E¨‹@`ÇD@ÇDDëÿEœ‹U¨‹Mœ9Jdw¤G‹9x(w€‹‹E¨‰º‰Ð‹]ô‹uø‹}ü‰ì]ÃU‰å숉]ô‰uø‰}ü‹]‹u º…ö„šEĉD$‰$èu„ÿÿ‰Â…À…ÇD$Y¦‰$èjT‰Â…À…gÇD$‘¦‰$èðT‰Â…À…M‹EĉD$‰$è7V‰Â…À…4ÇD$7¦‰$è½T‰Â…À…EÀ‰D$‰$è4Z‰Â…À…E¼‰D$‹E‰D$‰$è÷Žÿÿ‰Â…À…áÇD$°§‰$èÊS‰Â…À…ÇÇD$§§‰$èPT‰Â…À…­ÇE´ÇE°é•ÇD$ŧ‰$è#T…À…¥E¬‰D$‰$èÜ\…À…•‹E¬Hƒø‡‹E¬ƒ|…¬…‹ÇD$`¬‰$èÙS…À…}‹E¬D…¬‰D$‰$èNY…À…iÇD$§§‰$è¦S…À…X‹E¼‰D$‰$èÿS…À„Tÿÿÿºƒ}°„ßÇD$„©‰$èÈR‰Â…À…ÅÇD$`¬‰$èNS‰Â…À…«‹E°‰D$‰$è•T‰Â…À…’ÇD$²©‰$èS‰Â…À…xE°‰D$‰$è’X‰Â…À…_ÇD$¬«‰$èèR…ÀtÇD$a«‰$èÔR‰Â…À…1E؉D$‰$èÛ[‰Â…À…E؉D$‰$èÂ[‰Â…À…ÿÇD$«‰$èˆR‰Â…À…åEȉD$‰$è[‰Â…À…̃}´„àÇD$`¬‰$èKR‰Â…À…¨‹E´‰D$‰$è’S‰Â…À…ÇD$²©‰$èR‰Â…À…uE´‰D$‰$èW‰Â…À…\ÇD$¬«‰$èåQ…ÀtÇD$a«‰$èÑQ‰Â…À….Eà‰D$‰$èØZ‰Â…À…ÇD$«‰$èžQ‰Â…À…ûEЉD$‰$è¥Z‰Â…À…âE¨‰$è^Ûÿÿ‰Â…À…ÍÇD$ ÇD$@ÇD$‰4$èÒÇEœÇD$l¬‰$èP‰Ç…À…ÌÇD$c§‰$èQ…ÀtÇD$7¦‰$èQ‰Ç…À…ž‹Uœ‰T$‰$èØN‰Ç=@„…Àu~E¤‰D$‰$èXV‰Ç…Àui‹E¤‰D$‹EÀ‰$èÒ…ÀuSÇD$²©‰$èœP‰Ç…Àu=E ‰D$‰$èV‰Ç…Àu(ÇD$ÿÿÿÿ‹E ‰D$ ‹E¨‰D$ÇD$‰$èpÞÿÿ‰ÇÿEœ…ÿ„ÿÿÿërÇD$‹E°‰D$ ‹E¨‰D$ÇD$‰$è;Þÿÿ‰Ç…ÀuFE°ƒxt(ÇD$‹@‰D$ ‹E¨‰D$ÇD$‰$èÞÿÿ‰Ç…ÿu‹E¨‰$è½ßÿÿ‰Ç…Àt&‹E¨‰$ècÚÿÿ ÇÇD$‰4$è½Ð‰Â ú鋉X4‹‹M‰H8‹ÝEØÝX‹ÝEàÝX‹ÝEÈÝX‹ÝEÐÝX ƒ}´tB‹Ç@(ë@‰ÂéÖ‰ÂéϺéź黉Âé´‰Âé­‰Â馋Ç@(¿‹ƒx(†€ÇEœ‹E¨‰Âƒxdvf½‰E˜‹M˜‹D °‰D$‹R`‹Mœ‰AÅ‹‰$è0Ð…Àu!‹‹Uœ‰T¸,‹E¨‹@`ÇD@ÇDDëÿEœ‹U¨‹Mœ9Jdw¤G‹9x(w€‹‹E¨‰º‰Ð‹]ô‹uø‹}ü‰ì]ÃU‰å숉]ô‰uø‰}ü‹]‹u º…ö„™ÇD$¬EĉD$‰$èî}ÿÿ‰Â…À…xÇD$Y¦‰$è¤c‰Â…À…^ÇD$‘¦‰$è d‰Â…À…D‹EĉD$‰$èaO…Àt+‰$èU9‰Â…À…‹EĉD$‰$èìS‰Â…À…ÇD$7¦‰$è²c‰Â…À…ì‹EĉD$EÀ‰D$‰$èU‰Â…À…ÌE¼‰D$‹E‰D$‰$èõ‡ÿÿ‰Â…À…¬ÇD$°§‰$èØb‰Â…À…’ÇD$§§‰$è>c‰Â…À…xÇE´ÇE°é•ÇD$ŧ‰$è!M…À…pE¬‰D$‰$èÚU…À…`‹E¬Hƒø‡Z‹E¬ƒ|…¬…VÇD$`¬‰$è×L…À…H‹E¬D…¬‰D$‰$èLR…À…4ÇD$§§‰$è¤L…À…#‹E¼‰D$‰$èýL…À„Tÿÿÿƒ}°…´ÇD$§§‰$è[b‰Â…À…•‰$è¹7‰Â…À…ƒ‹E¼‰D$‰$èPR‰Â…À…jÇD$ŧ‰$èb‰Â…À…PÇD$‰$è|U‰Â…À…6ÇD$`¬‰$èâa‰Â…À…ÇD$‹¬E°‰D$‰$è1S‰Â…À…ûƒ}´…´ÇD$§§‰$èa‰Â…À…׉$èû6‰Â…À…Å‹E¼‰D$‰$è’Q‰Â…À…¬ÇD$ŧ‰$èXa‰Â…À…’ÇD$‰$è¾T‰Â…À…xÇD$`¬‰$è$a‰Â…À…^ÇD$•¬E´‰D$‰$èsR‰Â…À…=ºƒ}°„.ÇD$„©‰$èZ`‰Â…À…ÇD$`¬‰$èÀ`‰Â…À…ú‹E°‰D$‰$è·Q‰Â…À…áÇD$²©‰$è`‰Â…À…Ç‹E°‰D$E°‰D$‰$èÝQ‰Â…À…§ÇD$¬«‰$ècJ…ÀtÇD$a«‰$è?`º@…À…vÇD$ÇD$ E؉D$‰$èU‰Â…À…MÇD$«‰$èù_‰Â…À…3ÇD$ÇD$ EȉD$‰$èÀT‰Â…À… ƒ}´„ ÇD$`¬‰$è¬_‰Â…À…æ‹E´‰D$‰$è£P‰Â…À…ÍÇD$²©‰$èy_‰Â…À…³‹E´‰D$E´‰D$‰$èÉP‰Â…À…“ÇD$¬«‰$èOI…ÀtÇD$a«‰$è+_º@…À…bÇD$ÇD$ Eà‰D$‰$èïS‰Â…À…9ÇD$«‰$èå^‰Â…À…ÇD$ÇD$ EЉD$‰$è¬S‰Â…À…öE¨‰$è¥Òÿÿ‰Â…À…áÇD$ ÇD$@ÇD$‰4$èMÉÇEœÇD$l¬‰$èæ]‰Ç…À…àÇD$c§‰$è\H…Àt.ÇD$7¦‰$èHH…ÀtÇD$c§‰$è$^‰Ç…À…ž‹Uœ‰T$‰$è F‰Ç=@„…Àu~E¤‰D$‰$è‹M‰Ç…Àui‹E¤‰D$‹EÀ‰$è3É…ÀuSÇD$²©‰$èÏG‰Ç…Àu=E ‰D$‰$èJM‰Ç…Àu(ÇD$ÿÿÿÿ‹E ‰D$ ‹E¨‰D$ÇD$‰$è£Õÿÿ‰ÇÿEœ…ÿ„ûþÿÿërÇD$‹E°‰D$ ‹E¨‰D$ÇD$‰$ènÕÿÿ‰Ç…ÀuFE°ƒxt(ÇD$‹@‰D$ ‹E¨‰D$ÇD$‰$è9Õÿÿ‰Ç…ÿu‹E¨‰$èðÖÿÿ‰Ç…Àt&‹E¨‰$è–Ñÿÿ ÇÇD$‰4$èðlj ú鋉X4‹‹M‰H8‹ÝEØÝX‹ÝEàÝX‹ÝEÈÝX‹ÝEÐÝX ƒ}´tB‹Ç@(ë@‰ÂéÖ‰ÂéϺéź黉Âé´‰Âé­‰Â馋Ç@(¿‹ƒx(†€ÇEœ‹E¨‰Âƒxdvf½‰E˜‹M˜‹D °‰D$‹R`‹Mœ‰AÅ‹‰$ècÇ…Àu!‹‹Uœ‰T¸,‹E¨‹@`ÇD@ÇDDëÿEœ‹U¨‹Mœ9Jdw¤G‹9x(w€‹‹E¨‰º‰Ð‹]ô‹uø‹}ü‰ì]ÃU‰åSƒì‹E»‰Eø…Àt ‹‰$è1Ðÿÿ‰ÃÇD$Eø‰$èˆÆ ؃Ä[]ÃU‰åS‹]¸…ÛtA‹‹C,‹J`€PÝEÜKÜCÝ\Ñ8ƒ{(u‹‹C0‹J`€PÝE ÜK ÜCÝ\Ñ8¸[]ÃU‰åìȉ]ô‰uø‰}ü‹]‹u ‹}º…Û„—ºƒ{(†ˆUÈE؉D$EЉD$‰T$ÙîÝT$ Ý\$‰$èe ‰Â…À…WU¨E¸‰D$E°‰D$‰T$ÇD$ ÇD$ð?ÇD$ÇD$‰$è ‰Â…À…UˆE˜‰D$E‰D$‰T$ÇD$ ÇD$ÇD$ÇD$ð?‰$è× ‰Â…À…ÉÝEˆÜeÈÝ•hÿÿÿÝE¨ÜeÈÝpÿÿÿÝEÜeÐÝ•xÿÿÿÝE°ÜeÐÝU€ÞÊÜpÿÿÿÞéºÙîÙÉÝáßàÝÙžzt|ÝE€ÜMÈÝ…pÿÿÿÜMÐÞáØñÝ•XÿÿÿÝ…xÿÿÿÜMÈÝ…hÿÿÿÜMÐÞéÞòÙÉÝ`ÿÿÿ…ötÝëÝØ…ÿtÝ…`ÿÿÿ݃}tÝ…XÿÿÿÜK‹E݃}tÝ…`ÿÿÿÜK ‹EݺëÝØ‰Ð‹]ô‹uø‹}ü‰ì]ÃU‰åWVSƒìl‹]‹M‹u‹}º…Û„•ºƒ{(††‹C4‰E ‹S0‰U¬‹C,‰E¨ÝC ÙîÙÉÚéßàžvºëºÿÿÿÿÝCÙîÙÉÚéßàžv ÇE¤ëÇE¤ÿÿÿÿÝC ÙîÝéßàžvÙàÝCÙîÝêßàžvÙàƒ} t ‹U ÝÝ]¸ë8…öt ÙîÙÊÝâßàÝÚžztRÛ$d$ÜØòÝ]¸ëÝØÝØëÝØÝØºéØ…ÉtÝÝ]°ë3…ÿtÙîÙÉÝáßàÝÙžztÛE¤ÜØñÝ]°ëÝØÝØëÝØÝØºéš…öu'ƒ} tÙîÙÊÝêßàÝÙžuzÝØëÝØÝØºéoÝÙ…ÿu…ÉtÙîÙÉÚéßàžuzëÝØºéJÝØEè‰D$Eà‰D$ E؉D$EЉD$‰$èŸüÿÿ‰Â…À…ÇD$„©‹U ‰$èA‰Â…À…ýÇD$²©‹M ‰ $è‘A‰Â…À…àÝEÐݨ¬ÙÁØáÝE¸ÙÉÝéßàžwÙÊÞÁÙÉÚéßàž†½ëÝØÝØÝØ‹U ‰$èÚ7‰Â…À…™‹‹P`‹M¬‰A‹‰D$‹E ‰$è€B‰Â…À…oÇD$a«‹U ‰$èóV‰Â…À…RÇD$ÇD$ EȉD$‹M ‰ $è·K‰Â…À…&ÝE¸ÜeÐÜK ÜkÝ\$ÇD$Ÿ¬‹E ‰$èZJ‰Â…À…ùÇD$²©‹U ‰$è@‰Â…À…ÜÝEØÝ¨¬ÙÁØáÝE°ÙÉÝéßàžwÙÊÞÁÙÉÚéßàž†­ëÝØÝØÝØ‹U ‰$èÖ6‰Â…À…•‹‹P`‹M¨‰A‹‰D$‹E ‰$è|A‰Â…ÀuoÇD$a«‹U ‰$èóU‰Â…ÀuVÇD$ÇD$ EÀ‰D$‹M ‰ $è»J‰Â…Àu.ÝE°ÜeØÜKÜkÝ\$ÇD$Ÿ¬‹E ‰$èbI‰Â…Àuº‰ÐƒÄl[^_]ÃU‰åWVSƒìl‹]‹} º…Û„Rºƒ{(†C‹s4‹C8Uì‰T$‰D$‰4$èŠwÿÿ‰Â…À… ‹C0‰E¤‹K,‰M ÝC ÙîÙÉÚéßàžv¹ë¹ÿÿÿÿÝCÙîÙÉÚéßàžvºëºÿÿÿÿÝC ÙîÝéßàžvÙàÝCÙîÝêßàžvÙà…ÿtÝÝ]°ë=ƒ}t#ÙîÙÊÝâßàÝÚžztQÛ$d$‹EÜØòÝ]°ëÝØÝØëÝØÝØºé|ƒ}t ‹MÝÝ]¨ë=ƒ}t#ÙîÙÉÝáßàÝÙžztRÛ$d$‹EÜØñÝ]¨ëÝØÝØëÝØÝØºé/ƒ}u%…ÿtÙîÙÊÝêßàÝÙžuzÝØëÝØÝØºéÝÙƒ}u!ƒ}tÙîÙÉÚéßàžuzëÝØºéÛÝØEà‰D$E؉D$ EЉD$EȉD$‰$è¸øÿÿ‰Â…À…«ÇD$„©‰4$è*=‰Â…À…‘ÇD$²©‰4$è°=‰Â…À…wÝEÈÝà¬ÙÁØáÝE°ÙÉÝéßàžwÙÊÞÁÙÉÚéßàž†®ëÝØÝØÝØ‰4$èü3‰Â…À…3‹‹P`‹M¤‰A‹‰D$‰4$è¥>‰Â…À… ÇD$¬«‰4$èS‰Â…À…òÇD$ÇD$ EÀ‰D$‰4$èâG‰Â…À…ÉÝE°ÜeÈÜK ÜkÝ\$ÇD$Ÿ¬‰4$èˆF‰Â…À…ŸÇD$²©‰4$è¾<‰Â…À……ÝEÐÝà¬ÙÁØáÝE¨ÙÉÝéßàžwÙÊÞÁÙÉÚéßàž†®ëÝØÝØÝØ‰4$è 3‰Â…À…A‹‹P`‹M ‰A‹‰D$‰4$è³=‰Â…À…ÇD$¬«‰4$è)R‰Â…À…ÇD$ÇD$ E¸‰D$‰4$èðF‰Â…À…×ÝE¨ÜeÐÜKÜkÝ\$ÇD$Ÿ¬‰4$è–E‰Â…À…­ÇD$K§‰4$è,;‰Â…À…“ÇD$7¦‰4$è²;‰Â…Àu}‹Eì‰D$‰4$èý<‰Â…ÀuhÇD$°¬‰4$èwQ‰Â…ÀuRÝE°ÜK Ý\$ÇD$Ÿ¬‰4$èE‰Â…Àu2ÇD$Ƭ‰4$èAQ‰Â…ÀuÝE¨ÜKÝ\$ÇD$Ÿ¬‰4$èáD‰Â‰ÐƒÄl[^_]ÃU‰åVSƒì`‹]‹u UØEè‰D$ Eà‰D$‰T$‰$è_‰Â…ÀuPU¸EȉD$EÀ‰D$‰T$ÙîÝT$ Ý\$‰$èd‰Â…Àu#…ötÝEØÜM¸ÝEàÜMÀÞÁÝEèÜMÈÞÁÙáݺ‰ÐƒÄ`[^]ÃU‰åƒì(‹E‰D$‹E‰D$‹E ‰D$ÙîÝT$ Ý\$‹E‰$èkÉÃU‰åSƒì4‹]ÝEÝ\$ ÝE Ý\$‰$èÉôÿÿ‰Â…Àu;‹E$‰D$0‹E ‰D$,‹E‰D$(ÙîÝT$ ÝT$ÝT$Ý\$ÇD$‹‰$èeËÿÿ‰Â‰ÐƒÄ4[]ÃU‰å츉]ô‰uø‰}ü‹]‹u‹} UÈE؉D$EЉD$‰T$Ùè¬ÝEØáÝ\$ Üm Ý\$‰$èIÿÿÿ‰Â…À…_U¨E¸‰D$E°‰D$‰T$Ùè¬ÝEØÁÝ\$ Üm Ý\$‰$è ÿÿÿ‰Â…À…"UˆE˜‰D$E‰D$‰T$Ùè¬ÝEØáÝ\$ ÝE ÞÁÝ\$‰$èÍþÿÿ‰Â…À…ãÝE¨ÜeÈÝU¨ÝE°ÜeÐÝU°ÝE¸ÜeØÝU¸ÝEˆÜeÈÝUˆÝEÜeÐÝUÝE˜ÜeØÝU˜ÜÌÙÉØËÞìÙËÝ•hÿÿÿÙÊØÉÙËØÌÞëÙÊÝ•pÿÿÿÙËÜMÙÊÜM°ÞêÙÉÝ•xÿÿÿÙÉØÈÙÊØÈÞÂØÈÞÁÙîÝéßàžr ÝØºëWÙÀÙúÝàßàžztÝØëÝØÝ$èUáëÝÙ…öt Ý…hÿÿÿØñÝ…ÿt Ý…pÿÿÿØñ݃}$tÝ…xÿÿÿÞñ‹E$ÝëÝØº‰Ð‹]ô‹uø‹}ü‰ì]ÃU‰å츉]ô‰uø‰}ü‹]‹u‹} º…Û„ôºƒ{(†åUÈE؉D$EЉD$‰T$Ùì¬ÝEØáÝ\$ Üm Ý\$‰$ègýÿÿ‰Â…À…¨U¨E¸‰D$E°‰D$‰T$Ùì¬ÝEØÁÝ\$ Üm Ý\$‰$è*ýÿÿ‰Â…À…kUˆE˜‰D$E‰D$‰T$Ùì¬ÝEØáÝ\$ ÝE ÞÁÝ\$‰$èëüÿÿ‰Â…À…,ÝE¨ÜeÈÝU¨ÝE°ÜeÐÝU°ÝE¸ÜeØÝU¸ÝEˆÜeÈÝUˆÝEÜeÐÝUÝE˜ÜeØÝU˜ÜÌÙÉØËÞìÙËÝ•hÿÿÿÙÊØÉÙËØÌÞëÙÊÝ•pÿÿÿÙËÜMÙÊÜM°ÞêÙÉÝ•xÿÿÿÙÉØÈÙÊØÈÞÂØÈÞÁÙîÝéßàžr ÝØºéÙÀÙúÝàßàžztÝØëÝØÝ$èpßëÝÙ…ötÝëÝØ…ÿtkÝEÈÙÀÞÉÝEÐØÈÞÁÝEØØÈÞÁÙîÝéßàžr ÝØºëIÙÀÙúÝàßàžztÝØëÝØÝ$èßëÝÙÝEÈÜhÿÿÿÝEÐÜpÿÿÿÞÁÝEØÜxÿÿÿÞÁÙáÞñݺ‰Ð‹]ô‹uø‹}ü‰ì]ÃU‰åS‹]‹M …Û”À…É” Шu9K(s¸ëÝDËÙá‹Eݸ[]ÃU‰åƒì(‰]ô‰uø‰}ü‹u‹] ‹}ÇD$›¦‰4$è5‰Â…À…a‰4$è,,‰Â…À…O…Û„#ÇD$ ÇD$‰\$ÇD$ð¬‰4$èM‰Â…À…ÇD$ ÇD$C‰D$ÇD$ù¬‰4$èÕL‰Â…À…èÇD$ ÇD$C‰D$ÇD$­‰4$è¤L‰Â…À…·ÇD$ ÇD$C‰D$ÇD$ ­‰4$èsL‰Â…À…†ÇD$ ÇD$C ‰D$ÇD$­‰4$èBL‰Â…À…UÇD$ ÇD$C(‰D$ÇD$"­‰4$èL‰Â…À…$…ÿ„ÇD$ ÇD$‰|$ÇD$.­‰4$èÛK‰Â…À…îÇD$ ÇD$G‰D$ÇD$;­‰4$èªK‰Â…À…½ÇD$ ÇD$G‰D$ÇD$H­‰4$èyK‰Â…À…ŒÇD$ ÇD$G‰D$ÇD$U­‰4$èHK‰Â…Àu_ÇD$ ÇD$G ‰D$ÇD$e­‰4$èK‰Â…Àu2ÇD$ ÇD$G(‰D$ÇD$t­‰4$èîJ‰Â…Àuº‰Ð‹]ô‹uø‹}ü‰ì]ÃU‰åƒì(‰]ô‰uø‰}ü‹]‹u ‹}Eð‰D$‰$è^bÿÿ‰Â…À…JÇD$›¦‰$ècH‰Â…À…0‰$èq)‰Â…À…ÇD$ ¦‰$è·H‰Â…À…ÇEìEì‰D$‰$è78…Àuƒ}ìt‹Eì€8u‹Eð‰D$‰$è–8‰Â…À…Ã…ö„aÇD$ð¬‰$èTH‰Â…À…¡ÝÝ\$ÇD$馉$èô;‰Â…À…ÇD$ù¬‰$èH‰Â…À…gÝFÝ\$ÇD$馉$è¹;‰Â…À…FÇD$­‰$èßG‰Â…À…,ÝFÝ\$ÇD$馉$è~;‰Â…À… ÇD$ ­‰$è¤G‰Â…À…ñÝFÝ\$ÇD$馉$èC;‰Â…À…ÐÇD$­‰$èiG‰Â…À…¶ÝF Ý\$ÇD$馉$è;‰Â…À…•ÇD$"­‰$è.G‰Â…À…{ÝF(Ý\$ÇD$馉$èÍ:‰Â…À…Z…ÿ„MÇD$.­‰$èëF‰Â…À…8ÝÝ\$ÇD$馉$è‹:‰Â…À…ÇD$;­‰$è±F‰Â…À…þÝGÝ\$ÇD$馉$èP:‰Â…À…ÝÇD$H­‰$èvF‰Â…À…ÃÝGÝ\$ÇD$馉$è:‰Â…À…¢ÇD$U­‰$è;F‰Â…À…ˆÝGÝ\$ÇD$馉$èÚ9‰Â…ÀukÇD$e­‰$èF‰Â…ÀuUÝG Ý\$ÇD$馉$è§9‰Â…Àu8ÇD$t­‰$èÑE‰Â…Àu"ÝG(Ý\$ÇD$馉$èt9‰Â…Àuº‰Ð‹]ô‹uø‹}ü‰ì]ÃU‰åƒì(‰]ô‰uø‰}ü‹u‹] ‹}ÇD$›¦‰4$èâ.‰Â…À…a‰4$è&‰Â…À…O…Û„#ÇD$ ÇD$‰\$ÇD$„­‰4$èÚF‰Â…À…ÇD$ ÇD$C‰D$ÇD$˜­‰4$è©F‰Â…À…èÇD$ ÇD$C‰D$ÇD$¬­‰4$èxF‰Â…À…·ÇD$ ÇD$C‰D$ÇD$À­‰4$èGF‰Â…À…†ÇD$ ÇD$C ‰D$ÇD$×­‰4$èF‰Â…À…UÇD$ ÇD$C(‰D$ÇD$í­‰4$èåE‰Â…À…$…ÿ„ÇD$ ÇD$‰|$ÇD$®‰4$è¯E‰Â…À…îÇD$ ÇD$G‰D$ÇD$®‰4$è~E‰Â…À…½ÇD$ ÇD$G‰D$ÇD$4®‰4$èME‰Â…À…ŒÇD$ ÇD$G‰D$ÇD$L®‰4$èE‰Â…Àu_ÇD$ ÇD$G ‰D$ÇD$g®‰4$èïD‰Â…Àu2ÇD$ ÇD$G(‰D$ÇD$®‰4$èÂD‰Â…Àuº‰Ð‹]ô‹uø‹}ü‰ì]ÃU‰åƒì(‰]ô‰uø‰}ü‹]‹u ‹}Eð‰D$‰$è2\ÿÿ‰Â…À…JÇD$›¦‰$è7B‰Â…À…0‰$èE#‰Â…À…ÇD$ ¦‰$è‹B‰Â…À…ÇEìEì‰D$‰$è 2…Àuƒ}ìt‹Eì€8u‹Eð‰D$‰$èj2‰Â…À…Ã…ö„aÇD$„­‰$è(B‰Â…À…¡ÝÝ\$ÇD$馉$èÈ5‰Â…À…ÇD$˜­‰$èîA‰Â…À…gÝFÝ\$ÇD$馉$è5‰Â…À…FÇD$¬­‰$è³A‰Â…À…,ÝFÝ\$ÇD$馉$èR5‰Â…À… ÇD$À­‰$èxA‰Â…À…ñÝFÝ\$ÇD$馉$è5‰Â…À…ÐÇD$×­‰$è=A‰Â…À…¶ÝF Ý\$ÇD$馉$èÜ4‰Â…À…•ÇD$í­‰$èA‰Â…À…{ÝF(Ý\$ÇD$馉$è¡4‰Â…À…Z…ÿ„MÇD$®‰$è¿@‰Â…À…8ÝÝ\$ÇD$馉$è_4‰Â…À…ÇD$®‰$è…@‰Â…À…þÝGÝ\$ÇD$馉$è$4‰Â…À…ÝÇD$4®‰$èJ@‰Â…À…ÃÝGÝ\$ÇD$馉$èé3‰Â…À…¢ÇD$L®‰$è@‰Â…À…ˆÝGÝ\$ÇD$馉$è®3‰Â…ÀukÇD$g®‰$èØ?‰Â…ÀuUÝG Ý\$ÇD$馉$è{3‰Â…Àu8ÇD$®‰$è¥?‰Â…Àu"ÝG(Ý\$ÇD$馉$èH3‰Â…Àuº‰Ð‹]ô‹uø‹}ü‰ì]ÃU‰åSƒìD‹]ÙèÝT$Ý$èÒØ5œ®Ý]ðÝÜKÜKÝ]èÝEðÜKÝ$èôÑÝUàØÈÙèÞáÝ]ØÝEðÜK Ý$èÚÑÝUÐØÈÜmØÝ]ÈÝEðÜK(Ý$èÁÑÙÀØÉÝEÈÞáÝEàØÀÜMÐÞÊÞÁÙÀÙúÝàßàžztÝØëÝØÝ$è±ÑëÝÙÜMè‹E ݸƒÄD[]ÃU‰åVSìð‹]‹u Eð‰D$‰$è,ÿÿÿÙèÝT$Ý$è<ÑØ5 ®ÝUèÙèÞñÝ]àÙîÝEðÙÉÚéßàžr ¸é{ÝCÜKÝ]ØÝEèÜKÝ$èÑÜMØÜuðÝÝCÜ Ý]ÐÝEèÜK Ý$èÿÐÜMÐÜuðÝ^ÝÜKÝ]ÈÝEèÜK(Ý$èàÐÜMÈÜuðÝ^ÝEèÜK ÝUÀÝ$è¶ÐÝ]¸ÝEèÜK(ÝU°Ý$è¢ÐÜM¸Ý]¨ÝEèÜKÝ$èŽÐÜm¨Ý] ÝEÀÝ$èÐÝ]˜ÝE°Ý$èÐÜM˜Ü} ÝUØÈÙèÞáÙÀÙúÝàßàžztÝØëÝØÝ$èeÐëÝÙÝEÝ\$Ý$è"ÐÜMàÝ^ÝEèÜK(ÝUˆÝ$èÐÝ]€ÝEèÜKÝ•xÿÿÿÝ$èÐÜM€ÝpÿÿÿÝEèÜK Ý$èíÏÜ­pÿÿÿÝhÿÿÿÝEˆÝ$èæÏÝ`ÿÿÿÝ…xÿÿÿÝ$èÒÏÜ`ÿÿÿܽhÿÿÿÝ•XÿÿÿØÈÙèÞáÙÀÙúÝàßàžztÝØëÝØÝ$è¯ÏëÝÙÝ…XÿÿÿÝ\$Ý$èiÏÜMàÝ^ ÝEèÜKÝ•PÿÿÿÝ$è_ÏÝHÿÿÿÝEèÜK Ý•@ÿÿÿÝ$èEÏÜHÿÿÿÝ8ÿÿÿÝEèÜK(Ý$è+ÏÜ­8ÿÿÿÝ0ÿÿÿÝ…PÿÿÿÝ$è!ÏÝ(ÿÿÿÝ…@ÿÿÿÝ$è ÏÜ(ÿÿÿܽ0ÿÿÿÝ• ÿÿÿØÈÙèÞáÙÀÙúÝàßàžztÝØëÝØÝ$èêÎëÝÙÝ… ÿÿÿÝ\$Ý$è¤ÎÜMàÝ^(¸Äð[^]ÃU‰åƒì‰]ø‰uü‹]‹u ÇD$|¦‰$è-%‰Â…À…ω$èK‰Â…À…½…ö„°ÇD$¤®‰$è™%‰Â…À…›‰t$‰$è£.‰Â…À……ÇD$­®‰$èi%‰Â…À…kF‰D$‰$èp.‰Â…À…RÇD$¶®‰$è6%‰Â…À…8F‰D$‰$è=.‰Â…À…ÇD$¿®‰$è%‰Â…À…F‰D$‰$è .‰Â…À…ìÇD$È®‰$èÐ$‰Â…À…ÒF ‰D$‰$è×-‰Â…À…¹ÇD$Ñ®‰$è$‰Â…À…ŸF(‰D$‰$è¤-‰Â…À…†ÇD$Ú®‰$èj$‰Â…ÀupF0‰D$‰$èu-‰Â…Àu[ÇD$㮉$è?$‰Â…ÀuEF8‰D$‰$èJ-‰Â…Àu0ÇD$쮉$è$‰Â…ÀuF@‰D$‰$è-‰Â…Àuº‰Ð‹]ø‹uü‰ì]ÃU‰åƒì(‰]ø‰uü‹]‹u Eô‰D$‰$èSÿÿ‰Â…À…’ÇD$|¦‰$è9‰Â…À…x‰$è+‰Â…À…fÇD$‘¦‰$èq9‰Â…À…LÇEðEð‰D$‰$èñ(…Àuƒ}ðt‹Eð€8u‹Eô‰D$‰$èP)‰Â…À… …ö„þÇD$¤®‰$è9‰Â…À…éÝÝ\$ÇD$馉$è®,‰Â…À…ÉÇD$­®‰$èÔ8‰Â…À…¯ÝFÝ\$ÇD$馉$ès,‰Â…À…ŽÇD$¶®‰$è™8‰Â…À…tÝFÝ\$ÇD$馉$è8,‰Â…À…SÇD$¿®‰$è^8‰Â…À…9ÝFÝ\$ÇD$馉$èý+‰Â…À…ÇD$È®‰$è#8‰Â…À…þÝF Ý\$ÇD$馉$èÂ+‰Â…À…ÝÇD$Ñ®‰$èè7‰Â…À…ÃÝF(Ý\$ÇD$馉$è‡+‰Â…À…¢ÇD$Ú®‰$è­7‰Â…À…ˆÝF0Ý\$ÇD$馉$èL+‰Â…ÀukÇD$㮉$èv7‰Â…ÀuUÝF8Ý\$ÇD$馉$è+‰Â…Àu8ÇD$쮉$èC7‰Â…Àu"ÝF@Ý\$ÇD$馉$èæ*‰Â…Àuº‰Ð‹]ø‹uü‰ì]ÃU¸‰åƒì‰]ø‹]‰uü‰D$ ¸,‰D$1À‰D$‰$è¡¡…Àt ‹]ø‹uü‰ì]Ãv1ö1ɺ‰t$ ‰L$‰T$‹‰$èQÊ…À‰Æu[‹Ç@Ç@$Ç@(Ç@ ‹Ç@‹XôÇ@Ç@ƒÂ@‰PÇ@Ç@ ‹]ø1À‹uü‰ì]É$1À‰D$èB¡ ðé^ÿÿÿt&¼'U‰å‹E‹U ‰P1À]ÃU‰åƒì‰]ø‹]‰uü1ö…Û‰]ôt ‹C H…À‰C ~ ‹]ø1À‹uü‰ì]ËC…Àu)‹‰$è߯ Æ1À‰D$Eô‰$èÌ  ð‹]ø‹uü‰ì]É$è˜ÿÿÿ‰ÆëËt&U‰åƒì(ƒ}‰]ô‹]‰uø‹u‰}ü‹}„°ãþÿÿË…ÿ¸„_÷Æ…`÷Æt!÷Æ…e÷Æ…Y‰ö¼'÷Æt÷Æ…<÷Æ…0÷À…D1ÉöÕÁ1ÒöÃ@•ÂÊ1ÉöÕÁÑ1Òöà •ÂÊ1ÉöÕÁÑ1ÀöÕÀÈöÃt@HÝ‹E ‰D$Eð‰$è+Þ…À…÷Æ…ï÷Æ„ã÷Æ…Ï÷Æ„Ã÷ÆtƒÎöÃuƒËöÇuË÷ÀuË€‹Eð‹‹M‰XH‰pD‰L$ ‰D$‰T$‰<$èe¸‰Ã‹E…Àu ‹EðÇEð‰$èÈß Ø‹]ô‹uø‹}ü‰ì]Ã÷Æ„”þÿÿ¶¼'¸‹]ô‹uø‹}ü‰ì]ÃãþéTþÿÿ¶öÇ„³þÿÿ¸ëÕƒÎé5ÿÿÿƒÎéÿÿÿU‰åƒì(ƒ}‰]ô‹]‰uø‹u‰}ü‹}„ãþÿÿË…ÿ¸„Â÷Æ…É÷Æt!÷Æ…Å÷Æ…¹‰ö¼'÷Æt÷Æ…œ÷Æ…÷À…¤1ÉöÕÁ1ÒöÃ@•ÂÊ1ÉöÕÁÑ1Òöà •ÂÊ1ÉöÕÁÑ1ÀöÕÀÈöÃt@HAº‰T$‹‰D$Eð‰$èg½…ÀtS‹]ô‹uø‹}ü‰ì]ö÷Æ„+ÿÿÿt&¸‹]ô‹uø‹}ü‰ì]Ããþéôþÿÿ¶öÇ„Sÿÿÿ¸ëÕ‹E ‰D$Eì‰$èÞÜ…Àu—÷Æ…”÷Æ„ˆ÷Æu{÷Æts÷ÆtƒÎöÃuƒËöÇuË÷ÀuË€‹Eì‹U‰XH‰pD‰T$ ‰D$‹Eð‰<$‰D$趉ËE…Àu ‹EìÇEì‰$èfÝ ØéüþÿÿƒÎ눃Îépÿÿÿ‰öU¸‰åƒì(‰}ü‹}‰]ô‹] …ÿ‰uøtl¸uð‰D$‹‰4$‰D$è¼…ÀuN…Ût!‰\$1À‰D$Ç$èÚىÅ۸t)‰\$ ¹‰L$‹Eð‰4$‰D$è³Å…À‰Æu‹Eð‰1À‹]ô‹uø‹}ü‰ì]É\$Ç$èIÚ‰ð‹]ô‹uø‹}ü‰ì]Ãv¼'U¸‰åƒì(‰}ü‹}‰]ô‹] …ÿ‰uøtl¸uð‰D$‹‰4$‰D$èX»…ÀuN…Ût!‰\$1À‰D$Ç$èىÅ۸t)‰\$ ¸‰D$‹Eð‰4$‰D$èóÄ…À‰Æu‹Eð‰1À‹]ô‹uø‹}ü‰ì]É\$Ç$è‰Ù‰ð‹]ô‹uø‹}ü‰ì]Ãv¼'U¸‰åƒì(‰}ü‹}‰]ô‹] …ÿ‰uøtl¹uð‰L$‹‰4$‰D$蘺…ÀuN…Ût!‰\$1Ò‰T$Ç$èZ؉Å۸t)‰\$ ¸‰D$‹Eð‰4$‰D$è“Â…À‰Æu‹Eð‰1À‹]ô‹uø‹}ü‰ì]É\$Ç$èÉØ‰ð‹]ô‹uø‹}ü‰ì]Ãv¼'U¸‰åƒì(‰}ü‹}‰]ô‹] …ÿ‰uøtl¸uð‰D$‹‰4$‰D$èØ¹…ÀuN…Ût!‰\$1À‰D$Ç$èš×‰Ã…Û¸t)‰\$ ¸‰D$‹Eð‰4$‰D$èÓÁ…À‰Æu‹Eð‰1À‹]ô‹uø‹}ü‰ì]É\$Ç$è Ø‰ð‹]ô‹uø‹}ü‰ì]Ãv¼'U¸‰åƒì(‰}ü‹}‰uø‹u …ÿ‰]ôtlº]ð‰T$‹‰$‰D$è¹…Àu[…öt!‰t$1À‰D$Ç$èÚ։ƅö¸t)‰t$ ¸‰D$‹Eð‰$‰D$è³Â…À‰Ãu=‹Eð‰1À‹]ô‹uø‹}ü‰ì]ø‰D$‹‰$‰D$袸…ÀtŠ‹]ô‹uø‹}ü‰ì]Ét$Ç$è ׉؋uø‹]ô‹}ü‰ì]ÃU¸‰åƒì(‰}ü‹}‰uø‹u …ÿ‰]ôtl¸]ð‰D$‹‰$‰D$è8¸…Àu[…öt!‰t$1À‰D$Ç$èúՉƅö¸t)‰t$ ¹‰L$‹Eð‰$‰D$è3À…À‰Ãu=‹Eð‰1À‹]ô‹uø‹}ü‰ì]ø‰D$‹‰$‰D$è·…ÀtŠ‹]ô‹uø‹}ü‰ì]Ét$Ç$è@։؋uø‹]ô‹}ü‰ì]ÃU¸‰åƒì(‹U‰]ô‰uø…Ò‰}üt¸‰D$‹‰D$Eð‰$è[·…Àt ‹]ô‹uø‹}ü‰ì]ËEð‰D$Eì‰$蘷…ÀuÝ1ö1Û;uìsQ}èë¶‹uäC;]ìs=‰\$‹Eð‰<$‰D$褸…Àu©‹Eè‰D$Eä‰$èN·…Àu“…ÛtÆ;uätĸ냋E …Àt‹E ‰0‹]ô1À‹uø‹}ü‰ì]Ãë U¸‰åVSƒì ‹u…öt¸]ô‰D$‹‰$‰D$è‚¶…ÀtƒÄ [^]ô&‰4$Eð‰D$èÑþÿÿ…Àuß‹E …Àt(Ç$‹E 1ɉL$‰D$èÔ‰E ‹U ¸…Òt°‰$‹E ‰D$ ¸‰D$‹Eô‰D$èï¿…À‰ÃtÇ$‹E ‰D$è–Ô‰Øéqÿÿÿ‹Eð‰D$‹Eô‰$è ¹…À‰ÃuÇF$‹EôÇF(‰1Àé?ÿÿÿ‹Eô‰$è¼ Øé-ÿÿÿt&¼'U¸‰åƒì‹U…Òt¸‰D$‹‰D$Eü‰$ètµ…ÀtÉËEü‰D$‹E ‰$è¼µÉÃv¼'U¸‰åƒì8‰}ü‹}‰]ô‰uø…ÿt¸‰D$‹‰D$Eð‰$èµ…Àt ‹]ô‹uø‹}ü‰ì]É<$Eì‰D$èkýÿÿ…Àuà‰<$Eè‰D$èHÿÿÿ…ÀuÍ;EèÇEàs6´&‹Eà‰D$‹Eð‰D$Eä‰$èW¶…À‰Ãtb…Ûu1ÿEà‹Eà;EèrÒ‹Eì‰G$‰G(1Àé{ÿÿÿ‹Eì‰D$‹Eä‰$è°·‰Æ ó‹Eà…Àt;ÿMà‹Eà‰D$‹Eð‰D$Eä‰$èùµ…À‰ÆtÁ óëÓ1À‰D$‹Eä‰$èžÀ‰Ã뉉ØéÿÿÿvU‰åƒì8‰}ü‹}‹E ‰]ô…ÿ‰Eฉuøt»‰\$‹‰D$Eð‰$èõ³…Àt‹]ô‹uø‹}ü‰ì]Ãt&‰<$Eì‰D$èAüÿÿ…Àu܉<$Eè‰D$èþÿÿ…ÀuÉ;EèÇEÜs<´&¼'‹E܉D$‹Eð‰D$Eä‰$è'µ…À‰Ãtb…Ûu1ÿEÜ‹EÜ;EèrÒ‹Eà‰G$‰G(1Àéqÿÿÿ‹Eà‰D$‹Eä‰$è¿‰Æ ó‹UÜ…ÒtBÿMÜ‹E܉D$‹Eð‰D$Eä‰$èÉ´…À‰ÆtÁ óëÓ‹Eà1ɉL$‰D$‹Eä‰$è'¾‰Ã낉Øé ÿÿÿ¶¿U‰åƒì8‰}ü‹}‹E ‰]ô…ÿ‰Eฉuøt¾‰t$‹‰D$Eð‰$èµ²…Àt‹]ô‹uø‹}ü‰ì]Ãt&‰<$Eì‰D$èûÿÿ…Àu܉<$Eè‰D$èÞüÿÿ…ÀuÉÇEÜ1ÛëÿEÜ ó‹EÜ;Eès5‹E܉D$‹Eð‰D$Eä‰$èé³…À‰ÆuÔ‹Eà‰D$‹Eä‰$èὉÆë¾ÿMì‹G$;Eà~H‰G$‹G(;Eà~H‰G(‰ØéZÿÿÿt&¼'U¸‰åƒì(‰}ü‹}‰]ô‹] …ÿ‰uøt_¸‰D$‹‰D$Eð‰$èȱ…ÀuA…Ût!‰\$1À‰D$Ç$èŠÏ‰Ã…Û¸t‰\$‹Eð‰$è®…À‰Æu‹Eð‰1À‹]ô‹uø‹}ü‰ì]ö‰\$Ç$èЉð‹]ô‹uø‹}ü‰ì]ÃU¸‰åƒì(‰}ü‹}‰]ô‹] …ÿ‰uøt_¸‰D$‹‰D$Eð‰$è±…ÀuA…Ût!‰\$1À‰D$Ç$èÚΉÅ۸t‰\$‹Eð‰$è`­…À‰Æu‹Eð‰1À‹]ô‹uø‹}ü‰ì]ö‰\$Ç$èPωð‹]ô‹uø‹}ü‰ì]ÃU¹‰åƒì(‰uø‹u‰]ô‰}ü…öt2º‰T$‹‰D$Eð‰$èk°‰Ã…À•Â1Àû@•À…‰Ùt‹]ô‰È‹uø‹}ü‰ì]Ãt&¸}ì‰D$‹‰<$‰D$è&°…À‰ÁuÍ…Ûtd‹E쉉D$Eè‰$èh°…À‰Áu¯1Û;]ès …ÀuÖ‹^(´&;]ìso‰\$‹Eð‰$輬…ÀtCëåt&‰\$‹Eð‰D$Eè‰$èjª…Àu’‹Mè…É•À1Ò…ÿ•Â…Ðt#‰|$A‰$èD§…Àu¸‰^$C‰F(1Àé\ÿÿÿ9ùëê¸@éNÿÿÿ‰öU‰åƒì‰]ø‹]‰uü‹u ‰$èõÿÿ…Àt ‹]ø‹uü‰ì]Éu ‹uü‰]‹]ø‰ì]éÔþÿÿt&U¸‰åƒì‹U…Òt¸‰D$‹‰D$Eü‰$èäž…ÀtÉËEü‰D$‹E ‰$è,ŸÉÃv¼'U¸‰åƒì‹U…Òt¸‰D$‹‰D$Eü‰$蔞…ÀtÉø‰D$‹Eü‰D$‹E ‰$èŸÉÃU¸‰åVSƒì‹]…Ût9ºuô‰T$‹‰4$‰D$èBž…Àu"¸‰D$‹Eô‰D$‹E ‰$èÞƒÄ[^]ø‰D$‹‰4$‰D$èž…ÀtÃÄ[^]Ãv¼'U¸‰åƒì‹U…Òt¹‰L$‹‰D$Eü‰$èÄ…ÀtÉËEü‰D$‹E ‰$è žÉÃv¼'U¸‰åƒì‹U…Òt¸‰D$‹‰D$Eü‰$èt…ÀtÉËEü‰D$‹E ‰$èLŸÉÃv¼'U¸‰åƒì‹U…Òt¸‰D$‹‰D$Eü‰$è$…ÀtÉËEü‰D$‹E ‰$èüžÉÃv¼'U¸‰åƒì‹U…Òt¸‰D$‹‰D$Eü‰$èÔœ…ÀtÉËEü‰D$‹E ‰$謞ÉÃv¼'U¸‰åƒì‹U…Òt¸‰D$‹‰D$Eü‰$脜…ÀtÉËEü‰D$‹E ‰$è\žÉÃv¼'U¸‰å‹U‹M …Òt …Ét‹B$‰1À]ÃU¸‰åƒì‹U…Òt¸‰D$‹‰D$Eü‰$蜅ÀtÉø‰D$‹Eü‰D$Eø‰$èó›…Àuß‹Eü‰D$‹E ‰$è ÉÃt&¼'U¸‰åVSƒì ‹]…Ût=¾‰t$‹uô‰4$‰D$袛…Àu&º‰T$‹Eô‰D$Eð‰$胛…ÀtAƒÄ [^]ù‰L$‹‰4$‰D$èa›…ÀuÞº‰T$‹Eô‰D$Eð‰$èB›…Àu¿‹Eô‰D$‹E ‰$è\œƒÄ [^]Ãt&Uº‰åVSƒì‹]‹u …ÛtI‹C$‰D$‹‰$èø§…Àºu/‹C$‰D$‹‰D$Eô‰$è§¥…À‰Âu…öt ‹Eô…Àt@‰1҃ĉÐ[^]ô&Ç1Òëæ¶U¸‰åVSƒì‹u‹] …ötN…Ût$‰\$¸€ÿÿÿ‰D$Ç$èL¸‰Ã…Û¸t&‰\$¸‰D$ ‹F$‰D$‹‰$è㜉Æ1À…öu ƒÄ[^]Ãt&‰\$Ç$èÀ¸ƒÄ‰ð[^]ô&U‰åƒì‰]ø‹]‰uü‹u ‰$‰t$è²ùÿÿ1Ò…Àu ‹]ø‰Ð‹uü‰ì]É$èˆäÿÿ…À‰Âuæ‰u ‹uü‰]‹]ø‰ì]éÿÿÿ´&¼'U‰åƒì‰]ø‹]‰uü‹u ‰$èvïÿÿ…Àu‰u ‹uü‰]‹]ø‰ì]énÿÿÿ‰$è&äÿÿ…Àt ‹]ø‹uü‰ì]Éu ‹uü‰]‹]ø‰ì]é´þÿÿt&U‰åƒì‰]ô‹] ‰uø‹u‰}ü‹}‰\$‰4$è þÿÿ…Àu‹…Òu'‰|$‰4$èvþÿÿ…Àu‰] ‹}ü‹]ô‰u‹uø‰ì]éÛýÿÿ‹]ô‹uø‹}ü‰ì]ô&¼'Uº‰åSƒì‹]…Ût8‹C$‰D$‹‰$è¼¥…Àºu‹C$‰D$‹‰D$Eø‰$èk£…À‰ÂtƒÄ‰Ð[]ËE ‰D$‹Eø‰$èû…ƒÄ‰Â‰Ð[]ÃU¸‰åVSƒì‹]‹u …Ût‹C$‰D$‹‰$èH¥…Àtǯ1ÀƒÄ[^]Ãt&‹C$‰D$‹‰D$Eô‰$è袅ÀuØ…ötÒ‹Eô…ÀuÇëÉt$‰$è凅Àuµë±ë U‰åEøSƒì‹] ‰D$‹E‰$è¤üÿÿ…Àu‹Uø¸@…Òt…Ût ‰$舠‰1ÀƒÄ[]ô&¼'U‰åEøSƒì‹] ‰D$‹E‰$èTüÿÿ…Àu‹Uø¸@…Òt…Ût ‰$è( Ý1ÀƒÄ[]ô&¼'U¹¯‰åSƒìT]¸‰L$‹E ‰$‰D$è>ž‰\$‹E‰$èoüÿÿƒÄT[]Éö¼'U‰åW}¨V1öSƒì\‹E ÝE‰<$‰D$Ý\$èü¶E¨ë ¶F¶D.¨< ”Â< ”À Шuê7‰$èoŸ…À‰Á~B¶D(§< ”Â< ”À Шt*Uè\¿´&IK…É~¶< ”Â< ”À ШuçUèÆD0À7‰D$‹E‰$èªûÿÿƒÄ\[^_]ÉöU‰åƒì‰]ô‹]‰}ü‹} ‰uø‹u‰|$‰$è<þÿÿ1Ò…Àu‹]ô‰Ð‹uø‹}ü‰ì]ô&‰t$‰$è´þÿÿ…À‰Âu؉} ‹uø‹}ü‰]‹]ô‰ì]é÷ýÿÿ´&U‰åƒì(ÝE‰]ø‹]‰uü‹u Ý]ð‰$‰t$èþÿÿ1Ò…Àu ‹]ø‰Ð‹uü‰ì]ÃÝE𸯉D$‰$Ý\$è‚þÿÿ…À‰ÂuÖ‰u ‹uü‰]‹]ø‰ì]éØýÿÿ´&Uº‰åSƒìD‹]…Û„‹C$‰D$‹‰$è8¢…Àºtv1À1Ò‰D$<1À‰D$81À‰D$41À‰D$0‹E,‰T$@‰D$,‹E(‰D$(‹E$‰D$$‹E ‰D$ ‹E‰D$‹E‰D$‹E‰D$1À‰D$‹E‰D$ ‹E ‰D$‹C$‰D$‹‰$è««‰ÂƒÄD‰Ð[]ÃUº‰åSƒìD‹]…Û„•‹C$‰D$‹‰$舡…Àºt{‹E@1ɉL$‰D$@‹E<‰D$<‹E8‰D$8‹E4‰D$4‹E0‰D$0‹E,‰D$,‹E(‰D$(‹E$‰D$$‹E ‰D$ ‹E‰D$‹E‰D$‹E‰D$‹E‰D$ ‹E ‰D$‹C$‰D$‹‰$èöª‰ÂƒÄD‰Ð[]ö¿Uº‰åSƒìT‹]…Û„‹C$‰D$‹‰$èÈ …Àºtv1À‰D$@1À‰D$<1À‰D$81À‰D$41À‰D$0Eø‰D$,‹E(‰D$(‹E$‰D$$‹E ‰D$ ‹E‰D$‹E‰D$‹E‰D$1À‰D$‹E‰D$ ‹E ‰D$‹C$‰D$‹‰$è;ª‰ÂƒÄT‰Ð[]ÃUº‰åSƒìT‹]…Û„•‹C$‰D$‹‰$è …Àºt{‹E<1Ò‰T$‰D$@‹E8‰D$<‹E4‰D$8‹E0‰D$4‹E,‰D$0Eø‰D$,‹E(‰D$(‹E$‰D$$‹E ‰D$ ‹E‰D$‹E‰D$‹E‰D$‹E‰D$ ‹E ‰D$‹C$‰D$‹‰$膩‰ÂƒÄT‰Ð[]ö¿Uº‰åSƒìD‹]…Û„‹‹C$‰D$‹‰$èXŸ…Àºtq1À1É1Ò‰D$@1À‰D$<1À‰D$01À‰D$,1À‰D$(1À‰D$$‹E‰L$81ɉD$ 1À‰D$1À‰D$‹E‰T$4‰L$‰D$‹E‰D$ ‹E ‰D$‹C$‰D$‹‰$èШ‰ÂƒÄD‰Ð[]öUº‰åSƒìD‹]…Û„‹C$‰D$‹‰$訞…Àºtv‹E,1Ò1ɉT$(‰L$,‰D$@‹E(‰D$<‹E$‰D$8‹E ‰D$4‹E‰D$01À‰D$$‹E‰D$ 1À‰D$1À‰D$‹E‰D$1À‰D$‹E‰D$ ‹E ‰D$‹C$‰D$‹‰$訉ƒÄD‰Ð[]ÃU¸‰åƒìX‹U…ÒtlEü‰D$8Eø‰D$4Eô‰D$0Eð‰D$,Eì‰D$(Eè‰D$$Eä‰D$ ‹E ‰D$‹E‰D$‹E‰D$‹E‰D$‹E‰D$ ‹E ‰D$‹B$‰D$‹‰$èò©ÉÃU¸‰åƒìX‹U…ÒtnEü‰D$8Eø‰D$4Eô‰D$0Eð‰D$,Eì‰D$(Eè‰D$$Eä‰D$ ‹E‰D$‹E‰D$¸‰D$‹E‰D$‹E‰D$ ‹E ‰D$‹B$‰D$‹‰$èp©Éô&¼'U¸‰åƒìH‹U‹M …Òtc‰L$(1À‰D$81À‰D$41À‰D$01À‰D$,¸¯‰D$$1À‰D$ ‹E‰L$‰D$‹E‰D$‹E‰D$‹E‰D$ ‹E ‰D$‹B$‰D$‹‰$èH¢ÉöU¸‰åƒìH‹U‹M …Òte‰L$(‹E4‰L$‰D$8‹E0‰D$4‹E,‰D$0‹E(‰D$,‹E$‰D$$1À‰D$ ‹E‰D$‹E‰D$‹E‰D$‹E‰D$ ‹E ‰D$‹B$‰D$‹‰$èÆ¡ÉÃt&U¸‰åƒìH‹U‹M…Òth‰L$(1À‰D$81À‰D$41À‰D$01À‰D$,¸¯‰D$$¸‰D$ ¸‰D$‹E‰L$‰D$‹E‰D$‹E‰D$ ‹E ‰D$‹B$‰D$‹‰$èC¡ÉÃU¸‰åƒìH‹U‹M…Òtj‰L$(‹E0‰L$‰D$8‹E,‰D$4‹E(‰D$0‹E$‰D$,‹E ‰D$$¸‰D$ ¸‰D$‹E‰D$‹E‰D$‹E‰D$ ‹E ‰D$‹B$‰D$‹‰$èÁ ÉÃë U‰åƒì8‰}ü‹} ‰]ô‹]‰uø‹uÇEèÇEä‰<$è’–ƒÀP‰D$ ¸‰D$1À‰D$Eð‰$èÁm…À…ЋUðöà ‰U섚‹F‹P(‹@,‰Uè‰EäƒãûöÄ•ÿF‹F…Àth‹F…ÀtPöÄ͉|$ öø¯uöø#¯u¸+¯‰D$¹,¯‰L$‹Eì‰$èP”‹F‰D$‹Eì‰$è®”1ÀUð‰D$‰$è]m‹]ô‹uø‹}ü‰ì]ÃöÃt[‹F‹V ‰Eè‰Uäé_ÿÿÿöÄeÿÿÿÿFé]ÿÿÿ‹FÇ$@¯‰D$ ¸ ‰D$¸‰D$è$”‹]ô‹uø‹}ü‰ì]ô&ƒËéÿÿÿ‹U䉨Áè…Ò” ШtB‰|$‹Eè@‰D$ öø¯uöø#¯u¸+¯‰D$¹d¯‰L$‹Uì‰$èh“éÿÿÿ‰|$‹Eä‰D$‹Eè@‰D$ öø¯uöø#¯u¸+¯‰D$º„¯‰T$‹Uì‰$è“éÊþÿÿv¼'Uº©¯‰åƒì‹E‰T$‰D$¡XôƒÀ@‰$èÚ’Éô&U¹Á¯‰åƒì‹E‰L$‰D$¡XôƒÀ@‰$誒Éô&U‰åƒì‰]ø‹] ‰uü‹u‰\$‰4$è"éÿÿ…Àu‹]ø1À‹uü‰ì]Éö‰\$‰4$èÏÿÿ…Àtâ‹]ø‹uü‰ì]öU‰åƒì‰]ø‹]‰uü‹u ‰$‰t$èÒéÿÿ…Àu1À‹]ø‹uü‰ì]Éö‰$Eô‰D$èaíÿÿ…Àt‰$¸×¯‰D$è\ÿÿÿ…Àủt$‰$èŒÑÿÿ…Àtº‹]ø‹uü‰ì]ô&¼'U‰åƒì(‰]ô‹]Eð‰}ü‹} ‰uø‰D$‰$è<îÿÿ…ÀtÇEð‰$uì‰t$èòÒÿÿ…ÀtÇEì‰|$‰$è»éÿÿ…Àu1À‹]ô‹uø‹}ü‰ì]Ét$‰$è¼Òÿÿ…Àuã‰|$‰$èŒÓÿÿ…ÀuÓ‹Eð;EìsɉD$‰$èdçÿÿ…Àu»ë·´&¼'U‰åƒì‰]ô‹E ‹]‰uø‹u‰}ü‹}‰D$‰$è)ÿÿÿ…Àu‰|$‰$è¹îÿÿ1Ò…Àt‰t$‰$è'ïÿÿ…À‰Ât‹]ô‰Ð‹uø‹}ü‰ì]Éö‰} ‹uø‹}ü‰]‹]ô‰ì]éyîÿÿ‰ö¼'U‰åƒì‰]ô‹E ‹]‰uø‹u‰}ü‹}‰D$‰$è©þÿÿ…Àu‰|$‰$èyñÿÿ1Ò…Àt‰t$‰$èòÿÿ…À‰Ât‹]ô‰Ð‹uø‹}ü‰ì]Éö‰} ‹uø‹}ü‰]‹]ô‰ì]é9ñÿÿ‰ö¼'U‰åVSƒì ‹]ÝE‹E ‹uÝ]ð‰D$‰$è-þÿÿ…Àu‰t$‰$èMñÿÿ1Ò…ÀtÝEð¸Þ¯‰D$‰$Ý\$è¿ñÿÿ…À‰Ât ƒÄ ‰Ð[^]Éu ‰]ƒÄ [^]éñÿÿë U‰å‹EÇ`ñ1À]ÃU‰å‹EÇyñ1À]ÃU‰å‹EÇ’ñ1À]ÃU‰å‹E…Àt‹P‹E ‰1À…Òu¸@]ÃU¸‰åƒì‰]ø‹]‰uü‹u …Ût‹C…ÀuÿF 1À‰s‹]ø‹uü‰ì]É$è4Çÿÿ…Àtâ‹]ø‹uü‰ì]öUº‰åƒì‰]ø‹]‰uü‹u …Ût‰t$‰$èiÿÿÿ1Ò…Àu‹]ø‰Ð‹uü‰ì]ô&C‰$èåÅÿÿ…À‰ÂuÜ‹C‰‹]ø‰Ð‹uü‰ì]ô&¼'U¸‰åì‰]ô‹]‰uø1ö…Û‰}ü‰µÿÿÿ„æ‹E‰$è ‰ÆƒþP¸Ë…$ÿÿÿ‰D$‹E‰$è&êÿÿ…À…®‹½$ÿÿÿ‰<$èЉÃûP¸‰|$½(ÿÿÿ‰<$讎¸ble)¹(hasºh_ta‰„+0ÿÿÿ1À‰Œ+(ÿÿÿ‰”+,ÿÿÿˆ„+4ÿÿÿ‹E]ˆ‰$‰D$èoޏ(has‰D.ˆ¸h_ne‰D.Œ¸xt)‰D.… ÿÿÿ‰D$‹E ‰$è“…Àtt&¼'‹]ô‹uø‹}ü‰ì]Ãv‹E‰D$‹E‰$èŽûÿÿ…ÀuÚ‹E…Àˆ—‹E‰D$‹E‰$èmãÿÿ…Àu¹…ÿÿÿ‰D$‹E‰$èôêÿÿ…Àu‹µÿÿÿ…ö…j‹U…ÒˆO‹E‰D$‹E‰$è%ãÿÿ…À…mÿÿÿ‹E ‰D$‹E‰$è+ëÿÿ…À…Sÿÿÿ…ÿÿÿ‰D$‹E‰$èNéÿÿ…À…6ÿÿÿ‰\$‹E‰$è×úÿÿ…À…ÿÿÿ¸ÿÿÿÿ‰D$‹E‰$è;îÿÿ…À…ÿÿÿ‰|$‹E‰$è$úÿÿ…À…ìþÿÿ‰\$‹E‰$èúÿÿ…À…Õþÿÿ…ÿÿÿ‰D$‹E‰$è Íÿÿ…À…¸þÿÿ‹… ÿÿÿ‹•ÿÿÿ@9Âs1‰•ÿÿÿ‹E‰$è¶Ïÿÿ…À…Žþÿÿ‹•ÿÿÿ‹… ÿÿÿB‰•ÿÿÿ@9ÂrÕ‰\$‹E‰$è'äÿÿ…À…_þÿÿ‹… ÿÿÿ‰D$‹E‰$èúáÿÿ…À…Bþÿÿ…ÿÿÿ‰D$‹E‰$è½ìÿÿ…À…†‹•ÿÿÿƒúÿ„w‹…ÿÿÿ9Ð}‰D$‹E‰$è-íÿÿ…À…õýÿÿ‹…$ÿÿÿ‰D$‹E‰$èãÿÿ…À…Øýÿÿ‰\$‹E‰$è‰ãÿÿ…À…Áýÿÿ‹•ÿÿÿ‹…ÿÿÿ9ˆ…Òxg ÿÿÿ‰T$‹E‰$èDáÿÿ…À…Œýÿÿ‰\$¸ÿÿÿÿ‰… ÿÿÿ‹E‰$èìÿÿ…À…Ž‹… ÿÿÿ…Àˆ€‹•ÿÿÿ9Ðx‰…ÿÿÿ…À‰ÂyŸ¸@é8ýÿÿ‹E‰$èMÎÿÿé³ýÿÿ‰\$‹E‰$èÙâÿÿ…À…ýÿÿ…ÿÿÿ‰D$‹E‰$èŒëÿÿ…À…býÿÿ…ÿÿÿ‰D$‹E ‰$èï…À…×üÿÿ‹…ÿÿÿ9… ÿÿÿ„3ýÿÿ‰|$‹E‰$èæ÷ÿÿ…À…®üÿÿ‰\$‹E‰$èOøÿÿ…À…—üÿÿ‹…ÿÿÿ‰D$‹E‰$è2àÿÿ…À…züÿÿ…ÿÿÿ‰D$‹E‰$èõêÿÿ…À…Ëüÿÿ‹E9…ÿÿÿ„P‹…$ÿÿÿ‰D$‹E‰$èYáÿÿ…À…1üÿÿ‰\$‹E‰$èâáÿÿ…À…üÿÿ‹•ÿÿÿ…Òˆzüÿÿ;U„qüÿÿ‰T$‹E‰$è¤ßÿÿ…À…ìûÿÿ… ÿÿÿ¹ÿÿÿÿ‰D$‹E‰ ÿÿÿ‰$è\êÿÿ…À…2üÿÿ‹… ÿÿÿ;…ÿÿÿŽ üÿÿ;E„«‰…ÿÿÿ‰Âë‹‹…ÿÿÿ‰D$‹E‰$èºêÿÿ…À…‚ûÿÿ‹…$ÿÿÿ‰D$‹E‰$èàÿÿ…À…eûÿÿ‰\$‹E‰$èáÿÿ…À…Nûÿÿ‹…ÿÿÿ‰D$‹E‰$èéÞÿÿ…À…1ûÿÿ¸ÿÿÿÿ‰D$‹E‰$èMêÿÿ…À…ûÿÿ‹E‰D$‹E‰$èÃàÿÿéþúÿÿ‹…ÿÿÿ‰D$‹E‰$èêÿÿ…À…áúÿÿéJûÿÿ‹•ÿÿÿ‰T$‹E‰$è÷éÿÿ…À…¿úÿÿ‹…ÿÿÿ‰D$‹E‰$èZÞÿÿ…À…¢úÿÿ‹… ÿÿÿ…Àx;…ÿÿÿ~‰D$‹E‰$è±éÿÿ…À…yúÿÿ‰\$‹E‰$èúèÿÿ…Àt¸ÿÿÿÿ‰D$‹E‰$è‚éÿÿ…À…Júÿÿ‹E‰D$‹E‰$èøßÿÿ‰Â1À…Ò„,úÿÿ‰Ðé%úÿÿ‰D$‹E‰$èÆÝÿÿ…À…úÿÿ‹…ÿÿÿ;…ÿÿÿ~‰D$‹E‰$è!éÿÿ…À…éùÿÿ… ÿÿÿ‰D$‹E‰$èdèÿÿ…À„·þÿÿé–þÿÿ´&U¸‰åìh‹U‰]ô‰uø…Ò‰}ütr‹E‰$èLj‰ÇƒÿP¸[…Äþÿÿ‰D$‹E‰$èæâÿÿ…ÀuB‹…Äþÿÿ‰$蔈‰ÆƒþP¸(…Àþÿÿ‰D$‹E ‰$èSŒ…Àtë ‹]ô‹uø‹}ü‰ì]Ãv‹…Àþÿÿ(ÿÿÿ‰D$¸¯‰D$…Èþÿÿ‰$艆‰$‹…Äþÿÿ‰D$臸(has1ɉ„.(ÿÿÿ¸h_ta‰„.,ÿÿÿ¸ble)ˆŒ.4ÿÿÿ‰„.0ÿÿÿ‹Euˆ‰4$‰D$èØ†‰\$¸h_neº(has‰D/Œ¸xt)‰T/ˆ‰D/‹E‰$è®óÿÿ…À…Fÿÿÿ‰t$‹E‰$èôÿÿ…À…/ÿÿÿ…¼þÿÿ‰D$‹E‰$è*Çÿÿ…À…ÿÿÿ‹Àþÿÿ‹•¼þÿÿA9Âs3‰•¸þÿÿ‹E‰$è>Éÿÿ…À…æþÿÿ‹•¸þÿÿ‹ÀþÿÿB‰•¸þÿÿA9ÂrÓ‰L$‹E‰$èÛÿÿ…À…*‹E½¸þÿÿ‰|$‰$è`æÿÿ…À… ‹…¸þÿÿ…Àˆÿ‹…Äþÿÿ‰D$‹E‰$èÅÜÿÿ…À…mþÿÿ‹…¸þÿÿ…ÀˆÔ´þÿÿëO‰\$‹E‰$èÈâÿÿ…À„ö‰t$‹E‰$è!Ýÿÿ…À…)þÿÿ‰|$‹E‰$èÚåÿÿ…À…‡‹…¸þÿÿ…Àx}‹E‰D$‹E‰$èæÜÿÿ…À…îýÿÿ‹…¸þÿÿ‰D$‹E‰$è¹Úÿÿ…À…Ñýÿÿ‹E…À…oÿÿÿ‰\$‹E‰$è7âÿÿ…À…oÿÿÿ‹E ‰D$‹…´þÿÿ‰$è ……À…Rÿÿÿ1Àé‹ýÿÿ‹…Äþÿÿ‰D$‹E‰$èÆÛÿÿ…À…nýÿÿ‹E‰D$‹E‰$èLÜÿÿ…À…Týÿÿ¸@éJýÿÿ‹E ‰D$‹…´þÿÿ‰$èu]…À…íþÿÿé(ýÿÿ´&U‰åƒì‰]ø‹E ‹]‰uü‹u‰D$‰$èïÛÿÿ…Àt ‹]ø‹uü‰ì]Ét$‰$è¤äÿÿ…Àt Ç‹uü‰]‹]øÇE ‰ì]é"åÿÿ‰ö‹@‰‹uü‰]‹]ø‰E ‰ì]éåÿÿ´&U‰åƒì‰]ø‹]‰uü‹u ‰$‰t$èrÛÿÿ…Àt‰u ‹uü‰]‹]ø‰ì]éZÅÿÿ‰$èÒÎÿÿ…Àtà‹]ø‹uü‰ì]Ãt&U¸@‰åWVSƒì‹U ‹}…ÒtI‰$èÐvƒ8‰E tN‹p1Û9ór ë6C9ós1‹E ‹U‰|$‰T$ ‹@‹˜‰D$‹E‰$è¥ÿÿÿ…ÀuÔ1ÀƒÄ[^_]Ãĸ@[^_]ËP…ÒuT€?t‹H…Étà‰|$‹@‰$èø[…ÀuÍ‹E ‹U‰D$E ‰T$‰$è›v…Àu¨‹U‹E ÇB$‰ÇB(뎀:_u¬ë¥´&U‰åWVSìì‹E‹] …À”À…Û” Шº…À‰$胃øPº‡ª1À€;_”ÀÉ$¸.‰D$胅À‰Æ„‰Ç)ß…àÆD/ˆ‰$èSƒÆ…(ÿÿÿ_؉Ã)󅕃ÿ¿ƒÓ1Àˆ„+(ÿÿÿ$ÿÿÿ‰|$‹U‹‰$‰D$èQz…Àu5…(ÿÿÿ‰D$ Eˆ‰D$‹…$ÿÿÿ‰D$‹E‰$è7þÿÿ‰ÂÄì‰Ð[^_]þ‰t$‹U‹‰$‰D$èþy…À‰Ât«Äì‰Ð[^_]É\$F‰D$1À…ÿ”À„(ÿÿÿ‰$èzéEÿÿÿt&‰|$Eˆ‰\$‰$è]éÿÿÿsÿ1ÿéþþÿÿ´&¼'U1À‰åWV1öS윋] ‰…Œþÿÿ‹‰$‰…tþÿÿ‰…”þÿÿ¸ä¯‰D$èHþÿÿ…Àt‰$¸ê¯‰D$è3þÿÿ…À…¿…äþÿÿ‰½Œþÿÿ‹;‰D$‰$‰½”þÿÿèfÜÿÿ…Àu" µŒþÿÿt*‰$…àþÿÿ‰D$èhÁÿÿ…À„õÄœ[^_]Ãt&‹½tþÿÿ¸õ¯‰;‰D$‰$è·ýÿÿ…À„ï‰$¸ °‰D$èžýÿÿ…À„Ö‹½tþÿÿ¸°‰;‰D$‰$è}ýÿÿ…À…%‰$…¼þÿÿ‰D$è3Üÿÿ…À…{ÿÿÿ‰$…àþÿÿ‰D$èÉÀÿÿ…À…aÿÿÿ‰$è)Îÿÿ…À…Qÿÿÿ¸.°‰D$‹E‰$èíìÿÿ…À…5ÿÿÿ1ÿ1À;½àþÿÿ‰…þÿÿȉ$‹…þÿÿ‰D$è=Õÿÿ…À…ÿÿÿ‰$‹…¼þÿÿ‰D$è³Ôÿÿ…À…ëþÿÿ‰$…¸þÿÿ‰D$è©Üÿÿ…À…Ñþÿÿ‹…Œþÿÿ…Àu3‰$¿A°‰|$èöÖÿÿ…À…®þÿÿ‰$…Üþÿÿ‰D$èlÜÿÿ…À…”þÿÿ‰$¹F°¾N°‰µ˜þÿÿ‰L$è¸Öÿÿ…À…܉$…´þÿÿ‰D$è.Üÿÿ…À…Vþÿÿ‹½¸þÿÿ…ÿ‰½ˆþÿÿ„¡ ‹µ´þÿÿ…ö„“ ‰<$è܉…„þÿÿ‰4$è΋•„þÿÿÐ=þ‡j ‰t$‰<$è¿~…Àt ¹[°‰˜þÿÿ‹…ˆþÿÿ½èþÿÿ‰<$‰D$èˆ~‹…¸þÿÿ‰$èz²:ˆ”(èþÿÿ‹…¸þÿÿ‰$èc”éþÿÿ‹…´þÿÿ‰$‰D$èJ~‰½¸þÿÿ¸ÿÿÿÿ‹}‰D$ ¸A°‰D$‹…Üþÿÿ‰<$‰D$èÝîÿÿ…À…eýÿÿ‰<$¸f°‰D$è„ëÿÿ…À…Lýÿÿ‰<$‹…¸þÿÿ‰D$èŠÛÿÿ…À…2ýÿÿ‰<$¸l°‰D$èQëÿÿ…À…ýÿÿ‰<$‹…˜þÿÿ‰D$èWÛÿÿ…À…ÿüÿÿÿ…þÿÿ‹½þÿÿ;½àþÿÿŒÈýÿÿ鋉ö‰$…¼þÿÿ‰D$è~Ùÿÿ…À…Æüÿÿ‰$…àþÿÿ‰D$è¾ÿÿ…À…¬üÿÿ‰$ètËÿÿ…À…œüÿÿ¸.°‰D$‹E‰$è8êÿÿ…À…€üÿÿ1ÿ1À;½àþÿÿ‰…þÿÿ´üÿÿ‰$‹…þÿÿ‰D$èˆÒÿÿ…À…Püÿÿ‰$‹…¼þÿÿ‰D$èþÑÿÿ…À…6üÿÿ‰$…¸þÿÿ‰D$èôÙÿÿ…À…üÿÿ‹…Œþÿÿ…Àu3‰$¸A°‰D$èAÔÿÿ…À…ùûÿÿ‰$…Üþÿÿ‰D$è·Ùÿÿ…À…ßûÿÿ¿ÿÿÿÿ‹…Üþÿÿ¾A°‰|$ ‹}‰t$‰D$‰<$è(íÿÿ…À…°ûÿÿ‰<$¹f°‰L$èÏéÿÿ…À…—ûÿÿ‰<$‹…¸þÿÿ‰D$èÕÙÿÿ…À…}ûÿÿ‰<$ºl°‰T$èœéÿÿ…À…dûÿÿ‰<$¸f°‰D$è£Ùÿÿ…À…Kûÿÿÿ…þÿÿ‹…þÿÿ;…àþÿÿŒÉþÿÿéxûÿÿ‰$¹w°‰L$è½Òÿÿ…À…óúÿÿ¾ééúÿÿ‰$èÓÉÿÿ…À…ûúÿÿ1Ò‰•þÿÿéï‹E‰…Üþÿÿ‰D$‹}¹‰L$ ºA°‰T$‰<$è„óÿÿ…Àt,‰<$¸ÿÿÿÿ‰D$ ¸A°‰D$‹…Üþÿÿ‰D$è ìÿÿ…À…”úÿÿ‹}…Øþÿÿ‰D$‰<$è×ÿÿ…À…wúÿÿ‰$¾|°‰t$è¦Òÿÿ…Àt‰$¹ˆ°‰L$è‘Òÿÿ…À…ɉ$‹…þÿÿ‰D$ègÐÿÿ…À…/úÿÿ‰$…Ôþÿÿ‰D$èí×ÿÿ…À„•‹½”þÿÿ¸’°‰;‰D$‰$è<Òÿÿ…Àu4‰$‹…þÿÿ‰D$èÐÿÿ…À…Þùÿÿ‰$…Ìþÿÿ‰D$èœ×ÿÿ…À„‹…tþÿÿ¿¡°‰‰|$‰$è‹÷ÿÿ…Àt‰$¾§°‰t$èv÷ÿÿ…Àu‰$…Èþÿÿ‰D$èP×ÿÿ…À„€‹…tþÿÿº·°‰‰T$‰$è?÷ÿÿ…Àt‰$¸Ì°‰D$è*÷ÿÿ…Àu‰$…Äþÿÿ‰D$è×ÿÿ…À„o‹…tþÿÿ‰¸à°‰D$‰$èóöÿÿ…À„«ÿ…þÿÿ‹…þÿÿ;…àþÿÿùÿÿ¿ù°‰|$‹}‰<$èæÿÿ…À…×øÿÿ‹µŒþÿÿ…ö„Ûýÿÿ‰$‹…äþÿÿ‰D$è÷Ðÿÿ…À…Áýÿÿ‰$‹…þÿÿ‰D$èÍÎÿÿ…À…•øÿÿ‰$…Üþÿÿ‰D$èSÖÿÿ…À…{øÿÿ‹…Üþÿÿé‹ýÿÿ‰$¸ÿ°‰D$è?öÿÿ…À„Âøÿÿ‹…tþÿÿ‰¸±‰D$‰$èöÿÿ…Àt‰$¸+±‰D$è öÿÿ…À…O‰$…àþÿÿ‰D$èo¹ÿÿ…À…øÿÿ‰$èÏÆÿÿ…À…÷÷ÿÿ1ÿ‰½þÿÿ1ÿ;½àþÿÿ‹E¾ù°‰t$‰$è}åÿÿ…À…Å÷ÿÿ‰$‹½þÿÿ‰|$èãÍÿÿ…À…«÷ÿÿ‰$1ɺ=±‰°þÿÿ‰T$èÒÏÿÿ…Àt‰$¸I±‰D$è½Ïÿÿ…Àu‰$…°þÿÿ‰D$è7Õÿÿ…Àt1À‰…°þÿÿ‰$1À‰…¬þÿÿ¸[±‰D$è‚Ïÿÿ…Àt‰$¸f±‰D$èmÏÿÿ…Àu‰$…¬þÿÿ‰D$èçÔÿÿ…Àt1À‰…¬þÿÿ‹•àþÿÿƒú„<‹µ°þÿÿ…öt‹…¬þÿÿ…À…|ÿ…þÿÿ9•þÿÿŒñþÿÿ‹…tþÿÿ‰¸ˆ°‰D$‰$è™ôÿÿ…Àt‰$¸w±‰D$è„ôÿÿ…À….‰$…àþÿÿ‰D$èê·ÿÿ…À…‚öÿÿ‰$èJÅÿÿ…À…röÿÿ‹;1À‰½”þÿÿ1ÿ;…àþÿÿ‰½þÿÿæ‹}¾„±‰t$‰<$èðãÿÿ…À…8öÿÿ‹…”þÿÿ‹½þÿÿ‰‰|$‰$èNÌÿÿ…À…öÿÿ‰$…Ðþÿÿ‰D$èÔÓÿÿ…À…üõÿÿ‹…Ðþÿÿ¹º±‰L$ ‰T$‰D$‹E‰$è•îÿÿ…Àt/¸ÿÿÿÿ‹}‰D$ ¸±‰D$‹…Ðþÿÿ‰<$‰D$èçÿÿ…À…¢õÿÿ‰$1À‰…¨þÿÿ¸’±‰…Ìþÿÿ¸’°‰D$è¾Íÿÿ…Àu‰$…Ìþÿÿ‰D$è8Óÿÿ…À„Ç‹…tþÿÿ¿•±‰‰|$‰$è'óÿÿ…Àt‰$¾¥±‰t$èóÿÿ…Àu$‰$…¨þÿÿ‰D$èìÒÿÿ…Àu‹¨þÿÿ…É…¯‹E¿ù°‰|$‰$è¦âÿÿ…À…îôÿÿ‹}¾A°‰t$‰<$è ãÿÿ…À…Òôÿÿ‹…¨þÿÿ…À„‰D$¹ºA°‰L$ ‰T$‰<$èfíÿÿ…À„®‰<$‹…¨þÿÿ¹A°‰L$¾ÿÿÿÿ‰t$ ‰D$èêåÿÿ…À…rôÿÿ‰<$º’°‰T$è‘âÿÿ…À…Yôÿÿ‰<$¸¸±‰D$è˜Òÿÿ…À…@ôÿÿ‹}…Øþÿÿ‰D$‰<$è»Ðÿÿ…À…#ôÿÿ‰<$¸|°‰D$èBâÿÿ…À… ôÿÿ‰<$…œþÿÿ‰D$èÈÑÿÿ…Àu‹…œþÿÿ…Àtüº¼±¹‰Æ‰×ó¦u0‹…Øþÿÿ‰D$ ¸|°‰D$‹…Ðþÿÿ‰D$‹E‰$èåÿÿ…À…§óÿÿ‹½tþÿÿ‰;¿¾±‰|$‰$ènñÿÿ…À„¶ÿ…þÿÿ‹…þÿÿ;…àþÿÿŒýÿÿ1Àégóÿÿ´&‰$…Àþÿÿ‰D$èÑÿÿ…À…;úÿÿ‹}¸Û±‰D$‰<$èÒÊÿÿ…À…*óÿÿ‰<$¸‰D$ ¸è±‰D$‹…Àþÿÿ‰D$èÆëÿÿ…Àt,‰<$‹…Àþÿÿ¹è±‰L$¾ÿÿÿÿ‰t$ ‰D$èNäÿÿ…À…Öòÿÿ‹}…Øþÿÿ‰D$‰<$èQÏÿÿ…À…¹òÿÿ‰<$‹…Øþÿÿºó±‰T$‰D$ ‹…Üþÿÿ‰D$èäÿÿ…À„ùÿÿé‡òÿÿ´&‹}º|°‰T$‰<$è¬Êÿÿ…À…dòÿÿ…Ðþÿÿ‰D$‰<$è"Ðÿÿ…Àu!‹…Ðþÿÿ…Àtüº¼±¹‰Æ‰×ó¦…øÿÿ‹…Øþÿÿ‰D$ ¸|°‰D$‹…Ôþÿÿ‰D$‹E‰$èuãÿÿ…À„è÷ÿÿéøñÿÿ‹}¹ý±‰L$‰<$è$Êÿÿ…À…Üñÿÿ‰<$‹…Èþÿÿ‰D$èÐÿÿ…À„Jøÿÿé½ñÿÿ‹}¸²‰D$‰<$èéÉÿÿ…À…¡ñÿÿ‰<$‹…Äþÿÿ‰D$èßÏÿÿ…À„[øÿÿé‚ñÿÿ‰ö‹½tþÿÿ¸ˆ°‰;‰D$‰$èGïÿÿ…Àt‰$¸²‰D$è2ïÿÿ…À…5÷ÿÿ‰$…Ôþÿÿ‰D$èÏÿÿ…À…÷ÿÿ¸|°‰D$‹E‰$è\Éÿÿ…À…ñÿÿ‹}…Ðþÿÿ‰D$é¨þÿÿ‹}¸’°‰D$‰<$è.Éÿÿ…À…æðÿÿ‰<$‹…Ìþÿÿ‰D$è$Ïÿÿ…À„÷ÿÿéÇðÿÿ´&‹½¬þÿÿ…ÿ…¶ùÿÿ‹…Üþÿÿ‰…¬þÿÿé¥ùÿÿ‹…Üþÿÿ¹'²º0²‰¸þÿÿ½èþÿÿ‰T$‰D$‰<$è…p‰<$èmÝÿÿéÔòÿÿ‰D$‹E¹‰L$ ºA°‰T$‰$èéÿÿ…Àt/¸ÿÿÿÿ‹}‰D$ ¸A°‰D$‹…¬þÿÿ‰<$‰D$èŒáÿÿ…À…ðÿÿ¸\²‰D$‹E‰$è@Èÿÿ…À…øïÿÿ‹…°þÿÿ‹}‰D$‰<$è3Îÿÿ…À…Ûïÿÿ‹•àþÿÿéìøÿÿ‰$…Àþÿÿ‰D$èŽÍÿÿ…À…0üÿÿ‹E¾c²‰t$‰$èBÇÿÿ…À…šïÿÿ‹…Àþÿÿ¹ºt²‰L$ ‹}‰T$‰D$‰<$è3èÿÿ…Àt,‰<$¸ÿÿÿÿ‰D$ ¸t²‰D$‹…Àþÿÿ‰D$è»àÿÿ…À…Cïÿÿ…Øþÿÿ‰D$‹E‰$è¾Ëÿÿ…À…&ïÿÿ‹…Øþÿÿ‹}‰D$ ¸ƒ²‰D$‹…Ðþÿÿ‰<$‰D$ènàÿÿ…À„pûÿÿéñîÿÿ¸’°‰D$‹E‰$è Ýÿÿ…À…Ôîÿÿ‹}…Ìþÿÿ‰D$‰<$èÌÿÿ…Àu‹…Ìþÿÿ…À…múÿÿ¸¸±‰D$‹E‰$éLúÿÿ¸’°‰D$‹E‰$èµÜÿÿ…À…}îÿÿ‹…Ìþÿÿ‹}‰D$‰<$è¸Ìÿÿ…À„ùÿÿé[îÿÿ‹}º‘²‰T$‰<$èwÜÿÿéÍ‹E½ þÿÿ‰|$‰$èýËÿÿ…Àu!‹… þÿÿ…Àtüº¼±¹‰Æ‰×ó¦„勵¨þÿÿ…öt‹… þÿÿ…Àt‰t$‰$è¨n…À„ø•²‰D$‹E‰$è Æÿÿ…À…Äíÿÿ‹}…¤þÿÿ‰D$‰<$è¿Îÿÿ…À…§íÿÿ‰<$¸‘²‰D$èÖÅÿÿ…À…Žíÿÿ‹…¤þÿÿ…Àx‰D$‹E‰$è¥Ãÿÿ…À„+ÿÿÿéhíÿÿ‰<$¸ÿÿÿÿ‰D$ ¸±‰D$‹…Ðþÿÿ‰D$è´Þÿÿ…À…<íÿÿ‰<$¸‘²‰D$èkÅÿÿ…À…#íÿÿ‹µ¨þÿÿ‰t$‹E‰$è^Ëÿÿ…À…íÿÿ‹}¸’°‰D$‰<$è"Ûÿÿ…À…êìÿÿ‰<$‹…Ìþÿÿ‰D$è(Ëÿÿ…À„Æ÷ÿÿéËìÿÿt&¼'U‰åWVSìì‹U‹u …Ò”À…ö” Шº……‰4$è=nƒøPºws1À€>_”ÀƉ4$¸.‰D$è¸m…À‰Ã„ΉÇ)÷…§ÆD/ˆ‰4$è÷mð‰Æ)Þut1Àˆ„.(ÿÿÿ¸‰D$‹U‹‰D$…$ÿÿÿ‰$èe…À‰ÂtÄì‰Ð[^_]Ãv…(ÿÿÿ‰D$ Eˆ‰D$‹…$ÿÿÿ‰D$‹E‰$èÚèÿÿÄì‰Â‰Ð[^_]Ét$C‰D$…(ÿÿÿ‰$èRlénÿÿÿ‰|$Eˆ‰t$‰$è:léAÿÿÿt&^ÿ1ÿé2ÿÿÿ¶U‰åSƒì‹]…Ût‰$¸£²‰D$è¡þÿÿ…Àt 1ÀƒÄ[]Ãt&‰$¸¯²‰D$èïçÿÿ…Àuà‰$¸Â²‰D$èÚçÿÿ…Àuˉ$¸Ô²‰D$èÅçÿÿ…Àu¶‰$¸é²‰D$è°çÿÿ…Àu¡‰$¹û²‰L$è›çÿÿ…ÀuŒëˆt&U‰åƒì(ƒ}‰]ô‹]‰uø‹u‰}ü‹}„ãþÿÿË…ÿ¸„Â÷Æ…É÷Æt!÷Æ…Å÷Æ…¹‰ö¼'÷Æt÷Æ…œ÷Æ…÷À…¤1ÉöÕÁ1ÒöÃ@•ÂÊ1ÉöÕÁÑ1Òöà •ÂÊ1ÉöÕÁÑ1ÀöÕÀÈöÃt@HAº‰T$‹‰D$Eð‰$è×b…ÀtS‹]ô‹uø‹}ü‰ì]ö÷Æ„+ÿÿÿt&¸‹]ô‹uø‹}ü‰ì]Ããþéôþÿÿ¶öÇ„Sÿÿÿ¸ëÕ‹E ‰D$Eì‰$è.…Àu—÷Æ…µ÷Æ„©÷Æ…•÷Æ„‰÷ÆtƒÎöÃuƒËöÇuË÷ÀuË€‹Eì‰pD‰XH‹G‰$èŠýÿÿ…À…ÿÿÿ‹E‰D$ ‹Eì‰D$‹Eð‰<$‰D$èU[‰Ã‹E…Àu ‹EìÇEì‰$踂 ØéÞþÿÿƒÎéoÿÿÿƒÎéOÿÿÿU‰åìx‰]ô‹M‹] ‰uø…É”À‰}ü…Û” Шºu‰ $…äþÿÿ‰D$èqÙÿÿ…À‰Ât‹]ô‰Ð‹uø‹}ü‰ì]ø³‰D$‹…äþÿÿ‰$è¥Õÿÿ…À‰ÂuÔ¸³‰D$‹…äþÿÿ‰$èØÕÿÿ…À‰Âu·¸<³‰D$‹…äþÿÿ‰$è;Öÿÿ…À‰Âuš¸U³‰D$‹…äþÿÿ‰$èÖÿÿ…À‰Â…yÿÿÿ‹…äþÿÿ¿c²‰|$‰$è}Õÿÿ…À‰Â…Xÿÿÿ‹…äþÿÿ¾ƒ²‰t$‰$èÜÕÿÿ…À‰Â…7ÿÿÿ‹…äþÿÿ¹t²‰L$‰$è»Õÿÿ…À‰Â…ÿÿÿ‹…äþÿÿº<³‰T$‰$èšÕÿÿ…À‰Â…õþÿÿ¸U³‰D$‹…äþÿÿ‰$èyÕÿÿ…À‰Â…Ôþÿÿ¸o³‰D$‹…äþÿÿ‰$èØÔÿÿ…À‰Â…³þÿÿ¸ˆ³‰D$‹…äþÿÿ‰$è7Õÿÿ…À‰Â…’þÿÿ¸³‰D$‹…äþÿÿ‰$èÕÿÿ…À‰Â…qþÿÿ¸Û±‰D$‹…äþÿÿ‰$èuÔÿÿ…À‰Â…Pþÿÿ¸ó±‰D$‹…äþÿÿ‰$èÔÔÿÿ…À‰Â…/þÿÿ‹…äþÿÿ¿è±‰|$‰$è³Ôÿÿ…À‰Â…þÿÿ‹…äþÿÿ¾ˆ³‰t$‰$è’Ôÿÿ…À‰Â…íýÿÿ‹…äþÿÿ¹³‰L$‰$èqÔÿÿ…À‰Â…Ìýÿÿ‹…äþÿÿº³³‰T$‰$èÐÓÿÿ…À‰Â…«ýÿÿ¸•²‰D$‹…äþÿÿ‰$è/Ôÿÿ…À‰Â…Šýÿÿ¸„±‰D$‹…äþÿÿ‰$èŽÓÿÿ…À‰Â…iýÿÿ¸±‰D$‹…äþÿÿ‰$èíÓÿÿ…À‰Â…Hýÿÿ¸•²‰D$‹…äþÿÿ‰$èÌÓÿÿ…À‰Â…'ýÿÿ¸‘²‰D$‹…äþÿÿ‰$è«Óÿÿ…À‰Â…ýÿÿ¸Ê³‰D$‹…äþÿÿ‰$è Óÿÿ…À‰Â…åüÿÿ‹…äþÿÿ¿Ü³‰|$‰$èiÓÿÿ…À‰Â…Äüÿÿ‹…äþÿÿ¾ì³‰t$‰$èHÓÿÿ…À‰Â…£üÿÿ‹…äþÿÿ¹ù°‰L$‰$è§Òÿÿ…À‰Â…‚üÿÿ‹…äþÿÿºA°‰T$‰$èÓÿÿ…À‰Â…aüÿÿ¸Ü³‰D$‹…äþÿÿ‰$èåÒÿÿ…À‰Â…@üÿÿ¸ý±‰D$‹…äþÿÿ‰$èÄÒÿÿ…À‰Â…üÿÿ¸|°‰D$‹…äþÿÿ‰$è£Òÿÿ…À‰Â…þûÿÿ¸ì³‰D$‹…äþÿÿ‰$è‚Òÿÿ…À‰Â…Ýûÿÿ¸´‰D$‹…äþÿÿ‰$èaÒÿÿ…À‰Â…¼ûÿÿ¸’°‰D$‹…äþÿÿ‰$è@Òÿÿ…À‰Â…›ûÿÿ‹…äþÿÿ¿²‰|$‰$èÒÿÿ…À‰Â…zûÿÿ‹…äþÿÿ¾\²‰t$‰$èþÑÿÿ…À‰Â…Yûÿÿ‹…äþÿÿ¹´‰L$‰$è]Ñÿÿ…À‰Â…8ûÿÿ‹…äþÿÿºÜ³‰T$‰$è¼Ñÿÿ…À‰Â…ûÿÿ¸.°‰D$‹…äþÿÿ‰$èÑÿÿ…À‰Â…öúÿÿ¸A°‰D$‹…äþÿÿ‰$èzÑÿÿ…À‰Â…Õúÿÿ¸Ü³‰D$‹…äþÿÿ‰$èYÑÿÿ…À‰Â…´úÿÿ¸f°‰D$‹…äþÿÿ‰$è8Ñÿÿ…À‰Â…“úÿÿ¸l°‰D$‹…äþÿÿ‰$èÑÿÿ…À‰Â…rúÿÿ‰$è5¯ÿÿ…À‰Â…`úÿÿ‰$…àþÿÿ‰D$虼ÿÿ…À‰Â…Dúÿÿ1ÿ;½àþÿÿsK‰|$‰$èɵÿÿ…À…‰$…Üþÿÿ‰D$èϽÿÿ…À…è‰$…Øþÿÿ‰D$èU°ÿÿ…À„ŠGë­‹…äþÿÿ¿3´‰|$‰$èƒõÿÿ…À…¿…Èþÿÿ‰D$‹…äþÿÿ‰$胣ÿÿ…À‰Â…®ùÿÿ1Û;Èþÿÿƒ‹…äþÿÿ¾\²‰t$‰$è4ºÿÿ…Àua‰\$‹…äþÿÿ‰$è¸ÿÿ…À„žC뼉$…Ôþÿÿ‰D$èñ»ÿÿ…Àu ‹…Ôþÿÿ…Àu+‰\$‹…Üþÿÿ‰D$‹…äþÿÿ‰$è÷àÿÿ…À„2ÿÿÿ‰Âéùÿÿ‰$…Ðþÿÿ‰D$èv¼ÿÿ…Àuã1ö;…Ðþÿÿƒÿÿÿ‰t$…Øþÿÿ‰D$‰$èž¶ÿÿƒ½Øþÿÿ„ÜF;µÐþÿÿëÎ…Äþÿÿ‰D$‹…äþÿÿ‰$èð¾ÿÿ…À…Bÿÿÿ‹…Äþÿÿ…À„4ÿÿÿ‰D$‹…äþÿÿ¹‰L$ ºA°‰T$‰$è¦Ùÿÿ…À…ÿÿÿ…Àþÿÿ‰D$‹…äþÿÿ‰$èV½ÿÿ…À…/ÿÿÿ¸ý±‰D$‹…äþÿÿ‰$èç¸ÿÿ…À…ÿÿÿ…¼þÿÿ‰D$‹…äþÿÿ‰$èW¾ÿÿ…À…©þÿÿ‹…¼þÿÿ…À„›þÿÿ‰\$‹…äþÿÿ‰$è¶ÿÿ…À…Èþÿÿ…¸þÿÿ‰D$‹…äþÿÿ‰$è¾ÿÿ…Àt1À‰…¸þÿÿ‹…¼þÿÿ‰D$‹…äþÿÿ‰$èk¾ÿÿ…À…„þÿÿ‹•¸þÿÿ…Ò„/þÿÿ‰$‹…¼þÿÿ‰D$èƒ9…À…þÿÿ¸A°‰D$‹…äþÿÿ‰$è¸ÿÿ…À…=þÿÿ…´þÿÿ‰D$‹…äþÿÿ‰$脽ÿÿ…À…Öýÿÿ‹…´þÿÿ‰D$ ‹…¸þÿÿ‰D$¸D´‰D$…èþÿÿ‰$è‘_é¦ýÿÿÇ$f´èa…ÀuJ1Òéúöÿÿ‰$…Ìþÿÿ‰D$èóºÿÿ…À…¼ýÿÿ‰\$‹…Ìþÿÿ‰D$‹…äþÿÿ‰$èÞÿÿ…À„æýÿÿé“ýÿÿ¡Xô1É1ÿ‰|$1ö1Û‰t$ƒÀ@‰D$‹…äþÿÿ‰\$ ‰L$‰$èôÿÿ…À‰Â…{öÿÿéuÿÿÿU‰åƒì(‰]ô‹M‹] ‰}ü…ɉuø”À…Û”‹} Шu8…ÿt4‹q¸@…öt€;_t5‰4$¹s´‰L$èÒñÿÿ…Àtn‹]ô‹uø‹}ü‰ì]Ë]ô¸‹uø‹}ü‰ì]É4$¸£²‰D$èñÿÿ…Àu"‰\$¸‰D$ ¸A°‰D$‰4$èûÖÿÿ…Àtw¸@‹]ô‹uø‹}ü‰ì]Ãt&‰4$èè¬ÿÿ…Àu†‰\$º¸Ž´‰T$ ‰D$‰4$è¶Öÿÿ…À…`ÿÿÿ‰4$¸—´‰D$è¶ÿÿ…À…Gÿÿÿ‰|$‰4$è™»ÿÿé6ÿÿÿt&‰4$»|°‰\$èïµÿÿ…À…pÿÿÿ‰4$Eð‰D$èh»ÿÿ…À…Yÿÿÿ‹]ð…Û…âþÿÿ¸@éIÿÿÿt&¼'U‰åƒì(‰}ü‹}‰]ô‹] …ÿ‰uø”À…Û” Ш…~‹M…Étw€;_‹wt(‹E‰\$‰<$‰D$èEþÿÿ…ÀuQ‹]ô1À‹uø‹}ü‰ì]Éö‰4$º£²‰T$è?ðÿÿ…Àu+‰\$¸‰D$ ¸A°‰D$‰4$èÕÿÿ…Àt"‰ö¼'‹E‰먋]ô¸‹uø‹}ü‰ì]É4$¸|°‰D$èæ´ÿÿ…ÀuÒ‰4$Eð‰D$ècºÿÿ…Àu¿‹Eð…Àt¸‰ÃéIÿÿÿU‰åVSƒì ‹M‹] ‹u…É”À…Û” Ш…Â…ö„º‰ $Eô‰D$èDÍÿÿ…À…œ‹Uô¸@…Ò„Œ‰$¹s´‰L$è[ïÿÿ…À…†‰\$¸‰D$ ¸Ž´‰D$‹Eô‰$è²Ôÿÿ…Àt.‰\$¸ÿÿÿÿ‰D$ ¸Ž´‰D$‹Eô‰$è=Íÿÿ…Àu)‰ö¼'Eð‰D$‹Eô‰$è>¸ÿÿ…Àtjv¼'ƒÄ [^]ÃƒÄ ¸[^]úŸ´‰T$‹Eô‰$èÙÈÿÿ…ÀuÕ¸c²‰D$‹Eô‰$èÉÿÿ…Àu½¸Ž´‰D$‹Eô‰$èyÉÿÿ…Àu¥é-ÿÿÿ‹Eð»—´‰\$‰t$‰D$ ‹Eô‰$è‘Ìÿÿé|ÿÿÿ¶¿U‰åƒì(‰uø‹M‹u ‰}ü…ɉ]ô”À…ö”‹} Шu]…ÿtY‹Yº@…Ût>‰$¸à°‰D$èîÿÿ…Àº@u$‰t$¸‰D$ ¸ª´‰D$‰$è`Óÿÿ…À‰Ât*‹]ô‰Ð‹uø‹}ü‰ì]Ë]ôº‹uø‹}ü‰ì‰Ð]ô&‰$¾µ´‰t$蟲ÿÿ…À‰Âu¿‰} ‹uø‹}ü‰]‹]ô‰ì]é¸ÿÿ‰öU‰åƒì‰uü‹M‹u ‰]ø…É‹]”À…ö” Шu/…Ût+‰\$‰t$‰ $è÷þÿÿ…Àu‹]ø1À‹uü‰ì]ô&‰3ëé‹]ø¸‹uü‰ì]ö¼'U‰åVSƒì ‹M‹] ‹u…É”À…Û” Ш…Â…ö„º‰ $Eô‰D$è”Êÿÿ…À…œ‹Uô¸@…Ò„Œ‰$¸à°‰D$è«ìÿÿ…À…†‰\$¹ºª´‰L$ ‰T$‹Eô‰$èÒÿÿ…Àt.‰\$¸ÿÿÿÿ‰D$ ¸ª´‰D$‹Eô‰$èÊÿÿ…Àu)‰ö¼'Eð‰D$‹Eô‰$莵ÿÿ…Àtjv¼'ƒÄ [^]ÃƒÄ ¸[^]øŸ´‰D$‹Eô‰$è)Æÿÿ…ÀuÕ¸Û±‰D$‹Eô‰$èaÆÿÿ…Àu½¸ª´‰D$‹Eô‰$èÉÆÿÿ…Àu¥é-ÿÿÿ‹Eð‰t$‰D$ ¸µ´‰D$‹Eô‰$èáÉÿÿé|ÿÿÿ¶¿U‰åƒì‰uø‹M‹u ‰}ü…ɉ]ô”À…ö”‹} Шu8…ÿt4‹Y¸@…Ût‰$¸ê¯‰D$èWëÿÿ…Àt%‹]ô‹uø‹}ü‰ì]ö‹]ô¸‹uø‹}ü‰ì]É$趦ÿÿ…Àuωt$‰$èv±ÿÿ…Àu¿‰$¸|°‰D$è°ÿÿ…Àuª‰} ‹uø‹}ü‰]‹]ô‰ì]évµÿÿ¶U‰åƒì(‰]ô‹]‰uø‹u …Û‰}ü”À…ö”‹} Шuh…ÿtd‰$Eð‰D$èeÈÿÿ…ÀuA‹Uð¸@…Òt5‰$¸ê¯‰D$è„êÿÿ…À„|¸Ÿ´‰D$‹Eð‰$èˆÄÿÿ…Àt&t&‹]ô‹uø‹}ü‰ì]Ãv‹]ô¸‹uø‹}ü‰ì]øw°‰D$‹Eð‰$èšÄÿÿ…ÀuƸA°‰D$‹Eð‰$èÅÿÿ…Àu®´&¼'¸|°‰D$‹Eð‰$èÜÄÿÿ…Àuˆ‹Eð‰$èm¥ÿÿ…À…uÿÿÿ‰t$‰$èÉ®ÿÿ…À…aÿÿÿë¹A°‰L$‹Eð‰$è«®ÿÿ…À…Cÿÿÿ‰t$‹Eð‰$è¯ÿÿ…ÀtP»¿´‰\$‹Eð‰$èlÄÿÿ…À…ÿÿÿEì‰D$‹Eð‰$èò³ÿÿ…ÀtŸ‹Eì…Àt˜‰|$‰$è›/…Àuˆ1Àéàþÿÿ‹Eð‰$è•™ÿÿ…À…Íþÿÿ‰t$‹Eð‰$è.´ÿÿ…À…¶þÿÿº|°‰T$‹Eð‰$è®ÿÿ…À…šþÿÿ‰|$‹Eð‰$èû³ÿÿé†þÿÿ¶U‰åìX‰]ô‹E‹]‰}ü¿é²‰uøƒ8t¿Â²‹p…ö„/‹C…Àt‹U ‹B…Àu¶¼'1À‹]ô‹uø‹}ü‰ì]À8tëÇ$f´èÏV…À…ò¸£²‰D$‹C‰$èSèÿÿ…Àu¿¹º|°‰L$ ‹M ‰T$‹A‰D$‹C‰$è¨Íÿÿ…Àu”…äýÿÿ‰D$‹C‰$è_±ÿÿ…À…yÿÿÿ‹…äýÿÿëk‹…äýÿÿ‰D$‹C‰$èÚªÿÿ…À…Tÿÿÿºì³‰T$‹C‰$èάÿÿ…À…8ÿÿÿ•äýÿÿ‰T$‹C‰$èµÿÿ…Àt ¸‰…äýÿÿ‹…äýÿÿ…Àˆÿÿÿ‰D$‹C‰$èuªÿÿ…À…ïþÿÿ¸A°‰D$‹C‰$èi¬ÿÿ…À…Óþÿÿ…àýÿÿ‰D$‹C‰$èܱÿÿ…À…¶þÿÿ‹…àýÿÿ…Àu ¸×¯‰…àýÿÿ¸|°‰D$‹C‰$è¬ÿÿ…À…ÿÿÿ…Üýÿÿ‰D$‹C‰$莱ÿÿ…À…÷þÿÿ‹•Üýÿÿ…Ò„éþÿÿ‹M ‹A‰$‰D$è&-…À…Ïþÿÿ‰|$1À‰…Èýÿÿ‹C‰$è·«ÿÿ…À„¹’°‰L$‹C‰$蛫ÿÿ…À„R‹…Èýÿÿ…Àކþÿÿ¸\²‰D$‹C‰$èq«ÿÿ…À…jþÿÿ…Ìýÿÿ‰D$‹C‰$èä°ÿÿ…À…Mþÿÿ‹…Ìýÿÿ…À„?þÿÿ‰D$¹ºA°‰L$ ‰T$‹C‰$èËÿÿ…À…þÿÿ‰|$‹C‰$è«ÿÿ…À…ÿýÿÿ…Øýÿÿ‰D$‹C‰$èy°ÿÿ…Àu‹•Øýÿÿ…Ò…~‰t$‹…àýÿÿ‰D$ ‹…Ìýÿÿ…Àu¸×¯‰D$èýÿÿ¸Ì´‰ $‰D$èoR‰$¹…èýÿÿ‰L$‰D$è4½ÿÿé€ýÿÿ¾×¯éÇüÿÿ1À‰D$1À‰D$1À‰D$ 1À‰D$¡XôƒÀ@‰D$‹C‰$è&çÿÿéÚüÿÿ…Ðýÿÿ‰D$‹C‰$輯ÿÿ…À…‘þÿÿ‹…Ðýÿÿ…À„ƒþÿÿ‰$º¸±‰T$èU+…À…jþÿÿ‹…Èýÿÿ…Àjþÿÿ‰t$ ‹…àýÿÿ‰D$¸ü´‰D$…èýÿÿ‰$èšQ‰$¸•èýÿÿ‰D$‰T$è_¼ÿÿéþÿÿ…Øýÿÿ‰D$‹C‰$è%¯ÿÿ…À…Þýÿÿ‹•Øýÿÿ…Ò„Ðýÿÿ‰$¸ ‰D$…Ôýÿÿ‰D$è´R‰…Èýÿÿéªýÿÿ‰$¸ ‰D$…Ôýÿÿ‰D$èŽR…À7üÿÿéZþÿÿU‰åìH ‰uø‹E1ö‰}ü‹U‹}‰]ôƒø‹Z„ƒø„¿ƒø„¥ƒø„ƒƒøt1À‹]ô‹uø‹}ü‰ì]ËE‹U ‹M ‹@B‰•ôÿÿ…À¾1t׉<$èfD‰…tôÿÿ…ÀtÅ‹x…ÿt¾‰D$‹M•ˆþÿÿ‰T$»P‰\$ ‰ $èó:…Àu˜‹U¹£²‰L$‹B‰$èhãÿÿ…À…yÿÿÿº¸A°ˆþÿÿ‰T$ ‹U‰D$‰L$‹B‰$è¶Èÿÿ…À…Gÿÿÿ‹M¸ý±‰D$‹A‰$è¨ÿÿ…À…(ÿÿÿ‹U…8ôÿÿ‰D$‹B‰$臭ÿÿ…À…ÿÿÿ1ÀƒþÉ…ôÿÿ„ F?ƒø‡ƒ ‹…ôÿÿ¿ ‰|$‰$èËP…À„I ¾Ãÿÿÿ‹…8ôÿÿ¹ºµ‰L$‰T$‰$èn)…À…п‰½ôÿÿ‹…8ôÿÿ»!µ‰\$‰$è´(…Àu‹M ¶<ÿt<Æt<Ät<Åt‹ôÿÿ…É„IF„Nþÿÿ‹M¸(µ‰D$‹A‰$èâÿÿ…À…/þÿÿ¸‹U‰D$ ¸A°‰D$…ˆþÿÿ‰D$‹B‰$èlÇÿÿ…À…ýýÿÿ‹U…,ôÿÿÙî‰D$‹BÝèóÿÿ‰$è«ÿÿ…À…×ýÿÿ1À¿Aµ‰…ðóÿÿ¸‰D$‹…8ôÿÿ‰|$‰$èt(…Àu(‹…8ôÿÿ¾»Fµ‰t$‰\$‰$èP(…À„Ü‹ôÿÿ¸‰…ðóÿÿ…(ôÿÿ‰D$‰ $è…OÝèóÿÿ‹…,ôÿÿ…ÀˆÒ‹U¸A°‰D$‹B‰$è¦ÿÿ…À…-ýÿÿ‹…,ôÿÿ‹M‰D$‹A‰$èê£ÿÿ…À… ýÿÿ‹U…$ôÿÿ‰D$‹B‰$èj«ÿÿ…À…íüÿÿ‹M¸Ü³‰D$‹A‰$軥ÿÿ…À…Îüÿÿ‹U…,ôÿÿ‰D$‹B‰$èk®ÿÿ…À…®üÿÿ‹…$ôÿÿ…À„Fÿÿÿ‰$ˆþÿÿ‰L$èÃ&…À…,ÿÿÿ‹U¸l°‰D$‹B‰$èT¥ÿÿ…À…güÿÿ‹M… ôÿÿ‰D$‹A‰$èĪÿÿ…À…Güÿÿ‹U¸f°‰D$‹B‰$è¥ÿÿ…À…(üÿÿ‹M…ôÿÿ‰D$‹A‰$è…ªÿÿ…À…üÿÿ‹… ôÿÿ¿f°‰|$‰$è&&…À…‡‹…ôÿÿ‰D$‹…ôÿÿ‰$è6M…À„Çûÿÿ‹µðóÿÿ…ö„aþÿÿ‹…ôÿÿ•(ôÿÿ‰T$‰$èÈMÝ…èóÿÿÙÉÚéßàž…6þÿÿ‹ˆûÿÿé+þÿÿ‰$‹M 1À‰D$ ¸‰D$‰L$èûÿÿ…À…_ûÿÿéXûÿÿ1À‹U‰D$ ¸‰D$‹E ‰$‰D$èîúÿÿ…À…1ûÿÿ‹M …tôÿÿ¿‰|$‰$‰L$è¨D…À„I‹M‹A…À„ûúÿÿ‰$º£²‰T$èÑÞÿÿ…À…âúÿÿ‹U¸Â²‰D$‹B‰$è"Èÿÿ…À…Åúÿÿ‹M¸Ô²‰D$‹A‰$èÈÿÿ…À…¦úÿÿ‹U¸é²‰D$‹B‰$èäÇÿÿ…À…‡úÿÿ‹M¸û²‰D$‹A‰$èÅÇÿÿéÿÿÿ‹E ¿tôÿÿ‰|$‰$‰D$èâC…À…Z‹…tôÿÿ‰D$…`ôÿÿ‰$è"D…À…#úÿÿ‹…`ôÿÿ…À„ø1Ò1ÿ1Û‰•ôÿÿ9ƃzµ\ôÿÿë C;`ôÿÿƒe‰\$1À‰…Xôÿÿ‹…tôÿÿ‰4$‰D$èE…ÀuÑ‹…\ôÿÿ‰D$…Xôÿÿ‰$è©C…Àuµ…Û…~‹½Xôÿÿ‰ø‰½ôÿÿ9…ôÿÿs‰…ôÿÿ9Çv‰Ç뉋E º‰T$‰D$…tôÿÿ‰$èûB…À…\ùÿÿ‹U 1ö‹B…Àt ‰$èŸK‰Æ‹tôÿÿ‹C…Àt €8…5ƒþKE‹tôÿÿ‹C…Àt ‹G…À…‹U‹B…À„ùÿÿ‰$1ɺ£²‰Pôÿÿ‰T$èÏÜÿÿ…À…àøÿÿ¸P‹Uˆþÿÿ‰D$ ‹E ‰L$‰$‰D$è4…À…³øÿÿ¸‹Uˆþÿÿ‰D$ ¸A°‰D$‰L$‹B‰$èðÁÿÿ…À…P‹G…Àt€8u)‰|$1À‰D$…Tôÿÿ‰$è”C…À…Wøÿÿ‹…Tôÿÿ‹@‰…Pôÿÿ‹…Pôÿÿ…Àt €8_„&ºA°¹‰T$‹U‰L$ ˆþÿÿ‰L$‹B‰$èpÁÿÿ…À…øÿÿ‹M¸|°‰D$‹A‰$èÑ ÿÿ…À„é‹U¸¯²@ôÿÿ‰\$‰D$‹B‰$è˜Äÿÿ…À…»÷ÿÿ¸‰D$‹…tôÿÿ‰D$…\ôÿÿ‰$è/A…À…“‰\$‹M¿é²‰|$‹A‰$èLÄÿÿ…À…o÷ÿÿ‹U…<ôÿÿ¾û²‰D$‰t$‹B‰$è#Äÿÿ…À…F÷ÿÿƒ½@ôÿÿŽƒ½<ôÿÿŽÒ•ˆþÿÿ‰T$ºLµ‰T$èþÿÿ‰$èÀG‰\$º‰T$‹M‰ $舲ÿÿéìöÿÿv‰$‹U ¿‰|$‰T$èh@…À…Éöÿÿ‹…tôÿÿ‰D$…`ôÿÿ‰$è¨@…À…©öÿÿ‹µ`ôÿÿ…ö…›öÿÿ»¹‰µ‰\$‰L$ë‹9½ôÿÿtE‹…tôÿÿ‹@…Àu¸×¯‰D$èþÿÿ¸¥µ‰D$‰$è G‰\$‹M¸‰D$‰ $èѱÿÿ‹…ôÿÿ…À…,öÿÿ‹…tôÿÿ‹@…Àu¸×¯‰D$¸Ãµ‰D$èþÿÿ‰$è¶F‰\$¸‰D$‹E‰$è~±ÿÿéâõÿÿ¸‰D$¸Üµ‰D$‹E‰$è\±ÿÿé™üÿÿ‹…tôÿÿ‰D$…pôÿÿ‰$èŸ?…À…¢õÿÿ‹•pôÿÿ…Ò…a…Û¸„‡õÿÿ‹…tôÿÿ‹@…À…#ü¾¶èþÿÿ·$¶¹ ‰ßó¥f‰¶&¶ˆG‰\$‹E¹‰L$‰$èʰÿÿ‹U‹Bé%úÿÿ‹…Xôÿÿé…ûÿÿ»¹'¶‰\$‰L$‹U‰$è—°ÿÿéûôÿÿ‰D$Ç$>¶è"…À„³ûÿÿ‹M ‹A…Àt €8_„ ûÿÿ‹tôÿÿ‹C‰$èGt0ƒþKŽ‘ûÿÿ‹U¸‰D$¸H¶‰D$‰$è,°ÿÿéiûÿÿ‰D$ ‹Cèþÿÿ‰$‰D$¸€¶‰D$è%E‹G‰D$‹…tôÿÿ‹@‰$è…À„?ûÿÿ‰\$‹M¾‰t$‰ $èͯÿÿé"ûÿÿ‹M‹A…À„#ôÿÿ1Û9Öƒùÿÿ½lôÿÿëƒøtZC;pôÿÿƒÌþÿÿ‰\$‹…tôÿÿ‰<$‰D$è ?…À…ãóÿÿ‹•lôÿÿ‹ƒøuÉT$‹…tôÿÿ‰D$‹E‰$èÂîÿÿ…Àt«é´óÿÿ‰T$…hôÿÿ‰$è—=…À…šóÿÿ1ö;…hôÿÿs‚‰t$‹…lôÿÿ•dôÿÿ‰$‰D$è©>…À…lóÿÿ‹•dôÿÿƒ:tBF;µhôÿÿrÈéEÿÿÿ‰D$»´¶‰\$èþÿÿ‰$èíCéæýÿÿˆþÿÿ¸Ø¶‰L$é ýÿÿ‰T$‹…lôÿÿ‹M‰D$‰ $è îÿÿ…Àt¡éýòÿÿ‰ö‹U…Lôÿÿ‰D$‹B‰$èX¡ÿÿ…À…÷úÿÿ‹•Lôÿÿ…Ò„éúÿÿ‹…Pôÿÿ…À„Ûúÿÿ‰T$‹M…Hôÿÿ‰D$‹A‰$èØåÿÿ…À…·úÿÿ…Dôÿÿ‹U‰D$‹…Pôÿÿ‰D$‹B‰$è®åÿÿ…À…úÿÿ‹…Dôÿÿ‰D$‹…Hôÿÿ‰$莅À„múÿÿ‹…Dôÿÿˆþÿÿèþÿÿ‰L$‰D$‹…Hôÿÿ‰$‰D$ ¸·‰D$èÑB‰\$¸‰D$‹E‰$è™­ÿÿéúÿÿ‰\$‹U¸Â²‰D$‹B‰$è¹¾ÿÿ…À…Üñÿÿ…<ôÿÿ‹M‰D$¸Ô²‰D$‹A‰$è¾ÿÿ…À…³ñÿÿƒ½@ôÿÿކ ƒ½<ôÿÿŽ@ ˆþÿÿ¸@·‰L$érûÿÿ‹•ôÿÿ» ‰\$‰$ècC…ÀtwƒþÂуþÁKƒþÀ…¹òÿÿ¸‰D$¸}·‰D$‹…8ôÿÿ‰$èô…À…º‹…ôÿÿ‰$ènCƒø„oòÿÿƒø…qòÿÿ‹•ôÿÿ€:+…bòÿÿéRòÿÿ¹ ‰L$‹ôÿÿ‰ $èÑB…À…jÿÿÿ‹…ôÿÿº ‰T$‰$è²B…À…Kÿÿÿ‹•ôÿÿ¸ ‰D$‰$è“B…À…,ÿÿÿ‹ôÿÿ¸ ‰D$‰ $ètB…À… ÿÿÿ¾Àÿÿÿéÿÿÿ¸‰D$¸„·‰D$‹…8ôÿÿ‰$è…À…Ï‹ôÿÿ‰ $èŒBƒø„ñÿÿƒø…ñÿÿ‹…ôÿÿ€8+éÿÿÿ‹…8ôÿÿ¹º‹·‰L$‰T$‰$è¼…À„Nñÿÿ¸‰D$¸·‰D$‹…8ôÿÿ‰$è”…À„&ñÿÿ¸‰D$¸•·‰D$‹…8ôÿÿ‰$èl…À„þðÿÿ¸‰D$¸š·‰D$‹…8ôÿÿ‰$èD…À„Öðÿÿ‹…8ôÿÿ¿»Ÿ·‰|$‰\$‰$è…À„®ðÿÿ‹…8ôÿÿ¹º¤·‰L$‰T$‰$èô…À„†ðÿÿ¸‰D$¸©·‰D$‹…8ôÿÿ‰$èÌ…À„^ðÿÿ¸‰D$¸­·‰D$‹…8ôÿÿ‰$褅À„6ðÿÿ¸‰D$¸²·‰D$‹…8ôÿÿ‰$è|…À„ðÿÿ‹…8ôÿÿ¿»··‰|$‰\$‰$èT…À„æïÿÿ‹…8ôÿÿ¹º¼·‰L$‰T$‰$è,…À„¾ïÿÿ¸‰D$¸µ‰D$‹…8ôÿÿ‰$è…À„–ïÿÿ¸‰D$¸Aµ‰D$‹…8ôÿÿ‰$èÜ…Àu(¸‰D$¸Fµ‰D$‹…8ôÿÿ‰$踅À„e¹ •0ôÿÿ‰L$‹ôÿÿ‰T$‰ $èÿ?‹…0ôÿÿ¶„Ò„ïÿÿ€ú(„ú¸¿Aµ‰D$‹…8ôÿÿ‰|$‰$èU…Àt$‹…8ôÿÿ¹À·»‰\$‰L$‰$è1…Àu[‹…ôÿÿ0ôÿÿ‰L$‰$èu?ÝØ‹…0ôÿÿ¶„Ò„œîÿÿ€ú(u+º @‰T$•0ôÿÿ‰T$‰$èQ?‹…0ôÿÿ€8)„lîÿÿ¸‰D$¸µ‰D$‹…8ôÿÿ‰$è²…À„Dîÿÿ‹…8ôÿÿ¿»©·‰|$‰\$‰$芅À„îÿÿ‹…8ôÿÿ¹ºŸ·‰L$‰T$‰$èb…À„ôíÿÿ¸‰D$¸¤·‰D$‹…8ôÿÿ‰$è:…À„Ìíÿÿ¸‰D$¸­·‰D$‹…8ôÿÿ‰$è…À„¤íÿÿ¸‰D$¸‹·‰D$‹…8ôÿÿ‰$èê…À„|íÿÿ‹…8ôÿÿ¿»·‰|$‰\$‰$èÂ…À„Tíÿÿé'íÿÿ‹M €y\…êìÿÿ‰ÈxöÿÿƒÀ‰…4ôÿÿ1À‰D$¸‰D$ ¸‰D$…4ôÿÿ‰\$‰$èí…À„§ìÿÿ‰ôÿÿ¾Áÿÿÿé—ìÿÿƒþľìÿÿFƒø‡åìÿÿéÕìÿÿ‹…8ôÿÿ¿»Å·‰|$‰\$‰$è…À…”¹ •0ôÿÿ1Û‰L$‹ôÿÿ‰T$‰ $è`=‹0ôÿÿ‰Ç€9_u&…0ôÿÿº ‰D$A‰T$‰$è5=‹0ôÿÿ‰Ã€9”À1Ò…ÿŸÂ…ЄMìÿÿ‰ØÿÀ÷ОÂÁè…„5ìÿÿûç)ìÿÿéìÿÿ¸‰D$¸Ê·‰D$‹…8ôÿÿ‰$è_…À…{úÿÿ1ɸÿÿÿÿº ‰… ôÿÿ¸ÿÿÿÿ1ÿ‰ôóÿÿ‹ôÿÿ1Û‰…ôÿÿ1À‰…ôÿÿ1À‰T$•0ôÿÿ‰½üóÿÿ‰ $‰…ôÿÿ‰øóÿÿ‰T$èh<‹0ôÿÿ‰Ç€9-„)¶<-”Â<+”À Шt*…0ôÿÿ» ‰D$A‰\$‰$è&<‰…ôóÿÿ‹0ôÿÿ€9‰ø÷ДÂÁè…„:ëÿÿÿ'žÀ1Òƒ½ ôÿÿŸÂ…Єëÿÿƒ½ ôÿÿ žÀ1Òƒ½ôÿÿŸÂ…Єÿêÿÿƒ½ôÿÿ‹…ôÿÿ÷ОÂÁè…„âêÿÿƒ½ôÿÿ‹…ôÿÿ÷ОÂÁè…„Åêÿÿƒ½ôÿÿ<‹…üóÿÿ÷ОÂÁè…„¨êÿÿƒ½üóÿÿ<÷•øóÿÿžÀÁ­øóÿÿ……øóÿÿ„…êÿÿ‹…ôóÿÿ÷ÐÁ能ôóÿÿžÂ…„hêÿÿéXêÿÿ¸ ‰D$…0ôÿÿ‰D$A‰$è;‰… ôÿÿ‹0ôÿÿ€9-…¤þÿÿ¸ •0ôÿÿ‰D$A‰T$‰$èÝ:‰…ôÿÿ‹0ôÿÿ¶€ûT”€ût”À Шu €û:…\þÿÿ¸ ‰D$…0ôÿÿ‰D$A‰$è•:‰…ôÿÿ‹0ôÿÿ€9:…)þÿÿ¸ •0ôÿÿ‰D$A‰T$‰$èb:‰…ôÿÿ‹0ôÿÿ€9:…öýÿÿ¸ ‰D$…0ôÿÿ‰D$A‰$è/:‰…üóÿÿ‹0ôÿÿ€9.…Ãýÿÿ¸ •0ôÿÿ‰D$A‰T$‰$èü9‰…øóÿÿ‹0ôÿÿé”ýÿÿº @‰T$•0ôÿÿ‰T$‰$èÏ9‹…0ôÿÿ€8)…Ûùÿÿéåèÿÿ‹…8ôÿÿ¿»À·‰|$‰\$‰$è+…À„Qúÿÿénùÿÿ…ˆþÿÿèþÿÿ‰D$¸Ð·‰D$‰$èí7‰\$‹U¸‰D$‰$èµ¢ÿÿ‹…<ôÿÿHŽçÿÿéuõÿÿ‹…8ôÿÿº¸èþÿÿ‰T$‰$‰D$ …ˆþÿÿ‰D$è˜7‰\$¸‰D$éÄñÿÿ¸‰D$¸©·‰D$‹…8ôÿÿ‰$èv…À„èÿÿ¸‰D$¸‹·‰D$‹…8ôÿÿ‰$èN…À„àçÿÿ¸‰D$¸·‰D$‹…8ôÿÿ‰$è&…Àé\õÿÿ»0¸ˆþÿÿ‰\$èþÿÿ‰L$‰$èî6‰\$‹E¹‰L$‰$è¶¡ÿÿ‹…<ôÿÿHŽæÿÿéãîÿÿ‰D$‹U¿‰|$ ¾A°‰t$‹B‰$èP¯ÿÿ…À…®íÿÿ‹M»|°‰\$‹A‰$豎ÿÿ…À…íÿÿ‹U…Pôÿÿ‰D$‹B‰$è!”ÿÿéríÿÿ‹…8ôÿÿ¹ºÀ·‰L$‰T$‰$èL…À„%èÿÿé÷çÿÿ•ˆþÿÿ¹d¸‰T$‰L$éIîÿÿ‹…ôÿÿ»:‰\$‰$è@7…À‰Ã„ççÿÿ‹•ôÿÿ)ЉD$…xõÿÿ‰T$‰$èh6‹ôÿÿ‰Ø1Ò)Ȉ”(xõÿÿC•xôÿÿ‰D$‰$èP6‹ðóÿÿ…Û„”€½xõÿÿtü»†¸¹µxõÿÿ‰ßó¦…¿ü‹ ôÿÿ»[°¸ ‰ß‰Î‰äóÿÿ‰Áó¦„ ü‹µäóÿÿ¸ ¿N°‰Áó¦…/çÿÿ…(ôÿÿ•xôÿÿ‰D$‰$è–6Ý…èóÿÿÙÉÚéßàž‚çÿÿéWäÿÿ€½xõÿÿ»[°uRü‹µ ôÿÿ¹ ‰ßó¦u ‹•ôÿÿ…xôÿÿ‰D$‰$èV…Àˆäÿÿ‹…ôÿÿxôÿÿ‰L$‰$è6…ÀŽ÷ãÿÿ€½xôÿÿuRü‹µ ôÿÿ¹ ‰ßó¦u ‹ôÿÿ•xõÿÿ‰T$‰ $èû …À¼ãÿÿ‹•ôÿÿ…xõÿÿ‰D$‰$èÛ …À‰œãÿÿü‹µ ôÿÿ¹ ‰ßó¦u‹…ôÿÿxôÿÿ‰L$‰$è© …ÀxE‹•ôÿÿ…xôÿÿ‰D$‰$è …Àöåÿÿ‹…ôÿÿxõÿÿ‰L$‰$èm …ÀˆÖåÿÿé)ãÿÿ‹ôÿÿ•xõÿÿ‰T$‰ $èH …À~Ÿéãÿÿ€½xôÿÿtü¹µxôÿÿ‰ßó¦…£ü‹… ôÿÿ»[°‰ß‰…äóÿÿ‹µäóÿÿ¸ ‰Áó¦„ùü‹µäóÿÿ¸ ¿N°‰Áó¦…Måÿÿ…(ôÿÿ•xõÿÿ‰D$‰$è´4Ý…èóÿÿéþÿÿ…(ôÿÿ•xôÿÿ‰D$‰$è‘4Ý…èóÿÿÙÉÚéßàž‡Wâÿÿ‹… ôÿÿ‰…äóÿÿé¤ýÿÿü‹… ôÿÿ»[°‰ß‰…äóÿÿ‹µäóÿÿ¸ ‰Áó¦„ü‹µäóÿÿ¸ ¿N°‰Áó¦…ªäÿÿ…xõÿÿ(ôÿÿ‰$‰\$è4Ý…èóÿÿÚéßàž‚äÿÿ‰\$…xôÿÿ‰$éSýÿÿ…(ôÿÿ•xõÿÿ‰D$‰$èÖ3Ý…èóÿÿÚéßàž‡žáÿÿ‹… ôÿÿ‰…äóÿÿéÍþÿÿ…xõÿÿ(ôÿÿ‰$‰\$èœ3Ý…èóÿÿÚéßàžw‹• ôÿÿ‰•äóÿÿé:ÿÿÿ‰\$…xôÿÿ‰$èl3Ý…èóÿÿÙÉÚéßàž‡2áÿÿ‹… ôÿÿ‰…äóÿÿéÿÿÿ´&U‰åƒìX‰]ô…À‹]‰uø‰Æ‰}ü‰×ºt*öÃtöÃu ‹º‰T$‰D$EÔ‰$èm*…À‰Ât‹]ô‰Ð‹uø‹}ü‰ì]Ã1À‰D$‹EÔ‰$èw-…À‰ÂuÚ‹EÔ‰‹F‰$èÁÅÿÿ…À‰ÂuÄ‹E …À„à‰|$}Љ<$èñI…À‰Âu¤‹EÐöÉFuƒËöÃtƒË‰X@‰EØ‹‰uàÇEä‰EÜE؉$è`‰4$‰Ã1À‰D$ ¸‰D$‹‰D$èÖßÿÿ…À‰Â…Eÿÿÿ…Ût|‹¹‰L$‰D$EÔ‰$èŽ)…À‰Â…ÿÿÿ‹EÔ‰D$Eĉ$èÒ)…À‰Ãu ‹UÄ…Ò„±ÇF‰<$èRJ1Òƒ~•Â Ø ÂéÙþÿÿ‰|$}Љ<$èñGéÿÿÿ1À‰D$‹EÔ‰D$Ẻ$è´*…À…dÿÿÿ‹ẺD$Eȉ$èê*…À…Jÿÿÿ‹EÈ…À…?ÿÿÿ‹ẺD$Eĉ$è5)…À…%ÿÿÿ‹]Ä…Û…ÿÿÿ‹Ẻ$è/é ÿÿÿ‰ö‰4$¸‰D$¸ˆ¸‰D$è–šÿÿé0ÿÿÿU‰å‹M‹E‹U ‰MÇE ]éÄýÿÿt&U‰å‹M‹E‹U ‰MÇE ]é¤ýÿÿt&U¹‰åWVSƒì‹}‹uýZÁë;] ‡ÈƒûÍÇEð‹E…ÀtÇEð‰Ø‰ÑÁà)ÁƒÁÓeðÇEìƒÿwÇEìÿÿÿÿ ýÓeìƒÿ‹M„À‡ªO„Ù‹E¶tFÇEð…ÿ……ö„¯‹E‹…Éu6…ö„Ñ…ÿt ‹9ú‚—‹Eð…ö‹U‰t‰>1Ò‹]ô‰Ð‹uø‹}ü‰ì]Ë…Û•À1Ò…ÿ•Â…Ðt&9ûv‰>‰û‰L$‹E‹Uð¯Ø‰$‰\$èÍ'‹E‹…Étމ $è\'ë„‹E¯Ç‰$èl'‰Eð…Àºt…ö…Yÿÿÿ´&‹U‹ ëÁ‹M‰ø‹])ЯÁ¯Ó‹Mð‰D$Ê1À‰D$‰$èÂ'é=ÿÿÿ‹E1Û‰\$¯Ç‰D$‹Eð‰$è¢'éÿÿÿ¶¼'U‰åS‹U‹E ‹]…Ò‹Mt#Ç…ÀtljM‰]‰E ‰U[]éiþÿÿ[¸]ÃU¸‰åƒì‰]ø‹]‰uü‹u …Ût‹…ÀuÇ…ötÇ1À‹]ø‹uü‰ì]Ãv‰$èH&ë×U‰åWVSƒì ‹u‹} ë¾À‰$èt'‰Ã¾‰$èg'9Ãu-FG¶„ÀuÛ¾À‰$èO'‰Ã¾‰$èB')ÃƒÄ ‰Ø[^_]ö¾À‰$è('‰Ã¾‰$è')ÃƒÄ ‰Ø[^_]Ãë U‰åWVSƒì ‹}‹uë+¶„Àt2¾À‰$èÝ&‹U ‰Ã¾‰$èÍ&9ÃuÿE NG…öuÑƒÄ 1À[^_]þ‰$è«&‹U ‰Ã¾‰$è›&)ÃƒÄ ‰Ø[^_]ÃU‰åWVSƒì‹EÇEìÿÿÿÿ‹]‹} ‹0S‰Uè¶<;„<ÇEð„À„¨¶ëW‹Eð¶T€ú;„ð€ú ”À„Ò” Ш…0‹U…Ò•À1ÒƒûžÂ…Ð…Q‹UðK¶2ˆGÿEð‹Eð¶ 0„ÉtL€ù ”À€ù ” Шt ‰]è‹Eð‰Eì‹E…Àt€ù\tB‹M…É•À1Òƒû”Â…Ð…jÿÿÿ‹Eð¶TénÿÿÿÆ‹Uð‹U‰¸ƒÄ[^_]Éö‹E…Àt ‹Uð€| tN‹E…À•À1ÒƒûžÂ…Ðt™Æ\ÆG‹Uð‹U‰1ÀƒÄ[^_]þD‰$è&…ÀuÓ‹Eð¶TéòþÿÿB‰Uðé!ÿÿÿ¾F‰$èÜ%…Àu€~u}Æ;‹E Æ@\Æ@ ‹UF‰ë¡‹Uð ¶2ÆGˆ‹UA‰‹Eð¶T€ú tH„Ò¸„.ÿÿÿ1Àéjÿÿÿ9]è‹UŸÀ9UèœÂ¶Ò…Є<ÿÿÿ‹Eì߉Eð‹Eè)Çé*ÿÿÿ¶é)þÿÿ‹UA‰‹Eð¶Të¦t&¼'U‰åWVS쬋]…Û„1¶ˆÐ@<—Á1À€úÿ•Àº…Á…è…„÷ÿÿ1ö‰D$‹E ‰t$‰$èm>…À‰Â…Ë„÷ÿÿ…É„…¶€úÄ@€úÀ”Àþ” Ш…´qK‰Ê‰€÷ÿÿ€{„|‹E ‹x09þw%‰ö€: „™F‰ÈA‰Ê‰€÷ÿÿ€x„W9þvÝ‹E º ‰T$‰$è‰H…À‰Âu3v¶¾ÂƒøÂ~5ƒøÃ„@„(‹] ‰$è*A‰Â´&Ĭ‰Ð[^_]ÃvƒøÁ}*ƒøÀë˶qéGÿÿÿ» ¸éæþÿÿ‰ðƒàøpé[ÿÿÿC‰l÷ÿÿ‹] ‹{0Æ…s÷ÿÿ'€úÁ³"t Æ…s÷ÿÿ"³'¾…s÷ÿÿ‰D$‹…l÷ÿÿ‰$èô"…Àt‹•l÷ÿÿ¾Ã‰D$‰$èÛ"…À„‹l÷ÿÿ‰$è%#‰Ã@9øs!¾µs÷ÿÿ‹…l÷ÿÿ‰t$‰$è£"…À„.‹U ]˜‹B,@‰D$ ‹B(‰$@‰D$¸£¸‰D$è4!‰$èŽÿÿ‹] ‹C,…Àt‰$¸ ‰D$è1G…À‰Â…×þÿÿ‹E ¿½¸‰|$‰$è#H…À‰Â…¹þÿÿ‹l÷ÿÿ1ö‰€÷ÿÿ€9„”‰ö‹U ‹z0‰Ó‹R,Gö9‡CGþ9Âv$‹E ¾Á¸‰t$‰$èÏG…À…]þÿÿ‹€÷ÿÿ1ö¾‹U ‰D$‰$èF…À…;þÿÿ‹€÷ÿÿ€9;”À1Ò…ö”Â…Ð…º€9 •À¶ð‰ÈA‰€÷ÿÿ€x…nÿÿÿ¹Ä¸‰L$韋U ‹z09þ†Âýÿÿé ýÿÿS‰•l÷ÿÿ‰$è¬!‰Æ‹E ‹x09þ‡¥¶S€ú"ˆ•r÷ÿÿ„’€ú'„‰¸É¸‰D$‹…l÷ÿÿ‰$è™!…À…j9þ„‹U ¸ ‰D$‰$èÅE…À‰Â…kýÿÿ‹l÷ÿÿ‰\$‹E ‰$è¶F…À‰Â…Lýÿÿé2ýÿÿ¾‰$èL!…À…±þÿÿ‹€÷ÿÿ€9\„¢þÿÿ‹{0‹S,éþÿÿ1Ò1À‰•t÷ÿÿ‰…x÷ÿÿ€{\„á1À¿¾‰…|÷ÿÿ‹…t÷ÿÿÉh÷ÿÿ‰ÙA‰€÷ÿÿ€{ë€9 „ÇG¾‰ÈA‰€÷ÿÿ€x„Ù€9;”À1Ò…ö”Â…Ðt;A‰$è¡ …À…¾‹€÷ÿÿ€yu­¸‰…x÷ÿÿë ¾A‰$èt …Àu‹€÷ÿÿ€y…&þÿÿ»Á¸‰\$‹] ‰$èœE…À…*üÿÿ‹€÷ÿÿ1öéþÿÿ¶éküÿÿ€{ …ÿÿÿ¸‰…t÷ÿÿéÿÿÿt&‹…t÷ÿÿ…Àt €yÿ\„Z1ö;½|÷ÿÿ~‰½|÷ÿÿ1ÿéÿÿÿ;½|÷ÿÿ~‰½|÷ÿÿ‹x÷ÿÿ…Û…ù‹U ‹|÷ÿÿ;Z0‡ç‹•t÷ÿÿ…Òt €yÿ\„Ó¸;‰D$‹E ‰$èÏC…À‰Â…uûÿÿ1À‰…x÷ÿÿ‹h÷ÿÿ‹•h÷ÿÿA‰€÷ÿÿ€z„µˆ÷ÿÿ½€÷ÿÿë‰ö‹€÷ÿÿ€9„ç‹x÷ÿÿ‹…t÷ÿÿ‹U ‰\$‰D$ ‹B0‰t$‰<$‰D$èÇ÷ÿÿ‰t$‰Ã‹E ‰$èVD…À…äúÿÿ…Ûuª‹U ¸ ‰D$‰$è&C…Àt’‰ÂéËúÿÿ‹€÷ÿÿéCþÿÿ‹U ]˜‹B,@‰D$ ‹B(‰$@‰D$¸£¸‰D$èɉ$豉ÿÿ‹] ¸½¸‰D$‰$èÝC‰Â…Ò¸„ûþÿÿéiúÿÿ‹U ¹ ‰L$‰$éúÿÿˆs÷ÿÿéçúÿÿ‹µt÷ÿÿ…öt €yÿ\„ª‹E ‹H,…Ét‰$º ‰T$èkB…À‰Â…úÿÿ‹U ¸Î¸‰D$‰$é¢üÿÿC9øs‹U ¸ ‰D$‰$è2B…À‰Â…Øùÿÿ‰t$‹] ‰$èB…À‰Â…¿ùÿÿ‰$‹…l÷ÿÿ‰D$è C…À‰Â…£ùÿÿ‰t$‰$èçAé<üÿÿOéËüÿÿ»Ä¸‰\$‹] ‰$éüÿÿ€½r÷ÿÿ;„Dýÿÿ9þ„øûÿÿéÕûÿÿU1À‰åWVSƒìl‹U…Ò„j‹E¶¸„Ò‰W€âÀ1À€úÀ„Iü‹U¹}Èó«¶B¿„Àués‹uG¶7„À„®‹M°‰MȾÀ‰$è‰$‰Æèމ‹EÈ Â‰U¤1Àƒþ ‰U°”À Ẽþ'”öà EЃþ"”E¸¶E¸ EÔƒÿž¾‡à¸9ð•À¶À Eؾ‡ç¸9ð•À¶À E܃ÿqÿÿÿ1Ƀþ_”À ب„¹‹u ÑG‰M¤‰M°¶7„À…RÿÿÿƒÿÇEÜÇEØü‹]¸‰Á¿î¸C‰Þó¦”À¿ð¸¶À E¤¸‰Á‰Þó¦‹}¤”À¶À ø…À‰EÈu9‹uØ…öt2‹]Ü…Ût+‹]1ÀÆÀ‰öƒÄl[^_]ö]¸ƒþ#”À ب„aÿÿÿéWÿÿÿ‹MÌ…Éu‹UÐ…Òt&‹EÔ…Àu ‹u1ÀÆÂëÀ‹U1ÀÆÃë¶‹EȉE¤éEÿÿÿ‹EÆÁ1Àë¡U¹‰åƒì‰}ü‹}‰]ô‹] …ÿ‰uøtz‹U¶„Àyp$À<Àt‰$èêýÿÿ…À‰Áu\‰$¾Äñ‰t$è…ÀuVü‹]¿ð¸¹C‰Þó¦t*¿î¸¹‰Þó¦t‹E¹€8Àu¶¼'‹U1ÉÆÀ‹]ô‰È‹uø‹}ü‰ì]É$¹¿ñ‰L$蘅Àu<ü‹]¿ð¸¹C‰Þó¦t¹¿î¸‰Þó¦—Â’À8¹uª‹E1ÉÆÿë ‰$ººñ‰T$èG…ÀuF‹]¸ò¸‰D$C‰$莅Àu‰$¸õ¸‰D$èy…À„ù‹]ô¹‹uø‹}ü‰ì‰È]É$¸µñ‰D$èì…Àtt‰$¾°ñ‰t$è×…À¹…ÿÿÿ‹]C¶€;t:‰$¹ø¸‰L$è …À‰Æ‰Ãt!¾F‰$èÆ…À…œ€>tÉ^€;uÆ‹U1ÉÆÃé¼þÿÿ‹]¸û¸‰D$C‰$è¿…À…Fÿÿÿ‰$¸þ¸‰D$覅À…-ÿÿÿ‰$¿ ‰|$è½…À…ÿÿÿ‹E1ÉÆÂé`þÿÿ‰$¸ ‰D$è—…À…îþÿÿ‹U1ÉÆÁé:þÿÿÇ$¹è&„ÿÿé`ÿÿÿU1À‰åƒì‰]ø‹]‰uü‹u …ÛÇtR¶¸„ÒyFˆÐ$À<Àt‰$èvûÿÿ…Àu2¶€úÀt>€úÁtE€úÂt*€úÃtEþ¸uÇ¿ñ1Àv¼'‹]ø‹uü‰ì]Ãǵñ1ÀëìÇÄñ1Àëâ‰öǺñ1ÀëÖǰñ1Àë̶¿U¸‰åƒì‰]ø‹]‰uü‹u …Ût‹C…Àu2‹C…Àu 1À‹]ø‹uü‰ì]É4$¸=¹‰D$èj=…Àtß‹]ø‹uü‰ì]É4$¸E¹‰D$èK=…Àu‹C‰4$‰D$è8=…Àu¯‰4$¸ ‰D$è<ë·U¸‰åƒì‰]ø‹]‰uü‹u …Ût‹C…Àu2‹S…Òu 1À‹]ø‹uü‰ì]É4$¸L¹‰D$èÚ<…Àtß‹]ø‹uü‰ì]É4$¸Z¹‰D$è»<…Àu‹C‰4$‰D$è¨<…Àu¯‰4$¹ ‰L$èƒ;ë·U‰åƒì8¶a¹‰uø‹u‰}ü‹}‰]ô‹] ˆEï¸Æ7ƉD$Eð‰\$‰$èÿ …À‰ÂuF‹Uð‹B…ÀuO‹C…À„.‰Ã‹B…Àt€8uF‰|$‰\$‰4$èv‰$è~9øºw1Ò‹]ô‰Ð‹uø‹}ü‰ì]Ãt&‹C]ï…Àt´ë°t&‰D$Ç$c¹è îÿÿ…Àt¦€;_t¡‹Mðº‹A…ÀtµÆ_Eè‰D$‹A‰D$‹E‰$èì¶ÿÿ…À‰Âu“Gÿ‰Eà‰D$‹Eè‰D$F‰$èÚ‹Eè‰$è߃øHwZ;EàwU‰4$è͉Eä9øsÆ0.@‰Eä9}ät‰\$‹U䉸)ЋUä‰D$‰$茉$蔋UäDƒøKw9ø† ÿÿÿºéÿÿÿ‰|$¸j¹‰D$‰4$èQºéäþÿÿ´&U¸P‰å쨉uøuˆ‰}ü‹}‰]ô‰D$ ‰t$‹E ‰D$‹E‰$èþÿÿ…Àu*‰t$…„þÿÿ‰D$‹E‰$è ¹ÿÿ…Àth‹]ô‹uø‹}ü‰ì]ÃÇEÕ...ˆþÿÿ‰t$‹G,@‰D$ ‹G(‰$@‰D$¸t¹‰D$è‰$è€ÿÿ‰t$…„þÿÿ‰D$‹E‰$訸ÿÿ…Àuœt&‹…„þÿÿ‰<$‰D$è:‹]ô‹uø‹}ü‰ì]ÃU¸‰åƒì(‰]ô‹]‰uø‹u …Û‰}ü‹}t?9s¸@v5‰t$Eð‰\$‰$èB…Àu‹Eð…Àu'‰|$Ç$è'ïÿÿ´&‹]ô‹uø‹}ü‰ì]Ãv‰$èØöÿÿ…Àuä‹Eð‰E춈È@<–€ùÿ”À ШuE€ùÄ”À€ùÆ” Шu€ùŸuª‰t$‰$è>d…Àuš‰|$‹E‰t$‰$‰D$ èSgë‰|$‹Eì‰$è’îÿÿémÿÿÿ¶¼'U¸‰åW1ÿVSƒì<‹U …Ò„ŠÇEà‹E ÇEì‹Xƒû†k‹HÇEè‹Uì‹‘…À„H‹@;Eà‡Q‹u싱…À„.‰÷t&G9ûv!‹¹…Òtô‹uì‹R‹±;P…‚ÿEèG9ûwßÇEÔ‹uìÇEÜ9þƒ‰ø)ð@Ñè@‰EÐët&F9þƒì‹E ‹H‹±‹X…Ûtç‰$è…À~€|ÿ]t&ƒø~ÏÇ$¹ºDû‰T$‰D$èÒêÿÿ…Àu®ÿEÜ‹UÜ9UÐs£ÇEԸȹ‰D$‹E‰$èÈ7…À…eÇEØ‹uì9þsH‹]‹U ‰\$‹B‹]‹°‰$‰D$è³üÿÿ…À…0¸ ‰D$‹E‰$èg6…À…F9þr¸ÇEä‹U ‹]ì‹J‹™‹p…ö„Þ‹uì9þ‰uð‰ò‰ðƒ`‹]Ø…Û„–ë ‹EÔ…Àt/‹‘‹X…Ût%‰$èwƒø‰Æpƒþ³‹u ‹N‹Uð‹Eä‹]‹u‰D$‰\$ ‰t$‹‘‰$èÊüÿÿ…Àuk‹EØ…À„»‹Eð@9ø‰Eð‰ÂƒÐ‹] ‹K‹]Ø…Û…yÿÿÿ‹u‰t$‹‰D$‹E‰$è ûÿÿ…Àu!‹U ‹J‹UðéNÿÿÿ‹u ‹^‰}ì9û‡˜ýÿÿ1ÀƒÄ<[^_]ÉEàé§ýÿÿƒ}àv ƒ}è‡_þÿÿ‹] ‹uì‹C‹°ƒx‡Iþÿÿ‹U¸ ‰D$‰$è5…Àu²ÇEØé—þÿÿ‰4$¸ ‰D$èß4…Àu‹Eð@9ø‰Eð‰Â‚0ÿÿÿ‹UEð1Û‰D$‰\$‰$è*…À…_ÿÿÿ‹Mð…É…›ÿEä‹u ‹Uì‹]ä‹N‹‘9X‡Hþÿÿ‹^é$ÿÿÿÇ$й¸‰D$D3ý‰D$èOèÿÿ…À…kþÿÿ‹]¸ ‰D$‰$èC4…À…ðþÿÿ‹U ‹JéSþÿÿÇ$Ô¹¸‰D$D3ù‰D$èèÿÿ…Àt¸‹E ‹Hé'þÿÿ‹]º ‰T$‰$èð3…À„Iÿÿÿé˜þÿÿv;Uà†}üÿÿ‰Uàéuüÿÿë U‰åƒì(‰]ô‹E‹] ‰uø‹u‰Eð‹E‰}ü‰Eì‰$èW‰Ã…Û¸t ‹ƒø„Áv ƒø„ăøtI¸‹]ô‹uø‹}ü‰ì]Ãøué‰4$¸Ü¹‰D$èY4…ÀuÙöFH„ë¸ô¹‰D$‰4$è:4ë(‹Eì‰t$‰\$‰D$ ‹Eð‰$èûÿÿ´&¼'…Àu‹Bþƒøw‹C1ÿ…ÀuI‰ö¼'ƒútm‰u‹]ô‹uø‹}ü‰ì]é—+´&‰t$‰$èöÿÿ벉t$‰$è–öÿÿë¤t&‹Eì‰t$‰D$ ‹C‹¸‰D$‹Eð‰$èÀþÿÿ…À… ÿÿÿG9{wÒ‹뎉4$¹º‰L$èm3…À„zÿÿÿéäþÿÿ¸$ºéÿÿÿU‰å‹Eëƒ8u ‹@…Àuô1À]ô&U‰åSƒì‹]‰$èÎÿÿÿ‰Ã…Û¸t‹CÇ$‰D$èP#‹E ‰C1ÀƒÄ[]ÉöU‰åWVSƒì ‹E ‰$èŒÿÿÿ‰E ‹} ¸…ÿ„»‹U ƒ:„¯ÇEð‹RƒúëÿEð;Uð†œ‹u…öth‹M ‹u‹A‹Mð‹ˆ‹@…À‰ÇtÕ€>t1´&¼'¾‰$èE ‰Ã¾‰$è8 9ÃuFG€>uÝ€?tO‹E ‹Pë’€>tî‹M ‹Që…‹M ‹A‹Mð‹ˆ‹H…É…nÿÿÿ‹U…Òt‹U‰1ÀƒÄ [^_]ÃƒÄ ¸@[^_]Ë]…Ûtâ‹U ‹Mð‹B‹U‹ˆ‰ëÏë U‰åVSƒì‹]‹u ‰$èjþÿÿ…À‰Ãºt‹@ …Àu(‹CÇ$‰D$èå!‰s1҃ĉÐ[^]ô&‰t$‹C Ç$‰D$èyþÿÿ…Àº u¸ëδ&¼'U‰åWVSƒì ‹E ‰$èìýÿÿ‰E ‹U ¸…Òtt‹U ƒ:tlÇEð‹Jƒùë,¶‹] ‹C‹]ð‹˜‹B…Àt ‰Ç‹E‹u9t_ÿEð;Mðvh‹}…ÿuÑ‹] ‹Uð‹C‹‹X…ÛuÞ‹]9u׋U…Òt‹U‰1ÀƒÄ [^_]þ‰$è… ‰Ã¾‰$èx 9Ãu!FG€>uÝ€?t%‹E ‹HëƒÄ ¸@[^_]À>tá‹] ‹Késÿÿÿ‹u…öt¡‹U ‹]ð‹B‹U‹˜‰뎉ö¼'U‰åWVSƒì ‹E ‰$èÜüÿÿ‰E ‹U ¸…ÒtJ‹U ƒ:tB‹BH‰Eðx4¶¿‹}…ÿ„…‹U ‹u‹B‹Uð‹‹@…À‰Çu0ÿMðyظ@ƒÄ [^_]þ‰$è  ‰Ã¾‰$è“ 9Ãu/FG€>uÝ€?uÆ‹u…öt‹U ‹B‹Uð‹‹U‰ƒÄ 1À[^_]À>už€?u™ëÑt&‹U ‹B‹Uð‹‹X…Ûu€‹M…ÉtË‹U‰ëÄë U‰åWVSƒì ‹E ‰$èÜûÿÿ‰E ‹} ¸…ÿtJ‹U ƒ:tB‹BH‰Eðx4¶¿‹u…ö„‹U ‹u‹B‹Uð‹‹@…À‰Çu0ÿMðyظ@ƒÄ [^_]þ‰$蠉þ‰$è“9Ãu/FG€>uÝ€?uÆ‹U ‹B‹Uð‹‹U9u³‹M…Ét‹U‰1Àë­€>tÓÿMð뜋U ‹B‹Uð‹‹X…ÛtÌÿMðë„´&¼'U‰åVSƒì‹E ‹u‹]‰$èçúÿÿ…Àºt´&¼'9t‹@ …Àuõº@‰ÐZ[^]Ã…öt‰1Ò‰ÐZ[^]Ãv¼'U‰åSƒì‹M ‹]‰ $è‹úÿÿ‰Á…Û”À…É” Шºu‹A1Ò‰Y‰Ð[]ô&U‰åWVSƒì‹] ‹}‰$èIúÿÿ‰Ã…ÿ”À…Û” ШuQƒ;tLÇ1Ò‹K9Ês3‹C‰EðëB9Ês&‹uð‹–‹u90uîÿB‹K9Êréë ƒÄ1À[^_]Ãĸ[^_]Éö¼'U‰åVSƒì‹E ‹u‰$èºùÿÿ…Àºt0‹H º@…Ét$‹Y1Òƒûv‹I´&9‘tB9Ówöº@[‰Ð[^]Ã…öt‰[1Ò‰Ð[^]Ãt&¼'U‰åVSƒì‹E ‹u‹]‰$èGùÿÿ…Àºtƒ8t9Xº@v…öt‹@‹˜‰1Ò^‰Ð[^]Ãv¼'U‰åSƒì‹E ‹]‰$èûøÿÿ…Àºt …Ût‹@‰1Ò‰ÐZ[]ÃU¸‰å‹U…Òt ƒ:u‹E ‰B1À]ÉöU¸‰åSƒì‹]…Ût=ƒ;u8‹K…Ét1‹S‹‰Cüÿÿÿ‰D$B‰$‰D$è‹C‹K‹S‰DŠü1ÀƒÄ[]Ãv¼'U‰åVSƒì‹]‹u ‰$èJøÿÿ‰Ã…Û¸tƒ;uF;CwB‹E…Àu‹S‹E‰²1ÀƒÄ[^]ËS‹ ²…Étç‰t$‰\$‹C‰$èL…ÀuØë˶‰D$‰$è…Àt®ƒÄ[^]Éö¼'U¸‰åWVSƒì‹}…ÿ„Ëw1À;u „µ} Ƀáƒé€} ‡¡‹E 1ÒH÷ñ¯ÁȉEì‹E 9Eìs‰Eì;u †‰ÇEè‹] ëC9ÞvH‹ƒø„Htí‹W‹š…ÀtãÇ@ ‹š‰$è~ Eè‹G‹wǘC9ÞwÁ‰ö¼'‹E …À„©‹E ‰G‹Eì9Gw]‹EèƒÄ[^_]ùéUÿÿÿ‰ö‹Eì9G‚Ÿ‹E ‰GƒÄ1À[^_]Ãt&‰\$¸‰D$ 1À‰D$‰<$èEþÿÿ Eè‹wé|ÿÿÿ‹G‰Eð‹Eì‰D$ ¸‰D$G‰D$Eð‰$è"Úÿÿ…À…vÿÿÿ‹Eð‰G‹Eèéhÿÿÿ‹G‰EðG‰D$Eð‰$è”Ûÿÿ‰EèÇGé0ÿÿÿ‹G‰Eð‹Eì‰D$ ¸‰D$G‰D$Eð‰$è½Ùÿÿ…À…ÿÿÿ‹Eð‰Gé&ÿÿÿv¼'U¸‰åSƒì‹]…Ût(ƒ;u#‹C‰$@‰D$èøýÿÿ…Àu‹E ‹K‹S‰DŠü1ÀƒÄ[]Ãë U‰åVSƒì‹]‹u ‰$èŠõÿÿ‰Ã…Û¸t6‰4$èwõÿÿ‰Æ…ö¸t#‹C‰$@‰D$èŒýÿÿ…Àu‰^ ‹C‹S‰tü1ÀƒÄ[^]ÉöU‰åVSƒì‹]‹u ‰$è*õÿÿ…À‰ÃºtX‰4$èõÿÿ…À‰ÆºtE‹@‰\$Ç$‰D$èUõÿÿ…Àº t%‹C‰$@‰D$è ýÿÿ…À‰Âu‰^ ‹S‹C‰tü1҃ĉÐ[^]ô&¼'U¸‰åVSƒì ‹u…öt>‹N …Ét%‹A1Òƒøvt&¼'‹Y94“t`‹AB9Ðwð‰4$1ɉL$è’üÿÿ…ÀtƒÄ [^]ô&‹FÇ$‰D$èÝF‰$袅ÀuЉuð1ÒEð‰T$‰$èjÙÿÿëºH…À‰At.9Ðvœ)ÐÁàÁâ‰D$‹AЃÀ‰D$‹YÚ‰$è÷érÿÿÿ‰]ôA‰D$Eô‰$èÙÿÿ…À…gÿÿÿ‹V ‹Eô‰BéGÿÿÿ´&U¸‰åVSƒì‹]‹u …Û„…‰$¸‰D$ ¸ ‰D$1À‰D$è…Øÿÿ…Àua‹Ç@‰0NÇ@‹Ç@ ‹ÇBÇBÇBtp‹E‰BB‰$èk…À‰Æt‰$1À‰D$ègØÿÿ‰ðt&ƒÄ[^]ËE‰D$‹‰$èóÿÿ…À‰Æu 1ÀƒÄ[^]˃À‰$èÌ Æ‹‰$è þÿÿ ðë¼ÇB1ÀëÑU¸‰åƒì(‰uø‹u‰]ô‹] ƒþ‰}ü‹}t+‰$è–òÿÿ‰Ã‹E‰D$ ‹C‰t$‰D$Eð‰$èÇþÿÿ…Àt‹]ô‹uø‹}ü‰ì]ö‹Eð‰$‰D$è±üÿÿ…À‰Ãu…ÿt‹Eð‰‹]ô1À‹uø‹}ü‰ì]ËEðÇ@‰$èqýÿÿ‰Øëª¶¼'U¸‰åVSƒì‹]‹u …Û„…‰$1À¹‰L$ º ‰T$‰D$èåÖÿÿ…Àua‹Ç@‰0NÇ@‹Ç@ ‹ÇBÇBÇBtp‹E‰BB‰$èË…À‰Æt‰$1À‰D$èÇÖÿÿ‰ðt&ƒÄ[^]ËE‰D$‹‰$èØòÿÿ…À‰Æu 1ÀƒÄ[^]˃À‰$è, Æ‹‰$è€üÿÿ ðë¼ÇB1ÀëÑU¸‰åƒì(‰}ü‹}‰uø‹u ƒÿ‰]ôt/‰4$èùðÿÿ‰|$ ‰Æ‹E‰t$‰D$‹U‰$èíôÿÿ…Àt=@t4‹]ô‹uø‹}ü‰ì]Ãt&‹EÇ$‰D$èM1À‹]ô‹uø‹}ü‰ì]ËU‰T$ ‹F‰|$‰D$Eð‰$èqþÿÿ…Àu«‹Eð‰4$‰D$èÎúÿÿ…À‰Ãu‹]…Ût´‹Eð‹U‰1À몋EðÇ@‰$è“ûÿÿ‰Øéjÿÿÿ¶¿U‰åVSƒì‹U ‹u‹]‰$èðÿÿ…À‰Â¹t ƒ8uC¹@;Bw…öt‹B‹˜‰1É^‰È[^]Ãt&U‰åVSƒì‹]‹u ‰$èÊïÿÿ…À‰Ãºt4‹@º@9ðr(‰$@‰D$èÖ÷ÿÿ…À‰Âu‹SBÿ9ðw‹S‹E‰²1҃ĉÐ[^]Éö)ò•üÿÿÿ‰D$‹Sµ‰T$‹SЃÀ‰$ècýë»U‰åVSƒì‹]‹u ‰$è:ïÿÿ‰Ã…Û¸tP9s¸@vF‰t$¸‰D$ 1À‰D$‰$èªöÿÿ…Àu'‹SBÿ9ðw$‹C1ɉLüBÿ‰E ‰]ƒÄ[^]é÷ÿÿƒÄ[^]Ã)ò•üÿÿÿµ‰D$‹CЃÀ‰D$‹sò‰$è»ü‹S몶U‰åƒì‹U‰$èîÿÿ‰Â…Ò¸t¸‰D$ ‹E ‰D$‹B‰$‰D$èöÿÿÉÃvU‰åWVSƒì 1Û‹u ‹}Çë´&¾;C‰$ècû‹ÁàÑê1‰‰<$èàû9Ãrܶ‰ƒÄ 1À[^_]ÃU‰åSƒì‹E ‰D$‹E‰D$Eø‰$è°ýÿÿ1Ò…Àu*‹Eø…Àt#¶1Û€ùÄ”À€ùÆ” Шu€ùÅt‰Út&ƒÄ‰Ð[]û‰Úëïë U‰åWVSìÌ‹u‹] ‹}@‰4$‰\$èoÿÿÿ…Àºt‰\$E´‰t$‰$è#ýÿÿ…À‰Ât Ä̉Ð[^_]ËU´E°uȾB‰D$DE¬‰D$@E¨‰D$1À}‰D$‰<$èO…À‰Ãu9‰t$¸‰D$ ‹E ‰D$‹E‰$è òÿÿ‰Ã1À…Ûu2ÄL[^_]ô&‰t$Ç$èà ÄL‰Ø[^_]Ãv‰t$Ç$èÀ ‰<$èÄL Ø[^_]Ãt&¼'U‰åƒì‹E ‰D$‹E‰D$Eü‰$è±ùÿÿ1Ò…Àu‹Eü…Àt1Ò€8Å”¶¿É‰Ðö¿U¸‰åƒìh‰]ô‹] ‰uø‹u…Û‰}üt-‰t$‰$è†ûÿÿ…À‰Çu(‰t$Eè‰\$‰$è=ùÿÿ…À„¤‹]ô‹uø‹}ü‰ì]Ét$1À1ɉD$H1À1Ò‰D$D1À‰D$@1À‰D$<1À‰D$81À‰D$41À‰D$(1À‰D$$1À‰D$ 1À‰D$1À‰D$1À‰D$Eð‰L$01ɉD$Eì‰T$,‰L$ ‰D$‰$èTûÿÿ…À…wÿÿÿ‰t$Eè‰\$‰$è™øÿÿ…À…\ÿÿÿ‰t$1Ò1À‰T$ ‰D$‰$èIðÿÿ…À…<ÿÿÿÇ$‹Eè‰D$è. …ÿtƒ}ìÆtEð‰$èy…À… ÿÿÿ1ÀéÿÿÿEð‰D$‹E‰$è¸ ëݶU1À‰å옉]ô‹]‰uø‹u º‰}ü‰T$ ‰D$‰t$‰$è½ïÿÿ…Àt ‹]ô‹uø‹}ü‰ì]ÃEĉD$‹C‰$èš …Àuݸ‰D$1À‰D$‹Eĉ$è¼!…Àu(EÀ‰D$‹Eĉ$èF!…Àt$Eĉ$è· ë—Eĉ$è¥ ë…‹E@‰D$8‹E<‰D$4‹E8‰D$0‹E4‰D$,¸Xº‰D$(‹E(‰D$$EȉD$ E¼‰D$E¸‰D$‹EĉD$‹E‰D$‹E$‰D$ ‹E ‰D$‹E‰D$‹E‰$èV…À‰ÇtEĉ$è ‰øéþþÿÿ¸‰D$¸Xº‰D$‹E,‰$è*Íÿÿ…ÀtEĉ$èë ¸éÈþÿÿ‰$‹E¹‰L$ºÆÿÿÿ¿Xº‰|$0‰D$H‹E@‰T$‰t$‰D$D‹E<‰D$@‹E8‰D$<‹E4‰D$8‹E0‰D$4‹E(‰D$,1Àƒ} •À‰D$(‹E¼‰D$$EȉD$ ‹E¸‰D$‹EÀ‰D$‹EĉD$‹E‰D$ èâúÿÿ‰Ã1À…Û„-þÿÿEĉ$è; ‰Øéþÿÿt&U‰åE¤WVSìÜ]ȉD$HE ‹}‰D$DEœ‹u ‰D$@E˜‰D$…À…Gþÿÿ‰|$(‹E@‹U<‰\$‰D$8‹E8‰T$4‹U4‰D$0‹E,‰T$,‹U(‰D$$‹E$‰T$ ‹U ‰D$‹E‰T$‹U‰D$‹E‰T$‹U‰D$ ‰4$‰T$è¸ýÿÿéÞýÿÿU1À‰åS¹ƒì‰L$ ‹]º‰T$‰D$‰$èFÄÿÿ…Àu‹ÇÇ@1ÀƒÄ[]Ãt&¼'U‰åƒì‰]ø‹]‰uü1ö…Ût‹…Àt‹…Òu‰$1À‰D$è1Äÿÿ Ɖð‹]ø‹uü‰ì]Ãv‰$èØ‰ÆëÕt&U¸‰å‹U…Òt ‹…Àt ÿ@1À]Ãt&‰U]é7ÿÿÿ´&U‰åS‹M»…Ét‹…Òt ‹B1ÛH‰B…Àt‰Ø[]Ã[]éQÿÿÿU‰åWVSƒì ‹E ‹}‰Eð´&¼'‹uð…ÿ”À…ö” ШuH‹…ÛuOèRì…À‰Ãta‰D$‰<$èЉƋ…öÇ@tÁ‰$èì…Àt΀‰ðƒÄ [^_]ÃƒÄ ¸[^_]É<$1ɉL$芅ÀuÙ‹‹Uð‰1ÀëÎƒÄ ¸[^_]ô&¼'U‰åVSƒì‹u‹] …ö”À…Û” Шºu-‹…Àt'9º@u‰4$èf…À‰ÂuÇ‹…Àu1Ò‰öƒÄ‰Ð[^]ô&‰$èhHuá‰4$è=…À‰Âu×1ÒëÓvU‰åƒì(‰}ü‹} ‰uø‹u…ÿ‰]ô‰ðt1„ÀtA‰<$è¹êƒÀ‰D$ ¸‰D$1À‰D$Eð‰$èèÁÿÿ…ÀtK‹]ô1À‹uø‹}ü‰ì]Ãt&‰<$èxê@‰D$ ¸‰D$1À‰D$Eð‰$è©Áÿÿ…ÀuÁ‹]ð‰|$‰$ë‹]ð‰ðˆC‰|$‰$è3鉨‹uø‹]ô‹}ü‰ì]Ãt&U‰åƒì‹E ‰Eü1À‰D$Eü‰$è“ÁÿÿÉÃU¸‰åƒì‰]ø‹]‰uü‰D$ ¸P‰D$1À‰D$‰$è!Áÿÿ…Àt ‹]ø‹uü‰ì]Ãv‹1Ò¾‰t$ ¹‰L$ƒÀ‰T$‰$èëÀÿÿ…À‰Æ…‹‹U Ç@‰‹PÇ@Ç@ Ç@‰PÇ@Ç@ Ç@$Ç@(Ç@,Ç@0PÇ@8Ç@<Ç@4Ç@LÇ@@Ç@DÇ@H‹]ø1À‹uü‰ì]É$1À‰D$èƒÀÿÿ‰ðéÿÿÿ¶¿U‰åSƒì‹]‹E ‰$‰D$èÇþÿÿ…Àu ‹Ç@01ÀƒÄ[]ÉöU‰åVSƒì 1Û‹u…öty‹…Òts‹…Àu{‹B4‹J‰Eô‹BL‰Eì‹B…Àt‹B…ÀuY‰MðB8‰D$Eô‰$èñ¿ÿÿ ˃À‰D$Eð‰$èÛ¿ÿÿ Ã1À‰D$Eì‰$èÈ¿ÿÿ‰4$ Ã1À‰D$踿ÿÿ ÃƒÄ ‰Ø[^]ÉEð륉$èpè…Àt»€‹émÿÿÿU‰åS‹M»‹E …Ét‹…Òt…Àt 9»@uÿB1Û‰Ø[]ÉE ‰M[]éÃýÿÿvU‰åS‹M»…Ét‹…Òt ‹B1ÛH‰B…Àt‰Ø[]Ã[]éáþÿÿU1À‰å‹U…Òt‹B]Ãë Uº‰åVSƒì ‹u‹] …öt<…Ût‹N89Ùs>‹F4º‰EôF8‰D$Eô‰T$‰\$ ‰$è½ÿÿ…À‰Âu‹Eô‰F4ƒÄ ‰Ð[^]Ãt&1Ò9Ás¹ƒÄ ‰Ð[^]ô&¼'U¸‰å‹U…Òt ÇB<1À]öU¸‰åSƒì‹]…Ût)‹K<‹S8A9Âr"‹E ‹S4ˆ‹SÇC ‰ù‰ÐÓàƒÇ Eð9÷}K‹C…Àu·‹‹BH‰B…Àx~‹¶@‰‰K‹Sƒúÿu¸ƒÄ[^_]ô&ÇCÿÿÿÿë´&¹‰ø)ð)Á‰C Óú¸‰SNÿÓà…Eðt‹uð÷Ø‹U ð‰1ÀƒÄ[^_]Ë]ðH‹M !؉1Àëé‰$è¡ä‰Á‰Ké{ÿÿÿ´&U‰åWVSƒì‹E‹}…ÀŽÓXà‰Æ…Û~)Þ‰t$Eð‰D$‹U‰$èxþÿÿ…À…¢ƒþ œÀ1Ò…ÿ”Â…Ð…¯ÇEè…Û~puìëL‰\$‰t$‹E‰$è8þÿÿ…Àuf‹Eðƒë Áè…ÿ•Â!ЋUìÐtÇE者ÿty‰ÐÁø÷Ð-€‰Eð…Û~ƒû |¯‰t$¸ ‰D$‹U‰$ë¨t&‹E …Àt‹Eð‹M ‰‹EèƒÄ[^_]ËE …Àt ‹E ǃÄ1À[^_]øÿÿÿÿ‰ñÓà÷Ð!Eðé>ÿÿÿÇEðÿÿÿÿëU¸‰åVSƒì ‹]…Ût<‹S 1À…Òt3‹KL…É…¹‹s…ötqÇC ‹C‹K)ÐÑ=ÿ‰K‰Cv 1ÀƒÄ [^]É΋KS‰$)Îð‰EôÀ¹‰D$ Eô‰L$‰D$è¸ÿÿ…Àut‹Eô‹K)ð‰Cñ‰K1Àë´t&‹K‹‰T$‰ $‰D$ ¸‰D$è¢à…À‰Æ~ ‹‰$èòß;s rCÇC 1Àéoÿÿÿ‰T$‹C‰ $‰D$è,‹S é,ÿÿÿÇC‹K‰ò‰s ‹Eô‰K‰Cë…ö~#‹C)ð‰D$‹S2‰D$‰$èËá‹C)ð‰C ¸é ÿÿÿ‰ö¼'U‰åƒìH‰]ô‹]‰uø‹u …Û‰}ü”À…ö” Шºu‹CL…Àt‰$èwþÿÿ…À‰Ât‹]ô‰Ð‹uø‹}ü‰ì]Éö‹CL}؉<$‰D$èn‹CL‰EÔ1À‰D$EÔ‰$èw¸ÿÿ…À‰ÂuÀÇCL‰|$‰4$è^J1Òë©v¼'U¸‰åSƒì‹]…ÛtQ‰$èõýÿÿ…ÀuE‹CL…Àu4ÇEø¸‰D$ ¸X‰D$1À‰D$Eø‰$èÀ·ÿÿ…Àu‹Eø‰CL‰$èžu1ÀƒÄ[]öU‰åWVSƒì ‹}ƒÿ ~>ë ‹E ¹ ‹U‰L$‰D$‰$èÅÿÿÿ…À…‘ƒE ƒï ƒÿ Ñ‹E ‹M¶‹E‹q ‹P‰ñÓãþ Óƒþ~N‰Â‰Ñ‹@ ‹Rˆ‹A @;A‰A tp‹E ƒî)÷‰ù‹Óûë ‹U‹B ‰Ñ‹Rˆ‹A @;A‰A t/ÁûƒîƒþÛ¸ÿÿÿÿ‰ñÓà÷Ð!ËE‰p ‰X1ÀƒÄ [^_]Ãt&‰ $è¸üÿÿ…ÀtÅ‹M‰q ‰Yë݉ $è¡üÿÿ…Àt„‹U‰r ‰ZëÆ‰öU1À‰åWVSƒì‹U‹}…ÒއZà‰Ñ…Û~)Ù‰L$‹U‹E ‰<$Áè…Ò•Â!Ð÷؉EðE ‰D$è¤þÿÿ…ÀuPƒû |,uð´&‰t$¸ ‰D$‰<$è{þÿÿ…Àu'ƒë ƒû }ß…Û~‰\$Eð‰D$‰<$èXþÿÿ…Àu1À‰öƒÄ[^_]ô&U¸‰åSƒì‹]…Ût!‰$¸1ɉD$ 1À‰D$‰L$è ÿÿÿ…Àt ƒÄ[]öÇC ÇC‰]ƒÄ[]é…ûÿÿt&U‰åƒì(‰uø‹u‰}ü‹} ‰]ô‰4$ècûÿÿ…Àuo‹F=ÿv9øƒ ‹VN‹^)Ó;‰Uð9ÐrU‰D$ ¸‰D$Eð‰D$‰ $è¹³ÿÿ…ÀtXÇF‹F‰^ ‰F‹Eð9ø‰FÀƒà´&‹]ô‹uø‹}ü‰ì]Ãv‰ $‰D$ ¸‰D$Eð‰D$èa³ÿÿ…Àu¨‹F؉F‹Eð)؉F‹]ô1À‹uø‹}ü‰ì]ô&¼'U¸‰å‹U…Òt ÇB 1À]öU‰å‹E…ÀtÇ@ Ç@]ëÅ]¸ô&¼'U‰åSƒì‹]‹C…Àt‹K …Éu(ÇC$ÿÿÿÿ‹C$Y[]Ë…Àtì‰$èl݉C$‹C$Y[]Éö‹C¾@ÿK‰CâÿAÿ‰S$‰C ‹C$Y[]ö¼'U¸ÿÿÿÿ‰åVSƒì‹]…ÛtT‹s$‰$èqÿÿÿƒø ‰Á”À1Òƒþ ”Â…Ðu=ƒù ”À1Òƒþ ”Â…Ðu+ƒù ”Àƒù ” Шt5ÿC(¹ ÇC,‰ÈƒÄ[^]É$èÿÿÿ‰Áƒù ”Àƒù ” Шu˃ù tƒùÿtÐÿC,ëËt&‹C,ƒàøƒÀ‰C,븉öU¸ÿÿÿÿ‰åSƒì‹]…Ût‹K ;Kt‹E ‹Sˆ1ÀÿC Z[]Ãv‰$èèøÿÿ…Àuí‹K ëÚë U¸ÿÿÿÿ‰åƒì‰uü‹u‰]ø‹] …öt%ƒû t0‰\$‰4$è„ÿÿÿ…Àuƒû t6ÿF,1À¶‹]ø‹uü‰ì]ö‹FHöÄu(öÄuCÿF(1ÀÇF,ëÕ‹F,ƒàøƒÀ‰F,1ÀëÅt&‰4$» ‰\$èÿÿÿ…Àu«‹FHë¾¶‰4$¹ ‰L$èÿþÿÿ…Àu‹ë¦‰ö¼'U¸‰åVSƒì‹] ‹u…Ût&¶„Àt‰ö‰4$¾À‰D$èÁþÿÿ…Àu C¶„Àuå1ÀƒÄ[^]ö¿U¸‰åVSƒì‹] ‹u…Ût&¶„Àt‰ö‰4$¾À‰D$èÁþÿÿ…Àu C¶„Àuå1ÀƒÄ[^]ö¿U¸‰åWVSƒìl‹u…ötqÇF<}˜ÇF,ë‰\$‰4$èóÿÿ…ÀuNƒû tS‰4$è[ýÿÿƒøÿ‰Ãt]‹F0@9F,uÓ‹F(‰<$@‰D$¸»‰D$è؉<$èúDÿÿ‰\$‰4$èÎòÿÿ…Àt²ƒÄl[^_]Éö‹} …ÿt‹F4‹U ‰ƒÄl1À[^_]ÃÄl¸[^_]Ãv¼'Uº‰åVSƒì‹]‹u …Ûte‰t$‰$èÍñÿÿ…À‰ÂuSÇC<9ðsF¶¿‹C…Àt>‹K<‰ð‹S )È9Âs]1À…Òu{)C)ÂC‰S …À„Š‹S<ЉC<9ðrÆ1҃ĉÐ[^]Ë…Àtm‰D$ ‰ò‹C<)‰T$º‰T$‹K4ȉ$èPÙë´‰D$‹C‰D$‹C4Á‰ $èæØ‹S<‰ð)ЋS ë…‰T$‹C‰D$‹C4Á‰ $èÂØ‹C ‰Âécÿÿÿºézÿÿÿ´&¼'U¸‰åƒì(‰]ô‹]‰uø‹u …Û‰}ütr9s8rm‰$èuõÿÿ…Àua…öt ‹SL…Ò…ª‹C…À„ç‹S ‹K29ÈwG‹K‰t$‹C4‰D$‰$è1Øs )s‰$è#õÿÿ‰Â1À…Òt ‰Ð‰ö¼'‹]ô‹uø‹}ü‰ì]ËCS‹{)Ç9‰Eðð‰D$ ¸‰D$Eð‰D$‰$èt­ÿÿ…Àu0‹Eð‹K‹S )øù‰K‰Céqÿÿÿ‰t$‹C4‰$‰D$èÅté>ÿÿÿÇC‹K‹Eð‰{ ‰K‰C‰$è‚ôÿÿ…À…jÿÿÿv¼'‹ …É•À1Ò…ö•Â1ÿ…Ðu9÷¸‚?ÿÿÿ‹]ô1À‹uø‹}ü‰ì]ÉL$ ¸‰t$‰D$‹C4‰$è„Õ‰ÇëÄU‰åWVSƒì,‹]ÇEì‹U ‹u…Û”À…Ò” Шºu‹…Àt ‹E ‹8…ÿuºƒÄ,‰Ð[^_]Ãt&‰$èÈóÿÿ…À‰Âuä‹U ‹J…Ét ‹C…À„.…ö„oC‰Eäëb‹K‰|$‹E ‹@4‰D$‰$èÖ{ ){‰}ì‹C…Àu$‹¹‰|$‹U ‰L$‰D$ ‹B4‰$è°Ô‰Eì9}ì‚e+uì„þÿ¿w‰÷‰|$‹U ‰$èmüÿÿ…À…/…ÿt‹SL…Òup‹C…Àt’‹S ‹K:9ȆUÿÿÿ‹C‹S)ЉEè‹Mä‰Eðø‰D$ ¸‰D$Eð‰D$‰ $è`«ÿÿ…À…©‹C‹Mè‹UèÁ‹Eð‰K)ЋS ‰Céÿÿÿ‰|$‹M ‹A4‰$‰D$è¤réuÿÿÿ‰Ñ‹R 9ò‚‹‰t$‹U ‰D$ ¸‰D$‹B‰$è±Ó‹M q)q)q 9ðÒâéXþÿÿ‹S…Òu1ÒéJþÿÿ‰$è òÿÿ…À‰Â…8þÿÿ1Òé1þÿÿÇC‹Eè‹K‰C ‹Eð‰K‰C‰$èîñÿÿ…À„nþÿÿ‰Âéþÿÿºé÷ýÿÿ…Òu‹M Q)QºÇA éÙýÿÿ‹‰T$‰D$ ¸‰D$‹A‰$èùÒ‹E ‹P ëÀU‰åVSƒì»‹U‹u …Òt‹ …Ét‹Z…Ût‹B‹J)È…öt‰1ۃĉØ[^]Ãv‰ $èˆÔƒøÿ»uÚëà¶¿U¹‰åƒì‹U‰]ô‹]‰uø‹u …Û‰}ütW‹…ÀtQ‹{…ÿtYƒú„ƒú„“…öxl‹K‹{‹S )ù9ÆwZ‰È)ðÂC7‰S ‰CÇC 1ÉÇC‹]ô‰È‹uø‹}ü‰ì]ÉT$‰t$‰$èÉÓ…À¹xØÇC ë¿´&‹]ô¹‹uø‹}ü‰ì‰È]ËC‹K)ÈÆémÿÿÿ‹C‹S‹{ )ÐøÆéYÿÿÿU‰åVSƒì‹u‹] ‰ö‰t$‹C‰$è!r= têƒÄ[^]ÃvU¸‰åƒì‰D$‹E ‰D$‹E‰$èß;ÿÿÉ1ÀÃt&¼'U‰å]Ãt&¼'U¹È‰åW…Xþÿÿ•8ûÿÿV1ö1ÿSìü‰… ûÿÿ»þÿÿÿ‰µ$ûÿÿ‰Æ‹…4ûÿÿ‰½(ûÿÿ‰×‰•ûÿÿ‰ûÿÿ‰,ûÿÿ‰…8ûÿÿ‹(ûÿÿ‹•ûÿÿf‰‹ ûÿÿÒD þ9ð‡)ÎÑþF½ûÿÿljµûÿÿ‡S‰•ûÿÿúÈv ¹È‰ûÿÿ‹µûÿÿ‹… ûÿÿ‹•ûÿÿö‰… ûÿÿD‰$èæÏ…À‰Ã„‰$‹…ûÿÿ‹ ûÿÿÀ‰D$‰L$èþω ûÿÿ‹•ûÿÿFƒàü‹µûÿÿÃÁâ‰ßƒúv öÃ…šü‰ÑÁéó¥‰ûÿÿ…Xþÿÿ;… ûÿÿt‹• ûÿÿ‰$èGÏ‹ûÿÿ‹… ûÿÿ‹•ûÿÿtHþ|Šü‹ûÿÿDHþ9ð†Y‹…(ûÿÿ¾˜Ð¾ƒûôtOƒ½,ûÿÿþ„Þ‹•,ûÿÿ…ÒŽZ½,ûÿÿºw ‹,ûÿÿ¶‘°½ÓƒûPw¾ƒP½9Є5‹…(ûÿÿ¶˜¼…Ût@¶“0¼¸)Љ•ûÿÿ‹‡ƒûE‰•0ûÿÿ‡Oÿ$À”Àƒûý” Ш„ù‹…$ûÿÿ…À„!ƒ½$ûÿÿ„¹‰$ûÿÿë;µ ûÿÿ„rƒîƒï¿‰…(ûÿÿ‹(ûÿÿ¾™Ð¾ƒûôtÓCƒûPwÍ€»P½uľ›ð¼…Û~¹ƒû„\ ‰(ûÿÿ‹…4ûÿÿƒÇƒÆ‰é‘ýÿÿ‹{ƒê‰‹µûÿÿƒÆéNþÿÿƒ½,ûÿÿŽß»þÿÿÿ‰,ûÿÿéTÿÿÿ‹U¸¹!¿‰D$‰L$‹B‰$è¢8ÿÿ1À1Ò‰D$¸‰D$…0ûÿÿ‰T$ ‰$èoÏÿÿ…À…¸‹Gü‰D$‹…0ûÿÿ‰$è‚Èÿÿ…À…›‹•0ûÿÿ¶›Ð»‹…ûÿÿÁà)Ç‹…ûÿÿƒÇ‰¾“»À)Æ·¿Á‰•(ûÿÿƒúPwf¾‚P½f9È„ù¾›q»‰(ûÿÿƒÆéüÿÿ…þÿÿƒî;µ ûÿÿuõ»Xþÿÿ; ûÿÿt‹… ûÿÿ‰$è¡Ì‰ØÄü[^_]Ã1À1Ò‰…,ûÿÿéµýÿÿ¾›ð¼…ÛŽúýÿÿƒû„Ù ‹…,ûÿÿ…Àt ¸þÿÿÿ‰…,ûÿÿƒÇƒ½$ûÿÿ‹…4ûÿÿƒ•$ûÿÿÿ‰éYÿÿÿ‹U¸4¿‰D$‹B‰$èCûÿÿéÐýÿÿ‹U…4ûÿÿ‰$‰T$èùúÿÿ‰…,ûÿÿéýÿÿ‹‰…0ûÿÿ‰Âé»þÿÿ¾‚ð¼ƒÆ‰…(ûÿÿé”ûÿÿ1ɺ‰T$‹U‰L$ ‹‰D$‹B‰$è÷zÿÿ…À…ÿÿÿ¸‰D$‹‰D$…0ûÿÿ‰$è²Äÿÿ…À…ëþÿÿ‹M‹…0ûÿÿ‹QÇA ‰é6þÿÿ÷ÛéÀüÿÿ‹º‰T$‰D$ ‹Gü‰D$…0ûÿÿ‰$è¥Ìÿÿ…À…žþÿÿ‹•0ûÿÿ‹M‰Q ‹‰T$‰D$ ¸‰D$…0ûÿÿ‰$èÎÿÿ…À…iþÿÿ‹M‹…0ûÿÿ‹Q‰‹A ‰$‰D$ ¸‰D$‹…0ûÿÿ‰D$èzÿÿé‘ýÿÿ‹‰D$ ¸‰D$‹Gü‰D$…0ûÿÿ‰$è¯Íÿÿ…À…þÿÿ‹U‹M‹B‹•0ûÿÿ‰‹…0ûÿÿ‰Â‰A éRýÿÿ‹‰D$ ¸‰D$‹Gü‰D$…0ûÿÿ‰$èbÍÿÿ…À…»ýÿÿ‹E‹P‹…0ûÿÿ‰‹UÇB éýÿÿ¸‹U‰D$¸A¿‰D$‹B‰$è=5ÿÿ¹‰L$‹Gü0ûÿÿ‰ $‰D$èÃÿÿ…À…Xýÿÿ‹‰D$ ¸‰D$‹…0ûÿÿéÿÿÿ‹¹‰L$‰D$ ‹Gü‰D$…0ûÿÿ‰$è¹Ìÿÿ…À…ýÿÿ‹E‹M‹P‹…0ûÿÿ‰é¡þÿÿ‹Gü‰…0ûÿÿ¸‰D$¸Y¿‰D$‹M‹A‰$è’4ÿÿé3üÿÿ¸‹U‰D$¸A¿‰D$‹B‰$èm4ÿÿ¸‰D$é+ÿÿÿ‹Gü‰…0ûÿÿ‰$èŽÄÿÿ…À…‡üÿÿ‹‰D$‹…0ûÿÿ‰$è’Îÿÿ…À…küÿÿ‹…0ûÿÿ‹M‰D$ ¸‰D$‹‰D$‹A‰$è#xÿÿéœûÿÿ1À‹M‰D$ ¸‰D$‹‰D$‹A‰$èûwÿÿ…À…üÿÿ¹‰L$‹‰D$…0ûÿÿ‰$è¶ÁÿÿéOûÿÿ‹Gü‰…0ûÿÿ‰$èàÃÿÿ…À…Ùûÿÿ‹‰D$‹…0ûÿÿ‰$èäÍÿÿ…À…½ûÿÿ‹…0ûÿÿ‹U‰D$ ¸‰D$‹‰D$‹B‰$éMÿÿÿ‹‰D$ ¸‰D$‹Gü‰D$…0ûÿÿ‰$èËÿÿ…À…jûÿÿ‹E‹M‹P‹…0ûÿÿ‰‹A ‰$‰D$ ¸‰D$‹…0ûÿÿ‰D$èwÿÿ…À…/ûÿÿ‹…0ûÿÿ‰D$‹Gü‰$èùÂÿÿ…À…ûÿÿ‹…0ûÿÿ‰D$‹Gü‰$èÌÅÿÿ…À…õúÿÿ‹Güéûÿÿ‹U‹B ‰…0ûÿÿ‹‰T$ º‰T$‰D$…0ûÿÿ‰$è_Êÿÿ…À…¸úÿÿ‹M‹…0ûÿÿ‹Q‰éLÿÿÿ‹Gü‰…0ûÿÿ¸‰D$¸k¿é¤ýÿÿ‹Gü‰…0ûÿÿ¸‰D$¸Y¿‰D$‹U‹Béˆýÿÿ‹Wü¹‰L$ ‰•0ûÿÿ‹‰$‰D$1À‰D$èœÂÿÿésþÿÿ‹‹M‰•0ûÿÿÇA éŒùÿÿ‹U‹Bé¹úÿÿ¸‰D$éýýÿÿ‹‹M‰Â‰…0ûÿÿÇA éZùÿÿ1À‰D$ ¸‰D$‹‰D$…0ûÿÿ‰$èkÉÿÿ…À…Äùÿÿ¸‰D$¸‚¿é?ÿÿÿ‹U¸‰D$¸¿‰D$‹B‰$èP1ÿÿ¸0ûÿÿ‰D$‹Gü‰ $‰D$è2¿ÿÿ…À…kùÿÿ1À‹U‰D$ ¸‰D$‹Gü‰D$‹B‰$è&uÿÿ…À…?ùÿÿ‹€8u"¹°¿¸‰L$‹M‰D$‹A‰$è×0ÿÿ‹‰D$‹…0ûÿÿ‰D$…0ûÿÿ‰$èɼÿÿ…Àu º¸Æ¿‰T$‹U‰D$‹B‰$è•0ÿÿ‹0ûÿÿ‰D$ ¸‰D$‹Gü‰ $‰D$èQÈÿÿ…À…ªøÿÿ‹E‹P‹…0ûÿÿ‰éü÷ÿÿ1À‹M‰D$ ¸‰D$‹Gü‰D$‹A‰$èRtÿÿ…À…køÿÿ‹€8u"º°¿¹‰T$‹U‰L$‹B‰$è0ÿÿ‹‰D$0ûÿÿ‹Gü‰ $‰D$é*ÿÿÿ‹0ûÿÿ‰D$ ¸‰D$‹Gü‰ $‰D$èÆÿÿ…À…ý÷ÿÿ‹¹‰L$‰D$ ‹…0ûÿÿéýÿÿ¸‹U‰D$¸A¿‰D$‹B‰$è‚/ÿÿ¸‰D$0ûÿÿ‹Gü‰ $‰D$èd½ÿÿ…À…÷ÿÿ‹‰D$ ¸‰D$‹…0ûÿÿéËøÿÿº¸A¿‰T$‹U‰D$‹B‰$è"/ÿÿ¸랸‰D$‹GüéBûÿÿ¸0ûÿÿ‰D$‹Gü‰ $‰D$èì¼ÿÿ…À…%÷ÿÿ‹‰D$ ¸‰D$‹…0ûÿÿ‰D$…0ûÿÿ‰$èÆÿÿ…À…ööÿÿ‹M‹…0ûÿÿ‹Q‰‹…0ûÿÿ‰D$‹Gü‰$è²¾ÿÿ…À…Ëöÿÿ‹…0ûÿÿ‹U‰B ‹GüéZ÷ÿÿ‹‰D$ ¸‰D$‹Güë“‹M¸‰D$¸à¿‰D$‹A‰$èB.ÿÿ¸‰D$‹Gü‰D$…0ûÿÿ‰$è$¼ÿÿ…À…]öÿÿ‹•0ûÿÿ‰$‰D$ ¸‰D$‹…0ûÿÿ‰D$èÕÅÿÿé>÷ÿÿ1Ò¸‰T$ ‹U‰D$‹‰D$‹Béíùÿÿ‹º0ûÿÿ‰T$‰D$ ‹Gü‰ $‰D$èìÃÿÿ…À…åõÿÿ‹•0ûÿÿ‹E‰P ‹‰T$•0ûÿÿ‰D$ ¸‰D$‰$éóúÿÿ¸0ûÿÿ‰D$‹Gü‰ $‰D$èY»ÿÿ…À…’õÿÿ‹¹‰L$‰D$ ‹…0ûÿÿ‰D$…0ûÿÿ‰$è Åÿÿ…À„{þÿÿé^õÿÿ‹‰D$ ¸‰D$‹Gü‰D$…0ûÿÿ‰$èÙÄÿÿ…À…2õÿÿ‹M‹…0ûÿÿ‹Q‰‹…0ûÿÿ‰A é4þÿÿºú¿»‰T$‹U‹B‰$è¹ðÿÿé×ôÿÿ1ÛéÐôÿÿU‰åSƒì‹]…Ût)¶„Àt"t&¼'¾À‰$èuÃ…Àt C¶„Àué¸Z[]ÃU‰åW1ÿVSƒì ‹]‹E …ÛǸt1¶„Àt#¾t&¾À‰$è%Ã…Àu‰÷CF¶„Àuæ‹E ‰81ÀƒÄ [^_]ô&U‰åWVSƒì ‹E‹} ‹…Éul‹E1ö‹t&¶ ¾Á‰$èÒÂ…Àub¶ €ù(t]„É…æ‰|$‹E‰$èOèÿÿ…Àu7‹‰$èÿÿÿ…Àu¶ €ù •À1Ò€ù •Â…Ðt«‹EÇ‹EÇIÁ1ÀƒÄ [^_]ö „Ét§€ù(tCézÿÿÿCF´&„jÿÿÿ¾ƒø)t"…Àt"ƒø(tC…öëâFC…öë܃ø\uðCC…öëÑNC…öëʉ|$‹E‰$è«çÿÿ…Àu“‹‰$è]þÿÿ…À…mÿÿÿ¶< •Â< •À¶À…Â…UÿÿÿC…ö눋EÇ‹E‰éOÿÿÿt&U‰åWVSƒì<‹E ÇEÈ…Àt ‹E Ç‹E…Àt ‹UÇ‹E…Àt ‹EÇ‹}…ÿt‹UÆ‹u…öt ‹EÇ@‹] …Ût ‹U Ç‹M$…Ét ‹E$Çÿÿÿÿ‹U(…Òt ‹U(Çÿÿÿÿ‹E,…Àt ¡äñ‹U,‰‹E0…Àt ‹E0Ç‹E4…Àt ‹U4Ç‹E8…Àt ‹E8Ç‹E<…Àt ‹U<Ç‹E@…Àt ‹E@ÇÇEØÿÿÿÿÇEÐÇEèÇEì¶‹}è…ÿu‹UEð‰D$‰$è7æÿÿ…À…ŒEì‰D$‹Eð‰$èýÿÿÿEЋEðÇEè€8;„1‰$¾»g‰t$‰\$è}˜ÿÿ…À„‹uð¶< ”Â< ”À Ѓà‰EÔ„,1ÿƒ}Ð~…ÿuƒ}ЋMÔ”À…É” Ш…È‹]ð…ÿ‰Þ‰]ätBÇEØ ë‹uð‹EØ‹…ò‰$蔿‰D$‰\$‰4$èô—ÿÿ…À„RÿMØyδ&‹EUð}è‰|$ uä‰t$‰T$‰$èüÿÿ…À……ƒ}Ø wr‹UØÿ$•¤Ã‹]äÇEÈ‹E Ç‹U̹…¾‰t$‰L$‰$èu—ÿÿ…À…ü‹Eä¾@‰$è.¿…À„ ÇEÈ‹E Ƕ‹]ì…Û…Uþÿÿ1ÀƒÄ<[^_]Éuä‰ó¶€ù:•À1Ò€ù ŸÂ…Ât"€ùt‰ØC‰]ä¶H€ù:•Â1À€ù ŸÀ…Âuß1ÿ9ó„þÿÿ€;:…‡þÿÿƒ}Ð¿Ž‚þÿÿ‰4$èõúÿÿ…À„rþÿÿ놋u0…ö„pÿÿÿ‹Eä‰$è¿‹U0‰‹]ì…Û…µýÿÿé[ÿÿÿ‹}@…ÿ„Eÿÿÿ‹Eä‰$èÚ¾‹U@‰ëÓ‹E<…À„(ÿÿÿ‹Eä‰$è½¾‹U<‰ë¶‹E8…À„ ÿÿÿ‹Eä‰$è ¾‹U8‰뙋E4…À„îþÿÿ‹Eä‰$胾‹U4‰éyÿÿÿ‹M,…É„Îþÿÿ¸0Áº ‰D$‹Eä‰T$‰$èñ•ÿÿ…À…Ñ¡àñ‹U,‰é:ÿÿÿÇEÈ‹Eä€8te‰|$ ‹UEð‰t$‰D$‰$èúÿÿ…À…vþÿÿ‹]ä€;"„"ƒ}È„&ƒ}È„¦ƒ}È„€;t C‰]ä€;u¦‹]È…Û„&þÿÿ¸é)þÿÿ‹M…É„þÿÿ‹Eä‰$覽‹U‰éœþÿÿ‹]…Û„ñýÿÿ‹Eä‰$膽‹U‰é|þÿÿ‹}…ÿ„Ñýÿÿ‹E例U‰t$‰D$‰$èv»‹EÆ@‹]ì…Û…üÿÿéªýÿÿ‹u …ö„cÿÿÿÇEÈ‹EäÇEÌ€8"„:‹U̹ŒÂ»‰\$‰L$Љ$è›”ÿÿ…À„3‹]ä‹U̹¾‰t$‰L$‰$èp”ÿÿ…À„È‹]ä‹U̸ ‰D$¸¤Â‰D$‰$èE”ÿÿ…À„^‹]ä‹U̹®Â¾‰t$‰L$‰$è”ÿÿ…À„õ‹]ä‹U̸‰D$¸¶Â‰D$‰$èï“ÿÿ…À„Œ‹]ä‹U̹¿Â¾‰t$‰L$‰$èÄ“ÿÿ…À„#‹]ä‹UÌ¿¾È‰|$‰t$‰$虓ÿÿ…Àt*‹E̹Í»‰\$‹Uä‰L$Љ$ès“ÿÿ…À…K‹Eä¾@‰$è,»…À…¬ûÿÿ‹]ä¶C<(„ ûÿÿ‹}Ì…ÿ„¥ûÿÿ<"…ûÿÿéˆûÿÿ¸ ‰D$¸Ò‰D$‹Eä‰$è“ÿÿ…À…é‹]ä€;„¿¶‰Ú<"t&<(„„<;„ýC‰]ä€;„ö¶‰Ú<"uÚC‰]ä€ztäv¶<"tÖ<\„A€;„ÈC‰]ä€;uß麋UØ‹•ò‰$躋UðЉEäé›úÿÿCƒ}ȉ]ä…Úüÿÿ‰$º¸ß‰T$‰D$èS’ÿÿ…À…ª‹]ä‹E$ƒÃ‰]ä…Àt ‹E$ÇÇEȉ$¸‰D$¸æÂ‰D$è’ÿÿ…À…`‹]ä‹E$ƒÃ‰]ä…Àt ‹U$ÇÿMȃ}È…Züÿÿ‰$E້D$ E܉D$¸ïÂÇEà‰D$èø¸‰\$‹Eà¹õ‰L$‹UäЉ$蛑ÿÿ…Àup‹Eà…Àti‹UÜ…Ò~bƒú@]‹]äËE ‰]ä…Àt‹E ‰€; „çÇEȉ$¸‰D$¸ù‰D$èF‘ÿÿ…À…ÇEÈ‹E(…Àt ‹U(Ç‹]äé ûÿÿ¸‰D$¸Ã‰D$‹Eä‰$è‘ÿÿ…À„òýÿÿ‹Eä¹Ã»‰\$‰L$‰$èÝÿÿ…À„Íýÿÿ¸Ãº‰D$‹Eä‰T$‰$è¸ÿÿ…À„¨ýÿÿ¸‰D$¸Ã‰D$‹Eä‰$è“ÿÿ…À„ƒýÿÿ¸éNùÿÿÇEÌéºûÿÿt&C‰]äé¶ýÿÿ‰|$ ‹UEð‰t$‰D$‰$èõÿÿ…À…ùÿÿ‹]äé^ýÿÿÇEØÿÿÿÿ‹]ì…Û…K÷ÿÿéñøÿÿ¸»Ã‰D$‹Eä‰\$‰$è ÿÿ…À…å‹EäX‰]ä€x „K‰$¹º!ÉL$‰T$èÔÿÿ…À…¥þÿÿÇEÈ‹E(…À„“þÿÿ‹E(‹]äÇé*úÿÿ‹]äéúÿÿ‹]äénýÿÿ‹Eä¾@‰$èZ·…À…b‹]ä¶C<(„V‹UÌ…Ò„¯ûÿÿ<"…§ûÿÿé>‹Eä¾@‰$è·…À…T‹]ä¶C<(„H‹}Ì…ÿ„Fûÿÿ<"…>ûÿÿé0‹Eä¾@‰$èÞ¶…À…þ‹]ä¶C<(„ò‹UÌ…Ò„Ýúÿÿ<"…ÕúÿÿéÚ‹Eä¾@ ‰$è ¶…À… ‹]ä¶C <(„‹}Ì…ÿ„túÿÿ<"…lúÿÿéü‹Eä¾@‰$èa¶…À…É‹]ä¶C<(„½‹UÌ…Ò„ úÿÿ<"…úÿÿ饉ö‹Eä¾@‰$è!¶…À…q‹]ä¶C<(„e‹}Ì…ÿ„Ÿùÿÿ<"…—ùÿÿéM‰ö‹]äéƒöÿÿ¸ ‰D$¸;Á‰D$‹Eä‰$èûÿÿ…À…øÿÿ¡äñ‹U,éøÿÿC‰]ä‰ö‰|$ ‹UEð‰t$‰D$‰$è–òÿÿ…À…‹öÿÿ¸ ‰D$¸&ÉD$‹Eä‰$è¡ÿÿ…À…‘úÿÿƒEä Eð‹U‰|$ ‰t$‰D$‰$èKòÿÿ…À…@öÿÿ‹]ä€;=…búÿÿ‰|$ ‹UC‰]äEð‰t$‰D$‰$èòÿÿ…À…öÿÿ‹E…À„.úÿÿÇEÌ‹Eä€8"„—‹U¹2û Ç@‹Ủ\$‰L$Љ$èûŒÿÿ…Àu ‹EÇ`‹E̹?û‰\$‹Uä‰L$Љ$èÌŒÿÿ…Àu ‹UÇ‹E̹Oû‰\$‹Uä‰L$Љ$èŒÿÿ…Àu ‹EÇP‹E̹_û‰\$‹Uä‰L$Љ$ènŒÿÿ…Àu ‹UÇp¸‰D$¸qÉD$‹EäEÌ‹Ủ$è>Œÿÿ…Àu ‹EÇ€‹U‹=”ƒø`”À Ш„ ùÿÿ‹]ä€;„Ëûÿÿ¶‰Ú<"„{<(„­<;„[C‰]ä€;uÚ‰|$ ‹UEð‰t$‰D$‰$è˜ðÿÿ…À…ôÿÿÇEÌ‹Eä€8"„‹U̹û‰\$‰L$Љ$莋ÿÿ…Àu ‹E‹Uä¸ỦD$¸—ÉD$‹Ẻ$è^‹ÿÿ…À…Bÿÿÿ‹U é4ÿÿÿ‹Eä¶@<(„ãóÿÿ‹UÌ…Ò„½õÿÿ<"…µõÿÿéËóÿÿ‹]äÇEÈ‹E Ç éO÷ÿÿ‹]äÇEÈ‹E Ç@éáöÿÿ‹]äÇEÈ‹E Çéôöÿÿ‹]äÇEÈ‹E Çé0öÿÿ‹]äÇEÈ‹E ÇéCöÿÿ‹]äÇEÈ‹E ÇéVöÿÿC‰]äé¥þÿÿ´&C‰]ä€z„‹þÿÿ¶<"„|þÿÿ<\t€;„xþÿÿC‰]ä€;ußéjþÿÿC‰]äëã‰|$ ‹UEð‰t$‰D$‰$èüîÿÿ…À…ñòÿÿ‹]äé5þÿÿ¸‰D$¸œÃ‰D$‹Eä‰$èÿ‰ÿÿ…À…Ðøÿÿ‹EäX‰]ä€x tq‰$¸‰D$¸!ÉD$èΉÿÿ…À…ŸøÿÿÇEÈ‹E(…À„øÿÿ‹U(‹]äÇé$ôÿÿX‰]äéªùÿÿÇEÌéßýÿÿÇEÌé]üÿÿC‰]äéøÿÿX‰]äë‡ë U1À‰åW1É1ÒVSƒìL‹]‰D$01À‹} ‰D$,Eð‹u‰D$(1À‰D$$1À‰D$ 1À‰D$1À‰D$Eì‰D$‹EÇEäÇEè‰D$‹E‰L$8‰T$4‰D$ Eè‰D$Eä‰D$‰$èîîÿÿ…ÀuJ‹U踅Òt>ÇC ‹EäÇCƒø„–*ƒø„§ƒøtj¸ë ƒÄL[^_]Ãø t~Bƒø@u؉t$1À‰D$ ‰T$‰|$‰$è2A…ÀuΉ<$èVÑÿÿ…Àu‹E…Àt‹Eè‹U‰1À믃ø뼉t$1À‰D$ ‰T$‰|$‰$èp-뼉t$1ö‰t$ ‰T$‰|$‰$èT(ë ‰t$1ɉL$ ‰T$‰|$‰$èè)ë„¶U‰åWVSìü‹]‹u ‰$‰t$è’·ÿÿ…Àº„£‰t$1À}ȉ…xÿÿÿE¤‰D$HE ‰D$DEœ‰D$@E˜‰D$u €~=„b1ÿëÿ…ÿÿÿGƒÿT‹E …Àt!‹• ÿÿÿ¾‰D$‹E ‰$è¼¢ÿÿ…À…üüÿÿ‹E…ÀtÁ‹• ÿÿÿ¶‹•$ÿÿÿˆ„*HÿÿÿBƒú?‰•$ÿÿÿ~ž¸@Uˆ‰D$…Hÿÿÿ‰D$‰$è¬1À‰…$ÿÿÿésÿÿÿH…tþÿÿÿÿÿ‹…ÿÿÿ-=ÿv#ƒ½ÿÿÿ=•À1Ò½ÿÿÿ»ï•Â…ÐtKé:þÿÿ¶…ÿÿÿˆDÿˆÿÿÿˆ 3é þÿÿt&€|»…/þÿÿ‰Ãéþÿÿ€|»…Ýþÿÿ‰ÃéÀþÿÿ€|»…«üÿÿ‰Ãé“üÿÿ€|»…ýÿÿ‰ÃéhýÿÿH…þÿÿÿÿÿ‹…ÿÿÿ-=ÿ†ôƒ½ÿÿÿ=•À1Ò½ÿÿÿ»ï•…ЄÓKéKþÿÿH…üÿÿ‰ÈÁà…ÿÿÿ‹…ÿÿÿ-=ÿ†6ƒ½ÿÿÿ=•À1Ò½ÿÿÿ»ï•…ЄKé¹ûÿÿ1À‹• ÿÿÿÆ@ƒø~ð¶¼'‹E…Àt2‹…$ÿÿÿ]ˆ…À…}‰\$(ÿÿÿ‰$è‰\$‹U‰$è'æÿÿ‹} …ÿt‹E ‰$èÕ™ÿÿ…À…õúÿÿ‹u…öt ‹…ÿÿÿ‹U‰Äü1À[^_]Ã1ÿ]ˆë´&ÿ…ÿÿÿGƒÿQÿÿÿ‹E …Àt!‹• ÿÿÿ¾‰D$‹E ‰$èP ÿÿ…À…úÿÿ‹u…ötÁ‹• ÿÿÿ¶‹•$ÿÿÿˆ„*HÿÿÿBƒú?‰•$ÿÿÿ~ž‰$¹@…Hÿÿÿ‰L$‰D$èC1Ò‰•$ÿÿÿévÿÿÿ¶H…bûÿÿ‰ÈÁà…ÿÿÿ‹…ÿÿÿ-=ÿ†åƒ½ÿÿÿ=•À1Ò½ÿÿÿ»ï•…ЄÄKéûÿÿ¶•ÿÿÿˆTÿˆÿÿÿˆ 3édüÿÿ1À¶‹• ÿÿÿÆ@ƒø~ðé¬ûÿÿ‹…$ÿÿÿ‰$‰D$…Hÿÿÿ‰D$èébþÿÿ€>u €~=„˜1ÿë´&ÿ…ÿÿÿGƒÿV‹E …Àt!‹• ÿÿÿ¾‰D$‹E ‰$èŸÿÿ…À…@ùÿÿ‹E…ÀtÁ‹• ÿÿÿ¶‹•$ÿÿÿˆ„*HÿÿÿBƒú?‰•$ÿÿÿ~ž¸@Uˆ‰D$…Hÿÿÿ‰D$‰$èð1ɉ$ÿÿÿésÿÿÿ1ÿ]ˆëÿ…ÿÿÿGƒÿ ‹U …Òt!‹• ÿÿÿ¾‰D$‹E ‰$èlžÿÿ…À…¬øÿÿ‹E…ÀtÁ‹• ÿÿÿ¶‹•$ÿÿÿˆ„*HÿÿÿBƒú?‰•$ÿÿÿ~ž‰$¸@‰D$…Hÿÿÿ‰D$è_1À‰…$ÿÿÿévÿÿÿ‰ö¶…ÿÿÿˆDÿˆÿÿÿˆ 3éøÿÿ¿1ɉ|$ ‰L$éžøÿÿ¶•ÿÿÿˆTÿˆÿÿÿˆ 3éCùÿÿ1À´&‹• ÿÿÿÆ@ƒø~ðéŒøÿÿ¿1ɉ|$ ‰L$é2ùÿÿ€|þu €|ÿ=„‰\$1ÿ‹• ÿÿÿ‰4$‰T$è-öÿÿ;½ÿÿÿƒ]ˆëÿ…ÿÿÿG;½ÿÿÿƒú‹E …Àt!‹• ÿÿÿ¾‰D$‹E ‰$è)ÿÿ…À…i÷ÿÿ‹E…Àt¾‹• ÿÿÿ¶‹•$ÿÿÿˆ„*HÿÿÿBƒú?‰•$ÿÿÿ~›‰$¸@1ö‰D$…Hÿÿÿ‰D$艵$ÿÿÿésÿÿÿ€~u €~=„ð¸1ÿ]ˆ‰D$‹• ÿÿÿ‰4$‰T$è_õÿÿëÿ…ÿÿÿGƒÿ‹E …Àt!‹• ÿÿÿ¾‰D$‹E ‰$èmœÿÿ…À…­öÿÿ‹E…ÀtÁ‹• ÿÿÿ¶‹•$ÿÿÿˆ„*HÿÿÿBƒú?‰•$ÿÿÿ~ž‰$…Hÿÿÿ¾@‰t$‰D$è`1ɉ$ÿÿÿévÿÿÿ€|þu €|ÿ=„ɉ\$ƒë‹• ÿÿÿ‰4$1ÿ‰T$è¦ôÿÿƒûŽNuˆëÿ…ÿÿÿG9ûŽ:‹E …Àt!‹• ÿÿÿ¾‰D$‹E ‰$è©›ÿÿ…À…éõÿÿ‹E…Àt‹• ÿÿÿ¶‹•$ÿÿÿˆ„*HÿÿÿBƒú?‰•$ÿÿÿ~Ÿ‰4$¸@‰D$…Hÿÿÿ‰D$èœ1ɉ$ÿÿÿéwÿÿÿ1À‹• ÿÿÿÆ@ƒø~ðé8úÿÿCþ1ÿƒë‰D$‹… ÿÿÿ‰4$‰D$èÚóÿÿ9߃ƒuˆ‹U …Òt!‹• ÿÿÿ¾‰D$‹E ‰$èïšÿÿ…À…/õÿÿ‹E…ÀtF‹• ÿÿÿ¶‹•$ÿÿÿˆ„*HÿÿÿBƒú?‰•$ÿÿÿ~#‰4$¸@‰D$…Hÿÿÿ‰D$èâ1À‰…$ÿÿÿÿ…ÿÿÿG9ßr€1À‹• ÿÿÿÆ@ƒø~ðéxùÿÿ1À‹• ÿÿÿÆ@ƒø~ðéaùÿÿ€|þu €|ÿ=„I‰\$ƒë‹• ÿÿÿ‰4$1ÿ‰T$èôòÿÿƒûŽÎuˆëÿ…ÿÿÿG9ûŽº‹E …Àt!‹• ÿÿÿ¾‰D$‹E ‰$è÷™ÿÿ…À…7ôÿÿ‹E…Àt‹• ÿÿÿ¶‹•$ÿÿÿˆ„*HÿÿÿBƒú?‰•$ÿÿÿ~Ÿ‰4$¸@‰D$…Hÿÿÿ‰D$èê1À‰…$ÿÿÿéwÿÿÿ€~u €~=„¸1ÿ]ˆ‰D$‹• ÿÿÿ‰4$‰T$è-òÿÿëÿ…ÿÿÿGƒÿ‹E …Àt!‹• ÿÿÿ¾‰D$‹E ‰$è;™ÿÿ…À…{óÿÿ‹E…ÀtÁ‹• ÿÿÿ¶‹•$ÿÿÿˆ„*HÿÿÿBƒú?‰•$ÿÿÿ~ž‰$¸@1ö‰D$…Hÿÿÿ‰D$è,‰µ$ÿÿÿévÿÿÿ€|þu €|ÿ=„‰\$1ÿ‹• ÿÿÿ‰4$‰T$èwñÿÿ;½ÿÿÿƒŽ]ˆëÿ…ÿÿÿG;½ÿÿÿsz‹E …Àt!‹• ÿÿÿ¾‰D$‹E ‰$èw˜ÿÿ…À…·òÿÿ‹E…Àt‹• ÿÿÿ¶‹•$ÿÿÿˆ„*HÿÿÿBƒú?‰•$ÿÿÿ~Ÿ‰$¸@1ö‰D$…Hÿÿÿ‰D$èh‰µ$ÿÿÿéwÿÿÿ1À‹• ÿÿÿÆ@ƒø~ðé÷ÿÿCþ1ÿƒë‰D$‹… ÿÿÿ‰4$‰D$è¨ðÿÿ9߃ƒuˆ‹M …Ét!‹• ÿÿÿ¾‰D$‹E ‰$è½—ÿÿ…À…ýñÿÿ‹U…ÒtF‹• ÿÿÿ¶‹•$ÿÿÿˆ„*HÿÿÿBƒú?‰•$ÿÿÿ~#‰4$¸@‰D$…Hÿÿÿ‰D$è°1À‰…$ÿÿÿÿ…ÿÿÿG9ßr€1À‹• ÿÿÿÆ@ƒø~ðéFöÿÿ1À‹• ÿÿÿÆ@ƒø~ðé/öÿÿº1ÿ]ˆ‰T$‹… ÿÿÿ‰4$‰D$èÏïÿÿëÿ…ÿÿÿGƒÿƒýõÿÿ‹E …Àt!‹• ÿÿÿ¾‰D$‹E ‰$èÝ–ÿÿ…À…ñÿÿ‹E…ÀtÁ‹• ÿÿÿ¶‹•$ÿÿÿˆ„*HÿÿÿBƒú?‰•$ÿÿÿ~ž‰$¸@‰D$…Hÿÿÿ‰D$èÐ1À‰…$ÿÿÿévÿÿÿCþ1ÿƒë‰D$‹… ÿÿÿ‰4$‰D$è%ïÿÿ9߃ûÿÿuˆëÿ…ÿÿÿG9߃úúÿÿ‹U …Òt!‹• ÿÿÿ¾‰D$‹E ‰$è)–ÿÿ…À…iðÿÿ‹E…Àt‹• ÿÿÿ¶‹•$ÿÿÿˆ„*HÿÿÿBƒú?‰•$ÿÿÿ~Ÿ‰4$¸@‰D$…Hÿÿÿ‰D$è1À‰…$ÿÿÿéwÿÿÿ¹1ÿ]ˆ‰L$‹… ÿÿÿ‰4$‰D$èoîÿÿëÿ…ÿÿÿGƒÿƒ%ûÿÿ‹U …Òt!‹• ÿÿÿ¾‰D$‹E ‰$è}•ÿÿ…À…½ïÿÿ‹E…ÀtÁ‹• ÿÿÿ¶‹•$ÿÿÿˆ„*HÿÿÿBƒú?‰•$ÿÿÿ~ž‰$¸@‰D$…Hÿÿÿ‰D$èp1À‰…$ÿÿÿévÿÿÿ¹1ÿ]ˆ‰L$‹… ÿÿÿ‰4$‰D$èÃíÿÿëÿ…ÿÿÿGƒÿƒðóÿÿ‹U …Òt!‹• ÿÿÿ¾‰D$‹E ‰$èДÿÿ…À…ïÿÿ‹E…ÀtÁ‹• ÿÿÿ¶‹•$ÿÿÿˆ„*HÿÿÿBƒú?‰•$ÿÿÿ~ž‰$¸@‰D$…Hÿÿÿ‰D$èà 1À‰…$ÿÿÿévÿÿÿ»1ÿ‰\$‹… ÿÿÿ]ˆ‰4$‰D$èíÿÿëÿ…ÿÿÿGƒÿƒþüÿÿ‹M …Ét!‹• ÿÿÿ¾‰D$‹E ‰$è$”ÿÿ…À…dîÿÿ‹U…ÒtÁ‹• ÿÿÿ¶‹•$ÿÿÿˆ„*HÿÿÿBƒú?‰•$ÿÿÿ~ž‰$¸@‰D$…Hÿÿÿ‰D$è 1À‰…$ÿÿÿévÿÿÿ1À‹• ÿÿÿÆ@ƒø~ðé³òÿÿCþ1ÿƒë‰D$‹… ÿÿÿ‰4$‰D$èUìÿÿ9߃pûÿÿuˆëÿ…ÿÿÿG9߃\ûÿÿ‹U …Òt!‹• ÿÿÿ¾‰D$‹E ‰$èY“ÿÿ…À…™íÿÿ‹E…Àt‹• ÿÿÿ¶‹•$ÿÿÿˆ„*HÿÿÿBƒú?‰•$ÿÿÿ~Ÿ‰4$¸@‰D$…Hÿÿÿ‰D$èL 1À‰…$ÿÿÿéwÿÿÿë U¸ ‰åW1ÿV1öSìL‰…Èþÿÿ¸‰…Äþÿÿ¸‰…Àþÿÿ1À‰…¼þÿÿ1À‰…Ðþÿÿ‹E…Àt ]ˆ‰$è­‹E9…¼þÿÿëK‰öH„é‰$è‘n…À…“ƒû=„8ƒþN.ØþÿÿFë ‹U9•¼þÿÿƒ1‹U‰$膑ÿÿƒøÿ‰Ã„'ƒø>„´ƒø<„ñƒø#„p‹U‹B,ƒø„²†kÿÿÿƒøt¦‰$èþm…À„mÿÿÿ…öt’1ÀØþÿÿˆ„.Øþÿÿ‹Èþÿÿ…Ôþÿÿ‰$ó‰L$‰D$èun;Ôþÿÿ‰…¸þÿÿ…+÷Ç•ÀƒÿŸÂ Ш…‰ø‹•ÀþÿÿÁèÑø1ÿ)Â9׉•Ìþÿÿ­4ÕøÿÿÿëGƒî;½Ìþÿÿ”‹…Äþÿÿ…Àˆ‹…¸þÿÿ ýÓè¶Ø‹E …Àt‰\$‹E ‰$è‘ÿÿ…À…d‹E…Àt«‹•Ðþÿÿˆœ*HÿÿÿBƒú?‰•Ðþÿÿ~’¸@MˆG‰D$…Hÿÿÿƒî‰D$‰ $è 1À;½Ìþÿÿ‰…ÐþÿÿŒlÿÿÿ‹…Ìþÿÿ1ö1ÿ…¼þÿÿéVþÿÿ¶‹M‰ $èåÿÿƒøÿ‰Ã•À1Òƒû •Â…Ðuáƒûÿ…hþÿÿ¸éÁ»‰Äþÿÿ» ‹U‹B,ƒø…Nþÿÿ‰$è÷l…À„ïýÿÿƒû0„æýÿÿƒë0‰ÀþÿÿéØýÿÿ¹ÿÿÿÿ» ‰Äþÿÿ븶‹}…ÿt2‹µÐþÿÿ]ˆ…ö…Ó‰\$(ÿÿÿ‰$è& ‰\$‹E‰$è7Õÿÿ‹M …Ét‹U ‰$èåˆÿÿ…Àu‹U…Òt ‹…¼þÿÿ‹M‰1ÀÄL[^_]ÉöƒûO”Àƒûo” Шº‰•Èþÿÿ…/ýÿÿƒûD¹ ”À‰Èþÿÿƒûd” Ш…ýÿÿƒûH”Àƒûh” Ш„Ðþÿÿº‰•ÈþÿÿéèüÿÿGéâüÿÿ‹…¸þÿÿ‰ñéñýÿÿ‰$‹Ðþÿÿ…Hÿÿÿ‰D$‰L$èIé ÿÿÿ¸éMÿÿÿU‰å‹EÇ@Ç@Ç#EgÇ@‰«ÍïÇ@þܺ˜Ç@ vT2]Ãë U1ɉåV‹uS‰Ãë ‰ö¶ˆA9ñrô[^]ÃU1ɉåW‹}V1öS‰Ãë&‹²ˆ‹²ÁèˆD ·D²ˆD ¶D²FˆD ƒÁ9ùrÖ[^_]ÃU1ɉåS‹]ë t&ˆA9Ùrø[]Ãt&U1ɉåWV1öSƒìp‰E¤‹}¤‰Ó‹‹‰E˜‹E¤‰}”‹}¤‹@‹ ‰E‰}Œ´&¼'¶D ¶Áà ¶D Áà ¶D ƒÁÁà ‰Tµ¨Fƒù@rÑ‹E”‹M‹UŒ‹]”÷Ћ}!Ћu”!Ë Ã‹E¨‹M¬‹U”ËE˜œx¤j׋E”ÁÃÉØ!Þ÷Ð!ø‹}Œ Æδ>V·ÇèÁÆ ‹}”Þ‰ð‰ñ÷Ð!Ð!Ù Á‹E°Á‹EŒÛp $ÁÁñ‰È‰Ê÷Ð!Ø!ò ‹E´”:îνÁÁÂʉЉ×÷Ð!ð!Ï Ç‹E¸Çœ¯|õÁÃӉ؉ß÷Ð!×!È Ç‹E¼Ç´7*ƇGÁÆ Þ‰ð‰÷÷Ð!Ð!ß Ç‹EÀÇŒF0¨ÁÁñ‰È‰Ï÷Ð!Ø!÷ Ç‹EÄÇ”•FýÁÂʉЉ×÷Ð!Ï!ð Ç‹EÈÇœؘ€iÁÃӉ؉ß÷Ð!È!× Ç‹EÌÇ´7¯÷D‹ÁÆ Þ‰ð‰÷÷Ð!Ð!ß Ç‹EÐÇŒ±[ÿÿÁÁñ‰È‰Ï÷Ð!÷!Ø Ç‹EÔÇ”¾×\‰ÁÂʉЉ×÷Ð!ð!Ï Ç‹EØÇœ"kÁÃӉ؉ß÷Ð!È!× Ç‹EÜÇ´7“q˜ýÁÆ Þ‰÷‰ð÷×!؉} !× ø‹}àøŒŽCy¦ÁÁñ‰Ï!M ‰È÷׉}œ!ð!ß ø‹}äø”!´I‹} ÁÂʉÐ!ð ø‹}¬ø!Uœœb%öÁÃÓ‹}œ‰Ø!È ø‹}Àø´0@³@ÀÁÆ މЉ÷÷Ð!×!Ø Ç‹EÔÇŒQZ^&‰ØÁÁñ÷ЉÏ!ð!ß Ç‹E¨Ç”ªÇ¶éÁ‰ðʉ×÷Ð!È!÷ Ç‹E¼Çœ]/Ö‰ÈÁÃ÷ÐÓ‰ß!Ð!Ï Ç‹EÐÇ´7SD‰ÐÁÆ Þ÷Љ÷!×!Ø Ç‹EäÇŒæ¡ØÁÁ‰Øñ‰Ï÷Ð!ð!ß Ç‹E¸Ç”ÈûÓç‰ðÁÂ÷Ðʉ×!È!÷ Ç‹EÌÇœæÍá!‰ÈÁÃÓ÷Љß!Ð!Ï Ç‹EàÇ´7Ö7ÃÁÆ ‰ÐÞ‰÷÷Ð!Ø!× Ç‹E´ÇŒ‡ Õô‰ØÁÁ÷Ðñ‰Ï!ð!ß Ç‹EÈÇ”íZE‰ðÁÂÊ÷Љ×!È!÷ Ç‹EÜÇœéã©ÁÉÈÓ‰ß÷Ð!Ð!Ï Ç‹E°Ç´7ø£ïü‰ÐÁÆ ÷ÐÞ‰÷!Ø!× Ç‹EÄÇŒÙog‰ØÁÁñ÷ЉÏ!ð!ß Ç‹EØÇ”ŠL*Á‹}¼ʉÐ1È1ðøœB9úÿ‹}ÈÁÃÓ‰Ø1Ð1Èø´0öq‡‹}ÔÁÆ Þ‰ð1Ø1ÐøŒ"amÁÁ‹}àñ‰È1ð1Øø” 8åý‹}¬ÁÂʉÐ1È1ðøœD꾤‹}¸ÁÃÓ‰Ø1Ð1Èø´0©ÏÞKÁÆ ‹}ÄÞ‰ð1Ø1ÐøŒ`K»ö‹}ÐÁÁñ‰È1ð1Øø”p¼¿¾‹}ÜÁÂʉÐ1È1ðøœÆ~›(ÁË}¨Ó‰Ø1Ð1Èø´0ú'¡ê‹}´ÁÆ Þ‰ð1Ø1ÐøŒ…0ïÔ‹}ÀÁÁñ‰È1ð1Øø”ˆÁ‹}ÌʉÐ1È1ðøœ9ÐÔÙ‹}ØÁÃÓ‰Ø1Ð1Èø´0å™Ûæ‹}äÁÆ Þ‰ð1Ø1ÐøŒø|¢ÁÁ‹}°ñ‰È1ð1Øø”eV¬Ä‰ðÁ‹}¨÷ÐÊ Ð1ÈøœD")ô‰ÈÁË}Ä÷ÐÓ Ø1Ðø´0—ÿ*C‰ÐÁÆ ‹}à÷ÐÞ ð1ØøŒ§#”«‰ØÁÁ‹}¼÷Ðñ È1ðø”9 “ü‰ðÁ‹}Ø÷ÐÊ Ð1ÈøœÃY[e‰ÈÁË}´÷ÐÓ Ø1Ðø´0’Ì ‰ÐÁÆ ‹}Ð÷ÐÞ ð1ØøŒ}ôïÿ‰ØÁÁ‹}¬÷Ðñ È1ðø”Ñ]„…‰ðÁ‹}È÷ÐÊ Ð1ÈøœO~¨o‰ÈÁË}ä÷ÐÓ Ø1Ðø´0àæ,þ‰ÐÁÆ ‹}À÷ÐÞ ð1ØøŒC£‰ØÁÁ‹}Ü÷Ðñ È1ðø”¡N‰ðÁ‹}¸÷ÐÊ Ð1Èøœ‚~S÷‰ÈÁË}Ô÷ÐÓ Ø1Ðø´05ò:½‰ÐÁÆ ‹}°÷ÐÞ ð1ØøŒ»Ò×*‰ØÁÁ‹}Ì÷Ðñ È1ðø”‘Ó†ë‹E˜ÁÂÊËE¤‰‹}”‹]úÙ‰P‹UŒ‰HÖ1Ò‰p E¨Ç$@èzøÿÿƒÄp[^_]ÉöU‰åWVSƒì‹}‹u‹E ‹_ õ‰Eð‰Ú‰GÁêƒâ?‰Uì‰Ê Ú÷Ð!Ù!РȈ®‹WÇEè@‹Mì‰ð)MèÁè1Û;uè‰Gs‹Uð)Þ‹Mì‰uƒÄÚ[D^_]é÷ÿÿ‹UèD‰$‹Uðè}÷ÿÿ‰øWèó÷ÿÿ‹]èC?9ðs‰ö¼'‹Uð‰øÚèÔ÷ÿÿƒÃ@C?9ðrêÇEì‹Uð)Þ‰u‹MìƒÄÚD[^_]é&÷ÿÿ¶‹WBéLÿÿÿ´&U‰åEðSƒì‹] Ç$Sè÷ÿÿ‹Cº8Áèƒà?ƒø7vºx‰$)¸`÷‰T$‰D$èµþÿÿ‰$¸‰D$Eð‰D$èþÿÿÇ$‹E‰Úè¼öÿÿÇ$X‰Ø1ÒèìöÿÿƒÄ[]ÃU‰åSƒì‹] ¾EÇ$‰D$‹E‰D$èûuÿÿ…Àt ‰‹EƒÄ[]ÃǸëíë U1À‰åWVSìü‰…´þÿÿ‹E‹H‰lþÿÿ‰ $è˜yÿÿ‹U …À‰º…z‹lþÿÿ¸ ‰…Pþÿÿ‹A,‹q$…À„’1Àƒþ.”À‰…Xþÿÿ‹•Xþÿÿ1Àƒþ#”À •À¶À…À‰…Lþÿÿ”À¶ø‰½\þÿÿ1Àƒ½Xþÿÿ‰½`þÿÿ‰½dþÿÿ‰½hþÿÿ”À‰…Tþÿÿéý¶‹´þÿÿ…É…"ƒþ'”ƒþ"”À‰Ç ׃çë ‹Tþÿÿ…Ût…É…Ž1Àƒþ#”À‰…Tþÿÿ‹•`þÿÿ‹…hþÿÿ‹\þÿÿ Ћ•Tþÿÿ Ø Ð ø …Xþÿÿu…É……É”À1Òƒþ;”Â…Ðt8…¬þÿÿ‰D$1À‰D$‹…lþÿÿ‰$èyÿÿ‹U …À‰…Ûƒ½¬þÿÿ„k‰t$‹…lþÿÿ‰$èExÿÿ‹M …À‰…¯ƒþÿ„‹lþÿÿ‰ $…´þÿÿ•°þÿÿ‰D$‰T$èmxÿÿ‹M …À‰…w‹Lþÿÿ…Û„1ɉLþÿÿ‹…´þÿÿ…À„l‹•hþÿÿ…Òt1‹…´þÿÿƒø†ƒøQ„މ4$èÂ^…À…3ƒþÿ„*‹…dþÿÿ…Àt1‹…´þÿÿƒø†øƒøQ„u‰4$è‡^…À…-ƒþÿ„$‹`þÿÿ…Ût 1ɉ`þÿÿ‹´þÿÿƒù†Ýƒù„Ì ‹…\þÿÿ…Àt‹…´þÿÿ…À…ì1Àƒþ_”À‰…\þÿÿ‹…Xþÿÿ…À…é…ÿ…àýÿÿ‹´þÿÿéþÿÿ¾ édýÿÿ‰µPþÿÿ‹…lþÿÿ‰$è'ÿÿ‹•lþÿÿ‰Æ‹B0@9B,„t‰4$èÊ]…À„¢Fõƒø‡¼þÿÿ¸"‰D$¸€É‰D$‹U‰$è™Æþÿ‹…´þÿÿ…À…Ÿþÿÿt&¼'‰4$èx]…À„‡Fõƒø‡þÿÿ¹€É»"‰\$‰L$‹E‰$èGÆþÿƒþÿ…ÿýÿÿ1ÒÄü‰Ð[^_]É4$è']…À…ƒþÿ„ù¸‰…Xþÿÿéîþÿÿ¶‹…°þÿÿ¾;…Pþÿÿ„oƒþ ¿”Àƒþÿ” Ш„Àþÿÿ‹…°þÿÿ€8'„› ¸¿˜É‰D$‰|$‹E‰$è¤Åþÿ‹°þÿÿ¾;…Pþÿÿ„*€9'„ ¾ÂÿÿÿA‰t$ ‰D$‹U ‰T$Ç$ éývƒþ •Â1Àƒþÿ•À!Љ…Tþÿÿ…düÿÿ1À‰D$ ‹…°þÿÿ@‰D$‹U Ç$ ‰T$麃þÿ„ýÿÿ‰ð, <^†ýÿÿ¸"‰D$¸ÁɉD$‹M‰ $èîÄþÿéPþÿÿ‹…lþÿÿ‹M‹P(‰Q‹@,‰A éãüÿÿ‰4$è÷Z‹´þÿÿ¾‘ÓÉ9ДÀ¶À‰…hþÿÿéöüÿÿ´&‰4$èÈZ‹´þÿÿ¾‘ÙÉ9ДÀ¶À‰…dþÿÿéýÿÿ‰4$è Z‹´þÿÿ¾‘ßÉ9ДÀ¶À…À‰…`þÿÿ…ýÿÿéóüÿÿ1À‰…\þÿÿ‰4$è8[…Àu$ƒþ.•À1Òƒþÿ•Â…Ðt¸‰…\þÿÿ´&‹´þÿÿƒù—À1Òƒ½\þÿÿ”…ЄÊüÿÿƒþ.…ž ƒùJv¹èÉ»‰\$‰L$‹M‰ $èÅÃþÿ1Ò‰T$ ‹…°þÿÿ@‰D$‹E Ç$‰D$é;‰4$è˜Z…À…€ƒþÿ„w‹´þÿÿéÌúÿÿƒù†ˆýÿÿ‰4$èkZ…À„xýÿÿéºýÿÿº"¸ ʉT$‰D$‹E‰$èAÃþÿéjüÿÿ¸‰D$¸$ʉD$‹E‰$èÃþÿéPûÿÿ¸‰D$¸LʉD$‹M‰ $èýÂþÿéiûÿÿ…pþÿÿ1Òµ¸þÿÿ‰t$‰D$ ‹…xþÿÿ‰T$‰D$‹…lþÿÿ‰$èÆêÿÿ…À…É ‹xþÿÿ…É„| ‹•pþÿÿ9Ñ„t ‹U ǺÄü‰Ð[^_]Ã1À‰D$ ‹…°þÿÿƒÀ‰D$‹U Ç$‰T$è!øÿÿÄü‰Â‰Ð[^_]ý´þÿÿº„üÿÿ1ö‰t$ ‹…°þÿÿƒÀ‰D$‹E Ç$‰D$ë·1À‰D$ ‹…°þÿÿ@‰D$‹M Ç$‰L$ë–¨þÿÿ‰L$‹…lþÿÿ‰$èd„ÿÿ‹U …À‰º…–ûÿÿ1Û‰Hþÿÿëa‹•lþÿÿ¿‹B0@9B,„Àƒû •Àƒ½Pþÿÿ;• Шu‹…lþÿÿƒx<‡_‹…Hþÿÿ…À”À1Ò…ÿ•…Єƒþÿ„U‰t$‹…lþÿÿ‰$èEqÿÿ‹M …À‰…¯þÿÿƒþ-„‹…lþÿÿ1ÿ‹Pþÿÿ‰µPþÿÿ‰$èc{ÿÿ‰$‰ÆèùX…À…Iÿÿÿ‰4$è X…À…9ÿÿÿ‰ò€ú „Fÿÿÿ€ú„=ÿÿÿ€ú•À1Òƒþÿ•…Є'ÿÿÿ¸"‰D$¸tʉD$‹M‰ $èºÀþÿéíþÿÿt&…´þÿÿ•°þÿÿ‰D$‰T$‹…lþÿÿ‰$èÞpÿÿ‹M …À‰…èýÿÿ…´þÿÿ‰D$‹…°þÿÿ‰$è ”ÿÿ‹…´þÿÿƒø†ÿÿÿ¹”ʉL$‹•°þÿÿЃè‰$èÞ.ÿÿ…À”À¶À‰…Hþÿÿéìþÿÿ‰4$è#W…À…ăþÿ…ˆþÿÿƒ½Pþÿÿ;•Àƒû • Ш…¨‹Hþÿÿ…É”À1Ò…ÿ•Â…Ð…F„ú‹Hþÿÿ¸¿ÿÿÿÿ‰…tþÿÿ¾ÿÿÿÿ1À‰½ˆþÿÿ1ÿ…Û‰…„þÿÿ‰µŒþÿÿ„p…¨þÿÿ‰D$‹…lþÿÿ‰$è‚ÿÿ‹U …À‰º…8ùÿÿ1À1É1Ò‰…œþÿÿ1ÀØþÿÿ‰…˜þÿÿ1À‰…”þÿÿ¸³Ê‰…þÿÿ…¤þÿÿ‰¤þÿÿ‰• þÿÿ‰D$8… þÿÿ‰D$4…œþÿÿ‰D$0…˜þÿÿ‰D$,…”þÿÿ‰D$(…þÿÿ‰D$$…Œþÿÿ‰D$ …ˆþÿÿ‰D$…„þÿÿ‰D$…€þÿÿ‰D$…|þÿÿ‰D$ …xþÿÿ‰D$…tþÿÿ‰\$‰D$‹…lþÿÿ‰$èç“ÿÿ‹M …Àº‰…Yøÿÿ‹lþÿÿöA@…Ó‹…tþÿÿƒø„£ƒø„°ƒø„‰ƒø„‹…xþÿÿÁ艅pþÿÿ¾‰t$‹…¤þÿÿ‹pþÿÿ‰ $؉D$è ÿÿ‹M …Àº‰…Û÷ÿÿ1À1ö‰…Pþÿÿëƒû •Àƒ½Pþÿÿ;• Ш„#ƒþÿ„*‹…lþÿÿ‹Pþÿÿ‰µPþÿÿ‰$èxÿÿƒøÿ‰Æu¼ƒû •Àƒ½Pþÿÿ;• Шt¦¿!¾Áʉ|$‰t$‹E‰$蔽þÿ‹U Ǻéíúÿÿ‰4$èxT…Àuƒþÿu4ºé)÷ÿÿ‹•lþÿÿ‹Z<…Û„Å÷ÿÿCÿ‰B<‹B4ÆDÿ‹°þÿÿé¬÷ÿÿ¸àʺ‰D$‰T$‹U‰$è½þÿ‹lþÿÿ‹A…À„±ÿIÿA ÿAÿI,ºÇA$é´öÿÿ¸"‰D$¸ ʉD$‹E‰$èÓ¼þÿéûÿÿ‰4$èÆS…À„Íþÿÿ‹…„þÿÿƒø@‡É…Àu » ‰„þÿÿƒ½ˆþÿÿÿ„¨1Òµlþÿÿ‰T$‰4$è?kÿÿ‹U …À‰º…1öÿÿØþÿÿ‰$è?¼ÿÿ…ÀuIÆ…ðþÿÿ¸----‰…Øþÿÿ¸----‰…Üþÿÿ¸----‰…àþÿÿ¸----‰…äþÿÿ¸----‰…èþÿÿ¸----‰…ìþÿÿ‹…€þÿÿ¹Ë‰D$D‹…¤þÿÿ‰D$@‹… þÿÿ‰D$<‹…œþÿÿ‰D$8‹…˜þÿÿ‰D$4‹…”þÿÿ‰D$0‹…þÿÿ‰D$,1Àƒ½ŒþÿÿŸÀ‰D$(‹…ˆþÿÿ‰D$$‹…„þÿÿ‰\$øþÿÿ‰D$ ‰|$‹…xþÿÿ‰D$‹…¨þÿÿ‰D$‹…lþÿÿ‰D$ ‹…|þÿÿ‰L$‰$‰D$èPƒ½tþÿÿ„P‰\$¸Åÿÿÿ‰D$ ‹E ‰D$Ç$ èôðÿÿ=‰Ãt‰Úéèôÿÿ‰4$èjÿÿ‹U ‰ÚéÔôÿÿƒ½´þÿÿ„j‹°þÿÿ‰L$¸Àÿÿÿ‰D$ ‹E ‰D$Ç$ éwøÿÿ´þÿÿ…°þÿÿ‰L$‰D$‹…lþÿÿ‰$è kÿÿ‹U …À‰º…môÿÿ‹…´þÿÿƒø†7‹•°þÿÿЃèƸÃÿÿÿ‰D$ ‹…°þÿÿ@‰D$‹M ‰L$éýôÿÿ¸Áÿÿÿ‰D$ A‰D$‹E ‰D$éáôÿÿ¸!»ÁʉD$‰\$‹U‰$è3ºþÿé6úÿÿ…€þÿÿ1ɉD$ …|þÿÿ‰D$…xþÿÿ‰L$‰D$‹…lþÿÿ‰$è\H‹U …À‰º…®óÿÿ¨þÿÿ‰L$‹…lþÿÿ‰$èR|ÿÿ‹U …À‰º…„óÿÿ‹…xþÿÿº‰…pþÿÿ‰T$‰D$‹…lþÿÿ‰$ékûÿÿ‹°þÿÿ¶O‹lþÿÿé?úÿÿ‹•xþÿÿ¸‰ˆˆˆÁâ÷âÁêécþÿÿ…pþÿÿ1ɵ¸þÿÿ‰t$‰D$ ‹…xþÿÿ‰L$‰D$‹…lþÿÿ‰$èyËÿÿé©þÿÿ…pþÿÿ1ÿµ¸þÿÿ‰t$‰D$ ‹…xþÿÿ‰|$‰D$‹…lþÿÿ‰$èòÇÿÿé÷óÿÿ‹…Hþÿÿ‰D$1À‰D$ 1À‰D$1À‰D$‹…lþÿÿ‰$èóD‹U …À‰º…Eðÿÿ‹…xþÿÿ¨þÿÿ‰…pþÿÿ‰L$‹…lþÿÿ‰$èÝxÿÿ‹U …À‰º…ðÿÿµ¸þÿÿ‰t$‹…pþÿÿ‰D$‹…lþÿÿ‰$èY·ÿÿé^óÿÿ‹E ºÇé}óÿÿU‰åWVSƒìLƒ} •À1Òƒ} •Â…Ðtƒ} •À1Òƒ} •Â…Ð…·‹E(…À…‹E ¹Áà‰E¼Hƒø?‡Š‹}¼‹E ƒÇÁï½)ПK‰ÆÓæƒ} „®;U „¥ƒÿK „=ÓàH‰EÄ‹E$…Àt‹U¼‹E$‰‰uÈ‹u…öuÇEÈ‹](…Û„êEЉ$赺þÿƒ} ‹M‰MÀ„ꇙƒ} „(ÇEÌ‹U9Ũº‰öƒÿŽ+‹EЀ8b„~1Ûë´&‹UÀ‹ƒÂ‰UÀ‰DØC9û|ì‹\½Ô‹EÈ‹MÄ‹UÈØ!È)Ѓÿ‰D½ÔŽ#1Û9û}O‹u¼Wÿ‰U¸¶¼'9]¸‰ð~¸ ‰D$ 1À‰D$‹D؉D$‹M‰ $èçkÿÿ…À…ýCƒî 9û|ÇÿEÌ‹M9MÌ‚Hÿÿÿ‹M …Ét‹E‹U¼¯Â‹U Áè‰1ɃÄL‰È[^_]Ã} ¹uë‹E(…À„>þÿÿEÔ‰$蓹þÿ…À‰ÁuÏü‹uÔ¹¿pÌó¦—Â’À8¹„ þÿÿëªÇEÄÿÿÿÿéaþÿÿƒ} „yƒ} „y‹MÀ¶‰EØ‹E ‹\½ÔEÀ‹EÈ‹MÄ‹UÈØ!È)Ѓÿ‰D½ÔÝþÿÿ‹E¼1Û‰\$‰D$ ‹E؉D$‹U‰$èêjÿÿ…À„ ÿÿÿƒÄL‰Á‰È[^_]ÃEЉ$軸þÿƒ} ‹M‰MÀ…þÿÿ‹u‹E ¯ð‰t$‹M‰ $è³kÿÿ…À…þÿÿ‹Eо‰$è=I‰Ã‹E,¾‰$è-I9Äa‰t$‹U‹J‹B ȉD$‹M‰ $èwOƒ} ”ƒ} ”À Ш…–‹U‹z ƒ} „D‹E ‹U‹u ‹M¯Ð…ö‰A „bþÿÿ‹E 1ɉéXþÿÿƒ} „Aÿÿÿƒ} …]ýÿÿé2ÿÿÿ‰û…ÿë´&‹MÀ‹ƒÁ‰MÀ‰DÔKuîé}ýÿÿ‹MÀ‹éþÿÿ‹UÀ·é‚þÿÿ¶M¼‰øé¸üÿÿÇEÌ‹E‹x ‹Hùƒþ†Uÿÿÿ‰ó¿·AƒEÌf‰Qf‰ƒÁ;]Ìwæé4ÿÿÿ‹E‰D$‹U‰$èkjÿÿ…À…¾üÿÿ‹M‰L$‹EÀ‰D$‹U‹J‹B ȉ$èÂH‹M‹U ‹EA …Ò„nýÿÿ‹U ‰édýÿÿ‰t$‹E‰D$‹U‹B ‹Z؉$è†H‹M‹y é¼þÿÿÇEÌ‹E‹]‹HÁãùƒû†žþÿÿƒEÌ‹‹A‰Q‰ƒÁ;]Ìwê‹U‹z é}þÿÿ¶¿U‰åWVSƒì\ƒ} ÇE¸•À1Òƒ} •Â…Ðtƒ} •À1Òƒ} •Â…Ð…Ä‹E,…À…Ï‹E ¹Hƒø?‡‹E »‹U‰ÞƒÀÁè‰E°‰U¼‰Â‹E Áâ)ÐÁàHÓæƒ} „Â;U „¹ƒ}°„qH ÓãK‰]ȉuÀ‹E$…ÀuÇEÀ‰uÌ‹E…ÀuÇEÌ‹E,…À„EЉ$è¾µþÿÇE´‹U9U´ÇEăè‹E°H‰E¬¶¼'ƒ}°Ž|1ö;u°}K‹] }؉ö¼'9u¬‰Ø~¸ 9u¬‰D$ ‹E$~1À‰|$‹U(F‰D$ƒë ƒÇ‰$è¬bÿÿ E¸;u°|Ä‹E¸…Àt÷E¸€„¨‹U¸‰U´‹U°‹EÀ‹]È‹t•Ô‹MÌð!Ø)ȃú‰D•ÔŽ·‹EЀ8b„ 1öë´&‹U¼‹DµØF‰ƒÂ‰U¼;u°|ëÿEÄ‹U9UÄ‚,ÿÿÿ‹E…Àt‹UÄ‹E‰‹M´ƒÄ\‰È[^_]Ã} ¹uë‹E,…À„1þÿÿEÔ‰$è´þÿ…À‰ÁuÏü‹uÔ¹¿pÌó¦—Â’À8¹„ýýÿÿëªt&ÇEÈÿÿÿÿéNþÿÿt&ƒ} „€ƒ} „‹EØ‹U¼ˆÿEÄ‹E ‹UE¼9UÄ‚þÿÿéNÿÿÿ‹E ‹U$‰D$ E؉D$‹E(‰T$‰$èZaÿÿ E¸é®þÿÿ‰Ö…Òë‹U¼‹DµÔ‰ƒÂN‰U¼uîÿEÄ‹U9UÄ‚+þÿÿéúþÿÿ‹EØ‹U¼‰ëˆEЉ$葳þÿéÞýÿÿ‹EØ‹U¼f‰éjÿÿÿ‹M ‹E°ÁáÓà‰ÁI‰MÈé‚ýÿÿ‹E…Àt‹UÄ‹E‰‹M¸‹}´ ùé²þÿÿUºB‰åƒì¡Xô‰T$Ç$€ÌƒÀ@‰D$ ¸‰D$èCÇ$è”Et&U¹‰åƒì¡Xô‰L$Ç$€ÌƒÀ@‰D$ ¸B‰D$èÐBÇ$èTEU‰åWVS윃} ÇE¨€€ÇE¤€•À1Òƒ} •Â…Ðtƒ} •À1Òƒ} •Â…Ð…%‹E(…À…0‹E ¹Áà‰EˆHƒø?‡õƒ}ˆ•À1Òƒ}ˆ•Â…Ð…Å‹uˆ‹E ƒÆÁîµ)ПK‰ÇÓçƒ} ‰}˜„€;U „wƒþ„(K ÓàH‰E”‹}$…ÿt‹Mˆ‹U$‰ ‹]‹}˜…Û‰}œuÇEœ‹M(…É„'E¬‰$èÆ±þÿƒ} ÇEÔ‹EÇEЋUœÇEÌÇEȉE‰TµÄÇEŒ„‡ƒ} „±ÇE ‹E9E ƒØ‰ö¼'ƒþŽ‹E¬€8b„½1Ûë´&‹M‹ƒÁ‰M‰DØC9ó|ì‹TµÔ‹Eœ‹}”Ð!ø1ÿ‰DµÔƒþŽœ1Ûë ‹DȉD¸C9ó|ó‰t$]¸‰$è/ÿÿ…À…|‰t$ E؉D$‰t$‰$è@ÿÿ…À…]‹M؉MÈ»9óœ‹U¸ë‹L¸…Ét‰ßC9óA‹DØ…Ò‰DÈyáƒ|¸ÿëàƒ}ˆ •À1Òƒ}ˆ@•…Є#þÿÿÄœ‰È[^_]Ã} ¹uè‹E(…À„ÐýÿÿE°‰$èT°þÿ…À‰ÁuÌü‹u°¹¿ÐÌó¦—Â’À8¹„œýÿÿë§‹U¸B=þ†3‚ÿ=þÿ‡Ê¸‰D$E¨‰D$‹E‰$èÌ`ÿÿ…À…i¸‰D$ ¸‰D$‹E¸‰D$‹U‰$è°aÿÿ…À…=ƒEŒt&ÿE ‹M9M ‚1þÿÿ‹E …Àt‹EŒ‹} ‰1ÉÄœ‰È[^_]ËMØ‹]ȉÊ)Ú…U˜t‹E”÷Р‰U¸éþÿÿƒ} „Úƒ} „Ë‹U¶ ‰MØ‹M Méþÿÿ¸‰D$E¨‰D$‹M‰ $è`ÿÿ…À…Ÿ¸ ¿‰D$ ‰|$‹E¸‰D$‹}‰<$èæ`ÿÿ…À…sƒEŒé5ÿÿÿ¸‰D$E¸‰D$‹}‰<$èª_ÿÿ…À…GÿEŒé ÿÿÿE¬‰$è®þÿéÔüÿÿÇE”ÿÿÿÿéüÿÿ‰ó…öë‹U‹ƒÂ‰U‰DÔKuîéEýÿÿ‹}‹é,ÿÿÿƒ} …áüÿÿ‹EÁà‰D$‹}‰<$èXaÿÿ…À…Äüÿÿ‹E1Û¹‰xÿÿÿ1ÿ‰tÿÿÿ‹P‹p ‹E¬Ö¾‰$èÂ>‹U,‰Ã¾‰$è²>9Ãt¸‰…xÿÿÿ1À‰…tÿÿÿ‹M,¾‰$è>ÇE ‹E9EŒëˆFÿEŒÿE ‹E9E ƒŠ‹U ‹M‹‘‰Â)ú‰ÇB=þvÒÆ€Ff‰U´‹•xÿÿÿ¶D*´ˆ‹tÿÿÿF¶D)´ˆFƒEŒ뮋E·é0þÿÿÄœ‰Á‰È[^_]Ã…ÿ„;ýÿÿ½ƒø†²ƒø‡,¹E¨‰L$‰D$‹}‰<$è^ÿÿ…Àu±‰<$º E¤‰T$‰D$èô]ÿÿ…Àu•1Û9ó}_‹}ˆFÿ‰…pÿÿÿ´&¼'9pÿÿÿ‰ø~¸ ‰D$ 1À9pÿÿÿ”À‰D$‹D¸‰D$‹U‰$è«^ÿÿ…À…8ÿÿÿCƒï 9ó|»ƒEŒéòüÿÿE¨»‰\$‰D$‹E‰$èg]ÿÿ…À…ÿÿÿ1Û9ó‡ýÿÿ‹}ˆVÿ‰•pÿÿÿ9pÿÿÿ‰ø~¸ ‰D$ 1À9pÿÿÿ”À‰D$‹D¸‰D$‹M‰ $è$^ÿÿ…À…±þÿÿCƒï 9ó|»ƒEŒéküÿÿ‹}ÿ‰|$‹U‰$è_ÿÿ…À…súÿÿÇE„‹M¸‰…|ÿÿÿÇE€‹A‹q Æ‹E¬¾‰$èm<‹U,‰Ã¾‰$è]<9ÃtÇE€1Û‰|ÿÿÿÇE ‹M9MŒƒ8‰ûëˆFÿEŒÿE ‹}9} ƒ‹E‹} ‹M„¿x‰Ð)Èf‰E¶‰U„‰ÂƒÀf=þvÈCý;EŒs=÷E…1‹UŒ)ЉD$‹U‰$è/^ÿÿ…À…È‹M‹y‹A ø‹}Œ48Æ€‹U€F¶D*¶ˆ‹|ÿÿÿF¶D)¶ˆFƒEŒécÿÿÿ‹M ‰ðÁáÓà‰ÁI‰M”éÌøÿÿ‹M‰L$‹}‰<$èÉ]ÿÿ…À…5ùÿÿÇE ‹G 1Ò‹w‹MÆ9MŒs&‹}¶(ЈF¶GƒE ‰}ˆÂ‹E9E rà‹U‹B ‹U‹MЉA ‹E …À„Úúÿÿ‹E‹} ‰éÍúÿÿ‹E‹u ‹UŒP …ö„¹úÿÿ‹M ‰1Éé¯úÿÿ‹U‹] ‹MŒJ …Û„™úÿÿ‹} ‰1Ééúÿÿ¹é“ùÿÿ¹é‰ùÿÿt&¼'U‰åWVS쌋] ƒ} •À1Òƒ} •Â…Ðtƒ} •À1Òƒ} •Â…Ð…ù‹E,…À…Cÿ¹ƒø?‡Ðs‹E Á])ÐÁà‰E„ƒÀ‰E”¸‰Ç¶M”Óçƒ} ‰}¬„î;U „åƒþ„â‹M„ƒÁ ÓàH‰E¤‹E$‹}¬…Àu1ÿ‹E‹M¬…À‰M¨uÇE¨‹E,…À„E°‰$è ©þÿÇEÔÇEÐÇEÌÇEȉ|µÄ1ÿ;}ƒë 1Òë‹D•È1ɉL•¸‰D•ØB9ò|íºE¸‰T$‰D$‹M(‰ $è¾Tÿÿ…À…È‹E¸<€„Ì©€t" ÿÿÿº‰E¸ët&¸ÿÿÿÿ‰D•¸B9ò|òƒþŽõ1Òët&‹D•ȉD•ØB9ò|ó‰t$ E¸‰D$E؉t$‰$è™ ÿÿ…À…S1Òë ‹D•؉D•ÈB9ò|ó‹M¨)LµÔƒþޱ‹E°€8b„Í1Òë ‹D•ØB‰ƒÃ9ò|òG;}‚ÿÿÿ‹E…Àt‹E‰81ÉÄŒ‰È[^_]Ã} ¹uè‹E,…À„üýÿÿE´‰$è«§þÿ…À‰ÁuÌü‹u´¹¿ÐÌó¦—Â’À8¹„Èýÿÿë§ÇE¤ÿÿÿÿé$þÿÿ‹E¸‹MÈ‹U¤È!ЉEØé.ÿÿÿƒ} tƒ} tE‹E؈‹E ÃGéSÿÿÿ‹E؉‹E Ãëî‰ò…öë ‹D•Ô‰ƒÃJuôGé.ÿÿÿE°‰$èó¦þÿéôýÿÿ‹EØf‰‹E Ã븸@‰D$E¸‰D$‹M(‰ $èöRÿÿ…À„lþÿÿÄŒ‰Á‰È[^_]ø‰D$E¸‰D$‹M(‰ $èÄRÿÿ…ÀuÒ‹E¸f=€tB©„*þÿÿ ÿÿº‰E¸ë ¸ÿÿÿÿ‰D•¸B9ò|òéþÿÿ‹M ‰ðÁáÓà‰ÁI‰M¤éýÿÿ¸ ‰D$E¸‰D$‹M(‰ $èZRÿÿ…À…dÿÿÿ‹E¸=€„3ÿÿÿ…À‰ºýÿÿºë ¸ÿÿÿÿ‰D•¸B9ò|òé ýÿÿU‰åWVSƒì<‹E‹U‹]‹€ ‹Š ‹}‰Æ‰EÔ΃æƒû~01É닉DØA9Ù|ô‰\$M؉ $èñÿÿ…À„ðƒÄ<[^_]ËM ‹‹)ЉEØ1É9Ù}‹E‰òÁâÂt&‹DØA‰ƒÂ9Ù|ò¹¸9Ù}$‹UØëƒ|Øt1ÀA9Ù…Òyêƒ|Øÿëè‰ö‹UØ…ÒtH‹M ‹‹9ȃ¤…ÒŽœ‹M‰ðÁà\¹‰ÐÁø÷ЉƒÃIyñ‹Eº‰”°ë ‹M1Û‰œ±‹EÔ‹U@‰‚ ƒÄ<1À[^_]Ã…ÀuŠ‹U¿‰¼²ëÔ‰\$ UØ‹E ‰\$‰$‰D$èÿÿ…À…îþÿÿ‹E‹€ ‰EÔéòþÿÿ9Èv…ÒˆXÿÿÿ1Щøÿÿÿu ‹U¿뢩ðÿÿÿt©àÿÿÿu‹EºéOÿÿÿ‹M»éPÿÿÿ©Àÿÿÿu ‹U¿éfÿÿÿ©€ÿÿÿu ‹M»é(ÿÿÿ©ÿÿÿu ‹Eºéÿÿÿ©þÿÿu ‹U¿é*ÿÿÿ©üÿÿu ‹M»éìþÿÿ©øÿÿu ‹Eº éÊþÿÿ©ðÿÿu ‹U¿ éîþÿÿ©àÿÿu ‹M» é°þÿÿ©Àÿÿu ‹Eº éŽþÿÿ©€ÿÿu‹U¸ ‰„²éˆþÿÿ%ÿÿ‹MƒøÀƒÀ‰„±élþÿÿU‰åWVSƒì<‹}‹]‹‡ ‰Æ‰EÔ‹‡ ƃæƒû~61Éë ‰ö‹U‹ЉDØA9Ù|ñ‰\$M؉ $èBÿÿ…À„ȃÄ<[^_]Éö‹M ‹U‹‹ )ȉEØ1É9Ù}‰ðÁà8v‹DØA‰ƒÂ9Ù|ò¹¸9Ù}(‹UØëƒ|Øt1ÀA9Ù}…Òyîƒ|Øÿëì¶…Àt6‹UØ…Òt6‹] ‹‹]‹ 9Èsu…Ò~q‰ð¹Áà\8‰ÐÁø÷ЉƒÃIyñ¸ë1À‰„·‹EÔ@‰‡ ƒÄ<1À[^_]É\$ UØ‹E ‰\$‰$‰D$èˆÿÿ…À…ÿÿÿ‹ ‰MÔé!ÿÿÿ9Èv…Òx‡1Щðÿÿÿu¸ëš©àÿÿÿt©Àÿÿÿu¸ë…¸é{ÿÿÿ©€ÿÿÿu ¸éjÿÿÿ©ÿÿÿu»‰œ·éYÿÿÿ%ÿÿƒøÀƒÀé@ÿÿÿ¶¼'U1À‰åWü¹V}ØSƒì<‹uó«‹E‹U‹] ƒÀ‰EЉD$ 1À‰D$‹E ‰$Áà ð‰D$è:Sÿÿ…À…¢‹}‰ñ¸Óà‰Æ…ÿ…”‹U ‹•à̉UÔ…Û•À1Òƒ}ÔA”Â…Ðt‰]Ô‹] …ÛŽ?ƒ}ÔA‹M‹ ‰Ã„º…ö‰÷ud‹Uðƒà‰‚ ‹E)² …Àt‹E …À„~‹EÔ‹M‹U¯ðD‰1Àv¼'ƒÄ<[^_]ËE ‹…͉EÔégÿÿÿ¶‹U‰ØƒàÁà‹MÔЉD$‹E‰L$‰$è=Qÿÿ…Àu¹COuÕ‹U‹‚ écÿÿÿ´&‹EЋM‰1Àë”t&…ö‰÷„Bÿÿÿ¶‹U‰Ø¹ ‰L$ƒàÁàЉD$‹E‰$èÛPÿÿ…À…Sÿÿÿ¹!U؉L$‹M‰T$‰ $è¸Pÿÿ…À…0ÿÿÿCOu¬érÿÿÿ´&‹M‹ éÎþÿÿ‰öU‰å‹MW‹}‹E V1öS‹— »ÓãÂ…Ût"¶¿‰Ðƒà‹„‡9ðv‰ÆBKuê[‰ð^_]ÃvU‰åW1ÿV1öSƒì,‰|$‰t$‹E‰$èÿÿÿ‹]‰Ç…Û„‹M1Û‹…Í‹Uƒ¹ D‰EðwO鋅ً͈UÓàt;}ìvs‹Eð‰ùÀ)ÐPú‹Eðð9Ðru‰UðC‹U‰Ï¸ˆÙÓà9‚ ‚ʼn\$ˆÙ¸Óà‰D$‹E‰$èùþÿÿ‰Eì‹M…Éu‹Mì‹U‹à̈ÙÓàt;}ìw‹U6‹Mì)ÐPú‹Eðð9Ðs‹‹U‰T$‹M‰L$‹E‰D$‹U ‰\$‰|$‰T$ ‹M‰ $è¯üÿÿƒÄ,[^_]ô&‹M1Û‹…àÌ‹Uƒ¹ D‰Eð‡Hÿÿÿ¶¼'‹M‰L$‹E‰D$‹U‰T$‹M ‰\$‰|$‰L$ ‹E‰$èAüÿÿƒÄ,[^_]Éö¼'U‰åWVSƒì<‹E(ÇEØ‹U‹uÇEÜÇEàÇEäÇ‹}$ÇEÐÿÿÿÿ‹M$ƒÇÁï½)ÁYƒût ÝÓeÐ÷UÐÇEÌ‹M$½»)Á ÍÓeÌë´&‹E(ǘC9ûrñ‹M ‹@9Є=‹M ‰»‰ö¼'‹EǘCƒû~ð‹…Û„‹M$Bþ‹]rÿ¯Á‹ ‰Ë)ËE$‰]ȉ˯Æ)É؋]‰C‹E ‹…Û„‹E$¯Â)Á9ó‰È„3‹M‹]ȉA ‰Y‹E‹0…ötX÷E,uO‹]‹ …Ét‹E$‹]¯Â¯Ã‹]$)Á‹M‰A‹E$»¯Â‹U¯Â‹U‹ š…Ét)Á‰LšCƒû~êt&ÇEÔ1Ûƒÿ‹utbë ‰|$ ‹M(‰t$‰|$‰ $èYÿþÿ…ÀuCƒÆƒû~Ü‹EÔƒø‡1ÀƒÄ<[^_]ÃÇ‹@;E„J‰é¯þÿÿ‹U‹š…ÀtÿEÔƒ}$„õƒ}$„¶‹M(Cƒû~Ñ‹U(‹]Ô‹Ñû…EÌ„ò÷UЋMРȉ…Û~‹U(‹LÔ‹ØÓø‰éyÿÿÿ‰|$‰ÃEÔ‰D$‹E(¾‰t$ Ñû‰$è–þþÿ…À…Pÿÿÿ‹U(‹Dºü…EÌ…Ê‹UЋM(!ЉD¹ü…ÛŽ*ÿÿÿ‰|$‹DÔ‹](‰D$‰$è£ÿþÿ…À… ÿÿÿéÿÿÿ¶‹M ‹…À…£þÿÿ‹u‹]$¯ÖJ¯Ó‹]‹Ç)ЉCéþÿÿ‹éÿÿÿ‹]‹EÈljCéþÿÿ·‹U(éõþÿÿ‹}ЋM(!ø‰é ÿÿÿÇ‹]ÿé\ýÿÿ‹MÇAÇA éÃýÿÿ÷UЋMРȉDºüé1ÿÿÿvU‰åWVSìüƒ} •À1Òƒ} •Â…Ðtƒ} •À1Òƒ} •Â…Ð…X‹U(…Ò…m‹} ¹ÁçGÿƒø?‡&¸_Áë‰D$ ¸ ‰D$1À‰D$E‰$è=ÿÿ…À‰Á…ó‹U1À‹u4‰‚ 1À‰‚ 1À€}‰•dÿÿÿ”À‰…`ÿÿÿ1À‰…\ÿÿÿ‹E0 ð E8…1À÷E”À÷Ø1Ò!…\ÿÿÿ‰•Xÿÿÿt‰½Xÿÿÿ‹E8…ÀuÇE8‹E4…ÀuÇE4‹E0…Àu‹U4‹u8‹E¯Ö‰Ñ1Ò÷ñ‰E0‹M4‹E0‹U8¯Á¹¯Â;E…91ö¸@‰t$‰D$ ‹E‰D$‹U‰$èÈJÿÿ…À‰Æ…„¹@1Ò‰L$ ‹E‰T$‰D$‹U‰$èJÿÿ…À‰Æ…Y¸@‰D$ ‹E‰D$1À‰D$‹U‰$èrJÿÿ…À‰Æ….¸@‰D$ 1À‰D$1À‰D$‹E‰$èHJÿÿ…À‰Æ…†¾1Ò‰µhÿÿÿ‹u´&¼'1ɉL•¨Bƒú~ô‹E ‰4ÿÿÿ)ÈÁà‰…TÿÿÿƒÀ‰…Dÿÿÿ¸‰Â¶DÿÿÿÓâƒ} ‰•pÿÿÿ„‹M 94ÿÿÿ„ÿƒû„/‹TÿÿÿƒÁ ÓàH‰…lÿÿÿ‹E$…Àt‹U$‰:‹E‹pÿÿÿ…À‰tÿÿÿu1À‰…tÿÿÿ‹E(…À„¢EŒ‰$èi—þÿCÿ1Òƒøë 1ɉL•ÈB9Ðõ‹tÿÿÿ1À‰Lĉ…|ÿÿÿ1À‰…xÿÿÿ‹E9…xÿÿÿÇE„ÇE€vƒÑƒûŽg‹EŒ€8b„1Òë ‹ƒÆ‰D•ØB9Ú|ò‰u¨‹•tÿÿÿ‹|Ô‹lÿÿÿ‹E ú!ÊÆ…•pÿÿÿt ‹…lÿÿÿ÷Р‰TÔ‹…`ÿÿÿ…À„ã‰\$ UÈM؉T$‰L$‹…dÿÿÿ‰$è’ðÿÿ‹•dÿÿÿº €„e1Òë ‹D•؉D•ÈB9Ú|ó‹…\ÿÿÿ…À…Òÿ…xÿÿÿ‹U9•xÿÿÿé)ÿÿÿ‹dÿÿÿ‹ …ÀtSuˆ‹…Xÿÿÿ‰D$‹•`ÿÿÿ‰t$‰T$ ‹M‰L$‹…dÿÿÿ‰$è¹öÿÿ…À‰Ã…[‹dÿÿÿ‹Uˆ•hÿÿÿ‹ …Àu°‹} …ÿt‹…hÿÿÿ‹U ƒÀÁè‰M1ö‰ $‰t$èþþÿ‰Át&¼'Äü‰È[^_]Ãvƒ} ¹uå‹U(…Ò„ûÿÿv¼'E”‰$è…•þÿ…À‰Áu¿ü‹u”¹¿@Íó¦—Â’À8¹„_ûÿÿëš¹‰\ÿÿÿéØûÿÿ1À‰D$‹dÿÿÿ‰ $èöýþÿÄü‰ñ‰È[^_]ËXÿÿÿUˆ‰L$‹…`ÿÿÿ‰T$‰D$ ‹M‰L$‹…dÿÿÿ‰$è—õÿÿ…À‰Ç…l‹Uˆ•hÿÿÿéSþÿÿ‰\$ UÈM؉T$‰L$‹…dÿÿÿ‰$è_ñÿÿéþÿÿƒ} „¢ƒ} „¹¶‰EØé™ýÿÿ‹ME˜‰D$ ‰L$$‹E ‰D$‹U8‰T$‹M4‰L$‹E0‰D$E„‰D$ E€‰D$…|ÿÿÿ‰D$E¨‰$èŽöÿÿ1Òë ‹D•˜‰D•ÈB9Ú|ó‹DÄ‹•tÿÿÿ‹…lÿÿÿ!Â…•pÿÿÿt ‹…lÿÿÿ÷Р‰TÄé¡ýÿÿ‹‰EØéýÿÿ‰Ú…Ûë ‹ƒÆ‰D•ÔJuôéëüÿÿ·‰EØéàüÿÿEŒ‰$è·“þÿéYüÿÿ¸ÿÿÿÿé üÿÿ1ÿ‰|$‹•dÿÿÿ‰$éyþÿÿ1ö‰t$‹•dÿÿÿ‰$è`üþÿ‰ÙéÙýÿÿ‹M ‰ØÁáÓà‰ÁI‰lÿÿÿéËûÿÿ1À‰D$‹…dÿÿÿ‰$è-üþÿ‰ùé¦ýÿÿ¶U‰åW1ÿVSììƒ} ‰½|ÿÿÿ•À1Òƒ} •Â…Ðtƒ} •À1Òƒ} •Â…Ð…™‹u,…ö…¤‹E ¹Áà‰…Pÿÿÿ‰…tÿÿÿHƒø?‡`‹½tÿÿÿ‹UƒÇ‰•dÿÿÿÁï1Ò¶¼'1Û‰\•¸Bƒú~ô‹U ½»‰Þ)ÂÁâJÓæ¹ÿÿÿÿ;E ‰lÿÿÿtƒÿ„ÐJ ÓãK‰lÿÿÿ‰µpÿÿÿ‹U…Òu1À‰…pÿÿÿ‹E,…À„)E‰$èI’þÿWÿ1Àƒú‰…hÿÿÿ‰•Lÿÿÿëv‹hÿÿÿ1À‰D˜A9Lÿÿÿ‰hÿÿÿwå‹…pÿÿÿ1ö‹U(‰t$‰D½”¸@‰D$ 1À‰D$‰$è[?ÿÿ…À‰Á…]1À€}‹]<”À‰…\ÿÿÿ‹E8 Ø E@•Â1À÷E”À1ɉTÿÿÿ!Љ…Xÿÿÿ…‡‹E@…ÀuÇE@‹E<…ÀuÇE<‹u8…öu‹U<‹]@‹E¯Ó‰Ñ1Ò÷ñ‰E8‹M<‹E8‹U@¯Á¹¯Â;E…ÉÇEˆ1À‰…hÿÿÿ‹E9…hÿÿÿÇE„ÇE€ƒ‰‹•\ÿÿÿƒÂ‰•Hÿÿÿ‹Hÿÿÿ1À‹U(‰D$EŒ‰L$ ‰D$‰$è`>ÿÿ‰…`ÿÿÿ…À…o‹EŒ»‹•\ÿÿÿ‰xÿÿÿ‰ÁƒáÓ¥xÿÿÿ…Ò„èÁèƒà‹…͉…tÿÿÿ‹µXÿÿÿ…ö•À1Òƒ½tÿÿÿA”Â…Ðt ‹…Tÿÿÿ‰…tÿÿÿ‹…xÿÿÿ‹hÿÿÿØ;Ev‹U‹hÿÿÿ)ʉ•xÿÿÿ1Ò‹xÿÿÿ‰•|ÿÿÿ9|ÿÿÿƒ‹…tÿÿÿƒè ‰…@ÿÿÿt&1Ò9ús&v¼'‹D•˜‰D•ØB9úró1Òë1À‰D•¨B9úrõ‹…tÿÿÿ…À„–ƒ½tÿÿÿ †¥1À1Û‰…`ÿÿÿ‹…tÿÿÿ…Àtu‹µtÿÿÿU¨‰•Dÿÿÿ¶9@ÿÿÿ‰ðv¸ ‰D$ 1À‹Dÿÿÿ9@ÿÿÿ‰L$–ÀƒÃ ‰D$‹E(ƒî ‰$èó<ÿÿ …`ÿÿÿƒ…Dÿÿÿ;tÿÿÿr®‹…`ÿÿÿ…À…ȃÿ‡ê‹uØ‹E¨‹lÿÿÿð!؉EØ‹…dÿÿÿ‹pÿÿÿ)L½Ôƒÿ‰E¸†‹E€8b„%1Òë‹dÿÿÿ‹D•ØB‰ƒÁ‰dÿÿÿ9úræ‹Xÿÿÿ…É…1Òë ‹D•؉D•˜B;•Lÿÿÿrï‹…pÿÿÿ‹\½ÔØÿ…|ÿÿÿ‹xÿÿÿ‰D½”9|ÿÿÿ‚ƒþÿÿ‹…xÿÿÿ‹U…hÿÿÿ9•hÿÿÿ‚†ýÿÿ‹M…Ét ‹hÿÿÿ‹E‰1ÉÄì‰È[^_]Ã} ¹uè‹u,…ö„\ûÿÿE”‰$èfŽþÿ…À‰ÁuÌü‹u”¹¿@Íó¦—Â’À8¹„(ûÿÿë§E‰$èŽþÿéÒûÿÿ‹Pÿÿÿ‰Tÿÿÿéhüÿÿƒ} „ùƒ} „5‹EØ‹•dÿÿÿˆ‹M dÿÿÿ‹Xÿÿÿ…É„äþÿÿ‹E‹U ‹M@‰D$$E˜‰D$ ‹E<‰T$‹U8‰D$Eˆ‰D$ E„‰D$E€‰D$E¸‰L$‰T$‰$èÚïÿÿ…Àu;‹…pÿÿÿ‹T½”‹µlÿÿÿÐ!ðéžþÿÿ‰|$ E¨‰D$E؉|$‰$èÃðþÿ…À„þÿÿ‰ÁéÀþÿÿ‹•tÿÿÿE¨‹M(‰D$‰T$‰ $èH9ÿÿ‰…`ÿÿÿºë ‹E¨Áø‰D•¨B9úrñé™ýÿÿ‹EØ‹•dÿÿÿ‰é ÿÿÿ‰ú…ÿë‹dÿÿÿ‹D•Ô‰ƒÁJ‰dÿÿÿuèéÕýÿÿÁèƒà‹…àÌéüÿÿ‹EØ‹dÿÿÿf‰éÅþÿÿ‹M ‰øÁáÓà‰ÁI‰lÿÿÿé$úÿÿ‹E…Àt‹…hÿÿÿ‹½|ÿÿÿ‹Uø‰‹`ÿÿÿéïýÿÿ‹}…ÿtî‹…hÿÿÿ‹µ|ÿÿÿ‹Mð‰ëÙU¸‰åVSƒì‹] ‹u…ÛtZ‹…ÒtT‰4$1À¹‰L$ º‰T$‰D$è£ôþÿ…Àu0‹‰Ç@Ç@Ç@ Ç@Ç@Ç@1ÀƒÄ[^]ô&U‰åSƒì‹]‰]ô…Ût0‹C‰EøC‰D$Eø‰$èwôþÿÇC1ÉEô‰L$‰$è_ôþÿƒÄ[]Éö¼'U¸‰åƒì(‹M ‰uü‹U‰]ø‹uƒù‡½ƒúA‡´ƒú †»9ʸ‚ž‰NÓà‰F ÐL‰V‹F‰L$ ‰Eô¸(‰D$F‰D$Eô‰$è8òþÿ…Àud‹^1É‹Eô…ۉ‰FuëD !؉Ë)ÉZAƒÂ(9Nv.ÇBÇ‹^ ÇB$ÇB 9ËÇBw‰JëÉÇF1Àt&‹]ø‹uü‰ì]öº!é;ÿÿÿ¶U¸‰åWVSƒì‹}‰D$ 1À‰D$‹G‰D$‹‰$èT<ÿÿ…À…ÜÇEð‹E ‹WÇ‹O‹GÓeð‹]ðÛÁà‹t…öuD‰ö¼'ƒè(K‹…Òtö‹UðC9Øs‰Ø)ÐHÿ‰L$¸1ö‰D$ ‰t$‹‰$è×;ÿÿ…Àuc‹E 1öƒ9ÞsQ‹UðB‰Uìë6¸‰D$ 1À‰D$‹W¶‹D‰D$‹‰$è—;ÿÿ…Àu#‹E Fƒ9Þs9uìuÅ‹Eð‹WÐpë¸1Àt&ƒÄ[^_]ô&U¸‰åƒì(‰D$ 1À‰uø‹u‰D$Eð‰]ô‰}ü‰D$‹‰$èž6ÿÿ…Àt ‹]ô‹uø‹}ü‰ì]ø‰D$ 1À‰D$Eì‰D$‹‰$èm6ÿÿ…Àuω4$‹Eì‰D$‹Eð‰D$ècýÿÿ…Àuµ‹N¿1Û‹FÓçø@‰Fë‹Eð›C‹N‰DÑ‹Uì‰øÐ9Ør9¸1ɉD$ Eð‰L$‰D$‹‰$èÿ5ÿÿ…À…]ÿÿÿG9Øu¸‹FøXë®1ÀéEÿÿÿë U‰åVSƒì»(‹u‹N‹VÓã‹DT ‰T$‰D$‹‰$è9ÿÿ…Àu‹F‹T‹E ‰1ÀƒÄ[^]Ãt&U‰åSƒì‹]‹U …Û‰Ðt‹9v‰T$‹C$‰$èØÿÿÿ‰C$‰ØƒÄ[]ÉT$‹C ‰$è¾ÿÿÿ‰C ëä‰ö¼'U‰å‹MS‹] …ɉØt‹A‰Êë‰Â‹@…Àu÷‰Z‰È[]ô&U1À‰åVSƒì‹u…öt0‹F$‰$èäÿÿÿ‰Ã‹F ‰$è×ÿÿÿ‰$‰t$è›ÿÿÿ‰$‰\$èÿÿÿƒÄ[^]ô&Uº‰åWVSƒì ‹E‹H‹xÓâ‹HʉÐ1É@‰Eðt81ö‰Ãë‰öƒÆ(Kt*‹>…Àtó‰ $>ƒÆ(‰D$èáþÿÿK‰Áuâ¶¿‰ $èHÿÿÿ‹Uð…Òt#‹]ð1Ò¶¿1ö1ɉt:$‰L: ƒÂ(KuîƒÄ [^_]öU‰åVS‹M‹u ‹A‹Q€@Ú‰A‹F‰r ‹‹‰B$Ù‹X‰ ‰Ð…Û‰Zt8; v4‹C‰Þ…Àt/t&¼';r;v‰Æ‹@…Àuï‰B‰Ø‰V´&[^]ËC‰B‰Ø‰V[^]ö¼'U‰åƒì‰uü‹u‹E ‰]ø…öt$‰FX‰\$‹F ‰$èÕÿÿÿ‰\$‹F$‰$èÆÿÿÿ‹]ø1À‹uü‰ì]Ãv¼'U¸‰åWVSƒìL‹UÇEÔÇEÀ‹JÇEÄ‹rÓàð@9EÔ‰EЃöÇE¸‹R‰U¼¶‹U¸‹M¼‹D …À„¾ÇEÌH„°‹EÌ‹M¸ÿẺÂ÷Ò‰EÀ‹E¼‹\‹MÀÚ‰ÏÁé‰Öƒç‰MÜ ˆ‹E¸‰}؃æÁê‰UäÁ‰uà‹Y ‰M´‰ù‰ØÓèƒà‹M¸‰EÀ‹E¼‹D ‰ñ‹UÀÓèƒà‰ù‰EÄ1‰ÐÓà1ËE´‹M¼‰X ‹Eä‹MàÓâ‹M¸1T ‹U¼‹EÌ‹t÷Ðð;ĖXÿÿÿ´&ÿEÔ‹MЃE¸(9MÔ‚ÿÿÿƒÄL1À[^_]ÃvU‰åW1ÿV1öSì,‹E‰µäþÿÿ‹U1ö‰½àþÿÿ‹H‹Z¸1ÒÓàع@‰…Üþÿÿ…èþÿÿ‰L$‰T$‰$èI;µÜþÿÿsgü‹M1ÿ‰½Øþÿÿ‹Q‹…Øþÿÿ‹\ƒû@‡Ô…Ût1‹Øþÿÿ1À| ¹ó«‹M‹„äþÿÿ‹Q‹Øþÿÿ‰D ÿ„äþÿÿƒ…Øþÿÿ(F;µÜþÿÿr¨1Û‰àþÿÿ»?¶¼'‹…àþÿÿ‹Œèþÿÿ‹”äþÿÿÈÑ艄äþÿÿK‰•äþÿÿ‰•àþÿÿuÒ‹½Üþÿÿ…ÿt'‹E1É‹µÜþÿÿ‹P‹\…Ût ‹„äþÿÿD ƒÁ(Nuç‹U‰$èvýÿÿÄ,[^_]ÃÄ,¸[^_]Ãt&¼'U‰åWVSƒì‹]‹E S ‹K‰Uð‹Px ‰Mì9Ês‰Uì‹Eì1ö…ÀuE‹K1À9Ñt ƒùÀƒàHƒÄ[^_]Ãt&ƒEðƒÇ‹1ö‹Eð‰ñ‹‰Ø1ÐÓè¨u"t&FÿMìt0ƒþ tÕ‹Eð‰ñ‹‹‰Ø1ÐÓè¨tâƒÄ‰Ø‰ñ[ÓèÓêƒàƒâ)Ð^_]ÃÄ1À[^_]ÃU‰åƒì ‰]ô‹] ‰uø‹u…Û‰}ü‹}„–‹N‹F€Ñ‹M@‰F‰‹9xtD‰\$B ‰D$ G‰D$‰4$èªÿÿÿ…Àu‹9zu.‹M‹‰P$1Àƒ(‹]ô‹uø‹}ü‰ì]Ãt&‰B ‹ƒÂ(9z‰tÒ‹U‹‰\$‰4$ƒÀ$‰D$ G‰D$èRÿÿÿ…Àu¼1À븋N]ð‰Mðé_ÿÿÿ¶¿U‰åSƒì‹]‰$èþüÿÿ…Àt ƒÄ[]Ãt&¸p¾‰D$ ¸(‰D$‹C‰D$‹C‰$èÜ‹E ‰$‰D$ ¸‰D$1À‰D$èÎþÿÿƒÄ[]ô&U‰å‹EW¿VS‹H‹X‹PÓçû›Áà‹t…öuDvƒè(K‹0…ötöC99Ø4ýs ‰Ø)È4Å1É9ùs6‰ùt&‹B¯ƒÂ(ÆIuò‰ù9Ùs ¶¿‹BÈ)ø¯AƒÂ(Æ9Ùrì[‰ð^_]Ãt&U‰åWVSƒì‹}‹U‹E‹‰Uì‹u ‰Eð‹K ‹SëI…Éu9‹C…Àtp‹K …ɄNjC¾@ÿK‰CAÿâÿ‰C ƒúÿ„¥¹‰ÐIƒà‹t† Ñú‹F …Àu°‰S‹Uð‰K ‹F‰‹W 9Ð}/‹G‹Uì‰1ÀƒÄ[^_]Ãt&‹‹BH‰B…ÀxB‹¶@‰‰Êë›)Љ‹Eð…Ò‰tW;W¸wÄ‹E쉋Uð‹‰U ‰]‰EƒÄ[^_]é±+ÿÿ‰$艋‰Á‰ÊéRÿÿÿÇC¸ÇC ƒÄ[^_]ø@émÿÿÿ‰ö¼'U‰åWV¾Sƒì,‹}‹E‹OÓæ…Àu8‹M ‰ð÷Ø 1ʅ„ˆ…Ò» x¹‰Ë‰ÐIÿÓè¨tóE ‰Eäë‹E » ‰EèÁø‰EìEè‰Eä‹W€4‹F‰D$F ‰D$‹‰$è°/ÿÿ‰\$‹Eä‰D$‹‰$è›/ÿÿ‹FËE‰ƒÄ,1À[^_]ËWFÿ!È€4‹^F ‰D$‰\$‹‰$èa/ÿÿ‹E‰ƒÄ,1À[^_]ÉöU‰åWVSƒì ƒ}•À1Òƒ}•Â…Ðtƒ}¸…)ÇEà‹E ‹U‰EÜ‹E‹RÁàƒø@‰Uغ†‰Uè‹E…ÀuÇEèÇEì‹E‹UÇEä‹]è‹HÓeä9UìÇEðÿÿÿÿƒ‹Mä‹UØ‹}‰‰EÔv¼'ƒ}„èƒ}„‹Mܶ‹EEÜ‹EèÂ;Uàv‹u…öt ;U舄‹Uà;Uðs‰Uð;Uìv‰Uì‰Ñ)Ùxr9Úsy‹MÔÿ(O‰Óu›‹]‹Eè)Eð)Eì…Ût‹E‹Uð‹M쉋E ‰‹Uä‹MØ’ÇÁ‰Ð‹U‹JÈ@‰B1ÀƒÄ [^_]ÃÇEàÿÿÿÿHÿÓâéèþÿÿ1Òéxÿÿÿ9ÚsŽ´&‹Eä 1Ë÷Ø…Ãu"‹EäH!È‹MØ€ÿÁénÿÿÿ‹MÜ‹éÿÿÿt&…Û¾ x¹‰ö‰Î‰ØIÿÓè¨tó‹Mäë¿‹EÜ·éêþÿÿU‰åƒìX‰uø‹u ‰}ü‹}ƒþ‰]ô•À1Òƒþ•Â…Ðt ƒþ¸u‰|$Eð‰$èðïÿÿ…Àt ‹]ô‹uø‹}ü‰ì]Ã1Û¹‰\$‰L$‹Eð‰$è•ðÿÿ…À‰Ã…>Eì‰D$Eè‰D$‹E‰D$‹U‰t$‰T$ ‹M‰L$‹Eð‰$èyýÿÿ…À‰Ã…‹Eð‰$è„ôÿÿ‹P…Òt#¶¼'‰D$‹Eð‰$èõÿÿ‹P…Òuê‰$1Û‰\$è|õÿÿ‹Eð‰$èaúÿÿ‰EÐ1Ò¹@‰L$ ‰T$‹E‰<$‰D$è`-ÿÿ…À‰Ã…‰¸@‰D$ ‹U‰T$‹Eè‰<$‰D$è7-ÿÿ…À‰Ã…`¸@‰D$ ‹M‰L$‹Eì‰<$‰D$è-ÿÿ…À‰Ã…7‰<$¸@‰D$ 1À‰D$1À‰D$èç,ÿÿ…À‰Ã…Eä‰D$‹Eð‰$èKðÿÿ…À‰Ã…ô‹Uä‹Eð‰UÔ‰$è*öÿÿ…À‰Ã…Ó‹Mõƒø@‰M̆FÇEØ‹E$º…Àt ‹E$Ç@‰UÜ‹]…ÛuÇEÜÇEà‹EÜ‹U9Uàƒ­ƒþ„ƒþ„‹M̶uÌ‹MÜË;]Øv‹U…Òt;]Üxc‹]؉Ù1Ò)Á‰L$9ÉÈ’ÂÁè1ЉD$Uä‰T$ ‹Eð‰$è—úÿÿ…À‰Ç…¿ÿEà‰Ø‹MäMÔézÿÿÿ‹Eð‰$èòíÿÿ‰Ø‹uø‹]ô‹}ü‰ì]Ã1Û뜋MÌ‹évÿÿÿ‹UÌ·ékÿÿÿMä‰L$‹Eð‰$è(ñÿÿ…À‰Ãuµ‹EäEÔ‹Eð‰$è¡íÿÿ‹Uи 9UÔ…$ýÿÿ‹E …Àt‹EÔ‹M ƒÀÁè‰1ÀéýÿÿÇEØÿÿÿÿ‹}$HÿºÓâ…ÿ„ºþÿÿ‹M$‰é°þÿÿ‹Eð‰$èCíÿÿ‰øéÐüÿÿ¶¿U‰åƒìx‰]ô‹] ‰uø‹u(ƒû‰}ü•À1Òƒû•Â…Ðt ƒû¸u!‰4$¸@‰D$ 1À‰D$1À‰D$è"&ÿÿ…Àt‹]ô‹uø‹}ü‰ì]Ét$Eĉ$èAìÿÿ…Àuß‹Eĉ$è"ïÿÿ…À‰Æ…EÀ‰D$‹Eĉ$èÖöÿÿ…À‰Æ…ôÇE¤Ý‹}ÇE´ƒø@w#ÇE´ÿÿÿÿºHÿ‰ÖÓæƒû‰u¤tˆÁÓâJ‰U´‹E‹u¤…À‰u¸uÇE¸ÇE°‹E¸‹U9U°‰EÈÇEÌ´&¼'ƒ‘‹EÀM¼u؉t$‰D$‹EĉL$ ‰$è:÷ÿÿ…À‰Æu=‹uÈ‹EØð;E´‰EÈv‹M…Ét;E¸xB‹E´‹U¸)Ѓût9ƒût8ˆÿE°ß‹M9M°ë—‹}…ÿt‹U°‹E‰‹Eĉ$èëÿÿ‰ðé¨þÿÿ1À뽉ëÊf‰ëÅ‹u…öt‹E°‹u‰‹Eĉ$è_ëÿÿ1ÀézþÿÿU‰åWVSƒì‹u‹}‰4$èX+ÿÿ‰$‰Ãè~…Àuê‰$èR …ÀuÞƒû ”Àƒû” Шt(¶¿‰4$è+ÿÿ‰Ãƒû ”Àƒû” ШuäƒûtßûÕ¸tƒÄ[^_]É4$è²*ÿÿ…Àuì‹U…Òuå‰4$¸@‰D$ ¸‰D$Eð‰D$èÖ#ÿÿ…ÀuÀ…ÿt‹Eð‰‰4$¸@1ÿ‰D$ Eì‰|$‰D$è«#ÿÿ…Àu•‹] …Ût‹Eì‹U ‰‰4$1Ò¹@‰L$ Eè‰T$‰D$èz#ÿÿ…À…`ÿÿÿ‹E…Àt‹Eè‹U‰1ÀéJÿÿÿÿ%4óÿ%,óÿ%@óÿ%0óÿ%Lóÿ%Tóÿ%<óÿ%Dóÿ%Póÿ%Hóÿ%$óÿ%óÿ%óÿ%Ðóÿ% óÿ%Ôóÿ%óÿ%óÿ% óÿ%óÿ% ôÿ%„óÿ%ôÿ%|óÿ%€óÿ%xóÿ%üóÿ%ôÿ%øòÿ%Àóÿ%ôóÿ%øóÿ%˜óÿ%èóÿ%àóÿ%äóÿ%Üóÿ%°óÿ%´óÿ%àòÿ%äòÿ%Èóÿ%¸óÿ%ôÿ%Ìóÿ%Äóÿ%hóÿ%ôÿ%ôÿ%üòÿ%ôÿ%ôÿ%¼óÿ%èòÿ%¬óÿ%óÿ%óÿ%dóÿ%ôòÿ% ôÿ%ðòÿ% óÿ%ìòÿ%¨óÿ%`óÿ%Xóÿ%tóÿ%lóÿ%œóÿ%ˆóÿ%óÿ%Œóÿ%ðóÿ%Øóÿ%Üòÿ%(óÿ%ìóÿ%”óÿ%póÿ%\óÿ%8óÿ%¤óÿ%Lôÿ%|ôÿ%œôÿ%Pôÿ%Àôÿ%Œôÿ%Üôÿ%õÿ%Äôÿ%øôÿ%ôÿ%¨ôÿ%Ðôÿ%”ôÿ%Ìôÿ%üôÿ%ðôÿ%ìôÿ%ˆôÿ%\ôÿ%pôÿ%Øôÿ%àôÿ% õÿ%õÿ%¼ôÿ%èôÿ%äôÿ%„ôÿ% õÿ%õÿ%¬ôÿ%ôôÿ%`ôÿ%dôÿ%õÿ%¸ôÿ%Èôÿ%xôÿ%õÿ% ôÿ%¤ôÿ%˜ôÿ%€ôÿ%Tôÿ%hôÿ%°ôÿ%õÿ%lôÿ%õÿ%´ôÿ%$õÿ%tôÿ%ÔôU¸‰å] U‰åƒì¡ ÷ƒ8tÿ‹  ÷‹QA£ ÷…ÒuéÉô&U‰åSƒì¡Ùƒøÿt)…À‰Ãt‰ö¼'ÿÙKuöÇ$0ÔèÊ<üÿY[]Ã1Àƒ=Ùë @‹…Ù…Ûuôë¾¶¼'U‰åSƒì‹À×…Ûu5¡Ù¹‰ À׃øÿt$…À‰Ãtt&ÿÙKuöÇ$0ÔèZ<üÿX[]Ã1Àƒ=Ùë @‹…Ù…ÒuôëÃU¹@Ήåë¶‹Q‹ƒÁ‚ù@Îrê]ÃU¡Ø‰å]‹Hÿá‰öUºB‰åS·Àƒìd‰T$U¨1Û‰T$‰$ÿ4ôº¹ƒì …ÀuëFÉJx€|*¨Auô ËÉJyòƒ;øÿÿèÿ%@ôÿ%0õÿ%4ôÿ%0ôÿ%,ôU‰å]éÇ8üÿÿÿÿÿðØÿÿÿÿtE"|ž^"¨pw"Ìò¯!ù#";JDSwig object carries a C/C++ instance pointerbb/Swig object carries a C/C++ instance pointerpÓz‰®S—‰~T­‰NUȉV쉩WŠVX0ŠnYPŠZpŠ0[Šß[¼Š×\èŠw]‹o^E‹__‹_|‹m`¨‹bÌ‹Ueô‹iŒùj@ŒLkdŒ…lˆŒLm°Œ–nØŒFoüŒp@q;RrXsvKt”ût¬{uÈYvðòxŽ5{@Žs|hŽ^~”ŽðÀމ‚äŽÊ„… 4†;ã†UÛ‡p{ˆ”s‰µŠË“Šäq‹¨Œ0(ŽTw!‘”’°î’Ð̓쪔‘ˆ•<‘É—d‘I™Œ‘Éš¯‘¸›Ì‘8ì‘ož’ºŸ4’˜ d’È¢„’ ¦¨’§Ì’A¨ð’#©“ª0“ߪS“¿«p“­˜“Þ­¼“ͮܓ«¯”â° ”#²D”³h”ª´Š”ᵨ”··Ì”ø¸ò”Ö¹•´º4•â¼X•b¾x•÷¿˜•wÁ¼•XÃà•6Ä–ÈÅ5–aÉT–çËx–ÒÍœ–°ÎÀ–ŸÏ䖇їeÒ$—åÓD—ÌÕp—»Ù”—¦Û¸—„ÜØ—Þø—;ߘ*àK˜áh˜ñ∘q䬘æИàæí˜è ™Xé0™6êP™ì€™Gî¡™*ðÀ™ñà™æñšÄò$š¢óLš”ôpšö”š”÷ÄšýøäšÛù›2û,›ýP›“þ|›qÿ¤›¨È›Øì›¶ œH0œ*Tœ„œæ°œ& Ïœ¦ êœ ,ëPkxIœ'¼äéž (žaLž¢pž€ž^¬ž<ÌžÉ íž²" Ÿ#,Ÿ«%MŸ‰&lŸx'Ÿø(´ŸI,ÔŸÉ-ôŸt1 R24 m4Q ¤5p $7” 8¼ @9Ü :ý ³;¡3=D¡Å>h¡£?¡B´¡CØ¡{Dü¡QF¢ÑGD¢²Id¢Jƒ¢”¢·¢Æ¢Ô¢ç¢ù¢£3£H£e£q£|£Ž£Ÿ£¸£Éߣæ£ð£ù£¤¤¤¤"¤+¤3¤Píhí€í˜í°íÈíàíøíî(î@îXîpîˆîPíhí€í˜í°íÈíàíøíî(î@îXîpîˆîàîï ï@ï`ï€ï ïÀïàïð ð@ð`ð€ðSwig var link object:¦H¦Y¦i¦|¦;Zx—µÔó0Nmlittle_endianbig_endianlittle_endianbig_endianieee 754-1985othertextdblqsglqnullwordPºXºfº0Á;ÁJÁXÁsÁ€ÁÁœÁ³ÁÐÁôÁÂ3ÂJÂABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/0123456789ABCDEFABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/ÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿ>ÿÿÿÿÿÿÿÿÿÿÿÿ?456789:;<=ÿÿÿÿÿÿÿÿÿÿÿÿ@ÿÿÿÿÿÿÿÿÿÿÿÿ ÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿ !"#$%&'()*+,-./0123ÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿ€Ùÿÿÿÿÿÿÿÿ0123456789abcdefNULLÞ8/& ùðç%s %sat least %s expected %s%d arguments, got noneUnpackTuple() argument list is not a tuple%s expected %s%d arguments, got %dat most __new____swig_destroy__%o%xswig/python detected a memory leak of type '%s', no destructor found. PySwigObjectowndisownreleases ownership of the pointeracquireaquires ownership of the pointerreturns/sets ownership of the pointerappendappends another 'this' objectnextreturns the next 'this' object__repr__returns object representation%s%sPySwigPackedthisswig_ptr: __dict__swiginittype_pointerswig_runtime_data3argument number %d:a '%s' is expected, '%s(%s)' is receiveda '%s' is expected, '%s' is receiveda '%s' is expectedunexpected type is receivedCBF_FORMAT CBF_ALLOC CBF_ARGUMENT CBF_ASCII CBF_BINARY CBF_BITCOUNT CBF_ENDOFDATA CBF_FILECLOSE CBF_FILEOPEN CBF_FILEREAD CBF_FILESEEK CBF_FILETELL CBF_FILEWRITE CBF_IDENTICAL CBF_NOTFOUND CBF_OVERFLOW CBF_UNDEFINED CBF_NOTIMPLEMENTED_p_charrbw+b:get_local_integer_byte_order:get_local_real_format:get_local_real_byte_orderOO:cbf_positioner_struct_matrix_setin method 'cbf_positioner_struct_matrix_set', argument 1 of type 'cbf_positioner_struct *'in method 'cbf_positioner_struct_matrix_set', argument 2 of type 'double [3][4]'invalid null reference in variable 'matrix' of type 'double [3][4]'O:cbf_positioner_struct_matrix_getin method 'cbf_positioner_struct_matrix_get', argument 1 of type 'cbf_positioner_struct *'OO:cbf_positioner_struct_axis_setin method 'cbf_positioner_struct_axis_set', argument 1 of type 'cbf_positioner_struct *'in method 'cbf_positioner_struct_axis_set', argument 2 of type 'cbf_axis_struct *'O:cbf_positioner_struct_axis_getin method 'cbf_positioner_struct_axis_get', argument 1 of type 'cbf_positioner_struct *'OO:cbf_positioner_struct_axes_setin method 'cbf_positioner_struct_axes_set', argument 1 of type 'cbf_positioner_struct *'in method 'cbf_positioner_struct_axes_set', argument 2 of type 'size_t'O:cbf_positioner_struct_axes_getin method 'cbf_positioner_struct_axes_get', argument 1 of type 'cbf_positioner_struct *'OO:cbf_positioner_struct_matrix_is_valid_setin method 'cbf_positioner_struct_matrix_is_valid_set', argument 1 of type 'cbf_positioner_struct *'in method 'cbf_positioner_struct_matrix_is_valid_set', argument 2 of type 'int'O:cbf_positioner_struct_matrix_is_valid_getin method 'cbf_positioner_struct_matrix_is_valid_get', argument 1 of type 'cbf_positioner_struct *'OO:cbf_positioner_struct_axes_are_connected_setin method 'cbf_positioner_struct_axes_are_connected_set', argument 1 of type 'cbf_positioner_struct *'in method 'cbf_positioner_struct_axes_are_connected_set', argument 2 of type 'int'O:cbf_positioner_struct_axes_are_connected_getin method 'cbf_positioner_struct_axes_are_connected_get', argument 1 of type 'cbf_positioner_struct *':new_cbf_positioner_structO:delete_cbf_positioner_structin method 'delete_cbf_positioner_struct', argument 1 of type 'cbf_positioner_struct *'O:cbf_positioner_struct_get_rotation_rangein method 'cbf_positioner_struct_get_rotation_range', argument 1 of type 'cbf_positioner_struct *'OOOOO:cbf_positioner_struct_rotate_vectorin method 'cbf_positioner_struct_rotate_vector', argument 1 of type 'cbf_positioner_struct *'in method 'cbf_positioner_struct_rotate_vector', argument 2 of type 'double'in method 'cbf_positioner_struct_rotate_vector', argument 3 of type 'double'in method 'cbf_positioner_struct_rotate_vector', argument 4 of type 'double'in method 'cbf_positioner_struct_rotate_vector', argument 5 of type 'double'OOOOOO:cbf_positioner_struct_get_reciprocalin method 'cbf_positioner_struct_get_reciprocal', argument 1 of type 'cbf_positioner_struct *'in method 'cbf_positioner_struct_get_reciprocal', argument 2 of type 'double'in method 'cbf_positioner_struct_get_reciprocal', argument 3 of type 'double'in method 'cbf_positioner_struct_get_reciprocal', argument 4 of type 'double'in method 'cbf_positioner_struct_get_reciprocal', argument 5 of type 'double'in method 'cbf_positioner_struct_get_reciprocal', argument 6 of type 'double'O:cbf_positioner_struct_get_rotation_axisin method 'cbf_positioner_struct_get_rotation_axis', argument 1 of type 'cbf_positioner_struct *'O|swigregisterOO:cbf_detector_struct_positioner_setin method 'cbf_detector_struct_positioner_set', argument 1 of type 'cbf_detector_struct *'in method 'cbf_detector_struct_positioner_set', argument 2 of type 'cbf_positioner'invalid null reference in method 'cbf_detector_struct_positioner_set', argument 2 of type 'cbf_positioner'O:cbf_detector_struct_positioner_getin method 'cbf_detector_struct_positioner_get', argument 1 of type 'cbf_detector_struct *'OO:cbf_detector_struct_displacement_setin method 'cbf_detector_struct_displacement_set', argument 1 of type 'cbf_detector_struct *'in method 'cbf_detector_struct_displacement_set', argument 2 of type 'double [2]'invalid null reference in variable 'displacement' of type 'double [2]'O:cbf_detector_struct_displacement_getin method 'cbf_detector_struct_displacement_get', argument 1 of type 'cbf_detector_struct *'OO:cbf_detector_struct_increment_setin method 'cbf_detector_struct_increment_set', argument 1 of type 'cbf_detector_struct *'in method 'cbf_detector_struct_increment_set', argument 2 of type 'double [2]'invalid null reference in variable 'increment' of type 'double [2]'O:cbf_detector_struct_increment_getin method 'cbf_detector_struct_increment_get', argument 1 of type 'cbf_detector_struct *'OO:cbf_detector_struct_axes_setin method 'cbf_detector_struct_axes_set', argument 1 of type 'cbf_detector_struct *'in method 'cbf_detector_struct_axes_set', argument 2 of type 'size_t'O:cbf_detector_struct_axes_getin method 'cbf_detector_struct_axes_get', argument 1 of type 'cbf_detector_struct *'OO:cbf_detector_struct_index_setin method 'cbf_detector_struct_index_set', argument 1 of type 'cbf_detector_struct *'in method 'cbf_detector_struct_index_set', argument 2 of type 'size_t [2]'invalid null reference in variable 'index' of type 'size_t [2]'O:cbf_detector_struct_index_getin method 'cbf_detector_struct_index_get', argument 1 of type 'cbf_detector_struct *':new_cbf_detector_structO:delete_cbf_detector_structin method 'delete_cbf_detector_struct', argument 1 of type 'cbf_detector_struct *'OOO:cbf_detector_struct_get_pixel_normalin method 'cbf_detector_struct_get_pixel_normal', argument 1 of type 'cbf_detector_struct *'in method 'cbf_detector_struct_get_pixel_normal', argument 2 of type 'double'in method 'cbf_detector_struct_get_pixel_normal', argument 3 of type 'double'OOO:cbf_detector_struct_get_pixel_areain method 'cbf_detector_struct_get_pixel_area', argument 1 of type 'cbf_detector_struct *'in method 'cbf_detector_struct_get_pixel_area', argument 2 of type 'double'in method 'cbf_detector_struct_get_pixel_area', argument 3 of type 'double'O:cbf_detector_struct_get_detector_distancein method 'cbf_detector_struct_get_detector_distance', argument 1 of type 'cbf_detector_struct *'O:cbf_detector_struct_get_detector_normalin method 'cbf_detector_struct_get_detector_normal', argument 1 of type 'cbf_detector_struct *'OO:cbf_detector_struct_get_inferred_pixel_sizein method 'cbf_detector_struct_get_inferred_pixel_size', argument 1 of type 'cbf_detector_struct *'in method 'cbf_detector_struct_get_inferred_pixel_size', argument 2 of type 'unsigned int'OOO:cbf_detector_struct_get_pixel_coordinatesin method 'cbf_detector_struct_get_pixel_coordinates', argument 1 of type 'cbf_detector_struct *'in method 'cbf_detector_struct_get_pixel_coordinates', argument 2 of type 'double'in method 'cbf_detector_struct_get_pixel_coordinates', argument 3 of type 'double'O:cbf_detector_struct_get_beam_centerin method 'cbf_detector_struct_get_beam_center', argument 1 of type 'cbf_detector_struct *'OO:cbf_handle_struct_node_setin method 'cbf_handle_struct_node_set', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_node_set', argument 2 of type 'cbf_node *'O:cbf_handle_struct_node_getin method 'cbf_handle_struct_node_get', argument 1 of type 'cbf_handle_struct *'OO:cbf_handle_struct_row_setin method 'cbf_handle_struct_row_set', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_row_set', argument 2 of type 'int'O:cbf_handle_struct_row_getin method 'cbf_handle_struct_row_get', argument 1 of type 'cbf_handle_struct *'OO:cbf_handle_struct_search_row_setin method 'cbf_handle_struct_search_row_set', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_search_row_set', argument 2 of type 'int'O:cbf_handle_struct_search_row_getin method 'cbf_handle_struct_search_row_get', argument 1 of type 'cbf_handle_struct *':new_cbf_handle_structO:delete_cbf_handle_structin method 'delete_cbf_handle_struct', argument 1 of type 'cbf_handle_struct *'OO:cbf_handle_struct_select_datablockin method 'cbf_handle_struct_select_datablock', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_select_datablock', argument 2 of type 'unsigned int'OO:cbf_handle_struct_force_new_datablockin method 'cbf_handle_struct_force_new_datablock', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_force_new_datablock', argument 2 of type 'char const *'O:cbf_handle_struct_reset_datablocksin method 'cbf_handle_struct_reset_datablocks', argument 1 of type 'cbf_handle_struct *'OOO:cbf_handle_struct_set_tag_categoryin method 'cbf_handle_struct_set_tag_category', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_set_tag_category', argument 2 of type 'char const *'in method 'cbf_handle_struct_set_tag_category', argument 3 of type 'char const *'O:cbf_handle_struct_row_numberin method 'cbf_handle_struct_row_number', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_set_imagein method 'cbf_handle_struct_set_image', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_set_bin_sizesin method 'cbf_handle_struct_set_bin_sizes', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_new_rowin method 'cbf_handle_struct_new_row', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_rewind_saveframein method 'cbf_handle_struct_rewind_saveframe', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_get_realarrayparametersin method 'cbf_handle_struct_get_realarrayparameters', argument 1 of type 'cbf_handle_struct *'OO:cbf_handle_struct_force_new_categoryin method 'cbf_handle_struct_force_new_category', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_force_new_category', argument 2 of type 'char const *'OO:cbf_handle_struct_force_new_saveframein method 'cbf_handle_struct_force_new_saveframe', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_force_new_saveframe', argument 2 of type 'char const *'O:cbf_handle_struct_count_datablocksin method 'cbf_handle_struct_count_datablocks', argument 1 of type 'cbf_handle_struct *'OO:cbf_handle_struct_find_rowin method 'cbf_handle_struct_find_row', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_find_row', argument 2 of type 'char const *'OO:cbf_handle_struct_select_columnin method 'cbf_handle_struct_select_column', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_select_column', argument 2 of type 'unsigned int'OO:cbf_handle_struct_construct_detectorin method 'cbf_handle_struct_construct_detector', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_construct_detector', argument 2 of type 'unsigned int'O:cbf_handle_struct_rewind_columnin method 'cbf_handle_struct_rewind_column', argument 1 of type 'cbf_handle_struct *'OOO:cbf_handle_struct_require_column_doublevaluein method 'cbf_handle_struct_require_column_doublevalue', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_require_column_doublevalue', argument 2 of type 'char const *'in method 'cbf_handle_struct_require_column_doublevalue', argument 4 of type 'double'O:cbf_handle_struct_get_datestampin method 'cbf_handle_struct_get_datestamp', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_get_integervaluein method 'cbf_handle_struct_get_integervalue', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_get_crystal_idin method 'cbf_handle_struct_get_crystal_id', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_get_doublevaluein method 'cbf_handle_struct_get_doublevalue', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_get_unit_cellin method 'cbf_handle_struct_get_unit_cell', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_remove_columnin method 'cbf_handle_struct_remove_column', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_rewind_blockitemin method 'cbf_handle_struct_rewind_blockitem', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_get_valuein method 'cbf_handle_struct_get_value', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_set_reciprocal_cellin method 'cbf_handle_struct_set_reciprocal_cell', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_count_categoriesin method 'cbf_handle_struct_count_categories', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_read_widefilein method 'cbf_handle_struct_read_widefile', argument 1 of type 'cbf_handle_struct *'OO:cbf_handle_struct_set_wavelengthin method 'cbf_handle_struct_set_wavelength', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_set_wavelength', argument 2 of type 'double'O:cbf_handle_struct_get_diffrn_idin method 'cbf_handle_struct_get_diffrn_id', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_get_dictionaryin method 'cbf_handle_struct_get_dictionary', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_get_polarizationin method 'cbf_handle_struct_get_polarization', argument 1 of type 'cbf_handle_struct *'OO:cbf_handle_struct_select_categoryin method 'cbf_handle_struct_select_category', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_select_category', argument 2 of type 'unsigned int'OOO:cbf_handle_struct_read_filein method 'cbf_handle_struct_read_file', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_read_file', argument 2 of type 'char *'in method 'cbf_handle_struct_read_file', argument 3 of type 'int'O:cbf_handle_struct_datablock_namein method 'cbf_handle_struct_datablock_name', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_set_realarray_wdimsin method 'cbf_handle_struct_set_realarray_wdims', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_rewind_rowin method 'cbf_handle_struct_rewind_row', argument 1 of type 'cbf_handle_struct *'OO:cbf_handle_struct_get_axis_settingin method 'cbf_handle_struct_get_axis_setting', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_get_axis_setting', argument 2 of type 'char const *'OO:cbf_handle_struct_require_columnin method 'cbf_handle_struct_require_column', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_require_column', argument 2 of type 'char const *'O:cbf_handle_struct_get_timestampin method 'cbf_handle_struct_get_timestamp', argument 1 of type 'cbf_handle_struct *'OO:cbf_handle_struct_find_nextrowin method 'cbf_handle_struct_find_nextrow', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_find_nextrow', argument 2 of type 'char const *'OO:cbf_handle_struct_require_tag_rootin method 'cbf_handle_struct_require_tag_root', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_require_tag_root', argument 2 of type 'char const *'O:cbf_handle_struct_reset_datablockin method 'cbf_handle_struct_reset_datablock', argument 1 of type 'cbf_handle_struct *'OO:cbf_handle_struct_require_integervaluein method 'cbf_handle_struct_require_integervalue', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_require_integervalue', argument 3 of type 'int'O:cbf_handle_struct_get_integerarrayparametersin method 'cbf_handle_struct_get_integerarrayparameters', argument 1 of type 'cbf_handle_struct *'OOOOO:cbf_handle_struct_write_filein method 'cbf_handle_struct_write_file', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_write_file', argument 2 of type 'char const *'in method 'cbf_handle_struct_write_file', argument 3 of type 'int'in method 'cbf_handle_struct_write_file', argument 4 of type 'int'in method 'cbf_handle_struct_write_file', argument 5 of type 'int'OOOO:cbf_handle_struct_set_divergencein method 'cbf_handle_struct_set_divergence', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_set_divergence', argument 2 of type 'double'in method 'cbf_handle_struct_set_divergence', argument 3 of type 'double'in method 'cbf_handle_struct_set_divergence', argument 4 of type 'double'O:cbf_handle_struct_remove_datablockin method 'cbf_handle_struct_remove_datablock', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_count_elementsin method 'cbf_handle_struct_count_elements', argument 1 of type 'cbf_handle_struct *'OOO:cbf_handle_struct_get_pixel_sizein method 'cbf_handle_struct_get_pixel_size', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_get_pixel_size', argument 2 of type 'unsigned int'in method 'cbf_handle_struct_get_pixel_size', argument 3 of type 'unsigned int'O:cbf_handle_struct_next_categoryin method 'cbf_handle_struct_next_category', argument 1 of type 'cbf_handle_struct *'OO:cbf_handle_struct_set_diffrn_idin method 'cbf_handle_struct_set_diffrn_id', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_set_diffrn_id', argument 2 of type 'char const *'OOOO:cbf_handle_struct_set_timestampin method 'cbf_handle_struct_set_timestamp', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_set_timestamp', argument 2 of type 'double'in method 'cbf_handle_struct_set_timestamp', argument 3 of type 'int'in method 'cbf_handle_struct_set_timestamp', argument 4 of type 'double'O:cbf_handle_struct_get_orientation_matrixin method 'cbf_handle_struct_get_orientation_matrix', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_get_divergencein method 'cbf_handle_struct_get_divergence', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_rewind_categoryin method 'cbf_handle_struct_rewind_category', argument 1 of type 'cbf_handle_struct *'OO:cbf_handle_struct_read_templatein method 'cbf_handle_struct_read_template', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_read_template', argument 2 of type 'char *'OO:cbf_handle_struct_select_rowin method 'cbf_handle_struct_select_row', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_select_row', argument 2 of type 'unsigned int'O:cbf_handle_struct_count_columnsin method 'cbf_handle_struct_count_columns', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_get_integerarrayparameters_wdimsin method 'cbf_handle_struct_get_integerarrayparameters_wdims', argument 1 of type 'cbf_handle_struct *'OO:cbf_handle_struct_get_gainin method 'cbf_handle_struct_get_gain', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_get_gain', argument 2 of type 'unsigned int'OO:cbf_handle_struct_new_saveframein method 'cbf_handle_struct_new_saveframe', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_new_saveframe', argument 2 of type 'char const *'OOO:cbf_handle_struct_set_polarizationin method 'cbf_handle_struct_set_polarization', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_set_polarization', argument 2 of type 'double'in method 'cbf_handle_struct_set_polarization', argument 3 of type 'double'O:cbf_handle_struct_set_real_3d_imagein method 'cbf_handle_struct_set_real_3d_image', argument 1 of type 'cbf_handle_struct *'OO:cbf_handle_struct_delete_rowin method 'cbf_handle_struct_delete_row', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_delete_row', argument 2 of type 'unsigned int'O:cbf_handle_struct_column_namein method 'cbf_handle_struct_column_name', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_remove_saveframein method 'cbf_handle_struct_remove_saveframe', argument 1 of type 'cbf_handle_struct *'OO:cbf_handle_struct_require_valuein method 'cbf_handle_struct_require_value', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_require_value', argument 2 of type 'char const *'OOO:cbf_handle_struct_require_column_integervaluein method 'cbf_handle_struct_require_column_integervalue', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_require_column_integervalue', argument 2 of type 'char const *'in method 'cbf_handle_struct_require_column_integervalue', argument 4 of type 'int'OOOO:cbf_handle_struct_set_pixel_sizein method 'cbf_handle_struct_set_pixel_size', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_set_pixel_size', argument 2 of type 'unsigned int'in method 'cbf_handle_struct_set_pixel_size', argument 3 of type 'unsigned int'in method 'cbf_handle_struct_set_pixel_size', argument 4 of type 'double'O:cbf_handle_struct_next_columnin method 'cbf_handle_struct_next_column', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_get_realarrayin method 'cbf_handle_struct_get_realarray', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_get_bin_sizesin method 'cbf_handle_struct_get_bin_sizes', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_reset_categoryin method 'cbf_handle_struct_reset_category', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_construct_goniometerin method 'cbf_handle_struct_construct_goniometer', argument 1 of type 'cbf_handle_struct *'OO:cbf_handle_struct_set_datablocknamein method 'cbf_handle_struct_set_datablockname', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_set_datablockname', argument 2 of type 'char const *'OO:cbf_handle_struct_set_crystal_idin method 'cbf_handle_struct_set_crystal_id', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_set_crystal_id', argument 2 of type 'char const *'O:cbf_handle_struct_get_integerarray_as_stringin method 'cbf_handle_struct_get_integerarray_as_string', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_set_3d_imagein method 'cbf_handle_struct_set_3d_image', argument 1 of type 'cbf_handle_struct *'OO:cbf_handle_struct_set_dictionaryin method 'cbf_handle_struct_set_dictionary', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_set_dictionary', argument 2 of type 'cbf_handle'OO:cbf_handle_struct_find_tag_categoryin method 'cbf_handle_struct_find_tag_category', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_find_tag_category', argument 2 of type 'char const *'OO:cbf_handle_struct_set_typeofvaluein method 'cbf_handle_struct_set_typeofvalue', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_set_typeofvalue', argument 2 of type 'char const *'O:cbf_handle_struct_set_integerarray_wdimsin method 'cbf_handle_struct_set_integerarray_wdims', argument 1 of type 'cbf_handle_struct *'OO:cbf_handle_struct_set_integration_timein method 'cbf_handle_struct_set_integration_time', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_set_integration_time', argument 2 of type 'double'OOOO:cbf_handle_struct_set_axis_settingin method 'cbf_handle_struct_set_axis_setting', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_set_axis_setting', argument 2 of type 'char const *'in method 'cbf_handle_struct_set_axis_setting', argument 3 of type 'double'in method 'cbf_handle_struct_set_axis_setting', argument 4 of type 'double'O:cbf_handle_struct_get_real_imagein method 'cbf_handle_struct_get_real_image', argument 1 of type 'cbf_handle_struct *'OO:cbf_handle_struct_get_overloadin method 'cbf_handle_struct_get_overload', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_get_overload', argument 2 of type 'unsigned int'O:cbf_handle_struct_get_wavelengthin method 'cbf_handle_struct_get_wavelength', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_next_datablockin method 'cbf_handle_struct_next_datablock', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_get_realarrayparameters_wdimsin method 'cbf_handle_struct_get_realarrayparameters_wdims', argument 1 of type 'cbf_handle_struct *'OOOOOOOOOO:cbf_handle_struct_set_orientation_matrixin method 'cbf_handle_struct_set_orientation_matrix', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_set_orientation_matrix', argument 2 of type 'double'in method 'cbf_handle_struct_set_orientation_matrix', argument 3 of type 'double'in method 'cbf_handle_struct_set_orientation_matrix', argument 4 of type 'double'in method 'cbf_handle_struct_set_orientation_matrix', argument 5 of type 'double'in method 'cbf_handle_struct_set_orientation_matrix', argument 6 of type 'double'in method 'cbf_handle_struct_set_orientation_matrix', argument 7 of type 'double'in method 'cbf_handle_struct_set_orientation_matrix', argument 8 of type 'double'in method 'cbf_handle_struct_set_orientation_matrix', argument 9 of type 'double'in method 'cbf_handle_struct_set_orientation_matrix', argument 10 of type 'double'OO:cbf_handle_struct_new_categoryin method 'cbf_handle_struct_new_category', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_new_category', argument 2 of type 'char const *'OOOO:cbf_handle_struct_set_gainin method 'cbf_handle_struct_set_gain', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_set_gain', argument 2 of type 'unsigned int'in method 'cbf_handle_struct_set_gain', argument 3 of type 'double'in method 'cbf_handle_struct_set_gain', argument 4 of type 'double'OO:cbf_handle_struct_find_columnin method 'cbf_handle_struct_find_column', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_find_column', argument 2 of type 'char const *'O:cbf_handle_struct_remove_categoryin method 'cbf_handle_struct_remove_category', argument 1 of type 'cbf_handle_struct *'OO:cbf_handle_struct_require_categoryin method 'cbf_handle_struct_require_category', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_require_category', argument 2 of type 'char const *'O:cbf_handle_struct_get_reciprocal_cellin method 'cbf_handle_struct_get_reciprocal_cell', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_get_3d_image_sizein method 'cbf_handle_struct_get_3d_image_size', argument 1 of type 'cbf_handle_struct *'OO:cbf_handle_struct_find_tag_rootin method 'cbf_handle_struct_find_tag_root', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_find_tag_root', argument 2 of type 'char const *'OO:cbf_handle_struct_require_category_rootin method 'cbf_handle_struct_require_category_root', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_require_category_root', argument 2 of type 'char const *'OO:cbf_handle_struct_set_integervaluein method 'cbf_handle_struct_set_integervalue', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_set_integervalue', argument 2 of type 'int'O:cbf_handle_struct_category_namein method 'cbf_handle_struct_category_name', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_get_typeofvaluein method 'cbf_handle_struct_get_typeofvalue', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_set_real_imagein method 'cbf_handle_struct_set_real_image', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_get_3d_imagein method 'cbf_handle_struct_get_3d_image', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_remove_rowin method 'cbf_handle_struct_remove_row', argument 1 of type 'cbf_handle_struct *'OOO:cbf_handle_struct_set_overloadin method 'cbf_handle_struct_set_overload', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_set_overload', argument 2 of type 'unsigned int'in method 'cbf_handle_struct_set_overload', argument 3 of type 'double'OO:cbf_handle_struct_get_image_sizein method 'cbf_handle_struct_get_image_size', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_get_image_size', argument 2 of type 'unsigned int'O:cbf_handle_struct_get_imagein method 'cbf_handle_struct_get_image', argument 1 of type 'cbf_handle_struct *'OOO:cbf_handle_struct_set_tag_rootin method 'cbf_handle_struct_set_tag_root', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_set_tag_root', argument 2 of type 'char const *'in method 'cbf_handle_struct_set_tag_root', argument 3 of type 'char const *'O:cbf_handle_struct_write_widefilein method 'cbf_handle_struct_write_widefile', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_count_rowsin method 'cbf_handle_struct_count_rows', argument 1 of type 'cbf_handle_struct *'OO:cbf_handle_struct_require_datablockin method 'cbf_handle_struct_require_datablock', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_require_datablock', argument 2 of type 'char const *'OOOOOOO:cbf_handle_struct_set_integerarrayin method 'cbf_handle_struct_set_integerarray', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_set_integerarray', argument 2 of type 'unsigned int'in method 'cbf_handle_struct_set_integerarray', argument 3 of type 'int'in method 'cbf_handle_struct_set_integerarray', argument 4 of type 'char *'in method 'cbf_handle_struct_set_integerarray', argument 6 of type 'int'in method 'cbf_handle_struct_set_integerarray', argument 7 of type 'int'in method 'cbf_handle_struct_set_integerarray', argument 8 of type 'int'OO:cbf_handle_struct_new_datablockin method 'cbf_handle_struct_new_datablock', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_new_datablock', argument 2 of type 'char const *'OOOOOOOOO:cbf_handle_struct_set_datestampin method 'cbf_handle_struct_set_datestamp', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_set_datestamp', argument 2 of type 'int'in method 'cbf_handle_struct_set_datestamp', argument 3 of type 'int'in method 'cbf_handle_struct_set_datestamp', argument 4 of type 'int'in method 'cbf_handle_struct_set_datestamp', argument 5 of type 'int'in method 'cbf_handle_struct_set_datestamp', argument 6 of type 'int'in method 'cbf_handle_struct_set_datestamp', argument 7 of type 'double'in method 'cbf_handle_struct_set_datestamp', argument 8 of type 'int'in method 'cbf_handle_struct_set_datestamp', argument 9 of type 'double'O:cbf_handle_struct_next_rowin method 'cbf_handle_struct_next_row', argument 1 of type 'cbf_handle_struct *'OOO:cbf_handle_struct_set_category_rootin method 'cbf_handle_struct_set_category_root', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_set_category_root', argument 2 of type 'char const *'in method 'cbf_handle_struct_set_category_root', argument 3 of type 'char const *'OO:cbf_handle_struct_insert_rowin method 'cbf_handle_struct_insert_row', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_insert_row', argument 2 of type 'unsigned int'OO:cbf_handle_struct_new_columnin method 'cbf_handle_struct_new_column', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_new_column', argument 2 of type 'char const *'O:cbf_handle_struct_get_real_3d_imagein method 'cbf_handle_struct_get_real_3d_image', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_get_integration_timein method 'cbf_handle_struct_get_integration_time', argument 1 of type 'cbf_handle_struct *'O:cbf_handle_struct_set_realarrayin method 'cbf_handle_struct_set_realarray', argument 1 of type 'cbf_handle_struct *'OO:cbf_handle_struct_get_element_idin method 'cbf_handle_struct_get_element_id', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_get_element_id', argument 2 of type 'unsigned int'OO:cbf_handle_struct_set_valuein method 'cbf_handle_struct_set_value', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_set_value', argument 2 of type 'char const *'OO:cbf_handle_struct_require_doublevaluein method 'cbf_handle_struct_require_doublevalue', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_require_doublevalue', argument 3 of type 'double'O:cbf_handle_struct_rewind_datablockin method 'cbf_handle_struct_rewind_datablock', argument 1 of type 'cbf_handle_struct *'OOO:cbf_handle_struct_require_column_valuein method 'cbf_handle_struct_require_column_value', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_require_column_value', argument 2 of type 'char const *'in method 'cbf_handle_struct_require_column_value', argument 3 of type 'char const *'OO:cbf_handle_struct_find_datablockin method 'cbf_handle_struct_find_datablock', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_find_datablock', argument 2 of type 'char const *'O:cbf_handle_struct_reset_saveframein method 'cbf_handle_struct_reset_saveframe', argument 1 of type 'cbf_handle_struct *'OOO:cbf_handle_struct_set_doublevaluein method 'cbf_handle_struct_set_doublevalue', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_set_doublevalue', argument 2 of type 'char const *'in method 'cbf_handle_struct_set_doublevalue', argument 3 of type 'double'OO:cbf_handle_struct_find_categoryin method 'cbf_handle_struct_find_category', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_find_category', argument 2 of type 'char const *'OO:cbf_handle_struct_find_category_rootin method 'cbf_handle_struct_find_category_root', argument 1 of type 'cbf_handle_struct *'in method 'cbf_handle_struct_find_category_root', argument 2 of type 'char const *'O:cbf_handle_struct_set_unit_cellin method 'cbf_handle_struct_set_unit_cell', argument 1 of type 'cbf_handle_struct *'get_local_integer_byte_orderget_local_real_formatget_local_real_byte_ordercbf_positioner_struct_matrix_setcbf_positioner_struct_matrix_getcbf_positioner_struct_axis_setcbf_positioner_struct_axis_getcbf_positioner_struct_axes_setcbf_positioner_struct_axes_getcbf_positioner_struct_matrix_is_valid_setcbf_positioner_struct_matrix_is_valid_getcbf_positioner_struct_axes_are_connected_setcbf_positioner_struct_axes_are_connected_getnew_cbf_positioner_structdelete_cbf_positioner_structcbf_positioner_struct_get_rotation_rangecbf_positioner_struct_rotate_vectorcbf_positioner_struct_get_reciprocalcbf_positioner_struct_get_rotation_axiscbf_positioner_struct_swigregistercbf_detector_struct_positioner_setcbf_detector_struct_positioner_getcbf_detector_struct_displacement_setcbf_detector_struct_displacement_getcbf_detector_struct_increment_setcbf_detector_struct_increment_getcbf_detector_struct_axes_setcbf_detector_struct_axes_getcbf_detector_struct_index_setcbf_detector_struct_index_getnew_cbf_detector_structdelete_cbf_detector_structcbf_detector_struct_get_pixel_normalcbf_detector_struct_get_pixel_areacbf_detector_struct_get_detector_distancecbf_detector_struct_get_detector_normalcbf_detector_struct_get_inferred_pixel_sizecbf_detector_struct_get_pixel_coordinatescbf_detector_struct_get_beam_centercbf_detector_struct_swigregistercbf_handle_struct_node_setcbf_handle_struct_node_getcbf_handle_struct_row_setcbf_handle_struct_row_getcbf_handle_struct_search_row_setcbf_handle_struct_search_row_getnew_cbf_handle_structdelete_cbf_handle_structcbf_handle_struct_select_datablockcbf_handle_struct_force_new_datablockcbf_handle_struct_reset_datablockscbf_handle_struct_set_tag_categorycbf_handle_struct_row_numbercbf_handle_struct_set_imagecbf_handle_struct_set_bin_sizescbf_handle_struct_new_rowcbf_handle_struct_rewind_saveframecbf_handle_struct_get_realarrayparameterscbf_handle_struct_force_new_categorycbf_handle_struct_force_new_saveframecbf_handle_struct_count_datablockscbf_handle_struct_find_rowcbf_handle_struct_select_columncbf_handle_struct_construct_detectorcbf_handle_struct_rewind_columncbf_handle_struct_require_column_doublevaluecbf_handle_struct_get_datestampcbf_handle_struct_get_integervaluecbf_handle_struct_get_crystal_idcbf_handle_struct_get_doublevaluecbf_handle_struct_get_unit_cellcbf_handle_struct_remove_columncbf_handle_struct_rewind_blockitemcbf_handle_struct_get_valuecbf_handle_struct_set_reciprocal_cellcbf_handle_struct_count_categoriescbf_handle_struct_read_widefilecbf_handle_struct_set_wavelengthcbf_handle_struct_get_diffrn_idcbf_handle_struct_get_dictionarycbf_handle_struct_get_polarizationcbf_handle_struct_select_categorycbf_handle_struct_read_filecbf_handle_struct_datablock_namecbf_handle_struct_set_realarray_wdimscbf_handle_struct_rewind_rowcbf_handle_struct_get_axis_settingcbf_handle_struct_require_columncbf_handle_struct_get_timestampcbf_handle_struct_find_nextrowcbf_handle_struct_require_tag_rootcbf_handle_struct_reset_datablockcbf_handle_struct_require_integervaluecbf_handle_struct_get_integerarrayparameterscbf_handle_struct_write_filecbf_handle_struct_set_divergencecbf_handle_struct_remove_datablockcbf_handle_struct_count_elementscbf_handle_struct_get_pixel_sizecbf_handle_struct_next_categorycbf_handle_struct_set_diffrn_idcbf_handle_struct_set_timestampcbf_handle_struct_get_orientation_matrixcbf_handle_struct_get_divergencecbf_handle_struct_rewind_categorycbf_handle_struct_read_templatecbf_handle_struct_select_rowcbf_handle_struct_count_columnscbf_handle_struct_get_integerarrayparameters_wdimscbf_handle_struct_get_gaincbf_handle_struct_new_saveframecbf_handle_struct_set_polarizationcbf_handle_struct_set_real_3d_imagecbf_handle_struct_delete_rowcbf_handle_struct_column_namecbf_handle_struct_remove_saveframecbf_handle_struct_require_valuecbf_handle_struct_require_column_integervaluecbf_handle_struct_set_pixel_sizecbf_handle_struct_next_columncbf_handle_struct_get_realarraycbf_handle_struct_get_bin_sizescbf_handle_struct_reset_categorycbf_handle_struct_construct_goniometercbf_handle_struct_set_datablocknamecbf_handle_struct_set_crystal_idcbf_handle_struct_get_integerarray_as_stringcbf_handle_struct_set_3d_imagecbf_handle_struct_set_dictionarycbf_handle_struct_find_tag_categorycbf_handle_struct_set_typeofvaluecbf_handle_struct_set_integerarray_wdimscbf_handle_struct_set_integration_timecbf_handle_struct_set_axis_settingcbf_handle_struct_get_real_imagecbf_handle_struct_get_overloadcbf_handle_struct_get_wavelengthcbf_handle_struct_next_datablockcbf_handle_struct_get_realarrayparameters_wdimscbf_handle_struct_set_orientation_matrixcbf_handle_struct_new_categorycbf_handle_struct_set_gaincbf_handle_struct_find_columncbf_handle_struct_remove_categorycbf_handle_struct_require_categorycbf_handle_struct_get_reciprocal_cellcbf_handle_struct_get_3d_image_sizecbf_handle_struct_find_tag_rootcbf_handle_struct_require_category_rootcbf_handle_struct_set_integervaluecbf_handle_struct_category_namecbf_handle_struct_get_typeofvaluecbf_handle_struct_set_real_imagecbf_handle_struct_get_3d_imagecbf_handle_struct_remove_rowcbf_handle_struct_set_overloadcbf_handle_struct_get_image_sizecbf_handle_struct_get_imagecbf_handle_struct_set_tag_rootcbf_handle_struct_write_widefilecbf_handle_struct_count_rowscbf_handle_struct_require_datablockcbf_handle_struct_set_integerarraycbf_handle_struct_new_datablockcbf_handle_struct_set_datestampcbf_handle_struct_next_rowcbf_handle_struct_set_category_rootcbf_handle_struct_insert_rowcbf_handle_struct_new_columncbf_handle_struct_get_real_3d_imagecbf_handle_struct_get_integration_timecbf_handle_struct_set_realarraycbf_handle_struct_get_element_idcbf_handle_struct_set_valuecbf_handle_struct_require_doublevaluecbf_handle_struct_rewind_datablockcbf_handle_struct_require_column_valuecbf_handle_struct_find_datablockcbf_handle_struct_reset_saveframecbf_handle_struct_set_doublevaluecbf_handle_struct_find_categorycbf_handle_struct_find_category_rootcbf_handle_struct_set_unit_cellcbf_handle_struct_swigregister_p_CBF_NODETYPEenum CBF_NODETYPE *|CBF_NODETYPE *_p_a_4__doubledouble (*)[4]_p_cbf_axis_structcbf_axis_struct *_p_cbf_detector_structcbf_detector_struct *|cbf_detector_p_cbf_handle_structcbf_handle_struct *|handle *_p_cbf_nodecbf_node *_p_cbf_positionercbf_positioner *_p_cbf_positioner_structcbf_positioner_struct *|cbf_goniometerchar *_p_doubledouble *_p_intint *_p_p_charchar **_p_size_tsize_t *_p_voidvoid *(, )Swig global variables %s Unknown C global variableswigvarlink_pycbfCBF_INTEGERCBF_FLOATCBF_CANONICALCBF_PACKEDCBF_BYTE_OFFSETCBF_PREDICTORCBF_NONEPLAIN_HEADERSMIME_HEADERSMSG_NODIGESTMSG_DIGESTMSG_DIGESTNOWHDR_DEFAULTMIME_NOHEADERSCBFCIFENC_NONEENC_BASE64ENC_QPENC_BASE10ENC_BASE16ENC_BASE8ENC_FORWARDENC_BACKWARDENC_CRTERMENC_LFTERMENC_DEFAULTCBF_UNDEFINEDCBF_LINKCBF_ROOTCBF_DATABLOCKCBF_SAVEFRAMECBF_CATEGORYCBF_COLUMNdiffrniddiffrn_sourcediffrn_radiationdiffrn_detectordiffrn_measurementdiffrn_orient_matrixdiffrn_idcellentry_idcrystal_idwavelength_iddiffrn_radiation_wavelengthwavelength%-.15gwt1.0polarizn_source_ratiopolarizn_source_normdiv_x_sourcediv_y_sourcediv_x_y_sourcediffrn_detector_elementdetector_iddiffrn_data_framediffrn_frame_datadetector_element_idarray_idarray_structure_listprecedenceindexarray_element_sizesizezDü©ñÒMbP?array_intensitiespixel_slow_bin_sizepixel_fast_bin_sizegaingain_esdoverloaddiffrn_scan_frameintegration_timepBaEÀ¨GŒ"ÒI.öJÀ¨Gdate%d-%d-%d%*c%d:%d:%lf%c%d:%d +-pBÀ¨G.öJ$ÒIYü£J8@€–@%04d-%02d-%02dT%02d:%02d:%0*.*f%c%02d:%02dpB?map_segmentmask_array_idaxissystemvector[1]vector[2]vector[3]CELL_A_AXISwordfractionalCELL_B_AXISCELL_C_AXISarray_structure_list_axisdimensiondirectionaxis_idincreasingfract_displacementfract_displacement_incrementð?decreasingarray_databinary_iddatalittle_endianarray_structureencoding_typesigned %d-bit integerunsigned %d-bit integersigned %d-bit real IEEEdblqcompression_typenonecanonicalpackedpacked_v2byte_offsetspredictor.nullcompression_type_flaguncorrelated_sectionsflatbyte_ordertypeoffset[1]offset[2]offset[3]diffrn_scan_frame_axisdisplacementdiffrn_scan_axisdisplacement_incrementangleangle_incrementreference_displacementreference_angledisplacement_startdisplacement_rangeangle_startangle_rangedepends_on9R¢Fß?diffrn_measurement_axismeasurement_idð?axis_set_iddiffrn_detector_axisDIFFRN_IDELEMENT_XELEMENT_Y%-fíµ ÷ư>reference_center_slowreference_center_fastíµ ÷ư>??length_alength_blength_cangle_alphaangle_betaangle_gammalength_a_esdlength_b_esdlength_c_esdangle_alpha_esdangle_beta_esdangle_gamma_esdreciprocal_length_areciprocal_length_breciprocal_length_creciprocal_angle_alphareciprocal_angle_betareciprocal_angle_gammareciprocal_length_a_esdreciprocal_length_b_esdreciprocal_length_c_esdreciprocal_angle_alpha_esdreciprocal_angle_beta_esdreciprocal_angle_gamma_esd4B4BUB[1][1]UB[1][2]UB[1][3]UB[2][1]UB[2][2]UB[2][3]UB[3][1]UB[3][2]UB[3][3]bnry%d%-.15glittle_endianerrorwarningCBFlib: %s -- %s CBFlib: memory allocation error CBFlib: %s input line %d -- %s CBFlib: %s input line %d (%d) -- %s CBFlib: warning -- %s CBFlib: error -- %s (null)%.15g_name_item.name_item_enumeration.value_enumeration_item_range.minimumitems_enumerationsnamemaximumclosed_rangeopen_rangevaluevalue_typeitemcategory_id_categorymandatory_code_type_item_type.code_enumeration_default_item_default.value_item_aliases.alias_nameitems_enumeration_range_item_linked.parent_name_item_link_parentparent_name_list_link_parentchild_name_list_link_child_category.idcategoriesidno_list_reference_category_key.nameyes _category_aliases.alias_nameitem_aliasesitem_aliasitem_roottype_codedefault_value_item.category_idinvaliddictionary: invalid range of values for %sparentcategory_aliasescategory_aliascategory_rootkeyid(hash_next)_items.nameCBF_wide_refcountsDB_wide_refcountsDBcat_wide_refcountsSF_wide_refcountsSFcat_wide_refcountscbf_dictionarycategory_aliases(hash_table)category_root(hash_next)category_alias(hash_next)item_aliases(hash_table)item_root(hash_next)item_alias(hash_next)categories(hash_table)items(hash_table)name(hash_next)category_id(hash_next)sub_category_iditems_enumerations(hash_table)_items.parent inconsistent data type %s for %sCBFLIB_DEBUG_category_aliases.alias_idalias_idroot_iddictionaryalias_nameroot_namecatgeory_idrequired parent tag %s for %s in %s not givenrequired tag %s in %s not giventextbinary_items_enumerations.namenumbintitem name %s appears more than once in a save frame categoryno categories in save frameincomplete row in category %sno rows in castegory %sitem name longer than 75 charactersdata block (null) ends with no contentno columns in category(none)category name + column name longer than 75 charactersitem category name %s inconsistent with category %sdata block %s ends with no contentitem name %s not found in the dictionarydictionary item %s, category name %s inconsistent with %sitem name %s appears more than once in a data block categoryuchar3uchar1charuchacodeucodlineulinanyatcophonemaifaxfloasymoyyyy-item name %s appears more than once in a data block %s type conflicts with dictionary type %sitem name %s appears more than once in a save frame %s value out of dictionary range.no data blocks foundÀ?output line %u(%u) folded;\ \ \ ; ; DATA_ LOOP_?.' ' ;" " text field contains terminator, will be folded on output data_ data_ save_(none) save_(none)_(null)output line %u(%u) column name too long or invalid converted to "%s"]_esd loop_ [1][1]_esd###CBF: VERSION 1.5 # CBF file written by CBFlib v0.7.7 save_ # CIF file written by CBFlib v0.7.7 unknownlittle_endianbig_endian %x %p %lx %lx %d %24s %x %d %d %14s %lu %lu %lu %lu %lu %u------------------------%x %p %lx %lx %1d %24s %x %d %d %14s %ld %ld %ld %ld %ld %uinput line %u over size limit !"#$%&')(*+-(*+-()*+- +, +-...(+-.,+-..+,+-...(+-.,+-..ÿ  !/"5ôôôôôôôôôôôôôôôôôôôôôôôôJûõ  !!!"###$$%%&&&''()*+,-... >?=B@! 4*.ACDE"#%'$&()+-,/0125683:79;<%+<.3B-9)=LAC#(IM&,84þ:þ>HDJN67;?@EFGKOP012'012012-$*   ÿ  ÿÿÿÿ ÿÿÿÿ ÿ ÿ   ôôAA6ôE8@@,ý8@E8@@,ý8@ôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôôredundant "loop_" syntax errordata name with no valuevalue without tagloop value without tagno data blockprior save frame not terminatedempty data block nameduplicate data block namesave frame not terminatedparser stack overflow¬¬ +  ª  R 9 Zž Zå   ££¾ wwÞ E¸ œ ^^>ã‰0T «O¡ ssw^ Þ E¸ œ ^>Š ö  T «O¡¬ââââââââbig_endianlittle_endianContent-Type:Content-Transfer-Encoding:Content-MD5:X-Binary-Size:X-Binary-ID:X-Binary-Element-Type:X-Binary-Element-Byte-Order:X-Binary-Size-Fastest-Dimension:X-Binary-Size-Second-Dimension:X-Binary-Size-Third-Dimension:X-Binary-Size-Padding:X-Binary-Number-of-Elements:--CIF-BINARY-FORMAT-SECTION--BinaryQuoted-PrintableBase64X-Base32kX-Base8X-Base10X-Base167bit8bitapplication/signedunsigned%d-%nbitintegerimage/text/audio/video/realieeeconversionsx-cbf_packedx-cbf_packed_v2x-cbf_canonicalx-cbf_byte_offsetx-cbf_predictoruncorrelated_sectionsflatcomplexQôÔV÷Ú½ u ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream Content-Type: application/octet-stream; conversions="x-CBF_UNKNOWN" Content-Transfer-Encoding: X-BASE16 X-Binary-Size: %lu X-Binary-ID: %d X-Binary-Element-Type: "signed %d-bit integer" big_endianBIG_ENDIANX-Binary-Element-Byte-Order: %s X-Binary-Size-Third-Dimension: %ld X-Binary-Size-Padding: %ld --CIF-BINARY-FORMAT-SECTION---- ; conversions="x-CBF_PACKED"; "flat"START OF BINARY SECTION conversions="x-CBF_PACKED_V2" END OF BINARY SECTION ; Content-Transfer-Encoding: QUOTED-PRINTABLE Content-Transfer-Encoding: BASE64 Content-Transfer-Encoding: X-BASE32K conversions="x-CBF_BYTE_OFFSET" Content-Transfer-Encoding: X-BASE8 conversions="x-CBF_CANONICAL" conversions="x-CBF_PREDICTOR" Content-Transfer-Encoding: BINARY Content-Transfer-Encoding: X-BASE10 X-Binary-Element-Type: "unsigned %d-bit integer" X-Binary-Element-Type: "signed %d-bit real IEEE" ; "uncorrelated_sections"X-Binary-Size-Second-Dimension: %ld X-Binary-Size-Fastest-Dimension: %ld X-Binary-Number-of-Elements: %ld Content-MD5: %24s little_endianLITTLE_ENDIAN= ==ApA# Hexadecimal encoding, byte %lu, byte order 1234... # %lX%1u> %lo, byte order ...4321 # # # Octal encoding%lu< # Decimal encodingThe file given for decoding was not correctly encoded!invalid space characterended before end of double-quoted stringinvalid characterDATA_SAVE_LOOP_category name exceeds 73 charactersover line size limitdata block name exceeds 75 characterssave frame name exceeds 75 charactersinvalid character in text field --CIF-BINARY-FORMAT-SECTION--little_endiantext field terminated by EOF"loop_" must be followed by white space%lx %p %lx %lx %d %s %x %d %d %s %ld %ld %ld %ld %ld %uended before end of single-quoted stringÜ…C… …Ü…Õ„Ü…Ü…Ü…ƒƒÜ…Ü…Ü…Ü…Ü…Ü…Ü…yÜ…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…yÜ…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…Ü…yieee *** Predictor-Huffman Algorithm Not Implemented Yet -- Abort *** ieeeA Aieee-LIBGCCW32-EH-2-SJLJ-GTHR-MINGW32w32_sharedptr->size == sizeof(W32_EH_SHARED)%s:%u: failed assertion `%s' ../../gcc/gcc/config/i386/w32-shared-ptr.cGetAtomNameA (atom, s, sizeof(s)) != 0‘šeF2à(à,à0àwS=à_pycbf.pydinit_pycbf|ðŒÿÜòÌñ¨ÿ,ôàñ¼ÿ@ôìñ¤LôÐò´0õ8õLõ`õtõˆõ õ¸õÌõÜõðõöö,ö<öLö\öpö„ö˜ö°öÄöÔöèöüö÷(÷@÷T÷h÷|÷÷¬÷À÷Ø÷è÷ü÷ø ø4øDøTødøxøˆøœø¬øÄøàøøøù ù4ùDùTùtù„ù ù´ùÐùàùôùúú,úHú`útúŒú¤úÄúÔúäúøúûû,û<ûPûhû€û û¸ûÌûØûäûôûüû üü$ü,ü4ü<üDüLüTü\üdüpü|ü„üŒü”ü ü¨ü°ü¸üÀüÈüÐüÜüèüôüý ýý ý,ý8ýDýPýXý`ýlýtý€ýŒý˜ý¤ý°ý¼ýÈýÔýàýìýøýþþþ$þ0þ<þ8õLõ`õtõˆõ õ¸õÌõÜõðõöö,ö<öLö\öpö„ö˜ö°öÄöÔöèöüö÷(÷@÷T÷h÷|÷÷¬÷À÷Ø÷è÷ü÷ø ø4øDøTødøxøˆøœø¬øÄøàøøøù ù4ùDùTùtù„ù ù´ùÐùàùôùúú,úHú`útúŒú¤úÄúÔúäúøúûû,û<ûPûhû€û û¸ûÌûØûäûôûüû üü$ü,ü4ü<üDüLüTü\üdüpü|ü„üŒü”ü ü¨ü°ü¸üÀüÈüÐüÜüèüôüý ýý ý,ý8ýDýPýXý`ýlýtý€ýŒý˜ý¤ý°ý¼ýÈýÔýàýìýøýþþþ$þ0þ<þPyArg_ParseTuplePyArg_UnpackTuplePyBool_FromLongPyCFunction_TypePyCObject_AsVoidPtrPyCObject_FromVoidPtrPyCObject_Import*PyClass_TypeMPyDict_GetItemSPyDict_NewUPyDict_SetItemVPyDict_SetItemString_PyErr_ClearbPyErr_FetchcPyErr_FormathPyErr_OccurredzPyErr_SetObject{PyErr_SetStringPyExc_AttributeError¡PyExc_Exception¤PyExc_IOError§PyExc_IndexError«PyExc_MemoryError­PyExc_NameError°PyExc_OverflowError´PyExc_RuntimeError¸PyExc_SyntaxErrorºPyExc_SystemError½PyExc_TypeErrorÄPyExc_ValueErrorÇPyExc_ZeroDivisionErrorÓPyFloat_AsDouble×PyFloat_FromDoubleÙPyFloat_TypePyInstance_NewRawPyInstance_TypePyInt_AsLongPyInt_FromLong PyInt_TypePyList_AppendPyList_NewPyList_SetItemPyList_Type PyLong_AsDouble!PyLong_AsLong#PyLong_AsUnsignedLong-PyLong_FromUnsignedLong/PyLong_FromVoidPtr0PyLong_TypeNPyModule_AddObjectPPyModule_GetDictPyOS_snprintf—PyObject_Call™PyObject_CallFunctionObjArgs¤PyObject_Free¨PyObject_GenericGetAttrªPyObject_GetAttr«PyObject_GetAttrString±PyObject_InitµPyObject_IsTrue·PyObject_MallocÃPyObject_Str PyString_AsString PyString_AsStringAndSize PyString_ConcatAndDelPyString_FormatPyString_FromFormatPyString_FromStringPyString_FromStringAndSizePyString_TypeJPyTuple_NewLPyTuple_SetItemNPyTuple_TypeQPyType_IsSubtypeSPyType_Type±Py_BuildValueÏPy_InitModule4ù_PyInstance_Lookup _PyObject_GetDictPtr._PyWeakref_CallableProxyType1_PyWeakref_ProxyType:_Py_NoneStructAddAtomA¯FindAtomAÜGetAtomNameAZ_swab8__dllonexit½_errnoÏ_filbuf_iobVatan2XatofYatoiZatol]ceil`coseexithfclosekfflushlfgetcqfloorsfopentfprintfufputcvfputsyfreadzfree~fseek€ftell‚fwrite†getenvisdigitisgraph•isspace«log10­malloc³memcpy´memmoveµmemsetºprintfÀqsortÌsinÎsprintfÏsqrtÑsscanfÓstrchrÔstrcmpÖstrcpyÚstrlenÜstrncmpÝstrncpyÞstrpbrkàstrspnástrstrâstrtodästrtolåstrtoulìtimeítmpfileðtoupperóungetcabortððððððððððððððððððððððððððððððððððððððððððððððððððððððððððððððððððððððððððððððððððpython24.dllðððKERNEL32.dll(ðmsvcrt.dll<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ð<ðmsvcr71.dllPðmsvcrt.dllÌC0M0q0Œ0¢0Í0Ü0ò01,1b1l1’1œ1N6[6}7m8Ú8ß8è8ñ8ú89 999'90999B9l9Š9œ9¤9¸9È9Ô9::1:`:ƒ:¿:Þ:å:õ:;;,;;ˆ;›; ;«;¾;Å;Ò;Þ;ã;î; <<(<-<8–>¼>Ì>ß>$???x?‡??Á?÷? Àf0Ÿ0¬0±0%1y1ž1ß1¤2°2Å2Ù2 393W3a33‰3“3Å3Ê3ø3>4%5/545:5C5k5x5Ò5"6¸6¾6Ð6Ö62787H7´7Á7Æ7ö7)8K8„8˜8¢8¬8¶8À8Å8ß8 999!9*9^9k9©9ë9L:V:\:a:f:–:Ä:Ø:è: ;;";S;q;{;¢;@=O=Y=ë=0>8?G?X?u?}?˜?¨?ç?ù?0À00&0>0€0h1s1z1€1…1‹1•1›1¤1-242:2D2P2o2x2 2©2®2³2Ø2ê2÷2'3=33½3Ó3æ3õ3444,484i44˜4î4555*5<5A5L5n5s5~5ˆ55˜5Þ5ï5ù56 666)61696@6K6V6^6f6m6x6ƒ6‹6“6š6¥6°6¸6À6Ç6Ò6Ý6å6í6ô6ÿ6 777!7,777?7G7N7Y7d7l7t7{7†7‘7™7¡7¨7³7¾7Æ7Î7Õ7à7ë7ó7û78 88 8(8/8:8E8M8U8\8g8r8z8‚8‰8”8Ÿ8§8¯8¶8Á8Ì8Ô8Ü8ã8î8ù89 999&9.969=9Z9k9v9~9…99•9ž9¶9Ñ9ñ9ø9::+:2:?:P:j:q:~:‹:”:®:Ô:Û:è:õ:;;*;7;?;V;};„;‘;¢;´;»;È;Õ;Ý;ô;?<`<Ž<ß<7=l=w=˜=Ó=>&>S>¬>ç>?3?N?m??”?¡?À?@ð0å0ý0#1B1P1_1{1“1Ç1þ12<2^2}2£2¾2ë2<3[3}3Ÿ3­3É3è3 44;4I4l4‹4­4Ö4õ455=5\5j5†5»5Ú56'6M6h6Ž6Þ677T77™7¸7è788T8s8è899%9?9^9}9‹9¼9Û9: :/:N:i::¿:ì:;;;:;Y;{;š;ö;?2>_>~>–>µ>À>Ï>ù>"?D?c?…?“?¢?¾?ä?Pô040^0i0Œ0®0ú01%1}1•1»1Ú1ù12/2:2d2†2¬2Ä2ñ23+3Q3p3–3¤3º3Æ3Ù3è3ø3ý34f4Š4–4©4¸4È4Í4Ø465Z5f5y5ˆ5˜55¨56U6a6~6´6Ù67_7…7È7Ô7í7#8:8‹8—8´8ê8 9B99™9²9è9:M:Y:v:¬:;O;[;t;ª;Ç;Ò; <<6C>Ž>š>³>é>??%?4?E?U?Z?e?y?®?º?×?`Ü 0020B0G0R0•0¡0¾0ô01$14191D1k1ˆ1¶1Ó1e2q2Ž2Ä23K33Õ3è3%454:4E4l4‰4·4Ô45 5Æ5Ò5ï5%6g6¬6ñ6977”7Þ7î7ó7þ7%8B8p88¼8Ù869B9_9•9¨9Ì9Ü9á9ì9:0:^:{:ª:Ç: ;;3;z;†;£;Ù;þ;4;>t>µ>Á>Ú>?-?{?‡?¤?Ú?ÿ?pô50n0¯0»0Ô0 1'1o1{1˜1Î1%2q2}2–2Ì2é2ô263B3_3•3º3ð3)4j4v44Å4â455 515A5F5Q5e5š5¦5Ã5ù5 66.636>66©6Æ6ü6>7ƒ7–7Å7Õ7Ú7å7 8)8W8t8£8À869B9_9•9×9:/:W:g:l:w:ž:»:é:;Y;e;‚;¸;Ë;ä;ô;ù;<(,>>œ>¹>ï>1?D?a?q?v??¥?Â?€ô40@0]0“0Õ01-1\1l1q1|1£1À1î1 2:2W2±2½2Ú23#3N3^3c3n3•3²3à3ý3,4I4{4˜4Û4ç45R5^5{5±5Ó5 6S6_6x6®6Ê677:7p7¯7ú788U8n8©8µ8Ò89G9’9ž9·9í9::):8:I:Y:^:i:}:²:¾:Û:;!;6;F;K;V;Ÿ;«;È;þ;@S>p>¦>¶>Ë>Û>à>ë>_?k?ˆ?¾?0`0p000¢0­0@1L1i1Ÿ1¯1Ä1Ô1Ù1ä1ø12/2;2X2Ž2ž2³2Ã2È2Ó2 3363l3|3‘3¡3¦3±3ë3÷34J4Z4o44„44É4Õ4ò4(585M5]5b5m5°5¼5Ù56"6M6]6b6m6”6±6ß6ü6+7H7z7—788.8d8µ8Å8Þ8î8ó8þ8…9‘9®9ä95:E:^:n:s:~:è:ô:;G;W;l;|;;Œ; ;«;ô;<>0>@>E>P>>©>Æ>ü>>?N?i?y?~?‰??Ù?å? $080H0]0m0r0}0ç0ó01F1—1Ù1ì1 22"2-2T2q2ð2ü23O3b3¢3²3·3Â3é3444Q4€44Ï4ì45;5‚5Ÿ5Ñ5î5?6K6h6ž6®6Ã6Ó6Ø6ã6ó6!7-7J7€7“7¨7¸7½7È7&8`8l8‰8¿8Ï8ä8ö8û899B9N9k9¡9±9Æ9Ö9Û9æ9 :,:I:::¤:´:¹:Ä:þ: ;';];m;‚;’;—;¢;²;à;ì; &>\>l>>‘>–>¡>µ>À>ì>ø>?K?[?p?€?…??Ù?å?°080z0Š0£0³0¸0Ã011,1b1u1Š1š1Ÿ1ª12B2N2k2¡2±2È2Ø2Ý2è2ü2=3I3f3œ3¯3Ì3Ü3á3ì3404^4{4Ø4ä4575y5‰5¢5²5·5Â5,686U6‹6Ü67.7K7[7`7k7Ø7ä7878J8_8o8t88Ý89#9@9v9†9›9«9°9»9õ9::T:d:y:‰:Ž:™:ø:;!;W;¨;»;Ü;ì;ñ;ü;#<@ >>Š>–>³>é>ü>?)?.?9?`?}?«?È?Àì30?0\0’0ã0ó0 11!1,1´1À1Ý12d2w22 2¥2°23w3ƒ3 3Ö3æ3û3 444h4t4‘4Ç4 5595I5N5Y5}5š5ð5ü56O6b6©6¹6¾6É6ð6 7;7X7‡7¤7Ö7ó7%8B8t8‘8Ã8à89/9É9Õ9ò9(:|:¾:;B;R;z;Š;;š;1<=P>`>u>…>Š>•>Ï>Û>ø>.?>?S?c?h?s?‡?’?à?ì?Ðü 0?00Ã0Ö0÷01 11;1X1¦1²1Ï122*2:2?2J2¡2­2Ê23Q3a3z3Š33š304<4Y44Ñ45X5h5Œ5œ5¡5¬5ô566S6f6´6Ä6É6Ô6û67F7c7’7¯7á7þ708M88œ8Î8ë89:9l9‰9ã9ï9 :B:U:y:‰:Ž:™:À:Ý: ;(;W;t;Å;Ñ;î;$<4>>[>‘>Ó>ã>ü> ???Z?f?ƒ?¹?É?Þ?î?ó?þ?àø00I0U0r0¨0¸0Í0Ý0â0í0>1J1g11ß1ò12#2(232Z2w2¥2Â2-393V3Œ3Ý3í3444&4­4¹4Ö4 5N5“5£5Ã5Ó5Ø5ã5!6-6J6€66¥6µ6º6Å67777m7¯7¿7Ø7è7í7ø788D8a8—8ª8¿8Ï8Ô8ß8=9w9ƒ9 9Ö9æ9û9 :::s::œ:Ò:#;6;O;_;d;o;Ð;fŸ>¼>ò>4?v?¸?È?é?ù?þ?ð 0I0U0r0¨0¸0Í0Ý0â0í0'131P1†1–1«1»1À1Ë122.2d2t2‰2™2ž2©2ã2ï2 3B3R3g3w3|3‡3Á3Í3ê3 404G4W4\4g4{4Ð4Ü4ù4/5€55©5¹5¾5É5P6\6y6¯677)797>7I7À7Ì7é7828R8b8g8r8Ç89(9E9{9‹9 9°9µ9À9::9:o:”:Ê:Ú:ó:;;;o;{;˜;Î;<2(>8>=>H>²>¾>Û>?!?6?F?K?V?Ÿ?«?È?þ?ä@0P0i0y0~0‰01 1*1`1±1ó182H2l2|22Œ2÷23 3V3f3{3‹33›3è3ô34G4‰4œ4¹4É4Î4Ù4ý45g5s55Æ5Ö5ë5ý56 66I6U6r6¨6¸6Í6Ý6â6í6'737P7†7–7«7»7À7Ë7‡8“8°8æ8(9p9¸9:H::Ø: ;h;{;ä;ô;ù;P>’>Ô>?)?M?]?b?m?É?Õ?ò?(0y0‰0¢0²0·0Â0,181U1‹1›1°1À1Å1Ð1'232P2†2×2ç2333 3Š3–3³3é3ù344#4.4h4t4‘4Ç4×4ì4ü45 5d5p55Ã56'6@6P6U6`6Á6E7Q7n7¤7õ78!81868A8¢89#9@9v9¸9È9á9ñ9ö9:A:M:j: :³:È:Ø:Ý:è:F;‚;Ž;«;á;ô; <<<)<‡<Á<Í<ê< =0=E=U=Z=e=Ÿ=«=È=þ=>#>3>8>C>}>‰>¦>Ü>ì>???!?y?…?¢?Ø? Ø0\0l0‰0™0ž0©0ÿ0 1(1^1 1³1Ô1ä1é1ô1282f2ƒ2Ñ2Ý2ú203@3U3e3j3u3é3õ34H4™4ê4ú45'5,575Ê5Ö5ó5)696N6^6c6n6¨6´6Ñ677,7<7A7L7`7k7´7À7Ý78d8t888¢8­8ƒ99¬9â9':l:¿:;J;Œ;Ÿ;Ü;ì;ñ;ü;…<‘<®<ä<5=E=^=n=s=~=^>j>‡>½>ÿ>D?‰?Î?0ü0U0š0Ü0ì001@1E1P1“1Ÿ1¼1ò122'2,272«2·2Ô2 3[3¬3¼3Ù3é3î3ù3›4§4Ä4ú4<5L5e5u5z5…5à5ì5 6?66 6¹6É6Î6Ù6C7O7l7¢7²7Ç7×7Ü7ç7&828O8…8˜8±8Á8Æ8Ñ8õ89_9k9ˆ9¾9Î9ã9ó9ø9:M:Y:v:¬:î:;;*;/;:;˜;ï;û;>6>F>K>V>z>—>ä>ð> ?C?S?h?x?}?ˆ?ü?@(0%0[0¬0ý01-1=1B1M1®1Y2e2‚2¸2 3323B3G3R3¼3È3å34+4@4P4U4`4Æ4Ò4ï4%5v5¸5È5å5õ5ú566™6¶6ì6=7M7f7v7{7†78878m8¾8Ñ8ê8ú8ÿ8 9k9Ñ9Ý9ú90:@:U:e:j:u:¡:­:Ê:î:÷:û:;; ;;&;9;R;Y;f;x;|;ƒ;—;œ;¯;È;Ó;í;ñ;<<¨>´>¹>Ä>?&?+?6?P?‰??§?±?»?Å?Ï?Ö?é?ó?ø?þ?P0/0<0Ñ0Þ0ã0”1ø1‚3Š3’3™3¾3Å3Ë3Ô3ê3ÿ3 4 4,4A4M4b4n4ƒ44¤4°4Å4Ñ4æ4ò455(545I5U5j5v5‹5—5¬5¸5Í5Ù5î5ú56606<6Q6]6r6~6“6Ÿ6´6À6Õ6á6ö677#787D7Y7e7z7†7›7§7¼7È7Ý7é7þ7 88+8@8L8¯8Å8þ89X9r9 9¤9ª9²9×9: ::/:}:“:Ì:â:4;N;y;;º;ó; <@+>A>^>›>µ>ä>?:?Œ?¦?Ù?ö?`Ä 0)0?0\0¤0¾0ñ0121°1Ê1ý1,2B2q2Þ2ø2+3V3l3í344B4©4Ã4é4%5Y5–5À5!6P6x6‰6ú67:7v7ª7ç7ÿ78L88š8¦8Ï8î8%9@9L9n9¯9â9:(:4:¯:Å:ð:;t;Ž;¹;Ö;ì; }>“>¾>Û> ? ?r?ˆ?³?Ü?å?ù?pT 0Ð0ã0‚1ˆ1Æ1à1§2Í2ê2H3(4.474I4b5“5Ÿ5Ð5Ù5®6'7œ78$8=8/>I>e>>ê>?f?€?š?´?Î?è?€Ð0,0F0`0z0”0®0â01J1d1Ž1¨1Â1Ü1ö12D2x2¬2Æ2ð2 3$3>3X3r3¦3À3ô3(4B4\4v44ª4Ä4Þ45;5o5‰5¼5ð5 6$6>6X6‚6µ6é67P7j7„7ž7¸7â78I8|8°8Ê8ä8þ8929L9f9€9ª9Ä9Þ9 ::/:X:d:~:˜:Â:Ü:ö:!;-;G;p;|;–;°;Ú;ô;<9“>Ì>"?€? Ä0L0g0Õ0ð0!1@1_1Œ1§12.2N2i2‰2¤2Ä2ß2ÿ2373R3o3Š3»3Ö3ñ3"4=4T4k4‚4é45656!6P6{6¦6ß6ù6(7S7~7 8$8T8„8ž8Î89 9P9|9’9º9V:p:¤:Ì:;;;U;…;­;ë;)1>K>{>œ>¶>×>ñ>?1?K?{?œ?¶?Ñ?ë?°D050V0l0‰0Ÿ0¼031M1}1ž1¸1Ò12#2B2\2Œ2­2Ã2Ù233„7ž7Î7d9Í9<ï?Àp 0<0ˆ0¢0¶012„45(5[5®5È5õ5?6r6°6Ê6ý607c7 7Ó7898¨8Â8Ö8;9‚;£;½;o>£>½>í>?:?t?·?Ð|070q0´031M1a1u1Ú1:4T4‡4Ú4ô4!5k5ž5Ü5ö5)6\6p6¼6ù6,7_7s7¦78/8C8¨8ï:;*;‚;Ü;ö;#*>Z>t>§>á>õ>;?ˆ?»?õ?àL 0O0Î0è0ü01u1“7°7Î7>8—8´8Ò8>99z;”;¯;‚?¿?ü?ð¬d1¡1Þ1–3Þ34@4q4¢4Ó4 5:5k5œ5É5ö5Q6}6à677;7U7v77±7Ë7ì78'8I8i8ƒ8¤8¾8ß8ù8909M9c9€9Â9 :;:l::Î:ÿ:5;f;—;È;õ;"<}<©< =,=F=g==¢=¼=Ý=÷=>2>S>u>•>¯>Ð>ê> ?%?F?\?y??¬?ì?H¶0w3«3Û34A4t4§4Ú4505—5Ã5&6F6`66›6¼6Ö6÷6727L7m7‡7¨7¾7Û7ñ78Î808¾1Â2j4":";£<­<´<½<-=‹=•=œ=¥=Ô=Þ=å=î=>'>B>W>?@-1x1ˆ1˜1:P”›0°0'1E1a1À1M2€2…23‰3¯3â3u45=5d5—5°5æ5<6]66²67S7m7Ÿ7¹7í78¤8Â8Ú839k9†9Á9Ö9G:_:À: ;L;z;…;·;Ñ; <&a>”>Î>î>?W?—?±?á?`˜0v0{0¹0Ú0ý0^1‚1®1ø1!2d2x2¹2ó213m3µ3Ø34¢5Ä5Ù5î566µ8Ò8ï8 939T9u9–9±9Ò9ó9:5:V:}:ž:¿:à:û:;=;^;; ;Ç;è; <*½> ?p€0S0&1y1—1ï1q2¦2Å23&3T34#4]4è4 505„5œ5´5Ô5<6`6¤6˜7·7à748L8d8Œ8ì8B9¿9Õ9:+:Q:’:Á:;;†;“;Ø;ê;’>¡>Ò>ô>>?p?€hÕ0ö0&1®1Ü12G2—2Ì2#3‚3é3(4j4r5‹5ª5É5è5n7É778l8‹8á89J9Ô9ø9:K:T:‘:÷:;;R;u;Ä;î;=?=B>t>>Ù>&?d0`0†0®0Ö01(1N1v1ž1È1ð12>2b2Á2æ2h3’3º3à3404Z45»5ñ8#9d9¤9Ì9ô9:m:Œ:Ð:ø:‰;ª;Ô;<ˆ=¶=+>Y> ]1?ß?°\0q0ã0A1¡2J4c4ã4e5\6n6Ô6á6À7Ö7ç7+8A8W8|8‘8ª8×8ì89`9}9á9P:l:v:‚:Œ:Ù:ø:i;ˆ;É;wð 9HÎ1 22/2:2`2Ä2Õ2ß2G3¯3Ì3ë3û3^4ª4ô4°6X7€7¯9Ë9‡:: ;Q;Þ;k<Ä<«=,?X†0Õ1¢2 3„3Ÿ3#5H5z6¤6Ø6ú6.7P7€7Ÿ7 8œ8Ì89d9€9Ý9:::\:Š:;K;"=>=|=>F>u>¤>Ù>‡?¿? 41U1ˆ8­8Ì8Ö89d9’9Ï9:[:z:‰:;C;v;I<Ü=>&>1>0HR0¨0¶0á011O1Y1c1m1w1‹1¨1Á1¼2ø243p3¨3Ï3<<°<Ä<á<ý<¯>Æ>?D?d?ï?@80V0}0 1¢1¨1a6†6Ë6 89?9 ::X:~:¼:ë:f;“=Ì=Ö=ù= >P *1p0j1T55E6ÿ6B7q7™78¨8Î8ð83;§;¯Æ>?õ?€¶1ä2t3 8=<>G>|>‡> L1õ9 j0þ0e2„2ú2h3<°Î0:3¶4À˜0¢;²;Â;Ò;â;ò;<<"<2>">2>B>R>b>r>‚>’>¢>²>Â>Ò>â>ò>??"?2?B?R?b?r?‚?’?¢?²?Â?Ò?â?ò?Ð00"020B0R0b0r0‚0’0¢0²0Â0Ò0â0ò011"121B1R1b1r1‚1’1¢1²1Â1Ò1â1ò122"222B2R2b2r2‚2’2¢2²2Â2Ò2â2ò233"323B3R3b3r3‚3’3¢3²3Â3Ò3â3ò34474D4O4h4ƒ44ž4©4É4Ò4Ý4ó4ý45525J5P5b5‘5È5Ü5á5ï5666O6e6{6Š6’6š6¢6¬6¹6ú67 77&7/777J7O7z7…77›7¦7±7¼7Ä7Î7á7888%8s8ƒ8¢8²8Â8Ò8â89à|00 0000 0$0,00040<0@0D0L0P0T0\01 1111À1Ä1Ð1Ô1à1ä1ð1ô12222 2$20242@2D2P2T2`2d2p2t2€2„22”2 2¤2°2´2À2Ä2Ð2Ô2à2ä2ð2ô23333 3$30343@3D3P3T3`3d3p3t3€3„33”3 3¤3°3´3À3Ä3Ð3Ô3à3ä3ð3ô34444 4$40444@4D4P4T4`4d4p4t4€4„44”4 4¤4°4´4À4Ä4Ð4Ô4à4ä4ð4ô45555 5$50545@5D5P5T5`5d5p5t5€5„55”5 5¤5°5´5À5Ä5Ð5Ô5à5ä5ð5ô56666 6$60646@6D6P6T6`6d6p6t6€6„66”6 6¤6°6´6À6Ä6Ð6Ô6à6ä6ð6ô67777 7$70747@7D7P7T7`7d7p7t7€7„77”7 7¤7°7´7À7Ä7Ð7Ô7à7ä7ð7ô78888 8$80848@8D8P8T8`8d8p8t8€8„88”8 8¤8°8´8À8Ä8Ð8Ô8à8ä8ð8ô89999 9$90949@9D9P9T9`9d9p9t9€9„99”9 9¤9°9´9À9Ä9Ð9Ô9à9ä9ð9ô9:::: :$:0:4:@:D:P:T:`:d:p:t:€:„::”: :¤:°:´:À:Ä:Ð:Ô:à:ä:ð:ô:;;;; ;$;0;4;@;D;P;T;`;d;p;t;€;„;;”; ;¤;°;´;À;Ä;Ð;Ô;à;ä;ð;ô;<<<< <$<0<4<@>(>,>@>D>X>\>p>t>ˆ>Œ> >¤>¨>¬>°>´>¸>¼>À>Ä>È>Ì>Ð>Ô>à>? ?@?`?€? ?À?à?ð\0 0@0`0€0 0¤0¨0¬0°0´0¸0¼0À0Ä0È0Ì0Ð0Ô0111 11Ð1Ô1Ø1à1ä1222 22222 2$2(2,2 7 00 0$0(0,0004080<0@0À00000 0$0(0,0004080<0@0D0H0L0P0T0X0\0`0d0h0l0p0t0x0|0€0„0ˆ0Œ00”0˜0œ0 0¤0¨0¬0°0´0¸0¼0À0Ä0È0Ì0Ð0Ô0Ø0Ü0à0ä0è0ì0ð0ô0ø0ü0111 11111 1$1¤3¨3¬3°3´3¸3¼3À3Ä3È3Ì3Ð3l;p;t;x;|;€;„;ˆ;Œ;;”;˜;œ; ;¤;¨;¬;°;´;¸;¼;À;Ä;È;Ì;Ð;Ô;Ø;Ü;à;ä;è;ì;ð;ô;ø;ü;<<< <<<<< <$<(<,<0<4<8<<<@reserved is presently unused and should be set to 0. Any of the destination pointers may be NULL. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. year Pointer to the destination timestamp year. month Pointer to the destination timestamp month (1-12). day Pointer to the destination timestamp day (1-31). hour Pointer to the destination timestamp hour (0-23). minute Pointer to the destination timestamp minute (0-59). second Pointer to the destination timestamp second (0-60.0). timezone Pointer to the destination timezone difference from UTC in minutes. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_datestamp; %apply int *OUTPUT {int *year, int *month, int *day, int *hour, int *minute, double *second, int *timezone} get_datestamp; void get_datestamp(int *year, int *month, int *day, int *hour, int *minute, double *second, int *timezone){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_get_datestamp(self,reserved, year,month,day,hour,minute,second,timezone)); } /* cfunc cbf_get_integervalue pyfunc get_integervalue arg cbf_handle handle arg int *number */ %feature("autodoc", " Returns : int *args : C prototype: int cbf_get_integervalue (cbf_handle handle, int *number); CBFLib documentation: DESCRIPTION cbf_get_integervalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal integer. cbf_require_integervalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal integer, setting it to defaultvalue if necessary. If the value is not ASCII, the function returns CBF_BINARY. ARGUMENTS handle CBF handle. number pointer to the number. defaultvalue default number value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")get_integervalue; int get_integervalue(void){ int result; cbf_failnez(cbf_get_integervalue(self,&result)); return result;} /* cfunc cbf_get_crystal_id pyfunc get_crystal_id arg cbf_handle handle arg const char **crystal_id */ %feature("autodoc", " Returns : *args : string C prototype: int cbf_get_crystal_id (cbf_handle handle, const char **crystal_id); CBFLib documentation: DESCRIPTION cbf_get_crystal_id sets *crystal_id to point to the ASCII value of the \"diffrn.crystal_id \" entry. If the value is not ASCII, the function returns CBF_BINARY. The value will be valid as long as the item exists and has not been set to a new value. The value must not be modified by the program in any way. ARGUMENTS handle CBF handle. crystal_id Pointer to the destination value pointer. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_crystal_id; const char* get_crystal_id(void){ const char* result; cbf_failnez(cbf_get_crystal_id(self, &result)); return result;} /* cfunc cbf_get_doublevalue pyfunc get_doublevalue arg cbf_handle handle arg double *number */ %feature("autodoc", " Returns : double *args : C prototype: int cbf_get_doublevalue (cbf_handle handle, double *number); CBFLib documentation: DESCRIPTION cbf_get_doublevalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal floating-point number. cbf_require_doublevalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal floating-point number, setting it to defaultvalue if necessary. If the value is not ASCII, the function returns CBF_BINARY. ARGUMENTS handle CBF handle. number Pointer to the destination number. defaultvalue default number value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")get_doublevalue; double get_doublevalue(void){ double result; cbf_failnez(cbf_get_doublevalue(self,&result)); return result;} %feature("autodoc", " Returns : Float a,Float b,Float c,Float alpha,Float beta,Float gamma *args : C prototype: int cbf_get_unit_cell (cbf_handle handle, double cell[6], double cell_esd[6] ); CBFLib documentation: DESCRIPTION cbf_get_unit_cell sets cell[0:2] to the double values of the cell edge lengths a, b and c in AAngstroms, cell[3:5] to the double values of the cell angles a, b and g in degrees, cell_esd[0:2] to the double values of the estimated strandard deviations of the cell edge lengths a, b and c in AAngstroms, cell_esd[3:5] to the double values of the estimated standard deviations of the the cell angles a, b and g in degrees. The values returned are retrieved from the first row of the \"cell \" category. The value of \"_cell.entry_id \" is ignored. cell or cell_esd may be NULL. If cell is NULL, the cell parameters are not retrieved. If cell_esd is NULL, the cell parameter esds are not retrieved. If the \"cell \" category is present, but some of the values are missing, zeros are returned for the missing values. ARGUMENTS handle CBF handle. cell Pointer to the destination array of 6 doubles for the cell parameters. cell_esd Pointer to the destination array of 6 doubles for the cell parameter esds. RETURN VALUE Returns an error code on failure or 0 for success. No errors is returned for missing values if the \"cell \" category exists. SEE ALSO ")get_unit_cell; %apply double *OUTPUT {double *a, double *b, double *c, double *alpha, double *beta, double *gamma} get_unit_cell; void get_unit_cell(double *a, double *b, double *c, double *alpha, double *beta, double *gamma) { double cell[6]; cbf_failnez(cbf_get_unit_cell(self,cell,NULL)); *a = cell[0]; *b = cell[1]; *c = cell[2]; *alpha = cell[3]; *beta = cell[4]; *gamma = cell[5]; } %feature("autodoc", " Returns : doubleArray cell *args : C prototype: int cbf_get_unit_cell (cbf_handle handle, double cell[6], double cell_esd[6] ); CBFLib documentation: DESCRIPTION cbf_get_unit_cell sets cell[0:2] to the double values of the cell edge lengths a, b and c in AAngstroms, cell[3:5] to the double values of the cell angles a, b and g in degrees, cell_esd[0:2] to the double values of the estimated strandard deviations of the cell edge lengths a, b and c in AAngstroms, cell_esd[3:5] to the double values of the estimated standard deviations of the the cell angles a, b and g in degrees. The values returned are retrieved from the first row of the \"cell \" category. The value of \"_cell.entry_id \" is ignored. cell or cell_esd may be NULL. If cell is NULL, the cell parameters are not retrieved. If cell_esd is NULL, the cell parameter esds are not retrieved. If the \"cell \" category is present, but some of the values are missing, zeros are returned for the missing values. ARGUMENTS handle CBF handle. cell Pointer to the destination array of 6 doubles for the cell parameters. cell_esd Pointer to the destination array of 6 doubles for the cell parameter esds. RETURN VALUE Returns an error code on failure or 0 for success. No errors is returned for missing values if the \"cell \" category exists. SEE ALSO ")get_unit_cell; %apply double *OUTPUT {double *a_esd, double *b_esd, double *c_esd, double *alpha_esd, double *beta_esd, double *gamma_esd} get_unit_cell_esd; void get_unit_cell_esd(double *a_esd, double *b_esd, double *c_esd, double *alpha_esd, double *beta_esd, double *gamma_esd) { double cell_esd[6]; cbf_failnez(cbf_get_unit_cell(self,NULL,cell_esd)); *a_esd = cell_esd[0]; *b_esd = cell_esd[1]; *c_esd = cell_esd[2]; *alpha_esd = cell_esd[3]; *beta_esd = cell_esd[4]; *gamma_esd = cell_esd[5]; } /* cfunc cbf_remove_column pyfunc remove_column arg cbf_handle handle */ %feature("autodoc", " Returns : *args : C prototype: int cbf_remove_column (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_remove_column deletes the current column. The current column becomes undefined. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")remove_column; void remove_column(void){ cbf_failnez(cbf_remove_column(self));} /* cfunc cbf_rewind_blockitem pyfunc rewind_blockitem arg cbf_handle handle arg CBF_NODETYPE * type */ %feature("autodoc", " Returns : CBF_NODETYPE *args : C prototype: int cbf_rewind_blockitem (cbf_handle handle, CBF_NODETYPE * type); CBFLib documentation: DESCRIPTION cbf_rewind_category makes the first category in the current data block the current category. cbf_rewind_saveframe makes the first saveframe in the current data block the current saveframe. cbf_rewind_blockitem makes the first blockitem (category or saveframe) in the current data block the current blockitem. The type of the blockitem (CBF_CATEGORY or CBF_SAVEFRAME) is returned in type. If there are no categories, saveframes or blockitems the function returns CBF_NOTFOUND. The current column and row become undefined. ARGUMENTS handle CBF handle. type CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")rewind_blockitem; CBF_NODETYPE rewind_blockitem(void){ CBF_NODETYPE result; cbf_failnez(cbf_rewind_blockitem(self,&result)); return result;} /* cfunc cbf_get_value pyfunc get_value arg cbf_handle handle arg const char **value */ %feature("autodoc", " Returns : *args : string C prototype: int cbf_get_value (cbf_handle handle, const char **value); CBFLib documentation: DESCRIPTION cbf_get_value sets *value to point to the ASCII value of the item at the current column and row. cbf_require_value sets *value to point to the ASCII value of the item at the current column and row, creating the data item if necessary and initializing it to a copy of defaultvalue. If the value is not ASCII, the function returns CBF_BINARY. The value will be valid as long as the item exists and has not been set to a new value. The value must not be modified by the program in any way. ARGUMENTS handle CBF handle. value Pointer to the destination value pointer. defaultvalue Default value character string. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")get_value; const char* get_value(void){ const char* result; cbf_failnez(cbf_get_value(self, &result)); return result;} /* cfunc cbf_count_categories pyfunc count_categories arg cbf_handle handle arg unsigned int *categories */ %feature("autodoc", " Returns : Integer *args : C prototype: int cbf_count_categories (cbf_handle handle, unsigned int *categories); CBFLib documentation: DESCRIPTION cbf_count_categories puts the number of categories in the current data block in *categories. ARGUMENTS handle CBF handle. categories Pointer to the destination category count. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")count_categories; unsigned int count_categories(void){ unsigned int result; cbf_failnez(cbf_count_categories(self,&result)); return result;} %feature("autodoc", " Returns : *args : String filename,Integer headers C prototype: int cbf_read_widefile (cbf_handle handle, FILE *file, int flags); CBFLib documentation: DESCRIPTION cbf_read_file reads the CBF or CIF file file into the CBF object specified by handle, using the CIF 1.0 convention of 80 character lines. cbf_read_widefile reads the CBF or CIF file file into the CBF object specified by handle, using the CIF 1.1 convention of 2048 character lines. A warning is issued to stderr for ascii lines over the limit. No test is performed on binary sections. Validation is performed in three ways levels: during the lexical scan, during the parse, and, if a dictionary was converted, against the value types, value enumerations, categories and parent-child relationships specified in the dictionary. flags controls the interpretation of binary section headers, the parsing of brackets constructs and the parsing of treble-quoted strings. MSG_DIGEST: Instructs CBFlib to check that the digest of the binary section matches any header digest value. If the digests do not match, the call will return CBF_FORMAT. This evaluation and comparison is delayed (a \"lazy \" evaluation) to ensure maximal processing efficiency. If an immediately evaluation is required, see MSG_DIGESTNOW, below. MSG_DIGESTNOW: Instructs CBFlib to check that the digest of the binary section matches any header digeste value. If the digests do not match, the call will return CBF_FORMAT. This evaluation and comparison is performed during initial parsing of the section to ensure timely error reporting at the expense of processing efficiency. If a more efficient delayed ( \"lazy \") evaluation is required, see MSG_DIGEST, above. MSG_DIGESTWARN: Instructs CBFlib to check that the digest of the binary section matches any header digeste value. If the digests do not match, a warning message will be sent to stderr, but processing will attempt to continue. This evaluation and comparison is first performed during initial parsing of the section to ensure timely error reporting at the expense of processing efficiency. An mismatch of the message digest usually indicates a serious error, but it is sometimes worth continuing processing to try to isolate the cause of the error. Use this option with caution. MSG_NODIGEST: Do not check the digest (default). PARSE_BRACKETS: Accept DDLm bracket-delimited [item,item,...item] or {item,item,...item} or (item,item,...item) constructs as valid, stripping non-quoted embedded whitespace and comments. These constructs may span multiple lines. PARSE_LIBERAL_BRACKETS: Accept DDLm bracket-delimited [item,item,...item] or {item,item,...item} or (item,item,...item) constructs as valid, stripping embedded non-quoted, non-separating whitespace and comments. These constructs may span multiple lines. In this case, whitespace may be used as an alternative to the comma. PARSE_TRIPLE_QUOTES: Accept DDLm triple-quoted \" \" \"item,item,...item \" \" \" or '''item,item,...item''' constructs as valid, stripping embedded whitespace and comments. These constructs may span multiple lines. If this flag is set, then ''' will not be interpreted as a quoted apoptrophe and \" \" \" will not be interpreted as a quoted double quote mark and PARSE_NOBRACKETS: Do not accept DDLm bracket-delimited [item,item,...item] or {item,item,...item} or (item,item,...item) constructs as valid, stripping non-quoted embedded whitespace and comments. These constructs may span multiple lines. PARSE_NOTRIPLE_QUOTES: No not accept DDLm triple-quoted \" \" \"item,item,...item \" \" \" or '''item,item,...item''' constructs as valid, stripping embedded whitespace and comments. These constructs may span multiple lines. If this flag is set, then ''' will be interpreted as a quoted apostrophe and \" \" \" will be interpreted as a quoted double quote mark. CBFlib defers reading binary sections as long as possible. In the current version of CBFlib, this means that: 1. The file must be a random-access file opened in binary mode (fopen ( , ")read_widefile; void read_widefile(char* filename, int headers){ /* CBFlib needs a stream that will remain open hence DO NOT open from python */ FILE *stream; if ( ! ( stream = fopen (filename, "rb")) ){ cbf_failnez(CBF_FILEOPEN); } else{ cbf_failnez(cbf_read_widefile(self, stream, headers)); } } /* cfunc cbf_set_wavelength pyfunc set_wavelength arg cbf_handle handle arg double wavelength */ %feature("autodoc", " Returns : double wavelength *args : C prototype: int cbf_set_wavelength (cbf_handle handle, double wavelength); CBFLib documentation: DESCRIPTION cbf_set_wavelength sets the current wavelength in AA to wavelength. ARGUMENTS handle CBF handle. wavelength Wavelength in AA. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_wavelength; void set_wavelength(double wavelength){ cbf_failnez(cbf_set_wavelength(self,wavelength));} %feature("autodoc", " Returns : *args : Int element_number,Int axis_number,Float pixel size C prototype: int cbf_set_pixel_size_sf(cbf_handle handle, unsigned int element_number, int axis_number, double psize); CBFLib documentation: DESCRIPTION cbf_set_pixel_size and cbf_set_pixel_size_sf set the item in the "e;size"e; column of the \"array_structure_list \" category at the row which matches axis axis_number of the detector element element_number converting the double pixel size psize from meters to millimeters in storing it in the \"size \" column for the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the slowest axis. cbf_set_pixel_size_fs sets the item ")set_pixel_size_sf; void set_pixel_size_sf (unsigned int element_number, unsigned int axis_number, double psize){ cbf_failnez(cbf_set_pixel_size_sf(self, element_number, axis_number, psize)); } /* cfunc cbf_get_diffrn_id pyfunc get_diffrn_id arg cbf_handle handle arg const char **diffrn_id */ %feature("autodoc", " Returns : *args : string C prototype: int cbf_get_diffrn_id (cbf_handle handle, const char **diffrn_id); CBFLib documentation: DESCRIPTION cbf_get_diffrn_id sets *diffrn_id to point to the ASCII value of the \"diffrn.id \" entry. cbf_require_diffrn_id also sets *diffrn_id to point to the ASCII value of the \"diffrn.id \" entry, but, if the \"diffrn.id \" entry does not exist, it sets the value in the CBF and in*diffrn_id to the character string given by default_id, creating the category and column is necessary. The diffrn_id will be valid as long as the item exists and has not been set to a new value. The diffrn_id must not be modified by the program in any way. ARGUMENTS handle CBF handle. diffrn_id Pointer to the destination value pointer. default_id Character string default value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_diffrn_id; const char* get_diffrn_id(void){ const char* result; cbf_failnez(cbf_get_diffrn_id(self, &result)); return result;} /* cfunc cbf_find_datablock pyfunc find_datablock arg cbf_handle handle arg const char *datablockname */ %feature("autodoc", " Returns : string *args : C prototype: int cbf_find_datablock (cbf_handle handle, const char *datablockname); CBFLib documentation: DESCRIPTION cbf_find_datablock makes the data block with name datablockname the current data block. The comparison is case-insensitive. If the data block does not exist, the function returns CBF_NOTFOUND. The current category becomes undefined. ARGUMENTS handle CBF handle. datablockname The name of the data block to find. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")find_datablock; void find_datablock(const char* arg){ cbf_failnez(cbf_find_datablock(self,arg));} %feature("autodoc", " Returns : float polarizn_source_ratio,float polarizn_source_norm *args : C prototype: int cbf_get_polarization (cbf_handle handle, double *polarizn_source_ratio, double *polarizn_source_norm); CBFLib documentation: DESCRIPTION cbf_get_polarization sets *polarizn_source_ratio and *polarizn_source_norm to the corresponding source polarization parameters. Either destination pointer may be NULL. ARGUMENTS handle CBF handle. polarizn_source_ratio Pointer to the destination polarizn_source_ratio. polarizn_source_norm Pointer to the destination polarizn_source_norm. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_polarization; /* Returns a pair of double values */ %apply double *OUTPUT { double *in1, double *in2 }; void get_polarization(double *in1,double *in2){ cbf_failnez(cbf_get_polarization (self, in1, in2)); } /* cfunc cbf_select_category pyfunc select_category arg cbf_handle handle arg unsigned int category */ %feature("autodoc", " Returns : *args : Integer C prototype: int cbf_select_category (cbf_handle handle, unsigned int category); CBFLib documentation: DESCRIPTION cbf_select_category selects category number category in the current data block as the current category. The first category is number 0. The current column and row become undefined. If the category does not exist, the function returns CBF_NOTFOUND. ARGUMENTS handle CBF handle. category Number of the category to select. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")select_category; void select_category(unsigned int arg){ cbf_failnez(cbf_select_category(self,arg));} %feature("autodoc", " Returns : Float pixel_size *args : Int element_number,Int axis_number C prototype: int cbf_get_pixel_size_fs(cbf_handle handle, unsigned int element_number, int axis_number, double *psize); CBFLib documentation: DESCRIPTION cbf_get_pixel_size and cbf_get_pixel_size_sf set *psize to point to the double value in millimeters of the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the slowest axis. cbf_get_pixel_size_fs sets *psize to point to the double value in millimeters of the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the fastest axis. If a negative axis number is given, the order of axes is reversed, so that -1 specifies the slowest axis for cbf_get_pixel_size_fs and the fastest axis for cbf_get_pixel_size_sf. If the pixel size is not given explcitly in the \"array_element_size \" category, the function returns CBF_NOTFOUND. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the \"diffrn_data_frame \" category. axis_number The number of the axis, starting from 1 for the fastest for cbf_get_pixel_size and cbf_get_pixel_size_fs and the slowest for cbf_get_pixel_size_sf. psize Pointer to the destination pixel size. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_pixel_size_fs; %apply double *OUTPUT {double *psize} get_pixel_size; void get_pixel_size_fs(unsigned int element_number, unsigned int axis_number, double *psize){ cbf_failnez(cbf_get_pixel_size_fs(self, element_number, axis_number, psize)); } %feature("autodoc", " Returns : *args : String filename,Integer headers C prototype: int cbf_read_file (cbf_handle handle, FILE *file, int flags); CBFLib documentation: DESCRIPTION cbf_read_file reads the CBF or CIF file file into the CBF object specified by handle, using the CIF 1.0 convention of 80 character lines. cbf_read_widefile reads the CBF or CIF file file into the CBF object specified by handle, using the CIF 1.1 convention of 2048 character lines. A warning is issued to stderr for ascii lines over the limit. No test is performed on binary sections. Validation is performed in three ways levels: during the lexical scan, during the parse, and, if a dictionary was converted, against the value types, value enumerations, categories and parent-child relationships specified in the dictionary. flags controls the interpretation of binary section headers, the parsing of brackets constructs and the parsing of treble-quoted strings. MSG_DIGEST: Instructs CBFlib to check that the digest of the binary section matches any header digest value. If the digests do not match, the call will return CBF_FORMAT. This evaluation and comparison is delayed (a \"lazy \" evaluation) to ensure maximal processing efficiency. If an immediately evaluation is required, see MSG_DIGESTNOW, below. MSG_DIGESTNOW: Instructs CBFlib to check that the digest of the binary section matches any header digeste value. If the digests do not match, the call will return CBF_FORMAT. This evaluation and comparison is performed during initial parsing of the section to ensure timely error reporting at the expense of processing efficiency. If a more efficient delayed ( \"lazy \") evaluation is required, see MSG_DIGEST, above. MSG_DIGESTWARN: Instructs CBFlib to check that the digest of the binary section matches any header digeste value. If the digests do not match, a warning message will be sent to stderr, but processing will attempt to continue. This evaluation and comparison is first performed during initial parsing of the section to ensure timely error reporting at the expense of processing efficiency. An mismatch of the message digest usually indicates a serious error, but it is sometimes worth continuing processing to try to isolate the cause of the error. Use this option with caution. MSG_NODIGEST: Do not check the digest (default). PARSE_BRACKETS: Accept DDLm bracket-delimited [item,item,...item] or {item,item,...item} or (item,item,...item) constructs as valid, stripping non-quoted embedded whitespace and comments. These constructs may span multiple lines. PARSE_LIBERAL_BRACKETS: Accept DDLm bracket-delimited [item,item,...item] or {item,item,...item} or (item,item,...item) constructs as valid, stripping embedded non-quoted, non-separating whitespace and comments. These constructs may span multiple lines. In this case, whitespace may be used as an alternative to the comma. PARSE_TRIPLE_QUOTES: Accept DDLm triple-quoted \" \" \"item,item,...item \" \" \" or '''item,item,...item''' constructs as valid, stripping embedded whitespace and comments. These constructs may span multiple lines. If this flag is set, then ''' will not be interpreted as a quoted apoptrophe and \" \" \" will not be interpreted as a quoted double quote mark and PARSE_NOBRACKETS: Do not accept DDLm bracket-delimited [item,item,...item] or {item,item,...item} or (item,item,...item) constructs as valid, stripping non-quoted embedded whitespace and comments. These constructs may span multiple lines. PARSE_NOTRIPLE_QUOTES: No not accept DDLm triple-quoted \" \" \"item,item,...item \" \" \" or '''item,item,...item''' constructs as valid, stripping embedded whitespace and comments. These constructs may span multiple lines. If this flag is set, then ''' will be interpreted as a quoted apostrophe and \" \" \" will be interpreted as a quoted double quote mark. CBFlib defers reading binary sections as long as possible. In the current version of CBFlib, this means that: 1. The file must be a random-access file opened in binary mode (fopen ( , ")read_file; void read_file(char* filename, int headers){ /* CBFlib needs a stream that will remain open hence DO NOT open from python */ FILE *stream; if ( ! ( stream = fopen (filename, "rb")) ){ cbf_failnez(CBF_FILEOPEN); } else{ cbf_failnez(cbf_read_file(self, stream, headers)); } } /* cfunc cbf_datablock_name pyfunc datablock_name arg cbf_handle handle arg const char **datablockname */ %feature("autodoc", " Returns : *args : string C prototype: int cbf_datablock_name (cbf_handle handle, const char **datablockname); CBFLib documentation: DESCRIPTION cbf_datablock_name sets *datablockname to point to the name of the current data block. The data block name will be valid as long as the data block exists and has not been renamed. The name must not be modified by the program in any way. ARGUMENTS handle CBF handle. datablockname Pointer to the destination data block name pointer. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")datablock_name; const char* datablock_name(void){ const char* result; cbf_failnez(cbf_datablock_name(self, &result)); return result;} %feature("autodoc", " Returns : *args : int compression,int binary_id,(binary) String data,int elsize, int elements,String byteorder,int dimfast,int dimmid,int dimslow, int padding C prototype: int cbf_set_realarray_wdims (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, size_t elements, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); CBFLib documentation: DESCRIPTION cbf_set_integerarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. The elements are signed if elsigned is non-0 and unsigned otherwise. binary_id is the binary section identifier. cbf_set_realarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. binary_id is the binary section identifier. The cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, cbf_set_integerarray_wdims_sf, cbf_set_realarray_wdims, cbf_set_realarray_wdims_fs and cbf_set_realarray_wdims_sf variants allow the data header values of byteorder, dimfast, dimmid, dimslow and padding to be set to the data byte order, the fastest, second fastest and third fastest array dimensions and the size in byte of the post data padding to be used. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \"byte_offset \" compression. CBF_NONE No compression. NOTE: This scheme is by far the slowest of the four and uses much more disk space. It is intended for routine use with small arrays only. With large arrays (like images) it should be used only for debugging. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned), for cbf_set_integerarray, or IEEE doubles or floats for cbf_set_realarray. If elsize is not equal to sizeof (char), sizeof (short) or sizeof (int), the function returns CBF_ARGUMENT. ARGUMENTS handle CBF handle. compression Compression method to use. binary_id Integer binary identifier. array Pointer to the source array. elsize Size in bytes of each source array element. elsigned Set to non-0 if the source array elements are signed. elements: The number of elements in the array. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")set_realarray_wdims; /* CBFlib must NOT modify the data string nor the byteorder string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_realarray_wdims; %apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_realarray_wdims; void set_realarray_wdims(unsigned int compression, int binary_id, char *data, int len, int elsize, int elements, char *bo, int bolen, int dimfast, int dimmid, int dimslow, int padding){ /* safety check on args */ size_t els, ele; void *array; char byteorder[15]; if(len == elsize*elements && elements==dimfast*dimmid*dimslow){ array = data; els = elsize; ele = elements; strncpy(byteorder,bo,bolen<15?bolen:14); byteorder[bolen<15?14:bolen] = 0; cbf_failnez(cbf_set_realarray_wdims (self, compression, binary_id, (void *) data, (size_t) elsize, (size_t) elements, (const char *)byteorder, (size_t)dimfast, (size_t)dimmid, (size_t)dimslow, (size_t)padding)); }else{ cbf_failnez(CBF_ARGUMENT); } } %feature("autodoc", " Returns : pycbf detector object *args : Integer element_number C prototype: int cbf_construct_reference_detector (cbf_handle handle, cbf_detector *detector, unsigned int element_number); CBFLib documentation: DESCRIPTION cbf_construct_detector constructs a detector object for detector element number element_number using the description in the CBF object handle and initialises the detector handle *detector. cbf_construct_reference_detector constructs a detector object for detector element number element_number using the description in the CBF object handle and initialises the detector handle *detector using the reference settings of the axes. cbf_require_reference_detector is similar, but try to force the creations of missing intermediate categories needed to construct a detector object. ARGUMENTS handle CBF handle. detector Pointer to the destination detector handle. element_number The number of the detector element counting from 0 by order of appearance in the \"diffrn_data_frame \" category. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")construct_reference_detector; cbf_detector construct_reference_detector(unsigned int element_number){ cbf_detector detector; cbf_failnez(cbf_construct_reference_detector(self,&detector,element_number)); return detector; } %feature("autodoc", " Returns : (Binary)String *args : int element_number,int elsize,int ndimfast,int ndimmid,int ndimslow C prototype: int cbf_get_real_3d_image_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimfast, size_t ndimmid, size_t ndimslow); CBFLib documentation: DESCRIPTION cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image array for element number element_number into an array. The array consists of ndimslow *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and cbf_get_real_image_sf read the image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. cbf_get_3d_image, cbf_get_3d_image_fs and cbf_get_3d_image_sf read the 3D image array for element number element_number into an array. The array consists of ndimslow *ndimmid *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order The structure of the array as a 1-, 2- or 3-dimensional array should agree with the structure of the array given in the ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1 both in the call and in the imgCIF data being processed. If the array is 2-dimensional and a 3D call is used, ndimslow and ndimmid should be the ")get_real_3d_image_fs_as_string; // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_real_3d_image_fs_as_string; // Get the length correct void get_real_3d_image_fs_as_string(int element_number, char **s, int *slen, int elsize, int ndimfast, int ndimmid, int ndimslow){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) { cbf_failnez (cbf_get_real_3d_image_fs(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, (size_t) ndimfast, (size_t)ndimmid, (size_t)ndimslow)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimmid*ndimslow; *s = (char *) array; } /* cfunc cbf_rewind_row pyfunc rewind_row arg cbf_handle handle */ %feature("autodoc", " Returns : *args : C prototype: int cbf_rewind_row (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_rewind_row makes the first row in the current category the current row. If there are no rows, the function returns CBF_NOTFOUND. The current column is not affected. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")rewind_row; void rewind_row(void){ cbf_failnez(cbf_rewind_row(self));} %feature("autodoc", " Returns : Float start,Float increment *args : String axis_id C prototype: int cbf_get_axis_setting (cbf_handle handle, unsigned int reserved, const char *axis_id, double *start, double *increment); CBFLib documentation: DESCRIPTION cbf_get_axis_setting sets *start and *increment to the corresponding values of the axis axis_id. Either of the destination pointers may be NULL. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. axis_id Axis id. start Pointer to the destination start value. increment Pointer to the destination increment value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_axis_setting; %apply double *OUTPUT {double *start, double *increment} get_axis_setting; void get_axis_setting(const char *axis_id, double *start, double *increment){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_get_axis_setting(self,reserved,axis_id, start,increment)); } /* cfunc cbf_require_column pyfunc require_column arg cbf_handle handle arg const char *columnname */ %feature("autodoc", " Returns : string *args : C prototype: int cbf_require_column (cbf_handle handle, const char *columnname); CBFLib documentation: DESCRIPTION cbf_require_column makes the columns in the current category with name columnname the current column, if it exists, or creates it if it does not. The comparison is case-insensitive. The current row is not affected. ARGUMENTS handle CBF handle. columnname The name of column to find. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")require_column; void require_column(const char* arg){ cbf_failnez(cbf_require_column(self,arg));} %feature("autodoc", " Returns : Float time,Integer timezone *args : C prototype: int cbf_get_timestamp (cbf_handle handle, unsigned int reserved, double *time, int *timezone); CBFLib documentation: DESCRIPTION cbf_get_timestamp sets *time to the collection timestamp in seconds since January 1 1970. *timezone is set to timezone difference from UTC in minutes. The parameter reserved is presently unused and should be set to 0. Either of the destination pointers may be NULL. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. time Pointer to the destination collection timestamp. timezone Pointer to the destination timezone difference. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_timestamp; %apply double *OUTPUT {double *time} get_timestamp; %apply int *OUTPUT {int *timezone} get_timestamp; void get_timestamp(double *time, int *timezone){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_get_timestamp(self,reserved,time,timezone)); } /* cfunc cbf_find_nextrow pyfunc find_nextrow arg cbf_handle handle arg const char *value */ %feature("autodoc", " Returns : string *args : C prototype: int cbf_find_nextrow (cbf_handle handle, const char *value); CBFLib documentation: DESCRIPTION cbf_find_nextrow makes the makes the next row in the current column with value value the current row. The search starts from the row following the last row found with cbf_find_row or cbf_find_nextrow, or from the current row if the current row was defined using any other function. The comparison is case-sensitive. If no more matching rows exist, the function returns CBF_NOTFOUND. The current column is not affected. ARGUMENTS handle CBF handle. value the value to search for. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")find_nextrow; void find_nextrow(const char* arg){ cbf_failnez(cbf_find_nextrow(self,arg));} %feature("autodoc", " Returns : int compression,int binary_id,int elsize,int elements,char **bo, int *bolen,int dimslow,int dimmid,int dimfast,int padding *args : C prototype: int cbf_get_realarrayparameters_wdims_sf (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, size_t *elements, const char **byteorder, size_t *dimslow, size_t *dimmid, size_t *dimfast, size_t *padding); CBFLib documentation: DESCRIPTION cbf_get_integerarrayparameters sets *compression, *binary_id, *elsize, *elsigned, *elunsigned, *elements, *minelement and *maxelement to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_integerarray, if a copy of the array is to be made into another CIF or CBF. cbf_get_realarrayparameters sets *compression, *binary_id, *elsize, *elements to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_realarray, if a copy of the arry is to be made into another CIF or CBF. The variants cbf_get_integerarrayparameters_wdims, cbf_get_integerarrayparameters_wdims_fs, cbf_get_integerarrayparameters_wdims_sf, cbf_get_realarrayparameters_wdims, cbf_get_realarrayparameters_wdims_fs, cbf_get_realarrayparameters_wdims_sf set **byteorder, *dimfast, *dimmid, *dimslow, and *padding as well, providing the additional parameters needed for a subsequent call to cbf_set_integerarray_wdims or cbf_set_realarray_wdims. The value returned in *byteorder is a pointer either to the string \"little_endian \" or to the string \"big_endian \". This should be the byte order of the data, not necessarily of the host machine. No attempt should be made to modify this string. At this time only \"little_endian \" will be returned. The values returned in *dimfast, *dimmid and *dimslow are the sizes of the fastest changing, second fastest changing and third fastest changing dimensions of the array, if specified, or zero, if not specified. The value returned in *padding is the size of the post-data padding, if any and if specified in the data header. The value is given as a count of octets. If the value is not binary, the function returns CBF_ASCII. ARGUMENTS handle CBF handle. compression Compression method used. elsize Size in bytes of each array element. binary_id Pointer to the destination integer binary identifier. elsigned Pointer to an integer. Set to 1 if the elements can be read as signed integers. elunsigned Pointer to an integer. Set to 1 if the elements can be read as unsigned integers. elements Pointer to the destination number of elements. minelement Pointer to the destination smallest element. maxelement Pointer to the destination largest element. byteorder Pointer to the destination byte order. dimfast Pointer to the destination fastest dimension. dimmid Pointer to the destination second fastest dimension. dimslow Pointer to the destination third fastest dimension. padding Pointer to the destination padding size. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")get_realarrayparameters_wdims_sf; %cstring_output_allocate_size(char **bo, int *bolen, free(*$1)); %apply int *OUTPUT {int *compression,int *binary_id, int *elsize, int *elements, int *dimslow, int *dimmid, int *dimfast, int *padding} get_realarrayparameters_wdims_sf; void get_realarrayparameters_wdims_sf(int *compression,int *binary_id, int *elsize, int *elements, char **bo, int *bolen, int *dimslow, int *dimmid, int *dimfast, int *padding ){ unsigned int comp; size_t elsiz, elem, df,dm,ds,pd; const char * byteorder; char * bot; cbf_failnez(cbf_get_realarrayparameters_wdims_sf(self, &comp,binary_id, &elsiz, &elem, &byteorder,&ds,&dm,&df,&pd )); *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)} strncpy(bot,byteorder,*bolen); *bo = bot; *compression = comp; *elsize = elsiz; *elements = elem; *dimfast = df; *dimmid = dm; *dimslow = ds; *padding = pd; } /* cfunc cbf_reset_datablock pyfunc reset_datablock arg cbf_handle handle */ %feature("autodoc", " Returns : *args : C prototype: int cbf_reset_datablock (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_reset_datablock deletes all categories from the current data block. cbf_reset_saveframe deletes all categories from the current save frame. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")reset_datablock; void reset_datablock(void){ cbf_failnez(cbf_reset_datablock(self));} %feature("autodoc", " Returns : *args : int element_number,int compression,(binary) String data,int elsize, int elsign,int dimfast,int dimmid,int dimslow C prototype: int cbf_set_3d_image_fs(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimfast, size_t ndimmid, size_t ndimslow); CBFLib documentation: DESCRIPTION cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-zero and unsigned otherwise. cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow IEEE double or float elements of elsize bytes each, starting at array. cbf_set_3d_image, cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_set_real_3d_image, cbf_set_real_3d_image_fs and cbf_set_real_3d_image_sf writes the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow IEEE double or float elements of elsize bytes each, starting at array. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the array is 2-dimensional and the 3D calls are used, ndimslow and ndimmid should be used for the array dimensions and ndimfast should be set to 1. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \"byte_offset \" compression. CBF_NONE No compression. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned)for cbf_set_image, or IEEE doubles or floats for cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the \"diffrn_data_frame \" category. compression Compression type. array Pointer to the image array. elsize Size in bytes of each image array element. elsigned Set to non-0 if the image array elements are signed. ndimslow Slowest array dimension. ndimmid Second slowest array dimension. ndimfast Fastest array dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_3d_image_fs; /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_3d_image; void set_3d_image_fs(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int elsign, int ndimfast, int ndimmid, int ndimslow){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimmid*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_3d_image_fs (self, reserved, element_number, compression, (void *) data, (size_t) elsize, elsign, (size_t) ndimfast, (size_t) ndimmid, (size_t)ndimslow)); }else{ cbf_failnez(CBF_ARGUMENT); } } /* cfunc cbf_set_saveframename pyfunc set_saveframename arg cbf_handle handle arg const char *saveframename */ %feature("autodoc", " Returns : string *args : C prototype: int cbf_set_saveframename (cbf_handle handle, const char *saveframename); CBFLib documentation: DESCRIPTION cbf_set_datablockname changes the name of the current data block to datablockname. cbf_set_saveframename changes the name of the current save frame to saveframename. If a data block or save frame with this name already exists (comparison is case-insensitive), the function returns CBF_IDENTICAL. ARGUMENTS handle CBF handle. datablockname The new data block name. datablockname The new save frame name. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")set_saveframename; void set_saveframename(const char* arg){ cbf_failnez(cbf_set_saveframename(self,arg));} %feature("autodoc", " Returns : Int number *args : Int thedefault C prototype: int cbf_require_integervalue (cbf_handle handle, int *number, int defaultvalue); CBFLib documentation: DESCRIPTION cbf_get_integervalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal integer. cbf_require_integervalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal integer, setting it to defaultvalue if necessary. If the value is not ASCII, the function returns CBF_BINARY. ARGUMENTS handle CBF handle. number pointer to the number. defaultvalue default number value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")require_integervalue; %apply int *OUTPUT {int *number} require_integervalue; void require_integervalue(int *number, int thedefault){ cbf_failnez(cbf_require_integervalue(self,number,thedefault)); } %feature("autodoc", " Returns : int compression,int binary_id,int elsize,int elsigned,int elunsigned, int elements,int minelement,int maxelement *args : C prototype: int cbf_get_integerarrayparameters (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, int *elsigned, int *elunsigned, size_t *elements, int *minelement, int *maxelement); CBFLib documentation: DESCRIPTION cbf_get_integerarrayparameters sets *compression, *binary_id, *elsize, *elsigned, *elunsigned, *elements, *minelement and *maxelement to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_integerarray, if a copy of the array is to be made into another CIF or CBF. cbf_get_realarrayparameters sets *compression, *binary_id, *elsize, *elements to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_realarray, if a copy of the arry is to be made into another CIF or CBF. The variants cbf_get_integerarrayparameters_wdims, cbf_get_integerarrayparameters_wdims_fs, cbf_get_integerarrayparameters_wdims_sf, cbf_get_realarrayparameters_wdims, cbf_get_realarrayparameters_wdims_fs, cbf_get_realarrayparameters_wdims_sf set **byteorder, *dimfast, *dimmid, *dimslow, and *padding as well, providing the additional parameters needed for a subsequent call to cbf_set_integerarray_wdims or cbf_set_realarray_wdims. The value returned in *byteorder is a pointer either to the string \"little_endian \" or to the string \"big_endian \". This should be the byte order of the data, not necessarily of the host machine. No attempt should be made to modify this string. At this time only \"little_endian \" will be returned. The values returned in *dimfast, *dimmid and *dimslow are the sizes of the fastest changing, second fastest changing and third fastest changing dimensions of the array, if specified, or zero, if not specified. The value returned in *padding is the size of the post-data padding, if any and if specified in the data header. The value is given as a count of octets. If the value is not binary, the function returns CBF_ASCII. ARGUMENTS handle CBF handle. compression Compression method used. elsize Size in bytes of each array element. binary_id Pointer to the destination integer binary identifier. elsigned Pointer to an integer. Set to 1 if the elements can be read as signed integers. elunsigned Pointer to an integer. Set to 1 if the elements can be read as unsigned integers. elements Pointer to the destination number of elements. minelement Pointer to the destination smallest element. maxelement Pointer to the destination largest element. byteorder Pointer to the destination byte order. dimfast Pointer to the destination fastest dimension. dimmid Pointer to the destination second fastest dimension. dimslow Pointer to the destination third fastest dimension. padding Pointer to the destination padding size. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")get_integerarrayparameters; %apply int *OUTPUT {int *compression,int *binary_id, int *elsize, int *elsigned, int *elunsigned, int *elements, int *minelement, int *maxelement} get_integerarrayparameters; void get_integerarrayparameters(int *compression,int *binary_id, int *elsize, int *elsigned, int *elunsigned, int *elements, int *minelement, int *maxelement){ unsigned int comp; size_t elsiz, elem; cbf_failnez(cbf_get_integerarrayparameters(self, &comp,binary_id, &elsiz, elsigned, elunsigned, &elem, minelement, maxelement)); *compression = comp; /* FIXME - does this convert in C? */ *elsize = elsiz; *elements = elem; } %feature("autodoc", " Returns : *args : int element_number,int compression,(binary) String data,int elsize, int dimslow,int dimmid,int dimfast C prototype: int cbf_set_real_3d_image_sf(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-zero and unsigned otherwise. cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow IEEE double or float elements of elsize bytes each, starting at array. cbf_set_3d_image, cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_set_real_3d_image, cbf_set_real_3d_image_fs and cbf_set_real_3d_image_sf writes the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow IEEE double or float elements of elsize bytes each, starting at array. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the array is 2-dimensional and the 3D calls are used, ndimslow and ndimmid should be used for the array dimensions and ndimfast should be set to 1. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \"byte_offset \" compression. CBF_NONE No compression. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned)for cbf_set_image, or IEEE doubles or floats for cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the \"diffrn_data_frame \" category. compression Compression type. array Pointer to the image array. elsize Size in bytes of each image array element. elsigned Set to non-0 if the image array elements are signed. ndimslow Slowest array dimension. ndimmid Second slowest array dimension. ndimfast Fastest array dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_real_3d_image_sf; /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_real_3d_image_sf; void set_real_3d_image_sf(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int ndimslow, int ndimmid, int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimmid*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_real_3d_image_sf (self, reserved, element_number, compression, (void *) data, (size_t) elsize, (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ARGUMENT); } } %feature("autodoc", " Returns : *args : String filename,Integer ciforcbf,Integer Headers,Integer encoding C prototype: int cbf_write_file (cbf_handle handle, FILE *file, int readable, int ciforcbf, int flags, int encoding); CBFLib documentation: DESCRIPTION cbf_write_file writes the CBF object specified by handle into the file file, following CIF 1.0 conventions of 80 character lines. cbf_write_widefile writes the CBF object specified by handle into the file file, following CIF 1.1 conventions of 2048 character lines. A warning is issued to stderr for ascii lines over the limit, and an attempt is made to fold lines to fit. No test is performed on binary sections. If a dictionary has been provided, aliases will be applied on output. Unlike cbf_read_file, the file does not have to be random-access. If the file is random-access and readable, readable can be set to non-0 to indicate to CBFlib that the file can be used as a buffer to conserve disk space. If the file is not random-access or not readable, readable must be 0. ")write_file; void write_file(const char* filename, int ciforcbf, int headers, int encoding){ FILE *stream; int readable; /* Make the file non-0 to make CBFlib close the file */ readable = 1; if ( ! ( stream = fopen (filename, "w+b")) ){ cbf_failnez(CBF_FILEOPEN); } else{ cbf_failnez(cbf_write_file(self, stream, readable, ciforcbf, headers, encoding)); } } %feature("autodoc", " Returns : *args : Float div_x_source,Float div_y_source,Float div_x_y_source C prototype: int cbf_set_divergence (cbf_handle handle, double div_x_source, double div_y_source, double div_x_y_source); CBFLib documentation: DESCRIPTION cbf_set_divergence sets the source divergence parameters to the values specified by div_x_source, div_y_source and div_x_y_source. ARGUMENTS handle CBF handle. div_x_source New value of div_x_source. div_y_source New value of div_y_source. div_x_y_source New value of div_x_y_source. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_divergence; void set_divergence ( double div_x_source, double div_y_source, double div_x_y_source){ cbf_failnez(cbf_set_divergence (self, div_x_source, div_y_source,div_x_y_source)); } /* cfunc cbf_remove_datablock pyfunc remove_datablock arg cbf_handle handle */ %feature("autodoc", " Returns : *args : C prototype: int cbf_remove_datablock (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_remove_datablock deletes the current data block. cbf_remove_saveframe deletes the current save frame. The current data block becomes undefined. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")remove_datablock; void remove_datablock(void){ cbf_failnez(cbf_remove_datablock(self));} /* cfunc cbf_count_elements pyfunc count_elements arg cbf_handle handle arg unsigned int *elements */ %feature("autodoc", " Returns : Integer *args : C prototype: int cbf_count_elements (cbf_handle handle, unsigned int *elements); CBFLib documentation: DESCRIPTION cbf_count_elements sets *elements to the number of detector elements. ARGUMENTS handle CBF handle. elements Pointer to the destination count. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")count_elements; unsigned int count_elements(void){ unsigned int result; cbf_failnez(cbf_count_elements(self,&result)); return result;} %feature("autodoc", " Returns : *args : int element_number,int compression,(binary) String data,int elsize, int elsign,int dimfast,int dimslow C prototype: int cbf_set_image_fs(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimfast, size_t ndimslow); CBFLib documentation: DESCRIPTION cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-zero and unsigned otherwise. cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow IEEE double or float elements of elsize bytes each, starting at array. cbf_set_3d_image, cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_set_real_3d_image, cbf_set_real_3d_image_fs and cbf_set_real_3d_image_sf writes the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow IEEE double or float elements of elsize bytes each, starting at array. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the array is 2-dimensional and the 3D calls are used, ndimslow and ndimmid should be used for the array dimensions and ndimfast should be set to 1. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \"byte_offset \" compression. CBF_NONE No compression. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned)for cbf_set_image, or IEEE doubles or floats for cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the \"diffrn_data_frame \" category. compression Compression type. array Pointer to the image array. elsize Size in bytes of each image array element. elsigned Set to non-0 if the image array elements are signed. ndimslow Slowest array dimension. ndimmid Second slowest array dimension. ndimfast Fastest array dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_image_fs; /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_image; void set_image_fs(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int elsign, int ndimfast, int ndimslow){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_image (self, reserved, element_number, compression, (void *) data, (size_t) elsize, elsign, (size_t) ndimfast, (size_t)ndimslow)); }else{ cbf_failnez(CBF_ARGUMENT); } } %feature("autodoc", " Returns : pycbf detector object *args : Integer element_number C prototype: int cbf_require_reference_detector (cbf_handle handle, cbf_detector *detector, unsigned int element_number); CBFLib documentation: DESCRIPTION cbf_construct_detector constructs a detector object for detector element number element_number using the description in the CBF object handle and initialises the detector handle *detector. cbf_construct_reference_detector constructs a detector object for detector element number element_number using the description in the CBF object handle and initialises the detector handle *detector using the reference settings of the axes. cbf_require_reference_detector is similar, but try to force the creations of missing intermediate categories needed to construct a detector object. ARGUMENTS handle CBF handle. detector Pointer to the destination detector handle. element_number The number of the detector element counting from 0 by order of appearance in the \"diffrn_data_frame \" category. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")require_reference_detector; cbf_detector require_reference_detector(unsigned int element_number){ cbf_detector detector; cbf_failnez(cbf_require_reference_detector(self,&detector,element_number)); return detector; } /* cfunc cbf_next_category pyfunc next_category arg cbf_handle handle */ %feature("autodoc", " Returns : *args : C prototype: int cbf_next_category (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_next_category makes the category following the current category in the current data block the current category. If there are no more categories, the function returns CBF_NOTFOUND. The current column and row become undefined. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")next_category; void next_category(void){ cbf_failnez(cbf_next_category(self));} /* cfunc cbf_set_diffrn_id pyfunc set_diffrn_id arg cbf_handle handle arg const char *diffrn_id */ %feature("autodoc", " Returns : string *args : C prototype: int cbf_set_diffrn_id (cbf_handle handle, const char *diffrn_id); CBFLib documentation: DESCRIPTION cbf_set_diffrn_id sets the \"diffrn.id \" entry of the current datablock to the ASCII value diffrn_id. This function also changes corresponding \"diffrn_id \" entries in the \"diffrn_source \", \"diffrn_radiation \", \"diffrn_detector \" and \"diffrn_measurement \" categories. ARGUMENTS handle CBF handle. diffrn_id ASCII value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_diffrn_id; void set_diffrn_id(const char* arg){ cbf_failnez(cbf_set_diffrn_id(self,arg));} %feature("autodoc", " Returns : *args : Float time,Integer timezone,Float precision C prototype: int cbf_set_timestamp (cbf_handle handle, unsigned int reserved, double time, int timezone, double precision); CBFLib documentation: DESCRIPTION cbf_set_timestamp sets the collection timestamp in seconds since January 1 1970 to the value specified by time. The timezone difference from UTC ")set_timestamp; void set_timestamp(double time, int timezone, double precision){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_set_timestamp(self,reserved,time,timezone,precision)); } %feature("autodoc", " Returns : Float matrix_0,Float matrix_1,Float matrix_2,Float matrix_3, Float matrix_4,Float matrix_5,Float matrix_6,Float matrix_7, Float matrix_8 *args : C prototype: int cbf_get_orientation_matrix (cbf_handle handle, double ub_matrix[9]); CBFLib documentation: DESCRIPTION cbf_get_orientation_matrix sets ub_matrix to point to the array of orientation matrix entries in the \"diffrn \" category in the order of columns: \"UB[1][1] \" \"UB[1][2] \" \"UB[1][3] \" \"UB[2][1] \" \"UB[2][2] \" \"UB[2][3] \" \"UB[3][1] \" \"UB[3][2] \" \"UB[3][3] \" cbf_set_orientation_matrix sets the values in the \"diffrn \" category to the values pointed to by ub_matrix. ARGUMENTS handle CBF handle. ubmatric Source or destination array of 9 doubles giving the orientation matrix parameters. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_orientation_matrix; %apply double *OUTPUT {double *m0,double *m1,double *m2, double *m3,double *m4, double *m5,double *m6, double *m7,double *m8 } get_orientation_matrix; void get_orientation_matrix( double *m0,double *m1, double *m2,double *m3,double *m4,double *m5,double *m6, double *m7,double *m8){ double m[9]; cbf_failnez(cbf_get_orientation_matrix(self,m)); *m0 = m[0]; *m1=m[1] ; *m2=m[2] ; *m3 = m[3]; *m4=m[4] ; *m5=m[5] ; *m6 = m[6]; *m7=m[7] ; *m8=m[8] ; } %feature("autodoc", " Returns : size_t ndimfast,size_t ndimslow *args : Integer element_number C prototype: int cbf_get_image_size_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimfast, size_t *ndimslow); CBFLib documentation: DESCRIPTION cbf_get_image_size, cbf_get_image_size_fs and cbf_get_image_size_sf set *ndimslow and *ndimfast to the slow and fast dimensions of the image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimfast will be set to 1. If the array is 3-dimensional an error code will be returned. cbf_get_3d_image_size, cbf_get_3d_image_size_fs and cbf_get_3d_image_size_sf set *ndimslow, *ndimmid and *ndimfast to the slowest, next fastest and fastest dimensions, respectively, of the 3D image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimmid and ")get_image_size_fs; %apply int *OUTPUT {int *ndimfast, int *ndimslow} get_image_size_fs; void get_image_size_fs(unsigned int element_number, int *ndimfast, int *ndimslow){ unsigned int reserved; size_t infast, inslow; reserved = 0; cbf_failnez(cbf_get_image_size_fs(self,reserved,element_number,&infast,&inslow)); *ndimfast = (int)infast; /* FIXME - is that how to convert? */ *ndimslow = (int)inslow; } %feature("autodoc", " Returns : Float div_x_source,Float div_y_source,Float div_x_y_source *args : C prototype: int cbf_get_divergence (cbf_handle handle, double *div_x_source, double *div_y_source, double *div_x_y_source); CBFLib documentation: DESCRIPTION cbf_get_divergence sets *div_x_source, *div_y_source and *div_x_y_source to the corresponding source divergence parameters. Any of the destination pointers may be NULL. ARGUMENTS handle CBF handle. div_x_source Pointer to the destination div_x_source. div_y_source Pointer to the destination div_y_source. div_x_y_source Pointer to the destination div_x_y_source. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_divergence; %apply double *OUTPUT {double *div_x_source, double *div_y_source, double *div_x_y_source } get_divergence; void get_divergence(double *div_x_source, double *div_y_source, double *div_x_y_source){ cbf_failnez(cbf_get_divergence(self, div_x_source, div_y_source, div_x_y_source)); } /* cfunc cbf_rewind_category pyfunc rewind_category arg cbf_handle handle */ %feature("autodoc", " Returns : *args : C prototype: int cbf_rewind_category (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_rewind_category makes the first category in the current data block the current category. cbf_rewind_saveframe makes the first saveframe in the current data block the current saveframe. cbf_rewind_blockitem makes the first blockitem (category or saveframe) in the current data block the current blockitem. The type of the blockitem (CBF_CATEGORY or CBF_SAVEFRAME) is returned in type. If there are no categories, saveframes or blockitems the function returns CBF_NOTFOUND. The current column and row become undefined. ARGUMENTS handle CBF handle. type CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")rewind_category; void rewind_category(void){ cbf_failnez(cbf_rewind_category(self));} %feature("autodoc", " Returns : *args : String filename C prototype: int cbf_read_template (cbf_handle handle, FILE *file); CBFLib documentation: DESCRIPTION cbf_read_template reads the CBF or CIF file file into the CBF object specified by handle and selects the first datablock as the current datablock. ARGUMENTS handle Pointer to a CBF handle. file Pointer to a file descriptor. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")read_template; void read_template(char* filename){ /* CBFlib needs a stream that will remain open hence DO NOT open from python */ FILE *stream; if ( ! ( stream = fopen (filename, "rb")) ){ cbf_failnez(CBF_FILEOPEN); } else{ cbf_failnez(cbf_read_template (self, stream)); } } /* cfunc cbf_select_row pyfunc select_row arg cbf_handle handle arg unsigned int row */ %feature("autodoc", " Returns : *args : Integer C prototype: int cbf_select_row (cbf_handle handle, unsigned int row); CBFLib documentation: DESCRIPTION cbf_select_row selects row number row in the current category as the current row. The first row is number 0. The current column is not affected If the row does not exist, the function returns CBF_NOTFOUND. ARGUMENTS handle CBF handle. row Number of the row to select. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")select_row; void select_row(unsigned int arg){ cbf_failnez(cbf_select_row(self,arg));} %feature("autodoc", " Returns : (Binary)String *args : int element_number,int elsize,int elsign,int ndimfast,int ndimslow C prototype: int cbf_get_image_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimfast, size_t ndimslow); CBFLib documentation: DESCRIPTION cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image array for element number element_number into an array. The array consists of ndimslow *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and cbf_get_real_image_sf read the image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. cbf_get_3d_image, cbf_get_3d_image_fs and cbf_get_3d_image_sf read the 3D image array for element number element_number into an array. The array consists of ndimslow *ndimmid *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order The structure of the array as a 1-, 2- or 3-dimensional array should agree with the structure of the array given in the ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1 both in the call and in the imgCIF data being processed. If the array is 2-dimensional and a 3D call is used, ndimslow and ndimmid should be the ")get_image_fs_as_string; // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_image_fs_as_string; // Get the length correct void get_image_fs_as_string(int element_number, char **s, int *slen, int elsize, int elsign, int ndimfast, int ndimslow){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimslow))) { cbf_failnez (cbf_get_image_fs(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, elsign, (size_t) ndimfast, (size_t)ndimslow)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimslow; *s = (char *) array; } %feature("autodoc", " Returns : size_t ndimslow,size_t ndimfast *args : Integer element_number C prototype: int cbf_get_image_size_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimslow, size_t *ndimfast); CBFLib documentation: DESCRIPTION cbf_get_image_size, cbf_get_image_size_fs and cbf_get_image_size_sf set *ndimslow and *ndimfast to the slow and fast dimensions of the image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimfast will be set to 1. If the array is 3-dimensional an error code will be returned. cbf_get_3d_image_size, cbf_get_3d_image_size_fs and cbf_get_3d_image_size_sf set *ndimslow, *ndimmid and *ndimfast to the slowest, next fastest and fastest dimensions, respectively, of the 3D image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimmid and ")get_image_size_sf; %apply int *OUTPUT {int *ndimslow, int *ndimfast} get_image_size_sf; void get_image_size_sf(unsigned int element_number, int *ndimslow, int *ndimfast){ unsigned int reserved; size_t inslow, infast; reserved = 0; cbf_failnez(cbf_get_image_size(self,reserved,element_number,&inslow,&infast)); *ndimslow = (int)inslow; *ndimfast = (int)infast; } %feature("autodoc", " Returns : (Binary)String *args : int element_number,int elsize,int ndimfast,int ndimslow C prototype: int cbf_get_real_image_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimfast, size_t ndimslow); CBFLib documentation: DESCRIPTION cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image array for element number element_number into an array. The array consists of ndimslow *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and cbf_get_real_image_sf read the image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. cbf_get_3d_image, cbf_get_3d_image_fs and cbf_get_3d_image_sf read the 3D image array for element number element_number into an array. The array consists of ndimslow *ndimmid *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order The structure of the array as a 1-, 2- or 3-dimensional array should agree with the structure of the array given in the ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1 both in the call and in the imgCIF data being processed. If the array is 2-dimensional and a 3D call is used, ndimslow and ndimmid should be the ")get_real_image_fs_as_string; // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_real_image_fs_as_string; // Get the length correct void get_real_image_fs_as_string(int element_number, char **s, int *slen, int elsize, int ndimfast, int ndimslow){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimslow))) { cbf_failnez (cbf_get_real_image_fs(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, (size_t) ndimfast, (size_t)ndimslow)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimslow; *s = (char *) array; } /* cfunc cbf_count_columns pyfunc count_columns arg cbf_handle handle arg unsigned int *columns */ %feature("autodoc", " Returns : Integer *args : C prototype: int cbf_count_columns (cbf_handle handle, unsigned int *columns); CBFLib documentation: DESCRIPTION cbf_count_columns puts the number of columns in the current category in *columns. ARGUMENTS handle CBF handle. columns Pointer to the destination column count. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")count_columns; unsigned int count_columns(void){ unsigned int result; cbf_failnez(cbf_count_columns(self,&result)); return result;} %feature("autodoc", " Returns : int compression,int binary_id,int elsize,int elsigned,int elunsigned, int elements,int minelement,int maxelement,char **bo,int *bolen, int dimfast,int dimmid,int dimslow,int padding *args : C prototype: int cbf_get_integerarrayparameters_wdims (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, int *elsigned, int *elunsigned, size_t *elements, int *minelement, int *maxelement, const char **byteorder, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding); CBFLib documentation: DESCRIPTION cbf_get_integerarrayparameters sets *compression, *binary_id, *elsize, *elsigned, *elunsigned, *elements, *minelement and *maxelement to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_integerarray, if a copy of the array is to be made into another CIF or CBF. cbf_get_realarrayparameters sets *compression, *binary_id, *elsize, *elements to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_realarray, if a copy of the arry is to be made into another CIF or CBF. The variants cbf_get_integerarrayparameters_wdims, cbf_get_integerarrayparameters_wdims_fs, cbf_get_integerarrayparameters_wdims_sf, cbf_get_realarrayparameters_wdims, cbf_get_realarrayparameters_wdims_fs, cbf_get_realarrayparameters_wdims_sf set **byteorder, *dimfast, *dimmid, *dimslow, and *padding as well, providing the additional parameters needed for a subsequent call to cbf_set_integerarray_wdims or cbf_set_realarray_wdims. The value returned in *byteorder is a pointer either to the string \"little_endian \" or to the string \"big_endian \". This should be the byte order of the data, not necessarily of the host machine. No attempt should be made to modify this string. At this time only \"little_endian \" will be returned. The values returned in *dimfast, *dimmid and *dimslow are the sizes of the fastest changing, second fastest changing and third fastest changing dimensions of the array, if specified, or zero, if not specified. The value returned in *padding is the size of the post-data padding, if any and if specified in the data header. The value is given as a count of octets. If the value is not binary, the function returns CBF_ASCII. ARGUMENTS handle CBF handle. compression Compression method used. elsize Size in bytes of each array element. binary_id Pointer to the destination integer binary identifier. elsigned Pointer to an integer. Set to 1 if the elements can be read as signed integers. elunsigned Pointer to an integer. Set to 1 if the elements can be read as unsigned integers. elements Pointer to the destination number of elements. minelement Pointer to the destination smallest element. maxelement Pointer to the destination largest element. byteorder Pointer to the destination byte order. dimfast Pointer to the destination fastest dimension. dimmid Pointer to the destination second fastest dimension. dimslow Pointer to the destination third fastest dimension. padding Pointer to the destination padding size. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")get_integerarrayparameters_wdims; %cstring_output_allocate_size(char **bo, int *bolen, free(*$1)); %apply int *OUTPUT {int *compression,int *binary_id, int *elsize, int *elsigned, int *elunsigned, int *elements, int *minelement, int *maxelement, int *dimfast, int *dimmid, int *dimslow, int *padding} get_integerarrayparameters_wdims; void get_integerarrayparameters_wdims(int *compression,int *binary_id, int *elsize, int *elsigned, int *elunsigned, int *elements, int *minelement, int *maxelement, char **bo, int *bolen, int *dimfast, int *dimmid, int *dimslow, int *padding ){ unsigned int comp; size_t elsiz, elem, df,dm,ds,pd; const char * byteorder; char * bot; cbf_failnez(cbf_get_integerarrayparameters_wdims(self, &comp,binary_id, &elsiz, elsigned, elunsigned, &elem, minelement, maxelement, &byteorder,&df,&dm,&ds,&pd )); *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)} strncpy(bot,byteorder,*bolen); *bo = bot; *compression = comp; *elsize = elsiz; *elements = elem; *dimfast = df; *dimmid = dm; *dimslow = ds; *padding = pd; } %feature("autodoc", " Returns : Float gain,Float gain_esd *args : C prototype: int cbf_get_gain (cbf_handle handle, unsigned int element_number, double *gain, double *gain_esd); CBFLib documentation: DESCRIPTION cbf_get_gain sets *gain and *gain_esd to the corresponding gain parameters for element number element_number. Either of the destination pointers may be NULL. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the \"diffrn_data_frame \" category. gain Pointer to the destination gain. gain_esd Pointer to the destination gain_esd. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_gain; %apply double *OUTPUT {double *gain, double *gain_esd} get_gain; void get_gain (unsigned int element_number, double *gain, double *gain_esd){ cbf_failnez(cbf_get_gain (self, element_number, gain, gain_esd)); } /* cfunc cbf_new_saveframe pyfunc new_saveframe arg cbf_handle handle arg const char *saveframename */ %feature("autodoc", " Returns : string *args : C prototype: int cbf_new_saveframe (cbf_handle handle, const char *saveframename); CBFLib documentation: DESCRIPTION cbf_new_datablock creates a new data block with name datablockname and makes it the current data block. cbf_new_saveframe creates a new save frame with name saveframename within the current data block and makes the new save frame the current save frame. If a data block or save frame with this name already exists, the existing data block or save frame becomes the current data block or save frame. ARGUMENTS handle CBF handle. datablockname The name of the new data block. saveframename The name of the new save frame. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")new_saveframe; void new_saveframe(const char* arg){ cbf_failnez(cbf_new_saveframe(self,arg));} %feature("autodoc", " Returns : *args : Float polarizn_source_ratio,Float polarizn_source_norm C prototype: int cbf_set_polarization (cbf_handle handle, double polarizn_source_ratio, double polarizn_source_norm); CBFLib documentation: DESCRIPTION cbf_set_polarization sets the source polarization to the values specified by polarizn_source_ratio and polarizn_source_norm. ARGUMENTS handle CBF handle. polarizn_source_ratio New value of polarizn_source_ratio. polarizn_source_norm New value of polarizn_source_norm. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_polarization; void set_polarization (double polarizn_source_ratio, double polarizn_source_norm){ cbf_failnez(cbf_set_polarization(self, polarizn_source_ratio, polarizn_source_norm)); } %feature("autodoc", " Returns : *args : int element_number,int compression,(binary) String data,int elsize, int dimslow,int dimmid,int dimfast C prototype: int cbf_set_real_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-zero and unsigned otherwise. cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow IEEE double or float elements of elsize bytes each, starting at array. cbf_set_3d_image, cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_set_real_3d_image, cbf_set_real_3d_image_fs and cbf_set_real_3d_image_sf writes the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow IEEE double or float elements of elsize bytes each, starting at array. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the array is 2-dimensional and the 3D calls are used, ndimslow and ndimmid should be used for the array dimensions and ndimfast should be set to 1. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \"byte_offset \" compression. CBF_NONE No compression. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned)for cbf_set_image, or IEEE doubles or floats for cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the \"diffrn_data_frame \" category. compression Compression type. array Pointer to the image array. elsize Size in bytes of each image array element. elsigned Set to non-0 if the image array elements are signed. ndimslow Slowest array dimension. ndimmid Second slowest array dimension. ndimfast Fastest array dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_real_3d_image; /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_real_3d_image_sf; void set_real_3d_image(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int ndimslow, int ndimmid, int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimmid*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_real_3d_image (self, reserved, element_number, compression, (void *) data, (size_t) elsize, (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ARGUMENT); } } /* cfunc cbf_delete_row pyfunc delete_row arg cbf_handle handle arg unsigned int rownumber */ %feature("autodoc", " Returns : *args : Integer C prototype: int cbf_delete_row (cbf_handle handle, unsigned int rownumber); CBFLib documentation: DESCRIPTION cbf_delete_row deletes a row from the current category. Rows starting from rownumber +1 are moved down by 1. If the current row was higher than rownumber, or if the current row is the last row, it will also move down by 1. The row numbers start from 0. ARGUMENTS handle CBF handle. rownumber The number of the row to delete. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")delete_row; void delete_row(unsigned int arg){ cbf_failnez(cbf_delete_row(self,arg));} /* cfunc cbf_column_name pyfunc column_name arg cbf_handle handle arg const char **columnname */ %feature("autodoc", " Returns : *args : string C prototype: int cbf_column_name (cbf_handle handle, const char **columnname); CBFLib documentation: DESCRIPTION cbf_column_name sets *columnname to point to the name of the current column of the current category. The column name will be valid as long as the column exists. The name must not be modified by the program in any way. ARGUMENTS handle CBF handle. columnname Pointer to the destination column name pointer. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")column_name; const char* column_name(void){ const char* result; cbf_failnez(cbf_column_name(self, &result)); return result;} /* cfunc cbf_remove_saveframe pyfunc remove_saveframe arg cbf_handle handle */ %feature("autodoc", " Returns : *args : C prototype: int cbf_remove_saveframe (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_remove_datablock deletes the current data block. cbf_remove_saveframe deletes the current save frame. The current data block becomes undefined. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")remove_saveframe; void remove_saveframe(void){ cbf_failnez(cbf_remove_saveframe(self));} %feature("autodoc", " Returns : *args : int compression,int binary_id,(binary) String data,int elsize, int elements,String byteorder,int dimslow,int dimmid,int dimfast, int padding C prototype: int cbf_set_integerarray_wdims_sf (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, int elsigned, size_t elements, const char *byteorder, size_t dimslow, size_t dimmid, size_t dimfast, size_t padding); CBFLib documentation: DESCRIPTION cbf_set_integerarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. The elements are signed if elsigned is non-0 and unsigned otherwise. binary_id is the binary section identifier. cbf_set_realarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. binary_id is the binary section identifier. The cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, cbf_set_integerarray_wdims_sf, cbf_set_realarray_wdims, cbf_set_realarray_wdims_fs and cbf_set_realarray_wdims_sf variants allow the data header values of byteorder, dimfast, dimmid, dimslow and padding to be set to the data byte order, the fastest, second fastest and third fastest array dimensions and the size in byte of the post data padding to be used. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \"byte_offset \" compression. CBF_NONE No compression. NOTE: This scheme is by far the slowest of the four and uses much more disk space. It is intended for routine use with small arrays only. With large arrays (like images) it should be used only for debugging. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned), for cbf_set_integerarray, or IEEE doubles or floats for cbf_set_realarray. If elsize is not equal to sizeof (char), sizeof (short) or sizeof (int), the function returns CBF_ARGUMENT. ARGUMENTS handle CBF handle. compression Compression method to use. binary_id Integer binary identifier. array Pointer to the source array. elsize Size in bytes of each source array element. elsigned Set to non-0 if the source array elements are signed. elements: The number of elements in the array. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")set_integerarray_wdims_sf; /* CBFlib must NOT modify the data string nor the byteorder string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_integerarray_wdims_sf; %apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_integerarray_wdims_sf; void set_integerarray_wdims_sf(unsigned int compression, int binary_id, char *data, int len, int elsize, int elsigned, int elements, char *bo, int bolen, int dimslow, int dimmid, int dimfast, int padding){ /* safety check on args */ size_t els, ele; void *array; char byteorder[15]; if(len == elsize*elements && elements==dimfast*dimmid*dimslow){ array = data; els = elsize; ele = elements; strncpy(byteorder,bo,bolen<15?bolen:14); byteorder[bolen<15?14:bolen] = 0; cbf_failnez(cbf_set_integerarray_wdims_sf (self, compression, binary_id, (void *) data, (size_t) elsize, elsigned, (size_t) elements, (const char *)byteorder, (size_t)dimslow, (size_t)dimmid, (size_t)dimfast, (size_t)padding)); }else{ cbf_failnez(CBF_ARGUMENT); } } %feature("autodoc", " Returns : String Value *args : String defaultvalue C prototype: int cbf_require_value (cbf_handle handle, const char **value, const char *defaultvalue ); CBFLib documentation: DESCRIPTION cbf_get_value sets *value to point to the ASCII value of the item at the current column and row. cbf_require_value sets *value to point to the ASCII value of the item at the current column and row, creating the data item if necessary and initializing it to a copy of defaultvalue. If the value is not ASCII, the function returns CBF_BINARY. The value will be valid as long as the item exists and has not been set to a new value. The value must not be modified by the program in any way. ARGUMENTS handle CBF handle. value Pointer to the destination value pointer. defaultvalue Default value character string. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")require_value; const char* require_value(const char* defaultvalue){ const char * result; cbf_failnez(cbf_require_value(self, &result, defaultvalue)); return result; } %feature("autodoc", " Returns : Int Value *args : String Columnvalue,Int default C prototype: int cbf_require_column_integervalue (cbf_handle handle, const char *columnname, int *number, const int defaultvalue); CBFLib documentation: DESCRIPTION cbf_require_column_doublevalue sets *number to the value of the ASCII item at the current row for the column given with the name given by *columnname, with the value interpreted as an integer number, or to the number given by defaultvalue if the item cannot be found. ARGUMENTS handle CBF handle. columnname Name of the column containing the number. number pointer to the location to receive the integer value. defaultvalue Value to use if the requested column and value cannot be found. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")require_column_integervalue; %apply int *OUTPUT {int *number} require_column_integervalue; void require_column_integervalue(const char *columnname, int *number, const int defaultvalue){ cbf_failnez(cbf_require_column_integervalue(self, columnname, number,defaultvalue)); } %feature("autodoc", " Returns : *args : Int element_number,Int axis_number,Float pixel size C prototype: int cbf_set_pixel_size (cbf_handle handle, unsigned int element_number, int axis_number, double psize); CBFLib documentation: DESCRIPTION cbf_set_pixel_size and cbf_set_pixel_size_sf set the item in the "e;size"e; column of the \"array_structure_list \" category at the row which matches axis axis_number of the detector element element_number converting the double pixel size psize from meters to millimeters in storing it in the \"size \" column for the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the slowest axis. cbf_set_pixel_size_fs sets the item ")set_pixel_size; void set_pixel_size (unsigned int element_number, unsigned int axis_number, double psize){ cbf_failnez(cbf_set_pixel_size(self, element_number, axis_number, psize)); } /* cfunc cbf_next_column pyfunc next_column arg cbf_handle handle */ %feature("autodoc", " Returns : *args : C prototype: int cbf_next_column (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_next_column makes the column following the current column in the current category the current column. If there are no more columns, the function returns CBF_NOTFOUND. The current row is not affected. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")next_column; void next_column(void){ cbf_failnez(cbf_next_column(self));} %feature("autodoc", " Returns : size_t ndimslow,size_t ndimmid,size_t ndimfast *args : Integer element_number C prototype: int cbf_get_3d_image_size_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimslow, size_t *ndimmid, size_t *ndimfast); CBFLib documentation: DESCRIPTION cbf_get_image_size, cbf_get_image_size_fs and cbf_get_image_size_sf set *ndimslow and *ndimfast to the slow and fast dimensions of the image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimfast will be set to 1. If the array is 3-dimensional an error code will be returned. cbf_get_3d_image_size, cbf_get_3d_image_size_fs and cbf_get_3d_image_size_sf set *ndimslow, *ndimmid and *ndimfast to the slowest, next fastest and fastest dimensions, respectively, of the 3D image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimmid and ")get_3d_image_size_sf; %apply int *OUTPUT {int *ndimslow, int *ndimmid, int *ndimfast} get_3d_image_size_sf; void get_3d_image_size_sf(unsigned int element_number, int *ndimslow, int *ndimmid, int *ndimfast){ unsigned int reserved; size_t inslow, inmid, infast; reserved = 0; cbf_failnez(cbf_get_3d_image_size_sf(self,reserved,element_number,&inslow,&inmid,&infast)); *ndimslow = (int)inslow; /* FIXME - is that how to convert? */ *ndimmid = (int)inmid; *ndimfast = (int)infast; } %feature("autodoc", " Returns : int compression,int binary_id,int elsize,int elements,char **bo, int *bolen,int dimfast,int dimmid,int dimslow,int padding *args : C prototype: int cbf_get_realarrayparameters_wdims_fs (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, size_t *elements, const char **byteorder, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding); CBFLib documentation: DESCRIPTION cbf_get_integerarrayparameters sets *compression, *binary_id, *elsize, *elsigned, *elunsigned, *elements, *minelement and *maxelement to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_integerarray, if a copy of the array is to be made into another CIF or CBF. cbf_get_realarrayparameters sets *compression, *binary_id, *elsize, *elements to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_realarray, if a copy of the arry is to be made into another CIF or CBF. The variants cbf_get_integerarrayparameters_wdims, cbf_get_integerarrayparameters_wdims_fs, cbf_get_integerarrayparameters_wdims_sf, cbf_get_realarrayparameters_wdims, cbf_get_realarrayparameters_wdims_fs, cbf_get_realarrayparameters_wdims_sf set **byteorder, *dimfast, *dimmid, *dimslow, and *padding as well, providing the additional parameters needed for a subsequent call to cbf_set_integerarray_wdims or cbf_set_realarray_wdims. The value returned in *byteorder is a pointer either to the string \"little_endian \" or to the string \"big_endian \". This should be the byte order of the data, not necessarily of the host machine. No attempt should be made to modify this string. At this time only \"little_endian \" will be returned. The values returned in *dimfast, *dimmid and *dimslow are the sizes of the fastest changing, second fastest changing and third fastest changing dimensions of the array, if specified, or zero, if not specified. The value returned in *padding is the size of the post-data padding, if any and if specified in the data header. The value is given as a count of octets. If the value is not binary, the function returns CBF_ASCII. ARGUMENTS handle CBF handle. compression Compression method used. elsize Size in bytes of each array element. binary_id Pointer to the destination integer binary identifier. elsigned Pointer to an integer. Set to 1 if the elements can be read as signed integers. elunsigned Pointer to an integer. Set to 1 if the elements can be read as unsigned integers. elements Pointer to the destination number of elements. minelement Pointer to the destination smallest element. maxelement Pointer to the destination largest element. byteorder Pointer to the destination byte order. dimfast Pointer to the destination fastest dimension. dimmid Pointer to the destination second fastest dimension. dimslow Pointer to the destination third fastest dimension. padding Pointer to the destination padding size. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")get_realarrayparameters_wdims_fs; %cstring_output_allocate_size(char **bo, int *bolen, free(*$1)); %apply int *OUTPUT {int *compression,int *binary_id, int *elsize, int *elements, int *dimslow, int *dimmid, int *dimfast, int *padding} get_realarrayparameters_wdims_fs; void get_realarrayparameters_wdims_fs(int *compression,int *binary_id, int *elsize, int *elements, char **bo, int *bolen, int *dimfast, int *dimmid, int *dimslow, int *padding ){ unsigned int comp; size_t elsiz, elem, df,dm,ds,pd; const char * byteorder; char * bot; cbf_failnez(cbf_get_realarrayparameters_wdims_fs(self, &comp,binary_id, &elsiz, &elem, &byteorder,&ds,&dm,&ds,&pd )); *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)} strncpy(bot,byteorder,*bolen); *bo = bot; *compression = comp; *elsize = elsiz; *elements = elem; *dimfast = df; *dimmid = dm; *dimslow = ds; *padding = pd; } %feature("autodoc", " Returns : (Binary)String *args : C prototype: int cbf_get_realarray (cbf_handle handle, int *binary_id, void *array, size_t elsize, size_t elements, size_t *elements_read); CBFLib documentation: DESCRIPTION cbf_get_integerarray reads the binary value of the item at the current column and row into an integer array. The array consists of elements elements of elsize bytes each, starting at array. The elements are signed if elsigned is non-0 and unsigned otherwise. *binary_id is set to the binary section identifier and *elements_read to the number of elements actually read. cbf_get_realarray reads the binary value of the item at the current column and row into a real array. The array consists of elements elements of elsize bytes each, starting at array. *binary_id is set to the binary section identifier and *elements_read to the number of elements actually read. If any element in the integer binary data cant fit into the destination element, the destination is set the nearest possible value. If the value is not binary, the function returns CBF_ASCII. If the requested number of elements cant be read, the function will read as many as it can and then return CBF_ENDOFDATA. Currently, the destination array must consist of chars, shorts or ints (signed or unsigned). If elsize is not equal to sizeof (char), sizeof (short) or sizeof (int), for cbf_get_integerarray, or sizeof(double) or sizeof(float), for cbf_get_realarray the function returns CBF_ARGUMENT. An additional restriction in the current version of CBFlib is that values too large to fit in an int are not correctly decompressed. As an example, if the machine with 32-bit ints is reading an array containing a value outside the range 0 .. 2^32-1 (unsigned) or -2^31 .. 2^31-1 (signed), the array will not be correctly decompressed. This restriction will be removed in a future release. For cbf_get_realarray, only IEEE format is supported. No conversion to other floating point formats is done at this time. ARGUMENTS handle CBF handle. binary_id Pointer to the destination integer binary identifier. array Pointer to the destination array. elsize Size in bytes of each destination array element. elsigned Set to non-0 if the destination array elements are signed. elements The number of elements to read. elements_read Pointer to the destination number of elements actually read. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")get_realarray_as_string; // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_realarray_as_string; // Get the length correct void get_realarray_as_string(char **s, int *slen){ int binary_id; size_t elements, elements_read, elsize; unsigned int compression; void * array; *slen = 0; /* Initialise in case of problems */ cbf_failnez(cbf_get_realarrayparameters(self, &compression, &binary_id, &elsize, &elements)); if ((array=malloc(elsize*elements))) { /* cbf_failnez (cbf_select_column(cbf,colnum)) */ cbf_failnez (cbf_get_realarray(self, &binary_id, (void *)array, elsize, elements, &elements_read)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*elements; *s = (char *) array; } %feature("autodoc", " Returns : Float slowbinsize,Float fastbinsize *args : Integer element_number C prototype: int cbf_get_bin_sizes(cbf_handle handle, unsigned int element_number, double * slowbinsize, double * fastbinsize); CBFLib documentation: DESCRIPTION cbf_get_bin_sizes sets slowbinsize to point to the value of the number of pixels composing one array element in the dimension that changes at the second-fastest rate and fastbinsize to point to the value of the number of pixels composing one array element in the dimension that changes at the fastest rate for the dectector element with the ordinal element_number. cbf_set_bin_sizes sets the the pixel bin sizes in the \"array_intensities \" category to the values of slowbinsize_in for the number of pixels composing one array element in the dimension that changes at the second-fastest rate and fastbinsize_in for the number of pixels composing one array element in the dimension that changes at the fastest rate for the dectector element with the ordinal element_number. In order to allow for software binning involving fractions of pixels, the bin sizes are doubles rather than ints. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the \"diffrn_data_frame \" category. slowbinsize Pointer to the returned number of pixels composing one array element in the dimension that changes at the second-fastest rate. fastbinsize Pointer to the returned number of pixels composing one array element in the dimension that changes at the fastest rate. slowbinsize_in The number of pixels composing one array element in the dimension that changes at the second-fastest rate. fastbinsize_in The number of pixels composing one array element in the dimension that changes at the fastest rate. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_bin_sizes; %apply double *OUTPUT {double *slowbinsize,double *fastbinsize}; void get_bin_sizes(int element_number, double *slowbinsize, double *fastbinsize) { cbf_failnez(cbf_get_bin_sizes (self, (unsigned int)element_number, slowbinsize, fastbinsize)); } /* cfunc cbf_reset_category pyfunc reset_category arg cbf_handle handle */ %feature("autodoc", " Returns : *args : C prototype: int cbf_reset_category (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_reset_category deletes all columns and rows from current category. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")reset_category; void reset_category(void){ cbf_failnez(cbf_reset_category(self));} %feature("autodoc", " Returns : pycbf goniometer object *args : C prototype: int cbf_construct_goniometer (cbf_handle handle, cbf_goniometer *goniometer); CBFLib documentation: DESCRIPTION cbf_construct_goniometer constructs a goniometer object using the description in the CBF object handle and initialises the goniometer handle *goniometer. ARGUMENTS handle CBF handle. goniometer Pointer to the destination goniometer handle. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")construct_goniometer; cbf_goniometer construct_goniometer(){ cbf_goniometer goniometer; cbf_failnez(cbf_construct_goniometer(self,&goniometer)); return goniometer; } /* cfunc cbf_set_datablockname pyfunc set_datablockname arg cbf_handle handle arg const char *datablockname */ %feature("autodoc", " Returns : string *args : C prototype: int cbf_set_datablockname (cbf_handle handle, const char *datablockname); CBFLib documentation: DESCRIPTION cbf_set_datablockname changes the name of the current data block to datablockname. cbf_set_saveframename changes the name of the current save frame to saveframename. If a data block or save frame with this name already exists (comparison is case-insensitive), the function returns CBF_IDENTICAL. ARGUMENTS handle CBF handle. datablockname The new data block name. datablockname The new save frame name. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")set_datablockname; void set_datablockname(const char* arg){ cbf_failnez(cbf_set_datablockname(self,arg));} /* cfunc cbf_set_crystal_id pyfunc set_crystal_id arg cbf_handle handle arg const char *crystal_id */ %feature("autodoc", " Returns : string *args : C prototype: int cbf_set_crystal_id (cbf_handle handle, const char *crystal_id); CBFLib documentation: DESCRIPTION cbf_set_crystal_id sets the \"diffrn.crystal_id \" entry to the ASCII value crystal_id. ARGUMENTS handle CBF handle. crystal_id ASCII value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_crystal_id; void set_crystal_id(const char* arg){ cbf_failnez(cbf_set_crystal_id(self,arg));} %feature("autodoc", " Returns : (Binary)String *args : C prototype: int cbf_get_integerarray (cbf_handle handle, int *binary_id, void *array, size_t elsize, int elsigned, size_t elements, size_t *elements_read); CBFLib documentation: DESCRIPTION cbf_get_integerarray reads the binary value of the item at the current column and row into an integer array. The array consists of elements elements of elsize bytes each, starting at array. The elements are signed if elsigned is non-0 and unsigned otherwise. *binary_id is set to the binary section identifier and *elements_read to the number of elements actually read. cbf_get_realarray reads the binary value of the item at the current column and row into a real array. The array consists of elements elements of elsize bytes each, starting at array. *binary_id is set to the binary section identifier and *elements_read to the number of elements actually read. If any element in the integer binary data cant fit into the destination element, the destination is set the nearest possible value. If the value is not binary, the function returns CBF_ASCII. If the requested number of elements cant be read, the function will read as many as it can and then return CBF_ENDOFDATA. Currently, the destination array must consist of chars, shorts or ints (signed or unsigned). If elsize is not equal to sizeof (char), sizeof (short) or sizeof (int), for cbf_get_integerarray, or sizeof(double) or sizeof(float), for cbf_get_realarray the function returns CBF_ARGUMENT. An additional restriction in the current version of CBFlib is that values too large to fit in an int are not correctly decompressed. As an example, if the machine with 32-bit ints is reading an array containing a value outside the range 0 .. 2^32-1 (unsigned) or -2^31 .. 2^31-1 (signed), the array will not be correctly decompressed. This restriction will be removed in a future release. For cbf_get_realarray, only IEEE format is supported. No conversion to other floating point formats is done at this time. ARGUMENTS handle CBF handle. binary_id Pointer to the destination integer binary identifier. array Pointer to the destination array. elsize Size in bytes of each destination array element. elsigned Set to non-0 if the destination array elements are signed. elements The number of elements to read. elements_read Pointer to the destination number of elements actually read. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")get_integerarray_as_string; // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_integerarray_as_string; // Get the length correct void get_integerarray_as_string(char **s, int *slen){ int binary_id, elsigned, elunsigned; size_t elements, elements_read, elsize; int minelement, maxelement; unsigned int compression; void * array; *slen = 0; /* Initialise in case of problems */ cbf_failnez(cbf_get_integerarrayparameters(self, &compression, &binary_id, &elsize, &elsigned, &elunsigned, &elements, &minelement, &maxelement)); if ((array=malloc(elsize*elements))) { /* cbf_failnez (cbf_select_column(cbf,colnum)) */ cbf_failnez (cbf_get_integerarray(self, &binary_id, (void *)array, elsize, elsigned, elements, &elements_read)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*elements; *s = (char *) array; } %feature("autodoc", " Returns : *args : int element_number,int compression,(binary) String data,int elsize, int elsign,int dimslow,int dimmid,int dimfast C prototype: int cbf_set_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-zero and unsigned otherwise. cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow IEEE double or float elements of elsize bytes each, starting at array. cbf_set_3d_image, cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_set_real_3d_image, cbf_set_real_3d_image_fs and cbf_set_real_3d_image_sf writes the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow IEEE double or float elements of elsize bytes each, starting at array. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the array is 2-dimensional and the 3D calls are used, ndimslow and ndimmid should be used for the array dimensions and ndimfast should be set to 1. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \"byte_offset \" compression. CBF_NONE No compression. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned)for cbf_set_image, or IEEE doubles or floats for cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the \"diffrn_data_frame \" category. compression Compression type. array Pointer to the image array. elsize Size in bytes of each image array element. elsigned Set to non-0 if the image array elements are signed. ndimslow Slowest array dimension. ndimmid Second slowest array dimension. ndimfast Fastest array dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_3d_image; /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_3d_image; void set_3d_image(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int elsign, int ndimslow, int ndimmid, int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimmid*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_3d_image (self, reserved, element_number, compression, (void *) data, (size_t) elsize, elsign, (size_t) ndimslow, (size_t) ndimmid, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ARGUMENT); } } %feature("autodoc", " Returns : *args : CBFHandle dictionary C prototype: int cbf_set_dictionary (cbf_handle handle, cbf_handle dictionary_in); CBFLib documentation: DESCRIPTION cbf_get_dictionary sets *dictionary to the handle of a CBF which has been associated with the CBF handle by cbf_set_dictionary. cbf_set_dictionary associates the CBF handle dictionary_in with handle as its dictionary. cbf_require_dictionary sets *dictionary to the handle of a CBF which has been associated with the CBF handle by cbf_set_dictionary or creates a new empty CBF and associates it with handle, returning the new handle in *dictionary. ARGUMENTS handle CBF handle. dictionary Pointer to CBF handle of dictionary. dictionary_in CBF handle of dcitionary. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_dictionary; void set_dictionary(cbf_handle other){ cbf_failnez(cbf_set_dictionary(self,other)); } %feature("autodoc", " Returns : String categoryname *args : String tagname C prototype: int cbf_find_tag_category (cbf_handle handle, const char* tagname, const char** categoryname); CBFLib documentation: DESCRIPTION cbf_find_tag_category sets categoryname to the category associated with tagname in the dictionary associated with handle. cbf_set_tag_category upddates the dictionary associated with handle to indicated that tagname is in category categoryname_in. ARGUMENTS handle CBF handle. tagname tag name. categoryname pointer to a returned category name. categoryname_in input category name. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")find_tag_category; const char * find_tag_category(const char *tagname){ const char * result; cbf_failnez(cbf_find_tag_category(self,tagname, &result)); return result; } %feature("autodoc", " Returns : (Binary)String *args : int element_number,int elsize,int ndimslow,int ndimmid,int ndimfast C prototype: int cbf_get_real_3d_image_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image array for element number element_number into an array. The array consists of ndimslow *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and cbf_get_real_image_sf read the image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. cbf_get_3d_image, cbf_get_3d_image_fs and cbf_get_3d_image_sf read the 3D image array for element number element_number into an array. The array consists of ndimslow *ndimmid *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order The structure of the array as a 1-, 2- or 3-dimensional array should agree with the structure of the array given in the ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1 both in the call and in the imgCIF data being processed. If the array is 2-dimensional and a 3D call is used, ndimslow and ndimmid should be the ")get_real_3d_image_sf_as_string; // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_real_3d_image_sf_as_string; // Get the length correct void get_real_3d_image_sf_as_string(int element_number, char **s, int *slen, int elsize, int ndimslow, int ndimmid, int ndimfast){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) { cbf_failnez (cbf_get_real_3d_image_sf(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimmid*ndimslow; *s = (char *) array; } /* cfunc cbf_set_typeofvalue pyfunc set_typeofvalue arg cbf_handle handle arg const char *typeofvalue */ %feature("autodoc", " Returns : string *args : C prototype: int cbf_set_typeofvalue (cbf_handle handle, const char *typeofvalue); CBFLib documentation: DESCRIPTION cbf_set_typeofvalue sets the type of the item at the current column and row to the type specified by the ASCII character string given by typeofvalue. The strings that may be used are: \"null \" for a null value indicated by a \". \" or a \"? \" \"bnry \" for a binary value \"word \" for an unquoted string \"dblq \" for a double-quoted string \"sglq \" for a single-quoted string \"text \" for a semicolon-quoted string (multiline text field) \"prns \" for a parenthesis-bracketed string (multiline text field) \"brcs \" for a brace-bracketed string (multiline text field) \"bkts \" for a square-bracket-bracketed string (multiline text field) \"tsqs \" for a treble-single-quote quoted string (multiline text field) \"tdqs \" for a treble-double-quote quoted string (multiline text field) Not all types may be used for all values. Not all types are valid for all type of CIF files. In partcular the types \"prns \", \"brcs \", \"bkts \" were introduced with DDLm and are not valid in DDL1 or DDL2 CIFS. The types \"tsqs \" and \"tdqs \" are not formally part of the CIF syntax. No changes may be made to the type of binary values. You may not set the type of a string that contains a single quote followed by a blank or a tab or which contains multiple lines to \"sglq \". You may not set the type of a string that contains a double quote followed by a blank or a tab or which contains multiple lines to \"dblq \". ARGUMENTS handle CBF handle. typeofvalue ASCII string for desired type of value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")set_typeofvalue; void set_typeofvalue(const char* arg){ cbf_failnez(cbf_set_typeofvalue(self,arg));} %feature("autodoc", " Returns : *args : int compression,int binary_id,(binary) String data,int elsize, int elements,String byteorder,int dimfast,int dimmid,int dimslow, int padding C prototype: int cbf_set_integerarray_wdims (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, int elsigned, size_t elements, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); CBFLib documentation: DESCRIPTION cbf_set_integerarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. The elements are signed if elsigned is non-0 and unsigned otherwise. binary_id is the binary section identifier. cbf_set_realarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. binary_id is the binary section identifier. The cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, cbf_set_integerarray_wdims_sf, cbf_set_realarray_wdims, cbf_set_realarray_wdims_fs and cbf_set_realarray_wdims_sf variants allow the data header values of byteorder, dimfast, dimmid, dimslow and padding to be set to the data byte order, the fastest, second fastest and third fastest array dimensions and the size in byte of the post data padding to be used. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \"byte_offset \" compression. CBF_NONE No compression. NOTE: This scheme is by far the slowest of the four and uses much more disk space. It is intended for routine use with small arrays only. With large arrays (like images) it should be used only for debugging. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned), for cbf_set_integerarray, or IEEE doubles or floats for cbf_set_realarray. If elsize is not equal to sizeof (char), sizeof (short) or sizeof (int), the function returns CBF_ARGUMENT. ARGUMENTS handle CBF handle. compression Compression method to use. binary_id Integer binary identifier. array Pointer to the source array. elsize Size in bytes of each source array element. elsigned Set to non-0 if the source array elements are signed. elements: The number of elements in the array. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")set_integerarray_wdims; /* CBFlib must NOT modify the data string nor the byteorder string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_integerarray_wdims; %apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_integerarray_wdims; void set_integerarray_wdims(unsigned int compression, int binary_id, char *data, int len, int elsize, int elsigned, int elements, char *bo, int bolen, int dimfast, int dimmid, int dimslow, int padding){ /* safety check on args */ size_t els, ele; void *array; char byteorder[15]; if(len == elsize*elements && elements==dimfast*dimmid*dimslow){ array = data; els = elsize; ele = elements; strncpy(byteorder,bo,bolen<15?bolen:14); byteorder[bolen<15?14:bolen] = 0; cbf_failnez(cbf_set_integerarray_wdims (self, compression, binary_id, (void *) data, (size_t) elsize, elsigned, (size_t) elements, (const char *)byteorder, (size_t)dimfast, (size_t)dimmid, (size_t)dimslow, (size_t)padding)); }else{ cbf_failnez(CBF_ARGUMENT); } } %feature("autodoc", " Returns : *args : Float time C prototype: int cbf_set_integration_time (cbf_handle handle, unsigned int reserved, double time); CBFLib documentation: DESCRIPTION cbf_set_integration_time sets the integration time in seconds to the value specified by time. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. time Integration time in seconds. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_integration_time; void set_integration_time(double time){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_set_integration_time(self,reserved,time)); } %feature("autodoc", " Returns : *args : String axis_id,Float start,Float increment C prototype: int cbf_set_axis_setting (cbf_handle handle, unsigned int reserved, const char *axis_id, double start, double increment); CBFLib documentation: DESCRIPTION cbf_set_axis_setting sets the starting and increment values of the axis axis_id to start and increment. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. axis_id Axis id. start Start value. increment Increment value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_axis_setting; void set_axis_setting(const char *axis_id, double start, double increment){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_set_axis_setting(self,reserved, axis_id,start,increment)); } %feature("autodoc", " Returns : (Binary)String *args : int element_number,int elsize,int ndimslow,int ndimfast C prototype: int cbf_get_real_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimslow, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image array for element number element_number into an array. The array consists of ndimslow *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and cbf_get_real_image_sf read the image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. cbf_get_3d_image, cbf_get_3d_image_fs and cbf_get_3d_image_sf read the 3D image array for element number element_number into an array. The array consists of ndimslow *ndimmid *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order The structure of the array as a 1-, 2- or 3-dimensional array should agree with the structure of the array given in the ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1 both in the call and in the imgCIF data being processed. If the array is 2-dimensional and a 3D call is used, ndimslow and ndimmid should be the ")get_real_image_as_string; // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_real_image_as_string; // Get the length correct void get_real_image_as_string(int element_number, char **s, int *slen, int elsize, int ndimslow, int ndimfast){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimslow))) { cbf_failnez (cbf_get_real_image(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, (size_t) ndimslow, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimslow; *s = (char *) array; } %feature("autodoc", " Returns : (Binary)String *args : int element_number,int elsize,int elsign,int ndimslow,int ndimmid, int ndimfast C prototype: int cbf_get_3d_image_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image array for element number element_number into an array. The array consists of ndimslow *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and cbf_get_real_image_sf read the image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. cbf_get_3d_image, cbf_get_3d_image_fs and cbf_get_3d_image_sf read the 3D image array for element number element_number into an array. The array consists of ndimslow *ndimmid *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order The structure of the array as a 1-, 2- or 3-dimensional array should agree with the structure of the array given in the ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1 both in the call and in the imgCIF data being processed. If the array is 2-dimensional and a 3D call is used, ndimslow and ndimmid should be the ")get_3d_image_sf_as_string; // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_3d_image_sf_as_string; // Get the length correct void get_3d_image_sf_as_string(int element_number, char **s, int *slen, int elsize, int elsign, int ndimfast, int ndimmid, int ndimslow){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) { cbf_failnez (cbf_get_3d_image_sf(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, elsign, (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimmid*ndimslow; *s = (char *) array; } %feature("autodoc", " Returns : *args : int element_number,int compression,(binary) String data,int elsize, int dimfast,int dimslow C prototype: int cbf_set_real_image_fs(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimfast, size_t ndimslow); CBFLib documentation: DESCRIPTION cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-zero and unsigned otherwise. cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow IEEE double or float elements of elsize bytes each, starting at array. cbf_set_3d_image, cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_set_real_3d_image, cbf_set_real_3d_image_fs and cbf_set_real_3d_image_sf writes the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow IEEE double or float elements of elsize bytes each, starting at array. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the array is 2-dimensional and the 3D calls are used, ndimslow and ndimmid should be used for the array dimensions and ndimfast should be set to 1. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \"byte_offset \" compression. CBF_NONE No compression. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned)for cbf_set_image, or IEEE doubles or floats for cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the \"diffrn_data_frame \" category. compression Compression type. array Pointer to the image array. elsize Size in bytes of each image array element. elsigned Set to non-0 if the image array elements are signed. ndimslow Slowest array dimension. ndimmid Second slowest array dimension. ndimfast Fastest array dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_real_image_fs; /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_real_image; void set_real_image_fs(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int ndimfast, int ndimslow){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_real_image_fs (self, reserved, element_number, compression, (void *) data, (size_t) elsize, (size_t) ndimfast, (size_t)ndimslow)); }else{ cbf_failnez(CBF_ARGUMENT); } } %feature("autodoc", " Returns : Float overload *args : Integer element_number C prototype: int cbf_get_overload (cbf_handle handle, unsigned int element_number, double *overload); CBFLib documentation: DESCRIPTION cbf_get_overload sets *overload to the overload value for element number element_number. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the \"diffrn_data_frame \" category. overload Pointer to the destination overload. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_overload; %apply double *OUTPUT {double *overload} get_overload; void get_overload(unsigned int element_number, double *overload){ cbf_failnez(cbf_get_overload(self,element_number,overload)); } /* cfunc cbf_get_wavelength pyfunc get_wavelength arg cbf_handle handle arg double *wavelength */ %feature("autodoc", " Returns : double *args : C prototype: int cbf_get_wavelength (cbf_handle handle, double *wavelength); CBFLib documentation: DESCRIPTION cbf_get_wavelength sets *wavelength to the current wavelength in AA. ARGUMENTS handle CBF handle. wavelength Pointer to the destination. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_wavelength; double get_wavelength(void){ double result; cbf_failnez(cbf_get_wavelength(self,&result)); return result;} /* cfunc cbf_next_datablock pyfunc next_datablock arg cbf_handle handle */ %feature("autodoc", " Returns : *args : C prototype: int cbf_next_datablock (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_next_datablock makes the data block following the current data block the current data block. If there are no more data blocks, the function returns CBF_NOTFOUND. The current category becomes undefined. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")next_datablock; void next_datablock(void){ cbf_failnez(cbf_next_datablock(self));} %feature("autodoc", " Returns : int compression,int binary_id,int elsize,int elements,char **bo, int *bolen,int dimfast,int dimmid,int dimslow,int padding *args : C prototype: int cbf_get_realarrayparameters_wdims (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, size_t *elements, const char **byteorder, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding); CBFLib documentation: DESCRIPTION cbf_get_integerarrayparameters sets *compression, *binary_id, *elsize, *elsigned, *elunsigned, *elements, *minelement and *maxelement to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_integerarray, if a copy of the array is to be made into another CIF or CBF. cbf_get_realarrayparameters sets *compression, *binary_id, *elsize, *elements to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_realarray, if a copy of the arry is to be made into another CIF or CBF. The variants cbf_get_integerarrayparameters_wdims, cbf_get_integerarrayparameters_wdims_fs, cbf_get_integerarrayparameters_wdims_sf, cbf_get_realarrayparameters_wdims, cbf_get_realarrayparameters_wdims_fs, cbf_get_realarrayparameters_wdims_sf set **byteorder, *dimfast, *dimmid, *dimslow, and *padding as well, providing the additional parameters needed for a subsequent call to cbf_set_integerarray_wdims or cbf_set_realarray_wdims. The value returned in *byteorder is a pointer either to the string \"little_endian \" or to the string \"big_endian \". This should be the byte order of the data, not necessarily of the host machine. No attempt should be made to modify this string. At this time only \"little_endian \" will be returned. The values returned in *dimfast, *dimmid and *dimslow are the sizes of the fastest changing, second fastest changing and third fastest changing dimensions of the array, if specified, or zero, if not specified. The value returned in *padding is the size of the post-data padding, if any and if specified in the data header. The value is given as a count of octets. If the value is not binary, the function returns CBF_ASCII. ARGUMENTS handle CBF handle. compression Compression method used. elsize Size in bytes of each array element. binary_id Pointer to the destination integer binary identifier. elsigned Pointer to an integer. Set to 1 if the elements can be read as signed integers. elunsigned Pointer to an integer. Set to 1 if the elements can be read as unsigned integers. elements Pointer to the destination number of elements. minelement Pointer to the destination smallest element. maxelement Pointer to the destination largest element. byteorder Pointer to the destination byte order. dimfast Pointer to the destination fastest dimension. dimmid Pointer to the destination second fastest dimension. dimslow Pointer to the destination third fastest dimension. padding Pointer to the destination padding size. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")get_realarrayparameters_wdims; %cstring_output_allocate_size(char **bo, int *bolen, free(*$1)); %apply int *OUTPUT {int *compression,int *binary_id, int *elsize, int *elements, int *dimslow, int *dimmid, int *dimfast, int *padding} get_realarrayparameters_wdims; void get_realarrayparameters_wdims(int *compression,int *binary_id, int *elsize, int *elements, char **bo, int *bolen, int *dimfast, int *dimmid, int *dimslow, int *padding ){ unsigned int comp; size_t elsiz, elem, df,dm,ds,pd; const char * byteorder; char * bot; cbf_failnez(cbf_get_realarrayparameters_wdims(self, &comp,binary_id, &elsiz, &elem, &byteorder,&ds,&dm,&ds,&pd )); *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)} strncpy(bot,byteorder,*bolen); *bo = bot; *compression = comp; *elsize = elsiz; *elements = elem; *dimfast = df; *dimmid = dm; *dimslow = ds; *padding = pd; } %feature("autodoc", " Returns : *args : Float matrix_0,Float matrix_1,Float matrix_2,Float matrix_3, Float matrix_4,Float matrix_5,Float matrix_6,Float matrix_7, Float matrix_8 C prototype: int cbf_set_orientation_matrix (cbf_handle handle, double ub_matrix[9]); CBFLib documentation: DESCRIPTION cbf_get_orientation_matrix sets ub_matrix to point to the array of orientation matrix entries in the \"diffrn \" category in the order of columns: \"UB[1][1] \" \"UB[1][2] \" \"UB[1][3] \" \"UB[2][1] \" \"UB[2][2] \" \"UB[2][3] \" \"UB[3][1] \" \"UB[3][2] \" \"UB[3][3] \" cbf_set_orientation_matrix sets the values in the \"diffrn \" category to the values pointed to by ub_matrix. ARGUMENTS handle CBF handle. ubmatric Source or destination array of 9 doubles giving the orientation matrix parameters. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_orientation_matrix; void set_orientation_matrix( double m0,double m1, double m2,double m3,double m4,double m5,double m6, double m7,double m8){ double m[9]; m[0] = m0; m[1]=m1 ; m[2]=m2 ; m[3] = m3; m[4]=m4 ; m[5]=m5 ; m[6] = m6; m[7]=m7 ; m[8]=m8 ; cbf_failnez(cbf_get_orientation_matrix(self,m)); } /* cfunc cbf_new_category pyfunc new_category arg cbf_handle handle arg const char *categoryname */ %feature("autodoc", " Returns : string *args : C prototype: int cbf_new_category (cbf_handle handle, const char *categoryname); CBFLib documentation: DESCRIPTION cbf_new_category creates a new category in the current data block with name categoryname and makes it the current category. If a category with this name already exists, the existing category becomes the current category. ARGUMENTS handle CBF handle. categoryname The name of the new category. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")new_category; void new_category(const char* arg){ cbf_failnez(cbf_new_category(self,arg));} %feature("autodoc", " Returns : *args : Float gain,Float gain_esd C prototype: int cbf_set_gain (cbf_handle handle, unsigned int element_number, double gain, double gain_esd); CBFLib documentation: DESCRIPTION cbf_set_gain sets the gain of element number element_number to the values specified by gain and gain_esd. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the \"diffrn_data_frame \" category. gain New gain value. gain_esd New gain_esd value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_gain; void set_gain (unsigned int element_number, double gain, double gain_esd){ cbf_failnez(cbf_set_gain (self, element_number, gain, gain_esd)); } /* cfunc cbf_find_column pyfunc find_column arg cbf_handle handle arg const char *columnname */ %feature("autodoc", " Returns : string *args : C prototype: int cbf_find_column (cbf_handle handle, const char *columnname); CBFLib documentation: DESCRIPTION cbf_find_column makes the columns in the current category with name columnname the current column. The comparison is case-insensitive. If the column does not exist, the function returns CBF_NOTFOUND. The current row is not affected. ARGUMENTS handle CBF handle. columnname The name of column to find. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")find_column; void find_column(const char* arg){ cbf_failnez(cbf_find_column(self,arg));} /* cfunc cbf_remove_category pyfunc remove_category arg cbf_handle handle */ %feature("autodoc", " Returns : *args : C prototype: int cbf_remove_category (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_remove_category deletes the current category. The current category becomes undefined. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")remove_category; void remove_category(void){ cbf_failnez(cbf_remove_category(self));} %feature("autodoc", " Returns : int compression,int binary_id,int elsize,int elsigned,int elunsigned, int elements,int minelement,int maxelement,char **bo,int *bolen, int dimslow,int dimmid,int dimfast,int padding *args : C prototype: int cbf_get_integerarrayparameters_wdims_sf (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, int *elsigned, int *elunsigned, size_t *elements, int *minelement, int *maxelement, const char **byteorder, size_t *dimslow, size_t *dimmid, size_t *dimfast, size_t *padding); CBFLib documentation: DESCRIPTION cbf_get_integerarrayparameters sets *compression, *binary_id, *elsize, *elsigned, *elunsigned, *elements, *minelement and *maxelement to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_integerarray, if a copy of the array is to be made into another CIF or CBF. cbf_get_realarrayparameters sets *compression, *binary_id, *elsize, *elements to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_realarray, if a copy of the arry is to be made into another CIF or CBF. The variants cbf_get_integerarrayparameters_wdims, cbf_get_integerarrayparameters_wdims_fs, cbf_get_integerarrayparameters_wdims_sf, cbf_get_realarrayparameters_wdims, cbf_get_realarrayparameters_wdims_fs, cbf_get_realarrayparameters_wdims_sf set **byteorder, *dimfast, *dimmid, *dimslow, and *padding as well, providing the additional parameters needed for a subsequent call to cbf_set_integerarray_wdims or cbf_set_realarray_wdims. The value returned in *byteorder is a pointer either to the string \"little_endian \" or to the string \"big_endian \". This should be the byte order of the data, not necessarily of the host machine. No attempt should be made to modify this string. At this time only \"little_endian \" will be returned. The values returned in *dimfast, *dimmid and *dimslow are the sizes of the fastest changing, second fastest changing and third fastest changing dimensions of the array, if specified, or zero, if not specified. The value returned in *padding is the size of the post-data padding, if any and if specified in the data header. The value is given as a count of octets. If the value is not binary, the function returns CBF_ASCII. ARGUMENTS handle CBF handle. compression Compression method used. elsize Size in bytes of each array element. binary_id Pointer to the destination integer binary identifier. elsigned Pointer to an integer. Set to 1 if the elements can be read as signed integers. elunsigned Pointer to an integer. Set to 1 if the elements can be read as unsigned integers. elements Pointer to the destination number of elements. minelement Pointer to the destination smallest element. maxelement Pointer to the destination largest element. byteorder Pointer to the destination byte order. dimfast Pointer to the destination fastest dimension. dimmid Pointer to the destination second fastest dimension. dimslow Pointer to the destination third fastest dimension. padding Pointer to the destination padding size. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")get_integerarrayparameters_wdims_sf; %cstring_output_allocate_size(char **bo, int *bolen, free(*$1)); %apply int *OUTPUT {int *compression,int *binary_id, int *elsize, int *elsigned, int *elunsigned, int *elements, int *minelement, int *maxelement, int *dimslow, int *dimmid, int *dimfast, int *padding} get_integerarrayparameters_wdims_sf; void get_integerarrayparameters_wdims_sf(int *compression,int *binary_id, int *elsize, int *elsigned, int *elunsigned, int *elements, int *minelement, int *maxelement, char **bo, int *bolen, int *dimslow, int *dimmid, int *dimfast, int *padding ){ unsigned int comp; size_t elsiz, elem, df,dm,ds,pd; const char * byteorder; char * bot; cbf_failnez(cbf_get_integerarrayparameters_wdims_sf(self, &comp,binary_id, &elsiz, elsigned, elunsigned, &elem, minelement, maxelement, &byteorder,&ds,&dm,&df,&pd )); *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)} strncpy(bot,byteorder,*bolen); *bo = bot; *compression = comp; *elsize = elsiz; *elements = elem; *dimfast = df; *dimmid = dm; *dimslow = ds; *padding = pd; } %feature("autodoc", " Returns : Float pixel_size *args : Int element_number,Int axis_number C prototype: int cbf_get_pixel_size (cbf_handle handle, unsigned int element_number, int axis_number, double *psize); CBFLib documentation: DESCRIPTION cbf_get_pixel_size and cbf_get_pixel_size_sf set *psize to point to the double value in millimeters of the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the slowest axis. cbf_get_pixel_size_fs sets *psize to point to the double value in millimeters of the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the fastest axis. If a negative axis number is given, the order of axes is reversed, so that -1 specifies the slowest axis for cbf_get_pixel_size_fs and the fastest axis for cbf_get_pixel_size_sf. If the pixel size is not given explcitly in the \"array_element_size \" category, the function returns CBF_NOTFOUND. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the \"diffrn_data_frame \" category. axis_number The number of the axis, starting from 1 for the fastest for cbf_get_pixel_size and cbf_get_pixel_size_fs and the slowest for cbf_get_pixel_size_sf. psize Pointer to the destination pixel size. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_pixel_size; %apply double *OUTPUT {double *psize} get_pixel_size; void get_pixel_size(unsigned int element_number, unsigned int axis_number, double *psize){ cbf_failnez(cbf_get_pixel_size(self, element_number, axis_number, psize)); } %feature("autodoc", " Returns : *args : int element_number,int compression,(binary) String data,int elsize, int dimslow,int dimfast C prototype: int cbf_set_real_image_sf(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimslow, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-zero and unsigned otherwise. cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow IEEE double or float elements of elsize bytes each, starting at array. cbf_set_3d_image, cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_set_real_3d_image, cbf_set_real_3d_image_fs and cbf_set_real_3d_image_sf writes the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow IEEE double or float elements of elsize bytes each, starting at array. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the array is 2-dimensional and the 3D calls are used, ndimslow and ndimmid should be used for the array dimensions and ndimfast should be set to 1. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \"byte_offset \" compression. CBF_NONE No compression. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned)for cbf_set_image, or IEEE doubles or floats for cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the \"diffrn_data_frame \" category. compression Compression type. array Pointer to the image array. elsize Size in bytes of each image array element. elsigned Set to non-0 if the image array elements are signed. ndimslow Slowest array dimension. ndimmid Second slowest array dimension. ndimfast Fastest array dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_real_image_sf; /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_real_image_sf; void set_real_image_sf(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int ndimslow, int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_real_image_sf (self, reserved, element_number, compression, (void *) data, (size_t) elsize, (size_t) ndimslow, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ARGUMENT); } } /* cfunc cbf_require_category pyfunc require_category arg cbf_handle handle arg const char *categoryname */ %feature("autodoc", " Returns : string *args : C prototype: int cbf_require_category (cbf_handle handle, const char *categoryname); CBFLib documentation: DESCRIPTION cbf_rewuire_category makes the category in the current data block with name categoryname the current category, if it exists, or creates the catagory if it does not exist. The comparison is case-insensitive. The current column and row become undefined. ARGUMENTS handle CBF handle. categoryname The name of the category to find. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")require_category; void require_category(const char* arg){ cbf_failnez(cbf_require_category(self,arg));} %feature("autodoc", " Returns : Float astar,Float bstar,Float cstar,Float alphastar,Float betastar, Float gammastar *args : C prototype: int cbf_get_reciprocal_cell (cbf_handle handle, double cell[6], double cell_esd[6] ); CBFLib documentation: DESCRIPTION cbf_get_reciprocal_cell sets cell[0:2] to the double values of the reciprocal cell edge lengths a*, b* and c* in AAngstroms-1, cell[3:5] to the double values of the reciprocal cell angles a*, b* and g* in degrees, cell_esd[0:2] to the double values of the estimated strandard deviations of the reciprocal cell edge lengths a*, b* and c* in AAngstroms-1, cell_esd[3:5] to the double values of the estimated standard deviations of the the reciprocal cell angles a*, b* and g* in degrees. The values returned are retrieved from the first row of the \"cell \" category. The value of \"_cell.entry_id \" is ignored. cell or cell_esd may be NULL. If cell is NULL, the reciprocal cell parameters are not retrieved. If cell_esd is NULL, the reciprocal cell parameter esds are not retrieved. If the \"cell \" category is present, but some of the values are missing, zeros are returned for the missing values. ARGUMENTS handle CBF handle. cell Pointer to the destination array of 6 doubles for the reciprocal cell parameters. cell_esd Pointer to the destination array of 6 doubles for the reciprocal cell parameter esds. RETURN VALUE Returns an error code on failure or 0 for success. No errors is returned for missing values if the \"cell \" category exists. SEE ALSO ")get_reciprocal_cell; %apply double *OUTPUT {double *astar, double *bstar, double *cstar, double *alphastar, double *betastar, double *gammastar} get_reciprocal_cell; void get_reciprocal_cell(double *astar, double *bstar, double *cstar, double *alphastar, double *betastar, double *gammastar) { double rcell[6]; cbf_failnez(cbf_get_reciprocal_cell(self,rcell,NULL)); *astar = rcell[0]; *bstar = rcell[1]; *cstar = rcell[2]; *alphastar = rcell[3]; *betastar = rcell[4]; *gammastar = rcell[5]; } %feature("autodoc", " Returns : doubleArray cell *args : C prototype: int cbf_get_reciprocal_cell (cbf_handle handle, double cell[6], double cell_esd[6] ); CBFLib documentation: DESCRIPTION cbf_get_reciprocal_cell sets cell[0:2] to the double values of the reciprocal cell edge lengths a*, b* and c* in AAngstroms-1, cell[3:5] to the double values of the reciprocal cell angles a*, b* and g* in degrees, cell_esd[0:2] to the double values of the estimated strandard deviations of the reciprocal cell edge lengths a*, b* and c* in AAngstroms-1, cell_esd[3:5] to the double values of the estimated standard deviations of the the reciprocal cell angles a*, b* and g* in degrees. The values returned are retrieved from the first row of the \"cell \" category. The value of \"_cell.entry_id \" is ignored. cell or cell_esd may be NULL. If cell is NULL, the reciprocal cell parameters are not retrieved. If cell_esd is NULL, the reciprocal cell parameter esds are not retrieved. If the \"cell \" category is present, but some of the values are missing, zeros are returned for the missing values. ARGUMENTS handle CBF handle. cell Pointer to the destination array of 6 doubles for the reciprocal cell parameters. cell_esd Pointer to the destination array of 6 doubles for the reciprocal cell parameter esds. RETURN VALUE Returns an error code on failure or 0 for success. No errors is returned for missing values if the \"cell \" category exists. SEE ALSO ")get_reciprocal_cell; %apply double *OUTPUT {double *a_esd, double *b_esd, double *c_esd, double *alpha_esd, double *beta_esd, double *gamma_esd} get_reciprocal_cell_esd; void get_reciprocal_cell_esd(double *a_esd, double *b_esd, double *c_esd, double *alpha_esd, double *beta_esd, double *gamma_esd) { double cell_esd[6]; cbf_failnez(cbf_get_reciprocal_cell(self,NULL,cell_esd)); *a_esd = cell_esd[0]; *b_esd = cell_esd[1]; *c_esd = cell_esd[2]; *alpha_esd = cell_esd[3]; *beta_esd = cell_esd[4]; *gamma_esd = cell_esd[5]; } %feature("autodoc", " Returns : size_t ndimslow,size_t ndimmid,size_t ndimfast *args : Integer element_number C prototype: int cbf_get_3d_image_size (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimslow, size_t *ndimmid, size_t *ndimfast); CBFLib documentation: DESCRIPTION cbf_get_image_size, cbf_get_image_size_fs and cbf_get_image_size_sf set *ndimslow and *ndimfast to the slow and fast dimensions of the image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimfast will be set to 1. If the array is 3-dimensional an error code will be returned. cbf_get_3d_image_size, cbf_get_3d_image_size_fs and cbf_get_3d_image_size_sf set *ndimslow, *ndimmid and *ndimfast to the slowest, next fastest and fastest dimensions, respectively, of the 3D image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimmid and ")get_3d_image_size; %apply int *OUTPUT {int *ndimslow, int *ndimmid, int *ndimfast} get_3d_image_size; void get_3d_image_size(unsigned int element_number, int *ndimslow, int *ndimmid, int *ndimfast){ unsigned int reserved; size_t inslow, inmid, infast; reserved = 0; cbf_failnez(cbf_get_3d_image_size(self,reserved,element_number,&inslow,&inmid,&infast)); *ndimslow = (int)inslow; /* FIXME - is that how to convert? */ *ndimmid = (int)inmid; *ndimfast = (int)infast; } %feature("autodoc", " Returns : String tagroot *args : String tagname C prototype: int cbf_find_tag_root (cbf_handle handle, const char* tagname, const char** tagroot); CBFLib documentation: DESCRIPTION cbf_find_tag_root sets *tagroot to the root tag of which tagname is an alias. cbf_set_tag_root sets tagname as an alias of tagroot_in in the dictionary associated with handle, creating the dictionary if necessary. cbf_require_tag_root sets *tagroot to the root tag of which tagname is an alias, if there is one, or to the value of tagname, if tagname is not an alias. A returned tagroot string must not be modified in any way. ARGUMENTS handle CBF handle. tagname tag name which may be an alias. tagroot pointer to a returned tag root name. tagroot_in input tag root name. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")find_tag_root; const char * find_tag_root(const char* tagname){ const char* result; cbf_failnez(cbf_find_tag_root(self,tagname,&result)); return result; } %feature("autodoc", " Returns : String categoryroot *args : String Categoryname C prototype: int cbf_require_category_root (cbf_handle handle, const char* categoryname, const char** categoryroot); CBFLib documentation: DESCRIPTION cbf_find_category_root sets *categoryroot to the root category of which categoryname is an alias. cbf_set_category_root sets categoryname_in as an alias of categoryroot in the dictionary associated with handle, creating the dictionary if necessary. cbf_require_category_root sets *categoryroot to the root category of which categoryname is an alias, if there is one, or to the value of categoryname, if categoryname is not an alias. A returned categoryroot string must not be modified in any way. ARGUMENTS handle CBF handle. categoryname category name which may be an alias. categoryroot pointer to a returned category root name. categoryroot_in input category root name. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")cbf_require_category_root; const char* require_category_root (const char* categoryname){ const char* result; cbf_failnez(cbf_require_category_root(self,categoryname, &result)); return result; } %feature("autodoc", " Returns : *args : int compression,int binary_id,(binary) String data,int elsize, int elements,String byteorder,int dimslow,int dimmid,int dimfast, int padding C prototype: int cbf_set_realarray_wdims_sf (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, size_t elements, const char *byteorder, size_t dimslow, size_t dimmid, size_t dimfast, size_t padding); CBFLib documentation: DESCRIPTION cbf_set_integerarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. The elements are signed if elsigned is non-0 and unsigned otherwise. binary_id is the binary section identifier. cbf_set_realarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. binary_id is the binary section identifier. The cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, cbf_set_integerarray_wdims_sf, cbf_set_realarray_wdims, cbf_set_realarray_wdims_fs and cbf_set_realarray_wdims_sf variants allow the data header values of byteorder, dimfast, dimmid, dimslow and padding to be set to the data byte order, the fastest, second fastest and third fastest array dimensions and the size in byte of the post data padding to be used. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \"byte_offset \" compression. CBF_NONE No compression. NOTE: This scheme is by far the slowest of the four and uses much more disk space. It is intended for routine use with small arrays only. With large arrays (like images) it should be used only for debugging. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned), for cbf_set_integerarray, or IEEE doubles or floats for cbf_set_realarray. If elsize is not equal to sizeof (char), sizeof (short) or sizeof (int), the function returns CBF_ARGUMENT. ARGUMENTS handle CBF handle. compression Compression method to use. binary_id Integer binary identifier. array Pointer to the source array. elsize Size in bytes of each source array element. elsigned Set to non-0 if the source array elements are signed. elements: The number of elements in the array. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")set_realarray_wdims_sf; /* CBFlib must NOT modify the data string nor the byteorder string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_realarray_wdims_sf; %apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_realarray_wdims_sf; void set_realarray_wdims_sf(unsigned int compression, int binary_id, char *data, int len, int elsize, int elements, char *bo, int bolen, int dimslow, int dimmid, int dimfast, int padding){ /* safety check on args */ size_t els, ele; void *array; char byteorder[15]; if(len == elsize*elements && elements==dimfast*dimmid*dimslow){ array = data; els = elsize; ele = elements; strncpy(byteorder,bo,bolen<15?bolen:14); byteorder[bolen<15?14:bolen] = 0; cbf_failnez(cbf_set_realarray_wdims_sf (self, compression, binary_id, (void *) data, (size_t) elsize, (size_t) elements, (const char *)byteorder, (size_t) dimslow, (size_t) dimmid, (size_t) dimfast, (size_t)padding)); }else{ cbf_failnez(CBF_ARGUMENT); } } /* cfunc cbf_set_integervalue pyfunc set_integervalue arg cbf_handle handle arg int number */ %feature("autodoc", " Returns : int number *args : C prototype: int cbf_set_integervalue (cbf_handle handle, int number); CBFLib documentation: DESCRIPTION cbf_set_integervalue sets the item at the current column and row to the integer value number written as a decimal ASCII string. ARGUMENTS handle CBF handle. number Integer value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")set_integervalue; void set_integervalue(int number){ cbf_failnez(cbf_set_integervalue(self,number));} /* cfunc cbf_category_name pyfunc category_name arg cbf_handle handle arg const char **categoryname */ %feature("autodoc", " Returns : *args : string C prototype: int cbf_category_name (cbf_handle handle, const char **categoryname); CBFLib documentation: DESCRIPTION cbf_category_name sets *categoryname to point to the name of the current category of the current data block. The category name will be valid as long as the category exists. The name must not be modified by the program in any way. ARGUMENTS handle CBF handle. categoryname Pointer to the destination category name pointer. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")category_name; const char* category_name(void){ const char* result; cbf_failnez(cbf_category_name(self, &result)); return result;} /* cfunc cbf_get_typeofvalue pyfunc get_typeofvalue arg cbf_handle handle arg const char **typeofvalue */ %feature("autodoc", " Returns : *args : string C prototype: int cbf_get_typeofvalue (cbf_handle handle, const char **typeofvalue); CBFLib documentation: DESCRIPTION cbf_get_value sets *typeofvalue to point an ASCII descriptor of the value of the item at the current column and row. The strings that may be returned are: \"null \" for a null value indicated by a \". \" or a \"? \" \"bnry \" for a binary value \"word \" for an unquoted string \"dblq \" for a double-quoted string \"sglq \" for a single-quoted string \"text \" for a semicolon-quoted string (multiline text field) \"prns \" for a parenthesis-bracketed string (multiline text field) \"brcs \" for a brace-bracketed string (multiline text field) \"bkts \" for a square-bracket-bracketed string (multiline text field) \"tsqs \" for a treble-single-quote quoted string (multiline text field) \"tdqs \" for a treble-double-quote quoted string (multiline text field) Not all types are valid for all type of CIF files. In partcular the types \"prns \", \"brcs \", \"bkts \" were introduced with DDLm and are not valid in DDL1 or DDL2 CIFS. The types \"tsqs \" and \"tdqs \" are not formally part of the CIF syntax. A field for which no value has been set sets *typeofvalue to NULL rather than to the string \"null \". The typeofvalue must not be modified by the program in any way. ARGUMENTS handle CBF handle. typeofvalue Pointer to the destination type-of-value string pointer. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")get_typeofvalue; const char* get_typeofvalue(void){ const char* result; cbf_failnez(cbf_get_typeofvalue(self, &result)); return result;} %feature("autodoc", " Returns : *args : int element_number,int compression,(binary) String data,int elsize, int dimslow,int dimfast C prototype: int cbf_set_real_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimslow, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-zero and unsigned otherwise. cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow IEEE double or float elements of elsize bytes each, starting at array. cbf_set_3d_image, cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_set_real_3d_image, cbf_set_real_3d_image_fs and cbf_set_real_3d_image_sf writes the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow IEEE double or float elements of elsize bytes each, starting at array. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the array is 2-dimensional and the 3D calls are used, ndimslow and ndimmid should be used for the array dimensions and ndimfast should be set to 1. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \"byte_offset \" compression. CBF_NONE No compression. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned)for cbf_set_image, or IEEE doubles or floats for cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the \"diffrn_data_frame \" category. compression Compression type. array Pointer to the image array. elsize Size in bytes of each image array element. elsigned Set to non-0 if the image array elements are signed. ndimslow Slowest array dimension. ndimmid Second slowest array dimension. ndimfast Fastest array dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_real_image; /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_real_image; void set_real_image(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int ndimslow, int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_real_image (self, reserved, element_number, compression, (void *) data, (size_t) elsize, (size_t) ndimslow, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ARGUMENT); } } %feature("autodoc", " Returns : (Binary)String *args : int element_number,int elsize,int elsign,int ndimslow,int ndimmid, int ndimfast C prototype: int cbf_get_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image array for element number element_number into an array. The array consists of ndimslow *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and cbf_get_real_image_sf read the image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. cbf_get_3d_image, cbf_get_3d_image_fs and cbf_get_3d_image_sf read the 3D image array for element number element_number into an array. The array consists of ndimslow *ndimmid *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order The structure of the array as a 1-, 2- or 3-dimensional array should agree with the structure of the array given in the ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1 both in the call and in the imgCIF data being processed. If the array is 2-dimensional and a 3D call is used, ndimslow and ndimmid should be the ")get_3d_image_as_string; // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_3d_image_as_string; // Get the length correct void get_3d_image_as_string(int element_number, char **s, int *slen, int elsize, int elsign, int ndimfast, int ndimmid, int ndimslow){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) { cbf_failnez (cbf_get_3d_image(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, elsign, (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimmid*ndimslow; *s = (char *) array; } /* cfunc cbf_remove_row pyfunc remove_row arg cbf_handle handle */ %feature("autodoc", " Returns : *args : C prototype: int cbf_remove_row (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_remove_row deletes the current row in the current category. If the current row was the last row, it will move down by 1, otherwise, it will remain the same. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")remove_row; void remove_row(void){ cbf_failnez(cbf_remove_row(self));} %feature("autodoc", " Returns : *args : Integer element_number,Float overload C prototype: int cbf_set_overload (cbf_handle handle, unsigned int element_number, double overload); CBFLib documentation: DESCRIPTION cbf_set_overload sets the overload value of element number element_number to overload. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the \"diffrn_data_frame \" category. overload New overload value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_overload; void set_overload(unsigned int element_number, double overload){ cbf_failnez(cbf_set_overload(self,element_number,overload)); } %feature("autodoc", " Returns : size_t ndim1,size_t ndim2 *args : Integer element_number C prototype: int cbf_get_image_size (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimslow, size_t *ndimfast); CBFLib documentation: DESCRIPTION cbf_get_image_size, cbf_get_image_size_fs and cbf_get_image_size_sf set *ndimslow and *ndimfast to the slow and fast dimensions of the image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimfast will be set to 1. If the array is 3-dimensional an error code will be returned. cbf_get_3d_image_size, cbf_get_3d_image_size_fs and cbf_get_3d_image_size_sf set *ndimslow, *ndimmid and *ndimfast to the slowest, next fastest and fastest dimensions, respectively, of the 3D image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimmid and ")get_image_size; %apply int *OUTPUT {int *ndimslow, int *ndimfast} get_image_size; void get_image_size(unsigned int element_number, int *ndimslow, int *ndimfast){ unsigned int reserved; size_t inslow, infast; reserved = 0; cbf_failnez(cbf_get_image_size(self,reserved,element_number,&inslow,&infast)); *ndimslow = (int)inslow; *ndimfast = (int)infast; } %feature("autodoc", " Returns : *args : int element_number,int compression,(binary) String data,int elsize, int elsign,int dimslow,int dimmid,int dimfast C prototype: int cbf_set_3d_image_sf(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-zero and unsigned otherwise. cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow IEEE double or float elements of elsize bytes each, starting at array. cbf_set_3d_image, cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_set_real_3d_image, cbf_set_real_3d_image_fs and cbf_set_real_3d_image_sf writes the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow IEEE double or float elements of elsize bytes each, starting at array. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the array is 2-dimensional and the 3D calls are used, ndimslow and ndimmid should be used for the array dimensions and ndimfast should be set to 1. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \"byte_offset \" compression. CBF_NONE No compression. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned)for cbf_set_image, or IEEE doubles or floats for cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the \"diffrn_data_frame \" category. compression Compression type. array Pointer to the image array. elsize Size in bytes of each image array element. elsigned Set to non-0 if the image array elements are signed. ndimslow Slowest array dimension. ndimmid Second slowest array dimension. ndimfast Fastest array dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_3d_image_sf; /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_3d_image; void set_3d_image_sf(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int elsign, int ndimslow, int ndimmid, int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimmid*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_3d_image_sf (self, reserved, element_number, compression, (void *) data, (size_t) elsize, elsign, (size_t) ndimslow, (size_t) ndimmid, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ARGUMENT); } } %feature("autodoc", " Returns : (Binary)String *args : int element_number,int elsize,int ndimslow,int ndimfast C prototype: int cbf_get_real_image_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimslow, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image array for element number element_number into an array. The array consists of ndimslow *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and cbf_get_real_image_sf read the image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. cbf_get_3d_image, cbf_get_3d_image_fs and cbf_get_3d_image_sf read the 3D image array for element number element_number into an array. The array consists of ndimslow *ndimmid *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order The structure of the array as a 1-, 2- or 3-dimensional array should agree with the structure of the array given in the ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1 both in the call and in the imgCIF data being processed. If the array is 2-dimensional and a 3D call is used, ndimslow and ndimmid should be the ")get_real_image_sf_as_string; // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_real_image_sf_as_string; // Get the length correct void get_real_image_sf_as_string(int element_number, char **s, int *slen, int elsize, int ndimslow, int ndimfast){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimslow))) { cbf_failnez (cbf_get_real_image_sf(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, (size_t) ndimslow, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimslow; *s = (char *) array; } %feature("autodoc", " Returns : (Binary)String *args : int element_number,int elsize,int elsign,int ndimslow,int ndimfast C prototype: int cbf_get_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image array for element number element_number into an array. The array consists of ndimslow *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and cbf_get_real_image_sf read the image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. cbf_get_3d_image, cbf_get_3d_image_fs and cbf_get_3d_image_sf read the 3D image array for element number element_number into an array. The array consists of ndimslow *ndimmid *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order The structure of the array as a 1-, 2- or 3-dimensional array should agree with the structure of the array given in the ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1 both in the call and in the imgCIF data being processed. If the array is 2-dimensional and a 3D call is used, ndimslow and ndimmid should be the ")get_image_as_string; // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_image_as_string; // Get the length correct void get_image_as_string(int element_number, char **s, int *slen, int elsize, int elsign, int ndimslow, int ndimfast){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimslow))) { cbf_failnez (cbf_get_image(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, elsign, (size_t) ndimslow, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimslow; *s = (char *) array; } %feature("autodoc", " Returns : *args : String tagname,String tagroot_in C prototype: int cbf_set_tag_root (cbf_handle handle, const char* tagname, const char*tagroot_in); CBFLib documentation: DESCRIPTION cbf_find_tag_root sets *tagroot to the root tag of which tagname is an alias. cbf_set_tag_root sets tagname as an alias of tagroot_in in the dictionary associated with handle, creating the dictionary if necessary. cbf_require_tag_root sets *tagroot to the root tag of which tagname is an alias, if there is one, or to the value of tagname, if tagname is not an alias. A returned tagroot string must not be modified in any way. ARGUMENTS handle CBF handle. tagname tag name which may be an alias. tagroot pointer to a returned tag root name. tagroot_in input tag root name. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_tag_root; void set_tag_root(const char* tagname, const char* tagroot_in){ cbf_failnez(cbf_set_tag_root(self,tagname,tagroot_in)); } %feature("autodoc", " Returns : *args : String filename,Integer ciforcbf,Integer Headers,Integer encoding C prototype: int cbf_write_widefile (cbf_handle handle, FILE *file, int readable, int ciforcbf, int flags, int encoding); CBFLib documentation: DESCRIPTION cbf_write_file writes the CBF object specified by handle into the file file, following CIF 1.0 conventions of 80 character lines. cbf_write_widefile writes the CBF object specified by handle into the file file, following CIF 1.1 conventions of 2048 character lines. A warning is issued to stderr for ascii lines over the limit, and an attempt is made to fold lines to fit. No test is performed on binary sections. If a dictionary has been provided, aliases will be applied on output. Unlike cbf_read_file, the file does not have to be random-access. If the file is random-access and readable, readable can be set to non-0 to indicate to CBFlib that the file can be used as a buffer to conserve disk space. If the file is not random-access or not readable, readable must be 0. ")write_widefile; void write_widefile(const char* filename, int ciforcbf, int headers, int encoding){ FILE *stream; int readable; /* Make the file non-0 to make CBFlib close the file */ readable = 1; if ( ! ( stream = fopen (filename, "w+b")) ){ cbf_failnez(CBF_FILEOPEN); } else{ cbf_failnez(cbf_write_widefile(self, stream, readable, ciforcbf, headers, encoding)); } } /* cfunc cbf_count_rows pyfunc count_rows arg cbf_handle handle arg unsigned int *rows */ %feature("autodoc", " Returns : Integer *args : C prototype: int cbf_count_rows (cbf_handle handle, unsigned int *rows); CBFLib documentation: DESCRIPTION cbf_count_rows puts the number of rows in the current category in *rows . ARGUMENTS handle CBF handle. rows Pointer to the destination row count. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")count_rows; unsigned int count_rows(void){ unsigned int result; cbf_failnez(cbf_count_rows(self,&result)); return result;} /* cfunc cbf_require_datablock pyfunc require_datablock arg cbf_handle handle arg const char *datablockname */ %feature("autodoc", " Returns : string *args : C prototype: int cbf_require_datablock (cbf_handle handle, const char *datablockname); CBFLib documentation: DESCRIPTION cbf_require_datablock makes the data block with name datablockname the current data block, if it exists, or creates it if it does not. The comparison is case-insensitive. The current category becomes undefined. ARGUMENTS handle CBF handle. datablockname The name of the data block to find or create. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")require_datablock; void require_datablock(const char* arg){ cbf_failnez(cbf_require_datablock(self,arg));} %feature("autodoc", " Returns : *args : int compression,int binary_id,(binary) String data,int elsize, int elsigned,int elements C prototype: int cbf_set_integerarray (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, int elsigned, size_t elements); CBFLib documentation: DESCRIPTION cbf_set_integerarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. The elements are signed if elsigned is non-0 and unsigned otherwise. binary_id is the binary section identifier. cbf_set_realarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. binary_id is the binary section identifier. The cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, cbf_set_integerarray_wdims_sf, cbf_set_realarray_wdims, cbf_set_realarray_wdims_fs and cbf_set_realarray_wdims_sf variants allow the data header values of byteorder, dimfast, dimmid, dimslow and padding to be set to the data byte order, the fastest, second fastest and third fastest array dimensions and the size in byte of the post data padding to be used. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \"byte_offset \" compression. CBF_NONE No compression. NOTE: This scheme is by far the slowest of the four and uses much more disk space. It is intended for routine use with small arrays only. With large arrays (like images) it should be used only for debugging. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned), for cbf_set_integerarray, or IEEE doubles or floats for cbf_set_realarray. If elsize is not equal to sizeof (char), sizeof (short) or sizeof (int), the function returns CBF_ARGUMENT. ARGUMENTS handle CBF handle. compression Compression method to use. binary_id Integer binary identifier. array Pointer to the source array. elsize Size in bytes of each source array element. elsigned Set to non-0 if the source array elements are signed. elements: The number of elements in the array. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")set_integerarray; /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_integerarray; void set_integerarray(unsigned int compression, int binary_id, char *data, int len, int elsize, int elsigned, int elements){ /* safety check on args */ size_t els, ele; void *array; if(len == elsize*elements){ array = data; els = elsize; ele = elements; cbf_failnez(cbf_set_integerarray (self, compression, binary_id, (void *) data, (size_t) elsize, elsigned, (size_t) elements)); }else{ cbf_failnez(CBF_ARGUMENT); } } /* cfunc cbf_new_datablock pyfunc new_datablock arg cbf_handle handle arg const char *datablockname */ %feature("autodoc", " Returns : string *args : C prototype: int cbf_new_datablock (cbf_handle handle, const char *datablockname); CBFLib documentation: DESCRIPTION cbf_new_datablock creates a new data block with name datablockname and makes it the current data block. cbf_new_saveframe creates a new save frame with name saveframename within the current data block and makes the new save frame the current save frame. If a data block or save frame with this name already exists, the existing data block or save frame becomes the current data block or save frame. ARGUMENTS handle CBF handle. datablockname The name of the new data block. saveframename The name of the new save frame. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")new_datablock; void new_datablock(const char* arg){ cbf_failnez(cbf_new_datablock(self,arg));} %feature("autodoc", " Returns : *args : int year,int month,int day,int hour,int minute,double second, int timezone,Float precision C prototype: int cbf_set_datestamp (cbf_handle handle, unsigned int reserved, int year, int month, int day, int hour, int minute, double second, int timezone, double precision); CBFLib documentation: DESCRIPTION cbf_set_datestamp sets the collection timestamp in seconds since January 1 1970 to the value specified by time. The timezone difference from UTC ")set_datestamp; void set_datestamp(int year, int month, int day, int hour, int minute, double second, int timezone, double precision){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_set_datestamp(self,reserved, year,month,day,hour,minute,second,timezone,precision)); } /* cfunc cbf_next_row pyfunc next_row arg cbf_handle handle */ %feature("autodoc", " Returns : *args : C prototype: int cbf_next_row (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_next_row makes the row following the current row in the current category the current row. If there are no more rows, the function returns CBF_NOTFOUND. The current column is not affected. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")next_row; void next_row(void){ cbf_failnez(cbf_next_row(self));} %feature("autodoc", " Returns : *args : String categoryname,String categoryroot C prototype: int cbf_set_category_root (cbf_handle handle, const char* categoryname_in, const char*categoryroot); CBFLib documentation: DESCRIPTION cbf_find_category_root sets *categoryroot to the root category of which categoryname is an alias. cbf_set_category_root sets categoryname_in as an alias of categoryroot in the dictionary associated with handle, creating the dictionary if necessary. cbf_require_category_root sets *categoryroot to the root category of which categoryname is an alias, if there is one, or to the value of categoryname, if categoryname is not an alias. A returned categoryroot string must not be modified in any way. ARGUMENTS handle CBF handle. categoryname category name which may be an alias. categoryroot pointer to a returned category root name. categoryroot_in input category root name. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_category_root; void set_category_root(const char* categoryname, const char* categoryroot){ cbf_failnez(cbf_set_category_root(self,categoryname,categoryroot)); } %feature("autodoc", " Returns : *args : Int element_number,Int axis_number,Float pixel size C prototype: int cbf_set_pixel_size_fs(cbf_handle handle, unsigned int element_number, int axis_number, double psize); CBFLib documentation: DESCRIPTION cbf_set_pixel_size and cbf_set_pixel_size_sf set the item in the "e;size"e; column of the \"array_structure_list \" category at the row which matches axis axis_number of the detector element element_number converting the double pixel size psize from meters to millimeters in storing it in the \"size \" column for the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the slowest axis. cbf_set_pixel_size_fs sets the item ")set_pixel_size_fs; void set_pixel_size_fs (unsigned int element_number, unsigned int axis_number, double psize){ cbf_failnez(cbf_set_pixel_size_fs(self, element_number, axis_number, psize)); } /* cfunc cbf_insert_row pyfunc insert_row arg cbf_handle handle arg unsigned int rownumber */ %feature("autodoc", " Returns : *args : Integer C prototype: int cbf_insert_row (cbf_handle handle, unsigned int rownumber); CBFLib documentation: DESCRIPTION cbf_insert_row adds a new row to the current category. The new row is inserted as row rownumber and existing rows starting from rownumber are moved up by 1. The new row becomes the current row. If the category has fewer than rownumber rows, the function returns CBF_NOTFOUND. The row numbers start from 0. ARGUMENTS handle CBF handle. rownumber The row number of the new row. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")insert_row; void insert_row(unsigned int arg){ cbf_failnez(cbf_insert_row(self,arg));} /* cfunc cbf_new_column pyfunc new_column arg cbf_handle handle arg const char *columnname */ %feature("autodoc", " Returns : string *args : C prototype: int cbf_new_column (cbf_handle handle, const char *columnname); CBFLib documentation: DESCRIPTION cbf_new_column creates a new column in the current category with name columnname and makes it the current column. If a column with this name already exists, the existing column becomes the current category. ARGUMENTS handle CBF handle. columnname The name of the new column. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")new_column; void new_column(const char* arg){ cbf_failnez(cbf_new_column(self,arg));} %feature("autodoc", " Returns : (Binary)String *args : int element_number,int elsize,int ndimslow,int ndimmid,int ndimfast C prototype: int cbf_get_real_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image array for element number element_number into an array. The array consists of ndimslow *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and cbf_get_real_image_sf read the image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. cbf_get_3d_image, cbf_get_3d_image_fs and cbf_get_3d_image_sf read the 3D image array for element number element_number into an array. The array consists of ndimslow *ndimmid *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order The structure of the array as a 1-, 2- or 3-dimensional array should agree with the structure of the array given in the ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1 both in the call and in the imgCIF data being processed. If the array is 2-dimensional and a 3D call is used, ndimslow and ndimmid should be the ")get_real_3d_image_as_string; // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_real_3d_image_as_string; // Get the length correct void get_real_3d_image_as_string(int element_number, char **s, int *slen, int elsize, int ndimslow, int ndimmid, int ndimfast){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) { cbf_failnez (cbf_get_real_3d_image(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimmid*ndimslow; *s = (char *) array; } %feature("autodoc", " Returns : Float time *args : C prototype: int cbf_get_integration_time (cbf_handle handle, unsigned int reserved, double *time); CBFLib documentation: DESCRIPTION cbf_get_integration_time sets *time to the integration time in seconds. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. time Pointer to the destination time. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_integration_time; %apply double *OUTPUT {double *time} get_integration_time; void get_integration_time( double *time ){ unsigned int reserved; double tim; reserved = 0; cbf_failnez(cbf_get_integration_time(self,reserved,&tim)); *time = tim; } %feature("autodoc", " Returns : *args : int compression,int binary_id,(binary) String data,int elsize, int elements C prototype: int cbf_set_realarray (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, size_t elements); CBFLib documentation: DESCRIPTION cbf_set_integerarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. The elements are signed if elsigned is non-0 and unsigned otherwise. binary_id is the binary section identifier. cbf_set_realarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. binary_id is the binary section identifier. The cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, cbf_set_integerarray_wdims_sf, cbf_set_realarray_wdims, cbf_set_realarray_wdims_fs and cbf_set_realarray_wdims_sf variants allow the data header values of byteorder, dimfast, dimmid, dimslow and padding to be set to the data byte order, the fastest, second fastest and third fastest array dimensions and the size in byte of the post data padding to be used. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \"byte_offset \" compression. CBF_NONE No compression. NOTE: This scheme is by far the slowest of the four and uses much more disk space. It is intended for routine use with small arrays only. With large arrays (like images) it should be used only for debugging. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned), for cbf_set_integerarray, or IEEE doubles or floats for cbf_set_realarray. If elsize is not equal to sizeof (char), sizeof (short) or sizeof (int), the function returns CBF_ARGUMENT. ARGUMENTS handle CBF handle. compression Compression method to use. binary_id Integer binary identifier. array Pointer to the source array. elsize Size in bytes of each source array element. elsigned Set to non-0 if the source array elements are signed. elements: The number of elements in the array. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")set_realarray; /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_realarray; void set_realarray(unsigned int compression, int binary_id, char *data, int len, int elsize, int elements){ /* safety check on args */ size_t els, ele; void *array; if(len == elsize*elements){ array = data; els = elsize; ele = elements; cbf_failnez(cbf_set_realarray (self, compression, binary_id, (void *) data, (size_t) elsize, (size_t) elements)); }else{ cbf_failnez(CBF_ARGUMENT); } } %feature("autodoc", " Returns : String *args : Integer element_number C prototype: int cbf_get_element_id (cbf_handle handle, unsigned int element_number, const char **element_id); CBFLib documentation: DESCRIPTION cbf_get_element_id sets *element_id to point to the ASCII value of the element_number'th \"diffrn_data_frame.detector_element_id \" entry, counting from 0. If the detector element does not exist, the function returns CBF_NOTFOUND. The element_id will be valid as long as the item exists and has not been set to a new value. The element_id must not be modified by the program in any way. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the \"diffrn_data_frame \" category. element_id Pointer to the destination. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_element_id; const char * get_element_id(unsigned int element_number){ const char * result; cbf_failnez(cbf_get_element_id (self, element_number, &result)); return result; } %feature("autodoc", " Returns : (Binary)String *args : int element_number,int elsize,int elsign,int ndimslow,int ndimfast C prototype: int cbf_get_image_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image array for element number element_number into an array. The array consists of ndimslow *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and cbf_get_real_image_sf read the image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. cbf_get_3d_image, cbf_get_3d_image_fs and cbf_get_3d_image_sf read the 3D image array for element number element_number into an array. The array consists of ndimslow *ndimmid *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order The structure of the array as a 1-, 2- or 3-dimensional array should agree with the structure of the array given in the ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1 both in the call and in the imgCIF data being processed. If the array is 2-dimensional and a 3D call is used, ndimslow and ndimmid should be the ")get_image_sf_as_string; // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_image_fs_as_string; // Get the length correct void get_image_sf_as_string(int element_number, char **s, int *slen, int elsize, int elsign, int ndimslow, int ndimfast){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimslow))) { cbf_failnez (cbf_get_image_sf(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, elsign, (size_t) ndimslow, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimslow; *s = (char *) array; } %feature("autodoc", " Returns : size_t ndimfast,size_t ndimmid,size_t ndimslow *args : Integer element_number C prototype: int cbf_get_3d_image_size_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimfast, size_t *ndimmid, size_t *ndimslow); CBFLib documentation: DESCRIPTION cbf_get_image_size, cbf_get_image_size_fs and cbf_get_image_size_sf set *ndimslow and *ndimfast to the slow and fast dimensions of the image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimfast will be set to 1. If the array is 3-dimensional an error code will be returned. cbf_get_3d_image_size, cbf_get_3d_image_size_fs and cbf_get_3d_image_size_sf set *ndimslow, *ndimmid and *ndimfast to the slowest, next fastest and fastest dimensions, respectively, of the 3D image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimmid and ")get_3d_image_size; %apply int *OUTPUT {int *ndimslow, int *ndimmid, int *ndimfast} get_3d_image_size; void get_3d_image_size_fs(unsigned int element_number, int *ndimfast, int *ndimmid, int *ndimslow){ unsigned int reserved; size_t inslow, inmid, infast; reserved = 0; cbf_failnez(cbf_get_3d_image_size_fs(self,reserved,element_number,&infast,&inmid,&inslow)); *ndimslow = (int)inslow; /* FIXME - is that how to convert? */ *ndimmid = (int)inmid; *ndimfast = (int)infast; } /* cfunc cbf_set_value pyfunc set_value arg cbf_handle handle arg const char *value */ %feature("autodoc", " Returns : string *args : C prototype: int cbf_set_value (cbf_handle handle, const char *value); CBFLib documentation: DESCRIPTION cbf_set_value sets the item at the current column and row to the ASCII value value. ARGUMENTS handle CBF handle. value ASCII value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")set_value; void set_value(const char* arg){ cbf_failnez(cbf_set_value(self,arg));} %feature("autodoc", " Returns : *args : Integer timezone C prototype: int cbf_set_current_timestamp (cbf_handle handle, unsigned int reserved, int timezone); CBFLib documentation: DESCRIPTION cbf_set_current_timestamp sets the collection timestamp to the current time. The timezone difference from UTC in minutes is set to timezone. If no timezone is desired, timezone should be CBF_NOTIMEZONE. If no timezone is used, the timest amp will be UTC. The parameter reserved is presently unused and should be set to 0. The new timestamp will have a precision of 1 second. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. timezone Timezone difference from UTC in minutes or CBF_NOTIMEZONE. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_current_timestamp; void set_current_timestamp(int timezone){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_set_current_timestamp(self,reserved,timezone)); } %feature("autodoc", " Returns : Float Number *args : Float Default C prototype: int cbf_require_doublevalue (cbf_handle handle, double *number, double defaultvalue); CBFLib documentation: DESCRIPTION cbf_get_doublevalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal floating-point number. cbf_require_doublevalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal floating-point number, setting it to defaultvalue if necessary. If the value is not ASCII, the function returns CBF_BINARY. ARGUMENTS handle CBF handle. number Pointer to the destination number. defaultvalue default number value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")require_doublevalue; %apply double *OUTPUT {double *number} require_doublevalue; void require_doublevalue(double *number, double defaultvalue){ cbf_failnez(cbf_require_doublevalue(self,number,defaultvalue)); } /* cfunc cbf_rewind_datablock pyfunc rewind_datablock arg cbf_handle handle */ %feature("autodoc", " Returns : *args : C prototype: int cbf_rewind_datablock (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_rewind_datablock makes the first data block the current data block. If there are no data blocks, the function returns CBF_NOTFOUND. The current category becomes undefined. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")rewind_datablock; void rewind_datablock(void){ cbf_failnez(cbf_rewind_datablock(self));} %feature("autodoc", " Returns : String Name *args : String columnnanme,String Default C prototype: int cbf_require_column_value (cbf_handle handle, const char *columnname, const char **value, const char *defaultvalue); CBFLib documentation: DESCRIPTION cbf_require_column_doublevalue sets *value to the ASCII item at the current row for the column given with the name given by *columnname, or to the string given by defaultvalue if the item cannot be found. ARGUMENTS handle CBF handle. columnname Name of the column containing the number. value pointer to the location to receive the value. defaultvalue Value to use if the requested column and value cannot be found. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")require_column_value; const char* require_column_value(const char *columnname, const char *defaultvalue){ const char * result; cbf_failnez(cbf_require_column_value(self,columnname, &result,defaultvalue)); return result; } %feature("autodoc", " Returns : CBFHandle dictionary *args : C prototype: int cbf_get_dictionary (cbf_handle handle, cbf_handle * dictionary); CBFLib documentation: DESCRIPTION cbf_get_dictionary sets *dictionary to the handle of a CBF which has been associated with the CBF handle by cbf_set_dictionary. cbf_set_dictionary associates the CBF handle dictionary_in with handle as its dictionary. cbf_require_dictionary sets *dictionary to the handle of a CBF which has been associated with the CBF handle by cbf_set_dictionary or creates a new empty CBF and associates it with handle, returning the new handle in *dictionary. ARGUMENTS handle CBF handle. dictionary Pointer to CBF handle of dictionary. dictionary_in CBF handle of dcitionary. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_dictionary; cbf_handle get_dictionary(){ cbf_handle temp; cbf_failnez(cbf_get_dictionary(self,&temp)); return temp; } /* cfunc cbf_reset_saveframe pyfunc reset_saveframe arg cbf_handle handle */ %feature("autodoc", " Returns : *args : C prototype: int cbf_reset_saveframe (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_reset_datablock deletes all categories from the current data block. cbf_reset_saveframe deletes all categories from the current save frame. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")reset_saveframe; void reset_saveframe(void){ cbf_failnez(cbf_reset_saveframe(self));} %feature("autodoc", " Returns : *args : double cell[6] C prototype: int cbf_set_reciprocal_cell (cbf_handle handle, double cell[6], double cell_esd[6] ); CBFLib documentation: DESCRIPTION cbf_set_reciprocal_cell sets the reciprocal cell parameters to the double values given in cell[0:2] for the reciprocal cell edge lengths a*, b* and c* in AAngstroms-1, the double values given in cell[3:5] for the reciprocal cell angles a*, b* and g* in degrees, the double values given in cell_esd[0:2] for the estimated strandard deviations of the reciprocal cell edge lengths a*, b* and c* in AAngstroms, and the double values given in cell_esd[3:5] for the estimated standard deviations of the reciprocal cell angles a*, b* and g* in degrees. The values are placed in the first row of the \"cell \" category. If no value has been given for \"_cell.entry_id \", it is set to the value of the \"diffrn.id \" entry of the current data block. cell or cell_esd may be NULL. If cell is NULL, the reciprocal cell parameters are not set. If cell_esd is NULL, the reciprocal cell parameter esds are not set. If the \"cell \" category is not present, it is created. If any of the necessary columns are not present, they are created. ARGUMENTS handle CBF handle. cell Pointer to the array of 6 doubles for the reciprocal cell parameters. cell_esd Pointer to the array of 6 doubles for the reciprocal cell parameter esds. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")set_reciprocal_cell; void set_reciprocal_cell(double cell[6]) { cbf_failnez(cbf_set_reciprocal_cell(self,cell,NULL)); } %feature("autodoc", " Returns : *args : double cell_esd[6] C prototype: int cbf_set_reciprocal_cell (cbf_handle handle, double cell[6], double cell_esd[6] ); CBFLib documentation: DESCRIPTION cbf_set_reciprocal_cell sets the reciprocal cell parameters to the double values given in cell[0:2] for the reciprocal cell edge lengths a*, b* and c* in AAngstroms-1, the double values given in cell[3:5] for the reciprocal cell angles a*, b* and g* in degrees, the double values given in cell_esd[0:2] for the estimated strandard deviations of the reciprocal cell edge lengths a*, b* and c* in AAngstroms, and the double values given in cell_esd[3:5] for the estimated standard deviations of the reciprocal cell angles a*, b* and g* in degrees. The values are placed in the first row of the \"cell \" category. If no value has been given for \"_cell.entry_id \", it is set to the value of the \"diffrn.id \" entry of the current data block. cell or cell_esd may be NULL. If cell is NULL, the reciprocal cell parameters are not set. If cell_esd is NULL, the reciprocal cell parameter esds are not set. If the \"cell \" category is not present, it is created. If any of the necessary columns are not present, they are created. ARGUMENTS handle CBF handle. cell Pointer to the array of 6 doubles for the reciprocal cell parameters. cell_esd Pointer to the array of 6 doubles for the reciprocal cell parameter esds. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")set_reciprocal_cell_esd; void set_reciprocal_cell_esd(double cell_esd[6]) { cbf_failnez(cbf_set_reciprocal_cell(self,NULL,cell_esd)); } %feature("autodoc", " Returns : *args : int element_number,int compression,(binary) String data,int elsize, int dimfast,int dimmid,int dimslow C prototype: int cbf_set_real_3d_image_fs(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimfast, size_t ndimmid, size_t ndimslow); CBFLib documentation: DESCRIPTION cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-zero and unsigned otherwise. cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow IEEE double or float elements of elsize bytes each, starting at array. cbf_set_3d_image, cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_set_real_3d_image, cbf_set_real_3d_image_fs and cbf_set_real_3d_image_sf writes the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow IEEE double or float elements of elsize bytes each, starting at array. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the array is 2-dimensional and the 3D calls are used, ndimslow and ndimmid should be used for the array dimensions and ndimfast should be set to 1. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \"byte_offset \" compression. CBF_NONE No compression. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned)for cbf_set_image, or IEEE doubles or floats for cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the \"diffrn_data_frame \" category. compression Compression type. array Pointer to the image array. elsize Size in bytes of each image array element. elsigned Set to non-0 if the image array elements are signed. ndimslow Slowest array dimension. ndimmid Second slowest array dimension. ndimfast Fastest array dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_real_3d_image_fs; /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_real_3d_image_fs; void set_real_3d_image_fs(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int ndimfast, int ndimmid, int ndimslow){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimmid*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_real_3d_image_fs (self, reserved, element_number, compression, (void *) data, (size_t) elsize, (size_t) ndimfast, (size_t)ndimmid, (size_t)ndimslow)); }else{ cbf_failnez(CBF_ARGUMENT); } } %feature("autodoc", " Returns : *args : String format,Float number C prototype: int cbf_set_doublevalue (cbf_handle handle, const char *format, double number); CBFLib documentation: DESCRIPTION cbf_set_doublevalue sets the item at the current column and row to the floating-point value number written as an ASCII string with the format specified by format as appropriate for the printf function. ARGUMENTS handle CBF handle. format Format for the number. number Floating-point value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")set_doublevalue; void set_doublevalue(const char *format, double number){ cbf_failnez(cbf_set_doublevalue(self,format,number));} /* cfunc cbf_find_category pyfunc find_category arg cbf_handle handle arg const char *categoryname */ %feature("autodoc", " Returns : string *args : C prototype: int cbf_find_category (cbf_handle handle, const char *categoryname); CBFLib documentation: DESCRIPTION cbf_find_category makes the category in the current data block with name categoryname the current category. The comparison is case-insensitive. If the category does not exist, the function returns CBF_NOTFOUND. The current column and row become undefined. ARGUMENTS handle CBF handle. categoryname The name of the category to find. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")find_category; void find_category(const char* arg){ cbf_failnez(cbf_find_category(self,arg));} %feature("autodoc", " Returns : int compression,int binary_id,int elsize,int elsigned,int elunsigned, int elements,int minelement,int maxelement,char **bo,int *bolen, int dimfast,int dimmid,int dimslow,int padding *args : C prototype: int cbf_get_integerarrayparameters_wdims_fs (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, int *elsigned, int *elunsigned, size_t *elements, int *minelement, int *maxelement, const char **byteorder, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding); CBFLib documentation: DESCRIPTION cbf_get_integerarrayparameters sets *compression, *binary_id, *elsize, *elsigned, *elunsigned, *elements, *minelement and *maxelement to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_integerarray, if a copy of the array is to be made into another CIF or CBF. cbf_get_realarrayparameters sets *compression, *binary_id, *elsize, *elements to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_realarray, if a copy of the arry is to be made into another CIF or CBF. The variants cbf_get_integerarrayparameters_wdims, cbf_get_integerarrayparameters_wdims_fs, cbf_get_integerarrayparameters_wdims_sf, cbf_get_realarrayparameters_wdims, cbf_get_realarrayparameters_wdims_fs, cbf_get_realarrayparameters_wdims_sf set **byteorder, *dimfast, *dimmid, *dimslow, and *padding as well, providing the additional parameters needed for a subsequent call to cbf_set_integerarray_wdims or cbf_set_realarray_wdims. The value returned in *byteorder is a pointer either to the string \"little_endian \" or to the string \"big_endian \". This should be the byte order of the data, not necessarily of the host machine. No attempt should be made to modify this string. At this time only \"little_endian \" will be returned. The values returned in *dimfast, *dimmid and *dimslow are the sizes of the fastest changing, second fastest changing and third fastest changing dimensions of the array, if specified, or zero, if not specified. The value returned in *padding is the size of the post-data padding, if any and if specified in the data header. The value is given as a count of octets. If the value is not binary, the function returns CBF_ASCII. ARGUMENTS handle CBF handle. compression Compression method used. elsize Size in bytes of each array element. binary_id Pointer to the destination integer binary identifier. elsigned Pointer to an integer. Set to 1 if the elements can be read as signed integers. elunsigned Pointer to an integer. Set to 1 if the elements can be read as unsigned integers. elements Pointer to the destination number of elements. minelement Pointer to the destination smallest element. maxelement Pointer to the destination largest element. byteorder Pointer to the destination byte order. dimfast Pointer to the destination fastest dimension. dimmid Pointer to the destination second fastest dimension. dimslow Pointer to the destination third fastest dimension. padding Pointer to the destination padding size. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")get_integerarrayparameters_wdims_fs; %cstring_output_allocate_size(char **bo, int *bolen, free(*$1)); %apply int *OUTPUT {int *compression,int *binary_id, int *elsize, int *elsigned, int *elunsigned, int *elements, int *minelement, int *maxelement, int *dimfast, int *dimmid, int *dimslow, int *padding} get_integerarrayparameters_wdims_fs; void get_integerarrayparameters_wdims_fs(int *compression,int *binary_id, int *elsize, int *elsigned, int *elunsigned, int *elements, int *minelement, int *maxelement, char **bo, int *bolen, int *dimfast, int *dimmid, int *dimslow, int *padding ){ unsigned int comp; size_t elsiz, elem, df,dm,ds,pd; const char * byteorder; char * bot; cbf_failnez(cbf_get_integerarrayparameters_wdims_fs(self, &comp,binary_id, &elsiz, elsigned, elunsigned, &elem, minelement, maxelement, &byteorder,&df,&dm,&ds,&pd )); *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)} strncpy(bot,byteorder,*bolen); *bo = bot; *compression = comp; *elsize = elsiz; *elements = elem; *dimfast = df; *dimmid = dm; *dimslow = ds; *padding = pd; } %feature("autodoc", " Returns : *args : int compression,int binary_id,(binary) String data,int elsize, int elements,String byteorder,int dimfast,int dimmid,int dimslow, int padding C prototype: int cbf_set_realarray_wdims_fs (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, size_t elements, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); CBFLib documentation: DESCRIPTION cbf_set_integerarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. The elements are signed if elsigned is non-0 and unsigned otherwise. binary_id is the binary section identifier. cbf_set_realarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. binary_id is the binary section identifier. The cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, cbf_set_integerarray_wdims_sf, cbf_set_realarray_wdims, cbf_set_realarray_wdims_fs and cbf_set_realarray_wdims_sf variants allow the data header values of byteorder, dimfast, dimmid, dimslow and padding to be set to the data byte order, the fastest, second fastest and third fastest array dimensions and the size in byte of the post data padding to be used. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \"byte_offset \" compression. CBF_NONE No compression. NOTE: This scheme is by far the slowest of the four and uses much more disk space. It is intended for routine use with small arrays only. With large arrays (like images) it should be used only for debugging. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned), for cbf_set_integerarray, or IEEE doubles or floats for cbf_set_realarray. If elsize is not equal to sizeof (char), sizeof (short) or sizeof (int), the function returns CBF_ARGUMENT. ARGUMENTS handle CBF handle. compression Compression method to use. binary_id Integer binary identifier. array Pointer to the source array. elsize Size in bytes of each source array element. elsigned Set to non-0 if the source array elements are signed. elements: The number of elements in the array. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")set_realarray_wdims_fs; /* CBFlib must NOT modify the data string nor the byteorder string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_realarray_wdims_fs; %apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_realarray_wdims_fs; void set_realarray_wdims_fs(unsigned int compression, int binary_id, char *data, int len, int elsize, int elements, char *bo, int bolen, int dimfast, int dimmid, int dimslow, int padding){ /* safety check on args */ size_t els, ele; void *array; char byteorder[15]; if(len == elsize*elements && elements==dimfast*dimmid*dimslow){ array = data; els = elsize; ele = elements; strncpy(byteorder,bo,bolen<15?bolen:14); byteorder[bolen<15?14:bolen] = 0; cbf_failnez(cbf_set_realarray_wdims_fs (self, compression, binary_id, (void *) data, (size_t) elsize, (size_t) elements, (const char *)byteorder, (size_t) dimfast, (size_t) dimmid, (size_t) dimslow, (size_t)padding)); }else{ cbf_failnez(CBF_ARGUMENT); } } %feature("autodoc", " Returns : String categoryroot *args : String categoryname C prototype: int cbf_find_category_root (cbf_handle handle, const char* categoryname, const char** categoryroot); CBFLib documentation: DESCRIPTION cbf_find_category_root sets *categoryroot to the root category of which categoryname is an alias. cbf_set_category_root sets categoryname_in as an alias of categoryroot in the dictionary associated with handle, creating the dictionary if necessary. cbf_require_category_root sets *categoryroot to the root category of which categoryname is an alias, if there is one, or to the value of categoryname, if categoryname is not an alias. A returned categoryroot string must not be modified in any way. ARGUMENTS handle CBF handle. categoryname category name which may be an alias. categoryroot pointer to a returned category root name. categoryroot_in input category root name. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")find_category_root; const char* find_category_root(const char* categoryname){ const char * result; cbf_failnez(cbf_find_category_root(self,categoryname,&result)); return result; } %feature("autodoc", " Returns : *args : int compression,int binary_id,(binary) String data,int elsize, int elements,String byteorder,int dimfast,int dimmid,int dimslow, int padding C prototype: int cbf_set_integerarray_wdims_fs (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, int elsigned, size_t elements, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); CBFLib documentation: DESCRIPTION cbf_set_integerarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. The elements are signed if elsigned is non-0 and unsigned otherwise. binary_id is the binary section identifier. cbf_set_realarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. binary_id is the binary section identifier. The cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, cbf_set_integerarray_wdims_sf, cbf_set_realarray_wdims, cbf_set_realarray_wdims_fs and cbf_set_realarray_wdims_sf variants allow the data header values of byteorder, dimfast, dimmid, dimslow and padding to be set to the data byte order, the fastest, second fastest and third fastest array dimensions and the size in byte of the post data padding to be used. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \"byte_offset \" compression. CBF_NONE No compression. NOTE: This scheme is by far the slowest of the four and uses much more disk space. It is intended for routine use with small arrays only. With large arrays (like images) it should be used only for debugging. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned), for cbf_set_integerarray, or IEEE doubles or floats for cbf_set_realarray. If elsize is not equal to sizeof (char), sizeof (short) or sizeof (int), the function returns CBF_ARGUMENT. ARGUMENTS handle CBF handle. compression Compression method to use. binary_id Integer binary identifier. array Pointer to the source array. elsize Size in bytes of each source array element. elsigned Set to non-0 if the source array elements are signed. elements: The number of elements in the array. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")set_integerarray_wdims_fs; /* CBFlib must NOT modify the data string nor the byteorder string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_integerarray_wdims_fs; %apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_integerarray_wdims_fs; void set_integerarray_wdims_fs(unsigned int compression, int binary_id, char *data, int len, int elsize, int elsigned, int elements, char *bo, int bolen, int dimfast, int dimmid, int dimslow, int padding){ /* safety check on args */ size_t els, ele; void *array; char byteorder[15]; if(len == elsize*elements && elements==dimfast*dimmid*dimslow){ array = data; els = elsize; ele = elements; strncpy(byteorder,bo,bolen<15?bolen:14); byteorder[bolen<15?14:bolen] = 0; cbf_failnez(cbf_set_integerarray_wdims_fs (self, compression, binary_id, (void *) data, (size_t) elsize, elsigned, (size_t) elements, (const char *)byteorder, (size_t)dimfast, (size_t)dimmid, (size_t)dimslow, (size_t)padding)); }else{ cbf_failnez(CBF_ARGUMENT); } } %feature("autodoc", " Returns : *args : int element_number,int compression,(binary) String data,int elsize, int elsign,int dimslow,int dimfast C prototype: int cbf_set_image_sf(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-zero and unsigned otherwise. cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow IEEE double or float elements of elsize bytes each, starting at array. cbf_set_3d_image, cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_set_real_3d_image, cbf_set_real_3d_image_fs and cbf_set_real_3d_image_sf writes the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow IEEE double or float elements of elsize bytes each, starting at array. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the array is 2-dimensional and the 3D calls are used, ndimslow and ndimmid should be used for the array dimensions and ndimfast should be set to 1. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \"byte_offset \" compression. CBF_NONE No compression. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned)for cbf_set_image, or IEEE doubles or floats for cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the \"diffrn_data_frame \" category. compression Compression type. array Pointer to the image array. elsize Size in bytes of each image array element. elsigned Set to non-0 if the image array elements are signed. ndimslow Slowest array dimension. ndimmid Second slowest array dimension. ndimfast Fastest array dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_image_sf; /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_image_sf; void set_image_sf(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int elsign, int ndimslow, int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_image_sf (self, reserved, element_number, compression, (void *) data, (size_t) elsize, elsign, (size_t) ndimslow, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ARGUMENT); } } %feature("autodoc", " Returns : *args : double cell[6] C prototype: int cbf_set_unit_cell (cbf_handle handle, double cell[6], double cell_esd[6] ); CBFLib documentation: DESCRIPTION cbf_set_unit_cell sets the cell parameters to the double values given in cell[0:2] for the cell edge lengths a, b and c in AAngstroms, the double values given in cell[3:5] for the cell angles a, b and g in degrees, the double values given in cell_esd[0:2] for the estimated strandard deviations of the cell edge lengths a, b and c in AAngstroms, and the double values given in cell_esd[3:5] for the estimated standard deviations of the the cell angles a, b and g in degrees. The values are placed in the first row of the \"cell \" category. If no value has been given for \"_cell.entry_id \", it is set to the value of the \"diffrn.id \" entry of the current data block. cell or cell_esd may be NULL. If cell is NULL, the cell parameters are not set. If cell_esd is NULL, the cell parameter esds are not set. If the \"cell \" category is not present, it is created. If any of the necessary columns are not present, they are created. ARGUMENTS handle CBF handle. cell Pointer to the array of 6 doubles for the cell parameters. cell_esd Pointer to the array of 6 doubles for the cell parameter esds. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")set_unit_cell; void set_unit_cell(double cell[6]) { cbf_failnez(cbf_set_unit_cell(self,cell,NULL)); } %feature("autodoc", " Returns : *args : double cell_esd[6] C prototype: int cbf_set_unit_cell (cbf_handle handle, double cell[6], double cell_esd[6] ); CBFLib documentation: DESCRIPTION cbf_set_unit_cell sets the cell parameters to the double values given in cell[0:2] for the cell edge lengths a, b and c in AAngstroms, the double values given in cell[3:5] for the cell angles a, b and g in degrees, the double values given in cell_esd[0:2] for the estimated strandard deviations of the cell edge lengths a, b and c in AAngstroms, and the double values given in cell_esd[3:5] for the estimated standard deviations of the the cell angles a, b and g in degrees. The values are placed in the first row of the \"cell \" category. If no value has been given for \"_cell.entry_id \", it is set to the value of the \"diffrn.id \" entry of the current data block. cell or cell_esd may be NULL. If cell is NULL, the cell parameters are not set. If cell_esd is NULL, the cell parameter esds are not set. If the \"cell \" category is not present, it is created. If any of the necessary columns are not present, they are created. ARGUMENTS handle CBF handle. cell Pointer to the array of 6 doubles for the cell parameters. cell_esd Pointer to the array of 6 doubles for the cell parameter esds. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO ")set_unit_cell_esd; void set_unit_cell_esd(double cell_esd[6]) { cbf_failnez(cbf_set_unit_cell(self,NULL,cell_esd)); } }; // End of cbf_handle_struct ./CBFlib-0.9.2.2/pycbf/pycbf.html0000644000076500007650000067600711603702120014706 0ustar yayayaya Python: module pycbf
     
     
    pycbf (version still_being_written, 14 Dec 2005)
    index
    d:\wright\cbflib\cbflib_0.7.7\pycbf\pycbf.py

    pycbf - python bindings to the CBFlib library
     
    A library for reading and writing ImageCIF and CBF files 
    which store area detector images for crystallography.
     
    This work is a derivative of the CBFlib version 0.7.7 library
    by  Paul J. Ellis of Stanford Synchrotron Radiation Laboratory
    and Herbert J. Bernstein of Bernstein + Sons
    See:
      http://www.bernstein-plus-sons.com/software/CBF/
     
    Licensing is GPL based, see:
      http://www.bernstein-plus-sons.com/software/CBF/doc/CBFlib_NOTICES.html
     
    These bindings were automatically generated by SWIG, and the
    input to SWIG was automatically generated by a python script.
    We very strongly recommend you do not attempt to edit them 
    by hand!
     
     
     
    Copyright (C) 2007    Jonathan Wright
                          ESRF, Grenoble, France
                   email: wright@esrf.fr

     
    Modules
           
    _pycbf
    new

     
    Classes
           
    __builtin__.object
    cbf_detector_struct
    cbf_handle_struct
    cbf_positioner_struct

     
    class cbf_detector_struct(__builtin__.object)
        Proxy of C cbf_detector_struct struct
     
      Methods defined here:
    __del__ lambda self
    __getattr__ lambda self, name
    __init__(self, *args)
    __init__(self) -> cbf_detector_struct
    __repr__ = _swig_repr(self)
    __setattr__ lambda self, name, value
    get_beam_center(*args)
    Returns : double index1,double index2,double center1,double center2
    *args   : 
     
    C prototype: int cbf_get_beam_center (cbf_detector detector, double *index1,
                     double    *index2, double *center1, double *center2);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_beam_center sets *center1 and *center2 to the displacements 
    in mm along the detector axes from pixel (0, 0) to the point at which 
    the beam intersects the detector and *index1 and *index2 to the 
    corresponding indices. cbf_set_beam_center sets the offsets in the 
    axis category for the detector element axis with precedence 1 to 
    place the beam center at the position given in mm by *center1 and 
    *center2 as the displacements in mm along the detector axes from 
    pixel (0, 0) to the point at which the beam intersects the detector 
    at the indices given *index1 and *index2.
    Any of the destination pointers may be NULL for getting the beam 
    center. For setting the beam axis, either the indices of the center 
    must not be NULL.
    The indices are non-negative for beam centers within the detector 
    surface, but the center for an axis with a negative increment will be 
    negative for a beam center within the detector surface.
    ARGUMENTS
    detector   Detector handle. index1   Pointer to the destination slow 
    index. index2   Pointer to the destination fast index. center1   
    Pointer to the destination displacement along the slow axis. center2  
     Pointer to the destination displacement along the fast axis.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    get_detector_distance(*args)
    Returns : double distance
    *args   : 
     
    C prototype: int cbf_get_detector_distance (cbf_detector detector,
                     double    *distance);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_detector_distance sets *distance to the nearest distance from 
    the sample position to the detector plane.
    ARGUMENTS
    detector   Detector handle. distance   Pointer to the destination 
    distance.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    get_detector_normal(*args)
    Returns : double normal1,double normal2,double normal3
    *args   : 
     
    C prototype: int cbf_get_detector_normal (cbf_detector detector,
                     double *normal1,    double *normal2, double *normal3);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_detector_normal sets *normal1, *normal2, and *normal3 to the 
    3 components of the of the normal vector to the detector plane. The 
    vector is normalized.
    Any of the destination pointers may be NULL.
    ARGUMENTS
    detector   Detector handle. normal1   Pointer to the destination x 
    component of the normal vector. normal2   Pointer to the destination 
    y component of the normal vector. normal3   Pointer to the 
    destination z component of the normal vector.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    get_inferred_pixel_size(*args)
    Returns : Float pixel size
    *args   : Int axis_number
     
    C prototype: int cbf_get_inferred_pixel_size (cbf_detector detector,
                     unsigned int    axis_number, double *psize);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_inferred_pixel_size sets *psize to point to the double value 
    in millimeters of the pixel size for the axis axis_number value for 
    pixel at (index1, index2) on the detector surface. The slow index is 
    treated as axis 1 and the fast index is treated as axis 2.
    ARGUMENTS
    detector      Detector handle. axis_number   The number of the axis. 
    area          Pointer to the destination pizel size in mm.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    get_pixel_area(*args)
    Returns : double area,double projected_area
    *args   : double index1,double index2
     
    C prototype: int cbf_get_pixel_area (cbf_detector detector, double index1,
                     double    index2, double *area, double *projected_area);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_pixel_area sets *area to the area of the pixel at (index1, 
    index2) on the detector surface and *projected_area to the apparent 
    area of the pixel as viewed from the sample position.
    Either of the destination pointers may be NULL.
    ARGUMENTS
    detector         Detector handle. index1           Slow index. index2 
              Fast index. area             Pointer to the destination 
    area in mm2. projected_area   Pointer to the destination apparent 
    area in mm2.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    get_pixel_coordinates(*args)
    Returns : double coordinate1,double coordinate2,double coordinate3
    *args   : double index1,double index2
     
    C prototype: int cbf_get_pixel_coordinates (cbf_detector detector,
                     double index1,    double index2, double *coordinate1,
                     double *coordinate2, double    *coordinate3);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_pixel_coordinates sets *coordinate1, *coordinate2, and 
    *coordinate3 to the vector position of pixel (index1, index2) on the 
    detector surface. If index1 and index2 are integers then the 
    coordinates correspond to the center of a pixel.
    Any of the destination pointers may be NULL.
    ARGUMENTS
    detector      Detector handle. index1        Slow index. index2       
     Fast index. coordinate1   Pointer to the destination x component. 
    coordinate2   Pointer to the destination y component. coordinate3   
    Pointer to the destination z component.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    get_pixel_normal(*args)
    Returns : double normal1,double normal2,double normal3
    *args   : double index1,double index2
     
    C prototype: int cbf_get_pixel_normal (cbf_detector detector, double index1,
                     double    index2, double *normal1, double *normal2,
                     double *normal3);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_detector_normal sets *normal1, *normal2, and *normal3 to the 
    3 components of the of the normal vector to the pixel at (index1, 
    index2). The vector is normalized.
    Any of the destination pointers may be NULL.
    ARGUMENTS
    detector   Detector handle. index1   Slow index. index2   Fast index. 
    normal1   Pointer to the destination x component of the normal 
    vector. normal2   Pointer to the destination y component of the 
    normal vector. normal3   Pointer to the destination z component of 
    the normal vector.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________

    Properties defined here:
    axes
    get = cbf_detector_struct_axes_get(...)
    set = cbf_detector_struct_axes_set(...)
    displacement
    get = cbf_detector_struct_displacement_get(...)
    set = cbf_detector_struct_displacement_set(...)
    increment
    get = cbf_detector_struct_increment_get(...)
    set = cbf_detector_struct_increment_set(...)
    index
    get = cbf_detector_struct_index_get(...)
    set = cbf_detector_struct_index_set(...)
    positioner
    get = cbf_detector_struct_positioner_get(...)
    set = cbf_detector_struct_positioner_set(...)

    Data and other attributes defined here:
    __dict__ = <dictproxy object>
    dictionary for instance variables (if defined)
    __swig_destroy__ = <built-in function delete_cbf_detector_struct>
    __swig_getmethods__ = {'axes': <built-in function cbf_detector_struct_axes_get>, 'displacement': <built-in function cbf_detector_struct_displacement_get>, 'increment': <built-in function cbf_detector_struct_increment_get>, 'index': <built-in function cbf_detector_struct_index_get>, 'positioner': <built-in function cbf_detector_struct_positioner_get>}
    __swig_setmethods__ = {'axes': <built-in function cbf_detector_struct_axes_set>, 'displacement': <built-in function cbf_detector_struct_displacement_set>, 'increment': <built-in function cbf_detector_struct_increment_set>, 'index': <built-in function cbf_detector_struct_index_set>, 'positioner': <built-in function cbf_detector_struct_positioner_set>}
    __weakref__ = <attribute '__weakref__' of 'cbf_detector_struct' objects>
    list of weak references to the object (if defined)

     
    class cbf_handle_struct(__builtin__.object)
        Proxy of C cbf_handle_struct struct
     
      Methods defined here:
    __del__ lambda self
    __getattr__ lambda self, name
    __init__(self, *args)
    __init__(self) -> cbf_handle_struct
    __repr__ = _swig_repr(self)
    __setattr__ lambda self, name, value
    category_name(*args)
    Returns : 
    *args   : string
     
    C prototype: int cbf_category_name (cbf_handle handle,
                     const char **categoryname);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_category_name sets *categoryname to point to the name of the 
    current category of the current data block.
    The category name will be valid as long as the category exists.
    The name must not be modified by the program in any way.
    ARGUMENTS
    handle         CBF handle. categoryname   Pointer to the destination 
    category name pointer.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    column_name(*args)
    Returns : 
    *args   : string
     
    C prototype: int cbf_column_name (cbf_handle handle, const char **columnname);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_column_name sets *columnname to point to the name of the current 
    column of the current category.
    The column name will be valid as long as the column exists.
    The name must not be modified by the program in any way.
    ARGUMENTS
    handle       CBF handle. columnname   Pointer to the destination 
    column name pointer.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    construct_detector(*args)
    Returns : pycbf detector object
    *args   : Integer element_number
     
    C prototype: int cbf_construct_detector (cbf_handle handle,
                     cbf_detector *detector,    unsigned int element_number);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_construct_detector constructs a detector object for detector 
    element number element_number using the description in the CBF object 
    handle and initialises the detector handle *detector.
    ARGUMENTS
    handle   CBF handle. detector   Pointer to the destination detector 
    handle. element_number   The number of the detector element counting 
    from 0 by order of appearance in the "diffrn_data_frame" category.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    construct_goniometer(*args)
    Returns : pycbf goniometer object
    *args   : 
     
    C prototype: int cbf_construct_goniometer (cbf_handle handle,
                     cbf_goniometer    *goniometer);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_construct_goniometer constructs a goniometer object using the 
    description in the CBF object handle and initialises the goniometer 
    handle *goniometer.
    ARGUMENTS
    handle       CBF handle. goniometer   Pointer to the destination 
    goniometer handle.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    count_categories(*args)
    Returns : unsigned
    *args   : 
     
    C prototype: int cbf_count_categories (cbf_handle handle,
                     unsigned int    *categories);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_count_categories puts the number of categories in the current 
    data block in *categories.
    ARGUMENTS
    handle       CBF handle. categories   Pointer to the destination 
    category count.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    count_columns(*args)
    Returns : Integer
    *args   : 
     
    C prototype: int cbf_count_columns (cbf_handle handle, unsigned int *columns);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_count_columns puts the number of columns in the current category 
    in *columns.
    ARGUMENTS
    handle    CBF handle. columns   Pointer to the destination column 
    count.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    count_datablocks(*args)
    Returns : unsigned
    *args   : 
     
    C prototype: int cbf_count_datablocks (cbf_handle handle,
                     unsigned int    *datablocks);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_count_datablocks puts the number of data blocks in *datablocks .
    ARGUMENTS
    handle       CBF handle. datablocks   Pointer to the destination data 
    block count.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    count_elements(*args)
    Returns : Integer
    *args   : 
     
    C prototype: int cbf_count_elements (cbf_handle handle,
                     unsigned int *elements);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_count_elements sets *elements to the number of detector elements.
    ARGUMENTS
    handle     CBF handle. elements   Pointer to the destination count.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    count_rows(*args)
    Returns : Integer
    *args   : 
     
    C prototype: int cbf_count_rows (cbf_handle handle, unsigned int *rows);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_count_rows puts the number of rows in the current category in 
    *rows .
    ARGUMENTS
    handle   CBF handle. rows     Pointer to the destination row count.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    datablock_name(*args)
    Returns : 
    *args   : string
     
    C prototype: int cbf_datablock_name (cbf_handle handle,
                     const char    **datablockname);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_datablock_name sets *datablockname to point to the name of the 
    current data block.
    The data block name will be valid as long as the data block exists 
    and has not been renamed.
    The name must not be modified by the program in any way.
    ARGUMENTS
    handle          CBF handle. datablockname   Pointer to the 
    destination data block name pointer.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    delete_row(*args)
    Returns : 
    *args   : Integer
     
    C prototype: int cbf_delete_row (cbf_handle handle, unsigned int rownumber);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_delete_row deletes a row from the current category. Rows starting 
    from rownumber +1 are moved down by 1. If the current row was higher 
    than rownumber, or if the current row is the last row, it will also 
    move down by 1.
    The row numbers start from 0.
    ARGUMENTS
    handle      CBF handle. rownumber   The number of the row to delete.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    find_category(*args)
    Returns : string
    *args   : 
     
    C prototype: int cbf_find_category (cbf_handle handle,
                     const char *categoryname);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_find_category makes the category in the current data block with 
    name categoryname the current category.
    The comparison is case-insensitive.
    If the category does not exist, the function returns CBF_NOTFOUND.
    The current column and row become undefined.
    ARGUMENTS
    handle         CBF handle. categoryname   The name of the category to 
    find.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    find_category_root(*args)
    Returns : String categoryroot
    *args   : String categoryname
     
    C prototype: int cbf_find_category_root (cbf_handle handle,
                     const char*    categoryname, const char** categoryroot);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_find_category_root sets *categoryroot to the root category of 
    which categoryname is an alias. cbf_set_category_root sets 
    categoryname_in as an alias of categoryroot in the dictionary 
    associated with handle, creating the dictionary if necessary. 
    cbf_require_category_root sets *categoryroot to the root category of 
    which categoryname is an alias, if there is one, or to the value of 
    categoryname, if categoryname is not an alias.
    A returned categoryroot string must not be modified in any way.
    ARGUMENTS
    handle            CBF handle. categoryname      category name which 
    may be an alias. categoryroot      pointer to a returned category 
    root name. categoryroot_in   input category root name.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    find_column(*args)
    Returns : string
    *args   : 
     
    C prototype: int cbf_find_column (cbf_handle handle, const char *columnname);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_find_column makes the columns in the current category with name 
    columnname the current column.
    The comparison is case-insensitive.
    If the column does not exist, the function returns CBF_NOTFOUND.
    The current row is not affected.
    ARGUMENTS
    handle       CBF handle. columnname   The name of column to find.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    find_datablock(*args)
    Returns : string
    *args   : 
     
    C prototype: int cbf_find_datablock (cbf_handle handle,
                     const char *datablockname);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_find_datablock makes the data block with name datablockname the 
    current data block.
    The comparison is case-insensitive.
    If the data block does not exist, the function returns CBF_NOTFOUND.
    The current category becomes undefined.
    ARGUMENTS
    handle          CBF handle. datablockname   The name of the data 
    block to find.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    find_nextrow(*args)
    Returns : string
    *args   : 
     
    C prototype: int cbf_find_nextrow (cbf_handle handle, const char *value);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_find_nextrow makes the makes the next row in the current column 
    with value value the current row. The search starts from the row 
    following the last row found with cbf_find_row or cbf_find_nextrow, 
    or from the current row if the current row was defined using any 
    other function.
    The comparison is case-sensitive.
    If no more matching rows exist, the function returns CBF_NOTFOUND.
    The current column is not affected.
    ARGUMENTS
    handle   CBF handle. value    the value to search for.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    find_row(*args)
    Returns : string
    *args   : 
     
    C prototype: int cbf_find_row (cbf_handle handle, const char *value);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_find_row makes the first row in the current column with value 
    value the current row.
    The comparison is case-sensitive.
    If a matching row does not exist, the function returns CBF_NOTFOUND.
    The current column is not affected.
    ARGUMENTS
    handle   CBF handle. value    The value of the row to find.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    find_tag_category(*args)
    Returns : String categoryname_in
    *args   : String tagname
     
    C prototype: int cbf_find_tag_category (cbf_handle handle,
                     const char* tagname,    const char** categoryname);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_find_tag_category sets categoryname to the category associated 
    with tagname in the dictionary associated with handle. 
    cbf_set_tag_category upddates the dictionary associated with handle 
    to indicated that tagname is in category categoryname_in.
    ARGUMENTS
    handle            CBF handle. tagname           tag name. 
    categoryname      pointer to a returned category name. 
    categoryname_in   input category name.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    find_tag_root(*args)
    Returns : String tagroot
    *args   : String tagname
     
    C prototype: int cbf_find_tag_root (cbf_handle handle, const char* tagname,
                     const    char** tagroot);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_find_tag_root sets *tagroot to the root tag of which tagname is 
    an alias. cbf_set_tag_root sets tagname as an alias of tagroot_in in 
    the dictionary associated with handle, creating the dictionary if 
    necessary. cbf_require_tag_root sets *tagroot to the root tag of 
    which tagname is an alias, if there is one, or to the value of 
    tagname, if tagname is not an alias.
    A returned tagroot string must not be modified in any way.
    ARGUMENTS
    handle       CBF handle. tagname      tag name which may be an alias. 
    tagroot      pointer to a returned tag root name. tagroot_in   input 
    tag root name.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    force_new_category(*args)
    Returns : string
    *args   : 
     
    C prototype: int cbf_force_new_category (cbf_handle handle,
                     const char    *categoryname);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_force_new_category creates a new category in the current data 
    block with name categoryname and makes it the current category. 
    Duplicate category names are allowed.
    Even if a category with this name already exists, a new category of 
    the same name is created and becomes the current category. The allows 
    for the creation of unlooped tag/value lists drawn from the same 
    category.
    ARGUMENTS
    handle         CBF handle. categoryname   The name of the new 
    category.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    force_new_datablock(*args)
    Returns : string
    *args   : 
     
    C prototype: int cbf_force_new_datablock (cbf_handle handle,
                     const char    *datablockname);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_force_new_datablock creates a new data block with name 
    datablockname and makes it the current data block. Duplicate data 
    block names are allowed. cbf_force_new_saveframe creates a new savew 
    frame with name saveframename and makes it the current save frame. 
    Duplicate save frame names are allowed.
    Even if a save frame with this name already exists, a new save frame 
    is created and becomes the current save frame.
    ARGUMENTS
    handle          CBF handle. datablockname   The name of the new data 
    block. saveframename   The name of the new save frame.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    force_new_saveframe(*args)
    Returns : string
    *args   : 
     
    C prototype: int cbf_force_new_saveframe (cbf_handle handle,
                     const char    *saveframename);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_force_new_datablock creates a new data block with name 
    datablockname and makes it the current data block. Duplicate data 
    block names are allowed. cbf_force_new_saveframe creates a new savew 
    frame with name saveframename and makes it the current save frame. 
    Duplicate save frame names are allowed.
    Even if a save frame with this name already exists, a new save frame 
    is created and becomes the current save frame.
    ARGUMENTS
    handle          CBF handle. datablockname   The name of the new data 
    block. saveframename   The name of the new save frame.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    get_3d_image(*args)
    get_3d_image(self, void ?)
    get_3d_image_size(*args)
    get_3d_image_size(self, void ?)
    get_axis_setting(*args)
    Returns : Float start,Float increment
    *args   : String axis_id
     
    C prototype: int cbf_get_axis_setting (cbf_handle handle,
                     unsigned int reserved,    const char *axis_id, double *start,
                     double *increment);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_axis_setting sets *start and *increment to the corresponding 
    values of the axis axis_id.
    Either of the destination pointers may be NULL.
    The parameter reserved is presently unused and should be set to 0.
    ARGUMENTS
    handle      CBF handle. reserved    Unused. Any value other than 0 is 
    invalid. axis_id     Axis id. start       Pointer to the destination 
    start value. increment   Pointer to the destination increment value.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    get_bin_sizes(*args)
    get_bin_sizes(self, void ?)
    get_crystal_id(*args)
    Returns : 
    *args   : string
     
    C prototype: int cbf_get_crystal_id (cbf_handle handle,
                     const char **crystal_id);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_crystal_id sets *crystal_id to point to the ASCII value of 
    the "diffrn.crystal_id" entry.
    If the value is not ASCII, the function returns CBF_BINARY.
    The value will be valid as long as the item exists and has not been 
    set to a new value.
    The value must not be modified by the program in any way.
    ARGUMENTS
    handle       CBF handle. crystal_id   Pointer to the destination 
    value pointer.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    get_datestamp(*args)
    Returns : int year,int month,int day,int hour,int minute,double second,
              int timezone
    *args   : 
     
    C prototype: int cbf_get_datestamp (cbf_handle handle, unsigned int reserved,
                     int    *year, int *month, int *day, int *hour, int *minute,
                     double *second,    int *timezone);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_datestamp sets *year, *month, *day, *hour, *minute and 
    *second to the corresponding values of the collection timestamp. 
    *timezone is set to timezone difference from UTC in minutes. The 
    parameter < i>reserved is presently unused and should be set to 0.
    Any of the destination pointers may be NULL.
    ARGUMENTS
    handle   CBF handle. reserved   Unused. Any value other than 0 is 
    invalid. year   Pointer to the destination timestamp year. month   
    Pointer to the destination timestamp month (1-12). day   Pointer to 
    the destination timestamp day (1-31). hour   Pointer to the 
    destination timestamp hour (0-23). minute   Pointer to the 
    destination timestamp minute (0-59). second   Pointer to the 
    destination timestamp second (0-60.0). timezone   Pointer to the 
    destination timezone difference from UTC in minutes.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    get_dictionary(*args)
    Returns : CBFHandle dictionary
    *args   : 
     
    C prototype: int cbf_get_dictionary (cbf_handle handle,
                     cbf_handle * dictionary);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_dictionary sets *dictionary to the handle of a CBF which has 
    been associated with the CBF handle by cbf_set_dictionary. 
    cbf_set_dictionary associates the CBF handle dictionary_in with 
    handle as its dictionary. cbf_require_dictionary sets *dictionary to 
    the handle of a CBF which has been associated with the CBF handle by 
    cbf_set_dictionary or creates a new empty CBF and associates it with 
    handle, returning the new handle in *dictionary.
    ARGUMENTS
    handle          CBF handle. dictionary      Pointer to CBF handle of 
    dictionary. dictionary_in   CBF handle of dcitionary.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    get_diffrn_id(*args)
    Returns : 
    *args   : string
     
    C prototype: int cbf_get_diffrn_id (cbf_handle handle,
                     const char **diffrn_id);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_diffrn_id sets *diffrn_id to point to the ASCII value of the 
    "diffrn.id" entry. cbf_require_diffrn_id also sets *diffrn_id to 
    point to the ASCII value of the "diffrn.id" entry, but, if the 
    "diffrn.id" entry does not exist, it sets the value in the CBF and 
    in*diffrn_id to the character string given by default_id, creating 
    the category and column is necessary.
    The diffrn_id will be valid as long as the item exists and has not 
    been set to a new value.
    The diffrn_id must not be modified by the program in any way.
    ARGUMENTS
    handle       CBF handle. diffrn_id    Pointer to the destination 
    value pointer. default_id   Character string default value.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    get_divergence(*args)
    Returns : Float div_x_source,Float div_y_source,Float div_x_y_source
    *args   : 
     
    C prototype: int cbf_get_divergence (cbf_handle handle, double *div_x_source,
                        double *div_y_source, double *div_x_y_source);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_divergence sets *div_x_source, *div_y_source and 
    *div_x_y_source to the corresponding source divergence parameters.
    Any of the destination pointers may be NULL.
    ARGUMENTS
    handle           CBF handle. div_x_source     Pointer to the 
    destination div_x_source. div_y_source     Pointer to the destination 
    div_y_source. div_x_y_source   Pointer to the destination 
    div_x_y_source.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    get_doublevalue(*args)
    Returns : double
    *args   : 
     
    C prototype: int cbf_get_doublevalue (cbf_handle handle, double *number);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_doublevalue sets *number to the value of the ASCII item at 
    the current column and row interpreted as a decimal floating-point 
    number. cbf_require_doublevalue sets *number to the value of the 
    ASCII item at the current column and row interpreted as a decimal 
    floating-point number, setting it to defaultvalue if necessary.
    If the value is not ASCII, the function returns CBF_BINARY.
    ARGUMENTS
    handle         CBF handle. number         Pointer to the destination 
    number. defaultvalue   default number value.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    get_element_id(*args)
    Returns : String
    *args   : Integer element_number
     
    C prototype: int cbf_get_element_id (cbf_handle handle,
                     unsigned int    element_number, const char **element_id);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_element_id sets *element_id to point to the ASCII value of 
    the element_number th "diffrn_data_frame.detector_element_id" 
    entry, counting from 0.
    If the detector element does not exist, the function returns 
    CBF_NOTFOUND.
    The element_id will be valid as long as the item exists and has not 
    been set to a new value.
    The element_id must not be modified by the program in any way.
    ARGUMENTS
    handle   CBF handle. element_number   The number of the detector 
    element counting from 0 by order of appearance in the 
    "diffrn_data_frame" category. element_id   Pointer to the 
    destination.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    get_gain(*args)
    Returns : Float gain,Float gain_esd
    *args   : 
     
    C prototype: int cbf_get_gain (cbf_handle handle, unsigned int element_number,
                        double *gain, double *gain_esd);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_gain sets *gain and *gain_esd to the corresponding gain 
    parameters for element number element_number.
    Either of the destination pointers may be NULL.
    ARGUMENTS
    handle   CBF handle. element_number   The number of the detector 
    element counting from 0 by order of appearance in the 
    "diffrn_data_frame" category. gain   Pointer to the destination 
    gain. gain_esd   Pointer to the destination gain_esd.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    get_image(*args)
    get_image(self, void ?)
    get_image_size(*args)
    Returns : size_t ndim1,size_t ndim2
    *args   : Integer element_number
     
    C prototype: int cbf_get_image_size (cbf_handle handle, unsigned int reserved,
                        unsigned int element_number, size_t *ndim1, size_t *ndim2);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_image_size sets *ndim1 and *ndim2 to the slow and fast 
    dimensions of the image array for element number element_number. If 
    the array is 1-dimensional, *ndim1 will be set to the array size and 
    *ndim2 will be set to 1. If the array is 3-dimensional an error code 
    will be returned. cbf_get_3d_image_size sets *ndim1, *ndim2 and 
    *ndim3 to the slowest, next fastest and fastest dimensions, 
    respectively, of the 3D image array for element number 
    element_number. If the array is 1-dimensional, *ndim1 will be set to 
    the array size and *ndim2 and
    get_integerarray_as_string(*args)
    Returns : (Binary)String
    *args   : 
     
    C prototype: int cbf_get_integerarray (cbf_handle handle, int *binary_id,
                     void    *array, size_t elsize, int elsigned, size_t elements,
                     size_t    *elements_read);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_integerarray reads the binary value of the item at the 
    current column and row into an integer array. The array consists of 
    elements elements of elsize bytes each, starting at array. The 
    elements are signed if elsigned is non-0 and unsigned otherwise. 
    *binary_id is set to the binary section identifier and *elements_read 
    to the number of elements actually read. cbf_get_realarray reads the 
    binary value of the item at the current column and row into a real 
    array. The array consists of elements elements of elsize bytes each, 
    starting at array. *binary_id is set to the binary section identifier 
    and *elements_read to the number of elements actually read.
    If any element in the integer binary data cant fit into the 
    destination element, the destination is set the nearest possible 
    value.
    If the value is not binary, the function returns CBF_ASCII.
    If the requested number of elements cant be read, the function will 
    read as many as it can and then return CBF_ENDOFDATA.
    Currently, the destination array must consist of chars, shorts or 
    ints (signed or unsigned). If elsize is not equal to sizeof (char), 
    sizeof (short) or sizeof (int), for cbf_get_integerarray, or 
    sizeof(double) or sizeof(float), for cbf_get_realarray the function 
    returns CBF_ARGUMENT.
    An additional restriction in the current version of CBFlib is that 
    values too large to fit in an int are not correctly decompressed. As 
    an example, if the machine with 32-bit ints is reading an array 
    containing a value outside the range 0 .. 2^32-1 (unsigned) or -2^31 
    .. 2^31-1 (signed), the array will not be correctly decompressed. 
    This restriction will be removed in a future release. For 
    cbf_get_realarray, only IEEE format is supported. No conversion to 
    other floating point formats is done at this time.
    ARGUMENTS
    handle   CBF handle. binary_id   Pointer to the destination integer 
    binary identifier. array   Pointer to the destination array. elsize   
    Size in bytes of each destination array element. elsigned   Set to 
    non-0 if the destination array elements are signed. elements   The 
    number of elements to read. elements_read   Pointer to the 
    destination number of elements actually read.
    RETURN VALUE
    Returns an error code on failure or 0 for success. SEE ALSO
    get_integerarrayparameters(*args)
    Returns : int compression,int binary_id,int elsize,int elsigned,int elunsigned,
              int elements,int minelement,int maxelement
    *args   : 
     
    C prototype: int cbf_get_integerarrayparameters (cbf_handle handle,
                     unsigned int    *compression, int *binary_id, size_t *elsize,
                     int *elsigned, int    *elunsigned, size_t *elements,
                     int *minelement, int *maxelement);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_integerarrayparameters sets *compression, *binary_id, 
    *elsize, *elsigned, *elunsigned, *elements, *minelement and 
    *maxelement to values read from the binary value of the item at the 
    current column and row. This provides all the arguments needed for a 
    subsequent call to cbf_set_integerarray, if a copy of the array is to 
    be made into another CIF or CBF. cbf_get_realarrayparameters sets 
    *compression, *binary_id, *elsize, *elements to values read from the 
    binary value of the item at the current column and row. This provides 
    all the arguments needed for a subsequent call to cbf_set_realarray, 
    if a copy of the arry is to be made into another CIF or CBF.
    The variants cbf_get_integerarrayparameters_wdims and 
    cbf_get_realarrayparameters_wdims set **byteorder, *dim1, *dim2, 
    *dim3, and *padding as well, providing the additional parameters 
    needed for a subsequent call to cbf_set_integerarray_wdims or 
    cbf_set_realarray_wdims.
    The value returned in *byteorder is a pointer either to the string 
    "little_endian" or to the string "big_endian". This should be the 
    byte order of the data, not necessarily of the host machine. No 
    attempt should be made to modify this string. At this time only 
    "little_endian" will be returned.
    The values returned in *dim1, *dim2 and *dim3 are the sizes of the 
    fastest changing, second fastest changing and third fastest changing 
    dimensions of the array, if specified, or zero, if not specified.
    The value returned in *padding is the size of the post-data padding, 
    if any and if specified in the data header. The value is given as a 
    count of octets.
    If the value is not binary, the function returns CBF_ASCII.
    ARGUMENTS
    handle   CBF handle. compression   Compression method used. elsize   
    Size in bytes of each array element. binary_id   Pointer to the 
    destination integer binary identifier. elsigned   Pointer to an 
    integer. Set to 1 if the elements can be read as signed integers. 
    elunsigned   Pointer to an integer. Set to 1 if the elements can be 
    read as unsigned integers. elements   Pointer to the destination 
    number of elements. minelement   Pointer to the destination smallest 
    element. maxelement   Pointer to the destination largest element. 
    byteorder   Pointer to the destination byte order. dim1   Pointer to 
    the destination fastest dimension. dim2   Pointer to the destination 
    second fastest dimension. dim3   Pointer to the destination third 
    fastest dimension. padding   Pointer to the destination padding size.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    get_integerarrayparameters_wdims(*args)
    get_integerarrayparameters_wdims(self, void ?)
    get_integervalue(*args)
    Returns : int
    *args   : 
     
    C prototype: int cbf_get_integervalue (cbf_handle handle, int *number);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_integervalue sets *number to the value of the ASCII item at 
    the current column and row interpreted as a decimal integer. 
    cbf_require_integervalue sets *number to the value of the ASCII item 
    at the current column and row interpreted as a decimal integer, 
    setting it to defaultvalue if necessary.
    If the value is not ASCII, the function returns CBF_BINARY.
    ARGUMENTS
    handle         CBF handle. number         pointer to the number. 
    defaultvalue   default number value.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    get_integration_time(*args)
    Returns : Float time
    *args   : 
     
    C prototype: int cbf_get_integration_time (cbf_handle handle,
                     unsigned int    reserved, double *time);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_integration_time sets *time to the integration time in 
    seconds. The parameter reserved is presently unused and should be set 
    to 0.
    ARGUMENTS
    handle     CBF handle. reserved   Unused. Any value other than 0 is 
    invalid. time       Pointer to the destination time.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    get_orientation_matrix(*args)
    Returns : Float matrix_0,Float matrix_1,Float matrix_2,Float matrix_3,
              Float matrix_4,Float matrix_5,Float matrix_6,Float matrix_7,
              Float matrix_8
    *args   : 
     
    C prototype: int cbf_get_orientation_matrix (cbf_handle handle,
                     double    ub_matrix[9]);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_orientation_matrix sets ub_matrix to point to the array of 
    orientation matrix entries in the "diffrn" category in the order of 
    columns:
    "UB[1][1]" "UB[1][2]" "UB[1][3]" "UB[2][1]" "UB[2][2]" 
    "UB[2][3]" "UB[3][1]" "UB[3][2]" "UB[3][3]"
    cbf_set_orientation_matrix sets the values in the "diffrn" category 
    to the values pointed to by ub_matrix.
    ARGUMENTS
    handle   CBF handle. ubmatric   Source or destination array of 9 
    doubles giving the orientation matrix parameters.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    get_overload(*args)
    Returns : Float overload
    *args   : Integer element_number
     
    C prototype: int cbf_get_overload (cbf_handle handle,
                     unsigned int element_number,    double *overload);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_overload sets *overload to the overload value for element 
    number element_number.
    ARGUMENTS
    handle   CBF handle. element_number   The number of the detector 
    element counting from 0 by order of appearance in the 
    "diffrn_data_frame" category. overload   Pointer to the destination 
    overload.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    get_pixel_size(*args)
    Returns : Float pixel_size
    *args   : Int element_number,Int axis_number
     
    C prototype: int cbf_get_pixel_size (cbf_handle handle,
                     unsigned int    element_number, unsigned int axis_number,
                     double *psize);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_pixel_size sets *psize to point to the double value in 
    millimeters of the axis axis_number of the detector element 
    element_number. The axis_number is numbered from 1, starting with the 
    fastest axis.
    If the pixel size is not given explcitly in the 
    "array_element_size" category, the function returns CBF_NOTFOUND.
    ARGUMENTS
    handle   CBF handle. element_number   The number of the detector 
    element counting from 0 by order of appearance in the 
    "diffrn_data_frame" category. axis_number   The number of the axis, 
    fastest first, starting from 1.
    get_polarization(*args)
    Returns : float polarizn_source_ratio,float polarizn_source_norm
    *args   : 
     
    C prototype: int cbf_get_polarization (cbf_handle handle,
                     double    *polarizn_source_ratio,
                     double *polarizn_source_norm);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_polarization sets *polarizn_source_ratio and 
    *polarizn_source_norm to the corresponding source polarization 
    parameters.
    Either destination pointer may be NULL.
    ARGUMENTS
    handle   CBF handle. polarizn_source_ratio   Pointer to the 
    destination polarizn_source_ratio. polarizn_source_norm   Pointer to 
    the destination polarizn_source_norm.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    get_real_3d_image(*args)
    get_real_3d_image(self, void ?)
    get_real_image(*args)
    get_real_image(self, void ?)
    get_realarray(*args)
    get_realarray(self, void ?)
    get_realarrayparameters(*args)
    Returns : int compression,int binary_id,int elsize,int elements
    *args   : 
     
    C prototype: int cbf_get_realarrayparameters (cbf_handle handle,
                     unsigned int    *compression, int *binary_id, size_t *elsize,
                     size_t *elements);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_integerarrayparameters sets *compression, *binary_id, 
    *elsize, *elsigned, *elunsigned, *elements, *minelement and 
    *maxelement to values read from the binary value of the item at the 
    current column and row. This provides all the arguments needed for a 
    subsequent call to cbf_set_integerarray, if a copy of the array is to 
    be made into another CIF or CBF. cbf_get_realarrayparameters sets 
    *compression, *binary_id, *elsize, *elements to values read from the 
    binary value of the item at the current column and row. This provides 
    all the arguments needed for a subsequent call to cbf_set_realarray, 
    if a copy of the arry is to be made into another CIF or CBF.
    The variants cbf_get_integerarrayparameters_wdims and 
    cbf_get_realarrayparameters_wdims set **byteorder, *dim1, *dim2, 
    *dim3, and *padding as well, providing the additional parameters 
    needed for a subsequent call to cbf_set_integerarray_wdims or 
    cbf_set_realarray_wdims.
    The value returned in *byteorder is a pointer either to the string 
    "little_endian" or to the string "big_endian". This should be the 
    byte order of the data, not necessarily of the host machine. No 
    attempt should be made to modify this string. At this time only 
    "little_endian" will be returned.
    The values returned in *dim1, *dim2 and *dim3 are the sizes of the 
    fastest changing, second fastest changing and third fastest changing 
    dimensions of the array, if specified, or zero, if not specified.
    The value returned in *padding is the size of the post-data padding, 
    if any and if specified in the data header. The value is given as a 
    count of octets.
    If the value is not binary, the function returns CBF_ASCII.
    ARGUMENTS
    handle   CBF handle. compression   Compression method used. elsize   
    Size in bytes of each array element. binary_id   Pointer to the 
    destination integer binary identifier. elsigned   Pointer to an 
    integer. Set to 1 if the elements can be read as signed integers. 
    elunsigned   Pointer to an integer. Set to 1 if the elements can be 
    read as unsigned integers. elements   Pointer to the destination 
    number of elements. minelement   Pointer to the destination smallest 
    element. maxelement   Pointer to the destination largest element. 
    byteorder   Pointer to the destination byte order. dim1   Pointer to 
    the destination fastest dimension. dim2   Pointer to the destination 
    second fastest dimension. dim3   Pointer to the destination third 
    fastest dimension. padding   Pointer to the destination padding size.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    get_realarrayparameters_wdims(*args)
    get_realarrayparameters_wdims(self, void ?)
    get_reciprocal_cell(*args)
    get_reciprocal_cell(self, void ?)
    get_timestamp(*args)
    Returns : Float time,Integer timezone
    *args   : 
     
    C prototype: int cbf_get_timestamp (cbf_handle handle, unsigned int reserved,
                        double *time, int *timezone);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_timestamp sets *time to the collection timestamp in seconds 
    since January 1 1970. *timezone is set to timezone difference from 
    UTC in minutes. The parameter reserved is presently unused and should 
    be set to 0.
    Either of the destination pointers may be NULL.
    ARGUMENTS
    handle     CBF handle. reserved   Unused. Any value other than 0 is 
    invalid. time       Pointer to the destination collection timestamp. 
    timezone   Pointer to the destination timezone difference.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    get_typeofvalue(*args)
    Returns : 
    *args   : string
     
    C prototype: int cbf_get_typeofvalue (cbf_handle handle,
                     const char **typeofvalue);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_value sets *typeofvalue to point an ASCII descriptor of the 
    value of the item at the current column and row. The strings that may 
    be returned are "null" for a null value indicated by a "." or a 
    "?", "bnry" for a binary value, "word" for an unquoted string, 
    "dblq" for a double-quoted string, "sglq" for a single-quoted 
    string, and "text" for a semicolon-quoted text field. A field for 
    which no value has been set sets *typeofvalue to NULL rather than to 
    the string "null".
    The typeofvalue must not be modified by the program in any way.
    ARGUMENTS
    handle   CBF handle. typeofvalue   Pointer to the destination 
    type-of-value string pointer.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    get_unit_cell(*args)
    get_unit_cell(self, void ?)
    get_value(*args)
    Returns : 
    *args   : string
     
    C prototype: int cbf_get_value (cbf_handle handle, const char **value);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_value sets *value to point to the ASCII value of the item at 
    the current column and row. cbf_set_value sets *value to point to the 
    ASCII value of the item at the current column and row, creating the 
    data item if necessary and initializing it to a copy of defaultvalue.
    If the value is not ASCII, the function returns CBF_BINARY.
    The value will be valid as long as the item exists and has not been 
    set to a new value.
    The value must not be modified by the program in any way.
    ARGUMENTS
    handle   CBF handle. value    Pointer to the destination value 
    pointer. value    Default value character string.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    get_wavelength(*args)
    Returns : double
    *args   : 
     
    C prototype: int cbf_get_wavelength (cbf_handle handle, double *wavelength);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_wavelength sets *wavelength to the current wavelength in 
    Angstrom.
    ARGUMENTS
    handle       CBF handle. wavelength   Pointer to the destination.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    insert_row(*args)
    Returns : 
    *args   : Integer
     
    C prototype: int cbf_insert_row (cbf_handle handle, unsigned int rownumber);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_insert_row adds a new row to the current category. The new row is 
    inserted as row rownumber and existing rows starting from rownumber 
    are moved up by 1. The new row becomes the current row.
    If the category has fewer than rownumber rows, the function returns 
    CBF_NOTFOUND.
    The row numbers start from 0.
    ARGUMENTS
    handle      CBF handle. rownumber   The row number of the new row.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    new_category(*args)
    Returns : string
    *args   : 
     
    C prototype: int cbf_new_category (cbf_handle handle,
                     const char *categoryname);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_new_category creates a new category in the current data block 
    with name categoryname and makes it the current category.
    If a category with this name already exists, the existing category 
    becomes the current category.
    ARGUMENTS
    handle         CBF handle. categoryname   The name of the new 
    category.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    new_column(*args)
    Returns : string
    *args   : 
     
    C prototype: int cbf_new_column (cbf_handle handle, const char *columnname);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_new_column creates a new column in the current category with name 
    columnname and makes it the current column.
    If a column with this name already exists, the existing column 
    becomes the current category.
    ARGUMENTS
    handle       CBF handle. columnname   The name of the new column.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    new_datablock(*args)
    Returns : string
    *args   : 
     
    C prototype: int cbf_new_datablock (cbf_handle handle,
                     const char *datablockname);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_new_datablock creates a new data block with name datablockname 
    and makes it the current data block. cbf_new_saveframe creates a new 
    save frame with name saveframename within the current data block and 
    makes the new save frame the current save frame.
    If a data block or save frame with this name already exists, the 
    existing data block or save frame becomes the current data block or 
    save frame.
    ARGUMENTS
    handle          CBF handle. datablockname   The name of the new data 
    block. saveframename   The name of the new save frame.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    new_row(*args)
    Returns : 
    *args   : 
     
    C prototype: int cbf_new_row (cbf_handle handle);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_new_row adds a new row to the current category and makes it the 
    current row.
    ARGUMENTS
    handle   CBF handle.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    new_saveframe(*args)
    Returns : string
    *args   : 
     
    C prototype: int cbf_new_saveframe (cbf_handle handle,
                     const char *saveframename);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_new_datablock creates a new data block with name datablockname 
    and makes it the current data block. cbf_new_saveframe creates a new 
    save frame with name saveframename within the current data block and 
    makes the new save frame the current save frame.
    If a data block or save frame with this name already exists, the 
    existing data block or save frame becomes the current data block or 
    save frame.
    ARGUMENTS
    handle          CBF handle. datablockname   The name of the new data 
    block. saveframename   The name of the new save frame.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    next_category(*args)
    Returns : 
    *args   : 
     
    C prototype: int cbf_next_category (cbf_handle handle);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_next_category makes the category following the current category 
    in the current data block the current category.
    If there are no more categories, the function returns CBF_NOTFOUND.
    The current column and row become undefined.
    ARGUMENTS
    handle   CBF handle.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    next_column(*args)
    Returns : 
    *args   : 
     
    C prototype: int cbf_next_column (cbf_handle handle);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_next_column makes the column following the current column in the 
    current category the current column.
    If there are no more columns, the function returns CBF_NOTFOUND.
    The current row is not affected.
    ARGUMENTS
    handle   CBF handle.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    next_datablock(*args)
    Returns : 
    *args   : 
     
    C prototype: int cbf_next_datablock (cbf_handle handle);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_next_datablock makes the data block following the current data 
    block the current data block.
    If there are no more data blocks, the function returns CBF_NOTFOUND.
    The current category becomes undefined.
    ARGUMENTS
    handle   CBF handle.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    next_row(*args)
    Returns : 
    *args   : 
     
    C prototype: int cbf_next_row (cbf_handle handle);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_next_row makes the row following the current row in the current 
    category the current row.
    If there are no more rows, the function returns CBF_NOTFOUND.
    The current column is not affected.
    ARGUMENTS
    handle   CBF handle.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    read_file(*args)
    Returns : 
    *args   : String filename,Integer headers
     
    C prototype: int cbf_read_file (cbf_handle handle, FILE *file, int headers);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_read_file reads the CBF or CIF file file into the CBF object 
    specified by handle, using the CIF 1.0 convention of 80 character 
    lines. cbf_read_widefile reads the CBF or CIF file file into the CBF 
    object specified by handle, using the CIF 1.1 convention of 2048 
    character lines. A warning is issued to stderr for ascii lines over 
    the limit. No test is performed on binary sections.
    Validation is performed in three ways levels: during the lexical 
    scan, during the parse, and, if a dictionary was converted, against 
    the value types, value enumerations, categories and parent-child 
    relationships specified in the dictionary.
    headers controls the interprestation of binary section headers of 
    imgCIF files.
    MSG_DIGEST:   Instructs CBFlib to check that the digest of the binary 
    section matches any header value. If the digests do not match, the 
    call will return CBF_FORMAT. This evaluation and comparison is 
    delayed (a "lazy" evaluation) to ensure maximal processing 
    efficiency. If an immediately evaluation is required, see 
    MSG_DIGESTNOW, below. MSG_DIGESTNOW:   Instructs CBFlib to check that 
    the digest of the binary section matches any header value. If the 
    digests do not match, the call will return CBF_FORMAT. This 
    evaluation and comparison is performed during initial parsing of the 
    section to ensure timely error reporting at the expense of processing 
    efficiency. If a more efficient delayed ("lazy") evaluation is 
    required, see MSG_DIGESTNOW, below. MSG_NODIGEST:   Do not check the 
    digest (default).
    CBFlib defers reading binary sections as long as possible. In the 
    current version of CBFlib, this means that:
    1. The file must be a random-access file opened in binary mode (fopen
    read_template(*args)
    Returns : 
    *args   : String filename
     
    C prototype: int cbf_read_template (cbf_handle handle, FILE *file);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_read_template reads the CBF or CIF file file into the CBF object 
    specified by handle and selects the first datablock as the current 
    datablock.
    ARGUMENTS
    handle   Pointer to a CBF handle. file     Pointer to a file 
    descriptor.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    read_widefile(*args)
    read_widefile(self, void ?)
    remove_category(*args)
    Returns : 
    *args   : 
     
    C prototype: int cbf_remove_category (cbf_handle handle);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_remove_category deletes the current category.
    The current category becomes undefined.
    ARGUMENTS
    handle   CBF handle.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    remove_column(*args)
    Returns : 
    *args   : 
     
    C prototype: int cbf_remove_column (cbf_handle handle);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_remove_column deletes the current column.
    The current column becomes undefined.
    ARGUMENTS
    handle   CBF handle.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    remove_datablock(*args)
    Returns : 
    *args   : 
     
    C prototype: int cbf_remove_datablock (cbf_handle handle);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_remove_datablock deletes the current data block. 
    cbf_remove_saveframe deletes the current save frame.
    The current data block becomes undefined.
    ARGUMENTS
    handle   CBF handle.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    remove_row(*args)
    Returns : 
    *args   : 
     
    C prototype: int cbf_remove_row (cbf_handle handle);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_remove_row deletes the current row in the current category.
    If the current row was the last row, it will move down by 1, 
    otherwise, it will remain the same.
    ARGUMENTS
    handle   CBF handle.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    remove_saveframe(*args)
    Returns : 
    *args   : 
     
    C prototype: int cbf_remove_saveframe (cbf_handle handle);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_remove_datablock deletes the current data block. 
    cbf_remove_saveframe deletes the current save frame.
    The current data block becomes undefined.
    ARGUMENTS
    handle   CBF handle.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    require_category(*args)
    Returns : string
    *args   : 
     
    C prototype: int cbf_require_category (cbf_handle handle,
                     const char    *categoryname);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_rewuire_category makes the category in the current data block 
    with name categoryname the current category, if it exists, or creates 
    the catagory if it does not exist.
    The comparison is case-insensitive.
    The current column and row become undefined.
    ARGUMENTS
    handle         CBF handle. categoryname   The name of the category to 
    find.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    require_category_root(*args)
    require_category_root(self, char categoryname) -> char
    require_column(*args)
    Returns : string
    *args   : 
     
    C prototype: int cbf_require_column (cbf_handle handle,
                     const char *columnname);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_require_column makes the columns in the current category with 
    name columnname the current column, if it exists, or creates it if it 
    does not.
    The comparison is case-insensitive.
    The current row is not affected.
    ARGUMENTS
    handle       CBF handle. columnname   The name of column to find.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    require_column_doublevalue(*args)
    Returns : Float defaultvalue
    *args   : String columnname,Float Value
     
    C prototype: int cbf_require_column_doublevalue (cbf_handle handle,
                     const char    *columnname, double *number,
                     const double defaultvalue);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_require_column_doublevalue sets *number to the value of the ASCII 
    item at the current row for the column given with the name given by 
    *columnname, with the value interpreted as a decimal floating-point 
    number, or to the number given by defaultvalue if the item cannot be 
    found.
    ARGUMENTS
    handle   CBF handle. columnname   Name of the column containing the 
    number. number   pointer to the location to receive the 
    floating-point value. defaultvalue   Value to use if the requested 
    column and value cannot be found.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    require_column_integervalue(*args)
    Returns : Int Value
    *args   : String Columnvalue,Int default
     
    C prototype: int cbf_require_column_integervalue (cbf_handle handle,
                     const char    *columnname, int *number,
                     const int defaultvalue);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_require_column_doublevalue sets *number to the value of the ASCII 
    item at the current row for the column given with the name given by 
    *columnname, with the value interpreted as an integer number, or to 
    the number given by defaultvalue if the item cannot be found.
    ARGUMENTS
    handle   CBF handle. columnname   Name of the column containing the 
    number. number   pointer to the location to receive the integer 
    value. defaultvalue   Value to use if the requested column and value 
    cannot be found.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    require_column_value(*args)
    Returns : String Name
    *args   : String columnnanme,String Default
     
    C prototype: int cbf_require_column_value (cbf_handle handle,
                     const char    *columnname, const char **value,
                     const char *defaultvalue);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_require_column_doublevalue sets *value to the ASCII item at the 
    current row for the column given with the name given by *columnname, 
    or to the string given by defaultvalue if the item cannot be found.
    ARGUMENTS
    handle   CBF handle. columnname   Name of the column containing the 
    number. value   pointer to the location to receive the value. 
    defaultvalue   Value to use if the requested column and value cannot 
    be found.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    require_datablock(*args)
    Returns : string
    *args   : 
     
    C prototype: int cbf_require_datablock (cbf_handle handle,
                     const char    *datablockname);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_require_datablock makes the data block with name datablockname 
    the current data block, if it exists, or creates it if it does not.
    The comparison is case-insensitive.
    The current category becomes undefined.
    ARGUMENTS
    handle          CBF handle. datablockname   The name of the data 
    block to find or create.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    require_doublevalue(*args)
    Returns : Float Number
    *args   : Float Default
     
    C prototype: int cbf_require_doublevalue (cbf_handle handle, double *number,
                     double    defaultvalue);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_doublevalue sets *number to the value of the ASCII item at 
    the current column and row interpreted as a decimal floating-point 
    number. cbf_require_doublevalue sets *number to the value of the 
    ASCII item at the current column and row interpreted as a decimal 
    floating-point number, setting it to defaultvalue if necessary.
    If the value is not ASCII, the function returns CBF_BINARY.
    ARGUMENTS
    handle         CBF handle. number         Pointer to the destination 
    number. defaultvalue   default number value.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    require_integervalue(*args)
    Returns : Int number
    *args   : Int thedefault
     
    C prototype: int cbf_require_integervalue (cbf_handle handle, int *number,
                     int    defaultvalue);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_integervalue sets *number to the value of the ASCII item at 
    the current column and row interpreted as a decimal integer. 
    cbf_require_integervalue sets *number to the value of the ASCII item 
    at the current column and row interpreted as a decimal integer, 
    setting it to defaultvalue if necessary.
    If the value is not ASCII, the function returns CBF_BINARY.
    ARGUMENTS
    handle         CBF handle. number         pointer to the number. 
    defaultvalue   default number value.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    require_tag_root(*args)
    Returns : String tagroot
    *args   : String tagname
     
    C prototype: int cbf_require_tag_root (cbf_handle handle, const char* tagname,
                        const char** tagroot);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_find_tag_root sets *tagroot to the root tag of which tagname is 
    an alias. cbf_set_tag_root sets tagname as an alias of tagroot_in in 
    the dictionary associated with handle, creating the dictionary if 
    necessary. cbf_require_tag_root sets *tagroot to the root tag of 
    which tagname is an alias, if there is one, or to the value of 
    tagname, if tagname is not an alias.
    A returned tagroot string must not be modified in any way.
    ARGUMENTS
    handle       CBF handle. tagname      tag name which may be an alias. 
    tagroot      pointer to a returned tag root name. tagroot_in   input 
    tag root name.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    require_value(*args)
    Returns : String Value
    *args   : String defaultvalue
     
    C prototype: int cbf_require_value (cbf_handle handle, const char **value,
                     const    char *defaultvalue );
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_value sets *value to point to the ASCII value of the item at 
    the current column and row. cbf_set_value sets *value to point to the 
    ASCII value of the item at the current column and row, creating the 
    data item if necessary and initializing it to a copy of defaultvalue.
    If the value is not ASCII, the function returns CBF_BINARY.
    The value will be valid as long as the item exists and has not been 
    set to a new value.
    The value must not be modified by the program in any way.
    ARGUMENTS
    handle   CBF handle. value    Pointer to the destination value 
    pointer. value    Default value character string.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    reset_category(*args)
    Returns : 
    *args   : 
     
    C prototype: int cbf_reset_category (cbf_handle handle);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_reset_category deletes all columns and rows from current category.
    ARGUMENTS
    handle   CBF handle.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    reset_datablock(*args)
    Returns : 
    *args   : 
     
    C prototype: int cbf_reset_datablock (cbf_handle handle);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_reset_datablock deletes all categories from the current data 
    block. cbf_reset_saveframe deletes all categories from the current 
    save frame.
    ARGUMENTS
    handle   CBF handle.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    reset_datablocks(*args)
    Returns : 
    *args   : 
     
    C prototype: int cbf_reset_datablocks (cbf_handle handle);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_reset_datablocks deletes all categories from all data blocks.
    The current data block does not change.
    ARGUMENTS
    handle   CBF handle.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    reset_saveframe(*args)
    Returns : 
    *args   : 
     
    C prototype: int cbf_reset_saveframe (cbf_handle handle);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_reset_datablock deletes all categories from the current data 
    block. cbf_reset_saveframe deletes all categories from the current 
    save frame.
    ARGUMENTS
    handle   CBF handle.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    rewind_blockitem(*args)
    Returns : CBF_NODETYPE
    *args   : 
     
    C prototype: int cbf_rewind_blockitem (cbf_handle handle,
                     CBF_NODETYPE * type);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_rewind_category makes the first category in the current data 
    block the current category. cbf_rewind_saveframe makes the first 
    saveframe in the current data block the current saveframe. 
    cbf_rewind_blockitem makes the first blockitem (category or 
    saveframe) in the current data block the current blockitem.
    If there are no categories, saveframes or blockitems the function 
    returns CBF_NOTFOUND.
    The current column and row become undefined.
    ARGUMENTS
    handle   CBF handle.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    rewind_category(*args)
    Returns : 
    *args   : 
     
    C prototype: int cbf_rewind_category (cbf_handle handle);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_rewind_category makes the first category in the current data 
    block the current category. cbf_rewind_saveframe makes the first 
    saveframe in the current data block the current saveframe. 
    cbf_rewind_blockitem makes the first blockitem (category or 
    saveframe) in the current data block the current blockitem.
    If there are no categories, saveframes or blockitems the function 
    returns CBF_NOTFOUND.
    The current column and row become undefined.
    ARGUMENTS
    handle   CBF handle.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    rewind_column(*args)
    Returns : 
    *args   : 
     
    C prototype: int cbf_rewind_column (cbf_handle handle);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_rewind_column makes the first column in the current category the 
    current column.
    If there are no columns, the function returns CBF_NOTFOUND.
    The current row is not affected.
    ARGUMENTS
    handle   CBF handle.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    rewind_datablock(*args)
    Returns : 
    *args   : 
     
    C prototype: int cbf_rewind_datablock (cbf_handle handle);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_rewind_datablock makes the first data block the current data 
    block.
    If there are no data blocks, the function returns CBF_NOTFOUND.
    The current category becomes undefined.
    ARGUMENTS
    handle   CBF handle.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    rewind_row(*args)
    Returns : 
    *args   : 
     
    C prototype: int cbf_rewind_row (cbf_handle handle);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_rewind_row makes the first row in the current category the 
    current row.
    If there are no rows, the function returns CBF_NOTFOUND.
    The current column is not affected.
    ARGUMENTS
    handle   CBF handle.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    rewind_saveframe(*args)
    Returns : 
    *args   : 
     
    C prototype: int cbf_rewind_saveframe (cbf_handle handle);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_rewind_category makes the first category in the current data 
    block the current category. cbf_rewind_saveframe makes the first 
    saveframe in the current data block the current saveframe. 
    cbf_rewind_blockitem makes the first blockitem (category or 
    saveframe) in the current data block the current blockitem.
    If there are no categories, saveframes or blockitems the function 
    returns CBF_NOTFOUND.
    The current column and row become undefined.
    ARGUMENTS
    handle   CBF handle.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    row_number(*args)
    Returns : Integer
    *args   : 
     
    C prototype: int cbf_row_number (cbf_handle handle, unsigned int *row);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_row_number sets *row to the number of the current row of the 
    current category.
    ARGUMENTS
    handle   CBF handle. row      Pointer to the destination row number.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    select_category(*args)
    Returns : 
    *args   : Integer
     
    C prototype: int cbf_select_category (cbf_handle handle,
                     unsigned int category);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_select_category selects category number category in the current 
    data block as the current category.
    The first category is number 0.
    The current column and row become undefined.
    If the category does not exist, the function returns CBF_NOTFOUND.
    ARGUMENTS
    handle     CBF handle. category   Number of the category to select.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    select_column(*args)
    Returns : 
    *args   : Integer
     
    C prototype: int cbf_select_column (cbf_handle handle, unsigned int column);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_select_column selects column number column in the current 
    category as the current column.
    The first column is number 0.
    The current row is not affected
    If the column does not exist, the function returns CBF_NOTFOUND.
    ARGUMENTS
    handle   CBF handle. column   Number of the column to select.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    select_datablock(*args)
    Returns : 
    *args   : Integer
     
    C prototype: int cbf_select_datablock (cbf_handle handle,
                     unsigned int datablock);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_select_datablock selects data block number datablock as the 
    current data block.
    The first data block is number 0.
    If the data block does not exist, the function returns CBF_NOTFOUND.
    ARGUMENTS
    handle      CBF handle. datablock   Number of the data block to 
    select.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    select_row(*args)
    Returns : 
    *args   : Integer
     
    C prototype: int cbf_select_row (cbf_handle handle, unsigned int row);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_select_row selects row number row in the current category as the 
    current row.
    The first row is number 0.
    The current column is not affected
    If the row does not exist, the function returns CBF_NOTFOUND.
    ARGUMENTS
    handle   CBF handle. row      Number of the row to select.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    set_3d_image(*args)
    set_3d_image(self, void ?)
    set_axis_setting(*args)
    Returns : 
    *args   : String axis_id,Float start,Float increment
     
    C prototype: int cbf_set_axis_setting (cbf_handle handle,
                     unsigned int reserved,    const char *axis_id, double start,
                     double increment);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_set_axis_setting sets the starting and increment values of the 
    axis axis_id to start and increment.
    The parameter reserved is presently unused and should be set to 0.
    ARGUMENTS
    handle      CBF handle. reserved    Unused. Any value other than 0 is 
    invalid. axis_id     Axis id. start       Start value. increment   
    Increment value.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    set_bin_sizes(*args)
    set_bin_sizes(self, void ?)
    set_category_root(*args)
    Returns : 
    *args   : String categoryname,String categoryroot
     
    C prototype: int cbf_set_category_root (cbf_handle handle,
                     const char*    categoryname_in, const char*categoryroot);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_find_category_root sets *categoryroot to the root category of 
    which categoryname is an alias. cbf_set_category_root sets 
    categoryname_in as an alias of categoryroot in the dictionary 
    associated with handle, creating the dictionary if necessary. 
    cbf_require_category_root sets *categoryroot to the root category of 
    which categoryname is an alias, if there is one, or to the value of 
    categoryname, if categoryname is not an alias.
    A returned categoryroot string must not be modified in any way.
    ARGUMENTS
    handle            CBF handle. categoryname      category name which 
    may be an alias. categoryroot      pointer to a returned category 
    root name. categoryroot_in   input category root name.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    set_crystal_id(*args)
    Returns : string
    *args   : 
     
    C prototype: int cbf_set_crystal_id (cbf_handle handle,
                     const char *crystal_id);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_set_crystal_id sets the "diffrn.crystal_id" entry to the ASCII 
    value crystal_id.
    ARGUMENTS
    handle       CBF handle. crystal_id   ASCII value.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    set_datablockname(*args)
    Returns : string
    *args   : 
     
    C prototype: int cbf_set_datablockname (cbf_handle handle,
                     const char    *datablockname);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_set_datablockname changes the name of the current data block to 
    datablockname. cbf_set_saveframename changes the name of the current 
    save frame to saveframename.
    If a data block or save frame with this name already exists 
    (comparison is case-insensitive), the function returns CBF_IDENTICAL.
    ARGUMENTS
    handle          CBF handle. datablockname   The new data block name. 
    datablockname   The new save frame name.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    set_datestamp(*args)
    Returns : 
    *args   : int year,int month,int day,int hour,int minute,double second,
              int timezone,Float precision
     
    C prototype: int cbf_set_datestamp (cbf_handle handle, unsigned int reserved,
                     int    year, int month, int day, int hour, int minute,
                     double second, int    timezone, double precision);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_set_datestamp sets the collection timestamp in seconds since 
    January 1 1970 to the value specified by time. The timezone 
    difference from UTC in minutes is set to timezone. If no timezone is 
    desired, timezone should be CBF_NOTIM EZONE. The parameter reserved 
    is presently unused and should be set to 0.
    The precision of the new timestamp is specified by the value 
    precision in seconds. If precision is 0, the saved timestamp is 
    assumed accurate to 1 second.
    ARGUMENTS
    handle    CBF handle. reserved  Unused. Any value other than 0 is 
    invalid. time      Timestamp in seconds since January 1 1970. 
    timezone  Timezone difference from UTC in minutes or CBF_NOTIMEZONE. 
    precision Timestamp precision in seconds.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    set_dictionary(*args)
    Returns : 
    *args   : CBFHandle dictionary
     
    C prototype: int cbf_set_dictionary (cbf_handle handle,
                     cbf_handle dictionary_in);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_dictionary sets *dictionary to the handle of a CBF which has 
    been associated with the CBF handle by cbf_set_dictionary. 
    cbf_set_dictionary associates the CBF handle dictionary_in with 
    handle as its dictionary. cbf_require_dictionary sets *dictionary to 
    the handle of a CBF which has been associated with the CBF handle by 
    cbf_set_dictionary or creates a new empty CBF and associates it with 
    handle, returning the new handle in *dictionary.
    ARGUMENTS
    handle          CBF handle. dictionary      Pointer to CBF handle of 
    dictionary. dictionary_in   CBF handle of dcitionary.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    set_diffrn_id(*args)
    Returns : string
    *args   : 
     
    C prototype: int cbf_set_diffrn_id (cbf_handle handle, const char *diffrn_id);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_set_diffrn_id sets the "diffrn.id" entry of the current 
    datablock to the ASCII value diffrn_id.
    This function also changes corresponding "diffrn_id" entries in the 
    "diffrn_source", "diffrn_radiation", "diffrn_detector" and 
    "diffrn_measurement" categories.
    ARGUMENTS
    handle      CBF handle. diffrn_id   ASCII value.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    set_divergence(*args)
    Returns : 
    *args   : Float div_x_source,Float div_y_source,Float div_x_y_source
     
    C prototype: int cbf_set_divergence (cbf_handle handle, double div_x_source,
                     double    div_y_source, double div_x_y_source);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_set_divergence sets the source divergence parameters to the 
    values specified by div_x_source, div_y_source and div_x_y_source.
    ARGUMENTS
    handle           CBF handle. div_x_source     New value of 
    div_x_source. div_y_source     New value of div_y_source. 
    div_x_y_source   New value of div_x_y_source.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    set_doublevalue(*args)
    Returns : 
    *args   : String format,Float number
     
    C prototype: int cbf_set_doublevalue (cbf_handle handle, const char *format,
                     double    number);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_set_doublevalue sets the item at the current column and row to 
    the floating-point value number written as an ASCII string with the 
    format specified by format as appropriate for the printf function.
    ARGUMENTS
    handle   CBF handle. format   Format for the number. number   
    Floating-point value.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    set_gain(*args)
    Returns : 
    *args   : Float gain,Float gain_esd
     
    C prototype: int cbf_set_gain (cbf_handle handle, unsigned int element_number,
                        double gain, double gain_esd);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_set_gain sets the gain of element number element_number to the 
    values specified by gain and gain_esd.
    ARGUMENTS
    handle   CBF handle. element_number   The number of the detector 
    element counting from 0 by order of appearance in the 
    "diffrn_data_frame" category. gain   New gain value. gain_esd   New 
    gain_esd value.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    set_image(*args)
    set_image(self, void ?)
    set_integerarray(*args)
    Returns : 
    *args   : int compression,int binary_id,(binary) String data,int elsize,
              int elsigned,int elements
     
    C prototype: int cbf_set_integerarray (cbf_handle handle,
                     unsigned int compression,    int binary_id, void *array,
                     size_t elsize, int elsigned, size_t    elements);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_set_integerarray sets the binary value of the item at the current 
    column and row to an integer array. The array consists of elements 
    elements of elsize bytes each, starting at array. The elements are 
    signed if elsigned is non-0 and unsigned otherwise. binary_id is the 
    binary section identifier. cbf_set_realarray sets the binary value of 
    the item at the current column and row to an integer array. The array 
    consists of elements elements of elsize bytes each, starting at 
    array. binary_id is the binary section identifier.
    The cbf_set_integerarray_wdims and cbf_set_realarray_wdims allow the 
    data header values of byteorder, dim1, dim2, dim3 and padding to be 
    set to the data byte order, the fastest, second fastest and third 
    fastest array dimensions and the size in byte of the post data 
    padding to be used.
    The array will be compressed using the compression scheme specifed by 
    compression. Currently, the available schemes are:
    CBF_CANONICAL   Canonical-code compression (section 3.3.1) CBF_PACKED 
      CCP4-style packing (section 3.3.2) CBF_PACKED_V2   CCP4-style 
    packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET   Simple 
    "byte_offset" compression. CBF_NONE   No compression. NOTE: This 
    scheme is by far the slowest of the four and uses much more disk 
    space. It is intended for routine use with small arrays only. With 
    large arrays (like images) it should be used only for debugging.
    The values compressed are limited to 64 bits. If any element in the 
    array is larger than 64 bits, the value compressed is the nearest 
    64-bit value.
    set_integerarray_wdims(*args)
    set_integerarray_wdims(self, void ?)
    set_integervalue(*args)
    Returns : int number
    *args   : 
     
    C prototype: int cbf_set_integervalue (cbf_handle handle, int number);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_set_integervalue sets the item at the current column and row to 
    the integer value number written as a decimal ASCII string.
    ARGUMENTS
    handle   CBF handle. number   Integer value.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    set_integration_time(*args)
    Returns : 
    *args   : Float time
     
    C prototype: int cbf_set_integration_time (cbf_handle handle,
                     unsigned int    reserved, double time);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_set_integration_time sets the integration time in seconds to the 
    value specified by time. The parameter reserved is presently unused 
    and should be set to 0.
    ARGUMENTS
    handle             CBF handle. reserved           Unused. Any value 
    other than 0 is invalid. time Integration   time in seconds.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    set_orientation_matrix(*args)
    Returns : 
    *args   : Float matrix_0,Float matrix_1,Float matrix_2,Float matrix_3,
              Float matrix_4,Float matrix_5,Float matrix_6,Float matrix_7,
              Float matrix_8
     
    C prototype: int cbf_set_orientation_matrix (cbf_handle handle,
                     double    ub_matrix[9]);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_orientation_matrix sets ub_matrix to point to the array of 
    orientation matrix entries in the "diffrn" category in the order of 
    columns:
    "UB[1][1]" "UB[1][2]" "UB[1][3]" "UB[2][1]" "UB[2][2]" 
    "UB[2][3]" "UB[3][1]" "UB[3][2]" "UB[3][3]"
    cbf_set_orientation_matrix sets the values in the "diffrn" category 
    to the values pointed to by ub_matrix.
    ARGUMENTS
    handle   CBF handle. ubmatric   Source or destination array of 9 
    doubles giving the orientation matrix parameters.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    set_overload(*args)
    Returns : 
    *args   : Integer element_number,Float overload
     
    C prototype: int cbf_set_overload (cbf_handle handle,
                     unsigned int element_number,    double overload);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_set_overload sets the overload value of element number 
    element_number to overload.
    ARGUMENTS
    handle   CBF handle. element_number   The number of the detector 
    element counting from 0 by order of appearance in the 
    "diffrn_data_frame" category. overload   New overload value.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    set_pixel_size(*args)
    Returns : 
    *args   : Int element_number,Int axis_number,Float pixel size
     
    C prototype: int cbf_set_pixel_size (cbf_handle handle,
                     unsigned int    element_number, unsigned int axis_number,
                     double psize);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_set_pixel_size sets the item in the &quote;size&quote; column of 
    the "array_structure_list" category at the row which matches axis 
    axis_number of the detector element element_number converting the 
    double pixel size psize from meters to millimeters in storing it in 
    the "size" column for the axis axis_number of the detector element 
    element_number. The axis_number is numbered from 1, starting with the 
    fastest axis.
    If the "array_structure_list" category does not already exist, it 
    is created.
    If the appropriate row in the "array_structure_list" catgeory does 
    not already exist, it is created.
    If the pixel size is not given explcitly in the "array_element_size 
    category", the function returns CBF_NOTFOUND.
    ARGUMENTS
    handle   CBF handle. element_number   The number of the detector 
    element counting from 0 by order of appearance in the 
    "diffrn_data_frame" category. axis_number   The number of the axis, 
    fastest first, starting from 1.
    set_polarization(*args)
    Returns : 
    *args   : Float polarizn_source_ratio,Float polarizn_source_norm
     
    C prototype: int cbf_set_polarization (cbf_handle handle,
                     double    polarizn_source_ratio, double polarizn_source_norm);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_set_polarization sets the source polarization to the values 
    specified by polarizn_source_ratio and polarizn_source_norm.
    ARGUMENTS
    handle                  CBF handle. polarizn_source_ratio   New value 
    of polarizn_source_ratio. polarizn_source_norm    New value of 
    polarizn_source_norm.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    set_real_3d_image(*args)
    set_real_3d_image(self, void ?)
    set_real_image(*args)
    set_real_image(self, void ?)
    set_realarray(*args)
    set_realarray(self, void ?)
    set_realarray_wdims(*args)
    set_realarray_wdims(self, void ?)
    set_reciprocal_cell(*args)
    set_reciprocal_cell(self, void ?)
    set_tag_category(*args)
    Returns : 
    *args   : String tagname,String categoryname_in
     
    C prototype: int cbf_set_tag_category (cbf_handle handle, const char* tagname,
                        const char* categoryname_in);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_find_tag_category sets categoryname to the category associated 
    with tagname in the dictionary associated with handle. 
    cbf_set_tag_category upddates the dictionary associated with handle 
    to indicated that tagname is in category categoryname_in.
    ARGUMENTS
    handle            CBF handle. tagname           tag name. 
    categoryname      pointer to a returned category name. 
    categoryname_in   input category name.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    set_tag_root(*args)
    Returns : 
    *args   : String tagname,String tagroot_in
     
    C prototype: int cbf_set_tag_root (cbf_handle handle, const char* tagname,
                     const    char*tagroot_in);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_find_tag_root sets *tagroot to the root tag of which tagname is 
    an alias. cbf_set_tag_root sets tagname as an alias of tagroot_in in 
    the dictionary associated with handle, creating the dictionary if 
    necessary. cbf_require_tag_root sets *tagroot to the root tag of 
    which tagname is an alias, if there is one, or to the value of 
    tagname, if tagname is not an alias.
    A returned tagroot string must not be modified in any way.
    ARGUMENTS
    handle       CBF handle. tagname      tag name which may be an alias. 
    tagroot      pointer to a returned tag root name. tagroot_in   input 
    tag root name.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    set_timestamp(*args)
    Returns : 
    *args   : Float time,Integer timezone,Float precision
     
    C prototype: int cbf_set_timestamp (cbf_handle handle, unsigned int reserved,
                        double time, int timezone, double precision);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_set_timestamp sets the collection timestamp in seconds since 
    January 1 1970 to the value specified by time. The timezone 
    difference from UTC in minutes is set to timezone. If no timezone is 
    desired, timezone should be CBF_NOTIM EZONE. The parameter reserved 
    is presently unused and should be set to 0.
    The precision of the new timestamp is specified by the value 
    precision in seconds. If precision is 0, the saved timestamp is 
    assumed accurate to 1 second.
    ARGUMENTS
    handle   CBF handle. reserved   Unused. Any value other than 0 is 
    invalid. time   Timestamp in seconds since January 1 1970. timezone   
    Timezone difference from UTC in minutes or CBF_NOTIMEZONE. precision  
     Timestamp precision in seconds.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    set_typeofvalue(*args)
    Returns : string
    *args   : 
     
    C prototype: int cbf_set_typeofvalue (cbf_handle handle,
                     const char *typeofvalue);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_set_typeofvalue sets the type of the item at the current column 
    and row to the type specified by the ASCII character string given by 
    typeofvalue. The strings that may be used are "null" for a null 
    value indicated by a "." or a "?", "word" for an unquoted 
    string, "dblq" for a double-quoted string, "sglq" for a 
    single-quoted string, and "text" for a semicolon-quoted text field. 
    Not all types may be used for all values. No changes may be made to 
    the type of binary values. You may not set the type of a string that 
    contains a single quote followed by a blank or a tab or which 
    contains multiple lines to "sglq". You may not set the type of a 
    string that contains a double quote followed by a blank or a tab or 
    which contains multiple lines to "dblq".
    ARGUMENTS
    handle        CBF handle. typeofvalue   ASCII string for desired type 
    of value.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    set_unit_cell(*args)
    set_unit_cell(self, void ?)
    set_value(*args)
    Returns : string
    *args   : 
     
    C prototype: int cbf_set_value (cbf_handle handle, const char *value);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_set_value sets the item at the current column and row to the 
    ASCII value value.
    ARGUMENTS
    handle         CBF handle. value          ASCII value. defaultvalue   
    default ASCII value.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    set_wavelength(*args)
    Returns : double wavelength
    *args   : 
     
    C prototype: int cbf_set_wavelength (cbf_handle handle, double wavelength);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_set_wavelength sets the current wavelength in Angstrom to 
    wavelength.
    ARGUMENTS
    handle       CBF handle. wavelength   Wavelength in Angstrom.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    write_file(*args)
    Returns : 
    *args   : String filename,Integer ciforcbf,Integer Headers,Integer encoding
     
    C prototype: int cbf_write_file (cbf_handle handle, FILE *file, int readable,
                     int    ciforcbf, int headers, int encoding);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_write_file writes the CBF object specified by handle into the 
    file file, following CIF 1.0 conventions of 80 character lines. 
    cbf_write_widefile writes the CBF object specified by handle into the 
    file file, following CIF 1.1 conventions of 2048 character lines. A 
    warning is issued to stderr for ascii lines over the limit, and an 
    attempt is made to fold lines to fit. No test is performed on binary 
    sections.
    If a dictionary has been provided, aliases will be applied on output.
    Unlike cbf_read_file, the file does not have to be random-access.
    If the file is random-access and readable, readable can be set to 
    non-0 to indicate to CBFlib that the file can be used as a buffer to 
    conserve disk space. If the file is not random-access or not 
    readable, readable must be 0.
    If readable is non-0, CBFlib will close the file when it is no longer 
    required, otherwise this is the responsibility of the program.
    ciforcbf selects the format in which the binary sections are written:
    CIF   Write an imgCIF file. CBF   Write a CBF file (default).
    headers selects the type of header used in CBF binary sections and 
    selects whether message digests are generated. The value of headers 
    can be a logical OR of any of:
    MIME_HEADERS     Use MIME-type headers (default). MIME_NOHEADERS   
    Use a simple ASCII headers. MSG_DIGEST       Generate message digests 
    for binary data validation. MSG_NODIGEST     Do not generate message 
    digests (default).
    encoding selects the type of encoding used for binary sections and 
    the type of line-termination in imgCIF files. The value can be a 
    logical OR of any of:
    ENC_BASE64   Use BASE64 encoding (default). ENC_QP   Use 
    QUOTED-PRINTABLE encoding. ENC_BASE8   Use BASE8 (octal) encoding. 
    ENC_BASE10   Use BASE10 (decimal) encoding. ENC_BASE16   Use BASE16 
    (hexadecimal) encoding. ENC_FORWARD   For BASE8, BASE10 or BASE16 
    encoding, map bytes to words forward (1234) (default on little-endian 
    machines). ENC_BACKWARD   Map bytes to words backward (4321) (default 
    on big-endian machines). ENC_CRTERM   Terminate lines with CR. 
    ENC_LFTERM   Terminate lines with LF (default).
    ARGUMENTS
    handle   CBF handle. file   Pointer to a file descriptor. readable   
    If non-0: this file is random-access and readable and can be used as 
    a buffer. ciforcbf   Selects the format in which the binary sections 
    are written (CIF/CBF). headers   Selects the type of header in CBF 
    binary sections and message digest generation. encoding   Selects the 
    type of encoding used for binary sections and the type of 
    line-termination in imgCIF files.
    RETURN VALUE
    Returns an error code on failure or 0 for success.
    SEE ALSO
    write_widefile(*args)
    write_widefile(self, void ?)

    Properties defined here:
    node
    get = cbf_handle_struct_node_get(...)
    set = cbf_handle_struct_node_set(...)
    row
    get = cbf_handle_struct_row_get(...)
    set = cbf_handle_struct_row_set(...)
    search_row
    get = cbf_handle_struct_search_row_get(...)
    set = cbf_handle_struct_search_row_set(...)

    Data and other attributes defined here:
    __dict__ = <dictproxy object>
    dictionary for instance variables (if defined)
    __swig_destroy__ = <built-in function delete_cbf_handle_struct>
    __swig_getmethods__ = {'node': <built-in function cbf_handle_struct_node_get>, 'row': <built-in function cbf_handle_struct_row_get>, 'search_row': <built-in function cbf_handle_struct_search_row_get>}
    __swig_setmethods__ = {'node': <built-in function cbf_handle_struct_node_set>, 'row': <built-in function cbf_handle_struct_row_set>, 'search_row': <built-in function cbf_handle_struct_search_row_set>}
    __weakref__ = <attribute '__weakref__' of 'cbf_handle_struct' objects>
    list of weak references to the object (if defined)

     
    class cbf_positioner_struct(__builtin__.object)
         Methods defined here:
    __del__ lambda self
    __getattr__ lambda self, name
    __init__(self, *args)
    __init__(self) -> cbf_positioner_struct
    __repr__ = _swig_repr(self)
    __setattr__ lambda self, name, value
    get_reciprocal(*args)
    Returns : double reciprocal1,double reciprocal2,double reciprocal3
    *args   : double ratio,double wavelength,double real1,double real2,double real3
     
    C prototype: int cbf_get_reciprocal (cbf_goniometer goniometer,
                     unsigned int    reserved, double ratio, double wavelength,
                     double real1, double real2,    double real3,
                     double *reciprocal1, double *reciprocal2,
                     double    *reciprocal3);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_reciprocal sets *reciprocal1, * reciprocal2, and * 
    reciprocal3 to the 3 components of the of the reciprocal-space vector 
    corresponding to the real-space vector (real1, real2, real3). The 
    reciprocal-space vector is oriented to correspond to the goniometer 
    setting with all axes at 0. The value wavelength is the wavlength in 
    Angstrom and the value ratio specifies the current goniometer setting 
    and varies from 0.0 at the beginning of the exposur e to 1.0 at the 
    end, irrespective of the actual rotation range.
    Any of the destination pointers may be NULL.
    The parameter reserved is presently unused and should be set to 0.
    ARGUMENTS
    goniometer   Goniometer handle. reserved   Unused. Any value other 
    than 0 is invalid. ratio   Goniometer setting. 0 = beginning of 
    exposure, 1 = end. wavelength   Wavelength in Angstrom. real1   x 
    component of the real-space vector. real2   y component of the 
    real-space vector. real3   z component of the real-space vector. 
    reciprocal1   Pointer to the destination x component of the 
    reciprocal-space vector. reciprocal2   Pointer to the destination y 
    component of the reciprocal-space vector. reciprocal3   Pointer to 
    the destination z component of the reciprocal-space vector.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    get_rotation_axis(*args)
    Returns : double vector1,double vector2,double vector3
    *args   : 
     
    C prototype: int cbf_get_rotation_axis (cbf_goniometer goniometer,
                     unsigned int    reserved, double *vector1, double *vector2,
                     double vector3);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_rotation_axis sets *vector1, *vector2, and *vector3 to the 3 
    components of the goniometer rotation axis used for the exposure.
    Any of the destination pointers may be NULL.
    The parameter reserved is presently unused and should be set to 0.
    ARGUMENTS
    goniometer   Goniometer handle. reserved   Unused. Any value other 
    than 0 is invalid. vector1   Pointer to the destination x component 
    of the rotation axis. vector2   Pointer to the destination y 
    component of the rotation axis. vector3   Pointer to the destination 
    z component of the rotation axis.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    get_rotation_range(*args)
    Returns : Float start,Float increment
    *args   : 
     
    C prototype: int cbf_get_rotation_range (cbf_goniometer goniometer,
                     unsigned int    reserved, double *start, double *increment);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_rotation_range sets *start and *increment to the 
    corresponding values of the goniometer rotation axis used for the 
    exposure.
    Either of the destination pointers may be NULL.
    The parameter reserved is presently unused and should be set to 0.
    ARGUMENTS
    goniometer   Goniometer handle. reserved     Unused. Any value other 
    than 0 is invalid. start        Pointer to the destination start 
    value. increment    Pointer to the destination increment value.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    rotate_vector(*args)
    Returns : double final1,double final2,double final3
    *args   : double ratio,double initial1,double initial2,double initial3
     
    C prototype: int cbf_rotate_vector (cbf_goniometer goniometer,
                     unsigned int    reserved, double ratio, double initial1,
                     double initial2, double    initial3, double *final1,
                     double *final2, double *final3);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_rotate_vector sets *final1, *final2, and *final3 to the 3 
    components of the of the vector (initial1, initial2, initial3) after 
    reorientation by applying the goniometer rotations. The value ratio 
    specif ies the goniometer setting and varies from 0.0 at the 
    beginning of the exposure to 1.0 at the end, irrespective of the 
    actual rotation range.
    Any of the destination pointers may be NULL.
    The parameter reserved is presently unused and should be set to 0.
    ARGUMENTS
    goniometer   Goniometer handle. reserved   Unused. Any value other 
    than 0 is invalid. ratio   Goniometer setting. 0 = beginning of 
    exposure, 1 = end. initial1   x component of the initial vector. 
    initial2   y component of the initial vector. initial3   z component 
    of the initial vector. vector1   Pointer to the destination x 
    component of the final vector. vector2   Pointer to the destination y 
    component of the final vector. vector3   Pointer to the destination z 
    component of the final vector.
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________

    Properties defined here:
    axes
    get = cbf_positioner_struct_axes_get(...)
    set = cbf_positioner_struct_axes_set(...)
    axes_are_connected
    get = cbf_positioner_struct_axes_are_connected_get(...)
    set = cbf_positioner_struct_axes_are_connected_set(...)
    axis
    get = cbf_positioner_struct_axis_get(...)
    set = cbf_positioner_struct_axis_set(...)
    matrix
    get = cbf_positioner_struct_matrix_get(...)
    set = cbf_positioner_struct_matrix_set(...)
    matrix_is_valid
    get = cbf_positioner_struct_matrix_is_valid_get(...)
    set = cbf_positioner_struct_matrix_is_valid_set(...)

    Data and other attributes defined here:
    __dict__ = <dictproxy object>
    dictionary for instance variables (if defined)
    __swig_destroy__ = <built-in function delete_cbf_positioner_struct>
    __swig_getmethods__ = {'axes': <built-in function cbf_positioner_struct_axes_get>, 'axes_are_connected': <built-in function cbf_positioner_struct_axes_are_connected_get>, 'axis': <built-in function cbf_positioner_struct_axis_get>, 'matrix': <built-in function cbf_positioner_struct_matrix_get>, 'matrix_is_valid': <built-in function cbf_positioner_struct_matrix_is_valid_get>}
    __swig_setmethods__ = {'axes': <built-in function cbf_positioner_struct_axes_set>, 'axes_are_connected': <built-in function cbf_positioner_struct_axes_are_connected_set>, 'axis': <built-in function cbf_positioner_struct_axis_set>, 'matrix': <built-in function cbf_positioner_struct_matrix_set>, 'matrix_is_valid': <built-in function cbf_positioner_struct_matrix_is_valid_set>}
    __weakref__ = <attribute '__weakref__' of 'cbf_positioner_struct' objects>
    list of weak references to the object (if defined)

     
    Functions
           
    cbf_detector_struct_swigregister(...)
    cbf_handle_struct_swigregister(...)
    cbf_positioner_struct_swigregister(...)
    get_local_integer_byte_order(*args)
    Returns : string
    *args   : 
     
    C prototype: int cbf_get_local_integer_byte_order (char ** byte_order);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_local_integer_byte_order returns the byte order of integers 
    on the machine on which the API is being run in the form of a 
    character string returned as the value pointed to by byte_order. 
    cbf_get_local_real_byte_order returns the byte order of reals on the 
    machine on which the API is being run in the form of a character 
    string returned as the value pointed to by byte_order. 
    cbf_get_local_real_format returns the format of floats on the machine 
    on which the API is being run in the form of a character string 
    returned as the value pointed to by real_format. The strings returned 
    must not be modified in any way.
    The values returned in byte_order may be the strings 
    "little_endian" or "big-endian". The values returned in 
    real_format may be the strings "ieee 754-1985" or "other". 
    Additional values may be returned by future versions of the API.
    ARGUMENTS
    byte_order    pointer to the returned string real_format   pointer to 
    the returned string
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    get_local_real_byte_order(*args)
    Returns : string
    *args   : 
     
    C prototype: int cbf_get_local_real_byte_order (char ** byte_order);
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_local_integer_byte_order returns the byte order of integers 
    on the machine on which the API is being run in the form of a 
    character string returned as the value pointed to by byte_order. 
    cbf_get_local_real_byte_order returns the byte order of reals on the 
    machine on which the API is being run in the form of a character 
    string returned as the value pointed to by byte_order. 
    cbf_get_local_real_format returns the format of floats on the machine 
    on which the API is being run in the form of a character string 
    returned as the value pointed to by real_format. The strings returned 
    must not be modified in any way.
    The values returned in byte_order may be the strings 
    "little_endian" or "big-endian". The values returned in 
    real_format may be the strings "ieee 754-1985" or "other". 
    Additional values may be returned by future versions of the API.
    ARGUMENTS
    byte_order    pointer to the returned string real_format   pointer to 
    the returned string
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________
    get_local_real_format(*args)
    Returns : string
    *args   : 
     
    C prototype: int cbf_get_local_real_format (char ** real_format );
     
    CBFLib documentation:
    DESCRIPTION
    cbf_get_local_integer_byte_order returns the byte order of integers 
    on the machine on which the API is being run in the form of a 
    character string returned as the value pointed to by byte_order. 
    cbf_get_local_real_byte_order returns the byte order of reals on the 
    machine on which the API is being run in the form of a character 
    string returned as the value pointed to by byte_order. 
    cbf_get_local_real_format returns the format of floats on the machine 
    on which the API is being run in the form of a character string 
    returned as the value pointed to by real_format. The strings returned 
    must not be modified in any way.
    The values returned in byte_order may be the strings 
    "little_endian" or "big-endian". The values returned in 
    real_format may be the strings "ieee 754-1985" or "other". 
    Additional values may be returned by future versions of the API.
    ARGUMENTS
    byte_order    pointer to the returned string real_format   pointer to 
    the returned string
    RETURN VALUE
    Returns an error code on failure or 0 for success. 
    _________________________________________________________________

     
    Data
            CBF = 0
    CBF_BYTE_OFFSET = 112
    CBF_CANONICAL = 80
    CBF_CATEGORY = 5
    CBF_COLUMN = 6
    CBF_DATABLOCK = 3
    CBF_FLOAT = 32
    CBF_INTEGER = 16
    CBF_LINK = 1
    CBF_NONE = 64
    CBF_PACKED = 96
    CBF_PREDICTOR = 128
    CBF_ROOT = 2
    CBF_SAVEFRAME = 4
    CBF_UNDEFINED = 65536
    CBF_UNDEFNODE = 0
    CIF = 1
    ENC_BACKWARD = 128
    ENC_BASE10 = 8
    ENC_BASE16 = 16
    ENC_BASE64 = 2
    ENC_BASE8 = 32
    ENC_CRTERM = 256
    ENC_DEFAULT = 578
    ENC_FORWARD = 64
    ENC_LFTERM = 512
    ENC_NONE = 1
    ENC_QP = 4
    HDR_DEFAULT = 6
    MIME_HEADERS = 2
    MIME_NOHEADERS = 1
    MSG_DIGEST = 8
    MSG_DIGESTNOW = 16
    MSG_NODIGEST = 4
    PLAIN_HEADERS = 1
    __author__ = 'Jon Wright <wright@esrf.fr>'
    __credits__ = 'Paul Ellis and Herbert Bernstein for the excellent CBFlib!'
    __date__ = '14 Dec 2005'
    __version__ = 'still_being_written'

     
    Author
            Jon Wright <wright@esrf.fr>

     
    Credits
            Paul Ellis and Herbert Bernstein for the excellent CBFlib!
    ./CBFlib-0.9.2.2/pycbf/CBFlib.txt0000644000076500007650000120212411603702120014521 0ustar yayayaya [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] ---------------------------------------------------------------------- | IUCr Home Page | CIF Home Page | CBF/imgCIF | CBFlib | | NOTICE | GPL | LGPL | imgCIF dictionary | | Click Here to Make a Donation | CBFlib An API for CBF/imgCIF Crystallographic Binary Files with ASCII Support Version 0.8 29 February 2008 by Paul J. Ellis Stanford Synchrotron Radiation Laboratory and Herbert J. Bernstein Bernstein + Sons yaya at bernstein-plus-sons dot com (c) Copyright 2006, 2007 Herbert J. Bernstein ---------------------------------------------------------------------- YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL. ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS OF THE LGPL. ---------------------------------------------------------------------- Before using this software, please read the NOTICE for important disclaimers and the IUCr Policy on the Use of the Crystallographic Information File (CIF) and for other important information. Work on imgCIF and CBFlib supported in part by the U. S. Department of Energy (DOE) under grants ER63601-1021466-0009501 and ER64212-1027708-0011962, by the U. S. National Science Foundation (NSF) under grants DBI-0610407, DBI-0315281 and EF-0312612, the U. S. National Institutes of Health (NIH) under grants 1R15GM078077 from NIGMS and 1R13RR023192 from NCRR and funding from the International Union for Crystallographyn (IUCr). The content is solely the responsibility of the authors and does not necessarily represent the official views of DOE, NSF, NIH, NIGMS, NCRR or IUCr. ---------------------------------------------------------------------- Version History Version Date By Description 0.1 Apr. 1998 PJE This was the first CBFlib release. It supported binary CBF files using binary strings. 0.2 Aug. 1998 HJB This release added ascii imgCIF support using MIME-encoded binary sections, added the option of MIME headers for the binary strings was well. MIME code adapted from mpack 1.5. Added hooks needed for DDL1-style names without categories. 0.3 Sep. 1998 PJE This release cleaned up the changes made for version 0.2, allowing multi-threaded use of the code, and removing dependence on the mpack package. 0.4 Nov. 1998 HJB This release merged much of the message digest code into the general file reading and writing to reduce the number of passes. More consistency checking between the MIME header and the binary header was introduced. The size in the MIME header was adjusted to agree with the version 0.2 documentation. 0.5 Dec. 1998 PJE This release greatly increased the speed of processing by allowing for deferred digest evaluation. 0.6 Jan. 1999 HJB This release removed the redundant information (binary id, size, compression id) from a binary header when there is a MIME header, removed the unused repeat argument, and made the memory allocation for buffering and tables with many rows sensitive to the current memory allocation already used. 0.6.1 Feb. 2001 HP (per This release fixed a memory leak due HJB) to misallocation by size of cbf_handle instead of cbf_handle_struct 0.7 Mar. 2001 PJE This release added high-level instructions based on the imgCIF dictionary version 1.1. 0.7.1 Mar. 2001 PJE The high-level functions were revised to permit future expansion to files with multiple images. 0.7.2 Apr. 2001 HJB This release adjusted cbf_cimple.c to conform to cif_img.dic version 1.1.3 0.7.2.1 May 2001 PJE This release corrected an if nesting error in the prior mod to cbf_cimple.c. 0.7.3 Oct 2002 PJE This release modified cbf_simple.c to reorder image data on read so that the indices are always increasing in memory (this behavior was undefined previously). 0.7.4 Jan 2004 HJB This release fixes a parse error for quoted strings, adds code to get and set character string types, and removes compiler warnings 0.7.5 Apr 2006 HJB This release cleans up some compiler warnings, corrects a parse error on quoted strings with a leading blank as adds the new routines for support of aliases, dictionaries and real arrays, higher level routines to get and set pixel sizes, do cell computations, and to set beam centers, improves support for conversion of images, picking up more data from headers. 0.7.6 Jul 2006 HJB This release reorganizes the kit into two pieces: CBFlib_0.7.6_Data_Files and CBFlib_0.7.6. An optional local copy of getopt is added. The 1.4 draft dictionary has been added. cif2cbf updated to support vcif2 validation. convert_image and cif2cbf updated to report text of error messages. convert_image updated to support tag and category aliases, default to adxv images. convert_image and img updated to support row-major images. Support added for binning. API Support added for validation, wide files and line folding. Logic changed for beam center reporting. Added new routines: cbf_validate, cbf_get_bin_sizes, cbf_set_bin_sizes, cbf_find_last_typed_child, cbf_compose_itemname, cbf_set_cbf_logfile, cbf_make_widefile, cbf_read_anyfile, cbf_read_widefile, cbf_write_local_file, cbf_write_widefile, cbf_column_number, cbf_blockitem_number, cbf_log, cbf_check_category_tags, cbf_set_beam_center 0.7.7 February 2007 HJB This release reflects changes for base 32K support developed by G. Darakev, and changes for support of reals, 3d arrays, byte_offset compression and J. P. Abrahams packed compression made in consultation with (in alphabetic order) E. Eikenberry, A. Hammerley, W. Kabsch, M. Kobas, J. Wright and others at PSI and ESRF in January 2007, as well accumulated changes fixing problems in release 0.7.6. 0.7.7.1 February 2007 HJB This release is a patch to 0.7.7 to change the treatment of the byteorder parameter from strcpy semantics to return of a pointer to a string constant. Our thanks to E. Eikenberry for pointing out the problem. 0.7.7.2 February 2007 HJB This release is a patch to 0.7.7.1 to add testing for JPA packed compression and to respect signs declared in the MIME header. 0.7.7.3 April 2007 HJB This release is a patch to 0.7.7.3 to add f90 support for reading of CBF byte-offset and packed compression, to fix problems with gcc 4.4.1 and to correct errors in multidimensional packed compression. 0.7.7.4 May 2007 HJB Corrects in handling SLS detector mincbfs and reorder dimensions versus arrays for some f90 compilers as per H. Powell. 0.7.7.5 May 2007 HJB Fix to cbf_get_image for bug reported by F. Remacle, fixes for windows builds as per J. Wright and F. Remacle. 0.7.7.6 Jun 2007 HJB Fix to CBF byte-offset compression writes, fix to Makefiles and m4 for f90 test programs to allow adjustable record length. 0.7.8 Jul 2007 HJB Release for full support of SLS data files with updated convert_minicbf, and support for gfortran from gcc 4.2. 0.7.8.1 Jul 2007 HJB Update to 0.7.8 release to fix memory leaks reported by N. Sauter and to update validation checks for recent changes. 0.7.8.2 Dec 2007 CN, HJB Update to 0.7.8.1 to add ADSC jiffie by Chris Nielsen, and to add ..._fs and ..._sf macros. 0.7.9 Dec 2007 CN, HJB Identical to 0.7.8.2 except for a cleanup of deprecated examples, e.g. diffrn_frame_data 0.7.9.1 Jan 2008 CN, HJB Update to 0.7.8.2 to add inverse ADSC jiffie by Chris Nielsen, to clean up problems in handling maps for RasMol. ---------------------------------------------------------------------- Known Problems This version does not have support for predictor compression. Code is needed to support array sub-sections. Foreword In order to work with CBFlib, you need: * the source code, in the form of a "gzipped" tar, CBFlib_0.8.tar.gz; and * the test data: * CBFlib_0.7.9_Data_Files_Input.tar.gz (13 MB) a "gzipped" tar of the input data files needed to test the API; * CBFlib_0.7.9_Data_Files_Output.tar.gz (34 MB) a "gzipped" tar of the output data files needed to test the API, or, if space is at a premium; * CBFlib_0.7.9_Data_Files_Output_Sigs_Only.tar.gz (1KB) is a "gzipped" tar of only the MD5 signatures of the output data files needed to test the API. If your system has the program wget, you only need the source code. The download of the other tar balls will be handled automatically. Be careful about space. A full build and test can use 350 MB or more. If space is tight, be sure to read the instructions below on using only the signatures of the test files. Uncompress and unpack : * gunzip < CBFlib_0.7.9.tar.gz | tar xvf - To run the test programs, you will also need Paul Ellis's sample MAR345 image, example.mar2300, Chris Nielsen's sample ADSC Quantum 315 image, mb_LP_1_001.img, and Eric Eikenberry's SLS sample Pilatus 6m image, insulin_pilatus6m, as sample data. In addition there are is a PDB mmCIF file, 9ins.cif, and 3 special test files testflatin.cbf, testflatpackedin.cbf and testrealin.cbf. All these files will be dowloaded and extracted by the Makefile from CBFlib_0.7.9_Data_Files_Input. Do not download copies into the top level directory. Thare are various sample Makefiles for common configurations. The Makefile_LINUX and Makefile_OSX samples are for systems with gfortran from prior to the release of gcc 4.2. For the most recent gfortran, use Makefile_LINUX_gcc42 ot Makfile_OSX_gcc42. All the Makefiles come from m4/Makefile.m4. The Makefiles use GNU make constructs, such as ifeq and ifneq. If you need to use a diferent version of make, you will need to edit out the conditionals If necessary, adjust the definition of CC and C++ and other defintions in Makefile to point to your compilers. Set the definition of CFLAGS to an appropriate value for your C and C++ compilers, the definition of F90C to point to your Fortan-90/95 compiler, and the definitions of F90FLAGS and F90LDFLAGS to approriate values for your Fortan-90/95 compilers, and then make all make tests or, if space is at a premium: make all make tests_sigs_only If you do not have a fortran compiler, you will need edit the Makefile or to define the variable NOFORTRAN, either in the Makefile or in the environment We have included examples of CBF/imgCIF files produced by CBFlib in the test data CBFlib_0.7.9_Data_Files_Output.tar.gz, the current best draft of the CBF Extensions Dictionary, and of Andy Hammersley's CBF definition, updated to become a DRAFT CBF/ImgCIF DEFINITION. ---------------------------------------------------------------------- Contents * 1. Introduction * 2. Function descriptions * 2.1 General description * 2.1.1 CBF handles * 2.1.2 CBF goniometer handles * 2.1.3 CBF detector handles * 2.1.4 Return values * 2.2 Reading and writing files containing binary sections * 2.2.1 Reading binary sections * 2.2.2 Writing binary sections * 2.2.3 Summary of reading and writing files containing binary sections * 2.2.4 Ordering of array indices * 2.3 Low-level function prototypes * 2.3.1 cbf_make_handle * 2.3.2 cbf_free_handle * 2.3.3 cbf_read_file, cbf_read_widefile * 2.3.4 cbf_write_file, cbf_write_widefile * 2.3.5 cbf_new_datablock, cbf_new_saveframe * 2.3.6 cbf_force_new_datablock, cbf_force_new_saveframe * 2.3.7 cbf_new_category * 2.3.8 cbf_force_new_category * 2.3.9 cbf_new_column * 2.3.10 cbf_new_row * 2.3.11 cbf_insert_row * 2.3.12 cbf_delete_row * 2.3.13 cbf_set_datablockname, cbf_set_saveframename * 2.3.14 cbf_reset_datablocks * 2.3.15 cbf_reset_datablock, cbf_reset_saveframe * 2.3.16 cbf_reset_category * 2.3.17 cbf_remove_datablock, cbf_remove_saveframe * 2.3.18 cbf_remove_category * 2.3.19 cbf_remove_column * 2.3.20 cbf_remove_row * 2.3.21 cbf_rewind_datablock * 2.3.22 cbf_rewind_category, cbf_rewind_saveframe, cbf_rewind_blockitem * 2.3.23 cbf_rewind_column * 2.3.24 cbf_rewind_row * 2.3.25 cbf_next_datablock * 2.3.26 cbf_next_category, cbf_next_saveframe, cbf_next_blockitem * 2.3.27 cbf_next_column * 2.3.28 cbf_next_row * 2.3.29 cbf_find_datablock * 2.3.30 cbf_find_category, cbf_find_saveframe, cbf_find_blockitem * 2.3.31 cbf_find_column * 2.3.32 cbf_find_row * 2.3.33 cbf_find_nextrow * 2.3.34 cbf_count_datablocks * 2.3.35 cbf_count_categories, cbf_count_saveframes, cbf_count_blockitems * 2.3.36 cbf_count_columns * 2.3.37 cbf_count_rows * 2.3.38 cbf_select_datablock * 2.3.39 cbf_select_category, cbf_select_saveframe, cbf_select_blockitem * 2.3.40 cbf_select_column * 2.3.41 cbf_select_row * 2.3.42 cbf_datablock_name * 2.3.43 cbf_category_name * 2.3.44 cbf_column_name * 2.3.45 cbf_row_number * 2.3.46 cbf_get_value, cbf_require_value * 2.3.47 cbf_set_value * 2.3.48 cbf_get_typeofvalue * 2.3.49 cbf_set_typeofvalue * 2.3.50 cbf_get_integervalue, cbf_require_integervalue * 2.3.51 cbf_set_integervalue * 2.3.52 cbf_get_doublevalue, cbf_require_doublevalue * 2.3.53 cbf_set_doublevalue * 2.3.54 cbf_get_integerarrayparameters, cbf_get_integerarrayparameters_wdims, cbf_get_integerarrayparameters_wdims_fs, cbf_get_integerarrayparameters_wdims_sf cbf_get_realarrayparameters, cbf_get_realarrayparameters_wdims, cbf_get_realarrayparameters_wdims_fs, cbf_get_realarrayparameters_wdims_sf * 2.3.55 cbf_get_integerarray, cbf_get_realarray * 2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, cbf_set_integerarray_wdims_sf, cbf_set_realarray, cbf_set_realarray_wdims, cbf_set_realarray_wdims_fs, cbf_set_realarray_wdims_sf * 2.3.57 cbf_failnez * 2.3.58 cbf_onfailnez * 2.3.59 cbf_require_datablock * 2.3.60 cbf_require_category * 2.3.61 cbf_require_column * 2.3.62 cbf_require_column_value * 2.3.63 cbf_require_column_integervalue * 2.3.64 cbf_require_column_doublevalue * 2.3.65 cbf_get_local_integer_byte_order, cbf_get_local_real_byte_order, cbf_get_local_real_format * 2.3.66 cbf_get_dictionary, cbf_set_dictionary, cbf_require_dictionary * 2.3.67 cbf_convert_dictionary * 2.3.68 cbf_find_tag, cbf_find_local_tag * 2.3.69 cbf_find_category_root, cbf_set_category_root, cbf_require_category_root * 2.3.70 cbf_find_tag_root, cbf_set_tag_root, cbf_require_tag_root * 2.3.71 cbf_find_tag_category, cbf_set_tag_category * 2.4 High-level function prototypes (new for version 0.7) * 2.4.1 cbf_read_template * 2.4.2 cbf_get_diffrn_id, cbf_require_diffrn_id * 2.4.3 cbf_set_diffrn_id * 2.4.4 cbf_get_crystal_id * 2.4.5 cbf_set_crystal_id * 2.4.6 cbf_get_wavelength * 2.4.7 cbf_set_wavelength * 2.4.8 cbf_get_polarization * 2.4.9 cbf_set_polarization * 2.4.10 cbf_get_divergence * 2.4.11 cbf_set_divergence * 2.4.12 cbf_count_elements * 2.4.13 cbf_get_element_id * 2.4.14 cbf_get_gain * 2.4.15 cbf_set_gain * 2.4.16 cbf_get_overload * 2.4.17 cbf_set_overload * 2.4.18 cbf_get_integration_time * 2.4.19 cbf_set_integration_time * 2.4.20 cbf_get_time * 2.4.21 cbf_set_time * 2.4.22 cbf_get_date * 2.4.23 cbf_set_date * 2.4.24 cbf_set_current_time * 2.4.25 cbf_get_image_size, cbf_get_image_size_fs, cbf_get_image_size_fs, cbf_get_3d_image_size, cbf_get_3d_image_size_fs, cbf_get_3d_image_size_sf * 2.4.26 cbf_get_image, cbf_get_image_fs, cbf_get_image_sf, cbf_get_real_image, cbf_get_real_image_fs, cbf_get_real_image_sf, cbf_get_3d_image, cbf_get_3d_image_fs, cbf_get_3d_image_sf, cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf * 2.4.27 cbf_set_image, cbf_set_image_fs, cbf_set_image_sf, cbf_set_real_image, cbf_set_real_image_fs, cbf_set_real_image_sf, cbf_set_3d_image, cbf_set_3d_image, cbf_set_3d_image, cbf_set_real_3d_image, cbf_set_real_3d_image_fs, cbf_set_real_3d_image_sf * 2.4.28 cbf_get_axis_setting * 2.4.29 cbf_set_axis_setting * 2.4.30 cbf_construct_goniometer * 2.4.31 cbf_free_goniometer * 2.4.32 cbf_get_rotation_axis * 2.4.33 cbf_get_rotation_range * 2.4.34 cbf_rotate_vector * 2.4.35 cbf_get_reciprocal * 2.4.36 cbf_construct_detector, cbf_construct_reference_detector, cbf_require_reference_detector * 2.4.37 cbf_free_detector * 2.4.38 cbf_get_beam_center, cbf_get_beam_center_fs, cbf_get_beam_center_sf, cbf_set_beam_center, cbf_set_beam_center_fs, cbf_set_beam_center_sf, cbf_set_reference_beam_center, cbf_set_reference_beam_center_fs, cbf_set_reference_beam_center_sf * 2.4.39 cbf_get_detector_distance * 2.4.40 cbf_get_detector_normal * 2.4.41 cbf_get_detector_axis_slow, cbf_get_detector_axis_fast, cbf_get_detector_axes, cbf_get_detector_axes_fs, cbf_get_detector_axes_sf * 2.4.42 cbf_get_pixel_coordinates, cbf_get_pixel_coordinates_fs, cbf_get_pixel_coordinates_sf * 2.4.43 cbf_get_pixel_normal, cbf_get_pixel_normal_fs, cbf_get_pixel_normal_sf * 2.4.44 cbf_get_pixel_area, cbf_get_pixel_area_fs, cbf_get_pixel_area_sf * 2.4.45 cbf_get_pixel_size, cbf_get_pixel_size_fs, cbf_get_pixel_size_sf * 2.4.46 cbf_set_pixel_size, cbf_set_pixel_size_fs, cbf_set_pixel_size_sf * 2.4.47 cbf_get_inferred_pixel_size, cbf_get_inferred_pixel_size_fs, cbf_get_inferred_pixel_size_sf * 2.4.48 cbf_get_unit_cell * 2.4.49 cbf_set_unit_cell * 2.4.50 cbf_get_reciprocal_cell * 2.4.51 cbf_set_reciprocal_cell * 2.4.52 cbf_compute_cell_volume * 2.4.53 cbf_compute_reciprocal_cell * 2.4.54 cbf_get_orientation_matrix, cbf_set_orientation_matrix * 2.4.55 cbf_get_bin_sizes, cbf_set_bin_sizes * 2.5 F90 function interfaces * 2.5.1 FCB_ATOL_WCNT * 2.5.2 FCB_CI_STRNCMPARR * 2.5.3 FCB_EXIT_BINARY * 2.5.4 FCB_NBLEN_ARRAY * 2.5.5 FCB_NEXT_BINARY * 2.5.6 FCB_OPEN_CIFIN * 2.5.7 FCB_PACKED: FCB_DECOMPRESS_PACKED_I2, FCB_DECOMPRESS_PACKED_I4, FCB_DECOMPRESS_PACKED_3D_I2, FCB_DECOMPRESS_PACKED_3D_I4 * 2.5.8 FCB_READ_BITS * 2.5.9 FCB_READ_BYTE * 2.5.10 FCB_READ_IMAGE_I2, FCB_READ_IMAGE_I4, FCB_READ_IMAGE_3D_I2, FCB_READ_IMAGE_3D_I4 * 2.5.11 FCB_READ_LINE * 2.5.12 FCB_READ_XDS_I2 * 2.5.13 FCB_SKIP_WHITESPACE * 3. File format * 3.1 General description * 3.2 Format of the binary sections * 3.2.1 Format of imgCIF binary sections * 3.2.2 Format of CBF binary sections * 3.3 Compression schemes * 3.3.1 Canonical-code compression * 3.3.2 CCP4-style compression * 3.3.3 Byte_offset compression * 4. Installation * 5. Example programs 1. Introduction CBFlib (Crystallographic Binary File library) is a library of ANSI-C functions providing a simple mechanism for accessing Crystallographic Binary Files (CBF files) and Image-supporting CIF (imgCIF) files. The CBFlib API is loosely based on the CIFPARSE API for mmCIF files. Like CIFPARSE, CBFlib does not perform any semantic integrity checks; rather it simply provides functions to create, read, modify and write CBF binary data files and imgCIF ASCII data files. Starting with version 0.7.7, an envolving FCBlib (Fortran Crystallographic Binary library) has been added. As of this release it includes code for reading byte-offset and packed compression image files created by CBFlib. 2. Function descriptions 2.1 General description Almost all of the CBFlib functions receive a value of type cbf_handle (a CBF handle) as the first argument. Several of the high-level CBFlib functions dealing with geometry receive a value of type cbf_goniometer (a handle for a CBF goniometer object) or cbf_detector (a handle for a CBF detector object). All functions return an integer equal to 0 for success or an error code for failure. 2.1.1 CBF handles CBFlib permits a program to use multiple CBF objects simultaneously. To identify the CBF object on which a function will operate, CBFlib uses a value of type cbf_handle. All functions in the library except cbf_make_handle expect a value of type cbf_handle as the first argument. The function cbf_make_handle creates and initializes a new CBF handle. The function cbf_free_handle destroys a handle and frees all memory associated with the corresponding CBF object. 2.1.2 CBF goniometer handles To represent the goniometer used to orient a sample, CBFlib uses a value of type cbf_goniometer. A goniometer object is created and initialized from a CBF object using the function cbf_construct_goniometer. The function cbf_free_goniometer destroys a goniometer handle and frees all memory associated with the corresponding object. 2.1.3 CBF detector handles To represent a detector surface mounted on a positioning system, CBFlib uses a value of type cbf_detector. A goniometer object is created and initialized from a CBF object using one of the functions cbf_construct_detector, cbf_construct_reference_detector or cbf_require_reference_detector. The function cbf_free_detector destroys a detector handle and frees all memory associated with the corresponding object. 2.1.4 Return values All of the CBFlib functions return 0 on success and an error code on failure. The error codes are: CBF_FORMAT The file format is invalid CBF_ALLOC Memory allocation failed CBF_ARGUMENT Invalid function argument CBF_ASCII The value is ASCII (not binary) CBF_BINARY The value is binary (not ASCII) CBF_BITCOUNT The expected number of bits does not match the actual number written CBF_ENDOFDATA The end of the data was reached before the end of the array CBF_FILECLOSE File close error CBF_FILEOPEN File open error CBF_FILEREAD File read error CBF_FILESEEK File seek error CBF_FILETELL File tell error CBF_FILEWRITE File write error CBF_IDENTICAL A data block with the new name already exists CBF_NOTFOUND The data block, category, column or row does not exist CBF_OVERFLOW The number read cannot fit into the destination argument. The destination has been set to the nearest value. CBF_UNDEFINED The requested number is not defined (e.g. 0/0; new for version 0.7). CBF_NOTIMPLEMENTED The requested functionality is not yet implemented (New for version 0.7). If more than one error has occurred, the error code is the logical OR of the individual error codes. 2.2 Reading and writing files containing binary sections 2.2.1 Reading binary sections The current version of CBFlib only decompresses a binary section from disk when requested by the program. When a file containing one or more binary sections is read, CBFlib saves the file pointer and the position of the binary section within the file and then jumps past the binary section. When the program attempts to access the binary data, CBFlib sets the file position back to the start of the binary section and then reads the data. For this scheme to work: 1. The file must be a random-access file opened in binary mode (fopen ( ," rb")). 2. The program must not close the file. CBFlib will close the file using fclose ( ) when it is no longer needed. At present, this also means that a program cant read a file and then write back to the same file. This restriction will be eliminated in a future version. When reading an imgCIF vs a CBF, the difference is detected automatically. 2.2.2 Writing binary sections When a program passes CBFlib a binary value, the data is compressed to a temporary file. If the CBF object is subsequently written to a file, the data is simply copied from the temporary file to the output file. The output file can be of any type. If the program indicates to CBFlib that the file is a random-access and readable, CBFlib will conserve disk space by closing the temporary file and using the output file as the location at which the binary value is stored. For this option to work: 1. The file must be a random-access file opened in binary update mode (fopen ( , "w+b")). 2. The program must not close the file. CBFlib will close the file using fclose ( ) when it is no longer needed. If this option is not used: 1. CBFlib will continue using the temporary file. 2. CBFlib will not close the file. This is the responsibility of the main program. 2.2.3 Summary of reading and writing files containing binary sections 1. Open disk files to read using the mode "rb". 2. If possible, open disk files to write using the mode "w+b" and tell CBFlib that it can use the file as a buffer. 3. Do not close any files read by CBFlib or written by CBFlib with buffering turned on. 4. Do not attempt to read from a file, then write to the same file. 2.2.4 Ordering of array indices There are two major conventions in the ordering of array indices: * fs: Fast to slow. The first array index (the one numbered "1") is the one for which the values of that index change "fastest". That is, as we move forward in memory, the value of this index changes more rapidly than any other. * sf: Slow to fast. The first array index (the one numbered "1") is the one for which the values of that index change "slowest". That is as we move forward in memory, the value of this index changes more slowly than any other. During the development of CBFlib, both conventions have been used. In order to avoid confusion, the functions for which array indices are used are available in three forms: a default version which may used either one convention or the other, a form in which the name of the function has an "_fs" suffix for the fast to slow convention and a form in which the name of the function has a "_sf" suffix for the slow to fast convention. Designers of applications are advised to use one of the two suffix conventions. There is no burden on performance for using one convention or the other. The differences are resolved at compile time by use of preprocessor macros. ---------------------------------------------------------------------- ---------------------------------------------------------------------- 2.3 Low-level function prototypes 2.3.1 cbf_make_handle PROTOTYPE #include "cbf.h" int cbf_make_handle (cbf_handle *handle); DESCRIPTION cbf_make_handle creates and initializes a new internal CBF object. All other CBFlib functions operating on this object receive the CBF handle as the first argument. ARGUMENTS handle Pointer to a CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.2 cbf_free_handle ---------------------------------------------------------------------- 2.3.2 cbf_free_handle PROTOTYPE #include "cbf.h" int cbf_free_handle (cbf_handle handle); DESCRIPTION cbf_free_handle destroys the CBF object specified by the handle and frees all associated memory. ARGUMENTS handle CBF handle to free. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.1 cbf_make_handle ---------------------------------------------------------------------- 2.3.3 cbf_read_file, cbf_read_widefile PROTOTYPE #include "cbf.h" int cbf_read_file (cbf_handle handle, FILE *file, int flags); int cbf_read_widefile (cbf_handle handle, FILE *file, int flags); DESCRIPTION cbf_read_file reads the CBF or CIF file file into the CBF object specified by handle, using the CIF 1.0 convention of 80 character lines. cbf_read_widefile reads the CBF or CIF file file into the CBF object specified by handle, using the CIF 1.1 convention of 2048 character lines. A warning is issued to stderr for ascii lines over the limit. No test is performed on binary sections. Validation is performed in three ways levels: during the lexical scan, during the parse, and, if a dictionary was converted, against the value types, value enumerations, categories and parent-child relationships specified in the dictionary. flags controls the interpretation of binary section headers, the parsing of brackets constructs and the parsing of treble-quoted strings. MSG_DIGEST: Instructs CBFlib to check that the digest of the binary section matches any header digest value. If the digests do not match, the call will return CBF_FORMAT. This evaluation and comparison is delayed (a "lazy" evaluation) to ensure maximal processing efficiency. If an immediately evaluation is required, see MSG_DIGESTNOW, below. MSG_DIGESTNOW: Instructs CBFlib to check that the digest of the binary section matches any header digeste value. If the digests do not match, the call will return CBF_FORMAT. This evaluation and comparison is performed during initial parsing of the section to ensure timely error reporting at the expense of processing efficiency. If a more efficient delayed ("lazy") evaluation is required, see MSG_DIGEST, above. MSG_DIGESTWARN: Instructs CBFlib to check that the digest of the binary section matches any header digeste value. If the digests do not match, a warning message will be sent to stderr, but processing will attempt to continue. This evaluation and comparison is first performed during initial parsing of the section to ensure timely error reporting at the expense of processing efficiency. An mismatch of the message digest usually indicates a serious error, but it is sometimes worth continuing processing to try to isolate the cause of the error. Use this option with caution. MSG_NODIGEST: Do not check the digest (default). PARSE_BRACKETS: Accept DDLm bracket-delimited [item,item,...item] or {item,item,...item} or (item,item,...item) constructs as valid, stripping non-quoted embedded whitespace and comments. These constructs may span multiple lines. PARSE_LIBERAL_BRACKETS: Accept DDLm bracket-delimited [item,item,...item] or {item,item,...item} or (item,item,...item) constructs as valid, stripping embedded non-quoted, non-separating whitespace and comments. These constructs may span multiple lines. In this case, whitespace may be used as an alternative to the comma. PARSE_TRIPLE_QUOTES: Accept DDLm triple-quoted """item,item,...item""" or '''item,item,...item''' constructs as valid, stripping embedded whitespace and comments. These constructs may span multiple lines. If this flag is set, then ''' will not be interpreted as a quoted apoptrophe and """ will not be interpreted as a quoted double quote mark and PARSE_NOBRACKETS: Do not accept DDLm bracket-delimited [item,item,...item] or {item,item,...item} or (item,item,...item) constructs as valid, stripping non-quoted embedded whitespace and comments. These constructs may span multiple lines. PARSE_NOTRIPLE_QUOTES: No not accept DDLm triple-quoted """item,item,...item""" or '''item,item,...item''' constructs as valid, stripping embedded whitespace and comments. These constructs may span multiple lines. If this flag is set, then ''' will be interpreted as a quoted apostrophe and """ will be interpreted as a quoted double quote mark. CBFlib defers reading binary sections as long as possible. In the current version of CBFlib, this means that: 1. The file must be a random-access file opened in binary mode (fopen ( , "rb")). 2. The program must not close the file. CBFlib will close the file using fclose ( ) when it is no longer needed. These restrictions may change in a future release. ARGUMENTS handle CBF handle. file Pointer to a file descriptor. headers Controls interprestation of binary section headers. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.4 cbf_write_file ---------------------------------------------------------------------- 2.3.4 cbf_write_file PROTOTYPE #include "cbf.h" int cbf_write_file (cbf_handle handle, FILE *file, int readable, int ciforcbf, int flags, int encoding); int cbf_write_widefile (cbf_handle handle, FILE *file, int readable, int ciforcbf, int flags, int encoding); DESCRIPTION cbf_write_file writes the CBF object specified by handle into the file file, following CIF 1.0 conventions of 80 character lines. cbf_write_widefile writes the CBF object specified by handle into the file file, following CIF 1.1 conventions of 2048 character lines. A warning is issued to stderr for ascii lines over the limit, and an attempt is made to fold lines to fit. No test is performed on binary sections. If a dictionary has been provided, aliases will be applied on output. Unlike cbf_read_file, the file does not have to be random-access. If the file is random-access and readable, readable can be set to non-0 to indicate to CBFlib that the file can be used as a buffer to conserve disk space. If the file is not random-access or not readable, readable must be 0. If readable is non-0, CBFlib will close the file when it is no longer required, otherwise this is the responsibility of the program. ciforcbf selects the format in which the binary sections are written: CIF Write an imgCIF file. CBF Write a CBF file (default). flags selects the type of header used in CBF binary sections, selects whether message digests are generated, and controls the style of output. The value of flags can be a logical OR of any of: MIME_HEADERS Use MIME-type headers (default). MIME_NOHEADERS Use a simple ASCII headers. MSG_DIGEST Generate message digests for binary data validation. MSG_NODIGEST Do not generate message digests (default). PARSE_BRACKETS Do not convert bracketed strings to text fields (default). PARSE_LIBERAL_BRACKETS Do not convert bracketed strings to text fields (default). PARSE_NOBRACKETS Convert bracketed strings to text fields (default). PARSE_TRIPLE_QUOTES Do not convert triple-quoted strings to text fields (default). PARSE_NOTRIPLE_QUOTES Convert triple-quoted strings to text fields (default). PAD_1K Pad binary sections with 1023 nulls. PAD_2K Pad binary sections with 2047 nulls. PAD_4K Pad binary sections with 4095 nulls. Note that on output, the types "prns&, "brcs" and "bkts" will be converted to "text" fields if PARSE_NOBRACKETS has been set flags, and that the types "tsqs" and "tdqs" will be converted to "text" fields if the flag PARSE_NOTRIPLE_QUOTES has been set in the flags. It is an error to set PARSE_NOBRACKETS and to set either PARSE_BRACKETS or PARSE_LIBERAL_BRACKETS. It is an error to set both PARSE_NOTRIPLE_QUOTES and PARSE_TRIPLE_QUOTES. encoding selects the type of encoding used for binary sections and the type of line-termination in imgCIF files. The value can be a logical OR of any of: ENC_BASE64 Use BASE64 encoding (default). ENC_QP Use QUOTED-PRINTABLE encoding. ENC_BASE8 Use BASE8 (octal) encoding. ENC_BASE10 Use BASE10 (decimal) encoding. ENC_BASE16 Use BASE16 (hexadecimal) encoding. ENC_FORWARD For BASE8, BASE10 or BASE16 encoding, map bytes to words forward (1234) (default on little-endian machines). ENC_BACKWARD Map bytes to words backward (4321) (default on big-endian machines). ENC_CRTERM Terminate lines with CR. ENC_LFTERM Terminate lines with LF (default). ARGUMENTS handle CBF handle. file Pointer to a file descriptor. readable If non-0: this file is random-access and readable and can be used as a buffer. ciforcbf Selects the format in which the binary sections are written (CIF/CBF). headers Selects the type of header in CBF binary sections and message digest generation. encoding Selects the type of encoding used for binary sections and the type of line-termination in imgCIF files. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.3 cbf_read_file ---------------------------------------------------------------------- 2.3.5 cbf_new_datablock, cbf_new_saveframe PROTOTYPE #include "cbf.h" int cbf_new_datablock (cbf_handle handle, const char *datablockname); int cbf_new_saveframe (cbf_handle handle, const char *saveframename); DESCRIPTION cbf_new_datablock creates a new data block with name datablockname and makes it the current data block. cbf_new_saveframe creates a new save frame with name saveframename within the current data block and makes the new save frame the current save frame. If a data block or save frame with this name already exists, the existing data block or save frame becomes the current data block or save frame. ARGUMENTS handle CBF handle. datablockname The name of the new data block. saveframename The name of the new save frame. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.6 cbf_force_new_datablock, cbf_force_new_saveframe 2.3.7 cbf_new_category 2.3.8 cbf_force_new_category 2.3.9 cbf_new_column 2.3.10 cbf_new_row 2.3.11 cbf_insert_row 2.3.12 cbf_set_datablockname, cbf_set_saveframename 2.3.17 cbf_remove_datablock, cbf_remove_saveframe 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.6 cbf_force_new_datablock, cbf_force_new_saveframe PROTOTYPE #include "cbf.h" int cbf_force_new_datablock (cbf_handle handle, const char *datablockname); int cbf_force_new_saveframe (cbf_handle handle, const char *saveframename); DESCRIPTION cbf_force_new_datablock creates a new data block with name datablockname and makes it the current data block. Duplicate data block names are allowed. cbf_force_new_saveframe creates a new savew frame with name saveframename and makes it the current save frame. Duplicate save frame names are allowed. Even if a save frame with this name already exists, a new save frame is created and becomes the current save frame. ARGUMENTS handle CBF handle. datablockname The name of the new data block. saveframename The name of the new save frame. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.5 cbf_new_datablock, cbf_new_saveframe 2.3.7 cbf_new_category 2.3.8 cbf_force_new_category 2.3.9 cbf_new_column 2.3.10 cbf_new_row 2.3.11 cbf_insert_row 2.3.12 cbf_set_datablockname, cbf_set_saveframename 2.3.17 cbf_remove_datablock, cbf_remove_saveframe 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.7 cbf_new_category PROTOTYPE #include "cbf.h" int cbf_new_category (cbf_handle handle, const char *categoryname); DESCRIPTION cbf_new_category creates a new category in the current data block with name categoryname and makes it the current category. If a category with this name already exists, the existing category becomes the current category. ARGUMENTS handle CBF handle. categoryname The name of the new category. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.5 cbf_new_datablock, cbf_new_saveframe 2.3.6 cbf_force_new_datablock, cbf_force_new_saveframe 2.3.8 cbf_force_new_category 2.3.9 cbf_new_column 2.3.10 cbf_new_row 2.3.11 cbf_insert_row 2.3.18 cbf_remove_category 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.8 cbf_force_new_category PROTOTYPE #include "cbf.h" int cbf_force_new_category (cbf_handle handle, const char *categoryname); DESCRIPTION cbf_force_new_category creates a new category in the current data block with name categoryname and makes it the current category. Duplicate category names are allowed. Even if a category with this name already exists, a new category of the same name is created and becomes the current category. The allows for the creation of unlooped tag/value lists drawn from the same category. ARGUMENTS handle CBF handle. categoryname The name of the new category. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.5 cbf_new_datablock, cbf_new_saveframe 2.3.6 cbf_force_new_datablock, cbf_force_new_saveframe 2.3.7 cbf_new_category 2.3.9 cbf_new_column 2.3.10 cbf_new_row 2.3.11 cbf_insert_row 2.3.18 cbf_remove_category 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.9 cbf_new_column PROTOTYPE #include "cbf.h" int cbf_new_column (cbf_handle handle, const char *columnname); DESCRIPTION cbf_new_column creates a new column in the current category with name columnname and makes it the current column. If a column with this name already exists, the existing column becomes the current category. ARGUMENTS handle CBF handle. columnname The name of the new column. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.5 cbf_new_datablock, cbf_new_saveframe 2.3.6 cbf_force_new_datablock, cbf_force_new_saveframe 2.3.7 cbf_new_category 2.3.8 cbf_force_new_category 2.3.10 cbf_new_row 2.3.11 cbf_insert_row 2.3.19 cbf_remove_column 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.10 cbf_new_row PROTOTYPE #include "cbf.h" int cbf_new_row (cbf_handle handle); DESCRIPTION cbf_new_row adds a new row to the current category and makes it the current row. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.5 cbf_new_datablock, cbf_new_saveframe 2.3.6 cbf_force_new_datablock, cbf_force_new_saveframe 2.3.7 cbf_new_category 2.3.8 cbf_force_new_category 2.3.9 cbf_new_column 2.3.11 cbf_insert_row 2.3.12 cbf_delete_row 2.3.20 cbf_remove_row 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.11 cbf_insert_row PROTOTYPE #include "cbf.h" int cbf_insert_row (cbf_handle handle, unsigned int rownumber); DESCRIPTION cbf_insert_row adds a new row to the current category. The new row is inserted as row rownumber and existing rows starting from rownumber are moved up by 1. The new row becomes the current row. If the category has fewer than rownumber rows, the function returns CBF_NOTFOUND. The row numbers start from 0. ARGUMENTS handle CBF handle. rownumber The row number of the new row. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.5 cbf_new_datablock, cbf_new_saveframe 2.3.6 cbf_force_new_datablock, cbf_force_new_saveframe 2.3.7 cbf_new_category 2.3.8 cbf_force_new_category 2.3.9 cbf_new_column 2.3.10 cbf_new_row 2.3.12 cbf_delete_row 2.3.20 cbf_remove_row 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.12 cbf_delete_row PROTOTYPE #include "cbf.h" int cbf_delete_row (cbf_handle handle, unsigned int rownumber); DESCRIPTION cbf_delete_row deletes a row from the current category. Rows starting from rownumber +1 are moved down by 1. If the current row was higher than rownumber, or if the current row is the last row, it will also move down by 1. The row numbers start from 0. ARGUMENTS handle CBF handle. rownumber The number of the row to delete. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.10 cbf_new_row 2.3.11 cbf_insert_row 2.3.17 cbf_remove_datablock, cbf_remove_saveframe 2.3.18 cbf_remove_category 2.3.19 cbf_remove_column 2.3.20 cbf_remove_row 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.13 cbf_set_datablockname, cbf_set_saveframename PROTOTYPE #include "cbf.h" int cbf_set_datablockname (cbf_handle handle, const char *datablockname); int cbf_set_saveframename (cbf_handle handle, const char *saveframename); DESCRIPTION cbf_set_datablockname changes the name of the current data block to datablockname. cbf_set_saveframename changes the name of the current save frame to saveframename. If a data block or save frame with this name already exists (comparison is case-insensitive), the function returns CBF_IDENTICAL. ARGUMENTS handle CBF handle. datablockname The new data block name. datablockname The new save frame name. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.5 cbf_new_datablock, cbf_new_saveframe 2.3.14 cbf_reset_datablocks 2.3.15 cbf_reset_datablock, cbf_reset_saveframe 2.3.17 cbf_remove_datablock, cbf_remove_saveframe 2.3.42 cbf_datablock_name ---------------------------------------------------------------------- 2.3.14 cbf_reset_datablocks PROTOTYPE #include "cbf.h" int cbf_reset_datablocks (cbf_handle handle); DESCRIPTION cbf_reset_datablocks deletes all categories from all data blocks. The current data block does not change. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.15 cbf_reset_datablock, cbf_reset_saveframe 2.3.18 cbf_remove_category ---------------------------------------------------------------------- 2.3.15 cbf_reset_datablock, cbf_reset_datablock PROTOTYPE #include "cbf.h" int cbf_reset_datablock (cbf_handle handle); int cbf_reset_saveframe (cbf_handle handle); DESCRIPTION cbf_reset_datablock deletes all categories from the current data block. cbf_reset_saveframe deletes all categories from the current save frame. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.14 cbf_reset_datablocks 2.3.18 cbf_remove_category ---------------------------------------------------------------------- 2.3.16 cbf_reset_category PROTOTYPE #include "cbf.h" int cbf_reset_category (cbf_handle handle); DESCRIPTION cbf_reset_category deletes all columns and rows from current category. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.16 cbf_reset_category 2.3.19 cbf_remove_column 2.3.20 cbf_remove_row ---------------------------------------------------------------------- 2.3.17 cbf_remove_datablock, cbf_remove_saveframe PROTOTYPE #include "cbf.h" int cbf_remove_datablock (cbf_handle handle); int cbf_remove_saveframe (cbf_handle handle); DESCRIPTION cbf_remove_datablock deletes the current data block. cbf_remove_saveframe deletes the current save frame. The current data block becomes undefined. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.5 cbf_new_datablock, cbf_new_saveframe 2.3.6 cbf_force_new_datablock, cbf_force_new_saveframe 2.3.18 cbf_remove_category 2.3.19 cbf_remove_column 2.3.20 cbf_remove_row 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.18 cbf_remove_category PROTOTYPE #include "cbf.h" int cbf_remove_category (cbf_handle handle); DESCRIPTION cbf_remove_category deletes the current category. The current category becomes undefined. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.7 cbf_new_category 2.3.8 cbf_force_new_category 2.3.17 cbf_remove_datablock, cbf_remove_saveframe 2.3.19 cbf_remove_column 2.3.20 cbf_remove_row 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.19 cbf_remove_column PROTOTYPE #include "cbf.h" int cbf_remove_column (cbf_handle handle); DESCRIPTION cbf_remove_column deletes the current column. The current column becomes undefined. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.9 cbf_new_column 2.3.17 cbf_remove_datablock, cbf_remove_saveframe 2.3.18 cbf_remove_category 2.3.20 cbf_remove_row 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.20 cbf_remove_row PROTOTYPE #include "cbf.h" int cbf_remove_row (cbf_handle handle); DESCRIPTION cbf_remove_row deletes the current row in the current category. If the current row was the last row, it will move down by 1, otherwise, it will remain the same. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.10 cbf_new_row 2.3.11 cbf_insert_row 2.3.17 cbf_remove_datablock, cbf_remove_saveframe 2.3.18 cbf_remove_category 2.3.19 cbf_remove_column 2.3.12 cbf_delete_row 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.21 cbf_rewind_datablock PROTOTYPE #include "cbf.h" int cbf_rewind_datablock (cbf_handle handle); DESCRIPTION cbf_rewind_datablock makes the first data block the current data block. If there are no data blocks, the function returns CBF_NOTFOUND. The current category becomes undefined. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.22 cbf_rewind_category, cbf_rewind_saveframe, cbf_rewind_blockitem 2.3.19 cbf_rewind_column 2.3.24 cbf_rewind_row 2.3.25 cbf_next_datablock ---------------------------------------------------------------------- 2.3.22 cbf_rewind_category, cbf_rewind_saveframe, cbf_rewind_blockitem PROTOTYPE #include "cbf.h" int cbf_rewind_category (cbf_handle handle); int cbf_rewind_saveframe (cbf_handle handle); int cbf_rewind_blockitem (cbf_handle handle, CBF_NODETYPE * type); DESCRIPTION cbf_rewind_category makes the first category in the current data block the current category. cbf_rewind_saveframe makes the first saveframe in the current data block the current saveframe. cbf_rewind_blockitem makes the first blockitem (category or saveframe) in the current data block the current blockitem. The type of the blockitem (CBF_CATEGORY or CBF_SAVEFRAME) is returned in type. If there are no categories, saveframes or blockitems the function returns CBF_NOTFOUND. The current column and row become undefined. ARGUMENTS handle CBF handle. type CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.21 cbf_rewind_datablock 2.3.19 cbf_rewind_column 2.3.24 cbf_rewind_row 2.3.26 cbf_next_category, cbf_next_saveframe, cbf_next_blockitem ---------------------------------------------------------------------- 2.3.23 cbf_rewind_column PROTOTYPE #include "cbf.h" int cbf_rewind_column (cbf_handle handle); DESCRIPTION cbf_rewind_column makes the first column in the current category the current column. If there are no columns, the function returns CBF_NOTFOUND. The current row is not affected. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.21 cbf_rewind_datablock 2.3.22 cbf_rewind_category, cbf_rewind_saveframe, cbf_rewind_blockitem 2.3.24 cbf_rewind_row 2.3.27 cbf_next_column ---------------------------------------------------------------------- 2.3.24 cbf_rewind_row PROTOTYPE #include "cbf.h" int cbf_rewind_row (cbf_handle handle); DESCRIPTION cbf_rewind_row makes the first row in the current category the current row. If there are no rows, the function returns CBF_NOTFOUND. The current column is not affected. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.21 cbf_rewind_datablock 2.3.22 cbf_rewind_category, cbf_rewind_saveframe, cbf_rewind_blockitem 2.3.19 cbf_rewind_column 2.3.28 cbf_next_row ---------------------------------------------------------------------- 2.3.25 cbf_next_datablock PROTOTYPE #include "cbf.h" int cbf_next_datablock (cbf_handle handle); DESCRIPTION cbf_next_datablock makes the data block following the current data block the current data block. If there are no more data blocks, the function returns CBF_NOTFOUND. The current category becomes undefined. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.21 cbf_rewind_datablock 2.3.26 cbf_next_category, cbf_next_saveframe, cbf_next_blockitem 2.3.27 cbf_next_column 2.3.28 cbf_next_row ---------------------------------------------------------------------- 2.3.26 cbf_next_category PROTOTYPE #include "cbf.h" int cbf_next_category (cbf_handle handle); DESCRIPTION cbf_next_category makes the category following the current category in the current data block the current category. If there are no more categories, the function returns CBF_NOTFOUND. The current column and row become undefined. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.22 cbf_rewind_category, cbf_rewind_saveframe, cbf_rewind_blockitem 2.3.25 cbf_next_datablock 2.3.27 cbf_next_column 2.3.27 cbf_next_row ---------------------------------------------------------------------- 2.3.27 cbf_next_column PROTOTYPE #include "cbf.h" int cbf_next_column (cbf_handle handle); DESCRIPTION cbf_next_column makes the column following the current column in the current category the current column. If there are no more columns, the function returns CBF_NOTFOUND. The current row is not affected. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.19 cbf_rewind_column 2.3.25 cbf_next_datablock 2.3.26 cbf_next_category, cbf_next_saveframe, cbf_next_blockitem 2.3.28 cbf_next_row ---------------------------------------------------------------------- 2.3.28 cbf_next_row PROTOTYPE #include "cbf.h" int cbf_next_row (cbf_handle handle); DESCRIPTION cbf_next_row makes the row following the current row in the current category the current row. If there are no more rows, the function returns CBF_NOTFOUND. The current column is not affected. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.24 cbf_rewind_row 2.3.25 cbf_next_datablock 2.3.26 cbf_next_category, cbf_next_saveframe, cbf_next_blockitem 2.3.27 cbf_next_column ---------------------------------------------------------------------- 2.3.29 cbf_find_datablock PROTOTYPE #include "cbf.h" int cbf_find_datablock (cbf_handle handle, const char *datablockname); DESCRIPTION cbf_find_datablock makes the data block with name datablockname the current data block. The comparison is case-insensitive. If the data block does not exist, the function returns CBF_NOTFOUND. The current category becomes undefined. ARGUMENTS handle CBF handle. datablockname The name of the data block to find. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.21 cbf_rewind_datablock 2.3.25 cbf_next_datablock 2.3.30 cbf_find_category, cbf_find_saveframe, cbf_find_blockitem 2.3.31 cbf_find_column 2.3.32 cbf_find_row 2.3.42 cbf_datablock_name 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.30 cbf_find_category PROTOTYPE #include "cbf.h" int cbf_find_category (cbf_handle handle, const char *categoryname); DESCRIPTION cbf_find_category makes the category in the current data block with name categoryname the current category. The comparison is case-insensitive. If the category does not exist, the function returns CBF_NOTFOUND. The current column and row become undefined. ARGUMENTS handle CBF handle. categoryname The name of the category to find. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.22 cbf_rewind_category, cbf_rewind_saveframe, cbf_rewind_blockitem 2.3.26 cbf_next_category, cbf_next_saveframe, cbf_next_blockitem 2.3.29 cbf_find_datablock 2.3.31 cbf_find_column 2.3.32 cbf_find_row 2.3.43 cbf_category_name 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.31 cbf_find_column PROTOTYPE #include "cbf.h" int cbf_find_column (cbf_handle handle, const char *columnname); DESCRIPTION cbf_find_column makes the columns in the current category with name columnname the current column. The comparison is case-insensitive. If the column does not exist, the function returns CBF_NOTFOUND. The current row is not affected. ARGUMENTS handle CBF handle. columnname The name of column to find. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.19 cbf_rewind_column 2.3.27 cbf_next_column 2.3.29 cbf_find_datablock 2.3.30 cbf_find_category, cbf_find_saveframe, cbf_find_blockitem 2.3.32 cbf_find_row 2.3.44 cbf_column_name 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.32 cbf_find_row PROTOTYPE #include "cbf.h" int cbf_find_row (cbf_handle handle, const char *value); DESCRIPTION cbf_find_row makes the first row in the current column with value value the current row. The comparison is case-sensitive. If a matching row does not exist, the function returns CBF_NOTFOUND. The current column is not affected. ARGUMENTS handle CBF handle. value The value of the row to find. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.24 cbf_rewind_row 2.3.28 cbf_next_row 2.3.29 cbf_find_datablock 2.3.30 cbf_find_category, cbf_find_saveframe, cbf_find_blockitem 2.3.31 cbf_find_column 2.3.33 cbf_find_nextrow 2.3.46 cbf_get_value, cbf_require_value 2.3.48 cbf_get_typeofvalue 2.3.33 cbf_find_nextrow PROTOTYPE #include "cbf.h" int cbf_find_nextrow (cbf_handle handle, const char *value); DESCRIPTION cbf_find_nextrow makes the makes the next row in the current column with value value the current row. The search starts from the row following the last row found with cbf_find_row or cbf_find_nextrow, or from the current row if the current row was defined using any other function. The comparison is case-sensitive. If no more matching rows exist, the function returns CBF_NOTFOUND. The current column is not affected. ARGUMENTS handle CBF handle. value the value to search for. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.24 cbf_rewind_row 2.3.28 cbf_next_row 2.3.29 cbf_find_datablock 2.3.30 cbf_find_category, cbf_find_saveframe, cbf_find_blockitem 2.3.31 cbf_find_column 2.3.32 cbf_find_row 2.3.46 cbf_get_value, cbf_require_value 2.3.48 cbf_get_typeofvalue ---------------------------------------------------------------------- 2.3.34 cbf_count_datablocks PROTOTYPE #include "cbf.h" int cbf_count_datablocks (cbf_handle handle, unsigned int *datablocks); DESCRIPTION cbf_count_datablocks puts the number of data blocks in *datablocks . ARGUMENTS handle CBF handle. datablocks Pointer to the destination data block count. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.35 cbf_count_categories, cbf_count_saveframes, cbf_count_blockitems 2.3.36 cbf_count_columns 2.3.37 cbf_count_rows 2.3.38 cbf_select_datablock ---------------------------------------------------------------------- 2.3.35 cbf_count_categories PROTOTYPE #include "cbf.h" int cbf_count_categories (cbf_handle handle, unsigned int *categories); DESCRIPTION cbf_count_categories puts the number of categories in the current data block in *categories. ARGUMENTS handle CBF handle. categories Pointer to the destination category count. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.34 cbf_count_datablocks 2.3.36 cbf_count_columns 2.3.37 cbf_count_rows 2.3.39 cbf_select_category, cbf_select_saveframe, cbf_select_blockitem ---------------------------------------------------------------------- 2.3.36 cbf_count_columns PROTOTYPE #include "cbf.h" int cbf_count_columns (cbf_handle handle, unsigned int *columns); DESCRIPTION cbf_count_columns puts the number of columns in the current category in *columns. ARGUMENTS handle CBF handle. columns Pointer to the destination column count. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.34 cbf_count_datablocks 2.3.35 cbf_count_categories, cbf_count_saveframes, cbf_count_blockitems 2.3.37 cbf_count_rows 2.3.40 cbf_select_column ---------------------------------------------------------------------- 2.3.37 cbf_count_rows PROTOTYPE #include "cbf.h" int cbf_count_rows (cbf_handle handle, unsigned int *rows); DESCRIPTION cbf_count_rows puts the number of rows in the current category in *rows . ARGUMENTS handle CBF handle. rows Pointer to the destination row count. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.34 cbf_count_datablocks 2.3.35 cbf_count_categories, cbf_count_saveframes, cbf_count_blockitems 2.3.36 cbf_count_columns 2.3.41 cbf_select_row ---------------------------------------------------------------------- 2.3.38 cbf_select_datablock PROTOTYPE #include "cbf.h" int cbf_select_datablock (cbf_handle handle, unsigned int datablock); DESCRIPTION cbf_select_datablock selects data block number datablock as the current data block. The first data block is number 0. If the data block does not exist, the function returns CBF_NOTFOUND. ARGUMENTS handle CBF handle. datablock Number of the data block to select. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.34 cbf_count_datablocks 2.3.39 cbf_select_category, cbf_select_saveframe, cbf_select_blockitem 2.3.40 cbf_select_column 2.3.41 cbf_select_row ---------------------------------------------------------------------- 2.3.39 cbf_select_category PROTOTYPE #include "cbf.h" int cbf_select_category (cbf_handle handle, unsigned int category); DESCRIPTION cbf_select_category selects category number category in the current data block as the current category. The first category is number 0. The current column and row become undefined. If the category does not exist, the function returns CBF_NOTFOUND. ARGUMENTS handle CBF handle. category Number of the category to select. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.35 cbf_count_categories, cbf_count_saveframes, cbf_count_blockitems 2.3.38 cbf_select_datablock 2.3.40 cbf_select_column 2.3.41 cbf_select_row ---------------------------------------------------------------------- 2.3.40 cbf_select_column PROTOTYPE #include "cbf.h" int cbf_select_column (cbf_handle handle, unsigned int column); DESCRIPTION cbf_select_column selects column number column in the current category as the current column. The first column is number 0. The current row is not affected If the column does not exist, the function returns CBF_NOTFOUND. ARGUMENTS handle CBF handle. column Number of the column to select. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.36 cbf_count_columns 2.3.38 cbf_select_datablock 2.3.39 cbf_select_category, cbf_select_saveframe, cbf_select_blockitem 2.3.41 cbf_select_row ---------------------------------------------------------------------- 2.3.41 cbf_select_row PROTOTYPE #include "cbf.h" int cbf_select_row (cbf_handle handle, unsigned int row); DESCRIPTION cbf_select_row selects row number row in the current category as the current row. The first row is number 0. The current column is not affected If the row does not exist, the function returns CBF_NOTFOUND. ARGUMENTS handle CBF handle. row Number of the row to select. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.37 cbf_count_rows 2.3.38 cbf_select_datablock 2.3.39 cbf_select_category, cbf_select_saveframe, cbf_select_blockitem 2.3.40 cbf_select_column ---------------------------------------------------------------------- 2.3.42 cbf_datablock_name PROTOTYPE #include "cbf.h" int cbf_datablock_name (cbf_handle handle, const char **datablockname); DESCRIPTION cbf_datablock_name sets *datablockname to point to the name of the current data block. The data block name will be valid as long as the data block exists and has not been renamed. The name must not be modified by the program in any way. ARGUMENTS handle CBF handle. datablockname Pointer to the destination data block name pointer. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.29 cbf_find_datablock ---------------------------------------------------------------------- 2.3.43 cbf_category_name PROTOTYPE #include "cbf.h" int cbf_category_name (cbf_handle handle, const char **categoryname); DESCRIPTION cbf_category_name sets *categoryname to point to the name of the current category of the current data block. The category name will be valid as long as the category exists. The name must not be modified by the program in any way. ARGUMENTS handle CBF handle. categoryname Pointer to the destination category name pointer. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.30 cbf_find_category, cbf_find_saveframe, cbf_find_blockitem ---------------------------------------------------------------------- 2.3.44 cbf_column_name PROTOTYPE #include "cbf.h" int cbf_column_name (cbf_handle handle, const char **columnname); DESCRIPTION cbf_column_name sets *columnname to point to the name of the current column of the current category. The column name will be valid as long as the column exists. The name must not be modified by the program in any way. ARGUMENTS handle CBF handle. columnname Pointer to the destination column name pointer. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.31 cbf_find_column ---------------------------------------------------------------------- 2.3.45 cbf_row_number PROTOTYPE #include "cbf.h" int cbf_row_number (cbf_handle handle, unsigned int *row); DESCRIPTION cbf_row_number sets *row to the number of the current row of the current category. ARGUMENTS handle CBF handle. row Pointer to the destination row number. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.41 cbf_select_row ---------------------------------------------------------------------- 2.3.46 cbf_get_value, cbf_require_value PROTOTYPE #include "cbf.h" int cbf_get_value (cbf_handle handle, const char **value); int cbf_require_value (cbf_handle handle, const char **value, const char *defaultvalue ); DESCRIPTION cbf_get_value sets *value to point to the ASCII value of the item at the current column and row. cbf_require_value sets *value to point to the ASCII value of the item at the current column and row, creating the data item if necessary and initializing it to a copy of defaultvalue. If the value is not ASCII, the function returns CBF_BINARY. The value will be valid as long as the item exists and has not been set to a new value. The value must not be modified by the program in any way. ARGUMENTS handle CBF handle. value Pointer to the destination value pointer. defaultvalue Default value character string. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.47 cbf_set_value 2.3.48 cbf_get_typeofvalue 2.3.49 cbf_set_typeofvalue 2.3.50 cbf_get_integervalue, cbf_require_integervalue 2.3.52 cbf_get_doublevalue, cbf_require_doublevalue 2.3.54 cbf_get_integerarrayparameters, cbf_get_integerarrayparameters_wdims, cbf_get_realarrayparameters, cbf_get_realarrayparameters_wdims 2.3.55 cbf_get_integerarray, cbf_get_realarray 2.3.62 cbf_require_column_value 2.3.63 cbf_require_column_integervalue 2.3.64 cbf_require_column_doublevalue ---------------------------------------------------------------------- 2.3.47 cbf_set_value PROTOTYPE #include "cbf.h" int cbf_set_value (cbf_handle handle, const char *value); DESCRIPTION cbf_set_value sets the item at the current column and row to the ASCII value value. ARGUMENTS handle CBF handle. value ASCII value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.46 cbf_get_value, cbf_require_value 2.3.48 cbf_get_typeofvalue 2.3.49 cbf_set_typeofvalue 2.3.51 cbf_set_integervalue 2.3.53 cbf_set_doublevalue 2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_realarray, cbf_set_realarray_wdims 2.3.62 cbf_require_column_value 2.3.63 cbf_require_column_integervalue 2.3.64 cbf_require_column_doublevalue ---------------------------------------------------------------------- 2.3.48 cbf_get_typeofvalue PROTOTYPE #include "cbf.h" int cbf_get_typeofvalue (cbf_handle handle, const char **typeofvalue); DESCRIPTION cbf_get_value sets *typeofvalue to point an ASCII descriptor of the value of the item at the current column and row. The strings that may be returned are: "null" for a null value indicated by a "." or a "?" "bnry" for a binary value "word" for an unquoted string "dblq" for a double-quoted string "sglq" for a single-quoted string "text" for a semicolon-quoted string (multiline text field) "prns" for a parenthesis-bracketed string (multiline text field) "brcs" for a brace-bracketed string (multiline text field) "bkts" for a square-bracket-bracketed string (multiline text field) "tsqs" for a treble-single-quote quoted string (multiline text field) "tdqs" for a treble-double-quote quoted string (multiline text field) Not all types are valid for all type of CIF files. In partcular the types "prns", "brcs", "bkts" were introduced with DDLm and are not valid in DDL1 or DDL2 CIFS. The types "tsqs" and "tdqs" are not formally part of the CIF syntax. A field for which no value has been set sets *typeofvalue to NULL rather than to the string "null". The typeofvalue must not be modified by the program in any way. ARGUMENTS handle CBF handle. typeofvalue Pointer to the destination type-of-value string pointer. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.46 cbf_get_value, cbf_require_value 2.3.47 cbf_set_value 2.3.49 cbf_set_typeofvalue 2.3.50 cbf_get_integervalue, cbf_require_integervalue 2.3.52 cbf_get_doublevalue, cbf_require_doublevalue 2.3.54 cbf_get_integerarrayparameters, cbf_get_integerarrayparameters_wdims, cbf_get_realarrayparameters, cbf_get_realarrayparameters_wdims 2.3.55 cbf_get_integerarray, cbf_get_realarray 2.3.62 cbf_require_column_value 2.3.63 cbf_require_column_integervalue 2.3.64 cbf_require_column_doublevalue ---------------------------------------------------------------------- 2.3.49 cbf_set_typeofvalue PROTOTYPE #include "cbf.h" int cbf_set_typeofvalue (cbf_handle handle, const char *typeofvalue); DESCRIPTION cbf_set_typeofvalue sets the type of the item at the current column and row to the type specified by the ASCII character string given by typeofvalue. The strings that may be used are: "null" for a null value indicated by a "." or a "?" "bnry" for a binary value "word" for an unquoted string "dblq" for a double-quoted string "sglq" for a single-quoted string "text" for a semicolon-quoted string (multiline text field) "prns" for a parenthesis-bracketed string (multiline text field) "brcs" for a brace-bracketed string (multiline text field) "bkts" for a square-bracket-bracketed string (multiline text field) "tsqs" for a treble-single-quote quoted string (multiline text field) "tdqs" for a treble-double-quote quoted string (multiline text field) Not all types may be used for all values. Not all types are valid for all type of CIF files. In partcular the types "prns", "brcs", "bkts" were introduced with DDLm and are not valid in DDL1 or DDL2 CIFS. The types "tsqs" and "tdqs" are not formally part of the CIF syntax. No changes may be made to the type of binary values. You may not set the type of a string that contains a single quote followed by a blank or a tab or which contains multiple lines to "sglq". You may not set the type of a string that contains a double quote followed by a blank or a tab or which contains multiple lines to "dblq". ARGUMENTS handle CBF handle. typeofvalue ASCII string for desired type of value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.46 cbf_get_value, cbf_require_value 2.3.47 cbf_set_value 2.3.48 cbf_get_typeofvalue 2.3.51 cbf_set_integervalue 2.3.53 cbf_set_doublevalue 2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_realarray, cbf_set_realarray_wdims 2.3.62 cbf_require_column_value 2.3.63 cbf_require_column_integervalue 2.3.64 cbf_require_column_doublevalue ---------------------------------------------------------------------- 2.3.50 cbf_get_integervalue, cbf_require_integervalue PROTOTYPE #include "cbf.h" int cbf_get_integervalue (cbf_handle handle, int *number); int cbf_require_integervalue (cbf_handle handle, int *number, int defaultvalue); DESCRIPTION cbf_get_integervalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal integer. cbf_require_integervalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal integer, setting it to defaultvalue if necessary. If the value is not ASCII, the function returns CBF_BINARY. ARGUMENTS handle CBF handle. number pointer to the number. defaultvalue default number value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.46 cbf_get_value, cbf_require_value 2.3.48 cbf_get_typeofvalue 2.3.51 cbf_set_integervalue 2.3.52 cbf_get_doublevalue, cbf_require_doublevalue 2.3.54 cbf_get_integerarrayparameters, cbf_get_integerarrayparameters_wdims, cbf_get_realarrayparameters, cbf_get_realarrayparameters_wdims 2.3.55 cbf_get_integerarray, cbf_get_realarray 2.3.62 cbf_require_column_value 2.3.63 cbf_require_column_integervalue 2.3.64 cbf_require_column_doublevalue ---------------------------------------------------------------------- 2.3.51 cbf_set_integervalue PROTOTYPE #include "cbf.h" int cbf_set_integervalue (cbf_handle handle, int number); DESCRIPTION cbf_set_integervalue sets the item at the current column and row to the integer value number written as a decimal ASCII string. ARGUMENTS handle CBF handle. number Integer value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.46 cbf_get_value, cbf_require_value 2.3.47 cbf_set_value 2.3.48 cbf_get_typeofvalue 2.3.49 cbf_set_typeofvalue 2.3.50 cbf_get_integervalue, cbf_require_integervalue 2.3.51 cbf_set_integervalue 2.3.53 cbf_set_doublevalue 2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_realarray, cbf_set_realarray_wdims 2.3.62 cbf_require_column_value 2.3.63 cbf_require_column_integervalue 2.3.64 cbf_require_column_doublevalue ---------------------------------------------------------------------- 2.3.52 cbf_get_doublevalue, cbf_require_doublevalue PROTOTYPE #include "cbf.h" int cbf_get_doublevalue (cbf_handle handle, double *number); int cbf_require_doublevalue (cbf_handle handle, double *number, double defaultvalue); DESCRIPTION cbf_get_doublevalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal floating-point number. cbf_require_doublevalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal floating-point number, setting it to defaultvalue if necessary. If the value is not ASCII, the function returns CBF_BINARY. ARGUMENTS handle CBF handle. number Pointer to the destination number. defaultvalue default number value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.46 cbf_get_value, cbf_require_value 2.3.48 cbf_get_typeofvalue 2.3.49 cbf_set_typeofvalue 2.3.50 cbf_get_integervalue, cbf_require_integervalue 2.3.53 cbf_set_doublevalue 2.3.54 cbf_get_integerarrayparameters, cbf_get_integerarrayparameters_wdims, cbf_get_realarrayparameters, cbf_get_realarrayparameters_wdims 2.3.55 cbf_get_integerarray, cbf_get_realarray 2.3.62 cbf_require_column_value 2.3.63 cbf_require_column_integervalue 2.3.64 cbf_require_column_doublevalue ---------------------------------------------------------------------- 2.3.53 cbf_set_doublevalue PROTOTYPE #include "cbf.h" int cbf_set_doublevalue (cbf_handle handle, const char *format, double number); DESCRIPTION cbf_set_doublevalue sets the item at the current column and row to the floating-point value number written as an ASCII string with the format specified by format as appropriate for the printf function. ARGUMENTS handle CBF handle. format Format for the number. number Floating-point value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.46 cbf_get_value, cbf_require_value 2.3.47 cbf_set_value 2.3.48 cbf_get_typeofvalue 2.3.49 cbf_set_typeofvalue 2.3.51 cbf_set_integervalue 2.3.52 cbf_get_doublevalue, cbf_require_doublevalue 2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_realarray, cbf_set_realarray_wdims 2.3.62 cbf_require_column_value 2.3.63 cbf_require_column_integervalue 2.3.64 cbf_require_column_doublevalue ---------------------------------------------------------------------- 2.3.54 cbf_get_integerarrayparameters, cbf_get_integerarrayparameters_wdims, cbf_get_integerarrayparameters_wdims_fs, cbf_get_integerarrayparameters_wdims_sf, cbf_get_realarrayparameters, cbf_get_realarrayparameters_wdims, cbf_get_realarrayparameters_wdims_fs, cbf_get_realarrayparameters_wdims_sf PROTOTYPE #include "cbf.h" int cbf_get_integerarrayparameters (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, int *elsigned, int *elunsigned, size_t *elements, int *minelement, int *maxelement); int cbf_get_integerarrayparameters_wdims (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, int *elsigned, int *elunsigned, size_t *elements, int *minelement, int *maxelement, const char **byteorder, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding); int cbf_get_integerarrayparameters_wdims_fs (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, int *elsigned, int *elunsigned, size_t *elements, int *minelement, int *maxelement, const char **byteorder, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding); int cbf_get_integerarrayparameters_wdims_sf (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, int *elsigned, int *elunsigned, size_t *elements, int *minelement, int *maxelement, const char **byteorder, size_t *dimslow, size_t *dimmid, size_t *dimfast, size_t *padding); int cbf_get_realarrayparameters (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, size_t *elements); int cbf_get_realarrayparameters_wdims (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, size_t *elements, const char **byteorder, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding); int cbf_get_realarrayparameters_wdims_fs (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, size_t *elements, const char **byteorder, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding); int cbf_get_realarrayparameters_wdims_sf (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, size_t *elements, const char **byteorder, size_t *dimslow, size_t *dimmid, size_t *dimfast, size_t *padding); DESCRIPTION cbf_get_integerarrayparameters sets *compression, *binary_id, *elsize, *elsigned, *elunsigned, *elements, *minelement and *maxelement to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_integerarray, if a copy of the array is to be made into another CIF or CBF. cbf_get_realarrayparameters sets *compression, *binary_id, *elsize, *elements to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_realarray, if a copy of the arry is to be made into another CIF or CBF. The variants cbf_get_integerarrayparameters_wdims, cbf_get_integerarrayparameters_wdims_fs, cbf_get_integerarrayparameters_wdims_sf, cbf_get_realarrayparameters_wdims, cbf_get_realarrayparameters_wdims_fs, cbf_get_realarrayparameters_wdims_sf set **byteorder, *dimfast, *dimmid, *dimslow, and *padding as well, providing the additional parameters needed for a subsequent call to cbf_set_integerarray_wdims or cbf_set_realarray_wdims. The value returned in *byteorder is a pointer either to the string "little_endian" or to the string "big_endian". This should be the byte order of the data, not necessarily of the host machine. No attempt should be made to modify this string. At this time only "little_endian" will be returned. The values returned in *dimfast, *dimmid and *dimslow are the sizes of the fastest changing, second fastest changing and third fastest changing dimensions of the array, if specified, or zero, if not specified. The value returned in *padding is the size of the post-data padding, if any and if specified in the data header. The value is given as a count of octets. If the value is not binary, the function returns CBF_ASCII. ARGUMENTS handle CBF handle. compression Compression method used. elsize Size in bytes of each array element. binary_id Pointer to the destination integer binary identifier. elsigned Pointer to an integer. Set to 1 if the elements can be read as signed integers. elunsigned Pointer to an integer. Set to 1 if the elements can be read as unsigned integers. elements Pointer to the destination number of elements. minelement Pointer to the destination smallest element. maxelement Pointer to the destination largest element. byteorder Pointer to the destination byte order. dimfast Pointer to the destination fastest dimension. dimmid Pointer to the destination second fastest dimension. dimslow Pointer to the destination third fastest dimension. padding Pointer to the destination padding size. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.46 cbf_get_value, cbf_require_value 2.3.48 cbf_get_typeofvalue 2.3.49 cbf_set_typeofvalue 2.3.50 cbf_get_integervalue, cbf_require_integervalue 2.3.52 cbf_get_doublevalue, cbf_require_doublevalue 2.3.55 cbf_get_integerarray, cbf_get_realarray 2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_realarray, cbf_set_realarray_wdims 2.3.62 cbf_require_column_value 2.3.63 cbf_require_column_integervalue 2.3.64 cbf_require_column_doublevalue ---------------------------------------------------------------------- 2.3.55 cbf_get_integerarray, cbf_get_realarray PROTOTYPE #include "cbf.h" int cbf_get_integerarray (cbf_handle handle, int *binary_id, void *array, size_t elsize, int elsigned, size_t elements, size_t *elements_read); int cbf_get_realarray (cbf_handle handle, int *binary_id, void *array, size_t elsize, size_t elements, size_t *elements_read); DESCRIPTION cbf_get_integerarray reads the binary value of the item at the current column and row into an integer array. The array consists of elements elements of elsize bytes each, starting at array. The elements are signed if elsigned is non-0 and unsigned otherwise. *binary_id is set to the binary section identifier and *elements_read to the number of elements actually read. cbf_get_realarray reads the binary value of the item at the current column and row into a real array. The array consists of elements elements of elsize bytes each, starting at array. *binary_id is set to the binary section identifier and *elements_read to the number of elements actually read. If any element in the integer binary data cant fit into the destination element, the destination is set the nearest possible value. If the value is not binary, the function returns CBF_ASCII. If the requested number of elements cant be read, the function will read as many as it can and then return CBF_ENDOFDATA. Currently, the destination array must consist of chars, shorts or ints (signed or unsigned). If elsize is not equal to sizeof (char), sizeof (short) or sizeof (int), for cbf_get_integerarray, or sizeof(double) or sizeof(float), for cbf_get_realarray the function returns CBF_ARGUMENT. An additional restriction in the current version of CBFlib is that values too large to fit in an int are not correctly decompressed. As an example, if the machine with 32-bit ints is reading an array containing a value outside the range 0 .. 2^32-1 (unsigned) or -2^31 .. 2^31-1 (signed), the array will not be correctly decompressed. This restriction will be removed in a future release. For cbf_get_realarray, only IEEE format is supported. No conversion to other floating point formats is done at this time. ARGUMENTS handle CBF handle. binary_id Pointer to the destination integer binary identifier. array Pointer to the destination array. elsize Size in bytes of each destination array element. elsigned Set to non-0 if the destination array elements are signed. elements The number of elements to read. elements_read Pointer to the destination number of elements actually read. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.46 cbf_get_value, cbf_require_value 2.3.48 cbf_get_typeofvalue 2.3.49 cbf_set_typeofvalue 2.3.50 cbf_get_integervalue, cbf_require_integervalue 2.3.52 cbf_get_doublevalue, cbf_require_doublevalue 2.3.54 cbf_get_integerarrayparameters, cbf_get_integerarrayparameters_wdims, cbf_get_realarrayparameters, cbf_get_realarrayparameters_wdims 2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_realarray, cbf_set_realarray_wdims 2.3.62 cbf_require_column_value 2.3.63 cbf_require_column_integervalue 2.3.64 cbf_require_column_doublevalue ---------------------------------------------------------------------- 2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, cbf_set_integerarray_wdims_sf, cbf_set_realarray, cbf_set_realarray_wdims, cbf_set_realarray_wdims_fs, cbf_set_realarray_wdims_sf PROTOTYPE #include "cbf.h" int cbf_set_integerarray (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, int elsigned, size_t elements); int cbf_set_integerarray_wdims (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, int elsigned, size_t elements, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); int cbf_set_integerarray_wdims_fs (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, int elsigned, size_t elements, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); int cbf_set_integerarray_wdims_sf (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, int elsigned, size_t elements, const char *byteorder, size_t dimslow, size_t dimmid, size_t dimfast, size_t padding); int cbf_set_realarray (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, size_t elements); int cbf_set_realarray_wdims (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, size_t elements, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); int cbf_set_realarray_wdims_fs (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, size_t elements, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); int cbf_set_realarray_wdims_sf (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, size_t elements, const char *byteorder, size_t dimslow, size_t dimmid, size_t dimfast, size_t padding); DESCRIPTION cbf_set_integerarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. The elements are signed if elsigned is non-0 and unsigned otherwise. binary_id is the binary section identifier. cbf_set_realarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. binary_id is the binary section identifier. The cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, cbf_set_integerarray_wdims_sf, cbf_set_realarray_wdims, cbf_set_realarray_wdims_fs and cbf_set_realarray_wdims_sf variants allow the data header values of byteorder, dimfast, dimmid, dimslow and padding to be set to the data byte order, the fastest, second fastest and third fastest array dimensions and the size in byte of the post data padding to be used. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple "byte_offset" compression. CBF_NONE No compression. NOTE: This scheme is by far the slowest of the four and uses much more disk space. It is intended for routine use with small arrays only. With large arrays (like images) it should be used only for debugging. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned), for cbf_set_integerarray, or IEEE doubles or floats for cbf_set_realarray. If elsize is not equal to sizeof (char), sizeof (short) or sizeof (int), the function returns CBF_ARGUMENT. ARGUMENTS handle CBF handle. compression Compression method to use. binary_id Integer binary identifier. array Pointer to the source array. elsize Size in bytes of each source array element. elsigned Set to non-0 if the source array elements are signed. elements: The number of elements in the array. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.47 cbf_set_value 2.3.48 cbf_get_typeofvalue 2.3.49 cbf_set_typeofvalue 2.3.51 cbf_set_integervalue 2.3.53 cbf_set_doublevalue 2.3.54 cbf_get_integerarrayparameters, cbf_get_integerarrayparameters_wdims, cbf_get_realarrayparameters, cbf_get_realarrayparameters_wdims 2.3.55 cbf_get_integerarray, cbf_get_realarray 2.3.62 cbf_require_column_value 2.3.63 cbf_require_column_integervalue 2.3.64 cbf_require_column_doublevalue ---------------------------------------------------------------------- 2.3.57 cbf_failnez DEFINITION #include "cbf.h" #define cbf_failnez(f) {int err; err = (f); if (err) return err; } DESCRIPTION cbf_failnez is a macro used for error propagation throughout CBFlib. cbf_failnez executes the function f and saves the returned error value. If the error value is non-0, cbf_failnez executes a return with the error value as argument. If CBFDEBUG is defined, then a report of the error is also printed to the standard error stream, stderr, in the form CBFlib error f in "symbol" where f is the decimal value of the error and symbol is the symbolic form. ARGUMENTS f Integer error value. SEE ALSO 2.3.58 cbf_onfailnez ---------------------------------------------------------------------- 2.3.58 cbf_onfailnez DEFINITION #include "cbf.h" #define cbf_onfailnez(f,c) {int err; err = (f); if (err) {{c; }return err; }} DESCRIPTION cbf_onfailnez is a macro used for error propagation throughout CBFlib. cbf_onfailnez executes the function f and saves the returned error value. If the error value is non-0, cbf_failnez executes first the statement c and then a return with the error value as argument. If CBFDEBUG is defined, then a report of the error is also printed to the standard error stream, stderr, in the form CBFlib error f in "symbol" where f is the decimal value of the error and symbol is the symbolic form. ARGUMENTS f integer function to execute. c statement to execute on failure. SEE ALSO * 2.3.57 cbf_failnez ---------------------------------------------------------------------- 2.3.59 cbf_require_datablock PROTOTYPE #include "cbf.h" int cbf_require_datablock (cbf_handle handle, const char *datablockname); DESCRIPTION cbf_require_datablock makes the data block with name datablockname the current data block, if it exists, or creates it if it does not. The comparison is case-insensitive. The current category becomes undefined. ARGUMENTS handle CBF handle. datablockname The name of the data block to find or create. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.21 cbf_rewind_datablock 2.3.25 cbf_next_datablock 2.3.29 cbf_find_datablock 2.3.30 cbf_find_category, cbf_find_saveframe, cbf_find_blockitem 2.3.31 cbf_find_column 2.3.32 cbf_find_row 2.3.42 cbf_datablock_name 2.3.60 cbf_require_category 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.60 cbf_require_category PROTOTYPE #include "cbf.h" int cbf_require_category (cbf_handle handle, const char *categoryname); DESCRIPTION cbf_rewuire_category makes the category in the current data block with name categoryname the current category, if it exists, or creates the catagory if it does not exist. The comparison is case-insensitive. The current column and row become undefined. ARGUMENTS handle CBF handle. categoryname The name of the category to find. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.22 cbf_rewind_category, cbf_rewind_saveframe, cbf_rewind_blockitem 2.3.26 cbf_next_category, cbf_next_saveframe, cbf_next_blockitem 2.3.29 cbf_find_datablock 2.3.31 cbf_find_column 2.3.32 cbf_find_row 2.3.43 cbf_category_name 2.3.59 cbf_require_datablock 2.3.61 cbf_require_column ---------------------------------------------------------------------- 2.3.61 cbf_require_column PROTOTYPE #include "cbf.h" int cbf_require_column (cbf_handle handle, const char *columnname); DESCRIPTION cbf_require_column makes the columns in the current category with name columnname the current column, if it exists, or creates it if it does not. The comparison is case-insensitive. The current row is not affected. ARGUMENTS handle CBF handle. columnname The name of column to find. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.19 cbf_rewind_column 2.3.27 cbf_next_column 2.3.29 cbf_find_datablock 2.3.30 cbf_find_category, cbf_find_saveframe, cbf_find_blockitem 2.3.32 cbf_find_row 2.3.44 cbf_column_name 2.3.59 cbf_require_datablock 2.3.60 cbf_require_category ---------------------------------------------------------------------- 2.3.62 cbf_require_column_value PROTOTYPE #include "cbf.h" int cbf_require_column_value (cbf_handle handle, const char *columnname, const char **value, const char *defaultvalue); DESCRIPTION cbf_require_column_doublevalue sets *value to the ASCII item at the current row for the column given with the name given by *columnname, or to the string given by defaultvalue if the item cannot be found. ARGUMENTS handle CBF handle. columnname Name of the column containing the number. value pointer to the location to receive the value. defaultvalue Value to use if the requested column and value cannot be found. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.46 cbf_get_value, cbf_require_value 2.3.47 cbf_set_value 2.3.48 cbf_get_typeofvalue 2.3.49 cbf_set_typeofvalue 2.3.51 cbf_set_integervalue 2.3.52 cbf_get_doublevalue, cbf_require_doublevalue 2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_realarray, cbf_set_realarray_wdims 2.3.63 cbf_require_column_integervalue 2.3.64 cbf_require_column_doublevalue ---------------------------------------------------------------------- 2.3.63 cbf_require_column_integervalue PROTOTYPE #include "cbf.h" int cbf_require_column_integervalue (cbf_handle handle, const char *columnname, int *number, const int defaultvalue); DESCRIPTION cbf_require_column_doublevalue sets *number to the value of the ASCII item at the current row for the column given with the name given by *columnname, with the value interpreted as an integer number, or to the number given by defaultvalue if the item cannot be found. ARGUMENTS handle CBF handle. columnname Name of the column containing the number. number pointer to the location to receive the integer value. defaultvalue Value to use if the requested column and value cannot be found. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.46 cbf_get_value, cbf_require_value 2.3.47 cbf_set_value 2.3.48 cbf_get_typeofvalue 2.3.49 cbf_set_typeofvalue 2.3.51 cbf_set_integervalue 2.3.52 cbf_get_doublevalue, cbf_require_doublevalue 2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_realarray, cbf_set_realarray_wdims 2.3.62 cbf_require_column_value 2.3.64 cbf_require_column_doublevalue ---------------------------------------------------------------------- 2.3.64 cbf_require_column_doublevalue PROTOTYPE #include "cbf.h" int cbf_require_column_doublevalue (cbf_handle handle, const char *columnname, double *number, const double defaultvalue); DESCRIPTION cbf_require_column_doublevalue sets *number to the value of the ASCII item at the current row for the column given with the name given by *columnname, with the value interpreted as a decimal floating-point number, or to the number given by defaultvalue if the item cannot be found. ARGUMENTS handle CBF handle. columnname Name of the column containing the number. number pointer to the location to receive the floating-point value. defaultvalue Value to use if the requested column and value cannot be found. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.3.46 cbf_get_value, cbf_require_value 2.3.47 cbf_set_value 2.3.48 cbf_get_typeofvalue 2.3.49 cbf_set_typeofvalue 2.3.51 cbf_set_integervalue 2.3.52 cbf_get_doublevalue, cbf_require_doublevalue 2.3.56 cbf_set_integerarray, cbf_set_integerarray_wdims, cbf_set_realarray, cbf_set_realarray_wdims 2.3.62 cbf_require_column_value 2.3.63 cbf_require_column_integervalue ---------------------------------------------------------------------- 2.3.65 cbf_get_local_integer_byte_order, cbf_get_local_real_byte_order, cbf_get_local_real_format PROTOTYPE #include "cbf.h" int cbf_get_local_integer_byte_order (char ** byte_order); int cbf_get_local_real_byte_order (char ** byte_order); int cbf_get_local_real_format (char ** real_format ); DESCRIPTION cbf_get_local_integer_byte_order returns the byte order of integers on the machine on which the API is being run in the form of a character string returned as the value pointed to by byte_order. cbf_get_local_real_byte_order returns the byte order of reals on the machine on which the API is being run in the form of a character string returned as the value pointed to by byte_order. cbf_get_local_real_format returns the format of floats on the machine on which the API is being run in the form of a character string returned as the value pointed to by real_format. The strings returned must not be modified in any way. The values returned in byte_order may be the strings "little_endian" or "big-endian". The values returned in real_format may be the strings "ieee 754-1985" or "other". Additional values may be returned by future versions of the API. ARGUMENTS byte_order pointer to the returned string real_format pointer to the returned string RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.3.66 cbf_get_dictionary, cbf_set_dictionary, cbf_require_dictionary PROTOTYPE #include "cbf.h" int cbf_get_dictionary (cbf_handle handle, cbf_handle * dictionary); int cbf_set_dictionary (cbf_handle handle, cbf_handle dictionary_in); int cbf_require_dictionary (cbf_handle handle, cbf_handle * dictionary) DESCRIPTION cbf_get_dictionary sets *dictionary to the handle of a CBF which has been associated with the CBF handle by cbf_set_dictionary. cbf_set_dictionary associates the CBF handle dictionary_in with handle as its dictionary. cbf_require_dictionary sets *dictionary to the handle of a CBF which has been associated with the CBF handle by cbf_set_dictionary or creates a new empty CBF and associates it with handle, returning the new handle in *dictionary. ARGUMENTS handle CBF handle. dictionary Pointer to CBF handle of dictionary. dictionary_in CBF handle of dcitionary. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.3.67 cbf_convert_dictionary PROTOTYPE #include "cbf.h" int cbf_convert_dictionary (cbf_handle handle, cbf_handle dictionary ) DESCRIPTION cbf_convert_dictionary converts dictionary as a DDL1 or DDL2 dictionary to a CBF dictionary of category and item properties for handle, creating a new dictionary if none exists or layering the definitions in dictionary onto the existing dictionary of handle if one exists. If a CBF is read into handle after calling cbf_convert_dictionary, then the dictionary will be used for validation of the CBF as it is read. ARGUMENTS handle CBF handle. dictionary CBF handle of dictionary. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.3.68 cbf_find_tag, cbf_find_local_tag PROTOTYPE #include "cbf.h" int cbf_find_tag (cbf_handle handle, const char *tag) int cbf_find_local_tag (cbf_handle handle, const char *tag) DESCRIPTION cbf_find_tag searches all of the CBF handle for the CIF tag given by the string tag and makes it the current tag. The search does not include the dictionary, but does include save frames as well as categories. The string tag is the complete tag in either DDL1 or DDL2 format, starting with the leading underscore, not just a category or column. ARGUMENTS handle CBF handle. tag CIF tag. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.3.69 cbf_find_category_root, cbf_set_category_root, cbf_require_category_root PROTOTYPE #include "cbf.h" int cbf_find_category_root (cbf_handle handle, const char* categoryname, const char** categoryroot); int cbf_set_category_root (cbf_handle handle, const char* categoryname_in, const char*categoryroot); int cbf_require_category_root (cbf_handle handle, const char* categoryname, const char** categoryroot); DESCRIPTION cbf_find_category_root sets *categoryroot to the root category of which categoryname is an alias. cbf_set_category_root sets categoryname_in as an alias of categoryroot in the dictionary associated with handle, creating the dictionary if necessary. cbf_require_category_root sets *categoryroot to the root category of which categoryname is an alias, if there is one, or to the value of categoryname, if categoryname is not an alias. A returned categoryroot string must not be modified in any way. ARGUMENTS handle CBF handle. categoryname category name which may be an alias. categoryroot pointer to a returned category root name. categoryroot_in input category root name. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.3.70 cbf_find_tag_root, cbf_set_tag_root, cbf_require_tag_root PROTOTYPE #include "cbf.h" int cbf_find_tag_root (cbf_handle handle, const char* tagname, const char** tagroot); int cbf_set_tag_root (cbf_handle handle, const char* tagname, const char*tagroot_in); int cbf_require_tag_root (cbf_handle handle, const char* tagname, const char** tagroot); DESCRIPTION cbf_find_tag_root sets *tagroot to the root tag of which tagname is an alias. cbf_set_tag_root sets tagname as an alias of tagroot_in in the dictionary associated with handle, creating the dictionary if necessary. cbf_require_tag_root sets *tagroot to the root tag of which tagname is an alias, if there is one, or to the value of tagname, if tagname is not an alias. A returned tagroot string must not be modified in any way. ARGUMENTS handle CBF handle. tagname tag name which may be an alias. tagroot pointer to a returned tag root name. tagroot_in input tag root name. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.3.71 cbf_find_tag_category, cbf_set_tag_category PROTOTYPE #include "cbf.h" int cbf_find_tag_category (cbf_handle handle, const char* tagname, const char** categoryname); int cbf_set_tag_category (cbf_handle handle, const char* tagname, const char* categoryname_in); DESCRIPTION cbf_find_tag_category sets categoryname to the category associated with tagname in the dictionary associated with handle. cbf_set_tag_category upddates the dictionary associated with handle to indicated that tagname is in category categoryname_in. ARGUMENTS handle CBF handle. tagname tag name. categoryname pointer to a returned category name. categoryname_in input category name. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ---------------------------------------------------------------------- 2.4 High-level function prototypes 2.4.1 cbf_read_template PROTOTYPE #include "cbf_simple.h" int cbf_read_template (cbf_handle handle, FILE *file); DESCRIPTION cbf_read_template reads the CBF or CIF file file into the CBF object specified by handle and selects the first datablock as the current datablock. ARGUMENTS handle Pointer to a CBF handle. file Pointer to a file descriptor. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.2 cbf_get_diffrn_id, cbf_require_diffrn_id PROTOTYPE #include "cbf_simple.h" int cbf_get_diffrn_id (cbf_handle handle, const char **diffrn_id); int cbf_require_diffrn_id (cbf_handle handle, const char **diffrn_id, const char *default_id) DESCRIPTION cbf_get_diffrn_id sets *diffrn_id to point to the ASCII value of the "diffrn.id" entry. cbf_require_diffrn_id also sets *diffrn_id to point to the ASCII value of the "diffrn.id" entry, but, if the "diffrn.id" entry does not exist, it sets the value in the CBF and in*diffrn_id to the character string given by default_id, creating the category and column is necessary. The diffrn_id will be valid as long as the item exists and has not been set to a new value. The diffrn_id must not be modified by the program in any way. ARGUMENTS handle CBF handle. diffrn_id Pointer to the destination value pointer. default_id Character string default value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.3 cbf_set_diffrn_id PROTOTYPE #include "cbf_simple.h" int cbf_set_diffrn_id (cbf_handle handle, const char *diffrn_id); DESCRIPTION cbf_set_diffrn_id sets the "diffrn.id" entry of the current datablock to the ASCII value diffrn_id. This function also changes corresponding "diffrn_id" entries in the "diffrn_source", "diffrn_radiation", "diffrn_detector" and "diffrn_measurement" categories. ARGUMENTS handle CBF handle. diffrn_id ASCII value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.4 cbf_get_crystal_id PROTOTYPE #include "cbf_simple.h" int cbf_get_crystal_id (cbf_handle handle, const char **crystal_id); DESCRIPTION cbf_get_crystal_id sets *crystal_id to point to the ASCII value of the "diffrn.crystal_id" entry. If the value is not ASCII, the function returns CBF_BINARY. The value will be valid as long as the item exists and has not been set to a new value. The value must not be modified by the program in any way. ARGUMENTS handle CBF handle. crystal_id Pointer to the destination value pointer. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.5 cbf_set_crystal_id PROTOTYPE #include "cbf_simple.h" int cbf_set_crystal_id (cbf_handle handle, const char *crystal_id); DESCRIPTION cbf_set_crystal_id sets the "diffrn.crystal_id" entry to the ASCII value crystal_id. ARGUMENTS handle CBF handle. crystal_id ASCII value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.6 cbf_get_wavelength PROTOTYPE #include "cbf_simple.h" int cbf_get_wavelength (cbf_handle handle, double *wavelength); DESCRIPTION cbf_get_wavelength sets *wavelength to the current wavelength in AA. ARGUMENTS handle CBF handle. wavelength Pointer to the destination. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.7 cbf_set_wavelength PROTOTYPE #include "cbf_simple.h" int cbf_set_wavelength (cbf_handle handle, double wavelength); DESCRIPTION cbf_set_wavelength sets the current wavelength in AA to wavelength. ARGUMENTS handle CBF handle. wavelength Wavelength in AA. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.8 cbf_get_polarization PROTOTYPE #include "cbf_simple.h" int cbf_get_polarization (cbf_handle handle, double *polarizn_source_ratio, double *polarizn_source_norm); DESCRIPTION cbf_get_polarization sets *polarizn_source_ratio and *polarizn_source_norm to the corresponding source polarization parameters. Either destination pointer may be NULL. ARGUMENTS handle CBF handle. polarizn_source_ratio Pointer to the destination polarizn_source_ratio. polarizn_source_norm Pointer to the destination polarizn_source_norm. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.9 cbf_set_polarization PROTOTYPE #include "cbf_simple.h" int cbf_set_polarization (cbf_handle handle, double polarizn_source_ratio, double polarizn_source_norm); DESCRIPTION cbf_set_polarization sets the source polarization to the values specified by polarizn_source_ratio and polarizn_source_norm. ARGUMENTS handle CBF handle. polarizn_source_ratio New value of polarizn_source_ratio. polarizn_source_norm New value of polarizn_source_norm. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.10 cbf_get_divergence PROTOTYPE #include "cbf_simple.h" int cbf_get_divergence (cbf_handle handle, double *div_x_source, double *div_y_source, double *div_x_y_source); DESCRIPTION cbf_get_divergence sets *div_x_source, *div_y_source and *div_x_y_source to the corresponding source divergence parameters. Any of the destination pointers may be NULL. ARGUMENTS handle CBF handle. div_x_source Pointer to the destination div_x_source. div_y_source Pointer to the destination div_y_source. div_x_y_source Pointer to the destination div_x_y_source. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.11 cbf_ set_divergence PROTOTYPE #include "cbf_simple.h" int cbf_set_divergence (cbf_handle handle, double div_x_source, double div_y_source, double div_x_y_source); DESCRIPTION cbf_set_divergence sets the source divergence parameters to the values specified by div_x_source, div_y_source and div_x_y_source. ARGUMENTS handle CBF handle. div_x_source New value of div_x_source. div_y_source New value of div_y_source. div_x_y_source New value of div_x_y_source. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.12 cbf_count_elements PROTOTYPE #include "cbf_simple.h" int cbf_count_elements (cbf_handle handle, unsigned int *elements); DESCRIPTION cbf_count_elements sets *elements to the number of detector elements. ARGUMENTS handle CBF handle. elements Pointer to the destination count. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.13 cbf_get_element_id PROTOTYPE #include "cbf_simple.h" int cbf_get_element_id (cbf_handle handle, unsigned int element_number, const char **element_id); DESCRIPTION cbf_get_element_id sets *element_id to point to the ASCII value of the element_number'th "diffrn_data_frame.detector_element_id" entry, counting from 0. If the detector element does not exist, the function returns CBF_NOTFOUND. The element_id will be valid as long as the item exists and has not been set to a new value. The element_id must not be modified by the program in any way. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category. element_id Pointer to the destination. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.14 cbf_get_gain PROTOTYPE #include "cbf_simple.h" int cbf_get_gain (cbf_handle handle, unsigned int element_number, double *gain, double *gain_esd); DESCRIPTION cbf_get_gain sets *gain and *gain_esd to the corresponding gain parameters for element number element_number. Either of the destination pointers may be NULL. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category. gain Pointer to the destination gain. gain_esd Pointer to the destination gain_esd. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.15 cbf_ set_gain PROTOTYPE #include "cbf_simple.h" int cbf_set_gain (cbf_handle handle, unsigned int element_number, double gain, double gain_esd); DESCRIPTION cbf_set_gain sets the gain of element number element_number to the values specified by gain and gain_esd. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category. gain New gain value. gain_esd New gain_esd value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.16 cbf_get_overload PROTOTYPE #include "cbf_simple.h" int cbf_get_overload (cbf_handle handle, unsigned int element_number, double *overload); DESCRIPTION cbf_get_overload sets *overload to the overload value for element number element_number. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category. overload Pointer to the destination overload. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.17 cbf_ set_overload PROTOTYPE #include "cbf_simple.h" int cbf_set_overload (cbf_handle handle, unsigned int element_number, double overload); DESCRIPTION cbf_set_overload sets the overload value of element number element_number to overload. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category. overload New overload value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.18 cbf_get_integration_time PROTOTYPE #include "cbf_simple.h" int cbf_get_integration_time (cbf_handle handle, unsigned int reserved, double *time); DESCRIPTION cbf_get_integration_time sets *time to the integration time in seconds. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. time Pointer to the destination time. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.19 cbf_set_integration_time PROTOTYPE #include "cbf_simple.h" int cbf_set_integration_time (cbf_handle handle, unsigned int reserved, double time); DESCRIPTION cbf_set_integration_time sets the integration time in seconds to the value specified by time. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. time Integration time in seconds. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.20 cbf_get_timestamp PROTOTYPE #include "cbf_simple.h" int cbf_get_timestamp (cbf_handle handle, unsigned int reserved, double *time, int *timezone); DESCRIPTION cbf_get_timestamp sets *time to the collection timestamp in seconds since January 1 1970. *timezone is set to timezone difference from UTC in minutes. The parameter reserved is presently unused and should be set to 0. Either of the destination pointers may be NULL. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. time Pointer to the destination collection timestamp. timezone Pointer to the destination timezone difference. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.21 cbf_set_timestamp PROTOTYPE #include "cbf_simple.h" int cbf_set_timestamp (cbf_handle handle, unsigned int reserved, double time, int timezone, double precision); DESCRIPTION cbf_set_timestamp sets the collection timestamp in seconds since January 1 1970 to the value specified by time. The timezone difference from UTC in minutes is set to timezone. If no timezone is desired, timezone should be CBF_NOTIM EZONE. The parameter reserved is presently unused and should be set to 0. The precision of the new timestamp is specified by the value precision in seconds. If precision is 0, the saved timestamp is assumed accurate to 1 second. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. time Timestamp in seconds since January 1 1970. timezone Timezone difference from UTC in minutes or CBF_NOTIMEZONE. precision Timestamp precision in seconds. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.22 cbf_get_datestamp PROTOTYPE #include "cbf_simple.h" int cbf_get_datestamp (cbf_handle handle, unsigned int reserved, int *year, int *month, int *day, int *hour, int *minute, double *second, int *timezone); DESCRIPTION cbf_get_datestamp sets *year, *month, *day, *hour, *minute and *second to the corresponding values of the collection timestamp. *timezone is set to timezone difference from UTC in minutes. The parameter < i>reserved is presently unused and should be set to 0. Any of the destination pointers may be NULL. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. year Pointer to the destination timestamp year. month Pointer to the destination timestamp month (1-12). day Pointer to the destination timestamp day (1-31). hour Pointer to the destination timestamp hour (0-23). minute Pointer to the destination timestamp minute (0-59). second Pointer to the destination timestamp second (0-60.0). timezone Pointer to the destination timezone difference from UTC in minutes. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.23 cbf_set_datestamp PROTOTYPE #include "cbf_simple.h" int cbf_set_datestamp (cbf_handle handle, unsigned int reserved, int year, int month, int day, int hour, int minute, double second, int timezone, double precision); DESCRIPTION cbf_set_datestamp sets the collection timestamp in seconds since January 1 1970 to the value specified by time. The timezone difference from UTC in minutes is set to timezone. If no timezone is desired, timezone should be CBF_NOTIM EZONE. The parameter reserved is presently unused and should be set to 0. The precision of the new timestamp is specified by the value precision in seconds. If precision is 0, the saved timestamp is assumed accurate to 1 second. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. time Timestamp in seconds since January 1 1970. timezone Timezone difference from UTC in minutes or CBF_NOTIMEZONE. precision Timestamp precision in seconds. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.24 cbf_set_current_timestamp PROTOTYPE #include "cbf_simple.h" int cbf_set_current_timestamp (cbf_handle handle, unsigned int reserved, int timezone); DESCRIPTION cbf_set_current_timestamp sets the collection timestamp to the current time. The timezone difference from UTC in minutes is set to timezone. If no timezone is desired, timezone should be CBF_NOTIMEZONE. If no timezone is used, the timest amp will be UTC. The parameter reserved is presently unused and should be set to 0. The new timestamp will have a precision of 1 second. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. timezone Timezone difference from UTC in minutes or CBF_NOTIMEZONE. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.25 cbf_get_image_size, cbf_get_image_size_fs, cbf_get_image_size_sf, cbf_get_3d_image_size, cbf_get_3d_image_size_fs, cbf_get_3d_image_size_sf PROTOTYPE #include "cbf_simple.h" int cbf_get_image_size (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimslow, size_t *ndimfast); int cbf_get_image_size_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimfast, size_t *ndimslow); int cbf_get_image_size_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimslow, size_t *ndimfast); int cbf_get_3d_image_size (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimslow, size_t *ndimmid, size_t *ndimfast); int cbf_get_3d_image_size_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimfast, size_t *ndimmid, size_t *ndimslow); int cbf_get_3d_image_size_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimslow, size_t *ndimmid, size_t *ndimfast); DESCRIPTION cbf_get_image_size, cbf_get_image_size_fs and cbf_get_image_size_sf set *ndimslow and *ndimfast to the slow and fast dimensions of the image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimfast will be set to 1. If the array is 3-dimensional an error code will be returned. cbf_get_3d_image_size, cbf_get_3d_image_size_fs and cbf_get_3d_image_size_sf set *ndimslow, *ndimmid and *ndimfast to the slowest, next fastest and fastest dimensions, respectively, of the 3D image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimmid and *ndimfast will be set to 1. If the array is 2-dimensional *ndimslow and *ndimmid will be set as for a call to cbf_get_image_size and *ndimfast will be set to 1. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order Note that the ordering of dimensions is specified by values of the tag _array_structure_list.precedence with a precedence of 1 for the fastest dimension, 2 for the next slower, etc., which is opposite to the ordering of the dimension arguments for these functions, except for the ones with the _fs suffix.. Any of the destination pointers may be NULL. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category. ndimslow Pointer to the destination slowest dimension. ndimmid Pointer to the destination next faster dimension. ndimfast Pointer to the destination fastest dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.26 cbf_get_image, cbf_get_image_fs, cbf_get_image_sf, cbf_get_real_image, cbf_get_real_image_fs, cbf_get_real_image_sf, cbf_get_3d_image, cbf_get_3d_image_fs, cbf_get_3d_image_sf, cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf PROTOTYPE #include "cbf_simple.h" int cbf_get_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast); int cbf_get_image_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimfast, size_t ndimslow); int cbf_get_image_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast); int cbf_get_real_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimslow, size_t ndimfast); int cbf_get_real_image_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimfast, size_t ndimslow); int cbf_get_real_image_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimslow, size_t ndimfast); int cbf_get_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); int cbf_get_3d_image_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimfast, size_t ndimmid, size_t ndimslow); int cbf_get_3d_image_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); int cbf_get_real_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); int cbf_get_real_3d_image_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimfast, size_t ndimmid, size_t ndimslow); int cbf_get_real_3d_image_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); DESCRIPTION cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image array for element number element_number into an array. The array consists of ndimslow *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and cbf_get_real_image_sf read the image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. cbf_get_3d_image, cbf_get_3d_image_fs and cbf_get_3d_image_sf read the 3D image array for element number element_number into an array. The array consists of ndimslow *ndimmid *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order The structure of the array as a 1-, 2- or 3-dimensional array should agree with the structure of the array given in the ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1 both in the call and in the imgCIF data being processed. If the array is 2-dimensional and a 3D call is used, ndimslow and ndimmid should be the array dimensions and ndimfast should be set to 1 both in the call and in the imgCIF data being processed. If any element in the binary data canOt fit into the destination element, the destination is set the nearest possible value. If the value is not binary, the function returns CBF_ASCII. If the requested number of elements canOt be read, the function will read as many as it can and then return CBF_ENDOFDATA. Currently, the destination array must consist of chars, shorts or ints (signed or unsigned) for cbf_get_image, or IEEE doubles or floats for cbf_get_real_image. If elsize is not equal to sizeof (char), sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category. array Pointer to the destination array. elsize Size in bytes of each destination array element. elsigned Set to non-0 if the destination array elements are signed. ndimslow Slowest array dimension. ndimmid Next faster array dimension. ndimfast Fastest array dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.27 cbf_set_image, cbf_set_image_fs, cbf_set_image_sf, cbf_set_real_image, cbf_set_real_image_fs, cbf_set_real_image_sf, cbf_set_3d_image, cbf_set_3d_image, cbf_set_3d_image, cbf_set_real_3d_image, cbf_set_real_3d_image_fs, cbf_set_real_3d_image_sf PROTOTYPE #include "cbf_simple.h" int cbf_set_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast); int cbf_set_image_fs(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimfast, size_t ndimslow); int cbf_set_image_sf(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast); int cbf_set_real_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimslow, size_t ndimfast); int cbf_set_real_image_fs(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimfast, size_t ndimslow); int cbf_set_real_image_sf(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimslow, size_t ndimfast); int cbf_set_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); int cbf_set_3d_image_fs(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimfast, size_t ndimmid, size_t ndimslow); int cbf_set_3d_image_sf(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); int cbf_set_real_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); int cbf_set_real_3d_image_fs(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimfast, size_t ndimmid, size_t ndimslow); int cbf_set_real_3d_image_sf(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); DESCRIPTION cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-zero and unsigned otherwise. cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow IEEE double or float elements of elsize bytes each, starting at array. cbf_set_3d_image, cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_set_real_3d_image, cbf_set_real_3d_image_fs and cbf_set_real_3d_image_sf writes the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow IEEE double or float elements of elsize bytes each, starting at array. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the array is 2-dimensional and the 3D calls are used, ndimslow and ndimmid should be used for the array dimensions and ndimfast should be set to 1. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple "byte_offset" compression. CBF_NONE No compression. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned)for cbf_set_image, or IEEE doubles or floats for cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category. compression Compression type. array Pointer to the image array. elsize Size in bytes of each image array element. elsigned Set to non-0 if the image array elements are signed. ndimslow Slowest array dimension. ndimmid Second slowest array dimension. ndimfast Fastest array dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.28 cbf_get_axis_setting PROTOTYPE #include "cbf_simple.h" int cbf_get_axis_setting (cbf_handle handle, unsigned int reserved, const char *axis_id, double *start, double *increment); DESCRIPTION cbf_get_axis_setting sets *start and *increment to the corresponding values of the axis axis_id. Either of the destination pointers may be NULL. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. axis_id Axis id. start Pointer to the destination start value. increment Pointer to the destination increment value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.29 cbf_set_axis_setting PROTOTYPE #include "cbf_simple.h" int cbf_set_axis_setting (cbf_handle handle, unsigned int reserved, const char *axis_id, double start, double increment); DESCRIPTION cbf_set_axis_setting sets the starting and increment values of the axis axis_id to start and increment. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. axis_id Axis id. start Start value. increment Increment value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.30 cbf_construct_goniometer PROTOTYPE #include "cbf_simple.h" int cbf_construct_goniometer (cbf_handle handle, cbf_goniometer *goniometer); DESCRIPTION cbf_construct_goniometer constructs a goniometer object using the description in the CBF object handle and initialises the goniometer handle *goniometer. ARGUMENTS handle CBF handle. goniometer Pointer to the destination goniometer handle. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.31 cbf_free_goniometer PROTOTYPE #include "cbf_simple.h" int cbf_free_goniometer (cbf_goniometer goniometer); DESCRIPTION cbf_free_goniometer destroys the goniometer object specified by goniometer and frees all associated memory. ARGUMENTS goniometer Goniometer handle to free. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.32 cbf_get_rotation_axis PROTOTYPE #include "cbf_simple.h" int cbf_get_rotation_axis (cbf_goniometer goniometer, unsigned int reserved, double *vector1, double *vector2, double *vector3); DESCRIPTION cbf_get_rotation_axis sets *vector1, *vector2, and *vector3 to the 3 components of the goniometer rotation axis used for the exposure. Any of the destination pointers may be NULL. The parameter reserved is presently unused and should be set to 0. ARGUMENTS goniometer Goniometer handle. reserved Unused. Any value other than 0 is invalid. vector1 Pointer to the destination x component of the rotation axis. vector2 Pointer to the destination y component of the rotation axis. vector3 Pointer to the destination z component of the rotation axis. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.33 cbf_get_rotation_range PROTOTYPE #include "cbf_simple.h" int cbf_get_rotation_range (cbf_goniometer goniometer, unsigned int reserved, double *start, double *increment); DESCRIPTION cbf_get_rotation_range sets *start and *increment to the corresponding values of the goniometer rotation axis used for the exposure. Either of the destination pointers may be NULL. The parameter reserved is presently unused and should be set to 0. ARGUMENTS goniometer Goniometer handle. reserved Unused. Any value other than 0 is invalid. start Pointer to the destination start value. increment Pointer to the destination increment value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.34 cbf_rotate_vector PROTOTYPE #include "cbf_simple.h" int cbf_rotate_vector (cbf_goniometer goniometer, unsigned int reserved, double ratio, double initial1, double initial2, double initial3, double *final1, double *final2, double *final3); DESCRIPTION cbf_rotate_vector sets *final1, *final2, and *final3 to the 3 components of the of the vector (initial1, initial2, initial3) after reorientation by applying the goniometer rotations. The value ratio specif ies the goniometer setting and varies from 0.0 at the beginning of the exposure to 1.0 at the end, irrespective of the actual rotation range. Any of the destination pointers may be NULL. The parameter reserved is presently unused and should be set to 0. ARGUMENTS goniometer Goniometer handle. reserved Unused. Any value other than 0 is invalid. ratio Goniometer setting. 0 = beginning of exposure, 1 = end. initial1 x component of the initial vector. initial2 y component of the initial vector. initial3 z component of the initial vector. vector1 Pointer to the destination x component of the final vector. vector2 Pointer to the destination y component of the final vector. vector3 Pointer to the destination z component of the final vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.35 cbf_get_reciprocal PROTOTYPE #include "cbf_simple.h" int cbf_get_reciprocal (cbf_goniometer goniometer, unsigned int reserved, double ratio, double wavelength, double real1, double real2, double real3, double *reciprocal1, double *reciprocal2, double *reciprocal3); DESCRIPTION cbf_get_reciprocal sets *reciprocal1, * reciprocal2, and * reciprocal3 to the 3 components of the of the reciprocal-space vector corresponding to the real-space vector (real1, real2, real3). The reciprocal-space vector is oriented to correspond to the goniometer setting with all axes at 0. The value wavelength is the wavlength in AA and the value ratio specifies the current goniometer setting and varies from 0.0 at the beginning of the exposur e to 1.0 at the end, irrespective of the actual rotation range. Any of the destination pointers may be NULL. The parameter reserved is presently unused and should be set to 0. ARGUMENTS goniometer Goniometer handle. reserved Unused. Any value other than 0 is invalid. ratio Goniometer setting. 0 = beginning of exposure, 1 = end. wavelength Wavelength in AA. real1 x component of the real-space vector. real2 y component of the real-space vector. real3 z component of the real-space vector. reciprocal1 Pointer to the destination x component of the reciprocal-space vector. reciprocal2 Pointer to the destination y component of the reciprocal-space vector. reciprocal3 Pointer to the destination z component of the reciprocal-space vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.36 cbf_construct_detector, cbf_construct_reference_detector, cbf_require_reference_detector PROTOTYPE #include "cbf_simple.h" int cbf_construct_detector (cbf_handle handle, cbf_detector *detector, unsigned int element_number); int cbf_construct_reference_detector (cbf_handle handle, cbf_detector *detector, unsigned int element_number); int cbf_require_reference_detector (cbf_handle handle, cbf_detector *detector, unsigned int element_number); DESCRIPTION cbf_construct_detector constructs a detector object for detector element number element_number using the description in the CBF object handle and initialises the detector handle *detector. cbf_construct_reference_detector constructs a detector object for detector element number element_number using the description in the CBF object handle and initialises the detector handle *detector using the reference settings of the axes. cbf_require_reference_detector is similar, but try to force the creations of missing intermediate categories needed to construct a detector object. ARGUMENTS handle CBF handle. detector Pointer to the destination detector handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.37 cbf_free_detector PROTOTYPE #include "cbf_simple.h" int cbf_free_detector (cbf_detector detector); DESCRIPTION cbf_free_detector destroys the detector object specified by detector and frees all associated memory. ARGUMENTS detector Detector handle to free. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.38 cbf_get_beam_center, cbf_get_beam_center_fs, cbf_get_beam_center_sf, cbf_set_beam_center, cbf_set_beam_center_fs, cbf_set_beam_center_sf, set_reference_beam_center, set_reference_beam_center_fs, set_reference_beam_center_fs PROTOTYPE #include "cbf_simple.h" int cbf_get_beam_center (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast); int cbf_get_beam_center_fs (cbf_detector detector, double *indexfast, double *indexslow, double *centerfast, double *centerslow); int cbf_get_beam_center_sf (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast); int cbf_set_beam_center (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast); int cbf_set_beam_center_fs (cbf_detector detector, double *indexfast, double *indexslow, double *centerfast, double *centerslow); int cbf_set_beam_center_sf (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast); int cbf_set_reference_beam_center (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast); int cbf_set_reference_beam_center_fs (cbf_detector detector, double *indexfast, double *indexslow, double *centerfast, double *centerslow); int cbf_set_reference_beam_center_sf (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast); DESCRIPTION cbf_get_beam_center sets *centerfast and *centerslow to the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector and *indexfast and *indexslow to the corresponding indices. cbf_set_beam_center sets the offsets in the axis category for the detector element axis with precedence 1 to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given *indexfast and *indexslow. cbf_set_reference_beam_center sets the displacments in the array_structure_list_axis category to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given by *indexfast and *indexslow. In order to achieve consistent results, a reference detector should be used for detector to have all axes at their reference settings. Note that the precedence 1 axis is the fastest axis, so that *centerfast and *indexfast are the fast axis components of the center and *centerslow and *indexslow are the slow axis components of the center. The _fs calls give the displacments in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the displacements in slow-to-fast order Any of the destination pointers may be NULL for getting the beam center. For setting the beam axis, either the indices of the center must not be NULL. The indices are non-negative for beam centers within the detector surface, but the center for an axis with a negative increment will be negative for a beam center within the detector surface. For cbf_set_beam_center if the diffrn_data_frame category exists with a row for the corresponding element id, the values will be set for _diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in millimetres and the value of _diffrn_data_frame.center_units will be set to 'mm'. For cbf_set_reference_beam_center if the diffrn_detector_element category exists with a row for the corresponding element id, the values will be set for _diffrn_detector_element.reference_center_fast and _diffrn_detector_element.reference_center_slow in millimetres and the value of _diffrn_detector_element.reference_units will be set to 'mm'. ARGUMENTS detector Detector handle. indexfast Pointer to the destination fast index. indexslow Pointer to the destination slow index. centerfast Pointer to the destination displacement along the fast axis. centerslow Pointer to the destination displacement along the slow axis. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.39 cbf_get_detector_distance PROTOTYPE #include "cbf_simple.h" int cbf_get_detector_distance (cbf_detector detector, double *distance); DESCRIPTION cbf_get_detector_distance sets *distance to the nearest distance from the sample position to the detector plane. ARGUMENTS detector Detector handle. distance Pointer to the destination distance. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.40 cbf_get_detector_normal PROTOTYPE #include "cbf_simple.h" int cbf_get_detector_normal (cbf_detector detector, double *normal1, double *normal2, double *normal3); DESCRIPTION cbf_get_detector_normal sets *normal1, *normal2, and *normal3 to the 3 components of the of the normal vector to the detector plane. The vector is normalized. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. normal1 Pointer to the destination x component of the normal vector. normal2 Pointer to the destination y component of the normal vector. normal3 Pointer to the destination z component of the normal vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.41 cbf_get_detector_axis_slow, cbf_get_detector_axis_slow, cbf_get_detector_axes, cbf_get_detector_axes_fs, cbf_get_detector_axes_sf PROTOTYPE #include "cbf_simple.h" int cbf_get_detector_axis_slow (cbf_detector detector, double *slowaxis1, double *slowaxis2, double *slowaxis3); int cbf_get_detector_axis_fast (cbf_detector detector, double *fastaxis1, double *fastaxis2, double *fastaxis3); int cbf_get_detector_axes (cbf_detector detector, double *slowaxis1, double *slowaxis2, double *slowaxis3, double *fastaxis1, double *fastaxis2, double *fastaxis3); int cbf_get_detector_axes_fs (cbf_detector detector, double *fastaxis1, double *fastaxis2, double *fastaxis3, double *slowaxis1, double *slowaxis2, double *slowaxis3); int cbf_get_detector_axes_sf (cbf_detector detector, double *slowaxis1, double *slowaxis2, double *slowaxis3, double *fastaxis1, double *fastaxis2, double *fastaxis3); DESCRIPTION cbf_get_detector_axis_slow sets *slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the slow axis of the specified detector at the current settings of all axes. cbf_get_detector_axis_slow sets *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 components of the fast axis of the specified detector at the current settings of all axes. cbf_get_detector_axes, cbf_get_detector_axes_fs and int cbf_get_detector_axes_sf set *slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the slow axis and *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 components of the fast axis of the specified detector at the current settings of all axes. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. slowaxis1 Pointer to the destination x component of the slow axis vector. slowaxis2 Pointer to the destination y component of the slow axis vector. slowaxis3 Pointer to the destination z component of the slow axis vector. fastaxis1 Pointer to the destination x component of the fast axis vector. fastaxis2 Pointer to the destination y component of the fast axis vector. fastaxis3 Pointer to the destination z component of the fast axis vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.42 cbf_get_pixel_coordinates, cbf_get_pixel_coordinates_fs, cbf_get_pixel_coordinates_sf PROTOTYPE #include "cbf_simple.h" int cbf_get_pixel_coordinates (cbf_detector detector, double indexslow, double indexfast, double *coordinate1, double *coordinate2, double *coordinate3); int cbf_get_pixel_coordinates_fs (cbf_detector detector, double indexfast, double indexslow, double *coordinate1, double *coordinate2, double *coordinate3); int cbf_get_pixel_coordinates_sf (cbf_detector detector, double indexslow, double indexfast, double *coordinate1, double *coordinate2, double *coordinate3); DESCRIPTION cbf_get_pixel_coordinates, cbf_get_pixel_coordinates_fs and cbf_get_pixel_coordinates_sf ses *coordinate1, *coordinate2, and *coordinate3 to the vector position of pixel (indexfast, indexslow) on the detector surface. If indexslow and indexfast are integers then the coordinates correspond to the center of a pixel. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. indexslow Slow index. indexfast Fast index. coordinate1 Pointer to the destination x component. coordinate2 Pointer to the destination y component. coordinate3 Pointer to the destination z component. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.43 cbf_get_pixel_normal, cbf_get_pixel_normal_fs, cbf_get_pixel_normal_sf PROTOTYPE #include "cbf_simple.h" int cbf_get_pixel_normal (cbf_detector detector, double indexslow, double indexfast, double *normal1, double *normal2, double *normal3); int cbf_get_pixel_normal_fs (cbf_detector detector, double indexfast, double indexslow, double *normal1, double *normal2, double *normal3); int cbf_get_pixel_normal (cbf_detector detector, double indexslow, double indexfast, double *normal1, double *normal2, double *normal3); DESCRIPTION cbf_get_detector_normal, cbf_get_pixel_normal_fs and cbf_get_pixel_normal_sf set *normal1, *normal2, and *normal3 to the 3 components of the of the normal vector to the pixel at (indexfast, indexslow). The vector is normalized. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. indexslow Slow index. indexfast Fast index. normal1 Pointer to the destination x component of the normal vector. normal2 Pointer to the destination y component of the normal vector. normal3 Pointer to the destination z component of the normal vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.44 cbf_get_pixel_area, cbf_get_pixel_area_fs, cbf_get_pixel_area_sf PROTOTYPE #include "cbf_simple.h" int cbf_get_pixel_area (cbf_detector detector, double indexslow, double indexfast, double *area, double *projected_area); int cbf_get_pixel_area_fs(cbf_detector detector, double indexfast, double indexslow, double *area, double *projected_area); int cbf_get_pixel_area_sf(cbf_detector detector, double indexslow, double indexfast, double *area, double *projected_area); DESCRIPTION cbf_get_pixel_area, cbf_get_pixel_area_fs and cbf_get_pixel_area_sf set *area to the area of the pixel at (indexfast, indexslow) on the detector surface and *projected_area to the apparent area of the pixel as viewed from the sample position, with indexslow being the slow axis and indexfast being the fast axis. Either of the destination pointers may be NULL. ARGUMENTS detector Detector handle. indexfast Fast index. indexslow Slow index. area Pointer to the destination area in mm2. projected_area Pointer to the destination apparent area in mm2. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.45 cbf_get_pixel_size, cbf_get_pixel_size_fs, cbf_get_pixel_size_sf PROTOTYPE #include "cbf_simple.h" int cbf_get_pixel_size (cbf_handle handle, unsigned int element_number, int axis_number, double *psize); int cbf_get_pixel_size_fs(cbf_handle handle, unsigned int element_number, int axis_number, double *psize); int cbf_get_pixel_size_sf(cbf_handle handle, unsigned int element_number, int axis_number, double *psize); DESCRIPTION cbf_get_pixel_size and cbf_get_pixel_size_sf set *psize to point to the double value in millimeters of the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the slowest axis. cbf_get_pixel_size_fs sets *psize to point to the double value in millimeters of the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the fastest axis. If a negative axis number is given, the order of axes is reversed, so that -1 specifies the slowest axis for cbf_get_pixel_size_fs and the fastest axis for cbf_get_pixel_size_sf. If the pixel size is not given explcitly in the "array_element_size" category, the function returns CBF_NOTFOUND. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category. axis_number The number of the axis, starting from 1 for the fastest for cbf_get_pixel_size and cbf_get_pixel_size_fs and the slowest for cbf_get_pixel_size_sf. psize Pointer to the destination pixel size. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.46 cbf_set_pixel_size, cbf_set_pixel_size_fs, cbf_set_pixel_size_sf PROTOTYPE #include "cbf_simple.h" int cbf_set_pixel_size (cbf_handle handle, unsigned int element_number, int axis_number, double psize); int cbf_set_pixel_size_fs(cbf_handle handle, unsigned int element_number, int axis_number, double psize); int cbf_set_pixel_size_sf(cbf_handle handle, unsigned int element_number, int axis_number, double psize); DESCRIPTION cbf_set_pixel_size and cbf_set_pixel_size_sf set the item in the "e;size"e; column of the "array_structure_list" category at the row which matches axis axis_number of the detector element element_number converting the double pixel size psize from meters to millimeters in storing it in the "size" column for the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the slowest axis. cbf_set_pixel_size_fs sets the item in the "e;size"e; column of the "array_structure_list" category at the row which matches axis axis_number of the detector element element_number converting the double pixel size psize from meters to millimeters in storing it in the "size" column for the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the fastest axis. If a negative axis number is given, the order of axes is reversed, so that -1 specifies the slowest axis for cbf_get_pixel_size_fs and the fastest axis for cbf_get_pixel_size_sf. If the "array_structure_list" category does not already exist, it is created. If the appropriate row in the "array_structure_list" catgeory does not already exist, it is created. If the pixel size is not given explcitly in the "array_element_size category", the function returns CBF_NOTFOUND. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category. axis_number The number of the axis, fastest first, starting from 1. psize The pixel size in millimeters. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.47 cbf_get_inferred_pixel_size, cbf_get_inferred_pixel_size_fs, cbf_get_inferred_pixel_size_sf PROTOTYPE #include "cbf_simple.h" int cbf_get_inferred_pixel_size (cbf_detector detector, int axis_number, double *psize); int cbf_get_inferred_pixel_size_fs(cbf_detector detector, int axis_number, double *psize); int cbf_get_inferred_pixel_size_sf(cbf_detector detector, int axis_number, double *psize); DESCRIPTION cbf_get_inferred_pixel_size, cbf_get_inferred_pixel_size_sf set *psize to point to the double value in millimeters of the pixel size for the axis axis_number value. The slow index is treated as axis 1 and the next faster index is treated as axis 2. cbf_get_inferred_pixel_size_fs sets *psize to point to the double value in millimeters of the pixel size for the axis axis_number value. The fast index is treated as axis 1 and the next slower index is treated as axis 2. If the axis number is negative, the axes are used in the reverse order so that an axis_number of -1 indicates the fast axes in a call to cbf_get_inferred_pixel_size or cbf_get_inferred_pixel_size_sf and indicates the fast axis in a call to cbf_get_inferred_pixel_size_fs. ARGUMENTS detector Detector handle. axis_number The number of the axis. area Pointer to the destination pizel size in mm. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.48 cbf_get_unit_cell PROTOTYPE #include "cbf_simple.h" int cbf_get_unit_cell (cbf_handle handle, double cell[6], double cell_esd[6] ); DESCRIPTION cbf_get_unit_cell sets cell[0:2] to the double values of the cell edge lengths a, b and c in AAngstroms, cell[3:5] to the double values of the cell angles a, b and g in degrees, cell_esd[0:2] to the double values of the estimated strandard deviations of the cell edge lengths a, b and c in AAngstroms, cell_esd[3:5] to the double values of the estimated standard deviations of the the cell angles a, b and g in degrees. The values returned are retrieved from the first row of the "cell" category. The value of "_cell.entry_id" is ignored. cell or cell_esd may be NULL. If cell is NULL, the cell parameters are not retrieved. If cell_esd is NULL, the cell parameter esds are not retrieved. If the "cell" category is present, but some of the values are missing, zeros are returned for the missing values. ARGUMENTS handle CBF handle. cell Pointer to the destination array of 6 doubles for the cell parameters. cell_esd Pointer to the destination array of 6 doubles for the cell parameter esds. RETURN VALUE Returns an error code on failure or 0 for success. No errors is returned for missing values if the "cell" category exists. SEE ALSO 2.4.49 cbf_set_unit_cell 2.4.50 cbf_get_reciprocal_cell 2.4.51 cbf_set_reciprocal_cell 2.4.52 cbf_compute_cell_volume 2.4.53 cbf_compute_reciprocal_cell ---------------------------------------------------------------------- 2.4.49 cbf_set_unit_cell PROTOTYPE #include "cbf_simple.h" int cbf_set_unit_cell (cbf_handle handle, double cell[6], double cell_esd[6] ); DESCRIPTION cbf_set_unit_cell sets the cell parameters to the double values given in cell[0:2] for the cell edge lengths a, b and c in AAngstroms, the double values given in cell[3:5] for the cell angles a, b and g in degrees, the double values given in cell_esd[0:2] for the estimated strandard deviations of the cell edge lengths a, b and c in AAngstroms, and the double values given in cell_esd[3:5] for the estimated standard deviations of the the cell angles a, b and g in degrees. The values are placed in the first row of the "cell" category. If no value has been given for "_cell.entry_id", it is set to the value of the "diffrn.id" entry of the current data block. cell or cell_esd may be NULL. If cell is NULL, the cell parameters are not set. If cell_esd is NULL, the cell parameter esds are not set. If the "cell" category is not present, it is created. If any of the necessary columns are not present, they are created. ARGUMENTS handle CBF handle. cell Pointer to the array of 6 doubles for the cell parameters. cell_esd Pointer to the array of 6 doubles for the cell parameter esds. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.4.48 cbf_get_unit_cell 2.4.50 cbf_get_reciprocal_cell 2.4.51 cbf_set_reciprocal_cell 2.4.52 cbf_compute_cell_volume 2.4.53 cbf_compute_reciprocal_cell ---------------------------------------------------------------------- SEE ALSO 2.4.50 cbf_get_reciprocal_cell PROTOTYPE #include "cbf_simple.h" int cbf_get_reciprocal_cell (cbf_handle handle, double cell[6], double cell_esd[6] ); DESCRIPTION cbf_get_reciprocal_cell sets cell[0:2] to the double values of the reciprocal cell edge lengths a*, b* and c* in AAngstroms-1, cell[3:5] to the double values of the reciprocal cell angles a*, b* and g* in degrees, cell_esd[0:2] to the double values of the estimated strandard deviations of the reciprocal cell edge lengths a*, b* and c* in AAngstroms-1, cell_esd[3:5] to the double values of the estimated standard deviations of the the reciprocal cell angles a*, b* and g* in degrees. The values returned are retrieved from the first row of the "cell" category. The value of "_cell.entry_id" is ignored. cell or cell_esd may be NULL. If cell is NULL, the reciprocal cell parameters are not retrieved. If cell_esd is NULL, the reciprocal cell parameter esds are not retrieved. If the "cell" category is present, but some of the values are missing, zeros are returned for the missing values. ARGUMENTS handle CBF handle. cell Pointer to the destination array of 6 doubles for the reciprocal cell parameters. cell_esd Pointer to the destination array of 6 doubles for the reciprocal cell parameter esds. RETURN VALUE Returns an error code on failure or 0 for success. No errors is returned for missing values if the "cell" category exists. SEE ALSO 2.4.48 cbf_get_unit_cell 2.4.49 cbf_set_unit_cell 2.4.51 cbf_set_reciprocal_cell 2.4.52 cbf_compute_cell_volume 2.4.53 cbf_compute_reciprocal_cell ---------------------------------------------------------------------- 2.4.51 cbf_set_reciprocal_cell PROTOTYPE #include "cbf_simple.h" int cbf_set_reciprocal_cell (cbf_handle handle, double cell[6], double cell_esd[6] ); DESCRIPTION cbf_set_reciprocal_cell sets the reciprocal cell parameters to the double values given in cell[0:2] for the reciprocal cell edge lengths a*, b* and c* in AAngstroms-1, the double values given in cell[3:5] for the reciprocal cell angles a*, b* and g* in degrees, the double values given in cell_esd[0:2] for the estimated strandard deviations of the reciprocal cell edge lengths a*, b* and c* in AAngstroms, and the double values given in cell_esd[3:5] for the estimated standard deviations of the reciprocal cell angles a*, b* and g* in degrees. The values are placed in the first row of the "cell" category. If no value has been given for "_cell.entry_id", it is set to the value of the "diffrn.id" entry of the current data block. cell or cell_esd may be NULL. If cell is NULL, the reciprocal cell parameters are not set. If cell_esd is NULL, the reciprocal cell parameter esds are not set. If the "cell" category is not present, it is created. If any of the necessary columns are not present, they are created. ARGUMENTS handle CBF handle. cell Pointer to the array of 6 doubles for the reciprocal cell parameters. cell_esd Pointer to the array of 6 doubles for the reciprocal cell parameter esds. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.4.48 cbf_get_unit_cell 2.4.49 cbf_set_unit_cell 2.4.50 cbf_get_reciprocal_cell 2.4.52 cbf_compute_cell_volume 2.4.53 cbf_compute_reciprocal_cell ---------------------------------------------------------------------- 2.4.52 cbf_compute_cell_volume PROTOTYPE #include "cbf_simple.h" int cbf_compute_cell_volume ( double cell[6], double *volume ); DESCRIPTION cbf_compute_cell_volume sets *volume to point to the volume of the unit cell computed from the double values in cell[0:2] for the cell edge lengths a, b and c in AAngstroms and the double values given in cell[3:5] for the cell angles a, b and g in degrees. ARGUMENTS cell Pointer to the array of 6 doubles giving the cell parameters. volume Pointer to the doubles for cell volume. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.4.48 cbf_get_unit_cell 2.4.49 cbf_set_unit_cell 2.4.50 cbf_get_reciprocal_cell 2.4.51 cbf_set_reciprocal_cell 2.4.53 cbf_compute_reciprocal_cell ---------------------------------------------------------------------- 2.4.53 cbf_compute_reciprocal_cell PROTOTYPE #include "cbf_simple.h" int cbf_compute_reciprocal_cell ( double cell[6], double rcell[6] ); DESCRIPTION cbf_compute_reciprocal_cell sets rcell to point to the array of reciprocal cell parameters computed from the double values cell[0:2] giving the cell edge lengths a, b and c in AAngstroms, and the double values cell[3:5] giving the cell angles a, b and g in degrees. The double values rcell[0:2] will be set to the reciprocal cell lengths a*, b* and c* in AAngstroms-1 and the double values rcell[3:5] will be set to the reciprocal cell angles a*, b* and g* in degrees. ARGUMENTS cell Pointer to the array of 6 doubles giving the cell parameters. rcell Pointer to the destination array of 6 doubles giving the reciprocal cell parameters. volume Pointer to the doubles for cell volume. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO 2.4.48 cbf_get_unit_cell 2.4.49 cbf_set_unit_cell 2.4.50 cbf_get_reciprocal_cell 2.4.51 cbf_set_reciprocal_cell 2.4.52 cbf_compute_cell_volume ---------------------------------------------------------------------- 2.4.54 cbf_get_orientation_matrix, cbf_set_orientation_matrix PROTOTYPE #include "cbf_simple.h" int cbf_get_orientation_matrix (cbf_handle handle, double ub_matrix[9]); int cbf_set_orientation_matrix (cbf_handle handle, double ub_matrix[9]); DESCRIPTION cbf_get_orientation_matrix sets ub_matrix to point to the array of orientation matrix entries in the "diffrn" category in the order of columns: "UB[1][1]" "UB[1][2]" "UB[1][3]" "UB[2][1]" "UB[2][2]" "UB[2][3]" "UB[3][1]" "UB[3][2]" "UB[3][3]" cbf_set_orientation_matrix sets the values in the "diffrn" category to the values pointed to by ub_matrix. ARGUMENTS handle CBF handle. ubmatric Source or destination array of 9 doubles giving the orientation matrix parameters. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.4.55 cbf_get_bin_sizes, cbf_set_bin_sizes PROTOTYPE #include "cbf_simple.h" int cbf_get_bin_sizes(cbf_handle handle, unsigned int element_number, double * slowbinsize, double * fastbinsize); int cbf_set_bin_sizes(cbf_handle handle, unsigned int element_number, double slowbinsize_in,double fastbinsize_in); DESCRIPTION cbf_get_bin_sizes sets slowbinsize to point to the value of the number of pixels composing one array element in the dimension that changes at the second-fastest rate and fastbinsize to point to the value of the number of pixels composing one array element in the dimension that changes at the fastest rate for the dectector element with the ordinal element_number. cbf_set_bin_sizes sets the the pixel bin sizes in the "array_intensities" category to the values of slowbinsize_in for the number of pixels composing one array element in the dimension that changes at the second-fastest rate and fastbinsize_in for the number of pixels composing one array element in the dimension that changes at the fastest rate for the dectector element with the ordinal element_number. In order to allow for software binning involving fractions of pixels, the bin sizes are doubles rather than ints. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame" category. slowbinsize Pointer to the returned number of pixels composing one array element in the dimension that changes at the second-fastest rate. fastbinsize Pointer to the returned number of pixels composing one array element in the dimension that changes at the fastest rate. slowbinsize_in The number of pixels composing one array element in the dimension that changes at the second-fastest rate. fastbinsize_in The number of pixels composing one array element in the dimension that changes at the fastest rate. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- 2.5 F90 function interfaces At the suggestion of W. Kabsch, Fortran 90/95 routines have been added to CBFlib. As of this writing code has been written to allow the reading of CBF_BYTE_OFFSET, CBF_PACKED and CBF_PACKED_V2 binary images. This code has been gather into FCBlib (Fortran Crystallographic Binary library) as lib/libfcb. In general, most of the FCBlib functions return 0 for normal completion and a non-zero value in case of an error. In a few cases, such as FCB_ATOL_WCNT and FCB_NBLEN_ARRAY in order to conform to the conventions for commonly used C-equivalent functions, the function return is the value being computed. For each function, an interface is given to be included in the declarations of your Fortran 90/95 code. Some functions in FCBlIB are not intended for external use and are subject to change: FCB_UPDATE_JPA_POINTERS_I2, FCB_UPDATE_JPA_POINTERS_I4, FCB_UPDATE_JPA_POINTERS_3D_I2, FCB_UPDATE_JPA_POINTERS_3D_I4 and CNT2PIX. These names should not be used for user routines. The functions involving reading of a CBF have been done strictly in Fortran without the use of C code. This has required some compromises and the use of direct access I/O. Rather than putting the buffer and its control variables into COMMON these are passed as local arguments to make the routines inherently 'threadsafe' in a parallel programming environment. Note also, that a reading error could occur for the last record if it does not fill a full block. The code is written to recover from end-of-record and end-of-file errors, if possible. On many modern system, no special action is required, but on some systems it may be necessary to make use of the padding between the end of binary data and the terminal MIME boundary marker in binary sections. To ensure maximum portability of CBF files, a padding of 4095 bytes is recommended. Existing files without padding can be converted to files with padding by use of the new -p4 option for cif2cbf. 2.5.1 FCB_ATOL_WCNT INTERFACE INTEGER(8) FUNCTION FCB_ATOL_WCNT(ARRAY, N, CNT) INTEGER(1),INTENT(IN):: ARRAY(N) INTEGER, INTENT(IN):: N INTEGER, INTENT(OUT):: CNT END FUNCTION END INTERFACE FCB_ATOL_WCNT converts INTEGER(1) bytes in ARRAY of N bytes to an INTEGER(8) value returned as the function value. The number of bytes of ARRAY actually used before encountering a character not used to form the number is returned in CNT. The scan stops at the first byte in ARRAY that cannot be properly parsed as part of the integer result. ARGUMENTS ARRAY The array of INTEGER(1) bytes to be scanned N The INTEGER size of ARRAY CNT The INTEGER size of the portion of ARRAY scanned. RETURN VALUE Returns the INTEGER(8) value derived from the characters ARRAY(1:CNT) scanned. ---------------------------------------------------------------------- 2.5.2 FCB_CI_STRNCMPARR INTERFACE INTEGER FUNCTION FCB_CI_STRNCMPARR(STRING>, ARRAY, N, LIMIT) CHARACTER(LEN=*),INTENT(IN):: STRING> INTEGER, INTENT(IN):: N, LIMIT INTEGER(1), INTENT(IN):: ARRAY(N) END FUNCTION END INTERFACE The function FCB_CI_STRNCMPARR compares up to LIMIT characters of character string STRING and INTEGER(1) byte array ARRAY of dimension N in a case-insensitive manner, returning 0 for a match. ARGUMENTS STRING A character string ARRAY The array of INTEGER(1) bytes to be scanned N The INTEGER size of ARRAY N The INTEGER limit on the number of characters to consider in the comparison RETURN VALUE Returns 0 if the string and array match, a non-zero value otherwise. ---------------------------------------------------------------------- 2.5.3 FCB_EXIT_BINARY INTERFACE INTEGER FUNCTION FCB_EXIT_BINARY(TAPIN,LAST_CHAR,FCB_BYTES_IN_REC,& BYTE_IN_FILE,REC_IN_FILE,BUFFER, & PADDING ) INTEGER, INTENT(IN) :: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: BYTE_IN_FILE,REC_IN_FILE INTEGER(1),INTENT(INOUT):: LAST_CHAR,BUFFER(FCB_BYTES_IN_REC) INTEGER(8),INTENT(IN) :: PADDING END FUNCTION END INTERFACE The function FCB_EXIT_BINARY is used to skip from the end of a binary section past any padding to the end of the text section that encloses the binary section. The values of the arguments must be consistent with those in the last call to FCB_NEXT_BINARY ARGUMENTS TAPIN The INTEGER Fortran device unit number assigned to image file. LAST_CHAR The last character (as an INTEGER(1) byte) read. FCB_BYTES_IN_REC The INTEGER number of bytes in a record. BYTE_IN_FILE The INTEGER byte (counting from 1) of the byte to read. REC_IN_FILE The INTEGER record number (counting from 1) of next record to read. BUFFER The INTEGER(1) array of length FCB_BYTES_IN_REC to hold the appropriate record from TAPIN PADDING The INTEGER(8) number of bytes of padding after the binary data and before the closing MIME boundary. RETURN VALUE Returns 0 if the function is successful. Returns whatever non-zero error value is reported by FCB_READ_LINE if a necessary next line cannot be read. SEE ALSO 2.5.5 FCB_NEXT_BINARY 2.5.6 FCB_OPEN_CIFIN 2.5.9 FCB_READ_BYTE 2.5.11 FCB_READ_LINE ---------------------------------------------------------------------- 2.5.4 FCB_NBLEN_ARRAY INTERFACE INTEGER FUNCTION FCB_NBLEN_ARRAY(ARRAY, ARRAYLEN) INTEGER, INTENT(IN):: ARRAYLEN INTEGER(1), INTENT(IN):: ARRAY(ARRAYLEN) END FUNCTION END INTERFACE The function FCB_NBLEN_ARRAY returns the trimmed length of the INTEGER(1) byte array ARRAY of dimension ARRAYLEN after removal of trailing ASCII blanks, horizontal tabs (Z'09'), newlines (Z'0A') and carriage returns (Z'0D'). The resulting length may be zero. The INTEGER trimmed length is returned as the function value. ARGUMENTS ARRAY The array of bytes for which the trimmed length is required. ARRAYLEN The dimension of the array of bytes to be scanned. RETURN VALUE Returns the trimmed length of the array ARRAY. ---------------------------------------------------------------------- 2.5.5 FCB_NEXT_BINARY INTERFACE INTEGER FUNCTION FCB_NEXT_BINARY(TAPIN,LAST_CHAR,FCB_BYTES_IN_REC,& BYTE_IN_FILE,REC_IN_FILE,BUFFER, & ENCODING,SIZE,ID,DIGEST, & COMPRESSION,BITS,VORZEICHEN,REELL,& BYTEORDER,DIMOVER,DIM1,DIM2,DIM3, & PADDING ) INTEGER, INTENT(IN) :: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: BYTE_IN_FILE,REC_IN_FILE INTEGER(1),INTENT(INOUT):: LAST_CHAR,BUFFER(FCB_BYTES_IN_REC) INTEGER, INTENT(OUT) :: ENCODING INTEGER, INTENT(OUT) :: SIZE !Binary size INTEGER, INTENT(OUT) :: ID !Binary ID CHARACTER(len=*),INTENT(OUT):: DIGEST !Message digest INTEGER, INTENT(OUT):: COMPRESSION INTEGER, INTENT(OUT):: BITS,VORZEICHEN,REELL CHARACTER(len=*),INTENT(OUT):: BYTEORDER INTEGER(8), INTENT(OUT):: DIMOVER INTEGER(8), INTENT(OUT):: DIM1 INTEGER(8), INTENT(OUT):: DIM2 INTEGER(8), INTENT(OUT):: DIM3 INTEGER(8), INTENT(OUT):: PADDING END FUNCTION END INTERFACE The function FCB_NEXT_BINARY skips to the start of the next binary section in the image file on unit TAPIN leaving the file positioned for a subsequent read of the image data. The skip may prior to the text field that contains the binary section. When the text filed is reached, it will be scanned for a MIME boundary marker, and, if it is found the subsequence MIME headers will be used to populate the arguments ENCODING, SIZE, ID, DIGEST, COMPRESSION, BITS, VORZEICHEN,REELL, BYTEORDER, DIMOVER, DIM1, DIM2,DIM3, PADDING. The value returned in ENCODING is taken from the MIME header Content-Transfer-Encoding as an INTEGER. It is returned as 0 if not specified. The reported value is one of the integer values ENC_NONE (Z'0001') for BINARY encoding, ENC_BASE64 (Z'0002') for BASE64 encoding, ENC_BASE32K (Z'0004') for X-BASE32K encoding, ENC_QP (Z'0008') for QUOTED-PRINTABLE encoding, ENC_BASE10 (Z'0010') for BASE10 encoding, ENC_BASE16 (Z'0020') for BASE16 encoding or ENC_BASE8 (Z'0040') for BASE8 encoding. At this time FCBlib only supports ENC_NONE BINARY encoding. The value returned in SIZE is taken from the MIME header X-Binary-Size as an INTEGER. It is returned as 0 if not specified. The value returned in ID is taken from the MIME header X-Binary-ID as an INTEGER. It is returned as 0 if not specified. The value returned in DIGEST is taken from the MIME header Content-MD5. It is returned as a character string. If no digest is given, an empty string is returned. The value returned in COMPRESSION is taken from the MIME header Content-Type in the conversions parameter. The reported value is one of the INTEGER values CBF_CANONICAL (Z'0050'), CBF_PACKED (Z'0060'), CBF_PACKED_V2 (Z'0090'), CBF_BYTE_OFFSET (Z'0070'), CBF_PREDICTOR (Z'0080'), CBF_NONE (Z'0040'). Two flags may be combined with CBF_PACKED or CBF_PACKED_V2: CBF_UNCORRELATED_SECTIONS (Z'0100') or CBF_FLAT_IMAGE (Z'0200'). At this time FCBlib does not support CBF_PREDICTOR or CBF_NONE compression. The values returned in BITS, VORZEICHEN and REELL are the parameters of the data types of the elements. These values are taken from the MIME header X-Binary-Element-Type, which has values of the form "signed BITS-bit integer", "unsigned BITS-bit integer", "signed BITS-bit real IEEE" or "signed BITS-bit complex IEEE". If no value is given, REELL is reported as -1. If the value in one of the integer types, REELL is reported as 0. If the value is one of the real or complex types, REELL is reported as 1. In the current release of FCBlib only the integer types for BITS equal to 16 or 32 are supported. The value returned in BYTEORDER is the byte order of the data in the image file as reported in the MIME header. The value, if specified, will be either the character string "LITTLE_ENDIAN" or the character string "BIG_ENDIAN". If no byte order is specified, "LITTLE_ENDIAN" is reported. This value is taken from the MIME header X-Binary-Element-Byte-Order. As of this writing, CBFlib will not generate "BIG_ENDIAN" byte-order files. However, both CBFlib and FCBlib read "LITTLE_ENDIAN" byte-order files, even on big-endian machines. The value returned in DIMOVER is the overall number of elements in the image array, if specified, or zero, if not specified. This value is taken from the MIME header X-Binary-Number-of-Elements. The values returned in DIM1, DIM2 and DIM3 are the sizes of the fastest changing, second fastest changing and third fastest changing dimensions of the array, if specified, or zero, if not specified. These values are taken from the MIME header X-Binary-Size-Fastest-Dimension, X-Binary-Size-Second-Dimension and X-Binary-Size-Third-Dimension respectively. The value returned in PADDING is the size of the post-data padding, if any, if specified or zero, if not specified. The value is given as a count of octets. This value is taken from the MIME header X-Binary-Size-Padding. ARGUMENTS TAPIN The INTEGER Fortran device unit number assigned to image file. LAST_CHAR The last character (as an INTEGER(1) byte) read. FCB_BYTES_IN_REC The INTEGER number of bytes in a record. BYTE_IN_FILE The INTEGER byte (counting from 1) of the byte to read. REC_IN_FILE The INTEGER record number (counting from 1) of next record to read. BUFFER The INTEGER(1) array of length FCB_BYTES_IN_REC to hold the appropriate record from TAPIN ENCODING INTEGER type of encoding for the binary section as reported in the MIME header. ID INTEGER binary identifier as reported in the MIME header. SIZE INTEGER size of compressed binary section as reported in the MIME header. DIGEST The MD5 message digest as reported in the MIME header. COMPRESSION INTEGER compression method as reported in the MIME header. BITS INTEGER number of bits in each element as reported in the MIME header. VORZEICHEN INTEGER flag for signed or unsigned elements as reported in the MIME header. Set to 1 if the elements can be read as signed values, 0 otherwise. REELL INTEGER flag for real elements as reported in the MIME header. Set to 1 if the elements can be read as REAL BYTEORDER The byte order as reported in the MIME header. DIM1 Pointer to the destination fastest dimension. DIM2 Pointer to the destination second fastest dimension. DIM3 Pointer to the destination third fastest dimension. PADDING Pointer to the destination padding size. RETURN VALUE Returns 0 if the function is successful. SEE ALSO 2.5.3 FCB_EXIT_BINARY 2.5.6 FCB_OPEN_CIFIN 2.5.9 FCB_READ_BYTE 2.5.11 FCB_READ_LINE ---------------------------------------------------------------------- 2.5.6 FCB_OPEN_CIFIN INTERFACE INTEGER FUNCTION FCB_OPEN_CIFIN(FILNAM,TAPIN,LAST_CHAR, & FCB_BYTES_IN_REC,BYTE_IN_FILE,REC_IN_FILE,BUFFER) CHARACTER(len=*),INTENT(IN) :: FILNAM INTEGER, INTENT(IN) :: TAPIN,FCB_BYTES_IN_REC INTEGER(1), INTENT(OUT):: LAST_CHAR INTEGER, INTENT(OUT):: BYTE_IN_FILE,REC_IN_FILE INTEGER(1), INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) INTEGER FCB_RECORD_SIZE END FUNCTION END INTERFACE The function FCB_OPEN_CIFIN opens the CBF image file given by the file name in the character string FILNAM on the logical unit TAPIN. The calling routine must provide an INTEGER(1) byte buffer BUFFER of some appropriate INTEGER size FCB_BYTES_IN_REC. The size must be chosen to suit the machine, but in most cases, 4096 will work. The values returned in LAST_CHAR, BYTE_IN_FILE, and REC_IN_FILE are for use in subsequent FCBlib I/O routines. The image file will be checked for the initial characters "###CBF: ". If there is no match the error value CBF_FILEREAD is returned. ARGUMENTS FILNAM The character string name of the image file to be opened. TAPIN The INTEGER Fortran device unit number assigned to image file. LAST_CHAR The last character (as an INTEGER(1) byte) read. FCB_BYTES_IN_REC The INTEGER number of bytes in a record. BYTE_IN_FILE The INTEGER byte (counting from 1) of the byte to read. REC_IN_FILE The INTEGER record number (counting from 1) of next record to read. BUFFER The INTEGER(1) array of length FCB_BYTES_IN_REC to hold the appropriate record from TAPIN RETURN VALUE Returns 0 if the function is successful. SEE ALSO 2.5.3 FCB_EXIT_BINARY 2.5.5 FCB_NEXT_BINARY 2.5.9 FCB_READ_BYTE 2.5.11 FCB_READ_LINE ---------------------------------------------------------------------- 2.5.7 FCB_PACKED: FCB_DECOMPRESS_PACKED_I2, FCB_DECOMPRESS_PACKED_I4, FCB_DECOMPRESS_PACKED_3D_I2, FCB_DECOMPRESS_PACKED_3D_I4 INTERFACE INTEGER FUNCTION FCB_DECOMPRESS_PACKED_I2 (ARRAY,NELEM,NELEM_READ, & ELSIGN, COMPRESSION, DIM1, DIM2, & TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) INTEGER(2), INTENT(OUT):: ARRAY(DIM1,DIM2) INTEGER(8), INTENT(OUT):: NELEM_READ INTEGER(8), INTENT(IN):: NELEM INTEGER, INTENT(IN):: ELSIGN, COMPRESSION INTEGER(8), INTENT(IN):: DIM1,DIM2 INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) END FUNCTION END INTERFACE INTERFACE INTEGER FUNCTION FCB_DECOMPRESS_PACKED_I4 (ARRAY,NELEM,NELEM_READ, & ELSIGN, COMPRESSION, DIM1, DIM2, & TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) INTEGER(4), INTENT(OUT):: ARRAY(DIM1,DIM2) INTEGER(8), INTENT(OUT):: NELEM_READ INTEGER(8), INTENT(IN):: NELEM INTEGER, INTENT(IN):: ELSIGN, COMPRESSION INTEGER(8), INTENT(IN):: DIM1,DIM2 INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) END FUNCTION END INTERFACE INTERFACE INTEGER FUNCTION FCB_DECOMPRESS_PACKED_3D_I2 (ARRAY,NELEM,NELEM_READ, & ELSIGN, COMPRESSION, DIM1, DIM2, DIM3, & TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) INTEGER(2), INTENT(OUT):: ARRAY(DIM1,DIM2,DIM3) INTEGER(8), INTENT(OUT):: NELEM_READ INTEGER(8), INTENT(IN):: NELEM INTEGER, INTENT(IN):: ELSIGN, COMPRESSION INTEGER(8), INTENT(IN):: DIM1,DIM2,DIM3 INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) END FUNCTION END INTERFACE INTERFACE INTEGER FUNCTION FCB_DECOMPRESS_PACKED_3D_I4 (ARRAY,NELEM,NELEM_READ, & ELSIGN, COMPRESSION, DIM1, DIM2, DIM3, & TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) INTEGER(4), INTENT(OUT):: ARRAY(DIM1,DIM2,DIM3) INTEGER(8), INTENT(OUT):: NELEM_READ INTEGER(8), INTENT(IN):: NELEM INTEGER, INTENT(IN):: ELSIGN, COMPRESSION INTEGER(8), INTENT(IN):: DIM1,DIM2,DIM3 INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) END FUNCTION END INTERFACE The functions FCB_DECOMPRESS_PACKED_I2, FCB_DECOMPRESS_PACKED_I4, FCB_DECOMPRESS_PACKED_3D_I2 and FCB_DECOMPRESS_PACKED_3D_I4, decompress images compress according the the CBF_PACKED or CBF_PACKED_V2 compression described in section 3.3.2 on J. P. Abrahams CCP4 packed compression. The relevant function should be called immediately after a call to FCB_NEXT_BINARY, using the values returned by FCB_NEXT_BINARY to select the appropriate version of the function. ARGUMENTS ARRAY The array to receive the image NELEM The INTEGER(8) number of elements to be read NELEM_READ The INTEGER(8) returned value of the number of elements actually read ELSIGN The INTEGER value of the flag for signed (1) OR unsigned (0) data COMPRESSION The compression of the image DIM1 The INTEGER(8) value of the fastest dimension of ARRAY DIM2 The INTEGER(8) value of the second fastest dimension DIM3 The INTEGER(8) value of the third fastest dimension TAPIN The INTEGER Fortran device unit number assigned to image file. FCB_BYTES_IN_REC The INTEGER number of bytes in a record. BYTE_IN_FILE The INTEGER byte (counting from 1) of the byte to read. REC_IN_FILE The INTEGER record number (counting from 1) of next record to read. BUFFER The INTEGER(1) array of length FCB_BYTES_IN_REC to hold the appropriate record from TAPIN RETURN VALUE Returns 0 if the function is successful. SEE ALSO 2.5.3 FCB_EXIT_BINARY 2.5.5 FCB_NEXT_BINARY 2.5.6 FCB_OPEN_CIFIN 2.5.9 FCB_READ_BYTE 2.5.11 FCB_READ_LINE ---------------------------------------------------------------------- 2.5.8 FCB_READ_BITS INTERFACE INTEGER FUNCTION FCB_READ_BITS(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,BCOUNT,BBYTE, & BITCOUNT,IINT,LINT) INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) INTEGER, INTENT(INOUT):: BCOUNT INTEGER(1),INTENT(INOUT):: BBYTE INTEGER, INTENT(IN):: BITCOUNT INTEGER, INTENT(IN):: LINT INTEGER(4), INTENT(OUT):: IINT(LINT) END FUNCTION END INTERFACE The function FCB_READ_BITS gets the integer value starting at BYTE_IN_FILE from file TAPIN continuing through BITCOUNT bits, with sign extension. BYTE_IN_FILE is left at the entry value and not incremented. The resulting, sign-extended integer value is stored in the INTEGER(4) array IINT of dimension LINT with the least significant portion in IINT(1). ARGUMENTS TAPIN The INTEGER Fortran device unit number assigned to image file. FCB_BYTES_IN_REC The INTEGER number of bytes in a record. BUFFER The INTEGER(1) array of length FCB_BYTES_IN_REC to hold the appropriate record from TAPIN REC_IN_FILE The INTEGER record number (counting from 1) of next record to read. BYTE_IN_FILE The INTEGER byte (counting from 1) of the byte to read. BCOUNT The INTEGER count of bits remaining unused from the last call to FCB_READ_BITS. BBYTE The INTEGER(1) byte containing the unused bits from the last call to FCB_READ_BITS. BITCOUNT The INTEGER count of the number of bits to be extracted from the image file. IINT The INTEGER(4) array into which to store the value extracted from the image file. LINT The INTEGER length of the array IINT. RETURN VALUE Returns 0 if the function is successful. Because of the use of direct access I/O in blocks of size FCB_BYTES_IN_REC the precise location of the end of file may not be detected. SEE ALSO 2.5.3 FCB_EXIT_BINARY 2.5.5 FCB_NEXT_BINARY 2.5.6 FCB_OPEN_CIFIN 2.5.9 FCB_READ_BYTE 2.5.11 FCB_READ_LINE ---------------------------------------------------------------------- 2.5.9 FCB_READ_BYTE INTERFACE INTEGER FUNCTION FCB_READ_BYTE(TAPIN,FCB_BYTES_IN_REC,BUFFER, & REC_IN_FILE,BYTE_IN_FILE,IBYTE) INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) INTEGER(1), INTENT(OUT):: IBYTE END FUNCTION END INTERFACE The function FCB_READ_BYTE reads the byte at the position BYTE_IN_FILE in the image file TAPIN. The first byte in the file is at BYTE_IN_FILE = 1. BYTE_IN_FILE should be set to the desired value before the call to the function and is not incremented within the function. The function attempts to suppress the error caused by a read of a short last record, and in most systems cannot determine the exact location of the end of the image file, returning zero bytes until the equivalent of a full final record has been read. ARGUMENTS TAPIN The INTEGER Fortran device unit number assigned to image file. FCB_BYTES_IN_REC The INTEGER number of bytes in a record. BUFFER The INTEGER(1) array of length FCB_BYTES_IN_REC to hold the appropriate record from TAPIN REC_IN_FILE The INTEGER record number (counting from 1) of next record to read. BYTE_IN_FILE The INTEGER byte (counting from 1) of the byte to read. IBYTE The INTEGER(1) byte found in the image file at the byte position BYTE_IN_FILE. RETURN VALUE Returns 0 if the function is successful. Because of the use of direct access I/O in blocks of size FCB_BYTES_IN_REC the precise location of the end of file may not be detected. SEE ALSO 2.5.3 FCB_EXIT_BINARY 2.5.5 FCB_NEXT_BINARY 2.5.6 FCB_OPEN_CIFIN 2.5.9 FCB_READ_BITS 2.5.11 FCB_READ_LINE ---------------------------------------------------------------------- 2.5.10 FCB_READ_IMAGE_I2, FCB_READ_IMAGE_I4, FCB_READ_IMAGE_3D_I2, FCB_READ_IMAGE_3D_I4 INTERFACE INTEGER FUNCTION FCB_READ_IMAGE_I2(ARRAY,NELEM,NELEM_READ, & ELSIGN, COMPRESSION, DIM1, DIM2, & PADDING,TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) INTEGER(2), INTENT(OUT):: ARRAY(DIM1,DIM2) INTEGER(8), INTENT(OUT):: NELEM_READ INTEGER(8), INTENT(IN):: NELEM INTEGER, INTENT(IN):: ELSIGN INTEGER, INTENT(OUT):: COMPRESSION INTEGER(8), INTENT(IN):: DIM1,DIM2 INTEGER(8), INTENT(OUT):: PADDING INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) END FUNCTION END INTERFACE INTERFACE INTEGER FUNCTION FCB_READ_IMAGE_I4(ARRAY,NELEM,NELEM_READ, & ELSIGN, COMPRESSION, DIM1, DIM2, & PADDING,TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) INTEGER(4), INTENT(OUT):: ARRAY(DIM1,DIM2) INTEGER(8), INTENT(OUT):: NELEM_READ INTEGER(8), INTENT(IN):: NELEM INTEGER, INTENT(IN):: ELSIGN INTEGER, INTENT(OUT):: COMPRESSION INTEGER(8), INTENT(IN):: DIM1,DIM2 INTEGER(8), INTENT(OUT):: PADDING INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) END FUNCTION END INTERFACE INTERFACE INTEGER FUNCTION FCB_READ_IMAGE_3D_I2(ARRAY,NELEM,NELEM_READ, & ELSIGN, COMPRESSION, DIM1, DIM2, DIM3, & PADDING,TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) INTEGER(2), INTENT(OUT):: ARRAY(DIM1,DIM2,DIM3) INTEGER(8), INTENT(OUT):: NELEM_READ INTEGER(8), INTENT(IN):: NELEM INTEGER, INTENT(IN):: ELSIGN INTEGER, INTENT(OUT):: COMPRESSION INTEGER(8), INTENT(IN):: DIM1,DIM2,DIM3 INTEGER(8), INTENT(OUT):: PADDING INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) END FUNCTION END INTERFACE INTERFACE INTEGER FUNCTION FCB_READ_IMAGE_3D_I4(ARRAY,NELEM,NELEM_READ, & ELSIGN, COMPRESSION, DIM1, DIM2, DIM3, & PADDING,TAPIN,FCB_BYTES_IN_REC,BYTE_IN_FILE, & REC_IN_FILE,BUFFER) INTEGER(4), INTENT(OUT):: ARRAY(DIM1,DIM2,DIM3) INTEGER(8), INTENT(OUT):: NELEM_READ INTEGER(8), INTENT(IN):: NELEM INTEGER, INTENT(IN):: ELSIGN INTEGER, INTENT(OUT):: COMPRESSION INTEGER(8), INTENT(IN):: DIM1,DIM2,DIM3 INTEGER(8), INTENT(OUT):: PADDING INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC INTEGER, INTENT(INOUT):: REC_IN_FILE,BYTE_IN_FILE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC) END FUNCTION END INTERFACE The function FCB_READ_IMAGE_I2 reads a 16-bit twos complement INTEGER(2) 2D image. The function FCB_READ_IMAGE_I4 read a 32-bit twos complement INTEGER(4) 2D image. The function FCB_READ_IMAGE_3D_I2 reads a 16-bit twos complement INTEGER(2) 3D image. The function FCB_READ_IMAGE_3D_I4 reads a 32-bit twos complement INTEGER(4) 3D image. In each case the image is compressed either by a BYTE_OFFSET algorithm by W. Kabsch based on a proposal by A. Hammersley or by a PACKED algorithm by J. P. Abrahams as used in CCP4, with modifications by P. Ellis and H. J. Bernstein. The relevant function automatically first calls FCB_NEXT_BINARY to skip to the next binary section and then starts to read. An error return will result if the parameters of this call are inconsistent with the values in MIME header. ARGUMENTS ARRAY The array to receive the image NELEM The INTEGER(8) number of elements to be read NELEM_READ The INTEGER(8) returned value of the number of elements actually read ELSIGN The INTEGER value of the flag for signed (1) OR unsigned (0) data COMPRESSION The actual compression of the image DIM1 The INTEGER(8) value of the fastest dimension of ARRAY DIM2 The INTEGER(8) value of the second fastest dimension DIM3 The INTEGER(8) value of the third fastest dimension TAPIN The INTEGER Fortran device unit number assigned to image file. FCB_BYTES_IN_REC The INTEGER number of bytes in a record. BYTE_IN_FILE The INTEGER byte (counting from 1) of the byte to read. REC_IN_FILE The INTEGER record number (counting from 1) of next record to read. BUFFER The INTEGER(1) array of length FCB_BYTES_IN_REC to hold the appropriate record from TAPIN RETURN VALUE Returns 0 if the function is successful. SEE ALSO 2.5.3 FCB_EXIT_BINARY 2.5.5 FCB_NEXT_BINARY 2.5.6 FCB_OPEN_CIFIN 2.5.7 FCB_DECOMPRESS: FCB_DECOMPRESS_PACKED_I2, FCB_DECOMPRESS_PACKED_I4, FCB_DECOMPRESS_PACKED_3D_I2, FCB_DECOMPRESS_PACKED_3D_I4 2.5.9 FCB_READ_BYTE 2.5.11 FCB_READ_LINE ---------------------------------------------------------------------- 2.5.11 FCB_READ_LINE INTERFACE INTEGER FUNCTION FCB_READ_LINE(TAPIN,LAST_CHAR,FCB_BYTES_IN_REC, & BYTE_IN_FILE,REC_IN_FILE,BUFFER,LINE,N,LINELEN) INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC,N INTEGER, INTENT(INOUT):: BYTE_IN_FILE,REC_IN_FILE INTEGER, INTENT(OUT):: LINELEN INTEGER(1),INTENT(INOUT):: LAST_CHAR,BUFFER,(FCB_BYTES_IN_REC) INTEGER(1), INTENT(OUT):: LINE(N) END FUNCTION END INTERFACE The function FCB_READ_LINE reads successive bytes into the INTEGER(1) byte array LINE of dimension N), stopping at N bytes or the first error or the first CR (Z'0D') or LF (Z'0A'), whichever comes first. It discards an LF after a CR. The variable LAST_CHAR is checked for the last character from the previous line to make this determination. The actual number of bytes read into the line, not including any terminal CR or LF is stored in LINELEN. ARGUMENTS TAPIN The INTEGER Fortran device unit number assigned to image file. LAST_CHAR The INTEGER(1) byte holding the ASCII value of the last character read for each line read. FCB_BYTES_IN_REC The INTEGER number of bytes in a record. BYTE_IN_FILE The INTEGER byte (counting from 1) of the byte to read. REC_IN_FILE The INTEGER record number (counting from 1) of next record to read. BUFFER The INTEGER(1) array of length FCB_BYTES_IN_REC to hold the appropriate record from TAPIN. LINE The INTEGER(1) array of length N to hold the line to be read from TAPIN. N The INTEGER dimension of LINE. LINELEN The INTEGER number of characters read into LINE. RETURN VALUE Returns 0 if the function is successful. SEE ALSO 2.5.3 FCB_EXIT_BINARY 2.5.5 FCB_NEXT_BINARY 2.5.6 FCB_OPEN_CIFIN 2.5.7 FCB_DECOMPRESS: FCB_DECOMPRESS_PACKED_I2, FCB_DECOMPRESS_PACKED_I4, FCB_DECOMPRESS_PACKED_3D_I2, FCB_DECOMPRESS_PACKED_3D_I4 2.5.9 FCB_READ_BYTE 2.5.12 FCB_READ_XDS_I2 INTERFACE INTEGER FUNCTION FCB_READ_XDS_I2(FILNAM,TAPIN,NX,NY,IFRAME,JFRAME) CHARACTER(len=*),INTENT(IN) :: FILNAM INTEGER, INTENT(IN) :: TAPIN,NX,NY INTEGER(2), INTENT(OUT):: IFRAME(NX*NY) INTEGER(4), INTENT(OUT):: JFRAME(NX,NY) END FUNCTION END INTERFACE The function FCB_READ_XDS_I2 read a 32-bit integer twos complement image into a 16-bit INTEGER(2) XDS image using the CBF_BYTE_OFFSET, CBF_PACKED or CBF_PACKED_V2 compressions for the 32-bit data. The BYTE_OFFSET algorithm is a variant of the September 2006 version by W. Kabsch which was based on a suggestion by A. Hammersley and which was further modified by H. Bernstein. The file named FILNAM is opened on the logical unit TAPIN and FCB_NEXT_BINARY is used to skip to the next binary image. The binary image is then decompressed to produce an XDS 16-bit integer image array IFRAME which is NX by NY. The dimensions must agree with the dimensions specified in MIME header. The conversion from a 32-bit integer I32 to 16-bit XDS pixel I16 is done as per W. Kabsch as follows: The value I32 is limited to the range -1023 =< I32 =< 1048576. If I32 is outside that range it is truncated to the closer boundary. The generate I16, the 16-bit result, if I32 > 32767, it is divided by 32 (producing a number between 1024 and 32768), and then negated (producing a number between -1024 and -32768). For CBF_BYTE_OFFSET this conversion can be done on the fly directly into the target array IFRAME, but for the CBF_PACKED or CBF_PACKED_V2, the full 32 bit precision is needed during the decompression, forcing the use of an intermediate INTEGER(4) array JFRAME to hold the 32-bit image in that case. The image file is closed after reading one image. ARGUMENTS FILNAM The character string name of the image file to be opened. TAPIN The INTEGER Fortran device unit number assigned to image file. NX The INTEGER fast dimension of the image array. NY The INTEGER slow dimension of the image array. IFRAME The INTEGER(2) XDS image array. JFRAME The INTEGER(4) 32-bit image scratch array needed for CBF_PACKED or CBF_PACKED_V2 images. RETURN VALUE Returns 0 if the function is successful, CBF_FORMAT (=1) if it cannot handle this CBF format (not implemented), -1 if it cannot determine endian architecture of this machine, -2: if it cannot open the image file, -3: if it finds the wrong image format and -4 if it cannot read the image. ---------------------------------------------------------------------- 2.5.13 FCB_SKIP_WHITESPACE INTERFACE INTEGER FUNCTION FCB_SKIP_WHITESPACE(TAPIN,LAST_CHAR, & FCB_BYTES_IN_REC,BYTE_IN_FILE,REC_IN_FILE,BUFFER,& LINE,N,LINELEN,ICUR,FRESH_LINE) INTEGER, INTENT(IN):: TAPIN,FCB_BYTES_IN_REC,N INTEGER, INTENT(INOUT):: BYTE_IN_FILE,REC_IN_FILE,LINELEN,ICUR, & FRESH_LINE INTEGER(1),INTENT(INOUT):: BUFFER(FCB_BYTES_IN_REC),LINE(N), & LAST_CHAR END INTERFACE The function FCB_SKIP_WHITESPACE skips forward on the current INTEGER(1) byte array LINE of size N with valid data in LINE(1:LINELEN) from the current position ICUR moving over MIME header whitespace and comments, reading new lines into LINE if needed. The flag FRESH_LINE indicates that a fresh line should be read on entry. ARGUMENTS TAPIN The INTEGER Fortran device unit number assigned to image file. LAST_CHAR The INTEGER(1) byte holding the ASCII value of the last character read for each line read. FCB_BYTES_IN_REC The INTEGER number of bytes in a record. BYTE_IN_FILE The INTEGER byte (counting from 1) of the byte to read. REC_IN_FILE The INTEGER record number (counting from 1) of next record to read. BUFFER The INTEGER(1) array of length FCB_BYTES_IN_REC to hold the appropriate record from TAPIN. LINE The INTEGER(1) array of length N to hold the line to be read from TAPIN. N The INTEGER dimension of LINE. LINELEN The INTEGER number of characters read into LINE. ICUR The INTEGER position within the line. FRESH_LINE The INTEGER flag that a fresh line is needed. RETURN VALUE Returns 0 if the function is successful. SEE ALSO 2.5.3 FCB_EXIT_BINARY 2.5.5 FCB_NEXT_BINARY 2.5.6 FCB_OPEN_CIFIN 2.5.7 FCB_DECOMPRESS: FCB_DECOMPRESS_PACKED_I2, FCB_DECOMPRESS_PACKED_I4, FCB_DECOMPRESS_PACKED_3D_I2, FCB_DECOMPRESS_PACKED_3D_I4 2.5.9 FCB_READ_BYTE ---------------------------------------------------------------------- 3. File format 3.1 General description With the exception of the binary sections, a CBF file is an mmCIF-format ASCII file, so a CBF file with no binary sections is a CIF file. An imgCIF file has any binary sections encoded as CIF-format ASCII strings and is a CIF file whether or not it contains binary sections. In most cases, CBFlib can also be used to access normal CIF files as well as CBF and imgCIF files. 3.2 Format of the binary sections Before getting to the binary data itself, there are some preliminaries to allow a smooth transition from the conventions of CIF to those of raw or encoded streams of "octets" (8-bit bytes). The binary data is given as the essential part of a specially formatted semicolon-delimited CIF multi-line text string. This text string is the value associated with the tag "_array_data.data". The specific format of the binary sections differs between an imgCIF and a CBF file. 3.2.1 Format of imgCIF binary sections Each binary section is encoded as a semicolon-delimited string. Within the text string, the conventions developed for transmitting email messages including binary attachments are followed. There is secondary ASCII header information, formatted as Multipurpose Internet Mail Extensions (MIME) headers (see RFCs 2045-49 by Freed, et al.). The boundary marker for the beginning of all this is the special string --CIF-BINARY-FORMAT-SECTION-- at the beginning of a line. The initial "--" says that this is a MIME boundary. We cannot put "###" in front of it and conform to MIME conventions. Immediately after the boundary marker are MIME headers, describing some useful information we will need to process the binary section. MIME headers can appear in different orders, and can be very confusing (look at the raw contents of a email message with attachments), but there is only one header which is has to be understood to process an imgCIF: "Content-Transfer-Encoding". If the value given on this header is "BINARY", this is a CBF and the data will be presented as raw binary, containing a count (in the header described in 3.2.2 Format of CBF binary sections) so that we'll know when to start looking for more information. If the value given for "Content-Transfer-Encoding" is one of the real encodings: "BASE64", "QUOTED-PRINTABLE", "X-BASE8", "X-BASE10" or "X-BASE16", the file is an imgCIF, and we'll need some other headers to process the encoded binary data properly. It is a good practice to give headers in all cases. The meanings of various encodings is given in the CBF extensions dictionary, cif_img_1.5.4.dic, as one html file, or as separate pages for each defintion. For certain compressions (e.g. CBF_PACKED) MIME headers are essential to determine the parameters of the compression. The full list of MIME headers recognized by and generated by CBFlib is: * Content-Type: * Content-Transfer-Encoding: * Content-MD5: * X-Binary-Size: * X-Binary-ID: * X-Binary-Element-Type: * X-Binary-Element-Byte-Order: * X-Binary-Number-of-Elements: * X-Binary-Size-Fastest-Dimension: * X-Binary-Size-Second-Dimension: * X-Binary-Size-Third-Dimension: * X-Binary-Size-Padding: * Content-Type: The "Content-Type" header tells us what sort of data we have (currently always "application/octet-stream" for a miscellaneous stream of binary data) and, optionally, the conversions that were applied to the original data. The default is to compress the data with the "CBF-PACKED" algorithm. The Content-Type may be any of the discrete types permitted in RFC 2045; 'application/octet-stream' is recommended. If an octet stream was compressed, the compression should be specified by the parameter 'conversions="X-CBF_PACKED"' or the parameter 'conversions="X-CBF_PACKED_V2"' or the parameter 'conversions="X-CBF_CANONICAL"' or the parameter 'conversions="X-CBF_BYTE_OFFSET"' If the parameter 'conversions="X-CBF_PACKED"' or 'conversions="X-CBF_PACKED_V2"' is given it may be further modified with the parameters '"uncorrelated_sections"' or '"flat"' If the '"uncorrelated_sections"' parameter is given, each section will be compressed without using the prior section for averaging. If the '"flat"' parameter is given, each the image will be treated as one long row. * Content-Transfer-Encoding: The "Content-Transfer-Encoding" may be 'BASE64', 'Quoted-Printable', 'X-BASE8', 'X-BASE10', 'X-BASE16' or 'X-BASE32K', for an imgCIF or 'BINARY' for a CBF. The octal, decimal and hexadecimal transfer encodings are provided for convenience in debugging and are not recommended for archiving and data interchange. In a CIF, one of the parameters 'charset=us-ascii', 'charset=utf-8' or 'charset=utf-16' may be used on the Content-Transfer-Encoding to specify the character set used for the external presentation of the encoded data. If no charset parameter is given, the character set of the enclosing CIF is assumed. In any case, if a BOM flag is detected (FE FF for big-endian UTF-16, FF FE for little-endian UTF-16 or EF BB BF for UTF-8) is detected, the indicated charset will be assumed until the end of the encoded data or the detection of a different BOM. The charset of the Content-Transfer-Encoding is not the character set of the encoded data, only the character set of the presentation of the encoded data and should be respecified for each distinct STAR string. In an imgCIF file, the encoded binary data begins after the empty line terminating the header. In an imgCIF file, the encoded binary data ends with the terminating boundary delimiter '\n--CIF-BINARY-FORMAT-SECTION----' in the currently effective charset or with the '\n; ' that terminates the STAR string. In a CBF, the raw binary data begins after an empty line terminating the header and after the sequence: Octet Hex Decimal Purpose 0 0C 12 (ctrl-L) Page break 1 1A 26 (ctrl-Z) Stop listings in MS-DOS 2 04 04 (Ctrl-D) Stop listings in UNIX 3 D5 213 Binary section begins None of these octets are included in the calculation of the message size or in the calculation of the message digest. * Content-MD5: An MD5 message digest may, optionally, be used. The 'RSA Data Security, Inc. MD5 Message-Digest Algorithm' should be used. No portion of the header is included in the calculation of the message digest. The optional "Content-MD5" header provides a much more sophisticated check on the integrity of the binary data than size checks alone can provide. * X-Binary-Size: The "X-Binary-Size" header specifies the size of the equivalent binary data in octets. This is the size after any compressions, but before any ascii encodings. This is useful in making a simple check for a missing portion of this file. The 8 bytes for the Compression type (see below) are not counted in this field, so the value of "X-Binary-Size" is 8 less than the quantity in bytes 12-19 of the raw binary data ( 3.2.2 Format of CBF binary sections). * X-Binary-ID: The "X-Binary-ID" header should contain the same value as was given for "_array_data.binary_id". * X-Binary-Element-Type: The "X-Binary-Element-Type" header specifies the type of binary data in the octets, using the same descriptive phrases as in _array_structure.encoding_type. The default value is 'unsigned 32-bit integer'. * X-Binary-Element-Byte-Order: The "X-Binary-Element-Byte-Order" can specify either '"BIG_ENDIAN"' or '"LITTLE_ENDIAN"' byte order of the image data. CBFlib only writes '"LITTLE_ENDIAN"', and in general can only process LITTLE_ENDIAN even on machines that are BIG_ENDIAN. * X-Binary-Number-of-Elements: The "X-Binary-Number-of-Elements" specifies the number of elements (not the number of octets) in the decompressed, decoded image. * X-Binary-Size-Fastest-Dimension: The optional "X-Binary-Size-Fastest-Dimension" specifies the number of elements (not the number of octets) in one row of the fastest changing dimension of the binary data array. This information must be in the MIME header for proper operation of some of the decompression algorithms. * X-Binary-Size-Second-Dimension: The optional "X-Binary-Size-Second-Dimension" specifies the number of elements (not the number of octets) in one column of the second-fastest changing dimension of the binary data array. This information must be in the MIME header for proper operation of some of the decompression algorithms. * X-Binary-Size-Third-Dimension: The optional "X-Binary-Size-Third-Dimension" specifies the number of sections for the third-fastest changing dimension of the binary data array. * X-Binary-Size-Padding: The optional "X-Binary-Size-Padding" specifies the size in octets of an optional padding after the binary array data and before the closing flags for a binary section. CBFlib always writes this padding as zeros, but this information should be in the MIME header for a binary section that uses padding, especially if non-zero padding is used. A blank line separator immediately precedes the start of the encoded binary data. Blank spaces may be added prior to the preceding "line separator" if desired (e.g. to force word or block alignment). Because CBFLIB may jump forward in the file from the MIME header, the length of encoded data cannot be greater than the value defined by "X-Binary-Size" (except when "X-Binary-Size" is zero, which means that the size is unknown), unless "X-Binary-Size-Padding" is specified to allow for the padding. At exactly the byte following the full binary section as defined by the length and padding values is the end of binary section identifier. This consists of the line-termination sequence followed by: --CIF-BINARY-FORMAT-SECTION---- ; with each of these lines followed by a line-termination sequence. This brings us back into a normal CIF environment. This identifier is, in a sense, redundant because the binary data length value tells the a program how many bytes to jump over to the end of the binary data. This redundancy has been deliberately added for error checking, and for possible file recovery in the case of a corrupted file and this identifier must be present at the end of every block of binary data. 3.2.2 Format of CBF binary sections In a CBF file, each binary section is encoded as a ;-delimited string, starting with an arbitrary number of pure-ASCII characters. Note: For historical reasons, CIFlib has the option of writing simple header and footer sections: "START OF BINARY SECTION" at the start of a binary section and "END OF BINARY SECTION" at the end of a binary section, or writing MIME-type header and footer sections (3.2.1 Format of imgCIF binary sections). If the simple header is used, the actual ASCII text is ignored when the binary section is read. Use of the simple binary header is deprecated. The MIME header is recommended. Between the ASCII header and the actual CBF binary data is a series of bytes ("octets") to try to stop the listing of the header, bytes which define the binary identifier which should match the "binary_id" defined in the header, and bytes which define the length of the binary section. Octet Hex Decimal Purpose 1 0C 12 (ctrl-L) End of Page 2 1A 26 (ctrl-Z) Stop listings in MS-DOS 3 04 04 (Ctrl-D) Stop listings in UNIX 4 D5 213 Binary section begins 5..5+n-1 Binary data (n octets) NOTE: When a MIME header is used, only bytes 5 through 5+n-1 are considered in computing the size and the message digest, and only these bytes are encoded for the equivalent imgCIF file using the indicated Content-Transfer-Encoding. If no MIME header has been requested (a deprecated use), then bytes 5 through 28 are used for three 8-byte words to hold the binary_id, the size and the compression type: 5..12 Binary Section Identifier (See _array_data.binary_id) 64-bit, little endian 13..20 The size (n) of the binary section in octets (i.e. the offset from octet 29 to the first byte following the data) 21..28 Compression type: CBF_NONE 0x0040 (64) CBF_CANONICAL 0x0050 (80) CBF_PACKED 0x0060 (96) CBF_BYTE_OFFSET 0x0070 (112) CBF_PREDICTOR 0x0080 (128) ... The binary data then follows in bytes 29 through 29+n-1. The binary characters serve specific purposes: o The Control-L (from-feed) will terminate printing of the current page on most operating systems. o The Control-Z will stop the listing of the file on MS-DOS type operating systems. o The Control-D will stop the listing of the file on Unix type operating systems. o The unsigned byte value 213 (decimal) is binary 11010101. (Octal 325, and hexadecimal D5). This has the eighth bit set so can be used for error checking on 7-bit transmission. It is also asymmetric, but with the first bit also set in the case that the bit order could be reversed (which is not a known concern). o (The carriage return, line-feed pair before the START_OF_BIN and other lines can also be used to check that the file has not been corrupted e.g. by being sent by ftp in ASCII mode.) At present four compression schemes are implemented are defined: CBF_NONE (for no compression), CBF_CANONICAL (for and entropy-coding scheme based on the canonical-code algorithm described by Moffat, et al. (International Journal of High Speed Electronics and Systems, Vol 8, No 1 (1997) 179-231)), CBF_PACKED or CBF_PACKED_V2 for J. P. Abrahams CCP4-style packing schemes and CBF_BYTE_OFFSET for a simple byte_offset compression scheme.. Other compression schemes will be added to this list in the future. For historical reasons, CBFlib can read or write a binary string without a MIME header. The structure of a binary string with simple headers is: Byte ASCII Decimal Description symbol value 1 ; 59 Initial ; delimiter 2 carriage-return 13 3 line-feed 10 The CBF new-line code is carriage-return, line-feed 4 S 83 5 T 84 6 A 65 7 R 83 8 T 84 9 32 10 O 79 11 F 70 12 32 13 B 66 14 I 73 15 N 78 16 A 65 17 R 83 18 Y 89 19 32 20 S 83 21 E 69 22 C 67 23 T 84 24 I 73 25 O 79 26 N 78 27 carriage-return 13 28 line-feed 10 29 form-feed 12 30 substitute 26 Stop the listing of the file in MS-DOS 31 end-of-transmission 4 Stop the listing of the file in unix 32 213 First non-ASCII value 33 .. 40 Binary section identifier (64-bit little-endien) 41 .. 48 Offset from byte 57 to the first ASCII character following the binary data 49 .. 56 Compression type 57 .. 57 + n-1 Binary data (nbytes) 57 + n carriage-return 13 58 + n line-feed 10 59 + n E 69 60 + n N 78 61 + n D 68 62 + n 32 63 + n O 79 64 + n F 70 65 + n 32 66 + n B 66 67 + n I 73 68 + n N 78 69 + n A 65 70 + n R 83 71 + n Y 89 72 + n 32 73 + n S 83 74 + n E 69 75 + n C 67 76 + n T 84 77 + n I 73 78 + n O 79 79 + n N 78 80 + n carriage-return 13 81 + n line-feed 10 82 + n ; 59 Final ; delimiter 3.3 Compression schemes Two schemes for lossless compression of integer arrays (such as images) have been implemented in this version of CBFlib: 1. An entropy-encoding scheme using canonical coding 2. A CCP4-style packing scheme. Both encode the difference (or error) between the current element in the array and the prior element. Parameters required for more sophisticated predictors have been included in the compression functions and will be used in a future version of the library. 3.3.1 Canonical-code compression The canonical-code compression scheme encodes errors in two ways: directly or indirectly. Errors are coded directly using a symbol corresponding to the error value. Errors are coded indirectly using a symbol for the number of bits in the (signed) error, followed by the error iteslf. At the start of the compression, CBFlib constructs a table containing a set of symbols, one for each of the 2^n direct codes from -2^(n-1) .. 2^(n-1)-1, one for a stop code, and one for each of the maxbits -n indirect codes, where n is chosen at compress time and maxbits is the maximum number of bits in an error. CBFlib then assigns to each symbol a bit-code, using a shorter bit code for the more common symbols and a longer bit code for the less common symbols. The bit-code lengths are calculated using a Huffman-type algorithm, and the actual bit-codes are constructed using the canonical-code algorithm described by Moffat, et al. (International Journal of High Speed Electronics and Systems, Vol 8, No 1 (1997) 179-231). The structure of the compressed data is: Byte Value 1 .. 8 Number of elements (64-bit little-endian number) 9 .. 16 Minimum element 17 .. 24 Maximum element 25 .. 32 (reserved for future use) 33 Number of bits directly coded, n 34 Maximum number of bits encoded, maxbits 35 .. 35+2^n-1 Number of bits in each direct code 35+2^n Number of bits in the stop code 35+2^n+1 .. 35+2^n+maxbits-n Number of bits in each indirect code 35+2^n+maxbits-n+1 .. Coded data 3.3.2 CCP4-style compression Starting with CBFlib 0.7.7, CBFlib supports three variations on CCP4-style compression: the "flat" version supported in versions of CBFlib prior to release 0.7.7, as well as both version 1 and version 2 of J. P. Abrahams "pack_c" compression. The CBF_PACKED and CBF_PACKED_V2 compression and decompression code incorporated in CBFlib is derived in large part from the J. P. Abrahams pack_c.c compression code in CCP4. This code is incorporated in CBFlib under the GPL and the LGPL with both the permission Jan Pieter Abrahams, the original author of pack_c.c (email from Jan Pieter Abrahams of 15 January 2007) and of the CCP4 project (email from Martyn Winn on 12 January 2007). The cooperation of J. P. Abrahams and of the CCP4 project is gratefully acknowledged. The basis for all three versions is a scheme to pack offsets (differences from a base value) into a small-endian bit stream. The stream is organized into blocks. Each block begins with a header of 6 bits in the flat packed version and version 1 of J. P. Abrahams compression, and 7 bits in version 2 of J. P. Abrahams compression. The header gives the number of offsets that follow and the number of bits in each offset. Each offset is a signed, 2's complement integer. The first 3 bits in the header gives the logarithm base 2 of the numer of offsets that follow the header. For example, if a header has a zero in bits, only one offset follows the header. If those same bits contain the number n, the number of offsets in the block is 2n. The following 3 bits (flat and version 1) or 4 bits (version 2) contains a number giving an index into a table of bit-lengths for the offsets. All offsets in a given block are of the same length. Bits 3 .. 5 (flat and version 1) or bits 3 .. 6 (version 2) encode the number of bits in each offset as follows: Value in Number of bits Number of bits bits 3 .. 5 in each V1 offset in each V2 offset 0 0 0 1 4 3 2 5 4 3 6 5 4 7 6 5 8 7 6 16 8 7 max 9 8 10 9 11 10 12 11 13 12 14 13 15 14 16 15 max The value "max" is determined by the compression version and the element size. If the compression used is "flat", then "max" is 65. If the compression is version 1 or version 2 of the JPA compression, then "max" is the number of bits in each element, i.e. 8, 16, 32 or 64 bits. The major difference between the three variants of packed compression is the choice of the base value from which the offset is measured. In all cases the first offset is measured from zero, i.e. the first offset is the value of the first pixel of the image. If "flat" is chosen or if the dimensions of the data array are not given, then the remaining offset are measure against the prior value, making it similar in approach to the "byte offset" compression described in section 3.3.3 Byte offset compression, but with a more efficient representation of the offsets. In version 1 and version 2 of the J. P. Abrahams compression, the offsets are measured against an average of earlier pixels. If there is only one row only the prior pxiel is used, starting with the same offsets for that row as for "flat". After the first row, three pixels from the prior row are used in addition to using the immediately prior pixel. If there are multiple sections, and the sections are marked as correlated, after the first section, 4 pixels from the prior section are included in the average. The CBFlib code differs from the pack_c code in the handling of the beginnings and ends of rows and sections. The pack_c code will use pixels from the other side of the image in doing the averaging. The CBFlib code drops pixels from the other side of the image from the pool. The details follow. After dealing with the special case of the first pixel, The algorithm uses an array of pointers, trail_char_data. The assignment of pixels to the pool to be averaged begins with trail_char_data[0] points to the pixel immediately prior to the next pixel to be processed, either in the same row (fastest index) or, at the end of the prior row if the next data element to be processed is at the end of a row. The location of the pixel pointed to by trail_char_data[0] is used to compute the locations of the other pixels in the pool. It will be dropped from the pool before averaging if it is on the opposite side of the image. The pool will consist of 1, 2, 4 or 8 pixels. Assume ndim1, ndim2, ndim3 are the indices of the same pixel as trail_char_data[0] points to. These indices are incremented to be the indices of the next pixel to be processed before populating trail_char_data. On exit, trail_char_data[0 .. 7] will have been populated with pointers to the pixels to be used in forming the average. Pixels that will not be used will be set to NULL. Note that trail_char_data[0] may be set to NULL. If we mark the next element to be processed with a "*" and the entries in trail_char_data with their array indices 0 .. 7, the possible patterns of settings in the general case are: current section: - - - - 0 * - - - - - - - - 3 2 1 - - - - - - - - - - - - - prior section: - - - - - 4 - - - - - - - - 7 6 5 - - - - - - - - - - - - - If there is no prior section (i.e. ndim3 is 0, or the CBF_UNCORRELATED_SECTIONS flag is set to indicate discontinuous sections), the values for trail_char_data[4 .. 7] will all be NULL. When there is a prior section, trail_char_data[5..7] are pointers to the pixels immediately below the elements pointed to by trail_char_data[1..3], except trail_char_data[4] is one element further along its row to be directly below the next element to be processed. The first element of the first row of the first section is a special case, with no averaging. In the first row of the first section (ndim2 == 0, and ndim3 == 0), after the first element (ndim1 > 0), only trail_char_data[0] is used current section: - - - - 0 * - - - - For subsequent rows of the first section (ndim2 > 0, and ndim3 == 0), for the first element (ndim1 == 0), two elements from the prior row are used: current section: * - - - - - - - - - 2 1 - - - - - - - - - - - - - - - - - - while for element after the first element, but before the last element of the row, a full set of 4 elements is used: current section: - - - - 0 * - - - - - - - - 3 2 1 - - - - - - - - - - - - - For the last element of a row (ndim1 == dim1-1), two elements are used current section: - - - - - - - - 0 * - - - - - - - - - 2 - - - - - - - - - - For sections after the first section, provided the CBF_UNCORRELATED_SECTIONS flag is not set in the compression, for each non-NULL entry in trail_char_data [0..3] an entry is made in trail_char_data [4..7], except for the first element of the first row of a section. In that case an entry is made in trail_char_data[4]. The structure of the compressed data is: Byte Value 1 .. 8 Number of elements (64-bit little-endian number) 9 .. 16 Minumum element (currently unused) 17 .. 24 Maximum element (currently unused) 25 .. 32 (reserved for future use) 33 .. Coded data 3.3.3 Byte_offset compression Starting with CBFlib 0.7.7, CBFlib supports a simple and efficient "byte_offset" algorithm originally proposed by Andy Hammerley and modified by Wolgang Kabsch and Herbert Bernstein. The original proposal was called "byte_offsets". We distinguish this variant by calling it "byte_offset". The major differences are that the "byte_offsets" algorithm started with explicit storage of the first element of the array as a 4-byte signed two's integer, and checked for image edges to changes the selection of prior pixel. The CBFlib "byte_offset" alogorithm starts with an assumed zero before the first pixel and represents the value of the first pixel as an offset of whatever number of size is needed to hold the value, and for speed, treats the entire image as a simple linear array, allowing use of the last pixel of one row as the base against which to compute the offset for the first element of the next row. The algorithm is simple and easily implemented. This algorithm can never achieve better than a factor of two compression relative to 16-bit raw data or 4 relative to 32-bit raw data, but for most diffraction data the compression will indeed be very close to these ideal values. It also has the advantage that integer values up to 32 bits (or 31 bits and sign) may be stored efficiently without the need for special over-load tables. It is a fixed algorithm which does not need to calculate any image statistics, so is fast. The algorithm works because of the following property of almost all diffraction data and much other image data: The value of one element tends to be close to the value of the adjacent elements, and the vast majority of the differences use little of the full dynamic range. However, noise in experimental data means that run-length encoding is not useful (unless the image is separated into different bit-planes). If a variable length code is used to store the differences, with the number of bits used being inversely proportional to the probability of occurrence, then compression ratios of 2.5 to 3.0 may be achieved. However, the optimum encoding becomes dependent of the exact properties of the image, and in particular on the noise. Here a lower compression ratio is achieved, but the resulting algorithm is much simpler and more robust. The "byte_offset" compression algorithm is the following: 1. Start with a base pixel value of 0. 2. Compute the difference delta between the next pixel value and the base pixel value. 3. If -127 =< delta =< 127, output delta as one byte, make the current pixel value the base pixel value and return to step 2. 4. Otherwise output -128 (80 hex). 5. We still have to output delta. If -32767 =< delta =< 32767, output delta as a little_endian 16-bit quantity, make the current pixel value the base pixel value and return to step 2. 6. Otherwise output -32768 (8000 hex, little_endian, i.e. 00 then 80) 7. We still have to output delta. If -2147483647 =< delta =< 2147483647, output delta as a little_endian 32 bit quantity, make the current pixel value the base pixel value and return to step 2. 8. Otherwise output -2147483648 (80000000 hex, little_endian, i.e. 00, then 00, then 00, then 80) and then output the pixel value as a little-endian 64 bit quantity, make the current pixel value the base pixel value and return to step 2. The "byte_offset" decompression algorithm is the following: 1. Start with a base pixel value of 0. 2. Read the next byte as delta 3. If -127 =< delta =< 127, add delta to the base pixel value, make that the new base pixel value, place it on the output array and return to step 2. 4. If delta is 80 hex, read the next two bytes as a little_endian 16-bit number and make that delta. 5. If -32767 =< delta =< 32767, add delta to the base pixel value, make that the new base pixel value, place it on the output array and return to step 2. 6. If delta is 8000 hex, read the next 4 bytes as a little_endian 32-bit number and make that delta 7. If -2147483647 =< delta =< 2147483647, add delta to the base pixel value, make that the new base pixel value, place it on the output array and return to step 2. 8. If delta is 80000000 hex, read the next 4 bytes as a little_endian 32-bit number and make that delta, read the next 8 bytes as a little_endia 64-bit number and make that delta, add delta to the base pixel value, make that the new base pixel value, place it on the output array and return to step 2. Let us look at an example, of two 1000 x 1000 flat field images presented as a mimimal imgCIF file. The first image uses 32-bit unsigned integers and the second image uses 16-bit unsigned integers. The imgCIF file begins with some identifying comments (magic numbers) to track the version of the dictionary and library: ###CBF: VERSION 1.5 # CBF file written by CBFlib v0.7.7 This is followed by the necessary syntax to start a CIF data block and by whatever tags and values are appropriate to describe the experiment. The minimum is something like data_testflat eventually we come to the actual binary data, which begins the loop header for the array_data category loop_ _array_data.data with any additional tags needed, and then the data itself, which starts with the mini-header: ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_BYTE_OFFSET" Content-Transfer-Encoding: BINARY X-Binary-Size: 1000002 X-Binary-ID: 1 X-Binary-Element-Type: "unsigned 32-bit integer" X-Binary-Element-Byte-Order: LITTLE_ENDIAN Content-MD5: +FqUJGxXhvCijXMFHC0kaA== X-Binary-Number-of-Elements: 1000000 X-Binary-Size-Fastest-Dimension: 1000 X-Binary-Size-Second-Dimension: 1000 X-Binary-Size-Padding: 4095 followed by an empty line and then the sequence of characters: ^L^Z^D followed immediately by the compressed data. The binary data begins with the hex byte 80 to flag the need for a value that will not fit in one byte. That is followed by the small_endian hex value 3E8 saying that the first delta is 1000. Then 999,999 bytes of zero follow, since this is a flat field, with all values equal to zero. That gives us our entire 1000x1000 compressed flat field. However, because we asked for 4095 bytes of padding, there is an additional 4095 bytes of zero that are not part of the compressed field. They are just pad and can be ignored. Finally, after the pad, the CIF text field that began with ; --CIF-BINARY-FORMAT-SECTION-- is completed with --CIF-BINARY-FORMAT-SECTION---- ; notice the extra -- The second flat field then follows, with a very similar mini-header: ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_BYTE_OFFSET" Content-Transfer-Encoding: BINARY X-Binary-Size: 1000002 X-Binary-ID: 2 X-Binary-Element-Type: "unsigned 16-bit integer" X-Binary-Element-Byte-Order: LITTLE_ENDIAN Content-MD5: +FqUJGxXhvCijXMFHC0kaA== X-Binary-Number-of-Elements: 1000000 X-Binary-Size-Fastest-Dimension: 1000 X-Binary-Size-Second-Dimension: 1000 X-Binary-Size-Padding: 4095 ^L^Z^D The only difference is that we have declared this array to be 16-bit and have chosen a different binary id (2 instead of 1). Even the checksum is the same. 4. Installation CBFlib should be built on a disk with at least 200 megabytes of free space. CBFlib.tar.gz is a "gzipped" tar of the code as it now stands. Place the gzipped tar in the directory that is intended to contain a new directory, named CBFlib_0.7.5 (the "top-level" directory) and uncompress it with gunzip and unpack it with tar: gunzip CBFlib.tar.gz tar xvf CBFLIB.tar As with prior releases, to run the test programs, you will also need Paul Ellis's sample MAR345 image, example.mar2300, and Chris Nielsen's sample ADSC Quantum 315 image, mb_LP_1_001.img as sample data. Both these files will be extracted by the Makefile from CBFlib_0.7.7_Data_Files. Do not download copies into the top level directory. After unpacking the archive, the top-level directory should contain a makefile: Makefile Makefile for unix and the subdirectories: src/ CBFLIB source files include/ CBFLIB header files m4/ CBFLIB m4 macro files (used to build .f90 files) examples/ Example program source files doc/ Documentation lib/ Compiled CBFLIB library bin/ Executable example programs html_images/ JPEG images used in rendering the HTML files For instructions on compiling and testing the library, go to the top-level directory and type: make The CBFLIB source and header files are in the "src" and "include" subdirectories. The FCBLIB source and m4 files are in the "src" and "m4" subdirectories. The files are: src/ include/ m4/ Description cbf.c cbf.h CBFLIB API functions cbf_alloc.c cbf_alloc.h Memory allocation functions cbf_ascii.c cbf_ascii.h Function for writing ASCII values cbf_binary.c cbf_binary.h Functions for binary values cbf_byte_offset.c cbf_byte_offset.h Byte-offset compression cbf_canonical.c cbf_canonical.h Canonical-code compression cbf_codes.c cbf_codes.h Encoding and message digest functions cbf_compress.c cbf_compress.h General compression routines cbf_context.c cbf_context.h Control of temporary files cbf_file.c cbf_file.h File in/out functions cbf_lex.c cbf_lex.h Lexical analyser cbf_packed.c cbf_packed.h CCP4-style packing compression cbf_predictor.c cbf_predictor.h Predictor-Huffman compression (not implemented) cbf_read_binary.c cbf_read_binary.h Read binary headers cbf_read_mime.c cbf_read_mime.h Read MIME-encoded binary sections cbf_simple.c cbf_simple.h Higher-level CBFlib functions cbf_string.c cbf_string.h Case-insensitive string comparisons cbf_stx.c cbf_stx.h Parser (generated from cbf.stx.y) cbf_tree.c cbf_tree.h CBF tree-structure functions cbf_uncompressed.c cbf_uncompressed.h Uncompressed binary sections cbf_write.c cbf_write.h Functions for writing cbf_write_binary.c cbf_write_binary.h Write binary sections cbf.stx.y bison grammar to define cbf_stx.c (see WARNING) md5c.c md5.h RSA message digest software from mpack global.h fcb_atol_wcnt.f90 Function to convert a string to an integer fcb_ci_strncmparr.f90 Function to do a case-insensitive comparison of a string to a byte array fcb_nblen_array.f90 Function to determine the non-blank length of a byte array fcb_read_byte.f90 Function to read a single byte fcb_read_line.f90 Function to read a line into a byte array fcb_skip_whitespace.f90 Function to skip whitespace and comments in a MIME header fcb_exit_binary.m4 Function to skip past the end of the current binary text field fcb_next_binary.m4 Function to skip to the next binary fcb_open_cifin.m4 Function to open a CBF file for reading fcb_packed.m4 Functions to read a JPA CCP4 compressed image fcb_read_bits.m4 Functions to read nay number of bits as an integer fcb_read_image.m4 Functions to read the next image in I2, I4, 3D_I2 and 3D_I4 format fcb_read_xds_i2.m4 Function to read a single xds image. fcblib_defines.m4 General m4 macro file for FCBLIB routines. In the "examples" subdirectory, there are 2 additional files used by the example programs (section 5) for reading MAR300, MAR345 or ADSC CCD images: img.c img.h Simple image library and the example programs themselves: makecbf.c Make a CBF file from an image img2cif.c Make an imgCIF or CBF from an image cif2cbf.c Copy a CIF/CBF to a CIF/CBF convert_image.c Convert an image file to a cbf using a template file cif2c.c Convert a template cbf file into a function to produce the same template in an internal cbf data structure testcell.C Exercise the cell functions as well as three template files: template_adscquantum4_2304x2304.cbf, template_mar345_2300x2300.cbf, and template_adscquantum315_3072x3072.cbf. Two additional examples (test_fcb_read_image.f90 and test_xds_binary.f90) are created from two files (test_fcb_read_image.m4 and test_xds_binary.m4) in the m4 directory. The documentation files are in the "doc" subdirectory: CBFlib.html This document (HTML) CBFlib.txt This document (ASCII) CBFlib_NOTICES.html Important NOTICES -- PLEASE READ CBFlib_NOTICES.txt Important NOTICES -- PLEASE READ gpl.txt GPL -- PLEASE READ lgpl.txt LGPL -- PLEASE READ cbf_definition_rev.txt Draft CBF/ImgCIF definition (ASCII) cbf_definition_rev.html Draft CBF/ImgCIF definition (HTML) cif_img.html CBF/ImgCIF extensions dictionary (HTML) cif_img.dic CBF/ImgCIF extensions dictionary (ASCII) ChangeLog,html Summary of change history (HTML) ChangeLog Summary of change history (ASCII) 5. Example programs The example programs makecbf.c, img2cif.c and convert_image.c read an image file from a MAR300, MAR345 or ADSC CCD detector and then uses CBFlib to convert it to CBF format (makecbf) or either imgCIF or CBF format (img2cif). makecbf writes the CBF-format image to disk, reads it in again, and then compares it to the original. img2cif just writes the desired file. makecbf works only from stated files on disk, so that random I/O can be used. img2cif includes code to process files from stdin and to stdout. convert_image reads a template as well as the image file and produces a complete CBF. The program convert_minicbf reads a minimal CBF file with just and image and some lines of text specifying the parameters of the data collection as done at SLS and combines the result with a template to produce a full CBF. The program cif2cbf can be used to convert among carious compression and encoding schemes. The program sauter_test.C is a C++ test program contributed by Nick Sauter to help in resolving a memory leak he found. The programs adscimg2cbf and cbf2adscimg are a "jiffies" contributed by Chris Nielsen of ADSC to convert ADSC images to imgCIF/CBF format and vice versa. makecbf.c is a good example of how many of the CBFlib functions can be used. To compile makecbf and the other example programs use the Makefile in the top-level directory: make all This will place the programs in the bin directory. makecbf To run makecbf with the example image, type: ./bin/makecbf example.mar2300 test.cbf The program img2cif has the following command line interface: img2cif [-i input_image] \ [-o output_cif] \ [-c {p[acked]|c[annonical]|[n[one]}] \ [-m {h[eaders]|n[oheaders]}] \ [-d {d[igest]|n[odigest]}] \ [-e {b[ase64]|q[uoted-printable]| \ d[ecimal]|h[exadecimal]|o[ctal]|n[one]}] \ [-b {f[orward]|b[ackwards]}] \ [input_image] [output_cif] the options are: -i input_image (default: stdin) the input_image file in MAR300, MAR345 or ADSC CCD detector format is given. If no input_image file is specified or is given as "-", an image is copied from stdin to a temporary file. -o output_cif (default: stdout) the output cif (if base64 or quoted-printable encoding is used) or cbf (if no encoding is used). if no output_cif is specified or is given as "-", the output is written to stdout -c compression_scheme (packed, canonical or none, default packed) -m [no]headers (default headers for cifs, noheaders for cbfs) selects MIME (N. Freed, N. Borenstein, RFC 2045, November 1996) headers within binary data value text fields. -d [no]digest (default md5 digest [R. Rivest, RFC 1321, April 1992 using"RSA Data Security, Inc. MD5 Message-Digest Algorithm"] when MIME headers are selected) -e encoding (base64, quoted-printable, decimal, hexadecimal, octal or none, default: base64) specifies one of the standard MIME encodings (base64 or quoted-printable) or a non-standard decimal, hexamdecimal or octal encoding for an ascii cif or "none" for a binary cbf -b direction (forward or backwards, default: backwards) specifies the direction of mapping of bytes into words for decimal, hexadecimal or octal output, marked by '>' for forward or '<' for backwards as the second character of each line of output, and in '#' comment lines. cif2cbf The test program cif2cbf uses the same command line options as img2cif, but accepts either a CIF or a CBF as input instead of an image file: cif2cbf [-i input_cif] [-o output_cbf] \ [-c {p[acked]|c[annonical]|{b[yte_offset]}|\ {v[2packed]}|{f[latpacked]}[n[one]}] \ [-m {h[eaders]|n[oheaders]}] [-d {d[igest]|n[odigest]}] \ [-e {b[ase64]|k|q[uoted-printable]| \ d[ecimal]|h[exadecimal]|o[ctal]|n[one]}] \ [-b {f[orward]|b[ackwards]}] \ [-p {0|1|2|4}] \ [-v dictionary]* [-w] \ [input_cif] [output_cbf] the options are: -i input_cif (default: stdin) the input file in CIF or CBF format. If input_cif is not specified or is given as "-", it is copied from stdin to a temporary file. -o output_cbf (default: stdout) the output cif (if base64 or quoted-printable encoding is used) or cbf (if no encoding is used). if no output_cif is specified or is given as "-", the output is written to stdout if the output_cbf is /dev/null, no output is written. The remaining options specify the characteristics of the output cbf. The characteristics of the input cif are derived from context. -c compression_scheme (packed, canonical, byte_offset, v2packed, flatpacked or none, default packed) -m [no]headers (default headers for cifs, noheaders for cbfs) selects MIME (N. Freed, N. Borenstein, RFC 2045, November 1996) headers within binary data value text fields. -d [no]digest (default md5 digest [R. Rivest, RFC 1321, April 1992 using"RSA Data Security, Inc. MD5 Message-Digest Algorithm"] when MIME headers are selected) -e encoding (base64, quoted-printable or none, default base64) specifies one of the standard MIME encodings for an ascii cif or "none" for a binary cbf -b byte_order (forward or backwards, default forward (1234) on little-endian machines, backwards (4321) on big-endian machines -p K_of_padding (0, 1, 2, 4) for no padding after binary data 1023, 2047 or 4095 bytes of padding after binary data -v dictionary specifies a dictionary to be used to validate the input cif and to apply aliases to the output cif. This option may be specified multiple times, with dictionaries layered in the order given. -w process wide (2048 character) lines convert_image The program convert_image requires two arguments: imagefile and cbffile. Those are the primary input and output. The detector type is extracted from the image file or from the command line, converted to lower case and used to construct the name of a template cbf file to use for the copy. The template file name is of the form template_name_columnsxrows. The full set of options is: convert_image [-i input_img] [-o output_cbf] [-p template_cbf]\ [-d detector name] -m [x|y|x=y] [-z distance] \ [-c category_alias=category_root]* \ [-t tag_alias=tag_root]* [-F] [-R] \ [input_img] [output_cbf] the options are: -i input_img (default: stdin) the input file as an image in smv, mar300, or mar345 format. If input_img is not specified or is given as "-", it is copied from stdin to a temporary file. -p template_cbf the template for the final cbf to be produced. If template_cbf is not specified the name is constructed from the first token of the detector name and the image size as template__x.cbf -o output_cbf (default: stdout ) the output cbf combining the image and the template. If the output_cbf is not specified or is given as "-", it is written to stdout. -d detectorname a detector name to be used if none is provided in the image header. -F when writing packed compression, treat the entire image as one line with no averaging -m [x|y|x=y] (default x=y, square arrays only) mirror the array in the x-axis (y -> -y) in the y-axis (x -> -x) or in x=y ( x -> y, y-> x) -r n rotate the array n times 90 degrees counter clockwise x -> y, y -> -x for each rotation, n = 1, 2 or 3 -R if setting a beam center, set reference values of axis settings as well as standard settings -z distance detector distance along Z-axis -c category_alias=category_root -t tag_alias=tagroot map the given alias to the given root, so that instead of outputting the alias, the root will be presented in the output cbf instead. These options may be repeated as many times as needed. convert_minicbf The program convert_minicbf requires two arguments: minicbf and cbffile. Those are the primary input and output. The detector type is extracted from the image file or from the command line, converted to lower case and used to construct the name of a template cbf file to use for the copy. The template file name is of the form template_name_columnsxrows. The full set of options is: convert_minicbf [-i input_cbf] [-o output_cbf] [-p template_cbf]\ [-q] [-C convention] \ [-d detector name] -m [x|y|x=y] [-z distance] \ [-c category_alias=category_root]* \ [-t tag_alias=tag_root]* [-F] [-R] \ [input_cbf] [output_cbf] the options are: -i input_cbf (default: stdin) the input file as a CBF with at least an image. -p template_cbf the template for the final cbf to be produced. If template_cbf is not specified the name is constructed from the first token of the detector name and the image size as template__x.cbf -o output_cbf (default: stdout ) the output cbf combining the image and the template. If the output_cbf is not specified or is given as "-", it is written to stdout. -q exit quickly with just the miniheader expanded after the data. No template is used. -Q exit quickly with just the miniheader unexpanded before the data. No template is used. -C convention convert the comment form of miniheader into the _array_data.header_convention convention _array_data.header_contents overriding any existing values -d detectorname a detector name to be used if none is provided in the image header. -F when writing packed compression, treat the entire image as one line with no averaging -m [x|y|x=y] (default x=y, square arrays only) mirror the array in the x-axis (y -> -y) in the y-axis (x -> -x) or in x=y ( x -> y, y-> x) -r n rotate the array n times 90 degrees counter clockwise x -> y, y -> -x for each rotation, n = 1, 2 or 3 -R if setting a beam center, set reference values of axis settings as well as standard settings -z distance detector distance along Z-axis -c category_alias=category_root -t tag_alias=tagroot map the given alias to the given root, so that instead of outputting the alias, the root will be presented in the output cbf instead. These options may be repeated as many times as needed. testreals, testflat and testflatpacked The example programs testreals, testflat and testflatpacked exercise the handling of reals, byte_offset compression and packed compression. Each is run without any arguments. testreals will read real images from the data file testrealin.cbf and write a file with real images in testrealout.cbf, which should be identical to testrealin.cbf. testflat and testflatpacked read 4 1000x1000 2D images and one 50x60x70 3D image and produce an output file that should be identical to the input. testflat reads testflatin.cbf and produces testflatout.cbf using CBF_BYTE_OFFSET compression. testflatpacked reads testflatpackedin.cbf and produces testflatpackedout.cbf. The images are: * A 1000 x 1000 array of 32-bit integers forming a flat field with all pixels set to 1000. * A 1000 x 1000 array of 16-bit integers forming a flat field with all pixels set to 1000. * A 1000 x 1000 array of 32-bit integers forming a flat field with all pixels set to 1000, except for -3 along the main diagonal and its transpose. * A 1000 x 1000 array of 16-bit integers forming a flat field with all pixels set to 1000, except for -3 along the main diagonal and its transpose. * A 50 x 60 x 70 array of 32-bit integers in a flat field of 1000, except for -3 along the main diagonal and the values i+j+k (counting from zero) every 1000th pixel test_fcb_read_image, test_xds_binary The example programs test_fcb_read_image and test_xds_binary are designed read the output of testflat and testflatpacked using the FCBlib routines in lib/libfcb. test_xds_binary reads only the first image and closes the file immediately. test_fcb_read_image reads all 5 images from the input file. The name of the input file should be provided on stdin, as in: * echo testflatout.cbf | bin/test_xds_binary * echo testflatpackedout.cbf | bin/test_xds_binary * echo testflatout.cbf | bin/test_fcb_read_image * echo testflatpackedout.cbf | bin/test_fcb_read_image In order to compile these programs correctly for the G95 compiler it is important to set the record size for reading to be no larger than the padding after binary images. This in controlled in Makefile by the line M4FLAGS = -Dfcb_bytes_in_rec=131072 which provides good performance for gfortran. For g95, this line must be changed to M4FLAGS = -Dfcb_bytes_in_rec=4096 sauter_test The program sauter_test.C is a C++ test program contributed by Nick Sauter to help in resolving a memory leak he found. The program is run as bin/sauter_test and should run long enough to allow a check with top to ensure that it has constant memory demands. In addition, starting with release 0.7.8.1, the addition of -DCBFLIB_MEM_DEBUG to the compiler flags will cause detailed reports on memory use to stderr to be reported. adscimg2cbf The example program adscimg2cbf accepts any number of raw or compressed ADSC images with .img, .img.gz, .img.bz2 or .img.Z extensions and converts each of them to an imgCIF/CBF file with a .cbf extension. adscimg2cbf [--flag[,modifier]] file1.img ... filen.img (creates file1.cbf ... filen.cbf) Image files may also be compressed (.gz, .bz2, .Z) Flags: --cbf_byte_offset Use BYTE_OFFSET compression (DEFAULT) --cbf_packed Use CCP4 packing (JPA) compression. --cbf_packed_v2 Use CCP4 packing version 2 (JPA) compression. --no_compression No compression. The following two modifiers can be appended to the flags (syntax: --flag,modifier): flat Flat (linear) images. uncorrelated Uncorrelated sections. adscimg2cbf The example program cbf2adscimg accepts any number of cbfs of ADSC images created by adscimg1cbf or convert_image and produces raw or compressed adsc image files with .img, .img.gz or .img.bz2 extensions. cbf2adscimg [--flag] file1.cbf ... filen.cbf (creates file1.img ... filen.img) Image files may be compressed on output: (.gz, .bz2) by using the flags below.\n"); Flags: --gz Output a .gz file (e.g., filen.img.gz). --bz2 Output a .bz2 file (e.g., filen.img.bz2). ---------------------------------------------------------------------- ---------------------------------------------------------------------- Updated 15 July 2009. Contact: yaya at bernstein-plus-sons dot com ./CBFlib-0.9.2.2/pycbf/win32.bat0000644000076500007650000000072211603702120014330 0ustar yayayaya nuweb pycbf latex pycbf nuweb pycbf latex pycbf dvipdfm pycbf nuweb pycbf C:\python24\python make_pycbf.py > TODO.txt "C:\program files\swigwin-1.3.31\swig.exe" -python pycbf.i C:\python24\python setup.py build --compiler=mingw32 copy build\lib.win32-2.4\_pycbf.pyd . REM C:\python24\python pycbf_test1.py C:\python24\python pycbf_test2.py C:\python24\python pycbf_test3.py C:\python24\lib\pydoc.py -w pycbf C:\python24\python makeflatascii.py pycbf_ascii_help.txt ./CBFlib-0.9.2.2/pycbf/cbfgoniometerwrappers.i0000644000076500007650000001753011603702120017464 0ustar yayayaya // Tell SWIG not to make constructor for these objects %nodefault cbf_positioner_struct; %nodefault cbf_goniometer; %nodefault cbf_axis_struct; // Tell SWIG what the object is, so we can build the class typedef struct { double matrix [3][4]; cbf_axis_struct *axis; size_t axes; int matrix_is_valid, axes_are_connected; } cbf_positioner_struct; typedef cbf_positioner_struct *cbf_goniometer; %feature("autodoc","1"); %extend cbf_positioner_struct{// Tell SWIG to attach functions to the structure cbf_positioner_struct(){ // Constructor // DO NOT CONSTRUCT WITHOUT A CBFHANDLE cbf_failnez(CBF_ARGUMENT); return NULL; /* Should never be executed */ } ~cbf_positioner_struct(){ // Destructor cbf_failnez(cbf_free_goniometer(self)); } %feature("autodoc", " Returns : Float start,Float increment *args : C prototype: int cbf_get_rotation_range (cbf_goniometer goniometer, unsigned int reserved, double *start, double *increment); CBFLib documentation: DESCRIPTION cbf_get_rotation_range sets *start and *increment to the corresponding values of the goniometer rotation axis used for the exposure. Either of the destination pointers may be NULL. The parameter reserved is presently unused and should be set to 0. ARGUMENTS goniometer Goniometer handle. reserved Unused. Any value other than 0 is invalid. start Pointer to the destination start value. increment Pointer to the destination increment value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_rotation_range; %apply double *OUTPUT {double *start,double *increment}; void get_rotation_range(double *start,double *increment){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_get_rotation_range (self,reserved, start,increment)); } %feature("autodoc", " Returns : double final1,double final2,double final3 *args : double ratio,double initial1,double initial2,double initial3 C prototype: int cbf_rotate_vector (cbf_goniometer goniometer, unsigned int reserved, double ratio, double initial1, double initial2, double initial3, double *final1, double *final2, double *final3); CBFLib documentation: DESCRIPTION cbf_rotate_vector sets *final1, *final2, and *final3 to the 3 components of the of the vector (initial1, initial2, initial3) after reorientation by applying the goniometer rotations. The value ratio specif ies the goniometer setting and varies from 0.0 at the beginning of the exposure to 1.0 at the end, irrespective of the actual rotation range. Any of the destination pointers may be NULL. The parameter reserved is presently unused and should be set to 0. ARGUMENTS goniometer Goniometer handle. reserved Unused. Any value other than 0 is invalid. ratio Goniometer setting. 0 = beginning of exposure, 1 = end. initial1 x component of the initial vector. initial2 y component of the initial vector. initial3 z component of the initial vector. vector1 Pointer to the destination x component of the final vector. vector2 Pointer to the destination y component of the final vector. vector3 Pointer to the destination z component of the final vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")rotate_vector; %apply double *OUTPUT {double *final1, double *final2, double *final3}; void rotate_vector (double ratio, double initial1,double initial2, double initial3, double *final1, double *final2, double *final3){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_rotate_vector (self, reserved, ratio, initial1, initial2, initial3, final1, final2, final3)); } %feature("autodoc", " Returns : double reciprocal1,double reciprocal2,double reciprocal3 *args : double ratio,double wavelength,double real1,double real2,double real3 C prototype: int cbf_get_reciprocal (cbf_goniometer goniometer, unsigned int reserved, double ratio, double wavelength, double real1, double real2, double real3, double *reciprocal1, double *reciprocal2, double *reciprocal3); CBFLib documentation: DESCRIPTION cbf_get_reciprocal sets *reciprocal1, * reciprocal2, and * reciprocal3 to the 3 components of the of the reciprocal-space vector corresponding to the real-space vector (real1, real2, real3). The reciprocal-space vector is oriented to correspond to the goniometer setting with all axes at 0. The value wavelength is the wavlength in AA and the value ratio specifies the current goniometer setting and varies from 0.0 at the beginning of the exposur e to 1.0 at the end, irrespective of the actual rotation range. Any of the destination pointers may be NULL. The parameter reserved is presently unused and should be set to 0. ARGUMENTS goniometer Goniometer handle. reserved Unused. Any value other than 0 is invalid. ratio Goniometer setting. 0 = beginning of exposure, 1 = end. wavelength Wavelength in AA. real1 x component of the real-space vector. real2 y component of the real-space vector. real3 z component of the real-space vector. reciprocal1 Pointer to the destination x component of the reciprocal-space vector. reciprocal2 Pointer to the destination y component of the reciprocal-space vector. reciprocal3 Pointer to the destination z component of the reciprocal-space vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_reciprocal; %apply double *OUTPUT {double *reciprocal1,double *reciprocal2, double *reciprocal3}; void get_reciprocal (double ratio,double wavelength, double real1, double real2, double real3, double *reciprocal1,double *reciprocal2, double *reciprocal3){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_get_reciprocal(self,reserved, ratio, wavelength, real1, real2, real3,reciprocal1, reciprocal2,reciprocal3)); } %feature("autodoc", " Returns : double vector1,double vector2,double vector3 *args : C prototype: int cbf_get_rotation_axis (cbf_goniometer goniometer, unsigned int reserved, double *vector1, double *vector2, double *vector3); CBFLib documentation: DESCRIPTION cbf_get_rotation_axis sets *vector1, *vector2, and *vector3 to the 3 components of the goniometer rotation axis used for the exposure. Any of the destination pointers may be NULL. The parameter reserved is presently unused and should be set to 0. ARGUMENTS goniometer Goniometer handle. reserved Unused. Any value other than 0 is invalid. vector1 Pointer to the destination x component of the rotation axis. vector2 Pointer to the destination y component of the rotation axis. vector3 Pointer to the destination z component of the rotation axis. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_rotation_axis; %apply double *OUTPUT {double *vector1, double *vector2, double *vector3}; void get_rotation_axis (double *vector1, double *vector2, double *vector3){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_get_rotation_axis (self, reserved, vector1, vector2, vector3)); } }; // End of cbf_positioner ./CBFlib-0.9.2.2/pycbf/cbfdetectorwrappers.i0000644000076500007650000017304111603702120017125 0ustar yayayaya // Tell SWIG not to make constructor for these objects %nodefault cbf_detector_struct; %nodefault cbf_detector; // Tell SWIG what the object is, so we can build the class typedef struct { cbf_positioner positioner; double displacement [2], increment [2]; size_t axes, index [2]; } cbf_detector_struct; typedef cbf_detector_struct *cbf_detector; %feature("autodoc","1"); %extend cbf_detector_struct{// Tell SWIG to attach functions to the structure cbf_detector_struct(){ // Constructor // DO NOT CONSTRUCT WITHOUT A CBFHANDLE cbf_failnez(CBF_ARGUMENT); return NULL; /* Should never be executed */ } ~cbf_detector_struct(){ // Destructor cbf_failnez(cbf_free_detector(self)); } %feature("autodoc", " Returns : *args : double indexfast,double indexslow,double centerfast,double centerslow C prototype: int cbf_set_reference_beam_center_fs (cbf_detector detector, double *indexfast, double *indexslow, double *centerfast, double *centerslow); CBFLib documentation: DESCRIPTION cbf_get_beam_center sets *centerfast and *centerslow to the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector and *indexfast and *indexslow to the corresponding indices. cbf_set_beam_center sets the offsets in the axis category for the detector element axis with precedence 1 to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given *indexfast and *indexslow. cbf_set_reference_beam_center sets the displacments in the array_structure_list_axis category to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given by *indexfast and *indexslow. In order to achieve consistent results, a reference detector should be used for detector to have all axes at their reference settings. Note that the precedence 1 axis is the fastest axis, so that *centerfast and *indexfast are the fast axis components of the center and *centerslow and *indexslow are the slow axis components of the center. The _fs calls give the displacments in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the displacements in slow-to-fast order Any of the destination pointers may be NULL for getting the beam center. For setting the beam axis, either the indices of the center must not be NULL. The indices are non-negative for beam centers within the detector surface, but the center for an axis with a negative increment will be negative for a beam center within the detector surface. For cbf_set_beam_center if the diffrn_data_frame category exists with a row for the corresponding element id, the values will be set for _diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in millimetres and the value of _diffrn_data_frame.center_units will be set to 'mm'. For cbf_set_reference_beam_center if the diffrn_detector_element category exists with a row for the corresponding element id, the values will be set for _diffrn_detector_element.reference_center_fast and _diffrn_detector_element.reference_center_slow in millimetres and the value of _diffrn_detector_element.reference_units will be set to 'mm'. ARGUMENTS detector Detector handle. indexfast Pointer to the destination fast index. indexslow Pointer to the destination slow index. centerfast Pointer to the destination displacement along the fast axis. centerslow Pointer to the destination displacement along the slow axis. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_reference_beam_center_fs; void set_reference_beam_center_fs(double *indexfast, double *indexslow, double *centerfast,double *centerslow){ cbf_failnez(cbf_set_reference_beam_center_fs(self, indexfast, indexslow, centerfast, centerslow)); } %feature("autodoc", " Returns : double coordinate1,double coordinate2,double coordinate3 *args : double indexfast,double indexslow C prototype: int cbf_get_pixel_coordinates_fs (cbf_detector detector, double indexfast, double indexslow, double *coordinate1, double *coordinate2, double *coordinate3); CBFLib documentation: DESCRIPTION cbf_get_pixel_coordinates, cbf_get_pixel_coordinates_fs and cbf_get_pixel_coordinates_sf ses *coordinate1, *coordinate2, and *coordinate3 to the vector position of pixel (indexfast, indexslow) on the detector surface. If indexslow and indexfast are integers then the coordinates correspond to the center of a pixel. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. indexslow Slow index. indexfast Fast index. coordinate1 Pointer to the destination x component. coordinate2 Pointer to the destination y component. coordinate3 Pointer to the destination z component. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_pixel_coordinates_fs; %apply double *OUTPUT {double *coordinate1, double *coordinate2, double *coordinate3}; void get_pixel_coordinates_fs(double indexfast, double indexslow, double *coordinate1, double *coordinate2, double *coordinate3){ cbf_failnez(cbf_get_pixel_coordinates_fs(self, indexfast, indexslow, coordinate1, coordinate2, coordinate3)); } %feature("autodoc", " Returns : *args : double indexfast,double indexslow,double centerfast,double centerslow C prototype: int cbf_set_beam_center_fs (cbf_detector detector, double *indexfast, double *indexslow, double *centerfast, double *centerslow); CBFLib documentation: DESCRIPTION cbf_get_beam_center sets *centerfast and *centerslow to the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector and *indexfast and *indexslow to the corresponding indices. cbf_set_beam_center sets the offsets in the axis category for the detector element axis with precedence 1 to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given *indexfast and *indexslow. cbf_set_reference_beam_center sets the displacments in the array_structure_list_axis category to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given by *indexfast and *indexslow. In order to achieve consistent results, a reference detector should be used for detector to have all axes at their reference settings. Note that the precedence 1 axis is the fastest axis, so that *centerfast and *indexfast are the fast axis components of the center and *centerslow and *indexslow are the slow axis components of the center. The _fs calls give the displacments in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the displacements in slow-to-fast order Any of the destination pointers may be NULL for getting the beam center. For setting the beam axis, either the indices of the center must not be NULL. The indices are non-negative for beam centers within the detector surface, but the center for an axis with a negative increment will be negative for a beam center within the detector surface. For cbf_set_beam_center if the diffrn_data_frame category exists with a row for the corresponding element id, the values will be set for _diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in millimetres and the value of _diffrn_data_frame.center_units will be set to 'mm'. For cbf_set_reference_beam_center if the diffrn_detector_element category exists with a row for the corresponding element id, the values will be set for _diffrn_detector_element.reference_center_fast and _diffrn_detector_element.reference_center_slow in millimetres and the value of _diffrn_detector_element.reference_units will be set to 'mm'. ARGUMENTS detector Detector handle. indexfast Pointer to the destination fast index. indexslow Pointer to the destination slow index. centerfast Pointer to the destination displacement along the fast axis. centerslow Pointer to the destination displacement along the slow axis. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_beam_center_fs; void set_beam_center_fs(double *indexfast, double *indexslow, double *centerfast,double *centerslow){ cbf_failnez(cbf_set_beam_center_fs(self, indexfast, indexslow, centerfast, centerslow)); } %feature("autodoc", " Returns : Float pixel size *args : Int axis_number C prototype: int cbf_get_inferred_pixel_size (cbf_detector detector, int axis_number, double *psize); CBFLib documentation: DESCRIPTION cbf_get_inferred_pixel_size, cbf_get_inferred_pixel_size_sf set *psize to point to the double value in millimeters of the pixel size for the axis axis_number value. The slow index is treated as axis 1 and the next faster index is treated as axis 2. cbf_get_inferred_pixel_size_fs sets *psize to point to the double value in millimeters of the pixel size for the axis axis_number value. The fast index is treated as axis 1 and the next slower index is treated as axis 2. If the axis number is negative, the axes are used in the reverse order so that an axis_number of -1 indicates the fast axes in a call to cbf_get_inferred_pixel_size or cbf_get_inferred_pixel_size_sf and indicates the fast axis in a call to cbf_get_inferred_pixel_size_fs. ARGUMENTS detector Detector handle. axis_number The number of the axis. area Pointer to the destination pizel size in mm. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_inferred_pixel_size; %apply double *OUTPUT { double *psize } get_inferred_pixel_size; void get_inferred_pixel_size(unsigned int axis_number, double* psize){ cbf_failnez(cbf_get_inferred_pixel_size(self, axis_number, psize)); } %feature("autodoc", " Returns : double area,double projected_area *args : double index1,double index2 C prototype: int cbf_get_pixel_area (cbf_detector detector, double indexslow, double indexfast, double *area, double *projected_area); CBFLib documentation: DESCRIPTION cbf_get_pixel_area, cbf_get_pixel_area_fs and cbf_get_pixel_area_sf set *area to the area of the pixel at (indexfast, indexslow) on the detector surface and *projected_area to the apparent area of the pixel as viewed from the sample position, with indexslow being the slow axis and indexfast being the fast axis. Either of the destination pointers may be NULL. ARGUMENTS detector Detector handle. indexfast Fast index. indexslow Slow index. area Pointer to the destination area in mm2. projected_area Pointer to the destination apparent area in mm2. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_pixel_area; %apply double *OUTPUT{double *area,double *projected_area}; void get_pixel_area(double index1, double index2, double *area,double *projected_area){ cbf_failnez(cbf_get_pixel_area (self, index1, index2, area,projected_area)); } %feature("autodoc", " Returns : double normal1,double normal2,double normal3 *args : double indexfast,double indexslow C prototype: int cbf_get_pixel_normal_fs (cbf_detector detector, double indexfast, double indexslow, double *normal1, double *normal2, double *normal3); CBFLib documentation: DESCRIPTION cbf_get_detector_normal, cbf_get_pixel_normal_fs and cbf_get_pixel_normal_sf set *normal1, *normal2, and *normal3 to the 3 components of the of the normal vector to the pixel at (indexfast, indexslow). The vector is normalized. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. indexslow Slow index. indexfast Fast index. normal1 Pointer to the destination x component of the normal vector. normal2 Pointer to the destination y component of the normal vector. normal3 Pointer to the destination z component of the normal vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_pixel_normal_fs; %apply double *OUTPUT {double *normal1,double *normal2, double *normal3}; void get_pixel_normal_fs ( double indexfast, double indexslow, double *normal1,double *normal2, double *normal3){ cbf_failnez(cbf_get_pixel_normal_fs(self, indexfast,indexslow,normal1,normal2,normal3)); } %feature("autodoc", " Returns : double slowaxis1,double slowaxis2,double slowaxis3,double fastaxis1, double fastaxis2,double fastaxis3 *args : C prototype: int cbf_get_detector_axes (cbf_detector detector, double *slowaxis1, double *slowaxis2, double *slowaxis3, double *fastaxis1, double *fastaxis2, double *fastaxis3); CBFLib documentation: DESCRIPTION cbf_get_detector_axis_slow sets *slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the slow axis of the specified detector at the current settings of all axes. cbf_get_detector_axis_slow sets *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 components of the fast axis of the specified detector at the current settings of all axes. cbf_get_detector_axes, cbf_get_detector_axes_fs and int cbf_get_detector_axes_sf set *slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the slow axis and *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 components of the fast axis of the specified detector at the current settings of all axes. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. slowaxis1 Pointer to the destination x component of the slow axis vector. slowaxis2 Pointer to the destination y component of the slow axis vector. slowaxis3 Pointer to the destination z component of the slow axis vector. fastaxis1 Pointer to the destination x component of the fast axis vector. fastaxis2 Pointer to the destination y component of the fast axis vector. fastaxis3 Pointer to the destination z component of the fast axis vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_detector_axes; %apply double *OUTPUT {double *slowaxis1, double *slowaxis2, double *slowaxis3, double *fastaxis1, double *fastaxis2, double *fastaxis3}; void get_detector_axes ( double *slowaxis1, double *slowaxis2, double *slowaxis3, double *fastaxis1, double *fastaxis2, double *fastaxis3){ cbf_failnez(cbf_get_detector_axes(self, slowaxis1,slowaxis2,slowaxis3, fastaxis1,fastaxis2,fastaxis3)); } %feature("autodoc", " Returns : *args : double indexslow,double indexfast,double centerslow,double centerfast C prototype: int cbf_set_reference_beam_center (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast); CBFLib documentation: DESCRIPTION cbf_get_beam_center sets *centerfast and *centerslow to the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector and *indexfast and *indexslow to the corresponding indices. cbf_set_beam_center sets the offsets in the axis category for the detector element axis with precedence 1 to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given *indexfast and *indexslow. cbf_set_reference_beam_center sets the displacments in the array_structure_list_axis category to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given by *indexfast and *indexslow. In order to achieve consistent results, a reference detector should be used for detector to have all axes at their reference settings. Note that the precedence 1 axis is the fastest axis, so that *centerfast and *indexfast are the fast axis components of the center and *centerslow and *indexslow are the slow axis components of the center. The _fs calls give the displacments in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the displacements in slow-to-fast order Any of the destination pointers may be NULL for getting the beam center. For setting the beam axis, either the indices of the center must not be NULL. The indices are non-negative for beam centers within the detector surface, but the center for an axis with a negative increment will be negative for a beam center within the detector surface. For cbf_set_beam_center if the diffrn_data_frame category exists with a row for the corresponding element id, the values will be set for _diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in millimetres and the value of _diffrn_data_frame.center_units will be set to 'mm'. For cbf_set_reference_beam_center if the diffrn_detector_element category exists with a row for the corresponding element id, the values will be set for _diffrn_detector_element.reference_center_fast and _diffrn_detector_element.reference_center_slow in millimetres and the value of _diffrn_detector_element.reference_units will be set to 'mm'. ARGUMENTS detector Detector handle. indexfast Pointer to the destination fast index. indexslow Pointer to the destination slow index. centerfast Pointer to the destination displacement along the fast axis. centerslow Pointer to the destination displacement along the slow axis. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_reference_beam_center; void set_reference_beam_center(double *indexslow, double *indexfast, double *centerslow,double *centerfast){ cbf_failnez(cbf_set_reference_beam_center(self, indexslow, indexfast, centerslow, centerfast)); } %feature("autodoc", " Returns : double slowaxis1,double slowaxis2,double slowaxis3 *args : C prototype: int cbf_get_detector_axis_slow (cbf_detector detector, double *slowaxis1, double *slowaxis2, double *slowaxis3); CBFLib documentation: DESCRIPTION cbf_get_detector_axis_slow sets *slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the slow axis of the specified detector at the current settings of all axes. cbf_get_detector_axis_slow sets *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 components of the fast axis of the specified detector at the current settings of all axes. cbf_get_detector_axes, cbf_get_detector_axes_fs and int cbf_get_detector_axes_sf set *slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the slow axis and *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 components of the fast axis of the specified detector at the current settings of all axes. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. slowaxis1 Pointer to the destination x component of the slow axis vector. slowaxis2 Pointer to the destination y component of the slow axis vector. slowaxis3 Pointer to the destination z component of the slow axis vector. fastaxis1 Pointer to the destination x component of the fast axis vector. fastaxis2 Pointer to the destination y component of the fast axis vector. fastaxis3 Pointer to the destination z component of the fast axis vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_detector_axis_slow; %apply double *OUTPUT {double *slowaxis1, double *slowaxis2, double *slowaxis3}; void get_detector_axis_slow ( double *slowaxis1, double *slowaxis2, double *slowaxis3){ cbf_failnez(cbf_get_detector_axis_slow(self, slowaxis1,slowaxis2,slowaxis3)); } %feature("autodoc", " Returns : double distance *args : C prototype: int cbf_get_detector_distance (cbf_detector detector, double *distance); CBFLib documentation: DESCRIPTION cbf_get_detector_distance sets *distance to the nearest distance from the sample position to the detector plane. ARGUMENTS detector Detector handle. distance Pointer to the destination distance. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_detector_distance; %apply double *OUTPUT {double *distance}; void get_detector_distance (double *distance){ cbf_failnez(cbf_get_detector_distance(self,distance)); } %feature("autodoc", " Returns : Float pixel size *args : Int axis_number C prototype: int cbf_get_inferred_pixel_size_fs(cbf_detector detector, int axis_number, double *psize); CBFLib documentation: DESCRIPTION cbf_get_inferred_pixel_size, cbf_get_inferred_pixel_size_sf set *psize to point to the double value in millimeters of the pixel size for the axis axis_number value. The slow index is treated as axis 1 and the next faster index is treated as axis 2. cbf_get_inferred_pixel_size_fs sets *psize to point to the double value in millimeters of the pixel size for the axis axis_number value. The fast index is treated as axis 1 and the next slower index is treated as axis 2. If the axis number is negative, the axes are used in the reverse order so that an axis_number of -1 indicates the fast axes in a call to cbf_get_inferred_pixel_size or cbf_get_inferred_pixel_size_sf and indicates the fast axis in a call to cbf_get_inferred_pixel_size_fs. ARGUMENTS detector Detector handle. axis_number The number of the axis. area Pointer to the destination pizel size in mm. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_inferred_pixel_size_fs; %apply double *OUTPUT { double *psize } get_inferred_pixel_size; void get_inferred_pixel_size_fs(unsigned int axis_number, double* psize){ cbf_failnez(cbf_get_inferred_pixel_size_fs(self, axis_number, psize)); } %feature("autodoc", " Returns : double normal1,double normal2,double normal3 *args : C prototype: int cbf_get_detector_normal (cbf_detector detector, double *normal1, double *normal2, double *normal3); CBFLib documentation: DESCRIPTION cbf_get_detector_normal sets *normal1, *normal2, and *normal3 to the 3 components of the of the normal vector to the detector plane. The vector is normalized. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. normal1 Pointer to the destination x component of the normal vector. normal2 Pointer to the destination y component of the normal vector. normal3 Pointer to the destination z component of the normal vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_detector_normal; %apply double *OUTPUT {double *normal1, double *normal2, double *normal3}; void get_detector_normal(double *normal1, double *normal2, double *normal3){ cbf_failnez(cbf_get_detector_normal(self, normal1, normal2, normal3)); } %feature("autodoc", " Returns : double fastaxis1,double fastaxis2,double fastaxis3 *args : C prototype: int cbf_get_detector_axis_fast (cbf_detector detector, double *fastaxis1, double *fastaxis2, double *fastaxis3); CBFLib documentation: DESCRIPTION cbf_get_detector_axis_slow sets *slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the slow axis of the specified detector at the current settings of all axes. cbf_get_detector_axis_slow sets *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 components of the fast axis of the specified detector at the current settings of all axes. cbf_get_detector_axes, cbf_get_detector_axes_fs and int cbf_get_detector_axes_sf set *slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the slow axis and *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 components of the fast axis of the specified detector at the current settings of all axes. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. slowaxis1 Pointer to the destination x component of the slow axis vector. slowaxis2 Pointer to the destination y component of the slow axis vector. slowaxis3 Pointer to the destination z component of the slow axis vector. fastaxis1 Pointer to the destination x component of the fast axis vector. fastaxis2 Pointer to the destination y component of the fast axis vector. fastaxis3 Pointer to the destination z component of the fast axis vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_detector_axis_fast; %apply double *OUTPUT {double *fastaxis1, double *fastaxis2, double *fastaxis3}; void get_detector_axis_fast ( double *fastaxis1, double *fastaxis2, double *fastaxis3){ cbf_failnez(cbf_get_detector_axis_fast(self, fastaxis1,fastaxis2,fastaxis3)); } %feature("autodoc", " Returns : double fastaxis1,double fastaxis2,double fastaxis3,double slowaxis1, double slowaxis2,double slowaxis3 *args : C prototype: int cbf_get_detector_axes_fs (cbf_detector detector, double *fastaxis1, double *fastaxis2, double *fastaxis3, double *slowaxis1, double *slowaxis2, double *slowaxis3); CBFLib documentation: DESCRIPTION cbf_get_detector_axis_slow sets *slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the slow axis of the specified detector at the current settings of all axes. cbf_get_detector_axis_slow sets *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 components of the fast axis of the specified detector at the current settings of all axes. cbf_get_detector_axes, cbf_get_detector_axes_fs and int cbf_get_detector_axes_sf set *slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the slow axis and *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 components of the fast axis of the specified detector at the current settings of all axes. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. slowaxis1 Pointer to the destination x component of the slow axis vector. slowaxis2 Pointer to the destination y component of the slow axis vector. slowaxis3 Pointer to the destination z component of the slow axis vector. fastaxis1 Pointer to the destination x component of the fast axis vector. fastaxis2 Pointer to the destination y component of the fast axis vector. fastaxis3 Pointer to the destination z component of the fast axis vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_detector_axes; %apply double *OUTPUT {double *slowaxis1, double *slowaxis2, double *slowaxis3, double *fastaxis1, double *fastaxis2, double *fastaxis3}; void get_detector_axes_fs ( double *fastaxis1, double *fastaxis2, double *fastaxis3, double *slowaxis1, double *slowaxis2, double *slowaxis3){ cbf_failnez(cbf_get_detector_axes(self, slowaxis1,slowaxis2,slowaxis3, fastaxis1,fastaxis2,fastaxis3)); } %feature("autodoc", " Returns : double slowaxis1,double slowaxis2,double slowaxis3,double fastaxis1, double fastaxis2,double fastaxis3 *args : C prototype: int cbf_get_detector_axes_sf (cbf_detector detector, double *slowaxis1, double *slowaxis2, double *slowaxis3, double *fastaxis1, double *fastaxis2, double *fastaxis3); CBFLib documentation: DESCRIPTION cbf_get_detector_axis_slow sets *slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the slow axis of the specified detector at the current settings of all axes. cbf_get_detector_axis_slow sets *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 components of the fast axis of the specified detector at the current settings of all axes. cbf_get_detector_axes, cbf_get_detector_axes_fs and int cbf_get_detector_axes_sf set *slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the slow axis and *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 components of the fast axis of the specified detector at the current settings of all axes. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. slowaxis1 Pointer to the destination x component of the slow axis vector. slowaxis2 Pointer to the destination y component of the slow axis vector. slowaxis3 Pointer to the destination z component of the slow axis vector. fastaxis1 Pointer to the destination x component of the fast axis vector. fastaxis2 Pointer to the destination y component of the fast axis vector. fastaxis3 Pointer to the destination z component of the fast axis vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_detector_axes_sf; %apply double *OUTPUT {double *slowaxis1, double *slowaxis2, double *slowaxis3, double *fastaxis1, double *fastaxis2, double *fastaxis3}; void get_detector_axes_sf ( double *slowaxis1, double *slowaxis2, double *slowaxis3, double *fastaxis1, double *fastaxis2, double *fastaxis3){ cbf_failnez(cbf_get_detector_axes(self, slowaxis1,slowaxis2,slowaxis3, fastaxis1,fastaxis2,fastaxis3)); } %feature("autodoc", " Returns : double coordinate1,double coordinate2,double coordinate3 *args : double indexslow,double indexfast C prototype: int cbf_get_pixel_coordinates_sf (cbf_detector detector, double indexslow, double indexfast, double *coordinate1, double *coordinate2, double *coordinate3); CBFLib documentation: DESCRIPTION cbf_get_pixel_coordinates, cbf_get_pixel_coordinates_fs and cbf_get_pixel_coordinates_sf ses *coordinate1, *coordinate2, and *coordinate3 to the vector position of pixel (indexfast, indexslow) on the detector surface. If indexslow and indexfast are integers then the coordinates correspond to the center of a pixel. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. indexslow Slow index. indexfast Fast index. coordinate1 Pointer to the destination x component. coordinate2 Pointer to the destination y component. coordinate3 Pointer to the destination z component. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_pixel_coordinates_sf; %apply double *OUTPUT {double *coordinate1, double *coordinate2, double *coordinate3}; void get_pixel_coordinates_sf(double indexslow, double indexfast, double *coordinate1, double *coordinate2, double *coordinate3){ cbf_failnez(cbf_get_pixel_coordinates_sf(self, indexslow, indexfast, coordinate1, coordinate2, coordinate3)); } %feature("autodoc", " Returns : *args : double indexslow,double indexfast,double centerslow,double centerfast C prototype: int cbf_set_beam_center (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast); CBFLib documentation: DESCRIPTION cbf_get_beam_center sets *centerfast and *centerslow to the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector and *indexfast and *indexslow to the corresponding indices. cbf_set_beam_center sets the offsets in the axis category for the detector element axis with precedence 1 to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given *indexfast and *indexslow. cbf_set_reference_beam_center sets the displacments in the array_structure_list_axis category to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given by *indexfast and *indexslow. In order to achieve consistent results, a reference detector should be used for detector to have all axes at their reference settings. Note that the precedence 1 axis is the fastest axis, so that *centerfast and *indexfast are the fast axis components of the center and *centerslow and *indexslow are the slow axis components of the center. The _fs calls give the displacments in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the displacements in slow-to-fast order Any of the destination pointers may be NULL for getting the beam center. For setting the beam axis, either the indices of the center must not be NULL. The indices are non-negative for beam centers within the detector surface, but the center for an axis with a negative increment will be negative for a beam center within the detector surface. For cbf_set_beam_center if the diffrn_data_frame category exists with a row for the corresponding element id, the values will be set for _diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in millimetres and the value of _diffrn_data_frame.center_units will be set to 'mm'. For cbf_set_reference_beam_center if the diffrn_detector_element category exists with a row for the corresponding element id, the values will be set for _diffrn_detector_element.reference_center_fast and _diffrn_detector_element.reference_center_slow in millimetres and the value of _diffrn_detector_element.reference_units will be set to 'mm'. ARGUMENTS detector Detector handle. indexfast Pointer to the destination fast index. indexslow Pointer to the destination slow index. centerfast Pointer to the destination displacement along the fast axis. centerslow Pointer to the destination displacement along the slow axis. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_beam_center; void set_beam_center(double *indexslow, double *indexfast, double *centerslow,double *centerfast){ cbf_failnez(cbf_set_beam_center(self, indexslow, indexfast, centerslow, centerfast)); } %feature("autodoc", " Returns : double area,double projected_area *args : double indexfast,double indexslow C prototype: int cbf_get_pixel_area_fs(cbf_detector detector, double indexfast, double indexslow, double *area, double *projected_area); CBFLib documentation: DESCRIPTION cbf_get_pixel_area, cbf_get_pixel_area_fs and cbf_get_pixel_area_sf set *area to the area of the pixel at (indexfast, indexslow) on the detector surface and *projected_area to the apparent area of the pixel as viewed from the sample position, with indexslow being the slow axis and indexfast being the fast axis. Either of the destination pointers may be NULL. ARGUMENTS detector Detector handle. indexfast Fast index. indexslow Slow index. area Pointer to the destination area in mm2. projected_area Pointer to the destination apparent area in mm2. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_pixel_area_fs; %apply double *OUTPUT{double *area,double *projected_area}; void get_pixel_area_fs(double indexfast, double indexslow, double *area,double *projected_area){ cbf_failnez(cbf_get_pixel_area_fs (self, indexfast, indexslow, area,projected_area)); } %feature("autodoc", " Returns : double indexfast,double indexslow,double centerfast,double centerslow *args : C prototype: int cbf_get_beam_center_fs (cbf_detector detector, double *indexfast, double *indexslow, double *centerfast, double *centerslow); CBFLib documentation: DESCRIPTION cbf_get_beam_center sets *centerfast and *centerslow to the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector and *indexfast and *indexslow to the corresponding indices. cbf_set_beam_center sets the offsets in the axis category for the detector element axis with precedence 1 to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given *indexfast and *indexslow. cbf_set_reference_beam_center sets the displacments in the array_structure_list_axis category to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given by *indexfast and *indexslow. In order to achieve consistent results, a reference detector should be used for detector to have all axes at their reference settings. Note that the precedence 1 axis is the fastest axis, so that *centerfast and *indexfast are the fast axis components of the center and *centerslow and *indexslow are the slow axis components of the center. The _fs calls give the displacments in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the displacements in slow-to-fast order Any of the destination pointers may be NULL for getting the beam center. For setting the beam axis, either the indices of the center must not be NULL. The indices are non-negative for beam centers within the detector surface, but the center for an axis with a negative increment will be negative for a beam center within the detector surface. For cbf_set_beam_center if the diffrn_data_frame category exists with a row for the corresponding element id, the values will be set for _diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in millimetres and the value of _diffrn_data_frame.center_units will be set to 'mm'. For cbf_set_reference_beam_center if the diffrn_detector_element category exists with a row for the corresponding element id, the values will be set for _diffrn_detector_element.reference_center_fast and _diffrn_detector_element.reference_center_slow in millimetres and the value of _diffrn_detector_element.reference_units will be set to 'mm'. ARGUMENTS detector Detector handle. indexfast Pointer to the destination fast index. indexslow Pointer to the destination slow index. centerfast Pointer to the destination displacement along the fast axis. centerslow Pointer to the destination displacement along the slow axis. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_beam_center_fs; %apply double *OUTPUT {double *indexfast, double *indexslow, double *centerfast,double *centerslow}; void get_beam_center_fs(double *indexfast, double *indexslow, double *centerfast,double *centerslow){ cbf_failnez(cbf_get_beam_center_fs(self, indexfast, indexslow, centerfast, centerslow)); } %feature("autodoc", " Returns : Float pixel size *args : Int axis_number C prototype: int cbf_get_inferred_pixel_size_sf(cbf_detector detector, int axis_number, double *psize); CBFLib documentation: DESCRIPTION cbf_get_inferred_pixel_size, cbf_get_inferred_pixel_size_sf set *psize to point to the double value in millimeters of the pixel size for the axis axis_number value. The slow index is treated as axis 1 and the next faster index is treated as axis 2. cbf_get_inferred_pixel_size_fs sets *psize to point to the double value in millimeters of the pixel size for the axis axis_number value. The fast index is treated as axis 1 and the next slower index is treated as axis 2. If the axis number is negative, the axes are used in the reverse order so that an axis_number of -1 indicates the fast axes in a call to cbf_get_inferred_pixel_size or cbf_get_inferred_pixel_size_sf and indicates the fast axis in a call to cbf_get_inferred_pixel_size_fs. ARGUMENTS detector Detector handle. axis_number The number of the axis. area Pointer to the destination pizel size in mm. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_inferred_pixel_size_sf; %apply double *OUTPUT { double *psize } get_inferred_pixel_size; void get_inferred_pixel_size_sf(unsigned int axis_number, double* psize){ cbf_failnez(cbf_get_inferred_pixel_size_sf(self, axis_number, psize)); } %feature("autodoc", " Returns : double coordinate1,double coordinate2,double coordinate3 *args : double index1,double index2 C prototype: int cbf_get_pixel_coordinates (cbf_detector detector, double indexslow, double indexfast, double *coordinate1, double *coordinate2, double *coordinate3); CBFLib documentation: DESCRIPTION cbf_get_pixel_coordinates, cbf_get_pixel_coordinates_fs and cbf_get_pixel_coordinates_sf ses *coordinate1, *coordinate2, and *coordinate3 to the vector position of pixel (indexfast, indexslow) on the detector surface. If indexslow and indexfast are integers then the coordinates correspond to the center of a pixel. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. indexslow Slow index. indexfast Fast index. coordinate1 Pointer to the destination x component. coordinate2 Pointer to the destination y component. coordinate3 Pointer to the destination z component. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_pixel_coordinates; %apply double *OUTPUT {double *coordinate1, double *coordinate2, double *coordinate3}; void get_pixel_coordinates(double index1, double index2, double *coordinate1, double *coordinate2, double *coordinate3){ cbf_failnez(cbf_get_pixel_coordinates(self, index1, index2, coordinate1, coordinate2, coordinate3)); } %feature("autodoc", " Returns : double indexslow,double indexfast,double centerslow,double centerfast *args : C prototype: int cbf_get_beam_center_sf (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast); CBFLib documentation: DESCRIPTION cbf_get_beam_center sets *centerfast and *centerslow to the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector and *indexfast and *indexslow to the corresponding indices. cbf_set_beam_center sets the offsets in the axis category for the detector element axis with precedence 1 to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given *indexfast and *indexslow. cbf_set_reference_beam_center sets the displacments in the array_structure_list_axis category to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given by *indexfast and *indexslow. In order to achieve consistent results, a reference detector should be used for detector to have all axes at their reference settings. Note that the precedence 1 axis is the fastest axis, so that *centerfast and *indexfast are the fast axis components of the center and *centerslow and *indexslow are the slow axis components of the center. The _fs calls give the displacments in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the displacements in slow-to-fast order Any of the destination pointers may be NULL for getting the beam center. For setting the beam axis, either the indices of the center must not be NULL. The indices are non-negative for beam centers within the detector surface, but the center for an axis with a negative increment will be negative for a beam center within the detector surface. For cbf_set_beam_center if the diffrn_data_frame category exists with a row for the corresponding element id, the values will be set for _diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in millimetres and the value of _diffrn_data_frame.center_units will be set to 'mm'. For cbf_set_reference_beam_center if the diffrn_detector_element category exists with a row for the corresponding element id, the values will be set for _diffrn_detector_element.reference_center_fast and _diffrn_detector_element.reference_center_slow in millimetres and the value of _diffrn_detector_element.reference_units will be set to 'mm'. ARGUMENTS detector Detector handle. indexfast Pointer to the destination fast index. indexslow Pointer to the destination slow index. centerfast Pointer to the destination displacement along the fast axis. centerslow Pointer to the destination displacement along the slow axis. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_beam_center_sf; %apply double *OUTPUT {double *indexslow, double *indexfast, double *centerslow,double *centerfast}; void get_beam_center_sf(double *indexslow, double *indexfast, double *centerslow,double *centerfast){ cbf_failnez(cbf_get_beam_center_sf(self, indexslow, indexfast, centerslow, centerfast)); } %feature("autodoc", " Returns : double area,double projected_area *args : double indexslow,double indexfast C prototype: int cbf_get_pixel_area_sf(cbf_detector detector, double indexslow, double indexfast, double *area, double *projected_area); CBFLib documentation: DESCRIPTION cbf_get_pixel_area, cbf_get_pixel_area_fs and cbf_get_pixel_area_sf set *area to the area of the pixel at (indexfast, indexslow) on the detector surface and *projected_area to the apparent area of the pixel as viewed from the sample position, with indexslow being the slow axis and indexfast being the fast axis. Either of the destination pointers may be NULL. ARGUMENTS detector Detector handle. indexfast Fast index. indexslow Slow index. area Pointer to the destination area in mm2. projected_area Pointer to the destination apparent area in mm2. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_pixel_area_sf; %apply double *OUTPUT{double *area,double *projected_area}; void get_pixel_area_sf(double indexslow, double indexfast, double *area,double *projected_area){ cbf_failnez(cbf_get_pixel_area_sf (self, indexslow, indexfast, area,projected_area)); } %feature("autodoc", " Returns : double index1,double index2,double center1,double center2 *args : C prototype: int cbf_get_beam_center (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast); CBFLib documentation: DESCRIPTION cbf_get_beam_center sets *centerfast and *centerslow to the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector and *indexfast and *indexslow to the corresponding indices. cbf_set_beam_center sets the offsets in the axis category for the detector element axis with precedence 1 to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given *indexfast and *indexslow. cbf_set_reference_beam_center sets the displacments in the array_structure_list_axis category to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given by *indexfast and *indexslow. In order to achieve consistent results, a reference detector should be used for detector to have all axes at their reference settings. Note that the precedence 1 axis is the fastest axis, so that *centerfast and *indexfast are the fast axis components of the center and *centerslow and *indexslow are the slow axis components of the center. The _fs calls give the displacments in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the displacements in slow-to-fast order Any of the destination pointers may be NULL for getting the beam center. For setting the beam axis, either the indices of the center must not be NULL. The indices are non-negative for beam centers within the detector surface, but the center for an axis with a negative increment will be negative for a beam center within the detector surface. For cbf_set_beam_center if the diffrn_data_frame category exists with a row for the corresponding element id, the values will be set for _diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in millimetres and the value of _diffrn_data_frame.center_units will be set to 'mm'. For cbf_set_reference_beam_center if the diffrn_detector_element category exists with a row for the corresponding element id, the values will be set for _diffrn_detector_element.reference_center_fast and _diffrn_detector_element.reference_center_slow in millimetres and the value of _diffrn_detector_element.reference_units will be set to 'mm'. ARGUMENTS detector Detector handle. indexfast Pointer to the destination fast index. indexslow Pointer to the destination slow index. centerfast Pointer to the destination displacement along the fast axis. centerslow Pointer to the destination displacement along the slow axis. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_beam_center; %apply double *OUTPUT {double *index1, double *index2, double *center1,double *center2}; void get_beam_center(double *index1, double *index2, double *center1,double *center2){ cbf_failnez(cbf_get_beam_center(self, index1, index2, center1, center2)); } %feature("autodoc", " Returns : *args : double indexslow,double indexfast,double centerslow,double centerfast C prototype: int cbf_set_reference_beam_center_sf (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast); CBFLib documentation: DESCRIPTION cbf_get_beam_center sets *centerfast and *centerslow to the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector and *indexfast and *indexslow to the corresponding indices. cbf_set_beam_center sets the offsets in the axis category for the detector element axis with precedence 1 to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given *indexfast and *indexslow. cbf_set_reference_beam_center sets the displacments in the array_structure_list_axis category to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given by *indexfast and *indexslow. In order to achieve consistent results, a reference detector should be used for detector to have all axes at their reference settings. Note that the precedence 1 axis is the fastest axis, so that *centerfast and *indexfast are the fast axis components of the center and *centerslow and *indexslow are the slow axis components of the center. The _fs calls give the displacments in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the displacements in slow-to-fast order Any of the destination pointers may be NULL for getting the beam center. For setting the beam axis, either the indices of the center must not be NULL. The indices are non-negative for beam centers within the detector surface, but the center for an axis with a negative increment will be negative for a beam center within the detector surface. For cbf_set_beam_center if the diffrn_data_frame category exists with a row for the corresponding element id, the values will be set for _diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in millimetres and the value of _diffrn_data_frame.center_units will be set to 'mm'. For cbf_set_reference_beam_center if the diffrn_detector_element category exists with a row for the corresponding element id, the values will be set for _diffrn_detector_element.reference_center_fast and _diffrn_detector_element.reference_center_slow in millimetres and the value of _diffrn_detector_element.reference_units will be set to 'mm'. ARGUMENTS detector Detector handle. indexfast Pointer to the destination fast index. indexslow Pointer to the destination slow index. centerfast Pointer to the destination displacement along the fast axis. centerslow Pointer to the destination displacement along the slow axis. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_reference_beam_center_sf; void set_reference_beam_center_sf(double *indexslow, double *indexfast, double *centerslow,double *centerfast){ cbf_failnez(cbf_set_reference_beam_center_sf(self, indexslow, indexfast, centerslow, centerfast)); } %feature("autodoc", " Returns : *args : double indexslow,double indexfast,double centerslow,double centerfast C prototype: int cbf_set_beam_center_sf (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast); CBFLib documentation: DESCRIPTION cbf_get_beam_center sets *centerfast and *centerslow to the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector and *indexfast and *indexslow to the corresponding indices. cbf_set_beam_center sets the offsets in the axis category for the detector element axis with precedence 1 to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given *indexfast and *indexslow. cbf_set_reference_beam_center sets the displacments in the array_structure_list_axis category to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given by *indexfast and *indexslow. In order to achieve consistent results, a reference detector should be used for detector to have all axes at their reference settings. Note that the precedence 1 axis is the fastest axis, so that *centerfast and *indexfast are the fast axis components of the center and *centerslow and *indexslow are the slow axis components of the center. The _fs calls give the displacments in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the displacements in slow-to-fast order Any of the destination pointers may be NULL for getting the beam center. For setting the beam axis, either the indices of the center must not be NULL. The indices are non-negative for beam centers within the detector surface, but the center for an axis with a negative increment will be negative for a beam center within the detector surface. For cbf_set_beam_center if the diffrn_data_frame category exists with a row for the corresponding element id, the values will be set for _diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in millimetres and the value of _diffrn_data_frame.center_units will be set to 'mm'. For cbf_set_reference_beam_center if the diffrn_detector_element category exists with a row for the corresponding element id, the values will be set for _diffrn_detector_element.reference_center_fast and _diffrn_detector_element.reference_center_slow in millimetres and the value of _diffrn_detector_element.reference_units will be set to 'mm'. ARGUMENTS detector Detector handle. indexfast Pointer to the destination fast index. indexslow Pointer to the destination slow index. centerfast Pointer to the destination displacement along the fast axis. centerslow Pointer to the destination displacement along the slow axis. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")set_beam_center_sf; void set_beam_center_sf(double *indexslow, double *indexfast, double *centerslow,double *centerfast){ cbf_failnez(cbf_set_beam_center_sf(self, indexslow, indexfast, centerslow, centerfast)); } %feature("autodoc", " Returns : double normal1,double normal2,double normal3 *args : double index1,double index2 C prototype: int cbf_get_pixel_normal (cbf_detector detector, double indexslow, double indexfast, double *normal1, double *normal2, double *normal3); CBFLib documentation: DESCRIPTION cbf_get_detector_normal, cbf_get_pixel_normal_fs and cbf_get_pixel_normal_sf set *normal1, *normal2, and *normal3 to the 3 components of the of the normal vector to the pixel at (indexfast, indexslow). The vector is normalized. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. indexslow Slow index. indexfast Fast index. normal1 Pointer to the destination x component of the normal vector. normal2 Pointer to the destination y component of the normal vector. normal3 Pointer to the destination z component of the normal vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- ")get_pixel_normal; %apply double *OUTPUT {double *normal1,double *normal2, double *normal3}; void get_pixel_normal ( double index1, double index2, double *normal1,double *normal2, double *normal3){ cbf_failnez(cbf_get_pixel_normal(self, index1,index2,normal1,normal2,normal3)); } }; // End of cbf_detector ./CBFlib-0.9.2.2/pycbf/pycbf_wrap.c0000644000076500007650000411157111603702120015207 0ustar yayayaya/* ---------------------------------------------------------------------------- * This file was automatically generated by SWIG (http://www.swig.org). * Version 1.3.40 * * This file is not intended to be easily readable and contains a number of * coding conventions designed to improve portability and efficiency. Do not make * changes to this file unless you know what you are doing--modify the SWIG * interface file instead. * ----------------------------------------------------------------------------- */ #define SWIGPYTHON #define SWIG_PYTHON_DIRECTOR_NO_VTABLE /* ----------------------------------------------------------------------------- * This section contains generic SWIG labels for method/variable * declarations/attributes, and other compiler dependent labels. * ----------------------------------------------------------------------------- */ /* template workaround for compilers that cannot correctly implement the C++ standard */ #ifndef SWIGTEMPLATEDISAMBIGUATOR # if defined(__SUNPRO_CC) && (__SUNPRO_CC <= 0x560) # define SWIGTEMPLATEDISAMBIGUATOR template # elif defined(__HP_aCC) /* Needed even with `aCC -AA' when `aCC -V' reports HP ANSI C++ B3910B A.03.55 */ /* If we find a maximum version that requires this, the test would be __HP_aCC <= 35500 for A.03.55 */ # define SWIGTEMPLATEDISAMBIGUATOR template # else # define SWIGTEMPLATEDISAMBIGUATOR # endif #endif /* inline attribute */ #ifndef SWIGINLINE # if defined(__cplusplus) || (defined(__GNUC__) && !defined(__STRICT_ANSI__)) # define SWIGINLINE inline # else # define SWIGINLINE # endif #endif /* attribute recognised by some compilers to avoid 'unused' warnings */ #ifndef SWIGUNUSED # if defined(__GNUC__) # if !(defined(__cplusplus)) || (__GNUC__ > 3 || (__GNUC__ == 3 && __GNUC_MINOR__ >= 4)) # define SWIGUNUSED __attribute__ ((__unused__)) # else # define SWIGUNUSED # endif # elif defined(__ICC) # define SWIGUNUSED __attribute__ ((__unused__)) # else # define SWIGUNUSED # endif #endif #ifndef SWIG_MSC_UNSUPPRESS_4505 # if defined(_MSC_VER) # pragma warning(disable : 4505) /* unreferenced local function has been removed */ # endif #endif #ifndef SWIGUNUSEDPARM # ifdef __cplusplus # define SWIGUNUSEDPARM(p) # else # define SWIGUNUSEDPARM(p) p SWIGUNUSED # endif #endif /* internal SWIG method */ #ifndef SWIGINTERN # define SWIGINTERN static SWIGUNUSED #endif /* internal inline SWIG method */ #ifndef SWIGINTERNINLINE # define SWIGINTERNINLINE SWIGINTERN SWIGINLINE #endif /* exporting methods */ #if (__GNUC__ >= 4) || (__GNUC__ == 3 && __GNUC_MINOR__ >= 4) # ifndef GCC_HASCLASSVISIBILITY # define GCC_HASCLASSVISIBILITY # endif #endif #ifndef SWIGEXPORT # if defined(_WIN32) || defined(__WIN32__) || defined(__CYGWIN__) # if defined(STATIC_LINKED) # define SWIGEXPORT # else # define SWIGEXPORT __declspec(dllexport) # endif # else # if defined(__GNUC__) && defined(GCC_HASCLASSVISIBILITY) # define SWIGEXPORT __attribute__ ((visibility("default"))) # else # define SWIGEXPORT # endif # endif #endif /* calling conventions for Windows */ #ifndef SWIGSTDCALL # if defined(_WIN32) || defined(__WIN32__) || defined(__CYGWIN__) # define SWIGSTDCALL __stdcall # else # define SWIGSTDCALL # endif #endif /* Deal with Microsoft's attempt at deprecating C standard runtime functions */ #if !defined(SWIG_NO_CRT_SECURE_NO_DEPRECATE) && defined(_MSC_VER) && !defined(_CRT_SECURE_NO_DEPRECATE) # define _CRT_SECURE_NO_DEPRECATE #endif /* Deal with Microsoft's attempt at deprecating methods in the standard C++ library */ #if !defined(SWIG_NO_SCL_SECURE_NO_DEPRECATE) && defined(_MSC_VER) && !defined(_SCL_SECURE_NO_DEPRECATE) # define _SCL_SECURE_NO_DEPRECATE #endif /* Python.h has to appear first */ #include /* ----------------------------------------------------------------------------- * swigrun.swg * * This file contains generic C API SWIG runtime support for pointer * type checking. * ----------------------------------------------------------------------------- */ /* This should only be incremented when either the layout of swig_type_info changes, or for whatever reason, the runtime changes incompatibly */ #define SWIG_RUNTIME_VERSION "4" /* define SWIG_TYPE_TABLE_NAME as "SWIG_TYPE_TABLE" */ #ifdef SWIG_TYPE_TABLE # define SWIG_QUOTE_STRING(x) #x # define SWIG_EXPAND_AND_QUOTE_STRING(x) SWIG_QUOTE_STRING(x) # define SWIG_TYPE_TABLE_NAME SWIG_EXPAND_AND_QUOTE_STRING(SWIG_TYPE_TABLE) #else # define SWIG_TYPE_TABLE_NAME #endif /* You can use the SWIGRUNTIME and SWIGRUNTIMEINLINE macros for creating a static or dynamic library from the SWIG runtime code. In 99.9% of the cases, SWIG just needs to declare them as 'static'. But only do this if strictly necessary, ie, if you have problems with your compiler or suchlike. */ #ifndef SWIGRUNTIME # define SWIGRUNTIME SWIGINTERN #endif #ifndef SWIGRUNTIMEINLINE # define SWIGRUNTIMEINLINE SWIGRUNTIME SWIGINLINE #endif /* Generic buffer size */ #ifndef SWIG_BUFFER_SIZE # define SWIG_BUFFER_SIZE 1024 #endif /* Flags for pointer conversions */ #define SWIG_POINTER_DISOWN 0x1 #define SWIG_CAST_NEW_MEMORY 0x2 /* Flags for new pointer objects */ #define SWIG_POINTER_OWN 0x1 /* Flags/methods for returning states. The SWIG conversion methods, as ConvertPtr, return and integer that tells if the conversion was successful or not. And if not, an error code can be returned (see swigerrors.swg for the codes). Use the following macros/flags to set or process the returning states. In old versions of SWIG, code such as the following was usually written: if (SWIG_ConvertPtr(obj,vptr,ty.flags) != -1) { // success code } else { //fail code } Now you can be more explicit: int res = SWIG_ConvertPtr(obj,vptr,ty.flags); if (SWIG_IsOK(res)) { // success code } else { // fail code } which is the same really, but now you can also do Type *ptr; int res = SWIG_ConvertPtr(obj,(void **)(&ptr),ty.flags); if (SWIG_IsOK(res)) { // success code if (SWIG_IsNewObj(res) { ... delete *ptr; } else { ... } } else { // fail code } I.e., now SWIG_ConvertPtr can return new objects and you can identify the case and take care of the deallocation. Of course that also requires SWIG_ConvertPtr to return new result values, such as int SWIG_ConvertPtr(obj, ptr,...) { if () { if () { *ptr = ; return SWIG_NEWOBJ; } else { *ptr = ; return SWIG_OLDOBJ; } } else { return SWIG_BADOBJ; } } Of course, returning the plain '0(success)/-1(fail)' still works, but you can be more explicit by returning SWIG_BADOBJ, SWIG_ERROR or any of the SWIG errors code. Finally, if the SWIG_CASTRANK_MODE is enabled, the result code allows to return the 'cast rank', for example, if you have this int food(double) int fooi(int); and you call food(1) // cast rank '1' (1 -> 1.0) fooi(1) // cast rank '0' just use the SWIG_AddCast()/SWIG_CheckState() */ #define SWIG_OK (0) #define SWIG_ERROR (-1) #define SWIG_IsOK(r) (r >= 0) #define SWIG_ArgError(r) ((r != SWIG_ERROR) ? r : SWIG_TypeError) /* The CastRankLimit says how many bits are used for the cast rank */ #define SWIG_CASTRANKLIMIT (1 << 8) /* The NewMask denotes the object was created (using new/malloc) */ #define SWIG_NEWOBJMASK (SWIG_CASTRANKLIMIT << 1) /* The TmpMask is for in/out typemaps that use temporal objects */ #define SWIG_TMPOBJMASK (SWIG_NEWOBJMASK << 1) /* Simple returning values */ #define SWIG_BADOBJ (SWIG_ERROR) #define SWIG_OLDOBJ (SWIG_OK) #define SWIG_NEWOBJ (SWIG_OK | SWIG_NEWOBJMASK) #define SWIG_TMPOBJ (SWIG_OK | SWIG_TMPOBJMASK) /* Check, add and del mask methods */ #define SWIG_AddNewMask(r) (SWIG_IsOK(r) ? (r | SWIG_NEWOBJMASK) : r) #define SWIG_DelNewMask(r) (SWIG_IsOK(r) ? (r & ~SWIG_NEWOBJMASK) : r) #define SWIG_IsNewObj(r) (SWIG_IsOK(r) && (r & SWIG_NEWOBJMASK)) #define SWIG_AddTmpMask(r) (SWIG_IsOK(r) ? (r | SWIG_TMPOBJMASK) : r) #define SWIG_DelTmpMask(r) (SWIG_IsOK(r) ? (r & ~SWIG_TMPOBJMASK) : r) #define SWIG_IsTmpObj(r) (SWIG_IsOK(r) && (r & SWIG_TMPOBJMASK)) /* Cast-Rank Mode */ #if defined(SWIG_CASTRANK_MODE) # ifndef SWIG_TypeRank # define SWIG_TypeRank unsigned long # endif # ifndef SWIG_MAXCASTRANK /* Default cast allowed */ # define SWIG_MAXCASTRANK (2) # endif # define SWIG_CASTRANKMASK ((SWIG_CASTRANKLIMIT) -1) # define SWIG_CastRank(r) (r & SWIG_CASTRANKMASK) SWIGINTERNINLINE int SWIG_AddCast(int r) { return SWIG_IsOK(r) ? ((SWIG_CastRank(r) < SWIG_MAXCASTRANK) ? (r + 1) : SWIG_ERROR) : r; } SWIGINTERNINLINE int SWIG_CheckState(int r) { return SWIG_IsOK(r) ? SWIG_CastRank(r) + 1 : 0; } #else /* no cast-rank mode */ # define SWIG_AddCast # define SWIG_CheckState(r) (SWIG_IsOK(r) ? 1 : 0) #endif #include #ifdef __cplusplus extern "C" { #endif typedef void *(*swig_converter_func)(void *, int *); typedef struct swig_type_info *(*swig_dycast_func)(void **); /* Structure to store information on one type */ typedef struct swig_type_info { const char *name; /* mangled name of this type */ const char *str; /* human readable name of this type */ swig_dycast_func dcast; /* dynamic cast function down a hierarchy */ struct swig_cast_info *cast; /* linked list of types that can cast into this type */ void *clientdata; /* language specific type data */ int owndata; /* flag if the structure owns the clientdata */ } swig_type_info; /* Structure to store a type and conversion function used for casting */ typedef struct swig_cast_info { swig_type_info *type; /* pointer to type that is equivalent to this type */ swig_converter_func converter; /* function to cast the void pointers */ struct swig_cast_info *next; /* pointer to next cast in linked list */ struct swig_cast_info *prev; /* pointer to the previous cast */ } swig_cast_info; /* Structure used to store module information * Each module generates one structure like this, and the runtime collects * all of these structures and stores them in a circularly linked list.*/ typedef struct swig_module_info { swig_type_info **types; /* Array of pointers to swig_type_info structures that are in this module */ size_t size; /* Number of types in this module */ struct swig_module_info *next; /* Pointer to next element in circularly linked list */ swig_type_info **type_initial; /* Array of initially generated type structures */ swig_cast_info **cast_initial; /* Array of initially generated casting structures */ void *clientdata; /* Language specific module data */ } swig_module_info; /* Compare two type names skipping the space characters, therefore "char*" == "char *" and "Class" == "Class", etc. Return 0 when the two name types are equivalent, as in strncmp, but skipping ' '. */ SWIGRUNTIME int SWIG_TypeNameComp(const char *f1, const char *l1, const char *f2, const char *l2) { for (;(f1 != l1) && (f2 != l2); ++f1, ++f2) { while ((*f1 == ' ') && (f1 != l1)) ++f1; while ((*f2 == ' ') && (f2 != l2)) ++f2; if (*f1 != *f2) return (*f1 > *f2) ? 1 : -1; } return (int)((l1 - f1) - (l2 - f2)); } /* Check type equivalence in a name list like ||... Return 0 if not equal, 1 if equal */ SWIGRUNTIME int SWIG_TypeEquiv(const char *nb, const char *tb) { int equiv = 0; const char* te = tb + strlen(tb); const char* ne = nb; while (!equiv && *ne) { for (nb = ne; *ne; ++ne) { if (*ne == '|') break; } equiv = (SWIG_TypeNameComp(nb, ne, tb, te) == 0) ? 1 : 0; if (*ne) ++ne; } return equiv; } /* Check type equivalence in a name list like ||... Return 0 if equal, -1 if nb < tb, 1 if nb > tb */ SWIGRUNTIME int SWIG_TypeCompare(const char *nb, const char *tb) { int equiv = 0; const char* te = tb + strlen(tb); const char* ne = nb; while (!equiv && *ne) { for (nb = ne; *ne; ++ne) { if (*ne == '|') break; } equiv = (SWIG_TypeNameComp(nb, ne, tb, te) == 0) ? 1 : 0; if (*ne) ++ne; } return equiv; } /* Check the typename */ SWIGRUNTIME swig_cast_info * SWIG_TypeCheck(const char *c, swig_type_info *ty) { if (ty) { swig_cast_info *iter = ty->cast; while (iter) { if (strcmp(iter->type->name, c) == 0) { if (iter == ty->cast) return iter; /* Move iter to the top of the linked list */ iter->prev->next = iter->next; if (iter->next) iter->next->prev = iter->prev; iter->next = ty->cast; iter->prev = 0; if (ty->cast) ty->cast->prev = iter; ty->cast = iter; return iter; } iter = iter->next; } } return 0; } /* Identical to SWIG_TypeCheck, except strcmp is replaced with a pointer comparison */ SWIGRUNTIME swig_cast_info * SWIG_TypeCheckStruct(swig_type_info *from, swig_type_info *ty) { if (ty) { swig_cast_info *iter = ty->cast; while (iter) { if (iter->type == from) { if (iter == ty->cast) return iter; /* Move iter to the top of the linked list */ iter->prev->next = iter->next; if (iter->next) iter->next->prev = iter->prev; iter->next = ty->cast; iter->prev = 0; if (ty->cast) ty->cast->prev = iter; ty->cast = iter; return iter; } iter = iter->next; } } return 0; } /* Cast a pointer up an inheritance hierarchy */ SWIGRUNTIMEINLINE void * SWIG_TypeCast(swig_cast_info *ty, void *ptr, int *newmemory) { return ((!ty) || (!ty->converter)) ? ptr : (*ty->converter)(ptr, newmemory); } /* Dynamic pointer casting. Down an inheritance hierarchy */ SWIGRUNTIME swig_type_info * SWIG_TypeDynamicCast(swig_type_info *ty, void **ptr) { swig_type_info *lastty = ty; if (!ty || !ty->dcast) return ty; while (ty && (ty->dcast)) { ty = (*ty->dcast)(ptr); if (ty) lastty = ty; } return lastty; } /* Return the name associated with this type */ SWIGRUNTIMEINLINE const char * SWIG_TypeName(const swig_type_info *ty) { return ty->name; } /* Return the pretty name associated with this type, that is an unmangled type name in a form presentable to the user. */ SWIGRUNTIME const char * SWIG_TypePrettyName(const swig_type_info *type) { /* The "str" field contains the equivalent pretty names of the type, separated by vertical-bar characters. We choose to print the last name, as it is often (?) the most specific. */ if (!type) return NULL; if (type->str != NULL) { const char *last_name = type->str; const char *s; for (s = type->str; *s; s++) if (*s == '|') last_name = s+1; return last_name; } else return type->name; } /* Set the clientdata field for a type */ SWIGRUNTIME void SWIG_TypeClientData(swig_type_info *ti, void *clientdata) { swig_cast_info *cast = ti->cast; /* if (ti->clientdata == clientdata) return; */ ti->clientdata = clientdata; while (cast) { if (!cast->converter) { swig_type_info *tc = cast->type; if (!tc->clientdata) { SWIG_TypeClientData(tc, clientdata); } } cast = cast->next; } } SWIGRUNTIME void SWIG_TypeNewClientData(swig_type_info *ti, void *clientdata) { SWIG_TypeClientData(ti, clientdata); ti->owndata = 1; } /* Search for a swig_type_info structure only by mangled name Search is a O(log #types) We start searching at module start, and finish searching when start == end. Note: if start == end at the beginning of the function, we go all the way around the circular list. */ SWIGRUNTIME swig_type_info * SWIG_MangledTypeQueryModule(swig_module_info *start, swig_module_info *end, const char *name) { swig_module_info *iter = start; do { if (iter->size) { register size_t l = 0; register size_t r = iter->size - 1; do { /* since l+r >= 0, we can (>> 1) instead (/ 2) */ register size_t i = (l + r) >> 1; const char *iname = iter->types[i]->name; if (iname) { register int compare = strcmp(name, iname); if (compare == 0) { return iter->types[i]; } else if (compare < 0) { if (i) { r = i - 1; } else { break; } } else if (compare > 0) { l = i + 1; } } else { break; /* should never happen */ } } while (l <= r); } iter = iter->next; } while (iter != end); return 0; } /* Search for a swig_type_info structure for either a mangled name or a human readable name. It first searches the mangled names of the types, which is a O(log #types) If a type is not found it then searches the human readable names, which is O(#types). We start searching at module start, and finish searching when start == end. Note: if start == end at the beginning of the function, we go all the way around the circular list. */ SWIGRUNTIME swig_type_info * SWIG_TypeQueryModule(swig_module_info *start, swig_module_info *end, const char *name) { /* STEP 1: Search the name field using binary search */ swig_type_info *ret = SWIG_MangledTypeQueryModule(start, end, name); if (ret) { return ret; } else { /* STEP 2: If the type hasn't been found, do a complete search of the str field (the human readable name) */ swig_module_info *iter = start; do { register size_t i = 0; for (; i < iter->size; ++i) { if (iter->types[i]->str && (SWIG_TypeEquiv(iter->types[i]->str, name))) return iter->types[i]; } iter = iter->next; } while (iter != end); } /* neither found a match */ return 0; } /* Pack binary data into a string */ SWIGRUNTIME char * SWIG_PackData(char *c, void *ptr, size_t sz) { static const char hex[17] = "0123456789abcdef"; register const unsigned char *u = (unsigned char *) ptr; register const unsigned char *eu = u + sz; for (; u != eu; ++u) { register unsigned char uu = *u; *(c++) = hex[(uu & 0xf0) >> 4]; *(c++) = hex[uu & 0xf]; } return c; } /* Unpack binary data from a string */ SWIGRUNTIME const char * SWIG_UnpackData(const char *c, void *ptr, size_t sz) { register unsigned char *u = (unsigned char *) ptr; register const unsigned char *eu = u + sz; for (; u != eu; ++u) { register char d = *(c++); register unsigned char uu; if ((d >= '0') && (d <= '9')) uu = ((d - '0') << 4); else if ((d >= 'a') && (d <= 'f')) uu = ((d - ('a'-10)) << 4); else return (char *) 0; d = *(c++); if ((d >= '0') && (d <= '9')) uu |= (d - '0'); else if ((d >= 'a') && (d <= 'f')) uu |= (d - ('a'-10)); else return (char *) 0; *u = uu; } return c; } /* Pack 'void *' into a string buffer. */ SWIGRUNTIME char * SWIG_PackVoidPtr(char *buff, void *ptr, const char *name, size_t bsz) { char *r = buff; if ((2*sizeof(void *) + 2) > bsz) return 0; *(r++) = '_'; r = SWIG_PackData(r,&ptr,sizeof(void *)); if (strlen(name) + 1 > (bsz - (r - buff))) return 0; strcpy(r,name); return buff; } SWIGRUNTIME const char * SWIG_UnpackVoidPtr(const char *c, void **ptr, const char *name) { if (*c != '_') { if (strcmp(c,"NULL") == 0) { *ptr = (void *) 0; return name; } else { return 0; } } return SWIG_UnpackData(++c,ptr,sizeof(void *)); } SWIGRUNTIME char * SWIG_PackDataName(char *buff, void *ptr, size_t sz, const char *name, size_t bsz) { char *r = buff; size_t lname = (name ? strlen(name) : 0); if ((2*sz + 2 + lname) > bsz) return 0; *(r++) = '_'; r = SWIG_PackData(r,ptr,sz); if (lname) { strncpy(r,name,lname+1); } else { *r = 0; } return buff; } SWIGRUNTIME const char * SWIG_UnpackDataName(const char *c, void *ptr, size_t sz, const char *name) { if (*c != '_') { if (strcmp(c,"NULL") == 0) { memset(ptr,0,sz); return name; } else { return 0; } } return SWIG_UnpackData(++c,ptr,sz); } #ifdef __cplusplus } #endif /* Errors in SWIG */ #define SWIG_UnknownError -1 #define SWIG_IOError -2 #define SWIG_RuntimeError -3 #define SWIG_IndexError -4 #define SWIG_TypeError -5 #define SWIG_DivisionByZero -6 #define SWIG_OverflowError -7 #define SWIG_SyntaxError -8 #define SWIG_ValueError -9 #define SWIG_SystemError -10 #define SWIG_AttributeError -11 #define SWIG_MemoryError -12 #define SWIG_NullReferenceError -13 /* Compatibility macros for Python 3 */ #if PY_VERSION_HEX >= 0x03000000 #define PyClass_Check(obj) PyObject_IsInstance(obj, (PyObject *)&PyType_Type) #define PyInt_Check(x) PyLong_Check(x) #define PyInt_AsLong(x) PyLong_AsLong(x) #define PyInt_FromLong(x) PyLong_FromLong(x) #define PyString_Format(fmt, args) PyUnicode_Format(fmt, args) #endif #ifndef Py_TYPE # define Py_TYPE(op) ((op)->ob_type) #endif /* SWIG APIs for compatibility of both Python 2 & 3 */ #if PY_VERSION_HEX >= 0x03000000 # define SWIG_Python_str_FromFormat PyUnicode_FromFormat #else # define SWIG_Python_str_FromFormat PyString_FromFormat #endif /* Warning: This function will allocate a new string in Python 3, * so please call SWIG_Python_str_DelForPy3(x) to free the space. */ SWIGINTERN char* SWIG_Python_str_AsChar(PyObject *str) { #if PY_VERSION_HEX >= 0x03000000 char *cstr; char *newstr; Py_ssize_t len; str = PyUnicode_AsUTF8String(str); PyBytes_AsStringAndSize(str, &cstr, &len); newstr = (char *) malloc(len+1); memcpy(newstr, cstr, len+1); Py_XDECREF(str); return newstr; #else return PyString_AsString(str); #endif } #if PY_VERSION_HEX >= 0x03000000 # define SWIG_Python_str_DelForPy3(x) free( (void*) (x) ) #else # define SWIG_Python_str_DelForPy3(x) #endif SWIGINTERN PyObject* SWIG_Python_str_FromChar(const char *c) { #if PY_VERSION_HEX >= 0x03000000 return PyUnicode_FromString(c); #else return PyString_FromString(c); #endif } /* Add PyOS_snprintf for old Pythons */ #if PY_VERSION_HEX < 0x02020000 # if defined(_MSC_VER) || defined(__BORLANDC__) || defined(_WATCOM) # define PyOS_snprintf _snprintf # else # define PyOS_snprintf snprintf # endif #endif /* A crude PyString_FromFormat implementation for old Pythons */ #if PY_VERSION_HEX < 0x02020000 #ifndef SWIG_PYBUFFER_SIZE # define SWIG_PYBUFFER_SIZE 1024 #endif static PyObject * PyString_FromFormat(const char *fmt, ...) { va_list ap; char buf[SWIG_PYBUFFER_SIZE * 2]; int res; va_start(ap, fmt); res = vsnprintf(buf, sizeof(buf), fmt, ap); va_end(ap); return (res < 0 || res >= (int)sizeof(buf)) ? 0 : PyString_FromString(buf); } #endif /* Add PyObject_Del for old Pythons */ #if PY_VERSION_HEX < 0x01060000 # define PyObject_Del(op) PyMem_DEL((op)) #endif #ifndef PyObject_DEL # define PyObject_DEL PyObject_Del #endif /* A crude PyExc_StopIteration exception for old Pythons */ #if PY_VERSION_HEX < 0x02020000 # ifndef PyExc_StopIteration # define PyExc_StopIteration PyExc_RuntimeError # endif # ifndef PyObject_GenericGetAttr # define PyObject_GenericGetAttr 0 # endif #endif /* Py_NotImplemented is defined in 2.1 and up. */ #if PY_VERSION_HEX < 0x02010000 # ifndef Py_NotImplemented # define Py_NotImplemented PyExc_RuntimeError # endif #endif /* A crude PyString_AsStringAndSize implementation for old Pythons */ #if PY_VERSION_HEX < 0x02010000 # ifndef PyString_AsStringAndSize # define PyString_AsStringAndSize(obj, s, len) {*s = PyString_AsString(obj); *len = *s ? strlen(*s) : 0;} # endif #endif /* PySequence_Size for old Pythons */ #if PY_VERSION_HEX < 0x02000000 # ifndef PySequence_Size # define PySequence_Size PySequence_Length # endif #endif /* PyBool_FromLong for old Pythons */ #if PY_VERSION_HEX < 0x02030000 static PyObject *PyBool_FromLong(long ok) { PyObject *result = ok ? Py_True : Py_False; Py_INCREF(result); return result; } #endif /* Py_ssize_t for old Pythons */ /* This code is as recommended by: */ /* http://www.python.org/dev/peps/pep-0353/#conversion-guidelines */ #if PY_VERSION_HEX < 0x02050000 && !defined(PY_SSIZE_T_MIN) typedef int Py_ssize_t; # define PY_SSIZE_T_MAX INT_MAX # define PY_SSIZE_T_MIN INT_MIN #endif /* ----------------------------------------------------------------------------- * error manipulation * ----------------------------------------------------------------------------- */ SWIGRUNTIME PyObject* SWIG_Python_ErrorType(int code) { PyObject* type = 0; switch(code) { case SWIG_MemoryError: type = PyExc_MemoryError; break; case SWIG_IOError: type = PyExc_IOError; break; case SWIG_RuntimeError: type = PyExc_RuntimeError; break; case SWIG_IndexError: type = PyExc_IndexError; break; case SWIG_TypeError: type = PyExc_TypeError; break; case SWIG_DivisionByZero: type = PyExc_ZeroDivisionError; break; case SWIG_OverflowError: type = PyExc_OverflowError; break; case SWIG_SyntaxError: type = PyExc_SyntaxError; break; case SWIG_ValueError: type = PyExc_ValueError; break; case SWIG_SystemError: type = PyExc_SystemError; break; case SWIG_AttributeError: type = PyExc_AttributeError; break; default: type = PyExc_RuntimeError; } return type; } SWIGRUNTIME void SWIG_Python_AddErrorMsg(const char* mesg) { PyObject *type = 0; PyObject *value = 0; PyObject *traceback = 0; if (PyErr_Occurred()) PyErr_Fetch(&type, &value, &traceback); if (value) { char *tmp; PyObject *old_str = PyObject_Str(value); PyErr_Clear(); Py_XINCREF(type); PyErr_Format(type, "%s %s", tmp = SWIG_Python_str_AsChar(old_str), mesg); SWIG_Python_str_DelForPy3(tmp); Py_DECREF(old_str); Py_DECREF(value); } else { PyErr_SetString(PyExc_RuntimeError, mesg); } } #if defined(SWIG_PYTHON_NO_THREADS) # if defined(SWIG_PYTHON_THREADS) # undef SWIG_PYTHON_THREADS # endif #endif #if defined(SWIG_PYTHON_THREADS) /* Threading support is enabled */ # if !defined(SWIG_PYTHON_USE_GIL) && !defined(SWIG_PYTHON_NO_USE_GIL) # if (PY_VERSION_HEX >= 0x02030000) /* For 2.3 or later, use the PyGILState calls */ # define SWIG_PYTHON_USE_GIL # endif # endif # if defined(SWIG_PYTHON_USE_GIL) /* Use PyGILState threads calls */ # ifndef SWIG_PYTHON_INITIALIZE_THREADS # define SWIG_PYTHON_INITIALIZE_THREADS PyEval_InitThreads() # endif # ifdef __cplusplus /* C++ code */ class SWIG_Python_Thread_Block { bool status; PyGILState_STATE state; public: void end() { if (status) { PyGILState_Release(state); status = false;} } SWIG_Python_Thread_Block() : status(true), state(PyGILState_Ensure()) {} ~SWIG_Python_Thread_Block() { end(); } }; class SWIG_Python_Thread_Allow { bool status; PyThreadState *save; public: void end() { if (status) { PyEval_RestoreThread(save); status = false; }} SWIG_Python_Thread_Allow() : status(true), save(PyEval_SaveThread()) {} ~SWIG_Python_Thread_Allow() { end(); } }; # define SWIG_PYTHON_THREAD_BEGIN_BLOCK SWIG_Python_Thread_Block _swig_thread_block # define SWIG_PYTHON_THREAD_END_BLOCK _swig_thread_block.end() # define SWIG_PYTHON_THREAD_BEGIN_ALLOW SWIG_Python_Thread_Allow _swig_thread_allow # define SWIG_PYTHON_THREAD_END_ALLOW _swig_thread_allow.end() # else /* C code */ # define SWIG_PYTHON_THREAD_BEGIN_BLOCK PyGILState_STATE _swig_thread_block = PyGILState_Ensure() # define SWIG_PYTHON_THREAD_END_BLOCK PyGILState_Release(_swig_thread_block) # define SWIG_PYTHON_THREAD_BEGIN_ALLOW PyThreadState *_swig_thread_allow = PyEval_SaveThread() # define SWIG_PYTHON_THREAD_END_ALLOW PyEval_RestoreThread(_swig_thread_allow) # endif # else /* Old thread way, not implemented, user must provide it */ # if !defined(SWIG_PYTHON_INITIALIZE_THREADS) # define SWIG_PYTHON_INITIALIZE_THREADS # endif # if !defined(SWIG_PYTHON_THREAD_BEGIN_BLOCK) # define SWIG_PYTHON_THREAD_BEGIN_BLOCK # endif # if !defined(SWIG_PYTHON_THREAD_END_BLOCK) # define SWIG_PYTHON_THREAD_END_BLOCK # endif # if !defined(SWIG_PYTHON_THREAD_BEGIN_ALLOW) # define SWIG_PYTHON_THREAD_BEGIN_ALLOW # endif # if !defined(SWIG_PYTHON_THREAD_END_ALLOW) # define SWIG_PYTHON_THREAD_END_ALLOW # endif # endif #else /* No thread support */ # define SWIG_PYTHON_INITIALIZE_THREADS # define SWIG_PYTHON_THREAD_BEGIN_BLOCK # define SWIG_PYTHON_THREAD_END_BLOCK # define SWIG_PYTHON_THREAD_BEGIN_ALLOW # define SWIG_PYTHON_THREAD_END_ALLOW #endif /* ----------------------------------------------------------------------------- * Python API portion that goes into the runtime * ----------------------------------------------------------------------------- */ #ifdef __cplusplus extern "C" { #if 0 } /* cc-mode */ #endif #endif /* ----------------------------------------------------------------------------- * Constant declarations * ----------------------------------------------------------------------------- */ /* Constant Types */ #define SWIG_PY_POINTER 4 #define SWIG_PY_BINARY 5 /* Constant information structure */ typedef struct swig_const_info { int type; char *name; long lvalue; double dvalue; void *pvalue; swig_type_info **ptype; } swig_const_info; /* ----------------------------------------------------------------------------- * Wrapper of PyInstanceMethod_New() used in Python 3 * It is exported to the generated module, used for -fastproxy * ----------------------------------------------------------------------------- */ SWIGRUNTIME PyObject* SWIG_PyInstanceMethod_New(PyObject *self, PyObject *func) { #if PY_VERSION_HEX >= 0x03000000 return PyInstanceMethod_New(func); #else return NULL; #endif } #ifdef __cplusplus #if 0 { /* cc-mode */ #endif } #endif /* ----------------------------------------------------------------------------- * See the LICENSE file for information on copyright, usage and redistribution * of SWIG, and the README file for authors - http://www.swig.org/release.html. * * pyrun.swg * * This file contains the runtime support for Python modules * and includes code for managing global variables and pointer * type checking. * * ----------------------------------------------------------------------------- */ /* Common SWIG API */ /* for raw pointers */ #define SWIG_Python_ConvertPtr(obj, pptr, type, flags) SWIG_Python_ConvertPtrAndOwn(obj, pptr, type, flags, 0) #define SWIG_ConvertPtr(obj, pptr, type, flags) SWIG_Python_ConvertPtr(obj, pptr, type, flags) #define SWIG_ConvertPtrAndOwn(obj,pptr,type,flags,own) SWIG_Python_ConvertPtrAndOwn(obj, pptr, type, flags, own) #define SWIG_NewPointerObj(ptr, type, flags) SWIG_Python_NewPointerObj(ptr, type, flags) #define SWIG_CheckImplicit(ty) SWIG_Python_CheckImplicit(ty) #define SWIG_AcquirePtr(ptr, src) SWIG_Python_AcquirePtr(ptr, src) #define swig_owntype int /* for raw packed data */ #define SWIG_ConvertPacked(obj, ptr, sz, ty) SWIG_Python_ConvertPacked(obj, ptr, sz, ty) #define SWIG_NewPackedObj(ptr, sz, type) SWIG_Python_NewPackedObj(ptr, sz, type) /* for class or struct pointers */ #define SWIG_ConvertInstance(obj, pptr, type, flags) SWIG_ConvertPtr(obj, pptr, type, flags) #define SWIG_NewInstanceObj(ptr, type, flags) SWIG_NewPointerObj(ptr, type, flags) /* for C or C++ function pointers */ #define SWIG_ConvertFunctionPtr(obj, pptr, type) SWIG_Python_ConvertFunctionPtr(obj, pptr, type) #define SWIG_NewFunctionPtrObj(ptr, type) SWIG_Python_NewPointerObj(ptr, type, 0) /* for C++ member pointers, ie, member methods */ #define SWIG_ConvertMember(obj, ptr, sz, ty) SWIG_Python_ConvertPacked(obj, ptr, sz, ty) #define SWIG_NewMemberObj(ptr, sz, type) SWIG_Python_NewPackedObj(ptr, sz, type) /* Runtime API */ #define SWIG_GetModule(clientdata) SWIG_Python_GetModule() #define SWIG_SetModule(clientdata, pointer) SWIG_Python_SetModule(pointer) #define SWIG_NewClientData(obj) SwigPyClientData_New(obj) #define SWIG_SetErrorObj SWIG_Python_SetErrorObj #define SWIG_SetErrorMsg SWIG_Python_SetErrorMsg #define SWIG_ErrorType(code) SWIG_Python_ErrorType(code) #define SWIG_Error(code, msg) SWIG_Python_SetErrorMsg(SWIG_ErrorType(code), msg) #define SWIG_fail goto fail /* Runtime API implementation */ /* Error manipulation */ SWIGINTERN void SWIG_Python_SetErrorObj(PyObject *errtype, PyObject *obj) { SWIG_PYTHON_THREAD_BEGIN_BLOCK; PyErr_SetObject(errtype, obj); Py_DECREF(obj); SWIG_PYTHON_THREAD_END_BLOCK; } SWIGINTERN void SWIG_Python_SetErrorMsg(PyObject *errtype, const char *msg) { SWIG_PYTHON_THREAD_BEGIN_BLOCK; PyErr_SetString(errtype, (char *) msg); SWIG_PYTHON_THREAD_END_BLOCK; } #define SWIG_Python_Raise(obj, type, desc) SWIG_Python_SetErrorObj(SWIG_Python_ExceptionType(desc), obj) /* Set a constant value */ SWIGINTERN void SWIG_Python_SetConstant(PyObject *d, const char *name, PyObject *obj) { PyDict_SetItemString(d, (char*) name, obj); Py_DECREF(obj); } /* Append a value to the result obj */ SWIGINTERN PyObject* SWIG_Python_AppendOutput(PyObject* result, PyObject* obj) { #if !defined(SWIG_PYTHON_OUTPUT_TUPLE) if (!result) { result = obj; } else if (result == Py_None) { Py_DECREF(result); result = obj; } else { if (!PyList_Check(result)) { PyObject *o2 = result; result = PyList_New(1); PyList_SetItem(result, 0, o2); } PyList_Append(result,obj); Py_DECREF(obj); } return result; #else PyObject* o2; PyObject* o3; if (!result) { result = obj; } else if (result == Py_None) { Py_DECREF(result); result = obj; } else { if (!PyTuple_Check(result)) { o2 = result; result = PyTuple_New(1); PyTuple_SET_ITEM(result, 0, o2); } o3 = PyTuple_New(1); PyTuple_SET_ITEM(o3, 0, obj); o2 = result; result = PySequence_Concat(o2, o3); Py_DECREF(o2); Py_DECREF(o3); } return result; #endif } /* Unpack the argument tuple */ SWIGINTERN int SWIG_Python_UnpackTuple(PyObject *args, const char *name, Py_ssize_t min, Py_ssize_t max, PyObject **objs) { if (!args) { if (!min && !max) { return 1; } else { PyErr_Format(PyExc_TypeError, "%s expected %s%d arguments, got none", name, (min == max ? "" : "at least "), (int)min); return 0; } } if (!PyTuple_Check(args)) { PyErr_SetString(PyExc_SystemError, "UnpackTuple() argument list is not a tuple"); return 0; } else { register Py_ssize_t l = PyTuple_GET_SIZE(args); if (l < min) { PyErr_Format(PyExc_TypeError, "%s expected %s%d arguments, got %d", name, (min == max ? "" : "at least "), (int)min, (int)l); return 0; } else if (l > max) { PyErr_Format(PyExc_TypeError, "%s expected %s%d arguments, got %d", name, (min == max ? "" : "at most "), (int)max, (int)l); return 0; } else { register int i; for (i = 0; i < l; ++i) { objs[i] = PyTuple_GET_ITEM(args, i); } for (; l < max; ++l) { objs[l] = 0; } return i + 1; } } } /* A functor is a function object with one single object argument */ #if PY_VERSION_HEX >= 0x02020000 #define SWIG_Python_CallFunctor(functor, obj) PyObject_CallFunctionObjArgs(functor, obj, NULL); #else #define SWIG_Python_CallFunctor(functor, obj) PyObject_CallFunction(functor, "O", obj); #endif /* Helper for static pointer initialization for both C and C++ code, for example static PyObject *SWIG_STATIC_POINTER(MyVar) = NewSomething(...); */ #ifdef __cplusplus #define SWIG_STATIC_POINTER(var) var #else #define SWIG_STATIC_POINTER(var) var = 0; if (!var) var #endif /* ----------------------------------------------------------------------------- * Pointer declarations * ----------------------------------------------------------------------------- */ /* Flags for new pointer objects */ #define SWIG_POINTER_NOSHADOW (SWIG_POINTER_OWN << 1) #define SWIG_POINTER_NEW (SWIG_POINTER_NOSHADOW | SWIG_POINTER_OWN) #define SWIG_POINTER_IMPLICIT_CONV (SWIG_POINTER_DISOWN << 1) #ifdef __cplusplus extern "C" { #if 0 } /* cc-mode */ #endif #endif /* How to access Py_None */ #if defined(_WIN32) || defined(__WIN32__) || defined(__CYGWIN__) # ifndef SWIG_PYTHON_NO_BUILD_NONE # ifndef SWIG_PYTHON_BUILD_NONE # define SWIG_PYTHON_BUILD_NONE # endif # endif #endif #ifdef SWIG_PYTHON_BUILD_NONE # ifdef Py_None # undef Py_None # define Py_None SWIG_Py_None() # endif SWIGRUNTIMEINLINE PyObject * _SWIG_Py_None(void) { PyObject *none = Py_BuildValue((char*)""); Py_DECREF(none); return none; } SWIGRUNTIME PyObject * SWIG_Py_None(void) { static PyObject *SWIG_STATIC_POINTER(none) = _SWIG_Py_None(); return none; } #endif /* The python void return value */ SWIGRUNTIMEINLINE PyObject * SWIG_Py_Void(void) { PyObject *none = Py_None; Py_INCREF(none); return none; } /* SwigPyClientData */ typedef struct { PyObject *klass; PyObject *newraw; PyObject *newargs; PyObject *destroy; int delargs; int implicitconv; } SwigPyClientData; SWIGRUNTIMEINLINE int SWIG_Python_CheckImplicit(swig_type_info *ty) { SwigPyClientData *data = (SwigPyClientData *)ty->clientdata; return data ? data->implicitconv : 0; } SWIGRUNTIMEINLINE PyObject * SWIG_Python_ExceptionType(swig_type_info *desc) { SwigPyClientData *data = desc ? (SwigPyClientData *) desc->clientdata : 0; PyObject *klass = data ? data->klass : 0; return (klass ? klass : PyExc_RuntimeError); } SWIGRUNTIME SwigPyClientData * SwigPyClientData_New(PyObject* obj) { if (!obj) { return 0; } else { SwigPyClientData *data = (SwigPyClientData *)malloc(sizeof(SwigPyClientData)); /* the klass element */ data->klass = obj; Py_INCREF(data->klass); /* the newraw method and newargs arguments used to create a new raw instance */ if (PyClass_Check(obj)) { data->newraw = 0; data->newargs = obj; Py_INCREF(obj); } else { #if (PY_VERSION_HEX < 0x02020000) data->newraw = 0; #else data->newraw = PyObject_GetAttrString(data->klass, (char *)"__new__"); #endif if (data->newraw) { Py_INCREF(data->newraw); data->newargs = PyTuple_New(1); PyTuple_SetItem(data->newargs, 0, obj); } else { data->newargs = obj; } Py_INCREF(data->newargs); } /* the destroy method, aka as the C++ delete method */ data->destroy = PyObject_GetAttrString(data->klass, (char *)"__swig_destroy__"); if (PyErr_Occurred()) { PyErr_Clear(); data->destroy = 0; } if (data->destroy) { int flags; Py_INCREF(data->destroy); flags = PyCFunction_GET_FLAGS(data->destroy); #ifdef METH_O data->delargs = !(flags & (METH_O)); #else data->delargs = 0; #endif } else { data->delargs = 0; } data->implicitconv = 0; return data; } } SWIGRUNTIME void SwigPyClientData_Del(SwigPyClientData* data) { Py_XDECREF(data->newraw); Py_XDECREF(data->newargs); Py_XDECREF(data->destroy); } /* =============== SwigPyObject =====================*/ typedef struct { PyObject_HEAD void *ptr; swig_type_info *ty; int own; PyObject *next; } SwigPyObject; SWIGRUNTIME PyObject * SwigPyObject_long(SwigPyObject *v) { return PyLong_FromVoidPtr(v->ptr); } SWIGRUNTIME PyObject * SwigPyObject_format(const char* fmt, SwigPyObject *v) { PyObject *res = NULL; PyObject *args = PyTuple_New(1); if (args) { if (PyTuple_SetItem(args, 0, SwigPyObject_long(v)) == 0) { PyObject *ofmt = SWIG_Python_str_FromChar(fmt); if (ofmt) { #if PY_VERSION_HEX >= 0x03000000 res = PyUnicode_Format(ofmt,args); #else res = PyString_Format(ofmt,args); #endif Py_DECREF(ofmt); } Py_DECREF(args); } } return res; } SWIGRUNTIME PyObject * SwigPyObject_oct(SwigPyObject *v) { return SwigPyObject_format("%o",v); } SWIGRUNTIME PyObject * SwigPyObject_hex(SwigPyObject *v) { return SwigPyObject_format("%x",v); } SWIGRUNTIME PyObject * #ifdef METH_NOARGS SwigPyObject_repr(SwigPyObject *v) #else SwigPyObject_repr(SwigPyObject *v, PyObject *args) #endif { const char *name = SWIG_TypePrettyName(v->ty); PyObject *repr = SWIG_Python_str_FromFormat("", name, v); if (v->next) { #ifdef METH_NOARGS PyObject *nrep = SwigPyObject_repr((SwigPyObject *)v->next); #else PyObject *nrep = SwigPyObject_repr((SwigPyObject *)v->next, args); #endif #if PY_VERSION_HEX >= 0x03000000 PyObject *joined = PyUnicode_Concat(repr, nrep); Py_DecRef(repr); Py_DecRef(nrep); repr = joined; #else PyString_ConcatAndDel(&repr,nrep); #endif } return repr; } SWIGRUNTIME int SwigPyObject_print(SwigPyObject *v, FILE *fp, int SWIGUNUSEDPARM(flags)) { char *str; #ifdef METH_NOARGS PyObject *repr = SwigPyObject_repr(v); #else PyObject *repr = SwigPyObject_repr(v, NULL); #endif if (repr) { str = SWIG_Python_str_AsChar(repr); fputs(str, fp); SWIG_Python_str_DelForPy3(str); Py_DECREF(repr); return 0; } else { return 1; } } SWIGRUNTIME PyObject * SwigPyObject_str(SwigPyObject *v) { char result[SWIG_BUFFER_SIZE]; return SWIG_PackVoidPtr(result, v->ptr, v->ty->name, sizeof(result)) ? SWIG_Python_str_FromChar(result) : 0; } SWIGRUNTIME int SwigPyObject_compare(SwigPyObject *v, SwigPyObject *w) { void *i = v->ptr; void *j = w->ptr; return (i < j) ? -1 : ((i > j) ? 1 : 0); } /* Added for Python 3.x, would it also be useful for Python 2.x? */ SWIGRUNTIME PyObject* SwigPyObject_richcompare(SwigPyObject *v, SwigPyObject *w, int op) { PyObject* res; if( op != Py_EQ && op != Py_NE ) { Py_INCREF(Py_NotImplemented); return Py_NotImplemented; } if( (SwigPyObject_compare(v, w)==0) == (op == Py_EQ) ) res = Py_True; else res = Py_False; Py_INCREF(res); return res; } SWIGRUNTIME PyTypeObject* _PySwigObject_type(void); SWIGRUNTIME PyTypeObject* SwigPyObject_type(void) { static PyTypeObject *SWIG_STATIC_POINTER(type) = _PySwigObject_type(); return type; } SWIGRUNTIMEINLINE int SwigPyObject_Check(PyObject *op) { return (Py_TYPE(op) == SwigPyObject_type()) || (strcmp(Py_TYPE(op)->tp_name,"SwigPyObject") == 0); } SWIGRUNTIME PyObject * SwigPyObject_New(void *ptr, swig_type_info *ty, int own); SWIGRUNTIME void SwigPyObject_dealloc(PyObject *v) { SwigPyObject *sobj = (SwigPyObject *) v; PyObject *next = sobj->next; if (sobj->own == SWIG_POINTER_OWN) { swig_type_info *ty = sobj->ty; SwigPyClientData *data = ty ? (SwigPyClientData *) ty->clientdata : 0; PyObject *destroy = data ? data->destroy : 0; if (destroy) { /* destroy is always a VARARGS method */ PyObject *res; if (data->delargs) { /* we need to create a temporary object to carry the destroy operation */ PyObject *tmp = SwigPyObject_New(sobj->ptr, ty, 0); res = SWIG_Python_CallFunctor(destroy, tmp); Py_DECREF(tmp); } else { PyCFunction meth = PyCFunction_GET_FUNCTION(destroy); PyObject *mself = PyCFunction_GET_SELF(destroy); res = ((*meth)(mself, v)); } Py_XDECREF(res); } #if !defined(SWIG_PYTHON_SILENT_MEMLEAK) else { const char *name = SWIG_TypePrettyName(ty); printf("swig/python detected a memory leak of type '%s', no destructor found.\n", (name ? name : "unknown")); } #endif } Py_XDECREF(next); PyObject_DEL(v); } SWIGRUNTIME PyObject* SwigPyObject_append(PyObject* v, PyObject* next) { SwigPyObject *sobj = (SwigPyObject *) v; #ifndef METH_O PyObject *tmp = 0; if (!PyArg_ParseTuple(next,(char *)"O:append", &tmp)) return NULL; next = tmp; #endif if (!SwigPyObject_Check(next)) { return NULL; } sobj->next = next; Py_INCREF(next); return SWIG_Py_Void(); } SWIGRUNTIME PyObject* #ifdef METH_NOARGS SwigPyObject_next(PyObject* v) #else SwigPyObject_next(PyObject* v, PyObject *SWIGUNUSEDPARM(args)) #endif { SwigPyObject *sobj = (SwigPyObject *) v; if (sobj->next) { Py_INCREF(sobj->next); return sobj->next; } else { return SWIG_Py_Void(); } } SWIGINTERN PyObject* #ifdef METH_NOARGS SwigPyObject_disown(PyObject *v) #else SwigPyObject_disown(PyObject* v, PyObject *SWIGUNUSEDPARM(args)) #endif { SwigPyObject *sobj = (SwigPyObject *)v; sobj->own = 0; return SWIG_Py_Void(); } SWIGINTERN PyObject* #ifdef METH_NOARGS SwigPyObject_acquire(PyObject *v) #else SwigPyObject_acquire(PyObject* v, PyObject *SWIGUNUSEDPARM(args)) #endif { SwigPyObject *sobj = (SwigPyObject *)v; sobj->own = SWIG_POINTER_OWN; return SWIG_Py_Void(); } SWIGINTERN PyObject* SwigPyObject_own(PyObject *v, PyObject *args) { PyObject *val = 0; #if (PY_VERSION_HEX < 0x02020000) if (!PyArg_ParseTuple(args,(char *)"|O:own",&val)) #else if (!PyArg_UnpackTuple(args, (char *)"own", 0, 1, &val)) #endif { return NULL; } else { SwigPyObject *sobj = (SwigPyObject *)v; PyObject *obj = PyBool_FromLong(sobj->own); if (val) { #ifdef METH_NOARGS if (PyObject_IsTrue(val)) { SwigPyObject_acquire(v); } else { SwigPyObject_disown(v); } #else if (PyObject_IsTrue(val)) { SwigPyObject_acquire(v,args); } else { SwigPyObject_disown(v,args); } #endif } return obj; } } #ifdef METH_O static PyMethodDef swigobject_methods[] = { {(char *)"disown", (PyCFunction)SwigPyObject_disown, METH_NOARGS, (char *)"releases ownership of the pointer"}, {(char *)"acquire", (PyCFunction)SwigPyObject_acquire, METH_NOARGS, (char *)"aquires ownership of the pointer"}, {(char *)"own", (PyCFunction)SwigPyObject_own, METH_VARARGS, (char *)"returns/sets ownership of the pointer"}, {(char *)"append", (PyCFunction)SwigPyObject_append, METH_O, (char *)"appends another 'this' object"}, {(char *)"next", (PyCFunction)SwigPyObject_next, METH_NOARGS, (char *)"returns the next 'this' object"}, {(char *)"__repr__",(PyCFunction)SwigPyObject_repr, METH_NOARGS, (char *)"returns object representation"}, {0, 0, 0, 0} }; #else static PyMethodDef swigobject_methods[] = { {(char *)"disown", (PyCFunction)SwigPyObject_disown, METH_VARARGS, (char *)"releases ownership of the pointer"}, {(char *)"acquire", (PyCFunction)SwigPyObject_acquire, METH_VARARGS, (char *)"aquires ownership of the pointer"}, {(char *)"own", (PyCFunction)SwigPyObject_own, METH_VARARGS, (char *)"returns/sets ownership of the pointer"}, {(char *)"append", (PyCFunction)SwigPyObject_append, METH_VARARGS, (char *)"appends another 'this' object"}, {(char *)"next", (PyCFunction)SwigPyObject_next, METH_VARARGS, (char *)"returns the next 'this' object"}, {(char *)"__repr__",(PyCFunction)SwigPyObject_repr, METH_VARARGS, (char *)"returns object representation"}, {0, 0, 0, 0} }; #endif #if PY_VERSION_HEX < 0x02020000 SWIGINTERN PyObject * SwigPyObject_getattr(SwigPyObject *sobj,char *name) { return Py_FindMethod(swigobject_methods, (PyObject *)sobj, name); } #endif SWIGRUNTIME PyTypeObject* _PySwigObject_type(void) { static char swigobject_doc[] = "Swig object carries a C/C++ instance pointer"; static PyNumberMethods SwigPyObject_as_number = { (binaryfunc)0, /*nb_add*/ (binaryfunc)0, /*nb_subtract*/ (binaryfunc)0, /*nb_multiply*/ /* nb_divide removed in Python 3 */ #if PY_VERSION_HEX < 0x03000000 (binaryfunc)0, /*nb_divide*/ #endif (binaryfunc)0, /*nb_remainder*/ (binaryfunc)0, /*nb_divmod*/ (ternaryfunc)0,/*nb_power*/ (unaryfunc)0, /*nb_negative*/ (unaryfunc)0, /*nb_positive*/ (unaryfunc)0, /*nb_absolute*/ (inquiry)0, /*nb_nonzero*/ 0, /*nb_invert*/ 0, /*nb_lshift*/ 0, /*nb_rshift*/ 0, /*nb_and*/ 0, /*nb_xor*/ 0, /*nb_or*/ #if PY_VERSION_HEX < 0x03000000 0, /*nb_coerce*/ #endif (unaryfunc)SwigPyObject_long, /*nb_int*/ #if PY_VERSION_HEX < 0x03000000 (unaryfunc)SwigPyObject_long, /*nb_long*/ #else 0, /*nb_reserved*/ #endif (unaryfunc)0, /*nb_float*/ #if PY_VERSION_HEX < 0x03000000 (unaryfunc)SwigPyObject_oct, /*nb_oct*/ (unaryfunc)SwigPyObject_hex, /*nb_hex*/ #endif #if PY_VERSION_HEX >= 0x03000000 /* 3.0 */ 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 /* nb_inplace_add -> nb_index, nb_inplace_divide removed */ #elif PY_VERSION_HEX >= 0x02050000 /* 2.5.0 */ 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 /* nb_inplace_add -> nb_index */ #elif PY_VERSION_HEX >= 0x02020000 /* 2.2.0 */ 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 /* nb_inplace_add -> nb_inplace_true_divide */ #elif PY_VERSION_HEX >= 0x02000000 /* 2.0.0 */ 0,0,0,0,0,0,0,0,0,0,0 /* nb_inplace_add -> nb_inplace_or */ #endif }; static PyTypeObject swigpyobject_type; static int type_init = 0; if (!type_init) { const PyTypeObject tmp = { /* PyObject header changed in Python 3 */ #if PY_VERSION_HEX >= 0x03000000 PyVarObject_HEAD_INIT(&PyType_Type, 0) #else PyObject_HEAD_INIT(NULL) 0, /* ob_size */ #endif (char *)"SwigPyObject", /* tp_name */ sizeof(SwigPyObject), /* tp_basicsize */ 0, /* tp_itemsize */ (destructor)SwigPyObject_dealloc, /* tp_dealloc */ (printfunc)SwigPyObject_print, /* tp_print */ #if PY_VERSION_HEX < 0x02020000 (getattrfunc)SwigPyObject_getattr, /* tp_getattr */ #else (getattrfunc)0, /* tp_getattr */ #endif (setattrfunc)0, /* tp_setattr */ #if PY_VERSION_HEX >= 0x03000000 0, /* tp_reserved in 3.0.1, tp_compare in 3.0.0 but not used */ #else (cmpfunc)SwigPyObject_compare, /* tp_compare */ #endif (reprfunc)SwigPyObject_repr, /* tp_repr */ &SwigPyObject_as_number, /* tp_as_number */ 0, /* tp_as_sequence */ 0, /* tp_as_mapping */ (hashfunc)0, /* tp_hash */ (ternaryfunc)0, /* tp_call */ (reprfunc)SwigPyObject_str, /* tp_str */ PyObject_GenericGetAttr, /* tp_getattro */ 0, /* tp_setattro */ 0, /* tp_as_buffer */ Py_TPFLAGS_DEFAULT, /* tp_flags */ swigobject_doc, /* tp_doc */ 0, /* tp_traverse */ 0, /* tp_clear */ (richcmpfunc)SwigPyObject_richcompare, /* tp_richcompare */ 0, /* tp_weaklistoffset */ #if PY_VERSION_HEX >= 0x02020000 0, /* tp_iter */ 0, /* tp_iternext */ swigobject_methods, /* tp_methods */ 0, /* tp_members */ 0, /* tp_getset */ 0, /* tp_base */ 0, /* tp_dict */ 0, /* tp_descr_get */ 0, /* tp_descr_set */ 0, /* tp_dictoffset */ 0, /* tp_init */ 0, /* tp_alloc */ 0, /* tp_new */ 0, /* tp_free */ 0, /* tp_is_gc */ 0, /* tp_bases */ 0, /* tp_mro */ 0, /* tp_cache */ 0, /* tp_subclasses */ 0, /* tp_weaklist */ #endif #if PY_VERSION_HEX >= 0x02030000 0, /* tp_del */ #endif #ifdef COUNT_ALLOCS 0,0,0,0 /* tp_alloc -> tp_next */ #endif }; swigpyobject_type = tmp; /* for Python 3 we already assigned ob_type in PyVarObject_HEAD_INIT() */ #if PY_VERSION_HEX < 0x03000000 swigpyobject_type.ob_type = &PyType_Type; #endif type_init = 1; } return &swigpyobject_type; } SWIGRUNTIME PyObject * SwigPyObject_New(void *ptr, swig_type_info *ty, int own) { SwigPyObject *sobj = PyObject_NEW(SwigPyObject, SwigPyObject_type()); if (sobj) { sobj->ptr = ptr; sobj->ty = ty; sobj->own = own; sobj->next = 0; } return (PyObject *)sobj; } /* ----------------------------------------------------------------------------- * Implements a simple Swig Packed type, and use it instead of string * ----------------------------------------------------------------------------- */ typedef struct { PyObject_HEAD void *pack; swig_type_info *ty; size_t size; } SwigPyPacked; SWIGRUNTIME int SwigPyPacked_print(SwigPyPacked *v, FILE *fp, int SWIGUNUSEDPARM(flags)) { char result[SWIG_BUFFER_SIZE]; fputs("pack, v->size, 0, sizeof(result))) { fputs("at ", fp); fputs(result, fp); } fputs(v->ty->name,fp); fputs(">", fp); return 0; } SWIGRUNTIME PyObject * SwigPyPacked_repr(SwigPyPacked *v) { char result[SWIG_BUFFER_SIZE]; if (SWIG_PackDataName(result, v->pack, v->size, 0, sizeof(result))) { return SWIG_Python_str_FromFormat("", result, v->ty->name); } else { return SWIG_Python_str_FromFormat("", v->ty->name); } } SWIGRUNTIME PyObject * SwigPyPacked_str(SwigPyPacked *v) { char result[SWIG_BUFFER_SIZE]; if (SWIG_PackDataName(result, v->pack, v->size, 0, sizeof(result))){ return SWIG_Python_str_FromFormat("%s%s", result, v->ty->name); } else { return SWIG_Python_str_FromChar(v->ty->name); } } SWIGRUNTIME int SwigPyPacked_compare(SwigPyPacked *v, SwigPyPacked *w) { size_t i = v->size; size_t j = w->size; int s = (i < j) ? -1 : ((i > j) ? 1 : 0); return s ? s : strncmp((char *)v->pack, (char *)w->pack, 2*v->size); } SWIGRUNTIME PyTypeObject* _PySwigPacked_type(void); SWIGRUNTIME PyTypeObject* SwigPyPacked_type(void) { static PyTypeObject *SWIG_STATIC_POINTER(type) = _PySwigPacked_type(); return type; } SWIGRUNTIMEINLINE int SwigPyPacked_Check(PyObject *op) { return ((op)->ob_type == _PySwigPacked_type()) || (strcmp((op)->ob_type->tp_name,"SwigPyPacked") == 0); } SWIGRUNTIME void SwigPyPacked_dealloc(PyObject *v) { if (SwigPyPacked_Check(v)) { SwigPyPacked *sobj = (SwigPyPacked *) v; free(sobj->pack); } PyObject_DEL(v); } SWIGRUNTIME PyTypeObject* _PySwigPacked_type(void) { static char swigpacked_doc[] = "Swig object carries a C/C++ instance pointer"; static PyTypeObject swigpypacked_type; static int type_init = 0; if (!type_init) { const PyTypeObject tmp = { /* PyObject header changed in Python 3 */ #if PY_VERSION_HEX>=0x03000000 PyVarObject_HEAD_INIT(&PyType_Type, 0) #else PyObject_HEAD_INIT(NULL) 0, /* ob_size */ #endif (char *)"SwigPyPacked", /* tp_name */ sizeof(SwigPyPacked), /* tp_basicsize */ 0, /* tp_itemsize */ (destructor)SwigPyPacked_dealloc, /* tp_dealloc */ (printfunc)SwigPyPacked_print, /* tp_print */ (getattrfunc)0, /* tp_getattr */ (setattrfunc)0, /* tp_setattr */ #if PY_VERSION_HEX>=0x03000000 0, /* tp_reserved in 3.0.1 */ #else (cmpfunc)SwigPyPacked_compare, /* tp_compare */ #endif (reprfunc)SwigPyPacked_repr, /* tp_repr */ 0, /* tp_as_number */ 0, /* tp_as_sequence */ 0, /* tp_as_mapping */ (hashfunc)0, /* tp_hash */ (ternaryfunc)0, /* tp_call */ (reprfunc)SwigPyPacked_str, /* tp_str */ PyObject_GenericGetAttr, /* tp_getattro */ 0, /* tp_setattro */ 0, /* tp_as_buffer */ Py_TPFLAGS_DEFAULT, /* tp_flags */ swigpacked_doc, /* tp_doc */ 0, /* tp_traverse */ 0, /* tp_clear */ 0, /* tp_richcompare */ 0, /* tp_weaklistoffset */ #if PY_VERSION_HEX >= 0x02020000 0, /* tp_iter */ 0, /* tp_iternext */ 0, /* tp_methods */ 0, /* tp_members */ 0, /* tp_getset */ 0, /* tp_base */ 0, /* tp_dict */ 0, /* tp_descr_get */ 0, /* tp_descr_set */ 0, /* tp_dictoffset */ 0, /* tp_init */ 0, /* tp_alloc */ 0, /* tp_new */ 0, /* tp_free */ 0, /* tp_is_gc */ 0, /* tp_bases */ 0, /* tp_mro */ 0, /* tp_cache */ 0, /* tp_subclasses */ 0, /* tp_weaklist */ #endif #if PY_VERSION_HEX >= 0x02030000 0, /* tp_del */ #endif #ifdef COUNT_ALLOCS 0,0,0,0 /* tp_alloc -> tp_next */ #endif }; swigpypacked_type = tmp; /* for Python 3 the ob_type already assigned in PyVarObject_HEAD_INIT() */ #if PY_VERSION_HEX < 0x03000000 swigpypacked_type.ob_type = &PyType_Type; #endif type_init = 1; } return &swigpypacked_type; } SWIGRUNTIME PyObject * SwigPyPacked_New(void *ptr, size_t size, swig_type_info *ty) { SwigPyPacked *sobj = PyObject_NEW(SwigPyPacked, SwigPyPacked_type()); if (sobj) { void *pack = malloc(size); if (pack) { memcpy(pack, ptr, size); sobj->pack = pack; sobj->ty = ty; sobj->size = size; } else { PyObject_DEL((PyObject *) sobj); sobj = 0; } } return (PyObject *) sobj; } SWIGRUNTIME swig_type_info * SwigPyPacked_UnpackData(PyObject *obj, void *ptr, size_t size) { if (SwigPyPacked_Check(obj)) { SwigPyPacked *sobj = (SwigPyPacked *)obj; if (sobj->size != size) return 0; memcpy(ptr, sobj->pack, size); return sobj->ty; } else { return 0; } } /* ----------------------------------------------------------------------------- * pointers/data manipulation * ----------------------------------------------------------------------------- */ SWIGRUNTIMEINLINE PyObject * _SWIG_This(void) { return SWIG_Python_str_FromChar("this"); } SWIGRUNTIME PyObject * SWIG_This(void) { static PyObject *SWIG_STATIC_POINTER(swig_this) = _SWIG_This(); return swig_this; } /* #define SWIG_PYTHON_SLOW_GETSET_THIS */ /* TODO: I don't know how to implement the fast getset in Python 3 right now */ #if PY_VERSION_HEX>=0x03000000 #define SWIG_PYTHON_SLOW_GETSET_THIS #endif SWIGRUNTIME SwigPyObject * SWIG_Python_GetSwigThis(PyObject *pyobj) { if (SwigPyObject_Check(pyobj)) { return (SwigPyObject *) pyobj; } else { PyObject *obj = 0; #if (!defined(SWIG_PYTHON_SLOW_GETSET_THIS) && (PY_VERSION_HEX >= 0x02030000)) if (PyInstance_Check(pyobj)) { obj = _PyInstance_Lookup(pyobj, SWIG_This()); } else { PyObject **dictptr = _PyObject_GetDictPtr(pyobj); if (dictptr != NULL) { PyObject *dict = *dictptr; obj = dict ? PyDict_GetItem(dict, SWIG_This()) : 0; } else { #ifdef PyWeakref_CheckProxy if (PyWeakref_CheckProxy(pyobj)) { PyObject *wobj = PyWeakref_GET_OBJECT(pyobj); return wobj ? SWIG_Python_GetSwigThis(wobj) : 0; } #endif obj = PyObject_GetAttr(pyobj,SWIG_This()); if (obj) { Py_DECREF(obj); } else { if (PyErr_Occurred()) PyErr_Clear(); return 0; } } } #else obj = PyObject_GetAttr(pyobj,SWIG_This()); if (obj) { Py_DECREF(obj); } else { if (PyErr_Occurred()) PyErr_Clear(); return 0; } #endif if (obj && !SwigPyObject_Check(obj)) { /* a PyObject is called 'this', try to get the 'real this' SwigPyObject from it */ return SWIG_Python_GetSwigThis(obj); } return (SwigPyObject *)obj; } } /* Acquire a pointer value */ SWIGRUNTIME int SWIG_Python_AcquirePtr(PyObject *obj, int own) { if (own == SWIG_POINTER_OWN) { SwigPyObject *sobj = SWIG_Python_GetSwigThis(obj); if (sobj) { int oldown = sobj->own; sobj->own = own; return oldown; } } return 0; } /* Convert a pointer value */ SWIGRUNTIME int SWIG_Python_ConvertPtrAndOwn(PyObject *obj, void **ptr, swig_type_info *ty, int flags, int *own) { if (!obj) return SWIG_ERROR; if (obj == Py_None) { if (ptr) *ptr = 0; return SWIG_OK; } else { SwigPyObject *sobj = SWIG_Python_GetSwigThis(obj); if (own) *own = 0; while (sobj) { void *vptr = sobj->ptr; if (ty) { swig_type_info *to = sobj->ty; if (to == ty) { /* no type cast needed */ if (ptr) *ptr = vptr; break; } else { swig_cast_info *tc = SWIG_TypeCheck(to->name,ty); if (!tc) { sobj = (SwigPyObject *)sobj->next; } else { if (ptr) { int newmemory = 0; *ptr = SWIG_TypeCast(tc,vptr,&newmemory); if (newmemory == SWIG_CAST_NEW_MEMORY) { assert(own); if (own) *own = *own | SWIG_CAST_NEW_MEMORY; } } break; } } } else { if (ptr) *ptr = vptr; break; } } if (sobj) { if (own) *own = *own | sobj->own; if (flags & SWIG_POINTER_DISOWN) { sobj->own = 0; } return SWIG_OK; } else { int res = SWIG_ERROR; if (flags & SWIG_POINTER_IMPLICIT_CONV) { SwigPyClientData *data = ty ? (SwigPyClientData *) ty->clientdata : 0; if (data && !data->implicitconv) { PyObject *klass = data->klass; if (klass) { PyObject *impconv; data->implicitconv = 1; /* avoid recursion and call 'explicit' constructors*/ impconv = SWIG_Python_CallFunctor(klass, obj); data->implicitconv = 0; if (PyErr_Occurred()) { PyErr_Clear(); impconv = 0; } if (impconv) { SwigPyObject *iobj = SWIG_Python_GetSwigThis(impconv); if (iobj) { void *vptr; res = SWIG_Python_ConvertPtrAndOwn((PyObject*)iobj, &vptr, ty, 0, 0); if (SWIG_IsOK(res)) { if (ptr) { *ptr = vptr; /* transfer the ownership to 'ptr' */ iobj->own = 0; res = SWIG_AddCast(res); res = SWIG_AddNewMask(res); } else { res = SWIG_AddCast(res); } } } Py_DECREF(impconv); } } } } return res; } } } /* Convert a function ptr value */ SWIGRUNTIME int SWIG_Python_ConvertFunctionPtr(PyObject *obj, void **ptr, swig_type_info *ty) { if (!PyCFunction_Check(obj)) { return SWIG_ConvertPtr(obj, ptr, ty, 0); } else { void *vptr = 0; /* here we get the method pointer for callbacks */ const char *doc = (((PyCFunctionObject *)obj) -> m_ml -> ml_doc); const char *desc = doc ? strstr(doc, "swig_ptr: ") : 0; if (desc) desc = ty ? SWIG_UnpackVoidPtr(desc + 10, &vptr, ty->name) : 0; if (!desc) return SWIG_ERROR; if (ty) { swig_cast_info *tc = SWIG_TypeCheck(desc,ty); if (tc) { int newmemory = 0; *ptr = SWIG_TypeCast(tc,vptr,&newmemory); assert(!newmemory); /* newmemory handling not yet implemented */ } else { return SWIG_ERROR; } } else { *ptr = vptr; } return SWIG_OK; } } /* Convert a packed value value */ SWIGRUNTIME int SWIG_Python_ConvertPacked(PyObject *obj, void *ptr, size_t sz, swig_type_info *ty) { swig_type_info *to = SwigPyPacked_UnpackData(obj, ptr, sz); if (!to) return SWIG_ERROR; if (ty) { if (to != ty) { /* check type cast? */ swig_cast_info *tc = SWIG_TypeCheck(to->name,ty); if (!tc) return SWIG_ERROR; } } return SWIG_OK; } /* ----------------------------------------------------------------------------- * Create a new pointer object * ----------------------------------------------------------------------------- */ /* Create a new instance object, without calling __init__, and set the 'this' attribute. */ SWIGRUNTIME PyObject* SWIG_Python_NewShadowInstance(SwigPyClientData *data, PyObject *swig_this) { #if (PY_VERSION_HEX >= 0x02020000) PyObject *inst = 0; PyObject *newraw = data->newraw; if (newraw) { inst = PyObject_Call(newraw, data->newargs, NULL); if (inst) { #if !defined(SWIG_PYTHON_SLOW_GETSET_THIS) PyObject **dictptr = _PyObject_GetDictPtr(inst); if (dictptr != NULL) { PyObject *dict = *dictptr; if (dict == NULL) { dict = PyDict_New(); *dictptr = dict; PyDict_SetItem(dict, SWIG_This(), swig_this); } } #else PyObject *key = SWIG_This(); PyObject_SetAttr(inst, key, swig_this); #endif } } else { #if PY_VERSION_HEX >= 0x03000000 inst = PyBaseObject_Type.tp_new((PyTypeObject*) data->newargs, Py_None, Py_None); PyObject_SetAttr(inst, SWIG_This(), swig_this); Py_TYPE(inst)->tp_flags &= ~Py_TPFLAGS_VALID_VERSION_TAG; #else PyObject *dict = PyDict_New(); PyDict_SetItem(dict, SWIG_This(), swig_this); inst = PyInstance_NewRaw(data->newargs, dict); Py_DECREF(dict); #endif } return inst; #else #if (PY_VERSION_HEX >= 0x02010000) PyObject *inst; PyObject *dict = PyDict_New(); PyDict_SetItem(dict, SWIG_This(), swig_this); inst = PyInstance_NewRaw(data->newargs, dict); Py_DECREF(dict); return (PyObject *) inst; #else PyInstanceObject *inst = PyObject_NEW(PyInstanceObject, &PyInstance_Type); if (inst == NULL) { return NULL; } inst->in_class = (PyClassObject *)data->newargs; Py_INCREF(inst->in_class); inst->in_dict = PyDict_New(); if (inst->in_dict == NULL) { Py_DECREF(inst); return NULL; } #ifdef Py_TPFLAGS_HAVE_WEAKREFS inst->in_weakreflist = NULL; #endif #ifdef Py_TPFLAGS_GC PyObject_GC_Init(inst); #endif PyDict_SetItem(inst->in_dict, SWIG_This(), swig_this); return (PyObject *) inst; #endif #endif } SWIGRUNTIME void SWIG_Python_SetSwigThis(PyObject *inst, PyObject *swig_this) { PyObject *dict; #if (PY_VERSION_HEX >= 0x02020000) && !defined(SWIG_PYTHON_SLOW_GETSET_THIS) PyObject **dictptr = _PyObject_GetDictPtr(inst); if (dictptr != NULL) { dict = *dictptr; if (dict == NULL) { dict = PyDict_New(); *dictptr = dict; } PyDict_SetItem(dict, SWIG_This(), swig_this); return; } #endif dict = PyObject_GetAttrString(inst, (char*)"__dict__"); PyDict_SetItem(dict, SWIG_This(), swig_this); Py_DECREF(dict); } SWIGINTERN PyObject * SWIG_Python_InitShadowInstance(PyObject *args) { PyObject *obj[2]; if (!SWIG_Python_UnpackTuple(args,(char*)"swiginit", 2, 2, obj)) { return NULL; } else { SwigPyObject *sthis = SWIG_Python_GetSwigThis(obj[0]); if (sthis) { SwigPyObject_append((PyObject*) sthis, obj[1]); } else { SWIG_Python_SetSwigThis(obj[0], obj[1]); } return SWIG_Py_Void(); } } /* Create a new pointer object */ SWIGRUNTIME PyObject * SWIG_Python_NewPointerObj(void *ptr, swig_type_info *type, int flags) { if (!ptr) { return SWIG_Py_Void(); } else { int own = (flags & SWIG_POINTER_OWN) ? SWIG_POINTER_OWN : 0; PyObject *robj = SwigPyObject_New(ptr, type, own); SwigPyClientData *clientdata = type ? (SwigPyClientData *)(type->clientdata) : 0; if (clientdata && !(flags & SWIG_POINTER_NOSHADOW)) { PyObject *inst = SWIG_Python_NewShadowInstance(clientdata, robj); if (inst) { Py_DECREF(robj); robj = inst; } } return robj; } } /* Create a new packed object */ SWIGRUNTIMEINLINE PyObject * SWIG_Python_NewPackedObj(void *ptr, size_t sz, swig_type_info *type) { return ptr ? SwigPyPacked_New((void *) ptr, sz, type) : SWIG_Py_Void(); } /* -----------------------------------------------------------------------------* * Get type list * -----------------------------------------------------------------------------*/ #ifdef SWIG_LINK_RUNTIME void *SWIG_ReturnGlobalTypeList(void *); #endif SWIGRUNTIME swig_module_info * SWIG_Python_GetModule(void) { static void *type_pointer = (void *)0; /* first check if module already created */ if (!type_pointer) { #ifdef SWIG_LINK_RUNTIME type_pointer = SWIG_ReturnGlobalTypeList((void *)0); #else type_pointer = PyCObject_Import((char*)"swig_runtime_data" SWIG_RUNTIME_VERSION, (char*)"type_pointer" SWIG_TYPE_TABLE_NAME); if (PyErr_Occurred()) { PyErr_Clear(); type_pointer = (void *)0; } #endif } return (swig_module_info *) type_pointer; } #if PY_MAJOR_VERSION < 2 /* PyModule_AddObject function was introduced in Python 2.0. The following function is copied out of Python/modsupport.c in python version 2.3.4 */ SWIGINTERN int PyModule_AddObject(PyObject *m, char *name, PyObject *o) { PyObject *dict; if (!PyModule_Check(m)) { PyErr_SetString(PyExc_TypeError, "PyModule_AddObject() needs module as first arg"); return SWIG_ERROR; } if (!o) { PyErr_SetString(PyExc_TypeError, "PyModule_AddObject() needs non-NULL value"); return SWIG_ERROR; } dict = PyModule_GetDict(m); if (dict == NULL) { /* Internal error -- modules must have a dict! */ PyErr_Format(PyExc_SystemError, "module '%s' has no __dict__", PyModule_GetName(m)); return SWIG_ERROR; } if (PyDict_SetItemString(dict, name, o)) return SWIG_ERROR; Py_DECREF(o); return SWIG_OK; } #endif SWIGRUNTIME void SWIG_Python_DestroyModule(void *vptr) { swig_module_info *swig_module = (swig_module_info *) vptr; swig_type_info **types = swig_module->types; size_t i; for (i =0; i < swig_module->size; ++i) { swig_type_info *ty = types[i]; if (ty->owndata) { SwigPyClientData *data = (SwigPyClientData *) ty->clientdata; if (data) SwigPyClientData_Del(data); } } Py_DECREF(SWIG_This()); } SWIGRUNTIME void SWIG_Python_SetModule(swig_module_info *swig_module) { static PyMethodDef swig_empty_runtime_method_table[] = { {NULL, NULL, 0, NULL} };/* Sentinel */ #if PY_VERSION_HEX >= 0x03000000 /* Add a dummy module object into sys.modules */ PyObject *module = PyImport_AddModule((char*)"swig_runtime_data" SWIG_RUNTIME_VERSION); #else PyObject *module = Py_InitModule((char*)"swig_runtime_data" SWIG_RUNTIME_VERSION, swig_empty_runtime_method_table); #endif PyObject *pointer = PyCObject_FromVoidPtr((void *) swig_module, SWIG_Python_DestroyModule); if (pointer && module) { PyModule_AddObject(module, (char*)"type_pointer" SWIG_TYPE_TABLE_NAME, pointer); } else { Py_XDECREF(pointer); } } /* The python cached type query */ SWIGRUNTIME PyObject * SWIG_Python_TypeCache(void) { static PyObject *SWIG_STATIC_POINTER(cache) = PyDict_New(); return cache; } SWIGRUNTIME swig_type_info * SWIG_Python_TypeQuery(const char *type) { PyObject *cache = SWIG_Python_TypeCache(); PyObject *key = SWIG_Python_str_FromChar(type); PyObject *obj = PyDict_GetItem(cache, key); swig_type_info *descriptor; if (obj) { descriptor = (swig_type_info *) PyCObject_AsVoidPtr(obj); } else { swig_module_info *swig_module = SWIG_Python_GetModule(); descriptor = SWIG_TypeQueryModule(swig_module, swig_module, type); if (descriptor) { obj = PyCObject_FromVoidPtr(descriptor, NULL); PyDict_SetItem(cache, key, obj); Py_DECREF(obj); } } Py_DECREF(key); return descriptor; } /* For backward compatibility only */ #define SWIG_POINTER_EXCEPTION 0 #define SWIG_arg_fail(arg) SWIG_Python_ArgFail(arg) #define SWIG_MustGetPtr(p, type, argnum, flags) SWIG_Python_MustGetPtr(p, type, argnum, flags) SWIGRUNTIME int SWIG_Python_AddErrMesg(const char* mesg, int infront) { if (PyErr_Occurred()) { PyObject *type = 0; PyObject *value = 0; PyObject *traceback = 0; PyErr_Fetch(&type, &value, &traceback); if (value) { char *tmp; PyObject *old_str = PyObject_Str(value); Py_XINCREF(type); PyErr_Clear(); if (infront) { PyErr_Format(type, "%s %s", mesg, tmp = SWIG_Python_str_AsChar(old_str)); } else { PyErr_Format(type, "%s %s", tmp = SWIG_Python_str_AsChar(old_str), mesg); } SWIG_Python_str_DelForPy3(tmp); Py_DECREF(old_str); } return 1; } else { return 0; } } SWIGRUNTIME int SWIG_Python_ArgFail(int argnum) { if (PyErr_Occurred()) { /* add information about failing argument */ char mesg[256]; PyOS_snprintf(mesg, sizeof(mesg), "argument number %d:", argnum); return SWIG_Python_AddErrMesg(mesg, 1); } else { return 0; } } SWIGRUNTIMEINLINE const char * SwigPyObject_GetDesc(PyObject *self) { SwigPyObject *v = (SwigPyObject *)self; swig_type_info *ty = v ? v->ty : 0; return ty ? ty->str : (char*)""; } SWIGRUNTIME void SWIG_Python_TypeError(const char *type, PyObject *obj) { if (type) { #if defined(SWIG_COBJECT_TYPES) if (obj && SwigPyObject_Check(obj)) { const char *otype = (const char *) SwigPyObject_GetDesc(obj); if (otype) { PyErr_Format(PyExc_TypeError, "a '%s' is expected, 'SwigPyObject(%s)' is received", type, otype); return; } } else #endif { const char *otype = (obj ? obj->ob_type->tp_name : 0); if (otype) { PyObject *str = PyObject_Str(obj); const char *cstr = str ? SWIG_Python_str_AsChar(str) : 0; if (cstr) { PyErr_Format(PyExc_TypeError, "a '%s' is expected, '%s(%s)' is received", type, otype, cstr); SWIG_Python_str_DelForPy3(cstr); } else { PyErr_Format(PyExc_TypeError, "a '%s' is expected, '%s' is received", type, otype); } Py_XDECREF(str); return; } } PyErr_Format(PyExc_TypeError, "a '%s' is expected", type); } else { PyErr_Format(PyExc_TypeError, "unexpected type is received"); } } /* Convert a pointer value, signal an exception on a type mismatch */ SWIGRUNTIME void * SWIG_Python_MustGetPtr(PyObject *obj, swig_type_info *ty, int argnum, int flags) { void *result; if (SWIG_Python_ConvertPtr(obj, &result, ty, flags) == -1) { PyErr_Clear(); #if SWIG_POINTER_EXCEPTION if (flags) { SWIG_Python_TypeError(SWIG_TypePrettyName(ty), obj); SWIG_Python_ArgFail(argnum); } #endif } return result; } #ifdef __cplusplus #if 0 { /* cc-mode */ #endif } #endif #define SWIG_exception_fail(code, msg) do { SWIG_Error(code, msg); SWIG_fail; } while(0) #define SWIG_contract_assert(expr, msg) if (!(expr)) { SWIG_Error(SWIG_RuntimeError, msg); SWIG_fail; } else /* -------- TYPES TABLE (BEGIN) -------- */ #define SWIGTYPE_p_CBF_NODETYPE swig_types[0] #define SWIGTYPE_p_a_4__double swig_types[1] #define SWIGTYPE_p_a_4__doubleArray swig_types[2] #define SWIGTYPE_p_cbf_axis_struct swig_types[3] #define SWIGTYPE_p_cbf_detector_struct swig_types[4] #define SWIGTYPE_p_cbf_handle_struct swig_types[5] #define SWIGTYPE_p_cbf_node swig_types[6] #define SWIGTYPE_p_cbf_positioner swig_types[7] #define SWIGTYPE_p_cbf_positioner_struct swig_types[8] #define SWIGTYPE_p_char swig_types[9] #define SWIGTYPE_p_double swig_types[10] #define SWIGTYPE_p_doubleArray swig_types[11] #define SWIGTYPE_p_int swig_types[12] #define SWIGTYPE_p_intArray swig_types[13] #define SWIGTYPE_p_long swig_types[14] #define SWIGTYPE_p_longArray swig_types[15] #define SWIGTYPE_p_p_char swig_types[16] #define SWIGTYPE_p_short swig_types[17] #define SWIGTYPE_p_shortArray swig_types[18] #define SWIGTYPE_p_size_t swig_types[19] #define SWIGTYPE_p_void swig_types[20] static swig_type_info *swig_types[22]; static swig_module_info swig_module = {swig_types, 21, 0, 0, 0, 0}; #define SWIG_TypeQuery(name) SWIG_TypeQueryModule(&swig_module, &swig_module, name) #define SWIG_MangledTypeQuery(name) SWIG_MangledTypeQueryModule(&swig_module, &swig_module, name) /* -------- TYPES TABLE (END) -------- */ #if (PY_VERSION_HEX <= 0x02000000) # if !defined(SWIG_PYTHON_CLASSIC) # error "This python version requires swig to be run with the '-classic' option" # endif #endif /*----------------------------------------------- @(target):= _pycbf.so ------------------------------------------------*/ #if PY_VERSION_HEX >= 0x03000000 # define SWIG_init PyInit__pycbf #else # define SWIG_init init_pycbf #endif #define SWIG_name "_pycbf" #define SWIGVERSION 0x010340 #define SWIG_VERSION SWIGVERSION #define SWIG_as_voidptr(a) (void *)((const void *)(a)) #define SWIG_as_voidptrptr(a) ((void)SWIG_as_voidptr(*a),(void**)(a)) typedef double doubleArray; SWIGINTERN int SWIG_AsVal_double (PyObject *obj, double *val) { int res = SWIG_TypeError; if (PyFloat_Check(obj)) { if (val) *val = PyFloat_AsDouble(obj); return SWIG_OK; } else if (PyInt_Check(obj)) { if (val) *val = PyInt_AsLong(obj); return SWIG_OK; } else if (PyLong_Check(obj)) { double v = PyLong_AsDouble(obj); if (!PyErr_Occurred()) { if (val) *val = v; return SWIG_OK; } else { PyErr_Clear(); } } #ifdef SWIG_PYTHON_CAST_MODE { int dispatch = 0; double d = PyFloat_AsDouble(obj); if (!PyErr_Occurred()) { if (val) *val = d; return SWIG_AddCast(SWIG_OK); } else { PyErr_Clear(); } if (!dispatch) { long v = PyLong_AsLong(obj); if (!PyErr_Occurred()) { if (val) *val = v; return SWIG_AddCast(SWIG_AddCast(SWIG_OK)); } else { PyErr_Clear(); } } } #endif return res; } #include #include SWIGINTERNINLINE int SWIG_CanCastAsInteger(double *d, double min, double max) { double x = *d; if ((min <= x && x <= max)) { double fx = floor(x); double cx = ceil(x); double rd = ((x - fx) < 0.5) ? fx : cx; /* simple rint */ if ((errno == EDOM) || (errno == ERANGE)) { errno = 0; } else { double summ, reps, diff; if (rd < x) { diff = x - rd; } else if (rd > x) { diff = rd - x; } else { return 1; } summ = rd + x; reps = diff/summ; if (reps < 8*DBL_EPSILON) { *d = rd; return 1; } } } return 0; } SWIGINTERN int SWIG_AsVal_unsigned_SS_long (PyObject *obj, unsigned long *val) { if (PyInt_Check(obj)) { long v = PyInt_AsLong(obj); if (v >= 0) { if (val) *val = v; return SWIG_OK; } else { return SWIG_OverflowError; } } else if (PyLong_Check(obj)) { unsigned long v = PyLong_AsUnsignedLong(obj); if (!PyErr_Occurred()) { if (val) *val = v; return SWIG_OK; } else { PyErr_Clear(); } } #ifdef SWIG_PYTHON_CAST_MODE { int dispatch = 0; unsigned long v = PyLong_AsUnsignedLong(obj); if (!PyErr_Occurred()) { if (val) *val = v; return SWIG_AddCast(SWIG_OK); } else { PyErr_Clear(); } if (!dispatch) { double d; int res = SWIG_AddCast(SWIG_AsVal_double (obj,&d)); if (SWIG_IsOK(res) && SWIG_CanCastAsInteger(&d, 0, ULONG_MAX)) { if (val) *val = (unsigned long)(d); return res; } } } #endif return SWIG_TypeError; } SWIGINTERNINLINE int SWIG_AsVal_size_t (PyObject * obj, size_t *val) { unsigned long v; int res = SWIG_AsVal_unsigned_SS_long (obj, val ? &v : 0); if (SWIG_IsOK(res) && val) *val = (size_t)(v); return res; } SWIGINTERN doubleArray *new_doubleArray(size_t nelements){ return (double *)malloc((nelements)*sizeof(double)); } SWIGINTERN void delete_doubleArray(doubleArray *self){ free((char*)self); } SWIGINTERN double doubleArray___getitem__(doubleArray *self,size_t index){ return self[index]; } #define SWIG_From_double PyFloat_FromDouble SWIGINTERN void doubleArray___setitem__(doubleArray *self,size_t index,double value){ self[index] = value; } SWIGINTERN double *doubleArray_cast(doubleArray *self){ return self; } SWIGINTERN doubleArray *doubleArray_frompointer(double *t){ return (doubleArray *)(t); } typedef int intArray; SWIGINTERN intArray *new_intArray(size_t nelements){ return (int *)malloc((nelements)*sizeof(int)); } SWIGINTERN void delete_intArray(intArray *self){ free((char*)self); } SWIGINTERN int intArray___getitem__(intArray *self,size_t index){ return self[index]; } #define SWIG_From_long PyInt_FromLong SWIGINTERNINLINE PyObject * SWIG_From_int (int value) { return SWIG_From_long (value); } #include #if !defined(SWIG_NO_LLONG_MAX) # if !defined(LLONG_MAX) && defined(__GNUC__) && defined (__LONG_LONG_MAX__) # define LLONG_MAX __LONG_LONG_MAX__ # define LLONG_MIN (-LLONG_MAX - 1LL) # define ULLONG_MAX (LLONG_MAX * 2ULL + 1ULL) # endif #endif SWIGINTERN int SWIG_AsVal_long (PyObject *obj, long* val) { if (PyInt_Check(obj)) { if (val) *val = PyInt_AsLong(obj); return SWIG_OK; } else if (PyLong_Check(obj)) { long v = PyLong_AsLong(obj); if (!PyErr_Occurred()) { if (val) *val = v; return SWIG_OK; } else { PyErr_Clear(); } } #ifdef SWIG_PYTHON_CAST_MODE { int dispatch = 0; long v = PyInt_AsLong(obj); if (!PyErr_Occurred()) { if (val) *val = v; return SWIG_AddCast(SWIG_OK); } else { PyErr_Clear(); } if (!dispatch) { double d; int res = SWIG_AddCast(SWIG_AsVal_double (obj,&d)); if (SWIG_IsOK(res) && SWIG_CanCastAsInteger(&d, LONG_MIN, LONG_MAX)) { if (val) *val = (long)(d); return res; } } } #endif return SWIG_TypeError; } SWIGINTERN int SWIG_AsVal_int (PyObject * obj, int *val) { long v; int res = SWIG_AsVal_long (obj, &v); if (SWIG_IsOK(res)) { if ((v < INT_MIN || v > INT_MAX)) { return SWIG_OverflowError; } else { if (val) *val = (int)(v); } } return res; } SWIGINTERN void intArray___setitem__(intArray *self,size_t index,int value){ self[index] = value; } SWIGINTERN int *intArray_cast(intArray *self){ return self; } SWIGINTERN intArray *intArray_frompointer(int *t){ return (intArray *)(t); } typedef short shortArray; SWIGINTERN shortArray *new_shortArray(size_t nelements){ return (short *)malloc((nelements)*sizeof(short)); } SWIGINTERN void delete_shortArray(shortArray *self){ free((char*)self); } SWIGINTERN short shortArray___getitem__(shortArray *self,size_t index){ return self[index]; } SWIGINTERNINLINE PyObject * SWIG_From_short (short value) { return SWIG_From_long (value); } SWIGINTERN int SWIG_AsVal_short (PyObject * obj, short *val) { long v; int res = SWIG_AsVal_long (obj, &v); if (SWIG_IsOK(res)) { if ((v < SHRT_MIN || v > SHRT_MAX)) { return SWIG_OverflowError; } else { if (val) *val = (short)(v); } } return res; } SWIGINTERN void shortArray___setitem__(shortArray *self,size_t index,short value){ self[index] = value; } SWIGINTERN short *shortArray_cast(shortArray *self){ return self; } SWIGINTERN shortArray *shortArray_frompointer(short *t){ return (shortArray *)(t); } typedef long longArray; SWIGINTERN longArray *new_longArray(size_t nelements){ return (long *)malloc((nelements)*sizeof(long)); } SWIGINTERN void delete_longArray(longArray *self){ free((char*)self); } SWIGINTERN long longArray___getitem__(longArray *self,size_t index){ return self[index]; } SWIGINTERN void longArray___setitem__(longArray *self,size_t index,long value){ self[index] = value; } SWIGINTERN long *longArray_cast(longArray *self){ return self; } SWIGINTERN longArray *longArray_frompointer(long *t){ return (longArray *)(t); } static int convert_darray(PyObject *input, double *ptr, int size) { int i; if (!PySequence_Check(input)) { PyErr_SetString(PyExc_TypeError,"Expecting a sequence"); return 0; } if (PyObject_Length(input) != size) { PyErr_SetString(PyExc_ValueError,"Sequence size mismatch"); return 0; } for (i =0; i < size; i++) { PyObject *o = PySequence_GetItem(input,i); /*if (!PyFloat_Check(o)) { Py_XDECREF(o); PyErr_SetString(PyExc_ValueError,"Expecting a sequence of floats"); return 0; }*/ ptr[i] = PyFloat_AsDouble(o); Py_DECREF(o); } return 1; } static long convert_larray(PyObject *input, long *ptr, int size) { int i; if (!PySequence_Check(input)) { PyErr_SetString(PyExc_TypeError,"Expecting a sequence"); return 0; } if (PyObject_Length(input) != size) { PyErr_SetString(PyExc_ValueError,"Sequence size mismatch"); return 0; } for (i =0; i < size; i++) { PyObject *o = PySequence_GetItem(input,i); /*if (!PyLong_Check(o)) { Py_XDECREF(o); PyErr_SetString(PyExc_ValueError,"Expecting a sequence of long integers"); return 0; }*/ ptr[i] = PyLong_AsLong(o); Py_DECREF(o); } return 1; } static int convert_iarray(PyObject *input, int *ptr, int size) { int i; if (!PySequence_Check(input)) { PyErr_SetString(PyExc_TypeError,"Expecting a sequence"); return 0; } if (PyObject_Length(input) != size) { PyErr_SetString(PyExc_ValueError,"Sequence size mismatch"); return 0; } for (i =0; i < size; i++) { PyObject *o = PySequence_GetItem(input,i); /*if (!PyInt_Check(o)) { Py_XDECREF(o); PyErr_SetString(PyExc_ValueError,"Expecting a sequence of long integers"); return 0; }*/ ptr[i] = (int)PyInt_AsLong(o); Py_DECREF(o); } return 1; } // Here is the c code needed to compile the wrappers, but not // to be wrapped #include "../include/cbf.h" #include "../include/cbf_simple.h" // Helper functions to generate error message static int error_status = 0; static char error_message[1024] ; // hope that is long enough /* prototype */ void get_error_message(void); void get_error_message(){ sprintf(error_message,"%s","CBFlib Error(s):"); if (error_status & CBF_FORMAT ) sprintf(error_message,"%s %s",error_message,"CBF_FORMAT "); if (error_status & CBF_ALLOC ) sprintf(error_message,"%s %s",error_message,"CBF_ALLOC "); if (error_status & CBF_ARGUMENT ) sprintf(error_message,"%s %s",error_message,"CBF_ARGUMENT "); if (error_status & CBF_ASCII ) sprintf(error_message,"%s %s",error_message,"CBF_ASCII "); if (error_status & CBF_BINARY ) sprintf(error_message,"%s %s",error_message,"CBF_BINARY "); if (error_status & CBF_BITCOUNT ) sprintf(error_message,"%s %s",error_message,"CBF_BITCOUNT "); if (error_status & CBF_ENDOFDATA ) sprintf(error_message,"%s %s",error_message,"CBF_ENDOFDATA "); if (error_status & CBF_FILECLOSE ) sprintf(error_message,"%s %s",error_message,"CBF_FILECLOSE "); if (error_status & CBF_FILEOPEN ) sprintf(error_message,"%s %s",error_message,"CBF_FILEOPEN "); if (error_status & CBF_FILEREAD ) sprintf(error_message,"%s %s",error_message,"CBF_FILEREAD "); if (error_status & CBF_FILESEEK ) sprintf(error_message,"%s %s",error_message,"CBF_FILESEEK "); if (error_status & CBF_FILETELL ) sprintf(error_message,"%s %s",error_message,"CBF_FILETELL "); if (error_status & CBF_FILEWRITE ) sprintf(error_message,"%s %s",error_message,"CBF_FILEWRITE "); if (error_status & CBF_IDENTICAL ) sprintf(error_message,"%s %s",error_message,"CBF_IDENTICAL "); if (error_status & CBF_NOTFOUND ) sprintf(error_message,"%s %s",error_message,"CBF_NOTFOUND "); if (error_status & CBF_OVERFLOW ) sprintf(error_message,"%s %s",error_message,"CBF_OVERFLOW "); if (error_status & CBF_UNDEFINED ) sprintf(error_message,"%s %s",error_message,"CBF_UNDEFINED "); if (error_status & CBF_NOTIMPLEMENTED) sprintf(error_message,"%s %s",error_message,"CBF_NOTIMPLEMENTED"); if (error_status & CBF_NOCOMPRESSION) sprintf(error_message,"%s %s",error_message,"CBF_NOCOMPRESSION"); } void get_local_integer_byte_order(char **bo, int *bolen) { char * byteorder; char * bot; error_status = cbf_get_local_integer_byte_order(&byteorder); *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {{(error_status = CBF_ALLOC);}} strncpy(bot,byteorder,*bolen); *bo = bot; } SWIGINTERN swig_type_info* SWIG_pchar_descriptor(void) { static int init = 0; static swig_type_info* info = 0; if (!init) { info = SWIG_TypeQuery("_p_char"); init = 1; } return info; } SWIGINTERNINLINE PyObject * SWIG_FromCharPtrAndSize(const char* carray, size_t size) { if (carray) { if (size > INT_MAX) { swig_type_info* pchar_descriptor = SWIG_pchar_descriptor(); return pchar_descriptor ? SWIG_NewPointerObj((char *)(carray), pchar_descriptor, 0) : SWIG_Py_Void(); } else { #if PY_VERSION_HEX >= 0x03000000 return PyUnicode_FromStringAndSize(carray, (int)(size)); #else return PyString_FromStringAndSize(carray, (int)(size)); #endif } } else { return SWIG_Py_Void(); } } void compute_cell_volume(double cell[6], double *volume) { {(error_status = cbf_compute_cell_volume(cell,volume));}; } void get_local_real_format(char **rf, int *rflen) { char * real_format; char * rft; error_status = cbf_get_local_real_format(&real_format); *rflen = strlen(real_format); if (!(rft = (char *)malloc(*rflen))) {{(error_status = CBF_ALLOC);}} strncpy(rft,real_format,*rflen); *rf = rft; } void get_local_real_byte_order(char **bo, int *bolen) { char * byteorder; char * bot; error_status = cbf_get_local_real_byte_order(&byteorder); *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {{(error_status = CBF_ALLOC);}} strncpy(bot,byteorder,*bolen); *bo = bot; } void compute_reciprocal_cell(double cell[6], double *astar, double *bstar, double *cstar, double *alphastar, double *betastar, double *gammastar) { double rcell[6]; {(error_status = cbf_compute_reciprocal_cell(cell,rcell));}; *astar = rcell[0]; *bstar = rcell[1]; *cstar = rcell[2]; *alphastar = rcell[3]; *betastar = rcell[4]; *gammastar = rcell[5]; } SWIGINTERNINLINE PyObject* SWIG_From_unsigned_SS_long (unsigned long value) { return (value > LONG_MAX) ? PyLong_FromUnsignedLong(value) : PyInt_FromLong((long)(value)); } SWIGINTERNINLINE PyObject * SWIG_From_size_t (size_t value) { return SWIG_From_unsigned_SS_long ((unsigned long)(value)); } SWIGINTERN cbf_positioner_struct *new_cbf_positioner_struct(){ // Constructor // DO NOT CONSTRUCT WITHOUT A CBFHANDLE {(error_status = CBF_ARGUMENT);}; return NULL; /* Should never be executed */ } SWIGINTERN void delete_cbf_positioner_struct(cbf_positioner_struct *self){ // Destructor {(error_status = cbf_free_goniometer(self));}; } SWIGINTERN void cbf_positioner_struct_get_rotation_range(cbf_positioner_struct *self,double *start,double *increment){ unsigned int reserved; reserved = 0; {(error_status = cbf_get_rotation_range (self,reserved, start,increment));}; } SWIGINTERN void cbf_positioner_struct_rotate_vector(cbf_positioner_struct *self,double ratio,double initial1,double initial2,double initial3,double *final1,double *final2,double *final3){ unsigned int reserved; reserved = 0; {(error_status = cbf_rotate_vector (self, reserved, ratio, initial1, initial2, initial3, final1, final2, final3));}; } SWIGINTERN void cbf_positioner_struct_get_reciprocal(cbf_positioner_struct *self,double ratio,double wavelength,double real1,double real2,double real3,double *reciprocal1,double *reciprocal2,double *reciprocal3){ unsigned int reserved; reserved = 0; {(error_status = cbf_get_reciprocal(self,reserved, ratio, wavelength, real1, real2, real3,reciprocal1, reciprocal2,reciprocal3));}; } SWIGINTERN void cbf_positioner_struct_get_rotation_axis(cbf_positioner_struct *self,double *vector1,double *vector2,double *vector3){ unsigned int reserved; reserved = 0; {(error_status = cbf_get_rotation_axis (self, reserved, vector1, vector2, vector3));}; } SWIGINTERN cbf_detector_struct *new_cbf_detector_struct(){ // Constructor // DO NOT CONSTRUCT WITHOUT A CBFHANDLE {(error_status = CBF_ARGUMENT);}; return NULL; /* Should never be executed */ } SWIGINTERN void delete_cbf_detector_struct(cbf_detector_struct *self){ // Destructor {(error_status = cbf_free_detector(self));}; } SWIGINTERN void cbf_detector_struct_set_reference_beam_center_fs(cbf_detector_struct *self,double *indexfast,double *indexslow,double *centerfast,double *centerslow){ {(error_status = cbf_set_reference_beam_center_fs(self, indexfast, indexslow, centerfast, centerslow));}; } SWIGINTERN void cbf_detector_struct_get_pixel_coordinates_fs(cbf_detector_struct *self,double indexfast,double indexslow,double *coordinate1,double *coordinate2,double *coordinate3){ {(error_status = cbf_get_pixel_coordinates_fs(self, indexfast, indexslow, coordinate1, coordinate2, coordinate3));}; } SWIGINTERN void cbf_detector_struct_set_beam_center_fs(cbf_detector_struct *self,double *indexfast,double *indexslow,double *centerfast,double *centerslow){ {(error_status = cbf_set_beam_center_fs(self, indexfast, indexslow, centerfast, centerslow));}; } SWIGINTERN int SWIG_AsVal_unsigned_SS_int (PyObject * obj, unsigned int *val) { unsigned long v; int res = SWIG_AsVal_unsigned_SS_long (obj, &v); if (SWIG_IsOK(res)) { if ((v > UINT_MAX)) { return SWIG_OverflowError; } else { if (val) *val = (unsigned int)(v); } } return res; } SWIGINTERN void cbf_detector_struct_get_inferred_pixel_size(cbf_detector_struct *self,unsigned int axis_number,double *psize){ {(error_status = cbf_get_inferred_pixel_size(self, axis_number, psize));}; } SWIGINTERN void cbf_detector_struct_get_pixel_area(cbf_detector_struct *self,double index1,double index2,double *area,double *projected_area){ {(error_status = cbf_get_pixel_area (self, index1, index2, area,projected_area));}; } SWIGINTERN void cbf_detector_struct_get_pixel_normal_fs(cbf_detector_struct *self,double indexfast,double indexslow,double *normal1,double *normal2,double *normal3){ {(error_status = cbf_get_pixel_normal_fs(self, indexfast,indexslow,normal1,normal2,normal3));}; } SWIGINTERN void cbf_detector_struct_get_detector_axes(cbf_detector_struct *self,double *slowaxis1,double *slowaxis2,double *slowaxis3,double *fastaxis1,double *fastaxis2,double *fastaxis3){ {(error_status = cbf_get_detector_axes(self, slowaxis1,slowaxis2,slowaxis3, fastaxis1,fastaxis2,fastaxis3));}; } SWIGINTERN void cbf_detector_struct_set_reference_beam_center(cbf_detector_struct *self,double *indexslow,double *indexfast,double *centerslow,double *centerfast){ {(error_status = cbf_set_reference_beam_center(self, indexslow, indexfast, centerslow, centerfast));}; } SWIGINTERN void cbf_detector_struct_get_detector_axis_slow(cbf_detector_struct *self,double *slowaxis1,double *slowaxis2,double *slowaxis3){ {(error_status = cbf_get_detector_axis_slow(self, slowaxis1,slowaxis2,slowaxis3));}; } SWIGINTERN void cbf_detector_struct_get_detector_distance(cbf_detector_struct *self,double *distance){ {(error_status = cbf_get_detector_distance(self,distance));}; } SWIGINTERN void cbf_detector_struct_get_inferred_pixel_size_fs(cbf_detector_struct *self,unsigned int axis_number,double *psize){ {(error_status = cbf_get_inferred_pixel_size_fs(self, axis_number, psize));}; } SWIGINTERN void cbf_detector_struct_get_detector_normal(cbf_detector_struct *self,double *normal1,double *normal2,double *normal3){ {(error_status = cbf_get_detector_normal(self, normal1, normal2, normal3));}; } SWIGINTERN void cbf_detector_struct_get_detector_axis_fast(cbf_detector_struct *self,double *fastaxis1,double *fastaxis2,double *fastaxis3){ {(error_status = cbf_get_detector_axis_fast(self, fastaxis1,fastaxis2,fastaxis3));}; } SWIGINTERN void cbf_detector_struct_get_detector_axes_fs(cbf_detector_struct *self,double *fastaxis1,double *fastaxis2,double *fastaxis3,double *slowaxis1,double *slowaxis2,double *slowaxis3){ {(error_status = cbf_get_detector_axes(self, slowaxis1,slowaxis2,slowaxis3, fastaxis1,fastaxis2,fastaxis3));}; } SWIGINTERN void cbf_detector_struct_get_detector_axes_sf(cbf_detector_struct *self,double *slowaxis1,double *slowaxis2,double *slowaxis3,double *fastaxis1,double *fastaxis2,double *fastaxis3){ {(error_status = cbf_get_detector_axes(self, slowaxis1,slowaxis2,slowaxis3, fastaxis1,fastaxis2,fastaxis3));}; } SWIGINTERN void cbf_detector_struct_get_pixel_coordinates_sf(cbf_detector_struct *self,double indexslow,double indexfast,double *coordinate1,double *coordinate2,double *coordinate3){ {(error_status = cbf_get_pixel_coordinates_sf(self, indexslow, indexfast, coordinate1, coordinate2, coordinate3));}; } SWIGINTERN void cbf_detector_struct_set_beam_center(cbf_detector_struct *self,double *indexslow,double *indexfast,double *centerslow,double *centerfast){ {(error_status = cbf_set_beam_center(self, indexslow, indexfast, centerslow, centerfast));}; } SWIGINTERN void cbf_detector_struct_get_pixel_area_fs(cbf_detector_struct *self,double indexfast,double indexslow,double *area,double *projected_area){ {(error_status = cbf_get_pixel_area_fs (self, indexfast, indexslow, area,projected_area));}; } SWIGINTERN void cbf_detector_struct_get_beam_center_fs(cbf_detector_struct *self,double *indexfast,double *indexslow,double *centerfast,double *centerslow){ {(error_status = cbf_get_beam_center_fs(self, indexfast, indexslow, centerfast, centerslow));}; } SWIGINTERN void cbf_detector_struct_get_inferred_pixel_size_sf(cbf_detector_struct *self,unsigned int axis_number,double *psize){ {(error_status = cbf_get_inferred_pixel_size_sf(self, axis_number, psize));}; } SWIGINTERN void cbf_detector_struct_get_pixel_coordinates(cbf_detector_struct *self,double index1,double index2,double *coordinate1,double *coordinate2,double *coordinate3){ {(error_status = cbf_get_pixel_coordinates(self, index1, index2, coordinate1, coordinate2, coordinate3));}; } SWIGINTERN void cbf_detector_struct_get_beam_center_sf(cbf_detector_struct *self,double *indexslow,double *indexfast,double *centerslow,double *centerfast){ {(error_status = cbf_get_beam_center_sf(self, indexslow, indexfast, centerslow, centerfast));}; } SWIGINTERN void cbf_detector_struct_get_pixel_area_sf(cbf_detector_struct *self,double indexslow,double indexfast,double *area,double *projected_area){ {(error_status = cbf_get_pixel_area_sf (self, indexslow, indexfast, area,projected_area));}; } SWIGINTERN void cbf_detector_struct_get_beam_center(cbf_detector_struct *self,double *index1,double *index2,double *center1,double *center2){ {(error_status = cbf_get_beam_center(self, index1, index2, center1, center2));}; } SWIGINTERN void cbf_detector_struct_set_reference_beam_center_sf(cbf_detector_struct *self,double *indexslow,double *indexfast,double *centerslow,double *centerfast){ {(error_status = cbf_set_reference_beam_center_sf(self, indexslow, indexfast, centerslow, centerfast));}; } SWIGINTERN void cbf_detector_struct_set_beam_center_sf(cbf_detector_struct *self,double *indexslow,double *indexfast,double *centerslow,double *centerfast){ {(error_status = cbf_set_beam_center_sf(self, indexslow, indexfast, centerslow, centerfast));}; } SWIGINTERN void cbf_detector_struct_get_pixel_normal(cbf_detector_struct *self,double index1,double index2,double *normal1,double *normal2,double *normal3){ {(error_status = cbf_get_pixel_normal(self, index1,index2,normal1,normal2,normal3));}; } SWIGINTERN cbf_handle_struct *new_cbf_handle_struct(){ // Constructor cbf_handle handle; {(error_status = cbf_make_handle(&handle));}; return handle; } SWIGINTERN void delete_cbf_handle_struct(cbf_handle_struct *self){ // Destructor {(error_status = cbf_free_handle(self));}; } SWIGINTERN void cbf_handle_struct_select_datablock(cbf_handle_struct *self,unsigned int arg){ {(error_status = cbf_select_datablock(self,arg));};} SWIGINTERN int SWIG_AsCharPtrAndSize(PyObject *obj, char** cptr, size_t* psize, int *alloc) { #if PY_VERSION_HEX>=0x03000000 if (PyUnicode_Check(obj)) #else if (PyString_Check(obj)) #endif { char *cstr; Py_ssize_t len; #if PY_VERSION_HEX>=0x03000000 if (!alloc && cptr) { /* We can't allow converting without allocation, since the internal representation of string in Python 3 is UCS-2/UCS-4 but we require a UTF-8 representation. TODO(bhy) More detailed explanation */ return SWIG_RuntimeError; } obj = PyUnicode_AsUTF8String(obj); PyBytes_AsStringAndSize(obj, &cstr, &len); if(alloc) *alloc = SWIG_NEWOBJ; #else PyString_AsStringAndSize(obj, &cstr, &len); #endif if (cptr) { if (alloc) { /* In python the user should not be able to modify the inner string representation. To warranty that, if you define SWIG_PYTHON_SAFE_CSTRINGS, a new/copy of the python string buffer is always returned. The default behavior is just to return the pointer value, so, be careful. */ #if defined(SWIG_PYTHON_SAFE_CSTRINGS) if (*alloc != SWIG_OLDOBJ) #else if (*alloc == SWIG_NEWOBJ) #endif { *cptr = (char *)memcpy((char *)malloc((len + 1)*sizeof(char)), cstr, sizeof(char)*(len + 1)); *alloc = SWIG_NEWOBJ; } else { *cptr = cstr; *alloc = SWIG_OLDOBJ; } } else { #if PY_VERSION_HEX>=0x03000000 assert(0); /* Should never reach here in Python 3 */ #endif *cptr = SWIG_Python_str_AsChar(obj); } } if (psize) *psize = len + 1; #if PY_VERSION_HEX>=0x03000000 Py_XDECREF(obj); #endif return SWIG_OK; } else { swig_type_info* pchar_descriptor = SWIG_pchar_descriptor(); if (pchar_descriptor) { void* vptr = 0; if (SWIG_ConvertPtr(obj, &vptr, pchar_descriptor, 0) == SWIG_OK) { if (cptr) *cptr = (char *) vptr; if (psize) *psize = vptr ? (strlen((char *)vptr) + 1) : 0; if (alloc) *alloc = SWIG_OLDOBJ; return SWIG_OK; } } } return SWIG_TypeError; } SWIGINTERN void cbf_handle_struct_force_new_datablock(cbf_handle_struct *self,char const *arg){ {(error_status = cbf_force_new_datablock(self,arg));};} SWIGINTERN void cbf_handle_struct_get_3d_image_fs_as_string(cbf_handle_struct *self,int element_number,char **s,int *slen,int elsize,int elsign,int ndimfast,int ndimmid,int ndimslow){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) { {(error_status = cbf_get_3d_image_fs(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, elsign, (size_t) ndimfast, (size_t)ndimmid, (size_t)ndimslow));}; }else{ {(error_status = CBF_ALLOC);}; } *slen = elsize*ndimfast*ndimmid*ndimslow; *s = (char *) array; } SWIGINTERN void cbf_handle_struct_reset_datablocks(cbf_handle_struct *self){ {(error_status = cbf_reset_datablocks(self));};} SWIGINTERN void cbf_handle_struct_set_tag_category(cbf_handle_struct *self,char const *tagname,char const *categoryname_in){ {(error_status = cbf_set_tag_category(self,tagname, categoryname_in));}; } SWIGINTERN char const *cbf_handle_struct_require_tag_root(cbf_handle_struct *self,char const *tagname){ const char* result; {(error_status = cbf_require_tag_root(self,tagname,&result));}; return result; } SWIGINTERNINLINE PyObject * SWIG_FromCharPtr(const char *cptr) { return SWIG_FromCharPtrAndSize(cptr, (cptr ? strlen(cptr) : 0)); } SWIGINTERN unsigned int cbf_handle_struct_row_number(cbf_handle_struct *self){ unsigned int result; {(error_status = cbf_row_number(self,&result));}; return result;} SWIGINTERNINLINE PyObject * SWIG_From_unsigned_SS_int (unsigned int value) { return SWIG_From_unsigned_SS_long (value); } SWIGINTERN void cbf_handle_struct_set_image(cbf_handle_struct *self,unsigned int element_number,unsigned int compression,char *data,int len,int elsize,int elsign,int ndimslow,int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimfast){ array = data; els = elsize; reserved = 0; {(error_status = cbf_set_image (self, reserved, element_number, compression, (void *) data, (size_t) elsize, elsign, (size_t) ndimslow, (size_t)ndimfast));}; }else{ {(error_status = CBF_ARGUMENT);}; } } SWIGINTERN void cbf_handle_struct_set_bin_sizes(cbf_handle_struct *self,int element_number,double slowbinsize_in,double fastbinsize_in){ {(error_status = cbf_set_bin_sizes(self,element_number,slowbinsize_in,fastbinsize_in));}; } SWIGINTERN void cbf_handle_struct_new_row(cbf_handle_struct *self){ {(error_status = cbf_new_row(self));};} SWIGINTERN void cbf_handle_struct_rewind_saveframe(cbf_handle_struct *self){ {(error_status = cbf_rewind_saveframe(self));};} SWIGINTERN void cbf_handle_struct_get_realarrayparameters(cbf_handle_struct *self,int *compression,int *binary_id,int *elsize,int *elements){ unsigned int comp; size_t elsiz, elem; {(error_status = cbf_get_realarrayparameters(self, &comp ,binary_id, &elsiz, &elem ));}; *compression = comp; /* FIXME - does this convert in C? */ *elsize = elsiz; *elements = elem; } SWIGINTERN void cbf_handle_struct_get_pixel_size_sf(cbf_handle_struct *self,unsigned int element_number,unsigned int axis_number,double *psize){ {(error_status = cbf_get_pixel_size_sf(self, element_number, axis_number, psize));}; } SWIGINTERN void cbf_handle_struct_force_new_category(cbf_handle_struct *self,char const *arg){ {(error_status = cbf_force_new_category(self,arg));};} SWIGINTERN void cbf_handle_struct_force_new_saveframe(cbf_handle_struct *self,char const *arg){ {(error_status = cbf_force_new_saveframe(self,arg));};} SWIGINTERN unsigned int cbf_handle_struct_count_datablocks(cbf_handle_struct *self){ unsigned int result; {(error_status = cbf_count_datablocks(self,&result));}; return result;} SWIGINTERN void cbf_handle_struct_find_row(cbf_handle_struct *self,char const *arg){ {(error_status = cbf_find_row(self,arg));};} SWIGINTERN void cbf_handle_struct_select_column(cbf_handle_struct *self,unsigned int arg){ {(error_status = cbf_select_column(self,arg));};} SWIGINTERN cbf_detector cbf_handle_struct_construct_detector(cbf_handle_struct *self,unsigned int element_number){ cbf_detector detector; {(error_status = cbf_construct_detector(self,&detector,element_number));}; return detector; } SWIGINTERN void cbf_handle_struct_rewind_column(cbf_handle_struct *self){ {(error_status = cbf_rewind_column(self));};} SWIGINTERN void cbf_handle_struct_require_column_doublevalue(cbf_handle_struct *self,char const *columnname,double *number,double const defaultvalue){ {(error_status = cbf_require_column_doublevalue(self, columnname,number,defaultvalue));}; } SWIGINTERN void cbf_handle_struct_get_datestamp(cbf_handle_struct *self,int *year,int *month,int *day,int *hour,int *minute,double *second,int *timezone){ unsigned int reserved; reserved = 0; {(error_status = cbf_get_datestamp(self,reserved, year,month,day,hour,minute,second,timezone));}; } SWIGINTERN int cbf_handle_struct_get_integervalue(cbf_handle_struct *self){ int result; {(error_status = cbf_get_integervalue(self,&result));}; return result;} SWIGINTERN char const *cbf_handle_struct_get_crystal_id(cbf_handle_struct *self){ const char* result; {(error_status = cbf_get_crystal_id(self, &result));}; return result;} SWIGINTERN double cbf_handle_struct_get_doublevalue(cbf_handle_struct *self){ double result; {(error_status = cbf_get_doublevalue(self,&result));}; return result;} SWIGINTERN void cbf_handle_struct_get_unit_cell(cbf_handle_struct *self,double *a,double *b,double *c,double *alpha,double *beta,double *gamma){ double cell[6]; {(error_status = cbf_get_unit_cell(self,cell,NULL));}; *a = cell[0]; *b = cell[1]; *c = cell[2]; *alpha = cell[3]; *beta = cell[4]; *gamma = cell[5]; } SWIGINTERN void cbf_handle_struct_get_unit_cell_esd(cbf_handle_struct *self,double *a_esd,double *b_esd,double *c_esd,double *alpha_esd,double *beta_esd,double *gamma_esd){ double cell_esd[6]; {(error_status = cbf_get_unit_cell(self,NULL,cell_esd));}; *a_esd = cell_esd[0]; *b_esd = cell_esd[1]; *c_esd = cell_esd[2]; *alpha_esd = cell_esd[3]; *beta_esd = cell_esd[4]; *gamma_esd = cell_esd[5]; } SWIGINTERN void cbf_handle_struct_remove_column(cbf_handle_struct *self){ {(error_status = cbf_remove_column(self));};} SWIGINTERN CBF_NODETYPE cbf_handle_struct_rewind_blockitem(cbf_handle_struct *self){ CBF_NODETYPE result; {(error_status = cbf_rewind_blockitem(self,&result));}; return result;} SWIGINTERN char const *cbf_handle_struct_get_value(cbf_handle_struct *self){ const char* result; {(error_status = cbf_get_value(self, &result));}; return result;} SWIGINTERN unsigned int cbf_handle_struct_count_categories(cbf_handle_struct *self){ unsigned int result; {(error_status = cbf_count_categories(self,&result));}; return result;} SWIGINTERN void cbf_handle_struct_read_widefile(cbf_handle_struct *self,char *filename,int headers){ /* CBFlib needs a stream that will remain open hence DO NOT open from python */ FILE *stream; if ( ! ( stream = fopen (filename, "rb")) ){ {(error_status = CBF_FILEOPEN);}; } else{ {(error_status = cbf_read_widefile(self, stream, headers));}; } } SWIGINTERN void cbf_handle_struct_set_wavelength(cbf_handle_struct *self,double wavelength){ {(error_status = cbf_set_wavelength(self,wavelength));};} SWIGINTERN void cbf_handle_struct_set_pixel_size_sf(cbf_handle_struct *self,unsigned int element_number,unsigned int axis_number,double psize){ {(error_status = cbf_set_pixel_size_sf(self, element_number, axis_number, psize));}; } SWIGINTERN char const *cbf_handle_struct_get_diffrn_id(cbf_handle_struct *self){ const char* result; {(error_status = cbf_get_diffrn_id(self, &result));}; return result;} SWIGINTERN void cbf_handle_struct_find_datablock(cbf_handle_struct *self,char const *arg){ {(error_status = cbf_find_datablock(self,arg));};} SWIGINTERN void cbf_handle_struct_get_polarization(cbf_handle_struct *self,double *in1,double *in2){ {(error_status = cbf_get_polarization (self, in1, in2));}; } SWIGINTERN void cbf_handle_struct_select_category(cbf_handle_struct *self,unsigned int arg){ {(error_status = cbf_select_category(self,arg));};} SWIGINTERN void cbf_handle_struct_get_pixel_size_fs(cbf_handle_struct *self,unsigned int element_number,unsigned int axis_number,double *psize){ {(error_status = cbf_get_pixel_size_fs(self, element_number, axis_number, psize));}; } SWIGINTERN void cbf_handle_struct_read_file(cbf_handle_struct *self,char *filename,int headers){ /* CBFlib needs a stream that will remain open hence DO NOT open from python */ FILE *stream; if ( ! ( stream = fopen (filename, "rb")) ){ {(error_status = CBF_FILEOPEN);}; } else{ {(error_status = cbf_read_file(self, stream, headers));}; } } SWIGINTERN char const *cbf_handle_struct_datablock_name(cbf_handle_struct *self){ const char* result; {(error_status = cbf_datablock_name(self, &result));}; return result;} SWIGINTERN void cbf_handle_struct_set_realarray_wdims(cbf_handle_struct *self,unsigned int compression,int binary_id,char *data,int len,int elsize,int elements,char *bo,int bolen,int dimfast,int dimmid,int dimslow,int padding){ /* safety check on args */ size_t els, ele; void *array; char byteorder[15]; if(len == elsize*elements && elements==dimfast*dimmid*dimslow){ array = data; els = elsize; ele = elements; strncpy(byteorder,bo,bolen<15?bolen:14); byteorder[bolen<15?14:bolen] = 0; {(error_status = cbf_set_realarray_wdims (self, compression, binary_id, (void *) data, (size_t) elsize, (size_t) elements, (const char *)byteorder, (size_t)dimfast, (size_t)dimmid, (size_t)dimslow, (size_t)padding));}; }else{ {(error_status = CBF_ARGUMENT);}; } } SWIGINTERN cbf_detector cbf_handle_struct_construct_reference_detector(cbf_handle_struct *self,unsigned int element_number){ cbf_detector detector; {(error_status = cbf_construct_reference_detector(self,&detector,element_number));}; return detector; } SWIGINTERN void cbf_handle_struct_get_real_3d_image_fs_as_string(cbf_handle_struct *self,int element_number,char **s,int *slen,int elsize,int ndimfast,int ndimmid,int ndimslow){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) { {(error_status = cbf_get_real_3d_image_fs(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, (size_t) ndimfast, (size_t)ndimmid, (size_t)ndimslow));}; }else{ {(error_status = CBF_ALLOC);}; } *slen = elsize*ndimfast*ndimmid*ndimslow; *s = (char *) array; } SWIGINTERN void cbf_handle_struct_rewind_row(cbf_handle_struct *self){ {(error_status = cbf_rewind_row(self));};} SWIGINTERN void cbf_handle_struct_get_axis_setting(cbf_handle_struct *self,char const *axis_id,double *start,double *increment){ unsigned int reserved; reserved = 0; {(error_status = cbf_get_axis_setting(self,reserved,axis_id, start,increment));}; } SWIGINTERN void cbf_handle_struct_require_column(cbf_handle_struct *self,char const *arg){ {(error_status = cbf_require_column(self,arg));};} SWIGINTERN void cbf_handle_struct_get_timestamp(cbf_handle_struct *self,double *time,int *timezone){ unsigned int reserved; reserved = 0; {(error_status = cbf_get_timestamp(self,reserved,time,timezone));}; } SWIGINTERN void cbf_handle_struct_find_nextrow(cbf_handle_struct *self,char const *arg){ {(error_status = cbf_find_nextrow(self,arg));};} SWIGINTERN void cbf_handle_struct_get_realarrayparameters_wdims_sf(cbf_handle_struct *self,int *compression,int *binary_id,int *elsize,int *elements,char **bo,int *bolen,int *dimslow,int *dimmid,int *dimfast,int *padding){ unsigned int comp; size_t elsiz, elem, df,dm,ds,pd; const char * byteorder; char * bot; {(error_status = cbf_get_realarrayparameters_wdims_sf(self, &comp,binary_id, &elsiz, &elem, &byteorder,&ds,&dm,&df,&pd ));}; *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {{(error_status = CBF_ALLOC);}} strncpy(bot,byteorder,*bolen); *bo = bot; *compression = comp; *elsize = elsiz; *elements = elem; *dimfast = df; *dimmid = dm; *dimslow = ds; *padding = pd; } SWIGINTERN void cbf_handle_struct_reset_datablock(cbf_handle_struct *self){ {(error_status = cbf_reset_datablock(self));};} SWIGINTERN void cbf_handle_struct_set_3d_image_fs(cbf_handle_struct *self,unsigned int element_number,unsigned int compression,char *data,int len,int elsize,int elsign,int ndimfast,int ndimmid,int ndimslow){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimmid*ndimfast){ array = data; els = elsize; reserved = 0; {(error_status = cbf_set_3d_image_fs (self, reserved, element_number, compression, (void *) data, (size_t) elsize, elsign, (size_t) ndimfast, (size_t) ndimmid, (size_t)ndimslow));}; }else{ {(error_status = CBF_ARGUMENT);}; } } SWIGINTERN void cbf_handle_struct_set_saveframename(cbf_handle_struct *self,char const *arg){ {(error_status = cbf_set_saveframename(self,arg));};} SWIGINTERN void cbf_handle_struct_require_integervalue(cbf_handle_struct *self,int *number,int thedefault){ {(error_status = cbf_require_integervalue(self,number,thedefault));}; } SWIGINTERN void cbf_handle_struct_get_integerarrayparameters(cbf_handle_struct *self,int *compression,int *binary_id,int *elsize,int *elsigned,int *elunsigned,int *elements,int *minelement,int *maxelement){ unsigned int comp; size_t elsiz, elem; {(error_status = cbf_get_integerarrayparameters(self, &comp,binary_id, &elsiz, elsigned, elunsigned, &elem, minelement, maxelement));}; *compression = comp; /* FIXME - does this convert in C? */ *elsize = elsiz; *elements = elem; } SWIGINTERN void cbf_handle_struct_set_real_3d_image_sf(cbf_handle_struct *self,unsigned int element_number,unsigned int compression,char *data,int len,int elsize,int ndimslow,int ndimmid,int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimmid*ndimfast){ array = data; els = elsize; reserved = 0; {(error_status = cbf_set_real_3d_image_sf (self, reserved, element_number, compression, (void *) data, (size_t) elsize, (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast));}; }else{ {(error_status = CBF_ARGUMENT);}; } } SWIGINTERN void cbf_handle_struct_write_file(cbf_handle_struct *self,char const *filename,int ciforcbf,int headers,int encoding){ FILE *stream; int readable; /* Make the file non-0 to make CBFlib close the file */ readable = 1; if ( ! ( stream = fopen (filename, "w+b")) ){ {(error_status = CBF_FILEOPEN);}; } else{ {(error_status = cbf_write_file(self, stream, readable, ciforcbf, headers, encoding));}; } } SWIGINTERN void cbf_handle_struct_set_divergence(cbf_handle_struct *self,double div_x_source,double div_y_source,double div_x_y_source){ {(error_status = cbf_set_divergence (self, div_x_source, div_y_source,div_x_y_source));}; } SWIGINTERN void cbf_handle_struct_remove_datablock(cbf_handle_struct *self){ {(error_status = cbf_remove_datablock(self));};} SWIGINTERN unsigned int cbf_handle_struct_count_elements(cbf_handle_struct *self){ unsigned int result; {(error_status = cbf_count_elements(self,&result));}; return result;} SWIGINTERN void cbf_handle_struct_set_image_fs(cbf_handle_struct *self,unsigned int element_number,unsigned int compression,char *data,int len,int elsize,int elsign,int ndimfast,int ndimslow){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimfast){ array = data; els = elsize; reserved = 0; {(error_status = cbf_set_image (self, reserved, element_number, compression, (void *) data, (size_t) elsize, elsign, (size_t) ndimfast, (size_t)ndimslow));}; }else{ {(error_status = CBF_ARGUMENT);}; } } SWIGINTERN cbf_detector cbf_handle_struct_require_reference_detector(cbf_handle_struct *self,unsigned int element_number){ cbf_detector detector; {(error_status = cbf_require_reference_detector(self,&detector,element_number));}; return detector; } SWIGINTERN void cbf_handle_struct_next_category(cbf_handle_struct *self){ {(error_status = cbf_next_category(self));};} SWIGINTERN void cbf_handle_struct_set_diffrn_id(cbf_handle_struct *self,char const *arg){ {(error_status = cbf_set_diffrn_id(self,arg));};} SWIGINTERN void cbf_handle_struct_set_timestamp(cbf_handle_struct *self,double time,int timezone,double precision){ unsigned int reserved; reserved = 0; {(error_status = cbf_set_timestamp(self,reserved,time,timezone,precision));}; } SWIGINTERN void cbf_handle_struct_get_orientation_matrix(cbf_handle_struct *self,double *m0,double *m1,double *m2,double *m3,double *m4,double *m5,double *m6,double *m7,double *m8){ double m[9]; {(error_status = cbf_get_orientation_matrix(self,m));}; *m0 = m[0]; *m1=m[1] ; *m2=m[2] ; *m3 = m[3]; *m4=m[4] ; *m5=m[5] ; *m6 = m[6]; *m7=m[7] ; *m8=m[8] ; } SWIGINTERN void cbf_handle_struct_get_image_size_fs(cbf_handle_struct *self,unsigned int element_number,int *ndimfast,int *ndimslow){ unsigned int reserved; size_t infast, inslow; reserved = 0; {(error_status = cbf_get_image_size_fs(self,reserved,element_number,&infast,&inslow));}; *ndimfast = (int)infast; /* FIXME - is that how to convert? */ *ndimslow = (int)inslow; } SWIGINTERN void cbf_handle_struct_get_divergence(cbf_handle_struct *self,double *div_x_source,double *div_y_source,double *div_x_y_source){ {(error_status = cbf_get_divergence(self, div_x_source, div_y_source, div_x_y_source));}; } SWIGINTERN void cbf_handle_struct_rewind_category(cbf_handle_struct *self){ {(error_status = cbf_rewind_category(self));};} SWIGINTERN void cbf_handle_struct_read_template(cbf_handle_struct *self,char *filename){ /* CBFlib needs a stream that will remain open hence DO NOT open from python */ FILE *stream; if ( ! ( stream = fopen (filename, "rb")) ){ {(error_status = CBF_FILEOPEN);}; } else{ {(error_status = cbf_read_template (self, stream));}; } } SWIGINTERN void cbf_handle_struct_select_row(cbf_handle_struct *self,unsigned int arg){ {(error_status = cbf_select_row(self,arg));};} SWIGINTERN void cbf_handle_struct_get_image_fs_as_string(cbf_handle_struct *self,int element_number,char **s,int *slen,int elsize,int elsign,int ndimfast,int ndimslow){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimslow))) { {(error_status = cbf_get_image_fs(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, elsign, (size_t) ndimfast, (size_t)ndimslow));}; }else{ {(error_status = CBF_ALLOC);}; } *slen = elsize*ndimfast*ndimslow; *s = (char *) array; } SWIGINTERN void cbf_handle_struct_get_image_size_sf(cbf_handle_struct *self,unsigned int element_number,int *ndimslow,int *ndimfast){ unsigned int reserved; size_t inslow, infast; reserved = 0; {(error_status = cbf_get_image_size(self,reserved,element_number,&inslow,&infast));}; *ndimslow = (int)inslow; *ndimfast = (int)infast; } SWIGINTERN void cbf_handle_struct_get_real_image_fs_as_string(cbf_handle_struct *self,int element_number,char **s,int *slen,int elsize,int ndimfast,int ndimslow){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimslow))) { {(error_status = cbf_get_real_image_fs(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, (size_t) ndimfast, (size_t)ndimslow));}; }else{ {(error_status = CBF_ALLOC);}; } *slen = elsize*ndimfast*ndimslow; *s = (char *) array; } SWIGINTERN unsigned int cbf_handle_struct_count_columns(cbf_handle_struct *self){ unsigned int result; {(error_status = cbf_count_columns(self,&result));}; return result;} SWIGINTERN void cbf_handle_struct_get_integerarrayparameters_wdims(cbf_handle_struct *self,int *compression,int *binary_id,int *elsize,int *elsigned,int *elunsigned,int *elements,int *minelement,int *maxelement,char **bo,int *bolen,int *dimfast,int *dimmid,int *dimslow,int *padding){ unsigned int comp; size_t elsiz, elem, df,dm,ds,pd; const char * byteorder; char * bot; {(error_status = cbf_get_integerarrayparameters_wdims(self, &comp,binary_id, &elsiz, elsigned, elunsigned, &elem, minelement, maxelement, &byteorder,&df,&dm,&ds,&pd ));}; *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {{(error_status = CBF_ALLOC);}} strncpy(bot,byteorder,*bolen); *bo = bot; *compression = comp; *elsize = elsiz; *elements = elem; *dimfast = df; *dimmid = dm; *dimslow = ds; *padding = pd; } SWIGINTERN void cbf_handle_struct_get_gain(cbf_handle_struct *self,unsigned int element_number,double *gain,double *gain_esd){ {(error_status = cbf_get_gain (self, element_number, gain, gain_esd));}; } SWIGINTERN void cbf_handle_struct_new_saveframe(cbf_handle_struct *self,char const *arg){ {(error_status = cbf_new_saveframe(self,arg));};} SWIGINTERN void cbf_handle_struct_set_polarization(cbf_handle_struct *self,double polarizn_source_ratio,double polarizn_source_norm){ {(error_status = cbf_set_polarization(self, polarizn_source_ratio, polarizn_source_norm));}; } SWIGINTERN void cbf_handle_struct_set_real_3d_image(cbf_handle_struct *self,unsigned int element_number,unsigned int compression,char *data,int len,int elsize,int ndimslow,int ndimmid,int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimmid*ndimfast){ array = data; els = elsize; reserved = 0; {(error_status = cbf_set_real_3d_image (self, reserved, element_number, compression, (void *) data, (size_t) elsize, (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast));}; }else{ {(error_status = CBF_ARGUMENT);}; } } SWIGINTERN void cbf_handle_struct_delete_row(cbf_handle_struct *self,unsigned int arg){ {(error_status = cbf_delete_row(self,arg));};} SWIGINTERN char const *cbf_handle_struct_column_name(cbf_handle_struct *self){ const char* result; {(error_status = cbf_column_name(self, &result));}; return result;} SWIGINTERN void cbf_handle_struct_remove_saveframe(cbf_handle_struct *self){ {(error_status = cbf_remove_saveframe(self));};} SWIGINTERN void cbf_handle_struct_set_integerarray_wdims_sf(cbf_handle_struct *self,unsigned int compression,int binary_id,char *data,int len,int elsize,int elsigned,int elements,char *bo,int bolen,int dimslow,int dimmid,int dimfast,int padding){ /* safety check on args */ size_t els, ele; void *array; char byteorder[15]; if(len == elsize*elements && elements==dimfast*dimmid*dimslow){ array = data; els = elsize; ele = elements; strncpy(byteorder,bo,bolen<15?bolen:14); byteorder[bolen<15?14:bolen] = 0; {(error_status = cbf_set_integerarray_wdims_sf (self, compression, binary_id, (void *) data, (size_t) elsize, elsigned, (size_t) elements, (const char *)byteorder, (size_t)dimslow, (size_t)dimmid, (size_t)dimfast, (size_t)padding));}; }else{ {(error_status = CBF_ARGUMENT);}; } } SWIGINTERN char const *cbf_handle_struct_require_value(cbf_handle_struct *self,char const *defaultvalue){ const char * result; {(error_status = cbf_require_value(self, &result, defaultvalue));}; return result; } SWIGINTERN void cbf_handle_struct_require_column_integervalue(cbf_handle_struct *self,char const *columnname,int *number,int const defaultvalue){ {(error_status = cbf_require_column_integervalue(self, columnname, number,defaultvalue));}; } SWIGINTERN void cbf_handle_struct_set_pixel_size(cbf_handle_struct *self,unsigned int element_number,unsigned int axis_number,double psize){ {(error_status = cbf_set_pixel_size(self, element_number, axis_number, psize));}; } SWIGINTERN void cbf_handle_struct_next_column(cbf_handle_struct *self){ {(error_status = cbf_next_column(self));};} SWIGINTERN void cbf_handle_struct_get_3d_image_size_sf(cbf_handle_struct *self,unsigned int element_number,int *ndimslow,int *ndimmid,int *ndimfast){ unsigned int reserved; size_t inslow, inmid, infast; reserved = 0; {(error_status = cbf_get_3d_image_size_sf(self,reserved,element_number,&inslow,&inmid,&infast));}; *ndimslow = (int)inslow; /* FIXME - is that how to convert? */ *ndimmid = (int)inmid; *ndimfast = (int)infast; } SWIGINTERN void cbf_handle_struct_get_realarrayparameters_wdims_fs(cbf_handle_struct *self,int *compression,int *binary_id,int *elsize,int *elements,char **bo,int *bolen,int *dimfast,int *dimmid,int *dimslow,int *padding){ unsigned int comp; size_t elsiz, elem, df,dm,ds,pd; const char * byteorder; char * bot; {(error_status = cbf_get_realarrayparameters_wdims_fs(self, &comp,binary_id, &elsiz, &elem, &byteorder,&ds,&dm,&ds,&pd ));}; *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {{(error_status = CBF_ALLOC);}} strncpy(bot,byteorder,*bolen); *bo = bot; *compression = comp; *elsize = elsiz; *elements = elem; *dimfast = df; *dimmid = dm; *dimslow = ds; *padding = pd; } SWIGINTERN void cbf_handle_struct_get_realarray_as_string(cbf_handle_struct *self,char **s,int *slen){ int binary_id; size_t elements, elements_read, elsize; unsigned int compression; void * array; *slen = 0; /* Initialise in case of problems */ {(error_status = cbf_get_realarrayparameters(self, &compression, &binary_id, &elsize, &elements));}; if ((array=malloc(elsize*elements))) { /* cbf_failnez (cbf_select_column(cbf,colnum)) */ {(error_status = cbf_get_realarray(self, &binary_id, (void *)array, elsize, elements, &elements_read));}; }else{ {(error_status = CBF_ALLOC);}; } *slen = elsize*elements; *s = (char *) array; } SWIGINTERN void cbf_handle_struct_get_bin_sizes(cbf_handle_struct *self,int element_number,double *slowbinsize,double *fastbinsize){ {(error_status = cbf_get_bin_sizes (self, (unsigned int)element_number, slowbinsize, fastbinsize));}; } SWIGINTERN void cbf_handle_struct_reset_category(cbf_handle_struct *self){ {(error_status = cbf_reset_category(self));};} SWIGINTERN cbf_goniometer cbf_handle_struct_construct_goniometer(cbf_handle_struct *self){ cbf_goniometer goniometer; {(error_status = cbf_construct_goniometer(self,&goniometer));}; return goniometer; } SWIGINTERN void cbf_handle_struct_set_datablockname(cbf_handle_struct *self,char const *arg){ {(error_status = cbf_set_datablockname(self,arg));};} SWIGINTERN void cbf_handle_struct_set_crystal_id(cbf_handle_struct *self,char const *arg){ {(error_status = cbf_set_crystal_id(self,arg));};} SWIGINTERN void cbf_handle_struct_get_integerarray_as_string(cbf_handle_struct *self,char **s,int *slen){ int binary_id, elsigned, elunsigned; size_t elements, elements_read, elsize; int minelement, maxelement; unsigned int compression; void * array; *slen = 0; /* Initialise in case of problems */ {(error_status = cbf_get_integerarrayparameters(self, &compression, &binary_id, &elsize, &elsigned, &elunsigned, &elements, &minelement, &maxelement));}; if ((array=malloc(elsize*elements))) { /* cbf_failnez (cbf_select_column(cbf,colnum)) */ {(error_status = cbf_get_integerarray(self, &binary_id, (void *)array, elsize, elsigned, elements, &elements_read));}; }else{ {(error_status = CBF_ALLOC);}; } *slen = elsize*elements; *s = (char *) array; } SWIGINTERN void cbf_handle_struct_set_3d_image(cbf_handle_struct *self,unsigned int element_number,unsigned int compression,char *data,int len,int elsize,int elsign,int ndimslow,int ndimmid,int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimmid*ndimfast){ array = data; els = elsize; reserved = 0; {(error_status = cbf_set_3d_image (self, reserved, element_number, compression, (void *) data, (size_t) elsize, elsign, (size_t) ndimslow, (size_t) ndimmid, (size_t)ndimfast));}; }else{ {(error_status = CBF_ARGUMENT);}; } } SWIGINTERN void cbf_handle_struct_set_dictionary(cbf_handle_struct *self,cbf_handle other){ {(error_status = cbf_set_dictionary(self,other));}; } SWIGINTERN char const *cbf_handle_struct_find_tag_category(cbf_handle_struct *self,char const *tagname){ const char * result; {(error_status = cbf_find_tag_category(self,tagname, &result));}; return result; } SWIGINTERN void cbf_handle_struct_get_real_3d_image_sf_as_string(cbf_handle_struct *self,int element_number,char **s,int *slen,int elsize,int ndimslow,int ndimmid,int ndimfast){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) { {(error_status = cbf_get_real_3d_image_sf(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast));}; }else{ {(error_status = CBF_ALLOC);}; } *slen = elsize*ndimfast*ndimmid*ndimslow; *s = (char *) array; } SWIGINTERN void cbf_handle_struct_set_typeofvalue(cbf_handle_struct *self,char const *arg){ {(error_status = cbf_set_typeofvalue(self,arg));};} SWIGINTERN void cbf_handle_struct_set_integerarray_wdims(cbf_handle_struct *self,unsigned int compression,int binary_id,char *data,int len,int elsize,int elsigned,int elements,char *bo,int bolen,int dimfast,int dimmid,int dimslow,int padding){ /* safety check on args */ size_t els, ele; void *array; char byteorder[15]; if(len == elsize*elements && elements==dimfast*dimmid*dimslow){ array = data; els = elsize; ele = elements; strncpy(byteorder,bo,bolen<15?bolen:14); byteorder[bolen<15?14:bolen] = 0; {(error_status = cbf_set_integerarray_wdims (self, compression, binary_id, (void *) data, (size_t) elsize, elsigned, (size_t) elements, (const char *)byteorder, (size_t)dimfast, (size_t)dimmid, (size_t)dimslow, (size_t)padding));}; }else{ {(error_status = CBF_ARGUMENT);}; } } SWIGINTERN void cbf_handle_struct_set_integration_time(cbf_handle_struct *self,double time){ unsigned int reserved; reserved = 0; {(error_status = cbf_set_integration_time(self,reserved,time));}; } SWIGINTERN void cbf_handle_struct_set_axis_setting(cbf_handle_struct *self,char const *axis_id,double start,double increment){ unsigned int reserved; reserved = 0; {(error_status = cbf_set_axis_setting(self,reserved, axis_id,start,increment));}; } SWIGINTERN void cbf_handle_struct_get_real_image_as_string(cbf_handle_struct *self,int element_number,char **s,int *slen,int elsize,int ndimslow,int ndimfast){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimslow))) { {(error_status = cbf_get_real_image(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, (size_t) ndimslow, (size_t)ndimfast));}; }else{ {(error_status = CBF_ALLOC);}; } *slen = elsize*ndimfast*ndimslow; *s = (char *) array; } SWIGINTERN void cbf_handle_struct_get_3d_image_sf_as_string(cbf_handle_struct *self,int element_number,char **s,int *slen,int elsize,int elsign,int ndimfast,int ndimmid,int ndimslow){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) { {(error_status = cbf_get_3d_image_sf(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, elsign, (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast));}; }else{ {(error_status = CBF_ALLOC);}; } *slen = elsize*ndimfast*ndimmid*ndimslow; *s = (char *) array; } SWIGINTERN void cbf_handle_struct_set_real_image_fs(cbf_handle_struct *self,unsigned int element_number,unsigned int compression,char *data,int len,int elsize,int ndimfast,int ndimslow){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimfast){ array = data; els = elsize; reserved = 0; {(error_status = cbf_set_real_image_fs (self, reserved, element_number, compression, (void *) data, (size_t) elsize, (size_t) ndimfast, (size_t)ndimslow));}; }else{ {(error_status = CBF_ARGUMENT);}; } } SWIGINTERN void cbf_handle_struct_get_overload(cbf_handle_struct *self,unsigned int element_number,double *overload){ {(error_status = cbf_get_overload(self,element_number,overload));}; } SWIGINTERN double cbf_handle_struct_get_wavelength(cbf_handle_struct *self){ double result; {(error_status = cbf_get_wavelength(self,&result));}; return result;} SWIGINTERN void cbf_handle_struct_next_datablock(cbf_handle_struct *self){ {(error_status = cbf_next_datablock(self));};} SWIGINTERN void cbf_handle_struct_get_realarrayparameters_wdims(cbf_handle_struct *self,int *compression,int *binary_id,int *elsize,int *elements,char **bo,int *bolen,int *dimfast,int *dimmid,int *dimslow,int *padding){ unsigned int comp; size_t elsiz, elem, df,dm,ds,pd; const char * byteorder; char * bot; {(error_status = cbf_get_realarrayparameters_wdims(self, &comp,binary_id, &elsiz, &elem, &byteorder,&ds,&dm,&ds,&pd ));}; *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {{(error_status = CBF_ALLOC);}} strncpy(bot,byteorder,*bolen); *bo = bot; *compression = comp; *elsize = elsiz; *elements = elem; *dimfast = df; *dimmid = dm; *dimslow = ds; *padding = pd; } SWIGINTERN void cbf_handle_struct_set_orientation_matrix(cbf_handle_struct *self,double m0,double m1,double m2,double m3,double m4,double m5,double m6,double m7,double m8){ double m[9]; m[0] = m0; m[1]=m1 ; m[2]=m2 ; m[3] = m3; m[4]=m4 ; m[5]=m5 ; m[6] = m6; m[7]=m7 ; m[8]=m8 ; {(error_status = cbf_get_orientation_matrix(self,m));}; } SWIGINTERN void cbf_handle_struct_new_category(cbf_handle_struct *self,char const *arg){ {(error_status = cbf_new_category(self,arg));};} SWIGINTERN void cbf_handle_struct_set_gain(cbf_handle_struct *self,unsigned int element_number,double gain,double gain_esd){ {(error_status = cbf_set_gain (self, element_number, gain, gain_esd));}; } SWIGINTERN void cbf_handle_struct_find_column(cbf_handle_struct *self,char const *arg){ {(error_status = cbf_find_column(self,arg));};} SWIGINTERN void cbf_handle_struct_remove_category(cbf_handle_struct *self){ {(error_status = cbf_remove_category(self));};} SWIGINTERN void cbf_handle_struct_get_integerarrayparameters_wdims_sf(cbf_handle_struct *self,int *compression,int *binary_id,int *elsize,int *elsigned,int *elunsigned,int *elements,int *minelement,int *maxelement,char **bo,int *bolen,int *dimslow,int *dimmid,int *dimfast,int *padding){ unsigned int comp; size_t elsiz, elem, df,dm,ds,pd; const char * byteorder; char * bot; {(error_status = cbf_get_integerarrayparameters_wdims_sf(self, &comp,binary_id, &elsiz, elsigned, elunsigned, &elem, minelement, maxelement, &byteorder,&ds,&dm,&df,&pd ));}; *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {{(error_status = CBF_ALLOC);}} strncpy(bot,byteorder,*bolen); *bo = bot; *compression = comp; *elsize = elsiz; *elements = elem; *dimfast = df; *dimmid = dm; *dimslow = ds; *padding = pd; } SWIGINTERN void cbf_handle_struct_get_pixel_size(cbf_handle_struct *self,unsigned int element_number,unsigned int axis_number,double *psize){ {(error_status = cbf_get_pixel_size(self, element_number, axis_number, psize));}; } SWIGINTERN void cbf_handle_struct_set_real_image_sf(cbf_handle_struct *self,unsigned int element_number,unsigned int compression,char *data,int len,int elsize,int ndimslow,int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimfast){ array = data; els = elsize; reserved = 0; {(error_status = cbf_set_real_image_sf (self, reserved, element_number, compression, (void *) data, (size_t) elsize, (size_t) ndimslow, (size_t)ndimfast));}; }else{ {(error_status = CBF_ARGUMENT);}; } } SWIGINTERN void cbf_handle_struct_require_category(cbf_handle_struct *self,char const *arg){ {(error_status = cbf_require_category(self,arg));};} SWIGINTERN void cbf_handle_struct_get_reciprocal_cell(cbf_handle_struct *self,double *astar,double *bstar,double *cstar,double *alphastar,double *betastar,double *gammastar){ double rcell[6]; {(error_status = cbf_get_reciprocal_cell(self,rcell,NULL));}; *astar = rcell[0]; *bstar = rcell[1]; *cstar = rcell[2]; *alphastar = rcell[3]; *betastar = rcell[4]; *gammastar = rcell[5]; } SWIGINTERN void cbf_handle_struct_get_reciprocal_cell_esd(cbf_handle_struct *self,double *a_esd,double *b_esd,double *c_esd,double *alpha_esd,double *beta_esd,double *gamma_esd){ double cell_esd[6]; {(error_status = cbf_get_reciprocal_cell(self,NULL,cell_esd));}; *a_esd = cell_esd[0]; *b_esd = cell_esd[1]; *c_esd = cell_esd[2]; *alpha_esd = cell_esd[3]; *beta_esd = cell_esd[4]; *gamma_esd = cell_esd[5]; } SWIGINTERN void cbf_handle_struct_get_3d_image_size(cbf_handle_struct *self,unsigned int element_number,int *ndimslow,int *ndimmid,int *ndimfast){ unsigned int reserved; size_t inslow, inmid, infast; reserved = 0; {(error_status = cbf_get_3d_image_size(self,reserved,element_number,&inslow,&inmid,&infast));}; *ndimslow = (int)inslow; /* FIXME - is that how to convert? */ *ndimmid = (int)inmid; *ndimfast = (int)infast; } SWIGINTERN char const *cbf_handle_struct_find_tag_root(cbf_handle_struct *self,char const *tagname){ const char* result; {(error_status = cbf_find_tag_root(self,tagname,&result));}; return result; } SWIGINTERN char const *cbf_handle_struct_require_category_root(cbf_handle_struct *self,char const *categoryname){ const char* result; {(error_status = cbf_require_category_root(self,categoryname, &result));}; return result; } SWIGINTERN void cbf_handle_struct_set_realarray_wdims_sf(cbf_handle_struct *self,unsigned int compression,int binary_id,char *data,int len,int elsize,int elements,char *bo,int bolen,int dimslow,int dimmid,int dimfast,int padding){ /* safety check on args */ size_t els, ele; void *array; char byteorder[15]; if(len == elsize*elements && elements==dimfast*dimmid*dimslow){ array = data; els = elsize; ele = elements; strncpy(byteorder,bo,bolen<15?bolen:14); byteorder[bolen<15?14:bolen] = 0; {(error_status = cbf_set_realarray_wdims_sf (self, compression, binary_id, (void *) data, (size_t) elsize, (size_t) elements, (const char *)byteorder, (size_t) dimslow, (size_t) dimmid, (size_t) dimfast, (size_t)padding));}; }else{ {(error_status = CBF_ARGUMENT);}; } } SWIGINTERN void cbf_handle_struct_set_integervalue(cbf_handle_struct *self,int number){ {(error_status = cbf_set_integervalue(self,number));};} SWIGINTERN char const *cbf_handle_struct_category_name(cbf_handle_struct *self){ const char* result; {(error_status = cbf_category_name(self, &result));}; return result;} SWIGINTERN char const *cbf_handle_struct_get_typeofvalue(cbf_handle_struct *self){ const char* result; {(error_status = cbf_get_typeofvalue(self, &result));}; return result;} SWIGINTERN void cbf_handle_struct_set_real_image(cbf_handle_struct *self,unsigned int element_number,unsigned int compression,char *data,int len,int elsize,int ndimslow,int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimfast){ array = data; els = elsize; reserved = 0; {(error_status = cbf_set_real_image (self, reserved, element_number, compression, (void *) data, (size_t) elsize, (size_t) ndimslow, (size_t)ndimfast));}; }else{ {(error_status = CBF_ARGUMENT);}; } } SWIGINTERN void cbf_handle_struct_get_3d_image_as_string(cbf_handle_struct *self,int element_number,char **s,int *slen,int elsize,int elsign,int ndimfast,int ndimmid,int ndimslow){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) { {(error_status = cbf_get_3d_image(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, elsign, (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast));}; }else{ {(error_status = CBF_ALLOC);}; } *slen = elsize*ndimfast*ndimmid*ndimslow; *s = (char *) array; } SWIGINTERN void cbf_handle_struct_remove_row(cbf_handle_struct *self){ {(error_status = cbf_remove_row(self));};} SWIGINTERN void cbf_handle_struct_set_overload(cbf_handle_struct *self,unsigned int element_number,double overload){ {(error_status = cbf_set_overload(self,element_number,overload));}; } SWIGINTERN void cbf_handle_struct_get_image_size(cbf_handle_struct *self,unsigned int element_number,int *ndimslow,int *ndimfast){ unsigned int reserved; size_t inslow, infast; reserved = 0; {(error_status = cbf_get_image_size(self,reserved,element_number,&inslow,&infast));}; *ndimslow = (int)inslow; *ndimfast = (int)infast; } SWIGINTERN void cbf_handle_struct_set_3d_image_sf(cbf_handle_struct *self,unsigned int element_number,unsigned int compression,char *data,int len,int elsize,int elsign,int ndimslow,int ndimmid,int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimmid*ndimfast){ array = data; els = elsize; reserved = 0; {(error_status = cbf_set_3d_image_sf (self, reserved, element_number, compression, (void *) data, (size_t) elsize, elsign, (size_t) ndimslow, (size_t) ndimmid, (size_t)ndimfast));}; }else{ {(error_status = CBF_ARGUMENT);}; } } SWIGINTERN void cbf_handle_struct_get_real_image_sf_as_string(cbf_handle_struct *self,int element_number,char **s,int *slen,int elsize,int ndimslow,int ndimfast){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimslow))) { {(error_status = cbf_get_real_image_sf(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, (size_t) ndimslow, (size_t)ndimfast));}; }else{ {(error_status = CBF_ALLOC);}; } *slen = elsize*ndimfast*ndimslow; *s = (char *) array; } SWIGINTERN void cbf_handle_struct_get_image_as_string(cbf_handle_struct *self,int element_number,char **s,int *slen,int elsize,int elsign,int ndimslow,int ndimfast){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimslow))) { {(error_status = cbf_get_image(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, elsign, (size_t) ndimslow, (size_t)ndimfast));}; }else{ {(error_status = CBF_ALLOC);}; } *slen = elsize*ndimfast*ndimslow; *s = (char *) array; } SWIGINTERN void cbf_handle_struct_set_tag_root(cbf_handle_struct *self,char const *tagname,char const *tagroot_in){ {(error_status = cbf_set_tag_root(self,tagname,tagroot_in));}; } SWIGINTERN void cbf_handle_struct_write_widefile(cbf_handle_struct *self,char const *filename,int ciforcbf,int headers,int encoding){ FILE *stream; int readable; /* Make the file non-0 to make CBFlib close the file */ readable = 1; if ( ! ( stream = fopen (filename, "w+b")) ){ {(error_status = CBF_FILEOPEN);}; } else{ {(error_status = cbf_write_widefile(self, stream, readable, ciforcbf, headers, encoding));}; } } SWIGINTERN unsigned int cbf_handle_struct_count_rows(cbf_handle_struct *self){ unsigned int result; {(error_status = cbf_count_rows(self,&result));}; return result;} SWIGINTERN void cbf_handle_struct_require_datablock(cbf_handle_struct *self,char const *arg){ {(error_status = cbf_require_datablock(self,arg));};} SWIGINTERN void cbf_handle_struct_set_integerarray(cbf_handle_struct *self,unsigned int compression,int binary_id,char *data,int len,int elsize,int elsigned,int elements){ /* safety check on args */ size_t els, ele; void *array; if(len == elsize*elements){ array = data; els = elsize; ele = elements; {(error_status = cbf_set_integerarray (self, compression, binary_id, (void *) data, (size_t) elsize, elsigned, (size_t) elements));}; }else{ {(error_status = CBF_ARGUMENT);}; } } SWIGINTERN void cbf_handle_struct_new_datablock(cbf_handle_struct *self,char const *arg){ {(error_status = cbf_new_datablock(self,arg));};} SWIGINTERN void cbf_handle_struct_set_datestamp(cbf_handle_struct *self,int year,int month,int day,int hour,int minute,double second,int timezone,double precision){ unsigned int reserved; reserved = 0; {(error_status = cbf_set_datestamp(self,reserved, year,month,day,hour,minute,second,timezone,precision));}; } SWIGINTERN void cbf_handle_struct_next_row(cbf_handle_struct *self){ {(error_status = cbf_next_row(self));};} SWIGINTERN void cbf_handle_struct_set_category_root(cbf_handle_struct *self,char const *categoryname,char const *categoryroot){ {(error_status = cbf_set_category_root(self,categoryname,categoryroot));}; } SWIGINTERN void cbf_handle_struct_set_pixel_size_fs(cbf_handle_struct *self,unsigned int element_number,unsigned int axis_number,double psize){ {(error_status = cbf_set_pixel_size_fs(self, element_number, axis_number, psize));}; } SWIGINTERN void cbf_handle_struct_insert_row(cbf_handle_struct *self,unsigned int arg){ {(error_status = cbf_insert_row(self,arg));};} SWIGINTERN void cbf_handle_struct_new_column(cbf_handle_struct *self,char const *arg){ {(error_status = cbf_new_column(self,arg));};} SWIGINTERN void cbf_handle_struct_get_real_3d_image_as_string(cbf_handle_struct *self,int element_number,char **s,int *slen,int elsize,int ndimslow,int ndimmid,int ndimfast){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) { {(error_status = cbf_get_real_3d_image(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast));}; }else{ {(error_status = CBF_ALLOC);}; } *slen = elsize*ndimfast*ndimmid*ndimslow; *s = (char *) array; } SWIGINTERN void cbf_handle_struct_get_integration_time(cbf_handle_struct *self,double *time){ unsigned int reserved; double tim; reserved = 0; {(error_status = cbf_get_integration_time(self,reserved,&tim));}; *time = tim; } SWIGINTERN void cbf_handle_struct_set_realarray(cbf_handle_struct *self,unsigned int compression,int binary_id,char *data,int len,int elsize,int elements){ /* safety check on args */ size_t els, ele; void *array; if(len == elsize*elements){ array = data; els = elsize; ele = elements; {(error_status = cbf_set_realarray (self, compression, binary_id, (void *) data, (size_t) elsize, (size_t) elements));}; }else{ {(error_status = CBF_ARGUMENT);}; } } SWIGINTERN char const *cbf_handle_struct_get_element_id(cbf_handle_struct *self,unsigned int element_number){ const char * result; {(error_status = cbf_get_element_id (self, element_number, &result));}; return result; } SWIGINTERN void cbf_handle_struct_get_image_sf_as_string(cbf_handle_struct *self,int element_number,char **s,int *slen,int elsize,int elsign,int ndimslow,int ndimfast){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimslow))) { {(error_status = cbf_get_image_sf(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, elsign, (size_t) ndimslow, (size_t)ndimfast));}; }else{ {(error_status = CBF_ALLOC);}; } *slen = elsize*ndimfast*ndimslow; *s = (char *) array; } SWIGINTERN void cbf_handle_struct_get_3d_image_size_fs(cbf_handle_struct *self,unsigned int element_number,int *ndimfast,int *ndimmid,int *ndimslow){ unsigned int reserved; size_t inslow, inmid, infast; reserved = 0; {(error_status = cbf_get_3d_image_size_fs(self,reserved,element_number,&infast,&inmid,&inslow));}; *ndimslow = (int)inslow; /* FIXME - is that how to convert? */ *ndimmid = (int)inmid; *ndimfast = (int)infast; } SWIGINTERN void cbf_handle_struct_set_value(cbf_handle_struct *self,char const *arg){ {(error_status = cbf_set_value(self,arg));};} SWIGINTERN void cbf_handle_struct_set_current_timestamp(cbf_handle_struct *self,int timezone){ unsigned int reserved; reserved = 0; {(error_status = cbf_set_current_timestamp(self,reserved,timezone));}; } SWIGINTERN void cbf_handle_struct_require_doublevalue(cbf_handle_struct *self,double *number,double defaultvalue){ {(error_status = cbf_require_doublevalue(self,number,defaultvalue));}; } SWIGINTERN void cbf_handle_struct_rewind_datablock(cbf_handle_struct *self){ {(error_status = cbf_rewind_datablock(self));};} SWIGINTERN char const *cbf_handle_struct_require_column_value(cbf_handle_struct *self,char const *columnname,char const *defaultvalue){ const char * result; {(error_status = cbf_require_column_value(self,columnname, &result,defaultvalue));}; return result; } SWIGINTERN cbf_handle cbf_handle_struct_get_dictionary(cbf_handle_struct *self){ cbf_handle temp; {(error_status = cbf_get_dictionary(self,&temp));}; return temp; } SWIGINTERN void cbf_handle_struct_reset_saveframe(cbf_handle_struct *self){ {(error_status = cbf_reset_saveframe(self));};} SWIGINTERN void cbf_handle_struct_set_reciprocal_cell(cbf_handle_struct *self,double cell[6]){ {(error_status = cbf_set_reciprocal_cell(self,cell,NULL));}; } SWIGINTERN void cbf_handle_struct_set_reciprocal_cell_esd(cbf_handle_struct *self,double cell_esd[6]){ {(error_status = cbf_set_reciprocal_cell(self,NULL,cell_esd));}; } SWIGINTERN void cbf_handle_struct_set_real_3d_image_fs(cbf_handle_struct *self,unsigned int element_number,unsigned int compression,char *data,int len,int elsize,int ndimfast,int ndimmid,int ndimslow){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimmid*ndimfast){ array = data; els = elsize; reserved = 0; {(error_status = cbf_set_real_3d_image_fs (self, reserved, element_number, compression, (void *) data, (size_t) elsize, (size_t) ndimfast, (size_t)ndimmid, (size_t)ndimslow));}; }else{ {(error_status = CBF_ARGUMENT);}; } } SWIGINTERN void cbf_handle_struct_set_doublevalue(cbf_handle_struct *self,char const *format,double number){ {(error_status = cbf_set_doublevalue(self,format,number));};} SWIGINTERN void cbf_handle_struct_find_category(cbf_handle_struct *self,char const *arg){ {(error_status = cbf_find_category(self,arg));};} SWIGINTERN void cbf_handle_struct_get_integerarrayparameters_wdims_fs(cbf_handle_struct *self,int *compression,int *binary_id,int *elsize,int *elsigned,int *elunsigned,int *elements,int *minelement,int *maxelement,char **bo,int *bolen,int *dimfast,int *dimmid,int *dimslow,int *padding){ unsigned int comp; size_t elsiz, elem, df,dm,ds,pd; const char * byteorder; char * bot; {(error_status = cbf_get_integerarrayparameters_wdims_fs(self, &comp,binary_id, &elsiz, elsigned, elunsigned, &elem, minelement, maxelement, &byteorder,&df,&dm,&ds,&pd ));}; *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {{(error_status = CBF_ALLOC);}} strncpy(bot,byteorder,*bolen); *bo = bot; *compression = comp; *elsize = elsiz; *elements = elem; *dimfast = df; *dimmid = dm; *dimslow = ds; *padding = pd; } SWIGINTERN void cbf_handle_struct_set_realarray_wdims_fs(cbf_handle_struct *self,unsigned int compression,int binary_id,char *data,int len,int elsize,int elements,char *bo,int bolen,int dimfast,int dimmid,int dimslow,int padding){ /* safety check on args */ size_t els, ele; void *array; char byteorder[15]; if(len == elsize*elements && elements==dimfast*dimmid*dimslow){ array = data; els = elsize; ele = elements; strncpy(byteorder,bo,bolen<15?bolen:14); byteorder[bolen<15?14:bolen] = 0; {(error_status = cbf_set_realarray_wdims_fs (self, compression, binary_id, (void *) data, (size_t) elsize, (size_t) elements, (const char *)byteorder, (size_t) dimfast, (size_t) dimmid, (size_t) dimslow, (size_t)padding));}; }else{ {(error_status = CBF_ARGUMENT);}; } } SWIGINTERN char const *cbf_handle_struct_find_category_root(cbf_handle_struct *self,char const *categoryname){ const char * result; {(error_status = cbf_find_category_root(self,categoryname,&result));}; return result; } SWIGINTERN void cbf_handle_struct_set_integerarray_wdims_fs(cbf_handle_struct *self,unsigned int compression,int binary_id,char *data,int len,int elsize,int elsigned,int elements,char *bo,int bolen,int dimfast,int dimmid,int dimslow,int padding){ /* safety check on args */ size_t els, ele; void *array; char byteorder[15]; if(len == elsize*elements && elements==dimfast*dimmid*dimslow){ array = data; els = elsize; ele = elements; strncpy(byteorder,bo,bolen<15?bolen:14); byteorder[bolen<15?14:bolen] = 0; {(error_status = cbf_set_integerarray_wdims_fs (self, compression, binary_id, (void *) data, (size_t) elsize, elsigned, (size_t) elements, (const char *)byteorder, (size_t)dimfast, (size_t)dimmid, (size_t)dimslow, (size_t)padding));}; }else{ {(error_status = CBF_ARGUMENT);}; } } SWIGINTERN void cbf_handle_struct_set_image_sf(cbf_handle_struct *self,unsigned int element_number,unsigned int compression,char *data,int len,int elsize,int elsign,int ndimslow,int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimfast){ array = data; els = elsize; reserved = 0; {(error_status = cbf_set_image_sf (self, reserved, element_number, compression, (void *) data, (size_t) elsize, elsign, (size_t) ndimslow, (size_t)ndimfast));}; }else{ {(error_status = CBF_ARGUMENT);}; } } SWIGINTERN void cbf_handle_struct_set_unit_cell(cbf_handle_struct *self,double cell[6]){ {(error_status = cbf_set_unit_cell(self,cell,NULL));}; } SWIGINTERN void cbf_handle_struct_set_unit_cell_esd(cbf_handle_struct *self,double cell_esd[6]){ {(error_status = cbf_set_unit_cell(self,NULL,cell_esd));}; } #ifdef __cplusplus extern "C" { #endif SWIGINTERN PyObject *_wrap_new_doubleArray(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; size_t arg1 ; size_t val1 ; int ecode1 = 0 ; PyObject * obj0 = 0 ; doubleArray *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:new_doubleArray",&obj0)) SWIG_fail; ecode1 = SWIG_AsVal_size_t(obj0, &val1); if (!SWIG_IsOK(ecode1)) { SWIG_exception_fail(SWIG_ArgError(ecode1), "in method '" "new_doubleArray" "', argument " "1"" of type '" "size_t""'"); } arg1 = (size_t)(val1); result = (doubleArray *)new_doubleArray(arg1); resultobj = SWIG_NewPointerObj(SWIG_as_voidptr(result), SWIGTYPE_p_doubleArray, SWIG_POINTER_NEW | 0 ); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_delete_doubleArray(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; doubleArray *arg1 = (doubleArray *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:delete_doubleArray",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_doubleArray, SWIG_POINTER_DISOWN | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "delete_doubleArray" "', argument " "1"" of type '" "doubleArray *""'"); } arg1 = (doubleArray *)(argp1); delete_doubleArray(arg1); resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_doubleArray___getitem__(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; doubleArray *arg1 = (doubleArray *) 0 ; size_t arg2 ; void *argp1 = 0 ; int res1 = 0 ; size_t val2 ; int ecode2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; double result; if (!PyArg_ParseTuple(args,(char *)"OO:doubleArray___getitem__",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_doubleArray, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "doubleArray___getitem__" "', argument " "1"" of type '" "doubleArray *""'"); } arg1 = (doubleArray *)(argp1); ecode2 = SWIG_AsVal_size_t(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "doubleArray___getitem__" "', argument " "2"" of type '" "size_t""'"); } arg2 = (size_t)(val2); result = (double)doubleArray___getitem__(arg1,arg2); resultobj = SWIG_From_double((double)(result)); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_doubleArray___setitem__(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; doubleArray *arg1 = (doubleArray *) 0 ; size_t arg2 ; double arg3 ; void *argp1 = 0 ; int res1 = 0 ; size_t val2 ; int ecode2 = 0 ; double val3 ; int ecode3 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOO:doubleArray___setitem__",&obj0,&obj1,&obj2)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_doubleArray, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "doubleArray___setitem__" "', argument " "1"" of type '" "doubleArray *""'"); } arg1 = (doubleArray *)(argp1); ecode2 = SWIG_AsVal_size_t(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "doubleArray___setitem__" "', argument " "2"" of type '" "size_t""'"); } arg2 = (size_t)(val2); ecode3 = SWIG_AsVal_double(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "doubleArray___setitem__" "', argument " "3"" of type '" "double""'"); } arg3 = (double)(val3); doubleArray___setitem__(arg1,arg2,arg3); resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_doubleArray_cast(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; doubleArray *arg1 = (doubleArray *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; double *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:doubleArray_cast",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_doubleArray, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "doubleArray_cast" "', argument " "1"" of type '" "doubleArray *""'"); } arg1 = (doubleArray *)(argp1); result = (double *)doubleArray_cast(arg1); resultobj = SWIG_NewPointerObj(SWIG_as_voidptr(result), SWIGTYPE_p_double, 0 | 0 ); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_doubleArray_frompointer(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; double *arg1 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; doubleArray *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:doubleArray_frompointer",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_double, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "doubleArray_frompointer" "', argument " "1"" of type '" "double *""'"); } arg1 = (double *)(argp1); result = (doubleArray *)doubleArray_frompointer(arg1); resultobj = SWIG_NewPointerObj(SWIG_as_voidptr(result), SWIGTYPE_p_doubleArray, 0 | 0 ); return resultobj; fail: return NULL; } SWIGINTERN PyObject *doubleArray_swigregister(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *obj; if (!PyArg_ParseTuple(args,(char*)"O:swigregister", &obj)) return NULL; SWIG_TypeNewClientData(SWIGTYPE_p_doubleArray, SWIG_NewClientData(obj)); return SWIG_Py_Void(); } SWIGINTERN PyObject *_wrap_new_intArray(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; size_t arg1 ; size_t val1 ; int ecode1 = 0 ; PyObject * obj0 = 0 ; intArray *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:new_intArray",&obj0)) SWIG_fail; ecode1 = SWIG_AsVal_size_t(obj0, &val1); if (!SWIG_IsOK(ecode1)) { SWIG_exception_fail(SWIG_ArgError(ecode1), "in method '" "new_intArray" "', argument " "1"" of type '" "size_t""'"); } arg1 = (size_t)(val1); result = (intArray *)new_intArray(arg1); resultobj = SWIG_NewPointerObj(SWIG_as_voidptr(result), SWIGTYPE_p_intArray, SWIG_POINTER_NEW | 0 ); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_delete_intArray(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; intArray *arg1 = (intArray *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:delete_intArray",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_intArray, SWIG_POINTER_DISOWN | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "delete_intArray" "', argument " "1"" of type '" "intArray *""'"); } arg1 = (intArray *)(argp1); delete_intArray(arg1); resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_intArray___getitem__(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; intArray *arg1 = (intArray *) 0 ; size_t arg2 ; void *argp1 = 0 ; int res1 = 0 ; size_t val2 ; int ecode2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; int result; if (!PyArg_ParseTuple(args,(char *)"OO:intArray___getitem__",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_intArray, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "intArray___getitem__" "', argument " "1"" of type '" "intArray *""'"); } arg1 = (intArray *)(argp1); ecode2 = SWIG_AsVal_size_t(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "intArray___getitem__" "', argument " "2"" of type '" "size_t""'"); } arg2 = (size_t)(val2); result = (int)intArray___getitem__(arg1,arg2); resultobj = SWIG_From_int((int)(result)); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_intArray___setitem__(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; intArray *arg1 = (intArray *) 0 ; size_t arg2 ; int arg3 ; void *argp1 = 0 ; int res1 = 0 ; size_t val2 ; int ecode2 = 0 ; int val3 ; int ecode3 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOO:intArray___setitem__",&obj0,&obj1,&obj2)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_intArray, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "intArray___setitem__" "', argument " "1"" of type '" "intArray *""'"); } arg1 = (intArray *)(argp1); ecode2 = SWIG_AsVal_size_t(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "intArray___setitem__" "', argument " "2"" of type '" "size_t""'"); } arg2 = (size_t)(val2); ecode3 = SWIG_AsVal_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "intArray___setitem__" "', argument " "3"" of type '" "int""'"); } arg3 = (int)(val3); intArray___setitem__(arg1,arg2,arg3); resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_intArray_cast(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; intArray *arg1 = (intArray *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; int *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:intArray_cast",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_intArray, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "intArray_cast" "', argument " "1"" of type '" "intArray *""'"); } arg1 = (intArray *)(argp1); result = (int *)intArray_cast(arg1); resultobj = SWIG_NewPointerObj(SWIG_as_voidptr(result), SWIGTYPE_p_int, 0 | 0 ); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_intArray_frompointer(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; int *arg1 = (int *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; intArray *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:intArray_frompointer",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_int, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "intArray_frompointer" "', argument " "1"" of type '" "int *""'"); } arg1 = (int *)(argp1); result = (intArray *)intArray_frompointer(arg1); resultobj = SWIG_NewPointerObj(SWIG_as_voidptr(result), SWIGTYPE_p_intArray, 0 | 0 ); return resultobj; fail: return NULL; } SWIGINTERN PyObject *intArray_swigregister(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *obj; if (!PyArg_ParseTuple(args,(char*)"O:swigregister", &obj)) return NULL; SWIG_TypeNewClientData(SWIGTYPE_p_intArray, SWIG_NewClientData(obj)); return SWIG_Py_Void(); } SWIGINTERN PyObject *_wrap_new_shortArray(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; size_t arg1 ; size_t val1 ; int ecode1 = 0 ; PyObject * obj0 = 0 ; shortArray *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:new_shortArray",&obj0)) SWIG_fail; ecode1 = SWIG_AsVal_size_t(obj0, &val1); if (!SWIG_IsOK(ecode1)) { SWIG_exception_fail(SWIG_ArgError(ecode1), "in method '" "new_shortArray" "', argument " "1"" of type '" "size_t""'"); } arg1 = (size_t)(val1); result = (shortArray *)new_shortArray(arg1); resultobj = SWIG_NewPointerObj(SWIG_as_voidptr(result), SWIGTYPE_p_shortArray, SWIG_POINTER_NEW | 0 ); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_delete_shortArray(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; shortArray *arg1 = (shortArray *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:delete_shortArray",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_shortArray, SWIG_POINTER_DISOWN | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "delete_shortArray" "', argument " "1"" of type '" "shortArray *""'"); } arg1 = (shortArray *)(argp1); delete_shortArray(arg1); resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_shortArray___getitem__(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; shortArray *arg1 = (shortArray *) 0 ; size_t arg2 ; void *argp1 = 0 ; int res1 = 0 ; size_t val2 ; int ecode2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; short result; if (!PyArg_ParseTuple(args,(char *)"OO:shortArray___getitem__",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_shortArray, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "shortArray___getitem__" "', argument " "1"" of type '" "shortArray *""'"); } arg1 = (shortArray *)(argp1); ecode2 = SWIG_AsVal_size_t(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "shortArray___getitem__" "', argument " "2"" of type '" "size_t""'"); } arg2 = (size_t)(val2); result = (short)shortArray___getitem__(arg1,arg2); resultobj = SWIG_From_short((short)(result)); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_shortArray___setitem__(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; shortArray *arg1 = (shortArray *) 0 ; size_t arg2 ; short arg3 ; void *argp1 = 0 ; int res1 = 0 ; size_t val2 ; int ecode2 = 0 ; short val3 ; int ecode3 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOO:shortArray___setitem__",&obj0,&obj1,&obj2)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_shortArray, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "shortArray___setitem__" "', argument " "1"" of type '" "shortArray *""'"); } arg1 = (shortArray *)(argp1); ecode2 = SWIG_AsVal_size_t(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "shortArray___setitem__" "', argument " "2"" of type '" "size_t""'"); } arg2 = (size_t)(val2); ecode3 = SWIG_AsVal_short(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "shortArray___setitem__" "', argument " "3"" of type '" "short""'"); } arg3 = (short)(val3); shortArray___setitem__(arg1,arg2,arg3); resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_shortArray_cast(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; shortArray *arg1 = (shortArray *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; short *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:shortArray_cast",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_shortArray, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "shortArray_cast" "', argument " "1"" of type '" "shortArray *""'"); } arg1 = (shortArray *)(argp1); result = (short *)shortArray_cast(arg1); resultobj = SWIG_NewPointerObj(SWIG_as_voidptr(result), SWIGTYPE_p_short, 0 | 0 ); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_shortArray_frompointer(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; short *arg1 = (short *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; shortArray *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:shortArray_frompointer",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_short, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "shortArray_frompointer" "', argument " "1"" of type '" "short *""'"); } arg1 = (short *)(argp1); result = (shortArray *)shortArray_frompointer(arg1); resultobj = SWIG_NewPointerObj(SWIG_as_voidptr(result), SWIGTYPE_p_shortArray, 0 | 0 ); return resultobj; fail: return NULL; } SWIGINTERN PyObject *shortArray_swigregister(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *obj; if (!PyArg_ParseTuple(args,(char*)"O:swigregister", &obj)) return NULL; SWIG_TypeNewClientData(SWIGTYPE_p_shortArray, SWIG_NewClientData(obj)); return SWIG_Py_Void(); } SWIGINTERN PyObject *_wrap_new_longArray(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; size_t arg1 ; size_t val1 ; int ecode1 = 0 ; PyObject * obj0 = 0 ; longArray *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:new_longArray",&obj0)) SWIG_fail; ecode1 = SWIG_AsVal_size_t(obj0, &val1); if (!SWIG_IsOK(ecode1)) { SWIG_exception_fail(SWIG_ArgError(ecode1), "in method '" "new_longArray" "', argument " "1"" of type '" "size_t""'"); } arg1 = (size_t)(val1); result = (longArray *)new_longArray(arg1); resultobj = SWIG_NewPointerObj(SWIG_as_voidptr(result), SWIGTYPE_p_longArray, SWIG_POINTER_NEW | 0 ); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_delete_longArray(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; longArray *arg1 = (longArray *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:delete_longArray",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_longArray, SWIG_POINTER_DISOWN | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "delete_longArray" "', argument " "1"" of type '" "longArray *""'"); } arg1 = (longArray *)(argp1); delete_longArray(arg1); resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_longArray___getitem__(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; longArray *arg1 = (longArray *) 0 ; size_t arg2 ; void *argp1 = 0 ; int res1 = 0 ; size_t val2 ; int ecode2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; long result; if (!PyArg_ParseTuple(args,(char *)"OO:longArray___getitem__",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_longArray, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "longArray___getitem__" "', argument " "1"" of type '" "longArray *""'"); } arg1 = (longArray *)(argp1); ecode2 = SWIG_AsVal_size_t(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "longArray___getitem__" "', argument " "2"" of type '" "size_t""'"); } arg2 = (size_t)(val2); result = (long)longArray___getitem__(arg1,arg2); resultobj = SWIG_From_long((long)(result)); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_longArray___setitem__(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; longArray *arg1 = (longArray *) 0 ; size_t arg2 ; long arg3 ; void *argp1 = 0 ; int res1 = 0 ; size_t val2 ; int ecode2 = 0 ; long val3 ; int ecode3 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOO:longArray___setitem__",&obj0,&obj1,&obj2)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_longArray, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "longArray___setitem__" "', argument " "1"" of type '" "longArray *""'"); } arg1 = (longArray *)(argp1); ecode2 = SWIG_AsVal_size_t(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "longArray___setitem__" "', argument " "2"" of type '" "size_t""'"); } arg2 = (size_t)(val2); ecode3 = SWIG_AsVal_long(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "longArray___setitem__" "', argument " "3"" of type '" "long""'"); } arg3 = (long)(val3); longArray___setitem__(arg1,arg2,arg3); resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_longArray_cast(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; longArray *arg1 = (longArray *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; long *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:longArray_cast",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_longArray, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "longArray_cast" "', argument " "1"" of type '" "longArray *""'"); } arg1 = (longArray *)(argp1); result = (long *)longArray_cast(arg1); resultobj = SWIG_NewPointerObj(SWIG_as_voidptr(result), SWIGTYPE_p_long, 0 | 0 ); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_longArray_frompointer(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; long *arg1 = (long *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; longArray *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:longArray_frompointer",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_long, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "longArray_frompointer" "', argument " "1"" of type '" "long *""'"); } arg1 = (long *)(argp1); result = (longArray *)longArray_frompointer(arg1); resultobj = SWIG_NewPointerObj(SWIG_as_voidptr(result), SWIGTYPE_p_longArray, 0 | 0 ); return resultobj; fail: return NULL; } SWIGINTERN PyObject *longArray_swigregister(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *obj; if (!PyArg_ParseTuple(args,(char*)"O:swigregister", &obj)) return NULL; SWIG_TypeNewClientData(SWIGTYPE_p_longArray, SWIG_NewClientData(obj)); return SWIG_Py_Void(); } SWIGINTERN PyObject *_wrap_get_local_integer_byte_order(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; char **arg1 = (char **) 0 ; int *arg2 = (int *) 0 ; char *temp1 = 0 ; int tempn1 ; arg1 = &temp1; arg2 = &tempn1; if (!PyArg_ParseTuple(args,(char *)":get_local_integer_byte_order")) SWIG_fail; { error_status=0; get_local_integer_byte_order(arg1,arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (*arg1) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_FromCharPtrAndSize(*arg1,*arg2)); free(*arg1); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_compute_cell_volume(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; double *arg1 ; double *arg2 = (double *) 0 ; double temp1[6] ; double temp2 ; int res2 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; if (!PyArg_ParseTuple(args,(char *)"O:compute_cell_volume",&obj0)) SWIG_fail; { if (obj0 == Py_None) arg1 = NULL; else if (!convert_darray(obj0,temp1,6)) { return NULL; } arg1 = &temp1[0]; } { error_status=0; compute_cell_volume(arg1,arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_get_local_real_format(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; char **arg1 = (char **) 0 ; int *arg2 = (int *) 0 ; char *temp1 = 0 ; int tempn1 ; arg1 = &temp1; arg2 = &tempn1; if (!PyArg_ParseTuple(args,(char *)":get_local_real_format")) SWIG_fail; { error_status=0; get_local_real_format(arg1,arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (*arg1) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_FromCharPtrAndSize(*arg1,*arg2)); free(*arg1); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_get_local_real_byte_order(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; char **arg1 = (char **) 0 ; int *arg2 = (int *) 0 ; char *temp1 = 0 ; int tempn1 ; arg1 = &temp1; arg2 = &tempn1; if (!PyArg_ParseTuple(args,(char *)":get_local_real_byte_order")) SWIG_fail; { error_status=0; get_local_real_byte_order(arg1,arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (*arg1) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_FromCharPtrAndSize(*arg1,*arg2)); free(*arg1); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_compute_reciprocal_cell(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; double *arg1 ; double *arg2 = (double *) 0 ; double *arg3 = (double *) 0 ; double *arg4 = (double *) 0 ; double *arg5 = (double *) 0 ; double *arg6 = (double *) 0 ; double *arg7 = (double *) 0 ; double temp1[6] ; double temp2 ; int res2 = SWIG_TMPOBJ ; double temp3 ; int res3 = SWIG_TMPOBJ ; double temp4 ; int res4 = SWIG_TMPOBJ ; double temp5 ; int res5 = SWIG_TMPOBJ ; double temp6 ; int res6 = SWIG_TMPOBJ ; double temp7 ; int res7 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; arg5 = &temp5; arg6 = &temp6; arg7 = &temp7; if (!PyArg_ParseTuple(args,(char *)"O:compute_reciprocal_cell",&obj0)) SWIG_fail; { if (obj0 == Py_None) arg1 = NULL; else if (!convert_darray(obj0,temp1,6)) { return NULL; } arg1 = &temp1[0]; } { error_status=0; compute_reciprocal_cell(arg1,arg2,arg3,arg4,arg5,arg6,arg7); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res6)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg6))); } else { int new_flags = SWIG_IsNewObj(res6) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg6), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res7)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg7))); } else { int new_flags = SWIG_IsNewObj(res7) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg7), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_positioner_struct_matrix_set(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_positioner_struct *arg1 = (cbf_positioner_struct *) 0 ; double (*arg2)[4] ; void *argp1 = 0 ; int res1 = 0 ; void *argp2 = 0 ; int res2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_positioner_struct_matrix_set",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_positioner_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_positioner_struct_matrix_set" "', argument " "1"" of type '" "cbf_positioner_struct *""'"); } arg1 = (cbf_positioner_struct *)(argp1); res2 = SWIG_ConvertPtr(obj1, &argp2,SWIGTYPE_p_a_4__double, 0 | 0 ); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_positioner_struct_matrix_set" "', argument " "2"" of type '" "double [3][4]""'"); } arg2 = (double (*)[4])(argp2); { if (arg2) { size_t ii = 0; for (; ii < (size_t)3; ++ii) { if (arg2[ii]) { size_t jj = 0; for (; jj < (size_t)4; ++jj) arg1->matrix[ii][jj] = arg2[ii][jj]; } else { SWIG_exception_fail(SWIG_ValueError, "invalid null reference " "in variable '""matrix""' of type '""double [3][4]""'"); } } } else { SWIG_exception_fail(SWIG_ValueError, "invalid null reference " "in variable '""matrix""' of type '""double [3][4]""'"); } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_positioner_struct_matrix_get(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_positioner_struct *arg1 = (cbf_positioner_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; double (*result)[4] = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_positioner_struct_matrix_get",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_positioner_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_positioner_struct_matrix_get" "', argument " "1"" of type '" "cbf_positioner_struct *""'"); } arg1 = (cbf_positioner_struct *)(argp1); result = (double (*)[4])(double (*)[4]) ((arg1)->matrix); resultobj = SWIG_NewPointerObj(SWIG_as_voidptr(result), SWIGTYPE_p_a_4__double, 0 | 0 ); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_positioner_struct_axis_set(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_positioner_struct *arg1 = (cbf_positioner_struct *) 0 ; cbf_axis_struct *arg2 = (cbf_axis_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; void *argp2 = 0 ; int res2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_positioner_struct_axis_set",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_positioner_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_positioner_struct_axis_set" "', argument " "1"" of type '" "cbf_positioner_struct *""'"); } arg1 = (cbf_positioner_struct *)(argp1); res2 = SWIG_ConvertPtr(obj1, &argp2,SWIGTYPE_p_cbf_axis_struct, SWIG_POINTER_DISOWN | 0 ); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_positioner_struct_axis_set" "', argument " "2"" of type '" "cbf_axis_struct *""'"); } arg2 = (cbf_axis_struct *)(argp2); if (arg1) (arg1)->axis = arg2; resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_positioner_struct_axis_get(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_positioner_struct *arg1 = (cbf_positioner_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; cbf_axis_struct *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_positioner_struct_axis_get",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_positioner_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_positioner_struct_axis_get" "', argument " "1"" of type '" "cbf_positioner_struct *""'"); } arg1 = (cbf_positioner_struct *)(argp1); result = (cbf_axis_struct *) ((arg1)->axis); resultobj = SWIG_NewPointerObj(SWIG_as_voidptr(result), SWIGTYPE_p_cbf_axis_struct, 0 | 0 ); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_positioner_struct_axes_set(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_positioner_struct *arg1 = (cbf_positioner_struct *) 0 ; size_t arg2 ; void *argp1 = 0 ; int res1 = 0 ; size_t val2 ; int ecode2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_positioner_struct_axes_set",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_positioner_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_positioner_struct_axes_set" "', argument " "1"" of type '" "cbf_positioner_struct *""'"); } arg1 = (cbf_positioner_struct *)(argp1); ecode2 = SWIG_AsVal_size_t(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_positioner_struct_axes_set" "', argument " "2"" of type '" "size_t""'"); } arg2 = (size_t)(val2); if (arg1) (arg1)->axes = arg2; resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_positioner_struct_axes_get(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_positioner_struct *arg1 = (cbf_positioner_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; size_t result; if (!PyArg_ParseTuple(args,(char *)"O:cbf_positioner_struct_axes_get",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_positioner_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_positioner_struct_axes_get" "', argument " "1"" of type '" "cbf_positioner_struct *""'"); } arg1 = (cbf_positioner_struct *)(argp1); result = ((arg1)->axes); resultobj = SWIG_From_size_t((size_t)(result)); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_positioner_struct_matrix_is_valid_set(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_positioner_struct *arg1 = (cbf_positioner_struct *) 0 ; int arg2 ; void *argp1 = 0 ; int res1 = 0 ; int val2 ; int ecode2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_positioner_struct_matrix_is_valid_set",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_positioner_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_positioner_struct_matrix_is_valid_set" "', argument " "1"" of type '" "cbf_positioner_struct *""'"); } arg1 = (cbf_positioner_struct *)(argp1); ecode2 = SWIG_AsVal_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_positioner_struct_matrix_is_valid_set" "', argument " "2"" of type '" "int""'"); } arg2 = (int)(val2); if (arg1) (arg1)->matrix_is_valid = arg2; resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_positioner_struct_matrix_is_valid_get(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_positioner_struct *arg1 = (cbf_positioner_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; int result; if (!PyArg_ParseTuple(args,(char *)"O:cbf_positioner_struct_matrix_is_valid_get",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_positioner_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_positioner_struct_matrix_is_valid_get" "', argument " "1"" of type '" "cbf_positioner_struct *""'"); } arg1 = (cbf_positioner_struct *)(argp1); result = (int) ((arg1)->matrix_is_valid); resultobj = SWIG_From_int((int)(result)); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_positioner_struct_axes_are_connected_set(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_positioner_struct *arg1 = (cbf_positioner_struct *) 0 ; int arg2 ; void *argp1 = 0 ; int res1 = 0 ; int val2 ; int ecode2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_positioner_struct_axes_are_connected_set",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_positioner_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_positioner_struct_axes_are_connected_set" "', argument " "1"" of type '" "cbf_positioner_struct *""'"); } arg1 = (cbf_positioner_struct *)(argp1); ecode2 = SWIG_AsVal_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_positioner_struct_axes_are_connected_set" "', argument " "2"" of type '" "int""'"); } arg2 = (int)(val2); if (arg1) (arg1)->axes_are_connected = arg2; resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_positioner_struct_axes_are_connected_get(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_positioner_struct *arg1 = (cbf_positioner_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; int result; if (!PyArg_ParseTuple(args,(char *)"O:cbf_positioner_struct_axes_are_connected_get",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_positioner_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_positioner_struct_axes_are_connected_get" "', argument " "1"" of type '" "cbf_positioner_struct *""'"); } arg1 = (cbf_positioner_struct *)(argp1); result = (int) ((arg1)->axes_are_connected); resultobj = SWIG_From_int((int)(result)); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_new_cbf_positioner_struct(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_positioner_struct *result = 0 ; if (!PyArg_ParseTuple(args,(char *)":new_cbf_positioner_struct")) SWIG_fail; { error_status=0; result = (cbf_positioner_struct *)new_cbf_positioner_struct(); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_NewPointerObj(SWIG_as_voidptr(result), SWIGTYPE_p_cbf_positioner_struct, SWIG_POINTER_NEW | 0 ); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_delete_cbf_positioner_struct(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_positioner_struct *arg1 = (cbf_positioner_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:delete_cbf_positioner_struct",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_positioner_struct, SWIG_POINTER_DISOWN | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "delete_cbf_positioner_struct" "', argument " "1"" of type '" "cbf_positioner_struct *""'"); } arg1 = (cbf_positioner_struct *)(argp1); { error_status=0; delete_cbf_positioner_struct(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_positioner_struct_get_rotation_range(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_positioner_struct *arg1 = (cbf_positioner_struct *) 0 ; double *arg2 = (double *) 0 ; double *arg3 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double temp2 ; int res2 = SWIG_TMPOBJ ; double temp3 ; int res3 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; if (!PyArg_ParseTuple(args,(char *)"O:cbf_positioner_struct_get_rotation_range",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_positioner_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_positioner_struct_get_rotation_range" "', argument " "1"" of type '" "cbf_positioner_struct *""'"); } arg1 = (cbf_positioner_struct *)(argp1); { error_status=0; cbf_positioner_struct_get_rotation_range(arg1,arg2,arg3); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_positioner_struct_rotate_vector(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_positioner_struct *arg1 = (cbf_positioner_struct *) 0 ; double arg2 ; double arg3 ; double arg4 ; double arg5 ; double *arg6 = (double *) 0 ; double *arg7 = (double *) 0 ; double *arg8 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double val2 ; int ecode2 = 0 ; double val3 ; int ecode3 = 0 ; double val4 ; int ecode4 = 0 ; double val5 ; int ecode5 = 0 ; double temp6 ; int res6 = SWIG_TMPOBJ ; double temp7 ; int res7 = SWIG_TMPOBJ ; double temp8 ; int res8 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; arg6 = &temp6; arg7 = &temp7; arg8 = &temp8; if (!PyArg_ParseTuple(args,(char *)"OOOOO:cbf_positioner_struct_rotate_vector",&obj0,&obj1,&obj2,&obj3,&obj4)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_positioner_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_positioner_struct_rotate_vector" "', argument " "1"" of type '" "cbf_positioner_struct *""'"); } arg1 = (cbf_positioner_struct *)(argp1); ecode2 = SWIG_AsVal_double(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_positioner_struct_rotate_vector" "', argument " "2"" of type '" "double""'"); } arg2 = (double)(val2); ecode3 = SWIG_AsVal_double(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_positioner_struct_rotate_vector" "', argument " "3"" of type '" "double""'"); } arg3 = (double)(val3); ecode4 = SWIG_AsVal_double(obj3, &val4); if (!SWIG_IsOK(ecode4)) { SWIG_exception_fail(SWIG_ArgError(ecode4), "in method '" "cbf_positioner_struct_rotate_vector" "', argument " "4"" of type '" "double""'"); } arg4 = (double)(val4); ecode5 = SWIG_AsVal_double(obj4, &val5); if (!SWIG_IsOK(ecode5)) { SWIG_exception_fail(SWIG_ArgError(ecode5), "in method '" "cbf_positioner_struct_rotate_vector" "', argument " "5"" of type '" "double""'"); } arg5 = (double)(val5); { error_status=0; cbf_positioner_struct_rotate_vector(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res6)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg6))); } else { int new_flags = SWIG_IsNewObj(res6) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg6), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res7)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg7))); } else { int new_flags = SWIG_IsNewObj(res7) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg7), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res8)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg8))); } else { int new_flags = SWIG_IsNewObj(res8) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg8), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_positioner_struct_get_reciprocal(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_positioner_struct *arg1 = (cbf_positioner_struct *) 0 ; double arg2 ; double arg3 ; double arg4 ; double arg5 ; double arg6 ; double *arg7 = (double *) 0 ; double *arg8 = (double *) 0 ; double *arg9 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double val2 ; int ecode2 = 0 ; double val3 ; int ecode3 = 0 ; double val4 ; int ecode4 = 0 ; double val5 ; int ecode5 = 0 ; double val6 ; int ecode6 = 0 ; double temp7 ; int res7 = SWIG_TMPOBJ ; double temp8 ; int res8 = SWIG_TMPOBJ ; double temp9 ; int res9 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; arg7 = &temp7; arg8 = &temp8; arg9 = &temp9; if (!PyArg_ParseTuple(args,(char *)"OOOOOO:cbf_positioner_struct_get_reciprocal",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_positioner_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_positioner_struct_get_reciprocal" "', argument " "1"" of type '" "cbf_positioner_struct *""'"); } arg1 = (cbf_positioner_struct *)(argp1); ecode2 = SWIG_AsVal_double(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_positioner_struct_get_reciprocal" "', argument " "2"" of type '" "double""'"); } arg2 = (double)(val2); ecode3 = SWIG_AsVal_double(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_positioner_struct_get_reciprocal" "', argument " "3"" of type '" "double""'"); } arg3 = (double)(val3); ecode4 = SWIG_AsVal_double(obj3, &val4); if (!SWIG_IsOK(ecode4)) { SWIG_exception_fail(SWIG_ArgError(ecode4), "in method '" "cbf_positioner_struct_get_reciprocal" "', argument " "4"" of type '" "double""'"); } arg4 = (double)(val4); ecode5 = SWIG_AsVal_double(obj4, &val5); if (!SWIG_IsOK(ecode5)) { SWIG_exception_fail(SWIG_ArgError(ecode5), "in method '" "cbf_positioner_struct_get_reciprocal" "', argument " "5"" of type '" "double""'"); } arg5 = (double)(val5); ecode6 = SWIG_AsVal_double(obj5, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_positioner_struct_get_reciprocal" "', argument " "6"" of type '" "double""'"); } arg6 = (double)(val6); { error_status=0; cbf_positioner_struct_get_reciprocal(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res7)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg7))); } else { int new_flags = SWIG_IsNewObj(res7) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg7), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res8)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg8))); } else { int new_flags = SWIG_IsNewObj(res8) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg8), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res9)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg9))); } else { int new_flags = SWIG_IsNewObj(res9) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg9), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_positioner_struct_get_rotation_axis(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_positioner_struct *arg1 = (cbf_positioner_struct *) 0 ; double *arg2 = (double *) 0 ; double *arg3 = (double *) 0 ; double *arg4 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double temp2 ; int res2 = SWIG_TMPOBJ ; double temp3 ; int res3 = SWIG_TMPOBJ ; double temp4 ; int res4 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; if (!PyArg_ParseTuple(args,(char *)"O:cbf_positioner_struct_get_rotation_axis",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_positioner_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_positioner_struct_get_rotation_axis" "', argument " "1"" of type '" "cbf_positioner_struct *""'"); } arg1 = (cbf_positioner_struct *)(argp1); { error_status=0; cbf_positioner_struct_get_rotation_axis(arg1,arg2,arg3,arg4); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *cbf_positioner_struct_swigregister(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *obj; if (!PyArg_ParseTuple(args,(char*)"O:swigregister", &obj)) return NULL; SWIG_TypeNewClientData(SWIGTYPE_p_cbf_positioner_struct, SWIG_NewClientData(obj)); return SWIG_Py_Void(); } SWIGINTERN PyObject *_wrap_cbf_detector_struct_positioner_set(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; cbf_positioner arg2 ; void *argp1 = 0 ; int res1 = 0 ; void *argp2 ; int res2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_detector_struct_positioner_set",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_positioner_set" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); { res2 = SWIG_ConvertPtr(obj1, &argp2, SWIGTYPE_p_cbf_positioner, 0 ); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_detector_struct_positioner_set" "', argument " "2"" of type '" "cbf_positioner""'"); } if (!argp2) { SWIG_exception_fail(SWIG_ValueError, "invalid null reference " "in method '" "cbf_detector_struct_positioner_set" "', argument " "2"" of type '" "cbf_positioner""'"); } else { arg2 = *((cbf_positioner *)(argp2)); } } if (arg1) (arg1)->positioner = arg2; resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_positioner_get(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; cbf_positioner result; if (!PyArg_ParseTuple(args,(char *)"O:cbf_detector_struct_positioner_get",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_positioner_get" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); result = ((arg1)->positioner); resultobj = SWIG_NewPointerObj((cbf_positioner *)memcpy((cbf_positioner *)malloc(sizeof(cbf_positioner)),&result,sizeof(cbf_positioner)), SWIGTYPE_p_cbf_positioner, SWIG_POINTER_OWN | 0 ); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_displacement_set(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; double *arg2 ; void *argp1 = 0 ; int res1 = 0 ; double temp2[2] ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_detector_struct_displacement_set",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_displacement_set" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); { if (obj1 == Py_None) arg2 = NULL; else if (!convert_darray(obj1,temp2,2)) { return NULL; } arg2 = &temp2[0]; } { if (arg2) { size_t ii = 0; for (; ii < (size_t)2; ++ii) arg1->displacement[ii] = arg2[ii]; } else { SWIG_exception_fail(SWIG_ValueError, "invalid null reference " "in variable '""displacement""' of type '""double [2]""'"); } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_displacement_get(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; double *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_detector_struct_displacement_get",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_displacement_get" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); result = (double *)(double *) ((arg1)->displacement); resultobj = SWIG_NewPointerObj(SWIG_as_voidptr(result), SWIGTYPE_p_double, 0 | 0 ); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_increment_set(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; double *arg2 ; void *argp1 = 0 ; int res1 = 0 ; double temp2[2] ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_detector_struct_increment_set",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_increment_set" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); { if (obj1 == Py_None) arg2 = NULL; else if (!convert_darray(obj1,temp2,2)) { return NULL; } arg2 = &temp2[0]; } { if (arg2) { size_t ii = 0; for (; ii < (size_t)2; ++ii) arg1->increment[ii] = arg2[ii]; } else { SWIG_exception_fail(SWIG_ValueError, "invalid null reference " "in variable '""increment""' of type '""double [2]""'"); } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_increment_get(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; double *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_detector_struct_increment_get",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_increment_get" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); result = (double *)(double *) ((arg1)->increment); resultobj = SWIG_NewPointerObj(SWIG_as_voidptr(result), SWIGTYPE_p_double, 0 | 0 ); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_axes_set(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; size_t arg2 ; void *argp1 = 0 ; int res1 = 0 ; size_t val2 ; int ecode2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_detector_struct_axes_set",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_axes_set" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); ecode2 = SWIG_AsVal_size_t(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_detector_struct_axes_set" "', argument " "2"" of type '" "size_t""'"); } arg2 = (size_t)(val2); if (arg1) (arg1)->axes = arg2; resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_axes_get(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; size_t result; if (!PyArg_ParseTuple(args,(char *)"O:cbf_detector_struct_axes_get",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_axes_get" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); result = ((arg1)->axes); resultobj = SWIG_From_size_t((size_t)(result)); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_index_set(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; size_t *arg2 ; void *argp1 = 0 ; int res1 = 0 ; void *argp2 = 0 ; int res2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_detector_struct_index_set",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_index_set" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); res2 = SWIG_ConvertPtr(obj1, &argp2,SWIGTYPE_p_size_t, 0 | 0 ); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_detector_struct_index_set" "', argument " "2"" of type '" "size_t [2]""'"); } arg2 = (size_t *)(argp2); { if (arg2) { size_t ii = 0; for (; ii < (size_t)2; ++ii) arg1->index[ii] = arg2[ii]; } else { SWIG_exception_fail(SWIG_ValueError, "invalid null reference " "in variable '""index""' of type '""size_t [2]""'"); } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_index_get(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; size_t *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_detector_struct_index_get",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_index_get" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); result = (size_t *)(size_t *) ((arg1)->index); resultobj = SWIG_NewPointerObj(SWIG_as_voidptr(result), SWIGTYPE_p_size_t, 0 | 0 ); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_new_cbf_detector_struct(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *result = 0 ; if (!PyArg_ParseTuple(args,(char *)":new_cbf_detector_struct")) SWIG_fail; { error_status=0; result = (cbf_detector_struct *)new_cbf_detector_struct(); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_NewPointerObj(SWIG_as_voidptr(result), SWIGTYPE_p_cbf_detector_struct, SWIG_POINTER_NEW | 0 ); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_delete_cbf_detector_struct(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:delete_cbf_detector_struct",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, SWIG_POINTER_DISOWN | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "delete_cbf_detector_struct" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); { error_status=0; delete_cbf_detector_struct(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_set_reference_beam_center_fs(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; double *arg2 = (double *) 0 ; double *arg3 = (double *) 0 ; double *arg4 = (double *) 0 ; double *arg5 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; void *argp2 = 0 ; int res2 = 0 ; void *argp3 = 0 ; int res3 = 0 ; void *argp4 = 0 ; int res4 = 0 ; void *argp5 = 0 ; int res5 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOO:cbf_detector_struct_set_reference_beam_center_fs",&obj0,&obj1,&obj2,&obj3,&obj4)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_set_reference_beam_center_fs" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); res2 = SWIG_ConvertPtr(obj1, &argp2,SWIGTYPE_p_double, 0 | 0 ); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_detector_struct_set_reference_beam_center_fs" "', argument " "2"" of type '" "double *""'"); } arg2 = (double *)(argp2); res3 = SWIG_ConvertPtr(obj2, &argp3,SWIGTYPE_p_double, 0 | 0 ); if (!SWIG_IsOK(res3)) { SWIG_exception_fail(SWIG_ArgError(res3), "in method '" "cbf_detector_struct_set_reference_beam_center_fs" "', argument " "3"" of type '" "double *""'"); } arg3 = (double *)(argp3); res4 = SWIG_ConvertPtr(obj3, &argp4,SWIGTYPE_p_double, 0 | 0 ); if (!SWIG_IsOK(res4)) { SWIG_exception_fail(SWIG_ArgError(res4), "in method '" "cbf_detector_struct_set_reference_beam_center_fs" "', argument " "4"" of type '" "double *""'"); } arg4 = (double *)(argp4); res5 = SWIG_ConvertPtr(obj4, &argp5,SWIGTYPE_p_double, 0 | 0 ); if (!SWIG_IsOK(res5)) { SWIG_exception_fail(SWIG_ArgError(res5), "in method '" "cbf_detector_struct_set_reference_beam_center_fs" "', argument " "5"" of type '" "double *""'"); } arg5 = (double *)(argp5); { error_status=0; cbf_detector_struct_set_reference_beam_center_fs(arg1,arg2,arg3,arg4,arg5); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_get_pixel_coordinates_fs(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; double arg2 ; double arg3 ; double *arg4 = (double *) 0 ; double *arg5 = (double *) 0 ; double *arg6 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double val2 ; int ecode2 = 0 ; double val3 ; int ecode3 = 0 ; double temp4 ; int res4 = SWIG_TMPOBJ ; double temp5 ; int res5 = SWIG_TMPOBJ ; double temp6 ; int res6 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; arg4 = &temp4; arg5 = &temp5; arg6 = &temp6; if (!PyArg_ParseTuple(args,(char *)"OOO:cbf_detector_struct_get_pixel_coordinates_fs",&obj0,&obj1,&obj2)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_get_pixel_coordinates_fs" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); ecode2 = SWIG_AsVal_double(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_detector_struct_get_pixel_coordinates_fs" "', argument " "2"" of type '" "double""'"); } arg2 = (double)(val2); ecode3 = SWIG_AsVal_double(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_detector_struct_get_pixel_coordinates_fs" "', argument " "3"" of type '" "double""'"); } arg3 = (double)(val3); { error_status=0; cbf_detector_struct_get_pixel_coordinates_fs(arg1,arg2,arg3,arg4,arg5,arg6); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res6)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg6))); } else { int new_flags = SWIG_IsNewObj(res6) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg6), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_set_beam_center_fs(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; double *arg2 = (double *) 0 ; double *arg3 = (double *) 0 ; double *arg4 = (double *) 0 ; double *arg5 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; void *argp2 = 0 ; int res2 = 0 ; void *argp3 = 0 ; int res3 = 0 ; void *argp4 = 0 ; int res4 = 0 ; void *argp5 = 0 ; int res5 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOO:cbf_detector_struct_set_beam_center_fs",&obj0,&obj1,&obj2,&obj3,&obj4)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_set_beam_center_fs" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); res2 = SWIG_ConvertPtr(obj1, &argp2,SWIGTYPE_p_double, 0 | 0 ); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_detector_struct_set_beam_center_fs" "', argument " "2"" of type '" "double *""'"); } arg2 = (double *)(argp2); res3 = SWIG_ConvertPtr(obj2, &argp3,SWIGTYPE_p_double, 0 | 0 ); if (!SWIG_IsOK(res3)) { SWIG_exception_fail(SWIG_ArgError(res3), "in method '" "cbf_detector_struct_set_beam_center_fs" "', argument " "3"" of type '" "double *""'"); } arg3 = (double *)(argp3); res4 = SWIG_ConvertPtr(obj3, &argp4,SWIGTYPE_p_double, 0 | 0 ); if (!SWIG_IsOK(res4)) { SWIG_exception_fail(SWIG_ArgError(res4), "in method '" "cbf_detector_struct_set_beam_center_fs" "', argument " "4"" of type '" "double *""'"); } arg4 = (double *)(argp4); res5 = SWIG_ConvertPtr(obj4, &argp5,SWIGTYPE_p_double, 0 | 0 ); if (!SWIG_IsOK(res5)) { SWIG_exception_fail(SWIG_ArgError(res5), "in method '" "cbf_detector_struct_set_beam_center_fs" "', argument " "5"" of type '" "double *""'"); } arg5 = (double *)(argp5); { error_status=0; cbf_detector_struct_set_beam_center_fs(arg1,arg2,arg3,arg4,arg5); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_get_inferred_pixel_size(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; unsigned int arg2 ; double *arg3 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; double temp3 ; int res3 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; arg3 = &temp3; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_detector_struct_get_inferred_pixel_size",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_get_inferred_pixel_size" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_detector_struct_get_inferred_pixel_size" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); { error_status=0; cbf_detector_struct_get_inferred_pixel_size(arg1,arg2,arg3); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_get_pixel_area(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; double arg2 ; double arg3 ; double *arg4 = (double *) 0 ; double *arg5 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double val2 ; int ecode2 = 0 ; double val3 ; int ecode3 = 0 ; double temp4 ; int res4 = SWIG_TMPOBJ ; double temp5 ; int res5 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; arg4 = &temp4; arg5 = &temp5; if (!PyArg_ParseTuple(args,(char *)"OOO:cbf_detector_struct_get_pixel_area",&obj0,&obj1,&obj2)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_get_pixel_area" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); ecode2 = SWIG_AsVal_double(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_detector_struct_get_pixel_area" "', argument " "2"" of type '" "double""'"); } arg2 = (double)(val2); ecode3 = SWIG_AsVal_double(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_detector_struct_get_pixel_area" "', argument " "3"" of type '" "double""'"); } arg3 = (double)(val3); { error_status=0; cbf_detector_struct_get_pixel_area(arg1,arg2,arg3,arg4,arg5); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_get_pixel_normal_fs(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; double arg2 ; double arg3 ; double *arg4 = (double *) 0 ; double *arg5 = (double *) 0 ; double *arg6 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double val2 ; int ecode2 = 0 ; double val3 ; int ecode3 = 0 ; double temp4 ; int res4 = SWIG_TMPOBJ ; double temp5 ; int res5 = SWIG_TMPOBJ ; double temp6 ; int res6 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; arg4 = &temp4; arg5 = &temp5; arg6 = &temp6; if (!PyArg_ParseTuple(args,(char *)"OOO:cbf_detector_struct_get_pixel_normal_fs",&obj0,&obj1,&obj2)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_get_pixel_normal_fs" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); ecode2 = SWIG_AsVal_double(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_detector_struct_get_pixel_normal_fs" "', argument " "2"" of type '" "double""'"); } arg2 = (double)(val2); ecode3 = SWIG_AsVal_double(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_detector_struct_get_pixel_normal_fs" "', argument " "3"" of type '" "double""'"); } arg3 = (double)(val3); { error_status=0; cbf_detector_struct_get_pixel_normal_fs(arg1,arg2,arg3,arg4,arg5,arg6); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res6)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg6))); } else { int new_flags = SWIG_IsNewObj(res6) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg6), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_get_detector_axes(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; double *arg2 = (double *) 0 ; double *arg3 = (double *) 0 ; double *arg4 = (double *) 0 ; double *arg5 = (double *) 0 ; double *arg6 = (double *) 0 ; double *arg7 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double temp2 ; int res2 = SWIG_TMPOBJ ; double temp3 ; int res3 = SWIG_TMPOBJ ; double temp4 ; int res4 = SWIG_TMPOBJ ; double temp5 ; int res5 = SWIG_TMPOBJ ; double temp6 ; int res6 = SWIG_TMPOBJ ; double temp7 ; int res7 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; arg5 = &temp5; arg6 = &temp6; arg7 = &temp7; if (!PyArg_ParseTuple(args,(char *)"O:cbf_detector_struct_get_detector_axes",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_get_detector_axes" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); { error_status=0; cbf_detector_struct_get_detector_axes(arg1,arg2,arg3,arg4,arg5,arg6,arg7); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res6)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg6))); } else { int new_flags = SWIG_IsNewObj(res6) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg6), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res7)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg7))); } else { int new_flags = SWIG_IsNewObj(res7) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg7), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_set_reference_beam_center(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; double *arg2 = (double *) 0 ; double *arg3 = (double *) 0 ; double *arg4 = (double *) 0 ; double *arg5 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; void *argp2 = 0 ; int res2 = 0 ; void *argp3 = 0 ; int res3 = 0 ; void *argp4 = 0 ; int res4 = 0 ; void *argp5 = 0 ; int res5 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOO:cbf_detector_struct_set_reference_beam_center",&obj0,&obj1,&obj2,&obj3,&obj4)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_set_reference_beam_center" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); res2 = SWIG_ConvertPtr(obj1, &argp2,SWIGTYPE_p_double, 0 | 0 ); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_detector_struct_set_reference_beam_center" "', argument " "2"" of type '" "double *""'"); } arg2 = (double *)(argp2); res3 = SWIG_ConvertPtr(obj2, &argp3,SWIGTYPE_p_double, 0 | 0 ); if (!SWIG_IsOK(res3)) { SWIG_exception_fail(SWIG_ArgError(res3), "in method '" "cbf_detector_struct_set_reference_beam_center" "', argument " "3"" of type '" "double *""'"); } arg3 = (double *)(argp3); res4 = SWIG_ConvertPtr(obj3, &argp4,SWIGTYPE_p_double, 0 | 0 ); if (!SWIG_IsOK(res4)) { SWIG_exception_fail(SWIG_ArgError(res4), "in method '" "cbf_detector_struct_set_reference_beam_center" "', argument " "4"" of type '" "double *""'"); } arg4 = (double *)(argp4); res5 = SWIG_ConvertPtr(obj4, &argp5,SWIGTYPE_p_double, 0 | 0 ); if (!SWIG_IsOK(res5)) { SWIG_exception_fail(SWIG_ArgError(res5), "in method '" "cbf_detector_struct_set_reference_beam_center" "', argument " "5"" of type '" "double *""'"); } arg5 = (double *)(argp5); { error_status=0; cbf_detector_struct_set_reference_beam_center(arg1,arg2,arg3,arg4,arg5); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_get_detector_axis_slow(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; double *arg2 = (double *) 0 ; double *arg3 = (double *) 0 ; double *arg4 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double temp2 ; int res2 = SWIG_TMPOBJ ; double temp3 ; int res3 = SWIG_TMPOBJ ; double temp4 ; int res4 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; if (!PyArg_ParseTuple(args,(char *)"O:cbf_detector_struct_get_detector_axis_slow",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_get_detector_axis_slow" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); { error_status=0; cbf_detector_struct_get_detector_axis_slow(arg1,arg2,arg3,arg4); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_get_detector_distance(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; double *arg2 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double temp2 ; int res2 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; if (!PyArg_ParseTuple(args,(char *)"O:cbf_detector_struct_get_detector_distance",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_get_detector_distance" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); { error_status=0; cbf_detector_struct_get_detector_distance(arg1,arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_get_inferred_pixel_size_fs(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; unsigned int arg2 ; double *arg3 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; double temp3 ; int res3 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; arg3 = &temp3; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_detector_struct_get_inferred_pixel_size_fs",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_get_inferred_pixel_size_fs" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_detector_struct_get_inferred_pixel_size_fs" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); { error_status=0; cbf_detector_struct_get_inferred_pixel_size_fs(arg1,arg2,arg3); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_get_detector_normal(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; double *arg2 = (double *) 0 ; double *arg3 = (double *) 0 ; double *arg4 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double temp2 ; int res2 = SWIG_TMPOBJ ; double temp3 ; int res3 = SWIG_TMPOBJ ; double temp4 ; int res4 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; if (!PyArg_ParseTuple(args,(char *)"O:cbf_detector_struct_get_detector_normal",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_get_detector_normal" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); { error_status=0; cbf_detector_struct_get_detector_normal(arg1,arg2,arg3,arg4); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_get_detector_axis_fast(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; double *arg2 = (double *) 0 ; double *arg3 = (double *) 0 ; double *arg4 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double temp2 ; int res2 = SWIG_TMPOBJ ; double temp3 ; int res3 = SWIG_TMPOBJ ; double temp4 ; int res4 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; if (!PyArg_ParseTuple(args,(char *)"O:cbf_detector_struct_get_detector_axis_fast",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_get_detector_axis_fast" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); { error_status=0; cbf_detector_struct_get_detector_axis_fast(arg1,arg2,arg3,arg4); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_get_detector_axes_fs(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; double *arg2 = (double *) 0 ; double *arg3 = (double *) 0 ; double *arg4 = (double *) 0 ; double *arg5 = (double *) 0 ; double *arg6 = (double *) 0 ; double *arg7 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double temp2 ; int res2 = SWIG_TMPOBJ ; double temp3 ; int res3 = SWIG_TMPOBJ ; double temp4 ; int res4 = SWIG_TMPOBJ ; double temp5 ; int res5 = SWIG_TMPOBJ ; double temp6 ; int res6 = SWIG_TMPOBJ ; double temp7 ; int res7 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; arg5 = &temp5; arg6 = &temp6; arg7 = &temp7; if (!PyArg_ParseTuple(args,(char *)"O:cbf_detector_struct_get_detector_axes_fs",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_get_detector_axes_fs" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); { error_status=0; cbf_detector_struct_get_detector_axes_fs(arg1,arg2,arg3,arg4,arg5,arg6,arg7); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res6)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg6))); } else { int new_flags = SWIG_IsNewObj(res6) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg6), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res7)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg7))); } else { int new_flags = SWIG_IsNewObj(res7) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg7), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_get_detector_axes_sf(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; double *arg2 = (double *) 0 ; double *arg3 = (double *) 0 ; double *arg4 = (double *) 0 ; double *arg5 = (double *) 0 ; double *arg6 = (double *) 0 ; double *arg7 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double temp2 ; int res2 = SWIG_TMPOBJ ; double temp3 ; int res3 = SWIG_TMPOBJ ; double temp4 ; int res4 = SWIG_TMPOBJ ; double temp5 ; int res5 = SWIG_TMPOBJ ; double temp6 ; int res6 = SWIG_TMPOBJ ; double temp7 ; int res7 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; arg5 = &temp5; arg6 = &temp6; arg7 = &temp7; if (!PyArg_ParseTuple(args,(char *)"O:cbf_detector_struct_get_detector_axes_sf",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_get_detector_axes_sf" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); { error_status=0; cbf_detector_struct_get_detector_axes_sf(arg1,arg2,arg3,arg4,arg5,arg6,arg7); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res6)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg6))); } else { int new_flags = SWIG_IsNewObj(res6) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg6), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res7)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg7))); } else { int new_flags = SWIG_IsNewObj(res7) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg7), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_get_pixel_coordinates_sf(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; double arg2 ; double arg3 ; double *arg4 = (double *) 0 ; double *arg5 = (double *) 0 ; double *arg6 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double val2 ; int ecode2 = 0 ; double val3 ; int ecode3 = 0 ; double temp4 ; int res4 = SWIG_TMPOBJ ; double temp5 ; int res5 = SWIG_TMPOBJ ; double temp6 ; int res6 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; arg4 = &temp4; arg5 = &temp5; arg6 = &temp6; if (!PyArg_ParseTuple(args,(char *)"OOO:cbf_detector_struct_get_pixel_coordinates_sf",&obj0,&obj1,&obj2)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_get_pixel_coordinates_sf" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); ecode2 = SWIG_AsVal_double(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_detector_struct_get_pixel_coordinates_sf" "', argument " "2"" of type '" "double""'"); } arg2 = (double)(val2); ecode3 = SWIG_AsVal_double(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_detector_struct_get_pixel_coordinates_sf" "', argument " "3"" of type '" "double""'"); } arg3 = (double)(val3); { error_status=0; cbf_detector_struct_get_pixel_coordinates_sf(arg1,arg2,arg3,arg4,arg5,arg6); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res6)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg6))); } else { int new_flags = SWIG_IsNewObj(res6) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg6), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_set_beam_center(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; double *arg2 = (double *) 0 ; double *arg3 = (double *) 0 ; double *arg4 = (double *) 0 ; double *arg5 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; void *argp2 = 0 ; int res2 = 0 ; void *argp3 = 0 ; int res3 = 0 ; void *argp4 = 0 ; int res4 = 0 ; void *argp5 = 0 ; int res5 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOO:cbf_detector_struct_set_beam_center",&obj0,&obj1,&obj2,&obj3,&obj4)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_set_beam_center" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); res2 = SWIG_ConvertPtr(obj1, &argp2,SWIGTYPE_p_double, 0 | 0 ); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_detector_struct_set_beam_center" "', argument " "2"" of type '" "double *""'"); } arg2 = (double *)(argp2); res3 = SWIG_ConvertPtr(obj2, &argp3,SWIGTYPE_p_double, 0 | 0 ); if (!SWIG_IsOK(res3)) { SWIG_exception_fail(SWIG_ArgError(res3), "in method '" "cbf_detector_struct_set_beam_center" "', argument " "3"" of type '" "double *""'"); } arg3 = (double *)(argp3); res4 = SWIG_ConvertPtr(obj3, &argp4,SWIGTYPE_p_double, 0 | 0 ); if (!SWIG_IsOK(res4)) { SWIG_exception_fail(SWIG_ArgError(res4), "in method '" "cbf_detector_struct_set_beam_center" "', argument " "4"" of type '" "double *""'"); } arg4 = (double *)(argp4); res5 = SWIG_ConvertPtr(obj4, &argp5,SWIGTYPE_p_double, 0 | 0 ); if (!SWIG_IsOK(res5)) { SWIG_exception_fail(SWIG_ArgError(res5), "in method '" "cbf_detector_struct_set_beam_center" "', argument " "5"" of type '" "double *""'"); } arg5 = (double *)(argp5); { error_status=0; cbf_detector_struct_set_beam_center(arg1,arg2,arg3,arg4,arg5); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_get_pixel_area_fs(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; double arg2 ; double arg3 ; double *arg4 = (double *) 0 ; double *arg5 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double val2 ; int ecode2 = 0 ; double val3 ; int ecode3 = 0 ; double temp4 ; int res4 = SWIG_TMPOBJ ; double temp5 ; int res5 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; arg4 = &temp4; arg5 = &temp5; if (!PyArg_ParseTuple(args,(char *)"OOO:cbf_detector_struct_get_pixel_area_fs",&obj0,&obj1,&obj2)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_get_pixel_area_fs" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); ecode2 = SWIG_AsVal_double(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_detector_struct_get_pixel_area_fs" "', argument " "2"" of type '" "double""'"); } arg2 = (double)(val2); ecode3 = SWIG_AsVal_double(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_detector_struct_get_pixel_area_fs" "', argument " "3"" of type '" "double""'"); } arg3 = (double)(val3); { error_status=0; cbf_detector_struct_get_pixel_area_fs(arg1,arg2,arg3,arg4,arg5); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_get_beam_center_fs(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; double *arg2 = (double *) 0 ; double *arg3 = (double *) 0 ; double *arg4 = (double *) 0 ; double *arg5 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double temp2 ; int res2 = SWIG_TMPOBJ ; double temp3 ; int res3 = SWIG_TMPOBJ ; double temp4 ; int res4 = SWIG_TMPOBJ ; double temp5 ; int res5 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; arg5 = &temp5; if (!PyArg_ParseTuple(args,(char *)"O:cbf_detector_struct_get_beam_center_fs",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_get_beam_center_fs" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); { error_status=0; cbf_detector_struct_get_beam_center_fs(arg1,arg2,arg3,arg4,arg5); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_get_inferred_pixel_size_sf(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; unsigned int arg2 ; double *arg3 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; double temp3 ; int res3 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; arg3 = &temp3; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_detector_struct_get_inferred_pixel_size_sf",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_get_inferred_pixel_size_sf" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_detector_struct_get_inferred_pixel_size_sf" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); { error_status=0; cbf_detector_struct_get_inferred_pixel_size_sf(arg1,arg2,arg3); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_get_pixel_coordinates(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; double arg2 ; double arg3 ; double *arg4 = (double *) 0 ; double *arg5 = (double *) 0 ; double *arg6 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double val2 ; int ecode2 = 0 ; double val3 ; int ecode3 = 0 ; double temp4 ; int res4 = SWIG_TMPOBJ ; double temp5 ; int res5 = SWIG_TMPOBJ ; double temp6 ; int res6 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; arg4 = &temp4; arg5 = &temp5; arg6 = &temp6; if (!PyArg_ParseTuple(args,(char *)"OOO:cbf_detector_struct_get_pixel_coordinates",&obj0,&obj1,&obj2)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_get_pixel_coordinates" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); ecode2 = SWIG_AsVal_double(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_detector_struct_get_pixel_coordinates" "', argument " "2"" of type '" "double""'"); } arg2 = (double)(val2); ecode3 = SWIG_AsVal_double(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_detector_struct_get_pixel_coordinates" "', argument " "3"" of type '" "double""'"); } arg3 = (double)(val3); { error_status=0; cbf_detector_struct_get_pixel_coordinates(arg1,arg2,arg3,arg4,arg5,arg6); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res6)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg6))); } else { int new_flags = SWIG_IsNewObj(res6) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg6), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_get_beam_center_sf(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; double *arg2 = (double *) 0 ; double *arg3 = (double *) 0 ; double *arg4 = (double *) 0 ; double *arg5 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double temp2 ; int res2 = SWIG_TMPOBJ ; double temp3 ; int res3 = SWIG_TMPOBJ ; double temp4 ; int res4 = SWIG_TMPOBJ ; double temp5 ; int res5 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; arg5 = &temp5; if (!PyArg_ParseTuple(args,(char *)"O:cbf_detector_struct_get_beam_center_sf",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_get_beam_center_sf" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); { error_status=0; cbf_detector_struct_get_beam_center_sf(arg1,arg2,arg3,arg4,arg5); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_get_pixel_area_sf(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; double arg2 ; double arg3 ; double *arg4 = (double *) 0 ; double *arg5 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double val2 ; int ecode2 = 0 ; double val3 ; int ecode3 = 0 ; double temp4 ; int res4 = SWIG_TMPOBJ ; double temp5 ; int res5 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; arg4 = &temp4; arg5 = &temp5; if (!PyArg_ParseTuple(args,(char *)"OOO:cbf_detector_struct_get_pixel_area_sf",&obj0,&obj1,&obj2)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_get_pixel_area_sf" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); ecode2 = SWIG_AsVal_double(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_detector_struct_get_pixel_area_sf" "', argument " "2"" of type '" "double""'"); } arg2 = (double)(val2); ecode3 = SWIG_AsVal_double(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_detector_struct_get_pixel_area_sf" "', argument " "3"" of type '" "double""'"); } arg3 = (double)(val3); { error_status=0; cbf_detector_struct_get_pixel_area_sf(arg1,arg2,arg3,arg4,arg5); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_get_beam_center(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; double *arg2 = (double *) 0 ; double *arg3 = (double *) 0 ; double *arg4 = (double *) 0 ; double *arg5 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double temp2 ; int res2 = SWIG_TMPOBJ ; double temp3 ; int res3 = SWIG_TMPOBJ ; double temp4 ; int res4 = SWIG_TMPOBJ ; double temp5 ; int res5 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; arg5 = &temp5; if (!PyArg_ParseTuple(args,(char *)"O:cbf_detector_struct_get_beam_center",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_get_beam_center" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); { error_status=0; cbf_detector_struct_get_beam_center(arg1,arg2,arg3,arg4,arg5); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_set_reference_beam_center_sf(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; double *arg2 = (double *) 0 ; double *arg3 = (double *) 0 ; double *arg4 = (double *) 0 ; double *arg5 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double temp2 ; int res2 = SWIG_TMPOBJ ; double temp3 ; int res3 = SWIG_TMPOBJ ; double temp4 ; int res4 = SWIG_TMPOBJ ; double temp5 ; int res5 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; arg5 = &temp5; if (!PyArg_ParseTuple(args,(char *)"O:cbf_detector_struct_set_reference_beam_center_sf",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_set_reference_beam_center_sf" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); { error_status=0; cbf_detector_struct_set_reference_beam_center_sf(arg1,arg2,arg3,arg4,arg5); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_set_beam_center_sf(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; double *arg2 = (double *) 0 ; double *arg3 = (double *) 0 ; double *arg4 = (double *) 0 ; double *arg5 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double temp2 ; int res2 = SWIG_TMPOBJ ; double temp3 ; int res3 = SWIG_TMPOBJ ; double temp4 ; int res4 = SWIG_TMPOBJ ; double temp5 ; int res5 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; arg5 = &temp5; if (!PyArg_ParseTuple(args,(char *)"O:cbf_detector_struct_set_beam_center_sf",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_set_beam_center_sf" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); { error_status=0; cbf_detector_struct_set_beam_center_sf(arg1,arg2,arg3,arg4,arg5); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_detector_struct_get_pixel_normal(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_detector_struct *arg1 = (cbf_detector_struct *) 0 ; double arg2 ; double arg3 ; double *arg4 = (double *) 0 ; double *arg5 = (double *) 0 ; double *arg6 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double val2 ; int ecode2 = 0 ; double val3 ; int ecode3 = 0 ; double temp4 ; int res4 = SWIG_TMPOBJ ; double temp5 ; int res5 = SWIG_TMPOBJ ; double temp6 ; int res6 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; arg4 = &temp4; arg5 = &temp5; arg6 = &temp6; if (!PyArg_ParseTuple(args,(char *)"OOO:cbf_detector_struct_get_pixel_normal",&obj0,&obj1,&obj2)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_detector_struct_get_pixel_normal" "', argument " "1"" of type '" "cbf_detector_struct *""'"); } arg1 = (cbf_detector_struct *)(argp1); ecode2 = SWIG_AsVal_double(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_detector_struct_get_pixel_normal" "', argument " "2"" of type '" "double""'"); } arg2 = (double)(val2); ecode3 = SWIG_AsVal_double(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_detector_struct_get_pixel_normal" "', argument " "3"" of type '" "double""'"); } arg3 = (double)(val3); { error_status=0; cbf_detector_struct_get_pixel_normal(arg1,arg2,arg3,arg4,arg5,arg6); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res6)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg6))); } else { int new_flags = SWIG_IsNewObj(res6) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg6), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *cbf_detector_struct_swigregister(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *obj; if (!PyArg_ParseTuple(args,(char*)"O:swigregister", &obj)) return NULL; SWIG_TypeNewClientData(SWIGTYPE_p_cbf_detector_struct, SWIG_NewClientData(obj)); return SWIG_Py_Void(); } SWIGINTERN PyObject *_wrap_cbf_handle_struct_node_set(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; cbf_node *arg2 = (cbf_node *) 0 ; void *argp1 = 0 ; int res1 = 0 ; void *argp2 = 0 ; int res2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_node_set",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_node_set" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_ConvertPtr(obj1, &argp2,SWIGTYPE_p_cbf_node, SWIG_POINTER_DISOWN | 0 ); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_node_set" "', argument " "2"" of type '" "cbf_node *""'"); } arg2 = (cbf_node *)(argp2); if (arg1) (arg1)->node = arg2; resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_node_get(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; cbf_node *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_node_get",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_node_get" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); result = (cbf_node *) ((arg1)->node); resultobj = SWIG_NewPointerObj(SWIG_as_voidptr(result), SWIGTYPE_p_cbf_node, 0 | 0 ); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_row_set(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int arg2 ; void *argp1 = 0 ; int res1 = 0 ; int val2 ; int ecode2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_row_set",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_row_set" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_row_set" "', argument " "2"" of type '" "int""'"); } arg2 = (int)(val2); if (arg1) (arg1)->row = arg2; resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_row_get(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; int result; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_row_get",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_row_get" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); result = (int) ((arg1)->row); resultobj = SWIG_From_int((int)(result)); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_search_row_set(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int arg2 ; void *argp1 = 0 ; int res1 = 0 ; int val2 ; int ecode2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_search_row_set",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_search_row_set" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_search_row_set" "', argument " "2"" of type '" "int""'"); } arg2 = (int)(val2); if (arg1) (arg1)->search_row = arg2; resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_search_row_get(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; int result; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_search_row_get",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_search_row_get" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); result = (int) ((arg1)->search_row); resultobj = SWIG_From_int((int)(result)); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_new_cbf_handle_struct(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *result = 0 ; if (!PyArg_ParseTuple(args,(char *)":new_cbf_handle_struct")) SWIG_fail; { error_status=0; result = (cbf_handle_struct *)new_cbf_handle_struct(); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_NewPointerObj(SWIG_as_voidptr(result), SWIGTYPE_p_cbf_handle_struct, SWIG_POINTER_NEW | 0 ); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_delete_cbf_handle_struct(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:delete_cbf_handle_struct",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, SWIG_POINTER_DISOWN | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "delete_cbf_handle_struct" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; delete_cbf_handle_struct(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_select_datablock(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_select_datablock",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_select_datablock" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_select_datablock" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); { error_status=0; cbf_handle_struct_select_datablock(arg1,arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_force_new_datablock(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_force_new_datablock",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_force_new_datablock" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_force_new_datablock" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; cbf_handle_struct_force_new_datablock(arg1,(char const *)arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_3d_image_fs_as_string(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int arg2 ; char **arg3 = (char **) 0 ; int *arg4 = (int *) 0 ; int arg5 ; int arg6 ; int arg7 ; int arg8 ; int arg9 ; void *argp1 = 0 ; int res1 = 0 ; int val2 ; int ecode2 = 0 ; char *temp3 = 0 ; int tempn3 ; int val5 ; int ecode5 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int val8 ; int ecode8 = 0 ; int val9 ; int ecode9 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; PyObject * obj6 = 0 ; arg3 = &temp3; arg4 = &tempn3; if (!PyArg_ParseTuple(args,(char *)"OOOOOOO:cbf_handle_struct_get_3d_image_fs_as_string",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5,&obj6)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_3d_image_fs_as_string" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_get_3d_image_fs_as_string" "', argument " "2"" of type '" "int""'"); } arg2 = (int)(val2); ecode5 = SWIG_AsVal_int(obj2, &val5); if (!SWIG_IsOK(ecode5)) { SWIG_exception_fail(SWIG_ArgError(ecode5), "in method '" "cbf_handle_struct_get_3d_image_fs_as_string" "', argument " "5"" of type '" "int""'"); } arg5 = (int)(val5); ecode6 = SWIG_AsVal_int(obj3, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_get_3d_image_fs_as_string" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj4, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_get_3d_image_fs_as_string" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); ecode8 = SWIG_AsVal_int(obj5, &val8); if (!SWIG_IsOK(ecode8)) { SWIG_exception_fail(SWIG_ArgError(ecode8), "in method '" "cbf_handle_struct_get_3d_image_fs_as_string" "', argument " "8"" of type '" "int""'"); } arg8 = (int)(val8); ecode9 = SWIG_AsVal_int(obj6, &val9); if (!SWIG_IsOK(ecode9)) { SWIG_exception_fail(SWIG_ArgError(ecode9), "in method '" "cbf_handle_struct_get_3d_image_fs_as_string" "', argument " "9"" of type '" "int""'"); } arg9 = (int)(val9); { error_status=0; cbf_handle_struct_get_3d_image_fs_as_string(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (*arg3) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_FromCharPtrAndSize(*arg3,*arg4)); free(*arg3); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_reset_datablocks(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_reset_datablocks",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_reset_datablocks" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_reset_datablocks(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_tag_category(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; char *arg3 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; int res3 ; char *buf3 = 0 ; int alloc3 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOO:cbf_handle_struct_set_tag_category",&obj0,&obj1,&obj2)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_tag_category" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_set_tag_category" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); res3 = SWIG_AsCharPtrAndSize(obj2, &buf3, NULL, &alloc3); if (!SWIG_IsOK(res3)) { SWIG_exception_fail(SWIG_ArgError(res3), "in method '" "cbf_handle_struct_set_tag_category" "', argument " "3"" of type '" "char const *""'"); } arg3 = (char *)(buf3); { error_status=0; cbf_handle_struct_set_tag_category(arg1,(char const *)arg2,(char const *)arg3); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); if (alloc3 == SWIG_NEWOBJ) free((char*)buf3); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); if (alloc3 == SWIG_NEWOBJ) free((char*)buf3); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_require_tag_root(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; char *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_require_tag_root",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_require_tag_root" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_require_tag_root" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; result = (char *)cbf_handle_struct_require_tag_root(arg1,(char const *)arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_FromCharPtr((const char *)result); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_row_number(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; unsigned int result; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_row_number",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_row_number" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; result = (unsigned int)cbf_handle_struct_row_number(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_From_unsigned_SS_int((unsigned int)(result)); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_image(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; unsigned int arg3 ; char *arg4 = (char *) 0 ; int arg5 ; int arg6 ; int arg7 ; int arg8 ; int arg9 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; unsigned int val3 ; int ecode3 = 0 ; int res4 ; char *buf4 = 0 ; size_t size4 = 0 ; int alloc4 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int val8 ; int ecode8 = 0 ; int val9 ; int ecode9 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; PyObject * obj6 = 0 ; PyObject * obj7 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOOOOO:cbf_handle_struct_set_image",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5,&obj6,&obj7)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_image" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_image" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_unsigned_SS_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_image" "', argument " "3"" of type '" "unsigned int""'"); } arg3 = (unsigned int)(val3); res4 = SWIG_AsCharPtrAndSize(obj3, &buf4, &size4, &alloc4); if (!SWIG_IsOK(res4)) { SWIG_exception_fail(SWIG_ArgError(res4), "in method '" "cbf_handle_struct_set_image" "', argument " "4"" of type '" "char *""'"); } arg4 = (char *)(buf4); arg5 = (int)(size4 - 1); ecode6 = SWIG_AsVal_int(obj4, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_set_image" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj5, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_set_image" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); ecode8 = SWIG_AsVal_int(obj6, &val8); if (!SWIG_IsOK(ecode8)) { SWIG_exception_fail(SWIG_ArgError(ecode8), "in method '" "cbf_handle_struct_set_image" "', argument " "8"" of type '" "int""'"); } arg8 = (int)(val8); ecode9 = SWIG_AsVal_int(obj7, &val9); if (!SWIG_IsOK(ecode9)) { SWIG_exception_fail(SWIG_ArgError(ecode9), "in method '" "cbf_handle_struct_set_image" "', argument " "9"" of type '" "int""'"); } arg9 = (int)(val9); { error_status=0; cbf_handle_struct_set_image(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return resultobj; fail: if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_bin_sizes(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int arg2 ; double arg3 ; double arg4 ; void *argp1 = 0 ; int res1 = 0 ; int val2 ; int ecode2 = 0 ; double val3 ; int ecode3 = 0 ; double val4 ; int ecode4 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOO:cbf_handle_struct_set_bin_sizes",&obj0,&obj1,&obj2,&obj3)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_bin_sizes" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_bin_sizes" "', argument " "2"" of type '" "int""'"); } arg2 = (int)(val2); ecode3 = SWIG_AsVal_double(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_bin_sizes" "', argument " "3"" of type '" "double""'"); } arg3 = (double)(val3); ecode4 = SWIG_AsVal_double(obj3, &val4); if (!SWIG_IsOK(ecode4)) { SWIG_exception_fail(SWIG_ArgError(ecode4), "in method '" "cbf_handle_struct_set_bin_sizes" "', argument " "4"" of type '" "double""'"); } arg4 = (double)(val4); { error_status=0; cbf_handle_struct_set_bin_sizes(arg1,arg2,arg3,arg4); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_new_row(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_new_row",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_new_row" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_new_row(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_rewind_saveframe(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_rewind_saveframe",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_rewind_saveframe" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_rewind_saveframe(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_realarrayparameters(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int *arg2 = (int *) 0 ; int *arg3 = (int *) 0 ; int *arg4 = (int *) 0 ; int *arg5 = (int *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int temp2 ; int res2 = SWIG_TMPOBJ ; int temp3 ; int res3 = SWIG_TMPOBJ ; int temp4 ; int res4 = SWIG_TMPOBJ ; int temp5 ; int res5 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; arg5 = &temp5; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_realarrayparameters",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_realarrayparameters" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_get_realarrayparameters(arg1,arg2,arg3,arg4,arg5); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_int, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_pixel_size_sf(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; unsigned int arg3 ; double *arg4 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; unsigned int val3 ; int ecode3 = 0 ; double temp4 ; int res4 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; arg4 = &temp4; if (!PyArg_ParseTuple(args,(char *)"OOO:cbf_handle_struct_get_pixel_size_sf",&obj0,&obj1,&obj2)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_pixel_size_sf" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_get_pixel_size_sf" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_unsigned_SS_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_get_pixel_size_sf" "', argument " "3"" of type '" "unsigned int""'"); } arg3 = (unsigned int)(val3); { error_status=0; cbf_handle_struct_get_pixel_size_sf(arg1,arg2,arg3,arg4); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_force_new_category(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_force_new_category",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_force_new_category" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_force_new_category" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; cbf_handle_struct_force_new_category(arg1,(char const *)arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_force_new_saveframe(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_force_new_saveframe",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_force_new_saveframe" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_force_new_saveframe" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; cbf_handle_struct_force_new_saveframe(arg1,(char const *)arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_count_datablocks(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; unsigned int result; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_count_datablocks",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_count_datablocks" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; result = (unsigned int)cbf_handle_struct_count_datablocks(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_From_unsigned_SS_int((unsigned int)(result)); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_find_row(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_find_row",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_find_row" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_find_row" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; cbf_handle_struct_find_row(arg1,(char const *)arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_select_column(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_select_column",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_select_column" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_select_column" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); { error_status=0; cbf_handle_struct_select_column(arg1,arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_construct_detector(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; cbf_detector result; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_construct_detector",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_construct_detector" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_construct_detector" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); { error_status=0; result = (cbf_detector)cbf_handle_struct_construct_detector(arg1,arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_NewPointerObj(SWIG_as_voidptr(result), SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_rewind_column(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_rewind_column",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_rewind_column" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_rewind_column(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_require_column_doublevalue(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; double *arg3 = (double *) 0 ; double arg4 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; double temp3 ; int res3 = SWIG_TMPOBJ ; double val4 ; int ecode4 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; arg3 = &temp3; if (!PyArg_ParseTuple(args,(char *)"OOO:cbf_handle_struct_require_column_doublevalue",&obj0,&obj1,&obj2)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_require_column_doublevalue" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_require_column_doublevalue" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); ecode4 = SWIG_AsVal_double(obj2, &val4); if (!SWIG_IsOK(ecode4)) { SWIG_exception_fail(SWIG_ArgError(ecode4), "in method '" "cbf_handle_struct_require_column_doublevalue" "', argument " "4"" of type '" "double""'"); } arg4 = (double)(val4); { error_status=0; cbf_handle_struct_require_column_doublevalue(arg1,(char const *)arg2,arg3,arg4); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_datestamp(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int *arg2 = (int *) 0 ; int *arg3 = (int *) 0 ; int *arg4 = (int *) 0 ; int *arg5 = (int *) 0 ; int *arg6 = (int *) 0 ; double *arg7 = (double *) 0 ; int *arg8 = (int *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int temp2 ; int res2 = SWIG_TMPOBJ ; int temp3 ; int res3 = SWIG_TMPOBJ ; int temp4 ; int res4 = SWIG_TMPOBJ ; int temp5 ; int res5 = SWIG_TMPOBJ ; int temp6 ; int res6 = SWIG_TMPOBJ ; double temp7 ; int res7 = SWIG_TMPOBJ ; int temp8 ; int res8 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; arg5 = &temp5; arg6 = &temp6; arg7 = &temp7; arg8 = &temp8; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_datestamp",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_datestamp" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_get_datestamp(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res6)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg6))); } else { int new_flags = SWIG_IsNewObj(res6) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg6), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res7)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg7))); } else { int new_flags = SWIG_IsNewObj(res7) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg7), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res8)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg8))); } else { int new_flags = SWIG_IsNewObj(res8) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg8), SWIGTYPE_p_int, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_integervalue(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; int result; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_integervalue",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_integervalue" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; result = (int)cbf_handle_struct_get_integervalue(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_From_int((int)(result)); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_crystal_id(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; char *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_crystal_id",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_crystal_id" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; result = (char *)cbf_handle_struct_get_crystal_id(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_FromCharPtr((const char *)result); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_doublevalue(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; double result; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_doublevalue",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_doublevalue" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; result = (double)cbf_handle_struct_get_doublevalue(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_From_double((double)(result)); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_unit_cell(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; double *arg2 = (double *) 0 ; double *arg3 = (double *) 0 ; double *arg4 = (double *) 0 ; double *arg5 = (double *) 0 ; double *arg6 = (double *) 0 ; double *arg7 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double temp2 ; int res2 = SWIG_TMPOBJ ; double temp3 ; int res3 = SWIG_TMPOBJ ; double temp4 ; int res4 = SWIG_TMPOBJ ; double temp5 ; int res5 = SWIG_TMPOBJ ; double temp6 ; int res6 = SWIG_TMPOBJ ; double temp7 ; int res7 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; arg5 = &temp5; arg6 = &temp6; arg7 = &temp7; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_unit_cell",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_unit_cell" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_get_unit_cell(arg1,arg2,arg3,arg4,arg5,arg6,arg7); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res6)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg6))); } else { int new_flags = SWIG_IsNewObj(res6) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg6), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res7)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg7))); } else { int new_flags = SWIG_IsNewObj(res7) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg7), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_unit_cell_esd(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; double *arg2 = (double *) 0 ; double *arg3 = (double *) 0 ; double *arg4 = (double *) 0 ; double *arg5 = (double *) 0 ; double *arg6 = (double *) 0 ; double *arg7 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double temp2 ; int res2 = SWIG_TMPOBJ ; double temp3 ; int res3 = SWIG_TMPOBJ ; double temp4 ; int res4 = SWIG_TMPOBJ ; double temp5 ; int res5 = SWIG_TMPOBJ ; double temp6 ; int res6 = SWIG_TMPOBJ ; double temp7 ; int res7 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; arg5 = &temp5; arg6 = &temp6; arg7 = &temp7; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_unit_cell_esd",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_unit_cell_esd" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_get_unit_cell_esd(arg1,arg2,arg3,arg4,arg5,arg6,arg7); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res6)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg6))); } else { int new_flags = SWIG_IsNewObj(res6) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg6), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res7)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg7))); } else { int new_flags = SWIG_IsNewObj(res7) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg7), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_remove_column(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_remove_column",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_remove_column" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_remove_column(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_rewind_blockitem(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; CBF_NODETYPE result; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_rewind_blockitem",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_rewind_blockitem" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; result = (CBF_NODETYPE)cbf_handle_struct_rewind_blockitem(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_From_int((int)(result)); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_value(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; char *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_value",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_value" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; result = (char *)cbf_handle_struct_get_value(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_FromCharPtr((const char *)result); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_count_categories(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; unsigned int result; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_count_categories",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_count_categories" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; result = (unsigned int)cbf_handle_struct_count_categories(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_From_unsigned_SS_int((unsigned int)(result)); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_read_widefile(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; int arg3 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; int val3 ; int ecode3 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOO:cbf_handle_struct_read_widefile",&obj0,&obj1,&obj2)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_read_widefile" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_read_widefile" "', argument " "2"" of type '" "char *""'"); } arg2 = (char *)(buf2); ecode3 = SWIG_AsVal_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_read_widefile" "', argument " "3"" of type '" "int""'"); } arg3 = (int)(val3); { error_status=0; cbf_handle_struct_read_widefile(arg1,arg2,arg3); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_wavelength(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; double arg2 ; void *argp1 = 0 ; int res1 = 0 ; double val2 ; int ecode2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_set_wavelength",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_wavelength" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_double(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_wavelength" "', argument " "2"" of type '" "double""'"); } arg2 = (double)(val2); { error_status=0; cbf_handle_struct_set_wavelength(arg1,arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_pixel_size_sf(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; unsigned int arg3 ; double arg4 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; unsigned int val3 ; int ecode3 = 0 ; double val4 ; int ecode4 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOO:cbf_handle_struct_set_pixel_size_sf",&obj0,&obj1,&obj2,&obj3)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_pixel_size_sf" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_pixel_size_sf" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_unsigned_SS_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_pixel_size_sf" "', argument " "3"" of type '" "unsigned int""'"); } arg3 = (unsigned int)(val3); ecode4 = SWIG_AsVal_double(obj3, &val4); if (!SWIG_IsOK(ecode4)) { SWIG_exception_fail(SWIG_ArgError(ecode4), "in method '" "cbf_handle_struct_set_pixel_size_sf" "', argument " "4"" of type '" "double""'"); } arg4 = (double)(val4); { error_status=0; cbf_handle_struct_set_pixel_size_sf(arg1,arg2,arg3,arg4); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_diffrn_id(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; char *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_diffrn_id",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_diffrn_id" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; result = (char *)cbf_handle_struct_get_diffrn_id(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_FromCharPtr((const char *)result); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_find_datablock(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_find_datablock",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_find_datablock" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_find_datablock" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; cbf_handle_struct_find_datablock(arg1,(char const *)arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_polarization(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; double *arg2 = (double *) 0 ; double *arg3 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double temp2 ; int res2 = SWIG_TMPOBJ ; double temp3 ; int res3 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_polarization",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_polarization" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_get_polarization(arg1,arg2,arg3); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_select_category(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_select_category",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_select_category" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_select_category" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); { error_status=0; cbf_handle_struct_select_category(arg1,arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_pixel_size_fs(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; unsigned int arg3 ; double *arg4 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; unsigned int val3 ; int ecode3 = 0 ; double temp4 ; int res4 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; arg4 = &temp4; if (!PyArg_ParseTuple(args,(char *)"OOO:cbf_handle_struct_get_pixel_size_fs",&obj0,&obj1,&obj2)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_pixel_size_fs" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_get_pixel_size_fs" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_unsigned_SS_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_get_pixel_size_fs" "', argument " "3"" of type '" "unsigned int""'"); } arg3 = (unsigned int)(val3); { error_status=0; cbf_handle_struct_get_pixel_size_fs(arg1,arg2,arg3,arg4); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_read_file(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; int arg3 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; int val3 ; int ecode3 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOO:cbf_handle_struct_read_file",&obj0,&obj1,&obj2)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_read_file" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_read_file" "', argument " "2"" of type '" "char *""'"); } arg2 = (char *)(buf2); ecode3 = SWIG_AsVal_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_read_file" "', argument " "3"" of type '" "int""'"); } arg3 = (int)(val3); { error_status=0; cbf_handle_struct_read_file(arg1,arg2,arg3); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_datablock_name(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; char *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_datablock_name",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_datablock_name" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; result = (char *)cbf_handle_struct_datablock_name(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_FromCharPtr((const char *)result); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_realarray_wdims(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; int arg3 ; char *arg4 = (char *) 0 ; int arg5 ; int arg6 ; int arg7 ; char *arg8 = (char *) 0 ; int arg9 ; int arg10 ; int arg11 ; int arg12 ; int arg13 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; int val3 ; int ecode3 = 0 ; int res4 ; char *buf4 = 0 ; size_t size4 = 0 ; int alloc4 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int res8 ; char *buf8 = 0 ; size_t size8 = 0 ; int alloc8 = 0 ; int val10 ; int ecode10 = 0 ; int val11 ; int ecode11 = 0 ; int val12 ; int ecode12 = 0 ; int val13 ; int ecode13 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; PyObject * obj6 = 0 ; PyObject * obj7 = 0 ; PyObject * obj8 = 0 ; PyObject * obj9 = 0 ; PyObject * obj10 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOOOOOOOO:cbf_handle_struct_set_realarray_wdims",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5,&obj6,&obj7,&obj8,&obj9,&obj10)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_realarray_wdims" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_realarray_wdims" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_realarray_wdims" "', argument " "3"" of type '" "int""'"); } arg3 = (int)(val3); res4 = SWIG_AsCharPtrAndSize(obj3, &buf4, &size4, &alloc4); if (!SWIG_IsOK(res4)) { SWIG_exception_fail(SWIG_ArgError(res4), "in method '" "cbf_handle_struct_set_realarray_wdims" "', argument " "4"" of type '" "char *""'"); } arg4 = (char *)(buf4); arg5 = (int)(size4 - 1); ecode6 = SWIG_AsVal_int(obj4, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_set_realarray_wdims" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj5, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_set_realarray_wdims" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); res8 = SWIG_AsCharPtrAndSize(obj6, &buf8, &size8, &alloc8); if (!SWIG_IsOK(res8)) { SWIG_exception_fail(SWIG_ArgError(res8), "in method '" "cbf_handle_struct_set_realarray_wdims" "', argument " "8"" of type '" "char *""'"); } arg8 = (char *)(buf8); arg9 = (int)(size8 - 1); ecode10 = SWIG_AsVal_int(obj7, &val10); if (!SWIG_IsOK(ecode10)) { SWIG_exception_fail(SWIG_ArgError(ecode10), "in method '" "cbf_handle_struct_set_realarray_wdims" "', argument " "10"" of type '" "int""'"); } arg10 = (int)(val10); ecode11 = SWIG_AsVal_int(obj8, &val11); if (!SWIG_IsOK(ecode11)) { SWIG_exception_fail(SWIG_ArgError(ecode11), "in method '" "cbf_handle_struct_set_realarray_wdims" "', argument " "11"" of type '" "int""'"); } arg11 = (int)(val11); ecode12 = SWIG_AsVal_int(obj9, &val12); if (!SWIG_IsOK(ecode12)) { SWIG_exception_fail(SWIG_ArgError(ecode12), "in method '" "cbf_handle_struct_set_realarray_wdims" "', argument " "12"" of type '" "int""'"); } arg12 = (int)(val12); ecode13 = SWIG_AsVal_int(obj10, &val13); if (!SWIG_IsOK(ecode13)) { SWIG_exception_fail(SWIG_ArgError(ecode13), "in method '" "cbf_handle_struct_set_realarray_wdims" "', argument " "13"" of type '" "int""'"); } arg13 = (int)(val13); { error_status=0; cbf_handle_struct_set_realarray_wdims(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9,arg10,arg11,arg12,arg13); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); if (alloc8 == SWIG_NEWOBJ) free((char*)buf8); return resultobj; fail: if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); if (alloc8 == SWIG_NEWOBJ) free((char*)buf8); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_construct_reference_detector(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; cbf_detector result; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_construct_reference_detector",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_construct_reference_detector" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_construct_reference_detector" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); { error_status=0; result = (cbf_detector)cbf_handle_struct_construct_reference_detector(arg1,arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_NewPointerObj(SWIG_as_voidptr(result), SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_real_3d_image_fs_as_string(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int arg2 ; char **arg3 = (char **) 0 ; int *arg4 = (int *) 0 ; int arg5 ; int arg6 ; int arg7 ; int arg8 ; void *argp1 = 0 ; int res1 = 0 ; int val2 ; int ecode2 = 0 ; char *temp3 = 0 ; int tempn3 ; int val5 ; int ecode5 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int val8 ; int ecode8 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; arg3 = &temp3; arg4 = &tempn3; if (!PyArg_ParseTuple(args,(char *)"OOOOOO:cbf_handle_struct_get_real_3d_image_fs_as_string",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_real_3d_image_fs_as_string" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_get_real_3d_image_fs_as_string" "', argument " "2"" of type '" "int""'"); } arg2 = (int)(val2); ecode5 = SWIG_AsVal_int(obj2, &val5); if (!SWIG_IsOK(ecode5)) { SWIG_exception_fail(SWIG_ArgError(ecode5), "in method '" "cbf_handle_struct_get_real_3d_image_fs_as_string" "', argument " "5"" of type '" "int""'"); } arg5 = (int)(val5); ecode6 = SWIG_AsVal_int(obj3, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_get_real_3d_image_fs_as_string" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj4, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_get_real_3d_image_fs_as_string" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); ecode8 = SWIG_AsVal_int(obj5, &val8); if (!SWIG_IsOK(ecode8)) { SWIG_exception_fail(SWIG_ArgError(ecode8), "in method '" "cbf_handle_struct_get_real_3d_image_fs_as_string" "', argument " "8"" of type '" "int""'"); } arg8 = (int)(val8); { error_status=0; cbf_handle_struct_get_real_3d_image_fs_as_string(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (*arg3) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_FromCharPtrAndSize(*arg3,*arg4)); free(*arg3); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_rewind_row(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_rewind_row",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_rewind_row" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_rewind_row(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_axis_setting(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; double *arg3 = (double *) 0 ; double *arg4 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; double temp3 ; int res3 = SWIG_TMPOBJ ; double temp4 ; int res4 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; arg3 = &temp3; arg4 = &temp4; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_get_axis_setting",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_axis_setting" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_get_axis_setting" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; cbf_handle_struct_get_axis_setting(arg1,(char const *)arg2,arg3,arg4); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_require_column(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_require_column",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_require_column" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_require_column" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; cbf_handle_struct_require_column(arg1,(char const *)arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_timestamp(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; double *arg2 = (double *) 0 ; int *arg3 = (int *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double temp2 ; int res2 = SWIG_TMPOBJ ; int temp3 ; int res3 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_timestamp",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_timestamp" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_get_timestamp(arg1,arg2,arg3); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_int, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_find_nextrow(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_find_nextrow",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_find_nextrow" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_find_nextrow" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; cbf_handle_struct_find_nextrow(arg1,(char const *)arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_realarrayparameters_wdims_sf(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int *arg2 = (int *) 0 ; int *arg3 = (int *) 0 ; int *arg4 = (int *) 0 ; int *arg5 = (int *) 0 ; char **arg6 = (char **) 0 ; int *arg7 = (int *) 0 ; int *arg8 = (int *) 0 ; int *arg9 = (int *) 0 ; int *arg10 = (int *) 0 ; int *arg11 = (int *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int temp2 ; int res2 = SWIG_TMPOBJ ; int temp3 ; int res3 = SWIG_TMPOBJ ; int temp4 ; int res4 = SWIG_TMPOBJ ; int temp5 ; int res5 = SWIG_TMPOBJ ; char *temp6 = 0 ; int tempn6 ; int temp8 ; int res8 = SWIG_TMPOBJ ; int temp9 ; int res9 = SWIG_TMPOBJ ; int temp10 ; int res10 = SWIG_TMPOBJ ; int temp11 ; int res11 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; arg5 = &temp5; arg6 = &temp6; arg7 = &tempn6; arg8 = &temp8; arg9 = &temp9; arg10 = &temp10; arg11 = &temp11; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_realarrayparameters_wdims_sf",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_realarrayparameters_wdims_sf" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_get_realarrayparameters_wdims_sf(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9,arg10,arg11); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_int, new_flags)); } if (*arg6) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_FromCharPtrAndSize(*arg6,*arg7)); free(*arg6); } if (SWIG_IsTmpObj(res8)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg8))); } else { int new_flags = SWIG_IsNewObj(res8) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg8), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res9)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg9))); } else { int new_flags = SWIG_IsNewObj(res9) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg9), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res10)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg10))); } else { int new_flags = SWIG_IsNewObj(res10) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg10), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res11)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg11))); } else { int new_flags = SWIG_IsNewObj(res11) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg11), SWIGTYPE_p_int, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_reset_datablock(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_reset_datablock",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_reset_datablock" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_reset_datablock(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_3d_image_fs(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; unsigned int arg3 ; char *arg4 = (char *) 0 ; int arg5 ; int arg6 ; int arg7 ; int arg8 ; int arg9 ; int arg10 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; unsigned int val3 ; int ecode3 = 0 ; int res4 ; char *buf4 = 0 ; size_t size4 = 0 ; int alloc4 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int val8 ; int ecode8 = 0 ; int val9 ; int ecode9 = 0 ; int val10 ; int ecode10 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; PyObject * obj6 = 0 ; PyObject * obj7 = 0 ; PyObject * obj8 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOOOOOO:cbf_handle_struct_set_3d_image_fs",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5,&obj6,&obj7,&obj8)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_3d_image_fs" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_3d_image_fs" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_unsigned_SS_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_3d_image_fs" "', argument " "3"" of type '" "unsigned int""'"); } arg3 = (unsigned int)(val3); res4 = SWIG_AsCharPtrAndSize(obj3, &buf4, &size4, &alloc4); if (!SWIG_IsOK(res4)) { SWIG_exception_fail(SWIG_ArgError(res4), "in method '" "cbf_handle_struct_set_3d_image_fs" "', argument " "4"" of type '" "char *""'"); } arg4 = (char *)(buf4); arg5 = (int)(size4 - 1); ecode6 = SWIG_AsVal_int(obj4, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_set_3d_image_fs" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj5, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_set_3d_image_fs" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); ecode8 = SWIG_AsVal_int(obj6, &val8); if (!SWIG_IsOK(ecode8)) { SWIG_exception_fail(SWIG_ArgError(ecode8), "in method '" "cbf_handle_struct_set_3d_image_fs" "', argument " "8"" of type '" "int""'"); } arg8 = (int)(val8); ecode9 = SWIG_AsVal_int(obj7, &val9); if (!SWIG_IsOK(ecode9)) { SWIG_exception_fail(SWIG_ArgError(ecode9), "in method '" "cbf_handle_struct_set_3d_image_fs" "', argument " "9"" of type '" "int""'"); } arg9 = (int)(val9); ecode10 = SWIG_AsVal_int(obj8, &val10); if (!SWIG_IsOK(ecode10)) { SWIG_exception_fail(SWIG_ArgError(ecode10), "in method '" "cbf_handle_struct_set_3d_image_fs" "', argument " "10"" of type '" "int""'"); } arg10 = (int)(val10); { error_status=0; cbf_handle_struct_set_3d_image_fs(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9,arg10); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return resultobj; fail: if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_saveframename(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_set_saveframename",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_saveframename" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_set_saveframename" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; cbf_handle_struct_set_saveframename(arg1,(char const *)arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_require_integervalue(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int *arg2 = (int *) 0 ; int arg3 ; void *argp1 = 0 ; int res1 = 0 ; int temp2 ; int res2 = SWIG_TMPOBJ ; int val3 ; int ecode3 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; arg2 = &temp2; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_require_integervalue",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_require_integervalue" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode3 = SWIG_AsVal_int(obj1, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_require_integervalue" "', argument " "3"" of type '" "int""'"); } arg3 = (int)(val3); { error_status=0; cbf_handle_struct_require_integervalue(arg1,arg2,arg3); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_int, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_integerarrayparameters(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int *arg2 = (int *) 0 ; int *arg3 = (int *) 0 ; int *arg4 = (int *) 0 ; int *arg5 = (int *) 0 ; int *arg6 = (int *) 0 ; int *arg7 = (int *) 0 ; int *arg8 = (int *) 0 ; int *arg9 = (int *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int temp2 ; int res2 = SWIG_TMPOBJ ; int temp3 ; int res3 = SWIG_TMPOBJ ; int temp4 ; int res4 = SWIG_TMPOBJ ; int temp5 ; int res5 = SWIG_TMPOBJ ; int temp6 ; int res6 = SWIG_TMPOBJ ; int temp7 ; int res7 = SWIG_TMPOBJ ; int temp8 ; int res8 = SWIG_TMPOBJ ; int temp9 ; int res9 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; arg5 = &temp5; arg6 = &temp6; arg7 = &temp7; arg8 = &temp8; arg9 = &temp9; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_integerarrayparameters",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_integerarrayparameters" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_get_integerarrayparameters(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res6)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg6))); } else { int new_flags = SWIG_IsNewObj(res6) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg6), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res7)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg7))); } else { int new_flags = SWIG_IsNewObj(res7) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg7), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res8)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg8))); } else { int new_flags = SWIG_IsNewObj(res8) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg8), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res9)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg9))); } else { int new_flags = SWIG_IsNewObj(res9) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg9), SWIGTYPE_p_int, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_real_3d_image_sf(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; unsigned int arg3 ; char *arg4 = (char *) 0 ; int arg5 ; int arg6 ; int arg7 ; int arg8 ; int arg9 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; unsigned int val3 ; int ecode3 = 0 ; int res4 ; char *buf4 = 0 ; size_t size4 = 0 ; int alloc4 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int val8 ; int ecode8 = 0 ; int val9 ; int ecode9 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; PyObject * obj6 = 0 ; PyObject * obj7 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOOOOO:cbf_handle_struct_set_real_3d_image_sf",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5,&obj6,&obj7)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_real_3d_image_sf" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_real_3d_image_sf" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_unsigned_SS_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_real_3d_image_sf" "', argument " "3"" of type '" "unsigned int""'"); } arg3 = (unsigned int)(val3); res4 = SWIG_AsCharPtrAndSize(obj3, &buf4, &size4, &alloc4); if (!SWIG_IsOK(res4)) { SWIG_exception_fail(SWIG_ArgError(res4), "in method '" "cbf_handle_struct_set_real_3d_image_sf" "', argument " "4"" of type '" "char *""'"); } arg4 = (char *)(buf4); arg5 = (int)(size4 - 1); ecode6 = SWIG_AsVal_int(obj4, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_set_real_3d_image_sf" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj5, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_set_real_3d_image_sf" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); ecode8 = SWIG_AsVal_int(obj6, &val8); if (!SWIG_IsOK(ecode8)) { SWIG_exception_fail(SWIG_ArgError(ecode8), "in method '" "cbf_handle_struct_set_real_3d_image_sf" "', argument " "8"" of type '" "int""'"); } arg8 = (int)(val8); ecode9 = SWIG_AsVal_int(obj7, &val9); if (!SWIG_IsOK(ecode9)) { SWIG_exception_fail(SWIG_ArgError(ecode9), "in method '" "cbf_handle_struct_set_real_3d_image_sf" "', argument " "9"" of type '" "int""'"); } arg9 = (int)(val9); { error_status=0; cbf_handle_struct_set_real_3d_image_sf(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return resultobj; fail: if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_write_file(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; int arg3 ; int arg4 ; int arg5 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; int val3 ; int ecode3 = 0 ; int val4 ; int ecode4 = 0 ; int val5 ; int ecode5 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOO:cbf_handle_struct_write_file",&obj0,&obj1,&obj2,&obj3,&obj4)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_write_file" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_write_file" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); ecode3 = SWIG_AsVal_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_write_file" "', argument " "3"" of type '" "int""'"); } arg3 = (int)(val3); ecode4 = SWIG_AsVal_int(obj3, &val4); if (!SWIG_IsOK(ecode4)) { SWIG_exception_fail(SWIG_ArgError(ecode4), "in method '" "cbf_handle_struct_write_file" "', argument " "4"" of type '" "int""'"); } arg4 = (int)(val4); ecode5 = SWIG_AsVal_int(obj4, &val5); if (!SWIG_IsOK(ecode5)) { SWIG_exception_fail(SWIG_ArgError(ecode5), "in method '" "cbf_handle_struct_write_file" "', argument " "5"" of type '" "int""'"); } arg5 = (int)(val5); { error_status=0; cbf_handle_struct_write_file(arg1,(char const *)arg2,arg3,arg4,arg5); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_divergence(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; double arg2 ; double arg3 ; double arg4 ; void *argp1 = 0 ; int res1 = 0 ; double val2 ; int ecode2 = 0 ; double val3 ; int ecode3 = 0 ; double val4 ; int ecode4 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOO:cbf_handle_struct_set_divergence",&obj0,&obj1,&obj2,&obj3)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_divergence" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_double(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_divergence" "', argument " "2"" of type '" "double""'"); } arg2 = (double)(val2); ecode3 = SWIG_AsVal_double(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_divergence" "', argument " "3"" of type '" "double""'"); } arg3 = (double)(val3); ecode4 = SWIG_AsVal_double(obj3, &val4); if (!SWIG_IsOK(ecode4)) { SWIG_exception_fail(SWIG_ArgError(ecode4), "in method '" "cbf_handle_struct_set_divergence" "', argument " "4"" of type '" "double""'"); } arg4 = (double)(val4); { error_status=0; cbf_handle_struct_set_divergence(arg1,arg2,arg3,arg4); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_remove_datablock(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_remove_datablock",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_remove_datablock" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_remove_datablock(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_count_elements(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; unsigned int result; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_count_elements",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_count_elements" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; result = (unsigned int)cbf_handle_struct_count_elements(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_From_unsigned_SS_int((unsigned int)(result)); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_image_fs(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; unsigned int arg3 ; char *arg4 = (char *) 0 ; int arg5 ; int arg6 ; int arg7 ; int arg8 ; int arg9 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; unsigned int val3 ; int ecode3 = 0 ; int res4 ; char *buf4 = 0 ; size_t size4 = 0 ; int alloc4 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int val8 ; int ecode8 = 0 ; int val9 ; int ecode9 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; PyObject * obj6 = 0 ; PyObject * obj7 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOOOOO:cbf_handle_struct_set_image_fs",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5,&obj6,&obj7)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_image_fs" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_image_fs" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_unsigned_SS_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_image_fs" "', argument " "3"" of type '" "unsigned int""'"); } arg3 = (unsigned int)(val3); res4 = SWIG_AsCharPtrAndSize(obj3, &buf4, &size4, &alloc4); if (!SWIG_IsOK(res4)) { SWIG_exception_fail(SWIG_ArgError(res4), "in method '" "cbf_handle_struct_set_image_fs" "', argument " "4"" of type '" "char *""'"); } arg4 = (char *)(buf4); arg5 = (int)(size4 - 1); ecode6 = SWIG_AsVal_int(obj4, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_set_image_fs" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj5, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_set_image_fs" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); ecode8 = SWIG_AsVal_int(obj6, &val8); if (!SWIG_IsOK(ecode8)) { SWIG_exception_fail(SWIG_ArgError(ecode8), "in method '" "cbf_handle_struct_set_image_fs" "', argument " "8"" of type '" "int""'"); } arg8 = (int)(val8); ecode9 = SWIG_AsVal_int(obj7, &val9); if (!SWIG_IsOK(ecode9)) { SWIG_exception_fail(SWIG_ArgError(ecode9), "in method '" "cbf_handle_struct_set_image_fs" "', argument " "9"" of type '" "int""'"); } arg9 = (int)(val9); { error_status=0; cbf_handle_struct_set_image_fs(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return resultobj; fail: if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_require_reference_detector(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; cbf_detector result; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_require_reference_detector",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_require_reference_detector" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_require_reference_detector" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); { error_status=0; result = (cbf_detector)cbf_handle_struct_require_reference_detector(arg1,arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_NewPointerObj(SWIG_as_voidptr(result), SWIGTYPE_p_cbf_detector_struct, 0 | 0 ); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_next_category(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_next_category",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_next_category" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_next_category(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_diffrn_id(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_set_diffrn_id",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_diffrn_id" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_set_diffrn_id" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; cbf_handle_struct_set_diffrn_id(arg1,(char const *)arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_timestamp(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; double arg2 ; int arg3 ; double arg4 ; void *argp1 = 0 ; int res1 = 0 ; double val2 ; int ecode2 = 0 ; int val3 ; int ecode3 = 0 ; double val4 ; int ecode4 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOO:cbf_handle_struct_set_timestamp",&obj0,&obj1,&obj2,&obj3)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_timestamp" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_double(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_timestamp" "', argument " "2"" of type '" "double""'"); } arg2 = (double)(val2); ecode3 = SWIG_AsVal_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_timestamp" "', argument " "3"" of type '" "int""'"); } arg3 = (int)(val3); ecode4 = SWIG_AsVal_double(obj3, &val4); if (!SWIG_IsOK(ecode4)) { SWIG_exception_fail(SWIG_ArgError(ecode4), "in method '" "cbf_handle_struct_set_timestamp" "', argument " "4"" of type '" "double""'"); } arg4 = (double)(val4); { error_status=0; cbf_handle_struct_set_timestamp(arg1,arg2,arg3,arg4); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_orientation_matrix(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; double *arg2 = (double *) 0 ; double *arg3 = (double *) 0 ; double *arg4 = (double *) 0 ; double *arg5 = (double *) 0 ; double *arg6 = (double *) 0 ; double *arg7 = (double *) 0 ; double *arg8 = (double *) 0 ; double *arg9 = (double *) 0 ; double *arg10 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double temp2 ; int res2 = SWIG_TMPOBJ ; double temp3 ; int res3 = SWIG_TMPOBJ ; double temp4 ; int res4 = SWIG_TMPOBJ ; double temp5 ; int res5 = SWIG_TMPOBJ ; double temp6 ; int res6 = SWIG_TMPOBJ ; double temp7 ; int res7 = SWIG_TMPOBJ ; double temp8 ; int res8 = SWIG_TMPOBJ ; double temp9 ; int res9 = SWIG_TMPOBJ ; double temp10 ; int res10 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; arg5 = &temp5; arg6 = &temp6; arg7 = &temp7; arg8 = &temp8; arg9 = &temp9; arg10 = &temp10; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_orientation_matrix",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_orientation_matrix" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_get_orientation_matrix(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9,arg10); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res6)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg6))); } else { int new_flags = SWIG_IsNewObj(res6) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg6), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res7)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg7))); } else { int new_flags = SWIG_IsNewObj(res7) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg7), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res8)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg8))); } else { int new_flags = SWIG_IsNewObj(res8) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg8), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res9)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg9))); } else { int new_flags = SWIG_IsNewObj(res9) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg9), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res10)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg10))); } else { int new_flags = SWIG_IsNewObj(res10) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg10), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_image_size_fs(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; int *arg3 = (int *) 0 ; int *arg4 = (int *) 0 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; int temp3 ; int res3 = SWIG_TMPOBJ ; int temp4 ; int res4 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; arg3 = &temp3; arg4 = &temp4; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_get_image_size_fs",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_image_size_fs" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_get_image_size_fs" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); { error_status=0; cbf_handle_struct_get_image_size_fs(arg1,arg2,arg3,arg4); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_int, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_divergence(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; double *arg2 = (double *) 0 ; double *arg3 = (double *) 0 ; double *arg4 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double temp2 ; int res2 = SWIG_TMPOBJ ; double temp3 ; int res3 = SWIG_TMPOBJ ; double temp4 ; int res4 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_divergence",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_divergence" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_get_divergence(arg1,arg2,arg3,arg4); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_rewind_category(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_rewind_category",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_rewind_category" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_rewind_category(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_read_template(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_read_template",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_read_template" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_read_template" "', argument " "2"" of type '" "char *""'"); } arg2 = (char *)(buf2); { error_status=0; cbf_handle_struct_read_template(arg1,arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_select_row(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_select_row",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_select_row" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_select_row" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); { error_status=0; cbf_handle_struct_select_row(arg1,arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_image_fs_as_string(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int arg2 ; char **arg3 = (char **) 0 ; int *arg4 = (int *) 0 ; int arg5 ; int arg6 ; int arg7 ; int arg8 ; void *argp1 = 0 ; int res1 = 0 ; int val2 ; int ecode2 = 0 ; char *temp3 = 0 ; int tempn3 ; int val5 ; int ecode5 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int val8 ; int ecode8 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; arg3 = &temp3; arg4 = &tempn3; if (!PyArg_ParseTuple(args,(char *)"OOOOOO:cbf_handle_struct_get_image_fs_as_string",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_image_fs_as_string" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_get_image_fs_as_string" "', argument " "2"" of type '" "int""'"); } arg2 = (int)(val2); ecode5 = SWIG_AsVal_int(obj2, &val5); if (!SWIG_IsOK(ecode5)) { SWIG_exception_fail(SWIG_ArgError(ecode5), "in method '" "cbf_handle_struct_get_image_fs_as_string" "', argument " "5"" of type '" "int""'"); } arg5 = (int)(val5); ecode6 = SWIG_AsVal_int(obj3, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_get_image_fs_as_string" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj4, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_get_image_fs_as_string" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); ecode8 = SWIG_AsVal_int(obj5, &val8); if (!SWIG_IsOK(ecode8)) { SWIG_exception_fail(SWIG_ArgError(ecode8), "in method '" "cbf_handle_struct_get_image_fs_as_string" "', argument " "8"" of type '" "int""'"); } arg8 = (int)(val8); { error_status=0; cbf_handle_struct_get_image_fs_as_string(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (*arg3) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_FromCharPtrAndSize(*arg3,*arg4)); free(*arg3); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_image_size_sf(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; int *arg3 = (int *) 0 ; int *arg4 = (int *) 0 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; int temp3 ; int res3 = SWIG_TMPOBJ ; int temp4 ; int res4 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; arg3 = &temp3; arg4 = &temp4; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_get_image_size_sf",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_image_size_sf" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_get_image_size_sf" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); { error_status=0; cbf_handle_struct_get_image_size_sf(arg1,arg2,arg3,arg4); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_int, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_real_image_fs_as_string(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int arg2 ; char **arg3 = (char **) 0 ; int *arg4 = (int *) 0 ; int arg5 ; int arg6 ; int arg7 ; void *argp1 = 0 ; int res1 = 0 ; int val2 ; int ecode2 = 0 ; char *temp3 = 0 ; int tempn3 ; int val5 ; int ecode5 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; arg3 = &temp3; arg4 = &tempn3; if (!PyArg_ParseTuple(args,(char *)"OOOOO:cbf_handle_struct_get_real_image_fs_as_string",&obj0,&obj1,&obj2,&obj3,&obj4)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_real_image_fs_as_string" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_get_real_image_fs_as_string" "', argument " "2"" of type '" "int""'"); } arg2 = (int)(val2); ecode5 = SWIG_AsVal_int(obj2, &val5); if (!SWIG_IsOK(ecode5)) { SWIG_exception_fail(SWIG_ArgError(ecode5), "in method '" "cbf_handle_struct_get_real_image_fs_as_string" "', argument " "5"" of type '" "int""'"); } arg5 = (int)(val5); ecode6 = SWIG_AsVal_int(obj3, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_get_real_image_fs_as_string" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj4, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_get_real_image_fs_as_string" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); { error_status=0; cbf_handle_struct_get_real_image_fs_as_string(arg1,arg2,arg3,arg4,arg5,arg6,arg7); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (*arg3) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_FromCharPtrAndSize(*arg3,*arg4)); free(*arg3); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_count_columns(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; unsigned int result; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_count_columns",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_count_columns" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; result = (unsigned int)cbf_handle_struct_count_columns(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_From_unsigned_SS_int((unsigned int)(result)); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_integerarrayparameters_wdims(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int *arg2 = (int *) 0 ; int *arg3 = (int *) 0 ; int *arg4 = (int *) 0 ; int *arg5 = (int *) 0 ; int *arg6 = (int *) 0 ; int *arg7 = (int *) 0 ; int *arg8 = (int *) 0 ; int *arg9 = (int *) 0 ; char **arg10 = (char **) 0 ; int *arg11 = (int *) 0 ; int *arg12 = (int *) 0 ; int *arg13 = (int *) 0 ; int *arg14 = (int *) 0 ; int *arg15 = (int *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int temp2 ; int res2 = SWIG_TMPOBJ ; int temp3 ; int res3 = SWIG_TMPOBJ ; int temp4 ; int res4 = SWIG_TMPOBJ ; int temp5 ; int res5 = SWIG_TMPOBJ ; int temp6 ; int res6 = SWIG_TMPOBJ ; int temp7 ; int res7 = SWIG_TMPOBJ ; int temp8 ; int res8 = SWIG_TMPOBJ ; int temp9 ; int res9 = SWIG_TMPOBJ ; char *temp10 = 0 ; int tempn10 ; int temp12 ; int res12 = SWIG_TMPOBJ ; int temp13 ; int res13 = SWIG_TMPOBJ ; int temp14 ; int res14 = SWIG_TMPOBJ ; int temp15 ; int res15 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; arg5 = &temp5; arg6 = &temp6; arg7 = &temp7; arg8 = &temp8; arg9 = &temp9; arg10 = &temp10; arg11 = &tempn10; arg12 = &temp12; arg13 = &temp13; arg14 = &temp14; arg15 = &temp15; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_integerarrayparameters_wdims",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_integerarrayparameters_wdims" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_get_integerarrayparameters_wdims(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9,arg10,arg11,arg12,arg13,arg14,arg15); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res6)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg6))); } else { int new_flags = SWIG_IsNewObj(res6) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg6), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res7)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg7))); } else { int new_flags = SWIG_IsNewObj(res7) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg7), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res8)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg8))); } else { int new_flags = SWIG_IsNewObj(res8) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg8), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res9)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg9))); } else { int new_flags = SWIG_IsNewObj(res9) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg9), SWIGTYPE_p_int, new_flags)); } if (*arg10) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_FromCharPtrAndSize(*arg10,*arg11)); free(*arg10); } if (SWIG_IsTmpObj(res12)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg12))); } else { int new_flags = SWIG_IsNewObj(res12) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg12), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res13)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg13))); } else { int new_flags = SWIG_IsNewObj(res13) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg13), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res14)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg14))); } else { int new_flags = SWIG_IsNewObj(res14) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg14), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res15)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg15))); } else { int new_flags = SWIG_IsNewObj(res15) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg15), SWIGTYPE_p_int, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_gain(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; double *arg3 = (double *) 0 ; double *arg4 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; double temp3 ; int res3 = SWIG_TMPOBJ ; double temp4 ; int res4 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; arg3 = &temp3; arg4 = &temp4; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_get_gain",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_gain" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_get_gain" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); { error_status=0; cbf_handle_struct_get_gain(arg1,arg2,arg3,arg4); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_new_saveframe(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_new_saveframe",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_new_saveframe" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_new_saveframe" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; cbf_handle_struct_new_saveframe(arg1,(char const *)arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_polarization(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; double arg2 ; double arg3 ; void *argp1 = 0 ; int res1 = 0 ; double val2 ; int ecode2 = 0 ; double val3 ; int ecode3 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOO:cbf_handle_struct_set_polarization",&obj0,&obj1,&obj2)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_polarization" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_double(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_polarization" "', argument " "2"" of type '" "double""'"); } arg2 = (double)(val2); ecode3 = SWIG_AsVal_double(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_polarization" "', argument " "3"" of type '" "double""'"); } arg3 = (double)(val3); { error_status=0; cbf_handle_struct_set_polarization(arg1,arg2,arg3); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_real_3d_image(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; unsigned int arg3 ; char *arg4 = (char *) 0 ; int arg5 ; int arg6 ; int arg7 ; int arg8 ; int arg9 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; unsigned int val3 ; int ecode3 = 0 ; int res4 ; char *buf4 = 0 ; size_t size4 = 0 ; int alloc4 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int val8 ; int ecode8 = 0 ; int val9 ; int ecode9 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; PyObject * obj6 = 0 ; PyObject * obj7 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOOOOO:cbf_handle_struct_set_real_3d_image",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5,&obj6,&obj7)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_real_3d_image" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_real_3d_image" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_unsigned_SS_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_real_3d_image" "', argument " "3"" of type '" "unsigned int""'"); } arg3 = (unsigned int)(val3); res4 = SWIG_AsCharPtrAndSize(obj3, &buf4, &size4, &alloc4); if (!SWIG_IsOK(res4)) { SWIG_exception_fail(SWIG_ArgError(res4), "in method '" "cbf_handle_struct_set_real_3d_image" "', argument " "4"" of type '" "char *""'"); } arg4 = (char *)(buf4); arg5 = (int)(size4 - 1); ecode6 = SWIG_AsVal_int(obj4, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_set_real_3d_image" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj5, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_set_real_3d_image" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); ecode8 = SWIG_AsVal_int(obj6, &val8); if (!SWIG_IsOK(ecode8)) { SWIG_exception_fail(SWIG_ArgError(ecode8), "in method '" "cbf_handle_struct_set_real_3d_image" "', argument " "8"" of type '" "int""'"); } arg8 = (int)(val8); ecode9 = SWIG_AsVal_int(obj7, &val9); if (!SWIG_IsOK(ecode9)) { SWIG_exception_fail(SWIG_ArgError(ecode9), "in method '" "cbf_handle_struct_set_real_3d_image" "', argument " "9"" of type '" "int""'"); } arg9 = (int)(val9); { error_status=0; cbf_handle_struct_set_real_3d_image(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return resultobj; fail: if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_delete_row(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_delete_row",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_delete_row" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_delete_row" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); { error_status=0; cbf_handle_struct_delete_row(arg1,arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_column_name(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; char *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_column_name",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_column_name" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; result = (char *)cbf_handle_struct_column_name(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_FromCharPtr((const char *)result); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_remove_saveframe(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_remove_saveframe",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_remove_saveframe" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_remove_saveframe(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_integerarray_wdims_sf(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; int arg3 ; char *arg4 = (char *) 0 ; int arg5 ; int arg6 ; int arg7 ; int arg8 ; char *arg9 = (char *) 0 ; int arg10 ; int arg11 ; int arg12 ; int arg13 ; int arg14 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; int val3 ; int ecode3 = 0 ; int res4 ; char *buf4 = 0 ; size_t size4 = 0 ; int alloc4 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int val8 ; int ecode8 = 0 ; int res9 ; char *buf9 = 0 ; size_t size9 = 0 ; int alloc9 = 0 ; int val11 ; int ecode11 = 0 ; int val12 ; int ecode12 = 0 ; int val13 ; int ecode13 = 0 ; int val14 ; int ecode14 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; PyObject * obj6 = 0 ; PyObject * obj7 = 0 ; PyObject * obj8 = 0 ; PyObject * obj9 = 0 ; PyObject * obj10 = 0 ; PyObject * obj11 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOOOOOOOOO:cbf_handle_struct_set_integerarray_wdims_sf",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5,&obj6,&obj7,&obj8,&obj9,&obj10,&obj11)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_integerarray_wdims_sf" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_integerarray_wdims_sf" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_integerarray_wdims_sf" "', argument " "3"" of type '" "int""'"); } arg3 = (int)(val3); res4 = SWIG_AsCharPtrAndSize(obj3, &buf4, &size4, &alloc4); if (!SWIG_IsOK(res4)) { SWIG_exception_fail(SWIG_ArgError(res4), "in method '" "cbf_handle_struct_set_integerarray_wdims_sf" "', argument " "4"" of type '" "char *""'"); } arg4 = (char *)(buf4); arg5 = (int)(size4 - 1); ecode6 = SWIG_AsVal_int(obj4, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_set_integerarray_wdims_sf" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj5, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_set_integerarray_wdims_sf" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); ecode8 = SWIG_AsVal_int(obj6, &val8); if (!SWIG_IsOK(ecode8)) { SWIG_exception_fail(SWIG_ArgError(ecode8), "in method '" "cbf_handle_struct_set_integerarray_wdims_sf" "', argument " "8"" of type '" "int""'"); } arg8 = (int)(val8); res9 = SWIG_AsCharPtrAndSize(obj7, &buf9, &size9, &alloc9); if (!SWIG_IsOK(res9)) { SWIG_exception_fail(SWIG_ArgError(res9), "in method '" "cbf_handle_struct_set_integerarray_wdims_sf" "', argument " "9"" of type '" "char *""'"); } arg9 = (char *)(buf9); arg10 = (int)(size9 - 1); ecode11 = SWIG_AsVal_int(obj8, &val11); if (!SWIG_IsOK(ecode11)) { SWIG_exception_fail(SWIG_ArgError(ecode11), "in method '" "cbf_handle_struct_set_integerarray_wdims_sf" "', argument " "11"" of type '" "int""'"); } arg11 = (int)(val11); ecode12 = SWIG_AsVal_int(obj9, &val12); if (!SWIG_IsOK(ecode12)) { SWIG_exception_fail(SWIG_ArgError(ecode12), "in method '" "cbf_handle_struct_set_integerarray_wdims_sf" "', argument " "12"" of type '" "int""'"); } arg12 = (int)(val12); ecode13 = SWIG_AsVal_int(obj10, &val13); if (!SWIG_IsOK(ecode13)) { SWIG_exception_fail(SWIG_ArgError(ecode13), "in method '" "cbf_handle_struct_set_integerarray_wdims_sf" "', argument " "13"" of type '" "int""'"); } arg13 = (int)(val13); ecode14 = SWIG_AsVal_int(obj11, &val14); if (!SWIG_IsOK(ecode14)) { SWIG_exception_fail(SWIG_ArgError(ecode14), "in method '" "cbf_handle_struct_set_integerarray_wdims_sf" "', argument " "14"" of type '" "int""'"); } arg14 = (int)(val14); { error_status=0; cbf_handle_struct_set_integerarray_wdims_sf(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9,arg10,arg11,arg12,arg13,arg14); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); if (alloc9 == SWIG_NEWOBJ) free((char*)buf9); return resultobj; fail: if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); if (alloc9 == SWIG_NEWOBJ) free((char*)buf9); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_require_value(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; char *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_require_value",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_require_value" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_require_value" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; result = (char *)cbf_handle_struct_require_value(arg1,(char const *)arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_FromCharPtr((const char *)result); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_require_column_integervalue(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; int *arg3 = (int *) 0 ; int arg4 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; int temp3 ; int res3 = SWIG_TMPOBJ ; int val4 ; int ecode4 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; arg3 = &temp3; if (!PyArg_ParseTuple(args,(char *)"OOO:cbf_handle_struct_require_column_integervalue",&obj0,&obj1,&obj2)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_require_column_integervalue" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_require_column_integervalue" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); ecode4 = SWIG_AsVal_int(obj2, &val4); if (!SWIG_IsOK(ecode4)) { SWIG_exception_fail(SWIG_ArgError(ecode4), "in method '" "cbf_handle_struct_require_column_integervalue" "', argument " "4"" of type '" "int""'"); } arg4 = (int)(val4); { error_status=0; cbf_handle_struct_require_column_integervalue(arg1,(char const *)arg2,arg3,arg4); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_int, new_flags)); } if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_pixel_size(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; unsigned int arg3 ; double arg4 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; unsigned int val3 ; int ecode3 = 0 ; double val4 ; int ecode4 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOO:cbf_handle_struct_set_pixel_size",&obj0,&obj1,&obj2,&obj3)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_pixel_size" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_pixel_size" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_unsigned_SS_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_pixel_size" "', argument " "3"" of type '" "unsigned int""'"); } arg3 = (unsigned int)(val3); ecode4 = SWIG_AsVal_double(obj3, &val4); if (!SWIG_IsOK(ecode4)) { SWIG_exception_fail(SWIG_ArgError(ecode4), "in method '" "cbf_handle_struct_set_pixel_size" "', argument " "4"" of type '" "double""'"); } arg4 = (double)(val4); { error_status=0; cbf_handle_struct_set_pixel_size(arg1,arg2,arg3,arg4); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_next_column(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_next_column",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_next_column" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_next_column(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_3d_image_size_sf(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; int *arg3 = (int *) 0 ; int *arg4 = (int *) 0 ; int *arg5 = (int *) 0 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; int temp3 ; int res3 = SWIG_TMPOBJ ; int temp4 ; int res4 = SWIG_TMPOBJ ; int temp5 ; int res5 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; arg3 = &temp3; arg4 = &temp4; arg5 = &temp5; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_get_3d_image_size_sf",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_3d_image_size_sf" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_get_3d_image_size_sf" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); { error_status=0; cbf_handle_struct_get_3d_image_size_sf(arg1,arg2,arg3,arg4,arg5); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_int, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_realarrayparameters_wdims_fs(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int *arg2 = (int *) 0 ; int *arg3 = (int *) 0 ; int *arg4 = (int *) 0 ; int *arg5 = (int *) 0 ; char **arg6 = (char **) 0 ; int *arg7 = (int *) 0 ; int *arg8 = (int *) 0 ; int *arg9 = (int *) 0 ; int *arg10 = (int *) 0 ; int *arg11 = (int *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int temp2 ; int res2 = SWIG_TMPOBJ ; int temp3 ; int res3 = SWIG_TMPOBJ ; int temp4 ; int res4 = SWIG_TMPOBJ ; int temp5 ; int res5 = SWIG_TMPOBJ ; char *temp6 = 0 ; int tempn6 ; int temp8 ; int res8 = SWIG_TMPOBJ ; int temp9 ; int res9 = SWIG_TMPOBJ ; int temp10 ; int res10 = SWIG_TMPOBJ ; int temp11 ; int res11 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; arg5 = &temp5; arg6 = &temp6; arg7 = &tempn6; arg8 = &temp8; arg9 = &temp9; arg10 = &temp10; arg11 = &temp11; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_realarrayparameters_wdims_fs",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_realarrayparameters_wdims_fs" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_get_realarrayparameters_wdims_fs(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9,arg10,arg11); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_int, new_flags)); } if (*arg6) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_FromCharPtrAndSize(*arg6,*arg7)); free(*arg6); } if (SWIG_IsTmpObj(res8)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg8))); } else { int new_flags = SWIG_IsNewObj(res8) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg8), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res9)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg9))); } else { int new_flags = SWIG_IsNewObj(res9) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg9), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res10)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg10))); } else { int new_flags = SWIG_IsNewObj(res10) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg10), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res11)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg11))); } else { int new_flags = SWIG_IsNewObj(res11) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg11), SWIGTYPE_p_int, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_realarray_as_string(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char **arg2 = (char **) 0 ; int *arg3 = (int *) 0 ; void *argp1 = 0 ; int res1 = 0 ; char *temp2 = 0 ; int tempn2 ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &tempn2; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_realarray_as_string",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_realarray_as_string" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_get_realarray_as_string(arg1,arg2,arg3); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (*arg2) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_FromCharPtrAndSize(*arg2,*arg3)); free(*arg2); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_bin_sizes(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int arg2 ; double *arg3 = (double *) 0 ; double *arg4 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int val2 ; int ecode2 = 0 ; double temp3 ; int res3 = SWIG_TMPOBJ ; double temp4 ; int res4 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; arg3 = &temp3; arg4 = &temp4; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_get_bin_sizes",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_bin_sizes" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_get_bin_sizes" "', argument " "2"" of type '" "int""'"); } arg2 = (int)(val2); { error_status=0; cbf_handle_struct_get_bin_sizes(arg1,arg2,arg3,arg4); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_reset_category(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_reset_category",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_reset_category" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_reset_category(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_construct_goniometer(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; cbf_goniometer result; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_construct_goniometer",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_construct_goniometer" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; result = (cbf_goniometer)cbf_handle_struct_construct_goniometer(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_NewPointerObj(SWIG_as_voidptr(result), SWIGTYPE_p_cbf_positioner_struct, 0 | 0 ); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_datablockname(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_set_datablockname",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_datablockname" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_set_datablockname" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; cbf_handle_struct_set_datablockname(arg1,(char const *)arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_crystal_id(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_set_crystal_id",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_crystal_id" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_set_crystal_id" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; cbf_handle_struct_set_crystal_id(arg1,(char const *)arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_integerarray_as_string(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char **arg2 = (char **) 0 ; int *arg3 = (int *) 0 ; void *argp1 = 0 ; int res1 = 0 ; char *temp2 = 0 ; int tempn2 ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &tempn2; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_integerarray_as_string",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_integerarray_as_string" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_get_integerarray_as_string(arg1,arg2,arg3); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (*arg2) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_FromCharPtrAndSize(*arg2,*arg3)); free(*arg2); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_3d_image(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; unsigned int arg3 ; char *arg4 = (char *) 0 ; int arg5 ; int arg6 ; int arg7 ; int arg8 ; int arg9 ; int arg10 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; unsigned int val3 ; int ecode3 = 0 ; int res4 ; char *buf4 = 0 ; size_t size4 = 0 ; int alloc4 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int val8 ; int ecode8 = 0 ; int val9 ; int ecode9 = 0 ; int val10 ; int ecode10 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; PyObject * obj6 = 0 ; PyObject * obj7 = 0 ; PyObject * obj8 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOOOOOO:cbf_handle_struct_set_3d_image",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5,&obj6,&obj7,&obj8)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_3d_image" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_3d_image" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_unsigned_SS_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_3d_image" "', argument " "3"" of type '" "unsigned int""'"); } arg3 = (unsigned int)(val3); res4 = SWIG_AsCharPtrAndSize(obj3, &buf4, &size4, &alloc4); if (!SWIG_IsOK(res4)) { SWIG_exception_fail(SWIG_ArgError(res4), "in method '" "cbf_handle_struct_set_3d_image" "', argument " "4"" of type '" "char *""'"); } arg4 = (char *)(buf4); arg5 = (int)(size4 - 1); ecode6 = SWIG_AsVal_int(obj4, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_set_3d_image" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj5, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_set_3d_image" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); ecode8 = SWIG_AsVal_int(obj6, &val8); if (!SWIG_IsOK(ecode8)) { SWIG_exception_fail(SWIG_ArgError(ecode8), "in method '" "cbf_handle_struct_set_3d_image" "', argument " "8"" of type '" "int""'"); } arg8 = (int)(val8); ecode9 = SWIG_AsVal_int(obj7, &val9); if (!SWIG_IsOK(ecode9)) { SWIG_exception_fail(SWIG_ArgError(ecode9), "in method '" "cbf_handle_struct_set_3d_image" "', argument " "9"" of type '" "int""'"); } arg9 = (int)(val9); ecode10 = SWIG_AsVal_int(obj8, &val10); if (!SWIG_IsOK(ecode10)) { SWIG_exception_fail(SWIG_ArgError(ecode10), "in method '" "cbf_handle_struct_set_3d_image" "', argument " "10"" of type '" "int""'"); } arg10 = (int)(val10); { error_status=0; cbf_handle_struct_set_3d_image(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9,arg10); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return resultobj; fail: if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_dictionary(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; cbf_handle arg2 = (cbf_handle) 0 ; void *argp1 = 0 ; int res1 = 0 ; void *argp2 = 0 ; int res2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_set_dictionary",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_dictionary" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_ConvertPtr(obj1, &argp2,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_set_dictionary" "', argument " "2"" of type '" "cbf_handle""'"); } arg2 = (cbf_handle)(argp2); { error_status=0; cbf_handle_struct_set_dictionary(arg1,arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_find_tag_category(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; char *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_find_tag_category",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_find_tag_category" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_find_tag_category" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; result = (char *)cbf_handle_struct_find_tag_category(arg1,(char const *)arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_FromCharPtr((const char *)result); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_real_3d_image_sf_as_string(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int arg2 ; char **arg3 = (char **) 0 ; int *arg4 = (int *) 0 ; int arg5 ; int arg6 ; int arg7 ; int arg8 ; void *argp1 = 0 ; int res1 = 0 ; int val2 ; int ecode2 = 0 ; char *temp3 = 0 ; int tempn3 ; int val5 ; int ecode5 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int val8 ; int ecode8 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; arg3 = &temp3; arg4 = &tempn3; if (!PyArg_ParseTuple(args,(char *)"OOOOOO:cbf_handle_struct_get_real_3d_image_sf_as_string",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_real_3d_image_sf_as_string" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_get_real_3d_image_sf_as_string" "', argument " "2"" of type '" "int""'"); } arg2 = (int)(val2); ecode5 = SWIG_AsVal_int(obj2, &val5); if (!SWIG_IsOK(ecode5)) { SWIG_exception_fail(SWIG_ArgError(ecode5), "in method '" "cbf_handle_struct_get_real_3d_image_sf_as_string" "', argument " "5"" of type '" "int""'"); } arg5 = (int)(val5); ecode6 = SWIG_AsVal_int(obj3, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_get_real_3d_image_sf_as_string" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj4, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_get_real_3d_image_sf_as_string" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); ecode8 = SWIG_AsVal_int(obj5, &val8); if (!SWIG_IsOK(ecode8)) { SWIG_exception_fail(SWIG_ArgError(ecode8), "in method '" "cbf_handle_struct_get_real_3d_image_sf_as_string" "', argument " "8"" of type '" "int""'"); } arg8 = (int)(val8); { error_status=0; cbf_handle_struct_get_real_3d_image_sf_as_string(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (*arg3) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_FromCharPtrAndSize(*arg3,*arg4)); free(*arg3); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_typeofvalue(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_set_typeofvalue",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_typeofvalue" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_set_typeofvalue" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; cbf_handle_struct_set_typeofvalue(arg1,(char const *)arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_integerarray_wdims(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; int arg3 ; char *arg4 = (char *) 0 ; int arg5 ; int arg6 ; int arg7 ; int arg8 ; char *arg9 = (char *) 0 ; int arg10 ; int arg11 ; int arg12 ; int arg13 ; int arg14 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; int val3 ; int ecode3 = 0 ; int res4 ; char *buf4 = 0 ; size_t size4 = 0 ; int alloc4 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int val8 ; int ecode8 = 0 ; int res9 ; char *buf9 = 0 ; size_t size9 = 0 ; int alloc9 = 0 ; int val11 ; int ecode11 = 0 ; int val12 ; int ecode12 = 0 ; int val13 ; int ecode13 = 0 ; int val14 ; int ecode14 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; PyObject * obj6 = 0 ; PyObject * obj7 = 0 ; PyObject * obj8 = 0 ; PyObject * obj9 = 0 ; PyObject * obj10 = 0 ; PyObject * obj11 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOOOOOOOOO:cbf_handle_struct_set_integerarray_wdims",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5,&obj6,&obj7,&obj8,&obj9,&obj10,&obj11)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_integerarray_wdims" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_integerarray_wdims" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_integerarray_wdims" "', argument " "3"" of type '" "int""'"); } arg3 = (int)(val3); res4 = SWIG_AsCharPtrAndSize(obj3, &buf4, &size4, &alloc4); if (!SWIG_IsOK(res4)) { SWIG_exception_fail(SWIG_ArgError(res4), "in method '" "cbf_handle_struct_set_integerarray_wdims" "', argument " "4"" of type '" "char *""'"); } arg4 = (char *)(buf4); arg5 = (int)(size4 - 1); ecode6 = SWIG_AsVal_int(obj4, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_set_integerarray_wdims" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj5, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_set_integerarray_wdims" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); ecode8 = SWIG_AsVal_int(obj6, &val8); if (!SWIG_IsOK(ecode8)) { SWIG_exception_fail(SWIG_ArgError(ecode8), "in method '" "cbf_handle_struct_set_integerarray_wdims" "', argument " "8"" of type '" "int""'"); } arg8 = (int)(val8); res9 = SWIG_AsCharPtrAndSize(obj7, &buf9, &size9, &alloc9); if (!SWIG_IsOK(res9)) { SWIG_exception_fail(SWIG_ArgError(res9), "in method '" "cbf_handle_struct_set_integerarray_wdims" "', argument " "9"" of type '" "char *""'"); } arg9 = (char *)(buf9); arg10 = (int)(size9 - 1); ecode11 = SWIG_AsVal_int(obj8, &val11); if (!SWIG_IsOK(ecode11)) { SWIG_exception_fail(SWIG_ArgError(ecode11), "in method '" "cbf_handle_struct_set_integerarray_wdims" "', argument " "11"" of type '" "int""'"); } arg11 = (int)(val11); ecode12 = SWIG_AsVal_int(obj9, &val12); if (!SWIG_IsOK(ecode12)) { SWIG_exception_fail(SWIG_ArgError(ecode12), "in method '" "cbf_handle_struct_set_integerarray_wdims" "', argument " "12"" of type '" "int""'"); } arg12 = (int)(val12); ecode13 = SWIG_AsVal_int(obj10, &val13); if (!SWIG_IsOK(ecode13)) { SWIG_exception_fail(SWIG_ArgError(ecode13), "in method '" "cbf_handle_struct_set_integerarray_wdims" "', argument " "13"" of type '" "int""'"); } arg13 = (int)(val13); ecode14 = SWIG_AsVal_int(obj11, &val14); if (!SWIG_IsOK(ecode14)) { SWIG_exception_fail(SWIG_ArgError(ecode14), "in method '" "cbf_handle_struct_set_integerarray_wdims" "', argument " "14"" of type '" "int""'"); } arg14 = (int)(val14); { error_status=0; cbf_handle_struct_set_integerarray_wdims(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9,arg10,arg11,arg12,arg13,arg14); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); if (alloc9 == SWIG_NEWOBJ) free((char*)buf9); return resultobj; fail: if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); if (alloc9 == SWIG_NEWOBJ) free((char*)buf9); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_integration_time(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; double arg2 ; void *argp1 = 0 ; int res1 = 0 ; double val2 ; int ecode2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_set_integration_time",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_integration_time" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_double(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_integration_time" "', argument " "2"" of type '" "double""'"); } arg2 = (double)(val2); { error_status=0; cbf_handle_struct_set_integration_time(arg1,arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_axis_setting(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; double arg3 ; double arg4 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; double val3 ; int ecode3 = 0 ; double val4 ; int ecode4 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOO:cbf_handle_struct_set_axis_setting",&obj0,&obj1,&obj2,&obj3)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_axis_setting" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_set_axis_setting" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); ecode3 = SWIG_AsVal_double(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_axis_setting" "', argument " "3"" of type '" "double""'"); } arg3 = (double)(val3); ecode4 = SWIG_AsVal_double(obj3, &val4); if (!SWIG_IsOK(ecode4)) { SWIG_exception_fail(SWIG_ArgError(ecode4), "in method '" "cbf_handle_struct_set_axis_setting" "', argument " "4"" of type '" "double""'"); } arg4 = (double)(val4); { error_status=0; cbf_handle_struct_set_axis_setting(arg1,(char const *)arg2,arg3,arg4); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_real_image_as_string(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int arg2 ; char **arg3 = (char **) 0 ; int *arg4 = (int *) 0 ; int arg5 ; int arg6 ; int arg7 ; void *argp1 = 0 ; int res1 = 0 ; int val2 ; int ecode2 = 0 ; char *temp3 = 0 ; int tempn3 ; int val5 ; int ecode5 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; arg3 = &temp3; arg4 = &tempn3; if (!PyArg_ParseTuple(args,(char *)"OOOOO:cbf_handle_struct_get_real_image_as_string",&obj0,&obj1,&obj2,&obj3,&obj4)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_real_image_as_string" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_get_real_image_as_string" "', argument " "2"" of type '" "int""'"); } arg2 = (int)(val2); ecode5 = SWIG_AsVal_int(obj2, &val5); if (!SWIG_IsOK(ecode5)) { SWIG_exception_fail(SWIG_ArgError(ecode5), "in method '" "cbf_handle_struct_get_real_image_as_string" "', argument " "5"" of type '" "int""'"); } arg5 = (int)(val5); ecode6 = SWIG_AsVal_int(obj3, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_get_real_image_as_string" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj4, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_get_real_image_as_string" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); { error_status=0; cbf_handle_struct_get_real_image_as_string(arg1,arg2,arg3,arg4,arg5,arg6,arg7); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (*arg3) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_FromCharPtrAndSize(*arg3,*arg4)); free(*arg3); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_3d_image_sf_as_string(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int arg2 ; char **arg3 = (char **) 0 ; int *arg4 = (int *) 0 ; int arg5 ; int arg6 ; int arg7 ; int arg8 ; int arg9 ; void *argp1 = 0 ; int res1 = 0 ; int val2 ; int ecode2 = 0 ; char *temp3 = 0 ; int tempn3 ; int val5 ; int ecode5 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int val8 ; int ecode8 = 0 ; int val9 ; int ecode9 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; PyObject * obj6 = 0 ; arg3 = &temp3; arg4 = &tempn3; if (!PyArg_ParseTuple(args,(char *)"OOOOOOO:cbf_handle_struct_get_3d_image_sf_as_string",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5,&obj6)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_3d_image_sf_as_string" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_get_3d_image_sf_as_string" "', argument " "2"" of type '" "int""'"); } arg2 = (int)(val2); ecode5 = SWIG_AsVal_int(obj2, &val5); if (!SWIG_IsOK(ecode5)) { SWIG_exception_fail(SWIG_ArgError(ecode5), "in method '" "cbf_handle_struct_get_3d_image_sf_as_string" "', argument " "5"" of type '" "int""'"); } arg5 = (int)(val5); ecode6 = SWIG_AsVal_int(obj3, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_get_3d_image_sf_as_string" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj4, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_get_3d_image_sf_as_string" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); ecode8 = SWIG_AsVal_int(obj5, &val8); if (!SWIG_IsOK(ecode8)) { SWIG_exception_fail(SWIG_ArgError(ecode8), "in method '" "cbf_handle_struct_get_3d_image_sf_as_string" "', argument " "8"" of type '" "int""'"); } arg8 = (int)(val8); ecode9 = SWIG_AsVal_int(obj6, &val9); if (!SWIG_IsOK(ecode9)) { SWIG_exception_fail(SWIG_ArgError(ecode9), "in method '" "cbf_handle_struct_get_3d_image_sf_as_string" "', argument " "9"" of type '" "int""'"); } arg9 = (int)(val9); { error_status=0; cbf_handle_struct_get_3d_image_sf_as_string(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (*arg3) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_FromCharPtrAndSize(*arg3,*arg4)); free(*arg3); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_real_image_fs(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; unsigned int arg3 ; char *arg4 = (char *) 0 ; int arg5 ; int arg6 ; int arg7 ; int arg8 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; unsigned int val3 ; int ecode3 = 0 ; int res4 ; char *buf4 = 0 ; size_t size4 = 0 ; int alloc4 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int val8 ; int ecode8 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; PyObject * obj6 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOOOO:cbf_handle_struct_set_real_image_fs",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5,&obj6)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_real_image_fs" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_real_image_fs" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_unsigned_SS_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_real_image_fs" "', argument " "3"" of type '" "unsigned int""'"); } arg3 = (unsigned int)(val3); res4 = SWIG_AsCharPtrAndSize(obj3, &buf4, &size4, &alloc4); if (!SWIG_IsOK(res4)) { SWIG_exception_fail(SWIG_ArgError(res4), "in method '" "cbf_handle_struct_set_real_image_fs" "', argument " "4"" of type '" "char *""'"); } arg4 = (char *)(buf4); arg5 = (int)(size4 - 1); ecode6 = SWIG_AsVal_int(obj4, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_set_real_image_fs" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj5, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_set_real_image_fs" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); ecode8 = SWIG_AsVal_int(obj6, &val8); if (!SWIG_IsOK(ecode8)) { SWIG_exception_fail(SWIG_ArgError(ecode8), "in method '" "cbf_handle_struct_set_real_image_fs" "', argument " "8"" of type '" "int""'"); } arg8 = (int)(val8); { error_status=0; cbf_handle_struct_set_real_image_fs(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return resultobj; fail: if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_overload(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; double *arg3 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; double temp3 ; int res3 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; arg3 = &temp3; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_get_overload",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_overload" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_get_overload" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); { error_status=0; cbf_handle_struct_get_overload(arg1,arg2,arg3); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_wavelength(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; double result; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_wavelength",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_wavelength" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; result = (double)cbf_handle_struct_get_wavelength(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_From_double((double)(result)); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_next_datablock(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_next_datablock",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_next_datablock" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_next_datablock(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_realarrayparameters_wdims(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int *arg2 = (int *) 0 ; int *arg3 = (int *) 0 ; int *arg4 = (int *) 0 ; int *arg5 = (int *) 0 ; char **arg6 = (char **) 0 ; int *arg7 = (int *) 0 ; int *arg8 = (int *) 0 ; int *arg9 = (int *) 0 ; int *arg10 = (int *) 0 ; int *arg11 = (int *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int temp2 ; int res2 = SWIG_TMPOBJ ; int temp3 ; int res3 = SWIG_TMPOBJ ; int temp4 ; int res4 = SWIG_TMPOBJ ; int temp5 ; int res5 = SWIG_TMPOBJ ; char *temp6 = 0 ; int tempn6 ; int temp8 ; int res8 = SWIG_TMPOBJ ; int temp9 ; int res9 = SWIG_TMPOBJ ; int temp10 ; int res10 = SWIG_TMPOBJ ; int temp11 ; int res11 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; arg5 = &temp5; arg6 = &temp6; arg7 = &tempn6; arg8 = &temp8; arg9 = &temp9; arg10 = &temp10; arg11 = &temp11; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_realarrayparameters_wdims",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_realarrayparameters_wdims" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_get_realarrayparameters_wdims(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9,arg10,arg11); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_int, new_flags)); } if (*arg6) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_FromCharPtrAndSize(*arg6,*arg7)); free(*arg6); } if (SWIG_IsTmpObj(res8)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg8))); } else { int new_flags = SWIG_IsNewObj(res8) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg8), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res9)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg9))); } else { int new_flags = SWIG_IsNewObj(res9) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg9), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res10)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg10))); } else { int new_flags = SWIG_IsNewObj(res10) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg10), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res11)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg11))); } else { int new_flags = SWIG_IsNewObj(res11) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg11), SWIGTYPE_p_int, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_orientation_matrix(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; double arg2 ; double arg3 ; double arg4 ; double arg5 ; double arg6 ; double arg7 ; double arg8 ; double arg9 ; double arg10 ; void *argp1 = 0 ; int res1 = 0 ; double val2 ; int ecode2 = 0 ; double val3 ; int ecode3 = 0 ; double val4 ; int ecode4 = 0 ; double val5 ; int ecode5 = 0 ; double val6 ; int ecode6 = 0 ; double val7 ; int ecode7 = 0 ; double val8 ; int ecode8 = 0 ; double val9 ; int ecode9 = 0 ; double val10 ; int ecode10 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; PyObject * obj6 = 0 ; PyObject * obj7 = 0 ; PyObject * obj8 = 0 ; PyObject * obj9 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOOOOOOO:cbf_handle_struct_set_orientation_matrix",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5,&obj6,&obj7,&obj8,&obj9)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_orientation_matrix" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_double(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_orientation_matrix" "', argument " "2"" of type '" "double""'"); } arg2 = (double)(val2); ecode3 = SWIG_AsVal_double(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_orientation_matrix" "', argument " "3"" of type '" "double""'"); } arg3 = (double)(val3); ecode4 = SWIG_AsVal_double(obj3, &val4); if (!SWIG_IsOK(ecode4)) { SWIG_exception_fail(SWIG_ArgError(ecode4), "in method '" "cbf_handle_struct_set_orientation_matrix" "', argument " "4"" of type '" "double""'"); } arg4 = (double)(val4); ecode5 = SWIG_AsVal_double(obj4, &val5); if (!SWIG_IsOK(ecode5)) { SWIG_exception_fail(SWIG_ArgError(ecode5), "in method '" "cbf_handle_struct_set_orientation_matrix" "', argument " "5"" of type '" "double""'"); } arg5 = (double)(val5); ecode6 = SWIG_AsVal_double(obj5, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_set_orientation_matrix" "', argument " "6"" of type '" "double""'"); } arg6 = (double)(val6); ecode7 = SWIG_AsVal_double(obj6, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_set_orientation_matrix" "', argument " "7"" of type '" "double""'"); } arg7 = (double)(val7); ecode8 = SWIG_AsVal_double(obj7, &val8); if (!SWIG_IsOK(ecode8)) { SWIG_exception_fail(SWIG_ArgError(ecode8), "in method '" "cbf_handle_struct_set_orientation_matrix" "', argument " "8"" of type '" "double""'"); } arg8 = (double)(val8); ecode9 = SWIG_AsVal_double(obj8, &val9); if (!SWIG_IsOK(ecode9)) { SWIG_exception_fail(SWIG_ArgError(ecode9), "in method '" "cbf_handle_struct_set_orientation_matrix" "', argument " "9"" of type '" "double""'"); } arg9 = (double)(val9); ecode10 = SWIG_AsVal_double(obj9, &val10); if (!SWIG_IsOK(ecode10)) { SWIG_exception_fail(SWIG_ArgError(ecode10), "in method '" "cbf_handle_struct_set_orientation_matrix" "', argument " "10"" of type '" "double""'"); } arg10 = (double)(val10); { error_status=0; cbf_handle_struct_set_orientation_matrix(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9,arg10); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_new_category(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_new_category",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_new_category" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_new_category" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; cbf_handle_struct_new_category(arg1,(char const *)arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_gain(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; double arg3 ; double arg4 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; double val3 ; int ecode3 = 0 ; double val4 ; int ecode4 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOO:cbf_handle_struct_set_gain",&obj0,&obj1,&obj2,&obj3)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_gain" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_gain" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_double(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_gain" "', argument " "3"" of type '" "double""'"); } arg3 = (double)(val3); ecode4 = SWIG_AsVal_double(obj3, &val4); if (!SWIG_IsOK(ecode4)) { SWIG_exception_fail(SWIG_ArgError(ecode4), "in method '" "cbf_handle_struct_set_gain" "', argument " "4"" of type '" "double""'"); } arg4 = (double)(val4); { error_status=0; cbf_handle_struct_set_gain(arg1,arg2,arg3,arg4); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_find_column(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_find_column",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_find_column" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_find_column" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; cbf_handle_struct_find_column(arg1,(char const *)arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_remove_category(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_remove_category",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_remove_category" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_remove_category(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_integerarrayparameters_wdims_sf(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int *arg2 = (int *) 0 ; int *arg3 = (int *) 0 ; int *arg4 = (int *) 0 ; int *arg5 = (int *) 0 ; int *arg6 = (int *) 0 ; int *arg7 = (int *) 0 ; int *arg8 = (int *) 0 ; int *arg9 = (int *) 0 ; char **arg10 = (char **) 0 ; int *arg11 = (int *) 0 ; int *arg12 = (int *) 0 ; int *arg13 = (int *) 0 ; int *arg14 = (int *) 0 ; int *arg15 = (int *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int temp2 ; int res2 = SWIG_TMPOBJ ; int temp3 ; int res3 = SWIG_TMPOBJ ; int temp4 ; int res4 = SWIG_TMPOBJ ; int temp5 ; int res5 = SWIG_TMPOBJ ; int temp6 ; int res6 = SWIG_TMPOBJ ; int temp7 ; int res7 = SWIG_TMPOBJ ; int temp8 ; int res8 = SWIG_TMPOBJ ; int temp9 ; int res9 = SWIG_TMPOBJ ; char *temp10 = 0 ; int tempn10 ; int temp12 ; int res12 = SWIG_TMPOBJ ; int temp13 ; int res13 = SWIG_TMPOBJ ; int temp14 ; int res14 = SWIG_TMPOBJ ; int temp15 ; int res15 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; arg5 = &temp5; arg6 = &temp6; arg7 = &temp7; arg8 = &temp8; arg9 = &temp9; arg10 = &temp10; arg11 = &tempn10; arg12 = &temp12; arg13 = &temp13; arg14 = &temp14; arg15 = &temp15; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_integerarrayparameters_wdims_sf",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_integerarrayparameters_wdims_sf" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_get_integerarrayparameters_wdims_sf(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9,arg10,arg11,arg12,arg13,arg14,arg15); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res6)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg6))); } else { int new_flags = SWIG_IsNewObj(res6) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg6), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res7)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg7))); } else { int new_flags = SWIG_IsNewObj(res7) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg7), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res8)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg8))); } else { int new_flags = SWIG_IsNewObj(res8) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg8), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res9)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg9))); } else { int new_flags = SWIG_IsNewObj(res9) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg9), SWIGTYPE_p_int, new_flags)); } if (*arg10) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_FromCharPtrAndSize(*arg10,*arg11)); free(*arg10); } if (SWIG_IsTmpObj(res12)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg12))); } else { int new_flags = SWIG_IsNewObj(res12) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg12), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res13)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg13))); } else { int new_flags = SWIG_IsNewObj(res13) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg13), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res14)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg14))); } else { int new_flags = SWIG_IsNewObj(res14) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg14), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res15)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg15))); } else { int new_flags = SWIG_IsNewObj(res15) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg15), SWIGTYPE_p_int, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_pixel_size(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; unsigned int arg3 ; double *arg4 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; unsigned int val3 ; int ecode3 = 0 ; double temp4 ; int res4 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; arg4 = &temp4; if (!PyArg_ParseTuple(args,(char *)"OOO:cbf_handle_struct_get_pixel_size",&obj0,&obj1,&obj2)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_pixel_size" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_get_pixel_size" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_unsigned_SS_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_get_pixel_size" "', argument " "3"" of type '" "unsigned int""'"); } arg3 = (unsigned int)(val3); { error_status=0; cbf_handle_struct_get_pixel_size(arg1,arg2,arg3,arg4); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_real_image_sf(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; unsigned int arg3 ; char *arg4 = (char *) 0 ; int arg5 ; int arg6 ; int arg7 ; int arg8 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; unsigned int val3 ; int ecode3 = 0 ; int res4 ; char *buf4 = 0 ; size_t size4 = 0 ; int alloc4 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int val8 ; int ecode8 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; PyObject * obj6 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOOOO:cbf_handle_struct_set_real_image_sf",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5,&obj6)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_real_image_sf" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_real_image_sf" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_unsigned_SS_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_real_image_sf" "', argument " "3"" of type '" "unsigned int""'"); } arg3 = (unsigned int)(val3); res4 = SWIG_AsCharPtrAndSize(obj3, &buf4, &size4, &alloc4); if (!SWIG_IsOK(res4)) { SWIG_exception_fail(SWIG_ArgError(res4), "in method '" "cbf_handle_struct_set_real_image_sf" "', argument " "4"" of type '" "char *""'"); } arg4 = (char *)(buf4); arg5 = (int)(size4 - 1); ecode6 = SWIG_AsVal_int(obj4, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_set_real_image_sf" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj5, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_set_real_image_sf" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); ecode8 = SWIG_AsVal_int(obj6, &val8); if (!SWIG_IsOK(ecode8)) { SWIG_exception_fail(SWIG_ArgError(ecode8), "in method '" "cbf_handle_struct_set_real_image_sf" "', argument " "8"" of type '" "int""'"); } arg8 = (int)(val8); { error_status=0; cbf_handle_struct_set_real_image_sf(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return resultobj; fail: if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_require_category(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_require_category",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_require_category" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_require_category" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; cbf_handle_struct_require_category(arg1,(char const *)arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_reciprocal_cell(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; double *arg2 = (double *) 0 ; double *arg3 = (double *) 0 ; double *arg4 = (double *) 0 ; double *arg5 = (double *) 0 ; double *arg6 = (double *) 0 ; double *arg7 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double temp2 ; int res2 = SWIG_TMPOBJ ; double temp3 ; int res3 = SWIG_TMPOBJ ; double temp4 ; int res4 = SWIG_TMPOBJ ; double temp5 ; int res5 = SWIG_TMPOBJ ; double temp6 ; int res6 = SWIG_TMPOBJ ; double temp7 ; int res7 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; arg5 = &temp5; arg6 = &temp6; arg7 = &temp7; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_reciprocal_cell",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_reciprocal_cell" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_get_reciprocal_cell(arg1,arg2,arg3,arg4,arg5,arg6,arg7); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res6)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg6))); } else { int new_flags = SWIG_IsNewObj(res6) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg6), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res7)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg7))); } else { int new_flags = SWIG_IsNewObj(res7) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg7), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_reciprocal_cell_esd(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; double *arg2 = (double *) 0 ; double *arg3 = (double *) 0 ; double *arg4 = (double *) 0 ; double *arg5 = (double *) 0 ; double *arg6 = (double *) 0 ; double *arg7 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double temp2 ; int res2 = SWIG_TMPOBJ ; double temp3 ; int res3 = SWIG_TMPOBJ ; double temp4 ; int res4 = SWIG_TMPOBJ ; double temp5 ; int res5 = SWIG_TMPOBJ ; double temp6 ; int res6 = SWIG_TMPOBJ ; double temp7 ; int res7 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; arg5 = &temp5; arg6 = &temp6; arg7 = &temp7; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_reciprocal_cell_esd",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_reciprocal_cell_esd" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_get_reciprocal_cell_esd(arg1,arg2,arg3,arg4,arg5,arg6,arg7); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res6)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg6))); } else { int new_flags = SWIG_IsNewObj(res6) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg6), SWIGTYPE_p_double, new_flags)); } if (SWIG_IsTmpObj(res7)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg7))); } else { int new_flags = SWIG_IsNewObj(res7) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg7), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_3d_image_size(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; int *arg3 = (int *) 0 ; int *arg4 = (int *) 0 ; int *arg5 = (int *) 0 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; int temp3 ; int res3 = SWIG_TMPOBJ ; int temp4 ; int res4 = SWIG_TMPOBJ ; int temp5 ; int res5 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; arg3 = &temp3; arg4 = &temp4; arg5 = &temp5; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_get_3d_image_size",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_3d_image_size" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_get_3d_image_size" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); { error_status=0; cbf_handle_struct_get_3d_image_size(arg1,arg2,arg3,arg4,arg5); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_int, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_find_tag_root(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; char *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_find_tag_root",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_find_tag_root" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_find_tag_root" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; result = (char *)cbf_handle_struct_find_tag_root(arg1,(char const *)arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_FromCharPtr((const char *)result); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_require_category_root(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; char *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_require_category_root",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_require_category_root" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_require_category_root" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; result = (char *)cbf_handle_struct_require_category_root(arg1,(char const *)arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_FromCharPtr((const char *)result); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_realarray_wdims_sf(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; int arg3 ; char *arg4 = (char *) 0 ; int arg5 ; int arg6 ; int arg7 ; char *arg8 = (char *) 0 ; int arg9 ; int arg10 ; int arg11 ; int arg12 ; int arg13 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; int val3 ; int ecode3 = 0 ; int res4 ; char *buf4 = 0 ; size_t size4 = 0 ; int alloc4 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int res8 ; char *buf8 = 0 ; size_t size8 = 0 ; int alloc8 = 0 ; int val10 ; int ecode10 = 0 ; int val11 ; int ecode11 = 0 ; int val12 ; int ecode12 = 0 ; int val13 ; int ecode13 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; PyObject * obj6 = 0 ; PyObject * obj7 = 0 ; PyObject * obj8 = 0 ; PyObject * obj9 = 0 ; PyObject * obj10 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOOOOOOOO:cbf_handle_struct_set_realarray_wdims_sf",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5,&obj6,&obj7,&obj8,&obj9,&obj10)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_realarray_wdims_sf" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_realarray_wdims_sf" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_realarray_wdims_sf" "', argument " "3"" of type '" "int""'"); } arg3 = (int)(val3); res4 = SWIG_AsCharPtrAndSize(obj3, &buf4, &size4, &alloc4); if (!SWIG_IsOK(res4)) { SWIG_exception_fail(SWIG_ArgError(res4), "in method '" "cbf_handle_struct_set_realarray_wdims_sf" "', argument " "4"" of type '" "char *""'"); } arg4 = (char *)(buf4); arg5 = (int)(size4 - 1); ecode6 = SWIG_AsVal_int(obj4, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_set_realarray_wdims_sf" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj5, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_set_realarray_wdims_sf" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); res8 = SWIG_AsCharPtrAndSize(obj6, &buf8, &size8, &alloc8); if (!SWIG_IsOK(res8)) { SWIG_exception_fail(SWIG_ArgError(res8), "in method '" "cbf_handle_struct_set_realarray_wdims_sf" "', argument " "8"" of type '" "char *""'"); } arg8 = (char *)(buf8); arg9 = (int)(size8 - 1); ecode10 = SWIG_AsVal_int(obj7, &val10); if (!SWIG_IsOK(ecode10)) { SWIG_exception_fail(SWIG_ArgError(ecode10), "in method '" "cbf_handle_struct_set_realarray_wdims_sf" "', argument " "10"" of type '" "int""'"); } arg10 = (int)(val10); ecode11 = SWIG_AsVal_int(obj8, &val11); if (!SWIG_IsOK(ecode11)) { SWIG_exception_fail(SWIG_ArgError(ecode11), "in method '" "cbf_handle_struct_set_realarray_wdims_sf" "', argument " "11"" of type '" "int""'"); } arg11 = (int)(val11); ecode12 = SWIG_AsVal_int(obj9, &val12); if (!SWIG_IsOK(ecode12)) { SWIG_exception_fail(SWIG_ArgError(ecode12), "in method '" "cbf_handle_struct_set_realarray_wdims_sf" "', argument " "12"" of type '" "int""'"); } arg12 = (int)(val12); ecode13 = SWIG_AsVal_int(obj10, &val13); if (!SWIG_IsOK(ecode13)) { SWIG_exception_fail(SWIG_ArgError(ecode13), "in method '" "cbf_handle_struct_set_realarray_wdims_sf" "', argument " "13"" of type '" "int""'"); } arg13 = (int)(val13); { error_status=0; cbf_handle_struct_set_realarray_wdims_sf(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9,arg10,arg11,arg12,arg13); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); if (alloc8 == SWIG_NEWOBJ) free((char*)buf8); return resultobj; fail: if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); if (alloc8 == SWIG_NEWOBJ) free((char*)buf8); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_integervalue(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int arg2 ; void *argp1 = 0 ; int res1 = 0 ; int val2 ; int ecode2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_set_integervalue",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_integervalue" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_integervalue" "', argument " "2"" of type '" "int""'"); } arg2 = (int)(val2); { error_status=0; cbf_handle_struct_set_integervalue(arg1,arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_category_name(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; char *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_category_name",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_category_name" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; result = (char *)cbf_handle_struct_category_name(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_FromCharPtr((const char *)result); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_typeofvalue(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; char *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_typeofvalue",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_typeofvalue" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; result = (char *)cbf_handle_struct_get_typeofvalue(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_FromCharPtr((const char *)result); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_real_image(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; unsigned int arg3 ; char *arg4 = (char *) 0 ; int arg5 ; int arg6 ; int arg7 ; int arg8 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; unsigned int val3 ; int ecode3 = 0 ; int res4 ; char *buf4 = 0 ; size_t size4 = 0 ; int alloc4 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int val8 ; int ecode8 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; PyObject * obj6 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOOOO:cbf_handle_struct_set_real_image",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5,&obj6)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_real_image" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_real_image" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_unsigned_SS_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_real_image" "', argument " "3"" of type '" "unsigned int""'"); } arg3 = (unsigned int)(val3); res4 = SWIG_AsCharPtrAndSize(obj3, &buf4, &size4, &alloc4); if (!SWIG_IsOK(res4)) { SWIG_exception_fail(SWIG_ArgError(res4), "in method '" "cbf_handle_struct_set_real_image" "', argument " "4"" of type '" "char *""'"); } arg4 = (char *)(buf4); arg5 = (int)(size4 - 1); ecode6 = SWIG_AsVal_int(obj4, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_set_real_image" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj5, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_set_real_image" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); ecode8 = SWIG_AsVal_int(obj6, &val8); if (!SWIG_IsOK(ecode8)) { SWIG_exception_fail(SWIG_ArgError(ecode8), "in method '" "cbf_handle_struct_set_real_image" "', argument " "8"" of type '" "int""'"); } arg8 = (int)(val8); { error_status=0; cbf_handle_struct_set_real_image(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return resultobj; fail: if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_3d_image_as_string(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int arg2 ; char **arg3 = (char **) 0 ; int *arg4 = (int *) 0 ; int arg5 ; int arg6 ; int arg7 ; int arg8 ; int arg9 ; void *argp1 = 0 ; int res1 = 0 ; int val2 ; int ecode2 = 0 ; char *temp3 = 0 ; int tempn3 ; int val5 ; int ecode5 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int val8 ; int ecode8 = 0 ; int val9 ; int ecode9 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; PyObject * obj6 = 0 ; arg3 = &temp3; arg4 = &tempn3; if (!PyArg_ParseTuple(args,(char *)"OOOOOOO:cbf_handle_struct_get_3d_image_as_string",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5,&obj6)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_3d_image_as_string" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_get_3d_image_as_string" "', argument " "2"" of type '" "int""'"); } arg2 = (int)(val2); ecode5 = SWIG_AsVal_int(obj2, &val5); if (!SWIG_IsOK(ecode5)) { SWIG_exception_fail(SWIG_ArgError(ecode5), "in method '" "cbf_handle_struct_get_3d_image_as_string" "', argument " "5"" of type '" "int""'"); } arg5 = (int)(val5); ecode6 = SWIG_AsVal_int(obj3, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_get_3d_image_as_string" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj4, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_get_3d_image_as_string" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); ecode8 = SWIG_AsVal_int(obj5, &val8); if (!SWIG_IsOK(ecode8)) { SWIG_exception_fail(SWIG_ArgError(ecode8), "in method '" "cbf_handle_struct_get_3d_image_as_string" "', argument " "8"" of type '" "int""'"); } arg8 = (int)(val8); ecode9 = SWIG_AsVal_int(obj6, &val9); if (!SWIG_IsOK(ecode9)) { SWIG_exception_fail(SWIG_ArgError(ecode9), "in method '" "cbf_handle_struct_get_3d_image_as_string" "', argument " "9"" of type '" "int""'"); } arg9 = (int)(val9); { error_status=0; cbf_handle_struct_get_3d_image_as_string(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (*arg3) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_FromCharPtrAndSize(*arg3,*arg4)); free(*arg3); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_remove_row(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_remove_row",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_remove_row" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_remove_row(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_overload(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; double arg3 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; double val3 ; int ecode3 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOO:cbf_handle_struct_set_overload",&obj0,&obj1,&obj2)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_overload" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_overload" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_double(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_overload" "', argument " "3"" of type '" "double""'"); } arg3 = (double)(val3); { error_status=0; cbf_handle_struct_set_overload(arg1,arg2,arg3); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_image_size(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; int *arg3 = (int *) 0 ; int *arg4 = (int *) 0 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; int temp3 ; int res3 = SWIG_TMPOBJ ; int temp4 ; int res4 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; arg3 = &temp3; arg4 = &temp4; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_get_image_size",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_image_size" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_get_image_size" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); { error_status=0; cbf_handle_struct_get_image_size(arg1,arg2,arg3,arg4); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_int, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_3d_image_sf(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; unsigned int arg3 ; char *arg4 = (char *) 0 ; int arg5 ; int arg6 ; int arg7 ; int arg8 ; int arg9 ; int arg10 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; unsigned int val3 ; int ecode3 = 0 ; int res4 ; char *buf4 = 0 ; size_t size4 = 0 ; int alloc4 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int val8 ; int ecode8 = 0 ; int val9 ; int ecode9 = 0 ; int val10 ; int ecode10 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; PyObject * obj6 = 0 ; PyObject * obj7 = 0 ; PyObject * obj8 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOOOOOO:cbf_handle_struct_set_3d_image_sf",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5,&obj6,&obj7,&obj8)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_3d_image_sf" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_3d_image_sf" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_unsigned_SS_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_3d_image_sf" "', argument " "3"" of type '" "unsigned int""'"); } arg3 = (unsigned int)(val3); res4 = SWIG_AsCharPtrAndSize(obj3, &buf4, &size4, &alloc4); if (!SWIG_IsOK(res4)) { SWIG_exception_fail(SWIG_ArgError(res4), "in method '" "cbf_handle_struct_set_3d_image_sf" "', argument " "4"" of type '" "char *""'"); } arg4 = (char *)(buf4); arg5 = (int)(size4 - 1); ecode6 = SWIG_AsVal_int(obj4, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_set_3d_image_sf" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj5, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_set_3d_image_sf" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); ecode8 = SWIG_AsVal_int(obj6, &val8); if (!SWIG_IsOK(ecode8)) { SWIG_exception_fail(SWIG_ArgError(ecode8), "in method '" "cbf_handle_struct_set_3d_image_sf" "', argument " "8"" of type '" "int""'"); } arg8 = (int)(val8); ecode9 = SWIG_AsVal_int(obj7, &val9); if (!SWIG_IsOK(ecode9)) { SWIG_exception_fail(SWIG_ArgError(ecode9), "in method '" "cbf_handle_struct_set_3d_image_sf" "', argument " "9"" of type '" "int""'"); } arg9 = (int)(val9); ecode10 = SWIG_AsVal_int(obj8, &val10); if (!SWIG_IsOK(ecode10)) { SWIG_exception_fail(SWIG_ArgError(ecode10), "in method '" "cbf_handle_struct_set_3d_image_sf" "', argument " "10"" of type '" "int""'"); } arg10 = (int)(val10); { error_status=0; cbf_handle_struct_set_3d_image_sf(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9,arg10); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return resultobj; fail: if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_real_image_sf_as_string(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int arg2 ; char **arg3 = (char **) 0 ; int *arg4 = (int *) 0 ; int arg5 ; int arg6 ; int arg7 ; void *argp1 = 0 ; int res1 = 0 ; int val2 ; int ecode2 = 0 ; char *temp3 = 0 ; int tempn3 ; int val5 ; int ecode5 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; arg3 = &temp3; arg4 = &tempn3; if (!PyArg_ParseTuple(args,(char *)"OOOOO:cbf_handle_struct_get_real_image_sf_as_string",&obj0,&obj1,&obj2,&obj3,&obj4)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_real_image_sf_as_string" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_get_real_image_sf_as_string" "', argument " "2"" of type '" "int""'"); } arg2 = (int)(val2); ecode5 = SWIG_AsVal_int(obj2, &val5); if (!SWIG_IsOK(ecode5)) { SWIG_exception_fail(SWIG_ArgError(ecode5), "in method '" "cbf_handle_struct_get_real_image_sf_as_string" "', argument " "5"" of type '" "int""'"); } arg5 = (int)(val5); ecode6 = SWIG_AsVal_int(obj3, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_get_real_image_sf_as_string" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj4, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_get_real_image_sf_as_string" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); { error_status=0; cbf_handle_struct_get_real_image_sf_as_string(arg1,arg2,arg3,arg4,arg5,arg6,arg7); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (*arg3) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_FromCharPtrAndSize(*arg3,*arg4)); free(*arg3); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_image_as_string(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int arg2 ; char **arg3 = (char **) 0 ; int *arg4 = (int *) 0 ; int arg5 ; int arg6 ; int arg7 ; int arg8 ; void *argp1 = 0 ; int res1 = 0 ; int val2 ; int ecode2 = 0 ; char *temp3 = 0 ; int tempn3 ; int val5 ; int ecode5 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int val8 ; int ecode8 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; arg3 = &temp3; arg4 = &tempn3; if (!PyArg_ParseTuple(args,(char *)"OOOOOO:cbf_handle_struct_get_image_as_string",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_image_as_string" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_get_image_as_string" "', argument " "2"" of type '" "int""'"); } arg2 = (int)(val2); ecode5 = SWIG_AsVal_int(obj2, &val5); if (!SWIG_IsOK(ecode5)) { SWIG_exception_fail(SWIG_ArgError(ecode5), "in method '" "cbf_handle_struct_get_image_as_string" "', argument " "5"" of type '" "int""'"); } arg5 = (int)(val5); ecode6 = SWIG_AsVal_int(obj3, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_get_image_as_string" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj4, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_get_image_as_string" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); ecode8 = SWIG_AsVal_int(obj5, &val8); if (!SWIG_IsOK(ecode8)) { SWIG_exception_fail(SWIG_ArgError(ecode8), "in method '" "cbf_handle_struct_get_image_as_string" "', argument " "8"" of type '" "int""'"); } arg8 = (int)(val8); { error_status=0; cbf_handle_struct_get_image_as_string(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (*arg3) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_FromCharPtrAndSize(*arg3,*arg4)); free(*arg3); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_tag_root(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; char *arg3 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; int res3 ; char *buf3 = 0 ; int alloc3 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOO:cbf_handle_struct_set_tag_root",&obj0,&obj1,&obj2)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_tag_root" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_set_tag_root" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); res3 = SWIG_AsCharPtrAndSize(obj2, &buf3, NULL, &alloc3); if (!SWIG_IsOK(res3)) { SWIG_exception_fail(SWIG_ArgError(res3), "in method '" "cbf_handle_struct_set_tag_root" "', argument " "3"" of type '" "char const *""'"); } arg3 = (char *)(buf3); { error_status=0; cbf_handle_struct_set_tag_root(arg1,(char const *)arg2,(char const *)arg3); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); if (alloc3 == SWIG_NEWOBJ) free((char*)buf3); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); if (alloc3 == SWIG_NEWOBJ) free((char*)buf3); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_write_widefile(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; int arg3 ; int arg4 ; int arg5 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; int val3 ; int ecode3 = 0 ; int val4 ; int ecode4 = 0 ; int val5 ; int ecode5 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOO:cbf_handle_struct_write_widefile",&obj0,&obj1,&obj2,&obj3,&obj4)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_write_widefile" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_write_widefile" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); ecode3 = SWIG_AsVal_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_write_widefile" "', argument " "3"" of type '" "int""'"); } arg3 = (int)(val3); ecode4 = SWIG_AsVal_int(obj3, &val4); if (!SWIG_IsOK(ecode4)) { SWIG_exception_fail(SWIG_ArgError(ecode4), "in method '" "cbf_handle_struct_write_widefile" "', argument " "4"" of type '" "int""'"); } arg4 = (int)(val4); ecode5 = SWIG_AsVal_int(obj4, &val5); if (!SWIG_IsOK(ecode5)) { SWIG_exception_fail(SWIG_ArgError(ecode5), "in method '" "cbf_handle_struct_write_widefile" "', argument " "5"" of type '" "int""'"); } arg5 = (int)(val5); { error_status=0; cbf_handle_struct_write_widefile(arg1,(char const *)arg2,arg3,arg4,arg5); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_count_rows(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; unsigned int result; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_count_rows",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_count_rows" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; result = (unsigned int)cbf_handle_struct_count_rows(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_From_unsigned_SS_int((unsigned int)(result)); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_require_datablock(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_require_datablock",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_require_datablock" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_require_datablock" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; cbf_handle_struct_require_datablock(arg1,(char const *)arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_integerarray(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; int arg3 ; char *arg4 = (char *) 0 ; int arg5 ; int arg6 ; int arg7 ; int arg8 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; int val3 ; int ecode3 = 0 ; int res4 ; char *buf4 = 0 ; size_t size4 = 0 ; int alloc4 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int val8 ; int ecode8 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; PyObject * obj6 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOOOO:cbf_handle_struct_set_integerarray",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5,&obj6)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_integerarray" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_integerarray" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_integerarray" "', argument " "3"" of type '" "int""'"); } arg3 = (int)(val3); res4 = SWIG_AsCharPtrAndSize(obj3, &buf4, &size4, &alloc4); if (!SWIG_IsOK(res4)) { SWIG_exception_fail(SWIG_ArgError(res4), "in method '" "cbf_handle_struct_set_integerarray" "', argument " "4"" of type '" "char *""'"); } arg4 = (char *)(buf4); arg5 = (int)(size4 - 1); ecode6 = SWIG_AsVal_int(obj4, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_set_integerarray" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj5, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_set_integerarray" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); ecode8 = SWIG_AsVal_int(obj6, &val8); if (!SWIG_IsOK(ecode8)) { SWIG_exception_fail(SWIG_ArgError(ecode8), "in method '" "cbf_handle_struct_set_integerarray" "', argument " "8"" of type '" "int""'"); } arg8 = (int)(val8); { error_status=0; cbf_handle_struct_set_integerarray(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return resultobj; fail: if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_new_datablock(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_new_datablock",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_new_datablock" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_new_datablock" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; cbf_handle_struct_new_datablock(arg1,(char const *)arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_datestamp(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int arg2 ; int arg3 ; int arg4 ; int arg5 ; int arg6 ; double arg7 ; int arg8 ; double arg9 ; void *argp1 = 0 ; int res1 = 0 ; int val2 ; int ecode2 = 0 ; int val3 ; int ecode3 = 0 ; int val4 ; int ecode4 = 0 ; int val5 ; int ecode5 = 0 ; int val6 ; int ecode6 = 0 ; double val7 ; int ecode7 = 0 ; int val8 ; int ecode8 = 0 ; double val9 ; int ecode9 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; PyObject * obj6 = 0 ; PyObject * obj7 = 0 ; PyObject * obj8 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOOOOOO:cbf_handle_struct_set_datestamp",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5,&obj6,&obj7,&obj8)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_datestamp" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_datestamp" "', argument " "2"" of type '" "int""'"); } arg2 = (int)(val2); ecode3 = SWIG_AsVal_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_datestamp" "', argument " "3"" of type '" "int""'"); } arg3 = (int)(val3); ecode4 = SWIG_AsVal_int(obj3, &val4); if (!SWIG_IsOK(ecode4)) { SWIG_exception_fail(SWIG_ArgError(ecode4), "in method '" "cbf_handle_struct_set_datestamp" "', argument " "4"" of type '" "int""'"); } arg4 = (int)(val4); ecode5 = SWIG_AsVal_int(obj4, &val5); if (!SWIG_IsOK(ecode5)) { SWIG_exception_fail(SWIG_ArgError(ecode5), "in method '" "cbf_handle_struct_set_datestamp" "', argument " "5"" of type '" "int""'"); } arg5 = (int)(val5); ecode6 = SWIG_AsVal_int(obj5, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_set_datestamp" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_double(obj6, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_set_datestamp" "', argument " "7"" of type '" "double""'"); } arg7 = (double)(val7); ecode8 = SWIG_AsVal_int(obj7, &val8); if (!SWIG_IsOK(ecode8)) { SWIG_exception_fail(SWIG_ArgError(ecode8), "in method '" "cbf_handle_struct_set_datestamp" "', argument " "8"" of type '" "int""'"); } arg8 = (int)(val8); ecode9 = SWIG_AsVal_double(obj8, &val9); if (!SWIG_IsOK(ecode9)) { SWIG_exception_fail(SWIG_ArgError(ecode9), "in method '" "cbf_handle_struct_set_datestamp" "', argument " "9"" of type '" "double""'"); } arg9 = (double)(val9); { error_status=0; cbf_handle_struct_set_datestamp(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_next_row(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_next_row",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_next_row" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_next_row(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_category_root(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; char *arg3 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; int res3 ; char *buf3 = 0 ; int alloc3 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOO:cbf_handle_struct_set_category_root",&obj0,&obj1,&obj2)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_category_root" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_set_category_root" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); res3 = SWIG_AsCharPtrAndSize(obj2, &buf3, NULL, &alloc3); if (!SWIG_IsOK(res3)) { SWIG_exception_fail(SWIG_ArgError(res3), "in method '" "cbf_handle_struct_set_category_root" "', argument " "3"" of type '" "char const *""'"); } arg3 = (char *)(buf3); { error_status=0; cbf_handle_struct_set_category_root(arg1,(char const *)arg2,(char const *)arg3); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); if (alloc3 == SWIG_NEWOBJ) free((char*)buf3); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); if (alloc3 == SWIG_NEWOBJ) free((char*)buf3); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_pixel_size_fs(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; unsigned int arg3 ; double arg4 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; unsigned int val3 ; int ecode3 = 0 ; double val4 ; int ecode4 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOO:cbf_handle_struct_set_pixel_size_fs",&obj0,&obj1,&obj2,&obj3)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_pixel_size_fs" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_pixel_size_fs" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_unsigned_SS_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_pixel_size_fs" "', argument " "3"" of type '" "unsigned int""'"); } arg3 = (unsigned int)(val3); ecode4 = SWIG_AsVal_double(obj3, &val4); if (!SWIG_IsOK(ecode4)) { SWIG_exception_fail(SWIG_ArgError(ecode4), "in method '" "cbf_handle_struct_set_pixel_size_fs" "', argument " "4"" of type '" "double""'"); } arg4 = (double)(val4); { error_status=0; cbf_handle_struct_set_pixel_size_fs(arg1,arg2,arg3,arg4); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_insert_row(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_insert_row",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_insert_row" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_insert_row" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); { error_status=0; cbf_handle_struct_insert_row(arg1,arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_new_column(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_new_column",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_new_column" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_new_column" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; cbf_handle_struct_new_column(arg1,(char const *)arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_real_3d_image_as_string(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int arg2 ; char **arg3 = (char **) 0 ; int *arg4 = (int *) 0 ; int arg5 ; int arg6 ; int arg7 ; int arg8 ; void *argp1 = 0 ; int res1 = 0 ; int val2 ; int ecode2 = 0 ; char *temp3 = 0 ; int tempn3 ; int val5 ; int ecode5 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int val8 ; int ecode8 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; arg3 = &temp3; arg4 = &tempn3; if (!PyArg_ParseTuple(args,(char *)"OOOOOO:cbf_handle_struct_get_real_3d_image_as_string",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_real_3d_image_as_string" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_get_real_3d_image_as_string" "', argument " "2"" of type '" "int""'"); } arg2 = (int)(val2); ecode5 = SWIG_AsVal_int(obj2, &val5); if (!SWIG_IsOK(ecode5)) { SWIG_exception_fail(SWIG_ArgError(ecode5), "in method '" "cbf_handle_struct_get_real_3d_image_as_string" "', argument " "5"" of type '" "int""'"); } arg5 = (int)(val5); ecode6 = SWIG_AsVal_int(obj3, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_get_real_3d_image_as_string" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj4, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_get_real_3d_image_as_string" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); ecode8 = SWIG_AsVal_int(obj5, &val8); if (!SWIG_IsOK(ecode8)) { SWIG_exception_fail(SWIG_ArgError(ecode8), "in method '" "cbf_handle_struct_get_real_3d_image_as_string" "', argument " "8"" of type '" "int""'"); } arg8 = (int)(val8); { error_status=0; cbf_handle_struct_get_real_3d_image_as_string(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (*arg3) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_FromCharPtrAndSize(*arg3,*arg4)); free(*arg3); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_integration_time(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; double *arg2 = (double *) 0 ; void *argp1 = 0 ; int res1 = 0 ; double temp2 ; int res2 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_integration_time",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_integration_time" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_get_integration_time(arg1,arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_realarray(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; int arg3 ; char *arg4 = (char *) 0 ; int arg5 ; int arg6 ; int arg7 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; int val3 ; int ecode3 = 0 ; int res4 ; char *buf4 = 0 ; size_t size4 = 0 ; int alloc4 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOOO:cbf_handle_struct_set_realarray",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_realarray" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_realarray" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_realarray" "', argument " "3"" of type '" "int""'"); } arg3 = (int)(val3); res4 = SWIG_AsCharPtrAndSize(obj3, &buf4, &size4, &alloc4); if (!SWIG_IsOK(res4)) { SWIG_exception_fail(SWIG_ArgError(res4), "in method '" "cbf_handle_struct_set_realarray" "', argument " "4"" of type '" "char *""'"); } arg4 = (char *)(buf4); arg5 = (int)(size4 - 1); ecode6 = SWIG_AsVal_int(obj4, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_set_realarray" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj5, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_set_realarray" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); { error_status=0; cbf_handle_struct_set_realarray(arg1,arg2,arg3,arg4,arg5,arg6,arg7); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return resultobj; fail: if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_element_id(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; char *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_get_element_id",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_element_id" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_get_element_id" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); { error_status=0; result = (char *)cbf_handle_struct_get_element_id(arg1,arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_FromCharPtr((const char *)result); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_image_sf_as_string(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int arg2 ; char **arg3 = (char **) 0 ; int *arg4 = (int *) 0 ; int arg5 ; int arg6 ; int arg7 ; int arg8 ; void *argp1 = 0 ; int res1 = 0 ; int val2 ; int ecode2 = 0 ; char *temp3 = 0 ; int tempn3 ; int val5 ; int ecode5 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int val8 ; int ecode8 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; arg3 = &temp3; arg4 = &tempn3; if (!PyArg_ParseTuple(args,(char *)"OOOOOO:cbf_handle_struct_get_image_sf_as_string",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_image_sf_as_string" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_get_image_sf_as_string" "', argument " "2"" of type '" "int""'"); } arg2 = (int)(val2); ecode5 = SWIG_AsVal_int(obj2, &val5); if (!SWIG_IsOK(ecode5)) { SWIG_exception_fail(SWIG_ArgError(ecode5), "in method '" "cbf_handle_struct_get_image_sf_as_string" "', argument " "5"" of type '" "int""'"); } arg5 = (int)(val5); ecode6 = SWIG_AsVal_int(obj3, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_get_image_sf_as_string" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj4, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_get_image_sf_as_string" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); ecode8 = SWIG_AsVal_int(obj5, &val8); if (!SWIG_IsOK(ecode8)) { SWIG_exception_fail(SWIG_ArgError(ecode8), "in method '" "cbf_handle_struct_get_image_sf_as_string" "', argument " "8"" of type '" "int""'"); } arg8 = (int)(val8); { error_status=0; cbf_handle_struct_get_image_sf_as_string(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (*arg3) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_FromCharPtrAndSize(*arg3,*arg4)); free(*arg3); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_3d_image_size_fs(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; int *arg3 = (int *) 0 ; int *arg4 = (int *) 0 ; int *arg5 = (int *) 0 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; int temp3 ; int res3 = SWIG_TMPOBJ ; int temp4 ; int res4 = SWIG_TMPOBJ ; int temp5 ; int res5 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; arg3 = &temp3; arg4 = &temp4; arg5 = &temp5; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_get_3d_image_size_fs",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_3d_image_size_fs" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_get_3d_image_size_fs" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); { error_status=0; cbf_handle_struct_get_3d_image_size_fs(arg1,arg2,arg3,arg4,arg5); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_int, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_value(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_set_value",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_value" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_set_value" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; cbf_handle_struct_set_value(arg1,(char const *)arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_current_timestamp(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int arg2 ; void *argp1 = 0 ; int res1 = 0 ; int val2 ; int ecode2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_set_current_timestamp",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_current_timestamp" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_current_timestamp" "', argument " "2"" of type '" "int""'"); } arg2 = (int)(val2); { error_status=0; cbf_handle_struct_set_current_timestamp(arg1,arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_require_doublevalue(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; double *arg2 = (double *) 0 ; double arg3 ; void *argp1 = 0 ; int res1 = 0 ; double temp2 ; int res2 = SWIG_TMPOBJ ; double val3 ; int ecode3 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; arg2 = &temp2; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_require_doublevalue",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_require_doublevalue" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode3 = SWIG_AsVal_double(obj1, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_require_doublevalue" "', argument " "3"" of type '" "double""'"); } arg3 = (double)(val3); { error_status=0; cbf_handle_struct_require_doublevalue(arg1,arg2,arg3); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_double((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_double, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_rewind_datablock(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_rewind_datablock",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_rewind_datablock" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_rewind_datablock(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_require_column_value(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; char *arg3 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; int res3 ; char *buf3 = 0 ; int alloc3 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; char *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOO:cbf_handle_struct_require_column_value",&obj0,&obj1,&obj2)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_require_column_value" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_require_column_value" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); res3 = SWIG_AsCharPtrAndSize(obj2, &buf3, NULL, &alloc3); if (!SWIG_IsOK(res3)) { SWIG_exception_fail(SWIG_ArgError(res3), "in method '" "cbf_handle_struct_require_column_value" "', argument " "3"" of type '" "char const *""'"); } arg3 = (char *)(buf3); { error_status=0; result = (char *)cbf_handle_struct_require_column_value(arg1,(char const *)arg2,(char const *)arg3); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_FromCharPtr((const char *)result); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); if (alloc3 == SWIG_NEWOBJ) free((char*)buf3); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); if (alloc3 == SWIG_NEWOBJ) free((char*)buf3); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_dictionary(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; cbf_handle result; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_dictionary",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_dictionary" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; result = (cbf_handle)cbf_handle_struct_get_dictionary(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_NewPointerObj(SWIG_as_voidptr(result), SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_reset_saveframe(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; void *argp1 = 0 ; int res1 = 0 ; PyObject * obj0 = 0 ; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_reset_saveframe",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_reset_saveframe" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_reset_saveframe(arg1); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_reciprocal_cell(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; double *arg2 ; void *argp1 = 0 ; int res1 = 0 ; double temp2[6] ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_set_reciprocal_cell",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_reciprocal_cell" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { if (obj1 == Py_None) arg2 = NULL; else if (!convert_darray(obj1,temp2,6)) { return NULL; } arg2 = &temp2[0]; } { error_status=0; cbf_handle_struct_set_reciprocal_cell(arg1,arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_reciprocal_cell_esd(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; double *arg2 ; void *argp1 = 0 ; int res1 = 0 ; double temp2[6] ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_set_reciprocal_cell_esd",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_reciprocal_cell_esd" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { if (obj1 == Py_None) arg2 = NULL; else if (!convert_darray(obj1,temp2,6)) { return NULL; } arg2 = &temp2[0]; } { error_status=0; cbf_handle_struct_set_reciprocal_cell_esd(arg1,arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_real_3d_image_fs(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; unsigned int arg3 ; char *arg4 = (char *) 0 ; int arg5 ; int arg6 ; int arg7 ; int arg8 ; int arg9 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; unsigned int val3 ; int ecode3 = 0 ; int res4 ; char *buf4 = 0 ; size_t size4 = 0 ; int alloc4 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int val8 ; int ecode8 = 0 ; int val9 ; int ecode9 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; PyObject * obj6 = 0 ; PyObject * obj7 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOOOOO:cbf_handle_struct_set_real_3d_image_fs",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5,&obj6,&obj7)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_real_3d_image_fs" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_real_3d_image_fs" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_unsigned_SS_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_real_3d_image_fs" "', argument " "3"" of type '" "unsigned int""'"); } arg3 = (unsigned int)(val3); res4 = SWIG_AsCharPtrAndSize(obj3, &buf4, &size4, &alloc4); if (!SWIG_IsOK(res4)) { SWIG_exception_fail(SWIG_ArgError(res4), "in method '" "cbf_handle_struct_set_real_3d_image_fs" "', argument " "4"" of type '" "char *""'"); } arg4 = (char *)(buf4); arg5 = (int)(size4 - 1); ecode6 = SWIG_AsVal_int(obj4, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_set_real_3d_image_fs" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj5, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_set_real_3d_image_fs" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); ecode8 = SWIG_AsVal_int(obj6, &val8); if (!SWIG_IsOK(ecode8)) { SWIG_exception_fail(SWIG_ArgError(ecode8), "in method '" "cbf_handle_struct_set_real_3d_image_fs" "', argument " "8"" of type '" "int""'"); } arg8 = (int)(val8); ecode9 = SWIG_AsVal_int(obj7, &val9); if (!SWIG_IsOK(ecode9)) { SWIG_exception_fail(SWIG_ArgError(ecode9), "in method '" "cbf_handle_struct_set_real_3d_image_fs" "', argument " "9"" of type '" "int""'"); } arg9 = (int)(val9); { error_status=0; cbf_handle_struct_set_real_3d_image_fs(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return resultobj; fail: if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_doublevalue(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; double arg3 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; double val3 ; int ecode3 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOO:cbf_handle_struct_set_doublevalue",&obj0,&obj1,&obj2)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_doublevalue" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_set_doublevalue" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); ecode3 = SWIG_AsVal_double(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_doublevalue" "', argument " "3"" of type '" "double""'"); } arg3 = (double)(val3); { error_status=0; cbf_handle_struct_set_doublevalue(arg1,(char const *)arg2,arg3); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_find_category(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_find_category",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_find_category" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_find_category" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; cbf_handle_struct_find_category(arg1,(char const *)arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_get_integerarrayparameters_wdims_fs(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; int *arg2 = (int *) 0 ; int *arg3 = (int *) 0 ; int *arg4 = (int *) 0 ; int *arg5 = (int *) 0 ; int *arg6 = (int *) 0 ; int *arg7 = (int *) 0 ; int *arg8 = (int *) 0 ; int *arg9 = (int *) 0 ; char **arg10 = (char **) 0 ; int *arg11 = (int *) 0 ; int *arg12 = (int *) 0 ; int *arg13 = (int *) 0 ; int *arg14 = (int *) 0 ; int *arg15 = (int *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int temp2 ; int res2 = SWIG_TMPOBJ ; int temp3 ; int res3 = SWIG_TMPOBJ ; int temp4 ; int res4 = SWIG_TMPOBJ ; int temp5 ; int res5 = SWIG_TMPOBJ ; int temp6 ; int res6 = SWIG_TMPOBJ ; int temp7 ; int res7 = SWIG_TMPOBJ ; int temp8 ; int res8 = SWIG_TMPOBJ ; int temp9 ; int res9 = SWIG_TMPOBJ ; char *temp10 = 0 ; int tempn10 ; int temp12 ; int res12 = SWIG_TMPOBJ ; int temp13 ; int res13 = SWIG_TMPOBJ ; int temp14 ; int res14 = SWIG_TMPOBJ ; int temp15 ; int res15 = SWIG_TMPOBJ ; PyObject * obj0 = 0 ; arg2 = &temp2; arg3 = &temp3; arg4 = &temp4; arg5 = &temp5; arg6 = &temp6; arg7 = &temp7; arg8 = &temp8; arg9 = &temp9; arg10 = &temp10; arg11 = &tempn10; arg12 = &temp12; arg13 = &temp13; arg14 = &temp14; arg15 = &temp15; if (!PyArg_ParseTuple(args,(char *)"O:cbf_handle_struct_get_integerarrayparameters_wdims_fs",&obj0)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_get_integerarrayparameters_wdims_fs" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { error_status=0; cbf_handle_struct_get_integerarrayparameters_wdims_fs(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9,arg10,arg11,arg12,arg13,arg14,arg15); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (SWIG_IsTmpObj(res2)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg2))); } else { int new_flags = SWIG_IsNewObj(res2) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg2), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res3)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg3))); } else { int new_flags = SWIG_IsNewObj(res3) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg3), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res4)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg4))); } else { int new_flags = SWIG_IsNewObj(res4) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg4), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res5)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg5))); } else { int new_flags = SWIG_IsNewObj(res5) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg5), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res6)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg6))); } else { int new_flags = SWIG_IsNewObj(res6) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg6), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res7)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg7))); } else { int new_flags = SWIG_IsNewObj(res7) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg7), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res8)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg8))); } else { int new_flags = SWIG_IsNewObj(res8) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg8), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res9)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg9))); } else { int new_flags = SWIG_IsNewObj(res9) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg9), SWIGTYPE_p_int, new_flags)); } if (*arg10) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_FromCharPtrAndSize(*arg10,*arg11)); free(*arg10); } if (SWIG_IsTmpObj(res12)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg12))); } else { int new_flags = SWIG_IsNewObj(res12) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg12), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res13)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg13))); } else { int new_flags = SWIG_IsNewObj(res13) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg13), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res14)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg14))); } else { int new_flags = SWIG_IsNewObj(res14) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg14), SWIGTYPE_p_int, new_flags)); } if (SWIG_IsTmpObj(res15)) { resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_From_int((*arg15))); } else { int new_flags = SWIG_IsNewObj(res15) ? (SWIG_POINTER_OWN | 0 ) : 0 ; resultobj = SWIG_Python_AppendOutput(resultobj, SWIG_NewPointerObj((void*)(arg15), SWIGTYPE_p_int, new_flags)); } return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_realarray_wdims_fs(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; int arg3 ; char *arg4 = (char *) 0 ; int arg5 ; int arg6 ; int arg7 ; char *arg8 = (char *) 0 ; int arg9 ; int arg10 ; int arg11 ; int arg12 ; int arg13 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; int val3 ; int ecode3 = 0 ; int res4 ; char *buf4 = 0 ; size_t size4 = 0 ; int alloc4 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int res8 ; char *buf8 = 0 ; size_t size8 = 0 ; int alloc8 = 0 ; int val10 ; int ecode10 = 0 ; int val11 ; int ecode11 = 0 ; int val12 ; int ecode12 = 0 ; int val13 ; int ecode13 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; PyObject * obj6 = 0 ; PyObject * obj7 = 0 ; PyObject * obj8 = 0 ; PyObject * obj9 = 0 ; PyObject * obj10 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOOOOOOOO:cbf_handle_struct_set_realarray_wdims_fs",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5,&obj6,&obj7,&obj8,&obj9,&obj10)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_realarray_wdims_fs" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_realarray_wdims_fs" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_realarray_wdims_fs" "', argument " "3"" of type '" "int""'"); } arg3 = (int)(val3); res4 = SWIG_AsCharPtrAndSize(obj3, &buf4, &size4, &alloc4); if (!SWIG_IsOK(res4)) { SWIG_exception_fail(SWIG_ArgError(res4), "in method '" "cbf_handle_struct_set_realarray_wdims_fs" "', argument " "4"" of type '" "char *""'"); } arg4 = (char *)(buf4); arg5 = (int)(size4 - 1); ecode6 = SWIG_AsVal_int(obj4, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_set_realarray_wdims_fs" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj5, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_set_realarray_wdims_fs" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); res8 = SWIG_AsCharPtrAndSize(obj6, &buf8, &size8, &alloc8); if (!SWIG_IsOK(res8)) { SWIG_exception_fail(SWIG_ArgError(res8), "in method '" "cbf_handle_struct_set_realarray_wdims_fs" "', argument " "8"" of type '" "char *""'"); } arg8 = (char *)(buf8); arg9 = (int)(size8 - 1); ecode10 = SWIG_AsVal_int(obj7, &val10); if (!SWIG_IsOK(ecode10)) { SWIG_exception_fail(SWIG_ArgError(ecode10), "in method '" "cbf_handle_struct_set_realarray_wdims_fs" "', argument " "10"" of type '" "int""'"); } arg10 = (int)(val10); ecode11 = SWIG_AsVal_int(obj8, &val11); if (!SWIG_IsOK(ecode11)) { SWIG_exception_fail(SWIG_ArgError(ecode11), "in method '" "cbf_handle_struct_set_realarray_wdims_fs" "', argument " "11"" of type '" "int""'"); } arg11 = (int)(val11); ecode12 = SWIG_AsVal_int(obj9, &val12); if (!SWIG_IsOK(ecode12)) { SWIG_exception_fail(SWIG_ArgError(ecode12), "in method '" "cbf_handle_struct_set_realarray_wdims_fs" "', argument " "12"" of type '" "int""'"); } arg12 = (int)(val12); ecode13 = SWIG_AsVal_int(obj10, &val13); if (!SWIG_IsOK(ecode13)) { SWIG_exception_fail(SWIG_ArgError(ecode13), "in method '" "cbf_handle_struct_set_realarray_wdims_fs" "', argument " "13"" of type '" "int""'"); } arg13 = (int)(val13); { error_status=0; cbf_handle_struct_set_realarray_wdims_fs(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9,arg10,arg11,arg12,arg13); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); if (alloc8 == SWIG_NEWOBJ) free((char*)buf8); return resultobj; fail: if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); if (alloc8 == SWIG_NEWOBJ) free((char*)buf8); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_find_category_root(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; char *arg2 = (char *) 0 ; void *argp1 = 0 ; int res1 = 0 ; int res2 ; char *buf2 = 0 ; int alloc2 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; char *result = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_find_category_root",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_find_category_root" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); res2 = SWIG_AsCharPtrAndSize(obj1, &buf2, NULL, &alloc2); if (!SWIG_IsOK(res2)) { SWIG_exception_fail(SWIG_ArgError(res2), "in method '" "cbf_handle_struct_find_category_root" "', argument " "2"" of type '" "char const *""'"); } arg2 = (char *)(buf2); { error_status=0; result = (char *)cbf_handle_struct_find_category_root(arg1,(char const *)arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_FromCharPtr((const char *)result); if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return resultobj; fail: if (alloc2 == SWIG_NEWOBJ) free((char*)buf2); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_integerarray_wdims_fs(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; int arg3 ; char *arg4 = (char *) 0 ; int arg5 ; int arg6 ; int arg7 ; int arg8 ; char *arg9 = (char *) 0 ; int arg10 ; int arg11 ; int arg12 ; int arg13 ; int arg14 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; int val3 ; int ecode3 = 0 ; int res4 ; char *buf4 = 0 ; size_t size4 = 0 ; int alloc4 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int val8 ; int ecode8 = 0 ; int res9 ; char *buf9 = 0 ; size_t size9 = 0 ; int alloc9 = 0 ; int val11 ; int ecode11 = 0 ; int val12 ; int ecode12 = 0 ; int val13 ; int ecode13 = 0 ; int val14 ; int ecode14 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; PyObject * obj6 = 0 ; PyObject * obj7 = 0 ; PyObject * obj8 = 0 ; PyObject * obj9 = 0 ; PyObject * obj10 = 0 ; PyObject * obj11 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOOOOOOOOO:cbf_handle_struct_set_integerarray_wdims_fs",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5,&obj6,&obj7,&obj8,&obj9,&obj10,&obj11)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_integerarray_wdims_fs" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_integerarray_wdims_fs" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_integerarray_wdims_fs" "', argument " "3"" of type '" "int""'"); } arg3 = (int)(val3); res4 = SWIG_AsCharPtrAndSize(obj3, &buf4, &size4, &alloc4); if (!SWIG_IsOK(res4)) { SWIG_exception_fail(SWIG_ArgError(res4), "in method '" "cbf_handle_struct_set_integerarray_wdims_fs" "', argument " "4"" of type '" "char *""'"); } arg4 = (char *)(buf4); arg5 = (int)(size4 - 1); ecode6 = SWIG_AsVal_int(obj4, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_set_integerarray_wdims_fs" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj5, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_set_integerarray_wdims_fs" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); ecode8 = SWIG_AsVal_int(obj6, &val8); if (!SWIG_IsOK(ecode8)) { SWIG_exception_fail(SWIG_ArgError(ecode8), "in method '" "cbf_handle_struct_set_integerarray_wdims_fs" "', argument " "8"" of type '" "int""'"); } arg8 = (int)(val8); res9 = SWIG_AsCharPtrAndSize(obj7, &buf9, &size9, &alloc9); if (!SWIG_IsOK(res9)) { SWIG_exception_fail(SWIG_ArgError(res9), "in method '" "cbf_handle_struct_set_integerarray_wdims_fs" "', argument " "9"" of type '" "char *""'"); } arg9 = (char *)(buf9); arg10 = (int)(size9 - 1); ecode11 = SWIG_AsVal_int(obj8, &val11); if (!SWIG_IsOK(ecode11)) { SWIG_exception_fail(SWIG_ArgError(ecode11), "in method '" "cbf_handle_struct_set_integerarray_wdims_fs" "', argument " "11"" of type '" "int""'"); } arg11 = (int)(val11); ecode12 = SWIG_AsVal_int(obj9, &val12); if (!SWIG_IsOK(ecode12)) { SWIG_exception_fail(SWIG_ArgError(ecode12), "in method '" "cbf_handle_struct_set_integerarray_wdims_fs" "', argument " "12"" of type '" "int""'"); } arg12 = (int)(val12); ecode13 = SWIG_AsVal_int(obj10, &val13); if (!SWIG_IsOK(ecode13)) { SWIG_exception_fail(SWIG_ArgError(ecode13), "in method '" "cbf_handle_struct_set_integerarray_wdims_fs" "', argument " "13"" of type '" "int""'"); } arg13 = (int)(val13); ecode14 = SWIG_AsVal_int(obj11, &val14); if (!SWIG_IsOK(ecode14)) { SWIG_exception_fail(SWIG_ArgError(ecode14), "in method '" "cbf_handle_struct_set_integerarray_wdims_fs" "', argument " "14"" of type '" "int""'"); } arg14 = (int)(val14); { error_status=0; cbf_handle_struct_set_integerarray_wdims_fs(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9,arg10,arg11,arg12,arg13,arg14); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); if (alloc9 == SWIG_NEWOBJ) free((char*)buf9); return resultobj; fail: if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); if (alloc9 == SWIG_NEWOBJ) free((char*)buf9); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_image_sf(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; unsigned int arg2 ; unsigned int arg3 ; char *arg4 = (char *) 0 ; int arg5 ; int arg6 ; int arg7 ; int arg8 ; int arg9 ; void *argp1 = 0 ; int res1 = 0 ; unsigned int val2 ; int ecode2 = 0 ; unsigned int val3 ; int ecode3 = 0 ; int res4 ; char *buf4 = 0 ; size_t size4 = 0 ; int alloc4 = 0 ; int val6 ; int ecode6 = 0 ; int val7 ; int ecode7 = 0 ; int val8 ; int ecode8 = 0 ; int val9 ; int ecode9 = 0 ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; PyObject * obj2 = 0 ; PyObject * obj3 = 0 ; PyObject * obj4 = 0 ; PyObject * obj5 = 0 ; PyObject * obj6 = 0 ; PyObject * obj7 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OOOOOOOO:cbf_handle_struct_set_image_sf",&obj0,&obj1,&obj2,&obj3,&obj4,&obj5,&obj6,&obj7)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_image_sf" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); ecode2 = SWIG_AsVal_unsigned_SS_int(obj1, &val2); if (!SWIG_IsOK(ecode2)) { SWIG_exception_fail(SWIG_ArgError(ecode2), "in method '" "cbf_handle_struct_set_image_sf" "', argument " "2"" of type '" "unsigned int""'"); } arg2 = (unsigned int)(val2); ecode3 = SWIG_AsVal_unsigned_SS_int(obj2, &val3); if (!SWIG_IsOK(ecode3)) { SWIG_exception_fail(SWIG_ArgError(ecode3), "in method '" "cbf_handle_struct_set_image_sf" "', argument " "3"" of type '" "unsigned int""'"); } arg3 = (unsigned int)(val3); res4 = SWIG_AsCharPtrAndSize(obj3, &buf4, &size4, &alloc4); if (!SWIG_IsOK(res4)) { SWIG_exception_fail(SWIG_ArgError(res4), "in method '" "cbf_handle_struct_set_image_sf" "', argument " "4"" of type '" "char *""'"); } arg4 = (char *)(buf4); arg5 = (int)(size4 - 1); ecode6 = SWIG_AsVal_int(obj4, &val6); if (!SWIG_IsOK(ecode6)) { SWIG_exception_fail(SWIG_ArgError(ecode6), "in method '" "cbf_handle_struct_set_image_sf" "', argument " "6"" of type '" "int""'"); } arg6 = (int)(val6); ecode7 = SWIG_AsVal_int(obj5, &val7); if (!SWIG_IsOK(ecode7)) { SWIG_exception_fail(SWIG_ArgError(ecode7), "in method '" "cbf_handle_struct_set_image_sf" "', argument " "7"" of type '" "int""'"); } arg7 = (int)(val7); ecode8 = SWIG_AsVal_int(obj6, &val8); if (!SWIG_IsOK(ecode8)) { SWIG_exception_fail(SWIG_ArgError(ecode8), "in method '" "cbf_handle_struct_set_image_sf" "', argument " "8"" of type '" "int""'"); } arg8 = (int)(val8); ecode9 = SWIG_AsVal_int(obj7, &val9); if (!SWIG_IsOK(ecode9)) { SWIG_exception_fail(SWIG_ArgError(ecode9), "in method '" "cbf_handle_struct_set_image_sf" "', argument " "9"" of type '" "int""'"); } arg9 = (int)(val9); { error_status=0; cbf_handle_struct_set_image_sf(arg1,arg2,arg3,arg4,arg5,arg6,arg7,arg8,arg9); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return resultobj; fail: if (alloc4 == SWIG_NEWOBJ) free((char*)buf4); return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_unit_cell(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; double *arg2 ; void *argp1 = 0 ; int res1 = 0 ; double temp2[6] ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_set_unit_cell",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_unit_cell" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { if (obj1 == Py_None) arg2 = NULL; else if (!convert_darray(obj1,temp2,6)) { return NULL; } arg2 = &temp2[0]; } { error_status=0; cbf_handle_struct_set_unit_cell(arg1,arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *_wrap_cbf_handle_struct_set_unit_cell_esd(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *resultobj = 0; cbf_handle_struct *arg1 = (cbf_handle_struct *) 0 ; double *arg2 ; void *argp1 = 0 ; int res1 = 0 ; double temp2[6] ; PyObject * obj0 = 0 ; PyObject * obj1 = 0 ; if (!PyArg_ParseTuple(args,(char *)"OO:cbf_handle_struct_set_unit_cell_esd",&obj0,&obj1)) SWIG_fail; res1 = SWIG_ConvertPtr(obj0, &argp1,SWIGTYPE_p_cbf_handle_struct, 0 | 0 ); if (!SWIG_IsOK(res1)) { SWIG_exception_fail(SWIG_ArgError(res1), "in method '" "cbf_handle_struct_set_unit_cell_esd" "', argument " "1"" of type '" "cbf_handle_struct *""'"); } arg1 = (cbf_handle_struct *)(argp1); { if (obj1 == Py_None) arg2 = NULL; else if (!convert_darray(obj1,temp2,6)) { return NULL; } arg2 = &temp2[0]; } { error_status=0; cbf_handle_struct_set_unit_cell_esd(arg1,arg2); if (error_status){ get_error_message(); PyErr_SetString(PyExc_Exception,error_message); return NULL; } } resultobj = SWIG_Py_Void(); return resultobj; fail: return NULL; } SWIGINTERN PyObject *cbf_handle_struct_swigregister(PyObject *SWIGUNUSEDPARM(self), PyObject *args) { PyObject *obj; if (!PyArg_ParseTuple(args,(char*)"O:swigregister", &obj)) return NULL; SWIG_TypeNewClientData(SWIGTYPE_p_cbf_handle_struct, SWIG_NewClientData(obj)); return SWIG_Py_Void(); } static PyMethodDef SwigMethods[] = { { (char *)"SWIG_PyInstanceMethod_New", (PyCFunction)SWIG_PyInstanceMethod_New, METH_O, NULL}, { (char *)"new_doubleArray", _wrap_new_doubleArray, METH_VARARGS, NULL}, { (char *)"delete_doubleArray", _wrap_delete_doubleArray, METH_VARARGS, NULL}, { (char *)"doubleArray___getitem__", _wrap_doubleArray___getitem__, METH_VARARGS, NULL}, { (char *)"doubleArray___setitem__", _wrap_doubleArray___setitem__, METH_VARARGS, NULL}, { (char *)"doubleArray_cast", _wrap_doubleArray_cast, METH_VARARGS, NULL}, { (char *)"doubleArray_frompointer", _wrap_doubleArray_frompointer, METH_VARARGS, NULL}, { (char *)"doubleArray_swigregister", doubleArray_swigregister, METH_VARARGS, NULL}, { (char *)"new_intArray", _wrap_new_intArray, METH_VARARGS, NULL}, { (char *)"delete_intArray", _wrap_delete_intArray, METH_VARARGS, NULL}, { (char *)"intArray___getitem__", _wrap_intArray___getitem__, METH_VARARGS, NULL}, { (char *)"intArray___setitem__", _wrap_intArray___setitem__, METH_VARARGS, NULL}, { (char *)"intArray_cast", _wrap_intArray_cast, METH_VARARGS, NULL}, { (char *)"intArray_frompointer", _wrap_intArray_frompointer, METH_VARARGS, NULL}, { (char *)"intArray_swigregister", intArray_swigregister, METH_VARARGS, NULL}, { (char *)"new_shortArray", _wrap_new_shortArray, METH_VARARGS, NULL}, { (char *)"delete_shortArray", _wrap_delete_shortArray, METH_VARARGS, NULL}, { (char *)"shortArray___getitem__", _wrap_shortArray___getitem__, METH_VARARGS, NULL}, { (char *)"shortArray___setitem__", _wrap_shortArray___setitem__, METH_VARARGS, NULL}, { (char *)"shortArray_cast", _wrap_shortArray_cast, METH_VARARGS, NULL}, { (char *)"shortArray_frompointer", _wrap_shortArray_frompointer, METH_VARARGS, NULL}, { (char *)"shortArray_swigregister", shortArray_swigregister, METH_VARARGS, NULL}, { (char *)"new_longArray", _wrap_new_longArray, METH_VARARGS, NULL}, { (char *)"delete_longArray", _wrap_delete_longArray, METH_VARARGS, NULL}, { (char *)"longArray___getitem__", _wrap_longArray___getitem__, METH_VARARGS, NULL}, { (char *)"longArray___setitem__", _wrap_longArray___setitem__, METH_VARARGS, NULL}, { (char *)"longArray_cast", _wrap_longArray_cast, METH_VARARGS, NULL}, { (char *)"longArray_frompointer", _wrap_longArray_frompointer, METH_VARARGS, NULL}, { (char *)"longArray_swigregister", longArray_swigregister, METH_VARARGS, NULL}, { (char *)"get_local_integer_byte_order", _wrap_get_local_integer_byte_order, METH_VARARGS, (char *)"\n" "Returns : char **bo,int *bolen\n" "*args : \n" "\n" "C prototype: int cbf_get_local_integer_byte_order (char ** byte_order);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_local_integer_byte_order returns the byte order of integers \n" "on the machine on which the API is being run in the form of a \n" "character string returned as the value pointed to by byte_order. \n" "cbf_get_local_real_byte_order returns the byte order of reals on the \n" "machine on which the API is being run in the form of a character \n" "string returned as the value pointed to by byte_order. \n" "cbf_get_local_real_format returns the format of floats on the machine \n" "on which the API is being run in the form of a character string \n" "returned as the value pointed to by real_format. The strings returned \n" "must not be modified in any way.\n" "The values returned in byte_order may be the strings \"little_endian \n" "\" or \"big-endian \". The values returned in real_format may be the \n" "strings \"ieee 754-1985 \" or \"other \". Additional values may be \n" "returned by future versions of the API.\n" "ARGUMENTS\n" "byte_order pointer to the returned string real_format pointer to \n" "the returned string\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"compute_cell_volume", _wrap_compute_cell_volume, METH_VARARGS, (char *)"\n" "Returns : Float volume\n" "*args : double cell[6]\n" "\n" "C prototype: int cbf_compute_cell_volume ( double cell[6], double *volume );\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_compute_cell_volume sets *volume to point to the volume of the \n" "unit cell computed from the double values in cell[0:2] for the cell \n" "edge lengths a, b and c in AAngstroms and the double values given in \n" "cell[3:5] for the cell angles a, b and g in degrees.\n" "ARGUMENTS\n" "cell Pointer to the array of 6 doubles giving the cell \n" "parameters. volume Pointer to the doubles for cell volume.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"get_local_real_format", _wrap_get_local_real_format, METH_VARARGS, (char *)"\n" "Returns : char **rf,int *rflen\n" "*args : \n" "\n" "C prototype: int cbf_get_local_real_format (char ** real_format );\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_local_integer_byte_order returns the byte order of integers \n" "on the machine on which the API is being run in the form of a \n" "character string returned as the value pointed to by byte_order. \n" "cbf_get_local_real_byte_order returns the byte order of reals on the \n" "machine on which the API is being run in the form of a character \n" "string returned as the value pointed to by byte_order. \n" "cbf_get_local_real_format returns the format of floats on the machine \n" "on which the API is being run in the form of a character string \n" "returned as the value pointed to by real_format. The strings returned \n" "must not be modified in any way.\n" "The values returned in byte_order may be the strings \"little_endian \n" "\" or \"big-endian \". The values returned in real_format may be the \n" "strings \"ieee 754-1985 \" or \"other \". Additional values may be \n" "returned by future versions of the API.\n" "ARGUMENTS\n" "byte_order pointer to the returned string real_format pointer to \n" "the returned string\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"get_local_real_byte_order", _wrap_get_local_real_byte_order, METH_VARARGS, (char *)"\n" "Returns : char **bo,int *bolen\n" "*args : \n" "\n" "C prototype: int cbf_get_local_real_byte_order (char ** byte_order);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_local_integer_byte_order returns the byte order of integers \n" "on the machine on which the API is being run in the form of a \n" "character string returned as the value pointed to by byte_order. \n" "cbf_get_local_real_byte_order returns the byte order of reals on the \n" "machine on which the API is being run in the form of a character \n" "string returned as the value pointed to by byte_order. \n" "cbf_get_local_real_format returns the format of floats on the machine \n" "on which the API is being run in the form of a character string \n" "returned as the value pointed to by real_format. The strings returned \n" "must not be modified in any way.\n" "The values returned in byte_order may be the strings \"little_endian \n" "\" or \"big-endian \". The values returned in real_format may be the \n" "strings \"ieee 754-1985 \" or \"other \". Additional values may be \n" "returned by future versions of the API.\n" "ARGUMENTS\n" "byte_order pointer to the returned string real_format pointer to \n" "the returned string\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"compute_reciprocal_cell", _wrap_compute_reciprocal_cell, METH_VARARGS, (char *)"\n" "Returns : Float astar,Float bstar,Float cstar,Float alphastar,Float betastar,\n" " Float gammastar\n" "*args : double cell[6]\n" "\n" "C prototype: int cbf_compute_reciprocal_cell ( double cell[6],\n" " double rcell[6] );\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_compute_reciprocal_cell sets rcell to point to the array of \n" "reciprocal cell parameters computed from the double values cell[0:2] \n" "giving the cell edge lengths a, b and c in AAngstroms, and the double \n" "values cell[3:5] giving the cell angles a, b and g in degrees. The \n" "double values rcell[0:2] will be set to the reciprocal cell lengths \n" "a*, b* and c* in AAngstroms-1 and the double values rcell[3:5] will \n" "be set to the reciprocal cell angles a*, b* and g* in degrees.\n" "ARGUMENTS\n" "cell Pointer to the array of 6 doubles giving the cell \n" "parameters. rcell Pointer to the destination array of 6 doubles \n" "giving the reciprocal cell parameters. volume Pointer to the \n" "doubles for cell volume.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_positioner_struct_matrix_set", _wrap_cbf_positioner_struct_matrix_set, METH_VARARGS, (char *)"cbf_positioner_struct_matrix_set(cbf_positioner_struct self, double matrix)"}, { (char *)"cbf_positioner_struct_matrix_get", _wrap_cbf_positioner_struct_matrix_get, METH_VARARGS, (char *)"cbf_positioner_struct_matrix_get(cbf_positioner_struct self) -> double"}, { (char *)"cbf_positioner_struct_axis_set", _wrap_cbf_positioner_struct_axis_set, METH_VARARGS, (char *)"cbf_positioner_struct_axis_set(cbf_positioner_struct self, cbf_axis_struct axis)"}, { (char *)"cbf_positioner_struct_axis_get", _wrap_cbf_positioner_struct_axis_get, METH_VARARGS, (char *)"cbf_positioner_struct_axis_get(cbf_positioner_struct self) -> cbf_axis_struct"}, { (char *)"cbf_positioner_struct_axes_set", _wrap_cbf_positioner_struct_axes_set, METH_VARARGS, (char *)"cbf_positioner_struct_axes_set(cbf_positioner_struct self, size_t axes)"}, { (char *)"cbf_positioner_struct_axes_get", _wrap_cbf_positioner_struct_axes_get, METH_VARARGS, (char *)"cbf_positioner_struct_axes_get(cbf_positioner_struct self) -> size_t"}, { (char *)"cbf_positioner_struct_matrix_is_valid_set", _wrap_cbf_positioner_struct_matrix_is_valid_set, METH_VARARGS, (char *)"cbf_positioner_struct_matrix_is_valid_set(cbf_positioner_struct self, int matrix_is_valid)"}, { (char *)"cbf_positioner_struct_matrix_is_valid_get", _wrap_cbf_positioner_struct_matrix_is_valid_get, METH_VARARGS, (char *)"cbf_positioner_struct_matrix_is_valid_get(cbf_positioner_struct self) -> int"}, { (char *)"cbf_positioner_struct_axes_are_connected_set", _wrap_cbf_positioner_struct_axes_are_connected_set, METH_VARARGS, (char *)"cbf_positioner_struct_axes_are_connected_set(cbf_positioner_struct self, int axes_are_connected)"}, { (char *)"cbf_positioner_struct_axes_are_connected_get", _wrap_cbf_positioner_struct_axes_are_connected_get, METH_VARARGS, (char *)"cbf_positioner_struct_axes_are_connected_get(cbf_positioner_struct self) -> int"}, { (char *)"new_cbf_positioner_struct", _wrap_new_cbf_positioner_struct, METH_VARARGS, (char *)"new_cbf_positioner_struct() -> cbf_positioner_struct"}, { (char *)"delete_cbf_positioner_struct", _wrap_delete_cbf_positioner_struct, METH_VARARGS, (char *)"delete_cbf_positioner_struct(cbf_positioner_struct self)"}, { (char *)"cbf_positioner_struct_get_rotation_range", _wrap_cbf_positioner_struct_get_rotation_range, METH_VARARGS, (char *)"\n" "Returns : Float start,Float increment\n" "*args : \n" "\n" "C prototype: int cbf_get_rotation_range (cbf_goniometer goniometer,\n" " unsigned int reserved, double *start, double *increment);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_rotation_range sets *start and *increment to the \n" "corresponding values of the goniometer rotation axis used for the \n" "exposure.\n" "Either of the destination pointers may be NULL.\n" "The parameter reserved is presently unused and should be set to 0.\n" "ARGUMENTS\n" "goniometer Goniometer handle. reserved Unused. Any value other \n" "than 0 is invalid. start Pointer to the destination start \n" "value. increment Pointer to the destination increment value.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_positioner_struct_rotate_vector", _wrap_cbf_positioner_struct_rotate_vector, METH_VARARGS, (char *)"\n" "Returns : double final1,double final2,double final3\n" "*args : double ratio,double initial1,double initial2,double initial3\n" "\n" "C prototype: int cbf_rotate_vector (cbf_goniometer goniometer,\n" " unsigned int reserved, double ratio, double initial1,\n" " double initial2, double initial3, double *final1,\n" " double *final2, double *final3);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_rotate_vector sets *final1, *final2, and *final3 to the 3 \n" "components of the of the vector (initial1, initial2, initial3) after \n" "reorientation by applying the goniometer rotations. The value ratio \n" "specif ies the goniometer setting and varies from 0.0 at the \n" "beginning of the exposure to 1.0 at the end, irrespective of the \n" "actual rotation range.\n" "Any of the destination pointers may be NULL.\n" "The parameter reserved is presently unused and should be set to 0.\n" "ARGUMENTS\n" "goniometer Goniometer handle. reserved Unused. Any value other \n" "than 0 is invalid. ratio Goniometer setting. 0 = beginning of \n" "exposure, 1 = end. initial1 x component of the initial vector. \n" "initial2 y component of the initial vector. initial3 z \n" "component of the initial vector. vector1 Pointer to the \n" "destination x component of the final vector. vector2 Pointer to \n" "the destination y component of the final vector. vector3 Pointer \n" "to the destination z component of the final vector.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_positioner_struct_get_reciprocal", _wrap_cbf_positioner_struct_get_reciprocal, METH_VARARGS, (char *)"\n" "Returns : double reciprocal1,double reciprocal2,double reciprocal3\n" "*args : double ratio,double wavelength,double real1,double real2,double real3\n" "\n" "C prototype: int cbf_get_reciprocal (cbf_goniometer goniometer,\n" " unsigned int reserved, double ratio, double wavelength,\n" " double real1, double real2, double real3,\n" " double *reciprocal1, double *reciprocal2,\n" " double *reciprocal3);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_reciprocal sets *reciprocal1, * reciprocal2, and * \n" "reciprocal3 to the 3 components of the of the reciprocal-space vector \n" "corresponding to the real-space vector (real1, real2, real3). The \n" "reciprocal-space vector is oriented to correspond to the goniometer \n" "setting with all axes at 0. The value wavelength is the wavlength in \n" "AA and the value ratio specifies the current goniometer setting and \n" "varies from 0.0 at the beginning of the exposur e to 1.0 at the end, \n" "irrespective of the actual rotation range.\n" "Any of the destination pointers may be NULL.\n" "The parameter reserved is presently unused and should be set to 0.\n" "ARGUMENTS\n" "goniometer Goniometer handle. reserved Unused. Any value \n" "other than 0 is invalid. ratio Goniometer setting. 0 = \n" "beginning of exposure, 1 = end. wavelength Wavelength in AA. real1 \n" " x component of the real-space vector. real2 y \n" "component of the real-space vector. real3 z component of the \n" "real-space vector. reciprocal1 Pointer to the destination x \n" "component of the reciprocal-space vector. reciprocal2 Pointer to \n" "the destination y component of the reciprocal-space vector. \n" "reciprocal3 Pointer to the destination z component of the \n" "reciprocal-space vector.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_positioner_struct_get_rotation_axis", _wrap_cbf_positioner_struct_get_rotation_axis, METH_VARARGS, (char *)"\n" "Returns : double vector1,double vector2,double vector3\n" "*args : \n" "\n" "C prototype: int cbf_get_rotation_axis (cbf_goniometer goniometer,\n" " unsigned int reserved, double *vector1, double *vector2,\n" " double *vector3);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_rotation_axis sets *vector1, *vector2, and *vector3 to the 3 \n" "components of the goniometer rotation axis used for the exposure.\n" "Any of the destination pointers may be NULL.\n" "The parameter reserved is presently unused and should be set to 0.\n" "ARGUMENTS\n" "goniometer Goniometer handle. reserved Unused. Any value other \n" "than 0 is invalid. vector1 Pointer to the destination x \n" "component of the rotation axis. vector2 Pointer to the \n" "destination y component of the rotation axis. vector3 Pointer to \n" "the destination z component of the rotation axis.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_positioner_struct_swigregister", cbf_positioner_struct_swigregister, METH_VARARGS, NULL}, { (char *)"cbf_detector_struct_positioner_set", _wrap_cbf_detector_struct_positioner_set, METH_VARARGS, (char *)"cbf_detector_struct_positioner_set(cbf_detector_struct self, cbf_positioner positioner)"}, { (char *)"cbf_detector_struct_positioner_get", _wrap_cbf_detector_struct_positioner_get, METH_VARARGS, (char *)"cbf_detector_struct_positioner_get(cbf_detector_struct self) -> cbf_positioner"}, { (char *)"cbf_detector_struct_displacement_set", _wrap_cbf_detector_struct_displacement_set, METH_VARARGS, (char *)"cbf_detector_struct_displacement_set(cbf_detector_struct self, double displacement)"}, { (char *)"cbf_detector_struct_displacement_get", _wrap_cbf_detector_struct_displacement_get, METH_VARARGS, (char *)"cbf_detector_struct_displacement_get(cbf_detector_struct self) -> double"}, { (char *)"cbf_detector_struct_increment_set", _wrap_cbf_detector_struct_increment_set, METH_VARARGS, (char *)"cbf_detector_struct_increment_set(cbf_detector_struct self, double increment)"}, { (char *)"cbf_detector_struct_increment_get", _wrap_cbf_detector_struct_increment_get, METH_VARARGS, (char *)"cbf_detector_struct_increment_get(cbf_detector_struct self) -> double"}, { (char *)"cbf_detector_struct_axes_set", _wrap_cbf_detector_struct_axes_set, METH_VARARGS, (char *)"cbf_detector_struct_axes_set(cbf_detector_struct self, size_t axes)"}, { (char *)"cbf_detector_struct_axes_get", _wrap_cbf_detector_struct_axes_get, METH_VARARGS, (char *)"cbf_detector_struct_axes_get(cbf_detector_struct self) -> size_t"}, { (char *)"cbf_detector_struct_index_set", _wrap_cbf_detector_struct_index_set, METH_VARARGS, (char *)"cbf_detector_struct_index_set(cbf_detector_struct self, size_t index)"}, { (char *)"cbf_detector_struct_index_get", _wrap_cbf_detector_struct_index_get, METH_VARARGS, (char *)"cbf_detector_struct_index_get(cbf_detector_struct self) -> size_t"}, { (char *)"new_cbf_detector_struct", _wrap_new_cbf_detector_struct, METH_VARARGS, (char *)"new_cbf_detector_struct() -> cbf_detector_struct"}, { (char *)"delete_cbf_detector_struct", _wrap_delete_cbf_detector_struct, METH_VARARGS, (char *)"delete_cbf_detector_struct(cbf_detector_struct self)"}, { (char *)"cbf_detector_struct_set_reference_beam_center_fs", _wrap_cbf_detector_struct_set_reference_beam_center_fs, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : double indexfast,double indexslow,double centerfast,double centerslow\n" "\n" "C prototype: int cbf_set_reference_beam_center_fs (cbf_detector detector,\n" " double *indexfast, double *indexslow, double *centerfast,\n" " double *centerslow);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_beam_center sets *centerfast and *centerslow to the \n" "displacements in mm along the detector axes from pixel (0, 0) to the \n" "point at which the beam intersects the detector and *indexfast and \n" "*indexslow to the corresponding indices. cbf_set_beam_center sets the \n" "offsets in the axis category for the detector element axis with \n" "precedence 1 to place the beam center at the position given in mm by \n" "*centerfast and *centerslow as the displacements in mm along the \n" "detector axes from pixel (0, 0) to the point at which the beam \n" "intersects the detector at the indices given *indexfast and \n" "*indexslow. cbf_set_reference_beam_center sets the displacments in \n" "the array_structure_list_axis category to place the beam center at \n" "the position given in mm by *centerfast and *centerslow as the \n" "displacements in mm along the detector axes from pixel (0, 0) to the \n" "point at which the beam intersects the detector at the indices given \n" "by *indexfast and *indexslow. In order to achieve consistent results, \n" "a reference detector should be used for detector to have all axes at \n" "their reference settings.\n" "Note that the precedence 1 axis is the fastest axis, so that \n" "*centerfast and *indexfast are the fast axis components of the center \n" "and *centerslow and *indexslow are the slow axis components of the \n" "center.\n" "The _fs calls give the displacments in a fast-to-slow order. The \n" "calls with no suffix and the calls _sf calls give the displacements \n" "in slow-to-fast order\n" "Any of the destination pointers may be NULL for getting the beam \n" "center. For setting the beam axis, either the indices of the center \n" "must not be NULL.\n" "The indices are non-negative for beam centers within the detector \n" "surface, but the center for an axis with a negative increment will be \n" "negative for a beam center within the detector surface.\n" "For cbf_set_beam_center if the diffrn_data_frame category exists with \n" "a row for the corresponding element id, the values will be set for \n" "_diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in \n" "millimetres and the value of _diffrn_data_frame.center_units will be \n" "set to 'mm'.\n" "For cbf_set_reference_beam_center if the diffrn_detector_element \n" "category exists with a row for the corresponding element id, the \n" "values will be set for _diffrn_detector_element.reference_center_fast \n" "and _diffrn_detector_element.reference_center_slow in millimetres and \n" "the value of _diffrn_detector_element.reference_units will be set to \n" "'mm'.\n" "ARGUMENTS\n" "detector Detector handle. indexfast Pointer to the destination \n" "fast index. indexslow Pointer to the destination slow index. \n" "centerfast Pointer to the destination displacement along the fast \n" "axis. centerslow Pointer to the destination displacement along the \n" "slow axis.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_detector_struct_get_pixel_coordinates_fs", _wrap_cbf_detector_struct_get_pixel_coordinates_fs, METH_VARARGS, (char *)"\n" "Returns : double coordinate1,double coordinate2,double coordinate3\n" "*args : double indexfast,double indexslow\n" "\n" "C prototype: int cbf_get_pixel_coordinates_fs (cbf_detector detector,\n" " double indexfast, double indexslow, double *coordinate1,\n" " double *coordinate2, double *coordinate3);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_pixel_coordinates, cbf_get_pixel_coordinates_fs and \n" "cbf_get_pixel_coordinates_sf ses *coordinate1, *coordinate2, and \n" "*coordinate3 to the vector position of pixel (indexfast, indexslow) \n" "on the detector surface. If indexslow and indexfast are integers then \n" "the coordinates correspond to the center of a pixel.\n" "Any of the destination pointers may be NULL.\n" "ARGUMENTS\n" "detector Detector handle. indexslow Slow index. indexfast \n" " Fast index. coordinate1 Pointer to the destination x component. \n" "coordinate2 Pointer to the destination y component. coordinate3 \n" "Pointer to the destination z component.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_detector_struct_set_beam_center_fs", _wrap_cbf_detector_struct_set_beam_center_fs, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : double indexfast,double indexslow,double centerfast,double centerslow\n" "\n" "C prototype: int cbf_set_beam_center_fs (cbf_detector detector,\n" " double *indexfast, double *indexslow, double *centerfast,\n" " double *centerslow);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_beam_center sets *centerfast and *centerslow to the \n" "displacements in mm along the detector axes from pixel (0, 0) to the \n" "point at which the beam intersects the detector and *indexfast and \n" "*indexslow to the corresponding indices. cbf_set_beam_center sets the \n" "offsets in the axis category for the detector element axis with \n" "precedence 1 to place the beam center at the position given in mm by \n" "*centerfast and *centerslow as the displacements in mm along the \n" "detector axes from pixel (0, 0) to the point at which the beam \n" "intersects the detector at the indices given *indexfast and \n" "*indexslow. cbf_set_reference_beam_center sets the displacments in \n" "the array_structure_list_axis category to place the beam center at \n" "the position given in mm by *centerfast and *centerslow as the \n" "displacements in mm along the detector axes from pixel (0, 0) to the \n" "point at which the beam intersects the detector at the indices given \n" "by *indexfast and *indexslow. In order to achieve consistent results, \n" "a reference detector should be used for detector to have all axes at \n" "their reference settings.\n" "Note that the precedence 1 axis is the fastest axis, so that \n" "*centerfast and *indexfast are the fast axis components of the center \n" "and *centerslow and *indexslow are the slow axis components of the \n" "center.\n" "The _fs calls give the displacments in a fast-to-slow order. The \n" "calls with no suffix and the calls _sf calls give the displacements \n" "in slow-to-fast order\n" "Any of the destination pointers may be NULL for getting the beam \n" "center. For setting the beam axis, either the indices of the center \n" "must not be NULL.\n" "The indices are non-negative for beam centers within the detector \n" "surface, but the center for an axis with a negative increment will be \n" "negative for a beam center within the detector surface.\n" "For cbf_set_beam_center if the diffrn_data_frame category exists with \n" "a row for the corresponding element id, the values will be set for \n" "_diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in \n" "millimetres and the value of _diffrn_data_frame.center_units will be \n" "set to 'mm'.\n" "For cbf_set_reference_beam_center if the diffrn_detector_element \n" "category exists with a row for the corresponding element id, the \n" "values will be set for _diffrn_detector_element.reference_center_fast \n" "and _diffrn_detector_element.reference_center_slow in millimetres and \n" "the value of _diffrn_detector_element.reference_units will be set to \n" "'mm'.\n" "ARGUMENTS\n" "detector Detector handle. indexfast Pointer to the destination \n" "fast index. indexslow Pointer to the destination slow index. \n" "centerfast Pointer to the destination displacement along the fast \n" "axis. centerslow Pointer to the destination displacement along the \n" "slow axis.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_detector_struct_get_inferred_pixel_size", _wrap_cbf_detector_struct_get_inferred_pixel_size, METH_VARARGS, (char *)"\n" "Returns : Float pixel size\n" "*args : Int axis_number\n" "\n" "C prototype: int cbf_get_inferred_pixel_size (cbf_detector detector,\n" " int axis_number, double *psize);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_inferred_pixel_size, cbf_get_inferred_pixel_size_sf set \n" "*psize to point to the double value in millimeters of the pixel size \n" "for the axis axis_number value. The slow index is treated as axis 1 \n" "and the next faster index is treated as axis 2. \n" "cbf_get_inferred_pixel_size_fs sets *psize to point to the double \n" "value in millimeters of the pixel size for the axis axis_number \n" "value. The fast index is treated as axis 1 and the next slower index \n" "is treated as axis 2.\n" "If the axis number is negative, the axes are used in the reverse \n" "order so that an axis_number of -1 indicates the fast axes in a call \n" "to cbf_get_inferred_pixel_size or cbf_get_inferred_pixel_size_sf and \n" "indicates the fast axis in a call to cbf_get_inferred_pixel_size_fs.\n" "ARGUMENTS\n" "detector Detector handle. axis_number The number of the axis. \n" "area Pointer to the destination pizel size in mm.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_detector_struct_get_pixel_area", _wrap_cbf_detector_struct_get_pixel_area, METH_VARARGS, (char *)"\n" "Returns : double area,double projected_area\n" "*args : double index1,double index2\n" "\n" "C prototype: int cbf_get_pixel_area (cbf_detector detector, double indexslow,\n" " double indexfast, double *area, double *projected_area);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_pixel_area, cbf_get_pixel_area_fs and cbf_get_pixel_area_sf \n" "set *area to the area of the pixel at (indexfast, indexslow) on the \n" "detector surface and *projected_area to the apparent area of the \n" "pixel as viewed from the sample position, with indexslow being the \n" "slow axis and indexfast being the fast axis.\n" "Either of the destination pointers may be NULL.\n" "ARGUMENTS\n" "detector Detector handle. indexfast Fast index. \n" "indexslow Slow index. area Pointer to the \n" "destination area in mm2. projected_area Pointer to the destination \n" "apparent area in mm2.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_detector_struct_get_pixel_normal_fs", _wrap_cbf_detector_struct_get_pixel_normal_fs, METH_VARARGS, (char *)"\n" "Returns : double normal1,double normal2,double normal3\n" "*args : double indexfast,double indexslow\n" "\n" "C prototype: int cbf_get_pixel_normal_fs (cbf_detector detector,\n" " double indexfast, double indexslow, double *normal1,\n" " double *normal2, double *normal3);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_detector_normal, cbf_get_pixel_normal_fs and \n" "cbf_get_pixel_normal_sf set *normal1, *normal2, and *normal3 to the 3 \n" "components of the of the normal vector to the pixel at (indexfast, \n" "indexslow). The vector is normalized.\n" "Any of the destination pointers may be NULL.\n" "ARGUMENTS\n" "detector Detector handle. indexslow Slow index. indexfast Fast \n" "index. normal1 Pointer to the destination x component of the \n" "normal vector. normal2 Pointer to the destination y component of \n" "the normal vector. normal3 Pointer to the destination z component \n" "of the normal vector.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_detector_struct_get_detector_axes", _wrap_cbf_detector_struct_get_detector_axes, METH_VARARGS, (char *)"\n" "Returns : double slowaxis1,double slowaxis2,double slowaxis3,double fastaxis1,\n" " double fastaxis2,double fastaxis3\n" "*args : \n" "\n" "C prototype: int cbf_get_detector_axes (cbf_detector detector,\n" " double *slowaxis1, double *slowaxis2, double *slowaxis3,\n" " double *fastaxis1, double *fastaxis2, double *fastaxis3);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_detector_axis_slow sets *slowaxis1, *slowaxis2, and \n" "*slowaxis3 to the 3 components of the slow axis of the specified \n" "detector at the current settings of all axes. \n" "cbf_get_detector_axis_slow sets *fastaxis1, *fastaxis2, and \n" "*fastaxis3 to the 3 components of the fast axis of the specified \n" "detector at the current settings of all axes. cbf_get_detector_axes, \n" "cbf_get_detector_axes_fs and int cbf_get_detector_axes_sf set \n" "*slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the \n" "slow axis and *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 \n" "components of the fast axis of the specified detector at the current \n" "settings of all axes.\n" "Any of the destination pointers may be NULL.\n" "ARGUMENTS\n" "detector Detector handle. slowaxis1 Pointer to the destination x \n" "component of the slow axis vector. slowaxis2 Pointer to the \n" "destination y component of the slow axis vector. slowaxis3 Pointer \n" "to the destination z component of the slow axis vector. fastaxis1 \n" "Pointer to the destination x component of the fast axis vector. \n" "fastaxis2 Pointer to the destination y component of the fast axis \n" "vector. fastaxis3 Pointer to the destination z component of the \n" "fast axis vector.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_detector_struct_set_reference_beam_center", _wrap_cbf_detector_struct_set_reference_beam_center, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : double indexslow,double indexfast,double centerslow,double centerfast\n" "\n" "C prototype: int cbf_set_reference_beam_center (cbf_detector detector,\n" " double *indexslow, double *indexfast, double *centerslow,\n" " double *centerfast);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_beam_center sets *centerfast and *centerslow to the \n" "displacements in mm along the detector axes from pixel (0, 0) to the \n" "point at which the beam intersects the detector and *indexfast and \n" "*indexslow to the corresponding indices. cbf_set_beam_center sets the \n" "offsets in the axis category for the detector element axis with \n" "precedence 1 to place the beam center at the position given in mm by \n" "*centerfast and *centerslow as the displacements in mm along the \n" "detector axes from pixel (0, 0) to the point at which the beam \n" "intersects the detector at the indices given *indexfast and \n" "*indexslow. cbf_set_reference_beam_center sets the displacments in \n" "the array_structure_list_axis category to place the beam center at \n" "the position given in mm by *centerfast and *centerslow as the \n" "displacements in mm along the detector axes from pixel (0, 0) to the \n" "point at which the beam intersects the detector at the indices given \n" "by *indexfast and *indexslow. In order to achieve consistent results, \n" "a reference detector should be used for detector to have all axes at \n" "their reference settings.\n" "Note that the precedence 1 axis is the fastest axis, so that \n" "*centerfast and *indexfast are the fast axis components of the center \n" "and *centerslow and *indexslow are the slow axis components of the \n" "center.\n" "The _fs calls give the displacments in a fast-to-slow order. The \n" "calls with no suffix and the calls _sf calls give the displacements \n" "in slow-to-fast order\n" "Any of the destination pointers may be NULL for getting the beam \n" "center. For setting the beam axis, either the indices of the center \n" "must not be NULL.\n" "The indices are non-negative for beam centers within the detector \n" "surface, but the center for an axis with a negative increment will be \n" "negative for a beam center within the detector surface.\n" "For cbf_set_beam_center if the diffrn_data_frame category exists with \n" "a row for the corresponding element id, the values will be set for \n" "_diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in \n" "millimetres and the value of _diffrn_data_frame.center_units will be \n" "set to 'mm'.\n" "For cbf_set_reference_beam_center if the diffrn_detector_element \n" "category exists with a row for the corresponding element id, the \n" "values will be set for _diffrn_detector_element.reference_center_fast \n" "and _diffrn_detector_element.reference_center_slow in millimetres and \n" "the value of _diffrn_detector_element.reference_units will be set to \n" "'mm'.\n" "ARGUMENTS\n" "detector Detector handle. indexfast Pointer to the destination \n" "fast index. indexslow Pointer to the destination slow index. \n" "centerfast Pointer to the destination displacement along the fast \n" "axis. centerslow Pointer to the destination displacement along the \n" "slow axis.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_detector_struct_get_detector_axis_slow", _wrap_cbf_detector_struct_get_detector_axis_slow, METH_VARARGS, (char *)"\n" "Returns : double slowaxis1,double slowaxis2,double slowaxis3\n" "*args : \n" "\n" "C prototype: int cbf_get_detector_axis_slow (cbf_detector detector,\n" " double *slowaxis1, double *slowaxis2, double *slowaxis3);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_detector_axis_slow sets *slowaxis1, *slowaxis2, and \n" "*slowaxis3 to the 3 components of the slow axis of the specified \n" "detector at the current settings of all axes. \n" "cbf_get_detector_axis_slow sets *fastaxis1, *fastaxis2, and \n" "*fastaxis3 to the 3 components of the fast axis of the specified \n" "detector at the current settings of all axes. cbf_get_detector_axes, \n" "cbf_get_detector_axes_fs and int cbf_get_detector_axes_sf set \n" "*slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the \n" "slow axis and *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 \n" "components of the fast axis of the specified detector at the current \n" "settings of all axes.\n" "Any of the destination pointers may be NULL.\n" "ARGUMENTS\n" "detector Detector handle. slowaxis1 Pointer to the destination x \n" "component of the slow axis vector. slowaxis2 Pointer to the \n" "destination y component of the slow axis vector. slowaxis3 Pointer \n" "to the destination z component of the slow axis vector. fastaxis1 \n" "Pointer to the destination x component of the fast axis vector. \n" "fastaxis2 Pointer to the destination y component of the fast axis \n" "vector. fastaxis3 Pointer to the destination z component of the \n" "fast axis vector.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_detector_struct_get_detector_distance", _wrap_cbf_detector_struct_get_detector_distance, METH_VARARGS, (char *)"\n" "Returns : double distance\n" "*args : \n" "\n" "C prototype: int cbf_get_detector_distance (cbf_detector detector,\n" " double *distance);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_detector_distance sets *distance to the nearest distance from \n" "the sample position to the detector plane.\n" "ARGUMENTS\n" "detector Detector handle. distance Pointer to the destination \n" "distance.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_detector_struct_get_inferred_pixel_size_fs", _wrap_cbf_detector_struct_get_inferred_pixel_size_fs, METH_VARARGS, (char *)"\n" "Returns : Float pixel size\n" "*args : Int axis_number\n" "\n" "C prototype: int cbf_get_inferred_pixel_size_fs(cbf_detector detector,\n" " int axis_number, double *psize);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_inferred_pixel_size, cbf_get_inferred_pixel_size_sf set \n" "*psize to point to the double value in millimeters of the pixel size \n" "for the axis axis_number value. The slow index is treated as axis 1 \n" "and the next faster index is treated as axis 2. \n" "cbf_get_inferred_pixel_size_fs sets *psize to point to the double \n" "value in millimeters of the pixel size for the axis axis_number \n" "value. The fast index is treated as axis 1 and the next slower index \n" "is treated as axis 2.\n" "If the axis number is negative, the axes are used in the reverse \n" "order so that an axis_number of -1 indicates the fast axes in a call \n" "to cbf_get_inferred_pixel_size or cbf_get_inferred_pixel_size_sf and \n" "indicates the fast axis in a call to cbf_get_inferred_pixel_size_fs.\n" "ARGUMENTS\n" "detector Detector handle. axis_number The number of the axis. \n" "area Pointer to the destination pizel size in mm.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_detector_struct_get_detector_normal", _wrap_cbf_detector_struct_get_detector_normal, METH_VARARGS, (char *)"\n" "Returns : double normal1,double normal2,double normal3\n" "*args : \n" "\n" "C prototype: int cbf_get_detector_normal (cbf_detector detector,\n" " double *normal1, double *normal2, double *normal3);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_detector_normal sets *normal1, *normal2, and *normal3 to the \n" "3 components of the of the normal vector to the detector plane. The \n" "vector is normalized.\n" "Any of the destination pointers may be NULL.\n" "ARGUMENTS\n" "detector Detector handle. normal1 Pointer to the destination x \n" "component of the normal vector. normal2 Pointer to the destination \n" "y component of the normal vector. normal3 Pointer to the \n" "destination z component of the normal vector.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_detector_struct_get_detector_axis_fast", _wrap_cbf_detector_struct_get_detector_axis_fast, METH_VARARGS, (char *)"\n" "Returns : double fastaxis1,double fastaxis2,double fastaxis3\n" "*args : \n" "\n" "C prototype: int cbf_get_detector_axis_fast (cbf_detector detector,\n" " double *fastaxis1, double *fastaxis2, double *fastaxis3);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_detector_axis_slow sets *slowaxis1, *slowaxis2, and \n" "*slowaxis3 to the 3 components of the slow axis of the specified \n" "detector at the current settings of all axes. \n" "cbf_get_detector_axis_slow sets *fastaxis1, *fastaxis2, and \n" "*fastaxis3 to the 3 components of the fast axis of the specified \n" "detector at the current settings of all axes. cbf_get_detector_axes, \n" "cbf_get_detector_axes_fs and int cbf_get_detector_axes_sf set \n" "*slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the \n" "slow axis and *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 \n" "components of the fast axis of the specified detector at the current \n" "settings of all axes.\n" "Any of the destination pointers may be NULL.\n" "ARGUMENTS\n" "detector Detector handle. slowaxis1 Pointer to the destination x \n" "component of the slow axis vector. slowaxis2 Pointer to the \n" "destination y component of the slow axis vector. slowaxis3 Pointer \n" "to the destination z component of the slow axis vector. fastaxis1 \n" "Pointer to the destination x component of the fast axis vector. \n" "fastaxis2 Pointer to the destination y component of the fast axis \n" "vector. fastaxis3 Pointer to the destination z component of the \n" "fast axis vector.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_detector_struct_get_detector_axes_fs", _wrap_cbf_detector_struct_get_detector_axes_fs, METH_VARARGS, (char *)"cbf_detector_struct_get_detector_axes_fs(cbf_detector_struct self)"}, { (char *)"cbf_detector_struct_get_detector_axes_sf", _wrap_cbf_detector_struct_get_detector_axes_sf, METH_VARARGS, (char *)"\n" "Returns : double slowaxis1,double slowaxis2,double slowaxis3,double fastaxis1,\n" " double fastaxis2,double fastaxis3\n" "*args : \n" "\n" "C prototype: int cbf_get_detector_axes_sf (cbf_detector detector,\n" " double *slowaxis1, double *slowaxis2, double *slowaxis3,\n" " double *fastaxis1, double *fastaxis2, double *fastaxis3);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_detector_axis_slow sets *slowaxis1, *slowaxis2, and \n" "*slowaxis3 to the 3 components of the slow axis of the specified \n" "detector at the current settings of all axes. \n" "cbf_get_detector_axis_slow sets *fastaxis1, *fastaxis2, and \n" "*fastaxis3 to the 3 components of the fast axis of the specified \n" "detector at the current settings of all axes. cbf_get_detector_axes, \n" "cbf_get_detector_axes_fs and int cbf_get_detector_axes_sf set \n" "*slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the \n" "slow axis and *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 \n" "components of the fast axis of the specified detector at the current \n" "settings of all axes.\n" "Any of the destination pointers may be NULL.\n" "ARGUMENTS\n" "detector Detector handle. slowaxis1 Pointer to the destination x \n" "component of the slow axis vector. slowaxis2 Pointer to the \n" "destination y component of the slow axis vector. slowaxis3 Pointer \n" "to the destination z component of the slow axis vector. fastaxis1 \n" "Pointer to the destination x component of the fast axis vector. \n" "fastaxis2 Pointer to the destination y component of the fast axis \n" "vector. fastaxis3 Pointer to the destination z component of the \n" "fast axis vector.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_detector_struct_get_pixel_coordinates_sf", _wrap_cbf_detector_struct_get_pixel_coordinates_sf, METH_VARARGS, (char *)"\n" "Returns : double coordinate1,double coordinate2,double coordinate3\n" "*args : double indexslow,double indexfast\n" "\n" "C prototype: int cbf_get_pixel_coordinates_sf (cbf_detector detector,\n" " double indexslow, double indexfast, double *coordinate1,\n" " double *coordinate2, double *coordinate3);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_pixel_coordinates, cbf_get_pixel_coordinates_fs and \n" "cbf_get_pixel_coordinates_sf ses *coordinate1, *coordinate2, and \n" "*coordinate3 to the vector position of pixel (indexfast, indexslow) \n" "on the detector surface. If indexslow and indexfast are integers then \n" "the coordinates correspond to the center of a pixel.\n" "Any of the destination pointers may be NULL.\n" "ARGUMENTS\n" "detector Detector handle. indexslow Slow index. indexfast \n" " Fast index. coordinate1 Pointer to the destination x component. \n" "coordinate2 Pointer to the destination y component. coordinate3 \n" "Pointer to the destination z component.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_detector_struct_set_beam_center", _wrap_cbf_detector_struct_set_beam_center, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : double indexslow,double indexfast,double centerslow,double centerfast\n" "\n" "C prototype: int cbf_set_beam_center (cbf_detector detector,\n" " double *indexslow, double *indexfast, double *centerslow,\n" " double *centerfast);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_beam_center sets *centerfast and *centerslow to the \n" "displacements in mm along the detector axes from pixel (0, 0) to the \n" "point at which the beam intersects the detector and *indexfast and \n" "*indexslow to the corresponding indices. cbf_set_beam_center sets the \n" "offsets in the axis category for the detector element axis with \n" "precedence 1 to place the beam center at the position given in mm by \n" "*centerfast and *centerslow as the displacements in mm along the \n" "detector axes from pixel (0, 0) to the point at which the beam \n" "intersects the detector at the indices given *indexfast and \n" "*indexslow. cbf_set_reference_beam_center sets the displacments in \n" "the array_structure_list_axis category to place the beam center at \n" "the position given in mm by *centerfast and *centerslow as the \n" "displacements in mm along the detector axes from pixel (0, 0) to the \n" "point at which the beam intersects the detector at the indices given \n" "by *indexfast and *indexslow. In order to achieve consistent results, \n" "a reference detector should be used for detector to have all axes at \n" "their reference settings.\n" "Note that the precedence 1 axis is the fastest axis, so that \n" "*centerfast and *indexfast are the fast axis components of the center \n" "and *centerslow and *indexslow are the slow axis components of the \n" "center.\n" "The _fs calls give the displacments in a fast-to-slow order. The \n" "calls with no suffix and the calls _sf calls give the displacements \n" "in slow-to-fast order\n" "Any of the destination pointers may be NULL for getting the beam \n" "center. For setting the beam axis, either the indices of the center \n" "must not be NULL.\n" "The indices are non-negative for beam centers within the detector \n" "surface, but the center for an axis with a negative increment will be \n" "negative for a beam center within the detector surface.\n" "For cbf_set_beam_center if the diffrn_data_frame category exists with \n" "a row for the corresponding element id, the values will be set for \n" "_diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in \n" "millimetres and the value of _diffrn_data_frame.center_units will be \n" "set to 'mm'.\n" "For cbf_set_reference_beam_center if the diffrn_detector_element \n" "category exists with a row for the corresponding element id, the \n" "values will be set for _diffrn_detector_element.reference_center_fast \n" "and _diffrn_detector_element.reference_center_slow in millimetres and \n" "the value of _diffrn_detector_element.reference_units will be set to \n" "'mm'.\n" "ARGUMENTS\n" "detector Detector handle. indexfast Pointer to the destination \n" "fast index. indexslow Pointer to the destination slow index. \n" "centerfast Pointer to the destination displacement along the fast \n" "axis. centerslow Pointer to the destination displacement along the \n" "slow axis.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_detector_struct_get_pixel_area_fs", _wrap_cbf_detector_struct_get_pixel_area_fs, METH_VARARGS, (char *)"\n" "Returns : double area,double projected_area\n" "*args : double indexfast,double indexslow\n" "\n" "C prototype: int cbf_get_pixel_area_fs(cbf_detector detector,\n" " double indexfast, double indexslow, double *area,\n" " double *projected_area);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_pixel_area, cbf_get_pixel_area_fs and cbf_get_pixel_area_sf \n" "set *area to the area of the pixel at (indexfast, indexslow) on the \n" "detector surface and *projected_area to the apparent area of the \n" "pixel as viewed from the sample position, with indexslow being the \n" "slow axis and indexfast being the fast axis.\n" "Either of the destination pointers may be NULL.\n" "ARGUMENTS\n" "detector Detector handle. indexfast Fast index. \n" "indexslow Slow index. area Pointer to the \n" "destination area in mm2. projected_area Pointer to the destination \n" "apparent area in mm2.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_detector_struct_get_beam_center_fs", _wrap_cbf_detector_struct_get_beam_center_fs, METH_VARARGS, (char *)"\n" "Returns : double indexfast,double indexslow,double centerfast,double centerslow\n" "*args : \n" "\n" "C prototype: int cbf_get_beam_center_fs (cbf_detector detector,\n" " double *indexfast, double *indexslow, double *centerfast,\n" " double *centerslow);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_beam_center sets *centerfast and *centerslow to the \n" "displacements in mm along the detector axes from pixel (0, 0) to the \n" "point at which the beam intersects the detector and *indexfast and \n" "*indexslow to the corresponding indices. cbf_set_beam_center sets the \n" "offsets in the axis category for the detector element axis with \n" "precedence 1 to place the beam center at the position given in mm by \n" "*centerfast and *centerslow as the displacements in mm along the \n" "detector axes from pixel (0, 0) to the point at which the beam \n" "intersects the detector at the indices given *indexfast and \n" "*indexslow. cbf_set_reference_beam_center sets the displacments in \n" "the array_structure_list_axis category to place the beam center at \n" "the position given in mm by *centerfast and *centerslow as the \n" "displacements in mm along the detector axes from pixel (0, 0) to the \n" "point at which the beam intersects the detector at the indices given \n" "by *indexfast and *indexslow. In order to achieve consistent results, \n" "a reference detector should be used for detector to have all axes at \n" "their reference settings.\n" "Note that the precedence 1 axis is the fastest axis, so that \n" "*centerfast and *indexfast are the fast axis components of the center \n" "and *centerslow and *indexslow are the slow axis components of the \n" "center.\n" "The _fs calls give the displacments in a fast-to-slow order. The \n" "calls with no suffix and the calls _sf calls give the displacements \n" "in slow-to-fast order\n" "Any of the destination pointers may be NULL for getting the beam \n" "center. For setting the beam axis, either the indices of the center \n" "must not be NULL.\n" "The indices are non-negative for beam centers within the detector \n" "surface, but the center for an axis with a negative increment will be \n" "negative for a beam center within the detector surface.\n" "For cbf_set_beam_center if the diffrn_data_frame category exists with \n" "a row for the corresponding element id, the values will be set for \n" "_diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in \n" "millimetres and the value of _diffrn_data_frame.center_units will be \n" "set to 'mm'.\n" "For cbf_set_reference_beam_center if the diffrn_detector_element \n" "category exists with a row for the corresponding element id, the \n" "values will be set for _diffrn_detector_element.reference_center_fast \n" "and _diffrn_detector_element.reference_center_slow in millimetres and \n" "the value of _diffrn_detector_element.reference_units will be set to \n" "'mm'.\n" "ARGUMENTS\n" "detector Detector handle. indexfast Pointer to the destination \n" "fast index. indexslow Pointer to the destination slow index. \n" "centerfast Pointer to the destination displacement along the fast \n" "axis. centerslow Pointer to the destination displacement along the \n" "slow axis.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_detector_struct_get_inferred_pixel_size_sf", _wrap_cbf_detector_struct_get_inferred_pixel_size_sf, METH_VARARGS, (char *)"\n" "Returns : Float pixel size\n" "*args : Int axis_number\n" "\n" "C prototype: int cbf_get_inferred_pixel_size_sf(cbf_detector detector,\n" " int axis_number, double *psize);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_inferred_pixel_size, cbf_get_inferred_pixel_size_sf set \n" "*psize to point to the double value in millimeters of the pixel size \n" "for the axis axis_number value. The slow index is treated as axis 1 \n" "and the next faster index is treated as axis 2. \n" "cbf_get_inferred_pixel_size_fs sets *psize to point to the double \n" "value in millimeters of the pixel size for the axis axis_number \n" "value. The fast index is treated as axis 1 and the next slower index \n" "is treated as axis 2.\n" "If the axis number is negative, the axes are used in the reverse \n" "order so that an axis_number of -1 indicates the fast axes in a call \n" "to cbf_get_inferred_pixel_size or cbf_get_inferred_pixel_size_sf and \n" "indicates the fast axis in a call to cbf_get_inferred_pixel_size_fs.\n" "ARGUMENTS\n" "detector Detector handle. axis_number The number of the axis. \n" "area Pointer to the destination pizel size in mm.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_detector_struct_get_pixel_coordinates", _wrap_cbf_detector_struct_get_pixel_coordinates, METH_VARARGS, (char *)"\n" "Returns : double coordinate1,double coordinate2,double coordinate3\n" "*args : double index1,double index2\n" "\n" "C prototype: int cbf_get_pixel_coordinates (cbf_detector detector,\n" " double indexslow, double indexfast, double *coordinate1,\n" " double *coordinate2, double *coordinate3);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_pixel_coordinates, cbf_get_pixel_coordinates_fs and \n" "cbf_get_pixel_coordinates_sf ses *coordinate1, *coordinate2, and \n" "*coordinate3 to the vector position of pixel (indexfast, indexslow) \n" "on the detector surface. If indexslow and indexfast are integers then \n" "the coordinates correspond to the center of a pixel.\n" "Any of the destination pointers may be NULL.\n" "ARGUMENTS\n" "detector Detector handle. indexslow Slow index. indexfast \n" " Fast index. coordinate1 Pointer to the destination x component. \n" "coordinate2 Pointer to the destination y component. coordinate3 \n" "Pointer to the destination z component.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_detector_struct_get_beam_center_sf", _wrap_cbf_detector_struct_get_beam_center_sf, METH_VARARGS, (char *)"\n" "Returns : double indexslow,double indexfast,double centerslow,double centerfast\n" "*args : \n" "\n" "C prototype: int cbf_get_beam_center_sf (cbf_detector detector,\n" " double *indexslow, double *indexfast, double *centerslow,\n" " double *centerfast);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_beam_center sets *centerfast and *centerslow to the \n" "displacements in mm along the detector axes from pixel (0, 0) to the \n" "point at which the beam intersects the detector and *indexfast and \n" "*indexslow to the corresponding indices. cbf_set_beam_center sets the \n" "offsets in the axis category for the detector element axis with \n" "precedence 1 to place the beam center at the position given in mm by \n" "*centerfast and *centerslow as the displacements in mm along the \n" "detector axes from pixel (0, 0) to the point at which the beam \n" "intersects the detector at the indices given *indexfast and \n" "*indexslow. cbf_set_reference_beam_center sets the displacments in \n" "the array_structure_list_axis category to place the beam center at \n" "the position given in mm by *centerfast and *centerslow as the \n" "displacements in mm along the detector axes from pixel (0, 0) to the \n" "point at which the beam intersects the detector at the indices given \n" "by *indexfast and *indexslow. In order to achieve consistent results, \n" "a reference detector should be used for detector to have all axes at \n" "their reference settings.\n" "Note that the precedence 1 axis is the fastest axis, so that \n" "*centerfast and *indexfast are the fast axis components of the center \n" "and *centerslow and *indexslow are the slow axis components of the \n" "center.\n" "The _fs calls give the displacments in a fast-to-slow order. The \n" "calls with no suffix and the calls _sf calls give the displacements \n" "in slow-to-fast order\n" "Any of the destination pointers may be NULL for getting the beam \n" "center. For setting the beam axis, either the indices of the center \n" "must not be NULL.\n" "The indices are non-negative for beam centers within the detector \n" "surface, but the center for an axis with a negative increment will be \n" "negative for a beam center within the detector surface.\n" "For cbf_set_beam_center if the diffrn_data_frame category exists with \n" "a row for the corresponding element id, the values will be set for \n" "_diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in \n" "millimetres and the value of _diffrn_data_frame.center_units will be \n" "set to 'mm'.\n" "For cbf_set_reference_beam_center if the diffrn_detector_element \n" "category exists with a row for the corresponding element id, the \n" "values will be set for _diffrn_detector_element.reference_center_fast \n" "and _diffrn_detector_element.reference_center_slow in millimetres and \n" "the value of _diffrn_detector_element.reference_units will be set to \n" "'mm'.\n" "ARGUMENTS\n" "detector Detector handle. indexfast Pointer to the destination \n" "fast index. indexslow Pointer to the destination slow index. \n" "centerfast Pointer to the destination displacement along the fast \n" "axis. centerslow Pointer to the destination displacement along the \n" "slow axis.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_detector_struct_get_pixel_area_sf", _wrap_cbf_detector_struct_get_pixel_area_sf, METH_VARARGS, (char *)"\n" "Returns : double area,double projected_area\n" "*args : double indexslow,double indexfast\n" "\n" "C prototype: int cbf_get_pixel_area_sf(cbf_detector detector,\n" " double indexslow, double indexfast, double *area,\n" " double *projected_area);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_pixel_area, cbf_get_pixel_area_fs and cbf_get_pixel_area_sf \n" "set *area to the area of the pixel at (indexfast, indexslow) on the \n" "detector surface and *projected_area to the apparent area of the \n" "pixel as viewed from the sample position, with indexslow being the \n" "slow axis and indexfast being the fast axis.\n" "Either of the destination pointers may be NULL.\n" "ARGUMENTS\n" "detector Detector handle. indexfast Fast index. \n" "indexslow Slow index. area Pointer to the \n" "destination area in mm2. projected_area Pointer to the destination \n" "apparent area in mm2.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_detector_struct_get_beam_center", _wrap_cbf_detector_struct_get_beam_center, METH_VARARGS, (char *)"\n" "Returns : double index1,double index2,double center1,double center2\n" "*args : \n" "\n" "C prototype: int cbf_get_beam_center (cbf_detector detector,\n" " double *indexslow, double *indexfast, double *centerslow,\n" " double *centerfast);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_beam_center sets *centerfast and *centerslow to the \n" "displacements in mm along the detector axes from pixel (0, 0) to the \n" "point at which the beam intersects the detector and *indexfast and \n" "*indexslow to the corresponding indices. cbf_set_beam_center sets the \n" "offsets in the axis category for the detector element axis with \n" "precedence 1 to place the beam center at the position given in mm by \n" "*centerfast and *centerslow as the displacements in mm along the \n" "detector axes from pixel (0, 0) to the point at which the beam \n" "intersects the detector at the indices given *indexfast and \n" "*indexslow. cbf_set_reference_beam_center sets the displacments in \n" "the array_structure_list_axis category to place the beam center at \n" "the position given in mm by *centerfast and *centerslow as the \n" "displacements in mm along the detector axes from pixel (0, 0) to the \n" "point at which the beam intersects the detector at the indices given \n" "by *indexfast and *indexslow. In order to achieve consistent results, \n" "a reference detector should be used for detector to have all axes at \n" "their reference settings.\n" "Note that the precedence 1 axis is the fastest axis, so that \n" "*centerfast and *indexfast are the fast axis components of the center \n" "and *centerslow and *indexslow are the slow axis components of the \n" "center.\n" "The _fs calls give the displacments in a fast-to-slow order. The \n" "calls with no suffix and the calls _sf calls give the displacements \n" "in slow-to-fast order\n" "Any of the destination pointers may be NULL for getting the beam \n" "center. For setting the beam axis, either the indices of the center \n" "must not be NULL.\n" "The indices are non-negative for beam centers within the detector \n" "surface, but the center for an axis with a negative increment will be \n" "negative for a beam center within the detector surface.\n" "For cbf_set_beam_center if the diffrn_data_frame category exists with \n" "a row for the corresponding element id, the values will be set for \n" "_diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in \n" "millimetres and the value of _diffrn_data_frame.center_units will be \n" "set to 'mm'.\n" "For cbf_set_reference_beam_center if the diffrn_detector_element \n" "category exists with a row for the corresponding element id, the \n" "values will be set for _diffrn_detector_element.reference_center_fast \n" "and _diffrn_detector_element.reference_center_slow in millimetres and \n" "the value of _diffrn_detector_element.reference_units will be set to \n" "'mm'.\n" "ARGUMENTS\n" "detector Detector handle. indexfast Pointer to the destination \n" "fast index. indexslow Pointer to the destination slow index. \n" "centerfast Pointer to the destination displacement along the fast \n" "axis. centerslow Pointer to the destination displacement along the \n" "slow axis.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_detector_struct_set_reference_beam_center_sf", _wrap_cbf_detector_struct_set_reference_beam_center_sf, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : double indexslow,double indexfast,double centerslow,double centerfast\n" "\n" "C prototype: int cbf_set_reference_beam_center_sf (cbf_detector detector,\n" " double *indexslow, double *indexfast, double *centerslow,\n" " double *centerfast);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_beam_center sets *centerfast and *centerslow to the \n" "displacements in mm along the detector axes from pixel (0, 0) to the \n" "point at which the beam intersects the detector and *indexfast and \n" "*indexslow to the corresponding indices. cbf_set_beam_center sets the \n" "offsets in the axis category for the detector element axis with \n" "precedence 1 to place the beam center at the position given in mm by \n" "*centerfast and *centerslow as the displacements in mm along the \n" "detector axes from pixel (0, 0) to the point at which the beam \n" "intersects the detector at the indices given *indexfast and \n" "*indexslow. cbf_set_reference_beam_center sets the displacments in \n" "the array_structure_list_axis category to place the beam center at \n" "the position given in mm by *centerfast and *centerslow as the \n" "displacements in mm along the detector axes from pixel (0, 0) to the \n" "point at which the beam intersects the detector at the indices given \n" "by *indexfast and *indexslow. In order to achieve consistent results, \n" "a reference detector should be used for detector to have all axes at \n" "their reference settings.\n" "Note that the precedence 1 axis is the fastest axis, so that \n" "*centerfast and *indexfast are the fast axis components of the center \n" "and *centerslow and *indexslow are the slow axis components of the \n" "center.\n" "The _fs calls give the displacments in a fast-to-slow order. The \n" "calls with no suffix and the calls _sf calls give the displacements \n" "in slow-to-fast order\n" "Any of the destination pointers may be NULL for getting the beam \n" "center. For setting the beam axis, either the indices of the center \n" "must not be NULL.\n" "The indices are non-negative for beam centers within the detector \n" "surface, but the center for an axis with a negative increment will be \n" "negative for a beam center within the detector surface.\n" "For cbf_set_beam_center if the diffrn_data_frame category exists with \n" "a row for the corresponding element id, the values will be set for \n" "_diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in \n" "millimetres and the value of _diffrn_data_frame.center_units will be \n" "set to 'mm'.\n" "For cbf_set_reference_beam_center if the diffrn_detector_element \n" "category exists with a row for the corresponding element id, the \n" "values will be set for _diffrn_detector_element.reference_center_fast \n" "and _diffrn_detector_element.reference_center_slow in millimetres and \n" "the value of _diffrn_detector_element.reference_units will be set to \n" "'mm'.\n" "ARGUMENTS\n" "detector Detector handle. indexfast Pointer to the destination \n" "fast index. indexslow Pointer to the destination slow index. \n" "centerfast Pointer to the destination displacement along the fast \n" "axis. centerslow Pointer to the destination displacement along the \n" "slow axis.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_detector_struct_set_beam_center_sf", _wrap_cbf_detector_struct_set_beam_center_sf, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : double indexslow,double indexfast,double centerslow,double centerfast\n" "\n" "C prototype: int cbf_set_beam_center_sf (cbf_detector detector,\n" " double *indexslow, double *indexfast, double *centerslow,\n" " double *centerfast);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_beam_center sets *centerfast and *centerslow to the \n" "displacements in mm along the detector axes from pixel (0, 0) to the \n" "point at which the beam intersects the detector and *indexfast and \n" "*indexslow to the corresponding indices. cbf_set_beam_center sets the \n" "offsets in the axis category for the detector element axis with \n" "precedence 1 to place the beam center at the position given in mm by \n" "*centerfast and *centerslow as the displacements in mm along the \n" "detector axes from pixel (0, 0) to the point at which the beam \n" "intersects the detector at the indices given *indexfast and \n" "*indexslow. cbf_set_reference_beam_center sets the displacments in \n" "the array_structure_list_axis category to place the beam center at \n" "the position given in mm by *centerfast and *centerslow as the \n" "displacements in mm along the detector axes from pixel (0, 0) to the \n" "point at which the beam intersects the detector at the indices given \n" "by *indexfast and *indexslow. In order to achieve consistent results, \n" "a reference detector should be used for detector to have all axes at \n" "their reference settings.\n" "Note that the precedence 1 axis is the fastest axis, so that \n" "*centerfast and *indexfast are the fast axis components of the center \n" "and *centerslow and *indexslow are the slow axis components of the \n" "center.\n" "The _fs calls give the displacments in a fast-to-slow order. The \n" "calls with no suffix and the calls _sf calls give the displacements \n" "in slow-to-fast order\n" "Any of the destination pointers may be NULL for getting the beam \n" "center. For setting the beam axis, either the indices of the center \n" "must not be NULL.\n" "The indices are non-negative for beam centers within the detector \n" "surface, but the center for an axis with a negative increment will be \n" "negative for a beam center within the detector surface.\n" "For cbf_set_beam_center if the diffrn_data_frame category exists with \n" "a row for the corresponding element id, the values will be set for \n" "_diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in \n" "millimetres and the value of _diffrn_data_frame.center_units will be \n" "set to 'mm'.\n" "For cbf_set_reference_beam_center if the diffrn_detector_element \n" "category exists with a row for the corresponding element id, the \n" "values will be set for _diffrn_detector_element.reference_center_fast \n" "and _diffrn_detector_element.reference_center_slow in millimetres and \n" "the value of _diffrn_detector_element.reference_units will be set to \n" "'mm'.\n" "ARGUMENTS\n" "detector Detector handle. indexfast Pointer to the destination \n" "fast index. indexslow Pointer to the destination slow index. \n" "centerfast Pointer to the destination displacement along the fast \n" "axis. centerslow Pointer to the destination displacement along the \n" "slow axis.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_detector_struct_get_pixel_normal", _wrap_cbf_detector_struct_get_pixel_normal, METH_VARARGS, (char *)"\n" "Returns : double normal1,double normal2,double normal3\n" "*args : double index1,double index2\n" "\n" "C prototype: int cbf_get_pixel_normal (cbf_detector detector,\n" " double indexslow, double indexfast, double *normal1,\n" " double *normal2, double *normal3);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_detector_normal, cbf_get_pixel_normal_fs and \n" "cbf_get_pixel_normal_sf set *normal1, *normal2, and *normal3 to the 3 \n" "components of the of the normal vector to the pixel at (indexfast, \n" "indexslow). The vector is normalized.\n" "Any of the destination pointers may be NULL.\n" "ARGUMENTS\n" "detector Detector handle. indexslow Slow index. indexfast Fast \n" "index. normal1 Pointer to the destination x component of the \n" "normal vector. normal2 Pointer to the destination y component of \n" "the normal vector. normal3 Pointer to the destination z component \n" "of the normal vector.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_detector_struct_swigregister", cbf_detector_struct_swigregister, METH_VARARGS, NULL}, { (char *)"cbf_handle_struct_node_set", _wrap_cbf_handle_struct_node_set, METH_VARARGS, (char *)"cbf_handle_struct_node_set(cbf_handle_struct self, cbf_node node)"}, { (char *)"cbf_handle_struct_node_get", _wrap_cbf_handle_struct_node_get, METH_VARARGS, (char *)"cbf_handle_struct_node_get(cbf_handle_struct self) -> cbf_node"}, { (char *)"cbf_handle_struct_row_set", _wrap_cbf_handle_struct_row_set, METH_VARARGS, (char *)"cbf_handle_struct_row_set(cbf_handle_struct self, int row)"}, { (char *)"cbf_handle_struct_row_get", _wrap_cbf_handle_struct_row_get, METH_VARARGS, (char *)"cbf_handle_struct_row_get(cbf_handle_struct self) -> int"}, { (char *)"cbf_handle_struct_search_row_set", _wrap_cbf_handle_struct_search_row_set, METH_VARARGS, (char *)"cbf_handle_struct_search_row_set(cbf_handle_struct self, int search_row)"}, { (char *)"cbf_handle_struct_search_row_get", _wrap_cbf_handle_struct_search_row_get, METH_VARARGS, (char *)"cbf_handle_struct_search_row_get(cbf_handle_struct self) -> int"}, { (char *)"new_cbf_handle_struct", _wrap_new_cbf_handle_struct, METH_VARARGS, (char *)"new_cbf_handle_struct() -> cbf_handle_struct"}, { (char *)"delete_cbf_handle_struct", _wrap_delete_cbf_handle_struct, METH_VARARGS, (char *)"delete_cbf_handle_struct(cbf_handle_struct self)"}, { (char *)"cbf_handle_struct_select_datablock", _wrap_cbf_handle_struct_select_datablock, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : Integer\n" "\n" "C prototype: int cbf_select_datablock (cbf_handle handle,\n" " unsigned int datablock);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_select_datablock selects data block number datablock as the \n" "current data block.\n" "The first data block is number 0.\n" "If the data block does not exist, the function returns CBF_NOTFOUND.\n" "ARGUMENTS\n" "handle CBF handle. datablock Number of the data block to \n" "select.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_force_new_datablock", _wrap_cbf_handle_struct_force_new_datablock, METH_VARARGS, (char *)"\n" "Returns : string\n" "*args : \n" "\n" "C prototype: int cbf_force_new_datablock (cbf_handle handle,\n" " const char *datablockname);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_force_new_datablock creates a new data block with name \n" "datablockname and makes it the current data block. Duplicate data \n" "block names are allowed. cbf_force_new_saveframe creates a new savew \n" "frame with name saveframename and makes it the current save frame. \n" "Duplicate save frame names are allowed.\n" "Even if a save frame with this name already exists, a new save frame \n" "is created and becomes the current save frame.\n" "ARGUMENTS\n" "handle CBF handle. datablockname The name of the new data \n" "block. saveframename The name of the new save frame.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_3d_image_fs_as_string", _wrap_cbf_handle_struct_get_3d_image_fs_as_string, METH_VARARGS, (char *)"\n" "Returns : (Binary)String\n" "*args : int element_number,int elsize,int elsign,int ndimfast,int ndimmid,\n" " int ndimslow\n" "\n" "C prototype: int cbf_get_3d_image_fs (cbf_handle handle,\n" " unsigned int reserved, unsigned int element_number,\n" " void *array, size_t elsize, int elsign, size_t ndimfast,\n" " size_t ndimmid, size_t ndimslow);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image \n" "array for element number element_number into an array. The array \n" "consists of ndimslow *ndimfast elements of elsize bytes each, \n" "starting at array. The elements are signed if elsign is non-0 and \n" "unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and \n" "cbf_get_real_image_sf read the image array of IEEE doubles or floats \n" "for element number element_number into an array. A real array is \n" "always signed. cbf_get_3d_image, cbf_get_3d_image_fs and \n" "cbf_get_3d_image_sf read the 3D image array for element number \n" "element_number into an array. The array consists of ndimslow *ndimmid \n" "*ndimfast elements of elsize bytes each, starting at array. The \n" "elements are signed if elsign is non-0 and unsigned otherwise. \n" "cbf_get_real_3d_image, cbf_get_real_3d_image_fs, \n" "cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or \n" "floats for element number element_number into an array. A real array \n" "is always signed.\n" "The _fs calls give the dimensions in a fast-to-slow order. The calls \n" "with no suffix and the calls _sf calls give the dimensions in \n" "slow-to-fast order\n" "The structure of the array as a 1-, 2- or 3-dimensional array should \n" "agree with the structure of the array given in the \n" "ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, \n" "ndimslow should be the array size and ndimfast and, for the 3D calls, \n" "ndimmid, should be set to 1 both in the call and in the imgCIF data \n" "being processed. If the array is 2-dimensional and a 3D call is used, \n" "ndimslow and ndimmid should be the\n" "\n" ""}, { (char *)"cbf_handle_struct_reset_datablocks", _wrap_cbf_handle_struct_reset_datablocks, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : \n" "\n" "C prototype: int cbf_reset_datablocks (cbf_handle handle);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_reset_datablocks deletes all categories from all data blocks.\n" "The current data block does not change.\n" "ARGUMENTS\n" "handle CBF handle.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_tag_category", _wrap_cbf_handle_struct_set_tag_category, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : String tagname,String categoryname_in\n" "\n" "C prototype: int cbf_set_tag_category (cbf_handle handle, const char* tagname,\n" " const char* categoryname_in);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_find_tag_category sets categoryname to the category associated \n" "with tagname in the dictionary associated with handle. \n" "cbf_set_tag_category upddates the dictionary associated with handle \n" "to indicated that tagname is in category categoryname_in.\n" "ARGUMENTS\n" "handle CBF handle. tagname tag name. \n" "categoryname pointer to a returned category name. \n" "categoryname_in input category name.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_require_tag_root", _wrap_cbf_handle_struct_require_tag_root, METH_VARARGS, (char *)"\n" "Returns : String tagroot\n" "*args : String tagname\n" "\n" "C prototype: int cbf_require_tag_root (cbf_handle handle, const char* tagname,\n" " const char** tagroot);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_find_tag_root sets *tagroot to the root tag of which tagname is \n" "an alias. cbf_set_tag_root sets tagname as an alias of tagroot_in in \n" "the dictionary associated with handle, creating the dictionary if \n" "necessary. cbf_require_tag_root sets *tagroot to the root tag of \n" "which tagname is an alias, if there is one, or to the value of \n" "tagname, if tagname is not an alias.\n" "A returned tagroot string must not be modified in any way.\n" "ARGUMENTS\n" "handle CBF handle. tagname tag name which may be an alias. \n" "tagroot pointer to a returned tag root name. tagroot_in input \n" "tag root name.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_row_number", _wrap_cbf_handle_struct_row_number, METH_VARARGS, (char *)"\n" "Returns : Integer\n" "*args : \n" "\n" "C prototype: int cbf_row_number (cbf_handle handle, unsigned int *row);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_row_number sets *row to the number of the current row of the \n" "current category.\n" "ARGUMENTS\n" "handle CBF handle. row Pointer to the destination row number.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_image", _wrap_cbf_handle_struct_set_image, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : int element_number,int compression,(binary) String data,int elsize,\n" " int elsign,int dimslow,int dimfast\n" "\n" "C prototype: int cbf_set_image (cbf_handle handle, unsigned int reserved,\n" " unsigned int element_number, unsigned int compression,\n" " void *array, size_t elsize, int elsign, size_t ndimslow,\n" " size_t ndimfast);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image \n" "array for element number element_number. The array consists of \n" "ndimfast *ndimslow elements of elsize bytes each, starting at array. \n" "The elements are signed if elsign is non-zero and unsigned otherwise. \n" "cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf \n" "write the image array for element number element_number. The array \n" "consists of ndimfast *ndimslow IEEE double or float elements of \n" "elsize bytes each, starting at array. cbf_set_3d_image, \n" "cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array \n" "for element number element_number. The array consists of ndimfast \n" "*ndimmid *ndimslow elements of elsize bytes each, starting at array. \n" "The elements are signed if elsign is non-0 and unsigned otherwise. \n" "cbf_set_real_3d_image, cbf_set_real_3d_image_fs and \n" "cbf_set_real_3d_image_sf writes the 3D image array for element number \n" "element_number. The array consists of ndimfast *ndimmid *ndimslow \n" "IEEE double or float elements of elsize bytes each, starting at \n" "array.\n" "The _fs calls give the dimensions in a fast-to-slow order. The calls \n" "with no suffix and the calls _sf calls give the dimensions in \n" "slow-to-fast order\n" "If the array is 1-dimensional, ndimslow should be the array size and \n" "ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the \n" "array is 2-dimensional and the 3D calls are used, ndimslow and \n" "ndimmid should be used for the array dimensions and ndimfast should \n" "be set to 1.\n" "The array will be compressed using the compression scheme specifed by \n" "compression. Currently, the available schemes are:\n" "CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED \n" " CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style \n" "packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \n" "\"byte_offset \" compression. CBF_NONE No compression.\n" "The values compressed are limited to 64 bits. If any element in the \n" "array is larger than 64 bits, the value compressed is the nearest \n" "64-bit value.\n" "Currently, the source array must consist of chars, shorts or ints \n" "(signed or unsigned)for cbf_set_image, or IEEE doubles or floats for \n" "cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof \n" "(int), sizeof(double) or sizeof(float), the function returns \n" "CBF_ARGUMENT.\n" "The parameter reserved is presently unused and should be set to 0.\n" "ARGUMENTS\n" "handle CBF handle. reserved Unused. Any value other \n" "than 0 is invalid. element_number The number of the detector \n" "element counting from 0 by order of appearance in the \n" "\"diffrn_data_frame \" category. compression Compression type. \n" "array Pointer to the image array. elsize Size in \n" "bytes of each image array element. elsigned Set to non-0 if \n" "the image array elements are signed. ndimslow Slowest array \n" "dimension. ndimmid Second slowest array dimension. ndimfast \n" " Fastest array dimension.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_set_bin_sizes", _wrap_cbf_handle_struct_set_bin_sizes, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : Integer element_number,Float slowbinsize_in,Float fastbinsize_in\n" "\n" "C prototype: int cbf_set_bin_sizes(cbf_handle handle,\n" " unsigned int element_number, double slowbinsize_in,\n" " double fastbinsize_in);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_bin_sizes sets slowbinsize to point to the value of the \n" "number of pixels composing one array element in the dimension that \n" "changes at the second-fastest rate and fastbinsize to point to the \n" "value of the number of pixels composing one array element in the \n" "dimension that changes at the fastest rate for the dectector element \n" "with the ordinal element_number. cbf_set_bin_sizes sets the the pixel \n" "bin sizes in the \"array_intensities \" category to the values of \n" "slowbinsize_in for the number of pixels composing one array element \n" "in the dimension that changes at the second-fastest rate and \n" "fastbinsize_in for the number of pixels composing one array element \n" "in the dimension that changes at the fastest rate for the dectector \n" "element with the ordinal element_number.\n" "In order to allow for software binning involving fractions of pixels, \n" "the bin sizes are doubles rather than ints.\n" "ARGUMENTS\n" "handle CBF handle. element_number The number of the \n" "detector element counting from 0 by order of appearance in the \n" "\"diffrn_data_frame \" category. slowbinsize Pointer to the \n" "returned number of pixels composing one array element in the \n" "dimension that changes at the second-fastest rate. fastbinsize \n" "Pointer to the returned number of pixels composing one array element \n" "in the dimension that changes at the fastest rate. slowbinsize_in \n" "The number of pixels composing one array element in the dimension \n" "that changes at the second-fastest rate. fastbinsize_in The number \n" "of pixels composing one array element in the dimension that changes \n" "at the fastest rate.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_new_row", _wrap_cbf_handle_struct_new_row, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : \n" "\n" "C prototype: int cbf_new_row (cbf_handle handle);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_new_row adds a new row to the current category and makes it the \n" "current row.\n" "ARGUMENTS\n" "handle CBF handle.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_rewind_saveframe", _wrap_cbf_handle_struct_rewind_saveframe, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : \n" "\n" "C prototype: int cbf_rewind_saveframe (cbf_handle handle);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_rewind_category makes the first category in the current data \n" "block the current category. cbf_rewind_saveframe makes the first \n" "saveframe in the current data block the current saveframe. \n" "cbf_rewind_blockitem makes the first blockitem (category or \n" "saveframe) in the current data block the current blockitem. The type \n" "of the blockitem (CBF_CATEGORY or CBF_SAVEFRAME) is returned in type.\n" "If there are no categories, saveframes or blockitems the function \n" "returns CBF_NOTFOUND.\n" "The current column and row become undefined.\n" "ARGUMENTS\n" "handle CBF handle. type CBF handle.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_realarrayparameters", _wrap_cbf_handle_struct_get_realarrayparameters, METH_VARARGS, (char *)"\n" "Returns : int compression,int binary_id,int elsize,int elements\n" "*args : \n" "\n" "C prototype: int cbf_get_realarrayparameters (cbf_handle handle,\n" " unsigned int *compression, int *binary_id, size_t *elsize,\n" " size_t *elements);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_integerarrayparameters sets *compression, *binary_id, \n" "*elsize, *elsigned, *elunsigned, *elements, *minelement and \n" "*maxelement to values read from the binary value of the item at the \n" "current column and row. This provides all the arguments needed for a \n" "subsequent call to cbf_set_integerarray, if a copy of the array is to \n" "be made into another CIF or CBF. cbf_get_realarrayparameters sets \n" "*compression, *binary_id, *elsize, *elements to values read from the \n" "binary value of the item at the current column and row. This provides \n" "all the arguments needed for a subsequent call to cbf_set_realarray, \n" "if a copy of the arry is to be made into another CIF or CBF.\n" "The variants cbf_get_integerarrayparameters_wdims, \n" "cbf_get_integerarrayparameters_wdims_fs, \n" "cbf_get_integerarrayparameters_wdims_sf, \n" "cbf_get_realarrayparameters_wdims, \n" "cbf_get_realarrayparameters_wdims_fs, \n" "cbf_get_realarrayparameters_wdims_sf set **byteorder, *dimfast, \n" "*dimmid, *dimslow, and *padding as well, providing the additional \n" "parameters needed for a subsequent call to cbf_set_integerarray_wdims \n" "or cbf_set_realarray_wdims.\n" "The value returned in *byteorder is a pointer either to the string \n" "\"little_endian \" or to the string \"big_endian \". This should be \n" "the byte order of the data, not necessarily of the host machine. No \n" "attempt should be made to modify this string. At this time only \n" "\"little_endian \" will be returned.\n" "The values returned in *dimfast, *dimmid and *dimslow are the sizes \n" "of the fastest changing, second fastest changing and third fastest \n" "changing dimensions of the array, if specified, or zero, if not \n" "specified.\n" "The value returned in *padding is the size of the post-data padding, \n" "if any and if specified in the data header. The value is given as a \n" "count of octets.\n" "If the value is not binary, the function returns CBF_ASCII.\n" "ARGUMENTS\n" "handle CBF handle. compression Compression method used. \n" "elsize Size in bytes of each array element. binary_id \n" "Pointer to the destination integer binary identifier. elsigned \n" "Pointer to an integer. Set to 1 if the elements can be read as signed \n" "integers. elunsigned Pointer to an integer. Set to 1 if the \n" "elements can be read as unsigned integers. elements Pointer to \n" "the destination number of elements. minelement Pointer to the \n" "destination smallest element. maxelement Pointer to the \n" "destination largest element. byteorder Pointer to the destination \n" "byte order. dimfast Pointer to the destination fastest \n" "dimension. dimmid Pointer to the destination second fastest \n" "dimension. dimslow Pointer to the destination third fastest \n" "dimension. padding Pointer to the destination padding size.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_pixel_size_sf", _wrap_cbf_handle_struct_get_pixel_size_sf, METH_VARARGS, (char *)"\n" "Returns : Float pixel_size\n" "*args : Int element_number,Int axis_number\n" "\n" "C prototype: int cbf_get_pixel_size_sf(cbf_handle handle,\n" " unsigned int element_number, int axis_number,\n" " double *psize);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_pixel_size and cbf_get_pixel_size_sf set *psize to point to \n" "the double value in millimeters of the axis axis_number of the \n" "detector element element_number. The axis_number is numbered from 1, \n" "starting with the slowest axis. cbf_get_pixel_size_fs sets *psize to \n" "point to the double value in millimeters of the axis axis_number of \n" "the detector element element_number. The axis_number is numbered from \n" "1, starting with the fastest axis.\n" "If a negative axis number is given, the order of axes is reversed, so \n" "that -1 specifies the slowest axis for cbf_get_pixel_size_fs and the \n" "fastest axis for cbf_get_pixel_size_sf.\n" "If the pixel size is not given explcitly in the \"array_element_size \n" "\" category, the function returns CBF_NOTFOUND.\n" "ARGUMENTS\n" "handle CBF handle. element_number The number of the \n" "detector element counting from 0 by order of appearance in the \n" "\"diffrn_data_frame \" category. axis_number The number of the \n" "axis, starting from 1 for the fastest for cbf_get_pixel_size and \n" "cbf_get_pixel_size_fs and the slowest for cbf_get_pixel_size_sf. \n" "psize Pointer to the destination pixel size.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_force_new_category", _wrap_cbf_handle_struct_force_new_category, METH_VARARGS, (char *)"\n" "Returns : string\n" "*args : \n" "\n" "C prototype: int cbf_force_new_category (cbf_handle handle,\n" " const char *categoryname);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_force_new_category creates a new category in the current data \n" "block with name categoryname and makes it the current category. \n" "Duplicate category names are allowed.\n" "Even if a category with this name already exists, a new category of \n" "the same name is created and becomes the current category. The allows \n" "for the creation of unlooped tag/value lists drawn from the same \n" "category.\n" "ARGUMENTS\n" "handle CBF handle. categoryname The name of the new \n" "category.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_force_new_saveframe", _wrap_cbf_handle_struct_force_new_saveframe, METH_VARARGS, (char *)"\n" "Returns : string\n" "*args : \n" "\n" "C prototype: int cbf_force_new_saveframe (cbf_handle handle,\n" " const char *saveframename);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_force_new_datablock creates a new data block with name \n" "datablockname and makes it the current data block. Duplicate data \n" "block names are allowed. cbf_force_new_saveframe creates a new savew \n" "frame with name saveframename and makes it the current save frame. \n" "Duplicate save frame names are allowed.\n" "Even if a save frame with this name already exists, a new save frame \n" "is created and becomes the current save frame.\n" "ARGUMENTS\n" "handle CBF handle. datablockname The name of the new data \n" "block. saveframename The name of the new save frame.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_count_datablocks", _wrap_cbf_handle_struct_count_datablocks, METH_VARARGS, (char *)"\n" "Returns : Integer\n" "*args : \n" "\n" "C prototype: int cbf_count_datablocks (cbf_handle handle,\n" " unsigned int *datablocks);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_count_datablocks puts the number of data blocks in *datablocks .\n" "ARGUMENTS\n" "handle CBF handle. datablocks Pointer to the destination data \n" "block count.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_find_row", _wrap_cbf_handle_struct_find_row, METH_VARARGS, (char *)"\n" "Returns : string\n" "*args : \n" "\n" "C prototype: int cbf_find_row (cbf_handle handle, const char *value);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_find_row makes the first row in the current column with value \n" "value the current row.\n" "The comparison is case-sensitive.\n" "If a matching row does not exist, the function returns CBF_NOTFOUND.\n" "The current column is not affected.\n" "ARGUMENTS\n" "handle CBF handle. value The value of the row to find.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_select_column", _wrap_cbf_handle_struct_select_column, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : Integer\n" "\n" "C prototype: int cbf_select_column (cbf_handle handle, unsigned int column);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_select_column selects column number column in the current \n" "category as the current column.\n" "The first column is number 0.\n" "The current row is not affected\n" "If the column does not exist, the function returns CBF_NOTFOUND.\n" "ARGUMENTS\n" "handle CBF handle. column Number of the column to select.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_construct_detector", _wrap_cbf_handle_struct_construct_detector, METH_VARARGS, (char *)"\n" "Returns : pycbf detector object\n" "*args : Integer element_number\n" "\n" "C prototype: int cbf_construct_detector (cbf_handle handle,\n" " cbf_detector *detector, unsigned int element_number);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_construct_detector constructs a detector object for detector \n" "element number element_number using the description in the CBF object \n" "handle and initialises the detector handle *detector.\n" "cbf_construct_reference_detector constructs a detector object for \n" "detector element number element_number using the description in the \n" "CBF object handle and initialises the detector handle *detector using \n" "the reference settings of the axes. cbf_require_reference_detector is \n" "similar, but try to force the creations of missing intermediate \n" "categories needed to construct a detector object.\n" "ARGUMENTS\n" "handle CBF handle. detector Pointer to the \n" "destination detector handle. element_number The number of the \n" "detector element counting from 0 by order of appearance in the \n" "\"diffrn_data_frame \" category.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_rewind_column", _wrap_cbf_handle_struct_rewind_column, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : \n" "\n" "C prototype: int cbf_rewind_column (cbf_handle handle);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_rewind_column makes the first column in the current category the \n" "current column.\n" "If there are no columns, the function returns CBF_NOTFOUND.\n" "The current row is not affected.\n" "ARGUMENTS\n" "handle CBF handle.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_require_column_doublevalue", _wrap_cbf_handle_struct_require_column_doublevalue, METH_VARARGS, (char *)"\n" "Returns : Float defaultvalue\n" "*args : String columnname,Float Value\n" "\n" "C prototype: int cbf_require_column_doublevalue (cbf_handle handle,\n" " const char *columnname, double *number,\n" " const double defaultvalue);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_require_column_doublevalue sets *number to the value of the ASCII \n" "item at the current row for the column given with the name given by \n" "*columnname, with the value interpreted as a decimal floating-point \n" "number, or to the number given by defaultvalue if the item cannot be \n" "found.\n" "ARGUMENTS\n" "handle CBF handle. columnname Name of the column \n" "containing the number. number pointer to the location to \n" "receive the floating-point value. defaultvalue Value to use if the \n" "requested column and value cannot be found.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_datestamp", _wrap_cbf_handle_struct_get_datestamp, METH_VARARGS, (char *)"\n" "Returns : int year,int month,int day,int hour,int minute,double second,\n" " int timezone\n" "*args : \n" "\n" "C prototype: int cbf_get_datestamp (cbf_handle handle, unsigned int reserved,\n" " int *year, int *month, int *day, int *hour, int *minute,\n" " double *second, int *timezone);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_datestamp sets *year, *month, *day, *hour, *minute and \n" "*second to the corresponding values of the collection timestamp. \n" "*timezone is set to timezone difference from UTC in minutes. The \n" "parameter < i>reserved is presently unused and should be set to 0.\n" "Any of the destination pointers may be NULL.\n" "ARGUMENTS\n" "handle CBF handle. reserved Unused. Any value other than 0 is \n" "invalid. year Pointer to the destination timestamp year. month \n" " Pointer to the destination timestamp month (1-12). day \n" "Pointer to the destination timestamp day (1-31). hour Pointer \n" "to the destination timestamp hour (0-23). minute Pointer to the \n" "destination timestamp minute (0-59). second Pointer to the \n" "destination timestamp second (0-60.0). timezone Pointer to the \n" "destination timezone difference from UTC in minutes.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_get_integervalue", _wrap_cbf_handle_struct_get_integervalue, METH_VARARGS, (char *)"\n" "Returns : int\n" "*args : \n" "\n" "C prototype: int cbf_get_integervalue (cbf_handle handle, int *number);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_integervalue sets *number to the value of the ASCII item at \n" "the current column and row interpreted as a decimal integer. \n" "cbf_require_integervalue sets *number to the value of the ASCII item \n" "at the current column and row interpreted as a decimal integer, \n" "setting it to defaultvalue if necessary.\n" "If the value is not ASCII, the function returns CBF_BINARY.\n" "ARGUMENTS\n" "handle CBF handle. number pointer to the number. \n" "defaultvalue default number value.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_crystal_id", _wrap_cbf_handle_struct_get_crystal_id, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : string\n" "\n" "C prototype: int cbf_get_crystal_id (cbf_handle handle,\n" " const char **crystal_id);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_crystal_id sets *crystal_id to point to the ASCII value of \n" "the \"diffrn.crystal_id \" entry.\n" "If the value is not ASCII, the function returns CBF_BINARY.\n" "The value will be valid as long as the item exists and has not been \n" "set to a new value.\n" "The value must not be modified by the program in any way.\n" "ARGUMENTS\n" "handle CBF handle. crystal_id Pointer to the destination \n" "value pointer.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_get_doublevalue", _wrap_cbf_handle_struct_get_doublevalue, METH_VARARGS, (char *)"\n" "Returns : double\n" "*args : \n" "\n" "C prototype: int cbf_get_doublevalue (cbf_handle handle, double *number);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_doublevalue sets *number to the value of the ASCII item at \n" "the current column and row interpreted as a decimal floating-point \n" "number. cbf_require_doublevalue sets *number to the value of the \n" "ASCII item at the current column and row interpreted as a decimal \n" "floating-point number, setting it to defaultvalue if necessary.\n" "If the value is not ASCII, the function returns CBF_BINARY.\n" "ARGUMENTS\n" "handle CBF handle. number Pointer to the destination \n" "number. defaultvalue default number value.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_unit_cell", _wrap_cbf_handle_struct_get_unit_cell, METH_VARARGS, (char *)"\n" "Returns : Float a,Float b,Float c,Float alpha,Float beta,Float gamma\n" "*args : \n" "\n" "C prototype: int cbf_get_unit_cell (cbf_handle handle, double cell[6],\n" " double cell_esd[6] );\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_unit_cell sets cell[0:2] to the double values of the cell \n" "edge lengths a, b and c in AAngstroms, cell[3:5] to the double values \n" "of the cell angles a, b and g in degrees, cell_esd[0:2] to the double \n" "values of the estimated strandard deviations of the cell edge lengths \n" "a, b and c in AAngstroms, cell_esd[3:5] to the double values of the \n" "estimated standard deviations of the the cell angles a, b and g in \n" "degrees.\n" "The values returned are retrieved from the first row of the \"cell \n" "\" category. The value of \"_cell.entry_id \" is ignored.\n" "cell or cell_esd may be NULL.\n" "If cell is NULL, the cell parameters are not retrieved.\n" "If cell_esd is NULL, the cell parameter esds are not retrieved.\n" "If the \"cell \" category is present, but some of the values are \n" "missing, zeros are returned for the missing values.\n" "ARGUMENTS\n" "handle CBF handle. cell Pointer to the destination array of \n" "6 doubles for the cell parameters. cell_esd Pointer to the \n" "destination array of 6 doubles for the cell parameter esds.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success. No errors is \n" "returned for missing values if the \"cell \" category exists.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_unit_cell_esd", _wrap_cbf_handle_struct_get_unit_cell_esd, METH_VARARGS, (char *)"cbf_handle_struct_get_unit_cell_esd(cbf_handle_struct self)"}, { (char *)"cbf_handle_struct_remove_column", _wrap_cbf_handle_struct_remove_column, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : \n" "\n" "C prototype: int cbf_remove_column (cbf_handle handle);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_remove_column deletes the current column.\n" "The current column becomes undefined.\n" "ARGUMENTS\n" "handle CBF handle.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_rewind_blockitem", _wrap_cbf_handle_struct_rewind_blockitem, METH_VARARGS, (char *)"\n" "Returns : CBF_NODETYPE\n" "*args : \n" "\n" "C prototype: int cbf_rewind_blockitem (cbf_handle handle,\n" " CBF_NODETYPE * type);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_rewind_category makes the first category in the current data \n" "block the current category. cbf_rewind_saveframe makes the first \n" "saveframe in the current data block the current saveframe. \n" "cbf_rewind_blockitem makes the first blockitem (category or \n" "saveframe) in the current data block the current blockitem. The type \n" "of the blockitem (CBF_CATEGORY or CBF_SAVEFRAME) is returned in type.\n" "If there are no categories, saveframes or blockitems the function \n" "returns CBF_NOTFOUND.\n" "The current column and row become undefined.\n" "ARGUMENTS\n" "handle CBF handle. type CBF handle.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_value", _wrap_cbf_handle_struct_get_value, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : string\n" "\n" "C prototype: int cbf_get_value (cbf_handle handle, const char **value);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_value sets *value to point to the ASCII value of the item at \n" "the current column and row. cbf_require_value sets *value to point to \n" "the ASCII value of the item at the current column and row, creating \n" "the data item if necessary and initializing it to a copy of \n" "defaultvalue.\n" "If the value is not ASCII, the function returns CBF_BINARY.\n" "The value will be valid as long as the item exists and has not been \n" "set to a new value.\n" "The value must not be modified by the program in any way.\n" "ARGUMENTS\n" "handle CBF handle. value Pointer to the destination \n" "value pointer. defaultvalue Default value character string.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_count_categories", _wrap_cbf_handle_struct_count_categories, METH_VARARGS, (char *)"\n" "Returns : Integer\n" "*args : \n" "\n" "C prototype: int cbf_count_categories (cbf_handle handle,\n" " unsigned int *categories);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_count_categories puts the number of categories in the current \n" "data block in *categories.\n" "ARGUMENTS\n" "handle CBF handle. categories Pointer to the destination \n" "category count.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_read_widefile", _wrap_cbf_handle_struct_read_widefile, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : String filename,Integer headers\n" "\n" "C prototype: int cbf_read_widefile (cbf_handle handle, FILE *file, int flags);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_read_file reads the CBF or CIF file file into the CBF object \n" "specified by handle, using the CIF 1.0 convention of 80 character \n" "lines. cbf_read_widefile reads the CBF or CIF file file into the CBF \n" "object specified by handle, using the CIF 1.1 convention of 2048 \n" "character lines. A warning is issued to stderr for ascii lines over \n" "the limit. No test is performed on binary sections.\n" "Validation is performed in three ways levels: during the lexical \n" "scan, during the parse, and, if a dictionary was converted, against \n" "the value types, value enumerations, categories and parent-child \n" "relationships specified in the dictionary.\n" "flags controls the interpretation of binary section headers, the \n" "parsing of brackets constructs and the parsing of treble-quoted \n" "strings.\n" "MSG_DIGEST: Instructs CBFlib to check that the digest \n" "of the binary section matches any header digest value. If the digests \n" "do not match, the call will return CBF_FORMAT. This evaluation and \n" "comparison is delayed (a \"lazy \" evaluation) to ensure maximal \n" "processing efficiency. If an immediately evaluation is required, see \n" "MSG_DIGESTNOW, below. MSG_DIGESTNOW: Instructs CBFlib to \n" "check that the digest of the binary section matches any header \n" "digeste value. If the digests do not match, the call will return \n" "CBF_FORMAT. This evaluation and comparison is performed during \n" "initial parsing of the section to ensure timely error reporting at \n" "the expense of processing efficiency. If a more efficient delayed ( \n" "\"lazy \") evaluation is required, see MSG_DIGEST, above. \n" "MSG_DIGESTWARN: Instructs CBFlib to check that the digest \n" "of the binary section matches any header digeste value. If the \n" "digests do not match, a warning message will be sent to stderr, but \n" "processing will attempt to continue. This evaluation and comparison \n" "is first performed during initial parsing of the section to ensure \n" "timely error reporting at the expense of processing efficiency. An \n" "mismatch of the message digest usually indicates a serious error, but \n" "it is sometimes worth continuing processing to try to isolate the \n" "cause of the error. Use this option with caution. MSG_NODIGEST: \n" " Do not check the digest (default). PARSE_BRACKETS: \n" "Accept DDLm bracket-delimited [item,item,...item] or \n" "{item,item,...item} or (item,item,...item) constructs as valid, \n" "stripping non-quoted embedded whitespace and comments. These \n" "constructs may span multiple lines. PARSE_LIBERAL_BRACKETS: Accept \n" "DDLm bracket-delimited [item,item,...item] or {item,item,...item} or \n" "(item,item,...item) constructs as valid, stripping embedded \n" "non-quoted, non-separating whitespace and comments. These constructs \n" "may span multiple lines. In this case, whitespace may be used as an \n" "alternative to the comma. PARSE_TRIPLE_QUOTES: Accept DDLm \n" "triple-quoted \" \" \"item,item,...item \" \" \" or \n" "'''item,item,...item''' constructs as valid, stripping embedded \n" "whitespace and comments. These constructs may span multiple lines. If \n" "this flag is set, then ''' will not be interpreted as a quoted \n" "apoptrophe and \" \" \" will not be interpreted as a quoted double \n" "quote mark and PARSE_NOBRACKETS: Do not accept DDLm \n" "bracket-delimited [item,item,...item] or {item,item,...item} or \n" "(item,item,...item) constructs as valid, stripping non-quoted \n" "embedded whitespace and comments. These constructs may span multiple \n" "lines. PARSE_NOTRIPLE_QUOTES: No not accept DDLm triple-quoted \" \n" "\" \"item,item,...item \" \" \" or '''item,item,...item''' constructs \n" "as valid, stripping embedded whitespace and comments. These \n" "constructs may span multiple lines. If this flag is set, then ''' \n" "will be interpreted as a quoted apostrophe and \" \" \" will be \n" "interpreted as a quoted double quote mark.\n" "CBFlib defers reading binary sections as long as possible. In the \n" "current version of CBFlib, this means that:\n" "1. The file must be a random-access file opened in binary mode (fopen \n" "( ,\n" "\n" ""}, { (char *)"cbf_handle_struct_set_wavelength", _wrap_cbf_handle_struct_set_wavelength, METH_VARARGS, (char *)"\n" "Returns : double wavelength\n" "*args : \n" "\n" "C prototype: int cbf_set_wavelength (cbf_handle handle, double wavelength);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_wavelength sets the current wavelength in AA to wavelength.\n" "ARGUMENTS\n" "handle CBF handle. wavelength Wavelength in AA.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_set_pixel_size_sf", _wrap_cbf_handle_struct_set_pixel_size_sf, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : Int element_number,Int axis_number,Float pixel size\n" "\n" "C prototype: int cbf_set_pixel_size_sf(cbf_handle handle,\n" " unsigned int element_number, int axis_number,\n" " double psize);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_pixel_size and cbf_set_pixel_size_sf set the item in the \n" ""e;size"e; column of the \"array_structure_list \" category \n" "at the row which matches axis axis_number of the detector element \n" "element_number converting the double pixel size psize from meters to \n" "millimeters in storing it in the \"size \" column for the axis \n" "axis_number of the detector element element_number. The axis_number \n" "is numbered from 1, starting with the slowest axis. \n" "cbf_set_pixel_size_fs sets the item\n" "\n" ""}, { (char *)"cbf_handle_struct_get_diffrn_id", _wrap_cbf_handle_struct_get_diffrn_id, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : string\n" "\n" "C prototype: int cbf_get_diffrn_id (cbf_handle handle,\n" " const char **diffrn_id);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_diffrn_id sets *diffrn_id to point to the ASCII value of the \n" "\"diffrn.id \" entry. cbf_require_diffrn_id also sets *diffrn_id to \n" "point to the ASCII value of the \"diffrn.id \" entry, but, if the \n" "\"diffrn.id \" entry does not exist, it sets the value in the CBF and \n" "in*diffrn_id to the character string given by default_id, creating \n" "the category and column is necessary.\n" "The diffrn_id will be valid as long as the item exists and has not \n" "been set to a new value.\n" "The diffrn_id must not be modified by the program in any way.\n" "ARGUMENTS\n" "handle CBF handle. diffrn_id Pointer to the destination \n" "value pointer. default_id Character string default value.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_find_datablock", _wrap_cbf_handle_struct_find_datablock, METH_VARARGS, (char *)"\n" "Returns : string\n" "*args : \n" "\n" "C prototype: int cbf_find_datablock (cbf_handle handle,\n" " const char *datablockname);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_find_datablock makes the data block with name datablockname the \n" "current data block.\n" "The comparison is case-insensitive.\n" "If the data block does not exist, the function returns CBF_NOTFOUND.\n" "The current category becomes undefined.\n" "ARGUMENTS\n" "handle CBF handle. datablockname The name of the data \n" "block to find.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_polarization", _wrap_cbf_handle_struct_get_polarization, METH_VARARGS, (char *)"\n" "Returns : float polarizn_source_ratio,float polarizn_source_norm\n" "*args : \n" "\n" "C prototype: int cbf_get_polarization (cbf_handle handle,\n" " double *polarizn_source_ratio,\n" " double *polarizn_source_norm);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_polarization sets *polarizn_source_ratio and \n" "*polarizn_source_norm to the corresponding source polarization \n" "parameters.\n" "Either destination pointer may be NULL.\n" "ARGUMENTS\n" "handle CBF handle. polarizn_source_ratio Pointer \n" "to the destination polarizn_source_ratio. polarizn_source_norm \n" "Pointer to the destination polarizn_source_norm.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_select_category", _wrap_cbf_handle_struct_select_category, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : Integer\n" "\n" "C prototype: int cbf_select_category (cbf_handle handle,\n" " unsigned int category);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_select_category selects category number category in the current \n" "data block as the current category.\n" "The first category is number 0.\n" "The current column and row become undefined.\n" "If the category does not exist, the function returns CBF_NOTFOUND.\n" "ARGUMENTS\n" "handle CBF handle. category Number of the category to select.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_pixel_size_fs", _wrap_cbf_handle_struct_get_pixel_size_fs, METH_VARARGS, (char *)"\n" "Returns : Float pixel_size\n" "*args : Int element_number,Int axis_number\n" "\n" "C prototype: int cbf_get_pixel_size_fs(cbf_handle handle,\n" " unsigned int element_number, int axis_number,\n" " double *psize);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_pixel_size and cbf_get_pixel_size_sf set *psize to point to \n" "the double value in millimeters of the axis axis_number of the \n" "detector element element_number. The axis_number is numbered from 1, \n" "starting with the slowest axis. cbf_get_pixel_size_fs sets *psize to \n" "point to the double value in millimeters of the axis axis_number of \n" "the detector element element_number. The axis_number is numbered from \n" "1, starting with the fastest axis.\n" "If a negative axis number is given, the order of axes is reversed, so \n" "that -1 specifies the slowest axis for cbf_get_pixel_size_fs and the \n" "fastest axis for cbf_get_pixel_size_sf.\n" "If the pixel size is not given explcitly in the \"array_element_size \n" "\" category, the function returns CBF_NOTFOUND.\n" "ARGUMENTS\n" "handle CBF handle. element_number The number of the \n" "detector element counting from 0 by order of appearance in the \n" "\"diffrn_data_frame \" category. axis_number The number of the \n" "axis, starting from 1 for the fastest for cbf_get_pixel_size and \n" "cbf_get_pixel_size_fs and the slowest for cbf_get_pixel_size_sf. \n" "psize Pointer to the destination pixel size.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_read_file", _wrap_cbf_handle_struct_read_file, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : String filename,Integer headers\n" "\n" "C prototype: int cbf_read_file (cbf_handle handle, FILE *file, int flags);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_read_file reads the CBF or CIF file file into the CBF object \n" "specified by handle, using the CIF 1.0 convention of 80 character \n" "lines. cbf_read_widefile reads the CBF or CIF file file into the CBF \n" "object specified by handle, using the CIF 1.1 convention of 2048 \n" "character lines. A warning is issued to stderr for ascii lines over \n" "the limit. No test is performed on binary sections.\n" "Validation is performed in three ways levels: during the lexical \n" "scan, during the parse, and, if a dictionary was converted, against \n" "the value types, value enumerations, categories and parent-child \n" "relationships specified in the dictionary.\n" "flags controls the interpretation of binary section headers, the \n" "parsing of brackets constructs and the parsing of treble-quoted \n" "strings.\n" "MSG_DIGEST: Instructs CBFlib to check that the digest \n" "of the binary section matches any header digest value. If the digests \n" "do not match, the call will return CBF_FORMAT. This evaluation and \n" "comparison is delayed (a \"lazy \" evaluation) to ensure maximal \n" "processing efficiency. If an immediately evaluation is required, see \n" "MSG_DIGESTNOW, below. MSG_DIGESTNOW: Instructs CBFlib to \n" "check that the digest of the binary section matches any header \n" "digeste value. If the digests do not match, the call will return \n" "CBF_FORMAT. This evaluation and comparison is performed during \n" "initial parsing of the section to ensure timely error reporting at \n" "the expense of processing efficiency. If a more efficient delayed ( \n" "\"lazy \") evaluation is required, see MSG_DIGEST, above. \n" "MSG_DIGESTWARN: Instructs CBFlib to check that the digest \n" "of the binary section matches any header digeste value. If the \n" "digests do not match, a warning message will be sent to stderr, but \n" "processing will attempt to continue. This evaluation and comparison \n" "is first performed during initial parsing of the section to ensure \n" "timely error reporting at the expense of processing efficiency. An \n" "mismatch of the message digest usually indicates a serious error, but \n" "it is sometimes worth continuing processing to try to isolate the \n" "cause of the error. Use this option with caution. MSG_NODIGEST: \n" " Do not check the digest (default). PARSE_BRACKETS: \n" "Accept DDLm bracket-delimited [item,item,...item] or \n" "{item,item,...item} or (item,item,...item) constructs as valid, \n" "stripping non-quoted embedded whitespace and comments. These \n" "constructs may span multiple lines. PARSE_LIBERAL_BRACKETS: Accept \n" "DDLm bracket-delimited [item,item,...item] or {item,item,...item} or \n" "(item,item,...item) constructs as valid, stripping embedded \n" "non-quoted, non-separating whitespace and comments. These constructs \n" "may span multiple lines. In this case, whitespace may be used as an \n" "alternative to the comma. PARSE_TRIPLE_QUOTES: Accept DDLm \n" "triple-quoted \" \" \"item,item,...item \" \" \" or \n" "'''item,item,...item''' constructs as valid, stripping embedded \n" "whitespace and comments. These constructs may span multiple lines. If \n" "this flag is set, then ''' will not be interpreted as a quoted \n" "apoptrophe and \" \" \" will not be interpreted as a quoted double \n" "quote mark and PARSE_NOBRACKETS: Do not accept DDLm \n" "bracket-delimited [item,item,...item] or {item,item,...item} or \n" "(item,item,...item) constructs as valid, stripping non-quoted \n" "embedded whitespace and comments. These constructs may span multiple \n" "lines. PARSE_NOTRIPLE_QUOTES: No not accept DDLm triple-quoted \" \n" "\" \"item,item,...item \" \" \" or '''item,item,...item''' constructs \n" "as valid, stripping embedded whitespace and comments. These \n" "constructs may span multiple lines. If this flag is set, then ''' \n" "will be interpreted as a quoted apostrophe and \" \" \" will be \n" "interpreted as a quoted double quote mark.\n" "CBFlib defers reading binary sections as long as possible. In the \n" "current version of CBFlib, this means that:\n" "1. The file must be a random-access file opened in binary mode (fopen \n" "( ,\n" "\n" ""}, { (char *)"cbf_handle_struct_datablock_name", _wrap_cbf_handle_struct_datablock_name, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : string\n" "\n" "C prototype: int cbf_datablock_name (cbf_handle handle,\n" " const char **datablockname);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_datablock_name sets *datablockname to point to the name of the \n" "current data block.\n" "The data block name will be valid as long as the data block exists \n" "and has not been renamed.\n" "The name must not be modified by the program in any way.\n" "ARGUMENTS\n" "handle CBF handle. datablockname Pointer to the \n" "destination data block name pointer.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_realarray_wdims", _wrap_cbf_handle_struct_set_realarray_wdims, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : int compression,int binary_id,(binary) String data,int elsize,\n" " int elements,String byteorder,int dimfast,int dimmid,int dimslow,\n" " int padding\n" "\n" "C prototype: int cbf_set_realarray_wdims (cbf_handle handle,\n" " unsigned int compression, int binary_id, void *array,\n" " size_t elsize, size_t elements, const char *byteorder,\n" " size_t dimfast, size_t dimmid, size_t dimslow,\n" " size_t padding);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_integerarray sets the binary value of the item at the current \n" "column and row to an integer array. The array consists of elements \n" "elements of elsize bytes each, starting at array. The elements are \n" "signed if elsigned is non-0 and unsigned otherwise. binary_id is the \n" "binary section identifier. cbf_set_realarray sets the binary value of \n" "the item at the current column and row to an integer array. The array \n" "consists of elements elements of elsize bytes each, starting at \n" "array. binary_id is the binary section identifier.\n" "The cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, \n" "cbf_set_integerarray_wdims_sf, cbf_set_realarray_wdims, \n" "cbf_set_realarray_wdims_fs and cbf_set_realarray_wdims_sf variants \n" "allow the data header values of byteorder, dimfast, dimmid, dimslow \n" "and padding to be set to the data byte order, the fastest, second \n" "fastest and third fastest array dimensions and the size in byte of \n" "the post data padding to be used.\n" "The array will be compressed using the compression scheme specifed by \n" "compression. Currently, the available schemes are:\n" "CBF_CANONICAL Canonical-code compression (section 3.3.1) \n" "CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 \n" " CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET \n" "Simple \"byte_offset \" compression. CBF_NONE No \n" "compression. NOTE: This scheme is by far the slowest of the four and \n" "uses much more disk space. It is intended for routine use with small \n" "arrays only. With large arrays (like images) it should be used only \n" "for debugging.\n" "The values compressed are limited to 64 bits. If any element in the \n" "array is larger than 64 bits, the value compressed is the nearest \n" "64-bit value.\n" "Currently, the source array must consist of chars, shorts or ints \n" "(signed or unsigned), for cbf_set_integerarray, or IEEE doubles or \n" "floats for cbf_set_realarray. If elsize is not equal to sizeof \n" "(char), sizeof (short) or sizeof (int), the function returns \n" "CBF_ARGUMENT.\n" "ARGUMENTS\n" "handle CBF handle. compression Compression method to use. \n" "binary_id Integer binary identifier. array Pointer to the \n" "source array. elsize Size in bytes of each source array \n" "element. elsigned Set to non-0 if the source array elements are \n" "signed. elements: The number of elements in the array.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_construct_reference_detector", _wrap_cbf_handle_struct_construct_reference_detector, METH_VARARGS, (char *)"\n" "Returns : pycbf detector object\n" "*args : Integer element_number\n" "\n" "C prototype: int cbf_construct_reference_detector (cbf_handle handle,\n" " cbf_detector *detector, unsigned int element_number);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_construct_detector constructs a detector object for detector \n" "element number element_number using the description in the CBF object \n" "handle and initialises the detector handle *detector.\n" "cbf_construct_reference_detector constructs a detector object for \n" "detector element number element_number using the description in the \n" "CBF object handle and initialises the detector handle *detector using \n" "the reference settings of the axes. cbf_require_reference_detector is \n" "similar, but try to force the creations of missing intermediate \n" "categories needed to construct a detector object.\n" "ARGUMENTS\n" "handle CBF handle. detector Pointer to the \n" "destination detector handle. element_number The number of the \n" "detector element counting from 0 by order of appearance in the \n" "\"diffrn_data_frame \" category.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_get_real_3d_image_fs_as_string", _wrap_cbf_handle_struct_get_real_3d_image_fs_as_string, METH_VARARGS, (char *)"\n" "Returns : (Binary)String\n" "*args : int element_number,int elsize,int ndimfast,int ndimmid,int ndimslow\n" "\n" "C prototype: int cbf_get_real_3d_image_fs (cbf_handle handle,\n" " unsigned int reserved, unsigned int element_number,\n" " void *array, size_t elsize, size_t ndimfast,\n" " size_t ndimmid, size_t ndimslow);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image \n" "array for element number element_number into an array. The array \n" "consists of ndimslow *ndimfast elements of elsize bytes each, \n" "starting at array. The elements are signed if elsign is non-0 and \n" "unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and \n" "cbf_get_real_image_sf read the image array of IEEE doubles or floats \n" "for element number element_number into an array. A real array is \n" "always signed. cbf_get_3d_image, cbf_get_3d_image_fs and \n" "cbf_get_3d_image_sf read the 3D image array for element number \n" "element_number into an array. The array consists of ndimslow *ndimmid \n" "*ndimfast elements of elsize bytes each, starting at array. The \n" "elements are signed if elsign is non-0 and unsigned otherwise. \n" "cbf_get_real_3d_image, cbf_get_real_3d_image_fs, \n" "cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or \n" "floats for element number element_number into an array. A real array \n" "is always signed.\n" "The _fs calls give the dimensions in a fast-to-slow order. The calls \n" "with no suffix and the calls _sf calls give the dimensions in \n" "slow-to-fast order\n" "The structure of the array as a 1-, 2- or 3-dimensional array should \n" "agree with the structure of the array given in the \n" "ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, \n" "ndimslow should be the array size and ndimfast and, for the 3D calls, \n" "ndimmid, should be set to 1 both in the call and in the imgCIF data \n" "being processed. If the array is 2-dimensional and a 3D call is used, \n" "ndimslow and ndimmid should be the\n" "\n" ""}, { (char *)"cbf_handle_struct_rewind_row", _wrap_cbf_handle_struct_rewind_row, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : \n" "\n" "C prototype: int cbf_rewind_row (cbf_handle handle);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_rewind_row makes the first row in the current category the \n" "current row.\n" "If there are no rows, the function returns CBF_NOTFOUND.\n" "The current column is not affected.\n" "ARGUMENTS\n" "handle CBF handle.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_axis_setting", _wrap_cbf_handle_struct_get_axis_setting, METH_VARARGS, (char *)"\n" "Returns : Float start,Float increment\n" "*args : String axis_id\n" "\n" "C prototype: int cbf_get_axis_setting (cbf_handle handle,\n" " unsigned int reserved, const char *axis_id, double *start,\n" " double *increment);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_axis_setting sets *start and *increment to the corresponding \n" "values of the axis axis_id.\n" "Either of the destination pointers may be NULL.\n" "The parameter reserved is presently unused and should be set to 0.\n" "ARGUMENTS\n" "handle CBF handle. reserved Unused. Any value other than 0 is \n" "invalid. axis_id Axis id. start Pointer to the destination \n" "start value. increment Pointer to the destination increment value.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_require_column", _wrap_cbf_handle_struct_require_column, METH_VARARGS, (char *)"\n" "Returns : string\n" "*args : \n" "\n" "C prototype: int cbf_require_column (cbf_handle handle,\n" " const char *columnname);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_require_column makes the columns in the current category with \n" "name columnname the current column, if it exists, or creates it if it \n" "does not.\n" "The comparison is case-insensitive.\n" "The current row is not affected.\n" "ARGUMENTS\n" "handle CBF handle. columnname The name of column to find.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_timestamp", _wrap_cbf_handle_struct_get_timestamp, METH_VARARGS, (char *)"\n" "Returns : Float time,Integer timezone\n" "*args : \n" "\n" "C prototype: int cbf_get_timestamp (cbf_handle handle, unsigned int reserved,\n" " double *time, int *timezone);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_timestamp sets *time to the collection timestamp in seconds \n" "since January 1 1970. *timezone is set to timezone difference from \n" "UTC in minutes. The parameter reserved is presently unused and should \n" "be set to 0.\n" "Either of the destination pointers may be NULL.\n" "ARGUMENTS\n" "handle CBF handle. reserved Unused. Any value other than 0 is \n" "invalid. time Pointer to the destination collection timestamp. \n" "timezone Pointer to the destination timezone difference.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_find_nextrow", _wrap_cbf_handle_struct_find_nextrow, METH_VARARGS, (char *)"\n" "Returns : string\n" "*args : \n" "\n" "C prototype: int cbf_find_nextrow (cbf_handle handle, const char *value);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_find_nextrow makes the makes the next row in the current column \n" "with value value the current row. The search starts from the row \n" "following the last row found with cbf_find_row or cbf_find_nextrow, \n" "or from the current row if the current row was defined using any \n" "other function.\n" "The comparison is case-sensitive.\n" "If no more matching rows exist, the function returns CBF_NOTFOUND.\n" "The current column is not affected.\n" "ARGUMENTS\n" "handle CBF handle. value the value to search for.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_realarrayparameters_wdims_sf", _wrap_cbf_handle_struct_get_realarrayparameters_wdims_sf, METH_VARARGS, (char *)"\n" "Returns : int compression,int binary_id,int elsize,int elements,char **bo,\n" " int *bolen,int dimslow,int dimmid,int dimfast,int padding\n" "*args : \n" "\n" "C prototype: int cbf_get_realarrayparameters_wdims_sf (cbf_handle handle,\n" " unsigned int *compression, int *binary_id, size_t *elsize,\n" " size_t *elements, const char **byteorder, size_t *dimslow,\n" " size_t *dimmid, size_t *dimfast, size_t *padding);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_integerarrayparameters sets *compression, *binary_id, \n" "*elsize, *elsigned, *elunsigned, *elements, *minelement and \n" "*maxelement to values read from the binary value of the item at the \n" "current column and row. This provides all the arguments needed for a \n" "subsequent call to cbf_set_integerarray, if a copy of the array is to \n" "be made into another CIF or CBF. cbf_get_realarrayparameters sets \n" "*compression, *binary_id, *elsize, *elements to values read from the \n" "binary value of the item at the current column and row. This provides \n" "all the arguments needed for a subsequent call to cbf_set_realarray, \n" "if a copy of the arry is to be made into another CIF or CBF.\n" "The variants cbf_get_integerarrayparameters_wdims, \n" "cbf_get_integerarrayparameters_wdims_fs, \n" "cbf_get_integerarrayparameters_wdims_sf, \n" "cbf_get_realarrayparameters_wdims, \n" "cbf_get_realarrayparameters_wdims_fs, \n" "cbf_get_realarrayparameters_wdims_sf set **byteorder, *dimfast, \n" "*dimmid, *dimslow, and *padding as well, providing the additional \n" "parameters needed for a subsequent call to cbf_set_integerarray_wdims \n" "or cbf_set_realarray_wdims.\n" "The value returned in *byteorder is a pointer either to the string \n" "\"little_endian \" or to the string \"big_endian \". This should be \n" "the byte order of the data, not necessarily of the host machine. No \n" "attempt should be made to modify this string. At this time only \n" "\"little_endian \" will be returned.\n" "The values returned in *dimfast, *dimmid and *dimslow are the sizes \n" "of the fastest changing, second fastest changing and third fastest \n" "changing dimensions of the array, if specified, or zero, if not \n" "specified.\n" "The value returned in *padding is the size of the post-data padding, \n" "if any and if specified in the data header. The value is given as a \n" "count of octets.\n" "If the value is not binary, the function returns CBF_ASCII.\n" "ARGUMENTS\n" "handle CBF handle. compression Compression method used. \n" "elsize Size in bytes of each array element. binary_id \n" "Pointer to the destination integer binary identifier. elsigned \n" "Pointer to an integer. Set to 1 if the elements can be read as signed \n" "integers. elunsigned Pointer to an integer. Set to 1 if the \n" "elements can be read as unsigned integers. elements Pointer to \n" "the destination number of elements. minelement Pointer to the \n" "destination smallest element. maxelement Pointer to the \n" "destination largest element. byteorder Pointer to the destination \n" "byte order. dimfast Pointer to the destination fastest \n" "dimension. dimmid Pointer to the destination second fastest \n" "dimension. dimslow Pointer to the destination third fastest \n" "dimension. padding Pointer to the destination padding size.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_reset_datablock", _wrap_cbf_handle_struct_reset_datablock, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : \n" "\n" "C prototype: int cbf_reset_datablock (cbf_handle handle);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_reset_datablock deletes all categories from the current data \n" "block. cbf_reset_saveframe deletes all categories from the current \n" "save frame.\n" "ARGUMENTS\n" "handle CBF handle.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_3d_image_fs", _wrap_cbf_handle_struct_set_3d_image_fs, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : int element_number,int compression,(binary) String data,int elsize,\n" " int elsign,int dimfast,int dimmid,int dimslow\n" "\n" "C prototype: int cbf_set_3d_image_fs(cbf_handle handle, unsigned int reserved,\n" " unsigned int element_number, unsigned int compression,\n" " void *array, size_t elsize, int elsign, size_t ndimfast,\n" " size_t ndimmid, size_t ndimslow);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image \n" "array for element number element_number. The array consists of \n" "ndimfast *ndimslow elements of elsize bytes each, starting at array. \n" "The elements are signed if elsign is non-zero and unsigned otherwise. \n" "cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf \n" "write the image array for element number element_number. The array \n" "consists of ndimfast *ndimslow IEEE double or float elements of \n" "elsize bytes each, starting at array. cbf_set_3d_image, \n" "cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array \n" "for element number element_number. The array consists of ndimfast \n" "*ndimmid *ndimslow elements of elsize bytes each, starting at array. \n" "The elements are signed if elsign is non-0 and unsigned otherwise. \n" "cbf_set_real_3d_image, cbf_set_real_3d_image_fs and \n" "cbf_set_real_3d_image_sf writes the 3D image array for element number \n" "element_number. The array consists of ndimfast *ndimmid *ndimslow \n" "IEEE double or float elements of elsize bytes each, starting at \n" "array.\n" "The _fs calls give the dimensions in a fast-to-slow order. The calls \n" "with no suffix and the calls _sf calls give the dimensions in \n" "slow-to-fast order\n" "If the array is 1-dimensional, ndimslow should be the array size and \n" "ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the \n" "array is 2-dimensional and the 3D calls are used, ndimslow and \n" "ndimmid should be used for the array dimensions and ndimfast should \n" "be set to 1.\n" "The array will be compressed using the compression scheme specifed by \n" "compression. Currently, the available schemes are:\n" "CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED \n" " CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style \n" "packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \n" "\"byte_offset \" compression. CBF_NONE No compression.\n" "The values compressed are limited to 64 bits. If any element in the \n" "array is larger than 64 bits, the value compressed is the nearest \n" "64-bit value.\n" "Currently, the source array must consist of chars, shorts or ints \n" "(signed or unsigned)for cbf_set_image, or IEEE doubles or floats for \n" "cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof \n" "(int), sizeof(double) or sizeof(float), the function returns \n" "CBF_ARGUMENT.\n" "The parameter reserved is presently unused and should be set to 0.\n" "ARGUMENTS\n" "handle CBF handle. reserved Unused. Any value other \n" "than 0 is invalid. element_number The number of the detector \n" "element counting from 0 by order of appearance in the \n" "\"diffrn_data_frame \" category. compression Compression type. \n" "array Pointer to the image array. elsize Size in \n" "bytes of each image array element. elsigned Set to non-0 if \n" "the image array elements are signed. ndimslow Slowest array \n" "dimension. ndimmid Second slowest array dimension. ndimfast \n" " Fastest array dimension.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_set_saveframename", _wrap_cbf_handle_struct_set_saveframename, METH_VARARGS, (char *)"\n" "Returns : string\n" "*args : \n" "\n" "C prototype: int cbf_set_saveframename (cbf_handle handle,\n" " const char *saveframename);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_datablockname changes the name of the current data block to \n" "datablockname. cbf_set_saveframename changes the name of the current \n" "save frame to saveframename.\n" "If a data block or save frame with this name already exists \n" "(comparison is case-insensitive), the function returns CBF_IDENTICAL.\n" "ARGUMENTS\n" "handle CBF handle. datablockname The new data block name. \n" "datablockname The new save frame name.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_require_integervalue", _wrap_cbf_handle_struct_require_integervalue, METH_VARARGS, (char *)"\n" "Returns : Int number\n" "*args : Int thedefault\n" "\n" "C prototype: int cbf_require_integervalue (cbf_handle handle, int *number,\n" " int defaultvalue);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_integervalue sets *number to the value of the ASCII item at \n" "the current column and row interpreted as a decimal integer. \n" "cbf_require_integervalue sets *number to the value of the ASCII item \n" "at the current column and row interpreted as a decimal integer, \n" "setting it to defaultvalue if necessary.\n" "If the value is not ASCII, the function returns CBF_BINARY.\n" "ARGUMENTS\n" "handle CBF handle. number pointer to the number. \n" "defaultvalue default number value.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_integerarrayparameters", _wrap_cbf_handle_struct_get_integerarrayparameters, METH_VARARGS, (char *)"\n" "Returns : int compression,int binary_id,int elsize,int elsigned,int elunsigned,\n" " int elements,int minelement,int maxelement\n" "*args : \n" "\n" "C prototype: int cbf_get_integerarrayparameters (cbf_handle handle,\n" " unsigned int *compression, int *binary_id, size_t *elsize,\n" " int *elsigned, int *elunsigned, size_t *elements,\n" " int *minelement, int *maxelement);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_integerarrayparameters sets *compression, *binary_id, \n" "*elsize, *elsigned, *elunsigned, *elements, *minelement and \n" "*maxelement to values read from the binary value of the item at the \n" "current column and row. This provides all the arguments needed for a \n" "subsequent call to cbf_set_integerarray, if a copy of the array is to \n" "be made into another CIF or CBF. cbf_get_realarrayparameters sets \n" "*compression, *binary_id, *elsize, *elements to values read from the \n" "binary value of the item at the current column and row. This provides \n" "all the arguments needed for a subsequent call to cbf_set_realarray, \n" "if a copy of the arry is to be made into another CIF or CBF.\n" "The variants cbf_get_integerarrayparameters_wdims, \n" "cbf_get_integerarrayparameters_wdims_fs, \n" "cbf_get_integerarrayparameters_wdims_sf, \n" "cbf_get_realarrayparameters_wdims, \n" "cbf_get_realarrayparameters_wdims_fs, \n" "cbf_get_realarrayparameters_wdims_sf set **byteorder, *dimfast, \n" "*dimmid, *dimslow, and *padding as well, providing the additional \n" "parameters needed for a subsequent call to cbf_set_integerarray_wdims \n" "or cbf_set_realarray_wdims.\n" "The value returned in *byteorder is a pointer either to the string \n" "\"little_endian \" or to the string \"big_endian \". This should be \n" "the byte order of the data, not necessarily of the host machine. No \n" "attempt should be made to modify this string. At this time only \n" "\"little_endian \" will be returned.\n" "The values returned in *dimfast, *dimmid and *dimslow are the sizes \n" "of the fastest changing, second fastest changing and third fastest \n" "changing dimensions of the array, if specified, or zero, if not \n" "specified.\n" "The value returned in *padding is the size of the post-data padding, \n" "if any and if specified in the data header. The value is given as a \n" "count of octets.\n" "If the value is not binary, the function returns CBF_ASCII.\n" "ARGUMENTS\n" "handle CBF handle. compression Compression method used. \n" "elsize Size in bytes of each array element. binary_id \n" "Pointer to the destination integer binary identifier. elsigned \n" "Pointer to an integer. Set to 1 if the elements can be read as signed \n" "integers. elunsigned Pointer to an integer. Set to 1 if the \n" "elements can be read as unsigned integers. elements Pointer to \n" "the destination number of elements. minelement Pointer to the \n" "destination smallest element. maxelement Pointer to the \n" "destination largest element. byteorder Pointer to the destination \n" "byte order. dimfast Pointer to the destination fastest \n" "dimension. dimmid Pointer to the destination second fastest \n" "dimension. dimslow Pointer to the destination third fastest \n" "dimension. padding Pointer to the destination padding size.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_real_3d_image_sf", _wrap_cbf_handle_struct_set_real_3d_image_sf, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : int element_number,int compression,(binary) String data,int elsize,\n" " int dimslow,int dimmid,int dimfast\n" "\n" "C prototype: int cbf_set_real_3d_image_sf(cbf_handle handle,\n" " unsigned int reserved, unsigned int element_number,\n" " unsigned int compression, void *array,size_t elsize,\n" " size_t ndimslow, size_t ndimmid, size_t ndimfast);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image \n" "array for element number element_number. The array consists of \n" "ndimfast *ndimslow elements of elsize bytes each, starting at array. \n" "The elements are signed if elsign is non-zero and unsigned otherwise. \n" "cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf \n" "write the image array for element number element_number. The array \n" "consists of ndimfast *ndimslow IEEE double or float elements of \n" "elsize bytes each, starting at array. cbf_set_3d_image, \n" "cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array \n" "for element number element_number. The array consists of ndimfast \n" "*ndimmid *ndimslow elements of elsize bytes each, starting at array. \n" "The elements are signed if elsign is non-0 and unsigned otherwise. \n" "cbf_set_real_3d_image, cbf_set_real_3d_image_fs and \n" "cbf_set_real_3d_image_sf writes the 3D image array for element number \n" "element_number. The array consists of ndimfast *ndimmid *ndimslow \n" "IEEE double or float elements of elsize bytes each, starting at \n" "array.\n" "The _fs calls give the dimensions in a fast-to-slow order. The calls \n" "with no suffix and the calls _sf calls give the dimensions in \n" "slow-to-fast order\n" "If the array is 1-dimensional, ndimslow should be the array size and \n" "ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the \n" "array is 2-dimensional and the 3D calls are used, ndimslow and \n" "ndimmid should be used for the array dimensions and ndimfast should \n" "be set to 1.\n" "The array will be compressed using the compression scheme specifed by \n" "compression. Currently, the available schemes are:\n" "CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED \n" " CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style \n" "packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \n" "\"byte_offset \" compression. CBF_NONE No compression.\n" "The values compressed are limited to 64 bits. If any element in the \n" "array is larger than 64 bits, the value compressed is the nearest \n" "64-bit value.\n" "Currently, the source array must consist of chars, shorts or ints \n" "(signed or unsigned)for cbf_set_image, or IEEE doubles or floats for \n" "cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof \n" "(int), sizeof(double) or sizeof(float), the function returns \n" "CBF_ARGUMENT.\n" "The parameter reserved is presently unused and should be set to 0.\n" "ARGUMENTS\n" "handle CBF handle. reserved Unused. Any value other \n" "than 0 is invalid. element_number The number of the detector \n" "element counting from 0 by order of appearance in the \n" "\"diffrn_data_frame \" category. compression Compression type. \n" "array Pointer to the image array. elsize Size in \n" "bytes of each image array element. elsigned Set to non-0 if \n" "the image array elements are signed. ndimslow Slowest array \n" "dimension. ndimmid Second slowest array dimension. ndimfast \n" " Fastest array dimension.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_write_file", _wrap_cbf_handle_struct_write_file, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : String filename,Integer ciforcbf,Integer Headers,Integer encoding\n" "\n" "C prototype: int cbf_write_file (cbf_handle handle, FILE *file, int readable,\n" " int ciforcbf, int flags, int encoding);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_write_file writes the CBF object specified by handle into the \n" "file file, following CIF 1.0 conventions of 80 character lines. \n" "cbf_write_widefile writes the CBF object specified by handle into the \n" "file file, following CIF 1.1 conventions of 2048 character lines. A \n" "warning is issued to stderr for ascii lines over the limit, and an \n" "attempt is made to fold lines to fit. No test is performed on binary \n" "sections.\n" "If a dictionary has been provided, aliases will be applied on output.\n" "Unlike cbf_read_file, the file does not have to be random-access.\n" "If the file is random-access and readable, readable can be set to \n" "non-0 to indicate to CBFlib that the file can be used as a buffer to \n" "conserve disk space. If the file is not random-access or not \n" "readable, readable must be 0.\n" "\n" ""}, { (char *)"cbf_handle_struct_set_divergence", _wrap_cbf_handle_struct_set_divergence, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : Float div_x_source,Float div_y_source,Float div_x_y_source\n" "\n" "C prototype: int cbf_set_divergence (cbf_handle handle, double div_x_source,\n" " double div_y_source, double div_x_y_source);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_divergence sets the source divergence parameters to the \n" "values specified by div_x_source, div_y_source and div_x_y_source.\n" "ARGUMENTS\n" "handle CBF handle. div_x_source New value of \n" "div_x_source. div_y_source New value of div_y_source. \n" "div_x_y_source New value of div_x_y_source.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_remove_datablock", _wrap_cbf_handle_struct_remove_datablock, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : \n" "\n" "C prototype: int cbf_remove_datablock (cbf_handle handle);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_remove_datablock deletes the current data block. \n" "cbf_remove_saveframe deletes the current save frame.\n" "The current data block becomes undefined.\n" "ARGUMENTS\n" "handle CBF handle.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_count_elements", _wrap_cbf_handle_struct_count_elements, METH_VARARGS, (char *)"\n" "Returns : Integer\n" "*args : \n" "\n" "C prototype: int cbf_count_elements (cbf_handle handle,\n" " unsigned int *elements);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_count_elements sets *elements to the number of detector elements.\n" "ARGUMENTS\n" "handle CBF handle. elements Pointer to the destination count.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_set_image_fs", _wrap_cbf_handle_struct_set_image_fs, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : int element_number,int compression,(binary) String data,int elsize,\n" " int elsign,int dimfast,int dimslow\n" "\n" "C prototype: int cbf_set_image_fs(cbf_handle handle, unsigned int reserved,\n" " unsigned int element_number, unsigned int compression,\n" " void *array, size_t elsize, int elsign, size_t ndimfast,\n" " size_t ndimslow);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image \n" "array for element number element_number. The array consists of \n" "ndimfast *ndimslow elements of elsize bytes each, starting at array. \n" "The elements are signed if elsign is non-zero and unsigned otherwise. \n" "cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf \n" "write the image array for element number element_number. The array \n" "consists of ndimfast *ndimslow IEEE double or float elements of \n" "elsize bytes each, starting at array. cbf_set_3d_image, \n" "cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array \n" "for element number element_number. The array consists of ndimfast \n" "*ndimmid *ndimslow elements of elsize bytes each, starting at array. \n" "The elements are signed if elsign is non-0 and unsigned otherwise. \n" "cbf_set_real_3d_image, cbf_set_real_3d_image_fs and \n" "cbf_set_real_3d_image_sf writes the 3D image array for element number \n" "element_number. The array consists of ndimfast *ndimmid *ndimslow \n" "IEEE double or float elements of elsize bytes each, starting at \n" "array.\n" "The _fs calls give the dimensions in a fast-to-slow order. The calls \n" "with no suffix and the calls _sf calls give the dimensions in \n" "slow-to-fast order\n" "If the array is 1-dimensional, ndimslow should be the array size and \n" "ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the \n" "array is 2-dimensional and the 3D calls are used, ndimslow and \n" "ndimmid should be used for the array dimensions and ndimfast should \n" "be set to 1.\n" "The array will be compressed using the compression scheme specifed by \n" "compression. Currently, the available schemes are:\n" "CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED \n" " CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style \n" "packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \n" "\"byte_offset \" compression. CBF_NONE No compression.\n" "The values compressed are limited to 64 bits. If any element in the \n" "array is larger than 64 bits, the value compressed is the nearest \n" "64-bit value.\n" "Currently, the source array must consist of chars, shorts or ints \n" "(signed or unsigned)for cbf_set_image, or IEEE doubles or floats for \n" "cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof \n" "(int), sizeof(double) or sizeof(float), the function returns \n" "CBF_ARGUMENT.\n" "The parameter reserved is presently unused and should be set to 0.\n" "ARGUMENTS\n" "handle CBF handle. reserved Unused. Any value other \n" "than 0 is invalid. element_number The number of the detector \n" "element counting from 0 by order of appearance in the \n" "\"diffrn_data_frame \" category. compression Compression type. \n" "array Pointer to the image array. elsize Size in \n" "bytes of each image array element. elsigned Set to non-0 if \n" "the image array elements are signed. ndimslow Slowest array \n" "dimension. ndimmid Second slowest array dimension. ndimfast \n" " Fastest array dimension.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_require_reference_detector", _wrap_cbf_handle_struct_require_reference_detector, METH_VARARGS, (char *)"\n" "Returns : pycbf detector object\n" "*args : Integer element_number\n" "\n" "C prototype: int cbf_require_reference_detector (cbf_handle handle,\n" " cbf_detector *detector, unsigned int element_number);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_construct_detector constructs a detector object for detector \n" "element number element_number using the description in the CBF object \n" "handle and initialises the detector handle *detector.\n" "cbf_construct_reference_detector constructs a detector object for \n" "detector element number element_number using the description in the \n" "CBF object handle and initialises the detector handle *detector using \n" "the reference settings of the axes. cbf_require_reference_detector is \n" "similar, but try to force the creations of missing intermediate \n" "categories needed to construct a detector object.\n" "ARGUMENTS\n" "handle CBF handle. detector Pointer to the \n" "destination detector handle. element_number The number of the \n" "detector element counting from 0 by order of appearance in the \n" "\"diffrn_data_frame \" category.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_next_category", _wrap_cbf_handle_struct_next_category, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : \n" "\n" "C prototype: int cbf_next_category (cbf_handle handle);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_next_category makes the category following the current category \n" "in the current data block the current category.\n" "If there are no more categories, the function returns CBF_NOTFOUND.\n" "The current column and row become undefined.\n" "ARGUMENTS\n" "handle CBF handle.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_diffrn_id", _wrap_cbf_handle_struct_set_diffrn_id, METH_VARARGS, (char *)"\n" "Returns : string\n" "*args : \n" "\n" "C prototype: int cbf_set_diffrn_id (cbf_handle handle, const char *diffrn_id);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_diffrn_id sets the \"diffrn.id \" entry of the current \n" "datablock to the ASCII value diffrn_id.\n" "This function also changes corresponding \"diffrn_id \" entries in \n" "the \"diffrn_source \", \"diffrn_radiation \", \"diffrn_detector \n" "\" and \"diffrn_measurement \" categories.\n" "ARGUMENTS\n" "handle CBF handle. diffrn_id ASCII value.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_set_timestamp", _wrap_cbf_handle_struct_set_timestamp, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : Float time,Integer timezone,Float precision\n" "\n" "C prototype: int cbf_set_timestamp (cbf_handle handle, unsigned int reserved,\n" " double time, int timezone, double precision);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_timestamp sets the collection timestamp in seconds since \n" "January 1 1970 to the value specified by time. The timezone \n" "difference from UTC\n" "\n" ""}, { (char *)"cbf_handle_struct_get_orientation_matrix", _wrap_cbf_handle_struct_get_orientation_matrix, METH_VARARGS, (char *)"\n" "Returns : Float matrix_0,Float matrix_1,Float matrix_2,Float matrix_3,\n" " Float matrix_4,Float matrix_5,Float matrix_6,Float matrix_7,\n" " Float matrix_8\n" "*args : \n" "\n" "C prototype: int cbf_get_orientation_matrix (cbf_handle handle,\n" " double ub_matrix[9]);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_orientation_matrix sets ub_matrix to point to the array of \n" "orientation matrix entries in the \"diffrn \" category in the order \n" "of columns:\n" " \"UB[1][1] \" \"UB[1][2] \" \"UB[1][3] \" \"UB[2][1] \" \n" "\"UB[2][2] \" \"UB[2][3] \" \"UB[3][1] \" \"UB[3][2] \" \n" "\"UB[3][3] \"\n" "cbf_set_orientation_matrix sets the values in the \"diffrn \" \n" "category to the values pointed to by ub_matrix.\n" "ARGUMENTS\n" "handle CBF handle. ubmatric Source or destination array of 9 \n" "doubles giving the orientation matrix parameters.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_get_image_size_fs", _wrap_cbf_handle_struct_get_image_size_fs, METH_VARARGS, (char *)"\n" "Returns : size_t ndimfast,size_t ndimslow\n" "*args : Integer element_number\n" "\n" "C prototype: int cbf_get_image_size_fs (cbf_handle handle,\n" " unsigned int reserved, unsigned int element_number,\n" " size_t *ndimfast, size_t *ndimslow);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_image_size, cbf_get_image_size_fs and cbf_get_image_size_sf \n" "set *ndimslow and *ndimfast to the slow and fast dimensions of the \n" "image array for element number element_number. If the array is \n" "1-dimensional, *ndimslow will be set to the array size and *ndimfast \n" "will be set to 1. If the array is 3-dimensional an error code will be \n" "returned. cbf_get_3d_image_size, cbf_get_3d_image_size_fs and \n" "cbf_get_3d_image_size_sf set *ndimslow, *ndimmid and *ndimfast to the \n" "slowest, next fastest and fastest dimensions, respectively, of the 3D \n" "image array for element number element_number. If the array is \n" "1-dimensional, *ndimslow will be set to the array size and *ndimmid \n" "and\n" "\n" ""}, { (char *)"cbf_handle_struct_get_divergence", _wrap_cbf_handle_struct_get_divergence, METH_VARARGS, (char *)"\n" "Returns : Float div_x_source,Float div_y_source,Float div_x_y_source\n" "*args : \n" "\n" "C prototype: int cbf_get_divergence (cbf_handle handle, double *div_x_source,\n" " double *div_y_source, double *div_x_y_source);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_divergence sets *div_x_source, *div_y_source and \n" "*div_x_y_source to the corresponding source divergence parameters.\n" "Any of the destination pointers may be NULL.\n" "ARGUMENTS\n" "handle CBF handle. div_x_source Pointer to the \n" "destination div_x_source. div_y_source Pointer to the destination \n" "div_y_source. div_x_y_source Pointer to the destination \n" "div_x_y_source.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_rewind_category", _wrap_cbf_handle_struct_rewind_category, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : \n" "\n" "C prototype: int cbf_rewind_category (cbf_handle handle);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_rewind_category makes the first category in the current data \n" "block the current category. cbf_rewind_saveframe makes the first \n" "saveframe in the current data block the current saveframe. \n" "cbf_rewind_blockitem makes the first blockitem (category or \n" "saveframe) in the current data block the current blockitem. The type \n" "of the blockitem (CBF_CATEGORY or CBF_SAVEFRAME) is returned in type.\n" "If there are no categories, saveframes or blockitems the function \n" "returns CBF_NOTFOUND.\n" "The current column and row become undefined.\n" "ARGUMENTS\n" "handle CBF handle. type CBF handle.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_read_template", _wrap_cbf_handle_struct_read_template, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : String filename\n" "\n" "C prototype: int cbf_read_template (cbf_handle handle, FILE *file);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_read_template reads the CBF or CIF file file into the CBF object \n" "specified by handle and selects the first datablock as the current \n" "datablock.\n" "ARGUMENTS\n" "handle Pointer to a CBF handle. file Pointer to a file \n" "descriptor.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_select_row", _wrap_cbf_handle_struct_select_row, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : Integer\n" "\n" "C prototype: int cbf_select_row (cbf_handle handle, unsigned int row);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_select_row selects row number row in the current category as the \n" "current row.\n" "The first row is number 0.\n" "The current column is not affected\n" "If the row does not exist, the function returns CBF_NOTFOUND.\n" "ARGUMENTS\n" "handle CBF handle. row Number of the row to select.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_image_fs_as_string", _wrap_cbf_handle_struct_get_image_fs_as_string, METH_VARARGS, (char *)"\n" "Returns : (Binary)String\n" "*args : int element_number,int elsize,int elsign,int ndimfast,int ndimslow\n" "\n" "C prototype: int cbf_get_image_fs (cbf_handle handle, unsigned int reserved,\n" " unsigned int element_number, void *array, size_t elsize,\n" " int elsign, size_t ndimfast, size_t ndimslow);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image \n" "array for element number element_number into an array. The array \n" "consists of ndimslow *ndimfast elements of elsize bytes each, \n" "starting at array. The elements are signed if elsign is non-0 and \n" "unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and \n" "cbf_get_real_image_sf read the image array of IEEE doubles or floats \n" "for element number element_number into an array. A real array is \n" "always signed. cbf_get_3d_image, cbf_get_3d_image_fs and \n" "cbf_get_3d_image_sf read the 3D image array for element number \n" "element_number into an array. The array consists of ndimslow *ndimmid \n" "*ndimfast elements of elsize bytes each, starting at array. The \n" "elements are signed if elsign is non-0 and unsigned otherwise. \n" "cbf_get_real_3d_image, cbf_get_real_3d_image_fs, \n" "cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or \n" "floats for element number element_number into an array. A real array \n" "is always signed.\n" "The _fs calls give the dimensions in a fast-to-slow order. The calls \n" "with no suffix and the calls _sf calls give the dimensions in \n" "slow-to-fast order\n" "The structure of the array as a 1-, 2- or 3-dimensional array should \n" "agree with the structure of the array given in the \n" "ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, \n" "ndimslow should be the array size and ndimfast and, for the 3D calls, \n" "ndimmid, should be set to 1 both in the call and in the imgCIF data \n" "being processed. If the array is 2-dimensional and a 3D call is used, \n" "ndimslow and ndimmid should be the\n" "\n" ""}, { (char *)"cbf_handle_struct_get_image_size_sf", _wrap_cbf_handle_struct_get_image_size_sf, METH_VARARGS, (char *)"\n" "Returns : size_t ndimslow,size_t ndimfast\n" "*args : Integer element_number\n" "\n" "C prototype: int cbf_get_image_size_sf (cbf_handle handle,\n" " unsigned int reserved, unsigned int element_number,\n" " size_t *ndimslow, size_t *ndimfast);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_image_size, cbf_get_image_size_fs and cbf_get_image_size_sf \n" "set *ndimslow and *ndimfast to the slow and fast dimensions of the \n" "image array for element number element_number. If the array is \n" "1-dimensional, *ndimslow will be set to the array size and *ndimfast \n" "will be set to 1. If the array is 3-dimensional an error code will be \n" "returned. cbf_get_3d_image_size, cbf_get_3d_image_size_fs and \n" "cbf_get_3d_image_size_sf set *ndimslow, *ndimmid and *ndimfast to the \n" "slowest, next fastest and fastest dimensions, respectively, of the 3D \n" "image array for element number element_number. If the array is \n" "1-dimensional, *ndimslow will be set to the array size and *ndimmid \n" "and\n" "\n" ""}, { (char *)"cbf_handle_struct_get_real_image_fs_as_string", _wrap_cbf_handle_struct_get_real_image_fs_as_string, METH_VARARGS, (char *)"\n" "Returns : (Binary)String\n" "*args : int element_number,int elsize,int ndimfast,int ndimslow\n" "\n" "C prototype: int cbf_get_real_image_fs (cbf_handle handle,\n" " unsigned int reserved, unsigned int element_number,\n" " void *array, size_t elsize, size_t ndimfast,\n" " size_t ndimslow);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image \n" "array for element number element_number into an array. The array \n" "consists of ndimslow *ndimfast elements of elsize bytes each, \n" "starting at array. The elements are signed if elsign is non-0 and \n" "unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and \n" "cbf_get_real_image_sf read the image array of IEEE doubles or floats \n" "for element number element_number into an array. A real array is \n" "always signed. cbf_get_3d_image, cbf_get_3d_image_fs and \n" "cbf_get_3d_image_sf read the 3D image array for element number \n" "element_number into an array. The array consists of ndimslow *ndimmid \n" "*ndimfast elements of elsize bytes each, starting at array. The \n" "elements are signed if elsign is non-0 and unsigned otherwise. \n" "cbf_get_real_3d_image, cbf_get_real_3d_image_fs, \n" "cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or \n" "floats for element number element_number into an array. A real array \n" "is always signed.\n" "The _fs calls give the dimensions in a fast-to-slow order. The calls \n" "with no suffix and the calls _sf calls give the dimensions in \n" "slow-to-fast order\n" "The structure of the array as a 1-, 2- or 3-dimensional array should \n" "agree with the structure of the array given in the \n" "ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, \n" "ndimslow should be the array size and ndimfast and, for the 3D calls, \n" "ndimmid, should be set to 1 both in the call and in the imgCIF data \n" "being processed. If the array is 2-dimensional and a 3D call is used, \n" "ndimslow and ndimmid should be the\n" "\n" ""}, { (char *)"cbf_handle_struct_count_columns", _wrap_cbf_handle_struct_count_columns, METH_VARARGS, (char *)"\n" "Returns : Integer\n" "*args : \n" "\n" "C prototype: int cbf_count_columns (cbf_handle handle, unsigned int *columns);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_count_columns puts the number of columns in the current category \n" "in *columns.\n" "ARGUMENTS\n" "handle CBF handle. columns Pointer to the destination column \n" "count.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_integerarrayparameters_wdims", _wrap_cbf_handle_struct_get_integerarrayparameters_wdims, METH_VARARGS, (char *)"\n" "Returns : int compression,int binary_id,int elsize,int elsigned,int elunsigned,\n" " int elements,int minelement,int maxelement,char **bo,int *bolen,\n" " int dimfast,int dimmid,int dimslow,int padding\n" "*args : \n" "\n" "C prototype: int cbf_get_integerarrayparameters_wdims (cbf_handle handle,\n" " unsigned int *compression, int *binary_id, size_t *elsize,\n" " int *elsigned, int *elunsigned, size_t *elements,\n" " int *minelement, int *maxelement, const char **byteorder,\n" " size_t *dimfast, size_t *dimmid, size_t *dimslow,\n" " size_t *padding);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_integerarrayparameters sets *compression, *binary_id, \n" "*elsize, *elsigned, *elunsigned, *elements, *minelement and \n" "*maxelement to values read from the binary value of the item at the \n" "current column and row. This provides all the arguments needed for a \n" "subsequent call to cbf_set_integerarray, if a copy of the array is to \n" "be made into another CIF or CBF. cbf_get_realarrayparameters sets \n" "*compression, *binary_id, *elsize, *elements to values read from the \n" "binary value of the item at the current column and row. This provides \n" "all the arguments needed for a subsequent call to cbf_set_realarray, \n" "if a copy of the arry is to be made into another CIF or CBF.\n" "The variants cbf_get_integerarrayparameters_wdims, \n" "cbf_get_integerarrayparameters_wdims_fs, \n" "cbf_get_integerarrayparameters_wdims_sf, \n" "cbf_get_realarrayparameters_wdims, \n" "cbf_get_realarrayparameters_wdims_fs, \n" "cbf_get_realarrayparameters_wdims_sf set **byteorder, *dimfast, \n" "*dimmid, *dimslow, and *padding as well, providing the additional \n" "parameters needed for a subsequent call to cbf_set_integerarray_wdims \n" "or cbf_set_realarray_wdims.\n" "The value returned in *byteorder is a pointer either to the string \n" "\"little_endian \" or to the string \"big_endian \". This should be \n" "the byte order of the data, not necessarily of the host machine. No \n" "attempt should be made to modify this string. At this time only \n" "\"little_endian \" will be returned.\n" "The values returned in *dimfast, *dimmid and *dimslow are the sizes \n" "of the fastest changing, second fastest changing and third fastest \n" "changing dimensions of the array, if specified, or zero, if not \n" "specified.\n" "The value returned in *padding is the size of the post-data padding, \n" "if any and if specified in the data header. The value is given as a \n" "count of octets.\n" "If the value is not binary, the function returns CBF_ASCII.\n" "ARGUMENTS\n" "handle CBF handle. compression Compression method used. \n" "elsize Size in bytes of each array element. binary_id \n" "Pointer to the destination integer binary identifier. elsigned \n" "Pointer to an integer. Set to 1 if the elements can be read as signed \n" "integers. elunsigned Pointer to an integer. Set to 1 if the \n" "elements can be read as unsigned integers. elements Pointer to \n" "the destination number of elements. minelement Pointer to the \n" "destination smallest element. maxelement Pointer to the \n" "destination largest element. byteorder Pointer to the destination \n" "byte order. dimfast Pointer to the destination fastest \n" "dimension. dimmid Pointer to the destination second fastest \n" "dimension. dimslow Pointer to the destination third fastest \n" "dimension. padding Pointer to the destination padding size.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_gain", _wrap_cbf_handle_struct_get_gain, METH_VARARGS, (char *)"\n" "Returns : Float gain,Float gain_esd\n" "*args : \n" "\n" "C prototype: int cbf_get_gain (cbf_handle handle, unsigned int element_number,\n" " double *gain, double *gain_esd);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_gain sets *gain and *gain_esd to the corresponding gain \n" "parameters for element number element_number.\n" "Either of the destination pointers may be NULL.\n" "ARGUMENTS\n" "handle CBF handle. element_number The number of the \n" "detector element counting from 0 by order of appearance in the \n" "\"diffrn_data_frame \" category. gain Pointer to the \n" "destination gain. gain_esd Pointer to the destination \n" "gain_esd.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_new_saveframe", _wrap_cbf_handle_struct_new_saveframe, METH_VARARGS, (char *)"\n" "Returns : string\n" "*args : \n" "\n" "C prototype: int cbf_new_saveframe (cbf_handle handle,\n" " const char *saveframename);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_new_datablock creates a new data block with name datablockname \n" "and makes it the current data block. cbf_new_saveframe creates a new \n" "save frame with name saveframename within the current data block and \n" "makes the new save frame the current save frame.\n" "If a data block or save frame with this name already exists, the \n" "existing data block or save frame becomes the current data block or \n" "save frame.\n" "ARGUMENTS\n" "handle CBF handle. datablockname The name of the new data \n" "block. saveframename The name of the new save frame.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_polarization", _wrap_cbf_handle_struct_set_polarization, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : Float polarizn_source_ratio,Float polarizn_source_norm\n" "\n" "C prototype: int cbf_set_polarization (cbf_handle handle,\n" " double polarizn_source_ratio,\n" " double polarizn_source_norm);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_polarization sets the source polarization to the values \n" "specified by polarizn_source_ratio and polarizn_source_norm.\n" "ARGUMENTS\n" "handle CBF handle. polarizn_source_ratio New value \n" "of polarizn_source_ratio. polarizn_source_norm New value of \n" "polarizn_source_norm.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_set_real_3d_image", _wrap_cbf_handle_struct_set_real_3d_image, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : int element_number,int compression,(binary) String data,int elsize,\n" " int dimslow,int dimmid,int dimfast\n" "\n" "C prototype: int cbf_set_real_3d_image (cbf_handle handle,\n" " unsigned int reserved, unsigned int element_number,\n" " unsigned int compression, void *array,size_t elsize,\n" " size_t ndimslow, size_t ndimmid, size_t ndimfast);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image \n" "array for element number element_number. The array consists of \n" "ndimfast *ndimslow elements of elsize bytes each, starting at array. \n" "The elements are signed if elsign is non-zero and unsigned otherwise. \n" "cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf \n" "write the image array for element number element_number. The array \n" "consists of ndimfast *ndimslow IEEE double or float elements of \n" "elsize bytes each, starting at array. cbf_set_3d_image, \n" "cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array \n" "for element number element_number. The array consists of ndimfast \n" "*ndimmid *ndimslow elements of elsize bytes each, starting at array. \n" "The elements are signed if elsign is non-0 and unsigned otherwise. \n" "cbf_set_real_3d_image, cbf_set_real_3d_image_fs and \n" "cbf_set_real_3d_image_sf writes the 3D image array for element number \n" "element_number. The array consists of ndimfast *ndimmid *ndimslow \n" "IEEE double or float elements of elsize bytes each, starting at \n" "array.\n" "The _fs calls give the dimensions in a fast-to-slow order. The calls \n" "with no suffix and the calls _sf calls give the dimensions in \n" "slow-to-fast order\n" "If the array is 1-dimensional, ndimslow should be the array size and \n" "ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the \n" "array is 2-dimensional and the 3D calls are used, ndimslow and \n" "ndimmid should be used for the array dimensions and ndimfast should \n" "be set to 1.\n" "The array will be compressed using the compression scheme specifed by \n" "compression. Currently, the available schemes are:\n" "CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED \n" " CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style \n" "packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \n" "\"byte_offset \" compression. CBF_NONE No compression.\n" "The values compressed are limited to 64 bits. If any element in the \n" "array is larger than 64 bits, the value compressed is the nearest \n" "64-bit value.\n" "Currently, the source array must consist of chars, shorts or ints \n" "(signed or unsigned)for cbf_set_image, or IEEE doubles or floats for \n" "cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof \n" "(int), sizeof(double) or sizeof(float), the function returns \n" "CBF_ARGUMENT.\n" "The parameter reserved is presently unused and should be set to 0.\n" "ARGUMENTS\n" "handle CBF handle. reserved Unused. Any value other \n" "than 0 is invalid. element_number The number of the detector \n" "element counting from 0 by order of appearance in the \n" "\"diffrn_data_frame \" category. compression Compression type. \n" "array Pointer to the image array. elsize Size in \n" "bytes of each image array element. elsigned Set to non-0 if \n" "the image array elements are signed. ndimslow Slowest array \n" "dimension. ndimmid Second slowest array dimension. ndimfast \n" " Fastest array dimension.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_delete_row", _wrap_cbf_handle_struct_delete_row, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : Integer\n" "\n" "C prototype: int cbf_delete_row (cbf_handle handle, unsigned int rownumber);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_delete_row deletes a row from the current category. Rows starting \n" "from rownumber +1 are moved down by 1. If the current row was higher \n" "than rownumber, or if the current row is the last row, it will also \n" "move down by 1.\n" "The row numbers start from 0.\n" "ARGUMENTS\n" "handle CBF handle. rownumber The number of the row to delete.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_column_name", _wrap_cbf_handle_struct_column_name, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : string\n" "\n" "C prototype: int cbf_column_name (cbf_handle handle, const char **columnname);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_column_name sets *columnname to point to the name of the current \n" "column of the current category.\n" "The column name will be valid as long as the column exists.\n" "The name must not be modified by the program in any way.\n" "ARGUMENTS\n" "handle CBF handle. columnname Pointer to the destination \n" "column name pointer.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_remove_saveframe", _wrap_cbf_handle_struct_remove_saveframe, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : \n" "\n" "C prototype: int cbf_remove_saveframe (cbf_handle handle);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_remove_datablock deletes the current data block. \n" "cbf_remove_saveframe deletes the current save frame.\n" "The current data block becomes undefined.\n" "ARGUMENTS\n" "handle CBF handle.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_integerarray_wdims_sf", _wrap_cbf_handle_struct_set_integerarray_wdims_sf, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : int compression,int binary_id,(binary) String data,int elsize,\n" " int elements,String byteorder,int dimslow,int dimmid,int dimfast,\n" " int padding\n" "\n" "C prototype: int cbf_set_integerarray_wdims_sf (cbf_handle handle,\n" " unsigned int compression, int binary_id, void *array,\n" " size_t elsize, int elsigned, size_t elements,\n" " const char *byteorder, size_t dimslow, size_t dimmid,\n" " size_t dimfast, size_t padding);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_integerarray sets the binary value of the item at the current \n" "column and row to an integer array. The array consists of elements \n" "elements of elsize bytes each, starting at array. The elements are \n" "signed if elsigned is non-0 and unsigned otherwise. binary_id is the \n" "binary section identifier. cbf_set_realarray sets the binary value of \n" "the item at the current column and row to an integer array. The array \n" "consists of elements elements of elsize bytes each, starting at \n" "array. binary_id is the binary section identifier.\n" "The cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, \n" "cbf_set_integerarray_wdims_sf, cbf_set_realarray_wdims, \n" "cbf_set_realarray_wdims_fs and cbf_set_realarray_wdims_sf variants \n" "allow the data header values of byteorder, dimfast, dimmid, dimslow \n" "and padding to be set to the data byte order, the fastest, second \n" "fastest and third fastest array dimensions and the size in byte of \n" "the post data padding to be used.\n" "The array will be compressed using the compression scheme specifed by \n" "compression. Currently, the available schemes are:\n" "CBF_CANONICAL Canonical-code compression (section 3.3.1) \n" "CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 \n" " CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET \n" "Simple \"byte_offset \" compression. CBF_NONE No \n" "compression. NOTE: This scheme is by far the slowest of the four and \n" "uses much more disk space. It is intended for routine use with small \n" "arrays only. With large arrays (like images) it should be used only \n" "for debugging.\n" "The values compressed are limited to 64 bits. If any element in the \n" "array is larger than 64 bits, the value compressed is the nearest \n" "64-bit value.\n" "Currently, the source array must consist of chars, shorts or ints \n" "(signed or unsigned), for cbf_set_integerarray, or IEEE doubles or \n" "floats for cbf_set_realarray. If elsize is not equal to sizeof \n" "(char), sizeof (short) or sizeof (int), the function returns \n" "CBF_ARGUMENT.\n" "ARGUMENTS\n" "handle CBF handle. compression Compression method to use. \n" "binary_id Integer binary identifier. array Pointer to the \n" "source array. elsize Size in bytes of each source array \n" "element. elsigned Set to non-0 if the source array elements are \n" "signed. elements: The number of elements in the array.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_require_value", _wrap_cbf_handle_struct_require_value, METH_VARARGS, (char *)"\n" "Returns : String Value\n" "*args : String defaultvalue\n" "\n" "C prototype: int cbf_require_value (cbf_handle handle, const char **value,\n" " const char *defaultvalue );\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_value sets *value to point to the ASCII value of the item at \n" "the current column and row. cbf_require_value sets *value to point to \n" "the ASCII value of the item at the current column and row, creating \n" "the data item if necessary and initializing it to a copy of \n" "defaultvalue.\n" "If the value is not ASCII, the function returns CBF_BINARY.\n" "The value will be valid as long as the item exists and has not been \n" "set to a new value.\n" "The value must not be modified by the program in any way.\n" "ARGUMENTS\n" "handle CBF handle. value Pointer to the destination \n" "value pointer. defaultvalue Default value character string.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_require_column_integervalue", _wrap_cbf_handle_struct_require_column_integervalue, METH_VARARGS, (char *)"\n" "Returns : Int Value\n" "*args : String Columnvalue,Int default\n" "\n" "C prototype: int cbf_require_column_integervalue (cbf_handle handle,\n" " const char *columnname, int *number,\n" " const int defaultvalue);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_require_column_doublevalue sets *number to the value of the ASCII \n" "item at the current row for the column given with the name given by \n" "*columnname, with the value interpreted as an integer number, or to \n" "the number given by defaultvalue if the item cannot be found.\n" "ARGUMENTS\n" "handle CBF handle. columnname Name of the column \n" "containing the number. number pointer to the location to \n" "receive the integer value. defaultvalue Value to use if the \n" "requested column and value cannot be found.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_pixel_size", _wrap_cbf_handle_struct_set_pixel_size, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : Int element_number,Int axis_number,Float pixel size\n" "\n" "C prototype: int cbf_set_pixel_size (cbf_handle handle,\n" " unsigned int element_number, int axis_number,\n" " double psize);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_pixel_size and cbf_set_pixel_size_sf set the item in the \n" ""e;size"e; column of the \"array_structure_list \" category \n" "at the row which matches axis axis_number of the detector element \n" "element_number converting the double pixel size psize from meters to \n" "millimeters in storing it in the \"size \" column for the axis \n" "axis_number of the detector element element_number. The axis_number \n" "is numbered from 1, starting with the slowest axis. \n" "cbf_set_pixel_size_fs sets the item\n" "\n" ""}, { (char *)"cbf_handle_struct_next_column", _wrap_cbf_handle_struct_next_column, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : \n" "\n" "C prototype: int cbf_next_column (cbf_handle handle);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_next_column makes the column following the current column in the \n" "current category the current column.\n" "If there are no more columns, the function returns CBF_NOTFOUND.\n" "The current row is not affected.\n" "ARGUMENTS\n" "handle CBF handle.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_3d_image_size_sf", _wrap_cbf_handle_struct_get_3d_image_size_sf, METH_VARARGS, (char *)"\n" "Returns : size_t ndimslow,size_t ndimmid,size_t ndimfast\n" "*args : Integer element_number\n" "\n" "C prototype: int cbf_get_3d_image_size_sf (cbf_handle handle,\n" " unsigned int reserved, unsigned int element_number,\n" " size_t *ndimslow, size_t *ndimmid, size_t *ndimfast);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_image_size, cbf_get_image_size_fs and cbf_get_image_size_sf \n" "set *ndimslow and *ndimfast to the slow and fast dimensions of the \n" "image array for element number element_number. If the array is \n" "1-dimensional, *ndimslow will be set to the array size and *ndimfast \n" "will be set to 1. If the array is 3-dimensional an error code will be \n" "returned. cbf_get_3d_image_size, cbf_get_3d_image_size_fs and \n" "cbf_get_3d_image_size_sf set *ndimslow, *ndimmid and *ndimfast to the \n" "slowest, next fastest and fastest dimensions, respectively, of the 3D \n" "image array for element number element_number. If the array is \n" "1-dimensional, *ndimslow will be set to the array size and *ndimmid \n" "and\n" "\n" ""}, { (char *)"cbf_handle_struct_get_realarrayparameters_wdims_fs", _wrap_cbf_handle_struct_get_realarrayparameters_wdims_fs, METH_VARARGS, (char *)"\n" "Returns : int compression,int binary_id,int elsize,int elements,char **bo,\n" " int *bolen,int dimfast,int dimmid,int dimslow,int padding\n" "*args : \n" "\n" "C prototype: int cbf_get_realarrayparameters_wdims_fs (cbf_handle handle,\n" " unsigned int *compression, int *binary_id, size_t *elsize,\n" " size_t *elements, const char **byteorder, size_t *dimfast,\n" " size_t *dimmid, size_t *dimslow, size_t *padding);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_integerarrayparameters sets *compression, *binary_id, \n" "*elsize, *elsigned, *elunsigned, *elements, *minelement and \n" "*maxelement to values read from the binary value of the item at the \n" "current column and row. This provides all the arguments needed for a \n" "subsequent call to cbf_set_integerarray, if a copy of the array is to \n" "be made into another CIF or CBF. cbf_get_realarrayparameters sets \n" "*compression, *binary_id, *elsize, *elements to values read from the \n" "binary value of the item at the current column and row. This provides \n" "all the arguments needed for a subsequent call to cbf_set_realarray, \n" "if a copy of the arry is to be made into another CIF or CBF.\n" "The variants cbf_get_integerarrayparameters_wdims, \n" "cbf_get_integerarrayparameters_wdims_fs, \n" "cbf_get_integerarrayparameters_wdims_sf, \n" "cbf_get_realarrayparameters_wdims, \n" "cbf_get_realarrayparameters_wdims_fs, \n" "cbf_get_realarrayparameters_wdims_sf set **byteorder, *dimfast, \n" "*dimmid, *dimslow, and *padding as well, providing the additional \n" "parameters needed for a subsequent call to cbf_set_integerarray_wdims \n" "or cbf_set_realarray_wdims.\n" "The value returned in *byteorder is a pointer either to the string \n" "\"little_endian \" or to the string \"big_endian \". This should be \n" "the byte order of the data, not necessarily of the host machine. No \n" "attempt should be made to modify this string. At this time only \n" "\"little_endian \" will be returned.\n" "The values returned in *dimfast, *dimmid and *dimslow are the sizes \n" "of the fastest changing, second fastest changing and third fastest \n" "changing dimensions of the array, if specified, or zero, if not \n" "specified.\n" "The value returned in *padding is the size of the post-data padding, \n" "if any and if specified in the data header. The value is given as a \n" "count of octets.\n" "If the value is not binary, the function returns CBF_ASCII.\n" "ARGUMENTS\n" "handle CBF handle. compression Compression method used. \n" "elsize Size in bytes of each array element. binary_id \n" "Pointer to the destination integer binary identifier. elsigned \n" "Pointer to an integer. Set to 1 if the elements can be read as signed \n" "integers. elunsigned Pointer to an integer. Set to 1 if the \n" "elements can be read as unsigned integers. elements Pointer to \n" "the destination number of elements. minelement Pointer to the \n" "destination smallest element. maxelement Pointer to the \n" "destination largest element. byteorder Pointer to the destination \n" "byte order. dimfast Pointer to the destination fastest \n" "dimension. dimmid Pointer to the destination second fastest \n" "dimension. dimslow Pointer to the destination third fastest \n" "dimension. padding Pointer to the destination padding size.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_realarray_as_string", _wrap_cbf_handle_struct_get_realarray_as_string, METH_VARARGS, (char *)"\n" "Returns : (Binary)String\n" "*args : \n" "\n" "C prototype: int cbf_get_realarray (cbf_handle handle, int *binary_id,\n" " void *array, size_t elsize, size_t elements,\n" " size_t *elements_read);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_integerarray reads the binary value of the item at the \n" "current column and row into an integer array. The array consists of \n" "elements elements of elsize bytes each, starting at array. The \n" "elements are signed if elsigned is non-0 and unsigned otherwise. \n" "*binary_id is set to the binary section identifier and *elements_read \n" "to the number of elements actually read. cbf_get_realarray reads the \n" "binary value of the item at the current column and row into a real \n" "array. The array consists of elements elements of elsize bytes each, \n" "starting at array. *binary_id is set to the binary section identifier \n" "and *elements_read to the number of elements actually read.\n" "If any element in the integer binary data cant fit into the \n" "destination element, the destination is set the nearest possible \n" "value.\n" "If the value is not binary, the function returns CBF_ASCII.\n" "If the requested number of elements cant be read, the function will \n" "read as many as it can and then return CBF_ENDOFDATA.\n" "Currently, the destination array must consist of chars, shorts or \n" "ints (signed or unsigned). If elsize is not equal to sizeof (char), \n" "sizeof (short) or sizeof (int), for cbf_get_integerarray, or \n" "sizeof(double) or sizeof(float), for cbf_get_realarray the function \n" "returns CBF_ARGUMENT.\n" "An additional restriction in the current version of CBFlib is that \n" "values too large to fit in an int are not correctly decompressed. As \n" "an example, if the machine with 32-bit ints is reading an array \n" "containing a value outside the range 0 .. 2^32-1 (unsigned) or -2^31 \n" ".. 2^31-1 (signed), the array will not be correctly decompressed. \n" "This restriction will be removed in a future release. For \n" "cbf_get_realarray, only IEEE format is supported. No conversion to \n" "other floating point formats is done at this time.\n" "ARGUMENTS\n" "handle CBF handle. binary_id Pointer to the \n" "destination integer binary identifier. array Pointer to the \n" "destination array. elsize Size in bytes of each destination \n" "array element. elsigned Set to non-0 if the destination array \n" "elements are signed. elements The number of elements to read. \n" "elements_read Pointer to the destination number of elements \n" "actually read.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success. SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_bin_sizes", _wrap_cbf_handle_struct_get_bin_sizes, METH_VARARGS, (char *)"\n" "Returns : Float slowbinsize,Float fastbinsize\n" "*args : Integer element_number\n" "\n" "C prototype: int cbf_get_bin_sizes(cbf_handle handle,\n" " unsigned int element_number, double * slowbinsize,\n" " double * fastbinsize);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_bin_sizes sets slowbinsize to point to the value of the \n" "number of pixels composing one array element in the dimension that \n" "changes at the second-fastest rate and fastbinsize to point to the \n" "value of the number of pixels composing one array element in the \n" "dimension that changes at the fastest rate for the dectector element \n" "with the ordinal element_number. cbf_set_bin_sizes sets the the pixel \n" "bin sizes in the \"array_intensities \" category to the values of \n" "slowbinsize_in for the number of pixels composing one array element \n" "in the dimension that changes at the second-fastest rate and \n" "fastbinsize_in for the number of pixels composing one array element \n" "in the dimension that changes at the fastest rate for the dectector \n" "element with the ordinal element_number.\n" "In order to allow for software binning involving fractions of pixels, \n" "the bin sizes are doubles rather than ints.\n" "ARGUMENTS\n" "handle CBF handle. element_number The number of the \n" "detector element counting from 0 by order of appearance in the \n" "\"diffrn_data_frame \" category. slowbinsize Pointer to the \n" "returned number of pixels composing one array element in the \n" "dimension that changes at the second-fastest rate. fastbinsize \n" "Pointer to the returned number of pixels composing one array element \n" "in the dimension that changes at the fastest rate. slowbinsize_in \n" "The number of pixels composing one array element in the dimension \n" "that changes at the second-fastest rate. fastbinsize_in The number \n" "of pixels composing one array element in the dimension that changes \n" "at the fastest rate.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_reset_category", _wrap_cbf_handle_struct_reset_category, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : \n" "\n" "C prototype: int cbf_reset_category (cbf_handle handle);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_reset_category deletes all columns and rows from current category.\n" "ARGUMENTS\n" "handle CBF handle.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_construct_goniometer", _wrap_cbf_handle_struct_construct_goniometer, METH_VARARGS, (char *)"\n" "Returns : pycbf goniometer object\n" "*args : \n" "\n" "C prototype: int cbf_construct_goniometer (cbf_handle handle,\n" " cbf_goniometer *goniometer);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_construct_goniometer constructs a goniometer object using the \n" "description in the CBF object handle and initialises the goniometer \n" "handle *goniometer.\n" "ARGUMENTS\n" "handle CBF handle. goniometer Pointer to the destination \n" "goniometer handle.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_set_datablockname", _wrap_cbf_handle_struct_set_datablockname, METH_VARARGS, (char *)"\n" "Returns : string\n" "*args : \n" "\n" "C prototype: int cbf_set_datablockname (cbf_handle handle,\n" " const char *datablockname);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_datablockname changes the name of the current data block to \n" "datablockname. cbf_set_saveframename changes the name of the current \n" "save frame to saveframename.\n" "If a data block or save frame with this name already exists \n" "(comparison is case-insensitive), the function returns CBF_IDENTICAL.\n" "ARGUMENTS\n" "handle CBF handle. datablockname The new data block name. \n" "datablockname The new save frame name.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_crystal_id", _wrap_cbf_handle_struct_set_crystal_id, METH_VARARGS, (char *)"\n" "Returns : string\n" "*args : \n" "\n" "C prototype: int cbf_set_crystal_id (cbf_handle handle,\n" " const char *crystal_id);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_crystal_id sets the \"diffrn.crystal_id \" entry to the \n" "ASCII value crystal_id.\n" "ARGUMENTS\n" "handle CBF handle. crystal_id ASCII value.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_get_integerarray_as_string", _wrap_cbf_handle_struct_get_integerarray_as_string, METH_VARARGS, (char *)"\n" "Returns : (Binary)String\n" "*args : \n" "\n" "C prototype: int cbf_get_integerarray (cbf_handle handle, int *binary_id,\n" " void *array, size_t elsize, int elsigned, size_t elements,\n" " size_t *elements_read);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_integerarray reads the binary value of the item at the \n" "current column and row into an integer array. The array consists of \n" "elements elements of elsize bytes each, starting at array. The \n" "elements are signed if elsigned is non-0 and unsigned otherwise. \n" "*binary_id is set to the binary section identifier and *elements_read \n" "to the number of elements actually read. cbf_get_realarray reads the \n" "binary value of the item at the current column and row into a real \n" "array. The array consists of elements elements of elsize bytes each, \n" "starting at array. *binary_id is set to the binary section identifier \n" "and *elements_read to the number of elements actually read.\n" "If any element in the integer binary data cant fit into the \n" "destination element, the destination is set the nearest possible \n" "value.\n" "If the value is not binary, the function returns CBF_ASCII.\n" "If the requested number of elements cant be read, the function will \n" "read as many as it can and then return CBF_ENDOFDATA.\n" "Currently, the destination array must consist of chars, shorts or \n" "ints (signed or unsigned). If elsize is not equal to sizeof (char), \n" "sizeof (short) or sizeof (int), for cbf_get_integerarray, or \n" "sizeof(double) or sizeof(float), for cbf_get_realarray the function \n" "returns CBF_ARGUMENT.\n" "An additional restriction in the current version of CBFlib is that \n" "values too large to fit in an int are not correctly decompressed. As \n" "an example, if the machine with 32-bit ints is reading an array \n" "containing a value outside the range 0 .. 2^32-1 (unsigned) or -2^31 \n" ".. 2^31-1 (signed), the array will not be correctly decompressed. \n" "This restriction will be removed in a future release. For \n" "cbf_get_realarray, only IEEE format is supported. No conversion to \n" "other floating point formats is done at this time.\n" "ARGUMENTS\n" "handle CBF handle. binary_id Pointer to the \n" "destination integer binary identifier. array Pointer to the \n" "destination array. elsize Size in bytes of each destination \n" "array element. elsigned Set to non-0 if the destination array \n" "elements are signed. elements The number of elements to read. \n" "elements_read Pointer to the destination number of elements \n" "actually read.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success. SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_3d_image", _wrap_cbf_handle_struct_set_3d_image, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : int element_number,int compression,(binary) String data,int elsize,\n" " int elsign,int dimslow,int dimmid,int dimfast\n" "\n" "C prototype: int cbf_set_3d_image (cbf_handle handle, unsigned int reserved,\n" " unsigned int element_number, unsigned int compression,\n" " void *array, size_t elsize, int elsign, size_t ndimslow,\n" " size_t ndimmid, size_t ndimfast);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image \n" "array for element number element_number. The array consists of \n" "ndimfast *ndimslow elements of elsize bytes each, starting at array. \n" "The elements are signed if elsign is non-zero and unsigned otherwise. \n" "cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf \n" "write the image array for element number element_number. The array \n" "consists of ndimfast *ndimslow IEEE double or float elements of \n" "elsize bytes each, starting at array. cbf_set_3d_image, \n" "cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array \n" "for element number element_number. The array consists of ndimfast \n" "*ndimmid *ndimslow elements of elsize bytes each, starting at array. \n" "The elements are signed if elsign is non-0 and unsigned otherwise. \n" "cbf_set_real_3d_image, cbf_set_real_3d_image_fs and \n" "cbf_set_real_3d_image_sf writes the 3D image array for element number \n" "element_number. The array consists of ndimfast *ndimmid *ndimslow \n" "IEEE double or float elements of elsize bytes each, starting at \n" "array.\n" "The _fs calls give the dimensions in a fast-to-slow order. The calls \n" "with no suffix and the calls _sf calls give the dimensions in \n" "slow-to-fast order\n" "If the array is 1-dimensional, ndimslow should be the array size and \n" "ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the \n" "array is 2-dimensional and the 3D calls are used, ndimslow and \n" "ndimmid should be used for the array dimensions and ndimfast should \n" "be set to 1.\n" "The array will be compressed using the compression scheme specifed by \n" "compression. Currently, the available schemes are:\n" "CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED \n" " CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style \n" "packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \n" "\"byte_offset \" compression. CBF_NONE No compression.\n" "The values compressed are limited to 64 bits. If any element in the \n" "array is larger than 64 bits, the value compressed is the nearest \n" "64-bit value.\n" "Currently, the source array must consist of chars, shorts or ints \n" "(signed or unsigned)for cbf_set_image, or IEEE doubles or floats for \n" "cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof \n" "(int), sizeof(double) or sizeof(float), the function returns \n" "CBF_ARGUMENT.\n" "The parameter reserved is presently unused and should be set to 0.\n" "ARGUMENTS\n" "handle CBF handle. reserved Unused. Any value other \n" "than 0 is invalid. element_number The number of the detector \n" "element counting from 0 by order of appearance in the \n" "\"diffrn_data_frame \" category. compression Compression type. \n" "array Pointer to the image array. elsize Size in \n" "bytes of each image array element. elsigned Set to non-0 if \n" "the image array elements are signed. ndimslow Slowest array \n" "dimension. ndimmid Second slowest array dimension. ndimfast \n" " Fastest array dimension.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_set_dictionary", _wrap_cbf_handle_struct_set_dictionary, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : CBFHandle dictionary\n" "\n" "C prototype: int cbf_set_dictionary (cbf_handle handle,\n" " cbf_handle dictionary_in);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_dictionary sets *dictionary to the handle of a CBF which has \n" "been associated with the CBF handle by cbf_set_dictionary. \n" "cbf_set_dictionary associates the CBF handle dictionary_in with \n" "handle as its dictionary. cbf_require_dictionary sets *dictionary to \n" "the handle of a CBF which has been associated with the CBF handle by \n" "cbf_set_dictionary or creates a new empty CBF and associates it with \n" "handle, returning the new handle in *dictionary.\n" "ARGUMENTS\n" "handle CBF handle. dictionary Pointer to CBF handle of \n" "dictionary. dictionary_in CBF handle of dcitionary.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_find_tag_category", _wrap_cbf_handle_struct_find_tag_category, METH_VARARGS, (char *)"\n" "Returns : String categoryname\n" "*args : String tagname\n" "\n" "C prototype: int cbf_find_tag_category (cbf_handle handle,\n" " const char* tagname, const char** categoryname);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_find_tag_category sets categoryname to the category associated \n" "with tagname in the dictionary associated with handle. \n" "cbf_set_tag_category upddates the dictionary associated with handle \n" "to indicated that tagname is in category categoryname_in.\n" "ARGUMENTS\n" "handle CBF handle. tagname tag name. \n" "categoryname pointer to a returned category name. \n" "categoryname_in input category name.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_get_real_3d_image_sf_as_string", _wrap_cbf_handle_struct_get_real_3d_image_sf_as_string, METH_VARARGS, (char *)"\n" "Returns : (Binary)String\n" "*args : int element_number,int elsize,int ndimslow,int ndimmid,int ndimfast\n" "\n" "C prototype: int cbf_get_real_3d_image_sf (cbf_handle handle,\n" " unsigned int reserved, unsigned int element_number,\n" " void *array, size_t elsize, size_t ndimslow,\n" " size_t ndimmid, size_t ndimfast);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image \n" "array for element number element_number into an array. The array \n" "consists of ndimslow *ndimfast elements of elsize bytes each, \n" "starting at array. The elements are signed if elsign is non-0 and \n" "unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and \n" "cbf_get_real_image_sf read the image array of IEEE doubles or floats \n" "for element number element_number into an array. A real array is \n" "always signed. cbf_get_3d_image, cbf_get_3d_image_fs and \n" "cbf_get_3d_image_sf read the 3D image array for element number \n" "element_number into an array. The array consists of ndimslow *ndimmid \n" "*ndimfast elements of elsize bytes each, starting at array. The \n" "elements are signed if elsign is non-0 and unsigned otherwise. \n" "cbf_get_real_3d_image, cbf_get_real_3d_image_fs, \n" "cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or \n" "floats for element number element_number into an array. A real array \n" "is always signed.\n" "The _fs calls give the dimensions in a fast-to-slow order. The calls \n" "with no suffix and the calls _sf calls give the dimensions in \n" "slow-to-fast order\n" "The structure of the array as a 1-, 2- or 3-dimensional array should \n" "agree with the structure of the array given in the \n" "ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, \n" "ndimslow should be the array size and ndimfast and, for the 3D calls, \n" "ndimmid, should be set to 1 both in the call and in the imgCIF data \n" "being processed. If the array is 2-dimensional and a 3D call is used, \n" "ndimslow and ndimmid should be the\n" "\n" ""}, { (char *)"cbf_handle_struct_set_typeofvalue", _wrap_cbf_handle_struct_set_typeofvalue, METH_VARARGS, (char *)"\n" "Returns : string\n" "*args : \n" "\n" "C prototype: int cbf_set_typeofvalue (cbf_handle handle,\n" " const char *typeofvalue);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_typeofvalue sets the type of the item at the current column \n" "and row to the type specified by the ASCII character string given by \n" "typeofvalue. The strings that may be used are:\n" " \"null \" for a null value indicated by a \". \" or a \"? \" \n" "\"bnry \" for a binary value \"word \" for an unquoted string \n" "\"dblq \" for a double-quoted string \"sglq \" for a single-quoted \n" "string \"text \" for a semicolon-quoted string (multiline text \n" "field) \"prns \" for a parenthesis-bracketed string (multiline text \n" "field) \"brcs \" for a brace-bracketed string (multiline text field) \n" " \"bkts \" for a square-bracket-bracketed string (multiline text \n" "field) \"tsqs \" for a treble-single-quote quoted string (multiline \n" "text field) \"tdqs \" for a treble-double-quote quoted string \n" "(multiline text field)\n" "Not all types may be used for all values. Not all types are valid for \n" "all type of CIF files. In partcular the types \"prns \", \"brcs \", \n" " \"bkts \" were introduced with DDLm and are not valid in DDL1 or \n" "DDL2 CIFS. The types \"tsqs \" and \"tdqs \" are not formally part \n" "of the CIF syntax. No changes may be made to the type of binary \n" "values. You may not set the type of a string that contains a single \n" "quote followed by a blank or a tab or which contains multiple lines \n" "to \"sglq \". You may not set the type of a string that contains a \n" "double quote followed by a blank or a tab or which contains multiple \n" "lines to \"dblq \".\n" "ARGUMENTS\n" "handle CBF handle. typeofvalue ASCII string for desired type \n" "of value.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_integerarray_wdims", _wrap_cbf_handle_struct_set_integerarray_wdims, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : int compression,int binary_id,(binary) String data,int elsize,\n" " int elements,String byteorder,int dimfast,int dimmid,int dimslow,\n" " int padding\n" "\n" "C prototype: int cbf_set_integerarray_wdims (cbf_handle handle,\n" " unsigned int compression, int binary_id, void *array,\n" " size_t elsize, int elsigned, size_t elements,\n" " const char *byteorder, size_t dimfast, size_t dimmid,\n" " size_t dimslow, size_t padding);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_integerarray sets the binary value of the item at the current \n" "column and row to an integer array. The array consists of elements \n" "elements of elsize bytes each, starting at array. The elements are \n" "signed if elsigned is non-0 and unsigned otherwise. binary_id is the \n" "binary section identifier. cbf_set_realarray sets the binary value of \n" "the item at the current column and row to an integer array. The array \n" "consists of elements elements of elsize bytes each, starting at \n" "array. binary_id is the binary section identifier.\n" "The cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, \n" "cbf_set_integerarray_wdims_sf, cbf_set_realarray_wdims, \n" "cbf_set_realarray_wdims_fs and cbf_set_realarray_wdims_sf variants \n" "allow the data header values of byteorder, dimfast, dimmid, dimslow \n" "and padding to be set to the data byte order, the fastest, second \n" "fastest and third fastest array dimensions and the size in byte of \n" "the post data padding to be used.\n" "The array will be compressed using the compression scheme specifed by \n" "compression. Currently, the available schemes are:\n" "CBF_CANONICAL Canonical-code compression (section 3.3.1) \n" "CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 \n" " CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET \n" "Simple \"byte_offset \" compression. CBF_NONE No \n" "compression. NOTE: This scheme is by far the slowest of the four and \n" "uses much more disk space. It is intended for routine use with small \n" "arrays only. With large arrays (like images) it should be used only \n" "for debugging.\n" "The values compressed are limited to 64 bits. If any element in the \n" "array is larger than 64 bits, the value compressed is the nearest \n" "64-bit value.\n" "Currently, the source array must consist of chars, shorts or ints \n" "(signed or unsigned), for cbf_set_integerarray, or IEEE doubles or \n" "floats for cbf_set_realarray. If elsize is not equal to sizeof \n" "(char), sizeof (short) or sizeof (int), the function returns \n" "CBF_ARGUMENT.\n" "ARGUMENTS\n" "handle CBF handle. compression Compression method to use. \n" "binary_id Integer binary identifier. array Pointer to the \n" "source array. elsize Size in bytes of each source array \n" "element. elsigned Set to non-0 if the source array elements are \n" "signed. elements: The number of elements in the array.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_integration_time", _wrap_cbf_handle_struct_set_integration_time, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : Float time\n" "\n" "C prototype: int cbf_set_integration_time (cbf_handle handle,\n" " unsigned int reserved, double time);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_integration_time sets the integration time in seconds to the \n" "value specified by time. The parameter reserved is presently unused \n" "and should be set to 0.\n" "ARGUMENTS\n" "handle CBF handle. reserved Unused. Any value \n" "other than 0 is invalid. time Integration time in seconds.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_set_axis_setting", _wrap_cbf_handle_struct_set_axis_setting, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : String axis_id,Float start,Float increment\n" "\n" "C prototype: int cbf_set_axis_setting (cbf_handle handle,\n" " unsigned int reserved, const char *axis_id, double start,\n" " double increment);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_axis_setting sets the starting and increment values of the \n" "axis axis_id to start and increment.\n" "The parameter reserved is presently unused and should be set to 0.\n" "ARGUMENTS\n" "handle CBF handle. reserved Unused. Any value other than 0 is \n" "invalid. axis_id Axis id. start Start value. increment \n" "Increment value.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_get_real_image_as_string", _wrap_cbf_handle_struct_get_real_image_as_string, METH_VARARGS, (char *)"\n" "Returns : (Binary)String\n" "*args : int element_number,int elsize,int ndimslow,int ndimfast\n" "\n" "C prototype: int cbf_get_real_image (cbf_handle handle, unsigned int reserved,\n" " unsigned int element_number, void *array, size_t elsize,\n" " size_t ndimslow, size_t ndimfast);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image \n" "array for element number element_number into an array. The array \n" "consists of ndimslow *ndimfast elements of elsize bytes each, \n" "starting at array. The elements are signed if elsign is non-0 and \n" "unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and \n" "cbf_get_real_image_sf read the image array of IEEE doubles or floats \n" "for element number element_number into an array. A real array is \n" "always signed. cbf_get_3d_image, cbf_get_3d_image_fs and \n" "cbf_get_3d_image_sf read the 3D image array for element number \n" "element_number into an array. The array consists of ndimslow *ndimmid \n" "*ndimfast elements of elsize bytes each, starting at array. The \n" "elements are signed if elsign is non-0 and unsigned otherwise. \n" "cbf_get_real_3d_image, cbf_get_real_3d_image_fs, \n" "cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or \n" "floats for element number element_number into an array. A real array \n" "is always signed.\n" "The _fs calls give the dimensions in a fast-to-slow order. The calls \n" "with no suffix and the calls _sf calls give the dimensions in \n" "slow-to-fast order\n" "The structure of the array as a 1-, 2- or 3-dimensional array should \n" "agree with the structure of the array given in the \n" "ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, \n" "ndimslow should be the array size and ndimfast and, for the 3D calls, \n" "ndimmid, should be set to 1 both in the call and in the imgCIF data \n" "being processed. If the array is 2-dimensional and a 3D call is used, \n" "ndimslow and ndimmid should be the\n" "\n" ""}, { (char *)"cbf_handle_struct_get_3d_image_sf_as_string", _wrap_cbf_handle_struct_get_3d_image_sf_as_string, METH_VARARGS, (char *)"\n" "Returns : (Binary)String\n" "*args : int element_number,int elsize,int elsign,int ndimslow,int ndimmid,\n" " int ndimfast\n" "\n" "C prototype: int cbf_get_3d_image_sf (cbf_handle handle,\n" " unsigned int reserved, unsigned int element_number,\n" " void *array, size_t elsize, int elsign, size_t ndimslow,\n" " size_t ndimmid, size_t ndimfast);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image \n" "array for element number element_number into an array. The array \n" "consists of ndimslow *ndimfast elements of elsize bytes each, \n" "starting at array. The elements are signed if elsign is non-0 and \n" "unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and \n" "cbf_get_real_image_sf read the image array of IEEE doubles or floats \n" "for element number element_number into an array. A real array is \n" "always signed. cbf_get_3d_image, cbf_get_3d_image_fs and \n" "cbf_get_3d_image_sf read the 3D image array for element number \n" "element_number into an array. The array consists of ndimslow *ndimmid \n" "*ndimfast elements of elsize bytes each, starting at array. The \n" "elements are signed if elsign is non-0 and unsigned otherwise. \n" "cbf_get_real_3d_image, cbf_get_real_3d_image_fs, \n" "cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or \n" "floats for element number element_number into an array. A real array \n" "is always signed.\n" "The _fs calls give the dimensions in a fast-to-slow order. The calls \n" "with no suffix and the calls _sf calls give the dimensions in \n" "slow-to-fast order\n" "The structure of the array as a 1-, 2- or 3-dimensional array should \n" "agree with the structure of the array given in the \n" "ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, \n" "ndimslow should be the array size and ndimfast and, for the 3D calls, \n" "ndimmid, should be set to 1 both in the call and in the imgCIF data \n" "being processed. If the array is 2-dimensional and a 3D call is used, \n" "ndimslow and ndimmid should be the\n" "\n" ""}, { (char *)"cbf_handle_struct_set_real_image_fs", _wrap_cbf_handle_struct_set_real_image_fs, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : int element_number,int compression,(binary) String data,int elsize,\n" " int dimfast,int dimslow\n" "\n" "C prototype: int cbf_set_real_image_fs(cbf_handle handle,\n" " unsigned int reserved, unsigned int element_number,\n" " unsigned int compression, void *array,size_t elsize,\n" " size_t ndimfast, size_t ndimslow);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image \n" "array for element number element_number. The array consists of \n" "ndimfast *ndimslow elements of elsize bytes each, starting at array. \n" "The elements are signed if elsign is non-zero and unsigned otherwise. \n" "cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf \n" "write the image array for element number element_number. The array \n" "consists of ndimfast *ndimslow IEEE double or float elements of \n" "elsize bytes each, starting at array. cbf_set_3d_image, \n" "cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array \n" "for element number element_number. The array consists of ndimfast \n" "*ndimmid *ndimslow elements of elsize bytes each, starting at array. \n" "The elements are signed if elsign is non-0 and unsigned otherwise. \n" "cbf_set_real_3d_image, cbf_set_real_3d_image_fs and \n" "cbf_set_real_3d_image_sf writes the 3D image array for element number \n" "element_number. The array consists of ndimfast *ndimmid *ndimslow \n" "IEEE double or float elements of elsize bytes each, starting at \n" "array.\n" "The _fs calls give the dimensions in a fast-to-slow order. The calls \n" "with no suffix and the calls _sf calls give the dimensions in \n" "slow-to-fast order\n" "If the array is 1-dimensional, ndimslow should be the array size and \n" "ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the \n" "array is 2-dimensional and the 3D calls are used, ndimslow and \n" "ndimmid should be used for the array dimensions and ndimfast should \n" "be set to 1.\n" "The array will be compressed using the compression scheme specifed by \n" "compression. Currently, the available schemes are:\n" "CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED \n" " CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style \n" "packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \n" "\"byte_offset \" compression. CBF_NONE No compression.\n" "The values compressed are limited to 64 bits. If any element in the \n" "array is larger than 64 bits, the value compressed is the nearest \n" "64-bit value.\n" "Currently, the source array must consist of chars, shorts or ints \n" "(signed or unsigned)for cbf_set_image, or IEEE doubles or floats for \n" "cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof \n" "(int), sizeof(double) or sizeof(float), the function returns \n" "CBF_ARGUMENT.\n" "The parameter reserved is presently unused and should be set to 0.\n" "ARGUMENTS\n" "handle CBF handle. reserved Unused. Any value other \n" "than 0 is invalid. element_number The number of the detector \n" "element counting from 0 by order of appearance in the \n" "\"diffrn_data_frame \" category. compression Compression type. \n" "array Pointer to the image array. elsize Size in \n" "bytes of each image array element. elsigned Set to non-0 if \n" "the image array elements are signed. ndimslow Slowest array \n" "dimension. ndimmid Second slowest array dimension. ndimfast \n" " Fastest array dimension.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_get_overload", _wrap_cbf_handle_struct_get_overload, METH_VARARGS, (char *)"\n" "Returns : Float overload\n" "*args : Integer element_number\n" "\n" "C prototype: int cbf_get_overload (cbf_handle handle,\n" " unsigned int element_number, double *overload);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_overload sets *overload to the overload value for element \n" "number element_number.\n" "ARGUMENTS\n" "handle CBF handle. element_number The number of the \n" "detector element counting from 0 by order of appearance in the \n" "\"diffrn_data_frame \" category. overload Pointer to the \n" "destination overload.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_get_wavelength", _wrap_cbf_handle_struct_get_wavelength, METH_VARARGS, (char *)"\n" "Returns : double\n" "*args : \n" "\n" "C prototype: int cbf_get_wavelength (cbf_handle handle, double *wavelength);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_wavelength sets *wavelength to the current wavelength in AA.\n" "ARGUMENTS\n" "handle CBF handle. wavelength Pointer to the destination.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_next_datablock", _wrap_cbf_handle_struct_next_datablock, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : \n" "\n" "C prototype: int cbf_next_datablock (cbf_handle handle);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_next_datablock makes the data block following the current data \n" "block the current data block.\n" "If there are no more data blocks, the function returns CBF_NOTFOUND.\n" "The current category becomes undefined.\n" "ARGUMENTS\n" "handle CBF handle.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_realarrayparameters_wdims", _wrap_cbf_handle_struct_get_realarrayparameters_wdims, METH_VARARGS, (char *)"\n" "Returns : int compression,int binary_id,int elsize,int elements,char **bo,\n" " int *bolen,int dimfast,int dimmid,int dimslow,int padding\n" "*args : \n" "\n" "C prototype: int cbf_get_realarrayparameters_wdims (cbf_handle handle,\n" " unsigned int *compression, int *binary_id, size_t *elsize,\n" " size_t *elements, const char **byteorder, size_t *dimfast,\n" " size_t *dimmid, size_t *dimslow, size_t *padding);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_integerarrayparameters sets *compression, *binary_id, \n" "*elsize, *elsigned, *elunsigned, *elements, *minelement and \n" "*maxelement to values read from the binary value of the item at the \n" "current column and row. This provides all the arguments needed for a \n" "subsequent call to cbf_set_integerarray, if a copy of the array is to \n" "be made into another CIF or CBF. cbf_get_realarrayparameters sets \n" "*compression, *binary_id, *elsize, *elements to values read from the \n" "binary value of the item at the current column and row. This provides \n" "all the arguments needed for a subsequent call to cbf_set_realarray, \n" "if a copy of the arry is to be made into another CIF or CBF.\n" "The variants cbf_get_integerarrayparameters_wdims, \n" "cbf_get_integerarrayparameters_wdims_fs, \n" "cbf_get_integerarrayparameters_wdims_sf, \n" "cbf_get_realarrayparameters_wdims, \n" "cbf_get_realarrayparameters_wdims_fs, \n" "cbf_get_realarrayparameters_wdims_sf set **byteorder, *dimfast, \n" "*dimmid, *dimslow, and *padding as well, providing the additional \n" "parameters needed for a subsequent call to cbf_set_integerarray_wdims \n" "or cbf_set_realarray_wdims.\n" "The value returned in *byteorder is a pointer either to the string \n" "\"little_endian \" or to the string \"big_endian \". This should be \n" "the byte order of the data, not necessarily of the host machine. No \n" "attempt should be made to modify this string. At this time only \n" "\"little_endian \" will be returned.\n" "The values returned in *dimfast, *dimmid and *dimslow are the sizes \n" "of the fastest changing, second fastest changing and third fastest \n" "changing dimensions of the array, if specified, or zero, if not \n" "specified.\n" "The value returned in *padding is the size of the post-data padding, \n" "if any and if specified in the data header. The value is given as a \n" "count of octets.\n" "If the value is not binary, the function returns CBF_ASCII.\n" "ARGUMENTS\n" "handle CBF handle. compression Compression method used. \n" "elsize Size in bytes of each array element. binary_id \n" "Pointer to the destination integer binary identifier. elsigned \n" "Pointer to an integer. Set to 1 if the elements can be read as signed \n" "integers. elunsigned Pointer to an integer. Set to 1 if the \n" "elements can be read as unsigned integers. elements Pointer to \n" "the destination number of elements. minelement Pointer to the \n" "destination smallest element. maxelement Pointer to the \n" "destination largest element. byteorder Pointer to the destination \n" "byte order. dimfast Pointer to the destination fastest \n" "dimension. dimmid Pointer to the destination second fastest \n" "dimension. dimslow Pointer to the destination third fastest \n" "dimension. padding Pointer to the destination padding size.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_orientation_matrix", _wrap_cbf_handle_struct_set_orientation_matrix, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : Float matrix_0,Float matrix_1,Float matrix_2,Float matrix_3,\n" " Float matrix_4,Float matrix_5,Float matrix_6,Float matrix_7,\n" " Float matrix_8\n" "\n" "C prototype: int cbf_set_orientation_matrix (cbf_handle handle,\n" " double ub_matrix[9]);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_orientation_matrix sets ub_matrix to point to the array of \n" "orientation matrix entries in the \"diffrn \" category in the order \n" "of columns:\n" " \"UB[1][1] \" \"UB[1][2] \" \"UB[1][3] \" \"UB[2][1] \" \n" "\"UB[2][2] \" \"UB[2][3] \" \"UB[3][1] \" \"UB[3][2] \" \n" "\"UB[3][3] \"\n" "cbf_set_orientation_matrix sets the values in the \"diffrn \" \n" "category to the values pointed to by ub_matrix.\n" "ARGUMENTS\n" "handle CBF handle. ubmatric Source or destination array of 9 \n" "doubles giving the orientation matrix parameters.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_new_category", _wrap_cbf_handle_struct_new_category, METH_VARARGS, (char *)"\n" "Returns : string\n" "*args : \n" "\n" "C prototype: int cbf_new_category (cbf_handle handle,\n" " const char *categoryname);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_new_category creates a new category in the current data block \n" "with name categoryname and makes it the current category.\n" "If a category with this name already exists, the existing category \n" "becomes the current category.\n" "ARGUMENTS\n" "handle CBF handle. categoryname The name of the new \n" "category.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_gain", _wrap_cbf_handle_struct_set_gain, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : Float gain,Float gain_esd\n" "\n" "C prototype: int cbf_set_gain (cbf_handle handle, unsigned int element_number,\n" " double gain, double gain_esd);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_gain sets the gain of element number element_number to the \n" "values specified by gain and gain_esd.\n" "ARGUMENTS\n" "handle CBF handle. element_number The number of the \n" "detector element counting from 0 by order of appearance in the \n" "\"diffrn_data_frame \" category. gain New gain value. \n" "gain_esd New gain_esd value.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_find_column", _wrap_cbf_handle_struct_find_column, METH_VARARGS, (char *)"\n" "Returns : string\n" "*args : \n" "\n" "C prototype: int cbf_find_column (cbf_handle handle, const char *columnname);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_find_column makes the columns in the current category with name \n" "columnname the current column.\n" "The comparison is case-insensitive.\n" "If the column does not exist, the function returns CBF_NOTFOUND.\n" "The current row is not affected.\n" "ARGUMENTS\n" "handle CBF handle. columnname The name of column to find.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_remove_category", _wrap_cbf_handle_struct_remove_category, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : \n" "\n" "C prototype: int cbf_remove_category (cbf_handle handle);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_remove_category deletes the current category.\n" "The current category becomes undefined.\n" "ARGUMENTS\n" "handle CBF handle.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_integerarrayparameters_wdims_sf", _wrap_cbf_handle_struct_get_integerarrayparameters_wdims_sf, METH_VARARGS, (char *)"\n" "Returns : int compression,int binary_id,int elsize,int elsigned,int elunsigned,\n" " int elements,int minelement,int maxelement,char **bo,int *bolen,\n" " int dimslow,int dimmid,int dimfast,int padding\n" "*args : \n" "\n" "C prototype: int cbf_get_integerarrayparameters_wdims_sf (cbf_handle handle,\n" " unsigned int *compression, int *binary_id, size_t *elsize,\n" " int *elsigned, int *elunsigned, size_t *elements,\n" " int *minelement, int *maxelement, const char **byteorder,\n" " size_t *dimslow, size_t *dimmid, size_t *dimfast,\n" " size_t *padding);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_integerarrayparameters sets *compression, *binary_id, \n" "*elsize, *elsigned, *elunsigned, *elements, *minelement and \n" "*maxelement to values read from the binary value of the item at the \n" "current column and row. This provides all the arguments needed for a \n" "subsequent call to cbf_set_integerarray, if a copy of the array is to \n" "be made into another CIF or CBF. cbf_get_realarrayparameters sets \n" "*compression, *binary_id, *elsize, *elements to values read from the \n" "binary value of the item at the current column and row. This provides \n" "all the arguments needed for a subsequent call to cbf_set_realarray, \n" "if a copy of the arry is to be made into another CIF or CBF.\n" "The variants cbf_get_integerarrayparameters_wdims, \n" "cbf_get_integerarrayparameters_wdims_fs, \n" "cbf_get_integerarrayparameters_wdims_sf, \n" "cbf_get_realarrayparameters_wdims, \n" "cbf_get_realarrayparameters_wdims_fs, \n" "cbf_get_realarrayparameters_wdims_sf set **byteorder, *dimfast, \n" "*dimmid, *dimslow, and *padding as well, providing the additional \n" "parameters needed for a subsequent call to cbf_set_integerarray_wdims \n" "or cbf_set_realarray_wdims.\n" "The value returned in *byteorder is a pointer either to the string \n" "\"little_endian \" or to the string \"big_endian \". This should be \n" "the byte order of the data, not necessarily of the host machine. No \n" "attempt should be made to modify this string. At this time only \n" "\"little_endian \" will be returned.\n" "The values returned in *dimfast, *dimmid and *dimslow are the sizes \n" "of the fastest changing, second fastest changing and third fastest \n" "changing dimensions of the array, if specified, or zero, if not \n" "specified.\n" "The value returned in *padding is the size of the post-data padding, \n" "if any and if specified in the data header. The value is given as a \n" "count of octets.\n" "If the value is not binary, the function returns CBF_ASCII.\n" "ARGUMENTS\n" "handle CBF handle. compression Compression method used. \n" "elsize Size in bytes of each array element. binary_id \n" "Pointer to the destination integer binary identifier. elsigned \n" "Pointer to an integer. Set to 1 if the elements can be read as signed \n" "integers. elunsigned Pointer to an integer. Set to 1 if the \n" "elements can be read as unsigned integers. elements Pointer to \n" "the destination number of elements. minelement Pointer to the \n" "destination smallest element. maxelement Pointer to the \n" "destination largest element. byteorder Pointer to the destination \n" "byte order. dimfast Pointer to the destination fastest \n" "dimension. dimmid Pointer to the destination second fastest \n" "dimension. dimslow Pointer to the destination third fastest \n" "dimension. padding Pointer to the destination padding size.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_pixel_size", _wrap_cbf_handle_struct_get_pixel_size, METH_VARARGS, (char *)"\n" "Returns : Float pixel_size\n" "*args : Int element_number,Int axis_number\n" "\n" "C prototype: int cbf_get_pixel_size (cbf_handle handle,\n" " unsigned int element_number, int axis_number,\n" " double *psize);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_pixel_size and cbf_get_pixel_size_sf set *psize to point to \n" "the double value in millimeters of the axis axis_number of the \n" "detector element element_number. The axis_number is numbered from 1, \n" "starting with the slowest axis. cbf_get_pixel_size_fs sets *psize to \n" "point to the double value in millimeters of the axis axis_number of \n" "the detector element element_number. The axis_number is numbered from \n" "1, starting with the fastest axis.\n" "If a negative axis number is given, the order of axes is reversed, so \n" "that -1 specifies the slowest axis for cbf_get_pixel_size_fs and the \n" "fastest axis for cbf_get_pixel_size_sf.\n" "If the pixel size is not given explcitly in the \"array_element_size \n" "\" category, the function returns CBF_NOTFOUND.\n" "ARGUMENTS\n" "handle CBF handle. element_number The number of the \n" "detector element counting from 0 by order of appearance in the \n" "\"diffrn_data_frame \" category. axis_number The number of the \n" "axis, starting from 1 for the fastest for cbf_get_pixel_size and \n" "cbf_get_pixel_size_fs and the slowest for cbf_get_pixel_size_sf. \n" "psize Pointer to the destination pixel size.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_set_real_image_sf", _wrap_cbf_handle_struct_set_real_image_sf, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : int element_number,int compression,(binary) String data,int elsize,\n" " int dimslow,int dimfast\n" "\n" "C prototype: int cbf_set_real_image_sf(cbf_handle handle,\n" " unsigned int reserved, unsigned int element_number,\n" " unsigned int compression, void *array,size_t elsize,\n" " size_t ndimslow, size_t ndimfast);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image \n" "array for element number element_number. The array consists of \n" "ndimfast *ndimslow elements of elsize bytes each, starting at array. \n" "The elements are signed if elsign is non-zero and unsigned otherwise. \n" "cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf \n" "write the image array for element number element_number. The array \n" "consists of ndimfast *ndimslow IEEE double or float elements of \n" "elsize bytes each, starting at array. cbf_set_3d_image, \n" "cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array \n" "for element number element_number. The array consists of ndimfast \n" "*ndimmid *ndimslow elements of elsize bytes each, starting at array. \n" "The elements are signed if elsign is non-0 and unsigned otherwise. \n" "cbf_set_real_3d_image, cbf_set_real_3d_image_fs and \n" "cbf_set_real_3d_image_sf writes the 3D image array for element number \n" "element_number. The array consists of ndimfast *ndimmid *ndimslow \n" "IEEE double or float elements of elsize bytes each, starting at \n" "array.\n" "The _fs calls give the dimensions in a fast-to-slow order. The calls \n" "with no suffix and the calls _sf calls give the dimensions in \n" "slow-to-fast order\n" "If the array is 1-dimensional, ndimslow should be the array size and \n" "ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the \n" "array is 2-dimensional and the 3D calls are used, ndimslow and \n" "ndimmid should be used for the array dimensions and ndimfast should \n" "be set to 1.\n" "The array will be compressed using the compression scheme specifed by \n" "compression. Currently, the available schemes are:\n" "CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED \n" " CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style \n" "packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \n" "\"byte_offset \" compression. CBF_NONE No compression.\n" "The values compressed are limited to 64 bits. If any element in the \n" "array is larger than 64 bits, the value compressed is the nearest \n" "64-bit value.\n" "Currently, the source array must consist of chars, shorts or ints \n" "(signed or unsigned)for cbf_set_image, or IEEE doubles or floats for \n" "cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof \n" "(int), sizeof(double) or sizeof(float), the function returns \n" "CBF_ARGUMENT.\n" "The parameter reserved is presently unused and should be set to 0.\n" "ARGUMENTS\n" "handle CBF handle. reserved Unused. Any value other \n" "than 0 is invalid. element_number The number of the detector \n" "element counting from 0 by order of appearance in the \n" "\"diffrn_data_frame \" category. compression Compression type. \n" "array Pointer to the image array. elsize Size in \n" "bytes of each image array element. elsigned Set to non-0 if \n" "the image array elements are signed. ndimslow Slowest array \n" "dimension. ndimmid Second slowest array dimension. ndimfast \n" " Fastest array dimension.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_require_category", _wrap_cbf_handle_struct_require_category, METH_VARARGS, (char *)"\n" "Returns : string\n" "*args : \n" "\n" "C prototype: int cbf_require_category (cbf_handle handle,\n" " const char *categoryname);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_rewuire_category makes the category in the current data block \n" "with name categoryname the current category, if it exists, or creates \n" "the catagory if it does not exist.\n" "The comparison is case-insensitive.\n" "The current column and row become undefined.\n" "ARGUMENTS\n" "handle CBF handle. categoryname The name of the category to \n" "find.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_reciprocal_cell", _wrap_cbf_handle_struct_get_reciprocal_cell, METH_VARARGS, (char *)"\n" "Returns : Float astar,Float bstar,Float cstar,Float alphastar,Float betastar,\n" " Float gammastar\n" "*args : \n" "\n" "C prototype: int cbf_get_reciprocal_cell (cbf_handle handle, double cell[6],\n" " double cell_esd[6] );\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_reciprocal_cell sets cell[0:2] to the double values of the \n" "reciprocal cell edge lengths a*, b* and c* in AAngstroms-1, cell[3:5] \n" "to the double values of the reciprocal cell angles a*, b* and g* in \n" "degrees, cell_esd[0:2] to the double values of the estimated \n" "strandard deviations of the reciprocal cell edge lengths a*, b* and \n" "c* in AAngstroms-1, cell_esd[3:5] to the double values of the \n" "estimated standard deviations of the the reciprocal cell angles a*, \n" "b* and g* in degrees.\n" "The values returned are retrieved from the first row of the \"cell \n" "\" category. The value of \"_cell.entry_id \" is ignored.\n" "cell or cell_esd may be NULL.\n" "If cell is NULL, the reciprocal cell parameters are not retrieved.\n" "If cell_esd is NULL, the reciprocal cell parameter esds are not \n" "retrieved.\n" "If the \"cell \" category is present, but some of the values are \n" "missing, zeros are returned for the missing values.\n" "ARGUMENTS\n" "handle CBF handle. cell Pointer to the destination array of \n" "6 doubles for the reciprocal cell parameters. cell_esd Pointer to \n" "the destination array of 6 doubles for the reciprocal cell parameter \n" "esds.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success. No errors is \n" "returned for missing values if the \"cell \" category exists.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_reciprocal_cell_esd", _wrap_cbf_handle_struct_get_reciprocal_cell_esd, METH_VARARGS, (char *)"cbf_handle_struct_get_reciprocal_cell_esd(cbf_handle_struct self)"}, { (char *)"cbf_handle_struct_get_3d_image_size", _wrap_cbf_handle_struct_get_3d_image_size, METH_VARARGS, (char *)"\n" "Returns : size_t ndimslow,size_t ndimmid,size_t ndimfast\n" "*args : Integer element_number\n" "\n" "C prototype: int cbf_get_3d_image_size (cbf_handle handle,\n" " unsigned int reserved, unsigned int element_number,\n" " size_t *ndimslow, size_t *ndimmid, size_t *ndimfast);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_image_size, cbf_get_image_size_fs and cbf_get_image_size_sf \n" "set *ndimslow and *ndimfast to the slow and fast dimensions of the \n" "image array for element number element_number. If the array is \n" "1-dimensional, *ndimslow will be set to the array size and *ndimfast \n" "will be set to 1. If the array is 3-dimensional an error code will be \n" "returned. cbf_get_3d_image_size, cbf_get_3d_image_size_fs and \n" "cbf_get_3d_image_size_sf set *ndimslow, *ndimmid and *ndimfast to the \n" "slowest, next fastest and fastest dimensions, respectively, of the 3D \n" "image array for element number element_number. If the array is \n" "1-dimensional, *ndimslow will be set to the array size and *ndimmid \n" "and\n" "\n" ""}, { (char *)"cbf_handle_struct_find_tag_root", _wrap_cbf_handle_struct_find_tag_root, METH_VARARGS, (char *)"\n" "Returns : String tagroot\n" "*args : String tagname\n" "\n" "C prototype: int cbf_find_tag_root (cbf_handle handle, const char* tagname,\n" " const char** tagroot);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_find_tag_root sets *tagroot to the root tag of which tagname is \n" "an alias. cbf_set_tag_root sets tagname as an alias of tagroot_in in \n" "the dictionary associated with handle, creating the dictionary if \n" "necessary. cbf_require_tag_root sets *tagroot to the root tag of \n" "which tagname is an alias, if there is one, or to the value of \n" "tagname, if tagname is not an alias.\n" "A returned tagroot string must not be modified in any way.\n" "ARGUMENTS\n" "handle CBF handle. tagname tag name which may be an alias. \n" "tagroot pointer to a returned tag root name. tagroot_in input \n" "tag root name.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_require_category_root", _wrap_cbf_handle_struct_require_category_root, METH_VARARGS, (char *)"cbf_handle_struct_require_category_root(cbf_handle_struct self, char categoryname) -> char"}, { (char *)"cbf_handle_struct_set_realarray_wdims_sf", _wrap_cbf_handle_struct_set_realarray_wdims_sf, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : int compression,int binary_id,(binary) String data,int elsize,\n" " int elements,String byteorder,int dimslow,int dimmid,int dimfast,\n" " int padding\n" "\n" "C prototype: int cbf_set_realarray_wdims_sf (cbf_handle handle,\n" " unsigned int compression, int binary_id, void *array,\n" " size_t elsize, size_t elements, const char *byteorder,\n" " size_t dimslow, size_t dimmid, size_t dimfast,\n" " size_t padding);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_integerarray sets the binary value of the item at the current \n" "column and row to an integer array. The array consists of elements \n" "elements of elsize bytes each, starting at array. The elements are \n" "signed if elsigned is non-0 and unsigned otherwise. binary_id is the \n" "binary section identifier. cbf_set_realarray sets the binary value of \n" "the item at the current column and row to an integer array. The array \n" "consists of elements elements of elsize bytes each, starting at \n" "array. binary_id is the binary section identifier.\n" "The cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, \n" "cbf_set_integerarray_wdims_sf, cbf_set_realarray_wdims, \n" "cbf_set_realarray_wdims_fs and cbf_set_realarray_wdims_sf variants \n" "allow the data header values of byteorder, dimfast, dimmid, dimslow \n" "and padding to be set to the data byte order, the fastest, second \n" "fastest and third fastest array dimensions and the size in byte of \n" "the post data padding to be used.\n" "The array will be compressed using the compression scheme specifed by \n" "compression. Currently, the available schemes are:\n" "CBF_CANONICAL Canonical-code compression (section 3.3.1) \n" "CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 \n" " CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET \n" "Simple \"byte_offset \" compression. CBF_NONE No \n" "compression. NOTE: This scheme is by far the slowest of the four and \n" "uses much more disk space. It is intended for routine use with small \n" "arrays only. With large arrays (like images) it should be used only \n" "for debugging.\n" "The values compressed are limited to 64 bits. If any element in the \n" "array is larger than 64 bits, the value compressed is the nearest \n" "64-bit value.\n" "Currently, the source array must consist of chars, shorts or ints \n" "(signed or unsigned), for cbf_set_integerarray, or IEEE doubles or \n" "floats for cbf_set_realarray. If elsize is not equal to sizeof \n" "(char), sizeof (short) or sizeof (int), the function returns \n" "CBF_ARGUMENT.\n" "ARGUMENTS\n" "handle CBF handle. compression Compression method to use. \n" "binary_id Integer binary identifier. array Pointer to the \n" "source array. elsize Size in bytes of each source array \n" "element. elsigned Set to non-0 if the source array elements are \n" "signed. elements: The number of elements in the array.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_integervalue", _wrap_cbf_handle_struct_set_integervalue, METH_VARARGS, (char *)"\n" "Returns : int number\n" "*args : \n" "\n" "C prototype: int cbf_set_integervalue (cbf_handle handle, int number);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_integervalue sets the item at the current column and row to \n" "the integer value number written as a decimal ASCII string.\n" "ARGUMENTS\n" "handle CBF handle. number Integer value.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_category_name", _wrap_cbf_handle_struct_category_name, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : string\n" "\n" "C prototype: int cbf_category_name (cbf_handle handle,\n" " const char **categoryname);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_category_name sets *categoryname to point to the name of the \n" "current category of the current data block.\n" "The category name will be valid as long as the category exists.\n" "The name must not be modified by the program in any way.\n" "ARGUMENTS\n" "handle CBF handle. categoryname Pointer to the destination \n" "category name pointer.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_typeofvalue", _wrap_cbf_handle_struct_get_typeofvalue, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : string\n" "\n" "C prototype: int cbf_get_typeofvalue (cbf_handle handle,\n" " const char **typeofvalue);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_value sets *typeofvalue to point an ASCII descriptor of the \n" "value of the item at the current column and row. The strings that may \n" "be returned are:\n" " \"null \" for a null value indicated by a \". \" or a \"? \" \n" "\"bnry \" for a binary value \"word \" for an unquoted string \n" "\"dblq \" for a double-quoted string \"sglq \" for a single-quoted \n" "string \"text \" for a semicolon-quoted string (multiline text \n" "field) \"prns \" for a parenthesis-bracketed string (multiline text \n" "field) \"brcs \" for a brace-bracketed string (multiline text field) \n" " \"bkts \" for a square-bracket-bracketed string (multiline text \n" "field) \"tsqs \" for a treble-single-quote quoted string (multiline \n" "text field) \"tdqs \" for a treble-double-quote quoted string \n" "(multiline text field)\n" "Not all types are valid for all type of CIF files. In partcular the \n" "types \"prns \", \"brcs \", \"bkts \" were introduced with DDLm \n" "and are not valid in DDL1 or DDL2 CIFS. The types \"tsqs \" and \n" "\"tdqs \" are not formally part of the CIF syntax. A field for which \n" "no value has been set sets *typeofvalue to NULL rather than to the \n" "string \"null \".\n" "The typeofvalue must not be modified by the program in any way.\n" "ARGUMENTS\n" "handle CBF handle. typeofvalue Pointer to the destination \n" "type-of-value string pointer.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_real_image", _wrap_cbf_handle_struct_set_real_image, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : int element_number,int compression,(binary) String data,int elsize,\n" " int dimslow,int dimfast\n" "\n" "C prototype: int cbf_set_real_image (cbf_handle handle, unsigned int reserved,\n" " unsigned int element_number, unsigned int compression,\n" " void *array,size_t elsize, size_t ndimslow,\n" " size_t ndimfast);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image \n" "array for element number element_number. The array consists of \n" "ndimfast *ndimslow elements of elsize bytes each, starting at array. \n" "The elements are signed if elsign is non-zero and unsigned otherwise. \n" "cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf \n" "write the image array for element number element_number. The array \n" "consists of ndimfast *ndimslow IEEE double or float elements of \n" "elsize bytes each, starting at array. cbf_set_3d_image, \n" "cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array \n" "for element number element_number. The array consists of ndimfast \n" "*ndimmid *ndimslow elements of elsize bytes each, starting at array. \n" "The elements are signed if elsign is non-0 and unsigned otherwise. \n" "cbf_set_real_3d_image, cbf_set_real_3d_image_fs and \n" "cbf_set_real_3d_image_sf writes the 3D image array for element number \n" "element_number. The array consists of ndimfast *ndimmid *ndimslow \n" "IEEE double or float elements of elsize bytes each, starting at \n" "array.\n" "The _fs calls give the dimensions in a fast-to-slow order. The calls \n" "with no suffix and the calls _sf calls give the dimensions in \n" "slow-to-fast order\n" "If the array is 1-dimensional, ndimslow should be the array size and \n" "ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the \n" "array is 2-dimensional and the 3D calls are used, ndimslow and \n" "ndimmid should be used for the array dimensions and ndimfast should \n" "be set to 1.\n" "The array will be compressed using the compression scheme specifed by \n" "compression. Currently, the available schemes are:\n" "CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED \n" " CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style \n" "packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \n" "\"byte_offset \" compression. CBF_NONE No compression.\n" "The values compressed are limited to 64 bits. If any element in the \n" "array is larger than 64 bits, the value compressed is the nearest \n" "64-bit value.\n" "Currently, the source array must consist of chars, shorts or ints \n" "(signed or unsigned)for cbf_set_image, or IEEE doubles or floats for \n" "cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof \n" "(int), sizeof(double) or sizeof(float), the function returns \n" "CBF_ARGUMENT.\n" "The parameter reserved is presently unused and should be set to 0.\n" "ARGUMENTS\n" "handle CBF handle. reserved Unused. Any value other \n" "than 0 is invalid. element_number The number of the detector \n" "element counting from 0 by order of appearance in the \n" "\"diffrn_data_frame \" category. compression Compression type. \n" "array Pointer to the image array. elsize Size in \n" "bytes of each image array element. elsigned Set to non-0 if \n" "the image array elements are signed. ndimslow Slowest array \n" "dimension. ndimmid Second slowest array dimension. ndimfast \n" " Fastest array dimension.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_get_3d_image_as_string", _wrap_cbf_handle_struct_get_3d_image_as_string, METH_VARARGS, (char *)"\n" "Returns : (Binary)String\n" "*args : int element_number,int elsize,int elsign,int ndimslow,int ndimmid,\n" " int ndimfast\n" "\n" "C prototype: int cbf_get_3d_image (cbf_handle handle, unsigned int reserved,\n" " unsigned int element_number, void *array, size_t elsize,\n" " int elsign, size_t ndimslow, size_t ndimmid,\n" " size_t ndimfast);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image \n" "array for element number element_number into an array. The array \n" "consists of ndimslow *ndimfast elements of elsize bytes each, \n" "starting at array. The elements are signed if elsign is non-0 and \n" "unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and \n" "cbf_get_real_image_sf read the image array of IEEE doubles or floats \n" "for element number element_number into an array. A real array is \n" "always signed. cbf_get_3d_image, cbf_get_3d_image_fs and \n" "cbf_get_3d_image_sf read the 3D image array for element number \n" "element_number into an array. The array consists of ndimslow *ndimmid \n" "*ndimfast elements of elsize bytes each, starting at array. The \n" "elements are signed if elsign is non-0 and unsigned otherwise. \n" "cbf_get_real_3d_image, cbf_get_real_3d_image_fs, \n" "cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or \n" "floats for element number element_number into an array. A real array \n" "is always signed.\n" "The _fs calls give the dimensions in a fast-to-slow order. The calls \n" "with no suffix and the calls _sf calls give the dimensions in \n" "slow-to-fast order\n" "The structure of the array as a 1-, 2- or 3-dimensional array should \n" "agree with the structure of the array given in the \n" "ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, \n" "ndimslow should be the array size and ndimfast and, for the 3D calls, \n" "ndimmid, should be set to 1 both in the call and in the imgCIF data \n" "being processed. If the array is 2-dimensional and a 3D call is used, \n" "ndimslow and ndimmid should be the\n" "\n" ""}, { (char *)"cbf_handle_struct_remove_row", _wrap_cbf_handle_struct_remove_row, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : \n" "\n" "C prototype: int cbf_remove_row (cbf_handle handle);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_remove_row deletes the current row in the current category.\n" "If the current row was the last row, it will move down by 1, \n" "otherwise, it will remain the same.\n" "ARGUMENTS\n" "handle CBF handle.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_overload", _wrap_cbf_handle_struct_set_overload, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : Integer element_number,Float overload\n" "\n" "C prototype: int cbf_set_overload (cbf_handle handle,\n" " unsigned int element_number, double overload);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_overload sets the overload value of element number \n" "element_number to overload.\n" "ARGUMENTS\n" "handle CBF handle. element_number The number of the \n" "detector element counting from 0 by order of appearance in the \n" "\"diffrn_data_frame \" category. overload New overload value.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_get_image_size", _wrap_cbf_handle_struct_get_image_size, METH_VARARGS, (char *)"\n" "Returns : size_t ndim1,size_t ndim2\n" "*args : Integer element_number\n" "\n" "C prototype: int cbf_get_image_size (cbf_handle handle, unsigned int reserved,\n" " unsigned int element_number, size_t *ndimslow,\n" " size_t *ndimfast);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_image_size, cbf_get_image_size_fs and cbf_get_image_size_sf \n" "set *ndimslow and *ndimfast to the slow and fast dimensions of the \n" "image array for element number element_number. If the array is \n" "1-dimensional, *ndimslow will be set to the array size and *ndimfast \n" "will be set to 1. If the array is 3-dimensional an error code will be \n" "returned. cbf_get_3d_image_size, cbf_get_3d_image_size_fs and \n" "cbf_get_3d_image_size_sf set *ndimslow, *ndimmid and *ndimfast to the \n" "slowest, next fastest and fastest dimensions, respectively, of the 3D \n" "image array for element number element_number. If the array is \n" "1-dimensional, *ndimslow will be set to the array size and *ndimmid \n" "and\n" "\n" ""}, { (char *)"cbf_handle_struct_set_3d_image_sf", _wrap_cbf_handle_struct_set_3d_image_sf, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : int element_number,int compression,(binary) String data,int elsize,\n" " int elsign,int dimslow,int dimmid,int dimfast\n" "\n" "C prototype: int cbf_set_3d_image_sf(cbf_handle handle, unsigned int reserved,\n" " unsigned int element_number, unsigned int compression,\n" " void *array, size_t elsize, int elsign, size_t ndimslow,\n" " size_t ndimmid, size_t ndimfast);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image \n" "array for element number element_number. The array consists of \n" "ndimfast *ndimslow elements of elsize bytes each, starting at array. \n" "The elements are signed if elsign is non-zero and unsigned otherwise. \n" "cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf \n" "write the image array for element number element_number. The array \n" "consists of ndimfast *ndimslow IEEE double or float elements of \n" "elsize bytes each, starting at array. cbf_set_3d_image, \n" "cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array \n" "for element number element_number. The array consists of ndimfast \n" "*ndimmid *ndimslow elements of elsize bytes each, starting at array. \n" "The elements are signed if elsign is non-0 and unsigned otherwise. \n" "cbf_set_real_3d_image, cbf_set_real_3d_image_fs and \n" "cbf_set_real_3d_image_sf writes the 3D image array for element number \n" "element_number. The array consists of ndimfast *ndimmid *ndimslow \n" "IEEE double or float elements of elsize bytes each, starting at \n" "array.\n" "The _fs calls give the dimensions in a fast-to-slow order. The calls \n" "with no suffix and the calls _sf calls give the dimensions in \n" "slow-to-fast order\n" "If the array is 1-dimensional, ndimslow should be the array size and \n" "ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the \n" "array is 2-dimensional and the 3D calls are used, ndimslow and \n" "ndimmid should be used for the array dimensions and ndimfast should \n" "be set to 1.\n" "The array will be compressed using the compression scheme specifed by \n" "compression. Currently, the available schemes are:\n" "CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED \n" " CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style \n" "packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \n" "\"byte_offset \" compression. CBF_NONE No compression.\n" "The values compressed are limited to 64 bits. If any element in the \n" "array is larger than 64 bits, the value compressed is the nearest \n" "64-bit value.\n" "Currently, the source array must consist of chars, shorts or ints \n" "(signed or unsigned)for cbf_set_image, or IEEE doubles or floats for \n" "cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof \n" "(int), sizeof(double) or sizeof(float), the function returns \n" "CBF_ARGUMENT.\n" "The parameter reserved is presently unused and should be set to 0.\n" "ARGUMENTS\n" "handle CBF handle. reserved Unused. Any value other \n" "than 0 is invalid. element_number The number of the detector \n" "element counting from 0 by order of appearance in the \n" "\"diffrn_data_frame \" category. compression Compression type. \n" "array Pointer to the image array. elsize Size in \n" "bytes of each image array element. elsigned Set to non-0 if \n" "the image array elements are signed. ndimslow Slowest array \n" "dimension. ndimmid Second slowest array dimension. ndimfast \n" " Fastest array dimension.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_get_real_image_sf_as_string", _wrap_cbf_handle_struct_get_real_image_sf_as_string, METH_VARARGS, (char *)"\n" "Returns : (Binary)String\n" "*args : int element_number,int elsize,int ndimslow,int ndimfast\n" "\n" "C prototype: int cbf_get_real_image_sf (cbf_handle handle,\n" " unsigned int reserved, unsigned int element_number,\n" " void *array, size_t elsize, size_t ndimslow,\n" " size_t ndimfast);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image \n" "array for element number element_number into an array. The array \n" "consists of ndimslow *ndimfast elements of elsize bytes each, \n" "starting at array. The elements are signed if elsign is non-0 and \n" "unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and \n" "cbf_get_real_image_sf read the image array of IEEE doubles or floats \n" "for element number element_number into an array. A real array is \n" "always signed. cbf_get_3d_image, cbf_get_3d_image_fs and \n" "cbf_get_3d_image_sf read the 3D image array for element number \n" "element_number into an array. The array consists of ndimslow *ndimmid \n" "*ndimfast elements of elsize bytes each, starting at array. The \n" "elements are signed if elsign is non-0 and unsigned otherwise. \n" "cbf_get_real_3d_image, cbf_get_real_3d_image_fs, \n" "cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or \n" "floats for element number element_number into an array. A real array \n" "is always signed.\n" "The _fs calls give the dimensions in a fast-to-slow order. The calls \n" "with no suffix and the calls _sf calls give the dimensions in \n" "slow-to-fast order\n" "The structure of the array as a 1-, 2- or 3-dimensional array should \n" "agree with the structure of the array given in the \n" "ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, \n" "ndimslow should be the array size and ndimfast and, for the 3D calls, \n" "ndimmid, should be set to 1 both in the call and in the imgCIF data \n" "being processed. If the array is 2-dimensional and a 3D call is used, \n" "ndimslow and ndimmid should be the\n" "\n" ""}, { (char *)"cbf_handle_struct_get_image_as_string", _wrap_cbf_handle_struct_get_image_as_string, METH_VARARGS, (char *)"\n" "Returns : (Binary)String\n" "*args : int element_number,int elsize,int elsign,int ndimslow,int ndimfast\n" "\n" "C prototype: int cbf_get_image (cbf_handle handle, unsigned int reserved,\n" " unsigned int element_number, void *array, size_t elsize,\n" " int elsign, size_t ndimslow, size_t ndimfast);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image \n" "array for element number element_number into an array. The array \n" "consists of ndimslow *ndimfast elements of elsize bytes each, \n" "starting at array. The elements are signed if elsign is non-0 and \n" "unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and \n" "cbf_get_real_image_sf read the image array of IEEE doubles or floats \n" "for element number element_number into an array. A real array is \n" "always signed. cbf_get_3d_image, cbf_get_3d_image_fs and \n" "cbf_get_3d_image_sf read the 3D image array for element number \n" "element_number into an array. The array consists of ndimslow *ndimmid \n" "*ndimfast elements of elsize bytes each, starting at array. The \n" "elements are signed if elsign is non-0 and unsigned otherwise. \n" "cbf_get_real_3d_image, cbf_get_real_3d_image_fs, \n" "cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or \n" "floats for element number element_number into an array. A real array \n" "is always signed.\n" "The _fs calls give the dimensions in a fast-to-slow order. The calls \n" "with no suffix and the calls _sf calls give the dimensions in \n" "slow-to-fast order\n" "The structure of the array as a 1-, 2- or 3-dimensional array should \n" "agree with the structure of the array given in the \n" "ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, \n" "ndimslow should be the array size and ndimfast and, for the 3D calls, \n" "ndimmid, should be set to 1 both in the call and in the imgCIF data \n" "being processed. If the array is 2-dimensional and a 3D call is used, \n" "ndimslow and ndimmid should be the\n" "\n" ""}, { (char *)"cbf_handle_struct_set_tag_root", _wrap_cbf_handle_struct_set_tag_root, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : String tagname,String tagroot_in\n" "\n" "C prototype: int cbf_set_tag_root (cbf_handle handle, const char* tagname,\n" " const char*tagroot_in);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_find_tag_root sets *tagroot to the root tag of which tagname is \n" "an alias. cbf_set_tag_root sets tagname as an alias of tagroot_in in \n" "the dictionary associated with handle, creating the dictionary if \n" "necessary. cbf_require_tag_root sets *tagroot to the root tag of \n" "which tagname is an alias, if there is one, or to the value of \n" "tagname, if tagname is not an alias.\n" "A returned tagroot string must not be modified in any way.\n" "ARGUMENTS\n" "handle CBF handle. tagname tag name which may be an alias. \n" "tagroot pointer to a returned tag root name. tagroot_in input \n" "tag root name.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_write_widefile", _wrap_cbf_handle_struct_write_widefile, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : String filename,Integer ciforcbf,Integer Headers,Integer encoding\n" "\n" "C prototype: int cbf_write_widefile (cbf_handle handle, FILE *file,\n" " int readable, int ciforcbf, int flags, int encoding);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_write_file writes the CBF object specified by handle into the \n" "file file, following CIF 1.0 conventions of 80 character lines. \n" "cbf_write_widefile writes the CBF object specified by handle into the \n" "file file, following CIF 1.1 conventions of 2048 character lines. A \n" "warning is issued to stderr for ascii lines over the limit, and an \n" "attempt is made to fold lines to fit. No test is performed on binary \n" "sections.\n" "If a dictionary has been provided, aliases will be applied on output.\n" "Unlike cbf_read_file, the file does not have to be random-access.\n" "If the file is random-access and readable, readable can be set to \n" "non-0 to indicate to CBFlib that the file can be used as a buffer to \n" "conserve disk space. If the file is not random-access or not \n" "readable, readable must be 0.\n" "\n" ""}, { (char *)"cbf_handle_struct_count_rows", _wrap_cbf_handle_struct_count_rows, METH_VARARGS, (char *)"\n" "Returns : Integer\n" "*args : \n" "\n" "C prototype: int cbf_count_rows (cbf_handle handle, unsigned int *rows);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_count_rows puts the number of rows in the current category in \n" "*rows .\n" "ARGUMENTS\n" "handle CBF handle. rows Pointer to the destination row count.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_require_datablock", _wrap_cbf_handle_struct_require_datablock, METH_VARARGS, (char *)"\n" "Returns : string\n" "*args : \n" "\n" "C prototype: int cbf_require_datablock (cbf_handle handle,\n" " const char *datablockname);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_require_datablock makes the data block with name datablockname \n" "the current data block, if it exists, or creates it if it does not.\n" "The comparison is case-insensitive.\n" "The current category becomes undefined.\n" "ARGUMENTS\n" "handle CBF handle. datablockname The name of the data \n" "block to find or create.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_integerarray", _wrap_cbf_handle_struct_set_integerarray, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : int compression,int binary_id,(binary) String data,int elsize,\n" " int elsigned,int elements\n" "\n" "C prototype: int cbf_set_integerarray (cbf_handle handle,\n" " unsigned int compression, int binary_id, void *array,\n" " size_t elsize, int elsigned, size_t elements);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_integerarray sets the binary value of the item at the current \n" "column and row to an integer array. The array consists of elements \n" "elements of elsize bytes each, starting at array. The elements are \n" "signed if elsigned is non-0 and unsigned otherwise. binary_id is the \n" "binary section identifier. cbf_set_realarray sets the binary value of \n" "the item at the current column and row to an integer array. The array \n" "consists of elements elements of elsize bytes each, starting at \n" "array. binary_id is the binary section identifier.\n" "The cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, \n" "cbf_set_integerarray_wdims_sf, cbf_set_realarray_wdims, \n" "cbf_set_realarray_wdims_fs and cbf_set_realarray_wdims_sf variants \n" "allow the data header values of byteorder, dimfast, dimmid, dimslow \n" "and padding to be set to the data byte order, the fastest, second \n" "fastest and third fastest array dimensions and the size in byte of \n" "the post data padding to be used.\n" "The array will be compressed using the compression scheme specifed by \n" "compression. Currently, the available schemes are:\n" "CBF_CANONICAL Canonical-code compression (section 3.3.1) \n" "CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 \n" " CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET \n" "Simple \"byte_offset \" compression. CBF_NONE No \n" "compression. NOTE: This scheme is by far the slowest of the four and \n" "uses much more disk space. It is intended for routine use with small \n" "arrays only. With large arrays (like images) it should be used only \n" "for debugging.\n" "The values compressed are limited to 64 bits. If any element in the \n" "array is larger than 64 bits, the value compressed is the nearest \n" "64-bit value.\n" "Currently, the source array must consist of chars, shorts or ints \n" "(signed or unsigned), for cbf_set_integerarray, or IEEE doubles or \n" "floats for cbf_set_realarray. If elsize is not equal to sizeof \n" "(char), sizeof (short) or sizeof (int), the function returns \n" "CBF_ARGUMENT.\n" "ARGUMENTS\n" "handle CBF handle. compression Compression method to use. \n" "binary_id Integer binary identifier. array Pointer to the \n" "source array. elsize Size in bytes of each source array \n" "element. elsigned Set to non-0 if the source array elements are \n" "signed. elements: The number of elements in the array.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_new_datablock", _wrap_cbf_handle_struct_new_datablock, METH_VARARGS, (char *)"\n" "Returns : string\n" "*args : \n" "\n" "C prototype: int cbf_new_datablock (cbf_handle handle,\n" " const char *datablockname);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_new_datablock creates a new data block with name datablockname \n" "and makes it the current data block. cbf_new_saveframe creates a new \n" "save frame with name saveframename within the current data block and \n" "makes the new save frame the current save frame.\n" "If a data block or save frame with this name already exists, the \n" "existing data block or save frame becomes the current data block or \n" "save frame.\n" "ARGUMENTS\n" "handle CBF handle. datablockname The name of the new data \n" "block. saveframename The name of the new save frame.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_datestamp", _wrap_cbf_handle_struct_set_datestamp, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : int year,int month,int day,int hour,int minute,double second,\n" " int timezone,Float precision\n" "\n" "C prototype: int cbf_set_datestamp (cbf_handle handle, unsigned int reserved,\n" " int year, int month, int day, int hour, int minute,\n" " double second, int timezone, double precision);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_datestamp sets the collection timestamp in seconds since \n" "January 1 1970 to the value specified by time. The timezone \n" "difference from UTC\n" "\n" ""}, { (char *)"cbf_handle_struct_next_row", _wrap_cbf_handle_struct_next_row, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : \n" "\n" "C prototype: int cbf_next_row (cbf_handle handle);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_next_row makes the row following the current row in the current \n" "category the current row.\n" "If there are no more rows, the function returns CBF_NOTFOUND.\n" "The current column is not affected.\n" "ARGUMENTS\n" "handle CBF handle.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_category_root", _wrap_cbf_handle_struct_set_category_root, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : String categoryname,String categoryroot\n" "\n" "C prototype: int cbf_set_category_root (cbf_handle handle,\n" " const char* categoryname_in, const char*categoryroot);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_find_category_root sets *categoryroot to the root category of \n" "which categoryname is an alias. cbf_set_category_root sets \n" "categoryname_in as an alias of categoryroot in the dictionary \n" "associated with handle, creating the dictionary if necessary. \n" "cbf_require_category_root sets *categoryroot to the root category of \n" "which categoryname is an alias, if there is one, or to the value of \n" "categoryname, if categoryname is not an alias.\n" "A returned categoryroot string must not be modified in any way.\n" "ARGUMENTS\n" "handle CBF handle. categoryname category name which \n" "may be an alias. categoryroot pointer to a returned category \n" "root name. categoryroot_in input category root name.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_set_pixel_size_fs", _wrap_cbf_handle_struct_set_pixel_size_fs, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : Int element_number,Int axis_number,Float pixel size\n" "\n" "C prototype: int cbf_set_pixel_size_fs(cbf_handle handle,\n" " unsigned int element_number, int axis_number,\n" " double psize);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_pixel_size and cbf_set_pixel_size_sf set the item in the \n" ""e;size"e; column of the \"array_structure_list \" category \n" "at the row which matches axis axis_number of the detector element \n" "element_number converting the double pixel size psize from meters to \n" "millimeters in storing it in the \"size \" column for the axis \n" "axis_number of the detector element element_number. The axis_number \n" "is numbered from 1, starting with the slowest axis. \n" "cbf_set_pixel_size_fs sets the item\n" "\n" ""}, { (char *)"cbf_handle_struct_insert_row", _wrap_cbf_handle_struct_insert_row, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : Integer\n" "\n" "C prototype: int cbf_insert_row (cbf_handle handle, unsigned int rownumber);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_insert_row adds a new row to the current category. The new row is \n" "inserted as row rownumber and existing rows starting from rownumber \n" "are moved up by 1. The new row becomes the current row.\n" "If the category has fewer than rownumber rows, the function returns \n" "CBF_NOTFOUND.\n" "The row numbers start from 0.\n" "ARGUMENTS\n" "handle CBF handle. rownumber The row number of the new row.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_new_column", _wrap_cbf_handle_struct_new_column, METH_VARARGS, (char *)"\n" "Returns : string\n" "*args : \n" "\n" "C prototype: int cbf_new_column (cbf_handle handle, const char *columnname);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_new_column creates a new column in the current category with name \n" "columnname and makes it the current column.\n" "If a column with this name already exists, the existing column \n" "becomes the current category.\n" "ARGUMENTS\n" "handle CBF handle. columnname The name of the new column.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_real_3d_image_as_string", _wrap_cbf_handle_struct_get_real_3d_image_as_string, METH_VARARGS, (char *)"\n" "Returns : (Binary)String\n" "*args : int element_number,int elsize,int ndimslow,int ndimmid,int ndimfast\n" "\n" "C prototype: int cbf_get_real_3d_image (cbf_handle handle,\n" " unsigned int reserved, unsigned int element_number,\n" " void *array, size_t elsize, size_t ndimslow,\n" " size_t ndimmid, size_t ndimfast);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image \n" "array for element number element_number into an array. The array \n" "consists of ndimslow *ndimfast elements of elsize bytes each, \n" "starting at array. The elements are signed if elsign is non-0 and \n" "unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and \n" "cbf_get_real_image_sf read the image array of IEEE doubles or floats \n" "for element number element_number into an array. A real array is \n" "always signed. cbf_get_3d_image, cbf_get_3d_image_fs and \n" "cbf_get_3d_image_sf read the 3D image array for element number \n" "element_number into an array. The array consists of ndimslow *ndimmid \n" "*ndimfast elements of elsize bytes each, starting at array. The \n" "elements are signed if elsign is non-0 and unsigned otherwise. \n" "cbf_get_real_3d_image, cbf_get_real_3d_image_fs, \n" "cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or \n" "floats for element number element_number into an array. A real array \n" "is always signed.\n" "The _fs calls give the dimensions in a fast-to-slow order. The calls \n" "with no suffix and the calls _sf calls give the dimensions in \n" "slow-to-fast order\n" "The structure of the array as a 1-, 2- or 3-dimensional array should \n" "agree with the structure of the array given in the \n" "ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, \n" "ndimslow should be the array size and ndimfast and, for the 3D calls, \n" "ndimmid, should be set to 1 both in the call and in the imgCIF data \n" "being processed. If the array is 2-dimensional and a 3D call is used, \n" "ndimslow and ndimmid should be the\n" "\n" ""}, { (char *)"cbf_handle_struct_get_integration_time", _wrap_cbf_handle_struct_get_integration_time, METH_VARARGS, (char *)"\n" "Returns : Float time\n" "*args : \n" "\n" "C prototype: int cbf_get_integration_time (cbf_handle handle,\n" " unsigned int reserved, double *time);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_integration_time sets *time to the integration time in \n" "seconds. The parameter reserved is presently unused and should be set \n" "to 0.\n" "ARGUMENTS\n" "handle CBF handle. reserved Unused. Any value other than 0 is \n" "invalid. time Pointer to the destination time.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_set_realarray", _wrap_cbf_handle_struct_set_realarray, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : int compression,int binary_id,(binary) String data,int elsize,\n" " int elements\n" "\n" "C prototype: int cbf_set_realarray (cbf_handle handle,\n" " unsigned int compression, int binary_id, void *array,\n" " size_t elsize, size_t elements);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_integerarray sets the binary value of the item at the current \n" "column and row to an integer array. The array consists of elements \n" "elements of elsize bytes each, starting at array. The elements are \n" "signed if elsigned is non-0 and unsigned otherwise. binary_id is the \n" "binary section identifier. cbf_set_realarray sets the binary value of \n" "the item at the current column and row to an integer array. The array \n" "consists of elements elements of elsize bytes each, starting at \n" "array. binary_id is the binary section identifier.\n" "The cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, \n" "cbf_set_integerarray_wdims_sf, cbf_set_realarray_wdims, \n" "cbf_set_realarray_wdims_fs and cbf_set_realarray_wdims_sf variants \n" "allow the data header values of byteorder, dimfast, dimmid, dimslow \n" "and padding to be set to the data byte order, the fastest, second \n" "fastest and third fastest array dimensions and the size in byte of \n" "the post data padding to be used.\n" "The array will be compressed using the compression scheme specifed by \n" "compression. Currently, the available schemes are:\n" "CBF_CANONICAL Canonical-code compression (section 3.3.1) \n" "CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 \n" " CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET \n" "Simple \"byte_offset \" compression. CBF_NONE No \n" "compression. NOTE: This scheme is by far the slowest of the four and \n" "uses much more disk space. It is intended for routine use with small \n" "arrays only. With large arrays (like images) it should be used only \n" "for debugging.\n" "The values compressed are limited to 64 bits. If any element in the \n" "array is larger than 64 bits, the value compressed is the nearest \n" "64-bit value.\n" "Currently, the source array must consist of chars, shorts or ints \n" "(signed or unsigned), for cbf_set_integerarray, or IEEE doubles or \n" "floats for cbf_set_realarray. If elsize is not equal to sizeof \n" "(char), sizeof (short) or sizeof (int), the function returns \n" "CBF_ARGUMENT.\n" "ARGUMENTS\n" "handle CBF handle. compression Compression method to use. \n" "binary_id Integer binary identifier. array Pointer to the \n" "source array. elsize Size in bytes of each source array \n" "element. elsigned Set to non-0 if the source array elements are \n" "signed. elements: The number of elements in the array.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_element_id", _wrap_cbf_handle_struct_get_element_id, METH_VARARGS, (char *)"\n" "Returns : String\n" "*args : Integer element_number\n" "\n" "C prototype: int cbf_get_element_id (cbf_handle handle,\n" " unsigned int element_number, const char **element_id);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_element_id sets *element_id to point to the ASCII value of \n" "the element_number'th \"diffrn_data_frame.detector_element_id \" \n" "entry, counting from 0.\n" "If the detector element does not exist, the function returns \n" "CBF_NOTFOUND.\n" "The element_id will be valid as long as the item exists and has not \n" "been set to a new value.\n" "The element_id must not be modified by the program in any way.\n" "ARGUMENTS\n" "handle CBF handle. element_number The number of the \n" "detector element counting from 0 by order of appearance in the \n" "\"diffrn_data_frame \" category. element_id Pointer to the \n" "destination.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_get_image_sf_as_string", _wrap_cbf_handle_struct_get_image_sf_as_string, METH_VARARGS, (char *)"\n" "Returns : (Binary)String\n" "*args : int element_number,int elsize,int elsign,int ndimslow,int ndimfast\n" "\n" "C prototype: int cbf_get_image_sf (cbf_handle handle, unsigned int reserved,\n" " unsigned int element_number, void *array, size_t elsize,\n" " int elsign, size_t ndimslow, size_t ndimfast);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image \n" "array for element number element_number into an array. The array \n" "consists of ndimslow *ndimfast elements of elsize bytes each, \n" "starting at array. The elements are signed if elsign is non-0 and \n" "unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and \n" "cbf_get_real_image_sf read the image array of IEEE doubles or floats \n" "for element number element_number into an array. A real array is \n" "always signed. cbf_get_3d_image, cbf_get_3d_image_fs and \n" "cbf_get_3d_image_sf read the 3D image array for element number \n" "element_number into an array. The array consists of ndimslow *ndimmid \n" "*ndimfast elements of elsize bytes each, starting at array. The \n" "elements are signed if elsign is non-0 and unsigned otherwise. \n" "cbf_get_real_3d_image, cbf_get_real_3d_image_fs, \n" "cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or \n" "floats for element number element_number into an array. A real array \n" "is always signed.\n" "The _fs calls give the dimensions in a fast-to-slow order. The calls \n" "with no suffix and the calls _sf calls give the dimensions in \n" "slow-to-fast order\n" "The structure of the array as a 1-, 2- or 3-dimensional array should \n" "agree with the structure of the array given in the \n" "ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, \n" "ndimslow should be the array size and ndimfast and, for the 3D calls, \n" "ndimmid, should be set to 1 both in the call and in the imgCIF data \n" "being processed. If the array is 2-dimensional and a 3D call is used, \n" "ndimslow and ndimmid should be the\n" "\n" ""}, { (char *)"cbf_handle_struct_get_3d_image_size_fs", _wrap_cbf_handle_struct_get_3d_image_size_fs, METH_VARARGS, (char *)"cbf_handle_struct_get_3d_image_size_fs(cbf_handle_struct self, unsigned int element_number)"}, { (char *)"cbf_handle_struct_set_value", _wrap_cbf_handle_struct_set_value, METH_VARARGS, (char *)"\n" "Returns : string\n" "*args : \n" "\n" "C prototype: int cbf_set_value (cbf_handle handle, const char *value);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_value sets the item at the current column and row to the \n" "ASCII value value.\n" "ARGUMENTS\n" "handle CBF handle. value ASCII value.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_current_timestamp", _wrap_cbf_handle_struct_set_current_timestamp, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : Integer timezone\n" "\n" "C prototype: int cbf_set_current_timestamp (cbf_handle handle,\n" " unsigned int reserved, int timezone);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_current_timestamp sets the collection timestamp to the \n" "current time. The timezone difference from UTC in minutes is set to \n" "timezone. If no timezone is desired, timezone should be \n" "CBF_NOTIMEZONE. If no timezone is used, the timest amp will be UTC. \n" "The parameter reserved is presently unused and should be set to 0.\n" "The new timestamp will have a precision of 1 second.\n" "ARGUMENTS\n" "handle CBF handle. reserved Unused. Any value other than 0 is \n" "invalid. timezone Timezone difference from UTC in minutes or \n" "CBF_NOTIMEZONE.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_require_doublevalue", _wrap_cbf_handle_struct_require_doublevalue, METH_VARARGS, (char *)"\n" "Returns : Float Number\n" "*args : Float Default\n" "\n" "C prototype: int cbf_require_doublevalue (cbf_handle handle, double *number,\n" " double defaultvalue);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_doublevalue sets *number to the value of the ASCII item at \n" "the current column and row interpreted as a decimal floating-point \n" "number. cbf_require_doublevalue sets *number to the value of the \n" "ASCII item at the current column and row interpreted as a decimal \n" "floating-point number, setting it to defaultvalue if necessary.\n" "If the value is not ASCII, the function returns CBF_BINARY.\n" "ARGUMENTS\n" "handle CBF handle. number Pointer to the destination \n" "number. defaultvalue default number value.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_rewind_datablock", _wrap_cbf_handle_struct_rewind_datablock, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : \n" "\n" "C prototype: int cbf_rewind_datablock (cbf_handle handle);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_rewind_datablock makes the first data block the current data \n" "block.\n" "If there are no data blocks, the function returns CBF_NOTFOUND.\n" "The current category becomes undefined.\n" "ARGUMENTS\n" "handle CBF handle.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_require_column_value", _wrap_cbf_handle_struct_require_column_value, METH_VARARGS, (char *)"\n" "Returns : String Name\n" "*args : String columnnanme,String Default\n" "\n" "C prototype: int cbf_require_column_value (cbf_handle handle,\n" " const char *columnname, const char **value,\n" " const char *defaultvalue);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_require_column_doublevalue sets *value to the ASCII item at the \n" "current row for the column given with the name given by *columnname, \n" "or to the string given by defaultvalue if the item cannot be found.\n" "ARGUMENTS\n" "handle CBF handle. columnname Name of the column \n" "containing the number. value pointer to the location to \n" "receive the value. defaultvalue Value to use if the requested \n" "column and value cannot be found.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_dictionary", _wrap_cbf_handle_struct_get_dictionary, METH_VARARGS, (char *)"\n" "Returns : CBFHandle dictionary\n" "*args : \n" "\n" "C prototype: int cbf_get_dictionary (cbf_handle handle,\n" " cbf_handle * dictionary);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_dictionary sets *dictionary to the handle of a CBF which has \n" "been associated with the CBF handle by cbf_set_dictionary. \n" "cbf_set_dictionary associates the CBF handle dictionary_in with \n" "handle as its dictionary. cbf_require_dictionary sets *dictionary to \n" "the handle of a CBF which has been associated with the CBF handle by \n" "cbf_set_dictionary or creates a new empty CBF and associates it with \n" "handle, returning the new handle in *dictionary.\n" "ARGUMENTS\n" "handle CBF handle. dictionary Pointer to CBF handle of \n" "dictionary. dictionary_in CBF handle of dcitionary.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_reset_saveframe", _wrap_cbf_handle_struct_reset_saveframe, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : \n" "\n" "C prototype: int cbf_reset_saveframe (cbf_handle handle);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_reset_datablock deletes all categories from the current data \n" "block. cbf_reset_saveframe deletes all categories from the current \n" "save frame.\n" "ARGUMENTS\n" "handle CBF handle.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_reciprocal_cell", _wrap_cbf_handle_struct_set_reciprocal_cell, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : double cell[6]\n" "\n" "C prototype: int cbf_set_reciprocal_cell (cbf_handle handle, double cell[6],\n" " double cell_esd[6] );\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_reciprocal_cell sets the reciprocal cell parameters to the \n" "double values given in cell[0:2] for the reciprocal cell edge lengths \n" "a*, b* and c* in AAngstroms-1, the double values given in cell[3:5] \n" "for the reciprocal cell angles a*, b* and g* in degrees, the double \n" "values given in cell_esd[0:2] for the estimated strandard deviations \n" "of the reciprocal cell edge lengths a*, b* and c* in AAngstroms, and \n" "the double values given in cell_esd[3:5] for the estimated standard \n" "deviations of the reciprocal cell angles a*, b* and g* in degrees.\n" "The values are placed in the first row of the \"cell \" category. If \n" "no value has been given for \"_cell.entry_id \", it is set to the \n" "value of the \"diffrn.id \" entry of the current data block.\n" "cell or cell_esd may be NULL.\n" "If cell is NULL, the reciprocal cell parameters are not set.\n" "If cell_esd is NULL, the reciprocal cell parameter esds are not set.\n" "If the \"cell \" category is not present, it is created. If any of \n" "the necessary columns are not present, they are created.\n" "ARGUMENTS\n" "handle CBF handle. cell Pointer to the array of 6 doubles \n" "for the reciprocal cell parameters. cell_esd Pointer to the array \n" "of 6 doubles for the reciprocal cell parameter esds.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_reciprocal_cell_esd", _wrap_cbf_handle_struct_set_reciprocal_cell_esd, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : double cell_esd[6]\n" "\n" "C prototype: int cbf_set_reciprocal_cell (cbf_handle handle, double cell[6],\n" " double cell_esd[6] );\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_reciprocal_cell sets the reciprocal cell parameters to the \n" "double values given in cell[0:2] for the reciprocal cell edge lengths \n" "a*, b* and c* in AAngstroms-1, the double values given in cell[3:5] \n" "for the reciprocal cell angles a*, b* and g* in degrees, the double \n" "values given in cell_esd[0:2] for the estimated strandard deviations \n" "of the reciprocal cell edge lengths a*, b* and c* in AAngstroms, and \n" "the double values given in cell_esd[3:5] for the estimated standard \n" "deviations of the reciprocal cell angles a*, b* and g* in degrees.\n" "The values are placed in the first row of the \"cell \" category. If \n" "no value has been given for \"_cell.entry_id \", it is set to the \n" "value of the \"diffrn.id \" entry of the current data block.\n" "cell or cell_esd may be NULL.\n" "If cell is NULL, the reciprocal cell parameters are not set.\n" "If cell_esd is NULL, the reciprocal cell parameter esds are not set.\n" "If the \"cell \" category is not present, it is created. If any of \n" "the necessary columns are not present, they are created.\n" "ARGUMENTS\n" "handle CBF handle. cell Pointer to the array of 6 doubles \n" "for the reciprocal cell parameters. cell_esd Pointer to the array \n" "of 6 doubles for the reciprocal cell parameter esds.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_real_3d_image_fs", _wrap_cbf_handle_struct_set_real_3d_image_fs, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : int element_number,int compression,(binary) String data,int elsize,\n" " int dimfast,int dimmid,int dimslow\n" "\n" "C prototype: int cbf_set_real_3d_image_fs(cbf_handle handle,\n" " unsigned int reserved, unsigned int element_number,\n" " unsigned int compression, void *array,size_t elsize,\n" " size_t ndimfast, size_t ndimmid, size_t ndimslow);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image \n" "array for element number element_number. The array consists of \n" "ndimfast *ndimslow elements of elsize bytes each, starting at array. \n" "The elements are signed if elsign is non-zero and unsigned otherwise. \n" "cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf \n" "write the image array for element number element_number. The array \n" "consists of ndimfast *ndimslow IEEE double or float elements of \n" "elsize bytes each, starting at array. cbf_set_3d_image, \n" "cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array \n" "for element number element_number. The array consists of ndimfast \n" "*ndimmid *ndimslow elements of elsize bytes each, starting at array. \n" "The elements are signed if elsign is non-0 and unsigned otherwise. \n" "cbf_set_real_3d_image, cbf_set_real_3d_image_fs and \n" "cbf_set_real_3d_image_sf writes the 3D image array for element number \n" "element_number. The array consists of ndimfast *ndimmid *ndimslow \n" "IEEE double or float elements of elsize bytes each, starting at \n" "array.\n" "The _fs calls give the dimensions in a fast-to-slow order. The calls \n" "with no suffix and the calls _sf calls give the dimensions in \n" "slow-to-fast order\n" "If the array is 1-dimensional, ndimslow should be the array size and \n" "ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the \n" "array is 2-dimensional and the 3D calls are used, ndimslow and \n" "ndimmid should be used for the array dimensions and ndimfast should \n" "be set to 1.\n" "The array will be compressed using the compression scheme specifed by \n" "compression. Currently, the available schemes are:\n" "CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED \n" " CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style \n" "packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \n" "\"byte_offset \" compression. CBF_NONE No compression.\n" "The values compressed are limited to 64 bits. If any element in the \n" "array is larger than 64 bits, the value compressed is the nearest \n" "64-bit value.\n" "Currently, the source array must consist of chars, shorts or ints \n" "(signed or unsigned)for cbf_set_image, or IEEE doubles or floats for \n" "cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof \n" "(int), sizeof(double) or sizeof(float), the function returns \n" "CBF_ARGUMENT.\n" "The parameter reserved is presently unused and should be set to 0.\n" "ARGUMENTS\n" "handle CBF handle. reserved Unused. Any value other \n" "than 0 is invalid. element_number The number of the detector \n" "element counting from 0 by order of appearance in the \n" "\"diffrn_data_frame \" category. compression Compression type. \n" "array Pointer to the image array. elsize Size in \n" "bytes of each image array element. elsigned Set to non-0 if \n" "the image array elements are signed. ndimslow Slowest array \n" "dimension. ndimmid Second slowest array dimension. ndimfast \n" " Fastest array dimension.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_set_doublevalue", _wrap_cbf_handle_struct_set_doublevalue, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : String format,Float number\n" "\n" "C prototype: int cbf_set_doublevalue (cbf_handle handle, const char *format,\n" " double number);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_doublevalue sets the item at the current column and row to \n" "the floating-point value number written as an ASCII string with the \n" "format specified by format as appropriate for the printf function.\n" "ARGUMENTS\n" "handle CBF handle. format Format for the number. number \n" "Floating-point value.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_find_category", _wrap_cbf_handle_struct_find_category, METH_VARARGS, (char *)"\n" "Returns : string\n" "*args : \n" "\n" "C prototype: int cbf_find_category (cbf_handle handle,\n" " const char *categoryname);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_find_category makes the category in the current data block with \n" "name categoryname the current category.\n" "The comparison is case-insensitive.\n" "If the category does not exist, the function returns CBF_NOTFOUND.\n" "The current column and row become undefined.\n" "ARGUMENTS\n" "handle CBF handle. categoryname The name of the category to \n" "find.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_get_integerarrayparameters_wdims_fs", _wrap_cbf_handle_struct_get_integerarrayparameters_wdims_fs, METH_VARARGS, (char *)"\n" "Returns : int compression,int binary_id,int elsize,int elsigned,int elunsigned,\n" " int elements,int minelement,int maxelement,char **bo,int *bolen,\n" " int dimfast,int dimmid,int dimslow,int padding\n" "*args : \n" "\n" "C prototype: int cbf_get_integerarrayparameters_wdims_fs (cbf_handle handle,\n" " unsigned int *compression, int *binary_id, size_t *elsize,\n" " int *elsigned, int *elunsigned, size_t *elements,\n" " int *minelement, int *maxelement, const char **byteorder,\n" " size_t *dimfast, size_t *dimmid, size_t *dimslow,\n" " size_t *padding);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_get_integerarrayparameters sets *compression, *binary_id, \n" "*elsize, *elsigned, *elunsigned, *elements, *minelement and \n" "*maxelement to values read from the binary value of the item at the \n" "current column and row. This provides all the arguments needed for a \n" "subsequent call to cbf_set_integerarray, if a copy of the array is to \n" "be made into another CIF or CBF. cbf_get_realarrayparameters sets \n" "*compression, *binary_id, *elsize, *elements to values read from the \n" "binary value of the item at the current column and row. This provides \n" "all the arguments needed for a subsequent call to cbf_set_realarray, \n" "if a copy of the arry is to be made into another CIF or CBF.\n" "The variants cbf_get_integerarrayparameters_wdims, \n" "cbf_get_integerarrayparameters_wdims_fs, \n" "cbf_get_integerarrayparameters_wdims_sf, \n" "cbf_get_realarrayparameters_wdims, \n" "cbf_get_realarrayparameters_wdims_fs, \n" "cbf_get_realarrayparameters_wdims_sf set **byteorder, *dimfast, \n" "*dimmid, *dimslow, and *padding as well, providing the additional \n" "parameters needed for a subsequent call to cbf_set_integerarray_wdims \n" "or cbf_set_realarray_wdims.\n" "The value returned in *byteorder is a pointer either to the string \n" "\"little_endian \" or to the string \"big_endian \". This should be \n" "the byte order of the data, not necessarily of the host machine. No \n" "attempt should be made to modify this string. At this time only \n" "\"little_endian \" will be returned.\n" "The values returned in *dimfast, *dimmid and *dimslow are the sizes \n" "of the fastest changing, second fastest changing and third fastest \n" "changing dimensions of the array, if specified, or zero, if not \n" "specified.\n" "The value returned in *padding is the size of the post-data padding, \n" "if any and if specified in the data header. The value is given as a \n" "count of octets.\n" "If the value is not binary, the function returns CBF_ASCII.\n" "ARGUMENTS\n" "handle CBF handle. compression Compression method used. \n" "elsize Size in bytes of each array element. binary_id \n" "Pointer to the destination integer binary identifier. elsigned \n" "Pointer to an integer. Set to 1 if the elements can be read as signed \n" "integers. elunsigned Pointer to an integer. Set to 1 if the \n" "elements can be read as unsigned integers. elements Pointer to \n" "the destination number of elements. minelement Pointer to the \n" "destination smallest element. maxelement Pointer to the \n" "destination largest element. byteorder Pointer to the destination \n" "byte order. dimfast Pointer to the destination fastest \n" "dimension. dimmid Pointer to the destination second fastest \n" "dimension. dimslow Pointer to the destination third fastest \n" "dimension. padding Pointer to the destination padding size.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_realarray_wdims_fs", _wrap_cbf_handle_struct_set_realarray_wdims_fs, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : int compression,int binary_id,(binary) String data,int elsize,\n" " int elements,String byteorder,int dimfast,int dimmid,int dimslow,\n" " int padding\n" "\n" "C prototype: int cbf_set_realarray_wdims_fs (cbf_handle handle,\n" " unsigned int compression, int binary_id, void *array,\n" " size_t elsize, size_t elements, const char *byteorder,\n" " size_t dimfast, size_t dimmid, size_t dimslow,\n" " size_t padding);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_integerarray sets the binary value of the item at the current \n" "column and row to an integer array. The array consists of elements \n" "elements of elsize bytes each, starting at array. The elements are \n" "signed if elsigned is non-0 and unsigned otherwise. binary_id is the \n" "binary section identifier. cbf_set_realarray sets the binary value of \n" "the item at the current column and row to an integer array. The array \n" "consists of elements elements of elsize bytes each, starting at \n" "array. binary_id is the binary section identifier.\n" "The cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, \n" "cbf_set_integerarray_wdims_sf, cbf_set_realarray_wdims, \n" "cbf_set_realarray_wdims_fs and cbf_set_realarray_wdims_sf variants \n" "allow the data header values of byteorder, dimfast, dimmid, dimslow \n" "and padding to be set to the data byte order, the fastest, second \n" "fastest and third fastest array dimensions and the size in byte of \n" "the post data padding to be used.\n" "The array will be compressed using the compression scheme specifed by \n" "compression. Currently, the available schemes are:\n" "CBF_CANONICAL Canonical-code compression (section 3.3.1) \n" "CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 \n" " CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET \n" "Simple \"byte_offset \" compression. CBF_NONE No \n" "compression. NOTE: This scheme is by far the slowest of the four and \n" "uses much more disk space. It is intended for routine use with small \n" "arrays only. With large arrays (like images) it should be used only \n" "for debugging.\n" "The values compressed are limited to 64 bits. If any element in the \n" "array is larger than 64 bits, the value compressed is the nearest \n" "64-bit value.\n" "Currently, the source array must consist of chars, shorts or ints \n" "(signed or unsigned), for cbf_set_integerarray, or IEEE doubles or \n" "floats for cbf_set_realarray. If elsize is not equal to sizeof \n" "(char), sizeof (short) or sizeof (int), the function returns \n" "CBF_ARGUMENT.\n" "ARGUMENTS\n" "handle CBF handle. compression Compression method to use. \n" "binary_id Integer binary identifier. array Pointer to the \n" "source array. elsize Size in bytes of each source array \n" "element. elsigned Set to non-0 if the source array elements are \n" "signed. elements: The number of elements in the array.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_find_category_root", _wrap_cbf_handle_struct_find_category_root, METH_VARARGS, (char *)"\n" "Returns : String categoryroot\n" "*args : String categoryname\n" "\n" "C prototype: int cbf_find_category_root (cbf_handle handle,\n" " const char* categoryname, const char** categoryroot);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_find_category_root sets *categoryroot to the root category of \n" "which categoryname is an alias. cbf_set_category_root sets \n" "categoryname_in as an alias of categoryroot in the dictionary \n" "associated with handle, creating the dictionary if necessary. \n" "cbf_require_category_root sets *categoryroot to the root category of \n" "which categoryname is an alias, if there is one, or to the value of \n" "categoryname, if categoryname is not an alias.\n" "A returned categoryroot string must not be modified in any way.\n" "ARGUMENTS\n" "handle CBF handle. categoryname category name which \n" "may be an alias. categoryroot pointer to a returned category \n" "root name. categoryroot_in input category root name.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_set_integerarray_wdims_fs", _wrap_cbf_handle_struct_set_integerarray_wdims_fs, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : int compression,int binary_id,(binary) String data,int elsize,\n" " int elements,String byteorder,int dimfast,int dimmid,int dimslow,\n" " int padding\n" "\n" "C prototype: int cbf_set_integerarray_wdims_fs (cbf_handle handle,\n" " unsigned int compression, int binary_id, void *array,\n" " size_t elsize, int elsigned, size_t elements,\n" " const char *byteorder, size_t dimfast, size_t dimmid,\n" " size_t dimslow, size_t padding);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_integerarray sets the binary value of the item at the current \n" "column and row to an integer array. The array consists of elements \n" "elements of elsize bytes each, starting at array. The elements are \n" "signed if elsigned is non-0 and unsigned otherwise. binary_id is the \n" "binary section identifier. cbf_set_realarray sets the binary value of \n" "the item at the current column and row to an integer array. The array \n" "consists of elements elements of elsize bytes each, starting at \n" "array. binary_id is the binary section identifier.\n" "The cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, \n" "cbf_set_integerarray_wdims_sf, cbf_set_realarray_wdims, \n" "cbf_set_realarray_wdims_fs and cbf_set_realarray_wdims_sf variants \n" "allow the data header values of byteorder, dimfast, dimmid, dimslow \n" "and padding to be set to the data byte order, the fastest, second \n" "fastest and third fastest array dimensions and the size in byte of \n" "the post data padding to be used.\n" "The array will be compressed using the compression scheme specifed by \n" "compression. Currently, the available schemes are:\n" "CBF_CANONICAL Canonical-code compression (section 3.3.1) \n" "CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 \n" " CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET \n" "Simple \"byte_offset \" compression. CBF_NONE No \n" "compression. NOTE: This scheme is by far the slowest of the four and \n" "uses much more disk space. It is intended for routine use with small \n" "arrays only. With large arrays (like images) it should be used only \n" "for debugging.\n" "The values compressed are limited to 64 bits. If any element in the \n" "array is larger than 64 bits, the value compressed is the nearest \n" "64-bit value.\n" "Currently, the source array must consist of chars, shorts or ints \n" "(signed or unsigned), for cbf_set_integerarray, or IEEE doubles or \n" "floats for cbf_set_realarray. If elsize is not equal to sizeof \n" "(char), sizeof (short) or sizeof (int), the function returns \n" "CBF_ARGUMENT.\n" "ARGUMENTS\n" "handle CBF handle. compression Compression method to use. \n" "binary_id Integer binary identifier. array Pointer to the \n" "source array. elsize Size in bytes of each source array \n" "element. elsigned Set to non-0 if the source array elements are \n" "signed. elements: The number of elements in the array.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_image_sf", _wrap_cbf_handle_struct_set_image_sf, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : int element_number,int compression,(binary) String data,int elsize,\n" " int elsign,int dimslow,int dimfast\n" "\n" "C prototype: int cbf_set_image_sf(cbf_handle handle, unsigned int reserved,\n" " unsigned int element_number, unsigned int compression,\n" " void *array, size_t elsize, int elsign, size_t ndimslow,\n" " size_t ndimfast);\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image \n" "array for element number element_number. The array consists of \n" "ndimfast *ndimslow elements of elsize bytes each, starting at array. \n" "The elements are signed if elsign is non-zero and unsigned otherwise. \n" "cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf \n" "write the image array for element number element_number. The array \n" "consists of ndimfast *ndimslow IEEE double or float elements of \n" "elsize bytes each, starting at array. cbf_set_3d_image, \n" "cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array \n" "for element number element_number. The array consists of ndimfast \n" "*ndimmid *ndimslow elements of elsize bytes each, starting at array. \n" "The elements are signed if elsign is non-0 and unsigned otherwise. \n" "cbf_set_real_3d_image, cbf_set_real_3d_image_fs and \n" "cbf_set_real_3d_image_sf writes the 3D image array for element number \n" "element_number. The array consists of ndimfast *ndimmid *ndimslow \n" "IEEE double or float elements of elsize bytes each, starting at \n" "array.\n" "The _fs calls give the dimensions in a fast-to-slow order. The calls \n" "with no suffix and the calls _sf calls give the dimensions in \n" "slow-to-fast order\n" "If the array is 1-dimensional, ndimslow should be the array size and \n" "ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the \n" "array is 2-dimensional and the 3D calls are used, ndimslow and \n" "ndimmid should be used for the array dimensions and ndimfast should \n" "be set to 1.\n" "The array will be compressed using the compression scheme specifed by \n" "compression. Currently, the available schemes are:\n" "CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED \n" " CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style \n" "packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple \n" "\"byte_offset \" compression. CBF_NONE No compression.\n" "The values compressed are limited to 64 bits. If any element in the \n" "array is larger than 64 bits, the value compressed is the nearest \n" "64-bit value.\n" "Currently, the source array must consist of chars, shorts or ints \n" "(signed or unsigned)for cbf_set_image, or IEEE doubles or floats for \n" "cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof \n" "(int), sizeof(double) or sizeof(float), the function returns \n" "CBF_ARGUMENT.\n" "The parameter reserved is presently unused and should be set to 0.\n" "ARGUMENTS\n" "handle CBF handle. reserved Unused. Any value other \n" "than 0 is invalid. element_number The number of the detector \n" "element counting from 0 by order of appearance in the \n" "\"diffrn_data_frame \" category. compression Compression type. \n" "array Pointer to the image array. elsize Size in \n" "bytes of each image array element. elsigned Set to non-0 if \n" "the image array elements are signed. ndimslow Slowest array \n" "dimension. ndimmid Second slowest array dimension. ndimfast \n" " Fastest array dimension.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "----------------------------------------------------------------------\n" "\n" ""}, { (char *)"cbf_handle_struct_set_unit_cell", _wrap_cbf_handle_struct_set_unit_cell, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : double cell[6]\n" "\n" "C prototype: int cbf_set_unit_cell (cbf_handle handle, double cell[6],\n" " double cell_esd[6] );\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_unit_cell sets the cell parameters to the double values given \n" "in cell[0:2] for the cell edge lengths a, b and c in AAngstroms, the \n" "double values given in cell[3:5] for the cell angles a, b and g in \n" "degrees, the double values given in cell_esd[0:2] for the estimated \n" "strandard deviations of the cell edge lengths a, b and c in \n" "AAngstroms, and the double values given in cell_esd[3:5] for the \n" "estimated standard deviations of the the cell angles a, b and g in \n" "degrees.\n" "The values are placed in the first row of the \"cell \" category. If \n" "no value has been given for \"_cell.entry_id \", it is set to the \n" "value of the \"diffrn.id \" entry of the current data block.\n" "cell or cell_esd may be NULL.\n" "If cell is NULL, the cell parameters are not set.\n" "If cell_esd is NULL, the cell parameter esds are not set.\n" "If the \"cell \" category is not present, it is created. If any of \n" "the necessary columns are not present, they are created.\n" "ARGUMENTS\n" "handle CBF handle. cell Pointer to the array of 6 doubles \n" "for the cell parameters. cell_esd Pointer to the array of 6 doubles \n" "for the cell parameter esds.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_set_unit_cell_esd", _wrap_cbf_handle_struct_set_unit_cell_esd, METH_VARARGS, (char *)"\n" "Returns : \n" "*args : double cell_esd[6]\n" "\n" "C prototype: int cbf_set_unit_cell (cbf_handle handle, double cell[6],\n" " double cell_esd[6] );\n" "\n" "CBFLib documentation:\n" "DESCRIPTION\n" "cbf_set_unit_cell sets the cell parameters to the double values given \n" "in cell[0:2] for the cell edge lengths a, b and c in AAngstroms, the \n" "double values given in cell[3:5] for the cell angles a, b and g in \n" "degrees, the double values given in cell_esd[0:2] for the estimated \n" "strandard deviations of the cell edge lengths a, b and c in \n" "AAngstroms, and the double values given in cell_esd[3:5] for the \n" "estimated standard deviations of the the cell angles a, b and g in \n" "degrees.\n" "The values are placed in the first row of the \"cell \" category. If \n" "no value has been given for \"_cell.entry_id \", it is set to the \n" "value of the \"diffrn.id \" entry of the current data block.\n" "cell or cell_esd may be NULL.\n" "If cell is NULL, the cell parameters are not set.\n" "If cell_esd is NULL, the cell parameter esds are not set.\n" "If the \"cell \" category is not present, it is created. If any of \n" "the necessary columns are not present, they are created.\n" "ARGUMENTS\n" "handle CBF handle. cell Pointer to the array of 6 doubles \n" "for the cell parameters. cell_esd Pointer to the array of 6 doubles \n" "for the cell parameter esds.\n" "RETURN VALUE\n" "Returns an error code on failure or 0 for success.\n" "SEE ALSO\n" "\n" ""}, { (char *)"cbf_handle_struct_swigregister", cbf_handle_struct_swigregister, METH_VARARGS, NULL}, { NULL, NULL, 0, NULL } }; /* -------- TYPE CONVERSION AND EQUIVALENCE RULES (BEGIN) -------- */ static void *_p_shortArrayTo_p_short(void *x, int *SWIGUNUSEDPARM(newmemory)) { return (void *)((short *) ((shortArray *) x)); } static void *_p_longArrayTo_p_long(void *x, int *SWIGUNUSEDPARM(newmemory)) { return (void *)((long *) ((longArray *) x)); } static void *_p_intArrayTo_p_int(void *x, int *SWIGUNUSEDPARM(newmemory)) { return (void *)((int *) ((intArray *) x)); } static void *_p_a_4__doubleArrayTo_p_a_4__double(void *x, int *SWIGUNUSEDPARM(newmemory)) { return (void *)((double (*)[4]) ((doubleArray (*)[4]) x)); } static void *_p_doubleArrayTo_p_double(void *x, int *SWIGUNUSEDPARM(newmemory)) { return (void *)((double *) ((doubleArray *) x)); } static swig_type_info _swigt__p_CBF_NODETYPE = {"_p_CBF_NODETYPE", "enum CBF_NODETYPE *|CBF_NODETYPE *", 0, 0, (void*)0, 0}; static swig_type_info _swigt__p_a_4__double = {"_p_a_4__double", "double (*)[4]", 0, 0, (void*)0, 0}; static swig_type_info _swigt__p_a_4__doubleArray = {"_p_a_4__doubleArray", 0, 0, 0, 0, 0}; static swig_type_info _swigt__p_cbf_axis_struct = {"_p_cbf_axis_struct", "cbf_axis_struct *", 0, 0, (void*)0, 0}; static swig_type_info _swigt__p_cbf_detector_struct = {"_p_cbf_detector_struct", "cbf_detector|cbf_detector_struct *", 0, 0, (void*)0, 0}; static swig_type_info _swigt__p_cbf_handle_struct = {"_p_cbf_handle_struct", "cbf_handle|cbf_handle_struct *|handle *", 0, 0, (void*)0, 0}; static swig_type_info _swigt__p_cbf_node = {"_p_cbf_node", "cbf_node *", 0, 0, (void*)0, 0}; static swig_type_info _swigt__p_cbf_positioner = {"_p_cbf_positioner", "cbf_positioner *", 0, 0, (void*)0, 0}; static swig_type_info _swigt__p_cbf_positioner_struct = {"_p_cbf_positioner_struct", "cbf_goniometer|cbf_positioner_struct *", 0, 0, (void*)0, 0}; static swig_type_info _swigt__p_char = {"_p_char", "char *", 0, 0, (void*)0, 0}; static swig_type_info _swigt__p_double = {"_p_double", "double *", 0, 0, (void*)0, 0}; static swig_type_info _swigt__p_doubleArray = {"_p_doubleArray", "struct doubleArray *|doubleArray *", 0, 0, (void*)0, 0}; static swig_type_info _swigt__p_int = {"_p_int", "int *", 0, 0, (void*)0, 0}; static swig_type_info _swigt__p_intArray = {"_p_intArray", "struct intArray *|intArray *", 0, 0, (void*)0, 0}; static swig_type_info _swigt__p_long = {"_p_long", "long *", 0, 0, (void*)0, 0}; static swig_type_info _swigt__p_longArray = {"_p_longArray", "struct longArray *|longArray *", 0, 0, (void*)0, 0}; static swig_type_info _swigt__p_p_char = {"_p_p_char", "char **", 0, 0, (void*)0, 0}; static swig_type_info _swigt__p_short = {"_p_short", "short *", 0, 0, (void*)0, 0}; static swig_type_info _swigt__p_shortArray = {"_p_shortArray", "struct shortArray *|shortArray *", 0, 0, (void*)0, 0}; static swig_type_info _swigt__p_size_t = {"_p_size_t", "size_t *", 0, 0, (void*)0, 0}; static swig_type_info _swigt__p_void = {"_p_void", "void *", 0, 0, (void*)0, 0}; static swig_type_info *swig_type_initial[] = { &_swigt__p_CBF_NODETYPE, &_swigt__p_a_4__double, &_swigt__p_a_4__doubleArray, &_swigt__p_cbf_axis_struct, &_swigt__p_cbf_detector_struct, &_swigt__p_cbf_handle_struct, &_swigt__p_cbf_node, &_swigt__p_cbf_positioner, &_swigt__p_cbf_positioner_struct, &_swigt__p_char, &_swigt__p_double, &_swigt__p_doubleArray, &_swigt__p_int, &_swigt__p_intArray, &_swigt__p_long, &_swigt__p_longArray, &_swigt__p_p_char, &_swigt__p_short, &_swigt__p_shortArray, &_swigt__p_size_t, &_swigt__p_void, }; static swig_cast_info _swigc__p_CBF_NODETYPE[] = { {&_swigt__p_CBF_NODETYPE, 0, 0, 0},{0, 0, 0, 0}}; static swig_cast_info _swigc__p_a_4__doubleArray[] = {{&_swigt__p_a_4__doubleArray, 0, 0, 0},{0, 0, 0, 0}}; static swig_cast_info _swigc__p_a_4__double[] = { {&_swigt__p_a_4__doubleArray, _p_a_4__doubleArrayTo_p_a_4__double, 0, 0}, {&_swigt__p_a_4__double, 0, 0, 0},{0, 0, 0, 0}}; static swig_cast_info _swigc__p_cbf_axis_struct[] = { {&_swigt__p_cbf_axis_struct, 0, 0, 0},{0, 0, 0, 0}}; static swig_cast_info _swigc__p_cbf_detector_struct[] = { {&_swigt__p_cbf_detector_struct, 0, 0, 0},{0, 0, 0, 0}}; static swig_cast_info _swigc__p_cbf_handle_struct[] = { {&_swigt__p_cbf_handle_struct, 0, 0, 0},{0, 0, 0, 0}}; static swig_cast_info _swigc__p_cbf_node[] = { {&_swigt__p_cbf_node, 0, 0, 0},{0, 0, 0, 0}}; static swig_cast_info _swigc__p_cbf_positioner[] = { {&_swigt__p_cbf_positioner, 0, 0, 0},{0, 0, 0, 0}}; static swig_cast_info _swigc__p_cbf_positioner_struct[] = { {&_swigt__p_cbf_positioner_struct, 0, 0, 0},{0, 0, 0, 0}}; static swig_cast_info _swigc__p_char[] = { {&_swigt__p_char, 0, 0, 0},{0, 0, 0, 0}}; static swig_cast_info _swigc__p_double[] = { {&_swigt__p_doubleArray, _p_doubleArrayTo_p_double, 0, 0}, {&_swigt__p_double, 0, 0, 0},{0, 0, 0, 0}}; static swig_cast_info _swigc__p_doubleArray[] = { {&_swigt__p_doubleArray, 0, 0, 0},{0, 0, 0, 0}}; static swig_cast_info _swigc__p_int[] = { {&_swigt__p_intArray, _p_intArrayTo_p_int, 0, 0}, {&_swigt__p_int, 0, 0, 0},{0, 0, 0, 0}}; static swig_cast_info _swigc__p_intArray[] = { {&_swigt__p_intArray, 0, 0, 0},{0, 0, 0, 0}}; static swig_cast_info _swigc__p_long[] = { {&_swigt__p_long, 0, 0, 0}, {&_swigt__p_longArray, _p_longArrayTo_p_long, 0, 0},{0, 0, 0, 0}}; static swig_cast_info _swigc__p_longArray[] = { {&_swigt__p_longArray, 0, 0, 0},{0, 0, 0, 0}}; static swig_cast_info _swigc__p_p_char[] = { {&_swigt__p_p_char, 0, 0, 0},{0, 0, 0, 0}}; static swig_cast_info _swigc__p_short[] = { {&_swigt__p_shortArray, _p_shortArrayTo_p_short, 0, 0}, {&_swigt__p_short, 0, 0, 0},{0, 0, 0, 0}}; static swig_cast_info _swigc__p_shortArray[] = { {&_swigt__p_shortArray, 0, 0, 0},{0, 0, 0, 0}}; static swig_cast_info _swigc__p_size_t[] = { {&_swigt__p_size_t, 0, 0, 0},{0, 0, 0, 0}}; static swig_cast_info _swigc__p_void[] = { {&_swigt__p_void, 0, 0, 0},{0, 0, 0, 0}}; static swig_cast_info *swig_cast_initial[] = { _swigc__p_CBF_NODETYPE, _swigc__p_a_4__double, _swigc__p_a_4__doubleArray, _swigc__p_cbf_axis_struct, _swigc__p_cbf_detector_struct, _swigc__p_cbf_handle_struct, _swigc__p_cbf_node, _swigc__p_cbf_positioner, _swigc__p_cbf_positioner_struct, _swigc__p_char, _swigc__p_double, _swigc__p_doubleArray, _swigc__p_int, _swigc__p_intArray, _swigc__p_long, _swigc__p_longArray, _swigc__p_p_char, _swigc__p_short, _swigc__p_shortArray, _swigc__p_size_t, _swigc__p_void, }; /* -------- TYPE CONVERSION AND EQUIVALENCE RULES (END) -------- */ static swig_const_info swig_const_table[] = { {0, 0, 0, 0.0, 0, 0}}; #ifdef __cplusplus } #endif /* ----------------------------------------------------------------------------- * Type initialization: * This problem is tough by the requirement that no dynamic * memory is used. Also, since swig_type_info structures store pointers to * swig_cast_info structures and swig_cast_info structures store pointers back * to swig_type_info structures, we need some lookup code at initialization. * The idea is that swig generates all the structures that are needed. * The runtime then collects these partially filled structures. * The SWIG_InitializeModule function takes these initial arrays out of * swig_module, and does all the lookup, filling in the swig_module.types * array with the correct data and linking the correct swig_cast_info * structures together. * * The generated swig_type_info structures are assigned staticly to an initial * array. We just loop through that array, and handle each type individually. * First we lookup if this type has been already loaded, and if so, use the * loaded structure instead of the generated one. Then we have to fill in the * cast linked list. The cast data is initially stored in something like a * two-dimensional array. Each row corresponds to a type (there are the same * number of rows as there are in the swig_type_initial array). Each entry in * a column is one of the swig_cast_info structures for that type. * The cast_initial array is actually an array of arrays, because each row has * a variable number of columns. So to actually build the cast linked list, * we find the array of casts associated with the type, and loop through it * adding the casts to the list. The one last trick we need to do is making * sure the type pointer in the swig_cast_info struct is correct. * * First off, we lookup the cast->type name to see if it is already loaded. * There are three cases to handle: * 1) If the cast->type has already been loaded AND the type we are adding * casting info to has not been loaded (it is in this module), THEN we * replace the cast->type pointer with the type pointer that has already * been loaded. * 2) If BOTH types (the one we are adding casting info to, and the * cast->type) are loaded, THEN the cast info has already been loaded by * the previous module so we just ignore it. * 3) Finally, if cast->type has not already been loaded, then we add that * swig_cast_info to the linked list (because the cast->type) pointer will * be correct. * ----------------------------------------------------------------------------- */ #ifdef __cplusplus extern "C" { #if 0 } /* c-mode */ #endif #endif #if 0 #define SWIGRUNTIME_DEBUG #endif SWIGRUNTIME void SWIG_InitializeModule(void *clientdata) { size_t i; swig_module_info *module_head, *iter; int found, init; clientdata = clientdata; /* check to see if the circular list has been setup, if not, set it up */ if (swig_module.next==0) { /* Initialize the swig_module */ swig_module.type_initial = swig_type_initial; swig_module.cast_initial = swig_cast_initial; swig_module.next = &swig_module; init = 1; } else { init = 0; } /* Try and load any already created modules */ module_head = SWIG_GetModule(clientdata); if (!module_head) { /* This is the first module loaded for this interpreter */ /* so set the swig module into the interpreter */ SWIG_SetModule(clientdata, &swig_module); module_head = &swig_module; } else { /* the interpreter has loaded a SWIG module, but has it loaded this one? */ found=0; iter=module_head; do { if (iter==&swig_module) { found=1; break; } iter=iter->next; } while (iter!= module_head); /* if the is found in the list, then all is done and we may leave */ if (found) return; /* otherwise we must add out module into the list */ swig_module.next = module_head->next; module_head->next = &swig_module; } /* When multiple interpeters are used, a module could have already been initialized in a different interpreter, but not yet have a pointer in this interpreter. In this case, we do not want to continue adding types... everything should be set up already */ if (init == 0) return; /* Now work on filling in swig_module.types */ #ifdef SWIGRUNTIME_DEBUG printf("SWIG_InitializeModule: size %d\n", swig_module.size); #endif for (i = 0; i < swig_module.size; ++i) { swig_type_info *type = 0; swig_type_info *ret; swig_cast_info *cast; #ifdef SWIGRUNTIME_DEBUG printf("SWIG_InitializeModule: type %d %s\n", i, swig_module.type_initial[i]->name); #endif /* if there is another module already loaded */ if (swig_module.next != &swig_module) { type = SWIG_MangledTypeQueryModule(swig_module.next, &swig_module, swig_module.type_initial[i]->name); } if (type) { /* Overwrite clientdata field */ #ifdef SWIGRUNTIME_DEBUG printf("SWIG_InitializeModule: found type %s\n", type->name); #endif if (swig_module.type_initial[i]->clientdata) { type->clientdata = swig_module.type_initial[i]->clientdata; #ifdef SWIGRUNTIME_DEBUG printf("SWIG_InitializeModule: found and overwrite type %s \n", type->name); #endif } } else { type = swig_module.type_initial[i]; } /* Insert casting types */ cast = swig_module.cast_initial[i]; while (cast->type) { /* Don't need to add information already in the list */ ret = 0; #ifdef SWIGRUNTIME_DEBUG printf("SWIG_InitializeModule: look cast %s\n", cast->type->name); #endif if (swig_module.next != &swig_module) { ret = SWIG_MangledTypeQueryModule(swig_module.next, &swig_module, cast->type->name); #ifdef SWIGRUNTIME_DEBUG if (ret) printf("SWIG_InitializeModule: found cast %s\n", ret->name); #endif } if (ret) { if (type == swig_module.type_initial[i]) { #ifdef SWIGRUNTIME_DEBUG printf("SWIG_InitializeModule: skip old type %s\n", ret->name); #endif cast->type = ret; ret = 0; } else { /* Check for casting already in the list */ swig_cast_info *ocast = SWIG_TypeCheck(ret->name, type); #ifdef SWIGRUNTIME_DEBUG if (ocast) printf("SWIG_InitializeModule: skip old cast %s\n", ret->name); #endif if (!ocast) ret = 0; } } if (!ret) { #ifdef SWIGRUNTIME_DEBUG printf("SWIG_InitializeModule: adding cast %s\n", cast->type->name); #endif if (type->cast) { type->cast->prev = cast; cast->next = type->cast; } type->cast = cast; } cast++; } /* Set entry in modules->types array equal to the type */ swig_module.types[i] = type; } swig_module.types[i] = 0; #ifdef SWIGRUNTIME_DEBUG printf("**** SWIG_InitializeModule: Cast List ******\n"); for (i = 0; i < swig_module.size; ++i) { int j = 0; swig_cast_info *cast = swig_module.cast_initial[i]; printf("SWIG_InitializeModule: type %d %s\n", i, swig_module.type_initial[i]->name); while (cast->type) { printf("SWIG_InitializeModule: cast type %s\n", cast->type->name); cast++; ++j; } printf("---- Total casts: %d\n",j); } printf("**** SWIG_InitializeModule: Cast List ******\n"); #endif } /* This function will propagate the clientdata field of type to * any new swig_type_info structures that have been added into the list * of equivalent types. It is like calling * SWIG_TypeClientData(type, clientdata) a second time. */ SWIGRUNTIME void SWIG_PropagateClientData(void) { size_t i; swig_cast_info *equiv; static int init_run = 0; if (init_run) return; init_run = 1; for (i = 0; i < swig_module.size; i++) { if (swig_module.types[i]->clientdata) { equiv = swig_module.types[i]->cast; while (equiv) { if (!equiv->converter) { if (equiv->type && !equiv->type->clientdata) SWIG_TypeClientData(equiv->type, swig_module.types[i]->clientdata); } equiv = equiv->next; } } } } #ifdef __cplusplus #if 0 { /* c-mode */ #endif } #endif #ifdef __cplusplus extern "C" { #endif /* Python-specific SWIG API */ #define SWIG_newvarlink() SWIG_Python_newvarlink() #define SWIG_addvarlink(p, name, get_attr, set_attr) SWIG_Python_addvarlink(p, name, get_attr, set_attr) #define SWIG_InstallConstants(d, constants) SWIG_Python_InstallConstants(d, constants) /* ----------------------------------------------------------------------------- * global variable support code. * ----------------------------------------------------------------------------- */ typedef struct swig_globalvar { char *name; /* Name of global variable */ PyObject *(*get_attr)(void); /* Return the current value */ int (*set_attr)(PyObject *); /* Set the value */ struct swig_globalvar *next; } swig_globalvar; typedef struct swig_varlinkobject { PyObject_HEAD swig_globalvar *vars; } swig_varlinkobject; SWIGINTERN PyObject * swig_varlink_repr(swig_varlinkobject *SWIGUNUSEDPARM(v)) { #if PY_VERSION_HEX >= 0x03000000 return PyUnicode_InternFromString(""); #else return PyString_FromString(""); #endif } SWIGINTERN PyObject * swig_varlink_str(swig_varlinkobject *v) { #if PY_VERSION_HEX >= 0x03000000 PyObject *str = PyUnicode_InternFromString("("); PyObject *tail; PyObject *joined; swig_globalvar *var; for (var = v->vars; var; var=var->next) { tail = PyUnicode_FromString(var->name); joined = PyUnicode_Concat(str, tail); Py_DecRef(str); Py_DecRef(tail); str = joined; if (var->next) { tail = PyUnicode_InternFromString(", "); joined = PyUnicode_Concat(str, tail); Py_DecRef(str); Py_DecRef(tail); str = joined; } } tail = PyUnicode_InternFromString(")"); joined = PyUnicode_Concat(str, tail); Py_DecRef(str); Py_DecRef(tail); str = joined; #else PyObject *str = PyString_FromString("("); swig_globalvar *var; for (var = v->vars; var; var=var->next) { PyString_ConcatAndDel(&str,PyString_FromString(var->name)); if (var->next) PyString_ConcatAndDel(&str,PyString_FromString(", ")); } PyString_ConcatAndDel(&str,PyString_FromString(")")); #endif return str; } SWIGINTERN int swig_varlink_print(swig_varlinkobject *v, FILE *fp, int SWIGUNUSEDPARM(flags)) { char *tmp; PyObject *str = swig_varlink_str(v); fprintf(fp,"Swig global variables "); fprintf(fp,"%s\n", tmp = SWIG_Python_str_AsChar(str)); SWIG_Python_str_DelForPy3(tmp); Py_DECREF(str); return 0; } SWIGINTERN void swig_varlink_dealloc(swig_varlinkobject *v) { swig_globalvar *var = v->vars; while (var) { swig_globalvar *n = var->next; free(var->name); free(var); var = n; } } SWIGINTERN PyObject * swig_varlink_getattr(swig_varlinkobject *v, char *n) { PyObject *res = NULL; swig_globalvar *var = v->vars; while (var) { if (strcmp(var->name,n) == 0) { res = (*var->get_attr)(); break; } var = var->next; } if (res == NULL && !PyErr_Occurred()) { PyErr_SetString(PyExc_NameError,"Unknown C global variable"); } return res; } SWIGINTERN int swig_varlink_setattr(swig_varlinkobject *v, char *n, PyObject *p) { int res = 1; swig_globalvar *var = v->vars; while (var) { if (strcmp(var->name,n) == 0) { res = (*var->set_attr)(p); break; } var = var->next; } if (res == 1 && !PyErr_Occurred()) { PyErr_SetString(PyExc_NameError,"Unknown C global variable"); } return res; } SWIGINTERN PyTypeObject* swig_varlink_type(void) { static char varlink__doc__[] = "Swig var link object"; static PyTypeObject varlink_type; static int type_init = 0; if (!type_init) { const PyTypeObject tmp = { /* PyObject header changed in Python 3 */ #if PY_VERSION_HEX >= 0x03000000 PyVarObject_HEAD_INIT(&PyType_Type, 0) #else PyObject_HEAD_INIT(NULL) 0, /* Number of items in variable part (ob_size) */ #endif (char *)"swigvarlink", /* Type name (tp_name) */ sizeof(swig_varlinkobject), /* Basic size (tp_basicsize) */ 0, /* Itemsize (tp_itemsize) */ (destructor) swig_varlink_dealloc, /* Deallocator (tp_dealloc) */ (printfunc) swig_varlink_print, /* Print (tp_print) */ (getattrfunc) swig_varlink_getattr, /* get attr (tp_getattr) */ (setattrfunc) swig_varlink_setattr, /* Set attr (tp_setattr) */ 0, /* tp_compare */ (reprfunc) swig_varlink_repr, /* tp_repr */ 0, /* tp_as_number */ 0, /* tp_as_sequence */ 0, /* tp_as_mapping */ 0, /* tp_hash */ 0, /* tp_call */ (reprfunc) swig_varlink_str, /* tp_str */ 0, /* tp_getattro */ 0, /* tp_setattro */ 0, /* tp_as_buffer */ 0, /* tp_flags */ varlink__doc__, /* tp_doc */ 0, /* tp_traverse */ 0, /* tp_clear */ 0, /* tp_richcompare */ 0, /* tp_weaklistoffset */ #if PY_VERSION_HEX >= 0x02020000 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, /* tp_iter -> tp_weaklist */ #endif #if PY_VERSION_HEX >= 0x02030000 0, /* tp_del */ #endif #ifdef COUNT_ALLOCS 0,0,0,0 /* tp_alloc -> tp_next */ #endif }; varlink_type = tmp; /* for Python 3 we already assigned ob_type in PyVarObject_HEAD_INIT() */ #if PY_VERSION_HEX < 0x03000000 varlink_type.ob_type = &PyType_Type; #endif type_init = 1; } return &varlink_type; } /* Create a variable linking object for use later */ SWIGINTERN PyObject * SWIG_Python_newvarlink(void) { swig_varlinkobject *result = PyObject_NEW(swig_varlinkobject, swig_varlink_type()); if (result) { result->vars = 0; } return ((PyObject*) result); } SWIGINTERN void SWIG_Python_addvarlink(PyObject *p, char *name, PyObject *(*get_attr)(void), int (*set_attr)(PyObject *p)) { swig_varlinkobject *v = (swig_varlinkobject *) p; swig_globalvar *gv = (swig_globalvar *) malloc(sizeof(swig_globalvar)); if (gv) { size_t size = strlen(name)+1; gv->name = (char *)malloc(size); if (gv->name) { strncpy(gv->name,name,size); gv->get_attr = get_attr; gv->set_attr = set_attr; gv->next = v->vars; } } v->vars = gv; } SWIGINTERN PyObject * SWIG_globals(void) { static PyObject *_SWIG_globals = 0; if (!_SWIG_globals) _SWIG_globals = SWIG_newvarlink(); return _SWIG_globals; } /* ----------------------------------------------------------------------------- * constants/methods manipulation * ----------------------------------------------------------------------------- */ /* Install Constants */ SWIGINTERN void SWIG_Python_InstallConstants(PyObject *d, swig_const_info constants[]) { PyObject *obj = 0; size_t i; for (i = 0; constants[i].type; ++i) { switch(constants[i].type) { case SWIG_PY_POINTER: obj = SWIG_NewPointerObj(constants[i].pvalue, *(constants[i]).ptype,0); break; case SWIG_PY_BINARY: obj = SWIG_NewPackedObj(constants[i].pvalue, constants[i].lvalue, *(constants[i].ptype)); break; default: obj = 0; break; } if (obj) { PyDict_SetItemString(d, constants[i].name, obj); Py_DECREF(obj); } } } /* -----------------------------------------------------------------------------*/ /* Fix SwigMethods to carry the callback ptrs when needed */ /* -----------------------------------------------------------------------------*/ SWIGINTERN void SWIG_Python_FixMethods(PyMethodDef *methods, swig_const_info *const_table, swig_type_info **types, swig_type_info **types_initial) { size_t i; for (i = 0; methods[i].ml_name; ++i) { const char *c = methods[i].ml_doc; if (c && (c = strstr(c, "swig_ptr: "))) { int j; swig_const_info *ci = 0; const char *name = c + 10; for (j = 0; const_table[j].type; ++j) { if (strncmp(const_table[j].name, name, strlen(const_table[j].name)) == 0) { ci = &(const_table[j]); break; } } if (ci) { size_t shift = (ci->ptype) - types; swig_type_info *ty = types_initial[shift]; size_t ldoc = (c - methods[i].ml_doc); size_t lptr = strlen(ty->name)+2*sizeof(void*)+2; char *ndoc = (char*)malloc(ldoc + lptr + 10); if (ndoc) { char *buff = ndoc; void *ptr = (ci->type == SWIG_PY_POINTER) ? ci->pvalue : 0; if (ptr) { strncpy(buff, methods[i].ml_doc, ldoc); buff += ldoc; strncpy(buff, "swig_ptr: ", 10); buff += 10; SWIG_PackVoidPtr(buff, ptr, ty->name, lptr); methods[i].ml_doc = ndoc; } } } } } } #ifdef __cplusplus } #endif /* -----------------------------------------------------------------------------* * Partial Init method * -----------------------------------------------------------------------------*/ #ifdef __cplusplus extern "C" #endif SWIGEXPORT #if PY_VERSION_HEX >= 0x03000000 PyObject* #else void #endif SWIG_init(void) { PyObject *m, *d; #if PY_VERSION_HEX >= 0x03000000 static struct PyModuleDef SWIG_module = { PyModuleDef_HEAD_INIT, (char *) SWIG_name, NULL, -1, SwigMethods, NULL, NULL, NULL, NULL }; #endif /* Fix SwigMethods to carry the callback ptrs when needed */ SWIG_Python_FixMethods(SwigMethods, swig_const_table, swig_types, swig_type_initial); #if PY_VERSION_HEX >= 0x03000000 m = PyModule_Create(&SWIG_module); #else m = Py_InitModule((char *) SWIG_name, SwigMethods); #endif d = PyModule_GetDict(m); SWIG_InitializeModule(0); SWIG_InstallConstants(d,swig_const_table); SWIG_Python_SetConstant(d, "CBF_INTEGER",SWIG_From_int((int)(0x0010))); SWIG_Python_SetConstant(d, "CBF_FLOAT",SWIG_From_int((int)(0x0020))); SWIG_Python_SetConstant(d, "CBF_CANONICAL",SWIG_From_int((int)(0x0050))); SWIG_Python_SetConstant(d, "CBF_PACKED",SWIG_From_int((int)(0x0060))); SWIG_Python_SetConstant(d, "CBF_PACKED_V2",SWIG_From_int((int)(0x0090))); SWIG_Python_SetConstant(d, "CBF_BYTE_OFFSET",SWIG_From_int((int)(0x0070))); SWIG_Python_SetConstant(d, "CBF_PREDICTOR",SWIG_From_int((int)(0x0080))); SWIG_Python_SetConstant(d, "CBF_NONE",SWIG_From_int((int)(0x0040))); SWIG_Python_SetConstant(d, "CBF_COMPRESSION_MASK",SWIG_From_int((int)(0x00FF))); SWIG_Python_SetConstant(d, "CBF_FLAG_MASK",SWIG_From_int((int)(0x0F00))); SWIG_Python_SetConstant(d, "CBF_UNCORRELATED_SECTIONS",SWIG_From_int((int)(0x0100))); SWIG_Python_SetConstant(d, "CBF_FLAT_IMAGE",SWIG_From_int((int)(0x0200))); SWIG_Python_SetConstant(d, "CBF_NO_EXPAND",SWIG_From_int((int)(0x0400))); SWIG_Python_SetConstant(d, "PLAIN_HEADERS",SWIG_From_int((int)(0x0001))); SWIG_Python_SetConstant(d, "MIME_HEADERS",SWIG_From_int((int)(0x0002))); SWIG_Python_SetConstant(d, "MSG_NODIGEST",SWIG_From_int((int)(0x0004))); SWIG_Python_SetConstant(d, "MSG_DIGEST",SWIG_From_int((int)(0x0008))); SWIG_Python_SetConstant(d, "MSG_DIGESTNOW",SWIG_From_int((int)(0x0010))); SWIG_Python_SetConstant(d, "MSG_DIGESTWARN",SWIG_From_int((int)(0x0020))); SWIG_Python_SetConstant(d, "PAD_1K",SWIG_From_int((int)(0x0020))); SWIG_Python_SetConstant(d, "PAD_2K",SWIG_From_int((int)(0x0040))); SWIG_Python_SetConstant(d, "PAD_4K",SWIG_From_int((int)(0x0080))); SWIG_Python_SetConstant(d, "CBF_PARSE_BRC",SWIG_From_int((int)(0x0100))); SWIG_Python_SetConstant(d, "CBF_PARSE_PRN",SWIG_From_int((int)(0x0200))); SWIG_Python_SetConstant(d, "CBF_PARSE_BKT",SWIG_From_int((int)(0x0400))); SWIG_Python_SetConstant(d, "CBF_PARSE_BRACKETS",SWIG_From_int((int)(0x0700))); SWIG_Python_SetConstant(d, "CBF_PARSE_TQ",SWIG_From_int((int)(0x0800))); SWIG_Python_SetConstant(d, "CBF_PARSE_CIF2_DELIMS",SWIG_From_int((int)(0x1000))); SWIG_Python_SetConstant(d, "CBF_PARSE_DDLm",SWIG_From_int((int)(0x0700))); SWIG_Python_SetConstant(d, "CBF_PARSE_CIF2",SWIG_From_int((int)(0x1F00))); SWIG_Python_SetConstant(d, "CBF_PARSE_DEFINES",SWIG_From_int((int)(0x2000))); SWIG_Python_SetConstant(d, "CBF_PARSE_WIDE",SWIG_From_int((int)(0x4000))); SWIG_Python_SetConstant(d, "CBF_PARSE_UTF8",SWIG_From_int((int)(0x10000))); SWIG_Python_SetConstant(d, "HDR_DEFAULT",SWIG_From_int((int)((0x0002|0x0004)))); SWIG_Python_SetConstant(d, "MIME_NOHEADERS",SWIG_From_int((int)(0x0001))); SWIG_Python_SetConstant(d, "CBF",SWIG_From_int((int)(0x0000))); SWIG_Python_SetConstant(d, "CIF",SWIG_From_int((int)(0x0001))); SWIG_Python_SetConstant(d, "ENC_NONE",SWIG_From_int((int)(0x0001))); SWIG_Python_SetConstant(d, "ENC_BASE64",SWIG_From_int((int)(0x0002))); SWIG_Python_SetConstant(d, "ENC_BASE32K",SWIG_From_int((int)(0x0004))); SWIG_Python_SetConstant(d, "ENC_QP",SWIG_From_int((int)(0x0008))); SWIG_Python_SetConstant(d, "ENC_BASE10",SWIG_From_int((int)(0x0010))); SWIG_Python_SetConstant(d, "ENC_BASE16",SWIG_From_int((int)(0x0020))); SWIG_Python_SetConstant(d, "ENC_BASE8",SWIG_From_int((int)(0x0040))); SWIG_Python_SetConstant(d, "ENC_FORWARD",SWIG_From_int((int)(0x0080))); SWIG_Python_SetConstant(d, "ENC_BACKWARD",SWIG_From_int((int)(0x0100))); SWIG_Python_SetConstant(d, "ENC_CRTERM",SWIG_From_int((int)(0x0200))); SWIG_Python_SetConstant(d, "ENC_LFTERM",SWIG_From_int((int)(0x0400))); SWIG_Python_SetConstant(d, "ENC_DEFAULT",SWIG_From_int((int)((0x0002|0x0400|0x0080)))); SWIG_Python_SetConstant(d, "CBF_UNDEFNODE",SWIG_From_int((int)(CBF_UNDEFNODE))); SWIG_Python_SetConstant(d, "CBF_LINK",SWIG_From_int((int)(CBF_LINK))); SWIG_Python_SetConstant(d, "CBF_ROOT",SWIG_From_int((int)(CBF_ROOT))); SWIG_Python_SetConstant(d, "CBF_DATABLOCK",SWIG_From_int((int)(CBF_DATABLOCK))); SWIG_Python_SetConstant(d, "CBF_SAVEFRAME",SWIG_From_int((int)(CBF_SAVEFRAME))); SWIG_Python_SetConstant(d, "CBF_CATEGORY",SWIG_From_int((int)(CBF_CATEGORY))); SWIG_Python_SetConstant(d, "CBF_COLUMN",SWIG_From_int((int)(CBF_COLUMN))); #if PY_VERSION_HEX >= 0x03000000 return m; #else return; #endif } ./CBFlib-0.9.2.2/pycbf/pycbf.py0000644000076500007650000135347111603702120014370 0ustar yayayaya# This file was automatically generated by SWIG (http://www.swig.org). # Version 1.3.40 # # Do not make changes to this file unless you know what you are doing--modify # the SWIG interface file instead. # This file is compatible with both classic and new-style classes. from sys import version_info if version_info >= (2,6,0): def swig_import_helper(): from os.path import dirname import imp fp = None try: fp, pathname, description = imp.find_module('_pycbf', [dirname(__file__)]) except ImportError: import _pycbf return _pycbf if fp is not None: try: _mod = imp.load_module('_pycbf', fp, pathname, description) finally: fp.close() return _mod _pycbf = swig_import_helper() del swig_import_helper else: import _pycbf del version_info try: _swig_property = property except NameError: pass # Python < 2.2 doesn't have 'property'. def _swig_setattr_nondynamic(self,class_type,name,value,static=1): if (name == "thisown"): return self.this.own(value) if (name == "this"): if type(value).__name__ == 'SwigPyObject': self.__dict__[name] = value return method = class_type.__swig_setmethods__.get(name,None) if method: return method(self,value) if (not static) or hasattr(self,name): self.__dict__[name] = value else: raise AttributeError("You cannot add attributes to %s" % self) def _swig_setattr(self,class_type,name,value): return _swig_setattr_nondynamic(self,class_type,name,value,0) def _swig_getattr(self,class_type,name): if (name == "thisown"): return self.this.own() method = class_type.__swig_getmethods__.get(name,None) if method: return method(self) raise AttributeError(name) def _swig_repr(self): try: strthis = "proxy of " + self.this.__repr__() except: strthis = "" return "<%s.%s; %s >" % (self.__class__.__module__, self.__class__.__name__, strthis,) try: _object = object _newclass = 1 except AttributeError: class _object : pass _newclass = 0 __author__ = "Jon Wright " __date__ = "14 Dec 2005" __version__ = "CBFlib 0.9" __credits__ = """Paul Ellis and Herbert Bernstein for the excellent CBFlib!""" __doc__=""" pycbf - python bindings to the CBFlib library A library for reading and writing ImageCIF and CBF files which store area detector images for crystallography. This work is a derivative of the CBFlib version 0.7.7 library by Paul J. Ellis of Stanford Synchrotron Radiation Laboratory and Herbert J. Bernstein of Bernstein + Sons See: http://www.bernstein-plus-sons.com/software/CBF/ Licensing is GPL based, see: http://www.bernstein-plus-sons.com/software/CBF/doc/CBFlib_NOTICES.html These bindings were automatically generated by SWIG, and the input to SWIG was automatically generated by a python script. We very strongly recommend you do not attempt to edit them by hand! Copyright (C) 2007 Jonathan Wright ESRF, Grenoble, France email: wright@esrf.fr Revised, August 2010 Herbert J. Bernstein Add defines from CBFlib 0.9.1 """ class doubleArray(_object): __swig_setmethods__ = {} __setattr__ = lambda self, name, value: _swig_setattr(self, doubleArray, name, value) __swig_getmethods__ = {} __getattr__ = lambda self, name: _swig_getattr(self, doubleArray, name) __repr__ = _swig_repr def __init__(self, *args): this = _pycbf.new_doubleArray(*args) try: self.this.append(this) except: self.this = this __swig_destroy__ = _pycbf.delete_doubleArray __del__ = lambda self : None; def __getitem__(self, *args): return _pycbf.doubleArray___getitem__(self, *args) def __setitem__(self, *args): return _pycbf.doubleArray___setitem__(self, *args) def cast(self): return _pycbf.doubleArray_cast(self) __swig_getmethods__["frompointer"] = lambda x: _pycbf.doubleArray_frompointer if _newclass:frompointer = staticmethod(_pycbf.doubleArray_frompointer) doubleArray_swigregister = _pycbf.doubleArray_swigregister doubleArray_swigregister(doubleArray) def doubleArray_frompointer(*args): return _pycbf.doubleArray_frompointer(*args) doubleArray_frompointer = _pycbf.doubleArray_frompointer class intArray(_object): __swig_setmethods__ = {} __setattr__ = lambda self, name, value: _swig_setattr(self, intArray, name, value) __swig_getmethods__ = {} __getattr__ = lambda self, name: _swig_getattr(self, intArray, name) __repr__ = _swig_repr def __init__(self, *args): this = _pycbf.new_intArray(*args) try: self.this.append(this) except: self.this = this __swig_destroy__ = _pycbf.delete_intArray __del__ = lambda self : None; def __getitem__(self, *args): return _pycbf.intArray___getitem__(self, *args) def __setitem__(self, *args): return _pycbf.intArray___setitem__(self, *args) def cast(self): return _pycbf.intArray_cast(self) __swig_getmethods__["frompointer"] = lambda x: _pycbf.intArray_frompointer if _newclass:frompointer = staticmethod(_pycbf.intArray_frompointer) intArray_swigregister = _pycbf.intArray_swigregister intArray_swigregister(intArray) def intArray_frompointer(*args): return _pycbf.intArray_frompointer(*args) intArray_frompointer = _pycbf.intArray_frompointer class shortArray(_object): __swig_setmethods__ = {} __setattr__ = lambda self, name, value: _swig_setattr(self, shortArray, name, value) __swig_getmethods__ = {} __getattr__ = lambda self, name: _swig_getattr(self, shortArray, name) __repr__ = _swig_repr def __init__(self, *args): this = _pycbf.new_shortArray(*args) try: self.this.append(this) except: self.this = this __swig_destroy__ = _pycbf.delete_shortArray __del__ = lambda self : None; def __getitem__(self, *args): return _pycbf.shortArray___getitem__(self, *args) def __setitem__(self, *args): return _pycbf.shortArray___setitem__(self, *args) def cast(self): return _pycbf.shortArray_cast(self) __swig_getmethods__["frompointer"] = lambda x: _pycbf.shortArray_frompointer if _newclass:frompointer = staticmethod(_pycbf.shortArray_frompointer) shortArray_swigregister = _pycbf.shortArray_swigregister shortArray_swigregister(shortArray) def shortArray_frompointer(*args): return _pycbf.shortArray_frompointer(*args) shortArray_frompointer = _pycbf.shortArray_frompointer class longArray(_object): __swig_setmethods__ = {} __setattr__ = lambda self, name, value: _swig_setattr(self, longArray, name, value) __swig_getmethods__ = {} __getattr__ = lambda self, name: _swig_getattr(self, longArray, name) __repr__ = _swig_repr def __init__(self, *args): this = _pycbf.new_longArray(*args) try: self.this.append(this) except: self.this = this __swig_destroy__ = _pycbf.delete_longArray __del__ = lambda self : None; def __getitem__(self, *args): return _pycbf.longArray___getitem__(self, *args) def __setitem__(self, *args): return _pycbf.longArray___setitem__(self, *args) def cast(self): return _pycbf.longArray_cast(self) __swig_getmethods__["frompointer"] = lambda x: _pycbf.longArray_frompointer if _newclass:frompointer = staticmethod(_pycbf.longArray_frompointer) longArray_swigregister = _pycbf.longArray_swigregister longArray_swigregister(longArray) def longArray_frompointer(*args): return _pycbf.longArray_frompointer(*args) longArray_frompointer = _pycbf.longArray_frompointer CBF_INTEGER = _pycbf.CBF_INTEGER CBF_FLOAT = _pycbf.CBF_FLOAT CBF_CANONICAL = _pycbf.CBF_CANONICAL CBF_PACKED = _pycbf.CBF_PACKED CBF_PACKED_V2 = _pycbf.CBF_PACKED_V2 CBF_BYTE_OFFSET = _pycbf.CBF_BYTE_OFFSET CBF_PREDICTOR = _pycbf.CBF_PREDICTOR CBF_NONE = _pycbf.CBF_NONE CBF_COMPRESSION_MASK = _pycbf.CBF_COMPRESSION_MASK CBF_FLAG_MASK = _pycbf.CBF_FLAG_MASK CBF_UNCORRELATED_SECTIONS = _pycbf.CBF_UNCORRELATED_SECTIONS CBF_FLAT_IMAGE = _pycbf.CBF_FLAT_IMAGE CBF_NO_EXPAND = _pycbf.CBF_NO_EXPAND PLAIN_HEADERS = _pycbf.PLAIN_HEADERS MIME_HEADERS = _pycbf.MIME_HEADERS MSG_NODIGEST = _pycbf.MSG_NODIGEST MSG_DIGEST = _pycbf.MSG_DIGEST MSG_DIGESTNOW = _pycbf.MSG_DIGESTNOW MSG_DIGESTWARN = _pycbf.MSG_DIGESTWARN PAD_1K = _pycbf.PAD_1K PAD_2K = _pycbf.PAD_2K PAD_4K = _pycbf.PAD_4K CBF_PARSE_BRC = _pycbf.CBF_PARSE_BRC CBF_PARSE_PRN = _pycbf.CBF_PARSE_PRN CBF_PARSE_BKT = _pycbf.CBF_PARSE_BKT CBF_PARSE_BRACKETS = _pycbf.CBF_PARSE_BRACKETS CBF_PARSE_TQ = _pycbf.CBF_PARSE_TQ CBF_PARSE_CIF2_DELIMS = _pycbf.CBF_PARSE_CIF2_DELIMS CBF_PARSE_DDLm = _pycbf.CBF_PARSE_DDLm CBF_PARSE_CIF2 = _pycbf.CBF_PARSE_CIF2 CBF_PARSE_DEFINES = _pycbf.CBF_PARSE_DEFINES CBF_PARSE_WIDE = _pycbf.CBF_PARSE_WIDE CBF_PARSE_UTF8 = _pycbf.CBF_PARSE_UTF8 HDR_DEFAULT = _pycbf.HDR_DEFAULT MIME_NOHEADERS = _pycbf.MIME_NOHEADERS CBF = _pycbf.CBF CIF = _pycbf.CIF ENC_NONE = _pycbf.ENC_NONE ENC_BASE64 = _pycbf.ENC_BASE64 ENC_BASE32K = _pycbf.ENC_BASE32K ENC_QP = _pycbf.ENC_QP ENC_BASE10 = _pycbf.ENC_BASE10 ENC_BASE16 = _pycbf.ENC_BASE16 ENC_BASE8 = _pycbf.ENC_BASE8 ENC_FORWARD = _pycbf.ENC_FORWARD ENC_BACKWARD = _pycbf.ENC_BACKWARD ENC_CRTERM = _pycbf.ENC_CRTERM ENC_LFTERM = _pycbf.ENC_LFTERM ENC_DEFAULT = _pycbf.ENC_DEFAULT def get_local_integer_byte_order(): """ Returns : char **bo,int *bolen *args : C prototype: int cbf_get_local_integer_byte_order (char ** byte_order); CBFLib documentation: DESCRIPTION cbf_get_local_integer_byte_order returns the byte order of integers on the machine on which the API is being run in the form of a character string returned as the value pointed to by byte_order. cbf_get_local_real_byte_order returns the byte order of reals on the machine on which the API is being run in the form of a character string returned as the value pointed to by byte_order. cbf_get_local_real_format returns the format of floats on the machine on which the API is being run in the form of a character string returned as the value pointed to by real_format. The strings returned must not be modified in any way. The values returned in byte_order may be the strings "little_endian " or "big-endian ". The values returned in real_format may be the strings "ieee 754-1985 " or "other ". Additional values may be returned by future versions of the API. ARGUMENTS byte_order pointer to the returned string real_format pointer to the returned string RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.get_local_integer_byte_order() def compute_cell_volume(*args): """ Returns : Float volume *args : double cell[6] C prototype: int cbf_compute_cell_volume ( double cell[6], double *volume ); CBFLib documentation: DESCRIPTION cbf_compute_cell_volume sets *volume to point to the volume of the unit cell computed from the double values in cell[0:2] for the cell edge lengths a, b and c in AAngstroms and the double values given in cell[3:5] for the cell angles a, b and g in degrees. ARGUMENTS cell Pointer to the array of 6 doubles giving the cell parameters. volume Pointer to the doubles for cell volume. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.compute_cell_volume(*args) def get_local_real_format(): """ Returns : char **rf,int *rflen *args : C prototype: int cbf_get_local_real_format (char ** real_format ); CBFLib documentation: DESCRIPTION cbf_get_local_integer_byte_order returns the byte order of integers on the machine on which the API is being run in the form of a character string returned as the value pointed to by byte_order. cbf_get_local_real_byte_order returns the byte order of reals on the machine on which the API is being run in the form of a character string returned as the value pointed to by byte_order. cbf_get_local_real_format returns the format of floats on the machine on which the API is being run in the form of a character string returned as the value pointed to by real_format. The strings returned must not be modified in any way. The values returned in byte_order may be the strings "little_endian " or "big-endian ". The values returned in real_format may be the strings "ieee 754-1985 " or "other ". Additional values may be returned by future versions of the API. ARGUMENTS byte_order pointer to the returned string real_format pointer to the returned string RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.get_local_real_format() def get_local_real_byte_order(): """ Returns : char **bo,int *bolen *args : C prototype: int cbf_get_local_real_byte_order (char ** byte_order); CBFLib documentation: DESCRIPTION cbf_get_local_integer_byte_order returns the byte order of integers on the machine on which the API is being run in the form of a character string returned as the value pointed to by byte_order. cbf_get_local_real_byte_order returns the byte order of reals on the machine on which the API is being run in the form of a character string returned as the value pointed to by byte_order. cbf_get_local_real_format returns the format of floats on the machine on which the API is being run in the form of a character string returned as the value pointed to by real_format. The strings returned must not be modified in any way. The values returned in byte_order may be the strings "little_endian " or "big-endian ". The values returned in real_format may be the strings "ieee 754-1985 " or "other ". Additional values may be returned by future versions of the API. ARGUMENTS byte_order pointer to the returned string real_format pointer to the returned string RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.get_local_real_byte_order() def compute_reciprocal_cell(*args): """ Returns : Float astar,Float bstar,Float cstar,Float alphastar,Float betastar, Float gammastar *args : double cell[6] C prototype: int cbf_compute_reciprocal_cell ( double cell[6], double rcell[6] ); CBFLib documentation: DESCRIPTION cbf_compute_reciprocal_cell sets rcell to point to the array of reciprocal cell parameters computed from the double values cell[0:2] giving the cell edge lengths a, b and c in AAngstroms, and the double values cell[3:5] giving the cell angles a, b and g in degrees. The double values rcell[0:2] will be set to the reciprocal cell lengths a*, b* and c* in AAngstroms-1 and the double values rcell[3:5] will be set to the reciprocal cell angles a*, b* and g* in degrees. ARGUMENTS cell Pointer to the array of 6 doubles giving the cell parameters. rcell Pointer to the destination array of 6 doubles giving the reciprocal cell parameters. volume Pointer to the doubles for cell volume. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.compute_reciprocal_cell(*args) class cbf_positioner_struct(_object): """Proxy of C cbf_positioner_struct struct""" __swig_setmethods__ = {} __setattr__ = lambda self, name, value: _swig_setattr(self, cbf_positioner_struct, name, value) __swig_getmethods__ = {} __getattr__ = lambda self, name: _swig_getattr(self, cbf_positioner_struct, name) __repr__ = _swig_repr __swig_setmethods__["matrix"] = _pycbf.cbf_positioner_struct_matrix_set __swig_getmethods__["matrix"] = _pycbf.cbf_positioner_struct_matrix_get if _newclass:matrix = _swig_property(_pycbf.cbf_positioner_struct_matrix_get, _pycbf.cbf_positioner_struct_matrix_set) __swig_setmethods__["axis"] = _pycbf.cbf_positioner_struct_axis_set __swig_getmethods__["axis"] = _pycbf.cbf_positioner_struct_axis_get if _newclass:axis = _swig_property(_pycbf.cbf_positioner_struct_axis_get, _pycbf.cbf_positioner_struct_axis_set) __swig_setmethods__["axes"] = _pycbf.cbf_positioner_struct_axes_set __swig_getmethods__["axes"] = _pycbf.cbf_positioner_struct_axes_get if _newclass:axes = _swig_property(_pycbf.cbf_positioner_struct_axes_get, _pycbf.cbf_positioner_struct_axes_set) __swig_setmethods__["matrix_is_valid"] = _pycbf.cbf_positioner_struct_matrix_is_valid_set __swig_getmethods__["matrix_is_valid"] = _pycbf.cbf_positioner_struct_matrix_is_valid_get if _newclass:matrix_is_valid = _swig_property(_pycbf.cbf_positioner_struct_matrix_is_valid_get, _pycbf.cbf_positioner_struct_matrix_is_valid_set) __swig_setmethods__["axes_are_connected"] = _pycbf.cbf_positioner_struct_axes_are_connected_set __swig_getmethods__["axes_are_connected"] = _pycbf.cbf_positioner_struct_axes_are_connected_get if _newclass:axes_are_connected = _swig_property(_pycbf.cbf_positioner_struct_axes_are_connected_get, _pycbf.cbf_positioner_struct_axes_are_connected_set) def __init__(self): """__init__(self) -> cbf_positioner_struct""" this = _pycbf.new_cbf_positioner_struct() try: self.this.append(this) except: self.this = this __swig_destroy__ = _pycbf.delete_cbf_positioner_struct __del__ = lambda self : None; def get_rotation_range(self): """ Returns : Float start,Float increment *args : C prototype: int cbf_get_rotation_range (cbf_goniometer goniometer, unsigned int reserved, double *start, double *increment); CBFLib documentation: DESCRIPTION cbf_get_rotation_range sets *start and *increment to the corresponding values of the goniometer rotation axis used for the exposure. Either of the destination pointers may be NULL. The parameter reserved is presently unused and should be set to 0. ARGUMENTS goniometer Goniometer handle. reserved Unused. Any value other than 0 is invalid. start Pointer to the destination start value. increment Pointer to the destination increment value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_positioner_struct_get_rotation_range(self) def rotate_vector(self, *args): """ Returns : double final1,double final2,double final3 *args : double ratio,double initial1,double initial2,double initial3 C prototype: int cbf_rotate_vector (cbf_goniometer goniometer, unsigned int reserved, double ratio, double initial1, double initial2, double initial3, double *final1, double *final2, double *final3); CBFLib documentation: DESCRIPTION cbf_rotate_vector sets *final1, *final2, and *final3 to the 3 components of the of the vector (initial1, initial2, initial3) after reorientation by applying the goniometer rotations. The value ratio specif ies the goniometer setting and varies from 0.0 at the beginning of the exposure to 1.0 at the end, irrespective of the actual rotation range. Any of the destination pointers may be NULL. The parameter reserved is presently unused and should be set to 0. ARGUMENTS goniometer Goniometer handle. reserved Unused. Any value other than 0 is invalid. ratio Goniometer setting. 0 = beginning of exposure, 1 = end. initial1 x component of the initial vector. initial2 y component of the initial vector. initial3 z component of the initial vector. vector1 Pointer to the destination x component of the final vector. vector2 Pointer to the destination y component of the final vector. vector3 Pointer to the destination z component of the final vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_positioner_struct_rotate_vector(self, *args) def get_reciprocal(self, *args): """ Returns : double reciprocal1,double reciprocal2,double reciprocal3 *args : double ratio,double wavelength,double real1,double real2,double real3 C prototype: int cbf_get_reciprocal (cbf_goniometer goniometer, unsigned int reserved, double ratio, double wavelength, double real1, double real2, double real3, double *reciprocal1, double *reciprocal2, double *reciprocal3); CBFLib documentation: DESCRIPTION cbf_get_reciprocal sets *reciprocal1, * reciprocal2, and * reciprocal3 to the 3 components of the of the reciprocal-space vector corresponding to the real-space vector (real1, real2, real3). The reciprocal-space vector is oriented to correspond to the goniometer setting with all axes at 0. The value wavelength is the wavlength in AA and the value ratio specifies the current goniometer setting and varies from 0.0 at the beginning of the exposur e to 1.0 at the end, irrespective of the actual rotation range. Any of the destination pointers may be NULL. The parameter reserved is presently unused and should be set to 0. ARGUMENTS goniometer Goniometer handle. reserved Unused. Any value other than 0 is invalid. ratio Goniometer setting. 0 = beginning of exposure, 1 = end. wavelength Wavelength in AA. real1 x component of the real-space vector. real2 y component of the real-space vector. real3 z component of the real-space vector. reciprocal1 Pointer to the destination x component of the reciprocal-space vector. reciprocal2 Pointer to the destination y component of the reciprocal-space vector. reciprocal3 Pointer to the destination z component of the reciprocal-space vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_positioner_struct_get_reciprocal(self, *args) def get_rotation_axis(self): """ Returns : double vector1,double vector2,double vector3 *args : C prototype: int cbf_get_rotation_axis (cbf_goniometer goniometer, unsigned int reserved, double *vector1, double *vector2, double *vector3); CBFLib documentation: DESCRIPTION cbf_get_rotation_axis sets *vector1, *vector2, and *vector3 to the 3 components of the goniometer rotation axis used for the exposure. Any of the destination pointers may be NULL. The parameter reserved is presently unused and should be set to 0. ARGUMENTS goniometer Goniometer handle. reserved Unused. Any value other than 0 is invalid. vector1 Pointer to the destination x component of the rotation axis. vector2 Pointer to the destination y component of the rotation axis. vector3 Pointer to the destination z component of the rotation axis. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_positioner_struct_get_rotation_axis(self) cbf_positioner_struct_swigregister = _pycbf.cbf_positioner_struct_swigregister cbf_positioner_struct_swigregister(cbf_positioner_struct) class cbf_detector_struct(_object): """Proxy of C cbf_detector_struct struct""" __swig_setmethods__ = {} __setattr__ = lambda self, name, value: _swig_setattr(self, cbf_detector_struct, name, value) __swig_getmethods__ = {} __getattr__ = lambda self, name: _swig_getattr(self, cbf_detector_struct, name) __repr__ = _swig_repr __swig_setmethods__["positioner"] = _pycbf.cbf_detector_struct_positioner_set __swig_getmethods__["positioner"] = _pycbf.cbf_detector_struct_positioner_get if _newclass:positioner = _swig_property(_pycbf.cbf_detector_struct_positioner_get, _pycbf.cbf_detector_struct_positioner_set) __swig_setmethods__["displacement"] = _pycbf.cbf_detector_struct_displacement_set __swig_getmethods__["displacement"] = _pycbf.cbf_detector_struct_displacement_get if _newclass:displacement = _swig_property(_pycbf.cbf_detector_struct_displacement_get, _pycbf.cbf_detector_struct_displacement_set) __swig_setmethods__["increment"] = _pycbf.cbf_detector_struct_increment_set __swig_getmethods__["increment"] = _pycbf.cbf_detector_struct_increment_get if _newclass:increment = _swig_property(_pycbf.cbf_detector_struct_increment_get, _pycbf.cbf_detector_struct_increment_set) __swig_setmethods__["axes"] = _pycbf.cbf_detector_struct_axes_set __swig_getmethods__["axes"] = _pycbf.cbf_detector_struct_axes_get if _newclass:axes = _swig_property(_pycbf.cbf_detector_struct_axes_get, _pycbf.cbf_detector_struct_axes_set) __swig_setmethods__["index"] = _pycbf.cbf_detector_struct_index_set __swig_getmethods__["index"] = _pycbf.cbf_detector_struct_index_get if _newclass:index = _swig_property(_pycbf.cbf_detector_struct_index_get, _pycbf.cbf_detector_struct_index_set) def __init__(self): """__init__(self) -> cbf_detector_struct""" this = _pycbf.new_cbf_detector_struct() try: self.this.append(this) except: self.this = this __swig_destroy__ = _pycbf.delete_cbf_detector_struct __del__ = lambda self : None; def set_reference_beam_center_fs(self, *args): """ Returns : *args : double indexfast,double indexslow,double centerfast,double centerslow C prototype: int cbf_set_reference_beam_center_fs (cbf_detector detector, double *indexfast, double *indexslow, double *centerfast, double *centerslow); CBFLib documentation: DESCRIPTION cbf_get_beam_center sets *centerfast and *centerslow to the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector and *indexfast and *indexslow to the corresponding indices. cbf_set_beam_center sets the offsets in the axis category for the detector element axis with precedence 1 to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given *indexfast and *indexslow. cbf_set_reference_beam_center sets the displacments in the array_structure_list_axis category to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given by *indexfast and *indexslow. In order to achieve consistent results, a reference detector should be used for detector to have all axes at their reference settings. Note that the precedence 1 axis is the fastest axis, so that *centerfast and *indexfast are the fast axis components of the center and *centerslow and *indexslow are the slow axis components of the center. The _fs calls give the displacments in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the displacements in slow-to-fast order Any of the destination pointers may be NULL for getting the beam center. For setting the beam axis, either the indices of the center must not be NULL. The indices are non-negative for beam centers within the detector surface, but the center for an axis with a negative increment will be negative for a beam center within the detector surface. For cbf_set_beam_center if the diffrn_data_frame category exists with a row for the corresponding element id, the values will be set for _diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in millimetres and the value of _diffrn_data_frame.center_units will be set to 'mm'. For cbf_set_reference_beam_center if the diffrn_detector_element category exists with a row for the corresponding element id, the values will be set for _diffrn_detector_element.reference_center_fast and _diffrn_detector_element.reference_center_slow in millimetres and the value of _diffrn_detector_element.reference_units will be set to 'mm'. ARGUMENTS detector Detector handle. indexfast Pointer to the destination fast index. indexslow Pointer to the destination slow index. centerfast Pointer to the destination displacement along the fast axis. centerslow Pointer to the destination displacement along the slow axis. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_detector_struct_set_reference_beam_center_fs(self, *args) def get_pixel_coordinates_fs(self, *args): """ Returns : double coordinate1,double coordinate2,double coordinate3 *args : double indexfast,double indexslow C prototype: int cbf_get_pixel_coordinates_fs (cbf_detector detector, double indexfast, double indexslow, double *coordinate1, double *coordinate2, double *coordinate3); CBFLib documentation: DESCRIPTION cbf_get_pixel_coordinates, cbf_get_pixel_coordinates_fs and cbf_get_pixel_coordinates_sf ses *coordinate1, *coordinate2, and *coordinate3 to the vector position of pixel (indexfast, indexslow) on the detector surface. If indexslow and indexfast are integers then the coordinates correspond to the center of a pixel. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. indexslow Slow index. indexfast Fast index. coordinate1 Pointer to the destination x component. coordinate2 Pointer to the destination y component. coordinate3 Pointer to the destination z component. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_detector_struct_get_pixel_coordinates_fs(self, *args) def set_beam_center_fs(self, *args): """ Returns : *args : double indexfast,double indexslow,double centerfast,double centerslow C prototype: int cbf_set_beam_center_fs (cbf_detector detector, double *indexfast, double *indexslow, double *centerfast, double *centerslow); CBFLib documentation: DESCRIPTION cbf_get_beam_center sets *centerfast and *centerslow to the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector and *indexfast and *indexslow to the corresponding indices. cbf_set_beam_center sets the offsets in the axis category for the detector element axis with precedence 1 to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given *indexfast and *indexslow. cbf_set_reference_beam_center sets the displacments in the array_structure_list_axis category to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given by *indexfast and *indexslow. In order to achieve consistent results, a reference detector should be used for detector to have all axes at their reference settings. Note that the precedence 1 axis is the fastest axis, so that *centerfast and *indexfast are the fast axis components of the center and *centerslow and *indexslow are the slow axis components of the center. The _fs calls give the displacments in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the displacements in slow-to-fast order Any of the destination pointers may be NULL for getting the beam center. For setting the beam axis, either the indices of the center must not be NULL. The indices are non-negative for beam centers within the detector surface, but the center for an axis with a negative increment will be negative for a beam center within the detector surface. For cbf_set_beam_center if the diffrn_data_frame category exists with a row for the corresponding element id, the values will be set for _diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in millimetres and the value of _diffrn_data_frame.center_units will be set to 'mm'. For cbf_set_reference_beam_center if the diffrn_detector_element category exists with a row for the corresponding element id, the values will be set for _diffrn_detector_element.reference_center_fast and _diffrn_detector_element.reference_center_slow in millimetres and the value of _diffrn_detector_element.reference_units will be set to 'mm'. ARGUMENTS detector Detector handle. indexfast Pointer to the destination fast index. indexslow Pointer to the destination slow index. centerfast Pointer to the destination displacement along the fast axis. centerslow Pointer to the destination displacement along the slow axis. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_detector_struct_set_beam_center_fs(self, *args) def get_inferred_pixel_size(self, *args): """ Returns : Float pixel size *args : Int axis_number C prototype: int cbf_get_inferred_pixel_size (cbf_detector detector, int axis_number, double *psize); CBFLib documentation: DESCRIPTION cbf_get_inferred_pixel_size, cbf_get_inferred_pixel_size_sf set *psize to point to the double value in millimeters of the pixel size for the axis axis_number value. The slow index is treated as axis 1 and the next faster index is treated as axis 2. cbf_get_inferred_pixel_size_fs sets *psize to point to the double value in millimeters of the pixel size for the axis axis_number value. The fast index is treated as axis 1 and the next slower index is treated as axis 2. If the axis number is negative, the axes are used in the reverse order so that an axis_number of -1 indicates the fast axes in a call to cbf_get_inferred_pixel_size or cbf_get_inferred_pixel_size_sf and indicates the fast axis in a call to cbf_get_inferred_pixel_size_fs. ARGUMENTS detector Detector handle. axis_number The number of the axis. area Pointer to the destination pizel size in mm. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_detector_struct_get_inferred_pixel_size(self, *args) def get_pixel_area(self, *args): """ Returns : double area,double projected_area *args : double index1,double index2 C prototype: int cbf_get_pixel_area (cbf_detector detector, double indexslow, double indexfast, double *area, double *projected_area); CBFLib documentation: DESCRIPTION cbf_get_pixel_area, cbf_get_pixel_area_fs and cbf_get_pixel_area_sf set *area to the area of the pixel at (indexfast, indexslow) on the detector surface and *projected_area to the apparent area of the pixel as viewed from the sample position, with indexslow being the slow axis and indexfast being the fast axis. Either of the destination pointers may be NULL. ARGUMENTS detector Detector handle. indexfast Fast index. indexslow Slow index. area Pointer to the destination area in mm2. projected_area Pointer to the destination apparent area in mm2. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_detector_struct_get_pixel_area(self, *args) def get_pixel_normal_fs(self, *args): """ Returns : double normal1,double normal2,double normal3 *args : double indexfast,double indexslow C prototype: int cbf_get_pixel_normal_fs (cbf_detector detector, double indexfast, double indexslow, double *normal1, double *normal2, double *normal3); CBFLib documentation: DESCRIPTION cbf_get_detector_normal, cbf_get_pixel_normal_fs and cbf_get_pixel_normal_sf set *normal1, *normal2, and *normal3 to the 3 components of the of the normal vector to the pixel at (indexfast, indexslow). The vector is normalized. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. indexslow Slow index. indexfast Fast index. normal1 Pointer to the destination x component of the normal vector. normal2 Pointer to the destination y component of the normal vector. normal3 Pointer to the destination z component of the normal vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_detector_struct_get_pixel_normal_fs(self, *args) def get_detector_axes(self): """ Returns : double slowaxis1,double slowaxis2,double slowaxis3,double fastaxis1, double fastaxis2,double fastaxis3 *args : C prototype: int cbf_get_detector_axes (cbf_detector detector, double *slowaxis1, double *slowaxis2, double *slowaxis3, double *fastaxis1, double *fastaxis2, double *fastaxis3); CBFLib documentation: DESCRIPTION cbf_get_detector_axis_slow sets *slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the slow axis of the specified detector at the current settings of all axes. cbf_get_detector_axis_slow sets *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 components of the fast axis of the specified detector at the current settings of all axes. cbf_get_detector_axes, cbf_get_detector_axes_fs and int cbf_get_detector_axes_sf set *slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the slow axis and *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 components of the fast axis of the specified detector at the current settings of all axes. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. slowaxis1 Pointer to the destination x component of the slow axis vector. slowaxis2 Pointer to the destination y component of the slow axis vector. slowaxis3 Pointer to the destination z component of the slow axis vector. fastaxis1 Pointer to the destination x component of the fast axis vector. fastaxis2 Pointer to the destination y component of the fast axis vector. fastaxis3 Pointer to the destination z component of the fast axis vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_detector_struct_get_detector_axes(self) def set_reference_beam_center(self, *args): """ Returns : *args : double indexslow,double indexfast,double centerslow,double centerfast C prototype: int cbf_set_reference_beam_center (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast); CBFLib documentation: DESCRIPTION cbf_get_beam_center sets *centerfast and *centerslow to the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector and *indexfast and *indexslow to the corresponding indices. cbf_set_beam_center sets the offsets in the axis category for the detector element axis with precedence 1 to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given *indexfast and *indexslow. cbf_set_reference_beam_center sets the displacments in the array_structure_list_axis category to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given by *indexfast and *indexslow. In order to achieve consistent results, a reference detector should be used for detector to have all axes at their reference settings. Note that the precedence 1 axis is the fastest axis, so that *centerfast and *indexfast are the fast axis components of the center and *centerslow and *indexslow are the slow axis components of the center. The _fs calls give the displacments in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the displacements in slow-to-fast order Any of the destination pointers may be NULL for getting the beam center. For setting the beam axis, either the indices of the center must not be NULL. The indices are non-negative for beam centers within the detector surface, but the center for an axis with a negative increment will be negative for a beam center within the detector surface. For cbf_set_beam_center if the diffrn_data_frame category exists with a row for the corresponding element id, the values will be set for _diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in millimetres and the value of _diffrn_data_frame.center_units will be set to 'mm'. For cbf_set_reference_beam_center if the diffrn_detector_element category exists with a row for the corresponding element id, the values will be set for _diffrn_detector_element.reference_center_fast and _diffrn_detector_element.reference_center_slow in millimetres and the value of _diffrn_detector_element.reference_units will be set to 'mm'. ARGUMENTS detector Detector handle. indexfast Pointer to the destination fast index. indexslow Pointer to the destination slow index. centerfast Pointer to the destination displacement along the fast axis. centerslow Pointer to the destination displacement along the slow axis. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_detector_struct_set_reference_beam_center(self, *args) def get_detector_axis_slow(self): """ Returns : double slowaxis1,double slowaxis2,double slowaxis3 *args : C prototype: int cbf_get_detector_axis_slow (cbf_detector detector, double *slowaxis1, double *slowaxis2, double *slowaxis3); CBFLib documentation: DESCRIPTION cbf_get_detector_axis_slow sets *slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the slow axis of the specified detector at the current settings of all axes. cbf_get_detector_axis_slow sets *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 components of the fast axis of the specified detector at the current settings of all axes. cbf_get_detector_axes, cbf_get_detector_axes_fs and int cbf_get_detector_axes_sf set *slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the slow axis and *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 components of the fast axis of the specified detector at the current settings of all axes. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. slowaxis1 Pointer to the destination x component of the slow axis vector. slowaxis2 Pointer to the destination y component of the slow axis vector. slowaxis3 Pointer to the destination z component of the slow axis vector. fastaxis1 Pointer to the destination x component of the fast axis vector. fastaxis2 Pointer to the destination y component of the fast axis vector. fastaxis3 Pointer to the destination z component of the fast axis vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_detector_struct_get_detector_axis_slow(self) def get_detector_distance(self): """ Returns : double distance *args : C prototype: int cbf_get_detector_distance (cbf_detector detector, double *distance); CBFLib documentation: DESCRIPTION cbf_get_detector_distance sets *distance to the nearest distance from the sample position to the detector plane. ARGUMENTS detector Detector handle. distance Pointer to the destination distance. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_detector_struct_get_detector_distance(self) def get_inferred_pixel_size_fs(self, *args): """ Returns : Float pixel size *args : Int axis_number C prototype: int cbf_get_inferred_pixel_size_fs(cbf_detector detector, int axis_number, double *psize); CBFLib documentation: DESCRIPTION cbf_get_inferred_pixel_size, cbf_get_inferred_pixel_size_sf set *psize to point to the double value in millimeters of the pixel size for the axis axis_number value. The slow index is treated as axis 1 and the next faster index is treated as axis 2. cbf_get_inferred_pixel_size_fs sets *psize to point to the double value in millimeters of the pixel size for the axis axis_number value. The fast index is treated as axis 1 and the next slower index is treated as axis 2. If the axis number is negative, the axes are used in the reverse order so that an axis_number of -1 indicates the fast axes in a call to cbf_get_inferred_pixel_size or cbf_get_inferred_pixel_size_sf and indicates the fast axis in a call to cbf_get_inferred_pixel_size_fs. ARGUMENTS detector Detector handle. axis_number The number of the axis. area Pointer to the destination pizel size in mm. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_detector_struct_get_inferred_pixel_size_fs(self, *args) def get_detector_normal(self): """ Returns : double normal1,double normal2,double normal3 *args : C prototype: int cbf_get_detector_normal (cbf_detector detector, double *normal1, double *normal2, double *normal3); CBFLib documentation: DESCRIPTION cbf_get_detector_normal sets *normal1, *normal2, and *normal3 to the 3 components of the of the normal vector to the detector plane. The vector is normalized. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. normal1 Pointer to the destination x component of the normal vector. normal2 Pointer to the destination y component of the normal vector. normal3 Pointer to the destination z component of the normal vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_detector_struct_get_detector_normal(self) def get_detector_axis_fast(self): """ Returns : double fastaxis1,double fastaxis2,double fastaxis3 *args : C prototype: int cbf_get_detector_axis_fast (cbf_detector detector, double *fastaxis1, double *fastaxis2, double *fastaxis3); CBFLib documentation: DESCRIPTION cbf_get_detector_axis_slow sets *slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the slow axis of the specified detector at the current settings of all axes. cbf_get_detector_axis_slow sets *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 components of the fast axis of the specified detector at the current settings of all axes. cbf_get_detector_axes, cbf_get_detector_axes_fs and int cbf_get_detector_axes_sf set *slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the slow axis and *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 components of the fast axis of the specified detector at the current settings of all axes. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. slowaxis1 Pointer to the destination x component of the slow axis vector. slowaxis2 Pointer to the destination y component of the slow axis vector. slowaxis3 Pointer to the destination z component of the slow axis vector. fastaxis1 Pointer to the destination x component of the fast axis vector. fastaxis2 Pointer to the destination y component of the fast axis vector. fastaxis3 Pointer to the destination z component of the fast axis vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_detector_struct_get_detector_axis_fast(self) def get_detector_axes_fs(self): """get_detector_axes_fs(self)""" return _pycbf.cbf_detector_struct_get_detector_axes_fs(self) def get_detector_axes_sf(self): """ Returns : double slowaxis1,double slowaxis2,double slowaxis3,double fastaxis1, double fastaxis2,double fastaxis3 *args : C prototype: int cbf_get_detector_axes_sf (cbf_detector detector, double *slowaxis1, double *slowaxis2, double *slowaxis3, double *fastaxis1, double *fastaxis2, double *fastaxis3); CBFLib documentation: DESCRIPTION cbf_get_detector_axis_slow sets *slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the slow axis of the specified detector at the current settings of all axes. cbf_get_detector_axis_slow sets *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 components of the fast axis of the specified detector at the current settings of all axes. cbf_get_detector_axes, cbf_get_detector_axes_fs and int cbf_get_detector_axes_sf set *slowaxis1, *slowaxis2, and *slowaxis3 to the 3 components of the slow axis and *fastaxis1, *fastaxis2, and *fastaxis3 to the 3 components of the fast axis of the specified detector at the current settings of all axes. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. slowaxis1 Pointer to the destination x component of the slow axis vector. slowaxis2 Pointer to the destination y component of the slow axis vector. slowaxis3 Pointer to the destination z component of the slow axis vector. fastaxis1 Pointer to the destination x component of the fast axis vector. fastaxis2 Pointer to the destination y component of the fast axis vector. fastaxis3 Pointer to the destination z component of the fast axis vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_detector_struct_get_detector_axes_sf(self) def get_pixel_coordinates_sf(self, *args): """ Returns : double coordinate1,double coordinate2,double coordinate3 *args : double indexslow,double indexfast C prototype: int cbf_get_pixel_coordinates_sf (cbf_detector detector, double indexslow, double indexfast, double *coordinate1, double *coordinate2, double *coordinate3); CBFLib documentation: DESCRIPTION cbf_get_pixel_coordinates, cbf_get_pixel_coordinates_fs and cbf_get_pixel_coordinates_sf ses *coordinate1, *coordinate2, and *coordinate3 to the vector position of pixel (indexfast, indexslow) on the detector surface. If indexslow and indexfast are integers then the coordinates correspond to the center of a pixel. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. indexslow Slow index. indexfast Fast index. coordinate1 Pointer to the destination x component. coordinate2 Pointer to the destination y component. coordinate3 Pointer to the destination z component. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_detector_struct_get_pixel_coordinates_sf(self, *args) def set_beam_center(self, *args): """ Returns : *args : double indexslow,double indexfast,double centerslow,double centerfast C prototype: int cbf_set_beam_center (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast); CBFLib documentation: DESCRIPTION cbf_get_beam_center sets *centerfast and *centerslow to the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector and *indexfast and *indexslow to the corresponding indices. cbf_set_beam_center sets the offsets in the axis category for the detector element axis with precedence 1 to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given *indexfast and *indexslow. cbf_set_reference_beam_center sets the displacments in the array_structure_list_axis category to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given by *indexfast and *indexslow. In order to achieve consistent results, a reference detector should be used for detector to have all axes at their reference settings. Note that the precedence 1 axis is the fastest axis, so that *centerfast and *indexfast are the fast axis components of the center and *centerslow and *indexslow are the slow axis components of the center. The _fs calls give the displacments in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the displacements in slow-to-fast order Any of the destination pointers may be NULL for getting the beam center. For setting the beam axis, either the indices of the center must not be NULL. The indices are non-negative for beam centers within the detector surface, but the center for an axis with a negative increment will be negative for a beam center within the detector surface. For cbf_set_beam_center if the diffrn_data_frame category exists with a row for the corresponding element id, the values will be set for _diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in millimetres and the value of _diffrn_data_frame.center_units will be set to 'mm'. For cbf_set_reference_beam_center if the diffrn_detector_element category exists with a row for the corresponding element id, the values will be set for _diffrn_detector_element.reference_center_fast and _diffrn_detector_element.reference_center_slow in millimetres and the value of _diffrn_detector_element.reference_units will be set to 'mm'. ARGUMENTS detector Detector handle. indexfast Pointer to the destination fast index. indexslow Pointer to the destination slow index. centerfast Pointer to the destination displacement along the fast axis. centerslow Pointer to the destination displacement along the slow axis. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_detector_struct_set_beam_center(self, *args) def get_pixel_area_fs(self, *args): """ Returns : double area,double projected_area *args : double indexfast,double indexslow C prototype: int cbf_get_pixel_area_fs(cbf_detector detector, double indexfast, double indexslow, double *area, double *projected_area); CBFLib documentation: DESCRIPTION cbf_get_pixel_area, cbf_get_pixel_area_fs and cbf_get_pixel_area_sf set *area to the area of the pixel at (indexfast, indexslow) on the detector surface and *projected_area to the apparent area of the pixel as viewed from the sample position, with indexslow being the slow axis and indexfast being the fast axis. Either of the destination pointers may be NULL. ARGUMENTS detector Detector handle. indexfast Fast index. indexslow Slow index. area Pointer to the destination area in mm2. projected_area Pointer to the destination apparent area in mm2. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_detector_struct_get_pixel_area_fs(self, *args) def get_beam_center_fs(self): """ Returns : double indexfast,double indexslow,double centerfast,double centerslow *args : C prototype: int cbf_get_beam_center_fs (cbf_detector detector, double *indexfast, double *indexslow, double *centerfast, double *centerslow); CBFLib documentation: DESCRIPTION cbf_get_beam_center sets *centerfast and *centerslow to the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector and *indexfast and *indexslow to the corresponding indices. cbf_set_beam_center sets the offsets in the axis category for the detector element axis with precedence 1 to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given *indexfast and *indexslow. cbf_set_reference_beam_center sets the displacments in the array_structure_list_axis category to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given by *indexfast and *indexslow. In order to achieve consistent results, a reference detector should be used for detector to have all axes at their reference settings. Note that the precedence 1 axis is the fastest axis, so that *centerfast and *indexfast are the fast axis components of the center and *centerslow and *indexslow are the slow axis components of the center. The _fs calls give the displacments in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the displacements in slow-to-fast order Any of the destination pointers may be NULL for getting the beam center. For setting the beam axis, either the indices of the center must not be NULL. The indices are non-negative for beam centers within the detector surface, but the center for an axis with a negative increment will be negative for a beam center within the detector surface. For cbf_set_beam_center if the diffrn_data_frame category exists with a row for the corresponding element id, the values will be set for _diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in millimetres and the value of _diffrn_data_frame.center_units will be set to 'mm'. For cbf_set_reference_beam_center if the diffrn_detector_element category exists with a row for the corresponding element id, the values will be set for _diffrn_detector_element.reference_center_fast and _diffrn_detector_element.reference_center_slow in millimetres and the value of _diffrn_detector_element.reference_units will be set to 'mm'. ARGUMENTS detector Detector handle. indexfast Pointer to the destination fast index. indexslow Pointer to the destination slow index. centerfast Pointer to the destination displacement along the fast axis. centerslow Pointer to the destination displacement along the slow axis. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_detector_struct_get_beam_center_fs(self) def get_inferred_pixel_size_sf(self, *args): """ Returns : Float pixel size *args : Int axis_number C prototype: int cbf_get_inferred_pixel_size_sf(cbf_detector detector, int axis_number, double *psize); CBFLib documentation: DESCRIPTION cbf_get_inferred_pixel_size, cbf_get_inferred_pixel_size_sf set *psize to point to the double value in millimeters of the pixel size for the axis axis_number value. The slow index is treated as axis 1 and the next faster index is treated as axis 2. cbf_get_inferred_pixel_size_fs sets *psize to point to the double value in millimeters of the pixel size for the axis axis_number value. The fast index is treated as axis 1 and the next slower index is treated as axis 2. If the axis number is negative, the axes are used in the reverse order so that an axis_number of -1 indicates the fast axes in a call to cbf_get_inferred_pixel_size or cbf_get_inferred_pixel_size_sf and indicates the fast axis in a call to cbf_get_inferred_pixel_size_fs. ARGUMENTS detector Detector handle. axis_number The number of the axis. area Pointer to the destination pizel size in mm. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_detector_struct_get_inferred_pixel_size_sf(self, *args) def get_pixel_coordinates(self, *args): """ Returns : double coordinate1,double coordinate2,double coordinate3 *args : double index1,double index2 C prototype: int cbf_get_pixel_coordinates (cbf_detector detector, double indexslow, double indexfast, double *coordinate1, double *coordinate2, double *coordinate3); CBFLib documentation: DESCRIPTION cbf_get_pixel_coordinates, cbf_get_pixel_coordinates_fs and cbf_get_pixel_coordinates_sf ses *coordinate1, *coordinate2, and *coordinate3 to the vector position of pixel (indexfast, indexslow) on the detector surface. If indexslow and indexfast are integers then the coordinates correspond to the center of a pixel. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. indexslow Slow index. indexfast Fast index. coordinate1 Pointer to the destination x component. coordinate2 Pointer to the destination y component. coordinate3 Pointer to the destination z component. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_detector_struct_get_pixel_coordinates(self, *args) def get_beam_center_sf(self): """ Returns : double indexslow,double indexfast,double centerslow,double centerfast *args : C prototype: int cbf_get_beam_center_sf (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast); CBFLib documentation: DESCRIPTION cbf_get_beam_center sets *centerfast and *centerslow to the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector and *indexfast and *indexslow to the corresponding indices. cbf_set_beam_center sets the offsets in the axis category for the detector element axis with precedence 1 to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given *indexfast and *indexslow. cbf_set_reference_beam_center sets the displacments in the array_structure_list_axis category to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given by *indexfast and *indexslow. In order to achieve consistent results, a reference detector should be used for detector to have all axes at their reference settings. Note that the precedence 1 axis is the fastest axis, so that *centerfast and *indexfast are the fast axis components of the center and *centerslow and *indexslow are the slow axis components of the center. The _fs calls give the displacments in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the displacements in slow-to-fast order Any of the destination pointers may be NULL for getting the beam center. For setting the beam axis, either the indices of the center must not be NULL. The indices are non-negative for beam centers within the detector surface, but the center for an axis with a negative increment will be negative for a beam center within the detector surface. For cbf_set_beam_center if the diffrn_data_frame category exists with a row for the corresponding element id, the values will be set for _diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in millimetres and the value of _diffrn_data_frame.center_units will be set to 'mm'. For cbf_set_reference_beam_center if the diffrn_detector_element category exists with a row for the corresponding element id, the values will be set for _diffrn_detector_element.reference_center_fast and _diffrn_detector_element.reference_center_slow in millimetres and the value of _diffrn_detector_element.reference_units will be set to 'mm'. ARGUMENTS detector Detector handle. indexfast Pointer to the destination fast index. indexslow Pointer to the destination slow index. centerfast Pointer to the destination displacement along the fast axis. centerslow Pointer to the destination displacement along the slow axis. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_detector_struct_get_beam_center_sf(self) def get_pixel_area_sf(self, *args): """ Returns : double area,double projected_area *args : double indexslow,double indexfast C prototype: int cbf_get_pixel_area_sf(cbf_detector detector, double indexslow, double indexfast, double *area, double *projected_area); CBFLib documentation: DESCRIPTION cbf_get_pixel_area, cbf_get_pixel_area_fs and cbf_get_pixel_area_sf set *area to the area of the pixel at (indexfast, indexslow) on the detector surface and *projected_area to the apparent area of the pixel as viewed from the sample position, with indexslow being the slow axis and indexfast being the fast axis. Either of the destination pointers may be NULL. ARGUMENTS detector Detector handle. indexfast Fast index. indexslow Slow index. area Pointer to the destination area in mm2. projected_area Pointer to the destination apparent area in mm2. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_detector_struct_get_pixel_area_sf(self, *args) def get_beam_center(self): """ Returns : double index1,double index2,double center1,double center2 *args : C prototype: int cbf_get_beam_center (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast); CBFLib documentation: DESCRIPTION cbf_get_beam_center sets *centerfast and *centerslow to the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector and *indexfast and *indexslow to the corresponding indices. cbf_set_beam_center sets the offsets in the axis category for the detector element axis with precedence 1 to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given *indexfast and *indexslow. cbf_set_reference_beam_center sets the displacments in the array_structure_list_axis category to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given by *indexfast and *indexslow. In order to achieve consistent results, a reference detector should be used for detector to have all axes at their reference settings. Note that the precedence 1 axis is the fastest axis, so that *centerfast and *indexfast are the fast axis components of the center and *centerslow and *indexslow are the slow axis components of the center. The _fs calls give the displacments in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the displacements in slow-to-fast order Any of the destination pointers may be NULL for getting the beam center. For setting the beam axis, either the indices of the center must not be NULL. The indices are non-negative for beam centers within the detector surface, but the center for an axis with a negative increment will be negative for a beam center within the detector surface. For cbf_set_beam_center if the diffrn_data_frame category exists with a row for the corresponding element id, the values will be set for _diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in millimetres and the value of _diffrn_data_frame.center_units will be set to 'mm'. For cbf_set_reference_beam_center if the diffrn_detector_element category exists with a row for the corresponding element id, the values will be set for _diffrn_detector_element.reference_center_fast and _diffrn_detector_element.reference_center_slow in millimetres and the value of _diffrn_detector_element.reference_units will be set to 'mm'. ARGUMENTS detector Detector handle. indexfast Pointer to the destination fast index. indexslow Pointer to the destination slow index. centerfast Pointer to the destination displacement along the fast axis. centerslow Pointer to the destination displacement along the slow axis. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_detector_struct_get_beam_center(self) def set_reference_beam_center_sf(self): """ Returns : *args : double indexslow,double indexfast,double centerslow,double centerfast C prototype: int cbf_set_reference_beam_center_sf (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast); CBFLib documentation: DESCRIPTION cbf_get_beam_center sets *centerfast and *centerslow to the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector and *indexfast and *indexslow to the corresponding indices. cbf_set_beam_center sets the offsets in the axis category for the detector element axis with precedence 1 to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given *indexfast and *indexslow. cbf_set_reference_beam_center sets the displacments in the array_structure_list_axis category to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given by *indexfast and *indexslow. In order to achieve consistent results, a reference detector should be used for detector to have all axes at their reference settings. Note that the precedence 1 axis is the fastest axis, so that *centerfast and *indexfast are the fast axis components of the center and *centerslow and *indexslow are the slow axis components of the center. The _fs calls give the displacments in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the displacements in slow-to-fast order Any of the destination pointers may be NULL for getting the beam center. For setting the beam axis, either the indices of the center must not be NULL. The indices are non-negative for beam centers within the detector surface, but the center for an axis with a negative increment will be negative for a beam center within the detector surface. For cbf_set_beam_center if the diffrn_data_frame category exists with a row for the corresponding element id, the values will be set for _diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in millimetres and the value of _diffrn_data_frame.center_units will be set to 'mm'. For cbf_set_reference_beam_center if the diffrn_detector_element category exists with a row for the corresponding element id, the values will be set for _diffrn_detector_element.reference_center_fast and _diffrn_detector_element.reference_center_slow in millimetres and the value of _diffrn_detector_element.reference_units will be set to 'mm'. ARGUMENTS detector Detector handle. indexfast Pointer to the destination fast index. indexslow Pointer to the destination slow index. centerfast Pointer to the destination displacement along the fast axis. centerslow Pointer to the destination displacement along the slow axis. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_detector_struct_set_reference_beam_center_sf(self) def set_beam_center_sf(self): """ Returns : *args : double indexslow,double indexfast,double centerslow,double centerfast C prototype: int cbf_set_beam_center_sf (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast); CBFLib documentation: DESCRIPTION cbf_get_beam_center sets *centerfast and *centerslow to the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector and *indexfast and *indexslow to the corresponding indices. cbf_set_beam_center sets the offsets in the axis category for the detector element axis with precedence 1 to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given *indexfast and *indexslow. cbf_set_reference_beam_center sets the displacments in the array_structure_list_axis category to place the beam center at the position given in mm by *centerfast and *centerslow as the displacements in mm along the detector axes from pixel (0, 0) to the point at which the beam intersects the detector at the indices given by *indexfast and *indexslow. In order to achieve consistent results, a reference detector should be used for detector to have all axes at their reference settings. Note that the precedence 1 axis is the fastest axis, so that *centerfast and *indexfast are the fast axis components of the center and *centerslow and *indexslow are the slow axis components of the center. The _fs calls give the displacments in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the displacements in slow-to-fast order Any of the destination pointers may be NULL for getting the beam center. For setting the beam axis, either the indices of the center must not be NULL. The indices are non-negative for beam centers within the detector surface, but the center for an axis with a negative increment will be negative for a beam center within the detector surface. For cbf_set_beam_center if the diffrn_data_frame category exists with a row for the corresponding element id, the values will be set for _diffrn_data_frame.center_fast and _diffrn_data_frame.center_slow in millimetres and the value of _diffrn_data_frame.center_units will be set to 'mm'. For cbf_set_reference_beam_center if the diffrn_detector_element category exists with a row for the corresponding element id, the values will be set for _diffrn_detector_element.reference_center_fast and _diffrn_detector_element.reference_center_slow in millimetres and the value of _diffrn_detector_element.reference_units will be set to 'mm'. ARGUMENTS detector Detector handle. indexfast Pointer to the destination fast index. indexslow Pointer to the destination slow index. centerfast Pointer to the destination displacement along the fast axis. centerslow Pointer to the destination displacement along the slow axis. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_detector_struct_set_beam_center_sf(self) def get_pixel_normal(self, *args): """ Returns : double normal1,double normal2,double normal3 *args : double index1,double index2 C prototype: int cbf_get_pixel_normal (cbf_detector detector, double indexslow, double indexfast, double *normal1, double *normal2, double *normal3); CBFLib documentation: DESCRIPTION cbf_get_detector_normal, cbf_get_pixel_normal_fs and cbf_get_pixel_normal_sf set *normal1, *normal2, and *normal3 to the 3 components of the of the normal vector to the pixel at (indexfast, indexslow). The vector is normalized. Any of the destination pointers may be NULL. ARGUMENTS detector Detector handle. indexslow Slow index. indexfast Fast index. normal1 Pointer to the destination x component of the normal vector. normal2 Pointer to the destination y component of the normal vector. normal3 Pointer to the destination z component of the normal vector. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_detector_struct_get_pixel_normal(self, *args) cbf_detector_struct_swigregister = _pycbf.cbf_detector_struct_swigregister cbf_detector_struct_swigregister(cbf_detector_struct) CBF_UNDEFNODE = _pycbf.CBF_UNDEFNODE CBF_LINK = _pycbf.CBF_LINK CBF_ROOT = _pycbf.CBF_ROOT CBF_DATABLOCK = _pycbf.CBF_DATABLOCK CBF_SAVEFRAME = _pycbf.CBF_SAVEFRAME CBF_CATEGORY = _pycbf.CBF_CATEGORY CBF_COLUMN = _pycbf.CBF_COLUMN class cbf_handle_struct(_object): """Proxy of C cbf_handle_struct struct""" __swig_setmethods__ = {} __setattr__ = lambda self, name, value: _swig_setattr(self, cbf_handle_struct, name, value) __swig_getmethods__ = {} __getattr__ = lambda self, name: _swig_getattr(self, cbf_handle_struct, name) __repr__ = _swig_repr __swig_setmethods__["node"] = _pycbf.cbf_handle_struct_node_set __swig_getmethods__["node"] = _pycbf.cbf_handle_struct_node_get if _newclass:node = _swig_property(_pycbf.cbf_handle_struct_node_get, _pycbf.cbf_handle_struct_node_set) __swig_setmethods__["row"] = _pycbf.cbf_handle_struct_row_set __swig_getmethods__["row"] = _pycbf.cbf_handle_struct_row_get if _newclass:row = _swig_property(_pycbf.cbf_handle_struct_row_get, _pycbf.cbf_handle_struct_row_set) __swig_setmethods__["search_row"] = _pycbf.cbf_handle_struct_search_row_set __swig_getmethods__["search_row"] = _pycbf.cbf_handle_struct_search_row_get if _newclass:search_row = _swig_property(_pycbf.cbf_handle_struct_search_row_get, _pycbf.cbf_handle_struct_search_row_set) def __init__(self): """__init__(self) -> cbf_handle_struct""" this = _pycbf.new_cbf_handle_struct() try: self.this.append(this) except: self.this = this __swig_destroy__ = _pycbf.delete_cbf_handle_struct __del__ = lambda self : None; def select_datablock(self, *args): """ Returns : *args : Integer C prototype: int cbf_select_datablock (cbf_handle handle, unsigned int datablock); CBFLib documentation: DESCRIPTION cbf_select_datablock selects data block number datablock as the current data block. The first data block is number 0. If the data block does not exist, the function returns CBF_NOTFOUND. ARGUMENTS handle CBF handle. datablock Number of the data block to select. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_select_datablock(self, *args) def force_new_datablock(self, *args): """ Returns : string *args : C prototype: int cbf_force_new_datablock (cbf_handle handle, const char *datablockname); CBFLib documentation: DESCRIPTION cbf_force_new_datablock creates a new data block with name datablockname and makes it the current data block. Duplicate data block names are allowed. cbf_force_new_saveframe creates a new savew frame with name saveframename and makes it the current save frame. Duplicate save frame names are allowed. Even if a save frame with this name already exists, a new save frame is created and becomes the current save frame. ARGUMENTS handle CBF handle. datablockname The name of the new data block. saveframename The name of the new save frame. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_force_new_datablock(self, *args) def get_3d_image_fs_as_string(self, *args): """ Returns : (Binary)String *args : int element_number,int elsize,int elsign,int ndimfast,int ndimmid, int ndimslow C prototype: int cbf_get_3d_image_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimfast, size_t ndimmid, size_t ndimslow); CBFLib documentation: DESCRIPTION cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image array for element number element_number into an array. The array consists of ndimslow *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and cbf_get_real_image_sf read the image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. cbf_get_3d_image, cbf_get_3d_image_fs and cbf_get_3d_image_sf read the 3D image array for element number element_number into an array. The array consists of ndimslow *ndimmid *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order The structure of the array as a 1-, 2- or 3-dimensional array should agree with the structure of the array given in the ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1 both in the call and in the imgCIF data being processed. If the array is 2-dimensional and a 3D call is used, ndimslow and ndimmid should be the """ return _pycbf.cbf_handle_struct_get_3d_image_fs_as_string(self, *args) def reset_datablocks(self, *args): """ Returns : *args : C prototype: int cbf_reset_datablocks (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_reset_datablocks deletes all categories from all data blocks. The current data block does not change. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_reset_datablocks(self, *args) def set_tag_category(self, *args): """ Returns : *args : String tagname,String categoryname_in C prototype: int cbf_set_tag_category (cbf_handle handle, const char* tagname, const char* categoryname_in); CBFLib documentation: DESCRIPTION cbf_find_tag_category sets categoryname to the category associated with tagname in the dictionary associated with handle. cbf_set_tag_category upddates the dictionary associated with handle to indicated that tagname is in category categoryname_in. ARGUMENTS handle CBF handle. tagname tag name. categoryname pointer to a returned category name. categoryname_in input category name. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_tag_category(self, *args) def require_tag_root(self, *args): """ Returns : String tagroot *args : String tagname C prototype: int cbf_require_tag_root (cbf_handle handle, const char* tagname, const char** tagroot); CBFLib documentation: DESCRIPTION cbf_find_tag_root sets *tagroot to the root tag of which tagname is an alias. cbf_set_tag_root sets tagname as an alias of tagroot_in in the dictionary associated with handle, creating the dictionary if necessary. cbf_require_tag_root sets *tagroot to the root tag of which tagname is an alias, if there is one, or to the value of tagname, if tagname is not an alias. A returned tagroot string must not be modified in any way. ARGUMENTS handle CBF handle. tagname tag name which may be an alias. tagroot pointer to a returned tag root name. tagroot_in input tag root name. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_require_tag_root(self, *args) def row_number(self, *args): """ Returns : Integer *args : C prototype: int cbf_row_number (cbf_handle handle, unsigned int *row); CBFLib documentation: DESCRIPTION cbf_row_number sets *row to the number of the current row of the current category. ARGUMENTS handle CBF handle. row Pointer to the destination row number. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_row_number(self, *args) def set_image(self, *args): """ Returns : *args : int element_number,int compression,(binary) String data,int elsize, int elsign,int dimslow,int dimfast C prototype: int cbf_set_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-zero and unsigned otherwise. cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow IEEE double or float elements of elsize bytes each, starting at array. cbf_set_3d_image, cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_set_real_3d_image, cbf_set_real_3d_image_fs and cbf_set_real_3d_image_sf writes the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow IEEE double or float elements of elsize bytes each, starting at array. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the array is 2-dimensional and the 3D calls are used, ndimslow and ndimmid should be used for the array dimensions and ndimfast should be set to 1. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple "byte_offset " compression. CBF_NONE No compression. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned)for cbf_set_image, or IEEE doubles or floats for cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame " category. compression Compression type. array Pointer to the image array. elsize Size in bytes of each image array element. elsigned Set to non-0 if the image array elements are signed. ndimslow Slowest array dimension. ndimmid Second slowest array dimension. ndimfast Fastest array dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_image(self, *args) def set_bin_sizes(self, *args): """ Returns : *args : Integer element_number,Float slowbinsize_in,Float fastbinsize_in C prototype: int cbf_set_bin_sizes(cbf_handle handle, unsigned int element_number, double slowbinsize_in, double fastbinsize_in); CBFLib documentation: DESCRIPTION cbf_get_bin_sizes sets slowbinsize to point to the value of the number of pixels composing one array element in the dimension that changes at the second-fastest rate and fastbinsize to point to the value of the number of pixels composing one array element in the dimension that changes at the fastest rate for the dectector element with the ordinal element_number. cbf_set_bin_sizes sets the the pixel bin sizes in the "array_intensities " category to the values of slowbinsize_in for the number of pixels composing one array element in the dimension that changes at the second-fastest rate and fastbinsize_in for the number of pixels composing one array element in the dimension that changes at the fastest rate for the dectector element with the ordinal element_number. In order to allow for software binning involving fractions of pixels, the bin sizes are doubles rather than ints. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame " category. slowbinsize Pointer to the returned number of pixels composing one array element in the dimension that changes at the second-fastest rate. fastbinsize Pointer to the returned number of pixels composing one array element in the dimension that changes at the fastest rate. slowbinsize_in The number of pixels composing one array element in the dimension that changes at the second-fastest rate. fastbinsize_in The number of pixels composing one array element in the dimension that changes at the fastest rate. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_bin_sizes(self, *args) def new_row(self, *args): """ Returns : *args : C prototype: int cbf_new_row (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_new_row adds a new row to the current category and makes it the current row. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_new_row(self, *args) def rewind_saveframe(self, *args): """ Returns : *args : C prototype: int cbf_rewind_saveframe (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_rewind_category makes the first category in the current data block the current category. cbf_rewind_saveframe makes the first saveframe in the current data block the current saveframe. cbf_rewind_blockitem makes the first blockitem (category or saveframe) in the current data block the current blockitem. The type of the blockitem (CBF_CATEGORY or CBF_SAVEFRAME) is returned in type. If there are no categories, saveframes or blockitems the function returns CBF_NOTFOUND. The current column and row become undefined. ARGUMENTS handle CBF handle. type CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_rewind_saveframe(self, *args) def get_realarrayparameters(self): """ Returns : int compression,int binary_id,int elsize,int elements *args : C prototype: int cbf_get_realarrayparameters (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, size_t *elements); CBFLib documentation: DESCRIPTION cbf_get_integerarrayparameters sets *compression, *binary_id, *elsize, *elsigned, *elunsigned, *elements, *minelement and *maxelement to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_integerarray, if a copy of the array is to be made into another CIF or CBF. cbf_get_realarrayparameters sets *compression, *binary_id, *elsize, *elements to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_realarray, if a copy of the arry is to be made into another CIF or CBF. The variants cbf_get_integerarrayparameters_wdims, cbf_get_integerarrayparameters_wdims_fs, cbf_get_integerarrayparameters_wdims_sf, cbf_get_realarrayparameters_wdims, cbf_get_realarrayparameters_wdims_fs, cbf_get_realarrayparameters_wdims_sf set **byteorder, *dimfast, *dimmid, *dimslow, and *padding as well, providing the additional parameters needed for a subsequent call to cbf_set_integerarray_wdims or cbf_set_realarray_wdims. The value returned in *byteorder is a pointer either to the string "little_endian " or to the string "big_endian ". This should be the byte order of the data, not necessarily of the host machine. No attempt should be made to modify this string. At this time only "little_endian " will be returned. The values returned in *dimfast, *dimmid and *dimslow are the sizes of the fastest changing, second fastest changing and third fastest changing dimensions of the array, if specified, or zero, if not specified. The value returned in *padding is the size of the post-data padding, if any and if specified in the data header. The value is given as a count of octets. If the value is not binary, the function returns CBF_ASCII. ARGUMENTS handle CBF handle. compression Compression method used. elsize Size in bytes of each array element. binary_id Pointer to the destination integer binary identifier. elsigned Pointer to an integer. Set to 1 if the elements can be read as signed integers. elunsigned Pointer to an integer. Set to 1 if the elements can be read as unsigned integers. elements Pointer to the destination number of elements. minelement Pointer to the destination smallest element. maxelement Pointer to the destination largest element. byteorder Pointer to the destination byte order. dimfast Pointer to the destination fastest dimension. dimmid Pointer to the destination second fastest dimension. dimslow Pointer to the destination third fastest dimension. padding Pointer to the destination padding size. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_get_realarrayparameters(self) def get_pixel_size_sf(self, *args): """ Returns : Float pixel_size *args : Int element_number,Int axis_number C prototype: int cbf_get_pixel_size_sf(cbf_handle handle, unsigned int element_number, int axis_number, double *psize); CBFLib documentation: DESCRIPTION cbf_get_pixel_size and cbf_get_pixel_size_sf set *psize to point to the double value in millimeters of the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the slowest axis. cbf_get_pixel_size_fs sets *psize to point to the double value in millimeters of the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the fastest axis. If a negative axis number is given, the order of axes is reversed, so that -1 specifies the slowest axis for cbf_get_pixel_size_fs and the fastest axis for cbf_get_pixel_size_sf. If the pixel size is not given explcitly in the "array_element_size " category, the function returns CBF_NOTFOUND. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame " category. axis_number The number of the axis, starting from 1 for the fastest for cbf_get_pixel_size and cbf_get_pixel_size_fs and the slowest for cbf_get_pixel_size_sf. psize Pointer to the destination pixel size. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_get_pixel_size_sf(self, *args) def force_new_category(self, *args): """ Returns : string *args : C prototype: int cbf_force_new_category (cbf_handle handle, const char *categoryname); CBFLib documentation: DESCRIPTION cbf_force_new_category creates a new category in the current data block with name categoryname and makes it the current category. Duplicate category names are allowed. Even if a category with this name already exists, a new category of the same name is created and becomes the current category. The allows for the creation of unlooped tag/value lists drawn from the same category. ARGUMENTS handle CBF handle. categoryname The name of the new category. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_force_new_category(self, *args) def force_new_saveframe(self, *args): """ Returns : string *args : C prototype: int cbf_force_new_saveframe (cbf_handle handle, const char *saveframename); CBFLib documentation: DESCRIPTION cbf_force_new_datablock creates a new data block with name datablockname and makes it the current data block. Duplicate data block names are allowed. cbf_force_new_saveframe creates a new savew frame with name saveframename and makes it the current save frame. Duplicate save frame names are allowed. Even if a save frame with this name already exists, a new save frame is created and becomes the current save frame. ARGUMENTS handle CBF handle. datablockname The name of the new data block. saveframename The name of the new save frame. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_force_new_saveframe(self, *args) def count_datablocks(self, *args): """ Returns : Integer *args : C prototype: int cbf_count_datablocks (cbf_handle handle, unsigned int *datablocks); CBFLib documentation: DESCRIPTION cbf_count_datablocks puts the number of data blocks in *datablocks . ARGUMENTS handle CBF handle. datablocks Pointer to the destination data block count. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_count_datablocks(self, *args) def find_row(self, *args): """ Returns : string *args : C prototype: int cbf_find_row (cbf_handle handle, const char *value); CBFLib documentation: DESCRIPTION cbf_find_row makes the first row in the current column with value value the current row. The comparison is case-sensitive. If a matching row does not exist, the function returns CBF_NOTFOUND. The current column is not affected. ARGUMENTS handle CBF handle. value The value of the row to find. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_find_row(self, *args) def select_column(self, *args): """ Returns : *args : Integer C prototype: int cbf_select_column (cbf_handle handle, unsigned int column); CBFLib documentation: DESCRIPTION cbf_select_column selects column number column in the current category as the current column. The first column is number 0. The current row is not affected If the column does not exist, the function returns CBF_NOTFOUND. ARGUMENTS handle CBF handle. column Number of the column to select. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_select_column(self, *args) def construct_detector(self, *args): """ Returns : pycbf detector object *args : Integer element_number C prototype: int cbf_construct_detector (cbf_handle handle, cbf_detector *detector, unsigned int element_number); CBFLib documentation: DESCRIPTION cbf_construct_detector constructs a detector object for detector element number element_number using the description in the CBF object handle and initialises the detector handle *detector. cbf_construct_reference_detector constructs a detector object for detector element number element_number using the description in the CBF object handle and initialises the detector handle *detector using the reference settings of the axes. cbf_require_reference_detector is similar, but try to force the creations of missing intermediate categories needed to construct a detector object. ARGUMENTS handle CBF handle. detector Pointer to the destination detector handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame " category. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_construct_detector(self, *args) def rewind_column(self, *args): """ Returns : *args : C prototype: int cbf_rewind_column (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_rewind_column makes the first column in the current category the current column. If there are no columns, the function returns CBF_NOTFOUND. The current row is not affected. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_rewind_column(self, *args) def require_column_doublevalue(self, *args): """ Returns : Float defaultvalue *args : String columnname,Float Value C prototype: int cbf_require_column_doublevalue (cbf_handle handle, const char *columnname, double *number, const double defaultvalue); CBFLib documentation: DESCRIPTION cbf_require_column_doublevalue sets *number to the value of the ASCII item at the current row for the column given with the name given by *columnname, with the value interpreted as a decimal floating-point number, or to the number given by defaultvalue if the item cannot be found. ARGUMENTS handle CBF handle. columnname Name of the column containing the number. number pointer to the location to receive the floating-point value. defaultvalue Value to use if the requested column and value cannot be found. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_require_column_doublevalue(self, *args) def get_datestamp(self): """ Returns : int year,int month,int day,int hour,int minute,double second, int timezone *args : C prototype: int cbf_get_datestamp (cbf_handle handle, unsigned int reserved, int *year, int *month, int *day, int *hour, int *minute, double *second, int *timezone); CBFLib documentation: DESCRIPTION cbf_get_datestamp sets *year, *month, *day, *hour, *minute and *second to the corresponding values of the collection timestamp. *timezone is set to timezone difference from UTC in minutes. The parameter < i>reserved is presently unused and should be set to 0. Any of the destination pointers may be NULL. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. year Pointer to the destination timestamp year. month Pointer to the destination timestamp month (1-12). day Pointer to the destination timestamp day (1-31). hour Pointer to the destination timestamp hour (0-23). minute Pointer to the destination timestamp minute (0-59). second Pointer to the destination timestamp second (0-60.0). timezone Pointer to the destination timezone difference from UTC in minutes. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_get_datestamp(self) def get_integervalue(self, *args): """ Returns : int *args : C prototype: int cbf_get_integervalue (cbf_handle handle, int *number); CBFLib documentation: DESCRIPTION cbf_get_integervalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal integer. cbf_require_integervalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal integer, setting it to defaultvalue if necessary. If the value is not ASCII, the function returns CBF_BINARY. ARGUMENTS handle CBF handle. number pointer to the number. defaultvalue default number value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_get_integervalue(self, *args) def get_crystal_id(self, *args): """ Returns : *args : string C prototype: int cbf_get_crystal_id (cbf_handle handle, const char **crystal_id); CBFLib documentation: DESCRIPTION cbf_get_crystal_id sets *crystal_id to point to the ASCII value of the "diffrn.crystal_id " entry. If the value is not ASCII, the function returns CBF_BINARY. The value will be valid as long as the item exists and has not been set to a new value. The value must not be modified by the program in any way. ARGUMENTS handle CBF handle. crystal_id Pointer to the destination value pointer. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_get_crystal_id(self, *args) def get_doublevalue(self, *args): """ Returns : double *args : C prototype: int cbf_get_doublevalue (cbf_handle handle, double *number); CBFLib documentation: DESCRIPTION cbf_get_doublevalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal floating-point number. cbf_require_doublevalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal floating-point number, setting it to defaultvalue if necessary. If the value is not ASCII, the function returns CBF_BINARY. ARGUMENTS handle CBF handle. number Pointer to the destination number. defaultvalue default number value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_get_doublevalue(self, *args) def get_unit_cell(self): """ Returns : Float a,Float b,Float c,Float alpha,Float beta,Float gamma *args : C prototype: int cbf_get_unit_cell (cbf_handle handle, double cell[6], double cell_esd[6] ); CBFLib documentation: DESCRIPTION cbf_get_unit_cell sets cell[0:2] to the double values of the cell edge lengths a, b and c in AAngstroms, cell[3:5] to the double values of the cell angles a, b and g in degrees, cell_esd[0:2] to the double values of the estimated strandard deviations of the cell edge lengths a, b and c in AAngstroms, cell_esd[3:5] to the double values of the estimated standard deviations of the the cell angles a, b and g in degrees. The values returned are retrieved from the first row of the "cell " category. The value of "_cell.entry_id " is ignored. cell or cell_esd may be NULL. If cell is NULL, the cell parameters are not retrieved. If cell_esd is NULL, the cell parameter esds are not retrieved. If the "cell " category is present, but some of the values are missing, zeros are returned for the missing values. ARGUMENTS handle CBF handle. cell Pointer to the destination array of 6 doubles for the cell parameters. cell_esd Pointer to the destination array of 6 doubles for the cell parameter esds. RETURN VALUE Returns an error code on failure or 0 for success. No errors is returned for missing values if the "cell " category exists. SEE ALSO """ return _pycbf.cbf_handle_struct_get_unit_cell(self) def get_unit_cell_esd(self): """get_unit_cell_esd(self)""" return _pycbf.cbf_handle_struct_get_unit_cell_esd(self) def remove_column(self, *args): """ Returns : *args : C prototype: int cbf_remove_column (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_remove_column deletes the current column. The current column becomes undefined. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_remove_column(self, *args) def rewind_blockitem(self, *args): """ Returns : CBF_NODETYPE *args : C prototype: int cbf_rewind_blockitem (cbf_handle handle, CBF_NODETYPE * type); CBFLib documentation: DESCRIPTION cbf_rewind_category makes the first category in the current data block the current category. cbf_rewind_saveframe makes the first saveframe in the current data block the current saveframe. cbf_rewind_blockitem makes the first blockitem (category or saveframe) in the current data block the current blockitem. The type of the blockitem (CBF_CATEGORY or CBF_SAVEFRAME) is returned in type. If there are no categories, saveframes or blockitems the function returns CBF_NOTFOUND. The current column and row become undefined. ARGUMENTS handle CBF handle. type CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_rewind_blockitem(self, *args) def get_value(self, *args): """ Returns : *args : string C prototype: int cbf_get_value (cbf_handle handle, const char **value); CBFLib documentation: DESCRIPTION cbf_get_value sets *value to point to the ASCII value of the item at the current column and row. cbf_require_value sets *value to point to the ASCII value of the item at the current column and row, creating the data item if necessary and initializing it to a copy of defaultvalue. If the value is not ASCII, the function returns CBF_BINARY. The value will be valid as long as the item exists and has not been set to a new value. The value must not be modified by the program in any way. ARGUMENTS handle CBF handle. value Pointer to the destination value pointer. defaultvalue Default value character string. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_get_value(self, *args) def count_categories(self, *args): """ Returns : Integer *args : C prototype: int cbf_count_categories (cbf_handle handle, unsigned int *categories); CBFLib documentation: DESCRIPTION cbf_count_categories puts the number of categories in the current data block in *categories. ARGUMENTS handle CBF handle. categories Pointer to the destination category count. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_count_categories(self, *args) def read_widefile(self, *args): """ Returns : *args : String filename,Integer headers C prototype: int cbf_read_widefile (cbf_handle handle, FILE *file, int flags); CBFLib documentation: DESCRIPTION cbf_read_file reads the CBF or CIF file file into the CBF object specified by handle, using the CIF 1.0 convention of 80 character lines. cbf_read_widefile reads the CBF or CIF file file into the CBF object specified by handle, using the CIF 1.1 convention of 2048 character lines. A warning is issued to stderr for ascii lines over the limit. No test is performed on binary sections. Validation is performed in three ways levels: during the lexical scan, during the parse, and, if a dictionary was converted, against the value types, value enumerations, categories and parent-child relationships specified in the dictionary. flags controls the interpretation of binary section headers, the parsing of brackets constructs and the parsing of treble-quoted strings. MSG_DIGEST: Instructs CBFlib to check that the digest of the binary section matches any header digest value. If the digests do not match, the call will return CBF_FORMAT. This evaluation and comparison is delayed (a "lazy " evaluation) to ensure maximal processing efficiency. If an immediately evaluation is required, see MSG_DIGESTNOW, below. MSG_DIGESTNOW: Instructs CBFlib to check that the digest of the binary section matches any header digeste value. If the digests do not match, the call will return CBF_FORMAT. This evaluation and comparison is performed during initial parsing of the section to ensure timely error reporting at the expense of processing efficiency. If a more efficient delayed ( "lazy ") evaluation is required, see MSG_DIGEST, above. MSG_DIGESTWARN: Instructs CBFlib to check that the digest of the binary section matches any header digeste value. If the digests do not match, a warning message will be sent to stderr, but processing will attempt to continue. This evaluation and comparison is first performed during initial parsing of the section to ensure timely error reporting at the expense of processing efficiency. An mismatch of the message digest usually indicates a serious error, but it is sometimes worth continuing processing to try to isolate the cause of the error. Use this option with caution. MSG_NODIGEST: Do not check the digest (default). PARSE_BRACKETS: Accept DDLm bracket-delimited [item,item,...item] or {item,item,...item} or (item,item,...item) constructs as valid, stripping non-quoted embedded whitespace and comments. These constructs may span multiple lines. PARSE_LIBERAL_BRACKETS: Accept DDLm bracket-delimited [item,item,...item] or {item,item,...item} or (item,item,...item) constructs as valid, stripping embedded non-quoted, non-separating whitespace and comments. These constructs may span multiple lines. In this case, whitespace may be used as an alternative to the comma. PARSE_TRIPLE_QUOTES: Accept DDLm triple-quoted " " "item,item,...item " " " or '''item,item,...item''' constructs as valid, stripping embedded whitespace and comments. These constructs may span multiple lines. If this flag is set, then ''' will not be interpreted as a quoted apoptrophe and " " " will not be interpreted as a quoted double quote mark and PARSE_NOBRACKETS: Do not accept DDLm bracket-delimited [item,item,...item] or {item,item,...item} or (item,item,...item) constructs as valid, stripping non-quoted embedded whitespace and comments. These constructs may span multiple lines. PARSE_NOTRIPLE_QUOTES: No not accept DDLm triple-quoted " " "item,item,...item " " " or '''item,item,...item''' constructs as valid, stripping embedded whitespace and comments. These constructs may span multiple lines. If this flag is set, then ''' will be interpreted as a quoted apostrophe and " " " will be interpreted as a quoted double quote mark. CBFlib defers reading binary sections as long as possible. In the current version of CBFlib, this means that: 1. The file must be a random-access file opened in binary mode (fopen ( , """ return _pycbf.cbf_handle_struct_read_widefile(self, *args) def set_wavelength(self, *args): """ Returns : double wavelength *args : C prototype: int cbf_set_wavelength (cbf_handle handle, double wavelength); CBFLib documentation: DESCRIPTION cbf_set_wavelength sets the current wavelength in AA to wavelength. ARGUMENTS handle CBF handle. wavelength Wavelength in AA. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_wavelength(self, *args) def set_pixel_size_sf(self, *args): """ Returns : *args : Int element_number,Int axis_number,Float pixel size C prototype: int cbf_set_pixel_size_sf(cbf_handle handle, unsigned int element_number, int axis_number, double psize); CBFLib documentation: DESCRIPTION cbf_set_pixel_size and cbf_set_pixel_size_sf set the item in the "e;size"e; column of the "array_structure_list " category at the row which matches axis axis_number of the detector element element_number converting the double pixel size psize from meters to millimeters in storing it in the "size " column for the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the slowest axis. cbf_set_pixel_size_fs sets the item """ return _pycbf.cbf_handle_struct_set_pixel_size_sf(self, *args) def get_diffrn_id(self, *args): """ Returns : *args : string C prototype: int cbf_get_diffrn_id (cbf_handle handle, const char **diffrn_id); CBFLib documentation: DESCRIPTION cbf_get_diffrn_id sets *diffrn_id to point to the ASCII value of the "diffrn.id " entry. cbf_require_diffrn_id also sets *diffrn_id to point to the ASCII value of the "diffrn.id " entry, but, if the "diffrn.id " entry does not exist, it sets the value in the CBF and in*diffrn_id to the character string given by default_id, creating the category and column is necessary. The diffrn_id will be valid as long as the item exists and has not been set to a new value. The diffrn_id must not be modified by the program in any way. ARGUMENTS handle CBF handle. diffrn_id Pointer to the destination value pointer. default_id Character string default value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_get_diffrn_id(self, *args) def find_datablock(self, *args): """ Returns : string *args : C prototype: int cbf_find_datablock (cbf_handle handle, const char *datablockname); CBFLib documentation: DESCRIPTION cbf_find_datablock makes the data block with name datablockname the current data block. The comparison is case-insensitive. If the data block does not exist, the function returns CBF_NOTFOUND. The current category becomes undefined. ARGUMENTS handle CBF handle. datablockname The name of the data block to find. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_find_datablock(self, *args) def get_polarization(self): """ Returns : float polarizn_source_ratio,float polarizn_source_norm *args : C prototype: int cbf_get_polarization (cbf_handle handle, double *polarizn_source_ratio, double *polarizn_source_norm); CBFLib documentation: DESCRIPTION cbf_get_polarization sets *polarizn_source_ratio and *polarizn_source_norm to the corresponding source polarization parameters. Either destination pointer may be NULL. ARGUMENTS handle CBF handle. polarizn_source_ratio Pointer to the destination polarizn_source_ratio. polarizn_source_norm Pointer to the destination polarizn_source_norm. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_get_polarization(self) def select_category(self, *args): """ Returns : *args : Integer C prototype: int cbf_select_category (cbf_handle handle, unsigned int category); CBFLib documentation: DESCRIPTION cbf_select_category selects category number category in the current data block as the current category. The first category is number 0. The current column and row become undefined. If the category does not exist, the function returns CBF_NOTFOUND. ARGUMENTS handle CBF handle. category Number of the category to select. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_select_category(self, *args) def get_pixel_size_fs(self, *args): """ Returns : Float pixel_size *args : Int element_number,Int axis_number C prototype: int cbf_get_pixel_size_fs(cbf_handle handle, unsigned int element_number, int axis_number, double *psize); CBFLib documentation: DESCRIPTION cbf_get_pixel_size and cbf_get_pixel_size_sf set *psize to point to the double value in millimeters of the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the slowest axis. cbf_get_pixel_size_fs sets *psize to point to the double value in millimeters of the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the fastest axis. If a negative axis number is given, the order of axes is reversed, so that -1 specifies the slowest axis for cbf_get_pixel_size_fs and the fastest axis for cbf_get_pixel_size_sf. If the pixel size is not given explcitly in the "array_element_size " category, the function returns CBF_NOTFOUND. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame " category. axis_number The number of the axis, starting from 1 for the fastest for cbf_get_pixel_size and cbf_get_pixel_size_fs and the slowest for cbf_get_pixel_size_sf. psize Pointer to the destination pixel size. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_get_pixel_size_fs(self, *args) def read_file(self, *args): """ Returns : *args : String filename,Integer headers C prototype: int cbf_read_file (cbf_handle handle, FILE *file, int flags); CBFLib documentation: DESCRIPTION cbf_read_file reads the CBF or CIF file file into the CBF object specified by handle, using the CIF 1.0 convention of 80 character lines. cbf_read_widefile reads the CBF or CIF file file into the CBF object specified by handle, using the CIF 1.1 convention of 2048 character lines. A warning is issued to stderr for ascii lines over the limit. No test is performed on binary sections. Validation is performed in three ways levels: during the lexical scan, during the parse, and, if a dictionary was converted, against the value types, value enumerations, categories and parent-child relationships specified in the dictionary. flags controls the interpretation of binary section headers, the parsing of brackets constructs and the parsing of treble-quoted strings. MSG_DIGEST: Instructs CBFlib to check that the digest of the binary section matches any header digest value. If the digests do not match, the call will return CBF_FORMAT. This evaluation and comparison is delayed (a "lazy " evaluation) to ensure maximal processing efficiency. If an immediately evaluation is required, see MSG_DIGESTNOW, below. MSG_DIGESTNOW: Instructs CBFlib to check that the digest of the binary section matches any header digeste value. If the digests do not match, the call will return CBF_FORMAT. This evaluation and comparison is performed during initial parsing of the section to ensure timely error reporting at the expense of processing efficiency. If a more efficient delayed ( "lazy ") evaluation is required, see MSG_DIGEST, above. MSG_DIGESTWARN: Instructs CBFlib to check that the digest of the binary section matches any header digeste value. If the digests do not match, a warning message will be sent to stderr, but processing will attempt to continue. This evaluation and comparison is first performed during initial parsing of the section to ensure timely error reporting at the expense of processing efficiency. An mismatch of the message digest usually indicates a serious error, but it is sometimes worth continuing processing to try to isolate the cause of the error. Use this option with caution. MSG_NODIGEST: Do not check the digest (default). PARSE_BRACKETS: Accept DDLm bracket-delimited [item,item,...item] or {item,item,...item} or (item,item,...item) constructs as valid, stripping non-quoted embedded whitespace and comments. These constructs may span multiple lines. PARSE_LIBERAL_BRACKETS: Accept DDLm bracket-delimited [item,item,...item] or {item,item,...item} or (item,item,...item) constructs as valid, stripping embedded non-quoted, non-separating whitespace and comments. These constructs may span multiple lines. In this case, whitespace may be used as an alternative to the comma. PARSE_TRIPLE_QUOTES: Accept DDLm triple-quoted " " "item,item,...item " " " or '''item,item,...item''' constructs as valid, stripping embedded whitespace and comments. These constructs may span multiple lines. If this flag is set, then ''' will not be interpreted as a quoted apoptrophe and " " " will not be interpreted as a quoted double quote mark and PARSE_NOBRACKETS: Do not accept DDLm bracket-delimited [item,item,...item] or {item,item,...item} or (item,item,...item) constructs as valid, stripping non-quoted embedded whitespace and comments. These constructs may span multiple lines. PARSE_NOTRIPLE_QUOTES: No not accept DDLm triple-quoted " " "item,item,...item " " " or '''item,item,...item''' constructs as valid, stripping embedded whitespace and comments. These constructs may span multiple lines. If this flag is set, then ''' will be interpreted as a quoted apostrophe and " " " will be interpreted as a quoted double quote mark. CBFlib defers reading binary sections as long as possible. In the current version of CBFlib, this means that: 1. The file must be a random-access file opened in binary mode (fopen ( , """ return _pycbf.cbf_handle_struct_read_file(self, *args) def datablock_name(self, *args): """ Returns : *args : string C prototype: int cbf_datablock_name (cbf_handle handle, const char **datablockname); CBFLib documentation: DESCRIPTION cbf_datablock_name sets *datablockname to point to the name of the current data block. The data block name will be valid as long as the data block exists and has not been renamed. The name must not be modified by the program in any way. ARGUMENTS handle CBF handle. datablockname Pointer to the destination data block name pointer. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_datablock_name(self, *args) def set_realarray_wdims(self, *args): """ Returns : *args : int compression,int binary_id,(binary) String data,int elsize, int elements,String byteorder,int dimfast,int dimmid,int dimslow, int padding C prototype: int cbf_set_realarray_wdims (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, size_t elements, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); CBFLib documentation: DESCRIPTION cbf_set_integerarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. The elements are signed if elsigned is non-0 and unsigned otherwise. binary_id is the binary section identifier. cbf_set_realarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. binary_id is the binary section identifier. The cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, cbf_set_integerarray_wdims_sf, cbf_set_realarray_wdims, cbf_set_realarray_wdims_fs and cbf_set_realarray_wdims_sf variants allow the data header values of byteorder, dimfast, dimmid, dimslow and padding to be set to the data byte order, the fastest, second fastest and third fastest array dimensions and the size in byte of the post data padding to be used. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple "byte_offset " compression. CBF_NONE No compression. NOTE: This scheme is by far the slowest of the four and uses much more disk space. It is intended for routine use with small arrays only. With large arrays (like images) it should be used only for debugging. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned), for cbf_set_integerarray, or IEEE doubles or floats for cbf_set_realarray. If elsize is not equal to sizeof (char), sizeof (short) or sizeof (int), the function returns CBF_ARGUMENT. ARGUMENTS handle CBF handle. compression Compression method to use. binary_id Integer binary identifier. array Pointer to the source array. elsize Size in bytes of each source array element. elsigned Set to non-0 if the source array elements are signed. elements: The number of elements in the array. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_set_realarray_wdims(self, *args) def construct_reference_detector(self, *args): """ Returns : pycbf detector object *args : Integer element_number C prototype: int cbf_construct_reference_detector (cbf_handle handle, cbf_detector *detector, unsigned int element_number); CBFLib documentation: DESCRIPTION cbf_construct_detector constructs a detector object for detector element number element_number using the description in the CBF object handle and initialises the detector handle *detector. cbf_construct_reference_detector constructs a detector object for detector element number element_number using the description in the CBF object handle and initialises the detector handle *detector using the reference settings of the axes. cbf_require_reference_detector is similar, but try to force the creations of missing intermediate categories needed to construct a detector object. ARGUMENTS handle CBF handle. detector Pointer to the destination detector handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame " category. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_construct_reference_detector(self, *args) def get_real_3d_image_fs_as_string(self, *args): """ Returns : (Binary)String *args : int element_number,int elsize,int ndimfast,int ndimmid,int ndimslow C prototype: int cbf_get_real_3d_image_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimfast, size_t ndimmid, size_t ndimslow); CBFLib documentation: DESCRIPTION cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image array for element number element_number into an array. The array consists of ndimslow *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and cbf_get_real_image_sf read the image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. cbf_get_3d_image, cbf_get_3d_image_fs and cbf_get_3d_image_sf read the 3D image array for element number element_number into an array. The array consists of ndimslow *ndimmid *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order The structure of the array as a 1-, 2- or 3-dimensional array should agree with the structure of the array given in the ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1 both in the call and in the imgCIF data being processed. If the array is 2-dimensional and a 3D call is used, ndimslow and ndimmid should be the """ return _pycbf.cbf_handle_struct_get_real_3d_image_fs_as_string(self, *args) def rewind_row(self, *args): """ Returns : *args : C prototype: int cbf_rewind_row (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_rewind_row makes the first row in the current category the current row. If there are no rows, the function returns CBF_NOTFOUND. The current column is not affected. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_rewind_row(self, *args) def get_axis_setting(self, *args): """ Returns : Float start,Float increment *args : String axis_id C prototype: int cbf_get_axis_setting (cbf_handle handle, unsigned int reserved, const char *axis_id, double *start, double *increment); CBFLib documentation: DESCRIPTION cbf_get_axis_setting sets *start and *increment to the corresponding values of the axis axis_id. Either of the destination pointers may be NULL. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. axis_id Axis id. start Pointer to the destination start value. increment Pointer to the destination increment value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_get_axis_setting(self, *args) def require_column(self, *args): """ Returns : string *args : C prototype: int cbf_require_column (cbf_handle handle, const char *columnname); CBFLib documentation: DESCRIPTION cbf_require_column makes the columns in the current category with name columnname the current column, if it exists, or creates it if it does not. The comparison is case-insensitive. The current row is not affected. ARGUMENTS handle CBF handle. columnname The name of column to find. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_require_column(self, *args) def get_timestamp(self): """ Returns : Float time,Integer timezone *args : C prototype: int cbf_get_timestamp (cbf_handle handle, unsigned int reserved, double *time, int *timezone); CBFLib documentation: DESCRIPTION cbf_get_timestamp sets *time to the collection timestamp in seconds since January 1 1970. *timezone is set to timezone difference from UTC in minutes. The parameter reserved is presently unused and should be set to 0. Either of the destination pointers may be NULL. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. time Pointer to the destination collection timestamp. timezone Pointer to the destination timezone difference. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_get_timestamp(self) def find_nextrow(self, *args): """ Returns : string *args : C prototype: int cbf_find_nextrow (cbf_handle handle, const char *value); CBFLib documentation: DESCRIPTION cbf_find_nextrow makes the makes the next row in the current column with value value the current row. The search starts from the row following the last row found with cbf_find_row or cbf_find_nextrow, or from the current row if the current row was defined using any other function. The comparison is case-sensitive. If no more matching rows exist, the function returns CBF_NOTFOUND. The current column is not affected. ARGUMENTS handle CBF handle. value the value to search for. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_find_nextrow(self, *args) def get_realarrayparameters_wdims_sf(self): """ Returns : int compression,int binary_id,int elsize,int elements,char **bo, int *bolen,int dimslow,int dimmid,int dimfast,int padding *args : C prototype: int cbf_get_realarrayparameters_wdims_sf (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, size_t *elements, const char **byteorder, size_t *dimslow, size_t *dimmid, size_t *dimfast, size_t *padding); CBFLib documentation: DESCRIPTION cbf_get_integerarrayparameters sets *compression, *binary_id, *elsize, *elsigned, *elunsigned, *elements, *minelement and *maxelement to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_integerarray, if a copy of the array is to be made into another CIF or CBF. cbf_get_realarrayparameters sets *compression, *binary_id, *elsize, *elements to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_realarray, if a copy of the arry is to be made into another CIF or CBF. The variants cbf_get_integerarrayparameters_wdims, cbf_get_integerarrayparameters_wdims_fs, cbf_get_integerarrayparameters_wdims_sf, cbf_get_realarrayparameters_wdims, cbf_get_realarrayparameters_wdims_fs, cbf_get_realarrayparameters_wdims_sf set **byteorder, *dimfast, *dimmid, *dimslow, and *padding as well, providing the additional parameters needed for a subsequent call to cbf_set_integerarray_wdims or cbf_set_realarray_wdims. The value returned in *byteorder is a pointer either to the string "little_endian " or to the string "big_endian ". This should be the byte order of the data, not necessarily of the host machine. No attempt should be made to modify this string. At this time only "little_endian " will be returned. The values returned in *dimfast, *dimmid and *dimslow are the sizes of the fastest changing, second fastest changing and third fastest changing dimensions of the array, if specified, or zero, if not specified. The value returned in *padding is the size of the post-data padding, if any and if specified in the data header. The value is given as a count of octets. If the value is not binary, the function returns CBF_ASCII. ARGUMENTS handle CBF handle. compression Compression method used. elsize Size in bytes of each array element. binary_id Pointer to the destination integer binary identifier. elsigned Pointer to an integer. Set to 1 if the elements can be read as signed integers. elunsigned Pointer to an integer. Set to 1 if the elements can be read as unsigned integers. elements Pointer to the destination number of elements. minelement Pointer to the destination smallest element. maxelement Pointer to the destination largest element. byteorder Pointer to the destination byte order. dimfast Pointer to the destination fastest dimension. dimmid Pointer to the destination second fastest dimension. dimslow Pointer to the destination third fastest dimension. padding Pointer to the destination padding size. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_get_realarrayparameters_wdims_sf(self) def reset_datablock(self, *args): """ Returns : *args : C prototype: int cbf_reset_datablock (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_reset_datablock deletes all categories from the current data block. cbf_reset_saveframe deletes all categories from the current save frame. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_reset_datablock(self, *args) def set_3d_image_fs(self, *args): """ Returns : *args : int element_number,int compression,(binary) String data,int elsize, int elsign,int dimfast,int dimmid,int dimslow C prototype: int cbf_set_3d_image_fs(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimfast, size_t ndimmid, size_t ndimslow); CBFLib documentation: DESCRIPTION cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-zero and unsigned otherwise. cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow IEEE double or float elements of elsize bytes each, starting at array. cbf_set_3d_image, cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_set_real_3d_image, cbf_set_real_3d_image_fs and cbf_set_real_3d_image_sf writes the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow IEEE double or float elements of elsize bytes each, starting at array. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the array is 2-dimensional and the 3D calls are used, ndimslow and ndimmid should be used for the array dimensions and ndimfast should be set to 1. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple "byte_offset " compression. CBF_NONE No compression. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned)for cbf_set_image, or IEEE doubles or floats for cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame " category. compression Compression type. array Pointer to the image array. elsize Size in bytes of each image array element. elsigned Set to non-0 if the image array elements are signed. ndimslow Slowest array dimension. ndimmid Second slowest array dimension. ndimfast Fastest array dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_3d_image_fs(self, *args) def set_saveframename(self, *args): """ Returns : string *args : C prototype: int cbf_set_saveframename (cbf_handle handle, const char *saveframename); CBFLib documentation: DESCRIPTION cbf_set_datablockname changes the name of the current data block to datablockname. cbf_set_saveframename changes the name of the current save frame to saveframename. If a data block or save frame with this name already exists (comparison is case-insensitive), the function returns CBF_IDENTICAL. ARGUMENTS handle CBF handle. datablockname The new data block name. datablockname The new save frame name. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_set_saveframename(self, *args) def require_integervalue(self, *args): """ Returns : Int number *args : Int thedefault C prototype: int cbf_require_integervalue (cbf_handle handle, int *number, int defaultvalue); CBFLib documentation: DESCRIPTION cbf_get_integervalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal integer. cbf_require_integervalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal integer, setting it to defaultvalue if necessary. If the value is not ASCII, the function returns CBF_BINARY. ARGUMENTS handle CBF handle. number pointer to the number. defaultvalue default number value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_require_integervalue(self, *args) def get_integerarrayparameters(self): """ Returns : int compression,int binary_id,int elsize,int elsigned,int elunsigned, int elements,int minelement,int maxelement *args : C prototype: int cbf_get_integerarrayparameters (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, int *elsigned, int *elunsigned, size_t *elements, int *minelement, int *maxelement); CBFLib documentation: DESCRIPTION cbf_get_integerarrayparameters sets *compression, *binary_id, *elsize, *elsigned, *elunsigned, *elements, *minelement and *maxelement to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_integerarray, if a copy of the array is to be made into another CIF or CBF. cbf_get_realarrayparameters sets *compression, *binary_id, *elsize, *elements to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_realarray, if a copy of the arry is to be made into another CIF or CBF. The variants cbf_get_integerarrayparameters_wdims, cbf_get_integerarrayparameters_wdims_fs, cbf_get_integerarrayparameters_wdims_sf, cbf_get_realarrayparameters_wdims, cbf_get_realarrayparameters_wdims_fs, cbf_get_realarrayparameters_wdims_sf set **byteorder, *dimfast, *dimmid, *dimslow, and *padding as well, providing the additional parameters needed for a subsequent call to cbf_set_integerarray_wdims or cbf_set_realarray_wdims. The value returned in *byteorder is a pointer either to the string "little_endian " or to the string "big_endian ". This should be the byte order of the data, not necessarily of the host machine. No attempt should be made to modify this string. At this time only "little_endian " will be returned. The values returned in *dimfast, *dimmid and *dimslow are the sizes of the fastest changing, second fastest changing and third fastest changing dimensions of the array, if specified, or zero, if not specified. The value returned in *padding is the size of the post-data padding, if any and if specified in the data header. The value is given as a count of octets. If the value is not binary, the function returns CBF_ASCII. ARGUMENTS handle CBF handle. compression Compression method used. elsize Size in bytes of each array element. binary_id Pointer to the destination integer binary identifier. elsigned Pointer to an integer. Set to 1 if the elements can be read as signed integers. elunsigned Pointer to an integer. Set to 1 if the elements can be read as unsigned integers. elements Pointer to the destination number of elements. minelement Pointer to the destination smallest element. maxelement Pointer to the destination largest element. byteorder Pointer to the destination byte order. dimfast Pointer to the destination fastest dimension. dimmid Pointer to the destination second fastest dimension. dimslow Pointer to the destination third fastest dimension. padding Pointer to the destination padding size. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_get_integerarrayparameters(self) def set_real_3d_image_sf(self, *args): """ Returns : *args : int element_number,int compression,(binary) String data,int elsize, int dimslow,int dimmid,int dimfast C prototype: int cbf_set_real_3d_image_sf(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-zero and unsigned otherwise. cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow IEEE double or float elements of elsize bytes each, starting at array. cbf_set_3d_image, cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_set_real_3d_image, cbf_set_real_3d_image_fs and cbf_set_real_3d_image_sf writes the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow IEEE double or float elements of elsize bytes each, starting at array. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the array is 2-dimensional and the 3D calls are used, ndimslow and ndimmid should be used for the array dimensions and ndimfast should be set to 1. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple "byte_offset " compression. CBF_NONE No compression. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned)for cbf_set_image, or IEEE doubles or floats for cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame " category. compression Compression type. array Pointer to the image array. elsize Size in bytes of each image array element. elsigned Set to non-0 if the image array elements are signed. ndimslow Slowest array dimension. ndimmid Second slowest array dimension. ndimfast Fastest array dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_real_3d_image_sf(self, *args) def write_file(self, *args): """ Returns : *args : String filename,Integer ciforcbf,Integer Headers,Integer encoding C prototype: int cbf_write_file (cbf_handle handle, FILE *file, int readable, int ciforcbf, int flags, int encoding); CBFLib documentation: DESCRIPTION cbf_write_file writes the CBF object specified by handle into the file file, following CIF 1.0 conventions of 80 character lines. cbf_write_widefile writes the CBF object specified by handle into the file file, following CIF 1.1 conventions of 2048 character lines. A warning is issued to stderr for ascii lines over the limit, and an attempt is made to fold lines to fit. No test is performed on binary sections. If a dictionary has been provided, aliases will be applied on output. Unlike cbf_read_file, the file does not have to be random-access. If the file is random-access and readable, readable can be set to non-0 to indicate to CBFlib that the file can be used as a buffer to conserve disk space. If the file is not random-access or not readable, readable must be 0. """ return _pycbf.cbf_handle_struct_write_file(self, *args) def set_divergence(self, *args): """ Returns : *args : Float div_x_source,Float div_y_source,Float div_x_y_source C prototype: int cbf_set_divergence (cbf_handle handle, double div_x_source, double div_y_source, double div_x_y_source); CBFLib documentation: DESCRIPTION cbf_set_divergence sets the source divergence parameters to the values specified by div_x_source, div_y_source and div_x_y_source. ARGUMENTS handle CBF handle. div_x_source New value of div_x_source. div_y_source New value of div_y_source. div_x_y_source New value of div_x_y_source. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_divergence(self, *args) def remove_datablock(self, *args): """ Returns : *args : C prototype: int cbf_remove_datablock (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_remove_datablock deletes the current data block. cbf_remove_saveframe deletes the current save frame. The current data block becomes undefined. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_remove_datablock(self, *args) def count_elements(self, *args): """ Returns : Integer *args : C prototype: int cbf_count_elements (cbf_handle handle, unsigned int *elements); CBFLib documentation: DESCRIPTION cbf_count_elements sets *elements to the number of detector elements. ARGUMENTS handle CBF handle. elements Pointer to the destination count. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_count_elements(self, *args) def set_image_fs(self, *args): """ Returns : *args : int element_number,int compression,(binary) String data,int elsize, int elsign,int dimfast,int dimslow C prototype: int cbf_set_image_fs(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimfast, size_t ndimslow); CBFLib documentation: DESCRIPTION cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-zero and unsigned otherwise. cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow IEEE double or float elements of elsize bytes each, starting at array. cbf_set_3d_image, cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_set_real_3d_image, cbf_set_real_3d_image_fs and cbf_set_real_3d_image_sf writes the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow IEEE double or float elements of elsize bytes each, starting at array. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the array is 2-dimensional and the 3D calls are used, ndimslow and ndimmid should be used for the array dimensions and ndimfast should be set to 1. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple "byte_offset " compression. CBF_NONE No compression. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned)for cbf_set_image, or IEEE doubles or floats for cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame " category. compression Compression type. array Pointer to the image array. elsize Size in bytes of each image array element. elsigned Set to non-0 if the image array elements are signed. ndimslow Slowest array dimension. ndimmid Second slowest array dimension. ndimfast Fastest array dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_image_fs(self, *args) def require_reference_detector(self, *args): """ Returns : pycbf detector object *args : Integer element_number C prototype: int cbf_require_reference_detector (cbf_handle handle, cbf_detector *detector, unsigned int element_number); CBFLib documentation: DESCRIPTION cbf_construct_detector constructs a detector object for detector element number element_number using the description in the CBF object handle and initialises the detector handle *detector. cbf_construct_reference_detector constructs a detector object for detector element number element_number using the description in the CBF object handle and initialises the detector handle *detector using the reference settings of the axes. cbf_require_reference_detector is similar, but try to force the creations of missing intermediate categories needed to construct a detector object. ARGUMENTS handle CBF handle. detector Pointer to the destination detector handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame " category. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_require_reference_detector(self, *args) def next_category(self, *args): """ Returns : *args : C prototype: int cbf_next_category (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_next_category makes the category following the current category in the current data block the current category. If there are no more categories, the function returns CBF_NOTFOUND. The current column and row become undefined. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_next_category(self, *args) def set_diffrn_id(self, *args): """ Returns : string *args : C prototype: int cbf_set_diffrn_id (cbf_handle handle, const char *diffrn_id); CBFLib documentation: DESCRIPTION cbf_set_diffrn_id sets the "diffrn.id " entry of the current datablock to the ASCII value diffrn_id. This function also changes corresponding "diffrn_id " entries in the "diffrn_source ", "diffrn_radiation ", "diffrn_detector " and "diffrn_measurement " categories. ARGUMENTS handle CBF handle. diffrn_id ASCII value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_diffrn_id(self, *args) def set_timestamp(self, *args): """ Returns : *args : Float time,Integer timezone,Float precision C prototype: int cbf_set_timestamp (cbf_handle handle, unsigned int reserved, double time, int timezone, double precision); CBFLib documentation: DESCRIPTION cbf_set_timestamp sets the collection timestamp in seconds since January 1 1970 to the value specified by time. The timezone difference from UTC """ return _pycbf.cbf_handle_struct_set_timestamp(self, *args) def get_orientation_matrix(self): """ Returns : Float matrix_0,Float matrix_1,Float matrix_2,Float matrix_3, Float matrix_4,Float matrix_5,Float matrix_6,Float matrix_7, Float matrix_8 *args : C prototype: int cbf_get_orientation_matrix (cbf_handle handle, double ub_matrix[9]); CBFLib documentation: DESCRIPTION cbf_get_orientation_matrix sets ub_matrix to point to the array of orientation matrix entries in the "diffrn " category in the order of columns: "UB[1][1] " "UB[1][2] " "UB[1][3] " "UB[2][1] " "UB[2][2] " "UB[2][3] " "UB[3][1] " "UB[3][2] " "UB[3][3] " cbf_set_orientation_matrix sets the values in the "diffrn " category to the values pointed to by ub_matrix. ARGUMENTS handle CBF handle. ubmatric Source or destination array of 9 doubles giving the orientation matrix parameters. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_get_orientation_matrix(self) def get_image_size_fs(self, *args): """ Returns : size_t ndimfast,size_t ndimslow *args : Integer element_number C prototype: int cbf_get_image_size_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimfast, size_t *ndimslow); CBFLib documentation: DESCRIPTION cbf_get_image_size, cbf_get_image_size_fs and cbf_get_image_size_sf set *ndimslow and *ndimfast to the slow and fast dimensions of the image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimfast will be set to 1. If the array is 3-dimensional an error code will be returned. cbf_get_3d_image_size, cbf_get_3d_image_size_fs and cbf_get_3d_image_size_sf set *ndimslow, *ndimmid and *ndimfast to the slowest, next fastest and fastest dimensions, respectively, of the 3D image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimmid and """ return _pycbf.cbf_handle_struct_get_image_size_fs(self, *args) def get_divergence(self): """ Returns : Float div_x_source,Float div_y_source,Float div_x_y_source *args : C prototype: int cbf_get_divergence (cbf_handle handle, double *div_x_source, double *div_y_source, double *div_x_y_source); CBFLib documentation: DESCRIPTION cbf_get_divergence sets *div_x_source, *div_y_source and *div_x_y_source to the corresponding source divergence parameters. Any of the destination pointers may be NULL. ARGUMENTS handle CBF handle. div_x_source Pointer to the destination div_x_source. div_y_source Pointer to the destination div_y_source. div_x_y_source Pointer to the destination div_x_y_source. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_get_divergence(self) def rewind_category(self, *args): """ Returns : *args : C prototype: int cbf_rewind_category (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_rewind_category makes the first category in the current data block the current category. cbf_rewind_saveframe makes the first saveframe in the current data block the current saveframe. cbf_rewind_blockitem makes the first blockitem (category or saveframe) in the current data block the current blockitem. The type of the blockitem (CBF_CATEGORY or CBF_SAVEFRAME) is returned in type. If there are no categories, saveframes or blockitems the function returns CBF_NOTFOUND. The current column and row become undefined. ARGUMENTS handle CBF handle. type CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_rewind_category(self, *args) def read_template(self, *args): """ Returns : *args : String filename C prototype: int cbf_read_template (cbf_handle handle, FILE *file); CBFLib documentation: DESCRIPTION cbf_read_template reads the CBF or CIF file file into the CBF object specified by handle and selects the first datablock as the current datablock. ARGUMENTS handle Pointer to a CBF handle. file Pointer to a file descriptor. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_read_template(self, *args) def select_row(self, *args): """ Returns : *args : Integer C prototype: int cbf_select_row (cbf_handle handle, unsigned int row); CBFLib documentation: DESCRIPTION cbf_select_row selects row number row in the current category as the current row. The first row is number 0. The current column is not affected If the row does not exist, the function returns CBF_NOTFOUND. ARGUMENTS handle CBF handle. row Number of the row to select. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_select_row(self, *args) def get_image_fs_as_string(self, *args): """ Returns : (Binary)String *args : int element_number,int elsize,int elsign,int ndimfast,int ndimslow C prototype: int cbf_get_image_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimfast, size_t ndimslow); CBFLib documentation: DESCRIPTION cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image array for element number element_number into an array. The array consists of ndimslow *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and cbf_get_real_image_sf read the image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. cbf_get_3d_image, cbf_get_3d_image_fs and cbf_get_3d_image_sf read the 3D image array for element number element_number into an array. The array consists of ndimslow *ndimmid *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order The structure of the array as a 1-, 2- or 3-dimensional array should agree with the structure of the array given in the ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1 both in the call and in the imgCIF data being processed. If the array is 2-dimensional and a 3D call is used, ndimslow and ndimmid should be the """ return _pycbf.cbf_handle_struct_get_image_fs_as_string(self, *args) def get_image_size_sf(self, *args): """ Returns : size_t ndimslow,size_t ndimfast *args : Integer element_number C prototype: int cbf_get_image_size_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimslow, size_t *ndimfast); CBFLib documentation: DESCRIPTION cbf_get_image_size, cbf_get_image_size_fs and cbf_get_image_size_sf set *ndimslow and *ndimfast to the slow and fast dimensions of the image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimfast will be set to 1. If the array is 3-dimensional an error code will be returned. cbf_get_3d_image_size, cbf_get_3d_image_size_fs and cbf_get_3d_image_size_sf set *ndimslow, *ndimmid and *ndimfast to the slowest, next fastest and fastest dimensions, respectively, of the 3D image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimmid and """ return _pycbf.cbf_handle_struct_get_image_size_sf(self, *args) def get_real_image_fs_as_string(self, *args): """ Returns : (Binary)String *args : int element_number,int elsize,int ndimfast,int ndimslow C prototype: int cbf_get_real_image_fs (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimfast, size_t ndimslow); CBFLib documentation: DESCRIPTION cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image array for element number element_number into an array. The array consists of ndimslow *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and cbf_get_real_image_sf read the image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. cbf_get_3d_image, cbf_get_3d_image_fs and cbf_get_3d_image_sf read the 3D image array for element number element_number into an array. The array consists of ndimslow *ndimmid *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order The structure of the array as a 1-, 2- or 3-dimensional array should agree with the structure of the array given in the ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1 both in the call and in the imgCIF data being processed. If the array is 2-dimensional and a 3D call is used, ndimslow and ndimmid should be the """ return _pycbf.cbf_handle_struct_get_real_image_fs_as_string(self, *args) def count_columns(self, *args): """ Returns : Integer *args : C prototype: int cbf_count_columns (cbf_handle handle, unsigned int *columns); CBFLib documentation: DESCRIPTION cbf_count_columns puts the number of columns in the current category in *columns. ARGUMENTS handle CBF handle. columns Pointer to the destination column count. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_count_columns(self, *args) def get_integerarrayparameters_wdims(self): """ Returns : int compression,int binary_id,int elsize,int elsigned,int elunsigned, int elements,int minelement,int maxelement,char **bo,int *bolen, int dimfast,int dimmid,int dimslow,int padding *args : C prototype: int cbf_get_integerarrayparameters_wdims (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, int *elsigned, int *elunsigned, size_t *elements, int *minelement, int *maxelement, const char **byteorder, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding); CBFLib documentation: DESCRIPTION cbf_get_integerarrayparameters sets *compression, *binary_id, *elsize, *elsigned, *elunsigned, *elements, *minelement and *maxelement to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_integerarray, if a copy of the array is to be made into another CIF or CBF. cbf_get_realarrayparameters sets *compression, *binary_id, *elsize, *elements to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_realarray, if a copy of the arry is to be made into another CIF or CBF. The variants cbf_get_integerarrayparameters_wdims, cbf_get_integerarrayparameters_wdims_fs, cbf_get_integerarrayparameters_wdims_sf, cbf_get_realarrayparameters_wdims, cbf_get_realarrayparameters_wdims_fs, cbf_get_realarrayparameters_wdims_sf set **byteorder, *dimfast, *dimmid, *dimslow, and *padding as well, providing the additional parameters needed for a subsequent call to cbf_set_integerarray_wdims or cbf_set_realarray_wdims. The value returned in *byteorder is a pointer either to the string "little_endian " or to the string "big_endian ". This should be the byte order of the data, not necessarily of the host machine. No attempt should be made to modify this string. At this time only "little_endian " will be returned. The values returned in *dimfast, *dimmid and *dimslow are the sizes of the fastest changing, second fastest changing and third fastest changing dimensions of the array, if specified, or zero, if not specified. The value returned in *padding is the size of the post-data padding, if any and if specified in the data header. The value is given as a count of octets. If the value is not binary, the function returns CBF_ASCII. ARGUMENTS handle CBF handle. compression Compression method used. elsize Size in bytes of each array element. binary_id Pointer to the destination integer binary identifier. elsigned Pointer to an integer. Set to 1 if the elements can be read as signed integers. elunsigned Pointer to an integer. Set to 1 if the elements can be read as unsigned integers. elements Pointer to the destination number of elements. minelement Pointer to the destination smallest element. maxelement Pointer to the destination largest element. byteorder Pointer to the destination byte order. dimfast Pointer to the destination fastest dimension. dimmid Pointer to the destination second fastest dimension. dimslow Pointer to the destination third fastest dimension. padding Pointer to the destination padding size. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_get_integerarrayparameters_wdims(self) def get_gain(self, *args): """ Returns : Float gain,Float gain_esd *args : C prototype: int cbf_get_gain (cbf_handle handle, unsigned int element_number, double *gain, double *gain_esd); CBFLib documentation: DESCRIPTION cbf_get_gain sets *gain and *gain_esd to the corresponding gain parameters for element number element_number. Either of the destination pointers may be NULL. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame " category. gain Pointer to the destination gain. gain_esd Pointer to the destination gain_esd. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_get_gain(self, *args) def new_saveframe(self, *args): """ Returns : string *args : C prototype: int cbf_new_saveframe (cbf_handle handle, const char *saveframename); CBFLib documentation: DESCRIPTION cbf_new_datablock creates a new data block with name datablockname and makes it the current data block. cbf_new_saveframe creates a new save frame with name saveframename within the current data block and makes the new save frame the current save frame. If a data block or save frame with this name already exists, the existing data block or save frame becomes the current data block or save frame. ARGUMENTS handle CBF handle. datablockname The name of the new data block. saveframename The name of the new save frame. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_new_saveframe(self, *args) def set_polarization(self, *args): """ Returns : *args : Float polarizn_source_ratio,Float polarizn_source_norm C prototype: int cbf_set_polarization (cbf_handle handle, double polarizn_source_ratio, double polarizn_source_norm); CBFLib documentation: DESCRIPTION cbf_set_polarization sets the source polarization to the values specified by polarizn_source_ratio and polarizn_source_norm. ARGUMENTS handle CBF handle. polarizn_source_ratio New value of polarizn_source_ratio. polarizn_source_norm New value of polarizn_source_norm. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_polarization(self, *args) def set_real_3d_image(self, *args): """ Returns : *args : int element_number,int compression,(binary) String data,int elsize, int dimslow,int dimmid,int dimfast C prototype: int cbf_set_real_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-zero and unsigned otherwise. cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow IEEE double or float elements of elsize bytes each, starting at array. cbf_set_3d_image, cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_set_real_3d_image, cbf_set_real_3d_image_fs and cbf_set_real_3d_image_sf writes the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow IEEE double or float elements of elsize bytes each, starting at array. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the array is 2-dimensional and the 3D calls are used, ndimslow and ndimmid should be used for the array dimensions and ndimfast should be set to 1. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple "byte_offset " compression. CBF_NONE No compression. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned)for cbf_set_image, or IEEE doubles or floats for cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame " category. compression Compression type. array Pointer to the image array. elsize Size in bytes of each image array element. elsigned Set to non-0 if the image array elements are signed. ndimslow Slowest array dimension. ndimmid Second slowest array dimension. ndimfast Fastest array dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_real_3d_image(self, *args) def delete_row(self, *args): """ Returns : *args : Integer C prototype: int cbf_delete_row (cbf_handle handle, unsigned int rownumber); CBFLib documentation: DESCRIPTION cbf_delete_row deletes a row from the current category. Rows starting from rownumber +1 are moved down by 1. If the current row was higher than rownumber, or if the current row is the last row, it will also move down by 1. The row numbers start from 0. ARGUMENTS handle CBF handle. rownumber The number of the row to delete. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_delete_row(self, *args) def column_name(self, *args): """ Returns : *args : string C prototype: int cbf_column_name (cbf_handle handle, const char **columnname); CBFLib documentation: DESCRIPTION cbf_column_name sets *columnname to point to the name of the current column of the current category. The column name will be valid as long as the column exists. The name must not be modified by the program in any way. ARGUMENTS handle CBF handle. columnname Pointer to the destination column name pointer. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_column_name(self, *args) def remove_saveframe(self, *args): """ Returns : *args : C prototype: int cbf_remove_saveframe (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_remove_datablock deletes the current data block. cbf_remove_saveframe deletes the current save frame. The current data block becomes undefined. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_remove_saveframe(self, *args) def set_integerarray_wdims_sf(self, *args): """ Returns : *args : int compression,int binary_id,(binary) String data,int elsize, int elements,String byteorder,int dimslow,int dimmid,int dimfast, int padding C prototype: int cbf_set_integerarray_wdims_sf (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, int elsigned, size_t elements, const char *byteorder, size_t dimslow, size_t dimmid, size_t dimfast, size_t padding); CBFLib documentation: DESCRIPTION cbf_set_integerarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. The elements are signed if elsigned is non-0 and unsigned otherwise. binary_id is the binary section identifier. cbf_set_realarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. binary_id is the binary section identifier. The cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, cbf_set_integerarray_wdims_sf, cbf_set_realarray_wdims, cbf_set_realarray_wdims_fs and cbf_set_realarray_wdims_sf variants allow the data header values of byteorder, dimfast, dimmid, dimslow and padding to be set to the data byte order, the fastest, second fastest and third fastest array dimensions and the size in byte of the post data padding to be used. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple "byte_offset " compression. CBF_NONE No compression. NOTE: This scheme is by far the slowest of the four and uses much more disk space. It is intended for routine use with small arrays only. With large arrays (like images) it should be used only for debugging. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned), for cbf_set_integerarray, or IEEE doubles or floats for cbf_set_realarray. If elsize is not equal to sizeof (char), sizeof (short) or sizeof (int), the function returns CBF_ARGUMENT. ARGUMENTS handle CBF handle. compression Compression method to use. binary_id Integer binary identifier. array Pointer to the source array. elsize Size in bytes of each source array element. elsigned Set to non-0 if the source array elements are signed. elements: The number of elements in the array. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_set_integerarray_wdims_sf(self, *args) def require_value(self, *args): """ Returns : String Value *args : String defaultvalue C prototype: int cbf_require_value (cbf_handle handle, const char **value, const char *defaultvalue ); CBFLib documentation: DESCRIPTION cbf_get_value sets *value to point to the ASCII value of the item at the current column and row. cbf_require_value sets *value to point to the ASCII value of the item at the current column and row, creating the data item if necessary and initializing it to a copy of defaultvalue. If the value is not ASCII, the function returns CBF_BINARY. The value will be valid as long as the item exists and has not been set to a new value. The value must not be modified by the program in any way. ARGUMENTS handle CBF handle. value Pointer to the destination value pointer. defaultvalue Default value character string. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_require_value(self, *args) def require_column_integervalue(self, *args): """ Returns : Int Value *args : String Columnvalue,Int default C prototype: int cbf_require_column_integervalue (cbf_handle handle, const char *columnname, int *number, const int defaultvalue); CBFLib documentation: DESCRIPTION cbf_require_column_doublevalue sets *number to the value of the ASCII item at the current row for the column given with the name given by *columnname, with the value interpreted as an integer number, or to the number given by defaultvalue if the item cannot be found. ARGUMENTS handle CBF handle. columnname Name of the column containing the number. number pointer to the location to receive the integer value. defaultvalue Value to use if the requested column and value cannot be found. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_require_column_integervalue(self, *args) def set_pixel_size(self, *args): """ Returns : *args : Int element_number,Int axis_number,Float pixel size C prototype: int cbf_set_pixel_size (cbf_handle handle, unsigned int element_number, int axis_number, double psize); CBFLib documentation: DESCRIPTION cbf_set_pixel_size and cbf_set_pixel_size_sf set the item in the "e;size"e; column of the "array_structure_list " category at the row which matches axis axis_number of the detector element element_number converting the double pixel size psize from meters to millimeters in storing it in the "size " column for the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the slowest axis. cbf_set_pixel_size_fs sets the item """ return _pycbf.cbf_handle_struct_set_pixel_size(self, *args) def next_column(self, *args): """ Returns : *args : C prototype: int cbf_next_column (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_next_column makes the column following the current column in the current category the current column. If there are no more columns, the function returns CBF_NOTFOUND. The current row is not affected. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_next_column(self, *args) def get_3d_image_size_sf(self, *args): """ Returns : size_t ndimslow,size_t ndimmid,size_t ndimfast *args : Integer element_number C prototype: int cbf_get_3d_image_size_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimslow, size_t *ndimmid, size_t *ndimfast); CBFLib documentation: DESCRIPTION cbf_get_image_size, cbf_get_image_size_fs and cbf_get_image_size_sf set *ndimslow and *ndimfast to the slow and fast dimensions of the image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimfast will be set to 1. If the array is 3-dimensional an error code will be returned. cbf_get_3d_image_size, cbf_get_3d_image_size_fs and cbf_get_3d_image_size_sf set *ndimslow, *ndimmid and *ndimfast to the slowest, next fastest and fastest dimensions, respectively, of the 3D image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimmid and """ return _pycbf.cbf_handle_struct_get_3d_image_size_sf(self, *args) def get_realarrayparameters_wdims_fs(self): """ Returns : int compression,int binary_id,int elsize,int elements,char **bo, int *bolen,int dimfast,int dimmid,int dimslow,int padding *args : C prototype: int cbf_get_realarrayparameters_wdims_fs (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, size_t *elements, const char **byteorder, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding); CBFLib documentation: DESCRIPTION cbf_get_integerarrayparameters sets *compression, *binary_id, *elsize, *elsigned, *elunsigned, *elements, *minelement and *maxelement to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_integerarray, if a copy of the array is to be made into another CIF or CBF. cbf_get_realarrayparameters sets *compression, *binary_id, *elsize, *elements to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_realarray, if a copy of the arry is to be made into another CIF or CBF. The variants cbf_get_integerarrayparameters_wdims, cbf_get_integerarrayparameters_wdims_fs, cbf_get_integerarrayparameters_wdims_sf, cbf_get_realarrayparameters_wdims, cbf_get_realarrayparameters_wdims_fs, cbf_get_realarrayparameters_wdims_sf set **byteorder, *dimfast, *dimmid, *dimslow, and *padding as well, providing the additional parameters needed for a subsequent call to cbf_set_integerarray_wdims or cbf_set_realarray_wdims. The value returned in *byteorder is a pointer either to the string "little_endian " or to the string "big_endian ". This should be the byte order of the data, not necessarily of the host machine. No attempt should be made to modify this string. At this time only "little_endian " will be returned. The values returned in *dimfast, *dimmid and *dimslow are the sizes of the fastest changing, second fastest changing and third fastest changing dimensions of the array, if specified, or zero, if not specified. The value returned in *padding is the size of the post-data padding, if any and if specified in the data header. The value is given as a count of octets. If the value is not binary, the function returns CBF_ASCII. ARGUMENTS handle CBF handle. compression Compression method used. elsize Size in bytes of each array element. binary_id Pointer to the destination integer binary identifier. elsigned Pointer to an integer. Set to 1 if the elements can be read as signed integers. elunsigned Pointer to an integer. Set to 1 if the elements can be read as unsigned integers. elements Pointer to the destination number of elements. minelement Pointer to the destination smallest element. maxelement Pointer to the destination largest element. byteorder Pointer to the destination byte order. dimfast Pointer to the destination fastest dimension. dimmid Pointer to the destination second fastest dimension. dimslow Pointer to the destination third fastest dimension. padding Pointer to the destination padding size. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_get_realarrayparameters_wdims_fs(self) def get_realarray_as_string(self): """ Returns : (Binary)String *args : C prototype: int cbf_get_realarray (cbf_handle handle, int *binary_id, void *array, size_t elsize, size_t elements, size_t *elements_read); CBFLib documentation: DESCRIPTION cbf_get_integerarray reads the binary value of the item at the current column and row into an integer array. The array consists of elements elements of elsize bytes each, starting at array. The elements are signed if elsigned is non-0 and unsigned otherwise. *binary_id is set to the binary section identifier and *elements_read to the number of elements actually read. cbf_get_realarray reads the binary value of the item at the current column and row into a real array. The array consists of elements elements of elsize bytes each, starting at array. *binary_id is set to the binary section identifier and *elements_read to the number of elements actually read. If any element in the integer binary data cant fit into the destination element, the destination is set the nearest possible value. If the value is not binary, the function returns CBF_ASCII. If the requested number of elements cant be read, the function will read as many as it can and then return CBF_ENDOFDATA. Currently, the destination array must consist of chars, shorts or ints (signed or unsigned). If elsize is not equal to sizeof (char), sizeof (short) or sizeof (int), for cbf_get_integerarray, or sizeof(double) or sizeof(float), for cbf_get_realarray the function returns CBF_ARGUMENT. An additional restriction in the current version of CBFlib is that values too large to fit in an int are not correctly decompressed. As an example, if the machine with 32-bit ints is reading an array containing a value outside the range 0 .. 2^32-1 (unsigned) or -2^31 .. 2^31-1 (signed), the array will not be correctly decompressed. This restriction will be removed in a future release. For cbf_get_realarray, only IEEE format is supported. No conversion to other floating point formats is done at this time. ARGUMENTS handle CBF handle. binary_id Pointer to the destination integer binary identifier. array Pointer to the destination array. elsize Size in bytes of each destination array element. elsigned Set to non-0 if the destination array elements are signed. elements The number of elements to read. elements_read Pointer to the destination number of elements actually read. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_get_realarray_as_string(self) def get_bin_sizes(self, *args): """ Returns : Float slowbinsize,Float fastbinsize *args : Integer element_number C prototype: int cbf_get_bin_sizes(cbf_handle handle, unsigned int element_number, double * slowbinsize, double * fastbinsize); CBFLib documentation: DESCRIPTION cbf_get_bin_sizes sets slowbinsize to point to the value of the number of pixels composing one array element in the dimension that changes at the second-fastest rate and fastbinsize to point to the value of the number of pixels composing one array element in the dimension that changes at the fastest rate for the dectector element with the ordinal element_number. cbf_set_bin_sizes sets the the pixel bin sizes in the "array_intensities " category to the values of slowbinsize_in for the number of pixels composing one array element in the dimension that changes at the second-fastest rate and fastbinsize_in for the number of pixels composing one array element in the dimension that changes at the fastest rate for the dectector element with the ordinal element_number. In order to allow for software binning involving fractions of pixels, the bin sizes are doubles rather than ints. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame " category. slowbinsize Pointer to the returned number of pixels composing one array element in the dimension that changes at the second-fastest rate. fastbinsize Pointer to the returned number of pixels composing one array element in the dimension that changes at the fastest rate. slowbinsize_in The number of pixels composing one array element in the dimension that changes at the second-fastest rate. fastbinsize_in The number of pixels composing one array element in the dimension that changes at the fastest rate. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_get_bin_sizes(self, *args) def reset_category(self, *args): """ Returns : *args : C prototype: int cbf_reset_category (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_reset_category deletes all columns and rows from current category. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_reset_category(self, *args) def construct_goniometer(self): """ Returns : pycbf goniometer object *args : C prototype: int cbf_construct_goniometer (cbf_handle handle, cbf_goniometer *goniometer); CBFLib documentation: DESCRIPTION cbf_construct_goniometer constructs a goniometer object using the description in the CBF object handle and initialises the goniometer handle *goniometer. ARGUMENTS handle CBF handle. goniometer Pointer to the destination goniometer handle. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_construct_goniometer(self) def set_datablockname(self, *args): """ Returns : string *args : C prototype: int cbf_set_datablockname (cbf_handle handle, const char *datablockname); CBFLib documentation: DESCRIPTION cbf_set_datablockname changes the name of the current data block to datablockname. cbf_set_saveframename changes the name of the current save frame to saveframename. If a data block or save frame with this name already exists (comparison is case-insensitive), the function returns CBF_IDENTICAL. ARGUMENTS handle CBF handle. datablockname The new data block name. datablockname The new save frame name. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_set_datablockname(self, *args) def set_crystal_id(self, *args): """ Returns : string *args : C prototype: int cbf_set_crystal_id (cbf_handle handle, const char *crystal_id); CBFLib documentation: DESCRIPTION cbf_set_crystal_id sets the "diffrn.crystal_id " entry to the ASCII value crystal_id. ARGUMENTS handle CBF handle. crystal_id ASCII value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_crystal_id(self, *args) def get_integerarray_as_string(self): """ Returns : (Binary)String *args : C prototype: int cbf_get_integerarray (cbf_handle handle, int *binary_id, void *array, size_t elsize, int elsigned, size_t elements, size_t *elements_read); CBFLib documentation: DESCRIPTION cbf_get_integerarray reads the binary value of the item at the current column and row into an integer array. The array consists of elements elements of elsize bytes each, starting at array. The elements are signed if elsigned is non-0 and unsigned otherwise. *binary_id is set to the binary section identifier and *elements_read to the number of elements actually read. cbf_get_realarray reads the binary value of the item at the current column and row into a real array. The array consists of elements elements of elsize bytes each, starting at array. *binary_id is set to the binary section identifier and *elements_read to the number of elements actually read. If any element in the integer binary data cant fit into the destination element, the destination is set the nearest possible value. If the value is not binary, the function returns CBF_ASCII. If the requested number of elements cant be read, the function will read as many as it can and then return CBF_ENDOFDATA. Currently, the destination array must consist of chars, shorts or ints (signed or unsigned). If elsize is not equal to sizeof (char), sizeof (short) or sizeof (int), for cbf_get_integerarray, or sizeof(double) or sizeof(float), for cbf_get_realarray the function returns CBF_ARGUMENT. An additional restriction in the current version of CBFlib is that values too large to fit in an int are not correctly decompressed. As an example, if the machine with 32-bit ints is reading an array containing a value outside the range 0 .. 2^32-1 (unsigned) or -2^31 .. 2^31-1 (signed), the array will not be correctly decompressed. This restriction will be removed in a future release. For cbf_get_realarray, only IEEE format is supported. No conversion to other floating point formats is done at this time. ARGUMENTS handle CBF handle. binary_id Pointer to the destination integer binary identifier. array Pointer to the destination array. elsize Size in bytes of each destination array element. elsigned Set to non-0 if the destination array elements are signed. elements The number of elements to read. elements_read Pointer to the destination number of elements actually read. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_get_integerarray_as_string(self) def set_3d_image(self, *args): """ Returns : *args : int element_number,int compression,(binary) String data,int elsize, int elsign,int dimslow,int dimmid,int dimfast C prototype: int cbf_set_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-zero and unsigned otherwise. cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow IEEE double or float elements of elsize bytes each, starting at array. cbf_set_3d_image, cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_set_real_3d_image, cbf_set_real_3d_image_fs and cbf_set_real_3d_image_sf writes the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow IEEE double or float elements of elsize bytes each, starting at array. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the array is 2-dimensional and the 3D calls are used, ndimslow and ndimmid should be used for the array dimensions and ndimfast should be set to 1. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple "byte_offset " compression. CBF_NONE No compression. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned)for cbf_set_image, or IEEE doubles or floats for cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame " category. compression Compression type. array Pointer to the image array. elsize Size in bytes of each image array element. elsigned Set to non-0 if the image array elements are signed. ndimslow Slowest array dimension. ndimmid Second slowest array dimension. ndimfast Fastest array dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_3d_image(self, *args) def set_dictionary(self, *args): """ Returns : *args : CBFHandle dictionary C prototype: int cbf_set_dictionary (cbf_handle handle, cbf_handle dictionary_in); CBFLib documentation: DESCRIPTION cbf_get_dictionary sets *dictionary to the handle of a CBF which has been associated with the CBF handle by cbf_set_dictionary. cbf_set_dictionary associates the CBF handle dictionary_in with handle as its dictionary. cbf_require_dictionary sets *dictionary to the handle of a CBF which has been associated with the CBF handle by cbf_set_dictionary or creates a new empty CBF and associates it with handle, returning the new handle in *dictionary. ARGUMENTS handle CBF handle. dictionary Pointer to CBF handle of dictionary. dictionary_in CBF handle of dcitionary. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_dictionary(self, *args) def find_tag_category(self, *args): """ Returns : String categoryname *args : String tagname C prototype: int cbf_find_tag_category (cbf_handle handle, const char* tagname, const char** categoryname); CBFLib documentation: DESCRIPTION cbf_find_tag_category sets categoryname to the category associated with tagname in the dictionary associated with handle. cbf_set_tag_category upddates the dictionary associated with handle to indicated that tagname is in category categoryname_in. ARGUMENTS handle CBF handle. tagname tag name. categoryname pointer to a returned category name. categoryname_in input category name. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_find_tag_category(self, *args) def get_real_3d_image_sf_as_string(self, *args): """ Returns : (Binary)String *args : int element_number,int elsize,int ndimslow,int ndimmid,int ndimfast C prototype: int cbf_get_real_3d_image_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image array for element number element_number into an array. The array consists of ndimslow *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and cbf_get_real_image_sf read the image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. cbf_get_3d_image, cbf_get_3d_image_fs and cbf_get_3d_image_sf read the 3D image array for element number element_number into an array. The array consists of ndimslow *ndimmid *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order The structure of the array as a 1-, 2- or 3-dimensional array should agree with the structure of the array given in the ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1 both in the call and in the imgCIF data being processed. If the array is 2-dimensional and a 3D call is used, ndimslow and ndimmid should be the """ return _pycbf.cbf_handle_struct_get_real_3d_image_sf_as_string(self, *args) def set_typeofvalue(self, *args): """ Returns : string *args : C prototype: int cbf_set_typeofvalue (cbf_handle handle, const char *typeofvalue); CBFLib documentation: DESCRIPTION cbf_set_typeofvalue sets the type of the item at the current column and row to the type specified by the ASCII character string given by typeofvalue. The strings that may be used are: "null " for a null value indicated by a ". " or a "? " "bnry " for a binary value "word " for an unquoted string "dblq " for a double-quoted string "sglq " for a single-quoted string "text " for a semicolon-quoted string (multiline text field) "prns " for a parenthesis-bracketed string (multiline text field) "brcs " for a brace-bracketed string (multiline text field) "bkts " for a square-bracket-bracketed string (multiline text field) "tsqs " for a treble-single-quote quoted string (multiline text field) "tdqs " for a treble-double-quote quoted string (multiline text field) Not all types may be used for all values. Not all types are valid for all type of CIF files. In partcular the types "prns ", "brcs ", "bkts " were introduced with DDLm and are not valid in DDL1 or DDL2 CIFS. The types "tsqs " and "tdqs " are not formally part of the CIF syntax. No changes may be made to the type of binary values. You may not set the type of a string that contains a single quote followed by a blank or a tab or which contains multiple lines to "sglq ". You may not set the type of a string that contains a double quote followed by a blank or a tab or which contains multiple lines to "dblq ". ARGUMENTS handle CBF handle. typeofvalue ASCII string for desired type of value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_set_typeofvalue(self, *args) def set_integerarray_wdims(self, *args): """ Returns : *args : int compression,int binary_id,(binary) String data,int elsize, int elements,String byteorder,int dimfast,int dimmid,int dimslow, int padding C prototype: int cbf_set_integerarray_wdims (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, int elsigned, size_t elements, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); CBFLib documentation: DESCRIPTION cbf_set_integerarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. The elements are signed if elsigned is non-0 and unsigned otherwise. binary_id is the binary section identifier. cbf_set_realarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. binary_id is the binary section identifier. The cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, cbf_set_integerarray_wdims_sf, cbf_set_realarray_wdims, cbf_set_realarray_wdims_fs and cbf_set_realarray_wdims_sf variants allow the data header values of byteorder, dimfast, dimmid, dimslow and padding to be set to the data byte order, the fastest, second fastest and third fastest array dimensions and the size in byte of the post data padding to be used. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple "byte_offset " compression. CBF_NONE No compression. NOTE: This scheme is by far the slowest of the four and uses much more disk space. It is intended for routine use with small arrays only. With large arrays (like images) it should be used only for debugging. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned), for cbf_set_integerarray, or IEEE doubles or floats for cbf_set_realarray. If elsize is not equal to sizeof (char), sizeof (short) or sizeof (int), the function returns CBF_ARGUMENT. ARGUMENTS handle CBF handle. compression Compression method to use. binary_id Integer binary identifier. array Pointer to the source array. elsize Size in bytes of each source array element. elsigned Set to non-0 if the source array elements are signed. elements: The number of elements in the array. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_set_integerarray_wdims(self, *args) def set_integration_time(self, *args): """ Returns : *args : Float time C prototype: int cbf_set_integration_time (cbf_handle handle, unsigned int reserved, double time); CBFLib documentation: DESCRIPTION cbf_set_integration_time sets the integration time in seconds to the value specified by time. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. time Integration time in seconds. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_integration_time(self, *args) def set_axis_setting(self, *args): """ Returns : *args : String axis_id,Float start,Float increment C prototype: int cbf_set_axis_setting (cbf_handle handle, unsigned int reserved, const char *axis_id, double start, double increment); CBFLib documentation: DESCRIPTION cbf_set_axis_setting sets the starting and increment values of the axis axis_id to start and increment. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. axis_id Axis id. start Start value. increment Increment value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_axis_setting(self, *args) def get_real_image_as_string(self, *args): """ Returns : (Binary)String *args : int element_number,int elsize,int ndimslow,int ndimfast C prototype: int cbf_get_real_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimslow, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image array for element number element_number into an array. The array consists of ndimslow *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and cbf_get_real_image_sf read the image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. cbf_get_3d_image, cbf_get_3d_image_fs and cbf_get_3d_image_sf read the 3D image array for element number element_number into an array. The array consists of ndimslow *ndimmid *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order The structure of the array as a 1-, 2- or 3-dimensional array should agree with the structure of the array given in the ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1 both in the call and in the imgCIF data being processed. If the array is 2-dimensional and a 3D call is used, ndimslow and ndimmid should be the """ return _pycbf.cbf_handle_struct_get_real_image_as_string(self, *args) def get_3d_image_sf_as_string(self, *args): """ Returns : (Binary)String *args : int element_number,int elsize,int elsign,int ndimslow,int ndimmid, int ndimfast C prototype: int cbf_get_3d_image_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image array for element number element_number into an array. The array consists of ndimslow *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and cbf_get_real_image_sf read the image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. cbf_get_3d_image, cbf_get_3d_image_fs and cbf_get_3d_image_sf read the 3D image array for element number element_number into an array. The array consists of ndimslow *ndimmid *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order The structure of the array as a 1-, 2- or 3-dimensional array should agree with the structure of the array given in the ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1 both in the call and in the imgCIF data being processed. If the array is 2-dimensional and a 3D call is used, ndimslow and ndimmid should be the """ return _pycbf.cbf_handle_struct_get_3d_image_sf_as_string(self, *args) def set_real_image_fs(self, *args): """ Returns : *args : int element_number,int compression,(binary) String data,int elsize, int dimfast,int dimslow C prototype: int cbf_set_real_image_fs(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimfast, size_t ndimslow); CBFLib documentation: DESCRIPTION cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-zero and unsigned otherwise. cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow IEEE double or float elements of elsize bytes each, starting at array. cbf_set_3d_image, cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_set_real_3d_image, cbf_set_real_3d_image_fs and cbf_set_real_3d_image_sf writes the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow IEEE double or float elements of elsize bytes each, starting at array. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the array is 2-dimensional and the 3D calls are used, ndimslow and ndimmid should be used for the array dimensions and ndimfast should be set to 1. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple "byte_offset " compression. CBF_NONE No compression. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned)for cbf_set_image, or IEEE doubles or floats for cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame " category. compression Compression type. array Pointer to the image array. elsize Size in bytes of each image array element. elsigned Set to non-0 if the image array elements are signed. ndimslow Slowest array dimension. ndimmid Second slowest array dimension. ndimfast Fastest array dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_real_image_fs(self, *args) def get_overload(self, *args): """ Returns : Float overload *args : Integer element_number C prototype: int cbf_get_overload (cbf_handle handle, unsigned int element_number, double *overload); CBFLib documentation: DESCRIPTION cbf_get_overload sets *overload to the overload value for element number element_number. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame " category. overload Pointer to the destination overload. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_get_overload(self, *args) def get_wavelength(self, *args): """ Returns : double *args : C prototype: int cbf_get_wavelength (cbf_handle handle, double *wavelength); CBFLib documentation: DESCRIPTION cbf_get_wavelength sets *wavelength to the current wavelength in AA. ARGUMENTS handle CBF handle. wavelength Pointer to the destination. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_get_wavelength(self, *args) def next_datablock(self, *args): """ Returns : *args : C prototype: int cbf_next_datablock (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_next_datablock makes the data block following the current data block the current data block. If there are no more data blocks, the function returns CBF_NOTFOUND. The current category becomes undefined. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_next_datablock(self, *args) def get_realarrayparameters_wdims(self): """ Returns : int compression,int binary_id,int elsize,int elements,char **bo, int *bolen,int dimfast,int dimmid,int dimslow,int padding *args : C prototype: int cbf_get_realarrayparameters_wdims (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, size_t *elements, const char **byteorder, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding); CBFLib documentation: DESCRIPTION cbf_get_integerarrayparameters sets *compression, *binary_id, *elsize, *elsigned, *elunsigned, *elements, *minelement and *maxelement to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_integerarray, if a copy of the array is to be made into another CIF or CBF. cbf_get_realarrayparameters sets *compression, *binary_id, *elsize, *elements to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_realarray, if a copy of the arry is to be made into another CIF or CBF. The variants cbf_get_integerarrayparameters_wdims, cbf_get_integerarrayparameters_wdims_fs, cbf_get_integerarrayparameters_wdims_sf, cbf_get_realarrayparameters_wdims, cbf_get_realarrayparameters_wdims_fs, cbf_get_realarrayparameters_wdims_sf set **byteorder, *dimfast, *dimmid, *dimslow, and *padding as well, providing the additional parameters needed for a subsequent call to cbf_set_integerarray_wdims or cbf_set_realarray_wdims. The value returned in *byteorder is a pointer either to the string "little_endian " or to the string "big_endian ". This should be the byte order of the data, not necessarily of the host machine. No attempt should be made to modify this string. At this time only "little_endian " will be returned. The values returned in *dimfast, *dimmid and *dimslow are the sizes of the fastest changing, second fastest changing and third fastest changing dimensions of the array, if specified, or zero, if not specified. The value returned in *padding is the size of the post-data padding, if any and if specified in the data header. The value is given as a count of octets. If the value is not binary, the function returns CBF_ASCII. ARGUMENTS handle CBF handle. compression Compression method used. elsize Size in bytes of each array element. binary_id Pointer to the destination integer binary identifier. elsigned Pointer to an integer. Set to 1 if the elements can be read as signed integers. elunsigned Pointer to an integer. Set to 1 if the elements can be read as unsigned integers. elements Pointer to the destination number of elements. minelement Pointer to the destination smallest element. maxelement Pointer to the destination largest element. byteorder Pointer to the destination byte order. dimfast Pointer to the destination fastest dimension. dimmid Pointer to the destination second fastest dimension. dimslow Pointer to the destination third fastest dimension. padding Pointer to the destination padding size. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_get_realarrayparameters_wdims(self) def set_orientation_matrix(self, *args): """ Returns : *args : Float matrix_0,Float matrix_1,Float matrix_2,Float matrix_3, Float matrix_4,Float matrix_5,Float matrix_6,Float matrix_7, Float matrix_8 C prototype: int cbf_set_orientation_matrix (cbf_handle handle, double ub_matrix[9]); CBFLib documentation: DESCRIPTION cbf_get_orientation_matrix sets ub_matrix to point to the array of orientation matrix entries in the "diffrn " category in the order of columns: "UB[1][1] " "UB[1][2] " "UB[1][3] " "UB[2][1] " "UB[2][2] " "UB[2][3] " "UB[3][1] " "UB[3][2] " "UB[3][3] " cbf_set_orientation_matrix sets the values in the "diffrn " category to the values pointed to by ub_matrix. ARGUMENTS handle CBF handle. ubmatric Source or destination array of 9 doubles giving the orientation matrix parameters. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_orientation_matrix(self, *args) def new_category(self, *args): """ Returns : string *args : C prototype: int cbf_new_category (cbf_handle handle, const char *categoryname); CBFLib documentation: DESCRIPTION cbf_new_category creates a new category in the current data block with name categoryname and makes it the current category. If a category with this name already exists, the existing category becomes the current category. ARGUMENTS handle CBF handle. categoryname The name of the new category. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_new_category(self, *args) def set_gain(self, *args): """ Returns : *args : Float gain,Float gain_esd C prototype: int cbf_set_gain (cbf_handle handle, unsigned int element_number, double gain, double gain_esd); CBFLib documentation: DESCRIPTION cbf_set_gain sets the gain of element number element_number to the values specified by gain and gain_esd. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame " category. gain New gain value. gain_esd New gain_esd value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_gain(self, *args) def find_column(self, *args): """ Returns : string *args : C prototype: int cbf_find_column (cbf_handle handle, const char *columnname); CBFLib documentation: DESCRIPTION cbf_find_column makes the columns in the current category with name columnname the current column. The comparison is case-insensitive. If the column does not exist, the function returns CBF_NOTFOUND. The current row is not affected. ARGUMENTS handle CBF handle. columnname The name of column to find. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_find_column(self, *args) def remove_category(self, *args): """ Returns : *args : C prototype: int cbf_remove_category (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_remove_category deletes the current category. The current category becomes undefined. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_remove_category(self, *args) def get_integerarrayparameters_wdims_sf(self): """ Returns : int compression,int binary_id,int elsize,int elsigned,int elunsigned, int elements,int minelement,int maxelement,char **bo,int *bolen, int dimslow,int dimmid,int dimfast,int padding *args : C prototype: int cbf_get_integerarrayparameters_wdims_sf (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, int *elsigned, int *elunsigned, size_t *elements, int *minelement, int *maxelement, const char **byteorder, size_t *dimslow, size_t *dimmid, size_t *dimfast, size_t *padding); CBFLib documentation: DESCRIPTION cbf_get_integerarrayparameters sets *compression, *binary_id, *elsize, *elsigned, *elunsigned, *elements, *minelement and *maxelement to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_integerarray, if a copy of the array is to be made into another CIF or CBF. cbf_get_realarrayparameters sets *compression, *binary_id, *elsize, *elements to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_realarray, if a copy of the arry is to be made into another CIF or CBF. The variants cbf_get_integerarrayparameters_wdims, cbf_get_integerarrayparameters_wdims_fs, cbf_get_integerarrayparameters_wdims_sf, cbf_get_realarrayparameters_wdims, cbf_get_realarrayparameters_wdims_fs, cbf_get_realarrayparameters_wdims_sf set **byteorder, *dimfast, *dimmid, *dimslow, and *padding as well, providing the additional parameters needed for a subsequent call to cbf_set_integerarray_wdims or cbf_set_realarray_wdims. The value returned in *byteorder is a pointer either to the string "little_endian " or to the string "big_endian ". This should be the byte order of the data, not necessarily of the host machine. No attempt should be made to modify this string. At this time only "little_endian " will be returned. The values returned in *dimfast, *dimmid and *dimslow are the sizes of the fastest changing, second fastest changing and third fastest changing dimensions of the array, if specified, or zero, if not specified. The value returned in *padding is the size of the post-data padding, if any and if specified in the data header. The value is given as a count of octets. If the value is not binary, the function returns CBF_ASCII. ARGUMENTS handle CBF handle. compression Compression method used. elsize Size in bytes of each array element. binary_id Pointer to the destination integer binary identifier. elsigned Pointer to an integer. Set to 1 if the elements can be read as signed integers. elunsigned Pointer to an integer. Set to 1 if the elements can be read as unsigned integers. elements Pointer to the destination number of elements. minelement Pointer to the destination smallest element. maxelement Pointer to the destination largest element. byteorder Pointer to the destination byte order. dimfast Pointer to the destination fastest dimension. dimmid Pointer to the destination second fastest dimension. dimslow Pointer to the destination third fastest dimension. padding Pointer to the destination padding size. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_get_integerarrayparameters_wdims_sf(self) def get_pixel_size(self, *args): """ Returns : Float pixel_size *args : Int element_number,Int axis_number C prototype: int cbf_get_pixel_size (cbf_handle handle, unsigned int element_number, int axis_number, double *psize); CBFLib documentation: DESCRIPTION cbf_get_pixel_size and cbf_get_pixel_size_sf set *psize to point to the double value in millimeters of the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the slowest axis. cbf_get_pixel_size_fs sets *psize to point to the double value in millimeters of the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the fastest axis. If a negative axis number is given, the order of axes is reversed, so that -1 specifies the slowest axis for cbf_get_pixel_size_fs and the fastest axis for cbf_get_pixel_size_sf. If the pixel size is not given explcitly in the "array_element_size " category, the function returns CBF_NOTFOUND. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame " category. axis_number The number of the axis, starting from 1 for the fastest for cbf_get_pixel_size and cbf_get_pixel_size_fs and the slowest for cbf_get_pixel_size_sf. psize Pointer to the destination pixel size. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_get_pixel_size(self, *args) def set_real_image_sf(self, *args): """ Returns : *args : int element_number,int compression,(binary) String data,int elsize, int dimslow,int dimfast C prototype: int cbf_set_real_image_sf(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimslow, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-zero and unsigned otherwise. cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow IEEE double or float elements of elsize bytes each, starting at array. cbf_set_3d_image, cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_set_real_3d_image, cbf_set_real_3d_image_fs and cbf_set_real_3d_image_sf writes the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow IEEE double or float elements of elsize bytes each, starting at array. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the array is 2-dimensional and the 3D calls are used, ndimslow and ndimmid should be used for the array dimensions and ndimfast should be set to 1. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple "byte_offset " compression. CBF_NONE No compression. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned)for cbf_set_image, or IEEE doubles or floats for cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame " category. compression Compression type. array Pointer to the image array. elsize Size in bytes of each image array element. elsigned Set to non-0 if the image array elements are signed. ndimslow Slowest array dimension. ndimmid Second slowest array dimension. ndimfast Fastest array dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_real_image_sf(self, *args) def require_category(self, *args): """ Returns : string *args : C prototype: int cbf_require_category (cbf_handle handle, const char *categoryname); CBFLib documentation: DESCRIPTION cbf_rewuire_category makes the category in the current data block with name categoryname the current category, if it exists, or creates the catagory if it does not exist. The comparison is case-insensitive. The current column and row become undefined. ARGUMENTS handle CBF handle. categoryname The name of the category to find. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_require_category(self, *args) def get_reciprocal_cell(self): """ Returns : Float astar,Float bstar,Float cstar,Float alphastar,Float betastar, Float gammastar *args : C prototype: int cbf_get_reciprocal_cell (cbf_handle handle, double cell[6], double cell_esd[6] ); CBFLib documentation: DESCRIPTION cbf_get_reciprocal_cell sets cell[0:2] to the double values of the reciprocal cell edge lengths a*, b* and c* in AAngstroms-1, cell[3:5] to the double values of the reciprocal cell angles a*, b* and g* in degrees, cell_esd[0:2] to the double values of the estimated strandard deviations of the reciprocal cell edge lengths a*, b* and c* in AAngstroms-1, cell_esd[3:5] to the double values of the estimated standard deviations of the the reciprocal cell angles a*, b* and g* in degrees. The values returned are retrieved from the first row of the "cell " category. The value of "_cell.entry_id " is ignored. cell or cell_esd may be NULL. If cell is NULL, the reciprocal cell parameters are not retrieved. If cell_esd is NULL, the reciprocal cell parameter esds are not retrieved. If the "cell " category is present, but some of the values are missing, zeros are returned for the missing values. ARGUMENTS handle CBF handle. cell Pointer to the destination array of 6 doubles for the reciprocal cell parameters. cell_esd Pointer to the destination array of 6 doubles for the reciprocal cell parameter esds. RETURN VALUE Returns an error code on failure or 0 for success. No errors is returned for missing values if the "cell " category exists. SEE ALSO """ return _pycbf.cbf_handle_struct_get_reciprocal_cell(self) def get_reciprocal_cell_esd(self): """get_reciprocal_cell_esd(self)""" return _pycbf.cbf_handle_struct_get_reciprocal_cell_esd(self) def get_3d_image_size(self, *args): """ Returns : size_t ndimslow,size_t ndimmid,size_t ndimfast *args : Integer element_number C prototype: int cbf_get_3d_image_size (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimslow, size_t *ndimmid, size_t *ndimfast); CBFLib documentation: DESCRIPTION cbf_get_image_size, cbf_get_image_size_fs and cbf_get_image_size_sf set *ndimslow and *ndimfast to the slow and fast dimensions of the image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimfast will be set to 1. If the array is 3-dimensional an error code will be returned. cbf_get_3d_image_size, cbf_get_3d_image_size_fs and cbf_get_3d_image_size_sf set *ndimslow, *ndimmid and *ndimfast to the slowest, next fastest and fastest dimensions, respectively, of the 3D image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimmid and """ return _pycbf.cbf_handle_struct_get_3d_image_size(self, *args) def find_tag_root(self, *args): """ Returns : String tagroot *args : String tagname C prototype: int cbf_find_tag_root (cbf_handle handle, const char* tagname, const char** tagroot); CBFLib documentation: DESCRIPTION cbf_find_tag_root sets *tagroot to the root tag of which tagname is an alias. cbf_set_tag_root sets tagname as an alias of tagroot_in in the dictionary associated with handle, creating the dictionary if necessary. cbf_require_tag_root sets *tagroot to the root tag of which tagname is an alias, if there is one, or to the value of tagname, if tagname is not an alias. A returned tagroot string must not be modified in any way. ARGUMENTS handle CBF handle. tagname tag name which may be an alias. tagroot pointer to a returned tag root name. tagroot_in input tag root name. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_find_tag_root(self, *args) def require_category_root(self, *args): """require_category_root(self, char categoryname) -> char""" return _pycbf.cbf_handle_struct_require_category_root(self, *args) def set_realarray_wdims_sf(self, *args): """ Returns : *args : int compression,int binary_id,(binary) String data,int elsize, int elements,String byteorder,int dimslow,int dimmid,int dimfast, int padding C prototype: int cbf_set_realarray_wdims_sf (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, size_t elements, const char *byteorder, size_t dimslow, size_t dimmid, size_t dimfast, size_t padding); CBFLib documentation: DESCRIPTION cbf_set_integerarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. The elements are signed if elsigned is non-0 and unsigned otherwise. binary_id is the binary section identifier. cbf_set_realarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. binary_id is the binary section identifier. The cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, cbf_set_integerarray_wdims_sf, cbf_set_realarray_wdims, cbf_set_realarray_wdims_fs and cbf_set_realarray_wdims_sf variants allow the data header values of byteorder, dimfast, dimmid, dimslow and padding to be set to the data byte order, the fastest, second fastest and third fastest array dimensions and the size in byte of the post data padding to be used. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple "byte_offset " compression. CBF_NONE No compression. NOTE: This scheme is by far the slowest of the four and uses much more disk space. It is intended for routine use with small arrays only. With large arrays (like images) it should be used only for debugging. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned), for cbf_set_integerarray, or IEEE doubles or floats for cbf_set_realarray. If elsize is not equal to sizeof (char), sizeof (short) or sizeof (int), the function returns CBF_ARGUMENT. ARGUMENTS handle CBF handle. compression Compression method to use. binary_id Integer binary identifier. array Pointer to the source array. elsize Size in bytes of each source array element. elsigned Set to non-0 if the source array elements are signed. elements: The number of elements in the array. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_set_realarray_wdims_sf(self, *args) def set_integervalue(self, *args): """ Returns : int number *args : C prototype: int cbf_set_integervalue (cbf_handle handle, int number); CBFLib documentation: DESCRIPTION cbf_set_integervalue sets the item at the current column and row to the integer value number written as a decimal ASCII string. ARGUMENTS handle CBF handle. number Integer value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_set_integervalue(self, *args) def category_name(self, *args): """ Returns : *args : string C prototype: int cbf_category_name (cbf_handle handle, const char **categoryname); CBFLib documentation: DESCRIPTION cbf_category_name sets *categoryname to point to the name of the current category of the current data block. The category name will be valid as long as the category exists. The name must not be modified by the program in any way. ARGUMENTS handle CBF handle. categoryname Pointer to the destination category name pointer. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_category_name(self, *args) def get_typeofvalue(self, *args): """ Returns : *args : string C prototype: int cbf_get_typeofvalue (cbf_handle handle, const char **typeofvalue); CBFLib documentation: DESCRIPTION cbf_get_value sets *typeofvalue to point an ASCII descriptor of the value of the item at the current column and row. The strings that may be returned are: "null " for a null value indicated by a ". " or a "? " "bnry " for a binary value "word " for an unquoted string "dblq " for a double-quoted string "sglq " for a single-quoted string "text " for a semicolon-quoted string (multiline text field) "prns " for a parenthesis-bracketed string (multiline text field) "brcs " for a brace-bracketed string (multiline text field) "bkts " for a square-bracket-bracketed string (multiline text field) "tsqs " for a treble-single-quote quoted string (multiline text field) "tdqs " for a treble-double-quote quoted string (multiline text field) Not all types are valid for all type of CIF files. In partcular the types "prns ", "brcs ", "bkts " were introduced with DDLm and are not valid in DDL1 or DDL2 CIFS. The types "tsqs " and "tdqs " are not formally part of the CIF syntax. A field for which no value has been set sets *typeofvalue to NULL rather than to the string "null ". The typeofvalue must not be modified by the program in any way. ARGUMENTS handle CBF handle. typeofvalue Pointer to the destination type-of-value string pointer. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_get_typeofvalue(self, *args) def set_real_image(self, *args): """ Returns : *args : int element_number,int compression,(binary) String data,int elsize, int dimslow,int dimfast C prototype: int cbf_set_real_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimslow, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-zero and unsigned otherwise. cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow IEEE double or float elements of elsize bytes each, starting at array. cbf_set_3d_image, cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_set_real_3d_image, cbf_set_real_3d_image_fs and cbf_set_real_3d_image_sf writes the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow IEEE double or float elements of elsize bytes each, starting at array. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the array is 2-dimensional and the 3D calls are used, ndimslow and ndimmid should be used for the array dimensions and ndimfast should be set to 1. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple "byte_offset " compression. CBF_NONE No compression. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned)for cbf_set_image, or IEEE doubles or floats for cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame " category. compression Compression type. array Pointer to the image array. elsize Size in bytes of each image array element. elsigned Set to non-0 if the image array elements are signed. ndimslow Slowest array dimension. ndimmid Second slowest array dimension. ndimfast Fastest array dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_real_image(self, *args) def get_3d_image_as_string(self, *args): """ Returns : (Binary)String *args : int element_number,int elsize,int elsign,int ndimslow,int ndimmid, int ndimfast C prototype: int cbf_get_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image array for element number element_number into an array. The array consists of ndimslow *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and cbf_get_real_image_sf read the image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. cbf_get_3d_image, cbf_get_3d_image_fs and cbf_get_3d_image_sf read the 3D image array for element number element_number into an array. The array consists of ndimslow *ndimmid *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order The structure of the array as a 1-, 2- or 3-dimensional array should agree with the structure of the array given in the ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1 both in the call and in the imgCIF data being processed. If the array is 2-dimensional and a 3D call is used, ndimslow and ndimmid should be the """ return _pycbf.cbf_handle_struct_get_3d_image_as_string(self, *args) def remove_row(self, *args): """ Returns : *args : C prototype: int cbf_remove_row (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_remove_row deletes the current row in the current category. If the current row was the last row, it will move down by 1, otherwise, it will remain the same. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_remove_row(self, *args) def set_overload(self, *args): """ Returns : *args : Integer element_number,Float overload C prototype: int cbf_set_overload (cbf_handle handle, unsigned int element_number, double overload); CBFLib documentation: DESCRIPTION cbf_set_overload sets the overload value of element number element_number to overload. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame " category. overload New overload value. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_overload(self, *args) def get_image_size(self, *args): """ Returns : size_t ndim1,size_t ndim2 *args : Integer element_number C prototype: int cbf_get_image_size (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimslow, size_t *ndimfast); CBFLib documentation: DESCRIPTION cbf_get_image_size, cbf_get_image_size_fs and cbf_get_image_size_sf set *ndimslow and *ndimfast to the slow and fast dimensions of the image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimfast will be set to 1. If the array is 3-dimensional an error code will be returned. cbf_get_3d_image_size, cbf_get_3d_image_size_fs and cbf_get_3d_image_size_sf set *ndimslow, *ndimmid and *ndimfast to the slowest, next fastest and fastest dimensions, respectively, of the 3D image array for element number element_number. If the array is 1-dimensional, *ndimslow will be set to the array size and *ndimmid and """ return _pycbf.cbf_handle_struct_get_image_size(self, *args) def set_3d_image_sf(self, *args): """ Returns : *args : int element_number,int compression,(binary) String data,int elsize, int elsign,int dimslow,int dimmid,int dimfast C prototype: int cbf_set_3d_image_sf(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-zero and unsigned otherwise. cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow IEEE double or float elements of elsize bytes each, starting at array. cbf_set_3d_image, cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_set_real_3d_image, cbf_set_real_3d_image_fs and cbf_set_real_3d_image_sf writes the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow IEEE double or float elements of elsize bytes each, starting at array. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the array is 2-dimensional and the 3D calls are used, ndimslow and ndimmid should be used for the array dimensions and ndimfast should be set to 1. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple "byte_offset " compression. CBF_NONE No compression. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned)for cbf_set_image, or IEEE doubles or floats for cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame " category. compression Compression type. array Pointer to the image array. elsize Size in bytes of each image array element. elsigned Set to non-0 if the image array elements are signed. ndimslow Slowest array dimension. ndimmid Second slowest array dimension. ndimfast Fastest array dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_3d_image_sf(self, *args) def get_real_image_sf_as_string(self, *args): """ Returns : (Binary)String *args : int element_number,int elsize,int ndimslow,int ndimfast C prototype: int cbf_get_real_image_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimslow, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image array for element number element_number into an array. The array consists of ndimslow *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and cbf_get_real_image_sf read the image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. cbf_get_3d_image, cbf_get_3d_image_fs and cbf_get_3d_image_sf read the 3D image array for element number element_number into an array. The array consists of ndimslow *ndimmid *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order The structure of the array as a 1-, 2- or 3-dimensional array should agree with the structure of the array given in the ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1 both in the call and in the imgCIF data being processed. If the array is 2-dimensional and a 3D call is used, ndimslow and ndimmid should be the """ return _pycbf.cbf_handle_struct_get_real_image_sf_as_string(self, *args) def get_image_as_string(self, *args): """ Returns : (Binary)String *args : int element_number,int elsize,int elsign,int ndimslow,int ndimfast C prototype: int cbf_get_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image array for element number element_number into an array. The array consists of ndimslow *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and cbf_get_real_image_sf read the image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. cbf_get_3d_image, cbf_get_3d_image_fs and cbf_get_3d_image_sf read the 3D image array for element number element_number into an array. The array consists of ndimslow *ndimmid *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order The structure of the array as a 1-, 2- or 3-dimensional array should agree with the structure of the array given in the ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1 both in the call and in the imgCIF data being processed. If the array is 2-dimensional and a 3D call is used, ndimslow and ndimmid should be the """ return _pycbf.cbf_handle_struct_get_image_as_string(self, *args) def set_tag_root(self, *args): """ Returns : *args : String tagname,String tagroot_in C prototype: int cbf_set_tag_root (cbf_handle handle, const char* tagname, const char*tagroot_in); CBFLib documentation: DESCRIPTION cbf_find_tag_root sets *tagroot to the root tag of which tagname is an alias. cbf_set_tag_root sets tagname as an alias of tagroot_in in the dictionary associated with handle, creating the dictionary if necessary. cbf_require_tag_root sets *tagroot to the root tag of which tagname is an alias, if there is one, or to the value of tagname, if tagname is not an alias. A returned tagroot string must not be modified in any way. ARGUMENTS handle CBF handle. tagname tag name which may be an alias. tagroot pointer to a returned tag root name. tagroot_in input tag root name. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_tag_root(self, *args) def write_widefile(self, *args): """ Returns : *args : String filename,Integer ciforcbf,Integer Headers,Integer encoding C prototype: int cbf_write_widefile (cbf_handle handle, FILE *file, int readable, int ciforcbf, int flags, int encoding); CBFLib documentation: DESCRIPTION cbf_write_file writes the CBF object specified by handle into the file file, following CIF 1.0 conventions of 80 character lines. cbf_write_widefile writes the CBF object specified by handle into the file file, following CIF 1.1 conventions of 2048 character lines. A warning is issued to stderr for ascii lines over the limit, and an attempt is made to fold lines to fit. No test is performed on binary sections. If a dictionary has been provided, aliases will be applied on output. Unlike cbf_read_file, the file does not have to be random-access. If the file is random-access and readable, readable can be set to non-0 to indicate to CBFlib that the file can be used as a buffer to conserve disk space. If the file is not random-access or not readable, readable must be 0. """ return _pycbf.cbf_handle_struct_write_widefile(self, *args) def count_rows(self, *args): """ Returns : Integer *args : C prototype: int cbf_count_rows (cbf_handle handle, unsigned int *rows); CBFLib documentation: DESCRIPTION cbf_count_rows puts the number of rows in the current category in *rows . ARGUMENTS handle CBF handle. rows Pointer to the destination row count. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_count_rows(self, *args) def require_datablock(self, *args): """ Returns : string *args : C prototype: int cbf_require_datablock (cbf_handle handle, const char *datablockname); CBFLib documentation: DESCRIPTION cbf_require_datablock makes the data block with name datablockname the current data block, if it exists, or creates it if it does not. The comparison is case-insensitive. The current category becomes undefined. ARGUMENTS handle CBF handle. datablockname The name of the data block to find or create. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_require_datablock(self, *args) def set_integerarray(self, *args): """ Returns : *args : int compression,int binary_id,(binary) String data,int elsize, int elsigned,int elements C prototype: int cbf_set_integerarray (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, int elsigned, size_t elements); CBFLib documentation: DESCRIPTION cbf_set_integerarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. The elements are signed if elsigned is non-0 and unsigned otherwise. binary_id is the binary section identifier. cbf_set_realarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. binary_id is the binary section identifier. The cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, cbf_set_integerarray_wdims_sf, cbf_set_realarray_wdims, cbf_set_realarray_wdims_fs and cbf_set_realarray_wdims_sf variants allow the data header values of byteorder, dimfast, dimmid, dimslow and padding to be set to the data byte order, the fastest, second fastest and third fastest array dimensions and the size in byte of the post data padding to be used. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple "byte_offset " compression. CBF_NONE No compression. NOTE: This scheme is by far the slowest of the four and uses much more disk space. It is intended for routine use with small arrays only. With large arrays (like images) it should be used only for debugging. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned), for cbf_set_integerarray, or IEEE doubles or floats for cbf_set_realarray. If elsize is not equal to sizeof (char), sizeof (short) or sizeof (int), the function returns CBF_ARGUMENT. ARGUMENTS handle CBF handle. compression Compression method to use. binary_id Integer binary identifier. array Pointer to the source array. elsize Size in bytes of each source array element. elsigned Set to non-0 if the source array elements are signed. elements: The number of elements in the array. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_set_integerarray(self, *args) def new_datablock(self, *args): """ Returns : string *args : C prototype: int cbf_new_datablock (cbf_handle handle, const char *datablockname); CBFLib documentation: DESCRIPTION cbf_new_datablock creates a new data block with name datablockname and makes it the current data block. cbf_new_saveframe creates a new save frame with name saveframename within the current data block and makes the new save frame the current save frame. If a data block or save frame with this name already exists, the existing data block or save frame becomes the current data block or save frame. ARGUMENTS handle CBF handle. datablockname The name of the new data block. saveframename The name of the new save frame. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_new_datablock(self, *args) def set_datestamp(self, *args): """ Returns : *args : int year,int month,int day,int hour,int minute,double second, int timezone,Float precision C prototype: int cbf_set_datestamp (cbf_handle handle, unsigned int reserved, int year, int month, int day, int hour, int minute, double second, int timezone, double precision); CBFLib documentation: DESCRIPTION cbf_set_datestamp sets the collection timestamp in seconds since January 1 1970 to the value specified by time. The timezone difference from UTC """ return _pycbf.cbf_handle_struct_set_datestamp(self, *args) def next_row(self, *args): """ Returns : *args : C prototype: int cbf_next_row (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_next_row makes the row following the current row in the current category the current row. If there are no more rows, the function returns CBF_NOTFOUND. The current column is not affected. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_next_row(self, *args) def set_category_root(self, *args): """ Returns : *args : String categoryname,String categoryroot C prototype: int cbf_set_category_root (cbf_handle handle, const char* categoryname_in, const char*categoryroot); CBFLib documentation: DESCRIPTION cbf_find_category_root sets *categoryroot to the root category of which categoryname is an alias. cbf_set_category_root sets categoryname_in as an alias of categoryroot in the dictionary associated with handle, creating the dictionary if necessary. cbf_require_category_root sets *categoryroot to the root category of which categoryname is an alias, if there is one, or to the value of categoryname, if categoryname is not an alias. A returned categoryroot string must not be modified in any way. ARGUMENTS handle CBF handle. categoryname category name which may be an alias. categoryroot pointer to a returned category root name. categoryroot_in input category root name. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_category_root(self, *args) def set_pixel_size_fs(self, *args): """ Returns : *args : Int element_number,Int axis_number,Float pixel size C prototype: int cbf_set_pixel_size_fs(cbf_handle handle, unsigned int element_number, int axis_number, double psize); CBFLib documentation: DESCRIPTION cbf_set_pixel_size and cbf_set_pixel_size_sf set the item in the "e;size"e; column of the "array_structure_list " category at the row which matches axis axis_number of the detector element element_number converting the double pixel size psize from meters to millimeters in storing it in the "size " column for the axis axis_number of the detector element element_number. The axis_number is numbered from 1, starting with the slowest axis. cbf_set_pixel_size_fs sets the item """ return _pycbf.cbf_handle_struct_set_pixel_size_fs(self, *args) def insert_row(self, *args): """ Returns : *args : Integer C prototype: int cbf_insert_row (cbf_handle handle, unsigned int rownumber); CBFLib documentation: DESCRIPTION cbf_insert_row adds a new row to the current category. The new row is inserted as row rownumber and existing rows starting from rownumber are moved up by 1. The new row becomes the current row. If the category has fewer than rownumber rows, the function returns CBF_NOTFOUND. The row numbers start from 0. ARGUMENTS handle CBF handle. rownumber The row number of the new row. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_insert_row(self, *args) def new_column(self, *args): """ Returns : string *args : C prototype: int cbf_new_column (cbf_handle handle, const char *columnname); CBFLib documentation: DESCRIPTION cbf_new_column creates a new column in the current category with name columnname and makes it the current column. If a column with this name already exists, the existing column becomes the current category. ARGUMENTS handle CBF handle. columnname The name of the new column. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_new_column(self, *args) def get_real_3d_image_as_string(self, *args): """ Returns : (Binary)String *args : int element_number,int elsize,int ndimslow,int ndimmid,int ndimfast C prototype: int cbf_get_real_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image array for element number element_number into an array. The array consists of ndimslow *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and cbf_get_real_image_sf read the image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. cbf_get_3d_image, cbf_get_3d_image_fs and cbf_get_3d_image_sf read the 3D image array for element number element_number into an array. The array consists of ndimslow *ndimmid *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order The structure of the array as a 1-, 2- or 3-dimensional array should agree with the structure of the array given in the ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1 both in the call and in the imgCIF data being processed. If the array is 2-dimensional and a 3D call is used, ndimslow and ndimmid should be the """ return _pycbf.cbf_handle_struct_get_real_3d_image_as_string(self, *args) def get_integration_time(self): """ Returns : Float time *args : C prototype: int cbf_get_integration_time (cbf_handle handle, unsigned int reserved, double *time); CBFLib documentation: DESCRIPTION cbf_get_integration_time sets *time to the integration time in seconds. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. time Pointer to the destination time. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_get_integration_time(self) def set_realarray(self, *args): """ Returns : *args : int compression,int binary_id,(binary) String data,int elsize, int elements C prototype: int cbf_set_realarray (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, size_t elements); CBFLib documentation: DESCRIPTION cbf_set_integerarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. The elements are signed if elsigned is non-0 and unsigned otherwise. binary_id is the binary section identifier. cbf_set_realarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. binary_id is the binary section identifier. The cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, cbf_set_integerarray_wdims_sf, cbf_set_realarray_wdims, cbf_set_realarray_wdims_fs and cbf_set_realarray_wdims_sf variants allow the data header values of byteorder, dimfast, dimmid, dimslow and padding to be set to the data byte order, the fastest, second fastest and third fastest array dimensions and the size in byte of the post data padding to be used. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple "byte_offset " compression. CBF_NONE No compression. NOTE: This scheme is by far the slowest of the four and uses much more disk space. It is intended for routine use with small arrays only. With large arrays (like images) it should be used only for debugging. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned), for cbf_set_integerarray, or IEEE doubles or floats for cbf_set_realarray. If elsize is not equal to sizeof (char), sizeof (short) or sizeof (int), the function returns CBF_ARGUMENT. ARGUMENTS handle CBF handle. compression Compression method to use. binary_id Integer binary identifier. array Pointer to the source array. elsize Size in bytes of each source array element. elsigned Set to non-0 if the source array elements are signed. elements: The number of elements in the array. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_set_realarray(self, *args) def get_element_id(self, *args): """ Returns : String *args : Integer element_number C prototype: int cbf_get_element_id (cbf_handle handle, unsigned int element_number, const char **element_id); CBFLib documentation: DESCRIPTION cbf_get_element_id sets *element_id to point to the ASCII value of the element_number'th "diffrn_data_frame.detector_element_id " entry, counting from 0. If the detector element does not exist, the function returns CBF_NOTFOUND. The element_id will be valid as long as the item exists and has not been set to a new value. The element_id must not be modified by the program in any way. ARGUMENTS handle CBF handle. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame " category. element_id Pointer to the destination. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_get_element_id(self, *args) def get_image_sf_as_string(self, *args): """ Returns : (Binary)String *args : int element_number,int elsize,int elsign,int ndimslow,int ndimfast C prototype: int cbf_get_image_sf (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_get_image, cbf_get_image_fs and cbf_get_image_sf read the image array for element number element_number into an array. The array consists of ndimslow *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_image, cbf_get_real_image_fs and cbf_get_real_image_sf read the image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. cbf_get_3d_image, cbf_get_3d_image_fs and cbf_get_3d_image_sf read the 3D image array for element number element_number into an array. The array consists of ndimslow *ndimmid *ndimfast elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_get_real_3d_image, cbf_get_real_3d_image_fs, cbf_get_real_3d_image_sf reads the 3D image array of IEEE doubles or floats for element number element_number into an array. A real array is always signed. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order The structure of the array as a 1-, 2- or 3-dimensional array should agree with the structure of the array given in the ARRAY_STRUCTURE_LIST category. If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1 both in the call and in the imgCIF data being processed. If the array is 2-dimensional and a 3D call is used, ndimslow and ndimmid should be the """ return _pycbf.cbf_handle_struct_get_image_sf_as_string(self, *args) def get_3d_image_size_fs(self, *args): """get_3d_image_size_fs(self, unsigned int element_number)""" return _pycbf.cbf_handle_struct_get_3d_image_size_fs(self, *args) def set_value(self, *args): """ Returns : string *args : C prototype: int cbf_set_value (cbf_handle handle, const char *value); CBFLib documentation: DESCRIPTION cbf_set_value sets the item at the current column and row to the ASCII value value. ARGUMENTS handle CBF handle. value ASCII value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_set_value(self, *args) def set_current_timestamp(self, *args): """ Returns : *args : Integer timezone C prototype: int cbf_set_current_timestamp (cbf_handle handle, unsigned int reserved, int timezone); CBFLib documentation: DESCRIPTION cbf_set_current_timestamp sets the collection timestamp to the current time. The timezone difference from UTC in minutes is set to timezone. If no timezone is desired, timezone should be CBF_NOTIMEZONE. If no timezone is used, the timest amp will be UTC. The parameter reserved is presently unused and should be set to 0. The new timestamp will have a precision of 1 second. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. timezone Timezone difference from UTC in minutes or CBF_NOTIMEZONE. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_current_timestamp(self, *args) def require_doublevalue(self, *args): """ Returns : Float Number *args : Float Default C prototype: int cbf_require_doublevalue (cbf_handle handle, double *number, double defaultvalue); CBFLib documentation: DESCRIPTION cbf_get_doublevalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal floating-point number. cbf_require_doublevalue sets *number to the value of the ASCII item at the current column and row interpreted as a decimal floating-point number, setting it to defaultvalue if necessary. If the value is not ASCII, the function returns CBF_BINARY. ARGUMENTS handle CBF handle. number Pointer to the destination number. defaultvalue default number value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_require_doublevalue(self, *args) def rewind_datablock(self, *args): """ Returns : *args : C prototype: int cbf_rewind_datablock (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_rewind_datablock makes the first data block the current data block. If there are no data blocks, the function returns CBF_NOTFOUND. The current category becomes undefined. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_rewind_datablock(self, *args) def require_column_value(self, *args): """ Returns : String Name *args : String columnnanme,String Default C prototype: int cbf_require_column_value (cbf_handle handle, const char *columnname, const char **value, const char *defaultvalue); CBFLib documentation: DESCRIPTION cbf_require_column_doublevalue sets *value to the ASCII item at the current row for the column given with the name given by *columnname, or to the string given by defaultvalue if the item cannot be found. ARGUMENTS handle CBF handle. columnname Name of the column containing the number. value pointer to the location to receive the value. defaultvalue Value to use if the requested column and value cannot be found. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_require_column_value(self, *args) def get_dictionary(self): """ Returns : CBFHandle dictionary *args : C prototype: int cbf_get_dictionary (cbf_handle handle, cbf_handle * dictionary); CBFLib documentation: DESCRIPTION cbf_get_dictionary sets *dictionary to the handle of a CBF which has been associated with the CBF handle by cbf_set_dictionary. cbf_set_dictionary associates the CBF handle dictionary_in with handle as its dictionary. cbf_require_dictionary sets *dictionary to the handle of a CBF which has been associated with the CBF handle by cbf_set_dictionary or creates a new empty CBF and associates it with handle, returning the new handle in *dictionary. ARGUMENTS handle CBF handle. dictionary Pointer to CBF handle of dictionary. dictionary_in CBF handle of dcitionary. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_get_dictionary(self) def reset_saveframe(self, *args): """ Returns : *args : C prototype: int cbf_reset_saveframe (cbf_handle handle); CBFLib documentation: DESCRIPTION cbf_reset_datablock deletes all categories from the current data block. cbf_reset_saveframe deletes all categories from the current save frame. ARGUMENTS handle CBF handle. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_reset_saveframe(self, *args) def set_reciprocal_cell(self, *args): """ Returns : *args : double cell[6] C prototype: int cbf_set_reciprocal_cell (cbf_handle handle, double cell[6], double cell_esd[6] ); CBFLib documentation: DESCRIPTION cbf_set_reciprocal_cell sets the reciprocal cell parameters to the double values given in cell[0:2] for the reciprocal cell edge lengths a*, b* and c* in AAngstroms-1, the double values given in cell[3:5] for the reciprocal cell angles a*, b* and g* in degrees, the double values given in cell_esd[0:2] for the estimated strandard deviations of the reciprocal cell edge lengths a*, b* and c* in AAngstroms, and the double values given in cell_esd[3:5] for the estimated standard deviations of the reciprocal cell angles a*, b* and g* in degrees. The values are placed in the first row of the "cell " category. If no value has been given for "_cell.entry_id ", it is set to the value of the "diffrn.id " entry of the current data block. cell or cell_esd may be NULL. If cell is NULL, the reciprocal cell parameters are not set. If cell_esd is NULL, the reciprocal cell parameter esds are not set. If the "cell " category is not present, it is created. If any of the necessary columns are not present, they are created. ARGUMENTS handle CBF handle. cell Pointer to the array of 6 doubles for the reciprocal cell parameters. cell_esd Pointer to the array of 6 doubles for the reciprocal cell parameter esds. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_set_reciprocal_cell(self, *args) def set_reciprocal_cell_esd(self, *args): """ Returns : *args : double cell_esd[6] C prototype: int cbf_set_reciprocal_cell (cbf_handle handle, double cell[6], double cell_esd[6] ); CBFLib documentation: DESCRIPTION cbf_set_reciprocal_cell sets the reciprocal cell parameters to the double values given in cell[0:2] for the reciprocal cell edge lengths a*, b* and c* in AAngstroms-1, the double values given in cell[3:5] for the reciprocal cell angles a*, b* and g* in degrees, the double values given in cell_esd[0:2] for the estimated strandard deviations of the reciprocal cell edge lengths a*, b* and c* in AAngstroms, and the double values given in cell_esd[3:5] for the estimated standard deviations of the reciprocal cell angles a*, b* and g* in degrees. The values are placed in the first row of the "cell " category. If no value has been given for "_cell.entry_id ", it is set to the value of the "diffrn.id " entry of the current data block. cell or cell_esd may be NULL. If cell is NULL, the reciprocal cell parameters are not set. If cell_esd is NULL, the reciprocal cell parameter esds are not set. If the "cell " category is not present, it is created. If any of the necessary columns are not present, they are created. ARGUMENTS handle CBF handle. cell Pointer to the array of 6 doubles for the reciprocal cell parameters. cell_esd Pointer to the array of 6 doubles for the reciprocal cell parameter esds. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_set_reciprocal_cell_esd(self, *args) def set_real_3d_image_fs(self, *args): """ Returns : *args : int element_number,int compression,(binary) String data,int elsize, int dimfast,int dimmid,int dimslow C prototype: int cbf_set_real_3d_image_fs(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array,size_t elsize, size_t ndimfast, size_t ndimmid, size_t ndimslow); CBFLib documentation: DESCRIPTION cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-zero and unsigned otherwise. cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow IEEE double or float elements of elsize bytes each, starting at array. cbf_set_3d_image, cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_set_real_3d_image, cbf_set_real_3d_image_fs and cbf_set_real_3d_image_sf writes the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow IEEE double or float elements of elsize bytes each, starting at array. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the array is 2-dimensional and the 3D calls are used, ndimslow and ndimmid should be used for the array dimensions and ndimfast should be set to 1. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple "byte_offset " compression. CBF_NONE No compression. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned)for cbf_set_image, or IEEE doubles or floats for cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame " category. compression Compression type. array Pointer to the image array. elsize Size in bytes of each image array element. elsigned Set to non-0 if the image array elements are signed. ndimslow Slowest array dimension. ndimmid Second slowest array dimension. ndimfast Fastest array dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_real_3d_image_fs(self, *args) def set_doublevalue(self, *args): """ Returns : *args : String format,Float number C prototype: int cbf_set_doublevalue (cbf_handle handle, const char *format, double number); CBFLib documentation: DESCRIPTION cbf_set_doublevalue sets the item at the current column and row to the floating-point value number written as an ASCII string with the format specified by format as appropriate for the printf function. ARGUMENTS handle CBF handle. format Format for the number. number Floating-point value. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_set_doublevalue(self, *args) def find_category(self, *args): """ Returns : string *args : C prototype: int cbf_find_category (cbf_handle handle, const char *categoryname); CBFLib documentation: DESCRIPTION cbf_find_category makes the category in the current data block with name categoryname the current category. The comparison is case-insensitive. If the category does not exist, the function returns CBF_NOTFOUND. The current column and row become undefined. ARGUMENTS handle CBF handle. categoryname The name of the category to find. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_find_category(self, *args) def get_integerarrayparameters_wdims_fs(self): """ Returns : int compression,int binary_id,int elsize,int elsigned,int elunsigned, int elements,int minelement,int maxelement,char **bo,int *bolen, int dimfast,int dimmid,int dimslow,int padding *args : C prototype: int cbf_get_integerarrayparameters_wdims_fs (cbf_handle handle, unsigned int *compression, int *binary_id, size_t *elsize, int *elsigned, int *elunsigned, size_t *elements, int *minelement, int *maxelement, const char **byteorder, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding); CBFLib documentation: DESCRIPTION cbf_get_integerarrayparameters sets *compression, *binary_id, *elsize, *elsigned, *elunsigned, *elements, *minelement and *maxelement to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_integerarray, if a copy of the array is to be made into another CIF or CBF. cbf_get_realarrayparameters sets *compression, *binary_id, *elsize, *elements to values read from the binary value of the item at the current column and row. This provides all the arguments needed for a subsequent call to cbf_set_realarray, if a copy of the arry is to be made into another CIF or CBF. The variants cbf_get_integerarrayparameters_wdims, cbf_get_integerarrayparameters_wdims_fs, cbf_get_integerarrayparameters_wdims_sf, cbf_get_realarrayparameters_wdims, cbf_get_realarrayparameters_wdims_fs, cbf_get_realarrayparameters_wdims_sf set **byteorder, *dimfast, *dimmid, *dimslow, and *padding as well, providing the additional parameters needed for a subsequent call to cbf_set_integerarray_wdims or cbf_set_realarray_wdims. The value returned in *byteorder is a pointer either to the string "little_endian " or to the string "big_endian ". This should be the byte order of the data, not necessarily of the host machine. No attempt should be made to modify this string. At this time only "little_endian " will be returned. The values returned in *dimfast, *dimmid and *dimslow are the sizes of the fastest changing, second fastest changing and third fastest changing dimensions of the array, if specified, or zero, if not specified. The value returned in *padding is the size of the post-data padding, if any and if specified in the data header. The value is given as a count of octets. If the value is not binary, the function returns CBF_ASCII. ARGUMENTS handle CBF handle. compression Compression method used. elsize Size in bytes of each array element. binary_id Pointer to the destination integer binary identifier. elsigned Pointer to an integer. Set to 1 if the elements can be read as signed integers. elunsigned Pointer to an integer. Set to 1 if the elements can be read as unsigned integers. elements Pointer to the destination number of elements. minelement Pointer to the destination smallest element. maxelement Pointer to the destination largest element. byteorder Pointer to the destination byte order. dimfast Pointer to the destination fastest dimension. dimmid Pointer to the destination second fastest dimension. dimslow Pointer to the destination third fastest dimension. padding Pointer to the destination padding size. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_get_integerarrayparameters_wdims_fs(self) def set_realarray_wdims_fs(self, *args): """ Returns : *args : int compression,int binary_id,(binary) String data,int elsize, int elements,String byteorder,int dimfast,int dimmid,int dimslow, int padding C prototype: int cbf_set_realarray_wdims_fs (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, size_t elements, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); CBFLib documentation: DESCRIPTION cbf_set_integerarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. The elements are signed if elsigned is non-0 and unsigned otherwise. binary_id is the binary section identifier. cbf_set_realarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. binary_id is the binary section identifier. The cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, cbf_set_integerarray_wdims_sf, cbf_set_realarray_wdims, cbf_set_realarray_wdims_fs and cbf_set_realarray_wdims_sf variants allow the data header values of byteorder, dimfast, dimmid, dimslow and padding to be set to the data byte order, the fastest, second fastest and third fastest array dimensions and the size in byte of the post data padding to be used. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple "byte_offset " compression. CBF_NONE No compression. NOTE: This scheme is by far the slowest of the four and uses much more disk space. It is intended for routine use with small arrays only. With large arrays (like images) it should be used only for debugging. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned), for cbf_set_integerarray, or IEEE doubles or floats for cbf_set_realarray. If elsize is not equal to sizeof (char), sizeof (short) or sizeof (int), the function returns CBF_ARGUMENT. ARGUMENTS handle CBF handle. compression Compression method to use. binary_id Integer binary identifier. array Pointer to the source array. elsize Size in bytes of each source array element. elsigned Set to non-0 if the source array elements are signed. elements: The number of elements in the array. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_set_realarray_wdims_fs(self, *args) def find_category_root(self, *args): """ Returns : String categoryroot *args : String categoryname C prototype: int cbf_find_category_root (cbf_handle handle, const char* categoryname, const char** categoryroot); CBFLib documentation: DESCRIPTION cbf_find_category_root sets *categoryroot to the root category of which categoryname is an alias. cbf_set_category_root sets categoryname_in as an alias of categoryroot in the dictionary associated with handle, creating the dictionary if necessary. cbf_require_category_root sets *categoryroot to the root category of which categoryname is an alias, if there is one, or to the value of categoryname, if categoryname is not an alias. A returned categoryroot string must not be modified in any way. ARGUMENTS handle CBF handle. categoryname category name which may be an alias. categoryroot pointer to a returned category root name. categoryroot_in input category root name. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_find_category_root(self, *args) def set_integerarray_wdims_fs(self, *args): """ Returns : *args : int compression,int binary_id,(binary) String data,int elsize, int elements,String byteorder,int dimfast,int dimmid,int dimslow, int padding C prototype: int cbf_set_integerarray_wdims_fs (cbf_handle handle, unsigned int compression, int binary_id, void *array, size_t elsize, int elsigned, size_t elements, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); CBFLib documentation: DESCRIPTION cbf_set_integerarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. The elements are signed if elsigned is non-0 and unsigned otherwise. binary_id is the binary section identifier. cbf_set_realarray sets the binary value of the item at the current column and row to an integer array. The array consists of elements elements of elsize bytes each, starting at array. binary_id is the binary section identifier. The cbf_set_integerarray_wdims, cbf_set_integerarray_wdims_fs, cbf_set_integerarray_wdims_sf, cbf_set_realarray_wdims, cbf_set_realarray_wdims_fs and cbf_set_realarray_wdims_sf variants allow the data header values of byteorder, dimfast, dimmid, dimslow and padding to be set to the data byte order, the fastest, second fastest and third fastest array dimensions and the size in byte of the post data padding to be used. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple "byte_offset " compression. CBF_NONE No compression. NOTE: This scheme is by far the slowest of the four and uses much more disk space. It is intended for routine use with small arrays only. With large arrays (like images) it should be used only for debugging. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned), for cbf_set_integerarray, or IEEE doubles or floats for cbf_set_realarray. If elsize is not equal to sizeof (char), sizeof (short) or sizeof (int), the function returns CBF_ARGUMENT. ARGUMENTS handle CBF handle. compression Compression method to use. binary_id Integer binary identifier. array Pointer to the source array. elsize Size in bytes of each source array element. elsigned Set to non-0 if the source array elements are signed. elements: The number of elements in the array. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_set_integerarray_wdims_fs(self, *args) def set_image_sf(self, *args): """ Returns : *args : int element_number,int compression,(binary) String data,int elsize, int elsign,int dimslow,int dimfast C prototype: int cbf_set_image_sf(cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast); CBFLib documentation: DESCRIPTION cbf_set_image, cbf_set_image_fs and cbf_set_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-zero and unsigned otherwise. cbf_set_real_image, cbf_set_real_image_fs and cbf_set_real_image_sf write the image array for element number element_number. The array consists of ndimfast *ndimslow IEEE double or float elements of elsize bytes each, starting at array. cbf_set_3d_image, cbf_set_3d_image_fs and cbf_set_3d_image_sf write the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow elements of elsize bytes each, starting at array. The elements are signed if elsign is non-0 and unsigned otherwise. cbf_set_real_3d_image, cbf_set_real_3d_image_fs and cbf_set_real_3d_image_sf writes the 3D image array for element number element_number. The array consists of ndimfast *ndimmid *ndimslow IEEE double or float elements of elsize bytes each, starting at array. The _fs calls give the dimensions in a fast-to-slow order. The calls with no suffix and the calls _sf calls give the dimensions in slow-to-fast order If the array is 1-dimensional, ndimslow should be the array size and ndimfast and, for the 3D calls, ndimmid, should be set to 1. If the array is 2-dimensional and the 3D calls are used, ndimslow and ndimmid should be used for the array dimensions and ndimfast should be set to 1. The array will be compressed using the compression scheme specifed by compression. Currently, the available schemes are: CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple "byte_offset " compression. CBF_NONE No compression. The values compressed are limited to 64 bits. If any element in the array is larger than 64 bits, the value compressed is the nearest 64-bit value. Currently, the source array must consist of chars, shorts or ints (signed or unsigned)for cbf_set_image, or IEEE doubles or floats for cbf_set_real_image. If elsize is not equal to sizeof (short), sizeof (int), sizeof(double) or sizeof(float), the function returns CBF_ARGUMENT. The parameter reserved is presently unused and should be set to 0. ARGUMENTS handle CBF handle. reserved Unused. Any value other than 0 is invalid. element_number The number of the detector element counting from 0 by order of appearance in the "diffrn_data_frame " category. compression Compression type. array Pointer to the image array. elsize Size in bytes of each image array element. elsigned Set to non-0 if the image array elements are signed. ndimslow Slowest array dimension. ndimmid Second slowest array dimension. ndimfast Fastest array dimension. RETURN VALUE Returns an error code on failure or 0 for success. ---------------------------------------------------------------------- """ return _pycbf.cbf_handle_struct_set_image_sf(self, *args) def set_unit_cell(self, *args): """ Returns : *args : double cell[6] C prototype: int cbf_set_unit_cell (cbf_handle handle, double cell[6], double cell_esd[6] ); CBFLib documentation: DESCRIPTION cbf_set_unit_cell sets the cell parameters to the double values given in cell[0:2] for the cell edge lengths a, b and c in AAngstroms, the double values given in cell[3:5] for the cell angles a, b and g in degrees, the double values given in cell_esd[0:2] for the estimated strandard deviations of the cell edge lengths a, b and c in AAngstroms, and the double values given in cell_esd[3:5] for the estimated standard deviations of the the cell angles a, b and g in degrees. The values are placed in the first row of the "cell " category. If no value has been given for "_cell.entry_id ", it is set to the value of the "diffrn.id " entry of the current data block. cell or cell_esd may be NULL. If cell is NULL, the cell parameters are not set. If cell_esd is NULL, the cell parameter esds are not set. If the "cell " category is not present, it is created. If any of the necessary columns are not present, they are created. ARGUMENTS handle CBF handle. cell Pointer to the array of 6 doubles for the cell parameters. cell_esd Pointer to the array of 6 doubles for the cell parameter esds. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_set_unit_cell(self, *args) def set_unit_cell_esd(self, *args): """ Returns : *args : double cell_esd[6] C prototype: int cbf_set_unit_cell (cbf_handle handle, double cell[6], double cell_esd[6] ); CBFLib documentation: DESCRIPTION cbf_set_unit_cell sets the cell parameters to the double values given in cell[0:2] for the cell edge lengths a, b and c in AAngstroms, the double values given in cell[3:5] for the cell angles a, b and g in degrees, the double values given in cell_esd[0:2] for the estimated strandard deviations of the cell edge lengths a, b and c in AAngstroms, and the double values given in cell_esd[3:5] for the estimated standard deviations of the the cell angles a, b and g in degrees. The values are placed in the first row of the "cell " category. If no value has been given for "_cell.entry_id ", it is set to the value of the "diffrn.id " entry of the current data block. cell or cell_esd may be NULL. If cell is NULL, the cell parameters are not set. If cell_esd is NULL, the cell parameter esds are not set. If the "cell " category is not present, it is created. If any of the necessary columns are not present, they are created. ARGUMENTS handle CBF handle. cell Pointer to the array of 6 doubles for the cell parameters. cell_esd Pointer to the array of 6 doubles for the cell parameter esds. RETURN VALUE Returns an error code on failure or 0 for success. SEE ALSO """ return _pycbf.cbf_handle_struct_set_unit_cell_esd(self, *args) cbf_handle_struct_swigregister = _pycbf.cbf_handle_struct_swigregister cbf_handle_struct_swigregister(cbf_handle_struct) ./CBFlib-0.9.2.2/pycbf/pycbf_0.7.7.zip0000644000076500007650000021305111603702120015257 0ustar yayayayaPK…‚Å6;gаŒÅ CBFlib.txtì}[wÛÆ®ð{~WÎÉ[Yµ.v’ö<Å–µŽím;Íî“-Q6w$R‡¤ì¨ëûñ.3ƒá’/;énºšˆCƒÁ æB§þÏá»ã¹ýâEÈ pç#gFý“¿¸9g£uœ¸óyx¹Ë[â¼ó7Z;ÇþÜ‹{?¹u—‡£‘s¹Z.Ã(yQÍÕï^ûaàìµ_ýu­è9ƒeäÏîÞÞëµÐôçz]wî®æÎ¯mg8Ÿûqø2qÉÔ¹\“Û(L"`øÂún‚¬Ÿ¸×aä&a´nÆL+á>xѵ%ÈÐ;/ âÄóƒjÂçüè\†A\ ¾v×îÿ^kèÝå|ïÆ€Ðž„‹<÷¯wœÃp¹Žü›ÛE~Ð"ÁW°8~èæâ³OÎÇÁÎÅðhtyu1z÷éjè\}¢^žŒÞ9çƒÃßï‡Î§Ó£á½¸^|¼tÎŽéáýùIÛaJƒxs:¸ý><ù£–.ªžf}·"ô Öú¨RHw1¨ ç¬b?¸q’[?vâp–Ü»‘×r–sÏ='òÜ)¼òêÙuNÏ®F‡C‡!ÉàýZ«$ÎÔ's×_€e‚®Egôé0rÎù?Y;a@EŸ ÆpFõå|ÂíeAæAŽ4it¼ƒÔ¨®ì}:û~¬,WÊŽÜÄsÞ­#/žDþÙbj{íü ¨ítÞ¾}ƒžã×!ö>vǽ“\f~'ÊÛB—P×´9˜}¢7u®Ék" €çäŽÕÅqÁSÜÖÕv±ÚÕ©öïïTµºÇN¬O|ßaÇ­jÊõ£Ã]/˜„jªò&ØÀ¸Å¨ !µz—0œ[Ð+Í Ö„HóÉm¿÷æó6#`@Î]bKgQ¸pKwòÅé´÷©Iªé6 ¿ÄNàyð@„ŽN:»q²} Ü…MÂUâL CnÂÈ÷D"=ôËÞ2ß"‘ üéÕ’XžÜºÁ ]@c°:¤tgFŸnËA¾G1-VóÄßMnÑžß(:5¬…j •,Â;F*SoéS«§lC5ÿro<Ãs /¼«êE0º¨r±šÜê:A1P¡Š|h@Ââõƒ$¤÷7^àEîÕˆ]pE,ÞG~BÎ"„âéjâi߬à½>pÇ^ ½†®eZÖíXƒ°¼ÉRH/¹÷W낼ƒ{[MÍÖkøû£1S¢iy'| áÒîÜ»óæ@šiø*(»FõS^B»é©ï±GºwÚ¶©¶Ý)©Ø³kš­"ƒŽ8B%»óc2)¤²[ø À$+xç}]ºÖƒš™¸ýÞrŽŒ¹ ëÂ?Ká ¯áÆˆI~tÚUý$$-Çê&þl ínC£S­íY•©¯Ë A£&X –1s0MåÁZÃH{˜+ÀÃ"DA¤8“ÆÑPr6¡ø¶[Xâû3_µ-Nµ `ÂÌŒeæLÝÄ…îåP,FíwîëZ ‚†x ”þÞ]ÇÚ1Ûð¤5øEw×Þ­{ç‡ìPW¸!3pPºŠçë« }ö@Ø„¾êž¼•`íàñ#x"‘Iÿß*)%5–sÓƒ2»ñ2öþ…4rAè‘‚u’õÒ‹­ñÐC'§J…œG’>÷Yh*aøÌÚÐà%HoáZ@ÂkéÞ϶' Ts¬Ö4çQ‘ pî_ L¢VRÏÞ=x®UâQ$:lB'áÎ}` j46êSU“Ý9ôg}Ù"K„&“-rY.¡æèˆ$›DMÔÊk,N@$„kÏ]H2‡ x YsˆÜ*óR¦<+ãmAe4‚£(A­X5iQƒeß<‚­æåýBj~ãÀ:K틟¨äž=Œïzÿ¬âÞ1A•cJ `£RïÚlPq&Hôœ›²\C#PjðÒñ©ŸtÑ=ŸFî,±]æ­‹¶â ˆø³.X*´ÚL>ÐHìß9wЯSÕð’1‰ ÙÔèHI(€ˆ@â}EÍ`Ó±Yœ%#xVÔ& œ:œ][êåÍ\p¾M¿ÞY8ÏMÃÑwwáþ+Œ4¶•aáðîhEmœêjym‰¦Öƒ‘²î>$3­°ù”(œ„7þ„ãjƶõU Œ«Bòhh@ÃÇÏäMU}^‹ž ÛÇÀà˜M„ÝmªHÐ3ð§ã¹'côAÓñäÖŸO)Œ½±Ÿx œFüæ¨Ø"Chá~ñÆØP*¥"ôÝcˆgÒ%HP1¾öƤºcz!¥X³4_-‚1ÇÝÿP¿ —ú…£ä‚µ®ŒAy¨ù¦5(ë1ËZ ù5NÑ LƒR5eÖ<›£Õ“"î·ßÜëxrÛr>ÂÏZßBN>S² ùâ4è>YÐùåˆ ‡—ÇÀ·FÈ-GÍw2YAf‰Çÿ V ¦2/pè7]ÁÞÐêÁv§Yú<ü%“[ðŒÊþFULn:Á©†øj6Iý@‘¬´‡2'KL@(bÄQŽÝ„Œ8®`e¡ÚF^J ±Ô˜Ãi;g+x5Áa/'~T&€Xà-Tó»[7¿ÝQL»SðŒR½¿ž”Veu›/Á`\¾ bžÏCþ §|ù)«pÊ#g£7d³ÇýDlÎÞîÙù™À‡3.©»vÙlˆÝ|+ZÜfÔ2£_l7“‰Óo÷ÛÕP6ñØ…J¨ôO}Б˜ÆâlϘ“s~ ÂûÀ9W­p¦™(LC0§ L`пóRbV1&€_6ßÎ!eJ°SužILvMðt½«s`íZQ7!˜º"ØQÀþéBá’¼ tZÎ:\Q½?+º?pâ!\E•KÒ*†Ó#6²—7úKp¸/!\À±‚ÿHèÿÁ‹öÍŸ¿`·ZtIã)Ê«£ZDÔŠÕ}âùS åé\‡‰ÎIÅ*,àa` Ê`ù‚›øÒâ›UU;ÿSÔçÿ!¬óõnæìfáK¹Ë£*EÑ!.@ñ9wÆ0£ncé*$Ç×Ý/´0›èâl¼¡–#б{ŸÆ ,(ë*‘Ö€R„AÓY_g™¹U?þ6’G øÒƒEI¥òi¦†q«ˆâñÉàý%ЃKpŒà§1­Ù;“þ¢õßîf9""Ç´ˆ±ûvï§·û†)F†J¬ÈkøNŽè‘8s*ŒrlE5W›z’0F³˜^S¿Ù'°#ýì‘×ĬÃ|žPëq%«½ªk—* öf*{l’y×@š§cÊ+Ѐ5üšÀHB­=2“4â¡ÁcUC öß1¡‰”ZöÜæuZä] ޝˆÍ‘Y”>NGW£³Óg Põ æÇÆÁu`q‡óÝÔ\] ŽæX¥äœ©^HJ/Íþè`ªë=çïm ,!(JŠS“q1H—@nÂÀ)´«†î)Ñ'h¤5°}ç‚"AÖËl+ºð6·ð Tis}œsf–œ k‚ºˆVcð.FìIcðÌy €£™J¦ó*!õuh¦Å÷™œ,šSâLµ«^»#sQî…b°.Ï}#¯¬'“ÖÂ9l^_&°Ù m æ>AÂŒ£ Ml[¦(·3ƒ¹F î7*„˜(CA^4¡óZWhæÌÅpo„lè·šªšÄ—ôßžƒ4L w2¬@:§Œ;yêÍÁ.+Àz: Ke;D\X\B¤¯T#E¦LG÷‹€[RX×A­‘z‡;““ÊveRZ[Û ¸®º·leGw÷²¢wºvy*ῸkN[V¡´µ•wG&¥’Šzpu3ûdE3µÝMjy`@¥‰¦¨¶TÛ¼×´ºqo \EÓX%f ú¯·g@3M›5é»Yƒžëu heÓzj„¨ìµ^Ï‘Êû*{¹ êÝCoß– -)IÄyQ˜È¢¬¦¬;º òµ¤®.{£œ&äDk¹÷Ö–þ–Âze&°Zuîï pµB÷;Y¡Ò}Ri߸|`蓊˜ÖUAö­ w©2§²Ý%`f€MíÿoSI.*A|­¾J¨7†‚‚¡"LL›ÒÅÕÍJÖL÷R¬¦+Ã’&õXUT¹P!I•f²}ç,C–§œW0×ä{9@±ãp‚ @’€hc‰«“Å€]K­f³¬hšO¤¸ß &u€2’Lxëx)ä>“l)6qï‚Ô¼à&¹-†T¡BH –!¸bÿOZv.†UáB#ØÎž%ièÁÜ<\ªb‚& ]+Ü…v-0OYÚS ÀR¹v¤³n\¿¬AªŸª¤‹BhÉ9QóÚà¬`zh^Ö<•©iù¶@Ëáõ >n ÏýÈ;w=ßáÂ+ïÚð ëÎÄ\Z Ì¦‘ÿµÂûåKè÷mºÌ„¦û¸l-1)m ›¹“bõ݇àóøðÝxpuv2þ|xzU Ô% ÃÑÎdž~<\\öpøÏÑÕøÝètpñG1XŸÀNß OÇ@kP¶Ï`ÃVS; °³s v8‚5çb¨×…S‡G?Óï£ááÙÇó‹áå¥*ºùn+í·JÞô6¢ƒÐýbŽßÊÅppÍ¿º,zkýq5,éä=}„ƒ¹Èa®¨Ÿg:£ÚVTÚ/©¹#À'£Ó2þºõÏ£K¨£Žõëò·Ñùøó‡ÑÕð¤8ÔKú½6fÍMÍtzµ ù\ ªÞ0Q¿bÝÃõpAR'†²xN!bª¶Ãwy¬4s¸ÀÚ caZPȶõÐ ,÷µKE&‚YŒÑ…=>ç}:ÜÙºç¼+Þ.¬{¢{.èȱ›XÅûp„ŸwµàT‚{ÚD˜Ý¡Eú|ë €ˆàa‡vqê'ÚÇrz9Ú=D:rì Ïfø¼À¡3BxŠ·âúñ‚fêîDŸ1ÌV „Ò×(¼2ç‚ùÐô£Ö]µq) ¼bmØa@ÚÂ%-ÃíýÈö< a]`:x†Øàb/‡æ¶‡ÅŠ4ÿ 2P-EÒl¿ÄãdhÀšlvx>å'êðhü möwù¨wÂ"Y+)#8Ú™ytþ™¶ø¸ÕÚìÊ`fDe—°øÒ y‡{9ùêïÌ»³/›háÖ0/€AÏñ¢Ý“Bà>+ˆ_”_uaÔ"{övü‘e§öÿ¢ŸÐ›®øX•½Ï·Á_GOY¸],+{gµ´t»ÙFÉ>#z9˜/Â8Á]cÊ-)²VA´âáqN—wÿ f¡ä¨$±÷ʵ6(í8Öqx9iÚ†CÛwÀ†©KN0ªjÓF5…i›é¾çAѺ’™.1OжÀìö¨ðú_à wx¸&‚Ï¢iTï ^[ Ð:}©6Ì£n©Ä°¹3wN»¿ÕI òP'ñ^l "š9z8¥©ö"ç7~‰«c`ÚÝA-x”ÖœäD@Ål ˆÅp$žŽ¶iÓlÇŠ¡[ÐÜ’[]Å=è<Ÿ3ã}¡!ÔŠÆ*ý…UÆÊ‘“Þk|ª÷uâ-“ì.((¦ùBe©—(šÞlêÌgCRN„6‚ªý‰Ït$PDž'•݆…6ãËq¹„ˆ"DŒ†¥Nv"8pN|4`}È]f—a@Aú@©@åÆ>Õ‹‘‡îÚMº†wRòœÀqyׯé=Õu@¥Ò”TæMÇñCÊÈqª«K{ø êBK˜¥©‘*¹ ”%û¼|Ô~á\O4è†TävKVt€+0ñŠfFÎ3²4üÒ)š˜6ºb%1 0Þ¢%&]nJŠèsv…ª²ª#4LªtY΀Ì;!³ •eQ5r1ôˆ^;^dÇx^v»AÇ‹-•·|–@gÀ ÆÇgWZ"fB@àt Q€''g‡ðûcþBPmÈ‹÷Ÿ>O‘ðˆ©˜v¯&Ðî0, ¬ _Aˆ¦b¥ƒ &¸ F(ŒÂ¸:<ûtÊ-վ؛Zׇ\ãà3 ¹c‘HaÂý'`ÔS°ÆÁ®i¡=<=:;>\ 4qÞž¨Ctètyr˺æË’4$¯ÍK¿ŒN†‡'gÖ:¾Oæ¡>ž†Â©¼Âá,(‚Á¹¢‚¡`­ær8üMÃÄž÷¥æjxr¢aHõÁ|¾]i®IV9®GG £Ã’°ˆhmÞYjû¹UÃû ¹ËX¨À­OÇУGöqµ±RV'y!Ü¡ÚñP± û™œP;û}xq|rö™©é®ÆšZ€3sHœ¦&ä#@áR*Mæ–zsK·Âp`a1àsÝ XwÛÂÆ§S:0ԭµJ€Eõ™{}ƒÂ+¯ G’÷~ÚûEHÎ-£¶S}ÁÐ'Û¶Þ©OØ•»óõa·ȕÊ-Cëæk9ND]† T|ÓQü…oµa_cŒjföÜ¢ÏÂ3>‹}’c‘`³|‚ðHGíø7ìÅæ˜>çªÖ˜»8mC&HKž†c"kÿZ-–1ŸÿÊc¶‰}»Qd¼ .Ò'8/V) •lV³ŽÖ!l ›×.mÚц㸘wÃ(‰$6þ—… SašÌªd>ãÈca§-ãßu]ã|,‚ábWñ=Ó–ÎÒ꺨¯fXNS4§õÒ‰®_î°Ýu®„H£U±37m+Д$óNî;›Ñ ¨a‡uÉOØFÁr˜™©3¡*¢JÁµ¨Ñ|Lo·‘Ð-.2ÉBï–°ŸsÓÝ tØ}Sù» Å´>Œg§eF…’óæþý ŠâquY6#QwëÔŠÎ}ÜÅÜ©sk>ÞÒ„Û µ*ãaÔ]%! Ñè4ækå*ÏИJ¥õêÎ0%±`Þ}h4«–ó—úÀ³ƒªâŒO ddâ6‰bñHnŒVÀ¥]:tàCçúþ»•Y«C|êâëLUª3ðä9,À@‘™×¥ ±s±CÂf·0ü6\j ‹ÅñMT¼i‰QB`,gð@‡÷fµÒ â©;ϸ¾ò@xXŸT;&ß">zÊ/3m ”J墭DMçÅ HˆW zÓ´Ñ«ËYËèùPÙ>Ræ¶ï¼¼ÿñßnü£™Ýf5ÓÜY·;Û]`- »UIßpcRH™vˆ?У9O{bÿÚÇ`Bùk>ÈééQÏÙê$[Ö¸uËΠ'HëF9i{ì—à£u»F3mbŸ9Ìá³ÌàŽF)–9/ŽŸé­,ùÐ5MêÒ9ª¹‡‡·Eh¡\'3|½6‘†™rH!ÓHEn±Ã¹!Mˉz_S×C°’ûí}ÈÑssþÑΡ>Ö•Ú#‰, ‘^_œ]]ýq>¤§ÿR¹lç%À¶o_¾àüv>w÷ÊJÑýÀÿîüò‚î^^ŒÎñä.>o˜˜£Ø "n;Qæ H¡ø ~.  R–’¡+@#¥Aš ¼ˆF§½Ç7±z"øfOîCÔW£Åít7å è(¶šñÔÉðÔÝ뿘æj /Ot(ÞˆWê&œ$K÷@òÅÑ îàž[@â¼üëiHWI®^ü¥q3R(ÅþÝÜ!—‚ç5¼Þ—®¿¤ñ(þ.jT« è+%4â‰Ë÷É;ºè‘ï^µ€àܺ²…êfK\Ü‚Ì3n³°¡îªT^þ<Ò.ÊiEµ‹ù‹]ºRŽoøœ3ä­¿Œ¥cô–ðA­WúJ ¿šS×ó µÄ™Ÿ«:+#:¦Ö¸¬Ë8Ì­D/ßFW?cȪ²ô±‰¢B^x7óuc±D’™*9[KÖw “xhÂ#(Å+Ù]3ýÂI$E¶:É.¹qØÊUÉP¯iþø˜Ô‚z»ÆìÜO4wÿ\¿´0v°=p“ºÏlg…ö-ÍÞlæO|¼ªºÍñ;φAËÐÁÏ×vÝÀ‰:¿0mašÖäéÙçÌaàºgÝÒ¯þ"b6¨ÌIÇTdRð¬87üŠàqWù|mrÑr¥£ƒMWk]^Ò9Ô3”‡3¥Iªë¹ãwÒ_§gÆ*T¯{H:畺as§m­ŸóÝÞP[qF|"Íá_3ÛÁDª›Ë*$¹£‡Nžó3çå¿?c•¨•Í»õ×êöAJc©–Þ So¥Bf|&ÞàŸLhMÅfKHSCñ»HGyÞæ^÷‰»ôÅ*O×YlØfóÈŽ“XêIݸF€˜ŠØø?7ÖµóK®ÂÍâ@S©¢Ó°Ò‚ 1ÛdúY9¯PLI°¦{‘Ù›…ú‹ùX1æ`1“vF[ò¢Ù(á¥có¢ƒÄ‚Èl$J„ØR«êÖPßéÊ`Æ£§úˆéHP©‡ø¢{ŸõŽÂiK_§¬“êx›ÚÜ'ª*;ÚVwÎa‡cæŽ$Ó«éK&ù²”“6üعުL¯úerËjQ“×̃Ý=ømRÊ’Q¶ÓÉ•R’vZŒé˜ü±• ír«bR•Í-úÃwøÆ Ä“=ä¹ózäé¼ ÚÐAFâÐòf ì¸[VÀ|¯'PÈà#ñŒøWï¨ë€½¢­Ø*W¡±Qv@@_/®ƒä_î%Qw¢ËF!ùHÖ×Z Vëðj8]j;þ›†—øŒßs¢Â]ä[“³Û)h§g ‘Ñ̆gÞB¢qs!µÃÞ«d›‡]h/sÚ×´ç£=x4áÞM ÅL/™a¡¨›ÌKê(æ%ßKÊáj$òi»àFqñN‡IÏݤ“rÝt {fxz8~7¸ô•xùA”V Â?Îð?>ÁN…Ýó‹ÑéÕÀ´všúÏ¿_…Øé¼SÜÙSÐü€À‡4ª‚zxu ×MV áŒæóà∠˜©–® ˜ŒAlÁȲ¤½Ó±ò€x#/iŒa0­èt{ý#(æ`ös¾~3Dœ“Mnq8ÚIñ}ø›âá£EIÓŠ.Óî÷ºmžóÝTÑ>¼ÀoÉaЬtÅãáPÝ|ažWžK÷7Î_Zát³XZ»zrüìì&/Ý`¼ãI(‡ù‹kŽáòæ^hhGNŸ–û Úº“›\–:ãj?œv#Ú½ˆ2jˆulëIÔü¾¹'yÚ)Šd†Ÿf†Òð†È ç-)z…³ÚÍJá®óCê¢D3ÉsQK(uµbñ#Ï/kée¬Ü¾+Nq(åúX~’ú”– ·ó ÈT…åHˆßIm©f¨mL%• /̈Ò[C˜©¦Ð¤XBw›Vi]/ùb*³wQß:Ì`S¥tÔ]ÁqY(ƒ%ðµÉü“÷¡éRÛGð§ T3]ËH"èr$áì©W™¶»oµü†Õº;U‹nQåò콩\š¿)U^t7¾ô´ÛÞâ6Ѻ۰jî¿*»ñêq?‘»e_nèa™Ä&~°s®6Gq#‡ ØÍ}.“ßÔóvÞùÖ{Þ£ÕrNóv*"ü‚HR Âß’„ÉšðVëªïë}už¹¼ëE*Ÿ¼(`Ž„7„$­¬màœ…iGOæJ‘[þÛ 7އþö¼ß¨çÍ÷ȦžÕÆ­85`ƒ€Sƒf<‹).ñÌ9¬ÄÀWú%žTTØITgub‘Çà÷õ[vŠÝ…Á.7|òM™ýÃû3»…ÂKÖ¿+C¶%õsf 5 7¶k&¾¥u#1ðí¬ÛŽ%Lq}$ÑÔ¤Á{`ÌÖZBiVvÁÂKöGë߬¯‚yˆß5ÄrþÄùÙ9ò‚_´¹çsH† ñ·ÚÐñøø·ë)w=yIlêr³>~ °&Ñf¼ B½…æ–šE)ØJ¿¢`$fÐl1Šö@iÛx!k¬Šr¹©*€¿¼¡–ŒÛlÁGV¾+sM·wc´Íö¿+$¼_HÛ">&a¡²§ .³K ñ6X/úWí¬g®WîÔW›äEþƒAß—ÊÛíÝFë³pˆZÁFÚëÈÊ'öK Bèm` j µ!–‰Ð²$–JÅh@f„Áâ˜OãE„ d(îÅ^…“r¸ZìtRuE¨XnïR\ªÝL3ïÞãO(K=ÄD+}IKÄfø"s©ƒÙ”Iµ3ºâŸ™ß« ³c¡0’#m ˆXú·ËØ,¬ý‹ú »YÛø Æ|<aÑãŸè2à‰,¢Äa\Øv„2¦ïüرL ÅÊøG³¬­ãÁºáŽFÆ´[¨û~Ç\îáÆôÜ‚±\¾ d¨b©÷YÌ>eòÊݲ@Ÿ:VØ4ÈÜ&á\<•l·~çÖºá7$7´å4݆Ë|Å ‡y†Jèµ·]6Ì1«Î1€1Ê °$q®¶ ¥ÐÛy–›PMïQ@+ôÇØOAÇGR'„ÀñÅÞ.ZR€×ÇÜy;ÅáFúªzŸÒ|Ý.½$ oj Sk™ßÚJ]É'UùõÆQÝÚ¥}ëïñ7u•4vSG‘ÅßlŽœÅ–~>·ŽvÒ`He¢lªË¯ ­ÚP6û­Ìž·Q¡ÂîñÕ¡–3Sø@)Ô ŸĆ·d*«R¨òÅ–vMIm´Uíù4¯ØÜŸ[ˬÏHo½Z—ÆÞF=4nªK9PSû¡Ã{îØM“ÒÏן–$ö>n'o4èmÜùˆ¿‘7A„íÝ bçýIÙ®²4^Öy”n¥ªËL2j¨k0¿Ü,ºÚ>±ó;dzÛýw‰è[ûËrNó®ñªàÍ·«ÂÛç 7ór}]µ[¶åšx y;=%T­¥¥ëÖW¹òoWC³¹é‡é_¡Gùkh ÍýVùkÆÜ|¡Wð Ê¡ŠrYœ{.I$gÈxì[Îb °äª:ãoiòM'„íïPýu-÷pÁC&ëiüMM!­v4ÈmŒ֖Ͼm«Àí‰ðZ˜%kª©Õï1évmÊ¥þR(Úž*%©øpq‡h¹õ:fô­w©ÕKε¯¦oäv­«j0aLsÑÁ0X´T¢”óhˆ<;?àÉáv¤yΚQƒ¥›ê Û˜«Àv«å•ØÅ‚Ò.ÓÍ\-–Èdÿp$”vª·DË‹T±÷|]KÈã-*‚§¼ iêXȼtÚH¹—oлsÆeˆ)K‘´”‰><¾géY\n=Aä-g jVÓkvá¦÷ûièBMVï¶y‹_“=›Á…ßz>°Q«Ì¯–>YŒf×½Ý1·™¢h¼ŒfVNO2«Z¨“øb;…d9ÿÇëd¥ó}cÔòI²õö=`‰°kWø u3+ú)q†\Œ×0ÔB…¥KMÿfÅ üXÃwÆk>·âî·_JämWÓ¨¢µº¨Xgå5}uªI\­1Ê5Y¢Û-ù;‰`Íßú¼ýú‰5Zèo¿"êVÑ«(ºÌ…šœ iNaøÐ(¤Eþ«ÆµEC{35| çüÔ.ØÐßê€ âmË,ÑSx%­I¾Û‚³ åêù— q7Î>šn>Ãt‹moö „8b7¾?ÉÚ]w+@Iž¼ÉÝr+¢}ÕÛ„µžg*Ì|-v;uß6(ÞhÛ±l¾NoåvP¬Om2ÅAu#Ãéí™ÎÏά |™/½¿Ì'½.¿Q¦\»Ÿø»Y۲Ķu¨ÈM¯÷h~·Gq–¾A~¾üžÂà+ËÖÈbך#lwµ†~ý\†ýxó‹Ç‹¯í}%Ç 3ß¡ P-Þ>·¨zå†ÌÏ™â/ÜÈO–¶³yB} ‹ß|RµÙüâ™l»hÖ`Â/6øDcy‰µRT®˜ùmUµjËEWk¥xõS­6]ó°n±Aºö×çÒFQi–y£tù›`êR‚Ç0ÌÏ(áQ·I«9"üLV™›}–$.žÏËÇÕžyClÙÖÊ£ý Äà©Û6ÆEôÅ áŒßÂëâZ¶µÄ}4 ÒÄĊ伫0'$#UbN¤€±çF“[>ún©b)Kn'µ)Š!þ¤ ÒæF9æ[P¨¯È'ˆŠ7`rh«¾¥Íßù0$c,vC_ ’I);ž ¹5}ªA#þÛ  ×ê}ÖÄ*xÈáÞ,~í½ék*¾û›'½\ñ—8ä¾ {ˆÛ„m"QAO}H*åT«wØ“tâò‰õ¿·o Ä^É“RÙ±ÖJËO6¯jòZi¯¼{mÞ‘EÉ ÖJú²ÒSnþ,nê–ji𪥯WKZ¨–ò¶r{"¼´+ÝFc vÆjO÷<úZè[¨€omÇ-…bVéSn',hǶŠJÈõZªÓ ô“àŠ”³.ýÀÜéšj•²d6_­Ž è›PÆÇõ­eêÛß|²Õ¬lí[j#`6QE«×C*TB,2_¨‚Úa<§~„äTjÂüU¯Â«ö;¢}O³ÎoÇØ%˜Å¯WCZ®Šyª\[qœVMqã&«¨¹3K~¬Ií=òêFW¼™vÀïSâ§p5”%ñﶃGÚ˼ì3Ú€ÕŽí7fÐë-@CÖ€†4ú¯ ”Êšçü†˜ÔÇâª÷çO ‰Il¹jøH«•ÅT½ð˜µóâù¬çq‡‰bGýmX]û¶SÈ ¬‡àØÁËáG¥×ê©*¢v+®È{i´æöx‹{ÍÃ,®'kªøùL#ó4UôGtžÞ,¬¶ÚFI˜Íïé®·2¦ ÓVž’x*¿Rf/»5.Ê-à!KhÍÕ+¡?§Ù«sŸO÷·HÕ=²â?Çœ6·5m›»j»éEµwifHÇXD5b‰“Qøa_ Ûdz‘¹9•¯î¸öøÛùhRóðÿ³÷¬ÍmãH~ß_Áò§$%»,{2Ý{T6qî|—óLÝfvkïùh‰²¹#‘Z‚ŠÇÙºÿ~ýП E{䙸C"Ý  ÑÝh4^¸ðTÝÊro¢¾‹I1AñGJK)ƒovªdø/ÓU æàæèn‹ü¤¸IK\÷ñC¯;¶Q3,ÂNÀ[}ô…&Y8zÄwe§Õ(‰6È!½ ݬ(TE–MÚQ68:«KÄ-l€€[PïÇáÖYA¿ȧß}—6§•rw‡Ò8'ÔP ÙÇ@®tsJŸl»aÆ€ŒÞ]¸"ÕøD2ÝâÈÈ3Á=©4Ë"û£94µFïéš]Ρ"*˜ýŽõ«nÏZHiÑdgÒ‹›×v¡ˆíÝçZëÒ†α.Þ÷O0§ Ø‘1P ­k¥wUYl)z†d8¢fñn]2va“ª²¬µº|ó§·——þÎ?ºŠ'¦ËÖ(Þ w^H@¨£˜Ž2füˆ¡Þñe"”Œ˜®¢,AéŠõ«ii––)ØÞÏžRÙ1ÐÛ’ƒâòÌ 7RŠžjr%;f’¼¼zóßóÈ݆Ÿë*žºç¦#•èšfÉ=ÓóÉO<<4ïúê¶#Bïs–HBãÒQeñØ&ä#…¡û«(WÏŽ›s_ŸZ\lðmRÔm‡ä¸ˆgq™ïnÖIždÚWÕò⢈¶1zqÀI ÷ö€\ß/ÓšY(Кu+ɯ“°•zÝXb½ÙS~Ö°§ÜÏ@YùõWM̼ÇÙ*'’4n\PÁãB×fÛºI ´”ž5—=ëôo€ÇØeøOì·pMª|:€}h9dtŸÂÌMn³ÖŸ›ìFåþZ]=jLÕZ,‚à¨ÙÌOð_‹þU{h” z˜.¾r€xR‚åø:qƲCç¢H·e^ˆç>Ôóáíð<†¢ à ÛÚ›D»$øøelÈvëõ©KáoãÒdK|ê}…8::9Šäè_HÂŽn²âÁàݤºQZŽîób©³2˜ßü}—#® d/oÖ×ÙH‰Å⸠¥n-T¤ ©Bm=*a_÷1É&V䙯ü|žõò$zÃ?ôþ.]Ü_Ä•F¿Êõ©š;êêÇ¢".ïÌ#l5u…4+Åÿbì§ð¤¤î:ç«cåz‰'𭱏2ž±µ_|¯ß¢ï¥eb?Û¯Úþ0Ó/T+>$Øs$#.š ªm²06D·Úô)ºM?%ÀüÎ7ÍÃÚ¦ê€P×Ð0ÀøSÓžÐø_áZðzMlPnssì0«˜Ÿ|ÈM¼Ä1Àí;öé¯ùÎŒ²YNCˆëº¿Q”Ê8Í”m`DuÖ‡Ôˆ·Ì¡›uœýÄ †Å¦È ]B`nsºë4KÖ‘Ù7¾BØ)ÓVˆz=d"Ñ3´±˜sµ±ßpp+³4m:¸‰Ã¨Ã—)ÃS Ã…#ŠC¹uHá¨?ÇËc½ƒ(ÐÇïœÉuÀÄDӗ቉‰ÿèN=XÃ"¼¹”Û"ÑïìÇP«Eº‰×‘.5Ümêèª]*÷©ÊLûý¥]zÑâiâ¿Cã)Ì·Ý_ü鎬0ÌÁYȽ,á·ýÛ_Û·{YYjeYþ»|u¡4&€j¬!‘0Šf´î¾HË2É|ããz3C§üÖ\bq¨×£<ŸÇšÞq¨žB¡ZãŠ.tÛõœó;ª4Ì÷@¯Š‘{2ld°°ÁžÌjÓR÷ñ6kWu±ö¨×XgÏ«QÑŒ}VþV{LõWë{=–-¶Æö‹kv°–ÜöÑ>[l7¢ ²½‰KÇà†¹l >ÆcÓ¦¶b¢Ú·ÌóØèÊ(*€+ޔ܏¬N&Ìí¶È·E—¬W} ¬•5\Cý?&?Þó&kª]5b|z _ñqfŽ_|Á@ dÇ'2ä–| éj­Sÿ¥|KP¾Ù  Ø:@Çk×éüžôsr IÉa>}0 ÂÃCÖEI6`Ê”FÚ¤™N1 ñÏ:áåÂÚCüén•&t­ªmf}uóP&y±L ! š{_gÞ×¹þâúlãå £°Ë•¥Çïû* ‚êÐgÓÔæ1Ù“®4›Fw¿Enkl3’Hž/rÒ4WÎÈ'1Ãùˆ¬FÐK¹ò‘ ÝdÜ=9©ÂÝŸR˜?à’#!ÄÅ펪eI²4ë‘0ºÞ(°×DJ¯N–yËè“®d¯2Ѥô(U€b/%çêä´ƒåíå{Ëѳ8ñ„­Ÿë@¥‰ñÂ],7ˆ{@)Ð]kád pOšé²) ÷š˜×À9w³5¸wP‡0s š ó}­cuÓz†4XÇ¢Õ.t9ï“õz¦Ùe®<Å\ô5aV.`¾Õ½¾µÍ™©ìE—giI£Õ±]ÑHR䱿µŠ6œ­Á_'×I¶Fã–ƒêö«›ôÖäjiQwùn½„N$8,)Q¡îU73Œ&Ø€Cº¶jt—+Ü·¬&´) .AP·hÊ mÙÀûº1U&¨½)ù»L7èD¯ššÂ'„=¶)—ož`¯³€Ìr#Q•³qp«2Q%og€*aØŒú²–´°®E= é@!I†ÚoˆGVdÖ3Ã^ùœ9&#S%«CDnSeÛ`JÙBÓ± „BOZ›ñ¹ )ŸˆÉ)ç»$†~>‘2šÀYmàäæp¥’¸€ôµUz³–GÓ8Äí.”’,˜Àí¸Iˆ>Uš¹Þ݆<r‚XzÚ’˜Ò©ð‹«wß¿÷æã®À[–¢õC ÜÓt:Ç T‹‚]hiîò奈R­½/ŒZVÅ^žD—Z ,w ¥1Mœ1è½@‚/gú“í—@ÈÂ@nHó˜! /xÈz‰t$‘±˜@]ëû ð‰[f¢§/™'@¹(RD«]]ø kLÎWHeÞðô-.ÐY™çìÏÂ/-¦Újêgq‘í@nýb&D ÖÂú‘Ïös¼ÙÒÀArdæã¼üv~v|ÃÒÁÁ&žËŠ1ÐûÒ)Ù›]©@cY,q›?ø''ÑÙÿ¹yôÂv-²÷RçH‡æ ³g2&)Õ¼ZšÄ1 ¤ä2Uæþ›üÏ`cè)è L['1˜n\ãk Í(¤]^\\èARëÝv •Сl¾î)Žjò`×<9îÂØÌÃežA£œ¸ÅÐiíDóNja'  › WѬu­Ïry¦©GÓtÕ\jË\Ÿi~l¶úeNÂ*ð2\ ž" w™ð½­ßÒ4(hÅ2$ºÛ¿`Ù÷ý2Ó ú™ÜƒQ \BzõäqkÈ*dŠV¹gXÖX ¥ÊDiÈÜ IȺbWÕ,(ºu]A™æÙ ú[êËŒÞ*£]üïs›Ù¸¢«z§¥SõD¥]ÍÕx*®[A؃ÏBÄçsÿRnM a߉÷³›v»H=AkŸ<ž4+|í;_ö˜öÈ3æj{Û+KBí6 ›Ðª91žLÕÒY éúÏgx3;=k'ñÇ¿~¼¸þþýû?]|¤‰Î+£#ì„ë|µ‚®?òø"ˆÐÜ øy•û|ƒ«Á/~OÓ:ÃåTÑÎϸànù9p¶¬òEˆ°Kñ¤ôâŽßò\¦ê§HA[Àb\â,Ž´53«òE¾MCDžúò2 ƒ¢yàIôHçù¶I±N‚ZmbXRz ¦B/[!#W„ªÏRßìnq½·¶þ,2FÓöuº£C@ðô`þ­NšCV@F¶¢P½øâƒ6“À’SKXЏð8ÍgÈÆ˜Ž¾.’)Â9AQ !žk³'‹¤ìöa%h®¥ !%Ni µFÛ$„3tªÞ» ÕÜ©¦‰ýå¸Ù;÷Ó‰;cŒ™³W0e(wæê6ý÷mu–d¦2ÝÄúé®#ÜëèÛAΉÃÕ~%s[ ¦,ù¬½í÷—W—èl7ÎC9‘ŸGrq_¬^Fÿ€F¡˜þÿ‰þ9‚´? Æ¼€Ï—Ú¨pþÿ5;öBŽ6na<¶Èå&Ö<ïßšU~¾naÜ)u ø¤J'ù9Yì@é}·¢RÅŸ(C¶ q²H¡8™Ó¬[>k.'ÖÄh$J5üXÙm…H+þîâ?þf¾ò2EF¤0Üʹ"æ¬UÎ=’¥ìVƒVÅ…n|‚¸nЙ^BÂLN ÉÇ™i~…Gêas“¯¹Ÿïaª‘`:qÉž»sçVŒKìdLÌ_é”×<~¬ÄÞ»Lj±b¯ÙZ噿úôú` ØG#›ub¶èÖ ÈýÇÔE ±z´ëGžM¥!yö‹é¿¶ÃˆR[²g·7O‹úT¨„iQ¯ ¥0-:0Ò£‰t^™kn[wÌã´d‹/QWºÊ(ñhJ÷;ì½³F ä¥Ð‡vêÄ7ñOIõåW$y„ÛÛ¡µÇ´Ôqã<€oO¤rž}OJ&Oè\ÇEªx±}«ä8͆ÊôS"pÕ[ùõ‡J^8 :ÂÜÿ–Žy2¢ù™O(ii[öØ{éÎæºÃî«ïèp6ûxYòs)™½/ðLñ¾I뫜s&9øâ@ÇTâ0žº²i+e³çnöc½báWbôãUüå |WDÁ#-ªÛöähU¥‹·[bã ,íúlmFH_¹cyÉtèUÒÜ&-·ÙZÇ'\nÖì3W³…ã’(J(©Mjxöµ¡c’„Ф 0[1XÏ›^åê ŸXϽRF>êc÷žÛzV©BS”›Zz—Á)IQ Ë¡£4Úo ®½¯¤¹ÝÏ*¹ZËO¤¯s#·÷u58ûFT‹sÂôjŠ1¸¦õÆé_ó8½6›Æ= áÓzÑE![’´À;ZÂ]õ—{ú/4‚Þ$±åçSY2‹ÄšÛ«‹½æÚÁ?¬\!$«£‹8ã­yP0 ¶Ã£äŽ¢^±’ºÕ—†õ+8¨2õ A2c3,’EMÀô®2þ¬9L+@iuO­xLC·)q³Ý Ùö ºGî ±¯h䬎@Ôm?ÓÖ{c‡…sï¿e8L ½¬­×°õÝ„\K7ÖÌU›E`Rdí~5ÙΡ›ÎvɈ :lÓÈá¶Q7ø‹üíÚÈ€…¼§7޽%îgïP«ÙF­ZGNýµÈ€ (ÉbŽ4—@çð-f­é_lçÛ¹ï&ˆi§læ@!^›Ò®iSï»ô!¨}n6Òjá#MCoWM¢zIšìï®WaT®½ ¹‰ÍÖº¿úzǘ½ GnÂÑÀ¸(¹Çì …ßwaƒþÃ%mqLÐ<»Ì]hE:±Õ^îa3˜Â8}Õ³,'yrÎ3Ôwï>ÌeøÿâûâÍÒìJäJVE¡F4!¥m„@˜ °lëSBÓȶ&ÛÝ¢=P²«e‹mkJoLÕâ­êÐT©!Îü Û«äÞzÿc¤Ô#ð̤r~êDì>%Åm’-ƹ}"n€]ÿÌâõ%7ã3ªà6½ÇêJH2+…ùEhË[-¡Óæ ýš¹}“™G“ÉUln«»‰ºƒa.¬‹þ0ý¡Ž.lêG·°<1˜ó2O¤¦Ð¬¾TŠ­nÔ€`ðËÓÜ%»Ý6ºRѪöTª6™X»65H]„ Ñuž°òš½@­/›ï}bª.«u"ý Éë¤-òW§Iò'xõ×LMx5Ò ýñS‘œA¯³S½¸[Ïõðey7>èäéíVD5àÜ1•˜«Îì¹  ßïá1W¿*qø¸Œ¯i×û‰‘[ž,ß îi®W8Ÿ>u£µ5q«®æu¾w ¯¶¼ÿþÇ«w`ÕTu‘M—1ù*[£ ï+/P6³¯ÊkjЃœªŽ·ÛF™laEëÝiOìY3ið3IÍe}ä6NÇÎð z¯þV•×õ¦‘ÀÌûºNTŸ#)0c Ä n³g ¹•ðC´rÄ„kV©¨ ˜Èi>X™FþtJ3A0±º &¼=er=x­ýêýAM ž¨)SügúÊW]"mûI²öi£M¶Ï\œÁ¦ŸÜغôr>úêÐ\–‡r˜"­óx÷K“èw¾ºŒ·&Òg® ɪ`›a¾¹\³ DšÅø¹Š¥njád¨‰_»žV¿Ñ†saT c€,ªš,ÖůnA›¼þ\cõž³~’FÐ|¾üÖ"­ ¹.ÓÍØpX©^9äSö*)>%Kñ^µYüZK"1dLc ˆÒÙqåWYÎ/ÖÖ7øláƒ^Ž„ºÒuPsý,ftƒE™Í¦§Ãc¶œ(ú‘ˆŸ`(ÙèLygÞ¿<åC4ÉdTnDÔʨÜÖ/r§×Ʀ“;5™Ü!fÈ[ÕU±k“6#jU_Ñs xˆ0™º<† #üõ %ýÎK‡ Q• ‡+”g²2†uVe¼ÙŽ”FF¯Š " ×üÍ0›~γ>k(%ÖÍà"_¯õcÇ&½ÂÊâ˜÷q¶ÃRóhþÝ7§'R8t¶‘1›„cR$€Çƒéß2¢MšíÊdû t¬H?Bäà—°ÉM} ˆ£ýFÝãû!/\œé{P'P'µ¿:‰6&Ênˆì°þvYýšz…h«Шh•îÛÎq ÖÙLÉꙣduÍäw3ù”¤´`®ØtÑ7ñ¾ü¯èâàóÍΑh.R.kÆÐ·Ë4?t"ìD¤$¼ÅJâŸê¾c¨¥O9Vj·Á:.»wí·Í‰Öð›™÷7[…¥")uóð±ÝöŠL˜'Ç¥S©O™špÍ­‰¤>ÁÚ9Š—{YMc°u1䫇$.ôH½É³òNÿ^Æú¨…àî‘I1štrÐPOõ[ÄU°ÅsÑ\¬)Ô”Ãú&ˆ™¯Z­›ï¡Ÿ Ã!ø'jù¿¦ÂW¿k`­ËÔ{p¦Ôtì‘þÑœxJ°z0_Ìçg/5>ô|(6€"îùÜàƒ«L°/NÏÎ56wp€Ãø ^g(°p†R`h¤ðõéÉéË}©fö- > 8T{Z@1€Žý³æO¬Ÿoü¸-•ñŽTý‹cötÌÚíõps­³½|³p׬Ç/{¾^ÙWV)ùØË4s?¦5dèFöüi_û%RRø\¯Ì+÷dˆõˆšŒê°­FBб¹>BU‚u‘[AÌF&¬UÕ´ìã•}¬Z.è/3=£ªî!ÞY4Há'™R¬.¾–e’M|›€~}Nf6í|)Écƒîíþp»˜é\ˆŒÞ5>×·L7sÿóLî:‘¶üÕ0Ÿ@„SÎ{ælRE6*L•”ˆ)ÚçJ×ù=%¯bEä!3ɼ—$ˆVD¯÷l¼kÀ·hÔ†ù±¥¯gº2¬£¢Ë‚Õ–³TÛ*ì‹ñË8wËðué0y®âÄéÐnÍtáµs ä2.Á]ø1q¾ÔþNÎP ¶hÐáÄ$xª¹eÑù»áìõÚ „Ʋ×ižÈU§ÏÜâtiÝóv½˜nQG’uEl·|¤äVDû*/}GÚ~\ÃùÊatÕƒ¬ðq4|Ô”kU»HCr½Æ÷óq˜H–hù–¶8’9¨¼ªVïãYtfòI"H>P­“rq2ãë±vùv›«´Ô·¿U›‚ßBX~»£í熴’ Äc]# ]ó 9CÇÍCÙqA"Þ9ËçîvÂA=ëFR4¢Ÿw¢WDñ 7/Ÿ}í)¿xü §Õ 3 ¤ÉÚÛ—øöžµ)Ž#Éïû+ú؈3($[ºðEŒ`ðÎ.X@»önx‰†éAšéæºIø^Üß¹|TUVõ{ÈȖ–¦»«²²²ò]¯ì·}Í€ÊöûCƒ#Õ¢Í5–aGˆËc}×’û–¾äoHF¶ÕÙ¨GÖÃg!É‹‡èó¢'´ô+ÓÒ{Ú¯¦ìgǾ‘¸ösgi\ÜMÓ´ÀÝÐ\…Ã1®tø–)#ú„Áï¹?¬]1^‰Â›w=¹Ï!̰R15c7Õ£¨˜$M¶wÑämÉ8|ŒU´ãYSÏb7‡œÙ£PŠï°ë°mÀÐÀü¶)ÞO8ƒí/J÷b§f4ıH]Ǥv@FݘÐßû#S9,hÁ‘©"#S”¦ZBp«fpÈ*ãcà4¸<ÖÙ3ŽW¡øÏ=pj?ˆà"ìén³H;‡y=H>j‘ ö”Î?]]\ž¿=‹<¼:]\ŠƒÞuS¬Äc `Ä«òä­#ß#2ÝÉáV b¿'0\×:¸†¡ÔÈRybžãù-úŠŽ_ìÈ9߃hÒ0 Ð a2BÒ!Á»²kâÓÛ‚ûeüÐb]üåö§äÁ°™©vãÁÍT @&ÿ þYŒ+ 1•{Åo&ÛÆ1A˜ÁpÌ•ŠíÙÿ­?í1h8îö8J}÷^dq‘E¾¹×,™>XrÑ'”ˆ9P„o¥ÂjHN,oš§Ö‡ã£Óã£Áå€18äœäì¡DNÚ]htàE»?U4C­E‚Mf`ÓèþÌ*œ-âißq„ï J•-2,kGKe XH1)¾L§|³íVO?>„"½âq"O›Üú´nÞ[>Ž7t&vú-S5†E\„‹ëAÇû»iì6ŽÐ:ÙÇr5ƒ»T'FDLs¶Šñ´ºUϪ"®^&/8bä*µqãX‚C.Y"C! å|5’Oÿ¶pï]e4¨Ö ªÇˆÝjt+TÅᨌHC¨Ø'ªG‹›»ÕMO¼0g1Ì#ëF~Ó©7…–€_|¿_è×cÆ—ë”ΧÈÊÇ,Σ.‘gyÖkŠD:»pTWÓY€àö×uf¬/ÓÖ!ˆ2|±äk¦ÈRø—ƒP€Ô5m2€Ò1u† *y£Ö±ïë`Tî»?|©ÓV%­SLØ.1¡À¨™î8• †Í îª";d¯Á]<ÊG™ª™é%£ûî½²ˆB ÔÍ»hnW™óÝ;ÅÐ%üþOˆÃÈu©w¯þ`&ããÓñèpp‚Ï!0e $ØßÉowSéÕûp»ÓÞ–©}68üëðHïˆ:<;ØVùà ½ÿ›÷€½_«_¨uõ÷~M½ž¹û?è×xýÓåðêôøøbx‰ž'¹AÁrâU:™7<¢˜jÐ×a ÿŒS¯ˆ¸r†‚ØaÏAðhŸø‹fsµSjáóLxéèÃTëIhì¶+7ª P~ÊsÉRP*‡”­#5á¨Z0U ‡£~ð p–Š?³†¾ÆŸk‰?IÀ:OxÉSsJƒ¿HxJ– LýŠbcëãÑ–`ô8ü¢âKÙp~ŠŠðAëEâå(±Ì‚½{è‰ÝçäÈ#`ÃwÔ;âetà_¥!‘œ ”ÊíÇ_ÐÚò› [›4)”e6ëÓïRÀ~!R¶o´¤bÞ!5Bø¦Š¶Ø“¿¨¯7ЯGŽÔãÉ‘/F]¤¨ˆŒ¬ÀÏ<™(_dŠ'50Ê\ϯô[Œ‹Fî}),¾ÏÛñ¹xRïê<û”†jI6¯UÅêTXŠPòF«Y·¾û§5å½¾ Q‚$bï@d]T¸ËQ£§9Îcà ¥i[.(H·žðTÉ©R»YiJ9®ÿ”yJ_ê›EÑêì$P„“ÜçN,SB„ÍÒU[¼…”BJ[ 4œnŸ¹÷ÛΣ9yÉ>TŒñöA®ÃEOy@ep–æÄh<–= ¹§aP;%óì…={Å}û‚Ÿ²»e”È hÉ.¦†huß$WÒD缊œe€“uñBѧ»TÁ@>­e­5<»¶€VS¶Yé}¢j¢XBÄײÞôaAp-ëOéîÉÊô~™ñ³0Yz.± hE©^24ôqX=8\F†ŸPø¸¨/.ÈLÛUÃÅßD¼¸O3™£+Ò!˺=ŒÕ$É»•Èø´{Å}ç² ón_Äo'¦’<÷ Ï Ö5Ј³ù¡Å´š }¤WÒÓ‰­ œ¥˜6x›l¢Åøús ³û:QW;’êgBÊ=A\ ¨_&v†J”0çåïzÿÎut' ëšó‘¢íÛÏd •)Þä/÷¬ ª»ß™ Aã! úï@ñï…Ò@ Kâ^°Ÿ¢D±òÞ†ùªù̯‚ÎÆÃbUСø¥c•e$Ÿ?X+úGh+ºG>´'|Yí¾lëÅ=Ô¸t6œ-©Ê} ëÔår)¥ˆXMËS³‡òÂÓê‚Ö^ù¥oÜ÷­‘”-ÉŠÞoçY ¬ó½WîVÓýzÍ/¶LS•}AqùBÉ`“i¥‰Ä¤Ù"}@êà£"Âs¼Ò>•“DF!ÑÚyN|Šê÷]±,î@òü.½)ß0jç¾I²ù ï*Ô³0Z-SÁ,Uv àt1M_íÒ’v©Ó…³Ó:óUfz©Âæk±*d¾©bDha+æJ`ð…Ú"À¶qUÀŸ¾¹{QȬO¢|•襨v@ <3¿š—vœ0Àü‰û–½DT~×a= L"4Ï  †IÁËH¿]Mbê5r¨-õäNô²²ð­2XU ‘yÒ?Zg-¤‚3gajWÎX¸½Ü|…ÃYGüó š«µ/×Q8¿º‰P2Ìn y¹üŒ”ºn\ÝÌå$ú´çºÒüª/EÒ^ñlðZVŸ½å[–ûO.¾„ gX}«»YxÃë°ôÕóyâe~>;‡ŸŒ_zŠ XÚí»[_uæ|¨ˆ±¶ˆKÀ.$ñåƒÑa:8¿ fåh>ÇÀ˜;Uô–5´t”ºâ®†°Ê 9¼R‡R1ŠÜ#Vö">…»¤ sÝw£B—]¶ó9{5á #UIû…pêißLxFÛÐ1âUƒ±pt@ô½e—Úb‚0¸û;Á1j˜Âw¢}/ˆ(7ïâfZåÊFn„ô£©f­8L¢Û£ÄÈ5dfOƒ«? ñÂßëûÜi•ꇉÃa``KþÛ,ÿF@^Ë¡ÛvUÓ¦ÝEõ½ÖÏ4NÎá‚n¥~û.RÉŽ`sSO 3…y<-KCܾ€y¼—V)Û\¡Cy¸üeÛ•°ê.Û~“| 6›û˜§ÞÎqóžô“Q‘*ÔE-š:6êÓdYvçÛ/b‡ROúrˆƒÝ2Í“4›¯”Ê,@juB¸ùâ¿ëû…ÚóŠ…¦‰m¤‹Æ…Ÿ:O$aa›¯f&›”L ׂµë“…mØ’¬‰-.‘OÑõ{Ü”&pKäL¨Þ—11p°g¹‘%H9@Œ]‹VYU‚Õ"Vl3=¡*zöl¯ê¥ŸÛ—÷-2XÆ”¤ÐoÎ}bi,4b…’‡[´x:5þ§î îlô1®vѧáíDâUêè¢ñEa xXÕÖwp÷Ó÷âqBƒQY¿d·»Y¼Â¸Î¡â?ÇE×IúÕ]=”ªvW¥ªÝÅþ ‹wßgôÕÍ%éh+ËñºµoL¿4KÊBæV®¥s<åö«UÆ©QäDÚ¾â§!©û}®,§du)E(òt—¥˜£&½“yÅ‚$“ Ë ýN§­¤ÕÑ?K³àãÁ¾» õéúUí¨àC}Œ&ƒU`˯|l×îÆ²Ý^–…˜;J?:¬_IJœ?ëëÚ>!k[òº`ž°pø ¹êñõ¤Û¹ñPµéØN¡š/"c»“hÉYç\ ‹yÓŒƒä‰~“«†´[Lù{F›gÍjŽÖðª$þeÄkOÎÇ d^ñìmÉH\!u6Ôs²ÌnbX&a§äøpƒÖØ@8œ¹®?voc8>};>Ztšò L5ʶ¾z$8=lI<3•Ë0ØÔÓž†F¼Ó(ò2(O9CÄëÜÔ:]}Ao”ó2rctÍ ¯üçÿܧyô_X@ÿÄ[gîç‰s;ÁFÕAùÂRfv#K?êùy˜ß¼‹X%.ªÁë=oaüefÎB"{a$Ý– ­òÔUOØGm :·ÓvˆD]wyê j±6¢OÒˆ•[8Ã;@½AuTÀë\Î75~M–Þeq˜ópÅIK[·‘Û@ªlδµ65ìjá¯jxA5|Y ~âÅž¼9p®H¦Q²³º®VÖ””òò–itO‹;Påiɰ֪-¡*GFmaë2™¿ÔÚ$g BÅ RvÑÎ Ú¢¥rý.aM!¦Y@8œÐ¥SÜrÿâŠÅü K÷–•î“8‡U³U2oF…+b¿ÿëÅÏN4O¯®"5×A3ÇKÄç l÷Uÿç*· Må£ Ÿ¥È«zì°"€øëÆ]á«z sÿÕó&˜m€p;‹h·máñíª'=«ÅÑÙ“„,4'ÆTV˜MÒ‡˜¸ªÜ¯'¦ÜA S‡\êÚÇÿë{PLç‹Ç¶Ùë°Pð!‹£Nzƒ-z ¦¥ lÆ –vÚ NØÙ=\Å“ Ô  XÓL{ ŒgšY*”S!£)нìÙîÉ2x³ö$¤¥®ÜT?€ïM0¤«¶ŸÎ‚{^·¢Ò9§{…œp+\!K™¨_¢,¥·BhÖÞ¶˜®¹¨C½i?ÿÑ{¡YK™¦©2‚j T¢Ü²J™Îk¼C4§\T±qò¨êSJTŽ"»¯¥ 8±oprqЬ{yÙ¤r•šýö²bgWâù.×n(±G%0á|ŸGôéê#‘-ÑwKá¬ËØøßïóìz|{£Jö¦J;T*UC_1R†wE‡·[#fõ*èPPl‚ j=H&Ž`ìÙ&> xAëTÕ3m±:¡=\ø¿ÝD‹•µJ+CÉ;o°K"ær)-Á@T`d¢„;‚x—,•‰iåÂD®k"Ùí ]£zðÍÛmÆÌÒ›÷bìµÌÔn1pXLŒœâÛó[Å5I"ÔÊ!Ô䄊iI@`ÉzËP¾v·ÒεٶE [gPh½Æ¬Ê‰÷ÿ;±@¦ÿüÜÞÏåì’é­“ßТ1‘¿i®JmÿûèË?cÕ ÿºÊûßÛ4ûÙ-TrÛ},-CpûlÁЉáû¡)têÞaTÕçÇ §p)!Ðo ¼’î®i ¨&k ~gq—/Þ [ª54²^öøÑX…-ì©}qVÐÃzmVO}.«§j¬^›bÉÓ.‘” yZ­j·¥5pHÔbCYa%±šqÑX®ÒXœ…íe©ûv òòÑ1š¦ƒ-o¥Õ×H¯ƒÝmúºYÜßEü'¤X&͹$àõÚÕG1†·_˜1¬ÃiÙéà HÁfé žq›Wm×-Oóê×"=8RÌß Kâ‚‚v®OW˜Ny½–œ€Y$i)Ê»(Ë"±D Ú±!mÃ4+Áre“jrÁ5.0«–À øíJØî°~~ ôZ\“KZ­^3ý¢‹(V¹  @„±ÀŒÍ!Y«`Z©D8ÌÍ &Üñ]µ¿(É€;ÊdpYåQgS{wšø>E tö§·÷jK&È뻥¥ÅUEÑ5 z­š&[*°g°­a÷Wu¶˜Ë±vU&›dœƒo¯ ¢ÉâOr&NùÛ’Z®º¡úØ›Ýk]î_/.Ü%»pM ë2lR¢Q}:µ]žá¥*,‡”@Cà%” ÆDxÓb執¯ÿµ÷3ü·a~öåçþÏ ÕúR­/ÕúmÕö¥Ú¾TÛ§j’ú¨§Ÿ„• ”È)p•’Lg>TóúA†`ѸéþšêÝ àó½‡iV­Í^Öh³ò¸’B{êkIŸËžë8¡Õ—J‹¸¼Zi“º…Q!€MöyG?Ð:K€„€$ì %•úmA¬©a§Ù«8éñ[jVÞjuÑ 2æt*qO1±‚rÑ®ÝâÎNVJ©â4aÕR¼#T.„§nÿJnéüX#<*ºI“ɶY/…9ïòÃ]C8ŒÛ*ˆ!Á xÉyX7þs»1 à]䳊e6-# „ác@åP.³ÌºŽ¸æ ™=DµežÌçÄùQ Ôaä4Ê@ë'N°%X‚=¼pe¥—Nóaá(%|Ì8=xExC©TéWÏà&cfâ,f¡œ¾ C»ðLÖSÙ !üVòŒeö®…÷Ò‚ã^Á{‰jèƒo%¼,3 6¾Tòh-*©Cã>QŠù<88¯1 ZŸ«Ñßy¿Ü•­IÈ´‰B±jRÞßB§Ì‰.ÿØ þ^+¼öý8Íp’'x¹û§—σ,½¡ŠÈ燈§.ÂÉ$⩚%w_ùÛzš%Vt«=Pû,óôT¼Õ9—†>f»xxϹ_œ´®Ý8 6$÷Ý$ÌÉ…XZ½e='Ðìñák@5ØÔýÚ‡ÙƒÊÛ,¼{ék@¹ þÝ B…¿ÿÿOo®­ö¼’(ûî穲Ç20xKu³¼‚ÇYm œEX„:Ò…¸$Àng%¤Ðö[öÙF¡à4úHŸHù"ç¼ü°Ý«ÁåéÉÕ?Ç—’ÞŒ_Ÿ Çp—öùà'€(úÄg ¨Èì&oiLeø„øÍÓdöÀ—'nõß1`E¤oþÞ7™]b ,Y˜ 8MÅÔâӽѶ2&™„CƒØ$~óêÚëˆÃ€vof2µ÷„ϳÄ;ZÌGt9hˆF¯AìÙcHsj8øÔóè`v{Îc“¡˜ðé½yªõÀ+¨K$~{v4fýËÙàêìt4¾ž_\ú½úo½¦ªûGX»ñó™#…‘îŸ~¤|àš€éRæh}>S®¾‚™‘b™Òˆwe1Disd~‚úRaÐÆ[$Œ!:ù)•IÍ’(Ó°H’4fÈFY4¡õ1Ä`¤ñ¼m»¨W*Oâ )’f F:Ý ÎâîÞ94ô~:2C–8WÈÎy–Îèþ„}þÃÓ7oNÇXGE<*  8&€àÝí=¿ªÛ<|Ï®+“Žà |¡Á7ù;¤• §Ñ7ÈX!EŸ³Yyµ •É|®/Š’q–&—¤ ÿ8Si Kh(n¬ `z³¸ÖÍ›…*×ù;b\©ç²Ëvc~s6ãé^b V‚±r”®»—Ù?ŠÀŒ¦Óm‹4odÄø¨6öRÅ@Èà”ZÀiÖ94â®@}Fó^èû-ŽÚæÈóº¨4á¡ç*ЇËLCË\-SÞ°ÇáiåòÀŠæv NÍh3@Þ–@Œç1 ò›Ñ›ap ~áÊàì=SIE,;$)@¥ žæ°…o~?‡žgyxÏâüA›§‰ƒyqƒ¾?Ø•ƒ—âËJ#Ô¡¤Wv‚!®!‚’\ÕÈŠ­&HÞWΩ*‰€¨°tÿÁ%J¶`ûî Hé€{VÜñ´a‰8y;{¾q0Ù+Ò(ǃáóüÃð|ó»­àøíøãi¿â&Ù‘^0î¡æÙ*TÛÛêáO(6o½zPáÍq¡XJ±qá»ý|úö¾cKºÄp|d“WN7॰¡§r4C”0‚HÈ1¿Cš³? ”Ð&L–H*ÏäñçßÉdhþq#ú¦cL¯#'d^ U¢Œ®{¡ë¡\”¡DsA–W6ÔÒB¬Ÿ8A‰:WÈH*OïÐM•¥)„’ô™´”Ô6wÝGÙìA/`}ˆ¿´ScçƒvÕý,¯Œâ4¡!¹×ÝÉž3š€>Wã_\Ñ”§PÒ’Ša?k‹ñ©×‰­eiöͱjy¼'0(îX¥ùzï•ÓÌ:]wÛ>1óáèêâò||øæ n]‘ÛRÍMø9ÿðß½@„ødôfdÅøðσóÁ!€Ýñûgaֵ˲l^HY ¹¬äEIK,"ã®ßRî)ya¼vìÆ¸¸ÈCÄMå$ÜE2>×jv}!q!âH†Ÿòí8QøÎúž#Wd=-ªØG!Ÿ?R-CŒ~(á·!k°r‘Y<É`çžvJê@BÅ .â™kúÇ*Mš%o׬·å"å¹OL¡žÉ]Nc­_Øö‰‘†?Ž.¯^ƃóŸ5§Þæåàl4î ..¯P¦zðÂYðüÇWçÃÃÞþ!èô+aãÑɰíï×oIúºB:!_5Úbxy$ìK87Ôc3]‹l“ 5…RܯÍbã[%ÿ¤WÀÚtp%%âŒa+c€õ>¾c; gJÚÁxIä¸öÐxjXYªh‡ôSnʳŽ °M9ü¡¾GJŽ…¿=D¾ú€F«œÏþ1Ù_Ê"É¡è'ZaÂIáÂåe-Ä<à+äÑzÚ›ˆÖ…*žÕðœƒ!§%6I\`ÉøˆzÛ 1AVTb[iEŽðq+z^¤9Pb¾(ù•YÁoúIcÀ©M_Ù sñj q«£j° 0DrÜ…Ì"  ID×ó²—EÌ»t6Ñ:Ø;J‰"xh±€(nK„«HNøaXšoçÅ6„ÿ%äb·–¾"SCy7ðj½GÊšIX*“…ÀvÇü‚[o­@áH•E…dtéŽ%¤hptu2±‘PM °tœ—˜‡Ä_’¢-Åó¢ ™/èÃéÙp É1’™ß¿ pÈÌë½=³µ›´ƒBp1“æÔ3qýoËfÄwêlÁ²ò¯rþté}@7Ó™9¾=ø„O´àÈTjw'ÏàÇÜÀç)ð™Y†ŸA*Y}pq8Aò%LÞ«Èbÿ’&9”ƒÜ 6ÿùÍîËo ÿ°#·ñ›Á7[vÓ 4ƒîÔ¸ó÷£oøÄewa3Ü “0Aî6õe¸ØåXµÄ¯ÍñœëmŠRQ—ë…J-JÖ‡õšÐ€ qy<ºëÀ.ÀU ²7¢ëw­XÊa„zOÙaŽOÑ8ô.FÿöFG½£ÑËKðu‡ ׳óáÅt¼÷ztyÑûûéù?‡£Ã?Ç€âðäd¡ÞžA?ŽFoNÿÎÿîá_}ük¿×§ß”;ì´Žk;|…’n9þB¥qŒñç𬅆ÝjŽŽ‚À© Ï¥dH¤“LÐ}dn‚zoРߢ>À9Ȇì‚Tv9ª[…J¶ë†¨å¹rRÕ1æ…÷:—ìw.¹ß­ä:"&G‰Q˜dO´Q¹äÙÃ*‡KœpÀ@ÑB&Vpø1‹B½Ò?ËéåœÑàT ÎÊ)04Q’“ÇM PrLÉ|rd2Á#N3™ô¤€  G³‰Î‰¢ÉŽU‹ýC_LbjÍ¢‰ÉôãT&ÎpÄúÞ71^Œhå Nyb©œŠ:Å؆ôì&âÊï Q¦ |ŸÞ¥w÷3tó¹KŠH‹ Æ­Ç=µÌ‚uKºÙQºÌÜúÇ^/½kx©°OÒMR[\hf&v ©ÞÑœfš`(»}™…‰šFÙöÒä|xq"Ì…ç¾gÄ޵/·¬Øx@"`¤Bv›¿ÝàèVrÈÉ ÛÝÝ? ÇQóz¤1êQÑ׃‹á‹]²¯KòK„P.¼ßÿ«.} Kÿ¸mÞû¥ÿv&8|§Ëþííéåðhûì1Ÿ·¢½]®³·Ëu¿¯*ü‚ ÷uá€_Ú’AšÙ²ßYt¤4¼¶…wxU r<·k!hº¿Ã!@6·.´ƒˆ‡¹‡ÈH"»}Á¬;Ç»4 Ô(bO×Ú<Ënw zsô¼ªÑ°”ZÖ»“Ù Cy¹”VeDó»üA`¸ºú¥;—w6iÅ3w"(YÒÝ Ë²ùÜœ?óİ`·Ñáà„¹÷9p¯»¬ˆß¾À·Ç_`Äß^r eúÖ~‚/OÏ­˜|g¾»‹è@G>¦ÁtÞšK60k~õ(çc"èãôŠß‚N=?ž .áåÅŒ÷µ±· m@-æÊ\Þ ~`úø¹RTeEW AºP¥?´~#R8Jõ§ÊÄ ǺPºˆ,LrÆHÆXÉHrj)®PúY¤§Ì’Ù‘_à1€R-šC‚ÀÌÖÓ!ì»PùYVšs¥eɜڤl_ǹ±°;ã>iøÈŸ„|Í"ÈŒ†Ãá± ™„}âZ$+O"™n’ãb¡ÞÞ£²è*N*,@arÖ@Ù e3Iø3S\!F‰wA£*}€k\&‘&'(¤Ì5Ø$x·ß×ë¶ ‡6ê!ñ_;IèêÅÀÂd2{å:¤¡tˆ øšËIΣ':uˆuÓäãòŒãÆÉèòòdx®öh0F®ðË[ôõè]Îð†Û•X9Íá2ûØ®ðj,F¼]7—äæ5´º}Š­V­öìé• ÜöÅô:É<òzAèoúDmé?§1¯ÛG9§¡ªn!/_úW©äpáo·£d‡zÉÒÍ;̽50 {¹Â.¸P fN$'n5P‘e8ÛTàÊÑõʆÞÓɱ¸>kèjB9ÚëŒxêHFŠÂ¥(Ÿ‡OÖ2óÒFs>/².}ÓË«â¬üIòzÎifK¦J³¤^ßö1£´}d0¡®øe.¨cR„zäÁÉœLXÄçög d³KÌA…%*€ê3¡‚Ýg7±@ úˆô’Q ·Žõò=_—‚þÈÕ’¢N8c w¾ÎþngMÐ.Ù$2ÎЈD‡h§ËÉŽ~­'71:àF<½¼NŒÓç/‹+[¬s U}ä* " 2`¸4©!š æ^º²vN$$Hºž3@…éúI4€âd¯(¨b혭&£Œ™êÜWqÎ6(<ÂZ|á—qz­ì0ÔÁª°ľ¯—½{k8 ]kÿ^°[ZóþfGrO-äÔ슴8àt±x“ÄâLvåT0ÀÍ·‹*†Tjö›k²µn°ß@Lz¹¾Ì™4‚0V­ËEj­³ý2ï^\¡õÔçÝ‹ø,41(Õ6ÁxŒozÅéA®\ž‰+M¶LnÕMÈÎñ0í ?»Î–•Öç½:Nêtž` *¦çºM­5 –Mp…¶g¥9ï ½‹xæC7eïúÁÎ… ¤$œK²¬Yò ™µ›°¯-ƽ-2»bOà×3¨`v·ðš2p >€.û\v£ Óvb§ó¢;á[â"©iú$ ØÞ¥ÊîNQ÷1-\7Ño‰ÞdÇûÞp¯Å 1?¦Ùû¦HäÆgNA ßP Áû¤ÌU¢2¹¤£O܃T±…JFŠPâE7ïó|c |Îܵ³üãaœ_;rÚa¦o£ã°øÆ[Øå YÔ]n&¶ÚIg&`$Ë,’„r@±ô€W^ +"دÎþïÂÙÿ\†º´dæ×¶Ôß|N«¿¢ßGCã¯ókÙŒYúb6rÖ|Ýoªºµò ª ô¼ñðdø†ÿ&b¹+a†'£ÆÞ„¯7ƒHY1ß ~DPþ#j Ë»ý-oƒ—,´kyJ«½Ë5¤§UeÅØÛ²e—¢P¬ŠLí°-Îíð»xFëˆ<ŠbÍîëˆj\œ…Y®Àœ_sÈxð•;ܹ¿6í‰aõã³é¢:”Öå|‰¬Jˆ·7ò{ä×õ(Ô_ƒ_ÛµêW~}Šü견w\ÏÐ4'ÙðëO"“*×çûö9¼Á@F¯Åÿý%3¥•„Îé8æ –ëˆ²,Pö(` 6{Ð{IBúÄe18ê÷Š;W^SsýP,­a¨h})ݦ¯—R©ÊuÝÈOAéMi(IPY–²†-d’TÏS“Sçš"Ë¥êÒOï\Æ2P€$G+h–i¬ª4±15¬m2“´~kw‹–†”fq®Ë^E2ý¥~y8”3íþvlRØÍ jsþ’òoP—ó”¼Ï׬ÍÊÚ`áudnžÚÜËwçIò»l­Í:§ˆ·Q5ì*Yly8<};¾ì½Æ—¡u' ÂUF#øëþÚú†6™"Z@¸í]7ôj/‰´lwQ‘ì›XtiŸÉgªà6ÊUy»ï•¡eU¤P\ê“´“ Õº´=½g¯ KïoßÙnÓìÏ.FULÙñ®6V ¦¹>!ˆoŽblÐ%3«öâäM ›P{~›ÀO¢‰ß!R49^õ('i µ$êú»l‘Ôrt-.Í©™xß„ bdOø‰ªÌòYV'­n¸>‹=xl£¶^ëËÒ_D ìRà¾0Nâ}r¯ä4&9 O;Ͼ ™áÍ ³ÍËx× ž]° ¾†nø^+Ãg7MÓ]YÕèMÃ1|äríKghv`§,q6TèÜÀI©Âj‘ÖU×s¼ŽnB9¸Î?ãÉ1Ð5>ÄPA‰êIdqUcECj‘ו˙+ÔSÜ_Á‡aš³¢£ÉoÖýñÛ],ídk­àþ´ºA#|ú‚¨Yö üj‹@,éICÊF¶Ð²õ5(v©¼‰V–wø'ÿÉ>ÚXؤ‚— é åÎj¯83¹wâKHçp9é9|e£ëP¡)*©¯ržGó;ÖšêþŽÓ>²( 'CB»ýãuD=ËIƒk[FË=Ì"sö¨9îeñA¡ƒþ’BrÕŠ«S|z;ç»Ñzmí %œ³-''C}sJë”&eìäœjìÅWŸæÿÙûúî6ncïÿõ)öðžóHjIF¤^í4=ǵäD½~»–Ó¤u]¹’7!wÕÅÒ’úäùîÏÌü °»¤(;ioï|,‘»À`0 ƒÁÌ¿«NsºBåÀÍîö|Mk€tÏô_—ÞO\zISû§-½£m@®Z²m¼õh¯õ~"&~ó N"Qã?ÇqÑ’Bý‚û>GzÐÁüýGžÿÊÓ£F¹‡Ä,yÀÁ}G—õïGô¿>µ–¢ô)|¿÷oÍ÷÷š¥~eû_Ùžê¶×ŠŸI⋃À/ÆüäÿûÅþ¿Üsà—šÒ±ûûõëLhÏ„Ÿi øo5î_ ~ ÿ£gB—ÍHu}k7J)H†Ä©oJ8ÊÀQb#’©Éø;Ðáj¨{•€îŽ=P†¤p•=×*ë¹áÛÝNÀKöK#½ã]žö)îÍ"ç–îÑsÞ#F0œ‚8@²‡ž]•½žÓ[Í¢–\¤\MY’e£4éŒ <¡`é|žUf–‘µ  œ•bh±3R’ÚØäy!NI8óãL7“>‘ ~êÑBêÅôEDÔü‚F#ÉáÊ)Í®á%åÓµ••&8ÓáÓäéGŸŸ?æ¢îÛÀmŒW´Ì <©iš›IZ±YP%ç«MÐDõ9%•î$fšw¾N|µYý0®+ZGÊ…‘ÄA–ÉÜøÃÈTDuõm®Be¥)CëË ò¥ ½Š;†aΨ Dä¦å8íŸrô¨Dë<)ã¥À;õ#©‚®Ýê—£d.mBY!¯—űõW‡Nîo饂¶ì«Åm¸ >‹´DiåÃ.LåŽ`Žp¥Ï=Ký߬@è ?Ö7ߟȇ¯ñ¨Ǹyù}ÿåŸû§ÏÞи%Ïb¦÷HTÍâ„„uT=%ϲë:“ <¦`ÌîÎì) &^¹ùwjBãŠf±o™WØü •Dê,*±ãÀf¢oºl#¼l!­öÔ²#Žà(˃ëpƒá}®vR¹¥5t5óÚÛp’…^ˆ³ HVO“Œåq•ÑVæÐ¢¬ j0Ä—ßsß_þYšTaksË¥WU–9“Š@Ñ²ÓÆò6 á-r¾Í¹§»cîPì¯óÛl–œŽUÒK.Z*­Fµ”9n6+oÌcü#Ðrƒ¬•B‡4é)D¿Áhg¼›|õ;.ÇF;{Gû‡L×U-5ç²”T¨¥™êŠfeª€ÉÛWir3ÆD#ÝRúR ³-™U9Úû=Qãðà°&ˆ²r ¬H/·0ª¢ÀÙUÍ罦~ìÙlé‚lája+²+Fr¡„O!?ÍÊßÐJu(mp<Œ }…uéÎzIaUHë´ºÊêˆ÷$œ“«$ŒÐ +ñlÆ4a2ÂïÈ.ËE–1Ŧ‹Ê 1\¤Ï­0ú=¥…0`…»˜mÏj+¼ê¢‚-­.‡²É:Aå 2ÅæASê¶Ø¿UÈ&1¬Ë´aÁSœ@DWñÏŠ†fí:Á,Z9\ºÚ¥1bmOy ›­`&ÕBEË<Ì"÷¬t¨m>Ooì Ìg¯Þ¼xBY¾msñÜåà– ”4gØrYFlN ¶%»9·¶gÓí>M_­¹¯2»¦>N>œr™3šk@µÁøqBx‡±Ÿ îÚ‚ô½°~É7UY\¡ ER¤Ï`/é4|õHÙ;‚Ú}öŸ§¯Ï¿ûæ”64¯zn×mÖº¨÷ðÈ‹ý¥b³Tÿôé·dø"ý6ª|ºßü瘩"dÖʱæþŒ£Ñ¾µFõ×Î6çm}ݺ1ú¢•‰2{“VÐï4yÁòŒ‘Œ©÷–})êk$ùÔeàªÒÑcgo…(¯Ž¿LfÒL?ÊjA‹n3J÷ OlsŠÊ'±äh¨ï—˜"»‘­¶ÑM/OM<§–ãDHGŠÊNsÖo ¶”0Ì ¬)zÀzÙ¸2ø«µèWkÑÿxkW—9WÖùª7Ye[CgV\Oæ]{Š9uöÞd§¿Ú§–Ù§~΃¬Ýaò,Ÿ9ý†Ÿð³Qòµlïf6xÌ5Ó_^~ç¼²ÛI&ݬŽ=! íÔX»ó{›—dN4 11«™RËÛxQ6a QbOQPü*òù•ûNº%·t׬ˆ þHÖ£0$à€]‡qW¸Rß­A™PÊ § š8±èÑÐ;Þ‹Ä.²‘Lg¦ ’º›(c2ãöÜj`É›Œ½>D?RÚG3t£D¶IéÇ’bÀ½5Ú›Ö.Q¿–Ī]›lv)[øŠúLóþ“ì \.—PÂ3["Ø5/9m /t ºÈËö¹ö-Bm–>R•Þ5݈0é³t.…{HåÑK¶Žx3ƒ…i¡cŒ5G”ËòL¤äV‰’×6g ³ üz„Löаɿù¤œ•Å`šY Š 9çÿÈbZM,O ¯HøÍ«ç ¯ë%5äîúYs%2:±.6BþÕÓý³5)M’ËU#HRžcPoÏH·;«ˆÎå š½Ê(ÞÉ'¬Ä/’<š*i±aDh܃€Bý&'°6”ÍÊkìBÁ7óÉ7ßgÄeœ0z¢ç£¡#TE÷þ„E âH[?*¬sz$A‰a&# w/xÀ¯Õ5óæ)ÛIЬN^XtN\D “l±^ºmÒW“eÉ›gO o÷ö{$FU•q®6͆ÛN÷læAÕ"ÙU^¢ø^ò´Â¶†OǸ–šƒË,¬Zì¬6 Þ` C™ÖPe¹eL4(wo0è%&½ƒêëEÒÖ_ÝÌío¯µ„ðî%¹LôŒU[¥\èK“ÜÁÐØ ƈ¶È’VqêW^]Ü2êK$‘œ´î‡JbÒfßʼ…xb/ζÅó0j‚{Ç]–2Ø™&W+Á½ƒðc&€¤³8GØš•å–ì,ÑdU`ʃ©G»H%!o‹qPã Kj¸²È,vj¶¦ ª!XŒZ]–agU(P€õ¥)e‘J Š,ä– H‡a\Ãô©Nëõ•?Ü:ä³È…yߨ ™˜TB P¾ÆžHm¤ˆ-èºÉ‹¢Ó±ô W5j¶%º¶‰À½7Ù&!ðcQÞ`³(qõmBf—³gN `È5” FH .¼Š‚9ì·†È\¸œ±™»–Ÿ!÷í‘~íô½Ï?8ª{ËªŽ­ð£tÜ.ScG3œx8Y­ž¼‡ÉªÙK˜š&WÌP×¼-à-k]ºÕÕ&ⱌ‚R2ÏRWfw9Û*F á“ué½}ÉLEê4—Ñ›ä—çÔÉóº†ô†új0êù ú!C*+~n²ëTήy±Ðíí4»ÌEè¨}’UÌñÞV6¤µKížÛ±TH«@™EÕìØé£›…ð…:°ãÏr#<çâ1²s¼*òØëüÅԥȧ2ææ±µ2ü&JûX.áS-¡Éqݳ8ñYûéé±>kgÕÖWåJÔ2Ë3ùi™Õí´\GV»{‹qf»ûKÙìo+É ¥íÿð¤þ2|'NvÖ;ŽÓL¸añdJQD1én2èCJkËÚÂxQœÝðz H´ͬgû¢  ã-¬;@óÜL¨Á´Èxò¡µÎõm¤]/eŸÆš° Ê; Ê‹‘  ge•_åTWOºy¦¥â³n¤ºôsÀ¯ª ÷ˆ¥˜l==X@Dr›%X¶q˜`â¤VÑ”³ S¯y6ÖH?ÅŠ˜…"êØ—Éæ2"n"̈b <•#2)ã` ¨œ¹ëás¿9ÍÕNè4yL^¥®Š‰d3 ôW$èUöô6‰¾±P±Õ»*éAÍëù”Ьœö6¥ _7×ïÞºò óÚqœõagÅ¢x³· ùG“jÆ‚ôÜi ‚½¼¤ÇÍ>,¯£€=Z}¬2¶ŒRHYÈÑézàorMËcåjb!Ò+ÞDÅYDW  ‡L¾mbXFßBrK笔TG7Ãu× q«Ô7*›Pr6û~dÿkQƒ×-Àì,ºÙO6­®£G;Á烈3ðpwüŸ›²CS¥GÆÚè&Þðò(’ƒgm:ó8Li’E–ÓÙmê¾×¶ªœÈ ´OØŽFâ°È©`&‚ìbqå’ÀJ%Ú ©ø@]œ>~´¥,$8x—l±™ŽrÓR_õȘ‰Ù:k²ú«…¤f’çJd}U_Ž˜|ñ#"© …uRa´|ðYtC‚Ý5ÓkeÌÃ1‰`÷£·´ 8µ_©¾)p¹›-–F'g·[Vx³R&sCn”ÉÍb.¼àu‚5SÉLÍ—Õ^½€å97>K²õì$yö,슦KN¾}ûŒÈ×çTŒGuF«Ë,‹ß3ÅOžQ¬½ä! y{´¶&ýñ§LSG7aòˆœ‘¶˜vÒÊlÀwÔNuÇÊ]¶,¦ÞJăhU1ù !Ó—­êÒ³µïež.Ña›.£J[«Øç¦&“Pœ½}òÆÚD¢Y€ûËö=0Ž˜ÀÁñ¶î ±ûytHnçæµ^+áìç¡4ºNpÕôá j*ÿZ¬²ôÐϦÛM©ú˜]^"S³…¢ƒ_iû™ô"Qò<.™¨jKˆ AÛwÖåtL Qègë/!£ ¹Rùæ&VÃÖŸW¬Ñßo²[¾áfåxòvºÖáø~?µ_Gcþ½5©«ÙàùvòšÊ Z lUá÷§;hÅ¿l'guyÍ;8î®Vž Ž_µ ŒÑü¾Ù[OÊq”o_ž~ß‚±‹»|ûâH¾ÿ!¶Ë‚è®êK]>LýëL§¢»Pu“Å,œ…B­­6…pµ¼B#ðpéî’ ¯E;w°hsÑÄ­QXÇ7ßœ=Iމ±³Œ¸;¯©Üi1 À88À'n±iEˆB|Yz TVA/Ô¼õ 4B?]ߤ gÁ;½‚*óÅäƒj®rªrýX‹®Ð,Õ0ÉÜg‹@8ßxÖ:}SF U© RñÄFëZ.Ýä«z½òh;áÛNã®ý,˜ø ¦ˆ³¯ç Àˇ»ÈüÒ÷`µ©(eDÛñJšÂS£/_‚%ш“˜j@ã-1+ ñØçFD6†ï‡J\>ÒEÙcŠŸð£c†m§ûÁ‚)|ã f³©œ\*$uÉh’:7Ôø ;äÃþ÷EZÔ<êy´6¼ŒNù»µÂJj¨±t¸ÌÄ£¡/”dV9û-Æ4ëyo-5Æç]Àç<Ÿö†ëX”™V‘%lêò³w­¾ÀÙò¦&A/ôHû#)ߪÔàÈ5÷³ÌöƒVÅ…¸_žs›‘Doê süÄà›ÃõMgJŒe{<ïâŽX ªFýþësò ;}òÒmŸŸ¾}ûüDj6ïÀ/•EŒƒS$¾›Š}±Ú |¸Q1gŒ˜Ô°@¼9:ª—d8zpŽš0@ÉLSä‡ë•bË ö”{VDÕ›çz\Œ´mù*º—Зo¼œÀõóa†Í¤±¦ÜS«Ñ £Ý—{:A ÛâåÎ M+q»úu-K2G §-€ðŒÅ'¤…‚ºF]«)¢@N÷ÆÐB¶±–1n€iãltè$6Μ̮•g´y#1œ;†Î²“š·c†²0”¯Úˆg͸–Èl©~8¹çº¢,Œ€+Uϧ÷N.fiñ£l*Ý_Y…IÅäzL6u”¯Óªi­ØˆuUºó& ÅØø3†)•„Öx° Ô³{ZÅ G=ðqÁqX—r÷&ãììSZRS˜F€t–¸näâó=?ýƒ4ÿÃb~í<°£¨åð¥Šg±;¸Ñœ±9®Ü¥+1WªeІ‚ãQ9¤ (-åt Þ|rˆÞÖ\Á+6€ýb½fHÊø œã‹í>}bMwé¼Éƒ;u8o†k™›äŽ+Ƚ¯F”r˜œ\|i.K¯õÎTË׃\»Œº O.ÞGN2ùMùÆÃʧ4Œle÷%6“;>Á †³o8t:c¼Ç³ñ冋í$Ö/Ýås&–¤­v}£ºP\À±qÁWH‰/íEYõ:¤^Ì«Rxµ‚îeúrøF‚ÀOÙ€U³§[K ââL”‹^ˆ®Èþ›| ÁžóÆÛ±º”é ·ø‹G Ê© é™ÜiPy¶©ÑúaݦÖJpØ)ŠH‚­+ciL~1³Sæ>£p§¶{‘.ás¢Å5mÿ¤ CðrUé…eX]b’´»’ hˆø Bb÷*¨:k‹ÌÖpäû²åÀÇ[qMÉ$'שhÓR1$Uj®i4€Sºå—e=fŒ¶m”•Ü& dx¯ÏüEã&¿žD^™¸UÝʇ6ÂË’€ú3v«a#åÛäÕ³Ä^/¶¦úªüAÒ’­G;Šeõu|Ò¶é“HwØŠ<ðp¶ÉVèI–;an;—,!´Q-pè죡¨W#»Yr Z^8¢‰Hl)ØžûÖdª¢%_Xœf¼î¥>jýÛxùižœcMƒSªÞG É¢¸;.V«KÙ¯cf…À–óÿÝ@Å‘íçš93jlÏë£*V&†™Dg'J9݆FǧöÔV¡ °$kCÜ©°± %]“»ýA-µlö­¦mýQ3wh£V 7[·#ûö‰0.›¹]”PÛ6Ûµ`ÙÞ Zܳ¿Ö6i£¬Z³Ù”}Ÿ-{8Üÿm1µ¢Z…¯Âí« sȳîqò3~ªLªGTv°ö}ú84“VL)¬àTãÌ»ž…p—š/‹i‡õ[ØÀ™7°0£† ‹%§a< ÏŽÔE0ô˜pù1÷W,ʨ»šJ…W}#çœi0“™Û"E G äé1>b¤ý/?ÏÈ@: ¢ÐfMtIÉO§ŠÆt 7޵Øõt€GãöÀžYf8õÓ“Ëo fD¹z°Ç&µ¾=Ÿµ7€Ý\ÙÇ;ACoÝPnîæY[·‹÷k[ù0b©º¼4Y-ª¸ú1E4äV¬ZŽ–leRGRO—‘©ýcïj“ëΉ›‘·;;{;ÉÖÁÞöòZ‘ëµOµŽv–ÖŠ®…k[TëÑÁòZ ![ëjFã{P¤»NǧOß¾zã;âjã#ª¶òg8ß°VµL²Â‹ñ¦u<åüG, †ÍʪÛðêô1¸¤a/ ¨K&W“ [•$‡“-æ“ÁeF—Öå”_YyoYøuKOnu?N²¥Ä¥!˜g¸°KÛ4ìjî/ÒIJ…"¦tb]˜Ì6¶&üãõà[ä·€î¬ã2ØÈú°e=u؃ Äh´#ÿ†ÉÖ+öòQ‹ú~¿éáC+Í6ö-^ÍÌò«5+ĵ8&˜nüÑ…éÜp§Y¾¸û)2K½—ôÌ”ê}rGŠPMÊ®˜O ;«X Rœ[7îÎ…CD Â?QGö‘cI.Z†óÐHÙYS9ÚÜU…ël½àU•3#!¸n_ö…ÂŽÄ_yæ.Mšæ+ß \–àHŽ=f×m5Éw@ïÚÁè9!l“Ä:rÁVa âyþvY_3I .Îiµú ÿ¤öÛ¦ËrQÅî–Ôþ«l"‚¿;}ÍYîThn]Ê¥½Ðv?–R&¤CÆsàún€•×¶«Ñ—0”EYð>‡ ej%µ ôB÷÷-$iíî%[¸f”Zc੟ô—§Ö7Ä´ÉÙu¦çG'œÞ¾â¦p/ñ ³ªŸü©œ%G}Úz%#™n'£ÃGƒñîh›ú§‚Üj‡ùà>Ç‘¶%¼öÀÔw³L2ÿkßR§%ð?•‰}Žu³cì†þTé±stEî¨UN–Z‰rdì4Ò“Šñ9n¼-Ý{êÕKÙ¹}\lë ˶óÙŒÕIœóùC@¤fU©×ÚÃï»Ïçu`uþFB㢜9µ_¯á7l½Öÿ%kNXíÃÍ-z þBNÑ÷€‰/ZІÓãU ðó¬uL›€{ŽÂÀ¹iÂaË€ÖÞðºýý?² ì3<þ¾‡ï<ƒùï>¾òMî üQ£ü#'Òå+ð{ÅõÙL…gü`Ç>7jì2…¹Åû€Q<å»öãø’ÙM$GM,GŒæŸùC£çx§A‡1ãyÂ0m1ãù”Ú»®›ˆŽ÷40®íñQk¸í FŸÍúþÅØò÷Ã,.hi¯uæÚ<[±è7÷Š»#ááSÖpÅdfYÔ‚ô hz>=ã5T΂¶ànBÚßÞŽî%–Ùi“-lBOάض¬<0ª–¿ReêÉþa¬è7l_FÕþ¦Ò¶ñˆÛØ?XªøS1j† ñïß&²nï{EuÚ¶ÜJ>Ø?B‘6/ˆ8‘—1·ìÈØÛFöá1qÇü0ž »x¦Ì+›4<ÔÙ+3®£ö<‹gñí¥NÁ¡ KéOSì ?ñ¬>Dâ™}ØÑŸCן³°ö^ÝÑŸx¦¢Cñl?luHúÐ$œüíèåÑν£~4Z1êG¶›º¢<Ë‹x=q¶ç]eR]”±Iº)ÝwøG—ÆÈOœ"ÁG;” <_”^HCLÎlËõ'X-TS—*V~Ë®ßXHGçÁëfYig°§¨Z–à­lØ©ÞrÕÆZ19’€ Ù»UOÈpàöÛî~¸…s~šûýf…Iï}¸R¤n©Ÿ?lø Ñ_Oe± ‘•ïH–•Q’µ]•üÁJÍiS>ƒJjÕ¦ÈÏlï÷Gýãi¨ãFíhÈËî"Ê:–¨$4‚3ñŸL³®îÃ(ÂûÔ}&'\ª¾˜Ó´ :µšÌx»Ž—ÅTƒ[ =¬mh¾)…§Ê™ŒG;“½#÷¶°Ûh¡ÆA;µmó±ûìÒžeÇGÍqSEµ, k²u\®Ñ÷§PêÜì«‘K$zÿÕ‚ÿ­°“þ¬jƒñß¶h‰á•„—ûm0R©lø¥Žì±;ÏÓ[¡ÇÀÞì âãáŒ=% ¾4lž­ƒ{ù\¬…Hn,ÑøI>_ÌÛT§ò ¨ól€m´Ø< ì”R®9N(·p†ì¬¢7ÀÔ ²L<Æo^„La¹?ÕUIÄ^\I6 ®aw`¬¥Ù»gSÑ7‹ËËyZÈQ’îûs‘å'CSq°VîG£(ø”½hsJ`ÖÚ‡ ëÇû§&ï;Ïl–îùÁVêO<¥ƒ²¬ÇÉÆâeË®KL Ëa«lŒ¬·a£ð"/˜+Èåu¨×2©ö¸Rz{¥ñ>•‡Ú»UelkÄR-»ÅÝ]ÛY%*E¼õ“¢]sW1kM²¬@=7-ãÚ»Àtÿ·$VDC}Ùœ¢2C‰Ó…8hõX®ªäÙJÿ–G×}¶È Š¥(ÄÒ¨›îMhhƒ•8ïH£‹àX‡öx›;Ù´3<:y.IüI𜫠8gY¬—@,Á-P¿Pô$÷Т5uaâg©É,2a(© Rt<ÈÏfÿmŒsê¦Q¨ÇúÒù¤"¨3[mJ kyÌt~{ú!Êùú-u-Eß4ö•¯òx8ãÈÊÖI=£Q‚ ¸Õá$i¶ã’ÇÁHl™¨i¤­#ÈŠ´òõëç^&?§/2ÚBG~„kèhè8†z³~ç‘êÇ7èÓY™˜qÙ- #ýZƒ‹öùå‚÷…c:_‘[ýVœJר«æf}€óñ_Íî ŠÓT ù83´¡ËC¯Ð6e—5&×7™|ì€uGk[¨gÙôJ]Äpš[_ÅÙ 3A˜­êNW¬K!Šœ»¹Ã8ÕÄ­“2<{x°í\™Ìœ@;ùNÓ7ø5¼¾rceu•JÜ TEòÿ¡„ÁÂ{2m}a`Γñâ½i$±x~ ™N¢pBÚ³‰@DzŸ”?tPu*¶kÆÓ”µÈñ틦C»£!¬õÐQ¹±¸Á‰å'j9ô FJo?o†¹Ü^OǦ’]¥S K¤HE;‘¡”Þ:¼Ä®² 6‹/1&¸óˆ§â«ˆ-¨ô5¶’v MŽ8¥±7DìBèðrE µQÌ2RnXWÚ¨µÈÒg‹9(fÉÛ´g_{vØð0àþÊ]:çu/»Žöû,§ˆê]'‡,ñÖlbžâÅ>UmMÈ@v»ÌèíŠÝji'.|™ƒ°'ºËf\”„]|¨‰ÖR¡ŒåE/ñ† ±¼ÇëO#‹Ú½è|ôñºÐõâkðagÝZ¤Ã©¯ÎÆîÃ>×\·–÷%:àšëÖbÄü ÂÁºµ1Îp¸n-BLŽÖ­Åˆ%ضÒ~aÝZGá(¬=^ÂZ£ukv‚Ïãµk‚ÏkóÆh|^›7F»Áçµyc´|^›7äHÇLf˜æRéÑ£^¢éèÔc<\w£UÌíñÄÉ+H\ÇZÞŒUçብíìs%Ôª—›P‘¨"Ýêïë'a@&H œ,°í~ÂÎN¼çØ»»"Ó½S téš§?ÐÕÅBSh¸·AìC§Å–I‹›…ò‰_[T™õ~•òFÕy–šE%‘>†¡ÓÓ™ŽÒOôR ë"hqÒ » PRó„ ;0¼FD!±.±]¢œæ r5õΑ¿B¬ñNüyv•Íaã³xqYב$½âe¿Vs2Ðí»ËÐymz󙄱Dˆreg íÉy Gû¸(îbxqbwHÿ`oiæþ.)ìgÙ%9HåÄOèKGܯtX×õe{P[|…òÛo¨1!©¦žViaã+ɨfi5˳ cjÜ4­2 £ê†t_”Ô×·y6S§ÒÈUÞ+GŠŽS´ÒZ€¥ø¦¡þð}/å1.ÒÇô±¨¹]›"0•ZðùÖ nY•jÿ oE¡ALí-(%ñng™†è¶ÒLŸ \ZñƹÆÇ¢ÒqÔG~Ïö¡Ù–Õ “lÕÔ >ug0 În˜ Þ£>É`æÄáo±i¥=!ÏE&£<ð½Ä&ʃ˜r\”nu®Qì-‰;m¦¥ êÕî[™€ P [;^–3wἦ½½ÓŠe2©èM:S¾ÔøÁ,(»$[ŸàÅ~KÜo&‘æ)¸.%~›0*jöœÏ¾á‘‹ÊÆØûm\X¸.=ÖüùÂñ4Ü[7a¾Ûy U² "€¶™;J%‡2h÷Ìe¦ê}x ^€¾eïb×Ä›•~|¤1ûrç6ŒöY·~ÆÍb¡A¥ ôš•ˆG¨ Ü-§쮋.šIÏz©ûý`b½Q~\Yí•N5ø³âµ[!I Y'Aåbä8BÌ[€¿–DY{*P´änȉõŠL,"ˆ¤G;˽+)hå¤2ügŒ?»,-4ˆVfÂÝ(@@:­d$ÁÊ( +*=OrOLmè×|ªC„êÀý{U™"¯ûm,yzø^(¥§»éÃÈ? åù¦çºâÞChÄõ5—Ô[šÜ+ ®žg“ #¿üöùó¡\æ’*]t§rˆ×ñWn°l(ñ–̧;ô~Óó‹s9ò¢Ù´—j¹u+ðC*ŠNàoñ ÑÒšh†iaöÀO RadM„mú~=£‡ºµàµö÷¹ýr—´—QëeûÃÕ¥±Ý–ÿ··¼­CÚµî¯ÛV íÐðÇMã¶&¿ßé'j(bk>e{õæÍÉó'oɦo¯ÌùØzàw1ZKvu_” K½æÖW=[t¢wí…ó!c‚»’Dîùh'Ò¸í¹E×MÏu<ñšbÂE…š²æE=:Œdr—”¡K»ïû6J»7ï!4=Ä0k:+Em7¼6`rè žâÒžBDgQltÕ’åe¬aÆôj &Ç 8žèR®èàôõu@n‰ôN¾ú*Ù¥\%ß·ûFUÇcT%¿çr¬¯Z?i®ZaöuÄåhé…YÙß/ëÅe¹¢(Æ>.ÊJm…žÀxþ~éãû¡ÿô¥È÷o]‰@›ldûqH.š~¢ ùÅô¥ê1ØÈ¤r ß9¨ì)r³fO~9K£ÞÂÛ«eÁ ñßÁ¨1r„íú›×½’m¬½§Ï†ÍÁâ©ïºÖäw;,iŠØ"’qsj·DíÒ{$“U^Ê$ºWtYK5¶Éiˆ¶«éAüén(bÿXö³Ìå³ðÍ=µ¹Ë©€æ:tW©2óʰ§ëånܦ(¯|ºheuqòNí^ˆ`¸såEæa–floßL³»«eF÷غ`û¶Tã wÉ XŬ²Vn¢¹™š|vº|[w­0ûK!d䨀™ì‹kˈuŒ”¢¥õ›22f‹‰’lëÐõ}&úôÆÐÞ Ë ‹ h¦öy)\!Ó©J…¥DsÅ”½ŠX‘²©Ë…4èv¯n`V`ÛÆ›mϸê/ª¦Ó4ÉÓ+ÌV7cÜNiq LÝ‘Œ¸£ïŽä3U¦Û¶d%“6S!HRÞßjÃPe.ä7–„ô`V¦S¸ MtIœ3Õ±q/ÊL” “ð´z·rWp+ÏÀZÙ Geˆluëb’›²úÑH!e_õ•°Që$*.Uâ¡a~驪DÜ… ˆÈ›ÇÔ¤Îåæ¶¬¦ÕØÙStô §ÒIàñ¯†s*'ü!¬|#qL}ÃâïBYžÞé<Ÿ$•OðMyÃÜß'"çb¸b™œU9·i3°Ñ·’jQX$ÓˆîÐàj8w ¡¸B»µæP‚'”G¶·‘kN)ƒÈ±’ E#ñ+Ac0i«]¬×ì56”ݾ¨‰‹Áy!žÝz\ÁYƒ±•éE>eE'œ#Mà-lå½'M•Ù3ܱĉ”iDi–ˆ%OD*M@3 ŠCü¡¡È¨¾ãLD°QÚú`¨×¬ÃðĨ¬õC:dPIˆÁÅ@ÝÆžëQõ9â*²˜±ŠIXáxêSað`ÙÁ”‹W˰Ñ^<ý¬><B%³+ª¬XZt’ìQqÝæ©®"7ð]£:Õ“cµ°*=XçŸV3haWŽ´#ºùÕï•?Ð÷~B¢ŽšÆC—…ºÃÒLaëv.¯ c'\·Ÿg×Ɉì qù†'*Zf´Ž(Óć'ØF±}QïLí ½uá‰îìŽâñß%‹¶ö,µâä{ »ÜùpÒÚḧΧuø Ýa .]Þ‘N÷c¼ìÙ;½“‰úÌÆ9\‹&ãÑÞáÞÑîÁ^D×}눴”:¼©iSÇbÌ~v8ê ŽvÁ’hg™,BD-ȵèƒ' ›%…m„?Ç(jŠ”xÃÉ×2×aí¿´.ºEÍ4û…Í›,ª0¡v¹ÿ`„{¥¥Û'uÙ9ÚM>I"uÓQ”ÖLÎTCÚ;Ðû€Ì2aÂx&Ì3Ë%UØ=Vy¥‹¦ƒÇŠê½Xm¹]7È©›[J«ÄÎZ´± øÏ¡…³ZîÄ´Ùé¤ÎÞ½´ÙßC§UÒGÅÎJ"Å‚¶ÿD²€@«Uâ§M¤_ŽPMGH $‚L¢ç^ˆ!5»…Ï'RÓjqÞ )ö\2_%.ÃoZ¨·¹ÝzŽ˜¸·òG® t@ÀQJ\ÉKAÿÒYn¨Ç7¨ Ÿ@hÀ$»-4¡³NIµ–÷í**•ƒ–CO ‰þíâ&ÜÉ5êrnÍ–>ŸØA3Ûλ£J%Pë±&te<Ý¥bë”8š¬6“?¼9#s4‰øýÿ2ýWœÉ±2Ÿ~c0Gè¢-FÏÁ¸-sG[£[Íû+éÕ°S‚/;„/UTMÂAH¸æ2øÍ‘¹‰Š0ïçXQ÷aÖæfïæF(X`ÒÍrZ/6¸ísö1aÆ^P£_èä-¹¤ ½èF°A–1FîÊDy­Ñe¼EFƒäÑ&œ†»¤˜“\ö|£™w^C Ó&Ý{‘¥3P*¿¥-Ôw1¯icviQ"‘m­¶d/é/ïITåUM–eéü36ÊyÛJG¹±€éÀûâsÙ’sC´̲–$ÀÑï ÆÅRµ…6Ð%ÏÁ¦ÌRHü‚Àè ¥~Q.Z]iƒ˜e·€€ÏàyvËd%Ò¤³;ƒÝ’ÖÀE]©¤_¥^;`â’Añ1 }"€^»oñ,†Óý£I8Cw¡íy6@+‡·žqër:'º1@È0«´×'rþĉÞ׸wîÜwãå˜^ZÓ¯Ò”D\Ë*Èd§[ë˜+›¨}Å,2Ù€ÖÞŒˆ—Þ ÅÓ*7 GaËègŒXZŽž‹{2µ½'ÆE†\äÎ ƒB¡]%÷H¿8A™ð—úÝvÏFÕ”•£‡î[ÿàóÁ7ËòSÐÖoMѨRv£YQ9¯ýPÀ|Ç,¢M4”˜^•0$dXK˜§r½íuŒŒú»'o^ž¾ü:ùtŸ–|Ëž=iJAS^Ö7´0b$ç<£× oFfå‹h[úrrqžÖåìüfRÔ¬ÁÉS%c³B¤–ûøYZ¸Ý=RP“œ¹·˜0wVKÀMK‚4i0vòÊä$qãÖÅ&¥‡h¼ ­€•¼»i awŠ2RÂê–—íjß!føý’Æù=÷‚ú`ãê„V&]ïžÊ\‚ß&B2?æ×çdÛ¯3Þ…/ƒÇ¥-MlÉžåÜL®Š¶ÎW#Ýœ™ïu5zšæÕÜ-/ªÐÞ¡F@­¢ÃO/W7­—Œ-Äö –×YA\LSµ ƒÞi†>ìàd\¼0Q0XwcFÇ‘C}È‚XL±]hrË_m–Á*Ò»†<™×:;Úl–4ªTtwæ“Óqy‹§{ýd÷øütÌl&ŸhG`3éu6~;5çù˜Z_9…¨”¦ç°µâ–ɦú_¼eìnÅ+ƒÑí¸žÛ½F›“»~|a˨󂴙ÄÚ[FûèÏþvÈAl˜a Œ3Д•X[Sòý\4‹ÞB{ÈçPÎDA%¿ÏU;C+~87Ùìc» ¿mänb-: °`åßfãIV,Ü©5˜,«®?T}ìÚ~J‘Âqü…(#¥~AU·XQO|‚5ªX¾W4zvy^câ$bC±‹ÚQP Ÿ‹z‘}©¼Ì¤Ÿ.&Y[þ‰‘Vaä…[l9/ƒÄšÓÁºcÁ$›Í†OaÀ¨&¹Á¢ÇO­*k4QD5Õ¶ÁÑý÷ótj&‡ùoïœ †{·ükH8ñì×r¤òs‰.±#%ìÓ l‰ç»;‡ã[þÅ¥‡>B½N0ǵ4‡¸瑬’…N›0µHy~µXËU¦úoMÐÝîMAÆâ!6ÁÑãmgÇ ±aQ=BÓT‡ñƒÞÇ2%žtÎTÌf¥ÖÐÂÂ7‘l±%i»«z}[ß_[l ¶ºÚZ)ãéÓ“³ƒSÞòÖ)Õ²¯é(,yýüäÉÙIòæäÉñ ‚ÇÃXuõz¦õ?ÉueíÙªÚÏ—Õæ)†åCøŽøá£9®ÒËš;øÅ)¤˜TZ."Ô\Œ¨J@bÈ«x4´2›Ð]*uØQ8m@Têp\·´ŠÜìz^^õ›z¶àíŽÜ—Àõ/$qêÆFá$k°˜8wÇ“Æ*†ù×±¼éú%óY%žëº0ËAZ²"órÌ ™¸ê“È,.…©øel±µÊ¤D]F‡Ž<8²×ÖlŠ|"æ,ň/üÈ™'¨gêÔ¥ÔæÇ%SÚ .„:ýânA.|‰¶lí¹6®s]º é™ÊÒhSÍó÷rË:Ü8t¼*Ë©ç‰òRÓ”cûÑ2ÍhfA‹×ÛÒã3šÖð<-†£zneן¼Xv°ZçÙ–¬nrrJvíNA~îÓC·Ö9$txªƒCGvÑ¡Àð >ø°5šg‚²úñ’ 芄­iÃí[6ŒD ¿]Í*ºäÇÍù:üónó&äzaµµ÷÷(]Uéêeb?yÇö>yhu’ÿ÷úìÔÞÿ4y—Öbýþ§wÅ»²ÈÞÿ¿÷«ªÏ©ú‡w0A¾ÿ‰jXs$U[§õ)UŸ¾kŽÔ†a‡*¯‡|FÕ/Þ¥&;Ø{ÿÓßß-JšqNK*'UïZ^]×ÞqÒ:î/uCRoâ[ùnRó_%B«õ jýò]Y‘ ŠhwÁDäkö=ówÁƒhFyðÓ`N.zI'ÛõcÈ,*\1*e§Ü:Rœ 5ˆç8tÉ™Û@Ë!›M^nª±ÝôúºªäÓÓ@naû"ðôY:î)=×®ÚR‰”¢ÿ ŒÍ߬Þ"q \trÊEÙ.DÝÇE'긒›¸ã!v¹ñžÀuiûÀ½œDWäÎm´ø-XMúšû„áÓGW– Šl39qRQ¾·³ÎÓ*±x<™<¦O ô™ôÚ€öZºIkë%9¢U#ð’]ª ÷ÿûÉ›gOÉ×eoŸ^ÐíZ±µŒùʶHÚ¼ˆœá]¨V+#c<âÖ’«ˆ“¹×™wß½¡{0DUS£õÑîxÔOžÐ â·?ÆÖµÇÖácní,#s™\:-&Ä<¨’°Ž,ª>q×uzï9¹OôdÎY²X2g‰2Çجßb²~b¥G?ÌâÛ·L2©;†ò±åÙmÏS¸Ü‡5N@i>=4ÖËÙ]”ªTl»ˆÁ¹|¬€žö©c9¢eþñŒÞcô{xïFË"‰C¬ÂÐß/!¹Î…ŒÚm}þÑîs¿bNˆ„)Ö^¸¶ ‹»—Y”×~a&ömøO“lþ~“ëYŠëæïä¹âÇ3Zo&¨;0¡ã£Ê =?ACþ®ìæl:»±Ñ[ ‘ï’³î°ÐQµHÐå€;í4Ü¢M'|Æ8-:M D[óTj ¼C9XFUšóã‘€RBÅ?Y§Pyyqoí¶Bò}¤­Ž<@i+#ÐEÚªÈ4‘¿n|†ÒVC …4+ë « r!*H—’„lÑ©¨’xÝC·tN½€V¡r{A—ÖÎU5¯—+R½­L$!7v)?—.ñs¨Ÿ¦I*ñ@MBkk¤N|®6ñs(Õ%H™øl]âÓU‰‡i¤J¬¡I´U>”ú¬VZB{%¿w!ö·ñQ‚ËîiÄlœVW ëm.oeÂÃÀ ÜUÀñH]¬@6kaîsYfm.”ù}ˆlʱP·X6¨‹Vßá&þ—ˆ;á"¨MeÒÁ(¢¹@‘Ιh]'>® IÐܹÀñy äÆR_äšÚôù%ùLÍóÂÜrHF‚Ð( ±•¼pÍ ‚îÅ”^ûGEz¼r“Šð°µ÷Aëv³êµïý½•›U§:ôL¸÷ëWyuûÓÝO·_Ý=´¯ÿ ÉÀsfr¯Å¥YÕ“÷k&Õ¸oÍÄ 2Á¶¹HÌü£(®²'áXÉ/¥áôRÛ°«éVR±Æ¶P- õôáÄv%¾ÆS•:‡M½ˆÂÔÚ`o1¸/ÈB0HÅê»ÜÏE—kØBÿïU#I=ËRŸ… ý46=qÞ'¾€ôbÖ,g 埋ÉT—9¤Ǻ†X‡Ùçê  Õ6دü%HQè=ËWŽNØc4›Cƒ•ɉÇ«h7:ÇØùlŽç«0¡„Öàˆ#Ïk—è? –‰GBŠs›±È? 9^þ š=&J#œÌ!lqr1qeâ¢nŠ’m}ˬœî5ýnì‘̹ä³veD"5úïÉ “õGÏGÞ[x"²žx¡ÕµMÎË‚iû6ŒHæ¾ßÌÓŒ+œþ#FrFÕÚ¨dÇÚ†´`¯=6ØÂkOÄ¢}Ñ›I»¨vdU¡"ÁÅV{ª/¥C#HyJR Æ:-KýÏ+¾§2‘`¨þ±)¡Nq€Éª4žšœ"»rÏ|JÔZgȽÊÉÝûÅ=¸±¶¡¾·}í ù~ÿ…“%NI¤®r*Ñ?Ù=)ÀmÖf—w.=4eÖü¨“š PÑNsðPKšÅ6µ+Ìá¼dpycbf.wä}{WG¶ïßãµü*ò8‘@Æ€Ç1CÂÃæƒàäf–Ò’ZÐc¡æt·Œ5>ÜÏ~{ïztuµ˜øž{ÖÕx‚ÔUµßµk×®G?V‡ã›¸«ivEÜWèˆ?ªA2ŒÕÃÕë4/T:PÅe’+üË‹hÔ2Sï&).U/íÇ*K‡C4OFÔjk4AƒÑ…*RÕO¥ÖÏ?«Þe”E½"ÎÔu–v£îp¢ò븗 ’Õ9!ÿÔée¬nR ÛÛÿ_¯wU4šÜ\ÆY 4L€÷ÆWñ¨Àƒ~ÒI9Qz*ÊâHIå«ÿw¨—¤#á"Õ(ŽûqÅa»žôºõ‹KTì¨f¢Û¿ì “®Âÿ³(›è&Ûéõ$K.. ÕÜn©õÕÕo•ú÷t— áw.¡jôÙ=9Þk«—YY{¶º¦ÔÛ“-sýî0-DqL“8Ÿ&wÆ•›úxœmÌ+µºŽr4dé•锥™fÖA´Tü±_Ö4Ð ¬E××Ú`<ê䊴˜\Çù C0=|pfKoåù»µÕë¢=¿Ž®ã¬]ܤyÒÛ ))†ñutŸв"é ã[n<Îñ´÷Ÿ.€ó2éå·ê1ú‡t½ë¤WŒ³8÷k‚ô<ùW|«Pó4› zI*>;`wÛÑxX¨«(»HF¸“Ée?»õ¿ëH®ûƒ«v7MߣÝû|³ÈÆq»‹â,¸Ç£ñU’ëKñêô±•HX›EÚ;ÿt‰o¶Q|ÓK¯® ãOg¢ìöÝÚù§3Ð[tò7|z´v{KB¸„²ÃDÍ$‚'ÌIIT«‰†•AQÕ)P®1ä\ͳ²²¢¸VL#ý¬€¸êB)€ ð޽ËMYӨء‰OÆ\Dÿ¢Òæ§µ•o{W·uõ!F \‰æ©‘1AÈÃøÓeÑàÃ)}x@¤^œÁ±]`è|‚Îò‘Œê ãÁU|™ÞüDX8Ú*nûïgYì‰÷2ºäVU,gô¬›—¶ÒÂ)•«3`ÔE+g ÒPŸnó^A’ÇÜÓJHJ(dÜü„ŸôØAÖª™Ë»ƒÝöñʶ_|Ô>ÞEñ0ø¥ƒ4-Þm“%¤ýhâ=60 ? Ï+4ÿ}E½YÑ£úmÀ+ÕÌÆÃø&é—·ŸVWž_£–цt/hôL­›ônËZ}ƒ Jj SkËbïXí› \ìöìLm-¨¡Ñõ²OL a4IG1Â$ŠÑrHž½N:Ò#k[]ãöÖO¿"0}8¡O'E”Ñ »÷ÔÚz›cž6Æ• ¢§ƒg°é ïcf…Eݼ –°…4ÐAÛ)ú¼>õ.3Ht¢^2LŠ$Îul“‡ìÎ/ÇUt…‘¨àøDE0 nL¸àqÈûÇÂù&ýᄼ;E’ûo·qìØ¢ÉÄ0B¾á/ÁÙÎ&n‡Ã”]ö¤…1#y’œZøbEf°sO¸QŽÿcThüÌǽK&®MT§/œ\±ºšdœ !;" ÝjtŒ-þx=LpC l©žQ)–øbȭ׋sVœ<…:âHâ±SŒ}$¨ Ìm½¹¹YéšjO®‡ãüIžŽòt‚§& } û{Ú‚ݯé‘6XáŽÉXqã‚c>ù}ÿ%œB³„6¿I.VÒì¢õðÚJrMYÜTl]A¦'ê"$8Ì3XBYÝJ/£!(уDî}Æk-}ÚG¸üÆ!R%/˜£Õσ)µ®¢^–ºjW~µÓKòç2%º-Pð üx@_aÃÅY'¹ƒ¬Üý„mqh“4!¯IŒiG“§>¿7l^&PìR¯Å-õw‰ëâ\FK!?â¨w)ÆF=ÆÆFlÙi*†Øð7ñqÑÀxÔ·T—y„$ÐwûcþÁ%§;RÍeÛjÁ8æ„ôu°FvŽ>0ÇmHusïê‘9-ÛËËdõÓ«+Àâ(x„()T¬i‡Ü­¾O ô8ËPK M¨y?zn«¦XjK¢L83€ã?DÂÃyZgÌ7ì1ò$Ó=v€r@Uðôêº 8äñü?ÇIï=Y1a£/w‚Š~ûvˆ8ŠÏÆ#®¤õ@AAñ¸ˆÒLÒª&…áž*Ðð;†Qj9Ä$E¥c”÷1ÍwHÚdl±1DÖ™ŒŒÄìHÛŠò âá;@[ý°qÃË%Ùh¸ê8Ç”uØëþå:”è“×OYM’!d R$–HMéÖâ¿ÉÐÓYЧ®Oš>ÂÚÉ(æ< ÅjE hÖžvÿ‰>Љ-µã „J膟Py”‹³íÎ:4=ÆgÄfpÞSò*4¿$“{YJà+XÂÜl–®›¼U6è$>ö°}BÄ“`!0‹¡3"‘]#‹ÀV¡Ž¢¹!3&#ÐÃÃÛ¸X›øò„WI¡0®„¢ko|cu=| °!cÏ'°!*w9Šc‹$¨%eO$i†¤ûœ8 “µ±Ž†ÜT†ÓJ²øÌË“%š&ÚÆl¬iô-£`N‚hpņˆfIŠD0ÅD ƒÃ b¶”FéU LÇ9M00–ö¢!3DJ=‰‹¸-±]2³+Š:µÚžôˆ1çpÙ§³;NÐ)G¤*èAh'C¨uÌÅÈHp‚‡ì®GtDš¢Q-&™‰‹fŸ¢ÛWO£Ü z®–2èƒÆŸÕà<5_<„0TŸòLÆË Ù â»2Þ6K>µòoƒˆs>*‡óˆ‡×%KÊ5°ôC"~R¢‘Œ c“¥p¡YÕnK­íˆ\e\7hŠÂº Xô”Ëc;¹F2úߤBPz=†iÁ¢<ò:cp*IÆh”P9 â¾Vâ9žE:[‹GÌ’Ã6rÝ™àž³¸2Kâ‚íF2 £"IïCˆã¬s`FÝ?Á`ÏãÙU,šº6É 1P¤¥µ€Ä7Ž)æ†Ã6À1º³ç W‡~j+çH¼Ãû8¾&3¿*žñìÁ½›SÍCðL¦zP ¹%ñ.4Us1–cŸE´¢(S{cÖˆzP·ˆtHEak K¡I‰ ÎéPDbÇ9”žöpÑŠ0>/â•Q\´xŸ)îƒZ¼y²î]šì®Ð¯t© ÁMÈã>Éêz\à9o>c|Û‹> õL³"€'­’ý›±+‹)áÓ„¡ŸåùšÕ¶É´fùW_‘™Z[¿[x ¯>a&)•Í”4dä?µ` :žh)»%¤déíÀNu,¢t`ãt1f·üÎY4¸0ÞÁYõuÂÄBÑú¤µ¨÷<QÂ5Ä›éîg«1‡/åPRºB¯§šd¬”Xõ£~z#Óïñ(ùØb¥‰7¼‚C¿¬Ø˜úLùž¨MÄ ]n€&É@CÖàÍ™½©rùq£+AÙ³[QzìQÞxô¤’¤µe á%ó&ïát¹ºëA z4L£>%L,¢;ŠöXžÎ^9/jn…’4‘Ê1ƒ‚¯€¨cnDnlâBrvyÉ~QŠ¡Åwi²2b ·Wš=q¦ÄÜG¥åôÜ÷Žn²6IÿûŠHŽÚa1€Bî¾:)¥îÁ„ŒQ7…‰¤ ,hÀp²&8îÇ2Ö›ie“ÖÍ_ðºÐ]SÏÄ­^Q‡,‰Û—oÐÏ0.cLÿ\¨PøS‘Pçð«ü»'+X{2Y”³š—¼Œ;½‚¨OLJ¡QWò|m3—Eódt=¦Å,Ìhlçí%×4m…+Ö3I«‚.F£AneGM]A Y¯ìû¿2ëNᖖÙÔ¢‚ÏŒ].^õ™û]¸=Ö««Ú½Íec’›˜ó¤°<£C3î6z2]Iºý–e%käÉ#6 C‡÷â™IæœK’Fƒ8År7Æ7™ìEÒè*¦ Z’_™)ÕDBÎ6é׿­ñsWeš _"¬‹¢Á+Î2hÊxÑŽ̘˜³`H‰ñ“Ì †LêíîþÈâ]Yyª¿?åTOÃihzµNΫ¨­¥óª2%.z¼Âx …Ñænœã ¥DúùGæü–ˆÞ…õ¦æX;½„w>ˆÍP%£9Þ}}ôÛ®z½Ëƒ›U"E)×@) XŠí²óÅNžƒ]µ$©7ÜèÉc­½ÐNF-Só•S†¶ùÕ› m,Š¿oþ»s«¥+Ðw³¬s'l™MüþØë9xN;e‡dzŸÿªÑÚ°Mž=8ÐOoåÏß×0”iÌ[9ýѨ¥5j-=åš/e™p¤öDœê`T$ÓÞ0¥îõDõˆ|3 l½ÙW:¡I"œXOm~ÆšœÒEÛÐ<ƃÂÄ,L/(aíÀ(åÒƒCë™Zõ¤wcÊG½ÉÎdÊýÀÙ𒞡ι”•ãZ ƒæ®F BPË »µX$–¶\C[Viö³öw;12É…thvY<Œ’}ÿs,Á;Vù\æ“,®¡"æd$ᇛF´íBTü˜‘#ìQæú1ÏØ)œ0KH]²§ERÊ¥œz:Ò kšõØ0ÐäF¬çÌyI[QIÏÌLx./mÜ[6+–Îa ®Œ‰6ì©\›V#ec¨Þ1‘»fšgm‘%û*–™‚¦³b§vP‰òÒ²„w)!yê|›$Š4´ÒÌdIªþÉà7߀tÍ>U1ÌÅ´‹‹ÇÀ”ŒüWó?| ÷öÑáÉ)öžu·^ï2ŽŸw껊ìðìK®ÇIÖA‡ú4¢NÇðdH=»³xºûr÷XÑgõãêêÚ*Ãy;ÒÍÅ.óyÀò!ímâ¹´^iwwW †)O·Ÿðb@ ¤í­Ã£Ãýí­ é[´aɆ" 2K³iz³µýëé;ô±Bܯ€™ é—?Nw;G{{'»§ é{ôËæy4€R0pàfÒt¼»³¿}zt¬iúAÓDór WãÁ±C^ RÚU%‰?H‡©ÇÙ`]Ôq‡ÿM³í;òн¼9ØÚ?ì¼ÚÝÚÙ=>Ñ8W×DË9ºøÒš['ÛûûÀ49¼Þ½kHë’W@L…tòrØÙ¹{rj!=gH;æÊ(f¢ ,Í˧@2p,¤DB3@Ì„txô»íW3 %WWP¾¬QTdþj縳³»·õöàT5=±ý—Ç{«Üˆê¡ÄÔôgôÎÓȹ¬2ô †-'‰U«‰õL¬­ýk^oïû5Ö<=?‰9ЯÂcH³l”ÛÁTˆß=Üv#DùËþáÖñ®qh[>¨_¶Nv¿ƒ=ÕX©-ê?ÞTñÜ‚ú·G§»;OÞïÓfòƒ] tUk«e;µ ¤hqª¸þwª28PßÝ ÔåÀ’¢ÅAaû Ô׉B{w¢d±ÿUFó_e¡¶$À¬H6ÎÎoÍrˆ›%÷x©¸Ô“7N’ÙåÙ+™|› ¯^Ç-å.%ÕÔ㸇óqö P> lå<”Ë•ò¼€º0ÿåÝ€Ž ¼¶e—£’ã%Ï‹aÚE¨àb;³‰¡Íðâ¾9ëØyh4²Ïôþ%pá¶W@·,“ñt)Ü…Ô6ùhM¥[^ø€kêM4Š»µM·,¤÷µF}ÉßÛý#9~Òã½ ù*1[Kô~ w FûGZI=ˆÅ®Ñ`èvì`y­”]¶[ˆÜ^Á¨ß×AÛ`œéœ<'% "³E¬Rk²±L€ƒì ºX:–6é§h–'¤„„—cDÐZ+˜ä®n˜R>A&ÅF‘8›±þü\m gP>”Ë9ÚøpqÉ3³%w܃ûÔ‡4é“\:¸&=nmP‹©UZ~ç×h4½²vãqÞh7ô$š'÷ͼõ‚gôŠ“o_K(}tüÚÆÒªE5g€W„¡ò4€„jÆ­ƒƒ£mu_Œ”Ù,n¿|ûz÷ðôž5”ER\z ÊbJ¤q_„eA„§ÛGoï+R²HwwŽöv¶N·î…ÐB™mÛ8Ew/„ÊbÞìÞO¤Ê"¥ªÇˆÓï ,ˆðdw÷×û#$( "<Ý=8¸?B‚² Âß÷Oïo4e£ÙßG¢ôŽZ(óbùi]öžF£¡,b4H£#Ýóûý( Y»{û‡»;÷Bh¡ÌGH+z¯ßìÒ಻ó¹}(ã-ß‹]ðª£4ŽÉ"å¶èm”]¯¨ ¤ô¶0^âPòálu(Éç²+a˜Ûsñ“â­mù6mØñD£eöUc=å2²îcY}s/VVt 8-Õï§=‘N•¶H£0{]žVÃEûÒ Éq=vÜ3H/àÜ\Ýàgúñ=4›–>ÈX¢õŒ5;íò ˆ[…Ë=ŠíçVǯÇ,sõ²,ÀÙJÓ|€¤,34TM"ÈóRí]Åÿj~ÄRU³rlmÜ*VwƒÆ¶Ì£ÎÏ{×U÷ÏFv¹5µ ‘¥#‹®ÝBæoЀ¯ „FÊ(UAJ›eûxÔVgÓœg#‰¶µ–S[ˆ$Êè)@ÛæáØzêVK^ˆº½5Sæê´y'Õ«Ë5ÓfZßÈÍâÍG:«cv&gÅ ²¦ïH¥AßÂUzÇ©¹xííVN­ ÞRóɽ|¨ç»uñ± î¬÷.óÑy ˜@7z@2þ‘ýô’D"ä­Þ/Åð'Þ< ×LÆäÀ ¥wJcÇ·ÛªÔ9>hò2>Í&§°ð¥ÀÎrXÍÕu«íö=÷i!t‰ÐëRn/?IT3$>&—é¾pÖ‰>&ù ºÒÒ=í–"H³à±“«n:Ô›29ûóð)”cbל?·›+À¨xލ‹€½·Äe!sÙÇ4g'ä.‰€~é?Çt©šWÍ?ñùÙæ©§åŸ_‘¹¸˜Œ»Ï$gŸÉ&U»ñCÔ,«ogYDºž@8UËZIHwæPÍéõ®1ë65#3Ó¬~?½ÞtÇ <æä,Ÿäêø¨TNÞˆO œ6×›ŒÈužå0ÒèC:ü Å`ub—ä]~D¯:—œ!{׌ë6Ęeœàˆ›`–ŶH†F{¬ì—6ågä´#=cã"t¦@§#·•¶ Iìªà‡ôqN¤„º û¶a‹H¿zÃ5¯BÊ.o–¨Çr{¿Áî·zðH*ý“ _9©&¾ÂyI'nrƦÙp®¹‰¬ÑZ¡¬Wi¶òoæ.ÞDò¦Usw ¾êmM¼t);(Íæx« ƒÃ¡tüu³¡)ÞÃj@Úëy„㽕œŽ•ê«‚42:ŠE'/6WÀNÂê“C0u7wÆü]ømlòŸˆq-ì†W„®­¹ÒOpÞÉæ“5 ¦ºc¢}•½ñü7‹ã=ÿBˆ,®Ö“µl&Ëküžorá»äœŸŒˆJiB*]!Ñ5oŽNNÿx³Ûhý¸¹Ê´ƒ×M†Jú…”ü#uÄëíz‹ F|¤4)xåÙÓùä~2Ç5ˆÍVÆûn.'?UÛ©š†0`ÀmÃßc}h.²ê0pññ ìkf}^“âwvO¶÷ßœîšZNw0“e#º•ŒìèºÙZn¨†®*‹y›«æ§èC·X^;×$–p4Z››Oœ4=MU±/oÖâÃT›Á™fͳ¼i±¨äé뫌Ó}²( í5Çð¢tÎÉ%!ËŽ–VYÿ àWÈÑî µ}lšžÑ!~TkV«ÜòZNŸ­¨=wMÀ4S|„Ýéµ*W‰ ãNÕ3S+Ùt½C£ àØ ‰"¾éa}åãÇ2t §¹~68pÍõQajlômæÚêèF5eW‡®X1Ð.„úÞî7áP.ÄvV´MÀ¢ÊÊuÚXÞ$‡Ç%Zøóø…g-®ñ»'kç›  b8Ρ.oŠÎ†šk¥ÜÀ¡˜ `Ó~%»^žÌYˆ~ünõœ„ô?›ÿl±lÿI2:2Üü·Ö9TU‰ªË†ìÚ:89bÛBÕé5;úÃ5-+N–‡Ö«Ó9ußWt8Ölœ5m–ñ·ÍÇ8¼ÂË:6Ë=`̡뛉w9”‘YŽ §h"àm½{ýrÜGœM×Ö4i6H¢PØ®§âiÓz·6½Åàc3n $†MìøŽ±o¾³ ÛV|Âþö·G€/‘Ë{úFÛÖœ¢ÛB %¨2>¥1¿bÙó|j7*E€ ‘’ôþQ7 Ò3˜'ä"L”e,Ž,É8æPï%îä¨ßÏ?Êãê^4½‘IyÞ1›AÝfË÷v†\™Í=!º]‰!<]R¦Ÿ°ôJŒ~è Øj®5g§¬xMÕ¼im¯%:ÅoŽOíóÄlê®ØÓ¡›ÔD£Àì{FÓÕœæêª­Ùjô•Cx½ïBç#mÕ0<úªì¾lB}„ÕW ñEM?¢ ÞMoõÄÀÔ²>Š"ÁpªŸOq3`Ïüj‘Ó±¿ÚVáÊÃ!A:„/µÎA$— # ÇÊ“'È58d ˜O+"p=ÛI™ñ‚t-cÛ³\ôÊ3*üÓ3ÆpÓ­ƒöËúÛdêœBÚ„³íF›p\ŸM ë˜³ˆtµ*º‚/J¥îð3i4uʰ]Ó¿Œ>í<î Ž|Ì ÿ‚*<纓»Ý¸Á˜=zsŠà1ùç¹³e¡9±Ì‚¥«Ì„d-u©0Š–ß0º´†MLÈ iRaR¢QÊn Ç{¹ —!ÝÒ»zª7#èUeÍì¶•"5G&í}jÅeåH=Ýë…–öd¬†Jr\F@KúJ¦òÑì¹Ð« ä”±áîj¢1þü£µ*5qâƒøhóFô¶H¨d˜â 4ѾQä1NEÓ%ͳå{ñ”r唊>fòrõBÏn3ùÍÇí¨4äv›.U]Þ¤’åF \€¬Kmx,Ä ²åÑTá µýý*xêC¾@½¶Úæ b/;>¸ÀËAÒÑû½Ä#ƒ²Ü°š /þ–Sèq•*›ÅW˜Ï.ÎÜ€f–-2§êï¾Õ¸6×¾ó0U!ý²wt}ó}„¦5ÐßZÆ¥åQ#‡àJ6BÅÜÙÜÙ·‘ŽZ˜3"L›NI_’›pdÜV]¹d“aÿîKÞhæz#47‚›k*r<}#I]»öÒËúVGÔ¿¤7Y¦óöÐȯ¤(ÕЧ!&£¯¼5—²°×Ѭ<±—GH‡'´Rèµ4¹Î|%«LÔÎF¢$ê6›Î4¹,PZ¾¨™ûËœ?»(z@¨‹ãÛZÒu­–ëݦ2™×”i1”‡GÜ$Ê©D®mBY4—´~\{N\©ˆ’Æk/ÜÔ´ D£i-ˆ­å5õåФÿ.k²—©]¥¾ëoÕ;5ñ\U8¤ e±%õsŸP,ö\búò¦©Ç gÌ"][ÑÕªV±¡öƒˆRì#“r¦ÈßU¼´…뀺BjE=ªëŠ[&2SR¹`ÇìqÕ÷ÞŒ ºÕÝÒ¨uô_ÞU "ñÏ,ñÉ}tä‹ù™Ë®ª× ´Í^‚Ì%Ô/d­Lô¨“S/¥TÊ„cr-ýu:Mœ`´œxéç Ï·!>lÚ<Ñ÷@Ž9-I׊îD—V4½ŸÖÆR`bG§ GȲo?ܰÝ#àScRWûoÈ-\"Šç‡íFiþõ·*`Œ–O夶\ZÇ‹ÊO/ôÙFFfg£§K‚Q­ýî7…^yjQ2üÈÌé Í0w ™$€‰l[WaééÙ(Ð •.oÒRuMç~9œëÅlÕéÉeDÓ’'\6sÁ^UZ.-I»ÊçÅ#£éröÜh@ë¹ÓÕfqRFˆ¢NLSâÄwçíw ‰:wÖR2”z™?~¬±=~üél„’Ãt w"“J5Ž)‚6Ÿj£›©¥Œp̨VÙŽMh¾Î4a½¹8´ hSÅÙèñmÕ#ÊÇ‘üÝ}•|®7™f£ñT­æ¦3QÏBiÞ#Ê:„– Â5M¼| ú§·Å¦fÙ†ˆâÑ¢ëyØ«èCpð +R—¹y'^@;‡sµ\ÓïÍԫ¹òU|¥™íUG-ðõŠçª9nÙû•Ë× º»yb½¾®ï « B kôþ­‘QÝý”táŽ?:S>W\y©Y®~‹´}E¹¹vÓ¿$’¯¡œÈè,}hýRà÷p¸B_¯.÷fúx21#s5‡6tÈ æ‰Í¸ùó?\¿û&Òx;¤ºÒEUoLm4ä >î­‘½~£ÔÞ:L‘¬1ÍLÎ'7I3ºb”šwL¸DÄÆ”çZa1ýÚ0woЮA˜*©§;L{ïéâè`—žÞ…¹³+ËÙä9‰]º5ÿáÚlçï m Ûúıٵ¸ôÔT<Ø?üU×qpŇüpŽNƒŠÇ¸È¿Z‘v¬ÿ‚ã¿–Qïàâæ©Tñdë·Ý½cœá.W<è ¥ŠÛ[8Š}tü‡©§=ãìuоP®xtðöõa…Æm\þ{524¢÷•Ȳ÷@ï¶¼4ºV‰\pwó1$wQ[ Z[ˆ’E F»àÃêXñ‘\L@—ëD¸¿¾ƒï(¹Uu¦â‡¥jÉ=šSÓV² “oA µÆ[oQÆ—ùõÃæôʉ²pØÓEùŽ5{þߺᵆ)œbpÛ®kqM¿²#¹f| ïÔ=uÝæ×ò·ÕÚ¨8âÊ­2týï:ˆ®Ø57½PJ·ÏÒ*aÐwò„q8?¾Ýp·µ„²qmíŠ90+æ;ÇêËÿ?G꟨?ÂØ÷ÜBׯDÞlå äò”Ó¥à]¸ÐñvÅZ%øN³ 0yu<^•û‹lâ²vjhÒôÀM ÚÜ*‡ú |ý­ñ‚x§ËSº¼ÀëÆV"\¬k´ËŠa+ )˜6³y¡7oIª“¸•õEU—3'ó'&D5êü €iz4Õÿ¶ØÃ¹Ü-¦®Èæn§¸‘³݉üÍ"}ñn42×ÝÙÈn׬ÔüDÂ#nʯf2eÔtxšÙ5àVI}~)æU% ÚÚ:b+/ÎwL&Qóy8•0«ª/í/ õ>uj^Vsf+æýf¿Æ>eªù® ‡ÒãÕ&¿Ñ ‰m4­@Zº¸J&³_pñtù ÜôfêmjmÊÝâï”î´. *ÝîüãhVÍÌTZTR‹´X’M…åU©5±®RªáKe4¸jÇw¢X"B˜îÈç9W`AÜu‚mŒö¯Öágä{æ*Áh`!Ï[Uó°pfzcýš+— [LÓ˜úZÚ¶Lff.^-,iƺþb:ã*΋‘Ü-eµ\©£»Yص貥±ÉIÌ@B9† G ʱÆÌíc'±¬o™†?ýô´'ÿ¬êîìν° qh­Ör_î⺫Uzž¡,üÿY®Á£|iªáL³éÿ¿5žsg?wWX÷eÑßÅ¥¡qµù\§6ÃØîàÔåËzµGæ®Ü»O÷bŒ|æLKoÚH‡£ôŠE¬ ÑíB*gèæ­ëSÑ…øÈäWíÝZ»§&l'». "½Mëøf±ú޶IðÜÌ{‰§Ýç÷ê0 ˜xeÔX¦ê¼;Þl¾p–>³©kkLm~‹Ï7ñ2¤Í|qK/û" ú¸³Þ ž¬}–hH y¨ië2sÏ7µ5ÌróViŒFÍàÚ`¹õŠ7¸ <Ÿ½;:ßEמ>‡›YËPnB¸R[õðMÏ/§–KÌ:7=`$‘ªÃ`žÍ^çrK]xÿ_ßjöGèS‘DN°ûXïÝ0w'Jö¼«+ýÀ/…¦æx·{«kì¶_<|àÇò¡Ó@ôÑÚð,.háW4e€KéÅö¸`ÝfúxM‹ÎtÛ-U}ï„%Tn®}à#”Á…¸ø]Ù¦rõ†ËpiK–½Âdä6œ´£ü¯¾x–_üá^ÈÝxñN\† ñn¿7x½ß'þQºý´ÍäjÉN‚+Úꇮé¥ÛmóCâûS0ó@Ä,Ý Wùé'æAôQ?¸­3i^¿0.`F½ægJà/’ÂgHB_F‰lÈ®èêŠ l+jÍ…¡ƒ›i>âÒ=ú¿&Dí’ˆ¾Ö8ûeο&Ô¾Êì9ÎÊ‹&žNÔ¦ðFëvö8x÷¯˜[ù˜òO²ì'£4ç/º“7•9ɸåšvcF‡’©ɼD$šÐ+–†e™Ÿ )xH¿¬¤ôo'¯j3C§©è$gž8ù5Î)üó<ö ÿ{Ü}«aÿt=ÔVû »çä}¹¾D¼ÌíH•ßÁTØÃt_Rÿïub÷KôÁm {ê`glšRó1¿ •×éô»žðëRó ¡ÇzîH†£Cïú¡ C蛲­kIoœ#¡ÞfxÍ¥¿¯•ÒU::QÞÀz÷†½q.p$N_3Z6ý@ !e:Ê&ëI²Þý†6lGû´Ç¨Æ†~Š§Þ¨é6Eë*–Ë%y™{,ìÐ5l®û£„Þ—ð›¡9à£hJ¯¥Ð­S÷»¾.ÑN¿úY,_Üøe˜¬iìÄùuYV_W†5œ 6S—f“©Ü¼b£k Fç’äÅ'ª²§¦Ì´b®å½ïc¡'m|Åv´7ÂrŸjóPhFT »Ö¦¨µÅ­õ”Œpvë’Ø<3a¹¦·4‰þ4‹¦½I•šº†¡¡U$í™"ŠuokYCõÝÜônª=]ó]ëD¯ƒ¨ó¶uXù‡%ÊÕ‡¬å-ܘjº÷[ëW' =wéÆÃÔ½Mo bC±{7Þ~åh§$—¾Ûßù#}±•~GÛ Œ8NNqÉúKq@»‡/O_Á>M!'Eä™°—¦Ê§†¥ÍiÎC`N7Åìò¥<ÊûÁxuÈ×’Ï£A\L´`R™“B¯)3pk¯Fø±µYsó»·S›¬_ÝÜ¥¬±VKxˆvö;¥GÔYœ’îI¹"á°o3umü)´Â^îŠ,Ÿ|s²ß§RZ¾”¸åÇå¾tô¬w*Œ-T5¸h4åGKI¯d†8昕WÂö»0´æ×v¸ù 5'¤á àkme¿¯ß*„aä^)r¤DSg4¦·± Èü´¸Ö,¶„aJº+±•yŒž=ü:rÅÌLÓv…Þ¯†þ³^a5@ƒR/vMr¹ü2½)½Ü‹]5ÇÜxÝYž³Š®ÜšNE–¤å†Óƒ¶¥ŸëµAèu‚Q^«ŠôÓ1Bgæ÷5Õ¾U~ë ç%]ÉêŸ>ÈzÍèn?ÛÆ#¤õi¶b!‹O_øsRý{÷V̱*§|Ç‚S~UñmzXFÛ˜ºŒò®±GocR%˜ççÊ·‹ÜÃiGz«_¿\}®‚P±ÕðôQâ^*¾µ…’+ZvãCEÍ\¼ ®Ûe•²7´þÞS+'k;t6Ãuu«SWèí#¢fëž%Èuÿ2[3gäTìe™N…ú݉yX™çâ®2EÏt¡{út‰7­ÚËù–ÉUs’AòúBWǹV ‘öÀ1T;ƒQ_áÿB t¥‚j:f7ËÝæ!SM¯|Ë{0ì»Å³é¾ÉiC­¦¦m‰ž"W§«'f"%$Æ™™EÊžDGšm<2‹ÅQzôJ5êÉ2Õ,)aÈA|u(‡A·r6^TìÏ+múÆç´à¦üâ>,^h±ñ(+S…ŒÞ+;â{/K¤^ò=;G4;¡2¹;Ùw_zZkŸw³™ìK›Œ'#å™ 4_ 9µ¶Ëõë^¯£i”Uµã9ƒ¿BUÿ3•U¯­°kIéYÆßj:)5\ j8Z‰•á[ÆO¾ %¿ý e‡¯–äÊ;Ë3-Æ ±if5i N k~å2ƒÒÂŽeÒ2äM¯mš¹C™» ÀnU]cè¶$šÚ*’Â/ÍWh¬Ñ‡ÝZ¼~Y+˜*(' ÊAq~ÛYA-§m¸¦ Ùãe%V+.ß ò«2“çFdeYyÚ÷›[3ÒÄrÙ qI‹PZe,¯Š *v¥íhÇHÉ>9œ!'‹ìøý¦U*†ýG ¨«.´‘©Ü´*$¿Øî ž!=G—ß Rfq(ð`Ï‘ÓA­ü4>ÛÅ %#rcæ¡S­wZgêçæ¬{!…fÖ˜©h‹Dwª ¹ÙÔ®0_›Õ.Q«HGÏ”#ê56Å);˜Ö1ÿÆUÚ¥§{\™ãÙzý<¯®¦q:Re¶R§rè Üš}Žb5Ó4[¦æ3tª¡W•ºÍ¥úicßQÎZÕÌoeeýMV~jôÆP\¬HäԺ˪¤—j¤5ÝÝÍ’dIvÖs©)U×ÑU„åA"õ<ù|3e°Mƒ âï‹ B êÕ &é×K%éÏ‘ˆ«7—"7naV…aÁ9I`(è¨xk<-;l[µ>Øba=ù_†f$bÏÙ3úZ/zé¼ñ’,pZǘïÙ9ïë~¬«[/]%¡YnWj67X‚¡ç^6åæsª-h…ÍŽ‡v‹ºxÔÉÓqÖ‹;UDÓúRzaHÅyæUa _¥[3_{ŽO·MCÂægèJDXG7åswâêH UR¥Ã&Ùöfªcoª:êWUú 2ü4]0ÒFƒÎG ·­ÊO'æ)Ík>[‹˜AjÞ•4ïDÃL¬ÖBðpÞ1E[&ìN4]‹½ÊçÆ[¼UÚ‚|Fl—vFä‘kmÇ‘ãVðU{v­ú¥ªi4R§ÄEe¡k‡:­Wi…Ñé•åQV°yÁÇH}÷¯‘»é®_ %µ`×¥ªmUþÕ‰ó¾ô?úUêyöÙÌåX½ |óF.ª§U 4RkÊî8ª`eîæÒòXÉ/ ¥jÌ™ºÑéNñd½ëùýY·¤Ïå84#Άá|Þ¯5KÂæ¼9¡^6lvCåŠ\|¸ÇÔ%i%ÖX/bårвêäªåÞ4 Þ¡5½ät«¤¶~áYÆ”ÝegÁ‚ûª´ú;f@†¡ÕÒXkŒÄ¬h g˜ Ïý4€õ¯µT/èü|ù.Y·ª péõâÞj­âý’н˜­Ø€Þð³ˆb/æ+Ýh¾fkæ^Ø,$oWœ›M™àâ.sRW_êïýh¢¿áÑ´…n{âc\”¢Ç<†nÍAzÍã¿Ò‘lqd9ËðŸ7ïOÓ]¨úB¦cÙ™ã˜Oáxc®4Ýš\Cè4ûq¨Ü¦uk6†1tóHÌWÂÅKºüKR™— 7• Á4?/Sxò@±N¯%µZ­ÎWjE§N¥ŽD0{›áí¹ûlÝ« å«Ï×~Û]k¾¾¸˜ˆÚU;v/x]pX¡ú·Êk¹1Ãoir‚&.Îô še<•˜a yh ô|~×vl—BozêƒgvM! ÁëDC*½éÿZ¯YHT ôÇò\‰-`Ç€¨ßXgž.?¹¦6«"hsDD’˜*$U·!€f¸QÞˆ§¬ûjf¹°,—ÒsG|E!J_ea‚°B¨Â˜"÷ˆ+I'q†pØÃ|žU=×SÌ`¦Cý—Uÿy,;¿ðÌÁx„×:o` kG0à „¬º¦ÞÉrƒY}Þ6wS Ç›í5 ÅÍ:÷6ÝñQ“Ìšj%Ž=˜e0ã!ÙaßõEPe…àÛµ©2µK³q/(»îó$Ðsåq‹_H<5.Ïuù_èöæ ª¶¢š)«iaš#œ++o€˜.«© Ëë™R®gÍŠg]L1'ht1c9dTí×gîës[ù[ûí»r³ïmÝEF ø(BCš‚"¾M„¥oëø¶®¼zϸÞ3*}ŽÒç\ï[|ûÖ¯÷×ûŽJ¿Gé÷\ï|ûAý%ªõ3ãÄ;‰ªä-¹;ÐøvµÒKEÞâþ½\ÁWÓaÜ=lFÿ¥—„•šZ5®_Sï8Âæz{ 5©x zT²ý°©ž¢Ùw?©RQžÍ*|.Khú9ì Ù]Y1}µ–é >-%úSzÙÁÔÁ-ä€ë{£XíTjÃtƒ7ŸJ´áÒrâ¥æg0@èM†›kú±¹(d„·ùÐÕ¹üvK}+£¹Aq4¾‰ùÍ»%öí=ºöµÜ†}ïuæ*¬·Èf „ù²Q¿ï;Ä ÍÕü¬äåÄ‚­ WÁá†`çä&ù­Þ𾫒ì|†Ä§J:”³{•º/i÷XÕÕ5½¾Z×~/V[ÕÖ<eiK¦KÓV!y:¹ÙÇUÉÝN}7ÞKÛ$¯¼Î‚Æ ó!Nè½®å·NEï5˜÷Þ9œæ Íþ[ëÚÔ!øv´‡è5DÃw}æ7Š€ÊI:ÎÍ+ BRðÛ¾ÒêtK/ƒ‹ûrÆ2 ®2å«Býׯ%öí±îå6ŽoÕ”Û/èÔéGõ1‹-÷J<ïxòß‹GÿóM rS¨»0Õ#6 ¿‹fPe/F¸_Å¿â'ßœ€¬w±”j˜Q­Zu=ƒª’O ·•TL9C6‘„{HÜ”Ošã@„ç7çÊx@o'—ýøî÷zå÷³ŠÈ=Tv:§„Ýþ-º]@û¿×½õt¿ìY[ݬ¿Z‘_f÷U¢fÐqæqÜ•x1<Ú…æªêUÃW R [–)UªH¶P‘kXéY1ní¾ ‡@‰›—ÛÞ“uzR®¤ÁÕ,Ð*ìuF.Ø­]ƒµvøl=¤¸Z)4HŸŽŠEê7¸ÿZî ›¹ÕÙ4‰¼ò¯uï׳E€ÜÕÙ\¡Å ‡AL¾jñ‹ŠNd¦…¥¥T–À̦N(æ{mgñéµ3¿Ji:75]ÏŠM7rö>kœWÁ[Ì®©{èw ½ ‡¼pÁn#þa­íÿ† ýºkp·P©fššŽmn¾ÁU¬mþ0IÔT<ìÜûËK¿¥[Ó ­ZÚþ,ŽÑ*Ö€sú3pƒ'Ïì¢Á-ýǾØ“þ»ß|æ 1gSßøëˆ ÊXL¦á}_K[ûRZ©NÔ(ä™_—^Å/»Œ¹ÌÞ‡‹NÍ“ddÓ=h‚SˆØÞËåˆÖŽF1ÅÊ2Á&G¤_Ã’àË‹[,þÛÞ§{½ÈÖ[àe¶x¬oeÙ>:ÄÅšo·OÕïû§¯à\ðšgšÕoîàõ͋ߔ¨ge‡o6øEÉØb¤ h†Œ{ãB¿Û9|å­ÏÂç½öÖ©âÞ¯¾u¤pÃÏCmõ…«!­ö=U¾ ñÀ½sá·`–à†¯ÂüÒïÁœûúËðM—•7}œí½Pn²ý¢á$<ýÃs_/ÆFU®C÷$„îr`]ª“Ö¬ÊBhªYm@e]ÛX$n~ii9I…-L‚Kã´Oϧ0ýyŽJõïè©*èšÀ…î\0軡¡â¬fK|oeiµL‡)Ô‹ÔчäC£æ»œóZ‡ÓKÓ Lb[t¦ëZ€‡²Àà à-|XUjHHóN#P=]ók-éÙô3ûµ”‹Þýñ§‚¤Lf™÷=0„ZT ŒNÿ§½ïonÛVÖþ¿3ý¨r;‘RY%Ûq’Q;Žã$ž7¿&vÚä¸ %Q6Iô+R±Ý3ç»ßgw‚$HJNÓsϹncKÀîb,‹°ÈJŠÅÌJK†ÒÔ¾«æF?ŽzïrC)tãÛi’ÐóÚùï½üD–/¼¹ùŠŸ5Å®]“áB:ÜHêFFRîÇp tÑåǺóej%°vB³ ‚g%Ä”VñŽÎ4X.ƒÉ]b™çcˆcAYNÈ«Ên®‹`ý ÂÚé›rªÒG9rBÆgåøho7 8ÒÜ0Ñ «»rß“Öãÿãž'͇ãwrþÇR~M¯ìGí/²æ½bË»h 'ŸÚ¼©–~uÝMzäq&7y]-W%ùêA®þwñ!i¤oãAÒÄþ÷út¾Ò{¤±ÿºïHú»Ô_bí÷¶¡g%sæ‹7˜Ên§Q e³¤¡ª×íöÔó%jtM“kü?'ùC[Ã^î³§T«)Ŭ-ïÕóSð,2TÀ‹K ¦Þ­ÀÎX½ ÇhZ€’â¿V xØÓ fh|>K<¾äcŒaBÛÑ’-€e8‚aòWaÀ† ²Á– õÅ yB‡PoÑÀ˜^R#Š6n˜N[Ø´ƒFq4C)³[< õYú‹D T¶£”¥šæ68{='Ä@Ј©˜ix±¢öÀ·F¸‹¡N½°ÅCÓ7šhÿ–-ÕðÝ­˜IÃW‘?yF¶n8~­­—§pʾŠÈõæÏîÍ~7Øñ=z,s.–a7™u0èPF zû(âw¬ä²dŸó——æÈp%‘¶e@j6Ìt/v‚+†ÿåjQB'E CO’Õö|‘ÀZÁ8ÛfõÎrzö&¸ÆN&œ(o¯¿¿£š¯~{§¼}ï‘×ÂòAª¯ F;=Õ¼‡rϡ콇$É{mÕ}ôØë=öú-Pzqx¨0YSN¿Ûëí©æÕý? `A·Tódur¤^Q÷´ÎHrOõŒ@‘!ÏÓØ þ‚þ “¸¡ ™H·ˆÅœ Ö>Îyè /~þùgmÂe}vrÂäá–Žê*™—‚vÀ(1õº7£ét:éíwU#^Ìi´+?¹¬ƒRÓ+d¡ð ×ÝoAè\!{ÜÛÿþ»Þ¾2?öÍß¹dø{ŽÅ¥µ¼y—ßj©¼"o©qÂj4¤¹ÿýj¡x2 nÂDΜßëªúšKíêjvǪ3ÁêúÓ0ÎKšý¡—R-Ô=0ZM+9 …årLÔƒ%Àvº»£éN;`ÆÛ{vè·rdtÃßÀÁèeQÊ®ÈXý—‡Îj¾»}+ž¯-Å¥ííõ¦cÝ!‚­r/åı†íá´»ÛÝ×ZÉ®—¬BêyFéñ:Ó~cAþKUÕo­>Õ%NS::j)oþBSM ]½<‰ÀböVpÂüt”«ÀdDFiz{£)uïh€NZï&/»æ½q8Òâ'˜tð±Ñ¯O^ Ÿ¿Àµ= æÛ¨o@Õ”¢X.¦Ç ýî§<Ü™îjI1Ï7 ¼þ^oßë>Ú£ñ˜kÞÇhØï¿Ã¯Ì(üAè·t{—µî4-æ`²kPvp…æƒ)rq)³$&¨œ¡t*–<ÌLV…fžC#37»€©´ YóqÒQoå†  É­Êž·lƒ)Íôè'à¤4![ÚC§ëU§}Ñ_´Â:ˆb$ca–ÝCªa–m| „˜uÑ\¨›ù*6&B8Ei]\,<Úþ’³®£åçŽ:ú‚¯H¶`æB u=`ïE‚bSUùD”NŬà—Râ2:Å#BïIÝû2^FÆ‹yêq·æÚÓ7g…VhÃöG<ó3·­L=,ºŠ?‡|TV£õì€C½r_&1 ŠãDW¥ëz²-jßIÔòþ{FàE À/i0Ùh€0ÉG/¥Úò>›¬ú…TŒÁ¼œ\‡K´YG8KZEä'J홨ʱªîÉ[ºöëmŠ{MwÞé åÑ,&U }l 7ÚpŒo‰…‹›­vC>5RbúùzK¬k©ý#€'‘’'-K7RzÓáÌ\§ý9d¿UŽ/›Cp|Ù^E¶™Æ]©y2×Óáç µÊÕÄê É$0³–‰4Yê+ä ’P@D¶Œ®ãA®”RÀ$àSŽFG3§ä›"î! K’>‹¢«'Ÿóí, >¤~04÷X„i/ç'ØbØDC%Éä*Fù½–,t»A ‚áúÛ-£tó²À¦õi£hdZB>’XüaÅ-š „ÛõÈmþa‹)o-·ž@Cƒÿ!é¦Ð϶P æ M­¸êVt[%d¤¨”Ãáç<¶¸¢)½%“I}›\U,A Ü `,œfië–Ñ—˜[ð8ÉöJáÇꙜsô‡m8¶ìæß‡§g(Ó#8//ƒ9kÆ•ÙX¼Õäâz‹›kåÔýÑ ý n£.Ãq)|9&¿Cö€®@Ü6‰°[ÝïµT)ö=õs‹’ÉåƒÙog ïÖŽFÿ*¨ƒ8ë>öºçíÉ™†E‹í}ßòÎËë10 /ÆhNÚÍ^¿ÛmÓ¯Zíž‹¤- ?¹‚9„ÙÓ.gþ¨C²:᜼(â |ǃ.þø7¯‹‚ê°Çé?£8ô®Mq?ÌÓOÑŠŸmWBÚ½l±Ùºdý/4µ¥›ö…Ô’Rœñ˜‰.3¿ú¤ªæÝ$˜5…5 ¦ßTÂé».‚ÜYÚ¬hjóY•Ÿí>]Þ¢JbÚ¡NÙ ßÀKÏe3æKØx12ÍõH~+ÓJ@öSXÀœ½^Èz$d•– l7‰¹²ÐÀAWUbG±OKcùqî¨7úÖÇΕt¦IŽ·˜ >ãÿ6V§ÔÇ3X‡dæ£sŸÌùplv±'&|I\ìó8sŽ‚™—>­PÉÄÄ&âá¬Ì~ÝqR\§ S‚t¡ÒQ'«%èRc;bL=<ÆÂ#¦þI4~ã9½Ð/í…6/r(ßœ z!ˆvÜ4™úzHn6vl+½kNY|¸ îÏÌ6Ý&Á0ZNÌ=›Ç…C(&€rúÿ¨`S÷-‘VíQû3ð¹ àö÷[5 ÒõÌ¿Æ]‘BKÝ‘·:ÎÄÙøµ\ 6KÕrPäww¶¼Gû»ÄQHg½8²áp€æ!=Õ=64©P2É­³óD6˜¤ÊÉÃîÍͪ‹äýF?a&¯lÕœÒÛÈG'ïŸ+ãÌHe˜$oºÎÅñ9ñ4Šñ“ðÉ¥±Œ:× íÁø¾¢¶À@… k´AKÄ»ËÿÃ¥ÿç-/sçäæÝžÏ¢0©ØIàk×HÍfÑ5an7OØ0ã|qêdýÃ<ýóDæ×õ•fÕ$ oG´ògqÄTÈ¡®t¥éX {Õ–ÑŒvÛPÑ–"” ºžXsÅ¡‘"rhVŒgG6¹¨xþ™ÞD5á`i•z/¨†`¼:Ö½b—ˆÓ‚öH)èR:¾k4âTæÁ„²I$½§ 2Œx©HGQi¼î‡ÔÐ°Š¯å~Ĩ‰ùåQe,TÛT1*Z£Ýû[KÞt_ô©”T͉ž–3&‡2u3)+è$²¥…mÁÖX¼wbr¹[‡ãa HÏTr=Šïˆ¿9í÷ ui„ÆÜo|Щ‘Ÿ&R\»†bÈqÒÛcÈ—ÚÄú—0~þI‚Ä-ÔÂô›¯Ì×)ƒ1—rµãò´ãrä¹üôrÜyÁÖɵ ýh• ó¨ëý™tÙ&ÎŒ$ÃôÀÆà19,b_|<~}¯Íà‘Ù¿†Väi£ÈÆl/ñVŸÑ†é1;’Ý8;-,Kl¿21ŠZ/ʪ„úZFV¤;»³Zw©P47f†›N|µÞlü¾hh…>“èR9ƒ$« hÆ+t\rO×ìL¼J¨Ÿ]rR’Yk>i´g9¿»]õ þã™B„*ü1.–:UøªÙê,õ‡§„:ãƒv\…s#²BnsBÝÓÆq[Â’'fÖ1~¯zEÞnH[Šc8¹FB’i¤³ÜQÇ”ð2€YEí_8ÇY¿Ô]¬°ÆÔ¥âLÌ·snÕ*<ü†ÉÊg„›TÈm4}3ýÚjm„Nã8š6y¨¶p„m§áâI½€Ioz7žq»ªÐÜïxóýLڽѦþva—~£ùÝå^ž‹W-Y2F -×¢,xçÜn’áDˆgøä‚äF‘·:0KóŽÒ»¡ðj¬w& ÿ6²¢ô¶á°Õç dZ2¤KÌ(#˜uc"ÓD»µRô\€3n˜65¬QŸ¼X"D+6ij#(G¾«=¦6Çø«Ÿžü¡<©Ár”j?¬½‚ÏM¯Û3;œBv0åÕ[³ß}ØKAdz(† WOgk:˜zÈ®j[ªíÔˆŽ·Í´\÷bSø8 Ï[j0¤†LSÖcל†ÎŒ’¶_~J mä qFii Zž.&&5ÊFzÆe÷Ì~k§4ÏõR‰ïÖþå“*Â1ѳ«‹qÖVhŠŸÈ Â)C:ÁÖb'· ÎЫƒeZJ’È‘©× p¬.ÀZF×`QmK“ Å (|¨˜–tvYÃÍ<žþcn;g7“îK\Õìíî)1 åêƒùÏ|ËÐ’RÆá¿ nMKßüŽý4õŠ‹9*;þ%¹TàˆLLÃõæ™Go=¨l]%WUóõë›Ôiîÿ-‡_Ðhä'–’› vH† —¤›)$;‹MHZ§ÁzzübxôæÙñÁT3J"¬úüöëãw'­'wìõêøôôÕQJíÙÑa›¼æÁ¬Ž+ö!fyRê?+i+ž?­”† ‘ï²bêˆÉÀ‰wD^rYâkhˆ4ë»u©$$>x_hnݱV±xd­ må'‡õš¦ß:–ø +Ü#$|R9°$õˆ¦²ÌÊ‚aCbž©_=Õ4ÊÛNo Þ†túkèô7¤³³†ÎΆtv¿½¿Bg¡Ý4LÃÊcâÏ´Ê%!Ð0kÈbêÇ S²Ä,¹@›+ d¨Ö‹1WVct¢%ºŽ³ Œ‰Ëjb¢pDGx\ClŒ¡ã†ÐïIU5GAr‹;Žbœ§|Ö‰6Þ븠ýL`…IlU,€@* NX'·©H­ÕÞV³ ±¦l™¶W ýaJ÷€±ømÕòEIi™,Ûs2ðG²‰>Ǻ‰ýØBÖ’CyÚ#Ê (.€‘£óùÁ«“£Z!bé@Õ‰·À@áÒ4„;vYàóÑ'‘þM–Ûm]pmKE°öÂEÁ`h-„-ÉÞtrÊ[½ýµöÀ3MôS¸áÃZö–že’2˰eS<ç±mŒ:¾»ˆ„¡V=Û¿D‡,Æ!­@ Tܾ HEl•Wî2J¢E<„í4Ž?YYml2Õ6‘SdÚUðCSý„yrÍD—Ú½`'–̼u$qˆœq¤¸eöÉÙ<¼ëþIe µ1þ_0û.ê«Ëžo|*Vù§[¦XÎɹ;sÌÎxbyœçå¼’|˜´#RfTð‘ÏG²¸„}Œ#0¹)öÄ 2hÍÈPÔìüÁÔQù“‰9¼áŽÝ»ÍÝŸú¬]_È™k’¯ËÇ­¥› Ê]‘±¿Ñ/ çpöìÔèApµ‚8£é@Q‹bžùKØŠAfPct×·†Öä¦l.}›©M$›<Ð¥oµ¼Mn¿-=û0PÖñnS•jNƒy½¦¬¥t]cGÑiµßü$©ÅûÁ*ÀüXÀûɵxúºwë|0¿ªÃMµå]˼Âöñ2üS¦uô¬ÆÛåÖEqGÏP0ÏvÖÍ|"å22†›K¹ ä¤Ü‘$ÊÔ_IáÛɶÐûv²-ô²²ýMèQ¬T9#QKï×=Ú«£ƒ‚âx.É€¨¡Ã½÷éžE¼¹ÛoAŽ­Ñ'k{a-"¨¿¯a{²†Ú’v_®gë.COP¾fè fåÐs1vÏš¥v*㸧žòX·çŒÓ´öà&abœW…þP§”å¶k9Š1ãa:”#‡“`„É=<ƨ¢Ä§œövÎÍ!D¢éþXžäæ³¢ .ØœõáG54€«c0†BLàŃU}ôÊ%VNMÀ•Z]q–Kýä¹r‚REñ¬W4…ßœä¨Þõò”LF›oûø1,Θ7U-œ{g$0[d÷üDÿöv~jö@Ö~õV¹k=ò®M@VKÜD\®]–'.Ïy©’;07Ëê2Ý" ðŒ¶È‹ËµÂ_ª>¶~¢úJå„‹\ ÿ•;gø„c烧×j–ü»xÀöpfnKHt7Ùy¡¨}|ãÇnR6åÞ…œT${Oî—Fô¾GŽfmœq %šJ.߆±¾†ý&'«éÔ…·wæääx[¾ðÊ &–Ÿ {ì˜ðÚf—²fï¢ø¹³Ô,ì³ïrPy\[Ù“Çî‰è¶©TÛV5ƒwOð©]¹b'N‚I±ÍB,UbÐgÜïñrª¯íó¡ÛF©”7²g€§ìLiõ'ôÊï®Mœøƒw~¨Yþ¾ò¥ŒŒ—b8Ÿ7ÎùHx“Ð4¿í{­j"·k‰ÜV)n. á°wI¹pB¯ïУmMøaˆÖƒ;Ø'BÈ–"u"—E§”‹MšöpqSÆ…|rއsV:ôóÒ'Ã?®QI2&MDdEAË0ÄDB¹†Ñ rüÍ"Û8\Z‘íôþ¸J§ b{9èwTw‚-w$a¼€³æ›h´Õú¸iýì±Î¾¡SX”Aüá ?3,sÕiÐh§hœ¹Yv~ÞrÚ”  ¥þR±­–ýöß’¶1°0Éè»»rƒ6”†¿saLËì-¼ö&Z?Ò(æVH`MMìD Ú:7Oˆ&Ýïm«¹-g“r…Nºœ™ÎR &|ïd£ë&!ãdíÍAa:½•4‘{…ü@'<¹^¼Kü›„%c+—’¥Ûˆ_¹¼Mwwé@Åc\BLl²xuuÁDâ^§»«+ºF]}ÇÚÜ&sƒNi¸ ØY„]Åö~²£“ÀòhÃe,ƒÛ1t‰¨A¼)¤Ùó õ«ú`¸éÓ“10œRÉSЃ€®ÕÉ\]æ6:ŵ—’Ñ ¯S%ñMQ ÓL¼ „¤ À6˜¯œ`rCØ\“0wv¹ßDnÛ~5"#A5’¡ÍÑJ;ÚÊ‘³Ìg¦‡vc™b—u–ä4ÿ¬A8V.; D¥i´òü0ŦÐuŠ—²ñÁ¹ FÚYÎR¶ ûÚ£ö¸íÏ®.ñ Ëë6o™Yõ«xnHË ýF)Û4õ:l‘Ö £5¼µÆk(ôª)°[cÈm³†H4í:;ëhPϬ#²{^ÇOYV£YX䘾ń’é((’q¿ììóõ²@Ñ€–‹¡çʓ҆Ñ4b_Ók÷Ú}ÃF.j››UÚ žžý89§¸d¶ÿ(^!vÛ„ª°å¡øU„Î4’Ùçå¦2_ *@ÞÕÆ‡„̢Ƴ£Ó£ÃÓ·ï‡ÿh´E#¤xíœÑ•ëÔÔCt±a!M!@aú.ÕÛ»SýTKõäÝÑáx>aš0×u¾ÞÓ"®R-è0ã2ìC"7-Ÿ`+ 'åe6NÞü7~Dé­MJব,†!re™¨‚K¨¬Â@¹‘…¸…Ù …¡¦ð-êÁŽ¿V‘Zr}™_aI:úèìјWó97f¾È=ÌXÂÌy,Ì`pÈ \›Ž C¶ò2f× ;\Ò]YÆ7ØCÁ¶¡(îÉ “̧Õ%*M<£-*Šð‹z#!â$HmkŽƒIÀ§C&ÝbTeÓK<ÃôE±!œ8ÕÃÄ ×BLMû7Ž^ÑÃ`ÀU$,w„ˆÚŠ!n1”.×»Ù—úòÍWx³O4 œ„šÊš¢~XQæ_h‹ì{uE5 OÚi þ±³‡˜¦"Û½Nw’hÃñò®Ä[ãã&3>þOæËúùãÿÉümñŸ/ó×yîî2Í×O^ŽS°ÒdO®/©À&_nZËÜDíëòŽõj:t.ÏOÔÔ¦È: äë½oÀú÷ß™ý$ÌœǑ82WqáÞÖ Ö¹j¡Ò´Ðm Ðm(}NÝ@˜ €u¡+!!‹,%«âl%¤™óIÃâYÛä³ [̧DÀÂØÈp‚ÉåþÎåR‚ÉÍÛ`iÝòÉ.ðM)p®QËœõ‚âsƒ“$—iSHç’Tˆ£I¥ —õþp»´9ýííðôåÑéÁð×£÷§Ç‡¯Œ¢"dfƒ¾…/ÂЋ·oŽß¾W/«y æø7ðÀMRÍÅÕ¿§%ÞÕµÄl ·Q%®Íúš&Khô5„F%„Æ_Ch\BÈŸ5î@È: JkÜû¡\RþÝI‘;*¥• hWkúöZÚ¯`KÊ<À&ü²@‰¥o?ŽU·³óp§gSF¸šçíÉwŠÎ{q«¼¾öd]ÑD¢ß×¶-·˜zØé?†%?Sº)4cØü ?ͧfÂó[݇š¹w½ý]½{Þnÿ‘|ýŒ¯]ïÑîCMOÒ=z¸gm…‚,;9nü?Ãù*A Üšâú~.$pª<áM­'Ž|4h6ŠgÜ!èãD-õ–¼qãÛð¤Ñt,‘e6˜÷ߨL{¹Z,@š¯š›÷]ä˜Cæéôpz™='Qq ¡mX "NP_8ê«_/ra%¶¡ØÌ‘N¡eã#'Uï˜Ox (äªAžXœ\…³M™?2ÁOHÓ—ïE–«KÙÝ4æˆÛ¨€yðàóõ$·kë¿©-+ÔÚ tO£tû74[³iM ÕdÝ n£ð"Ê=­QE~´\}–…8ìhF0™Öƒ:™ÐïRÄ13!‹åšžð®ëèÇJ¿°_ *'¾¨É¿QÇÜÙŠ‹FTåÉà€GÊ2œ`ZC }X$Dû†Âµf—µ/K•îe —K C:òW:Þ„êS9•1xxü\z}üúHº8YóL¹ ½9>=89ÚÛÉ å0ÓÂ#Yù–?4–Ò;ؽM½Y·ñ›Æ1ÌEÌçß“ssœFä1šÚÄ‚üÛœµ ™xú† ”4‡Î´èù@.)¸m–À7MéI¶µQ@Cáo¢%³BÔr…;˦מZpÏX—Ç š Úåâ{ª¦;¬ŠL9«E@<ëv<¯­ð»Ç¿û窭ØãÄ'öúçœÖç´>§õû(ÑúÒE€E.ìq„Çç¶iÃ¥ ° k»Ýhå^@a7«Ë]5®‰µÕ‡§ƒÕ¨­Ìêpàõú\,/nãÀLÄvãÝ„ċŠgÜ4ºtL­MåáX~“ÜFSˆ¥‹4êx¯îÓ/ðûê>yÉXî«ÝvÙ×1ßR®]úÅÙ\R«µñ±˜ð©˜ðb»ãÓ×uLë}9´guf¾RJïšqC•‘†‘!;KBÔM.ÒVÀñ–JU¦Ä—Žž¿?x}äYÆÞ¿?ø1Ëqç¯ÉË—›]•žšr̰—Q9~*Ž"mÖŸ«úiÜ äÝ»ŒŒáÐ3zæÃH>°ö9[•,Jñ¨Ñé|'"“þñ*Š—ªó§"#ùVq³ÄfÌséfóÙ¥Êìt{¸”Bn#™ÊYÅÅ­…JK5­åô—L5î?A:ÿ.à#ç°B§”Öé˵ÅX=™ñºýÎÃ]|V% Ÿ6§úqsPÖËÕàåÂÈ"œÊxM¦h¨R€â&cP¹ÀåÍKtà¨þ^W*‡5Ø£‡[^o«»sêu÷úwökkÂ’W[gŒ9v¬”e»²m8¯iBdØÍw…6—_+©.°M+’eùŸF´yŽÄ¹&mNÌ'±¡äs€ ÀWÒlƺ¡{€ñ0Z˜Y^bTHèúi¶Mâ J!¡WH`§ŸÒ92ûìi‡”þëÐ@Êw])ŠÛÿ Í^FáÝz )ppòöÃûÃ#½8Ÿ™x(b)ï~=>ý”‚ad~ “[†Ûò,¹:YÚ¨A2â•`ˆg‚a,±z­*Ìýh%q )H2qá"~\ƒøIÐ\D‘aÔ×Á4”sE¦¦êÚ…°'U}´Û ¡ ôß¡ò:›ì\ù¹AVv:(µo«òù”PUfz¨ Àã«&¤†„=LS«ëÿGøÃf‚OObÚú[°ž€õÊÀ>­k­×mñëá*aÜI`cÀœ%”ÖÑ|u»#ëí}o/'&öÓ–Ú(·ê˜’©'é èœH8™¼ä©Ì%/Œ¿„ö(ͽÀîCeÆ0ˆËiÒVÜ,òË3W ¾ýh‚ýg%Dx!gO7}ÄNïvë‡MAn"Ä7š@t8dNI~îý’rû.å°¡„GøLð↢»œ{h×nC`#IÿœDãÉRÿPK…‚Å6;gаŒÅ CBFlib.txtPKšÅ6µ+Ìá¼d Űpycbf.wPKm¦./CBFlib-0.9.2.2/pycbf/setup.py0000644000076500007650000000074111603702120014411 0ustar yayayaya # Import the things to build python binary extensions from distutils.core import setup, Extension # Make our extension module e = Extension('_pycbf', sources = ["pycbf_wrap.c","../src/cbf_simple.c"], extra_compile_args=["-g"], library_dirs=["../lib/"], libraries=["cbf"], include_dirs = ["../include"] ) # Build it setup(name="_pycbf",ext_modules=[e],) setup(name="pycbf", py_modules=['pycbf']) ./CBFlib-0.9.2.2/pycbf/pycbf_ascii_help.txt0000644000076500007650000043143411603702120016732 0ustar yayayayaHelp on module pycbf: NAME pycbf - pycbf - python bindings to the CBFlib library FILE d:\wright\cbflib\cbflib_0.7.7\pycbf\pycbf.py DESCRIPTION A library for reading and writing ImageCIF and CBF files which store area detector images for crystallography. This work is a derivative of the CBFlib version 0.7.7 library by Paul J. Ellis of Stanford Synchrotron Radiation Laboratory and Herbert J. Bernstein of Bernstein + Sons See: http://www.bernstein-plus-sons.com/software/CBF/ Licensing is GPL based, see: http://www.bernstein-plus-sons.com/software/CBF/doc/CBFlib_NOTICES.html These bindings were automatically generated by SWIG, and the input to SWIG was automatically generated by a python script. We very strongly recommend you do not attempt to edit them by hand! Copyright (C) 2007 Jonathan Wright ESRF, Grenoble, France email: wright@esrf.fr CLASSES __builtin__.object cbf_detector_struct cbf_handle_struct cbf_positioner_struct class cbf_detector_struct(__builtin__.object) | Proxy of C cbf_detector_struct struct | | Methods defined here: | | __del__ lambda self | | __getattr__ lambda self, name | | __init__(self, *args) | __init__(self) -> cbf_detector_struct | | __repr__ = _swig_repr(self) | | __setattr__ lambda self, name, value | | get_beam_center(*args) | Returns : double index1,double index2,double center1,double center2 | *args : | | C prototype: int cbf_get_beam_center (cbf_detector detector, double *index1, | double *index2, double *center1, double *center2); | | CBFLib documentation: | DESCRIPTION | cbf_get_beam_center sets *center1 and *center2 to the displacements | in mm along the detector axes from pixel (0, 0) to the point at which | the beam intersects the detector and *index1 and *index2 to the | corresponding indices. cbf_set_beam_center sets the offsets in the | axis category for the detector element axis with precedence 1 to | place the beam center at the position given in mm by *center1 and | *center2 as the displacements in mm along the detector axes from | pixel (0, 0) to the point at which the beam intersects the detector | at the indices given *index1 and *index2. | Any of the destination pointers may be NULL for getting the beam | center. For setting the beam axis, either the indices of the center | must not be NULL. | The indices are non-negative for beam centers within the detector | surface, but the center for an axis with a negative increment will be | negative for a beam center within the detector surface. | ARGUMENTS | detector Detector handle. index1 Pointer to the destination slow | index. index2 Pointer to the destination fast index. center1 | Pointer to the destination displacement along the slow axis. center2 | Pointer to the destination displacement along the fast axis. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | get_detector_distance(*args) | Returns : double distance | *args : | | C prototype: int cbf_get_detector_distance (cbf_detector detector, | double *distance); | | CBFLib documentation: | DESCRIPTION | cbf_get_detector_distance sets *distance to the nearest distance from | the sample position to the detector plane. | ARGUMENTS | detector Detector handle. distance Pointer to the destination | distance. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | get_detector_normal(*args) | Returns : double normal1,double normal2,double normal3 | *args : | | C prototype: int cbf_get_detector_normal (cbf_detector detector, | double *normal1, double *normal2, double *normal3); | | CBFLib documentation: | DESCRIPTION | cbf_get_detector_normal sets *normal1, *normal2, and *normal3 to the | 3 components of the of the normal vector to the detector plane. The | vector is normalized. | Any of the destination pointers may be NULL. | ARGUMENTS | detector Detector handle. normal1 Pointer to the destination x | component of the normal vector. normal2 Pointer to the destination | y component of the normal vector. normal3 Pointer to the | destination z component of the normal vector. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | get_inferred_pixel_size(*args) | Returns : Float pixel size | *args : Int axis_number | | C prototype: int cbf_get_inferred_pixel_size (cbf_detector detector, | unsigned int axis_number, double *psize); | | CBFLib documentation: | DESCRIPTION | cbf_get_inferred_pixel_size sets *psize to point to the double value | in millimeters of the pixel size for the axis axis_number value for | pixel at (index1, index2) on the detector surface. The slow index is | treated as axis 1 and the fast index is treated as axis 2. | ARGUMENTS | detector Detector handle. axis_number The number of the axis. | area Pointer to the destination pizel size in mm. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | get_pixel_area(*args) | Returns : double area,double projected_area | *args : double index1,double index2 | | C prototype: int cbf_get_pixel_area (cbf_detector detector, double index1, | double index2, double *area, double *projected_area); | | CBFLib documentation: | DESCRIPTION | cbf_get_pixel_area sets *area to the area of the pixel at (index1, | index2) on the detector surface and *projected_area to the apparent | area of the pixel as viewed from the sample position. | Either of the destination pointers may be NULL. | ARGUMENTS | detector Detector handle. index1 Slow index. index2 | Fast index. area Pointer to the destination | area in mm2. projected_area Pointer to the destination apparent | area in mm2. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | get_pixel_coordinates(*args) | Returns : double coordinate1,double coordinate2,double coordinate3 | *args : double index1,double index2 | | C prototype: int cbf_get_pixel_coordinates (cbf_detector detector, | double index1, double index2, double *coordinate1, | double *coordinate2, double *coordinate3); | | CBFLib documentation: | DESCRIPTION | cbf_get_pixel_coordinates sets *coordinate1, *coordinate2, and | *coordinate3 to the vector position of pixel (index1, index2) on the | detector surface. If index1 and index2 are integers then the | coordinates correspond to the center of a pixel. | Any of the destination pointers may be NULL. | ARGUMENTS | detector Detector handle. index1 Slow index. index2 | Fast index. coordinate1 Pointer to the destination x component. | coordinate2 Pointer to the destination y component. coordinate3 | Pointer to the destination z component. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | get_pixel_normal(*args) | Returns : double normal1,double normal2,double normal3 | *args : double index1,double index2 | | C prototype: int cbf_get_pixel_normal (cbf_detector detector, double index1, | double index2, double *normal1, double *normal2, | double *normal3); | | CBFLib documentation: | DESCRIPTION | cbf_get_detector_normal sets *normal1, *normal2, and *normal3 to the | 3 components of the of the normal vector to the pixel at (index1, | index2). The vector is normalized. | Any of the destination pointers may be NULL. | ARGUMENTS | detector Detector handle. index1 Slow index. index2 Fast index. | normal1 Pointer to the destination x component of the normal | vector. normal2 Pointer to the destination y component of the | normal vector. normal3 Pointer to the destination z component of | the normal vector. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | ---------------------------------------------------------------------- | Properties defined here: | | axes | = cbf_detector_struct_axes_get(...) | | = cbf_detector_struct_axes_set(...) | | displacement | = cbf_detector_struct_displacement_get(...) | | = cbf_detector_struct_displacement_set(...) | | increment | = cbf_detector_struct_increment_get(...) | | = cbf_detector_struct_increment_set(...) | | index | = cbf_detector_struct_index_get(...) | | = cbf_detector_struct_index_set(...) | | positioner | = cbf_detector_struct_positioner_get(...) | | = cbf_detector_struct_positioner_set(...) | | ---------------------------------------------------------------------- | Data and other attributes defined here: | | __dict__ = | dictionary for instance variables (if defined) | | __swig_destroy__ = | | | __swig_getmethods__ = {'axes': cbf_handle_struct | | __repr__ = _swig_repr(self) | | __setattr__ lambda self, name, value | | category_name(*args) | Returns : | *args : string | | C prototype: int cbf_category_name (cbf_handle handle, | const char **categoryname); | | CBFLib documentation: | DESCRIPTION | cbf_category_name sets *categoryname to point to the name of the | current category of the current data block. | The category name will be valid as long as the category exists. | The name must not be modified by the program in any way. | ARGUMENTS | handle CBF handle. categoryname Pointer to the destination | category name pointer. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | column_name(*args) | Returns : | *args : string | | C prototype: int cbf_column_name (cbf_handle handle, const char **columnname); | | CBFLib documentation: | DESCRIPTION | cbf_column_name sets *columnname to point to the name of the current | column of the current category. | The column name will be valid as long as the column exists. | The name must not be modified by the program in any way. | ARGUMENTS | handle CBF handle. columnname Pointer to the destination | column name pointer. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | construct_detector(*args) | Returns : pycbf detector object | *args : Integer element_number | | C prototype: int cbf_construct_detector (cbf_handle handle, | cbf_detector *detector, unsigned int element_number); | | CBFLib documentation: | DESCRIPTION | cbf_construct_detector constructs a detector object for detector | element number element_number using the description in the CBF object | handle and initialises the detector handle *detector. | ARGUMENTS | handle CBF handle. detector Pointer to the destination detector | handle. element_number The number of the detector element counting | from 0 by order of appearance in the "diffrn_data_frame" category. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | construct_goniometer(*args) | Returns : pycbf goniometer object | *args : | | C prototype: int cbf_construct_goniometer (cbf_handle handle, | cbf_goniometer *goniometer); | | CBFLib documentation: | DESCRIPTION | cbf_construct_goniometer constructs a goniometer object using the | description in the CBF object handle and initialises the goniometer | handle *goniometer. | ARGUMENTS | handle CBF handle. goniometer Pointer to the destination | goniometer handle. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | count_categories(*args) | Returns : unsigned | *args : | | C prototype: int cbf_count_categories (cbf_handle handle, | unsigned int *categories); | | CBFLib documentation: | DESCRIPTION | cbf_count_categories puts the number of categories in the current | data block in *categories. | ARGUMENTS | handle CBF handle. categories Pointer to the destination | category count. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | count_columns(*args) | Returns : Integer | *args : | | C prototype: int cbf_count_columns (cbf_handle handle, unsigned int *columns); | | CBFLib documentation: | DESCRIPTION | cbf_count_columns puts the number of columns in the current category | in *columns. | ARGUMENTS | handle CBF handle. columns Pointer to the destination column | count. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | count_datablocks(*args) | Returns : unsigned | *args : | | C prototype: int cbf_count_datablocks (cbf_handle handle, | unsigned int *datablocks); | | CBFLib documentation: | DESCRIPTION | cbf_count_datablocks puts the number of data blocks in *datablocks . | ARGUMENTS | handle CBF handle. datablocks Pointer to the destination data | block count. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | count_elements(*args) | Returns : Integer | *args : | | C prototype: int cbf_count_elements (cbf_handle handle, | unsigned int *elements); | | CBFLib documentation: | DESCRIPTION | cbf_count_elements sets *elements to the number of detector elements. | ARGUMENTS | handle CBF handle. elements Pointer to the destination count. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | count_rows(*args) | Returns : Integer | *args : | | C prototype: int cbf_count_rows (cbf_handle handle, unsigned int *rows); | | CBFLib documentation: | DESCRIPTION | cbf_count_rows puts the number of rows in the current category in | *rows . | ARGUMENTS | handle CBF handle. rows Pointer to the destination row count. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | datablock_name(*args) | Returns : | *args : string | | C prototype: int cbf_datablock_name (cbf_handle handle, | const char **datablockname); | | CBFLib documentation: | DESCRIPTION | cbf_datablock_name sets *datablockname to point to the name of the | current data block. | The data block name will be valid as long as the data block exists | and has not been renamed. | The name must not be modified by the program in any way. | ARGUMENTS | handle CBF handle. datablockname Pointer to the | destination data block name pointer. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | delete_row(*args) | Returns : | *args : Integer | | C prototype: int cbf_delete_row (cbf_handle handle, unsigned int rownumber); | | CBFLib documentation: | DESCRIPTION | cbf_delete_row deletes a row from the current category. Rows starting | from rownumber +1 are moved down by 1. If the current row was higher | than rownumber, or if the current row is the last row, it will also | move down by 1. | The row numbers start from 0. | ARGUMENTS | handle CBF handle. rownumber The number of the row to delete. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | find_category(*args) | Returns : string | *args : | | C prototype: int cbf_find_category (cbf_handle handle, | const char *categoryname); | | CBFLib documentation: | DESCRIPTION | cbf_find_category makes the category in the current data block with | name categoryname the current category. | The comparison is case-insensitive. | If the category does not exist, the function returns CBF_NOTFOUND. | The current column and row become undefined. | ARGUMENTS | handle CBF handle. categoryname The name of the category to | find. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | find_category_root(*args) | Returns : String categoryroot | *args : String categoryname | | C prototype: int cbf_find_category_root (cbf_handle handle, | const char* categoryname, const char** categoryroot); | | CBFLib documentation: | DESCRIPTION | cbf_find_category_root sets *categoryroot to the root category of | which categoryname is an alias. cbf_set_category_root sets | categoryname_in as an alias of categoryroot in the dictionary | associated with handle, creating the dictionary if necessary. | cbf_require_category_root sets *categoryroot to the root category of | which categoryname is an alias, if there is one, or to the value of | categoryname, if categoryname is not an alias. | A returned categoryroot string must not be modified in any way. | ARGUMENTS | handle CBF handle. categoryname category name which | may be an alias. categoryroot pointer to a returned category | root name. categoryroot_in input category root name. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | find_column(*args) | Returns : string | *args : | | C prototype: int cbf_find_column (cbf_handle handle, const char *columnname); | | CBFLib documentation: | DESCRIPTION | cbf_find_column makes the columns in the current category with name | columnname the current column. | The comparison is case-insensitive. | If the column does not exist, the function returns CBF_NOTFOUND. | The current row is not affected. | ARGUMENTS | handle CBF handle. columnname The name of column to find. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | find_datablock(*args) | Returns : string | *args : | | C prototype: int cbf_find_datablock (cbf_handle handle, | const char *datablockname); | | CBFLib documentation: | DESCRIPTION | cbf_find_datablock makes the data block with name datablockname the | current data block. | The comparison is case-insensitive. | If the data block does not exist, the function returns CBF_NOTFOUND. | The current category becomes undefined. | ARGUMENTS | handle CBF handle. datablockname The name of the data | block to find. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | find_nextrow(*args) | Returns : string | *args : | | C prototype: int cbf_find_nextrow (cbf_handle handle, const char *value); | | CBFLib documentation: | DESCRIPTION | cbf_find_nextrow makes the makes the next row in the current column | with value value the current row. The search starts from the row | following the last row found with cbf_find_row or cbf_find_nextrow, | or from the current row if the current row was defined using any | other function. | The comparison is case-sensitive. | If no more matching rows exist, the function returns CBF_NOTFOUND. | The current column is not affected. | ARGUMENTS | handle CBF handle. value the value to search for. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | find_row(*args) | Returns : string | *args : | | C prototype: int cbf_find_row (cbf_handle handle, const char *value); | | CBFLib documentation: | DESCRIPTION | cbf_find_row makes the first row in the current column with value | value the current row. | The comparison is case-sensitive. | If a matching row does not exist, the function returns CBF_NOTFOUND. | The current column is not affected. | ARGUMENTS | handle CBF handle. value The value of the row to find. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | find_tag_category(*args) | Returns : String categoryname_in | *args : String tagname | | C prototype: int cbf_find_tag_category (cbf_handle handle, | const char* tagname, const char** categoryname); | | CBFLib documentation: | DESCRIPTION | cbf_find_tag_category sets categoryname to the category associated | with tagname in the dictionary associated with handle. | cbf_set_tag_category upddates the dictionary associated with handle | to indicated that tagname is in category categoryname_in. | ARGUMENTS | handle CBF handle. tagname tag name. | categoryname pointer to a returned category name. | categoryname_in input category name. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | find_tag_root(*args) | Returns : String tagroot | *args : String tagname | | C prototype: int cbf_find_tag_root (cbf_handle handle, const char* tagname, | const char** tagroot); | | CBFLib documentation: | DESCRIPTION | cbf_find_tag_root sets *tagroot to the root tag of which tagname is | an alias. cbf_set_tag_root sets tagname as an alias of tagroot_in in | the dictionary associated with handle, creating the dictionary if | necessary. cbf_require_tag_root sets *tagroot to the root tag of | which tagname is an alias, if there is one, or to the value of | tagname, if tagname is not an alias. | A returned tagroot string must not be modified in any way. | ARGUMENTS | handle CBF handle. tagname tag name which may be an alias. | tagroot pointer to a returned tag root name. tagroot_in input | tag root name. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | force_new_category(*args) | Returns : string | *args : | | C prototype: int cbf_force_new_category (cbf_handle handle, | const char *categoryname); | | CBFLib documentation: | DESCRIPTION | cbf_force_new_category creates a new category in the current data | block with name categoryname and makes it the current category. | Duplicate category names are allowed. | Even if a category with this name already exists, a new category of | the same name is created and becomes the current category. The allows | for the creation of unlooped tag/value lists drawn from the same | category. | ARGUMENTS | handle CBF handle. categoryname The name of the new | category. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | force_new_datablock(*args) | Returns : string | *args : | | C prototype: int cbf_force_new_datablock (cbf_handle handle, | const char *datablockname); | | CBFLib documentation: | DESCRIPTION | cbf_force_new_datablock creates a new data block with name | datablockname and makes it the current data block. Duplicate data | block names are allowed. cbf_force_new_saveframe creates a new savew | frame with name saveframename and makes it the current save frame. | Duplicate save frame names are allowed. | Even if a save frame with this name already exists, a new save frame | is created and becomes the current save frame. | ARGUMENTS | handle CBF handle. datablockname The name of the new data | block. saveframename The name of the new save frame. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | force_new_saveframe(*args) | Returns : string | *args : | | C prototype: int cbf_force_new_saveframe (cbf_handle handle, | const char *saveframename); | | CBFLib documentation: | DESCRIPTION | cbf_force_new_datablock creates a new data block with name | datablockname and makes it the current data block. Duplicate data | block names are allowed. cbf_force_new_saveframe creates a new savew | frame with name saveframename and makes it the current save frame. | Duplicate save frame names are allowed. | Even if a save frame with this name already exists, a new save frame | is created and becomes the current save frame. | ARGUMENTS | handle CBF handle. datablockname The name of the new data | block. saveframename The name of the new save frame. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | get_3d_image(*args) | get_3d_image(self, void ?) | | get_3d_image_size(*args) | get_3d_image_size(self, void ?) | | get_axis_setting(*args) | Returns : Float start,Float increment | *args : String axis_id | | C prototype: int cbf_get_axis_setting (cbf_handle handle, | unsigned int reserved, const char *axis_id, double *start, | double *increment); | | CBFLib documentation: | DESCRIPTION | cbf_get_axis_setting sets *start and *increment to the corresponding | values of the axis axis_id. | Either of the destination pointers may be NULL. | The parameter reserved is presently unused and should be set to 0. | ARGUMENTS | handle CBF handle. reserved Unused. Any value other than 0 is | invalid. axis_id Axis id. start Pointer to the destination | start value. increment Pointer to the destination increment value. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | get_bin_sizes(*args) | get_bin_sizes(self, void ?) | | get_crystal_id(*args) | Returns : | *args : string | | C prototype: int cbf_get_crystal_id (cbf_handle handle, | const char **crystal_id); | | CBFLib documentation: | DESCRIPTION | cbf_get_crystal_id sets *crystal_id to point to the ASCII value of | the "diffrn.crystal_id" entry. | If the value is not ASCII, the function returns CBF_BINARY. | The value will be valid as long as the item exists and has not been | set to a new value. | The value must not be modified by the program in any way. | ARGUMENTS | handle CBF handle. crystal_id Pointer to the destination | value pointer. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | get_datestamp(*args) | Returns : int year,int month,int day,int hour,int minute,double second, | int timezone | *args : | | C prototype: int cbf_get_datestamp (cbf_handle handle, unsigned int reserved, | int *year, int *month, int *day, int *hour, int *minute, | double *second, int *timezone); | | CBFLib documentation: | DESCRIPTION | cbf_get_datestamp sets *year, *month, *day, *hour, *minute and | *second to the corresponding values of the collection timestamp. | *timezone is set to timezone difference from UTC in minutes. The | parameter < i>reserved is presently unused and should be set to 0. | Any of the destination pointers may be NULL. | ARGUMENTS | handle CBF handle. reserved Unused. Any value other than 0 is | invalid. year Pointer to the destination timestamp year. month | Pointer to the destination timestamp month (1-12). day Pointer to | the destination timestamp day (1-31). hour Pointer to the | destination timestamp hour (0-23). minute Pointer to the | destination timestamp minute (0-59). second Pointer to the | destination timestamp second (0-60.0). timezone Pointer to the | destination timezone difference from UTC in minutes. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | get_dictionary(*args) | Returns : CBFHandle dictionary | *args : | | C prototype: int cbf_get_dictionary (cbf_handle handle, | cbf_handle * dictionary); | | CBFLib documentation: | DESCRIPTION | cbf_get_dictionary sets *dictionary to the handle of a CBF which has | been associated with the CBF handle by cbf_set_dictionary. | cbf_set_dictionary associates the CBF handle dictionary_in with | handle as its dictionary. cbf_require_dictionary sets *dictionary to | the handle of a CBF which has been associated with the CBF handle by | cbf_set_dictionary or creates a new empty CBF and associates it with | handle, returning the new handle in *dictionary. | ARGUMENTS | handle CBF handle. dictionary Pointer to CBF handle of | dictionary. dictionary_in CBF handle of dcitionary. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | get_diffrn_id(*args) | Returns : | *args : string | | C prototype: int cbf_get_diffrn_id (cbf_handle handle, | const char **diffrn_id); | | CBFLib documentation: | DESCRIPTION | cbf_get_diffrn_id sets *diffrn_id to point to the ASCII value of the | "diffrn.id" entry. cbf_require_diffrn_id also sets *diffrn_id to | point to the ASCII value of the "diffrn.id" entry, but, if the | "diffrn.id" entry does not exist, it sets the value in the CBF and | in*diffrn_id to the character string given by default_id, creating | the category and column is necessary. | The diffrn_id will be valid as long as the item exists and has not | been set to a new value. | The diffrn_id must not be modified by the program in any way. | ARGUMENTS | handle CBF handle. diffrn_id Pointer to the destination | value pointer. default_id Character string default value. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | get_divergence(*args) | Returns : Float div_x_source,Float div_y_source,Float div_x_y_source | *args : | | C prototype: int cbf_get_divergence (cbf_handle handle, double *div_x_source, | double *div_y_source, double *div_x_y_source); | | CBFLib documentation: | DESCRIPTION | cbf_get_divergence sets *div_x_source, *div_y_source and | *div_x_y_source to the corresponding source divergence parameters. | Any of the destination pointers may be NULL. | ARGUMENTS | handle CBF handle. div_x_source Pointer to the | destination div_x_source. div_y_source Pointer to the destination | div_y_source. div_x_y_source Pointer to the destination | div_x_y_source. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | get_doublevalue(*args) | Returns : double | *args : | | C prototype: int cbf_get_doublevalue (cbf_handle handle, double *number); | | CBFLib documentation: | DESCRIPTION | cbf_get_doublevalue sets *number to the value of the ASCII item at | the current column and row interpreted as a decimal floating-point | number. cbf_require_doublevalue sets *number to the value of the | ASCII item at the current column and row interpreted as a decimal | floating-point number, setting it to defaultvalue if necessary. | If the value is not ASCII, the function returns CBF_BINARY. | ARGUMENTS | handle CBF handle. number Pointer to the destination | number. defaultvalue default number value. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | get_element_id(*args) | Returns : String | *args : Integer element_number | | C prototype: int cbf_get_element_id (cbf_handle handle, | unsigned int element_number, const char **element_id); | | CBFLib documentation: | DESCRIPTION | cbf_get_element_id sets *element_id to point to the ASCII value of | the element_number th "diffrn_data_frame.detector_element_id" | entry, counting from 0. | If the detector element does not exist, the function returns | CBF_NOTFOUND. | The element_id will be valid as long as the item exists and has not | been set to a new value. | The element_id must not be modified by the program in any way. | ARGUMENTS | handle CBF handle. element_number The number of the detector | element counting from 0 by order of appearance in the | "diffrn_data_frame" category. element_id Pointer to the | destination. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | get_gain(*args) | Returns : Float gain,Float gain_esd | *args : | | C prototype: int cbf_get_gain (cbf_handle handle, unsigned int element_number, | double *gain, double *gain_esd); | | CBFLib documentation: | DESCRIPTION | cbf_get_gain sets *gain and *gain_esd to the corresponding gain | parameters for element number element_number. | Either of the destination pointers may be NULL. | ARGUMENTS | handle CBF handle. element_number The number of the detector | element counting from 0 by order of appearance in the | "diffrn_data_frame" category. gain Pointer to the destination | gain. gain_esd Pointer to the destination gain_esd. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | get_image(*args) | get_image(self, void ?) | | get_image_size(*args) | Returns : size_t ndim1,size_t ndim2 | *args : Integer element_number | | C prototype: int cbf_get_image_size (cbf_handle handle, unsigned int reserved, | unsigned int element_number, size_t *ndim1, size_t *ndim2); | | CBFLib documentation: | DESCRIPTION | cbf_get_image_size sets *ndim1 and *ndim2 to the slow and fast | dimensions of the image array for element number element_number. If | the array is 1-dimensional, *ndim1 will be set to the array size and | *ndim2 will be set to 1. If the array is 3-dimensional an error code | will be returned. cbf_get_3d_image_size sets *ndim1, *ndim2 and | *ndim3 to the slowest, next fastest and fastest dimensions, | respectively, of the 3D image array for element number | element_number. If the array is 1-dimensional, *ndim1 will be set to | the array size and *ndim2 and | | get_integerarray_as_string(*args) | Returns : (Binary)String | *args : | | C prototype: int cbf_get_integerarray (cbf_handle handle, int *binary_id, | void *array, size_t elsize, int elsigned, size_t elements, | size_t *elements_read); | | CBFLib documentation: | DESCRIPTION | cbf_get_integerarray reads the binary value of the item at the | current column and row into an integer array. The array consists of | elements elements of elsize bytes each, starting at array. The | elements are signed if elsigned is non-0 and unsigned otherwise. | *binary_id is set to the binary section identifier and *elements_read | to the number of elements actually read. cbf_get_realarray reads the | binary value of the item at the current column and row into a real | array. The array consists of elements elements of elsize bytes each, | starting at array. *binary_id is set to the binary section identifier | and *elements_read to the number of elements actually read. | If any element in the integer binary data cant fit into the | destination element, the destination is set the nearest possible | value. | If the value is not binary, the function returns CBF_ASCII. | If the requested number of elements cant be read, the function will | read as many as it can and then return CBF_ENDOFDATA. | Currently, the destination array must consist of chars, shorts or | ints (signed or unsigned). If elsize is not equal to sizeof (char), | sizeof (short) or sizeof (int), for cbf_get_integerarray, or | sizeof(double) or sizeof(float), for cbf_get_realarray the function | returns CBF_ARGUMENT. | An additional restriction in the current version of CBFlib is that | values too large to fit in an int are not correctly decompressed. As | an example, if the machine with 32-bit ints is reading an array | containing a value outside the range 0 .. 2^32-1 (unsigned) or -2^31 | .. 2^31-1 (signed), the array will not be correctly decompressed. | This restriction will be removed in a future release. For | cbf_get_realarray, only IEEE format is supported. No conversion to | other floating point formats is done at this time. | ARGUMENTS | handle CBF handle. binary_id Pointer to the destination integer | binary identifier. array Pointer to the destination array. elsize | Size in bytes of each destination array element. elsigned Set to | non-0 if the destination array elements are signed. elements The | number of elements to read. elements_read Pointer to the | destination number of elements actually read. | RETURN VALUE | Returns an error code on failure or 0 for success. SEE ALSO | | get_integerarrayparameters(*args) | Returns : int compression,int binary_id,int elsize,int elsigned,int elunsigned, | int elements,int minelement,int maxelement | *args : | | C prototype: int cbf_get_integerarrayparameters (cbf_handle handle, | unsigned int *compression, int *binary_id, size_t *elsize, | int *elsigned, int *elunsigned, size_t *elements, | int *minelement, int *maxelement); | | CBFLib documentation: | DESCRIPTION | cbf_get_integerarrayparameters sets *compression, *binary_id, | *elsize, *elsigned, *elunsigned, *elements, *minelement and | *maxelement to values read from the binary value of the item at the | current column and row. This provides all the arguments needed for a | subsequent call to cbf_set_integerarray, if a copy of the array is to | be made into another CIF or CBF. cbf_get_realarrayparameters sets | *compression, *binary_id, *elsize, *elements to values read from the | binary value of the item at the current column and row. This provides | all the arguments needed for a subsequent call to cbf_set_realarray, | if a copy of the arry is to be made into another CIF or CBF. | The variants cbf_get_integerarrayparameters_wdims and | cbf_get_realarrayparameters_wdims set **byteorder, *dim1, *dim2, | *dim3, and *padding as well, providing the additional parameters | needed for a subsequent call to cbf_set_integerarray_wdims or | cbf_set_realarray_wdims. | The value returned in *byteorder is a pointer either to the string | "little_endian" or to the string "big_endian". This should be the | byte order of the data, not necessarily of the host machine. No | attempt should be made to modify this string. At this time only | "little_endian" will be returned. | The values returned in *dim1, *dim2 and *dim3 are the sizes of the | fastest changing, second fastest changing and third fastest changing | dimensions of the array, if specified, or zero, if not specified. | The value returned in *padding is the size of the post-data padding, | if any and if specified in the data header. The value is given as a | count of octets. | If the value is not binary, the function returns CBF_ASCII. | ARGUMENTS | handle CBF handle. compression Compression method used. elsize | Size in bytes of each array element. binary_id Pointer to the | destination integer binary identifier. elsigned Pointer to an | integer. Set to 1 if the elements can be read as signed integers. | elunsigned Pointer to an integer. Set to 1 if the elements can be | read as unsigned integers. elements Pointer to the destination | number of elements. minelement Pointer to the destination smallest | element. maxelement Pointer to the destination largest element. | byteorder Pointer to the destination byte order. dim1 Pointer to | the destination fastest dimension. dim2 Pointer to the destination | second fastest dimension. dim3 Pointer to the destination third | fastest dimension. padding Pointer to the destination padding size. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | get_integerarrayparameters_wdims(*args) | get_integerarrayparameters_wdims(self, void ?) | | get_integervalue(*args) | Returns : int | *args : | | C prototype: int cbf_get_integervalue (cbf_handle handle, int *number); | | CBFLib documentation: | DESCRIPTION | cbf_get_integervalue sets *number to the value of the ASCII item at | the current column and row interpreted as a decimal integer. | cbf_require_integervalue sets *number to the value of the ASCII item | at the current column and row interpreted as a decimal integer, | setting it to defaultvalue if necessary. | If the value is not ASCII, the function returns CBF_BINARY. | ARGUMENTS | handle CBF handle. number pointer to the number. | defaultvalue default number value. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | get_integration_time(*args) | Returns : Float time | *args : | | C prototype: int cbf_get_integration_time (cbf_handle handle, | unsigned int reserved, double *time); | | CBFLib documentation: | DESCRIPTION | cbf_get_integration_time sets *time to the integration time in | seconds. The parameter reserved is presently unused and should be set | to 0. | ARGUMENTS | handle CBF handle. reserved Unused. Any value other than 0 is | invalid. time Pointer to the destination time. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | get_orientation_matrix(*args) | Returns : Float matrix_0,Float matrix_1,Float matrix_2,Float matrix_3, | Float matrix_4,Float matrix_5,Float matrix_6,Float matrix_7, | Float matrix_8 | *args : | | C prototype: int cbf_get_orientation_matrix (cbf_handle handle, | double ub_matrix[9]); | | CBFLib documentation: | DESCRIPTION | cbf_get_orientation_matrix sets ub_matrix to point to the array of | orientation matrix entries in the "diffrn" category in the order of | columns: | "UB[1][1]" "UB[1][2]" "UB[1][3]" "UB[2][1]" "UB[2][2]" | "UB[2][3]" "UB[3][1]" "UB[3][2]" "UB[3][3]" | cbf_set_orientation_matrix sets the values in the "diffrn" category | to the values pointed to by ub_matrix. | ARGUMENTS | handle CBF handle. ubmatric Source or destination array of 9 | doubles giving the orientation matrix parameters. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | get_overload(*args) | Returns : Float overload | *args : Integer element_number | | C prototype: int cbf_get_overload (cbf_handle handle, | unsigned int element_number, double *overload); | | CBFLib documentation: | DESCRIPTION | cbf_get_overload sets *overload to the overload value for element | number element_number. | ARGUMENTS | handle CBF handle. element_number The number of the detector | element counting from 0 by order of appearance in the | "diffrn_data_frame" category. overload Pointer to the destination | overload. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | get_pixel_size(*args) | Returns : Float pixel_size | *args : Int element_number,Int axis_number | | C prototype: int cbf_get_pixel_size (cbf_handle handle, | unsigned int element_number, unsigned int axis_number, | double *psize); | | CBFLib documentation: | DESCRIPTION | cbf_get_pixel_size sets *psize to point to the double value in | millimeters of the axis axis_number of the detector element | element_number. The axis_number is numbered from 1, starting with the | fastest axis. | If the pixel size is not given explcitly in the | "array_element_size" category, the function returns CBF_NOTFOUND. | ARGUMENTS | handle CBF handle. element_number The number of the detector | element counting from 0 by order of appearance in the | "diffrn_data_frame" category. axis_number The number of the axis, | fastest first, starting from 1. | | get_polarization(*args) | Returns : float polarizn_source_ratio,float polarizn_source_norm | *args : | | C prototype: int cbf_get_polarization (cbf_handle handle, | double *polarizn_source_ratio, | double *polarizn_source_norm); | | CBFLib documentation: | DESCRIPTION | cbf_get_polarization sets *polarizn_source_ratio and | *polarizn_source_norm to the corresponding source polarization | parameters. | Either destination pointer may be NULL. | ARGUMENTS | handle CBF handle. polarizn_source_ratio Pointer to the | destination polarizn_source_ratio. polarizn_source_norm Pointer to | the destination polarizn_source_norm. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | get_real_3d_image(*args) | get_real_3d_image(self, void ?) | | get_real_image(*args) | get_real_image(self, void ?) | | get_realarray(*args) | get_realarray(self, void ?) | | get_realarrayparameters(*args) | Returns : int compression,int binary_id,int elsize,int elements | *args : | | C prototype: int cbf_get_realarrayparameters (cbf_handle handle, | unsigned int *compression, int *binary_id, size_t *elsize, | size_t *elements); | | CBFLib documentation: | DESCRIPTION | cbf_get_integerarrayparameters sets *compression, *binary_id, | *elsize, *elsigned, *elunsigned, *elements, *minelement and | *maxelement to values read from the binary value of the item at the | current column and row. This provides all the arguments needed for a | subsequent call to cbf_set_integerarray, if a copy of the array is to | be made into another CIF or CBF. cbf_get_realarrayparameters sets | *compression, *binary_id, *elsize, *elements to values read from the | binary value of the item at the current column and row. This provides | all the arguments needed for a subsequent call to cbf_set_realarray, | if a copy of the arry is to be made into another CIF or CBF. | The variants cbf_get_integerarrayparameters_wdims and | cbf_get_realarrayparameters_wdims set **byteorder, *dim1, *dim2, | *dim3, and *padding as well, providing the additional parameters | needed for a subsequent call to cbf_set_integerarray_wdims or | cbf_set_realarray_wdims. | The value returned in *byteorder is a pointer either to the string | "little_endian" or to the string "big_endian". This should be the | byte order of the data, not necessarily of the host machine. No | attempt should be made to modify this string. At this time only | "little_endian" will be returned. | The values returned in *dim1, *dim2 and *dim3 are the sizes of the | fastest changing, second fastest changing and third fastest changing | dimensions of the array, if specified, or zero, if not specified. | The value returned in *padding is the size of the post-data padding, | if any and if specified in the data header. The value is given as a | count of octets. | If the value is not binary, the function returns CBF_ASCII. | ARGUMENTS | handle CBF handle. compression Compression method used. elsize | Size in bytes of each array element. binary_id Pointer to the | destination integer binary identifier. elsigned Pointer to an | integer. Set to 1 if the elements can be read as signed integers. | elunsigned Pointer to an integer. Set to 1 if the elements can be | read as unsigned integers. elements Pointer to the destination | number of elements. minelement Pointer to the destination smallest | element. maxelement Pointer to the destination largest element. | byteorder Pointer to the destination byte order. dim1 Pointer to | the destination fastest dimension. dim2 Pointer to the destination | second fastest dimension. dim3 Pointer to the destination third | fastest dimension. padding Pointer to the destination padding size. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | get_realarrayparameters_wdims(*args) | get_realarrayparameters_wdims(self, void ?) | | get_reciprocal_cell(*args) | get_reciprocal_cell(self, void ?) | | get_timestamp(*args) | Returns : Float time,Integer timezone | *args : | | C prototype: int cbf_get_timestamp (cbf_handle handle, unsigned int reserved, | double *time, int *timezone); | | CBFLib documentation: | DESCRIPTION | cbf_get_timestamp sets *time to the collection timestamp in seconds | since January 1 1970. *timezone is set to timezone difference from | UTC in minutes. The parameter reserved is presently unused and should | be set to 0. | Either of the destination pointers may be NULL. | ARGUMENTS | handle CBF handle. reserved Unused. Any value other than 0 is | invalid. time Pointer to the destination collection timestamp. | timezone Pointer to the destination timezone difference. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | get_typeofvalue(*args) | Returns : | *args : string | | C prototype: int cbf_get_typeofvalue (cbf_handle handle, | const char **typeofvalue); | | CBFLib documentation: | DESCRIPTION | cbf_get_value sets *typeofvalue to point an ASCII descriptor of the | value of the item at the current column and row. The strings that may | be returned are "null" for a null value indicated by a "." or a | "?", "bnry" for a binary value, "word" for an unquoted string, | "dblq" for a double-quoted string, "sglq" for a single-quoted | string, and "text" for a semicolon-quoted text field. A field for | which no value has been set sets *typeofvalue to NULL rather than to | the string "null". | The typeofvalue must not be modified by the program in any way. | ARGUMENTS | handle CBF handle. typeofvalue Pointer to the destination | type-of-value string pointer. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | get_unit_cell(*args) | get_unit_cell(self, void ?) | | get_value(*args) | Returns : | *args : string | | C prototype: int cbf_get_value (cbf_handle handle, const char **value); | | CBFLib documentation: | DESCRIPTION | cbf_get_value sets *value to point to the ASCII value of the item at | the current column and row. cbf_set_value sets *value to point to the | ASCII value of the item at the current column and row, creating the | data item if necessary and initializing it to a copy of defaultvalue. | If the value is not ASCII, the function returns CBF_BINARY. | The value will be valid as long as the item exists and has not been | set to a new value. | The value must not be modified by the program in any way. | ARGUMENTS | handle CBF handle. value Pointer to the destination value | pointer. value Default value character string. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | get_wavelength(*args) | Returns : double | *args : | | C prototype: int cbf_get_wavelength (cbf_handle handle, double *wavelength); | | CBFLib documentation: | DESCRIPTION | cbf_get_wavelength sets *wavelength to the current wavelength in | Angstrom. | ARGUMENTS | handle CBF handle. wavelength Pointer to the destination. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | insert_row(*args) | Returns : | *args : Integer | | C prototype: int cbf_insert_row (cbf_handle handle, unsigned int rownumber); | | CBFLib documentation: | DESCRIPTION | cbf_insert_row adds a new row to the current category. The new row is | inserted as row rownumber and existing rows starting from rownumber | are moved up by 1. The new row becomes the current row. | If the category has fewer than rownumber rows, the function returns | CBF_NOTFOUND. | The row numbers start from 0. | ARGUMENTS | handle CBF handle. rownumber The row number of the new row. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | new_category(*args) | Returns : string | *args : | | C prototype: int cbf_new_category (cbf_handle handle, | const char *categoryname); | | CBFLib documentation: | DESCRIPTION | cbf_new_category creates a new category in the current data block | with name categoryname and makes it the current category. | If a category with this name already exists, the existing category | becomes the current category. | ARGUMENTS | handle CBF handle. categoryname The name of the new | category. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | new_column(*args) | Returns : string | *args : | | C prototype: int cbf_new_column (cbf_handle handle, const char *columnname); | | CBFLib documentation: | DESCRIPTION | cbf_new_column creates a new column in the current category with name | columnname and makes it the current column. | If a column with this name already exists, the existing column | becomes the current category. | ARGUMENTS | handle CBF handle. columnname The name of the new column. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | new_datablock(*args) | Returns : string | *args : | | C prototype: int cbf_new_datablock (cbf_handle handle, | const char *datablockname); | | CBFLib documentation: | DESCRIPTION | cbf_new_datablock creates a new data block with name datablockname | and makes it the current data block. cbf_new_saveframe creates a new | save frame with name saveframename within the current data block and | makes the new save frame the current save frame. | If a data block or save frame with this name already exists, the | existing data block or save frame becomes the current data block or | save frame. | ARGUMENTS | handle CBF handle. datablockname The name of the new data | block. saveframename The name of the new save frame. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | new_row(*args) | Returns : | *args : | | C prototype: int cbf_new_row (cbf_handle handle); | | CBFLib documentation: | DESCRIPTION | cbf_new_row adds a new row to the current category and makes it the | current row. | ARGUMENTS | handle CBF handle. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | new_saveframe(*args) | Returns : string | *args : | | C prototype: int cbf_new_saveframe (cbf_handle handle, | const char *saveframename); | | CBFLib documentation: | DESCRIPTION | cbf_new_datablock creates a new data block with name datablockname | and makes it the current data block. cbf_new_saveframe creates a new | save frame with name saveframename within the current data block and | makes the new save frame the current save frame. | If a data block or save frame with this name already exists, the | existing data block or save frame becomes the current data block or | save frame. | ARGUMENTS | handle CBF handle. datablockname The name of the new data | block. saveframename The name of the new save frame. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | next_category(*args) | Returns : | *args : | | C prototype: int cbf_next_category (cbf_handle handle); | | CBFLib documentation: | DESCRIPTION | cbf_next_category makes the category following the current category | in the current data block the current category. | If there are no more categories, the function returns CBF_NOTFOUND. | The current column and row become undefined. | ARGUMENTS | handle CBF handle. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | next_column(*args) | Returns : | *args : | | C prototype: int cbf_next_column (cbf_handle handle); | | CBFLib documentation: | DESCRIPTION | cbf_next_column makes the column following the current column in the | current category the current column. | If there are no more columns, the function returns CBF_NOTFOUND. | The current row is not affected. | ARGUMENTS | handle CBF handle. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | next_datablock(*args) | Returns : | *args : | | C prototype: int cbf_next_datablock (cbf_handle handle); | | CBFLib documentation: | DESCRIPTION | cbf_next_datablock makes the data block following the current data | block the current data block. | If there are no more data blocks, the function returns CBF_NOTFOUND. | The current category becomes undefined. | ARGUMENTS | handle CBF handle. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | next_row(*args) | Returns : | *args : | | C prototype: int cbf_next_row (cbf_handle handle); | | CBFLib documentation: | DESCRIPTION | cbf_next_row makes the row following the current row in the current | category the current row. | If there are no more rows, the function returns CBF_NOTFOUND. | The current column is not affected. | ARGUMENTS | handle CBF handle. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | read_file(*args) | Returns : | *args : String filename,Integer headers | | C prototype: int cbf_read_file (cbf_handle handle, FILE *file, int headers); | | CBFLib documentation: | DESCRIPTION | cbf_read_file reads the CBF or CIF file file into the CBF object | specified by handle, using the CIF 1.0 convention of 80 character | lines. cbf_read_widefile reads the CBF or CIF file file into the CBF | object specified by handle, using the CIF 1.1 convention of 2048 | character lines. A warning is issued to stderr for ascii lines over | the limit. No test is performed on binary sections. | Validation is performed in three ways levels: during the lexical | scan, during the parse, and, if a dictionary was converted, against | the value types, value enumerations, categories and parent-child | relationships specified in the dictionary. | headers controls the interprestation of binary section headers of | imgCIF files. | MSG_DIGEST: Instructs CBFlib to check that the digest of the binary | section matches any header value. If the digests do not match, the | call will return CBF_FORMAT. This evaluation and comparison is | delayed (a "lazy" evaluation) to ensure maximal processing | efficiency. If an immediately evaluation is required, see | MSG_DIGESTNOW, below. MSG_DIGESTNOW: Instructs CBFlib to check that | the digest of the binary section matches any header value. If the | digests do not match, the call will return CBF_FORMAT. This | evaluation and comparison is performed during initial parsing of the | section to ensure timely error reporting at the expense of processing | efficiency. If a more efficient delayed ("lazy") evaluation is | required, see MSG_DIGESTNOW, below. MSG_NODIGEST: Do not check the | digest (default). | CBFlib defers reading binary sections as long as possible. In the | current version of CBFlib, this means that: | 1. The file must be a random-access file opened in binary mode (fopen | | read_template(*args) | Returns : | *args : String filename | | C prototype: int cbf_read_template (cbf_handle handle, FILE *file); | | CBFLib documentation: | DESCRIPTION | cbf_read_template reads the CBF or CIF file file into the CBF object | specified by handle and selects the first datablock as the current | datablock. | ARGUMENTS | handle Pointer to a CBF handle. file Pointer to a file | descriptor. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | read_widefile(*args) | read_widefile(self, void ?) | | remove_category(*args) | Returns : | *args : | | C prototype: int cbf_remove_category (cbf_handle handle); | | CBFLib documentation: | DESCRIPTION | cbf_remove_category deletes the current category. | The current category becomes undefined. | ARGUMENTS | handle CBF handle. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | remove_column(*args) | Returns : | *args : | | C prototype: int cbf_remove_column (cbf_handle handle); | | CBFLib documentation: | DESCRIPTION | cbf_remove_column deletes the current column. | The current column becomes undefined. | ARGUMENTS | handle CBF handle. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | remove_datablock(*args) | Returns : | *args : | | C prototype: int cbf_remove_datablock (cbf_handle handle); | | CBFLib documentation: | DESCRIPTION | cbf_remove_datablock deletes the current data block. | cbf_remove_saveframe deletes the current save frame. | The current data block becomes undefined. | ARGUMENTS | handle CBF handle. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | remove_row(*args) | Returns : | *args : | | C prototype: int cbf_remove_row (cbf_handle handle); | | CBFLib documentation: | DESCRIPTION | cbf_remove_row deletes the current row in the current category. | If the current row was the last row, it will move down by 1, | otherwise, it will remain the same. | ARGUMENTS | handle CBF handle. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | remove_saveframe(*args) | Returns : | *args : | | C prototype: int cbf_remove_saveframe (cbf_handle handle); | | CBFLib documentation: | DESCRIPTION | cbf_remove_datablock deletes the current data block. | cbf_remove_saveframe deletes the current save frame. | The current data block becomes undefined. | ARGUMENTS | handle CBF handle. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | require_category(*args) | Returns : string | *args : | | C prototype: int cbf_require_category (cbf_handle handle, | const char *categoryname); | | CBFLib documentation: | DESCRIPTION | cbf_rewuire_category makes the category in the current data block | with name categoryname the current category, if it exists, or creates | the catagory if it does not exist. | The comparison is case-insensitive. | The current column and row become undefined. | ARGUMENTS | handle CBF handle. categoryname The name of the category to | find. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | require_category_root(*args) | require_category_root(self, char categoryname) -> char | | require_column(*args) | Returns : string | *args : | | C prototype: int cbf_require_column (cbf_handle handle, | const char *columnname); | | CBFLib documentation: | DESCRIPTION | cbf_require_column makes the columns in the current category with | name columnname the current column, if it exists, or creates it if it | does not. | The comparison is case-insensitive. | The current row is not affected. | ARGUMENTS | handle CBF handle. columnname The name of column to find. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | require_column_doublevalue(*args) | Returns : Float defaultvalue | *args : String columnname,Float Value | | C prototype: int cbf_require_column_doublevalue (cbf_handle handle, | const char *columnname, double *number, | const double defaultvalue); | | CBFLib documentation: | DESCRIPTION | cbf_require_column_doublevalue sets *number to the value of the ASCII | item at the current row for the column given with the name given by | *columnname, with the value interpreted as a decimal floating-point | number, or to the number given by defaultvalue if the item cannot be | found. | ARGUMENTS | handle CBF handle. columnname Name of the column containing the | number. number pointer to the location to receive the | floating-point value. defaultvalue Value to use if the requested | column and value cannot be found. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | require_column_integervalue(*args) | Returns : Int Value | *args : String Columnvalue,Int default | | C prototype: int cbf_require_column_integervalue (cbf_handle handle, | const char *columnname, int *number, | const int defaultvalue); | | CBFLib documentation: | DESCRIPTION | cbf_require_column_doublevalue sets *number to the value of the ASCII | item at the current row for the column given with the name given by | *columnname, with the value interpreted as an integer number, or to | the number given by defaultvalue if the item cannot be found. | ARGUMENTS | handle CBF handle. columnname Name of the column containing the | number. number pointer to the location to receive the integer | value. defaultvalue Value to use if the requested column and value | cannot be found. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | require_column_value(*args) | Returns : String Name | *args : String columnnanme,String Default | | C prototype: int cbf_require_column_value (cbf_handle handle, | const char *columnname, const char **value, | const char *defaultvalue); | | CBFLib documentation: | DESCRIPTION | cbf_require_column_doublevalue sets *value to the ASCII item at the | current row for the column given with the name given by *columnname, | or to the string given by defaultvalue if the item cannot be found. | ARGUMENTS | handle CBF handle. columnname Name of the column containing the | number. value pointer to the location to receive the value. | defaultvalue Value to use if the requested column and value cannot | be found. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | require_datablock(*args) | Returns : string | *args : | | C prototype: int cbf_require_datablock (cbf_handle handle, | const char *datablockname); | | CBFLib documentation: | DESCRIPTION | cbf_require_datablock makes the data block with name datablockname | the current data block, if it exists, or creates it if it does not. | The comparison is case-insensitive. | The current category becomes undefined. | ARGUMENTS | handle CBF handle. datablockname The name of the data | block to find or create. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | require_doublevalue(*args) | Returns : Float Number | *args : Float Default | | C prototype: int cbf_require_doublevalue (cbf_handle handle, double *number, | double defaultvalue); | | CBFLib documentation: | DESCRIPTION | cbf_get_doublevalue sets *number to the value of the ASCII item at | the current column and row interpreted as a decimal floating-point | number. cbf_require_doublevalue sets *number to the value of the | ASCII item at the current column and row interpreted as a decimal | floating-point number, setting it to defaultvalue if necessary. | If the value is not ASCII, the function returns CBF_BINARY. | ARGUMENTS | handle CBF handle. number Pointer to the destination | number. defaultvalue default number value. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | require_integervalue(*args) | Returns : Int number | *args : Int thedefault | | C prototype: int cbf_require_integervalue (cbf_handle handle, int *number, | int defaultvalue); | | CBFLib documentation: | DESCRIPTION | cbf_get_integervalue sets *number to the value of the ASCII item at | the current column and row interpreted as a decimal integer. | cbf_require_integervalue sets *number to the value of the ASCII item | at the current column and row interpreted as a decimal integer, | setting it to defaultvalue if necessary. | If the value is not ASCII, the function returns CBF_BINARY. | ARGUMENTS | handle CBF handle. number pointer to the number. | defaultvalue default number value. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | require_tag_root(*args) | Returns : String tagroot | *args : String tagname | | C prototype: int cbf_require_tag_root (cbf_handle handle, const char* tagname, | const char** tagroot); | | CBFLib documentation: | DESCRIPTION | cbf_find_tag_root sets *tagroot to the root tag of which tagname is | an alias. cbf_set_tag_root sets tagname as an alias of tagroot_in in | the dictionary associated with handle, creating the dictionary if | necessary. cbf_require_tag_root sets *tagroot to the root tag of | which tagname is an alias, if there is one, or to the value of | tagname, if tagname is not an alias. | A returned tagroot string must not be modified in any way. | ARGUMENTS | handle CBF handle. tagname tag name which may be an alias. | tagroot pointer to a returned tag root name. tagroot_in input | tag root name. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | require_value(*args) | Returns : String Value | *args : String defaultvalue | | C prototype: int cbf_require_value (cbf_handle handle, const char **value, | const char *defaultvalue ); | | CBFLib documentation: | DESCRIPTION | cbf_get_value sets *value to point to the ASCII value of the item at | the current column and row. cbf_set_value sets *value to point to the | ASCII value of the item at the current column and row, creating the | data item if necessary and initializing it to a copy of defaultvalue. | If the value is not ASCII, the function returns CBF_BINARY. | The value will be valid as long as the item exists and has not been | set to a new value. | The value must not be modified by the program in any way. | ARGUMENTS | handle CBF handle. value Pointer to the destination value | pointer. value Default value character string. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | reset_category(*args) | Returns : | *args : | | C prototype: int cbf_reset_category (cbf_handle handle); | | CBFLib documentation: | DESCRIPTION | cbf_reset_category deletes all columns and rows from current category. | ARGUMENTS | handle CBF handle. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | reset_datablock(*args) | Returns : | *args : | | C prototype: int cbf_reset_datablock (cbf_handle handle); | | CBFLib documentation: | DESCRIPTION | cbf_reset_datablock deletes all categories from the current data | block. cbf_reset_saveframe deletes all categories from the current | save frame. | ARGUMENTS | handle CBF handle. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | reset_datablocks(*args) | Returns : | *args : | | C prototype: int cbf_reset_datablocks (cbf_handle handle); | | CBFLib documentation: | DESCRIPTION | cbf_reset_datablocks deletes all categories from all data blocks. | The current data block does not change. | ARGUMENTS | handle CBF handle. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | reset_saveframe(*args) | Returns : | *args : | | C prototype: int cbf_reset_saveframe (cbf_handle handle); | | CBFLib documentation: | DESCRIPTION | cbf_reset_datablock deletes all categories from the current data | block. cbf_reset_saveframe deletes all categories from the current | save frame. | ARGUMENTS | handle CBF handle. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | rewind_blockitem(*args) | Returns : CBF_NODETYPE | *args : | | C prototype: int cbf_rewind_blockitem (cbf_handle handle, | CBF_NODETYPE * type); | | CBFLib documentation: | DESCRIPTION | cbf_rewind_category makes the first category in the current data | block the current category. cbf_rewind_saveframe makes the first | saveframe in the current data block the current saveframe. | cbf_rewind_blockitem makes the first blockitem (category or | saveframe) in the current data block the current blockitem. | If there are no categories, saveframes or blockitems the function | returns CBF_NOTFOUND. | The current column and row become undefined. | ARGUMENTS | handle CBF handle. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | rewind_category(*args) | Returns : | *args : | | C prototype: int cbf_rewind_category (cbf_handle handle); | | CBFLib documentation: | DESCRIPTION | cbf_rewind_category makes the first category in the current data | block the current category. cbf_rewind_saveframe makes the first | saveframe in the current data block the current saveframe. | cbf_rewind_blockitem makes the first blockitem (category or | saveframe) in the current data block the current blockitem. | If there are no categories, saveframes or blockitems the function | returns CBF_NOTFOUND. | The current column and row become undefined. | ARGUMENTS | handle CBF handle. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | rewind_column(*args) | Returns : | *args : | | C prototype: int cbf_rewind_column (cbf_handle handle); | | CBFLib documentation: | DESCRIPTION | cbf_rewind_column makes the first column in the current category the | current column. | If there are no columns, the function returns CBF_NOTFOUND. | The current row is not affected. | ARGUMENTS | handle CBF handle. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | rewind_datablock(*args) | Returns : | *args : | | C prototype: int cbf_rewind_datablock (cbf_handle handle); | | CBFLib documentation: | DESCRIPTION | cbf_rewind_datablock makes the first data block the current data | block. | If there are no data blocks, the function returns CBF_NOTFOUND. | The current category becomes undefined. | ARGUMENTS | handle CBF handle. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | rewind_row(*args) | Returns : | *args : | | C prototype: int cbf_rewind_row (cbf_handle handle); | | CBFLib documentation: | DESCRIPTION | cbf_rewind_row makes the first row in the current category the | current row. | If there are no rows, the function returns CBF_NOTFOUND. | The current column is not affected. | ARGUMENTS | handle CBF handle. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | rewind_saveframe(*args) | Returns : | *args : | | C prototype: int cbf_rewind_saveframe (cbf_handle handle); | | CBFLib documentation: | DESCRIPTION | cbf_rewind_category makes the first category in the current data | block the current category. cbf_rewind_saveframe makes the first | saveframe in the current data block the current saveframe. | cbf_rewind_blockitem makes the first blockitem (category or | saveframe) in the current data block the current blockitem. | If there are no categories, saveframes or blockitems the function | returns CBF_NOTFOUND. | The current column and row become undefined. | ARGUMENTS | handle CBF handle. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | row_number(*args) | Returns : Integer | *args : | | C prototype: int cbf_row_number (cbf_handle handle, unsigned int *row); | | CBFLib documentation: | DESCRIPTION | cbf_row_number sets *row to the number of the current row of the | current category. | ARGUMENTS | handle CBF handle. row Pointer to the destination row number. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | select_category(*args) | Returns : | *args : Integer | | C prototype: int cbf_select_category (cbf_handle handle, | unsigned int category); | | CBFLib documentation: | DESCRIPTION | cbf_select_category selects category number category in the current | data block as the current category. | The first category is number 0. | The current column and row become undefined. | If the category does not exist, the function returns CBF_NOTFOUND. | ARGUMENTS | handle CBF handle. category Number of the category to select. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | select_column(*args) | Returns : | *args : Integer | | C prototype: int cbf_select_column (cbf_handle handle, unsigned int column); | | CBFLib documentation: | DESCRIPTION | cbf_select_column selects column number column in the current | category as the current column. | The first column is number 0. | The current row is not affected | If the column does not exist, the function returns CBF_NOTFOUND. | ARGUMENTS | handle CBF handle. column Number of the column to select. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | select_datablock(*args) | Returns : | *args : Integer | | C prototype: int cbf_select_datablock (cbf_handle handle, | unsigned int datablock); | | CBFLib documentation: | DESCRIPTION | cbf_select_datablock selects data block number datablock as the | current data block. | The first data block is number 0. | If the data block does not exist, the function returns CBF_NOTFOUND. | ARGUMENTS | handle CBF handle. datablock Number of the data block to | select. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | select_row(*args) | Returns : | *args : Integer | | C prototype: int cbf_select_row (cbf_handle handle, unsigned int row); | | CBFLib documentation: | DESCRIPTION | cbf_select_row selects row number row in the current category as the | current row. | The first row is number 0. | The current column is not affected | If the row does not exist, the function returns CBF_NOTFOUND. | ARGUMENTS | handle CBF handle. row Number of the row to select. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | set_3d_image(*args) | set_3d_image(self, void ?) | | set_axis_setting(*args) | Returns : | *args : String axis_id,Float start,Float increment | | C prototype: int cbf_set_axis_setting (cbf_handle handle, | unsigned int reserved, const char *axis_id, double start, | double increment); | | CBFLib documentation: | DESCRIPTION | cbf_set_axis_setting sets the starting and increment values of the | axis axis_id to start and increment. | The parameter reserved is presently unused and should be set to 0. | ARGUMENTS | handle CBF handle. reserved Unused. Any value other than 0 is | invalid. axis_id Axis id. start Start value. increment | Increment value. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | set_bin_sizes(*args) | set_bin_sizes(self, void ?) | | set_category_root(*args) | Returns : | *args : String categoryname,String categoryroot | | C prototype: int cbf_set_category_root (cbf_handle handle, | const char* categoryname_in, const char*categoryroot); | | CBFLib documentation: | DESCRIPTION | cbf_find_category_root sets *categoryroot to the root category of | which categoryname is an alias. cbf_set_category_root sets | categoryname_in as an alias of categoryroot in the dictionary | associated with handle, creating the dictionary if necessary. | cbf_require_category_root sets *categoryroot to the root category of | which categoryname is an alias, if there is one, or to the value of | categoryname, if categoryname is not an alias. | A returned categoryroot string must not be modified in any way. | ARGUMENTS | handle CBF handle. categoryname category name which | may be an alias. categoryroot pointer to a returned category | root name. categoryroot_in input category root name. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | set_crystal_id(*args) | Returns : string | *args : | | C prototype: int cbf_set_crystal_id (cbf_handle handle, | const char *crystal_id); | | CBFLib documentation: | DESCRIPTION | cbf_set_crystal_id sets the "diffrn.crystal_id" entry to the ASCII | value crystal_id. | ARGUMENTS | handle CBF handle. crystal_id ASCII value. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | set_datablockname(*args) | Returns : string | *args : | | C prototype: int cbf_set_datablockname (cbf_handle handle, | const char *datablockname); | | CBFLib documentation: | DESCRIPTION | cbf_set_datablockname changes the name of the current data block to | datablockname. cbf_set_saveframename changes the name of the current | save frame to saveframename. | If a data block or save frame with this name already exists | (comparison is case-insensitive), the function returns CBF_IDENTICAL. | ARGUMENTS | handle CBF handle. datablockname The new data block name. | datablockname The new save frame name. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | set_datestamp(*args) | Returns : | *args : int year,int month,int day,int hour,int minute,double second, | int timezone,Float precision | | C prototype: int cbf_set_datestamp (cbf_handle handle, unsigned int reserved, | int year, int month, int day, int hour, int minute, | double second, int timezone, double precision); | | CBFLib documentation: | DESCRIPTION | cbf_set_datestamp sets the collection timestamp in seconds since | January 1 1970 to the value specified by time. The timezone | difference from UTC in minutes is set to timezone. If no timezone is | desired, timezone should be CBF_NOTIM EZONE. The parameter reserved | is presently unused and should be set to 0. | The precision of the new timestamp is specified by the value | precision in seconds. If precision is 0, the saved timestamp is | assumed accurate to 1 second. | ARGUMENTS | handle CBF handle. reserved Unused. Any value other than 0 is | invalid. time Timestamp in seconds since January 1 1970. | timezone Timezone difference from UTC in minutes or CBF_NOTIMEZONE. | precision Timestamp precision in seconds. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | set_dictionary(*args) | Returns : | *args : CBFHandle dictionary | | C prototype: int cbf_set_dictionary (cbf_handle handle, | cbf_handle dictionary_in); | | CBFLib documentation: | DESCRIPTION | cbf_get_dictionary sets *dictionary to the handle of a CBF which has | been associated with the CBF handle by cbf_set_dictionary. | cbf_set_dictionary associates the CBF handle dictionary_in with | handle as its dictionary. cbf_require_dictionary sets *dictionary to | the handle of a CBF which has been associated with the CBF handle by | cbf_set_dictionary or creates a new empty CBF and associates it with | handle, returning the new handle in *dictionary. | ARGUMENTS | handle CBF handle. dictionary Pointer to CBF handle of | dictionary. dictionary_in CBF handle of dcitionary. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | set_diffrn_id(*args) | Returns : string | *args : | | C prototype: int cbf_set_diffrn_id (cbf_handle handle, const char *diffrn_id); | | CBFLib documentation: | DESCRIPTION | cbf_set_diffrn_id sets the "diffrn.id" entry of the current | datablock to the ASCII value diffrn_id. | This function also changes corresponding "diffrn_id" entries in the | "diffrn_source", "diffrn_radiation", "diffrn_detector" and | "diffrn_measurement" categories. | ARGUMENTS | handle CBF handle. diffrn_id ASCII value. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | set_divergence(*args) | Returns : | *args : Float div_x_source,Float div_y_source,Float div_x_y_source | | C prototype: int cbf_set_divergence (cbf_handle handle, double div_x_source, | double div_y_source, double div_x_y_source); | | CBFLib documentation: | DESCRIPTION | cbf_set_divergence sets the source divergence parameters to the | values specified by div_x_source, div_y_source and div_x_y_source. | ARGUMENTS | handle CBF handle. div_x_source New value of | div_x_source. div_y_source New value of div_y_source. | div_x_y_source New value of div_x_y_source. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | set_doublevalue(*args) | Returns : | *args : String format,Float number | | C prototype: int cbf_set_doublevalue (cbf_handle handle, const char *format, | double number); | | CBFLib documentation: | DESCRIPTION | cbf_set_doublevalue sets the item at the current column and row to | the floating-point value number written as an ASCII string with the | format specified by format as appropriate for the printf function. | ARGUMENTS | handle CBF handle. format Format for the number. number | Floating-point value. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | set_gain(*args) | Returns : | *args : Float gain,Float gain_esd | | C prototype: int cbf_set_gain (cbf_handle handle, unsigned int element_number, | double gain, double gain_esd); | | CBFLib documentation: | DESCRIPTION | cbf_set_gain sets the gain of element number element_number to the | values specified by gain and gain_esd. | ARGUMENTS | handle CBF handle. element_number The number of the detector | element counting from 0 by order of appearance in the | "diffrn_data_frame" category. gain New gain value. gain_esd New | gain_esd value. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | set_image(*args) | set_image(self, void ?) | | set_integerarray(*args) | Returns : | *args : int compression,int binary_id,(binary) String data,int elsize, | int elsigned,int elements | | C prototype: int cbf_set_integerarray (cbf_handle handle, | unsigned int compression, int binary_id, void *array, | size_t elsize, int elsigned, size_t elements); | | CBFLib documentation: | DESCRIPTION | cbf_set_integerarray sets the binary value of the item at the current | column and row to an integer array. The array consists of elements | elements of elsize bytes each, starting at array. The elements are | signed if elsigned is non-0 and unsigned otherwise. binary_id is the | binary section identifier. cbf_set_realarray sets the binary value of | the item at the current column and row to an integer array. The array | consists of elements elements of elsize bytes each, starting at | array. binary_id is the binary section identifier. | The cbf_set_integerarray_wdims and cbf_set_realarray_wdims allow the | data header values of byteorder, dim1, dim2, dim3 and padding to be | set to the data byte order, the fastest, second fastest and third | fastest array dimensions and the size in byte of the post data | padding to be used. | The array will be compressed using the compression scheme specifed by | compression. Currently, the available schemes are: | CBF_CANONICAL Canonical-code compression (section 3.3.1) CBF_PACKED | CCP4-style packing (section 3.3.2) CBF_PACKED_V2 CCP4-style | packing, version 2 (section 3.3.2) CBF_BYTE_OFFSET Simple | "byte_offset" compression. CBF_NONE No compression. NOTE: This | scheme is by far the slowest of the four and uses much more disk | space. It is intended for routine use with small arrays only. With | large arrays (like images) it should be used only for debugging. | The values compressed are limited to 64 bits. If any element in the | array is larger than 64 bits, the value compressed is the nearest | 64-bit value. | | set_integerarray_wdims(*args) | set_integerarray_wdims(self, void ?) | | set_integervalue(*args) | Returns : int number | *args : | | C prototype: int cbf_set_integervalue (cbf_handle handle, int number); | | CBFLib documentation: | DESCRIPTION | cbf_set_integervalue sets the item at the current column and row to | the integer value number written as a decimal ASCII string. | ARGUMENTS | handle CBF handle. number Integer value. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | set_integration_time(*args) | Returns : | *args : Float time | | C prototype: int cbf_set_integration_time (cbf_handle handle, | unsigned int reserved, double time); | | CBFLib documentation: | DESCRIPTION | cbf_set_integration_time sets the integration time in seconds to the | value specified by time. The parameter reserved is presently unused | and should be set to 0. | ARGUMENTS | handle CBF handle. reserved Unused. Any value | other than 0 is invalid. time Integration time in seconds. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | set_orientation_matrix(*args) | Returns : | *args : Float matrix_0,Float matrix_1,Float matrix_2,Float matrix_3, | Float matrix_4,Float matrix_5,Float matrix_6,Float matrix_7, | Float matrix_8 | | C prototype: int cbf_set_orientation_matrix (cbf_handle handle, | double ub_matrix[9]); | | CBFLib documentation: | DESCRIPTION | cbf_get_orientation_matrix sets ub_matrix to point to the array of | orientation matrix entries in the "diffrn" category in the order of | columns: | "UB[1][1]" "UB[1][2]" "UB[1][3]" "UB[2][1]" "UB[2][2]" | "UB[2][3]" "UB[3][1]" "UB[3][2]" "UB[3][3]" | cbf_set_orientation_matrix sets the values in the "diffrn" category | to the values pointed to by ub_matrix. | ARGUMENTS | handle CBF handle. ubmatric Source or destination array of 9 | doubles giving the orientation matrix parameters. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | set_overload(*args) | Returns : | *args : Integer element_number,Float overload | | C prototype: int cbf_set_overload (cbf_handle handle, | unsigned int element_number, double overload); | | CBFLib documentation: | DESCRIPTION | cbf_set_overload sets the overload value of element number | element_number to overload. | ARGUMENTS | handle CBF handle. element_number The number of the detector | element counting from 0 by order of appearance in the | "diffrn_data_frame" category. overload New overload value. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | set_pixel_size(*args) | Returns : | *args : Int element_number,Int axis_number,Float pixel size | | C prototype: int cbf_set_pixel_size (cbf_handle handle, | unsigned int element_number, unsigned int axis_number, | double psize); | | CBFLib documentation: | DESCRIPTION | cbf_set_pixel_size sets the item in the "e;size"e; column of | the "array_structure_list" category at the row which matches axis | axis_number of the detector element element_number converting the | double pixel size psize from meters to millimeters in storing it in | the "size" column for the axis axis_number of the detector element | element_number. The axis_number is numbered from 1, starting with the | fastest axis. | If the "array_structure_list" category does not already exist, it | is created. | If the appropriate row in the "array_structure_list" catgeory does | not already exist, it is created. | If the pixel size is not given explcitly in the "array_element_size | category", the function returns CBF_NOTFOUND. | ARGUMENTS | handle CBF handle. element_number The number of the detector | element counting from 0 by order of appearance in the | "diffrn_data_frame" category. axis_number The number of the axis, | fastest first, starting from 1. | | set_polarization(*args) | Returns : | *args : Float polarizn_source_ratio,Float polarizn_source_norm | | C prototype: int cbf_set_polarization (cbf_handle handle, | double polarizn_source_ratio, double polarizn_source_norm); | | CBFLib documentation: | DESCRIPTION | cbf_set_polarization sets the source polarization to the values | specified by polarizn_source_ratio and polarizn_source_norm. | ARGUMENTS | handle CBF handle. polarizn_source_ratio New value | of polarizn_source_ratio. polarizn_source_norm New value of | polarizn_source_norm. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | set_real_3d_image(*args) | set_real_3d_image(self, void ?) | | set_real_image(*args) | set_real_image(self, void ?) | | set_realarray(*args) | set_realarray(self, void ?) | | set_realarray_wdims(*args) | set_realarray_wdims(self, void ?) | | set_reciprocal_cell(*args) | set_reciprocal_cell(self, void ?) | | set_tag_category(*args) | Returns : | *args : String tagname,String categoryname_in | | C prototype: int cbf_set_tag_category (cbf_handle handle, const char* tagname, | const char* categoryname_in); | | CBFLib documentation: | DESCRIPTION | cbf_find_tag_category sets categoryname to the category associated | with tagname in the dictionary associated with handle. | cbf_set_tag_category upddates the dictionary associated with handle | to indicated that tagname is in category categoryname_in. | ARGUMENTS | handle CBF handle. tagname tag name. | categoryname pointer to a returned category name. | categoryname_in input category name. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | set_tag_root(*args) | Returns : | *args : String tagname,String tagroot_in | | C prototype: int cbf_set_tag_root (cbf_handle handle, const char* tagname, | const char*tagroot_in); | | CBFLib documentation: | DESCRIPTION | cbf_find_tag_root sets *tagroot to the root tag of which tagname is | an alias. cbf_set_tag_root sets tagname as an alias of tagroot_in in | the dictionary associated with handle, creating the dictionary if | necessary. cbf_require_tag_root sets *tagroot to the root tag of | which tagname is an alias, if there is one, or to the value of | tagname, if tagname is not an alias. | A returned tagroot string must not be modified in any way. | ARGUMENTS | handle CBF handle. tagname tag name which may be an alias. | tagroot pointer to a returned tag root name. tagroot_in input | tag root name. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | set_timestamp(*args) | Returns : | *args : Float time,Integer timezone,Float precision | | C prototype: int cbf_set_timestamp (cbf_handle handle, unsigned int reserved, | double time, int timezone, double precision); | | CBFLib documentation: | DESCRIPTION | cbf_set_timestamp sets the collection timestamp in seconds since | January 1 1970 to the value specified by time. The timezone | difference from UTC in minutes is set to timezone. If no timezone is | desired, timezone should be CBF_NOTIM EZONE. The parameter reserved | is presently unused and should be set to 0. | The precision of the new timestamp is specified by the value | precision in seconds. If precision is 0, the saved timestamp is | assumed accurate to 1 second. | ARGUMENTS | handle CBF handle. reserved Unused. Any value other than 0 is | invalid. time Timestamp in seconds since January 1 1970. timezone | Timezone difference from UTC in minutes or CBF_NOTIMEZONE. precision | Timestamp precision in seconds. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | set_typeofvalue(*args) | Returns : string | *args : | | C prototype: int cbf_set_typeofvalue (cbf_handle handle, | const char *typeofvalue); | | CBFLib documentation: | DESCRIPTION | cbf_set_typeofvalue sets the type of the item at the current column | and row to the type specified by the ASCII character string given by | typeofvalue. The strings that may be used are "null" for a null | value indicated by a "." or a "?", "word" for an unquoted | string, "dblq" for a double-quoted string, "sglq" for a | single-quoted string, and "text" for a semicolon-quoted text field. | Not all types may be used for all values. No changes may be made to | the type of binary values. You may not set the type of a string that | contains a single quote followed by a blank or a tab or which | contains multiple lines to "sglq". You may not set the type of a | string that contains a double quote followed by a blank or a tab or | which contains multiple lines to "dblq". | ARGUMENTS | handle CBF handle. typeofvalue ASCII string for desired type | of value. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | set_unit_cell(*args) | set_unit_cell(self, void ?) | | set_value(*args) | Returns : string | *args : | | C prototype: int cbf_set_value (cbf_handle handle, const char *value); | | CBFLib documentation: | DESCRIPTION | cbf_set_value sets the item at the current column and row to the | ASCII value value. | ARGUMENTS | handle CBF handle. value ASCII value. defaultvalue | default ASCII value. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | set_wavelength(*args) | Returns : double wavelength | *args : | | C prototype: int cbf_set_wavelength (cbf_handle handle, double wavelength); | | CBFLib documentation: | DESCRIPTION | cbf_set_wavelength sets the current wavelength in Angstrom to | wavelength. | ARGUMENTS | handle CBF handle. wavelength Wavelength in Angstrom. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | write_file(*args) | Returns : | *args : String filename,Integer ciforcbf,Integer Headers,Integer encoding | | C prototype: int cbf_write_file (cbf_handle handle, FILE *file, int readable, | int ciforcbf, int headers, int encoding); | | CBFLib documentation: | DESCRIPTION | cbf_write_file writes the CBF object specified by handle into the | file file, following CIF 1.0 conventions of 80 character lines. | cbf_write_widefile writes the CBF object specified by handle into the | file file, following CIF 1.1 conventions of 2048 character lines. A | warning is issued to stderr for ascii lines over the limit, and an | attempt is made to fold lines to fit. No test is performed on binary | sections. | If a dictionary has been provided, aliases will be applied on output. | Unlike cbf_read_file, the file does not have to be random-access. | If the file is random-access and readable, readable can be set to | non-0 to indicate to CBFlib that the file can be used as a buffer to | conserve disk space. If the file is not random-access or not | readable, readable must be 0. | If readable is non-0, CBFlib will close the file when it is no longer | required, otherwise this is the responsibility of the program. | ciforcbf selects the format in which the binary sections are written: | CIF Write an imgCIF file. CBF Write a CBF file (default). | headers selects the type of header used in CBF binary sections and | selects whether message digests are generated. The value of headers | can be a logical OR of any of: | MIME_HEADERS Use MIME-type headers (default). MIME_NOHEADERS | Use a simple ASCII headers. MSG_DIGEST Generate message digests | for binary data validation. MSG_NODIGEST Do not generate message | digests (default). | encoding selects the type of encoding used for binary sections and | the type of line-termination in imgCIF files. The value can be a | logical OR of any of: | ENC_BASE64 Use BASE64 encoding (default). ENC_QP Use | QUOTED-PRINTABLE encoding. ENC_BASE8 Use BASE8 (octal) encoding. | ENC_BASE10 Use BASE10 (decimal) encoding. ENC_BASE16 Use BASE16 | (hexadecimal) encoding. ENC_FORWARD For BASE8, BASE10 or BASE16 | encoding, map bytes to words forward (1234) (default on little-endian | machines). ENC_BACKWARD Map bytes to words backward (4321) (default | on big-endian machines). ENC_CRTERM Terminate lines with CR. | ENC_LFTERM Terminate lines with LF (default). | ARGUMENTS | handle CBF handle. file Pointer to a file descriptor. readable | If non-0: this file is random-access and readable and can be used as | a buffer. ciforcbf Selects the format in which the binary sections | are written (CIF/CBF). headers Selects the type of header in CBF | binary sections and message digest generation. encoding Selects the | type of encoding used for binary sections and the type of | line-termination in imgCIF files. | RETURN VALUE | Returns an error code on failure or 0 for success. | SEE ALSO | | write_widefile(*args) | write_widefile(self, void ?) | | ---------------------------------------------------------------------- | Properties defined here: | | node | = cbf_handle_struct_node_get(...) | | = cbf_handle_struct_node_set(...) | | row | = cbf_handle_struct_row_get(...) | | = cbf_handle_struct_row_set(...) | | search_row | = cbf_handle_struct_search_row_get(...) | | = cbf_handle_struct_search_row_set(...) | | ---------------------------------------------------------------------- | Data and other attributes defined here: | | __dict__ = | dictionary for instance variables (if defined) | | __swig_destroy__ = | | | __swig_getmethods__ = {'node': | list of weak references to the object (if defined) class cbf_positioner_struct(__builtin__.object) | Methods defined here: | | __del__ lambda self | | __getattr__ lambda self, name | | __init__(self, *args) | __init__(self) -> cbf_positioner_struct | | __repr__ = _swig_repr(self) | | __setattr__ lambda self, name, value | | get_reciprocal(*args) | Returns : double reciprocal1,double reciprocal2,double reciprocal3 | *args : double ratio,double wavelength,double real1,double real2,double real3 | | C prototype: int cbf_get_reciprocal (cbf_goniometer goniometer, | unsigned int reserved, double ratio, double wavelength, | double real1, double real2, double real3, | double *reciprocal1, double *reciprocal2, | double *reciprocal3); | | CBFLib documentation: | DESCRIPTION | cbf_get_reciprocal sets *reciprocal1, * reciprocal2, and * | reciprocal3 to the 3 components of the of the reciprocal-space vector | corresponding to the real-space vector (real1, real2, real3). The | reciprocal-space vector is oriented to correspond to the goniometer | setting with all axes at 0. The value wavelength is the wavlength in | Angstrom and the value ratio specifies the current goniometer setting | and varies from 0.0 at the beginning of the exposur e to 1.0 at the | end, irrespective of the actual rotation range. | Any of the destination pointers may be NULL. | The parameter reserved is presently unused and should be set to 0. | ARGUMENTS | goniometer Goniometer handle. reserved Unused. Any value other | than 0 is invalid. ratio Goniometer setting. 0 = beginning of | exposure, 1 = end. wavelength Wavelength in Angstrom. real1 x | component of the real-space vector. real2 y component of the | real-space vector. real3 z component of the real-space vector. | reciprocal1 Pointer to the destination x component of the | reciprocal-space vector. reciprocal2 Pointer to the destination y | component of the reciprocal-space vector. reciprocal3 Pointer to | the destination z component of the reciprocal-space vector. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | get_rotation_axis(*args) | Returns : double vector1,double vector2,double vector3 | *args : | | C prototype: int cbf_get_rotation_axis (cbf_goniometer goniometer, | unsigned int reserved, double *vector1, double *vector2, | double vector3); | | CBFLib documentation: | DESCRIPTION | cbf_get_rotation_axis sets *vector1, *vector2, and *vector3 to the 3 | components of the goniometer rotation axis used for the exposure. | Any of the destination pointers may be NULL. | The parameter reserved is presently unused and should be set to 0. | ARGUMENTS | goniometer Goniometer handle. reserved Unused. Any value other | than 0 is invalid. vector1 Pointer to the destination x component | of the rotation axis. vector2 Pointer to the destination y | component of the rotation axis. vector3 Pointer to the destination | z component of the rotation axis. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | get_rotation_range(*args) | Returns : Float start,Float increment | *args : | | C prototype: int cbf_get_rotation_range (cbf_goniometer goniometer, | unsigned int reserved, double *start, double *increment); | | CBFLib documentation: | DESCRIPTION | cbf_get_rotation_range sets *start and *increment to the | corresponding values of the goniometer rotation axis used for the | exposure. | Either of the destination pointers may be NULL. | The parameter reserved is presently unused and should be set to 0. | ARGUMENTS | goniometer Goniometer handle. reserved Unused. Any value other | than 0 is invalid. start Pointer to the destination start | value. increment Pointer to the destination increment value. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | rotate_vector(*args) | Returns : double final1,double final2,double final3 | *args : double ratio,double initial1,double initial2,double initial3 | | C prototype: int cbf_rotate_vector (cbf_goniometer goniometer, | unsigned int reserved, double ratio, double initial1, | double initial2, double initial3, double *final1, | double *final2, double *final3); | | CBFLib documentation: | DESCRIPTION | cbf_rotate_vector sets *final1, *final2, and *final3 to the 3 | components of the of the vector (initial1, initial2, initial3) after | reorientation by applying the goniometer rotations. The value ratio | specif ies the goniometer setting and varies from 0.0 at the | beginning of the exposure to 1.0 at the end, irrespective of the | actual rotation range. | Any of the destination pointers may be NULL. | The parameter reserved is presently unused and should be set to 0. | ARGUMENTS | goniometer Goniometer handle. reserved Unused. Any value other | than 0 is invalid. ratio Goniometer setting. 0 = beginning of | exposure, 1 = end. initial1 x component of the initial vector. | initial2 y component of the initial vector. initial3 z component | of the initial vector. vector1 Pointer to the destination x | component of the final vector. vector2 Pointer to the destination y | component of the final vector. vector3 Pointer to the destination z | component of the final vector. | RETURN VALUE | Returns an error code on failure or 0 for success. | _________________________________________________________________ | | ---------------------------------------------------------------------- | Properties defined here: | | axes | = cbf_positioner_struct_axes_get(...) | | = cbf_positioner_struct_axes_set(...) | | axes_are_connected | = cbf_positioner_struct_axes_are_connected_get(...) | | = cbf_positioner_struct_axes_are_connected_set(...) | | axis | = cbf_positioner_struct_axis_get(...) | | = cbf_positioner_struct_axis_set(...) | | matrix | = cbf_positioner_struct_matrix_get(...) | | = cbf_positioner_struct_matrix_set(...) | | matrix_is_valid | = cbf_positioner_struct_matrix_is_valid_get(...) | | = cbf_positioner_struct_matrix_is_valid_set(...) | | ---------------------------------------------------------------------- | Data and other attributes defined here: | | __dict__ = | dictionary for instance variables (if defined) | | __swig_destroy__ = | | | __swig_getmethods__ = {'axes': CREDITS Paul Ellis and Herbert Bernstein for the excellent CBFlib! ./CBFlib-0.9.2.2/pycbf/make_pycbf.py0000644000076500007650000035112311603702120015354 0ustar yayayaya print "\\begin{verbatim}" print "This output comes from make_pycbf.py which generates the wrappers" print "pycbf Copyright (C) 2005 Jonathan Wright, no warranty, LGPL" ###################################################################### # # # YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE INCLUDING PYCBF UNDER THE # # TERMS OF THE GPL # # # # ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API INCLUDING PYCBF # # UNDER THE TERMS OF THE LGPL # # # ###################################################################### ########################### GPL NOTICES ############################## # # # This program is free software; you can redistribute it and/or # # modify it under the terms of the GNU General Public License as # # published by the Free Software Foundation; either version 2 of # # (the License, or (at your option) any later version. # # # # This program is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # # GNU General Public License for more details. # # # # You should have received a copy of the GNU General Public License # # along with this program; if not, write to the Free Software # # Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA # # 02111-1307 USA # # # ###################################################################### ######################### LGPL NOTICES ############################### # # # This library is free software; you can redistribute it and/or # # modify it under the terms of the GNU Lesser General Public # # License as published by the Free Software Foundation; either # # version 2.1 of the License, or (at your option) any later version. # # # # This library is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # # Lesser General Public License for more details. # # # # You should have received a copy of the GNU Lesser General Public # # License along with this library; if not, write to the Free # # Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, # # MA 02110-1301 USA # # # ###################################################################### # Get the ascii text as a list of strings lines = open("CBFlib.txt","r").readlines() # Variables to hold the useful things we find in the file docstring = "\n" name="" # Flag to indicate we have not read anything useful yet on=0 # Dictionary of function prototypes and documentation, keyed by name in C. name_dict = {} i=-1 debug = 0 # Parse the text prototypes = "" while i=0 and on==1: on=10 # Only try for ten lines after it say PROTOTYPE continue if line.find("#include")>=0: # why? continue if line.find("int cbf_")>=0: # We found a function # keep going up to DESCRIPTION prototypes+=""+lines[i].rstrip()+" " # print lines[i].rstrip() check=0 while lines[i+1].find("DESCRIPTION")==-1 and lines[i+1].find("int cbf_")==-1: i=i+1 prototypes+=lines[i].rstrip()+" " # lose the \n # print lines[i].rstrip() check+=1 if check>20: raise Exception("Runaway prototype "+prototypes) on=1 # Keep reading docstring continue if on > 1: # why? on=on-1 if line.find("3. File format")>=0 and on==1: # Stop processing at section 3 i=len(lines) if on==1: # Docstring ends at 2.xxx for next function or see also # We are losing the see also information for now (needed the section # breaks in the rtf file) if len(line.strip())==0: docstring+="\n" continue else: if docstring[-1]=="\n": docstring += line.lstrip().rstrip() else: docstring =docstring+" "+line.lstrip().rstrip() if line.strip()[0] in [str(j) for j in range(9)] or \ line.find("SEE ALSO")>=0 or \ line.find("________")>=0 or \ line.find("--------")>=0: if len(docstring)>0: # print "Prototypes: ",prototypes docstring = docstring.replace("\"", " \\\"") # escape the quotes for prototype in prototypes.strip().split(";")[:-1]: name = prototype.split("(")[0].strip() cname = name.split()[1].strip() prototype = prototype.strip()+";" name_dict[cname]=[prototype,docstring] # print "Prototype: ","::",cname,"::",name,"::", prototype prototypes = "" # print "Found ",prototype docstring="\n" prototype="" cname="" on=0 else: raise Exception("bad docstring") # End of CBFlib.txt file - now generate wrapper code for swig def myformat(s,l,indent=0,breakon=" "): """ Try to pretty print lines - this is a pain... """ lines = s.rstrip().split("\n") out="" for line in lines: if len(line)==0: continue # skip blank lines if len(line)>l: words = line.split(breakon) newline=words[0] if len(words)>1: for word in words[1:]: if len(newline)+len(word)+1 < l: newline=newline+breakon+word else: out = out+newline+breakon+"\n"+indent*" " newline=word out += newline+"\n" else: out += "\n" else: out += line+"\n" # Last one if out == "": return "\n" else: return out def docstringwrite(pyfunc,input,output,prototype,cbflibdoc): doc = "%feature(\"autodoc\", \"\nReturns : " returns = "" for out in output: returns += out+"," if len(returns)>0: doc += myformat(returns[:-1],70,indent = 10,breakon=",") else: doc += "\n" doc += "*args : " takes = "" for inp in input: takes += inp+"," if len(takes)>0: doc += myformat(takes[:-1],70,indent = 10,breakon=",") else: doc += "\n" doc += "\nC prototype: "+myformat(prototype,65,indent=16,breakon=",") doc += "\nCBFLib documentation:\n"+myformat(cbflibdoc,70)+"\")" doc += pyfunc+";\n" return doc cbfhandle_specials = { "cbf_get_integerarrayparameters":[""" %apply int *OUTPUT {int *compression,int *binary_id, int *elsize, int *elsigned, int *elunsigned, int *elements, int *minelement, int *maxelement} get_integerarrayparameters; void get_integerarrayparameters(int *compression,int *binary_id, int *elsize, int *elsigned, int *elunsigned, int *elements, int *minelement, int *maxelement){ unsigned int comp; size_t elsiz, elem; cbf_failnez(cbf_get_integerarrayparameters(self, &comp,binary_id, &elsiz, elsigned, elunsigned, &elem, minelement, maxelement)); *compression = comp; /* FIXME - does this convert in C? */ *elsize = elsiz; *elements = elem; } ""","get_integerarrayparameters",[],["int compression","int binary_id", "int elsize", "int elsigned", "int elunsigned", "int elements", "int minelement", "int maxelement"]], "cbf_get_integerarrayparameters_wdims":[""" %cstring_output_allocate_size(char **bo, int *bolen, free(*$1)); %apply int *OUTPUT {int *compression,int *binary_id, int *elsize, int *elsigned, int *elunsigned, int *elements, int *minelement, int *maxelement, int *dimfast, int *dimmid, int *dimslow, int *padding} get_integerarrayparameters_wdims; void get_integerarrayparameters_wdims(int *compression,int *binary_id, int *elsize, int *elsigned, int *elunsigned, int *elements, int *minelement, int *maxelement, char **bo, int *bolen, int *dimfast, int *dimmid, int *dimslow, int *padding ){ unsigned int comp; size_t elsiz, elem, df,dm,ds,pd; const char * byteorder; char * bot; cbf_failnez(cbf_get_integerarrayparameters_wdims(self, &comp,binary_id, &elsiz, elsigned, elunsigned, &elem, minelement, maxelement, &byteorder,&df,&dm,&ds,&pd )); *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)} strncpy(bot,byteorder,*bolen); *bo = bot; *compression = comp; *elsize = elsiz; *elements = elem; *dimfast = df; *dimmid = dm; *dimslow = ds; *padding = pd; } ""","get_integerarrayparameters_wdims",[],["int compression","int binary_id", "int elsize", "int elsigned", "int elunsigned", "int elements", "int minelement", "int maxelement", "char **bo", "int *bolen", "int dimfast", "int dimmid", "int dimslow", "int padding"]], "cbf_get_integerarrayparameters_wdims_fs":[""" %cstring_output_allocate_size(char **bo, int *bolen, free(*$1)); %apply int *OUTPUT {int *compression,int *binary_id, int *elsize, int *elsigned, int *elunsigned, int *elements, int *minelement, int *maxelement, int *dimfast, int *dimmid, int *dimslow, int *padding} get_integerarrayparameters_wdims_fs; void get_integerarrayparameters_wdims_fs(int *compression,int *binary_id, int *elsize, int *elsigned, int *elunsigned, int *elements, int *minelement, int *maxelement, char **bo, int *bolen, int *dimfast, int *dimmid, int *dimslow, int *padding ){ unsigned int comp; size_t elsiz, elem, df,dm,ds,pd; const char * byteorder; char * bot; cbf_failnez(cbf_get_integerarrayparameters_wdims_fs(self, &comp,binary_id, &elsiz, elsigned, elunsigned, &elem, minelement, maxelement, &byteorder,&df,&dm,&ds,&pd )); *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)} strncpy(bot,byteorder,*bolen); *bo = bot; *compression = comp; *elsize = elsiz; *elements = elem; *dimfast = df; *dimmid = dm; *dimslow = ds; *padding = pd; } ""","get_integerarrayparameters_wdims_fs",[],["int compression","int binary_id", "int elsize", "int elsigned", "int elunsigned", "int elements", "int minelement", "int maxelement", "char **bo", "int *bolen", "int dimfast", "int dimmid", "int dimslow", "int padding"]], "cbf_get_integerarrayparameters_wdims_sf":[""" %cstring_output_allocate_size(char **bo, int *bolen, free(*$1)); %apply int *OUTPUT {int *compression,int *binary_id, int *elsize, int *elsigned, int *elunsigned, int *elements, int *minelement, int *maxelement, int *dimslow, int *dimmid, int *dimfast, int *padding} get_integerarrayparameters_wdims_sf; void get_integerarrayparameters_wdims_sf(int *compression,int *binary_id, int *elsize, int *elsigned, int *elunsigned, int *elements, int *minelement, int *maxelement, char **bo, int *bolen, int *dimslow, int *dimmid, int *dimfast, int *padding ){ unsigned int comp; size_t elsiz, elem, df,dm,ds,pd; const char * byteorder; char * bot; cbf_failnez(cbf_get_integerarrayparameters_wdims_sf(self, &comp,binary_id, &elsiz, elsigned, elunsigned, &elem, minelement, maxelement, &byteorder,&ds,&dm,&df,&pd )); *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)} strncpy(bot,byteorder,*bolen); *bo = bot; *compression = comp; *elsize = elsiz; *elements = elem; *dimfast = df; *dimmid = dm; *dimslow = ds; *padding = pd; } ""","get_integerarrayparameters_wdims_sf",[],["int compression","int binary_id", "int elsize", "int elsigned", "int elunsigned", "int elements", "int minelement", "int maxelement", "char **bo", "int *bolen", "int dimslow", "int dimmid", "int dimfast", "int padding"]], "cbf_get_realarrayparameters":[""" %apply int *OUTPUT {int *compression,int *binary_id, int *elsize, int *elements} get_realarrayparameters; void get_realarrayparameters(int *compression,int *binary_id, int *elsize, int *elements){ unsigned int comp; size_t elsiz, elem; cbf_failnez(cbf_get_realarrayparameters(self, &comp ,binary_id, &elsiz, &elem )); *compression = comp; /* FIXME - does this convert in C? */ *elsize = elsiz; *elements = elem; } ""","get_realarrayparameters",[],["int compression","int binary_id", "int elsize", "int elements"]], "cbf_get_realarrayparameters_wdims":[""" %cstring_output_allocate_size(char **bo, int *bolen, free(*$1)); %apply int *OUTPUT {int *compression,int *binary_id, int *elsize, int *elements, int *dimslow, int *dimmid, int *dimfast, int *padding} get_realarrayparameters_wdims; void get_realarrayparameters_wdims(int *compression,int *binary_id, int *elsize, int *elements, char **bo, int *bolen, int *dimfast, int *dimmid, int *dimslow, int *padding ){ unsigned int comp; size_t elsiz, elem, df,dm,ds,pd; const char * byteorder; char * bot; cbf_failnez(cbf_get_realarrayparameters_wdims(self, &comp,binary_id, &elsiz, &elem, &byteorder,&ds,&dm,&ds,&pd )); *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)} strncpy(bot,byteorder,*bolen); *bo = bot; *compression = comp; *elsize = elsiz; *elements = elem; *dimfast = df; *dimmid = dm; *dimslow = ds; *padding = pd; } ""","get_realarrayparameters_wdims",[],["int compression","int binary_id", "int elsize", "int elements", "char **bo", "int *bolen", "int dimfast", "int dimmid", "int dimslow", "int padding"]], "cbf_get_realarrayparameters_wdims_fs":[""" %cstring_output_allocate_size(char **bo, int *bolen, free(*$1)); %apply int *OUTPUT {int *compression,int *binary_id, int *elsize, int *elements, int *dimslow, int *dimmid, int *dimfast, int *padding} get_realarrayparameters_wdims_fs; void get_realarrayparameters_wdims_fs(int *compression,int *binary_id, int *elsize, int *elements, char **bo, int *bolen, int *dimfast, int *dimmid, int *dimslow, int *padding ){ unsigned int comp; size_t elsiz, elem, df,dm,ds,pd; const char * byteorder; char * bot; cbf_failnez(cbf_get_realarrayparameters_wdims_fs(self, &comp,binary_id, &elsiz, &elem, &byteorder,&ds,&dm,&ds,&pd )); *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)} strncpy(bot,byteorder,*bolen); *bo = bot; *compression = comp; *elsize = elsiz; *elements = elem; *dimfast = df; *dimmid = dm; *dimslow = ds; *padding = pd; } ""","get_realarrayparameters_wdims_fs",[],["int compression","int binary_id", "int elsize", "int elements", "char **bo", "int *bolen", "int dimfast", "int dimmid", "int dimslow", "int padding"]], "cbf_get_realarrayparameters_wdims_sf":[""" %cstring_output_allocate_size(char **bo, int *bolen, free(*$1)); %apply int *OUTPUT {int *compression,int *binary_id, int *elsize, int *elements, int *dimslow, int *dimmid, int *dimfast, int *padding} get_realarrayparameters_wdims_sf; void get_realarrayparameters_wdims_sf(int *compression,int *binary_id, int *elsize, int *elements, char **bo, int *bolen, int *dimslow, int *dimmid, int *dimfast, int *padding ){ unsigned int comp; size_t elsiz, elem, df,dm,ds,pd; const char * byteorder; char * bot; cbf_failnez(cbf_get_realarrayparameters_wdims_sf(self, &comp,binary_id, &elsiz, &elem, &byteorder,&ds,&dm,&df,&pd )); *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)} strncpy(bot,byteorder,*bolen); *bo = bot; *compression = comp; *elsize = elsiz; *elements = elem; *dimfast = df; *dimmid = dm; *dimslow = ds; *padding = pd; } ""","get_realarrayparameters_wdims_sf",[],["int compression","int binary_id", "int elsize", "int elements", "char **bo", "int *bolen", "int dimslow", "int dimmid", "int dimfast", "int padding"]], "cbf_get_integerarray":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_integerarray_as_string; // Get the length correct void get_integerarray_as_string(char **s, int *slen){ int binary_id, elsigned, elunsigned; size_t elements, elements_read, elsize; int minelement, maxelement; unsigned int compression; void * array; *slen = 0; /* Initialise in case of problems */ cbf_failnez(cbf_get_integerarrayparameters(self, &compression, &binary_id, &elsize, &elsigned, &elunsigned, &elements, &minelement, &maxelement)); if ((array=malloc(elsize*elements))) { /* cbf_failnez (cbf_select_column(cbf,colnum)) */ cbf_failnez (cbf_get_integerarray(self, &binary_id, (void *)array, elsize, elsigned, elements, &elements_read)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*elements; *s = (char *) array; } ""","get_integerarray_as_string",[],["(Binary)String"] ], "cbf_get_image":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_image_as_string; // Get the length correct void get_image_as_string(int element_number, char **s, int *slen, int elsize, int elsign, int ndimslow, int ndimfast){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimslow))) { cbf_failnez (cbf_get_image(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, elsign, (size_t) ndimslow, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimslow; *s = (char *) array; } ""","get_image_as_string",["int element_number", "int elsize", "int elsign", "int ndimslow", "int ndimfast"],["(Binary)String"] ], "cbf_get_image_fs":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_image_fs_as_string; // Get the length correct void get_image_fs_as_string(int element_number, char **s, int *slen, int elsize, int elsign, int ndimfast, int ndimslow){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimslow))) { cbf_failnez (cbf_get_image_fs(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, elsign, (size_t) ndimfast, (size_t)ndimslow)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimslow; *s = (char *) array; } ""","get_image_fs_as_string",["int element_number", "int elsize", "int elsign", "int ndimfast", "int ndimslow"],["(Binary)String"] ], "cbf_get_image_sf":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_image_fs_as_string; // Get the length correct void get_image_sf_as_string(int element_number, char **s, int *slen, int elsize, int elsign, int ndimslow, int ndimfast){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimslow))) { cbf_failnez (cbf_get_image_sf(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, elsign, (size_t) ndimslow, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimslow; *s = (char *) array; } ""","get_image_sf_as_string",["int element_number", "int elsize", "int elsign", "int ndimslow", "int ndimfast"],["(Binary)String"] ], "cbf_get_real_image":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_real_image_as_string; // Get the length correct void get_real_image_as_string(int element_number, char **s, int *slen, int elsize, int ndimslow, int ndimfast){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimslow))) { cbf_failnez (cbf_get_real_image(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, (size_t) ndimslow, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimslow; *s = (char *) array; } ""","get_real_image_as_string",["int element_number", "int elsize", "int ndimslow", "int ndimfast"],["(Binary)String"] ], "cbf_get_real_image_fs":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_real_image_fs_as_string; // Get the length correct void get_real_image_fs_as_string(int element_number, char **s, int *slen, int elsize, int ndimfast, int ndimslow){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimslow))) { cbf_failnez (cbf_get_real_image_fs(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, (size_t) ndimfast, (size_t)ndimslow)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimslow; *s = (char *) array; } ""","get_real_image_fs_as_string",["int element_number", "int elsize", "int ndimfast", "int ndimslow"],["(Binary)String"] ], "cbf_get_real_image_sf":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_real_image_sf_as_string; // Get the length correct void get_real_image_sf_as_string(int element_number, char **s, int *slen, int elsize, int ndimslow, int ndimfast){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimslow))) { cbf_failnez (cbf_get_real_image_sf(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, (size_t) ndimslow, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimslow; *s = (char *) array; } ""","get_real_image_sf_as_string",["int element_number", "int elsize", "int ndimslow", "int ndimfast"],["(Binary)String"] ], "cbf_get_3d_image":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_3d_image_as_string; // Get the length correct void get_3d_image_as_string(int element_number, char **s, int *slen, int elsize, int elsign, int ndimfast, int ndimmid, int ndimslow){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) { cbf_failnez (cbf_get_3d_image(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, elsign, (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimmid*ndimslow; *s = (char *) array; } ""","get_3d_image_as_string",["int element_number", "int elsize", "int elsign", "int ndimslow", "int ndimmid", "int ndimfast"],["(Binary)String"] ], "cbf_get_3d_image_fs":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_3d_image_fs_as_string; // Get the length correct void get_3d_image_fs_as_string(int element_number, char **s, int *slen, int elsize, int elsign, int ndimfast, int ndimmid, int ndimslow){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) { cbf_failnez (cbf_get_3d_image_fs(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, elsign, (size_t) ndimfast, (size_t)ndimmid, (size_t)ndimslow)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimmid*ndimslow; *s = (char *) array; } ""","get_3d_image_fs_as_string",["int element_number", "int elsize", "int elsign", "int ndimfast", "int ndimmid", "int ndimslow"],["(Binary)String"] ], "cbf_get_3d_image_sf":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_3d_image_sf_as_string; // Get the length correct void get_3d_image_sf_as_string(int element_number, char **s, int *slen, int elsize, int elsign, int ndimfast, int ndimmid, int ndimslow){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) { cbf_failnez (cbf_get_3d_image_sf(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, elsign, (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimmid*ndimslow; *s = (char *) array; } ""","get_3d_image_sf_as_string",["int element_number", "int elsize", "int elsign", "int ndimslow", "int ndimmid", "int ndimfast"],["(Binary)String"] ], "cbf_get_real_3d_image":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_real_3d_image_as_string; // Get the length correct void get_real_3d_image_as_string(int element_number, char **s, int *slen, int elsize, int ndimslow, int ndimmid, int ndimfast){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) { cbf_failnez (cbf_get_real_3d_image(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimmid*ndimslow; *s = (char *) array; } ""","get_real_3d_image_as_string",["int element_number", "int elsize", "int ndimslow", "int ndimmid", "int ndimfast"],["(Binary)String"] ], "cbf_get_real_3d_image_fs":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_real_3d_image_fs_as_string; // Get the length correct void get_real_3d_image_fs_as_string(int element_number, char **s, int *slen, int elsize, int ndimfast, int ndimmid, int ndimslow){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) { cbf_failnez (cbf_get_real_3d_image_fs(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, (size_t) ndimfast, (size_t)ndimmid, (size_t)ndimslow)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimmid*ndimslow; *s = (char *) array; } ""","get_real_3d_image_fs_as_string",["int element_number", "int elsize", "int ndimfast", "int ndimmid", "int ndimslow"],["(Binary)String"] ], "cbf_get_real_3d_image_sf":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_real_3d_image_sf_as_string; // Get the length correct void get_real_3d_image_sf_as_string(int element_number, char **s, int *slen, int elsize, int ndimslow, int ndimmid, int ndimfast){ void *array; int reserved = 0; *slen = 0; /* Initialise in case of problems */ if ((array=malloc(elsize*ndimfast*ndimmid*ndimslow))) { cbf_failnez (cbf_get_real_3d_image_sf(self, reserved, (unsigned int)element_number, (void *)array, (size_t)elsize, (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*ndimfast*ndimmid*ndimslow; *s = (char *) array; } ""","get_real_3d_image_sf_as_string",["int element_number", "int elsize", "int ndimslow", "int ndimmid", "int ndimfast"],["(Binary)String"] ], "cbf_get_realarray":[""" // Ensure we free the local temporary %cstring_output_allocate_size(char ** s, int *slen, free(*$1)) get_realarray_as_string; // Get the length correct void get_realarray_as_string(char **s, int *slen){ int binary_id; size_t elements, elements_read, elsize; unsigned int compression; void * array; *slen = 0; /* Initialise in case of problems */ cbf_failnez(cbf_get_realarrayparameters(self, &compression, &binary_id, &elsize, &elements)); if ((array=malloc(elsize*elements))) { /* cbf_failnez (cbf_select_column(cbf,colnum)) */ cbf_failnez (cbf_get_realarray(self, &binary_id, (void *)array, elsize, elements, &elements_read)); }else{ cbf_failnez(CBF_ALLOC); } *slen = elsize*elements; *s = (char *) array; } ""","get_realarray_as_string",[],["(Binary)String"] ], "cbf_set_integerarray":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_integerarray; void set_integerarray(unsigned int compression, int binary_id, char *data, int len, int elsize, int elsigned, int elements){ /* safety check on args */ size_t els, ele; void *array; if(len == elsize*elements){ array = data; els = elsize; ele = elements; cbf_failnez(cbf_set_integerarray (self, compression, binary_id, (void *) data, (size_t) elsize, elsigned, (size_t) elements)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_integerarray", [ "int compression", "int binary_id","(binary) String data", "int elsize", "int elsigned","int elements"],[]], "cbf_set_integerarray_wdims":[""" /* CBFlib must NOT modify the data string nor the byteorder string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_integerarray_wdims; %apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_integerarray_wdims; void set_integerarray_wdims(unsigned int compression, int binary_id, char *data, int len, int elsize, int elsigned, int elements, char *bo, int bolen, int dimfast, int dimmid, int dimslow, int padding){ /* safety check on args */ size_t els, ele; void *array; char byteorder[15]; if(len == elsize*elements && elements==dimfast*dimmid*dimslow){ array = data; els = elsize; ele = elements; strncpy(byteorder,bo,bolen<15?bolen:14); byteorder[bolen<15?14:bolen] = 0; cbf_failnez(cbf_set_integerarray_wdims (self, compression, binary_id, (void *) data, (size_t) elsize, elsigned, (size_t) elements, (const char *)byteorder, (size_t)dimfast, (size_t)dimmid, (size_t)dimslow, (size_t)padding)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_integerarray_wdims", [ "int compression", "int binary_id","(binary) String data", "int elsize","int elements", "String byteorder", "int dimfast", "int dimmid", "int dimslow", "int padding"],[]], "cbf_set_integerarray_wdims_sf":[""" /* CBFlib must NOT modify the data string nor the byteorder string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_integerarray_wdims_sf; %apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_integerarray_wdims_sf; void set_integerarray_wdims_sf(unsigned int compression, int binary_id, char *data, int len, int elsize, int elsigned, int elements, char *bo, int bolen, int dimslow, int dimmid, int dimfast, int padding){ /* safety check on args */ size_t els, ele; void *array; char byteorder[15]; if(len == elsize*elements && elements==dimfast*dimmid*dimslow){ array = data; els = elsize; ele = elements; strncpy(byteorder,bo,bolen<15?bolen:14); byteorder[bolen<15?14:bolen] = 0; cbf_failnez(cbf_set_integerarray_wdims_sf (self, compression, binary_id, (void *) data, (size_t) elsize, elsigned, (size_t) elements, (const char *)byteorder, (size_t)dimslow, (size_t)dimmid, (size_t)dimfast, (size_t)padding)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_integerarray_wdims_sf", [ "int compression", "int binary_id","(binary) String data", "int elsize","int elements", "String byteorder", "int dimslow", "int dimmid", "int dimfast", "int padding"],[]], "cbf_set_integerarray_wdims_fs":[""" /* CBFlib must NOT modify the data string nor the byteorder string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_integerarray_wdims_fs; %apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_integerarray_wdims_fs; void set_integerarray_wdims_fs(unsigned int compression, int binary_id, char *data, int len, int elsize, int elsigned, int elements, char *bo, int bolen, int dimfast, int dimmid, int dimslow, int padding){ /* safety check on args */ size_t els, ele; void *array; char byteorder[15]; if(len == elsize*elements && elements==dimfast*dimmid*dimslow){ array = data; els = elsize; ele = elements; strncpy(byteorder,bo,bolen<15?bolen:14); byteorder[bolen<15?14:bolen] = 0; cbf_failnez(cbf_set_integerarray_wdims_fs (self, compression, binary_id, (void *) data, (size_t) elsize, elsigned, (size_t) elements, (const char *)byteorder, (size_t)dimfast, (size_t)dimmid, (size_t)dimslow, (size_t)padding)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_integerarray_wdims_fs", [ "int compression", "int binary_id","(binary) String data", "int elsize","int elements", "String byteorder", "int dimfast", "int dimmid", "int dimslow", "int padding"],[]], "cbf_set_realarray":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_realarray; void set_realarray(unsigned int compression, int binary_id, char *data, int len, int elsize, int elements){ /* safety check on args */ size_t els, ele; void *array; if(len == elsize*elements){ array = data; els = elsize; ele = elements; cbf_failnez(cbf_set_realarray (self, compression, binary_id, (void *) data, (size_t) elsize, (size_t) elements)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_realarray", [ "int compression", "int binary_id","(binary) String data", "int elsize","int elements"],[]], "cbf_set_realarray_wdims":[""" /* CBFlib must NOT modify the data string nor the byteorder string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_realarray_wdims; %apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_realarray_wdims; void set_realarray_wdims(unsigned int compression, int binary_id, char *data, int len, int elsize, int elements, char *bo, int bolen, int dimfast, int dimmid, int dimslow, int padding){ /* safety check on args */ size_t els, ele; void *array; char byteorder[15]; if(len == elsize*elements && elements==dimfast*dimmid*dimslow){ array = data; els = elsize; ele = elements; strncpy(byteorder,bo,bolen<15?bolen:14); byteorder[bolen<15?14:bolen] = 0; cbf_failnez(cbf_set_realarray_wdims (self, compression, binary_id, (void *) data, (size_t) elsize, (size_t) elements, (const char *)byteorder, (size_t)dimfast, (size_t)dimmid, (size_t)dimslow, (size_t)padding)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_realarray_wdims", [ "int compression", "int binary_id","(binary) String data", "int elsize","int elements", "String byteorder", "int dimfast", "int dimmid", "int dimslow", "int padding"],[]], "cbf_set_realarray_wdims_sf":[""" /* CBFlib must NOT modify the data string nor the byteorder string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_realarray_wdims_sf; %apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_realarray_wdims_sf; void set_realarray_wdims_sf(unsigned int compression, int binary_id, char *data, int len, int elsize, int elements, char *bo, int bolen, int dimslow, int dimmid, int dimfast, int padding){ /* safety check on args */ size_t els, ele; void *array; char byteorder[15]; if(len == elsize*elements && elements==dimfast*dimmid*dimslow){ array = data; els = elsize; ele = elements; strncpy(byteorder,bo,bolen<15?bolen:14); byteorder[bolen<15?14:bolen] = 0; cbf_failnez(cbf_set_realarray_wdims_sf (self, compression, binary_id, (void *) data, (size_t) elsize, (size_t) elements, (const char *)byteorder, (size_t) dimslow, (size_t) dimmid, (size_t) dimfast, (size_t)padding)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_realarray_wdims_sf", [ "int compression", "int binary_id","(binary) String data", "int elsize","int elements", "String byteorder", "int dimslow", "int dimmid", "int dimfast", "int padding"],[]], "cbf_set_realarray_wdims_fs":[""" /* CBFlib must NOT modify the data string nor the byteorder string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_realarray_wdims_fs; %apply (char *STRING, int LENGTH) { (char *bo, int bolen) } set_realarray_wdims_fs; void set_realarray_wdims_fs(unsigned int compression, int binary_id, char *data, int len, int elsize, int elements, char *bo, int bolen, int dimfast, int dimmid, int dimslow, int padding){ /* safety check on args */ size_t els, ele; void *array; char byteorder[15]; if(len == elsize*elements && elements==dimfast*dimmid*dimslow){ array = data; els = elsize; ele = elements; strncpy(byteorder,bo,bolen<15?bolen:14); byteorder[bolen<15?14:bolen] = 0; cbf_failnez(cbf_set_realarray_wdims_fs (self, compression, binary_id, (void *) data, (size_t) elsize, (size_t) elements, (const char *)byteorder, (size_t) dimfast, (size_t) dimmid, (size_t) dimslow, (size_t)padding)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_realarray_wdims_fs", [ "int compression", "int binary_id","(binary) String data", "int elsize","int elements", "String byteorder", "int dimfast", "int dimmid", "int dimslow", "int padding"],[]], "cbf_set_image":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_image; void set_image(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int elsign, int ndimslow, int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_image (self, reserved, element_number, compression, (void *) data, (size_t) elsize, elsign, (size_t) ndimslow, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_image", [ "int element_number","int compression","(binary) String data", "int elsize", "int elsign", "int dimslow", "int dimfast"],[]], "cbf_set_image_fs":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_image; void set_image_fs(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int elsign, int ndimfast, int ndimslow){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_image (self, reserved, element_number, compression, (void *) data, (size_t) elsize, elsign, (size_t) ndimfast, (size_t)ndimslow)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_image_fs", [ "int element_number","int compression","(binary) String data", "int elsize", "int elsign", "int dimfast", "int dimslow"],[]], "cbf_set_image_sf":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_image_sf; void set_image_sf(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int elsign, int ndimslow, int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_image_sf (self, reserved, element_number, compression, (void *) data, (size_t) elsize, elsign, (size_t) ndimslow, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_image_sf", [ "int element_number","int compression","(binary) String data", "int elsize", "int elsign", "int dimslow", "int dimfast"],[]], "cbf_set_real_image":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_real_image; void set_real_image(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int ndimslow, int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_real_image (self, reserved, element_number, compression, (void *) data, (size_t) elsize, (size_t) ndimslow, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_real_image", [ "int element_number","int compression","(binary) String data", "int elsize", "int dimslow", "int dimfast"],[]], "cbf_set_real_image_fs":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_real_image; void set_real_image_fs(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int ndimfast, int ndimslow){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_real_image_fs (self, reserved, element_number, compression, (void *) data, (size_t) elsize, (size_t) ndimfast, (size_t)ndimslow)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_real_image_fs", [ "int element_number","int compression","(binary) String data", "int elsize", "int dimfast", "int dimslow"],[]], "cbf_set_real_image_sf":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_real_image_sf; void set_real_image_sf(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int ndimslow, int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_real_image_sf (self, reserved, element_number, compression, (void *) data, (size_t) elsize, (size_t) ndimslow, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_real_image_sf", [ "int element_number","int compression","(binary) String data", "int elsize", "int dimslow", "int dimfast"],[]], "cbf_set_3d_image":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_3d_image; void set_3d_image(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int elsign, int ndimslow, int ndimmid, int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimmid*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_3d_image (self, reserved, element_number, compression, (void *) data, (size_t) elsize, elsign, (size_t) ndimslow, (size_t) ndimmid, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_3d_image", [ "int element_number","int compression","(binary) String data", "int elsize", "int elsign", "int dimslow", "int dimmid", "int dimfast"],[]], "cbf_set_3d_image_fs":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_3d_image; void set_3d_image_fs(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int elsign, int ndimfast, int ndimmid, int ndimslow){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimmid*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_3d_image_fs (self, reserved, element_number, compression, (void *) data, (size_t) elsize, elsign, (size_t) ndimfast, (size_t) ndimmid, (size_t)ndimslow)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_3d_image_fs", [ "int element_number","int compression","(binary) String data", "int elsize", "int elsign", "int dimfast", "int dimmid", "int dimslow"],[]], "cbf_set_3d_image_sf":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_3d_image; void set_3d_image_sf(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int elsign, int ndimslow, int ndimmid, int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimmid*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_3d_image_sf (self, reserved, element_number, compression, (void *) data, (size_t) elsize, elsign, (size_t) ndimslow, (size_t) ndimmid, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_3d_image_sf", [ "int element_number","int compression","(binary) String data", "int elsize", "int elsign", "int dimslow", "int dimmid", "int dimfast"],[]], "cbf_set_real_3d_image":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_real_3d_image_sf; void set_real_3d_image(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int ndimslow, int ndimmid, int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimmid*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_real_3d_image (self, reserved, element_number, compression, (void *) data, (size_t) elsize, (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_real_3d_image", [ "int element_number","int compression","(binary) String data", "int elsize", "int dimslow", "int dimmid", "int dimfast"],[]], "cbf_set_real_3d_image_fs":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_real_3d_image_fs; void set_real_3d_image_fs(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int ndimfast, int ndimmid, int ndimslow){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimmid*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_real_3d_image_fs (self, reserved, element_number, compression, (void *) data, (size_t) elsize, (size_t) ndimfast, (size_t)ndimmid, (size_t)ndimslow)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_real_3d_image_fs", [ "int element_number","int compression","(binary) String data", "int elsize", "int dimfast", "int dimmid", "int dimslow"],[]], "cbf_set_real_3d_image_sf":[""" /* CBFlib must NOT modify the data string which belongs to the scripting language we will get and check the length via a typemap */ %apply (char *STRING, int LENGTH) { (char *data, int len) } set_real_3d_image_sf; void set_real_3d_image_sf(unsigned int element_number, unsigned int compression, char *data, int len, int elsize, int ndimslow, int ndimmid, int ndimfast){ /* safety check on args */ size_t els; unsigned int reserved; void *array; if(len == elsize*ndimslow*ndimmid*ndimfast){ array = data; els = elsize; reserved = 0; cbf_failnez(cbf_set_real_3d_image_sf (self, reserved, element_number, compression, (void *) data, (size_t) elsize, (size_t) ndimslow, (size_t)ndimmid, (size_t)ndimfast)); }else{ cbf_failnez(CBF_ARGUMENT); } } ""","set_real_3d_image_sf", [ "int element_number","int compression","(binary) String data", "int elsize", "int dimslow", "int dimmid", "int dimfast"],[]], "cbf_get_image_size": [""" %apply int *OUTPUT {int *ndimslow, int *ndimfast} get_image_size; void get_image_size(unsigned int element_number, int *ndimslow, int *ndimfast){ unsigned int reserved; size_t inslow, infast; reserved = 0; cbf_failnez(cbf_get_image_size(self,reserved,element_number,&inslow,&infast)); *ndimslow = (int)inslow; *ndimfast = (int)infast; } ""","get_image_size",["Integer element_number"],["size_t ndim1","size_t ndim2"]], "cbf_get_image_size_fs": [""" %apply int *OUTPUT {int *ndimfast, int *ndimslow} get_image_size_fs; void get_image_size_fs(unsigned int element_number, int *ndimfast, int *ndimslow){ unsigned int reserved; size_t infast, inslow; reserved = 0; cbf_failnez(cbf_get_image_size_fs(self,reserved,element_number,&infast,&inslow)); *ndimfast = (int)infast; /* FIXME - is that how to convert? */ *ndimslow = (int)inslow; } ""","get_image_size_fs",["Integer element_number"],["size_t ndimfast","size_t ndimslow"]], "cbf_get_image_size_sf": [""" %apply int *OUTPUT {int *ndimslow, int *ndimfast} get_image_size_sf; void get_image_size_sf(unsigned int element_number, int *ndimslow, int *ndimfast){ unsigned int reserved; size_t inslow, infast; reserved = 0; cbf_failnez(cbf_get_image_size(self,reserved,element_number,&inslow,&infast)); *ndimslow = (int)inslow; *ndimfast = (int)infast; } ""","get_image_size_sf",["Integer element_number"],["size_t ndimslow","size_t ndimfast"]], "cbf_get_3d_image_size": [""" %apply int *OUTPUT {int *ndimslow, int *ndimmid, int *ndimfast} get_3d_image_size; void get_3d_image_size(unsigned int element_number, int *ndimslow, int *ndimmid, int *ndimfast){ unsigned int reserved; size_t inslow, inmid, infast; reserved = 0; cbf_failnez(cbf_get_3d_image_size(self,reserved,element_number,&inslow,&inmid,&infast)); *ndimslow = (int)inslow; /* FIXME - is that how to convert? */ *ndimmid = (int)inmid; *ndimfast = (int)infast; } ""","get_3d_image_size",["Integer element_number"],["size_t ndimslow","size_t ndimmid","size_t ndimfast"]], "cbf_get_3d_image_size_fs": [""" %apply int *OUTPUT {int *ndimslow, int *ndimmid, int *ndimfast} get_3d_image_size; void get_3d_image_size_fs(unsigned int element_number, int *ndimfast, int *ndimmid, int *ndimslow){ unsigned int reserved; size_t inslow, inmid, infast; reserved = 0; cbf_failnez(cbf_get_3d_image_size_fs(self,reserved,element_number,&infast,&inmid,&inslow)); *ndimslow = (int)inslow; /* FIXME - is that how to convert? */ *ndimmid = (int)inmid; *ndimfast = (int)infast; } ""","get_3d_image_size",["Integer element_number"],["size_t ndimfast","size_t ndimmid","size_t ndimslow"]], "cbf_get_3d_image_size_sf": [""" %apply int *OUTPUT {int *ndimslow, int *ndimmid, int *ndimfast} get_3d_image_size_sf; void get_3d_image_size_sf(unsigned int element_number, int *ndimslow, int *ndimmid, int *ndimfast){ unsigned int reserved; size_t inslow, inmid, infast; reserved = 0; cbf_failnez(cbf_get_3d_image_size_sf(self,reserved,element_number,&inslow,&inmid,&infast)); *ndimslow = (int)inslow; /* FIXME - is that how to convert? */ *ndimmid = (int)inmid; *ndimfast = (int)infast; } ""","get_3d_image_size_sf",["Integer element_number"],["size_t ndimslow","size_t ndimmid","size_t ndimfast"]], "cbf_get_pixel_size" : [""" %apply double *OUTPUT {double *psize} get_pixel_size; void get_pixel_size(unsigned int element_number, unsigned int axis_number, double *psize){ cbf_failnez(cbf_get_pixel_size(self, element_number, axis_number, psize)); } ""","get_pixel_size",["Int element_number","Int axis_number"], ["Float pixel_size"]] , "cbf_get_pixel_size_fs" : [""" %apply double *OUTPUT {double *psize} get_pixel_size; void get_pixel_size_fs(unsigned int element_number, unsigned int axis_number, double *psize){ cbf_failnez(cbf_get_pixel_size_fs(self, element_number, axis_number, psize)); } ""","get_pixel_size_fs",["Int element_number","Int axis_number"], ["Float pixel_size"]] , "cbf_get_pixel_size_sf" : [""" %apply double *OUTPUT {double *psize} get_pixel_size; void get_pixel_size_sf(unsigned int element_number, unsigned int axis_number, double *psize){ cbf_failnez(cbf_get_pixel_size_sf(self, element_number, axis_number, psize)); } ""","get_pixel_size_sf",["Int element_number","Int axis_number"], ["Float pixel_size"]] , "cbf_set_pixel_size":[""" void set_pixel_size (unsigned int element_number, unsigned int axis_number, double psize){ cbf_failnez(cbf_set_pixel_size(self, element_number, axis_number, psize)); } ""","set_pixel_size", ["Int element_number","Int axis_number","Float pixel size"],[]], "cbf_set_pixel_size_fs":[""" void set_pixel_size_fs (unsigned int element_number, unsigned int axis_number, double psize){ cbf_failnez(cbf_set_pixel_size_fs(self, element_number, axis_number, psize)); } ""","set_pixel_size_fs", ["Int element_number","Int axis_number","Float pixel size"],[]], "cbf_set_pixel_size_sf":[""" void set_pixel_size_sf (unsigned int element_number, unsigned int axis_number, double psize){ cbf_failnez(cbf_set_pixel_size_sf(self, element_number, axis_number, psize)); } ""","set_pixel_size_sf", ["Int element_number","Int axis_number","Float pixel size"],[]], "cbf_write_file" : [""" void write_file(const char* filename, int ciforcbf, int headers, int encoding){ FILE *stream; int readable; /* Make the file non-0 to make CBFlib close the file */ readable = 1; if ( ! ( stream = fopen (filename, "w+b")) ){ cbf_failnez(CBF_FILEOPEN); } else{ cbf_failnez(cbf_write_file(self, stream, readable, ciforcbf, headers, encoding)); } } ""","write_file",["String filename","Integer ciforcbf","Integer Headers", "Integer encoding"],[]], "cbf_write_widefile" : [""" void write_widefile(const char* filename, int ciforcbf, int headers, int encoding){ FILE *stream; int readable; /* Make the file non-0 to make CBFlib close the file */ readable = 1; if ( ! ( stream = fopen (filename, "w+b")) ){ cbf_failnez(CBF_FILEOPEN); } else{ cbf_failnez(cbf_write_widefile(self, stream, readable, ciforcbf, headers, encoding)); } } ""","write_widefile",["String filename","Integer ciforcbf","Integer Headers", "Integer encoding"],[]], "cbf_read_template":[""" void read_template(char* filename){ /* CBFlib needs a stream that will remain open hence DO NOT open from python */ FILE *stream; if ( ! ( stream = fopen (filename, "rb")) ){ cbf_failnez(CBF_FILEOPEN); } else{ cbf_failnez(cbf_read_template (self, stream)); } } ""","read_template",["String filename"],[]], "cbf_read_file" : [""" void read_file(char* filename, int headers){ /* CBFlib needs a stream that will remain open hence DO NOT open from python */ FILE *stream; if ( ! ( stream = fopen (filename, "rb")) ){ cbf_failnez(CBF_FILEOPEN); } else{ cbf_failnez(cbf_read_file(self, stream, headers)); } } ""","read_file",["String filename","Integer headers"],[]], "cbf_read_widefile" : [""" void read_widefile(char* filename, int headers){ /* CBFlib needs a stream that will remain open hence DO NOT open from python */ FILE *stream; if ( ! ( stream = fopen (filename, "rb")) ){ cbf_failnez(CBF_FILEOPEN); } else{ cbf_failnez(cbf_read_widefile(self, stream, headers)); } } ""","read_widefile",["String filename","Integer headers"],[]], "cbf_set_doublevalue":[""" void set_doublevalue(const char *format, double number){ cbf_failnez(cbf_set_doublevalue(self,format,number));} ""","set_doublevalue",["String format","Float number"],[]], "cbf_require_integervalue":[""" %apply int *OUTPUT {int *number} require_integervalue; void require_integervalue(int *number, int thedefault){ cbf_failnez(cbf_require_integervalue(self,number,thedefault)); } ""","require_integervalue", ["Int thedefault"],["Int number"]], "cbf_require_doublevalue":[""" %apply double *OUTPUT {double *number} require_doublevalue; void require_doublevalue(double *number, double defaultvalue){ cbf_failnez(cbf_require_doublevalue(self,number,defaultvalue)); } ""","require_doublevalue",["Float Default"],["Float Number"]], "cbf_require_column_value":[""" const char* require_column_value(const char *columnname, const char *defaultvalue){ const char * result; cbf_failnez(cbf_require_column_value(self,columnname, &result,defaultvalue)); return result; } ""","require_column_value", ["String columnnanme","String Default"],["String Name"]], "cbf_require_column_doublevalue":[""" %apply double *OUTPUT { double *number} require_column_doublevalue; void require_column_doublevalue(const char *columnname, double * number, const double defaultvalue){ cbf_failnez(cbf_require_column_doublevalue(self, columnname,number,defaultvalue)); } ""","require_column_doublevalue",["String columnname","Float Value"], ["Float defaultvalue"]], "cbf_require_column_integervalue":[""" %apply int *OUTPUT {int *number} require_column_integervalue; void require_column_integervalue(const char *columnname, int *number, const int defaultvalue){ cbf_failnez(cbf_require_column_integervalue(self, columnname, number,defaultvalue)); } ""","require_column_integervalue",["String Columnvalue","Int default"], ["Int Value"]], "cbf_require_value" : [""" const char* require_value(const char* defaultvalue){ const char * result; cbf_failnez(cbf_require_value(self, &result, defaultvalue)); return result; } ""","require_value",["String defaultvalue"],['String Value']], "cbf_require_diffrn_id":[""" const char* require_diffrn_id(const char* defaultid){ const char * id; cbf_failnez(cbf_require_diffrn_id(self,&id,defaultid)); return id; } ""","require_diffrn_id", ["String Default_id"],["String diffrn_id"]], "cbf_get_polarization":[""" /* Returns a pair of double values */ %apply double *OUTPUT { double *in1, double *in2 }; void get_polarization(double *in1,double *in2){ cbf_failnez(cbf_get_polarization (self, in1, in2)); } ""","get_polarization",[], ["float polarizn_source_ratio","float polarizn_source_norm"]], "cbf_set_polarization":[""" void set_polarization (double polarizn_source_ratio, double polarizn_source_norm){ cbf_failnez(cbf_set_polarization(self, polarizn_source_ratio, polarizn_source_norm)); } ""","set_polarization", ["Float polarizn_source_ratio","Float polarizn_source_norm"],[]], "cbf_get_divergence":[""" %apply double *OUTPUT {double *div_x_source, double *div_y_source, double *div_x_y_source } get_divergence; void get_divergence(double *div_x_source, double *div_y_source, double *div_x_y_source){ cbf_failnez(cbf_get_divergence(self, div_x_source, div_y_source, div_x_y_source)); } ""","get_divergence",[], ["Float div_x_source","Float div_y_source","Float div_x_y_source"]], "cbf_set_divergence":[""" void set_divergence ( double div_x_source, double div_y_source, double div_x_y_source){ cbf_failnez(cbf_set_divergence (self, div_x_source, div_y_source,div_x_y_source)); } ""","set_divergence", ["Float div_x_source","Float div_y_source","Float div_x_y_source"],[]], "cbf_get_gain":[""" %apply double *OUTPUT {double *gain, double *gain_esd} get_gain; void get_gain (unsigned int element_number, double *gain, double *gain_esd){ cbf_failnez(cbf_get_gain (self, element_number, gain, gain_esd)); } ""","get_gain", [],["Float gain", "Float gain_esd"]], "cbf_set_gain":[""" void set_gain (unsigned int element_number, double gain, double gain_esd){ cbf_failnez(cbf_set_gain (self, element_number, gain, gain_esd)); } ""","set_gain",["Float gain", "Float gain_esd"],[]], "cbf_get_element_id":[""" const char * get_element_id(unsigned int element_number){ const char * result; cbf_failnez(cbf_get_element_id (self, element_number, &result)); return result; } ""","get_element_id", ["Integer element_number"],["String"]], "cbf_set_axis_setting":[""" void set_axis_setting(const char *axis_id, double start, double increment){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_set_axis_setting(self,reserved, axis_id,start,increment)); } ""","set_axis_setting",["String axis_id", "Float start", "Float increment"], []], "cbf_get_axis_setting":[""" %apply double *OUTPUT {double *start, double *increment} get_axis_setting; void get_axis_setting(const char *axis_id, double *start, double *increment){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_get_axis_setting(self,reserved,axis_id, start,increment)); } ""","get_axis_setting",["String axis_id"],["Float start", "Float increment"],], "cbf_get_datestamp":[""" %apply int *OUTPUT {int *year, int *month, int *day, int *hour, int *minute, double *second, int *timezone} get_datestamp; void get_datestamp(int *year, int *month, int *day, int *hour, int *minute, double *second, int *timezone){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_get_datestamp(self,reserved, year,month,day,hour,minute,second,timezone)); } ""","get_datestamp",[],["int year", "int month", "int day", "int hour", "int minute", "double second", "int timezone"]], "cbf_set_datestamp":[""" void set_datestamp(int year, int month, int day, int hour, int minute, double second, int timezone, double precision){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_set_datestamp(self,reserved, year,month,day,hour,minute,second,timezone,precision)); } ""","set_datestamp",["int year", "int month", "int day", "int hour", "int minute", "double second", "int timezone","Float precision"],[]], "cbf_get_timestamp":[""" %apply double *OUTPUT {double *time} get_timestamp; %apply int *OUTPUT {int *timezone} get_timestamp; void get_timestamp(double *time, int *timezone){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_get_timestamp(self,reserved,time,timezone)); } ""","get_timestamp",[],["Float time","Integer timezone"]], "cbf_set_timestamp":[""" void set_timestamp(double time, int timezone, double precision){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_set_timestamp(self,reserved,time,timezone,precision)); } ""","set_timestamp",["Float time","Integer timezone","Float precision"],[]], "cbf_set_current_timestamp":[""" void set_current_timestamp(int timezone){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_set_current_timestamp(self,reserved,timezone)); } ""","set_current_timestamp",["Integer timezone"],[]], "cbf_get_overload":[""" %apply double *OUTPUT {double *overload} get_overload; void get_overload(unsigned int element_number, double *overload){ cbf_failnez(cbf_get_overload(self,element_number,overload)); } ""","get_overload",["Integer element_number"],["Float overload"]], "cbf_set_overload":[""" void set_overload(unsigned int element_number, double overload){ cbf_failnez(cbf_set_overload(self,element_number,overload)); } ""","set_overload",["Integer element_number","Float overload"],[]], "cbf_set_integration_time":[""" void set_integration_time(double time){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_set_integration_time(self,reserved,time)); } ""","set_integration_time",["Float time"],[]], "cbf_get_integration_time":[""" %apply double *OUTPUT {double *time} get_integration_time; void get_integration_time( double *time ){ unsigned int reserved; double tim; reserved = 0; cbf_failnez(cbf_get_integration_time(self,reserved,&tim)); *time = tim; } ""","get_integration_time",[],["Float time"]], "cbf_get_orientation_matrix":[""" %apply double *OUTPUT {double *m0,double *m1,double *m2, double *m3,double *m4, double *m5,double *m6, double *m7,double *m8 } get_orientation_matrix; void get_orientation_matrix( double *m0,double *m1, double *m2,double *m3,double *m4,double *m5,double *m6, double *m7,double *m8){ double m[9]; cbf_failnez(cbf_get_orientation_matrix(self,m)); *m0 = m[0]; *m1=m[1] ; *m2=m[2] ; *m3 = m[3]; *m4=m[4] ; *m5=m[5] ; *m6 = m[6]; *m7=m[7] ; *m8=m[8] ; } ""","get_orientation_matrix", [],[ "Float matrix_%d"%(ind) for ind in range(9) ]], "cbf_get_unit_cell":[""" %apply double *OUTPUT {double *a, double *b, double *c, double *alpha, double *beta, double *gamma} get_unit_cell; void get_unit_cell(double *a, double *b, double *c, double *alpha, double *beta, double *gamma) { double cell[6]; cbf_failnez(cbf_get_unit_cell(self,cell,NULL)); *a = cell[0]; *b = cell[1]; *c = cell[2]; *alpha = cell[3]; *beta = cell[4]; *gamma = cell[5]; } ""","get_unit_cell", [],["Float a", "Float b", "Float c", "Float alpha", "Float beta", "Float gamma" ] ], "cbf_get_unit_cell_esd":[""" %apply double *OUTPUT {double *a_esd, double *b_esd, double *c_esd, double *alpha_esd, double *beta_esd, double *gamma_esd} get_unit_cell_esd; void get_unit_cell_esd(double *a_esd, double *b_esd, double *c_esd, double *alpha_esd, double *beta_esd, double *gamma_esd) { double cell_esd[6]; cbf_failnez(cbf_get_unit_cell(self,NULL,cell_esd)); *a_esd = cell_esd[0]; *b_esd = cell_esd[1]; *c_esd = cell_esd[2]; *alpha_esd = cell_esd[3]; *beta_esd = cell_esd[4]; *gamma_esd = cell_esd[5]; } ""","get_unit_cell", [],["doubleArray cell"] ], "cbf_get_reciprocal_cell":[""" %apply double *OUTPUT {double *astar, double *bstar, double *cstar, double *alphastar, double *betastar, double *gammastar} get_reciprocal_cell; void get_reciprocal_cell(double *astar, double *bstar, double *cstar, double *alphastar, double *betastar, double *gammastar) { double rcell[6]; cbf_failnez(cbf_get_reciprocal_cell(self,rcell,NULL)); *astar = rcell[0]; *bstar = rcell[1]; *cstar = rcell[2]; *alphastar = rcell[3]; *betastar = rcell[4]; *gammastar = rcell[5]; } ""","get_reciprocal_cell", [],["Float astar", "Float bstar", "Float cstar", "Float alphastar", "Float betastar", "Float gammastar"] ], "cbf_get_reciprocal_cell_esd":[""" %apply double *OUTPUT {double *a_esd, double *b_esd, double *c_esd, double *alpha_esd, double *beta_esd, double *gamma_esd} get_reciprocal_cell_esd; void get_reciprocal_cell_esd(double *a_esd, double *b_esd, double *c_esd, double *alpha_esd, double *beta_esd, double *gamma_esd) { double cell_esd[6]; cbf_failnez(cbf_get_reciprocal_cell(self,NULL,cell_esd)); *a_esd = cell_esd[0]; *b_esd = cell_esd[1]; *c_esd = cell_esd[2]; *alpha_esd = cell_esd[3]; *beta_esd = cell_esd[4]; *gamma_esd = cell_esd[5]; } ""","get_reciprocal_cell", [],["doubleArray cell"] ], "cbf_set_unit_cell":[""" void set_unit_cell(double cell[6]) { cbf_failnez(cbf_set_unit_cell(self,cell,NULL)); } ""","set_unit_cell", ["double cell[6]"],[] ], "cbf_set_unit_cell_esd":[""" void set_unit_cell_esd(double cell_esd[6]) { cbf_failnez(cbf_set_unit_cell(self,NULL,cell_esd)); } ""","set_unit_cell_esd", ["double cell_esd[6]"],[] ], "cbf_set_reciprocal_cell":[""" void set_reciprocal_cell(double cell[6]) { cbf_failnez(cbf_set_reciprocal_cell(self,cell,NULL)); } ""","set_reciprocal_cell", ["double cell[6]"],[] ], "cbf_set_reciprocal_cell_esd":[""" void set_reciprocal_cell_esd(double cell_esd[6]) { cbf_failnez(cbf_set_reciprocal_cell(self,NULL,cell_esd)); } ""","set_reciprocal_cell_esd", ["double cell_esd[6]"],[] ], "cbf_set_tag_category":[""" void set_tag_category(const char *tagname, const char* categoryname_in){ cbf_failnez(cbf_set_tag_category(self,tagname, categoryname_in)); } ""","set_tag_category",["String tagname","String categoryname_in"],[] ], "cbf_find_tag_category":[""" const char * find_tag_category(const char *tagname){ const char * result; cbf_failnez(cbf_find_tag_category(self,tagname, &result)); return result; } ""","find_tag_category",["String tagname"],["String categoryname"] ], "cbf_require_tag_root":[""" const char* require_tag_root(const char* tagname){ const char* result; cbf_failnez(cbf_require_tag_root(self,tagname,&result)); return result; } ""","require_tag_root",["String tagname"],["String tagroot"]], "cbf_find_tag_root":[""" const char * find_tag_root(const char* tagname){ const char* result; cbf_failnez(cbf_find_tag_root(self,tagname,&result)); return result; } ""","find_tag_root",["String tagname"],["String tagroot"]], "cbf_set_tag_root":[""" void set_tag_root(const char* tagname, const char* tagroot_in){ cbf_failnez(cbf_set_tag_root(self,tagname,tagroot_in)); } ""","set_tag_root",["String tagname","String tagroot_in"],[]], "cbf_set_category_root":[""" void set_category_root(const char* categoryname, const char* categoryroot){ cbf_failnez(cbf_set_category_root(self,categoryname,categoryroot)); } ""","set_category_root",["String categoryname","String categoryroot"],[]], "cbf_find_category_root":[""" const char* find_category_root(const char* categoryname){ const char * result; cbf_failnez(cbf_find_category_root(self,categoryname,&result)); return result; } ""","find_category_root",["String categoryname"],["String categoryroot"]], "cbf_require_category_root":[""" const char* require_category_root (const char* categoryname){ const char* result; cbf_failnez(cbf_require_category_root(self,categoryname, &result)); return result; } ""","cbf_require_category_root",["String Categoryname"],["String categoryroot"]], "cbf_set_orientation_matrix":[""" void set_orientation_matrix( double m0,double m1, double m2,double m3,double m4,double m5,double m6, double m7,double m8){ double m[9]; m[0] = m0; m[1]=m1 ; m[2]=m2 ; m[3] = m3; m[4]=m4 ; m[5]=m5 ; m[6] = m6; m[7]=m7 ; m[8]=m8 ; cbf_failnez(cbf_get_orientation_matrix(self,m)); } ""","set_orientation_matrix", [ "Float matrix_%d"%(ind) for ind in range(9) ] ,[]], "cbf_set_bin_sizes":[""" void set_bin_sizes( int element_number, double slowbinsize_in, double fastbinsize_in) { cbf_failnez(cbf_set_bin_sizes(self,element_number,slowbinsize_in,fastbinsize_in)); } ""","set_bin_sizes",["Integer element_number","Float slowbinsize_in","Float fastbinsize_in"],[] ], "cbf_get_bin_sizes":[""" %apply double *OUTPUT {double *slowbinsize,double *fastbinsize}; void get_bin_sizes(int element_number, double *slowbinsize, double *fastbinsize) { cbf_failnez(cbf_get_bin_sizes (self, (unsigned int)element_number, slowbinsize, fastbinsize)); } ""","get_bin_sizes",["Integer element_number"],["Float slowbinsize","Float fastbinsize"] ], # cbfhandle dict functions UNTESTED "cbf_require_dictionary":[""" cbf_handle require_dictionary(){ cbf_handle temp; cbf_failnez(cbf_require_dictionary(self,&temp)); return temp; } ""","require_dictionary",[],["CBFHandle dictionary"]], "cbf_get_dictionary":[""" cbf_handle get_dictionary(){ cbf_handle temp; cbf_failnez(cbf_get_dictionary(self,&temp)); return temp; } ""","get_dictionary",[],["CBFHandle dictionary"]], "cbf_set_dictionary":[""" void set_dictionary(cbf_handle other){ cbf_failnez(cbf_set_dictionary(self,other)); } ""","set_dictionary",["CBFHandle dictionary"],[]], "cbf_convert_dictionary":[""" void convert_dictionary(cbf_handle other){ cbf_failnez(cbf_convert_dictionary(self,other)); } ""","convert_dictionary",["CBFHandle dictionary"],[]], "cbf_construct_detector":[""" cbf_detector construct_detector(unsigned int element_number){ cbf_detector detector; cbf_failnez(cbf_construct_detector(self,&detector,element_number)); return detector; } ""","construct_detector",["Integer element_number"],["pycbf detector object"]], "cbf_construct_reference_detector":[""" cbf_detector construct_reference_detector(unsigned int element_number){ cbf_detector detector; cbf_failnez(cbf_construct_reference_detector(self,&detector,element_number)); return detector; } ""","construct_reference_detector",["Integer element_number"],["pycbf detector object"]], "cbf_require_reference_detector":[""" cbf_detector require_reference_detector(unsigned int element_number){ cbf_detector detector; cbf_failnez(cbf_require_reference_detector(self,&detector,element_number)); return detector; } ""","require_reference_detector",["Integer element_number"],["pycbf detector object"]], # Prelude to the next section of the nuweb doc "cbf_construct_goniometer":[""" cbf_goniometer construct_goniometer(){ cbf_goniometer goniometer; cbf_failnez(cbf_construct_goniometer(self,&goniometer)); return goniometer; } ""","construct_goniometer",[],["pycbf goniometer object"]], } class cbfhandlewrapper: def __init__(self): self.code = """ // Tell SWIG not to make constructor for these objects %nodefault cbf_handle; %nodefault cbf_handle_struct; %nodefault cbf_node; // A couple of blockitem functions return CBF_NODETYPE typedef enum { CBF_UNDEFNODE, /* Undefined */ CBF_LINK, /* Link */ CBF_ROOT, /* Root */ CBF_DATABLOCK, /* Datablock */ CBF_SAVEFRAME, /* Saveframe */ CBF_CATEGORY, /* Category */ CBF_COLUMN /* Column */ } CBF_NODETYPE; // Tell SWIG what the object is, so we can build the class typedef struct { cbf_node *node; int row, search_row; } cbf_handle_struct; typedef cbf_handle_struct *cbf_handle; typedef cbf_handle_struct handle; %feature("autodoc","1"); %extend cbf_handle_struct{ // Tell SWIG to attach functions to the structure cbf_handle_struct(){ // Constructor cbf_handle handle; cbf_failnez(cbf_make_handle(&handle)); return handle; } ~cbf_handle_struct(){ // Destructor cbf_failnez(cbf_free_handle(self)); } """ self.tail = """ }; // End of cbf_handle_struct """ # End of init function def get_code(self): return self.code+self.tail def wrap(self,cfunc,prototype,args,docstring): # print "cfunc: ", cfunc pyfunc = cfunc.replace("cbf_","") # Insert a comment for debugging this script code = "\n/* cfunc %s pyfunc %s \n"%(cfunc,pyfunc) for a in args: code += " arg %s "%(a) code += "*/\n\n" # Make and free handle are done in the header so skip if cfunc.find("cbf_make_handle")>-1 or cfunc.find("cbf_free_handle")>-1: # Constructor and destructor done in headers return if args[0] != "cbf_handle handle": # Must be for cbfhandle print "problem",cfunc,pyfunc,args return if len(args)==1: # Only takes CBFhandle arg code+= docstringwrite(pyfunc,[],[],prototype,docstring) code+= " void %s(void){\n"%(pyfunc) code+= " cbf_failnez(%s(self));}\n"%(cfunc) self.code=self.code+code return # Now case by case rather than writing a proper parser # Special cases ... not_found=0 try: code, pyname, input, output = cbfhandle_specials[cfunc] self.code += docstringwrite(pyname,input,output, prototype,docstring)+ code return except KeyError: not_found = 1 # print "KeyError" except ValueError: print "problem in",cfunc for item in cbfhandle_specials[cfunc]: print "***",item raise if len(args)==2: if args[1].find("const char")>-1 and \ args[1].find("*")>-1 and \ args[1].find("**")==-1 : # 1 input string code += docstringwrite(pyfunc,[],["string"],prototype,docstring) code += " void %s(const char* arg){\n"%(pyfunc) code +=" cbf_failnez(%s(self,arg));}\n"%(cfunc) self.code=self.code+code return if args[1].find("const char")>-1 and \ args[1].find("**")>-1 :# return string code += docstringwrite(pyfunc,["string"],[],prototype,docstring) code += " const char* %s(void){\n"%(pyfunc) code += " const char* result;\n" code += " cbf_failnez(%s(self, &result));\n"%(cfunc) code += " return result;}\n" self.code=self.code+code return if args[1].find("unsigned int")>-1 and args[1].find("*")==-1: # set uint if args[1].find("reserved")>-1: raise Exception("Setting reserved??? %s %s %s"%(pyfunc, cfunc,str(args))) code += docstringwrite(pyfunc,["Integer"],[],prototype,docstring) code +=" void %s(unsigned int arg){\n"%(pyfunc) code +=" cbf_failnez(%s(self,arg));}\n"%(cfunc) self.code=self.code+code return if args[1].find("unsigned int *")>-1 and args[1].find("**")==-1: # output uint if args[1].find("reserved")>-1: raise Exception("Setting reserved??? %s %s %s"%(pyfunc, cfunc,str(args))) code += docstringwrite(pyfunc,[],["Integer"],prototype,docstring) code +=" unsigned int %s(void){\n"%(pyfunc) code +=" unsigned int result;\n" code +=" cbf_failnez(%s(self,&result));\n"%(cfunc) code +=" return result;}\n" self.code=self.code+code return # For the rest attempt to guess if args[1].find("cbf")==-1: # but do not try the goniometer constructor if args[1].find("*")>-1 and args[1].find("cbf")==-1: # pointer used for returning something type = args[1].split(" ")[0] code += docstringwrite(pyfunc,[],[type.replace("*","")], prototype,docstring) code+= " "+type+" "+pyfunc+"(void){\n" code+= " "+type+" result;\n" code+= " cbf_failnez(%s(self,&result));\n"%(cfunc) code+= " return result;}\n" self.code=self.code+code return else: var = args[1].split(" ")[-1] code += docstringwrite(pyfunc,[],[args[1]],prototype,docstring) code+= " void %s(%s){\n"%(pyfunc,args[1]) code +=" cbf_failnez(%s(self,%s));}\n"%(cfunc,var) self.code=self.code+code return if not_found: code+= " void %s(void){\n"%(pyfunc) code +=" cbf_failnez(CBF_NOTIMPLEMENTED);}\n" self.code=self.code+code print "Have not implemented: cbfhandle.%s"%(pyfunc) print " ",cfunc print " args:" for a in args: print " ",a print return cbf_handle_wrapper = cbfhandlewrapper() cbf_goniometer_specials = { "cbf_get_rotation_range":[""" %apply double *OUTPUT {double *start,double *increment}; void get_rotation_range(double *start,double *increment){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_get_rotation_range (self,reserved, start,increment)); } ""","get_rotation_range",[],["Float start","Float increment"]], "cbf_rotate_vector":[""" %apply double *OUTPUT {double *final1, double *final2, double *final3}; void rotate_vector (double ratio, double initial1,double initial2, double initial3, double *final1, double *final2, double *final3){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_rotate_vector (self, reserved, ratio, initial1, initial2, initial3, final1, final2, final3)); } """, "rotate_vector", [ "double ratio", "double initial1","double initial2", "double initial3" ] , [ "double final1" ,"double final2" , "double final3" ] ], "cbf_get_reciprocal":[""" %apply double *OUTPUT {double *reciprocal1,double *reciprocal2, double *reciprocal3}; void get_reciprocal (double ratio,double wavelength, double real1, double real2, double real3, double *reciprocal1,double *reciprocal2, double *reciprocal3){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_get_reciprocal(self,reserved, ratio, wavelength, real1, real2, real3,reciprocal1, reciprocal2,reciprocal3)); } """, "get_reciprocal", ["double ratio","double wavelength", "double real1","double real2","double real3"], ["double reciprocal1","double reciprocal2", "double reciprocal3" ]], "cbf_get_rotation_axis":[""" %apply double *OUTPUT {double *vector1, double *vector2, double *vector3}; void get_rotation_axis (double *vector1, double *vector2, double *vector3){ unsigned int reserved; reserved = 0; cbf_failnez(cbf_get_rotation_axis (self, reserved, vector1, vector2, vector3)); } ""","get_rotation_axis", [] , ["double vector1", "double vector2", "double vector3"] ], } class cbfgoniometerwrapper: def __init__(self): self.code = """ // Tell SWIG not to make constructor for these objects %nodefault cbf_positioner_struct; %nodefault cbf_goniometer; %nodefault cbf_axis_struct; // Tell SWIG what the object is, so we can build the class typedef struct { double matrix [3][4]; cbf_axis_struct *axis; size_t axes; int matrix_is_valid, axes_are_connected; } cbf_positioner_struct; typedef cbf_positioner_struct *cbf_goniometer; %feature("autodoc","1"); %extend cbf_positioner_struct{// Tell SWIG to attach functions to the structure cbf_positioner_struct(){ // Constructor // DO NOT CONSTRUCT WITHOUT A CBFHANDLE cbf_failnez(CBF_ARGUMENT); return NULL; /* Should never be executed */ } ~cbf_positioner_struct(){ // Destructor cbf_failnez(cbf_free_goniometer(self)); } """ self.tail = """ }; // End of cbf_positioner """ def wrap(self,cfunc,prototype,args,docstring): if cfunc.find("cbf_free_goniometer")>-1: return try: code, pyname, input, output = cbf_goniometer_specials[cfunc] self.code += docstringwrite(pyname,input,output, prototype,docstring)+ code except KeyError: print "TODO: Goniometer:",prototype def get_code(self): return self.code+self.tail cbf_goniometer_wrapper = cbfgoniometerwrapper() cbf_detector_specials = { "cbf_get_pixel_normal":[""" %apply double *OUTPUT {double *normal1,double *normal2, double *normal3}; void get_pixel_normal ( double index1, double index2, double *normal1,double *normal2, double *normal3){ cbf_failnez(cbf_get_pixel_normal(self, index1,index2,normal1,normal2,normal3)); } ""","get_pixel_normal",["double index1","double index2"] , ["double normal1","double normal2", "double normal3" ] ], "cbf_get_pixel_normal_fs":[""" %apply double *OUTPUT {double *normal1,double *normal2, double *normal3}; void get_pixel_normal_fs ( double indexfast, double indexslow, double *normal1,double *normal2, double *normal3){ cbf_failnez(cbf_get_pixel_normal_fs(self, indexfast,indexslow,normal1,normal2,normal3)); } ""","get_pixel_normal_fs",["double indexfast","double indexslow"] , ["double normal1","double normal2", "double normal3" ] ], "cbf_get_pixel_normal_sf":[""" %apply double *OUTPUT {double *normal1, double *normal2, double *normal3}; void get_pixel_normal_sf ( double indexslow, double indexfast, double *normal1, double *normal2, double *normal3){ cbf_failnez(cbf_get_pixel_normal_sf(self, indexslow,indexfast,normal1,normal2,normal3)); } ""","get_pixel_normal_sf",["double indexslow","double indexfast"] , ["double normal1","double normal2", "double normal3" ] ], "cbf_get_detector_axis_slow":[""" %apply double *OUTPUT {double *slowaxis1, double *slowaxis2, double *slowaxis3}; void get_detector_axis_slow ( double *slowaxis1, double *slowaxis2, double *slowaxis3){ cbf_failnez(cbf_get_detector_axis_slow(self, slowaxis1,slowaxis2,slowaxis3)); } ""","get_detector_axis_slow", [ ], ["double slowaxis1","double slowaxis2", "double slowaxis3" ] ], "cbf_get_detector_axis_fast":[""" %apply double *OUTPUT {double *fastaxis1, double *fastaxis2, double *fastaxis3}; void get_detector_axis_fast ( double *fastaxis1, double *fastaxis2, double *fastaxis3){ cbf_failnez(cbf_get_detector_axis_fast(self, fastaxis1,fastaxis2,fastaxis3)); } ""","get_detector_axis_fast", [ ], ["double fastaxis1","double fastaxis2", "double fastaxis3" ] ], "cbf_get_detector_axes":[""" %apply double *OUTPUT {double *slowaxis1, double *slowaxis2, double *slowaxis3, double *fastaxis1, double *fastaxis2, double *fastaxis3}; void get_detector_axes ( double *slowaxis1, double *slowaxis2, double *slowaxis3, double *fastaxis1, double *fastaxis2, double *fastaxis3){ cbf_failnez(cbf_get_detector_axes(self, slowaxis1,slowaxis2,slowaxis3, fastaxis1,fastaxis2,fastaxis3)); } ""","get_detector_axes", [ ], ["double slowaxis1","double slowaxis2", "double slowaxis3", "double fastaxis1","double fastaxis2", "double fastaxis3" ] ], "cbf_get_detector_axes_fs":[""" %apply double *OUTPUT {double *slowaxis1, double *slowaxis2, double *slowaxis3, double *fastaxis1, double *fastaxis2, double *fastaxis3}; void get_detector_axes_fs ( double *fastaxis1, double *fastaxis2, double *fastaxis3, double *slowaxis1, double *slowaxis2, double *slowaxis3){ cbf_failnez(cbf_get_detector_axes(self, slowaxis1,slowaxis2,slowaxis3, fastaxis1,fastaxis2,fastaxis3)); } ""","get_detector_axes", [ ], ["double fastaxis1","double fastaxis2", "double fastaxis3", "double slowaxis1","double slowaxis2", "double slowaxis3"] ], "cbf_get_detector_axes_sf":[""" %apply double *OUTPUT {double *slowaxis1, double *slowaxis2, double *slowaxis3, double *fastaxis1, double *fastaxis2, double *fastaxis3}; void get_detector_axes_sf ( double *slowaxis1, double *slowaxis2, double *slowaxis3, double *fastaxis1, double *fastaxis2, double *fastaxis3){ cbf_failnez(cbf_get_detector_axes(self, slowaxis1,slowaxis2,slowaxis3, fastaxis1,fastaxis2,fastaxis3)); } ""","get_detector_axes_sf", [ ], ["double slowaxis1","double slowaxis2", "double slowaxis3", "double fastaxis1","double fastaxis2", "double fastaxis3" ] ], "cbf_get_pixel_area":[""" %apply double *OUTPUT{double *area,double *projected_area}; void get_pixel_area(double index1, double index2, double *area,double *projected_area){ cbf_failnez(cbf_get_pixel_area (self, index1, index2, area,projected_area)); } ""","get_pixel_area",["double index1", "double index2"], ["double area","double projected_area"] ], "cbf_get_pixel_area_fs":[""" %apply double *OUTPUT{double *area,double *projected_area}; void get_pixel_area_fs(double indexfast, double indexslow, double *area,double *projected_area){ cbf_failnez(cbf_get_pixel_area_fs (self, indexfast, indexslow, area,projected_area)); } ""","get_pixel_area_fs",["double indexfast", "double indexslow"], ["double area","double projected_area"] ], "cbf_get_pixel_area_sf":[""" %apply double *OUTPUT{double *area,double *projected_area}; void get_pixel_area_sf(double indexslow, double indexfast, double *area,double *projected_area){ cbf_failnez(cbf_get_pixel_area_sf (self, indexslow, indexfast, area,projected_area)); } ""","get_pixel_area_sf",["double indexslow", "double indexfast"], ["double area","double projected_area"] ], "cbf_get_detector_distance":[""" %apply double *OUTPUT {double *distance}; void get_detector_distance (double *distance){ cbf_failnez(cbf_get_detector_distance(self,distance)); } ""","get_detector_distance",[],["double distance"]], "cbf_get_detector_normal":[""" %apply double *OUTPUT {double *normal1, double *normal2, double *normal3}; void get_detector_normal(double *normal1, double *normal2, double *normal3){ cbf_failnez(cbf_get_detector_normal(self, normal1, normal2, normal3)); } ""","get_detector_normal",[], ["double normal1", "double normal2", "double normal3"]], "cbf_get_pixel_coordinates":[""" %apply double *OUTPUT {double *coordinate1, double *coordinate2, double *coordinate3}; void get_pixel_coordinates(double index1, double index2, double *coordinate1, double *coordinate2, double *coordinate3){ cbf_failnez(cbf_get_pixel_coordinates(self, index1, index2, coordinate1, coordinate2, coordinate3)); } ""","get_pixel_coordinates",["double index1","double index2"], ["double coordinate1", "double coordinate2", "double coordinate3"] ], "cbf_get_pixel_coordinates_fs":[""" %apply double *OUTPUT {double *coordinate1, double *coordinate2, double *coordinate3}; void get_pixel_coordinates_fs(double indexfast, double indexslow, double *coordinate1, double *coordinate2, double *coordinate3){ cbf_failnez(cbf_get_pixel_coordinates_fs(self, indexfast, indexslow, coordinate1, coordinate2, coordinate3)); } ""","get_pixel_coordinates_fs",["double indexfast","double indexslow"], ["double coordinate1", "double coordinate2", "double coordinate3"] ], "cbf_get_pixel_coordinates_sf":[""" %apply double *OUTPUT {double *coordinate1, double *coordinate2, double *coordinate3}; void get_pixel_coordinates_sf(double indexslow, double indexfast, double *coordinate1, double *coordinate2, double *coordinate3){ cbf_failnez(cbf_get_pixel_coordinates_sf(self, indexslow, indexfast, coordinate1, coordinate2, coordinate3)); } ""","get_pixel_coordinates_sf",["double indexslow","double indexfast"], ["double coordinate1", "double coordinate2", "double coordinate3"] ], "cbf_get_beam_center":[""" %apply double *OUTPUT {double *index1, double *index2, double *center1,double *center2}; void get_beam_center(double *index1, double *index2, double *center1,double *center2){ cbf_failnez(cbf_get_beam_center(self, index1, index2, center1, center2)); } ""","get_beam_center",[], ["double index1", "double index2", "double center1","double center2"]], "cbf_get_beam_center_fs":[""" %apply double *OUTPUT {double *indexfast, double *indexslow, double *centerfast,double *centerslow}; void get_beam_center_fs(double *indexfast, double *indexslow, double *centerfast,double *centerslow){ cbf_failnez(cbf_get_beam_center_fs(self, indexfast, indexslow, centerfast, centerslow)); } ""","get_beam_center_fs",[], ["double indexfast", "double indexslow", "double centerfast","double centerslow"]], "cbf_get_beam_center_sf":[""" %apply double *OUTPUT {double *indexslow, double *indexfast, double *centerslow,double *centerfast}; void get_beam_center_sf(double *indexslow, double *indexfast, double *centerslow,double *centerfast){ cbf_failnez(cbf_get_beam_center_sf(self, indexslow, indexfast, centerslow, centerfast)); } ""","get_beam_center_sf",[], ["double indexslow", "double indexfast", "double centerslow","double centerfast"]], "cbf_set_beam_center":[""" void set_beam_center(double *indexslow, double *indexfast, double *centerslow,double *centerfast){ cbf_failnez(cbf_set_beam_center(self, indexslow, indexfast, centerslow, centerfast)); } ""","set_beam_center", ["double indexslow", "double indexfast", "double centerslow","double centerfast"],[]], "cbf_set_beam_center_fs":[""" void set_beam_center_fs(double *indexfast, double *indexslow, double *centerfast,double *centerslow){ cbf_failnez(cbf_set_beam_center_fs(self, indexfast, indexslow, centerfast, centerslow)); } ""","set_beam_center_fs", ["double indexfast", "double indexslow", "double centerfast","double centerslow"],[]], "cbf_set_beam_center_sf":[""" void set_beam_center_sf(double *indexslow, double *indexfast, double *centerslow,double *centerfast){ cbf_failnez(cbf_set_beam_center_sf(self, indexslow, indexfast, centerslow, centerfast)); } ""","set_beam_center_sf", ["double indexslow", "double indexfast", "double centerslow","double centerfast"],[]], "cbf_set_reference_beam_center":[""" void set_reference_beam_center(double *indexslow, double *indexfast, double *centerslow,double *centerfast){ cbf_failnez(cbf_set_reference_beam_center(self, indexslow, indexfast, centerslow, centerfast)); } ""","set_reference_beam_center", ["double indexslow", "double indexfast", "double centerslow","double centerfast"],[]], "cbf_set_reference_beam_center_fs":[""" void set_reference_beam_center_fs(double *indexfast, double *indexslow, double *centerfast,double *centerslow){ cbf_failnez(cbf_set_reference_beam_center_fs(self, indexfast, indexslow, centerfast, centerslow)); } ""","set_reference_beam_center_fs", ["double indexfast", "double indexslow", "double centerfast","double centerslow"],[]], "cbf_set_reference_beam_center_sf":[""" void set_reference_beam_center_sf(double *indexslow, double *indexfast, double *centerslow,double *centerfast){ cbf_failnez(cbf_set_reference_beam_center_sf(self, indexslow, indexfast, centerslow, centerfast)); } ""","set_reference_beam_center_sf", ["double indexslow", "double indexfast", "double centerslow","double centerfast"],[]], "cbf_get_inferred_pixel_size" : [""" %apply double *OUTPUT { double *psize } get_inferred_pixel_size; void get_inferred_pixel_size(unsigned int axis_number, double* psize){ cbf_failnez(cbf_get_inferred_pixel_size(self, axis_number, psize)); } ""","get_inferred_pixel_size",["Int axis_number"],["Float pixel size"] ], "cbf_get_inferred_pixel_size_fs" : [""" %apply double *OUTPUT { double *psize } get_inferred_pixel_size; void get_inferred_pixel_size_fs(unsigned int axis_number, double* psize){ cbf_failnez(cbf_get_inferred_pixel_size_fs(self, axis_number, psize)); } ""","get_inferred_pixel_size_fs",["Int axis_number"],["Float pixel size"] ], "cbf_get_inferred_pixel_size_sf" : [""" %apply double *OUTPUT { double *psize } get_inferred_pixel_size; void get_inferred_pixel_size_sf(unsigned int axis_number, double* psize){ cbf_failnez(cbf_get_inferred_pixel_size_sf(self, axis_number, psize)); } ""","get_inferred_pixel_size_sf",["Int axis_number"],["Float pixel size"] ] } class cbfdetectorwrapper: def __init__(self): self.code = """ // Tell SWIG not to make constructor for these objects %nodefault cbf_detector_struct; %nodefault cbf_detector; // Tell SWIG what the object is, so we can build the class typedef struct { cbf_positioner positioner; double displacement [2], increment [2]; size_t axes, index [2]; } cbf_detector_struct; typedef cbf_detector_struct *cbf_detector; %feature("autodoc","1"); %extend cbf_detector_struct{// Tell SWIG to attach functions to the structure cbf_detector_struct(){ // Constructor // DO NOT CONSTRUCT WITHOUT A CBFHANDLE cbf_failnez(CBF_ARGUMENT); return NULL; /* Should never be executed */ } ~cbf_detector_struct(){ // Destructor cbf_failnez(cbf_free_detector(self)); } """ self.tail = """ }; // End of cbf_detector """ def wrap(self,cfunc,prototype,args,docstring): if cfunc.find("cbf_free_detector")>-1: return try: code, pyname, input, output = cbf_detector_specials[cfunc] self.code += docstringwrite(pyname,input,output, prototype,docstring)+ code except KeyError: print "TODO: Detector:",prototype def get_code(self): return self.code+self.tail cbf_detector_wrapper = cbfdetectorwrapper() cbfgeneric_specials = { "cbf_get_local_integer_byte_order":[""" %cstring_output_allocate_size(char **bo, int *bolen, free(*$1)); %inline { void get_local_integer_byte_order(char **bo, int *bolen) { char * byteorder; char * bot; error_status = cbf_get_local_integer_byte_order(&byteorder); *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)} strncpy(bot,byteorder,*bolen); *bo = bot; } } ""","get_local_integer_byte_order",[],["char **bo", "int *bolen"]], "cbf_get_local_real_format":[""" %cstring_output_allocate_size(char **rf, int *rflen, free(*$1)); %inline { void get_local_real_format(char **rf, int *rflen) { char * real_format; char * rft; error_status = cbf_get_local_real_format(&real_format); *rflen = strlen(real_format); if (!(rft = (char *)malloc(*rflen))) {cbf_failnez(CBF_ALLOC)} strncpy(rft,real_format,*rflen); *rf = rft; } } ""","get_local_real_format",[],["char **rf", "int *rflen"]], "cbf_get_local_real_byte_order":[""" %cstring_output_allocate_size(char **bo, int *bolen, free(*$1)); %inline { void get_local_real_byte_order(char **bo, int *bolen) { char * byteorder; char * bot; error_status = cbf_get_local_real_byte_order(&byteorder); *bolen = strlen(byteorder); if (!(bot = (char *)malloc(*bolen))) {cbf_failnez(CBF_ALLOC)} strncpy(bot,byteorder,*bolen); *bo = bot; } } ""","get_local_real_byte_order",[],["char **bo", "int *bolen"]], "cbf_compute_cell_volume":[""" %apply double *OUTPUT {double *volume}; %inline { void compute_cell_volume(double cell[6], double *volume) { cbf_failnez(cbf_compute_cell_volume(cell,volume)); } } ""","compute_cell_volume",["double cell[6]"],["Float volume"]], "cbf_compute_reciprocal_cell":[""" %apply double *OUTPUT {double *astar, double *bstar, double *cstar, double *alphastar, double *betastar, double *gammastar}; %inline { void compute_reciprocal_cell(double cell[6], double *astar, double *bstar, double *cstar, double *alphastar, double *betastar, double *gammastar) { double rcell[6]; cbf_failnez(cbf_compute_reciprocal_cell(cell,rcell)); *astar = rcell[0]; *bstar = rcell[1]; *cstar = rcell[2]; *alphastar = rcell[3]; *betastar = rcell[4]; *gammastar = rcell[5]; } } ""","compute_reciprocal_cell",["double cell[6]"], ["Float astar", "Float bstar", "Float cstar", "Float alphastar", "Float betastar", "Float gammastar"] ] } class genericwrapper: def __init__(self): self.code = """ // Start of generic functions %feature("autodoc","1"); """ self.tail = "// End of generic functions\n" def get_code(self): return self.code + self.tail def wrap(self,cfunc,prototype,args,docstring): pyfunc = cfunc.replace("cbf_","") # Insert a comment for debugging this script code = "\n/* cfunc %s pyfunc %s \n"%(cfunc,pyfunc) for a in args: code += " arg %s "%(a) code += "*/\n\n" self.code+=code code = "" not_found = 0 try: code, pyname, input, output = cbfgeneric_specials[cfunc] self.code += docstringwrite(pyname,input,output, prototype,docstring)+ code return except KeyError: not_found = 1 # print "KeyError" except ValueError: print "problem in generic",cfunc for item in cbfgeneric_specials[cfunc]: print "***",item raise if len(args)==1 and args[0].find("char")>-1 and \ args[0].find("**")>-1 :# return string # first write the c code and inline it code += docstringwrite(pyfunc,[],["string"],prototype,docstring) code += "%%inline %%{\n char* %s(void);\n"%(pyfunc) code += " char* %s(void){\n"%(pyfunc) code += " char *r;\n" code += " error_status = %s(&r);\n"%(cfunc) code += " return r; }\n%}\n" # now the thing to wrap is: code += "char* %s(void);"%(pyfunc) self.code=self.code+code return # code+= " void %s(void){\n"%(pyfunc) # code +=" cbf_failnez(CBF_NOTIMPLEMENTED);}\n" # self.code=self.code+code print "Have not implemented:" for s in [cfunc, pyfunc] + args: print "\t",s print return generic_wrapper = genericwrapper() def generate_wrappers(name_dict): names = name_dict.keys() for cname in names: prototype = name_dict[cname][0] docstring = name_dict[cname][1] # print "Generate wrappers: ", "::",cname,"::", prototype,"::", docstring # Check prototype begins with "int cbf_" if prototype.find("int cbf_")!=0: print "problem with:",prototype # Get arguments from prototypes try: args = prototype.split("(")[1].split(")")[0].split(",") args = [ s.lstrip().rstrip() for s in args ] # strip spaces off ends # print "Args: ", args except: # print cname # print prototype raise if args[0].find("cbf_handle")>=0: # This is for the cbfhandle object cbf_handle_wrapper.wrap(cname,prototype,args,docstring) if (cname=="cbf_get_unit_cell"): cbf_handle_wrapper.wrap("cbf_get_unit_cell_esd",prototype,args,docstring) if (cname=="cbf_get_reciprocal_cell"): cbf_handle_wrapper.wrap("cbf_get_reciprocal_cell_esd",prototype,args,docstring) if (cname=="cbf_set_unit_cell"): cbf_handle_wrapper.wrap("cbf_set_unit_cell_esd",prototype,args,docstring) if (cname=="cbf_set_reciprocal_cell"): cbf_handle_wrapper.wrap("cbf_set_reciprocal_cell_esd",prototype,args,docstring) continue if args[0].find("cbf_goniometer")>=0: # This is for the cbfgoniometer cbf_goniometer_wrapper.wrap(cname,prototype,args,docstring) continue if args[0].find("cbf_detector")>=0: # This is for the cbfdetector cbf_detector_wrapper.wrap(cname,prototype,args,docstring) continue generic_wrapper.wrap(cname,prototype,args,docstring) generate_wrappers(name_dict) open("cbfgoniometerwrappers.i","w").write(cbf_goniometer_wrapper.get_code()) open("cbfdetectorwrappers.i","w").write(cbf_detector_wrapper.get_code()) open("cbfhandlewrappers.i","w").write(cbf_handle_wrapper.get_code()) open("cbfgenericwrappers.i","w").write(generic_wrapper.get_code()) print "End of output from make_pycbf.py" print "\\end{verbatim}" ./CBFlib-0.9.2.2/pycbf/linux.sh0000644000076500007650000000053711603702120014375 0ustar yayayaya nuweb pycbf latex pycbf nuweb pycbf latex pycbf dvipdfm pycbf nuweb pycbf lynx -dump CBFlib.html > CBFlib.txt python make_pycbf.py swig -python pycbf.i python setup.py build rm _pycbf.so cp build/lib.linux-i686-2.4/_pycbf.so . python pycbf_test1.py python pycbf_test2.py pydoc -w pycbf python makeflatascii.py pycbf_ascii_help.txt ./CBFlib-0.9.2.2/README0000644000076500007650000002042511603745600012467 0ustar yayayaya CBFlib README Information for CBFlib 0.9.2 release of 12 February 2011 revised as the CBFlib 0.9.2.1 release of 20 June 2011 revised as the CBFlib 0.9.2.2 release of 2 July 2011 by Paul J. Ellis Stanford Synchrotron Radiation Laboratory and Herbert J. Bernstein Bernstein + Sons yaya at bernstein-plus-sons dot com (c) Copyright 2006, 2007, 2008, 2010, 2011 Herbert J. Bernstein ---------------------------------------------------------------------- YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL. ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS OF THE LGPL. ---------------------------------------------------------------------- Before using this software, please read the NOTICE for important disclaimers and the IUCr Policy on the Use of the Crystallographic Information File (CIF) and other important information. Work on imgCIF and CBFlib supported in part by the U. S. Department of Energy (DOE) under grants ER63601-1021466-0009501 and ER64212-1027708-0011962, by the U. S. National Science Foundation (NSF) under grants DBI-0610407, DBI-0315281 and EF-0312612, the U. S. National Institutes of Health (NIH) under grants 1R15GM078077 from NIGMS and 1R13RR023192 from NCRR and funding from the International Union for Crystallography (IUCr). The content is solely the responsibility of the authors and does not necessarily represent the official views of DOE, NSF, NIH, NIGMS, NCRR or IUCr. ---------------------------------------------------------------------- CBFlib 0.9.2.2 is a minor revision to the CBFlib 0.9.2.1 release in July 2011 to update doc/cif_img.dic to the 1.6.4 revision. CBFlib 0.9.2.1 is a minor revision to the CBFlib 0.9.2 release in June 2011 to upgrade the setup script for the pycbf Python bindings to simplify using pycbf outside the context of the CBFlib pycbf directory. CBFlib 0.9.2 is the recommended release of CBFlib of February 2011. The commulative changes in releases 0.9.1 and 0.9.2 since CBFlib 0.9.0 are: * Temporary removal of default PyCifRW support for compliance with Fedora license requirements. * Addition of a new tiff2cbf example program. * Update pycbf python wraapper for CBFlib. * Padding options added to adscimg2cbf by C. Nielsen. * System and gnu versions of getopt replaced by cbf_getopt. * Code to handle CIF2 bracketed constructs and quoted strings added. * System to log errors and warnings added. * Java wrapper by Peter Chang added. * Dectris template code by E. Eikenberry added. CBFlib 0.9.1 included a correction to CBFlib 0.9.0 to make axis the cbf_simple routines apply axis rotations correctly for detectors and to pick up corrections for byte offet compression incorporated into the upcoming CBFlib 0.9.1 release. The earlier version had failed to apply the rotations to the accumulated displacements. Our thanks to Joerg Kaercher of Bruker-AXS for identifying the rotation problem. CBFlib 0.9.0 was a partial pre-release of CBFlib version 0.8 needed to support changes in RasMol. This release was incomplete and used were advided to use it with caution, but it has proven to be a reliable, stable release for 2 years. There have been significant changes in the input/output logic and in validation. For a ChangeLog consult the SVN of the CBFlib project on sourceforge. CBFLIB is a library of ANSI-C functions providing a simple mechanism for accessing Crystallographic Binary Files (CBF files) and Image-supporting CIF (imgCIF) files. The CBFLIB API is loosely based on the CIFPARSE API for mmCIF files. Starting with this release, CBFLIB performs validation checks on reading of a CBF. If a dictionary is provided, values will be validated against dictionary ranges and enumerations. Tags missing under parent-child relationships or category key requirements will be reported. CBFlib provides functions to create, read, modify and write CBF binary data files and imgCIF ASCII data files. Installation CBFLIB should be built on a disk with at least 350 megabytes of free space, for a full installation with complete tests. Read the instructions below carefully, if space is a problem. A gizpped tarball of this release is available on sourceforge at http://downloads.sf.net/cbflib/CBFlib-0.9.2.2.tar.gz In addition, http://downloads.sf.net/cbflib/CBFlib_0.9.2_Data_Files_Input.tar.gz (13 MB) is a "gzipped" tar of the input data files needed to test the API, http://downloads.sf.net/cbflib/CBFlib_0.9.2_Data_Files_Output.tar.gz (34 MB) is a "gzipped" tar of the output data files needed to test the API, and, if space is at a premium, http://downloads.sf.net/cbflib/CBFlib_0.9.2_Data_Files_Output_Sigs_Only.tar.gz (1KB) is a "gzipped" tar of only the MD5 signatures of the output data files needed to test the API. Place the CBFlib_0.9.2.2.tar.gz file in the directory that is intended to contain up to 4 new directories, named CBFlib_0.9.2.2 (the "top-level" directory), CBFlib_0.9.2_Data_Files_Input and either CBFlib_0.9.2_Data_Files_Output or CBFlib_0.9.2_Data_Files_Output_Sigs_Only. If you have wget on your machine, you only need to download the source tarball. If you do not have wget, you will need to download all the tarballs into the same directory Uncompress CBFlib_0.9.2.tar.gz with gunzip and unpack it with tar: gunzip CBFlib_0.9.2.tar.gz tar xvf CBFLIB_0.9.2.tar To run the test programs, you will also need Paul Ellis's sample MAR345 image, example.mar2300, Chris Nielsen's sample ADSC Quantum 315 image, mb_LP_1_001.img, and Eric Eikenberry's SLS sample Pilatus 6m image, insulin_pilatus6m, as sample data. In addition there are is a PDB mmCIF file, 9ins.cif, and 3 special test files testflatin.cbf, testflatpackedin.cbf and testrealin.cbf. All these files will be dowloaded and extracted by the Makefile from CBFlib_0.9.2_Data_Files_Input. Do not download copies into the top level directory. After unpacking the archives, the top-level directory should contain a makefile: Makefile Makefile for unix and the subdirectories: src/ CBFLIB source files include/ CBFLIB header files bin/ Executable example programs doc/ Documentation examples/ Example program source files html_images/ JPEG images used in rendering the HTML files lib/ Compiled CBFLIB (libcbf.a) and FCBLIB (libfcb.a) libraries m4/ CBFLIB m4 macro files (used to build .f90 files) mswin/ An MS Windows CodeWarrior project file pycbf/ Jon Wright's Python bindings and additional Makefiles for other systems. All the makefiles are created from m4/Makefile.m4. Edit the closest approximation to your system, and then copy that variant to Makefile. For instructions on compiling and testing the library, go to the top-level directory and type: make Once you have a properly configure Makefile, compile and test the package with make tests or, if space is at a premium, with make tests_sigs_only Please refer to the manual doc/CBFlib.html for more detailed information. ---------------------------------------------------------------------- ---------------------------------------------------------------------- Updated 2 July 2011. yaya at bernstein-plus-sons dot com ./CBFlib-0.9.2.2/Makefile_LINUX_DMALLOC0000644000076500007650000020025711603702122015354 0ustar yayayaya ###################################################################### # Makefile - command file for make to create CBFlib # # # # Version 0.9.2 12 Feb 2011 # # # # Paul Ellis and # # Herbert J. Bernstein (yaya@bernstein-plus-sons.com) # # # # (C) Copyright 2006 - 2011 Herbert J. Bernstein # # # ###################################################################### ###################################################################### # # # YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL # # # # ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS # # OF THE LGPL # # # ###################################################################### ########################### GPL NOTICES ############################## # # # This program is free software; you can redistribute it and/or # # modify it under the terms of the GNU General Public License as # # published by the Free Software Foundation; either version 2 of # # (the License, or (at your option) any later version. # # # # This program is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # # GNU General Public License for more details. # # # # You should have received a copy of the GNU General Public License # # along with this program; if not, write to the Free Software # # Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA # # 02111-1307 USA # # # ###################################################################### ######################### LGPL NOTICES ############################### # # # This library is free software; you can redistribute it and/or # # modify it under the terms of the GNU Lesser General Public # # License as published by the Free Software Foundation; either # # version 2.1 of the License, or (at your option) any later version. # # # # This library is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # # Lesser General Public License for more details. # # # # You should have received a copy of the GNU Lesser General Public # # License along with this library; if not, write to the Free # # Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, # # MA 02110-1301 USA # # # ###################################################################### ###################################################################### # # # Stanford University Notices # # for the CBFlib software package that incorporates SLAC software # # on which copyright is disclaimed # # # # This software # # ------------- # # The term "this software", as used in these Notices, refers to # # those portions of the software package CBFlib that were created by # # employees of the Stanford Linear Accelerator Center, Stanford # # University. # # # # Stanford disclaimer of copyright # # -------------------------------- # # Stanford University, owner of the copyright, hereby disclaims its # # copyright and all other rights in this software. Hence, anyone # # may freely use it for any purpose without restriction. # # # # Acknowledgement of sponsorship # # ------------------------------ # # This software was produced by the Stanford Linear Accelerator # # Center, Stanford University, under Contract DE-AC03-76SFO0515 with # # the Department of Energy. # # # # Government disclaimer of liability # # ---------------------------------- # # Neither the United States nor the United States Department of # # Energy, nor any of their employees, makes any warranty, express or # # implied, or assumes any legal liability or responsibility for the # # accuracy, completeness, or usefulness of any data, apparatus, # # product, or process disclosed, or represents that its use would # # not infringe privately owned rights. # # # # Stanford disclaimer of liability # # -------------------------------- # # Stanford University makes no representations or warranties, # # express or implied, nor assumes any liability for the use of this # # software. # # # # Maintenance of notices # # ---------------------- # # In the interest of clarity regarding the origin and status of this # # software, this and all the preceding Stanford University notices # # are to remain affixed to any copy or derivative of this software # # made or distributed by the recipient and are to be affixed to any # # copy of software made or distributed by the recipient that # # contains a copy or derivative of this software. # # # # Based on SLAC Software Notices, Set 4 # # OTT.002a, 2004 FEB 03 # ###################################################################### ###################################################################### # NOTICE # # Creative endeavors depend on the lively exchange of ideas. There # # are laws and customs which establish rights and responsibilities # # for authors and the users of what authors create. This notice # # is not intended to prevent you from using the software and # # documents in this package, but to ensure that there are no # # misunderstandings about terms and conditions of such use. # # # # Please read the following notice carefully. If you do not # # understand any portion of this notice, please seek appropriate # # professional legal advice before making use of the software and # # documents included in this software package. In addition to # # whatever other steps you may be obliged to take to respect the # # intellectual property rights of the various parties involved, if # # you do make use of the software and documents in this package, # # please give credit where credit is due by citing this package, # # its authors and the URL or other source from which you obtained # # it, or equivalent primary references in the literature with the # # same authors. # # # # Some of the software and documents included within this software # # package are the intellectual property of various parties, and # # placement in this package does not in any way imply that any # # such rights have in any way been waived or diminished. # # # # With respect to any software or documents for which a copyright # # exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. # # # # Even though the authors of the various documents and software # # found here have made a good faith effort to ensure that the # # documents are correct and that the software performs according # # to its documentation, and we would greatly appreciate hearing of # # any problems you may encounter, the programs and documents any # # files created by the programs are provided **AS IS** without any * # warranty as to correctness, merchantability or fitness for any # # particular or general use. # # # # THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF # # PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE # # PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS # # OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE # # PROGRAMS OR DOCUMENTS. # ###################################################################### ###################################################################### # # # The IUCr Policy # # for the Protection and the Promotion of the STAR File and # # CIF Standards for Exchanging and Archiving Electronic Data # # # # Overview # # # # The Crystallographic Information File (CIF)[1] is a standard for # # information interchange promulgated by the International Union of # # Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the # # recommended method for submitting publications to Acta # # Crystallographica Section C and reports of crystal structure # # determinations to other sections of Acta Crystallographica # # and many other journals. The syntax of a CIF is a subset of the # # more general STAR File[2] format. The CIF and STAR File approaches # # are used increasingly in the structural sciences for data exchange # # and archiving, and are having a significant influence on these # # activities in other fields. # # # # Statement of intent # # # # The IUCr's interest in the STAR File is as a general data # # interchange standard for science, and its interest in the CIF, # # a conformant derivative of the STAR File, is as a concise data # # exchange and archival standard for crystallography and structural # # science. # # # # Protection of the standards # # # # To protect the STAR File and the CIF as standards for # # interchanging and archiving electronic data, the IUCr, on behalf # # of the scientific community, # # # # # holds the copyrights on the standards themselves, * # # # # owns the associated trademarks and service marks, and * # # # # holds a patent on the STAR File. * # # # These intellectual property rights relate solely to the # # interchange formats, not to the data contained therein, nor to # # the software used in the generation, access or manipulation of # # the data. # # # # Promotion of the standards # # # # The sole requirement that the IUCr, in its protective role, # # imposes on software purporting to process STAR File or CIF data # # is that the following conditions be met prior to sale or # # distribution. # # # # # Software claiming to read files written to either the STAR * # File or the CIF standard must be able to extract the pertinent # # data from a file conformant to the STAR File syntax, or the CIF # # syntax, respectively. # # # # # Software claiming to write files in either the STAR File, or * # the CIF, standard must produce files that are conformant to the # # STAR File syntax, or the CIF syntax, respectively. # # # # # Software claiming to read definitions from a specific data * # dictionary approved by the IUCr must be able to extract any # # pertinent definition which is conformant to the dictionary # # definition language (DDL)[3] associated with that dictionary. # # # # The IUCr, through its Committee on CIF Standards, will assist # # any developer to verify that software meets these conformance # # conditions. # # # # Glossary of terms # # # # [1] CIF: is a data file conformant to the file syntax defined # # at http://www.iucr.org/iucr-top/cif/spec/index.html # # # # [2] STAR File: is a data file conformant to the file syntax # # defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html # # # # [3] DDL: is a language used in a data dictionary to define data # # items in terms of "attributes". Dictionaries currently approved # # by the IUCr, and the DDL versions used to construct these # # dictionaries, are listed at # # http://www.iucr.org/iucr-top/cif/spec/ddl/index.html # # # # Last modified: 30 September 2000 # # # # IUCr Policy Copyright (C) 2000 International Union of # # Crystallography # ###################################################################### # Version string VERSION = 0.9.2 # # Comment out the next line if scratch test files sould be retain # CLEANTESTS = yes # # Definition to get a version of tifflib to support tiff2cbf # TIFF = tiff-3.9.4-rev-6Feb11 TIFFPREFIX = $(PWD) # # Definitions to get a stable version of regex # REGEX = regex-20090805 REGEXDIR = /usr/lib REGEXDEP = # Program to use to retrieve a URL DOWNLOAD = wget # Flag to control symlinks versus copying SLFLAGS = --use_ln # # Program to use to pack shars # SHAR = /usr/bin/shar #SHAR = /usr/local/bin/gshar # # Program to use to create archives # AR = /usr/bin/ar # # Program to use to add an index to an archive # RANLIB = /usr/bin/ranlib # # Program to use to decompress a data file # DECOMPRESS = /usr/bin/bunzip2 # # Program to use to compress a data file # COMPRESS = /usr/bin/bzip2 # # Program to use to generate a signature # SIGNATURE = /usr/bin/openssl dgst -md5 # # Extension for compressed data file (with period) # CEXT = .bz2 # # Extension for signatures of files # SEXT = .md5 # call to time a command #TIME = #TIME = time # # Program to display differences between files # DIFF = diff -u -b # # Program to generate wrapper classes for Python # PYSWIG = swig -python # # Program to generate wrapper classes for Java # JSWIG = swig -java # # Program to generate LaTex and HTML program documentation # NUWEB = nuweb # # Compiler for Java # JAVAC = javac # # Java archiver for compiled classes # JAR = jar # # Java SDK root directory # ifeq ($(JDKDIR),) JDKDIR = /usr/lib/java endif ifneq ($(CBF_DONT_USE_LONG_LONG),) NOLLFLAG = -DCBF_DONT_USE_LONG_LONG else NOLLFLAG = endif # # PYCBF definitions # PYCBFEXT = so PYCBFBOPT = SETUP_PY = setup.py # # Set the compiler and flags # ######################################################### # # Appropriate compiler definitions for Linux and DMALLOC # ######################################################### CC = gcc C++ = g++ CFLAGS = -g -O2 -Wall -D_USE_XOPEN_EXTENDED -fno-strict-aliasing -DDMALLOC -DDMALLOC_FUNC_CHECK -I$(HOME)/include F90C = gfortran F90FLAGS = -g F90LDFLAGS = SOCFLAGS = -fPIC SOLDFLAGS = -shared -Wl,-rpath,$(INSTALLDIR)/lib JAVAINCLUDES = -I$(JDKDIR)/include -I$(JDKDIR)/include/linux LDPREFIX = LD_LIBRARY_PATH=$(SOLIB) EXTRALIBS = -lm -L$(HOME)/lib -ldmalloc M4FLAGS = -Dfcb_bytes_in_rec=131072 TIME = time ifneq ($(NOFORTRAN),) F90C = endif # # Directories # ROOT = . LIB = $(ROOT)/lib SOLIB = $(ROOT)/solib JCBF = $(ROOT)/jcbf JAVADIR = $(ROOT)/java BIN = $(ROOT)/bin SRC = $(ROOT)/src INCLUDE = $(ROOT)/include M4 = $(ROOT)/m4 PYCBF = $(ROOT)/pycbf EXAMPLES = $(ROOT)/examples DECTRIS_EXAMPLES = $(EXAMPLES)/dectris_cbf_template_test DOC = $(ROOT)/doc GRAPHICS = $(ROOT)/html_graphics DATADIRI = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Input DATADIRO = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Output DATADIRS = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only INSTALLDIR = $(HOME) # # URLs from which to retrieve the data directories # DATAURLBASE = http://downloads.sf.net/cbflib/ DATAURLI = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Input.tar.gz DATAURLO = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Output.tar.gz DATAURLS = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz # # URLs from which to retrieve needed external package snapshots # REGEXURL = http://downloads.sf.net/cbflib/$(REGEX).tar.gz TIFFURL = http://downloads.sf.net/cbflib/$(TIFF).tar.gz # # Include directories # INCLUDES = -I$(INCLUDE) -I$(SRC) ###################################################################### # You should not need to make modifications below this line # ###################################################################### # # Suffixes of files to be used or built # .SUFFIXES: .c .o .f90 .m4 .m4.f90: m4 -P $(M4FLAGS) $< > $@ ifneq ($(F90C),) .f90.o: $(F90C) $(F90FLAGS) -c $< -o $@ endif # # Common dependencies # COMMONDEP = Makefile # # Source files # SOURCE = $(SRC)/cbf.c \ $(SRC)/cbf_alloc.c \ $(SRC)/cbf_ascii.c \ $(SRC)/cbf_binary.c \ $(SRC)/cbf_byte_offset.c \ $(SRC)/cbf_canonical.c \ $(SRC)/cbf_codes.c \ $(SRC)/cbf_compress.c \ $(SRC)/cbf_context.c \ $(SRC)/cbf_copy.c \ $(SRC)/cbf_file.c \ $(SRC)/cbf_getopt.c \ $(SRC)/cbf_lex.c \ $(SRC)/cbf_packed.c \ $(SRC)/cbf_predictor.c \ $(SRC)/cbf_read_binary.c \ $(SRC)/cbf_read_mime.c \ $(SRC)/cbf_simple.c \ $(SRC)/cbf_string.c \ $(SRC)/cbf_stx.c \ $(SRC)/cbf_tree.c \ $(SRC)/cbf_uncompressed.c \ $(SRC)/cbf_write.c \ $(SRC)/cbf_write_binary.c \ $(SRC)/cbf_ws.c \ $(SRC)/md5c.c F90SOURCE = $(SRC)/fcb_atol_wcnt.f90 \ $(SRC)/fcb_ci_strncmparr.f90 \ $(SRC)/fcb_exit_binary.f90 \ $(SRC)/fcb_nblen_array.f90 \ $(SRC)/fcb_next_binary.f90 \ $(SRC)/fcb_open_cifin.f90 \ $(SRC)/fcb_packed.f90 \ $(SRC)/fcb_read_bits.f90 \ $(SRC)/fcb_read_byte.f90 \ $(SRC)/fcb_read_image.f90 \ $(SRC)/fcb_read_line.f90 \ $(SRC)/fcb_read_xds_i2.f90 \ $(SRC)/fcb_skip_whitespace.f90 \ $(EXAMPLES)/test_fcb_read_image.f90 \ $(EXAMPLES)/test_xds_binary.f90 # # Header files # HEADERS = $(INCLUDE)/cbf.h \ $(INCLUDE)/cbf_alloc.h \ $(INCLUDE)/cbf_ascii.h \ $(INCLUDE)/cbf_binary.h \ $(INCLUDE)/cbf_byte_offset.h \ $(INCLUDE)/cbf_canonical.h \ $(INCLUDE)/cbf_codes.h \ $(INCLUDE)/cbf_compress.h \ $(INCLUDE)/cbf_context.h \ $(INCLUDE)/cbf_copy.h \ $(INCLUDE)/cbf_file.h \ $(INCLUDE)/cbf_getopt.h \ $(INCLUDE)/cbf_lex.h \ $(INCLUDE)/cbf_packed.h \ $(INCLUDE)/cbf_predictor.h \ $(INCLUDE)/cbf_read_binary.h \ $(INCLUDE)/cbf_read_mime.h \ $(INCLUDE)/cbf_simple.h \ $(INCLUDE)/cbf_string.h \ $(INCLUDE)/cbf_stx.h \ $(INCLUDE)/cbf_tree.h \ $(INCLUDE)/cbf_uncompressed.h \ $(INCLUDE)/cbf_write.h \ $(INCLUDE)/cbf_write_binary.h \ $(INCLUDE)/cbf_ws.h \ $(INCLUDE)/global.h \ $(INCLUDE)/cbff.h \ $(INCLUDE)/md5.h # # m4 macro files # M4FILES = $(M4)/fcblib_defines.m4 \ $(M4)/fcb_exit_binary.m4 \ $(M4)/fcb_next_binary.m4 \ $(M4)/fcb_open_cifin.m4 \ $(M4)/fcb_packed.m4 \ $(M4)/fcb_read_bits.m4 \ $(M4)/fcb_read_image.m4 \ $(M4)/fcb_read_xds_i2.m4 \ $(M4)/test_fcb_read_image.m4 \ $(M4)/test_xds_binary.m4 # # Documentation files # DOCUMENTS = $(DOC)/CBFlib.html \ $(DOC)/CBFlib.txt \ $(DOC)/CBFlib_NOTICES.html \ $(DOC)/CBFlib_NOTICES.txt \ $(DOC)/ChangeLog \ $(DOC)/ChangeLog.html \ $(DOC)/MANIFEST \ $(DOC)/gpl.txt $(DOC)/lgpl.txt # # HTML Graphics files # JPEGS = $(GRAPHICS)/CBFbackground.jpg \ $(GRAPHICS)/CBFbig.jpg \ $(GRAPHICS)/CBFbutton.jpg \ $(GRAPHICS)/cbflibbackground.jpg \ $(GRAPHICS)/cbflibbig.jpg \ $(GRAPHICS)/cbflibbutton.jpg \ $(GRAPHICS)/cifhome.jpg \ $(GRAPHICS)/iucrhome.jpg \ $(GRAPHICS)/noticeButton.jpg # # Default: instructions # default: @echo ' ' @echo '***************************************************************' @echo ' ' @echo ' PLEASE READ README and doc/CBFlib_NOTICES.txt' @echo ' ' @echo ' Before making the CBF library and example programs, check' @echo ' that the C compiler name and flags are correct:' @echo ' ' @echo ' The current values are:' @echo ' ' @echo ' $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG)' @echo ' ' @echo ' Before installing the CBF library and example programs, check' @echo ' that the install directory is correct:' @echo ' ' @echo ' The current value :' @echo ' ' @echo ' $(INSTALLDIR) ' @echo ' ' @echo ' To compile the CBF library and example programs type:' @echo ' ' @echo ' make clean' @echo ' make all' @echo ' ' @echo ' To compile the CBF library as a shared object library, type:' @echo ' ' @echo ' make shared' @echo ' ' @echo ' To compile the Java wrapper classes for CBF library, type:' @echo ' ' @echo ' make javawrapper' @echo ' ' @echo ' To run a set of tests type:' @echo ' ' @echo ' make tests' @echo ' ' @echo ' To run some java tests type:' @echo ' ' @echo ' make javatests' @echo ' ' @echo ' The tests assume that several data files are in the directories' @echo ' $(DATADIRI) and $(DATADIRO)' @echo ' ' @echo ' Alternatively tests can be run comparing MD5 signatures only by' @echo ' ' @echo ' make tests_sigs_only' @echo ' ' @echo ' These signature only tests save space and download time by' @echo ' assuming that input data files and the output signatures' @echo ' are in the directories' @echo ' $(DATADIRI) and $(DATADIRS)' @echo ' ' @echo ' These directory can be obtained from' @echo ' ' @echo ' $(DATAURLI) ' @echo ' $(DATAURLO) ' @echo ' $(DATAURLS) ' @echo ' ' @echo ' To clean up the directories type:' @echo ' ' @echo ' make clean' @echo ' ' @echo ' To install the library and binaries type:' @echo ' ' @echo ' make install' @echo ' ' @echo '***************************************************************' @echo ' ' # # Compile the library and examples # all:: $(BIN) $(SOURCE) $(F90SOURCE) $(HEADERS) \ symlinksdone $(REGEXDEP) \ $(LIB)/libcbf.a \ $(LIB)/libfcb.a \ $(LIB)/libimg.a \ $(BIN)/adscimg2cbf \ $(BIN)/cbf2adscimg \ $(BIN)/convert_image \ $(BIN)/convert_minicbf \ $(BIN)/sequence_match \ $(BIN)/arvai_test \ $(BIN)/makecbf \ $(BIN)/img2cif \ $(BIN)/adscimg2cbf \ $(BIN)/cif2cbf \ $(BIN)/testcell \ $(BIN)/cif2c \ $(BIN)/testreals \ $(BIN)/testflat \ $(BIN)/testflatpacked ifneq ($(F90C),) all:: $(BIN)/test_xds_binary \ $(BIN)/test_fcb_read_image endif shared: $(SOLIB)/libcbf.so $(SOLIB)/libfcb.so $(SOLIB)/libimg.so javawrapper: shared $(JCBF) $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf_wrap.so ifneq ($(CBFLIB_USE_PYCIFRW),) PYCIFRWDEF = -Dcbf_use_pycifrw=yes else PYCIFRWDEF = endif Makefiles: Makefile \ Makefile_LINUX \ Makefile_LINUX_64 \ Makefile_LINUX_gcc42 \ Makefile_LINUX_DMALLOC \ Makefile_LINUX_gcc42_DMALLOC \ Makefile_OSX \ Makefile_OSX_gcc42 \ Makefile_OSX_gcc42_DMALLOC \ Makefile_AIX \ Makefile_MINGW \ Makefile_IRIX_gcc Makefile_LINUX: $(M4)/Makefile.m4 -cp Makefile_LINUX Makefile_LINUX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX $(M4)/Makefile.m4 > Makefile_LINUX Makefile_LINUX_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_LINUX Makefile_LINUX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_DMALLOC $(M4)/Makefile.m4 > Makefile_LINUX_DMALLOC Makefile_LINUX_64: $(M4)/Makefile.m4 -cp Makefile_LINUX_64 Makefile_LINUX_64_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_64 $(M4)/Makefile.m4 > Makefile_LINUX_64 Makefile_LINUX_gcc42: $(M4)/Makefile.m4 -cp Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_gcc42 $(M4)/Makefile.m4 > Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_gcc42_DMALLOC $(M4)/Makefile.m4 > Makefile_LINUX_gcc42_DMALLOC Makefile_OSX: $(M4)/Makefile.m4 -cp Makefile_OSX Makefile_OSX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX $(M4)/Makefile.m4 > Makefile_OSX Makefile_OSX_gcc42: $(M4)/Makefile.m4 -cp Makefile_OSX_gcc42 Makefile_OSX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX_gcc42 $(M4)/Makefile.m4 > Makefile_OSX_gcc42 Makefile_OSX_gcc42_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_OSX_gcc42 Makefile_OSX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX_gcc42_DMALLOC $(M4)/Makefile.m4 > Makefile_OSX_gcc42_DMALLOC Makefile_AIX: $(M4)/Makefile.m4 -cp Makefile_AIX Makefile_AIX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=AIX $(M4)/Makefile.m4 > Makefile_AIX Makefile_MINGW: $(M4)/Makefile.m4 -cp Makefile_MINGW Makefile_MINGW_old m4 -P $(PYCIFRWDEF) -Dcbf_system=MINGW $(M4)/Makefile.m4 > Makefile_MINGW Makefile_IRIX_gcc: $(M4)/Makefile.m4 -cp Makefile_IRIX_gcc Makefile_IRIX_gcc_old m4 -P $(PYCIFREDEF) -Dcbf_system=IRIX_gcc $(M4)/Makefile.m4 > Makefile_IRIX_gcc Makefile: $(M4)/Makefile.m4 -cp Makefile Makefile_old m4 -P $(PYCIFRWDEF) -Dcbf_system=default $(M4)/Makefile.m4 > Makefile symlinksdone: chmod a+x .symlinks chmod a+x .undosymlinks chmod a+x doc/.symlinks chmod a+x doc/.undosymlinks chmod a+x libtool/.symlinks chmod a+x libtool/.undosymlinks ./.symlinks $(SLFLAGS) touch symlinksdone install: all $(INSTALLDIR) $(INSTALLDIR)/lib $(INSTALLDIR)/bin \ $(INSTALLDIR)/include $(INSTALLDIR)/include/cbflib \ $(PYSOURCE) -chmod -R 755 $(INSTALLDIR)/include/cbflib -chmod 755 $(INSTALLDIR)/lib/libcbf.a -cp $(INSTALLDIR)/lib/libcbf.a $(INSTALLDIR)/lib/libcbf_old.a cp $(LIB)/libcbf.a $(INSTALLDIR)/lib/libcbf.a -cp $(INSTALLDIR)/lib/libimg.a $(INSTALLDIR)/lib/libimg_old.a cp $(LIB)/libimg.a $(INSTALLDIR)/lib/libimg.a -cp $(INSTALLDIR)/bin/adscimg2cbf $(INSTALLDIR)/bin/adscimg2cbf_old cp $(BIN)/adscimg2cbf $(INSTALLDIR)/bin/adscimg2cbf -cp $(INSTALLDIR)/bin/cbf2adscimg $(INSTALLDIR)/bin/cbf2adscimg_old cp $(BIN)/cbf2adscimg $(INSTALLDIR)/bin/cbf2adscimg -cp $(INSTALLDIR)/bin/convert_image $(INSTALLDIR)/bin/convert_image_old cp $(BIN)/convert_image $(INSTALLDIR)/bin/convert_image -cp $(INSTALLDIR)/bin/convert_minicbf $(INSTALLDIR)/bin/convert_minicbf_old cp $(BIN)/convert_minicbf $(INSTALLDIR)/bin/convert_minicbf -cp $(INSTALLDIR)/bin/makecbf $(INSTALLDIR)/bin/makecbf_old cp $(BIN)/makecbf $(INSTALLDIR)/bin/makecbf -cp $(INSTALLDIR)/bin/img2cif $(INSTALLDIR)/bin/img2cif_old cp $(BIN)/img2cif $(INSTALLDIR)/bin/img2cif -cp $(INSTALLDIR)/bin/cif2cbf $(INSTALLDIR)/bin/cif2cbf_old cp $(BIN)/cif2cbf $(INSTALLDIR)/bin/cif2cbf -cp $(INSTALLDIR)/bin/sequence_match $(INSTALLDIR)/bin/sequence_match_old cp $(BIN)/sequence_match $(INSTALLDIR)/bin/sequence_match -cp $(INSTALLDIR)/bin/arvai_test $(INSTALLDIR)/bin/arvai_test_old cp $(BIN)/arvai_test $(INSTALLDIR)/bin/arvai_test -cp $(INSTALLDIR)/bin/cif2c $(INSTALLDIR)/bin/cif2c_old cp $(BIN)/cif2c $(INSTALLDIR)/bin/cif2c -cp $(INSTALLDIR)/bin/testreals $(INSTALLDIR)/bin/testreals_old cp $(BIN)/testreals $(INSTALLDIR)/bin/testreals -cp $(INSTALLDIR)/bin/testflat $(INSTALLDIR)/bin/testflat_old cp $(BIN)/testflat $(INSTALLDIR)/bin/testflat -cp $(INSTALLDIR)/bin/testflatpacked $(INSTALLDIR)/bin/testflatpacked_old cp $(BIN)/testflatpacked $(INSTALLDIR)/bin/testflatpacked chmod -R 755 $(INSTALLDIR)/include/cbflib -rm -rf $(INSTALLDIR)/include/cbflib_old -cp -r $(INSTALLDIR)/include/cbflib $(INSTALLDIR)/include/cbflib_old -rm -rf $(INSTALLDIR)/include/cbflib cp -r $(INCLUDE) $(INSTALLDIR)/include/cbflib chmod 644 $(INSTALLDIR)/lib/libcbf.a chmod 755 $(INSTALLDIR)/bin/convert_image chmod 755 $(INSTALLDIR)/bin/convert_minicbf chmod 755 $(INSTALLDIR)/bin/makecbf chmod 755 $(INSTALLDIR)/bin/img2cif chmod 755 $(INSTALLDIR)/bin/cif2cbf chmod 755 $(INSTALLDIR)/bin/sequence_match chmod 755 $(INSTALLDIR)/bin/arvai_test chmod 755 $(INSTALLDIR)/bin/cif2c chmod 755 $(INSTALLDIR)/bin/testreals chmod 755 $(INSTALLDIR)/bin/testflat chmod 755 $(INSTALLDIR)/bin/testflatpacked chmod 644 $(INSTALLDIR)/include/cbflib/*.h # # REGEX # ifneq ($(REGEXDEP),) $(REGEXDEP): $(REGEX) (cd $(REGEX); ./configure; make install) endif $(REGEX): $(DOWNLOAD) $(REGEXURL) tar -xvf $(REGEX).tar.gz -rm $(REGEX).tar.gz # # TIFF # $(TIFF): $(DOWNLOAD) $(TIFFURL) tar -xvf $(TIFF).tar.gz -rm $(TIFF).tar.gz (cd $(TIFF); ./configure --prefix=$(TIFFPREFIX); make install) # # Directories # $(INSTALLDIR): mkdir -p $(INSTALLDIR) $(INSTALLDIR)/lib: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/lib $(INSTALLDIR)/bin: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/bin $(INSTALLDIR)/include: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/include $(INSTALLDIR)/include/cbflib: $(INSTALLDIR)/include mkdir -p $(INSTALLDIR)/include/cbflib $(LIB): mkdir $@ $(BIN): mkdir $@ $(SOLIB): mkdir $@ $(JCBF): mkdir $@ # # Parser # $(SRC)/cbf_stx.c: $(SRC)/cbf.stx.y bison $(SRC)/cbf.stx.y -o $(SRC)/cbf.stx.tab.c -d mv $(SRC)/cbf.stx.tab.c $(SRC)/cbf_stx.c mv $(SRC)/cbf.stx.tab.h $(INCLUDE)/cbf_stx.h # # CBF library # $(LIB)/libcbf.a: $(SOURCE) $(HEADERS) $(COMMONDEP) $(LIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG) $(INCLUDES) $(WARNINGS) -c $(SOURCE) $(AR) cr $@ *.o mv *.o $(LIB) ifneq ($(RANLIB),) $(RANLIB) $@ endif $(SOLIB)/libcbf.so: $(SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(SOURCE) $(CC) -o $@ *.o $(SOLDFLAGS) $(EXTRALIBS) rm *.o # # IMG library # $(LIB)/libimg.a: $(EXAMPLES)/img.c $(HEADERS) $(COMMONDEP) $(LIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) -c $(EXAMPLES)/img.c $(AR) cr $@ img.o ifneq ($(RANLIB),) $(RANLIB) $@ endif rm img.o $(SOLIB)/libimg.so: $(SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(EXAMPLES)/img.c $(CC) -o $@ img.o $(SOLDFLAGS) rm img.o # # CBF and IMG libraries # CBF_IMG_LIBS: $(LIB)/libcbf.a $(LIB)/libimg.a # # FCB library # $(LIB)/libfcb.a: $(F90SOURCE) $(COMMONDEP) $(LIB) ifneq ($(F90C),) $(F90C) $(F90FLAGS) -c $(F90SOURCE) $(AR) cr $@ *.o ifneq ($(RANLIB),) $(RANLIB) $@ endif rm *.o else echo "Define F90C to build $(LIB)/libfcb.a" endif $(SOLIB)/libfcb.so: $(F90SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) ifneq ($(F90C),) $(F90C) $(F90FLAGS) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(F90SOURCE) $(F90C) $(F90FLAGS) -o $@ *.o $(SOLDFLAGS) rm *.o else echo "Define F90C to build $(SOLIB)/libfcb.so" endif # # Python bindings # $(PYCBF)/_pycbf.$(PYCBFEXT): $(PYCBF) $(LIB)/libcbf.a \ $(PYCBF)/$(SETUP_PY) \ $(LIB)/libfcb.a \ $(LIB)/libimg.a \ $(PYCBF)/pycbf.i \ $(PYCBF)/cbfhandlewrappers.i \ $(PYCBF)/cbfdetectorwrappers.i \ $(PYCBF)/cbfgenericwrappers.i \ $(PYCBF)/cbfgoniometerwrappers.i (cd $(PYCBF); python $(SETUP_PY) build $(PYCBFBOPT); cp build/lib.*/_pycbf.$(PYCBFEXT) .) $(PYCBF)/setup.py: $(M4)/setup_py.m4 (m4 -P -Dregexlib=NOREGEXLIB -Dregexlibdir=NOREGEXLIBDIR $(M4)/setup_py.m4 > $@) $(PYCBF)/setup_MINGW.py: m4/setup_py.m4 (m4 -P -Dregexlib=regex -Dregexlibdir=$(REGEXDIR) $(M4)/setup_py.m4 > $@) $(LIB)/_pycbf.$(PYCBFEXT): $(PYCBF)/_pycbf.$(PYCBFEXT) cp $(PYCBF)/_pycbf.$(PYCBFEXT) $(LIB)/_pycbf.$(PYCBFEXT) $(PYCBF)/pycbf.pdf: $(PYCBF)/pycbf.w (cd $(PYCBF); \ $(NUWEB) pycbf; \ latex pycbf; \ $(NUWEB) pycbf; \ latex pycbf; \ dvipdfm pycbf ) $(PYCBF)/CBFlib.txt: $(DOC)/CBFlib.html links -dump $(DOC)/CBFlib.html > $(PYCBF)/CBFlib.txt $(PYCBF)/cbfhandlewrappers.i \ $(PYCBF)/cbfdetectorwrappers.i \ $(PYCBF)/cbfgenericwrappers.i \ $(PYCBF)/cbfgoniometerwrappers.i: $(PYCBF)/CBFlib.txt $(PYCBF)/make_pycbf.py (cd $(PYCBF); python make_pycbf.py; $(PYSWIG) pycbf.i; python setup.py build) # # Java bindings # $(JCBF)/cbflib-$(VERSION).jar: $(JCBF) $(JCBF)/jcbf.i $(JSWIG) -I$(INCLUDE) -package org.iucr.cbflib -outdir $(JCBF) $(JCBF)/jcbf.i $(JAVAC) -d . $(JCBF)/*.java $(JAR) cf $@ org $(SOLIB)/libcbf_wrap.so: $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf.so $(CC) $(CFLAGS) $(NOLLFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) $(JAVAINCLUDES) -c $(JCBF)/jcbf_wrap.c $(CC) -o $@ jcbf_wrap.o $(SOLDFLAGS) -L$(SOLIB) -lcbf rm jcbf_wrap.o # # F90SOURCE # $(SRC)/fcb_exit_binary.f90: $(M4)/fcb_exit_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_exit_binary.m4) > $(SRC)/fcb_exit_binary.f90 $(SRC)/fcb_next_binary.f90: $(M4)/fcb_next_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_next_binary.m4) > $(SRC)/fcb_next_binary.f90 $(SRC)/fcb_open_cifin.f90: $(M4)/fcb_open_cifin.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_open_cifin.m4) > $(SRC)/fcb_open_cifin.f90 $(SRC)/fcb_packed.f90: $(M4)/fcb_packed.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_packed.m4) > $(SRC)/fcb_packed.f90 $(SRC)/fcb_read_bits.f90: $(M4)/fcb_read_bits.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_bits.m4) > $(SRC)/fcb_read_bits.f90 $(SRC)/fcb_read_image.f90: $(M4)/fcb_read_image.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_image.m4) > $(SRC)/fcb_read_image.f90 $(SRC)/fcb_read_xds_i2.f90: $(M4)/fcb_read_xds_i2.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_xds_i2.m4) > $(SRC)/fcb_read_xds_i2.f90 $(EXAMPLES)/test_fcb_read_image.f90: $(M4)/test_fcb_read_image.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) test_fcb_read_image.m4) > $(EXAMPLES)/test_fcb_read_image.f90 $(EXAMPLES)/test_xds_binary.f90: $(M4)/test_xds_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) test_xds_binary.m4) > $(EXAMPLES)/test_xds_binary.f90 # # convert_image example program # $(BIN)/convert_image: $(LIB)/libcbf.a $(EXAMPLES)/convert_image.c $(EXAMPLES)/img.c \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/convert_image.c $(EXAMPLES)/img.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # convert_minicbf example program # $(BIN)/convert_minicbf: $(LIB)/libcbf.a $(EXAMPLES)/convert_minicbf.c \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/convert_minicbf.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # makecbf example program # $(BIN)/makecbf: $(LIB)/libcbf.a $(EXAMPLES)/makecbf.c $(LIB)/libimg.a $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/makecbf.c -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # adscimg2cbf example program # $(BIN)/adscimg2cbf: $(LIB)/libcbf.a $(EXAMPLES)/adscimg2cbf.c $(EXAMPLES)/adscimg2cbf_sub.c $(CC) $(CFLAGS) $(NOLLFLAG) -D_SVID_SOURCE $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/adscimg2cbf.c $(EXAMPLES)/adscimg2cbf_sub.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # cbf2adscimg example program # $(BIN)/cbf2adscimg: $(LIB)/libcbf.a $(EXAMPLES)/cbf2adscimg.c $(EXAMPLES)/cbf2adscimg_sub.c $(CC) $(CFLAGS) $(NOLLFLAG) -D_SVID_SOURCE $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cbf2adscimg.c $(EXAMPLES)/cbf2adscimg_sub.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # changtestcompression example program # $(BIN)/changtestcompression: $(LIB)/libcbf.a $(EXAMPLES)/changtestcompression.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/changtestcompression.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # img2cif example program # $(BIN)/img2cif: $(LIB)/libcbf.a $(EXAMPLES)/img2cif.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOTPINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/img2cif.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # cif2cbf example program # $(BIN)/cif2cbf: $(LIB)/libcbf.a $(EXAMPLES)/cif2cbf.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cif2cbf.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # dectris cbf_template_t program # $(BIN)/cbf_template_t: $(DECTRIS_EXAMPLES)/cbf_template_t.c \ $(DECTRIS_EXAMPLES)/mx_cbf_t_extras.h \ $(DECTRIS_EXAMPLES)/mx_parms.h $(CC) $(CFLAGS) $(NOLLFLAG) -I $(DECTRIS_EXAMPLES) $(WARNINGS) \ $(DECTRIS_EXAMPLES)/cbf_template_t.c -o $@ # # testcell example program # $(BIN)/testcell: $(LIB)/libcbf.a $(EXAMPLES)/testcell.C $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testcell.C -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # cif2c example program # $(BIN)/cif2c: $(LIB)/libcbf.a $(EXAMPLES)/cif2c.c $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cif2c.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # sauter_test example program # $(BIN)/sauter_test: $(LIB)/libcbf.a $(EXAMPLES)/sauter_test.C $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/sauter_test.C -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # sequence_match example program # $(BIN)/sequence_match: $(LIB)/libcbf.a $(EXAMPLES)/sequence_match.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/sequence_match.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # tiff2cbf example program # $(BIN)/tiff2cbf: $(LIB)/libcbf.a $(EXAMPLES)/tiff2cbf.c \ $(GOPTLIB) $(GOPTINC) $(TIFF) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ -I$(TIFFPREFIX)/include $(EXAMPLES)/tiff2cbf.c $(GOPTLIB) -L$(LIB) \ -lcbf -L$(TIFFPREFIX)/lib -ltiff $(EXTRALIBS) -limg -o $@ # # Andy Arvai's buffered read test program # $(BIN)/arvai_test: $(LIB)/libcbf.a $(EXAMPLES)/arvai_test.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/arvai_test.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # testreals example program # $(BIN)/testreals: $(LIB)/libcbf.a $(EXAMPLES)/testreals.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testreals.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testflat example program # $(BIN)/testflat: $(LIB)/libcbf.a $(EXAMPLES)/testflat.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testflat.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testflatpacked example program # $(BIN)/testflatpacked: $(LIB)/libcbf.a $(EXAMPLES)/testflatpacked.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testflatpacked.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ ifneq ($(F90C),) # # test_xds_binary example program # $(BIN)/test_xds_binary: $(LIB)/libfcb.a $(EXAMPLES)/test_xds_binary.f90 $(F90C) $(F90FLAGS) $(F90LDFLAGS) $(EXAMPLES)/test_xds_binary.f90 \ -L$(LIB) -lfcb -o $@ # # test_fcb_read_image example program # $(BIN)/test_fcb_read_image: $(LIB)/libfcb.a $(EXAMPLES)/test_fcb_read_image.f90 $(F90C) $(F90FLAGS) $(F90LDFLAGS) $(EXAMPLES)/test_fcb_read_image.f90 \ -L$(LIB) -lfcb -o $@ endif # # testcbf (C) # $(BIN)/ctestcbf: $(EXAMPLES)/testcbf.c $(LIB)/libcbf.a $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testcbf.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testcbf (Java) # $(BIN)/testcbf.class: $(EXAMPLES)/testcbf.java $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf_wrap.so $(JAVAC) -cp $(JCBF)/cbflib-$(VERSION).jar -d $(BIN) $(EXAMPLES)/testcbf.java # # Data files for tests # $(DATADIRI): (cd ..; $(DOWNLOAD) $(DATAURLI)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Input.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Input.tar.gz) $(DATADIRO): (cd ..; $(DOWNLOAD) $(DATAURLO)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Output.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Output.tar.gz) $(DATADIRS): (cd ..; $(DOWNLOAD) $(DATAURLS)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz) # Input Data Files TESTINPUT_BASIC = example.mar2300 DATADIRI_INPUT_BASIC = $(DATADIRI)/example.mar2300$(CEXT) TESTINPUT_EXTRA = 9ins.cif mb_LP_1_001.img insulin_pilatus6m.cbf testrealin.cbf \ testflatin.cbf testflatpackedin.cbf XRD1621.tif DATADIRI_INPUT_EXTRA = $(DATADIRI)/9ins.cif$(CEXT) $(DATADIRI)/mb_LP_1_001.img$(CEXT) \ $(DATADIRI)/insulin_pilatus6m.cbf$(CEXT) $(DATADIRI)/testrealin.cbf$(CEXT) \ $(DATADIRI)/testflatin.cbf$(CEXT) $(DATADIRI)/testflatpackedin.cbf$(CEXT) \ $(DATADIRI)/XRD1621.tif$(CEXT) # Output Data Files TESTOUTPUT = adscconverted_flat_orig.cbf \ adscconverted_orig.cbf converted_flat_orig.cbf converted_orig.cbf \ insulin_pilatus6mconverted_orig.cbf \ mb_LP_1_001_orig.cbf testcell_orig.prt \ test_xds_bin_testflatout_orig.out \ test_xds_bin_testflatpackedout_orig.out test_fcb_read_testflatout_orig.out \ test_fcb_read_testflatpackedout_orig.out \ XRD1621_orig.cbf XRD1621_I4encbC100_orig.cbf NEWTESTOUTPUT = adscconverted_flat.cbf \ adscconverted.cbf converted_flat.cbf converted.cbf \ insulin_pilatus6mconverted.cbf \ mb_LP_1_001.cbf testcell.prt \ test_xds_bin_testflatout.out \ test_xds_bin_testflatpackedout.out test_fcb_read_testflatout.out \ test_fcb_read_testflatpackedout.out \ XRD1621.cbf XRD1621_I4encbC100.cbf DATADIRO_OUTPUT = $(DATADIRO)/adscconverted_flat_orig.cbf$(CEXT) \ $(DATADIRO)/adscconverted_orig.cbf$(CEXT) \ $(DATADIRO)/converted_flat_orig.cbf$(CEXT) \ $(DATADIRO)/converted_orig.cbf$(CEXT) \ $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(CEXT) \ $(DATADIRO)/mb_LP_1_001_orig.cbf$(CEXT) \ $(DATADIRO)/testcell_orig.prt$(CEXT) \ $(DATADIRO)/test_xds_bin_testflatout_orig.out$(CEXT) \ $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(CEXT) \ $(DATADIRO)/test_fcb_read_testflatout_orig.out$(CEXT) \ $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(CEXT) \ $(DATADIRO)/XRD1621_orig.cbf$(CEXT) \ $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(CEXT) DATADIRO_OUTPUT_SIGNATURES = $(DATADIRO)/adscconverted_flat_orig.cbf$(SEXT) \ $(DATADIRO)/adscconverted_orig.cbf$(SEXT) \ $(DATADIRO)/converted_flat_orig.cbf$(SEXT) \ $(DATADIRO)/converted_orig.cbf$(SEXT) \ $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(SEXT) \ $(DATADIRO)/mb_LP_1_001_orig.cbf$(SEXT) \ $(DATADIRO)/testcell_orig.prt$(SEXT) \ $(DATADIRO)/test_xds_bin_testflatout_orig.out$(SEXT) \ $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(SEXT) \ $(DATADIRO)/test_fcb_read_testflatout_orig.out$(SEXT) \ $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(SEXT) \ $(DATADIRO)/XRD1621_orig.cbf$(SEXT) \ $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(SEXT) # Output Data File Signatures TESTOUTPUTSIGS = adscconverted_flat_orig.cbf$(SEXT) \ adscconverted_orig.cbf$(SEXT) converted_flat_orig.cbf$(SEXT) converted_orig.cbf$(SEXT) \ insulin_pilatus6mconverted_orig.cbf$(SEXT) \ mb_LP_1_001_orig.cbf$(SEXT) testcell_orig.prt$(SEXT) \ test_xds_bin_testflatout_orig.out$(SEXT) \ test_xds_bin_testflatpackedout_orig.out$(SEXT) test_fcb_read_testflatout_orig.out$(SEXT) \ test_fcb_read_testflatpackedout_orig.out$(SEXT) \ XRD1621_orig.cbf$(SEXT) DATADIRS_OUTPUT_SIGNATURES = $(DATADIRS)/adscconverted_flat_orig.cbf$(SEXT) \ $(DATADIRS)/adscconverted_orig.cbf$(SEXT) \ $(DATADIRS)/converted_flat_orig.cbf$(SEXT) \ $(DATADIRS)/converted_orig.cbf$(SEXT) \ $(DATADIRS)/insulin_pilatus6mconverted_orig.cbf$(SEXT) \ $(DATADIRS)/mb_LP_1_001_orig.cbf$(SEXT) \ $(DATADIRS)/testcell_orig.prt$(SEXT) \ $(DATADIRS)/test_xds_bin_testflatout_orig.out$(SEXT) \ $(DATADIRS)/test_xds_bin_testflatpackedout_orig.out$(SEXT) \ $(DATADIRS)/test_fcb_read_testflatout_orig.out$(SEXT) \ $(DATADIRS)/test_fcb_read_testflatpackedout_orig.out$(SEXT) \ $(DATADIRS)/XRD1621_orig.cbf$(SEXT) \ $(DATADIRS)/XRD1621_I4encbC100_orig.cbf$(SEXT) # Fetch Input Data Files $(TESTINPUT_BASIC): $(DATADIRI) $(DATADIRI_INPUT_BASIC) $(DECOMPRESS) < $(DATADIRI)/$@$(CEXT) > $@ cp $(DATADIRI)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) $(TESTINPUT_EXTRA): $(DATADIRI) $(DATADIRI_INPUT_EXTRA) $(DECOMPRESS) < $(DATADIRI)/$@$(CEXT) > $@ cp $(DATADIRI)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) # Fetch Output Data Files and Signatures $(TESTOUTPUT): $(DATADIRO) $(DATADIRO_OUTPUT) $(DATADIRO_OUTPUT_SIGNATURES) $(DECOMPRESS) < $(DATADIRO)/$@$(CEXT) > $@ cp $(DATADIRO)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) # Fetch Output Data File Signatures $(TESTOUTPUTSIGS): $(DATADIRS) $(DATADIRS_OUTPUT_SIGNATURES) cp $(DATADIRS)/$@ $@ # # Tests # tests: $(LIB) $(BIN) symlinksdone basic extra dectristests pycbftests tests_sigs_only: $(LIB) $(BIN) symlinksdone basic extra_sigs_only restore_output: $(NEWTESTOUTPUT) $(DATADIRO) $(SIGNATURE) < adscconverted_flat.cbf > $(DATADIRO)/adscconverted_flat_orig.cbf$(SEXT) $(SIGNATURE) < adscconverted.cbf > $(DATADIRO)/adscconverted_orig.cbf$(SEXT) $(SIGNATURE) < converted_flat.cbf > $(DATADIRO)/converted_flat_orig.cbf$(SEXT) $(SIGNATURE) < converted.cbf > $(DATADIRO)/converted_orig.cbf$(SEXT) $(SIGNATURE) < insulin_pilatus6mconverted.cbf > $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(SEXT) $(SIGNATURE) < mb_LP_1_001.cbf$ > $(DATADIRO)/mb_LP_1_001_orig.cbf$(SEXT) $(SIGNATURE) < testcell.prt > $(DATADIRO)/testcell_orig.prt$(SEXT) $(SIGNATURE) < test_xds_bin_testflatout.out > $(DATADIRO)/test_xds_bin_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_xds_bin_testflatpackedout.out > $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatout.out > $(DATADIRO)/test_fcb_read_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatpackedout.out > $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < XRD1621.cbf > $(DATADIRO)/XRD1621_orig.cbf$(SEXT) $(SIGNATURE) < XRD1621_I4encbC100.cbf > $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(SEXT) $(COMPRESS) < adscconverted_flat.cbf > $(DATADIRO)/adscconverted_flat_orig.cbf$(CEXT) $(COMPRESS) < adscconverted.cbf > $(DATADIRO)/adscconverted_orig.cbf$(CEXT) $(COMPRESS) < converted_flat.cbf > $(DATADIRO)/converted_flat_orig.cbf$(CEXT) $(COMPRESS) < converted.cbf > $(DATADIRO)/converted_orig.cbf$(CEXT) $(COMPRESS) < insulin_pilatus6mconverted.cbf > $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(CEXT) $(COMPRESS) < mb_LP_1_001.cbf$ > $(DATADIRO)/mb_LP_1_001_orig.cbf$(CEXT) $(COMPRESS) < testcell.prt > $(DATADIRO)/testcell_orig.prt$(CEXT) $(COMPRESS) < test_xds_bin_testflatout.out > $(DATADIRO)/test_xds_bin_testflatout_orig.out$(CEXT) $(COMPRESS) < test_xds_bin_testflatpackedout.out > $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(CEXT) $(COMPRESS) < test_fcb_read_testflatout.out > $(DATADIRO)/test_fcb_read_testflatout_orig.out$(CEXT) $(COMPRESS) < test_fcb_read_testflatpackedout.out > $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(CEXT) $(COMPRESS) < XRD1621.cbf > $(DATADIRO)/XRD1621_orig.cbf$(CEXT) $(COMPRESS) < XRD1621_I4encbC100.cbf > $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(CEXT) restore_sigs_only: $(NEWTESTOUTPUT) $(DATADIRS) $(SIGNATURE) < adscconverted_flat.cbf > $(DATADIRS)/adscconverted_flat_orig.cbf$(SEXT) $(SIGNATURE) < adscconverted.cbf > $(DATADIRS)/adscconverted_orig.cbf$(SEXT) $(SIGNATURE) < converted_flat.cbf > $(DATADIRS)/converted_flat_orig.cbf$(SEXT) $(SIGNATURE) < converted.cbf > $(DATADIRS)/converted_orig.cbf$(SEXT) $(SIGNATURE) < insulin_pilatus6mconverted.cbf > $(DATADIRS)/insulin_pilatus6mconverted_orig.cbf$(SEXT) $(SIGNATURE) < mb_LP_1_001.cbf$ > $(DATADIRS)/mb_LP_1_001_orig.cbf$(SEXT) $(SIGNATURE) < testcell.prt > $(DATADIRS)/testcell_orig.prt$(SEXT) $(SIGNATURE) < test_xds_bin_testflatout.out > $(DATADIRS)/test_xds_bin_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_xds_bin_testflatpackedout.out > $(DATADIRS)/test_xds_bin_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatout.out > $(DATADIRS)/test_fcb_read_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatpackedout.out > $(DATADIRS)/test_fcb_read_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < XRD1621.cbf > $(DATADIRS)/XRD1621_orig.cbf$(SEXT) $(SIGNATURE) < XRD1621_I4encbC100.cbf > $(DATADIRS)/XRD1621_I4encbC100_orig.cbf$(SEXT) restore_signatures: restore_output restore_sigs_only # # Basic Tests # basic: $(BIN)/makecbf $(BIN)/img2cif $(BIN)/cif2cbf $(TESTINPUT_BASIC) $(BIN)/makecbf example.mar2300 makecbf.cbf $(BIN)/img2cif -c flatpacked -m headers -d digest \ -e base64 example.mar2300 img2cif_packed.cif $(BIN)/img2cif -c canonical -m headers -d digest \ -e base64 example.mar2300 img2cif_canonical.cif $(BIN)/img2cif -c flatpacked -m headers -d digest \ -e none example.mar2300 img2cif_packed.cbf $(BIN)/img2cif -c canonical -m headers -d digest \ -e none example.mar2300 img2cif_canonical.cbf $(BIN)/cif2cbf -e none -c flatpacked \ img2cif_canonical.cif cif2cbf_packed.cbf $(BIN)/cif2cbf -e none -c canonical \ img2cif_packed.cif cif2cbf_canonical.cbf -cmp cif2cbf_packed.cbf makecbf.cbf -cmp cif2cbf_packed.cbf img2cif_packed.cbf -cmp cif2cbf_canonical.cbf img2cif_canonical.cbf # # Extra Tests # ifneq ($(F90C),) extra: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/test_xds_binary $(BIN)/test_fcb_read_image $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg \ $(BIN)/changtestcompression $(BIN)/tiff2cbf \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUT) else extra: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUT) endif $(TIME) $(BIN)/cif2cbf -e hex -c none \ makecbf.cbf cif2cbf_ehcn.cif $(TIME) $(BIN)/cif2cbf -e none -c flatpacked \ cif2cbf_ehcn.cif cif2cbf_encp.cbf; rm cif2cbf_ehcn.cif -cmp makecbf.cbf cif2cbf_encp.cbf $(TIME) $(BIN)/cif2cbf -i 9ins.cif -o 9ins.cbf -cmp 9ins.cif 9ins.cbf $(TIME) $(BIN)/convert_image -F example.mar2300 converted_flat.cbf -cmp converted_flat.cbf converted_flat_orig.cbf $(TIME) $(BIN)/convert_image example.mar2300 converted.cbf -cmp converted.cbf converted_orig.cbf -$(TIME) $(BIN)/testcell < testcell.dat > testcell.prt -cmp testcell.prt testcell_orig.prt $(TIME) $(BIN)/convert_image -F -d adscquantum315 mb_LP_1_001.img adscconverted_flat.cbf -cmp adscconverted_flat.cbf adscconverted_flat_orig.cbf $(TIME) $(BIN)/convert_image -d adscquantum315 mb_LP_1_001.img adscconverted.cbf -cmp adscconverted.cbf adscconverted_orig.cbf $(TIME) $(BIN)/adscimg2cbf --no_pad --cbf_packed,flat mb_LP_1_001.img -cmp mb_LP_1_001.cbf mb_LP_1_001_orig.cbf ifneq ($(CLEANTESTS),) mv mb_LP_1_001.cbf nmb_LP_1_001.cbf else cp mb_LP_1_001.cbf nmb_LP_1_001.cbf endif $(TIME) $(BIN)/cbf2adscimg nmb_LP_1_001.cbf -cmp nmb_LP_1_001.img mb_LP_1_001.img rm nmb_LP_1_001.cbf ifneq ($(CLEANTESTS),) rm nmb_LP_1_001.img endif $(TIME) $(BIN)/convert_minicbf -d pilatus6m insulin_pilatus6m.cbf insulin_pilatus6mconverted.cbf -cmp insulin_pilatus6mconverted.cbf insulin_pilatus6mconverted_orig.cbf $(TIME) $(BIN)/testreals -cmp testrealin.cbf testrealout.cbf $(TIME) $(BIN)/testflat -cmp testflatin.cbf testflatout.cbf $(TIME) $(BIN)/testflatpacked -cmp testflatpackedin.cbf testflatpackedout.cbf ifneq ($(F90C),) echo testflatout.cbf | $(TIME) $(BIN)/test_xds_binary > test_xds_bin_testflatout.out -$(DIFF) test_xds_bin_testflatout.out test_xds_bin_testflatout_orig.out echo testflatpackedout.cbf | $(TIME) $(BIN)/test_xds_binary > test_xds_bin_testflatpackedout.out -$(DIFF) test_xds_bin_testflatpackedout.out test_xds_bin_testflatpackedout_orig.out echo testflatout.cbf | $(TIME) $(BIN)/test_fcb_read_image > test_fcb_read_testflatout.out -$(DIFF) test_fcb_read_testflatout.out test_fcb_read_testflatout_orig.out echo testflatpackedout.cbf | $(TIME) $(BIN)/test_fcb_read_image > test_fcb_read_testflatpackedout.out -$(DIFF) test_fcb_read_testflatpackedout.out test_fcb_read_testflatpackedout_orig.out endif $(TIME) $(BIN)/sauter_test $(TIME) $(BIN)/changtestcompression $(TIME) (export LD_LIBRARY_PATH=$(LIB);$(BIN)/tiff2cbf XRD1621.tif XRD1621.cbf) -$(DIFF) XRD1621.cbf XRD1621_orig.cbf $(TIME) $(BIN)/cif2cbf -I 4 -C 100. -L 0. -e n -c b -i XRD1621.cbf -o XRD1621_I4encbC100.cbf -$(DIFF) XRD1621_I4encbC100.cbf XRD1621_I4encbC100_orig.cbf ifneq ($(F90C),) extra_sigs_only: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/test_xds_binary $(BIN)/test_fcb_read_image $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg $(BIN)/tiff2cbf \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) else extra_sigs_only: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf\ basic $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) endif $(TIME) $(BIN)/cif2cbf -e hex -c none \ makecbf.cbf cif2cbf_ehcn.cif $(TIME) $(BIN)/cif2cbf -e none -c packed \ cif2cbf_ehcn.cif cif2cbf_encp.cbf; rm cif2cbf_ehcn.cif -cmp makecbf.cbf cif2cbf_encp.cbf $(TIME) $(BIN)/cif2cbf -i 9ins.cif -o 9ins.cbf -cmp 9ins.cif 9ins.cbf $(TIME) $(BIN)/convert_image -F example.mar2300 converted_flat.cbf -$(SIGNATURE) < converted_flat.cbf | $(DIFF) - converted_flat_orig.cbf$(SEXT); rm converted_flat.cbf $(TIME) $(BIN)/convert_image example.mar2300 converted.cbf -$(SIGNATURE) < converted.cbf | $(DIFF) - converted_orig.cbf$(SEXT); rm converted.cbf -$(TIME) $(BIN)/testcell < testcell.dat | \ $(SIGNATURE) | $(DIFF) - testcell_orig.prt$(SEXT) $(TIME) $(BIN)/convert_image -F -d adscquantum315 mb_LP_1_001.img adscconverted_flat.cbf -$(SIGNATURE) < adscconverted_flat.cbf | $(DIFF) - adscconverted_flat_orig.cbf$(SEXT) $(TIME) $(BIN)/convert_image -d adscquantum315 mb_LP_1_001.img adscconverted.cbf -$(SIGNATURE) < adscconverted.cbf | $(DIFF) - adscconverted_orig.cbf$(SEXT); rm adscconverted.cbf $(TIME) $(BIN)/adscimg2cbf --cbf_packed,flat mb_LP_1_001.img -$(SIGNATURE) < mb_LP_1_001.cbf | $(DIFF) - mb_LP_1_001_orig.cbf$(SEXT) mv mb_LP_1_001.cbf nmb_LP_1_001.cbf $(TIME) $(BIN)/cbf2adscimg nmb_LP_1_001.cbf -cmp nmb_LP_1_001.img mb_LP_1_001.img rm nmb_LP_1_001.cbf rm nmb_LP_1_001.img $(TIME) $(BIN)/convert_minicbf -d pilatus6m insulin_pilatus6m.cbf insulin_pilatus6mconverted.cbf -$(SIGNATURE) < insulin_pilatus6mconverted.cbf | $(DIFF) - insulin_pilatus6mconverted_orig.cbf$(SEXT); rm insulin_pilatus6mconverted.cbf $(TIME) $(BIN)/testreals -cmp testrealin.cbf testrealout.cbf $(TIME) $(BIN)/testflat -cmp testflatin.cbf testflatout.cbf $(TIME) $(BIN)/testflatpacked -cmp testflatpackedin.cbf testflatpackedout.cbf ifneq ($(F90C),) echo testflatout.cbf | $(TIME) $(BIN)/test_xds_binary | \ $(SIGNATURE) | $(DIFF) - test_xds_bin_testflatout_orig.out$(SEXT) echo testflatpackedout.cbf | $(TIME) $(BIN)/test_xds_binary | \ $(SIGNATURE) | $(DIFF) - test_xds_bin_testflatpackedout_orig.out$(SEXT) echo testflatout.cbf | $(TIME) $(BIN)/test_fcb_read_image | \ $(SIGNATURE) | $(DIFF) - test_fcb_read_testflatout_orig.out$(SEXT) echo testflatpackedout.cbf | $(TIME) $(BIN)/test_fcb_read_image | \ $(SIGNATURE) | $(DIFF) - test_fcb_read_testflatpackedout_orig.out$(SEXT) endif $(TIME) $(BIN)/sauter_test $(TIME) $(BIN)/tiff2cbf XRD1621.tif XRD1621.cbf $(TIME) $(BIN)/cif2cbf -I 4 -C 100. -L 0. -e n -c b -i XRD1621.cbf -o XRD1621_I4encbC100.cbf -$(SIGNATURE) < XRD1621.cbf | $(DIFF) - XRD1621_orig.cbf$(SEXT); rm XRD1621.cbf -$(SIGNATURE) < XRD1621_I4encbC100.cbf | $(DIFF) - XRD1621_I4encbC100_orig.cbf$(SEXT); rm XRD1621_I4encbC100.cbf @-rm -f adscconverted_flat.cbf @-rm -f $(TESTINPUT_BASIC) $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) @-rm -f cif2cbf_packed.cbf makecbf.cbf \ cif2cbf_packed.cbf img2cif_packed.cbf \ cif2cbf_canonical.cbf img2cif_canonical.cbf @-rm -f testrealout.cbf testflatout.cbf testflatpackedout.cbf \ cif2cbf_encp.cbf img2cif_canonical.cif img2cif_packed.cif 9ins.cbf pycbftests: $(PYCBF)/_pycbf.$(PYCBFEXT) (cd $(PYCBF); python pycbf_test1.py) (cd $(PYCBF); python pycbf_test2.py) (cd $(PYCBF); python pycbf_test3.py) javatests: $(BIN)/ctestcbf $(BIN)/testcbf.class $(SOLIB)/libcbf_wrap.so $(BIN)/ctestcbf > testcbfc.txt $(LDPREFIX) java -cp $(JCBF)/cbflib-$(VERSION).jar:$(BIN) testcbf > testcbfj.txt $(DIFF) testcbfc.txt testcbfj.txt dectristests: $(BIN)/cbf_template_t $(DECTRIS_EXAMPLES)/cbf_test_orig.out (cd $(DECTRIS_EXAMPLES); ../../bin/cbf_template_t; diff -a -u cbf_test_orig.out cbf_template_t.out) # # Remove all non-source files # empty: @-rm -f $(LIB)/*.o @-rm -f $(LIB)/libcbf.a @-rm -f $(LIB)/libfcb.a @-rm -f $(LIB)/libimg.a @-rm -f $(LIB)/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/build/*/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/build/src/cbf_simple.o @-rm -f $(PYCBF)/build/*/pycbf_wrap.o @-rm -rf $(BIN)/adscimg2cbf* @-rm -rf $(BIN)/cbf2adscimg* @-rm -rf $(BIN)/makecbf* @-rm -rf $(BIN)/img2cif* @-rm -rf $(BIN)/cif2cbf* @-rm -rf $(BIN)/convert_image* @-rm -rf $(BIN)/convert_minicbf* @-rm -rf $(BIN)/test_fcb_read_image* @-rm -rf $(BIN)/test_xds_binary* @-rm -rf $(BIN)/testcell* @-rm -rf $(BIN)/cif2c* @-rm -rf $(BIN)/testreals* @-rm -rf $(BIN)/testflat* @-rm -rf $(BIN)/testflatpacked* @-rm -rf $(BIN)/cbf_template_t* @-rm -rf $(BIN)/sauter_test* @-rm -rf $(BIN)/arvai_test* @-rm -rf $(BIN)/changtestcompression* @-rm -rf $(BIN)/tiff2cbf* @-rm -f makecbf.cbf @-rm -f img2cif_packed.cif @-rm -f img2cif_canonical.cif @-rm -f img2cif_packed.cbf @-rm -f img2cif_canonical.cbf @-rm -f img2cif_raw.cbf @-rm -f cif2cbf_packed.cbf @-rm -f cif2cbf_canonical.cbf @-rm -f converted.cbf @-rm -f adscconverted.cbf @-rm -f converted_flat.cbf @-rm -f adscconverted_flat.cbf @-rm -f adscconverted_flat_rev.cbf @-rm -f mb_LP_1_001.cbf @-rm -f cif2cbf_ehcn.cif @-rm -f cif2cbf_encp.cbf @-rm -f 9ins.cbf @-rm -f 9ins.cif @-rm -f testcell.prt @-rm -f example.mar2300 @-rm -f converted_orig.cbf @-rm -f adscconverted_orig.cbf @-rm -f converted_flat_orig.cbf @-rm -f adscconverted_flat_orig.cbf @-rm -f adscconverted_flat_rev_orig.cbf @-rm -f mb_LP_1_001_orig.cbf @-rm -f insulin_pilatus6mconverted_orig.cbf @-rm -f insulin_pilatus6mconverted.cbf @-rm -f insulin_pilatus6m.cbf @-rm -f testrealin.cbf @-rm -f testrealout.cbf @-rm -f testflatin.cbf @-rm -f testflatout.cbf @-rm -f testflatpackedin.cbf @-rm -f testflatpackedout.cbf @-rm -f CTC.cbf @-rm -f test_fcb_read_testflatout.out @-rm -f test_fcb_read_testflatpackedout.out @-rm -f test_xds_bin_testflatpackedout.out @-rm -f test_xds_bin_testflatout.out @-rm -f test_fcb_read_testflatout_orig.out @-rm -f test_fcb_read_testflatpackedout_orig.out @-rm -f test_xds_bin_testflatpackedout_orig.out @-rm -f test_xds_bin_testflatout_orig.out @-rm -f mb_LP_1_001.img @-rm -f 9ins.cif @-rm -f testcell_orig.prt @-rm -f $(DECTRIS_EXAMPLES)/cbf_template_t.out @-rm -f XRD1621.cbf @-rm -f XRD1621_orig.cbf @-rm -f XRD1621_orig.cbf @-rm -f XRD1621_I4encbC100.cbf @-rm -f $(SRC)/fcb_exit_binary.f90 @-rm -f $(SRC)/fcb_next_binary.f90 @-rm -f $(SRC)/fcb_open_cifin.f90 @-rm -f $(SRC)/fcb_packed.f90 @-rm -f $(SRC)/fcb_read_bits.f90 @-rm -f $(SRC)/fcb_read_image.f90 @-rm -f $(SRC)/fcb_read_xds_i2.f90 @-rm -f $(EXAMPLES)/test_fcb_read_image.f90 @-rm -f $(EXAMPLES)/test_xds_binary.f90 @-rm -f symlinksdone @-rm -f $(TESTOUTPUT) *$(SEXT) @-rm -f $(SOLIB)/*.o @-rm -f $(SOLIB)/libcbf_wrap.so @-rm -f $(SOLIB)/libjcbf.so @-rm -f $(SOLIB)/libimg.so @-rm -f $(SOLIB)/libfcb.so @-rm -rf $(JCBF)/org @-rm -f $(JCBF)/*.java @-rm -f $(JCBF)/jcbf_wrap.c @-rm -f $(SRC)/cbf_wrap.c @-rm -f $(BIN)/ctestcbf $(BIN)/testcbf.class testcbfc.txt testcbfj.txt @-rm -rf $(REGEX) @-rm -rf $(TIFF) ./.undosymlinks # # Remove temporary files # clean: @-rm -f core @-rm -f *.o @-rm -f *.u # # Restore to distribution state # distclean: clean empty # # Create a Tape Archive for distribution # tar: $(DOCUMENTS) $(SOURCE) $(SRC)/cbf.stx $(HEADERS) $(M4FILES)\ $(EXAMPLES) \ README.html README Makefile \ $(JPEGS) -/bin/rm -f CBFlib.tar* tar cvBf CBFlib.tar \ $(DOCUMENTS) $(SOURCE) $(SRC)/cbf.stx $(HEADERS) $(M4FILES)\ $(EXAMPLES) \ README.html README Makefile \ $(JPEGS) gzip --best CBFlib.tar ./CBFlib-0.9.2.2/Makefile_LINUX_640000644000076500007650000020025711603702122014532 0ustar yayayaya ###################################################################### # Makefile - command file for make to create CBFlib # # # # Version 0.9.2 12 Feb 2011 # # # # Paul Ellis and # # Herbert J. Bernstein (yaya@bernstein-plus-sons.com) # # # # (C) Copyright 2006 - 2011 Herbert J. Bernstein # # # ###################################################################### ###################################################################### # # # YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL # # # # ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS # # OF THE LGPL # # # ###################################################################### ########################### GPL NOTICES ############################## # # # This program is free software; you can redistribute it and/or # # modify it under the terms of the GNU General Public License as # # published by the Free Software Foundation; either version 2 of # # (the License, or (at your option) any later version. # # # # This program is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # # GNU General Public License for more details. # # # # You should have received a copy of the GNU General Public License # # along with this program; if not, write to the Free Software # # Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA # # 02111-1307 USA # # # ###################################################################### ######################### LGPL NOTICES ############################### # # # This library is free software; you can redistribute it and/or # # modify it under the terms of the GNU Lesser General Public # # License as published by the Free Software Foundation; either # # version 2.1 of the License, or (at your option) any later version. # # # # This library is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # # Lesser General Public License for more details. # # # # You should have received a copy of the GNU Lesser General Public # # License along with this library; if not, write to the Free # # Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, # # MA 02110-1301 USA # # # ###################################################################### ###################################################################### # # # Stanford University Notices # # for the CBFlib software package that incorporates SLAC software # # on which copyright is disclaimed # # # # This software # # ------------- # # The term "this software", as used in these Notices, refers to # # those portions of the software package CBFlib that were created by # # employees of the Stanford Linear Accelerator Center, Stanford # # University. # # # # Stanford disclaimer of copyright # # -------------------------------- # # Stanford University, owner of the copyright, hereby disclaims its # # copyright and all other rights in this software. Hence, anyone # # may freely use it for any purpose without restriction. # # # # Acknowledgement of sponsorship # # ------------------------------ # # This software was produced by the Stanford Linear Accelerator # # Center, Stanford University, under Contract DE-AC03-76SFO0515 with # # the Department of Energy. # # # # Government disclaimer of liability # # ---------------------------------- # # Neither the United States nor the United States Department of # # Energy, nor any of their employees, makes any warranty, express or # # implied, or assumes any legal liability or responsibility for the # # accuracy, completeness, or usefulness of any data, apparatus, # # product, or process disclosed, or represents that its use would # # not infringe privately owned rights. # # # # Stanford disclaimer of liability # # -------------------------------- # # Stanford University makes no representations or warranties, # # express or implied, nor assumes any liability for the use of this # # software. # # # # Maintenance of notices # # ---------------------- # # In the interest of clarity regarding the origin and status of this # # software, this and all the preceding Stanford University notices # # are to remain affixed to any copy or derivative of this software # # made or distributed by the recipient and are to be affixed to any # # copy of software made or distributed by the recipient that # # contains a copy or derivative of this software. # # # # Based on SLAC Software Notices, Set 4 # # OTT.002a, 2004 FEB 03 # ###################################################################### ###################################################################### # NOTICE # # Creative endeavors depend on the lively exchange of ideas. There # # are laws and customs which establish rights and responsibilities # # for authors and the users of what authors create. This notice # # is not intended to prevent you from using the software and # # documents in this package, but to ensure that there are no # # misunderstandings about terms and conditions of such use. # # # # Please read the following notice carefully. If you do not # # understand any portion of this notice, please seek appropriate # # professional legal advice before making use of the software and # # documents included in this software package. In addition to # # whatever other steps you may be obliged to take to respect the # # intellectual property rights of the various parties involved, if # # you do make use of the software and documents in this package, # # please give credit where credit is due by citing this package, # # its authors and the URL or other source from which you obtained # # it, or equivalent primary references in the literature with the # # same authors. # # # # Some of the software and documents included within this software # # package are the intellectual property of various parties, and # # placement in this package does not in any way imply that any # # such rights have in any way been waived or diminished. # # # # With respect to any software or documents for which a copyright # # exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. # # # # Even though the authors of the various documents and software # # found here have made a good faith effort to ensure that the # # documents are correct and that the software performs according # # to its documentation, and we would greatly appreciate hearing of # # any problems you may encounter, the programs and documents any # # files created by the programs are provided **AS IS** without any * # warranty as to correctness, merchantability or fitness for any # # particular or general use. # # # # THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF # # PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE # # PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS # # OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE # # PROGRAMS OR DOCUMENTS. # ###################################################################### ###################################################################### # # # The IUCr Policy # # for the Protection and the Promotion of the STAR File and # # CIF Standards for Exchanging and Archiving Electronic Data # # # # Overview # # # # The Crystallographic Information File (CIF)[1] is a standard for # # information interchange promulgated by the International Union of # # Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the # # recommended method for submitting publications to Acta # # Crystallographica Section C and reports of crystal structure # # determinations to other sections of Acta Crystallographica # # and many other journals. The syntax of a CIF is a subset of the # # more general STAR File[2] format. The CIF and STAR File approaches # # are used increasingly in the structural sciences for data exchange # # and archiving, and are having a significant influence on these # # activities in other fields. # # # # Statement of intent # # # # The IUCr's interest in the STAR File is as a general data # # interchange standard for science, and its interest in the CIF, # # a conformant derivative of the STAR File, is as a concise data # # exchange and archival standard for crystallography and structural # # science. # # # # Protection of the standards # # # # To protect the STAR File and the CIF as standards for # # interchanging and archiving electronic data, the IUCr, on behalf # # of the scientific community, # # # # # holds the copyrights on the standards themselves, * # # # # owns the associated trademarks and service marks, and * # # # # holds a patent on the STAR File. * # # # These intellectual property rights relate solely to the # # interchange formats, not to the data contained therein, nor to # # the software used in the generation, access or manipulation of # # the data. # # # # Promotion of the standards # # # # The sole requirement that the IUCr, in its protective role, # # imposes on software purporting to process STAR File or CIF data # # is that the following conditions be met prior to sale or # # distribution. # # # # # Software claiming to read files written to either the STAR * # File or the CIF standard must be able to extract the pertinent # # data from a file conformant to the STAR File syntax, or the CIF # # syntax, respectively. # # # # # Software claiming to write files in either the STAR File, or * # the CIF, standard must produce files that are conformant to the # # STAR File syntax, or the CIF syntax, respectively. # # # # # Software claiming to read definitions from a specific data * # dictionary approved by the IUCr must be able to extract any # # pertinent definition which is conformant to the dictionary # # definition language (DDL)[3] associated with that dictionary. # # # # The IUCr, through its Committee on CIF Standards, will assist # # any developer to verify that software meets these conformance # # conditions. # # # # Glossary of terms # # # # [1] CIF: is a data file conformant to the file syntax defined # # at http://www.iucr.org/iucr-top/cif/spec/index.html # # # # [2] STAR File: is a data file conformant to the file syntax # # defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html # # # # [3] DDL: is a language used in a data dictionary to define data # # items in terms of "attributes". Dictionaries currently approved # # by the IUCr, and the DDL versions used to construct these # # dictionaries, are listed at # # http://www.iucr.org/iucr-top/cif/spec/ddl/index.html # # # # Last modified: 30 September 2000 # # # # IUCr Policy Copyright (C) 2000 International Union of # # Crystallography # ###################################################################### # Version string VERSION = 0.9.2 # # Comment out the next line if scratch test files sould be retain # CLEANTESTS = yes # # Definition to get a version of tifflib to support tiff2cbf # TIFF = tiff-3.9.4-rev-6Feb11 TIFFPREFIX = $(PWD) # # Definitions to get a stable version of regex # REGEX = regex-20090805 REGEXDIR = /usr/lib REGEXDEP = # Program to use to retrieve a URL DOWNLOAD = wget # Flag to control symlinks versus copying SLFLAGS = --use_ln # # Program to use to pack shars # SHAR = /usr/bin/shar #SHAR = /usr/local/bin/gshar # # Program to use to create archives # AR = /usr/bin/ar # # Program to use to add an index to an archive # RANLIB = /usr/bin/ranlib # # Program to use to decompress a data file # DECOMPRESS = /usr/bin/bunzip2 # # Program to use to compress a data file # COMPRESS = /usr/bin/bzip2 # # Program to use to generate a signature # SIGNATURE = /usr/bin/openssl dgst -md5 # # Extension for compressed data file (with period) # CEXT = .bz2 # # Extension for signatures of files # SEXT = .md5 # call to time a command #TIME = #TIME = time # # Program to display differences between files # DIFF = diff -u -b # # Program to generate wrapper classes for Python # PYSWIG = swig -python # # Program to generate wrapper classes for Java # JSWIG = swig -java # # Program to generate LaTex and HTML program documentation # NUWEB = nuweb # # Compiler for Java # JAVAC = javac # # Java archiver for compiled classes # JAR = jar # # Java SDK root directory # ifeq ($(JDKDIR),) JDKDIR = /usr/lib/java endif ifneq ($(CBF_DONT_USE_LONG_LONG),) NOLLFLAG = -DCBF_DONT_USE_LONG_LONG else NOLLFLAG = endif # # PYCBF definitions # PYCBFEXT = so PYCBFBOPT = SETUP_PY = setup.py # # Set the compiler and flags # ######################################################### # # Appropriate compiler definitions for Linux x86_64 # with gcc version 4.2 # ######################################################### CC = gcc -m64 C++ = g++ -m64 CFLAGS = -g -O2 -Wall -D_USE_XOPEN_EXTENDED -fno-strict-aliasing F90C = gfortran -m64 F90FLAGS = -g -fno-range-check F90LDFLAGS = SOCFLAGS = -fPIC SOLDFLAGS = -shared -Wl,-rpath,$(INSTALLDIR)/lib JAVAINCLUDES = -I$(JDKDIR)/include -I$(JDKDIR)/include/linux LDPREFIX = LD_LIBRARY_PATH=$(SOLIB) EXTRALIBS = -lm M4FLAGS = -Dfcb_bytes_in_rec=131072 TIME = time DOWNLOAD = /sw/bin/wget ifneq ($(NOFORTRAN),) F90C = endif # # Directories # ROOT = . LIB = $(ROOT)/lib SOLIB = $(ROOT)/solib JCBF = $(ROOT)/jcbf JAVADIR = $(ROOT)/java BIN = $(ROOT)/bin SRC = $(ROOT)/src INCLUDE = $(ROOT)/include M4 = $(ROOT)/m4 PYCBF = $(ROOT)/pycbf EXAMPLES = $(ROOT)/examples DECTRIS_EXAMPLES = $(EXAMPLES)/dectris_cbf_template_test DOC = $(ROOT)/doc GRAPHICS = $(ROOT)/html_graphics DATADIRI = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Input DATADIRO = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Output DATADIRS = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only INSTALLDIR = $(HOME) # # URLs from which to retrieve the data directories # DATAURLBASE = http://downloads.sf.net/cbflib/ DATAURLI = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Input.tar.gz DATAURLO = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Output.tar.gz DATAURLS = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz # # URLs from which to retrieve needed external package snapshots # REGEXURL = http://downloads.sf.net/cbflib/$(REGEX).tar.gz TIFFURL = http://downloads.sf.net/cbflib/$(TIFF).tar.gz # # Include directories # INCLUDES = -I$(INCLUDE) -I$(SRC) ###################################################################### # You should not need to make modifications below this line # ###################################################################### # # Suffixes of files to be used or built # .SUFFIXES: .c .o .f90 .m4 .m4.f90: m4 -P $(M4FLAGS) $< > $@ ifneq ($(F90C),) .f90.o: $(F90C) $(F90FLAGS) -c $< -o $@ endif # # Common dependencies # COMMONDEP = Makefile # # Source files # SOURCE = $(SRC)/cbf.c \ $(SRC)/cbf_alloc.c \ $(SRC)/cbf_ascii.c \ $(SRC)/cbf_binary.c \ $(SRC)/cbf_byte_offset.c \ $(SRC)/cbf_canonical.c \ $(SRC)/cbf_codes.c \ $(SRC)/cbf_compress.c \ $(SRC)/cbf_context.c \ $(SRC)/cbf_copy.c \ $(SRC)/cbf_file.c \ $(SRC)/cbf_getopt.c \ $(SRC)/cbf_lex.c \ $(SRC)/cbf_packed.c \ $(SRC)/cbf_predictor.c \ $(SRC)/cbf_read_binary.c \ $(SRC)/cbf_read_mime.c \ $(SRC)/cbf_simple.c \ $(SRC)/cbf_string.c \ $(SRC)/cbf_stx.c \ $(SRC)/cbf_tree.c \ $(SRC)/cbf_uncompressed.c \ $(SRC)/cbf_write.c \ $(SRC)/cbf_write_binary.c \ $(SRC)/cbf_ws.c \ $(SRC)/md5c.c F90SOURCE = $(SRC)/fcb_atol_wcnt.f90 \ $(SRC)/fcb_ci_strncmparr.f90 \ $(SRC)/fcb_exit_binary.f90 \ $(SRC)/fcb_nblen_array.f90 \ $(SRC)/fcb_next_binary.f90 \ $(SRC)/fcb_open_cifin.f90 \ $(SRC)/fcb_packed.f90 \ $(SRC)/fcb_read_bits.f90 \ $(SRC)/fcb_read_byte.f90 \ $(SRC)/fcb_read_image.f90 \ $(SRC)/fcb_read_line.f90 \ $(SRC)/fcb_read_xds_i2.f90 \ $(SRC)/fcb_skip_whitespace.f90 \ $(EXAMPLES)/test_fcb_read_image.f90 \ $(EXAMPLES)/test_xds_binary.f90 # # Header files # HEADERS = $(INCLUDE)/cbf.h \ $(INCLUDE)/cbf_alloc.h \ $(INCLUDE)/cbf_ascii.h \ $(INCLUDE)/cbf_binary.h \ $(INCLUDE)/cbf_byte_offset.h \ $(INCLUDE)/cbf_canonical.h \ $(INCLUDE)/cbf_codes.h \ $(INCLUDE)/cbf_compress.h \ $(INCLUDE)/cbf_context.h \ $(INCLUDE)/cbf_copy.h \ $(INCLUDE)/cbf_file.h \ $(INCLUDE)/cbf_getopt.h \ $(INCLUDE)/cbf_lex.h \ $(INCLUDE)/cbf_packed.h \ $(INCLUDE)/cbf_predictor.h \ $(INCLUDE)/cbf_read_binary.h \ $(INCLUDE)/cbf_read_mime.h \ $(INCLUDE)/cbf_simple.h \ $(INCLUDE)/cbf_string.h \ $(INCLUDE)/cbf_stx.h \ $(INCLUDE)/cbf_tree.h \ $(INCLUDE)/cbf_uncompressed.h \ $(INCLUDE)/cbf_write.h \ $(INCLUDE)/cbf_write_binary.h \ $(INCLUDE)/cbf_ws.h \ $(INCLUDE)/global.h \ $(INCLUDE)/cbff.h \ $(INCLUDE)/md5.h # # m4 macro files # M4FILES = $(M4)/fcblib_defines.m4 \ $(M4)/fcb_exit_binary.m4 \ $(M4)/fcb_next_binary.m4 \ $(M4)/fcb_open_cifin.m4 \ $(M4)/fcb_packed.m4 \ $(M4)/fcb_read_bits.m4 \ $(M4)/fcb_read_image.m4 \ $(M4)/fcb_read_xds_i2.m4 \ $(M4)/test_fcb_read_image.m4 \ $(M4)/test_xds_binary.m4 # # Documentation files # DOCUMENTS = $(DOC)/CBFlib.html \ $(DOC)/CBFlib.txt \ $(DOC)/CBFlib_NOTICES.html \ $(DOC)/CBFlib_NOTICES.txt \ $(DOC)/ChangeLog \ $(DOC)/ChangeLog.html \ $(DOC)/MANIFEST \ $(DOC)/gpl.txt $(DOC)/lgpl.txt # # HTML Graphics files # JPEGS = $(GRAPHICS)/CBFbackground.jpg \ $(GRAPHICS)/CBFbig.jpg \ $(GRAPHICS)/CBFbutton.jpg \ $(GRAPHICS)/cbflibbackground.jpg \ $(GRAPHICS)/cbflibbig.jpg \ $(GRAPHICS)/cbflibbutton.jpg \ $(GRAPHICS)/cifhome.jpg \ $(GRAPHICS)/iucrhome.jpg \ $(GRAPHICS)/noticeButton.jpg # # Default: instructions # default: @echo ' ' @echo '***************************************************************' @echo ' ' @echo ' PLEASE READ README and doc/CBFlib_NOTICES.txt' @echo ' ' @echo ' Before making the CBF library and example programs, check' @echo ' that the C compiler name and flags are correct:' @echo ' ' @echo ' The current values are:' @echo ' ' @echo ' $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG)' @echo ' ' @echo ' Before installing the CBF library and example programs, check' @echo ' that the install directory is correct:' @echo ' ' @echo ' The current value :' @echo ' ' @echo ' $(INSTALLDIR) ' @echo ' ' @echo ' To compile the CBF library and example programs type:' @echo ' ' @echo ' make clean' @echo ' make all' @echo ' ' @echo ' To compile the CBF library as a shared object library, type:' @echo ' ' @echo ' make shared' @echo ' ' @echo ' To compile the Java wrapper classes for CBF library, type:' @echo ' ' @echo ' make javawrapper' @echo ' ' @echo ' To run a set of tests type:' @echo ' ' @echo ' make tests' @echo ' ' @echo ' To run some java tests type:' @echo ' ' @echo ' make javatests' @echo ' ' @echo ' The tests assume that several data files are in the directories' @echo ' $(DATADIRI) and $(DATADIRO)' @echo ' ' @echo ' Alternatively tests can be run comparing MD5 signatures only by' @echo ' ' @echo ' make tests_sigs_only' @echo ' ' @echo ' These signature only tests save space and download time by' @echo ' assuming that input data files and the output signatures' @echo ' are in the directories' @echo ' $(DATADIRI) and $(DATADIRS)' @echo ' ' @echo ' These directory can be obtained from' @echo ' ' @echo ' $(DATAURLI) ' @echo ' $(DATAURLO) ' @echo ' $(DATAURLS) ' @echo ' ' @echo ' To clean up the directories type:' @echo ' ' @echo ' make clean' @echo ' ' @echo ' To install the library and binaries type:' @echo ' ' @echo ' make install' @echo ' ' @echo '***************************************************************' @echo ' ' # # Compile the library and examples # all:: $(BIN) $(SOURCE) $(F90SOURCE) $(HEADERS) \ symlinksdone $(REGEXDEP) \ $(LIB)/libcbf.a \ $(LIB)/libfcb.a \ $(LIB)/libimg.a \ $(BIN)/adscimg2cbf \ $(BIN)/cbf2adscimg \ $(BIN)/convert_image \ $(BIN)/convert_minicbf \ $(BIN)/sequence_match \ $(BIN)/arvai_test \ $(BIN)/makecbf \ $(BIN)/img2cif \ $(BIN)/adscimg2cbf \ $(BIN)/cif2cbf \ $(BIN)/testcell \ $(BIN)/cif2c \ $(BIN)/testreals \ $(BIN)/testflat \ $(BIN)/testflatpacked ifneq ($(F90C),) all:: $(BIN)/test_xds_binary \ $(BIN)/test_fcb_read_image endif shared: $(SOLIB)/libcbf.so $(SOLIB)/libfcb.so $(SOLIB)/libimg.so javawrapper: shared $(JCBF) $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf_wrap.so ifneq ($(CBFLIB_USE_PYCIFRW),) PYCIFRWDEF = -Dcbf_use_pycifrw=yes else PYCIFRWDEF = endif Makefiles: Makefile \ Makefile_LINUX \ Makefile_LINUX_64 \ Makefile_LINUX_gcc42 \ Makefile_LINUX_DMALLOC \ Makefile_LINUX_gcc42_DMALLOC \ Makefile_OSX \ Makefile_OSX_gcc42 \ Makefile_OSX_gcc42_DMALLOC \ Makefile_AIX \ Makefile_MINGW \ Makefile_IRIX_gcc Makefile_LINUX: $(M4)/Makefile.m4 -cp Makefile_LINUX Makefile_LINUX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX $(M4)/Makefile.m4 > Makefile_LINUX Makefile_LINUX_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_LINUX Makefile_LINUX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_DMALLOC $(M4)/Makefile.m4 > Makefile_LINUX_DMALLOC Makefile_LINUX_64: $(M4)/Makefile.m4 -cp Makefile_LINUX_64 Makefile_LINUX_64_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_64 $(M4)/Makefile.m4 > Makefile_LINUX_64 Makefile_LINUX_gcc42: $(M4)/Makefile.m4 -cp Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_gcc42 $(M4)/Makefile.m4 > Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_gcc42_DMALLOC $(M4)/Makefile.m4 > Makefile_LINUX_gcc42_DMALLOC Makefile_OSX: $(M4)/Makefile.m4 -cp Makefile_OSX Makefile_OSX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX $(M4)/Makefile.m4 > Makefile_OSX Makefile_OSX_gcc42: $(M4)/Makefile.m4 -cp Makefile_OSX_gcc42 Makefile_OSX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX_gcc42 $(M4)/Makefile.m4 > Makefile_OSX_gcc42 Makefile_OSX_gcc42_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_OSX_gcc42 Makefile_OSX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX_gcc42_DMALLOC $(M4)/Makefile.m4 > Makefile_OSX_gcc42_DMALLOC Makefile_AIX: $(M4)/Makefile.m4 -cp Makefile_AIX Makefile_AIX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=AIX $(M4)/Makefile.m4 > Makefile_AIX Makefile_MINGW: $(M4)/Makefile.m4 -cp Makefile_MINGW Makefile_MINGW_old m4 -P $(PYCIFRWDEF) -Dcbf_system=MINGW $(M4)/Makefile.m4 > Makefile_MINGW Makefile_IRIX_gcc: $(M4)/Makefile.m4 -cp Makefile_IRIX_gcc Makefile_IRIX_gcc_old m4 -P $(PYCIFREDEF) -Dcbf_system=IRIX_gcc $(M4)/Makefile.m4 > Makefile_IRIX_gcc Makefile: $(M4)/Makefile.m4 -cp Makefile Makefile_old m4 -P $(PYCIFRWDEF) -Dcbf_system=default $(M4)/Makefile.m4 > Makefile symlinksdone: chmod a+x .symlinks chmod a+x .undosymlinks chmod a+x doc/.symlinks chmod a+x doc/.undosymlinks chmod a+x libtool/.symlinks chmod a+x libtool/.undosymlinks ./.symlinks $(SLFLAGS) touch symlinksdone install: all $(INSTALLDIR) $(INSTALLDIR)/lib $(INSTALLDIR)/bin \ $(INSTALLDIR)/include $(INSTALLDIR)/include/cbflib \ $(PYSOURCE) -chmod -R 755 $(INSTALLDIR)/include/cbflib -chmod 755 $(INSTALLDIR)/lib/libcbf.a -cp $(INSTALLDIR)/lib/libcbf.a $(INSTALLDIR)/lib/libcbf_old.a cp $(LIB)/libcbf.a $(INSTALLDIR)/lib/libcbf.a -cp $(INSTALLDIR)/lib/libimg.a $(INSTALLDIR)/lib/libimg_old.a cp $(LIB)/libimg.a $(INSTALLDIR)/lib/libimg.a -cp $(INSTALLDIR)/bin/adscimg2cbf $(INSTALLDIR)/bin/adscimg2cbf_old cp $(BIN)/adscimg2cbf $(INSTALLDIR)/bin/adscimg2cbf -cp $(INSTALLDIR)/bin/cbf2adscimg $(INSTALLDIR)/bin/cbf2adscimg_old cp $(BIN)/cbf2adscimg $(INSTALLDIR)/bin/cbf2adscimg -cp $(INSTALLDIR)/bin/convert_image $(INSTALLDIR)/bin/convert_image_old cp $(BIN)/convert_image $(INSTALLDIR)/bin/convert_image -cp $(INSTALLDIR)/bin/convert_minicbf $(INSTALLDIR)/bin/convert_minicbf_old cp $(BIN)/convert_minicbf $(INSTALLDIR)/bin/convert_minicbf -cp $(INSTALLDIR)/bin/makecbf $(INSTALLDIR)/bin/makecbf_old cp $(BIN)/makecbf $(INSTALLDIR)/bin/makecbf -cp $(INSTALLDIR)/bin/img2cif $(INSTALLDIR)/bin/img2cif_old cp $(BIN)/img2cif $(INSTALLDIR)/bin/img2cif -cp $(INSTALLDIR)/bin/cif2cbf $(INSTALLDIR)/bin/cif2cbf_old cp $(BIN)/cif2cbf $(INSTALLDIR)/bin/cif2cbf -cp $(INSTALLDIR)/bin/sequence_match $(INSTALLDIR)/bin/sequence_match_old cp $(BIN)/sequence_match $(INSTALLDIR)/bin/sequence_match -cp $(INSTALLDIR)/bin/arvai_test $(INSTALLDIR)/bin/arvai_test_old cp $(BIN)/arvai_test $(INSTALLDIR)/bin/arvai_test -cp $(INSTALLDIR)/bin/cif2c $(INSTALLDIR)/bin/cif2c_old cp $(BIN)/cif2c $(INSTALLDIR)/bin/cif2c -cp $(INSTALLDIR)/bin/testreals $(INSTALLDIR)/bin/testreals_old cp $(BIN)/testreals $(INSTALLDIR)/bin/testreals -cp $(INSTALLDIR)/bin/testflat $(INSTALLDIR)/bin/testflat_old cp $(BIN)/testflat $(INSTALLDIR)/bin/testflat -cp $(INSTALLDIR)/bin/testflatpacked $(INSTALLDIR)/bin/testflatpacked_old cp $(BIN)/testflatpacked $(INSTALLDIR)/bin/testflatpacked chmod -R 755 $(INSTALLDIR)/include/cbflib -rm -rf $(INSTALLDIR)/include/cbflib_old -cp -r $(INSTALLDIR)/include/cbflib $(INSTALLDIR)/include/cbflib_old -rm -rf $(INSTALLDIR)/include/cbflib cp -r $(INCLUDE) $(INSTALLDIR)/include/cbflib chmod 644 $(INSTALLDIR)/lib/libcbf.a chmod 755 $(INSTALLDIR)/bin/convert_image chmod 755 $(INSTALLDIR)/bin/convert_minicbf chmod 755 $(INSTALLDIR)/bin/makecbf chmod 755 $(INSTALLDIR)/bin/img2cif chmod 755 $(INSTALLDIR)/bin/cif2cbf chmod 755 $(INSTALLDIR)/bin/sequence_match chmod 755 $(INSTALLDIR)/bin/arvai_test chmod 755 $(INSTALLDIR)/bin/cif2c chmod 755 $(INSTALLDIR)/bin/testreals chmod 755 $(INSTALLDIR)/bin/testflat chmod 755 $(INSTALLDIR)/bin/testflatpacked chmod 644 $(INSTALLDIR)/include/cbflib/*.h # # REGEX # ifneq ($(REGEXDEP),) $(REGEXDEP): $(REGEX) (cd $(REGEX); ./configure; make install) endif $(REGEX): $(DOWNLOAD) $(REGEXURL) tar -xvf $(REGEX).tar.gz -rm $(REGEX).tar.gz # # TIFF # $(TIFF): $(DOWNLOAD) $(TIFFURL) tar -xvf $(TIFF).tar.gz -rm $(TIFF).tar.gz (cd $(TIFF); ./configure --prefix=$(TIFFPREFIX); make install) # # Directories # $(INSTALLDIR): mkdir -p $(INSTALLDIR) $(INSTALLDIR)/lib: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/lib $(INSTALLDIR)/bin: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/bin $(INSTALLDIR)/include: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/include $(INSTALLDIR)/include/cbflib: $(INSTALLDIR)/include mkdir -p $(INSTALLDIR)/include/cbflib $(LIB): mkdir $@ $(BIN): mkdir $@ $(SOLIB): mkdir $@ $(JCBF): mkdir $@ # # Parser # $(SRC)/cbf_stx.c: $(SRC)/cbf.stx.y bison $(SRC)/cbf.stx.y -o $(SRC)/cbf.stx.tab.c -d mv $(SRC)/cbf.stx.tab.c $(SRC)/cbf_stx.c mv $(SRC)/cbf.stx.tab.h $(INCLUDE)/cbf_stx.h # # CBF library # $(LIB)/libcbf.a: $(SOURCE) $(HEADERS) $(COMMONDEP) $(LIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG) $(INCLUDES) $(WARNINGS) -c $(SOURCE) $(AR) cr $@ *.o mv *.o $(LIB) ifneq ($(RANLIB),) $(RANLIB) $@ endif $(SOLIB)/libcbf.so: $(SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(SOURCE) $(CC) -o $@ *.o $(SOLDFLAGS) $(EXTRALIBS) rm *.o # # IMG library # $(LIB)/libimg.a: $(EXAMPLES)/img.c $(HEADERS) $(COMMONDEP) $(LIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) -c $(EXAMPLES)/img.c $(AR) cr $@ img.o ifneq ($(RANLIB),) $(RANLIB) $@ endif rm img.o $(SOLIB)/libimg.so: $(SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(EXAMPLES)/img.c $(CC) -o $@ img.o $(SOLDFLAGS) rm img.o # # CBF and IMG libraries # CBF_IMG_LIBS: $(LIB)/libcbf.a $(LIB)/libimg.a # # FCB library # $(LIB)/libfcb.a: $(F90SOURCE) $(COMMONDEP) $(LIB) ifneq ($(F90C),) $(F90C) $(F90FLAGS) -c $(F90SOURCE) $(AR) cr $@ *.o ifneq ($(RANLIB),) $(RANLIB) $@ endif rm *.o else echo "Define F90C to build $(LIB)/libfcb.a" endif $(SOLIB)/libfcb.so: $(F90SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) ifneq ($(F90C),) $(F90C) $(F90FLAGS) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(F90SOURCE) $(F90C) $(F90FLAGS) -o $@ *.o $(SOLDFLAGS) rm *.o else echo "Define F90C to build $(SOLIB)/libfcb.so" endif # # Python bindings # $(PYCBF)/_pycbf.$(PYCBFEXT): $(PYCBF) $(LIB)/libcbf.a \ $(PYCBF)/$(SETUP_PY) \ $(LIB)/libfcb.a \ $(LIB)/libimg.a \ $(PYCBF)/pycbf.i \ $(PYCBF)/cbfhandlewrappers.i \ $(PYCBF)/cbfdetectorwrappers.i \ $(PYCBF)/cbfgenericwrappers.i \ $(PYCBF)/cbfgoniometerwrappers.i (cd $(PYCBF); python $(SETUP_PY) build $(PYCBFBOPT); cp build/lib.*/_pycbf.$(PYCBFEXT) .) $(PYCBF)/setup.py: $(M4)/setup_py.m4 (m4 -P -Dregexlib=NOREGEXLIB -Dregexlibdir=NOREGEXLIBDIR $(M4)/setup_py.m4 > $@) $(PYCBF)/setup_MINGW.py: m4/setup_py.m4 (m4 -P -Dregexlib=regex -Dregexlibdir=$(REGEXDIR) $(M4)/setup_py.m4 > $@) $(LIB)/_pycbf.$(PYCBFEXT): $(PYCBF)/_pycbf.$(PYCBFEXT) cp $(PYCBF)/_pycbf.$(PYCBFEXT) $(LIB)/_pycbf.$(PYCBFEXT) $(PYCBF)/pycbf.pdf: $(PYCBF)/pycbf.w (cd $(PYCBF); \ $(NUWEB) pycbf; \ latex pycbf; \ $(NUWEB) pycbf; \ latex pycbf; \ dvipdfm pycbf ) $(PYCBF)/CBFlib.txt: $(DOC)/CBFlib.html links -dump $(DOC)/CBFlib.html > $(PYCBF)/CBFlib.txt $(PYCBF)/cbfhandlewrappers.i \ $(PYCBF)/cbfdetectorwrappers.i \ $(PYCBF)/cbfgenericwrappers.i \ $(PYCBF)/cbfgoniometerwrappers.i: $(PYCBF)/CBFlib.txt $(PYCBF)/make_pycbf.py (cd $(PYCBF); python make_pycbf.py; $(PYSWIG) pycbf.i; python setup.py build) # # Java bindings # $(JCBF)/cbflib-$(VERSION).jar: $(JCBF) $(JCBF)/jcbf.i $(JSWIG) -I$(INCLUDE) -package org.iucr.cbflib -outdir $(JCBF) $(JCBF)/jcbf.i $(JAVAC) -d . $(JCBF)/*.java $(JAR) cf $@ org $(SOLIB)/libcbf_wrap.so: $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf.so $(CC) $(CFLAGS) $(NOLLFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) $(JAVAINCLUDES) -c $(JCBF)/jcbf_wrap.c $(CC) -o $@ jcbf_wrap.o $(SOLDFLAGS) -L$(SOLIB) -lcbf rm jcbf_wrap.o # # F90SOURCE # $(SRC)/fcb_exit_binary.f90: $(M4)/fcb_exit_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_exit_binary.m4) > $(SRC)/fcb_exit_binary.f90 $(SRC)/fcb_next_binary.f90: $(M4)/fcb_next_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_next_binary.m4) > $(SRC)/fcb_next_binary.f90 $(SRC)/fcb_open_cifin.f90: $(M4)/fcb_open_cifin.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_open_cifin.m4) > $(SRC)/fcb_open_cifin.f90 $(SRC)/fcb_packed.f90: $(M4)/fcb_packed.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_packed.m4) > $(SRC)/fcb_packed.f90 $(SRC)/fcb_read_bits.f90: $(M4)/fcb_read_bits.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_bits.m4) > $(SRC)/fcb_read_bits.f90 $(SRC)/fcb_read_image.f90: $(M4)/fcb_read_image.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_image.m4) > $(SRC)/fcb_read_image.f90 $(SRC)/fcb_read_xds_i2.f90: $(M4)/fcb_read_xds_i2.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_xds_i2.m4) > $(SRC)/fcb_read_xds_i2.f90 $(EXAMPLES)/test_fcb_read_image.f90: $(M4)/test_fcb_read_image.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) test_fcb_read_image.m4) > $(EXAMPLES)/test_fcb_read_image.f90 $(EXAMPLES)/test_xds_binary.f90: $(M4)/test_xds_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) test_xds_binary.m4) > $(EXAMPLES)/test_xds_binary.f90 # # convert_image example program # $(BIN)/convert_image: $(LIB)/libcbf.a $(EXAMPLES)/convert_image.c $(EXAMPLES)/img.c \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/convert_image.c $(EXAMPLES)/img.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # convert_minicbf example program # $(BIN)/convert_minicbf: $(LIB)/libcbf.a $(EXAMPLES)/convert_minicbf.c \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/convert_minicbf.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # makecbf example program # $(BIN)/makecbf: $(LIB)/libcbf.a $(EXAMPLES)/makecbf.c $(LIB)/libimg.a $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/makecbf.c -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # adscimg2cbf example program # $(BIN)/adscimg2cbf: $(LIB)/libcbf.a $(EXAMPLES)/adscimg2cbf.c $(EXAMPLES)/adscimg2cbf_sub.c $(CC) $(CFLAGS) $(NOLLFLAG) -D_SVID_SOURCE $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/adscimg2cbf.c $(EXAMPLES)/adscimg2cbf_sub.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # cbf2adscimg example program # $(BIN)/cbf2adscimg: $(LIB)/libcbf.a $(EXAMPLES)/cbf2adscimg.c $(EXAMPLES)/cbf2adscimg_sub.c $(CC) $(CFLAGS) $(NOLLFLAG) -D_SVID_SOURCE $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cbf2adscimg.c $(EXAMPLES)/cbf2adscimg_sub.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # changtestcompression example program # $(BIN)/changtestcompression: $(LIB)/libcbf.a $(EXAMPLES)/changtestcompression.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/changtestcompression.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # img2cif example program # $(BIN)/img2cif: $(LIB)/libcbf.a $(EXAMPLES)/img2cif.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOTPINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/img2cif.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # cif2cbf example program # $(BIN)/cif2cbf: $(LIB)/libcbf.a $(EXAMPLES)/cif2cbf.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cif2cbf.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # dectris cbf_template_t program # $(BIN)/cbf_template_t: $(DECTRIS_EXAMPLES)/cbf_template_t.c \ $(DECTRIS_EXAMPLES)/mx_cbf_t_extras.h \ $(DECTRIS_EXAMPLES)/mx_parms.h $(CC) $(CFLAGS) $(NOLLFLAG) -I $(DECTRIS_EXAMPLES) $(WARNINGS) \ $(DECTRIS_EXAMPLES)/cbf_template_t.c -o $@ # # testcell example program # $(BIN)/testcell: $(LIB)/libcbf.a $(EXAMPLES)/testcell.C $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testcell.C -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # cif2c example program # $(BIN)/cif2c: $(LIB)/libcbf.a $(EXAMPLES)/cif2c.c $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cif2c.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # sauter_test example program # $(BIN)/sauter_test: $(LIB)/libcbf.a $(EXAMPLES)/sauter_test.C $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/sauter_test.C -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # sequence_match example program # $(BIN)/sequence_match: $(LIB)/libcbf.a $(EXAMPLES)/sequence_match.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/sequence_match.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # tiff2cbf example program # $(BIN)/tiff2cbf: $(LIB)/libcbf.a $(EXAMPLES)/tiff2cbf.c \ $(GOPTLIB) $(GOPTINC) $(TIFF) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ -I$(TIFFPREFIX)/include $(EXAMPLES)/tiff2cbf.c $(GOPTLIB) -L$(LIB) \ -lcbf -L$(TIFFPREFIX)/lib -ltiff $(EXTRALIBS) -limg -o $@ # # Andy Arvai's buffered read test program # $(BIN)/arvai_test: $(LIB)/libcbf.a $(EXAMPLES)/arvai_test.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/arvai_test.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # testreals example program # $(BIN)/testreals: $(LIB)/libcbf.a $(EXAMPLES)/testreals.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testreals.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testflat example program # $(BIN)/testflat: $(LIB)/libcbf.a $(EXAMPLES)/testflat.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testflat.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testflatpacked example program # $(BIN)/testflatpacked: $(LIB)/libcbf.a $(EXAMPLES)/testflatpacked.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testflatpacked.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ ifneq ($(F90C),) # # test_xds_binary example program # $(BIN)/test_xds_binary: $(LIB)/libfcb.a $(EXAMPLES)/test_xds_binary.f90 $(F90C) $(F90FLAGS) $(F90LDFLAGS) $(EXAMPLES)/test_xds_binary.f90 \ -L$(LIB) -lfcb -o $@ # # test_fcb_read_image example program # $(BIN)/test_fcb_read_image: $(LIB)/libfcb.a $(EXAMPLES)/test_fcb_read_image.f90 $(F90C) $(F90FLAGS) $(F90LDFLAGS) $(EXAMPLES)/test_fcb_read_image.f90 \ -L$(LIB) -lfcb -o $@ endif # # testcbf (C) # $(BIN)/ctestcbf: $(EXAMPLES)/testcbf.c $(LIB)/libcbf.a $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testcbf.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testcbf (Java) # $(BIN)/testcbf.class: $(EXAMPLES)/testcbf.java $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf_wrap.so $(JAVAC) -cp $(JCBF)/cbflib-$(VERSION).jar -d $(BIN) $(EXAMPLES)/testcbf.java # # Data files for tests # $(DATADIRI): (cd ..; $(DOWNLOAD) $(DATAURLI)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Input.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Input.tar.gz) $(DATADIRO): (cd ..; $(DOWNLOAD) $(DATAURLO)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Output.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Output.tar.gz) $(DATADIRS): (cd ..; $(DOWNLOAD) $(DATAURLS)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz) # Input Data Files TESTINPUT_BASIC = example.mar2300 DATADIRI_INPUT_BASIC = $(DATADIRI)/example.mar2300$(CEXT) TESTINPUT_EXTRA = 9ins.cif mb_LP_1_001.img insulin_pilatus6m.cbf testrealin.cbf \ testflatin.cbf testflatpackedin.cbf XRD1621.tif DATADIRI_INPUT_EXTRA = $(DATADIRI)/9ins.cif$(CEXT) $(DATADIRI)/mb_LP_1_001.img$(CEXT) \ $(DATADIRI)/insulin_pilatus6m.cbf$(CEXT) $(DATADIRI)/testrealin.cbf$(CEXT) \ $(DATADIRI)/testflatin.cbf$(CEXT) $(DATADIRI)/testflatpackedin.cbf$(CEXT) \ $(DATADIRI)/XRD1621.tif$(CEXT) # Output Data Files TESTOUTPUT = adscconverted_flat_orig.cbf \ adscconverted_orig.cbf converted_flat_orig.cbf converted_orig.cbf \ insulin_pilatus6mconverted_orig.cbf \ mb_LP_1_001_orig.cbf testcell_orig.prt \ test_xds_bin_testflatout_orig.out \ test_xds_bin_testflatpackedout_orig.out test_fcb_read_testflatout_orig.out \ test_fcb_read_testflatpackedout_orig.out \ XRD1621_orig.cbf XRD1621_I4encbC100_orig.cbf NEWTESTOUTPUT = adscconverted_flat.cbf \ adscconverted.cbf converted_flat.cbf converted.cbf \ insulin_pilatus6mconverted.cbf \ mb_LP_1_001.cbf testcell.prt \ test_xds_bin_testflatout.out \ test_xds_bin_testflatpackedout.out test_fcb_read_testflatout.out \ test_fcb_read_testflatpackedout.out \ XRD1621.cbf XRD1621_I4encbC100.cbf DATADIRO_OUTPUT = $(DATADIRO)/adscconverted_flat_orig.cbf$(CEXT) \ $(DATADIRO)/adscconverted_orig.cbf$(CEXT) \ $(DATADIRO)/converted_flat_orig.cbf$(CEXT) \ $(DATADIRO)/converted_orig.cbf$(CEXT) \ $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(CEXT) \ $(DATADIRO)/mb_LP_1_001_orig.cbf$(CEXT) \ $(DATADIRO)/testcell_orig.prt$(CEXT) \ $(DATADIRO)/test_xds_bin_testflatout_orig.out$(CEXT) \ $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(CEXT) \ $(DATADIRO)/test_fcb_read_testflatout_orig.out$(CEXT) \ $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(CEXT) \ $(DATADIRO)/XRD1621_orig.cbf$(CEXT) \ $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(CEXT) DATADIRO_OUTPUT_SIGNATURES = $(DATADIRO)/adscconverted_flat_orig.cbf$(SEXT) \ $(DATADIRO)/adscconverted_orig.cbf$(SEXT) \ $(DATADIRO)/converted_flat_orig.cbf$(SEXT) \ $(DATADIRO)/converted_orig.cbf$(SEXT) \ $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(SEXT) \ $(DATADIRO)/mb_LP_1_001_orig.cbf$(SEXT) \ $(DATADIRO)/testcell_orig.prt$(SEXT) \ $(DATADIRO)/test_xds_bin_testflatout_orig.out$(SEXT) \ $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(SEXT) \ $(DATADIRO)/test_fcb_read_testflatout_orig.out$(SEXT) \ $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(SEXT) \ $(DATADIRO)/XRD1621_orig.cbf$(SEXT) \ $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(SEXT) # Output Data File Signatures TESTOUTPUTSIGS = adscconverted_flat_orig.cbf$(SEXT) \ adscconverted_orig.cbf$(SEXT) converted_flat_orig.cbf$(SEXT) converted_orig.cbf$(SEXT) \ insulin_pilatus6mconverted_orig.cbf$(SEXT) \ mb_LP_1_001_orig.cbf$(SEXT) testcell_orig.prt$(SEXT) \ test_xds_bin_testflatout_orig.out$(SEXT) \ test_xds_bin_testflatpackedout_orig.out$(SEXT) test_fcb_read_testflatout_orig.out$(SEXT) \ test_fcb_read_testflatpackedout_orig.out$(SEXT) \ XRD1621_orig.cbf$(SEXT) DATADIRS_OUTPUT_SIGNATURES = $(DATADIRS)/adscconverted_flat_orig.cbf$(SEXT) \ $(DATADIRS)/adscconverted_orig.cbf$(SEXT) \ $(DATADIRS)/converted_flat_orig.cbf$(SEXT) \ $(DATADIRS)/converted_orig.cbf$(SEXT) \ $(DATADIRS)/insulin_pilatus6mconverted_orig.cbf$(SEXT) \ $(DATADIRS)/mb_LP_1_001_orig.cbf$(SEXT) \ $(DATADIRS)/testcell_orig.prt$(SEXT) \ $(DATADIRS)/test_xds_bin_testflatout_orig.out$(SEXT) \ $(DATADIRS)/test_xds_bin_testflatpackedout_orig.out$(SEXT) \ $(DATADIRS)/test_fcb_read_testflatout_orig.out$(SEXT) \ $(DATADIRS)/test_fcb_read_testflatpackedout_orig.out$(SEXT) \ $(DATADIRS)/XRD1621_orig.cbf$(SEXT) \ $(DATADIRS)/XRD1621_I4encbC100_orig.cbf$(SEXT) # Fetch Input Data Files $(TESTINPUT_BASIC): $(DATADIRI) $(DATADIRI_INPUT_BASIC) $(DECOMPRESS) < $(DATADIRI)/$@$(CEXT) > $@ cp $(DATADIRI)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) $(TESTINPUT_EXTRA): $(DATADIRI) $(DATADIRI_INPUT_EXTRA) $(DECOMPRESS) < $(DATADIRI)/$@$(CEXT) > $@ cp $(DATADIRI)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) # Fetch Output Data Files and Signatures $(TESTOUTPUT): $(DATADIRO) $(DATADIRO_OUTPUT) $(DATADIRO_OUTPUT_SIGNATURES) $(DECOMPRESS) < $(DATADIRO)/$@$(CEXT) > $@ cp $(DATADIRO)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) # Fetch Output Data File Signatures $(TESTOUTPUTSIGS): $(DATADIRS) $(DATADIRS_OUTPUT_SIGNATURES) cp $(DATADIRS)/$@ $@ # # Tests # tests: $(LIB) $(BIN) symlinksdone basic extra dectristests pycbftests tests_sigs_only: $(LIB) $(BIN) symlinksdone basic extra_sigs_only restore_output: $(NEWTESTOUTPUT) $(DATADIRO) $(SIGNATURE) < adscconverted_flat.cbf > $(DATADIRO)/adscconverted_flat_orig.cbf$(SEXT) $(SIGNATURE) < adscconverted.cbf > $(DATADIRO)/adscconverted_orig.cbf$(SEXT) $(SIGNATURE) < converted_flat.cbf > $(DATADIRO)/converted_flat_orig.cbf$(SEXT) $(SIGNATURE) < converted.cbf > $(DATADIRO)/converted_orig.cbf$(SEXT) $(SIGNATURE) < insulin_pilatus6mconverted.cbf > $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(SEXT) $(SIGNATURE) < mb_LP_1_001.cbf$ > $(DATADIRO)/mb_LP_1_001_orig.cbf$(SEXT) $(SIGNATURE) < testcell.prt > $(DATADIRO)/testcell_orig.prt$(SEXT) $(SIGNATURE) < test_xds_bin_testflatout.out > $(DATADIRO)/test_xds_bin_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_xds_bin_testflatpackedout.out > $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatout.out > $(DATADIRO)/test_fcb_read_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatpackedout.out > $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < XRD1621.cbf > $(DATADIRO)/XRD1621_orig.cbf$(SEXT) $(SIGNATURE) < XRD1621_I4encbC100.cbf > $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(SEXT) $(COMPRESS) < adscconverted_flat.cbf > $(DATADIRO)/adscconverted_flat_orig.cbf$(CEXT) $(COMPRESS) < adscconverted.cbf > $(DATADIRO)/adscconverted_orig.cbf$(CEXT) $(COMPRESS) < converted_flat.cbf > $(DATADIRO)/converted_flat_orig.cbf$(CEXT) $(COMPRESS) < converted.cbf > $(DATADIRO)/converted_orig.cbf$(CEXT) $(COMPRESS) < insulin_pilatus6mconverted.cbf > $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(CEXT) $(COMPRESS) < mb_LP_1_001.cbf$ > $(DATADIRO)/mb_LP_1_001_orig.cbf$(CEXT) $(COMPRESS) < testcell.prt > $(DATADIRO)/testcell_orig.prt$(CEXT) $(COMPRESS) < test_xds_bin_testflatout.out > $(DATADIRO)/test_xds_bin_testflatout_orig.out$(CEXT) $(COMPRESS) < test_xds_bin_testflatpackedout.out > $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(CEXT) $(COMPRESS) < test_fcb_read_testflatout.out > $(DATADIRO)/test_fcb_read_testflatout_orig.out$(CEXT) $(COMPRESS) < test_fcb_read_testflatpackedout.out > $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(CEXT) $(COMPRESS) < XRD1621.cbf > $(DATADIRO)/XRD1621_orig.cbf$(CEXT) $(COMPRESS) < XRD1621_I4encbC100.cbf > $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(CEXT) restore_sigs_only: $(NEWTESTOUTPUT) $(DATADIRS) $(SIGNATURE) < adscconverted_flat.cbf > $(DATADIRS)/adscconverted_flat_orig.cbf$(SEXT) $(SIGNATURE) < adscconverted.cbf > $(DATADIRS)/adscconverted_orig.cbf$(SEXT) $(SIGNATURE) < converted_flat.cbf > $(DATADIRS)/converted_flat_orig.cbf$(SEXT) $(SIGNATURE) < converted.cbf > $(DATADIRS)/converted_orig.cbf$(SEXT) $(SIGNATURE) < insulin_pilatus6mconverted.cbf > $(DATADIRS)/insulin_pilatus6mconverted_orig.cbf$(SEXT) $(SIGNATURE) < mb_LP_1_001.cbf$ > $(DATADIRS)/mb_LP_1_001_orig.cbf$(SEXT) $(SIGNATURE) < testcell.prt > $(DATADIRS)/testcell_orig.prt$(SEXT) $(SIGNATURE) < test_xds_bin_testflatout.out > $(DATADIRS)/test_xds_bin_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_xds_bin_testflatpackedout.out > $(DATADIRS)/test_xds_bin_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatout.out > $(DATADIRS)/test_fcb_read_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatpackedout.out > $(DATADIRS)/test_fcb_read_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < XRD1621.cbf > $(DATADIRS)/XRD1621_orig.cbf$(SEXT) $(SIGNATURE) < XRD1621_I4encbC100.cbf > $(DATADIRS)/XRD1621_I4encbC100_orig.cbf$(SEXT) restore_signatures: restore_output restore_sigs_only # # Basic Tests # basic: $(BIN)/makecbf $(BIN)/img2cif $(BIN)/cif2cbf $(TESTINPUT_BASIC) $(BIN)/makecbf example.mar2300 makecbf.cbf $(BIN)/img2cif -c flatpacked -m headers -d digest \ -e base64 example.mar2300 img2cif_packed.cif $(BIN)/img2cif -c canonical -m headers -d digest \ -e base64 example.mar2300 img2cif_canonical.cif $(BIN)/img2cif -c flatpacked -m headers -d digest \ -e none example.mar2300 img2cif_packed.cbf $(BIN)/img2cif -c canonical -m headers -d digest \ -e none example.mar2300 img2cif_canonical.cbf $(BIN)/cif2cbf -e none -c flatpacked \ img2cif_canonical.cif cif2cbf_packed.cbf $(BIN)/cif2cbf -e none -c canonical \ img2cif_packed.cif cif2cbf_canonical.cbf -cmp cif2cbf_packed.cbf makecbf.cbf -cmp cif2cbf_packed.cbf img2cif_packed.cbf -cmp cif2cbf_canonical.cbf img2cif_canonical.cbf # # Extra Tests # ifneq ($(F90C),) extra: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/test_xds_binary $(BIN)/test_fcb_read_image $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg \ $(BIN)/changtestcompression $(BIN)/tiff2cbf \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUT) else extra: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUT) endif $(TIME) $(BIN)/cif2cbf -e hex -c none \ makecbf.cbf cif2cbf_ehcn.cif $(TIME) $(BIN)/cif2cbf -e none -c flatpacked \ cif2cbf_ehcn.cif cif2cbf_encp.cbf; rm cif2cbf_ehcn.cif -cmp makecbf.cbf cif2cbf_encp.cbf $(TIME) $(BIN)/cif2cbf -i 9ins.cif -o 9ins.cbf -cmp 9ins.cif 9ins.cbf $(TIME) $(BIN)/convert_image -F example.mar2300 converted_flat.cbf -cmp converted_flat.cbf converted_flat_orig.cbf $(TIME) $(BIN)/convert_image example.mar2300 converted.cbf -cmp converted.cbf converted_orig.cbf -$(TIME) $(BIN)/testcell < testcell.dat > testcell.prt -cmp testcell.prt testcell_orig.prt $(TIME) $(BIN)/convert_image -F -d adscquantum315 mb_LP_1_001.img adscconverted_flat.cbf -cmp adscconverted_flat.cbf adscconverted_flat_orig.cbf $(TIME) $(BIN)/convert_image -d adscquantum315 mb_LP_1_001.img adscconverted.cbf -cmp adscconverted.cbf adscconverted_orig.cbf $(TIME) $(BIN)/adscimg2cbf --no_pad --cbf_packed,flat mb_LP_1_001.img -cmp mb_LP_1_001.cbf mb_LP_1_001_orig.cbf ifneq ($(CLEANTESTS),) mv mb_LP_1_001.cbf nmb_LP_1_001.cbf else cp mb_LP_1_001.cbf nmb_LP_1_001.cbf endif $(TIME) $(BIN)/cbf2adscimg nmb_LP_1_001.cbf -cmp nmb_LP_1_001.img mb_LP_1_001.img rm nmb_LP_1_001.cbf ifneq ($(CLEANTESTS),) rm nmb_LP_1_001.img endif $(TIME) $(BIN)/convert_minicbf -d pilatus6m insulin_pilatus6m.cbf insulin_pilatus6mconverted.cbf -cmp insulin_pilatus6mconverted.cbf insulin_pilatus6mconverted_orig.cbf $(TIME) $(BIN)/testreals -cmp testrealin.cbf testrealout.cbf $(TIME) $(BIN)/testflat -cmp testflatin.cbf testflatout.cbf $(TIME) $(BIN)/testflatpacked -cmp testflatpackedin.cbf testflatpackedout.cbf ifneq ($(F90C),) echo testflatout.cbf | $(TIME) $(BIN)/test_xds_binary > test_xds_bin_testflatout.out -$(DIFF) test_xds_bin_testflatout.out test_xds_bin_testflatout_orig.out echo testflatpackedout.cbf | $(TIME) $(BIN)/test_xds_binary > test_xds_bin_testflatpackedout.out -$(DIFF) test_xds_bin_testflatpackedout.out test_xds_bin_testflatpackedout_orig.out echo testflatout.cbf | $(TIME) $(BIN)/test_fcb_read_image > test_fcb_read_testflatout.out -$(DIFF) test_fcb_read_testflatout.out test_fcb_read_testflatout_orig.out echo testflatpackedout.cbf | $(TIME) $(BIN)/test_fcb_read_image > test_fcb_read_testflatpackedout.out -$(DIFF) test_fcb_read_testflatpackedout.out test_fcb_read_testflatpackedout_orig.out endif $(TIME) $(BIN)/sauter_test $(TIME) $(BIN)/changtestcompression $(TIME) (export LD_LIBRARY_PATH=$(LIB);$(BIN)/tiff2cbf XRD1621.tif XRD1621.cbf) -$(DIFF) XRD1621.cbf XRD1621_orig.cbf $(TIME) $(BIN)/cif2cbf -I 4 -C 100. -L 0. -e n -c b -i XRD1621.cbf -o XRD1621_I4encbC100.cbf -$(DIFF) XRD1621_I4encbC100.cbf XRD1621_I4encbC100_orig.cbf ifneq ($(F90C),) extra_sigs_only: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/test_xds_binary $(BIN)/test_fcb_read_image $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg $(BIN)/tiff2cbf \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) else extra_sigs_only: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf\ basic $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) endif $(TIME) $(BIN)/cif2cbf -e hex -c none \ makecbf.cbf cif2cbf_ehcn.cif $(TIME) $(BIN)/cif2cbf -e none -c packed \ cif2cbf_ehcn.cif cif2cbf_encp.cbf; rm cif2cbf_ehcn.cif -cmp makecbf.cbf cif2cbf_encp.cbf $(TIME) $(BIN)/cif2cbf -i 9ins.cif -o 9ins.cbf -cmp 9ins.cif 9ins.cbf $(TIME) $(BIN)/convert_image -F example.mar2300 converted_flat.cbf -$(SIGNATURE) < converted_flat.cbf | $(DIFF) - converted_flat_orig.cbf$(SEXT); rm converted_flat.cbf $(TIME) $(BIN)/convert_image example.mar2300 converted.cbf -$(SIGNATURE) < converted.cbf | $(DIFF) - converted_orig.cbf$(SEXT); rm converted.cbf -$(TIME) $(BIN)/testcell < testcell.dat | \ $(SIGNATURE) | $(DIFF) - testcell_orig.prt$(SEXT) $(TIME) $(BIN)/convert_image -F -d adscquantum315 mb_LP_1_001.img adscconverted_flat.cbf -$(SIGNATURE) < adscconverted_flat.cbf | $(DIFF) - adscconverted_flat_orig.cbf$(SEXT) $(TIME) $(BIN)/convert_image -d adscquantum315 mb_LP_1_001.img adscconverted.cbf -$(SIGNATURE) < adscconverted.cbf | $(DIFF) - adscconverted_orig.cbf$(SEXT); rm adscconverted.cbf $(TIME) $(BIN)/adscimg2cbf --cbf_packed,flat mb_LP_1_001.img -$(SIGNATURE) < mb_LP_1_001.cbf | $(DIFF) - mb_LP_1_001_orig.cbf$(SEXT) mv mb_LP_1_001.cbf nmb_LP_1_001.cbf $(TIME) $(BIN)/cbf2adscimg nmb_LP_1_001.cbf -cmp nmb_LP_1_001.img mb_LP_1_001.img rm nmb_LP_1_001.cbf rm nmb_LP_1_001.img $(TIME) $(BIN)/convert_minicbf -d pilatus6m insulin_pilatus6m.cbf insulin_pilatus6mconverted.cbf -$(SIGNATURE) < insulin_pilatus6mconverted.cbf | $(DIFF) - insulin_pilatus6mconverted_orig.cbf$(SEXT); rm insulin_pilatus6mconverted.cbf $(TIME) $(BIN)/testreals -cmp testrealin.cbf testrealout.cbf $(TIME) $(BIN)/testflat -cmp testflatin.cbf testflatout.cbf $(TIME) $(BIN)/testflatpacked -cmp testflatpackedin.cbf testflatpackedout.cbf ifneq ($(F90C),) echo testflatout.cbf | $(TIME) $(BIN)/test_xds_binary | \ $(SIGNATURE) | $(DIFF) - test_xds_bin_testflatout_orig.out$(SEXT) echo testflatpackedout.cbf | $(TIME) $(BIN)/test_xds_binary | \ $(SIGNATURE) | $(DIFF) - test_xds_bin_testflatpackedout_orig.out$(SEXT) echo testflatout.cbf | $(TIME) $(BIN)/test_fcb_read_image | \ $(SIGNATURE) | $(DIFF) - test_fcb_read_testflatout_orig.out$(SEXT) echo testflatpackedout.cbf | $(TIME) $(BIN)/test_fcb_read_image | \ $(SIGNATURE) | $(DIFF) - test_fcb_read_testflatpackedout_orig.out$(SEXT) endif $(TIME) $(BIN)/sauter_test $(TIME) $(BIN)/tiff2cbf XRD1621.tif XRD1621.cbf $(TIME) $(BIN)/cif2cbf -I 4 -C 100. -L 0. -e n -c b -i XRD1621.cbf -o XRD1621_I4encbC100.cbf -$(SIGNATURE) < XRD1621.cbf | $(DIFF) - XRD1621_orig.cbf$(SEXT); rm XRD1621.cbf -$(SIGNATURE) < XRD1621_I4encbC100.cbf | $(DIFF) - XRD1621_I4encbC100_orig.cbf$(SEXT); rm XRD1621_I4encbC100.cbf @-rm -f adscconverted_flat.cbf @-rm -f $(TESTINPUT_BASIC) $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) @-rm -f cif2cbf_packed.cbf makecbf.cbf \ cif2cbf_packed.cbf img2cif_packed.cbf \ cif2cbf_canonical.cbf img2cif_canonical.cbf @-rm -f testrealout.cbf testflatout.cbf testflatpackedout.cbf \ cif2cbf_encp.cbf img2cif_canonical.cif img2cif_packed.cif 9ins.cbf pycbftests: $(PYCBF)/_pycbf.$(PYCBFEXT) (cd $(PYCBF); python pycbf_test1.py) (cd $(PYCBF); python pycbf_test2.py) (cd $(PYCBF); python pycbf_test3.py) javatests: $(BIN)/ctestcbf $(BIN)/testcbf.class $(SOLIB)/libcbf_wrap.so $(BIN)/ctestcbf > testcbfc.txt $(LDPREFIX) java -cp $(JCBF)/cbflib-$(VERSION).jar:$(BIN) testcbf > testcbfj.txt $(DIFF) testcbfc.txt testcbfj.txt dectristests: $(BIN)/cbf_template_t $(DECTRIS_EXAMPLES)/cbf_test_orig.out (cd $(DECTRIS_EXAMPLES); ../../bin/cbf_template_t; diff -a -u cbf_test_orig.out cbf_template_t.out) # # Remove all non-source files # empty: @-rm -f $(LIB)/*.o @-rm -f $(LIB)/libcbf.a @-rm -f $(LIB)/libfcb.a @-rm -f $(LIB)/libimg.a @-rm -f $(LIB)/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/build/*/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/build/src/cbf_simple.o @-rm -f $(PYCBF)/build/*/pycbf_wrap.o @-rm -rf $(BIN)/adscimg2cbf* @-rm -rf $(BIN)/cbf2adscimg* @-rm -rf $(BIN)/makecbf* @-rm -rf $(BIN)/img2cif* @-rm -rf $(BIN)/cif2cbf* @-rm -rf $(BIN)/convert_image* @-rm -rf $(BIN)/convert_minicbf* @-rm -rf $(BIN)/test_fcb_read_image* @-rm -rf $(BIN)/test_xds_binary* @-rm -rf $(BIN)/testcell* @-rm -rf $(BIN)/cif2c* @-rm -rf $(BIN)/testreals* @-rm -rf $(BIN)/testflat* @-rm -rf $(BIN)/testflatpacked* @-rm -rf $(BIN)/cbf_template_t* @-rm -rf $(BIN)/sauter_test* @-rm -rf $(BIN)/arvai_test* @-rm -rf $(BIN)/changtestcompression* @-rm -rf $(BIN)/tiff2cbf* @-rm -f makecbf.cbf @-rm -f img2cif_packed.cif @-rm -f img2cif_canonical.cif @-rm -f img2cif_packed.cbf @-rm -f img2cif_canonical.cbf @-rm -f img2cif_raw.cbf @-rm -f cif2cbf_packed.cbf @-rm -f cif2cbf_canonical.cbf @-rm -f converted.cbf @-rm -f adscconverted.cbf @-rm -f converted_flat.cbf @-rm -f adscconverted_flat.cbf @-rm -f adscconverted_flat_rev.cbf @-rm -f mb_LP_1_001.cbf @-rm -f cif2cbf_ehcn.cif @-rm -f cif2cbf_encp.cbf @-rm -f 9ins.cbf @-rm -f 9ins.cif @-rm -f testcell.prt @-rm -f example.mar2300 @-rm -f converted_orig.cbf @-rm -f adscconverted_orig.cbf @-rm -f converted_flat_orig.cbf @-rm -f adscconverted_flat_orig.cbf @-rm -f adscconverted_flat_rev_orig.cbf @-rm -f mb_LP_1_001_orig.cbf @-rm -f insulin_pilatus6mconverted_orig.cbf @-rm -f insulin_pilatus6mconverted.cbf @-rm -f insulin_pilatus6m.cbf @-rm -f testrealin.cbf @-rm -f testrealout.cbf @-rm -f testflatin.cbf @-rm -f testflatout.cbf @-rm -f testflatpackedin.cbf @-rm -f testflatpackedout.cbf @-rm -f CTC.cbf @-rm -f test_fcb_read_testflatout.out @-rm -f test_fcb_read_testflatpackedout.out @-rm -f test_xds_bin_testflatpackedout.out @-rm -f test_xds_bin_testflatout.out @-rm -f test_fcb_read_testflatout_orig.out @-rm -f test_fcb_read_testflatpackedout_orig.out @-rm -f test_xds_bin_testflatpackedout_orig.out @-rm -f test_xds_bin_testflatout_orig.out @-rm -f mb_LP_1_001.img @-rm -f 9ins.cif @-rm -f testcell_orig.prt @-rm -f $(DECTRIS_EXAMPLES)/cbf_template_t.out @-rm -f XRD1621.cbf @-rm -f XRD1621_orig.cbf @-rm -f XRD1621_orig.cbf @-rm -f XRD1621_I4encbC100.cbf @-rm -f $(SRC)/fcb_exit_binary.f90 @-rm -f $(SRC)/fcb_next_binary.f90 @-rm -f $(SRC)/fcb_open_cifin.f90 @-rm -f $(SRC)/fcb_packed.f90 @-rm -f $(SRC)/fcb_read_bits.f90 @-rm -f $(SRC)/fcb_read_image.f90 @-rm -f $(SRC)/fcb_read_xds_i2.f90 @-rm -f $(EXAMPLES)/test_fcb_read_image.f90 @-rm -f $(EXAMPLES)/test_xds_binary.f90 @-rm -f symlinksdone @-rm -f $(TESTOUTPUT) *$(SEXT) @-rm -f $(SOLIB)/*.o @-rm -f $(SOLIB)/libcbf_wrap.so @-rm -f $(SOLIB)/libjcbf.so @-rm -f $(SOLIB)/libimg.so @-rm -f $(SOLIB)/libfcb.so @-rm -rf $(JCBF)/org @-rm -f $(JCBF)/*.java @-rm -f $(JCBF)/jcbf_wrap.c @-rm -f $(SRC)/cbf_wrap.c @-rm -f $(BIN)/ctestcbf $(BIN)/testcbf.class testcbfc.txt testcbfj.txt @-rm -rf $(REGEX) @-rm -rf $(TIFF) ./.undosymlinks # # Remove temporary files # clean: @-rm -f core @-rm -f *.o @-rm -f *.u # # Restore to distribution state # distclean: clean empty # # Create a Tape Archive for distribution # tar: $(DOCUMENTS) $(SOURCE) $(SRC)/cbf.stx $(HEADERS) $(M4FILES)\ $(EXAMPLES) \ README.html README Makefile \ $(JPEGS) -/bin/rm -f CBFlib.tar* tar cvBf CBFlib.tar \ $(DOCUMENTS) $(SOURCE) $(SRC)/cbf.stx $(HEADERS) $(M4FILES)\ $(EXAMPLES) \ README.html README Makefile \ $(JPEGS) gzip --best CBFlib.tar ./CBFlib-0.9.2.2/libtool/0000755000076500007650000000000011603703065013247 5ustar yayayaya./CBFlib-0.9.2.2/libtool/ltmain.sh0000755000076500007650000060447011603702120015074 0ustar yayayaya# ltmain.sh - Provide generalized library-building support services. # NOTE: Changing this file will not affect anything until you rerun configure. # # Copyright (C) 1996, 1997, 1998, 1999, 2000, 2001, 2003, 2004, 2005, 2006, # 2007 Free Software Foundation, Inc. # Originally by Gordon Matzigkeit , 1996 # # This program is free software; you can redistribute it and/or modify # it under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2 of the License, or # (at your option) any later version. # # This program is distributed in the hope that it will be useful, but # WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # General Public License for more details. # # You should have received a copy of the GNU General Public License # along with this program; if not, write to the Free Software # Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. # # As a special exception to the GNU General Public License, if you # distribute this file as part of a program that contains a # configuration script generated by Autoconf, you may include it under # the same distribution terms that you use for the rest of that program. basename="s,^.*/,,g" # Work around backward compatibility issue on IRIX 6.5. On IRIX 6.4+, sh # is ksh but when the shell is invoked as "sh" and the current value of # the _XPG environment variable is not equal to 1 (one), the special # positional parameter $0, within a function call, is the name of the # function. progpath="$0" # The name of this program: progname=`echo "$progpath" | $SED $basename` modename="$progname" # Global variables: EXIT_SUCCESS=0 EXIT_FAILURE=1 PROGRAM=ltmain.sh PACKAGE=libtool VERSION=1.5.24 TIMESTAMP=" (1.1220.2.455 2007/06/24 02:13:29)" # Be Bourne compatible (taken from Autoconf:_AS_BOURNE_COMPATIBLE). if test -n "${ZSH_VERSION+set}" && (emulate sh) >/dev/null 2>&1; then emulate sh NULLCMD=: # Zsh 3.x and 4.x performs word splitting on ${1+"$@"}, which # is contrary to our usage. Disable this feature. alias -g '${1+"$@"}'='"$@"' setopt NO_GLOB_SUBST else case `(set -o) 2>/dev/null` in *posix*) set -o posix;; esac fi BIN_SH=xpg4; export BIN_SH # for Tru64 DUALCASE=1; export DUALCASE # for MKS sh # Check that we have a working $echo. if test "X$1" = X--no-reexec; then # Discard the --no-reexec flag, and continue. shift elif test "X$1" = X--fallback-echo; then # Avoid inline document here, it may be left over : elif test "X`($echo '\t') 2>/dev/null`" = 'X\t'; then # Yippee, $echo works! : else # Restart under the correct shell, and then maybe $echo will work. exec $SHELL "$progpath" --no-reexec ${1+"$@"} fi if test "X$1" = X--fallback-echo; then # used as fallback echo shift cat <&2 $echo "Fatal configuration error. See the $PACKAGE docs for more information." 1>&2 exit $EXIT_FAILURE fi # Global variables. mode=$default_mode nonopt= prev= prevopt= run= show="$echo" show_help= execute_dlfiles= duplicate_deps=no preserve_args= lo2o="s/\\.lo\$/.${objext}/" o2lo="s/\\.${objext}\$/.lo/" extracted_archives= extracted_serial=0 ##################################### # Shell function definitions: # This seems to be the best place for them # func_mktempdir [string] # Make a temporary directory that won't clash with other running # libtool processes, and avoids race conditions if possible. If # given, STRING is the basename for that directory. func_mktempdir () { my_template="${TMPDIR-/tmp}/${1-$progname}" if test "$run" = ":"; then # Return a directory name, but don't create it in dry-run mode my_tmpdir="${my_template}-$$" else # If mktemp works, use that first and foremost my_tmpdir=`mktemp -d "${my_template}-XXXXXXXX" 2>/dev/null` if test ! -d "$my_tmpdir"; then # Failing that, at least try and use $RANDOM to avoid a race my_tmpdir="${my_template}-${RANDOM-0}$$" save_mktempdir_umask=`umask` umask 0077 $mkdir "$my_tmpdir" umask $save_mktempdir_umask fi # If we're not in dry-run mode, bomb out on failure test -d "$my_tmpdir" || { $echo "cannot create temporary directory \`$my_tmpdir'" 1>&2 exit $EXIT_FAILURE } fi $echo "X$my_tmpdir" | $Xsed } # func_win32_libid arg # return the library type of file 'arg' # # Need a lot of goo to handle *both* DLLs and import libs # Has to be a shell function in order to 'eat' the argument # that is supplied when $file_magic_command is called. func_win32_libid () { win32_libid_type="unknown" win32_fileres=`file -L $1 2>/dev/null` case $win32_fileres in *ar\ archive\ import\ library*) # definitely import win32_libid_type="x86 archive import" ;; *ar\ archive*) # could be an import, or static if eval $OBJDUMP -f $1 | $SED -e '10q' 2>/dev/null | \ $EGREP -e 'file format pe-i386(.*architecture: i386)?' >/dev/null ; then win32_nmres=`eval $NM -f posix -A $1 | \ $SED -n -e '1,100{ / I /{ s,.*,import, p q } }'` case $win32_nmres in import*) win32_libid_type="x86 archive import";; *) win32_libid_type="x86 archive static";; esac fi ;; *DLL*) win32_libid_type="x86 DLL" ;; *executable*) # but shell scripts are "executable" too... case $win32_fileres in *MS\ Windows\ PE\ Intel*) win32_libid_type="x86 DLL" ;; esac ;; esac $echo $win32_libid_type } # func_infer_tag arg # Infer tagged configuration to use if any are available and # if one wasn't chosen via the "--tag" command line option. # Only attempt this if the compiler in the base compile # command doesn't match the default compiler. # arg is usually of the form 'gcc ...' func_infer_tag () { if test -n "$available_tags" && test -z "$tagname"; then CC_quoted= for arg in $CC; do case $arg in *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*|"") arg="\"$arg\"" ;; esac CC_quoted="$CC_quoted $arg" done case $@ in # Blanks in the command may have been stripped by the calling shell, # but not from the CC environment variable when configure was run. " $CC "* | "$CC "* | " `$echo $CC` "* | "`$echo $CC` "* | " $CC_quoted"* | "$CC_quoted "* | " `$echo $CC_quoted` "* | "`$echo $CC_quoted` "*) ;; # Blanks at the start of $base_compile will cause this to fail # if we don't check for them as well. *) for z in $available_tags; do if grep "^# ### BEGIN LIBTOOL TAG CONFIG: $z$" < "$progpath" > /dev/null; then # Evaluate the configuration. eval "`${SED} -n -e '/^# ### BEGIN LIBTOOL TAG CONFIG: '$z'$/,/^# ### END LIBTOOL TAG CONFIG: '$z'$/p' < $progpath`" CC_quoted= for arg in $CC; do # Double-quote args containing other shell metacharacters. case $arg in *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*|"") arg="\"$arg\"" ;; esac CC_quoted="$CC_quoted $arg" done case "$@ " in " $CC "* | "$CC "* | " `$echo $CC` "* | "`$echo $CC` "* | " $CC_quoted"* | "$CC_quoted "* | " `$echo $CC_quoted` "* | "`$echo $CC_quoted` "*) # The compiler in the base compile command matches # the one in the tagged configuration. # Assume this is the tagged configuration we want. tagname=$z break ;; esac fi done # If $tagname still isn't set, then no tagged configuration # was found and let the user know that the "--tag" command # line option must be used. if test -z "$tagname"; then $echo "$modename: unable to infer tagged configuration" $echo "$modename: specify a tag with \`--tag'" 1>&2 exit $EXIT_FAILURE # else # $echo "$modename: using $tagname tagged configuration" fi ;; esac fi } # func_extract_an_archive dir oldlib func_extract_an_archive () { f_ex_an_ar_dir="$1"; shift f_ex_an_ar_oldlib="$1" $show "(cd $f_ex_an_ar_dir && $AR x $f_ex_an_ar_oldlib)" $run eval "(cd \$f_ex_an_ar_dir && $AR x \$f_ex_an_ar_oldlib)" || exit $? if ($AR t "$f_ex_an_ar_oldlib" | sort | sort -uc >/dev/null 2>&1); then : else $echo "$modename: ERROR: object name conflicts: $f_ex_an_ar_dir/$f_ex_an_ar_oldlib" 1>&2 exit $EXIT_FAILURE fi } # func_extract_archives gentop oldlib ... func_extract_archives () { my_gentop="$1"; shift my_oldlibs=${1+"$@"} my_oldobjs="" my_xlib="" my_xabs="" my_xdir="" my_status="" $show "${rm}r $my_gentop" $run ${rm}r "$my_gentop" $show "$mkdir $my_gentop" $run $mkdir "$my_gentop" my_status=$? if test "$my_status" -ne 0 && test ! -d "$my_gentop"; then exit $my_status fi for my_xlib in $my_oldlibs; do # Extract the objects. case $my_xlib in [\\/]* | [A-Za-z]:[\\/]*) my_xabs="$my_xlib" ;; *) my_xabs=`pwd`"/$my_xlib" ;; esac my_xlib=`$echo "X$my_xlib" | $Xsed -e 's%^.*/%%'` my_xlib_u=$my_xlib while :; do case " $extracted_archives " in *" $my_xlib_u "*) extracted_serial=`expr $extracted_serial + 1` my_xlib_u=lt$extracted_serial-$my_xlib ;; *) break ;; esac done extracted_archives="$extracted_archives $my_xlib_u" my_xdir="$my_gentop/$my_xlib_u" $show "${rm}r $my_xdir" $run ${rm}r "$my_xdir" $show "$mkdir $my_xdir" $run $mkdir "$my_xdir" exit_status=$? if test "$exit_status" -ne 0 && test ! -d "$my_xdir"; then exit $exit_status fi case $host in *-darwin*) $show "Extracting $my_xabs" # Do not bother doing anything if just a dry run if test -z "$run"; then darwin_orig_dir=`pwd` cd $my_xdir || exit $? darwin_archive=$my_xabs darwin_curdir=`pwd` darwin_base_archive=`$echo "X$darwin_archive" | $Xsed -e 's%^.*/%%'` darwin_arches=`lipo -info "$darwin_archive" 2>/dev/null | $EGREP Architectures 2>/dev/null` if test -n "$darwin_arches"; then darwin_arches=`echo "$darwin_arches" | $SED -e 's/.*are://'` darwin_arch= $show "$darwin_base_archive has multiple architectures $darwin_arches" for darwin_arch in $darwin_arches ; do mkdir -p "unfat-$$/${darwin_base_archive}-${darwin_arch}" lipo -thin $darwin_arch -output "unfat-$$/${darwin_base_archive}-${darwin_arch}/${darwin_base_archive}" "${darwin_archive}" cd "unfat-$$/${darwin_base_archive}-${darwin_arch}" func_extract_an_archive "`pwd`" "${darwin_base_archive}" cd "$darwin_curdir" $rm "unfat-$$/${darwin_base_archive}-${darwin_arch}/${darwin_base_archive}" done # $darwin_arches ## Okay now we have a bunch of thin objects, gotta fatten them up :) darwin_filelist=`find unfat-$$ -type f -name \*.o -print -o -name \*.lo -print| xargs basename | sort -u | $NL2SP` darwin_file= darwin_files= for darwin_file in $darwin_filelist; do darwin_files=`find unfat-$$ -name $darwin_file -print | $NL2SP` lipo -create -output "$darwin_file" $darwin_files done # $darwin_filelist ${rm}r unfat-$$ cd "$darwin_orig_dir" else cd "$darwin_orig_dir" func_extract_an_archive "$my_xdir" "$my_xabs" fi # $darwin_arches fi # $run ;; *) func_extract_an_archive "$my_xdir" "$my_xabs" ;; esac my_oldobjs="$my_oldobjs "`find $my_xdir -name \*.$objext -print -o -name \*.lo -print | $NL2SP` done func_extract_archives_result="$my_oldobjs" } # End of Shell function definitions ##################################### # Darwin sucks eval std_shrext=\"$shrext_cmds\" disable_libs=no # Parse our command line options once, thoroughly. while test "$#" -gt 0 do arg="$1" shift case $arg in -*=*) optarg=`$echo "X$arg" | $Xsed -e 's/[-_a-zA-Z0-9]*=//'` ;; *) optarg= ;; esac # If the previous option needs an argument, assign it. if test -n "$prev"; then case $prev in execute_dlfiles) execute_dlfiles="$execute_dlfiles $arg" ;; tag) tagname="$arg" preserve_args="${preserve_args}=$arg" # Check whether tagname contains only valid characters case $tagname in *[!-_A-Za-z0-9,/]*) $echo "$progname: invalid tag name: $tagname" 1>&2 exit $EXIT_FAILURE ;; esac case $tagname in CC) # Don't test for the "default" C tag, as we know, it's there, but # not specially marked. ;; *) if grep "^# ### BEGIN LIBTOOL TAG CONFIG: $tagname$" < "$progpath" > /dev/null; then taglist="$taglist $tagname" # Evaluate the configuration. eval "`${SED} -n -e '/^# ### BEGIN LIBTOOL TAG CONFIG: '$tagname'$/,/^# ### END LIBTOOL TAG CONFIG: '$tagname'$/p' < $progpath`" else $echo "$progname: ignoring unknown tag $tagname" 1>&2 fi ;; esac ;; *) eval "$prev=\$arg" ;; esac prev= prevopt= continue fi # Have we seen a non-optional argument yet? case $arg in --help) show_help=yes ;; --version) echo "\ $PROGRAM (GNU $PACKAGE) $VERSION$TIMESTAMP Copyright (C) 2007 Free Software Foundation, Inc. This is free software; see the source for copying conditions. There is NO warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE." exit $? ;; --config) ${SED} -e '1,/^# ### BEGIN LIBTOOL CONFIG/d' -e '/^# ### END LIBTOOL CONFIG/,$d' $progpath # Now print the configurations for the tags. for tagname in $taglist; do ${SED} -n -e "/^# ### BEGIN LIBTOOL TAG CONFIG: $tagname$/,/^# ### END LIBTOOL TAG CONFIG: $tagname$/p" < "$progpath" done exit $? ;; --debug) $echo "$progname: enabling shell trace mode" set -x preserve_args="$preserve_args $arg" ;; --dry-run | -n) run=: ;; --features) $echo "host: $host" if test "$build_libtool_libs" = yes; then $echo "enable shared libraries" else $echo "disable shared libraries" fi if test "$build_old_libs" = yes; then $echo "enable static libraries" else $echo "disable static libraries" fi exit $? ;; --finish) mode="finish" ;; --mode) prevopt="--mode" prev=mode ;; --mode=*) mode="$optarg" ;; --preserve-dup-deps) duplicate_deps="yes" ;; --quiet | --silent) show=: preserve_args="$preserve_args $arg" ;; --tag) prevopt="--tag" prev=tag preserve_args="$preserve_args --tag" ;; --tag=*) set tag "$optarg" ${1+"$@"} shift prev=tag preserve_args="$preserve_args --tag" ;; -dlopen) prevopt="-dlopen" prev=execute_dlfiles ;; -*) $echo "$modename: unrecognized option \`$arg'" 1>&2 $echo "$help" 1>&2 exit $EXIT_FAILURE ;; *) nonopt="$arg" break ;; esac done if test -n "$prevopt"; then $echo "$modename: option \`$prevopt' requires an argument" 1>&2 $echo "$help" 1>&2 exit $EXIT_FAILURE fi case $disable_libs in no) ;; shared) build_libtool_libs=no build_old_libs=yes ;; static) build_old_libs=`case $build_libtool_libs in yes) echo no;; *) echo yes;; esac` ;; esac # If this variable is set in any of the actions, the command in it # will be execed at the end. This prevents here-documents from being # left over by shells. exec_cmd= if test -z "$show_help"; then # Infer the operation mode. if test -z "$mode"; then $echo "*** Warning: inferring the mode of operation is deprecated." 1>&2 $echo "*** Future versions of Libtool will require --mode=MODE be specified." 1>&2 case $nonopt in *cc | cc* | *++ | gcc* | *-gcc* | g++* | xlc*) mode=link for arg do case $arg in -c) mode=compile break ;; esac done ;; *db | *dbx | *strace | *truss) mode=execute ;; *install*|cp|mv) mode=install ;; *rm) mode=uninstall ;; *) # If we have no mode, but dlfiles were specified, then do execute mode. test -n "$execute_dlfiles" && mode=execute # Just use the default operation mode. if test -z "$mode"; then if test -n "$nonopt"; then $echo "$modename: warning: cannot infer operation mode from \`$nonopt'" 1>&2 else $echo "$modename: warning: cannot infer operation mode without MODE-ARGS" 1>&2 fi fi ;; esac fi # Only execute mode is allowed to have -dlopen flags. if test -n "$execute_dlfiles" && test "$mode" != execute; then $echo "$modename: unrecognized option \`-dlopen'" 1>&2 $echo "$help" 1>&2 exit $EXIT_FAILURE fi # Change the help message to a mode-specific one. generic_help="$help" help="Try \`$modename --help --mode=$mode' for more information." # These modes are in order of execution frequency so that they run quickly. case $mode in # libtool compile mode compile) modename="$modename: compile" # Get the compilation command and the source file. base_compile= srcfile="$nonopt" # always keep a non-empty value in "srcfile" suppress_opt=yes suppress_output= arg_mode=normal libobj= later= for arg do case $arg_mode in arg ) # do not "continue". Instead, add this to base_compile lastarg="$arg" arg_mode=normal ;; target ) libobj="$arg" arg_mode=normal continue ;; normal ) # Accept any command-line options. case $arg in -o) if test -n "$libobj" ; then $echo "$modename: you cannot specify \`-o' more than once" 1>&2 exit $EXIT_FAILURE fi arg_mode=target continue ;; -static | -prefer-pic | -prefer-non-pic) later="$later $arg" continue ;; -no-suppress) suppress_opt=no continue ;; -Xcompiler) arg_mode=arg # the next one goes into the "base_compile" arg list continue # The current "srcfile" will either be retained or ;; # replaced later. I would guess that would be a bug. -Wc,*) args=`$echo "X$arg" | $Xsed -e "s/^-Wc,//"` lastarg= save_ifs="$IFS"; IFS=',' for arg in $args; do IFS="$save_ifs" # Double-quote args containing other shell metacharacters. # Many Bourne shells cannot handle close brackets correctly # in scan sets, so we specify it separately. case $arg in *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*|"") arg="\"$arg\"" ;; esac lastarg="$lastarg $arg" done IFS="$save_ifs" lastarg=`$echo "X$lastarg" | $Xsed -e "s/^ //"` # Add the arguments to base_compile. base_compile="$base_compile $lastarg" continue ;; * ) # Accept the current argument as the source file. # The previous "srcfile" becomes the current argument. # lastarg="$srcfile" srcfile="$arg" ;; esac # case $arg ;; esac # case $arg_mode # Aesthetically quote the previous argument. lastarg=`$echo "X$lastarg" | $Xsed -e "$sed_quote_subst"` case $lastarg in # Double-quote args containing other shell metacharacters. # Many Bourne shells cannot handle close brackets correctly # in scan sets, and some SunOS ksh mistreat backslash-escaping # in scan sets (worked around with variable expansion), # and furthermore cannot handle '|' '&' '(' ')' in scan sets # at all, so we specify them separately. *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*|"") lastarg="\"$lastarg\"" ;; esac base_compile="$base_compile $lastarg" done # for arg case $arg_mode in arg) $echo "$modename: you must specify an argument for -Xcompile" exit $EXIT_FAILURE ;; target) $echo "$modename: you must specify a target with \`-o'" 1>&2 exit $EXIT_FAILURE ;; *) # Get the name of the library object. [ -z "$libobj" ] && libobj=`$echo "X$srcfile" | $Xsed -e 's%^.*/%%'` ;; esac # Recognize several different file suffixes. # If the user specifies -o file.o, it is replaced with file.lo xform='[cCFSifmso]' case $libobj in *.ada) xform=ada ;; *.adb) xform=adb ;; *.ads) xform=ads ;; *.asm) xform=asm ;; *.c++) xform=c++ ;; *.cc) xform=cc ;; *.ii) xform=ii ;; *.class) xform=class ;; *.cpp) xform=cpp ;; *.cxx) xform=cxx ;; *.[fF][09]?) xform=[fF][09]. ;; *.for) xform=for ;; *.java) xform=java ;; *.obj) xform=obj ;; esac libobj=`$echo "X$libobj" | $Xsed -e "s/\.$xform$/.lo/"` case $libobj in *.lo) obj=`$echo "X$libobj" | $Xsed -e "$lo2o"` ;; *) $echo "$modename: cannot determine name of library object from \`$libobj'" 1>&2 exit $EXIT_FAILURE ;; esac func_infer_tag $base_compile for arg in $later; do case $arg in -static) build_old_libs=yes continue ;; -prefer-pic) pic_mode=yes continue ;; -prefer-non-pic) pic_mode=no continue ;; esac done qlibobj=`$echo "X$libobj" | $Xsed -e "$sed_quote_subst"` case $qlibobj in *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*|"") qlibobj="\"$qlibobj\"" ;; esac test "X$libobj" != "X$qlibobj" \ && $echo "X$libobj" | grep '[]~#^*{};<>?"'"'"' &()|`$[]' \ && $echo "$modename: libobj name \`$libobj' may not contain shell special characters." objname=`$echo "X$obj" | $Xsed -e 's%^.*/%%'` xdir=`$echo "X$obj" | $Xsed -e 's%/[^/]*$%%'` if test "X$xdir" = "X$obj"; then xdir= else xdir=$xdir/ fi lobj=${xdir}$objdir/$objname if test -z "$base_compile"; then $echo "$modename: you must specify a compilation command" 1>&2 $echo "$help" 1>&2 exit $EXIT_FAILURE fi # Delete any leftover library objects. if test "$build_old_libs" = yes; then removelist="$obj $lobj $libobj ${libobj}T" else removelist="$lobj $libobj ${libobj}T" fi $run $rm $removelist trap "$run $rm $removelist; exit $EXIT_FAILURE" 1 2 15 # On Cygwin there's no "real" PIC flag so we must build both object types case $host_os in cygwin* | mingw* | pw32* | os2*) pic_mode=default ;; esac if test "$pic_mode" = no && test "$deplibs_check_method" != pass_all; then # non-PIC code in shared libraries is not supported pic_mode=default fi # Calculate the filename of the output object if compiler does # not support -o with -c if test "$compiler_c_o" = no; then output_obj=`$echo "X$srcfile" | $Xsed -e 's%^.*/%%' -e 's%\.[^.]*$%%'`.${objext} lockfile="$output_obj.lock" removelist="$removelist $output_obj $lockfile" trap "$run $rm $removelist; exit $EXIT_FAILURE" 1 2 15 else output_obj= need_locks=no lockfile= fi # Lock this critical section if it is needed # We use this script file to make the link, it avoids creating a new file if test "$need_locks" = yes; then until $run ln "$progpath" "$lockfile" 2>/dev/null; do $show "Waiting for $lockfile to be removed" sleep 2 done elif test "$need_locks" = warn; then if test -f "$lockfile"; then $echo "\ *** ERROR, $lockfile exists and contains: `cat $lockfile 2>/dev/null` This indicates that another process is trying to use the same temporary object file, and libtool could not work around it because your compiler does not support \`-c' and \`-o' together. If you repeat this compilation, it may succeed, by chance, but you had better avoid parallel builds (make -j) in this platform, or get a better compiler." $run $rm $removelist exit $EXIT_FAILURE fi $echo "$srcfile" > "$lockfile" fi if test -n "$fix_srcfile_path"; then eval srcfile=\"$fix_srcfile_path\" fi qsrcfile=`$echo "X$srcfile" | $Xsed -e "$sed_quote_subst"` case $qsrcfile in *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*|"") qsrcfile="\"$qsrcfile\"" ;; esac $run $rm "$libobj" "${libobj}T" # Create a libtool object file (analogous to a ".la" file), # but don't create it if we're doing a dry run. test -z "$run" && cat > ${libobj}T </dev/null`" != "X$srcfile"; then $echo "\ *** ERROR, $lockfile contains: `cat $lockfile 2>/dev/null` but it should contain: $srcfile This indicates that another process is trying to use the same temporary object file, and libtool could not work around it because your compiler does not support \`-c' and \`-o' together. If you repeat this compilation, it may succeed, by chance, but you had better avoid parallel builds (make -j) in this platform, or get a better compiler." $run $rm $removelist exit $EXIT_FAILURE fi # Just move the object if needed, then go on to compile the next one if test -n "$output_obj" && test "X$output_obj" != "X$lobj"; then $show "$mv $output_obj $lobj" if $run $mv $output_obj $lobj; then : else error=$? $run $rm $removelist exit $error fi fi # Append the name of the PIC object to the libtool object file. test -z "$run" && cat >> ${libobj}T <> ${libobj}T </dev/null`" != "X$srcfile"; then $echo "\ *** ERROR, $lockfile contains: `cat $lockfile 2>/dev/null` but it should contain: $srcfile This indicates that another process is trying to use the same temporary object file, and libtool could not work around it because your compiler does not support \`-c' and \`-o' together. If you repeat this compilation, it may succeed, by chance, but you had better avoid parallel builds (make -j) in this platform, or get a better compiler." $run $rm $removelist exit $EXIT_FAILURE fi # Just move the object if needed if test -n "$output_obj" && test "X$output_obj" != "X$obj"; then $show "$mv $output_obj $obj" if $run $mv $output_obj $obj; then : else error=$? $run $rm $removelist exit $error fi fi # Append the name of the non-PIC object the libtool object file. # Only append if the libtool object file exists. test -z "$run" && cat >> ${libobj}T <> ${libobj}T <&2 fi if test -n "$link_static_flag"; then dlopen_self=$dlopen_self_static fi prefer_static_libs=yes ;; -static) if test -z "$pic_flag" && test -n "$link_static_flag"; then dlopen_self=$dlopen_self_static fi prefer_static_libs=built ;; -static-libtool-libs) if test -z "$pic_flag" && test -n "$link_static_flag"; then dlopen_self=$dlopen_self_static fi prefer_static_libs=yes ;; esac build_libtool_libs=no build_old_libs=yes break ;; esac done # See if our shared archives depend on static archives. test -n "$old_archive_from_new_cmds" && build_old_libs=yes # Go through the arguments, transforming them on the way. while test "$#" -gt 0; do arg="$1" shift case $arg in *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*|"") qarg=\"`$echo "X$arg" | $Xsed -e "$sed_quote_subst"`\" ### testsuite: skip nested quoting test ;; *) qarg=$arg ;; esac libtool_args="$libtool_args $qarg" # If the previous option needs an argument, assign it. if test -n "$prev"; then case $prev in output) compile_command="$compile_command @OUTPUT@" finalize_command="$finalize_command @OUTPUT@" ;; esac case $prev in dlfiles|dlprefiles) if test "$preload" = no; then # Add the symbol object into the linking commands. compile_command="$compile_command @SYMFILE@" finalize_command="$finalize_command @SYMFILE@" preload=yes fi case $arg in *.la | *.lo) ;; # We handle these cases below. force) if test "$dlself" = no; then dlself=needless export_dynamic=yes fi prev= continue ;; self) if test "$prev" = dlprefiles; then dlself=yes elif test "$prev" = dlfiles && test "$dlopen_self" != yes; then dlself=yes else dlself=needless export_dynamic=yes fi prev= continue ;; *) if test "$prev" = dlfiles; then dlfiles="$dlfiles $arg" else dlprefiles="$dlprefiles $arg" fi prev= continue ;; esac ;; expsyms) export_symbols="$arg" if test ! -f "$arg"; then $echo "$modename: symbol file \`$arg' does not exist" exit $EXIT_FAILURE fi prev= continue ;; expsyms_regex) export_symbols_regex="$arg" prev= continue ;; inst_prefix) inst_prefix_dir="$arg" prev= continue ;; precious_regex) precious_files_regex="$arg" prev= continue ;; release) release="-$arg" prev= continue ;; objectlist) if test -f "$arg"; then save_arg=$arg moreargs= for fil in `cat $save_arg` do # moreargs="$moreargs $fil" arg=$fil # A libtool-controlled object. # Check to see that this really is a libtool object. if (${SED} -e '2q' $arg | grep "^# Generated by .*$PACKAGE") >/dev/null 2>&1; then pic_object= non_pic_object= # Read the .lo file # If there is no directory component, then add one. case $arg in */* | *\\*) . $arg ;; *) . ./$arg ;; esac if test -z "$pic_object" || \ test -z "$non_pic_object" || test "$pic_object" = none && \ test "$non_pic_object" = none; then $echo "$modename: cannot find name of object for \`$arg'" 1>&2 exit $EXIT_FAILURE fi # Extract subdirectory from the argument. xdir=`$echo "X$arg" | $Xsed -e 's%/[^/]*$%%'` if test "X$xdir" = "X$arg"; then xdir= else xdir="$xdir/" fi if test "$pic_object" != none; then # Prepend the subdirectory the object is found in. pic_object="$xdir$pic_object" if test "$prev" = dlfiles; then if test "$build_libtool_libs" = yes && test "$dlopen_support" = yes; then dlfiles="$dlfiles $pic_object" prev= continue else # If libtool objects are unsupported, then we need to preload. prev=dlprefiles fi fi # CHECK ME: I think I busted this. -Ossama if test "$prev" = dlprefiles; then # Preload the old-style object. dlprefiles="$dlprefiles $pic_object" prev= fi # A PIC object. libobjs="$libobjs $pic_object" arg="$pic_object" fi # Non-PIC object. if test "$non_pic_object" != none; then # Prepend the subdirectory the object is found in. non_pic_object="$xdir$non_pic_object" # A standard non-PIC object non_pic_objects="$non_pic_objects $non_pic_object" if test -z "$pic_object" || test "$pic_object" = none ; then arg="$non_pic_object" fi else # If the PIC object exists, use it instead. # $xdir was prepended to $pic_object above. non_pic_object="$pic_object" non_pic_objects="$non_pic_objects $non_pic_object" fi else # Only an error if not doing a dry-run. if test -z "$run"; then $echo "$modename: \`$arg' is not a valid libtool object" 1>&2 exit $EXIT_FAILURE else # Dry-run case. # Extract subdirectory from the argument. xdir=`$echo "X$arg" | $Xsed -e 's%/[^/]*$%%'` if test "X$xdir" = "X$arg"; then xdir= else xdir="$xdir/" fi pic_object=`$echo "X${xdir}${objdir}/${arg}" | $Xsed -e "$lo2o"` non_pic_object=`$echo "X${xdir}${arg}" | $Xsed -e "$lo2o"` libobjs="$libobjs $pic_object" non_pic_objects="$non_pic_objects $non_pic_object" fi fi done else $echo "$modename: link input file \`$save_arg' does not exist" exit $EXIT_FAILURE fi arg=$save_arg prev= continue ;; rpath | xrpath) # We need an absolute path. case $arg in [\\/]* | [A-Za-z]:[\\/]*) ;; *) $echo "$modename: only absolute run-paths are allowed" 1>&2 exit $EXIT_FAILURE ;; esac if test "$prev" = rpath; then case "$rpath " in *" $arg "*) ;; *) rpath="$rpath $arg" ;; esac else case "$xrpath " in *" $arg "*) ;; *) xrpath="$xrpath $arg" ;; esac fi prev= continue ;; xcompiler) compiler_flags="$compiler_flags $qarg" prev= compile_command="$compile_command $qarg" finalize_command="$finalize_command $qarg" continue ;; xlinker) linker_flags="$linker_flags $qarg" compiler_flags="$compiler_flags $wl$qarg" prev= compile_command="$compile_command $wl$qarg" finalize_command="$finalize_command $wl$qarg" continue ;; xcclinker) linker_flags="$linker_flags $qarg" compiler_flags="$compiler_flags $qarg" prev= compile_command="$compile_command $qarg" finalize_command="$finalize_command $qarg" continue ;; shrext) shrext_cmds="$arg" prev= continue ;; darwin_framework|darwin_framework_skip) test "$prev" = "darwin_framework" && compiler_flags="$compiler_flags $arg" compile_command="$compile_command $arg" finalize_command="$finalize_command $arg" prev= continue ;; *) eval "$prev=\"\$arg\"" prev= continue ;; esac fi # test -n "$prev" prevarg="$arg" case $arg in -all-static) if test -n "$link_static_flag"; then compile_command="$compile_command $link_static_flag" finalize_command="$finalize_command $link_static_flag" fi continue ;; -allow-undefined) # FIXME: remove this flag sometime in the future. $echo "$modename: \`-allow-undefined' is deprecated because it is the default" 1>&2 continue ;; -avoid-version) avoid_version=yes continue ;; -dlopen) prev=dlfiles continue ;; -dlpreopen) prev=dlprefiles continue ;; -export-dynamic) export_dynamic=yes continue ;; -export-symbols | -export-symbols-regex) if test -n "$export_symbols" || test -n "$export_symbols_regex"; then $echo "$modename: more than one -exported-symbols argument is not allowed" exit $EXIT_FAILURE fi if test "X$arg" = "X-export-symbols"; then prev=expsyms else prev=expsyms_regex fi continue ;; -framework|-arch|-isysroot) case " $CC " in *" ${arg} ${1} "* | *" ${arg} ${1} "*) prev=darwin_framework_skip ;; *) compiler_flags="$compiler_flags $arg" prev=darwin_framework ;; esac compile_command="$compile_command $arg" finalize_command="$finalize_command $arg" continue ;; -inst-prefix-dir) prev=inst_prefix continue ;; # The native IRIX linker understands -LANG:*, -LIST:* and -LNO:* # so, if we see these flags be careful not to treat them like -L -L[A-Z][A-Z]*:*) case $with_gcc/$host in no/*-*-irix* | /*-*-irix*) compile_command="$compile_command $arg" finalize_command="$finalize_command $arg" ;; esac continue ;; -L*) dir=`$echo "X$arg" | $Xsed -e 's/^-L//'` # We need an absolute path. case $dir in [\\/]* | [A-Za-z]:[\\/]*) ;; *) absdir=`cd "$dir" && pwd` if test -z "$absdir"; then $echo "$modename: cannot determine absolute directory name of \`$dir'" 1>&2 absdir="$dir" notinst_path="$notinst_path $dir" fi dir="$absdir" ;; esac case "$deplibs " in *" -L$dir "*) ;; *) deplibs="$deplibs -L$dir" lib_search_path="$lib_search_path $dir" ;; esac case $host in *-*-cygwin* | *-*-mingw* | *-*-pw32* | *-*-os2*) testbindir=`$echo "X$dir" | $Xsed -e 's*/lib$*/bin*'` case :$dllsearchpath: in *":$dir:"*) ;; *) dllsearchpath="$dllsearchpath:$dir";; esac case :$dllsearchpath: in *":$testbindir:"*) ;; *) dllsearchpath="$dllsearchpath:$testbindir";; esac ;; esac continue ;; -l*) if test "X$arg" = "X-lc" || test "X$arg" = "X-lm"; then case $host in *-*-cygwin* | *-*-mingw* | *-*-pw32* | *-*-beos*) # These systems don't actually have a C or math library (as such) continue ;; *-*-os2*) # These systems don't actually have a C library (as such) test "X$arg" = "X-lc" && continue ;; *-*-openbsd* | *-*-freebsd* | *-*-dragonfly*) # Do not include libc due to us having libc/libc_r. test "X$arg" = "X-lc" && continue ;; *-*-rhapsody* | *-*-darwin1.[012]) # Rhapsody C and math libraries are in the System framework deplibs="$deplibs -framework System" continue ;; *-*-sco3.2v5* | *-*-sco5v6*) # Causes problems with __ctype test "X$arg" = "X-lc" && continue ;; *-*-sysv4.2uw2* | *-*-sysv5* | *-*-unixware* | *-*-OpenUNIX*) # Compiler inserts libc in the correct place for threads to work test "X$arg" = "X-lc" && continue ;; esac elif test "X$arg" = "X-lc_r"; then case $host in *-*-openbsd* | *-*-freebsd* | *-*-dragonfly*) # Do not include libc_r directly, use -pthread flag. continue ;; esac fi deplibs="$deplibs $arg" continue ;; # Tru64 UNIX uses -model [arg] to determine the layout of C++ # classes, name mangling, and exception handling. -model) compile_command="$compile_command $arg" compiler_flags="$compiler_flags $arg" finalize_command="$finalize_command $arg" prev=xcompiler continue ;; -mt|-mthreads|-kthread|-Kthread|-pthread|-pthreads|--thread-safe|-threads) compiler_flags="$compiler_flags $arg" compile_command="$compile_command $arg" finalize_command="$finalize_command $arg" continue ;; -module) module=yes continue ;; # -64, -mips[0-9] enable 64-bit mode on the SGI compiler # -r[0-9][0-9]* specifies the processor on the SGI compiler # -xarch=*, -xtarget=* enable 64-bit mode on the Sun compiler # +DA*, +DD* enable 64-bit mode on the HP compiler # -q* pass through compiler args for the IBM compiler # -m* pass through architecture-specific compiler args for GCC # -m*, -t[45]*, -txscale* pass through architecture-specific # compiler args for GCC # -p, -pg, --coverage, -fprofile-* pass through profiling flag for GCC # -F/path gives path to uninstalled frameworks, gcc on darwin # @file GCC response files -64|-mips[0-9]|-r[0-9][0-9]*|-xarch=*|-xtarget=*|+DA*|+DD*|-q*|-m*| \ -t[45]*|-txscale*|-p|-pg|--coverage|-fprofile-*|-F*|@*) # Unknown arguments in both finalize_command and compile_command need # to be aesthetically quoted because they are evaled later. arg=`$echo "X$arg" | $Xsed -e "$sed_quote_subst"` case $arg in *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*|"") arg="\"$arg\"" ;; esac compile_command="$compile_command $arg" finalize_command="$finalize_command $arg" compiler_flags="$compiler_flags $arg" continue ;; -shrext) prev=shrext continue ;; -no-fast-install) fast_install=no continue ;; -no-install) case $host in *-*-cygwin* | *-*-mingw* | *-*-pw32* | *-*-os2* | *-*-darwin*) # The PATH hackery in wrapper scripts is required on Windows # and Darwin in order for the loader to find any dlls it needs. $echo "$modename: warning: \`-no-install' is ignored for $host" 1>&2 $echo "$modename: warning: assuming \`-no-fast-install' instead" 1>&2 fast_install=no ;; *) no_install=yes ;; esac continue ;; -no-undefined) allow_undefined=no continue ;; -objectlist) prev=objectlist continue ;; -o) prev=output ;; -precious-files-regex) prev=precious_regex continue ;; -release) prev=release continue ;; -rpath) prev=rpath continue ;; -R) prev=xrpath continue ;; -R*) dir=`$echo "X$arg" | $Xsed -e 's/^-R//'` # We need an absolute path. case $dir in [\\/]* | [A-Za-z]:[\\/]*) ;; *) $echo "$modename: only absolute run-paths are allowed" 1>&2 exit $EXIT_FAILURE ;; esac case "$xrpath " in *" $dir "*) ;; *) xrpath="$xrpath $dir" ;; esac continue ;; -static | -static-libtool-libs) # The effects of -static are defined in a previous loop. # We used to do the same as -all-static on platforms that # didn't have a PIC flag, but the assumption that the effects # would be equivalent was wrong. It would break on at least # Digital Unix and AIX. continue ;; -thread-safe) thread_safe=yes continue ;; -version-info) prev=vinfo continue ;; -version-number) prev=vinfo vinfo_number=yes continue ;; -Wc,*) args=`$echo "X$arg" | $Xsed -e "$sed_quote_subst" -e 's/^-Wc,//'` arg= save_ifs="$IFS"; IFS=',' for flag in $args; do IFS="$save_ifs" case $flag in *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*|"") flag="\"$flag\"" ;; esac arg="$arg $wl$flag" compiler_flags="$compiler_flags $flag" done IFS="$save_ifs" arg=`$echo "X$arg" | $Xsed -e "s/^ //"` ;; -Wl,*) args=`$echo "X$arg" | $Xsed -e "$sed_quote_subst" -e 's/^-Wl,//'` arg= save_ifs="$IFS"; IFS=',' for flag in $args; do IFS="$save_ifs" case $flag in *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*|"") flag="\"$flag\"" ;; esac arg="$arg $wl$flag" compiler_flags="$compiler_flags $wl$flag" linker_flags="$linker_flags $flag" done IFS="$save_ifs" arg=`$echo "X$arg" | $Xsed -e "s/^ //"` ;; -Xcompiler) prev=xcompiler continue ;; -Xlinker) prev=xlinker continue ;; -XCClinker) prev=xcclinker continue ;; # Some other compiler flag. -* | +*) # Unknown arguments in both finalize_command and compile_command need # to be aesthetically quoted because they are evaled later. arg=`$echo "X$arg" | $Xsed -e "$sed_quote_subst"` case $arg in *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*|"") arg="\"$arg\"" ;; esac ;; *.$objext) # A standard object. objs="$objs $arg" ;; *.lo) # A libtool-controlled object. # Check to see that this really is a libtool object. if (${SED} -e '2q' $arg | grep "^# Generated by .*$PACKAGE") >/dev/null 2>&1; then pic_object= non_pic_object= # Read the .lo file # If there is no directory component, then add one. case $arg in */* | *\\*) . $arg ;; *) . ./$arg ;; esac if test -z "$pic_object" || \ test -z "$non_pic_object" || test "$pic_object" = none && \ test "$non_pic_object" = none; then $echo "$modename: cannot find name of object for \`$arg'" 1>&2 exit $EXIT_FAILURE fi # Extract subdirectory from the argument. xdir=`$echo "X$arg" | $Xsed -e 's%/[^/]*$%%'` if test "X$xdir" = "X$arg"; then xdir= else xdir="$xdir/" fi if test "$pic_object" != none; then # Prepend the subdirectory the object is found in. pic_object="$xdir$pic_object" if test "$prev" = dlfiles; then if test "$build_libtool_libs" = yes && test "$dlopen_support" = yes; then dlfiles="$dlfiles $pic_object" prev= continue else # If libtool objects are unsupported, then we need to preload. prev=dlprefiles fi fi # CHECK ME: I think I busted this. -Ossama if test "$prev" = dlprefiles; then # Preload the old-style object. dlprefiles="$dlprefiles $pic_object" prev= fi # A PIC object. libobjs="$libobjs $pic_object" arg="$pic_object" fi # Non-PIC object. if test "$non_pic_object" != none; then # Prepend the subdirectory the object is found in. non_pic_object="$xdir$non_pic_object" # A standard non-PIC object non_pic_objects="$non_pic_objects $non_pic_object" if test -z "$pic_object" || test "$pic_object" = none ; then arg="$non_pic_object" fi else # If the PIC object exists, use it instead. # $xdir was prepended to $pic_object above. non_pic_object="$pic_object" non_pic_objects="$non_pic_objects $non_pic_object" fi else # Only an error if not doing a dry-run. if test -z "$run"; then $echo "$modename: \`$arg' is not a valid libtool object" 1>&2 exit $EXIT_FAILURE else # Dry-run case. # Extract subdirectory from the argument. xdir=`$echo "X$arg" | $Xsed -e 's%/[^/]*$%%'` if test "X$xdir" = "X$arg"; then xdir= else xdir="$xdir/" fi pic_object=`$echo "X${xdir}${objdir}/${arg}" | $Xsed -e "$lo2o"` non_pic_object=`$echo "X${xdir}${arg}" | $Xsed -e "$lo2o"` libobjs="$libobjs $pic_object" non_pic_objects="$non_pic_objects $non_pic_object" fi fi ;; *.$libext) # An archive. deplibs="$deplibs $arg" old_deplibs="$old_deplibs $arg" continue ;; *.la) # A libtool-controlled library. if test "$prev" = dlfiles; then # This library was specified with -dlopen. dlfiles="$dlfiles $arg" prev= elif test "$prev" = dlprefiles; then # The library was specified with -dlpreopen. dlprefiles="$dlprefiles $arg" prev= else deplibs="$deplibs $arg" fi continue ;; # Some other compiler argument. *) # Unknown arguments in both finalize_command and compile_command need # to be aesthetically quoted because they are evaled later. arg=`$echo "X$arg" | $Xsed -e "$sed_quote_subst"` case $arg in *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*|"") arg="\"$arg\"" ;; esac ;; esac # arg # Now actually substitute the argument into the commands. if test -n "$arg"; then compile_command="$compile_command $arg" finalize_command="$finalize_command $arg" fi done # argument parsing loop if test -n "$prev"; then $echo "$modename: the \`$prevarg' option requires an argument" 1>&2 $echo "$help" 1>&2 exit $EXIT_FAILURE fi if test "$export_dynamic" = yes && test -n "$export_dynamic_flag_spec"; then eval arg=\"$export_dynamic_flag_spec\" compile_command="$compile_command $arg" finalize_command="$finalize_command $arg" fi oldlibs= # calculate the name of the file, without its directory outputname=`$echo "X$output" | $Xsed -e 's%^.*/%%'` libobjs_save="$libobjs" if test -n "$shlibpath_var"; then # get the directories listed in $shlibpath_var eval shlib_search_path=\`\$echo \"X\${$shlibpath_var}\" \| \$Xsed -e \'s/:/ /g\'\` else shlib_search_path= fi eval sys_lib_search_path=\"$sys_lib_search_path_spec\" eval sys_lib_dlsearch_path=\"$sys_lib_dlsearch_path_spec\" output_objdir=`$echo "X$output" | $Xsed -e 's%/[^/]*$%%'` if test "X$output_objdir" = "X$output"; then output_objdir="$objdir" else output_objdir="$output_objdir/$objdir" fi # Create the object directory. if test ! -d "$output_objdir"; then $show "$mkdir $output_objdir" $run $mkdir $output_objdir exit_status=$? if test "$exit_status" -ne 0 && test ! -d "$output_objdir"; then exit $exit_status fi fi # Determine the type of output case $output in "") $echo "$modename: you must specify an output file" 1>&2 $echo "$help" 1>&2 exit $EXIT_FAILURE ;; *.$libext) linkmode=oldlib ;; *.lo | *.$objext) linkmode=obj ;; *.la) linkmode=lib ;; *) linkmode=prog ;; # Anything else should be a program. esac case $host in *cygwin* | *mingw* | *pw32*) # don't eliminate duplications in $postdeps and $predeps duplicate_compiler_generated_deps=yes ;; *) duplicate_compiler_generated_deps=$duplicate_deps ;; esac specialdeplibs= libs= # Find all interdependent deplibs by searching for libraries # that are linked more than once (e.g. -la -lb -la) for deplib in $deplibs; do if test "X$duplicate_deps" = "Xyes" ; then case "$libs " in *" $deplib "*) specialdeplibs="$specialdeplibs $deplib" ;; esac fi libs="$libs $deplib" done if test "$linkmode" = lib; then libs="$predeps $libs $compiler_lib_search_path $postdeps" # Compute libraries that are listed more than once in $predeps # $postdeps and mark them as special (i.e., whose duplicates are # not to be eliminated). pre_post_deps= if test "X$duplicate_compiler_generated_deps" = "Xyes" ; then for pre_post_dep in $predeps $postdeps; do case "$pre_post_deps " in *" $pre_post_dep "*) specialdeplibs="$specialdeplibs $pre_post_deps" ;; esac pre_post_deps="$pre_post_deps $pre_post_dep" done fi pre_post_deps= fi deplibs= newdependency_libs= newlib_search_path= need_relink=no # whether we're linking any uninstalled libtool libraries notinst_deplibs= # not-installed libtool libraries case $linkmode in lib) passes="conv link" for file in $dlfiles $dlprefiles; do case $file in *.la) ;; *) $echo "$modename: libraries can \`-dlopen' only libtool libraries: $file" 1>&2 exit $EXIT_FAILURE ;; esac done ;; prog) compile_deplibs= finalize_deplibs= alldeplibs=no newdlfiles= newdlprefiles= passes="conv scan dlopen dlpreopen link" ;; *) passes="conv" ;; esac for pass in $passes; do if test "$linkmode,$pass" = "lib,link" || test "$linkmode,$pass" = "prog,scan"; then libs="$deplibs" deplibs= fi if test "$linkmode" = prog; then case $pass in dlopen) libs="$dlfiles" ;; dlpreopen) libs="$dlprefiles" ;; link) libs="$deplibs %DEPLIBS% $dependency_libs" ;; esac fi if test "$pass" = dlopen; then # Collect dlpreopened libraries save_deplibs="$deplibs" deplibs= fi for deplib in $libs; do lib= found=no case $deplib in -mt|-mthreads|-kthread|-Kthread|-pthread|-pthreads|--thread-safe|-threads) if test "$linkmode,$pass" = "prog,link"; then compile_deplibs="$deplib $compile_deplibs" finalize_deplibs="$deplib $finalize_deplibs" else compiler_flags="$compiler_flags $deplib" fi continue ;; -l*) if test "$linkmode" != lib && test "$linkmode" != prog; then $echo "$modename: warning: \`-l' is ignored for archives/objects" 1>&2 continue fi name=`$echo "X$deplib" | $Xsed -e 's/^-l//'` for searchdir in $newlib_search_path $lib_search_path $sys_lib_search_path $shlib_search_path; do for search_ext in .la $std_shrext .so .a; do # Search the libtool library lib="$searchdir/lib${name}${search_ext}" if test -f "$lib"; then if test "$search_ext" = ".la"; then found=yes else found=no fi break 2 fi done done if test "$found" != yes; then # deplib doesn't seem to be a libtool library if test "$linkmode,$pass" = "prog,link"; then compile_deplibs="$deplib $compile_deplibs" finalize_deplibs="$deplib $finalize_deplibs" else deplibs="$deplib $deplibs" test "$linkmode" = lib && newdependency_libs="$deplib $newdependency_libs" fi continue else # deplib is a libtool library # If $allow_libtool_libs_with_static_runtimes && $deplib is a stdlib, # We need to do some special things here, and not later. if test "X$allow_libtool_libs_with_static_runtimes" = "Xyes" ; then case " $predeps $postdeps " in *" $deplib "*) if (${SED} -e '2q' $lib | grep "^# Generated by .*$PACKAGE") >/dev/null 2>&1; then library_names= old_library= case $lib in */* | *\\*) . $lib ;; *) . ./$lib ;; esac for l in $old_library $library_names; do ll="$l" done if test "X$ll" = "X$old_library" ; then # only static version available found=no ladir=`$echo "X$lib" | $Xsed -e 's%/[^/]*$%%'` test "X$ladir" = "X$lib" && ladir="." lib=$ladir/$old_library if test "$linkmode,$pass" = "prog,link"; then compile_deplibs="$deplib $compile_deplibs" finalize_deplibs="$deplib $finalize_deplibs" else deplibs="$deplib $deplibs" test "$linkmode" = lib && newdependency_libs="$deplib $newdependency_libs" fi continue fi fi ;; *) ;; esac fi fi ;; # -l -L*) case $linkmode in lib) deplibs="$deplib $deplibs" test "$pass" = conv && continue newdependency_libs="$deplib $newdependency_libs" newlib_search_path="$newlib_search_path "`$echo "X$deplib" | $Xsed -e 's/^-L//'` ;; prog) if test "$pass" = conv; then deplibs="$deplib $deplibs" continue fi if test "$pass" = scan; then deplibs="$deplib $deplibs" else compile_deplibs="$deplib $compile_deplibs" finalize_deplibs="$deplib $finalize_deplibs" fi newlib_search_path="$newlib_search_path "`$echo "X$deplib" | $Xsed -e 's/^-L//'` ;; *) $echo "$modename: warning: \`-L' is ignored for archives/objects" 1>&2 ;; esac # linkmode continue ;; # -L -R*) if test "$pass" = link; then dir=`$echo "X$deplib" | $Xsed -e 's/^-R//'` # Make sure the xrpath contains only unique directories. case "$xrpath " in *" $dir "*) ;; *) xrpath="$xrpath $dir" ;; esac fi deplibs="$deplib $deplibs" continue ;; *.la) lib="$deplib" ;; *.$libext) if test "$pass" = conv; then deplibs="$deplib $deplibs" continue fi case $linkmode in lib) valid_a_lib=no case $deplibs_check_method in match_pattern*) set dummy $deplibs_check_method match_pattern_regex=`expr "$deplibs_check_method" : "$2 \(.*\)"` if eval $echo \"$deplib\" 2>/dev/null \ | $SED 10q \ | $EGREP "$match_pattern_regex" > /dev/null; then valid_a_lib=yes fi ;; pass_all) valid_a_lib=yes ;; esac if test "$valid_a_lib" != yes; then $echo $echo "*** Warning: Trying to link with static lib archive $deplib." $echo "*** I have the capability to make that library automatically link in when" $echo "*** you link to this library. But I can only do this if you have a" $echo "*** shared version of the library, which you do not appear to have" $echo "*** because the file extensions .$libext of this argument makes me believe" $echo "*** that it is just a static archive that I should not used here." else $echo $echo "*** Warning: Linking the shared library $output against the" $echo "*** static library $deplib is not portable!" deplibs="$deplib $deplibs" fi continue ;; prog) if test "$pass" != link; then deplibs="$deplib $deplibs" else compile_deplibs="$deplib $compile_deplibs" finalize_deplibs="$deplib $finalize_deplibs" fi continue ;; esac # linkmode ;; # *.$libext *.lo | *.$objext) if test "$pass" = conv; then deplibs="$deplib $deplibs" elif test "$linkmode" = prog; then if test "$pass" = dlpreopen || test "$dlopen_support" != yes || test "$build_libtool_libs" = no; then # If there is no dlopen support or we're linking statically, # we need to preload. newdlprefiles="$newdlprefiles $deplib" compile_deplibs="$deplib $compile_deplibs" finalize_deplibs="$deplib $finalize_deplibs" else newdlfiles="$newdlfiles $deplib" fi fi continue ;; %DEPLIBS%) alldeplibs=yes continue ;; esac # case $deplib if test "$found" = yes || test -f "$lib"; then : else $echo "$modename: cannot find the library \`$lib' or unhandled argument \`$deplib'" 1>&2 exit $EXIT_FAILURE fi # Check to see that this really is a libtool archive. if (${SED} -e '2q' $lib | grep "^# Generated by .*$PACKAGE") >/dev/null 2>&1; then : else $echo "$modename: \`$lib' is not a valid libtool archive" 1>&2 exit $EXIT_FAILURE fi ladir=`$echo "X$lib" | $Xsed -e 's%/[^/]*$%%'` test "X$ladir" = "X$lib" && ladir="." dlname= dlopen= dlpreopen= libdir= library_names= old_library= # If the library was installed with an old release of libtool, # it will not redefine variables installed, or shouldnotlink installed=yes shouldnotlink=no avoidtemprpath= # Read the .la file case $lib in */* | *\\*) . $lib ;; *) . ./$lib ;; esac if test "$linkmode,$pass" = "lib,link" || test "$linkmode,$pass" = "prog,scan" || { test "$linkmode" != prog && test "$linkmode" != lib; }; then test -n "$dlopen" && dlfiles="$dlfiles $dlopen" test -n "$dlpreopen" && dlprefiles="$dlprefiles $dlpreopen" fi if test "$pass" = conv; then # Only check for convenience libraries deplibs="$lib $deplibs" if test -z "$libdir"; then if test -z "$old_library"; then $echo "$modename: cannot find name of link library for \`$lib'" 1>&2 exit $EXIT_FAILURE fi # It is a libtool convenience library, so add in its objects. convenience="$convenience $ladir/$objdir/$old_library" old_convenience="$old_convenience $ladir/$objdir/$old_library" tmp_libs= for deplib in $dependency_libs; do deplibs="$deplib $deplibs" if test "X$duplicate_deps" = "Xyes" ; then case "$tmp_libs " in *" $deplib "*) specialdeplibs="$specialdeplibs $deplib" ;; esac fi tmp_libs="$tmp_libs $deplib" done elif test "$linkmode" != prog && test "$linkmode" != lib; then $echo "$modename: \`$lib' is not a convenience library" 1>&2 exit $EXIT_FAILURE fi continue fi # $pass = conv # Get the name of the library we link against. linklib= for l in $old_library $library_names; do linklib="$l" done if test -z "$linklib"; then $echo "$modename: cannot find name of link library for \`$lib'" 1>&2 exit $EXIT_FAILURE fi # This library was specified with -dlopen. if test "$pass" = dlopen; then if test -z "$libdir"; then $echo "$modename: cannot -dlopen a convenience library: \`$lib'" 1>&2 exit $EXIT_FAILURE fi if test -z "$dlname" || test "$dlopen_support" != yes || test "$build_libtool_libs" = no; then # If there is no dlname, no dlopen support or we're linking # statically, we need to preload. We also need to preload any # dependent libraries so libltdl's deplib preloader doesn't # bomb out in the load deplibs phase. dlprefiles="$dlprefiles $lib $dependency_libs" else newdlfiles="$newdlfiles $lib" fi continue fi # $pass = dlopen # We need an absolute path. case $ladir in [\\/]* | [A-Za-z]:[\\/]*) abs_ladir="$ladir" ;; *) abs_ladir=`cd "$ladir" && pwd` if test -z "$abs_ladir"; then $echo "$modename: warning: cannot determine absolute directory name of \`$ladir'" 1>&2 $echo "$modename: passing it literally to the linker, although it might fail" 1>&2 abs_ladir="$ladir" fi ;; esac laname=`$echo "X$lib" | $Xsed -e 's%^.*/%%'` # Find the relevant object directory and library name. if test "X$installed" = Xyes; then if test ! -f "$libdir/$linklib" && test -f "$abs_ladir/$linklib"; then $echo "$modename: warning: library \`$lib' was moved." 1>&2 dir="$ladir" absdir="$abs_ladir" libdir="$abs_ladir" else dir="$libdir" absdir="$libdir" fi test "X$hardcode_automatic" = Xyes && avoidtemprpath=yes else if test ! -f "$ladir/$objdir/$linklib" && test -f "$abs_ladir/$linklib"; then dir="$ladir" absdir="$abs_ladir" # Remove this search path later notinst_path="$notinst_path $abs_ladir" else dir="$ladir/$objdir" absdir="$abs_ladir/$objdir" # Remove this search path later notinst_path="$notinst_path $abs_ladir" fi fi # $installed = yes name=`$echo "X$laname" | $Xsed -e 's/\.la$//' -e 's/^lib//'` # This library was specified with -dlpreopen. if test "$pass" = dlpreopen; then if test -z "$libdir"; then $echo "$modename: cannot -dlpreopen a convenience library: \`$lib'" 1>&2 exit $EXIT_FAILURE fi # Prefer using a static library (so that no silly _DYNAMIC symbols # are required to link). if test -n "$old_library"; then newdlprefiles="$newdlprefiles $dir/$old_library" # Otherwise, use the dlname, so that lt_dlopen finds it. elif test -n "$dlname"; then newdlprefiles="$newdlprefiles $dir/$dlname" else newdlprefiles="$newdlprefiles $dir/$linklib" fi fi # $pass = dlpreopen if test -z "$libdir"; then # Link the convenience library if test "$linkmode" = lib; then deplibs="$dir/$old_library $deplibs" elif test "$linkmode,$pass" = "prog,link"; then compile_deplibs="$dir/$old_library $compile_deplibs" finalize_deplibs="$dir/$old_library $finalize_deplibs" else deplibs="$lib $deplibs" # used for prog,scan pass fi continue fi if test "$linkmode" = prog && test "$pass" != link; then newlib_search_path="$newlib_search_path $ladir" deplibs="$lib $deplibs" linkalldeplibs=no if test "$link_all_deplibs" != no || test -z "$library_names" || test "$build_libtool_libs" = no; then linkalldeplibs=yes fi tmp_libs= for deplib in $dependency_libs; do case $deplib in -L*) newlib_search_path="$newlib_search_path "`$echo "X$deplib" | $Xsed -e 's/^-L//'`;; ### testsuite: skip nested quoting test esac # Need to link against all dependency_libs? if test "$linkalldeplibs" = yes; then deplibs="$deplib $deplibs" else # Need to hardcode shared library paths # or/and link against static libraries newdependency_libs="$deplib $newdependency_libs" fi if test "X$duplicate_deps" = "Xyes" ; then case "$tmp_libs " in *" $deplib "*) specialdeplibs="$specialdeplibs $deplib" ;; esac fi tmp_libs="$tmp_libs $deplib" done # for deplib continue fi # $linkmode = prog... if test "$linkmode,$pass" = "prog,link"; then if test -n "$library_names" && { { test "$prefer_static_libs" = no || test "$prefer_static_libs,$installed" = "built,yes"; } || test -z "$old_library"; }; then # We need to hardcode the library path if test -n "$shlibpath_var" && test -z "$avoidtemprpath" ; then # Make sure the rpath contains only unique directories. case "$temp_rpath " in *" $dir "*) ;; *" $absdir "*) ;; *) temp_rpath="$temp_rpath $absdir" ;; esac fi # Hardcode the library path. # Skip directories that are in the system default run-time # search path. case " $sys_lib_dlsearch_path " in *" $absdir "*) ;; *) case "$compile_rpath " in *" $absdir "*) ;; *) compile_rpath="$compile_rpath $absdir" esac ;; esac case " $sys_lib_dlsearch_path " in *" $libdir "*) ;; *) case "$finalize_rpath " in *" $libdir "*) ;; *) finalize_rpath="$finalize_rpath $libdir" esac ;; esac fi # $linkmode,$pass = prog,link... if test "$alldeplibs" = yes && { test "$deplibs_check_method" = pass_all || { test "$build_libtool_libs" = yes && test -n "$library_names"; }; }; then # We only need to search for static libraries continue fi fi link_static=no # Whether the deplib will be linked statically use_static_libs=$prefer_static_libs if test "$use_static_libs" = built && test "$installed" = yes ; then use_static_libs=no fi if test -n "$library_names" && { test "$use_static_libs" = no || test -z "$old_library"; }; then if test "$installed" = no; then notinst_deplibs="$notinst_deplibs $lib" need_relink=yes fi # This is a shared library # Warn about portability, can't link against -module's on # some systems (darwin) if test "$shouldnotlink" = yes && test "$pass" = link ; then $echo if test "$linkmode" = prog; then $echo "*** Warning: Linking the executable $output against the loadable module" else $echo "*** Warning: Linking the shared library $output against the loadable module" fi $echo "*** $linklib is not portable!" fi if test "$linkmode" = lib && test "$hardcode_into_libs" = yes; then # Hardcode the library path. # Skip directories that are in the system default run-time # search path. case " $sys_lib_dlsearch_path " in *" $absdir "*) ;; *) case "$compile_rpath " in *" $absdir "*) ;; *) compile_rpath="$compile_rpath $absdir" esac ;; esac case " $sys_lib_dlsearch_path " in *" $libdir "*) ;; *) case "$finalize_rpath " in *" $libdir "*) ;; *) finalize_rpath="$finalize_rpath $libdir" esac ;; esac fi if test -n "$old_archive_from_expsyms_cmds"; then # figure out the soname set dummy $library_names realname="$2" shift; shift libname=`eval \\$echo \"$libname_spec\"` # use dlname if we got it. it's perfectly good, no? if test -n "$dlname"; then soname="$dlname" elif test -n "$soname_spec"; then # bleh windows case $host in *cygwin* | mingw*) major=`expr $current - $age` versuffix="-$major" ;; esac eval soname=\"$soname_spec\" else soname="$realname" fi # Make a new name for the extract_expsyms_cmds to use soroot="$soname" soname=`$echo $soroot | ${SED} -e 's/^.*\///'` newlib="libimp-`$echo $soname | ${SED} 's/^lib//;s/\.dll$//'`.a" # If the library has no export list, then create one now if test -f "$output_objdir/$soname-def"; then : else $show "extracting exported symbol list from \`$soname'" save_ifs="$IFS"; IFS='~' cmds=$extract_expsyms_cmds for cmd in $cmds; do IFS="$save_ifs" eval cmd=\"$cmd\" $show "$cmd" $run eval "$cmd" || exit $? done IFS="$save_ifs" fi # Create $newlib if test -f "$output_objdir/$newlib"; then :; else $show "generating import library for \`$soname'" save_ifs="$IFS"; IFS='~' cmds=$old_archive_from_expsyms_cmds for cmd in $cmds; do IFS="$save_ifs" eval cmd=\"$cmd\" $show "$cmd" $run eval "$cmd" || exit $? done IFS="$save_ifs" fi # make sure the library variables are pointing to the new library dir=$output_objdir linklib=$newlib fi # test -n "$old_archive_from_expsyms_cmds" if test "$linkmode" = prog || test "$mode" != relink; then add_shlibpath= add_dir= add= lib_linked=yes case $hardcode_action in immediate | unsupported) if test "$hardcode_direct" = no; then add="$dir/$linklib" case $host in *-*-sco3.2v5.0.[024]*) add_dir="-L$dir" ;; *-*-sysv4*uw2*) add_dir="-L$dir" ;; *-*-sysv5OpenUNIX* | *-*-sysv5UnixWare7.[01].[10]* | \ *-*-unixware7*) add_dir="-L$dir" ;; *-*-darwin* ) # if the lib is a module then we can not link against # it, someone is ignoring the new warnings I added if /usr/bin/file -L $add 2> /dev/null | $EGREP ": [^:]* bundle" >/dev/null ; then $echo "** Warning, lib $linklib is a module, not a shared library" if test -z "$old_library" ; then $echo $echo "** And there doesn't seem to be a static archive available" $echo "** The link will probably fail, sorry" else add="$dir/$old_library" fi fi esac elif test "$hardcode_minus_L" = no; then case $host in *-*-sunos*) add_shlibpath="$dir" ;; esac add_dir="-L$dir" add="-l$name" elif test "$hardcode_shlibpath_var" = no; then add_shlibpath="$dir" add="-l$name" else lib_linked=no fi ;; relink) if test "$hardcode_direct" = yes; then add="$dir/$linklib" elif test "$hardcode_minus_L" = yes; then add_dir="-L$dir" # Try looking first in the location we're being installed to. if test -n "$inst_prefix_dir"; then case $libdir in [\\/]*) add_dir="$add_dir -L$inst_prefix_dir$libdir" ;; esac fi add="-l$name" elif test "$hardcode_shlibpath_var" = yes; then add_shlibpath="$dir" add="-l$name" else lib_linked=no fi ;; *) lib_linked=no ;; esac if test "$lib_linked" != yes; then $echo "$modename: configuration error: unsupported hardcode properties" exit $EXIT_FAILURE fi if test -n "$add_shlibpath"; then case :$compile_shlibpath: in *":$add_shlibpath:"*) ;; *) compile_shlibpath="$compile_shlibpath$add_shlibpath:" ;; esac fi if test "$linkmode" = prog; then test -n "$add_dir" && compile_deplibs="$add_dir $compile_deplibs" test -n "$add" && compile_deplibs="$add $compile_deplibs" else test -n "$add_dir" && deplibs="$add_dir $deplibs" test -n "$add" && deplibs="$add $deplibs" if test "$hardcode_direct" != yes && \ test "$hardcode_minus_L" != yes && \ test "$hardcode_shlibpath_var" = yes; then case :$finalize_shlibpath: in *":$libdir:"*) ;; *) finalize_shlibpath="$finalize_shlibpath$libdir:" ;; esac fi fi fi if test "$linkmode" = prog || test "$mode" = relink; then add_shlibpath= add_dir= add= # Finalize command for both is simple: just hardcode it. if test "$hardcode_direct" = yes; then add="$libdir/$linklib" elif test "$hardcode_minus_L" = yes; then add_dir="-L$libdir" add="-l$name" elif test "$hardcode_shlibpath_var" = yes; then case :$finalize_shlibpath: in *":$libdir:"*) ;; *) finalize_shlibpath="$finalize_shlibpath$libdir:" ;; esac add="-l$name" elif test "$hardcode_automatic" = yes; then if test -n "$inst_prefix_dir" && test -f "$inst_prefix_dir$libdir/$linklib" ; then add="$inst_prefix_dir$libdir/$linklib" else add="$libdir/$linklib" fi else # We cannot seem to hardcode it, guess we'll fake it. add_dir="-L$libdir" # Try looking first in the location we're being installed to. if test -n "$inst_prefix_dir"; then case $libdir in [\\/]*) add_dir="$add_dir -L$inst_prefix_dir$libdir" ;; esac fi add="-l$name" fi if test "$linkmode" = prog; then test -n "$add_dir" && finalize_deplibs="$add_dir $finalize_deplibs" test -n "$add" && finalize_deplibs="$add $finalize_deplibs" else test -n "$add_dir" && deplibs="$add_dir $deplibs" test -n "$add" && deplibs="$add $deplibs" fi fi elif test "$linkmode" = prog; then # Here we assume that one of hardcode_direct or hardcode_minus_L # is not unsupported. This is valid on all known static and # shared platforms. if test "$hardcode_direct" != unsupported; then test -n "$old_library" && linklib="$old_library" compile_deplibs="$dir/$linklib $compile_deplibs" finalize_deplibs="$dir/$linklib $finalize_deplibs" else compile_deplibs="-l$name -L$dir $compile_deplibs" finalize_deplibs="-l$name -L$dir $finalize_deplibs" fi elif test "$build_libtool_libs" = yes; then # Not a shared library if test "$deplibs_check_method" != pass_all; then # We're trying link a shared library against a static one # but the system doesn't support it. # Just print a warning and add the library to dependency_libs so # that the program can be linked against the static library. $echo $echo "*** Warning: This system can not link to static lib archive $lib." $echo "*** I have the capability to make that library automatically link in when" $echo "*** you link to this library. But I can only do this if you have a" $echo "*** shared version of the library, which you do not appear to have." if test "$module" = yes; then $echo "*** But as you try to build a module library, libtool will still create " $echo "*** a static module, that should work as long as the dlopening application" $echo "*** is linked with the -dlopen flag to resolve symbols at runtime." if test -z "$global_symbol_pipe"; then $echo $echo "*** However, this would only work if libtool was able to extract symbol" $echo "*** lists from a program, using \`nm' or equivalent, but libtool could" $echo "*** not find such a program. So, this module is probably useless." $echo "*** \`nm' from GNU binutils and a full rebuild may help." fi if test "$build_old_libs" = no; then build_libtool_libs=module build_old_libs=yes else build_libtool_libs=no fi fi else deplibs="$dir/$old_library $deplibs" link_static=yes fi fi # link shared/static library? if test "$linkmode" = lib; then if test -n "$dependency_libs" && { test "$hardcode_into_libs" != yes || test "$build_old_libs" = yes || test "$link_static" = yes; }; then # Extract -R from dependency_libs temp_deplibs= for libdir in $dependency_libs; do case $libdir in -R*) temp_xrpath=`$echo "X$libdir" | $Xsed -e 's/^-R//'` case " $xrpath " in *" $temp_xrpath "*) ;; *) xrpath="$xrpath $temp_xrpath";; esac;; *) temp_deplibs="$temp_deplibs $libdir";; esac done dependency_libs="$temp_deplibs" fi newlib_search_path="$newlib_search_path $absdir" # Link against this library test "$link_static" = no && newdependency_libs="$abs_ladir/$laname $newdependency_libs" # ... and its dependency_libs tmp_libs= for deplib in $dependency_libs; do newdependency_libs="$deplib $newdependency_libs" if test "X$duplicate_deps" = "Xyes" ; then case "$tmp_libs " in *" $deplib "*) specialdeplibs="$specialdeplibs $deplib" ;; esac fi tmp_libs="$tmp_libs $deplib" done if test "$link_all_deplibs" != no; then # Add the search paths of all dependency libraries for deplib in $dependency_libs; do case $deplib in -L*) path="$deplib" ;; *.la) dir=`$echo "X$deplib" | $Xsed -e 's%/[^/]*$%%'` test "X$dir" = "X$deplib" && dir="." # We need an absolute path. case $dir in [\\/]* | [A-Za-z]:[\\/]*) absdir="$dir" ;; *) absdir=`cd "$dir" && pwd` if test -z "$absdir"; then $echo "$modename: warning: cannot determine absolute directory name of \`$dir'" 1>&2 absdir="$dir" fi ;; esac if grep "^installed=no" $deplib > /dev/null; then path="$absdir/$objdir" else eval libdir=`${SED} -n -e 's/^libdir=\(.*\)$/\1/p' $deplib` if test -z "$libdir"; then $echo "$modename: \`$deplib' is not a valid libtool archive" 1>&2 exit $EXIT_FAILURE fi #if test "$absdir" != "$libdir"; then # $echo "$modename: warning: \`$deplib' seems to be moved" 1>&2 #fi path="$absdir" fi depdepl= case $host in *-*-darwin*) # we do not want to link against static libs, # but need to link against shared eval deplibrary_names=`${SED} -n -e 's/^library_names=\(.*\)$/\1/p' $deplib` if test -n "$deplibrary_names" ; then for tmp in $deplibrary_names ; do depdepl=$tmp done if test -f "$path/$depdepl" ; then depdepl="$path/$depdepl" fi # do not add paths which are already there case " $newlib_search_path " in *" $path "*) ;; *) newlib_search_path="$newlib_search_path $path";; esac fi path="" ;; *) path="-L$path" ;; esac ;; -l*) case $host in *-*-darwin*) # Again, we only want to link against shared libraries eval tmp_libs=`$echo "X$deplib" | $Xsed -e "s,^\-l,,"` for tmp in $newlib_search_path ; do if test -f "$tmp/lib$tmp_libs.dylib" ; then eval depdepl="$tmp/lib$tmp_libs.dylib" break fi done path="" ;; *) continue ;; esac ;; *) continue ;; esac case " $deplibs " in *" $path "*) ;; *) deplibs="$path $deplibs" ;; esac case " $deplibs " in *" $depdepl "*) ;; *) deplibs="$depdepl $deplibs" ;; esac done fi # link_all_deplibs != no fi # linkmode = lib done # for deplib in $libs dependency_libs="$newdependency_libs" if test "$pass" = dlpreopen; then # Link the dlpreopened libraries before other libraries for deplib in $save_deplibs; do deplibs="$deplib $deplibs" done fi if test "$pass" != dlopen; then if test "$pass" != conv; then # Make sure lib_search_path contains only unique directories. lib_search_path= for dir in $newlib_search_path; do case "$lib_search_path " in *" $dir "*) ;; *) lib_search_path="$lib_search_path $dir" ;; esac done newlib_search_path= fi if test "$linkmode,$pass" != "prog,link"; then vars="deplibs" else vars="compile_deplibs finalize_deplibs" fi for var in $vars dependency_libs; do # Add libraries to $var in reverse order eval tmp_libs=\"\$$var\" new_libs= for deplib in $tmp_libs; do # FIXME: Pedantically, this is the right thing to do, so # that some nasty dependency loop isn't accidentally # broken: #new_libs="$deplib $new_libs" # Pragmatically, this seems to cause very few problems in # practice: case $deplib in -L*) new_libs="$deplib $new_libs" ;; -R*) ;; *) # And here is the reason: when a library appears more # than once as an explicit dependence of a library, or # is implicitly linked in more than once by the # compiler, it is considered special, and multiple # occurrences thereof are not removed. Compare this # with having the same library being listed as a # dependency of multiple other libraries: in this case, # we know (pedantically, we assume) the library does not # need to be listed more than once, so we keep only the # last copy. This is not always right, but it is rare # enough that we require users that really mean to play # such unportable linking tricks to link the library # using -Wl,-lname, so that libtool does not consider it # for duplicate removal. case " $specialdeplibs " in *" $deplib "*) new_libs="$deplib $new_libs" ;; *) case " $new_libs " in *" $deplib "*) ;; *) new_libs="$deplib $new_libs" ;; esac ;; esac ;; esac done tmp_libs= for deplib in $new_libs; do case $deplib in -L*) case " $tmp_libs " in *" $deplib "*) ;; *) tmp_libs="$tmp_libs $deplib" ;; esac ;; *) tmp_libs="$tmp_libs $deplib" ;; esac done eval $var=\"$tmp_libs\" done # for var fi # Last step: remove runtime libs from dependency_libs # (they stay in deplibs) tmp_libs= for i in $dependency_libs ; do case " $predeps $postdeps $compiler_lib_search_path " in *" $i "*) i="" ;; esac if test -n "$i" ; then tmp_libs="$tmp_libs $i" fi done dependency_libs=$tmp_libs done # for pass if test "$linkmode" = prog; then dlfiles="$newdlfiles" dlprefiles="$newdlprefiles" fi case $linkmode in oldlib) if test -n "$deplibs"; then $echo "$modename: warning: \`-l' and \`-L' are ignored for archives" 1>&2 fi if test -n "$dlfiles$dlprefiles" || test "$dlself" != no; then $echo "$modename: warning: \`-dlopen' is ignored for archives" 1>&2 fi if test -n "$rpath"; then $echo "$modename: warning: \`-rpath' is ignored for archives" 1>&2 fi if test -n "$xrpath"; then $echo "$modename: warning: \`-R' is ignored for archives" 1>&2 fi if test -n "$vinfo"; then $echo "$modename: warning: \`-version-info/-version-number' is ignored for archives" 1>&2 fi if test -n "$release"; then $echo "$modename: warning: \`-release' is ignored for archives" 1>&2 fi if test -n "$export_symbols" || test -n "$export_symbols_regex"; then $echo "$modename: warning: \`-export-symbols' is ignored for archives" 1>&2 fi # Now set the variables for building old libraries. build_libtool_libs=no oldlibs="$output" objs="$objs$old_deplibs" ;; lib) # Make sure we only generate libraries of the form `libNAME.la'. case $outputname in lib*) name=`$echo "X$outputname" | $Xsed -e 's/\.la$//' -e 's/^lib//'` eval shared_ext=\"$shrext_cmds\" eval libname=\"$libname_spec\" ;; *) if test "$module" = no; then $echo "$modename: libtool library \`$output' must begin with \`lib'" 1>&2 $echo "$help" 1>&2 exit $EXIT_FAILURE fi if test "$need_lib_prefix" != no; then # Add the "lib" prefix for modules if required name=`$echo "X$outputname" | $Xsed -e 's/\.la$//'` eval shared_ext=\"$shrext_cmds\" eval libname=\"$libname_spec\" else libname=`$echo "X$outputname" | $Xsed -e 's/\.la$//'` fi ;; esac if test -n "$objs"; then if test "$deplibs_check_method" != pass_all; then $echo "$modename: cannot build libtool library \`$output' from non-libtool objects on this host:$objs" 2>&1 exit $EXIT_FAILURE else $echo $echo "*** Warning: Linking the shared library $output against the non-libtool" $echo "*** objects $objs is not portable!" libobjs="$libobjs $objs" fi fi if test "$dlself" != no; then $echo "$modename: warning: \`-dlopen self' is ignored for libtool libraries" 1>&2 fi set dummy $rpath if test "$#" -gt 2; then $echo "$modename: warning: ignoring multiple \`-rpath's for a libtool library" 1>&2 fi install_libdir="$2" oldlibs= if test -z "$rpath"; then if test "$build_libtool_libs" = yes; then # Building a libtool convenience library. # Some compilers have problems with a `.al' extension so # convenience libraries should have the same extension an # archive normally would. oldlibs="$output_objdir/$libname.$libext $oldlibs" build_libtool_libs=convenience build_old_libs=yes fi if test -n "$vinfo"; then $echo "$modename: warning: \`-version-info/-version-number' is ignored for convenience libraries" 1>&2 fi if test -n "$release"; then $echo "$modename: warning: \`-release' is ignored for convenience libraries" 1>&2 fi else # Parse the version information argument. save_ifs="$IFS"; IFS=':' set dummy $vinfo 0 0 0 IFS="$save_ifs" if test -n "$8"; then $echo "$modename: too many parameters to \`-version-info'" 1>&2 $echo "$help" 1>&2 exit $EXIT_FAILURE fi # convert absolute version numbers to libtool ages # this retains compatibility with .la files and attempts # to make the code below a bit more comprehensible case $vinfo_number in yes) number_major="$2" number_minor="$3" number_revision="$4" # # There are really only two kinds -- those that # use the current revision as the major version # and those that subtract age and use age as # a minor version. But, then there is irix # which has an extra 1 added just for fun # case $version_type in darwin|linux|osf|windows|none) current=`expr $number_major + $number_minor` age="$number_minor" revision="$number_revision" ;; freebsd-aout|freebsd-elf|sunos) current="$number_major" revision="$number_minor" age="0" ;; irix|nonstopux) current=`expr $number_major + $number_minor` age="$number_minor" revision="$number_minor" lt_irix_increment=no ;; esac ;; no) current="$2" revision="$3" age="$4" ;; esac # Check that each of the things are valid numbers. case $current in 0|[1-9]|[1-9][0-9]|[1-9][0-9][0-9]|[1-9][0-9][0-9][0-9]|[1-9][0-9][0-9][0-9][0-9]) ;; *) $echo "$modename: CURRENT \`$current' must be a nonnegative integer" 1>&2 $echo "$modename: \`$vinfo' is not valid version information" 1>&2 exit $EXIT_FAILURE ;; esac case $revision in 0|[1-9]|[1-9][0-9]|[1-9][0-9][0-9]|[1-9][0-9][0-9][0-9]|[1-9][0-9][0-9][0-9][0-9]) ;; *) $echo "$modename: REVISION \`$revision' must be a nonnegative integer" 1>&2 $echo "$modename: \`$vinfo' is not valid version information" 1>&2 exit $EXIT_FAILURE ;; esac case $age in 0|[1-9]|[1-9][0-9]|[1-9][0-9][0-9]|[1-9][0-9][0-9][0-9]|[1-9][0-9][0-9][0-9][0-9]) ;; *) $echo "$modename: AGE \`$age' must be a nonnegative integer" 1>&2 $echo "$modename: \`$vinfo' is not valid version information" 1>&2 exit $EXIT_FAILURE ;; esac if test "$age" -gt "$current"; then $echo "$modename: AGE \`$age' is greater than the current interface number \`$current'" 1>&2 $echo "$modename: \`$vinfo' is not valid version information" 1>&2 exit $EXIT_FAILURE fi # Calculate the version variables. major= versuffix= verstring= case $version_type in none) ;; darwin) # Like Linux, but with the current version available in # verstring for coding it into the library header major=.`expr $current - $age` versuffix="$major.$age.$revision" # Darwin ld doesn't like 0 for these options... minor_current=`expr $current + 1` xlcverstring="${wl}-compatibility_version ${wl}$minor_current ${wl}-current_version ${wl}$minor_current.$revision" verstring="-compatibility_version $minor_current -current_version $minor_current.$revision" ;; freebsd-aout) major=".$current" versuffix=".$current.$revision"; ;; freebsd-elf) major=".$current" versuffix=".$current"; ;; irix | nonstopux) if test "X$lt_irix_increment" = "Xno"; then major=`expr $current - $age` else major=`expr $current - $age + 1` fi case $version_type in nonstopux) verstring_prefix=nonstopux ;; *) verstring_prefix=sgi ;; esac verstring="$verstring_prefix$major.$revision" # Add in all the interfaces that we are compatible with. loop=$revision while test "$loop" -ne 0; do iface=`expr $revision - $loop` loop=`expr $loop - 1` verstring="$verstring_prefix$major.$iface:$verstring" done # Before this point, $major must not contain `.'. major=.$major versuffix="$major.$revision" ;; linux) major=.`expr $current - $age` versuffix="$major.$age.$revision" ;; osf) major=.`expr $current - $age` versuffix=".$current.$age.$revision" verstring="$current.$age.$revision" # Add in all the interfaces that we are compatible with. loop=$age while test "$loop" -ne 0; do iface=`expr $current - $loop` loop=`expr $loop - 1` verstring="$verstring:${iface}.0" done # Make executables depend on our current version. verstring="$verstring:${current}.0" ;; sunos) major=".$current" versuffix=".$current.$revision" ;; windows) # Use '-' rather than '.', since we only want one # extension on DOS 8.3 filesystems. major=`expr $current - $age` versuffix="-$major" ;; *) $echo "$modename: unknown library version type \`$version_type'" 1>&2 $echo "Fatal configuration error. See the $PACKAGE docs for more information." 1>&2 exit $EXIT_FAILURE ;; esac # Clear the version info if we defaulted, and they specified a release. if test -z "$vinfo" && test -n "$release"; then major= case $version_type in darwin) # we can't check for "0.0" in archive_cmds due to quoting # problems, so we reset it completely verstring= ;; *) verstring="0.0" ;; esac if test "$need_version" = no; then versuffix= else versuffix=".0.0" fi fi # Remove version info from name if versioning should be avoided if test "$avoid_version" = yes && test "$need_version" = no; then major= versuffix= verstring="" fi # Check to see if the archive will have undefined symbols. if test "$allow_undefined" = yes; then if test "$allow_undefined_flag" = unsupported; then $echo "$modename: warning: undefined symbols not allowed in $host shared libraries" 1>&2 build_libtool_libs=no build_old_libs=yes fi else # Don't allow undefined symbols. allow_undefined_flag="$no_undefined_flag" fi fi if test "$mode" != relink; then # Remove our outputs, but don't remove object files since they # may have been created when compiling PIC objects. removelist= tempremovelist=`$echo "$output_objdir/*"` for p in $tempremovelist; do case $p in *.$objext) ;; $output_objdir/$outputname | $output_objdir/$libname.* | $output_objdir/${libname}${release}.*) if test "X$precious_files_regex" != "X"; then if echo $p | $EGREP -e "$precious_files_regex" >/dev/null 2>&1 then continue fi fi removelist="$removelist $p" ;; *) ;; esac done if test -n "$removelist"; then $show "${rm}r $removelist" $run ${rm}r $removelist fi fi # Now set the variables for building old libraries. if test "$build_old_libs" = yes && test "$build_libtool_libs" != convenience ; then oldlibs="$oldlibs $output_objdir/$libname.$libext" # Transform .lo files to .o files. oldobjs="$objs "`$echo "X$libobjs" | $SP2NL | $Xsed -e '/\.'${libext}'$/d' -e "$lo2o" | $NL2SP` fi # Eliminate all temporary directories. #for path in $notinst_path; do # lib_search_path=`$echo "$lib_search_path " | ${SED} -e "s% $path % %g"` # deplibs=`$echo "$deplibs " | ${SED} -e "s% -L$path % %g"` # dependency_libs=`$echo "$dependency_libs " | ${SED} -e "s% -L$path % %g"` #done if test -n "$xrpath"; then # If the user specified any rpath flags, then add them. temp_xrpath= for libdir in $xrpath; do temp_xrpath="$temp_xrpath -R$libdir" case "$finalize_rpath " in *" $libdir "*) ;; *) finalize_rpath="$finalize_rpath $libdir" ;; esac done if test "$hardcode_into_libs" != yes || test "$build_old_libs" = yes; then dependency_libs="$temp_xrpath $dependency_libs" fi fi # Make sure dlfiles contains only unique files that won't be dlpreopened old_dlfiles="$dlfiles" dlfiles= for lib in $old_dlfiles; do case " $dlprefiles $dlfiles " in *" $lib "*) ;; *) dlfiles="$dlfiles $lib" ;; esac done # Make sure dlprefiles contains only unique files old_dlprefiles="$dlprefiles" dlprefiles= for lib in $old_dlprefiles; do case "$dlprefiles " in *" $lib "*) ;; *) dlprefiles="$dlprefiles $lib" ;; esac done if test "$build_libtool_libs" = yes; then if test -n "$rpath"; then case $host in *-*-cygwin* | *-*-mingw* | *-*-pw32* | *-*-os2* | *-*-beos*) # these systems don't actually have a c library (as such)! ;; *-*-rhapsody* | *-*-darwin1.[012]) # Rhapsody C library is in the System framework deplibs="$deplibs -framework System" ;; *-*-netbsd*) # Don't link with libc until the a.out ld.so is fixed. ;; *-*-openbsd* | *-*-freebsd* | *-*-dragonfly*) # Do not include libc due to us having libc/libc_r. ;; *-*-sco3.2v5* | *-*-sco5v6*) # Causes problems with __ctype ;; *-*-sysv4.2uw2* | *-*-sysv5* | *-*-unixware* | *-*-OpenUNIX*) # Compiler inserts libc in the correct place for threads to work ;; *) # Add libc to deplibs on all other systems if necessary. if test "$build_libtool_need_lc" = "yes"; then deplibs="$deplibs -lc" fi ;; esac fi # Transform deplibs into only deplibs that can be linked in shared. name_save=$name libname_save=$libname release_save=$release versuffix_save=$versuffix major_save=$major # I'm not sure if I'm treating the release correctly. I think # release should show up in the -l (ie -lgmp5) so we don't want to # add it in twice. Is that correct? release="" versuffix="" major="" newdeplibs= droppeddeps=no case $deplibs_check_method in pass_all) # Don't check for shared/static. Everything works. # This might be a little naive. We might want to check # whether the library exists or not. But this is on # osf3 & osf4 and I'm not really sure... Just # implementing what was already the behavior. newdeplibs=$deplibs ;; test_compile) # This code stresses the "libraries are programs" paradigm to its # limits. Maybe even breaks it. We compile a program, linking it # against the deplibs as a proxy for the library. Then we can check # whether they linked in statically or dynamically with ldd. $rm conftest.c cat > conftest.c </dev/null` for potent_lib in $potential_libs; do # Follow soft links. if ls -lLd "$potent_lib" 2>/dev/null \ | grep " -> " >/dev/null; then continue fi # The statement above tries to avoid entering an # endless loop below, in case of cyclic links. # We might still enter an endless loop, since a link # loop can be closed while we follow links, # but so what? potlib="$potent_lib" while test -h "$potlib" 2>/dev/null; do potliblink=`ls -ld $potlib | ${SED} 's/.* -> //'` case $potliblink in [\\/]* | [A-Za-z]:[\\/]*) potlib="$potliblink";; *) potlib=`$echo "X$potlib" | $Xsed -e 's,[^/]*$,,'`"$potliblink";; esac done if eval $file_magic_cmd \"\$potlib\" 2>/dev/null \ | ${SED} 10q \ | $EGREP "$file_magic_regex" > /dev/null; then newdeplibs="$newdeplibs $a_deplib" a_deplib="" break 2 fi done done fi if test -n "$a_deplib" ; then droppeddeps=yes $echo $echo "*** Warning: linker path does not have real file for library $a_deplib." $echo "*** I have the capability to make that library automatically link in when" $echo "*** you link to this library. But I can only do this if you have a" $echo "*** shared version of the library, which you do not appear to have" $echo "*** because I did check the linker path looking for a file starting" if test -z "$potlib" ; then $echo "*** with $libname but no candidates were found. (...for file magic test)" else $echo "*** with $libname and none of the candidates passed a file format test" $echo "*** using a file magic. Last file checked: $potlib" fi fi else # Add a -L argument. newdeplibs="$newdeplibs $a_deplib" fi done # Gone through all deplibs. ;; match_pattern*) set dummy $deplibs_check_method match_pattern_regex=`expr "$deplibs_check_method" : "$2 \(.*\)"` for a_deplib in $deplibs; do name=`expr $a_deplib : '-l\(.*\)'` # If $name is empty we are operating on a -L argument. if test -n "$name" && test "$name" != "0"; then if test "X$allow_libtool_libs_with_static_runtimes" = "Xyes" ; then case " $predeps $postdeps " in *" $a_deplib "*) newdeplibs="$newdeplibs $a_deplib" a_deplib="" ;; esac fi if test -n "$a_deplib" ; then libname=`eval \\$echo \"$libname_spec\"` for i in $lib_search_path $sys_lib_search_path $shlib_search_path; do potential_libs=`ls $i/$libname[.-]* 2>/dev/null` for potent_lib in $potential_libs; do potlib="$potent_lib" # see symlink-check above in file_magic test if eval $echo \"$potent_lib\" 2>/dev/null \ | ${SED} 10q \ | $EGREP "$match_pattern_regex" > /dev/null; then newdeplibs="$newdeplibs $a_deplib" a_deplib="" break 2 fi done done fi if test -n "$a_deplib" ; then droppeddeps=yes $echo $echo "*** Warning: linker path does not have real file for library $a_deplib." $echo "*** I have the capability to make that library automatically link in when" $echo "*** you link to this library. But I can only do this if you have a" $echo "*** shared version of the library, which you do not appear to have" $echo "*** because I did check the linker path looking for a file starting" if test -z "$potlib" ; then $echo "*** with $libname but no candidates were found. (...for regex pattern test)" else $echo "*** with $libname and none of the candidates passed a file format test" $echo "*** using a regex pattern. Last file checked: $potlib" fi fi else # Add a -L argument. newdeplibs="$newdeplibs $a_deplib" fi done # Gone through all deplibs. ;; none | unknown | *) newdeplibs="" tmp_deplibs=`$echo "X $deplibs" | $Xsed -e 's/ -lc$//' \ -e 's/ -[LR][^ ]*//g'` if test "X$allow_libtool_libs_with_static_runtimes" = "Xyes" ; then for i in $predeps $postdeps ; do # can't use Xsed below, because $i might contain '/' tmp_deplibs=`$echo "X $tmp_deplibs" | ${SED} -e "1s,^X,," -e "s,$i,,"` done fi if $echo "X $tmp_deplibs" | $Xsed -e 's/[ ]//g' \ | grep . >/dev/null; then $echo if test "X$deplibs_check_method" = "Xnone"; then $echo "*** Warning: inter-library dependencies are not supported in this platform." else $echo "*** Warning: inter-library dependencies are not known to be supported." fi $echo "*** All declared inter-library dependencies are being dropped." droppeddeps=yes fi ;; esac versuffix=$versuffix_save major=$major_save release=$release_save libname=$libname_save name=$name_save case $host in *-*-rhapsody* | *-*-darwin1.[012]) # On Rhapsody replace the C library is the System framework newdeplibs=`$echo "X $newdeplibs" | $Xsed -e 's/ -lc / -framework System /'` ;; esac if test "$droppeddeps" = yes; then if test "$module" = yes; then $echo $echo "*** Warning: libtool could not satisfy all declared inter-library" $echo "*** dependencies of module $libname. Therefore, libtool will create" $echo "*** a static module, that should work as long as the dlopening" $echo "*** application is linked with the -dlopen flag." if test -z "$global_symbol_pipe"; then $echo $echo "*** However, this would only work if libtool was able to extract symbol" $echo "*** lists from a program, using \`nm' or equivalent, but libtool could" $echo "*** not find such a program. So, this module is probably useless." $echo "*** \`nm' from GNU binutils and a full rebuild may help." fi if test "$build_old_libs" = no; then oldlibs="$output_objdir/$libname.$libext" build_libtool_libs=module build_old_libs=yes else build_libtool_libs=no fi else $echo "*** The inter-library dependencies that have been dropped here will be" $echo "*** automatically added whenever a program is linked with this library" $echo "*** or is declared to -dlopen it." if test "$allow_undefined" = no; then $echo $echo "*** Since this library must not contain undefined symbols," $echo "*** because either the platform does not support them or" $echo "*** it was explicitly requested with -no-undefined," $echo "*** libtool will only create a static version of it." if test "$build_old_libs" = no; then oldlibs="$output_objdir/$libname.$libext" build_libtool_libs=module build_old_libs=yes else build_libtool_libs=no fi fi fi fi # Done checking deplibs! deplibs=$newdeplibs fi # move library search paths that coincide with paths to not yet # installed libraries to the beginning of the library search list new_libs= for path in $notinst_path; do case " $new_libs " in *" -L$path/$objdir "*) ;; *) case " $deplibs " in *" -L$path/$objdir "*) new_libs="$new_libs -L$path/$objdir" ;; esac ;; esac done for deplib in $deplibs; do case $deplib in -L*) case " $new_libs " in *" $deplib "*) ;; *) new_libs="$new_libs $deplib" ;; esac ;; *) new_libs="$new_libs $deplib" ;; esac done deplibs="$new_libs" # All the library-specific variables (install_libdir is set above). library_names= old_library= dlname= # Test again, we may have decided not to build it any more if test "$build_libtool_libs" = yes; then if test "$hardcode_into_libs" = yes; then # Hardcode the library paths hardcode_libdirs= dep_rpath= rpath="$finalize_rpath" test "$mode" != relink && rpath="$compile_rpath$rpath" for libdir in $rpath; do if test -n "$hardcode_libdir_flag_spec"; then if test -n "$hardcode_libdir_separator"; then if test -z "$hardcode_libdirs"; then hardcode_libdirs="$libdir" else # Just accumulate the unique libdirs. case $hardcode_libdir_separator$hardcode_libdirs$hardcode_libdir_separator in *"$hardcode_libdir_separator$libdir$hardcode_libdir_separator"*) ;; *) hardcode_libdirs="$hardcode_libdirs$hardcode_libdir_separator$libdir" ;; esac fi else eval flag=\"$hardcode_libdir_flag_spec\" dep_rpath="$dep_rpath $flag" fi elif test -n "$runpath_var"; then case "$perm_rpath " in *" $libdir "*) ;; *) perm_rpath="$perm_rpath $libdir" ;; esac fi done # Substitute the hardcoded libdirs into the rpath. if test -n "$hardcode_libdir_separator" && test -n "$hardcode_libdirs"; then libdir="$hardcode_libdirs" if test -n "$hardcode_libdir_flag_spec_ld"; then case $archive_cmds in *\$LD*) eval dep_rpath=\"$hardcode_libdir_flag_spec_ld\" ;; *) eval dep_rpath=\"$hardcode_libdir_flag_spec\" ;; esac else eval dep_rpath=\"$hardcode_libdir_flag_spec\" fi fi if test -n "$runpath_var" && test -n "$perm_rpath"; then # We should set the runpath_var. rpath= for dir in $perm_rpath; do rpath="$rpath$dir:" done eval "$runpath_var='$rpath\$$runpath_var'; export $runpath_var" fi test -n "$dep_rpath" && deplibs="$dep_rpath $deplibs" fi shlibpath="$finalize_shlibpath" test "$mode" != relink && shlibpath="$compile_shlibpath$shlibpath" if test -n "$shlibpath"; then eval "$shlibpath_var='$shlibpath\$$shlibpath_var'; export $shlibpath_var" fi # Get the real and link names of the library. eval shared_ext=\"$shrext_cmds\" eval library_names=\"$library_names_spec\" set dummy $library_names realname="$2" shift; shift if test -n "$soname_spec"; then eval soname=\"$soname_spec\" else soname="$realname" fi if test -z "$dlname"; then dlname=$soname fi lib="$output_objdir/$realname" linknames= for link do linknames="$linknames $link" done # Use standard objects if they are pic test -z "$pic_flag" && libobjs=`$echo "X$libobjs" | $SP2NL | $Xsed -e "$lo2o" | $NL2SP` # Prepare the list of exported symbols if test -z "$export_symbols"; then if test "$always_export_symbols" = yes || test -n "$export_symbols_regex"; then $show "generating symbol list for \`$libname.la'" export_symbols="$output_objdir/$libname.exp" $run $rm $export_symbols cmds=$export_symbols_cmds save_ifs="$IFS"; IFS='~' for cmd in $cmds; do IFS="$save_ifs" eval cmd=\"$cmd\" if len=`expr "X$cmd" : ".*"` && test "$len" -le "$max_cmd_len" || test "$max_cmd_len" -le -1; then $show "$cmd" $run eval "$cmd" || exit $? skipped_export=false else # The command line is too long to execute in one step. $show "using reloadable object file for export list..." skipped_export=: # Break out early, otherwise skipped_export may be # set to false by a later but shorter cmd. break fi done IFS="$save_ifs" if test -n "$export_symbols_regex"; then $show "$EGREP -e \"$export_symbols_regex\" \"$export_symbols\" > \"${export_symbols}T\"" $run eval '$EGREP -e "$export_symbols_regex" "$export_symbols" > "${export_symbols}T"' $show "$mv \"${export_symbols}T\" \"$export_symbols\"" $run eval '$mv "${export_symbols}T" "$export_symbols"' fi fi fi if test -n "$export_symbols" && test -n "$include_expsyms"; then $run eval '$echo "X$include_expsyms" | $SP2NL >> "$export_symbols"' fi tmp_deplibs= for test_deplib in $deplibs; do case " $convenience " in *" $test_deplib "*) ;; *) tmp_deplibs="$tmp_deplibs $test_deplib" ;; esac done deplibs="$tmp_deplibs" if test -n "$convenience"; then if test -n "$whole_archive_flag_spec"; then save_libobjs=$libobjs eval libobjs=\"\$libobjs $whole_archive_flag_spec\" else gentop="$output_objdir/${outputname}x" generated="$generated $gentop" func_extract_archives $gentop $convenience libobjs="$libobjs $func_extract_archives_result" fi fi if test "$thread_safe" = yes && test -n "$thread_safe_flag_spec"; then eval flag=\"$thread_safe_flag_spec\" linker_flags="$linker_flags $flag" fi # Make a backup of the uninstalled library when relinking if test "$mode" = relink; then $run eval '(cd $output_objdir && $rm ${realname}U && $mv $realname ${realname}U)' || exit $? fi # Do each of the archive commands. if test "$module" = yes && test -n "$module_cmds" ; then if test -n "$export_symbols" && test -n "$module_expsym_cmds"; then eval test_cmds=\"$module_expsym_cmds\" cmds=$module_expsym_cmds else eval test_cmds=\"$module_cmds\" cmds=$module_cmds fi else if test -n "$export_symbols" && test -n "$archive_expsym_cmds"; then eval test_cmds=\"$archive_expsym_cmds\" cmds=$archive_expsym_cmds else eval test_cmds=\"$archive_cmds\" cmds=$archive_cmds fi fi if test "X$skipped_export" != "X:" && len=`expr "X$test_cmds" : ".*" 2>/dev/null` && test "$len" -le "$max_cmd_len" || test "$max_cmd_len" -le -1; then : else # The command line is too long to link in one step, link piecewise. $echo "creating reloadable object files..." # Save the value of $output and $libobjs because we want to # use them later. If we have whole_archive_flag_spec, we # want to use save_libobjs as it was before # whole_archive_flag_spec was expanded, because we can't # assume the linker understands whole_archive_flag_spec. # This may have to be revisited, in case too many # convenience libraries get linked in and end up exceeding # the spec. if test -z "$convenience" || test -z "$whole_archive_flag_spec"; then save_libobjs=$libobjs fi save_output=$output output_la=`$echo "X$output" | $Xsed -e "$basename"` # Clear the reloadable object creation command queue and # initialize k to one. test_cmds= concat_cmds= objlist= delfiles= last_robj= k=1 output=$output_objdir/$output_la-${k}.$objext # Loop over the list of objects to be linked. for obj in $save_libobjs do eval test_cmds=\"$reload_cmds $objlist $last_robj\" if test "X$objlist" = X || { len=`expr "X$test_cmds" : ".*" 2>/dev/null` && test "$len" -le "$max_cmd_len"; }; then objlist="$objlist $obj" else # The command $test_cmds is almost too long, add a # command to the queue. if test "$k" -eq 1 ; then # The first file doesn't have a previous command to add. eval concat_cmds=\"$reload_cmds $objlist $last_robj\" else # All subsequent reloadable object files will link in # the last one created. eval concat_cmds=\"\$concat_cmds~$reload_cmds $objlist $last_robj\" fi last_robj=$output_objdir/$output_la-${k}.$objext k=`expr $k + 1` output=$output_objdir/$output_la-${k}.$objext objlist=$obj len=1 fi done # Handle the remaining objects by creating one last # reloadable object file. All subsequent reloadable object # files will link in the last one created. test -z "$concat_cmds" || concat_cmds=$concat_cmds~ eval concat_cmds=\"\${concat_cmds}$reload_cmds $objlist $last_robj\" if ${skipped_export-false}; then $show "generating symbol list for \`$libname.la'" export_symbols="$output_objdir/$libname.exp" $run $rm $export_symbols libobjs=$output # Append the command to create the export file. eval concat_cmds=\"\$concat_cmds~$export_symbols_cmds\" fi # Set up a command to remove the reloadable object files # after they are used. i=0 while test "$i" -lt "$k" do i=`expr $i + 1` delfiles="$delfiles $output_objdir/$output_la-${i}.$objext" done $echo "creating a temporary reloadable object file: $output" # Loop through the commands generated above and execute them. save_ifs="$IFS"; IFS='~' for cmd in $concat_cmds; do IFS="$save_ifs" $show "$cmd" $run eval "$cmd" || exit $? done IFS="$save_ifs" libobjs=$output # Restore the value of output. output=$save_output if test -n "$convenience" && test -n "$whole_archive_flag_spec"; then eval libobjs=\"\$libobjs $whole_archive_flag_spec\" fi # Expand the library linking commands again to reset the # value of $libobjs for piecewise linking. # Do each of the archive commands. if test "$module" = yes && test -n "$module_cmds" ; then if test -n "$export_symbols" && test -n "$module_expsym_cmds"; then cmds=$module_expsym_cmds else cmds=$module_cmds fi else if test -n "$export_symbols" && test -n "$archive_expsym_cmds"; then cmds=$archive_expsym_cmds else cmds=$archive_cmds fi fi # Append the command to remove the reloadable object files # to the just-reset $cmds. eval cmds=\"\$cmds~\$rm $delfiles\" fi save_ifs="$IFS"; IFS='~' for cmd in $cmds; do IFS="$save_ifs" eval cmd=\"$cmd\" $show "$cmd" $run eval "$cmd" || { lt_exit=$? # Restore the uninstalled library and exit if test "$mode" = relink; then $run eval '(cd $output_objdir && $rm ${realname}T && $mv ${realname}U $realname)' fi exit $lt_exit } done IFS="$save_ifs" # Restore the uninstalled library and exit if test "$mode" = relink; then $run eval '(cd $output_objdir && $rm ${realname}T && $mv $realname ${realname}T && $mv "$realname"U $realname)' || exit $? if test -n "$convenience"; then if test -z "$whole_archive_flag_spec"; then $show "${rm}r $gentop" $run ${rm}r "$gentop" fi fi exit $EXIT_SUCCESS fi # Create links to the real library. for linkname in $linknames; do if test "$realname" != "$linkname"; then $show "(cd $output_objdir && $rm $linkname && $LN_S $realname $linkname)" $run eval '(cd $output_objdir && $rm $linkname && $LN_S $realname $linkname)' || exit $? fi done # If -module or -export-dynamic was specified, set the dlname. if test "$module" = yes || test "$export_dynamic" = yes; then # On all known operating systems, these are identical. dlname="$soname" fi fi ;; obj) if test -n "$deplibs"; then $echo "$modename: warning: \`-l' and \`-L' are ignored for objects" 1>&2 fi if test -n "$dlfiles$dlprefiles" || test "$dlself" != no; then $echo "$modename: warning: \`-dlopen' is ignored for objects" 1>&2 fi if test -n "$rpath"; then $echo "$modename: warning: \`-rpath' is ignored for objects" 1>&2 fi if test -n "$xrpath"; then $echo "$modename: warning: \`-R' is ignored for objects" 1>&2 fi if test -n "$vinfo"; then $echo "$modename: warning: \`-version-info' is ignored for objects" 1>&2 fi if test -n "$release"; then $echo "$modename: warning: \`-release' is ignored for objects" 1>&2 fi case $output in *.lo) if test -n "$objs$old_deplibs"; then $echo "$modename: cannot build library object \`$output' from non-libtool objects" 1>&2 exit $EXIT_FAILURE fi libobj="$output" obj=`$echo "X$output" | $Xsed -e "$lo2o"` ;; *) libobj= obj="$output" ;; esac # Delete the old objects. $run $rm $obj $libobj # Objects from convenience libraries. This assumes # single-version convenience libraries. Whenever we create # different ones for PIC/non-PIC, this we'll have to duplicate # the extraction. reload_conv_objs= gentop= # reload_cmds runs $LD directly, so let us get rid of # -Wl from whole_archive_flag_spec and hope we can get by with # turning comma into space.. wl= if test -n "$convenience"; then if test -n "$whole_archive_flag_spec"; then eval tmp_whole_archive_flags=\"$whole_archive_flag_spec\" reload_conv_objs=$reload_objs\ `$echo "X$tmp_whole_archive_flags" | $Xsed -e 's|,| |g'` else gentop="$output_objdir/${obj}x" generated="$generated $gentop" func_extract_archives $gentop $convenience reload_conv_objs="$reload_objs $func_extract_archives_result" fi fi # Create the old-style object. reload_objs="$objs$old_deplibs "`$echo "X$libobjs" | $SP2NL | $Xsed -e '/\.'${libext}$'/d' -e '/\.lib$/d' -e "$lo2o" | $NL2SP`" $reload_conv_objs" ### testsuite: skip nested quoting test output="$obj" cmds=$reload_cmds save_ifs="$IFS"; IFS='~' for cmd in $cmds; do IFS="$save_ifs" eval cmd=\"$cmd\" $show "$cmd" $run eval "$cmd" || exit $? done IFS="$save_ifs" # Exit if we aren't doing a library object file. if test -z "$libobj"; then if test -n "$gentop"; then $show "${rm}r $gentop" $run ${rm}r $gentop fi exit $EXIT_SUCCESS fi if test "$build_libtool_libs" != yes; then if test -n "$gentop"; then $show "${rm}r $gentop" $run ${rm}r $gentop fi # Create an invalid libtool object if no PIC, so that we don't # accidentally link it into a program. # $show "echo timestamp > $libobj" # $run eval "echo timestamp > $libobj" || exit $? exit $EXIT_SUCCESS fi if test -n "$pic_flag" || test "$pic_mode" != default; then # Only do commands if we really have different PIC objects. reload_objs="$libobjs $reload_conv_objs" output="$libobj" cmds=$reload_cmds save_ifs="$IFS"; IFS='~' for cmd in $cmds; do IFS="$save_ifs" eval cmd=\"$cmd\" $show "$cmd" $run eval "$cmd" || exit $? done IFS="$save_ifs" fi if test -n "$gentop"; then $show "${rm}r $gentop" $run ${rm}r $gentop fi exit $EXIT_SUCCESS ;; prog) case $host in *cygwin*) output=`$echo $output | ${SED} -e 's,.exe$,,;s,$,.exe,'` ;; esac if test -n "$vinfo"; then $echo "$modename: warning: \`-version-info' is ignored for programs" 1>&2 fi if test -n "$release"; then $echo "$modename: warning: \`-release' is ignored for programs" 1>&2 fi if test "$preload" = yes; then if test "$dlopen_support" = unknown && test "$dlopen_self" = unknown && test "$dlopen_self_static" = unknown; then $echo "$modename: warning: \`AC_LIBTOOL_DLOPEN' not used. Assuming no dlopen support." fi fi case $host in *-*-rhapsody* | *-*-darwin1.[012]) # On Rhapsody replace the C library is the System framework compile_deplibs=`$echo "X $compile_deplibs" | $Xsed -e 's/ -lc / -framework System /'` finalize_deplibs=`$echo "X $finalize_deplibs" | $Xsed -e 's/ -lc / -framework System /'` ;; esac case $host in *darwin*) # Don't allow lazy linking, it breaks C++ global constructors if test "$tagname" = CXX ; then compile_command="$compile_command ${wl}-bind_at_load" finalize_command="$finalize_command ${wl}-bind_at_load" fi ;; esac # move library search paths that coincide with paths to not yet # installed libraries to the beginning of the library search list new_libs= for path in $notinst_path; do case " $new_libs " in *" -L$path/$objdir "*) ;; *) case " $compile_deplibs " in *" -L$path/$objdir "*) new_libs="$new_libs -L$path/$objdir" ;; esac ;; esac done for deplib in $compile_deplibs; do case $deplib in -L*) case " $new_libs " in *" $deplib "*) ;; *) new_libs="$new_libs $deplib" ;; esac ;; *) new_libs="$new_libs $deplib" ;; esac done compile_deplibs="$new_libs" compile_command="$compile_command $compile_deplibs" finalize_command="$finalize_command $finalize_deplibs" if test -n "$rpath$xrpath"; then # If the user specified any rpath flags, then add them. for libdir in $rpath $xrpath; do # This is the magic to use -rpath. case "$finalize_rpath " in *" $libdir "*) ;; *) finalize_rpath="$finalize_rpath $libdir" ;; esac done fi # Now hardcode the library paths rpath= hardcode_libdirs= for libdir in $compile_rpath $finalize_rpath; do if test -n "$hardcode_libdir_flag_spec"; then if test -n "$hardcode_libdir_separator"; then if test -z "$hardcode_libdirs"; then hardcode_libdirs="$libdir" else # Just accumulate the unique libdirs. case $hardcode_libdir_separator$hardcode_libdirs$hardcode_libdir_separator in *"$hardcode_libdir_separator$libdir$hardcode_libdir_separator"*) ;; *) hardcode_libdirs="$hardcode_libdirs$hardcode_libdir_separator$libdir" ;; esac fi else eval flag=\"$hardcode_libdir_flag_spec\" rpath="$rpath $flag" fi elif test -n "$runpath_var"; then case "$perm_rpath " in *" $libdir "*) ;; *) perm_rpath="$perm_rpath $libdir" ;; esac fi case $host in *-*-cygwin* | *-*-mingw* | *-*-pw32* | *-*-os2*) testbindir=`$echo "X$libdir" | $Xsed -e 's*/lib$*/bin*'` case :$dllsearchpath: in *":$libdir:"*) ;; *) dllsearchpath="$dllsearchpath:$libdir";; esac case :$dllsearchpath: in *":$testbindir:"*) ;; *) dllsearchpath="$dllsearchpath:$testbindir";; esac ;; esac done # Substitute the hardcoded libdirs into the rpath. if test -n "$hardcode_libdir_separator" && test -n "$hardcode_libdirs"; then libdir="$hardcode_libdirs" eval rpath=\" $hardcode_libdir_flag_spec\" fi compile_rpath="$rpath" rpath= hardcode_libdirs= for libdir in $finalize_rpath; do if test -n "$hardcode_libdir_flag_spec"; then if test -n "$hardcode_libdir_separator"; then if test -z "$hardcode_libdirs"; then hardcode_libdirs="$libdir" else # Just accumulate the unique libdirs. case $hardcode_libdir_separator$hardcode_libdirs$hardcode_libdir_separator in *"$hardcode_libdir_separator$libdir$hardcode_libdir_separator"*) ;; *) hardcode_libdirs="$hardcode_libdirs$hardcode_libdir_separator$libdir" ;; esac fi else eval flag=\"$hardcode_libdir_flag_spec\" rpath="$rpath $flag" fi elif test -n "$runpath_var"; then case "$finalize_perm_rpath " in *" $libdir "*) ;; *) finalize_perm_rpath="$finalize_perm_rpath $libdir" ;; esac fi done # Substitute the hardcoded libdirs into the rpath. if test -n "$hardcode_libdir_separator" && test -n "$hardcode_libdirs"; then libdir="$hardcode_libdirs" eval rpath=\" $hardcode_libdir_flag_spec\" fi finalize_rpath="$rpath" if test -n "$libobjs" && test "$build_old_libs" = yes; then # Transform all the library objects into standard objects. compile_command=`$echo "X$compile_command" | $SP2NL | $Xsed -e "$lo2o" | $NL2SP` finalize_command=`$echo "X$finalize_command" | $SP2NL | $Xsed -e "$lo2o" | $NL2SP` fi dlsyms= if test -n "$dlfiles$dlprefiles" || test "$dlself" != no; then if test -n "$NM" && test -n "$global_symbol_pipe"; then dlsyms="${outputname}S.c" else $echo "$modename: not configured to extract global symbols from dlpreopened files" 1>&2 fi fi if test -n "$dlsyms"; then case $dlsyms in "") ;; *.c) # Discover the nlist of each of the dlfiles. nlist="$output_objdir/${outputname}.nm" $show "$rm $nlist ${nlist}S ${nlist}T" $run $rm "$nlist" "${nlist}S" "${nlist}T" # Parse the name list into a source file. $show "creating $output_objdir/$dlsyms" test -z "$run" && $echo > "$output_objdir/$dlsyms" "\ /* $dlsyms - symbol resolution table for \`$outputname' dlsym emulation. */ /* Generated by $PROGRAM - GNU $PACKAGE $VERSION$TIMESTAMP */ #ifdef __cplusplus extern \"C\" { #endif /* Prevent the only kind of declaration conflicts we can make. */ #define lt_preloaded_symbols some_other_symbol /* External symbol declarations for the compiler. */\ " if test "$dlself" = yes; then $show "generating symbol list for \`$output'" test -z "$run" && $echo ': @PROGRAM@ ' > "$nlist" # Add our own program objects to the symbol list. progfiles=`$echo "X$objs$old_deplibs" | $SP2NL | $Xsed -e "$lo2o" | $NL2SP` for arg in $progfiles; do $show "extracting global C symbols from \`$arg'" $run eval "$NM $arg | $global_symbol_pipe >> '$nlist'" done if test -n "$exclude_expsyms"; then $run eval '$EGREP -v " ($exclude_expsyms)$" "$nlist" > "$nlist"T' $run eval '$mv "$nlist"T "$nlist"' fi if test -n "$export_symbols_regex"; then $run eval '$EGREP -e "$export_symbols_regex" "$nlist" > "$nlist"T' $run eval '$mv "$nlist"T "$nlist"' fi # Prepare the list of exported symbols if test -z "$export_symbols"; then export_symbols="$output_objdir/$outputname.exp" $run $rm $export_symbols $run eval "${SED} -n -e '/^: @PROGRAM@ $/d' -e 's/^.* \(.*\)$/\1/p' "'< "$nlist" > "$export_symbols"' case $host in *cygwin* | *mingw* ) $run eval "echo EXPORTS "'> "$output_objdir/$outputname.def"' $run eval 'cat "$export_symbols" >> "$output_objdir/$outputname.def"' ;; esac else $run eval "${SED} -e 's/\([].[*^$]\)/\\\\\1/g' -e 's/^/ /' -e 's/$/$/'"' < "$export_symbols" > "$output_objdir/$outputname.exp"' $run eval 'grep -f "$output_objdir/$outputname.exp" < "$nlist" > "$nlist"T' $run eval 'mv "$nlist"T "$nlist"' case $host in *cygwin* | *mingw* ) $run eval "echo EXPORTS "'> "$output_objdir/$outputname.def"' $run eval 'cat "$nlist" >> "$output_objdir/$outputname.def"' ;; esac fi fi for arg in $dlprefiles; do $show "extracting global C symbols from \`$arg'" name=`$echo "$arg" | ${SED} -e 's%^.*/%%'` $run eval '$echo ": $name " >> "$nlist"' $run eval "$NM $arg | $global_symbol_pipe >> '$nlist'" done if test -z "$run"; then # Make sure we have at least an empty file. test -f "$nlist" || : > "$nlist" if test -n "$exclude_expsyms"; then $EGREP -v " ($exclude_expsyms)$" "$nlist" > "$nlist"T $mv "$nlist"T "$nlist" fi # Try sorting and uniquifying the output. if grep -v "^: " < "$nlist" | if sort -k 3 /dev/null 2>&1; then sort -k 3 else sort +2 fi | uniq > "$nlist"S; then : else grep -v "^: " < "$nlist" > "$nlist"S fi if test -f "$nlist"S; then eval "$global_symbol_to_cdecl"' < "$nlist"S >> "$output_objdir/$dlsyms"' else $echo '/* NONE */' >> "$output_objdir/$dlsyms" fi $echo >> "$output_objdir/$dlsyms" "\ #undef lt_preloaded_symbols #if defined (__STDC__) && __STDC__ # define lt_ptr void * #else # define lt_ptr char * # define const #endif /* The mapping between symbol names and symbols. */ " case $host in *cygwin* | *mingw* ) $echo >> "$output_objdir/$dlsyms" "\ /* DATA imports from DLLs on WIN32 can't be const, because runtime relocations are performed -- see ld's documentation on pseudo-relocs */ struct { " ;; * ) $echo >> "$output_objdir/$dlsyms" "\ const struct { " ;; esac $echo >> "$output_objdir/$dlsyms" "\ const char *name; lt_ptr address; } lt_preloaded_symbols[] = {\ " eval "$global_symbol_to_c_name_address" < "$nlist" >> "$output_objdir/$dlsyms" $echo >> "$output_objdir/$dlsyms" "\ {0, (lt_ptr) 0} }; /* This works around a problem in FreeBSD linker */ #ifdef FREEBSD_WORKAROUND static const void *lt_preloaded_setup() { return lt_preloaded_symbols; } #endif #ifdef __cplusplus } #endif\ " fi pic_flag_for_symtable= case $host in # compiling the symbol table file with pic_flag works around # a FreeBSD bug that causes programs to crash when -lm is # linked before any other PIC object. But we must not use # pic_flag when linking with -static. The problem exists in # FreeBSD 2.2.6 and is fixed in FreeBSD 3.1. *-*-freebsd2*|*-*-freebsd3.0*|*-*-freebsdelf3.0*) case "$compile_command " in *" -static "*) ;; *) pic_flag_for_symtable=" $pic_flag -DFREEBSD_WORKAROUND";; esac;; *-*-hpux*) case "$compile_command " in *" -static "*) ;; *) pic_flag_for_symtable=" $pic_flag";; esac esac # Now compile the dynamic symbol file. $show "(cd $output_objdir && $LTCC $LTCFLAGS -c$no_builtin_flag$pic_flag_for_symtable \"$dlsyms\")" $run eval '(cd $output_objdir && $LTCC $LTCFLAGS -c$no_builtin_flag$pic_flag_for_symtable "$dlsyms")' || exit $? # Clean up the generated files. $show "$rm $output_objdir/$dlsyms $nlist ${nlist}S ${nlist}T" $run $rm "$output_objdir/$dlsyms" "$nlist" "${nlist}S" "${nlist}T" # Transform the symbol file into the correct name. case $host in *cygwin* | *mingw* ) if test -f "$output_objdir/${outputname}.def" ; then compile_command=`$echo "X$compile_command" | $SP2NL | $Xsed -e "s%@SYMFILE@%$output_objdir/${outputname}.def $output_objdir/${outputname}S.${objext}%" | $NL2SP` finalize_command=`$echo "X$finalize_command" | $SP2NL | $Xsed -e "s%@SYMFILE@%$output_objdir/${outputname}.def $output_objdir/${outputname}S.${objext}%" | $NL2SP` else compile_command=`$echo "X$compile_command" | $SP2NL | $Xsed -e "s%@SYMFILE@%$output_objdir/${outputname}S.${objext}%" | $NL2SP` finalize_command=`$echo "X$finalize_command" | $SP2NL | $Xsed -e "s%@SYMFILE@%$output_objdir/${outputname}S.${objext}%" | $NL2SP` fi ;; * ) compile_command=`$echo "X$compile_command" | $SP2NL | $Xsed -e "s%@SYMFILE@%$output_objdir/${outputname}S.${objext}%" | $NL2SP` finalize_command=`$echo "X$finalize_command" | $SP2NL | $Xsed -e "s%@SYMFILE@%$output_objdir/${outputname}S.${objext}%" | $NL2SP` ;; esac ;; *) $echo "$modename: unknown suffix for \`$dlsyms'" 1>&2 exit $EXIT_FAILURE ;; esac else # We keep going just in case the user didn't refer to # lt_preloaded_symbols. The linker will fail if global_symbol_pipe # really was required. # Nullify the symbol file. compile_command=`$echo "X$compile_command" | $SP2NL | $Xsed -e "s% @SYMFILE@%%" | $NL2SP` finalize_command=`$echo "X$finalize_command" | $SP2NL | $Xsed -e "s% @SYMFILE@%%" | $NL2SP` fi if test "$need_relink" = no || test "$build_libtool_libs" != yes; then # Replace the output file specification. compile_command=`$echo "X$compile_command" | $SP2NL | $Xsed -e 's%@OUTPUT@%'"$output"'%g' | $NL2SP` link_command="$compile_command$compile_rpath" # We have no uninstalled library dependencies, so finalize right now. $show "$link_command" $run eval "$link_command" exit_status=$? # Delete the generated files. if test -n "$dlsyms"; then $show "$rm $output_objdir/${outputname}S.${objext}" $run $rm "$output_objdir/${outputname}S.${objext}" fi exit $exit_status fi if test -n "$shlibpath_var"; then # We should set the shlibpath_var rpath= for dir in $temp_rpath; do case $dir in [\\/]* | [A-Za-z]:[\\/]*) # Absolute path. rpath="$rpath$dir:" ;; *) # Relative path: add a thisdir entry. rpath="$rpath\$thisdir/$dir:" ;; esac done temp_rpath="$rpath" fi if test -n "$compile_shlibpath$finalize_shlibpath"; then compile_command="$shlibpath_var=\"$compile_shlibpath$finalize_shlibpath\$$shlibpath_var\" $compile_command" fi if test -n "$finalize_shlibpath"; then finalize_command="$shlibpath_var=\"$finalize_shlibpath\$$shlibpath_var\" $finalize_command" fi compile_var= finalize_var= if test -n "$runpath_var"; then if test -n "$perm_rpath"; then # We should set the runpath_var. rpath= for dir in $perm_rpath; do rpath="$rpath$dir:" done compile_var="$runpath_var=\"$rpath\$$runpath_var\" " fi if test -n "$finalize_perm_rpath"; then # We should set the runpath_var. rpath= for dir in $finalize_perm_rpath; do rpath="$rpath$dir:" done finalize_var="$runpath_var=\"$rpath\$$runpath_var\" " fi fi if test "$no_install" = yes; then # We don't need to create a wrapper script. link_command="$compile_var$compile_command$compile_rpath" # Replace the output file specification. link_command=`$echo "X$link_command" | $Xsed -e 's%@OUTPUT@%'"$output"'%g'` # Delete the old output file. $run $rm $output # Link the executable and exit $show "$link_command" $run eval "$link_command" || exit $? exit $EXIT_SUCCESS fi if test "$hardcode_action" = relink; then # Fast installation is not supported link_command="$compile_var$compile_command$compile_rpath" relink_command="$finalize_var$finalize_command$finalize_rpath" $echo "$modename: warning: this platform does not like uninstalled shared libraries" 1>&2 $echo "$modename: \`$output' will be relinked during installation" 1>&2 else if test "$fast_install" != no; then link_command="$finalize_var$compile_command$finalize_rpath" if test "$fast_install" = yes; then relink_command=`$echo "X$compile_var$compile_command$compile_rpath" | $SP2NL | $Xsed -e 's%@OUTPUT@%\$progdir/\$file%g' | $NL2SP` else # fast_install is set to needless relink_command= fi else link_command="$compile_var$compile_command$compile_rpath" relink_command="$finalize_var$finalize_command$finalize_rpath" fi fi # Replace the output file specification. link_command=`$echo "X$link_command" | $Xsed -e 's%@OUTPUT@%'"$output_objdir/$outputname"'%g'` # Delete the old output files. $run $rm $output $output_objdir/$outputname $output_objdir/lt-$outputname $show "$link_command" $run eval "$link_command" || exit $? # Now create the wrapper script. $show "creating $output" # Quote the relink command for shipping. if test -n "$relink_command"; then # Preserve any variables that may affect compiler behavior for var in $variables_saved_for_relink; do if eval test -z \"\${$var+set}\"; then relink_command="{ test -z \"\${$var+set}\" || unset $var || { $var=; export $var; }; }; $relink_command" elif eval var_value=\$$var; test -z "$var_value"; then relink_command="$var=; export $var; $relink_command" else var_value=`$echo "X$var_value" | $Xsed -e "$sed_quote_subst"` relink_command="$var=\"$var_value\"; export $var; $relink_command" fi done relink_command="(cd `pwd`; $relink_command)" relink_command=`$echo "X$relink_command" | $SP2NL | $Xsed -e "$sed_quote_subst" | $NL2SP` fi # Quote $echo for shipping. if test "X$echo" = "X$SHELL $progpath --fallback-echo"; then case $progpath in [\\/]* | [A-Za-z]:[\\/]*) qecho="$SHELL $progpath --fallback-echo";; *) qecho="$SHELL `pwd`/$progpath --fallback-echo";; esac qecho=`$echo "X$qecho" | $Xsed -e "$sed_quote_subst"` else qecho=`$echo "X$echo" | $Xsed -e "$sed_quote_subst"` fi # Only actually do things if our run command is non-null. if test -z "$run"; then # win32 will think the script is a binary if it has # a .exe suffix, so we strip it off here. case $output in *.exe) output=`$echo $output|${SED} 's,.exe$,,'` ;; esac # test for cygwin because mv fails w/o .exe extensions case $host in *cygwin*) exeext=.exe outputname=`$echo $outputname|${SED} 's,.exe$,,'` ;; *) exeext= ;; esac case $host in *cygwin* | *mingw* ) output_name=`basename $output` output_path=`dirname $output` cwrappersource="$output_path/$objdir/lt-$output_name.c" cwrapper="$output_path/$output_name.exe" $rm $cwrappersource $cwrapper trap "$rm $cwrappersource $cwrapper; exit $EXIT_FAILURE" 1 2 15 cat > $cwrappersource <> $cwrappersource<<"EOF" #include #include #include #include #include #include #include #include #include #if defined(PATH_MAX) # define LT_PATHMAX PATH_MAX #elif defined(MAXPATHLEN) # define LT_PATHMAX MAXPATHLEN #else # define LT_PATHMAX 1024 #endif #ifndef DIR_SEPARATOR # define DIR_SEPARATOR '/' # define PATH_SEPARATOR ':' #endif #if defined (_WIN32) || defined (__MSDOS__) || defined (__DJGPP__) || \ defined (__OS2__) # define HAVE_DOS_BASED_FILE_SYSTEM # ifndef DIR_SEPARATOR_2 # define DIR_SEPARATOR_2 '\\' # endif # ifndef PATH_SEPARATOR_2 # define PATH_SEPARATOR_2 ';' # endif #endif #ifndef DIR_SEPARATOR_2 # define IS_DIR_SEPARATOR(ch) ((ch) == DIR_SEPARATOR) #else /* DIR_SEPARATOR_2 */ # define IS_DIR_SEPARATOR(ch) \ (((ch) == DIR_SEPARATOR) || ((ch) == DIR_SEPARATOR_2)) #endif /* DIR_SEPARATOR_2 */ #ifndef PATH_SEPARATOR_2 # define IS_PATH_SEPARATOR(ch) ((ch) == PATH_SEPARATOR) #else /* PATH_SEPARATOR_2 */ # define IS_PATH_SEPARATOR(ch) ((ch) == PATH_SEPARATOR_2) #endif /* PATH_SEPARATOR_2 */ #define XMALLOC(type, num) ((type *) xmalloc ((num) * sizeof(type))) #define XFREE(stale) do { \ if (stale) { free ((void *) stale); stale = 0; } \ } while (0) /* -DDEBUG is fairly common in CFLAGS. */ #undef DEBUG #if defined DEBUGWRAPPER # define DEBUG(format, ...) fprintf(stderr, format, __VA_ARGS__) #else # define DEBUG(format, ...) #endif const char *program_name = NULL; void * xmalloc (size_t num); char * xstrdup (const char *string); const char * base_name (const char *name); char * find_executable(const char *wrapper); int check_executable(const char *path); char * strendzap(char *str, const char *pat); void lt_fatal (const char *message, ...); int main (int argc, char *argv[]) { char **newargz; int i; program_name = (char *) xstrdup (base_name (argv[0])); DEBUG("(main) argv[0] : %s\n",argv[0]); DEBUG("(main) program_name : %s\n",program_name); newargz = XMALLOC(char *, argc+2); EOF cat >> $cwrappersource <> $cwrappersource <<"EOF" newargz[1] = find_executable(argv[0]); if (newargz[1] == NULL) lt_fatal("Couldn't find %s", argv[0]); DEBUG("(main) found exe at : %s\n",newargz[1]); /* we know the script has the same name, without the .exe */ /* so make sure newargz[1] doesn't end in .exe */ strendzap(newargz[1],".exe"); for (i = 1; i < argc; i++) newargz[i+1] = xstrdup(argv[i]); newargz[argc+1] = NULL; for (i=0; i> $cwrappersource <> $cwrappersource <> $cwrappersource <<"EOF" return 127; } void * xmalloc (size_t num) { void * p = (void *) malloc (num); if (!p) lt_fatal ("Memory exhausted"); return p; } char * xstrdup (const char *string) { return string ? strcpy ((char *) xmalloc (strlen (string) + 1), string) : NULL ; } const char * base_name (const char *name) { const char *base; #if defined (HAVE_DOS_BASED_FILE_SYSTEM) /* Skip over the disk name in MSDOS pathnames. */ if (isalpha ((unsigned char)name[0]) && name[1] == ':') name += 2; #endif for (base = name; *name; name++) if (IS_DIR_SEPARATOR (*name)) base = name + 1; return base; } int check_executable(const char * path) { struct stat st; DEBUG("(check_executable) : %s\n", path ? (*path ? path : "EMPTY!") : "NULL!"); if ((!path) || (!*path)) return 0; if ((stat (path, &st) >= 0) && ( /* MinGW & native WIN32 do not support S_IXOTH or S_IXGRP */ #if defined (S_IXOTH) ((st.st_mode & S_IXOTH) == S_IXOTH) || #endif #if defined (S_IXGRP) ((st.st_mode & S_IXGRP) == S_IXGRP) || #endif ((st.st_mode & S_IXUSR) == S_IXUSR)) ) return 1; else return 0; } /* Searches for the full path of the wrapper. Returns newly allocated full path name if found, NULL otherwise */ char * find_executable (const char* wrapper) { int has_slash = 0; const char* p; const char* p_next; /* static buffer for getcwd */ char tmp[LT_PATHMAX + 1]; int tmp_len; char* concat_name; DEBUG("(find_executable) : %s\n", wrapper ? (*wrapper ? wrapper : "EMPTY!") : "NULL!"); if ((wrapper == NULL) || (*wrapper == '\0')) return NULL; /* Absolute path? */ #if defined (HAVE_DOS_BASED_FILE_SYSTEM) if (isalpha ((unsigned char)wrapper[0]) && wrapper[1] == ':') { concat_name = xstrdup (wrapper); if (check_executable(concat_name)) return concat_name; XFREE(concat_name); } else { #endif if (IS_DIR_SEPARATOR (wrapper[0])) { concat_name = xstrdup (wrapper); if (check_executable(concat_name)) return concat_name; XFREE(concat_name); } #if defined (HAVE_DOS_BASED_FILE_SYSTEM) } #endif for (p = wrapper; *p; p++) if (*p == '/') { has_slash = 1; break; } if (!has_slash) { /* no slashes; search PATH */ const char* path = getenv ("PATH"); if (path != NULL) { for (p = path; *p; p = p_next) { const char* q; size_t p_len; for (q = p; *q; q++) if (IS_PATH_SEPARATOR(*q)) break; p_len = q - p; p_next = (*q == '\0' ? q : q + 1); if (p_len == 0) { /* empty path: current directory */ if (getcwd (tmp, LT_PATHMAX) == NULL) lt_fatal ("getcwd failed"); tmp_len = strlen(tmp); concat_name = XMALLOC(char, tmp_len + 1 + strlen(wrapper) + 1); memcpy (concat_name, tmp, tmp_len); concat_name[tmp_len] = '/'; strcpy (concat_name + tmp_len + 1, wrapper); } else { concat_name = XMALLOC(char, p_len + 1 + strlen(wrapper) + 1); memcpy (concat_name, p, p_len); concat_name[p_len] = '/'; strcpy (concat_name + p_len + 1, wrapper); } if (check_executable(concat_name)) return concat_name; XFREE(concat_name); } } /* not found in PATH; assume curdir */ } /* Relative path | not found in path: prepend cwd */ if (getcwd (tmp, LT_PATHMAX) == NULL) lt_fatal ("getcwd failed"); tmp_len = strlen(tmp); concat_name = XMALLOC(char, tmp_len + 1 + strlen(wrapper) + 1); memcpy (concat_name, tmp, tmp_len); concat_name[tmp_len] = '/'; strcpy (concat_name + tmp_len + 1, wrapper); if (check_executable(concat_name)) return concat_name; XFREE(concat_name); return NULL; } char * strendzap(char *str, const char *pat) { size_t len, patlen; assert(str != NULL); assert(pat != NULL); len = strlen(str); patlen = strlen(pat); if (patlen <= len) { str += len - patlen; if (strcmp(str, pat) == 0) *str = '\0'; } return str; } static void lt_error_core (int exit_status, const char * mode, const char * message, va_list ap) { fprintf (stderr, "%s: %s: ", program_name, mode); vfprintf (stderr, message, ap); fprintf (stderr, ".\n"); if (exit_status >= 0) exit (exit_status); } void lt_fatal (const char *message, ...) { va_list ap; va_start (ap, message); lt_error_core (EXIT_FAILURE, "FATAL", message, ap); va_end (ap); } EOF # we should really use a build-platform specific compiler # here, but OTOH, the wrappers (shell script and this C one) # are only useful if you want to execute the "real" binary. # Since the "real" binary is built for $host, then this # wrapper might as well be built for $host, too. $run $LTCC $LTCFLAGS -s -o $cwrapper $cwrappersource ;; esac $rm $output trap "$rm $output; exit $EXIT_FAILURE" 1 2 15 $echo > $output "\ #! $SHELL # $output - temporary wrapper script for $objdir/$outputname # Generated by $PROGRAM - GNU $PACKAGE $VERSION$TIMESTAMP # # The $output program cannot be directly executed until all the libtool # libraries that it depends on are installed. # # This wrapper script should never be moved out of the build directory. # If it is, it will not operate correctly. # Sed substitution that helps us do robust quoting. It backslashifies # metacharacters that are still active within double-quoted strings. Xsed='${SED} -e 1s/^X//' sed_quote_subst='$sed_quote_subst' # Be Bourne compatible (taken from Autoconf:_AS_BOURNE_COMPATIBLE). if test -n \"\${ZSH_VERSION+set}\" && (emulate sh) >/dev/null 2>&1; then emulate sh NULLCMD=: # Zsh 3.x and 4.x performs word splitting on \${1+\"\$@\"}, which # is contrary to our usage. Disable this feature. alias -g '\${1+\"\$@\"}'='\"\$@\"' setopt NO_GLOB_SUBST else case \`(set -o) 2>/dev/null\` in *posix*) set -o posix;; esac fi BIN_SH=xpg4; export BIN_SH # for Tru64 DUALCASE=1; export DUALCASE # for MKS sh # The HP-UX ksh and POSIX shell print the target directory to stdout # if CDPATH is set. (unset CDPATH) >/dev/null 2>&1 && unset CDPATH relink_command=\"$relink_command\" # This environment variable determines our operation mode. if test \"\$libtool_install_magic\" = \"$magic\"; then # install mode needs the following variable: notinst_deplibs='$notinst_deplibs' else # When we are sourced in execute mode, \$file and \$echo are already set. if test \"\$libtool_execute_magic\" != \"$magic\"; then echo=\"$qecho\" file=\"\$0\" # Make sure echo works. if test \"X\$1\" = X--no-reexec; then # Discard the --no-reexec flag, and continue. shift elif test \"X\`(\$echo '\t') 2>/dev/null\`\" = 'X\t'; then # Yippee, \$echo works! : else # Restart under the correct shell, and then maybe \$echo will work. exec $SHELL \"\$0\" --no-reexec \${1+\"\$@\"} fi fi\ " $echo >> $output "\ # Find the directory that this script lives in. thisdir=\`\$echo \"X\$file\" | \$Xsed -e 's%/[^/]*$%%'\` test \"x\$thisdir\" = \"x\$file\" && thisdir=. # Follow symbolic links until we get to the real thisdir. file=\`ls -ld \"\$file\" | ${SED} -n 's/.*-> //p'\` while test -n \"\$file\"; do destdir=\`\$echo \"X\$file\" | \$Xsed -e 's%/[^/]*\$%%'\` # If there was a directory component, then change thisdir. if test \"x\$destdir\" != \"x\$file\"; then case \"\$destdir\" in [\\\\/]* | [A-Za-z]:[\\\\/]*) thisdir=\"\$destdir\" ;; *) thisdir=\"\$thisdir/\$destdir\" ;; esac fi file=\`\$echo \"X\$file\" | \$Xsed -e 's%^.*/%%'\` file=\`ls -ld \"\$thisdir/\$file\" | ${SED} -n 's/.*-> //p'\` done # Try to get the absolute directory name. absdir=\`cd \"\$thisdir\" && pwd\` test -n \"\$absdir\" && thisdir=\"\$absdir\" " if test "$fast_install" = yes; then $echo >> $output "\ program=lt-'$outputname'$exeext progdir=\"\$thisdir/$objdir\" if test ! -f \"\$progdir/\$program\" || \\ { file=\`ls -1dt \"\$progdir/\$program\" \"\$progdir/../\$program\" 2>/dev/null | ${SED} 1q\`; \\ test \"X\$file\" != \"X\$progdir/\$program\"; }; then file=\"\$\$-\$program\" if test ! -d \"\$progdir\"; then $mkdir \"\$progdir\" else $rm \"\$progdir/\$file\" fi" $echo >> $output "\ # relink executable if necessary if test -n \"\$relink_command\"; then if relink_command_output=\`eval \$relink_command 2>&1\`; then : else $echo \"\$relink_command_output\" >&2 $rm \"\$progdir/\$file\" exit $EXIT_FAILURE fi fi $mv \"\$progdir/\$file\" \"\$progdir/\$program\" 2>/dev/null || { $rm \"\$progdir/\$program\"; $mv \"\$progdir/\$file\" \"\$progdir/\$program\"; } $rm \"\$progdir/\$file\" fi" else $echo >> $output "\ program='$outputname' progdir=\"\$thisdir/$objdir\" " fi $echo >> $output "\ if test -f \"\$progdir/\$program\"; then" # Export our shlibpath_var if we have one. if test "$shlibpath_overrides_runpath" = yes && test -n "$shlibpath_var" && test -n "$temp_rpath"; then $echo >> $output "\ # Add our own library path to $shlibpath_var $shlibpath_var=\"$temp_rpath\$$shlibpath_var\" # Some systems cannot cope with colon-terminated $shlibpath_var # The second colon is a workaround for a bug in BeOS R4 sed $shlibpath_var=\`\$echo \"X\$$shlibpath_var\" | \$Xsed -e 's/::*\$//'\` export $shlibpath_var " fi # fixup the dll searchpath if we need to. if test -n "$dllsearchpath"; then $echo >> $output "\ # Add the dll search path components to the executable PATH PATH=$dllsearchpath:\$PATH " fi $echo >> $output "\ if test \"\$libtool_execute_magic\" != \"$magic\"; then # Run the actual program with our arguments. " case $host in # Backslashes separate directories on plain windows *-*-mingw | *-*-os2*) $echo >> $output "\ exec \"\$progdir\\\\\$program\" \${1+\"\$@\"} " ;; *) $echo >> $output "\ exec \"\$progdir/\$program\" \${1+\"\$@\"} " ;; esac $echo >> $output "\ \$echo \"\$0: cannot exec \$program \$*\" exit $EXIT_FAILURE fi else # The program doesn't exist. \$echo \"\$0: error: \\\`\$progdir/\$program' does not exist\" 1>&2 \$echo \"This script is just a wrapper for \$program.\" 1>&2 $echo \"See the $PACKAGE documentation for more information.\" 1>&2 exit $EXIT_FAILURE fi fi\ " chmod +x $output fi exit $EXIT_SUCCESS ;; esac # See if we need to build an old-fashioned archive. for oldlib in $oldlibs; do if test "$build_libtool_libs" = convenience; then oldobjs="$libobjs_save" addlibs="$convenience" build_libtool_libs=no else if test "$build_libtool_libs" = module; then oldobjs="$libobjs_save" build_libtool_libs=no else oldobjs="$old_deplibs $non_pic_objects" fi addlibs="$old_convenience" fi if test -n "$addlibs"; then gentop="$output_objdir/${outputname}x" generated="$generated $gentop" func_extract_archives $gentop $addlibs oldobjs="$oldobjs $func_extract_archives_result" fi # Do each command in the archive commands. if test -n "$old_archive_from_new_cmds" && test "$build_libtool_libs" = yes; then cmds=$old_archive_from_new_cmds else # POSIX demands no paths to be encoded in archives. We have # to avoid creating archives with duplicate basenames if we # might have to extract them afterwards, e.g., when creating a # static archive out of a convenience library, or when linking # the entirety of a libtool archive into another (currently # not supported by libtool). if (for obj in $oldobjs do $echo "X$obj" | $Xsed -e 's%^.*/%%' done | sort | sort -uc >/dev/null 2>&1); then : else $echo "copying selected object files to avoid basename conflicts..." if test -z "$gentop"; then gentop="$output_objdir/${outputname}x" generated="$generated $gentop" $show "${rm}r $gentop" $run ${rm}r "$gentop" $show "$mkdir $gentop" $run $mkdir "$gentop" exit_status=$? if test "$exit_status" -ne 0 && test ! -d "$gentop"; then exit $exit_status fi fi save_oldobjs=$oldobjs oldobjs= counter=1 for obj in $save_oldobjs do objbase=`$echo "X$obj" | $Xsed -e 's%^.*/%%'` case " $oldobjs " in " ") oldobjs=$obj ;; *[\ /]"$objbase "*) while :; do # Make sure we don't pick an alternate name that also # overlaps. newobj=lt$counter-$objbase counter=`expr $counter + 1` case " $oldobjs " in *[\ /]"$newobj "*) ;; *) if test ! -f "$gentop/$newobj"; then break; fi ;; esac done $show "ln $obj $gentop/$newobj || cp $obj $gentop/$newobj" $run ln "$obj" "$gentop/$newobj" || $run cp "$obj" "$gentop/$newobj" oldobjs="$oldobjs $gentop/$newobj" ;; *) oldobjs="$oldobjs $obj" ;; esac done fi eval cmds=\"$old_archive_cmds\" if len=`expr "X$cmds" : ".*"` && test "$len" -le "$max_cmd_len" || test "$max_cmd_len" -le -1; then cmds=$old_archive_cmds else # the command line is too long to link in one step, link in parts $echo "using piecewise archive linking..." save_RANLIB=$RANLIB RANLIB=: objlist= concat_cmds= save_oldobjs=$oldobjs # Is there a better way of finding the last object in the list? for obj in $save_oldobjs do last_oldobj=$obj done for obj in $save_oldobjs do oldobjs="$objlist $obj" objlist="$objlist $obj" eval test_cmds=\"$old_archive_cmds\" if len=`expr "X$test_cmds" : ".*" 2>/dev/null` && test "$len" -le "$max_cmd_len"; then : else # the above command should be used before it gets too long oldobjs=$objlist if test "$obj" = "$last_oldobj" ; then RANLIB=$save_RANLIB fi test -z "$concat_cmds" || concat_cmds=$concat_cmds~ eval concat_cmds=\"\${concat_cmds}$old_archive_cmds\" objlist= fi done RANLIB=$save_RANLIB oldobjs=$objlist if test "X$oldobjs" = "X" ; then eval cmds=\"\$concat_cmds\" else eval cmds=\"\$concat_cmds~\$old_archive_cmds\" fi fi fi save_ifs="$IFS"; IFS='~' for cmd in $cmds; do eval cmd=\"$cmd\" IFS="$save_ifs" $show "$cmd" $run eval "$cmd" || exit $? done IFS="$save_ifs" done if test -n "$generated"; then $show "${rm}r$generated" $run ${rm}r$generated fi # Now create the libtool archive. case $output in *.la) old_library= test "$build_old_libs" = yes && old_library="$libname.$libext" $show "creating $output" # Preserve any variables that may affect compiler behavior for var in $variables_saved_for_relink; do if eval test -z \"\${$var+set}\"; then relink_command="{ test -z \"\${$var+set}\" || unset $var || { $var=; export $var; }; }; $relink_command" elif eval var_value=\$$var; test -z "$var_value"; then relink_command="$var=; export $var; $relink_command" else var_value=`$echo "X$var_value" | $Xsed -e "$sed_quote_subst"` relink_command="$var=\"$var_value\"; export $var; $relink_command" fi done # Quote the link command for shipping. relink_command="(cd `pwd`; $SHELL $progpath $preserve_args --mode=relink $libtool_args @inst_prefix_dir@)" relink_command=`$echo "X$relink_command" | $SP2NL | $Xsed -e "$sed_quote_subst" | $NL2SP` if test "$hardcode_automatic" = yes ; then relink_command= fi # Only create the output if not a dry run. if test -z "$run"; then for installed in no yes; do if test "$installed" = yes; then if test -z "$install_libdir"; then break fi output="$output_objdir/$outputname"i # Replace all uninstalled libtool libraries with the installed ones newdependency_libs= for deplib in $dependency_libs; do case $deplib in *.la) name=`$echo "X$deplib" | $Xsed -e 's%^.*/%%'` eval libdir=`${SED} -n -e 's/^libdir=\(.*\)$/\1/p' $deplib` if test -z "$libdir"; then $echo "$modename: \`$deplib' is not a valid libtool archive" 1>&2 exit $EXIT_FAILURE fi newdependency_libs="$newdependency_libs $libdir/$name" ;; *) newdependency_libs="$newdependency_libs $deplib" ;; esac done dependency_libs="$newdependency_libs" newdlfiles= for lib in $dlfiles; do name=`$echo "X$lib" | $Xsed -e 's%^.*/%%'` eval libdir=`${SED} -n -e 's/^libdir=\(.*\)$/\1/p' $lib` if test -z "$libdir"; then $echo "$modename: \`$lib' is not a valid libtool archive" 1>&2 exit $EXIT_FAILURE fi newdlfiles="$newdlfiles $libdir/$name" done dlfiles="$newdlfiles" newdlprefiles= for lib in $dlprefiles; do name=`$echo "X$lib" | $Xsed -e 's%^.*/%%'` eval libdir=`${SED} -n -e 's/^libdir=\(.*\)$/\1/p' $lib` if test -z "$libdir"; then $echo "$modename: \`$lib' is not a valid libtool archive" 1>&2 exit $EXIT_FAILURE fi newdlprefiles="$newdlprefiles $libdir/$name" done dlprefiles="$newdlprefiles" else newdlfiles= for lib in $dlfiles; do case $lib in [\\/]* | [A-Za-z]:[\\/]*) abs="$lib" ;; *) abs=`pwd`"/$lib" ;; esac newdlfiles="$newdlfiles $abs" done dlfiles="$newdlfiles" newdlprefiles= for lib in $dlprefiles; do case $lib in [\\/]* | [A-Za-z]:[\\/]*) abs="$lib" ;; *) abs=`pwd`"/$lib" ;; esac newdlprefiles="$newdlprefiles $abs" done dlprefiles="$newdlprefiles" fi $rm $output # place dlname in correct position for cygwin tdlname=$dlname case $host,$output,$installed,$module,$dlname in *cygwin*,*lai,yes,no,*.dll | *mingw*,*lai,yes,no,*.dll) tdlname=../bin/$dlname ;; esac $echo > $output "\ # $outputname - a libtool library file # Generated by $PROGRAM - GNU $PACKAGE $VERSION$TIMESTAMP # # Please DO NOT delete this file! # It is necessary for linking the library. # The name that we can dlopen(3). dlname='$tdlname' # Names of this library. library_names='$library_names' # The name of the static archive. old_library='$old_library' # Libraries that this one depends upon. dependency_libs='$dependency_libs' # Version information for $libname. current=$current age=$age revision=$revision # Is this an already installed library? installed=$installed # Should we warn about portability when linking against -modules? shouldnotlink=$module # Files to dlopen/dlpreopen dlopen='$dlfiles' dlpreopen='$dlprefiles' # Directory that this library needs to be installed in: libdir='$install_libdir'" if test "$installed" = no && test "$need_relink" = yes; then $echo >> $output "\ relink_command=\"$relink_command\"" fi done fi # Do a symbolic link so that the libtool archive can be found in # LD_LIBRARY_PATH before the program is installed. $show "(cd $output_objdir && $rm $outputname && $LN_S ../$outputname $outputname)" $run eval '(cd $output_objdir && $rm $outputname && $LN_S ../$outputname $outputname)' || exit $? ;; esac exit $EXIT_SUCCESS ;; # libtool install mode install) modename="$modename: install" # There may be an optional sh(1) argument at the beginning of # install_prog (especially on Windows NT). if test "$nonopt" = "$SHELL" || test "$nonopt" = /bin/sh || # Allow the use of GNU shtool's install command. $echo "X$nonopt" | grep shtool > /dev/null; then # Aesthetically quote it. arg=`$echo "X$nonopt" | $Xsed -e "$sed_quote_subst"` case $arg in *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*|"") arg="\"$arg\"" ;; esac install_prog="$arg " arg="$1" shift else install_prog= arg=$nonopt fi # The real first argument should be the name of the installation program. # Aesthetically quote it. arg=`$echo "X$arg" | $Xsed -e "$sed_quote_subst"` case $arg in *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*|"") arg="\"$arg\"" ;; esac install_prog="$install_prog$arg" # We need to accept at least all the BSD install flags. dest= files= opts= prev= install_type= isdir=no stripme= for arg do if test -n "$dest"; then files="$files $dest" dest=$arg continue fi case $arg in -d) isdir=yes ;; -f) case " $install_prog " in *[\\\ /]cp\ *) ;; *) prev=$arg ;; esac ;; -g | -m | -o) prev=$arg ;; -s) stripme=" -s" continue ;; -*) ;; *) # If the previous option needed an argument, then skip it. if test -n "$prev"; then prev= else dest=$arg continue fi ;; esac # Aesthetically quote the argument. arg=`$echo "X$arg" | $Xsed -e "$sed_quote_subst"` case $arg in *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*|"") arg="\"$arg\"" ;; esac install_prog="$install_prog $arg" done if test -z "$install_prog"; then $echo "$modename: you must specify an install program" 1>&2 $echo "$help" 1>&2 exit $EXIT_FAILURE fi if test -n "$prev"; then $echo "$modename: the \`$prev' option requires an argument" 1>&2 $echo "$help" 1>&2 exit $EXIT_FAILURE fi if test -z "$files"; then if test -z "$dest"; then $echo "$modename: no file or destination specified" 1>&2 else $echo "$modename: you must specify a destination" 1>&2 fi $echo "$help" 1>&2 exit $EXIT_FAILURE fi # Strip any trailing slash from the destination. dest=`$echo "X$dest" | $Xsed -e 's%/$%%'` # Check to see that the destination is a directory. test -d "$dest" && isdir=yes if test "$isdir" = yes; then destdir="$dest" destname= else destdir=`$echo "X$dest" | $Xsed -e 's%/[^/]*$%%'` test "X$destdir" = "X$dest" && destdir=. destname=`$echo "X$dest" | $Xsed -e 's%^.*/%%'` # Not a directory, so check to see that there is only one file specified. set dummy $files if test "$#" -gt 2; then $echo "$modename: \`$dest' is not a directory" 1>&2 $echo "$help" 1>&2 exit $EXIT_FAILURE fi fi case $destdir in [\\/]* | [A-Za-z]:[\\/]*) ;; *) for file in $files; do case $file in *.lo) ;; *) $echo "$modename: \`$destdir' must be an absolute directory name" 1>&2 $echo "$help" 1>&2 exit $EXIT_FAILURE ;; esac done ;; esac # This variable tells wrapper scripts just to set variables rather # than running their programs. libtool_install_magic="$magic" staticlibs= future_libdirs= current_libdirs= for file in $files; do # Do each installation. case $file in *.$libext) # Do the static libraries later. staticlibs="$staticlibs $file" ;; *.la) # Check to see that this really is a libtool archive. if (${SED} -e '2q' $file | grep "^# Generated by .*$PACKAGE") >/dev/null 2>&1; then : else $echo "$modename: \`$file' is not a valid libtool archive" 1>&2 $echo "$help" 1>&2 exit $EXIT_FAILURE fi library_names= old_library= relink_command= # If there is no directory component, then add one. case $file in */* | *\\*) . $file ;; *) . ./$file ;; esac # Add the libdir to current_libdirs if it is the destination. if test "X$destdir" = "X$libdir"; then case "$current_libdirs " in *" $libdir "*) ;; *) current_libdirs="$current_libdirs $libdir" ;; esac else # Note the libdir as a future libdir. case "$future_libdirs " in *" $libdir "*) ;; *) future_libdirs="$future_libdirs $libdir" ;; esac fi dir=`$echo "X$file" | $Xsed -e 's%/[^/]*$%%'`/ test "X$dir" = "X$file/" && dir= dir="$dir$objdir" if test -n "$relink_command"; then # Determine the prefix the user has applied to our future dir. inst_prefix_dir=`$echo "$destdir" | $SED "s%$libdir\$%%"` # Don't allow the user to place us outside of our expected # location b/c this prevents finding dependent libraries that # are installed to the same prefix. # At present, this check doesn't affect windows .dll's that # are installed into $libdir/../bin (currently, that works fine) # but it's something to keep an eye on. if test "$inst_prefix_dir" = "$destdir"; then $echo "$modename: error: cannot install \`$file' to a directory not ending in $libdir" 1>&2 exit $EXIT_FAILURE fi if test -n "$inst_prefix_dir"; then # Stick the inst_prefix_dir data into the link command. relink_command=`$echo "$relink_command" | $SP2NL | $SED "s%@inst_prefix_dir@%-inst-prefix-dir $inst_prefix_dir%" | $NL2SP` else relink_command=`$echo "$relink_command" | $SP2NL | $SED "s%@inst_prefix_dir@%%" | $NL2SP` fi $echo "$modename: warning: relinking \`$file'" 1>&2 $show "$relink_command" if $run eval "$relink_command"; then : else $echo "$modename: error: relink \`$file' with the above command before installing it" 1>&2 exit $EXIT_FAILURE fi fi # See the names of the shared library. set dummy $library_names if test -n "$2"; then realname="$2" shift shift srcname="$realname" test -n "$relink_command" && srcname="$realname"T # Install the shared library and build the symlinks. $show "$install_prog $dir/$srcname $destdir/$realname" $run eval "$install_prog $dir/$srcname $destdir/$realname" || exit $? if test -n "$stripme" && test -n "$striplib"; then $show "$striplib $destdir/$realname" $run eval "$striplib $destdir/$realname" || exit $? fi if test "$#" -gt 0; then # Delete the old symlinks, and create new ones. # Try `ln -sf' first, because the `ln' binary might depend on # the symlink we replace! Solaris /bin/ln does not understand -f, # so we also need to try rm && ln -s. for linkname do if test "$linkname" != "$realname"; then $show "(cd $destdir && { $LN_S -f $realname $linkname || { $rm $linkname && $LN_S $realname $linkname; }; })" $run eval "(cd $destdir && { $LN_S -f $realname $linkname || { $rm $linkname && $LN_S $realname $linkname; }; })" fi done fi # Do each command in the postinstall commands. lib="$destdir/$realname" cmds=$postinstall_cmds save_ifs="$IFS"; IFS='~' for cmd in $cmds; do IFS="$save_ifs" eval cmd=\"$cmd\" $show "$cmd" $run eval "$cmd" || { lt_exit=$? # Restore the uninstalled library and exit if test "$mode" = relink; then $run eval '(cd $output_objdir && $rm ${realname}T && $mv ${realname}U $realname)' fi exit $lt_exit } done IFS="$save_ifs" fi # Install the pseudo-library for information purposes. name=`$echo "X$file" | $Xsed -e 's%^.*/%%'` instname="$dir/$name"i $show "$install_prog $instname $destdir/$name" $run eval "$install_prog $instname $destdir/$name" || exit $? # Maybe install the static library, too. test -n "$old_library" && staticlibs="$staticlibs $dir/$old_library" ;; *.lo) # Install (i.e. copy) a libtool object. # Figure out destination file name, if it wasn't already specified. if test -n "$destname"; then destfile="$destdir/$destname" else destfile=`$echo "X$file" | $Xsed -e 's%^.*/%%'` destfile="$destdir/$destfile" fi # Deduce the name of the destination old-style object file. case $destfile in *.lo) staticdest=`$echo "X$destfile" | $Xsed -e "$lo2o"` ;; *.$objext) staticdest="$destfile" destfile= ;; *) $echo "$modename: cannot copy a libtool object to \`$destfile'" 1>&2 $echo "$help" 1>&2 exit $EXIT_FAILURE ;; esac # Install the libtool object if requested. if test -n "$destfile"; then $show "$install_prog $file $destfile" $run eval "$install_prog $file $destfile" || exit $? fi # Install the old object if enabled. if test "$build_old_libs" = yes; then # Deduce the name of the old-style object file. staticobj=`$echo "X$file" | $Xsed -e "$lo2o"` $show "$install_prog $staticobj $staticdest" $run eval "$install_prog \$staticobj \$staticdest" || exit $? fi exit $EXIT_SUCCESS ;; *) # Figure out destination file name, if it wasn't already specified. if test -n "$destname"; then destfile="$destdir/$destname" else destfile=`$echo "X$file" | $Xsed -e 's%^.*/%%'` destfile="$destdir/$destfile" fi # If the file is missing, and there is a .exe on the end, strip it # because it is most likely a libtool script we actually want to # install stripped_ext="" case $file in *.exe) if test ! -f "$file"; then file=`$echo $file|${SED} 's,.exe$,,'` stripped_ext=".exe" fi ;; esac # Do a test to see if this is really a libtool program. case $host in *cygwin*|*mingw*) wrapper=`$echo $file | ${SED} -e 's,.exe$,,'` ;; *) wrapper=$file ;; esac if (${SED} -e '4q' $wrapper | grep "^# Generated by .*$PACKAGE")>/dev/null 2>&1; then notinst_deplibs= relink_command= # Note that it is not necessary on cygwin/mingw to append a dot to # foo even if both foo and FILE.exe exist: automatic-append-.exe # behavior happens only for exec(3), not for open(2)! Also, sourcing # `FILE.' does not work on cygwin managed mounts. # # If there is no directory component, then add one. case $wrapper in */* | *\\*) . ${wrapper} ;; *) . ./${wrapper} ;; esac # Check the variables that should have been set. if test -z "$notinst_deplibs"; then $echo "$modename: invalid libtool wrapper script \`$wrapper'" 1>&2 exit $EXIT_FAILURE fi finalize=yes for lib in $notinst_deplibs; do # Check to see that each library is installed. libdir= if test -f "$lib"; then # If there is no directory component, then add one. case $lib in */* | *\\*) . $lib ;; *) . ./$lib ;; esac fi libfile="$libdir/"`$echo "X$lib" | $Xsed -e 's%^.*/%%g'` ### testsuite: skip nested quoting test if test -n "$libdir" && test ! -f "$libfile"; then $echo "$modename: warning: \`$lib' has not been installed in \`$libdir'" 1>&2 finalize=no fi done relink_command= # Note that it is not necessary on cygwin/mingw to append a dot to # foo even if both foo and FILE.exe exist: automatic-append-.exe # behavior happens only for exec(3), not for open(2)! Also, sourcing # `FILE.' does not work on cygwin managed mounts. # # If there is no directory component, then add one. case $wrapper in */* | *\\*) . ${wrapper} ;; *) . ./${wrapper} ;; esac outputname= if test "$fast_install" = no && test -n "$relink_command"; then if test "$finalize" = yes && test -z "$run"; then tmpdir=`func_mktempdir` file=`$echo "X$file$stripped_ext" | $Xsed -e 's%^.*/%%'` outputname="$tmpdir/$file" # Replace the output file specification. relink_command=`$echo "X$relink_command" | $SP2NL | $Xsed -e 's%@OUTPUT@%'"$outputname"'%g' | $NL2SP` $show "$relink_command" if $run eval "$relink_command"; then : else $echo "$modename: error: relink \`$file' with the above command before installing it" 1>&2 ${rm}r "$tmpdir" continue fi file="$outputname" else $echo "$modename: warning: cannot relink \`$file'" 1>&2 fi else # Install the binary that we compiled earlier. file=`$echo "X$file$stripped_ext" | $Xsed -e "s%\([^/]*\)$%$objdir/\1%"` fi fi # remove .exe since cygwin /usr/bin/install will append another # one anyway case $install_prog,$host in */usr/bin/install*,*cygwin*) case $file:$destfile in *.exe:*.exe) # this is ok ;; *.exe:*) destfile=$destfile.exe ;; *:*.exe) destfile=`$echo $destfile | ${SED} -e 's,.exe$,,'` ;; esac ;; esac $show "$install_prog$stripme $file $destfile" $run eval "$install_prog\$stripme \$file \$destfile" || exit $? test -n "$outputname" && ${rm}r "$tmpdir" ;; esac done for file in $staticlibs; do name=`$echo "X$file" | $Xsed -e 's%^.*/%%'` # Set up the ranlib parameters. oldlib="$destdir/$name" $show "$install_prog $file $oldlib" $run eval "$install_prog \$file \$oldlib" || exit $? if test -n "$stripme" && test -n "$old_striplib"; then $show "$old_striplib $oldlib" $run eval "$old_striplib $oldlib" || exit $? fi # Do each command in the postinstall commands. cmds=$old_postinstall_cmds save_ifs="$IFS"; IFS='~' for cmd in $cmds; do IFS="$save_ifs" eval cmd=\"$cmd\" $show "$cmd" $run eval "$cmd" || exit $? done IFS="$save_ifs" done if test -n "$future_libdirs"; then $echo "$modename: warning: remember to run \`$progname --finish$future_libdirs'" 1>&2 fi if test -n "$current_libdirs"; then # Maybe just do a dry run. test -n "$run" && current_libdirs=" -n$current_libdirs" exec_cmd='$SHELL $progpath $preserve_args --finish$current_libdirs' else exit $EXIT_SUCCESS fi ;; # libtool finish mode finish) modename="$modename: finish" libdirs="$nonopt" admincmds= if test -n "$finish_cmds$finish_eval" && test -n "$libdirs"; then for dir do libdirs="$libdirs $dir" done for libdir in $libdirs; do if test -n "$finish_cmds"; then # Do each command in the finish commands. cmds=$finish_cmds save_ifs="$IFS"; IFS='~' for cmd in $cmds; do IFS="$save_ifs" eval cmd=\"$cmd\" $show "$cmd" $run eval "$cmd" || admincmds="$admincmds $cmd" done IFS="$save_ifs" fi if test -n "$finish_eval"; then # Do the single finish_eval. eval cmds=\"$finish_eval\" $run eval "$cmds" || admincmds="$admincmds $cmds" fi done fi # Exit here if they wanted silent mode. test "$show" = : && exit $EXIT_SUCCESS $echo "X----------------------------------------------------------------------" | $Xsed $echo "Libraries have been installed in:" for libdir in $libdirs; do $echo " $libdir" done $echo $echo "If you ever happen to want to link against installed libraries" $echo "in a given directory, LIBDIR, you must either use libtool, and" $echo "specify the full pathname of the library, or use the \`-LLIBDIR'" $echo "flag during linking and do at least one of the following:" if test -n "$shlibpath_var"; then $echo " - add LIBDIR to the \`$shlibpath_var' environment variable" $echo " during execution" fi if test -n "$runpath_var"; then $echo " - add LIBDIR to the \`$runpath_var' environment variable" $echo " during linking" fi if test -n "$hardcode_libdir_flag_spec"; then libdir=LIBDIR eval flag=\"$hardcode_libdir_flag_spec\" $echo " - use the \`$flag' linker flag" fi if test -n "$admincmds"; then $echo " - have your system administrator run these commands:$admincmds" fi if test -f /etc/ld.so.conf; then $echo " - have your system administrator add LIBDIR to \`/etc/ld.so.conf'" fi $echo $echo "See any operating system documentation about shared libraries for" $echo "more information, such as the ld(1) and ld.so(8) manual pages." $echo "X----------------------------------------------------------------------" | $Xsed exit $EXIT_SUCCESS ;; # libtool execute mode execute) modename="$modename: execute" # The first argument is the command name. cmd="$nonopt" if test -z "$cmd"; then $echo "$modename: you must specify a COMMAND" 1>&2 $echo "$help" exit $EXIT_FAILURE fi # Handle -dlopen flags immediately. for file in $execute_dlfiles; do if test ! -f "$file"; then $echo "$modename: \`$file' is not a file" 1>&2 $echo "$help" 1>&2 exit $EXIT_FAILURE fi dir= case $file in *.la) # Check to see that this really is a libtool archive. if (${SED} -e '2q' $file | grep "^# Generated by .*$PACKAGE") >/dev/null 2>&1; then : else $echo "$modename: \`$lib' is not a valid libtool archive" 1>&2 $echo "$help" 1>&2 exit $EXIT_FAILURE fi # Read the libtool library. dlname= library_names= # If there is no directory component, then add one. case $file in */* | *\\*) . $file ;; *) . ./$file ;; esac # Skip this library if it cannot be dlopened. if test -z "$dlname"; then # Warn if it was a shared library. test -n "$library_names" && $echo "$modename: warning: \`$file' was not linked with \`-export-dynamic'" continue fi dir=`$echo "X$file" | $Xsed -e 's%/[^/]*$%%'` test "X$dir" = "X$file" && dir=. if test -f "$dir/$objdir/$dlname"; then dir="$dir/$objdir" else if test ! -f "$dir/$dlname"; then $echo "$modename: cannot find \`$dlname' in \`$dir' or \`$dir/$objdir'" 1>&2 exit $EXIT_FAILURE fi fi ;; *.lo) # Just add the directory containing the .lo file. dir=`$echo "X$file" | $Xsed -e 's%/[^/]*$%%'` test "X$dir" = "X$file" && dir=. ;; *) $echo "$modename: warning \`-dlopen' is ignored for non-libtool libraries and objects" 1>&2 continue ;; esac # Get the absolute pathname. absdir=`cd "$dir" && pwd` test -n "$absdir" && dir="$absdir" # Now add the directory to shlibpath_var. if eval "test -z \"\$$shlibpath_var\""; then eval "$shlibpath_var=\"\$dir\"" else eval "$shlibpath_var=\"\$dir:\$$shlibpath_var\"" fi done # This variable tells wrapper scripts just to set shlibpath_var # rather than running their programs. libtool_execute_magic="$magic" # Check if any of the arguments is a wrapper script. args= for file do case $file in -*) ;; *) # Do a test to see if this is really a libtool program. if (${SED} -e '4q' $file | grep "^# Generated by .*$PACKAGE") >/dev/null 2>&1; then # If there is no directory component, then add one. case $file in */* | *\\*) . $file ;; *) . ./$file ;; esac # Transform arg to wrapped name. file="$progdir/$program" fi ;; esac # Quote arguments (to preserve shell metacharacters). file=`$echo "X$file" | $Xsed -e "$sed_quote_subst"` args="$args \"$file\"" done if test -z "$run"; then if test -n "$shlibpath_var"; then # Export the shlibpath_var. eval "export $shlibpath_var" fi # Restore saved environment variables for lt_var in LANG LC_ALL LC_CTYPE LC_COLLATE LC_MESSAGES do eval "if test \"\${save_$lt_var+set}\" = set; then $lt_var=\$save_$lt_var; export $lt_var fi" done # Now prepare to actually exec the command. exec_cmd="\$cmd$args" else # Display what would be done. if test -n "$shlibpath_var"; then eval "\$echo \"\$shlibpath_var=\$$shlibpath_var\"" $echo "export $shlibpath_var" fi $echo "$cmd$args" exit $EXIT_SUCCESS fi ;; # libtool clean and uninstall mode clean | uninstall) modename="$modename: $mode" rm="$nonopt" files= rmforce= exit_status=0 # This variable tells wrapper scripts just to set variables rather # than running their programs. libtool_install_magic="$magic" for arg do case $arg in -f) rm="$rm $arg"; rmforce=yes ;; -*) rm="$rm $arg" ;; *) files="$files $arg" ;; esac done if test -z "$rm"; then $echo "$modename: you must specify an RM program" 1>&2 $echo "$help" 1>&2 exit $EXIT_FAILURE fi rmdirs= origobjdir="$objdir" for file in $files; do dir=`$echo "X$file" | $Xsed -e 's%/[^/]*$%%'` if test "X$dir" = "X$file"; then dir=. objdir="$origobjdir" else objdir="$dir/$origobjdir" fi name=`$echo "X$file" | $Xsed -e 's%^.*/%%'` test "$mode" = uninstall && objdir="$dir" # Remember objdir for removal later, being careful to avoid duplicates if test "$mode" = clean; then case " $rmdirs " in *" $objdir "*) ;; *) rmdirs="$rmdirs $objdir" ;; esac fi # Don't error if the file doesn't exist and rm -f was used. if (test -L "$file") >/dev/null 2>&1 \ || (test -h "$file") >/dev/null 2>&1 \ || test -f "$file"; then : elif test -d "$file"; then exit_status=1 continue elif test "$rmforce" = yes; then continue fi rmfiles="$file" case $name in *.la) # Possibly a libtool archive, so verify it. if (${SED} -e '2q' $file | grep "^# Generated by .*$PACKAGE") >/dev/null 2>&1; then . $dir/$name # Delete the libtool libraries and symlinks. for n in $library_names; do rmfiles="$rmfiles $objdir/$n" done test -n "$old_library" && rmfiles="$rmfiles $objdir/$old_library" case "$mode" in clean) case " $library_names " in # " " in the beginning catches empty $dlname *" $dlname "*) ;; *) rmfiles="$rmfiles $objdir/$dlname" ;; esac test -n "$libdir" && rmfiles="$rmfiles $objdir/$name $objdir/${name}i" ;; uninstall) if test -n "$library_names"; then # Do each command in the postuninstall commands. cmds=$postuninstall_cmds save_ifs="$IFS"; IFS='~' for cmd in $cmds; do IFS="$save_ifs" eval cmd=\"$cmd\" $show "$cmd" $run eval "$cmd" if test "$?" -ne 0 && test "$rmforce" != yes; then exit_status=1 fi done IFS="$save_ifs" fi if test -n "$old_library"; then # Do each command in the old_postuninstall commands. cmds=$old_postuninstall_cmds save_ifs="$IFS"; IFS='~' for cmd in $cmds; do IFS="$save_ifs" eval cmd=\"$cmd\" $show "$cmd" $run eval "$cmd" if test "$?" -ne 0 && test "$rmforce" != yes; then exit_status=1 fi done IFS="$save_ifs" fi # FIXME: should reinstall the best remaining shared library. ;; esac fi ;; *.lo) # Possibly a libtool object, so verify it. if (${SED} -e '2q' $file | grep "^# Generated by .*$PACKAGE") >/dev/null 2>&1; then # Read the .lo file . $dir/$name # Add PIC object to the list of files to remove. if test -n "$pic_object" \ && test "$pic_object" != none; then rmfiles="$rmfiles $dir/$pic_object" fi # Add non-PIC object to the list of files to remove. if test -n "$non_pic_object" \ && test "$non_pic_object" != none; then rmfiles="$rmfiles $dir/$non_pic_object" fi fi ;; *) if test "$mode" = clean ; then noexename=$name case $file in *.exe) file=`$echo $file|${SED} 's,.exe$,,'` noexename=`$echo $name|${SED} 's,.exe$,,'` # $file with .exe has already been added to rmfiles, # add $file without .exe rmfiles="$rmfiles $file" ;; esac # Do a test to see if this is a libtool program. if (${SED} -e '4q' $file | grep "^# Generated by .*$PACKAGE") >/dev/null 2>&1; then relink_command= . $dir/$noexename # note $name still contains .exe if it was in $file originally # as does the version of $file that was added into $rmfiles rmfiles="$rmfiles $objdir/$name $objdir/${name}S.${objext}" if test "$fast_install" = yes && test -n "$relink_command"; then rmfiles="$rmfiles $objdir/lt-$name" fi if test "X$noexename" != "X$name" ; then rmfiles="$rmfiles $objdir/lt-${noexename}.c" fi fi fi ;; esac $show "$rm $rmfiles" $run $rm $rmfiles || exit_status=1 done objdir="$origobjdir" # Try to remove the ${objdir}s in the directories where we deleted files for dir in $rmdirs; do if test -d "$dir"; then $show "rmdir $dir" $run rmdir $dir >/dev/null 2>&1 fi done exit $exit_status ;; "") $echo "$modename: you must specify a MODE" 1>&2 $echo "$generic_help" 1>&2 exit $EXIT_FAILURE ;; esac if test -z "$exec_cmd"; then $echo "$modename: invalid operation mode \`$mode'" 1>&2 $echo "$generic_help" 1>&2 exit $EXIT_FAILURE fi fi # test -z "$show_help" if test -n "$exec_cmd"; then eval exec $exec_cmd exit $EXIT_FAILURE fi # We need to display help for each of the modes. case $mode in "") $echo \ "Usage: $modename [OPTION]... [MODE-ARG]... Provide generalized library-building support services. --config show all configuration variables --debug enable verbose shell tracing -n, --dry-run display commands without modifying any files --features display basic configuration information and exit --finish same as \`--mode=finish' --help display this help message and exit --mode=MODE use operation mode MODE [default=inferred from MODE-ARGS] --quiet same as \`--silent' --silent don't print informational messages --tag=TAG use configuration variables from tag TAG --version print version information MODE must be one of the following: clean remove files from the build directory compile compile a source file into a libtool object execute automatically set library path, then run a program finish complete the installation of libtool libraries install install libraries or executables link create a library or an executable uninstall remove libraries from an installed directory MODE-ARGS vary depending on the MODE. Try \`$modename --help --mode=MODE' for a more detailed description of MODE. Report bugs to ." exit $EXIT_SUCCESS ;; clean) $echo \ "Usage: $modename [OPTION]... --mode=clean RM [RM-OPTION]... FILE... Remove files from the build directory. RM is the name of the program to use to delete files associated with each FILE (typically \`/bin/rm'). RM-OPTIONS are options (such as \`-f') to be passed to RM. If FILE is a libtool library, object or program, all the files associated with it are deleted. Otherwise, only FILE itself is deleted using RM." ;; compile) $echo \ "Usage: $modename [OPTION]... --mode=compile COMPILE-COMMAND... SOURCEFILE Compile a source file into a libtool library object. This mode accepts the following additional options: -o OUTPUT-FILE set the output file name to OUTPUT-FILE -prefer-pic try to building PIC objects only -prefer-non-pic try to building non-PIC objects only -static always build a \`.o' file suitable for static linking COMPILE-COMMAND is a command to be used in creating a \`standard' object file from the given SOURCEFILE. The output file name is determined by removing the directory component from SOURCEFILE, then substituting the C source code suffix \`.c' with the library object suffix, \`.lo'." ;; execute) $echo \ "Usage: $modename [OPTION]... --mode=execute COMMAND [ARGS]... Automatically set library path, then run a program. This mode accepts the following additional options: -dlopen FILE add the directory containing FILE to the library path This mode sets the library path environment variable according to \`-dlopen' flags. If any of the ARGS are libtool executable wrappers, then they are translated into their corresponding uninstalled binary, and any of their required library directories are added to the library path. Then, COMMAND is executed, with ARGS as arguments." ;; finish) $echo \ "Usage: $modename [OPTION]... --mode=finish [LIBDIR]... Complete the installation of libtool libraries. Each LIBDIR is a directory that contains libtool libraries. The commands that this mode executes may require superuser privileges. Use the \`--dry-run' option if you just want to see what would be executed." ;; install) $echo \ "Usage: $modename [OPTION]... --mode=install INSTALL-COMMAND... Install executables or libraries. INSTALL-COMMAND is the installation command. The first component should be either the \`install' or \`cp' program. The rest of the components are interpreted as arguments to that command (only BSD-compatible install options are recognized)." ;; link) $echo \ "Usage: $modename [OPTION]... --mode=link LINK-COMMAND... Link object files or libraries together to form another library, or to create an executable program. LINK-COMMAND is a command using the C compiler that you would use to create a program from several object files. The following components of LINK-COMMAND are treated specially: -all-static do not do any dynamic linking at all -avoid-version do not add a version suffix if possible -dlopen FILE \`-dlpreopen' FILE if it cannot be dlopened at runtime -dlpreopen FILE link in FILE and add its symbols to lt_preloaded_symbols -export-dynamic allow symbols from OUTPUT-FILE to be resolved with dlsym(3) -export-symbols SYMFILE try to export only the symbols listed in SYMFILE -export-symbols-regex REGEX try to export only the symbols matching REGEX -LLIBDIR search LIBDIR for required installed libraries -lNAME OUTPUT-FILE requires the installed library libNAME -module build a library that can dlopened -no-fast-install disable the fast-install mode -no-install link a not-installable executable -no-undefined declare that a library does not refer to external symbols -o OUTPUT-FILE create OUTPUT-FILE from the specified objects -objectlist FILE Use a list of object files found in FILE to specify objects -precious-files-regex REGEX don't remove output files matching REGEX -release RELEASE specify package release information -rpath LIBDIR the created library will eventually be installed in LIBDIR -R[ ]LIBDIR add LIBDIR to the runtime path of programs and libraries -static do not do any dynamic linking of uninstalled libtool libraries -static-libtool-libs do not do any dynamic linking of libtool libraries -version-info CURRENT[:REVISION[:AGE]] specify library version info [each variable defaults to 0] All other options (arguments beginning with \`-') are ignored. Every other argument is treated as a filename. Files ending in \`.la' are treated as uninstalled libtool libraries, other files are standard or library object files. If the OUTPUT-FILE ends in \`.la', then a libtool library is created, only library objects (\`.lo' files) may be specified, and \`-rpath' is required, except when creating a convenience library. If OUTPUT-FILE ends in \`.a' or \`.lib', then a standard library is created using \`ar' and \`ranlib', or on Windows using \`lib'. If OUTPUT-FILE ends in \`.lo' or \`.${objext}', then a reloadable object file is created, otherwise an executable program is created." ;; uninstall) $echo \ "Usage: $modename [OPTION]... --mode=uninstall RM [RM-OPTION]... FILE... Remove libraries from an installation directory. RM is the name of the program to use to delete files associated with each FILE (typically \`/bin/rm'). RM-OPTIONS are options (such as \`-f') to be passed to RM. If FILE is a libtool library, all the files associated with it are deleted. Otherwise, only FILE itself is deleted using RM." ;; *) $echo "$modename: invalid operation mode \`$mode'" 1>&2 $echo "$help" 1>&2 exit $EXIT_FAILURE ;; esac $echo $echo "Try \`$modename --help' for more information about other modes." exit $? # The TAGs below are defined such that we never get into a situation # in which we disable both kinds of libraries. Given conflicting # choices, we go for a static library, that is the most portable, # since we can't tell whether shared libraries were disabled because # the user asked for that or because the platform doesn't support # them. This is particularly important on AIX, because we don't # support having both static and shared libraries enabled at the same # time on that platform, so we default to a shared-only configuration. # If a disable-shared tag is given, we'll fallback to a static-only # configuration. But we'll never go from static-only to shared-only. # ### BEGIN LIBTOOL TAG CONFIG: disable-shared disable_libs=shared # ### END LIBTOOL TAG CONFIG: disable-shared # ### BEGIN LIBTOOL TAG CONFIG: disable-static disable_libs=static # ### END LIBTOOL TAG CONFIG: disable-static # Local Variables: # mode:shell-script # sh-indentation:2 # End: ./CBFlib-0.9.2.2/libtool/config.guess0000755000076500007650000012706311603702120015567 0ustar yayayaya#! /bin/sh # Attempt to guess a canonical system name. # Copyright (C) 1992, 1993, 1994, 1995, 1996, 1997, 1998, 1999, # 2000, 2001, 2002, 2003, 2004, 2005, 2006 Free Software Foundation, # Inc. timestamp='2007-05-17' # This file is free software; you can redistribute it and/or modify it # under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2 of the License, or # (at your option) any later version. # # This program is distributed in the hope that it will be useful, but # WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # General Public License for more details. # # You should have received a copy of the GNU General Public License # along with this program; if not, write to the Free Software # Foundation, Inc., 51 Franklin Street - Fifth Floor, Boston, MA # 02110-1301, USA. # # As a special exception to the GNU General Public License, if you # distribute this file as part of a program that contains a # configuration script generated by Autoconf, you may include it under # the same distribution terms that you use for the rest of that program. # Originally written by Per Bothner . # Please send patches to . Submit a context # diff and a properly formatted ChangeLog entry. # # This script attempts to guess a canonical system name similar to # config.sub. If it succeeds, it prints the system name on stdout, and # exits with 0. Otherwise, it exits with 1. # # The plan is that this can be called by configure scripts if you # don't specify an explicit build system type. me=`echo "$0" | sed -e 's,.*/,,'` usage="\ Usage: $0 [OPTION] Output the configuration name of the system \`$me' is run on. Operation modes: -h, --help print this help, then exit -t, --time-stamp print date of last modification, then exit -v, --version print version number, then exit Report bugs and patches to ." version="\ GNU config.guess ($timestamp) Originally written by Per Bothner. Copyright (C) 1992, 1993, 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002, 2003, 2004, 2005 Free Software Foundation, Inc. This is free software; see the source for copying conditions. There is NO warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE." help=" Try \`$me --help' for more information." # Parse command line while test $# -gt 0 ; do case $1 in --time-stamp | --time* | -t ) echo "$timestamp" ; exit ;; --version | -v ) echo "$version" ; exit ;; --help | --h* | -h ) echo "$usage"; exit ;; -- ) # Stop option processing shift; break ;; - ) # Use stdin as input. break ;; -* ) echo "$me: invalid option $1$help" >&2 exit 1 ;; * ) break ;; esac done if test $# != 0; then echo "$me: too many arguments$help" >&2 exit 1 fi trap 'exit 1' 1 2 15 # CC_FOR_BUILD -- compiler used by this script. Note that the use of a # compiler to aid in system detection is discouraged as it requires # temporary files to be created and, as you can see below, it is a # headache to deal with in a portable fashion. # Historically, `CC_FOR_BUILD' used to be named `HOST_CC'. We still # use `HOST_CC' if defined, but it is deprecated. # Portable tmp directory creation inspired by the Autoconf team. set_cc_for_build=' trap "exitcode=\$?; (rm -f \$tmpfiles 2>/dev/null; rmdir \$tmp 2>/dev/null) && exit \$exitcode" 0 ; trap "rm -f \$tmpfiles 2>/dev/null; rmdir \$tmp 2>/dev/null; exit 1" 1 2 13 15 ; : ${TMPDIR=/tmp} ; { tmp=`(umask 077 && mktemp -d "$TMPDIR/cgXXXXXX") 2>/dev/null` && test -n "$tmp" && test -d "$tmp" ; } || { test -n "$RANDOM" && tmp=$TMPDIR/cg$$-$RANDOM && (umask 077 && mkdir $tmp) ; } || { tmp=$TMPDIR/cg-$$ && (umask 077 && mkdir $tmp) && echo "Warning: creating insecure temp directory" >&2 ; } || { echo "$me: cannot create a temporary directory in $TMPDIR" >&2 ; exit 1 ; } ; dummy=$tmp/dummy ; tmpfiles="$dummy.c $dummy.o $dummy.rel $dummy" ; case $CC_FOR_BUILD,$HOST_CC,$CC in ,,) echo "int x;" > $dummy.c ; for c in cc gcc c89 c99 ; do if ($c -c -o $dummy.o $dummy.c) >/dev/null 2>&1 ; then CC_FOR_BUILD="$c"; break ; fi ; done ; if test x"$CC_FOR_BUILD" = x ; then CC_FOR_BUILD=no_compiler_found ; fi ;; ,,*) CC_FOR_BUILD=$CC ;; ,*,*) CC_FOR_BUILD=$HOST_CC ;; esac ; set_cc_for_build= ;' # This is needed to find uname on a Pyramid OSx when run in the BSD universe. # (ghazi@noc.rutgers.edu 1994-08-24) if (test -f /.attbin/uname) >/dev/null 2>&1 ; then PATH=$PATH:/.attbin ; export PATH fi UNAME_MACHINE=`(uname -m) 2>/dev/null` || UNAME_MACHINE=unknown UNAME_RELEASE=`(uname -r) 2>/dev/null` || UNAME_RELEASE=unknown UNAME_SYSTEM=`(uname -s) 2>/dev/null` || UNAME_SYSTEM=unknown UNAME_VERSION=`(uname -v) 2>/dev/null` || UNAME_VERSION=unknown # Note: order is significant - the case branches are not exclusive. case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in *:NetBSD:*:*) # NetBSD (nbsd) targets should (where applicable) match one or # more of the tupples: *-*-netbsdelf*, *-*-netbsdaout*, # *-*-netbsdecoff* and *-*-netbsd*. For targets that recently # switched to ELF, *-*-netbsd* would select the old # object file format. This provides both forward # compatibility and a consistent mechanism for selecting the # object file format. # # Note: NetBSD doesn't particularly care about the vendor # portion of the name. We always set it to "unknown". sysctl="sysctl -n hw.machine_arch" UNAME_MACHINE_ARCH=`(/sbin/$sysctl 2>/dev/null || \ /usr/sbin/$sysctl 2>/dev/null || echo unknown)` case "${UNAME_MACHINE_ARCH}" in armeb) machine=armeb-unknown ;; arm*) machine=arm-unknown ;; sh3el) machine=shl-unknown ;; sh3eb) machine=sh-unknown ;; sh5el) machine=sh5le-unknown ;; *) machine=${UNAME_MACHINE_ARCH}-unknown ;; esac # The Operating System including object format, if it has switched # to ELF recently, or will in the future. case "${UNAME_MACHINE_ARCH}" in arm*|i386|m68k|ns32k|sh3*|sparc|vax) eval $set_cc_for_build if echo __ELF__ | $CC_FOR_BUILD -E - 2>/dev/null \ | grep __ELF__ >/dev/null then # Once all utilities can be ECOFF (netbsdecoff) or a.out (netbsdaout). # Return netbsd for either. FIX? os=netbsd else os=netbsdelf fi ;; *) os=netbsd ;; esac # The OS release # Debian GNU/NetBSD machines have a different userland, and # thus, need a distinct triplet. However, they do not need # kernel version information, so it can be replaced with a # suitable tag, in the style of linux-gnu. case "${UNAME_VERSION}" in Debian*) release='-gnu' ;; *) release=`echo ${UNAME_RELEASE}|sed -e 's/[-_].*/\./'` ;; esac # Since CPU_TYPE-MANUFACTURER-KERNEL-OPERATING_SYSTEM: # contains redundant information, the shorter form: # CPU_TYPE-MANUFACTURER-OPERATING_SYSTEM is used. echo "${machine}-${os}${release}" exit ;; *:OpenBSD:*:*) UNAME_MACHINE_ARCH=`arch | sed 's/OpenBSD.//'` echo ${UNAME_MACHINE_ARCH}-unknown-openbsd${UNAME_RELEASE} exit ;; *:ekkoBSD:*:*) echo ${UNAME_MACHINE}-unknown-ekkobsd${UNAME_RELEASE} exit ;; *:SolidBSD:*:*) echo ${UNAME_MACHINE}-unknown-solidbsd${UNAME_RELEASE} exit ;; macppc:MirBSD:*:*) echo powerpc-unknown-mirbsd${UNAME_RELEASE} exit ;; *:MirBSD:*:*) echo ${UNAME_MACHINE}-unknown-mirbsd${UNAME_RELEASE} exit ;; alpha:OSF1:*:*) case $UNAME_RELEASE in *4.0) UNAME_RELEASE=`/usr/sbin/sizer -v | awk '{print $3}'` ;; *5.*) UNAME_RELEASE=`/usr/sbin/sizer -v | awk '{print $4}'` ;; esac # According to Compaq, /usr/sbin/psrinfo has been available on # OSF/1 and Tru64 systems produced since 1995. I hope that # covers most systems running today. This code pipes the CPU # types through head -n 1, so we only detect the type of CPU 0. ALPHA_CPU_TYPE=`/usr/sbin/psrinfo -v | sed -n -e 's/^ The alpha \(.*\) processor.*$/\1/p' | head -n 1` case "$ALPHA_CPU_TYPE" in "EV4 (21064)") UNAME_MACHINE="alpha" ;; "EV4.5 (21064)") UNAME_MACHINE="alpha" ;; "LCA4 (21066/21068)") UNAME_MACHINE="alpha" ;; "EV5 (21164)") UNAME_MACHINE="alphaev5" ;; "EV5.6 (21164A)") UNAME_MACHINE="alphaev56" ;; "EV5.6 (21164PC)") UNAME_MACHINE="alphapca56" ;; "EV5.7 (21164PC)") UNAME_MACHINE="alphapca57" ;; "EV6 (21264)") UNAME_MACHINE="alphaev6" ;; "EV6.7 (21264A)") UNAME_MACHINE="alphaev67" ;; "EV6.8CB (21264C)") UNAME_MACHINE="alphaev68" ;; "EV6.8AL (21264B)") UNAME_MACHINE="alphaev68" ;; "EV6.8CX (21264D)") UNAME_MACHINE="alphaev68" ;; "EV6.9A (21264/EV69A)") UNAME_MACHINE="alphaev69" ;; "EV7 (21364)") UNAME_MACHINE="alphaev7" ;; "EV7.9 (21364A)") UNAME_MACHINE="alphaev79" ;; esac # A Pn.n version is a patched version. # A Vn.n version is a released version. # A Tn.n version is a released field test version. # A Xn.n version is an unreleased experimental baselevel. # 1.2 uses "1.2" for uname -r. echo ${UNAME_MACHINE}-dec-osf`echo ${UNAME_RELEASE} | sed -e 's/^[PVTX]//' | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz'` exit ;; Alpha\ *:Windows_NT*:*) # How do we know it's Interix rather than the generic POSIX subsystem? # Should we change UNAME_MACHINE based on the output of uname instead # of the specific Alpha model? echo alpha-pc-interix exit ;; 21064:Windows_NT:50:3) echo alpha-dec-winnt3.5 exit ;; Amiga*:UNIX_System_V:4.0:*) echo m68k-unknown-sysv4 exit ;; *:[Aa]miga[Oo][Ss]:*:*) echo ${UNAME_MACHINE}-unknown-amigaos exit ;; *:[Mm]orph[Oo][Ss]:*:*) echo ${UNAME_MACHINE}-unknown-morphos exit ;; *:OS/390:*:*) echo i370-ibm-openedition exit ;; *:z/VM:*:*) echo s390-ibm-zvmoe exit ;; *:OS400:*:*) echo powerpc-ibm-os400 exit ;; arm:RISC*:1.[012]*:*|arm:riscix:1.[012]*:*) echo arm-acorn-riscix${UNAME_RELEASE} exit ;; arm:riscos:*:*|arm:RISCOS:*:*) echo arm-unknown-riscos exit ;; SR2?01:HI-UX/MPP:*:* | SR8000:HI-UX/MPP:*:*) echo hppa1.1-hitachi-hiuxmpp exit ;; Pyramid*:OSx*:*:* | MIS*:OSx*:*:* | MIS*:SMP_DC-OSx*:*:*) # akee@wpdis03.wpafb.af.mil (Earle F. Ake) contributed MIS and NILE. if test "`(/bin/universe) 2>/dev/null`" = att ; then echo pyramid-pyramid-sysv3 else echo pyramid-pyramid-bsd fi exit ;; NILE*:*:*:dcosx) echo pyramid-pyramid-svr4 exit ;; DRS?6000:unix:4.0:6*) echo sparc-icl-nx6 exit ;; DRS?6000:UNIX_SV:4.2*:7* | DRS?6000:isis:4.2*:7*) case `/usr/bin/uname -p` in sparc) echo sparc-icl-nx7; exit ;; esac ;; sun4H:SunOS:5.*:*) echo sparc-hal-solaris2`echo ${UNAME_RELEASE}|sed -e 's/[^.]*//'` exit ;; sun4*:SunOS:5.*:* | tadpole*:SunOS:5.*:*) echo sparc-sun-solaris2`echo ${UNAME_RELEASE}|sed -e 's/[^.]*//'` exit ;; i86pc:SunOS:5.*:* | ix86xen:SunOS:5.*:*) echo i386-pc-solaris2`echo ${UNAME_RELEASE}|sed -e 's/[^.]*//'` exit ;; sun4*:SunOS:6*:*) # According to config.sub, this is the proper way to canonicalize # SunOS6. Hard to guess exactly what SunOS6 will be like, but # it's likely to be more like Solaris than SunOS4. echo sparc-sun-solaris3`echo ${UNAME_RELEASE}|sed -e 's/[^.]*//'` exit ;; sun4*:SunOS:*:*) case "`/usr/bin/arch -k`" in Series*|S4*) UNAME_RELEASE=`uname -v` ;; esac # Japanese Language versions have a version number like `4.1.3-JL'. echo sparc-sun-sunos`echo ${UNAME_RELEASE}|sed -e 's/-/_/'` exit ;; sun3*:SunOS:*:*) echo m68k-sun-sunos${UNAME_RELEASE} exit ;; sun*:*:4.2BSD:*) UNAME_RELEASE=`(sed 1q /etc/motd | awk '{print substr($5,1,3)}') 2>/dev/null` test "x${UNAME_RELEASE}" = "x" && UNAME_RELEASE=3 case "`/bin/arch`" in sun3) echo m68k-sun-sunos${UNAME_RELEASE} ;; sun4) echo sparc-sun-sunos${UNAME_RELEASE} ;; esac exit ;; aushp:SunOS:*:*) echo sparc-auspex-sunos${UNAME_RELEASE} exit ;; # The situation for MiNT is a little confusing. The machine name # can be virtually everything (everything which is not # "atarist" or "atariste" at least should have a processor # > m68000). The system name ranges from "MiNT" over "FreeMiNT" # to the lowercase version "mint" (or "freemint"). Finally # the system name "TOS" denotes a system which is actually not # MiNT. But MiNT is downward compatible to TOS, so this should # be no problem. atarist[e]:*MiNT:*:* | atarist[e]:*mint:*:* | atarist[e]:*TOS:*:*) echo m68k-atari-mint${UNAME_RELEASE} exit ;; atari*:*MiNT:*:* | atari*:*mint:*:* | atarist[e]:*TOS:*:*) echo m68k-atari-mint${UNAME_RELEASE} exit ;; *falcon*:*MiNT:*:* | *falcon*:*mint:*:* | *falcon*:*TOS:*:*) echo m68k-atari-mint${UNAME_RELEASE} exit ;; milan*:*MiNT:*:* | milan*:*mint:*:* | *milan*:*TOS:*:*) echo m68k-milan-mint${UNAME_RELEASE} exit ;; hades*:*MiNT:*:* | hades*:*mint:*:* | *hades*:*TOS:*:*) echo m68k-hades-mint${UNAME_RELEASE} exit ;; *:*MiNT:*:* | *:*mint:*:* | *:*TOS:*:*) echo m68k-unknown-mint${UNAME_RELEASE} exit ;; m68k:machten:*:*) echo m68k-apple-machten${UNAME_RELEASE} exit ;; powerpc:machten:*:*) echo powerpc-apple-machten${UNAME_RELEASE} exit ;; RISC*:Mach:*:*) echo mips-dec-mach_bsd4.3 exit ;; RISC*:ULTRIX:*:*) echo mips-dec-ultrix${UNAME_RELEASE} exit ;; VAX*:ULTRIX*:*:*) echo vax-dec-ultrix${UNAME_RELEASE} exit ;; 2020:CLIX:*:* | 2430:CLIX:*:*) echo clipper-intergraph-clix${UNAME_RELEASE} exit ;; mips:*:*:UMIPS | mips:*:*:RISCos) eval $set_cc_for_build sed 's/^ //' << EOF >$dummy.c #ifdef __cplusplus #include /* for printf() prototype */ int main (int argc, char *argv[]) { #else int main (argc, argv) int argc; char *argv[]; { #endif #if defined (host_mips) && defined (MIPSEB) #if defined (SYSTYPE_SYSV) printf ("mips-mips-riscos%ssysv\n", argv[1]); exit (0); #endif #if defined (SYSTYPE_SVR4) printf ("mips-mips-riscos%ssvr4\n", argv[1]); exit (0); #endif #if defined (SYSTYPE_BSD43) || defined(SYSTYPE_BSD) printf ("mips-mips-riscos%sbsd\n", argv[1]); exit (0); #endif #endif exit (-1); } EOF $CC_FOR_BUILD -o $dummy $dummy.c && dummyarg=`echo "${UNAME_RELEASE}" | sed -n 's/\([0-9]*\).*/\1/p'` && SYSTEM_NAME=`$dummy $dummyarg` && { echo "$SYSTEM_NAME"; exit; } echo mips-mips-riscos${UNAME_RELEASE} exit ;; Motorola:PowerMAX_OS:*:*) echo powerpc-motorola-powermax exit ;; Motorola:*:4.3:PL8-*) echo powerpc-harris-powermax exit ;; Night_Hawk:*:*:PowerMAX_OS | Synergy:PowerMAX_OS:*:*) echo powerpc-harris-powermax exit ;; Night_Hawk:Power_UNIX:*:*) echo powerpc-harris-powerunix exit ;; m88k:CX/UX:7*:*) echo m88k-harris-cxux7 exit ;; m88k:*:4*:R4*) echo m88k-motorola-sysv4 exit ;; m88k:*:3*:R3*) echo m88k-motorola-sysv3 exit ;; AViiON:dgux:*:*) # DG/UX returns AViiON for all architectures UNAME_PROCESSOR=`/usr/bin/uname -p` if [ $UNAME_PROCESSOR = mc88100 ] || [ $UNAME_PROCESSOR = mc88110 ] then if [ ${TARGET_BINARY_INTERFACE}x = m88kdguxelfx ] || \ [ ${TARGET_BINARY_INTERFACE}x = x ] then echo m88k-dg-dgux${UNAME_RELEASE} else echo m88k-dg-dguxbcs${UNAME_RELEASE} fi else echo i586-dg-dgux${UNAME_RELEASE} fi exit ;; M88*:DolphinOS:*:*) # DolphinOS (SVR3) echo m88k-dolphin-sysv3 exit ;; M88*:*:R3*:*) # Delta 88k system running SVR3 echo m88k-motorola-sysv3 exit ;; XD88*:*:*:*) # Tektronix XD88 system running UTekV (SVR3) echo m88k-tektronix-sysv3 exit ;; Tek43[0-9][0-9]:UTek:*:*) # Tektronix 4300 system running UTek (BSD) echo m68k-tektronix-bsd exit ;; *:IRIX*:*:*) echo mips-sgi-irix`echo ${UNAME_RELEASE}|sed -e 's/-/_/g'` exit ;; ????????:AIX?:[12].1:2) # AIX 2.2.1 or AIX 2.1.1 is RT/PC AIX. echo romp-ibm-aix # uname -m gives an 8 hex-code CPU id exit ;; # Note that: echo "'`uname -s`'" gives 'AIX ' i*86:AIX:*:*) echo i386-ibm-aix exit ;; ia64:AIX:*:*) if [ -x /usr/bin/oslevel ] ; then IBM_REV=`/usr/bin/oslevel` else IBM_REV=${UNAME_VERSION}.${UNAME_RELEASE} fi echo ${UNAME_MACHINE}-ibm-aix${IBM_REV} exit ;; *:AIX:2:3) if grep bos325 /usr/include/stdio.h >/dev/null 2>&1; then eval $set_cc_for_build sed 's/^ //' << EOF >$dummy.c #include main() { if (!__power_pc()) exit(1); puts("powerpc-ibm-aix3.2.5"); exit(0); } EOF if $CC_FOR_BUILD -o $dummy $dummy.c && SYSTEM_NAME=`$dummy` then echo "$SYSTEM_NAME" else echo rs6000-ibm-aix3.2.5 fi elif grep bos324 /usr/include/stdio.h >/dev/null 2>&1; then echo rs6000-ibm-aix3.2.4 else echo rs6000-ibm-aix3.2 fi exit ;; *:AIX:*:[45]) IBM_CPU_ID=`/usr/sbin/lsdev -C -c processor -S available | sed 1q | awk '{ print $1 }'` if /usr/sbin/lsattr -El ${IBM_CPU_ID} | grep ' POWER' >/dev/null 2>&1; then IBM_ARCH=rs6000 else IBM_ARCH=powerpc fi if [ -x /usr/bin/oslevel ] ; then IBM_REV=`/usr/bin/oslevel` else IBM_REV=${UNAME_VERSION}.${UNAME_RELEASE} fi echo ${IBM_ARCH}-ibm-aix${IBM_REV} exit ;; *:AIX:*:*) echo rs6000-ibm-aix exit ;; ibmrt:4.4BSD:*|romp-ibm:BSD:*) echo romp-ibm-bsd4.4 exit ;; ibmrt:*BSD:*|romp-ibm:BSD:*) # covers RT/PC BSD and echo romp-ibm-bsd${UNAME_RELEASE} # 4.3 with uname added to exit ;; # report: romp-ibm BSD 4.3 *:BOSX:*:*) echo rs6000-bull-bosx exit ;; DPX/2?00:B.O.S.:*:*) echo m68k-bull-sysv3 exit ;; 9000/[34]??:4.3bsd:1.*:*) echo m68k-hp-bsd exit ;; hp300:4.4BSD:*:* | 9000/[34]??:4.3bsd:2.*:*) echo m68k-hp-bsd4.4 exit ;; 9000/[34678]??:HP-UX:*:*) HPUX_REV=`echo ${UNAME_RELEASE}|sed -e 's/[^.]*.[0B]*//'` case "${UNAME_MACHINE}" in 9000/31? ) HP_ARCH=m68000 ;; 9000/[34]?? ) HP_ARCH=m68k ;; 9000/[678][0-9][0-9]) if [ -x /usr/bin/getconf ]; then sc_cpu_version=`/usr/bin/getconf SC_CPU_VERSION 2>/dev/null` sc_kernel_bits=`/usr/bin/getconf SC_KERNEL_BITS 2>/dev/null` case "${sc_cpu_version}" in 523) HP_ARCH="hppa1.0" ;; # CPU_PA_RISC1_0 528) HP_ARCH="hppa1.1" ;; # CPU_PA_RISC1_1 532) # CPU_PA_RISC2_0 case "${sc_kernel_bits}" in 32) HP_ARCH="hppa2.0n" ;; 64) HP_ARCH="hppa2.0w" ;; '') HP_ARCH="hppa2.0" ;; # HP-UX 10.20 esac ;; esac fi if [ "${HP_ARCH}" = "" ]; then eval $set_cc_for_build sed 's/^ //' << EOF >$dummy.c #define _HPUX_SOURCE #include #include int main () { #if defined(_SC_KERNEL_BITS) long bits = sysconf(_SC_KERNEL_BITS); #endif long cpu = sysconf (_SC_CPU_VERSION); switch (cpu) { case CPU_PA_RISC1_0: puts ("hppa1.0"); break; case CPU_PA_RISC1_1: puts ("hppa1.1"); break; case CPU_PA_RISC2_0: #if defined(_SC_KERNEL_BITS) switch (bits) { case 64: puts ("hppa2.0w"); break; case 32: puts ("hppa2.0n"); break; default: puts ("hppa2.0"); break; } break; #else /* !defined(_SC_KERNEL_BITS) */ puts ("hppa2.0"); break; #endif default: puts ("hppa1.0"); break; } exit (0); } EOF (CCOPTS= $CC_FOR_BUILD -o $dummy $dummy.c 2>/dev/null) && HP_ARCH=`$dummy` test -z "$HP_ARCH" && HP_ARCH=hppa fi ;; esac if [ ${HP_ARCH} = "hppa2.0w" ] then eval $set_cc_for_build # hppa2.0w-hp-hpux* has a 64-bit kernel and a compiler generating # 32-bit code. hppa64-hp-hpux* has the same kernel and a compiler # generating 64-bit code. GNU and HP use different nomenclature: # # $ CC_FOR_BUILD=cc ./config.guess # => hppa2.0w-hp-hpux11.23 # $ CC_FOR_BUILD="cc +DA2.0w" ./config.guess # => hppa64-hp-hpux11.23 if echo __LP64__ | (CCOPTS= $CC_FOR_BUILD -E - 2>/dev/null) | grep __LP64__ >/dev/null then HP_ARCH="hppa2.0w" else HP_ARCH="hppa64" fi fi echo ${HP_ARCH}-hp-hpux${HPUX_REV} exit ;; ia64:HP-UX:*:*) HPUX_REV=`echo ${UNAME_RELEASE}|sed -e 's/[^.]*.[0B]*//'` echo ia64-hp-hpux${HPUX_REV} exit ;; 3050*:HI-UX:*:*) eval $set_cc_for_build sed 's/^ //' << EOF >$dummy.c #include int main () { long cpu = sysconf (_SC_CPU_VERSION); /* The order matters, because CPU_IS_HP_MC68K erroneously returns true for CPU_PA_RISC1_0. CPU_IS_PA_RISC returns correct results, however. */ if (CPU_IS_PA_RISC (cpu)) { switch (cpu) { case CPU_PA_RISC1_0: puts ("hppa1.0-hitachi-hiuxwe2"); break; case CPU_PA_RISC1_1: puts ("hppa1.1-hitachi-hiuxwe2"); break; case CPU_PA_RISC2_0: puts ("hppa2.0-hitachi-hiuxwe2"); break; default: puts ("hppa-hitachi-hiuxwe2"); break; } } else if (CPU_IS_HP_MC68K (cpu)) puts ("m68k-hitachi-hiuxwe2"); else puts ("unknown-hitachi-hiuxwe2"); exit (0); } EOF $CC_FOR_BUILD -o $dummy $dummy.c && SYSTEM_NAME=`$dummy` && { echo "$SYSTEM_NAME"; exit; } echo unknown-hitachi-hiuxwe2 exit ;; 9000/7??:4.3bsd:*:* | 9000/8?[79]:4.3bsd:*:* ) echo hppa1.1-hp-bsd exit ;; 9000/8??:4.3bsd:*:*) echo hppa1.0-hp-bsd exit ;; *9??*:MPE/iX:*:* | *3000*:MPE/iX:*:*) echo hppa1.0-hp-mpeix exit ;; hp7??:OSF1:*:* | hp8?[79]:OSF1:*:* ) echo hppa1.1-hp-osf exit ;; hp8??:OSF1:*:*) echo hppa1.0-hp-osf exit ;; i*86:OSF1:*:*) if [ -x /usr/sbin/sysversion ] ; then echo ${UNAME_MACHINE}-unknown-osf1mk else echo ${UNAME_MACHINE}-unknown-osf1 fi exit ;; parisc*:Lites*:*:*) echo hppa1.1-hp-lites exit ;; C1*:ConvexOS:*:* | convex:ConvexOS:C1*:*) echo c1-convex-bsd exit ;; C2*:ConvexOS:*:* | convex:ConvexOS:C2*:*) if getsysinfo -f scalar_acc then echo c32-convex-bsd else echo c2-convex-bsd fi exit ;; C34*:ConvexOS:*:* | convex:ConvexOS:C34*:*) echo c34-convex-bsd exit ;; C38*:ConvexOS:*:* | convex:ConvexOS:C38*:*) echo c38-convex-bsd exit ;; C4*:ConvexOS:*:* | convex:ConvexOS:C4*:*) echo c4-convex-bsd exit ;; CRAY*Y-MP:*:*:*) echo ymp-cray-unicos${UNAME_RELEASE} | sed -e 's/\.[^.]*$/.X/' exit ;; CRAY*[A-Z]90:*:*:*) echo ${UNAME_MACHINE}-cray-unicos${UNAME_RELEASE} \ | sed -e 's/CRAY.*\([A-Z]90\)/\1/' \ -e y/ABCDEFGHIJKLMNOPQRSTUVWXYZ/abcdefghijklmnopqrstuvwxyz/ \ -e 's/\.[^.]*$/.X/' exit ;; CRAY*TS:*:*:*) echo t90-cray-unicos${UNAME_RELEASE} | sed -e 's/\.[^.]*$/.X/' exit ;; CRAY*T3E:*:*:*) echo alphaev5-cray-unicosmk${UNAME_RELEASE} | sed -e 's/\.[^.]*$/.X/' exit ;; CRAY*SV1:*:*:*) echo sv1-cray-unicos${UNAME_RELEASE} | sed -e 's/\.[^.]*$/.X/' exit ;; *:UNICOS/mp:*:*) echo craynv-cray-unicosmp${UNAME_RELEASE} | sed -e 's/\.[^.]*$/.X/' exit ;; F30[01]:UNIX_System_V:*:* | F700:UNIX_System_V:*:*) FUJITSU_PROC=`uname -m | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz'` FUJITSU_SYS=`uname -p | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz' | sed -e 's/\///'` FUJITSU_REL=`echo ${UNAME_RELEASE} | sed -e 's/ /_/'` echo "${FUJITSU_PROC}-fujitsu-${FUJITSU_SYS}${FUJITSU_REL}" exit ;; 5000:UNIX_System_V:4.*:*) FUJITSU_SYS=`uname -p | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz' | sed -e 's/\///'` FUJITSU_REL=`echo ${UNAME_RELEASE} | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz' | sed -e 's/ /_/'` echo "sparc-fujitsu-${FUJITSU_SYS}${FUJITSU_REL}" exit ;; i*86:BSD/386:*:* | i*86:BSD/OS:*:* | *:Ascend\ Embedded/OS:*:*) echo ${UNAME_MACHINE}-pc-bsdi${UNAME_RELEASE} exit ;; sparc*:BSD/OS:*:*) echo sparc-unknown-bsdi${UNAME_RELEASE} exit ;; *:BSD/OS:*:*) echo ${UNAME_MACHINE}-unknown-bsdi${UNAME_RELEASE} exit ;; *:FreeBSD:*:*) case ${UNAME_MACHINE} in pc98) echo i386-unknown-freebsd`echo ${UNAME_RELEASE}|sed -e 's/[-(].*//'` ;; amd64) echo x86_64-unknown-freebsd`echo ${UNAME_RELEASE}|sed -e 's/[-(].*//'` ;; *) echo ${UNAME_MACHINE}-unknown-freebsd`echo ${UNAME_RELEASE}|sed -e 's/[-(].*//'` ;; esac exit ;; i*:CYGWIN*:*) echo ${UNAME_MACHINE}-pc-cygwin exit ;; *:MINGW*:*) echo ${UNAME_MACHINE}-pc-mingw32 exit ;; i*:windows32*:*) # uname -m includes "-pc" on this system. echo ${UNAME_MACHINE}-mingw32 exit ;; i*:PW*:*) echo ${UNAME_MACHINE}-pc-pw32 exit ;; *:Interix*:[3456]*) case ${UNAME_MACHINE} in x86) echo i586-pc-interix${UNAME_RELEASE} exit ;; EM64T | authenticamd) echo x86_64-unknown-interix${UNAME_RELEASE} exit ;; esac ;; [345]86:Windows_95:* | [345]86:Windows_98:* | [345]86:Windows_NT:*) echo i${UNAME_MACHINE}-pc-mks exit ;; i*:Windows_NT*:* | Pentium*:Windows_NT*:*) # How do we know it's Interix rather than the generic POSIX subsystem? # It also conflicts with pre-2.0 versions of AT&T UWIN. Should we # UNAME_MACHINE based on the output of uname instead of i386? echo i586-pc-interix exit ;; i*:UWIN*:*) echo ${UNAME_MACHINE}-pc-uwin exit ;; amd64:CYGWIN*:*:* | x86_64:CYGWIN*:*:*) echo x86_64-unknown-cygwin exit ;; p*:CYGWIN*:*) echo powerpcle-unknown-cygwin exit ;; prep*:SunOS:5.*:*) echo powerpcle-unknown-solaris2`echo ${UNAME_RELEASE}|sed -e 's/[^.]*//'` exit ;; *:GNU:*:*) # the GNU system echo `echo ${UNAME_MACHINE}|sed -e 's,[-/].*$,,'`-unknown-gnu`echo ${UNAME_RELEASE}|sed -e 's,/.*$,,'` exit ;; *:GNU/*:*:*) # other systems with GNU libc and userland echo ${UNAME_MACHINE}-unknown-`echo ${UNAME_SYSTEM} | sed 's,^[^/]*/,,' | tr '[A-Z]' '[a-z]'``echo ${UNAME_RELEASE}|sed -e 's/[-(].*//'`-gnu exit ;; i*86:Minix:*:*) echo ${UNAME_MACHINE}-pc-minix exit ;; arm*:Linux:*:*) echo ${UNAME_MACHINE}-unknown-linux-gnu exit ;; avr32*:Linux:*:*) echo ${UNAME_MACHINE}-unknown-linux-gnu exit ;; cris:Linux:*:*) echo cris-axis-linux-gnu exit ;; crisv32:Linux:*:*) echo crisv32-axis-linux-gnu exit ;; frv:Linux:*:*) echo frv-unknown-linux-gnu exit ;; ia64:Linux:*:*) echo ${UNAME_MACHINE}-unknown-linux-gnu exit ;; m32r*:Linux:*:*) echo ${UNAME_MACHINE}-unknown-linux-gnu exit ;; m68*:Linux:*:*) echo ${UNAME_MACHINE}-unknown-linux-gnu exit ;; mips:Linux:*:*) eval $set_cc_for_build sed 's/^ //' << EOF >$dummy.c #undef CPU #undef mips #undef mipsel #if defined(__MIPSEL__) || defined(__MIPSEL) || defined(_MIPSEL) || defined(MIPSEL) CPU=mipsel #else #if defined(__MIPSEB__) || defined(__MIPSEB) || defined(_MIPSEB) || defined(MIPSEB) CPU=mips #else CPU= #endif #endif EOF eval "`$CC_FOR_BUILD -E $dummy.c 2>/dev/null | sed -n ' /^CPU/{ s: ::g p }'`" test x"${CPU}" != x && { echo "${CPU}-unknown-linux-gnu"; exit; } ;; mips64:Linux:*:*) eval $set_cc_for_build sed 's/^ //' << EOF >$dummy.c #undef CPU #undef mips64 #undef mips64el #if defined(__MIPSEL__) || defined(__MIPSEL) || defined(_MIPSEL) || defined(MIPSEL) CPU=mips64el #else #if defined(__MIPSEB__) || defined(__MIPSEB) || defined(_MIPSEB) || defined(MIPSEB) CPU=mips64 #else CPU= #endif #endif EOF eval "`$CC_FOR_BUILD -E $dummy.c 2>/dev/null | sed -n ' /^CPU/{ s: ::g p }'`" test x"${CPU}" != x && { echo "${CPU}-unknown-linux-gnu"; exit; } ;; or32:Linux:*:*) echo or32-unknown-linux-gnu exit ;; ppc:Linux:*:*) echo powerpc-unknown-linux-gnu exit ;; ppc64:Linux:*:*) echo powerpc64-unknown-linux-gnu exit ;; alpha:Linux:*:*) case `sed -n '/^cpu model/s/^.*: \(.*\)/\1/p' < /proc/cpuinfo` in EV5) UNAME_MACHINE=alphaev5 ;; EV56) UNAME_MACHINE=alphaev56 ;; PCA56) UNAME_MACHINE=alphapca56 ;; PCA57) UNAME_MACHINE=alphapca56 ;; EV6) UNAME_MACHINE=alphaev6 ;; EV67) UNAME_MACHINE=alphaev67 ;; EV68*) UNAME_MACHINE=alphaev68 ;; esac objdump --private-headers /bin/sh | grep ld.so.1 >/dev/null if test "$?" = 0 ; then LIBC="libc1" ; else LIBC="" ; fi echo ${UNAME_MACHINE}-unknown-linux-gnu${LIBC} exit ;; parisc:Linux:*:* | hppa:Linux:*:*) # Look for CPU level case `grep '^cpu[^a-z]*:' /proc/cpuinfo 2>/dev/null | cut -d' ' -f2` in PA7*) echo hppa1.1-unknown-linux-gnu ;; PA8*) echo hppa2.0-unknown-linux-gnu ;; *) echo hppa-unknown-linux-gnu ;; esac exit ;; parisc64:Linux:*:* | hppa64:Linux:*:*) echo hppa64-unknown-linux-gnu exit ;; s390:Linux:*:* | s390x:Linux:*:*) echo ${UNAME_MACHINE}-ibm-linux exit ;; sh64*:Linux:*:*) echo ${UNAME_MACHINE}-unknown-linux-gnu exit ;; sh*:Linux:*:*) echo ${UNAME_MACHINE}-unknown-linux-gnu exit ;; sparc:Linux:*:* | sparc64:Linux:*:*) echo ${UNAME_MACHINE}-unknown-linux-gnu exit ;; vax:Linux:*:*) echo ${UNAME_MACHINE}-dec-linux-gnu exit ;; x86_64:Linux:*:*) echo x86_64-unknown-linux-gnu exit ;; xtensa:Linux:*:*) echo xtensa-unknown-linux-gnu exit ;; i*86:Linux:*:*) # The BFD linker knows what the default object file format is, so # first see if it will tell us. cd to the root directory to prevent # problems with other programs or directories called `ld' in the path. # Set LC_ALL=C to ensure ld outputs messages in English. ld_supported_targets=`cd /; LC_ALL=C ld --help 2>&1 \ | sed -ne '/supported targets:/!d s/[ ][ ]*/ /g s/.*supported targets: *// s/ .*// p'` case "$ld_supported_targets" in elf32-i386) TENTATIVE="${UNAME_MACHINE}-pc-linux-gnu" ;; a.out-i386-linux) echo "${UNAME_MACHINE}-pc-linux-gnuaout" exit ;; coff-i386) echo "${UNAME_MACHINE}-pc-linux-gnucoff" exit ;; "") # Either a pre-BFD a.out linker (linux-gnuoldld) or # one that does not give us useful --help. echo "${UNAME_MACHINE}-pc-linux-gnuoldld" exit ;; esac # Determine whether the default compiler is a.out or elf eval $set_cc_for_build sed 's/^ //' << EOF >$dummy.c #include #ifdef __ELF__ # ifdef __GLIBC__ # if __GLIBC__ >= 2 LIBC=gnu # else LIBC=gnulibc1 # endif # else LIBC=gnulibc1 # endif #else #if defined(__INTEL_COMPILER) || defined(__PGI) || defined(__SUNPRO_C) || defined(__SUNPRO_CC) LIBC=gnu #else LIBC=gnuaout #endif #endif #ifdef __dietlibc__ LIBC=dietlibc #endif EOF eval "`$CC_FOR_BUILD -E $dummy.c 2>/dev/null | sed -n ' /^LIBC/{ s: ::g p }'`" test x"${LIBC}" != x && { echo "${UNAME_MACHINE}-pc-linux-${LIBC}" exit } test x"${TENTATIVE}" != x && { echo "${TENTATIVE}"; exit; } ;; i*86:DYNIX/ptx:4*:*) # ptx 4.0 does uname -s correctly, with DYNIX/ptx in there. # earlier versions are messed up and put the nodename in both # sysname and nodename. echo i386-sequent-sysv4 exit ;; i*86:UNIX_SV:4.2MP:2.*) # Unixware is an offshoot of SVR4, but it has its own version # number series starting with 2... # I am not positive that other SVR4 systems won't match this, # I just have to hope. -- rms. # Use sysv4.2uw... so that sysv4* matches it. echo ${UNAME_MACHINE}-pc-sysv4.2uw${UNAME_VERSION} exit ;; i*86:OS/2:*:*) # If we were able to find `uname', then EMX Unix compatibility # is probably installed. echo ${UNAME_MACHINE}-pc-os2-emx exit ;; i*86:XTS-300:*:STOP) echo ${UNAME_MACHINE}-unknown-stop exit ;; i*86:atheos:*:*) echo ${UNAME_MACHINE}-unknown-atheos exit ;; i*86:syllable:*:*) echo ${UNAME_MACHINE}-pc-syllable exit ;; i*86:LynxOS:2.*:* | i*86:LynxOS:3.[01]*:* | i*86:LynxOS:4.0*:*) echo i386-unknown-lynxos${UNAME_RELEASE} exit ;; i*86:*DOS:*:*) echo ${UNAME_MACHINE}-pc-msdosdjgpp exit ;; i*86:*:4.*:* | i*86:SYSTEM_V:4.*:*) UNAME_REL=`echo ${UNAME_RELEASE} | sed 's/\/MP$//'` if grep Novell /usr/include/link.h >/dev/null 2>/dev/null; then echo ${UNAME_MACHINE}-univel-sysv${UNAME_REL} else echo ${UNAME_MACHINE}-pc-sysv${UNAME_REL} fi exit ;; i*86:*:5:[678]*) # UnixWare 7.x, OpenUNIX and OpenServer 6. case `/bin/uname -X | grep "^Machine"` in *486*) UNAME_MACHINE=i486 ;; *Pentium) UNAME_MACHINE=i586 ;; *Pent*|*Celeron) UNAME_MACHINE=i686 ;; esac echo ${UNAME_MACHINE}-unknown-sysv${UNAME_RELEASE}${UNAME_SYSTEM}${UNAME_VERSION} exit ;; i*86:*:3.2:*) if test -f /usr/options/cb.name; then UNAME_REL=`sed -n 's/.*Version //p' /dev/null >/dev/null ; then UNAME_REL=`(/bin/uname -X|grep Release|sed -e 's/.*= //')` (/bin/uname -X|grep i80486 >/dev/null) && UNAME_MACHINE=i486 (/bin/uname -X|grep '^Machine.*Pentium' >/dev/null) \ && UNAME_MACHINE=i586 (/bin/uname -X|grep '^Machine.*Pent *II' >/dev/null) \ && UNAME_MACHINE=i686 (/bin/uname -X|grep '^Machine.*Pentium Pro' >/dev/null) \ && UNAME_MACHINE=i686 echo ${UNAME_MACHINE}-pc-sco$UNAME_REL else echo ${UNAME_MACHINE}-pc-sysv32 fi exit ;; pc:*:*:*) # Left here for compatibility: # uname -m prints for DJGPP always 'pc', but it prints nothing about # the processor, so we play safe by assuming i386. echo i386-pc-msdosdjgpp exit ;; Intel:Mach:3*:*) echo i386-pc-mach3 exit ;; paragon:*:*:*) echo i860-intel-osf1 exit ;; i860:*:4.*:*) # i860-SVR4 if grep Stardent /usr/include/sys/uadmin.h >/dev/null 2>&1 ; then echo i860-stardent-sysv${UNAME_RELEASE} # Stardent Vistra i860-SVR4 else # Add other i860-SVR4 vendors below as they are discovered. echo i860-unknown-sysv${UNAME_RELEASE} # Unknown i860-SVR4 fi exit ;; mini*:CTIX:SYS*5:*) # "miniframe" echo m68010-convergent-sysv exit ;; mc68k:UNIX:SYSTEM5:3.51m) echo m68k-convergent-sysv exit ;; M680?0:D-NIX:5.3:*) echo m68k-diab-dnix exit ;; M68*:*:R3V[5678]*:*) test -r /sysV68 && { echo 'm68k-motorola-sysv'; exit; } ;; 3[345]??:*:4.0:3.0 | 3[34]??A:*:4.0:3.0 | 3[34]??,*:*:4.0:3.0 | 3[34]??/*:*:4.0:3.0 | 4400:*:4.0:3.0 | 4850:*:4.0:3.0 | SKA40:*:4.0:3.0 | SDS2:*:4.0:3.0 | SHG2:*:4.0:3.0 | S7501*:*:4.0:3.0) OS_REL='' test -r /etc/.relid \ && OS_REL=.`sed -n 's/[^ ]* [^ ]* \([0-9][0-9]\).*/\1/p' < /etc/.relid` /bin/uname -p 2>/dev/null | grep 86 >/dev/null \ && { echo i486-ncr-sysv4.3${OS_REL}; exit; } /bin/uname -p 2>/dev/null | /bin/grep entium >/dev/null \ && { echo i586-ncr-sysv4.3${OS_REL}; exit; } ;; 3[34]??:*:4.0:* | 3[34]??,*:*:4.0:*) /bin/uname -p 2>/dev/null | grep 86 >/dev/null \ && { echo i486-ncr-sysv4; exit; } ;; m68*:LynxOS:2.*:* | m68*:LynxOS:3.0*:*) echo m68k-unknown-lynxos${UNAME_RELEASE} exit ;; mc68030:UNIX_System_V:4.*:*) echo m68k-atari-sysv4 exit ;; TSUNAMI:LynxOS:2.*:*) echo sparc-unknown-lynxos${UNAME_RELEASE} exit ;; rs6000:LynxOS:2.*:*) echo rs6000-unknown-lynxos${UNAME_RELEASE} exit ;; PowerPC:LynxOS:2.*:* | PowerPC:LynxOS:3.[01]*:* | PowerPC:LynxOS:4.0*:*) echo powerpc-unknown-lynxos${UNAME_RELEASE} exit ;; SM[BE]S:UNIX_SV:*:*) echo mips-dde-sysv${UNAME_RELEASE} exit ;; RM*:ReliantUNIX-*:*:*) echo mips-sni-sysv4 exit ;; RM*:SINIX-*:*:*) echo mips-sni-sysv4 exit ;; *:SINIX-*:*:*) if uname -p 2>/dev/null >/dev/null ; then UNAME_MACHINE=`(uname -p) 2>/dev/null` echo ${UNAME_MACHINE}-sni-sysv4 else echo ns32k-sni-sysv fi exit ;; PENTIUM:*:4.0*:*) # Unisys `ClearPath HMP IX 4000' SVR4/MP effort # says echo i586-unisys-sysv4 exit ;; *:UNIX_System_V:4*:FTX*) # From Gerald Hewes . # How about differentiating between stratus architectures? -djm echo hppa1.1-stratus-sysv4 exit ;; *:*:*:FTX*) # From seanf@swdc.stratus.com. echo i860-stratus-sysv4 exit ;; i*86:VOS:*:*) # From Paul.Green@stratus.com. echo ${UNAME_MACHINE}-stratus-vos exit ;; *:VOS:*:*) # From Paul.Green@stratus.com. echo hppa1.1-stratus-vos exit ;; mc68*:A/UX:*:*) echo m68k-apple-aux${UNAME_RELEASE} exit ;; news*:NEWS-OS:6*:*) echo mips-sony-newsos6 exit ;; R[34]000:*System_V*:*:* | R4000:UNIX_SYSV:*:* | R*000:UNIX_SV:*:*) if [ -d /usr/nec ]; then echo mips-nec-sysv${UNAME_RELEASE} else echo mips-unknown-sysv${UNAME_RELEASE} fi exit ;; BeBox:BeOS:*:*) # BeOS running on hardware made by Be, PPC only. echo powerpc-be-beos exit ;; BeMac:BeOS:*:*) # BeOS running on Mac or Mac clone, PPC only. echo powerpc-apple-beos exit ;; BePC:BeOS:*:*) # BeOS running on Intel PC compatible. echo i586-pc-beos exit ;; SX-4:SUPER-UX:*:*) echo sx4-nec-superux${UNAME_RELEASE} exit ;; SX-5:SUPER-UX:*:*) echo sx5-nec-superux${UNAME_RELEASE} exit ;; SX-6:SUPER-UX:*:*) echo sx6-nec-superux${UNAME_RELEASE} exit ;; SX-7:SUPER-UX:*:*) echo sx7-nec-superux${UNAME_RELEASE} exit ;; SX-8:SUPER-UX:*:*) echo sx8-nec-superux${UNAME_RELEASE} exit ;; SX-8R:SUPER-UX:*:*) echo sx8r-nec-superux${UNAME_RELEASE} exit ;; Power*:Rhapsody:*:*) echo powerpc-apple-rhapsody${UNAME_RELEASE} exit ;; *:Rhapsody:*:*) echo ${UNAME_MACHINE}-apple-rhapsody${UNAME_RELEASE} exit ;; *:Darwin:*:*) UNAME_PROCESSOR=`uname -p` || UNAME_PROCESSOR=unknown case $UNAME_PROCESSOR in unknown) UNAME_PROCESSOR=powerpc ;; esac echo ${UNAME_PROCESSOR}-apple-darwin${UNAME_RELEASE} exit ;; *:procnto*:*:* | *:QNX:[0123456789]*:*) UNAME_PROCESSOR=`uname -p` if test "$UNAME_PROCESSOR" = "x86"; then UNAME_PROCESSOR=i386 UNAME_MACHINE=pc fi echo ${UNAME_PROCESSOR}-${UNAME_MACHINE}-nto-qnx${UNAME_RELEASE} exit ;; *:QNX:*:4*) echo i386-pc-qnx exit ;; NSE-?:NONSTOP_KERNEL:*:*) echo nse-tandem-nsk${UNAME_RELEASE} exit ;; NSR-?:NONSTOP_KERNEL:*:*) echo nsr-tandem-nsk${UNAME_RELEASE} exit ;; *:NonStop-UX:*:*) echo mips-compaq-nonstopux exit ;; BS2000:POSIX*:*:*) echo bs2000-siemens-sysv exit ;; DS/*:UNIX_System_V:*:*) echo ${UNAME_MACHINE}-${UNAME_SYSTEM}-${UNAME_RELEASE} exit ;; *:Plan9:*:*) # "uname -m" is not consistent, so use $cputype instead. 386 # is converted to i386 for consistency with other x86 # operating systems. if test "$cputype" = "386"; then UNAME_MACHINE=i386 else UNAME_MACHINE="$cputype" fi echo ${UNAME_MACHINE}-unknown-plan9 exit ;; *:TOPS-10:*:*) echo pdp10-unknown-tops10 exit ;; *:TENEX:*:*) echo pdp10-unknown-tenex exit ;; KS10:TOPS-20:*:* | KL10:TOPS-20:*:* | TYPE4:TOPS-20:*:*) echo pdp10-dec-tops20 exit ;; XKL-1:TOPS-20:*:* | TYPE5:TOPS-20:*:*) echo pdp10-xkl-tops20 exit ;; *:TOPS-20:*:*) echo pdp10-unknown-tops20 exit ;; *:ITS:*:*) echo pdp10-unknown-its exit ;; SEI:*:*:SEIUX) echo mips-sei-seiux${UNAME_RELEASE} exit ;; *:DragonFly:*:*) echo ${UNAME_MACHINE}-unknown-dragonfly`echo ${UNAME_RELEASE}|sed -e 's/[-(].*//'` exit ;; *:*VMS:*:*) UNAME_MACHINE=`(uname -p) 2>/dev/null` case "${UNAME_MACHINE}" in A*) echo alpha-dec-vms ; exit ;; I*) echo ia64-dec-vms ; exit ;; V*) echo vax-dec-vms ; exit ;; esac ;; *:XENIX:*:SysV) echo i386-pc-xenix exit ;; i*86:skyos:*:*) echo ${UNAME_MACHINE}-pc-skyos`echo ${UNAME_RELEASE}` | sed -e 's/ .*$//' exit ;; i*86:rdos:*:*) echo ${UNAME_MACHINE}-pc-rdos exit ;; esac #echo '(No uname command or uname output not recognized.)' 1>&2 #echo "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" 1>&2 eval $set_cc_for_build cat >$dummy.c < # include #endif main () { #if defined (sony) #if defined (MIPSEB) /* BFD wants "bsd" instead of "newsos". Perhaps BFD should be changed, I don't know.... */ printf ("mips-sony-bsd\n"); exit (0); #else #include printf ("m68k-sony-newsos%s\n", #ifdef NEWSOS4 "4" #else "" #endif ); exit (0); #endif #endif #if defined (__arm) && defined (__acorn) && defined (__unix) printf ("arm-acorn-riscix\n"); exit (0); #endif #if defined (hp300) && !defined (hpux) printf ("m68k-hp-bsd\n"); exit (0); #endif #if defined (NeXT) #if !defined (__ARCHITECTURE__) #define __ARCHITECTURE__ "m68k" #endif int version; version=`(hostinfo | sed -n 's/.*NeXT Mach \([0-9]*\).*/\1/p') 2>/dev/null`; if (version < 4) printf ("%s-next-nextstep%d\n", __ARCHITECTURE__, version); else printf ("%s-next-openstep%d\n", __ARCHITECTURE__, version); exit (0); #endif #if defined (MULTIMAX) || defined (n16) #if defined (UMAXV) printf ("ns32k-encore-sysv\n"); exit (0); #else #if defined (CMU) printf ("ns32k-encore-mach\n"); exit (0); #else printf ("ns32k-encore-bsd\n"); exit (0); #endif #endif #endif #if defined (__386BSD__) printf ("i386-pc-bsd\n"); exit (0); #endif #if defined (sequent) #if defined (i386) printf ("i386-sequent-dynix\n"); exit (0); #endif #if defined (ns32000) printf ("ns32k-sequent-dynix\n"); exit (0); #endif #endif #if defined (_SEQUENT_) struct utsname un; uname(&un); if (strncmp(un.version, "V2", 2) == 0) { printf ("i386-sequent-ptx2\n"); exit (0); } if (strncmp(un.version, "V1", 2) == 0) { /* XXX is V1 correct? */ printf ("i386-sequent-ptx1\n"); exit (0); } printf ("i386-sequent-ptx\n"); exit (0); #endif #if defined (vax) # if !defined (ultrix) # include # if defined (BSD) # if BSD == 43 printf ("vax-dec-bsd4.3\n"); exit (0); # else # if BSD == 199006 printf ("vax-dec-bsd4.3reno\n"); exit (0); # else printf ("vax-dec-bsd\n"); exit (0); # endif # endif # else printf ("vax-dec-bsd\n"); exit (0); # endif # else printf ("vax-dec-ultrix\n"); exit (0); # endif #endif #if defined (alliant) && defined (i860) printf ("i860-alliant-bsd\n"); exit (0); #endif exit (1); } EOF $CC_FOR_BUILD -o $dummy $dummy.c 2>/dev/null && SYSTEM_NAME=`$dummy` && { echo "$SYSTEM_NAME"; exit; } # Apollos put the system type in the environment. test -d /usr/apollo && { echo ${ISP}-apollo-${SYSTYPE}; exit; } # Convex versions that predate uname can use getsysinfo(1) if [ -x /usr/convex/getsysinfo ] then case `getsysinfo -f cpu_type` in c1*) echo c1-convex-bsd exit ;; c2*) if getsysinfo -f scalar_acc then echo c32-convex-bsd else echo c2-convex-bsd fi exit ;; c34*) echo c34-convex-bsd exit ;; c38*) echo c38-convex-bsd exit ;; c4*) echo c4-convex-bsd exit ;; esac fi cat >&2 < in order to provide the needed information to handle your system. config.guess timestamp = $timestamp uname -m = `(uname -m) 2>/dev/null || echo unknown` uname -r = `(uname -r) 2>/dev/null || echo unknown` uname -s = `(uname -s) 2>/dev/null || echo unknown` uname -v = `(uname -v) 2>/dev/null || echo unknown` /usr/bin/uname -p = `(/usr/bin/uname -p) 2>/dev/null` /bin/uname -X = `(/bin/uname -X) 2>/dev/null` hostinfo = `(hostinfo) 2>/dev/null` /bin/universe = `(/bin/universe) 2>/dev/null` /usr/bin/arch -k = `(/usr/bin/arch -k) 2>/dev/null` /bin/arch = `(/bin/arch) 2>/dev/null` /usr/bin/oslevel = `(/usr/bin/oslevel) 2>/dev/null` /usr/convex/getsysinfo = `(/usr/convex/getsysinfo) 2>/dev/null` UNAME_MACHINE = ${UNAME_MACHINE} UNAME_RELEASE = ${UNAME_RELEASE} UNAME_SYSTEM = ${UNAME_SYSTEM} UNAME_VERSION = ${UNAME_VERSION} EOF exit 1 # Local variables: # eval: (add-hook 'write-file-hooks 'time-stamp) # time-stamp-start: "timestamp='" # time-stamp-format: "%:y-%02m-%02d" # time-stamp-end: "'" # End: ./CBFlib-0.9.2.2/libtool/config.sub0000755000076500007650000007772611603702120015244 0ustar yayayaya#! /bin/sh # Configuration validation subroutine script. # Copyright (C) 1992, 1993, 1994, 1995, 1996, 1997, 1998, 1999, # 2000, 2001, 2002, 2003, 2004, 2005, 2006 Free Software Foundation, # Inc. timestamp='2007-04-29' # This file is (in principle) common to ALL GNU software. # The presence of a machine in this file suggests that SOME GNU software # can handle that machine. It does not imply ALL GNU software can. # # This file is free software; you can redistribute it and/or modify # it under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2 of the License, or # (at your option) any later version. # # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # GNU General Public License for more details. # # You should have received a copy of the GNU General Public License # along with this program; if not, write to the Free Software # Foundation, Inc., 51 Franklin Street - Fifth Floor, Boston, MA # 02110-1301, USA. # # As a special exception to the GNU General Public License, if you # distribute this file as part of a program that contains a # configuration script generated by Autoconf, you may include it under # the same distribution terms that you use for the rest of that program. # Please send patches to . Submit a context # diff and a properly formatted ChangeLog entry. # # Configuration subroutine to validate and canonicalize a configuration type. # Supply the specified configuration type as an argument. # If it is invalid, we print an error message on stderr and exit with code 1. # Otherwise, we print the canonical config type on stdout and succeed. # This file is supposed to be the same for all GNU packages # and recognize all the CPU types, system types and aliases # that are meaningful with *any* GNU software. # Each package is responsible for reporting which valid configurations # it does not support. The user should be able to distinguish # a failure to support a valid configuration from a meaningless # configuration. # The goal of this file is to map all the various variations of a given # machine specification into a single specification in the form: # CPU_TYPE-MANUFACTURER-OPERATING_SYSTEM # or in some cases, the newer four-part form: # CPU_TYPE-MANUFACTURER-KERNEL-OPERATING_SYSTEM # It is wrong to echo any other type of specification. me=`echo "$0" | sed -e 's,.*/,,'` usage="\ Usage: $0 [OPTION] CPU-MFR-OPSYS $0 [OPTION] ALIAS Canonicalize a configuration name. Operation modes: -h, --help print this help, then exit -t, --time-stamp print date of last modification, then exit -v, --version print version number, then exit Report bugs and patches to ." version="\ GNU config.sub ($timestamp) Copyright (C) 1992, 1993, 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002, 2003, 2004, 2005 Free Software Foundation, Inc. This is free software; see the source for copying conditions. There is NO warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE." help=" Try \`$me --help' for more information." # Parse command line while test $# -gt 0 ; do case $1 in --time-stamp | --time* | -t ) echo "$timestamp" ; exit ;; --version | -v ) echo "$version" ; exit ;; --help | --h* | -h ) echo "$usage"; exit ;; -- ) # Stop option processing shift; break ;; - ) # Use stdin as input. break ;; -* ) echo "$me: invalid option $1$help" exit 1 ;; *local*) # First pass through any local machine types. echo $1 exit ;; * ) break ;; esac done case $# in 0) echo "$me: missing argument$help" >&2 exit 1;; 1) ;; *) echo "$me: too many arguments$help" >&2 exit 1;; esac # Separate what the user gave into CPU-COMPANY and OS or KERNEL-OS (if any). # Here we must recognize all the valid KERNEL-OS combinations. maybe_os=`echo $1 | sed 's/^\(.*\)-\([^-]*-[^-]*\)$/\2/'` case $maybe_os in nto-qnx* | linux-gnu* | linux-dietlibc | linux-newlib* | linux-uclibc* | \ uclinux-uclibc* | uclinux-gnu* | kfreebsd*-gnu* | knetbsd*-gnu* | netbsd*-gnu* | \ storm-chaos* | os2-emx* | rtmk-nova*) os=-$maybe_os basic_machine=`echo $1 | sed 's/^\(.*\)-\([^-]*-[^-]*\)$/\1/'` ;; *) basic_machine=`echo $1 | sed 's/-[^-]*$//'` if [ $basic_machine != $1 ] then os=`echo $1 | sed 's/.*-/-/'` else os=; fi ;; esac ### Let's recognize common machines as not being operating systems so ### that things like config.sub decstation-3100 work. We also ### recognize some manufacturers as not being operating systems, so we ### can provide default operating systems below. case $os in -sun*os*) # Prevent following clause from handling this invalid input. ;; -dec* | -mips* | -sequent* | -encore* | -pc532* | -sgi* | -sony* | \ -att* | -7300* | -3300* | -delta* | -motorola* | -sun[234]* | \ -unicom* | -ibm* | -next | -hp | -isi* | -apollo | -altos* | \ -convergent* | -ncr* | -news | -32* | -3600* | -3100* | -hitachi* |\ -c[123]* | -convex* | -sun | -crds | -omron* | -dg | -ultra | -tti* | \ -harris | -dolphin | -highlevel | -gould | -cbm | -ns | -masscomp | \ -apple | -axis | -knuth | -cray) os= basic_machine=$1 ;; -sim | -cisco | -oki | -wec | -winbond) os= basic_machine=$1 ;; -scout) ;; -wrs) os=-vxworks basic_machine=$1 ;; -chorusos*) os=-chorusos basic_machine=$1 ;; -chorusrdb) os=-chorusrdb basic_machine=$1 ;; -hiux*) os=-hiuxwe2 ;; -sco6) os=-sco5v6 basic_machine=`echo $1 | sed -e 's/86-.*/86-pc/'` ;; -sco5) os=-sco3.2v5 basic_machine=`echo $1 | sed -e 's/86-.*/86-pc/'` ;; -sco4) os=-sco3.2v4 basic_machine=`echo $1 | sed -e 's/86-.*/86-pc/'` ;; -sco3.2.[4-9]*) os=`echo $os | sed -e 's/sco3.2./sco3.2v/'` basic_machine=`echo $1 | sed -e 's/86-.*/86-pc/'` ;; -sco3.2v[4-9]*) # Don't forget version if it is 3.2v4 or newer. basic_machine=`echo $1 | sed -e 's/86-.*/86-pc/'` ;; -sco5v6*) # Don't forget version if it is 3.2v4 or newer. basic_machine=`echo $1 | sed -e 's/86-.*/86-pc/'` ;; -sco*) os=-sco3.2v2 basic_machine=`echo $1 | sed -e 's/86-.*/86-pc/'` ;; -udk*) basic_machine=`echo $1 | sed -e 's/86-.*/86-pc/'` ;; -isc) os=-isc2.2 basic_machine=`echo $1 | sed -e 's/86-.*/86-pc/'` ;; -clix*) basic_machine=clipper-intergraph ;; -isc*) basic_machine=`echo $1 | sed -e 's/86-.*/86-pc/'` ;; -lynx*) os=-lynxos ;; -ptx*) basic_machine=`echo $1 | sed -e 's/86-.*/86-sequent/'` ;; -windowsnt*) os=`echo $os | sed -e 's/windowsnt/winnt/'` ;; -psos*) os=-psos ;; -mint | -mint[0-9]*) basic_machine=m68k-atari os=-mint ;; esac # Decode aliases for certain CPU-COMPANY combinations. case $basic_machine in # Recognize the basic CPU types without company name. # Some are omitted here because they have special meanings below. 1750a | 580 \ | a29k \ | alpha | alphaev[4-8] | alphaev56 | alphaev6[78] | alphapca5[67] \ | alpha64 | alpha64ev[4-8] | alpha64ev56 | alpha64ev6[78] | alpha64pca5[67] \ | am33_2.0 \ | arc | arm | arm[bl]e | arme[lb] | armv[2345] | armv[345][lb] | avr | avr32 \ | bfin \ | c4x | clipper \ | d10v | d30v | dlx | dsp16xx \ | fido | fr30 | frv \ | h8300 | h8500 | hppa | hppa1.[01] | hppa2.0 | hppa2.0[nw] | hppa64 \ | i370 | i860 | i960 | ia64 \ | ip2k | iq2000 \ | m32c | m32r | m32rle | m68000 | m68k | m88k \ | maxq | mb | microblaze | mcore | mep \ | mips | mipsbe | mipseb | mipsel | mipsle \ | mips16 \ | mips64 | mips64el \ | mips64vr | mips64vrel \ | mips64orion | mips64orionel \ | mips64vr4100 | mips64vr4100el \ | mips64vr4300 | mips64vr4300el \ | mips64vr5000 | mips64vr5000el \ | mips64vr5900 | mips64vr5900el \ | mipsisa32 | mipsisa32el \ | mipsisa32r2 | mipsisa32r2el \ | mipsisa64 | mipsisa64el \ | mipsisa64r2 | mipsisa64r2el \ | mipsisa64sb1 | mipsisa64sb1el \ | mipsisa64sr71k | mipsisa64sr71kel \ | mipstx39 | mipstx39el \ | mn10200 | mn10300 \ | mt \ | msp430 \ | nios | nios2 \ | ns16k | ns32k \ | or32 \ | pdp10 | pdp11 | pj | pjl \ | powerpc | powerpc64 | powerpc64le | powerpcle | ppcbe \ | pyramid \ | score \ | sh | sh[1234] | sh[24]a | sh[23]e | sh[34]eb | sheb | shbe | shle | sh[1234]le | sh3ele \ | sh64 | sh64le \ | sparc | sparc64 | sparc64b | sparc64v | sparc86x | sparclet | sparclite \ | sparcv8 | sparcv9 | sparcv9b | sparcv9v \ | spu | strongarm \ | tahoe | thumb | tic4x | tic80 | tron \ | v850 | v850e \ | we32k \ | x86 | xc16x | xscale | xscalee[bl] | xstormy16 | xtensa \ | z8k) basic_machine=$basic_machine-unknown ;; m6811 | m68hc11 | m6812 | m68hc12) # Motorola 68HC11/12. basic_machine=$basic_machine-unknown os=-none ;; m88110 | m680[12346]0 | m683?2 | m68360 | m5200 | v70 | w65 | z8k) ;; ms1) basic_machine=mt-unknown ;; # We use `pc' rather than `unknown' # because (1) that's what they normally are, and # (2) the word "unknown" tends to confuse beginning users. i*86 | x86_64) basic_machine=$basic_machine-pc ;; # Object if more than one company name word. *-*-*) echo Invalid configuration \`$1\': machine \`$basic_machine\' not recognized 1>&2 exit 1 ;; # Recognize the basic CPU types with company name. 580-* \ | a29k-* \ | alpha-* | alphaev[4-8]-* | alphaev56-* | alphaev6[78]-* \ | alpha64-* | alpha64ev[4-8]-* | alpha64ev56-* | alpha64ev6[78]-* \ | alphapca5[67]-* | alpha64pca5[67]-* | arc-* \ | arm-* | armbe-* | armle-* | armeb-* | armv*-* \ | avr-* | avr32-* \ | bfin-* | bs2000-* \ | c[123]* | c30-* | [cjt]90-* | c4x-* | c54x-* | c55x-* | c6x-* \ | clipper-* | craynv-* | cydra-* \ | d10v-* | d30v-* | dlx-* \ | elxsi-* \ | f30[01]-* | f700-* | fido-* | fr30-* | frv-* | fx80-* \ | h8300-* | h8500-* \ | hppa-* | hppa1.[01]-* | hppa2.0-* | hppa2.0[nw]-* | hppa64-* \ | i*86-* | i860-* | i960-* | ia64-* \ | ip2k-* | iq2000-* \ | m32c-* | m32r-* | m32rle-* \ | m68000-* | m680[012346]0-* | m68360-* | m683?2-* | m68k-* \ | m88110-* | m88k-* | maxq-* | mcore-* \ | mips-* | mipsbe-* | mipseb-* | mipsel-* | mipsle-* \ | mips16-* \ | mips64-* | mips64el-* \ | mips64vr-* | mips64vrel-* \ | mips64orion-* | mips64orionel-* \ | mips64vr4100-* | mips64vr4100el-* \ | mips64vr4300-* | mips64vr4300el-* \ | mips64vr5000-* | mips64vr5000el-* \ | mips64vr5900-* | mips64vr5900el-* \ | mipsisa32-* | mipsisa32el-* \ | mipsisa32r2-* | mipsisa32r2el-* \ | mipsisa64-* | mipsisa64el-* \ | mipsisa64r2-* | mipsisa64r2el-* \ | mipsisa64sb1-* | mipsisa64sb1el-* \ | mipsisa64sr71k-* | mipsisa64sr71kel-* \ | mipstx39-* | mipstx39el-* \ | mmix-* \ | mt-* \ | msp430-* \ | nios-* | nios2-* \ | none-* | np1-* | ns16k-* | ns32k-* \ | orion-* \ | pdp10-* | pdp11-* | pj-* | pjl-* | pn-* | power-* \ | powerpc-* | powerpc64-* | powerpc64le-* | powerpcle-* | ppcbe-* \ | pyramid-* \ | romp-* | rs6000-* \ | sh-* | sh[1234]-* | sh[24]a-* | sh[23]e-* | sh[34]eb-* | sheb-* | shbe-* \ | shle-* | sh[1234]le-* | sh3ele-* | sh64-* | sh64le-* \ | sparc-* | sparc64-* | sparc64b-* | sparc64v-* | sparc86x-* | sparclet-* \ | sparclite-* \ | sparcv8-* | sparcv9-* | sparcv9b-* | sparcv9v-* | strongarm-* | sv1-* | sx?-* \ | tahoe-* | thumb-* \ | tic30-* | tic4x-* | tic54x-* | tic55x-* | tic6x-* | tic80-* \ | tron-* \ | v850-* | v850e-* | vax-* \ | we32k-* \ | x86-* | x86_64-* | xc16x-* | xps100-* | xscale-* | xscalee[bl]-* \ | xstormy16-* | xtensa-* \ | ymp-* \ | z8k-*) ;; # Recognize the various machine names and aliases which stand # for a CPU type and a company and sometimes even an OS. 386bsd) basic_machine=i386-unknown os=-bsd ;; 3b1 | 7300 | 7300-att | att-7300 | pc7300 | safari | unixpc) basic_machine=m68000-att ;; 3b*) basic_machine=we32k-att ;; a29khif) basic_machine=a29k-amd os=-udi ;; abacus) basic_machine=abacus-unknown ;; adobe68k) basic_machine=m68010-adobe os=-scout ;; alliant | fx80) basic_machine=fx80-alliant ;; altos | altos3068) basic_machine=m68k-altos ;; am29k) basic_machine=a29k-none os=-bsd ;; amd64) basic_machine=x86_64-pc ;; amd64-*) basic_machine=x86_64-`echo $basic_machine | sed 's/^[^-]*-//'` ;; amdahl) basic_machine=580-amdahl os=-sysv ;; amiga | amiga-*) basic_machine=m68k-unknown ;; amigaos | amigados) basic_machine=m68k-unknown os=-amigaos ;; amigaunix | amix) basic_machine=m68k-unknown os=-sysv4 ;; apollo68) basic_machine=m68k-apollo os=-sysv ;; apollo68bsd) basic_machine=m68k-apollo os=-bsd ;; aux) basic_machine=m68k-apple os=-aux ;; balance) basic_machine=ns32k-sequent os=-dynix ;; c90) basic_machine=c90-cray os=-unicos ;; convex-c1) basic_machine=c1-convex os=-bsd ;; convex-c2) basic_machine=c2-convex os=-bsd ;; convex-c32) basic_machine=c32-convex os=-bsd ;; convex-c34) basic_machine=c34-convex os=-bsd ;; convex-c38) basic_machine=c38-convex os=-bsd ;; cray | j90) basic_machine=j90-cray os=-unicos ;; craynv) basic_machine=craynv-cray os=-unicosmp ;; cr16c) basic_machine=cr16c-unknown os=-elf ;; crds | unos) basic_machine=m68k-crds ;; crisv32 | crisv32-* | etraxfs*) basic_machine=crisv32-axis ;; cris | cris-* | etrax*) basic_machine=cris-axis ;; crx) basic_machine=crx-unknown os=-elf ;; da30 | da30-*) basic_machine=m68k-da30 ;; decstation | decstation-3100 | pmax | pmax-* | pmin | dec3100 | decstatn) basic_machine=mips-dec ;; decsystem10* | dec10*) basic_machine=pdp10-dec os=-tops10 ;; decsystem20* | dec20*) basic_machine=pdp10-dec os=-tops20 ;; delta | 3300 | motorola-3300 | motorola-delta \ | 3300-motorola | delta-motorola) basic_machine=m68k-motorola ;; delta88) basic_machine=m88k-motorola os=-sysv3 ;; djgpp) basic_machine=i586-pc os=-msdosdjgpp ;; dpx20 | dpx20-*) basic_machine=rs6000-bull os=-bosx ;; dpx2* | dpx2*-bull) basic_machine=m68k-bull os=-sysv3 ;; ebmon29k) basic_machine=a29k-amd os=-ebmon ;; elxsi) basic_machine=elxsi-elxsi os=-bsd ;; encore | umax | mmax) basic_machine=ns32k-encore ;; es1800 | OSE68k | ose68k | ose | OSE) basic_machine=m68k-ericsson os=-ose ;; fx2800) basic_machine=i860-alliant ;; genix) basic_machine=ns32k-ns ;; gmicro) basic_machine=tron-gmicro os=-sysv ;; go32) basic_machine=i386-pc os=-go32 ;; h3050r* | hiux*) basic_machine=hppa1.1-hitachi os=-hiuxwe2 ;; h8300hms) basic_machine=h8300-hitachi os=-hms ;; h8300xray) basic_machine=h8300-hitachi os=-xray ;; h8500hms) basic_machine=h8500-hitachi os=-hms ;; harris) basic_machine=m88k-harris os=-sysv3 ;; hp300-*) basic_machine=m68k-hp ;; hp300bsd) basic_machine=m68k-hp os=-bsd ;; hp300hpux) basic_machine=m68k-hp os=-hpux ;; hp3k9[0-9][0-9] | hp9[0-9][0-9]) basic_machine=hppa1.0-hp ;; hp9k2[0-9][0-9] | hp9k31[0-9]) basic_machine=m68000-hp ;; hp9k3[2-9][0-9]) basic_machine=m68k-hp ;; hp9k6[0-9][0-9] | hp6[0-9][0-9]) basic_machine=hppa1.0-hp ;; hp9k7[0-79][0-9] | hp7[0-79][0-9]) basic_machine=hppa1.1-hp ;; hp9k78[0-9] | hp78[0-9]) # FIXME: really hppa2.0-hp basic_machine=hppa1.1-hp ;; hp9k8[67]1 | hp8[67]1 | hp9k80[24] | hp80[24] | hp9k8[78]9 | hp8[78]9 | hp9k893 | hp893) # FIXME: really hppa2.0-hp basic_machine=hppa1.1-hp ;; hp9k8[0-9][13679] | hp8[0-9][13679]) basic_machine=hppa1.1-hp ;; hp9k8[0-9][0-9] | hp8[0-9][0-9]) basic_machine=hppa1.0-hp ;; hppa-next) os=-nextstep3 ;; hppaosf) basic_machine=hppa1.1-hp os=-osf ;; hppro) basic_machine=hppa1.1-hp os=-proelf ;; i370-ibm* | ibm*) basic_machine=i370-ibm ;; # I'm not sure what "Sysv32" means. Should this be sysv3.2? i*86v32) basic_machine=`echo $1 | sed -e 's/86.*/86-pc/'` os=-sysv32 ;; i*86v4*) basic_machine=`echo $1 | sed -e 's/86.*/86-pc/'` os=-sysv4 ;; i*86v) basic_machine=`echo $1 | sed -e 's/86.*/86-pc/'` os=-sysv ;; i*86sol2) basic_machine=`echo $1 | sed -e 's/86.*/86-pc/'` os=-solaris2 ;; i386mach) basic_machine=i386-mach os=-mach ;; i386-vsta | vsta) basic_machine=i386-unknown os=-vsta ;; iris | iris4d) basic_machine=mips-sgi case $os in -irix*) ;; *) os=-irix4 ;; esac ;; isi68 | isi) basic_machine=m68k-isi os=-sysv ;; m88k-omron*) basic_machine=m88k-omron ;; magnum | m3230) basic_machine=mips-mips os=-sysv ;; merlin) basic_machine=ns32k-utek os=-sysv ;; mingw32) basic_machine=i386-pc os=-mingw32 ;; mingw32ce) basic_machine=arm-unknown os=-mingw32ce ;; miniframe) basic_machine=m68000-convergent ;; *mint | -mint[0-9]* | *MiNT | *MiNT[0-9]*) basic_machine=m68k-atari os=-mint ;; mips3*-*) basic_machine=`echo $basic_machine | sed -e 's/mips3/mips64/'` ;; mips3*) basic_machine=`echo $basic_machine | sed -e 's/mips3/mips64/'`-unknown ;; monitor) basic_machine=m68k-rom68k os=-coff ;; morphos) basic_machine=powerpc-unknown os=-morphos ;; msdos) basic_machine=i386-pc os=-msdos ;; ms1-*) basic_machine=`echo $basic_machine | sed -e 's/ms1-/mt-/'` ;; mvs) basic_machine=i370-ibm os=-mvs ;; ncr3000) basic_machine=i486-ncr os=-sysv4 ;; netbsd386) basic_machine=i386-unknown os=-netbsd ;; netwinder) basic_machine=armv4l-rebel os=-linux ;; news | news700 | news800 | news900) basic_machine=m68k-sony os=-newsos ;; news1000) basic_machine=m68030-sony os=-newsos ;; news-3600 | risc-news) basic_machine=mips-sony os=-newsos ;; necv70) basic_machine=v70-nec os=-sysv ;; next | m*-next ) basic_machine=m68k-next case $os in -nextstep* ) ;; -ns2*) os=-nextstep2 ;; *) os=-nextstep3 ;; esac ;; nh3000) basic_machine=m68k-harris os=-cxux ;; nh[45]000) basic_machine=m88k-harris os=-cxux ;; nindy960) basic_machine=i960-intel os=-nindy ;; mon960) basic_machine=i960-intel os=-mon960 ;; nonstopux) basic_machine=mips-compaq os=-nonstopux ;; np1) basic_machine=np1-gould ;; nsr-tandem) basic_machine=nsr-tandem ;; op50n-* | op60c-*) basic_machine=hppa1.1-oki os=-proelf ;; openrisc | openrisc-*) basic_machine=or32-unknown ;; os400) basic_machine=powerpc-ibm os=-os400 ;; OSE68000 | ose68000) basic_machine=m68000-ericsson os=-ose ;; os68k) basic_machine=m68k-none os=-os68k ;; pa-hitachi) basic_machine=hppa1.1-hitachi os=-hiuxwe2 ;; paragon) basic_machine=i860-intel os=-osf ;; pbd) basic_machine=sparc-tti ;; pbb) basic_machine=m68k-tti ;; pc532 | pc532-*) basic_machine=ns32k-pc532 ;; pc98) basic_machine=i386-pc ;; pc98-*) basic_machine=i386-`echo $basic_machine | sed 's/^[^-]*-//'` ;; pentium | p5 | k5 | k6 | nexgen | viac3) basic_machine=i586-pc ;; pentiumpro | p6 | 6x86 | athlon | athlon_*) basic_machine=i686-pc ;; pentiumii | pentium2 | pentiumiii | pentium3) basic_machine=i686-pc ;; pentium4) basic_machine=i786-pc ;; pentium-* | p5-* | k5-* | k6-* | nexgen-* | viac3-*) basic_machine=i586-`echo $basic_machine | sed 's/^[^-]*-//'` ;; pentiumpro-* | p6-* | 6x86-* | athlon-*) basic_machine=i686-`echo $basic_machine | sed 's/^[^-]*-//'` ;; pentiumii-* | pentium2-* | pentiumiii-* | pentium3-*) basic_machine=i686-`echo $basic_machine | sed 's/^[^-]*-//'` ;; pentium4-*) basic_machine=i786-`echo $basic_machine | sed 's/^[^-]*-//'` ;; pn) basic_machine=pn-gould ;; power) basic_machine=power-ibm ;; ppc) basic_machine=powerpc-unknown ;; ppc-*) basic_machine=powerpc-`echo $basic_machine | sed 's/^[^-]*-//'` ;; ppcle | powerpclittle | ppc-le | powerpc-little) basic_machine=powerpcle-unknown ;; ppcle-* | powerpclittle-*) basic_machine=powerpcle-`echo $basic_machine | sed 's/^[^-]*-//'` ;; ppc64) basic_machine=powerpc64-unknown ;; ppc64-*) basic_machine=powerpc64-`echo $basic_machine | sed 's/^[^-]*-//'` ;; ppc64le | powerpc64little | ppc64-le | powerpc64-little) basic_machine=powerpc64le-unknown ;; ppc64le-* | powerpc64little-*) basic_machine=powerpc64le-`echo $basic_machine | sed 's/^[^-]*-//'` ;; ps2) basic_machine=i386-ibm ;; pw32) basic_machine=i586-unknown os=-pw32 ;; rdos) basic_machine=i386-pc os=-rdos ;; rom68k) basic_machine=m68k-rom68k os=-coff ;; rm[46]00) basic_machine=mips-siemens ;; rtpc | rtpc-*) basic_machine=romp-ibm ;; s390 | s390-*) basic_machine=s390-ibm ;; s390x | s390x-*) basic_machine=s390x-ibm ;; sa29200) basic_machine=a29k-amd os=-udi ;; sb1) basic_machine=mipsisa64sb1-unknown ;; sb1el) basic_machine=mipsisa64sb1el-unknown ;; sde) basic_machine=mipsisa32-sde os=-elf ;; sei) basic_machine=mips-sei os=-seiux ;; sequent) basic_machine=i386-sequent ;; sh) basic_machine=sh-hitachi os=-hms ;; sh5el) basic_machine=sh5le-unknown ;; sh64) basic_machine=sh64-unknown ;; sparclite-wrs | simso-wrs) basic_machine=sparclite-wrs os=-vxworks ;; sps7) basic_machine=m68k-bull os=-sysv2 ;; spur) basic_machine=spur-unknown ;; st2000) basic_machine=m68k-tandem ;; stratus) basic_machine=i860-stratus os=-sysv4 ;; sun2) basic_machine=m68000-sun ;; sun2os3) basic_machine=m68000-sun os=-sunos3 ;; sun2os4) basic_machine=m68000-sun os=-sunos4 ;; sun3os3) basic_machine=m68k-sun os=-sunos3 ;; sun3os4) basic_machine=m68k-sun os=-sunos4 ;; sun4os3) basic_machine=sparc-sun os=-sunos3 ;; sun4os4) basic_machine=sparc-sun os=-sunos4 ;; sun4sol2) basic_machine=sparc-sun os=-solaris2 ;; sun3 | sun3-*) basic_machine=m68k-sun ;; sun4) basic_machine=sparc-sun ;; sun386 | sun386i | roadrunner) basic_machine=i386-sun ;; sv1) basic_machine=sv1-cray os=-unicos ;; symmetry) basic_machine=i386-sequent os=-dynix ;; t3e) basic_machine=alphaev5-cray os=-unicos ;; t90) basic_machine=t90-cray os=-unicos ;; tic54x | c54x*) basic_machine=tic54x-unknown os=-coff ;; tic55x | c55x*) basic_machine=tic55x-unknown os=-coff ;; tic6x | c6x*) basic_machine=tic6x-unknown os=-coff ;; tx39) basic_machine=mipstx39-unknown ;; tx39el) basic_machine=mipstx39el-unknown ;; toad1) basic_machine=pdp10-xkl os=-tops20 ;; tower | tower-32) basic_machine=m68k-ncr ;; tpf) basic_machine=s390x-ibm os=-tpf ;; udi29k) basic_machine=a29k-amd os=-udi ;; ultra3) basic_machine=a29k-nyu os=-sym1 ;; v810 | necv810) basic_machine=v810-nec os=-none ;; vaxv) basic_machine=vax-dec os=-sysv ;; vms) basic_machine=vax-dec os=-vms ;; vpp*|vx|vx-*) basic_machine=f301-fujitsu ;; vxworks960) basic_machine=i960-wrs os=-vxworks ;; vxworks68) basic_machine=m68k-wrs os=-vxworks ;; vxworks29k) basic_machine=a29k-wrs os=-vxworks ;; w65*) basic_machine=w65-wdc os=-none ;; w89k-*) basic_machine=hppa1.1-winbond os=-proelf ;; xbox) basic_machine=i686-pc os=-mingw32 ;; xps | xps100) basic_machine=xps100-honeywell ;; ymp) basic_machine=ymp-cray os=-unicos ;; z8k-*-coff) basic_machine=z8k-unknown os=-sim ;; none) basic_machine=none-none os=-none ;; # Here we handle the default manufacturer of certain CPU types. It is in # some cases the only manufacturer, in others, it is the most popular. w89k) basic_machine=hppa1.1-winbond ;; op50n) basic_machine=hppa1.1-oki ;; op60c) basic_machine=hppa1.1-oki ;; romp) basic_machine=romp-ibm ;; mmix) basic_machine=mmix-knuth ;; rs6000) basic_machine=rs6000-ibm ;; vax) basic_machine=vax-dec ;; pdp10) # there are many clones, so DEC is not a safe bet basic_machine=pdp10-unknown ;; pdp11) basic_machine=pdp11-dec ;; we32k) basic_machine=we32k-att ;; sh[1234] | sh[24]a | sh[34]eb | sh[1234]le | sh[23]ele) basic_machine=sh-unknown ;; sparc | sparcv8 | sparcv9 | sparcv9b | sparcv9v) basic_machine=sparc-sun ;; cydra) basic_machine=cydra-cydrome ;; orion) basic_machine=orion-highlevel ;; orion105) basic_machine=clipper-highlevel ;; mac | mpw | mac-mpw) basic_machine=m68k-apple ;; pmac | pmac-mpw) basic_machine=powerpc-apple ;; *-unknown) # Make sure to match an already-canonicalized machine name. ;; *) echo Invalid configuration \`$1\': machine \`$basic_machine\' not recognized 1>&2 exit 1 ;; esac # Here we canonicalize certain aliases for manufacturers. case $basic_machine in *-digital*) basic_machine=`echo $basic_machine | sed 's/digital.*/dec/'` ;; *-commodore*) basic_machine=`echo $basic_machine | sed 's/commodore.*/cbm/'` ;; *) ;; esac # Decode manufacturer-specific aliases for certain operating systems. if [ x"$os" != x"" ] then case $os in # First match some system type aliases # that might get confused with valid system types. # -solaris* is a basic system type, with this one exception. -solaris1 | -solaris1.*) os=`echo $os | sed -e 's|solaris1|sunos4|'` ;; -solaris) os=-solaris2 ;; -svr4*) os=-sysv4 ;; -unixware*) os=-sysv4.2uw ;; -gnu/linux*) os=`echo $os | sed -e 's|gnu/linux|linux-gnu|'` ;; # First accept the basic system types. # The portable systems comes first. # Each alternative MUST END IN A *, to match a version number. # -sysv* is not here because it comes later, after sysvr4. -gnu* | -bsd* | -mach* | -minix* | -genix* | -ultrix* | -irix* \ | -*vms* | -sco* | -esix* | -isc* | -aix* | -sunos | -sunos[34]*\ | -hpux* | -unos* | -osf* | -luna* | -dgux* | -solaris* | -sym* \ | -amigaos* | -amigados* | -msdos* | -newsos* | -unicos* | -aof* \ | -aos* \ | -nindy* | -vxsim* | -vxworks* | -ebmon* | -hms* | -mvs* \ | -clix* | -riscos* | -uniplus* | -iris* | -rtu* | -xenix* \ | -hiux* | -386bsd* | -knetbsd* | -mirbsd* | -netbsd* \ | -openbsd* | -solidbsd* \ | -ekkobsd* | -kfreebsd* | -freebsd* | -riscix* | -lynxos* \ | -bosx* | -nextstep* | -cxux* | -aout* | -elf* | -oabi* \ | -ptx* | -coff* | -ecoff* | -winnt* | -domain* | -vsta* \ | -udi* | -eabi* | -lites* | -ieee* | -go32* | -aux* \ | -chorusos* | -chorusrdb* \ | -cygwin* | -pe* | -psos* | -moss* | -proelf* | -rtems* \ | -mingw32* | -linux-gnu* | -linux-newlib* | -linux-uclibc* \ | -uxpv* | -beos* | -mpeix* | -udk* \ | -interix* | -uwin* | -mks* | -rhapsody* | -darwin* | -opened* \ | -openstep* | -oskit* | -conix* | -pw32* | -nonstopux* \ | -storm-chaos* | -tops10* | -tenex* | -tops20* | -its* \ | -os2* | -vos* | -palmos* | -uclinux* | -nucleus* \ | -morphos* | -superux* | -rtmk* | -rtmk-nova* | -windiss* \ | -powermax* | -dnix* | -nx6 | -nx7 | -sei* | -dragonfly* \ | -skyos* | -haiku* | -rdos* | -toppers* | -drops*) # Remember, each alternative MUST END IN *, to match a version number. ;; -qnx*) case $basic_machine in x86-* | i*86-*) ;; *) os=-nto$os ;; esac ;; -nto-qnx*) ;; -nto*) os=`echo $os | sed -e 's|nto|nto-qnx|'` ;; -sim | -es1800* | -hms* | -xray | -os68k* | -none* | -v88r* \ | -windows* | -osx | -abug | -netware* | -os9* | -beos* | -haiku* \ | -macos* | -mpw* | -magic* | -mmixware* | -mon960* | -lnews*) ;; -mac*) os=`echo $os | sed -e 's|mac|macos|'` ;; -linux-dietlibc) os=-linux-dietlibc ;; -linux*) os=`echo $os | sed -e 's|linux|linux-gnu|'` ;; -sunos5*) os=`echo $os | sed -e 's|sunos5|solaris2|'` ;; -sunos6*) os=`echo $os | sed -e 's|sunos6|solaris3|'` ;; -opened*) os=-openedition ;; -os400*) os=-os400 ;; -wince*) os=-wince ;; -osfrose*) os=-osfrose ;; -osf*) os=-osf ;; -utek*) os=-bsd ;; -dynix*) os=-bsd ;; -acis*) os=-aos ;; -atheos*) os=-atheos ;; -syllable*) os=-syllable ;; -386bsd) os=-bsd ;; -ctix* | -uts*) os=-sysv ;; -nova*) os=-rtmk-nova ;; -ns2 ) os=-nextstep2 ;; -nsk*) os=-nsk ;; # Preserve the version number of sinix5. -sinix5.*) os=`echo $os | sed -e 's|sinix|sysv|'` ;; -sinix*) os=-sysv4 ;; -tpf*) os=-tpf ;; -triton*) os=-sysv3 ;; -oss*) os=-sysv3 ;; -svr4) os=-sysv4 ;; -svr3) os=-sysv3 ;; -sysvr4) os=-sysv4 ;; # This must come after -sysvr4. -sysv*) ;; -ose*) os=-ose ;; -es1800*) os=-ose ;; -xenix) os=-xenix ;; -*mint | -mint[0-9]* | -*MiNT | -MiNT[0-9]*) os=-mint ;; -aros*) os=-aros ;; -kaos*) os=-kaos ;; -zvmoe) os=-zvmoe ;; -none) ;; *) # Get rid of the `-' at the beginning of $os. os=`echo $os | sed 's/[^-]*-//'` echo Invalid configuration \`$1\': system \`$os\' not recognized 1>&2 exit 1 ;; esac else # Here we handle the default operating systems that come with various machines. # The value should be what the vendor currently ships out the door with their # machine or put another way, the most popular os provided with the machine. # Note that if you're going to try to match "-MANUFACTURER" here (say, # "-sun"), then you have to tell the case statement up towards the top # that MANUFACTURER isn't an operating system. Otherwise, code above # will signal an error saying that MANUFACTURER isn't an operating # system, and we'll never get to this point. case $basic_machine in score-*) os=-elf ;; spu-*) os=-elf ;; *-acorn) os=-riscix1.2 ;; arm*-rebel) os=-linux ;; arm*-semi) os=-aout ;; c4x-* | tic4x-*) os=-coff ;; # This must come before the *-dec entry. pdp10-*) os=-tops20 ;; pdp11-*) os=-none ;; *-dec | vax-*) os=-ultrix4.2 ;; m68*-apollo) os=-domain ;; i386-sun) os=-sunos4.0.2 ;; m68000-sun) os=-sunos3 # This also exists in the configure program, but was not the # default. # os=-sunos4 ;; m68*-cisco) os=-aout ;; mep-*) os=-elf ;; mips*-cisco) os=-elf ;; mips*-*) os=-elf ;; or32-*) os=-coff ;; *-tti) # must be before sparc entry or we get the wrong os. os=-sysv3 ;; sparc-* | *-sun) os=-sunos4.1.1 ;; *-be) os=-beos ;; *-haiku) os=-haiku ;; *-ibm) os=-aix ;; *-knuth) os=-mmixware ;; *-wec) os=-proelf ;; *-winbond) os=-proelf ;; *-oki) os=-proelf ;; *-hp) os=-hpux ;; *-hitachi) os=-hiux ;; i860-* | *-att | *-ncr | *-altos | *-motorola | *-convergent) os=-sysv ;; *-cbm) os=-amigaos ;; *-dg) os=-dgux ;; *-dolphin) os=-sysv3 ;; m68k-ccur) os=-rtu ;; m88k-omron*) os=-luna ;; *-next ) os=-nextstep ;; *-sequent) os=-ptx ;; *-crds) os=-unos ;; *-ns) os=-genix ;; i370-*) os=-mvs ;; *-next) os=-nextstep3 ;; *-gould) os=-sysv ;; *-highlevel) os=-bsd ;; *-encore) os=-bsd ;; *-sgi) os=-irix ;; *-siemens) os=-sysv4 ;; *-masscomp) os=-rtu ;; f30[01]-fujitsu | f700-fujitsu) os=-uxpv ;; *-rom68k) os=-coff ;; *-*bug) os=-coff ;; *-apple) os=-macos ;; *-atari*) os=-mint ;; *) os=-none ;; esac fi # Here we handle the case where we know the os, and the CPU type, but not the # manufacturer. We pick the logical manufacturer. vendor=unknown case $basic_machine in *-unknown) case $os in -riscix*) vendor=acorn ;; -sunos*) vendor=sun ;; -aix*) vendor=ibm ;; -beos*) vendor=be ;; -hpux*) vendor=hp ;; -mpeix*) vendor=hp ;; -hiux*) vendor=hitachi ;; -unos*) vendor=crds ;; -dgux*) vendor=dg ;; -luna*) vendor=omron ;; -genix*) vendor=ns ;; -mvs* | -opened*) vendor=ibm ;; -os400*) vendor=ibm ;; -ptx*) vendor=sequent ;; -tpf*) vendor=ibm ;; -vxsim* | -vxworks* | -windiss*) vendor=wrs ;; -aux*) vendor=apple ;; -hms*) vendor=hitachi ;; -mpw* | -macos*) vendor=apple ;; -*mint | -mint[0-9]* | -*MiNT | -MiNT[0-9]*) vendor=atari ;; -vos*) vendor=stratus ;; esac basic_machine=`echo $basic_machine | sed "s/unknown/$vendor/"` ;; esac echo $basic_machine$os exit # Local variables: # eval: (add-hook 'write-file-hooks 'time-stamp) # time-stamp-start: "timestamp='" # time-stamp-format: "%:y-%02m-%02d" # time-stamp-end: "'" # End: ./CBFlib-0.9.2.2/libtool/ltconfig0000755000076500007650000030205111603702120014772 0ustar yayayaya#! /bin/sh # ltconfig - Create a system-specific libtool. # Copyright (C) 1996-1999 Free Software Foundation, Inc. # Originally by Gordon Matzigkeit , 1996 # # This file is free software; you can redistribute it and/or modify it # under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2 of the License, or # (at your option) any later version. # # This program is distributed in the hope that it will be useful, but # WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # General Public License for more details. # # You should have received a copy of the GNU General Public License # along with this program; if not, write to the Free Software # Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA. # # As a special exception to the GNU General Public License, if you # distribute this file as part of a program that contains a # configuration script generated by Autoconf, you may include it under # the same distribution terms that you use for the rest of that program. # A lot of this script is taken from autoconf-2.10. # Check that we are running under the correct shell. SHELL=${CONFIG_SHELL-/bin/sh} echo=echo if test "X$1" = X--no-reexec; then # Discard the --no-reexec flag, and continue. shift elif test "X$1" = X--fallback-echo; then # Avoid inline document here, it may be left over : elif test "X`($echo '\t') 2>/dev/null`" = 'X\t'; then # Yippee, $echo works! : else # Restart under the correct shell. exec "$SHELL" "$0" --no-reexec ${1+"$@"} fi if test "X$1" = X--fallback-echo; then # used as fallback echo shift cat </dev/null`} case X$UNAME in *-DOS) PATH_SEPARATOR=';' ;; *) PATH_SEPARATOR=':' ;; esac fi # The HP-UX ksh and POSIX shell print the target directory to stdout # if CDPATH is set. if test "X${CDPATH+set}" = Xset; then CDPATH=:; export CDPATH; fi if test "X${echo_test_string+set}" != Xset; then # find a string as large as possible, as long as the shell can cope with it for cmd in 'sed 50q "$0"' 'sed 20q "$0"' 'sed 10q "$0"' 'sed 2q "$0"' 'echo test'; do # expected sizes: less than 2Kb, 1Kb, 512 bytes, 16 bytes, ... if (echo_test_string="`eval $cmd`") 2>/dev/null && echo_test_string="`eval $cmd`" && (test "X$echo_test_string" = "X$echo_test_string") 2>/dev/null; then break fi done fi if test "X`($echo '\t') 2>/dev/null`" != 'X\t' || test "X`($echo "$echo_test_string") 2>/dev/null`" != X"$echo_test_string"; then # The Solaris, AIX, and Digital Unix default echo programs unquote # backslashes. This makes it impossible to quote backslashes using # echo "$something" | sed 's/\\/\\\\/g' # # So, first we look for a working echo in the user's PATH. IFS="${IFS= }"; save_ifs="$IFS"; IFS="${IFS}${PATH_SEPARATOR}" for dir in $PATH /usr/ucb; do if (test -f $dir/echo || test -f $dir/echo$ac_exeext) && test "X`($dir/echo '\t') 2>/dev/null`" = 'X\t' && test "X`($dir/echo "$echo_test_string") 2>/dev/null`" = X"$echo_test_string"; then echo="$dir/echo" break fi done IFS="$save_ifs" if test "X$echo" = Xecho; then # We didn't find a better echo, so look for alternatives. if test "X`(print -r '\t') 2>/dev/null`" = 'X\t' && test "X`(print -r "$echo_test_string") 2>/dev/null`" = X"$echo_test_string"; then # This shell has a builtin print -r that does the trick. echo='print -r' elif (test -f /bin/ksh || test -f /bin/ksh$ac_exeext) && test "X$CONFIG_SHELL" != X/bin/ksh; then # If we have ksh, try running ltconfig again with it. ORIGINAL_CONFIG_SHELL="${CONFIG_SHELL-/bin/sh}" export ORIGINAL_CONFIG_SHELL CONFIG_SHELL=/bin/ksh export CONFIG_SHELL exec "$CONFIG_SHELL" "$0" --no-reexec ${1+"$@"} else # Try using printf. echo='printf "%s\n"' if test "X`($echo '\t') 2>/dev/null`" = 'X\t' && test "X`($echo "$echo_test_string") 2>/dev/null`" = X"$echo_test_string"; then # Cool, printf works : elif test "X`("$ORIGINAL_CONFIG_SHELL" "$0" --fallback-echo '\t') 2>/dev/null`" = 'X\t' && test "X`("$ORIGINAL_CONFIG_SHELL" "$0" --fallback-echo "$echo_test_string") 2>/dev/null`" = X"$echo_test_string"; then CONFIG_SHELL="$ORIGINAL_CONFIG_SHELL" export CONFIG_SHELL SHELL="$CONFIG_SHELL" export SHELL echo="$CONFIG_SHELL $0 --fallback-echo" elif test "X`("$CONFIG_SHELL" "$0" --fallback-echo '\t') 2>/dev/null`" = 'X\t' && test "X`("$CONFIG_SHELL" "$0" --fallback-echo "$echo_test_string") 2>/dev/null`" = X"$echo_test_string"; then echo="$CONFIG_SHELL $0 --fallback-echo" else # maybe with a smaller string... prev=: for cmd in 'echo test' 'sed 2q "$0"' 'sed 10q "$0"' 'sed 20q "$0"' 'sed 50q "$0"'; do if (test "X$echo_test_string" = "X`eval $cmd`") 2>/dev/null; then break fi prev="$cmd" done if test "$prev" != 'sed 50q "$0"'; then echo_test_string=`eval $prev` export echo_test_string exec "${ORIGINAL_CONFIG_SHELL}" "$0" ${1+"$@"} else # Oops. We lost completely, so just stick with echo. echo=echo fi fi fi fi fi # Sed substitution that helps us do robust quoting. It backslashifies # metacharacters that are still active within double-quoted strings. Xsed='sed -e s/^X//' sed_quote_subst='s/\([\\"\\`$\\\\]\)/\\\1/g' # Same as above, but do not quote variable references. double_quote_subst='s/\([\\"\\`\\\\]\)/\\\1/g' # Sed substitution to delay expansion of an escaped shell variable in a # double_quote_subst'ed string. delay_variable_subst='s/\\\\\\\\\\\$/\\\\\\$/g' # The name of this program. progname=`$echo "X$0" | $Xsed -e 's%^.*/%%'` # Constants: PROGRAM=ltconfig PACKAGE=libtool VERSION=1.3.5 TIMESTAMP=" (1.385.2.206 2000/05/27 11:12:27)" ac_compile='${CC-cc} -c $CFLAGS $CPPFLAGS conftest.$ac_ext 1>&5' ac_link='${CC-cc} -o conftest $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS 1>&5' rm="rm -f" help="Try \`$progname --help' for more information." # Global variables: default_ofile=libtool can_build_shared=yes enable_shared=yes # All known linkers require a `.a' archive for static linking (except M$VC, # which needs '.lib'). enable_static=yes enable_fast_install=yes enable_dlopen=unknown enable_win32_dll=no ltmain= silent= srcdir= ac_config_guess= ac_config_sub= host= nonopt= ofile="$default_ofile" verify_host=yes with_gcc=no with_gnu_ld=no need_locks=yes ac_ext=c objext=o libext=a exeext= cache_file= old_AR="$AR" old_CC="$CC" old_CFLAGS="$CFLAGS" old_CPPFLAGS="$CPPFLAGS" old_LDFLAGS="$LDFLAGS" old_LD="$LD" old_LN_S="$LN_S" old_LIBS="$LIBS" old_NM="$NM" old_RANLIB="$RANLIB" old_DLLTOOL="$DLLTOOL" old_OBJDUMP="$OBJDUMP" old_AS="$AS" # Parse the command line options. args= prev= for option do case "$option" in -*=*) optarg=`echo "$option" | sed 's/[-_a-zA-Z0-9]*=//'` ;; *) optarg= ;; esac # If the previous option needs an argument, assign it. if test -n "$prev"; then eval "$prev=\$option" prev= continue fi case "$option" in --help) cat <&2 echo "$help" 1>&2 exit 1 ;; *) if test -z "$ltmain"; then ltmain="$option" elif test -z "$host"; then # This generates an unnecessary warning for sparc-sun-solaris4.1.3_U1 # if test -n "`echo $option| sed 's/[-a-z0-9.]//g'`"; then # echo "$progname: warning \`$option' is not a valid host type" 1>&2 # fi host="$option" else echo "$progname: too many arguments" 1>&2 echo "$help" 1>&2 exit 1 fi ;; esac done if test -z "$ltmain"; then echo "$progname: you must specify a LTMAIN file" 1>&2 echo "$help" 1>&2 exit 1 fi if test ! -f "$ltmain"; then echo "$progname: \`$ltmain' does not exist" 1>&2 echo "$help" 1>&2 exit 1 fi # Quote any args containing shell metacharacters. ltconfig_args= for arg do case "$arg" in *" "*|*" "*|*[\[\]\~\#\$\^\&\*\(\)\{\}\\\|\;\<\>\?]*) ltconfig_args="$ltconfig_args '$arg'" ;; *) ltconfig_args="$ltconfig_args $arg" ;; esac done # A relevant subset of AC_INIT. # File descriptor usage: # 0 standard input # 1 file creation # 2 errors and warnings # 3 some systems may open it to /dev/tty # 4 used on the Kubota Titan # 5 compiler messages saved in config.log # 6 checking for... messages and results if test "$silent" = yes; then exec 6>/dev/null else exec 6>&1 fi exec 5>>./config.log # NLS nuisances. # Only set LANG and LC_ALL to C if already set. # These must not be set unconditionally because not all systems understand # e.g. LANG=C (notably SCO). if test "X${LC_ALL+set}" = Xset; then LC_ALL=C; export LC_ALL; fi if test "X${LANG+set}" = Xset; then LANG=C; export LANG; fi if test -n "$cache_file" && test -r "$cache_file"; then echo "loading cache $cache_file within ltconfig" . $cache_file fi if (echo "testing\c"; echo 1,2,3) | grep c >/dev/null; then # Stardent Vistra SVR4 grep lacks -e, says ghazi@caip.rutgers.edu. if (echo -n testing; echo 1,2,3) | sed s/-n/xn/ | grep xn >/dev/null; then ac_n= ac_c=' ' ac_t=' ' else ac_n=-n ac_c= ac_t= fi else ac_n= ac_c='\c' ac_t= fi if test -z "$srcdir"; then # Assume the source directory is the same one as the path to LTMAIN. srcdir=`$echo "X$ltmain" | $Xsed -e 's%/[^/]*$%%'` test "$srcdir" = "$ltmain" && srcdir=. fi trap "$rm conftest*; exit 1" 1 2 15 if test "$verify_host" = yes; then # Check for config.guess and config.sub. ac_aux_dir= for ac_dir in $srcdir $srcdir/.. $srcdir/../..; do if test -f $ac_dir/config.guess; then ac_aux_dir=$ac_dir break fi done if test -z "$ac_aux_dir"; then echo "$progname: cannot find config.guess in $srcdir $srcdir/.. $srcdir/../.." 1>&2 echo "$help" 1>&2 exit 1 fi ac_config_guess=$ac_aux_dir/config.guess ac_config_sub=$ac_aux_dir/config.sub # Make sure we can run config.sub. if $SHELL $ac_config_sub sun4 >/dev/null 2>&1; then : else echo "$progname: cannot run $ac_config_sub" 1>&2 echo "$help" 1>&2 exit 1 fi echo $ac_n "checking host system type""... $ac_c" 1>&6 host_alias=$host case "$host_alias" in "") if host_alias=`$SHELL $ac_config_guess`; then : else echo "$progname: cannot guess host type; you must specify one" 1>&2 echo "$help" 1>&2 exit 1 fi ;; esac host=`$SHELL $ac_config_sub $host_alias` echo "$ac_t$host" 1>&6 # Make sure the host verified. test -z "$host" && exit 1 elif test -z "$host"; then echo "$progname: you must specify a host type if you use \`--no-verify'" 1>&2 echo "$help" 1>&2 exit 1 else host_alias=$host fi # Transform linux* to *-*-linux-gnu*, to support old configure scripts. case "$host_os" in linux-gnu*) ;; linux*) host=`echo $host | sed 's/^\(.*-.*-linux\)\(.*\)$/\1-gnu\2/'` esac host_cpu=`echo $host | sed 's/^\([^-]*\)-\([^-]*\)-\(.*\)$/\1/'` host_vendor=`echo $host | sed 's/^\([^-]*\)-\([^-]*\)-\(.*\)$/\2/'` host_os=`echo $host | sed 's/^\([^-]*\)-\([^-]*\)-\(.*\)$/\3/'` case "$host_os" in aix3*) # AIX sometimes has problems with the GCC collect2 program. For some # reason, if we set the COLLECT_NAMES environment variable, the problems # vanish in a puff of smoke. if test "X${COLLECT_NAMES+set}" != Xset; then COLLECT_NAMES= export COLLECT_NAMES fi ;; esac # Determine commands to create old-style static archives. old_archive_cmds='$AR cru $oldlib$oldobjs' old_postinstall_cmds='chmod 644 $oldlib' old_postuninstall_cmds= # Set a sane default for `AR'. test -z "$AR" && AR=ar # Set a sane default for `OBJDUMP'. test -z "$OBJDUMP" && OBJDUMP=objdump # If RANLIB is not set, then run the test. if test "${RANLIB+set}" != "set"; then result=no echo $ac_n "checking for ranlib... $ac_c" 1>&6 IFS="${IFS= }"; save_ifs="$IFS"; IFS="${IFS}${PATH_SEPARATOR}" for dir in $PATH; do test -z "$dir" && dir=. if test -f $dir/ranlib || test -f $dir/ranlib$ac_exeext; then RANLIB="ranlib" result="ranlib" break fi done IFS="$save_ifs" echo "$ac_t$result" 1>&6 fi if test -n "$RANLIB"; then old_archive_cmds="$old_archive_cmds~\$RANLIB \$oldlib" old_postinstall_cmds="\$RANLIB \$oldlib~$old_postinstall_cmds" fi # Set sane defaults for `DLLTOOL', `OBJDUMP', and `AS', used on cygwin. test -z "$DLLTOOL" && DLLTOOL=dlltool test -z "$OBJDUMP" && OBJDUMP=objdump test -z "$AS" && AS=as # Check to see if we are using GCC. if test "$with_gcc" != yes || test -z "$CC"; then # If CC is not set, then try to find GCC or a usable CC. if test -z "$CC"; then echo $ac_n "checking for gcc... $ac_c" 1>&6 IFS="${IFS= }"; save_ifs="$IFS"; IFS="${IFS}${PATH_SEPARATOR}" for dir in $PATH; do test -z "$dir" && dir=. if test -f $dir/gcc || test -f $dir/gcc$ac_exeext; then CC="gcc" break fi done IFS="$save_ifs" if test -n "$CC"; then echo "$ac_t$CC" 1>&6 else echo "$ac_t"no 1>&6 fi fi # Not "gcc", so try "cc", rejecting "/usr/ucb/cc". if test -z "$CC"; then echo $ac_n "checking for cc... $ac_c" 1>&6 IFS="${IFS= }"; save_ifs="$IFS"; IFS="${IFS}${PATH_SEPARATOR}" cc_rejected=no for dir in $PATH; do test -z "$dir" && dir=. if test -f $dir/cc || test -f $dir/cc$ac_exeext; then if test "$dir/cc" = "/usr/ucb/cc"; then cc_rejected=yes continue fi CC="cc" break fi done IFS="$save_ifs" if test $cc_rejected = yes; then # We found a bogon in the path, so make sure we never use it. set dummy $CC shift if test $# -gt 0; then # We chose a different compiler from the bogus one. # However, it has the same name, so the bogon will be chosen # first if we set CC to just the name; use the full file name. shift set dummy "$dir/cc" "$@" shift CC="$@" fi fi if test -n "$CC"; then echo "$ac_t$CC" 1>&6 else echo "$ac_t"no 1>&6 fi if test -z "$CC"; then echo "$progname: error: no acceptable cc found in \$PATH" 1>&2 exit 1 fi fi # Now see if the compiler is really GCC. with_gcc=no echo $ac_n "checking whether we are using GNU C... $ac_c" 1>&6 echo "$progname:581: checking whether we are using GNU C" >&5 $rm conftest.c cat > conftest.c <&5; (eval $ac_try) 2>&5; }; } | egrep yes >/dev/null 2>&1; then with_gcc=yes fi $rm conftest.c echo "$ac_t$with_gcc" 1>&6 fi # Allow CC to be a program name with arguments. set dummy $CC compiler="$2" echo $ac_n "checking for object suffix... $ac_c" 1>&6 $rm conftest* echo 'int i = 1;' > conftest.c echo "$progname:603: checking for object suffix" >& 5 if { (eval echo $progname:604: \"$ac_compile\") 1>&5; (eval $ac_compile) 2>conftest.err; }; then # Append any warnings to the config.log. cat conftest.err 1>&5 for ac_file in conftest.*; do case $ac_file in *.c) ;; *) objext=`echo $ac_file | sed -e s/conftest.//` ;; esac done else cat conftest.err 1>&5 echo "$progname: failed program was:" >&5 cat conftest.c >&5 fi $rm conftest* echo "$ac_t$objext" 1>&6 echo $ac_n "checking for executable suffix... $ac_c" 1>&6 if eval "test \"`echo '$''{'ac_cv_exeext'+set}'`\" = set"; then echo $ac_n "(cached) $ac_c" 1>&6 else ac_cv_exeext="no" $rm conftest* echo 'main () { return 0; }' > conftest.c echo "$progname:629: checking for executable suffix" >& 5 if { (eval echo $progname:630: \"$ac_link\") 1>&5; (eval $ac_link) 2>conftest.err; }; then # Append any warnings to the config.log. cat conftest.err 1>&5 for ac_file in conftest.*; do case $ac_file in *.c | *.err | *.$objext ) ;; *) ac_cv_exeext=.`echo $ac_file | sed -e s/conftest.//` ;; esac done else cat conftest.err 1>&5 echo "$progname: failed program was:" >&5 cat conftest.c >&5 fi $rm conftest* fi if test "X$ac_cv_exeext" = Xno; then exeext="" else exeext="$ac_cv_exeext" fi echo "$ac_t$ac_cv_exeext" 1>&6 echo $ac_n "checking for $compiler option to produce PIC... $ac_c" 1>&6 pic_flag= special_shlib_compile_flags= wl= link_static_flag= no_builtin_flag= if test "$with_gcc" = yes; then wl='-Wl,' link_static_flag='-static' case "$host_os" in beos* | irix5* | irix6* | osf3* | osf4* | osf5*) # PIC is the default for these OSes. ;; aix*) # Below there is a dirty hack to force normal static linking with -ldl # The problem is because libdl dynamically linked with both libc and # libC (AIX C++ library), which obviously doesn't included in libraries # list by gcc. This cause undefined symbols with -static flags. # This hack allows C programs to be linked with "-static -ldl", but # we not sure about C++ programs. link_static_flag="$link_static_flag ${wl}-lC" ;; cygwin* | mingw* | os2*) # We can build DLLs from non-PIC. ;; darwin* | rhapsody*) # PIC is the default on this platform # Common symbols not allowed in MH_DYLIB files pic_flag='-fno-common' ;; amigaos*) # FIXME: we need at least 68020 code to build shared libraries, but # adding the `-m68020' flag to GCC prevents building anything better, # like `-m68040'. pic_flag='-m68020 -resident32 -malways-restore-a4' ;; sysv4*MP*) if test -d /usr/nec; then pic_flag=-Kconform_pic fi ;; *) pic_flag='-fPIC' ;; esac else # PORTME Check for PIC flags for the system compiler. case "$host_os" in aix3* | aix4*) # All AIX code is PIC. link_static_flag='-bnso -bI:/lib/syscalls.exp' ;; hpux9* | hpux10* | hpux11*) # Is there a better link_static_flag that works with the bundled CC? wl='-Wl,' link_static_flag="${wl}-a ${wl}archive" pic_flag='+Z' ;; irix5* | irix6*) wl='-Wl,' link_static_flag='-non_shared' # PIC (with -KPIC) is the default. ;; cygwin* | mingw* | os2*) # We can build DLLs from non-PIC. ;; osf3* | osf4* | osf5*) # All OSF/1 code is PIC. wl='-Wl,' link_static_flag='-non_shared' ;; sco3.2v5*) pic_flag='-Kpic' link_static_flag='-dn' special_shlib_compile_flags='-belf' ;; solaris*) pic_flag='-KPIC' link_static_flag='-Bstatic' wl='-Wl,' ;; sunos4*) pic_flag='-PIC' link_static_flag='-Bstatic' wl='-Qoption ld ' ;; sysv4 | sysv4.2uw2* | sysv4.3* | sysv5*) pic_flag='-KPIC' link_static_flag='-Bstatic' wl='-Wl,' ;; uts4*) pic_flag='-pic' link_static_flag='-Bstatic' ;; sysv4*MP*) if test -d /usr/nec ;then pic_flag='-Kconform_pic' link_static_flag='-Bstatic' fi ;; *) can_build_shared=no ;; esac fi if test -n "$pic_flag"; then echo "$ac_t$pic_flag" 1>&6 # Check to make sure the pic_flag actually works. echo $ac_n "checking if $compiler PIC flag $pic_flag works... $ac_c" 1>&6 $rm conftest* echo "int some_variable = 0;" > conftest.c save_CFLAGS="$CFLAGS" CFLAGS="$CFLAGS $pic_flag -DPIC" echo "$progname:781: checking if $compiler PIC flag $pic_flag works" >&5 if { (eval echo $progname:782: \"$ac_compile\") 1>&5; (eval $ac_compile) 2>conftest.err; } && test -s conftest.$objext; then # Append any warnings to the config.log. cat conftest.err 1>&5 case "$host_os" in hpux9* | hpux10* | hpux11*) # On HP-UX, both CC and GCC only warn that PIC is supported... then they # create non-PIC objects. So, if there were any warnings, we assume that # PIC is not supported. if test -s conftest.err; then echo "$ac_t"no 1>&6 can_build_shared=no pic_flag= else echo "$ac_t"yes 1>&6 pic_flag=" $pic_flag" fi ;; *) echo "$ac_t"yes 1>&6 pic_flag=" $pic_flag" ;; esac else # Append any errors to the config.log. cat conftest.err 1>&5 can_build_shared=no pic_flag= echo "$ac_t"no 1>&6 fi CFLAGS="$save_CFLAGS" $rm conftest* else echo "$ac_t"none 1>&6 fi # Check to see if options -o and -c are simultaneously supported by compiler echo $ac_n "checking if $compiler supports -c -o file.o... $ac_c" 1>&6 $rm -r conftest 2>/dev/null mkdir conftest cd conftest $rm conftest* echo "int some_variable = 0;" > conftest.c mkdir out # According to Tom Tromey, Ian Lance Taylor reported there are C compilers # that will create temporary files in the current directory regardless of # the output directory. Thus, making CWD read-only will cause this test # to fail, enabling locking or at least warning the user not to do parallel # builds. chmod -w . save_CFLAGS="$CFLAGS" CFLAGS="$CFLAGS -o out/conftest2.o" echo "$progname:834: checking if $compiler supports -c -o file.o" >&5 if { (eval echo $progname:835: \"$ac_compile\") 1>&5; (eval $ac_compile) 2>out/conftest.err; } && test -s out/conftest2.o; then # The compiler can only warn and ignore the option if not recognized # So say no if there are warnings if test -s out/conftest.err; then echo "$ac_t"no 1>&6 compiler_c_o=no else echo "$ac_t"yes 1>&6 compiler_c_o=yes fi else # Append any errors to the config.log. cat out/conftest.err 1>&5 compiler_c_o=no echo "$ac_t"no 1>&6 fi CFLAGS="$save_CFLAGS" chmod u+w . $rm conftest* out/* rmdir out cd .. rmdir conftest $rm -r conftest 2>/dev/null if test x"$compiler_c_o" = x"yes"; then # Check to see if we can write to a .lo echo $ac_n "checking if $compiler supports -c -o file.lo... $ac_c" 1>&6 $rm conftest* echo "int some_variable = 0;" > conftest.c save_CFLAGS="$CFLAGS" CFLAGS="$CFLAGS -c -o conftest.lo" echo "$progname:867: checking if $compiler supports -c -o file.lo" >&5 if { (eval echo $progname:868: \"$ac_compile\") 1>&5; (eval $ac_compile) 2>conftest.err; } && test -s conftest.lo; then # The compiler can only warn and ignore the option if not recognized # So say no if there are warnings if test -s conftest.err; then echo "$ac_t"no 1>&6 compiler_o_lo=no else echo "$ac_t"yes 1>&6 compiler_o_lo=yes fi else # Append any errors to the config.log. cat conftest.err 1>&5 compiler_o_lo=no echo "$ac_t"no 1>&6 fi CFLAGS="$save_CFLAGS" $rm conftest* else compiler_o_lo=no fi # Check to see if we can do hard links to lock some files if needed hard_links="nottested" if test "$compiler_c_o" = no && test "$need_locks" != no; then # do not overwrite the value of need_locks provided by the user echo $ac_n "checking if we can lock with hard links... $ac_c" 1>&6 hard_links=yes $rm conftest* ln conftest.a conftest.b 2>/dev/null && hard_links=no touch conftest.a ln conftest.a conftest.b 2>&5 || hard_links=no ln conftest.a conftest.b 2>/dev/null && hard_links=no echo "$ac_t$hard_links" 1>&6 $rm conftest* if test "$hard_links" = no; then echo "*** WARNING: \`$CC' does not support \`-c -o', so \`make -j' may be unsafe" >&2 need_locks=warn fi else need_locks=no fi if test "$with_gcc" = yes; then # Check to see if options -fno-rtti -fno-exceptions are supported by compiler echo $ac_n "checking if $compiler supports -fno-rtti -fno-exceptions ... $ac_c" 1>&6 $rm conftest* echo "int some_variable = 0;" > conftest.c save_CFLAGS="$CFLAGS" CFLAGS="$CFLAGS -fno-rtti -fno-exceptions -c conftest.c" echo "$progname:919: checking if $compiler supports -fno-rtti -fno-exceptions" >&5 if { (eval echo $progname:920: \"$ac_compile\") 1>&5; (eval $ac_compile) 2>conftest.err; } && test -s conftest.o; then # The compiler can only warn and ignore the option if not recognized # So say no if there are warnings if test -s conftest.err; then echo "$ac_t"no 1>&6 compiler_rtti_exceptions=no else echo "$ac_t"yes 1>&6 compiler_rtti_exceptions=yes fi else # Append any errors to the config.log. cat conftest.err 1>&5 compiler_rtti_exceptions=no echo "$ac_t"no 1>&6 fi CFLAGS="$save_CFLAGS" $rm conftest* if test "$compiler_rtti_exceptions" = "yes"; then no_builtin_flag=' -fno-builtin -fno-rtti -fno-exceptions' else no_builtin_flag=' -fno-builtin' fi fi # Check for any special shared library compilation flags. if test -n "$special_shlib_compile_flags"; then echo "$progname: warning: \`$CC' requires \`$special_shlib_compile_flags' to build shared libraries" 1>&2 if echo "$old_CC $old_CFLAGS " | egrep -e "[ ]$special_shlib_compile_flags[ ]" >/dev/null; then : else echo "$progname: add \`$special_shlib_compile_flags' to the CC or CFLAGS env variable and reconfigure" 1>&2 can_build_shared=no fi fi echo $ac_n "checking if $compiler static flag $link_static_flag works... $ac_c" 1>&6 $rm conftest* echo 'main(){return(0);}' > conftest.c save_LDFLAGS="$LDFLAGS" LDFLAGS="$LDFLAGS $link_static_flag" echo "$progname:963: checking if $compiler static flag $link_static_flag works" >&5 if { (eval echo $progname:964: \"$ac_link\") 1>&5; (eval $ac_link) 2>&5; } && test -s conftest; then echo "$ac_t$link_static_flag" 1>&6 else echo "$ac_t"none 1>&6 link_static_flag= fi LDFLAGS="$save_LDFLAGS" $rm conftest* if test -z "$LN_S"; then # Check to see if we can use ln -s, or we need hard links. echo $ac_n "checking whether ln -s works... $ac_c" 1>&6 $rm conftest.dat if ln -s X conftest.dat 2>/dev/null; then $rm conftest.dat LN_S="ln -s" else LN_S=ln fi if test "$LN_S" = "ln -s"; then echo "$ac_t"yes 1>&6 else echo "$ac_t"no 1>&6 fi fi # Make sure LD is an absolute path. if test -z "$LD"; then ac_prog=ld if test "$with_gcc" = yes; then # Check if gcc -print-prog-name=ld gives a path. echo $ac_n "checking for ld used by GCC... $ac_c" 1>&6 echo "$progname:996: checking for ld used by GCC" >&5 ac_prog=`($CC -print-prog-name=ld) 2>&5` case "$ac_prog" in # Accept absolute paths. [\\/]* | [A-Za-z]:[\\/]*) re_direlt='/[^/][^/]*/\.\./' # Canonicalize the path of ld ac_prog=`echo $ac_prog| sed 's%\\\\%/%g'` while echo $ac_prog | grep "$re_direlt" > /dev/null 2>&1; do ac_prog=`echo $ac_prog| sed "s%$re_direlt%/%"` done test -z "$LD" && LD="$ac_prog" ;; "") # If it fails, then pretend we are not using GCC. ac_prog=ld ;; *) # If it is relative, then search for the first ld in PATH. with_gnu_ld=unknown ;; esac elif test "$with_gnu_ld" = yes; then echo $ac_n "checking for GNU ld... $ac_c" 1>&6 echo "$progname:1020: checking for GNU ld" >&5 else echo $ac_n "checking for non-GNU ld""... $ac_c" 1>&6 echo "$progname:1023: checking for non-GNU ld" >&5 fi if test -z "$LD"; then IFS="${IFS= }"; ac_save_ifs="$IFS"; IFS="${IFS}${PATH_SEPARATOR}" for ac_dir in $PATH; do test -z "$ac_dir" && ac_dir=. if test -f "$ac_dir/$ac_prog" || test -f "$ac_dir/$ac_prog$ac_exeext"; then LD="$ac_dir/$ac_prog" # Check to see if the program is GNU ld. I'd rather use --version, # but apparently some GNU ld's only accept -v. # Break only if it was the GNU/non-GNU ld that we prefer. if "$LD" -v 2>&1 < /dev/null | egrep '(GNU|with BFD)' > /dev/null; then test "$with_gnu_ld" != no && break else test "$with_gnu_ld" != yes && break fi fi done IFS="$ac_save_ifs" fi if test -n "$LD"; then echo "$ac_t$LD" 1>&6 else echo "$ac_t"no 1>&6 fi if test -z "$LD"; then echo "$progname: error: no acceptable ld found in \$PATH" 1>&2 exit 1 fi fi # Check to see if it really is or is not GNU ld. echo $ac_n "checking if the linker ($LD) is GNU ld... $ac_c" 1>&6 # I'd rather use --version here, but apparently some GNU ld's only accept -v. if $LD -v 2>&1 &5; then with_gnu_ld=yes else with_gnu_ld=no fi echo "$ac_t$with_gnu_ld" 1>&6 # See if the linker supports building shared libraries. echo $ac_n "checking whether the linker ($LD) supports shared libraries... $ac_c" 1>&6 allow_undefined_flag= no_undefined_flag= need_lib_prefix=unknown need_version=unknown # when you set need_version to no, make sure it does not cause -set_version # flags to be left without arguments archive_cmds= archive_expsym_cmds= old_archive_from_new_cmds= export_dynamic_flag_spec= whole_archive_flag_spec= thread_safe_flag_spec= hardcode_libdir_flag_spec= hardcode_libdir_separator= hardcode_direct=no hardcode_minus_L=no hardcode_shlibpath_var=unsupported runpath_var= always_export_symbols=no export_symbols_cmds='$NM $libobjs $convenience | $global_symbol_pipe | sed '\''s/.* //'\'' | sort | uniq > $export_symbols' # include_expsyms should be a list of space-separated symbols to be *always* # included in the symbol list include_expsyms= # exclude_expsyms can be an egrep regular expression of symbols to exclude # it will be wrapped by ` (' and `)$', so one must not match beginning or # end of line. Example: `a|bc|.*d.*' will exclude the symbols `a' and `bc', # as well as any symbol that contains `d'. exclude_expsyms="_GLOBAL_OFFSET_TABLE_" # Although _GLOBAL_OFFSET_TABLE_ is a valid symbol C name, most a.out # platforms (ab)use it in PIC code, but their linkers get confused if # the symbol is explicitly referenced. Since portable code cannot # rely on this symbol name, it's probably fine to never include it in # preloaded symbol tables. case "$host_os" in cygwin* | mingw*) # FIXME: the MSVC++ port hasn't been tested in a loooong time # When not using gcc, we currently assume that we are using # Microsoft Visual C++. if test "$with_gcc" != yes; then with_gnu_ld=no fi ;; esac ld_shlibs=yes if test "$with_gnu_ld" = yes; then # If archive_cmds runs LD, not CC, wlarc should be empty wlarc='${wl}' # See if GNU ld supports shared libraries. case "$host_os" in aix3* | aix4*) # On AIX, the GNU linker is very broken ld_shlibs=no cat <&2 *** Warning: the GNU linker, at least up to release 2.9.1, is reported *** to be unable to reliably create shared libraries on AIX. *** Therefore, libtool is disabling shared libraries support. If you *** really care for shared libraries, you may want to modify your PATH *** so that a non-GNU linker is found, and then restart. EOF ;; amigaos*) archive_cmds='$rm $objdir/a2ixlibrary.data~$echo "#define NAME $libname" > $objdir/a2ixlibrary.data~$echo "#define LIBRARY_ID 1" >> $objdir/a2ixlibrary.data~$echo "#define VERSION $major" >> $objdir/a2ixlibrary.data~$echo "#define REVISION $revision" >> $objdir/a2ixlibrary.data~$AR cru $lib $libobjs~$RANLIB $lib~(cd $objdir && a2ixlibrary -32)' hardcode_libdir_flag_spec='-L$libdir' hardcode_minus_L=yes # Samuel A. Falvo II reports # that the semantics of dynamic libraries on AmigaOS, at least up # to version 4, is to share data among multiple programs linked # with the same dynamic library. Since this doesn't match the # behavior of shared libraries on other platforms, we can use # them. ld_shlibs=no ;; beos*) if $LD --help 2>&1 | egrep ': supported targets:.* elf' > /dev/null; then allow_undefined_flag=unsupported # Joseph Beckenbach says some releases of gcc # support --undefined. This deserves some investigation. FIXME archive_cmds='$CC -nostart $libobjs $deplibs $linkopts ${wl}-soname $wl$soname -o $lib' else ld_shlibs=no fi ;; cygwin* | mingw*) # hardcode_libdir_flag_spec is actually meaningless, as there is # no search path for DLLs. hardcode_libdir_flag_spec='-L$libdir' allow_undefined_flag=unsupported always_export_symbols=yes # Extract the symbol export list from an `--export-all' def file, # then regenerate the def file from the symbol export list, so that # the compiled dll only exports the symbol export list. # Be careful not to strip the DATA tag left by newer dlltools. export_symbols_cmds='test -f $objdir/$soname-ltdll.c || sed -e "/^# \/\* ltdll\.c starts here \*\//,/^# \/\* ltdll.c ends here \*\// { s/^# //; p; }" -e d < $0 > $objdir/$soname-ltdll.c~ test -f $objdir/$soname-ltdll.$objext || (cd $objdir && $CC -c $soname-ltdll.c)~ $DLLTOOL --export-all --exclude-symbols DllMain@12,_cygwin_dll_entry@12,_cygwin_noncygwin_dll_entry@12 --output-def $objdir/$soname-def $objdir/$soname-ltdll.$objext $libobjs $convenience~ sed -e "1,/EXPORTS/d" -e "s/ @ [0-9]*//" -e "s/ *;.*$//" < $objdir/$soname-def > $export_symbols' # If DATA tags from a recent dlltool are present, honour them! archive_expsym_cmds='echo EXPORTS > $objdir/$soname-def~ _lt_hint=1; cat $export_symbols | while read symbol; do set dummy \$symbol; case \$# in 2) echo " \$2 @ \$_lt_hint ; " >> $objdir/$soname-def;; *) echo " \$2 @ \$_lt_hint \$3 ; " >> $objdir/$soname-def;; esac; _lt_hint=`expr 1 + \$_lt_hint`; done~ test -f $objdir/$soname-ltdll.c || sed -e "/^# \/\* ltdll\.c starts here \*\//,/^# \/\* ltdll.c ends here \*\// { s/^# //; p; }" -e d < $0 > $objdir/$soname-ltdll.c~ test -f $objdir/$soname-ltdll.$objext || (cd $objdir && $CC -c $soname-ltdll.c)~ $CC -Wl,--base-file,$objdir/$soname-base -Wl,--dll -nostartfiles -Wl,-e,__cygwin_dll_entry@12 -o $lib $objdir/$soname-ltdll.$objext $libobjs $deplibs $linkopts~ $DLLTOOL --as=$AS --dllname $soname --exclude-symbols DllMain@12,_cygwin_dll_entry@12,_cygwin_noncygwin_dll_entry@12 --def $objdir/$soname-def --base-file $objdir/$soname-base --output-exp $objdir/$soname-exp~ $CC -Wl,--base-file,$objdir/$soname-base $objdir/$soname-exp -Wl,--dll -nostartfiles -Wl,-e,__cygwin_dll_entry@12 -o $lib $objdir/$soname-ltdll.$objext $libobjs $deplibs $linkopts~ $DLLTOOL --as=$AS --dllname $soname --exclude-symbols DllMain@12,_cygwin_dll_entry@12,_cygwin_noncygwin_dll_entry@12 --def $objdir/$soname-def --base-file $objdir/$soname-base --output-exp $objdir/$soname-exp~ $CC $objdir/$soname-exp -Wl,--dll -nostartfiles -Wl,-e,__cygwin_dll_entry@12 -o $lib $objdir/$soname-ltdll.$objext $libobjs $deplibs $linkopts' old_archive_from_new_cmds='$DLLTOOL --as=$AS --dllname $soname --def $objdir/$soname-def --output-lib $objdir/$libname.a' ;; netbsd*) if echo __ELF__ | $CC -E - | grep __ELF__ >/dev/null; then archive_cmds='$CC -shared $libobjs $deplibs $linkopts ${wl}-soname $wl$soname -o $lib' archive_expsym_cmds='$CC -shared $libobjs $deplibs $linkopts ${wl}-soname $wl$soname ${wl}-retain-symbols-file $wl$export_symbols -o $lib' else archive_cmds='$LD -Bshareable $libobjs $deplibs $linkopts -o $lib' # can we support soname and/or expsyms with a.out? -oliva fi ;; solaris* | sysv5*) if $LD -v 2>&1 | egrep 'BFD 2\.8' > /dev/null; then ld_shlibs=no cat <&2 *** Warning: The releases 2.8.* of the GNU linker cannot reliably *** create shared libraries on Solaris systems. Therefore, libtool *** is disabling shared libraries support. We urge you to upgrade GNU *** binutils to release 2.9.1 or newer. Another option is to modify *** your PATH or compiler configuration so that the native linker is *** used, and then restart. EOF elif $LD --help 2>&1 | egrep ': supported targets:.* elf' > /dev/null; then archive_cmds='$CC -shared $libobjs $deplibs $linkopts ${wl}-soname $wl$soname -o $lib' archive_expsym_cmds='$CC -shared $libobjs $deplibs $linkopts ${wl}-soname $wl$soname ${wl}-retain-symbols-file $wl$export_symbols -o $lib' else ld_shlibs=no fi ;; sunos4*) archive_cmds='$LD -assert pure-text -Bshareable -o $lib $libobjs $deplibs $linkopts' wlarc= hardcode_direct=yes hardcode_shlibpath_var=no ;; *) if $LD --help 2>&1 | egrep ': supported targets:.* elf' > /dev/null; then archive_cmds='$CC -shared $libobjs $deplibs $linkopts ${wl}-soname $wl$soname -o $lib' archive_expsym_cmds='$CC -shared $libobjs $deplibs $linkopts ${wl}-soname $wl$soname ${wl}-retain-symbols-file $wl$export_symbols -o $lib' else ld_shlibs=no fi ;; esac if test "$ld_shlibs" = yes; then runpath_var=LD_RUN_PATH hardcode_libdir_flag_spec='${wl}--rpath ${wl}$libdir' export_dynamic_flag_spec='${wl}--export-dynamic' case $host_os in cygwin* | mingw*) # dlltool doesn't understand --whole-archive et. al. whole_archive_flag_spec= ;; *) # ancient GNU ld didn't support --whole-archive et. al. if $LD --help 2>&1 | egrep 'no-whole-archive' > /dev/null; then whole_archive_flag_spec="$wlarc"'--whole-archive$convenience '"$wlarc"'--no-whole-archive' else whole_archive_flag_spec= fi ;; esac fi else # PORTME fill in a description of your system's linker (not GNU ld) case "$host_os" in aix3*) allow_undefined_flag=unsupported always_export_symbols=yes archive_expsym_cmds='$LD -o $objdir/$soname $libobjs $deplibs $linkopts -bE:$export_symbols -T512 -H512 -bM:SRE~$AR cru $lib $objdir/$soname' # Note: this linker hardcodes the directories in LIBPATH if there # are no directories specified by -L. hardcode_minus_L=yes if test "$with_gcc" = yes && test -z "$link_static_flag"; then # Neither direct hardcoding nor static linking is supported with a # broken collect2. hardcode_direct=unsupported fi ;; aix4*) hardcode_libdir_flag_spec='${wl}-b ${wl}nolibpath ${wl}-b ${wl}libpath:$libdir:/usr/lib:/lib' hardcode_libdir_separator=':' if test "$with_gcc" = yes; then collect2name=`${CC} -print-prog-name=collect2` if test -f "$collect2name" && \ strings "$collect2name" | grep resolve_lib_name >/dev/null then # We have reworked collect2 hardcode_direct=yes else # We have old collect2 hardcode_direct=unsupported # It fails to find uninstalled libraries when the uninstalled # path is not listed in the libpath. Setting hardcode_minus_L # to unsupported forces relinking hardcode_minus_L=yes hardcode_libdir_flag_spec='-L$libdir' hardcode_libdir_separator= fi shared_flag='-shared' else shared_flag='${wl}-bM:SRE' hardcode_direct=yes fi allow_undefined_flag=' ${wl}-berok' archive_cmds="\$CC $shared_flag"' -o $objdir/$soname $libobjs $deplibs $linkopts ${wl}-bexpall ${wl}-bnoentry${allow_undefined_flag}' archive_expsym_cmds="\$CC $shared_flag"' -o $objdir/$soname $libobjs $deplibs $linkopts ${wl}-bE:$export_symbols ${wl}-bnoentry${allow_undefined_flag}' case "$host_os" in aix4.[01]|aix4.[01].*) # According to Greg Wooledge, -bexpall is only supported from AIX 4.2 on always_export_symbols=yes ;; esac ;; amigaos*) archive_cmds='$rm $objdir/a2ixlibrary.data~$echo "#define NAME $libname" > $objdir/a2ixlibrary.data~$echo "#define LIBRARY_ID 1" >> $objdir/a2ixlibrary.data~$echo "#define VERSION $major" >> $objdir/a2ixlibrary.data~$echo "#define REVISION $revision" >> $objdir/a2ixlibrary.data~$AR cru $lib $libobjs~$RANLIB $lib~(cd $objdir && a2ixlibrary -32)' hardcode_libdir_flag_spec='-L$libdir' hardcode_minus_L=yes # see comment about different semantics on the GNU ld section ld_shlibs=no ;; cygwin* | mingw*) # When not using gcc, we currently assume that we are using # Microsoft Visual C++. # hardcode_libdir_flag_spec is actually meaningless, as there is # no search path for DLLs. hardcode_libdir_flag_spec=' ' allow_undefined_flag=unsupported # Tell ltmain to make .lib files, not .a files. libext=lib # FIXME: Setting linknames here is a bad hack. archive_cmds='$CC -o $lib $libobjs $linkopts `echo "$deplibs" | sed -e '\''s/ -lc$//'\''` -link -dll~linknames=' # The linker will automatically build a .lib file if we build a DLL. old_archive_from_new_cmds='true' # FIXME: Should let the user specify the lib program. old_archive_cmds='lib /OUT:$oldlib$oldobjs' fix_srcfile_path='`cygpath -w $srcfile`' ;; freebsd1*) ld_shlibs=no ;; # FreeBSD 2.2.[012] allows us to include c++rt0.o to get C++ constructor # support. Future versions do this automatically, but an explicit c++rt0.o # does not break anything, and helps significantly (at the cost of a little # extra space). freebsd2.2*) archive_cmds='$LD -Bshareable -o $lib $libobjs $deplibs $linkopts /usr/lib/c++rt0.o' hardcode_libdir_flag_spec='-R$libdir' hardcode_direct=yes hardcode_shlibpath_var=no ;; # Unfortunately, older versions of FreeBSD 2 do not have this feature. freebsd2*) archive_cmds='$LD -Bshareable -o $lib $libobjs $deplibs $linkopts' hardcode_direct=yes hardcode_minus_L=yes hardcode_shlibpath_var=no ;; # FreeBSD 3 and greater uses gcc -shared to do shared libraries. freebsd*) archive_cmds='$CC -shared -o $lib $libobjs $deplibs $linkopts' hardcode_libdir_flag_spec='-R$libdir' hardcode_direct=yes hardcode_shlibpath_var=no ;; darwin* | rhapsody*) case "$host_os" in rhapsody* | darwin1.[012]) allow_undefined_flag='-undefined suppress' ;; *) # Darwin 1.3 on if test -z ${MACOSX_DEPLOYMENT_TARGET} ; then allow_undefined_flag='-flat_namespace -undefined suppress' else case ${MACOSX_DEPLOYMENT_TARGET} in 10.[012]) allow_undefined_flag='-flat_namespace -undefined suppress' ;; 10.*) allow_undefined_flag='-undefined dynamic_lookup' ;; esac fi ;; esac archive_cmds='$nonopt $(test .$module = .yes && echo -bundle || echo -dynamiclib) $allow_undefined_flag -o $lib $libobjs $deplibs $linkopts $(test .$module != .yes && echo -install_name $rpath/$soname $verstring)' # We need to add '_' to the symbols in $export_symbols first #archive_expsym_cmds="$archive_cmds"' && strip -s $export_symbols $lib' hardcode_direct=yes hardcode_shlibpath_var=no whole_archive_flag_spec='-all_load $convenience' ;; hpux9* | hpux10* | hpux11*) case "$host_os" in hpux9*) archive_cmds='$rm $objdir/$soname~$LD -b +b $install_libdir -o $objdir/$soname $libobjs $deplibs $linkopts~test $objdir/$soname = $lib || mv $objdir/$soname $lib' ;; *) archive_cmds='$LD -b +h $soname +b $install_libdir -o $lib $libobjs $deplibs $linkopts' ;; esac hardcode_libdir_flag_spec='${wl}+b ${wl}$libdir' hardcode_libdir_separator=: hardcode_direct=yes hardcode_minus_L=yes # Not in the search PATH, but as the default # location of the library. export_dynamic_flag_spec='${wl}-E' ;; irix5* | irix6*) if test "$with_gcc" = yes; then archive_cmds='$CC -shared $libobjs $deplibs $linkopts ${wl}-soname ${wl}$soname `test -n "$verstring" && echo ${wl}-set_version ${wl}$verstring` ${wl}-update_registry ${wl}${objdir}/so_locations -o $lib' else archive_cmds='$LD -shared $libobjs $deplibs $linkopts -soname $soname `test -n "$verstring" && echo -set_version $verstring` -update_registry ${objdir}/so_locations -o $lib' fi hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' hardcode_libdir_separator=: ;; netbsd*) if echo __ELF__ | $CC -E - | grep __ELF__ >/dev/null; then archive_cmds='$LD -Bshareable -o $lib $libobjs $deplibs $linkopts' # a.out else archive_cmds='$LD -shared -o $lib $libobjs $deplibs $linkopts' # ELF fi hardcode_libdir_flag_spec='${wl}-R$libdir' hardcode_direct=yes hardcode_shlibpath_var=no ;; openbsd*) archive_cmds='$LD -Bshareable -o $lib $libobjs $deplibs $linkopts' hardcode_libdir_flag_spec='-R$libdir' hardcode_direct=yes hardcode_shlibpath_var=no ;; os2*) hardcode_libdir_flag_spec='-L$libdir' hardcode_minus_L=yes allow_undefined_flag=unsupported archive_cmds='$echo "LIBRARY $libname INITINSTANCE" > $objdir/$libname.def~$echo "DESCRIPTION \"$libname\"" >> $objdir/$libname.def~$echo DATA >> $objdir/$libname.def~$echo " SINGLE NONSHARED" >> $objdir/$libname.def~$echo EXPORTS >> $objdir/$libname.def~emxexp $libobjs >> $objdir/$libname.def~$CC -Zdll -Zcrtdll -o $lib $libobjs $deplibs $linkopts $objdir/$libname.def' old_archive_from_new_cmds='emximp -o $objdir/$libname.a $objdir/$libname.def' ;; osf3*) if test "$with_gcc" = yes; then allow_undefined_flag=' ${wl}-expect_unresolved ${wl}\*' archive_cmds='$CC -shared${allow_undefined_flag} $libobjs $deplibs $linkopts ${wl}-soname ${wl}$soname `test -n "$verstring" && echo ${wl}-set_version ${wl}$verstring` ${wl}-update_registry ${wl}${objdir}/so_locations -o $lib' else allow_undefined_flag=' -expect_unresolved \*' archive_cmds='$LD -shared${allow_undefined_flag} $libobjs $deplibs $linkopts -soname $soname `test -n "$verstring" && echo -set_version $verstring` -update_registry ${objdir}/so_locations -o $lib' fi hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' hardcode_libdir_separator=: ;; osf4* | osf5*) # As osf3* with the addition of the -msym flag if test "$with_gcc" = yes; then allow_undefined_flag=' ${wl}-expect_unresolved ${wl}\*' archive_cmds='$CC -shared${allow_undefined_flag} $libobjs $deplibs $linkopts ${wl}-msym ${wl}-soname ${wl}$soname `test -n "$verstring" && echo ${wl}-set_version ${wl}$verstring` ${wl}-update_registry ${wl}${objdir}/so_locations -o $lib' else allow_undefined_flag=' -expect_unresolved \*' archive_cmds='$LD -shared${allow_undefined_flag} $libobjs $deplibs $linkopts -msym -soname $soname `test -n "$verstring" && echo -set_version $verstring` -update_registry ${objdir}/so_locations -o $lib' fi hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' hardcode_libdir_separator=: ;; sco3.2v5*) archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linkopts' hardcode_shlibpath_var=no runpath_var=LD_RUN_PATH hardcode_runpath_var=yes ;; solaris*) no_undefined_flag=' -z text' # $CC -shared without GNU ld will not create a library from C++ # object files and a static libstdc++, better avoid it by now archive_cmds='$LD -G${allow_undefined_flag} -h $soname -o $lib $libobjs $deplibs $linkopts' archive_expsym_cmds='$echo "{ global:" > $lib.exp~cat $export_symbols | sed -e "s/\(.*\)/\1;/" >> $lib.exp~$echo "local: *; };" >> $lib.exp~ $LD -G${allow_undefined_flag} -M $lib.exp -h $soname -o $lib $libobjs $deplibs $linkopts~$rm $lib.exp' hardcode_libdir_flag_spec='-R$libdir' hardcode_shlibpath_var=no case "$host_os" in solaris2.[0-5] | solaris2.[0-5].*) ;; *) # Supported since Solaris 2.6 (maybe 2.5.1?) whole_archive_flag_spec='-z allextract$convenience -z defaultextract' ;; esac ;; sunos4*) archive_cmds='$LD -assert pure-text -Bstatic -o $lib $libobjs $deplibs $linkopts' hardcode_libdir_flag_spec='-L$libdir' hardcode_direct=yes hardcode_minus_L=yes hardcode_shlibpath_var=no ;; sysv4) if test "x$host_vendor" = xsequent; then # Use $CC to link under sequent, because it throws in some extra .o # files that make .init and .fini sections work. archive_cmds='$CC -G ${wl}-h $soname -o $lib $libobjs $deplibs $linkopts' else archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linkopts' fi runpath_var='LD_RUN_PATH' hardcode_shlibpath_var=no hardcode_direct=no #Motorola manual says yes, but my tests say they lie ;; sysv4.3*) archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linkopts' hardcode_shlibpath_var=no export_dynamic_flag_spec='-Bexport' ;; sysv5*) no_undefined_flag=' -z text' # $CC -shared without GNU ld will not create a library from C++ # object files and a static libstdc++, better avoid it by now archive_cmds='$LD -G${allow_undefined_flag} -h $soname -o $lib $libobjs $deplibs $linkopts' archive_expsym_cmds='$echo "{ global:" > $lib.exp~cat $export_symbols | sed -e "s/\(.*\)/\1;/" >> $lib.exp~$echo "local: *; };" >> $lib.exp~ $LD -G${allow_undefined_flag} -M $lib.exp -h $soname -o $lib $libobjs $deplibs $linkopts~$rm $lib.exp' hardcode_libdir_flag_spec= hardcode_shlibpath_var=no runpath_var='LD_RUN_PATH' ;; uts4*) archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linkopts' hardcode_libdir_flag_spec='-L$libdir' hardcode_shlibpath_var=no ;; dgux*) archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linkopts' hardcode_libdir_flag_spec='-L$libdir' hardcode_shlibpath_var=no ;; sysv4*MP*) if test -d /usr/nec; then archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linkopts' hardcode_shlibpath_var=no runpath_var=LD_RUN_PATH hardcode_runpath_var=yes ld_shlibs=yes fi ;; sysv4.2uw2*) archive_cmds='$LD -G -o $lib $libobjs $deplibs $linkopts' hardcode_direct=yes hardcode_minus_L=no hardcode_shlibpath_var=no hardcode_runpath_var=yes runpath_var=LD_RUN_PATH ;; unixware7*) archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linkopts' runpath_var='LD_RUN_PATH' hardcode_shlibpath_var=no ;; *) ld_shlibs=no ;; esac fi echo "$ac_t$ld_shlibs" 1>&6 test "$ld_shlibs" = no && can_build_shared=no if test -z "$NM"; then echo $ac_n "checking for BSD-compatible nm... $ac_c" 1>&6 case "$NM" in [\\/]* | [A-Za-z]:[\\/]*) ;; # Let the user override the test with a path. *) IFS="${IFS= }"; ac_save_ifs="$IFS"; IFS="${IFS}${PATH_SEPARATOR}" for ac_dir in $PATH /usr/ucb /usr/ccs/bin /bin; do test -z "$ac_dir" && ac_dir=. if test -f $ac_dir/nm || test -f $ac_dir/nm$ac_exeext; then # Check to see if the nm accepts a BSD-compat flag. # Adding the `sed 1q' prevents false positives on HP-UX, which says: # nm: unknown option "B" ignored if ($ac_dir/nm -B /dev/null 2>&1 | sed '1q'; exit 0) | egrep /dev/null >/dev/null; then NM="$ac_dir/nm -B" break elif ($ac_dir/nm -p /dev/null 2>&1 | sed '1q'; exit 0) | egrep /dev/null >/dev/null; then NM="$ac_dir/nm -p" break else NM=${NM="$ac_dir/nm"} # keep the first match, but continue # so that we can try to find one that supports BSD flags fi fi done IFS="$ac_save_ifs" test -z "$NM" && NM=nm ;; esac echo "$ac_t$NM" 1>&6 fi # Check for command to grab the raw symbol name followed by C symbol from nm. echo $ac_n "checking command to parse $NM output... $ac_c" 1>&6 # These are sane defaults that work on at least a few old systems. # [They come from Ultrix. What could be older than Ultrix?!! ;)] # Character class describing NM global symbol codes. symcode='[BCDEGRST]' # Regexp to match symbols that can be accessed directly from C. sympat='\([_A-Za-z][_A-Za-z0-9]*\)' # Transform the above into a raw symbol and a C symbol. symxfrm='\1 \2\3 \3' # Transform an extracted symbol line into a proper C declaration global_symbol_to_cdecl="sed -n -e 's/^. .* \(.*\)$/extern char \1;/p'" # Define system-specific variables. case "$host_os" in aix*) symcode='[BCDT]' ;; cygwin* | mingw*) symcode='[ABCDGISTW]' ;; hpux*) # Its linker distinguishes data from code symbols global_symbol_to_cdecl="sed -n -e 's/^T .* \(.*\)$/extern char \1();/p' -e 's/^. .* \(.*\)$/extern char \1;/p'" ;; irix*) symcode='[BCDEGRST]' ;; solaris*) symcode='[BDT]' ;; sysv4) symcode='[DFNSTU]' ;; esac # If we're using GNU nm, then use its standard symbol codes. if $NM -V 2>&1 | egrep '(GNU|with BFD)' > /dev/null; then symcode='[ABCDGISTW]' fi # Try without a prefix undercore, then with it. for ac_symprfx in "" "_"; do # Write the raw and C identifiers. global_symbol_pipe="sed -n -e 's/^.*[ ]\($symcode\)[ ][ ]*\($ac_symprfx\)$sympat$/$symxfrm/p'" # Check to see that the pipe works correctly. pipe_works=no $rm conftest* cat > conftest.c <&5 if { (eval echo $progname:1681: \"$ac_compile\") 1>&5; (eval $ac_compile) 2>&5; } && test -s conftest.$objext; then # Now try to grab the symbols. nlist=conftest.nm if { echo "$progname:1684: eval \"$NM conftest.$objext | $global_symbol_pipe > $nlist\"" >&5; eval "$NM conftest.$objext | $global_symbol_pipe > $nlist 2>&5"; } && test -s "$nlist"; then # Try sorting and uniquifying the output. if sort "$nlist" | uniq > "$nlist"T; then mv -f "$nlist"T "$nlist" else rm -f "$nlist"T fi # Make sure that we snagged all the symbols we need. if egrep ' nm_test_var$' "$nlist" >/dev/null; then if egrep ' nm_test_func$' "$nlist" >/dev/null; then cat < conftest.c #ifdef __cplusplus extern "C" { #endif EOF # Now generate the symbol file. eval "$global_symbol_to_cdecl"' < "$nlist" >> conftest.c' cat <> conftest.c #if defined (__STDC__) && __STDC__ # define lt_ptr_t void * #else # define lt_ptr_t char * # define const #endif /* The mapping between symbol names and symbols. */ const struct { const char *name; lt_ptr_t address; } lt_preloaded_symbols[] = { EOF sed 's/^. \(.*\) \(.*\)$/ {"\2", (lt_ptr_t) \&\2},/' < "$nlist" >> conftest.c cat <<\EOF >> conftest.c {0, (lt_ptr_t) 0} }; #ifdef __cplusplus } #endif EOF # Now try linking the two files. mv conftest.$objext conftstm.$objext save_LIBS="$LIBS" save_CFLAGS="$CFLAGS" LIBS="conftstm.$objext" CFLAGS="$CFLAGS$no_builtin_flag" if { (eval echo $progname:1736: \"$ac_link\") 1>&5; (eval $ac_link) 2>&5; } && test -s conftest; then pipe_works=yes else echo "$progname: failed program was:" >&5 cat conftest.c >&5 fi LIBS="$save_LIBS" else echo "cannot find nm_test_func in $nlist" >&5 fi else echo "cannot find nm_test_var in $nlist" >&5 fi else echo "cannot run $global_symbol_pipe" >&5 fi else echo "$progname: failed program was:" >&5 cat conftest.c >&5 fi $rm conftest* conftst* # Do not use the global_symbol_pipe unless it works. if test "$pipe_works" = yes; then break else global_symbol_pipe= fi done if test "$pipe_works" = yes; then echo "${ac_t}ok" 1>&6 else echo "${ac_t}failed" 1>&6 fi if test -z "$global_symbol_pipe"; then global_symbol_to_cdecl= fi # Check hardcoding attributes. echo $ac_n "checking how to hardcode library paths into programs... $ac_c" 1>&6 hardcode_action= if test -n "$hardcode_libdir_flag_spec" || \ test -n "$runpath_var"; then # We can hardcode non-existant directories. if test "$hardcode_direct" != no && # If the only mechanism to avoid hardcoding is shlibpath_var, we # have to relink, otherwise we might link with an installed library # when we should be linking with a yet-to-be-installed one ## test "$hardcode_shlibpath_var" != no && test "$hardcode_minus_L" != no; then # Linking always hardcodes the temporary library directory. hardcode_action=relink else # We can link without hardcoding, and we can hardcode nonexisting dirs. hardcode_action=immediate fi else # We cannot hardcode anything, or else we can only hardcode existing # directories. hardcode_action=unsupported fi echo "$ac_t$hardcode_action" 1>&6 reload_flag= reload_cmds='$LD$reload_flag -o $output$reload_objs' echo $ac_n "checking for $LD option to reload object files... $ac_c" 1>&6 # PORTME Some linkers may need a different reload flag. reload_flag='-r' echo "$ac_t$reload_flag" 1>&6 test -n "$reload_flag" && reload_flag=" $reload_flag" # PORTME Fill in your ld.so characteristics library_names_spec= libname_spec='lib$name' soname_spec= postinstall_cmds= postuninstall_cmds= finish_cmds= finish_eval= shlibpath_var= shlibpath_overrides_runpath=unknown version_type=none dynamic_linker="$host_os ld.so" sys_lib_dlsearch_path_spec="/lib /usr/lib" sys_lib_search_path_spec="/lib /usr/lib /usr/local/lib" file_magic_cmd= file_magic_test_file= deplibs_check_method='unknown' # Need to set the preceding variable on all platforms that support # interlibrary dependencies. # 'none' -- dependencies not supported. # `unknown' -- same as none, but documents that we really don't know. # 'pass_all' -- all dependencies passed with no checks. # 'test_compile' -- check by making test program. # 'file_magic [regex]' -- check by looking for files in library path # which responds to the $file_magic_cmd with a given egrep regex. # If you have `file' or equivalent on your system and you're not sure # whether `pass_all' will *always* work, you probably want this one. echo $ac_n "checking dynamic linker characteristics... $ac_c" 1>&6 case "$host_os" in aix3*) version_type=linux library_names_spec='${libname}${release}.so$versuffix $libname.a' shlibpath_var=LIBPATH # AIX has no versioning support, so we append a major version to the name. soname_spec='${libname}${release}.so$major' ;; aix4*) version_type=linux # AIX has no versioning support, so currently we can not hardcode correct # soname into executable. Probably we can add versioning support to # collect2, so additional links can be useful in future. # We preserve .a as extension for shared libraries though AIX4.2 # and later linker supports .so library_names_spec='${libname}${release}.so$versuffix ${libname}${release}.so$major $libname.a' shlibpath_var=LIBPATH deplibs_check_method=pass_all ;; amigaos*) library_names_spec='$libname.ixlibrary $libname.a' # Create ${libname}_ixlibrary.a entries in /sys/libs. finish_eval='for lib in `ls $libdir/*.ixlibrary 2>/dev/null`; do libname=`$echo "X$lib" | $Xsed -e '\''s%^.*/\([^/]*\)\.ixlibrary$%\1%'\''`; test $rm /sys/libs/${libname}_ixlibrary.a; $show "(cd /sys/libs && $LN_S $lib ${libname}_ixlibrary.a)"; (cd /sys/libs && $LN_S $lib ${libname}_ixlibrary.a) || exit 1; done' ;; beos*) library_names_spec='${libname}.so' dynamic_linker="$host_os ld.so" shlibpath_var=LIBRARY_PATH deplibs_check_method=pass_all lt_cv_dlopen="load_add_on" lt_cv_dlopen_libs= lt_cv_dlopen_self=yes ;; bsdi4*) version_type=linux need_version=no library_names_spec='${libname}${release}.so$versuffix ${libname}${release}.so$major $libname.so' soname_spec='${libname}${release}.so$major' finish_cmds='PATH="\$PATH:/sbin" ldconfig $libdir' shlibpath_var=LD_LIBRARY_PATH deplibs_check_method='file_magic ELF [0-9][0-9]*-bit [ML]SB (shared object|dynamic lib)' file_magic_cmd=/usr/bin/file file_magic_test_file=/shlib/libc.so sys_lib_search_path_spec="/shlib /usr/lib /usr/X11/lib /usr/contrib/lib /lib /usr/local/lib" sys_lib_dlsearch_path_spec="/shlib /usr/lib /usr/local/lib" export_dynamic_flag_spec=-rdynamic # the default ld.so.conf also contains /usr/contrib/lib and # /usr/X11R6/lib (/usr/X11 is a link to /usr/X11R6), but let us allow # libtool to hard-code these into programs ;; cygwin* | mingw*) version_type=windows need_version=no need_lib_prefix=no if test "$with_gcc" = yes; then library_names_spec='${libname}`echo ${release} | sed -e 's/[.]/-/g'`${versuffix}.dll $libname.a' else library_names_spec='${libname}`echo ${release} | sed -e 's/[.]/-/g'`${versuffix}.dll $libname.lib' fi dynamic_linker='Win32 ld.exe' deplibs_check_method='file_magic file format pei*-i386(.*architecture: i386)?' file_magic_cmd='${OBJDUMP} -f' # FIXME: first we should search . and the directory the executable is in shlibpath_var=PATH lt_cv_dlopen="LoadLibrary" lt_cv_dlopen_libs= ;; freebsd1*) dynamic_linker=no ;; freebsd*) objformat=`test -x /usr/bin/objformat && /usr/bin/objformat || echo aout` version_type=freebsd-$objformat case "$version_type" in freebsd-elf*) deplibs_check_method='file_magic ELF [0-9][0-9]*-bit [LM]SB shared object' file_magic_cmd=/usr/bin/file file_magic_test_file=`echo /usr/lib/libc.so*` library_names_spec='${libname}${release}.so$versuffix ${libname}${release}.so $libname.so' need_version=no need_lib_prefix=no ;; freebsd-*) deplibs_check_method=unknown library_names_spec='${libname}${release}.so$versuffix $libname.so$versuffix' need_version=yes ;; esac shlibpath_var=LD_LIBRARY_PATH case "$host_os" in freebsd2* | freebsd3.[01]* | freebsdelf3.[01]*) shlibpath_overrides_runpath=yes ;; *) # from 3.2 on shlibpath_overrides_runpath=no ;; esac ;; darwin* | rhapsody*) dynamic_linker="$host_os dyld" version_type=darwin need_lib_prefix=no need_version=no deplibs_check_method='file_magic Mach-O dynamically linked shared library' file_magic_cmd='/usr/bin/file -L' case "$host_os" in rhapsody* | darwin1.[012]) file_magic_test_file='/System/Library/Frameworks/System.framework/System' ;; *) # Darwin 1.3 on file_magic_test_file='/usr/lib/libSystem.dylib' ;; esac library_names_spec='${libname}${release}${versuffix}.$(test .$module = .yes && echo so || echo dylib) ${libname}${release}${major}.$(test .$module = .yes && echo so || echo dylib) ${libname}.$(test .$module = .yes && echo so || echo dylib)' soname_spec='${libname}${release}${major}.$(test .$module = .yes && echo so || echo dylib)' shlibpath_overrides_runpath=yes shlibpath_var=DYLD_LIBRARY_PATH ;; gnu*) version_type=linux need_lib_prefix=no need_version=no library_names_spec='${libname}${release}.so$versuffix ${libname}${release}.so${major} ${libname}.so' soname_spec='${libname}${release}.so$major' shlibpath_var=LD_LIBRARY_PATH ;; hpux9* | hpux10* | hpux11*) # Give a soname corresponding to the major version so that dld.sl refuses to # link against other versions. dynamic_linker="$host_os dld.sl" version_type=sunos need_lib_prefix=no need_version=no shlibpath_var=SHLIB_PATH shlibpath_overrides_runpath=no # +s is required to enable SHLIB_PATH library_names_spec='${libname}${release}.sl$versuffix ${libname}${release}.sl$major $libname.sl' soname_spec='${libname}${release}.sl$major' # HP-UX runs *really* slowly unless shared libraries are mode 555. postinstall_cmds='chmod 555 $lib' case "$host_os" in hpux10.20*) # TODO: Does this work for hpux-11 too? deplibs_check_method='file_magic (s[0-9][0-9][0-9]|PA-RISC[0-9].[0-9]) shared library' file_magic_cmd=/usr/bin/file file_magic_test_file=/usr/lib/libc.sl ;; esac ;; irix5* | irix6*) version_type=irix need_lib_prefix=no need_version=no soname_spec='${libname}${release}.so.$major' library_names_spec='${libname}${release}.so.$versuffix ${libname}${release}.so.$major ${libname}${release}.so $libname.so' case "$host_os" in irix5*) libsuff= shlibsuff= # this will be overridden with pass_all, but let us keep it just in case deplibs_check_method="file_magic ELF 32-bit MSB dynamic lib MIPS - version 1" ;; *) case "$LD" in # libtool.m4 will add one of these switches to LD *-32|*"-32 ") libsuff= shlibsuff= libmagic=32-bit;; *-n32|*"-n32 ") libsuff=32 shlibsuff=N32 libmagic=N32;; *-64|*"-64 ") libsuff=64 shlibsuff=64 libmagic=64-bit;; *) libsuff= shlibsuff= libmagic=never-match;; esac ;; esac shlibpath_var=LD_LIBRARY${shlibsuff}_PATH shlibpath_overrides_runpath=no sys_lib_search_path_spec="/usr/lib${libsuff} /lib${libsuff} /usr/local/lib${libsuff}" sys_lib_dlsearch_path_spec="/usr/lib${libsuff} /lib${libsuff}" file_magic_cmd=/usr/bin/file file_magic_test_file=`echo /lib${libsuff}/libc.so*` deplibs_check_method='pass_all' ;; # No shared lib support for Linux oldld, aout, or coff. linux-gnuoldld* | linux-gnuaout* | linux-gnucoff*) dynamic_linker=no ;; # This must be Linux ELF. linux-gnu*) version_type=linux need_lib_prefix=no need_version=no library_names_spec='${libname}${release}.so$versuffix ${libname}${release}.so$major $libname.so' soname_spec='${libname}${release}.so$major' finish_cmds='PATH="\$PATH:/sbin" ldconfig -n $libdir' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=no deplibs_check_method=pass_all if test -f /lib/ld.so.1; then dynamic_linker='GNU ld.so' else # Only the GNU ld.so supports shared libraries on MkLinux. case "$host_cpu" in powerpc*) dynamic_linker=no ;; *) dynamic_linker='Linux ld.so' ;; esac fi ;; netbsd*) version_type=sunos if echo __ELF__ | $CC -E - | grep __ELF__ >/dev/null; then library_names_spec='${libname}${release}.so$versuffix ${libname}.so$versuffix' finish_cmds='PATH="\$PATH:/sbin" ldconfig -m $libdir' dynamic_linker='NetBSD (a.out) ld.so' else library_names_spec='${libname}${release}.so$versuffix ${libname}${release}.so$major ${libname}${release}.so ${libname}.so' soname_spec='${libname}${release}.so$major' dynamic_linker='NetBSD ld.elf_so' fi shlibpath_var=LD_LIBRARY_PATH ;; openbsd*) version_type=sunos if test "$with_gnu_ld" = yes; then need_lib_prefix=no need_version=no fi library_names_spec='${libname}${release}.so$versuffix ${libname}.so$versuffix' finish_cmds='PATH="\$PATH:/sbin" ldconfig -m $libdir' shlibpath_var=LD_LIBRARY_PATH ;; os2*) libname_spec='$name' need_lib_prefix=no library_names_spec='$libname.dll $libname.a' dynamic_linker='OS/2 ld.exe' shlibpath_var=LIBPATH ;; osf3* | osf4* | osf5*) version_type=osf need_version=no soname_spec='${libname}${release}.so' library_names_spec='${libname}${release}.so$versuffix ${libname}${release}.so $libname.so' shlibpath_var=LD_LIBRARY_PATH # this will be overridden with pass_all, but let us keep it just in case deplibs_check_method='file_magic COFF format alpha shared library' file_magic_cmd=/usr/bin/file file_magic_test_file=/shlib/libc.so deplibs_check_method='pass_all' sys_lib_search_path_spec="/usr/shlib /usr/ccs/lib /usr/lib/cmplrs/cc /usr/lib /usr/local/lib /var/shlib" sys_lib_dlsearch_path_spec="$sys_lib_search_path_spec" ;; sco3.2v5*) version_type=osf soname_spec='${libname}${release}.so$major' library_names_spec='${libname}${release}.so$versuffix ${libname}${release}.so$major $libname.so' shlibpath_var=LD_LIBRARY_PATH ;; solaris*) version_type=linux need_lib_prefix=no need_version=no library_names_spec='${libname}${release}.so$versuffix ${libname}${release}.so$major $libname.so' soname_spec='${libname}${release}.so$major' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=yes # ldd complains unless libraries are executable postinstall_cmds='chmod +x $lib' deplibs_check_method="file_magic ELF [0-9][0-9]-bit [LM]SB dynamic lib" file_magic_cmd=/usr/bin/file file_magic_test_file=/lib/libc.so ;; sunos4*) version_type=sunos library_names_spec='${libname}${release}.so$versuffix ${libname}.so$versuffix' finish_cmds='PATH="\$PATH:/usr/etc" ldconfig $libdir' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=yes if test "$with_gnu_ld" = yes; then need_lib_prefix=no fi need_version=yes ;; sysv4 | sysv4.2uw2* | sysv4.3* | sysv5*) version_type=linux library_names_spec='${libname}${release}.so$versuffix ${libname}${release}.so$major $libname.so' soname_spec='${libname}${release}.so$major' shlibpath_var=LD_LIBRARY_PATH case "$host_vendor" in sequent) file_magic_cmd='/bin/file' deplibs_check_method='file_magic ELF [0-9][0-9]*-bit [LM]SB (shared object|dynamic lib )' ;; ncr) deplibs_check_method='pass_all' ;; motorola) need_lib_prefix=no need_version=no shlibpath_overrides_runpath=no sys_lib_search_path_spec='/lib /usr/lib /usr/ccs/lib' deplibs_check_method='file_magic ELF [0-9][0-9]*-bit [ML]SB (shared object|dynamic lib) M[0-9][0-9]* Version [0-9]' file_magic_cmd=/usr/bin/file file_magic_test_file=`echo /usr/lib/libc.so*` ;; esac ;; uts4*) version_type=linux library_names_spec='${libname}${release}.so$versuffix ${libname}${release}.so$major $libname.so' soname_spec='${libname}${release}.so$major' shlibpath_var=LD_LIBRARY_PATH ;; dgux*) version_type=linux need_lib_prefix=no need_version=no library_names_spec='${libname}${release}.so$versuffix ${libname}${release}.so$major $libname.so' soname_spec='${libname}${release}.so$major' shlibpath_var=LD_LIBRARY_PATH ;; sysv4*MP*) if test -d /usr/nec ;then version_type=linux library_names_spec='$libname.so.$versuffix $libname.so.$major $libname.so' soname_spec='$libname.so.$major' shlibpath_var=LD_LIBRARY_PATH fi ;; *) dynamic_linker=no ;; esac echo "$ac_t$dynamic_linker" 1>&6 test "$dynamic_linker" = no && can_build_shared=no # Report the final consequences. echo "checking if libtool supports shared libraries... $can_build_shared" 1>&6 # Only try to build win32 dlls if AC_LIBTOOL_WIN32_DLL was used in # configure.in, otherwise build static only libraries. case "$host_os" in cygwin* | mingw* | os2*) if test x$can_build_shared = xyes; then test x$enable_win32_dll = xno && can_build_shared=no echo "checking if package supports dlls... $can_build_shared" 1>&6 fi ;; esac if test -n "$file_magic_test_file" && test -n "$file_magic_cmd"; then case "$deplibs_check_method" in "file_magic "*) file_magic_regex="`expr \"$deplibs_check_method\" : \"file_magic \(.*\)\"`" if eval $file_magic_cmd \$file_magic_test_file 2> /dev/null | egrep "$file_magic_regex" > /dev/null; then : else cat <&2 *** Warning: the command libtool uses to detect shared libraries, *** $file_magic_cmd, produces output that libtool cannot recognize. *** The result is that libtool may fail to recognize shared libraries *** as such. This will affect the creation of libtool libraries that *** depend on shared libraries, but programs linked with such libtool *** libraries will work regardless of this problem. Nevertheless, you *** may want to report the problem to your system manager and/or to *** bug-libtool@gnu.org EOF fi ;; esac fi echo $ac_n "checking whether to build shared libraries... $ac_c" 1>&6 test "$can_build_shared" = "no" && enable_shared=no # On AIX, shared libraries and static libraries use the same namespace, and # are all built from PIC. case "$host_os" in aix3*) test "$enable_shared" = yes && enable_static=no if test -n "$RANLIB"; then archive_cmds="$archive_cmds~\$RANLIB \$lib" postinstall_cmds='$RANLIB $lib' fi ;; aix4*) test "$enable_shared" = yes && enable_static=no ;; esac echo "$ac_t$enable_shared" 1>&6 # Make sure either enable_shared or enable_static is yes. test "$enable_shared" = yes || enable_static=yes echo "checking whether to build static libraries... $enable_static" 1>&6 if test "$hardcode_action" = relink; then # Fast installation is not supported enable_fast_install=no elif test "$shlibpath_overrides_runpath" = yes || test "$enable_shared" = no; then # Fast installation is not necessary enable_fast_install=needless fi echo $ac_n "checking for objdir... $ac_c" 1>&6 rm -f .libs 2>/dev/null mkdir .libs 2>/dev/null if test -d .libs; then objdir=.libs else # MS-DOS does not allow filenames that begin with a dot. objdir=_libs fi rmdir .libs 2>/dev/null echo "$ac_t$objdir" 1>&6 if test "x$enable_dlopen" != xyes; then enable_dlopen=unknown enable_dlopen_self=unknown enable_dlopen_self_static=unknown else if eval "test \"`echo '$''{'lt_cv_dlopen'+set}'`\" != set"; then lt_cv_dlopen=no lt_cv_dlopen_libs= echo $ac_n "checking for dlopen in -ldl""... $ac_c" 1>&6 echo "$progname:2288: checking for dlopen in -ldl" >&5 ac_lib_var=`echo dl'_'dlopen | sed 'y%./+-%__p_%'` if eval "test \"`echo '$''{'ac_cv_lib_$ac_lib_var'+set}'`\" = set"; then echo $ac_n "(cached) $ac_c" 1>&6 else ac_save_LIBS="$LIBS" LIBS="-ldl $LIBS" cat > conftest.$ac_ext <&5; (eval $ac_link) 2>&5; } && test -s conftest${ac_exeext}; then rm -rf conftest* eval "ac_cv_lib_$ac_lib_var=yes" else echo "$progname: failed program was:" >&5 cat conftest.$ac_ext >&5 rm -rf conftest* eval "ac_cv_lib_$ac_lib_var=no" fi rm -f conftest* LIBS="$ac_save_LIBS" fi if eval "test \"`echo '$ac_cv_lib_'$ac_lib_var`\" = yes"; then echo "$ac_t""yes" 1>&6 lt_cv_dlopen="dlopen" lt_cv_dlopen_libs="-ldl" else echo "$ac_t""no" 1>&6 echo $ac_n "checking for dlopen""... $ac_c" 1>&6 echo "$progname:2328: checking for dlopen" >&5 if eval "test \"`echo '$''{'ac_cv_func_dlopen'+set}'`\" = set"; then echo $ac_n "(cached) $ac_c" 1>&6 else cat > conftest.$ac_ext < /* Override any gcc2 internal prototype to avoid an error. */ /* We use char because int might match the return type of a gcc2 builtin and then its argument prototype would still apply. */ #ifdef __cplusplus extern "C" #endif char dlopen(); int main() { /* The GNU C library defines this for functions which it implements to always fail with ENOSYS. Some functions are actually named something starting with __ and the normal name is an alias. */ #if defined (__stub_dlopen) || defined (__stub___dlopen) choke me #else dlopen(); #endif ; return 0; } EOF if { (eval echo $progname:2358: \"$ac_link\") 1>&5; (eval $ac_link) 2>&5; } && test -s conftest${ac_exeext}; then rm -rf conftest* eval "ac_cv_func_dlopen=yes" else echo "$progname: failed program was:" >&5 cat conftest.$ac_ext >&5 rm -rf conftest* eval "ac_cv_func_dlopen=no" fi rm -f conftest* fi if eval "test \"`echo '$ac_cv_func_'dlopen`\" = yes"; then echo "$ac_t""yes" 1>&6 lt_cv_dlopen="dlopen" else echo "$ac_t""no" 1>&6 echo $ac_n "checking for dld_link in -ldld""... $ac_c" 1>&6 echo "$progname:2375: checking for dld_link in -ldld" >&5 ac_lib_var=`echo dld'_'dld_link | sed 'y%./+-%__p_%'` if eval "test \"`echo '$''{'ac_cv_lib_$ac_lib_var'+set}'`\" = set"; then echo $ac_n "(cached) $ac_c" 1>&6 else ac_save_LIBS="$LIBS" LIBS="-ldld $LIBS" cat > conftest.$ac_ext <&5; (eval $ac_link) 2>&5; } && test -s conftest${ac_exeext}; then rm -rf conftest* eval "ac_cv_lib_$ac_lib_var=yes" else echo "$progname: failed program was:" >&5 cat conftest.$ac_ext >&5 rm -rf conftest* eval "ac_cv_lib_$ac_lib_var=no" fi rm -f conftest* LIBS="$ac_save_LIBS" fi if eval "test \"`echo '$ac_cv_lib_'$ac_lib_var`\" = yes"; then echo "$ac_t""yes" 1>&6 lt_cv_dlopen="dld_link" lt_cv_dlopen_libs="-ldld" else echo "$ac_t""no" 1>&6 echo $ac_n "checking for shl_load""... $ac_c" 1>&6 echo "$progname:2415: checking for shl_load" >&5 if eval "test \"`echo '$''{'ac_cv_func_shl_load'+set}'`\" = set"; then echo $ac_n "(cached) $ac_c" 1>&6 else cat > conftest.$ac_ext < /* Override any gcc2 internal prototype to avoid an error. */ /* We use char because int might match the return type of a gcc2 builtin and then its argument prototype would still apply. */ #ifdef __cplusplus extern "C" #endif char shl_load(); int main() { /* The GNU C library defines this for functions which it implements to always fail with ENOSYS. Some functions are actually named something starting with __ and the normal name is an alias. */ #if defined (__stub_shl_load) || defined (__stub___shl_load) choke me #else shl_load(); #endif ; return 0; } EOF if { (eval echo $progname:2445: \"$ac_link\") 1>&5; (eval $ac_link) 2>&5; } && test -s conftest${ac_exeext}; then rm -rf conftest* eval "ac_cv_func_shl_load=yes" else echo "$progname: failed program was:" >&5 cat conftest.$ac_ext >&5 rm -rf conftest* eval "ac_cv_func_shl_load=no" fi rm -f conftest* fi if eval "test \"`echo '$ac_cv_func_'shl_load`\" = yes"; then echo "$ac_t""yes" 1>&6 lt_cv_dlopen="shl_load" else echo "$ac_t""no" 1>&6 echo $ac_n "checking for shl_load in -ldld""... $ac_c" 1>&6 echo "$progname:2463: checking for shl_load in -ldld" >&5 ac_lib_var=`echo dld'_'shl_load | sed 'y%./+-%__p_%'` if eval "test \"`echo '$''{'ac_cv_lib_$ac_lib_var'+set}'`\" = set"; then echo $ac_n "(cached) $ac_c" 1>&6 else ac_save_LIBS="$LIBS" LIBS="-ldld $LIBS" cat > conftest.$ac_ext <&5; (eval $ac_link) 2>&5; } && test -s conftest${ac_exeext}; then rm -rf conftest* eval "ac_cv_lib_$ac_lib_var=yes" else echo "$progname: failed program was:" >&5 cat conftest.$ac_ext >&5 rm -rf conftest* eval "ac_cv_lib_$ac_lib_var=no" fi rm -f conftest* LIBS="$ac_save_LIBS" fi if eval "test \"`echo '$ac_cv_lib_'$ac_lib_var`\" = yes"; then echo "$ac_t""yes" 1>&6 lt_cv_dlopen="shl_load" lt_cv_dlopen_libs="-ldld" else echo "$ac_t""no" 1>&6 fi fi fi fi fi fi if test "x$lt_cv_dlopen" != xno; then enable_dlopen=yes fi case "$lt_cv_dlopen" in dlopen) for ac_hdr in dlfcn.h; do ac_safe=`echo "$ac_hdr" | sed 'y%./+-%__p_%'` echo $ac_n "checking for $ac_hdr""... $ac_c" 1>&6 echo "$progname:2528: checking for $ac_hdr" >&5 if eval "test \"`echo '$''{'ac_cv_header_$ac_safe'+set}'`\" = set"; then echo $ac_n "(cached) $ac_c" 1>&6 else cat > conftest.$ac_ext < int fnord = 0; EOF ac_try="$ac_compile >/dev/null 2>conftest.out" { (eval echo $progname:2538: \"$ac_try\") 1>&5; (eval $ac_try) 2>&5; } ac_err=`grep -v '^ *+' conftest.out | grep -v "^conftest.${ac_ext}\$"` if test -z "$ac_err"; then rm -rf conftest* eval "ac_cv_header_$ac_safe=yes" else echo "$ac_err" >&5 echo "$progname: failed program was:" >&5 cat conftest.$ac_ext >&5 rm -rf conftest* eval "ac_cv_header_$ac_safe=no" fi rm -f conftest* fi if eval "test \"`echo '$ac_cv_header_'$ac_safe`\" = yes"; then echo "$ac_t""yes" 1>&6 else echo "$ac_t""no" 1>&6 fi done if test "x$ac_cv_header_dlfcn_h" = xyes; then CPPFLAGS="$CPPFLAGS -DHAVE_DLFCN_H" fi eval LDFLAGS=\"\$LDFLAGS $export_dynamic_flag_spec\" LIBS="$lt_cv_dlopen_libs $LIBS" echo $ac_n "checking whether a program can dlopen itself""... $ac_c" 1>&6 echo "$progname:2566: checking whether a program can dlopen itself" >&5 if test "${lt_cv_dlopen_self+set}" = set; then echo $ac_n "(cached) $ac_c" 1>&6 else if test "$cross_compiling" = yes; then lt_cv_dlopen_self=cross else cat > conftest.c < #endif #include #ifdef RTLD_GLOBAL # define LTDL_GLOBAL RTLD_GLOBAL #else # ifdef DL_GLOBAL # define LTDL_GLOBAL DL_GLOBAL # else # define LTDL_GLOBAL 0 # endif #endif /* We may have to define LTDL_LAZY_OR_NOW in the command line if we find out it does not work in some platform. */ #ifndef LTDL_LAZY_OR_NOW # ifdef RTLD_LAZY # define LTDL_LAZY_OR_NOW RTLD_LAZY # else # ifdef DL_LAZY # define LTDL_LAZY_OR_NOW DL_LAZY # else # ifdef RTLD_NOW # define LTDL_LAZY_OR_NOW RTLD_NOW # else # ifdef DL_NOW # define LTDL_LAZY_OR_NOW DL_NOW # else # define LTDL_LAZY_OR_NOW 0 # endif # endif # endif # endif #endif fnord() { int i=42;} main() { void *self, *ptr1, *ptr2; self=dlopen(0,LTDL_GLOBAL|LTDL_LAZY_OR_NOW); if(self) { ptr1=dlsym(self,"fnord"); ptr2=dlsym(self,"_fnord"); if(ptr1 || ptr2) { dlclose(self); exit(0); } } exit(1); } EOF if { (eval echo $progname:2620: \"$ac_link\") 1>&5; (eval $ac_link) 2>&5; } && test -s conftest && (./conftest; exit) 2>/dev/null then lt_cv_dlopen_self=yes else echo "$progname: failed program was:" >&5 cat conftest.$ac_ext >&5 rm -fr conftest* lt_cv_dlopen_self=no fi rm -fr conftest* fi fi echo "$ac_t""$lt_cv_dlopen_self" 1>&6 if test "$lt_cv_dlopen_self" = yes; then LDFLAGS="$LDFLAGS $link_static_flag" echo $ac_n "checking whether a statically linked program can dlopen itself""... $ac_c" 1>&6 echo "$progname:2639: checking whether a statically linked program can dlopen itself" >&5 if test "${lt_cv_dlopen_self_static+set}" = set; then echo $ac_n "(cached) $ac_c" 1>&6 else if test "$cross_compiling" = yes; then lt_cv_dlopen_self_static=cross else cat > conftest.c < #endif #include #ifdef RTLD_GLOBAL # define LTDL_GLOBAL RTLD_GLOBAL #else # ifdef DL_GLOBAL # define LTDL_GLOBAL DL_GLOBAL # else # define LTDL_GLOBAL 0 # endif #endif /* We may have to define LTDL_LAZY_OR_NOW in the command line if we find out it does not work in some platform. */ #ifndef LTDL_LAZY_OR_NOW # ifdef RTLD_LAZY # define LTDL_LAZY_OR_NOW RTLD_LAZY # else # ifdef DL_LAZY # define LTDL_LAZY_OR_NOW DL_LAZY # else # ifdef RTLD_NOW # define LTDL_LAZY_OR_NOW RTLD_NOW # else # ifdef DL_NOW # define LTDL_LAZY_OR_NOW DL_NOW # else # define LTDL_LAZY_OR_NOW 0 # endif # endif # endif # endif #endif fnord() { int i=42;} main() { void *self, *ptr1, *ptr2; self=dlopen(0,LTDL_GLOBAL|LTDL_LAZY_OR_NOW); if(self) { ptr1=dlsym(self,"fnord"); ptr2=dlsym(self,"_fnord"); if(ptr1 || ptr2) { dlclose(self); exit(0); } } exit(1); } EOF if { (eval echo $progname:2693: \"$ac_link\") 1>&5; (eval $ac_link) 2>&5; } && test -s conftest && (./conftest; exit) 2>/dev/null then lt_cv_dlopen_self_static=yes else echo "$progname: failed program was:" >&5 cat conftest.$ac_ext >&5 rm -fr conftest* lt_cv_dlopen_self_static=no fi rm -fr conftest* fi fi echo "$ac_t""$lt_cv_dlopen_self_static" 1>&6 fi ;; esac case "$lt_cv_dlopen_self" in yes|no) enable_dlopen_self=$lt_cv_dlopen_self ;; *) enable_dlopen_self=unknown ;; esac case "$lt_cv_dlopen_self_static" in yes|no) enable_dlopen_self_static=$lt_cv_dlopen_self_static ;; *) enable_dlopen_self_static=unknown ;; esac fi # Copy echo and quote the copy, instead of the original, because it is # used later. ltecho="$echo" if test "X$ltecho" = "X$CONFIG_SHELL $0 --fallback-echo"; then ltecho="$CONFIG_SHELL \$0 --fallback-echo" fi LTSHELL="$SHELL" LTCONFIG_VERSION="$VERSION" # Only quote variables if we're using ltmain.sh. case "$ltmain" in *.sh) # Now quote all the things that may contain metacharacters. for var in ltecho old_CC old_CFLAGS old_CPPFLAGS \ old_LD old_LDFLAGS old_LIBS \ old_NM old_RANLIB old_LN_S old_DLLTOOL old_OBJDUMP old_AS \ AR CC LD LN_S NM LTSHELL LTCONFIG_VERSION \ reload_flag reload_cmds wl \ pic_flag link_static_flag no_builtin_flag export_dynamic_flag_spec \ thread_safe_flag_spec whole_archive_flag_spec libname_spec \ library_names_spec soname_spec \ RANLIB old_archive_cmds old_archive_from_new_cmds old_postinstall_cmds \ old_postuninstall_cmds archive_cmds archive_expsym_cmds postinstall_cmds postuninstall_cmds \ file_magic_cmd export_symbols_cmds deplibs_check_method allow_undefined_flag no_undefined_flag \ finish_cmds finish_eval global_symbol_pipe global_symbol_to_cdecl \ hardcode_libdir_flag_spec hardcode_libdir_separator \ sys_lib_search_path_spec sys_lib_dlsearch_path_spec \ compiler_c_o compiler_o_lo need_locks exclude_expsyms include_expsyms; do case "$var" in reload_cmds | old_archive_cmds | old_archive_from_new_cmds | \ old_postinstall_cmds | old_postuninstall_cmds | \ export_symbols_cmds | archive_cmds | archive_expsym_cmds | \ postinstall_cmds | postuninstall_cmds | \ finish_cmds | sys_lib_search_path_spec | sys_lib_dlsearch_path_spec) # Double-quote double-evaled strings. eval "$var=\\\"\`\$echo \"X\$$var\" | \$Xsed -e \"\$double_quote_subst\" -e \"\$sed_quote_subst\" -e \"\$delay_variable_subst\"\`\\\"" ;; *) eval "$var=\\\"\`\$echo \"X\$$var\" | \$Xsed -e \"\$sed_quote_subst\"\`\\\"" ;; esac done case "$ltecho" in *'\$0 --fallback-echo"') ltecho=`$echo "X$ltecho" | $Xsed -e 's/\\\\\\\$0 --fallback-echo"$/$0 --fallback-echo"/'` ;; esac trap "$rm \"$ofile\"; exit 1" 1 2 15 echo "creating $ofile" $rm "$ofile" cat < "$ofile" #! $SHELL # `$echo "$ofile" | sed 's%^.*/%%'` - Provide generalized library-building support services. # Generated automatically by $PROGRAM (GNU $PACKAGE $VERSION$TIMESTAMP) # NOTE: Changes made to this file will be lost: look at ltconfig or ltmain.sh. # # Copyright (C) 1996-1999 Free Software Foundation, Inc. # Originally by Gordon Matzigkeit , 1996 # # This program is free software; you can redistribute it and/or modify # it under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2 of the License, or # (at your option) any later version. # # This program is distributed in the hope that it will be useful, but # WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # General Public License for more details. # # You should have received a copy of the GNU General Public License # along with this program; if not, write to the Free Software # Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA. # # As a special exception to the GNU General Public License, if you # distribute this file as part of a program that contains a # configuration script generated by Autoconf, you may include it under # the same distribution terms that you use for the rest of that program. # Sed that helps us avoid accidentally triggering echo(1) options like -n. Xsed="sed -e s/^X//" # The HP-UX ksh and POSIX shell print the target directory to stdout # if CDPATH is set. if test "X\${CDPATH+set}" = Xset; then CDPATH=:; export CDPATH; fi ### BEGIN LIBTOOL CONFIG EOF cfgfile="$ofile" ;; *) # Double-quote the variables that need it (for aesthetics). for var in old_CC old_CFLAGS old_CPPFLAGS \ old_LD old_LDFLAGS old_LIBS \ old_NM old_RANLIB old_LN_S old_DLLTOOL old_OBJDUMP old_AS; do eval "$var=\\\"\$var\\\"" done # Just create a config file. cfgfile="$ofile.cfg" trap "$rm \"$cfgfile\"; exit 1" 1 2 15 echo "creating $cfgfile" $rm "$cfgfile" cat < "$cfgfile" # `$echo "$cfgfile" | sed 's%^.*/%%'` - Libtool configuration file. # Generated automatically by $PROGRAM (GNU $PACKAGE $VERSION$TIMESTAMP) EOF ;; esac cat <> "$cfgfile" # Libtool was configured as follows, on host `(hostname || uname -n) 2>/dev/null | sed 1q`: # # CC=$old_CC CFLAGS=$old_CFLAGS CPPFLAGS=$old_CPPFLAGS \\ # LD=$old_LD LDFLAGS=$old_LDFLAGS LIBS=$old_LIBS \\ # NM=$old_NM RANLIB=$old_RANLIB LN_S=$old_LN_S \\ # DLLTOOL=$old_DLLTOOL OBJDUMP=$old_OBJDUMP AS=$old_AS \\ # $0$ltconfig_args # # Compiler and other test output produced by $progname, useful for # debugging $progname, is in ./config.log if it exists. # The version of $progname that generated this script. LTCONFIG_VERSION=$LTCONFIG_VERSION # Shell to use when invoking shell scripts. SHELL=$LTSHELL # Whether or not to build shared libraries. build_libtool_libs=$enable_shared # Whether or not to build static libraries. build_old_libs=$enable_static # Whether or not to optimize for fast installation. fast_install=$enable_fast_install # The host system. host_alias=$host_alias host=$host # An echo program that does not interpret backslashes. echo=$ltecho # The archiver. AR=$AR # The default C compiler. CC=$CC # The linker used to build libraries. LD=$LD # Whether we need hard or soft links. LN_S=$LN_S # A BSD-compatible nm program. NM=$NM # Used on cygwin: DLL creation program. DLLTOOL="$DLLTOOL" # Used on cygwin: object dumper. OBJDUMP="$OBJDUMP" # Used on cygwin: assembler. AS="$AS" # The name of the directory that contains temporary libtool files. objdir=$objdir # How to create reloadable object files. reload_flag=$reload_flag reload_cmds=$reload_cmds # How to pass a linker flag through the compiler. wl=$wl # Object file suffix (normally "o"). objext="$objext" # Old archive suffix (normally "a"). libext="$libext" # Executable file suffix (normally ""). exeext="$exeext" # Additional compiler flags for building library objects. pic_flag=$pic_flag # Does compiler simultaneously support -c and -o options? compiler_c_o=$compiler_c_o # Can we write directly to a .lo ? compiler_o_lo=$compiler_o_lo # Must we lock files when doing compilation ? need_locks=$need_locks # Do we need the lib prefix for modules? need_lib_prefix=$need_lib_prefix # Do we need a version for libraries? need_version=$need_version # Whether dlopen is supported. dlopen=$enable_dlopen # Whether dlopen of programs is supported. dlopen_self=$enable_dlopen_self # Whether dlopen of statically linked programs is supported. dlopen_self_static=$enable_dlopen_self_static # Compiler flag to prevent dynamic linking. link_static_flag=$link_static_flag # Compiler flag to turn off builtin functions. no_builtin_flag=$no_builtin_flag # Compiler flag to allow reflexive dlopens. export_dynamic_flag_spec=$export_dynamic_flag_spec # Compiler flag to generate shared objects directly from archives. whole_archive_flag_spec=$whole_archive_flag_spec # Compiler flag to generate thread-safe objects. thread_safe_flag_spec=$thread_safe_flag_spec # Library versioning type. version_type=$version_type # Format of library name prefix. libname_spec=$libname_spec # List of archive names. First name is the real one, the rest are links. # The last name is the one that the linker finds with -lNAME. library_names_spec=$library_names_spec # The coded name of the library, if different from the real name. soname_spec=$soname_spec # Commands used to build and install an old-style archive. RANLIB=$RANLIB old_archive_cmds=$old_archive_cmds old_postinstall_cmds=$old_postinstall_cmds old_postuninstall_cmds=$old_postuninstall_cmds # Create an old-style archive from a shared archive. old_archive_from_new_cmds=$old_archive_from_new_cmds # Commands used to build and install a shared archive. archive_cmds=$archive_cmds archive_expsym_cmds=$archive_expsym_cmds postinstall_cmds=$postinstall_cmds postuninstall_cmds=$postuninstall_cmds # Method to check whether dependent libraries are shared objects. deplibs_check_method=$deplibs_check_method # Command to use when deplibs_check_method == file_magic. file_magic_cmd=$file_magic_cmd # Flag that allows shared libraries with undefined symbols to be built. allow_undefined_flag=$allow_undefined_flag # Flag that forces no undefined symbols. no_undefined_flag=$no_undefined_flag # Commands used to finish a libtool library installation in a directory. finish_cmds=$finish_cmds # Same as above, but a single script fragment to be evaled but not shown. finish_eval=$finish_eval # Take the output of nm and produce a listing of raw symbols and C names. global_symbol_pipe=$global_symbol_pipe # Transform the output of nm in a proper C declaration global_symbol_to_cdecl=$global_symbol_to_cdecl # This is the shared library runtime path variable. runpath_var=$runpath_var # This is the shared library path variable. shlibpath_var=$shlibpath_var # Is shlibpath searched before the hard-coded library search path? shlibpath_overrides_runpath=$shlibpath_overrides_runpath # How to hardcode a shared library path into an executable. hardcode_action=$hardcode_action # Flag to hardcode \$libdir into a binary during linking. # This must work even if \$libdir does not exist. hardcode_libdir_flag_spec=$hardcode_libdir_flag_spec # Whether we need a single -rpath flag with a separated argument. hardcode_libdir_separator=$hardcode_libdir_separator # Set to yes if using DIR/libNAME.so during linking hardcodes DIR into the # resulting binary. hardcode_direct=$hardcode_direct # Set to yes if using the -LDIR flag during linking hardcodes DIR into the # resulting binary. hardcode_minus_L=$hardcode_minus_L # Set to yes if using SHLIBPATH_VAR=DIR during linking hardcodes DIR into # the resulting binary. hardcode_shlibpath_var=$hardcode_shlibpath_var # Compile-time system search path for libraries sys_lib_search_path_spec=$sys_lib_search_path_spec # Run-time system search path for libraries sys_lib_dlsearch_path_spec=$sys_lib_dlsearch_path_spec # Fix the shell variable \$srcfile for the compiler. fix_srcfile_path="$fix_srcfile_path" # Set to yes if exported symbols are required. always_export_symbols=$always_export_symbols # The commands to list exported symbols. export_symbols_cmds=$export_symbols_cmds # Symbols that should not be listed in the preloaded symbols. exclude_expsyms=$exclude_expsyms # Symbols that must always be exported. include_expsyms=$include_expsyms EOF case "$ltmain" in *.sh) echo '### END LIBTOOL CONFIG' >> "$ofile" echo >> "$ofile" case "$host_os" in aix3*) cat <<\EOF >> "$ofile" # AIX sometimes has problems with the GCC collect2 program. For some # reason, if we set the COLLECT_NAMES environment variable, the problems # vanish in a puff of smoke. if test "X${COLLECT_NAMES+set}" != Xset; then COLLECT_NAMES= export COLLECT_NAMES fi EOF ;; esac # Append the ltmain.sh script. sed '$q' "$ltmain" >> "$ofile" || (rm -f "$ofile"; exit 1) # We use sed instead of cat because bash on DJGPP gets confused if # if finds mixed CR/LF and LF-only lines. Since sed operates in # text mode, it properly converts lines to CR/LF. This bash problem # is reportedly fixed, but why not run on old versions too? chmod +x "$ofile" ;; *) # Compile the libtool program. echo "FIXME: would compile $ltmain" ;; esac test -n "$cache_file" || exit 0 # AC_CACHE_SAVE trap '' 1 2 15 cat > confcache <<\EOF # This file is a shell script that caches the results of configure # tests run on this system so they can be shared between configure # scripts and configure runs. It is not useful on other systems. # If it contains results you don't want to keep, you may remove or edit it. # # By default, configure uses ./config.cache as the cache file, # creating it if it does not exist already. You can give configure # the --cache-file=FILE option to use a different cache file; that is # what configure does when it calls configure scripts in # subdirectories, so they share the cache. # Giving --cache-file=/dev/null disables caching, for debugging configure. # config.status only pays attention to the cache file if you give it the # --recheck option to rerun configure. # EOF # The following way of writing the cache mishandles newlines in values, # but we know of no workaround that is simple, portable, and efficient. # So, don't put newlines in cache variables' values. # Ultrix sh set writes to stderr and can't be redirected directly, # and sets the high bit in the cache file unless we assign to the vars. (set) 2>&1 | case `(ac_space=' '; set | grep ac_space) 2>&1` in *ac_space=\ *) # `set' does not quote correctly, so add quotes (double-quote substitution # turns \\\\ into \\, and sed turns \\ into \). sed -n \ -e "s/'/'\\\\''/g" \ -e "s/^\\([a-zA-Z0-9_]*_cv_[a-zA-Z0-9_]*\\)=\\(.*\\)/\\1=\${\\1='\\2'}/p" ;; *) # `set' quotes correctly as required by POSIX, so do not add quotes. sed -n -e 's/^\([a-zA-Z0-9_]*_cv_[a-zA-Z0-9_]*\)=\(.*\)/\1=${\1=\2}/p' ;; esac >> confcache if cmp -s $cache_file confcache; then : else if test -w $cache_file; then echo "updating cache $cache_file" cat confcache > $cache_file else echo "not updating unwritable cache $cache_file" fi fi rm -f confcache exit 0 # Local Variables: # mode:shell-script # sh-indentation:2 # End: ./CBFlib-0.9.2.2/libtool/.undosymlinks0000755000076500007650000001021311603702120015776 0ustar yayayaya#!/bin/sh ###################################################################### # # # .undosymlinks for CBFlib/libtool directory # # # # # # Version 0.8.0 20 Jul 2008 # # # # Paul Ellis and # # Herbert J. Bernstein (yaya@bernstein-plus-sons.com) # # # # (C) Copyright 2006 - 2008 Herbert J. Bernstein # # # ###################################################################### ###################################################################### # # # YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL # # # # ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS # # OF THE LGPL # # # ###################################################################### ########################### GPL NOTICES ############################## # # # This program is free software; you can redistribute it and/or # # modify it under the terms of the GNU General Public License as # # published by the Free Software Foundation; either version 2 of # # (the License, or (at your option) any later version. # # # # This program is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # # GNU General Public License for more details. # # # # You should have received a copy of the GNU General Public License # # along with this program; if not, write to the Free Software # # Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA # # 02111-1307 USA # # # ###################################################################### ######################### LGPL NOTICES ############################### # # # This library is free software; you can redistribute it and/or # # modify it under the terms of the GNU Lesser General Public # # License as published by the Free Software Foundation; either # # version 2.1 of the License, or (at your option) any later version. # # # # This library is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # # Lesser General Public License for more details. # # # # You should have received a copy of the GNU Lesser General Public # # License along with this library; if not, write to the Free # # Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, # # MA 02110-1301 USA # # # ###################################################################### # Usage ./.undosymlinks for file in * do if [ -d "$file" ] ; then if [ -e "$file/.undosymlinks" ] ; then (cd "$file"; sh -c "./.undosymlinks") fi fi done ./CBFlib-0.9.2.2/libtool/build_libtool.sh0000755000076500007650000000004111603702120016413 0ustar yayayaya#!/bin/sh ./ltconfig ./ltmain.sh ./CBFlib-0.9.2.2/libtool/.symlinks0000755000076500007650000001056211603702120015117 0ustar yayayaya#!/bin/sh ###################################################################### # # # .symlinks for CBFlib/libtool directory # # # # originally a csh script by H. J. Bernstein # # converted to sh by J. Wright, 12 Jun 2007 # # # # Version 0.8.0 20 Jul 2008 # # # # Paul Ellis and # # Herbert J. Bernstein (yaya@bernstein-plus-sons.com) # # # # (C) Copyright 2006 - 2008 Herbert J. Bernstein # # # ###################################################################### ###################################################################### # # # YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL # # # # ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS # # OF THE LGPL # # # ###################################################################### ########################### GPL NOTICES ############################## # # # This program is free software; you can redistribute it and/or # # modify it under the terms of the GNU General Public License as # # published by the Free Software Foundation; either version 2 of # # (the License, or (at your option) any later version. # # # # This program is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # # GNU General Public License for more details. # # # # You should have received a copy of the GNU General Public License # # along with this program; if not, write to the Free Software # # Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA # # 02111-1307 USA # # # ###################################################################### ######################### LGPL NOTICES ############################### # # # This library is free software; you can redistribute it and/or # # modify it under the terms of the GNU Lesser General Public # # License as published by the Free Software Foundation; either # # version 2.1 of the License, or (at your option) any later version. # # # # This library is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # # Lesser General Public License for more details. # # # # You should have received a copy of the GNU Lesser General Public # # License along with this library; if not, write to the Free # # Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, # # MA 02110-1301 USA # # # ###################################################################### # Usage ./.symlinks [--use_cp] if [ ${1:-NOARG} = "--use_cp" ] ; then LN="cp -p" else LN="ln -s" fi chmod 755 *.sh for file in * do if [ -d "$file" ] ; then if [ -e "$file/.symlinks" ] ; then (cd "$file"; sh -c "./.symlinks $1") fi fi done ./CBFlib-0.9.2.2/index.html0000777000076500007650000000000011603751102015413 2README.htmlustar yayayaya./CBFlib-0.9.2.2/Makefile_LINUX_gcc420000644000076500007650000020020211603702122015171 0ustar yayayaya ###################################################################### # Makefile - command file for make to create CBFlib # # # # Version 0.9.2 12 Feb 2011 # # # # Paul Ellis and # # Herbert J. Bernstein (yaya@bernstein-plus-sons.com) # # # # (C) Copyright 2006 - 2011 Herbert J. Bernstein # # # ###################################################################### ###################################################################### # # # YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL # # # # ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS # # OF THE LGPL # # # ###################################################################### ########################### GPL NOTICES ############################## # # # This program is free software; you can redistribute it and/or # # modify it under the terms of the GNU General Public License as # # published by the Free Software Foundation; either version 2 of # # (the License, or (at your option) any later version. # # # # This program is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # # GNU General Public License for more details. # # # # You should have received a copy of the GNU General Public License # # along with this program; if not, write to the Free Software # # Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA # # 02111-1307 USA # # # ###################################################################### ######################### LGPL NOTICES ############################### # # # This library is free software; you can redistribute it and/or # # modify it under the terms of the GNU Lesser General Public # # License as published by the Free Software Foundation; either # # version 2.1 of the License, or (at your option) any later version. # # # # This library is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # # Lesser General Public License for more details. # # # # You should have received a copy of the GNU Lesser General Public # # License along with this library; if not, write to the Free # # Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, # # MA 02110-1301 USA # # # ###################################################################### ###################################################################### # # # Stanford University Notices # # for the CBFlib software package that incorporates SLAC software # # on which copyright is disclaimed # # # # This software # # ------------- # # The term "this software", as used in these Notices, refers to # # those portions of the software package CBFlib that were created by # # employees of the Stanford Linear Accelerator Center, Stanford # # University. # # # # Stanford disclaimer of copyright # # -------------------------------- # # Stanford University, owner of the copyright, hereby disclaims its # # copyright and all other rights in this software. Hence, anyone # # may freely use it for any purpose without restriction. # # # # Acknowledgement of sponsorship # # ------------------------------ # # This software was produced by the Stanford Linear Accelerator # # Center, Stanford University, under Contract DE-AC03-76SFO0515 with # # the Department of Energy. # # # # Government disclaimer of liability # # ---------------------------------- # # Neither the United States nor the United States Department of # # Energy, nor any of their employees, makes any warranty, express or # # implied, or assumes any legal liability or responsibility for the # # accuracy, completeness, or usefulness of any data, apparatus, # # product, or process disclosed, or represents that its use would # # not infringe privately owned rights. # # # # Stanford disclaimer of liability # # -------------------------------- # # Stanford University makes no representations or warranties, # # express or implied, nor assumes any liability for the use of this # # software. # # # # Maintenance of notices # # ---------------------- # # In the interest of clarity regarding the origin and status of this # # software, this and all the preceding Stanford University notices # # are to remain affixed to any copy or derivative of this software # # made or distributed by the recipient and are to be affixed to any # # copy of software made or distributed by the recipient that # # contains a copy or derivative of this software. # # # # Based on SLAC Software Notices, Set 4 # # OTT.002a, 2004 FEB 03 # ###################################################################### ###################################################################### # NOTICE # # Creative endeavors depend on the lively exchange of ideas. There # # are laws and customs which establish rights and responsibilities # # for authors and the users of what authors create. This notice # # is not intended to prevent you from using the software and # # documents in this package, but to ensure that there are no # # misunderstandings about terms and conditions of such use. # # # # Please read the following notice carefully. If you do not # # understand any portion of this notice, please seek appropriate # # professional legal advice before making use of the software and # # documents included in this software package. In addition to # # whatever other steps you may be obliged to take to respect the # # intellectual property rights of the various parties involved, if # # you do make use of the software and documents in this package, # # please give credit where credit is due by citing this package, # # its authors and the URL or other source from which you obtained # # it, or equivalent primary references in the literature with the # # same authors. # # # # Some of the software and documents included within this software # # package are the intellectual property of various parties, and # # placement in this package does not in any way imply that any # # such rights have in any way been waived or diminished. # # # # With respect to any software or documents for which a copyright # # exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. # # # # Even though the authors of the various documents and software # # found here have made a good faith effort to ensure that the # # documents are correct and that the software performs according # # to its documentation, and we would greatly appreciate hearing of # # any problems you may encounter, the programs and documents any # # files created by the programs are provided **AS IS** without any * # warranty as to correctness, merchantability or fitness for any # # particular or general use. # # # # THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF # # PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE # # PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS # # OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE # # PROGRAMS OR DOCUMENTS. # ###################################################################### ###################################################################### # # # The IUCr Policy # # for the Protection and the Promotion of the STAR File and # # CIF Standards for Exchanging and Archiving Electronic Data # # # # Overview # # # # The Crystallographic Information File (CIF)[1] is a standard for # # information interchange promulgated by the International Union of # # Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the # # recommended method for submitting publications to Acta # # Crystallographica Section C and reports of crystal structure # # determinations to other sections of Acta Crystallographica # # and many other journals. The syntax of a CIF is a subset of the # # more general STAR File[2] format. The CIF and STAR File approaches # # are used increasingly in the structural sciences for data exchange # # and archiving, and are having a significant influence on these # # activities in other fields. # # # # Statement of intent # # # # The IUCr's interest in the STAR File is as a general data # # interchange standard for science, and its interest in the CIF, # # a conformant derivative of the STAR File, is as a concise data # # exchange and archival standard for crystallography and structural # # science. # # # # Protection of the standards # # # # To protect the STAR File and the CIF as standards for # # interchanging and archiving electronic data, the IUCr, on behalf # # of the scientific community, # # # # # holds the copyrights on the standards themselves, * # # # # owns the associated trademarks and service marks, and * # # # # holds a patent on the STAR File. * # # # These intellectual property rights relate solely to the # # interchange formats, not to the data contained therein, nor to # # the software used in the generation, access or manipulation of # # the data. # # # # Promotion of the standards # # # # The sole requirement that the IUCr, in its protective role, # # imposes on software purporting to process STAR File or CIF data # # is that the following conditions be met prior to sale or # # distribution. # # # # # Software claiming to read files written to either the STAR * # File or the CIF standard must be able to extract the pertinent # # data from a file conformant to the STAR File syntax, or the CIF # # syntax, respectively. # # # # # Software claiming to write files in either the STAR File, or * # the CIF, standard must produce files that are conformant to the # # STAR File syntax, or the CIF syntax, respectively. # # # # # Software claiming to read definitions from a specific data * # dictionary approved by the IUCr must be able to extract any # # pertinent definition which is conformant to the dictionary # # definition language (DDL)[3] associated with that dictionary. # # # # The IUCr, through its Committee on CIF Standards, will assist # # any developer to verify that software meets these conformance # # conditions. # # # # Glossary of terms # # # # [1] CIF: is a data file conformant to the file syntax defined # # at http://www.iucr.org/iucr-top/cif/spec/index.html # # # # [2] STAR File: is a data file conformant to the file syntax # # defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html # # # # [3] DDL: is a language used in a data dictionary to define data # # items in terms of "attributes". Dictionaries currently approved # # by the IUCr, and the DDL versions used to construct these # # dictionaries, are listed at # # http://www.iucr.org/iucr-top/cif/spec/ddl/index.html # # # # Last modified: 30 September 2000 # # # # IUCr Policy Copyright (C) 2000 International Union of # # Crystallography # ###################################################################### # Version string VERSION = 0.9.2 # # Comment out the next line if scratch test files sould be retain # CLEANTESTS = yes # # Definition to get a version of tifflib to support tiff2cbf # TIFF = tiff-3.9.4-rev-6Feb11 TIFFPREFIX = $(PWD) # # Definitions to get a stable version of regex # REGEX = regex-20090805 REGEXDIR = /usr/lib REGEXDEP = # Program to use to retrieve a URL DOWNLOAD = wget # Flag to control symlinks versus copying SLFLAGS = --use_ln # # Program to use to pack shars # SHAR = /usr/bin/shar #SHAR = /usr/local/bin/gshar # # Program to use to create archives # AR = /usr/bin/ar # # Program to use to add an index to an archive # RANLIB = /usr/bin/ranlib # # Program to use to decompress a data file # DECOMPRESS = /usr/bin/bunzip2 # # Program to use to compress a data file # COMPRESS = /usr/bin/bzip2 # # Program to use to generate a signature # SIGNATURE = /usr/bin/openssl dgst -md5 # # Extension for compressed data file (with period) # CEXT = .bz2 # # Extension for signatures of files # SEXT = .md5 # call to time a command #TIME = #TIME = time # # Program to display differences between files # DIFF = diff -u -b # # Program to generate wrapper classes for Python # PYSWIG = swig -python # # Program to generate wrapper classes for Java # JSWIG = swig -java # # Program to generate LaTex and HTML program documentation # NUWEB = nuweb # # Compiler for Java # JAVAC = javac # # Java archiver for compiled classes # JAR = jar # # Java SDK root directory # ifeq ($(JDKDIR),) JDKDIR = /usr/lib/java endif ifneq ($(CBF_DONT_USE_LONG_LONG),) NOLLFLAG = -DCBF_DONT_USE_LONG_LONG else NOLLFLAG = endif # # PYCBF definitions # PYCBFEXT = so PYCBFBOPT = SETUP_PY = setup.py # # Set the compiler and flags # ######################################################### # # Appropriate compiler definitions for Linux # with gcc version 4.2 # ######################################################### CC = gcc C++ = g++ CFLAGS = -g -O2 -Wall -D_USE_XOPEN_EXTENDED -fno-strict-aliasing F90C = gfortran F90FLAGS = -g -fno-range-check F90LDFLAGS = SOCFLAGS = -fPIC SOLDFLAGS = -shared -Wl,-rpath,$(INSTALLDIR)/lib JAVAINCLUDES = -I$(JDKDIR)/include -I$(JDKDIR)/include/linux LDPREFIX = LD_LIBRARY_PATH=$(SOLIB) EXTRALIBS = -lm M4FLAGS = -Dfcb_bytes_in_rec=131072 TIME = time ifneq ($(NOFORTRAN),) F90C = endif # # Directories # ROOT = . LIB = $(ROOT)/lib SOLIB = $(ROOT)/solib JCBF = $(ROOT)/jcbf JAVADIR = $(ROOT)/java BIN = $(ROOT)/bin SRC = $(ROOT)/src INCLUDE = $(ROOT)/include M4 = $(ROOT)/m4 PYCBF = $(ROOT)/pycbf EXAMPLES = $(ROOT)/examples DECTRIS_EXAMPLES = $(EXAMPLES)/dectris_cbf_template_test DOC = $(ROOT)/doc GRAPHICS = $(ROOT)/html_graphics DATADIRI = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Input DATADIRO = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Output DATADIRS = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only INSTALLDIR = $(HOME) # # URLs from which to retrieve the data directories # DATAURLBASE = http://downloads.sf.net/cbflib/ DATAURLI = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Input.tar.gz DATAURLO = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Output.tar.gz DATAURLS = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz # # URLs from which to retrieve needed external package snapshots # REGEXURL = http://downloads.sf.net/cbflib/$(REGEX).tar.gz TIFFURL = http://downloads.sf.net/cbflib/$(TIFF).tar.gz # # Include directories # INCLUDES = -I$(INCLUDE) -I$(SRC) ###################################################################### # You should not need to make modifications below this line # ###################################################################### # # Suffixes of files to be used or built # .SUFFIXES: .c .o .f90 .m4 .m4.f90: m4 -P $(M4FLAGS) $< > $@ ifneq ($(F90C),) .f90.o: $(F90C) $(F90FLAGS) -c $< -o $@ endif # # Common dependencies # COMMONDEP = Makefile # # Source files # SOURCE = $(SRC)/cbf.c \ $(SRC)/cbf_alloc.c \ $(SRC)/cbf_ascii.c \ $(SRC)/cbf_binary.c \ $(SRC)/cbf_byte_offset.c \ $(SRC)/cbf_canonical.c \ $(SRC)/cbf_codes.c \ $(SRC)/cbf_compress.c \ $(SRC)/cbf_context.c \ $(SRC)/cbf_copy.c \ $(SRC)/cbf_file.c \ $(SRC)/cbf_getopt.c \ $(SRC)/cbf_lex.c \ $(SRC)/cbf_packed.c \ $(SRC)/cbf_predictor.c \ $(SRC)/cbf_read_binary.c \ $(SRC)/cbf_read_mime.c \ $(SRC)/cbf_simple.c \ $(SRC)/cbf_string.c \ $(SRC)/cbf_stx.c \ $(SRC)/cbf_tree.c \ $(SRC)/cbf_uncompressed.c \ $(SRC)/cbf_write.c \ $(SRC)/cbf_write_binary.c \ $(SRC)/cbf_ws.c \ $(SRC)/md5c.c F90SOURCE = $(SRC)/fcb_atol_wcnt.f90 \ $(SRC)/fcb_ci_strncmparr.f90 \ $(SRC)/fcb_exit_binary.f90 \ $(SRC)/fcb_nblen_array.f90 \ $(SRC)/fcb_next_binary.f90 \ $(SRC)/fcb_open_cifin.f90 \ $(SRC)/fcb_packed.f90 \ $(SRC)/fcb_read_bits.f90 \ $(SRC)/fcb_read_byte.f90 \ $(SRC)/fcb_read_image.f90 \ $(SRC)/fcb_read_line.f90 \ $(SRC)/fcb_read_xds_i2.f90 \ $(SRC)/fcb_skip_whitespace.f90 \ $(EXAMPLES)/test_fcb_read_image.f90 \ $(EXAMPLES)/test_xds_binary.f90 # # Header files # HEADERS = $(INCLUDE)/cbf.h \ $(INCLUDE)/cbf_alloc.h \ $(INCLUDE)/cbf_ascii.h \ $(INCLUDE)/cbf_binary.h \ $(INCLUDE)/cbf_byte_offset.h \ $(INCLUDE)/cbf_canonical.h \ $(INCLUDE)/cbf_codes.h \ $(INCLUDE)/cbf_compress.h \ $(INCLUDE)/cbf_context.h \ $(INCLUDE)/cbf_copy.h \ $(INCLUDE)/cbf_file.h \ $(INCLUDE)/cbf_getopt.h \ $(INCLUDE)/cbf_lex.h \ $(INCLUDE)/cbf_packed.h \ $(INCLUDE)/cbf_predictor.h \ $(INCLUDE)/cbf_read_binary.h \ $(INCLUDE)/cbf_read_mime.h \ $(INCLUDE)/cbf_simple.h \ $(INCLUDE)/cbf_string.h \ $(INCLUDE)/cbf_stx.h \ $(INCLUDE)/cbf_tree.h \ $(INCLUDE)/cbf_uncompressed.h \ $(INCLUDE)/cbf_write.h \ $(INCLUDE)/cbf_write_binary.h \ $(INCLUDE)/cbf_ws.h \ $(INCLUDE)/global.h \ $(INCLUDE)/cbff.h \ $(INCLUDE)/md5.h # # m4 macro files # M4FILES = $(M4)/fcblib_defines.m4 \ $(M4)/fcb_exit_binary.m4 \ $(M4)/fcb_next_binary.m4 \ $(M4)/fcb_open_cifin.m4 \ $(M4)/fcb_packed.m4 \ $(M4)/fcb_read_bits.m4 \ $(M4)/fcb_read_image.m4 \ $(M4)/fcb_read_xds_i2.m4 \ $(M4)/test_fcb_read_image.m4 \ $(M4)/test_xds_binary.m4 # # Documentation files # DOCUMENTS = $(DOC)/CBFlib.html \ $(DOC)/CBFlib.txt \ $(DOC)/CBFlib_NOTICES.html \ $(DOC)/CBFlib_NOTICES.txt \ $(DOC)/ChangeLog \ $(DOC)/ChangeLog.html \ $(DOC)/MANIFEST \ $(DOC)/gpl.txt $(DOC)/lgpl.txt # # HTML Graphics files # JPEGS = $(GRAPHICS)/CBFbackground.jpg \ $(GRAPHICS)/CBFbig.jpg \ $(GRAPHICS)/CBFbutton.jpg \ $(GRAPHICS)/cbflibbackground.jpg \ $(GRAPHICS)/cbflibbig.jpg \ $(GRAPHICS)/cbflibbutton.jpg \ $(GRAPHICS)/cifhome.jpg \ $(GRAPHICS)/iucrhome.jpg \ $(GRAPHICS)/noticeButton.jpg # # Default: instructions # default: @echo ' ' @echo '***************************************************************' @echo ' ' @echo ' PLEASE READ README and doc/CBFlib_NOTICES.txt' @echo ' ' @echo ' Before making the CBF library and example programs, check' @echo ' that the C compiler name and flags are correct:' @echo ' ' @echo ' The current values are:' @echo ' ' @echo ' $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG)' @echo ' ' @echo ' Before installing the CBF library and example programs, check' @echo ' that the install directory is correct:' @echo ' ' @echo ' The current value :' @echo ' ' @echo ' $(INSTALLDIR) ' @echo ' ' @echo ' To compile the CBF library and example programs type:' @echo ' ' @echo ' make clean' @echo ' make all' @echo ' ' @echo ' To compile the CBF library as a shared object library, type:' @echo ' ' @echo ' make shared' @echo ' ' @echo ' To compile the Java wrapper classes for CBF library, type:' @echo ' ' @echo ' make javawrapper' @echo ' ' @echo ' To run a set of tests type:' @echo ' ' @echo ' make tests' @echo ' ' @echo ' To run some java tests type:' @echo ' ' @echo ' make javatests' @echo ' ' @echo ' The tests assume that several data files are in the directories' @echo ' $(DATADIRI) and $(DATADIRO)' @echo ' ' @echo ' Alternatively tests can be run comparing MD5 signatures only by' @echo ' ' @echo ' make tests_sigs_only' @echo ' ' @echo ' These signature only tests save space and download time by' @echo ' assuming that input data files and the output signatures' @echo ' are in the directories' @echo ' $(DATADIRI) and $(DATADIRS)' @echo ' ' @echo ' These directory can be obtained from' @echo ' ' @echo ' $(DATAURLI) ' @echo ' $(DATAURLO) ' @echo ' $(DATAURLS) ' @echo ' ' @echo ' To clean up the directories type:' @echo ' ' @echo ' make clean' @echo ' ' @echo ' To install the library and binaries type:' @echo ' ' @echo ' make install' @echo ' ' @echo '***************************************************************' @echo ' ' # # Compile the library and examples # all:: $(BIN) $(SOURCE) $(F90SOURCE) $(HEADERS) \ symlinksdone $(REGEXDEP) \ $(LIB)/libcbf.a \ $(LIB)/libfcb.a \ $(LIB)/libimg.a \ $(BIN)/adscimg2cbf \ $(BIN)/cbf2adscimg \ $(BIN)/convert_image \ $(BIN)/convert_minicbf \ $(BIN)/sequence_match \ $(BIN)/arvai_test \ $(BIN)/makecbf \ $(BIN)/img2cif \ $(BIN)/adscimg2cbf \ $(BIN)/cif2cbf \ $(BIN)/testcell \ $(BIN)/cif2c \ $(BIN)/testreals \ $(BIN)/testflat \ $(BIN)/testflatpacked ifneq ($(F90C),) all:: $(BIN)/test_xds_binary \ $(BIN)/test_fcb_read_image endif shared: $(SOLIB)/libcbf.so $(SOLIB)/libfcb.so $(SOLIB)/libimg.so javawrapper: shared $(JCBF) $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf_wrap.so ifneq ($(CBFLIB_USE_PYCIFRW),) PYCIFRWDEF = -Dcbf_use_pycifrw=yes else PYCIFRWDEF = endif Makefiles: Makefile \ Makefile_LINUX \ Makefile_LINUX_64 \ Makefile_LINUX_gcc42 \ Makefile_LINUX_DMALLOC \ Makefile_LINUX_gcc42_DMALLOC \ Makefile_OSX \ Makefile_OSX_gcc42 \ Makefile_OSX_gcc42_DMALLOC \ Makefile_AIX \ Makefile_MINGW \ Makefile_IRIX_gcc Makefile_LINUX: $(M4)/Makefile.m4 -cp Makefile_LINUX Makefile_LINUX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX $(M4)/Makefile.m4 > Makefile_LINUX Makefile_LINUX_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_LINUX Makefile_LINUX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_DMALLOC $(M4)/Makefile.m4 > Makefile_LINUX_DMALLOC Makefile_LINUX_64: $(M4)/Makefile.m4 -cp Makefile_LINUX_64 Makefile_LINUX_64_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_64 $(M4)/Makefile.m4 > Makefile_LINUX_64 Makefile_LINUX_gcc42: $(M4)/Makefile.m4 -cp Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_gcc42 $(M4)/Makefile.m4 > Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_gcc42_DMALLOC $(M4)/Makefile.m4 > Makefile_LINUX_gcc42_DMALLOC Makefile_OSX: $(M4)/Makefile.m4 -cp Makefile_OSX Makefile_OSX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX $(M4)/Makefile.m4 > Makefile_OSX Makefile_OSX_gcc42: $(M4)/Makefile.m4 -cp Makefile_OSX_gcc42 Makefile_OSX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX_gcc42 $(M4)/Makefile.m4 > Makefile_OSX_gcc42 Makefile_OSX_gcc42_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_OSX_gcc42 Makefile_OSX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX_gcc42_DMALLOC $(M4)/Makefile.m4 > Makefile_OSX_gcc42_DMALLOC Makefile_AIX: $(M4)/Makefile.m4 -cp Makefile_AIX Makefile_AIX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=AIX $(M4)/Makefile.m4 > Makefile_AIX Makefile_MINGW: $(M4)/Makefile.m4 -cp Makefile_MINGW Makefile_MINGW_old m4 -P $(PYCIFRWDEF) -Dcbf_system=MINGW $(M4)/Makefile.m4 > Makefile_MINGW Makefile_IRIX_gcc: $(M4)/Makefile.m4 -cp Makefile_IRIX_gcc Makefile_IRIX_gcc_old m4 -P $(PYCIFREDEF) -Dcbf_system=IRIX_gcc $(M4)/Makefile.m4 > Makefile_IRIX_gcc Makefile: $(M4)/Makefile.m4 -cp Makefile Makefile_old m4 -P $(PYCIFRWDEF) -Dcbf_system=default $(M4)/Makefile.m4 > Makefile symlinksdone: chmod a+x .symlinks chmod a+x .undosymlinks chmod a+x doc/.symlinks chmod a+x doc/.undosymlinks chmod a+x libtool/.symlinks chmod a+x libtool/.undosymlinks ./.symlinks $(SLFLAGS) touch symlinksdone install: all $(INSTALLDIR) $(INSTALLDIR)/lib $(INSTALLDIR)/bin \ $(INSTALLDIR)/include $(INSTALLDIR)/include/cbflib \ $(PYSOURCE) -chmod -R 755 $(INSTALLDIR)/include/cbflib -chmod 755 $(INSTALLDIR)/lib/libcbf.a -cp $(INSTALLDIR)/lib/libcbf.a $(INSTALLDIR)/lib/libcbf_old.a cp $(LIB)/libcbf.a $(INSTALLDIR)/lib/libcbf.a -cp $(INSTALLDIR)/lib/libimg.a $(INSTALLDIR)/lib/libimg_old.a cp $(LIB)/libimg.a $(INSTALLDIR)/lib/libimg.a -cp $(INSTALLDIR)/bin/adscimg2cbf $(INSTALLDIR)/bin/adscimg2cbf_old cp $(BIN)/adscimg2cbf $(INSTALLDIR)/bin/adscimg2cbf -cp $(INSTALLDIR)/bin/cbf2adscimg $(INSTALLDIR)/bin/cbf2adscimg_old cp $(BIN)/cbf2adscimg $(INSTALLDIR)/bin/cbf2adscimg -cp $(INSTALLDIR)/bin/convert_image $(INSTALLDIR)/bin/convert_image_old cp $(BIN)/convert_image $(INSTALLDIR)/bin/convert_image -cp $(INSTALLDIR)/bin/convert_minicbf $(INSTALLDIR)/bin/convert_minicbf_old cp $(BIN)/convert_minicbf $(INSTALLDIR)/bin/convert_minicbf -cp $(INSTALLDIR)/bin/makecbf $(INSTALLDIR)/bin/makecbf_old cp $(BIN)/makecbf $(INSTALLDIR)/bin/makecbf -cp $(INSTALLDIR)/bin/img2cif $(INSTALLDIR)/bin/img2cif_old cp $(BIN)/img2cif $(INSTALLDIR)/bin/img2cif -cp $(INSTALLDIR)/bin/cif2cbf $(INSTALLDIR)/bin/cif2cbf_old cp $(BIN)/cif2cbf $(INSTALLDIR)/bin/cif2cbf -cp $(INSTALLDIR)/bin/sequence_match $(INSTALLDIR)/bin/sequence_match_old cp $(BIN)/sequence_match $(INSTALLDIR)/bin/sequence_match -cp $(INSTALLDIR)/bin/arvai_test $(INSTALLDIR)/bin/arvai_test_old cp $(BIN)/arvai_test $(INSTALLDIR)/bin/arvai_test -cp $(INSTALLDIR)/bin/cif2c $(INSTALLDIR)/bin/cif2c_old cp $(BIN)/cif2c $(INSTALLDIR)/bin/cif2c -cp $(INSTALLDIR)/bin/testreals $(INSTALLDIR)/bin/testreals_old cp $(BIN)/testreals $(INSTALLDIR)/bin/testreals -cp $(INSTALLDIR)/bin/testflat $(INSTALLDIR)/bin/testflat_old cp $(BIN)/testflat $(INSTALLDIR)/bin/testflat -cp $(INSTALLDIR)/bin/testflatpacked $(INSTALLDIR)/bin/testflatpacked_old cp $(BIN)/testflatpacked $(INSTALLDIR)/bin/testflatpacked chmod -R 755 $(INSTALLDIR)/include/cbflib -rm -rf $(INSTALLDIR)/include/cbflib_old -cp -r $(INSTALLDIR)/include/cbflib $(INSTALLDIR)/include/cbflib_old -rm -rf $(INSTALLDIR)/include/cbflib cp -r $(INCLUDE) $(INSTALLDIR)/include/cbflib chmod 644 $(INSTALLDIR)/lib/libcbf.a chmod 755 $(INSTALLDIR)/bin/convert_image chmod 755 $(INSTALLDIR)/bin/convert_minicbf chmod 755 $(INSTALLDIR)/bin/makecbf chmod 755 $(INSTALLDIR)/bin/img2cif chmod 755 $(INSTALLDIR)/bin/cif2cbf chmod 755 $(INSTALLDIR)/bin/sequence_match chmod 755 $(INSTALLDIR)/bin/arvai_test chmod 755 $(INSTALLDIR)/bin/cif2c chmod 755 $(INSTALLDIR)/bin/testreals chmod 755 $(INSTALLDIR)/bin/testflat chmod 755 $(INSTALLDIR)/bin/testflatpacked chmod 644 $(INSTALLDIR)/include/cbflib/*.h # # REGEX # ifneq ($(REGEXDEP),) $(REGEXDEP): $(REGEX) (cd $(REGEX); ./configure; make install) endif $(REGEX): $(DOWNLOAD) $(REGEXURL) tar -xvf $(REGEX).tar.gz -rm $(REGEX).tar.gz # # TIFF # $(TIFF): $(DOWNLOAD) $(TIFFURL) tar -xvf $(TIFF).tar.gz -rm $(TIFF).tar.gz (cd $(TIFF); ./configure --prefix=$(TIFFPREFIX); make install) # # Directories # $(INSTALLDIR): mkdir -p $(INSTALLDIR) $(INSTALLDIR)/lib: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/lib $(INSTALLDIR)/bin: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/bin $(INSTALLDIR)/include: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/include $(INSTALLDIR)/include/cbflib: $(INSTALLDIR)/include mkdir -p $(INSTALLDIR)/include/cbflib $(LIB): mkdir $@ $(BIN): mkdir $@ $(SOLIB): mkdir $@ $(JCBF): mkdir $@ # # Parser # $(SRC)/cbf_stx.c: $(SRC)/cbf.stx.y bison $(SRC)/cbf.stx.y -o $(SRC)/cbf.stx.tab.c -d mv $(SRC)/cbf.stx.tab.c $(SRC)/cbf_stx.c mv $(SRC)/cbf.stx.tab.h $(INCLUDE)/cbf_stx.h # # CBF library # $(LIB)/libcbf.a: $(SOURCE) $(HEADERS) $(COMMONDEP) $(LIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG) $(INCLUDES) $(WARNINGS) -c $(SOURCE) $(AR) cr $@ *.o mv *.o $(LIB) ifneq ($(RANLIB),) $(RANLIB) $@ endif $(SOLIB)/libcbf.so: $(SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(SOURCE) $(CC) -o $@ *.o $(SOLDFLAGS) $(EXTRALIBS) rm *.o # # IMG library # $(LIB)/libimg.a: $(EXAMPLES)/img.c $(HEADERS) $(COMMONDEP) $(LIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) -c $(EXAMPLES)/img.c $(AR) cr $@ img.o ifneq ($(RANLIB),) $(RANLIB) $@ endif rm img.o $(SOLIB)/libimg.so: $(SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(EXAMPLES)/img.c $(CC) -o $@ img.o $(SOLDFLAGS) rm img.o # # CBF and IMG libraries # CBF_IMG_LIBS: $(LIB)/libcbf.a $(LIB)/libimg.a # # FCB library # $(LIB)/libfcb.a: $(F90SOURCE) $(COMMONDEP) $(LIB) ifneq ($(F90C),) $(F90C) $(F90FLAGS) -c $(F90SOURCE) $(AR) cr $@ *.o ifneq ($(RANLIB),) $(RANLIB) $@ endif rm *.o else echo "Define F90C to build $(LIB)/libfcb.a" endif $(SOLIB)/libfcb.so: $(F90SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) ifneq ($(F90C),) $(F90C) $(F90FLAGS) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(F90SOURCE) $(F90C) $(F90FLAGS) -o $@ *.o $(SOLDFLAGS) rm *.o else echo "Define F90C to build $(SOLIB)/libfcb.so" endif # # Python bindings # $(PYCBF)/_pycbf.$(PYCBFEXT): $(PYCBF) $(LIB)/libcbf.a \ $(PYCBF)/$(SETUP_PY) \ $(LIB)/libfcb.a \ $(LIB)/libimg.a \ $(PYCBF)/pycbf.i \ $(PYCBF)/cbfhandlewrappers.i \ $(PYCBF)/cbfdetectorwrappers.i \ $(PYCBF)/cbfgenericwrappers.i \ $(PYCBF)/cbfgoniometerwrappers.i (cd $(PYCBF); python $(SETUP_PY) build $(PYCBFBOPT); cp build/lib.*/_pycbf.$(PYCBFEXT) .) $(PYCBF)/setup.py: $(M4)/setup_py.m4 (m4 -P -Dregexlib=NOREGEXLIB -Dregexlibdir=NOREGEXLIBDIR $(M4)/setup_py.m4 > $@) $(PYCBF)/setup_MINGW.py: m4/setup_py.m4 (m4 -P -Dregexlib=regex -Dregexlibdir=$(REGEXDIR) $(M4)/setup_py.m4 > $@) $(LIB)/_pycbf.$(PYCBFEXT): $(PYCBF)/_pycbf.$(PYCBFEXT) cp $(PYCBF)/_pycbf.$(PYCBFEXT) $(LIB)/_pycbf.$(PYCBFEXT) $(PYCBF)/pycbf.pdf: $(PYCBF)/pycbf.w (cd $(PYCBF); \ $(NUWEB) pycbf; \ latex pycbf; \ $(NUWEB) pycbf; \ latex pycbf; \ dvipdfm pycbf ) $(PYCBF)/CBFlib.txt: $(DOC)/CBFlib.html links -dump $(DOC)/CBFlib.html > $(PYCBF)/CBFlib.txt $(PYCBF)/cbfhandlewrappers.i \ $(PYCBF)/cbfdetectorwrappers.i \ $(PYCBF)/cbfgenericwrappers.i \ $(PYCBF)/cbfgoniometerwrappers.i: $(PYCBF)/CBFlib.txt $(PYCBF)/make_pycbf.py (cd $(PYCBF); python make_pycbf.py; $(PYSWIG) pycbf.i; python setup.py build) # # Java bindings # $(JCBF)/cbflib-$(VERSION).jar: $(JCBF) $(JCBF)/jcbf.i $(JSWIG) -I$(INCLUDE) -package org.iucr.cbflib -outdir $(JCBF) $(JCBF)/jcbf.i $(JAVAC) -d . $(JCBF)/*.java $(JAR) cf $@ org $(SOLIB)/libcbf_wrap.so: $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf.so $(CC) $(CFLAGS) $(NOLLFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) $(JAVAINCLUDES) -c $(JCBF)/jcbf_wrap.c $(CC) -o $@ jcbf_wrap.o $(SOLDFLAGS) -L$(SOLIB) -lcbf rm jcbf_wrap.o # # F90SOURCE # $(SRC)/fcb_exit_binary.f90: $(M4)/fcb_exit_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_exit_binary.m4) > $(SRC)/fcb_exit_binary.f90 $(SRC)/fcb_next_binary.f90: $(M4)/fcb_next_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_next_binary.m4) > $(SRC)/fcb_next_binary.f90 $(SRC)/fcb_open_cifin.f90: $(M4)/fcb_open_cifin.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_open_cifin.m4) > $(SRC)/fcb_open_cifin.f90 $(SRC)/fcb_packed.f90: $(M4)/fcb_packed.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_packed.m4) > $(SRC)/fcb_packed.f90 $(SRC)/fcb_read_bits.f90: $(M4)/fcb_read_bits.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_bits.m4) > $(SRC)/fcb_read_bits.f90 $(SRC)/fcb_read_image.f90: $(M4)/fcb_read_image.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_image.m4) > $(SRC)/fcb_read_image.f90 $(SRC)/fcb_read_xds_i2.f90: $(M4)/fcb_read_xds_i2.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_xds_i2.m4) > $(SRC)/fcb_read_xds_i2.f90 $(EXAMPLES)/test_fcb_read_image.f90: $(M4)/test_fcb_read_image.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) test_fcb_read_image.m4) > $(EXAMPLES)/test_fcb_read_image.f90 $(EXAMPLES)/test_xds_binary.f90: $(M4)/test_xds_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) test_xds_binary.m4) > $(EXAMPLES)/test_xds_binary.f90 # # convert_image example program # $(BIN)/convert_image: $(LIB)/libcbf.a $(EXAMPLES)/convert_image.c $(EXAMPLES)/img.c \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/convert_image.c $(EXAMPLES)/img.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # convert_minicbf example program # $(BIN)/convert_minicbf: $(LIB)/libcbf.a $(EXAMPLES)/convert_minicbf.c \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/convert_minicbf.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # makecbf example program # $(BIN)/makecbf: $(LIB)/libcbf.a $(EXAMPLES)/makecbf.c $(LIB)/libimg.a $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/makecbf.c -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # adscimg2cbf example program # $(BIN)/adscimg2cbf: $(LIB)/libcbf.a $(EXAMPLES)/adscimg2cbf.c $(EXAMPLES)/adscimg2cbf_sub.c $(CC) $(CFLAGS) $(NOLLFLAG) -D_SVID_SOURCE $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/adscimg2cbf.c $(EXAMPLES)/adscimg2cbf_sub.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # cbf2adscimg example program # $(BIN)/cbf2adscimg: $(LIB)/libcbf.a $(EXAMPLES)/cbf2adscimg.c $(EXAMPLES)/cbf2adscimg_sub.c $(CC) $(CFLAGS) $(NOLLFLAG) -D_SVID_SOURCE $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cbf2adscimg.c $(EXAMPLES)/cbf2adscimg_sub.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # changtestcompression example program # $(BIN)/changtestcompression: $(LIB)/libcbf.a $(EXAMPLES)/changtestcompression.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/changtestcompression.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # img2cif example program # $(BIN)/img2cif: $(LIB)/libcbf.a $(EXAMPLES)/img2cif.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOTPINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/img2cif.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # cif2cbf example program # $(BIN)/cif2cbf: $(LIB)/libcbf.a $(EXAMPLES)/cif2cbf.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cif2cbf.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # dectris cbf_template_t program # $(BIN)/cbf_template_t: $(DECTRIS_EXAMPLES)/cbf_template_t.c \ $(DECTRIS_EXAMPLES)/mx_cbf_t_extras.h \ $(DECTRIS_EXAMPLES)/mx_parms.h $(CC) $(CFLAGS) $(NOLLFLAG) -I $(DECTRIS_EXAMPLES) $(WARNINGS) \ $(DECTRIS_EXAMPLES)/cbf_template_t.c -o $@ # # testcell example program # $(BIN)/testcell: $(LIB)/libcbf.a $(EXAMPLES)/testcell.C $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testcell.C -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # cif2c example program # $(BIN)/cif2c: $(LIB)/libcbf.a $(EXAMPLES)/cif2c.c $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cif2c.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # sauter_test example program # $(BIN)/sauter_test: $(LIB)/libcbf.a $(EXAMPLES)/sauter_test.C $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/sauter_test.C -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # sequence_match example program # $(BIN)/sequence_match: $(LIB)/libcbf.a $(EXAMPLES)/sequence_match.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/sequence_match.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # tiff2cbf example program # $(BIN)/tiff2cbf: $(LIB)/libcbf.a $(EXAMPLES)/tiff2cbf.c \ $(GOPTLIB) $(GOPTINC) $(TIFF) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ -I$(TIFFPREFIX)/include $(EXAMPLES)/tiff2cbf.c $(GOPTLIB) -L$(LIB) \ -lcbf -L$(TIFFPREFIX)/lib -ltiff $(EXTRALIBS) -limg -o $@ # # Andy Arvai's buffered read test program # $(BIN)/arvai_test: $(LIB)/libcbf.a $(EXAMPLES)/arvai_test.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/arvai_test.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # testreals example program # $(BIN)/testreals: $(LIB)/libcbf.a $(EXAMPLES)/testreals.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testreals.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testflat example program # $(BIN)/testflat: $(LIB)/libcbf.a $(EXAMPLES)/testflat.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testflat.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testflatpacked example program # $(BIN)/testflatpacked: $(LIB)/libcbf.a $(EXAMPLES)/testflatpacked.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testflatpacked.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ ifneq ($(F90C),) # # test_xds_binary example program # $(BIN)/test_xds_binary: $(LIB)/libfcb.a $(EXAMPLES)/test_xds_binary.f90 $(F90C) $(F90FLAGS) $(F90LDFLAGS) $(EXAMPLES)/test_xds_binary.f90 \ -L$(LIB) -lfcb -o $@ # # test_fcb_read_image example program # $(BIN)/test_fcb_read_image: $(LIB)/libfcb.a $(EXAMPLES)/test_fcb_read_image.f90 $(F90C) $(F90FLAGS) $(F90LDFLAGS) $(EXAMPLES)/test_fcb_read_image.f90 \ -L$(LIB) -lfcb -o $@ endif # # testcbf (C) # $(BIN)/ctestcbf: $(EXAMPLES)/testcbf.c $(LIB)/libcbf.a $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testcbf.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testcbf (Java) # $(BIN)/testcbf.class: $(EXAMPLES)/testcbf.java $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf_wrap.so $(JAVAC) -cp $(JCBF)/cbflib-$(VERSION).jar -d $(BIN) $(EXAMPLES)/testcbf.java # # Data files for tests # $(DATADIRI): (cd ..; $(DOWNLOAD) $(DATAURLI)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Input.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Input.tar.gz) $(DATADIRO): (cd ..; $(DOWNLOAD) $(DATAURLO)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Output.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Output.tar.gz) $(DATADIRS): (cd ..; $(DOWNLOAD) $(DATAURLS)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz) # Input Data Files TESTINPUT_BASIC = example.mar2300 DATADIRI_INPUT_BASIC = $(DATADIRI)/example.mar2300$(CEXT) TESTINPUT_EXTRA = 9ins.cif mb_LP_1_001.img insulin_pilatus6m.cbf testrealin.cbf \ testflatin.cbf testflatpackedin.cbf XRD1621.tif DATADIRI_INPUT_EXTRA = $(DATADIRI)/9ins.cif$(CEXT) $(DATADIRI)/mb_LP_1_001.img$(CEXT) \ $(DATADIRI)/insulin_pilatus6m.cbf$(CEXT) $(DATADIRI)/testrealin.cbf$(CEXT) \ $(DATADIRI)/testflatin.cbf$(CEXT) $(DATADIRI)/testflatpackedin.cbf$(CEXT) \ $(DATADIRI)/XRD1621.tif$(CEXT) # Output Data Files TESTOUTPUT = adscconverted_flat_orig.cbf \ adscconverted_orig.cbf converted_flat_orig.cbf converted_orig.cbf \ insulin_pilatus6mconverted_orig.cbf \ mb_LP_1_001_orig.cbf testcell_orig.prt \ test_xds_bin_testflatout_orig.out \ test_xds_bin_testflatpackedout_orig.out test_fcb_read_testflatout_orig.out \ test_fcb_read_testflatpackedout_orig.out \ XRD1621_orig.cbf XRD1621_I4encbC100_orig.cbf NEWTESTOUTPUT = adscconverted_flat.cbf \ adscconverted.cbf converted_flat.cbf converted.cbf \ insulin_pilatus6mconverted.cbf \ mb_LP_1_001.cbf testcell.prt \ test_xds_bin_testflatout.out \ test_xds_bin_testflatpackedout.out test_fcb_read_testflatout.out \ test_fcb_read_testflatpackedout.out \ XRD1621.cbf XRD1621_I4encbC100.cbf DATADIRO_OUTPUT = $(DATADIRO)/adscconverted_flat_orig.cbf$(CEXT) \ $(DATADIRO)/adscconverted_orig.cbf$(CEXT) \ $(DATADIRO)/converted_flat_orig.cbf$(CEXT) \ $(DATADIRO)/converted_orig.cbf$(CEXT) \ $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(CEXT) \ $(DATADIRO)/mb_LP_1_001_orig.cbf$(CEXT) \ $(DATADIRO)/testcell_orig.prt$(CEXT) \ $(DATADIRO)/test_xds_bin_testflatout_orig.out$(CEXT) \ $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(CEXT) \ $(DATADIRO)/test_fcb_read_testflatout_orig.out$(CEXT) \ $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(CEXT) \ $(DATADIRO)/XRD1621_orig.cbf$(CEXT) \ $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(CEXT) DATADIRO_OUTPUT_SIGNATURES = $(DATADIRO)/adscconverted_flat_orig.cbf$(SEXT) \ $(DATADIRO)/adscconverted_orig.cbf$(SEXT) \ $(DATADIRO)/converted_flat_orig.cbf$(SEXT) \ $(DATADIRO)/converted_orig.cbf$(SEXT) \ $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(SEXT) \ $(DATADIRO)/mb_LP_1_001_orig.cbf$(SEXT) \ $(DATADIRO)/testcell_orig.prt$(SEXT) \ $(DATADIRO)/test_xds_bin_testflatout_orig.out$(SEXT) \ $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(SEXT) \ $(DATADIRO)/test_fcb_read_testflatout_orig.out$(SEXT) \ $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(SEXT) \ $(DATADIRO)/XRD1621_orig.cbf$(SEXT) \ $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(SEXT) # Output Data File Signatures TESTOUTPUTSIGS = adscconverted_flat_orig.cbf$(SEXT) \ adscconverted_orig.cbf$(SEXT) converted_flat_orig.cbf$(SEXT) converted_orig.cbf$(SEXT) \ insulin_pilatus6mconverted_orig.cbf$(SEXT) \ mb_LP_1_001_orig.cbf$(SEXT) testcell_orig.prt$(SEXT) \ test_xds_bin_testflatout_orig.out$(SEXT) \ test_xds_bin_testflatpackedout_orig.out$(SEXT) test_fcb_read_testflatout_orig.out$(SEXT) \ test_fcb_read_testflatpackedout_orig.out$(SEXT) \ XRD1621_orig.cbf$(SEXT) DATADIRS_OUTPUT_SIGNATURES = $(DATADIRS)/adscconverted_flat_orig.cbf$(SEXT) \ $(DATADIRS)/adscconverted_orig.cbf$(SEXT) \ $(DATADIRS)/converted_flat_orig.cbf$(SEXT) \ $(DATADIRS)/converted_orig.cbf$(SEXT) \ $(DATADIRS)/insulin_pilatus6mconverted_orig.cbf$(SEXT) \ $(DATADIRS)/mb_LP_1_001_orig.cbf$(SEXT) \ $(DATADIRS)/testcell_orig.prt$(SEXT) \ $(DATADIRS)/test_xds_bin_testflatout_orig.out$(SEXT) \ $(DATADIRS)/test_xds_bin_testflatpackedout_orig.out$(SEXT) \ $(DATADIRS)/test_fcb_read_testflatout_orig.out$(SEXT) \ $(DATADIRS)/test_fcb_read_testflatpackedout_orig.out$(SEXT) \ $(DATADIRS)/XRD1621_orig.cbf$(SEXT) \ $(DATADIRS)/XRD1621_I4encbC100_orig.cbf$(SEXT) # Fetch Input Data Files $(TESTINPUT_BASIC): $(DATADIRI) $(DATADIRI_INPUT_BASIC) $(DECOMPRESS) < $(DATADIRI)/$@$(CEXT) > $@ cp $(DATADIRI)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) $(TESTINPUT_EXTRA): $(DATADIRI) $(DATADIRI_INPUT_EXTRA) $(DECOMPRESS) < $(DATADIRI)/$@$(CEXT) > $@ cp $(DATADIRI)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) # Fetch Output Data Files and Signatures $(TESTOUTPUT): $(DATADIRO) $(DATADIRO_OUTPUT) $(DATADIRO_OUTPUT_SIGNATURES) $(DECOMPRESS) < $(DATADIRO)/$@$(CEXT) > $@ cp $(DATADIRO)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) # Fetch Output Data File Signatures $(TESTOUTPUTSIGS): $(DATADIRS) $(DATADIRS_OUTPUT_SIGNATURES) cp $(DATADIRS)/$@ $@ # # Tests # tests: $(LIB) $(BIN) symlinksdone basic extra dectristests pycbftests tests_sigs_only: $(LIB) $(BIN) symlinksdone basic extra_sigs_only restore_output: $(NEWTESTOUTPUT) $(DATADIRO) $(SIGNATURE) < adscconverted_flat.cbf > $(DATADIRO)/adscconverted_flat_orig.cbf$(SEXT) $(SIGNATURE) < adscconverted.cbf > $(DATADIRO)/adscconverted_orig.cbf$(SEXT) $(SIGNATURE) < converted_flat.cbf > $(DATADIRO)/converted_flat_orig.cbf$(SEXT) $(SIGNATURE) < converted.cbf > $(DATADIRO)/converted_orig.cbf$(SEXT) $(SIGNATURE) < insulin_pilatus6mconverted.cbf > $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(SEXT) $(SIGNATURE) < mb_LP_1_001.cbf$ > $(DATADIRO)/mb_LP_1_001_orig.cbf$(SEXT) $(SIGNATURE) < testcell.prt > $(DATADIRO)/testcell_orig.prt$(SEXT) $(SIGNATURE) < test_xds_bin_testflatout.out > $(DATADIRO)/test_xds_bin_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_xds_bin_testflatpackedout.out > $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatout.out > $(DATADIRO)/test_fcb_read_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatpackedout.out > $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < XRD1621.cbf > $(DATADIRO)/XRD1621_orig.cbf$(SEXT) $(SIGNATURE) < XRD1621_I4encbC100.cbf > $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(SEXT) $(COMPRESS) < adscconverted_flat.cbf > $(DATADIRO)/adscconverted_flat_orig.cbf$(CEXT) $(COMPRESS) < adscconverted.cbf > $(DATADIRO)/adscconverted_orig.cbf$(CEXT) $(COMPRESS) < converted_flat.cbf > $(DATADIRO)/converted_flat_orig.cbf$(CEXT) $(COMPRESS) < converted.cbf > $(DATADIRO)/converted_orig.cbf$(CEXT) $(COMPRESS) < insulin_pilatus6mconverted.cbf > $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(CEXT) $(COMPRESS) < mb_LP_1_001.cbf$ > $(DATADIRO)/mb_LP_1_001_orig.cbf$(CEXT) $(COMPRESS) < testcell.prt > $(DATADIRO)/testcell_orig.prt$(CEXT) $(COMPRESS) < test_xds_bin_testflatout.out > $(DATADIRO)/test_xds_bin_testflatout_orig.out$(CEXT) $(COMPRESS) < test_xds_bin_testflatpackedout.out > $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(CEXT) $(COMPRESS) < test_fcb_read_testflatout.out > $(DATADIRO)/test_fcb_read_testflatout_orig.out$(CEXT) $(COMPRESS) < test_fcb_read_testflatpackedout.out > $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(CEXT) $(COMPRESS) < XRD1621.cbf > $(DATADIRO)/XRD1621_orig.cbf$(CEXT) $(COMPRESS) < XRD1621_I4encbC100.cbf > $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(CEXT) restore_sigs_only: $(NEWTESTOUTPUT) $(DATADIRS) $(SIGNATURE) < adscconverted_flat.cbf > $(DATADIRS)/adscconverted_flat_orig.cbf$(SEXT) $(SIGNATURE) < adscconverted.cbf > $(DATADIRS)/adscconverted_orig.cbf$(SEXT) $(SIGNATURE) < converted_flat.cbf > $(DATADIRS)/converted_flat_orig.cbf$(SEXT) $(SIGNATURE) < converted.cbf > $(DATADIRS)/converted_orig.cbf$(SEXT) $(SIGNATURE) < insulin_pilatus6mconverted.cbf > $(DATADIRS)/insulin_pilatus6mconverted_orig.cbf$(SEXT) $(SIGNATURE) < mb_LP_1_001.cbf$ > $(DATADIRS)/mb_LP_1_001_orig.cbf$(SEXT) $(SIGNATURE) < testcell.prt > $(DATADIRS)/testcell_orig.prt$(SEXT) $(SIGNATURE) < test_xds_bin_testflatout.out > $(DATADIRS)/test_xds_bin_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_xds_bin_testflatpackedout.out > $(DATADIRS)/test_xds_bin_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatout.out > $(DATADIRS)/test_fcb_read_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatpackedout.out > $(DATADIRS)/test_fcb_read_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < XRD1621.cbf > $(DATADIRS)/XRD1621_orig.cbf$(SEXT) $(SIGNATURE) < XRD1621_I4encbC100.cbf > $(DATADIRS)/XRD1621_I4encbC100_orig.cbf$(SEXT) restore_signatures: restore_output restore_sigs_only # # Basic Tests # basic: $(BIN)/makecbf $(BIN)/img2cif $(BIN)/cif2cbf $(TESTINPUT_BASIC) $(BIN)/makecbf example.mar2300 makecbf.cbf $(BIN)/img2cif -c flatpacked -m headers -d digest \ -e base64 example.mar2300 img2cif_packed.cif $(BIN)/img2cif -c canonical -m headers -d digest \ -e base64 example.mar2300 img2cif_canonical.cif $(BIN)/img2cif -c flatpacked -m headers -d digest \ -e none example.mar2300 img2cif_packed.cbf $(BIN)/img2cif -c canonical -m headers -d digest \ -e none example.mar2300 img2cif_canonical.cbf $(BIN)/cif2cbf -e none -c flatpacked \ img2cif_canonical.cif cif2cbf_packed.cbf $(BIN)/cif2cbf -e none -c canonical \ img2cif_packed.cif cif2cbf_canonical.cbf -cmp cif2cbf_packed.cbf makecbf.cbf -cmp cif2cbf_packed.cbf img2cif_packed.cbf -cmp cif2cbf_canonical.cbf img2cif_canonical.cbf # # Extra Tests # ifneq ($(F90C),) extra: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/test_xds_binary $(BIN)/test_fcb_read_image $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg \ $(BIN)/changtestcompression $(BIN)/tiff2cbf \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUT) else extra: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUT) endif $(TIME) $(BIN)/cif2cbf -e hex -c none \ makecbf.cbf cif2cbf_ehcn.cif $(TIME) $(BIN)/cif2cbf -e none -c flatpacked \ cif2cbf_ehcn.cif cif2cbf_encp.cbf; rm cif2cbf_ehcn.cif -cmp makecbf.cbf cif2cbf_encp.cbf $(TIME) $(BIN)/cif2cbf -i 9ins.cif -o 9ins.cbf -cmp 9ins.cif 9ins.cbf $(TIME) $(BIN)/convert_image -F example.mar2300 converted_flat.cbf -cmp converted_flat.cbf converted_flat_orig.cbf $(TIME) $(BIN)/convert_image example.mar2300 converted.cbf -cmp converted.cbf converted_orig.cbf -$(TIME) $(BIN)/testcell < testcell.dat > testcell.prt -cmp testcell.prt testcell_orig.prt $(TIME) $(BIN)/convert_image -F -d adscquantum315 mb_LP_1_001.img adscconverted_flat.cbf -cmp adscconverted_flat.cbf adscconverted_flat_orig.cbf $(TIME) $(BIN)/convert_image -d adscquantum315 mb_LP_1_001.img adscconverted.cbf -cmp adscconverted.cbf adscconverted_orig.cbf $(TIME) $(BIN)/adscimg2cbf --no_pad --cbf_packed,flat mb_LP_1_001.img -cmp mb_LP_1_001.cbf mb_LP_1_001_orig.cbf ifneq ($(CLEANTESTS),) mv mb_LP_1_001.cbf nmb_LP_1_001.cbf else cp mb_LP_1_001.cbf nmb_LP_1_001.cbf endif $(TIME) $(BIN)/cbf2adscimg nmb_LP_1_001.cbf -cmp nmb_LP_1_001.img mb_LP_1_001.img rm nmb_LP_1_001.cbf ifneq ($(CLEANTESTS),) rm nmb_LP_1_001.img endif $(TIME) $(BIN)/convert_minicbf -d pilatus6m insulin_pilatus6m.cbf insulin_pilatus6mconverted.cbf -cmp insulin_pilatus6mconverted.cbf insulin_pilatus6mconverted_orig.cbf $(TIME) $(BIN)/testreals -cmp testrealin.cbf testrealout.cbf $(TIME) $(BIN)/testflat -cmp testflatin.cbf testflatout.cbf $(TIME) $(BIN)/testflatpacked -cmp testflatpackedin.cbf testflatpackedout.cbf ifneq ($(F90C),) echo testflatout.cbf | $(TIME) $(BIN)/test_xds_binary > test_xds_bin_testflatout.out -$(DIFF) test_xds_bin_testflatout.out test_xds_bin_testflatout_orig.out echo testflatpackedout.cbf | $(TIME) $(BIN)/test_xds_binary > test_xds_bin_testflatpackedout.out -$(DIFF) test_xds_bin_testflatpackedout.out test_xds_bin_testflatpackedout_orig.out echo testflatout.cbf | $(TIME) $(BIN)/test_fcb_read_image > test_fcb_read_testflatout.out -$(DIFF) test_fcb_read_testflatout.out test_fcb_read_testflatout_orig.out echo testflatpackedout.cbf | $(TIME) $(BIN)/test_fcb_read_image > test_fcb_read_testflatpackedout.out -$(DIFF) test_fcb_read_testflatpackedout.out test_fcb_read_testflatpackedout_orig.out endif $(TIME) $(BIN)/sauter_test $(TIME) $(BIN)/changtestcompression $(TIME) (export LD_LIBRARY_PATH=$(LIB);$(BIN)/tiff2cbf XRD1621.tif XRD1621.cbf) -$(DIFF) XRD1621.cbf XRD1621_orig.cbf $(TIME) $(BIN)/cif2cbf -I 4 -C 100. -L 0. -e n -c b -i XRD1621.cbf -o XRD1621_I4encbC100.cbf -$(DIFF) XRD1621_I4encbC100.cbf XRD1621_I4encbC100_orig.cbf ifneq ($(F90C),) extra_sigs_only: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/test_xds_binary $(BIN)/test_fcb_read_image $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg $(BIN)/tiff2cbf \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) else extra_sigs_only: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf\ basic $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) endif $(TIME) $(BIN)/cif2cbf -e hex -c none \ makecbf.cbf cif2cbf_ehcn.cif $(TIME) $(BIN)/cif2cbf -e none -c packed \ cif2cbf_ehcn.cif cif2cbf_encp.cbf; rm cif2cbf_ehcn.cif -cmp makecbf.cbf cif2cbf_encp.cbf $(TIME) $(BIN)/cif2cbf -i 9ins.cif -o 9ins.cbf -cmp 9ins.cif 9ins.cbf $(TIME) $(BIN)/convert_image -F example.mar2300 converted_flat.cbf -$(SIGNATURE) < converted_flat.cbf | $(DIFF) - converted_flat_orig.cbf$(SEXT); rm converted_flat.cbf $(TIME) $(BIN)/convert_image example.mar2300 converted.cbf -$(SIGNATURE) < converted.cbf | $(DIFF) - converted_orig.cbf$(SEXT); rm converted.cbf -$(TIME) $(BIN)/testcell < testcell.dat | \ $(SIGNATURE) | $(DIFF) - testcell_orig.prt$(SEXT) $(TIME) $(BIN)/convert_image -F -d adscquantum315 mb_LP_1_001.img adscconverted_flat.cbf -$(SIGNATURE) < adscconverted_flat.cbf | $(DIFF) - adscconverted_flat_orig.cbf$(SEXT) $(TIME) $(BIN)/convert_image -d adscquantum315 mb_LP_1_001.img adscconverted.cbf -$(SIGNATURE) < adscconverted.cbf | $(DIFF) - adscconverted_orig.cbf$(SEXT); rm adscconverted.cbf $(TIME) $(BIN)/adscimg2cbf --cbf_packed,flat mb_LP_1_001.img -$(SIGNATURE) < mb_LP_1_001.cbf | $(DIFF) - mb_LP_1_001_orig.cbf$(SEXT) mv mb_LP_1_001.cbf nmb_LP_1_001.cbf $(TIME) $(BIN)/cbf2adscimg nmb_LP_1_001.cbf -cmp nmb_LP_1_001.img mb_LP_1_001.img rm nmb_LP_1_001.cbf rm nmb_LP_1_001.img $(TIME) $(BIN)/convert_minicbf -d pilatus6m insulin_pilatus6m.cbf insulin_pilatus6mconverted.cbf -$(SIGNATURE) < insulin_pilatus6mconverted.cbf | $(DIFF) - insulin_pilatus6mconverted_orig.cbf$(SEXT); rm insulin_pilatus6mconverted.cbf $(TIME) $(BIN)/testreals -cmp testrealin.cbf testrealout.cbf $(TIME) $(BIN)/testflat -cmp testflatin.cbf testflatout.cbf $(TIME) $(BIN)/testflatpacked -cmp testflatpackedin.cbf testflatpackedout.cbf ifneq ($(F90C),) echo testflatout.cbf | $(TIME) $(BIN)/test_xds_binary | \ $(SIGNATURE) | $(DIFF) - test_xds_bin_testflatout_orig.out$(SEXT) echo testflatpackedout.cbf | $(TIME) $(BIN)/test_xds_binary | \ $(SIGNATURE) | $(DIFF) - test_xds_bin_testflatpackedout_orig.out$(SEXT) echo testflatout.cbf | $(TIME) $(BIN)/test_fcb_read_image | \ $(SIGNATURE) | $(DIFF) - test_fcb_read_testflatout_orig.out$(SEXT) echo testflatpackedout.cbf | $(TIME) $(BIN)/test_fcb_read_image | \ $(SIGNATURE) | $(DIFF) - test_fcb_read_testflatpackedout_orig.out$(SEXT) endif $(TIME) $(BIN)/sauter_test $(TIME) $(BIN)/tiff2cbf XRD1621.tif XRD1621.cbf $(TIME) $(BIN)/cif2cbf -I 4 -C 100. -L 0. -e n -c b -i XRD1621.cbf -o XRD1621_I4encbC100.cbf -$(SIGNATURE) < XRD1621.cbf | $(DIFF) - XRD1621_orig.cbf$(SEXT); rm XRD1621.cbf -$(SIGNATURE) < XRD1621_I4encbC100.cbf | $(DIFF) - XRD1621_I4encbC100_orig.cbf$(SEXT); rm XRD1621_I4encbC100.cbf @-rm -f adscconverted_flat.cbf @-rm -f $(TESTINPUT_BASIC) $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) @-rm -f cif2cbf_packed.cbf makecbf.cbf \ cif2cbf_packed.cbf img2cif_packed.cbf \ cif2cbf_canonical.cbf img2cif_canonical.cbf @-rm -f testrealout.cbf testflatout.cbf testflatpackedout.cbf \ cif2cbf_encp.cbf img2cif_canonical.cif img2cif_packed.cif 9ins.cbf pycbftests: $(PYCBF)/_pycbf.$(PYCBFEXT) (cd $(PYCBF); python pycbf_test1.py) (cd $(PYCBF); python pycbf_test2.py) (cd $(PYCBF); python pycbf_test3.py) javatests: $(BIN)/ctestcbf $(BIN)/testcbf.class $(SOLIB)/libcbf_wrap.so $(BIN)/ctestcbf > testcbfc.txt $(LDPREFIX) java -cp $(JCBF)/cbflib-$(VERSION).jar:$(BIN) testcbf > testcbfj.txt $(DIFF) testcbfc.txt testcbfj.txt dectristests: $(BIN)/cbf_template_t $(DECTRIS_EXAMPLES)/cbf_test_orig.out (cd $(DECTRIS_EXAMPLES); ../../bin/cbf_template_t; diff -a -u cbf_test_orig.out cbf_template_t.out) # # Remove all non-source files # empty: @-rm -f $(LIB)/*.o @-rm -f $(LIB)/libcbf.a @-rm -f $(LIB)/libfcb.a @-rm -f $(LIB)/libimg.a @-rm -f $(LIB)/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/build/*/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/build/src/cbf_simple.o @-rm -f $(PYCBF)/build/*/pycbf_wrap.o @-rm -rf $(BIN)/adscimg2cbf* @-rm -rf $(BIN)/cbf2adscimg* @-rm -rf $(BIN)/makecbf* @-rm -rf $(BIN)/img2cif* @-rm -rf $(BIN)/cif2cbf* @-rm -rf $(BIN)/convert_image* @-rm -rf $(BIN)/convert_minicbf* @-rm -rf $(BIN)/test_fcb_read_image* @-rm -rf $(BIN)/test_xds_binary* @-rm -rf $(BIN)/testcell* @-rm -rf $(BIN)/cif2c* @-rm -rf $(BIN)/testreals* @-rm -rf $(BIN)/testflat* @-rm -rf $(BIN)/testflatpacked* @-rm -rf $(BIN)/cbf_template_t* @-rm -rf $(BIN)/sauter_test* @-rm -rf $(BIN)/arvai_test* @-rm -rf $(BIN)/changtestcompression* @-rm -rf $(BIN)/tiff2cbf* @-rm -f makecbf.cbf @-rm -f img2cif_packed.cif @-rm -f img2cif_canonical.cif @-rm -f img2cif_packed.cbf @-rm -f img2cif_canonical.cbf @-rm -f img2cif_raw.cbf @-rm -f cif2cbf_packed.cbf @-rm -f cif2cbf_canonical.cbf @-rm -f converted.cbf @-rm -f adscconverted.cbf @-rm -f converted_flat.cbf @-rm -f adscconverted_flat.cbf @-rm -f adscconverted_flat_rev.cbf @-rm -f mb_LP_1_001.cbf @-rm -f cif2cbf_ehcn.cif @-rm -f cif2cbf_encp.cbf @-rm -f 9ins.cbf @-rm -f 9ins.cif @-rm -f testcell.prt @-rm -f example.mar2300 @-rm -f converted_orig.cbf @-rm -f adscconverted_orig.cbf @-rm -f converted_flat_orig.cbf @-rm -f adscconverted_flat_orig.cbf @-rm -f adscconverted_flat_rev_orig.cbf @-rm -f mb_LP_1_001_orig.cbf @-rm -f insulin_pilatus6mconverted_orig.cbf @-rm -f insulin_pilatus6mconverted.cbf @-rm -f insulin_pilatus6m.cbf @-rm -f testrealin.cbf @-rm -f testrealout.cbf @-rm -f testflatin.cbf @-rm -f testflatout.cbf @-rm -f testflatpackedin.cbf @-rm -f testflatpackedout.cbf @-rm -f CTC.cbf @-rm -f test_fcb_read_testflatout.out @-rm -f test_fcb_read_testflatpackedout.out @-rm -f test_xds_bin_testflatpackedout.out @-rm -f test_xds_bin_testflatout.out @-rm -f test_fcb_read_testflatout_orig.out @-rm -f test_fcb_read_testflatpackedout_orig.out @-rm -f test_xds_bin_testflatpackedout_orig.out @-rm -f test_xds_bin_testflatout_orig.out @-rm -f mb_LP_1_001.img @-rm -f 9ins.cif @-rm -f testcell_orig.prt @-rm -f $(DECTRIS_EXAMPLES)/cbf_template_t.out @-rm -f XRD1621.cbf @-rm -f XRD1621_orig.cbf @-rm -f XRD1621_orig.cbf @-rm -f XRD1621_I4encbC100.cbf @-rm -f $(SRC)/fcb_exit_binary.f90 @-rm -f $(SRC)/fcb_next_binary.f90 @-rm -f $(SRC)/fcb_open_cifin.f90 @-rm -f $(SRC)/fcb_packed.f90 @-rm -f $(SRC)/fcb_read_bits.f90 @-rm -f $(SRC)/fcb_read_image.f90 @-rm -f $(SRC)/fcb_read_xds_i2.f90 @-rm -f $(EXAMPLES)/test_fcb_read_image.f90 @-rm -f $(EXAMPLES)/test_xds_binary.f90 @-rm -f symlinksdone @-rm -f $(TESTOUTPUT) *$(SEXT) @-rm -f $(SOLIB)/*.o @-rm -f $(SOLIB)/libcbf_wrap.so @-rm -f $(SOLIB)/libjcbf.so @-rm -f $(SOLIB)/libimg.so @-rm -f $(SOLIB)/libfcb.so @-rm -rf $(JCBF)/org @-rm -f $(JCBF)/*.java @-rm -f $(JCBF)/jcbf_wrap.c @-rm -f $(SRC)/cbf_wrap.c @-rm -f $(BIN)/ctestcbf $(BIN)/testcbf.class testcbfc.txt testcbfj.txt @-rm -rf $(REGEX) @-rm -rf $(TIFF) ./.undosymlinks # # Remove temporary files # clean: @-rm -f core @-rm -f *.o @-rm -f *.u # # Restore to distribution state # distclean: clean empty # # Create a Tape Archive for distribution # tar: $(DOCUMENTS) $(SOURCE) $(SRC)/cbf.stx $(HEADERS) $(M4FILES)\ $(EXAMPLES) \ README.html README Makefile \ $(JPEGS) -/bin/rm -f CBFlib.tar* tar cvBf CBFlib.tar \ $(DOCUMENTS) $(SOURCE) $(SRC)/cbf.stx $(HEADERS) $(M4FILES)\ $(EXAMPLES) \ README.html README Makefile \ $(JPEGS) gzip --best CBFlib.tar ./CBFlib-0.9.2.2/drel-ply/0000755000076500007650000000000011603703065013333 5ustar yayayaya./CBFlib-0.9.2.2/drel-ply/CVS/0000755000076500007650000000000011603703070013762 5ustar yayayaya./CBFlib-0.9.2.2/drel-ply/CVS/Root0000644000076500007650000000005611603702115014630 0ustar yayayaya:ext:yaya@blondie.dowling.edu:/cvsroot/cbflib ./CBFlib-0.9.2.2/drel-ply/CVS/Repository0000644000076500007650000000003611603702115016062 0ustar yayayayaCBFlib_bleeding_edge/drel-ply ./CBFlib-0.9.2.2/drel-ply/CVS/Entries.Log0000644000076500007650000000004611603702115016035 0ustar yayayayaA D/PyCifRW-3.1.2//// A D/ply-2.5//// ./CBFlib-0.9.2.2/drel-ply/CVS/Entries0000644000076500007650000000053611603702115015321 0ustar yayayaya/TestDrel.py/1.1/Tue Feb 24 04:35:34 2009// /drel_lex.py/1.1/Tue Feb 24 04:35:34 2009// /drel_yacc.py/1.1/Wed Feb 25 18:23:13 2009// /gu.py/1.1/Wed Feb 25 18:23:13 2009// /method_expression/1.1/Wed Feb 25 18:23:13 2009// /method_output/1.1/Wed Feb 25 18:23:13 2009// /testdic/1.1/Wed Feb 25 18:23:13 2009// /testdic2/1.1/Wed Feb 25 18:23:13 2009// D ./CBFlib-0.9.2.2/drel-ply/drel-gu.py0000644000076500007650000000306311603702115015241 0ustar yayayaya#!/usr/bin/python import drel_lex import drel_yacc import sys import CifFile import StarFile class Process: def execute_method(self): #create our lexer and parser self.lexer = drel_lex.lexer self.parser = drel_yacc.parser #use a simple dictionary self.testdic = CifFile.CifDic("dict/cif_short.dic") self.testdic.diclang = "DDLm" self.testblock = CifFile.CifFile("tests/c2ctest5.cif") ["c2ctest5"] #create the global namespace self.namespace = self.testblock.keys() self.namespace = dict(map(None,self.namespace,self.namespace)) self.parser.loopable_cats = ["import"] self.parser.special_id = [self.namespace] self.parser.withtable = {} self.parser.target_id = None self.parser.indent = "" #get valuename from cmdline valuename = sys.argv[1] f = open("method_expression") expression = f.readline() str_list = [] str_list.append(expression) while expression: expression = f.readline() str_list.append(expression) expression = "".join(str_list) self.parser.target_id = valuename res = self.parser.parse(expression + "\n", lexer=self.lexer) realfunc = drel_yacc.make_func(res, "myfunc", valuename) print "Compiling dREL....." exec realfunc realres = myfunc(self.testdic,self.testblock) print "Generated value: %s" % realres fout = open("method_output", 'w') print>>fout, realres #method returns realres as the value that would be missing #for validation #failUnless(realres == value) p = Process() p.execute_method() ./CBFlib-0.9.2.2/drel-ply/method_expression0000644000076500007650000000045111603702115017010 0ustar yayayaya With v as cell_vector _cell.volume = v.a * ( v.b ^ v.c ) ./CBFlib-0.9.2.2/drel-ply/drel_lex.py0000644000076500007650000000705711603702115015507 0ustar yayayaya#Attempt to implement dREL using PLY (Python Lex Yacc) import ply.lex as lex import re #for multiline flag tokens = ( 'SHORTSTRING', 'LONGSTRING', 'INTEGER', 'BININT', 'HEXINT', 'OCTINT', 'REAL', 'POWER', 'ISEQUAL', 'NEQ', 'GTE', 'LTE', 'IMAGINARY', 'ID', #variable name 'ITEM_TAG', #cif item as variable 'COMMENT', 'STRPREFIX', 'ELLIPSIS', 'AND', 'OR', 'IN', 'NOT', 'DO', 'FOR', 'LOOP', 'AS', 'WITH', 'WHERE', 'ELSE', 'BREAK', 'NEXT', 'IF', 'SWITCH', 'CASE', 'DEFAULT', 'AUGOP', 'PRINT', 'FUNCTION' ) literals = '+*-/;()[],:^<>{}=.`' t_ignore = ' \t\n' def t_error(t): print 'Illegal character %s' % repr(t.value[0]) t_POWER = r'\*\*' t_ISEQUAL = r'==' t_NEQ = r'!=' t_GTE = r'>=' t_LTE = r'<=' t_ELLIPSIS = r'\.\.\.' def t_AUGOP(t): r'(\+\+=)|(\+=)|(-=)|(\*=)|(/=)' return t # Do the reals before the integers, otherwise the integer will # match the first part of the real # def t_IMAGINARY(t): r'(((([0-9]+[.][0-9]*)|([.][0-9]+))([Ee][+-]?[0-9]+)?)|([0-9]+))[jJ]' return t def t_REAL(t): r'(([0-9]+[.][0-9]*)|([.][0-9]+))([Ee][+-]?[0-9]+)?' try: value = float(t.value) except ValueError: print 'Error converting %s to real' % t.value return t # Do the binary,octal etc before decimal integer otherwise the 0 at # the front will match the decimal integer 0 # def t_BININT(t): r'0[bB][0-1]+' try: t.value = `int(t.value[2:],base=2)` except ValueError: print 'Unable to convert binary value %s' % t.value return t def t_OCTINT(t): r'0[oO][0-7]+' try: t.value = `int(t.value[2:],base=8)` except ValueError: print 'Unable to convert octal value %s' % t.value return t def t_HEXINT(t): r'0[xX][0-9a-fA-F]+' try: t.value = `int(t.value,base=16)` except ValueError: print 'Unable to convert hex value %s' % t.value return t def t_INTEGER(t): r'[0-9]+' try: value = int(t.value) except ValueError: print 'Incorrect integer value %s' % t.value return t def t_STRPREFIX(t): r'r(?=["\'])|u(?=["\'])|R(?=["\'])|U(?=["\'])|ur(?=["\'])|UR(?=["\'])|Ur(?=["\'])|uR(?=["\'])' return t # try longstring first as otherwise the '' will match a shortstring def t_LONGSTRING(t): r"('''([^\\]|(\\.))*''')|(\"\"\"([^\\]|(\\.))*\"\"\")" return t def t_SHORTSTRING(t): r"('([^'\n]|(\\.))*')|(\"([^\"\n]|(\\.))*\")" return t reserved = { 'and': 'AND', 'or': 'OR', 'in': 'IN', 'not': 'NOT', 'do': 'DO', 'Do': 'DO', 'for': 'FOR', 'For': 'FOR', 'loop': 'LOOP', 'Loop': 'LOOP', 'as': 'AS', 'with': 'WITH', 'With': 'WITH', 'where': 'WHERE', 'Where': 'WHERE', 'else': 'ELSE', 'Else': 'ELSE', 'Next': 'NEXT', 'next' : 'NEXT', 'break': 'BREAK', 'if': 'IF', 'If': 'IF', 'switch': 'SWITCH', 'case' : 'CASE', 'Function' : 'FUNCTION', 'function' : 'FUNCTION', 'Print' : 'PRINT', 'print' : 'PRINT', 'default' : 'DEFAULT' } def t_ID(t): r'[a-zA-Z][a-zA-Z0-9_$]*' t.type = reserved.get(t.value,'ID') if t.type == 'NEXT': t.value = 'continue' return t # Item tags can have periods and underscores inside, and must have # at least one of them at the front def t_ITEM_TAG(t): r'_[a-zA-Z_.]+' return t def t_COMMENT(t): r'\#.*' pass lexer = lex.lex(reflags=re.MULTILINE) if __name__ == "__main__": lex.runmain(lexer) ./CBFlib-0.9.2.2/drel-ply/testdic20000755000076500007650000000560711603702115015005 0ustar yayayaya############################################################################## # # # PROTOTYPE DDL DICTIONARY # # # ############################################################################## data_TEST_DIC _dictionary.title TEST_DIC _dictionary.class Attribute _dictionary.version 3.7.06 _dictionary.date 2007-03-18 _dictionary.uri www.iucr.org/cif/dic/ddl.dic _dictionary.ddl_conformance 3.7.06 _dictionary.namespace DdlDic _description.text ; This dictionary contains the definitions of attributes that make up the DDLm dictionary definition language. It provides the meta meta data for all CIF dictionaries. ; save_TEST_ATTR _definition.id test_attr _definition.scope Category _definition.class Head _definition.update 2006-12-05 _description.text ; This category is parent of all other categories in the DDLm dictionary. ; save_ #------------------------------------------------------------------------------- save_POSITION _definition.id position _category.id position _category_key.generic '_position.object_id' _definition.scope Category save_ save_position.number _definition.id '_position.number' _name.category_id position _name.object_id number _type.container Single _type.contents Integer _type.purpose Index save_ save_position.object_id _definition.id '_position.object_id' _name.category_id position _name.object_id object_id _type.container Single _type.contents Uchar save_ save_position.vector_xyz _definition.id '_position.vector_xyz' _name.category_id position _name.object_id vector_xyz _type.container Array _type.contents Real _type.dimension [3] save_ save_GEOM _definition.id geom _category.id geom _definition.scope Category save_ save_geom.vertex1_id _definition.id '_geom.vertex1_id' _name.category_id geom _name.object_id vertex1_id _name.linked_item_id '_position.object_id' _type.container Single _type.contents Uchar save_ save_geom.vertex2_id _definition.id '_geom.vertex2_id' _name.category_id geom _name.object_id vertex2_id _name.linked_item_id '_position.object_id' _type.container Single _type.contents Uchar save_ save_geom.vertex3_id _definition.id '_geom.vertex3_id' _name.category_id geom _name.object_id vertex3_id _name.linked_item_id '_position.object_id' _type.container Single _type.contents Uchar save_ ./CBFlib-0.9.2.2/drel-ply/TestDrel.py0000644000076500007650000003325711603702115015440 0ustar yayayaya# Test suite for the dRel parser # import unittest import drel_lex import drel_yacc import CifFile import StarFile # Test simple statements class SimpleStatementTestCase(unittest.TestCase): def setUp(self): #create our lexer and parser self.lexer = drel_lex.lexer self.parser = drel_yacc.parser # as we disallow simple expressions on a separate line to avoid a # reduce/reduce conflict for identifiers, we need at least an # assignment statement def testrealnum(self): """test parsing of real numbers""" res = self.parser.parse('a=5.45\n',debug=True,lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc","a",have_sn=False) exec realfunc self.failUnless(myfunc(self,self)==5.45) res = self.parser.parse('a=.45e-24\n',debug=True,lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc","a",have_sn=False) exec realfunc self.failUnless(myfunc(self,self) ==.45e-24) def testinteger(self): """test parsing an integer""" resm = [0,0,0,0] checkm = [1230,77,5,473] resm[0] = self.parser.parse('a = 1230\n',lexer=self.lexer) resm[1] = self.parser.parse('a = 0x4D\n',lexer=self.lexer) resm[2] = self.parser.parse('a = 0B0101\n',lexer=self.lexer) resm[3] = self.parser.parse('a = 0o731\n',lexer=self.lexer) for res,check in zip(resm,checkm): realfunc = drel_yacc.make_func(res,"myfunc","a",have_sn=False) exec realfunc self.failUnless(myfunc(self,self) == check) def testcomplex(self): """test parsing a complex number""" resc = self.parser.parse('a = 13.45j\n',lexer=self.lexer) realfunc = drel_yacc.make_func(resc,"myfunc","a",have_sn=False) exec realfunc self.failUnless(myfunc(self,self) == 13.45j) def testshortstring(self): """test parsing a one-line string""" jk = "a = \"my pink pony's mane\"" jl = "a = 'my pink pony\"s mane'" ress = self.parser.parse(jk+"\n",lexer=self.lexer) resr = self.parser.parse(jl+"\n",lexer=self.lexer) realfunc = drel_yacc.make_func(ress,"myfunc","a",have_sn=False) exec realfunc self.failUnless(myfunc(self,self) == jk[5:-1]) realfunc = drel_yacc.make_func(resr,"myfunc","a",have_sn=False) exec realfunc self.failUnless(myfunc(self,self) == jl[5:-1]) # # This fails due to extra indentation introduced when constructing the # enclosing function # def testlongstring(self): """test parsing multi-line strings""" jk = '''a = """ a long string la la la '"' some more end"""''' jl = """a = ''' a long string la la la '"' some more end'''""" ress = self.parser.parse(jk+"\n",lexer=self.lexer) resr = self.parser.parse(jl+"\n",lexer=self.lexer) realfunc = drel_yacc.make_func(ress,"myfunc","a",have_sn=False) exec realfunc self.failUnless(myfunc(self,self) == jk[7:-3]) realfunc = drel_yacc.make_func(resr,"myfunc","a",have_sn=False) exec realfunc self.failUnless(myfunc(self,self) == jl[7:-3]) def testmathexpr(self): """test simple maths expressions """ testexpr = (("a = 5.45 + 23.6e05",5.45+23.6e05), ("a = 11 - 45",11-45), ("a = 45.6 / 22.2",45.6/22.2)) for test,check in testexpr: res = self.parser.parse(test+"\n",lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc","a",have_sn=False) exec realfunc self.failUnless(myfunc(self,self) == check) def testexprlist(self): """test comma-separated expressions""" test = "a = 5,6,7+8.5e2" res = self.parser.parse(test+"\n",lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc","a",have_sn=False) exec realfunc self.failUnless(myfunc(self,self) ==(5,6,7+8.5e2)) def testparen(self): """test parentheses""" test = "a = ('once', 'upon', 6,7j +.5e2)" res = self.parser.parse(test+"\n",lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc","a",have_sn=False) exec realfunc self.failUnless(myfunc(self,self) ==('once' , 'upon' , 6 , 7j + .5e2 )) def testlists(self): """test list parsing""" test = "a = ['once', 'upon', 6,7j +.5e2]" res = self.parser.parse(test+"\n",lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc","a",have_sn=False) exec realfunc self.failUnless(myfunc(self,self) ==['once' , 'upon' , 6 , 7j + .5e2 ]) class MoreComplexTestCase(unittest.TestCase): def setUp(self): #create our lexer and parser self.lexer = drel_lex.lexer self.parser = drel_yacc.parser self.parser.withtable = {} self.parser.special_id = [] self.parser.target_id = None self.parser.indent = "" def testassignment(self): """Test that an assignment works""" teststrg = "n = 11" res = self.parser.parse(teststrg,lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc","n",have_sn=False) exec realfunc self.failUnless(myfunc(self,self)==11) def test_do_stmt(self): """Test how a do statement comes out""" teststrg = """ total = 0 do jkl = 0,20,2 { total = total + jkl } do emm = 1,5 { total = total + emm } """ res = self.parser.parse(teststrg + "\n",lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc","total",have_sn=False) exec realfunc realres = myfunc(self,self) # Do statements are inclusive print "Do statement returns %d" % realres self.failUnless(realres==125) print res def test_do_stmt_2(self): """Test how another do statement comes out""" teststrg = """ pp = 0 geom_hbond = [(1,2),(2,3),(3,4)] do i= 0,1 { l,s = geom_hbond [i] pp += s } """ self.parser.special_id = [{'axy':1}] res = self.parser.parse(teststrg + "\n",debug=True,lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc","pp",have_sn=False) exec realfunc realres = myfunc(self,self) # Do statements are inclusive print "Do statement returns %d" % realres self.failUnless(realres==5) print res def test_nested_stmt(self): """Test how a nested do statement prints""" teststrg = """ total = 0 othertotal = 0 do jkl = 0,20,2 { total = total + jkl do emm = 1,5 { othertotal = othertotal + 1 } } end_of_loop = -25.6 """ res = self.parser.parse(teststrg + "\n",lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc","othertotal,total",have_sn=False) print "Nested do:\n" + realfunc exec realfunc othertotal,total = myfunc(self,self) print "nested do returns %d, %d" % (othertotal,total) self.failUnless(othertotal==55) self.failUnless(total==110) def test_if_stmt(self): """test parsing of if statement""" teststrg = """ dmin = 5.0 d1 = 4.0 rad1 = 2.2 radius_bond = 2.0 If (d1(rad1+radius_bond)) b = 5 """ res = self.parser.parse(teststrg + "\n",lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc","b",have_sn=False) exec realfunc b = myfunc(self,self) print "if returns %d" % b self.failUnless(b==5) # We don't test the return value until we have a way to actually access it! def test_fancy_assign(self): """Test fancy assignment""" teststrg = """ a = [2,3,4] b = 3 c= 4 do jkl = 1,5,1 { geom_angle( .id = Tuple(a,b,c), .distances = Tuple(b,c), .value = jkl) } """ self.parser.target_id = "geom_angle" res = self.parser.parse(teststrg + "\n",debug=True,lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc",None,cat_meth = True,have_sn=False) print "Fancy assign: %s" % res[0] exec realfunc b = myfunc(self,self) print "Geom_angle.angle = %s" % b['geom_angle.value'] self.failUnless(b['geom_angle.value']==[1,2,3,4]) def test_tables(self): """Test that tables are parsed correctly""" teststrg = """ jk = Table() jk['bx'] = 25 """ print "Table test:" res = self.parser.parse(teststrg+"\n",debug=True,lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc","jk",have_sn=False) print "Table: %s" % `res[0]` exec realfunc b = myfunc(self,self) self.failUnless(b['bx']==25) class WithDictTestCase(unittest.TestCase): """Now test flow control which requires a dictionary present""" def setUp(self): #create our lexer and parser self.lexer = drel_lex.lexer self.parser = drel_yacc.parser #use a simple dictionary self.testdic = CifFile.CifDic("testdic") self.testblock = CifFile.CifFile("testdic")["DDL_DIC"] #create the global namespace self.namespace = self.testblock.keys() self.namespace = dict(map(None,self.namespace,self.namespace)) self.parser.special_id = [self.namespace] self.parser.withtable = {} self.parser.target_id = None self.parser.indent = "" def test_with_stmt(self): """Test what comes out of a simple flow statement, including multiple with statements""" teststrg = """ with p as description with q as dictionary { x = 22 j = 25 jj = q.date px = p.text _dictionary.date = "2007-04-01" }""" self.parser.loopable_cats = [] #category dictionary is not looped self.parser.target_id = '_dictionary.date' res = self.parser.parse(teststrg+"\n",lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc",None) print "With statement -> \n" + realfunc exec realfunc newdate = myfunc(self.testdic,self.testblock) print 'date now %s' % newdate self.failUnless(newdate == "2007-04-01") def test_loop_statement(self): """Test proper processing of loop statements""" teststrg = """ n = 0 loop p as dictionary_audit n += 1 _symmetry.ops = n """ self.parser.loopable_cats = ['dictionary_audit'] #category dictionary is not looped self.parser.target_id = '_symmetry.ops' res = self.parser.parse(teststrg+"\n",lexer=self.lexer,debug=1) realfunc = drel_yacc.make_func(res,"myfunc",None) print "Loop statement -> \n" + realfunc exec realfunc symops = myfunc(self.testdic,self.testblock) print 'symops now %d' % symops self.failUnless(symops == 81) def test_functions(self): """Test that functions are converted correctly""" struct_testdic = CifFile.CifFile("cif_core.dic", grammar="DDLm") struct_testblock = struct_testdic["CIF_CORE"] self.parser.loopable_cats = ["import"] #category import is looped self.parser.target_id = "_import_list.id" self.parser.withtable = {} teststrg = """ with i as import _import_list.id = List([i.scope, i.block, i.file, i.if_dupl, i.if_miss]) """ res = self.parser.parse(teststrg+"\n",lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc",None) print "With statement -> \n" + realfunc exec realfunc retval = myfunc(self.testdic,struct_testblock,3) self.failUnless(retval == StarFile.StarList(["dic","CORE_MODEL","core_model.dic","exit","exit"])) def test_attributes(self): """Test that attributes of complex expressions come out OK""" # We need to do a scary funky attribute of a key lookup ourdic = CifFile.CifDic("testdic2") testblock = CifFile.CifFile("test_data.cif")["testdata"] self.parser.loopable_cats = ['geom','position'] # teststrg = """ LineList = [] PointList = [] With p as position Loop g as geom { If (g.type == "point") { PointList += Tuple(g.vertex1_id,p[g.vertex1_id].vector_xyz) } #Else if (g.type == "line") { # LineList ++= Tuple(Tuple(g.vertex1_id, g.vertex2_id), # Tuple(p[g.vertex1_id].vector_xyz, # p[g.vertex2_id].vector_xyz)) #} } """ self.parser.target_id = 'PointList' res = self.parser.parse(teststrg+"\n",lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc","PointList") print "Function -> \n" + realfunc exec realfunc retval = myfunc(ourdic,testblock,"LineList") print "testdic2 return value" + `retval` print "Value for comparison with docs: %s" % `retval[0]` def test_funcdef(self): """Test function conversion""" teststrg = """ function Closest( v :[Array, Real], # coord vector to be cell translated w :[Array, Real]) { # target vector d = v - w t = Int( Mod( 99.5 + d, 1.0 ) - d ) Closest = Tuple ( v+t, t ) } """ self.parser.target_id = 'Closest' res,ww = self.parser.parse(teststrg+"\n",lexer=self.lexer) print "Function -> \n" + res exec res retval = Closest(0.2,0.8) print 'Closest 0.2,0.8 returns ' + ",".join([`retval[0]`,`retval[1]`]) self.failUnless(retval == StarFile.StarTuple(1.2,1)) if __name__=='__main__': unittest.main() ./CBFlib-0.9.2.2/drel-ply/testdic0000755000076500007650000017542211603702115014726 0ustar yayayaya############################################################################## # # # PROTOTYPE DDL DICTIONARY # # # ############################################################################## data_DDL_DIC _dictionary.title DDL_DIC _dictionary.class Attribute _dictionary.version 3.7.06 _dictionary.date 2007-03-18 _dictionary.uri www.iucr.org/cif/dic/ddl.dic _dictionary.ddl_conformance 3.7.06 _dictionary.namespace DdlDic _description.text ; This dictionary contains the definitions of attributes that make up the DDLm dictionary definition language. It provides the meta meta data for all CIF dictionaries. ; save_DDL_ATTR _definition.id ddl_attr _definition.scope Category _definition.class Head _definition.update 2006-12-05 _description.text ; This category is parent of all other categories in the DDLm dictionary. ; save_ #------------------------------------------------------------------------------- save_ALIAS _definition.id alias _definition.scope Category _definition.class List _definition.update 2007-02-06 _description.text ; The attributes used to specify the aliased names of definitions. ; _category.parent_id ddl_attr _category_key.generic '_alias.definition_id' save_ save_alias.definition_id _definition.id '_alias.definition_id' _definition.class Attribute _definition.update 2006-11-16 _description.text ; Identifier tag of an aliased definition. ; _name.category_id alias _name.object_id definition_id _type.purpose Key _type.container Single _type.contents Tag save_ save_alias.dictionary_uri _definition.id '_alias.dictionary_uri' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Dictionary URI in which the aliased definition belongs. ; _name.category_id alias _name.object_id dictionary_uri _type.purpose Identify _type.container Single _type.contents Uri save_ #---------------------------------------------------------------------------- save_CATEGORY _definition.id category _definition.scope Category _definition.class Set _definition.update 2006-11-16 _description.text ; The attributes used to specify the properties of a "category" of data items. ; _category.parent_id ddl_attr save_ save_category.parent_id _definition.id '_category.parent_id' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The definition id of the category which is a higher member of the organisational hierarchy than the current category definition. ; _name.category_id category _name.object_id parent_id _type.purpose Identify _type.container Single _type.contents Tag save_ save_category.parent_join _definition.id '_category.parent_join' _definition.update 2006-12-21 _definition.class Attribute _description.text ; Yes or No flag indication if a category-list may be merged at instantiation with its parent category. Note that category-sets may always be merged with the parent category. ; _name.category_id category _name.object_id parent_join _type.purpose Identify _type.container Single _type.contents YesorNo _enumeration.default No save_ #---------------------------------------------------------------------------- save_CATEGORY_KEY _definition.id category_key _definition.scope Category _definition.class Set _definition.update 2006-11-16 _description.text ; Attributes used to specify the access keys of List categories. ; _category.parent_id category save_ save_category_key.generic _definition.id '_category_key.generic' _definition.update 2007-02-08 _definition.class Attribute _description.text ; Tag of a data item in a List category which is the generic key to access other items in the category. The value of this item must be unique in order to provide unambiguous access to a packet (row) in the table of values. ; _name.category_id category_key _name.object_id generic _type.purpose Identify _type.container Single _type.contents Tag save_ save_category_key.primitive _definition.id '_category_key.primitive' _definition.update 2007-02-08 _definition.class Attribute _description.text ; Tuple of the data item (or data items) in a List category which form the primitive composite key to access other items in the category. The value of this tuple must be unique to provide unambiguous access to a packet (row) in the table of values. ; _name.category_id category_key _name.object_id primitive _type.purpose Identify _type.container Tuple _type.contents Tag _type.dimension [1:] save_ #----------------------------------------------------------------------------- save_CATEGORY_MANDATORY _definition.id category_mandatory _definition.scope Category _definition.class List _definition.update 2007-02-06 _description.text ; The attributes used to specify the properties of a "category_mandatory" of data items. ; _category.parent_id category _category_key.generic '_category_mandatory.item_id' save_ save_category_mandatory.item_id _definition.id '_category_mandatory.item_id' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The data name of an item in this category which must exist within a data file if any item within this category appears. ; _name.category_id category_mandatory _name.object_id item_id _type.purpose Key _type.container Single _type.contents Tag save_ #---------------------------------------------------------------------------- save_DEFINITION _definition.id definition _definition.scope Category _definition.class Set _definition.update 2006-11-16 _description.text ; The attributes for classifying dictionary definitions. ; _category.parent_id ddl_attr save_ save_definition.class _definition.id '_definition.class' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The nature and the function of a definition or definitions. ; _name.category_id definition _name.object_id class _type.purpose State _type.container Single _type.contents Code loop_ _enumeration_set.state _enumeration_set.detail Audit ; Item used to IDENTIFY and AUDIT dictionary properties only. ; Attribute ; Item used as an attribute in the definition of other data items. Applied in dictionaries only. ; Head ; Category of items that is the parent of all other categories in the dictionary. ; List ; Category of items that in a data file must reside in a looped list with a key item defined. ; Set ; Category of items that form a set (but not a loopable list). These items may be referenced as a class of items in a dREL methods expression. ; Datum ; Item in a domain-specific dictionary. These items appear in data files. ; Transient ; Definition saveframes specifying the attributes, enumeration values and functions used in dictionary definitions. These tags are ONLY used in dictionary definitions. ; _enumeration.default Datum save_ save_definition.id _definition.id '_definition.id' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Identifier name of the definition contained within a save frame. ; _name.category_id definition _name.object_id id _type.purpose Identify _type.container Single _type.contents Tag save_ save_definition.scope _definition.id '_definition.scope' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The extent to which a definition affects other definitions. ; _name.category_id definition _name.object_id scope _type.purpose State _type.container Single _type.contents Code loop_ _enumeration_set.state _enumeration_set.detail Dictionary "applies to all defined items in the dictionary" Category "applies to all defined items in the category" Item "applies to a single item definition" _enumeration.default Item save_ save_definition.update _definition.id '_definition.update' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The date that a definition was last changed. ; _name.category_id definition _name.object_id update _type.purpose Audit _type.container Single _type.contents Date save_ save_definition.xref_code _definition.id '_definition.xref_code' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Code identifying the equivalent definition in the dictionary referenced by the DICTIONARY_XREF attributes. ; _name.category_id definition _name.object_id xref_code _type.purpose Identify _type.container Single _type.contents Code save_ #---------------------------------------------------------------------------- save_DESCRIPTION _definition.id description _definition.scope Category _definition.class Set _definition.update 2006-11-16 _description.text ; The attributes of descriptive (non-machine parseable) parts of definitions. ; _category.parent_id ddl_attr save_ save_description.key_words _definition.id '_description.key_words' _definition.update 2006-11-16 _definition.class Attribute _description.text ; List of key-words categorising the item. ; _description.common 'key words' _name.category_id description _name.object_id key_words _type.purpose Describe _type.container List _type.contents Code save_ save_description.common _definition.id '_description.common' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Commonly-used identifying name for the item. ; _description.common 'common name' _name.category_id description _name.object_id common _type.purpose Describe _type.container Single _type.contents Text save_ save_description.text _definition.id '_description.text' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The text description of the defined item. ; _description.common 'description' _name.category_id description _name.object_id text _type.purpose Describe _type.container Single _type.contents Text save_ #---------------------------------------------------------------------------- save_DESCRIPTION_EXAMPLE _definition.id description_example _definition.scope Category _definition.class List _definition.update 2007-02-06 _description.text ; The attributes of descriptive (non-machine parseable) examples of values of the defined items. ; _category.parent_id description _category_key.generic '_description_example.case' save_ save_description_example.case _definition.id '_description_example.case' _definition.update 2006-11-16 _definition.class Attribute _description.text ; An example case of the defined item. ; _name.category_id description_example _name.object_id case _type.purpose Key _type.container Single _type.contents Text save_ save_description_example.detail _definition.id '_description_example.detail' _definition.update 2006-11-16 _definition.class Attribute _description.text ; A description of an example case for the defined item. ; _name.category_id description_example _name.object_id detail _type.purpose Describe _type.container Single _type.contents Text save_ #---------------------------------------------------------------------------- save_DICTIONARY _definition.id dictionary _definition.scope Category _definition.class Set _definition.update 2006-11-16 _description.text ; Attributes for identifying and registering the dictionary. The items in this category are NOT used as attributes of INDIVIDUAL data items. ; _category.parent_id ddl_attr save_ save_dictionary.class _definition.id '_dictionary.class' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The nature, or field of interest, of data items defined in the dictionary. ; _name.category_id dictionary _name.object_id class _type.purpose State _type.container Single _type.contents Code loop_ _enumeration_set.state _enumeration_set.detail Attribute 'dictionary containing DDL attribute definitions' Instance 'dictionary containing data definitions' Import 'dictionary containing definitions for importation' Function 'dictionary containing method function definitions' _enumeration.default Instance save_ save_dictionary.date _definition.id '_dictionary.date' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The date that the last dictionary revision took place. ; _name.category_id dictionary _name.object_id date _type.purpose Audit _type.container Single _type.contents Date save_ save_dictionary.ddl_conformance _definition.id '_dictionary.ddl_conformance' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The version number of the DDL dictionary that this dictionary conforms to. ; _name.category_id dictionary _name.object_id ddl_conformance _type.purpose Audit _type.container Single _type.contents Version save_ save_dictionary.namespace _definition.id '_dictionary.namespace' _definition.update 2006-12-05 _definition.class Attribute _description.text ; The namespace code that may be prefixed (with a trailing colon ":") to an item tag defined in the defining dictionary when used in particular applications. Because tags must be unique, namespace codes are unlikely to be used data files. ; _name.category_id dictionary _name.object_id namespace _type.purpose Identify _type.container Single _type.contents Code save_ save_dictionary.title _definition.id '_dictionary.title' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The common title of the dictionary. Will usually match the name attached to the data_ statement of the dictionary file. ; _name.category_id dictionary _name.object_id title _type.purpose Identify _type.container Single _type.contents Code save_ save_dictionary.uri _definition.id '_dictionary.uri' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The universal resource indicator of this dictionary. ; _name.category_id dictionary _name.object_id uri _type.purpose Identify _type.container Single _type.contents Uri save_ save_dictionary.version _definition.id '_dictionary.version' _definition.update 2006-11-16 _definition.class Attribute _description.text ; A unique version identifier for the dictionary. ; _name.category_id dictionary _name.object_id version _type.purpose Audit _type.container Single _type.contents Version save_ #---------------------------------------------------------------------------- save_DICTIONARY_AUDIT _definition.id dictionary_audit _definition.scope Category _definition.class List _definition.update 2007-02-06 _description.text ; Attributes for identifying and registering the dictionary. The items in this category are NOT used as attributes of individual data items. ; _category.parent_id dictionary _category_key.generic '_dictionary_audit.version' save_ save_dictionary_audit.date _definition.id '_dictionary_audit.date' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The date of each dictionary revision. ; _name.category_id dictionary_audit _name.object_id date _type.purpose Audit _type.container Single _type.contents Date save_ save_dictionary_audit.revision _definition.id '_dictionary_audit.revision' _definition.update 2006-11-16 _definition.class Attribute _description.text ; A description of the revision applied for the _dictionary_audit.version. ; _name.category_id dictionary_audit _name.object_id revision _type.purpose Describe _type.container Single _type.contents Text save_ save_dictionary_audit.version _definition.id '_dictionary_audit.version' _definition.update 2006-11-16 _definition.class Attribute _description.text ; A unique version identifier for each revision of the dictionary. ; _name.category_id dictionary_audit _name.object_id version _type.purpose Key _type.container Single _type.contents Version save_ #----------------------------------------------------------------------------- save_DICTIONARY_VALID _definition.id dictionary_valid _definition.scope Category _definition.class List _definition.update 2007-02-06 _description.text ; Data items which are used to specify the contents of definitions in the dictionary in terms of the _definition.scope and the required and prohibited attributes. ; _category.parent_id dictionary _category_key.generic '_dictionary_valid.scope' save_ save_dictionary_valid.attributes _definition.id '_dictionary_valid.attributes' _definition.update 2006-11-16 _definition.class Attribute _description.text ; A list of the attribute names and the attribute categories that are either MANDATORY or PROHIBITED for the _definition.scope value specified in the corresponding _dictionary_valid.scope. All unlisted attributes are considered optional. MANDATORY attributes are preceded by a "+" character. PROHIBITED attributes are preceded by a "!" character. RECOMMENDED attributes are preceded by a "." character. ; _name.category_id dictionary_valid _name.object_id attributes _type.purpose Audit _type.container Single _type.contents Text save_ save_dictionary_valid.scope _definition.id '_dictionary_valid.scope' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The _definition.scope code corresponding to the attribute list given in _dictionary_valid.attributes. ; _name.category_id dictionary_valid _name.object_id scope _name.linked_item_id '_definition.scope' _type.purpose Key _type.container Single _type.contents Code loop_ _enumeration_set.state _enumeration_set.detail Dictionary "applies to all defined items in the dictionary" Category "applies to all defined items in the category" Item "applies to a single definition" save_ #----------------------------------------------------------------------------- save_DICTIONARY_XREF _definition.id dictionary_xref _definition.scope Category _definition.class List _definition.update 2007-02-06 _description.text ; Data items which are used to cross reference other dictionaries that have defined the same data items. Data items in this category are NOT used as attributes of individual data items. ; _category.parent_id dictionary _category_key.generic '_dictionary_xref.code' save_ save_dictionary_xref.code _definition.id '_dictionary_xref.code' _definition.update 2006-11-16 _definition.class Attribute _description.text ; A code identifying the cross-referenced dictionary. ; _name.category_id dictionary_xref _name.object_id code _type.purpose Key _type.container Single _type.contents Code save_ save_dictionary_xref.date _definition.id '_dictionary_xref.date' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Date of the cross-referenced dictionary. ; _name.category_id dictionary_xref _name.object_id date _type.purpose Audit _type.container Single _type.contents Date save_ save_dictionary_xref.format _definition.id '_dictionary_xref.format' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Format of the cross referenced dictionary. ; _name.category_id dictionary_xref _name.object_id format _type.purpose Audit _type.container Single _type.contents Text save_ save_dictionary_xref.name _definition.id '_dictionary_xref.name' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The name and description of the cross-referenced dictionary. ; _name.category_id dictionary_xref _name.object_id name _type.purpose Audit _type.container Single _type.contents Text save_ save_dictionary_xref.uri _definition.id '_dictionary_xref.uri' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The source URI of the cross referenced dictionary data. ; _name.category_id dictionary_xref _name.object_id uri _type.purpose Audit _type.container Single _type.contents Uri save_ #---------------------------------------------------------------------------- save_ENUMERATION _definition.id enumeration _definition.scope Category _definition.class Set _definition.update 2006-11-16 _description.text ; The attributes for restricting the values of defined data items. ; _category.parent_id ddl_attr save_ save_enumeration.default _definition.id '_enumeration.default' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The default value for the defined item if it is not specified explicitly. ; _name.category_id enumeration _name.object_id default _type.purpose Limit _type.container Single _type.contents Implied save_ save_enumeration.def_index_id _definition.id '_enumeration.def_index_id' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The data name of the value that is used as an index in the DEFAULTS enumeration list to select the default enumeration value. The value must match one of the _enumeration_default.index values. ; _name.category_id enumeration _name.object_id def_index_id _type.purpose Identify _type.container Single _type.contents Tag save_ save_enumeration.range _definition.id '_enumeration.range' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The inclusive range of values "from:to" allowed for the defined item. ; _name.category_id enumeration _name.object_id range _type.purpose Limit _type.container Single _type.contents Range save_ save_enumeration.mandatory _definition.id '_enumeration.mandatory' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Yes or No flag on whether the enumerate states specified for an item in the current definition (in which item appears) MUST be used on instantiation. ; _name.category_id enumeration _name.object_id mandatory _type.purpose Limit _type.container Single _type.contents YesorNo _enumeration.default Yes save_ #----------------------------------------------------------------------------- save_ENUMERATION_DEFAULT _definition.id enumeration_default _definition.scope Category _definition.class List _definition.update 2007-02-06 _description.text ; List of pre-determined default enumeration values indexed to a data item by the item _enumeration.def_index_id. ; _category.parent_id enumeration _category_key.generic '_enumeration_default.index' save_ save_enumeration_default.index _definition.id '_enumeration_default.index' _definition.update 2006-11-16 _definition.class Attribute _description.text ; A list of possible values for the item _enumeration.def_index_id used to index (select) the enumeration default value from the _enumeration_default.value list. ; _name.category_id enumeration_default _name.object_id index _type.purpose Key _type.container Single _type.contents Code save_ save_enumeration_default.value _definition.id '_enumeration_default.value' _definition.update 2006-11-16 _definition.class Attribute _description.text ; A list of possible default enumeration values for the defined item. This is selected by the _enumeration_default.index value which matches value of the item specified by _enumeration.def_index_id. ; _name.category_id enumeration_default _name.object_id value _type.purpose Limit _type.container Single _type.contents Implied save_ #----------------------------------------------------------------------------- save_ENUMERATION_SET _definition.id enumeration_set _definition.scope Category _definition.class List _definition.update 2007-02-06 _description.text ; Attributes of data items which are used to define a set of unique pre-determined values. ; _category.parent_id enumeration _category_key.generic '_enumeration_set.state' save_ save_enumeration_set.state _definition.id '_enumeration_set.state' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Permitted value state for the defined item. ; _name.category_id enumeration_set _name.object_id state _type.purpose Key _type.container Single _type.contents Code save_ save_enumeration_set.construct _definition.id '_enumeration_set.construct' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The construction rules of the value that the code describes. The code conforms to regular expression (REGEX) specifications. ; _name.category_id enumeration_set _name.object_id construct _type.purpose Limit _type.container Single _type.contents Regex save_ save_enumeration_set.detail _definition.id '_enumeration_set.detail' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The meaning of the code (identified by _enumeration_set.state) in terms of the value of the quantity it describes. ; _name.category_id enumeration_set _name.object_id detail _type.purpose Describe _type.container Single _type.contents Text save_ save_enumeration_set.xref_code _definition.id '_enumeration_set.xref_code' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Identity of the equivalent item in the dictionary referenced by the DICTIONARY_XREF attributes. ; _name.category_id enumeration_set _name.object_id xref_code _type.purpose Identify _type.container Single _type.contents Code save_ save_enumeration_set.xref_dictionary _definition.id '_enumeration_set.xref_dictionary' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Code identifying the dictionary in the DICTIONARY_XREF list. ; _name.category_id enumeration_set _name.object_id xref_dictionary _type.purpose Link _type.container Single _type.contents Code save_ #---------------------------------------------------------------------------- save_IMPORT _definition.id import _definition.scope Category _definition.class List _definition.update 2007-02-06 _description.text ; Used to import the values of specific attributes from other dictionary definitions within and without the current dictionary. ; _category.parent_id ddl_attr _category_key.generic '_import.block' save_ save_import.block _definition.id '_import.block' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Tag of the definition block to be imported with the file specified by _import.file ; _name.category_id import _name.object_id block _type.purpose Key _type.container Single _type.contents Tag loop_ _description_example.case '_atom_site.xyz' 'refln' save_ save_import.file _definition.id '_import.file' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The URI or filename of the file from which the definition block, designated by _import.block, is to be sourced. ; _name.category_id import _name.object_id file _type.purpose Identify _type.container Single _type.contents Uri save_ save_import.if_dupl _definition.id '_import.if_dupl' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Action taken if the definition block requested already exists in the importing dictionary. ; _name.category_id import _name.object_id if_dupl _type.purpose State _type.container Single _type.contents Code loop_ _enumeration_set.state _enumeration_set.detail Ignore 'ignore imported definitions if id conflict' Replace 'replace existing with imported definitions' Exit 'issue error exception and exit' _enumeration.default Exit save_ save_import.if_miss _definition.id '_import.if_miss' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Action taken if the definition block requested is missing from the source dictionary. ; _name.category_id import _name.object_id if_miss _type.purpose State _type.container Single _type.contents Code loop_ _enumeration_set.state _enumeration_set.detail Ignore 'ignore import' Exit 'issue error exception and exit' _enumeration.default Exit save_ save_import.scope _definition.id '_import.scope' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Code signaling the scope of the definition block to be imported. ; _name.category_id import _name.object_id scope _type.purpose State _type.container Single _type.contents Code loop_ _enumeration_set.state _enumeration_set.detail Dic 'all saveframes in the source file' Cat 'all saveframes in the specific category' Grp 'all saveframes in the category with children' Itm 'one saveframe containing an item definition' Att 'import attributes within a saveframe' Sta 'import enumeration state list only' Val 'import enumeration default value list only' save_ #---------------------------------------------------------------------------- save_IMPORT_LIST _definition.id import_list _definition.scope Category _definition.class Set _definition.update 2006-11-16 _description.text ; Used to import the values of specific attributes from other dictionary definitions within and without the current dictionary, as a LIST of attributes. ; _category.parent_id ddl_attr save_ save_import_list.id _definition.id '_import_list.id' _definition.update 2006-11-16 _definition.class AttributeSet _description.text ; A list of the attributes, defined individually in the category IMPORT, used to import definitions from other dictionaries. ; _name.category_id import_list _name.object_id id _type.purpose Import _type.container List _type.contents [Code,Tag,Uri,Code,Code] _type.dimension [5 []*] loop_ _method.purpose _method.expression Definition ; With i as import _import_list.id = List([i.scope, i.block, i.file, i.if_dupl, i.if_miss]) ; save_ #---------------------------------------------------------------------------- save_LOOP _definition.id loop _definition.scope Category _definition.class Set _definition.update 2006-11-16 _description.text ; Attributes for looped lists. ; _category.parent_id ddl_attr save_ save_loop.level _definition.id '_loop.level' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Specifies the level of the loop structure in which a defined item must reside if it used in a looped list. ; _name.category_id loop _name.object_id level _type.purpose Limit _type.container Single _type.contents Index _enumeration.range 1: _enumeration.default 1 save_ #---------------------------------------------------------------------------- save_METHOD _definition.id method _definition.scope Category _definition.class List _definition.update 2007-02-06 _description.text ; Methods used for evaluating, validating and defining items. ; _category.parent_id ddl_attr _category_key.generic '_method.purpose' save_ save_method.purpose _definition.id '_method.purpose' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The purpose and scope of the method expression. ; _name.category_id method _name.object_id purpose _type.purpose State _type.container Single _type.contents Code loop_ _enumeration_set.state _enumeration_set.detail Evaluation "method evaluates an item from related item values" Definition "method generates attribute value(s) in the definition" Validation "method compares an evaluation with existing item value" _enumeration.default Evaluation save_ save_method.expression _definition.id '_method.expression' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The method expression for the defined item. ; _name.category_id method _name.object_id expression _type.purpose Method _type.container Single _type.contents Text save_ #---------------------------------------------------------------------------- save_NAME _definition.id name _definition.scope Category _definition.class Set _definition.update 2006-11-16 _description.text ; Attributes for identifying items and item categories. ; _category.parent_id ddl_attr save_ save_name.object_id _definition.id '_name.object_id' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The object name part of a data tag that is unique within the category or mergable family of categories. ; _name.category_id name _name.object_id object_id _type.purpose Identify _type.container Single _type.contents Otag save_ save_name.category_id _definition.id '_name.category_id' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Name of the category of the defined data item. ; _name.category_id name _name.object_id category_id _type.purpose Identify _type.container Single _type.contents Ctag save_ save_name.linked_item_id _definition.id '_name.linked_item_id' _definition.update 2007-03-18 _definition.class Attribute _description.text ; Name of an equivalent item in another category which has a common set of values. ; _name.category_id name _name.object_id linked_item_id _type.purpose Identify _type.container Single _type.contents Tag save_ #---------------------------------------------------------------------------- save_TYPE _definition.id type _definition.scope Category _definition.class Set _definition.update 2006-11-16 _description.text ; Attributes which specify the 'typing' of data items. ; _category.parent_id ddl_attr save_ save_type.container _definition.id '_type.container' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The CONTAINER type of the defined data item value. ; _name.category_id type _name.object_id container _type.purpose State _type.container Single _type.contents Code loop_ _enumeration_set.state _enumeration_set.detail Single 'a single value' Multiple 'values related by boolean ',|&!*' or range ":" ops' List 'list of values bounded by []; separated by commas' Array 'List of fixed length and dimension' Tuple 'immutable List bounded by (); nested tuples allowed' Table 'key:value elements bounded by {}; separated by commas' Implied 'implied by type.container of associated value' _enumeration.default Single save_ save_type.contents _definition.id '_type.contents' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Used to specify the syntax construction of value elements of the defined object. The syntax is specified in terms of fixed regex constructs that have been enumerated as states. Values with more than one element may be specified as a list of multiple states. Note that this list may contain states related by boolean or range operators. The typing of elements is determined by the replication of the minimum set of states declared. ; _name.category_id type _name.object_id contents _type.purpose State _type.container Multiple _type.contents Code _import_list.id ['sta','type_contents','com_val.dic','exit','exit'] loop_ _description_example.case _description_example.detail 'Integer' 'all elements are integer' 'Real,Code' 'elements are in muliples of real number and codes' 'Real|Code' 'elements are either a real number or a code' save_ save_type.purpose _definition.id '_type.purpose' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The primary purpose or origin of the defined data item. ; _name.category_id type _name.object_id purpose _type.purpose State _type.container Single _type.contents Code loop_ _enumeration_set.state _enumeration_set.detail _enumeration_set.construct Import ; >>> For dictionaries only <<< Used within dictionaries to import definition lines from other dictionaries. In the expanded dictionary the import item is replaced by the imported items. ; Method ; >>> For dictionaries only <<< A text method expression in a dictionary definition relating the defined item to other defined items. ; Audit ; An item used to contain audit information about the creation or conformance of a file. ; Identify An item used to identify another item or file. ; Describe ; A descriptive item intended only for human interpretation. ; Limit ; An item used to limit the values of other items. ; State ; An item with one or more codified values that must exist within a discrete and countable list of enumerated states. ; Key ; An item with a codified value that is the key to identifying specific packets of items in the same category. ; Link ; An item with a value that is a foreign key linking packets in this category list to packets in another category. ; Assigned An item whose value is assigned in the process of modelling measured and observed data items. ; Observed ; An item whose value is determined by observation or deduction. Numerical observed values do NOT have a standard uncertainty. ; Measured ; A numerical item whose value is measured or derived from a measurement. It is expected to have a standard uncertainty value which is either 1) appended as integers in parentheses at the precision of the trailing digits, or 2) as a separate item with the same name as defined item but with a trailing '_su'. ; save_ save_type.dimension _definition.id '_type.dimension' _definition.update 2006-12-05 _definition.class Attribute _description.text ; The dimensions of the list array bounded by square brackets. Each dimension may be expressed simply as an integer giving the maximum index permitted (the minimum is assumed to be 1). * is used to signal unknown number of array elements. Alternately, each dimension may be entered in the form: :. ; _name.category_id type _name.object_id dimension _type.purpose Limit _type.container List _type.contents Index _type_array.dimension [1: []*] loop_ _description_example.case _description_example.detail "[3,3]" 'in Array definition: 3x3 elements' "[6]" 'in List definition: 6 values' "[4[2]]" 'in Tuple defn: 4 Tuples of 2 values' save_ #---------------------------------------------------------------------------- save_UNITS _definition.id units _definition.scope Category _definition.class Set _definition.update 2006-11-16 _description.text ; The attributes for specifying units of measure. ; _category.parent_id ddl_attr save_ save_units.code _definition.id '_units.code' _definition.update 2006-11-16 _definition.class Attribute _description.text ; A code which identifies the units of measurement. ; _name.category_id units _name.object_id code _type.purpose State _type.container Single _type.contents Code _import_list.id ['sta','units_code','com_val.dic','exit','exit'] save_ #============================================================================= # The dictionary's attribute validation criteria and the creation history. #============================================================================ loop_ _dictionary_valid.scope _dictionary_valid.attributes Dictionary ; + _dictionary.title + _dictionary.class + _dictionary.version + _dictionary.date + _dictionary.uri + _dictionary.ddl_conformance + _dictionary.namespace + _dictionary_audit.version + _dictionary_audit.date + _dictionary_audit.revision . _description.text ! ALIAS ! CATEGORY ! DEFINITION ! ENUMERATION ! LOOP ! METHOD ! NAME ! TYPE ! UNITS ; Category ; + _definition.id + _definition.scope + _definition.class + _category.parent_id . _category_key.generic . _category_key.primitive . _category_mandatory.item_id . _description.text ! ALIAS ! DICTIONARY ! ENUMERATION ! IMPORT ! LOOP ! NAME ! TYPE ! UNITS ; Item ; + _definition.id + _definition.scope + _definition.class + _definition.update + _name.object_id + _name.category_id + _type.purpose + _type.container + _type.contents . _description.text . _description.common ! CATEGORY ! DICTIONARY ; loop_ _dictionary_audit.version _dictionary_audit.date _dictionary_audit.revision 3.0 1999-04-06 ; Initial draft of DDL3 based on attributes from DDL1.4 and DDL2.1.1. ; 3.0.1 1999-05-06 ; Added new method attributes and enumeration LIST values ; 3.0.2 1999-05-11 ; Repacked and redefined some definition and dictionary attributes ; 3.0.3 1999-05-12 ; Introduced category.level etc. attributes and rearranged categories ; 3.0.4 1999-05-18 ; Removed category.level, linked.parent, linked.child, category.child_id Changed related.function to include "Parent_Key", "Linked_Key", "Linked_Values" and "Linked_Array" codes. ; 3.0.5 1999-05-22 ; Access keys in category families are inherited. Remove "Linked_Values" for related.function. ; 3.0.6 1999-05-24 ; Add "Su_Implicit" code to related.function. ; 3.0.7 1999-05-25 ; Further simplifications to the syntax. ; 3.0.8 1999-05-27 ; Change _definition.class code DATA_ITEM to ITEM_DEFINITION ; 3.0.9 1999-06-10 ; Add "List" to _type_array.class enumerations. ; 3.0.10 1999-06-11 ; Add various codes to the enumeration lists. ; 3.0.11 1999-06-22 ; Convert all enumeration list data names. ; 3.0.12 1999-06-28 ; Recaste the TYPE attributes and enumerations. ; 3.0.13 1999-07-05 ; Change "pattern" to "function" for TYPE attributes. ; 3.0.14 1999-07-09 ; Change "string" to "container" for TYPE attributes. Change codes for definition.scope and definition.class ; 3.0.15 1999-11-26 ; Add the _definition.update attribute. ; 3.0.16 2000-02-15 ; Change the names of the files to reflect prototype specifications. ; 3.0.17 2000-04-17 ; Add the attributes description.compact and description.abbreviated. ; 3.0.18 2000-05-19 ; Add the definition class TRANSIENT for FUNCTION definitions. ; 3.0.19 2000-06-06 ; Change the definition scope GROUP to Category. Change the definition scope ITEM to SINGLE. Add the definition scope COSET for common definitions. Change type.function to type.purpose. ; 3.0.20 2000-06-07 ; Add the definition for category.coset_id Add the definition for item.coset_id Added the Equivalent code to related.function ; 3.1.00 2000-06-12 ; Reorganised families into category groupings ATTRIBUTES and ENUMERATION ; 3.1.01 2000-06-20 ; Inserted possible method validation scripts ; 3.1.02 2000-06-24 ; MAJOR modifications and additions following discussions with JW. ; 3.1.03 2000-06-26 ; Changes to MODEL attributes and many other changes. ; 3.1.04 2000-06-28 ; Version agreed upon up to JW's return to Rutgers. ; 3.1.05 2000-06-29 ; In method.class change ENUMERATION to EVALUATION. ; 3.1.06 2000-07-03 ; Corrections from running dREL 1.0.3. ; 3.1.07 2000-07-11 ; Add the attribute enumeration.dot. ; 3.1.08 2000-09-13 ; Remove the attribute enumeration.dot. ; 3.1.09 2000-10-09 ; Add the XREF definitions. In type_purpose change 'From:To' to 'Range'; 'Code' to 'State'. In type_container add the enumeration 'Multiple' ; 3.2.00 2000-11-02 ; MAJOR revision and simplification of ALL definitions. Blame PMR! ; 3.2.01 2000-11-03 ; Move the enumeration lists back into their respective definitions. ; 3.2.02 2000-11-06 ; Change "State" back to "Code". ; 3.2.03 2000-11-07 ; Add category_key.relational which gives the relational key used in DDL2 ; 3.2.04 2000-11-10 ; MAJOR changes to a number of attributes and categories. ; 3.2.05 2000-11-13 ; Introduced definition.import_id. ; 3.2.06 2000-11-24 ; Change the _method.class enumeration state "Units" to "Definition". ; 3.2.07 2001-08-30 ; Change "category.parent_id" to "category.family_id". ; 3.2.08 2001-09-03 ; Change "alias.dictionary_class" to "alias.dictionary_uri". Change the "dictionary.class" states to "Attribute" and "Instance" ; 3.2.09 2001-09-26 ; Change "category.family_id" to "category.parent_id". ; 3.2.10 2001-10-01 ; Remove the definition of "alias.dictionary_version". ; 3.2.11 2001-10-02 ; Converted reference to "codes.unit_code" to "codes.units_code". ; 3.2.12 2001-11-13 ; Corrected loop miscount in "type.purpose". ; 3.2.13 2001-11-14 ; Corrected name.category_id in category.parent_id. ; 3.2.14 2002-02-02 ; Remove key from category DEFINITION. ; 3.2.15 2002-07-30 ; Several small typos corrected. Add "Tuple" to the list of type.container enumerations ; 3.2.16 2004-10-12 ; Corrected mismatch in version numbering between v2.13a and v2.13b and merged these changes into this version. ; 3.2.17 2004-10-12 ; In dictionary.class changed enumeration.default to "Instance" In type.container append a ' to the enumeration detail of "Tuple" ; 3.3.00 2004-11-09 ; Change definition.import_id to definition_import.id in many defs. Insert category DEFINITION_IMPORT and the items .id, .conflict, .protocol and .source. ; 3.3.01 2004-11-10 ; Make further changes to the DEFINITION_IMPORT definitions and introduce the DEFINITION_TEMPLATE category. ; 3.3.02 2004-11-11 ; Introduce an IMPORT category containing IMPORT_DICTIONARY, IMPORT_DEFINITION, IMPORT_CATEGORY, IMPORT_ATTRIBUTE. Change DEFINITION_TEMPLATE to IMPORT_TEMPLATE. ; 3.3.03 2004-11-12 ; Major changes to all the new attributes. Introduce categories DEFINITION_CONTEXT. ; 3.3.04 2004-11-13 ; Cleaned up the IMPORT changes and cases of enumerates. ; 3.3.05 2004-11-16 ; Further changes to IMPORT definitions. ; 3.3.06 2004-11-18 ; Some minor correction of typos ; 3.3.07 2005-11-22 ; Changed _dictionary.name to _dictionary.filename Changed _dictionary_xref.name to _dictionary_xref.filename Added _dictionary.title to describe the common name of the dictionary ; 3.3.08 2005-12-12 ; Changed ddl to ddl_attr Added Template and Function to _dictionary.class ; 3.3.09 2006-02-02 ; Add the definition of _dictionary_xref.source. ; 3.3.10 2006-02-07 ; Add import attribute definitions ; 3.4.01 2006-02-12 ; Remove save frames from dictionary attributes. Change the attribute _dictionary.parent_name to _dictionary.parent_id ; 3.4.02 2006-02-16 ; In the _import_*.conflict definitions change the enumeration state Unique to Ignore, and change the default state to Error. In the _import_*.missing definitions change default enumeration state to Error. ; 3.5.01 2006-03-07 ; Structural changes to the file to conform with the import model 3. Move the template file for *.relational_id to com_att.dic Change all references to *.relational_id into the tuple format. Move the _codes_ddl.units_code to enum_set.dic and insert the _import_enum_set.id tuples. ; 3.5.02 2006-03-22 ; Rename _enumeration.default_index_id to _enumeration.def_index_id. Correct the attributes _enumeration_default.index and *.value. ; 3.5.03 2006-05-09 ; Reword many of the import attributes. Correct the tuple description for _import_dictionary. Insert all of the definitions for _import_defaults attributes. Update _dictionary.class definition - change "Template" to "Import". Remove _enumeration.scope "open" from _definition_context.domain. ; 3.6.01 2006-06-16 ; Major revamp of TYPE attributes... changed: _type.value to _type.contents and expand enumeration list. _type.purpose has new role and different enumeration states. _name.object_id changed to _name.object_id. _enumeration_set.code becomes _enumeration_set.state. Changed the _type.value (now .contents) states to match expanded list. Added _dictionary.ddl_conformance attribute. Changed _category.join_set_id to _category.join_cat_id. Remove _enumeration.scope definition. ; 3.6.02 2006-06-17 ; Change the states of _type.purpose. ; 3.6.03 2006-06-18 ; Correct _type.contents value in _import_dictionary.id. ; 3.6.04 2006-06-20 ; Change state 'Point' to 'Link' in _type.contents definition. Add Formula to _type.contents ; 3.6.05 2006-06-27 ; Change all IMPORT attributes and apply. Add _dictionary.namespace attribute and apply. Add states to _definition.class and apply. Add _enumeration_set.scope. Add .context to ENUMERATE_SET, ENUMERATE_DEFAULT, DESCRIPTION_EXAMPLE ; 3.6.06 2006-07-18 ; Change the descriptions of the _type.container states. The _enueration_set.scope removed (enumeration.mandatory used). In _type_array.dimension change _type.contents to List. ; 3.6.07 2006-08-30 ; Change 'att' to 'sta' in the imports of _type.contents and _units.code. Replace states 'vector' and 'matrix' in _type.container with 'array'. In _type.purpose change 'model' to 'assigned'; 'observe' to 'observed'; and 'measure' to 'measured'. ; 3.6.08 2006-08-31 ; Remove the category TYPE_ARRAY and insert _type.dimension Replace _description.compact with _description.common Replace _description.abbreviated with _description.key_words ; 3.6.09 2006-10-31 ; Remove all attributes and categories referring to 'context'. ; 3.6.10 2006-11-09 ; Replace _method.id with method.purpose. Redefine the DICTIONARY_VALID values. ; 3.7.01 2006-11-16 ; Apply _definition.scope changes. Add _category.parent_join. Add _dictionary.xref_code. Add _enumeration_set.xref_dictionary. Remove all relational keys. ; 3.7.02 2006-12-05 ; Rewording of description.text in DDL_ATTR and definition.namespace Rewording of category_mandatory.item_id Reworded descriptions of definition.class descriptions. Removed dictionary.filename. Corrected examples in type.dimension. Remove dictionary.parent_id and dictionary.parent_uri. ; 3.7.03 2006-12-21 ; Default for _category.parent_join is now "No" ; 3.7.04 2007-02-06 ; Change _category_key.item_id to _category_key.generic Add _category_key.primitive ; 3.7.05 2007-02-08 ; Change the _type.purpose of _category_key.generic and .primitive to Identify ; 3.7.06 2007-03-18 ; Change the description for _name.linked_item_id ; ./CBFlib-0.9.2.2/drel-ply/drel_yacc.py0000644000076500007650000005636211603702115015641 0ustar yayayaya# A dREL grammar written for python-ply # # The output string should be a series of executable python statements, # which define a function which is called with a PyCIFRW CifBlock # object as single argument "cfdata" # # The object so defined will be a method of the dictionary object, taking # arguments self,cfdata. Therefore dictionary information is accessed # through "self", and data through "cfdata". import drel_lex import ply.yacc as yacc tokens = drel_lex.tokens # Overall translation unit # We return the text of the function, as well as a table of 'with' packets # and corresponding index names # def p_final_input(p): '''final_input : input''' p[0] = [p[1],p.parser.withtable] def p_input(p): '''input : statement | input statement''' p[0] = "\n".join(p[1:]) def p_statement(p): '''statement : stmt_list | compound_stmt''' p[0] = p[1] def p_stmt_list(p): '''stmt_list : simple_stmt | stmt_list ";" simple_stmt | stmt_list ";" simple_stmt ";" ''' if len(p) == 2: p[0] = p[1] else: p[0] = ";".join((p[1],p[3])) # differs from Python in that an expression list is not # allowed. Thus no procedure calls, for example. # This is done to avoid a reduce/reduce conflict for # identifiers (start of expression? start of target?) def p_simple_stmt(p): '''simple_stmt : assignment_stmt | augmented_assignment_stmt | fancy_drel_assignment_stmt | print_stmt | BREAK | NEXT''' p[0] = p[1] print "Simple statement: " + p[0] def p_print_stmt(p): '''print_stmt : PRINT expression ''' p[0] = 'print ' + p[2] # note do not accept trailing commas def p_expression_list(p): '''expression_list : expression | expression_list "," expression ''' if len(p) == 2: p[0] = p[1] else: p[0] = " ".join((p[1],",",p[3])) print "constructing expr list: %s" % `p[0]` # Simplified from the python 2.5 version due to apparent conflict with # the other type of IF expression... # def p_expression(p): '''expression : or_test ''' if len(p) == 2: p[0] = p[1] # else: p[0] = " ".join((p[1],"if",p[3],"else", p[5])) # This is too generous, as it allows a function call on the # LHS to be assigned to. This will cause a syntax error on # execution we hope. def p_target(p): '''target : primary | "(" target_list ")" | "[" target_list "]" ''' # search our enclosing blocks for special ids newid = 0 # print 'Special ids: %s' % `p.parser.special_id` for idtable in p.parser.special_id: newid = idtable.get(p[1],0) if newid: break if newid: p[0] = newid else: p[0] = " ".join(p[1:]) def p_or_test(p): ''' or_test : and_test | or_test OR and_test''' if len(p) == 2: p[0] = p[1] else: p[0] = " ".join((p[1],"or",p[3])) def p_and_test(p): '''and_test : not_test | and_test AND not_test''' if len(p) == 2: p[0] = p[1] else: p[0] = " ".join((p[1],"and",p[3])) def p_not_test(p): '''not_test : comparison | NOT not_test''' if len(p) == 2: p[0] = p[1] else: p[0] = " ".join(("not",p[2])) def p_comparison(p): '''comparison : a_expr | a_expr comp_operator a_expr''' if len(p) == 2: p[0] = p[1] else: p[0] = " ".join((p[1],p[2],p[3])) def p_comp_operator(p): '''comp_operator : "<" | ">" | GTE | LTE | NEQ | ISEQUAL | IN | NOT IN ''' if len(p)==3: p[0] = " not in " else: p[0] = p[1] def p_a_expr(p): '''a_expr : m_expr | a_expr "+" m_expr | a_expr "-" m_expr''' if len(p) == 2: p[0] = p[1] else: p[0] = " ".join((p[1] , p[2] , p[3])) def p_m_expr(p): '''m_expr : u_expr | m_expr "*" u_expr | m_expr "/" u_expr | m_expr "^" u_expr ''' if len(p) == 2: p[0] = p[1] else: if p[2] == "^": p[0] = "numpy.cross(" + p[1] + " , " + p[3] + ")" elif p[2] == "*": #need to invoke numpy version p[0] = "numpy.dot("+p[1]+","+p[3]+")" else: p[0] = " ".join((p[1] , p[2] , p[3])) def p_u_expr(p): '''u_expr : power | "-" u_expr | "+" u_expr''' if len(p) == 2: p[0] = p[1] else: p[0] = " ".join(p[1:]) def p_power(p): '''power : primary | primary POWER u_expr''' if len(p) == 2: p[0] = p[1] else: p[0] = " ".join((p[1] , "**" , p[3])) print 'At power: p[0] is %s' % `p[0]` def p_primary(p): '''primary : atom | primary_att | subscription | slicing | call''' # print 'Primary -> %s' % repr(p[1]) p[0] = p[1] # Separated out so that we can re-initialise subscription category def p_primary_att(p): '''primary_att : attributeref''' print "Reinitialising sub_subject from %s to null" % p.parser.sub_subject p.parser.sub_subject = "" p[0] = p[1] def p_atom(p): '''atom : ID | item_tag | literal | enclosure''' # print 'Atom -> %s' % repr(p[1]) p[0] = p[1] def p_item_tag(p): '''item_tag : ITEM_TAG''' # print "Target %s, treating %s" % (p.parser.target_name,"".join(p[1:])) if p.parser.target_id == "".join(p[1:]): p[0] = "__dreltarget" else: p[0] = "ciffile['%s']" % p[1] def p_literal(p): '''literal : stringliteral | INTEGER | HEXINT | OCTINT | BININT | REAL | IMAGINARY''' # print 'literal-> %s' % repr(p[1]) p[0] = p[1] def p_stringliteral(p): '''stringliteral : STRPREFIX SHORTSTRING | STRPREFIX LONGSTRING | SHORTSTRING | LONGSTRING''' if len(p)==3: p[0] = p[1]+p[2] else: p[0] = p[1] def p_enclosure(p): '''enclosure : parenth_form | string_conversion | list_display ''' p[0]=p[1] def p_parenth_form(p): '''parenth_form : "(" expression_list ")" | "(" ")" ''' if len(p) == 3: p[0] = "( )" else: p[0] = " ".join(p[1:]) # print 'Parens: %s' % `p[0]` def p_string_conversion(p): '''string_conversion : "`" expression_list "`" ''' p[0] = "".join(p[1:]) def p_list_display(p): ''' list_display : "[" listmaker "]" | "[" "]" ''' if len(p) == 3: p[0] = "StarFile.StarList([])" else: p[0] = "StarFile.StarList("+"".join(p[1:])+")" # scrap the trailing comma def p_listmaker(p): '''listmaker : expression listmaker2 | expression list_for ''' p[0] = " ".join(p[1:]) #no need to rewrite for dREL->python # print 'listmaker: %s' % `p[0]` def p_listmaker2(p): '''listmaker2 : "," expression | listmaker2 "," expression | ''' p[0] = " ".join(p[1:]) def p_list_for(p): '''list_for : FOR expression_list IN testlist | FOR expression_list IN testlist list_iter''' pass def p_testlist(p): '''testlist : or_test | testlist "," or_test | testlist "," or_test "," ''' pass def p_list_iter(p): '''list_iter : list_for | list_if''' pass def p_list_if(p): '''list_if : IF or_test | IF or_test list_iter''' pass # We have to intercept attribute references which relate to # aliased category variables, as well as to catch literal # item names containing a period. # # Note that we need to catch tags of the form 't.12', which # our lexer will interpret as ID REAL. We therefore also # accept t.12(3), which is not allowed, but we don't bother # trying to catch this error here. # # Note that there is no other meaning for '.' in drel beyond # category-item specifications, so we adopt a default stance # of converting all otherwise unresolvable attribute references # to simple table references to fit in with the PyCIFRW practice. def p_attributeref(p): '''attributeref : primary attribute_tag ''' # intercept special loop variables # print `p.parser.special_id` newid = None for idtable in p.parser.special_id: newid = idtable.get(p[1],0) if newid: break if newid: p[0] = "ciffile["+'"_'+newid[0]+p[2]+'"]' print "In ID processing: %s\n" % `newid` # a with statement may require an index if newid[1]: p[0] = p[0] + "[" + newid[1] + "]" elif p.parser.special_id[0].has_key("".join(p[1:])): # a global variable from the dictionary print "Using global dictionary variable "+p[1:] p[0] = 'ciffile['+"".join(p[1:])+']' else: #could be a keyed index operation, add back category val p[0] = p[1]+'["'+ p.parser.sub_subject+p[2] + '"]' p.parser.sub_subject = "" def p_attribute_tag(p): '''attribute_tag : "." ID | REAL ''' p[0] = "".join(p[1:]) # A subscription becomes a key lookup if the primary is a # pre-defined 'category variable'. We use the GetKeyedPacket # method we have specially added to PyCIFRW to simplify the # code here # def p_subscription(p): '''subscription : primary "[" expression_list "]" ''' # intercept special loop variables # print `p.parser.special_id` newid = None for idtable in p.parser.special_id: newid = idtable.get(p[1],0) if newid: break if newid: # We first get the PyCIFRW Loop block... key_item = 'self["'+newid[0]+'"]["_category_key.generic"]' get_loop = "ciffile.GetLoop(%s).GetKeyedPacket(%s,%s)" % (key_item,key_item,p[3]) p[0] = get_loop p.parser.sub_subject = "_"+newid[0]#in case of attribute reference following print "Set sub_subject to %s" % p.parser.sub_subject else: p[0] = " ".join(p[1:]) def p_slicing(p): '''slicing : simple_slicing | extended_slicing ''' p[0] = p[1] def p_simple_slicing(p): '''simple_slicing : primary "[" short_slice "]" ''' p[0] = " ".join(p[1:]) def p_short_slice(p): '''short_slice : ":" | expression ":" expression | ":" expression | expression ":" ''' p[0] = " ".join(p[1:]) def p_extended_slicing(p): '''extended_slicing : primary "[" slice_list "]" ''' p[0] = " ".join(p[1:]) def p_slice_list(p): '''slice_list : slice_item | slice_list "," slice_item ''' p[0] = " ".join(p[1:]) def p_slice_item(p): '''slice_item : expression | proper_slice | ELLIPSIS ''' p[0] = p[1] def p_proper_slice(p): '''proper_slice : short_slice | long_slice ''' p[0] = p[1] def p_long_slice(p): '''long_slice : short_slice ":" | short_slice ":" expression ''' p[0] = " ".join(p[1:]) # Last of the primary non-terminals... # We can catch quite a few of the functions simply by # rewriting the function name. By default, the function # name is passed through unchanged; this makes sure that # the built-in functions are found OK # def p_call(p): '''call : primary "(" ")" | primary "(" argument_list ")" ''' # simple built-in functions only at this stage builtins = {"list":"StarFile.StarList", "tuple":"StarFile.StarTuple", "table":"dict", "int":"int", "len":"len"} funcname = builtins.get(p[1].lower(),p[1]) # try to catch a few straightforward trickier ones if funcname.lower() == "mod": p[0] = "divmod" + "".join(p[2:]) + "[1]" elif funcname.lower() in ['sind','cosd','tand']: p[0] = "math."+funcname[:3].lower()+"("+ "math.radians" + "".join(p[2:])+")" elif funcname.lower() in ['array']: p[0] = "numpy.array(" + "".join(p[2:]) + ")" else: p[0] = funcname + "".join(p[2:]) #print "Function call: %s" % p[0] # It seems that in dREL the arguments are expressed differently # in the form arg [: specifier], arg ... # # We assume a simplified form # def p_argument_list(p): '''argument_list : func_arg | argument_list "," func_arg ''' p[0] = " ".join(p[1:]) def p_func_arg(p): '''func_arg : expression ''' p[0] = p[1] #ignore list structure for now def p_augmented_assignment_stmt(p): '''augmented_assignment_stmt : target AUGOP expression_list''' augsym = "%s" % p[2] if augsym == "++=": #append to list p[0] = p[1] + "+= [" + p[3] + "]" else: p[0] = " ".join(p[1:]) # We simultaneously create multiple results for a single category. In # this case __dreltarget is a dictionary with keys for each category # entry. def p_fancy_drel_assignment_stmt(p): '''fancy_drel_assignment_stmt : primary "(" dotlist ")" ''' del p.parser.fancy_drel_id p[0] = p[3] print "Fancy assignment -> " + p[0] # Something made up specially for drel. We accumulate results for a series of # items in a dictionary which is returned def p_dotlist(p): '''dotlist : "." ID "=" expression | dotlist "," "." ID "=" expression''' if len(p) == 5: #first element of dotlist, element -2 is category id p.parser.fancy_drel_id = p[-2] if p[-2] == p.parser.target_id: #we will return the results realid = p[-2]+"."+p[2] p[0] = "__dreltarget.update({'%s':__dreltarget.get('%s',[])+[%s]})\n" % (realid,realid,p[4]) else: p[0] = p[-2] + "".join(p[1:]) + "\n" print 'Fancy id is ' + `p[-2]` else: if p.parser.fancy_drel_id == p.parser.target_id: realid = p.parser.fancy_drel_id + "." + p[4] p[0] = p[1] + "__dreltarget.update({'%s':__dreltarget.get('%s',[])+[%s]})\n" % (realid,realid,p[6]) else: p[0] = p[1] + p.parser.fancy_drel_id + "".join(p[3:]) + "\n" def p_assignment_stmt(p): '''assignment_stmt : target_list "=" expression_list''' p[0] = " ".join(p[1:]) def p_target_list(p): '''target_list : target | target_list "," target ''' p[0] = " ".join(p[1:]) # now for the compound statements def p_compound_stmt(p): '''compound_stmt : if_stmt | for_stmt | do_stmt | loop_stmt | with_stmt | where_stmt | switch_stmt | funcdef ''' p[0] = p[1] print "Compound statement: \n" + p[0] def p_if_stmt(p): '''if_stmt : IF expression suite | if_stmt ELSE suite ''' if p[1].lower() == "if": #first form of expression p[0] = "if " p[0] += p[2] + ":" p[0] += add_indent(p[3]) else: #else statement p[0] = p[1] + "\n" p[0] += p[2].lower() + ":" + add_indent(p[3]) print "If statement: \n" + p[0] # Note the dREL divergence from Python here: we allow compound # statements to follow without a separate block (like C etc.) # For simplicity we indent consistently (further up) def p_suite(p): '''suite : simple_stmt | compound_stmt | open_brace statement_block close_brace ''' if len(p) == 2: p[0] = "\n" + p[1] else: p[0] = p[2] + "\n" # separate so we can do the indent/dedent thing def p_open_brace(p): '''open_brace : "{"''' p.parser.indent += 4*" " print 'Parser indent now "%s"' % p.parser.indent def p_close_brace(p): '''close_brace : "}"''' p.parser.indent = p.parser.indent[:-4] print 'Parser indent now "%s"' % p.parser.indent def p_statement_block(p): '''statement_block : statement | statement_block statement''' if len(p) == 2: p[0] = "\n" + p[1] else: p[0] = p[1] + "\n" + p[2] def p_for_stmt(p): '''for_stmt : FOR target_list IN expression_list suite''' p[0] = "for " + p[2] + "in" + p[4] + ":\n" + add_indent(p[5]) # We split the loop statement into parts so that we can capture the # ID before the suite is processed. Note that we should record that # we have an extra indent due to the loop test and remove it at the # end, but we haven't done this yet. def p_loop_stmt(p): '''loop_stmt : loop_head suite''' p[0] = p[1] + add_indent(p[2]) # We capture a list of all the actually present items in the current # datafile def p_loop_head(p): '''loop_head : LOOP ID AS ID | LOOP ID AS ID ":" ID | LOOP ID AS ID ":" ID comp_operator ID''' p[0] = "__pycitems = self.names_in_cat('%s')" % p[4] p[0] += "\nprint 'names in cat = %s' % `__pycitems`" p[0] += "\n" + "__pycitems = filter(lambda a:ciffile.has_key(a),__pycitems)" p[0] += "\nprint 'names in cat -> %s' % `__pycitems`\n" p.parser.special_id[-1].update({p[2]: [p[4],"",False]}) print "%s means %s" % (p[2],p.parser.special_id[-1][p[2]][0]) if p[4] in p.parser.loopable_cats: #loop over another index if len(p)>5: #are provided with index loop_index = p[6] else: loop_index = "__pi%d" % len(p.parser.special_id[-1]) p.parser.special_id[-1][p[2]][1] = loop_index p.parser.special_id[-1][p[2]][2] = True p[0] += "\n"+ "for %s in range(len(ciffile[__pycitems[0]])):" % loop_index else: #have to emit a block which runs once... p[0] += "\n" + "for __noloop in [0]:" if len(p)==9: # do an "if" test before proceeding iftest = "if " + "".join(p[6:9]) + ":" p[0] += "\n " + iftest def p_do_stmt(p): '''do_stmt : do_stmt_head suite''' p[0] = p[1] + add_indent(p[2]) # To translate the dREL do to a for statement, we need to make the # end of the range included in the range def p_do_stmt_head(p): '''do_stmt_head : DO ID "=" expression "," expression | DO ID "=" expression "," expression "," expression ''' print "Do stmt: " + `p[1:]` incr = "1" if len(p)==9: incr = p[8] rangeend = p[6]+"+%s/2" % incr # avoid float expressions else: rangeend = p[6]+"+%s" % incr # because 1/2 = 0 p[0] = "for " + p[2] + " in range(" + p[4] + "," + rangeend + "," + incr + "):" # Statement blocks after with statements do not require indenting so we # undo our indentation def p_with_stmt(p): '''with_stmt : with_head suite''' p[0] = p[2] #outgoing = p.parser.special_id.pop() #outindents = filter(lambda a:a[2],outgoing.values()) #p.parser.indent = p.parser.indent[:len(p.parser.indent)-4*len(outindents)] # Done here to capture the id before processing the suite # A with statement doesn't need any indenting... # We assume a variable 'loopable_cats' is available to us # We have a somewhat complex structure to allow for multiple simultaneous # with statements, although that is not in the standard. We could # probably assume a single packet variable per with statement and # simplify the special_id structure a bit # Note that we allow multiple with statements grouped together (as long # as nothing else separates them) def p_with_head(p): '''with_head : WITH ID AS ID''' # p[0] = "__pycitems = self.names_in_cat('%s')" % p[4] p.parser.special_id.append({p[2]: [p[4],"",False]}) if p[4] in p.parser.loopable_cats: tb_length = len(p.parser.withtable) #generate unique id p.parser.withtable.update({p[4]:"__pi%d" % tb_length}) p.parser.special_id[-1][p[2]][1] = p.parser.withtable[p[4]] print "%s means %s" % (p[2],p.parser.special_id[-1][p[2]][0]) if p.parser.special_id[-1][p[2]][1]: print "%s looped using %s" % (p[2],p.parser.special_id[-1][p[2]][1]) def p_where_stmt(p): '''where_stmt : WHERE expression suite ELSE suite''' pass def p_switch_stmt(p): '''switch_stmt : SWITCH ID open_brace caselist DEFAULT suite close_brace ''' pass def p_caselist(p): '''caselist : CASE target_list suite | caselist CASE target_list suite''' pass def p_funcdef(p): ''' funcdef : FUNCTION ID "(" arglist ")" suite ''' p[0] = "def " + "".join(p[2:6]) + ":" # add some import statements p[0] += "\n" + add_indent("import StarFile,math,numpy") # add a return statement as the last statement of the suite p[0] += "\n" + add_indent(p[6] + 'return ' + p[2] + '\n') def p_arglist(p): ''' arglist : ID ":" list_display | arglist "," ID ":" list_display ''' if len(p) == 4: p[0] = p[1] else: p[0] = p[1] + "," + p[3] def p_error(p): print 'Syntax error at token %s, value %s' % (p.type,p.value) ### Now some helper functions # do indentation: we substitute any "\n" characters in the # input with "\n+4 spaces" def add_indent(instring): import re indented = re.sub("(?m)^"," ",instring) indented = indented.rstrip(" ") #remove extras at end print "Indenting: \n%s\n->\n%s" % (instring,indented) return indented # The following function creates a function. The function # modifies the 'ciffile' argument in place. The pi argument is a # packet index for when we are accessing looped data using a # 'with' statement. Returnname is the variable name for returned # data, and for looped data this should always be "__dreltarget". # See the test file for ways of using this # # The parser data is a two-element list with the first element the text of # the function, and the second element a table of looped values # # Normally this function is called in a context where 'self' is a CifDic # object; for the purposes of testing, we want to be able to remove any # references to dictionary methods and so include the have_sn flag. def make_func(parser_data,funcname,returnname,cat_meth = False,have_sn=True): import re if not returnname: returnname = "__dreltarget" func_text = parser_data[0] # now indent the string noindent = func_text.splitlines() # get the minimum indent and remove empty lines noindent = filter(lambda a:a,noindent) no_spaces = map(lambda a:re.match(r' *',a),noindent) no_spaces = map(lambda a:a.end(),no_spaces) min_spaces = min(no_spaces)+4 # because we add 4 ourselves to everything with_indices = parser_data[1].values() w_i_list = ",".join(with_indices) preamble = "def %s(self,ciffile,%s):\n" % (funcname,w_i_list) preamble += min_spaces*" " + "import StarFile\n" preamble += min_spaces*" " + "import math\n" preamble += min_spaces*" " + "import numpy\n" if have_sn: preamble += min_spaces*" " + "self.switch_numpy(True)\n" if cat_meth: preamble += min_spaces*" " + "%s = {}\n" % returnname indented = map(lambda a:" " + a+"\n",noindent) postamble = "" if have_sn: postamble = " "*min_spaces + "self.switch_numpy(False)\n" postamble += " "*min_spaces + "return %s" % returnname final = preamble + "".join(indented) + postamble return final parser = yacc.yacc() parser.indent = "" parser.special_id=[{}] parser.looped_value = False #Determines with statement construction parser.target_id = None parser.withtable = {} #Table of 'with' packet access info parser.sub_subject="" ./CBFlib-0.9.2.2/drel-ply/method_output0000644000076500007650000000000411603702115016143 0ustar yayayaya110 ./CBFlib-0.9.2.2/Java.txt0000644000076500007650000000364411603702122013225 0ustar yayayayaAn initial set of Java wrapper classes for CBFlib-0.8.0 has been implemented using SWIG. A pair of example programs (testcbf.c and testcbf.java) are included that show the similarities and differences of using CBFlib in C and Java. This has been tested using Red Hat EL 4.7 WS for i568 and Red Hat EL 5.3 WS for x86_64 with Sun's JDK. It was also tested using Microsoft Windows XP with MinGW and MSYS. In addition to the static methods in org.iucr.cbflib.cbf, six helper classes are included: four wrapper classes for C pointers that point to size_t (sizetP), int (intP), unsigned int (uintP) and double (doubleP); two wrapper classes for C arrays that hold int (intArray) and double (doubleArray). Also, some helper functions for a pointer to pointer to char (charPP_*) aid the output of strings, and pointer casts to void (int_void and double_void). CBF_NODETYPE is supported too as mapped to ints. Finally, a constructor and a destructor has been added to the cbf_handle_struct class. Peter.Chang@diamond.ac.uk 23/03/2009 An initial set of Java wrapper classes for CBFlib-0.8.0 has been implemented using SWIG. A pair of example programs (testcbf.c and testcbf.java) are included that show the similarities and differences of using CBFlib in C and Java. This has been tested using Red Hat EL 4.7 WS for i568 and Red Hat EL 5.3 WS for x86_64 with Sun's JDK. In addition to the static methods in org.iucr.cbflib.cbf, six helper classes are included: four wrapper classes for C pointers that point to size_t (sizetP), int (intP), unsigned int (uintP) and double (doubleP); two wrapper classes for C arrays that hold int (intArray) and double (doubleArray). Also, some helper functions for a pointer to pointer to char (charPP_*) aid the output of strings, and pointer casts to void (int_void and double_void). Finally, a constructor and a destructor has been added to the cbf_handle_struct class. Peter.Chang@diamond.ac.uk 23/02/2009 ./CBFlib-0.9.2.2/.undosymlinks0000755000076500007650000001055111603702122014341 0ustar yayayaya#!/bin/sh ###################################################################### # # # .undosymlinks for CBFlib/doc directory # # # # # # Version 0.8.0 20 Jul 2008 # # # # Paul Ellis and # # Herbert J. Bernstein (yaya@bernstein-plus-sons.com) # # # # (C) Copyright 2006 - 2008 Herbert J. Bernstein # # # ###################################################################### ###################################################################### # # # YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL # # # # ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS # # OF THE LGPL # # # ###################################################################### ########################### GPL NOTICES ############################## # # # This program is free software; you can redistribute it and/or # # modify it under the terms of the GNU General Public License as # # published by the Free Software Foundation; either version 2 of # # (the License, or (at your option) any later version. # # # # This program is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # # GNU General Public License for more details. # # # # You should have received a copy of the GNU General Public License # # along with this program; if not, write to the Free Software # # Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA # # 02111-1307 USA # # # ###################################################################### ######################### LGPL NOTICES ############################### # # # This library is free software; you can redistribute it and/or # # modify it under the terms of the GNU Lesser General Public # # License as published by the Free Software Foundation; either # # version 2.1 of the License, or (at your option) any later version. # # # # This library is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # # Lesser General Public License for more details. # # # # You should have received a copy of the GNU Lesser General Public # # License along with this library; if not, write to the Free # # Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, # # MA 02110-1301 USA # # # ###################################################################### # Usage ./.undosymlinks for file in index.html CBFlib.tar.gz template_adscquantum315_3072x3072.cbf \ template_adscquantum4_2304x2304.cbf \ template_mar345_2300x2300.cbf template_pilatus6m_2463x2527.cbf gpl.txt lgpl.txt do rm -rf $file done for file in * do if [ -d "$file" ] ; then if [ -e "$file/.undosymlinks" ] ; then (cd "$file"; sh -c "./.undosymlinks") fi fi done ./CBFlib-0.9.2.2/Makefile_LINUX0000644000076500007650000020013111603702122014210 0ustar yayayaya ###################################################################### # Makefile - command file for make to create CBFlib # # # # Version 0.9.2 12 Feb 2011 # # # # Paul Ellis and # # Herbert J. Bernstein (yaya@bernstein-plus-sons.com) # # # # (C) Copyright 2006 - 2011 Herbert J. Bernstein # # # ###################################################################### ###################################################################### # # # YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL # # # # ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS # # OF THE LGPL # # # ###################################################################### ########################### GPL NOTICES ############################## # # # This program is free software; you can redistribute it and/or # # modify it under the terms of the GNU General Public License as # # published by the Free Software Foundation; either version 2 of # # (the License, or (at your option) any later version. # # # # This program is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # # GNU General Public License for more details. # # # # You should have received a copy of the GNU General Public License # # along with this program; if not, write to the Free Software # # Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA # # 02111-1307 USA # # # ###################################################################### ######################### LGPL NOTICES ############################### # # # This library is free software; you can redistribute it and/or # # modify it under the terms of the GNU Lesser General Public # # License as published by the Free Software Foundation; either # # version 2.1 of the License, or (at your option) any later version. # # # # This library is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # # Lesser General Public License for more details. # # # # You should have received a copy of the GNU Lesser General Public # # License along with this library; if not, write to the Free # # Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, # # MA 02110-1301 USA # # # ###################################################################### ###################################################################### # # # Stanford University Notices # # for the CBFlib software package that incorporates SLAC software # # on which copyright is disclaimed # # # # This software # # ------------- # # The term "this software", as used in these Notices, refers to # # those portions of the software package CBFlib that were created by # # employees of the Stanford Linear Accelerator Center, Stanford # # University. # # # # Stanford disclaimer of copyright # # -------------------------------- # # Stanford University, owner of the copyright, hereby disclaims its # # copyright and all other rights in this software. Hence, anyone # # may freely use it for any purpose without restriction. # # # # Acknowledgement of sponsorship # # ------------------------------ # # This software was produced by the Stanford Linear Accelerator # # Center, Stanford University, under Contract DE-AC03-76SFO0515 with # # the Department of Energy. # # # # Government disclaimer of liability # # ---------------------------------- # # Neither the United States nor the United States Department of # # Energy, nor any of their employees, makes any warranty, express or # # implied, or assumes any legal liability or responsibility for the # # accuracy, completeness, or usefulness of any data, apparatus, # # product, or process disclosed, or represents that its use would # # not infringe privately owned rights. # # # # Stanford disclaimer of liability # # -------------------------------- # # Stanford University makes no representations or warranties, # # express or implied, nor assumes any liability for the use of this # # software. # # # # Maintenance of notices # # ---------------------- # # In the interest of clarity regarding the origin and status of this # # software, this and all the preceding Stanford University notices # # are to remain affixed to any copy or derivative of this software # # made or distributed by the recipient and are to be affixed to any # # copy of software made or distributed by the recipient that # # contains a copy or derivative of this software. # # # # Based on SLAC Software Notices, Set 4 # # OTT.002a, 2004 FEB 03 # ###################################################################### ###################################################################### # NOTICE # # Creative endeavors depend on the lively exchange of ideas. There # # are laws and customs which establish rights and responsibilities # # for authors and the users of what authors create. This notice # # is not intended to prevent you from using the software and # # documents in this package, but to ensure that there are no # # misunderstandings about terms and conditions of such use. # # # # Please read the following notice carefully. If you do not # # understand any portion of this notice, please seek appropriate # # professional legal advice before making use of the software and # # documents included in this software package. In addition to # # whatever other steps you may be obliged to take to respect the # # intellectual property rights of the various parties involved, if # # you do make use of the software and documents in this package, # # please give credit where credit is due by citing this package, # # its authors and the URL or other source from which you obtained # # it, or equivalent primary references in the literature with the # # same authors. # # # # Some of the software and documents included within this software # # package are the intellectual property of various parties, and # # placement in this package does not in any way imply that any # # such rights have in any way been waived or diminished. # # # # With respect to any software or documents for which a copyright # # exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. # # # # Even though the authors of the various documents and software # # found here have made a good faith effort to ensure that the # # documents are correct and that the software performs according # # to its documentation, and we would greatly appreciate hearing of # # any problems you may encounter, the programs and documents any # # files created by the programs are provided **AS IS** without any * # warranty as to correctness, merchantability or fitness for any # # particular or general use. # # # # THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF # # PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE # # PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS # # OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE # # PROGRAMS OR DOCUMENTS. # ###################################################################### ###################################################################### # # # The IUCr Policy # # for the Protection and the Promotion of the STAR File and # # CIF Standards for Exchanging and Archiving Electronic Data # # # # Overview # # # # The Crystallographic Information File (CIF)[1] is a standard for # # information interchange promulgated by the International Union of # # Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the # # recommended method for submitting publications to Acta # # Crystallographica Section C and reports of crystal structure # # determinations to other sections of Acta Crystallographica # # and many other journals. The syntax of a CIF is a subset of the # # more general STAR File[2] format. The CIF and STAR File approaches # # are used increasingly in the structural sciences for data exchange # # and archiving, and are having a significant influence on these # # activities in other fields. # # # # Statement of intent # # # # The IUCr's interest in the STAR File is as a general data # # interchange standard for science, and its interest in the CIF, # # a conformant derivative of the STAR File, is as a concise data # # exchange and archival standard for crystallography and structural # # science. # # # # Protection of the standards # # # # To protect the STAR File and the CIF as standards for # # interchanging and archiving electronic data, the IUCr, on behalf # # of the scientific community, # # # # # holds the copyrights on the standards themselves, * # # # # owns the associated trademarks and service marks, and * # # # # holds a patent on the STAR File. * # # # These intellectual property rights relate solely to the # # interchange formats, not to the data contained therein, nor to # # the software used in the generation, access or manipulation of # # the data. # # # # Promotion of the standards # # # # The sole requirement that the IUCr, in its protective role, # # imposes on software purporting to process STAR File or CIF data # # is that the following conditions be met prior to sale or # # distribution. # # # # # Software claiming to read files written to either the STAR * # File or the CIF standard must be able to extract the pertinent # # data from a file conformant to the STAR File syntax, or the CIF # # syntax, respectively. # # # # # Software claiming to write files in either the STAR File, or * # the CIF, standard must produce files that are conformant to the # # STAR File syntax, or the CIF syntax, respectively. # # # # # Software claiming to read definitions from a specific data * # dictionary approved by the IUCr must be able to extract any # # pertinent definition which is conformant to the dictionary # # definition language (DDL)[3] associated with that dictionary. # # # # The IUCr, through its Committee on CIF Standards, will assist # # any developer to verify that software meets these conformance # # conditions. # # # # Glossary of terms # # # # [1] CIF: is a data file conformant to the file syntax defined # # at http://www.iucr.org/iucr-top/cif/spec/index.html # # # # [2] STAR File: is a data file conformant to the file syntax # # defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html # # # # [3] DDL: is a language used in a data dictionary to define data # # items in terms of "attributes". Dictionaries currently approved # # by the IUCr, and the DDL versions used to construct these # # dictionaries, are listed at # # http://www.iucr.org/iucr-top/cif/spec/ddl/index.html # # # # Last modified: 30 September 2000 # # # # IUCr Policy Copyright (C) 2000 International Union of # # Crystallography # ###################################################################### # Version string VERSION = 0.9.2 # # Comment out the next line if scratch test files sould be retain # CLEANTESTS = yes # # Definition to get a version of tifflib to support tiff2cbf # TIFF = tiff-3.9.4-rev-6Feb11 TIFFPREFIX = $(PWD) # # Definitions to get a stable version of regex # REGEX = regex-20090805 REGEXDIR = /usr/lib REGEXDEP = # Program to use to retrieve a URL DOWNLOAD = wget # Flag to control symlinks versus copying SLFLAGS = --use_ln # # Program to use to pack shars # SHAR = /usr/bin/shar #SHAR = /usr/local/bin/gshar # # Program to use to create archives # AR = /usr/bin/ar # # Program to use to add an index to an archive # RANLIB = /usr/bin/ranlib # # Program to use to decompress a data file # DECOMPRESS = /usr/bin/bunzip2 # # Program to use to compress a data file # COMPRESS = /usr/bin/bzip2 # # Program to use to generate a signature # SIGNATURE = /usr/bin/openssl dgst -md5 # # Extension for compressed data file (with period) # CEXT = .bz2 # # Extension for signatures of files # SEXT = .md5 # call to time a command #TIME = #TIME = time # # Program to display differences between files # DIFF = diff -u -b # # Program to generate wrapper classes for Python # PYSWIG = swig -python # # Program to generate wrapper classes for Java # JSWIG = swig -java # # Program to generate LaTex and HTML program documentation # NUWEB = nuweb # # Compiler for Java # JAVAC = javac # # Java archiver for compiled classes # JAR = jar # # Java SDK root directory # ifeq ($(JDKDIR),) JDKDIR = /usr/lib/java endif ifneq ($(CBF_DONT_USE_LONG_LONG),) NOLLFLAG = -DCBF_DONT_USE_LONG_LONG else NOLLFLAG = endif # # PYCBF definitions # PYCBFEXT = so PYCBFBOPT = SETUP_PY = setup.py # # Set the compiler and flags # ######################################################### # # Appropriate compiler definitions for Linux # ######################################################### CC = gcc C++ = g++ CFLAGS = -g -O2 -Wall -D_USE_XOPEN_EXTENDED -fno-strict-aliasing F90C = gfortran F90FLAGS = -g F90LDFLAGS = SOCFLAGS = -fPIC SOLDFLAGS = -shared -Wl,-rpath,$(INSTALLDIR)/lib JAVAINCLUDES = -I$(JDKDIR)/include -I$(JDKDIR)/include/linux LDPREFIX = LD_LIBRARY_PATH=$(SOLIB) EXTRALIBS = -lm M4FLAGS = -Dfcb_bytes_in_rec=131072 TIME = time ifneq ($(NOFORTRAN),) F90C = endif # # Directories # ROOT = . LIB = $(ROOT)/lib SOLIB = $(ROOT)/solib JCBF = $(ROOT)/jcbf JAVADIR = $(ROOT)/java BIN = $(ROOT)/bin SRC = $(ROOT)/src INCLUDE = $(ROOT)/include M4 = $(ROOT)/m4 PYCBF = $(ROOT)/pycbf EXAMPLES = $(ROOT)/examples DECTRIS_EXAMPLES = $(EXAMPLES)/dectris_cbf_template_test DOC = $(ROOT)/doc GRAPHICS = $(ROOT)/html_graphics DATADIRI = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Input DATADIRO = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Output DATADIRS = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only INSTALLDIR = $(HOME) # # URLs from which to retrieve the data directories # DATAURLBASE = http://downloads.sf.net/cbflib/ DATAURLI = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Input.tar.gz DATAURLO = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Output.tar.gz DATAURLS = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz # # URLs from which to retrieve needed external package snapshots # REGEXURL = http://downloads.sf.net/cbflib/$(REGEX).tar.gz TIFFURL = http://downloads.sf.net/cbflib/$(TIFF).tar.gz # # Include directories # INCLUDES = -I$(INCLUDE) -I$(SRC) ###################################################################### # You should not need to make modifications below this line # ###################################################################### # # Suffixes of files to be used or built # .SUFFIXES: .c .o .f90 .m4 .m4.f90: m4 -P $(M4FLAGS) $< > $@ ifneq ($(F90C),) .f90.o: $(F90C) $(F90FLAGS) -c $< -o $@ endif # # Common dependencies # COMMONDEP = Makefile # # Source files # SOURCE = $(SRC)/cbf.c \ $(SRC)/cbf_alloc.c \ $(SRC)/cbf_ascii.c \ $(SRC)/cbf_binary.c \ $(SRC)/cbf_byte_offset.c \ $(SRC)/cbf_canonical.c \ $(SRC)/cbf_codes.c \ $(SRC)/cbf_compress.c \ $(SRC)/cbf_context.c \ $(SRC)/cbf_copy.c \ $(SRC)/cbf_file.c \ $(SRC)/cbf_getopt.c \ $(SRC)/cbf_lex.c \ $(SRC)/cbf_packed.c \ $(SRC)/cbf_predictor.c \ $(SRC)/cbf_read_binary.c \ $(SRC)/cbf_read_mime.c \ $(SRC)/cbf_simple.c \ $(SRC)/cbf_string.c \ $(SRC)/cbf_stx.c \ $(SRC)/cbf_tree.c \ $(SRC)/cbf_uncompressed.c \ $(SRC)/cbf_write.c \ $(SRC)/cbf_write_binary.c \ $(SRC)/cbf_ws.c \ $(SRC)/md5c.c F90SOURCE = $(SRC)/fcb_atol_wcnt.f90 \ $(SRC)/fcb_ci_strncmparr.f90 \ $(SRC)/fcb_exit_binary.f90 \ $(SRC)/fcb_nblen_array.f90 \ $(SRC)/fcb_next_binary.f90 \ $(SRC)/fcb_open_cifin.f90 \ $(SRC)/fcb_packed.f90 \ $(SRC)/fcb_read_bits.f90 \ $(SRC)/fcb_read_byte.f90 \ $(SRC)/fcb_read_image.f90 \ $(SRC)/fcb_read_line.f90 \ $(SRC)/fcb_read_xds_i2.f90 \ $(SRC)/fcb_skip_whitespace.f90 \ $(EXAMPLES)/test_fcb_read_image.f90 \ $(EXAMPLES)/test_xds_binary.f90 # # Header files # HEADERS = $(INCLUDE)/cbf.h \ $(INCLUDE)/cbf_alloc.h \ $(INCLUDE)/cbf_ascii.h \ $(INCLUDE)/cbf_binary.h \ $(INCLUDE)/cbf_byte_offset.h \ $(INCLUDE)/cbf_canonical.h \ $(INCLUDE)/cbf_codes.h \ $(INCLUDE)/cbf_compress.h \ $(INCLUDE)/cbf_context.h \ $(INCLUDE)/cbf_copy.h \ $(INCLUDE)/cbf_file.h \ $(INCLUDE)/cbf_getopt.h \ $(INCLUDE)/cbf_lex.h \ $(INCLUDE)/cbf_packed.h \ $(INCLUDE)/cbf_predictor.h \ $(INCLUDE)/cbf_read_binary.h \ $(INCLUDE)/cbf_read_mime.h \ $(INCLUDE)/cbf_simple.h \ $(INCLUDE)/cbf_string.h \ $(INCLUDE)/cbf_stx.h \ $(INCLUDE)/cbf_tree.h \ $(INCLUDE)/cbf_uncompressed.h \ $(INCLUDE)/cbf_write.h \ $(INCLUDE)/cbf_write_binary.h \ $(INCLUDE)/cbf_ws.h \ $(INCLUDE)/global.h \ $(INCLUDE)/cbff.h \ $(INCLUDE)/md5.h # # m4 macro files # M4FILES = $(M4)/fcblib_defines.m4 \ $(M4)/fcb_exit_binary.m4 \ $(M4)/fcb_next_binary.m4 \ $(M4)/fcb_open_cifin.m4 \ $(M4)/fcb_packed.m4 \ $(M4)/fcb_read_bits.m4 \ $(M4)/fcb_read_image.m4 \ $(M4)/fcb_read_xds_i2.m4 \ $(M4)/test_fcb_read_image.m4 \ $(M4)/test_xds_binary.m4 # # Documentation files # DOCUMENTS = $(DOC)/CBFlib.html \ $(DOC)/CBFlib.txt \ $(DOC)/CBFlib_NOTICES.html \ $(DOC)/CBFlib_NOTICES.txt \ $(DOC)/ChangeLog \ $(DOC)/ChangeLog.html \ $(DOC)/MANIFEST \ $(DOC)/gpl.txt $(DOC)/lgpl.txt # # HTML Graphics files # JPEGS = $(GRAPHICS)/CBFbackground.jpg \ $(GRAPHICS)/CBFbig.jpg \ $(GRAPHICS)/CBFbutton.jpg \ $(GRAPHICS)/cbflibbackground.jpg \ $(GRAPHICS)/cbflibbig.jpg \ $(GRAPHICS)/cbflibbutton.jpg \ $(GRAPHICS)/cifhome.jpg \ $(GRAPHICS)/iucrhome.jpg \ $(GRAPHICS)/noticeButton.jpg # # Default: instructions # default: @echo ' ' @echo '***************************************************************' @echo ' ' @echo ' PLEASE READ README and doc/CBFlib_NOTICES.txt' @echo ' ' @echo ' Before making the CBF library and example programs, check' @echo ' that the C compiler name and flags are correct:' @echo ' ' @echo ' The current values are:' @echo ' ' @echo ' $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG)' @echo ' ' @echo ' Before installing the CBF library and example programs, check' @echo ' that the install directory is correct:' @echo ' ' @echo ' The current value :' @echo ' ' @echo ' $(INSTALLDIR) ' @echo ' ' @echo ' To compile the CBF library and example programs type:' @echo ' ' @echo ' make clean' @echo ' make all' @echo ' ' @echo ' To compile the CBF library as a shared object library, type:' @echo ' ' @echo ' make shared' @echo ' ' @echo ' To compile the Java wrapper classes for CBF library, type:' @echo ' ' @echo ' make javawrapper' @echo ' ' @echo ' To run a set of tests type:' @echo ' ' @echo ' make tests' @echo ' ' @echo ' To run some java tests type:' @echo ' ' @echo ' make javatests' @echo ' ' @echo ' The tests assume that several data files are in the directories' @echo ' $(DATADIRI) and $(DATADIRO)' @echo ' ' @echo ' Alternatively tests can be run comparing MD5 signatures only by' @echo ' ' @echo ' make tests_sigs_only' @echo ' ' @echo ' These signature only tests save space and download time by' @echo ' assuming that input data files and the output signatures' @echo ' are in the directories' @echo ' $(DATADIRI) and $(DATADIRS)' @echo ' ' @echo ' These directory can be obtained from' @echo ' ' @echo ' $(DATAURLI) ' @echo ' $(DATAURLO) ' @echo ' $(DATAURLS) ' @echo ' ' @echo ' To clean up the directories type:' @echo ' ' @echo ' make clean' @echo ' ' @echo ' To install the library and binaries type:' @echo ' ' @echo ' make install' @echo ' ' @echo '***************************************************************' @echo ' ' # # Compile the library and examples # all:: $(BIN) $(SOURCE) $(F90SOURCE) $(HEADERS) \ symlinksdone $(REGEXDEP) \ $(LIB)/libcbf.a \ $(LIB)/libfcb.a \ $(LIB)/libimg.a \ $(BIN)/adscimg2cbf \ $(BIN)/cbf2adscimg \ $(BIN)/convert_image \ $(BIN)/convert_minicbf \ $(BIN)/sequence_match \ $(BIN)/arvai_test \ $(BIN)/makecbf \ $(BIN)/img2cif \ $(BIN)/adscimg2cbf \ $(BIN)/cif2cbf \ $(BIN)/testcell \ $(BIN)/cif2c \ $(BIN)/testreals \ $(BIN)/testflat \ $(BIN)/testflatpacked ifneq ($(F90C),) all:: $(BIN)/test_xds_binary \ $(BIN)/test_fcb_read_image endif shared: $(SOLIB)/libcbf.so $(SOLIB)/libfcb.so $(SOLIB)/libimg.so javawrapper: shared $(JCBF) $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf_wrap.so ifneq ($(CBFLIB_USE_PYCIFRW),) PYCIFRWDEF = -Dcbf_use_pycifrw=yes else PYCIFRWDEF = endif Makefiles: Makefile \ Makefile_LINUX \ Makefile_LINUX_64 \ Makefile_LINUX_gcc42 \ Makefile_LINUX_DMALLOC \ Makefile_LINUX_gcc42_DMALLOC \ Makefile_OSX \ Makefile_OSX_gcc42 \ Makefile_OSX_gcc42_DMALLOC \ Makefile_AIX \ Makefile_MINGW \ Makefile_IRIX_gcc Makefile_LINUX: $(M4)/Makefile.m4 -cp Makefile_LINUX Makefile_LINUX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX $(M4)/Makefile.m4 > Makefile_LINUX Makefile_LINUX_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_LINUX Makefile_LINUX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_DMALLOC $(M4)/Makefile.m4 > Makefile_LINUX_DMALLOC Makefile_LINUX_64: $(M4)/Makefile.m4 -cp Makefile_LINUX_64 Makefile_LINUX_64_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_64 $(M4)/Makefile.m4 > Makefile_LINUX_64 Makefile_LINUX_gcc42: $(M4)/Makefile.m4 -cp Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_gcc42 $(M4)/Makefile.m4 > Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_gcc42_DMALLOC $(M4)/Makefile.m4 > Makefile_LINUX_gcc42_DMALLOC Makefile_OSX: $(M4)/Makefile.m4 -cp Makefile_OSX Makefile_OSX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX $(M4)/Makefile.m4 > Makefile_OSX Makefile_OSX_gcc42: $(M4)/Makefile.m4 -cp Makefile_OSX_gcc42 Makefile_OSX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX_gcc42 $(M4)/Makefile.m4 > Makefile_OSX_gcc42 Makefile_OSX_gcc42_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_OSX_gcc42 Makefile_OSX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX_gcc42_DMALLOC $(M4)/Makefile.m4 > Makefile_OSX_gcc42_DMALLOC Makefile_AIX: $(M4)/Makefile.m4 -cp Makefile_AIX Makefile_AIX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=AIX $(M4)/Makefile.m4 > Makefile_AIX Makefile_MINGW: $(M4)/Makefile.m4 -cp Makefile_MINGW Makefile_MINGW_old m4 -P $(PYCIFRWDEF) -Dcbf_system=MINGW $(M4)/Makefile.m4 > Makefile_MINGW Makefile_IRIX_gcc: $(M4)/Makefile.m4 -cp Makefile_IRIX_gcc Makefile_IRIX_gcc_old m4 -P $(PYCIFREDEF) -Dcbf_system=IRIX_gcc $(M4)/Makefile.m4 > Makefile_IRIX_gcc Makefile: $(M4)/Makefile.m4 -cp Makefile Makefile_old m4 -P $(PYCIFRWDEF) -Dcbf_system=default $(M4)/Makefile.m4 > Makefile symlinksdone: chmod a+x .symlinks chmod a+x .undosymlinks chmod a+x doc/.symlinks chmod a+x doc/.undosymlinks chmod a+x libtool/.symlinks chmod a+x libtool/.undosymlinks ./.symlinks $(SLFLAGS) touch symlinksdone install: all $(INSTALLDIR) $(INSTALLDIR)/lib $(INSTALLDIR)/bin \ $(INSTALLDIR)/include $(INSTALLDIR)/include/cbflib \ $(PYSOURCE) -chmod -R 755 $(INSTALLDIR)/include/cbflib -chmod 755 $(INSTALLDIR)/lib/libcbf.a -cp $(INSTALLDIR)/lib/libcbf.a $(INSTALLDIR)/lib/libcbf_old.a cp $(LIB)/libcbf.a $(INSTALLDIR)/lib/libcbf.a -cp $(INSTALLDIR)/lib/libimg.a $(INSTALLDIR)/lib/libimg_old.a cp $(LIB)/libimg.a $(INSTALLDIR)/lib/libimg.a -cp $(INSTALLDIR)/bin/adscimg2cbf $(INSTALLDIR)/bin/adscimg2cbf_old cp $(BIN)/adscimg2cbf $(INSTALLDIR)/bin/adscimg2cbf -cp $(INSTALLDIR)/bin/cbf2adscimg $(INSTALLDIR)/bin/cbf2adscimg_old cp $(BIN)/cbf2adscimg $(INSTALLDIR)/bin/cbf2adscimg -cp $(INSTALLDIR)/bin/convert_image $(INSTALLDIR)/bin/convert_image_old cp $(BIN)/convert_image $(INSTALLDIR)/bin/convert_image -cp $(INSTALLDIR)/bin/convert_minicbf $(INSTALLDIR)/bin/convert_minicbf_old cp $(BIN)/convert_minicbf $(INSTALLDIR)/bin/convert_minicbf -cp $(INSTALLDIR)/bin/makecbf $(INSTALLDIR)/bin/makecbf_old cp $(BIN)/makecbf $(INSTALLDIR)/bin/makecbf -cp $(INSTALLDIR)/bin/img2cif $(INSTALLDIR)/bin/img2cif_old cp $(BIN)/img2cif $(INSTALLDIR)/bin/img2cif -cp $(INSTALLDIR)/bin/cif2cbf $(INSTALLDIR)/bin/cif2cbf_old cp $(BIN)/cif2cbf $(INSTALLDIR)/bin/cif2cbf -cp $(INSTALLDIR)/bin/sequence_match $(INSTALLDIR)/bin/sequence_match_old cp $(BIN)/sequence_match $(INSTALLDIR)/bin/sequence_match -cp $(INSTALLDIR)/bin/arvai_test $(INSTALLDIR)/bin/arvai_test_old cp $(BIN)/arvai_test $(INSTALLDIR)/bin/arvai_test -cp $(INSTALLDIR)/bin/cif2c $(INSTALLDIR)/bin/cif2c_old cp $(BIN)/cif2c $(INSTALLDIR)/bin/cif2c -cp $(INSTALLDIR)/bin/testreals $(INSTALLDIR)/bin/testreals_old cp $(BIN)/testreals $(INSTALLDIR)/bin/testreals -cp $(INSTALLDIR)/bin/testflat $(INSTALLDIR)/bin/testflat_old cp $(BIN)/testflat $(INSTALLDIR)/bin/testflat -cp $(INSTALLDIR)/bin/testflatpacked $(INSTALLDIR)/bin/testflatpacked_old cp $(BIN)/testflatpacked $(INSTALLDIR)/bin/testflatpacked chmod -R 755 $(INSTALLDIR)/include/cbflib -rm -rf $(INSTALLDIR)/include/cbflib_old -cp -r $(INSTALLDIR)/include/cbflib $(INSTALLDIR)/include/cbflib_old -rm -rf $(INSTALLDIR)/include/cbflib cp -r $(INCLUDE) $(INSTALLDIR)/include/cbflib chmod 644 $(INSTALLDIR)/lib/libcbf.a chmod 755 $(INSTALLDIR)/bin/convert_image chmod 755 $(INSTALLDIR)/bin/convert_minicbf chmod 755 $(INSTALLDIR)/bin/makecbf chmod 755 $(INSTALLDIR)/bin/img2cif chmod 755 $(INSTALLDIR)/bin/cif2cbf chmod 755 $(INSTALLDIR)/bin/sequence_match chmod 755 $(INSTALLDIR)/bin/arvai_test chmod 755 $(INSTALLDIR)/bin/cif2c chmod 755 $(INSTALLDIR)/bin/testreals chmod 755 $(INSTALLDIR)/bin/testflat chmod 755 $(INSTALLDIR)/bin/testflatpacked chmod 644 $(INSTALLDIR)/include/cbflib/*.h # # REGEX # ifneq ($(REGEXDEP),) $(REGEXDEP): $(REGEX) (cd $(REGEX); ./configure; make install) endif $(REGEX): $(DOWNLOAD) $(REGEXURL) tar -xvf $(REGEX).tar.gz -rm $(REGEX).tar.gz # # TIFF # $(TIFF): $(DOWNLOAD) $(TIFFURL) tar -xvf $(TIFF).tar.gz -rm $(TIFF).tar.gz (cd $(TIFF); ./configure --prefix=$(TIFFPREFIX); make install) # # Directories # $(INSTALLDIR): mkdir -p $(INSTALLDIR) $(INSTALLDIR)/lib: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/lib $(INSTALLDIR)/bin: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/bin $(INSTALLDIR)/include: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/include $(INSTALLDIR)/include/cbflib: $(INSTALLDIR)/include mkdir -p $(INSTALLDIR)/include/cbflib $(LIB): mkdir $@ $(BIN): mkdir $@ $(SOLIB): mkdir $@ $(JCBF): mkdir $@ # # Parser # $(SRC)/cbf_stx.c: $(SRC)/cbf.stx.y bison $(SRC)/cbf.stx.y -o $(SRC)/cbf.stx.tab.c -d mv $(SRC)/cbf.stx.tab.c $(SRC)/cbf_stx.c mv $(SRC)/cbf.stx.tab.h $(INCLUDE)/cbf_stx.h # # CBF library # $(LIB)/libcbf.a: $(SOURCE) $(HEADERS) $(COMMONDEP) $(LIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG) $(INCLUDES) $(WARNINGS) -c $(SOURCE) $(AR) cr $@ *.o mv *.o $(LIB) ifneq ($(RANLIB),) $(RANLIB) $@ endif $(SOLIB)/libcbf.so: $(SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(SOURCE) $(CC) -o $@ *.o $(SOLDFLAGS) $(EXTRALIBS) rm *.o # # IMG library # $(LIB)/libimg.a: $(EXAMPLES)/img.c $(HEADERS) $(COMMONDEP) $(LIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) -c $(EXAMPLES)/img.c $(AR) cr $@ img.o ifneq ($(RANLIB),) $(RANLIB) $@ endif rm img.o $(SOLIB)/libimg.so: $(SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(EXAMPLES)/img.c $(CC) -o $@ img.o $(SOLDFLAGS) rm img.o # # CBF and IMG libraries # CBF_IMG_LIBS: $(LIB)/libcbf.a $(LIB)/libimg.a # # FCB library # $(LIB)/libfcb.a: $(F90SOURCE) $(COMMONDEP) $(LIB) ifneq ($(F90C),) $(F90C) $(F90FLAGS) -c $(F90SOURCE) $(AR) cr $@ *.o ifneq ($(RANLIB),) $(RANLIB) $@ endif rm *.o else echo "Define F90C to build $(LIB)/libfcb.a" endif $(SOLIB)/libfcb.so: $(F90SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) ifneq ($(F90C),) $(F90C) $(F90FLAGS) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(F90SOURCE) $(F90C) $(F90FLAGS) -o $@ *.o $(SOLDFLAGS) rm *.o else echo "Define F90C to build $(SOLIB)/libfcb.so" endif # # Python bindings # $(PYCBF)/_pycbf.$(PYCBFEXT): $(PYCBF) $(LIB)/libcbf.a \ $(PYCBF)/$(SETUP_PY) \ $(LIB)/libfcb.a \ $(LIB)/libimg.a \ $(PYCBF)/pycbf.i \ $(PYCBF)/cbfhandlewrappers.i \ $(PYCBF)/cbfdetectorwrappers.i \ $(PYCBF)/cbfgenericwrappers.i \ $(PYCBF)/cbfgoniometerwrappers.i (cd $(PYCBF); python $(SETUP_PY) build $(PYCBFBOPT); cp build/lib.*/_pycbf.$(PYCBFEXT) .) $(PYCBF)/setup.py: $(M4)/setup_py.m4 (m4 -P -Dregexlib=NOREGEXLIB -Dregexlibdir=NOREGEXLIBDIR $(M4)/setup_py.m4 > $@) $(PYCBF)/setup_MINGW.py: m4/setup_py.m4 (m4 -P -Dregexlib=regex -Dregexlibdir=$(REGEXDIR) $(M4)/setup_py.m4 > $@) $(LIB)/_pycbf.$(PYCBFEXT): $(PYCBF)/_pycbf.$(PYCBFEXT) cp $(PYCBF)/_pycbf.$(PYCBFEXT) $(LIB)/_pycbf.$(PYCBFEXT) $(PYCBF)/pycbf.pdf: $(PYCBF)/pycbf.w (cd $(PYCBF); \ $(NUWEB) pycbf; \ latex pycbf; \ $(NUWEB) pycbf; \ latex pycbf; \ dvipdfm pycbf ) $(PYCBF)/CBFlib.txt: $(DOC)/CBFlib.html links -dump $(DOC)/CBFlib.html > $(PYCBF)/CBFlib.txt $(PYCBF)/cbfhandlewrappers.i \ $(PYCBF)/cbfdetectorwrappers.i \ $(PYCBF)/cbfgenericwrappers.i \ $(PYCBF)/cbfgoniometerwrappers.i: $(PYCBF)/CBFlib.txt $(PYCBF)/make_pycbf.py (cd $(PYCBF); python make_pycbf.py; $(PYSWIG) pycbf.i; python setup.py build) # # Java bindings # $(JCBF)/cbflib-$(VERSION).jar: $(JCBF) $(JCBF)/jcbf.i $(JSWIG) -I$(INCLUDE) -package org.iucr.cbflib -outdir $(JCBF) $(JCBF)/jcbf.i $(JAVAC) -d . $(JCBF)/*.java $(JAR) cf $@ org $(SOLIB)/libcbf_wrap.so: $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf.so $(CC) $(CFLAGS) $(NOLLFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) $(JAVAINCLUDES) -c $(JCBF)/jcbf_wrap.c $(CC) -o $@ jcbf_wrap.o $(SOLDFLAGS) -L$(SOLIB) -lcbf rm jcbf_wrap.o # # F90SOURCE # $(SRC)/fcb_exit_binary.f90: $(M4)/fcb_exit_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_exit_binary.m4) > $(SRC)/fcb_exit_binary.f90 $(SRC)/fcb_next_binary.f90: $(M4)/fcb_next_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_next_binary.m4) > $(SRC)/fcb_next_binary.f90 $(SRC)/fcb_open_cifin.f90: $(M4)/fcb_open_cifin.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_open_cifin.m4) > $(SRC)/fcb_open_cifin.f90 $(SRC)/fcb_packed.f90: $(M4)/fcb_packed.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_packed.m4) > $(SRC)/fcb_packed.f90 $(SRC)/fcb_read_bits.f90: $(M4)/fcb_read_bits.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_bits.m4) > $(SRC)/fcb_read_bits.f90 $(SRC)/fcb_read_image.f90: $(M4)/fcb_read_image.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_image.m4) > $(SRC)/fcb_read_image.f90 $(SRC)/fcb_read_xds_i2.f90: $(M4)/fcb_read_xds_i2.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_xds_i2.m4) > $(SRC)/fcb_read_xds_i2.f90 $(EXAMPLES)/test_fcb_read_image.f90: $(M4)/test_fcb_read_image.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) test_fcb_read_image.m4) > $(EXAMPLES)/test_fcb_read_image.f90 $(EXAMPLES)/test_xds_binary.f90: $(M4)/test_xds_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) test_xds_binary.m4) > $(EXAMPLES)/test_xds_binary.f90 # # convert_image example program # $(BIN)/convert_image: $(LIB)/libcbf.a $(EXAMPLES)/convert_image.c $(EXAMPLES)/img.c \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/convert_image.c $(EXAMPLES)/img.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # convert_minicbf example program # $(BIN)/convert_minicbf: $(LIB)/libcbf.a $(EXAMPLES)/convert_minicbf.c \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/convert_minicbf.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # makecbf example program # $(BIN)/makecbf: $(LIB)/libcbf.a $(EXAMPLES)/makecbf.c $(LIB)/libimg.a $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/makecbf.c -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # adscimg2cbf example program # $(BIN)/adscimg2cbf: $(LIB)/libcbf.a $(EXAMPLES)/adscimg2cbf.c $(EXAMPLES)/adscimg2cbf_sub.c $(CC) $(CFLAGS) $(NOLLFLAG) -D_SVID_SOURCE $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/adscimg2cbf.c $(EXAMPLES)/adscimg2cbf_sub.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # cbf2adscimg example program # $(BIN)/cbf2adscimg: $(LIB)/libcbf.a $(EXAMPLES)/cbf2adscimg.c $(EXAMPLES)/cbf2adscimg_sub.c $(CC) $(CFLAGS) $(NOLLFLAG) -D_SVID_SOURCE $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cbf2adscimg.c $(EXAMPLES)/cbf2adscimg_sub.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # changtestcompression example program # $(BIN)/changtestcompression: $(LIB)/libcbf.a $(EXAMPLES)/changtestcompression.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/changtestcompression.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # img2cif example program # $(BIN)/img2cif: $(LIB)/libcbf.a $(EXAMPLES)/img2cif.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOTPINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/img2cif.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # cif2cbf example program # $(BIN)/cif2cbf: $(LIB)/libcbf.a $(EXAMPLES)/cif2cbf.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cif2cbf.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # dectris cbf_template_t program # $(BIN)/cbf_template_t: $(DECTRIS_EXAMPLES)/cbf_template_t.c \ $(DECTRIS_EXAMPLES)/mx_cbf_t_extras.h \ $(DECTRIS_EXAMPLES)/mx_parms.h $(CC) $(CFLAGS) $(NOLLFLAG) -I $(DECTRIS_EXAMPLES) $(WARNINGS) \ $(DECTRIS_EXAMPLES)/cbf_template_t.c -o $@ # # testcell example program # $(BIN)/testcell: $(LIB)/libcbf.a $(EXAMPLES)/testcell.C $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testcell.C -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # cif2c example program # $(BIN)/cif2c: $(LIB)/libcbf.a $(EXAMPLES)/cif2c.c $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cif2c.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # sauter_test example program # $(BIN)/sauter_test: $(LIB)/libcbf.a $(EXAMPLES)/sauter_test.C $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/sauter_test.C -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # sequence_match example program # $(BIN)/sequence_match: $(LIB)/libcbf.a $(EXAMPLES)/sequence_match.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/sequence_match.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # tiff2cbf example program # $(BIN)/tiff2cbf: $(LIB)/libcbf.a $(EXAMPLES)/tiff2cbf.c \ $(GOPTLIB) $(GOPTINC) $(TIFF) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ -I$(TIFFPREFIX)/include $(EXAMPLES)/tiff2cbf.c $(GOPTLIB) -L$(LIB) \ -lcbf -L$(TIFFPREFIX)/lib -ltiff $(EXTRALIBS) -limg -o $@ # # Andy Arvai's buffered read test program # $(BIN)/arvai_test: $(LIB)/libcbf.a $(EXAMPLES)/arvai_test.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/arvai_test.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # testreals example program # $(BIN)/testreals: $(LIB)/libcbf.a $(EXAMPLES)/testreals.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testreals.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testflat example program # $(BIN)/testflat: $(LIB)/libcbf.a $(EXAMPLES)/testflat.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testflat.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testflatpacked example program # $(BIN)/testflatpacked: $(LIB)/libcbf.a $(EXAMPLES)/testflatpacked.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testflatpacked.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ ifneq ($(F90C),) # # test_xds_binary example program # $(BIN)/test_xds_binary: $(LIB)/libfcb.a $(EXAMPLES)/test_xds_binary.f90 $(F90C) $(F90FLAGS) $(F90LDFLAGS) $(EXAMPLES)/test_xds_binary.f90 \ -L$(LIB) -lfcb -o $@ # # test_fcb_read_image example program # $(BIN)/test_fcb_read_image: $(LIB)/libfcb.a $(EXAMPLES)/test_fcb_read_image.f90 $(F90C) $(F90FLAGS) $(F90LDFLAGS) $(EXAMPLES)/test_fcb_read_image.f90 \ -L$(LIB) -lfcb -o $@ endif # # testcbf (C) # $(BIN)/ctestcbf: $(EXAMPLES)/testcbf.c $(LIB)/libcbf.a $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testcbf.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testcbf (Java) # $(BIN)/testcbf.class: $(EXAMPLES)/testcbf.java $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf_wrap.so $(JAVAC) -cp $(JCBF)/cbflib-$(VERSION).jar -d $(BIN) $(EXAMPLES)/testcbf.java # # Data files for tests # $(DATADIRI): (cd ..; $(DOWNLOAD) $(DATAURLI)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Input.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Input.tar.gz) $(DATADIRO): (cd ..; $(DOWNLOAD) $(DATAURLO)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Output.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Output.tar.gz) $(DATADIRS): (cd ..; $(DOWNLOAD) $(DATAURLS)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz) # Input Data Files TESTINPUT_BASIC = example.mar2300 DATADIRI_INPUT_BASIC = $(DATADIRI)/example.mar2300$(CEXT) TESTINPUT_EXTRA = 9ins.cif mb_LP_1_001.img insulin_pilatus6m.cbf testrealin.cbf \ testflatin.cbf testflatpackedin.cbf XRD1621.tif DATADIRI_INPUT_EXTRA = $(DATADIRI)/9ins.cif$(CEXT) $(DATADIRI)/mb_LP_1_001.img$(CEXT) \ $(DATADIRI)/insulin_pilatus6m.cbf$(CEXT) $(DATADIRI)/testrealin.cbf$(CEXT) \ $(DATADIRI)/testflatin.cbf$(CEXT) $(DATADIRI)/testflatpackedin.cbf$(CEXT) \ $(DATADIRI)/XRD1621.tif$(CEXT) # Output Data Files TESTOUTPUT = adscconverted_flat_orig.cbf \ adscconverted_orig.cbf converted_flat_orig.cbf converted_orig.cbf \ insulin_pilatus6mconverted_orig.cbf \ mb_LP_1_001_orig.cbf testcell_orig.prt \ test_xds_bin_testflatout_orig.out \ test_xds_bin_testflatpackedout_orig.out test_fcb_read_testflatout_orig.out \ test_fcb_read_testflatpackedout_orig.out \ XRD1621_orig.cbf XRD1621_I4encbC100_orig.cbf NEWTESTOUTPUT = adscconverted_flat.cbf \ adscconverted.cbf converted_flat.cbf converted.cbf \ insulin_pilatus6mconverted.cbf \ mb_LP_1_001.cbf testcell.prt \ test_xds_bin_testflatout.out \ test_xds_bin_testflatpackedout.out test_fcb_read_testflatout.out \ test_fcb_read_testflatpackedout.out \ XRD1621.cbf XRD1621_I4encbC100.cbf DATADIRO_OUTPUT = $(DATADIRO)/adscconverted_flat_orig.cbf$(CEXT) \ $(DATADIRO)/adscconverted_orig.cbf$(CEXT) \ $(DATADIRO)/converted_flat_orig.cbf$(CEXT) \ $(DATADIRO)/converted_orig.cbf$(CEXT) \ $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(CEXT) \ $(DATADIRO)/mb_LP_1_001_orig.cbf$(CEXT) \ $(DATADIRO)/testcell_orig.prt$(CEXT) \ $(DATADIRO)/test_xds_bin_testflatout_orig.out$(CEXT) \ $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(CEXT) \ $(DATADIRO)/test_fcb_read_testflatout_orig.out$(CEXT) \ $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(CEXT) \ $(DATADIRO)/XRD1621_orig.cbf$(CEXT) \ $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(CEXT) DATADIRO_OUTPUT_SIGNATURES = $(DATADIRO)/adscconverted_flat_orig.cbf$(SEXT) \ $(DATADIRO)/adscconverted_orig.cbf$(SEXT) \ $(DATADIRO)/converted_flat_orig.cbf$(SEXT) \ $(DATADIRO)/converted_orig.cbf$(SEXT) \ $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(SEXT) \ $(DATADIRO)/mb_LP_1_001_orig.cbf$(SEXT) \ $(DATADIRO)/testcell_orig.prt$(SEXT) \ $(DATADIRO)/test_xds_bin_testflatout_orig.out$(SEXT) \ $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(SEXT) \ $(DATADIRO)/test_fcb_read_testflatout_orig.out$(SEXT) \ $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(SEXT) \ $(DATADIRO)/XRD1621_orig.cbf$(SEXT) \ $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(SEXT) # Output Data File Signatures TESTOUTPUTSIGS = adscconverted_flat_orig.cbf$(SEXT) \ adscconverted_orig.cbf$(SEXT) converted_flat_orig.cbf$(SEXT) converted_orig.cbf$(SEXT) \ insulin_pilatus6mconverted_orig.cbf$(SEXT) \ mb_LP_1_001_orig.cbf$(SEXT) testcell_orig.prt$(SEXT) \ test_xds_bin_testflatout_orig.out$(SEXT) \ test_xds_bin_testflatpackedout_orig.out$(SEXT) test_fcb_read_testflatout_orig.out$(SEXT) \ test_fcb_read_testflatpackedout_orig.out$(SEXT) \ XRD1621_orig.cbf$(SEXT) DATADIRS_OUTPUT_SIGNATURES = $(DATADIRS)/adscconverted_flat_orig.cbf$(SEXT) \ $(DATADIRS)/adscconverted_orig.cbf$(SEXT) \ $(DATADIRS)/converted_flat_orig.cbf$(SEXT) \ $(DATADIRS)/converted_orig.cbf$(SEXT) \ $(DATADIRS)/insulin_pilatus6mconverted_orig.cbf$(SEXT) \ $(DATADIRS)/mb_LP_1_001_orig.cbf$(SEXT) \ $(DATADIRS)/testcell_orig.prt$(SEXT) \ $(DATADIRS)/test_xds_bin_testflatout_orig.out$(SEXT) \ $(DATADIRS)/test_xds_bin_testflatpackedout_orig.out$(SEXT) \ $(DATADIRS)/test_fcb_read_testflatout_orig.out$(SEXT) \ $(DATADIRS)/test_fcb_read_testflatpackedout_orig.out$(SEXT) \ $(DATADIRS)/XRD1621_orig.cbf$(SEXT) \ $(DATADIRS)/XRD1621_I4encbC100_orig.cbf$(SEXT) # Fetch Input Data Files $(TESTINPUT_BASIC): $(DATADIRI) $(DATADIRI_INPUT_BASIC) $(DECOMPRESS) < $(DATADIRI)/$@$(CEXT) > $@ cp $(DATADIRI)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) $(TESTINPUT_EXTRA): $(DATADIRI) $(DATADIRI_INPUT_EXTRA) $(DECOMPRESS) < $(DATADIRI)/$@$(CEXT) > $@ cp $(DATADIRI)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) # Fetch Output Data Files and Signatures $(TESTOUTPUT): $(DATADIRO) $(DATADIRO_OUTPUT) $(DATADIRO_OUTPUT_SIGNATURES) $(DECOMPRESS) < $(DATADIRO)/$@$(CEXT) > $@ cp $(DATADIRO)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) # Fetch Output Data File Signatures $(TESTOUTPUTSIGS): $(DATADIRS) $(DATADIRS_OUTPUT_SIGNATURES) cp $(DATADIRS)/$@ $@ # # Tests # tests: $(LIB) $(BIN) symlinksdone basic extra dectristests pycbftests tests_sigs_only: $(LIB) $(BIN) symlinksdone basic extra_sigs_only restore_output: $(NEWTESTOUTPUT) $(DATADIRO) $(SIGNATURE) < adscconverted_flat.cbf > $(DATADIRO)/adscconverted_flat_orig.cbf$(SEXT) $(SIGNATURE) < adscconverted.cbf > $(DATADIRO)/adscconverted_orig.cbf$(SEXT) $(SIGNATURE) < converted_flat.cbf > $(DATADIRO)/converted_flat_orig.cbf$(SEXT) $(SIGNATURE) < converted.cbf > $(DATADIRO)/converted_orig.cbf$(SEXT) $(SIGNATURE) < insulin_pilatus6mconverted.cbf > $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(SEXT) $(SIGNATURE) < mb_LP_1_001.cbf$ > $(DATADIRO)/mb_LP_1_001_orig.cbf$(SEXT) $(SIGNATURE) < testcell.prt > $(DATADIRO)/testcell_orig.prt$(SEXT) $(SIGNATURE) < test_xds_bin_testflatout.out > $(DATADIRO)/test_xds_bin_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_xds_bin_testflatpackedout.out > $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatout.out > $(DATADIRO)/test_fcb_read_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatpackedout.out > $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < XRD1621.cbf > $(DATADIRO)/XRD1621_orig.cbf$(SEXT) $(SIGNATURE) < XRD1621_I4encbC100.cbf > $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(SEXT) $(COMPRESS) < adscconverted_flat.cbf > $(DATADIRO)/adscconverted_flat_orig.cbf$(CEXT) $(COMPRESS) < adscconverted.cbf > $(DATADIRO)/adscconverted_orig.cbf$(CEXT) $(COMPRESS) < converted_flat.cbf > $(DATADIRO)/converted_flat_orig.cbf$(CEXT) $(COMPRESS) < converted.cbf > $(DATADIRO)/converted_orig.cbf$(CEXT) $(COMPRESS) < insulin_pilatus6mconverted.cbf > $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(CEXT) $(COMPRESS) < mb_LP_1_001.cbf$ > $(DATADIRO)/mb_LP_1_001_orig.cbf$(CEXT) $(COMPRESS) < testcell.prt > $(DATADIRO)/testcell_orig.prt$(CEXT) $(COMPRESS) < test_xds_bin_testflatout.out > $(DATADIRO)/test_xds_bin_testflatout_orig.out$(CEXT) $(COMPRESS) < test_xds_bin_testflatpackedout.out > $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(CEXT) $(COMPRESS) < test_fcb_read_testflatout.out > $(DATADIRO)/test_fcb_read_testflatout_orig.out$(CEXT) $(COMPRESS) < test_fcb_read_testflatpackedout.out > $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(CEXT) $(COMPRESS) < XRD1621.cbf > $(DATADIRO)/XRD1621_orig.cbf$(CEXT) $(COMPRESS) < XRD1621_I4encbC100.cbf > $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(CEXT) restore_sigs_only: $(NEWTESTOUTPUT) $(DATADIRS) $(SIGNATURE) < adscconverted_flat.cbf > $(DATADIRS)/adscconverted_flat_orig.cbf$(SEXT) $(SIGNATURE) < adscconverted.cbf > $(DATADIRS)/adscconverted_orig.cbf$(SEXT) $(SIGNATURE) < converted_flat.cbf > $(DATADIRS)/converted_flat_orig.cbf$(SEXT) $(SIGNATURE) < converted.cbf > $(DATADIRS)/converted_orig.cbf$(SEXT) $(SIGNATURE) < insulin_pilatus6mconverted.cbf > $(DATADIRS)/insulin_pilatus6mconverted_orig.cbf$(SEXT) $(SIGNATURE) < mb_LP_1_001.cbf$ > $(DATADIRS)/mb_LP_1_001_orig.cbf$(SEXT) $(SIGNATURE) < testcell.prt > $(DATADIRS)/testcell_orig.prt$(SEXT) $(SIGNATURE) < test_xds_bin_testflatout.out > $(DATADIRS)/test_xds_bin_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_xds_bin_testflatpackedout.out > $(DATADIRS)/test_xds_bin_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatout.out > $(DATADIRS)/test_fcb_read_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatpackedout.out > $(DATADIRS)/test_fcb_read_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < XRD1621.cbf > $(DATADIRS)/XRD1621_orig.cbf$(SEXT) $(SIGNATURE) < XRD1621_I4encbC100.cbf > $(DATADIRS)/XRD1621_I4encbC100_orig.cbf$(SEXT) restore_signatures: restore_output restore_sigs_only # # Basic Tests # basic: $(BIN)/makecbf $(BIN)/img2cif $(BIN)/cif2cbf $(TESTINPUT_BASIC) $(BIN)/makecbf example.mar2300 makecbf.cbf $(BIN)/img2cif -c flatpacked -m headers -d digest \ -e base64 example.mar2300 img2cif_packed.cif $(BIN)/img2cif -c canonical -m headers -d digest \ -e base64 example.mar2300 img2cif_canonical.cif $(BIN)/img2cif -c flatpacked -m headers -d digest \ -e none example.mar2300 img2cif_packed.cbf $(BIN)/img2cif -c canonical -m headers -d digest \ -e none example.mar2300 img2cif_canonical.cbf $(BIN)/cif2cbf -e none -c flatpacked \ img2cif_canonical.cif cif2cbf_packed.cbf $(BIN)/cif2cbf -e none -c canonical \ img2cif_packed.cif cif2cbf_canonical.cbf -cmp cif2cbf_packed.cbf makecbf.cbf -cmp cif2cbf_packed.cbf img2cif_packed.cbf -cmp cif2cbf_canonical.cbf img2cif_canonical.cbf # # Extra Tests # ifneq ($(F90C),) extra: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/test_xds_binary $(BIN)/test_fcb_read_image $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg \ $(BIN)/changtestcompression $(BIN)/tiff2cbf \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUT) else extra: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUT) endif $(TIME) $(BIN)/cif2cbf -e hex -c none \ makecbf.cbf cif2cbf_ehcn.cif $(TIME) $(BIN)/cif2cbf -e none -c flatpacked \ cif2cbf_ehcn.cif cif2cbf_encp.cbf; rm cif2cbf_ehcn.cif -cmp makecbf.cbf cif2cbf_encp.cbf $(TIME) $(BIN)/cif2cbf -i 9ins.cif -o 9ins.cbf -cmp 9ins.cif 9ins.cbf $(TIME) $(BIN)/convert_image -F example.mar2300 converted_flat.cbf -cmp converted_flat.cbf converted_flat_orig.cbf $(TIME) $(BIN)/convert_image example.mar2300 converted.cbf -cmp converted.cbf converted_orig.cbf -$(TIME) $(BIN)/testcell < testcell.dat > testcell.prt -cmp testcell.prt testcell_orig.prt $(TIME) $(BIN)/convert_image -F -d adscquantum315 mb_LP_1_001.img adscconverted_flat.cbf -cmp adscconverted_flat.cbf adscconverted_flat_orig.cbf $(TIME) $(BIN)/convert_image -d adscquantum315 mb_LP_1_001.img adscconverted.cbf -cmp adscconverted.cbf adscconverted_orig.cbf $(TIME) $(BIN)/adscimg2cbf --no_pad --cbf_packed,flat mb_LP_1_001.img -cmp mb_LP_1_001.cbf mb_LP_1_001_orig.cbf ifneq ($(CLEANTESTS),) mv mb_LP_1_001.cbf nmb_LP_1_001.cbf else cp mb_LP_1_001.cbf nmb_LP_1_001.cbf endif $(TIME) $(BIN)/cbf2adscimg nmb_LP_1_001.cbf -cmp nmb_LP_1_001.img mb_LP_1_001.img rm nmb_LP_1_001.cbf ifneq ($(CLEANTESTS),) rm nmb_LP_1_001.img endif $(TIME) $(BIN)/convert_minicbf -d pilatus6m insulin_pilatus6m.cbf insulin_pilatus6mconverted.cbf -cmp insulin_pilatus6mconverted.cbf insulin_pilatus6mconverted_orig.cbf $(TIME) $(BIN)/testreals -cmp testrealin.cbf testrealout.cbf $(TIME) $(BIN)/testflat -cmp testflatin.cbf testflatout.cbf $(TIME) $(BIN)/testflatpacked -cmp testflatpackedin.cbf testflatpackedout.cbf ifneq ($(F90C),) echo testflatout.cbf | $(TIME) $(BIN)/test_xds_binary > test_xds_bin_testflatout.out -$(DIFF) test_xds_bin_testflatout.out test_xds_bin_testflatout_orig.out echo testflatpackedout.cbf | $(TIME) $(BIN)/test_xds_binary > test_xds_bin_testflatpackedout.out -$(DIFF) test_xds_bin_testflatpackedout.out test_xds_bin_testflatpackedout_orig.out echo testflatout.cbf | $(TIME) $(BIN)/test_fcb_read_image > test_fcb_read_testflatout.out -$(DIFF) test_fcb_read_testflatout.out test_fcb_read_testflatout_orig.out echo testflatpackedout.cbf | $(TIME) $(BIN)/test_fcb_read_image > test_fcb_read_testflatpackedout.out -$(DIFF) test_fcb_read_testflatpackedout.out test_fcb_read_testflatpackedout_orig.out endif $(TIME) $(BIN)/sauter_test $(TIME) $(BIN)/changtestcompression $(TIME) (export LD_LIBRARY_PATH=$(LIB);$(BIN)/tiff2cbf XRD1621.tif XRD1621.cbf) -$(DIFF) XRD1621.cbf XRD1621_orig.cbf $(TIME) $(BIN)/cif2cbf -I 4 -C 100. -L 0. -e n -c b -i XRD1621.cbf -o XRD1621_I4encbC100.cbf -$(DIFF) XRD1621_I4encbC100.cbf XRD1621_I4encbC100_orig.cbf ifneq ($(F90C),) extra_sigs_only: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/test_xds_binary $(BIN)/test_fcb_read_image $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg $(BIN)/tiff2cbf \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) else extra_sigs_only: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf\ basic $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) endif $(TIME) $(BIN)/cif2cbf -e hex -c none \ makecbf.cbf cif2cbf_ehcn.cif $(TIME) $(BIN)/cif2cbf -e none -c packed \ cif2cbf_ehcn.cif cif2cbf_encp.cbf; rm cif2cbf_ehcn.cif -cmp makecbf.cbf cif2cbf_encp.cbf $(TIME) $(BIN)/cif2cbf -i 9ins.cif -o 9ins.cbf -cmp 9ins.cif 9ins.cbf $(TIME) $(BIN)/convert_image -F example.mar2300 converted_flat.cbf -$(SIGNATURE) < converted_flat.cbf | $(DIFF) - converted_flat_orig.cbf$(SEXT); rm converted_flat.cbf $(TIME) $(BIN)/convert_image example.mar2300 converted.cbf -$(SIGNATURE) < converted.cbf | $(DIFF) - converted_orig.cbf$(SEXT); rm converted.cbf -$(TIME) $(BIN)/testcell < testcell.dat | \ $(SIGNATURE) | $(DIFF) - testcell_orig.prt$(SEXT) $(TIME) $(BIN)/convert_image -F -d adscquantum315 mb_LP_1_001.img adscconverted_flat.cbf -$(SIGNATURE) < adscconverted_flat.cbf | $(DIFF) - adscconverted_flat_orig.cbf$(SEXT) $(TIME) $(BIN)/convert_image -d adscquantum315 mb_LP_1_001.img adscconverted.cbf -$(SIGNATURE) < adscconverted.cbf | $(DIFF) - adscconverted_orig.cbf$(SEXT); rm adscconverted.cbf $(TIME) $(BIN)/adscimg2cbf --cbf_packed,flat mb_LP_1_001.img -$(SIGNATURE) < mb_LP_1_001.cbf | $(DIFF) - mb_LP_1_001_orig.cbf$(SEXT) mv mb_LP_1_001.cbf nmb_LP_1_001.cbf $(TIME) $(BIN)/cbf2adscimg nmb_LP_1_001.cbf -cmp nmb_LP_1_001.img mb_LP_1_001.img rm nmb_LP_1_001.cbf rm nmb_LP_1_001.img $(TIME) $(BIN)/convert_minicbf -d pilatus6m insulin_pilatus6m.cbf insulin_pilatus6mconverted.cbf -$(SIGNATURE) < insulin_pilatus6mconverted.cbf | $(DIFF) - insulin_pilatus6mconverted_orig.cbf$(SEXT); rm insulin_pilatus6mconverted.cbf $(TIME) $(BIN)/testreals -cmp testrealin.cbf testrealout.cbf $(TIME) $(BIN)/testflat -cmp testflatin.cbf testflatout.cbf $(TIME) $(BIN)/testflatpacked -cmp testflatpackedin.cbf testflatpackedout.cbf ifneq ($(F90C),) echo testflatout.cbf | $(TIME) $(BIN)/test_xds_binary | \ $(SIGNATURE) | $(DIFF) - test_xds_bin_testflatout_orig.out$(SEXT) echo testflatpackedout.cbf | $(TIME) $(BIN)/test_xds_binary | \ $(SIGNATURE) | $(DIFF) - test_xds_bin_testflatpackedout_orig.out$(SEXT) echo testflatout.cbf | $(TIME) $(BIN)/test_fcb_read_image | \ $(SIGNATURE) | $(DIFF) - test_fcb_read_testflatout_orig.out$(SEXT) echo testflatpackedout.cbf | $(TIME) $(BIN)/test_fcb_read_image | \ $(SIGNATURE) | $(DIFF) - test_fcb_read_testflatpackedout_orig.out$(SEXT) endif $(TIME) $(BIN)/sauter_test $(TIME) $(BIN)/tiff2cbf XRD1621.tif XRD1621.cbf $(TIME) $(BIN)/cif2cbf -I 4 -C 100. -L 0. -e n -c b -i XRD1621.cbf -o XRD1621_I4encbC100.cbf -$(SIGNATURE) < XRD1621.cbf | $(DIFF) - XRD1621_orig.cbf$(SEXT); rm XRD1621.cbf -$(SIGNATURE) < XRD1621_I4encbC100.cbf | $(DIFF) - XRD1621_I4encbC100_orig.cbf$(SEXT); rm XRD1621_I4encbC100.cbf @-rm -f adscconverted_flat.cbf @-rm -f $(TESTINPUT_BASIC) $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) @-rm -f cif2cbf_packed.cbf makecbf.cbf \ cif2cbf_packed.cbf img2cif_packed.cbf \ cif2cbf_canonical.cbf img2cif_canonical.cbf @-rm -f testrealout.cbf testflatout.cbf testflatpackedout.cbf \ cif2cbf_encp.cbf img2cif_canonical.cif img2cif_packed.cif 9ins.cbf pycbftests: $(PYCBF)/_pycbf.$(PYCBFEXT) (cd $(PYCBF); python pycbf_test1.py) (cd $(PYCBF); python pycbf_test2.py) (cd $(PYCBF); python pycbf_test3.py) javatests: $(BIN)/ctestcbf $(BIN)/testcbf.class $(SOLIB)/libcbf_wrap.so $(BIN)/ctestcbf > testcbfc.txt $(LDPREFIX) java -cp $(JCBF)/cbflib-$(VERSION).jar:$(BIN) testcbf > testcbfj.txt $(DIFF) testcbfc.txt testcbfj.txt dectristests: $(BIN)/cbf_template_t $(DECTRIS_EXAMPLES)/cbf_test_orig.out (cd $(DECTRIS_EXAMPLES); ../../bin/cbf_template_t; diff -a -u cbf_test_orig.out cbf_template_t.out) # # Remove all non-source files # empty: @-rm -f $(LIB)/*.o @-rm -f $(LIB)/libcbf.a @-rm -f $(LIB)/libfcb.a @-rm -f $(LIB)/libimg.a @-rm -f $(LIB)/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/build/*/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/build/src/cbf_simple.o @-rm -f $(PYCBF)/build/*/pycbf_wrap.o @-rm -rf $(BIN)/adscimg2cbf* @-rm -rf $(BIN)/cbf2adscimg* @-rm -rf $(BIN)/makecbf* @-rm -rf $(BIN)/img2cif* @-rm -rf $(BIN)/cif2cbf* @-rm -rf $(BIN)/convert_image* @-rm -rf $(BIN)/convert_minicbf* @-rm -rf $(BIN)/test_fcb_read_image* @-rm -rf $(BIN)/test_xds_binary* @-rm -rf $(BIN)/testcell* @-rm -rf $(BIN)/cif2c* @-rm -rf $(BIN)/testreals* @-rm -rf $(BIN)/testflat* @-rm -rf $(BIN)/testflatpacked* @-rm -rf $(BIN)/cbf_template_t* @-rm -rf $(BIN)/sauter_test* @-rm -rf $(BIN)/arvai_test* @-rm -rf $(BIN)/changtestcompression* @-rm -rf $(BIN)/tiff2cbf* @-rm -f makecbf.cbf @-rm -f img2cif_packed.cif @-rm -f img2cif_canonical.cif @-rm -f img2cif_packed.cbf @-rm -f img2cif_canonical.cbf @-rm -f img2cif_raw.cbf @-rm -f cif2cbf_packed.cbf @-rm -f cif2cbf_canonical.cbf @-rm -f converted.cbf @-rm -f adscconverted.cbf @-rm -f converted_flat.cbf @-rm -f adscconverted_flat.cbf @-rm -f adscconverted_flat_rev.cbf @-rm -f mb_LP_1_001.cbf @-rm -f cif2cbf_ehcn.cif @-rm -f cif2cbf_encp.cbf @-rm -f 9ins.cbf @-rm -f 9ins.cif @-rm -f testcell.prt @-rm -f example.mar2300 @-rm -f converted_orig.cbf @-rm -f adscconverted_orig.cbf @-rm -f converted_flat_orig.cbf @-rm -f adscconverted_flat_orig.cbf @-rm -f adscconverted_flat_rev_orig.cbf @-rm -f mb_LP_1_001_orig.cbf @-rm -f insulin_pilatus6mconverted_orig.cbf @-rm -f insulin_pilatus6mconverted.cbf @-rm -f insulin_pilatus6m.cbf @-rm -f testrealin.cbf @-rm -f testrealout.cbf @-rm -f testflatin.cbf @-rm -f testflatout.cbf @-rm -f testflatpackedin.cbf @-rm -f testflatpackedout.cbf @-rm -f CTC.cbf @-rm -f test_fcb_read_testflatout.out @-rm -f test_fcb_read_testflatpackedout.out @-rm -f test_xds_bin_testflatpackedout.out @-rm -f test_xds_bin_testflatout.out @-rm -f test_fcb_read_testflatout_orig.out @-rm -f test_fcb_read_testflatpackedout_orig.out @-rm -f test_xds_bin_testflatpackedout_orig.out @-rm -f test_xds_bin_testflatout_orig.out @-rm -f mb_LP_1_001.img @-rm -f 9ins.cif @-rm -f testcell_orig.prt @-rm -f $(DECTRIS_EXAMPLES)/cbf_template_t.out @-rm -f XRD1621.cbf @-rm -f XRD1621_orig.cbf @-rm -f XRD1621_orig.cbf @-rm -f XRD1621_I4encbC100.cbf @-rm -f $(SRC)/fcb_exit_binary.f90 @-rm -f $(SRC)/fcb_next_binary.f90 @-rm -f $(SRC)/fcb_open_cifin.f90 @-rm -f $(SRC)/fcb_packed.f90 @-rm -f $(SRC)/fcb_read_bits.f90 @-rm -f $(SRC)/fcb_read_image.f90 @-rm -f $(SRC)/fcb_read_xds_i2.f90 @-rm -f $(EXAMPLES)/test_fcb_read_image.f90 @-rm -f $(EXAMPLES)/test_xds_binary.f90 @-rm -f symlinksdone @-rm -f $(TESTOUTPUT) *$(SEXT) @-rm -f $(SOLIB)/*.o @-rm -f $(SOLIB)/libcbf_wrap.so @-rm -f $(SOLIB)/libjcbf.so @-rm -f $(SOLIB)/libimg.so @-rm -f $(SOLIB)/libfcb.so @-rm -rf $(JCBF)/org @-rm -f $(JCBF)/*.java @-rm -f $(JCBF)/jcbf_wrap.c @-rm -f $(SRC)/cbf_wrap.c @-rm -f $(BIN)/ctestcbf $(BIN)/testcbf.class testcbfc.txt testcbfj.txt @-rm -rf $(REGEX) @-rm -rf $(TIFF) ./.undosymlinks # # Remove temporary files # clean: @-rm -f core @-rm -f *.o @-rm -f *.u # # Restore to distribution state # distclean: clean empty # # Create a Tape Archive for distribution # tar: $(DOCUMENTS) $(SOURCE) $(SRC)/cbf.stx $(HEADERS) $(M4FILES)\ $(EXAMPLES) \ README.html README Makefile \ $(JPEGS) -/bin/rm -f CBFlib.tar* tar cvBf CBFlib.tar \ $(DOCUMENTS) $(SOURCE) $(SRC)/cbf.stx $(HEADERS) $(M4FILES)\ $(EXAMPLES) \ README.html README Makefile \ $(JPEGS) gzip --best CBFlib.tar ./CBFlib-0.9.2.2/Makefile_MINGW0000644000076500007650000020062011603702122014175 0ustar yayayaya ###################################################################### # Makefile - command file for make to create CBFlib # # # # Version 0.9.2 12 Feb 2011 # # # # Paul Ellis and # # Herbert J. Bernstein (yaya@bernstein-plus-sons.com) # # # # (C) Copyright 2006 - 2011 Herbert J. Bernstein # # # ###################################################################### ###################################################################### # # # YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL # # # # ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS # # OF THE LGPL # # # ###################################################################### ########################### GPL NOTICES ############################## # # # This program is free software; you can redistribute it and/or # # modify it under the terms of the GNU General Public License as # # published by the Free Software Foundation; either version 2 of # # (the License, or (at your option) any later version. # # # # This program is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # # GNU General Public License for more details. # # # # You should have received a copy of the GNU General Public License # # along with this program; if not, write to the Free Software # # Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA # # 02111-1307 USA # # # ###################################################################### ######################### LGPL NOTICES ############################### # # # This library is free software; you can redistribute it and/or # # modify it under the terms of the GNU Lesser General Public # # License as published by the Free Software Foundation; either # # version 2.1 of the License, or (at your option) any later version. # # # # This library is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # # Lesser General Public License for more details. # # # # You should have received a copy of the GNU Lesser General Public # # License along with this library; if not, write to the Free # # Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, # # MA 02110-1301 USA # # # ###################################################################### ###################################################################### # # # Stanford University Notices # # for the CBFlib software package that incorporates SLAC software # # on which copyright is disclaimed # # # # This software # # ------------- # # The term "this software", as used in these Notices, refers to # # those portions of the software package CBFlib that were created by # # employees of the Stanford Linear Accelerator Center, Stanford # # University. # # # # Stanford disclaimer of copyright # # -------------------------------- # # Stanford University, owner of the copyright, hereby disclaims its # # copyright and all other rights in this software. Hence, anyone # # may freely use it for any purpose without restriction. # # # # Acknowledgement of sponsorship # # ------------------------------ # # This software was produced by the Stanford Linear Accelerator # # Center, Stanford University, under Contract DE-AC03-76SFO0515 with # # the Department of Energy. # # # # Government disclaimer of liability # # ---------------------------------- # # Neither the United States nor the United States Department of # # Energy, nor any of their employees, makes any warranty, express or # # implied, or assumes any legal liability or responsibility for the # # accuracy, completeness, or usefulness of any data, apparatus, # # product, or process disclosed, or represents that its use would # # not infringe privately owned rights. # # # # Stanford disclaimer of liability # # -------------------------------- # # Stanford University makes no representations or warranties, # # express or implied, nor assumes any liability for the use of this # # software. # # # # Maintenance of notices # # ---------------------- # # In the interest of clarity regarding the origin and status of this # # software, this and all the preceding Stanford University notices # # are to remain affixed to any copy or derivative of this software # # made or distributed by the recipient and are to be affixed to any # # copy of software made or distributed by the recipient that # # contains a copy or derivative of this software. # # # # Based on SLAC Software Notices, Set 4 # # OTT.002a, 2004 FEB 03 # ###################################################################### ###################################################################### # NOTICE # # Creative endeavors depend on the lively exchange of ideas. There # # are laws and customs which establish rights and responsibilities # # for authors and the users of what authors create. This notice # # is not intended to prevent you from using the software and # # documents in this package, but to ensure that there are no # # misunderstandings about terms and conditions of such use. # # # # Please read the following notice carefully. If you do not # # understand any portion of this notice, please seek appropriate # # professional legal advice before making use of the software and # # documents included in this software package. In addition to # # whatever other steps you may be obliged to take to respect the # # intellectual property rights of the various parties involved, if # # you do make use of the software and documents in this package, # # please give credit where credit is due by citing this package, # # its authors and the URL or other source from which you obtained # # it, or equivalent primary references in the literature with the # # same authors. # # # # Some of the software and documents included within this software # # package are the intellectual property of various parties, and # # placement in this package does not in any way imply that any # # such rights have in any way been waived or diminished. # # # # With respect to any software or documents for which a copyright # # exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. # # # # Even though the authors of the various documents and software # # found here have made a good faith effort to ensure that the # # documents are correct and that the software performs according # # to its documentation, and we would greatly appreciate hearing of # # any problems you may encounter, the programs and documents any # # files created by the programs are provided **AS IS** without any * # warranty as to correctness, merchantability or fitness for any # # particular or general use. # # # # THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF # # PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE # # PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS # # OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE # # PROGRAMS OR DOCUMENTS. # ###################################################################### ###################################################################### # # # The IUCr Policy # # for the Protection and the Promotion of the STAR File and # # CIF Standards for Exchanging and Archiving Electronic Data # # # # Overview # # # # The Crystallographic Information File (CIF)[1] is a standard for # # information interchange promulgated by the International Union of # # Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the # # recommended method for submitting publications to Acta # # Crystallographica Section C and reports of crystal structure # # determinations to other sections of Acta Crystallographica # # and many other journals. The syntax of a CIF is a subset of the # # more general STAR File[2] format. The CIF and STAR File approaches # # are used increasingly in the structural sciences for data exchange # # and archiving, and are having a significant influence on these # # activities in other fields. # # # # Statement of intent # # # # The IUCr's interest in the STAR File is as a general data # # interchange standard for science, and its interest in the CIF, # # a conformant derivative of the STAR File, is as a concise data # # exchange and archival standard for crystallography and structural # # science. # # # # Protection of the standards # # # # To protect the STAR File and the CIF as standards for # # interchanging and archiving electronic data, the IUCr, on behalf # # of the scientific community, # # # # # holds the copyrights on the standards themselves, * # # # # owns the associated trademarks and service marks, and * # # # # holds a patent on the STAR File. * # # # These intellectual property rights relate solely to the # # interchange formats, not to the data contained therein, nor to # # the software used in the generation, access or manipulation of # # the data. # # # # Promotion of the standards # # # # The sole requirement that the IUCr, in its protective role, # # imposes on software purporting to process STAR File or CIF data # # is that the following conditions be met prior to sale or # # distribution. # # # # # Software claiming to read files written to either the STAR * # File or the CIF standard must be able to extract the pertinent # # data from a file conformant to the STAR File syntax, or the CIF # # syntax, respectively. # # # # # Software claiming to write files in either the STAR File, or * # the CIF, standard must produce files that are conformant to the # # STAR File syntax, or the CIF syntax, respectively. # # # # # Software claiming to read definitions from a specific data * # dictionary approved by the IUCr must be able to extract any # # pertinent definition which is conformant to the dictionary # # definition language (DDL)[3] associated with that dictionary. # # # # The IUCr, through its Committee on CIF Standards, will assist # # any developer to verify that software meets these conformance # # conditions. # # # # Glossary of terms # # # # [1] CIF: is a data file conformant to the file syntax defined # # at http://www.iucr.org/iucr-top/cif/spec/index.html # # # # [2] STAR File: is a data file conformant to the file syntax # # defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html # # # # [3] DDL: is a language used in a data dictionary to define data # # items in terms of "attributes". Dictionaries currently approved # # by the IUCr, and the DDL versions used to construct these # # dictionaries, are listed at # # http://www.iucr.org/iucr-top/cif/spec/ddl/index.html # # # # Last modified: 30 September 2000 # # # # IUCr Policy Copyright (C) 2000 International Union of # # Crystallography # ###################################################################### # Version string VERSION = 0.9.2 # # Comment out the next line if scratch test files sould be retain # CLEANTESTS = yes # # Definition to get a version of tifflib to support tiff2cbf # TIFF = tiff-3.9.4-rev-6Feb11 TIFFPREFIX = $(PWD) # # Definitions to get a stable version of regex # REGEX = regex-20090805 REGEXDIR = /usr/lib REGEXDEP = # Program to use to retrieve a URL DOWNLOAD = wget # Flag to control symlinks versus copying SLFLAGS = --use_ln # # Program to use to pack shars # SHAR = /usr/bin/shar #SHAR = /usr/local/bin/gshar # # Program to use to create archives # AR = /usr/bin/ar # # Program to use to add an index to an archive # RANLIB = /usr/bin/ranlib # # Program to use to decompress a data file # DECOMPRESS = /usr/bin/bunzip2 # # Program to use to compress a data file # COMPRESS = /usr/bin/bzip2 # # Program to use to generate a signature # SIGNATURE = /usr/bin/openssl dgst -md5 # # Extension for compressed data file (with period) # CEXT = .bz2 # # Extension for signatures of files # SEXT = .md5 # call to time a command #TIME = #TIME = time # # Program to display differences between files # DIFF = diff -u -b # # Program to generate wrapper classes for Python # PYSWIG = swig -python # # Program to generate wrapper classes for Java # JSWIG = swig -java # # Program to generate LaTex and HTML program documentation # NUWEB = nuweb # # Compiler for Java # JAVAC = javac # # Java archiver for compiled classes # JAR = jar # # Java SDK root directory # ifeq ($(JDKDIR),) JDKDIR = /usr/lib/java endif ifneq ($(CBF_DONT_USE_LONG_LONG),) NOLLFLAG = -DCBF_DONT_USE_LONG_LONG else NOLLFLAG = endif # # PYCBF definitions # PYCBFEXT = so PYCBFBOPT = SETUP_PY = setup.py # # Set the compiler and flags # ######################################################### # # Appropriate compiler definitions for Mingw # Also change from symlinks to copies and # use default paths for utilities # ######################################################### CC = gcc C++ = g++ CFLAGS = -g -O2 -Wall -static -I/usr/include -fno-strict-aliasing F90C = g95 F90FLAGS = -g F90LDFLAGS = M4FLAGS = -Dfcb_bytes_in_rec=4096 SOCFLAGS = -D_JNI_IMPLEMENTATION_ SOLDFLAGS = -shared -Wl,--kill-at JAVAINCLUDES = -I$(JDKDIR)/include -I$(JDKDIR)/include/win32 EXTRALIBS = -L$(REGEXDIR) -lregex -lm REGEXDEP = $(REGEXDIR)/libregex.a TIME = PYCBFEXT = pyd PYCBFBOPT = --compiler=mingw32 SETUP_PY = setup_MINGW.py JDKDIR = /java JSWIG = /swig/swig -java PYSWIG = /swig/swig -python SLFLAGS = --use_cp SHAR = shar AR = ar RANLIB = ranlib DECOMPRESS = bunzip2 ifneq ($(NOFORTRAN),) F90C = endif # # Directories # ROOT = . LIB = $(ROOT)/lib SOLIB = $(ROOT)/solib JCBF = $(ROOT)/jcbf JAVADIR = $(ROOT)/java BIN = $(ROOT)/bin SRC = $(ROOT)/src INCLUDE = $(ROOT)/include M4 = $(ROOT)/m4 PYCBF = $(ROOT)/pycbf EXAMPLES = $(ROOT)/examples DECTRIS_EXAMPLES = $(EXAMPLES)/dectris_cbf_template_test DOC = $(ROOT)/doc GRAPHICS = $(ROOT)/html_graphics DATADIRI = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Input DATADIRO = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Output DATADIRS = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only INSTALLDIR = $(HOME) # # URLs from which to retrieve the data directories # DATAURLBASE = http://downloads.sf.net/cbflib/ DATAURLI = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Input.tar.gz DATAURLO = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Output.tar.gz DATAURLS = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz # # URLs from which to retrieve needed external package snapshots # REGEXURL = http://downloads.sf.net/cbflib/$(REGEX).tar.gz TIFFURL = http://downloads.sf.net/cbflib/$(TIFF).tar.gz # # Include directories # INCLUDES = -I$(INCLUDE) -I$(SRC) ###################################################################### # You should not need to make modifications below this line # ###################################################################### # # Suffixes of files to be used or built # .SUFFIXES: .c .o .f90 .m4 .m4.f90: m4 -P $(M4FLAGS) $< > $@ ifneq ($(F90C),) .f90.o: $(F90C) $(F90FLAGS) -c $< -o $@ endif # # Common dependencies # COMMONDEP = Makefile # # Source files # SOURCE = $(SRC)/cbf.c \ $(SRC)/cbf_alloc.c \ $(SRC)/cbf_ascii.c \ $(SRC)/cbf_binary.c \ $(SRC)/cbf_byte_offset.c \ $(SRC)/cbf_canonical.c \ $(SRC)/cbf_codes.c \ $(SRC)/cbf_compress.c \ $(SRC)/cbf_context.c \ $(SRC)/cbf_copy.c \ $(SRC)/cbf_file.c \ $(SRC)/cbf_getopt.c \ $(SRC)/cbf_lex.c \ $(SRC)/cbf_packed.c \ $(SRC)/cbf_predictor.c \ $(SRC)/cbf_read_binary.c \ $(SRC)/cbf_read_mime.c \ $(SRC)/cbf_simple.c \ $(SRC)/cbf_string.c \ $(SRC)/cbf_stx.c \ $(SRC)/cbf_tree.c \ $(SRC)/cbf_uncompressed.c \ $(SRC)/cbf_write.c \ $(SRC)/cbf_write_binary.c \ $(SRC)/cbf_ws.c \ $(SRC)/md5c.c F90SOURCE = $(SRC)/fcb_atol_wcnt.f90 \ $(SRC)/fcb_ci_strncmparr.f90 \ $(SRC)/fcb_exit_binary.f90 \ $(SRC)/fcb_nblen_array.f90 \ $(SRC)/fcb_next_binary.f90 \ $(SRC)/fcb_open_cifin.f90 \ $(SRC)/fcb_packed.f90 \ $(SRC)/fcb_read_bits.f90 \ $(SRC)/fcb_read_byte.f90 \ $(SRC)/fcb_read_image.f90 \ $(SRC)/fcb_read_line.f90 \ $(SRC)/fcb_read_xds_i2.f90 \ $(SRC)/fcb_skip_whitespace.f90 \ $(EXAMPLES)/test_fcb_read_image.f90 \ $(EXAMPLES)/test_xds_binary.f90 # # Header files # HEADERS = $(INCLUDE)/cbf.h \ $(INCLUDE)/cbf_alloc.h \ $(INCLUDE)/cbf_ascii.h \ $(INCLUDE)/cbf_binary.h \ $(INCLUDE)/cbf_byte_offset.h \ $(INCLUDE)/cbf_canonical.h \ $(INCLUDE)/cbf_codes.h \ $(INCLUDE)/cbf_compress.h \ $(INCLUDE)/cbf_context.h \ $(INCLUDE)/cbf_copy.h \ $(INCLUDE)/cbf_file.h \ $(INCLUDE)/cbf_getopt.h \ $(INCLUDE)/cbf_lex.h \ $(INCLUDE)/cbf_packed.h \ $(INCLUDE)/cbf_predictor.h \ $(INCLUDE)/cbf_read_binary.h \ $(INCLUDE)/cbf_read_mime.h \ $(INCLUDE)/cbf_simple.h \ $(INCLUDE)/cbf_string.h \ $(INCLUDE)/cbf_stx.h \ $(INCLUDE)/cbf_tree.h \ $(INCLUDE)/cbf_uncompressed.h \ $(INCLUDE)/cbf_write.h \ $(INCLUDE)/cbf_write_binary.h \ $(INCLUDE)/cbf_ws.h \ $(INCLUDE)/global.h \ $(INCLUDE)/cbff.h \ $(INCLUDE)/md5.h # # m4 macro files # M4FILES = $(M4)/fcblib_defines.m4 \ $(M4)/fcb_exit_binary.m4 \ $(M4)/fcb_next_binary.m4 \ $(M4)/fcb_open_cifin.m4 \ $(M4)/fcb_packed.m4 \ $(M4)/fcb_read_bits.m4 \ $(M4)/fcb_read_image.m4 \ $(M4)/fcb_read_xds_i2.m4 \ $(M4)/test_fcb_read_image.m4 \ $(M4)/test_xds_binary.m4 # # Documentation files # DOCUMENTS = $(DOC)/CBFlib.html \ $(DOC)/CBFlib.txt \ $(DOC)/CBFlib_NOTICES.html \ $(DOC)/CBFlib_NOTICES.txt \ $(DOC)/ChangeLog \ $(DOC)/ChangeLog.html \ $(DOC)/MANIFEST \ $(DOC)/gpl.txt $(DOC)/lgpl.txt # # HTML Graphics files # JPEGS = $(GRAPHICS)/CBFbackground.jpg \ $(GRAPHICS)/CBFbig.jpg \ $(GRAPHICS)/CBFbutton.jpg \ $(GRAPHICS)/cbflibbackground.jpg \ $(GRAPHICS)/cbflibbig.jpg \ $(GRAPHICS)/cbflibbutton.jpg \ $(GRAPHICS)/cifhome.jpg \ $(GRAPHICS)/iucrhome.jpg \ $(GRAPHICS)/noticeButton.jpg # # Default: instructions # default: @echo ' ' @echo '***************************************************************' @echo ' ' @echo ' PLEASE READ README and doc/CBFlib_NOTICES.txt' @echo ' ' @echo ' Before making the CBF library and example programs, check' @echo ' that the C compiler name and flags are correct:' @echo ' ' @echo ' The current values are:' @echo ' ' @echo ' $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG)' @echo ' ' @echo ' Before installing the CBF library and example programs, check' @echo ' that the install directory is correct:' @echo ' ' @echo ' The current value :' @echo ' ' @echo ' $(INSTALLDIR) ' @echo ' ' @echo ' To compile the CBF library and example programs type:' @echo ' ' @echo ' make clean' @echo ' make all' @echo ' ' @echo ' To compile the CBF library as a shared object library, type:' @echo ' ' @echo ' make shared' @echo ' ' @echo ' To compile the Java wrapper classes for CBF library, type:' @echo ' ' @echo ' make javawrapper' @echo ' ' @echo ' To run a set of tests type:' @echo ' ' @echo ' make tests' @echo ' ' @echo ' To run some java tests type:' @echo ' ' @echo ' make javatests' @echo ' ' @echo ' The tests assume that several data files are in the directories' @echo ' $(DATADIRI) and $(DATADIRO)' @echo ' ' @echo ' Alternatively tests can be run comparing MD5 signatures only by' @echo ' ' @echo ' make tests_sigs_only' @echo ' ' @echo ' These signature only tests save space and download time by' @echo ' assuming that input data files and the output signatures' @echo ' are in the directories' @echo ' $(DATADIRI) and $(DATADIRS)' @echo ' ' @echo ' These directory can be obtained from' @echo ' ' @echo ' $(DATAURLI) ' @echo ' $(DATAURLO) ' @echo ' $(DATAURLS) ' @echo ' ' @echo ' To clean up the directories type:' @echo ' ' @echo ' make clean' @echo ' ' @echo ' To install the library and binaries type:' @echo ' ' @echo ' make install' @echo ' ' @echo '***************************************************************' @echo ' ' # # Compile the library and examples # all:: $(BIN) $(SOURCE) $(F90SOURCE) $(HEADERS) \ symlinksdone $(REGEXDEP) \ $(LIB)/libcbf.a \ $(LIB)/libfcb.a \ $(LIB)/libimg.a \ $(BIN)/adscimg2cbf \ $(BIN)/cbf2adscimg \ $(BIN)/convert_image \ $(BIN)/convert_minicbf \ $(BIN)/sequence_match \ $(BIN)/arvai_test \ $(BIN)/makecbf \ $(BIN)/img2cif \ $(BIN)/adscimg2cbf \ $(BIN)/cif2cbf \ $(BIN)/testcell \ $(BIN)/cif2c \ $(BIN)/testreals \ $(BIN)/testflat \ $(BIN)/testflatpacked ifneq ($(F90C),) all:: $(BIN)/test_xds_binary \ $(BIN)/test_fcb_read_image endif shared: $(SOLIB)/libcbf.so $(SOLIB)/libfcb.so $(SOLIB)/libimg.so javawrapper: shared $(JCBF) $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf_wrap.so ifneq ($(CBFLIB_USE_PYCIFRW),) PYCIFRWDEF = -Dcbf_use_pycifrw=yes else PYCIFRWDEF = endif Makefiles: Makefile \ Makefile_LINUX \ Makefile_LINUX_64 \ Makefile_LINUX_gcc42 \ Makefile_LINUX_DMALLOC \ Makefile_LINUX_gcc42_DMALLOC \ Makefile_OSX \ Makefile_OSX_gcc42 \ Makefile_OSX_gcc42_DMALLOC \ Makefile_AIX \ Makefile_MINGW \ Makefile_IRIX_gcc Makefile_LINUX: $(M4)/Makefile.m4 -cp Makefile_LINUX Makefile_LINUX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX $(M4)/Makefile.m4 > Makefile_LINUX Makefile_LINUX_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_LINUX Makefile_LINUX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_DMALLOC $(M4)/Makefile.m4 > Makefile_LINUX_DMALLOC Makefile_LINUX_64: $(M4)/Makefile.m4 -cp Makefile_LINUX_64 Makefile_LINUX_64_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_64 $(M4)/Makefile.m4 > Makefile_LINUX_64 Makefile_LINUX_gcc42: $(M4)/Makefile.m4 -cp Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_gcc42 $(M4)/Makefile.m4 > Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_gcc42_DMALLOC $(M4)/Makefile.m4 > Makefile_LINUX_gcc42_DMALLOC Makefile_OSX: $(M4)/Makefile.m4 -cp Makefile_OSX Makefile_OSX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX $(M4)/Makefile.m4 > Makefile_OSX Makefile_OSX_gcc42: $(M4)/Makefile.m4 -cp Makefile_OSX_gcc42 Makefile_OSX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX_gcc42 $(M4)/Makefile.m4 > Makefile_OSX_gcc42 Makefile_OSX_gcc42_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_OSX_gcc42 Makefile_OSX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX_gcc42_DMALLOC $(M4)/Makefile.m4 > Makefile_OSX_gcc42_DMALLOC Makefile_AIX: $(M4)/Makefile.m4 -cp Makefile_AIX Makefile_AIX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=AIX $(M4)/Makefile.m4 > Makefile_AIX Makefile_MINGW: $(M4)/Makefile.m4 -cp Makefile_MINGW Makefile_MINGW_old m4 -P $(PYCIFRWDEF) -Dcbf_system=MINGW $(M4)/Makefile.m4 > Makefile_MINGW Makefile_IRIX_gcc: $(M4)/Makefile.m4 -cp Makefile_IRIX_gcc Makefile_IRIX_gcc_old m4 -P $(PYCIFREDEF) -Dcbf_system=IRIX_gcc $(M4)/Makefile.m4 > Makefile_IRIX_gcc Makefile: $(M4)/Makefile.m4 -cp Makefile Makefile_old m4 -P $(PYCIFRWDEF) -Dcbf_system=default $(M4)/Makefile.m4 > Makefile symlinksdone: chmod a+x .symlinks chmod a+x .undosymlinks chmod a+x doc/.symlinks chmod a+x doc/.undosymlinks chmod a+x libtool/.symlinks chmod a+x libtool/.undosymlinks ./.symlinks $(SLFLAGS) touch symlinksdone install: all $(INSTALLDIR) $(INSTALLDIR)/lib $(INSTALLDIR)/bin \ $(INSTALLDIR)/include $(INSTALLDIR)/include/cbflib \ $(PYSOURCE) -chmod -R 755 $(INSTALLDIR)/include/cbflib -chmod 755 $(INSTALLDIR)/lib/libcbf.a -cp $(INSTALLDIR)/lib/libcbf.a $(INSTALLDIR)/lib/libcbf_old.a cp $(LIB)/libcbf.a $(INSTALLDIR)/lib/libcbf.a -cp $(INSTALLDIR)/lib/libimg.a $(INSTALLDIR)/lib/libimg_old.a cp $(LIB)/libimg.a $(INSTALLDIR)/lib/libimg.a -cp $(INSTALLDIR)/bin/adscimg2cbf $(INSTALLDIR)/bin/adscimg2cbf_old cp $(BIN)/adscimg2cbf $(INSTALLDIR)/bin/adscimg2cbf -cp $(INSTALLDIR)/bin/cbf2adscimg $(INSTALLDIR)/bin/cbf2adscimg_old cp $(BIN)/cbf2adscimg $(INSTALLDIR)/bin/cbf2adscimg -cp $(INSTALLDIR)/bin/convert_image $(INSTALLDIR)/bin/convert_image_old cp $(BIN)/convert_image $(INSTALLDIR)/bin/convert_image -cp $(INSTALLDIR)/bin/convert_minicbf $(INSTALLDIR)/bin/convert_minicbf_old cp $(BIN)/convert_minicbf $(INSTALLDIR)/bin/convert_minicbf -cp $(INSTALLDIR)/bin/makecbf $(INSTALLDIR)/bin/makecbf_old cp $(BIN)/makecbf $(INSTALLDIR)/bin/makecbf -cp $(INSTALLDIR)/bin/img2cif $(INSTALLDIR)/bin/img2cif_old cp $(BIN)/img2cif $(INSTALLDIR)/bin/img2cif -cp $(INSTALLDIR)/bin/cif2cbf $(INSTALLDIR)/bin/cif2cbf_old cp $(BIN)/cif2cbf $(INSTALLDIR)/bin/cif2cbf -cp $(INSTALLDIR)/bin/sequence_match $(INSTALLDIR)/bin/sequence_match_old cp $(BIN)/sequence_match $(INSTALLDIR)/bin/sequence_match -cp $(INSTALLDIR)/bin/arvai_test $(INSTALLDIR)/bin/arvai_test_old cp $(BIN)/arvai_test $(INSTALLDIR)/bin/arvai_test -cp $(INSTALLDIR)/bin/cif2c $(INSTALLDIR)/bin/cif2c_old cp $(BIN)/cif2c $(INSTALLDIR)/bin/cif2c -cp $(INSTALLDIR)/bin/testreals $(INSTALLDIR)/bin/testreals_old cp $(BIN)/testreals $(INSTALLDIR)/bin/testreals -cp $(INSTALLDIR)/bin/testflat $(INSTALLDIR)/bin/testflat_old cp $(BIN)/testflat $(INSTALLDIR)/bin/testflat -cp $(INSTALLDIR)/bin/testflatpacked $(INSTALLDIR)/bin/testflatpacked_old cp $(BIN)/testflatpacked $(INSTALLDIR)/bin/testflatpacked chmod -R 755 $(INSTALLDIR)/include/cbflib -rm -rf $(INSTALLDIR)/include/cbflib_old -cp -r $(INSTALLDIR)/include/cbflib $(INSTALLDIR)/include/cbflib_old -rm -rf $(INSTALLDIR)/include/cbflib cp -r $(INCLUDE) $(INSTALLDIR)/include/cbflib chmod 644 $(INSTALLDIR)/lib/libcbf.a chmod 755 $(INSTALLDIR)/bin/convert_image chmod 755 $(INSTALLDIR)/bin/convert_minicbf chmod 755 $(INSTALLDIR)/bin/makecbf chmod 755 $(INSTALLDIR)/bin/img2cif chmod 755 $(INSTALLDIR)/bin/cif2cbf chmod 755 $(INSTALLDIR)/bin/sequence_match chmod 755 $(INSTALLDIR)/bin/arvai_test chmod 755 $(INSTALLDIR)/bin/cif2c chmod 755 $(INSTALLDIR)/bin/testreals chmod 755 $(INSTALLDIR)/bin/testflat chmod 755 $(INSTALLDIR)/bin/testflatpacked chmod 644 $(INSTALLDIR)/include/cbflib/*.h # # REGEX # ifneq ($(REGEXDEP),) $(REGEXDEP): $(REGEX) (cd $(REGEX); ./configure; make install) endif $(REGEX): $(DOWNLOAD) $(REGEXURL) tar -xvf $(REGEX).tar.gz -rm $(REGEX).tar.gz # # TIFF # $(TIFF): $(DOWNLOAD) $(TIFFURL) tar -xvf $(TIFF).tar.gz -rm $(TIFF).tar.gz (cd $(TIFF); ./configure --prefix=$(TIFFPREFIX); make install) # # Directories # $(INSTALLDIR): mkdir -p $(INSTALLDIR) $(INSTALLDIR)/lib: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/lib $(INSTALLDIR)/bin: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/bin $(INSTALLDIR)/include: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/include $(INSTALLDIR)/include/cbflib: $(INSTALLDIR)/include mkdir -p $(INSTALLDIR)/include/cbflib $(LIB): mkdir $@ $(BIN): mkdir $@ $(SOLIB): mkdir $@ $(JCBF): mkdir $@ # # Parser # $(SRC)/cbf_stx.c: $(SRC)/cbf.stx.y bison $(SRC)/cbf.stx.y -o $(SRC)/cbf.stx.tab.c -d mv $(SRC)/cbf.stx.tab.c $(SRC)/cbf_stx.c mv $(SRC)/cbf.stx.tab.h $(INCLUDE)/cbf_stx.h # # CBF library # $(LIB)/libcbf.a: $(SOURCE) $(HEADERS) $(COMMONDEP) $(LIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG) $(INCLUDES) $(WARNINGS) -c $(SOURCE) $(AR) cr $@ *.o mv *.o $(LIB) ifneq ($(RANLIB),) $(RANLIB) $@ endif $(SOLIB)/libcbf.so: $(SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(SOURCE) $(CC) -o $@ *.o $(SOLDFLAGS) $(EXTRALIBS) rm *.o # # IMG library # $(LIB)/libimg.a: $(EXAMPLES)/img.c $(HEADERS) $(COMMONDEP) $(LIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) -c $(EXAMPLES)/img.c $(AR) cr $@ img.o ifneq ($(RANLIB),) $(RANLIB) $@ endif rm img.o $(SOLIB)/libimg.so: $(SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(EXAMPLES)/img.c $(CC) -o $@ img.o $(SOLDFLAGS) rm img.o # # CBF and IMG libraries # CBF_IMG_LIBS: $(LIB)/libcbf.a $(LIB)/libimg.a # # FCB library # $(LIB)/libfcb.a: $(F90SOURCE) $(COMMONDEP) $(LIB) ifneq ($(F90C),) $(F90C) $(F90FLAGS) -c $(F90SOURCE) $(AR) cr $@ *.o ifneq ($(RANLIB),) $(RANLIB) $@ endif rm *.o else echo "Define F90C to build $(LIB)/libfcb.a" endif $(SOLIB)/libfcb.so: $(F90SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) ifneq ($(F90C),) $(F90C) $(F90FLAGS) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(F90SOURCE) $(F90C) $(F90FLAGS) -o $@ *.o $(SOLDFLAGS) rm *.o else echo "Define F90C to build $(SOLIB)/libfcb.so" endif # # Python bindings # $(PYCBF)/_pycbf.$(PYCBFEXT): $(PYCBF) $(LIB)/libcbf.a \ $(PYCBF)/$(SETUP_PY) \ $(LIB)/libfcb.a \ $(LIB)/libimg.a \ $(PYCBF)/pycbf.i \ $(PYCBF)/cbfhandlewrappers.i \ $(PYCBF)/cbfdetectorwrappers.i \ $(PYCBF)/cbfgenericwrappers.i \ $(PYCBF)/cbfgoniometerwrappers.i (cd $(PYCBF); python $(SETUP_PY) build $(PYCBFBOPT); cp build/lib.*/_pycbf.$(PYCBFEXT) .) $(PYCBF)/setup.py: $(M4)/setup_py.m4 (m4 -P -Dregexlib=NOREGEXLIB -Dregexlibdir=NOREGEXLIBDIR $(M4)/setup_py.m4 > $@) $(PYCBF)/setup_MINGW.py: m4/setup_py.m4 (m4 -P -Dregexlib=regex -Dregexlibdir=$(REGEXDIR) $(M4)/setup_py.m4 > $@) $(LIB)/_pycbf.$(PYCBFEXT): $(PYCBF)/_pycbf.$(PYCBFEXT) cp $(PYCBF)/_pycbf.$(PYCBFEXT) $(LIB)/_pycbf.$(PYCBFEXT) $(PYCBF)/pycbf.pdf: $(PYCBF)/pycbf.w (cd $(PYCBF); \ $(NUWEB) pycbf; \ latex pycbf; \ $(NUWEB) pycbf; \ latex pycbf; \ dvipdfm pycbf ) $(PYCBF)/CBFlib.txt: $(DOC)/CBFlib.html links -dump $(DOC)/CBFlib.html > $(PYCBF)/CBFlib.txt $(PYCBF)/cbfhandlewrappers.i \ $(PYCBF)/cbfdetectorwrappers.i \ $(PYCBF)/cbfgenericwrappers.i \ $(PYCBF)/cbfgoniometerwrappers.i: $(PYCBF)/CBFlib.txt $(PYCBF)/make_pycbf.py (cd $(PYCBF); python make_pycbf.py; $(PYSWIG) pycbf.i; python setup.py build) # # Java bindings # $(JCBF)/cbflib-$(VERSION).jar: $(JCBF) $(JCBF)/jcbf.i $(JSWIG) -I$(INCLUDE) -package org.iucr.cbflib -outdir $(JCBF) $(JCBF)/jcbf.i $(JAVAC) -d . $(JCBF)/*.java $(JAR) cf $@ org $(SOLIB)/libcbf_wrap.so: $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf.so $(CC) $(CFLAGS) $(NOLLFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) $(JAVAINCLUDES) -c $(JCBF)/jcbf_wrap.c $(CC) -o $@ jcbf_wrap.o $(SOLDFLAGS) -L$(SOLIB) -lcbf rm jcbf_wrap.o # # F90SOURCE # $(SRC)/fcb_exit_binary.f90: $(M4)/fcb_exit_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_exit_binary.m4) > $(SRC)/fcb_exit_binary.f90 $(SRC)/fcb_next_binary.f90: $(M4)/fcb_next_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_next_binary.m4) > $(SRC)/fcb_next_binary.f90 $(SRC)/fcb_open_cifin.f90: $(M4)/fcb_open_cifin.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_open_cifin.m4) > $(SRC)/fcb_open_cifin.f90 $(SRC)/fcb_packed.f90: $(M4)/fcb_packed.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_packed.m4) > $(SRC)/fcb_packed.f90 $(SRC)/fcb_read_bits.f90: $(M4)/fcb_read_bits.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_bits.m4) > $(SRC)/fcb_read_bits.f90 $(SRC)/fcb_read_image.f90: $(M4)/fcb_read_image.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_image.m4) > $(SRC)/fcb_read_image.f90 $(SRC)/fcb_read_xds_i2.f90: $(M4)/fcb_read_xds_i2.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_xds_i2.m4) > $(SRC)/fcb_read_xds_i2.f90 $(EXAMPLES)/test_fcb_read_image.f90: $(M4)/test_fcb_read_image.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) test_fcb_read_image.m4) > $(EXAMPLES)/test_fcb_read_image.f90 $(EXAMPLES)/test_xds_binary.f90: $(M4)/test_xds_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) test_xds_binary.m4) > $(EXAMPLES)/test_xds_binary.f90 # # convert_image example program # $(BIN)/convert_image: $(LIB)/libcbf.a $(EXAMPLES)/convert_image.c $(EXAMPLES)/img.c \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/convert_image.c $(EXAMPLES)/img.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # convert_minicbf example program # $(BIN)/convert_minicbf: $(LIB)/libcbf.a $(EXAMPLES)/convert_minicbf.c \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/convert_minicbf.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # makecbf example program # $(BIN)/makecbf: $(LIB)/libcbf.a $(EXAMPLES)/makecbf.c $(LIB)/libimg.a $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/makecbf.c -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # adscimg2cbf example program # $(BIN)/adscimg2cbf: $(LIB)/libcbf.a $(EXAMPLES)/adscimg2cbf.c $(EXAMPLES)/adscimg2cbf_sub.c $(CC) $(CFLAGS) $(NOLLFLAG) -D_SVID_SOURCE $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/adscimg2cbf.c $(EXAMPLES)/adscimg2cbf_sub.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # cbf2adscimg example program # $(BIN)/cbf2adscimg: $(LIB)/libcbf.a $(EXAMPLES)/cbf2adscimg.c $(EXAMPLES)/cbf2adscimg_sub.c $(CC) $(CFLAGS) $(NOLLFLAG) -D_SVID_SOURCE $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cbf2adscimg.c $(EXAMPLES)/cbf2adscimg_sub.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # changtestcompression example program # $(BIN)/changtestcompression: $(LIB)/libcbf.a $(EXAMPLES)/changtestcompression.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/changtestcompression.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # img2cif example program # $(BIN)/img2cif: $(LIB)/libcbf.a $(EXAMPLES)/img2cif.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOTPINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/img2cif.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # cif2cbf example program # $(BIN)/cif2cbf: $(LIB)/libcbf.a $(EXAMPLES)/cif2cbf.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cif2cbf.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # dectris cbf_template_t program # $(BIN)/cbf_template_t: $(DECTRIS_EXAMPLES)/cbf_template_t.c \ $(DECTRIS_EXAMPLES)/mx_cbf_t_extras.h \ $(DECTRIS_EXAMPLES)/mx_parms.h $(CC) $(CFLAGS) $(NOLLFLAG) -I $(DECTRIS_EXAMPLES) $(WARNINGS) \ $(DECTRIS_EXAMPLES)/cbf_template_t.c -o $@ # # testcell example program # $(BIN)/testcell: $(LIB)/libcbf.a $(EXAMPLES)/testcell.C $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testcell.C -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # cif2c example program # $(BIN)/cif2c: $(LIB)/libcbf.a $(EXAMPLES)/cif2c.c $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cif2c.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # sauter_test example program # $(BIN)/sauter_test: $(LIB)/libcbf.a $(EXAMPLES)/sauter_test.C $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/sauter_test.C -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # sequence_match example program # $(BIN)/sequence_match: $(LIB)/libcbf.a $(EXAMPLES)/sequence_match.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/sequence_match.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # tiff2cbf example program # $(BIN)/tiff2cbf: $(LIB)/libcbf.a $(EXAMPLES)/tiff2cbf.c \ $(GOPTLIB) $(GOPTINC) $(TIFF) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ -I$(TIFFPREFIX)/include $(EXAMPLES)/tiff2cbf.c $(GOPTLIB) -L$(LIB) \ -lcbf -L$(TIFFPREFIX)/lib -ltiff $(EXTRALIBS) -limg -o $@ # # Andy Arvai's buffered read test program # $(BIN)/arvai_test: $(LIB)/libcbf.a $(EXAMPLES)/arvai_test.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/arvai_test.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # testreals example program # $(BIN)/testreals: $(LIB)/libcbf.a $(EXAMPLES)/testreals.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testreals.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testflat example program # $(BIN)/testflat: $(LIB)/libcbf.a $(EXAMPLES)/testflat.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testflat.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testflatpacked example program # $(BIN)/testflatpacked: $(LIB)/libcbf.a $(EXAMPLES)/testflatpacked.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testflatpacked.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ ifneq ($(F90C),) # # test_xds_binary example program # $(BIN)/test_xds_binary: $(LIB)/libfcb.a $(EXAMPLES)/test_xds_binary.f90 $(F90C) $(F90FLAGS) $(F90LDFLAGS) $(EXAMPLES)/test_xds_binary.f90 \ -L$(LIB) -lfcb -o $@ # # test_fcb_read_image example program # $(BIN)/test_fcb_read_image: $(LIB)/libfcb.a $(EXAMPLES)/test_fcb_read_image.f90 $(F90C) $(F90FLAGS) $(F90LDFLAGS) $(EXAMPLES)/test_fcb_read_image.f90 \ -L$(LIB) -lfcb -o $@ endif # # testcbf (C) # $(BIN)/ctestcbf: $(EXAMPLES)/testcbf.c $(LIB)/libcbf.a $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testcbf.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testcbf (Java) # $(BIN)/testcbf.class: $(EXAMPLES)/testcbf.java $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf_wrap.so $(JAVAC) -cp $(JCBF)/cbflib-$(VERSION).jar -d $(BIN) $(EXAMPLES)/testcbf.java # # Data files for tests # $(DATADIRI): (cd ..; $(DOWNLOAD) $(DATAURLI)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Input.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Input.tar.gz) $(DATADIRO): (cd ..; $(DOWNLOAD) $(DATAURLO)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Output.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Output.tar.gz) $(DATADIRS): (cd ..; $(DOWNLOAD) $(DATAURLS)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz) # Input Data Files TESTINPUT_BASIC = example.mar2300 DATADIRI_INPUT_BASIC = $(DATADIRI)/example.mar2300$(CEXT) TESTINPUT_EXTRA = 9ins.cif mb_LP_1_001.img insulin_pilatus6m.cbf testrealin.cbf \ testflatin.cbf testflatpackedin.cbf XRD1621.tif DATADIRI_INPUT_EXTRA = $(DATADIRI)/9ins.cif$(CEXT) $(DATADIRI)/mb_LP_1_001.img$(CEXT) \ $(DATADIRI)/insulin_pilatus6m.cbf$(CEXT) $(DATADIRI)/testrealin.cbf$(CEXT) \ $(DATADIRI)/testflatin.cbf$(CEXT) $(DATADIRI)/testflatpackedin.cbf$(CEXT) \ $(DATADIRI)/XRD1621.tif$(CEXT) # Output Data Files TESTOUTPUT = adscconverted_flat_orig.cbf \ adscconverted_orig.cbf converted_flat_orig.cbf converted_orig.cbf \ insulin_pilatus6mconverted_orig.cbf \ mb_LP_1_001_orig.cbf testcell_orig.prt \ test_xds_bin_testflatout_orig.out \ test_xds_bin_testflatpackedout_orig.out test_fcb_read_testflatout_orig.out \ test_fcb_read_testflatpackedout_orig.out \ XRD1621_orig.cbf XRD1621_I4encbC100_orig.cbf NEWTESTOUTPUT = adscconverted_flat.cbf \ adscconverted.cbf converted_flat.cbf converted.cbf \ insulin_pilatus6mconverted.cbf \ mb_LP_1_001.cbf testcell.prt \ test_xds_bin_testflatout.out \ test_xds_bin_testflatpackedout.out test_fcb_read_testflatout.out \ test_fcb_read_testflatpackedout.out \ XRD1621.cbf XRD1621_I4encbC100.cbf DATADIRO_OUTPUT = $(DATADIRO)/adscconverted_flat_orig.cbf$(CEXT) \ $(DATADIRO)/adscconverted_orig.cbf$(CEXT) \ $(DATADIRO)/converted_flat_orig.cbf$(CEXT) \ $(DATADIRO)/converted_orig.cbf$(CEXT) \ $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(CEXT) \ $(DATADIRO)/mb_LP_1_001_orig.cbf$(CEXT) \ $(DATADIRO)/testcell_orig.prt$(CEXT) \ $(DATADIRO)/test_xds_bin_testflatout_orig.out$(CEXT) \ $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(CEXT) \ $(DATADIRO)/test_fcb_read_testflatout_orig.out$(CEXT) \ $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(CEXT) \ $(DATADIRO)/XRD1621_orig.cbf$(CEXT) \ $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(CEXT) DATADIRO_OUTPUT_SIGNATURES = $(DATADIRO)/adscconverted_flat_orig.cbf$(SEXT) \ $(DATADIRO)/adscconverted_orig.cbf$(SEXT) \ $(DATADIRO)/converted_flat_orig.cbf$(SEXT) \ $(DATADIRO)/converted_orig.cbf$(SEXT) \ $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(SEXT) \ $(DATADIRO)/mb_LP_1_001_orig.cbf$(SEXT) \ $(DATADIRO)/testcell_orig.prt$(SEXT) \ $(DATADIRO)/test_xds_bin_testflatout_orig.out$(SEXT) \ $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(SEXT) \ $(DATADIRO)/test_fcb_read_testflatout_orig.out$(SEXT) \ $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(SEXT) \ $(DATADIRO)/XRD1621_orig.cbf$(SEXT) \ $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(SEXT) # Output Data File Signatures TESTOUTPUTSIGS = adscconverted_flat_orig.cbf$(SEXT) \ adscconverted_orig.cbf$(SEXT) converted_flat_orig.cbf$(SEXT) converted_orig.cbf$(SEXT) \ insulin_pilatus6mconverted_orig.cbf$(SEXT) \ mb_LP_1_001_orig.cbf$(SEXT) testcell_orig.prt$(SEXT) \ test_xds_bin_testflatout_orig.out$(SEXT) \ test_xds_bin_testflatpackedout_orig.out$(SEXT) test_fcb_read_testflatout_orig.out$(SEXT) \ test_fcb_read_testflatpackedout_orig.out$(SEXT) \ XRD1621_orig.cbf$(SEXT) DATADIRS_OUTPUT_SIGNATURES = $(DATADIRS)/adscconverted_flat_orig.cbf$(SEXT) \ $(DATADIRS)/adscconverted_orig.cbf$(SEXT) \ $(DATADIRS)/converted_flat_orig.cbf$(SEXT) \ $(DATADIRS)/converted_orig.cbf$(SEXT) \ $(DATADIRS)/insulin_pilatus6mconverted_orig.cbf$(SEXT) \ $(DATADIRS)/mb_LP_1_001_orig.cbf$(SEXT) \ $(DATADIRS)/testcell_orig.prt$(SEXT) \ $(DATADIRS)/test_xds_bin_testflatout_orig.out$(SEXT) \ $(DATADIRS)/test_xds_bin_testflatpackedout_orig.out$(SEXT) \ $(DATADIRS)/test_fcb_read_testflatout_orig.out$(SEXT) \ $(DATADIRS)/test_fcb_read_testflatpackedout_orig.out$(SEXT) \ $(DATADIRS)/XRD1621_orig.cbf$(SEXT) \ $(DATADIRS)/XRD1621_I4encbC100_orig.cbf$(SEXT) # Fetch Input Data Files $(TESTINPUT_BASIC): $(DATADIRI) $(DATADIRI_INPUT_BASIC) $(DECOMPRESS) < $(DATADIRI)/$@$(CEXT) > $@ cp $(DATADIRI)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) $(TESTINPUT_EXTRA): $(DATADIRI) $(DATADIRI_INPUT_EXTRA) $(DECOMPRESS) < $(DATADIRI)/$@$(CEXT) > $@ cp $(DATADIRI)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) # Fetch Output Data Files and Signatures $(TESTOUTPUT): $(DATADIRO) $(DATADIRO_OUTPUT) $(DATADIRO_OUTPUT_SIGNATURES) $(DECOMPRESS) < $(DATADIRO)/$@$(CEXT) > $@ cp $(DATADIRO)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) # Fetch Output Data File Signatures $(TESTOUTPUTSIGS): $(DATADIRS) $(DATADIRS_OUTPUT_SIGNATURES) cp $(DATADIRS)/$@ $@ # # Tests # tests: $(LIB) $(BIN) symlinksdone basic extra dectristests pycbftests tests_sigs_only: $(LIB) $(BIN) symlinksdone basic extra_sigs_only restore_output: $(NEWTESTOUTPUT) $(DATADIRO) $(SIGNATURE) < adscconverted_flat.cbf > $(DATADIRO)/adscconverted_flat_orig.cbf$(SEXT) $(SIGNATURE) < adscconverted.cbf > $(DATADIRO)/adscconverted_orig.cbf$(SEXT) $(SIGNATURE) < converted_flat.cbf > $(DATADIRO)/converted_flat_orig.cbf$(SEXT) $(SIGNATURE) < converted.cbf > $(DATADIRO)/converted_orig.cbf$(SEXT) $(SIGNATURE) < insulin_pilatus6mconverted.cbf > $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(SEXT) $(SIGNATURE) < mb_LP_1_001.cbf$ > $(DATADIRO)/mb_LP_1_001_orig.cbf$(SEXT) $(SIGNATURE) < testcell.prt > $(DATADIRO)/testcell_orig.prt$(SEXT) $(SIGNATURE) < test_xds_bin_testflatout.out > $(DATADIRO)/test_xds_bin_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_xds_bin_testflatpackedout.out > $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatout.out > $(DATADIRO)/test_fcb_read_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatpackedout.out > $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < XRD1621.cbf > $(DATADIRO)/XRD1621_orig.cbf$(SEXT) $(SIGNATURE) < XRD1621_I4encbC100.cbf > $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(SEXT) $(COMPRESS) < adscconverted_flat.cbf > $(DATADIRO)/adscconverted_flat_orig.cbf$(CEXT) $(COMPRESS) < adscconverted.cbf > $(DATADIRO)/adscconverted_orig.cbf$(CEXT) $(COMPRESS) < converted_flat.cbf > $(DATADIRO)/converted_flat_orig.cbf$(CEXT) $(COMPRESS) < converted.cbf > $(DATADIRO)/converted_orig.cbf$(CEXT) $(COMPRESS) < insulin_pilatus6mconverted.cbf > $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(CEXT) $(COMPRESS) < mb_LP_1_001.cbf$ > $(DATADIRO)/mb_LP_1_001_orig.cbf$(CEXT) $(COMPRESS) < testcell.prt > $(DATADIRO)/testcell_orig.prt$(CEXT) $(COMPRESS) < test_xds_bin_testflatout.out > $(DATADIRO)/test_xds_bin_testflatout_orig.out$(CEXT) $(COMPRESS) < test_xds_bin_testflatpackedout.out > $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(CEXT) $(COMPRESS) < test_fcb_read_testflatout.out > $(DATADIRO)/test_fcb_read_testflatout_orig.out$(CEXT) $(COMPRESS) < test_fcb_read_testflatpackedout.out > $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(CEXT) $(COMPRESS) < XRD1621.cbf > $(DATADIRO)/XRD1621_orig.cbf$(CEXT) $(COMPRESS) < XRD1621_I4encbC100.cbf > $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(CEXT) restore_sigs_only: $(NEWTESTOUTPUT) $(DATADIRS) $(SIGNATURE) < adscconverted_flat.cbf > $(DATADIRS)/adscconverted_flat_orig.cbf$(SEXT) $(SIGNATURE) < adscconverted.cbf > $(DATADIRS)/adscconverted_orig.cbf$(SEXT) $(SIGNATURE) < converted_flat.cbf > $(DATADIRS)/converted_flat_orig.cbf$(SEXT) $(SIGNATURE) < converted.cbf > $(DATADIRS)/converted_orig.cbf$(SEXT) $(SIGNATURE) < insulin_pilatus6mconverted.cbf > $(DATADIRS)/insulin_pilatus6mconverted_orig.cbf$(SEXT) $(SIGNATURE) < mb_LP_1_001.cbf$ > $(DATADIRS)/mb_LP_1_001_orig.cbf$(SEXT) $(SIGNATURE) < testcell.prt > $(DATADIRS)/testcell_orig.prt$(SEXT) $(SIGNATURE) < test_xds_bin_testflatout.out > $(DATADIRS)/test_xds_bin_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_xds_bin_testflatpackedout.out > $(DATADIRS)/test_xds_bin_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatout.out > $(DATADIRS)/test_fcb_read_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatpackedout.out > $(DATADIRS)/test_fcb_read_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < XRD1621.cbf > $(DATADIRS)/XRD1621_orig.cbf$(SEXT) $(SIGNATURE) < XRD1621_I4encbC100.cbf > $(DATADIRS)/XRD1621_I4encbC100_orig.cbf$(SEXT) restore_signatures: restore_output restore_sigs_only # # Basic Tests # basic: $(BIN)/makecbf $(BIN)/img2cif $(BIN)/cif2cbf $(TESTINPUT_BASIC) $(BIN)/makecbf example.mar2300 makecbf.cbf $(BIN)/img2cif -c flatpacked -m headers -d digest \ -e base64 example.mar2300 img2cif_packed.cif $(BIN)/img2cif -c canonical -m headers -d digest \ -e base64 example.mar2300 img2cif_canonical.cif $(BIN)/img2cif -c flatpacked -m headers -d digest \ -e none example.mar2300 img2cif_packed.cbf $(BIN)/img2cif -c canonical -m headers -d digest \ -e none example.mar2300 img2cif_canonical.cbf $(BIN)/cif2cbf -e none -c flatpacked \ img2cif_canonical.cif cif2cbf_packed.cbf $(BIN)/cif2cbf -e none -c canonical \ img2cif_packed.cif cif2cbf_canonical.cbf -cmp cif2cbf_packed.cbf makecbf.cbf -cmp cif2cbf_packed.cbf img2cif_packed.cbf -cmp cif2cbf_canonical.cbf img2cif_canonical.cbf # # Extra Tests # ifneq ($(F90C),) extra: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/test_xds_binary $(BIN)/test_fcb_read_image $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg \ $(BIN)/changtestcompression $(BIN)/tiff2cbf \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUT) else extra: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUT) endif $(TIME) $(BIN)/cif2cbf -e hex -c none \ makecbf.cbf cif2cbf_ehcn.cif $(TIME) $(BIN)/cif2cbf -e none -c flatpacked \ cif2cbf_ehcn.cif cif2cbf_encp.cbf; rm cif2cbf_ehcn.cif -cmp makecbf.cbf cif2cbf_encp.cbf $(TIME) $(BIN)/cif2cbf -i 9ins.cif -o 9ins.cbf -cmp 9ins.cif 9ins.cbf $(TIME) $(BIN)/convert_image -F example.mar2300 converted_flat.cbf -cmp converted_flat.cbf converted_flat_orig.cbf $(TIME) $(BIN)/convert_image example.mar2300 converted.cbf -cmp converted.cbf converted_orig.cbf -$(TIME) $(BIN)/testcell < testcell.dat > testcell.prt -cmp testcell.prt testcell_orig.prt $(TIME) $(BIN)/convert_image -F -d adscquantum315 mb_LP_1_001.img adscconverted_flat.cbf -cmp adscconverted_flat.cbf adscconverted_flat_orig.cbf $(TIME) $(BIN)/convert_image -d adscquantum315 mb_LP_1_001.img adscconverted.cbf -cmp adscconverted.cbf adscconverted_orig.cbf $(TIME) $(BIN)/adscimg2cbf --no_pad --cbf_packed,flat mb_LP_1_001.img -cmp mb_LP_1_001.cbf mb_LP_1_001_orig.cbf ifneq ($(CLEANTESTS),) mv mb_LP_1_001.cbf nmb_LP_1_001.cbf else cp mb_LP_1_001.cbf nmb_LP_1_001.cbf endif $(TIME) $(BIN)/cbf2adscimg nmb_LP_1_001.cbf -cmp nmb_LP_1_001.img mb_LP_1_001.img rm nmb_LP_1_001.cbf ifneq ($(CLEANTESTS),) rm nmb_LP_1_001.img endif $(TIME) $(BIN)/convert_minicbf -d pilatus6m insulin_pilatus6m.cbf insulin_pilatus6mconverted.cbf -cmp insulin_pilatus6mconverted.cbf insulin_pilatus6mconverted_orig.cbf $(TIME) $(BIN)/testreals -cmp testrealin.cbf testrealout.cbf $(TIME) $(BIN)/testflat -cmp testflatin.cbf testflatout.cbf $(TIME) $(BIN)/testflatpacked -cmp testflatpackedin.cbf testflatpackedout.cbf ifneq ($(F90C),) echo testflatout.cbf | $(TIME) $(BIN)/test_xds_binary > test_xds_bin_testflatout.out -$(DIFF) test_xds_bin_testflatout.out test_xds_bin_testflatout_orig.out echo testflatpackedout.cbf | $(TIME) $(BIN)/test_xds_binary > test_xds_bin_testflatpackedout.out -$(DIFF) test_xds_bin_testflatpackedout.out test_xds_bin_testflatpackedout_orig.out echo testflatout.cbf | $(TIME) $(BIN)/test_fcb_read_image > test_fcb_read_testflatout.out -$(DIFF) test_fcb_read_testflatout.out test_fcb_read_testflatout_orig.out echo testflatpackedout.cbf | $(TIME) $(BIN)/test_fcb_read_image > test_fcb_read_testflatpackedout.out -$(DIFF) test_fcb_read_testflatpackedout.out test_fcb_read_testflatpackedout_orig.out endif $(TIME) $(BIN)/sauter_test $(TIME) $(BIN)/changtestcompression $(TIME) (export LD_LIBRARY_PATH=$(LIB);$(BIN)/tiff2cbf XRD1621.tif XRD1621.cbf) -$(DIFF) XRD1621.cbf XRD1621_orig.cbf $(TIME) $(BIN)/cif2cbf -I 4 -C 100. -L 0. -e n -c b -i XRD1621.cbf -o XRD1621_I4encbC100.cbf -$(DIFF) XRD1621_I4encbC100.cbf XRD1621_I4encbC100_orig.cbf ifneq ($(F90C),) extra_sigs_only: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/test_xds_binary $(BIN)/test_fcb_read_image $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg $(BIN)/tiff2cbf \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) else extra_sigs_only: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf\ basic $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) endif $(TIME) $(BIN)/cif2cbf -e hex -c none \ makecbf.cbf cif2cbf_ehcn.cif $(TIME) $(BIN)/cif2cbf -e none -c packed \ cif2cbf_ehcn.cif cif2cbf_encp.cbf; rm cif2cbf_ehcn.cif -cmp makecbf.cbf cif2cbf_encp.cbf $(TIME) $(BIN)/cif2cbf -i 9ins.cif -o 9ins.cbf -cmp 9ins.cif 9ins.cbf $(TIME) $(BIN)/convert_image -F example.mar2300 converted_flat.cbf -$(SIGNATURE) < converted_flat.cbf | $(DIFF) - converted_flat_orig.cbf$(SEXT); rm converted_flat.cbf $(TIME) $(BIN)/convert_image example.mar2300 converted.cbf -$(SIGNATURE) < converted.cbf | $(DIFF) - converted_orig.cbf$(SEXT); rm converted.cbf -$(TIME) $(BIN)/testcell < testcell.dat | \ $(SIGNATURE) | $(DIFF) - testcell_orig.prt$(SEXT) $(TIME) $(BIN)/convert_image -F -d adscquantum315 mb_LP_1_001.img adscconverted_flat.cbf -$(SIGNATURE) < adscconverted_flat.cbf | $(DIFF) - adscconverted_flat_orig.cbf$(SEXT) $(TIME) $(BIN)/convert_image -d adscquantum315 mb_LP_1_001.img adscconverted.cbf -$(SIGNATURE) < adscconverted.cbf | $(DIFF) - adscconverted_orig.cbf$(SEXT); rm adscconverted.cbf $(TIME) $(BIN)/adscimg2cbf --cbf_packed,flat mb_LP_1_001.img -$(SIGNATURE) < mb_LP_1_001.cbf | $(DIFF) - mb_LP_1_001_orig.cbf$(SEXT) mv mb_LP_1_001.cbf nmb_LP_1_001.cbf $(TIME) $(BIN)/cbf2adscimg nmb_LP_1_001.cbf -cmp nmb_LP_1_001.img mb_LP_1_001.img rm nmb_LP_1_001.cbf rm nmb_LP_1_001.img $(TIME) $(BIN)/convert_minicbf -d pilatus6m insulin_pilatus6m.cbf insulin_pilatus6mconverted.cbf -$(SIGNATURE) < insulin_pilatus6mconverted.cbf | $(DIFF) - insulin_pilatus6mconverted_orig.cbf$(SEXT); rm insulin_pilatus6mconverted.cbf $(TIME) $(BIN)/testreals -cmp testrealin.cbf testrealout.cbf $(TIME) $(BIN)/testflat -cmp testflatin.cbf testflatout.cbf $(TIME) $(BIN)/testflatpacked -cmp testflatpackedin.cbf testflatpackedout.cbf ifneq ($(F90C),) echo testflatout.cbf | $(TIME) $(BIN)/test_xds_binary | \ $(SIGNATURE) | $(DIFF) - test_xds_bin_testflatout_orig.out$(SEXT) echo testflatpackedout.cbf | $(TIME) $(BIN)/test_xds_binary | \ $(SIGNATURE) | $(DIFF) - test_xds_bin_testflatpackedout_orig.out$(SEXT) echo testflatout.cbf | $(TIME) $(BIN)/test_fcb_read_image | \ $(SIGNATURE) | $(DIFF) - test_fcb_read_testflatout_orig.out$(SEXT) echo testflatpackedout.cbf | $(TIME) $(BIN)/test_fcb_read_image | \ $(SIGNATURE) | $(DIFF) - test_fcb_read_testflatpackedout_orig.out$(SEXT) endif $(TIME) $(BIN)/sauter_test $(TIME) $(BIN)/tiff2cbf XRD1621.tif XRD1621.cbf $(TIME) $(BIN)/cif2cbf -I 4 -C 100. -L 0. -e n -c b -i XRD1621.cbf -o XRD1621_I4encbC100.cbf -$(SIGNATURE) < XRD1621.cbf | $(DIFF) - XRD1621_orig.cbf$(SEXT); rm XRD1621.cbf -$(SIGNATURE) < XRD1621_I4encbC100.cbf | $(DIFF) - XRD1621_I4encbC100_orig.cbf$(SEXT); rm XRD1621_I4encbC100.cbf @-rm -f adscconverted_flat.cbf @-rm -f $(TESTINPUT_BASIC) $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) @-rm -f cif2cbf_packed.cbf makecbf.cbf \ cif2cbf_packed.cbf img2cif_packed.cbf \ cif2cbf_canonical.cbf img2cif_canonical.cbf @-rm -f testrealout.cbf testflatout.cbf testflatpackedout.cbf \ cif2cbf_encp.cbf img2cif_canonical.cif img2cif_packed.cif 9ins.cbf pycbftests: $(PYCBF)/_pycbf.$(PYCBFEXT) (cd $(PYCBF); python pycbf_test1.py) (cd $(PYCBF); python pycbf_test2.py) (cd $(PYCBF); python pycbf_test3.py) javatests: $(BIN)/ctestcbf $(BIN)/testcbf.class $(SOLIB)/libcbf_wrap.so $(BIN)/ctestcbf > testcbfc.txt $(LDPREFIX) java -cp $(JCBF)/cbflib-$(VERSION).jar:$(BIN) testcbf > testcbfj.txt $(DIFF) testcbfc.txt testcbfj.txt dectristests: $(BIN)/cbf_template_t $(DECTRIS_EXAMPLES)/cbf_test_orig.out (cd $(DECTRIS_EXAMPLES); ../../bin/cbf_template_t; diff -a -u cbf_test_orig.out cbf_template_t.out) # # Remove all non-source files # empty: @-rm -f $(LIB)/*.o @-rm -f $(LIB)/libcbf.a @-rm -f $(LIB)/libfcb.a @-rm -f $(LIB)/libimg.a @-rm -f $(LIB)/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/build/*/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/build/src/cbf_simple.o @-rm -f $(PYCBF)/build/*/pycbf_wrap.o @-rm -rf $(BIN)/adscimg2cbf* @-rm -rf $(BIN)/cbf2adscimg* @-rm -rf $(BIN)/makecbf* @-rm -rf $(BIN)/img2cif* @-rm -rf $(BIN)/cif2cbf* @-rm -rf $(BIN)/convert_image* @-rm -rf $(BIN)/convert_minicbf* @-rm -rf $(BIN)/test_fcb_read_image* @-rm -rf $(BIN)/test_xds_binary* @-rm -rf $(BIN)/testcell* @-rm -rf $(BIN)/cif2c* @-rm -rf $(BIN)/testreals* @-rm -rf $(BIN)/testflat* @-rm -rf $(BIN)/testflatpacked* @-rm -rf $(BIN)/cbf_template_t* @-rm -rf $(BIN)/sauter_test* @-rm -rf $(BIN)/arvai_test* @-rm -rf $(BIN)/changtestcompression* @-rm -rf $(BIN)/tiff2cbf* @-rm -f makecbf.cbf @-rm -f img2cif_packed.cif @-rm -f img2cif_canonical.cif @-rm -f img2cif_packed.cbf @-rm -f img2cif_canonical.cbf @-rm -f img2cif_raw.cbf @-rm -f cif2cbf_packed.cbf @-rm -f cif2cbf_canonical.cbf @-rm -f converted.cbf @-rm -f adscconverted.cbf @-rm -f converted_flat.cbf @-rm -f adscconverted_flat.cbf @-rm -f adscconverted_flat_rev.cbf @-rm -f mb_LP_1_001.cbf @-rm -f cif2cbf_ehcn.cif @-rm -f cif2cbf_encp.cbf @-rm -f 9ins.cbf @-rm -f 9ins.cif @-rm -f testcell.prt @-rm -f example.mar2300 @-rm -f converted_orig.cbf @-rm -f adscconverted_orig.cbf @-rm -f converted_flat_orig.cbf @-rm -f adscconverted_flat_orig.cbf @-rm -f adscconverted_flat_rev_orig.cbf @-rm -f mb_LP_1_001_orig.cbf @-rm -f insulin_pilatus6mconverted_orig.cbf @-rm -f insulin_pilatus6mconverted.cbf @-rm -f insulin_pilatus6m.cbf @-rm -f testrealin.cbf @-rm -f testrealout.cbf @-rm -f testflatin.cbf @-rm -f testflatout.cbf @-rm -f testflatpackedin.cbf @-rm -f testflatpackedout.cbf @-rm -f CTC.cbf @-rm -f test_fcb_read_testflatout.out @-rm -f test_fcb_read_testflatpackedout.out @-rm -f test_xds_bin_testflatpackedout.out @-rm -f test_xds_bin_testflatout.out @-rm -f test_fcb_read_testflatout_orig.out @-rm -f test_fcb_read_testflatpackedout_orig.out @-rm -f test_xds_bin_testflatpackedout_orig.out @-rm -f test_xds_bin_testflatout_orig.out @-rm -f mb_LP_1_001.img @-rm -f 9ins.cif @-rm -f testcell_orig.prt @-rm -f $(DECTRIS_EXAMPLES)/cbf_template_t.out @-rm -f XRD1621.cbf @-rm -f XRD1621_orig.cbf @-rm -f XRD1621_orig.cbf @-rm -f XRD1621_I4encbC100.cbf @-rm -f $(SRC)/fcb_exit_binary.f90 @-rm -f $(SRC)/fcb_next_binary.f90 @-rm -f $(SRC)/fcb_open_cifin.f90 @-rm -f $(SRC)/fcb_packed.f90 @-rm -f $(SRC)/fcb_read_bits.f90 @-rm -f $(SRC)/fcb_read_image.f90 @-rm -f $(SRC)/fcb_read_xds_i2.f90 @-rm -f $(EXAMPLES)/test_fcb_read_image.f90 @-rm -f $(EXAMPLES)/test_xds_binary.f90 @-rm -f symlinksdone @-rm -f $(TESTOUTPUT) *$(SEXT) @-rm -f $(SOLIB)/*.o @-rm -f $(SOLIB)/libcbf_wrap.so @-rm -f $(SOLIB)/libjcbf.so @-rm -f $(SOLIB)/libimg.so @-rm -f $(SOLIB)/libfcb.so @-rm -rf $(JCBF)/org @-rm -f $(JCBF)/*.java @-rm -f $(JCBF)/jcbf_wrap.c @-rm -f $(SRC)/cbf_wrap.c @-rm -f $(BIN)/ctestcbf $(BIN)/testcbf.class testcbfc.txt testcbfj.txt @-rm -rf $(REGEX) @-rm -rf $(TIFF) ./.undosymlinks # # Remove temporary files # clean: @-rm -f core @-rm -f *.o @-rm -f *.u # # Restore to distribution state # distclean: clean empty # # Create a Tape Archive for distribution # tar: $(DOCUMENTS) $(SOURCE) $(SRC)/cbf.stx $(HEADERS) $(M4FILES)\ $(EXAMPLES) \ README.html README Makefile \ $(JPEGS) -/bin/rm -f CBFlib.tar* tar cvBf CBFlib.tar \ $(DOCUMENTS) $(SOURCE) $(SRC)/cbf.stx $(HEADERS) $(M4FILES)\ $(EXAMPLES) \ README.html README Makefile \ $(JPEGS) gzip --best CBFlib.tar ./CBFlib-0.9.2.2/gpl.txt0000777000076500007650000000000011603751102015206 2doc/gpl.txtustar yayayaya./CBFlib-0.9.2.2/Makefile_AIX0000644000076500007650000017762611603702122013760 0ustar yayayaya ###################################################################### # Makefile - command file for make to create CBFlib # # # # Version 0.9.2 12 Feb 2011 # # # # Paul Ellis and # # Herbert J. Bernstein (yaya@bernstein-plus-sons.com) # # # # (C) Copyright 2006 - 2011 Herbert J. Bernstein # # # ###################################################################### ###################################################################### # # # YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL # # # # ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS # # OF THE LGPL # # # ###################################################################### ########################### GPL NOTICES ############################## # # # This program is free software; you can redistribute it and/or # # modify it under the terms of the GNU General Public License as # # published by the Free Software Foundation; either version 2 of # # (the License, or (at your option) any later version. # # # # This program is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # # GNU General Public License for more details. # # # # You should have received a copy of the GNU General Public License # # along with this program; if not, write to the Free Software # # Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA # # 02111-1307 USA # # # ###################################################################### ######################### LGPL NOTICES ############################### # # # This library is free software; you can redistribute it and/or # # modify it under the terms of the GNU Lesser General Public # # License as published by the Free Software Foundation; either # # version 2.1 of the License, or (at your option) any later version. # # # # This library is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # # Lesser General Public License for more details. # # # # You should have received a copy of the GNU Lesser General Public # # License along with this library; if not, write to the Free # # Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, # # MA 02110-1301 USA # # # ###################################################################### ###################################################################### # # # Stanford University Notices # # for the CBFlib software package that incorporates SLAC software # # on which copyright is disclaimed # # # # This software # # ------------- # # The term "this software", as used in these Notices, refers to # # those portions of the software package CBFlib that were created by # # employees of the Stanford Linear Accelerator Center, Stanford # # University. # # # # Stanford disclaimer of copyright # # -------------------------------- # # Stanford University, owner of the copyright, hereby disclaims its # # copyright and all other rights in this software. Hence, anyone # # may freely use it for any purpose without restriction. # # # # Acknowledgement of sponsorship # # ------------------------------ # # This software was produced by the Stanford Linear Accelerator # # Center, Stanford University, under Contract DE-AC03-76SFO0515 with # # the Department of Energy. # # # # Government disclaimer of liability # # ---------------------------------- # # Neither the United States nor the United States Department of # # Energy, nor any of their employees, makes any warranty, express or # # implied, or assumes any legal liability or responsibility for the # # accuracy, completeness, or usefulness of any data, apparatus, # # product, or process disclosed, or represents that its use would # # not infringe privately owned rights. # # # # Stanford disclaimer of liability # # -------------------------------- # # Stanford University makes no representations or warranties, # # express or implied, nor assumes any liability for the use of this # # software. # # # # Maintenance of notices # # ---------------------- # # In the interest of clarity regarding the origin and status of this # # software, this and all the preceding Stanford University notices # # are to remain affixed to any copy or derivative of this software # # made or distributed by the recipient and are to be affixed to any # # copy of software made or distributed by the recipient that # # contains a copy or derivative of this software. # # # # Based on SLAC Software Notices, Set 4 # # OTT.002a, 2004 FEB 03 # ###################################################################### ###################################################################### # NOTICE # # Creative endeavors depend on the lively exchange of ideas. There # # are laws and customs which establish rights and responsibilities # # for authors and the users of what authors create. This notice # # is not intended to prevent you from using the software and # # documents in this package, but to ensure that there are no # # misunderstandings about terms and conditions of such use. # # # # Please read the following notice carefully. If you do not # # understand any portion of this notice, please seek appropriate # # professional legal advice before making use of the software and # # documents included in this software package. In addition to # # whatever other steps you may be obliged to take to respect the # # intellectual property rights of the various parties involved, if # # you do make use of the software and documents in this package, # # please give credit where credit is due by citing this package, # # its authors and the URL or other source from which you obtained # # it, or equivalent primary references in the literature with the # # same authors. # # # # Some of the software and documents included within this software # # package are the intellectual property of various parties, and # # placement in this package does not in any way imply that any # # such rights have in any way been waived or diminished. # # # # With respect to any software or documents for which a copyright # # exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. # # # # Even though the authors of the various documents and software # # found here have made a good faith effort to ensure that the # # documents are correct and that the software performs according # # to its documentation, and we would greatly appreciate hearing of # # any problems you may encounter, the programs and documents any # # files created by the programs are provided **AS IS** without any * # warranty as to correctness, merchantability or fitness for any # # particular or general use. # # # # THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF # # PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE # # PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS # # OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE # # PROGRAMS OR DOCUMENTS. # ###################################################################### ###################################################################### # # # The IUCr Policy # # for the Protection and the Promotion of the STAR File and # # CIF Standards for Exchanging and Archiving Electronic Data # # # # Overview # # # # The Crystallographic Information File (CIF)[1] is a standard for # # information interchange promulgated by the International Union of # # Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the # # recommended method for submitting publications to Acta # # Crystallographica Section C and reports of crystal structure # # determinations to other sections of Acta Crystallographica # # and many other journals. The syntax of a CIF is a subset of the # # more general STAR File[2] format. The CIF and STAR File approaches # # are used increasingly in the structural sciences for data exchange # # and archiving, and are having a significant influence on these # # activities in other fields. # # # # Statement of intent # # # # The IUCr's interest in the STAR File is as a general data # # interchange standard for science, and its interest in the CIF, # # a conformant derivative of the STAR File, is as a concise data # # exchange and archival standard for crystallography and structural # # science. # # # # Protection of the standards # # # # To protect the STAR File and the CIF as standards for # # interchanging and archiving electronic data, the IUCr, on behalf # # of the scientific community, # # # # # holds the copyrights on the standards themselves, * # # # # owns the associated trademarks and service marks, and * # # # # holds a patent on the STAR File. * # # # These intellectual property rights relate solely to the # # interchange formats, not to the data contained therein, nor to # # the software used in the generation, access or manipulation of # # the data. # # # # Promotion of the standards # # # # The sole requirement that the IUCr, in its protective role, # # imposes on software purporting to process STAR File or CIF data # # is that the following conditions be met prior to sale or # # distribution. # # # # # Software claiming to read files written to either the STAR * # File or the CIF standard must be able to extract the pertinent # # data from a file conformant to the STAR File syntax, or the CIF # # syntax, respectively. # # # # # Software claiming to write files in either the STAR File, or * # the CIF, standard must produce files that are conformant to the # # STAR File syntax, or the CIF syntax, respectively. # # # # # Software claiming to read definitions from a specific data * # dictionary approved by the IUCr must be able to extract any # # pertinent definition which is conformant to the dictionary # # definition language (DDL)[3] associated with that dictionary. # # # # The IUCr, through its Committee on CIF Standards, will assist # # any developer to verify that software meets these conformance # # conditions. # # # # Glossary of terms # # # # [1] CIF: is a data file conformant to the file syntax defined # # at http://www.iucr.org/iucr-top/cif/spec/index.html # # # # [2] STAR File: is a data file conformant to the file syntax # # defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html # # # # [3] DDL: is a language used in a data dictionary to define data # # items in terms of "attributes". Dictionaries currently approved # # by the IUCr, and the DDL versions used to construct these # # dictionaries, are listed at # # http://www.iucr.org/iucr-top/cif/spec/ddl/index.html # # # # Last modified: 30 September 2000 # # # # IUCr Policy Copyright (C) 2000 International Union of # # Crystallography # ###################################################################### # Version string VERSION = 0.9.2 # # Comment out the next line if scratch test files sould be retain # CLEANTESTS = yes # # Definition to get a version of tifflib to support tiff2cbf # TIFF = tiff-3.9.4-rev-6Feb11 TIFFPREFIX = $(PWD) # # Definitions to get a stable version of regex # REGEX = regex-20090805 REGEXDIR = /usr/lib REGEXDEP = # Program to use to retrieve a URL DOWNLOAD = wget # Flag to control symlinks versus copying SLFLAGS = --use_ln # # Program to use to pack shars # SHAR = /usr/bin/shar #SHAR = /usr/local/bin/gshar # # Program to use to create archives # AR = /usr/bin/ar # # Program to use to add an index to an archive # RANLIB = /usr/bin/ranlib # # Program to use to decompress a data file # DECOMPRESS = /usr/bin/bunzip2 # # Program to use to compress a data file # COMPRESS = /usr/bin/bzip2 # # Program to use to generate a signature # SIGNATURE = /usr/bin/openssl dgst -md5 # # Extension for compressed data file (with period) # CEXT = .bz2 # # Extension for signatures of files # SEXT = .md5 # call to time a command #TIME = #TIME = time # # Program to display differences between files # DIFF = diff -u -b # # Program to generate wrapper classes for Python # PYSWIG = swig -python # # Program to generate wrapper classes for Java # JSWIG = swig -java # # Program to generate LaTex and HTML program documentation # NUWEB = nuweb # # Compiler for Java # JAVAC = javac # # Java archiver for compiled classes # JAR = jar # # Java SDK root directory # ifeq ($(JDKDIR),) JDKDIR = /usr/lib/java endif ifneq ($(CBF_DONT_USE_LONG_LONG),) NOLLFLAG = -DCBF_DONT_USE_LONG_LONG else NOLLFLAG = endif # # PYCBF definitions # PYCBFEXT = so PYCBFBOPT = SETUP_PY = setup.py # # Set the compiler and flags # ######################################################### # # Appropriate compiler definitions for AIX # ######################################################### CC = xlc C++ = xlC CFLAGS = -g -O2 -Wall F90C = xlf90 F90FLAGS = -g -qsuffix=f=f90 F90LDFLAGS = M4FLAGS = -Dfcb_bytes_in_rec=131072 EXTRALIBS = -lm TIME = time ifneq ($(NOFORTRAN),) F90C = endif # # Directories # ROOT = . LIB = $(ROOT)/lib SOLIB = $(ROOT)/solib JCBF = $(ROOT)/jcbf JAVADIR = $(ROOT)/java BIN = $(ROOT)/bin SRC = $(ROOT)/src INCLUDE = $(ROOT)/include M4 = $(ROOT)/m4 PYCBF = $(ROOT)/pycbf EXAMPLES = $(ROOT)/examples DECTRIS_EXAMPLES = $(EXAMPLES)/dectris_cbf_template_test DOC = $(ROOT)/doc GRAPHICS = $(ROOT)/html_graphics DATADIRI = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Input DATADIRO = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Output DATADIRS = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only INSTALLDIR = $(HOME) # # URLs from which to retrieve the data directories # DATAURLBASE = http://downloads.sf.net/cbflib/ DATAURLI = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Input.tar.gz DATAURLO = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Output.tar.gz DATAURLS = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz # # URLs from which to retrieve needed external package snapshots # REGEXURL = http://downloads.sf.net/cbflib/$(REGEX).tar.gz TIFFURL = http://downloads.sf.net/cbflib/$(TIFF).tar.gz # # Include directories # INCLUDES = -I$(INCLUDE) -I$(SRC) ###################################################################### # You should not need to make modifications below this line # ###################################################################### # # Suffixes of files to be used or built # .SUFFIXES: .c .o .f90 .m4 .m4.f90: m4 -P $(M4FLAGS) $< > $@ ifneq ($(F90C),) .f90.o: $(F90C) $(F90FLAGS) -c $< -o $@ endif # # Common dependencies # COMMONDEP = Makefile # # Source files # SOURCE = $(SRC)/cbf.c \ $(SRC)/cbf_alloc.c \ $(SRC)/cbf_ascii.c \ $(SRC)/cbf_binary.c \ $(SRC)/cbf_byte_offset.c \ $(SRC)/cbf_canonical.c \ $(SRC)/cbf_codes.c \ $(SRC)/cbf_compress.c \ $(SRC)/cbf_context.c \ $(SRC)/cbf_copy.c \ $(SRC)/cbf_file.c \ $(SRC)/cbf_getopt.c \ $(SRC)/cbf_lex.c \ $(SRC)/cbf_packed.c \ $(SRC)/cbf_predictor.c \ $(SRC)/cbf_read_binary.c \ $(SRC)/cbf_read_mime.c \ $(SRC)/cbf_simple.c \ $(SRC)/cbf_string.c \ $(SRC)/cbf_stx.c \ $(SRC)/cbf_tree.c \ $(SRC)/cbf_uncompressed.c \ $(SRC)/cbf_write.c \ $(SRC)/cbf_write_binary.c \ $(SRC)/cbf_ws.c \ $(SRC)/md5c.c F90SOURCE = $(SRC)/fcb_atol_wcnt.f90 \ $(SRC)/fcb_ci_strncmparr.f90 \ $(SRC)/fcb_exit_binary.f90 \ $(SRC)/fcb_nblen_array.f90 \ $(SRC)/fcb_next_binary.f90 \ $(SRC)/fcb_open_cifin.f90 \ $(SRC)/fcb_packed.f90 \ $(SRC)/fcb_read_bits.f90 \ $(SRC)/fcb_read_byte.f90 \ $(SRC)/fcb_read_image.f90 \ $(SRC)/fcb_read_line.f90 \ $(SRC)/fcb_read_xds_i2.f90 \ $(SRC)/fcb_skip_whitespace.f90 \ $(EXAMPLES)/test_fcb_read_image.f90 \ $(EXAMPLES)/test_xds_binary.f90 # # Header files # HEADERS = $(INCLUDE)/cbf.h \ $(INCLUDE)/cbf_alloc.h \ $(INCLUDE)/cbf_ascii.h \ $(INCLUDE)/cbf_binary.h \ $(INCLUDE)/cbf_byte_offset.h \ $(INCLUDE)/cbf_canonical.h \ $(INCLUDE)/cbf_codes.h \ $(INCLUDE)/cbf_compress.h \ $(INCLUDE)/cbf_context.h \ $(INCLUDE)/cbf_copy.h \ $(INCLUDE)/cbf_file.h \ $(INCLUDE)/cbf_getopt.h \ $(INCLUDE)/cbf_lex.h \ $(INCLUDE)/cbf_packed.h \ $(INCLUDE)/cbf_predictor.h \ $(INCLUDE)/cbf_read_binary.h \ $(INCLUDE)/cbf_read_mime.h \ $(INCLUDE)/cbf_simple.h \ $(INCLUDE)/cbf_string.h \ $(INCLUDE)/cbf_stx.h \ $(INCLUDE)/cbf_tree.h \ $(INCLUDE)/cbf_uncompressed.h \ $(INCLUDE)/cbf_write.h \ $(INCLUDE)/cbf_write_binary.h \ $(INCLUDE)/cbf_ws.h \ $(INCLUDE)/global.h \ $(INCLUDE)/cbff.h \ $(INCLUDE)/md5.h # # m4 macro files # M4FILES = $(M4)/fcblib_defines.m4 \ $(M4)/fcb_exit_binary.m4 \ $(M4)/fcb_next_binary.m4 \ $(M4)/fcb_open_cifin.m4 \ $(M4)/fcb_packed.m4 \ $(M4)/fcb_read_bits.m4 \ $(M4)/fcb_read_image.m4 \ $(M4)/fcb_read_xds_i2.m4 \ $(M4)/test_fcb_read_image.m4 \ $(M4)/test_xds_binary.m4 # # Documentation files # DOCUMENTS = $(DOC)/CBFlib.html \ $(DOC)/CBFlib.txt \ $(DOC)/CBFlib_NOTICES.html \ $(DOC)/CBFlib_NOTICES.txt \ $(DOC)/ChangeLog \ $(DOC)/ChangeLog.html \ $(DOC)/MANIFEST \ $(DOC)/gpl.txt $(DOC)/lgpl.txt # # HTML Graphics files # JPEGS = $(GRAPHICS)/CBFbackground.jpg \ $(GRAPHICS)/CBFbig.jpg \ $(GRAPHICS)/CBFbutton.jpg \ $(GRAPHICS)/cbflibbackground.jpg \ $(GRAPHICS)/cbflibbig.jpg \ $(GRAPHICS)/cbflibbutton.jpg \ $(GRAPHICS)/cifhome.jpg \ $(GRAPHICS)/iucrhome.jpg \ $(GRAPHICS)/noticeButton.jpg # # Default: instructions # default: @echo ' ' @echo '***************************************************************' @echo ' ' @echo ' PLEASE READ README and doc/CBFlib_NOTICES.txt' @echo ' ' @echo ' Before making the CBF library and example programs, check' @echo ' that the C compiler name and flags are correct:' @echo ' ' @echo ' The current values are:' @echo ' ' @echo ' $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG)' @echo ' ' @echo ' Before installing the CBF library and example programs, check' @echo ' that the install directory is correct:' @echo ' ' @echo ' The current value :' @echo ' ' @echo ' $(INSTALLDIR) ' @echo ' ' @echo ' To compile the CBF library and example programs type:' @echo ' ' @echo ' make clean' @echo ' make all' @echo ' ' @echo ' To compile the CBF library as a shared object library, type:' @echo ' ' @echo ' make shared' @echo ' ' @echo ' To compile the Java wrapper classes for CBF library, type:' @echo ' ' @echo ' make javawrapper' @echo ' ' @echo ' To run a set of tests type:' @echo ' ' @echo ' make tests' @echo ' ' @echo ' To run some java tests type:' @echo ' ' @echo ' make javatests' @echo ' ' @echo ' The tests assume that several data files are in the directories' @echo ' $(DATADIRI) and $(DATADIRO)' @echo ' ' @echo ' Alternatively tests can be run comparing MD5 signatures only by' @echo ' ' @echo ' make tests_sigs_only' @echo ' ' @echo ' These signature only tests save space and download time by' @echo ' assuming that input data files and the output signatures' @echo ' are in the directories' @echo ' $(DATADIRI) and $(DATADIRS)' @echo ' ' @echo ' These directory can be obtained from' @echo ' ' @echo ' $(DATAURLI) ' @echo ' $(DATAURLO) ' @echo ' $(DATAURLS) ' @echo ' ' @echo ' To clean up the directories type:' @echo ' ' @echo ' make clean' @echo ' ' @echo ' To install the library and binaries type:' @echo ' ' @echo ' make install' @echo ' ' @echo '***************************************************************' @echo ' ' # # Compile the library and examples # all:: $(BIN) $(SOURCE) $(F90SOURCE) $(HEADERS) \ symlinksdone $(REGEXDEP) \ $(LIB)/libcbf.a \ $(LIB)/libfcb.a \ $(LIB)/libimg.a \ $(BIN)/adscimg2cbf \ $(BIN)/cbf2adscimg \ $(BIN)/convert_image \ $(BIN)/convert_minicbf \ $(BIN)/sequence_match \ $(BIN)/arvai_test \ $(BIN)/makecbf \ $(BIN)/img2cif \ $(BIN)/adscimg2cbf \ $(BIN)/cif2cbf \ $(BIN)/testcell \ $(BIN)/cif2c \ $(BIN)/testreals \ $(BIN)/testflat \ $(BIN)/testflatpacked ifneq ($(F90C),) all:: $(BIN)/test_xds_binary \ $(BIN)/test_fcb_read_image endif shared: $(SOLIB)/libcbf.so $(SOLIB)/libfcb.so $(SOLIB)/libimg.so javawrapper: shared $(JCBF) $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf_wrap.so ifneq ($(CBFLIB_USE_PYCIFRW),) PYCIFRWDEF = -Dcbf_use_pycifrw=yes else PYCIFRWDEF = endif Makefiles: Makefile \ Makefile_LINUX \ Makefile_LINUX_64 \ Makefile_LINUX_gcc42 \ Makefile_LINUX_DMALLOC \ Makefile_LINUX_gcc42_DMALLOC \ Makefile_OSX \ Makefile_OSX_gcc42 \ Makefile_OSX_gcc42_DMALLOC \ Makefile_AIX \ Makefile_MINGW \ Makefile_IRIX_gcc Makefile_LINUX: $(M4)/Makefile.m4 -cp Makefile_LINUX Makefile_LINUX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX $(M4)/Makefile.m4 > Makefile_LINUX Makefile_LINUX_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_LINUX Makefile_LINUX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_DMALLOC $(M4)/Makefile.m4 > Makefile_LINUX_DMALLOC Makefile_LINUX_64: $(M4)/Makefile.m4 -cp Makefile_LINUX_64 Makefile_LINUX_64_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_64 $(M4)/Makefile.m4 > Makefile_LINUX_64 Makefile_LINUX_gcc42: $(M4)/Makefile.m4 -cp Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_gcc42 $(M4)/Makefile.m4 > Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_gcc42_DMALLOC $(M4)/Makefile.m4 > Makefile_LINUX_gcc42_DMALLOC Makefile_OSX: $(M4)/Makefile.m4 -cp Makefile_OSX Makefile_OSX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX $(M4)/Makefile.m4 > Makefile_OSX Makefile_OSX_gcc42: $(M4)/Makefile.m4 -cp Makefile_OSX_gcc42 Makefile_OSX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX_gcc42 $(M4)/Makefile.m4 > Makefile_OSX_gcc42 Makefile_OSX_gcc42_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_OSX_gcc42 Makefile_OSX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX_gcc42_DMALLOC $(M4)/Makefile.m4 > Makefile_OSX_gcc42_DMALLOC Makefile_AIX: $(M4)/Makefile.m4 -cp Makefile_AIX Makefile_AIX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=AIX $(M4)/Makefile.m4 > Makefile_AIX Makefile_MINGW: $(M4)/Makefile.m4 -cp Makefile_MINGW Makefile_MINGW_old m4 -P $(PYCIFRWDEF) -Dcbf_system=MINGW $(M4)/Makefile.m4 > Makefile_MINGW Makefile_IRIX_gcc: $(M4)/Makefile.m4 -cp Makefile_IRIX_gcc Makefile_IRIX_gcc_old m4 -P $(PYCIFREDEF) -Dcbf_system=IRIX_gcc $(M4)/Makefile.m4 > Makefile_IRIX_gcc Makefile: $(M4)/Makefile.m4 -cp Makefile Makefile_old m4 -P $(PYCIFRWDEF) -Dcbf_system=default $(M4)/Makefile.m4 > Makefile symlinksdone: chmod a+x .symlinks chmod a+x .undosymlinks chmod a+x doc/.symlinks chmod a+x doc/.undosymlinks chmod a+x libtool/.symlinks chmod a+x libtool/.undosymlinks ./.symlinks $(SLFLAGS) touch symlinksdone install: all $(INSTALLDIR) $(INSTALLDIR)/lib $(INSTALLDIR)/bin \ $(INSTALLDIR)/include $(INSTALLDIR)/include/cbflib \ $(PYSOURCE) -chmod -R 755 $(INSTALLDIR)/include/cbflib -chmod 755 $(INSTALLDIR)/lib/libcbf.a -cp $(INSTALLDIR)/lib/libcbf.a $(INSTALLDIR)/lib/libcbf_old.a cp $(LIB)/libcbf.a $(INSTALLDIR)/lib/libcbf.a -cp $(INSTALLDIR)/lib/libimg.a $(INSTALLDIR)/lib/libimg_old.a cp $(LIB)/libimg.a $(INSTALLDIR)/lib/libimg.a -cp $(INSTALLDIR)/bin/adscimg2cbf $(INSTALLDIR)/bin/adscimg2cbf_old cp $(BIN)/adscimg2cbf $(INSTALLDIR)/bin/adscimg2cbf -cp $(INSTALLDIR)/bin/cbf2adscimg $(INSTALLDIR)/bin/cbf2adscimg_old cp $(BIN)/cbf2adscimg $(INSTALLDIR)/bin/cbf2adscimg -cp $(INSTALLDIR)/bin/convert_image $(INSTALLDIR)/bin/convert_image_old cp $(BIN)/convert_image $(INSTALLDIR)/bin/convert_image -cp $(INSTALLDIR)/bin/convert_minicbf $(INSTALLDIR)/bin/convert_minicbf_old cp $(BIN)/convert_minicbf $(INSTALLDIR)/bin/convert_minicbf -cp $(INSTALLDIR)/bin/makecbf $(INSTALLDIR)/bin/makecbf_old cp $(BIN)/makecbf $(INSTALLDIR)/bin/makecbf -cp $(INSTALLDIR)/bin/img2cif $(INSTALLDIR)/bin/img2cif_old cp $(BIN)/img2cif $(INSTALLDIR)/bin/img2cif -cp $(INSTALLDIR)/bin/cif2cbf $(INSTALLDIR)/bin/cif2cbf_old cp $(BIN)/cif2cbf $(INSTALLDIR)/bin/cif2cbf -cp $(INSTALLDIR)/bin/sequence_match $(INSTALLDIR)/bin/sequence_match_old cp $(BIN)/sequence_match $(INSTALLDIR)/bin/sequence_match -cp $(INSTALLDIR)/bin/arvai_test $(INSTALLDIR)/bin/arvai_test_old cp $(BIN)/arvai_test $(INSTALLDIR)/bin/arvai_test -cp $(INSTALLDIR)/bin/cif2c $(INSTALLDIR)/bin/cif2c_old cp $(BIN)/cif2c $(INSTALLDIR)/bin/cif2c -cp $(INSTALLDIR)/bin/testreals $(INSTALLDIR)/bin/testreals_old cp $(BIN)/testreals $(INSTALLDIR)/bin/testreals -cp $(INSTALLDIR)/bin/testflat $(INSTALLDIR)/bin/testflat_old cp $(BIN)/testflat $(INSTALLDIR)/bin/testflat -cp $(INSTALLDIR)/bin/testflatpacked $(INSTALLDIR)/bin/testflatpacked_old cp $(BIN)/testflatpacked $(INSTALLDIR)/bin/testflatpacked chmod -R 755 $(INSTALLDIR)/include/cbflib -rm -rf $(INSTALLDIR)/include/cbflib_old -cp -r $(INSTALLDIR)/include/cbflib $(INSTALLDIR)/include/cbflib_old -rm -rf $(INSTALLDIR)/include/cbflib cp -r $(INCLUDE) $(INSTALLDIR)/include/cbflib chmod 644 $(INSTALLDIR)/lib/libcbf.a chmod 755 $(INSTALLDIR)/bin/convert_image chmod 755 $(INSTALLDIR)/bin/convert_minicbf chmod 755 $(INSTALLDIR)/bin/makecbf chmod 755 $(INSTALLDIR)/bin/img2cif chmod 755 $(INSTALLDIR)/bin/cif2cbf chmod 755 $(INSTALLDIR)/bin/sequence_match chmod 755 $(INSTALLDIR)/bin/arvai_test chmod 755 $(INSTALLDIR)/bin/cif2c chmod 755 $(INSTALLDIR)/bin/testreals chmod 755 $(INSTALLDIR)/bin/testflat chmod 755 $(INSTALLDIR)/bin/testflatpacked chmod 644 $(INSTALLDIR)/include/cbflib/*.h # # REGEX # ifneq ($(REGEXDEP),) $(REGEXDEP): $(REGEX) (cd $(REGEX); ./configure; make install) endif $(REGEX): $(DOWNLOAD) $(REGEXURL) tar -xvf $(REGEX).tar.gz -rm $(REGEX).tar.gz # # TIFF # $(TIFF): $(DOWNLOAD) $(TIFFURL) tar -xvf $(TIFF).tar.gz -rm $(TIFF).tar.gz (cd $(TIFF); ./configure --prefix=$(TIFFPREFIX); make install) # # Directories # $(INSTALLDIR): mkdir -p $(INSTALLDIR) $(INSTALLDIR)/lib: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/lib $(INSTALLDIR)/bin: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/bin $(INSTALLDIR)/include: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/include $(INSTALLDIR)/include/cbflib: $(INSTALLDIR)/include mkdir -p $(INSTALLDIR)/include/cbflib $(LIB): mkdir $@ $(BIN): mkdir $@ $(SOLIB): mkdir $@ $(JCBF): mkdir $@ # # Parser # $(SRC)/cbf_stx.c: $(SRC)/cbf.stx.y bison $(SRC)/cbf.stx.y -o $(SRC)/cbf.stx.tab.c -d mv $(SRC)/cbf.stx.tab.c $(SRC)/cbf_stx.c mv $(SRC)/cbf.stx.tab.h $(INCLUDE)/cbf_stx.h # # CBF library # $(LIB)/libcbf.a: $(SOURCE) $(HEADERS) $(COMMONDEP) $(LIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG) $(INCLUDES) $(WARNINGS) -c $(SOURCE) $(AR) cr $@ *.o mv *.o $(LIB) ifneq ($(RANLIB),) $(RANLIB) $@ endif $(SOLIB)/libcbf.so: $(SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(SOURCE) $(CC) -o $@ *.o $(SOLDFLAGS) $(EXTRALIBS) rm *.o # # IMG library # $(LIB)/libimg.a: $(EXAMPLES)/img.c $(HEADERS) $(COMMONDEP) $(LIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) -c $(EXAMPLES)/img.c $(AR) cr $@ img.o ifneq ($(RANLIB),) $(RANLIB) $@ endif rm img.o $(SOLIB)/libimg.so: $(SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(EXAMPLES)/img.c $(CC) -o $@ img.o $(SOLDFLAGS) rm img.o # # CBF and IMG libraries # CBF_IMG_LIBS: $(LIB)/libcbf.a $(LIB)/libimg.a # # FCB library # $(LIB)/libfcb.a: $(F90SOURCE) $(COMMONDEP) $(LIB) ifneq ($(F90C),) $(F90C) $(F90FLAGS) -c $(F90SOURCE) $(AR) cr $@ *.o ifneq ($(RANLIB),) $(RANLIB) $@ endif rm *.o else echo "Define F90C to build $(LIB)/libfcb.a" endif $(SOLIB)/libfcb.so: $(F90SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) ifneq ($(F90C),) $(F90C) $(F90FLAGS) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(F90SOURCE) $(F90C) $(F90FLAGS) -o $@ *.o $(SOLDFLAGS) rm *.o else echo "Define F90C to build $(SOLIB)/libfcb.so" endif # # Python bindings # $(PYCBF)/_pycbf.$(PYCBFEXT): $(PYCBF) $(LIB)/libcbf.a \ $(PYCBF)/$(SETUP_PY) \ $(LIB)/libfcb.a \ $(LIB)/libimg.a \ $(PYCBF)/pycbf.i \ $(PYCBF)/cbfhandlewrappers.i \ $(PYCBF)/cbfdetectorwrappers.i \ $(PYCBF)/cbfgenericwrappers.i \ $(PYCBF)/cbfgoniometerwrappers.i (cd $(PYCBF); python $(SETUP_PY) build $(PYCBFBOPT); cp build/lib.*/_pycbf.$(PYCBFEXT) .) $(PYCBF)/setup.py: $(M4)/setup_py.m4 (m4 -P -Dregexlib=NOREGEXLIB -Dregexlibdir=NOREGEXLIBDIR $(M4)/setup_py.m4 > $@) $(PYCBF)/setup_MINGW.py: m4/setup_py.m4 (m4 -P -Dregexlib=regex -Dregexlibdir=$(REGEXDIR) $(M4)/setup_py.m4 > $@) $(LIB)/_pycbf.$(PYCBFEXT): $(PYCBF)/_pycbf.$(PYCBFEXT) cp $(PYCBF)/_pycbf.$(PYCBFEXT) $(LIB)/_pycbf.$(PYCBFEXT) $(PYCBF)/pycbf.pdf: $(PYCBF)/pycbf.w (cd $(PYCBF); \ $(NUWEB) pycbf; \ latex pycbf; \ $(NUWEB) pycbf; \ latex pycbf; \ dvipdfm pycbf ) $(PYCBF)/CBFlib.txt: $(DOC)/CBFlib.html links -dump $(DOC)/CBFlib.html > $(PYCBF)/CBFlib.txt $(PYCBF)/cbfhandlewrappers.i \ $(PYCBF)/cbfdetectorwrappers.i \ $(PYCBF)/cbfgenericwrappers.i \ $(PYCBF)/cbfgoniometerwrappers.i: $(PYCBF)/CBFlib.txt $(PYCBF)/make_pycbf.py (cd $(PYCBF); python make_pycbf.py; $(PYSWIG) pycbf.i; python setup.py build) # # Java bindings # $(JCBF)/cbflib-$(VERSION).jar: $(JCBF) $(JCBF)/jcbf.i $(JSWIG) -I$(INCLUDE) -package org.iucr.cbflib -outdir $(JCBF) $(JCBF)/jcbf.i $(JAVAC) -d . $(JCBF)/*.java $(JAR) cf $@ org $(SOLIB)/libcbf_wrap.so: $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf.so $(CC) $(CFLAGS) $(NOLLFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) $(JAVAINCLUDES) -c $(JCBF)/jcbf_wrap.c $(CC) -o $@ jcbf_wrap.o $(SOLDFLAGS) -L$(SOLIB) -lcbf rm jcbf_wrap.o # # F90SOURCE # $(SRC)/fcb_exit_binary.f90: $(M4)/fcb_exit_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_exit_binary.m4) > $(SRC)/fcb_exit_binary.f90 $(SRC)/fcb_next_binary.f90: $(M4)/fcb_next_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_next_binary.m4) > $(SRC)/fcb_next_binary.f90 $(SRC)/fcb_open_cifin.f90: $(M4)/fcb_open_cifin.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_open_cifin.m4) > $(SRC)/fcb_open_cifin.f90 $(SRC)/fcb_packed.f90: $(M4)/fcb_packed.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_packed.m4) > $(SRC)/fcb_packed.f90 $(SRC)/fcb_read_bits.f90: $(M4)/fcb_read_bits.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_bits.m4) > $(SRC)/fcb_read_bits.f90 $(SRC)/fcb_read_image.f90: $(M4)/fcb_read_image.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_image.m4) > $(SRC)/fcb_read_image.f90 $(SRC)/fcb_read_xds_i2.f90: $(M4)/fcb_read_xds_i2.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_xds_i2.m4) > $(SRC)/fcb_read_xds_i2.f90 $(EXAMPLES)/test_fcb_read_image.f90: $(M4)/test_fcb_read_image.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) test_fcb_read_image.m4) > $(EXAMPLES)/test_fcb_read_image.f90 $(EXAMPLES)/test_xds_binary.f90: $(M4)/test_xds_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) test_xds_binary.m4) > $(EXAMPLES)/test_xds_binary.f90 # # convert_image example program # $(BIN)/convert_image: $(LIB)/libcbf.a $(EXAMPLES)/convert_image.c $(EXAMPLES)/img.c \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/convert_image.c $(EXAMPLES)/img.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # convert_minicbf example program # $(BIN)/convert_minicbf: $(LIB)/libcbf.a $(EXAMPLES)/convert_minicbf.c \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/convert_minicbf.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # makecbf example program # $(BIN)/makecbf: $(LIB)/libcbf.a $(EXAMPLES)/makecbf.c $(LIB)/libimg.a $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/makecbf.c -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # adscimg2cbf example program # $(BIN)/adscimg2cbf: $(LIB)/libcbf.a $(EXAMPLES)/adscimg2cbf.c $(EXAMPLES)/adscimg2cbf_sub.c $(CC) $(CFLAGS) $(NOLLFLAG) -D_SVID_SOURCE $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/adscimg2cbf.c $(EXAMPLES)/adscimg2cbf_sub.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # cbf2adscimg example program # $(BIN)/cbf2adscimg: $(LIB)/libcbf.a $(EXAMPLES)/cbf2adscimg.c $(EXAMPLES)/cbf2adscimg_sub.c $(CC) $(CFLAGS) $(NOLLFLAG) -D_SVID_SOURCE $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cbf2adscimg.c $(EXAMPLES)/cbf2adscimg_sub.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # changtestcompression example program # $(BIN)/changtestcompression: $(LIB)/libcbf.a $(EXAMPLES)/changtestcompression.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/changtestcompression.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # img2cif example program # $(BIN)/img2cif: $(LIB)/libcbf.a $(EXAMPLES)/img2cif.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOTPINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/img2cif.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # cif2cbf example program # $(BIN)/cif2cbf: $(LIB)/libcbf.a $(EXAMPLES)/cif2cbf.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cif2cbf.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # dectris cbf_template_t program # $(BIN)/cbf_template_t: $(DECTRIS_EXAMPLES)/cbf_template_t.c \ $(DECTRIS_EXAMPLES)/mx_cbf_t_extras.h \ $(DECTRIS_EXAMPLES)/mx_parms.h $(CC) $(CFLAGS) $(NOLLFLAG) -I $(DECTRIS_EXAMPLES) $(WARNINGS) \ $(DECTRIS_EXAMPLES)/cbf_template_t.c -o $@ # # testcell example program # $(BIN)/testcell: $(LIB)/libcbf.a $(EXAMPLES)/testcell.C $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testcell.C -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # cif2c example program # $(BIN)/cif2c: $(LIB)/libcbf.a $(EXAMPLES)/cif2c.c $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cif2c.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # sauter_test example program # $(BIN)/sauter_test: $(LIB)/libcbf.a $(EXAMPLES)/sauter_test.C $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/sauter_test.C -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # sequence_match example program # $(BIN)/sequence_match: $(LIB)/libcbf.a $(EXAMPLES)/sequence_match.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/sequence_match.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # tiff2cbf example program # $(BIN)/tiff2cbf: $(LIB)/libcbf.a $(EXAMPLES)/tiff2cbf.c \ $(GOPTLIB) $(GOPTINC) $(TIFF) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ -I$(TIFFPREFIX)/include $(EXAMPLES)/tiff2cbf.c $(GOPTLIB) -L$(LIB) \ -lcbf -L$(TIFFPREFIX)/lib -ltiff $(EXTRALIBS) -limg -o $@ # # Andy Arvai's buffered read test program # $(BIN)/arvai_test: $(LIB)/libcbf.a $(EXAMPLES)/arvai_test.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/arvai_test.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # testreals example program # $(BIN)/testreals: $(LIB)/libcbf.a $(EXAMPLES)/testreals.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testreals.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testflat example program # $(BIN)/testflat: $(LIB)/libcbf.a $(EXAMPLES)/testflat.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testflat.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testflatpacked example program # $(BIN)/testflatpacked: $(LIB)/libcbf.a $(EXAMPLES)/testflatpacked.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testflatpacked.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ ifneq ($(F90C),) # # test_xds_binary example program # $(BIN)/test_xds_binary: $(LIB)/libfcb.a $(EXAMPLES)/test_xds_binary.f90 $(F90C) $(F90FLAGS) $(F90LDFLAGS) $(EXAMPLES)/test_xds_binary.f90 \ -L$(LIB) -lfcb -o $@ # # test_fcb_read_image example program # $(BIN)/test_fcb_read_image: $(LIB)/libfcb.a $(EXAMPLES)/test_fcb_read_image.f90 $(F90C) $(F90FLAGS) $(F90LDFLAGS) $(EXAMPLES)/test_fcb_read_image.f90 \ -L$(LIB) -lfcb -o $@ endif # # testcbf (C) # $(BIN)/ctestcbf: $(EXAMPLES)/testcbf.c $(LIB)/libcbf.a $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testcbf.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testcbf (Java) # $(BIN)/testcbf.class: $(EXAMPLES)/testcbf.java $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf_wrap.so $(JAVAC) -cp $(JCBF)/cbflib-$(VERSION).jar -d $(BIN) $(EXAMPLES)/testcbf.java # # Data files for tests # $(DATADIRI): (cd ..; $(DOWNLOAD) $(DATAURLI)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Input.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Input.tar.gz) $(DATADIRO): (cd ..; $(DOWNLOAD) $(DATAURLO)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Output.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Output.tar.gz) $(DATADIRS): (cd ..; $(DOWNLOAD) $(DATAURLS)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz) # Input Data Files TESTINPUT_BASIC = example.mar2300 DATADIRI_INPUT_BASIC = $(DATADIRI)/example.mar2300$(CEXT) TESTINPUT_EXTRA = 9ins.cif mb_LP_1_001.img insulin_pilatus6m.cbf testrealin.cbf \ testflatin.cbf testflatpackedin.cbf XRD1621.tif DATADIRI_INPUT_EXTRA = $(DATADIRI)/9ins.cif$(CEXT) $(DATADIRI)/mb_LP_1_001.img$(CEXT) \ $(DATADIRI)/insulin_pilatus6m.cbf$(CEXT) $(DATADIRI)/testrealin.cbf$(CEXT) \ $(DATADIRI)/testflatin.cbf$(CEXT) $(DATADIRI)/testflatpackedin.cbf$(CEXT) \ $(DATADIRI)/XRD1621.tif$(CEXT) # Output Data Files TESTOUTPUT = adscconverted_flat_orig.cbf \ adscconverted_orig.cbf converted_flat_orig.cbf converted_orig.cbf \ insulin_pilatus6mconverted_orig.cbf \ mb_LP_1_001_orig.cbf testcell_orig.prt \ test_xds_bin_testflatout_orig.out \ test_xds_bin_testflatpackedout_orig.out test_fcb_read_testflatout_orig.out \ test_fcb_read_testflatpackedout_orig.out \ XRD1621_orig.cbf XRD1621_I4encbC100_orig.cbf NEWTESTOUTPUT = adscconverted_flat.cbf \ adscconverted.cbf converted_flat.cbf converted.cbf \ insulin_pilatus6mconverted.cbf \ mb_LP_1_001.cbf testcell.prt \ test_xds_bin_testflatout.out \ test_xds_bin_testflatpackedout.out test_fcb_read_testflatout.out \ test_fcb_read_testflatpackedout.out \ XRD1621.cbf XRD1621_I4encbC100.cbf DATADIRO_OUTPUT = $(DATADIRO)/adscconverted_flat_orig.cbf$(CEXT) \ $(DATADIRO)/adscconverted_orig.cbf$(CEXT) \ $(DATADIRO)/converted_flat_orig.cbf$(CEXT) \ $(DATADIRO)/converted_orig.cbf$(CEXT) \ $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(CEXT) \ $(DATADIRO)/mb_LP_1_001_orig.cbf$(CEXT) \ $(DATADIRO)/testcell_orig.prt$(CEXT) \ $(DATADIRO)/test_xds_bin_testflatout_orig.out$(CEXT) \ $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(CEXT) \ $(DATADIRO)/test_fcb_read_testflatout_orig.out$(CEXT) \ $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(CEXT) \ $(DATADIRO)/XRD1621_orig.cbf$(CEXT) \ $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(CEXT) DATADIRO_OUTPUT_SIGNATURES = $(DATADIRO)/adscconverted_flat_orig.cbf$(SEXT) \ $(DATADIRO)/adscconverted_orig.cbf$(SEXT) \ $(DATADIRO)/converted_flat_orig.cbf$(SEXT) \ $(DATADIRO)/converted_orig.cbf$(SEXT) \ $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(SEXT) \ $(DATADIRO)/mb_LP_1_001_orig.cbf$(SEXT) \ $(DATADIRO)/testcell_orig.prt$(SEXT) \ $(DATADIRO)/test_xds_bin_testflatout_orig.out$(SEXT) \ $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(SEXT) \ $(DATADIRO)/test_fcb_read_testflatout_orig.out$(SEXT) \ $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(SEXT) \ $(DATADIRO)/XRD1621_orig.cbf$(SEXT) \ $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(SEXT) # Output Data File Signatures TESTOUTPUTSIGS = adscconverted_flat_orig.cbf$(SEXT) \ adscconverted_orig.cbf$(SEXT) converted_flat_orig.cbf$(SEXT) converted_orig.cbf$(SEXT) \ insulin_pilatus6mconverted_orig.cbf$(SEXT) \ mb_LP_1_001_orig.cbf$(SEXT) testcell_orig.prt$(SEXT) \ test_xds_bin_testflatout_orig.out$(SEXT) \ test_xds_bin_testflatpackedout_orig.out$(SEXT) test_fcb_read_testflatout_orig.out$(SEXT) \ test_fcb_read_testflatpackedout_orig.out$(SEXT) \ XRD1621_orig.cbf$(SEXT) DATADIRS_OUTPUT_SIGNATURES = $(DATADIRS)/adscconverted_flat_orig.cbf$(SEXT) \ $(DATADIRS)/adscconverted_orig.cbf$(SEXT) \ $(DATADIRS)/converted_flat_orig.cbf$(SEXT) \ $(DATADIRS)/converted_orig.cbf$(SEXT) \ $(DATADIRS)/insulin_pilatus6mconverted_orig.cbf$(SEXT) \ $(DATADIRS)/mb_LP_1_001_orig.cbf$(SEXT) \ $(DATADIRS)/testcell_orig.prt$(SEXT) \ $(DATADIRS)/test_xds_bin_testflatout_orig.out$(SEXT) \ $(DATADIRS)/test_xds_bin_testflatpackedout_orig.out$(SEXT) \ $(DATADIRS)/test_fcb_read_testflatout_orig.out$(SEXT) \ $(DATADIRS)/test_fcb_read_testflatpackedout_orig.out$(SEXT) \ $(DATADIRS)/XRD1621_orig.cbf$(SEXT) \ $(DATADIRS)/XRD1621_I4encbC100_orig.cbf$(SEXT) # Fetch Input Data Files $(TESTINPUT_BASIC): $(DATADIRI) $(DATADIRI_INPUT_BASIC) $(DECOMPRESS) < $(DATADIRI)/$@$(CEXT) > $@ cp $(DATADIRI)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) $(TESTINPUT_EXTRA): $(DATADIRI) $(DATADIRI_INPUT_EXTRA) $(DECOMPRESS) < $(DATADIRI)/$@$(CEXT) > $@ cp $(DATADIRI)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) # Fetch Output Data Files and Signatures $(TESTOUTPUT): $(DATADIRO) $(DATADIRO_OUTPUT) $(DATADIRO_OUTPUT_SIGNATURES) $(DECOMPRESS) < $(DATADIRO)/$@$(CEXT) > $@ cp $(DATADIRO)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) # Fetch Output Data File Signatures $(TESTOUTPUTSIGS): $(DATADIRS) $(DATADIRS_OUTPUT_SIGNATURES) cp $(DATADIRS)/$@ $@ # # Tests # tests: $(LIB) $(BIN) symlinksdone basic extra dectristests pycbftests tests_sigs_only: $(LIB) $(BIN) symlinksdone basic extra_sigs_only restore_output: $(NEWTESTOUTPUT) $(DATADIRO) $(SIGNATURE) < adscconverted_flat.cbf > $(DATADIRO)/adscconverted_flat_orig.cbf$(SEXT) $(SIGNATURE) < adscconverted.cbf > $(DATADIRO)/adscconverted_orig.cbf$(SEXT) $(SIGNATURE) < converted_flat.cbf > $(DATADIRO)/converted_flat_orig.cbf$(SEXT) $(SIGNATURE) < converted.cbf > $(DATADIRO)/converted_orig.cbf$(SEXT) $(SIGNATURE) < insulin_pilatus6mconverted.cbf > $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(SEXT) $(SIGNATURE) < mb_LP_1_001.cbf$ > $(DATADIRO)/mb_LP_1_001_orig.cbf$(SEXT) $(SIGNATURE) < testcell.prt > $(DATADIRO)/testcell_orig.prt$(SEXT) $(SIGNATURE) < test_xds_bin_testflatout.out > $(DATADIRO)/test_xds_bin_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_xds_bin_testflatpackedout.out > $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatout.out > $(DATADIRO)/test_fcb_read_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatpackedout.out > $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < XRD1621.cbf > $(DATADIRO)/XRD1621_orig.cbf$(SEXT) $(SIGNATURE) < XRD1621_I4encbC100.cbf > $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(SEXT) $(COMPRESS) < adscconverted_flat.cbf > $(DATADIRO)/adscconverted_flat_orig.cbf$(CEXT) $(COMPRESS) < adscconverted.cbf > $(DATADIRO)/adscconverted_orig.cbf$(CEXT) $(COMPRESS) < converted_flat.cbf > $(DATADIRO)/converted_flat_orig.cbf$(CEXT) $(COMPRESS) < converted.cbf > $(DATADIRO)/converted_orig.cbf$(CEXT) $(COMPRESS) < insulin_pilatus6mconverted.cbf > $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(CEXT) $(COMPRESS) < mb_LP_1_001.cbf$ > $(DATADIRO)/mb_LP_1_001_orig.cbf$(CEXT) $(COMPRESS) < testcell.prt > $(DATADIRO)/testcell_orig.prt$(CEXT) $(COMPRESS) < test_xds_bin_testflatout.out > $(DATADIRO)/test_xds_bin_testflatout_orig.out$(CEXT) $(COMPRESS) < test_xds_bin_testflatpackedout.out > $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(CEXT) $(COMPRESS) < test_fcb_read_testflatout.out > $(DATADIRO)/test_fcb_read_testflatout_orig.out$(CEXT) $(COMPRESS) < test_fcb_read_testflatpackedout.out > $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(CEXT) $(COMPRESS) < XRD1621.cbf > $(DATADIRO)/XRD1621_orig.cbf$(CEXT) $(COMPRESS) < XRD1621_I4encbC100.cbf > $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(CEXT) restore_sigs_only: $(NEWTESTOUTPUT) $(DATADIRS) $(SIGNATURE) < adscconverted_flat.cbf > $(DATADIRS)/adscconverted_flat_orig.cbf$(SEXT) $(SIGNATURE) < adscconverted.cbf > $(DATADIRS)/adscconverted_orig.cbf$(SEXT) $(SIGNATURE) < converted_flat.cbf > $(DATADIRS)/converted_flat_orig.cbf$(SEXT) $(SIGNATURE) < converted.cbf > $(DATADIRS)/converted_orig.cbf$(SEXT) $(SIGNATURE) < insulin_pilatus6mconverted.cbf > $(DATADIRS)/insulin_pilatus6mconverted_orig.cbf$(SEXT) $(SIGNATURE) < mb_LP_1_001.cbf$ > $(DATADIRS)/mb_LP_1_001_orig.cbf$(SEXT) $(SIGNATURE) < testcell.prt > $(DATADIRS)/testcell_orig.prt$(SEXT) $(SIGNATURE) < test_xds_bin_testflatout.out > $(DATADIRS)/test_xds_bin_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_xds_bin_testflatpackedout.out > $(DATADIRS)/test_xds_bin_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatout.out > $(DATADIRS)/test_fcb_read_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatpackedout.out > $(DATADIRS)/test_fcb_read_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < XRD1621.cbf > $(DATADIRS)/XRD1621_orig.cbf$(SEXT) $(SIGNATURE) < XRD1621_I4encbC100.cbf > $(DATADIRS)/XRD1621_I4encbC100_orig.cbf$(SEXT) restore_signatures: restore_output restore_sigs_only # # Basic Tests # basic: $(BIN)/makecbf $(BIN)/img2cif $(BIN)/cif2cbf $(TESTINPUT_BASIC) $(BIN)/makecbf example.mar2300 makecbf.cbf $(BIN)/img2cif -c flatpacked -m headers -d digest \ -e base64 example.mar2300 img2cif_packed.cif $(BIN)/img2cif -c canonical -m headers -d digest \ -e base64 example.mar2300 img2cif_canonical.cif $(BIN)/img2cif -c flatpacked -m headers -d digest \ -e none example.mar2300 img2cif_packed.cbf $(BIN)/img2cif -c canonical -m headers -d digest \ -e none example.mar2300 img2cif_canonical.cbf $(BIN)/cif2cbf -e none -c flatpacked \ img2cif_canonical.cif cif2cbf_packed.cbf $(BIN)/cif2cbf -e none -c canonical \ img2cif_packed.cif cif2cbf_canonical.cbf -cmp cif2cbf_packed.cbf makecbf.cbf -cmp cif2cbf_packed.cbf img2cif_packed.cbf -cmp cif2cbf_canonical.cbf img2cif_canonical.cbf # # Extra Tests # ifneq ($(F90C),) extra: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/test_xds_binary $(BIN)/test_fcb_read_image $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg \ $(BIN)/changtestcompression $(BIN)/tiff2cbf \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUT) else extra: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUT) endif $(TIME) $(BIN)/cif2cbf -e hex -c none \ makecbf.cbf cif2cbf_ehcn.cif $(TIME) $(BIN)/cif2cbf -e none -c flatpacked \ cif2cbf_ehcn.cif cif2cbf_encp.cbf; rm cif2cbf_ehcn.cif -cmp makecbf.cbf cif2cbf_encp.cbf $(TIME) $(BIN)/cif2cbf -i 9ins.cif -o 9ins.cbf -cmp 9ins.cif 9ins.cbf $(TIME) $(BIN)/convert_image -F example.mar2300 converted_flat.cbf -cmp converted_flat.cbf converted_flat_orig.cbf $(TIME) $(BIN)/convert_image example.mar2300 converted.cbf -cmp converted.cbf converted_orig.cbf -$(TIME) $(BIN)/testcell < testcell.dat > testcell.prt -cmp testcell.prt testcell_orig.prt $(TIME) $(BIN)/convert_image -F -d adscquantum315 mb_LP_1_001.img adscconverted_flat.cbf -cmp adscconverted_flat.cbf adscconverted_flat_orig.cbf $(TIME) $(BIN)/convert_image -d adscquantum315 mb_LP_1_001.img adscconverted.cbf -cmp adscconverted.cbf adscconverted_orig.cbf $(TIME) $(BIN)/adscimg2cbf --no_pad --cbf_packed,flat mb_LP_1_001.img -cmp mb_LP_1_001.cbf mb_LP_1_001_orig.cbf ifneq ($(CLEANTESTS),) mv mb_LP_1_001.cbf nmb_LP_1_001.cbf else cp mb_LP_1_001.cbf nmb_LP_1_001.cbf endif $(TIME) $(BIN)/cbf2adscimg nmb_LP_1_001.cbf -cmp nmb_LP_1_001.img mb_LP_1_001.img rm nmb_LP_1_001.cbf ifneq ($(CLEANTESTS),) rm nmb_LP_1_001.img endif $(TIME) $(BIN)/convert_minicbf -d pilatus6m insulin_pilatus6m.cbf insulin_pilatus6mconverted.cbf -cmp insulin_pilatus6mconverted.cbf insulin_pilatus6mconverted_orig.cbf $(TIME) $(BIN)/testreals -cmp testrealin.cbf testrealout.cbf $(TIME) $(BIN)/testflat -cmp testflatin.cbf testflatout.cbf $(TIME) $(BIN)/testflatpacked -cmp testflatpackedin.cbf testflatpackedout.cbf ifneq ($(F90C),) echo testflatout.cbf | $(TIME) $(BIN)/test_xds_binary > test_xds_bin_testflatout.out -$(DIFF) test_xds_bin_testflatout.out test_xds_bin_testflatout_orig.out echo testflatpackedout.cbf | $(TIME) $(BIN)/test_xds_binary > test_xds_bin_testflatpackedout.out -$(DIFF) test_xds_bin_testflatpackedout.out test_xds_bin_testflatpackedout_orig.out echo testflatout.cbf | $(TIME) $(BIN)/test_fcb_read_image > test_fcb_read_testflatout.out -$(DIFF) test_fcb_read_testflatout.out test_fcb_read_testflatout_orig.out echo testflatpackedout.cbf | $(TIME) $(BIN)/test_fcb_read_image > test_fcb_read_testflatpackedout.out -$(DIFF) test_fcb_read_testflatpackedout.out test_fcb_read_testflatpackedout_orig.out endif $(TIME) $(BIN)/sauter_test $(TIME) $(BIN)/changtestcompression $(TIME) (export LD_LIBRARY_PATH=$(LIB);$(BIN)/tiff2cbf XRD1621.tif XRD1621.cbf) -$(DIFF) XRD1621.cbf XRD1621_orig.cbf $(TIME) $(BIN)/cif2cbf -I 4 -C 100. -L 0. -e n -c b -i XRD1621.cbf -o XRD1621_I4encbC100.cbf -$(DIFF) XRD1621_I4encbC100.cbf XRD1621_I4encbC100_orig.cbf ifneq ($(F90C),) extra_sigs_only: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/test_xds_binary $(BIN)/test_fcb_read_image $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg $(BIN)/tiff2cbf \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) else extra_sigs_only: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf\ basic $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) endif $(TIME) $(BIN)/cif2cbf -e hex -c none \ makecbf.cbf cif2cbf_ehcn.cif $(TIME) $(BIN)/cif2cbf -e none -c packed \ cif2cbf_ehcn.cif cif2cbf_encp.cbf; rm cif2cbf_ehcn.cif -cmp makecbf.cbf cif2cbf_encp.cbf $(TIME) $(BIN)/cif2cbf -i 9ins.cif -o 9ins.cbf -cmp 9ins.cif 9ins.cbf $(TIME) $(BIN)/convert_image -F example.mar2300 converted_flat.cbf -$(SIGNATURE) < converted_flat.cbf | $(DIFF) - converted_flat_orig.cbf$(SEXT); rm converted_flat.cbf $(TIME) $(BIN)/convert_image example.mar2300 converted.cbf -$(SIGNATURE) < converted.cbf | $(DIFF) - converted_orig.cbf$(SEXT); rm converted.cbf -$(TIME) $(BIN)/testcell < testcell.dat | \ $(SIGNATURE) | $(DIFF) - testcell_orig.prt$(SEXT) $(TIME) $(BIN)/convert_image -F -d adscquantum315 mb_LP_1_001.img adscconverted_flat.cbf -$(SIGNATURE) < adscconverted_flat.cbf | $(DIFF) - adscconverted_flat_orig.cbf$(SEXT) $(TIME) $(BIN)/convert_image -d adscquantum315 mb_LP_1_001.img adscconverted.cbf -$(SIGNATURE) < adscconverted.cbf | $(DIFF) - adscconverted_orig.cbf$(SEXT); rm adscconverted.cbf $(TIME) $(BIN)/adscimg2cbf --cbf_packed,flat mb_LP_1_001.img -$(SIGNATURE) < mb_LP_1_001.cbf | $(DIFF) - mb_LP_1_001_orig.cbf$(SEXT) mv mb_LP_1_001.cbf nmb_LP_1_001.cbf $(TIME) $(BIN)/cbf2adscimg nmb_LP_1_001.cbf -cmp nmb_LP_1_001.img mb_LP_1_001.img rm nmb_LP_1_001.cbf rm nmb_LP_1_001.img $(TIME) $(BIN)/convert_minicbf -d pilatus6m insulin_pilatus6m.cbf insulin_pilatus6mconverted.cbf -$(SIGNATURE) < insulin_pilatus6mconverted.cbf | $(DIFF) - insulin_pilatus6mconverted_orig.cbf$(SEXT); rm insulin_pilatus6mconverted.cbf $(TIME) $(BIN)/testreals -cmp testrealin.cbf testrealout.cbf $(TIME) $(BIN)/testflat -cmp testflatin.cbf testflatout.cbf $(TIME) $(BIN)/testflatpacked -cmp testflatpackedin.cbf testflatpackedout.cbf ifneq ($(F90C),) echo testflatout.cbf | $(TIME) $(BIN)/test_xds_binary | \ $(SIGNATURE) | $(DIFF) - test_xds_bin_testflatout_orig.out$(SEXT) echo testflatpackedout.cbf | $(TIME) $(BIN)/test_xds_binary | \ $(SIGNATURE) | $(DIFF) - test_xds_bin_testflatpackedout_orig.out$(SEXT) echo testflatout.cbf | $(TIME) $(BIN)/test_fcb_read_image | \ $(SIGNATURE) | $(DIFF) - test_fcb_read_testflatout_orig.out$(SEXT) echo testflatpackedout.cbf | $(TIME) $(BIN)/test_fcb_read_image | \ $(SIGNATURE) | $(DIFF) - test_fcb_read_testflatpackedout_orig.out$(SEXT) endif $(TIME) $(BIN)/sauter_test $(TIME) $(BIN)/tiff2cbf XRD1621.tif XRD1621.cbf $(TIME) $(BIN)/cif2cbf -I 4 -C 100. -L 0. -e n -c b -i XRD1621.cbf -o XRD1621_I4encbC100.cbf -$(SIGNATURE) < XRD1621.cbf | $(DIFF) - XRD1621_orig.cbf$(SEXT); rm XRD1621.cbf -$(SIGNATURE) < XRD1621_I4encbC100.cbf | $(DIFF) - XRD1621_I4encbC100_orig.cbf$(SEXT); rm XRD1621_I4encbC100.cbf @-rm -f adscconverted_flat.cbf @-rm -f $(TESTINPUT_BASIC) $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) @-rm -f cif2cbf_packed.cbf makecbf.cbf \ cif2cbf_packed.cbf img2cif_packed.cbf \ cif2cbf_canonical.cbf img2cif_canonical.cbf @-rm -f testrealout.cbf testflatout.cbf testflatpackedout.cbf \ cif2cbf_encp.cbf img2cif_canonical.cif img2cif_packed.cif 9ins.cbf pycbftests: $(PYCBF)/_pycbf.$(PYCBFEXT) (cd $(PYCBF); python pycbf_test1.py) (cd $(PYCBF); python pycbf_test2.py) (cd $(PYCBF); python pycbf_test3.py) javatests: $(BIN)/ctestcbf $(BIN)/testcbf.class $(SOLIB)/libcbf_wrap.so $(BIN)/ctestcbf > testcbfc.txt $(LDPREFIX) java -cp $(JCBF)/cbflib-$(VERSION).jar:$(BIN) testcbf > testcbfj.txt $(DIFF) testcbfc.txt testcbfj.txt dectristests: $(BIN)/cbf_template_t $(DECTRIS_EXAMPLES)/cbf_test_orig.out (cd $(DECTRIS_EXAMPLES); ../../bin/cbf_template_t; diff -a -u cbf_test_orig.out cbf_template_t.out) # # Remove all non-source files # empty: @-rm -f $(LIB)/*.o @-rm -f $(LIB)/libcbf.a @-rm -f $(LIB)/libfcb.a @-rm -f $(LIB)/libimg.a @-rm -f $(LIB)/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/build/*/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/build/src/cbf_simple.o @-rm -f $(PYCBF)/build/*/pycbf_wrap.o @-rm -rf $(BIN)/adscimg2cbf* @-rm -rf $(BIN)/cbf2adscimg* @-rm -rf $(BIN)/makecbf* @-rm -rf $(BIN)/img2cif* @-rm -rf $(BIN)/cif2cbf* @-rm -rf $(BIN)/convert_image* @-rm -rf $(BIN)/convert_minicbf* @-rm -rf $(BIN)/test_fcb_read_image* @-rm -rf $(BIN)/test_xds_binary* @-rm -rf $(BIN)/testcell* @-rm -rf $(BIN)/cif2c* @-rm -rf $(BIN)/testreals* @-rm -rf $(BIN)/testflat* @-rm -rf $(BIN)/testflatpacked* @-rm -rf $(BIN)/cbf_template_t* @-rm -rf $(BIN)/sauter_test* @-rm -rf $(BIN)/arvai_test* @-rm -rf $(BIN)/changtestcompression* @-rm -rf $(BIN)/tiff2cbf* @-rm -f makecbf.cbf @-rm -f img2cif_packed.cif @-rm -f img2cif_canonical.cif @-rm -f img2cif_packed.cbf @-rm -f img2cif_canonical.cbf @-rm -f img2cif_raw.cbf @-rm -f cif2cbf_packed.cbf @-rm -f cif2cbf_canonical.cbf @-rm -f converted.cbf @-rm -f adscconverted.cbf @-rm -f converted_flat.cbf @-rm -f adscconverted_flat.cbf @-rm -f adscconverted_flat_rev.cbf @-rm -f mb_LP_1_001.cbf @-rm -f cif2cbf_ehcn.cif @-rm -f cif2cbf_encp.cbf @-rm -f 9ins.cbf @-rm -f 9ins.cif @-rm -f testcell.prt @-rm -f example.mar2300 @-rm -f converted_orig.cbf @-rm -f adscconverted_orig.cbf @-rm -f converted_flat_orig.cbf @-rm -f adscconverted_flat_orig.cbf @-rm -f adscconverted_flat_rev_orig.cbf @-rm -f mb_LP_1_001_orig.cbf @-rm -f insulin_pilatus6mconverted_orig.cbf @-rm -f insulin_pilatus6mconverted.cbf @-rm -f insulin_pilatus6m.cbf @-rm -f testrealin.cbf @-rm -f testrealout.cbf @-rm -f testflatin.cbf @-rm -f testflatout.cbf @-rm -f testflatpackedin.cbf @-rm -f testflatpackedout.cbf @-rm -f CTC.cbf @-rm -f test_fcb_read_testflatout.out @-rm -f test_fcb_read_testflatpackedout.out @-rm -f test_xds_bin_testflatpackedout.out @-rm -f test_xds_bin_testflatout.out @-rm -f test_fcb_read_testflatout_orig.out @-rm -f test_fcb_read_testflatpackedout_orig.out @-rm -f test_xds_bin_testflatpackedout_orig.out @-rm -f test_xds_bin_testflatout_orig.out @-rm -f mb_LP_1_001.img @-rm -f 9ins.cif @-rm -f testcell_orig.prt @-rm -f $(DECTRIS_EXAMPLES)/cbf_template_t.out @-rm -f XRD1621.cbf @-rm -f XRD1621_orig.cbf @-rm -f XRD1621_orig.cbf @-rm -f XRD1621_I4encbC100.cbf @-rm -f $(SRC)/fcb_exit_binary.f90 @-rm -f $(SRC)/fcb_next_binary.f90 @-rm -f $(SRC)/fcb_open_cifin.f90 @-rm -f $(SRC)/fcb_packed.f90 @-rm -f $(SRC)/fcb_read_bits.f90 @-rm -f $(SRC)/fcb_read_image.f90 @-rm -f $(SRC)/fcb_read_xds_i2.f90 @-rm -f $(EXAMPLES)/test_fcb_read_image.f90 @-rm -f $(EXAMPLES)/test_xds_binary.f90 @-rm -f symlinksdone @-rm -f $(TESTOUTPUT) *$(SEXT) @-rm -f $(SOLIB)/*.o @-rm -f $(SOLIB)/libcbf_wrap.so @-rm -f $(SOLIB)/libjcbf.so @-rm -f $(SOLIB)/libimg.so @-rm -f $(SOLIB)/libfcb.so @-rm -rf $(JCBF)/org @-rm -f $(JCBF)/*.java @-rm -f $(JCBF)/jcbf_wrap.c @-rm -f $(SRC)/cbf_wrap.c @-rm -f $(BIN)/ctestcbf $(BIN)/testcbf.class testcbfc.txt testcbfj.txt @-rm -rf $(REGEX) @-rm -rf $(TIFF) ./.undosymlinks # # Remove temporary files # clean: @-rm -f core @-rm -f *.o @-rm -f *.u # # Restore to distribution state # distclean: clean empty # # Create a Tape Archive for distribution # tar: $(DOCUMENTS) $(SOURCE) $(SRC)/cbf.stx $(HEADERS) $(M4FILES)\ $(EXAMPLES) \ README.html README Makefile \ $(JPEGS) -/bin/rm -f CBFlib.tar* tar cvBf CBFlib.tar \ $(DOCUMENTS) $(SOURCE) $(SRC)/cbf.stx $(HEADERS) $(M4FILES)\ $(EXAMPLES) \ README.html README Makefile \ $(JPEGS) gzip --best CBFlib.tar ./CBFlib-0.9.2.2/Makefile_OSX0000644000076500007650000017777211603702122014012 0ustar yayayaya ###################################################################### # Makefile - command file for make to create CBFlib # # # # Version 0.9.2 12 Feb 2011 # # # # Paul Ellis and # # Herbert J. Bernstein (yaya@bernstein-plus-sons.com) # # # # (C) Copyright 2006 - 2011 Herbert J. Bernstein # # # ###################################################################### ###################################################################### # # # YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL # # # # ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS # # OF THE LGPL # # # ###################################################################### ########################### GPL NOTICES ############################## # # # This program is free software; you can redistribute it and/or # # modify it under the terms of the GNU General Public License as # # published by the Free Software Foundation; either version 2 of # # (the License, or (at your option) any later version. # # # # This program is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # # GNU General Public License for more details. # # # # You should have received a copy of the GNU General Public License # # along with this program; if not, write to the Free Software # # Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA # # 02111-1307 USA # # # ###################################################################### ######################### LGPL NOTICES ############################### # # # This library is free software; you can redistribute it and/or # # modify it under the terms of the GNU Lesser General Public # # License as published by the Free Software Foundation; either # # version 2.1 of the License, or (at your option) any later version. # # # # This library is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # # Lesser General Public License for more details. # # # # You should have received a copy of the GNU Lesser General Public # # License along with this library; if not, write to the Free # # Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, # # MA 02110-1301 USA # # # ###################################################################### ###################################################################### # # # Stanford University Notices # # for the CBFlib software package that incorporates SLAC software # # on which copyright is disclaimed # # # # This software # # ------------- # # The term "this software", as used in these Notices, refers to # # those portions of the software package CBFlib that were created by # # employees of the Stanford Linear Accelerator Center, Stanford # # University. # # # # Stanford disclaimer of copyright # # -------------------------------- # # Stanford University, owner of the copyright, hereby disclaims its # # copyright and all other rights in this software. Hence, anyone # # may freely use it for any purpose without restriction. # # # # Acknowledgement of sponsorship # # ------------------------------ # # This software was produced by the Stanford Linear Accelerator # # Center, Stanford University, under Contract DE-AC03-76SFO0515 with # # the Department of Energy. # # # # Government disclaimer of liability # # ---------------------------------- # # Neither the United States nor the United States Department of # # Energy, nor any of their employees, makes any warranty, express or # # implied, or assumes any legal liability or responsibility for the # # accuracy, completeness, or usefulness of any data, apparatus, # # product, or process disclosed, or represents that its use would # # not infringe privately owned rights. # # # # Stanford disclaimer of liability # # -------------------------------- # # Stanford University makes no representations or warranties, # # express or implied, nor assumes any liability for the use of this # # software. # # # # Maintenance of notices # # ---------------------- # # In the interest of clarity regarding the origin and status of this # # software, this and all the preceding Stanford University notices # # are to remain affixed to any copy or derivative of this software # # made or distributed by the recipient and are to be affixed to any # # copy of software made or distributed by the recipient that # # contains a copy or derivative of this software. # # # # Based on SLAC Software Notices, Set 4 # # OTT.002a, 2004 FEB 03 # ###################################################################### ###################################################################### # NOTICE # # Creative endeavors depend on the lively exchange of ideas. There # # are laws and customs which establish rights and responsibilities # # for authors and the users of what authors create. This notice # # is not intended to prevent you from using the software and # # documents in this package, but to ensure that there are no # # misunderstandings about terms and conditions of such use. # # # # Please read the following notice carefully. If you do not # # understand any portion of this notice, please seek appropriate # # professional legal advice before making use of the software and # # documents included in this software package. In addition to # # whatever other steps you may be obliged to take to respect the # # intellectual property rights of the various parties involved, if # # you do make use of the software and documents in this package, # # please give credit where credit is due by citing this package, # # its authors and the URL or other source from which you obtained # # it, or equivalent primary references in the literature with the # # same authors. # # # # Some of the software and documents included within this software # # package are the intellectual property of various parties, and # # placement in this package does not in any way imply that any # # such rights have in any way been waived or diminished. # # # # With respect to any software or documents for which a copyright # # exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. # # # # Even though the authors of the various documents and software # # found here have made a good faith effort to ensure that the # # documents are correct and that the software performs according # # to its documentation, and we would greatly appreciate hearing of # # any problems you may encounter, the programs and documents any # # files created by the programs are provided **AS IS** without any * # warranty as to correctness, merchantability or fitness for any # # particular or general use. # # # # THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF # # PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE # # PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS # # OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE # # PROGRAMS OR DOCUMENTS. # ###################################################################### ###################################################################### # # # The IUCr Policy # # for the Protection and the Promotion of the STAR File and # # CIF Standards for Exchanging and Archiving Electronic Data # # # # Overview # # # # The Crystallographic Information File (CIF)[1] is a standard for # # information interchange promulgated by the International Union of # # Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the # # recommended method for submitting publications to Acta # # Crystallographica Section C and reports of crystal structure # # determinations to other sections of Acta Crystallographica # # and many other journals. The syntax of a CIF is a subset of the # # more general STAR File[2] format. The CIF and STAR File approaches # # are used increasingly in the structural sciences for data exchange # # and archiving, and are having a significant influence on these # # activities in other fields. # # # # Statement of intent # # # # The IUCr's interest in the STAR File is as a general data # # interchange standard for science, and its interest in the CIF, # # a conformant derivative of the STAR File, is as a concise data # # exchange and archival standard for crystallography and structural # # science. # # # # Protection of the standards # # # # To protect the STAR File and the CIF as standards for # # interchanging and archiving electronic data, the IUCr, on behalf # # of the scientific community, # # # # # holds the copyrights on the standards themselves, * # # # # owns the associated trademarks and service marks, and * # # # # holds a patent on the STAR File. * # # # These intellectual property rights relate solely to the # # interchange formats, not to the data contained therein, nor to # # the software used in the generation, access or manipulation of # # the data. # # # # Promotion of the standards # # # # The sole requirement that the IUCr, in its protective role, # # imposes on software purporting to process STAR File or CIF data # # is that the following conditions be met prior to sale or # # distribution. # # # # # Software claiming to read files written to either the STAR * # File or the CIF standard must be able to extract the pertinent # # data from a file conformant to the STAR File syntax, or the CIF # # syntax, respectively. # # # # # Software claiming to write files in either the STAR File, or * # the CIF, standard must produce files that are conformant to the # # STAR File syntax, or the CIF syntax, respectively. # # # # # Software claiming to read definitions from a specific data * # dictionary approved by the IUCr must be able to extract any # # pertinent definition which is conformant to the dictionary # # definition language (DDL)[3] associated with that dictionary. # # # # The IUCr, through its Committee on CIF Standards, will assist # # any developer to verify that software meets these conformance # # conditions. # # # # Glossary of terms # # # # [1] CIF: is a data file conformant to the file syntax defined # # at http://www.iucr.org/iucr-top/cif/spec/index.html # # # # [2] STAR File: is a data file conformant to the file syntax # # defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html # # # # [3] DDL: is a language used in a data dictionary to define data # # items in terms of "attributes". Dictionaries currently approved # # by the IUCr, and the DDL versions used to construct these # # dictionaries, are listed at # # http://www.iucr.org/iucr-top/cif/spec/ddl/index.html # # # # Last modified: 30 September 2000 # # # # IUCr Policy Copyright (C) 2000 International Union of # # Crystallography # ###################################################################### # Version string VERSION = 0.9.2 # # Comment out the next line if scratch test files sould be retain # CLEANTESTS = yes # # Definition to get a version of tifflib to support tiff2cbf # TIFF = tiff-3.9.4-rev-6Feb11 TIFFPREFIX = $(PWD) # # Definitions to get a stable version of regex # REGEX = regex-20090805 REGEXDIR = /usr/lib REGEXDEP = # Program to use to retrieve a URL DOWNLOAD = wget # Flag to control symlinks versus copying SLFLAGS = --use_ln # # Program to use to pack shars # SHAR = /usr/bin/shar #SHAR = /usr/local/bin/gshar # # Program to use to create archives # AR = /usr/bin/ar # # Program to use to add an index to an archive # RANLIB = /usr/bin/ranlib # # Program to use to decompress a data file # DECOMPRESS = /usr/bin/bunzip2 # # Program to use to compress a data file # COMPRESS = /usr/bin/bzip2 # # Program to use to generate a signature # SIGNATURE = /usr/bin/openssl dgst -md5 # # Extension for compressed data file (with period) # CEXT = .bz2 # # Extension for signatures of files # SEXT = .md5 # call to time a command #TIME = #TIME = time # # Program to display differences between files # DIFF = diff -u -b # # Program to generate wrapper classes for Python # PYSWIG = swig -python # # Program to generate wrapper classes for Java # JSWIG = swig -java # # Program to generate LaTex and HTML program documentation # NUWEB = nuweb # # Compiler for Java # JAVAC = javac # # Java archiver for compiled classes # JAR = jar # # Java SDK root directory # ifeq ($(JDKDIR),) JDKDIR = /usr/lib/java endif ifneq ($(CBF_DONT_USE_LONG_LONG),) NOLLFLAG = -DCBF_DONT_USE_LONG_LONG else NOLLFLAG = endif # # PYCBF definitions # PYCBFEXT = so PYCBFBOPT = SETUP_PY = setup.py # # Set the compiler and flags # ######################################################### # # Appropriate compiler definitions for MAC OS X # Also change defintion of DOWNLOAD # ######################################################### CC = gcc C++ = g++ CFLAGS = -g -O2 -Wall -ansi -pedantic F90C = gfortran F90FLAGS = -g -fno-range-check F90LDFLAGS = -bind_at_load EXTRALIBS = -lm M4FLAGS = -Dfcb_bytes_in_rec=131072 TIME = time DOWNLOAD = /sw/bin/wget ifneq ($(NOFORTRAN),) F90C = endif # # Directories # ROOT = . LIB = $(ROOT)/lib SOLIB = $(ROOT)/solib JCBF = $(ROOT)/jcbf JAVADIR = $(ROOT)/java BIN = $(ROOT)/bin SRC = $(ROOT)/src INCLUDE = $(ROOT)/include M4 = $(ROOT)/m4 PYCBF = $(ROOT)/pycbf EXAMPLES = $(ROOT)/examples DECTRIS_EXAMPLES = $(EXAMPLES)/dectris_cbf_template_test DOC = $(ROOT)/doc GRAPHICS = $(ROOT)/html_graphics DATADIRI = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Input DATADIRO = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Output DATADIRS = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only INSTALLDIR = $(HOME) # # URLs from which to retrieve the data directories # DATAURLBASE = http://downloads.sf.net/cbflib/ DATAURLI = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Input.tar.gz DATAURLO = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Output.tar.gz DATAURLS = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz # # URLs from which to retrieve needed external package snapshots # REGEXURL = http://downloads.sf.net/cbflib/$(REGEX).tar.gz TIFFURL = http://downloads.sf.net/cbflib/$(TIFF).tar.gz # # Include directories # INCLUDES = -I$(INCLUDE) -I$(SRC) ###################################################################### # You should not need to make modifications below this line # ###################################################################### # # Suffixes of files to be used or built # .SUFFIXES: .c .o .f90 .m4 .m4.f90: m4 -P $(M4FLAGS) $< > $@ ifneq ($(F90C),) .f90.o: $(F90C) $(F90FLAGS) -c $< -o $@ endif # # Common dependencies # COMMONDEP = Makefile # # Source files # SOURCE = $(SRC)/cbf.c \ $(SRC)/cbf_alloc.c \ $(SRC)/cbf_ascii.c \ $(SRC)/cbf_binary.c \ $(SRC)/cbf_byte_offset.c \ $(SRC)/cbf_canonical.c \ $(SRC)/cbf_codes.c \ $(SRC)/cbf_compress.c \ $(SRC)/cbf_context.c \ $(SRC)/cbf_copy.c \ $(SRC)/cbf_file.c \ $(SRC)/cbf_getopt.c \ $(SRC)/cbf_lex.c \ $(SRC)/cbf_packed.c \ $(SRC)/cbf_predictor.c \ $(SRC)/cbf_read_binary.c \ $(SRC)/cbf_read_mime.c \ $(SRC)/cbf_simple.c \ $(SRC)/cbf_string.c \ $(SRC)/cbf_stx.c \ $(SRC)/cbf_tree.c \ $(SRC)/cbf_uncompressed.c \ $(SRC)/cbf_write.c \ $(SRC)/cbf_write_binary.c \ $(SRC)/cbf_ws.c \ $(SRC)/md5c.c F90SOURCE = $(SRC)/fcb_atol_wcnt.f90 \ $(SRC)/fcb_ci_strncmparr.f90 \ $(SRC)/fcb_exit_binary.f90 \ $(SRC)/fcb_nblen_array.f90 \ $(SRC)/fcb_next_binary.f90 \ $(SRC)/fcb_open_cifin.f90 \ $(SRC)/fcb_packed.f90 \ $(SRC)/fcb_read_bits.f90 \ $(SRC)/fcb_read_byte.f90 \ $(SRC)/fcb_read_image.f90 \ $(SRC)/fcb_read_line.f90 \ $(SRC)/fcb_read_xds_i2.f90 \ $(SRC)/fcb_skip_whitespace.f90 \ $(EXAMPLES)/test_fcb_read_image.f90 \ $(EXAMPLES)/test_xds_binary.f90 # # Header files # HEADERS = $(INCLUDE)/cbf.h \ $(INCLUDE)/cbf_alloc.h \ $(INCLUDE)/cbf_ascii.h \ $(INCLUDE)/cbf_binary.h \ $(INCLUDE)/cbf_byte_offset.h \ $(INCLUDE)/cbf_canonical.h \ $(INCLUDE)/cbf_codes.h \ $(INCLUDE)/cbf_compress.h \ $(INCLUDE)/cbf_context.h \ $(INCLUDE)/cbf_copy.h \ $(INCLUDE)/cbf_file.h \ $(INCLUDE)/cbf_getopt.h \ $(INCLUDE)/cbf_lex.h \ $(INCLUDE)/cbf_packed.h \ $(INCLUDE)/cbf_predictor.h \ $(INCLUDE)/cbf_read_binary.h \ $(INCLUDE)/cbf_read_mime.h \ $(INCLUDE)/cbf_simple.h \ $(INCLUDE)/cbf_string.h \ $(INCLUDE)/cbf_stx.h \ $(INCLUDE)/cbf_tree.h \ $(INCLUDE)/cbf_uncompressed.h \ $(INCLUDE)/cbf_write.h \ $(INCLUDE)/cbf_write_binary.h \ $(INCLUDE)/cbf_ws.h \ $(INCLUDE)/global.h \ $(INCLUDE)/cbff.h \ $(INCLUDE)/md5.h # # m4 macro files # M4FILES = $(M4)/fcblib_defines.m4 \ $(M4)/fcb_exit_binary.m4 \ $(M4)/fcb_next_binary.m4 \ $(M4)/fcb_open_cifin.m4 \ $(M4)/fcb_packed.m4 \ $(M4)/fcb_read_bits.m4 \ $(M4)/fcb_read_image.m4 \ $(M4)/fcb_read_xds_i2.m4 \ $(M4)/test_fcb_read_image.m4 \ $(M4)/test_xds_binary.m4 # # Documentation files # DOCUMENTS = $(DOC)/CBFlib.html \ $(DOC)/CBFlib.txt \ $(DOC)/CBFlib_NOTICES.html \ $(DOC)/CBFlib_NOTICES.txt \ $(DOC)/ChangeLog \ $(DOC)/ChangeLog.html \ $(DOC)/MANIFEST \ $(DOC)/gpl.txt $(DOC)/lgpl.txt # # HTML Graphics files # JPEGS = $(GRAPHICS)/CBFbackground.jpg \ $(GRAPHICS)/CBFbig.jpg \ $(GRAPHICS)/CBFbutton.jpg \ $(GRAPHICS)/cbflibbackground.jpg \ $(GRAPHICS)/cbflibbig.jpg \ $(GRAPHICS)/cbflibbutton.jpg \ $(GRAPHICS)/cifhome.jpg \ $(GRAPHICS)/iucrhome.jpg \ $(GRAPHICS)/noticeButton.jpg # # Default: instructions # default: @echo ' ' @echo '***************************************************************' @echo ' ' @echo ' PLEASE READ README and doc/CBFlib_NOTICES.txt' @echo ' ' @echo ' Before making the CBF library and example programs, check' @echo ' that the C compiler name and flags are correct:' @echo ' ' @echo ' The current values are:' @echo ' ' @echo ' $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG)' @echo ' ' @echo ' Before installing the CBF library and example programs, check' @echo ' that the install directory is correct:' @echo ' ' @echo ' The current value :' @echo ' ' @echo ' $(INSTALLDIR) ' @echo ' ' @echo ' To compile the CBF library and example programs type:' @echo ' ' @echo ' make clean' @echo ' make all' @echo ' ' @echo ' To compile the CBF library as a shared object library, type:' @echo ' ' @echo ' make shared' @echo ' ' @echo ' To compile the Java wrapper classes for CBF library, type:' @echo ' ' @echo ' make javawrapper' @echo ' ' @echo ' To run a set of tests type:' @echo ' ' @echo ' make tests' @echo ' ' @echo ' To run some java tests type:' @echo ' ' @echo ' make javatests' @echo ' ' @echo ' The tests assume that several data files are in the directories' @echo ' $(DATADIRI) and $(DATADIRO)' @echo ' ' @echo ' Alternatively tests can be run comparing MD5 signatures only by' @echo ' ' @echo ' make tests_sigs_only' @echo ' ' @echo ' These signature only tests save space and download time by' @echo ' assuming that input data files and the output signatures' @echo ' are in the directories' @echo ' $(DATADIRI) and $(DATADIRS)' @echo ' ' @echo ' These directory can be obtained from' @echo ' ' @echo ' $(DATAURLI) ' @echo ' $(DATAURLO) ' @echo ' $(DATAURLS) ' @echo ' ' @echo ' To clean up the directories type:' @echo ' ' @echo ' make clean' @echo ' ' @echo ' To install the library and binaries type:' @echo ' ' @echo ' make install' @echo ' ' @echo '***************************************************************' @echo ' ' # # Compile the library and examples # all:: $(BIN) $(SOURCE) $(F90SOURCE) $(HEADERS) \ symlinksdone $(REGEXDEP) \ $(LIB)/libcbf.a \ $(LIB)/libfcb.a \ $(LIB)/libimg.a \ $(BIN)/adscimg2cbf \ $(BIN)/cbf2adscimg \ $(BIN)/convert_image \ $(BIN)/convert_minicbf \ $(BIN)/sequence_match \ $(BIN)/arvai_test \ $(BIN)/makecbf \ $(BIN)/img2cif \ $(BIN)/adscimg2cbf \ $(BIN)/cif2cbf \ $(BIN)/testcell \ $(BIN)/cif2c \ $(BIN)/testreals \ $(BIN)/testflat \ $(BIN)/testflatpacked ifneq ($(F90C),) all:: $(BIN)/test_xds_binary \ $(BIN)/test_fcb_read_image endif shared: $(SOLIB)/libcbf.so $(SOLIB)/libfcb.so $(SOLIB)/libimg.so javawrapper: shared $(JCBF) $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf_wrap.so ifneq ($(CBFLIB_USE_PYCIFRW),) PYCIFRWDEF = -Dcbf_use_pycifrw=yes else PYCIFRWDEF = endif Makefiles: Makefile \ Makefile_LINUX \ Makefile_LINUX_64 \ Makefile_LINUX_gcc42 \ Makefile_LINUX_DMALLOC \ Makefile_LINUX_gcc42_DMALLOC \ Makefile_OSX \ Makefile_OSX_gcc42 \ Makefile_OSX_gcc42_DMALLOC \ Makefile_AIX \ Makefile_MINGW \ Makefile_IRIX_gcc Makefile_LINUX: $(M4)/Makefile.m4 -cp Makefile_LINUX Makefile_LINUX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX $(M4)/Makefile.m4 > Makefile_LINUX Makefile_LINUX_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_LINUX Makefile_LINUX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_DMALLOC $(M4)/Makefile.m4 > Makefile_LINUX_DMALLOC Makefile_LINUX_64: $(M4)/Makefile.m4 -cp Makefile_LINUX_64 Makefile_LINUX_64_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_64 $(M4)/Makefile.m4 > Makefile_LINUX_64 Makefile_LINUX_gcc42: $(M4)/Makefile.m4 -cp Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_gcc42 $(M4)/Makefile.m4 > Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_gcc42_DMALLOC $(M4)/Makefile.m4 > Makefile_LINUX_gcc42_DMALLOC Makefile_OSX: $(M4)/Makefile.m4 -cp Makefile_OSX Makefile_OSX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX $(M4)/Makefile.m4 > Makefile_OSX Makefile_OSX_gcc42: $(M4)/Makefile.m4 -cp Makefile_OSX_gcc42 Makefile_OSX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX_gcc42 $(M4)/Makefile.m4 > Makefile_OSX_gcc42 Makefile_OSX_gcc42_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_OSX_gcc42 Makefile_OSX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX_gcc42_DMALLOC $(M4)/Makefile.m4 > Makefile_OSX_gcc42_DMALLOC Makefile_AIX: $(M4)/Makefile.m4 -cp Makefile_AIX Makefile_AIX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=AIX $(M4)/Makefile.m4 > Makefile_AIX Makefile_MINGW: $(M4)/Makefile.m4 -cp Makefile_MINGW Makefile_MINGW_old m4 -P $(PYCIFRWDEF) -Dcbf_system=MINGW $(M4)/Makefile.m4 > Makefile_MINGW Makefile_IRIX_gcc: $(M4)/Makefile.m4 -cp Makefile_IRIX_gcc Makefile_IRIX_gcc_old m4 -P $(PYCIFREDEF) -Dcbf_system=IRIX_gcc $(M4)/Makefile.m4 > Makefile_IRIX_gcc Makefile: $(M4)/Makefile.m4 -cp Makefile Makefile_old m4 -P $(PYCIFRWDEF) -Dcbf_system=default $(M4)/Makefile.m4 > Makefile symlinksdone: chmod a+x .symlinks chmod a+x .undosymlinks chmod a+x doc/.symlinks chmod a+x doc/.undosymlinks chmod a+x libtool/.symlinks chmod a+x libtool/.undosymlinks ./.symlinks $(SLFLAGS) touch symlinksdone install: all $(INSTALLDIR) $(INSTALLDIR)/lib $(INSTALLDIR)/bin \ $(INSTALLDIR)/include $(INSTALLDIR)/include/cbflib \ $(PYSOURCE) -chmod -R 755 $(INSTALLDIR)/include/cbflib -chmod 755 $(INSTALLDIR)/lib/libcbf.a -cp $(INSTALLDIR)/lib/libcbf.a $(INSTALLDIR)/lib/libcbf_old.a cp $(LIB)/libcbf.a $(INSTALLDIR)/lib/libcbf.a -cp $(INSTALLDIR)/lib/libimg.a $(INSTALLDIR)/lib/libimg_old.a cp $(LIB)/libimg.a $(INSTALLDIR)/lib/libimg.a -cp $(INSTALLDIR)/bin/adscimg2cbf $(INSTALLDIR)/bin/adscimg2cbf_old cp $(BIN)/adscimg2cbf $(INSTALLDIR)/bin/adscimg2cbf -cp $(INSTALLDIR)/bin/cbf2adscimg $(INSTALLDIR)/bin/cbf2adscimg_old cp $(BIN)/cbf2adscimg $(INSTALLDIR)/bin/cbf2adscimg -cp $(INSTALLDIR)/bin/convert_image $(INSTALLDIR)/bin/convert_image_old cp $(BIN)/convert_image $(INSTALLDIR)/bin/convert_image -cp $(INSTALLDIR)/bin/convert_minicbf $(INSTALLDIR)/bin/convert_minicbf_old cp $(BIN)/convert_minicbf $(INSTALLDIR)/bin/convert_minicbf -cp $(INSTALLDIR)/bin/makecbf $(INSTALLDIR)/bin/makecbf_old cp $(BIN)/makecbf $(INSTALLDIR)/bin/makecbf -cp $(INSTALLDIR)/bin/img2cif $(INSTALLDIR)/bin/img2cif_old cp $(BIN)/img2cif $(INSTALLDIR)/bin/img2cif -cp $(INSTALLDIR)/bin/cif2cbf $(INSTALLDIR)/bin/cif2cbf_old cp $(BIN)/cif2cbf $(INSTALLDIR)/bin/cif2cbf -cp $(INSTALLDIR)/bin/sequence_match $(INSTALLDIR)/bin/sequence_match_old cp $(BIN)/sequence_match $(INSTALLDIR)/bin/sequence_match -cp $(INSTALLDIR)/bin/arvai_test $(INSTALLDIR)/bin/arvai_test_old cp $(BIN)/arvai_test $(INSTALLDIR)/bin/arvai_test -cp $(INSTALLDIR)/bin/cif2c $(INSTALLDIR)/bin/cif2c_old cp $(BIN)/cif2c $(INSTALLDIR)/bin/cif2c -cp $(INSTALLDIR)/bin/testreals $(INSTALLDIR)/bin/testreals_old cp $(BIN)/testreals $(INSTALLDIR)/bin/testreals -cp $(INSTALLDIR)/bin/testflat $(INSTALLDIR)/bin/testflat_old cp $(BIN)/testflat $(INSTALLDIR)/bin/testflat -cp $(INSTALLDIR)/bin/testflatpacked $(INSTALLDIR)/bin/testflatpacked_old cp $(BIN)/testflatpacked $(INSTALLDIR)/bin/testflatpacked chmod -R 755 $(INSTALLDIR)/include/cbflib -rm -rf $(INSTALLDIR)/include/cbflib_old -cp -r $(INSTALLDIR)/include/cbflib $(INSTALLDIR)/include/cbflib_old -rm -rf $(INSTALLDIR)/include/cbflib cp -r $(INCLUDE) $(INSTALLDIR)/include/cbflib chmod 644 $(INSTALLDIR)/lib/libcbf.a chmod 755 $(INSTALLDIR)/bin/convert_image chmod 755 $(INSTALLDIR)/bin/convert_minicbf chmod 755 $(INSTALLDIR)/bin/makecbf chmod 755 $(INSTALLDIR)/bin/img2cif chmod 755 $(INSTALLDIR)/bin/cif2cbf chmod 755 $(INSTALLDIR)/bin/sequence_match chmod 755 $(INSTALLDIR)/bin/arvai_test chmod 755 $(INSTALLDIR)/bin/cif2c chmod 755 $(INSTALLDIR)/bin/testreals chmod 755 $(INSTALLDIR)/bin/testflat chmod 755 $(INSTALLDIR)/bin/testflatpacked chmod 644 $(INSTALLDIR)/include/cbflib/*.h # # REGEX # ifneq ($(REGEXDEP),) $(REGEXDEP): $(REGEX) (cd $(REGEX); ./configure; make install) endif $(REGEX): $(DOWNLOAD) $(REGEXURL) tar -xvf $(REGEX).tar.gz -rm $(REGEX).tar.gz # # TIFF # $(TIFF): $(DOWNLOAD) $(TIFFURL) tar -xvf $(TIFF).tar.gz -rm $(TIFF).tar.gz (cd $(TIFF); ./configure --prefix=$(TIFFPREFIX); make install) # # Directories # $(INSTALLDIR): mkdir -p $(INSTALLDIR) $(INSTALLDIR)/lib: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/lib $(INSTALLDIR)/bin: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/bin $(INSTALLDIR)/include: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/include $(INSTALLDIR)/include/cbflib: $(INSTALLDIR)/include mkdir -p $(INSTALLDIR)/include/cbflib $(LIB): mkdir $@ $(BIN): mkdir $@ $(SOLIB): mkdir $@ $(JCBF): mkdir $@ # # Parser # $(SRC)/cbf_stx.c: $(SRC)/cbf.stx.y bison $(SRC)/cbf.stx.y -o $(SRC)/cbf.stx.tab.c -d mv $(SRC)/cbf.stx.tab.c $(SRC)/cbf_stx.c mv $(SRC)/cbf.stx.tab.h $(INCLUDE)/cbf_stx.h # # CBF library # $(LIB)/libcbf.a: $(SOURCE) $(HEADERS) $(COMMONDEP) $(LIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG) $(INCLUDES) $(WARNINGS) -c $(SOURCE) $(AR) cr $@ *.o mv *.o $(LIB) ifneq ($(RANLIB),) $(RANLIB) $@ endif $(SOLIB)/libcbf.so: $(SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(SOURCE) $(CC) -o $@ *.o $(SOLDFLAGS) $(EXTRALIBS) rm *.o # # IMG library # $(LIB)/libimg.a: $(EXAMPLES)/img.c $(HEADERS) $(COMMONDEP) $(LIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) -c $(EXAMPLES)/img.c $(AR) cr $@ img.o ifneq ($(RANLIB),) $(RANLIB) $@ endif rm img.o $(SOLIB)/libimg.so: $(SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(EXAMPLES)/img.c $(CC) -o $@ img.o $(SOLDFLAGS) rm img.o # # CBF and IMG libraries # CBF_IMG_LIBS: $(LIB)/libcbf.a $(LIB)/libimg.a # # FCB library # $(LIB)/libfcb.a: $(F90SOURCE) $(COMMONDEP) $(LIB) ifneq ($(F90C),) $(F90C) $(F90FLAGS) -c $(F90SOURCE) $(AR) cr $@ *.o ifneq ($(RANLIB),) $(RANLIB) $@ endif rm *.o else echo "Define F90C to build $(LIB)/libfcb.a" endif $(SOLIB)/libfcb.so: $(F90SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) ifneq ($(F90C),) $(F90C) $(F90FLAGS) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(F90SOURCE) $(F90C) $(F90FLAGS) -o $@ *.o $(SOLDFLAGS) rm *.o else echo "Define F90C to build $(SOLIB)/libfcb.so" endif # # Python bindings # $(PYCBF)/_pycbf.$(PYCBFEXT): $(PYCBF) $(LIB)/libcbf.a \ $(PYCBF)/$(SETUP_PY) \ $(LIB)/libfcb.a \ $(LIB)/libimg.a \ $(PYCBF)/pycbf.i \ $(PYCBF)/cbfhandlewrappers.i \ $(PYCBF)/cbfdetectorwrappers.i \ $(PYCBF)/cbfgenericwrappers.i \ $(PYCBF)/cbfgoniometerwrappers.i (cd $(PYCBF); python $(SETUP_PY) build $(PYCBFBOPT); cp build/lib.*/_pycbf.$(PYCBFEXT) .) $(PYCBF)/setup.py: $(M4)/setup_py.m4 (m4 -P -Dregexlib=NOREGEXLIB -Dregexlibdir=NOREGEXLIBDIR $(M4)/setup_py.m4 > $@) $(PYCBF)/setup_MINGW.py: m4/setup_py.m4 (m4 -P -Dregexlib=regex -Dregexlibdir=$(REGEXDIR) $(M4)/setup_py.m4 > $@) $(LIB)/_pycbf.$(PYCBFEXT): $(PYCBF)/_pycbf.$(PYCBFEXT) cp $(PYCBF)/_pycbf.$(PYCBFEXT) $(LIB)/_pycbf.$(PYCBFEXT) $(PYCBF)/pycbf.pdf: $(PYCBF)/pycbf.w (cd $(PYCBF); \ $(NUWEB) pycbf; \ latex pycbf; \ $(NUWEB) pycbf; \ latex pycbf; \ dvipdfm pycbf ) $(PYCBF)/CBFlib.txt: $(DOC)/CBFlib.html links -dump $(DOC)/CBFlib.html > $(PYCBF)/CBFlib.txt $(PYCBF)/cbfhandlewrappers.i \ $(PYCBF)/cbfdetectorwrappers.i \ $(PYCBF)/cbfgenericwrappers.i \ $(PYCBF)/cbfgoniometerwrappers.i: $(PYCBF)/CBFlib.txt $(PYCBF)/make_pycbf.py (cd $(PYCBF); python make_pycbf.py; $(PYSWIG) pycbf.i; python setup.py build) # # Java bindings # $(JCBF)/cbflib-$(VERSION).jar: $(JCBF) $(JCBF)/jcbf.i $(JSWIG) -I$(INCLUDE) -package org.iucr.cbflib -outdir $(JCBF) $(JCBF)/jcbf.i $(JAVAC) -d . $(JCBF)/*.java $(JAR) cf $@ org $(SOLIB)/libcbf_wrap.so: $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf.so $(CC) $(CFLAGS) $(NOLLFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) $(JAVAINCLUDES) -c $(JCBF)/jcbf_wrap.c $(CC) -o $@ jcbf_wrap.o $(SOLDFLAGS) -L$(SOLIB) -lcbf rm jcbf_wrap.o # # F90SOURCE # $(SRC)/fcb_exit_binary.f90: $(M4)/fcb_exit_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_exit_binary.m4) > $(SRC)/fcb_exit_binary.f90 $(SRC)/fcb_next_binary.f90: $(M4)/fcb_next_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_next_binary.m4) > $(SRC)/fcb_next_binary.f90 $(SRC)/fcb_open_cifin.f90: $(M4)/fcb_open_cifin.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_open_cifin.m4) > $(SRC)/fcb_open_cifin.f90 $(SRC)/fcb_packed.f90: $(M4)/fcb_packed.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_packed.m4) > $(SRC)/fcb_packed.f90 $(SRC)/fcb_read_bits.f90: $(M4)/fcb_read_bits.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_bits.m4) > $(SRC)/fcb_read_bits.f90 $(SRC)/fcb_read_image.f90: $(M4)/fcb_read_image.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_image.m4) > $(SRC)/fcb_read_image.f90 $(SRC)/fcb_read_xds_i2.f90: $(M4)/fcb_read_xds_i2.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_xds_i2.m4) > $(SRC)/fcb_read_xds_i2.f90 $(EXAMPLES)/test_fcb_read_image.f90: $(M4)/test_fcb_read_image.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) test_fcb_read_image.m4) > $(EXAMPLES)/test_fcb_read_image.f90 $(EXAMPLES)/test_xds_binary.f90: $(M4)/test_xds_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) test_xds_binary.m4) > $(EXAMPLES)/test_xds_binary.f90 # # convert_image example program # $(BIN)/convert_image: $(LIB)/libcbf.a $(EXAMPLES)/convert_image.c $(EXAMPLES)/img.c \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/convert_image.c $(EXAMPLES)/img.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # convert_minicbf example program # $(BIN)/convert_minicbf: $(LIB)/libcbf.a $(EXAMPLES)/convert_minicbf.c \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/convert_minicbf.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # makecbf example program # $(BIN)/makecbf: $(LIB)/libcbf.a $(EXAMPLES)/makecbf.c $(LIB)/libimg.a $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/makecbf.c -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # adscimg2cbf example program # $(BIN)/adscimg2cbf: $(LIB)/libcbf.a $(EXAMPLES)/adscimg2cbf.c $(EXAMPLES)/adscimg2cbf_sub.c $(CC) $(CFLAGS) $(NOLLFLAG) -D_SVID_SOURCE $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/adscimg2cbf.c $(EXAMPLES)/adscimg2cbf_sub.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # cbf2adscimg example program # $(BIN)/cbf2adscimg: $(LIB)/libcbf.a $(EXAMPLES)/cbf2adscimg.c $(EXAMPLES)/cbf2adscimg_sub.c $(CC) $(CFLAGS) $(NOLLFLAG) -D_SVID_SOURCE $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cbf2adscimg.c $(EXAMPLES)/cbf2adscimg_sub.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # changtestcompression example program # $(BIN)/changtestcompression: $(LIB)/libcbf.a $(EXAMPLES)/changtestcompression.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/changtestcompression.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # img2cif example program # $(BIN)/img2cif: $(LIB)/libcbf.a $(EXAMPLES)/img2cif.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOTPINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/img2cif.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # cif2cbf example program # $(BIN)/cif2cbf: $(LIB)/libcbf.a $(EXAMPLES)/cif2cbf.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cif2cbf.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # dectris cbf_template_t program # $(BIN)/cbf_template_t: $(DECTRIS_EXAMPLES)/cbf_template_t.c \ $(DECTRIS_EXAMPLES)/mx_cbf_t_extras.h \ $(DECTRIS_EXAMPLES)/mx_parms.h $(CC) $(CFLAGS) $(NOLLFLAG) -I $(DECTRIS_EXAMPLES) $(WARNINGS) \ $(DECTRIS_EXAMPLES)/cbf_template_t.c -o $@ # # testcell example program # $(BIN)/testcell: $(LIB)/libcbf.a $(EXAMPLES)/testcell.C $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testcell.C -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # cif2c example program # $(BIN)/cif2c: $(LIB)/libcbf.a $(EXAMPLES)/cif2c.c $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cif2c.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # sauter_test example program # $(BIN)/sauter_test: $(LIB)/libcbf.a $(EXAMPLES)/sauter_test.C $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/sauter_test.C -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # sequence_match example program # $(BIN)/sequence_match: $(LIB)/libcbf.a $(EXAMPLES)/sequence_match.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/sequence_match.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # tiff2cbf example program # $(BIN)/tiff2cbf: $(LIB)/libcbf.a $(EXAMPLES)/tiff2cbf.c \ $(GOPTLIB) $(GOPTINC) $(TIFF) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ -I$(TIFFPREFIX)/include $(EXAMPLES)/tiff2cbf.c $(GOPTLIB) -L$(LIB) \ -lcbf -L$(TIFFPREFIX)/lib -ltiff $(EXTRALIBS) -limg -o $@ # # Andy Arvai's buffered read test program # $(BIN)/arvai_test: $(LIB)/libcbf.a $(EXAMPLES)/arvai_test.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/arvai_test.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # testreals example program # $(BIN)/testreals: $(LIB)/libcbf.a $(EXAMPLES)/testreals.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testreals.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testflat example program # $(BIN)/testflat: $(LIB)/libcbf.a $(EXAMPLES)/testflat.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testflat.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testflatpacked example program # $(BIN)/testflatpacked: $(LIB)/libcbf.a $(EXAMPLES)/testflatpacked.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testflatpacked.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ ifneq ($(F90C),) # # test_xds_binary example program # $(BIN)/test_xds_binary: $(LIB)/libfcb.a $(EXAMPLES)/test_xds_binary.f90 $(F90C) $(F90FLAGS) $(F90LDFLAGS) $(EXAMPLES)/test_xds_binary.f90 \ -L$(LIB) -lfcb -o $@ # # test_fcb_read_image example program # $(BIN)/test_fcb_read_image: $(LIB)/libfcb.a $(EXAMPLES)/test_fcb_read_image.f90 $(F90C) $(F90FLAGS) $(F90LDFLAGS) $(EXAMPLES)/test_fcb_read_image.f90 \ -L$(LIB) -lfcb -o $@ endif # # testcbf (C) # $(BIN)/ctestcbf: $(EXAMPLES)/testcbf.c $(LIB)/libcbf.a $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testcbf.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testcbf (Java) # $(BIN)/testcbf.class: $(EXAMPLES)/testcbf.java $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf_wrap.so $(JAVAC) -cp $(JCBF)/cbflib-$(VERSION).jar -d $(BIN) $(EXAMPLES)/testcbf.java # # Data files for tests # $(DATADIRI): (cd ..; $(DOWNLOAD) $(DATAURLI)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Input.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Input.tar.gz) $(DATADIRO): (cd ..; $(DOWNLOAD) $(DATAURLO)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Output.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Output.tar.gz) $(DATADIRS): (cd ..; $(DOWNLOAD) $(DATAURLS)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz) # Input Data Files TESTINPUT_BASIC = example.mar2300 DATADIRI_INPUT_BASIC = $(DATADIRI)/example.mar2300$(CEXT) TESTINPUT_EXTRA = 9ins.cif mb_LP_1_001.img insulin_pilatus6m.cbf testrealin.cbf \ testflatin.cbf testflatpackedin.cbf XRD1621.tif DATADIRI_INPUT_EXTRA = $(DATADIRI)/9ins.cif$(CEXT) $(DATADIRI)/mb_LP_1_001.img$(CEXT) \ $(DATADIRI)/insulin_pilatus6m.cbf$(CEXT) $(DATADIRI)/testrealin.cbf$(CEXT) \ $(DATADIRI)/testflatin.cbf$(CEXT) $(DATADIRI)/testflatpackedin.cbf$(CEXT) \ $(DATADIRI)/XRD1621.tif$(CEXT) # Output Data Files TESTOUTPUT = adscconverted_flat_orig.cbf \ adscconverted_orig.cbf converted_flat_orig.cbf converted_orig.cbf \ insulin_pilatus6mconverted_orig.cbf \ mb_LP_1_001_orig.cbf testcell_orig.prt \ test_xds_bin_testflatout_orig.out \ test_xds_bin_testflatpackedout_orig.out test_fcb_read_testflatout_orig.out \ test_fcb_read_testflatpackedout_orig.out \ XRD1621_orig.cbf XRD1621_I4encbC100_orig.cbf NEWTESTOUTPUT = adscconverted_flat.cbf \ adscconverted.cbf converted_flat.cbf converted.cbf \ insulin_pilatus6mconverted.cbf \ mb_LP_1_001.cbf testcell.prt \ test_xds_bin_testflatout.out \ test_xds_bin_testflatpackedout.out test_fcb_read_testflatout.out \ test_fcb_read_testflatpackedout.out \ XRD1621.cbf XRD1621_I4encbC100.cbf DATADIRO_OUTPUT = $(DATADIRO)/adscconverted_flat_orig.cbf$(CEXT) \ $(DATADIRO)/adscconverted_orig.cbf$(CEXT) \ $(DATADIRO)/converted_flat_orig.cbf$(CEXT) \ $(DATADIRO)/converted_orig.cbf$(CEXT) \ $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(CEXT) \ $(DATADIRO)/mb_LP_1_001_orig.cbf$(CEXT) \ $(DATADIRO)/testcell_orig.prt$(CEXT) \ $(DATADIRO)/test_xds_bin_testflatout_orig.out$(CEXT) \ $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(CEXT) \ $(DATADIRO)/test_fcb_read_testflatout_orig.out$(CEXT) \ $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(CEXT) \ $(DATADIRO)/XRD1621_orig.cbf$(CEXT) \ $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(CEXT) DATADIRO_OUTPUT_SIGNATURES = $(DATADIRO)/adscconverted_flat_orig.cbf$(SEXT) \ $(DATADIRO)/adscconverted_orig.cbf$(SEXT) \ $(DATADIRO)/converted_flat_orig.cbf$(SEXT) \ $(DATADIRO)/converted_orig.cbf$(SEXT) \ $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(SEXT) \ $(DATADIRO)/mb_LP_1_001_orig.cbf$(SEXT) \ $(DATADIRO)/testcell_orig.prt$(SEXT) \ $(DATADIRO)/test_xds_bin_testflatout_orig.out$(SEXT) \ $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(SEXT) \ $(DATADIRO)/test_fcb_read_testflatout_orig.out$(SEXT) \ $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(SEXT) \ $(DATADIRO)/XRD1621_orig.cbf$(SEXT) \ $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(SEXT) # Output Data File Signatures TESTOUTPUTSIGS = adscconverted_flat_orig.cbf$(SEXT) \ adscconverted_orig.cbf$(SEXT) converted_flat_orig.cbf$(SEXT) converted_orig.cbf$(SEXT) \ insulin_pilatus6mconverted_orig.cbf$(SEXT) \ mb_LP_1_001_orig.cbf$(SEXT) testcell_orig.prt$(SEXT) \ test_xds_bin_testflatout_orig.out$(SEXT) \ test_xds_bin_testflatpackedout_orig.out$(SEXT) test_fcb_read_testflatout_orig.out$(SEXT) \ test_fcb_read_testflatpackedout_orig.out$(SEXT) \ XRD1621_orig.cbf$(SEXT) DATADIRS_OUTPUT_SIGNATURES = $(DATADIRS)/adscconverted_flat_orig.cbf$(SEXT) \ $(DATADIRS)/adscconverted_orig.cbf$(SEXT) \ $(DATADIRS)/converted_flat_orig.cbf$(SEXT) \ $(DATADIRS)/converted_orig.cbf$(SEXT) \ $(DATADIRS)/insulin_pilatus6mconverted_orig.cbf$(SEXT) \ $(DATADIRS)/mb_LP_1_001_orig.cbf$(SEXT) \ $(DATADIRS)/testcell_orig.prt$(SEXT) \ $(DATADIRS)/test_xds_bin_testflatout_orig.out$(SEXT) \ $(DATADIRS)/test_xds_bin_testflatpackedout_orig.out$(SEXT) \ $(DATADIRS)/test_fcb_read_testflatout_orig.out$(SEXT) \ $(DATADIRS)/test_fcb_read_testflatpackedout_orig.out$(SEXT) \ $(DATADIRS)/XRD1621_orig.cbf$(SEXT) \ $(DATADIRS)/XRD1621_I4encbC100_orig.cbf$(SEXT) # Fetch Input Data Files $(TESTINPUT_BASIC): $(DATADIRI) $(DATADIRI_INPUT_BASIC) $(DECOMPRESS) < $(DATADIRI)/$@$(CEXT) > $@ cp $(DATADIRI)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) $(TESTINPUT_EXTRA): $(DATADIRI) $(DATADIRI_INPUT_EXTRA) $(DECOMPRESS) < $(DATADIRI)/$@$(CEXT) > $@ cp $(DATADIRI)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) # Fetch Output Data Files and Signatures $(TESTOUTPUT): $(DATADIRO) $(DATADIRO_OUTPUT) $(DATADIRO_OUTPUT_SIGNATURES) $(DECOMPRESS) < $(DATADIRO)/$@$(CEXT) > $@ cp $(DATADIRO)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) # Fetch Output Data File Signatures $(TESTOUTPUTSIGS): $(DATADIRS) $(DATADIRS_OUTPUT_SIGNATURES) cp $(DATADIRS)/$@ $@ # # Tests # tests: $(LIB) $(BIN) symlinksdone basic extra dectristests pycbftests tests_sigs_only: $(LIB) $(BIN) symlinksdone basic extra_sigs_only restore_output: $(NEWTESTOUTPUT) $(DATADIRO) $(SIGNATURE) < adscconverted_flat.cbf > $(DATADIRO)/adscconverted_flat_orig.cbf$(SEXT) $(SIGNATURE) < adscconverted.cbf > $(DATADIRO)/adscconverted_orig.cbf$(SEXT) $(SIGNATURE) < converted_flat.cbf > $(DATADIRO)/converted_flat_orig.cbf$(SEXT) $(SIGNATURE) < converted.cbf > $(DATADIRO)/converted_orig.cbf$(SEXT) $(SIGNATURE) < insulin_pilatus6mconverted.cbf > $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(SEXT) $(SIGNATURE) < mb_LP_1_001.cbf$ > $(DATADIRO)/mb_LP_1_001_orig.cbf$(SEXT) $(SIGNATURE) < testcell.prt > $(DATADIRO)/testcell_orig.prt$(SEXT) $(SIGNATURE) < test_xds_bin_testflatout.out > $(DATADIRO)/test_xds_bin_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_xds_bin_testflatpackedout.out > $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatout.out > $(DATADIRO)/test_fcb_read_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatpackedout.out > $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < XRD1621.cbf > $(DATADIRO)/XRD1621_orig.cbf$(SEXT) $(SIGNATURE) < XRD1621_I4encbC100.cbf > $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(SEXT) $(COMPRESS) < adscconverted_flat.cbf > $(DATADIRO)/adscconverted_flat_orig.cbf$(CEXT) $(COMPRESS) < adscconverted.cbf > $(DATADIRO)/adscconverted_orig.cbf$(CEXT) $(COMPRESS) < converted_flat.cbf > $(DATADIRO)/converted_flat_orig.cbf$(CEXT) $(COMPRESS) < converted.cbf > $(DATADIRO)/converted_orig.cbf$(CEXT) $(COMPRESS) < insulin_pilatus6mconverted.cbf > $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(CEXT) $(COMPRESS) < mb_LP_1_001.cbf$ > $(DATADIRO)/mb_LP_1_001_orig.cbf$(CEXT) $(COMPRESS) < testcell.prt > $(DATADIRO)/testcell_orig.prt$(CEXT) $(COMPRESS) < test_xds_bin_testflatout.out > $(DATADIRO)/test_xds_bin_testflatout_orig.out$(CEXT) $(COMPRESS) < test_xds_bin_testflatpackedout.out > $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(CEXT) $(COMPRESS) < test_fcb_read_testflatout.out > $(DATADIRO)/test_fcb_read_testflatout_orig.out$(CEXT) $(COMPRESS) < test_fcb_read_testflatpackedout.out > $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(CEXT) $(COMPRESS) < XRD1621.cbf > $(DATADIRO)/XRD1621_orig.cbf$(CEXT) $(COMPRESS) < XRD1621_I4encbC100.cbf > $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(CEXT) restore_sigs_only: $(NEWTESTOUTPUT) $(DATADIRS) $(SIGNATURE) < adscconverted_flat.cbf > $(DATADIRS)/adscconverted_flat_orig.cbf$(SEXT) $(SIGNATURE) < adscconverted.cbf > $(DATADIRS)/adscconverted_orig.cbf$(SEXT) $(SIGNATURE) < converted_flat.cbf > $(DATADIRS)/converted_flat_orig.cbf$(SEXT) $(SIGNATURE) < converted.cbf > $(DATADIRS)/converted_orig.cbf$(SEXT) $(SIGNATURE) < insulin_pilatus6mconverted.cbf > $(DATADIRS)/insulin_pilatus6mconverted_orig.cbf$(SEXT) $(SIGNATURE) < mb_LP_1_001.cbf$ > $(DATADIRS)/mb_LP_1_001_orig.cbf$(SEXT) $(SIGNATURE) < testcell.prt > $(DATADIRS)/testcell_orig.prt$(SEXT) $(SIGNATURE) < test_xds_bin_testflatout.out > $(DATADIRS)/test_xds_bin_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_xds_bin_testflatpackedout.out > $(DATADIRS)/test_xds_bin_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatout.out > $(DATADIRS)/test_fcb_read_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatpackedout.out > $(DATADIRS)/test_fcb_read_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < XRD1621.cbf > $(DATADIRS)/XRD1621_orig.cbf$(SEXT) $(SIGNATURE) < XRD1621_I4encbC100.cbf > $(DATADIRS)/XRD1621_I4encbC100_orig.cbf$(SEXT) restore_signatures: restore_output restore_sigs_only # # Basic Tests # basic: $(BIN)/makecbf $(BIN)/img2cif $(BIN)/cif2cbf $(TESTINPUT_BASIC) $(BIN)/makecbf example.mar2300 makecbf.cbf $(BIN)/img2cif -c flatpacked -m headers -d digest \ -e base64 example.mar2300 img2cif_packed.cif $(BIN)/img2cif -c canonical -m headers -d digest \ -e base64 example.mar2300 img2cif_canonical.cif $(BIN)/img2cif -c flatpacked -m headers -d digest \ -e none example.mar2300 img2cif_packed.cbf $(BIN)/img2cif -c canonical -m headers -d digest \ -e none example.mar2300 img2cif_canonical.cbf $(BIN)/cif2cbf -e none -c flatpacked \ img2cif_canonical.cif cif2cbf_packed.cbf $(BIN)/cif2cbf -e none -c canonical \ img2cif_packed.cif cif2cbf_canonical.cbf -cmp cif2cbf_packed.cbf makecbf.cbf -cmp cif2cbf_packed.cbf img2cif_packed.cbf -cmp cif2cbf_canonical.cbf img2cif_canonical.cbf # # Extra Tests # ifneq ($(F90C),) extra: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/test_xds_binary $(BIN)/test_fcb_read_image $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg \ $(BIN)/changtestcompression $(BIN)/tiff2cbf \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUT) else extra: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUT) endif $(TIME) $(BIN)/cif2cbf -e hex -c none \ makecbf.cbf cif2cbf_ehcn.cif $(TIME) $(BIN)/cif2cbf -e none -c flatpacked \ cif2cbf_ehcn.cif cif2cbf_encp.cbf; rm cif2cbf_ehcn.cif -cmp makecbf.cbf cif2cbf_encp.cbf $(TIME) $(BIN)/cif2cbf -i 9ins.cif -o 9ins.cbf -cmp 9ins.cif 9ins.cbf $(TIME) $(BIN)/convert_image -F example.mar2300 converted_flat.cbf -cmp converted_flat.cbf converted_flat_orig.cbf $(TIME) $(BIN)/convert_image example.mar2300 converted.cbf -cmp converted.cbf converted_orig.cbf -$(TIME) $(BIN)/testcell < testcell.dat > testcell.prt -cmp testcell.prt testcell_orig.prt $(TIME) $(BIN)/convert_image -F -d adscquantum315 mb_LP_1_001.img adscconverted_flat.cbf -cmp adscconverted_flat.cbf adscconverted_flat_orig.cbf $(TIME) $(BIN)/convert_image -d adscquantum315 mb_LP_1_001.img adscconverted.cbf -cmp adscconverted.cbf adscconverted_orig.cbf $(TIME) $(BIN)/adscimg2cbf --no_pad --cbf_packed,flat mb_LP_1_001.img -cmp mb_LP_1_001.cbf mb_LP_1_001_orig.cbf ifneq ($(CLEANTESTS),) mv mb_LP_1_001.cbf nmb_LP_1_001.cbf else cp mb_LP_1_001.cbf nmb_LP_1_001.cbf endif $(TIME) $(BIN)/cbf2adscimg nmb_LP_1_001.cbf -cmp nmb_LP_1_001.img mb_LP_1_001.img rm nmb_LP_1_001.cbf ifneq ($(CLEANTESTS),) rm nmb_LP_1_001.img endif $(TIME) $(BIN)/convert_minicbf -d pilatus6m insulin_pilatus6m.cbf insulin_pilatus6mconverted.cbf -cmp insulin_pilatus6mconverted.cbf insulin_pilatus6mconverted_orig.cbf $(TIME) $(BIN)/testreals -cmp testrealin.cbf testrealout.cbf $(TIME) $(BIN)/testflat -cmp testflatin.cbf testflatout.cbf $(TIME) $(BIN)/testflatpacked -cmp testflatpackedin.cbf testflatpackedout.cbf ifneq ($(F90C),) echo testflatout.cbf | $(TIME) $(BIN)/test_xds_binary > test_xds_bin_testflatout.out -$(DIFF) test_xds_bin_testflatout.out test_xds_bin_testflatout_orig.out echo testflatpackedout.cbf | $(TIME) $(BIN)/test_xds_binary > test_xds_bin_testflatpackedout.out -$(DIFF) test_xds_bin_testflatpackedout.out test_xds_bin_testflatpackedout_orig.out echo testflatout.cbf | $(TIME) $(BIN)/test_fcb_read_image > test_fcb_read_testflatout.out -$(DIFF) test_fcb_read_testflatout.out test_fcb_read_testflatout_orig.out echo testflatpackedout.cbf | $(TIME) $(BIN)/test_fcb_read_image > test_fcb_read_testflatpackedout.out -$(DIFF) test_fcb_read_testflatpackedout.out test_fcb_read_testflatpackedout_orig.out endif $(TIME) $(BIN)/sauter_test $(TIME) $(BIN)/changtestcompression $(TIME) (export LD_LIBRARY_PATH=$(LIB);$(BIN)/tiff2cbf XRD1621.tif XRD1621.cbf) -$(DIFF) XRD1621.cbf XRD1621_orig.cbf $(TIME) $(BIN)/cif2cbf -I 4 -C 100. -L 0. -e n -c b -i XRD1621.cbf -o XRD1621_I4encbC100.cbf -$(DIFF) XRD1621_I4encbC100.cbf XRD1621_I4encbC100_orig.cbf ifneq ($(F90C),) extra_sigs_only: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/test_xds_binary $(BIN)/test_fcb_read_image $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg $(BIN)/tiff2cbf \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) else extra_sigs_only: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf\ basic $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) endif $(TIME) $(BIN)/cif2cbf -e hex -c none \ makecbf.cbf cif2cbf_ehcn.cif $(TIME) $(BIN)/cif2cbf -e none -c packed \ cif2cbf_ehcn.cif cif2cbf_encp.cbf; rm cif2cbf_ehcn.cif -cmp makecbf.cbf cif2cbf_encp.cbf $(TIME) $(BIN)/cif2cbf -i 9ins.cif -o 9ins.cbf -cmp 9ins.cif 9ins.cbf $(TIME) $(BIN)/convert_image -F example.mar2300 converted_flat.cbf -$(SIGNATURE) < converted_flat.cbf | $(DIFF) - converted_flat_orig.cbf$(SEXT); rm converted_flat.cbf $(TIME) $(BIN)/convert_image example.mar2300 converted.cbf -$(SIGNATURE) < converted.cbf | $(DIFF) - converted_orig.cbf$(SEXT); rm converted.cbf -$(TIME) $(BIN)/testcell < testcell.dat | \ $(SIGNATURE) | $(DIFF) - testcell_orig.prt$(SEXT) $(TIME) $(BIN)/convert_image -F -d adscquantum315 mb_LP_1_001.img adscconverted_flat.cbf -$(SIGNATURE) < adscconverted_flat.cbf | $(DIFF) - adscconverted_flat_orig.cbf$(SEXT) $(TIME) $(BIN)/convert_image -d adscquantum315 mb_LP_1_001.img adscconverted.cbf -$(SIGNATURE) < adscconverted.cbf | $(DIFF) - adscconverted_orig.cbf$(SEXT); rm adscconverted.cbf $(TIME) $(BIN)/adscimg2cbf --cbf_packed,flat mb_LP_1_001.img -$(SIGNATURE) < mb_LP_1_001.cbf | $(DIFF) - mb_LP_1_001_orig.cbf$(SEXT) mv mb_LP_1_001.cbf nmb_LP_1_001.cbf $(TIME) $(BIN)/cbf2adscimg nmb_LP_1_001.cbf -cmp nmb_LP_1_001.img mb_LP_1_001.img rm nmb_LP_1_001.cbf rm nmb_LP_1_001.img $(TIME) $(BIN)/convert_minicbf -d pilatus6m insulin_pilatus6m.cbf insulin_pilatus6mconverted.cbf -$(SIGNATURE) < insulin_pilatus6mconverted.cbf | $(DIFF) - insulin_pilatus6mconverted_orig.cbf$(SEXT); rm insulin_pilatus6mconverted.cbf $(TIME) $(BIN)/testreals -cmp testrealin.cbf testrealout.cbf $(TIME) $(BIN)/testflat -cmp testflatin.cbf testflatout.cbf $(TIME) $(BIN)/testflatpacked -cmp testflatpackedin.cbf testflatpackedout.cbf ifneq ($(F90C),) echo testflatout.cbf | $(TIME) $(BIN)/test_xds_binary | \ $(SIGNATURE) | $(DIFF) - test_xds_bin_testflatout_orig.out$(SEXT) echo testflatpackedout.cbf | $(TIME) $(BIN)/test_xds_binary | \ $(SIGNATURE) | $(DIFF) - test_xds_bin_testflatpackedout_orig.out$(SEXT) echo testflatout.cbf | $(TIME) $(BIN)/test_fcb_read_image | \ $(SIGNATURE) | $(DIFF) - test_fcb_read_testflatout_orig.out$(SEXT) echo testflatpackedout.cbf | $(TIME) $(BIN)/test_fcb_read_image | \ $(SIGNATURE) | $(DIFF) - test_fcb_read_testflatpackedout_orig.out$(SEXT) endif $(TIME) $(BIN)/sauter_test $(TIME) $(BIN)/tiff2cbf XRD1621.tif XRD1621.cbf $(TIME) $(BIN)/cif2cbf -I 4 -C 100. -L 0. -e n -c b -i XRD1621.cbf -o XRD1621_I4encbC100.cbf -$(SIGNATURE) < XRD1621.cbf | $(DIFF) - XRD1621_orig.cbf$(SEXT); rm XRD1621.cbf -$(SIGNATURE) < XRD1621_I4encbC100.cbf | $(DIFF) - XRD1621_I4encbC100_orig.cbf$(SEXT); rm XRD1621_I4encbC100.cbf @-rm -f adscconverted_flat.cbf @-rm -f $(TESTINPUT_BASIC) $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) @-rm -f cif2cbf_packed.cbf makecbf.cbf \ cif2cbf_packed.cbf img2cif_packed.cbf \ cif2cbf_canonical.cbf img2cif_canonical.cbf @-rm -f testrealout.cbf testflatout.cbf testflatpackedout.cbf \ cif2cbf_encp.cbf img2cif_canonical.cif img2cif_packed.cif 9ins.cbf pycbftests: $(PYCBF)/_pycbf.$(PYCBFEXT) (cd $(PYCBF); python pycbf_test1.py) (cd $(PYCBF); python pycbf_test2.py) (cd $(PYCBF); python pycbf_test3.py) javatests: $(BIN)/ctestcbf $(BIN)/testcbf.class $(SOLIB)/libcbf_wrap.so $(BIN)/ctestcbf > testcbfc.txt $(LDPREFIX) java -cp $(JCBF)/cbflib-$(VERSION).jar:$(BIN) testcbf > testcbfj.txt $(DIFF) testcbfc.txt testcbfj.txt dectristests: $(BIN)/cbf_template_t $(DECTRIS_EXAMPLES)/cbf_test_orig.out (cd $(DECTRIS_EXAMPLES); ../../bin/cbf_template_t; diff -a -u cbf_test_orig.out cbf_template_t.out) # # Remove all non-source files # empty: @-rm -f $(LIB)/*.o @-rm -f $(LIB)/libcbf.a @-rm -f $(LIB)/libfcb.a @-rm -f $(LIB)/libimg.a @-rm -f $(LIB)/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/build/*/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/build/src/cbf_simple.o @-rm -f $(PYCBF)/build/*/pycbf_wrap.o @-rm -rf $(BIN)/adscimg2cbf* @-rm -rf $(BIN)/cbf2adscimg* @-rm -rf $(BIN)/makecbf* @-rm -rf $(BIN)/img2cif* @-rm -rf $(BIN)/cif2cbf* @-rm -rf $(BIN)/convert_image* @-rm -rf $(BIN)/convert_minicbf* @-rm -rf $(BIN)/test_fcb_read_image* @-rm -rf $(BIN)/test_xds_binary* @-rm -rf $(BIN)/testcell* @-rm -rf $(BIN)/cif2c* @-rm -rf $(BIN)/testreals* @-rm -rf $(BIN)/testflat* @-rm -rf $(BIN)/testflatpacked* @-rm -rf $(BIN)/cbf_template_t* @-rm -rf $(BIN)/sauter_test* @-rm -rf $(BIN)/arvai_test* @-rm -rf $(BIN)/changtestcompression* @-rm -rf $(BIN)/tiff2cbf* @-rm -f makecbf.cbf @-rm -f img2cif_packed.cif @-rm -f img2cif_canonical.cif @-rm -f img2cif_packed.cbf @-rm -f img2cif_canonical.cbf @-rm -f img2cif_raw.cbf @-rm -f cif2cbf_packed.cbf @-rm -f cif2cbf_canonical.cbf @-rm -f converted.cbf @-rm -f adscconverted.cbf @-rm -f converted_flat.cbf @-rm -f adscconverted_flat.cbf @-rm -f adscconverted_flat_rev.cbf @-rm -f mb_LP_1_001.cbf @-rm -f cif2cbf_ehcn.cif @-rm -f cif2cbf_encp.cbf @-rm -f 9ins.cbf @-rm -f 9ins.cif @-rm -f testcell.prt @-rm -f example.mar2300 @-rm -f converted_orig.cbf @-rm -f adscconverted_orig.cbf @-rm -f converted_flat_orig.cbf @-rm -f adscconverted_flat_orig.cbf @-rm -f adscconverted_flat_rev_orig.cbf @-rm -f mb_LP_1_001_orig.cbf @-rm -f insulin_pilatus6mconverted_orig.cbf @-rm -f insulin_pilatus6mconverted.cbf @-rm -f insulin_pilatus6m.cbf @-rm -f testrealin.cbf @-rm -f testrealout.cbf @-rm -f testflatin.cbf @-rm -f testflatout.cbf @-rm -f testflatpackedin.cbf @-rm -f testflatpackedout.cbf @-rm -f CTC.cbf @-rm -f test_fcb_read_testflatout.out @-rm -f test_fcb_read_testflatpackedout.out @-rm -f test_xds_bin_testflatpackedout.out @-rm -f test_xds_bin_testflatout.out @-rm -f test_fcb_read_testflatout_orig.out @-rm -f test_fcb_read_testflatpackedout_orig.out @-rm -f test_xds_bin_testflatpackedout_orig.out @-rm -f test_xds_bin_testflatout_orig.out @-rm -f mb_LP_1_001.img @-rm -f 9ins.cif @-rm -f testcell_orig.prt @-rm -f $(DECTRIS_EXAMPLES)/cbf_template_t.out @-rm -f XRD1621.cbf @-rm -f XRD1621_orig.cbf @-rm -f XRD1621_orig.cbf @-rm -f XRD1621_I4encbC100.cbf @-rm -f $(SRC)/fcb_exit_binary.f90 @-rm -f $(SRC)/fcb_next_binary.f90 @-rm -f $(SRC)/fcb_open_cifin.f90 @-rm -f $(SRC)/fcb_packed.f90 @-rm -f $(SRC)/fcb_read_bits.f90 @-rm -f $(SRC)/fcb_read_image.f90 @-rm -f $(SRC)/fcb_read_xds_i2.f90 @-rm -f $(EXAMPLES)/test_fcb_read_image.f90 @-rm -f $(EXAMPLES)/test_xds_binary.f90 @-rm -f symlinksdone @-rm -f $(TESTOUTPUT) *$(SEXT) @-rm -f $(SOLIB)/*.o @-rm -f $(SOLIB)/libcbf_wrap.so @-rm -f $(SOLIB)/libjcbf.so @-rm -f $(SOLIB)/libimg.so @-rm -f $(SOLIB)/libfcb.so @-rm -rf $(JCBF)/org @-rm -f $(JCBF)/*.java @-rm -f $(JCBF)/jcbf_wrap.c @-rm -f $(SRC)/cbf_wrap.c @-rm -f $(BIN)/ctestcbf $(BIN)/testcbf.class testcbfc.txt testcbfj.txt @-rm -rf $(REGEX) @-rm -rf $(TIFF) ./.undosymlinks # # Remove temporary files # clean: @-rm -f core @-rm -f *.o @-rm -f *.u # # Restore to distribution state # distclean: clean empty # # Create a Tape Archive for distribution # tar: $(DOCUMENTS) $(SOURCE) $(SRC)/cbf.stx $(HEADERS) $(M4FILES)\ $(EXAMPLES) \ README.html README Makefile \ $(JPEGS) -/bin/rm -f CBFlib.tar* tar cvBf CBFlib.tar \ $(DOCUMENTS) $(SOURCE) $(SRC)/cbf.stx $(HEADERS) $(M4FILES)\ $(EXAMPLES) \ README.html README Makefile \ $(JPEGS) gzip --best CBFlib.tar ./CBFlib-0.9.2.2/CBFlib.tar.gz0000777000076500007650000000000011603751102017232 2../CBFlib-0.9.2.2.tar.gzustar yayayaya./CBFlib-0.9.2.2/testcell.dat0000644000076500007650000000003311603702122014101 0ustar yayayaya1.5 1.4 1.3 85. 105. 115. ./CBFlib-0.9.2.2/Makefile_IRIX_gcc0000644000076500007650000017775211603702122014726 0ustar yayayaya ###################################################################### # Makefile - command file for make to create CBFlib # # # # Version 0.9.2 12 Feb 2011 # # # # Paul Ellis and # # Herbert J. Bernstein (yaya@bernstein-plus-sons.com) # # # # (C) Copyright 2006 - 2011 Herbert J. Bernstein # # # ###################################################################### ###################################################################### # # # YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL # # # # ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS # # OF THE LGPL # # # ###################################################################### ########################### GPL NOTICES ############################## # # # This program is free software; you can redistribute it and/or # # modify it under the terms of the GNU General Public License as # # published by the Free Software Foundation; either version 2 of # # (the License, or (at your option) any later version. # # # # This program is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # # GNU General Public License for more details. # # # # You should have received a copy of the GNU General Public License # # along with this program; if not, write to the Free Software # # Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA # # 02111-1307 USA # # # ###################################################################### ######################### LGPL NOTICES ############################### # # # This library is free software; you can redistribute it and/or # # modify it under the terms of the GNU Lesser General Public # # License as published by the Free Software Foundation; either # # version 2.1 of the License, or (at your option) any later version. # # # # This library is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # # Lesser General Public License for more details. # # # # You should have received a copy of the GNU Lesser General Public # # License along with this library; if not, write to the Free # # Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, # # MA 02110-1301 USA # # # ###################################################################### ###################################################################### # # # Stanford University Notices # # for the CBFlib software package that incorporates SLAC software # # on which copyright is disclaimed # # # # This software # # ------------- # # The term "this software", as used in these Notices, refers to # # those portions of the software package CBFlib that were created by # # employees of the Stanford Linear Accelerator Center, Stanford # # University. # # # # Stanford disclaimer of copyright # # -------------------------------- # # Stanford University, owner of the copyright, hereby disclaims its # # copyright and all other rights in this software. Hence, anyone # # may freely use it for any purpose without restriction. # # # # Acknowledgement of sponsorship # # ------------------------------ # # This software was produced by the Stanford Linear Accelerator # # Center, Stanford University, under Contract DE-AC03-76SFO0515 with # # the Department of Energy. # # # # Government disclaimer of liability # # ---------------------------------- # # Neither the United States nor the United States Department of # # Energy, nor any of their employees, makes any warranty, express or # # implied, or assumes any legal liability or responsibility for the # # accuracy, completeness, or usefulness of any data, apparatus, # # product, or process disclosed, or represents that its use would # # not infringe privately owned rights. # # # # Stanford disclaimer of liability # # -------------------------------- # # Stanford University makes no representations or warranties, # # express or implied, nor assumes any liability for the use of this # # software. # # # # Maintenance of notices # # ---------------------- # # In the interest of clarity regarding the origin and status of this # # software, this and all the preceding Stanford University notices # # are to remain affixed to any copy or derivative of this software # # made or distributed by the recipient and are to be affixed to any # # copy of software made or distributed by the recipient that # # contains a copy or derivative of this software. # # # # Based on SLAC Software Notices, Set 4 # # OTT.002a, 2004 FEB 03 # ###################################################################### ###################################################################### # NOTICE # # Creative endeavors depend on the lively exchange of ideas. There # # are laws and customs which establish rights and responsibilities # # for authors and the users of what authors create. This notice # # is not intended to prevent you from using the software and # # documents in this package, but to ensure that there are no # # misunderstandings about terms and conditions of such use. # # # # Please read the following notice carefully. If you do not # # understand any portion of this notice, please seek appropriate # # professional legal advice before making use of the software and # # documents included in this software package. In addition to # # whatever other steps you may be obliged to take to respect the # # intellectual property rights of the various parties involved, if # # you do make use of the software and documents in this package, # # please give credit where credit is due by citing this package, # # its authors and the URL or other source from which you obtained # # it, or equivalent primary references in the literature with the # # same authors. # # # # Some of the software and documents included within this software # # package are the intellectual property of various parties, and # # placement in this package does not in any way imply that any # # such rights have in any way been waived or diminished. # # # # With respect to any software or documents for which a copyright # # exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. # # # # Even though the authors of the various documents and software # # found here have made a good faith effort to ensure that the # # documents are correct and that the software performs according # # to its documentation, and we would greatly appreciate hearing of # # any problems you may encounter, the programs and documents any # # files created by the programs are provided **AS IS** without any * # warranty as to correctness, merchantability or fitness for any # # particular or general use. # # # # THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF # # PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE # # PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS # # OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE # # PROGRAMS OR DOCUMENTS. # ###################################################################### ###################################################################### # # # The IUCr Policy # # for the Protection and the Promotion of the STAR File and # # CIF Standards for Exchanging and Archiving Electronic Data # # # # Overview # # # # The Crystallographic Information File (CIF)[1] is a standard for # # information interchange promulgated by the International Union of # # Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the # # recommended method for submitting publications to Acta # # Crystallographica Section C and reports of crystal structure # # determinations to other sections of Acta Crystallographica # # and many other journals. The syntax of a CIF is a subset of the # # more general STAR File[2] format. The CIF and STAR File approaches # # are used increasingly in the structural sciences for data exchange # # and archiving, and are having a significant influence on these # # activities in other fields. # # # # Statement of intent # # # # The IUCr's interest in the STAR File is as a general data # # interchange standard for science, and its interest in the CIF, # # a conformant derivative of the STAR File, is as a concise data # # exchange and archival standard for crystallography and structural # # science. # # # # Protection of the standards # # # # To protect the STAR File and the CIF as standards for # # interchanging and archiving electronic data, the IUCr, on behalf # # of the scientific community, # # # # # holds the copyrights on the standards themselves, * # # # # owns the associated trademarks and service marks, and * # # # # holds a patent on the STAR File. * # # # These intellectual property rights relate solely to the # # interchange formats, not to the data contained therein, nor to # # the software used in the generation, access or manipulation of # # the data. # # # # Promotion of the standards # # # # The sole requirement that the IUCr, in its protective role, # # imposes on software purporting to process STAR File or CIF data # # is that the following conditions be met prior to sale or # # distribution. # # # # # Software claiming to read files written to either the STAR * # File or the CIF standard must be able to extract the pertinent # # data from a file conformant to the STAR File syntax, or the CIF # # syntax, respectively. # # # # # Software claiming to write files in either the STAR File, or * # the CIF, standard must produce files that are conformant to the # # STAR File syntax, or the CIF syntax, respectively. # # # # # Software claiming to read definitions from a specific data * # dictionary approved by the IUCr must be able to extract any # # pertinent definition which is conformant to the dictionary # # definition language (DDL)[3] associated with that dictionary. # # # # The IUCr, through its Committee on CIF Standards, will assist # # any developer to verify that software meets these conformance # # conditions. # # # # Glossary of terms # # # # [1] CIF: is a data file conformant to the file syntax defined # # at http://www.iucr.org/iucr-top/cif/spec/index.html # # # # [2] STAR File: is a data file conformant to the file syntax # # defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html # # # # [3] DDL: is a language used in a data dictionary to define data # # items in terms of "attributes". Dictionaries currently approved # # by the IUCr, and the DDL versions used to construct these # # dictionaries, are listed at # # http://www.iucr.org/iucr-top/cif/spec/ddl/index.html # # # # Last modified: 30 September 2000 # # # # IUCr Policy Copyright (C) 2000 International Union of # # Crystallography # ###################################################################### # Version string VERSION = 0.9.2 # # Comment out the next line if scratch test files sould be retain # CLEANTESTS = yes # # Definition to get a version of tifflib to support tiff2cbf # TIFF = tiff-3.9.4-rev-6Feb11 TIFFPREFIX = $(PWD) # # Definitions to get a stable version of regex # REGEX = regex-20090805 REGEXDIR = /usr/lib REGEXDEP = # Program to use to retrieve a URL DOWNLOAD = wget # Flag to control symlinks versus copying SLFLAGS = --use_ln # # Program to use to pack shars # SHAR = /usr/bin/shar #SHAR = /usr/local/bin/gshar # # Program to use to create archives # AR = /usr/bin/ar # # Program to use to add an index to an archive # RANLIB = /usr/bin/ranlib # # Program to use to decompress a data file # DECOMPRESS = /usr/bin/bunzip2 # # Program to use to compress a data file # COMPRESS = /usr/bin/bzip2 # # Program to use to generate a signature # SIGNATURE = /usr/bin/openssl dgst -md5 # # Extension for compressed data file (with period) # CEXT = .bz2 # # Extension for signatures of files # SEXT = .md5 # call to time a command #TIME = #TIME = time # # Program to display differences between files # DIFF = diff -u -b # # Program to generate wrapper classes for Python # PYSWIG = swig -python # # Program to generate wrapper classes for Java # JSWIG = swig -java # # Program to generate LaTex and HTML program documentation # NUWEB = nuweb # # Compiler for Java # JAVAC = javac # # Java archiver for compiled classes # JAR = jar # # Java SDK root directory # ifeq ($(JDKDIR),) JDKDIR = /usr/lib/java endif ifneq ($(CBF_DONT_USE_LONG_LONG),) NOLLFLAG = -DCBF_DONT_USE_LONG_LONG else NOLLFLAG = endif # # PYCBF definitions # PYCBFEXT = so PYCBFBOPT = SETUP_PY = setup.py # # Set the compiler and flags # ######################################################### # # Appropriate compiler definitions for IRIX w. gcc # No f90 # use default paths for utilities # ######################################################### CC = gcc C++ = g++ CFLAGS = -g -O2 -Wall F90C = F90FLAGS = M4FLAGS = -Dfcb_bytes_in_rec=4096 EXTRALIBS = -lm TIME = SHAR = shar AR = ar RANLIB = DECOMPRESS = bunzip2 ifneq ($(NOFORTRAN),) F90C = endif # # Directories # ROOT = . LIB = $(ROOT)/lib SOLIB = $(ROOT)/solib JCBF = $(ROOT)/jcbf JAVADIR = $(ROOT)/java BIN = $(ROOT)/bin SRC = $(ROOT)/src INCLUDE = $(ROOT)/include M4 = $(ROOT)/m4 PYCBF = $(ROOT)/pycbf EXAMPLES = $(ROOT)/examples DECTRIS_EXAMPLES = $(EXAMPLES)/dectris_cbf_template_test DOC = $(ROOT)/doc GRAPHICS = $(ROOT)/html_graphics DATADIRI = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Input DATADIRO = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Output DATADIRS = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only INSTALLDIR = $(HOME) # # URLs from which to retrieve the data directories # DATAURLBASE = http://downloads.sf.net/cbflib/ DATAURLI = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Input.tar.gz DATAURLO = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Output.tar.gz DATAURLS = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz # # URLs from which to retrieve needed external package snapshots # REGEXURL = http://downloads.sf.net/cbflib/$(REGEX).tar.gz TIFFURL = http://downloads.sf.net/cbflib/$(TIFF).tar.gz # # Include directories # INCLUDES = -I$(INCLUDE) -I$(SRC) ###################################################################### # You should not need to make modifications below this line # ###################################################################### # # Suffixes of files to be used or built # .SUFFIXES: .c .o .f90 .m4 .m4.f90: m4 -P $(M4FLAGS) $< > $@ ifneq ($(F90C),) .f90.o: $(F90C) $(F90FLAGS) -c $< -o $@ endif # # Common dependencies # COMMONDEP = Makefile # # Source files # SOURCE = $(SRC)/cbf.c \ $(SRC)/cbf_alloc.c \ $(SRC)/cbf_ascii.c \ $(SRC)/cbf_binary.c \ $(SRC)/cbf_byte_offset.c \ $(SRC)/cbf_canonical.c \ $(SRC)/cbf_codes.c \ $(SRC)/cbf_compress.c \ $(SRC)/cbf_context.c \ $(SRC)/cbf_copy.c \ $(SRC)/cbf_file.c \ $(SRC)/cbf_getopt.c \ $(SRC)/cbf_lex.c \ $(SRC)/cbf_packed.c \ $(SRC)/cbf_predictor.c \ $(SRC)/cbf_read_binary.c \ $(SRC)/cbf_read_mime.c \ $(SRC)/cbf_simple.c \ $(SRC)/cbf_string.c \ $(SRC)/cbf_stx.c \ $(SRC)/cbf_tree.c \ $(SRC)/cbf_uncompressed.c \ $(SRC)/cbf_write.c \ $(SRC)/cbf_write_binary.c \ $(SRC)/cbf_ws.c \ $(SRC)/md5c.c F90SOURCE = $(SRC)/fcb_atol_wcnt.f90 \ $(SRC)/fcb_ci_strncmparr.f90 \ $(SRC)/fcb_exit_binary.f90 \ $(SRC)/fcb_nblen_array.f90 \ $(SRC)/fcb_next_binary.f90 \ $(SRC)/fcb_open_cifin.f90 \ $(SRC)/fcb_packed.f90 \ $(SRC)/fcb_read_bits.f90 \ $(SRC)/fcb_read_byte.f90 \ $(SRC)/fcb_read_image.f90 \ $(SRC)/fcb_read_line.f90 \ $(SRC)/fcb_read_xds_i2.f90 \ $(SRC)/fcb_skip_whitespace.f90 \ $(EXAMPLES)/test_fcb_read_image.f90 \ $(EXAMPLES)/test_xds_binary.f90 # # Header files # HEADERS = $(INCLUDE)/cbf.h \ $(INCLUDE)/cbf_alloc.h \ $(INCLUDE)/cbf_ascii.h \ $(INCLUDE)/cbf_binary.h \ $(INCLUDE)/cbf_byte_offset.h \ $(INCLUDE)/cbf_canonical.h \ $(INCLUDE)/cbf_codes.h \ $(INCLUDE)/cbf_compress.h \ $(INCLUDE)/cbf_context.h \ $(INCLUDE)/cbf_copy.h \ $(INCLUDE)/cbf_file.h \ $(INCLUDE)/cbf_getopt.h \ $(INCLUDE)/cbf_lex.h \ $(INCLUDE)/cbf_packed.h \ $(INCLUDE)/cbf_predictor.h \ $(INCLUDE)/cbf_read_binary.h \ $(INCLUDE)/cbf_read_mime.h \ $(INCLUDE)/cbf_simple.h \ $(INCLUDE)/cbf_string.h \ $(INCLUDE)/cbf_stx.h \ $(INCLUDE)/cbf_tree.h \ $(INCLUDE)/cbf_uncompressed.h \ $(INCLUDE)/cbf_write.h \ $(INCLUDE)/cbf_write_binary.h \ $(INCLUDE)/cbf_ws.h \ $(INCLUDE)/global.h \ $(INCLUDE)/cbff.h \ $(INCLUDE)/md5.h # # m4 macro files # M4FILES = $(M4)/fcblib_defines.m4 \ $(M4)/fcb_exit_binary.m4 \ $(M4)/fcb_next_binary.m4 \ $(M4)/fcb_open_cifin.m4 \ $(M4)/fcb_packed.m4 \ $(M4)/fcb_read_bits.m4 \ $(M4)/fcb_read_image.m4 \ $(M4)/fcb_read_xds_i2.m4 \ $(M4)/test_fcb_read_image.m4 \ $(M4)/test_xds_binary.m4 # # Documentation files # DOCUMENTS = $(DOC)/CBFlib.html \ $(DOC)/CBFlib.txt \ $(DOC)/CBFlib_NOTICES.html \ $(DOC)/CBFlib_NOTICES.txt \ $(DOC)/ChangeLog \ $(DOC)/ChangeLog.html \ $(DOC)/MANIFEST \ $(DOC)/gpl.txt $(DOC)/lgpl.txt # # HTML Graphics files # JPEGS = $(GRAPHICS)/CBFbackground.jpg \ $(GRAPHICS)/CBFbig.jpg \ $(GRAPHICS)/CBFbutton.jpg \ $(GRAPHICS)/cbflibbackground.jpg \ $(GRAPHICS)/cbflibbig.jpg \ $(GRAPHICS)/cbflibbutton.jpg \ $(GRAPHICS)/cifhome.jpg \ $(GRAPHICS)/iucrhome.jpg \ $(GRAPHICS)/noticeButton.jpg # # Default: instructions # default: @echo ' ' @echo '***************************************************************' @echo ' ' @echo ' PLEASE READ README and doc/CBFlib_NOTICES.txt' @echo ' ' @echo ' Before making the CBF library and example programs, check' @echo ' that the C compiler name and flags are correct:' @echo ' ' @echo ' The current values are:' @echo ' ' @echo ' $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG)' @echo ' ' @echo ' Before installing the CBF library and example programs, check' @echo ' that the install directory is correct:' @echo ' ' @echo ' The current value :' @echo ' ' @echo ' $(INSTALLDIR) ' @echo ' ' @echo ' To compile the CBF library and example programs type:' @echo ' ' @echo ' make clean' @echo ' make all' @echo ' ' @echo ' To compile the CBF library as a shared object library, type:' @echo ' ' @echo ' make shared' @echo ' ' @echo ' To compile the Java wrapper classes for CBF library, type:' @echo ' ' @echo ' make javawrapper' @echo ' ' @echo ' To run a set of tests type:' @echo ' ' @echo ' make tests' @echo ' ' @echo ' To run some java tests type:' @echo ' ' @echo ' make javatests' @echo ' ' @echo ' The tests assume that several data files are in the directories' @echo ' $(DATADIRI) and $(DATADIRO)' @echo ' ' @echo ' Alternatively tests can be run comparing MD5 signatures only by' @echo ' ' @echo ' make tests_sigs_only' @echo ' ' @echo ' These signature only tests save space and download time by' @echo ' assuming that input data files and the output signatures' @echo ' are in the directories' @echo ' $(DATADIRI) and $(DATADIRS)' @echo ' ' @echo ' These directory can be obtained from' @echo ' ' @echo ' $(DATAURLI) ' @echo ' $(DATAURLO) ' @echo ' $(DATAURLS) ' @echo ' ' @echo ' To clean up the directories type:' @echo ' ' @echo ' make clean' @echo ' ' @echo ' To install the library and binaries type:' @echo ' ' @echo ' make install' @echo ' ' @echo '***************************************************************' @echo ' ' # # Compile the library and examples # all:: $(BIN) $(SOURCE) $(F90SOURCE) $(HEADERS) \ symlinksdone $(REGEXDEP) \ $(LIB)/libcbf.a \ $(LIB)/libfcb.a \ $(LIB)/libimg.a \ $(BIN)/adscimg2cbf \ $(BIN)/cbf2adscimg \ $(BIN)/convert_image \ $(BIN)/convert_minicbf \ $(BIN)/sequence_match \ $(BIN)/arvai_test \ $(BIN)/makecbf \ $(BIN)/img2cif \ $(BIN)/adscimg2cbf \ $(BIN)/cif2cbf \ $(BIN)/testcell \ $(BIN)/cif2c \ $(BIN)/testreals \ $(BIN)/testflat \ $(BIN)/testflatpacked ifneq ($(F90C),) all:: $(BIN)/test_xds_binary \ $(BIN)/test_fcb_read_image endif shared: $(SOLIB)/libcbf.so $(SOLIB)/libfcb.so $(SOLIB)/libimg.so javawrapper: shared $(JCBF) $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf_wrap.so ifneq ($(CBFLIB_USE_PYCIFRW),) PYCIFRWDEF = -Dcbf_use_pycifrw=yes else PYCIFRWDEF = endif Makefiles: Makefile \ Makefile_LINUX \ Makefile_LINUX_64 \ Makefile_LINUX_gcc42 \ Makefile_LINUX_DMALLOC \ Makefile_LINUX_gcc42_DMALLOC \ Makefile_OSX \ Makefile_OSX_gcc42 \ Makefile_OSX_gcc42_DMALLOC \ Makefile_AIX \ Makefile_MINGW \ Makefile_IRIX_gcc Makefile_LINUX: $(M4)/Makefile.m4 -cp Makefile_LINUX Makefile_LINUX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX $(M4)/Makefile.m4 > Makefile_LINUX Makefile_LINUX_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_LINUX Makefile_LINUX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_DMALLOC $(M4)/Makefile.m4 > Makefile_LINUX_DMALLOC Makefile_LINUX_64: $(M4)/Makefile.m4 -cp Makefile_LINUX_64 Makefile_LINUX_64_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_64 $(M4)/Makefile.m4 > Makefile_LINUX_64 Makefile_LINUX_gcc42: $(M4)/Makefile.m4 -cp Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_gcc42 $(M4)/Makefile.m4 > Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_gcc42_DMALLOC $(M4)/Makefile.m4 > Makefile_LINUX_gcc42_DMALLOC Makefile_OSX: $(M4)/Makefile.m4 -cp Makefile_OSX Makefile_OSX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX $(M4)/Makefile.m4 > Makefile_OSX Makefile_OSX_gcc42: $(M4)/Makefile.m4 -cp Makefile_OSX_gcc42 Makefile_OSX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX_gcc42 $(M4)/Makefile.m4 > Makefile_OSX_gcc42 Makefile_OSX_gcc42_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_OSX_gcc42 Makefile_OSX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX_gcc42_DMALLOC $(M4)/Makefile.m4 > Makefile_OSX_gcc42_DMALLOC Makefile_AIX: $(M4)/Makefile.m4 -cp Makefile_AIX Makefile_AIX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=AIX $(M4)/Makefile.m4 > Makefile_AIX Makefile_MINGW: $(M4)/Makefile.m4 -cp Makefile_MINGW Makefile_MINGW_old m4 -P $(PYCIFRWDEF) -Dcbf_system=MINGW $(M4)/Makefile.m4 > Makefile_MINGW Makefile_IRIX_gcc: $(M4)/Makefile.m4 -cp Makefile_IRIX_gcc Makefile_IRIX_gcc_old m4 -P $(PYCIFREDEF) -Dcbf_system=IRIX_gcc $(M4)/Makefile.m4 > Makefile_IRIX_gcc Makefile: $(M4)/Makefile.m4 -cp Makefile Makefile_old m4 -P $(PYCIFRWDEF) -Dcbf_system=default $(M4)/Makefile.m4 > Makefile symlinksdone: chmod a+x .symlinks chmod a+x .undosymlinks chmod a+x doc/.symlinks chmod a+x doc/.undosymlinks chmod a+x libtool/.symlinks chmod a+x libtool/.undosymlinks ./.symlinks $(SLFLAGS) touch symlinksdone install: all $(INSTALLDIR) $(INSTALLDIR)/lib $(INSTALLDIR)/bin \ $(INSTALLDIR)/include $(INSTALLDIR)/include/cbflib \ $(PYSOURCE) -chmod -R 755 $(INSTALLDIR)/include/cbflib -chmod 755 $(INSTALLDIR)/lib/libcbf.a -cp $(INSTALLDIR)/lib/libcbf.a $(INSTALLDIR)/lib/libcbf_old.a cp $(LIB)/libcbf.a $(INSTALLDIR)/lib/libcbf.a -cp $(INSTALLDIR)/lib/libimg.a $(INSTALLDIR)/lib/libimg_old.a cp $(LIB)/libimg.a $(INSTALLDIR)/lib/libimg.a -cp $(INSTALLDIR)/bin/adscimg2cbf $(INSTALLDIR)/bin/adscimg2cbf_old cp $(BIN)/adscimg2cbf $(INSTALLDIR)/bin/adscimg2cbf -cp $(INSTALLDIR)/bin/cbf2adscimg $(INSTALLDIR)/bin/cbf2adscimg_old cp $(BIN)/cbf2adscimg $(INSTALLDIR)/bin/cbf2adscimg -cp $(INSTALLDIR)/bin/convert_image $(INSTALLDIR)/bin/convert_image_old cp $(BIN)/convert_image $(INSTALLDIR)/bin/convert_image -cp $(INSTALLDIR)/bin/convert_minicbf $(INSTALLDIR)/bin/convert_minicbf_old cp $(BIN)/convert_minicbf $(INSTALLDIR)/bin/convert_minicbf -cp $(INSTALLDIR)/bin/makecbf $(INSTALLDIR)/bin/makecbf_old cp $(BIN)/makecbf $(INSTALLDIR)/bin/makecbf -cp $(INSTALLDIR)/bin/img2cif $(INSTALLDIR)/bin/img2cif_old cp $(BIN)/img2cif $(INSTALLDIR)/bin/img2cif -cp $(INSTALLDIR)/bin/cif2cbf $(INSTALLDIR)/bin/cif2cbf_old cp $(BIN)/cif2cbf $(INSTALLDIR)/bin/cif2cbf -cp $(INSTALLDIR)/bin/sequence_match $(INSTALLDIR)/bin/sequence_match_old cp $(BIN)/sequence_match $(INSTALLDIR)/bin/sequence_match -cp $(INSTALLDIR)/bin/arvai_test $(INSTALLDIR)/bin/arvai_test_old cp $(BIN)/arvai_test $(INSTALLDIR)/bin/arvai_test -cp $(INSTALLDIR)/bin/cif2c $(INSTALLDIR)/bin/cif2c_old cp $(BIN)/cif2c $(INSTALLDIR)/bin/cif2c -cp $(INSTALLDIR)/bin/testreals $(INSTALLDIR)/bin/testreals_old cp $(BIN)/testreals $(INSTALLDIR)/bin/testreals -cp $(INSTALLDIR)/bin/testflat $(INSTALLDIR)/bin/testflat_old cp $(BIN)/testflat $(INSTALLDIR)/bin/testflat -cp $(INSTALLDIR)/bin/testflatpacked $(INSTALLDIR)/bin/testflatpacked_old cp $(BIN)/testflatpacked $(INSTALLDIR)/bin/testflatpacked chmod -R 755 $(INSTALLDIR)/include/cbflib -rm -rf $(INSTALLDIR)/include/cbflib_old -cp -r $(INSTALLDIR)/include/cbflib $(INSTALLDIR)/include/cbflib_old -rm -rf $(INSTALLDIR)/include/cbflib cp -r $(INCLUDE) $(INSTALLDIR)/include/cbflib chmod 644 $(INSTALLDIR)/lib/libcbf.a chmod 755 $(INSTALLDIR)/bin/convert_image chmod 755 $(INSTALLDIR)/bin/convert_minicbf chmod 755 $(INSTALLDIR)/bin/makecbf chmod 755 $(INSTALLDIR)/bin/img2cif chmod 755 $(INSTALLDIR)/bin/cif2cbf chmod 755 $(INSTALLDIR)/bin/sequence_match chmod 755 $(INSTALLDIR)/bin/arvai_test chmod 755 $(INSTALLDIR)/bin/cif2c chmod 755 $(INSTALLDIR)/bin/testreals chmod 755 $(INSTALLDIR)/bin/testflat chmod 755 $(INSTALLDIR)/bin/testflatpacked chmod 644 $(INSTALLDIR)/include/cbflib/*.h # # REGEX # ifneq ($(REGEXDEP),) $(REGEXDEP): $(REGEX) (cd $(REGEX); ./configure; make install) endif $(REGEX): $(DOWNLOAD) $(REGEXURL) tar -xvf $(REGEX).tar.gz -rm $(REGEX).tar.gz # # TIFF # $(TIFF): $(DOWNLOAD) $(TIFFURL) tar -xvf $(TIFF).tar.gz -rm $(TIFF).tar.gz (cd $(TIFF); ./configure --prefix=$(TIFFPREFIX); make install) # # Directories # $(INSTALLDIR): mkdir -p $(INSTALLDIR) $(INSTALLDIR)/lib: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/lib $(INSTALLDIR)/bin: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/bin $(INSTALLDIR)/include: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/include $(INSTALLDIR)/include/cbflib: $(INSTALLDIR)/include mkdir -p $(INSTALLDIR)/include/cbflib $(LIB): mkdir $@ $(BIN): mkdir $@ $(SOLIB): mkdir $@ $(JCBF): mkdir $@ # # Parser # $(SRC)/cbf_stx.c: $(SRC)/cbf.stx.y bison $(SRC)/cbf.stx.y -o $(SRC)/cbf.stx.tab.c -d mv $(SRC)/cbf.stx.tab.c $(SRC)/cbf_stx.c mv $(SRC)/cbf.stx.tab.h $(INCLUDE)/cbf_stx.h # # CBF library # $(LIB)/libcbf.a: $(SOURCE) $(HEADERS) $(COMMONDEP) $(LIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG) $(INCLUDES) $(WARNINGS) -c $(SOURCE) $(AR) cr $@ *.o mv *.o $(LIB) ifneq ($(RANLIB),) $(RANLIB) $@ endif $(SOLIB)/libcbf.so: $(SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(SOURCE) $(CC) -o $@ *.o $(SOLDFLAGS) $(EXTRALIBS) rm *.o # # IMG library # $(LIB)/libimg.a: $(EXAMPLES)/img.c $(HEADERS) $(COMMONDEP) $(LIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) -c $(EXAMPLES)/img.c $(AR) cr $@ img.o ifneq ($(RANLIB),) $(RANLIB) $@ endif rm img.o $(SOLIB)/libimg.so: $(SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(EXAMPLES)/img.c $(CC) -o $@ img.o $(SOLDFLAGS) rm img.o # # CBF and IMG libraries # CBF_IMG_LIBS: $(LIB)/libcbf.a $(LIB)/libimg.a # # FCB library # $(LIB)/libfcb.a: $(F90SOURCE) $(COMMONDEP) $(LIB) ifneq ($(F90C),) $(F90C) $(F90FLAGS) -c $(F90SOURCE) $(AR) cr $@ *.o ifneq ($(RANLIB),) $(RANLIB) $@ endif rm *.o else echo "Define F90C to build $(LIB)/libfcb.a" endif $(SOLIB)/libfcb.so: $(F90SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) ifneq ($(F90C),) $(F90C) $(F90FLAGS) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(F90SOURCE) $(F90C) $(F90FLAGS) -o $@ *.o $(SOLDFLAGS) rm *.o else echo "Define F90C to build $(SOLIB)/libfcb.so" endif # # Python bindings # $(PYCBF)/_pycbf.$(PYCBFEXT): $(PYCBF) $(LIB)/libcbf.a \ $(PYCBF)/$(SETUP_PY) \ $(LIB)/libfcb.a \ $(LIB)/libimg.a \ $(PYCBF)/pycbf.i \ $(PYCBF)/cbfhandlewrappers.i \ $(PYCBF)/cbfdetectorwrappers.i \ $(PYCBF)/cbfgenericwrappers.i \ $(PYCBF)/cbfgoniometerwrappers.i (cd $(PYCBF); python $(SETUP_PY) build $(PYCBFBOPT); cp build/lib.*/_pycbf.$(PYCBFEXT) .) $(PYCBF)/setup.py: $(M4)/setup_py.m4 (m4 -P -Dregexlib=NOREGEXLIB -Dregexlibdir=NOREGEXLIBDIR $(M4)/setup_py.m4 > $@) $(PYCBF)/setup_MINGW.py: m4/setup_py.m4 (m4 -P -Dregexlib=regex -Dregexlibdir=$(REGEXDIR) $(M4)/setup_py.m4 > $@) $(LIB)/_pycbf.$(PYCBFEXT): $(PYCBF)/_pycbf.$(PYCBFEXT) cp $(PYCBF)/_pycbf.$(PYCBFEXT) $(LIB)/_pycbf.$(PYCBFEXT) $(PYCBF)/pycbf.pdf: $(PYCBF)/pycbf.w (cd $(PYCBF); \ $(NUWEB) pycbf; \ latex pycbf; \ $(NUWEB) pycbf; \ latex pycbf; \ dvipdfm pycbf ) $(PYCBF)/CBFlib.txt: $(DOC)/CBFlib.html links -dump $(DOC)/CBFlib.html > $(PYCBF)/CBFlib.txt $(PYCBF)/cbfhandlewrappers.i \ $(PYCBF)/cbfdetectorwrappers.i \ $(PYCBF)/cbfgenericwrappers.i \ $(PYCBF)/cbfgoniometerwrappers.i: $(PYCBF)/CBFlib.txt $(PYCBF)/make_pycbf.py (cd $(PYCBF); python make_pycbf.py; $(PYSWIG) pycbf.i; python setup.py build) # # Java bindings # $(JCBF)/cbflib-$(VERSION).jar: $(JCBF) $(JCBF)/jcbf.i $(JSWIG) -I$(INCLUDE) -package org.iucr.cbflib -outdir $(JCBF) $(JCBF)/jcbf.i $(JAVAC) -d . $(JCBF)/*.java $(JAR) cf $@ org $(SOLIB)/libcbf_wrap.so: $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf.so $(CC) $(CFLAGS) $(NOLLFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) $(JAVAINCLUDES) -c $(JCBF)/jcbf_wrap.c $(CC) -o $@ jcbf_wrap.o $(SOLDFLAGS) -L$(SOLIB) -lcbf rm jcbf_wrap.o # # F90SOURCE # $(SRC)/fcb_exit_binary.f90: $(M4)/fcb_exit_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_exit_binary.m4) > $(SRC)/fcb_exit_binary.f90 $(SRC)/fcb_next_binary.f90: $(M4)/fcb_next_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_next_binary.m4) > $(SRC)/fcb_next_binary.f90 $(SRC)/fcb_open_cifin.f90: $(M4)/fcb_open_cifin.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_open_cifin.m4) > $(SRC)/fcb_open_cifin.f90 $(SRC)/fcb_packed.f90: $(M4)/fcb_packed.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_packed.m4) > $(SRC)/fcb_packed.f90 $(SRC)/fcb_read_bits.f90: $(M4)/fcb_read_bits.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_bits.m4) > $(SRC)/fcb_read_bits.f90 $(SRC)/fcb_read_image.f90: $(M4)/fcb_read_image.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_image.m4) > $(SRC)/fcb_read_image.f90 $(SRC)/fcb_read_xds_i2.f90: $(M4)/fcb_read_xds_i2.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_xds_i2.m4) > $(SRC)/fcb_read_xds_i2.f90 $(EXAMPLES)/test_fcb_read_image.f90: $(M4)/test_fcb_read_image.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) test_fcb_read_image.m4) > $(EXAMPLES)/test_fcb_read_image.f90 $(EXAMPLES)/test_xds_binary.f90: $(M4)/test_xds_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) test_xds_binary.m4) > $(EXAMPLES)/test_xds_binary.f90 # # convert_image example program # $(BIN)/convert_image: $(LIB)/libcbf.a $(EXAMPLES)/convert_image.c $(EXAMPLES)/img.c \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/convert_image.c $(EXAMPLES)/img.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # convert_minicbf example program # $(BIN)/convert_minicbf: $(LIB)/libcbf.a $(EXAMPLES)/convert_minicbf.c \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/convert_minicbf.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # makecbf example program # $(BIN)/makecbf: $(LIB)/libcbf.a $(EXAMPLES)/makecbf.c $(LIB)/libimg.a $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/makecbf.c -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # adscimg2cbf example program # $(BIN)/adscimg2cbf: $(LIB)/libcbf.a $(EXAMPLES)/adscimg2cbf.c $(EXAMPLES)/adscimg2cbf_sub.c $(CC) $(CFLAGS) $(NOLLFLAG) -D_SVID_SOURCE $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/adscimg2cbf.c $(EXAMPLES)/adscimg2cbf_sub.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # cbf2adscimg example program # $(BIN)/cbf2adscimg: $(LIB)/libcbf.a $(EXAMPLES)/cbf2adscimg.c $(EXAMPLES)/cbf2adscimg_sub.c $(CC) $(CFLAGS) $(NOLLFLAG) -D_SVID_SOURCE $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cbf2adscimg.c $(EXAMPLES)/cbf2adscimg_sub.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # changtestcompression example program # $(BIN)/changtestcompression: $(LIB)/libcbf.a $(EXAMPLES)/changtestcompression.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/changtestcompression.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # img2cif example program # $(BIN)/img2cif: $(LIB)/libcbf.a $(EXAMPLES)/img2cif.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOTPINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/img2cif.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # cif2cbf example program # $(BIN)/cif2cbf: $(LIB)/libcbf.a $(EXAMPLES)/cif2cbf.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cif2cbf.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # dectris cbf_template_t program # $(BIN)/cbf_template_t: $(DECTRIS_EXAMPLES)/cbf_template_t.c \ $(DECTRIS_EXAMPLES)/mx_cbf_t_extras.h \ $(DECTRIS_EXAMPLES)/mx_parms.h $(CC) $(CFLAGS) $(NOLLFLAG) -I $(DECTRIS_EXAMPLES) $(WARNINGS) \ $(DECTRIS_EXAMPLES)/cbf_template_t.c -o $@ # # testcell example program # $(BIN)/testcell: $(LIB)/libcbf.a $(EXAMPLES)/testcell.C $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testcell.C -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # cif2c example program # $(BIN)/cif2c: $(LIB)/libcbf.a $(EXAMPLES)/cif2c.c $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cif2c.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # sauter_test example program # $(BIN)/sauter_test: $(LIB)/libcbf.a $(EXAMPLES)/sauter_test.C $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/sauter_test.C -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # sequence_match example program # $(BIN)/sequence_match: $(LIB)/libcbf.a $(EXAMPLES)/sequence_match.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/sequence_match.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # tiff2cbf example program # $(BIN)/tiff2cbf: $(LIB)/libcbf.a $(EXAMPLES)/tiff2cbf.c \ $(GOPTLIB) $(GOPTINC) $(TIFF) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ -I$(TIFFPREFIX)/include $(EXAMPLES)/tiff2cbf.c $(GOPTLIB) -L$(LIB) \ -lcbf -L$(TIFFPREFIX)/lib -ltiff $(EXTRALIBS) -limg -o $@ # # Andy Arvai's buffered read test program # $(BIN)/arvai_test: $(LIB)/libcbf.a $(EXAMPLES)/arvai_test.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/arvai_test.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # testreals example program # $(BIN)/testreals: $(LIB)/libcbf.a $(EXAMPLES)/testreals.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testreals.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testflat example program # $(BIN)/testflat: $(LIB)/libcbf.a $(EXAMPLES)/testflat.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testflat.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testflatpacked example program # $(BIN)/testflatpacked: $(LIB)/libcbf.a $(EXAMPLES)/testflatpacked.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testflatpacked.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ ifneq ($(F90C),) # # test_xds_binary example program # $(BIN)/test_xds_binary: $(LIB)/libfcb.a $(EXAMPLES)/test_xds_binary.f90 $(F90C) $(F90FLAGS) $(F90LDFLAGS) $(EXAMPLES)/test_xds_binary.f90 \ -L$(LIB) -lfcb -o $@ # # test_fcb_read_image example program # $(BIN)/test_fcb_read_image: $(LIB)/libfcb.a $(EXAMPLES)/test_fcb_read_image.f90 $(F90C) $(F90FLAGS) $(F90LDFLAGS) $(EXAMPLES)/test_fcb_read_image.f90 \ -L$(LIB) -lfcb -o $@ endif # # testcbf (C) # $(BIN)/ctestcbf: $(EXAMPLES)/testcbf.c $(LIB)/libcbf.a $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testcbf.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testcbf (Java) # $(BIN)/testcbf.class: $(EXAMPLES)/testcbf.java $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf_wrap.so $(JAVAC) -cp $(JCBF)/cbflib-$(VERSION).jar -d $(BIN) $(EXAMPLES)/testcbf.java # # Data files for tests # $(DATADIRI): (cd ..; $(DOWNLOAD) $(DATAURLI)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Input.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Input.tar.gz) $(DATADIRO): (cd ..; $(DOWNLOAD) $(DATAURLO)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Output.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Output.tar.gz) $(DATADIRS): (cd ..; $(DOWNLOAD) $(DATAURLS)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz) # Input Data Files TESTINPUT_BASIC = example.mar2300 DATADIRI_INPUT_BASIC = $(DATADIRI)/example.mar2300$(CEXT) TESTINPUT_EXTRA = 9ins.cif mb_LP_1_001.img insulin_pilatus6m.cbf testrealin.cbf \ testflatin.cbf testflatpackedin.cbf XRD1621.tif DATADIRI_INPUT_EXTRA = $(DATADIRI)/9ins.cif$(CEXT) $(DATADIRI)/mb_LP_1_001.img$(CEXT) \ $(DATADIRI)/insulin_pilatus6m.cbf$(CEXT) $(DATADIRI)/testrealin.cbf$(CEXT) \ $(DATADIRI)/testflatin.cbf$(CEXT) $(DATADIRI)/testflatpackedin.cbf$(CEXT) \ $(DATADIRI)/XRD1621.tif$(CEXT) # Output Data Files TESTOUTPUT = adscconverted_flat_orig.cbf \ adscconverted_orig.cbf converted_flat_orig.cbf converted_orig.cbf \ insulin_pilatus6mconverted_orig.cbf \ mb_LP_1_001_orig.cbf testcell_orig.prt \ test_xds_bin_testflatout_orig.out \ test_xds_bin_testflatpackedout_orig.out test_fcb_read_testflatout_orig.out \ test_fcb_read_testflatpackedout_orig.out \ XRD1621_orig.cbf XRD1621_I4encbC100_orig.cbf NEWTESTOUTPUT = adscconverted_flat.cbf \ adscconverted.cbf converted_flat.cbf converted.cbf \ insulin_pilatus6mconverted.cbf \ mb_LP_1_001.cbf testcell.prt \ test_xds_bin_testflatout.out \ test_xds_bin_testflatpackedout.out test_fcb_read_testflatout.out \ test_fcb_read_testflatpackedout.out \ XRD1621.cbf XRD1621_I4encbC100.cbf DATADIRO_OUTPUT = $(DATADIRO)/adscconverted_flat_orig.cbf$(CEXT) \ $(DATADIRO)/adscconverted_orig.cbf$(CEXT) \ $(DATADIRO)/converted_flat_orig.cbf$(CEXT) \ $(DATADIRO)/converted_orig.cbf$(CEXT) \ $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(CEXT) \ $(DATADIRO)/mb_LP_1_001_orig.cbf$(CEXT) \ $(DATADIRO)/testcell_orig.prt$(CEXT) \ $(DATADIRO)/test_xds_bin_testflatout_orig.out$(CEXT) \ $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(CEXT) \ $(DATADIRO)/test_fcb_read_testflatout_orig.out$(CEXT) \ $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(CEXT) \ $(DATADIRO)/XRD1621_orig.cbf$(CEXT) \ $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(CEXT) DATADIRO_OUTPUT_SIGNATURES = $(DATADIRO)/adscconverted_flat_orig.cbf$(SEXT) \ $(DATADIRO)/adscconverted_orig.cbf$(SEXT) \ $(DATADIRO)/converted_flat_orig.cbf$(SEXT) \ $(DATADIRO)/converted_orig.cbf$(SEXT) \ $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(SEXT) \ $(DATADIRO)/mb_LP_1_001_orig.cbf$(SEXT) \ $(DATADIRO)/testcell_orig.prt$(SEXT) \ $(DATADIRO)/test_xds_bin_testflatout_orig.out$(SEXT) \ $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(SEXT) \ $(DATADIRO)/test_fcb_read_testflatout_orig.out$(SEXT) \ $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(SEXT) \ $(DATADIRO)/XRD1621_orig.cbf$(SEXT) \ $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(SEXT) # Output Data File Signatures TESTOUTPUTSIGS = adscconverted_flat_orig.cbf$(SEXT) \ adscconverted_orig.cbf$(SEXT) converted_flat_orig.cbf$(SEXT) converted_orig.cbf$(SEXT) \ insulin_pilatus6mconverted_orig.cbf$(SEXT) \ mb_LP_1_001_orig.cbf$(SEXT) testcell_orig.prt$(SEXT) \ test_xds_bin_testflatout_orig.out$(SEXT) \ test_xds_bin_testflatpackedout_orig.out$(SEXT) test_fcb_read_testflatout_orig.out$(SEXT) \ test_fcb_read_testflatpackedout_orig.out$(SEXT) \ XRD1621_orig.cbf$(SEXT) DATADIRS_OUTPUT_SIGNATURES = $(DATADIRS)/adscconverted_flat_orig.cbf$(SEXT) \ $(DATADIRS)/adscconverted_orig.cbf$(SEXT) \ $(DATADIRS)/converted_flat_orig.cbf$(SEXT) \ $(DATADIRS)/converted_orig.cbf$(SEXT) \ $(DATADIRS)/insulin_pilatus6mconverted_orig.cbf$(SEXT) \ $(DATADIRS)/mb_LP_1_001_orig.cbf$(SEXT) \ $(DATADIRS)/testcell_orig.prt$(SEXT) \ $(DATADIRS)/test_xds_bin_testflatout_orig.out$(SEXT) \ $(DATADIRS)/test_xds_bin_testflatpackedout_orig.out$(SEXT) \ $(DATADIRS)/test_fcb_read_testflatout_orig.out$(SEXT) \ $(DATADIRS)/test_fcb_read_testflatpackedout_orig.out$(SEXT) \ $(DATADIRS)/XRD1621_orig.cbf$(SEXT) \ $(DATADIRS)/XRD1621_I4encbC100_orig.cbf$(SEXT) # Fetch Input Data Files $(TESTINPUT_BASIC): $(DATADIRI) $(DATADIRI_INPUT_BASIC) $(DECOMPRESS) < $(DATADIRI)/$@$(CEXT) > $@ cp $(DATADIRI)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) $(TESTINPUT_EXTRA): $(DATADIRI) $(DATADIRI_INPUT_EXTRA) $(DECOMPRESS) < $(DATADIRI)/$@$(CEXT) > $@ cp $(DATADIRI)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) # Fetch Output Data Files and Signatures $(TESTOUTPUT): $(DATADIRO) $(DATADIRO_OUTPUT) $(DATADIRO_OUTPUT_SIGNATURES) $(DECOMPRESS) < $(DATADIRO)/$@$(CEXT) > $@ cp $(DATADIRO)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) # Fetch Output Data File Signatures $(TESTOUTPUTSIGS): $(DATADIRS) $(DATADIRS_OUTPUT_SIGNATURES) cp $(DATADIRS)/$@ $@ # # Tests # tests: $(LIB) $(BIN) symlinksdone basic extra dectristests pycbftests tests_sigs_only: $(LIB) $(BIN) symlinksdone basic extra_sigs_only restore_output: $(NEWTESTOUTPUT) $(DATADIRO) $(SIGNATURE) < adscconverted_flat.cbf > $(DATADIRO)/adscconverted_flat_orig.cbf$(SEXT) $(SIGNATURE) < adscconverted.cbf > $(DATADIRO)/adscconverted_orig.cbf$(SEXT) $(SIGNATURE) < converted_flat.cbf > $(DATADIRO)/converted_flat_orig.cbf$(SEXT) $(SIGNATURE) < converted.cbf > $(DATADIRO)/converted_orig.cbf$(SEXT) $(SIGNATURE) < insulin_pilatus6mconverted.cbf > $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(SEXT) $(SIGNATURE) < mb_LP_1_001.cbf$ > $(DATADIRO)/mb_LP_1_001_orig.cbf$(SEXT) $(SIGNATURE) < testcell.prt > $(DATADIRO)/testcell_orig.prt$(SEXT) $(SIGNATURE) < test_xds_bin_testflatout.out > $(DATADIRO)/test_xds_bin_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_xds_bin_testflatpackedout.out > $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatout.out > $(DATADIRO)/test_fcb_read_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatpackedout.out > $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < XRD1621.cbf > $(DATADIRO)/XRD1621_orig.cbf$(SEXT) $(SIGNATURE) < XRD1621_I4encbC100.cbf > $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(SEXT) $(COMPRESS) < adscconverted_flat.cbf > $(DATADIRO)/adscconverted_flat_orig.cbf$(CEXT) $(COMPRESS) < adscconverted.cbf > $(DATADIRO)/adscconverted_orig.cbf$(CEXT) $(COMPRESS) < converted_flat.cbf > $(DATADIRO)/converted_flat_orig.cbf$(CEXT) $(COMPRESS) < converted.cbf > $(DATADIRO)/converted_orig.cbf$(CEXT) $(COMPRESS) < insulin_pilatus6mconverted.cbf > $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(CEXT) $(COMPRESS) < mb_LP_1_001.cbf$ > $(DATADIRO)/mb_LP_1_001_orig.cbf$(CEXT) $(COMPRESS) < testcell.prt > $(DATADIRO)/testcell_orig.prt$(CEXT) $(COMPRESS) < test_xds_bin_testflatout.out > $(DATADIRO)/test_xds_bin_testflatout_orig.out$(CEXT) $(COMPRESS) < test_xds_bin_testflatpackedout.out > $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(CEXT) $(COMPRESS) < test_fcb_read_testflatout.out > $(DATADIRO)/test_fcb_read_testflatout_orig.out$(CEXT) $(COMPRESS) < test_fcb_read_testflatpackedout.out > $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(CEXT) $(COMPRESS) < XRD1621.cbf > $(DATADIRO)/XRD1621_orig.cbf$(CEXT) $(COMPRESS) < XRD1621_I4encbC100.cbf > $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(CEXT) restore_sigs_only: $(NEWTESTOUTPUT) $(DATADIRS) $(SIGNATURE) < adscconverted_flat.cbf > $(DATADIRS)/adscconverted_flat_orig.cbf$(SEXT) $(SIGNATURE) < adscconverted.cbf > $(DATADIRS)/adscconverted_orig.cbf$(SEXT) $(SIGNATURE) < converted_flat.cbf > $(DATADIRS)/converted_flat_orig.cbf$(SEXT) $(SIGNATURE) < converted.cbf > $(DATADIRS)/converted_orig.cbf$(SEXT) $(SIGNATURE) < insulin_pilatus6mconverted.cbf > $(DATADIRS)/insulin_pilatus6mconverted_orig.cbf$(SEXT) $(SIGNATURE) < mb_LP_1_001.cbf$ > $(DATADIRS)/mb_LP_1_001_orig.cbf$(SEXT) $(SIGNATURE) < testcell.prt > $(DATADIRS)/testcell_orig.prt$(SEXT) $(SIGNATURE) < test_xds_bin_testflatout.out > $(DATADIRS)/test_xds_bin_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_xds_bin_testflatpackedout.out > $(DATADIRS)/test_xds_bin_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatout.out > $(DATADIRS)/test_fcb_read_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatpackedout.out > $(DATADIRS)/test_fcb_read_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < XRD1621.cbf > $(DATADIRS)/XRD1621_orig.cbf$(SEXT) $(SIGNATURE) < XRD1621_I4encbC100.cbf > $(DATADIRS)/XRD1621_I4encbC100_orig.cbf$(SEXT) restore_signatures: restore_output restore_sigs_only # # Basic Tests # basic: $(BIN)/makecbf $(BIN)/img2cif $(BIN)/cif2cbf $(TESTINPUT_BASIC) $(BIN)/makecbf example.mar2300 makecbf.cbf $(BIN)/img2cif -c flatpacked -m headers -d digest \ -e base64 example.mar2300 img2cif_packed.cif $(BIN)/img2cif -c canonical -m headers -d digest \ -e base64 example.mar2300 img2cif_canonical.cif $(BIN)/img2cif -c flatpacked -m headers -d digest \ -e none example.mar2300 img2cif_packed.cbf $(BIN)/img2cif -c canonical -m headers -d digest \ -e none example.mar2300 img2cif_canonical.cbf $(BIN)/cif2cbf -e none -c flatpacked \ img2cif_canonical.cif cif2cbf_packed.cbf $(BIN)/cif2cbf -e none -c canonical \ img2cif_packed.cif cif2cbf_canonical.cbf -cmp cif2cbf_packed.cbf makecbf.cbf -cmp cif2cbf_packed.cbf img2cif_packed.cbf -cmp cif2cbf_canonical.cbf img2cif_canonical.cbf # # Extra Tests # ifneq ($(F90C),) extra: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/test_xds_binary $(BIN)/test_fcb_read_image $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg \ $(BIN)/changtestcompression $(BIN)/tiff2cbf \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUT) else extra: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUT) endif $(TIME) $(BIN)/cif2cbf -e hex -c none \ makecbf.cbf cif2cbf_ehcn.cif $(TIME) $(BIN)/cif2cbf -e none -c flatpacked \ cif2cbf_ehcn.cif cif2cbf_encp.cbf; rm cif2cbf_ehcn.cif -cmp makecbf.cbf cif2cbf_encp.cbf $(TIME) $(BIN)/cif2cbf -i 9ins.cif -o 9ins.cbf -cmp 9ins.cif 9ins.cbf $(TIME) $(BIN)/convert_image -F example.mar2300 converted_flat.cbf -cmp converted_flat.cbf converted_flat_orig.cbf $(TIME) $(BIN)/convert_image example.mar2300 converted.cbf -cmp converted.cbf converted_orig.cbf -$(TIME) $(BIN)/testcell < testcell.dat > testcell.prt -cmp testcell.prt testcell_orig.prt $(TIME) $(BIN)/convert_image -F -d adscquantum315 mb_LP_1_001.img adscconverted_flat.cbf -cmp adscconverted_flat.cbf adscconverted_flat_orig.cbf $(TIME) $(BIN)/convert_image -d adscquantum315 mb_LP_1_001.img adscconverted.cbf -cmp adscconverted.cbf adscconverted_orig.cbf $(TIME) $(BIN)/adscimg2cbf --no_pad --cbf_packed,flat mb_LP_1_001.img -cmp mb_LP_1_001.cbf mb_LP_1_001_orig.cbf ifneq ($(CLEANTESTS),) mv mb_LP_1_001.cbf nmb_LP_1_001.cbf else cp mb_LP_1_001.cbf nmb_LP_1_001.cbf endif $(TIME) $(BIN)/cbf2adscimg nmb_LP_1_001.cbf -cmp nmb_LP_1_001.img mb_LP_1_001.img rm nmb_LP_1_001.cbf ifneq ($(CLEANTESTS),) rm nmb_LP_1_001.img endif $(TIME) $(BIN)/convert_minicbf -d pilatus6m insulin_pilatus6m.cbf insulin_pilatus6mconverted.cbf -cmp insulin_pilatus6mconverted.cbf insulin_pilatus6mconverted_orig.cbf $(TIME) $(BIN)/testreals -cmp testrealin.cbf testrealout.cbf $(TIME) $(BIN)/testflat -cmp testflatin.cbf testflatout.cbf $(TIME) $(BIN)/testflatpacked -cmp testflatpackedin.cbf testflatpackedout.cbf ifneq ($(F90C),) echo testflatout.cbf | $(TIME) $(BIN)/test_xds_binary > test_xds_bin_testflatout.out -$(DIFF) test_xds_bin_testflatout.out test_xds_bin_testflatout_orig.out echo testflatpackedout.cbf | $(TIME) $(BIN)/test_xds_binary > test_xds_bin_testflatpackedout.out -$(DIFF) test_xds_bin_testflatpackedout.out test_xds_bin_testflatpackedout_orig.out echo testflatout.cbf | $(TIME) $(BIN)/test_fcb_read_image > test_fcb_read_testflatout.out -$(DIFF) test_fcb_read_testflatout.out test_fcb_read_testflatout_orig.out echo testflatpackedout.cbf | $(TIME) $(BIN)/test_fcb_read_image > test_fcb_read_testflatpackedout.out -$(DIFF) test_fcb_read_testflatpackedout.out test_fcb_read_testflatpackedout_orig.out endif $(TIME) $(BIN)/sauter_test $(TIME) $(BIN)/changtestcompression $(TIME) (export LD_LIBRARY_PATH=$(LIB);$(BIN)/tiff2cbf XRD1621.tif XRD1621.cbf) -$(DIFF) XRD1621.cbf XRD1621_orig.cbf $(TIME) $(BIN)/cif2cbf -I 4 -C 100. -L 0. -e n -c b -i XRD1621.cbf -o XRD1621_I4encbC100.cbf -$(DIFF) XRD1621_I4encbC100.cbf XRD1621_I4encbC100_orig.cbf ifneq ($(F90C),) extra_sigs_only: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/test_xds_binary $(BIN)/test_fcb_read_image $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg $(BIN)/tiff2cbf \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) else extra_sigs_only: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf\ basic $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) endif $(TIME) $(BIN)/cif2cbf -e hex -c none \ makecbf.cbf cif2cbf_ehcn.cif $(TIME) $(BIN)/cif2cbf -e none -c packed \ cif2cbf_ehcn.cif cif2cbf_encp.cbf; rm cif2cbf_ehcn.cif -cmp makecbf.cbf cif2cbf_encp.cbf $(TIME) $(BIN)/cif2cbf -i 9ins.cif -o 9ins.cbf -cmp 9ins.cif 9ins.cbf $(TIME) $(BIN)/convert_image -F example.mar2300 converted_flat.cbf -$(SIGNATURE) < converted_flat.cbf | $(DIFF) - converted_flat_orig.cbf$(SEXT); rm converted_flat.cbf $(TIME) $(BIN)/convert_image example.mar2300 converted.cbf -$(SIGNATURE) < converted.cbf | $(DIFF) - converted_orig.cbf$(SEXT); rm converted.cbf -$(TIME) $(BIN)/testcell < testcell.dat | \ $(SIGNATURE) | $(DIFF) - testcell_orig.prt$(SEXT) $(TIME) $(BIN)/convert_image -F -d adscquantum315 mb_LP_1_001.img adscconverted_flat.cbf -$(SIGNATURE) < adscconverted_flat.cbf | $(DIFF) - adscconverted_flat_orig.cbf$(SEXT) $(TIME) $(BIN)/convert_image -d adscquantum315 mb_LP_1_001.img adscconverted.cbf -$(SIGNATURE) < adscconverted.cbf | $(DIFF) - adscconverted_orig.cbf$(SEXT); rm adscconverted.cbf $(TIME) $(BIN)/adscimg2cbf --cbf_packed,flat mb_LP_1_001.img -$(SIGNATURE) < mb_LP_1_001.cbf | $(DIFF) - mb_LP_1_001_orig.cbf$(SEXT) mv mb_LP_1_001.cbf nmb_LP_1_001.cbf $(TIME) $(BIN)/cbf2adscimg nmb_LP_1_001.cbf -cmp nmb_LP_1_001.img mb_LP_1_001.img rm nmb_LP_1_001.cbf rm nmb_LP_1_001.img $(TIME) $(BIN)/convert_minicbf -d pilatus6m insulin_pilatus6m.cbf insulin_pilatus6mconverted.cbf -$(SIGNATURE) < insulin_pilatus6mconverted.cbf | $(DIFF) - insulin_pilatus6mconverted_orig.cbf$(SEXT); rm insulin_pilatus6mconverted.cbf $(TIME) $(BIN)/testreals -cmp testrealin.cbf testrealout.cbf $(TIME) $(BIN)/testflat -cmp testflatin.cbf testflatout.cbf $(TIME) $(BIN)/testflatpacked -cmp testflatpackedin.cbf testflatpackedout.cbf ifneq ($(F90C),) echo testflatout.cbf | $(TIME) $(BIN)/test_xds_binary | \ $(SIGNATURE) | $(DIFF) - test_xds_bin_testflatout_orig.out$(SEXT) echo testflatpackedout.cbf | $(TIME) $(BIN)/test_xds_binary | \ $(SIGNATURE) | $(DIFF) - test_xds_bin_testflatpackedout_orig.out$(SEXT) echo testflatout.cbf | $(TIME) $(BIN)/test_fcb_read_image | \ $(SIGNATURE) | $(DIFF) - test_fcb_read_testflatout_orig.out$(SEXT) echo testflatpackedout.cbf | $(TIME) $(BIN)/test_fcb_read_image | \ $(SIGNATURE) | $(DIFF) - test_fcb_read_testflatpackedout_orig.out$(SEXT) endif $(TIME) $(BIN)/sauter_test $(TIME) $(BIN)/tiff2cbf XRD1621.tif XRD1621.cbf $(TIME) $(BIN)/cif2cbf -I 4 -C 100. -L 0. -e n -c b -i XRD1621.cbf -o XRD1621_I4encbC100.cbf -$(SIGNATURE) < XRD1621.cbf | $(DIFF) - XRD1621_orig.cbf$(SEXT); rm XRD1621.cbf -$(SIGNATURE) < XRD1621_I4encbC100.cbf | $(DIFF) - XRD1621_I4encbC100_orig.cbf$(SEXT); rm XRD1621_I4encbC100.cbf @-rm -f adscconverted_flat.cbf @-rm -f $(TESTINPUT_BASIC) $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) @-rm -f cif2cbf_packed.cbf makecbf.cbf \ cif2cbf_packed.cbf img2cif_packed.cbf \ cif2cbf_canonical.cbf img2cif_canonical.cbf @-rm -f testrealout.cbf testflatout.cbf testflatpackedout.cbf \ cif2cbf_encp.cbf img2cif_canonical.cif img2cif_packed.cif 9ins.cbf pycbftests: $(PYCBF)/_pycbf.$(PYCBFEXT) (cd $(PYCBF); python pycbf_test1.py) (cd $(PYCBF); python pycbf_test2.py) (cd $(PYCBF); python pycbf_test3.py) javatests: $(BIN)/ctestcbf $(BIN)/testcbf.class $(SOLIB)/libcbf_wrap.so $(BIN)/ctestcbf > testcbfc.txt $(LDPREFIX) java -cp $(JCBF)/cbflib-$(VERSION).jar:$(BIN) testcbf > testcbfj.txt $(DIFF) testcbfc.txt testcbfj.txt dectristests: $(BIN)/cbf_template_t $(DECTRIS_EXAMPLES)/cbf_test_orig.out (cd $(DECTRIS_EXAMPLES); ../../bin/cbf_template_t; diff -a -u cbf_test_orig.out cbf_template_t.out) # # Remove all non-source files # empty: @-rm -f $(LIB)/*.o @-rm -f $(LIB)/libcbf.a @-rm -f $(LIB)/libfcb.a @-rm -f $(LIB)/libimg.a @-rm -f $(LIB)/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/build/*/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/build/src/cbf_simple.o @-rm -f $(PYCBF)/build/*/pycbf_wrap.o @-rm -rf $(BIN)/adscimg2cbf* @-rm -rf $(BIN)/cbf2adscimg* @-rm -rf $(BIN)/makecbf* @-rm -rf $(BIN)/img2cif* @-rm -rf $(BIN)/cif2cbf* @-rm -rf $(BIN)/convert_image* @-rm -rf $(BIN)/convert_minicbf* @-rm -rf $(BIN)/test_fcb_read_image* @-rm -rf $(BIN)/test_xds_binary* @-rm -rf $(BIN)/testcell* @-rm -rf $(BIN)/cif2c* @-rm -rf $(BIN)/testreals* @-rm -rf $(BIN)/testflat* @-rm -rf $(BIN)/testflatpacked* @-rm -rf $(BIN)/cbf_template_t* @-rm -rf $(BIN)/sauter_test* @-rm -rf $(BIN)/arvai_test* @-rm -rf $(BIN)/changtestcompression* @-rm -rf $(BIN)/tiff2cbf* @-rm -f makecbf.cbf @-rm -f img2cif_packed.cif @-rm -f img2cif_canonical.cif @-rm -f img2cif_packed.cbf @-rm -f img2cif_canonical.cbf @-rm -f img2cif_raw.cbf @-rm -f cif2cbf_packed.cbf @-rm -f cif2cbf_canonical.cbf @-rm -f converted.cbf @-rm -f adscconverted.cbf @-rm -f converted_flat.cbf @-rm -f adscconverted_flat.cbf @-rm -f adscconverted_flat_rev.cbf @-rm -f mb_LP_1_001.cbf @-rm -f cif2cbf_ehcn.cif @-rm -f cif2cbf_encp.cbf @-rm -f 9ins.cbf @-rm -f 9ins.cif @-rm -f testcell.prt @-rm -f example.mar2300 @-rm -f converted_orig.cbf @-rm -f adscconverted_orig.cbf @-rm -f converted_flat_orig.cbf @-rm -f adscconverted_flat_orig.cbf @-rm -f adscconverted_flat_rev_orig.cbf @-rm -f mb_LP_1_001_orig.cbf @-rm -f insulin_pilatus6mconverted_orig.cbf @-rm -f insulin_pilatus6mconverted.cbf @-rm -f insulin_pilatus6m.cbf @-rm -f testrealin.cbf @-rm -f testrealout.cbf @-rm -f testflatin.cbf @-rm -f testflatout.cbf @-rm -f testflatpackedin.cbf @-rm -f testflatpackedout.cbf @-rm -f CTC.cbf @-rm -f test_fcb_read_testflatout.out @-rm -f test_fcb_read_testflatpackedout.out @-rm -f test_xds_bin_testflatpackedout.out @-rm -f test_xds_bin_testflatout.out @-rm -f test_fcb_read_testflatout_orig.out @-rm -f test_fcb_read_testflatpackedout_orig.out @-rm -f test_xds_bin_testflatpackedout_orig.out @-rm -f test_xds_bin_testflatout_orig.out @-rm -f mb_LP_1_001.img @-rm -f 9ins.cif @-rm -f testcell_orig.prt @-rm -f $(DECTRIS_EXAMPLES)/cbf_template_t.out @-rm -f XRD1621.cbf @-rm -f XRD1621_orig.cbf @-rm -f XRD1621_orig.cbf @-rm -f XRD1621_I4encbC100.cbf @-rm -f $(SRC)/fcb_exit_binary.f90 @-rm -f $(SRC)/fcb_next_binary.f90 @-rm -f $(SRC)/fcb_open_cifin.f90 @-rm -f $(SRC)/fcb_packed.f90 @-rm -f $(SRC)/fcb_read_bits.f90 @-rm -f $(SRC)/fcb_read_image.f90 @-rm -f $(SRC)/fcb_read_xds_i2.f90 @-rm -f $(EXAMPLES)/test_fcb_read_image.f90 @-rm -f $(EXAMPLES)/test_xds_binary.f90 @-rm -f symlinksdone @-rm -f $(TESTOUTPUT) *$(SEXT) @-rm -f $(SOLIB)/*.o @-rm -f $(SOLIB)/libcbf_wrap.so @-rm -f $(SOLIB)/libjcbf.so @-rm -f $(SOLIB)/libimg.so @-rm -f $(SOLIB)/libfcb.so @-rm -rf $(JCBF)/org @-rm -f $(JCBF)/*.java @-rm -f $(JCBF)/jcbf_wrap.c @-rm -f $(SRC)/cbf_wrap.c @-rm -f $(BIN)/ctestcbf $(BIN)/testcbf.class testcbfc.txt testcbfj.txt @-rm -rf $(REGEX) @-rm -rf $(TIFF) ./.undosymlinks # # Remove temporary files # clean: @-rm -f core @-rm -f *.o @-rm -f *.u # # Restore to distribution state # distclean: clean empty # # Create a Tape Archive for distribution # tar: $(DOCUMENTS) $(SOURCE) $(SRC)/cbf.stx $(HEADERS) $(M4FILES)\ $(EXAMPLES) \ README.html README Makefile \ $(JPEGS) -/bin/rm -f CBFlib.tar* tar cvBf CBFlib.tar \ $(DOCUMENTS) $(SOURCE) $(SRC)/cbf.stx $(HEADERS) $(M4FILES)\ $(EXAMPLES) \ README.html README Makefile \ $(JPEGS) gzip --best CBFlib.tar ./CBFlib-0.9.2.2/template_mar345_2300x2300.cbf0000777000076500007650000000000011603751102024657 2examples/template_mar345_2300x2300.cbfustar yayayaya./CBFlib-0.9.2.2/lgpl.txt0000777000076500007650000000000011603751102015536 2doc/lgpl.txtustar yayayaya./CBFlib-0.9.2.2/README.html0000755000076500007650000002440611603745600013440 0ustar yayayaya CBFlib
    [IUCr Home Page] [CIF Home Page] [CBF/imgCIF] [CBFlib] Get CBFlib at SourceForge.net. Fast, secure and Free Open Source software downloads


    | IUCr Home Page | CIF Home Page | CBF/imgCIF | CBFlib |
    | NOTICE | doc/GPL | doc/LGPL | imgCIF dictionary | SourceForge CBFlib site |
    | Click Here to Make a Donation |

    CBFlib

    README

    Information for CBFlib 0.9.2 release of 12 February 2011
    revised as the CBFlib 0.9.2.1 release of 20 June 2011
    revised as the CBFlib 0.9.2.2 release of 2 July 2011

    by
    Paul J. Ellis
    Stanford Synchrotron Radiation Laboratory

    and
    Herbert J. Bernstein
    Bernstein + Sons

    © Copyright 2006, 2007, 2008, 2010, 2011 Herbert J. Bernstein


    YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL.

    ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS OF THE LGPL.


    Before using this software, please read the
    NOTICE
    for important disclaimers and the IUCr Policy on the Use of the Crystallographic Information File (CIF) and other important information.

    Work on imgCIF and CBFlib supported in part by the U. S. Department of Energy (DOE) under grants ER63601-1021466-0009501 and ER64212-1027708-0011962, by the U. S. National Science Foundation (NSF) under grants DBI-0610407, DBI-0315281 and EF-0312612, the U. S. National Institutes of Health (NIH) under grants 1R15GM078077 from NIGMS and 1R13RR023192 from NCRR and funding from the International Union for Crystallography (IUCr). The content is solely the responsibility of the authors and does not necessarily represent the official views of DOE, NSF, NIH, NIGMS, NCRR or IUCr.


    CBFlib 0.9.2.2 is a minor revision to the CBFlib 0.9.2.1 release in July 2011 to update doc/cif_img.dic to the 1.6.4 revision.

    CBFlib 0.9.2.1 is a minor revision to the CBFlib 0.9.2 release in June 2011 to upgrade the setup script for the pycbf Python bindings to simplify using pycbf outside the context of the CBFlib pycbf directory.

    CBFlib 0.9.2 is the recommended release of CBFlib of February 2011. The commulative changes in releases 0.9.1 and 0.9.2 since CBFlib 0.9.0 are:

    • Temporary removal of default PyCifRW support for compliance with Fedora license requirements.
    • Addition of a new tiff2cbf example program.
    • Update pycbf python wraapper for CBFlib.
    • Padding options added to adscimg2cbf by C. Nielsen.
    • System and gnu versions of getopt replaced by cbf_getopt.
    • Code to handle CIF2 bracketed constructs and quoted strings added.
    • System to log errors and warnings added.
    • Java wrapper by Peter Chang added.
    • Dectris template code by E. Eikenberry added.

    CBFlib 0.9.1 included a correction to CBFlib 0.9.0 to make axis the cbf_simple routines apply axis rotations correctly for detectors and to pick up corrections for byte offet compression incorporated into the upcoming CBFlib 0.9.1 release. The earlier version had failed to apply the rotations to the accumulated displacements. Our thanks to Joerg Kaercher of Bruker-AXS for identifying the rotation problem.

    CBFlib 0.9.0 was a partial pre-release of CBFlib version 0.8 needed to support changes in RasMol. This release was incomplete and used were advided to use it with caution, but it has proven to be a reliable, stable release for 2 years. There have been significant changes in the input/output logic and in validation. For a ChangeLog consult the SVN of the CBFlib project on sourceforge.

    CBFLIB is a library of ANSI-C functions providing a simple mechanism for accessing Crystallographic Binary Files (CBF files) and Image-supporting CIF (imgCIF) files. The CBFLIB API is loosely based on the CIFPARSE API for mmCIF files. Starting with this release, CBFLIB performs validation checks on reading of a CBF. If a dictionary is provided, values will be validated against dictionary ranges and enumerations. Tags missing under parent-child relationships or category key requirements will be reported. CBFlib provides functions to create, read, modify and write CBF binary data files and imgCIF ASCII data files.

    Installation

    CBFLIB should be built on a disk with at least 350 megabytes of free space, for a full installation with complete tests. Read the instructions below carefully, if space is a problem.

    A gizpped tarball of this release is available on sourceforge at

    http://downloads.sf.net/cbflib/CBFlib-0.9.2.2.tar.gz

    In addition, http://downloads.sf.net/cbflib/CBFlib_0.9.2_Data_Files_Input.tar.gz (13 MB) is a "gzipped" tar of the input data files needed to test the API, http://downloads.sf.net/cbflib/CBFlib_0.9.2_Data_Files_Output.tar.gz (34 MB) is a "gzipped" tar of the output data files needed to test the API, and, if space is at a premium, http://downloads.sf.net/cbflib/CBFlib_0.9.2_Data_Files_Output_Sigs_Only.tar.gz (1KB) is a "gzipped" tar of only the MD5 signatures of the output data files needed to test the API. Place the CBFlib_0.9.2.2.tar.gz file in the directory that is intended to contain up to 4 new directories, named CBFlib_0.9.2.2 (the "top-level" directory), CBFlib_0.9.2_Data_Files_Input and either CBFlib_0.9.2_Data_Files_Output or CBFlib_0.9.2_Data_Files_Output_Sigs_Only. If you have wget on your machine, you only need to download the source tarball. If you do not have wget, you will need to download all the tarballs into the same directory

    Uncompress CBFlib_0.9.2.tar.gz with gunzip and unpack it with tar:

         gunzip CBFlib_0.9.2.tar.gz
         tar xvf CBFLIB_0.9.2.tar
    

    To run the test programs, you will also need Paul Ellis's sample MAR345 image, example.mar2300, Chris Nielsen's sample ADSC Quantum 315 image, mb_LP_1_001.img, and Eric Eikenberry's SLS sample Pilatus 6m image, insulin_pilatus6m, as sample data. In addition there are is a PDB mmCIF file, 9ins.cif, and 3 special test files testflatin.cbf, testflatpackedin.cbf and testrealin.cbf. All these files will be dowloaded and extracted by the Makefile from CBFlib_0.9.2_Data_Files_Input. Do not download copies into the top level directory.

    After unpacking the archives, the top-level directory should contain a makefile:

      Makefile  Makefile for unix

    and the subdirectories:

      src/  CBFLIB source files
      include/  CBFLIB header files
        
      bin/  Executable example programs
      doc/  Documentation
      examples/  Example program source files
      html_images/  JPEG images used in rendering the HTML files
      lib/  Compiled CBFLIB (libcbf.a) and FCBLIB (libfcb.a) libraries
      m4/  CBFLIB m4 macro files (used to build .f90 files)
      mswin/  An MS Windows CodeWarrior project file
      pycbf/  Jon Wright's Python bindings

    and additional Makefiles for other systems. All the makefiles are created from m4/Makefile.m4. Edit the closest approximation to your system, and then copy that variant to Makefile.

    For instructions on compiling and testing the library, go to the top-level directory and type:

         make
    

    Once you have a properly configure Makefile, compile and test the package with

         make tests
    

    or, if space is at a premium, with

         make tests_sigs_only
    

    Please refer to the manual doc/CBFlib.html for more detailed information.



    Updated 2 July 2011.
    ./CBFlib-0.9.2.2/template_adscquantum4_2304x2304.cbf0000777000076500007650000000000011603751102027673 2examples/template_adscquantum4_2304x2304.cbfustar yayayaya./CBFlib-0.9.2.2/examples/0000755000076500007650000000000011603703065013421 5ustar yayayaya./CBFlib-0.9.2.2/examples/makecbf.c0000644000076500007650000006305011603702122015152 0ustar yayayaya/********************************************************************** * makecbf -- convert an image file to a cbf file * * * * Version 0.7.6 28 June 2006 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * WHILE YOU MAY ALTERNATIVE DISTRIBUTE THE API UNDER THE LGPL * * YOU MAY ***NOT*** DISTRBUTE THIS PROGRAM UNDER THE LGPL * * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #include "cbf.h" #include "img.h" #include #include #include #include #include int local_exit(int status) { exit(status); return status; /* to avoid warning messages */ } #undef cbf_failnez #define cbf_failnez(x) \ {int err; \ err = (x); \ if (err) { \ fprintf(stderr,"\nCBFlib fatal error %x \n",err); \ local_exit(-1); \ } \ } int main (int argc, char *argv []) { FILE *in, *out; clock_t a,b; img_handle img, cbf_img; cbf_handle cbf; int id, index; unsigned int column, row; size_t nelem_read; double pixel_size, gain, wavelength, distance; int overload, dimension [2], precedence [2]; const char *detector; char *detector_char; char detector_id [64]; const char *direction [2], *array_id; /* Usage */ if (argc < 3) { fprintf (stderr, "\n Usage: %s imagefile cbffile\n", argv [0]); exit (2); } /* Read the image */ img = img_make_handle (); a = clock (); cbf_failnez (img_read (img, argv [1])) b = clock (); fprintf (stderr, " Time to read the image: %.3fs\n", ((b - a) * 1.0) / CLOCKS_PER_SEC); /* Get some detector parameters */ /* Detector identifier */ detector = img_get_field (img, "DETECTOR"); if (!detector) detector = "unknown"; strncpy (detector_id, detector, 63); detector_id [63] = 0; detector_char = detector_id; while (*detector_char) if (isspace (*detector_char)) memmove (detector_char, detector_char + 1, strlen (detector_char)); else { *detector_char = tolower (*detector_char); detector_char++; } /* Pixel size */ pixel_size = img_get_number (img, "PIXEL SIZE") * 0.001; /* Wavelength */ wavelength = img_get_number (img, "WAVELENGTH"); /* Distance */ distance = img_get_number (img, "DISTANCE") * 0.001; /* Image size and orientation & gain and overload */ if (strcmp (detector_id, "mar180") == 0 || strcmp (detector_id, "mar300") == 0) { gain = 1.08; overload = 120000; dimension [0] = img_rows (img); dimension [1] = img_columns (img); precedence [0] = 1; precedence [1] = 2; direction [0] = "decreasing"; direction [1] = "increasing"; } else if (strcmp (detector_id, "mar345") == 0) { gain = 1.55; overload = 240000; dimension [0] = img_columns (img); dimension [1] = img_rows (img); precedence [0] = 2; precedence [1] = 1; direction [0] = "increasing"; direction [1] = "increasing"; } else if (strncmp (detector_id, "adscquantum", 11) == 0) { gain = 0.20; overload = 65000; dimension [0] = img_columns (img); dimension [1] = img_rows (img); precedence [0] = 2; precedence [1] = 1; direction [0] = "increasing"; direction [1] = "increasing"; } else { gain = 0.0; overload = 0; dimension [0] = img_rows (img); dimension [1] = img_columns (img); precedence [0] = 1; precedence [1] = 2; direction [0] = NULL; direction [1] = NULL; } /* Make a cbf version of the image */ a = clock (); /* Create the cbf */ cbf_failnez (cbf_make_handle (&cbf)) /* Make a new data block */ cbf_failnez (cbf_new_datablock (cbf, "image_1")) /* Make the _diffrn category */ cbf_failnez (cbf_new_category (cbf, "diffrn")) cbf_failnez (cbf_new_column (cbf, "id")) cbf_failnez (cbf_set_value (cbf, "DS1")) /* Make the _diffrn_source category */ cbf_failnez (cbf_new_category (cbf, "diffrn_source")) cbf_failnez (cbf_new_column (cbf, "diffrn_id")) cbf_failnez (cbf_set_value (cbf, "DS1")) cbf_failnez (cbf_new_column (cbf, "source")) cbf_failnez (cbf_set_value (cbf, "synchrotron")) cbf_failnez (cbf_new_column (cbf, "type")) cbf_failnez (cbf_set_value (cbf, "ssrl crystallography")) /* Make the _diffrn_radiation category */ cbf_failnez (cbf_new_category (cbf, "diffrn_radiation")) cbf_failnez (cbf_new_column (cbf, "diffrn_id")) cbf_failnez (cbf_set_value (cbf, "DS1")) cbf_failnez (cbf_new_column (cbf, "wavelength_id")) cbf_failnez (cbf_set_value (cbf, "L1")) /* Make the _diffrn_radiation_wavelength category */ cbf_failnez (cbf_new_category (cbf, "diffrn_radiation_wavelength")) cbf_failnez (cbf_new_column (cbf, "id")) cbf_failnez (cbf_set_value (cbf, "L1")) cbf_failnez (cbf_new_column (cbf, "wavelength")) if (wavelength) cbf_failnez (cbf_set_doublevalue (cbf, "%.4f", wavelength)) cbf_failnez (cbf_new_column (cbf, "wt")) cbf_failnez (cbf_set_value (cbf, "1.0")) /* Make the _diffrn_measurement category */ cbf_failnez (cbf_new_category (cbf, "diffrn_measurement")) cbf_failnez (cbf_new_column (cbf, "diffrn_id")) cbf_failnez (cbf_set_value (cbf, "DS1")) cbf_failnez (cbf_new_column (cbf, "method")) cbf_failnez (cbf_set_value (cbf, "oscillation")) cbf_failnez (cbf_new_column (cbf, "sample_detector_distance")) if (distance) cbf_failnez (cbf_set_doublevalue (cbf, "%.4f", distance)) /* Make the _diffrn_detector category */ cbf_failnez (cbf_new_category (cbf, "diffrn_detector")) cbf_failnez (cbf_new_column (cbf, "id")) cbf_failnez (cbf_set_value (cbf, detector_id)) cbf_failnez (cbf_new_column (cbf, "diffrn_id")) cbf_failnez (cbf_set_value (cbf, "DS1")) cbf_failnez (cbf_new_column (cbf, "type")) cbf_failnez (cbf_set_value (cbf, detector)) /* Make the _diffrn_detector_element category */ cbf_failnez (cbf_new_category (cbf, "diffrn_detector_element")) cbf_failnez (cbf_new_column (cbf, "id")) cbf_failnez (cbf_set_integervalue (cbf, 1)) cbf_failnez (cbf_new_column (cbf, "detector_id")) cbf_failnez (cbf_set_value (cbf, detector_id)) /* Make the _diffrn_frame_data category */ cbf_failnez (cbf_new_category (cbf, "diffrn_frame_data")) cbf_failnez (cbf_new_column (cbf, "id")) cbf_failnez (cbf_set_value (cbf, "frame_1")) cbf_failnez (cbf_new_column (cbf, "detector_element_id")) cbf_failnez (cbf_set_integervalue (cbf, 1)) cbf_failnez (cbf_new_column (cbf, "detector_id")) cbf_failnez (cbf_set_value (cbf, detector_id)) cbf_failnez (cbf_new_column (cbf, "array_id")) cbf_failnez (cbf_set_value (cbf, "image_1")) cbf_failnez (cbf_new_column (cbf, "binary_id")) cbf_failnez (cbf_set_integervalue (cbf, 1)) /* Make the _array_structure_list category */ cbf_failnez (cbf_new_category (cbf, "array_structure_list")) cbf_failnez (cbf_new_column (cbf, "array_id")) cbf_failnez (cbf_set_value (cbf, "image_1")) cbf_failnez (cbf_new_row (cbf)) cbf_failnez (cbf_set_value (cbf, "image_1")) cbf_failnez (cbf_new_column (cbf, "index")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_integervalue (cbf, 1)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_integervalue (cbf, 2)) cbf_failnez (cbf_new_column (cbf, "dimension")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_integervalue (cbf, dimension [0])) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_integervalue (cbf, dimension [1])) cbf_failnez (cbf_new_column (cbf, "precedence")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_integervalue (cbf, precedence [0])) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_integervalue (cbf, precedence [1])) cbf_failnez (cbf_new_column (cbf, "direction")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_value (cbf, direction [0])) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, direction [1])) /* Make the _array_element_size category */ cbf_failnez (cbf_new_category (cbf, "array_element_size")) cbf_failnez (cbf_new_column (cbf, "array_id")) cbf_failnez (cbf_set_value (cbf, "image_1")) cbf_failnez (cbf_new_row (cbf)) cbf_failnez (cbf_set_value (cbf, "image_1")) cbf_failnez (cbf_new_column (cbf, "index")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_integervalue (cbf, 1)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_integervalue (cbf, 2)) cbf_failnez (cbf_new_column (cbf, "size")) if (pixel_size > 0) { cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.1fe-6", pixel_size * 1e6)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.1fe-6", pixel_size * 1e6)) } /* Make the _array_intensities category */ cbf_failnez (cbf_new_category (cbf, "array_intensities")) cbf_failnez (cbf_new_column (cbf, "array_id")) cbf_failnez (cbf_set_value (cbf, "image_1")) cbf_failnez (cbf_new_column (cbf, "binary_id")) cbf_failnez (cbf_set_integervalue (cbf, 1)) cbf_failnez (cbf_new_column (cbf, "linearity")) cbf_failnez (cbf_set_value (cbf, "linear")) cbf_failnez (cbf_new_column (cbf, "gain")) if (gain) cbf_failnez (cbf_set_doublevalue (cbf, "%.3g", gain)) cbf_failnez (cbf_new_column (cbf, "overload")) if (overload) cbf_failnez (cbf_set_integervalue (cbf, overload)) cbf_failnez (cbf_new_column (cbf, "undefined")) cbf_failnez (cbf_set_integervalue (cbf, 0)) /* Make the _array_data category */ cbf_failnez (cbf_new_category (cbf, "array_data")) cbf_failnez (cbf_new_column (cbf, "array_id")) cbf_failnez (cbf_set_value (cbf, "image_1")) cbf_failnez (cbf_new_column (cbf, "binary_id")) cbf_failnez (cbf_set_integervalue (cbf, 1)) cbf_failnez (cbf_new_column (cbf, "data")) /* Save the binary data */ cbf_failnez (cbf_set_integerarray_wdims_fs (cbf, CBF_PACKED|CBF_FLAT_IMAGE, 1, img_pixelptr (img, 0, 0), sizeof (int), 1, img_rows (img) * img_columns (img), "little_endian",img_rows (img),img_columns (img),0,0 )) /* Write the new file */ out = fopen (argv [2], "w+b"); if (!out) { fprintf (stderr, " Couldn't open the CBF file %s\n", argv [2]); exit (1); } cbf_failnez (cbf_write_file (cbf, out, 1, CBF, MSG_DIGEST | MIME_HEADERS , 0)) /* Free the cbf */ cbf_failnez (cbf_free_handle (cbf)) b = clock (); fprintf (stderr, " Time to write the CBF image: %.3fs\n", ((b - a) * 1.0) / CLOCKS_PER_SEC); /* Read the CBF file and compare the image to the original */ a = clock (); /* Create the cbf */ cbf_failnez (cbf_make_handle (&cbf)) /* Read the file */ in = fopen (argv [2], "rb"); if (!in) { fprintf (stderr, " Couldn't reopen the CBF file %s\n", argv [2]); exit (1); } cbf_failnez (cbf_read_file (cbf, in, MSG_DIGEST)) /* Get the image identifier */ cbf_failnez (cbf_rewind_datablock (cbf)) cbf_failnez (cbf_find_category (cbf, "diffrn_frame_data")) cbf_failnez (cbf_find_column (cbf, "array_id")) cbf_failnez (cbf_get_value (cbf, &array_id)) /* Get the image dimensions (second dimension = fast, first = slow) */ cbf_failnez (cbf_find_category (cbf, "array_structure_list")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_find_column (cbf, "array_id")) dimension [0] = dimension [1] = 0; while (cbf_find_nextrow (cbf, array_id) == 0) { cbf_failnez (cbf_find_column (cbf, "precedence")) cbf_failnez (cbf_get_integervalue (cbf, &index)) if (index >= 1 && index <= 2) { cbf_failnez (cbf_find_column (cbf, "dimension")) cbf_failnez (cbf_get_integervalue (cbf, &dimension [2 - index])) } else exit (1); cbf_failnez (cbf_find_column (cbf, "array_id")) } if (dimension [0] == 0 || dimension [1] == 0) exit (1); /* Create the new image */ cbf_img = img_make_handle (); img_set_dimensions (cbf_img, dimension [0], dimension [1]); /* Find the binary data */ cbf_failnez (cbf_find_category (cbf, "array_data")) cbf_failnez (cbf_find_column (cbf, "array_id")) cbf_failnez (cbf_find_row (cbf, array_id)) cbf_failnez (cbf_find_column (cbf, "data")) /* Read the binary data */ cbf_failnez (cbf_get_integerarray (cbf, &id, img_pixelptr (cbf_img, 0, 0), sizeof (int), 1, img_rows (cbf_img) * img_columns (cbf_img), &nelem_read)) /* Free the cbf */ cbf_failnez (cbf_free_handle (cbf)) b = clock (); fprintf (stderr, " Time to read the CBF image: %.3fs\n", ((b - a) * 1.0) / CLOCKS_PER_SEC); /* Compare the images */ if (img_rows (img) != img_rows (cbf_img) || img_columns (img) != img_columns (cbf_img)) { fprintf (stderr, " The dimensions of the CBF image don't match the original\n"); exit (1); } for (column = 0; column < (unsigned int) img_columns (cbf_img); column++) for (row = 0; row < (unsigned int) img_rows (cbf_img); row++) if (img_pixel (cbf_img, column, row) != img_pixel (img, column, row)) { fprintf (stderr, " The CBF image differs from the original at (%d, %d)\n", column, row); exit (1); } fprintf (stderr, " The CBF image matches the original\n"); /* Free the images */ img_free_handle (img); img_free_handle (cbf_img); /* Success */ return 0; } ./CBFlib-0.9.2.2/examples/cbf2adscimg.c0000755000076500007650000001576011603702122015736 0ustar yayayaya#include #include #include #include #include /****************************************************************/ static void gethd ( char* field, char* value, char* header ) { char *hp, *lhp, *fp, *vp; int l, j; char *newfield; /* * Find the last occurance of "field" in "header" */ l = strlen (field); newfield = (char*) malloc ( l + 3 ); *newfield = 10; strncpy (newfield+1, field, l); *(newfield+l+1) = '='; *(newfield+l+2) = (char) 0; l += 2; lhp = 0; for (hp=header; *hp != '}'; hp++) { for (fp=newfield, j=0; j 1 && argv[1][0] == '-' && argv[1][1] == '-') { for(j = 0; flags[j] != NULL; j++) if(NULL != strstr(argv[1], flags[j])) break; if(NULL == flags[j]) { fprintf(stderr,"cbf2adscimg: %s is an unknown flag\n\n", argv[1]); usage(); exit(0); } output_packing = j; argc--; argv++; } output_packing++; while(argc > 1) { strcpy(in_filename, argv[1]); i = strlen(in_filename); k = strlen(".cbf"); if(0 == endswith(in_filename, ".cbf")) { fprintf(stderr,"cbf2adscimg: Input file name %s does not end in .cbf\n", in_filename); exit(0); } strcpy(out_filename, in_filename); out_filename[i - k] = '\0'; strcat(out_filename, endings[output_packing]); cbf_status = cbf2adscimg_sub(in_filename, &header, &data); if(0 != cbf_status) { fprintf(stderr, "cbf2adscimg: Error converting cbf file %s to .img format\n", in_filename); exit(0); } if(NULL == header) { fprintf(stderr, "cbf2adscimg: Error: cbf2adscimg_sub returned NULL for header on file %s\n", in_filename); exit(0); } if(0 == output_packing) { if(NULL == (fp = fopen(out_filename, "wb"))) { fprintf(stderr, "cbf2adscimg: Cannot create %s as output .img file\n", out_filename); exit(0); } } else { if(0 == output_packing) sprintf(popen_command, "gzip > %s", out_filename); else sprintf(popen_command, "bzip2 > %s", out_filename); if(NULL == (fp = popen(popen_command, "w"))) { fprintf(stderr, "cbf2adscimg: Cannot exec %s command to compress output image file.\n", popen_command); exit(0); } } /* * Output the header block(s). */ for(i = 0; i < 5; i++) header_bytes[0 + i] = header[15 + i]; header_bytes[5] = '\0'; header_size_char = atoi(header_bytes); if(header_size_char != fwrite(header, sizeof (char), header_size_char, fp)) { fprintf(stderr, "cbf2adscimg: Cannot write header, size %d bytes, of file %s.\n", header_size_char, in_filename); if(0 == output_packing) fclose(fp); else { status_pclose = pclose(fp); if(0 != status_pclose) { fprintf(stderr, "Status returned from compress command via popen NON-ZERO: %d\n", status_pclose); perror("popen command (maybe this will be useful)"); fprintf(stderr, "Filename being compressed: %s with command: %s\n", out_filename, popen_command); fprintf(stderr, "Program exiting.\n"); exit(0); } } exit(0); } field[0] = '\0'; gethd("SIZE1", field, header); if('\0' == field[0]) { fprintf(stderr,"cbf2adscimg: keyword SIZE1 not found in header. Cannot convert file %s\n", in_filename); exit(0); } size1 = atoi(field); field[0] = '\0'; gethd("SIZE2", field, header); if('\0' == field[0]) { fprintf(stderr,"cbf2adscimg: keyword SIZE2 not found in header. Cannot convert file %s\n", in_filename); exit(0); } size2 = atoi(field); data_size = size1 * size2 * sizeof(unsigned short); gethd("BYTE_ORDER", field, header); cbf_get_local_integer_byte_order(&lbo); if (cbf_cistrcmp(field,lbo)) { unsigned char *p; unsigned char temp; size_t ii; p = (unsigned char *)data; for (ii=0; ii #include "cbf.h" #include "cbf_simple.h" int main (int argc, char ** argv) { double cell[6], rcell[6], ncell[6], volume; cout << "Type a,b,c,alpha,beta,gamma\n" << endl; cin >> cell[0] >> cell[1] >> cell[2] >> cell[3] >> cell[4] >> cell[5];; cout << " Cell: " << cell[0]<< ", " << cell[1]<< ", " << cell[2]<< ", " << cell[3]<< ", " << cell[4]<< ", " << cell[5] << endl; cbf_failnez(cbf_compute_cell_volume(cell, &volume)) cbf_failnez(cbf_compute_reciprocal_cell(cell, rcell)) cbf_failnez(cbf_compute_reciprocal_cell(rcell, ncell)) cout << " Volume: " << volume; cout << " Reciprocal Cell: " << rcell[0]<< ", " << rcell[1]<< ", " << rcell[2]<< ", " << rcell[3]<< ", " << rcell[4]<< ", " << rcell[5] << endl; cout << " Recomputed Cell: " << ncell[0]<< ", " << ncell[1]<< ", " << ncell[2]<< ", " << ncell[3]<< ", " << ncell[4]<< ", " << ncell[5] << endl; return 0; } ./CBFlib-0.9.2.2/examples/testcbf.java0000644000076500007650000000124211603702122015706 0ustar yayayayaimport org.iucr.cbflib.*; // javac -cp cbflib-0.8.0.jar testcbf.java // LD_LIBRARY_PATH=solib java -cp cbflib-0.8.0.jar:. testcbf public class testcbf { static { System.loadLibrary("cbf_wrap"); } public static void main(String[] args) { SWIGTYPE_p_FILE f = cbf.fopen("examples/template_pilatus6m_2463x2527.cbf", "rb"); cbf_handle_struct chs = new cbf_handle_struct(); int status = 0; status = cbf.cbf_read_widefile(chs, f, cbfConstants.MSG_DIGEST); System.out.println("read_widefile (" + status + ")"); uintp mp = new uintp(); status = cbf.cbf_count_datablocks(chs, mp.cast()); System.out.println("count_dbs (" + status + ") = " + mp.value()); } } ./CBFlib-0.9.2.2/examples/img.c0000644000076500007650000010624711603702122014344 0ustar yayayaya /* image object v. 1.1 */ #ifdef __cplusplus extern "C" { #endif #include "img.h" #include #include #include #include #include #define FailNEZ(x) { int FailNEZ_status = (x); \ if (FailNEZ_status != 0) \ return FailNEZ_status; } #define isNaN(x) ((((x) & 0x7F800000L) == 0x7F800000L) && \ (((x) & 0x007FFFFFL) != 0x00000000L)) /* I/O functions */ int img_swap_i4 (int i4) { return ((i4 << 24) & 0x0FF000000) | ((i4 << 8) & 0x000FF0000) | ((i4 >> 8) & 0x00000FF00) | ((i4 >> 24) & 0x0000000FF); } float img_float_i4 (int i4, int VAX) { int O; float f; if (VAX) i4 = ((i4 << 16) & 0x0FFFF0000) | ((i4 >> 16) & 0x00000FFFF); O = 1; if (*((char *) &O) == 1) O = 0; else O = sizeof (int) - 4; f = 0.0; if (!isNaN (i4)) { /* Translate a non-denormalised IEEE number */ double d; d = (i4 & 0x007FFFFF) | 0x00800000; d *= pow (2.0, ((i4 >> 23) & 0xFF) - 150.0); if (i4 & 0x80000000) d = -d; f = (float) d; } if (VAX) f /= 4; return f; } int img_read_i4 (FILE *file, int *i4) { int O = 1; if (*((char *) &O) == 1) O = 0; else O = sizeof (int) - 4; return fread (((char *) i4) + O, 4, 1, file) != 1; } /* Read the header of an smv file */ int img_read_smvheader (img_handle img, FILE *file) { /* Start : { Line : tag=data; End : } */ int end_code = 0, eol = 0, start = 0; char *line = NULL; int max_line = 0; int c, count = 0, total = 0, header_bytes = 0, tags = 0; double centre [2], time, oscillation, twotheta, pixel; int dimension [2], status; char C64 [65]; while ((c = getc (file)) != EOF) { total++; if (c == '\r') continue; if (c == '\t') c = ' '; if (count == end_code && c == ' ') continue; /* Header start or end? */ if (!start) { start = c == '{'; continue; } if (c == '}') break; /* Add the character to the line */ if (count >= max_line) { char * oline = line; if (line) free (line); max_line += 256; line = (char *) malloc (max_line); if (!line) return img_BAD_ALLOC; if (count) memcpy (line, oline, count); } line [count] = (char) c; count++; /* Premature end? */ if (c == '\n') { count = end_code = eol = 0; continue; } if (eol) continue; /* End of value? */ if (end_code && c == ';') { char * value = line + end_code; line [count - 1] = 0; /* Remove trailing spaces */ for (c = count - end_code - 2; c >= 0; c--) if (value [c] == ' ') value [c] = 0; else break; /* Save it */ img_set_field (img, line, value); tags++; if (tags == 1) if (strcmp (line, "HEADER_BYTES") != 0) return img_BAD_FORMAT; eol = 1; } /* End of key? */ if (c == '=') { /* Remove trailing spaces */ end_code = count; line [count - 1] = 0; for (c = count - 2; c >= 0; c--) if (line [c] == ' ') line [c] = 0; else break; } } /* Free the buffer */ if (line) free (line); /* Check the format */ if (c != '}') return img_BAD_FORMAT; if (header_bytes <= 0) header_bytes = (int) img_get_number (img, "HEADER_BYTES"); if (header_bytes <= 0) return img_BAD_FORMAT; /* Read and discard the remainder of the header */ for (; total < header_bytes; total++) if (getc (file) == EOF) return img_BAD_READ; /* Translate the header entries to the standard */ dimension [0] = (int) img_get_number (img, "SIZE1"); dimension [1] = (int) img_get_number (img, "SIZE2"); centre [0] = img_get_number (img, "BEAM_CENTER_X"); centre [1] = img_get_number (img, "BEAM_CENTER_Y"); time = img_get_number (img, "TIME"); oscillation = img_get_number (img, "OSC_RANGE"); twotheta = img_get_number (img, "TWOTHETA"); pixel = img_get_number (img, "PIXEL_SIZE"); status = img_set_number (img, "PIXEL SIZE", "%.6g", pixel); status |= img_set_number (img, "OSCILLATION RANGE", "%.6g", oscillation); status |= img_set_number (img, "EXPOSURE TIME", "%.6g", time); status |= img_set_number (img, "TWO THETA", "%.6g", twotheta); if (dimension [0] == 1152 && dimension [1] == 1152) status |= img_set_field (img, "DETECTOR", "ADSC QUANTUM1"); if (dimension [0] == 2304 && dimension [1] == 2304) status |= img_set_field (img, "DETECTOR", "ADSC QUANTUM4"); if (dimension [0] == 3072 && dimension [1] == 3072) status |= img_set_field (img, "DETECTOR", "ADSC QUANTUM315"); sprintf (C64, "%.6g %.6g", centre [0], centre [1]); status |= img_set_field (img, "BEAM CENTRE", C64); if (img_get_field (img, "AXIS")) { strncpy (C64, img_get_field (img, "AXIS"), 63); C64 [63] = 0; for (c = 0; C64 [c]; c++) C64 [c] = (char) toupper (C64 [c]); status |= img_set_field (img, "OSCILLATION AXIS", C64); } return status; } /* Read the image data from an smv file */ int img_read_smvdata (img_handle img, FILE *file) { const char *order, *type; int little, size, sign, rows, cols; int readcount, datacount; unsigned char *data; int *pixel, *stop_pixel; /* Get the byte order */ order = img_get_field (img, "BYTE_ORDER"); if (!order) return img_BAD_FORMAT; little = order [0] == 'l' || order [0] == 'L'; /* Get the data type */ type = img_get_field (img, "TYPE"); if (!type) return img_BAD_FORMAT; size = 1; sign = 0; if (strstr (type, "short") || strstr (type, "mad")) size = 2; if (strstr (type, "long")) sign = size = 4; if (strstr (type, "unsigned")) sign = 0; else if (strstr (type, "signed")) sign = 1; if (sign) { if (size < sizeof (int)) { sign = -(1 << (size * 8)); } else { sign = 0; } } /* Get the image size */ if (getenv("CBF_SMVIMGCOLUMNMAJOR")) { rows = (int) img_get_number (img, "SIZE1"); cols = (int) img_get_number (img, "SIZE2"); img->rowmajor = 0; img_set_field (img, "PRECEDENCE", "COLUMN MAJOR"); } else { rows = (int) img_get_number (img, "SIZE2"); cols = (int) img_get_number (img, "SIZE1"); img->rowmajor = 1; img_set_field (img, "PRECEDENCE", "ROW MAJOR"); } if (rows > 0 && cols == 0) cols = 1; if (img_set_dimensions (img, cols, rows)) return img_BAD_FORMAT; if (img->size [0] == 0 || img->size [1] == 0) return 0; /* Read the data */ data = (unsigned char *) malloc (4096); if (!data) return img_BAD_ALLOC; /* Note that the smv file has the first dimension fast */ /* The "official" SMV format is as follows and it's relationship to data collected with the ADSC detectors: Data are stored in row major order, with SIZE1 columns and SIZE2 rows. The data type is as specified (unsigned_short, etc). That's it; not very flexible. Data from the ADSC detectors are stored with the origin in the upper left hand corner of the detector: O -------> X (SIZE1) | | \/ Y (SIZE2) The "X" dimension varies fastest. The "view" of the data is from the source looking at the detector's front, so you are "standing behind the xrays" rather than "standing behind the detector". (We hate being irradiated!). -- email from "Chris Nielsen" , 16 Jun 2006 */ datacount = 0; pixel = img_pixelptr (img, 0, 0); stop_pixel = img_pixelptr (img, cols - 1, rows - 1) + 1; while ((readcount = fread (data + datacount, 1, 4096 - datacount, file)) > 0) { unsigned char *c, *stop; datacount += readcount; c = data; stop = data + (datacount / size) * size; while (c != stop) { if (little) if (size == 2) *pixel = (c [0]) + (c [1] << 8); else *pixel = (c [0]) + (c [1] << 8) + (c [2] << 16) + (c [3] << 24); else if (size == 2) *pixel = (c [0] << 8) + (c [1]); else *pixel = (c [0] << 24) + (c [1] << 16) + (c [2] << 8) + (c [3]); c += size; pixel++; if (pixel == stop_pixel) { free (data); return 0; } } datacount = datacount % size; if (datacount && c != data) memmove (data, c, datacount); } /* Failure */ free (data); return img_BAD_READ; } int img_read_smv (img_handle img, const char *name) { FILE * file; int status; if (!img) return img_BAD_ARGUMENT; file = fopen (name, "rb"); if (!file) return img_BAD_OPEN; status = img_read_smvheader (img, file); if (status == 0) status = img_read_smvdata (img, file); fclose (file); return status; } /* Write an smv-format file */ int img_write_smv (img_object *img, const char *name, unsigned int bits) { static const char *tags [] = { "PIXEL_SIZE", /* Pixel size (mm) */ "BIN", /* Binning (none/ ) */ "ADC", /* Read speed (fast/slow) */ "DETECTOR_SN", /* Detector serial number */ "DATE", /* Date (eg: Thu Apr 15 16:56:05 1999) */ "TIME", /* Exposure time (s) */ "DISTANCE", /* Distance (mm) */ "PHI", /* Phi angle (degrees) */ "OMEGA", /* Omega angle (degrees) */ "KAPPA", /* Kappa angle (degrees) */ "AXIS", /* Rotation axis (phi/omega/kappa) */ "OSC_START", /* Rotation start (degrees) */ "OSC_RANGE", /* Rotation range (degrees) */ "WAVELENGTH", /* Wavelength (angstroms) */ "BEAM_CENTER_X", /* Beam center (mm) */ "BEAM_CENTER_Y", NULL }; const char **tag, *val; FILE *file; char data [4100]; unsigned char *c; int bytes, size, little, done; int *pixel, *stop_pixel, data_size, value; int limit; /* (1) Calculate the header space required */ bytes = 128; for (tag = tags; *tag; tag++) { val = img_get_field (img, *tag); if (val) bytes += strlen (*tag) + strlen (val) + 3; } bytes = ((bytes + 511) / 512) * 512; /* (2) Write the header */ file = fopen (name, "wb"); if (file == NULL) return img_BAD_OPEN; if (bits <= 16) { size = 2; limit = 0x0ffff; } else { size = 4; if (((unsigned int) (~0)) > 0x0ffffffffU) limit = 0x0ffffffffU; else limit = ((unsigned int) (~0)) / 2; } little = 1; if (*((char *) &little) == 0) little = 0; sprintf (data, "{\012" "HEADER_BYTES=%5d;\012" "DIM=2;\012" "BYTE_ORDER=%s;\012" "TYPE=%s;\012" "SIZE1=%d;\012" "SIZE2=%d;\012", bytes, little ? "little_endian" : "big_endian", size == 2 ? "unsigned_short" : "unsigned_long", img_columns (img), img_rows (img)); if (fputs (data, file) == EOF) { fclose (file); return img_BAD_WRITE; } bytes -= strlen (data); for (tag = tags; *tag; tag++) { val = img_get_field (img, *tag); if (val) { sprintf (data, "%s=%s;\n", *tag, val); if (fputs (data, file) == EOF) { fclose (file); return img_BAD_WRITE; } bytes -= strlen (data); } } if (fputs ("}\014", file) == EOF) { fclose (file); return img_BAD_WRITE; } bytes -= 2; if (bytes < 0) { fclose (file); return img_BAD_ARGUMENT; } while (bytes > 0) { if (fputc ('\040', file) == EOF) { fclose (file); return img_BAD_WRITE; } bytes--; } /* (3) Write the pixel values */ pixel = img_pixelptr (img, 0, 0); stop_pixel = img_pixelptr (img, img_columns (img) - 1, img_rows (img) - 1) + 1; data_size = 0; c = (unsigned char *) data; while (pixel != stop_pixel) { value = *pixel++; if (((unsigned int) value) >= (unsigned int) limit) { if (value < 0) { value = 0; } else { value = (int) limit; } } if (little) if (size == 2) { c [0] = (value); c [1] = (value >> 8); } else { c [0] = (value); c [1] = (value >> 8); c [2] = (value >> 16); c [3] = (value >> 24); } else if (size == 2) { c [0] = (value >> 8); c [1] = (value); } else { c [0] = (value >> 24); c [1] = (value >> 16); c [2] = (value >> 8); c [3] = (value); } data_size += size; c += size; if (data_size >= 4096) { done = fwrite (data, 1, data_size, file); if (done <= 0) { fclose (file); return img_BAD_WRITE; } data_size -= done; c -= done; if (data_size > 0) memmove (data, data + done, data_size); } } while (data_size > 0) { done = fwrite (data, 1, data_size, file); if (done <= 0) { fclose (file); return img_BAD_WRITE; } data_size -= done; c -= done; if (data_size > 0) memmove (data, data + done, data_size); } fclose (file); return 0; } /* Read the header of an old-style MAR file */ int img_read_mar300header (img_handle img, FILE *file, int *org_data) { int i4_data [25], count, swap, status, model; float f4_data [25]; char C64 [65]; double pixel_size; /* Read the start of the header */ for (count = 0; count < 25; count++) if (img_read_i4 (file, &i4_data [count])) return img_BAD_READ; /* Do we need to swap the bytes? */ swap = (i4_data [0] != 1200 && i4_data [0] != 1600 && i4_data [0] != 1800 && i4_data [0] != 2000 && i4_data [0] != 2300 && i4_data [0] != 2400 && i4_data [0] != 3000 && i4_data [0] != 3450); /* Swap? */ if (swap) for (count = 0; count < 25; count++) i4_data [count] = img_swap_i4 (i4_data [count]); /* Convert the floating-point data */ for (count = 10; count < 25; count++) f4_data [count] = img_float_i4 (i4_data [count], 0); /* Check the wavelength: this indicates if we should try the VAX fix */ if (f4_data [19] <= 0.25 || f4_data [19] >= 4.0) for (count = 10; count < 25; count++) f4_data [count] = img_float_i4 (i4_data [count], 1); /* Check the header again */ for (count = 0; count < 2; count++) if (i4_data [count] != 1200 && i4_data [count] != 1800 && i4_data [count] != 1600 && i4_data [count] != 2400 && i4_data [count] != 2000 && i4_data [count] != 3000 && i4_data [count] != 3000 && i4_data [count] != 3450) return img_BAD_FORMAT; /* Copy the data needed to read the image */ org_data [0] = i4_data [0]; org_data [1] = i4_data [1]; org_data [2] = i4_data [2]; org_data [3] = i4_data [3]; org_data [4] = i4_data [4]; org_data [5] = swap; if (org_data [2] <= 0) org_data [2] = 2 * org_data [0]; /* Header data */ model = 0; if (f4_data [11] > 50.0 && f4_data [11] <= 300.0) model = (int) floor (f4_data [11] * 2 + 0.5); strcpy (C64, "MAR"); if (model) sprintf (C64, "MAR %d", model); status = img_set_field (img, "DETECTOR", C64); if (status) return status; if (i4_data [6] <= 0) { i4_data [6] = i4_data [7]; i4_data [7] = 0; } if (i4_data [6] > 0) { sprintf (C64, "%d", i4_data [6]); if (i4_data [7] > 0) sprintf (C64 + strlen (C64), " %d", i4_data [7]); status = img_set_field (img, "BEAM INTENSITY", C64); if (status) return status; } if (i4_data [9] > 0) { status = img_set_number (img, "DOSE", "%.6f", i4_data [9]); if (status) return status; } /* If the wavelength is out of range, the floats are probably invalid */ if (f4_data [19] > 0.25 && f4_data [19] < 4.0) { status = img_set_number (img, "WAVELENGTH", "%.6f", f4_data [19]); if (status) return status; if (f4_data [10] > 0) { status = img_set_number (img, "EXPOSURE TIME", "%.6f", f4_data [10] * 0.001); if (status) return status; } pixel_size = 0.0; if (f4_data [11] > 50.0 && f4_data [11] <= 400.0 && org_data [0] == org_data [1]) pixel_size = (f4_data [11] * 2) / org_data [0]; if (pixel_size > 0.0) { status = img_set_number (img, "PIXEL SIZE", "%.6g", pixel_size); if (status) return status; } if (f4_data [17] || f4_data [18]) { sprintf (C64, "%.6f %.6f", f4_data [17], f4_data [18]); status = img_set_field (img, "BEAM CENTRE", C64); if (status) return status; } if (f4_data [20]) { status = img_set_number (img, "DISTANCE", "%.6g", f4_data [20]); if (status) return status; } if (f4_data [21]) { status = img_set_field (img, "OSCILLATION AXIS", "PHI"); status |= img_set_number (img, "PHI", ".6g", f4_data [21]); if (f4_data [22] != f4_data [21]) status |= img_set_number (img, "OSCILLATION RANGE", ".6g", f4_data [22] - f4_data [21]); if (status) return status; } if (f4_data [23]) { status = img_set_number (img, "OMEGA", "%.6g", f4_data [23]); if (status) return status; } } /* Date and time */ if (fread (C64, 24, 1, file) == 0) return img_BAD_READ; C64 [24] = 0; while (strchr (C64, '-')) *strchr (C64, '-') = ' '; for (count = 23; count >= 0; count--) if (C64 [count] == ' ' || C64 [count] == 0) C64 [count] = 0; else break; if (count >= 0 && C64 [0]) status = img_set_field (img, "DATE", C64); /* Skip the rest of the header */ for (count = org_data [2] - 124; count > 0; count--) if (getc (file) == EOF) return img_BAD_READ; return 0; } /* Read the image data from an old-style MAR file */ int img_read_mar300data (img_handle img, FILE *file, int *org_data) { int x, y, little; unsigned char *data, *cdata; /* Get the image size */ if (img_set_dimensions (img, org_data [0], org_data [1])) return img_BAD_FORMAT; if (img->size [0] == 0 || img->size [1] == 0) return 0; /* Read the unsigned short data */ little = org_data [5]; x = 1; if (*((char *) &x) == 0) little = !little; data = (unsigned char *) malloc (org_data [2]); if (!data) return img_BAD_ALLOC; for (x = 0; x < img_columns (img); x++) { if (fread (data, org_data [2], 1, file) == 0) { free (data); return img_BAD_READ; } cdata = data; for (y = 0; y < img_rows (img); y++, cdata += 2) *(img_pixelptr (img, x, y)) = (int) cdata [little] + ((int) cdata [1 - little] << 8); } free (data); /* Read the overflows */ for (; org_data [4] > 0; org_data [4]--) { int O [2], c; for (c = 0; c < 2; c++) { if (img_read_i4 (file, &O [c])) return img_BAD_READ; if (org_data [5]) O [c] = img_swap_i4 (O [c]); } x = (O [0] - 1) / img_rows (img); y = (O [0] - 1) % img_rows (img); if (x >= 0 && x < img_columns (img) && y >= 0 && y < img_rows (img)) *(img_pixelptr (img, x, y)) = O [1]; else return img_BAD_FORMAT; } return 0; } /* Read an old-style MAR file */ int img_read_mar300 (img_handle img, const char *name) { FILE * file; int status, org_data [6]; if (!img) return img_BAD_ARGUMENT; file = fopen (name, "rb"); if (!file) return img_BAD_OPEN; status = img_read_mar300header (img, file, org_data); if (status == 0) status = img_read_mar300data (img, file, org_data); fclose (file); return status; } /* Read the header of a new-style MAR file */ int img_read_mar345header (img_handle img, FILE *file, int *org_data) { int i4_data [16], count, swap; char C64[65], D64[65], *C, *D, *E; /* Read the start of the header */ for (count = 0; count < 16; count++) if (img_read_i4 (file, &i4_data [count])) return img_BAD_READ; /* Do we need to swap the bytes? */ swap = i4_data [0] != 1234; if (swap) { for (count = 0; count < 16; count++) i4_data [count] = img_swap_i4 (i4_data [count]); /* Check the header again */ if (i4_data [0] != 1234) return img_BAD_FORMAT; } /* Copy the data needed to read the image */ /* x = y */ org_data [0] = org_data [1] = i4_data [1]; /* Overflows */ org_data [2] = i4_data [2]; /* Byteswap? */ org_data [3] = swap; /* Header data */ FailNEZ (img_set_field (img, "DETECTOR", "MAR 345")); if (i4_data [6] <= 0) i4_data [6] = i4_data [7]; if (i4_data [7] <= 0) i4_data [7] = i4_data [6]; if (i4_data [6] > 0) { sprintf (C64, "%.6g %.6g", i4_data [6] / 1000.0, i4_data [7] / 1000.0); FailNEZ (img_set_field (img, "PIXEL SIZE", C64)); } FailNEZ (img_set_number (img, "WAVELENGTH", "%.6f", i4_data [8] / 1000000.0)); FailNEZ (img_set_number (img, "DISTANCE", "%.6g", i4_data [9] / 1000.0)); FailNEZ (img_set_field (img, "OSCILLATION AXIS", "PHI")); FailNEZ (img_set_number (img, "PHI", "%.6g", i4_data [10] / 1000.0)); FailNEZ (img_set_number (img, "OSCILLATION RANGE", "%.6g", (i4_data [11] - i4_data [10]) / 1000.0)); /* Read the remaining (ASCII) part of the header in 64-byte chunks */ if (i4_data [2] > 0) { for (count = 4096 - 64; count > 0; count -= 64) { if (fread (C64, 64, 1, file) <= 0) return img_BAD_READ; C64[64] = '\0'; for (C = C64; *C; C++) if (isspace(*C)) *C = ' '; for (C = C64; *C; C++) if ((*C) < 32 || (*C) > 126 ) *C = '\0'; for (C = C64+strlen(C64)-1; (C != C64-1 && *C == ' '); C-- ) *C = '\0'; C = C64 + strcspn (C64, " "); C = C + strspn (C, " "); if (strncmp (C64, "DATE", 4) == 0) { FailNEZ (img_set_field (img, "DATE", C)); } else { if (strncmp (C64, "TIME", 4) == 0) { FailNEZ (img_set_field (img, "EXPOSURE TIME", C)); } else { if ((D=strstr(C64," "))) { *D = '\0'; C = D+ strspn(D+1, " ") + 1; if (strlen(C64) > 0) { strcpy (D64,C64); D64[64] = '\0'; while (1) { if (!(E=(char *)img_get_field (img, (const char *)D64))) { FailNEZ (img_set_field (img, D64, C)); break; } else { if (strcmp(E,C)) { double test1, test2; char * endptr1, * endptr2; test1 = strtod (E, &endptr1); test2 = strtod (C, &endptr2); if (test1 == test2 && *endptr1=='\0' && *endptr2=='\0') break; if (strlen(D64) > 62 ) break; strncat(D64,"..",64); } else { break; } } } } } } } } } return 0; } /* Read the image data from a new-style MAR file */ int img_read_mar345data (img_handle img, FILE *file, int *org_data) { int *O_data = NULL; int count, C, a, x, y, PACK, pixels, pixel, get, in, incount, pixcount=0, init, next, need; int *cimg; char C64 [65]; /* Get the image size */ FailNEZ (img_set_dimensions (img, org_data [0], org_data [1])) if (img->size [0] == 0 || img->size [1] == 0) return 0; /* Save the overflows */ if (org_data [2] > 0) { O_data = (int *) malloc (2 * org_data [2] * sizeof (int)); if (!O_data) return img_BAD_ALLOC; for (count = 0; count < org_data [2] * 2; count++) if (img_read_i4 (file, &O_data [count])) return img_BAD_READ; if (org_data [3]) for (count = 0; count < org_data [2] * 2; count++) O_data [count] = img_swap_i4 (O_data [count]); } /* Find the "CCP4 packed image" identifier */ for (C = '\n', count = 0; C != EOF; C = getc (file)) { if (count == 63) { C = '-'; count = 0; } C64 [count] = (char) C; count++; C64 [count] = 0; if (C == '\n') { x = y = 0; sscanf (C64, "CCP4 packed image, X: %04d, Y: %04d", &x, &y); if (x && y) { PACK = 1; break; } x = y = 0; sscanf (C64, "CCP4 packed image V%d, X: %04d, Y: %04d", &PACK, &x, &y); if (x && y) break; count = 0; } } if (C == EOF || PACK > 1) { if (org_data [2] > 0) free (O_data); return img_BAD_FORMAT; } /* MAR 345 images have the first dimension fast? */ /* Read the packed unsigned short data */ pixels = org_data [0] * org_data [1]; pixel = 0; in = incount = 0; get = 6; init = 1; x = org_data [0]; cimg = (int *)(img_pixelptr (img, 0, 0)); while (pixel < pixels) { /* Get the next "get" bits of data into "next" */ next = 0; need = get; while (need) { if (incount == 0) { in = getc (file); if (in == EOF) { if (org_data [2] > 0) free (O_data); return img_BAD_READ; } incount = 8; } if (need > incount) { next |= in << (get - need); need -= incount; in = 0; incount = 0; } else { next |= (in & ((1 << need) - 1)) << (get - need); in = (in >> need) & 0x0FF; incount -= need; break; } } /* Decode bits 0-5 */ if (init) { static int decode [8] = { 0, 4, 5, 6, 7, 8, 16, 32 }; pixcount = 1 << (next & 7); get = decode [(next >> 3) & 7]; init = 0; } else { /* Decode a pixel */ /* Sign-extend? */ if (get) next |= -(next & (1 << (get - 1))); /* Calculate the final pixel value */ if (pixel > x) { int A, B, C, D; A = cimg [-1 - x]; B = cimg [ - x]; C = cimg [ 1 - x]; D = cimg [-1 ]; *cimg = (next + (((A & 0x07FFF) + (B & 0x07FFF) + (C & 0x07FFF) + (D & 0x07FFF) - (A & 0x08000) - (B & 0x08000) - (C & 0x08000) - (D & 0x08000) + 2) / 4)) & 0x0FFFF; } else if (pixel) *cimg = (cimg [-1] + next) & 0x0FFFF; else *cimg = next & 0x0FFFF; pixel++; cimg++; pixcount--; /* New set? */ if (pixcount == 0) { init = 1; get = 6; } } } /* Overflows? */ for (count = 0; count < org_data [2]; count++) { a = O_data [count * 2]; x = a / img_rows (img); y = a % img_rows (img); if (x >= 0 && x < img_columns (img) && y >= 0 && y < img_rows (img)) *(img_pixelptr (img, x, y)) = O_data [count * 2 + 1]; else return img_BAD_FORMAT; } if (org_data [2] > 0) free (O_data); return 0; } /* Read a new-style MAR file */ int img_read_mar345 (img_handle img, const char *name) { FILE * file; int status, org_data [4]; if (!img) return img_BAD_ARGUMENT; file = fopen (name, "rb"); if (!file) return img_BAD_OPEN; status = img_read_mar345header (img, file, org_data); if (status == 0) status = img_read_mar345data (img, file, org_data); fclose (file); return status; } int img_set_tags (img_handle img, int tags); /* Read a file */ int img_read (img_handle img, const char *name) { int status; img_set_tags (img, 0); img_set_dimensions (img, 0, 0); status = img_read_mar345 (img, name); if (status == 0) return 0; status = img_read_mar300 (img, name); if (status == 0) return 0; status = img_read_smv (img, name); if (status == 0) return 0; return img_BAD_ARGUMENT; } img_handle img_make_handle () { img_handle img = (img_handle) malloc (sizeof (img_object)); if (img) { img->tags = 0; img->tag = NULL; img->rowmajor = 0; img->size [0] = 0; img->size [1] = 0; img->image = NULL; } return img; } int img_set_tags (img_handle img, int tags) { if (!img || tags < 0) return img_BAD_ARGUMENT; tags = (tags + 0x03F) & ~0x03F; if (tags > img->tags) { img_tag * old_tag = img->tag; img->tag = (img_tag *) malloc (tags * sizeof (img_tag)); if (!img->tag) { img->tag = old_tag; return img_BAD_ALLOC; } if (old_tag) { memcpy (img->tag, old_tag, img->tags * sizeof (img_tag)); free (old_tag); } memset (img->tag + img->tags, 0, (tags - img->tags) * sizeof (img_tag)); img->tags = tags; } if (tags == 0) { if (img->tag) { while (--img->tags >= 0) { if (img->tag [img->tags].tag) free (img->tag [img->tags].tag); if (img->tag [img->tags].data) free (img->tag [img->tags].data); } free (img->tag); } img->tags = 0; img->tag = NULL; } return 0; } int img_get_tags (img_handle img) { int x; if (!img) return 0; for (x = img->tags - 1; x >= 0; x--) if (img->tag [x].tag) break; return x + 1; } int img_free_handle (img_handle img) { if (!img) return img_BAD_ARGUMENT; img_set_tags (img, 0); if (img->image) free (img->image); free (img); return 0; } int img_delete_fieldnumber (img_handle img, int x) { if (!img) return img_BAD_ARGUMENT; if (x < 0) return img_BAD_ARGUMENT; if (x >= img->tags) return img_BAD_FIELD; if (!img->tag [x].tag) return img_BAD_FIELD; free (img->tag [x].tag); if (img->tag [x].data) free (img->tag [x].data); if (x < img->tags - 1) memmove (&img->tag [x], &img->tag [x + 1], (img->tags - 1 - x) * sizeof (img_tag)); img->tag [img->tags - 1].tag = NULL; img->tag [img->tags - 1].data = NULL; return 0; } int img_delete_field (img_handle img, const char * tag) { int x; if (!img || !tag) return img_BAD_ARGUMENT; for (x = img->tags - 1; x >= 0; x--) { if (!img->tag [x].tag) continue; if (strcmp (img->tag [x].tag, tag) == 0) return img_delete_fieldnumber (img, x); } return img_BAD_FIELD; } const char *img_get_field (img_handle img, const char *tag) { int x; if (!img || !tag) return NULL; /* Find the entry with the given tag */ for (x = img->tags - 1; x >= 0; x--) if (img->tag [x].tag) if (strcmp (img->tag [x].tag, tag) == 0) return img->tag [x].data; return NULL; } int img_get_next_field (img_handle img, const char **tag, const char **data, int *index) { if (*index < 0 || *index >= img_get_tags(img)) return img_BAD_ARGUMENT; if (!img || !tag || !data) return img_BAD_ARGUMENT; *tag = img->tag[*index].tag; *data = img->tag[*index].data; (*index)++; return 0; } int img_set_field (img_handle img, const char *tag, const char *data) { int x, x0; if (!img || !tag) return img_BAD_ARGUMENT; /* Find the entry with the given tag */ x0 = img->tags; for (x = x0 - 1; x >= 0; x--) { if (!img->tag [x].tag) { x0 = x; continue; } if (strcmp (img->tag [x].tag, tag) == 0) { if (img->tag [x].data) free (img->tag [x].data); img->tag [x].data = (char *) malloc (strlen (data) + 1); if (!img->tag [x].data) return img_BAD_ALLOC; strcpy (img->tag [x].data, data); return 0; } } /* Create a new entry */ if (img_set_tags (img, x0 + 1)) return img_BAD_ALLOC; img->tag [x0].tag = (char *) malloc (strlen (tag) + 1); if (!img->tag [x0].tag) return img_BAD_ALLOC; img->tag [x0].data = (char *) malloc (strlen (data) + 1); if (!img->tag [x0].data) return img_BAD_ALLOC; strcpy (img->tag [x0].tag, tag); strcpy (img->tag [x0].data, data); return 0; } double img_get_number (img_handle img, const char *tag) { const char *field; field = img_get_field (img, tag); if (!field) return 0.; return atof (field); } int img_set_number (img_handle img, const char *tag, const char *format, double data) { char number [128]; if (!img || !tag || !format) return img_BAD_ARGUMENT; sprintf (number, format, data); return img_set_field (img, tag, number); } int img_get_pixel (img_handle img, int x, int y) { if (!img) return 0; if (x < 0 || x >= img->size [0] || y > 0 || y <= img->size [1]) return 0; if (img->rowmajor) return img->image [y * img->size [0] + x]; else return img->image [x * img->size [1] + y]; } int img_set_pixel (img_handle img, int x, int y, int data) { if (!img) return 0; if (x < 0 || x >= img->size [0] || y > 0 || y <= img->size [1]) return 0; if (img->rowmajor) return img->image [y * img->size [0] + x] = data; else return img->image [x * img->size [1] + y] = data; } int img_set_dimensions (img_handle img, int columns, int rows) { if (columns < 0 || rows < 0 || !img) return img_BAD_ARGUMENT; if (columns != img->size [0] || rows != img->size [1]) { if (img->image) { free (img->image); img->image = NULL; img->size [0] = img->size [1] = 0; } if (columns > 0 && rows > 0) { img->image = (int *) malloc (columns * rows * sizeof (int)); if (!img->image) return img_BAD_ALLOC; } } img->size [0] = columns; img->size [1] = rows; return 0; } int img_get_dimension (img_handle img, int dimension) { if (!img) return 0; if (dimension < 1 || dimension > 2) return 1; return img->size [dimension - 1]; } #ifdef __cplusplus } #endif /* IMG_C */ ./CBFlib-0.9.2.2/examples/img.h0000644000076500007650000000477611603702122014355 0ustar yayayaya /* image object v. 1.1 */ #ifndef IMG_H #define IMG_H #ifdef __cplusplus extern "C" { #endif #define img_BAD_ARGUMENT 0x0001 #define img_BAD_ALLOC 0x0002 #define img_BAD_OPEN 0x0004 #define img_BAD_READ 0x0008 #define img_BAD_FORMAT 0x0010 #define img_BAD_FIELD 0x0020 #define img_BAD_WRITE 0x0040 /* Tag */ typedef struct { char *tag; char *data; } img_tag; /* Image */ typedef struct { int tags; img_tag *tag; int size [2]; /* size[0] = columns, size[1] = rows */ int rowmajor; /* set to 1 for row major, 0 for column major */ int *image; } img_object; typedef img_object *img_handle; /* Functions */ #define img_pixel(img,x,y) \ (((img)->rowmajor)? \ (((img)->image) [((img)->size) [0] * (int) (y) + (int) (x)]) :\ (((img)->image) [((img)->size) [1] * (int) (x) + (int) (y)])) #define img_pixelptr(img,x,y) \ (((img)->rowmajor)? \ &(((img)->image) [((img)->size) [0] * (int) (y) + (int) (x)]) :\ &(((img)->image) [((img)->size) [1] * (int) (x) + (int) (y)])) #define img_columns(img) ((img)->size [0]) #define img_rows(img) ((img)->size [1]) img_handle img_make_handle (); int img_read (img_handle img, const char *name); int img_free_handle (img_handle img); int img_delete_field (img_handle img, const char *tag); const char *img_get_field (img_handle img, const char *tag); int img_get_next_field (img_handle img, const char **tag, const char **data, int *index); int img_set_field (img_handle img, const char *tag, const char *data); double img_get_number (img_handle img, const char *tag); int img_set_number (img_handle img, const char *tag, const char *format, double data); int img_get_pixel (img_handle img, int x, int y); int img_set_pixel (img_handle img, int x, int y, int data); int img_set_dimensions (img_handle img, int columns, int rows); int img_get_dimension (img_handle img, int dimension); #ifdef __cplusplus } #endif #endif /* IMG_H */ ./CBFlib-0.9.2.2/examples/testflat.c0000644000076500007650000007602411603702122015415 0ustar yayayaya/********************************************************************** * testflat -- test read and write for flat field * * * * Version 0.7.6.3 21 January 2007 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * WHILE YOU MAY ALTERNATIVE DISTRIBUTE THE API UNDER THE LGPL * * YOU MAY ***NOT*** DISTRBUTE THIS PROGRAM UNDER THE LGPL * * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term 'this software', as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ /********************************************************************** * SYNOPSIS * * * * testflat * * * **********************************************************************/ #include "cbf.h" #include #include #include #include #include #include #include int local_exit (int status); int outerror(int err) { if ((err&CBF_FORMAT)==CBF_FORMAT) fprintf(stderr, " testflat: The file format is invalid.\n"); if ((err&CBF_ALLOC)==CBF_ALLOC) fprintf(stderr, " testflat Memory allocation failed.\n"); if ((err&CBF_ARGUMENT)==CBF_ARGUMENT) fprintf(stderr, " testflat: Invalid function argument.\n"); if ((err&CBF_ASCII)==CBF_ASCII) fprintf(stderr, " testflat: The value is ASCII (not binary).\n"); if ((err&CBF_BINARY)==CBF_BINARY) fprintf(stderr, " testflat: The value is binary (not ASCII).\n"); if ((err&CBF_BITCOUNT)==CBF_BITCOUNT) fprintf(stderr, " testflat: The expected number of bits does" " not match the actual number written.\n"); if ((err&CBF_ENDOFDATA)==CBF_ENDOFDATA) fprintf(stderr, " testflat: The end of the data was reached" " before the end of the array.\n"); if ((err&CBF_FILECLOSE)==CBF_FILECLOSE) fprintf(stderr, " testflat: File close error.\n"); if ((err&CBF_FILEOPEN)==CBF_FILEOPEN) fprintf(stderr, " testflat: File open error.\n"); if ((err&CBF_FILEREAD)==CBF_FILEREAD) fprintf(stderr, " testflat: File read error.\n"); if ((err&CBF_FILESEEK)==CBF_FILESEEK) fprintf(stderr, " testflat: File seek error.\n"); if ((err&CBF_FILETELL)==CBF_FILETELL) fprintf(stderr, " testflat: File tell error.\n"); if ((err&CBF_FILEWRITE)==CBF_FILEWRITE) fprintf(stderr, " testflat: File write error.\n"); if ((err&CBF_IDENTICAL)==CBF_IDENTICAL) fprintf(stderr, " testflat: A data block with the new name already exists.\n"); if ((err&CBF_NOTFOUND)==CBF_NOTFOUND) fprintf(stderr, " testflat: The data block, category, column or" " row does not exist.\n"); if ((err&CBF_OVERFLOW)==CBF_OVERFLOW) fprintf(stderr, " testflat: The number read cannot fit into the " "destination argument.\n The destination has been set to the nearest value.\n"); if ((err& CBF_UNDEFINED)==CBF_UNDEFINED) fprintf(stderr, " testflat: The requested number is not defined (e.g. 0/0).\n"); if ((err&CBF_NOTIMPLEMENTED)==CBF_NOTIMPLEMENTED) fprintf(stderr, " testflat: The requested functionality is not yet implemented.\n"); return 0; } #undef cbf_failnez #define cbf_failnez(x) \ {int xerr; \ xerr = (x); \ if (xerr) { \ fprintf(stderr," testflat: CBFlib fatal error %d\n",xerr); \ outerror(xerr); \ outusage(); \ local_exit (-1); \ } \ } int outusage ( void ) { fprintf(stderr," \n Usage:\n"); fprintf(stderr," testflat \\\n"); fprintf(stderr," Requires testflatin.cbf\n "); fprintf(stderr," Creates testflatout.cbf\n "); return -1; } int main (int argc, char *argv []) { cbf_handle incbf, cbf; FILE *in, *out; int *image; size_t numread, nelem, elsize; unsigned int compression; int id, elsigned, elunsigned, maxel, minel; short *shimage; int i, j, k; /* Read the input test file */ if (!(in = fopen ("testflatin.cbf", "rb"))) { fprintf (stderr,"testflat: Couldn't open the input imgCIF file %s\n", "testflatin.cbf"); } else { const char * byteorder; size_t dim1, dim2, dim3, padding; cbf_failnez (cbf_make_handle (&incbf)) cbf_failnez (cbf_read_file (incbf, in, MSG_DIGEST)) cbf_failnez(cbf_find_datablock(incbf,"testflat")) cbf_failnez(cbf_find_category(incbf,"array_data")) cbf_failnez(cbf_find_column(incbf,"data")) cbf_failnez(cbf_rewind_row(incbf)) cbf_failnez ( (image = (int *)malloc(sizeof(int)*1000000))==NULL?CBF_ALLOC:0); cbf_failnez (cbf_get_integerarrayparameters_wdims (incbf, &compression, &id, &elsize, &elsigned, &elunsigned, &nelem, &maxel, &minel, &byteorder, &dim1, &dim2, &dim3, &padding)) fprintf (stderr,"testflat: element size %ld, element signed %d, element unsigned %d\n", (long)elsize, elsigned, elunsigned ); fprintf (stderr,"testflat: byte order %s, dimensions %ld, %ld, padding %ld\n", byteorder, (long)dim1, (long)dim2, (long)padding); if (compression != CBF_BYTE_OFFSET) fprintf(stderr, "testflat: Compression %x instead of CBF_BYTE_OFFSET\n", compression); if (elsize != sizeof(int)) fprintf(stderr,"testflat: element size %ld instead of %d\n", (long)elsize, (int)sizeof(int)); cbf_failnez (cbf_get_integerarray (incbf, NULL, image, sizeof (int), 0, nelem, &numread)) if (numread != 1000000) fprintf(stderr,"testflat: Read %ld instead of 1000000 ints\n", (long)numread); for (i = 0; i < 1000000; i++) { if (image[i] != 1000) { fprintf(stderr,"testflat: Mismatch for index %d, int value in file %d != %d\n", i, image[i], 1000); /* exit(-1); */ } } free(image); cbf_failnez(cbf_next_row(incbf)) cbf_failnez ( (shimage = (short *)malloc(sizeof(short)*1000000))==NULL?CBF_ALLOC:0); cbf_failnez (cbf_get_integerarrayparameters_wdims (incbf, &compression, &id, &elsize, &elsigned, &elunsigned, &nelem, &maxel, &minel, &byteorder, &dim1, &dim2, &dim3, &padding)) fprintf (stderr,"testflat: element size %ld, element signed %d, element unsigned %d\n", (long)elsize, elsigned, elunsigned ); fprintf (stderr,"testflat: byte order %s, dimensions %ld, %ld, padding %ld\n", byteorder, (long)dim1, (long)dim2, (long)padding); if (compression != CBF_BYTE_OFFSET) fprintf(stderr, "testflat: Compression %x instead of CBF_BYTE_OFFSET\n", compression); if (elsize != sizeof(short)) fprintf(stderr,"testflat: element size %ld instead of %d\n", (long)elsize, (int)sizeof(short)); cbf_failnez (cbf_get_integerarray (incbf, NULL, shimage, sizeof (short), 0, 1000000,&numread)) if (numread != 1000000) fprintf(stderr,"testflat: Read %ld instead of 1000000 shorts\n", (long)numread); for (i = 0; i < 1000000; i++) { if (shimage[i] != 1000) { fprintf(stderr,"testflat: Mismatch for index %d, short value in file %d != %d\n", i, shimage[i], 1000); /* exit(-1); */ } } free(shimage); cbf_failnez(cbf_next_row(incbf)) cbf_failnez ( (image = (int *)malloc(sizeof(int)*1000000))==NULL?CBF_ALLOC:0); cbf_failnez (cbf_get_integerarrayparameters_wdims (incbf, &compression, &id, &elsize, &elsigned, &elunsigned, &nelem, &maxel, &minel, &byteorder, &dim1, &dim2, &dim3, &padding)) fprintf (stderr,"testflat: element size %ld, element signed %d, element unsigned %d\n", (long)elsize, elsigned, elunsigned ); fprintf (stderr,"testflat: byte order %s, dimensions %ld, %ld, padding %ld\n", byteorder, (long)dim1, (long)dim2, (long)padding); if (compression != CBF_BYTE_OFFSET) fprintf(stderr, "testflat: Compression %x instead of CBF_BYTE_OFFSET\n", compression); if (elsize != sizeof(int)) fprintf(stderr,"testflat: element size %ld instead of %d\n", (long)elsize, (int)sizeof(int)); cbf_failnez (cbf_get_integerarray (incbf, NULL, image, sizeof (int), 1, nelem, &numread)) if (numread != 1000000) fprintf(stderr,"testflat: Read %ld instead of 1000000 ints\n", (long)numread); for (i = 0; i < 1000; i++) { for (j = 0; j < 1000; j++) { int dtarg; dtarg = 1000; if (i == j || i == 999-j) dtarg = -3; if (image[i+j*1000] != dtarg) fprintf(stderr,"testflat: Mismatch for index %d, int value in file %d != %d\n", i+j*1000, image[i+j*1000], dtarg); } } free(image); cbf_failnez(cbf_next_row(incbf)) cbf_failnez ( (shimage = (short *)malloc(sizeof(short)*1000000))==NULL?CBF_ALLOC:0); cbf_failnez (cbf_get_integerarrayparameters_wdims (incbf, &compression, &id, &elsize, &elsigned, &elunsigned, &nelem, &maxel, &minel, &byteorder, &dim1, &dim2, &dim3, &padding)) fprintf (stderr,"testflat: element size %ld, element signed %d, element unsigned %d\n", (long)elsize, elsigned, elunsigned ); fprintf (stderr,"testflat: byte order %s, dimensions %ld, %ld, padding %ld\n", byteorder, (long)dim1, (long)dim2, (long)padding); if (compression != CBF_BYTE_OFFSET) fprintf(stderr, "testflat: Compression %x instead of CBF_BYTE_OFFSET\n", compression); if (elsize != sizeof(short)) fprintf(stderr,"testflat: element size %ld instead of %d\n", (long)elsize, (int)sizeof(short)); cbf_failnez (cbf_get_integerarray (incbf, NULL, shimage, sizeof (short), 1, 1000000,&numread)) if (numread != 1000000) fprintf(stderr,"testflat: Read %ld instead of 1000000 shorts\n", (long)numread); for (i = 0; i < 1000; i++) { for (j = 0; j < 1000; j++) { short dtarg; dtarg = 1000; if (i == j || i == 999-j) dtarg = -3; if (shimage[i+j*1000] != dtarg) fprintf(stderr,"testflat: Mismatch for index %d, short value in file %d != %d\n", i+j*1000, shimage[i+j*1000], dtarg); } } free(shimage); cbf_failnez(cbf_next_row(incbf)) cbf_failnez ( (image = (int *)malloc(sizeof(int)*50*60*70))==NULL?CBF_ALLOC:0); cbf_failnez (cbf_get_integerarrayparameters_wdims (incbf, &compression, &id, &elsize, &elsigned, &elunsigned, &nelem, &maxel, &minel, &byteorder, &dim1, &dim2, &dim3, &padding)) fprintf (stderr,"testflat: element size %ld, element signed %d, element unsigned %d\n", (long)elsize, elsigned, elunsigned ); fprintf (stderr,"testflat: byte order %s, dimensions %ld, %ld, %ld, padding %ld\n", byteorder, (long)dim1, (long)dim2, (long)dim3, (long)padding); if (compression != CBF_BYTE_OFFSET) fprintf(stderr, "testflat: Compression %x instead of CBF_BYTE_OFFSET\n", compression); if (elsize != sizeof(int)) fprintf(stderr,"testflat: element size %ld instead of %d\n", (long)elsize, (int)sizeof(int)); cbf_failnez (cbf_get_integerarray (incbf, NULL, image, sizeof (int), 1, nelem, &numread)) if (numread != 50*60*70) fprintf(stderr,"testflat: Read %ld instead of 50*60*70 ints\n", (long)numread); for (i = 0; i < 50; i++) { for (j = 0; j < 60; j++) { for (k = 0; k < 70; k++) { int dtarg; dtarg = 1000; if (i == j || j == k ) dtarg = -3; if ((i + j*50 + k*50*60)%1000 == 0) dtarg = i+j+k; if (image[i + j*50 + k*50*60] != dtarg) fprintf(stderr,"testflat: Mismatch for index %d, int value in file %d != %d\n", i + j*50 + k*50*60, image[i + j*50 + k*50*60], dtarg ); } } } free(image); } cbf_failnez (cbf_make_handle (&cbf)) cbf_failnez(cbf_new_datablock(cbf,"testflat")) cbf_failnez(cbf_new_category(cbf,"array_data")) cbf_failnez(cbf_new_column(cbf,"data")) cbf_failnez(cbf_new_row(cbf)) /* Create an array 1000 x 1000 ints in a flat field of 1000 */ cbf_failnez ( (image = (int *)malloc(sizeof(int)*1000000))==NULL?CBF_ALLOC:0); for (i = 0; i < 1000000; i++) { image[i] = 1000; } cbf_failnez (cbf_set_integerarray_wdims (cbf, CBF_BYTE_OFFSET, 1, image, sizeof (int), 0, 1000000,"little_endian",1000,1000,0,4095)) free(image); cbf_failnez(cbf_new_row(cbf)) /* Create an array 1000 x 1000 shorts as a flat field */ cbf_failnez( (shimage = (short *)malloc(sizeof(short)*1000000))==NULL?CBF_ALLOC:0); for (i = 0; i < 1000000; i++) { shimage[i] = 1000; } cbf_failnez (cbf_set_integerarray_wdims (cbf, CBF_BYTE_OFFSET, 2, shimage, sizeof (short), 0, 1000000, "little_endian",1000,1000,0,4095)) free(shimage); cbf_failnez(cbf_new_row(cbf)) /* Create an array 1000 x 1000 signed ints in a flat field of 1000, except for -3 along the main diagonal and its transpose */ cbf_failnez ( (image = (int *)malloc(sizeof(int)*1000000))==NULL?CBF_ALLOC:0); for (i = 0; i < 1000; i++) { for (j = 0; j < 1000; j++) { image[i+j*1000] = 1000; if (i == j || i == 999-j) image[i+j*1000] = -3; } } cbf_failnez (cbf_set_integerarray_wdims (cbf, CBF_BYTE_OFFSET, 3, image, sizeof (int), 1, 1000000,"little_endian",1000,1000,0,4095)) free(image); cbf_failnez(cbf_new_row(cbf)) /* Create an array 1000 x 1000 shorts in a flat field of 1000, except for -3 along the main diagonal and its transpose */ cbf_failnez( (shimage = (short *)malloc(sizeof(short)*1000000))==NULL?CBF_ALLOC:0); for (i = 0; i < 1000; i++) { for (j = 0; j < 1000; j++) { shimage[i+j*1000] = 1000; if (i == j || i == 999-j) shimage[i+j*1000] = -3; } } cbf_failnez (cbf_set_integerarray_wdims (cbf, CBF_BYTE_OFFSET, 4, shimage, sizeof (short), 1, 1000000, "little_endian",1000,1000,0,4095)) free(shimage); cbf_failnez(cbf_new_row(cbf)) /* Create an array 50 x 60 x 70 signed ints in a flat field of 1000, except for -3 along the main diagonal and the values i+j+k every 1000th pixel */ cbf_failnez ( (image = (int *)malloc(sizeof(int)*50*60*70))==NULL?CBF_ALLOC:0); for (i = 0; i < 50; i++) { for (j = 0; j < 60; j++) { for (k = 0; k < 70; k++) { image[i + j*50 + k*50*60] = 1000; if (i == j || j == k ) image[i + j*50 + k*50*60] = -3; if ((i + j*50 + k*50*60)%1000 == 0) image[i + j*50 + k*50*60] = i+j+k; } } } cbf_failnez (cbf_set_integerarray_wdims (cbf, CBF_BYTE_OFFSET, 3, image, sizeof (int), 1, 50*60*70,"little_endian",50,60,70,4095)) free(image); /* Write the new file */ out = fopen ("testflatout.cbf", "w+b"); if (!out) { fprintf (stderr, " testflat: Couldn't open the CBF file %s\n", "testflatout.cbf"); exit (1); } cbf_failnez (cbf_write_file (cbf, out, 1, CBF, MSG_DIGEST | MIME_HEADERS, 0)) /* Free the cbf */ cbf_failnez (cbf_free_handle (cbf)) /* Success */ return 0; } int local_exit (int status) { exit(status); return 1; /* avoid warnings */ } ./CBFlib-0.9.2.2/examples/convert_minicbf.c0000644000076500007650000026755211603702122016746 0ustar yayayaya/********************************************************************** * convert_minicbf -- convert a minimal cbf to a full cbf file * * * * Version 0.7.8 2 July 2007 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * WHILE YOU MAY ALTERNATIVELY DISTRIBUTE THE API UNDER THE LGPL * * YOU MAY ***NOT*** DISTRIBUTE THIS PROGRAM UNDER THE LGPL * * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term 'this software', as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ /********************************************************************** * SYNOPSIS * * * * convert_minicbf [-i input_cbf] [-o output_cbf] [-p template_cbf]\ * * [-q] [-C convention] \ * * [-d detector name] -m [x|y|x=y] [-z distance] \ * * [-c category_alias=category_root]* \ * * [-t tag_alias=tag_root]* [-F] [-R] \ * * [input_cbf] [output_cbf] * * * * the options are: * * * * -i input_cbf (default: stdin) * * the input file as a CBF with at least an image. * * * * -p template_cbf * * the template for the final cbf to be produced. If template_cbf * * is not specified the name is constructed from the first token * * of the detector name and the image size as * * template__x.cbf * * * * -o output_cbf (default: stdout ) * * the output cbf combining the image and the template. If the * * output_cbf is not specified or is given as "-", it is written * * to stdout. * * * * -q * * exit quickly with just the miniheader expanded * * after the data. No template is used. * * * * -Q * * exit quickly with just the miniheader unexpanded * * before the data. No template is used. * * * * -C convention * * convert the comment form of miniheader into the * * _array_data.header_convention convention * * _array_data.header_contents * * overriding any existing values * * * * -d detectorname * * a detector name to be used if none is provided in the image * * header. * * * * -F * * when writing packed compression, treat the entire image as * * one line with no averaging * * * * -m [x|y|x=y] (default x=y, square arrays only) * * mirror the array in the x-axis (y -> -y) * * in the y-axis (x -> -x) * * or in x=y ( x -> y, y-> x) * * * * -r n * * rotate the array n times 90 degrees counter clockwise * * x -> y, y -> -x for each rotation, n = 1, 2 or 3 * * * * -R * * if setting a beam center, set reference values of * * axis settings as well as standard settings * * * * -z distance * * detector distance along Z-axis * * * * -c category_alias=category_root * * -t tag_alias=tagroot * * map the given alias to the given root, so that instead * * of outputting the alias, the root will be presented in the * * output cbf instead. These options may be repeated as many * * times as needed. * * * **********************************************************************/ #include "cbf.h" #include "cbf_simple.h" #include "cbf_string.h" #include #include #include #include #include #include #include "cbf_getopt.h" #include #define CVTBUFSIZ 8192 #ifdef __MINGW32__ #define NOMKSTEMP #define NOTMPDIR #endif int outusage ( void ); double rint(double); int local_exit (int status); int outerror(int err); /* parse a string from an sls comment style header and add it to cbf The strings specified by E. Eikenberry as of 13 June 2007 are: # Detector: PILATUS 6M SN01 # 2007/Jun/13 13:13:16.286 # Pixel_size 172e-6 m x 172e-6 m # Silicon sensor, thickness 0.000320 m # Exposure_time 0.095000 s # Exposure_period 0.100000 s # Tau = 0 s # Count_cutoff 1048575 counts # Threshold_setting 0 eV # Wavelength 0.7085 A # Energy_range (0, 0) eV # Detector_distance 0.79988 m # Detector_Voffset -0.00002 m # Beam_xy (1231.50, 1263.50) pixels # Flux 0 ph/s # Filter_transmission 1.0000 # Start_angle 0.0900 deg. # Angle_increment 0.0100 deg. # Detector_2theta 0.0000 deg. # Polarization 0.950 # Alpha 0.0000 deg. # Kappa 0.0000 deg. # Phi 0.0000 deg. # Chi 0.0000 deg. # Oscillation_axis X, CW # N_oscillations 1 */ #undef cbf_failnez #define cbf_failnez(x) \ {int err; \ err = (x); \ if (err) { \ fprintf(stderr," convert_minicbf: CBFlib fatal error %d\n",err); \ outerror(err); \ outusage(); \ local_exit (-1); \ } \ } int cbf_scale_units(char * actual_units, char * std_units, double * actual_per_std) { #ifdef DEBUG if (std_units) fprintf(stderr,"Scale actual |%s| to standard |%s|\n",actual_units,std_units); #endif if (!std_units || !cbf_cistrcmp(actual_units, std_units)) { *actual_per_std = 1.; return 0; } else if (strlen(actual_units) == strlen(std_units)+1 && !cbf_cistrcmp(actual_units+1,std_units)) { switch (actual_units[0]) { case ('m') : *actual_per_std = 1.e-3; break; case ('u') : *actual_per_std = 1.e-6; break; case ('n') : *actual_per_std = 1.e-9; break; case ('p') : *actual_per_std = 1.e-12; break; case ('K') : *actual_per_std = 1.e3; break; case ('M') : *actual_per_std = 1.e6; break; case ('G') : *actual_per_std = 1.e9; break; case ('T') : *actual_per_std = 1.e12; break; case ('P') : *actual_per_std = 1.e15; break; default: return CBF_FORMAT; } #ifdef DEBUG fprintf(stderr,"actual units per standard unit = %g\n", *actual_per_std); #endif return 0; } else if (strlen(actual_units) == strlen(std_units)-1 && !cbf_cistrcmp(actual_units,std_units+1)) { switch (std_units[0]) { case ('m') : *actual_per_std = 1.e3; break; case ('u') : *actual_per_std = 1.e6; break; case ('n') : *actual_per_std = 1.e9; break; case ('p') : *actual_per_std = 1.e12; break; case ('K') : *actual_per_std = 1.e-3; break; case ('M') : *actual_per_std = 1.e-6; break; case ('G') : *actual_per_std = 1.e-9; break; case ('T') : *actual_per_std = 1.e-12; break; case ('P') : *actual_per_std = 1.e-15; break; default: return CBF_FORMAT; } #ifdef DEBUG fprintf(stderr,"actual units per standard unit = %g\n", *actual_per_std); #endif return 0; } else if (strlen(actual_units) == strlen(std_units) && strlen(actual_units) > 1 && !cbf_cistrcmp(actual_units+1,std_units+1)) { switch (actual_units[0]) { case ('m') : *actual_per_std = 1.e-3; break; case ('u') : *actual_per_std = 1.e-6; break; case ('n') : *actual_per_std = 1.e-9; break; case ('p') : *actual_per_std = 1.e-12; break; case ('K') : *actual_per_std = 1.e3; break; case ('M') : *actual_per_std = 1.e6; break; case ('G') : *actual_per_std = 1.e9; break; case ('T') : *actual_per_std = 1.e12; break; case ('P') : *actual_per_std = 1.e15; break; default: return CBF_FORMAT; } switch (std_units[0]) { case ('m') : *actual_per_std *= 1.e3; break; case ('u') : *actual_per_std *= 1.e6; break; case ('n') : *actual_per_std *= 1.e9; break; case ('p') : *actual_per_std *= 1.e12; break; case ('K') : *actual_per_std *= 1.e-3; break; case ('M') : *actual_per_std *= 1.e-6; break; case ('G') : *actual_per_std *= 1.e-9; break; case ('T') : *actual_per_std *= 1.e-12; break; case ('P') : *actual_per_std *= 1.e-15; break; default: return CBF_FORMAT; } #ifdef DEBUG fprintf(stderr,"actual units per standard unit = %g\n", *actual_per_std); #endif return 0; } return CBF_FORMAT; } int cbf_parse_sls_header(cbf_handle cbf, const char * buffer, int commentflg) { double pscalex=1., pscaley=1.; double bcx, bcy, bcscalex, bcscaley, erlow, erhigh; double tempdouble, unitsratio; char * tempendptr; char * slsstr; const char * valstr; char slsbuf[2049]; char valbuf[4097]; char mxunits[33], myunits[33]; static const char *monthname [] = { "Jan", "Feb", "Mar", "Apr", "May", "Jun", "Jul", "Aug", "Sep", "Oct", "Nov", "Dec" }; #define cbf_set_value_from_string(cbf,cbfstring,cbfcat,cbfcol) \ \ cbf_failnez(cbf_require_category((cbf),(cbfcat))) \ \ while (*(cbfstring) && isspace(*(cbfstring))) (cbfstring)++; \ \ cbf_failnez(cbf_require_column((cbf),(cbfcol))) \ \ if (!cbf_get_value((cbf),(const char **)&valstr) && valstr && *valstr){\ \ if (strlen(valstr)+strlen((cbfstring))<4095) { \ \ if (*valstr != '\n') { \ \ strcpy(valbuf,"\n"); strcat(valbuf,valstr); \ \ } else { \ \ strcpy(valbuf,valstr); \ \ } \ \ strcat(valbuf,"\n"); strcat(valbuf,cbfstring); \ \ cbf_failnez(cbf_set_value((cbf),valbuf)) \ \ } else { \ \ return CBF_FORMAT; \ \ } \ \ \ } else { \ \ cbf_failnez(cbf_set_value((cbf),(cbfstring))) \ \ } \ #define cbf_set_doublevalue_from_string(cbf,cbfstring,cbfcat,cbfcol,unit) \ \ cbf_failnez(cbf_require_category((cbf),(cbfcat))) \ \ while (*(cbfstring) && isspace(*(cbfstring))) (cbfstring)++; \ \ tempdouble = strtod(cbfstring,&tempendptr); \ \ cbfstring = tempendptr; \ \ while (*(cbfstring) && isspace(*(cbfstring))) (cbfstring)++; \ \ cbf_failnez(cbf_scale_units(cbfstring, unit, &unitsratio)) \ \ tempdouble *= unitsratio; \ \ cbf_failnez(cbf_require_column((cbf),(cbfcol))) \ \ cbf_failnez(cbf_set_doublevalue((cbf),"%-15g",tempdouble)) while(*buffer) { slsstr = (char *)slsbuf; while(*buffer && (*buffer!='\r') && (*buffer!='\n') && (slsstr-slsbuf)<2047) *slsstr++=*buffer++; while(slsstr != slsbuf && isspace(*(slsstr-1))) slsstr--; *slsstr='\0'; slsstr = (char *)slsbuf; /* skip all initial whitespace */ while (*slsstr && isspace(*slsstr)) slsstr++; if (strlen(slsstr) == 0) { while (*buffer && ((*buffer=='\r') || (*buffer=='\n'))) buffer++; continue; } #ifdef DEBUG fprintf(stderr,"Processing %s\n",slsstr); #endif /* if we have specified that this must be a comment require a leading "# " abort if not */ if (commentflg) { if (strlen(slsstr) < 2 || slsstr[0] != '#' || !isspace(slsstr[1])) return CBF_FORMAT; slsstr += 2; } while (*slsstr && isspace(*slsstr)) slsstr++; if (slsstr[0] == '#') { slsstr++; while (*slsstr && isspace(*slsstr)) slsstr++; } /* check for Detector: PILATUS 6M SN01 */ if (!cbf_cistrncmp(slsstr,"Detector: ",strlen("Detector: "))) { char * ptr; slsstr += strlen("Detector: "); while (*slsstr && isspace(*slsstr)) slsstr++; ptr = slsstr; while (*ptr && (cbf_cistrncmp(ptr," SN",3))&&(cbf_cistrncmp(ptr," S/N",4))) ptr++; if (*ptr) *ptr++ = 0; while (*ptr && isspace(*ptr)) ptr++; cbf_set_value_from_string(cbf,slsstr,"diffrn_detector","type") cbf_set_value_from_string(cbf,ptr,"diffrn_detector","details") } else /* check for 2007/Jun/13 13:13:16.286 */ if (strlen(slsstr)>=11 && (slsstr[4]=='/' || slsstr[4]=='-' ) && (slsstr[8]=='/' || slsstr[8]=='-') ){ char *endptr; int errflg; int notime; int yyyy,mm,dd,hr,mn; double ss; errflg = 0; yyyy = strtol(slsstr,&endptr,10); if (*endptr == '/' || *endptr == '-') { slsstr = endptr+1; for (mm = 1; mm < 13; mm++) { if (!cbf_cistrncmp(monthname[mm-1],slsstr,3)) break; } if (mm > 12) errflg++; else { slsstr+=4; dd = strtol(slsstr,&endptr,10); hr = mn = ss = 0; notime=1; if (*endptr && (isspace(*endptr)||*endptr=='T'||*endptr=='t'||*endptr==':')) { slsstr = endptr+1; hr = strtol(slsstr,&endptr,10); if (*endptr == ':') { notime = 0; slsstr = endptr+1; mn = strtol(slsstr,&endptr,10); if (*endptr==':') { slsstr = endptr+1; ss = strtod(slsstr,&endptr); } } } } } else errflg++; if (!errflg) { cbf_failnez (cbf_set_datestamp (cbf, 0, yyyy, mm, dd, hr, mn, ss, CBF_NOTIMEZONE,.001)) } } else /* check for Pixel_size 172e-6 m x 172e-6 m */ if (!cbf_cistrncmp(slsstr,"Pixel_size ",strlen("Pixel_size "))) { char *endptr; double psx, psy; slsstr += strlen("Pixel_size "); pscalex = pscaley = 1.; psy = psx = strtod (slsstr, &endptr); if (endptr && *endptr) { slsstr = endptr; while (*slsstr && isspace(*slsstr)) slsstr++; if (!cbf_cistrncmp("m ",slsstr,2)) slsstr += 2; else if (!cbf_cistrncmp("mm ",slsstr,2) || !cbf_cistrcmp("mm",slsstr)) { slsstr +=2; pscaley = pscalex = 1.e-3; } else { pscaley = pscalex = 1.e-6; } while (*slsstr && isspace(*slsstr)) slsstr++; if (*slsstr == 'x' || *slsstr == 'X' || *slsstr==',') { slsstr++; while (*slsstr && isspace(*slsstr)) slsstr++; } if (*slsstr) { psy = strtod (slsstr, &endptr); if (endptr && *endptr) { slsstr = endptr; while (*slsstr && isspace(*slsstr)) slsstr++; if (!cbf_cistrncmp("m ",slsstr,2)|| !cbf_cistrcmp("m",slsstr)) slsstr ++; else if ( !cbf_cistrncmp("mm ",slsstr,2) || !cbf_cistrcmp("mm",slsstr) ) { slsstr +=2; pscaley = 1.e-3; } else { pscaley = 1.e-6; } } } } psx *= pscalex; psy *= pscaley; cbf_failnez(cbf_require_category(cbf,"array_element_size")) cbf_failnez(cbf_require_column(cbf,"index")) cbf_failnez(cbf_set_integervalue(cbf,1)) cbf_failnez(cbf_require_column(cbf,"size")) cbf_failnez(cbf_set_doublevalue(cbf,"%-15g",psx)) cbf_failnez(cbf_next_row(cbf)) cbf_failnez(cbf_require_column(cbf,"index")) cbf_failnez(cbf_set_integervalue(cbf,2)) cbf_failnez(cbf_require_column(cbf,"size")) cbf_failnez(cbf_set_doublevalue(cbf,"%-15g",psy)) } else /* Check for Silicon sensor, thickness 0.000320 m */ if (!cbf_cistrncmp(slsstr,"Silicon sensor, thickness ",strlen("Silicon sensor, thickness "))) { cbf_set_value_from_string(cbf,slsstr,"diffrn_detector","details") } else /* check for Exposure_time 0.095000 s */ if (!cbf_cistrncmp(slsstr,"Exposure_time ",strlen("Exposure time "))) { slsstr += strlen("Exposure time: "); cbf_set_doublevalue_from_string(cbf,slsstr,"diffrn_scan_frame","integration_time","s") } else /* check for Exposure_period 0.100000 s */ if (!cbf_cistrncmp(slsstr,"Exposure_period ",strlen("Exposure_period "))) { slsstr += strlen("Exposure_period "); cbf_set_doublevalue_from_string(cbf,slsstr,"diffrn_scan_frame","integration_period","s") } else /* check for Tau = 0 s */ if (!cbf_cistrncmp(slsstr,"Tau = ",strlen("Tau = "))) { slsstr += strlen("Tau = "); cbf_set_doublevalue_from_string(cbf,slsstr,"diffrn_radiation","tau","s") } else /* check for Count_cutoff 1048575 counts */ if (!cbf_cistrncmp(slsstr,"Count_cutoff ", strlen("Count_cutoff "))) { slsstr += strlen("Count_cutoff "); cbf_set_doublevalue_from_string(cbf,slsstr,"array_intensities","overload","counts") } else /* check for Threshold_setting 0 eV */ if (!cbf_cistrncmp(slsstr,"Threshold_setting ", strlen("Threshold_setting "))) { slsstr += strlen("Threshold_setting "); cbf_set_doublevalue_from_string(cbf,slsstr,"diffrn_detector","threshold","eV") } else /* check for Wavelength 0.7085 A */ if (!cbf_cistrncmp(slsstr,"wavelength ",strlen("wavelength "))) { slsstr += strlen("wavelength "); cbf_set_doublevalue_from_string(cbf,slsstr,"diffrn_radiation_wavelength","wavelength","A") } else /* check for Energy_range (0, 0) eV */ if (!cbf_cistrncmp(slsstr,"Energy_range ", strlen("Energy_range "))) { char *endptr; slsstr += strlen("Energy_range "); erlow = erhigh = 0.; if (*slsstr == '(' || *slsstr == '[' || *slsstr == '{') slsstr++; while (*slsstr && isspace(*slsstr)) slsstr++; erlow = erhigh = strtod (slsstr, &endptr); if (endptr && *endptr) { slsstr = endptr; while (*slsstr && isspace(*slsstr)) slsstr++; if (*slsstr == ',' ) slsstr++; while (*slsstr && isspace(*slsstr)) slsstr++; if (*slsstr) { erhigh = strtod (slsstr, &endptr); if (endptr && *endptr) slsstr = endptr; while (*slsstr && isspace(*slsstr)) slsstr++; } } while (*slsstr && isspace(*slsstr)) slsstr++; if (*slsstr == ')' || *slsstr == ']' || *slsstr == '}') slsstr++; while (*slsstr && isspace(*slsstr)) slsstr++; if (!cbf_cistrncmp("eV",slsstr,2)) { cbf_failnez(cbf_require_category(cbf,"diffrn_detector")) cbf_failnez(cbf_require_column(cbf,"energy_range_low")) cbf_failnez(cbf_set_doublevalue(cbf,"%-15g",erlow)) cbf_failnez(cbf_require_column(cbf,"energy_range_high")) } else { cbf_failnez(CBF_FORMAT); } } else /* check for Detector_distance 0.79988 m */ if (!cbf_cistrncmp(slsstr,"Detector_distance ", strlen("Detector_distance "))) { slsstr += strlen("Detector_distance "); cbf_set_doublevalue_from_string(cbf,slsstr,"diffrn_measurement", "sample_detector_distance", "mm"); } else /* check for Detector_Voffset -0.00002 m */ if (!cbf_cistrncmp(slsstr,"Detector_Voffset ", strlen("Detector_Voffset "))) { slsstr += strlen("Detector_Voffset "); cbf_set_doublevalue_from_string(cbf,slsstr,"diffrn_measurement", "sample_detector_voffset", "mm"); } else /* check for Beam_xy (1231.50, 1263.50) pixels */ if (!cbf_cistrncmp(slsstr,"beam_xy ", strlen("beam_xy "))) { char *endptr; char *bcunits; slsstr += strlen("beam_xy "); bcscalex = bcscaley = 1.; bcunits = "unknown"; while (*slsstr && isspace(*slsstr)) slsstr++; if (*slsstr == '(' || *slsstr == '[' || *slsstr == '{') slsstr++; while (*slsstr && isspace(*slsstr)) slsstr++; bcy = bcx = strtod (slsstr, &endptr); if (endptr && *endptr) { slsstr = endptr; while (*slsstr && isspace(*slsstr)) slsstr++; endptr = mxunits; while ((endptr-mxunits)<32 && *slsstr && *slsstr!=',' && *slsstr!=')' && *slsstr!=']' && *slsstr!='}' && !(isspace(*slsstr)) && !(isdigit(*slsstr))) *endptr++=*slsstr++; *endptr='\0'; while (*slsstr && isspace(*slsstr)) slsstr++; if (!cbf_scale_units(mxunits, "mm",&bcscalex)) { bcscaley = bcscalex; bcunits = "mm"; } else if (!cbf_scale_units(mxunits, "pixels",&bcscalex)) { bcscaley = bcscalex; bcunits = "pixels"; } else if (!cbf_scale_units(mxunits, "bins",&bcscalex)) { bcscaley = bcscalex; bcunits = "bins"; } else { bcscaley = bcscalex = 1.; bcunits = mxunits; } if (*slsstr == ',' ) slsstr++; while (*slsstr && isspace(*slsstr)) slsstr++; if (*slsstr) { bcy = strtod (slsstr, &endptr); while (*slsstr && isspace(*slsstr)) slsstr++; endptr = myunits; while ((endptr-myunits)<32 && *slsstr && *slsstr!=',' && *slsstr!=')' && *slsstr!=']' && *slsstr!='}' && !(isspace(*slsstr)) && !(isdigit(*slsstr))) *endptr++=*slsstr++; *endptr='\0'; while (*slsstr && isspace(*slsstr)) slsstr++; if (!cbf_cistrcmp(bcunits,"unknown") || !*bcunits) { if (!cbf_scale_units(myunits, "mm",&bcscalex)) { bcscaley = bcscalex; bcunits = "mm"; } else if (!cbf_scale_units(myunits, "pixels",&bcscalex)) { bcscaley = bcscalex; bcunits = "pixels"; } else if (!cbf_scale_units(myunits, "bins",&bcscalex)) { bcscaley = bcscalex; bcunits = "bins"; } else { bcscaley = bcscalex = 1.; bcunits = myunits; } } else { if (!cbf_scale_units(myunits, "mm",&bcscaley)) { if (cbf_cistrcmp(bcunits,"mm")) return CBF_FORMAT; } else if (!cbf_scale_units(myunits, "pixels",&bcscaley)) { if (cbf_cistrcmp(bcunits,"pixels")) return CBF_FORMAT; } else if (!cbf_scale_units(myunits, "bins",&bcscaley)) { if (cbf_cistrcmp(bcunits,"bins")) return CBF_FORMAT; } else { bcscaley = 1.; if (cbf_cistrcmp(bcunits,myunits)) return CBF_FORMAT; } } } else { if (*slsstr == ')' || *slsstr == ']' || *slsstr != ']') slsstr++; } } while (*slsstr && isspace(*slsstr)) slsstr++; if (*slsstr == ')' || *slsstr == ']' || *slsstr == '}') slsstr++; while (*slsstr && isspace(*slsstr)) slsstr++; if (*bcunits || !cbf_cistrcmp(bcunits,"unknown") ){ endptr = mxunits; while ((endptr-myunits)<32 && *slsstr && *slsstr!=',' && *slsstr!=')' && *slsstr!=']' && *slsstr!='}' && !(isspace(*slsstr)) && !(isdigit(*slsstr))) *endptr++=*slsstr++; *endptr='\0'; while (*slsstr && isspace(*slsstr)) slsstr++; if (!cbf_scale_units(mxunits, "mm",&bcscalex)) { bcscaley = bcscalex; bcunits = "mm"; } else if (!cbf_scale_units(mxunits, "pixels",&bcscalex)) { bcscaley = bcscalex; bcunits = "pixels"; } else if (!cbf_scale_units(mxunits, "bins",&bcscalex)) { bcscaley = bcscalex; bcunits = "bins"; } else { bcscaley = bcscalex = 1.; bcunits = mxunits; } } if (!*bcunits || !cbf_cistrcmp(bcunits,"unknown") ) { bcunits = "pixels"; bcscaley = bcscalex = 1.; } bcx *= bcscalex; bcy *= bcscaley; cbf_failnez(cbf_require_category(cbf,"diffrn_detector_element")) cbf_failnez(cbf_require_column(cbf,"reference_center_fast")) cbf_failnez(cbf_set_doublevalue(cbf,"%-15g",bcx)) cbf_failnez(cbf_require_column(cbf,"reference_center_slow")) cbf_failnez(cbf_set_doublevalue(cbf,"%-15g",bcy)) cbf_failnez(cbf_require_column(cbf,"reference_center_units")) cbf_failnez(cbf_set_value(cbf,bcunits)) } else /* check for Flux 0 ph/s */ if (!cbf_cistrncmp(slsstr,"Flux ", strlen("Flux "))) { slsstr += strlen("Flux "); while (*slsstr && isspace(*slsstr)) slsstr++; cbf_set_doublevalue_from_string(cbf,slsstr,"diffrn_radiation","flux","ph/s"); } else /* check for Filter_transmission 1.0000 */ if (!cbf_cistrncmp(slsstr,"Filter_transmission ", strlen("Filter_transmission "))) { slsstr += strlen("Filter_transmission "); while (*slsstr && isspace(*slsstr)) slsstr++; cbf_set_doublevalue_from_string(cbf,slsstr,"diffrn_radiation","filter_transmission",NULL); } else /* check for Start_angle 0.0900 deg. */ if (!cbf_cistrncmp(slsstr,"Start_angle ", strlen("Start_angle "))) { double scan; char *endptr; cbf_failnez(cbf_require_category(cbf,"diffrn_scan_frame_axis")) cbf_failnez(cbf_require_column(cbf,"axis_id")) cbf_failnez(cbf_require_row(cbf,"GONIOMETER_SCAN")) cbf_failnez(cbf_require_column(cbf,"angle")) slsstr += strlen("Start_angle "); while (*slsstr && isspace(*slsstr)) slsstr++; scan = strtod(slsstr,&endptr); cbf_failnez(cbf_set_doublevalue(cbf,"%-15g",scan)) } else /* check for Oscillation_axis X, CW */ if (!cbf_cistrncmp(slsstr,"Oscillation_axis ", strlen("Oscillation_axis "))) { slsstr += strlen("Oscillation_axis "); while (*slsstr && isspace(*slsstr)) slsstr++; cbf_failnez(cbf_require_category(cbf,"diffrn_scan_frame_axis")) cbf_failnez(cbf_require_column(cbf,"axis_id")) cbf_failnez(cbf_require_row(cbf,"GONIOMETER_SCAN")) cbf_failnez(cbf_require_column(cbf,"axis_description")) cbf_failnez(cbf_set_value(cbf,slsstr)) } else /* check for Angle_increment 0.0100 deg. */ if (!cbf_cistrncmp(slsstr,"Angle_increment ", strlen("Angle_increment "))) { double scan; char * endptr; cbf_failnez(cbf_require_category(cbf,"diffrn_scan_frame_axis")) cbf_failnez(cbf_require_column(cbf,"axis_id")) cbf_failnez(cbf_require_row(cbf,"GONIOMETER_SCAN")) cbf_failnez(cbf_require_column(cbf,"angle_increment")) slsstr += strlen("Angle_increment "); while (*slsstr && isspace(*slsstr)) slsstr++; scan = strtod(slsstr, &endptr); cbf_failnez(cbf_set_doublevalue(cbf,"%-15g",scan)) } else /* check for Detector_2theta 0.0000 deg. */ if (!cbf_cistrncmp(slsstr,"Detector_2theta ", strlen("Detector_2theta "))) { double twotheta; char *endptr; slsstr += strlen("Detector_2theta "); while (*slsstr && isspace(*slsstr)) slsstr++; twotheta = strtod(slsstr, &endptr); cbf_failnez(cbf_require_category(cbf,"diffrn_scan_frame_axis")) cbf_failnez(cbf_require_column(cbf,"axis_id")) cbf_failnez(cbf_require_row(cbf,"DETECTOR_TWOTHETA")) cbf_failnez(cbf_require_column(cbf,"angle")) cbf_failnez(cbf_set_doublevalue(cbf,"%-15g",twotheta)) } else /* check for Polarization 0.950 */ if (!cbf_cistrncmp(slsstr,"Polarization ", strlen("Polarization "))) { slsstr += strlen("Polarization "); while (*slsstr && isspace(*slsstr)) slsstr++; cbf_set_doublevalue_from_string(cbf,slsstr,"diffrn_radiation","polarizn_source_ratio",NULL); } else /* check for Alpha 0.0000 deg. */ if (!cbf_cistrncmp(slsstr,"Alpha ", strlen("Alpha "))) { double alpha; char *endptr; slsstr += strlen("Alpha "); while (*slsstr && isspace(*slsstr)) slsstr++; alpha = strtod(slsstr, &endptr); cbf_failnez(cbf_require_category(cbf,"diffrn_scan_frame_axis")) cbf_failnez(cbf_require_column(cbf,"axis_id")) cbf_failnez(cbf_require_row(cbf,"GONIOMETER_ALPHA")) cbf_failnez(cbf_require_column(cbf,"angle")) cbf_failnez(cbf_set_doublevalue(cbf,"%-15g",alpha)) } else /* check for Omega 0.0000 deg. */ if (!cbf_cistrncmp(slsstr,"Omega ", strlen("Omega "))) { double omega; char *endptr; slsstr += strlen("Omega "); while (*slsstr && isspace(*slsstr)) slsstr++; omega = strtod(slsstr, &endptr); cbf_failnez(cbf_require_category(cbf,"diffrn_scan_frame_axis")) cbf_failnez(cbf_require_column(cbf,"axis_id")) cbf_failnez(cbf_require_row(cbf,"GONIOMETER_OMEGA")) cbf_failnez(cbf_require_column(cbf,"angle")) cbf_failnez(cbf_set_doublevalue(cbf,"%-15g",omega)) } else /* check for Kappa 0.0000 deg. */ if (!cbf_cistrncmp(slsstr,"Kappa ", strlen("Kappa "))) { double kappa; char *endptr; slsstr += strlen("Kappa "); while (*slsstr && isspace(*slsstr)) slsstr++; kappa = strtod(slsstr, &endptr); cbf_failnez(cbf_require_category(cbf,"diffrn_scan_frame_axis")) cbf_failnez(cbf_require_column(cbf,"axis_id")) cbf_failnez(cbf_require_row(cbf,"GONIOMETER_KAPPA")) cbf_failnez(cbf_require_column(cbf,"angle")) cbf_failnez(cbf_set_doublevalue(cbf,"%-15g",kappa)) } else if (!cbf_cistrncmp(slsstr,"Chi ", strlen("Chi "))) { double chi; char *endptr; slsstr += strlen("Chi "); while (*slsstr && isspace(*slsstr)) slsstr++; chi = strtod(slsstr, &endptr); cbf_failnez(cbf_require_category(cbf,"diffrn_scan_frame_axis")) cbf_failnez(cbf_require_column(cbf,"axis_id")) cbf_failnez(cbf_require_row(cbf,"GONIOMETER_CHI")) cbf_failnez(cbf_require_column(cbf,"angle")) cbf_failnez(cbf_set_doublevalue(cbf,"%-15g",chi)) } else if (!cbf_cistrncmp(slsstr,"Phi ", strlen("Phi "))) { double phi; char *endptr; slsstr += strlen("Phi "); while (*slsstr && isspace(*slsstr)) slsstr++; phi = strtod(slsstr, &endptr); cbf_failnez(cbf_require_category(cbf,"diffrn_scan_frame_axis")) cbf_failnez(cbf_require_column(cbf,"axis_id")) cbf_failnez(cbf_require_row(cbf,"GONIOMETER_PHI")) cbf_failnez(cbf_require_column(cbf,"angle")) cbf_failnez(cbf_set_doublevalue(cbf,"%-15g",phi)) } else /* check for N_oscillations 1 */ if (!cbf_cistrncmp(slsstr,"N_oscillations ", strlen("N_oscillations "))) { slsstr += strlen("N_oscillations "); while (*slsstr && isspace(*slsstr)) slsstr++; cbf_set_doublevalue_from_string(cbf,slsstr,"diffrn_scan_frame","oscillations",NULL); } else { /* cbf_failnez(CBF_FORMAT); */ fprintf(stderr," convert_minicbf: warning did not recognize miniheader string %s\n",slsstr); } while (*buffer && ((*buffer=='\r') || (*buffer=='\n'))) buffer++; } return 0; } int outerror(int err) { if ((err&CBF_FORMAT)==CBF_FORMAT) fprintf(stderr, " convert_minicbf: The file format is invalid.\n"); if ((err&CBF_ALLOC)==CBF_ALLOC) fprintf(stderr, " convert_minicbf Memory allocation failed.\n"); if ((err&CBF_ARGUMENT)==CBF_ARGUMENT) fprintf(stderr, " convert_minicbf: Invalid function argument.\n"); if ((err&CBF_ASCII)==CBF_ASCII) fprintf(stderr, " convert_minicbf: The value is ASCII (not binary).\n"); if ((err&CBF_BINARY)==CBF_BINARY) fprintf(stderr, " convert_minicbf: The value is binary (not ASCII).\n"); if ((err&CBF_BITCOUNT)==CBF_BITCOUNT) fprintf(stderr, " convert_minicbf: The expected number of bits does" " not match the actual number written.\n"); if ((err&CBF_ENDOFDATA)==CBF_ENDOFDATA) fprintf(stderr, " convert_minicbf: The end of the data was reached" " before the end of the array.\n"); if ((err&CBF_FILECLOSE)==CBF_FILECLOSE) fprintf(stderr, " convert_minicbf: File close error.\n"); if ((err&CBF_FILEOPEN)==CBF_FILEOPEN) fprintf(stderr, " convert_minicbf: File open error.\n"); if ((err&CBF_FILEREAD)==CBF_FILEREAD) fprintf(stderr, " convert_minicbf: File read error.\n"); if ((err&CBF_FILESEEK)==CBF_FILESEEK) fprintf(stderr, " convert_minicbf: File seek error.\n"); if ((err&CBF_FILETELL)==CBF_FILETELL) fprintf(stderr, " convert_minicbf: File tell error.\n"); if ((err&CBF_FILEWRITE)==CBF_FILEWRITE) fprintf(stderr, " convert_minicbf: File write error.\n"); if ((err&CBF_IDENTICAL)==CBF_IDENTICAL) fprintf(stderr, " convert_minicbf: A data block with the new name already exists.\n"); if ((err&CBF_NOTFOUND)==CBF_NOTFOUND) fprintf(stderr, " convert_minicbf: The data block, category, column or" " row does not exist.\n"); if ((err&CBF_OVERFLOW)==CBF_OVERFLOW) fprintf(stderr, " convert_minicbf: The number read cannot fit into the" "destination argument.\n The destination has been set to the nearest value.\n"); if ((err& CBF_UNDEFINED)==CBF_UNDEFINED) fprintf(stderr, " convert_minicbf: The requested number is not defined (e.g. 0/0).\n"); if ((err&CBF_NOTIMPLEMENTED)==CBF_NOTIMPLEMENTED) fprintf(stderr, " convert_minicbf: The requested functionality is not yet implemented.\n"); return 0; } #undef cbf_failnez #define cbf_failnez(x) \ {int err; \ err = (x); \ if (err) { \ fprintf(stderr," convert_minicbf: CBFlib fatal error %d\n",err); \ outerror(err); \ outusage(); \ local_exit (-1); \ } \ } typedef enum { posx=1, posy=2, negx=-1, negy=-2 } axes; typedef struct { axes posxtarg, posytarg; } axisxform; int outusage ( void ) { fprintf(stderr," \n Usage:\n"); fprintf(stderr," convert_minicbf [-i input_cbf] [-o output_cbf] [-p template_cbf]\\\n"); fprintf(stderr," [-q] [-C convention] \\\n"); fprintf(stderr," [-d detector name] -m [x|y|x=y] [-z distance] \\\n"); fprintf(stderr," [-c category_alias=category_root]* \\\n"); fprintf(stderr," [-t tag_alias=tag_root]* [-F] [-R]\\\n"); fprintf(stderr," [input_cbf] [output_cbf]\n"); fprintf(stderr," the options are:\n"); fprintf(stderr," -i input_cbf (default: stdin)\n"); fprintf(stderr," the input file as a CBF with at least an image.\n"); fprintf(stderr," -p template_cbf\n"); fprintf(stderr," the template for the final cbf to be produced. If template_cbf\n"); fprintf(stderr," is not specified the name is constructed from the first token\n"); fprintf(stderr," of the detector name and the image size as\n"); fprintf(stderr," template__x.cbf\n"); fprintf(stderr," -o output_cbf (default: stdout )\n"); fprintf(stderr," the output cbf combining the image and the template. If the\n"); fprintf(stderr," output_cbf is not specified or is given as \"-\", it is written\n"); fprintf(stderr," to stdout.\n"); fprintf(stderr," -q\n"); fprintf(stderr," exit quickly with just the miniheader expanded\n"); fprintf(stderr," after the data. No template is used.\n"); fprintf(stderr," -Q\n"); fprintf(stderr," exit quickly with just the miniheader unexpanded\n"); fprintf(stderr," before the data. No template is used.\n"); fprintf(stderr," -C convention\n"); fprintf(stderr," convert the comment form of miniheader into the\n"); fprintf(stderr," _array_data.header_convention convention\n"); fprintf(stderr," _array_data.header_contents\n"); fprintf(stderr," overriding any existing values\n"); fprintf(stderr," -d detectorname\n"); fprintf(stderr," a detector name to be used if none is provided in the image\n"); fprintf(stderr," header.\n"); fprintf(stderr," -F\n"); fprintf(stderr," when writing packed compression, treat the entire image as\n"); fprintf(stderr," one line with no averaging \n"); fprintf(stderr," -m [x|y|x=y] (default x=y, square arrays only)\n"); fprintf(stderr," mirror the array in the x-axis (y -> -y)\n"); fprintf(stderr," in the y-axis (x -> -x)\n"); fprintf(stderr," or in x=y ( x -> y, y-> x)\n"); fprintf(stderr," -r n\n"); fprintf(stderr," rotate the array n times 90 degrees counter clockwise\n"); fprintf(stderr," x -> y, y -> -x for each rotation, n = 1, 2 or 3\n"); fprintf(stderr," -R \n"); fprintf(stderr," if setting a beam center, set reference values of\n"); fprintf(stderr," axis settings as well as standard settings\n"); fprintf(stderr," -u \n"); fprintf(stderr," write the image as unsigned short.\n"); fprintf(stderr," -z distance\n"); fprintf(stderr," detector distance along Z-axis.\n"); fprintf(stderr," -c category_alias=category_root\n"); fprintf(stderr," -t tag_alias=tagroot\n"); fprintf(stderr," map the given alias to the given root, so that instead\n"); fprintf(stderr," of outputting the alias, the root will be presented in the\n"); fprintf(stderr," output cbf instead. These options may be repeated as many\n"); fprintf(stderr," times as needed.\n"); return -1; } void applyxform(axisxform * current, axisxform * xform) { switch (current->posxtarg) { case (posx): current->posxtarg = xform->posxtarg; break; case (posy): current->posxtarg = xform->posytarg; break; case (negx): current->posxtarg = xform->posxtarg==posx?negx: (xform->posxtarg==negx?posx: (xform->posxtarg==posy?negy: (xform->posxtarg==negy?posy:0))); break; case (negy): current->posxtarg = xform->posytarg==posx?negx: (xform->posytarg==negx?posx: (xform->posytarg==posy?negy: (xform->posytarg==negy?posy:0))); break; } switch (current->posytarg) { case (posx): current->posytarg = xform->posxtarg; break; case (posy): current->posytarg = xform->posytarg; break; case (negx): current->posytarg = xform->posxtarg==posx?negx: (xform->posxtarg==negx?posx: (xform->posxtarg==posy?negy: (xform->posxtarg==negy?posy:0))); break; case (negy): current->posytarg = xform->posytarg==posx?negx: (xform->posytarg==negx?posx: (xform->posytarg==posy?negy: (xform->posytarg==negy?posy:0))); break; } return; } int main (int argc, char *argv []) { FILE *in, *out, *file; cbf_handle minicbf; cbf_handle cbf; char detector_type [64], template_name [256], *c; const char *detector_name, *detector_opt, *array_id; const char *datablockname; char *header_info; char *header_info_copy; size_t header_info_size; size_t header_info_cap; int dorefs; axisxform overall = { posx, posy }; axisxform mirrorx = { posx, negy }; axisxform mirrory = { negx, posy }; axisxform mirrorxy = { posy, posx }; axisxform rotate1 = { posy, negx }; axisxform rotate2 = { negx, negy }; axisxform rotate3 = { negy, posx }; axisxform * currentxform; int copt; int errflg = 0; char cbfintmp[19]; #ifndef NOMKSTEMP int cbfintmpfd; #endif int cbfintmpused = 0; char buf[CVTBUFSIZ]; const char *cbfin, *cbfout, *template, *distancestr, *alias; const char *convention; char *root; char xalias[81]; int transpose; int fastlen, slowlen; int flat; int quick; int unshort; unsigned int compression; int binary_id; size_t elsize; int elsigned; int elunsigned; size_t elements, elements_read; int minelement; int maxelement; char *byteorder ="little_endian"; size_t dim1; size_t dim2; size_t dim3; size_t padding; unsigned char *image; size_t nbytes; const char * optarg; cbf_getopt_handle opts; /* Usage */ cbfin = NULL; cbfout = NULL; template = NULL; detector_opt = NULL; transpose = 0; distancestr = NULL; convention = NULL; dorefs = 0; flat = 0; quick = 0; unshort = 0; cbf_failnez (cbf_make_handle (&cbf)) cbf_failnez(cbf_make_getopt_handle(&opts)) cbf_failnez(cbf_getopt_parse(opts, argc, argv, "FRQqui:o:p:C:d:m:r:z:c:t:")) if (!cbf_rewind_getopt_option(opts)) for(;!cbf_get_getopt_data(opts,&copt,NULL,NULL,&optarg);cbf_next_getopt_option(opts)) { if (!copt) break; switch(copt) { case 'i': if (cbfin) errflg++; else cbfin = optarg; break; case 'o': if (cbfout) errflg++; else cbfout = optarg; break; case 'q': if (quick) errflg++; else quick=1; break; case 'Q': if (quick) errflg++; else quick=-1; break; case 'p': if (template) errflg++; else template = optarg; break; case 'F': flat = 1; break; case 'C': if (convention) errflg++; else convention = optarg; break; case 'm': currentxform = (axisxform *)NULL; if (!strcmp(optarg,"x")) currentxform = &mirrorx; if (!strcmp(optarg,"y")) currentxform = &mirrory; if (!strcmp(optarg,"x=y")) currentxform = &mirrorxy; if (!currentxform) errflg++; else applyxform(&overall,currentxform); break; case 'r': currentxform = (axisxform *)NULL; if (!strcmp(optarg,"1")) currentxform = &rotate1; if (!strcmp(optarg,"2")) currentxform = &rotate2; if (!strcmp(optarg,"3")) currentxform = &rotate3; if (!currentxform) errflg++; else applyxform(&overall,currentxform); break; case 'R': dorefs = 1; break; case 'u': unshort = 1; break; case 'd': if (detector_opt) errflg++; else detector_opt = optarg; break; case 'z': if (distancestr) errflg++; else distancestr = optarg; break; case 'c': case 't': alias = optarg; if (alias == NULL || *alias == '\0') { errflg++; break; } root = strchr(alias,'='); if (root == NULL || root-alias > 80 || root-alias < 2 || *(root+1) =='\0') { errflg++; break; } strncpy(xalias,optarg,root-alias); xalias[root-alias] = '\0'; root++; if(copt == 'c') { cbf_failnez (cbf_set_category_root(cbf, (const char *)xalias, (const char *) root)) } else { cbf_failnez (cbf_set_tag_root(cbf, (const char *)xalias, (const char *) root)) } break; default: errflg++; break; } } for(;!cbf_get_getopt_data(opts,&copt,NULL,NULL,&optarg);cbf_next_getopt_option(opts)) { if (!cbfin) { cbfin = optarg; } else { if (!cbfout) { cbfout = optarg; } else { errflg++; } } } if (errflg) { outusage(); exit(-1); } if (!cbfin || strcmp(cbfin?cbfin:"","-") == 0) { #ifdef NOTMPDIR strcpy(cbfintmp, "cif2cbfXXXXXX"); #else strcpy(cbfintmp, "/tmp/cif2cbfXXXXXX"); #endif #ifdef NOMKSTEMP if (mktemp(cbfintmp) == NULL ) { fprintf(stderr,"\n convert_minicbf: Can't create temporary file name %s.\n", cbfintmp); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } if ( (file = fopen(cbfintmp,"wb+")) == NULL) { fprintf(stderr,"Can't open temporary file %s.\n", cbfintmp); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } #else if ((cbfintmpfd = mkstemp(cbfintmp)) == -1 ) { fprintf(stderr,"\n convert_minicbf: Can't create temporary file name %s.\n", cbfintmp); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } if ( (file = fdopen(cbfintmpfd, "w+")) == NULL) { fprintf(stderr,"Can't open temporary file %s.\n", cbfintmp); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } #endif while ((nbytes = fread(buf, 1, CVTBUFSIZ, stdin))) { if(nbytes != fwrite(buf, 1, nbytes, file)) { fprintf(stderr,"Failed to write %s.\n", cbfintmp); exit(1); } } fclose(file); cbfin = cbfintmp; cbfintmpused = 1; } /* Read the minicbf */ if (!(in = fopen (cbfin, "rb"))) { fprintf (stderr,"Couldn't open the input minicbf file %s\n", cbfin); exit (1); } cbf_failnez (cbf_make_handle (&minicbf)) cbf_failnez (cbf_read_widefile (minicbf, in, MSG_DIGEST)) header_info_size = 0; header_info_cap = 0; header_info = NULL; if (!convention && !cbf_find_tag(minicbf,"_array_data.header_contents")) { cbf_failnez(cbf_get_value(minicbf,(const char * *)&header_info)) cbf_parse_sls_header(minicbf, header_info, 0); } else { char * lead = " "; if (quick) lead = "# "; if (!(in = fopen (cbfin, "rb"))) { fprintf (stderr,"Couldn't open the input minicbf file %s\n", cbfin); exit (1); } while (fgets(buf,CVTBUFSIZ,in)) { size_t slen; int ignore; char * bufptr; slen = strlen(buf); if (slen > 0 && buf[slen-1]=='\n') buf[slen] = '\0'; if (!strncmp(buf,"##",2)) continue; ignore = 1; bufptr = buf; while(*bufptr) { if (!isspace(*bufptr)) break; bufptr++; } if (!*bufptr) continue; if (*bufptr != '#') break; if (!strncmp(bufptr,"# ",2)) { if (header_info_size+strlen(bufptr+2)+4 > header_info_cap) { char * nheader_info; size_t nheader_info_cap; size_t ii; nheader_info_cap = 2*(header_info_cap + strlen(bufptr+2)+4); cbf_failnez((nheader_info = malloc(sizeof(char)*nheader_info_cap))==NULL?CBF_ALLOC:0) if (header_info_size) for(ii=0;ii 0) { /* Write the new file */ out = stdout; if (cbfout && strcmp(cbfout,"-"))out = fopen (cbfout, "w+b"); if (!out) { fprintf (stderr, " convert_minicbf: Couldn't open the output CBF file %s\n", cbfout); exit (1); } cbf_failnez (cbf_write_file (minicbf, out, 1, CBF, MSG_DIGEST | MIME_HEADERS | PAD_4K, 0)) /* Free the cbf */ cbf_failnez (cbf_free_handle (cbf)) /* Free the minicbf */ cbf_failnez (cbf_free_handle (minicbf)) /* Success */ if (cbfintmpused) { if (unlink(cbfintmp) != 0 ) { fprintf(stderr," convert_minicbf: Can't unlink temporary file %s.\n", cbfintmp); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } } return 0; } else if (quick < 0) { const char * value; cbf_failnez(cbf_datablock_name(minicbf,&datablockname)) cbf_failnez(cbf_force_new_datablock(cbf,datablockname)) cbf_failnez(cbf_find_tag(minicbf, "_array_data.data")) cbf_failnez(cbf_require_category(cbf,"array_data")); cbf_failnez(cbf_rewind_row(minicbf)) if (!cbf_find_column(minicbf,"header_convention") && !cbf_get_value(minicbf,&value) && value) { cbf_failnez(cbf_require_column(cbf,"header_convention")) cbf_failnez(cbf_set_value(cbf,value)) } if (!cbf_find_column(minicbf,"header_contents") && !cbf_get_value(minicbf,&value) && value) { cbf_failnez(cbf_require_column(cbf,"header_contents")) cbf_failnez(cbf_set_value(cbf,value)) } else if (header_info) { cbf_failnez(cbf_require_column(cbf,"header_contents")) cbf_failnez(cbf_set_value(cbf,header_info)) } cbf_failnez(cbf_find_column(minicbf,"data")) cbf_failnez(cbf_get_integerarrayparameters_wdims (minicbf, &compression, &binary_id, &elsize, &elsigned, &elunsigned, &elements, &minelement, &maxelement,(const char **) &byteorder, &dim1, &dim2, &dim3, &padding)) fastlen = dim1; slowlen = dim2; cbf_failnez((image = (unsigned char*)malloc(elements*elsize))!=NULL?0:CBF_ALLOC) cbf_failnez(cbf_get_integerarray (minicbf, &binary_id, (void *)image, elsize, elsigned, elements, &elements_read)) if (elements != elements_read) { cbf_failnez(CBF_FORMAT) } cbf_failnez (cbf_require_column(cbf,"data")) if (flat) { cbf_failnez( cbf_set_integerarray_wdims (cbf, CBF_PACKED|CBF_FLAT_IMAGE, binary_id, image, elsize, elsigned, elements, byteorder, dim1, dim2, dim3, padding)) } else { cbf_failnez( cbf_set_integerarray_wdims (cbf, compression, binary_id, image, elsize, elsigned, elements, byteorder, dim1, dim2, dim3, padding)) } /* Write the new file */ out = stdout; if (cbfout && strcmp(cbfout,"-"))out = fopen (cbfout, "w+b"); if (!out) { fprintf (stderr, " convert_minicbf: Couldn't open the output CBF file %s\n", cbfout); exit (1); } cbf_failnez (cbf_write_file (cbf, out, 1, CBF, MSG_DIGEST | MIME_HEADERS | PAD_4K, 0)) /* Free the cbf */ cbf_failnez (cbf_free_handle (cbf)) /* Free the minicbf */ cbf_failnez (cbf_free_handle (minicbf)) /* Success */ if (cbfintmpused) { if (unlink(cbfintmp) != 0 ) { fprintf(stderr," convert_minicbf: Can't unlink temporary file %s.\n", cbfintmp); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } } return 0; } /* Find the image */ cbf_failnez(cbf_find_tag(minicbf, "_array_data.data")) cbf_failnez(cbf_rewind_row(minicbf)) cbf_failnez(cbf_get_integerarrayparameters_wdims (minicbf, &compression, &binary_id, &elsize, &elsigned, &elunsigned, &elements, &minelement, &maxelement,(const char **) &byteorder, &dim1, &dim2, &dim3, &padding)) cbf_failnez((image = (unsigned char*)malloc(elements*elsize))!=NULL?0:CBF_ALLOC) cbf_failnez(cbf_get_integerarray (minicbf, &binary_id, (void *)image, elsize, elsigned, elements, &elements_read)) if (elements != elements_read) { cbf_failnez(CBF_FORMAT) } /* Identify the detector */ if (!cbf_find_tag(minicbf,"_diffrn_detector.type")) { cbf_failnez(cbf_rewind_row(minicbf)) if (cbf_get_value(minicbf,&detector_name) || !detector_name || !*detector_name) { if (detector_opt == NULL) { fprintf (stderr, "\n convert_inage: No detector name provided in minicbf or on the command line!"); outusage(); exit (3); } detector_name = detector_opt; } } else { if (detector_opt == NULL) { fprintf (stderr, "\n convert_inage: No detector name provided in minicbf or on the command line!"); outusage(); exit (3); } detector_name = detector_opt; } for (c = detector_type; *detector_name; detector_name++) if (!isspace (*detector_name)) *c++ = tolower (*detector_name); *c = '\0'; /* Construct the template name */ if (template) { in = fopen (template, "rb"); } else { sprintf (template_name, "template_%s_%dx%d.cbf", detector_type, (int)dim1, (int)dim2); fprintf(stderr," convert_minicbf: template_name: %s\n", template_name); /* Read and modify the template */ in = fopen (template_name, "rb"); } if (!in) { fprintf (stderr," convert_minicbf: unable to open template_name: %s\n", template?template:template_name); exit (4); } cbf_failnez (cbf_read_template (cbf, in)) cbf_failnez(cbf_get_array_id(cbf, 0, &array_id)) cbf_failnez(cbf_require_column(cbf, "details")) if (header_info) { char * src; char * dst; char ccur, cprev; header_info_copy=(char *)malloc(strlen(header_info)+1); src = header_info; dst = header_info_copy; cprev = '\n'; while((ccur=*src++)) { if (ccur == '#' && (cprev == '\n'|| cprev == '\r' ) ) *dst++ = ' '; else *dst++=ccur; cprev = ccur; } *dst++ = '\0'; cbf_failnez(cbf_set_value(cbf, header_info_copy)) cbf_failnez(cbf_set_typeofvalue(cbf,"text")) } /* diffrn.id */ cbf_failnez (cbf_set_diffrn_id (cbf, "DS1")) /* diffrn_detector.details */ if (!cbf_find_tag(minicbf,"_diffrn_detector.details")) { const char *details; cbf_failnez(cbf_rewind_row(minicbf)) if (!cbf_get_value(minicbf,&details) && details && *details) { cbf_failnez(cbf_require_category(cbf,"diffrn_detector")) cbf_failnez(cbf_require_column(cbf,"details")) cbf_failnez(cbf_rewind_row(cbf)) cbf_failnez(cbf_set_value(cbf,details)) } } /* Exposure time */ if (!cbf_find_tag(minicbf,"_diffrn_scan_frame.integration_time")) { const char *time; cbf_failnez(cbf_rewind_row(minicbf)) if (!cbf_get_value(minicbf,&time) && time && *time) { cbf_failnez(cbf_require_category(cbf,"diffrn_scan_frame")) cbf_failnez(cbf_require_column(cbf,"integration_time")) cbf_failnez(cbf_rewind_row(cbf)) cbf_failnez(cbf_set_value(cbf,time)) } } /* Date stamp */ if (!cbf_find_tag(minicbf,"_diffrn_scan_frame.date")) { const char *date; cbf_failnez(cbf_rewind_row(minicbf)) if (!cbf_get_value(minicbf,&date) && date && *date) { cbf_failnez(cbf_require_category(cbf,"diffrn_scan_frame")) cbf_failnez(cbf_require_column(cbf,"date")) cbf_failnez(cbf_rewind_row(cbf)) cbf_failnez(cbf_set_value(cbf,date)) } } /* Oscillations */ if (!cbf_find_tag(minicbf,"_diffrn_scan_frame.oscillations")) { const char *oscillations; cbf_failnez(cbf_rewind_row(minicbf)) if (!cbf_get_value(minicbf,&oscillations) && oscillations && *oscillations) { cbf_failnez(cbf_require_category(cbf,"diffrn_scan_frame")) cbf_failnez(cbf_require_column(cbf,"oscillations")) cbf_failnez(cbf_rewind_row(cbf)) cbf_failnez(cbf_set_value(cbf,oscillations)) } } /* Element size */ if (!cbf_find_tag(minicbf,"_array_element_size.size")) { const char *size, *index; cbf_failnez(cbf_rewind_row(minicbf)) if (!cbf_get_value(minicbf,&size) && size && *size) { cbf_failnez(cbf_require_category(cbf,"array_element_size")) cbf_failnez(cbf_require_column(cbf,"size")) cbf_failnez(cbf_rewind_row(cbf)) cbf_failnez(cbf_set_value(cbf,size)) cbf_failnez(cbf_require_column(cbf,"index")) cbf_failnez(cbf_require_column(minicbf,"index")) if (!cbf_get_value(minicbf,&index) && index && *index) { cbf_failnez(cbf_set_value(cbf,index)) } if (!cbf_next_row(minicbf)) { cbf_failnez(cbf_find_column(minicbf,"size")) if (!cbf_get_value(minicbf,&size) && size && *size) { cbf_failnez(cbf_find_column(cbf,"size")) cbf_failnez(cbf_next_row(cbf)) cbf_failnez(cbf_set_value(cbf,size)) cbf_failnez(cbf_find_column(cbf,"index")) cbf_failnez(cbf_find_column(minicbf,"index")) if (!cbf_get_value(minicbf,&index) && index && *index) { cbf_failnez(cbf_set_value(cbf,index)) } } } } } /* diffrn_radiation.tau */ if (!cbf_find_tag(minicbf,"_diffrn_radiation.tau")) { const char *tau; cbf_failnez(cbf_rewind_row(minicbf)) if (!cbf_get_value(minicbf,&tau) && tau && *tau) { cbf_failnez(cbf_require_category(cbf,"diffrn_radiation")) cbf_failnez(cbf_require_column(cbf,"tau")) cbf_failnez(cbf_rewind_row(cbf)) cbf_failnez(cbf_set_value(cbf,tau)) } } /* diffrn_radiation.flux */ if (!cbf_find_tag(minicbf,"_diffrn_radiation.flux")) { const char *flux; cbf_failnez(cbf_rewind_row(minicbf)) if (!cbf_get_value(minicbf,&flux) && flux && *flux) { cbf_failnez(cbf_require_category(cbf,"diffrn_radiation")) cbf_failnez(cbf_require_column(cbf,"flux")) cbf_failnez(cbf_rewind_row(cbf)) cbf_failnez(cbf_set_value(cbf,flux)) } } /* diffrn_radiation.polarizn_source_ratio */ if (!cbf_find_tag(minicbf,"_diffrn_radiation.polarizn_source_ratio")) { const char *polarizn_source_ratio; cbf_failnez(cbf_rewind_row(minicbf)) if (!cbf_get_value(minicbf,&polarizn_source_ratio) && polarizn_source_ratio && *polarizn_source_ratio) { cbf_failnez(cbf_require_category(cbf,"diffrn_radiation")) cbf_failnez(cbf_require_column(cbf,"polarizn_source_ratio")) cbf_failnez(cbf_rewind_row(cbf)) cbf_failnez(cbf_set_value(cbf,polarizn_source_ratio)) } } /* array_intensities.overload */ if (!cbf_find_tag(minicbf,"_array_intensities.overload")) { const char *overload; cbf_failnez(cbf_rewind_row(minicbf)) if (!cbf_get_value(minicbf,&overload) && overload && *overload) { cbf_failnez(cbf_require_category(cbf,"array_intensities")) cbf_failnez(cbf_require_column(cbf,"overload")) cbf_failnez(cbf_rewind_row(cbf)) cbf_failnez(cbf_set_value(cbf,overload)) } } /* Wavelength */ if (!cbf_find_tag(minicbf,"_diffrn_radiation_wavelength.wavelength")) { double wavelength; cbf_failnez(cbf_get_doublevalue(minicbf,&wavelength)) if (wavelength) cbf_failnez (cbf_set_wavelength (cbf, wavelength)) } /* Distance */ if (!cbf_find_tag(minicbf,"_diffrn_measurement.sample_detector_distance")) { double distance; cbf_failnez(cbf_get_doublevalue(minicbf,&distance)) if (distance == 0.) { distance = atof (distancestr); } cbf_failnez (cbf_set_axis_setting (cbf, 0, "DETECTOR_Z", distance, 0)) cbf_failnez(cbf_require_category(cbf,"diffrn_measurement")) cbf_failnez(cbf_require_column(cbf,"sample_detector_distance")) cbf_failnez(cbf_set_doublevalue(cbf,"%g", distance)) } /* Vertical Offset */ if (!cbf_find_tag(minicbf,"_diffrn_measurement.sample_detector_voffset")) { double voffset; cbf_failnez(cbf_get_doublevalue(minicbf,&voffset)) cbf_failnez (cbf_set_axis_setting (cbf, 0, "DETECTOR_Y", voffset, 0)) cbf_failnez(cbf_require_category(cbf,"diffrn_measurement")) cbf_failnez(cbf_require_column(cbf,"sample_detector_voffset")) cbf_failnez(cbf_set_doublevalue(cbf,"%g", voffset)) } /* Oscillation start and range */ if (!cbf_find_tag(minicbf,"_diffrn_scan_frame_axis.axis_id")) { char * axis; char oscaxis[40]; double osc_start, osc_range; cbf_failnez(cbf_rewind_row(minicbf)) cbf_failnez(cbf_find_row(minicbf,"GONIOMETER_SCAN")) axis = "PHI"; cbf_failnez(cbf_find_column(minicbf,"angle")) cbf_failnez(cbf_get_doublevalue(minicbf,&osc_start)) cbf_failnez(cbf_find_column(minicbf,"angle_increment")) cbf_failnez(cbf_get_doublevalue(minicbf,&osc_range)) sprintf (oscaxis, "GONIOMETER_%s", axis); cbf_failnez (cbf_set_axis_setting (cbf, 0, oscaxis, osc_start, osc_range)) } /* Beam Center */ if (!cbf_find_tag(minicbf,"_diffrn_detector_element.reference_center_fast")){ cbf_detector detector; const char * units; double bcx, bcy; cbf_failnez(cbf_rewind_row(minicbf)) cbf_failnez(cbf_require_column(minicbf,"reference_center_fast")) cbf_failnez(cbf_get_doublevalue(minicbf,&bcx)) cbf_failnez(cbf_require_column(minicbf,"reference_center_slow")) cbf_failnez(cbf_get_doublevalue(minicbf,&bcy)) cbf_failnez(cbf_require_column(minicbf,"reference_center_units")) cbf_failnez(cbf_require_value(minicbf,&units,"mm")) if (!cbf_cistrcmp(units,"pixels")) { cbf_failnez(cbf_construct_detector (cbf, &detector, 0)) cbf_failnez(cbf_set_beam_center(detector, &bcy, &bcx, NULL, NULL)) cbf_failnez(cbf_free_detector(detector)) if (dorefs) { cbf_failnez(cbf_require_reference_detector (cbf, &detector, 0)) cbf_failnez(cbf_set_reference_beam_center(detector, &bcy, &bcx, NULL, NULL)) cbf_failnez(cbf_free_detector(detector)) } } else if (!cbf_cistrcmp(units,"mm")) { cbf_failnez(cbf_construct_detector (cbf, &detector, 0)) cbf_failnez(cbf_set_beam_center(detector, NULL, NULL, &bcy, &bcx)) cbf_failnez(cbf_free_detector(detector)) if (dorefs) { cbf_failnez(cbf_require_reference_detector (cbf, &detector, 0)) cbf_failnez(cbf_set_reference_beam_center(detector, NULL, NULL, &bcy, &bcx)) cbf_failnez(cbf_free_detector(detector)) } } else cbf_failnez(CBF_FORMAT) } /* Image */ fastlen = dim1; slowlen = dim2; if (overall.posxtarg != posx || overall.posytarg != posy ) { int fastorig, faststep, sloworig, slowstep, curpos, i, j; int * tempimg; if (overall.posxtarg==0 || overall.posytarg==0) { fprintf (stderr,"\n convert_minicbf: invalid image transform.\n"); exit(1); } if (dim2 != dim1 ) { fprintf(stderr,"\n convert_img: Unable to transpose image\n"); exit(-1); } /* The fast index is the x axis, counting the columns, and the slow index is the y axis, counting the rows */ fastorig = sloworig = 0; faststep = 1; slowstep = dim1; switch (overall.posxtarg) { case (posx): break; case (negx): fastorig = dim1-1; faststep = -1; break; case (posy): faststep = dim1; fastlen = dim2; slowlen = dim1; break; case (negy): fastorig = (dim1)*(dim2-1); faststep = -dim1; fastlen = dim2; slowlen = dim1; break; } switch (overall.posytarg) { case (posx): slowstep = 1; fastlen = dim2; slowlen = dim1; break; case (negx): sloworig = dim1-1; slowstep= -1; fastlen = dim2; slowlen = dim1; break; case (posy): break; case (negy): sloworig = dim1*(dim2-1); slowstep = -dim1; break; } curpos = fastorig+sloworig; tempimg = malloc(dim1*dim2*elsize); if (!tempimg) { fprintf(stderr,"\n unable to allocate temporary image array\n"); } if (elsize == sizeof(int)) { for (i=0;i 0xFFFF) j = 0xFFFF; tempimg[i] = j; } } if (flat) { cbf_failnez (cbf_set_image (cbf, 0, 0, CBF_PACKED|CBF_FLAT_IMAGE, image, sizeof(short), 0, slowlen, fastlen)) } else { cbf_failnez (cbf_set_image (cbf, 0, 0, compression, image, sizeof(short), 0, slowlen, fastlen)) } } /* fix up the array_structure_list.direction and .precedence */ if (overall.posxtarg != posx || overall.posytarg != posy) { unsigned int arow[2], precedence[2], temp; char * direction[2], * dtemp; arow[0] = arow[1] = 0; precedence[0] = 1; precedence[1] = 2; direction[0] = direction[1] = NULL; cbf_failnez (cbf_find_category (cbf, "array_structure_list")) cbf_failnez (cbf_find_column (cbf, "array_id")) while (!cbf_find_nextrow (cbf, array_id)) { cbf_failnez (cbf_find_column (cbf, "precedence")) cbf_failnez (cbf_get_integervalue (cbf, (int *)&temp)) if (temp == 1 || temp == 2) { cbf_failnez(cbf_row_number(cbf,&(arow[temp-1]))) arow[temp-1]++; cbf_failnez(cbf_find_column(cbf,"direction")) cbf_failnez(cbf_get_value(cbf,(const char**)&(direction[temp-1]))) cbf_failnez(cbf_find_column (cbf, "array_id")) } } switch (overall.posxtarg) { case (posx): break; case (negx): if (!cbf_cistrcmp(direction[0],"increasing")) { direction[0] = "decreasing"; } else { direction[0] = "increasing"; } break; case (posy): precedence[0] = 2; precedence[1] = 1; dtemp = direction[0]; direction[0]=direction[1]; direction[1]=dtemp; break; case (negy): precedence[0] = 2; precedence[1] = 1; dtemp = direction[0]; direction[0]=direction[1]; direction[1]=dtemp; if (!cbf_cistrcmp(direction[0],"increasing")) { direction[0] = "decreasing"; } else { direction[0] = "increasing"; } break; } switch (overall.posytarg) { case (posx): break; case (negx): if (!cbf_cistrcmp(direction[1],"increasing")) { direction[1] = "decreasing"; } else { direction[1] = "increasing"; } break; case (posy): break; case (negy): if (!cbf_cistrcmp(direction[1],"increasing")) { direction[1] = "decreasing"; } else { direction[1] = "increasing"; } break; } if (arow[0]) { cbf_failnez (cbf_select_row (cbf, arow[0]-1)) cbf_failnez (cbf_find_column (cbf, "precedence")) cbf_failnez (cbf_set_integervalue (cbf, precedence[0])) cbf_failnez (cbf_find_column (cbf, "direction")) cbf_failnez (cbf_set_value (cbf, direction[0])) } if (arow[1]) { cbf_failnez (cbf_select_row (cbf, arow[1]-1)) cbf_failnez (cbf_find_column (cbf, "precedence")) cbf_failnez (cbf_set_integervalue (cbf, precedence[1])) cbf_failnez (cbf_find_column (cbf, "direction")) cbf_failnez (cbf_set_value (cbf, direction[1])) } } /*****************************************************************************/ /* Write the new file */ out = stdout; if (cbfout && strcmp(cbfout,"-"))out = fopen (cbfout, "w+b"); if (!out) { fprintf (stderr, " convert_minicbf: Couldn't open the output CBF file %s\n", cbfout); exit (1); } cbf_failnez (cbf_write_file (cbf, out, 1, CBF, MSG_DIGEST | MIME_HEADERS | PAD_4K, 0)) /* Free the cbf */ cbf_failnez (cbf_free_handle (cbf)) /* Free the minicbf */ cbf_failnez (cbf_free_handle (minicbf)) /* Free the getopt_handle */ cbf_failnez (cbf_free_getopt_handle(opts)) /* Success */ if (cbfintmpused) { if (unlink(cbfintmp) != 0 ) { fprintf(stderr," convert_minicbf: Can't unlink temporary file %s.\n", cbfintmp); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } } return 0; } int local_exit (int status) { exit(status); return 1; /* avoid warnings */ } ./CBFlib-0.9.2.2/examples/arvai_test.c0000644000076500007650000000327711603702122015730 0ustar yayayaya/* * arvai_test.c * * * Created by Herbert J. Bernstein on 3/2/10. * Copyright 2010 __MyCompanyName__. All rights reserved. * */ /******************* Begin testcbf.c ***********************/ #include #include #include int main (int argc, char ** argv) { char buf[256]; char *data_buffer; char *temp_buffer; int data_buffer_len=0; int read_count; char filename[] = "/tmp/mb_LP_1_001_orig.cbf.bz2"; FILE *fp; int ierr; cbf_handle cbf; cbf_failnez (cbf_make_handle (&cbf)) sprintf(buf,"bunzip2 -c %s 2>/dev/null\n",filename); if((fp = popen(buf,"r")) == NULL) return -1; data_buffer = (char *)malloc(sizeof(char)*1024*1024); if (data_buffer == NULL) { fprintf(stderr,"not enough memory.\n"); fflush(stderr); fclose(fp); return -1; } while ((read_count = fread (data_buffer + data_buffer_len, 1, 1024*1024, fp)) != 0) { data_buffer_len += read_count; if (read_count < 1024*1024) break; temp_buffer = (char*)malloc(sizeof(char)*data_buffer_len+1024*1024); if (temp_buffer == NULL) { fprintf(stderr,"not enough memory.\n"); fflush(stderr); fclose(fp); return -1; } memmove(temp_buffer,data_buffer,data_buffer_len); free(data_buffer); data_buffer=temp_buffer; } fprintf(stderr,"data_buffer_len=%d\n",data_buffer_len); fflush(stderr); ierr = cbf_read_buffered_file (cbf, NULL, MSG_DIGESTNOW, data_buffer, data_buffer_len); fprintf(stderr,"ierr=%d \n",ierr); fflush(stderr); exit(0); } int big_endian () { int x=1; if ( *(char *)&x == 1) return 0; else return 1; } ./CBFlib-0.9.2.2/examples/adscimg2cbf.c0000644000076500007650000002726711603702122015740 0ustar yayayaya#include #ifdef NO_POPEN_PROTOTYPE /* * This is supposed to be found in stdio.h. */ FILE *popen(char *popen_command, const char *type); int pclose(FILE *stream); #endif #include #include #include /****************************************************************/ static void gethd ( char* field, char* value, char* header ) { char *hp, *lhp, *fp, *vp; int l, j; char *newfield; /* * Find the last occurance of "field" in "header" */ l = strlen (field); newfield = (char*) malloc ( l + 3 ); *newfield = 10; strncpy (newfield+1, field, l); *(newfield+l+1) = '='; *(newfield+l+2) = (char) 0; l += 2; lhp = 0; for (hp=header; *hp != '}'; hp++) { for (fp=newfield, j=0; j 1 && argv[1][0] == '-' && argv[1][1] == '-') { for(j = 0; flags[j] != NULL; j++) if(NULL != strstr(argv[1], flags[j])) break; if(NULL == flags[j]) { fprintf(stderr,"adscimg2cbf: %s is an unknown flag\n\n", argv[1]); usage(); exit(0); } switch(j) { case 0: pack_flags = CBF_BYTE_OFFSET; break; case 1: pack_flags = CBF_PACKED_V2; break; case 2: pack_flags = CBF_PACKED; break; case 3: pack_flags = CBF_NONE; break; case 4: beam_center_convention = BEAM_CENTER_FROM_HEADER; break; case 5: beam_center_convention = BEAM_CENTER_MOSFLM; break; case 6: beam_center_convention = BEAM_CENTER_ULHC; break; case 7: beam_center_convention = BEAM_CENTER_LLHC; break; case 8: pad_flag = PAD_1K; break; case 9: pad_flag = PAD_2K; break; case 10: pad_flag = PAD_4K; break; case 11: pad_flag = 0; break; } if(j < 3) { if(NULL != strstr(argv[1], ",flat")) pack_flags |= CBF_FLAT_IMAGE; else if(NULL != strstr(argv[1], ",uncorrelated")) pack_flags |= CBF_UNCORRELATED_SECTIONS; } argc--; argv++; } while(argc > 1) { file_type = 0; strcpy(in_filename, argv[1]); i = strlen(in_filename); for(j = 0; endings[j] != NULL; j++) { k = strlen(endings[j]); if(endswith(in_filename, endings[j])) { file_type = j; break; } } if(NULL == endings[j]) { fprintf(stderr,"adscimg2cbf: Input file name %s does not end in .img, .img.gz, or .img.bz2, or .img.Z\n", in_filename); exit(0); } strcpy(out_filename, in_filename); out_filename[i - k] = '\0'; strcat(out_filename, ".cbf"); if(0 == file_type) { if(NULL == (fp = fopen(in_filename, "rb"))) { fprintf(stderr, "adscimg2cbf: Cannot open %s as input .img file\n", in_filename); exit(0); } } else { if(2 == file_type) sprintf(popen_command, "bzcat %s", in_filename); else sprintf(popen_command, "zcat %s", in_filename); if(NULL == (fp = popen(popen_command, "rb"))) { fprintf(stderr, "adscimg2cbf: Cannot exec %s command to uncompress input file\n", popen_command); exit(0); } } /* * Get the first header block. Can't use seeks on input file. */ if(NULL == (hptr = malloc(512 * sizeof (char)))) { fprintf(stderr,"adscimg2cbf: cannot allocate memory for first 512 bytes of header of input file %s\n", in_filename); exit(0); } if(512 != (actread=fread(hptr, sizeof (char), 512, fp))) { fprintf(stderr, "adscimg2cbf: Cannot read first header block of file %s, actual read %d.\n", in_filename,actread); if(0 == file_type) fclose(fp); else { status_pclose = pclose(fp); if(0 != status_pclose) { fprintf(stderr, "Status returned from uncompress command via popen NON-ZERO: %d\n", status_pclose); perror("popen command (maybe this will be useful)"); fprintf(stderr, "Program exiting. This may be evidence of a corrupt compressed file!\n"); fprintf(stderr, "Filename being uncompressed: %s with command: %s\n", in_filename, popen_command); exit(0); } } exit(0); } for(i = 0; i < 5; i++) header_bytes[0 + i] = hptr[15 + i]; header_bytes[5] = '\0'; header_size_char = atoi(header_bytes); if(NULL == (hptr = realloc(hptr, header_size_char))) { fprintf(stderr,"adscimg2cbf: cannot reallocate memory for %d bytes of header of input file %s\n", header_size_char, in_filename); exit(0); } if(header_size_char > 512) { if((header_size_char - 512) != (actread=fread(hptr + 512, sizeof (char), (header_size_char - 512), fp))) { fprintf(stderr, "adscimg2cbf: Cannot read next %d bytes of header of file %s," " actual read %d.\n", header_size_char - 512, in_filename, actread); if(0 == file_type) fclose(fp); else { status_pclose = pclose(fp); if(0 != status_pclose) { fprintf(stderr, "Status returned from uncompress command via popen NON-ZERO: %d\n", status_pclose); perror("popen command (maybe this will be useful)"); fprintf(stderr, "Program exiting. This may be evidence of a corrupt compressed file!\n"); fprintf(stderr, "Filename being uncompressed: %s with command: %s\n", in_filename, popen_command); exit(0); } } exit(0); } } field[0] = '\0'; gethd("SIZE1", field, hptr); if('\0' == field[0]) { fprintf(stderr,"adscimg2cbf: keyword SIZE1 not found in header. Cannot convert file %s\n", in_filename); exit(0); } size1 = atoi(field); field[0] = '\0'; gethd("SIZE2", field, hptr); if('\0' == field[0]) { fprintf(stderr,"adscimg2cbf: keyword SIZE2 not found in header. Cannot convert file %s\n", in_filename); exit(0); } size2 = atoi(field); file_size = header_size_char + size1 * size2 * sizeof(unsigned short); if(NULL == (hptr = realloc(hptr, file_size))) { fprintf(stderr,"adscimg2cbf: cannot reallocate memory (size %d) for input file %s\n", file_size, in_filename); exit(0); } if((file_size - header_size_char) != (actread=fread(hptr + header_size_char, sizeof (char), (file_size - header_size_char), fp))) { fprintf(stderr, "adscimg2cbf: Cannot read data (size %d bytes) from input file %s." " actual read %d\n", file_size - header_size_char, in_filename, actread); if(0 == file_type) fclose(fp); else { status_pclose = pclose(fp); if(0 != status_pclose) { fprintf(stderr, "Status returned from uncompress command via popen NON-ZERO: %d\n", status_pclose); perror("popen command (maybe this will be useful)"); fprintf(stderr, "Program exiting. This may be evidence of a corrupt compressed file!\n"); fprintf(stderr, "Filename being uncompressed: %s with command: %s\n", in_filename, popen_command); exit(0); } } exit(0); } if(0 == file_type) fclose(fp); else { status_pclose = pclose(fp); if(0 != status_pclose) { fprintf(stderr, "Status returned from uncompress command via popen NON-ZERO: %d\n", status_pclose); perror("popen command (maybe this will be useful)"); fprintf(stderr, "Program exiting. This may be evidence of a corrupt compressed file!\n"); fprintf(stderr, "Filename being uncompressed: %s with command: %s\n", in_filename, popen_command); exit(0); } } uptr = ((unsigned short *) (hptr + header_size_char)); cbf_status = adscimg2cbf_sub(hptr, uptr, out_filename, pack_flags, beam_center_convention, pad_flag); free(hptr); argv++; argc--; } exit(0); } ./CBFlib-0.9.2.2/examples/testreals.c0000644000076500007650000005357011603702122015576 0ustar yayayaya/********************************************************************** * testreals -- test read and write for reals * * * * Version 0.7.6.3 21 January 2007 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * WHILE YOU MAY ALTERNATIVE DISTRIBUTE THE API UNDER THE LGPL * * YOU MAY ***NOT*** DISTRBUTE THIS PROGRAM UNDER THE LGPL * * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term 'this software', as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ /********************************************************************** * SYNOPSIS * * * * testreals * * * **********************************************************************/ #include "cbf.h" #include #include #include #include #include #include #include int local_exit (int status); int outerror(int err) { if ((err&CBF_FORMAT)==CBF_FORMAT) fprintf(stderr, " testreals: The file format is invalid.\n"); if ((err&CBF_ALLOC)==CBF_ALLOC) fprintf(stderr, " testreals Memory allocation failed.\n"); if ((err&CBF_ARGUMENT)==CBF_ARGUMENT) fprintf(stderr, " testreals: Invalid function argument.\n"); if ((err&CBF_ASCII)==CBF_ASCII) fprintf(stderr, " testreals: The value is ASCII (not binary).\n"); if ((err&CBF_BINARY)==CBF_BINARY) fprintf(stderr, " testreals: The value is binary (not ASCII).\n"); if ((err&CBF_BITCOUNT)==CBF_BITCOUNT) fprintf(stderr, " testreals: The expected number of bits does" " not match the actual number written.\n"); if ((err&CBF_ENDOFDATA)==CBF_ENDOFDATA) fprintf(stderr, " testreals: The end of the data was reached" " before the end of the array.\n"); if ((err&CBF_FILECLOSE)==CBF_FILECLOSE) fprintf(stderr, " testreals: File close error.\n"); if ((err&CBF_FILEOPEN)==CBF_FILEOPEN) fprintf(stderr, " testreals: File open error.\n"); if ((err&CBF_FILEREAD)==CBF_FILEREAD) fprintf(stderr, " testreals: File read error.\n"); if ((err&CBF_FILESEEK)==CBF_FILESEEK) fprintf(stderr, " testreals: File seek error.\n"); if ((err&CBF_FILETELL)==CBF_FILETELL) fprintf(stderr, " testreals: File tell error.\n"); if ((err&CBF_FILEWRITE)==CBF_FILEWRITE) fprintf(stderr, " testreals: File write error.\n"); if ((err&CBF_IDENTICAL)==CBF_IDENTICAL) fprintf(stderr, " testreals: A data block with the new name already exists.\n"); if ((err&CBF_NOTFOUND)==CBF_NOTFOUND) fprintf(stderr, " testreals: The data block, category, column or" " row does not exist.\n"); if ((err&CBF_OVERFLOW)==CBF_OVERFLOW) fprintf(stderr, " testreals: The number read cannot fit into the" "destination argument.\n The destination has been set to the nearest value.\n"); if ((err& CBF_UNDEFINED)==CBF_UNDEFINED) fprintf(stderr, " testreals: The requested number is not defined (e.g. 0/0).\n"); if ((err&CBF_NOTIMPLEMENTED)==CBF_NOTIMPLEMENTED) fprintf(stderr, " testreals: The requested functionality is not yet implemented.\n"); return 0; } #undef cbf_failnez #define cbf_failnez(x) \ {int xerr; \ xerr = (x); \ if (xerr) { \ fprintf(stderr," testreals: CBFlib fatal error %d\n",xerr); \ outerror(xerr); \ outusage(); \ local_exit (-1); \ } \ } int outusage ( void ) { fprintf(stderr," \n Usage:\n"); fprintf(stderr," testreals \\\n"); fprintf(stderr," Requires testrealin.cbf\n "); fprintf(stderr," Creates testrealout.cbf\n "); return -1; } int main (int argc, char *argv []) { cbf_handle incbf, cbf; FILE *in, *out; double *image; float *flimage; int i; /* Read the input test file */ if (!(in = fopen ("testrealin.cbf", "rb"))) { fprintf (stderr,"testreals: Couldn't open the input imgCIF file %s\n", "testrealin.cbf"); exit (1); } cbf_failnez (cbf_make_handle (&incbf)) cbf_failnez (cbf_read_file (incbf, in, MSG_DIGEST)) cbf_failnez (cbf_make_handle (&cbf)) cbf_failnez(cbf_find_datablock(incbf,"testreals")) cbf_failnez(cbf_find_category(incbf,"array_data")) cbf_failnez(cbf_find_column(incbf,"data")) cbf_failnez(cbf_rewind_row(incbf)) cbf_failnez ( (image = (double *)malloc(sizeof(double)*1000000))==NULL?CBF_ALLOC:0); cbf_failnez (cbf_get_realarray (incbf, NULL, image, sizeof (double), 1000000, NULL)) for (i = 0; i < 1000000; i++) { if (image[i] != (double)(i+1)) { fprintf(stderr,"testreals: Mismatch for index %d, file %g != %g\n", i, image[i], (double)(i+1)); exit(-1); } } free(image); cbf_failnez(cbf_next_row(incbf)) cbf_failnez ( (flimage = (float *)malloc(sizeof(float)*1000000))==NULL?CBF_ALLOC:0); cbf_failnez (cbf_get_realarray (incbf, NULL, flimage, sizeof (float), 1000000, NULL)) for (i = 0; i < 1000000; i++) { if (flimage[i] != (float)(i+1)) { fprintf(stderr,"testreals: Mismatch for index %d, value in file %f != %f\n", i, flimage[i], (float)(i+1)); exit(-1); } } free(flimage); cbf_failnez(cbf_new_datablock(cbf,"testreals")) cbf_failnez(cbf_new_category(cbf,"array_data")) cbf_failnez(cbf_new_column(cbf,"data")) cbf_failnez(cbf_new_row(cbf)) /* Create a real array 1000 x 1000 doubles running in sequence */ cbf_failnez ( (image = (double *)malloc(sizeof(double)*1000000))==NULL?CBF_ALLOC:0); for (i = 0; i < 1000000; i++) { image[i] = (double)(i+1); } cbf_failnez (cbf_set_realarray (cbf, CBF_NONE, 1, image, sizeof (double), 1000000)) free(image); cbf_failnez(cbf_new_row(cbf)) /* Create a real array 1000 x 1000 floats running in sequence */ cbf_failnez( (flimage = (float *)malloc(sizeof(float)*1000000))==NULL?CBF_ALLOC:0); for (i = 0; i < 1000000; i++) { flimage[i] = (float)(i+1); } cbf_failnez (cbf_set_realarray (cbf, CBF_NONE, 2, flimage, sizeof (float), 1000000)) free(flimage); /* Write the new file */ out = fopen ("testrealout.cbf", "w+b"); if (!out) { fprintf (stderr, " testreal: Couldn't open the CBF file %s\n", "testrealout.cbf"); exit (1); } cbf_failnez (cbf_write_file (cbf, out, 1, CBF, MSG_DIGEST | MIME_HEADERS, 0)) /* Free the cbf */ cbf_failnez (cbf_free_handle (cbf)) /* Success */ return 0; } int local_exit (int status) { exit(status); return 1; /* avoid warnings */ } ./CBFlib-0.9.2.2/examples/testflatpacked.c0000644000076500007650000007573511603702122016575 0ustar yayayaya/********************************************************************** * testflat -- test read and write for flat field * * * * Version 0.7.6.3 21 January 2007 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * WHILE YOU MAY ALTERNATIVE DISTRIBUTE THE API UNDER THE LGPL * * YOU MAY ***NOT*** DISTRBUTE THIS PROGRAM UNDER THE LGPL * * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term 'this software', as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ /********************************************************************** * SYNOPSIS * * * * testflatpacked * * * **********************************************************************/ #include "cbf.h" #include #include #include #include #include #include #include int local_exit (int status); int outerror(int err) { if ((err&CBF_FORMAT)==CBF_FORMAT) fprintf(stderr, " testflat: The file format is invalid.\n"); if ((err&CBF_ALLOC)==CBF_ALLOC) fprintf(stderr, " testflat Memory allocation failed.\n"); if ((err&CBF_ARGUMENT)==CBF_ARGUMENT) fprintf(stderr, " testflat: Invalid function argument.\n"); if ((err&CBF_ASCII)==CBF_ASCII) fprintf(stderr, " testflat: The value is ASCII (not binary).\n"); if ((err&CBF_BINARY)==CBF_BINARY) fprintf(stderr, " testflat: The value is binary (not ASCII).\n"); if ((err&CBF_BITCOUNT)==CBF_BITCOUNT) fprintf(stderr, " testflat: The expected number of bits does" " not match the actual number written.\n"); if ((err&CBF_ENDOFDATA)==CBF_ENDOFDATA) fprintf(stderr, " testflat: The end of the data was reached" " before the end of the array.\n"); if ((err&CBF_FILECLOSE)==CBF_FILECLOSE) fprintf(stderr, " testflat: File close error.\n"); if ((err&CBF_FILEOPEN)==CBF_FILEOPEN) fprintf(stderr, " testflat: File open error.\n"); if ((err&CBF_FILEREAD)==CBF_FILEREAD) fprintf(stderr, " testflat: File read error.\n"); if ((err&CBF_FILESEEK)==CBF_FILESEEK) fprintf(stderr, " testflat: File seek error.\n"); if ((err&CBF_FILETELL)==CBF_FILETELL) fprintf(stderr, " testflat: File tell error.\n"); if ((err&CBF_FILEWRITE)==CBF_FILEWRITE) fprintf(stderr, " testflat: File write error.\n"); if ((err&CBF_IDENTICAL)==CBF_IDENTICAL) fprintf(stderr, " testflat: A data block with the new name already exists.\n"); if ((err&CBF_NOTFOUND)==CBF_NOTFOUND) fprintf(stderr, " testflat: The data block, category, column or" " row does not exist.\n"); if ((err&CBF_OVERFLOW)==CBF_OVERFLOW) fprintf(stderr, " testflat: The number read cannot fit into the " "destination argument.\n The destination has been set to the nearest value.\n"); if ((err& CBF_UNDEFINED)==CBF_UNDEFINED) fprintf(stderr, " testflat: The requested number is not defined (e.g. 0/0).\n"); if ((err&CBF_NOTIMPLEMENTED)==CBF_NOTIMPLEMENTED) fprintf(stderr, " testflat: The requested functionality is not yet implemented.\n"); return 0; } #undef cbf_failnez #define cbf_failnez(x) \ {int xerr; \ xerr = (x); \ if (xerr) { \ fprintf(stderr," testflat: CBFlib fatal error %d\n",xerr); \ outerror(xerr); \ outusage(); \ local_exit (-1); \ } \ } int outusage ( void ) { fprintf(stderr," \n Usage:\n"); fprintf(stderr," testflatpacked \\\n"); fprintf(stderr," Requires testflatpackedin.cbf\n "); fprintf(stderr," Creates testflatpackedout.cbf\n "); return -1; } int main (int argc, char *argv []) { cbf_handle incbf, cbf; FILE *in, *out; int *image; size_t numread, nelem, elsize; unsigned int compression; int id, elsigned, elunsigned, maxel, minel; short *shimage; int i, j, k; /* Read the input test file */ if (!(in = fopen ("testflatpackedin.cbf", "rb"))) { fprintf (stderr,"testflat: Couldn't open the input imgCIF file %s\n", "testflatpackedin.cbf"); } else { const char * byteorder; size_t dim1, dim2, dim3, padding; cbf_failnez (cbf_make_handle (&incbf)) cbf_failnez (cbf_read_file (incbf, in, MSG_DIGEST)) cbf_failnez(cbf_find_datablock(incbf,"testflat")) cbf_failnez(cbf_find_category(incbf,"array_data")) cbf_failnez(cbf_find_column(incbf,"data")) cbf_failnez(cbf_rewind_row(incbf)) cbf_failnez ( (image = (int *)malloc(sizeof(int)*1000000))==NULL?CBF_ALLOC:0); cbf_failnez (cbf_get_integerarrayparameters_wdims (incbf, &compression, &id, &elsize, &elsigned, &elunsigned, &nelem, &maxel, &minel, &byteorder, &dim1, &dim2, &dim3, &padding)) fprintf (stderr,"testflat: element size %ld, element signed %d, element unsigned %d\n", (long)elsize, elsigned, elunsigned ); fprintf (stderr,"testflat: byte order %s, dimensions %ld, %ld, padding %ld\n", byteorder, (long)dim1, (long)dim2, (long)padding); if (compression != CBF_PACKED) fprintf(stderr, "testflat: Compression %x instead of CBF_PACKED\n", compression); if (elsize != sizeof(int)) fprintf(stderr,"testflat: element size %ld instead of %d\n", (long)elsize, (int)sizeof(int)); cbf_failnez (cbf_get_integerarray (incbf, NULL, image, sizeof (int), 0, nelem, &numread)) if (numread != 1000000) fprintf(stderr,"testflat: Read %ld instead of 1000000 ints\n", (long)numread); for (i = 0; i < 1000000; i++) { if (image[i] != 1000) { fprintf(stderr,"testflat: Mismatch for index %d, int value in file %d != %d\n", i, image[i], 1000); /* exit(-1); */ } } free(image); cbf_failnez(cbf_next_row(incbf)) cbf_failnez ( (shimage = (short *)malloc(sizeof(short)*1000000))==NULL?CBF_ALLOC:0); cbf_failnez (cbf_get_integerarrayparameters_wdims (incbf, &compression, &id, &elsize, &elsigned, &elunsigned, &nelem, &maxel, &minel, &byteorder, &dim1, &dim2, &dim3, &padding)) fprintf (stderr,"testflat: element size %ld, element signed %d, element unsigned %d\n", (long)elsize, elsigned, elunsigned ); fprintf (stderr,"testflat: byte order %s, dimensions %ld, %ld, padding %ld\n", byteorder, (long)dim1, (long)dim2, (long)padding); if (compression != CBF_PACKED) fprintf(stderr, "testflat: Compression %x instead of CBF_PACKED\n", compression); if (elsize != sizeof(short)) fprintf(stderr,"testflat: element size %ld instead of %d\n", (long)elsize, (int)sizeof(short)); cbf_failnez (cbf_get_integerarray (incbf, NULL, shimage, sizeof (short), 0, 1000000,&numread)) if (numread != 1000000) fprintf(stderr,"testflat: Read %ld instead of 1000000 shorts\n", (long)numread); for (i = 0; i < 1000000; i++) { if (shimage[i] != 1000) { fprintf(stderr,"testflat: Mismatch for index %d, short value in file %d != %d\n", i, shimage[i], 1000); /* exit(-1); */ } } free(shimage); cbf_failnez(cbf_next_row(incbf)) cbf_failnez ( (image = (int *)malloc(sizeof(int)*1000000))==NULL?CBF_ALLOC:0); cbf_failnez (cbf_get_integerarrayparameters_wdims (incbf, &compression, &id, &elsize, &elsigned, &elunsigned, &nelem, &maxel, &minel, &byteorder, &dim1, &dim2, &dim3, &padding)) fprintf (stderr,"testflat: element size %ld, element signed %d, element unsigned %d\n", (long)elsize, elsigned, elunsigned ); fprintf (stderr,"testflat: byte order %s, dimensions %ld, %ld, padding %ld\n", byteorder, (long)dim1, (long)dim2, (long)padding); if (compression != CBF_PACKED) fprintf(stderr, "testflat: Compression %x instead of CBF_PACKED\n", compression); if (elsize != sizeof(int)) fprintf(stderr,"testflat: element size %ld instead of %d\n", (long)elsize, (int)sizeof(int)); cbf_failnez (cbf_get_integerarray (incbf, NULL, image, sizeof (int), 1, nelem, &numread)) if (numread != 1000000) fprintf(stderr,"testflat: Read %ld instead of 1000000 ints\n", (long)numread); for (i = 0; i < 1000; i++) { for (j = 0; j < 1000; j++) { int dtarg; dtarg = 1000; if (i == j || i == 999-j) dtarg = -3; if (image[i+j*1000] != dtarg) fprintf(stderr,"testflat: Mismatch for index %d, int value in file %d != %d\n", i+j*1000, image[i+j*1000], dtarg); } } free(image); cbf_failnez(cbf_next_row(incbf)) cbf_failnez ( (shimage = (short *)malloc(sizeof(short)*1000000))==NULL?CBF_ALLOC:0); cbf_failnez (cbf_get_integerarrayparameters_wdims (incbf, &compression, &id, &elsize, &elsigned, &elunsigned, &nelem, &maxel, &minel, &byteorder, &dim1, &dim2, &dim3, &padding)) fprintf (stderr,"testflat: element size %ld, element signed %d, element unsigned %d\n", (long)elsize, elsigned, elunsigned ); fprintf (stderr,"testflat: byte order %s, dimensions %ld, %ld, padding %ld\n", byteorder, (long)dim1, (long)dim2, (long)padding); if (compression != CBF_PACKED) fprintf(stderr, "testflat: Compression %x instead of CBF_PACKED\n", compression); if (elsize != sizeof(short)) fprintf(stderr,"testflat: element size %ld instead of %d\n", (long)elsize, (int)sizeof(short)); cbf_failnez (cbf_get_integerarray (incbf, NULL, shimage, sizeof (short), 1, 1000000,&numread)) if (numread != 1000000) fprintf(stderr,"testflat: Read %ld instead of 1000000 shorts\n", (long)numread); for (i = 0; i < 1000; i++) { for (j = 0; j < 1000; j++) { short dtarg; dtarg = 1000; if (i == j || i == 999-j) dtarg = -3; if (shimage[i+j*1000] != dtarg) fprintf(stderr,"testflat: Mismatch for index %d, short value in file %d != %d\n", i+j*1000, shimage[i+j*1000], dtarg); } } free(shimage); cbf_failnez(cbf_next_row(incbf)) cbf_failnez ( (image = (int *)malloc(sizeof(int)*50*60*70))==NULL?CBF_ALLOC:0); cbf_failnez (cbf_get_integerarrayparameters_wdims (incbf, &compression, &id, &elsize, &elsigned, &elunsigned, &nelem, &maxel, &minel, &byteorder, &dim1, &dim2, &dim3, &padding)) fprintf (stderr,"testflat: element size %ld, element signed %d, element unsigned %d\n", (long)elsize, elsigned, elunsigned ); fprintf (stderr,"testflat: byte order %s, dimensions %ld, %ld, %ld, padding %ld\n", byteorder, (long)dim1, (long)dim2, (long)dim3, (long)padding); if (compression != CBF_PACKED) fprintf(stderr, "testflat: Compression %x instead of CBF_PACKED\n", compression); if (elsize != sizeof(int)) fprintf(stderr,"testflat: element size %ld instead of %d\n", (long)elsize, (int)sizeof(int)); cbf_failnez (cbf_get_integerarray (incbf, NULL, image, sizeof (int), 1, nelem, &numread)) if (numread != 50*60*70) fprintf(stderr,"testflat: Read %ld instead of 50*60*70 ints\n", (long)numread); for (i = 0; i < 50; i++) { for (j = 0; j < 60; j++) { for (k = 0; k < 70; k++) { int dtarg; dtarg = 1000; if (i == j || j == k ) dtarg = -3; if ((i + j*50 + k*50*60)%1000 == 0) dtarg = i+j+k; if (image[i + j*50 + k*50*60] != dtarg) fprintf(stderr,"testflat: Mismatch for index %d, int value in file %d != %d\n", i + j*50 + k*50*60, image[i + j*50 + k*50*60], dtarg ); } } } free(image); } cbf_failnez (cbf_make_handle (&cbf)) cbf_failnez(cbf_new_datablock(cbf,"testflat")) cbf_failnez(cbf_new_category(cbf,"array_data")) cbf_failnez(cbf_new_column(cbf,"data")) cbf_failnez(cbf_new_row(cbf)) /* Create an array 1000 x 1000 ints in a flat field of 1000 */ cbf_failnez ( (image = (int *)malloc(sizeof(int)*1000000))==NULL?CBF_ALLOC:0); for (i = 0; i < 1000000; i++) { image[i] = 1000; } cbf_failnez (cbf_set_integerarray_wdims (cbf, CBF_PACKED, 1, image, sizeof (int), 0, 1000000,"little_endian",1000,1000,0,4095)) free(image); cbf_failnez(cbf_new_row(cbf)) /* Create an array 1000 x 1000 shorts as a flat field */ cbf_failnez( (shimage = (short *)malloc(sizeof(short)*1000000))==NULL?CBF_ALLOC:0); for (i = 0; i < 1000000; i++) { shimage[i] = 1000; } cbf_failnez (cbf_set_integerarray_wdims (cbf, CBF_PACKED, 2, shimage, sizeof (short), 0, 1000000, "little_endian",1000,1000,0,4095)) free(shimage); cbf_failnez(cbf_new_row(cbf)) /* Create an array 1000 x 1000 signed ints in a flat field of 1000, except for -3 along the main diagonal and its transpose */ cbf_failnez ( (image = (int *)malloc(sizeof(int)*1000000))==NULL?CBF_ALLOC:0); for (i = 0; i < 1000; i++) { for (j = 0; j < 1000; j++) { image[i+j*1000] = 1000; if (i == j || i == 999-j) image[i+j*1000] = -3; } } cbf_failnez (cbf_set_integerarray_wdims (cbf, CBF_PACKED, 3, image, sizeof (int), 1, 1000000,"little_endian",1000,1000,0,4095)) free(image); cbf_failnez(cbf_new_row(cbf)) /* Create an array 1000 x 1000 shorts in a flat field of 1000, except for -3 along the main diagonal and its transpose */ cbf_failnez( (shimage = (short *)malloc(sizeof(short)*1000000))==NULL?CBF_ALLOC:0); for (i = 0; i < 1000; i++) { for (j = 0; j < 1000; j++) { shimage[i+j*1000] = 1000; if (i == j || i == 999-j) shimage[i+j*1000] = -3; } } cbf_failnez (cbf_set_integerarray_wdims (cbf, CBF_PACKED, 4, shimage, sizeof (short), 1, 1000000, "little_endian",1000,1000,0,4095)) free(shimage); cbf_failnez(cbf_new_row(cbf)) /* Create an array 50 x 60 x 70 signed ints in a flat field of 1000, except for -3 along the main diagonal and the values i+j+k every 1000th pixel */ cbf_failnez ( (image = (int *)malloc(sizeof(int)*50*60*70))==NULL?CBF_ALLOC:0); for (i = 0; i < 50; i++) { for (j = 0; j < 60; j++) { for (k = 0; k < 70; k++) { image[i + j*50 + k*50*60] = 1000; if (i == j || j == k ) image[i + j*50 + k*50*60] = -3; if ((i + j*50 + k*50*60)%1000 == 0) image[i + j*50 + k*50*60] = i+j+k; } } } cbf_failnez (cbf_set_integerarray_wdims (cbf, CBF_PACKED, 3, image, sizeof (int), 1, 50*60*70,"little_endian",50,60,70,4095)) free(image); /* Write the new file */ out = fopen ("testflatpackedout.cbf", "w+b"); if (!out) { fprintf (stderr, " testflat: Couldn't open the CBF file %s\n", "testflatout.cbf"); exit (1); } cbf_failnez (cbf_write_file (cbf, out, 1, CBF, MSG_DIGEST | MIME_HEADERS, 0)) /* Free the cbf */ cbf_failnez (cbf_free_handle (cbf)) /* Success */ return 0; } int local_exit (int status) { exit(status); return 1; /* avoid warnings */ } ./CBFlib-0.9.2.2/examples/sauter_test.C0000644000076500007650000000216411603702122016063 0ustar yayayaya#include "cbf.h" #include "cbf_simple.h" #include #include #include #include #ifdef CBFLIB_MEM_DEBUG extern size_t memory_allocated; #endif struct Error : public std::exception { std::string s; Error(std::string s):s(s){} virtual const char* what() const throw() {return s.c_str();} virtual ~Error() throw() {} }; int main() { std::string file("adscconverted_flat.cbf"); for (int cc=0; cc<20000; ++cc) { #ifdef CBFLIB_MEM_DEBUG fprintf(stderr,"Iteration %8d\n",cc); fprintf(stderr,"Memory allocated %ld\n",(long)memory_allocated); #endif cbf_handle cbf_h; FILE* private_file = std::fopen(file.c_str(),"rb"); if (!private_file) throw Error("cbf file BAD_OPEN"); cbf_failnez ( cbf_make_handle (&cbf_h) ) cbf_failnez ( cbf_read_file (cbf_h, private_file, MSG_DIGEST)) //file handle must be left open & is closed by the cbf library. cbf_detector detector1; cbf_failnez ( cbf_construct_detector(cbf_h,&detector1,0) ) cbf_failnez ( cbf_free_detector(detector1) ) cbf_failnez ( cbf_free_handle (cbf_h)) //fclose(private_file); } } ./CBFlib-0.9.2.2/examples/seqmatchsub.c0000644000076500007650000000025211603702122016074 0ustar yayayaya/* * seqmatchsub.c * * * Created by Herbert J. Bernstein on 2/24/10. * Copyright 2010 __MyCompanyName__. All rights reserved. * */ #include "seqmatchsub.h" ./CBFlib-0.9.2.2/examples/seqmatchsub.h0000644000076500007650000000053011603702122016100 0ustar yayayaya/* * seqmatchsub.h * * * Created by Herbert J. Bernstein on 2/24/10. * Copyright 2010 __MyCompanyName__. All rights reserved. * */ int seqsubmatch(const char * seq1, const int * resn1, int * resflg1, int seqlen1, const char * seq2, const int * resn2, int * resflg2, int seqlen2) { int stutter = 0; } ./CBFlib-0.9.2.2/examples/fit2d_data.cbf0000644000076500007650000075017711603702122016110 0ustar yayayaya###CBF: VERSION 1.3.2 # CBF file written by CBFlib v0.7.5 data_image_1 _diffrn.id DS1 loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type DS1 synchrotron '?' loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id DS1 L1 loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt L1 1.7712 1.0 loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.method DS1 oscillation loop_ _diffrn_detector.id _diffrn_detector.diffrn_id _diffrn_detector.type Generic DS1 '?' loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id 1 Generic loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.detector_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id frame_1 1 Generic image_1 1 loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction image_1 1 263 1 increasing image_1 2 236 2 increasing loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size image_1 1 0.0e-6 image_1 2 0.0e-6 loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity image_1 1 linear loop_ _array_data.array_id _array_data.binary_id _array_data.data image_1 1 ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream Content-Transfer-Encoding: BINARY X-Binary-Size: 248272 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" Content-MD5: WPlVpB1neUj2582vHTqy0A== Õ             ""#! & &$(+%!'-!'$-/!#$(-&+*((1. ')0+1+3"$&)#"-,").*)'03 0-7+7'&'%&&1,-%.3&!$'-7. +!"2%).2"-"(& !++#+(#("%)#"&"            !)+!%#"%'#,',!)$#%$! %/ %%.,!-(%'%%,-*&0&>+38*!.(.'3&-+&&2(*4/,4(/2 /*'-5),'+:-.941*!3*!.4)-%#'#/2.+%,$!,* (01%!" %#"%') '"                #)%' $7" $&) (((%1.&$()/ /,,2(10$()-##)+ *4)00202<-4++&3'1*4&-9=)+61-<6)-#'0&4$-+3..2+1,796#/*"**'$&-$!,"%2$%"-'*#&#$ "#!'!"  $           '"$##&%",#$!$"& --$$')51'#5&/)% -+*))-*5.(4&0'<,%471#+*(+-9%0.76;-8/#=(0/3+-1&/4,-+."7/')),8:&%445-&+:,)5",)30-0,3/30-' )$(&+! -* "(+/+$%&            # 1#!#*+!%" ' * )(/'#7&-26,00"/7&85.1.=/%-0.6-51A2;-/1..E-&1:.,-047.>25;250/A677730@(-9:+J77*;221,312)*3+?.:1/-4-90##'2301))2#'&(( +%% '-%',(+!#$!,!         ! %%*)$!$("&#'#$ $*)&*-0$//2!/,:/<$(0&.331%/A8;800114$09842>8;--;D199/0;064=?211.702E30F;?72=:=8/-671426,91452<52%4-28+.0..&1(,+,,&+,"+'*$/$=($!'"3"#  !&+"""               "'!$ +" $+*)'#$$1&:.40,-(61+'(8@14?53/F105*<856B%80;6<08/461@932.C8D:?6D9E+4ADBC33D<F@;B8;8>9757C32?0:*982<31<174<6.355);<4&5/&/%/3$*!',4($+'$%'%'&& "$%% , "#! "'           ###1!&").&('",*' &-1'.&*).2!34-,<+5'1)4;4290<**8B.;;6<<I6:487:D1/84JBB<G9<>8C<D=M0??F14+>FC99@7=7>7@:8?.D3694@=<<E1927=2B4?0-0/0/=871.)-.,(&.04+&-.).')"))%% !$ " "!"""!          # ' /&$( )&"4& )(!(3('.+1399='*53;(85.9/117A.;053C-:;4</-=?/B;>7@@EG7?:?A=98D9@3=BD<89>3CH?D5?GCBPC5A57F??=<;9>J@7:@<*6?<77?..:>3794:=7,+8<1.A2/,1$,-'#4)3%-$3,+,++(("&&% %/"%!            #$ "$#!# !+'*1(1-+2'&4(1,5+%&,*@5BB*;098B(7<$6/K8*=D;9A<69HF0@9X=FJ:<FBAD;A><@B8CO=L8F?98OONB@=Q?ANAPFCC<=5:>=<:BLE;5?;@<?=@EE6<*<+;?6<46A9;;:-2/06*3,<<#* *#((+,).&,$)$* '$%)$& '         ##%"*&+.#!' #%!*/,$)'+85!84*),<;86<=(*;9.1?:</6913>AF=:CR>3B7AD>=EAHH=6B<Y@RGBBR@;FJGBA=BA:HLQGKC;CXB8:FSI3=AQODK8?NA?<:N6QA>1E<@ADFA:<3E2)97>;.2B<:4@3564)3A863=-':*./'()#./'/%'/,%(,)%*" #          #"!" #((("#%" "'+)60'//*1,$<55 ..2:6=3/B2?5=<=@49BI2B@?<?E6SBKL=AK>6EDK:BNCBGIIIYQPQG=@AEBPA\MN]M?EHHOBUhSH>PSLH[MPIJLGMLK9AIP6AAFA@7;;:CP8:-7DGK0BI5999IC1=@36:+,'/*.4*.0'36/%!5.,,"0',*+"# .       "##,-$%!'!.$,(-/'-/&71-%;:+.)3)-1-?:.A3*26/<68?3CSAD9@@6ED@;IFR;C>M@POMIA?CKA=JXBLJa[LSSLRPSHJERCHRGUIPSKT=LUMLHO\TC?=QAGRJFJXLES=EC3<SC?H<;@A>?7G@DG1B:=881;=EH798<5)4*</6,&5, &&-2%,,$(/*#%#%)%!&#%    $ '$ $4%&.-,"&*,5(%7"3,#/7.50:24=@1MH6>8=@,D9?>OE?AGQAA@D9GEK@KT@7BGEKWN<MXWMPVCEOCS[RKOTJJTH\IKXKORDR]JKQFXOUMaMNUWNFNKBMQDOSCTWNSKN;QNPJ<=M=C>;D8B@><B??E4;4C.8>C=13A,2;,70+4,576(1(+.".&&+2$ +--         $$%& " $+&/$! !)$)2(1#" *((2-*-4,2/0=204:<>48;AI</M9<BF9GAB8GELL`IIMAHGE>LHFOGMKVEKNPL>UOFKJIZHbTOJ\MV]JZIVSG=KTVDGJNRITYUNTOWX<_UMGZIPGIM?OFOCLNKZHEHJCAFBPA@?H?@=88@<<;D=4=:8A@4/1%9-0497600'2%-(6)18.$'&#"$#!&        "'!%# +#($+&,%1$4%!!503*,+)9'!*71/>6.882GD>H?:@N70@F<J9J?DG?IKQ@FDHLUDGSN[NEF]ILHFATaNVZVRWXUYUM_N[TWRc[SgUTMNZcSMfP[YJIECYOUc\IHYRUWKjTRVOJKU`IPGc]J@UUHBNPJLIIF8<QNF?7A?:C:.>2:C7<=7?2?(D7;6.+74*+3 &,1++0#&#'"("      $!$##!)&"*(."'*#$/(41$)%<= 5(120;;.4;<?:>UF8@AL<;LEOC@PMDLPGLT@SNEPIPHHOIXEVPSEFTRS^cefJ`[YYa^gOUR]NOSIQQiRdZ\`XYRIWdSUmeRZX`bURSRCdfpPiXKbVLY]ZJIESZNYLGBP;Z@H8K?K=BJLKCB@>;@?7?9F3:3<0EE1;).?%.-.*&.&&3% "(%%'        #$ (/##03++'2(1.+*-&-=11'@92:/2E6;=EA;,<13DMEJI9OAHCTUP=<GEQMWMIXGPEQKOHWJXDULOeVeWf[KU_RYa]oP\ZTZ]eN_ZjZZKTbjbbOiUT]YoaVTUbTX[Z\kn]P`gcQMPjNWQRRSTKWU\V^?\]UOHJCNGLAP=H><LI@1LL9=A+3;4>+93=)6:60601/;7*-?).*,(   "%'* $! ! %(!'#(*,3 #/4-+"("5$<:<251&6//E5==M><KE9NN>AVB<FWHEJURKLSPIYQ[^LaQM_ST[UL[aTO[OcxX\YaJkagfb\rogVXzZYc^mWaf_`Xc[Ydvf{qlgrh`k[gRg]f`aTcj[SjH[[VWT`^YWRSGNXPbMISODORWLTCEB;PYCG_9A@=CLI-=<;4<BG57>C6383*210*1+!$+*!    !%$"((%-)#/)#- ).+++..#:,(::48--@/35::FD6>C9FG;IJLAJEELNEVDAe[VOP`IPS\RfL^YYJYQUSePYdU[XbbgchTXS]^nao`lbfVh^^`kr_we\odw_ogg]aklqcale`gNy_eb]\XkbshYa[Ttn[elbcYTO^USIHR?X[WNXaDEKLH\FJNQMS9:<ADH;:@B=1A<2;9:)8@10-(*/4!6)       ! " #"%%% (&)!+("-*1-,2-843>05>6B0@48/0C@JAFBAMHHK=EREAEHKHPLQLCPPMR^gJU\YObQXgGfienUfghc\yOpi`fhocop{^hgek~]felsxeeidezv{Vyscdkibƒ{hd~ocmci^Snomsq`xTfga_eg\Wn\wSUSXbZZPUVjZJHHAFXFJNJALK[EGGCM8NGR;<>>B5>70>:72?6)6(4&9.0     ! -")$)'-(/*)$(+-/-2!5A21;6>13BAE;7B95>=HAD.<HDOIMOViTPe=fNH\]JYRZ`ZVRT`EbWTjobSs]ahXmc^]mke`x^esnwpc{f[nltfo~bwj~|ujriim]zmtfoesfeJiwj]oeun_wtjjWicaZa\ZM{hdRmOfJ^X`aTSRRcK]FSJJJXVPGU?MFKDM6RA:A5FB672?15/2-,7'+3831-   &#!"%"&+&12/)16%*-)4/=(355@ED6PML?GGF?IMAIJD[MKMMQPMR\R[`VKfQVY[hYjRW\Sa[iWw\trc^cidly…d]nglimp‹fp_jpwj{[iƒqnŒoxjmjrrckrw‹‚lkŒvmxv‹ms\ffbfri]\sqrxvqklhfYfkfeRjo]`][URggRZfN`YYYDSSQZNQENSNOCH<I2NFG6D17=75F56=6:(5=23/      ##$$%! "$!.*!-4',2B5'B=6647BG432;1A8ME>E:L>DB?\JOXIN=E[[eU_S__WGZ\b^fpSejP[riWufiqjes`f[lmylfrwi}twz}pdw‚jxrm…„mwimo‹~rwz„kkimmqvˆ€ggouu|mziihez‚qik~oxsw}{sT`jllifmZYcY[o\q]byfKG`ZV\UVONNJaXHHXJ@PKODMBAL:<?AM==C9),$&>4)   #!&, &&%%&,$"$,''.+-45)12-:2=%..*559=89BCG8L@D6SUC:RWQWJJV]VLQES\WThe_X_Z`ah^nipc`nkm|[ssphe…kfujwpˆqx†vpzoxˆus|Œ„{…ƒ†Œoš‰~‡lt}„’jom‚|‰‹…u{|‹sm}†w‚si|~qrnx|vkVsyn]„_fy_TW^h`jqbsacfkaY`Qf\`OUb\LQZQJTOJ<BKZ?DIG@EC>EC9=3?:A6A,5   !!""  #!!#$2 &*(2/60%(7E..;:040637AB82E?EOE7HbRJORraEFILNGQ\ioNKHc]gfegTbekimncfinnvojxw{{jy}oqcrs‡§„‚‚n††ƒ›~q{—š‹vˆ‡s“ƒ…‹x~‰‚Œ‚†{•z•{€Œ‚z}s€r_wœpq‘n‚}yt€xgqg}msy}jm^jgiYP^iTkX_P_`SQXYQdQ_EEX]UQMJFNRV<BBAR;I-;E:<=5:D@=    %+&.)6'-($*%212<01/%7239==624AH4ICOH=OIRAGFOBZVST_QIS\ZbiKm\\S]nh^ggzWsbkmvxml|i|lubkes‡„u†z‚p“ysˆ†ˆƒ•ƒ{ u‹vr€š‹ŽšƒjŒŒ}ˆw‘šoh‰–}Ž“‚„‰„|‡q™¡w€~{{”Š‹{j…Œpuw~ri{j~]ri}ƒfljYvab^Xdj`VnQXT_Z_VKTZWHMAFHILQ=@?H2==>E<019>     $-,/!.&(-!2+-A8.,,:2(;89197A9-7?:@CAPSLX>DTP@G>ZWKQ[\JYU_W^jb\edgcioinizk{y~{pŠ}tz{€Šq‹sŠ}†‰‡z|“p’‚ˆ€„‹’‡Š–Š–‹Ÿ†ˆ‰Œ‡›–Œ‡ˆ€”Žƒˆ‘~ž•ƒš”™ˆz•}•“lˆ{ˆ†ŒyyŽzŒm{y~zc~mtud}qqfk`fv\pl^ad`_JbX_bUV`_Z\J@_ZUPX4F7J@A=CEH8=DF5<   ("#$%(+.%%,().;)(+3,0034A)87>7->:5<=OBOFS>BIPEOXJROeNQjW_]^Ub]Vrae\qX[jz|tpos‚k~zuulzm‹’‡–}’€‡|™—’—•¡~ŽŒ¤™Š—|”™‘•”—†yˆŒ€‹”§’š‡•…¯±”ž’‹˜š„¡§›—…„˜‚—}‡—|…œ•z~r|h“wyƒk‹}}‹u†wo‡jƒhzrkjf[praYjpmaoOPbN\TIR[POUDQRQCHDT;HKAFD4  $! #(/)&6)-'%"),.;-,5A2,.942?CB@@8E:ICT=QYLLIePIdOQWVKoUYX[cln_ahpg{gtk`k^pzqUsŠtfyr‚„ƒŽƒy“‰‚‹’‹¤‘š””š“›‰¨š¶ ¡ ŒššŸ˜—œ—©«¢¯§ –¡˜ Ÿ²»Ž¦˜§˜Œ¤œž“‘Ÿž£š•Œ˜–ŽŽ‰{Š‘”{ƒ€•˜„ƒ}…y{ˆ|dg~~cswkcxlocdr`ahiaZM[URZGS[VNQFMKO;QLFGIBAH=EF#)#+-,-&)+$1'1,(/5=9374RD>91<Q:ECNFJE`BC??DWXDUWUcVXU\[__yWzhgbqndns€qjlht‰qz…Š„‹j~“•–ƒš“‘‘~ƒ}š‰˜ž ¥•”Š«‰—–¤™”¢«Œšž¬Œ—Ÿ°®³Ÿ’¯¥§£‘¥˜Ê±¯‘š›š“š¢—•®¨¡•„¢ž˜‰ŒŸ“„އ•‘ƒz…{™–‚’…‡wƒ|‚‘_vk{‰€jdfkjev}d^h]dTiYqefVbXTFPe^laUGKBCOIKH  #"$!% %"-#"0%2',),441.+&'<H8:;2;166A.DBHCK<IMMISOHKG[VnKWb\\e[bXk][leas€oajov€vr‘t‚{yz{‰Œ–€ƒ‰œ”Œ©Ã’¥{Â{•œ’ˆ ¤Ÿ©¢—²§™¤·™¥—­™«ª¤¥‘šª¶»¿²¤¿³›­©£ ¦—µ£§´¥—ˆ®ÂªŽ®š¤£•£®Ž–’•†‹¡™”Ž’ŠŽ‚Œ„v‹‚ƒƒk…Šr‡Žfr{{r}gjr…ioibd\_aoYU_C^\N`RQ`VHPKBIIG8C #"# )'"0+9236)B2=)1.;+,6;=6J4ABDWE8FDDNO?JFPTM]aSQYQU`WOh_acbafcdlk^xiz{qˆm…{vty{y•‚œ•Œ˜‡‘˜šžÀšƒ›¡œ²œ ®­¦•¢ £§—ª«­¯§£½ª¸œ‘«ÂŸÒ¨À²¤Â¤›š°­³¨ÅºÀž¥·Â©ž¾ ²§¢³”–«¹£©·ª¨‘š‘’©¥†ˆŸ’~ˆr“Ž„mc‚szoxs„‰rqsemdglzjkmrSmudWgXOROHOXKAN=GKK !&*' (.-/)-/,023,3<)(:5>:8DCL5@H@CLKOZR\RJ[XP]XR\_LhfQcrbnbgxƒ|^z~ƒus‚t‹€‘y˜„‚…w›Œ’ƒ•˜—›—‡†™”¡ ‹ªÈµ¸²¶³¥¥¿¡Ç¦µ¬«¹¨±¹¶¶«°¦½­Ç¢µ·¶±¸¸¶µ¾®©—¾œ¾¨³§§²¹Ã©¨¦¨¥¥·»¬§ª°¤™“£’£¥§—ž“¨“–„ˆ”œª}††–šˆ›‰€~rdo‰wqŠpƒluij~ndjUbpcwSYUWURWKJVTWFLJ"##%!*&(/+',*1(:,6-(34<8=8AD55=H;TJHPCN[PPCWYYA^gMPes]mUlsn…fedame{[prt|ƒŠ†|Œrx†Žy›ƒ’‡|“›§“›”¥š¨ž–´Ž’¶´±»» µË¶«½¹¶Î›² È«£¹­»Ä­Ç×ȸ½¬µ¨¶Àµ¸Ã¸Í¼¶¹»°¹»»¾¨Â°¨ÀÅ¥©Ã½±’œº«—Á°ž¹µ¦Ç¨¬³ª¢Œ™¨¢ ‡²¢~—„‹Œ™…‚„‹„‰‹€z€–itu`„q}l~_sabwo†Sbpmb\_DP^QYSQRRN$!% #$!!*,,).((1A,;22<2?H49B@@UT6:>ULPNTYWR\[NScma\b_xqpiujinkrl¡srv„‰}‘}Š€†xŠ›z”¥•£‹•ª¦¦“˜‘œŒž§¨¤ ÁÁ°«Ê·¼±°­ª·¥·¬¶ÄÀ»ºÀ¾ÀÜ˹«µÉ¹ºÉ³¯ºØÁÄѹ͵˿ªÆÓ³¿Î¢©À¶£µ¸°´É¦Á£³°©½µ½¯¡©ª¾¤‘¶©²µœ¯¢”™žœ’”‘’ˆ“Ž¡€’‡qˆŠƒv‰zŠw†yzoirztdlcJZkai\H[Naak\_RSH $ #"$$++1.&*-5?//#,/;202576?KC?U@FIEESNQQeXQTRRJdj†_h[]{fgqs|guupuv„’x…yp|ƒx‘z†¬“ˆ¦–µ˜—ž©·®’¡£¨¨£½¤Î¶­¼¹Ï©Ë½¿±µ¸²µ¹ÜÃÙ˰ȽßÔßÔÙÈÐêÂÈ«ÂÄÔÇÔÀ»ºÌ³ØÕÍÖÁÛ¾ÓÀ³Æ¾Ä·ÖÓÉÈ¿ÌÉȾϯě¿¬²­£Á­«©œŒ¿¨¢˜«£Ÿˆ“‘˜‰€—¡† xˆ~k‹~`˜Zq}|iakzjktcj`^bOkJZaU]eRIL# *!(.*(/4&%(,5>7);04?@42>55EGCE6?TEIPVJKV\o]Pf_YayffXngbntdloiƒƒcn}Žtl‰t£ˆ{‚“’ƒ„“‘™¾™ª¶Ãœ¡œ°­Î¥«¯¹³³¾¿¸ª¤¾¹µ¶À­ÌÎÏÎÏÅʶͱ×ÄÈßÒµÍÐÇÑÍéÌÆÙ÷Ïä¿»ÉÇÎ¼ÒÆÐßÃÔÓØÃÔåÉÍź¿ÄÇÓÃðàÙ¥Á©¯Ï´½¹Ã²«¤¾µ´ž«¢±¦°Ÿ–žš‘¡¦¡™¡—™ˆŠƒˆ‘¥y‹†ƒx|vtmr|dVi~ujtpqd\bYUXdg`[&'/  (!$+,2/*//$A&1(804005*85C9=YC>NK[OI>TUIII^XZXIm}_}lipkgc~yto‰†m‚{|x}t‚‡“¡—¨œŽ™ª¢©—¦©­œ¯¢­º¦Å­¹Â³Éµ´Ç°ÁºÈ¹®ØªÍÇÏÑʶÇÇèÉÒ¸ÎÉóÚÑëãÌ×ÜÐØßÖÆÔëÙÌážØÍÇàÅÃãÜÝÓÇ׸à߼ÃÃÊÕÂÎÙÙï½ÄáÙ¾¼À¢ȼ¹¿Ê¯ÀÇŸ¹¨£¤À¯£š› »ž §‘Œ¡˜’r”–€“…vƒx‚x‰tyq€q^\k[dZV^HkVcd"$! &!"(%)1/)+2/6<2-9/77=&<GF=:;V?TgVTASRZbdifdZ^m\ƒjprWkw}…‚‚sŽ€‡Š‰z–„ˆ›y‰…wŽ—§zŸ˜˜¢µŸ°§À£¾´º»Ã̯³»¹¾Ð±Ø¹Ã½Õ®ÂÀÑÐèðÏÝÇÙ½Óñ×ÖçÚÝÒãËËáÝïÊÝöèÍö×åÿÎßÍ÷çÓÃøÜÝÔÐàÙïíÙÙìÏØÊÞÔÀÔÌäê½ÞµÆÊËÅÈÖ³´¶Ä³·¸ÈÅ¥·°¦š°ž¢¬¦š¤Ÿ¥Šˆ…Ž’‘”Œ’„‡n|…|ƒv{tp`ip‚_jjnZcnbUW"",+!%,#+.*:'/6//38-57IAI@S9FC@BLLQKJWHPNIZWhWKU_cxbokiofwotnw‰‡†}„“~|‹¯™ ¤“‘¦  šš®¶§Û³©Á¨Ã§ºÁ¼¨Ï»ÚÍÂÚ¼É͵ÐÀÙØØâî×àÜÐçÂËãÒÝÚÔêÓñòÙÔÖêèÅêôäæõßëúáÉÙîÔûîàÜÚáå ÔìÜÙç娨ÛÄçèÁÔÖÈæÊ¾æé×ÃпÇȾ¾±©º«ºÄÔ»¢«¦¹¸§§¶¦¨•°‚‘¡›{›ƒŽ‚Œ–wŽŸ{xjig‚jrlkymT`uT`  '"4("-2/1$5&5/155/51D<=G:?.HPKONQRIXWQPhcZ[jame\rpVt}g‡gwldq~–Œˆ…¡˜¡œ› ´žž¬¨¯••¡¬žªºžÃ·Ì·¾·ÉÁ½Ô¿ÁËËØÌê½ãæÿçßéÔä×ÓëáðØâæÞòÑÞ÷áüÖëìùðøïóãóÛîëÞïÜÿäùÜèèãÞåòåíýòåÖèïÔéÐÚÒñäÔÙ¶ÍåÖèÁÚß¼¼¿ÁÌØ·¯¯¤ÁÅ˰ÊÅ®¾±¾œÁ²°•Œ—š‘Œ™¢”Ž~€”–ˆ•n‹nŠwynn†b‚jbmab]Y #!*0&$!&+$#)142()4=510B11<;:>>WHLJFVODVXPLLP^e[``edxZyP^Vkmx‰wtv{‚…€…w‹ŽŠ—ž…˜¥Œ™­¡Å² £¦Æ¿¹²¹Ì½¹²°ºÎÀÉ¿ÆÁËÈË»ÁÑéÞâîáçæßéäèóðøäõãåçþíß Ýëîøèëßäôãöë×ùâùõæ æ÷òôúöíâíóñïßäÚÐÓÑÖÏÛÖÝÚÓîÊÙßÐËáàãÇ̾¹Ñ¿ÊÕ×˲··±É ­Ÿµ¹–¹žºœ¯¥Ž§¢—“ƒ‚‡x}n}|ƒw~wotkpea]kk! #&# -7)+-1/8;6+*9C;E;;<C=>FCMHPT>JU[MTQjS`Y\jl||vmnhnwdtxywstp~š†Œ›“’†¡¡–¡—¤“²±¯°°¼©Ã¶Á¸£ºÒ¹ÂÐÐÄßÁËÍÚëÛáè¸úô׿âêùèèößÙòúäòäìôú  ôúçû÷'ò ùüãò  &ü ÷êèûö ò×ÜðåççîþñéäßðâìÃÅëåíÛáãÉúÑÐíØÝÏÉÊÏÌÄÃÈÑÀ«¹´¶Á°½œ¬¶´§¤²˜Œ±~¢†„~sƒ‰€‘qŠjeyqYnlr" )& !! '% (*)10.(957AA<6@4?4@H>Q;CFSVRMNXhVMQPennZmbmk„`aj…ƒ…w”{ƒ„‘ˆ“™¢ž“¬©¢ŸŒ ŒÇÅ«·§µ¾É¹ÆÃÕ½ÏÑ×ËÙÕÔÃãñÞÛ×åÃëýäþåïôÙéÜý ì÷ õ çþùíù óóòõ #-õ#ç(ðþïà  éù îûõòèÕÇøç ùèìë¹ãÚçÐéÔÇçäØÌÊÝÅÄàÅа£¸¯°£°©«°¹ œ¯¦œy“ˆ–„¥Œ’znv’gzuxtt{ude$ "#+,(+ ,%0"/,(0/03,*/6504<FF:<OKAGZ\N\RVYeS\YUl^`X``hozz_q€tŒ“}‘Œ‡”~…ƒ’™™š‘“¥¸°¨±¤¥ ®Ì²²³´ÓºÃâÇÉÉÅÕÝèäÕÛß¼èæáÇ÷ãÛÒýöõúêí úï é ïì(ë*  üû+ýÿ÷÷íññóüþòßìíÿ ý èþðåþðëãúäñÑáßçàâËÏÒÐÞïÇÊÐÏÃÍÊ̶̹¦¨ÎÔέ³©¬¢•–†¤z‚w˜v‚Ž‚•ˆt{bxu#(* -$'$905.0)/./3*36:4*E:D?FIWAFMFM;[G`d[WPTg_mselfufh††}€xxŽ›„‡†„©…¡—†­Œ–¡»¶±™Ä»ÔÎеÁÚÒÀÄÖ´ÕËÒ»ÛÔÕÙçÖìÎåÜîìîïìê*ùýèÿêì,2,4 <%$$.*÷ÿ#ø)!  úéÿ úõêòï÷êÔÍçíçßâóåÇÜÏÂÞäÛ²¾Å¾»Ã¯¤¶ºŸ¯§£ª˜¤£œ«˜–~ˆˆ}…Œr|p` $ +&(& &%&(*,$'/%&,2;:6?:3:=@@CJRU\KRIOWWQ\TjDN]cdgQm†hpp‚o}|ƒuŸ}}ƒ„Ƈ§˜®•‰±´£«ž¦´²¾µÏ¹²ÚÒÌѼǹ¾ôáâÚÝîá×Ûãéæ÷àô÷æõüæï  ä   #'#. 3!*1'+ 'G ,>2 5'  2û#% ø  ÷ÿñ õæêéùüéòòçïçÒÓåÕÛÓÑÒÓÃÖÒ·¿Á¥¶¯±ª¾¸­´¦«›ž“†¥™›‘„||‚~y”s‹x"0&*/+2$"(10.,32'26?75E=7DIR9@C@IbYM[WmZZa]LfZcoZcZYsvojŠmu~q‡yƒŸ‚ŠŸ›¹¤¥¯³©žÁ§´®¾Üи©¶×²ÕÚÙÌÈîÌñÜöÈçëýíûøëþôïóòéðûïø õí %# &<L&") ! HA6NL(D%",(C2/'&ö/+#*;-$O&&/)1 /$ ( ç)ùæøîüãúâðàãäÀÕÝØê¿ê½ÃÀÙÆÃÄ®º®²¦´²´­  Žª“ˆ“—€¥”Œ€sƒynˆ$" +!'''.(5+2-6-32,47*:IAJEKHS@PIF[IQSWV^Z[W^n}dhltrrykux‚_ouƒƒt‘{y…‹ž¤µ˜™™¯š´§Â´Þ»·­ÙËÏÊÊÁîºæäÔÔêçËÚïÞòîæ ò%é ú úùùÿ"!  ,:S0!&$#/&?/PI%%HID<G@1;DG3CN7&&9A+5:21=PB=(7+-ø#0 #þ ùúåßöãþôõÛüÅñÛòÝÑѺÍÇÆ¿Ë¹µ±¸Ð¿¿¸¦­­¥®”Œ‹ˆ’ƒ£…ˆ„yr…%$"6/'6!$# "="2(0-H'8:J9?:JGXF>@EMTL^^\ZTZVa^bkfemsxweuw}”’s‘{„‘’¬€‹ š©¯¦ª³®²¸»¢ÄÏÞÆÔÐÓÚ×ÇÞä×ÜåÂßýòàöìõ é!)!5!>05;=(Jbi*F2=>(;9!,>E,!+I89NCe<W:'RENZB8E[<OE6;B0AC12(8I'-"ø0üýýêùÿøóçÈßÔìËÔÊâÓÃÊÉÆ²ÃËҹʴ¿³¹³¸¨©¢›Ÿ¨™„¡©“’—t‡‘}Ž"(+#%++(4*+#3/217718I2;;@L7P?YINAHIUIIXYajkWX]wpdignhj~€vw}ƒ—}‡ˆˆšœ¦¾·¥£›±®¤»¡¿´¿Î±°ÄºÌÑÃëÌÈèãó íâãÝöå ýñì þó  51"W?'4+B5 V$JGYDAY7W01AibDRV;YEU`I>LIZ<8v6LW5Ie2ABJ/ZP'.aNHU/E</"2#),(/ñü ýýò÷çáê÷üåæëùÙÔàÛÂØÃÀ¹ÐÅ¿£ª§½¦¿¬Ê§”®³›š§›¡ƒ¡ˆ‰‡Œp!()//%#'0)$+A)+.5(6DE7;F1AS9?9FPDXUShMd]MSh_aqhbwfrtzxyz„•‰ ž“ª£š§²¢«¦«¨ÑºÉÑÏÌÅÈÂÑÌÁËÆËçóçóéãð þ-íý #&34 (E57?6H;jIFC*QW:gU#_M8Je]S?L<ZkDNMPFDŠI4`^DN\S5OBroWEWN8U<52VCFF&0-53#I-K+R,  èëîñÙòçæäÚÑãâÌÛÛÑØÑ»Ã½«´ºÆµ°½¢¼³¥©”–Ž¡’‹–Ž!*$'*2%*&#.;2%>)-?474UJGARQIB>JWQIPc_WScYfh|oYrc”fsjq}‡‚Š•§‰“¥” ¶¦­¸ ¯¿µªÒÊ̾ÄÂëçÞÏÌÖÂÝûæØåïÖúì ùæ *KR!$7+;"18Y$Q@\VM;OFZFU'FR=dOBLDeM:Xl:_hdAdV_IoNrWmPUc‰9O`Te`]NDFb_dYIaWVAKiB6-GII3086!8 ;+,1 ú ðý÷ÏçûñôíÐüéݽÒàîвÂÚÚ²Õ´®°º¤·±º•²ž­‰ “”ŒŠ"- (-,%?02*,2@,:9599EJNNBPCNGNR\M]\Rccdmjztl†nr…ƒƒ‡”zk…‰›•¢™”̱ª’¥¥«°¯ÆÂÓÌÕÕÝÞÑÎÒêçÇèìèâäå÷å þø  /R-1.>+_6NOQ>RRPGS7R39IFaK…D‚pnSwT…H_€h^\~TPz_€~uZ|rQ\bmQPZsrMJ[MDjf2PPiROjnAMNMc9,C7!4:8èüïðáøë÷ñÊ÷ØáýÕÑâÑÔÅÕ¿¯¯É¸¢¤¯›®¹®’”•™}Œ""#+)"1-*@?17&9J81G7GD:L5FNNJKaV`G`cPQnXm`garuzjr}‚‹z{š|‚‘–‘‡³Ž¸¡À¼¦´¥°ºÒªÉàÁÕÌÐÅÜÕÓÚóìúßàöý$ # ")56=$?&CQ?2RWe6Q=~[Aep[P‘;5JJb}cx@_Up’jTˆ…u{pk~„mQkƒmehzikv†‹jiY~|™Xq„fZjFhj^kPomVJNNDE[%\nBA5H:#G ('1+&-)  ñðïêßùäÑÉààÇ×áÐÎÄ©©­«®«µª³©¸¦š¡¡—(&0-&)&#,(!63=J9<:AA:JMEQE?NMGQR]aTc_jfslq{~h†~ŠsŠ‘‹Šˆ˜Š–𛛤–·—¾œ¬Æ·±Á³ÃÆ¿ÆÂÝÂâÓþìçï×ü÷ñÿß$/!"' 6%&>/.8+:/=D#o'Mv:6WtxŠSZflYOJu~oc{R˜‚]Ž€fŒ‚Ÿpko‚“\w‚~psksŒVv†pˆ–HpgXm}cnhgiK:\+5NagGBj@K;RQCL>");-ý!?2",! ÿøþôööòÝÙÛæìÂÑËÖÚÑÓçÆÐÄ®­µ¹§±¹œ±¦š˜¦*+((#,$0/57@0*099@IK5GHSKPWKVUa\\hbMnhpYgouqxr†‚…ys‚ŠŽ™‰ ¯£Œ™¶™¯ÉźµÔÀ¹Ê½ËÈÁØÎäÎÈçàîÝïâÞóÿ)ó,$.'1 2F%84ODKPG>]XPV[MSZffŒ>QX{’iQ}xqxmsmm˜vg‰œ‡”{~z¹”yf¤~–ž—rˆ|ƒuˆqjŠz~z†yƒ{P…ˆjhL¥€~bx}n^lOTWUU-UKCj2Q/KB%7% >!? #-òøíþú"úýÞëöìûÝÕÌä×ÍÆØËà·›¤Ô¨º©—¬§§¨%$(4!-/*/0<C2I?55=9NC>NHMJEHUW]][cclcfhhyen|atvl‚†}‰}—„ž”œŸ¬§À¨©¬³¨ÑÅ»ÔÍÖ¿ÎÏÃáßÒøôììíôûý÷ó  *3-0QF2`M<97+pBfAY^_‹pyl‘„qLmtˆ‡~ªqjŒe‘kŒP€–ˆv­’¾¥“«µ™  ±¡‘™¦u‰—x‡®kŒ|žWxƒzgŒ‰jQl~jraŠm`maXoTyueFJlMg<<I[L.1I((A',!-)  üùùüÙîêåï×ÙÕߨ¸ÅÏÍÍ®²»«´§¢³…..+)1,7,,.;0"92GP=KLFGDFFSZMbX`[_jVg]mbaf€zqvst}~‡{Œ£ —ž•µ¦¨¶¨§«ÆÌ¢¹Ò—®çÏÅØííÓùåß  ÷õ363,G794F8uRDddHH_]M3i`VQzS}‰yrpƒ€ˆšdƒ–c’¤µ—šš“qž®‰»› ­¶¦˜’–¬˜¶£Š Ãs•x§–w²ª—‰ƒ‡z…Ž}ln‰|š[{ˆamz_q‹O{xP9WcFWZ?PSEWG)HF"'8ï! üêãýúöúñäÜÇÝÄܾÓÄÐÉÅÍբשҶ±ž­..0)0&.5-33E89:L6E8R@RJMPJPNPUVOZ\eX`wghb|{z„…‚°~’}|“¢­“‘–£´º¦¢²·»ÃÖ×ÚÜâëÃêÓÉÏæýúì, 5- )*I$328XPXfe_YmqamMUoc‡nŒŠŽ—…o­Šv° §‹ƒ‘‹„€š‘‡ˆ‹½‘¯½©”s©€ž~ÆÃ´°¢ž¦¨­›€…¢µ§€–‘¤¬±e Ÿ¨~ºŠt‹}žŸxy^Gsw]fW[3PZSi>aXTY%8G!C,)4<"!ùõðâøôïðÍëÕÈØÏÃíÕݰ±Ë°µº1,+/18'=20.8:FIOCELCGBMZCUZZciY`V_cit`~xrp……˜x¯{‘¢¨‹­£´¢¿µžÃĨѣ³ÂíÛîåâòñØãèëäâÿ "!6RW7:3O?0KA@QgN^Yb[erpYOMž]œ`v‘v‘vj›©žp›­{yr¯“¢²º¥±¦Ã°¥Ø¯§´º¿°²¥§§·Ú‚¶ž¡µ¡¿Ô£Ë¸–ºžÅ̰ª¦¦»¦| ‡©‰q~m‡„vdvOWhFq]`i?sJK=M!2g2+D>!83'"! êí÷ óÉàøÝÞ÷ÍáâàÖÝÒÔÏÏ鰚ĭ("5*,##%J;L>H=EJMHWIDO`PNWYW^[oaeii`p}luiŒ„‡—…‘ˆ„¤®Ž£›£ÂªÁËÅÐ½ÃæÜèÁÄáÕÔõôõôìúë "(0#:0%236'+'>GdNIB\]_|ylpiSwp€•œ‹‡’~€ŠŽ•­›×›™©Ï«„ÉÅ¥¤Ì¨²Ùϼƥ湿ÌÎ’ª²ˆá§·µÌÓ»¹·¯ÄÅž½ºÑ¼®­”Œ¬Š‹s“sxy©wšžqƒ…cfjphec\UiU;B.7D.'`@(!,5#  íöäúïíôÕèåÓì¿ÖÍÏÁǶ¹—&51<*/4/7=C@HBBWGMDPNQEWd]SSbhalpnohyoe{gx…|}…‘‘©”’€—½«°ª¿ÌÈͲÃÍϹÓÄæÜéÚÜêÜçíü9 6%O)FG/>EUX]LLLdŠn‡sxui}}h{…“t—´…’¬¨–Ÿ”»ªŸ•Ê­Èä´®¶ÍøÇÒÆÝáõÎÁäÕµÀÃÖ¯ÂȾÑÎãÏÓѱÑÍË΢½Æ×Ò±¢À»Æ±œ¨³•ׇµÃ´ŸŒv­“Œ¼Š´‰pi‚zŽ^omk†pdzQhTJgpN+>3(*-6"/öõõïãåÆêØæìëÕôÅÞÓÓÊÈÔ1$2/0)9<@7=72:HGWJPEFJXROUYZZbdWwcrwu~|ƒqz†„‘“~•˜£ š¼µ³¾§³ÃµÁ²ÝÒÖÚÙÞåêäÝóóðôü  &#-DH99HMU_@_R~YoP‡nSjv]‡h“’Šr™u¥­Ç¬³š¬Ñ¦­º™×¹ ¿­¾ÌµÕÊߺµÛÌͤͿÎÝÆ´¾õÇýåÁðÁÂÜÛøÁÄÔâÞȺê×ÑÆ³ÖÚ‰ç×½Â×Ò¼»˜ª»²n¯’µž¨…Mv‡’€fZ€‚\plSjw6L:VUuD95R!J+F 0ùð ýýîåÊÕÊêËÇæÆ½É­#846(8<<867B?TAAW\UDLLQ^iLcbaf\Tnvas~pŠ…}‰’vš”§ž¯™®«Š”¢´›³¶¹Õ°ÃÈËÖÉÜÅÚòàõËöèÿóI ,4!!-&Z*`@P`;9c8cMišZ}a^„€† ~|…Œ—˜¯³ŒÃ~œÎ¶¸Â¼à¶ÈÖڨ̻ϾµÚã÷Ïç½Ó¼ÜÆÖûÏÞ¾çÚçÝÐííìØÐìãÚâÏÖø¼ÕÖ©º«á¶çÉ×Á£ÊËÄš¾È«§Äž´o¾x¡©—”¡vx‘µ†vUmrIE}gQ8GT%@U9$'$ú 'ûÿõùêÕèëåÇûÛËà¶®Â%'6)498D:GAE=?LCNTUA\YT\[gcW^mthmhqqrm{€Š™‚€Š³¤­•®¥¸£Ãº¥ÅÏÎÊÎåÀÌÜßÚêÕöÿ #èå=+1 EBB0 KZ_Dg@QR{mvMZxx‹Ž€¬£t«¡££À“—¥¿ªÞ‰²êó®°ÊíöÝ»ÛÝéßÆØØååáÒåæöÛçóãèÓîßÓí¿êÞÿÚÁØÁëòÙØÉêÛíÖäÌÎ׬Òðþ®Ï¹ÈÞ·ÆÆÚ£›»ŽÌ~¼orz™‚ƒ}obSr^Nlj>8K8A4@C==C)2ô  öóíøæèèñÝäÑÉÅϹ8/=693IGCCBC?LCTOZN_U>T]UTVhZpqqqct–x‚‹‹‹¤”•¨•Œ˜Û±ª¤È±±³ÂÍÅÙÏÀæêêæÖãöôìÿ#*441@OG]IBRJ„PqKZi|b{[œ|•§}”¯~Ç ¼»Ïª²ÁÆÃ§ÈõÖäêÒÜìÁ×ÒéÕì°âáëÿÄè Óéæ çá æàîíéðéêãØêåúÜÆÛÐÛÙþÊ·âÕÊÁµâ¾·Ú¯”ªË¨º¥{¹šˆ­¨pip‹N¡NULScepT&PR-6 0I* 2  þóò$ùÖõóìÞàçÅÍÆÎ556/:2:@<9@ID;JYNJ`PRTQnq[hjinh~qz”tv““†Ž”‡‘ˆ¬º®°½Ä¬ÎÒÆÐ·¼ÒÝÉã×Íñàôô åô#Z852-H5H/NTUbZEDq‰wvŽ?œp…„}‡—Ÿ ç’´·©“̯µÉŷл·ÕÁÐãöøç³ÚÜîÐßÄäåÓýÿñúÿðæó)Jõÿõ  òøGõùäëºüíÛåêÐùËøò ßêïÄÉÏâ×ÖÃå¹¼Ö¿´¥­µ¿Ü³µ‘–r‘ddl™x«‘†q_S^XEJ:8I*4H=* /,$ óùÿúêîÕüÖÎÅÇ<B7/GCO3;Q>GDQ=XLML^GZg[Rcfoe``gv†’†}Œ˜‰¥š–¢£šª¨¨Ò¯Æ»À½±Ëç¶ÍÏìËòûöëøúùë'*)-: B**e>KDVpNDZYPhn†oŽ| ª–½‡¨ªµ†Á©ÊÏâÁ·½ÆÓºêáìÔìø°øáöáüî÷÷äï 8ô2*0î:0ð- öø ù+ôúòöÿÔøðåéØ ¼ûÊÞÕÆ¿ïØ«¨Å¯´†¼¼ª¨®³¥«¤€…k„’€bcnnWOah`WK ;$.'3'!ûð ùåôïóÃÈÚò+4+0=78@H>BK;MEB]UShO\]dyr]cj„wd€†‚…„e‡€—’’œ²­ªÁµÚÇįÉÈÝÃÂÂîÀéìñéá   <8ü6HNH]]Q$TLrVM?Mgj[‘ª™›¨´£¦¸ Ä™¬»ž¹Ì¶æÏáÈØÐàíÀþëáøþÜÞñþ öþý* ÿ!Å? / /2%9-) -ù&5 ë ë"èöÍÍýÜ ßíÎóÄÏãÆÖÆÌªÆ¼Ø’¨­Ž”™ªŽœ‹iŽm’…aaxpi_bUQF99F&)S>/VE=! !÷÷÷ØßëÝÙÜÛ81CF@87CJOAJNIYRXVdXn_mpdtc|ys{yŒ~‡ŠŽ¨“”‚·ª›´®Âڨ˾¿¼ÕÈîîÞÜþíéèòë  !6-2M#9< J3TEwMZQ\Jzsw’©†”¤«› ›œ§±±²×ÊÀÆÛѸëçàÌâòõïöÜøèÿ:Û)' 043 3 O'*9<òBð,E '%$öü56>4)=!#ê(,+ÿ÷áæâÙñóà·¼µÛ¼²Á¶±Ä¡²ž¿¤«˜“¬‘hy¢Vv|tRŽW|p[fnV4RI0.A%'2 'ùõõéëåÛÔ6?<:94DGWMCRKCBRMLQscUlbsohlv{‚†r›€‹†Œ–‰¤’’³–¬®š²·À¯ÏØÔ´ÎÓÕÆìÞöàëòô ü/1 0\66J+XFVqXiŽXu^p““Zɤ¦­¶¯µ½É¯ß¼ÆÌÌë·ÜÚ×Íí öìá&:ûóH8//&JJ15=W N6PA:3B?)4Kü7)e)4 7AYóáþÿØù×èÞÒÁȳ罿ϳÀҗ§¦”“ž”i}u{’p•qTk~TVCb0T[VHF3)* !öôûòôïü71?7B;RDEFZTRSY[KU`cVjewfljl‚xi‚ƒŽ…‡ŸŽŸ¬ž—¶ª®Åʵ²ÂÉ­ÁÄÐÕÀöìã÷æóü$% "ô1,*UYfYR]W`\’[sx€€––{Œ®x¸¡‹®À³Ö»Ê¯¾ÐÊÂÉé òññüñüþçôì'%ý +!&?E-B1':!#%';1N@RQN@mWYi0R9gKd;f)/[E'<.5:*8QùAI  õ*ãäéûÞ÷ùûéÍÓôº¯ÂÐÐᢜ¹›Ð–©}Ž™~€ˆ€c}ŠTxHK^?FD2F(.G-ì òôôäÒî>>4;1>FT?KRNZD^OU`[Tfllepvjw††`}…ršƒ‹¢¹šš«§¼Ã·°ÁÒàµÄÐÇØÔÂÏæèþß ø÷ #2 4+36Q??@Xi]g]Ugn–}z”Àœ¦Ÿž¸©×³ÍǫĬ»ÈöüÔàýÜìóã íû#    "-'=)7?8÷R2$deZ775QDvWVW4<0>;hS8TJ)`<F#4B0GF0>&;#c5/"& , öòúëñòÏæãóçÊå«ýÁŸ½¶ð¹‘¾q¯†—žphe~wq~diKOME9$OV@%+ øïÿùõèH0;JF=GFSJdOK]fKPc\{_pnanxwƒ~~zz‹}Œ‘Ÿ£™ž»Åű·ÌâËÖÒÊúÈîåòûë ôùú !)(43+C8>Pap`ikH’s¢˜r|„Ÿ±˜³˜Æ¹Æ¯Þ­­Ô¬ÄãÔèäÛÖÁî÷ñØ %ê4?ï6+÷KM<:K4H.W;KWhthG<-BPh}qblPFMTBsN\@ƒfHU:\HMNeLZqUH450. '.*å×-òàÚ%üâèíðÁØöÓÞ¢¾á¹®ªÓœÔ£µ˜š–……xl^hEqbYcJ=.@D*+)- ÷#þõê08=UWCEOGWR_TX^_LcfZhcuhiee}u—ˆ}sŽ’Œ’–³­®ŸÈÀ²ÁËÐÚѹ×ÝõñäöêöñÝ#/4!E>-]JZM=`uZkfj”†’²’ª›Ž”¿”žÈ­Ó·Êæáî Öíó ï!)"(@4,@8O8EGSGGrw`Up0Ehfkg”Hpke}†]¡v_a]Ji|wU~hg((NEC\XRjDD;a(F<%ñT;"#ûæ  åìÞκ¶©Ü¬¶Ë¿Ã²œ«‘§½ {ˆpq{I„\RkfHXeW23&(;-)44>H=F8TMELQXO^XZ^pYebm{Z{`tŠ}–—˜†š ¢£¤œ‘¹º©¿Õ©¢ÒËß××ÍÿíÙóüíâð!%$%A/$M+>XQKVOJZ]rp‹~}˜w޼¬œ«½·¹®åµâÄÁÅÚøðëüëü&òû 58: /h]>>/ULf"]9jXX>eXflpWevh„z€Lw_„Z]‰”€=R–BeVV~s7|__nj3I:4`(R.!-RYT!ú*í&þ  üÝÖèÆæÌ»ìÒż½Ì…¢°Ã§—b{…jp‰R‘FOchafH3?.-< ! %.ô ÜB=RI<EUO^^GU[[Ufi_[oZ^mtŠŠy†{„ƒœ”‹¦—•¨¤¹°¯Úį±´äοâïñØòûäì$)%5D>*APK\\f|ƒ~grm]‡žœ—~†Ã𮕧’槯Ñþâù¼öÅìý0" #G%$G, ?:f*NZic€7Ld:\¤h‰q\…mP…^€›|gŸ†u{’€¯ˆ€‚^¢G˜kkŒP†qjtY†U]h;P/VWj<MKa_^Q+*$K&êÝ%é2  û%ëÙ Öîù»ß¿Õ­¯¸˜¦°£zŸ¬•Žk†vii‚d?Xj3QX6LW)'÷:6@9D7ZWTN`V`fj]kez\yelg‚ty€Žˆ›ž‰Ÿž£ž¯³¶À¯Á¹ÖÇãÐðãçÕôîëæï   2222EeX9f{Wo—u‰~_wƒ‰q„±¿yÃá¶Ù¦ÙãÒàÞØØçá/"ïî" "^[KSC6g6.Q–@8Šmi{u}x`mPWdY€WsŠmŸ…~ –f–¸bˆ‹“œx‹€•ŒqtŽrQ†€„LŠ}:oN„emvr]\O 'V)]<ý æêð ãâæåÍáÁ¬Ì ˧µªš²Ÿˆ’¬Ÿ“¦RމNekfpfaS19?H<A3$ "í?OEHKPQPZGPPRVbd_`ip‡n€v‚}Œ‚ˆ‹˜ š›¦“¡œ®ÁÆ·½ÊÍÙÞß×Ýüðí øüý (1?7-CI%_@cbr^gY„m€zj§ˆ£ª³¥ÁÌÑÉÎÈÃâÌÅèÿþ"ÿ7ö&. 0+;MBLUIANHjh[Œ†rtŠ{_ƒh{¦z^¾¤MŠlÁ¢ƒ¦ÖµµŸ“Å ¤q©—ËŠlšq‘¯k{›vpyŒ[‰cuX]‡}~;^?^8"4JO;@+%2þ*çþïíáÓóàÞÏæ÷ÐÒÂà¬Â¸¢»¦ ¡†iiiŒUQOycWM@9>5,=##C;;?FHGXHKX_c]RjjUu„unqr›‰—t–¢…–¯•¢›—•¶ªžÝ´×¸ÉÑÂØÊØå÷ ùóÿ # :13CGC7GH[XV`BC_‰o‚p–‡š«šµ•Ϭ§¹Éë×îù èæýðÿè%[ 5%D%-KL:%Fš]AdIeOk|lytn—ƒ´¶Å€vk©°l…‘ªž–£ŒžËˆ¬š£Äž«®–ŸÉšœ|‡{¤t“q”¶ƒš”²ƒŠmvuˆPJyt?XJ'C e+÷&#Ø êâýò×ÔêÉ·êÛ×Ì·©¹²Ž­› œ}°tq}tuhCHWJ7gI\EO&9$73ANGFNSXVNZMYRmk€iijgqŠ‹‘u„‚”¬œ ¥©ž¡·­É¿ÊÀÖÍÎÃäÌÐÙÓùÓ÷ ø(<5G9R?NQSK`Nv3‡h{r¤¥²–‹ˆ¡ºÐÝÊÇíÆÚÌîÚ áû#1L6,H%0SOc.Jkw{J€pvrV©ul}zxŒ¨u“~´ ¢ÆÀÁ¯Åž•¶¡œŸÃ£­¾äÕ°¾ËÇ ¥š²¡Í¤­Ÿj|°}§~g}¨€Ÿ¡wxŠV„lG„PNb:HH,J&'7ÿ1 åãÙɺ²³á²°«¿ª²©—y”‡hdcwd\|VS<q9F;2'7SMRNHNNLTfc^[RenWohygz~lˆ†‘œ¬ˆƒ•£†«£¸µµ¢¥·ÅÁ¯ÔÞÕçðøêÿöÿ02I9IVTUBRCtJoPffy‹‰¨“£°Ÿ°{»ÕƦ·Ãɼ×èüíãßö!&4"#$MODY`fC\lWND\¦•gvyŸi‡€¾®¬Œwšg«¿ÀÅз‡¹ýæìÉŒy»¸¬¡¾ØÉß»´» ŽÉ‡Ý޶§›­¡€§¡œ•«—t©†‰bB]b~TV_J;26$ -6ëäûÞÓÓýû㽩¯»˜ª¢¼†¡‰ˆ^‡pvAhLA-48+L@ *"EGJNETUYQHSTtr\acbcuu}‰uz™“‹¤˜¦•¡µ½­²¸»ÌÂÛÜÎÅÐéþàÞèåÛ 4:* (0F6@R7EFb`[„XnmŠ~yË‘²Æ³¡ÄÛʽޞúï,ÞJÿ3'J-!6,>bO0^)JxI†‹yZz€m‰“}JÊj~a­lžº‚œÃÒ¯µ¥Ú­´’»Å©Û›âëͶÕȶ­Ä –ÍÂÙ¤ºÁª¼‹­µ®ÅºžÎx}ÀàŠº«‡wv¶cz{RK:;i Z><>^N5BH7$Áþñ)øø¥Õº³Þª®›²¥£v‚ut€trlIn@I>C1]X?9+QHPKSRQWvO\mUckhuxhoh{jr†Œ”j  ´³ Ã¾½½ÄºÃ×ÇËØèåæÙýéïüö 824JNM>JK>LaZ˜j› i‰‰‰‰Œ§£È§ÄѶÜîàâààÒãô#)ó! 82G4;^‡YP@9†~AM›|pƒ·§’™­‹µ‘«²ªšµ¾àÊàÂÉ ëòÐäð綪¤·¶²±ÞÓüÁÈÖ×ÓÛ㙟ÚʬÝ·£ÏŸ{‰‘¼Ÿ q{y“‡•Šwyk[P‚gIWV(?F,s%@Ý&çÞãç®Úϳ»°ã¹›¬›˜r~vzdaazwbSX8K[SB13PBUGRPSNQ`i[dXl_huez‰m—‚˜‹Ÿ¨¢±±ºµ¬¹ÄËÓ³ÎÊÈÊåÜÊÆàòîüí -'+142'1&HQfsctr~{€€¨Ÿo©””¼šÂµ¨Æ¼ÄáòðüÞÒ7ù C%BK-iK["mw•/_½u–˜’n¼«™y´Š¯”Ù‚»ÚØßÃ̺àÌãߣÎÉÌÉï²ÌÌÝåâØ½ÁÈ×¹ÇßåÁêÎèÏ´ÆÓí–ý¿ÖÎÁµ›Äµ­¹~˜e—ž˜Œƒb^ml[ŽSK[\:8+KB$0%ý ÷ô$ëóì×è¿æÜ¥¾à¬’¯•¸ˆ‚§dU[|š\ebJc.154UT"KXHMaOXUP\rklpij{~tv}x‰¡—‡‡‚”¨­ž«­¨¥Ç´ÁЮéÎÓÙíáúäéþõ "4*%H)N0LDKvOUa`†m„€­Ÿ«Ê¹½ÐÀ­Êߺè÷ïÛúý6 9B&}n<_mP…‚~”•Œs——¡š¬¯…ɷƶ­­ÆœÏÚÏûÍ¿¯ßÖìáâ¼»ÄÞÇÕýàúÿÚôòóþÙçÛò³ìîñÏûÙÖ¯Ú©šÁ±£¾®˜ž¿ª¡—rË€¢¤phgŠa[ŽuTe(JLMX7%üöà=üïáäÍóÀ¿ã —¤’šywyˆ{\`]WLPMRR#:6DW^US\_Pbcdd`N`mfv‡†“†Œž‹“—«¹Ç›¥¹´ÞÐÌÅãßÝèÓèÖó ÷, Q%F?BFW[A…|‚{ˆ©£k‹ž–§´³Î§ÏáéÆüÍàÈäóö&÷(H81-:{8S]Fluqf†]¤È§w~†œ`•ªªÚÉ’Û»Õ·ÝëñùþÌâ×ÞþíðÔž²Öéêüúíýáâ·üóí ÔñÊòËõËÝÈýàØ¯Çº¾ßí»Ì£¦œÐÛ¢º¢„©©l’I„tw•~X[O8K56C : F$ú)ðæûÏíèÚ³Ç⓵»¡«°•‹’ \Pz€…W€a>9Z#V5`OLUR\Z^camj_whxupdy‚€°„—„›‚™©™®¾«¬É××ÓϸÍÚëþ ÷ñ#0),ME5OK]yA\[€ˆ‰xa¡‹Âˤ¢£££èÂÈèËÕéù )%æ-2=&7e8N\`ƒ+˜?„˜…¢˜}”£Ç´Å±óÊ›­ÐÕâ¬éö¼äïèäð÷ìæÒàÐùóôÙ&ôíáõéôõ'óüËæöø ÓêÑ×óÆáßÞâÝÃ¾æ»Æ¥ž}¢®„¯rs†}yxuHzViWJs!3;R þ@ ò âäðôáÀ´Ü×Ö¶Œ|މt—qf‰Sa\33=DV-QUHTYWdaT\e`p^kyj}†‚‰–y€–Š—¯¹‘¤È”µ©ÁÀÜðÎá ÔÜÿ  > *0*D/2EOo[r`jcŒ‡§ª‹µ™§‘¹­¿Å«åãØçÚèüø-ÿ2 K?:K[WzYP}«‹‡¯Œ§¢© ±ž›Ã¥˜®ÞµØÍåËÏó ÒüþÍ -Êß/û 1óõÿõÃë÷û* ×òäóÒøÝîÝÞìÛôÖÚÈíÐÁе¾Ã ¯­‡á®¶†¨¨Å‰°}Žiœ‘UV8SFT(1 /Bä ìëâ×ÛÙê߼؛¼·¡©­›tˆ—‰wlyY*DgB?DSHOV[lqgmzaaupƒl€~{•ž‹Ÿœ‹’¦®Äʦ¼¥Ð³ÊåÞñÕÖãïöèóý < 8B<C0H&bx€gPwf]lŠo§šŸ ¡Í›¥ÜÕñäÓùçþõÐ* B=1,qF%i`T[Pmnuwi~ŸÒ¥Æ­Òºä—ïÈöÙÛÍÓѰËÞìÎõÔóþä$ëßNIí$3*ïÜî+ .üóþðóõäÃðÒÃýÚÓûøÖÅ–½¯Î“ÜŽ–t’‡†LwpV_£lUcXlL5Hg%&ÿáù ÑêæâòÊÊ€¸‹½ÕÁ–’“žŽu‚“mkmjPG7/TX_M[`fV_le^}ktytƒ‹{˜z†…–§¬É ›¶Ë­ËÃڲ·æÞÜéãò  "&ZA-6@AAj\l__tˆš”ƒ…†…ȾʸìÓ»ÆýÚÞõ ò0@ #J<WUX@`]‘XOvw¢¥º‰¹¾Ìٲε²ÍÈã®ËÕÝåì/ñò,ö¸Ýâ  Ðù ôí#)þ029   (ô9ëâ.óû/ÅÄÊÜÕîïט¼Íß³‹¶ËۘУ¾©£ˆ‡Odd_“6iFA\?1C"2æìåÐßãÍòʵ¤Ï §îž“““’~yPd]uOSXDNP\TZQZcpQk\am{qrŽqw£†œ“›³ƒœ¯£­©©Á âÄÅÓÌÉÛäãø×ñåðü%%!5T++:Lahz•†…s£Ë¦¿É²µ¾¾ñëìßâæícM</dNaY…S[ltlRh¹ÈÀˆðx¡Ð¡˜è ÕÀàä*ÃØ*ÿáç)òì#ó5ÿ*ó'9ÿü.,T'ö5V+L66 8ý2=U<?*ìëøðÎÛàøñð»Îâ½°¸À¥Æº¨–ˆ‰ŠpWqkUyhf[NMD& (+2,íöÝÑüÒâÓÚÖ±±±|Šo”ŒgYnVQg>EBKXRW`\\tbrvommˆŒŠw‚‘Ž•“Ÿ¬œ¡¤ÉÉ¥³ÃÈÍäÉãêèñÿúü+$764LXPL„ng_€t–”›yš ÆÉ¾³¹ééøÒýéíòû1" 6VD,"Z]MVHjˆ†“Ò©¤à¨ºÂÞ¡ÍÝÁÚÐÞÄçøG·ø&âÿõ)92&3[4P;6XjT%g(5YV09E<áú ÏËêøäûìËÕ±ÀÝÙõæÑð¼ðjÅ¥kˆl–…Sk`j;1D5;- ó-ùÜèÐȽâï©›Êyˆ¤‘‹dKv\7)>]f[fQRb\nbbvnol~Š~{Ž”¢‘Ÿš¤˜­ÀÉЧáÀãßÞÛÜßõóÕóïãð" (N59?TPJ@YJo„‘„‰ÄŠ£ž¸ÍÖ¿ùÇëâËíÒû #áöA%B ;"dG\qur…p–xr¤Ù©Ó¶²Ê£®¾’Ö¶ñóÞÎú êö0ô!+?/,3HHHZB0M%hd#S:.\F4,-.8FKD59÷ÿ@LI1#å÷ã2çæØÒëÈ´§Å¿¸ûǬ¶¦—Rriw|†hw-NVN4+*ú$âòô³ØÑ¶°¼²½Á‚–¨€m]keWmo@GZ]N]Wk|qpmuT|„Ž~Šiz‡§…œ¿ªžÇ ²Á´Ë»ËÓÚàÛïëú% ( )@+cXBLTQj^t„u¢®¡Ë²µ±¨œ¯ùßÐ÷îî!9>$>#1€TrPxI’m‹€l›z²Éª½¢È äÍÄÞ òáï÷ò   Lú %;mE560(:>CLH% *.Nù>C_eDCh-6tH+0X=&;*5+2 9"9åGGòûÿìãÕÓÒҡຫ°ÕØÓÀ¤´”¨{mtV‚Rh^qKdN&3,B;î#ûáÙÛáÃ÷ÎËÜ´¦³¾³·˜š””£‡ƒ‰~`^ZUi]b_RY\j‡lˆ‹~€‚…­›‘«¬›¯ÎÇ‘¦¹ÐºÒÇÐÑÏÛÞñþ'*.V CKGjhQhYpW”‚£z˜ƒŸØž½âýÐéçììáô((?O(PoM3aQk„H}ŠTf„x­§ÏžÈ¯°×ÑÔâÝ!Óöäü(óòï8&7ò Kwac1`+DlBRg`bp?)‚Ake†S)gAHW„DL_q/NQ1R2!0%$)B -)õÓ*òîϺÏã°äê×›¬•¤Š±˜‰´pUpTvdaaLc><2: øõäÛ ÒÙ¿¸Á š¶u—Žœn~}qFGQgjZe_XXlidZnvw€|„““‹‹Ÿ–¥œ¨¡±¯¿¬Ð¹ÒÊØÒÜÞèÜìûù*1'AE&8>>YeSl}cuiv|’´}¤¥¨Ç¾³Êæåãããî çîëY-3GHLTc_›E¢K…º‹¬¦õãâ­Ïü×ð$Ñ/ÑÙòÕ'?-B$>I5NKV+04YNDv–Td'QerŠk#u=[!.Nvo\K@ciF#&R-?,3'7-þ+&öçëÕëÈÝÞå±Û™ÄÙ™®”–ŸVW\z†aAe]^Z&N]:ùçêåÛÐÏÈð·ÐȘ¾‰„r›p€qj\gLVWo[akusmthsŠŠ…‚~{“œŽŒ˜š¡Ÿ¥«­»¹¿¾¼Ääãæôââæïü ü&4B*%f[Zfjd_k}|‹†’˜˜“¯Ç¿¸»¸×ÊÇÖâòâ 'BCdM_l=]dRg}ƒpŒw¾£…¤£Ò×½Ìíéß ðãX+÷>Y 3DS#LPGOeNibb€Yoe€]‡yTVŽUZ§£\Uckj!ov7da'W'B\%:2e"/.92ýÓáÊØÁø·ÃÀ¢µ³©ŽÀ­ƒ«e…^sJ\dV7{E1N+  þýÜÞ½ÛɼǮĪ¡ƒ¡ˆm„dbj[dRYT_skdopzŠ—†”£ˆŽ¦Ÿ‘³—ɤ½¶ªÉÊÕÔØÐðìæîýäþ+#9=*!>>6Qƒx†]tg™‡“­ˆÃš¯ÐØÙÆÛýô ,ð'#'\6[FEIOYnqSr¦”¤±Ø­ÄÁÅÈʯѰ©ô? ñ[à`1W.M,8SX_>Ubk‚œ@OK<empM]…?~zB ¬ghPv;:ŒLW*Ea3QA/1:*<D‡i@2M$01âJ ååºÆæÞä—®†ê©›Æ™cu‚~qdy^b‚=,5-)&þññá丿§¹¨©ˆ–©»ofnsWN^^iolg\rd{is‰|ˆ‡†‘›˜…¶Œ›¦°«ÄаºÁÄûÈÏãÍÕÒñíó1"%2DE(EHZS^P_Šžo”a€~¶°Ÿ«³§ÉØÇâ«÷Ðï,/1<\3/[A-UMvjwp—ƒœ±˜½»Ãµë÷ýíûôàü>´> -P,:].1Vm€c>bvM7ij;X\/6b\a^¨‹x§‰ƒjT §gP…xi~u&VkY`Hjc33LOY9 Q$0&,+ûàâûêíÚ¸ÀØȨ̂À·‘Œƒ´h‚§ˆt…JVCEB=A*ìÂãïßÈñϳ°š™¶ œ‘curuwXU[[fqidlmqˆ‰‡‰‘ޤ”§˜•´¢¶½ªÇ¹Á¹ÛËÖñÏãþèñó  (8#C7SFH;YXtfPx…w²ÂË翳ÀÞãèñêûáCõd0Mf@?~dŒ{:“¢‘•®¾›½©µÄÛìðÞáê+:$7U4"Jt<v!s]Od«ZnW~@\l`ixHgo`€cH”€qvš¹Hog6duŠ8ŠÌb|j]yRYn=rX'$P40" Hò úûµàØñÂÌêõ¹°„´ƒ¤i¢œª‘Exe0:^>6/&.èñ ÎÜÞܵĎ•ª«Œ‘yRhWYUZa]fvwjdt‡~‚ˆ€…{°– ”‹··Á®¨°À±ÅÛÂàÚáïíùÝ ÿU<A0BW:\HUuRoxVqŠ{«µšÄ¿·Ì¤ÔÖåÚü 'GKBPb'wFMIT e~‡Ò‚µ´¦­ûáÊäÛá çÑüõúý:WZJ=KQ[NYs5VO@€ck‚W}§•€§”c¬¨Ž²·Tg·Šq|šVyy‚„НS‚S¤'‡kp\K“PI{I_G9$I 5üü"ÓÏ ÕÁà¡ïÃÜŒ¸½~j™††\UuTFKB?AE."ò ñª°êž¥ŒÁ½©g‰x`VfbhYddqpm„|xŠŠ•Љ‡¦§£®¦¿ª´¯ÏÈÒÝäóóäëôõöý '")\?R/s\\Xhl†u†·‰‡¯žÀ›Æ‹êÔÙêñ ù ñ)12V<CtWS^H‹‚p‚…Ç´­˜£ÁÚ¤æÝè·ñã#,>6M'2bW(e=Gd-Cqt)wg«rš^ˆ‹Y¹š‰‚°œŸ¤r|¡­ºZq_|``v®x‘fd|åŽLSj}-c2*>ED86óÑèàüåçßÂäùÐѪ¸–¾…mtœfkCi1[^N.* ,æøóÖçáÁÂÄ«¹±’³„ž•pZPTOefujƒh‰w{~“’Œ“›‰Ÿ¢®œ¤Æ¾°¿º¿Ñ×ÞÉÑáØôó 3<FN[ +VjIl\Žw˜¦Œ‡§…ÑŸÃÖùâÌíî åú=+%MA<JDfWpWoBp™Ž¼¢µÁ¼ÎÐÄÒÉè Ôù!ñ ( DH]2-3_IH][hf|. dyh¯G¤²[Œºa—˜p–’œˆ’½Ï£É…£˜~—µ†s“Q š‹rrv[I>qz wB4WA3óõèþÃûøÅ춴ɯg–ÌŽv{‰hok=XJ1N.;5'9 ÿ¹ùïͳܼ¬®v±’~zb[zf_cb^`Z_qmƒt›‡Š£›ªª±©Ã½´ÄÍ¿ÒÄÊÂëÝ×÷ëúûü(! 4:6XYB_3bwl‡†’‘¾ž¾½®²ÃµëðèýãÙâ!ù96I('wWqKDtl„¶{ʦ‘œÙ²²¹»³ÍÍúøð!2 `>_^^]O>OwtKah„]ˆ›_{…mb›¤šžÌ’¨ `¦¢¦¤\š·Šƒˆ”¢…¹ˆ°©–wXŠ^q“pw€~‡tdk2UmBþHìJ#8"ü&ÿ ý»ÇÙÚ©Þ¦ä´|„¥t‡QYYI7gS6Q16!íßëäį̈§ñÑŲƒ•Š–{˜r]V_groqjb‚Œy–†’¢”†¦ ”’¥ªÁ¡—»åÆÆÛÜÔØóãé %)8*iK/VVVJefyl€–¬¶¥¯¢ËÑÓ»ÔÕù ùøôöM\I:;„p˜Zb„¨À·»½Ü³×¾éýúè-ùþÿ#TGH;YyiT—5,pdKow’T¡w½Z‘¯²Â’›¨…¿uº½‡¨ š›uµ¡·ÊŸµœv‡y¬fŽŽÂh«±gBg5L„yVi#gEWuûS?'ÿ8ó øÚ3ê¿Ù·±Ü•‡¥j—žŽnmomyLLqH[HW!ùßÔáÜÕËϢ̿“¦¤{‡TVVpv…jd~g”{І ˜€‹˜œ¬™§¦²•µ¿¨Áº×ØÏÙîã÷óì ô "@7$9!7mclXzshp‰™’—¦Í¥™×ÆôÖáßòþÿPE4'[FnaqH]€£d{©‰~ºšØ©¸®ë¶ïÙûAAù%CXeNpdŠuq{MYUž¦žŸ¼¤¢Ü|¶¨„“©ŸÍ›«›Ùê‚´ƒ˜³Â°Ÿ¯»„‘®ym–ª_’§›Œ\K{˜WjLm:}%ì4öA(ÿä%ÏÉ'¶ÈϺ££ŽÓ„„­~|“u{fKV]@@@ô*ê*ø êÈðØäÒªÅLj¾¡m{cjTkUeosky€x‰Ÿu‚†¡©¡˜²°ž¹Ê¼Ð°ßÜÓÂäëËÖöóÿì&)!)XnA8uio`˜‹ˆ†qŽšµŸØéÅ£¦åøù× ÿò%%73C+3mZp}Y‘¬¤¡Äªº™ãÇ»¿Öçô&÷Úñ6!#+P4Q:nX*A“‰{_sŸ‘fL˜½¼q§˜‘`Åcås™|¼²Ô¤’§¤Ê´§—­¿È¸À¾k’rš‘˜rŒËQ´‡Y€ssfƒIYbF‹]P>#=/ðW;-ùþñÈÓñí¨æí•Þå™®”®’ mqzg\GY$[>HG BøêïÔßÐÊãͰ´»¼Ø°ŠŽ€œYq[oagrvrƒ€jpzŽ€“¨™’–›Á¦‘¶°ºÇÈ»àäÑêììøìöô>%eFLVRpj\eYˆž‹˜°šÁ¾ÆÊÙáçØßÏîü!4A5X0XHwoyu_—Y«…ž„ʛܮæÌ¿Éá ÷B% ?oaq:^\UT°{j‰…M|¨¦¶†±¤‹‰¬‚½“Ú¦´»ÂžÈý´†Ù—´ÏÃÃñÅ«š¶ºÎ¦ŽœèȧȦ’‹„©Žv®UcNq`eUI<1N,%:/ÿ2è+ÝõèäÖÊëÁÚ¬œ™ëœl“–x¡z`k7@PK2:û ìßÝÅÄÌÖĻѹw ’Š^Oir_Zxovv‹†x„“€˜Ÿ£ ­½¬©¦ÄÚ½¹ÀàÙâÜö¿õÿùöõ4 2&"9XSDRd]pŒ…‘|‘¥µºÑ­­Õ´ ÚÓú 3<';@I7LejL<hjz˜„¹ÁÉ«¨ÅÊãá²çþÛù>A0 `S+kJešMXwoJr½s‘‘¯Kœ ³zÁ¼Èñ´ŽÇ¶˜•¢ÅËàࢌحãÄÁµÖå¼ÈÌ‘¸±°¥±×˜Å–»¹HIg‚]^]dAL BnHae3Hù,øæú ñàЦª³µŒŠÁ~Œ‡ƒl…mZ#BqO:,ÿJà0ôíïÎÕÎÒ©žµn—Ž©pW[i`u~„}ej„t‹˜‘•¢›£¦£ž«Íǽ߿ÔÙëçõØÏôöÿ%/C?B[/Ep[e]{aŸy£w·´µÑÄïíÝëÿÖ;÷,H;*\E5QqmvmŽ•­¥’²¸®áÔöÍò"ëC. ÿ2X,A<4ML:WV›Bzv‘z’t¸¦”㥽’„‘¤›¿ÉæÉߎæ°òÂ|–ÒÈßÃÞ¥®ÕÃ;’—µ¿°Úµ˜Ž„Ü¿g„¢Š’|Œxƒ€(SnaZT8<=CqZ$_Rÿ äåèäþ¸¨­•¤§¬Ï~®|aHfQB|J=*( ÷ööåëÁ®Ï‡´›¥­z©Xnlq`umvwp|›‰z“¡ˆ·Å¥½³¼­ÈÿÚÓ¸ãÒÜàÐ ýþ7# ,4$3JK>ZhMvvˆw‚g~ž¥ºº¶»Ã®èçËí"þú&A?Ydm>w}‚’v‰®ªÃªßËżìæðóæüç>J!=|O2M(‚{Z:Áaj~tŠ‹¤¨°¾¸•g¡»«¤µ¥Ï»µÆâÆüèл̱ͷ뒔÷̰°½Ä»Œ°×› Á¢o…؉Sl–E¶gwˆLfXiRŽ6bB$ûMý0 ;ñ ÎóóÞùøƒÆÅ¡Èˆ¢¨…4ZYHFv%1%$' < ãîÓ›¼Îµ¾ƒŒ†›fcZbpf€u€wzw‰ƒ™šƒŒ‰­¥¡¶£¦±ÄÈßàÆÓóÓòáüï(3<)J[JcM\eXkqˆ‹­±¹³ºá¼ÇñÞèÂÜâ@ A?202-*o…{—jY¢¾£¡Ž¿ÐùÏýÜ´ÝÕ=Ñú û>.MB1)k’KwT~qˆ…¥†¾§­’©Ú§æ¬º‹¸Ï½›ÃÑàÆËÀçó—ËáÞ³ä¾ÝÕÄѾÀ㶸ÏÈöҽˆ§¸èŠÍ¬‹Ÿ}Z‘¥±QhN|OZ>4';# /6Îã ×ìñåÐÆÈ„ë~…Ÿµˆ”UƒFl$#@`*!%!æäæüÚݳ°Ì¡Å±‘œs“^^kkstnw|try}‹‹Ž’³©”£©·Ñ°¸ÅËÏÃßáÜòíæí%#'L%=KLfbw”cf‚€Š™­¨á®ÓÍÖéó  1ûñ IU:Wfm\Xu{‘§vvŽ´¾›ŠòðÛðý"-7Jè <A0ˆ<q}?€zvdoyÍ•x”ͰÓ¸Òþ©ºŸµ•Òл îÑÔÙà÷|ƶå¸ÑØØÓ†ÃÀŒÃ¨®ßÚùÒ¥ù½¤«¼•´d¨{É{fcrOZX'j‡€-B,56 üßùðÔêùÑš ²›š¥°£‰¨a¤bmƒS…1C[?$*;÷ðãæèÿÇÏȶ«–s•„olU]Ppc||xŽqŒ™”y𔦝›¢§Á¶¸ÅîÞíëëÏ÷çáëôí" (,(4ICOSJpqˆi|yÀv»Ã‚¦œÎ°ÌÛëîâüßíüø/*N;W9{~_€ttºœ¼‰ô¿º­Õ¤´ â %2-5T!=2MŒ7u†vq–Åúš¨‡´À±ž¸ÃØÚ¥·¡²¯ØáÝ)Ô³ü·Ï¬ ×Î!Š•ÝÓîÖ Áèñ—˜¢¥©³Ð£»­~‡W‰m¨’fQNrx_M)4#< *0!öøõÜ¿ÒýßÔ¿¥kÇÈ”hk}€—–oZ]WCZÿ ( îÜùåçθ¸«¢š ½™¥’icidtxooxušls™“œŠŸ¢©»¢´°¹ÙÚæÏßçØðçéôþþ "/-4'7O7*xkZx‰‚~j ­Ž»Ëœ×’ÚÞ˜Çæñë*óáD.<35FAKx•i:o“¤ÇŠÌ°Ð´Û™èðüÝ÷ïÔ0Þø(D1/37†HMxª¦ƒÂ‹¿bÖÅÆ¶³•½Ú¢­ÛÛÓÝÌ¡Ã'÷㾨Ñ(÷ÔÛùºòÑ!èáíö¿É´¦Á·É΃¿ä­ºao‹ŠtQŠoaq]KK7€E/ñæÒâ%òÛöÅöÙÔÅí´”Æm`šeyHv„CkFl&46+äìÜíûÒÄ廿³ƒ¼w¤Xo`vxne†~t…}Œ©™’¥ ¡µÉ±½ÃÀÆÏÄßËéâóòýø÷ G5ROa^oKwk„qo‘‹c š©­¿Ã¿¸ä·ÔÉ ú1ó-.$M[1JuWXd–…޵¦­ÂΨ´ºÊÿÑ âèîFþ<.6 P`aVO{K’Zt†jŒŠŒi¾†…ŠŒˆÝ‹Ç°Éäι¿Ùà⥠«ÁÑÔØÁüÐð œÌ›ñ¸æÂ š¿½Åò¡ÐˆŸë‡¹£¹¾ˆˆyOƒ®qc\M?cNU=108.7Ú+Ϲßõ§´ÊèÈÒ°¤——iƒjˆR<5<(:'%ÓúÊÏñÑĪÕÁ™¦´\rZqog…yu~tu¦™†“–ž±¡ÃȬËǪÂåȼÎâýØóôõñü(ù%3B23=BDaLint|pNމ­•” €¯ÇÛÖºØïáÞè  $N "F\TS<U=„t£•mþ‹³ëµÅáéðå)ùNí {tE^KC=Š¥iJ¤k¦£ˆ¢•”®À»ÅæÙó¹¶ÆôÙ¹¶"Ê éÕµôÛÁùÆÉéùÓæÓÙ꘳ ¤æÄ¦¸·Ék¾j‚Ðã¹redjµl›i›ˆvKf„GCwK6; 'Ðó×$³Òã¦êÎÃt˜˜˜RKQDZQRF8. +üöÐß娶½¶ª½ž–oWhopw[r{vnz€Š–“«’œ ¨¼¬«Ó¼ÍÎËØâßÌèìúõ! #>$>KL2Q@ZX_Œ]Ÿ‘ª—¨Žº«´ù¼»»Üãô ðð'5,-?y;|{@h‹‡‚˜´~Õ¬ÜßÀÊÍùìûä!  5 T?'L<[nn-ƒŽ`…A¨¨z”ÈŠÀ±]èÃÈÁȬýȲɽ䵳³ëºÅµÊð¯¯ý±´·ÒßòœÏ¿ÀÉÆÚšÜȵ¹Ì„tغ´ÔŸÂÕ¥g€”W=n~oufHF#.-Eö ûòÃп»ãÁžœs‹œdX5=^FI34E, ;ìóÛÑÙÙµØÒ§—ˆRdw}qnsm™qƒ~Ž ¡š¢¯¤§ÏÄɱÉÞÅÐèÌþçêùõìó>W_BeEXk^[€sxœ³€²€ÚØÆÍîÜÑå  ñ%CO>?ig`WuŠ¥‹‡vÄÈÊËÞÌÝà#Ô*÷*'6mTzDEG}„h_l„xu³†¡»¥¥ÔÜœûªË⵬¶Ýî„ÔäËâ4Ù׻ϻÃ÷!Ü"àãËä×ÝÓs¤ÜñéÄâÉɶ¸úÈŠ¯¢¸w…€smc{TaCpQ\8cS)&IðáÝÏ©ÏÆéø£«¨¡Š†ª’hŒc\F93-C.'ùþèüÛðºÀµ—¿«ˆ¦¦sZqSztxx„l—x†…–§­˜¼¯À³»ØÙçÕÔäÝâßï"ûG4"0Y6JLTWu†€¨‰¤¢Åس¶ÁåÇÑúì2!T>2?<€W|ƒer–~޵œÕ·ÊŽÙôõ÷çõ ='ý :.gY:vlt›1Ž°ÍŒ½¨ŸÒ¢Ê¦Ìèå¸ìµìؽÙîÝëìéÞ"³Ê)ÕõÿØÜÉñå«Ú̷ð°£½Ë̘ƨ‹¥“®fŽl|z“ooX4?oYh+O'û;ðñ,éûÀÈ ë ¹¤¢²ÈÇ|yH[}Lf6ri"->ãîú³ëÅ”¾Ë¢œŠh]oajwgv€‚‡{ƒŸ‘œ’¨ª¡¢¼¤ÆËÑÝ×ÑÁáìçã )óþ4,.1Ff&1U\WpxUufŸª„¨ž›¨å¸Éîëÿòó ÿBa9'k<*j]—•}±ªãòÓ³éÕÊùãÓ:×8- ÷A )Yw3dA`Vsly‰z[o“Ö±´æ¥ìñ³zâÏÛÚÆðØØ½ÏìÀÎζêÓéúéË´ÉÓâðùãØ¶ÒÄŲåÓæ»ÔÞÜÍœš—±€«Í~·€»o“LWQc~w7‡d* 15ø Ô¹²®Á’³˜¹ÃŸ‘­\ªvXmoZVI$/'\40ìÏËðËÀ¸ð¢Ê‘¾¹‘T]pxtpxmƒ}†“¤›²™«²²ÁÑÜÀÕÃàÄâÜïâüúùðõ 7&/A@AH;`V[Qodlu‹ÌŸÂ é§ÑÁéùõÚ 'GArZ4^ZQx~nrˆˆ¹šÁÃÓÚϲ¦íÖ¥ÿü -ø/~*hDw@“Xš°•i}‹x¬˜wŸæ±íÆâÀÐéηøÜô¹ÀŸÄÜâÒ+¨ââØëÃìÒÆÞ¾ÝäÐÌÍäÔ¸·Ðºå·š¹¥¥¢™š”vµYª`w<vcX%T -û41.$íýöôÂìÙÒ¹ª–“¯ž˜€ygYP2>-WDA'ôüËÓÊ÷ÔÏ ¼À¸Š˜hxkdkr€‹‡ƒ‹‘¤}žŸ “žË¬¹Åưɺ¿ÌÊÕóñýñ %(<+8K>83ZiBk‘hn¬}…o´¶˜¯«¹ÑÓáÊõØè0,E*0rbE~wv~mŒ§Š ³Ù¤êØßùßõó*×-+W2_e‹R[U67_o{¬r~l ±}—®»‰Ø¹õÕ¸á²êýØåðÞä .>ØäæÇÑÓí¯áúɯö æÞÕ¿¹‹ß„дÌ˾£Œyw°y_}hJb—IW65S='RðÿÓùèèÂë™Á°yš– “ƒ™nv`5$;M@W 6 ñïèèäÍÁÓ§¶Ê½˜PfbevUt~}‡—€‹Ÿ©¢›ˆ›²º¯¿Ú·Ü«·ÜÔèÔÖàðøò &$+%#LO-OFGfr{†~¢ˆ‚~Ÿ¹¢¨ÇÛêÚï×è ;$D['QmUb‹TŒhΖª¬Æ½}ÅØûþôæÿð9"@E>P 8‹PVL}•fC’–vŠ—²˜¤³®Ÿ´•ÐËÇϳÏÕãɬïÀû÷ çÃÙðà ÈÁ½¡½ÛíóÞÙ±êÎÌ€»ªÃœƒÃ„2~rˆ—œv&ƒ£V[,]G/&<ÁAñúïܼ¢¨ÓÀ»¤ˆ›fŸŽNhLM<=+ù ýÝ÷ýÏÔå·Ö—›™­hd_typuyj~•{€~“‰¬¦²©¹Ï¸Á±ÞÕæ­íüÓÍ è  '@.;1;ofON-{r’t…‰‰ ²š¹Û¾ÁÏÊÞöõÞÝ1%+3*H]3`cbˆFy…•{†¡Á¹¬ÊËÇÝéôñæÕ5! eGNInŠ|L’µ}”cŸ¡Ã}w´£³ò´´ÞÊÔʰÒÙèÓжêÊõÖÓ°ï$Úïëøõ9áÔÜØôÜê×Ôá–¨«Þ²Ù~š¿Íß‘\±˜P{v‚•)‚upMcW@(=øØ%ÓÍÐïÑÈŽ±Ô» Ž˜¤€t]]€*f;SP'>àéøê½áÙäÀ±šÀ³Šhqimp{xus~tp{‘ž  —ž¦­®¹²ÂÇÅËÜÃÈÔàÝîö  ,M-QQK^_eRgq£‡š¢p›´ÆšÄ·Çä¾ÚÝã ø 5'.3,T9‚fZ•fzœq…¶±× Ûȱ×ÏéòéûR0#n;NWG"q“smp[¸ £iŒÊ®¢³¬yÔ³§ÇÒœöÞ²ÉÙÙõÊûòìõóð˜ÌñËõãµÉðÏòÕ·°ÉĬ±®´œ¥¹ÂÀql«“CV\Ojg;qY?FK_>P¹Úí ¼¶§è°¯¥·iª}[qgS9HkSR>ùú ùúÝ ñÿäȲʙÀ¹À¡fk`io|rt‡‰wm‡y‹›’©¡ ·»¿·Ö¿ÐÜèé××ßêæüñö  -&0\B-2FPOSjm^i—‡œ¥² ¨Ë²¾äñÐò äó.*bJ'CŠcyXœhsªhvµÆ…É×ÇéÔÝøÛöìà7}û40 SW2/`Xw_›npyQ›Ÿ²¥Î±›ËĦ» ÈÏõ«ÑãÍ·ÉÚ÷ðÈ©ÌÖÉüÒÅôüù àáÊÀä#®)ëÎÞŠ®°˜Ÿóøðœy‘{‘|ˆ„mVJœwb]EM"/ðýðÍÍü»Û¶Ÿ¬¯µe©€¦¬jF>›2b[=;ûå&" ÎæüË®»›¢È¶s~b`c[`rty\qu”Šuˆ|’Œ¨»Ÿ»¿¹«ÏÀÉÄÔËÊñéðú#9÷&=aER\ZjydcŠª¦»ž‘Å®°á•×òàî   W23ZBKcqw¦`¯…šÃÂÂÒÍÔÁâÐ,çÓ 1JH;/HQP`†pX„¦ãŠÎ«œ¼â›ÀÍåôÕ­–âÅÕÚ¼ò½óûÈàÑ¿×òÒ½¢Ê[ÍáÝõüæØçÊíðΰӥ£€ÈŠ©ªWm ‚²[_|PKT„G<fE@* = ÿð  ôòèùÇÓÀȉ®£™¸¸˜‹zl‚Lz;I02+C "ùóôóæÉÓ¼½®¶•¾`Xh~rpoŽtq“—¦†¨ Šž®«¢©½¢´¹ÄÎÖÒÎÝÛáöþ 0!+219I.@DznW}lmŒ{ˆŠ”Æ›¬¾ÈÅ»ëâ÷ð#î  [>;STk]†yDŽ^fž—¶½Ì¯´äÛêõæöÈ û< ö&D8E‚Gpcž“—š¸š™¤«¢ú±Á’³Á¦Üë± ¨Ô¾Žå¿ëØîæúÂÁáÿÞ¿·ÁØüû30éÛ—!³°àÊÃáå¥Ã\»È¿¦µ­V~x2L[1S]MM@+m5;F(í¿Îáìé£é„κ¸ª‘£“‚bjjc5PVJR#$ûôøîèÜÇլƳ¯¥£†¦Ydinvf{jfvo”¦…‘¢œ˜’̷ѯ¢³ãÙ½êó×Ûçø ó&G.!<^f\L0„fq…™”Œ»™¹ÂË¡¼ôÑëþô #û /'@>?f?Ž[p±yf €Ž¢Ì¬¦Óîåèêåç LøaK[)C1*vE2<N“†oÀ¢ƒl˘››”Ï—Æä֓ĽÑÁŽÅÊôÁÖ«Øô¿ÍÃüàÞÐɶĬ¡Î¾Êñ¹Ö̯ä¡Í¥¯¨Ò¿Ñ¡›Åär¾šyf`rorZH*B6&3-G%.ûùAÞÓľ»õļ®‹à‘´sgcŒf‡T;ROT!7)KöTíö ÌØ¥¼º‡Ä¸«»±xkfg`juk}s‹–€ŸžŸ©†˜ž° ÈÍíĬÏÖÍÜÁ׿íË"ì  ÿ$?>K[r:q~^…Q˜{Áš•™¡ÏáÄæàÜý÷ ó÷*g eO1—bgoy›˜ ¶Ÿ¾¾œÉ¶Ö¿Òô 3ð!=D,^|M–G[‹Q±WŒx®€žƒÃ­y•¥ä­¤³µyú3¤È±ØÉ ãØµýí›ïæ‘ÊÛÖú÷ÇÖ¶Å­¤Ï¯óÊÎ܃µÐ½¤¤sÄÌ~ºŽtQœqt>=dƒ_3Zbô(ê óúíÐ̳üòžëŸ´ÆÄ¶y„zŠ5p.5iD'K'%' ½çÛÒÐÑŹ°¤Ëˆ¦a}xmaoi`Љl„ƒ‡£¢º¯¬¹©Ó·ÄÞÐÜíæúäòæÿ  $D*+bTqd\frƒyzŽ‹¶‰¥²©·ÊÌ×Éýöðý+"?RK=X]GGt<£}š¥·÷îÆÎïòîîøÿõ  W@[L!sz[~›‰§~GœsÀŒŒ¢²«´âó®³èª×ÆÆÄÇ´ò÷äË­½›ÎÏžÜ÷Ö÷Á­ÓËý¹Ñ®­Íâ·¬¿ŽÑ®ªÎˆ™Ž|‡ˆ†Š9ŒE–r&T+$PJ:$ ":ûÖ. ÜÙ«Üã׳uÈ…–dr‚w‡b831Y1.ã( ýøô ÑÂÇÅǦ©±“¨¢—Z}ukjlrl}w‡›žˆ£³‘¦“ª°¯·Ï´³¿Í×ÙÙãñÜí1B7M2EJJ^=<_\„ašm…˜¸œš®´«Úçëá!.  '5T<„~|ŸŸŒ¥¥˜¼º·Ø½É¨Óõ½ ý^0b[UI'bH%6ia˜]€d~­»¯s®“ßÇÀ©¶¢° Ìíïý ´ ¾ÖÛ篻íÅíñºÂÁ®« ³ëÂç¼ £˜xª½¶c•¾p•mŠgpƒ©uXhkY(]SD/7"þ äàèÀÔÀ×ï«°˜“ž¥omt}9ajZA/7ò ÁÜ ôñ©¯ÌÎÈÌÖ“¼½Vmktwzut{‰ƒ‹…‚Œ~™³±¯“²š©Ã´É¿ÁÍÜ×Ðã÷Òûèô &-JYMU]X9WWb£{‚´w¯Æ³»Ê¾ëÍ»èôßú$óþ&>A2d3ilf}r_…žœ¡™—ó¾èþ 7ýÿ)R nPQB+A0‰”7²{¥¾ƒ—Š}‡šŸ˜£®ÀÀÁÞÖÛÉ´ÃÑÑíÄßàîÃæ§×ÇÔýîÒÈÁ¨ñèèáù›½Ìø‘s¤¶Œƒ_¿¨dftjfMl@†d(:QL"(Ý-)ê´ùÔãéõň¾Ñ’¦““QapV‹F5U:H ùî×òâÇÙÁ¾¯¢—’hZdasg„mo’}]m‚{œ€¬ ³¶šÂª½Æ·ÏáÜÀÕÇçÐÑÓîä. H17GCLL„jd„…mm†lª«©Ì˜»¬ÙÔµèÜíüùùDUB+/`MmƒpmfgƒÀ‚³əÃåñÌÛÖûÛû!>+#E3VVa ’e=~h–iª†c‚ÒŽŸ y—›œµšæ°êÖìÌËæÅœÐÇèî¼Á‡òÇÅнåÓÚ–…î¨ÆÚÂ’ÛªÁáM¦n³x‘mÀ˜šO’yUeW/€gb4PAM#ÐñÇéÁéÌ䪣¨Ñ™hyzBh9N]6IT/$ùíß ßÐÍÓü ­¯²ÁÒŒWfzj_fqxk‹}†‰™¦†¨œ«—œ•­¿¢§®ÅÁÑÁàØ×îåéû ý&-9/</K<fTQU‰qˆ–©Œª¥—³®»×ËÔååðôÔ!(%#I7\d^VKdvƒwª™£Ä—±­œÙ¿ Õöû8ð8% #LdFF9Fawa^Œm­Éª¡ŽÇ«¨´‘¶œäÏëÁã¡ÃÈÀÅ—…ßżžñâ¿©¯|×ß…¾„·ÀµÉª¡Ìn“†¼ƒ˜”£”ˆxp€ERMO%25&ÿÓóÝÕáüñÊÇÔÃäw¦Ž~pšrl2IRF(ë ÊðæàñÈ©²ÒÀ‡®†pmqehhvaknx‹‹w{~“’£¨›•¦»µ­Á½ØêÚìÞêõÛõø1)' >J")@DH"j3œc]ve „§€™‚–®ñÚÜäõÏ#7;>=K<P^Td_je¯p²£|³œ‰¶ÚÉêàéÄíç4'+_P?J&hVp&>h•±}ƒ^x¡¤Ÿ[¸µyŤإšÎÔêåuÖÇ«¸ÐŽõÉéε¡½³ãÞ|¢ÔÀΩÀ㮨·™ÝŸ…„V–{zhZ‚dFmŠNJ3=;106íò.äñɬÔÔº ÙÈ’¾àŸxmrH]IxD`,+1ð$!Ü÷ÎôßÞÊÊÊÛÀ»°¶°r”X\^f`pstsxv‹Žœv®ŠŽ±–¬­¸¿¯¼¾£¿ÎǾâñáò ôþø +A%7(7;2^X…^xŠˆ–˜f§Ë¯­ÂŸËÄÃÕëóüæÎGï4QB:p„Šy‹p†o£’¤¦¥ÐÔñÇݰßüÛó+&WPi"ofŽUZŠpqqI‡sj˜|‚S„±¢·«¼—¦ÙÄ·¿íÞÊ¢‡¶Áà¿®Á³Œ Ñ–Å®àÍ¥•„¶Š€²Š§r‘‚—¤{p§=†R9A]\Suw=@M*Ýì ßÒ¥ø¼ôŸÖ¼¼¥˜‹XNYTp8VB[2ó )áÌðôý±ãÔÅ«ºª¦–œ®ƒfpe_gnuhd„{”|‚o“—ª”´…±¹ÉÀÎÓÉÖÇØôöìñø &<'C381YHkGCq_eqŸ—³¤œ‡¥©ÙÖÖÝßõ: LbN^gT|t€ÏŠ›«°ŽçºèÝæð Ð4 K;/ZihhvxEh›]ŽsedŠzÆ‚›œŽŠyÉ—‘Ó°‹¼«àÁ¸Ã¦àÝœžÉªÐ÷‹ÙÂÀž«‘ˆŽ²¯¯„º¿{xFZTSŸŽUj?hIR*U3->)åÕÈð²ÑÔšå·Ã±¾¦Ìi@h‚}o=B3$G2:.! çæáÙæÉѲ̩®°ƒ¿€d`^j]t`ut‹qo“š~” š£«¡«Ÿ¦ª¯Â¸®¾ËÀ÷Ûðüò÷óùñþÿþ,7.CG?BDN[^vŽ“§¬›ˆÝ±×¶ÒºûóÎòáúÿ*5V&F:Jj}a€f_«…µÃ•Õ߯ÍÌìäÔéÙ&îÜA(øüA9U?MPUlwt‰Œx\d“yxs‡’¥‹lœ‰‰ˆg‡½¹¥£’¬»»ž‹ž†ñ½ª¬¤‰·»Ãò®ŸÃ½j¢š¡˜’s„XŒZuuˆy.j@w)-">A2%àôößò¿ÝàÑ«ÖÒËŠ¬Ç…~’‘ia_FAeAM&;<ñ'óäí··ãÀ»°¥°¦•mcfRVcaq{dxf`|h–›‹¢¤¦¡·ž¶¡Ã«¾Ð½ÍáÛÒÞèïùû û)%(:û,)fF9wYlioŒs™x°£¾–ëÎÓÖÄæØêéù ô4"R!RlUWT€ŠY‰ˆp¤ŠÉƒÈº¥ÃâÆâèëÝý )6F"DY…=&cN0†dBt²bwgS»~‰Ž‡¡ƒ‰¹¹ª©‘“¶¡¸«žÍÁÌ»€¹ÄÇœØ}žŠY|qhr¹žh`ff©uipK1PA6 KJco?:& ÿíØý÷óÙâÇÂÆð± ÈÇŠ fRP[UJKqX6!3B5 "ÖÔíËÔ ¼¨ª{¢| †TWbZkjbsin†|‚‘Ÿž‡œ˜– ®šÆ³¹½Â»ã¾ØÏÍãöÒÜ÷ ì8 *@5D9AWQ^uBe|oƒ‘ˆ¼ˆÖ¨Ó¾ïéïìùØíæ):.SK.B5vL„}Lu£owˆ¿©¿Óȵ¹ÐÓò§Ë«ë5å8-,ú38AQ]KeGaco¦l¹˜W‚|yŠ®‡´›²Š‡‘rÁºÓÅ––¢êҥά—©›¯Ø ¨¼¥£­i|„Ÿ…rjSZ8]WV-LS2+%,, #)+1êÕÊðƽÇÖœš£»¬ª}NzdŠ’FX4G?,%-öçâÅÑØ¦ºä¸Ï¡¨}‚Ž„r`gS\chWzhys„{€‡§«}™©³«¸¿¬À´ÉáÄÖèêÏÛøê!úæ'#"+ FNDQ`KIhfrtˆ…}¢§Ÿ¯µÎÎÖ³ÄêÚÄÝã ,Aj6u\[^B™ƒŽŽa«¬¿p¨ÂžÊ´¹÷Üñãé+G9,G>*$BLb;T|BTAt_•§˜t{b…—w¿z ®ƒ²œŽ˜Ò›†´Šˆ£³œžš«Õ¬u†g ­©¬†otŽ`~ˆ^‚GC_:4ŸCd /YfOó,÷÷îòìèÁ¨®È½ÄÇ¢pŠ<ŠcšMG,cPV,÷  àúá󼹪›¥™Œu‰{y`SWj\gkfqratt|ww›‡¦‘¸´·¬ÀÀ®ÙÁçäãÓäèâøéã<F;Z f:MUpTwu’l{}ŠÆÊ»«žÚÀÜ×ãóîÚòø,0I€B=]O•€e[™”j¦{—£®²Û³ÌæýüåÒíýÿOB*>7\P>hn­?R}Bƒ¹Tš’‹}…®jŒ‚—Œ°¬À„·I€e|º›‡‘sŸYŸ€h‘Zo­}c@t8kOpKV=YW?eG Q:* æ2â ×éËØ²ÆÈÛ¶ª›™«>‡«yeasl~bP]?2åÿ îôÞôÊÆÇСܯ›·¼°‚œ‹Yhhh[qdklm}{~˜›‘• ‹¼ÂŸ¨´®ÉÑÙºÛòî߯åûôëëúÿ õ!@IAi]HYkl\rn~œ“ªÓ¡°âšÍÂÆØ   <%2Gb,U|poŠkvе”¿º°ª’˜¼žÝÎÃÚÜìù (é=<0G^GB?dow6Hqgv‡ŒlŒqÈj~}ˆ{£•_jR§®¹†‘„igƒžxˆM¡ŠX’šVi•}GSeQ<XaV3UB:E)A3 .)êÁóØËû¤»†ÆŸ¹Ï€r•i•Vgd]Q+H4#4$-0':õÓððݼ¹ØÚ¨µÈ¦œ“ n „v‚uWe_Vmouggrrzwˆ|™“Ž“’±¶™©¡¾¦«ËÊÆ´úÕéåÉûôûô %*"RR[JJqVmw†‡z“¡’¦¹¨±ºãÁ¼âÍìü#å= *5LKBK_`{frog­or{˜ˆ¾ÏÚÖíËÌúÓîòý ÿòBQïÕ7Ipf<aF[4’\a-€\{qwidŸ+bmk”Ÿa’pITq´Ž˜»Õ÷a³|{~uj’/m…ua–3G_DcZ‰P6‡R&u`9(÷û2üõÐôÑÊâ±ïÕá«Ê­™^vh‚;._@MR0>+/ï áܸɯ¿Ô¼Øºˆ¥”‡y¦€p\XS__r\{szw{t}uu‹‡œ‰} £›¨¢²©’ÔÒâ±Æ×ÓÕáóöèþ÷ =7^B+(ZiSiRai‡}^˜¹x®™œ²ØÒÄËåêôýá((#C9E-[YM„aЇލ—§½”ºÌœªëŸñÜøÍñ, ÷-&0--'.M.1W]=/ndƒ‰r€N©k„…vwsT|Ч„Žhoh¢}•ƒ€“L[q&H}g’>AX=Q"3$r0(M=v÷!áãä2Kèï´Á­èįϸ«„…È©”™ šsvt8<:3bV/;è4ôíùèÁåìÕÕÕŸÇÄ͇‰™n‹fn@XWXi]^`Zrd{…}“|‚Ž…—ª˜“™°®¦Åȵ°×ÂÉÔÉÜÔä÷òøì";!22@X?a]ZNŒqjm……p‘§Å¶ÀßÑÎÉ øÞÚÓûF>&EZ*U?[ip\eQS¿™nž‹ÅƨÙ¿ØèÜù  Ù!%5+RADvoB.52(1[kN7ta‚`dvºUTšf‘u~e…Ž–€]EplWxPƒA~^Zpcm/muK<A<!!&&ë*ãðûÀæÖȾÝûɛҕЗĒw˜mZ‹uXV;S(37ç-ÔÿáöÛÑ­Ä©´½«Â±º‡mY}oeoKac^Z`qpjbkwsŒ‹ou“‘Ž–”—µ“º¡¤Î½·ÎÙÒÐìÈúÙãë÷áûøý)))" 7VJfˆHEt‹`•~™ž´s–¨¡ÎÏÑÏ»×êçû ýñ.C*=U_|fWI‡tpv¿Š‹¦¯Ã»¾Þ£¿¾Õñ ûÿ þì63F^/=#G2^KWN[Pƒ…uMMkxUcpKp‚sS¡„Jy‡›@}d‚‰f\1zMWKUg?n$\T1\,9)3-RT# ñêò øÈíÙ‹‚¼Ï¬¤–Ķ¥†—v…U~\yS]AN$&6Då÷èÛçüɹÅÊÁ­‹’Ř­”kgshqMMQSjlcmephbx†ƒ‰Š†•¢™¡Àª¯®³ÆÐãÇÄÙÉ÷Üëëæâåñ"#:L?@)G(:Fbc_E\di]™ƒ™“£´®¯¥ÑÇÑä×ãÐ7æ!ü&E>1-cP:x_j‘‰ŠÌ• É¤ž¢ÎÈâÍßÎÙÝàÊÒô,Ü)93BD2<@%BmV)&DGvook‡Dcyda0js783E0JJeECbGa[P5pLWSL+;9<Z(5!2 ÞéôóþÀýóæÃÆÌÑʹ¥¢Œ±‘~”_…ˆnŽQ4QLG5Dü 3ù-3öæÊçÙ½×­§–Ê~޶Œ†^sMKST\_^\toe{‡€k„’”ŽœŽ–˜¢¨«ÁžÁ°Á¾ÍØÖïÛÒíãóá ëù2+(;9>QGNSQiq„kuŒz¡µ›c ¨‹Ø´ÀÊÌáÇêÝ .(]úCP/Bjj†vw¡o†y˜–¦µŽ¼ÑžéÓÃÆøÍÈÓæ÷÷æõ B-#P<q(7M8mÿ\X!GS32e`D\¤jceFAfwŠ;xWI{IIXo\eUe3Y&09êh82B#ëw'*ùô1"Ûü¸Ïçêáà´Ìû·Ÿ” ‘rw|ažp7I€"GNGiF8:ß­ÍçéÒ¿ç¼Áʘ©®{y¤ˆmZ>`QUaWZCZgWd`ukkqvzxq‹„§ ¥®½¨º°¿×ʼ½´ÒÔ¾ÕêÝíÓÞ  486 I0VE*UdI]‘}š{~u¡À¢ÁÀ·¿ØØ¬çÙ÷ìëå(&ï5)J+7-=hitz‡HšŠ»’´”»¹¦ÆÜ“ÿ¹ýèìÜëõ÷')ð(2SVf6e^BBT>b<AakkC[bŠjrJ)=KA=9xT+*@. \a,üW0 0ÐáîáÝþºÌÖÔΟ¨ØÐLJ¬¨´¿–§nŒhf=n8y>OG$>%öæõêäÅï´ÊÈܽ­ž ·¢ˆ’‹iai\–kXWdX^QeYpbnmxˆn‹}€Œž‹¡¡ž£¢¢¹³¿ÀÈ»´éÚÜÞÛñýóô/&2*)5);@EQVZetˆan`»|­¼§¤ÒÁŸÈ¹åõãÒ#" &>6G*3[‚YUom‡žvru‰—²ß³ÌÇ׫öÜãØöòîÿ'4'&A!8G\@&m51bq<+'3:r3C-m7_E:c_)V+=7_GM@ô  1E^ þ&ÀíÞ)çåîÈͿ׌Ɣ¦œœŽknj’h™†v[G_?O52 ôúü)éù¹ÏǼîÈÀµŽ¤¼ª‹–|ss†]vu[jGW\j_f[Syrgkk~{‹‰‚‡Ÿ“ «²ŒÌ­ÀȬ¼ÊÄÈÚåÞíÅöç0×ôý( ñ+<;*S>WiUq_d–n†oÜm´ºªØµáÓçó÷ýþþûøQ8GQwSƒe8J¹¯ƒ™w®–Ÿ­ØÊàØ®ð½ÔËéäÓ!ë'B+!)8!BK)&84C:!E!K1#1=LD.?eWQQ_IL/:'(/ "ìÿ3 ñãÞçøùø×æÐéÐé¶ÚØä¿‹­¤¤’§ª£™Ž}<s‰1]*‡K?1 8ç'ýýçäÊÀÁÆÕ§—©¾¯Å½–¢Œ{„‚lfZ[WWGYPXOVVWc`nxk†…†ƒ“ˆ‰”Œ¬›‰®«¸¸¤²²ÄÃÂÑÚÊØÇûÝçô ,,# F-@-E`Fp††[‡‰}x‰ª›¦äÁçÏÇéÖÏüôèÔ ò I ;Y>E_8BQ¦mmk—q‘|š¼—¯¨Ñ‘‰ä“ÌÖ¾ì± äïé!ïýZ ÿý 1÷EB)C7*ALZ1d(N%WJ 5C&XE<.%@ûÒ# 'ÿÚÿõüöÊÖßÇÛäâͱӗ“}Å~jtŠm~ab_PmHZ<:5"7 "êÚÝùíú¡ÄÖ¢±¬‰¹–‹“m†s‡Xp/i.B?OU[^dUXi``j}w…w}l~®ƒ¦…£¬±«°­©¸ËÇÁÔÈÛïÞîåðýúêî ) =&>.CEoLvvi€™«ƒŒ–·¬™ÃÜëÂÈÖïè ùM#4?8GRZwJ`™š‘¸ ®Ïšv·u¸Íœ»ÖëÉúº êè(ùìüß  ?èñ ÷T+ +%ø]0ú;U&GD8?" :+ %ùÎÇûüüþèÊ÷×êäÑÙËÄâ⫝̸ï½v£™—¬Ët†f_5|s[]J`^:*løüñèðûçÙÅɯܛӴ‡ºªš‡„…hd[^\`ItNSlRN^a`Qtnpiyrxny}nŠŠ”‚±“¡’­° °·È¶ÐÔ×ÐæÛøÌõøíü#,B!<<J0=<XVuao›ox·‡¡«Œ³·×ÉžãÃæî·ÍÖ  5 ó- /_?i%n^uZWNyeš|X“q¥œ­™¬ÏÄï–¾ÇËÀèØæõé!«ÒÜåà!ò*')F ('*ø!E*%'6BHý Þ'ò*Lúñá,×ïé>ÏÅÔñ¾áõÅÖ«àǼ¼›—‡ˆ³›xuŒZXz|2B4xýÿ&OæñûúíÈáÓ½ÈÀ°™§´—ŒÑˆ†Ÿ‘ƒprcqI<M2lhCV`ThUk[\`Por^vn|vˆy•v‰ ªŸ›À¯¹Ä°¦¾°ÛãÆÂÕåòþí! ;3"dHB+K::~[td‚`’n®„®‹®©ÎÑÌ»½àÆÆÙìëô ý 5*&GCh8;FlX£bÆ”Ÿˆ`¡˜ˆ­Ê»‡½ê¬Ý®ÎÞ÷Òåñ-êÍÍå -æ  +) ú$ì"= ê&2ûûÙéûâÊâéçàððÂ۷뤦°ŸÄ¼±}Ÿº€vƒƒ¡‰QBkLWR ]#.MI3þ"ÚúóµÓÞÅѳžŸ˜œ–…uˆ[e_tgWRMZ8OXJ^W\hjnhlgif†dyk“}z†}Ž–†‡–­£¡²¼¡¹¿±ÃÎÌàÕÈòÆÖÌÙâ- !+0=MT\AOUktUu˜†—b¨Ÿ‹½¤âÊ»ªÛàñ¼ÕöÀ÷â úÿ+).j B.F_9~fo€~„eQŽ”˜¦—´¶‹Ï“Á·¼—ÌæÌ­ÖËÔåÀ»ç1ï¹ýõï $@ã,îýÿ1éâ ,O1öúê¹ôÝäøËÞÎØ÷Üóë÷žËªÅɸ…Ï¿»§¼‹x—Ÿ”ƒQjRQ1/d7xG#ößÿâùê¿ ÞõÒ¯°¶Ðë …n¢¹|}ZzwEW=dNMfYKMSM_Q^\gZWzRs|vbƒ}‘‚“yvŸ¢™–œ—œ¯ª´ÀµÍÑÐÐßÑß÷Õëûâìû  ED&G07^>:YH[KQ\މjŒ–”¨}¹³£vµ äÜÎÂñÌÕ îåH4\o_W{~u„y¬‰v•…¥`¦h©¥¢†£…Å«³Ã²Ù’ØóÊíæ¬ÐáíÀì)ã èþ½ñþ÷7 ñþèû÷ÝúðüÖØÈÖ±£Û°ê÷¢Ñš¤ÂƒÄn­˜¬e®“—‹t|p8…kpY,iT>E!þFöâãÔÏÆÙÙÑÃÏºŽŸœ€’¯vwduhAHcfA0AQ=IGSNDJYbUh]eqdlqusy}~~““”‡«­¥¯Ê¦¼¾°ÂÎãÆçØéëáãéùû ö@*90HB[EU;fugCn‘‹™¢š—‘ŸŸ¸±ÀÆÇÉìÔç÷ Ó"ç/%9L*&GIibUmxu•‹yvŽv’y¯±¥¤™›£ù±âÌÊÛ´åáÁÓÛ·ÉéßÜßîÛÉÌØÌÓë'ÑÅ äÛ÷ï½åãÿûÒõçµý¶á¦£½»ÜÅÕ¾¹Œ•²¥º¬‹Œ‚Š£wzMz„hz^_<T445*$/: ïÝ,óôïíεÓÛ½Ú±Á¨¡Œ¨Ø‘g{ybb‡msgvU_;49JMPGJJrhO_Mz[[jqth|{‘‘Œ…™Œ«˜…ާ°Á³µ´Ñ±òÉ×ÌßÈèíòüþðùü 0)2-1N BAx\Q†Vlqq™„–¦“œ—¦ÍȾÒð«Ý´öÞëîå#ü<ùB*$3>ŽX=Gtw`vƒCˆj‚–mƒŠºÊ„œ€ºÂÒ©±ÖÆåʧÁ˾®ÇÑÅòãòþÿéõÁÛÛç÷ÿØ÷ééÈÆÏÓùûȨáÁµÕ½Þ½ÉùÌŸÂÀÃ_•¨²Ñ’ǰɃ¤˜?l‹œfa`Y]CqG54Y$H@ 8$ùÚ áòÚɸ±Â¯Œ²×¸Ã†²}–vz…|o`n9gZW/'-*L\PVHI:[UZh^d~snoxmxiz‹x“˜˜œŒ›¼«œª¶ÑºËÒÔÁÙÑÛÍ÷ïåñø êþ )$7 0<-?oY8mX\pSNkw‹¨ˆ°¡Ã¸¢¿«Ï·çÁúÃÙð 'â,n3:FTB]TCUboxIOlIE´žKznhªÔ“Ðò”´¹¹¦Ì¢©åíÝéê¾×½ÂÈ–ÝÃÖöôÝÂâ¸Ööñ»Øß©ûðù¿ÑÕÑ«½¤—ª­Þ¯•›•¯“š‹„€b†ShskAocL9DFC?D  éâÍïóäðúÐì¶áÊ鲺©§”•yostJ_zUPM)$&)<4P?XVSQ]QXggiV`bpk}vf„†rŠiŠ–†Žž‘š¬š”ª¸¢ÄÈÃá²ÝÉó¼òÎêåâëüÿ%571+:I6WWB^oXm\z…”ˆ¡—£‰¤¿¶ì×ÔÙïôØÞòà726 .39*D?<Y^Oa>v1EeMŒtxul…ƒœ©Œ³w¡éÂ’ÊѤɗԴÑɶÄÜݸîÇܧöïËØµø”ÎÀÁ¾âÔȵưËÎËÂÂÉ⎆„•¼¢n’‡|Œ§n||*QIC?3 j;:b<1&ÿéÑçìþïÁÁ¥ÙÁ­Æ±¿¥«±›d„g^~w•vSJYBS-V5+2S\>Y]O[^g]bhcValq{‚p†sj‚‡–…’”Ѝ¢¨±±º ½µ²©ÍÓÃàÒÚÌðáýêóûõ# 0#8B!BB<9=l3Rf>_[nnš“o£u¬«ÈÚĹ˜ÖÛâÂíãý# @ö2; &B3yXhR‚jbPaŒYoÊ^ƒi“Œ}ž†ºŠ¨ž›Ö¶É»Ö¢à£—³ªÜÐÊǾ·­ËÒ«“³ÚÙÐÛ¡ª»ºªËµ©¾Î—™˜¯”©µ—Žzµ™x˜‚Šb‚o¥NfWDEdJ+EC!ú$ÖöþÜÕÊûØÕɾ·ÁÀç´ª·¡¤©…ª{tŸ`ijo>`?Fe]_85-8MLWVMT_TRXMV^hadxowys†rŠ‹‰ŽtŒ ‘©—³¬¸¬ª·É¹ÌØÆÍÔÓáÒàõ ó20õ<A9'*Z]3jyU|†p„r³‘‰y™‘©ƒ½»Ð³Øàîèöð èó2!(4)!!66)5uTRu†t†uH€§”X—‡‹™‡ªy°¬¬¸Ÿ’λ®§À«Ü”¬±á­Ë •ê˜Ð›ª«µ}µñè¬Ð ©·s¼~¼Œ™«¿œ£f€R„œ[?q9v„^kSLCV#2’7M#M/#2î $ýÿöó×ÙÒòÎõ¿§å¨†´œz†“’wŽ€p†cOajRV4DF:X8 -)4QK9YFSK^U\YUdk_tpnjwi}{„|}u†œ’¨¤Š©œ¥Ã¯±­ÅÑ×¼ÓàÈßßçþé úî +øB2(2ECYS^eNvrzLr\†™z¿ªÙÏ­²ÇæÀÒÍóéøÝó>#%J)(8VS).YQ\=[qXpT}€cuqËËl©€{„Ÿ¨‚Ì·½ªŽ¬¨¤Õµ¢œ±š¯¾Ÿ¶Ô‹±¬™·Äµ‹†’º§ž•€v©£¨OmtM˜šUsr]asQ‹cU\3;I61'!0%%ùÝü÷¾âçÄäÊà˰ »ÐÕ¹‰©„…pƒ¤f™_‡]_\cS_S4C84&0&QAED@ITVSeW`^^\hei{lnpo‹ts}pŒ“}˜“ާªšŸ²¯¬ÐµÀ°ÖÚÜÒÉãí÷âøîîðñ'$=%CSNi=YVbf‚giw…~z°“•n¥«¼¬É¼¼¶ÌðïÐñöø%&2-2*"4!3he6\Sp[ep^p„o€gg{`˜|ŸÅŒŒ¥ž ®Ÿ›¬¦¥™± x|€¼±Äº³§{¨¥ªc¨wpޤ`«{n¤dŸ‹m€}mFt<†WRq4¡SZig5;$,þ´ ïØÝáÑÊÏìÕ¶®½¢¢²À ˆ~‹‰mwb‚qY[P-KQ3h3X +@FHB<TR@EcPOd_^Zfrytegiixzz”†…y®£›¶¨¡œ±¾š±©ËϼââÛØÙÜÜæïíÝÿþí#(!D\GXMNbX`VCftˆXU“ƒ¡‚Â§ŽµºÀ«ÂÂÒÄÑ·ûèëüÕïíú/C#6DWdC6?Mh[$Ao5ZG^j_SdŒ|‰zxwrl¥‹t~m†˜¬›œ‰¨ŸÊšlC~ެ£\|yk•‰•k’Œ‡€uQ[wviLCfb{HIOHfU0N<,6+ )òèîéâÁÆßÖ¸àÍÞ…Ù|akŽ¢Œ²“ŽmsBZea5`L2K555 08' &CI?9OL5UU\KV`J\h^lfvajfw„z}Œ……—­”•­£§¹¼ÏºÇ©Þ½Ç°ÌÐØðÚÇ×øþâþö %./-*05RVpmof^mapŽˆ€s±±ÀŸ³ÇžÊÈÛüÿæÏÜæøöúèëõÔ% :%!LH00B44YN/p‘fOM<Œ^[{_£W¤o‡…½f»‰Œ˜˜£‰‹¢¹ŠoN§£¦’|]¼ƒ]ƒ]khk~Sf„fDR=N6$> õ '&ñöè÷ïÜä¸ìÃÅ֥λÀÇš}¢{{~‡•ŒˆFqFgXM540<)"$:!(#(!C@GNM@[PN9[Yffg^^jmaazxrgw†pvœxŽ„˜§¥ž²¥µÎ£Á±ÌÎÊÙÐÔÆÆÍÑàõèôéÞ )?;3=CH6"\3MEYYu}SjxŸvv{„¼ÄÔ»ÒÃŒÁßÖÏôêçüè÷ è àEIJL&.>O*CS5ETH=nh\JŒm}…‘i]…y…vlqpm £‡~W~£UeŠlaq’y„x`xlWkUx}qlfJSHK^8ZU2Mm*F9/þ,öýî ÝãïääÔôËÞ®Û~¸Ÿ±¿œ¥Š‘˜v…^ƒ}sn^WGF_7@/B7=%&%ýCI?>E;OGLLKYYkUMfUS|yojr~z‰o‡u•ƒ›x„¦˜ ˜›¡² œá¶ÚÄÙÒÈÎèÁêã÷çÿûàó  !D2$)>Xzde;D_]eŒ}UŠz¹‡™‘µ«Æžš­Û©ìÛàÞ²ðòÀüµôî ç>A>Q+")B/ EGTO^GI\kLIbln>b|wKXpHˆRe\e_cFx…Aa6k_<]vgp[jRYdQxDDYZ@S?G<K1.D:ß;#èÿýßÜ×éëØ×ή»¿§­±Âw¦š¦‘yJh{aWTxN>s?kIR!21 ê  3:@D=IJD[@F`c][YX[mYgj^}msp‡z‹ˆ”‹‹ƒ¤ –’›“±¨¢¹¼ÑÏÇÇÓØàÄ×ÊÑàýöï÷  ,),30.F>TBX^Du^]—u‡qŒsxˆ…¨ ¬œ¬Î¹ñ¾Õº¿×ÚÑÍêö #Ø 7&8(G>SWoBJ=N#Y+9d€^T`\LagsYDX}_?VNjwx^VW`fg‹`_s?|b9+:,`/lP#J0=0N%4# 90#íì"ú÷ôòöÀæÉÅ仿ìÓ¨ ‚¾Ä±œnyuŠ‚XIeJnLo;O:4*/1/ *þÿúA8>:B8;EUVKSPTYXH_`_sZZq|ƒt‰h…Ž‚’}š“‘®¦ª­°œ§³µ¹©·ÅÄàêìëêðçßïõî ñ  $51>,/.d6?HUqXXS]E[\¨•† r¦›®ºÌÌ¢ƒÙÇ˽÷´ìÈÐðÛåë8 ô 6[#>-1?Ad)C$SgWaBOxJu>mUJ2F^_6Yj{]a_+Rp?vKvaZeQI"EU]%231<@/7ñ&óíò èúòæŸìççÕØ·²±´©”¿’Õ‡²¢y|]hv‰aZ^DWX;FD@:0M'&ûë÷óô:/-?N776R=GNJXB[Slwle^di[iwn†~vˆ{’w”…˜™‰¸º·¼º³Ó×ÓÓâ·ºÖÚÒÁáïòÿøëû+7#B(*HIlOZh6qrO†—•p€Œ}r–wŸ¡¥‘ÈĸØÃ¡ÊÔßÉÜÑÀÕûÜæú÷ø0)6 /=  *![3V2MH) Z?awU IBJE`VL1f4W2%/L:c.Y_+.GKV1&!O'#"/ñòÿ ñìöôÿôØÝÁÛÍØÑÑóÌÁ±§ºÄ·§”v…†adc`j;UqG6C9*4&.(üì(â øëå22:6$7MD;==RHWUWWZXY]^bfSjuwn{†}zq˜‡›—Žœ›´–œ¬ª¸®¶©ÐͽÎÚÕÍçïáéþúðþ÷ %%9 ;<U8|U`wfytgu—º{ˆ‰˜š·q»£“¼¾¤Žº½ÔæÇ ÔøúÓøöû5ü"ü(U+;++<=^#%U<85F@SI*+7E~?A[T5.7(?(%'00M8*ý  ,'21# îAùúåã Æ¾ÈìÎÊÖ¯¦ÖÊÉÉ®´¤—£Ÿ h‰»€gGmbaRXIs2VRQ7-9E,  < òø÷ýô×.A:IMDHI6KEP[C^OQYOoe`h|Vkqt‰n|v}i|‰Ž’¢’£˜ž¬²¤±¬¿­®Å¤ÞÇÜâÌÙèéÝ üßïù /" <.'GII7J=JNdfks\uHy“‰hš—†w¡· ´¨Ì±¿¶¯»Þæ½âÜòì÷âþç  Èî1î$=H')))  $L6O'82"?3Q0s=H>4@D..6\):-8@ N.#ö.ç,è÷õâáòøë ìÚþÈÀÆä¸Ãްͨ¤º¢²¥‰”†“–jv‘rFtpK`Oo=MU@I;4,(Jññëäüìã78@@>KLEFHANJ[UULjUZby_a|fyZel|v|ƒvƒˆŽœœ•¿·¨¢Æª·ÙÈÊÁËÊíæÖÚòáÊðïýêü>3<-E>"%K5G;4RSeZ„`k}›|o”v‡˜Ÿ‹Ô®ÁÄÊÕ¨ÐÓÄÉêìÛÓÖÛÃïïõÆ/ ôûô! ) 3òÿÿ/2:8B$$ "&í+.+(7,-') ñ÷UîòêíÅóøÃÚí×ã¼ýÖÌ´×Ç¿¹À­›˜¸»˜§{¯Í³† oVY{JP~ƒ*J9UOBG(4üýòÿíøæêÔàç5<+F4<V<QJIBFP@NUXYNZYhe\`scih`{|mtwtz’š¢Œ£¦ ™¨Ÿ³ÃÏÌ·¾¼ÌÅ¿ÏÅÜãÊßçùöþ67 '+*D?K[{>Y^FiDhig€rS’v€˜§Ÿž¨Ç ¤¨¤£´¸ÚÊËÒí·ÝÐàÈÓÄùôÊó ë'":   $") 4*P##,C!  ñ 5 è*ËýÜêöðÙÛÑèáÒ¸ÃßÑÔÆ©»Œ’©²©Ÿš’”t¦˜iufLmqZRomXgMXF'H)1:() ïéöÿùáöíæá847@47G@IL>AGNQJV]\`TZ\NiriWftx|~e†x‚|Šƒž•Ž”¨Â·¤¹Àª±¶¼Áâ¾ÛÒæçÚÞâñÛëúþßóøþî)<&'.JI )3U4;t6ZMayZ_gu‚¢ˆVއŽqȽĨ˜´­º©¯Ø½Ãêá»ðÍ¿úÓçÖëí öðùÿùÿ Óþ2 ÷7ò*îøùúõþ%Þ÷þ óöùøÕùäôú×ϾßÅÎé›Ö¼ÏÅ´°é«ÎŰ¥¦Ï“ˆ¨ƒ˜¹c•šrM]cbSdkq\cQ @<04:3üÿýòïõèêåÞÙ8)H=+6/7G=<FD<LQS>WfTUP[fNihkmwnƒŠyj‡…†‡Œ¸œ‹•‡¬·¹ª¨¨··ÉׯÑÜÏÈÝíÖìøáù÷ýûú-D+B]O=[=hP?uvp`nWaeƒ\„™”˜²§¨˜‘Ë»Óɯ‘¸ØÇÐÂÅתæÉïÛðÏÚÞòòî÷¾ÕîÁçòðÕÖA÷óåú$ 'ôú ÿáá÷ÌïáÞáêöÚÞöïæ ÑßËáíÉÃÃÆ£ôÄ·ËË»•›Ì——‘’›…Œ¬ƒNƒgagbO_bY7>"=N? ; <(÷ úí(ìñóêåèèÕÚÝ05041895@:FQ<;iLLGWYW[dJP`kahomYsrtƒ€|“Œ…~{ެ“©›»¹³­·È²¸ÄÓÖÁËÍÙãÃêߨýêóðõû 5/-1*>HSS:q=JJHUŒvs…yon›„š|ж°€Ž‰™©·›–¤¦£ÜÄÚ¬ð¬Íõ³êåÐäÌôùòÕÒôïñôÌúâû%õúë ûûÈÛ¿äæÝéþ ïçäéíרëöÖëèóÔâÍÛ–¬Ç¾§ºÁΫ§¨’¢‘‘œ«f|Ž\jcŽ|z:‹cip\1J<0[K@&& )ýüñìÚæߨòáñÑÍÖ,330B<5K?C=:=CDD6ORPF_V`[lhh`Ono€|pni…y}‚x‹›‰Ž–®®œ¬°´·±¿ÃËáÁ××âÛóôÒØùôþÜ!3+52*:/FHFDQKaSYYhŠ™Xdh`ˆ‰Šˆ¯‘°Ê¨ž€‹€¶¦‰Ë¥ÂÙÅÖèֲ⤢¾óÎö½ÞÛñøñäØ×ìèÊÔçÞ&ßí+ÝåÎë©ÜçþêÑÄÚ×ÂÏÒöýÕãû½êäà¿ÑزÞÇіƳÍÒÒ££x£Ä†ª“rwz’„d}„o’cf}[^‡AGbSKCBCR&%K) 0ÿ÷áñõùûñÞØÊíÐÐÀÙÝ:+725AA6A@5?OEI`UNQGV^YPY^jYZYdoqoU|~„ƒŠ†ˆ‡ŠŸˆŒš’–§¤À­–¨·¾¯ÃÏÎÙÌÚÈÓÓÖÚ íî ßä û &1$-0F!:;d1`D.bNGg?tcbC€—lŠfo²†|~šmž”¶ËƒÊµÛÛØÃÇ«­Ï° ÔáÎÏÓçÎоÕÑÆØø¿æÿÞ%õ òÏÊòÌíßòÖÔÏìϸÖãÍ¿¤·¼ÒÖ½à¿ÊÕ»¼ÅÌ’¶Óª™Û•”ˆ¥‹˜š|x|]„ogauON|qKG?KiGVP9HI+(þ õ"ù  éÞàãæ»âçËÔȹº04;0C0.878-?5GNEHH;OMQOYbiWepdd`fpyrlqd‰m‚‡‡’…Š™œ—Ÿ¸¸¹ª§Ã¯¾Æª¶Í¾ÌíÒäÈÌÜÿß÷äüÿ ÿ þ&7:# .CHEDFSXS?QhYWt|XXw”™|oi†ªuÁ‡—”šÁޱê¹·Ò¿¾ßײ—ý¼Ó»³Þ ëÅ®ÊËò¨ÍÔ¸²ßè×»Ô¼±ÃÃâã÷ÜÕØ“ÑÑ̿ӱ¯Õ¯®±Ð´¢­¼‹‚œµŸy£©»†¸~€w°žs]‚}aR`nUCh~eACM,74O2# & øÿôßý÷êçòÕÕÑââìÙÄÛÓ³½%+070(;24DB::D=<HFJKTOP`^OLnUKQfQhuhzjpƒ……†€„“†Ÿš’ ¤«°»´¦Ó¹¨Ã¿ÀÛÇÐæÎøåáÜÜÏêòà ðþ  :( -E,K:/U;q[fY_SepNPk¥€j«fšy™q¢µ˜¥›°¼¬¯ºÃ£¸µÀšª¦Äݱ²¼ Ê­µÁÀÏÖÙ¬ÂáÔÚéÅÎÜÔÿ´µêÊIJ§«©¡¸¯ß¬™ ¼­¸·§Æš§y›y“•u‘|x[pi€zZtOiia9SAI13>5'7=/- øõúþôóõîëéÖáàäÆÖÚÃϬӢ.3(,8H43388957HDGATIOgSKhUZMbW^h^g{d~dojvm…uŒ‡–•–†’{¤¬™±¿½¬µÅ§ÁÂļ̽ÐßàâÓÄÕúÛ÷ï  " /++%AI6RAcY[RZEncl\m]…oˆtYœŽjœ—{žŸŸŸª’¹¥¸¢¦{®¦ ¥È¢´Ò뫧ð̦¿éÁÑ£ÎÐÁ¶ÍÄŽêÅßÁ¹Â‹·—Á¹¤£´Éª¤¼›±{‹•¶¥›š¨V–y¤mv…‹m}xftYSvqiQJS^?c=C<N95"ð#2   òïü÷èþçâÄÞÞãçÌÄÄÀÝÖ½ÀÍ»+(,!1:/5;<08-?:@<LI<QQCXVSKU]XZfh]divpa[wdtuu”†rz€˜±Ž‡¸Ÿ¡¦¤°¹Ô±°Ã¼ÖÎϹÁ×Úçîú÷çêäíá% ûB/1+%.?AFGk@GdHVeOXdxh_nR€—€~Œ™“‚—€“­›Ã¼•í²¡¹³–…石»Ý¹®¶»¬¾ÆïäžÊËØÅ¯¥¿®Ã”ª¡”§³•y½ ²§…‡£Vd‡q‹eƒ_j€uiU`la`u1yTNso>]MI5O74'# #öþï éðéßèáääÒÖÌÞ˸ÊζƤ(*,%7:6+32:7=C<5@4N@6KITOK\chKQdec]gehkoru‹|Š„‰…‘ˆ •š¤œ±º«µºªÅ½Ë¿ÎÚàÜÂÔÇÜýìÙçôð  ÿ'  337* MR4cNH-QZAkP‰Wrt…|FE•ƒsUˆ“gu”‘p¢¨|…œn„„À¶ÁˆÆœŸ–¯ÌšÔ¼½‘œñ»•ªµÄž‡§­§¡¢±ºŸ£­›¨‚›”މŽ~˜‡€’ˆŽcbi„‰hMm}XShQ_ImI>5UG=A+ =06@-;9ø # øßçÖéðçÙáóäÄØÌÇཫ¯¨ª¦ªª®73#/.#,(6><,=B30D=J?BICHHRLRFJ[Q[iflmml^aoq}i–z€ˆ’ ‚Š‹‰Ž«¹œ²´´³ª¯Øµ½ÈïÏÏ·ÏÌÔÌíîÚÝêçôäóú þú,-.&<HG5!3/;F=%6JHˆHV[^Rq/mYdIdkb µ~nv˜{‰ˆŸŒ ’–žmŽ´·ž¡­™}~£«˜—†‰‘v°‘’ˆ“¢™ˆœp€ž””u”€„¢‰¦xZ~¤qW_fdtsUZFWJRNGhY\F#1APK .L.$þ8 ôø øîìñéðëáÓÉõèÊêÆÍĵ̶ª¥¾»¾%&'5-+619@870;;C46N9CWMCJPVRXRRPYZSan_c`mxy…zˆ†t‡’†— ‚¶£—¼ª¬ÀÎËÆ­¹ÐλÀâåÒÜÌÓìöáéíõð ' &4#L)0R2;b6BOHVIMT]YKzZ]YQfuyigjj‘{wž›€||ˆj¡ƒ–¸¿’”¾t•Àu–y›®¡˜”š‘v„‹ƒc‚u|y„t{„‹~]gth†Rq‹gmqMUp7jPYM^?g4**$,2&9&6;# 6E1&ú÷×ë øæåáóüÀÔÊÃÎÖÉÇÈ›«¼º®£¸•¸''*.$A'.;52!8:@9;E>?7VFH@MYSOTPQW[VYjdggeawfmig~{‹y†n…†§r’µ¢’‹‚›¥·««µÍ¯Ç¯ÒÁÌÒÉåãåüÙþïêøäßýú 3 ÷ ,B1H1,*\W=7AF`DZ7F8QSaaiH‰Ov\sy›qflko~…]yƒ˜‘¯‹§•§^‡œ˜yr½‘‡›Š•eq…ƒ¸xS……‡Ÿobz]€dnWkngQsLm^h:GX`qy98PISX/<^0D7A,B"?ÿú(7ÿÛÿ êìïáúÜåûéè±ÞØÉµÈ¿¹·ª¦Š™¸¡ª™¤ -:0"1(=92:6=>64;@I=5QV@ANONUUOAUgcmn_oanp\mfszl‚Ž–‚Œ®”›‰¡£Œ«²²«´¿°Ÿ¼ÉžÄ¾ßÖëëñèèÔ÷÷èíìîçô ó "'%/2>3$.-<C81:9+QF)cA;7e]VuYgJYfˆbV„}¨kv‹¢’qr¡¬‚—wz_Wwƒwu„Ž‚sœy{oˆtY^vQaQ}wZp‹wŠ}\tIUnanaO`I_(Pv(HDL??#FB::.=9 ÿúîõþòÒúñôçÉÖáÜп»ÖßÈÒ¯ÊÂȱº®ª¿¬®Žª›'!$2!)1*79-(4?H<9B6=B4;F=EEMNSL\;O\E]d^_qwdki`yp{ŒŠwsw’ˆ‹ž¤Œ”–™¸´º»¸ÇË˸¼¦Ô­ËIJáæÙÔðåúûã÷êì÷ëú #/. -77=3OB+ F6;J>FLga"=[cTW]WZ^i^N]Srgcxv•AW_X~ž]l†honQci‚@mzg„bj^Wbijgci`UmGreVZgbcQMLLC@]'?42:1NE#)."#) ü áèêùÜôÐØÝÎäÚÔÐÔ¿¤™ÂÀĹȨ²¸³¢³¦…"()*4&+($(;5,-1<7B5E>7:6<JAAVVCPSKYQ]\[aiasQd[jpqcm„”…vŸ††}™£‚£‰±²§²´¹¾®¸·È½ÑµÕïèÐÛÒÕïÞÞìçÆÕö  ÿ+ûú4?NA>-A@2CN+PGU? Kn_W=]o8[ƒwHU[lk^OF>^wMnQuemeU]kPZk]p^{Œjm]dasVPhy\Ud{ixO.A]pD,0PQ%7789/ 5,<!1ýõüñþ ìñôÏÚÛÙàÅÅ㿺ÚͰÔÃ̵Ϧž–ž´•¦ ¶—«‚Œ(#"+$*.$),.**350(1:.?,=2K<ID<OKFELGSOHGta[\gYp\o|v‰ƒhzrytq~‰Š—‡‹… ž–ž¤“Å·¦ª¼ÔÑ¢Ö©Ö´á¿ßÏÉàÞÞÝïÕÎáâñïÖíþ(9(I+.S7:F@3W5KbC*JD?XMs`STUUSlXMN7e`Z}0mCk\b]OpCGPePH\Sb8M][PljVeHfQ>GB<=:H31,(<f."&G@13*(% ! äúøúçìïäèÛÒòæÞë×¹¸Ù­ÆÀئ»º³£¶ž§Ÿœª›“”ŒŽŽ)"$&(+,.>11651977=478A<FQM?HLL;VbH[VYRfhek]ge~nuom…~uw„—|‹–ƒ‹˜•²®•¢¨ ³¢³£À«¸Á¿´ÄÓ¿âÙ×àÓõÕÄÉäØúâÞõðùøýö07(4+8V(<;'3.M3#d5?ACYAhOJL>A8\SIM^YjIYnV2RSejOaKFeCeYegBS=HCK9=9V^5 5-^GL"$'"E.+&  5&û # "' $ðóðëóÝìïÒçÓÚëëØâÔ¹ÔÄ;ͺ®Ä²»•º•º¨˜™Š“Œ•ˆ#"*##$&-!,)/?+-(3:-@9:6?E?JMMJMM?EKMQQK]XhVg`aoeng[w‹x‚„lƒ‘„ƒˆ†•ŸŠ¢œ™œ—©œ±·½«µ§ÍžºÌ½ØÁ¹ÍØ×áÚ×é×áäôþîå   ÿ+ûF!<64&:66,",>'JH@A<B$:>8Z*e6‘HM\4CRU99PO0H>W\7$9;9@4F)<ESC<8=0H?PBB/+$L' ,.1"õòññäûîäðñàéïüÔÞéÜÏÊ»à¾Ç¬¾Àûռæ«À¥¦Ÿ•°””§˜”†”“†*!%'+1/41+441264;>CBB6C5JF6DFC[E`HM\\enXW`s~yfnv€yjsx~ovsv”’‹”£º–•¢¢µ¶Ð˜ªŸ·ÈÁµÁ´½¹ãÎÝÊéÉëãÔñÞèìáó÷÷ð öï ù"3 $6I*2,3%1<+8-3!+&,'3VqCO3Q?6b?DOI>KY@L*8%:4+(+Q8'=(D7(7*.OJ,(*K-$ %úÿôó÷úèëëòØñâÖÝÝÆâÀîÈßÚÄÉÕ¿½³ÒЧ¹¨¸±¨Ÿ¡‘—‘ª ’—{~~w&*2"/0,.12+*:3I4>97=F;=8APGIBMNTTobXQZfUag_wflbhq[}xzŒ€£q|†Š’Š˜”¶›™¥¡Âµ°µµ³·Ä¿Æ¾ÌÉÝÅØÛàÍÕÿæ÷ç×ÏÖëì ïüúöôõ  **(1$%0(885&F+=A@D15"6B(,';7,<8O<7%K.)9)(&52/^'6)' þûþýýïðéðø)ïöãëöÜÞéÌØÏÑåÙÒÔÜͲ¾¨Ã¼¶Ï¢°«ž §§®¥ˆ²–£}{˜œŒ€%&#"(%(,'-)0,1*-469:C287FA?\AMBJIMETRG`bTQ]^\Wlfiwgjot{‚„’•v……‚®Ž˜Š›£´±¡¬§£§Å«¿ËÑÏ׺ÆÇÍÎÞÖÖÐëéÕþÎÞþöíèòïõïéþ õþ  ü,"&- =7A5*. W>0(J& %!UC5+A:-!'78'#06& +@%F$&  óÿýò úïæåö÷ÖûÉáêÅÕÝîÚȼÅÙ¿ÖŵœµÃ¯¢¿¯¦˜°¦¡Ž›—²©Èµ—‹†„ƒrt'+'!*+,$*+1%6$.870459913?B9;=>S;MRXSPPSQVLUZhaaJ\|Syvdt{k}wjd}ƒ‡l‹‡€•œ‘¢ž­™”ž›Ÿ¤¨Õ²Ë¾µ¼¸²À»Æ¶ÌàÑéÕåãùèÇõÛÛæäØñüàãéðêýû&  1÷5 !+*29'*!,,2?B?%! )ù#ùü úù óøåçôïøäýáÚëÚÝéÞêÒÏÊÛê¸ÖÝÙ´´Ï·£Á§µ¥´¨ ˜”žšš“–™§‹‘‚‡š†€|%"')$&+)%*3<)1..,98@57887LH>CHPVBHIUU?TLO`MPcibaaghid†s~t{y}mzˆŽy‡ƒ‹Š°ªž§¡ª­¶¤Ã™¤ž¤°¶¿£ã«ÐÍ·Ðç¸ËäòÖéÞçÆôÓÛäôòêÑö þïö 2ý '* ! ÿ%"  :+$7  ý( ú$ ò*þïìõÛÜøèÌèÔÙÝÍøåÍ罺㼽Ӻ̹¹»¶ÆÓ²®˜£¦³ª—¡§Ÿ•›v˜{ˆ³’zrztƒs{u% #" /%"<2-=)0C6-491-A1F4AQSOC>IWRPS`[_\Y_Jc€baJnfp}^r{gpyw~t{’ •–Œ˜•‘£±Ÿš® ¥¥žš°œºÎ£©·¶°Ý¶Á®ÚÈäÏËÚÀàéÄÙÝàïèüØóØîäóå òõìõà êüãçó þ ýü  ö  þ  þ ! úõ õìÞùöòöëþéíäËÈÞêÍéÝÚ×ÊÓàÕʸ®ÄÅଵ°¢²°¯—•­’¦¨ ¯¦Ž› ”•vy{’„ƒ~vqqoqjl"$%1! (& &*&+'1-1.:513D<+183>JGCDLACCC>ZX[Hn^[Z|aJlk]|_ryuph‚j‹rzxxŠ…pŽvŒ’¤—·›‚™¸–ª«¿°Á´É¸­·Î¸¾ÊÆÏÖæ¹ÂÍÝÈìéòÙÛÖÖ×äÚèúí üêÿ ý÷òýúÿûöíú%ÿîï .  #  ý1ûôû øýò÷õöóþÓ íñó  Ü÷ööãñÐðÞùäÝäàÇåÈÎÚ¶ÁçÚÎÎÙÕÉËÆÀ³½•¯´À¯´¸³—©¨®¦Ÿ¤¡Ž‚w…‹”mƒŒ‰mx~y^Zgeq$*"&(&,-#++):.)-82<279H=:28:>:@MA?JR\PQMYSgxhT^`Xijgnccng„zm|Š{ƒ{…’Œˆš‚“’‘”Ž•Ž¸Â¼˜¤®¦ÐœŸº¶Ð¹¾Èª¾ÊÇÖÌÜż×ãåàÏÜÛôãíßÿöøèï× â õØøìçÿøòöùü þáó$ÿ ò õåúú é éýêöèððøæØâêïÛÑåèèÞÇÏáÛ¾Ð×ÜÇ˰©³Í»ËÆ»¹¸Â¨¹À¤¦¦¦›Èž²­´Œ§p™ŽŽ€Ž}‚v‰}‡qs~_ƒvl{d! $%'*&(3'*,,-2*+7344/6C5>7B->>FSI>>WBJECHMaYLY]kU[_dt]\dcyŠtsnp~w”y†ˆx„xš—‘‘¤—• ¤¦Æ‡š£ ¦Åµ¹¬ ··°Ó¼ËÎ̹ÝÈØ°ÇÚÉÏéáÇâõÙÕïòÞãåáâðýðëò*ÖóöÞóßûëÚíñö ýôßúâëåäí íãäõõ ðëòíöûéØÚ ÝêóùÒÔÝÛØÙÞÜáÌÆçÓÍæÂÒǽͯÜ˺ÃǸŸ·Å™¹·º°”©‘‰™»©µ¢·˜ˆš”“‡xˆtv~‚l…|}nbN|_iXk*"1(+020 (,+10/)41=><C<E<99LHN<CFKIQHARIOOLIhjbbcndb]idqnup{m}osƒ~nqy‚|—Šœ’“‹¨½ª­©¡ «¸¾»±·°°ËÒÏüľÆ×¼»ÈÍØã×ÞúÈØÏäßÎÆçÜÛëÕáËýåØöÚßêææû÷úðþëíçÐëöÞüøÜêáú÷üðæâéè ãðÔôòâÛÝëã½âÚßÝÜÝòÏÜÝ¿ÛÖ™ãÐÂÚÙʸ»»¹ÆºÐ­Á¸²¶¾´¡¦‰–°¶ˆ–¤†ž¥ƒƒŽz—’~Œ‰xgŒrsi|biekrffjsi"" "%(.$!&0$81;81)F,>:469:8P@8E=L;XFXU\RLHPb[i[Y^lfdpeia_rbqxYxr€_yr{‚r˜€yˆ„‘Œ’‡¦Œ˜¤¬¨¢Ÿžµ°±Ç´Á´´¹À¦Ø×½´Æ¿³¿ÔÉÀÎðıöÆÎËÄÎÄÖÓÂÁÏÎÊ×ÕîÝÞæíßÂææäÍùÝôðôäéðÕÍäþääÞÈ×ëËúØÞÚïÙØÍßéÜß¶åÓåÜÕÍÅÖÖÕÈÑÑÈνËÒÏÎþ²¦®¶³²»°®°É±³ž­­ˆ¦«£˜“~“‰‘”–‚€Ž‡}ww~mŠvzhhm|q\ivXSjV !#!(3++--+0;9-8>7IE6K:E1ATI?MBGKBMNSZaYRO\q_fafgky[ffguwscxŠ|yu{‘uŒ…ˆˆœ“‹Ž“¦œ±Œšž®º™— ²œ¯”«È¼Å¹Á»Å¬ÇºÂʳ¾ÇÑÐÛÒÒ½ÁÂÖªÓÑÍãâÏßÎçßÉÙÛñåÓåÚÊòèã òàÌÚÖàÛÚøÐÔÔÓÎÝÚß¿åÝÔÐÝËÖÂäÞ¹çÐØ¼Ì°Ûµ½½×± ¤ÁÕ´¶¸¥´›®¡´¦ž®©‘¥ —©¬£’”¤”‰ƒ}||{|Švq€xxsz}tjpm_be^]^R^! #//'$",'##)%717$20?57*;,=E99PRILON^:BLWSSmJUTQOVWtdV_Xme{vc}n‚ftz|sŠ˜‰šžŒƒ”z“ž¦ª‰¢¢¢Œ•´£¯³­–¼–¯³Ñ­Ä¦¿ª³À¿ÇØÅ«¹ÕÇçÀÆÐܹÍèÍâÖø¼ÄÍ»àÒØÏâÚÑÛßùÔºáèëÙÈàåãÓæÝοÉßÞ××Ü¿ÓÛäÒÙÈÙ¾ÔѶ½ÁÛÁ½Ã¶·¦È»ÁÌ«¬²Í³­·±±¥¼­“¨˜”³­©™‘‘“|–zr”€v‰{‡mv„e}nerk[_uzoqgeiiWOX',&&#-#)&0&.%9.2:C9704>4<BF=CECKSJ@DKAY[QNKbXnk[UOTbng_erktyjzmuuwx€„|‹ˆ‹”|w ³…в“› ¡ºœ«¬¶²ª•®­µµŸ«¾»µÇ¿¸®¼¹±Æ¼Ó˸ºÃϽÔÁÕâÊÔ´Ï×È¿ÖÏË×´Ò½ÙÔïÆôËÇ´Ãí¿Ó¯ÅӵúÆãÈÑÉÓ­¾»ÀѲ¬´¼»µ¹µ¸»º¾µ»£ÐÆ´¶ª§·¹Ä³°¸“•‘™Ÿ—“ˆ–’‰‡€Ÿƒ›Š}‰nwn{x‚girryomc^i`_]Xcbf]YNX!/ /("/!4,9--9.-#622646*-5/4KA?KLWM=MN\@PBTYbYSTYWeWgWWxhhpqi{se{|lqsƒ{vˆ’‚žŽ’ƒ†”›­¢’—ª˜ž¥¤›­ ©¬¹‹¦¬ÇªŸ©ºº¼±§¨´Ä²ÀÚ¨ÚͯڥÒÈÓʽ¾Ê¾ÇÉÜåãÑÔÞ¶ÎØÞºÂ̾ÀÆÎÇÉÎÔ·Õۮȸ͹¾¹­ËºÃ±¹¾¸µª§¯¢¼³¡¯¯Ã½•ª¡Á¢—› ••‹ ”¤Ž§£~“”{~‹‚ŒxŒ…|spsgevvegYeoi|fhZZgX[LSQ_^&$#.%.$($*--*(36.9+::<63>@?>MC:D9?DCFBUQV^N^fJLVoepj]bj_x`t{vpsxnv|s†zš‚}‹‹ƒŸ”Œž•“’˜ž¬¦’­Ä±›§»­¢¡¥¾Ä±»¬¿¬±É¨ÑÒ¯º¶Éš°¼ÇƸ±ÊðÂã·®ÈÚ°½Åº¾ØÍàµÆØÀй°Ã°ºŸ×¦¬ÎÅŸ¸±¡®¿ÇΨ¯žÁ·† –¶»—¬–¦£ž‘¡—››¶w§“š†–¨~•‚yv‘}‹ih†w…uatSsdo{wUdquWUISJ[OS`YM"!!$$!",#*&/0"-(*4 -/'22+6716BC<@>@GIFFSAJMGLONKRZ]REM\RdhZ[m__bncnfhoym‰l~v„‚v}Œz}x¡—¡Žž—…¢—“˜›u´´¢•Ŧ­°– ¦©²¤©¨Ë±¡¼´³³¶¹É¿±Ä¶¤·«»É¬ÂµÂ¾Ò¥¬Óßä«»ÅÓŸºÀ£°ÄÁ¹£¼³·§±Å­Ã©³©¹¨²·«¨¦­¨™Ž™“—ž¢¨¤ˆœ˜£Œˆ’‰ƒ€~”ˆ†y†n…~zzltj|„ylqqnv[joX\[d_i\LcTYpR\@\  "&%"#($*))72)..-42*2+3.7A8-@7F4.QD6>XTEHCDMRAIQR\HXFbi\rahfgkisW^mpuf|h|usu‡€{~lŽˆˆ|—–‹Š‹ž’„z’®›Ÿ¥–” …¥™‹£¬­šÀ“¥¾´²¦ª·¡·­¡·¨³º´º³ÎΦ£®µÂ½º³Ç¼±¿·Ïµš§³²·œÀ·Æµ»·­©»¦µ°¨«´˜º§¨“®‹Ÿ¢œ—ŠŒš™ˆš–†Ž‚‹zŽz|ssvxx‚„t‡exdfqmmqZndVilPlR_OVWcQcFaPJPNL!#" &"- &-(8.0 /*2;,-,88/047;I75B7I8HHF;MLOSQDXQhQXPnZVcZn^nZbwseoxvd|zu}{„m~v~‹‘ˆx‘vŸ“Œˆš–‘Ž£‚—™‚¬“œŸ£¯»ª¤“·«³—²¤«ª°¤Ã±£µ¯£­·§¤¬ Î®¬ž¥š¢¸¸¹µ•·¶È½¥¤µ´°­°¨©£±¹•¥™¦¬›¨š ¦†ª„„’Š¡›œ—Œƒ„~‡z€ƒwtt‘yui`yngkvom`ftk_eTZ]TGpETMeJEZAKKRQKCO *#$$"'%& !#"$"-*6+,.A+*82/5/924E?4JL79IKFSFESOUBXBSWU]N\P[o`^eZf]Sliuto‡irqa‡}o…}}t„‰ŒŒ|{–„„Ž…“~‹~”˜{”’œ¬®†¢›–£Ÿ¨¡¬“¬´¦«žº£ŒÄ˜¦ž–£´”Ÿ¬¯œ²§®¡˜¨¢¬¿¤©•©®ª³¨–ŽŸ¢ŸÂ§¯³¡™˜§ƒ‘¨•–‡„Ž‹”«€†ŽŽƒy{v‹z‡•nux„oullktmz]qY`cYkfx\]cfYTfPQ`_IIJFG[IOKCH  !$  +.(&(" .*33$.:360<B@A9@<858@38@ID?JIaOGZOFgVPjQ[ZTTZf_Zc_qqr_kg\jaggrk{ko†z~ox…{‚…‰…Ч„Œ}£•’…¦™™—ƒ¼„‹‚–®–ˆ ®˜Š¯µ››™»¶Œ¢–‰œ«¯Â£¡£©·¬°£¥¶˜®š™¨•œ¬‡›ž’¢–„š“­žš•{£„“¢‘ˆ˜u’Œ}†Ž‰€gou{yo{ivrtblb}mhfOn[ReXQWZ[SWB_PTPHZN[9@?CDNFL$&#&%&&-)-$**$."200&%=60)B/3D26:GB<7<=L:@K>,TDDYSMSXNJtMa]Ma^b[VcgnojWachbzXƒtvv}fƒtˆ‚jx}yj¢“¡Š”…zŠ“}~‚†”—€ŒŒŒ——Œ«—³ž‹š‰¥¡uŽ‚¥Ž¢­’”¤—›‡§¥ˆž¬Ÿ—’“™’¯‚…ž‹¥˜ƒžŠ…y™™”ŠŠ‰z„Œ~„ƒt~…Œ˜zqƒ„ˆ~}•r‹qhƒ}}hgvjepbiixyvYW[X]hRePcSXXWAVRSQIE4ENH78B?A   ##!%%!)$' ., *,+$&-*7.89/?/6,/8/I:CI;DGCWK>LPLHVVJZI[PZTd]`e[ZZ`lwbrsa]cphaindrsj}etsk‰~—znŠŽux“‰’‰’™†~˜ŠŸ¢ƒ¨ŒŒžŽ™Ž¡”‘¯§‰¯”Ÿzˆ—‹’±—”†§‰‡zŽ•ƒ“…•ˆ‡”}|…§‚—‚‡r“€‚zshwl„˜vq‡ogrhbUYnkghgW]oqp^fZioL_gaSYVHKQS^DEGT@4VCEDC8@DJ   #$!(!""",&+$1-,%0))6/03;3?B0?<I<J=ABCJ>DTCBNJJESKBWJNS[PccrZXZkcf}klke\^xpizqv}fd„opquyxŽ…tw‡ˆzmyš‰…‰Ž{„š‹‘vzžŽ™¥›xžšœ™Š“Š‚£ˆŒˆŒ—z‘‹’§w‹•Œ“‚|z|„€…Žˆz}zyn‹{‡„d€~kqjfxipqmee``]d`aapW]NW]YPHP8NKR[JQFNN8=NEN:>C?64   " !$')'+&)6#,&.)9*)2)2102&57*?09B:ED4SA7T3NSAJTEO?WSJQX`NQRJaVU_c`VXo]aUdtq|Ytvm|vu[x€~ttizrnt{”Žn…z‰v‰ƒ~x–…‰Š„j’–~ƒ†yˆ’šŸ‰Œ‚ˆ‹€~„€­ƒ™ƒ”‰•‰—v|jp„z}}}‚y{—s‚jwmykq|pviur\ogymzXhl_dhqb^\[f[SWaNTMQRKORJNQKNF<KJDG;D<B>GC==<;    !$ !" /"$&/,*'$4&*."705->5--07FFA38@DAC;AWPDN7GMXS\JRdHL]gabP`]bkRiN`dr]XlsUthyxhhg~‚a‡†r‹{um‰†pw—vr‚{‰}z‹vˆ†ˆŒ~’qy“}y}||†–l}Ž{˜|–Žsv‚‰‡tp€‡„uzl„ˆsw}tii‚{ksmhlgua[am`wixZ^eTR`deh\\Ob^^^PaMLEGKJADOKPL@HH?EBHXAHK<?09/74   !")"&%$ ,$3#/*0+$+/.+23?1(-47768CC64M8><56IBBCC8KOJMcESZQFGTVXQc^mbdhWnhkjq^\`zkbjmmq`q~tj`ytpƒnuwtyspo…}jˆ˜y‰‰‡g†¨‡yq‹n{z|‚—ƒˆ’ap‡}‰}u|rzv|}}‹Ÿu|tyƒ~l|luhmiz„uv‹o`WqxnXiYabgUMm\IiRW__\U_FOXPVKGVU=RRJWACDF;LG;MDK:F3J0=@+15    #" %%,!,$/'&/!('!1)&,5+.B4?204(A:;8B<DARJ>EJGJlKZBQZK\BKJYV]]P[]b[nb\\`QhbUkfd€jprlfjlokk‚obvmsx~jsg|†dy|l|oy~ˆ}|wpsyxp„‚yn|‡qynŠ…i{€„l‚zyq}li|yhfhrqjosbmeo_p\egbp^T_hb^q[aQ]^aMVajhebVJMXQJJMCT7SB=I7=H9?=56=<S3,I7</-5)2  #-%$(%$)##('!,.,4?-(8-31.+5A16596G0@78JOO@WDDCAI:\MPYDB^MOQW_TMLU_X]QjeUeajWjne{‚e~o]fisft`tchw{g€vokmvot|mohmztorjvWofƒxw†|ˆ†„‚xpl|nrmƒodmwuojsq_mljvccdxemfdfZjgfm_^\nNO^iU^R^^OLQYSJW[XFSEAINTBE?CIN?EH->=I.?2>91.',.4      !!!!%'#!(%+;&'*'/='-)/8,599+(J=/9E9;8H9;K>JIDPT@WL9OMFJYVYPP=P>GO^H`UPQgiXX[]XVWcfbij`_pd^reX[g|\wiajshtrrzcre]xkxn€^vwigwprqao…pki}`quprfcmzcs_Zig`k^hujs`tjbWb^Z]cZkQZ_Y^WESLbLTNG\CAMIOFLJOCIFC:P;<89B6G<6EF92.:/2'94$A,       )'&"*&..!2#-5*64+66-;76B296)35787UDB<N:?IM?HEFKOF=QPRLNKXJKkXW\_Q\hmO_k_S^dRgbTgThcm\Yqm^my]rqbosPniggbgoeznhyc‚bsdzxok]p\zjo\ephmncjPvZVoal_T\kffYka]^U\Vf]`[XO[LTXQWFGRaN[FUTEW?<@C=5=CNI97A<=A0D4*3H6,62-:9;*+57+      $# ",3")!,.2103%+-A75=B66;2>E<8?D56=0;@DE?@QBEFAJ\QGGGILOHSKNX_NOMVQI_^ULcg\fTYIZgBTUhh__jQdf^_`UmYgfdvWZdgVe[fvknscf_]kt`pd`sq]uYTTPatdscw^b]_X`Wr^TVa^`W\KeSQT\f\URMZYNGAEJ:FHAGA@N<@A@?CRBD9765635@0@.,012('* -+)        !)"%(%!!"'0,)2,&%.:/9)(-'7:35=3964::+8CO;E<BH@:>SMKFAMO`AL:DWOQGGXHLKRRQWX\][YaRfeT[_XaUWZ^X\^cVg^YdM\cesv[Y`eImop_lWdljlojmhoMfo]Sca\`[j\`aJYY[VRTKVuaYa^eV\MU]SRNXOJKJIT<KEMAGF7CD5:9;<H;:@9GQ6463@643/.+276-(*+5,-!        "%#$#+-".').*/%%-0'%;6524./258?92:=:D><HQBECB.KI9BAMB[GH:UOZPTTPMADPYOS_XPYS^[oOmVYa^YZq^h^RuS\bVZ\l]frc_lZ`YeJ\aS_^VgcX[^RWFVZkT[X^kXlFtLUaHSG^UkkKAOSKSIEPKJYRFH^OI@G\PK;@GM<<EF9FJAB7684F0=>,0>,77/004)(0*1&)4        "%$"++#-3*)#-)-&%%.%-5<+**101?2<E<4;5;<N8EBK9?E>;@?L=EBOJFLPPXFJIT?VOPKaVNTF<NC\KXM_H\QddNUO\UbXKWYPLa\MhSfccTGUaZRaW\[`eZbRWT`NkKZM[[LWK\dZVKRXNLNKUETIKMIUS@TR0ML8E?SE1TB>B;HA8D4=,55:,283(.)0+$<(/-,01 +.$((- --CIF-BINARY-FORMAT-SECTION---- ; ./CBFlib-0.9.2.2/examples/changtestcompression.c0000644000076500007650000005010311603702122020017 0ustar yayayaya/* * testcompression.c - test compression schemes */ #include #include #include #include #include #include "cbf.h" #ifdef CBF_USE_LONG_LONG #ifndef LLONG_MAX #define LLONG_MAX (1ll << (sizeof(long long) * CHAR_BIT - 1)) #define ULLONG_MAX (~0ll) #endif #endif #define NSTEPS 5 double urand() { return rand() * 1.0 / RAND_MAX; } #define DATAUC 0 #define DATASC 1 #define DATAUS 2 #define DATASS 3 #define DATAUI 4 #define DATASI 5 #define DATAUL 6 #define DATASL 7 #define DATAULL 8 #define DATASLL 9 #define DATAF 10 #define DATAD 11 /* * Create images where spots are separated by a uniform distribution of mean * distance of NSTEPS/2 and have height uniformly distributed over (positive * part of) data range */ size_t createtestimage(void **data, int type, int nelem) { unsigned char *ucdata; signed char *scdata; unsigned short *usdata; signed short *ssdata; unsigned int *uidata; signed int *sidata; unsigned long *uldata; signed long *sldata; CBF_ull_type *ulldata; CBF_sll_type *slldata; float *fdata; double *ddata; int i = 0; size_t elsize = 0; switch (type) { case DATAUC: /* unsigned char */ ucdata = (unsigned char *)calloc(nelem, 1); elsize = sizeof(char); while (i < nelem) { ucdata[i] = urand() * UCHAR_MAX; i += 1 + urand() * NSTEPS; } *data = ucdata; break; case DATASC: /* signed char */ scdata = (signed char *)calloc(nelem, 1); elsize = sizeof(char); while (i < nelem) { scdata[i] = urand() * SCHAR_MAX; i += 1 + urand() * NSTEPS; } *data = scdata; break; case DATAUS: /* unsigned short */ usdata = (unsigned short *)calloc(nelem, sizeof(short)); elsize = sizeof(short); while (i < nelem) { usdata[i] = urand() * USHRT_MAX; i += 1 + urand() * NSTEPS; } *data = usdata; break; case DATASS: /* signed short */ ssdata = (signed short *)calloc(nelem, sizeof(short)); elsize = sizeof(short); while (i < nelem) { ssdata[i] = urand() * SHRT_MAX; i += 1 + urand() * NSTEPS; } *data = ssdata; break; case DATAUI: /* unsigned int */ uidata = (unsigned int *)calloc(nelem, sizeof(int)); elsize = sizeof(int); while (i < nelem) { uidata[i] = urand() * UINT_MAX; i += 1 + urand() * NSTEPS; } *data = uidata; break; case DATASI: /* signed int */ sidata = (signed int *)calloc(nelem, sizeof(int)); elsize = sizeof(int); while (i < nelem) { sidata[i] = urand() * INT_MAX; i += 1 + urand() * NSTEPS; } *data = sidata; break; case DATAUL: /* unsigned long */ uldata = (unsigned long *)calloc(nelem, sizeof(long)); elsize = sizeof(long); while (i < nelem) { uldata[i] = urand() * ULONG_MAX; i += 1 + urand() * NSTEPS; } *data = uldata; break; case DATASL: /* signed long */ sldata = (signed long *)calloc(nelem, sizeof(long)); elsize = sizeof(long); while (i < nelem) { sldata[i] = urand() * LONG_MAX; i += 1 + urand() * NSTEPS; } *data = sldata; break; #ifdef CBF_USE_LONG_LONG case DATAULL: /* unsigned long long */ ulldata = (unsigned long long *)calloc(nelem, sizeof(long long)); elsize = sizeof(long long); while (i < nelem) { ulldata[i] = urand() * ULLONG_MAX; i += 1 + urand() * NSTEPS; } *data = ulldata; break; case DATASLL: /* signed long long */ slldata = (signed long long *)calloc(nelem, sizeof(long long)); elsize = sizeof(long long); while (i < nelem) { slldata[i] = urand() * LLONG_MAX; i += 1 + urand() * NSTEPS; } *data = slldata; break; #else case DATAULL: /* unsigned long long as an array */ ulldata = (CBF_ull_type *)calloc(nelem, sizeof(CBF_ull_type)); elsize = sizeof(CBF_ull_type); while (i < nelem) { ulldata[i].el0 = urand() * INT_MAX; ulldata[i].el1 = urand() * INT_MAX; #if CBF_ULL_INTS == 4 ulldata[i].el2 = urand() * INT_MAX; ulldata[i].el3 = urand() * INT_MAX; #endif i += 1 + urand() * NSTEPS; } *data = ulldata; break; case DATASLL: /* signed long long */ slldata = (CBF_sll_type *)calloc(nelem, sizeof(CBF_sll_type)); elsize = sizeof(CBF_sll_type); while (i < nelem) { slldata[i].el0 = urand() * INT_MAX; slldata[i].el1 = urand() * INT_MAX; #if CBF_ULL_INTS == 4 slldata[i].el2 = urand() * INT_MAX; slldata[i].el3 = urand() * INT_MAX; #endif i += 1 + urand() * NSTEPS; } *data = slldata; break; #endif case DATAF: /* float */ fdata = (float *)calloc(nelem, sizeof(float)); elsize = sizeof(float); while (i < nelem) { fdata[i] = urand() * INT_MAX; i += 1 + urand() * NSTEPS; } *data = fdata; break; case DATAD: /* double */ ddata = (double *)calloc(nelem, sizeof(double)); elsize = sizeof(double); while (i < nelem) { ddata[i] = urand() * INT_MAX; i += 1 + urand() * NSTEPS; } *data = ddata; break; default: fprintf(stderr, "Unknown type number\n"); } return elsize; } int createtestfile(const char *fn, int isreal, int rows, int columns, int compression, void *data, size_t elsize, int elsigned) { int status; cbf_handle ch; FILE *f; status = cbf_make_handle(&ch); if (status) printf("make_handle (%d)\n", status); status = cbf_new_datablock (ch, "image_1"); if (status) printf("new_datablock (%d)\n", status); status = cbf_new_category(ch, "array_data"); if (status) printf("new_category (%d)\n", status); status = cbf_new_column(ch, "array_id"); if (status) printf("new_column (%d)\n", status); status = cbf_set_value(ch, "image_1"); if (status) printf("set_value (%d)\n", status); status = cbf_new_column(ch, "binary_id"); if (status) printf("new_column (%d)\n", status); status = cbf_set_integervalue(ch, 1); if (status) printf("set_integervalue (%d)\n", status); status = cbf_new_column(ch, "data"); if (status) printf("new_column (%d)\n", status); if (isreal) { status = cbf_set_realarray_wdims(ch, compression, 1, data, elsize, rows * columns, "little_endian", columns, rows, 0, 0); if (status) printf("set_realarray_wdims (%d)\n", status); } else { status = cbf_set_integerarray_wdims(ch, compression, 1, data, elsize, elsigned, rows * columns, "little_endian", columns, rows, 0, 0); if (status) printf("set_integerarray_wdims (%d)\n", status); } if (status) return status; f = fopen(fn, "wb"); status = cbf_write_widefile(ch, f, 1, CBF, MIME_HEADERS | MSG_DIGEST, 0); if (status) printf("write_widefile (%d)\n", status); status = cbf_free_handle(ch); if (status) printf("free_handle (%d)\n", status); return status; } size_t readtestimage(const char *fn, void **data, size_t *size, int *sign) { cbf_handle ch; int status; FILE *f; unsigned int cifcomp = 0; int bid = 0, els = 0, elu = 0; int minel = 0, maxel = 0, isre = 0; size_t elsize = 0, elnum = 0; size_t dim1 = 0, dim2 = 0, dim3 = 0, pad = 0; const char *byteorder = NULL; int isreal; int id; size_t rsize = 0; status = cbf_make_handle(&ch); if (status) printf("make_handle (%d)\n", status); f = fopen(fn, "rb"); status = cbf_read_widefile(ch, f, MSG_DIGEST); if (status) printf("read_widefile (%d)\n", status); status = cbf_rewind_datablock(ch); if (status) printf("rewind_db (%d)\n", status); status = cbf_find_category(ch, "array_data"); if (status) printf("find_cat (%d)\n", status); status = cbf_find_tag(ch, "_array_data.data"); if (status) printf("find_tag (%d)\n", status); status = cbf_rewind_row(ch); if (status) printf("rewind_row (%d)\n", status); status = cbf_get_arrayparameters_wdims(ch, &cifcomp, &bid, &elsize, &els, &elu, &elnum, &minel, &maxel, &isre, &byteorder, &dim1, &dim2, &dim3, &pad); if (status) printf("get_aparams (%d) = %d, %d, %ld, %d, %d,\n", status, cifcomp, bid, (long)elsize, els, elu); if (status) printf(" %ld, %d, %d, %d, %s,\n", (long)elnum, minel, maxel, isre, (byteorder == NULL) ? "null" : byteorder); if (status) printf(" %ld, %ld, %ld, %ld\n", (long)dim1, (long)dim2, (long)dim3, (long)pad); isreal = (isre == 1); if (isreal) { if (elsize == sizeof(float) || elsize == sizeof(double)) { void *rdata = malloc(elsize * elnum); status = cbf_get_realarray(ch, &id, rdata, elsize, elnum, &rsize); if (status) printf("get_realarray (%d)\n", status); *data = rdata; } else { fprintf(stderr, "Size of element (%ld) does not match any real types\n", (long)elsize); } } else { if (els && elu) { fprintf(stderr, "Both signed and unsigned flags have been set!\n"); return rsize; } if (elsize == sizeof(char) || elsize == sizeof(short) || elsize == sizeof(int) || elsize == sizeof(long) #ifdef CBF_USE_LONG_LONG || elsize == sizeof(long long) #else || elsize == sizeof(CBF_sll_type) #endif ) { void *idata = malloc(elsize * elnum); status = cbf_get_integerarray(ch, &id, idata, elsize, els, elnum, &rsize); if (status) printf("get_integerarray (%d)\n", status); *data = idata; } else { fprintf(stderr, "Size of element (%ld) does not match any integer types\n", (long)elsize); } } status = cbf_free_handle(ch); if (status) printf("free_handle (%d)\n", status); *sign = els; *size = elsize; if (rsize != elnum) printf("Read %ld elements\n", (long)rsize); return rsize; } void checkdata(int type, int nelem, void *data, void *idata) { unsigned char *ucdata, *ucidata; signed char *scdata, *scidata; unsigned short *usdata, *usidata; signed short *ssdata, *ssidata; unsigned int *uidata, *uiidata; signed int *sidata, *siidata; unsigned long *uldata, *ulidata; signed long *sldata, *slidata; #ifdef CBF_USE_LONG_LONG unsigned long long *ulldata, *ullidata; signed long long *slldata, *sllidata; #else CBF_ull_type *ulldata, *ullidata; CBF_sll_type *slldata, *sllidata; #endif float *fdata, *fidata; double *ddata, *didata; int i = 0; switch (type) { case DATAUC: /* unsigned char */ ucdata = (unsigned char *)data; ucidata = (unsigned char *)idata; while (i < nelem) { if (ucdata[i] != ucidata[i]) { fprintf(stderr, "UC element %d did not match (%d != %d)\n", i, ucdata[i], ucidata[i]); fprintf(stderr, "Previous UC elements are (%x %x)\n", ucdata[i-1], ucidata[i-1]); fprintf(stderr, "Previous UC elements are ~(%x %x)\n", ~ucdata[i-1], ~ucidata[i-1]); return; } i++; } break; case DATASC: /* signed char */ scdata = (signed char *)data; scidata = (signed char *)idata; while (i < nelem) { if (scdata[i] != scidata[i]) { fprintf(stderr, "SC element %d did not match (%d != %d)\n", i, scdata[i], scidata[i]); fprintf(stderr, "Previous SC elements are (%x %x)\n", scdata[i-1], scidata[i-1]); fprintf(stderr, "Previous SC elements are ~(%x %x)\n", ~scdata[i-1], ~scidata[i-1]); return; } i++; } break; case DATAUS: /* unsigned short */ usdata = (unsigned short *)data; usidata = (unsigned short *)idata; while (i < nelem) { if (usdata[i] != usidata[i]) { fprintf(stderr, "US element %d did not match (%d != %d)\n", i, usdata[i], usidata[i]); return; } i++; } break; case DATASS: /* signed short */ ssdata = (signed short *)data; ssidata = (signed short *)idata; while (i < nelem) { if (ssdata[i] != ssidata[i]) { fprintf(stderr, "SS element %d did not match (%d != %d)\n", i, ssdata[i], ssidata[i]); return; } i++; } break; case DATAUI: /* unsigned int */ uidata = (unsigned int *)data; uiidata = (unsigned int *)idata; while (i < nelem) { if (uidata[i] != uiidata[i]) { fprintf(stderr, "UI element %d did not match (%d != %d)\n", i, uidata[i], uiidata[i]); return; } i++; } break; case DATASI: /* signed int */ sidata = (signed int *)data; siidata = (signed int *)idata; while (i < nelem) { if (sidata[i] != siidata[i]) { fprintf(stderr, "SI element %d did not match (%d != %d)\n", i, sidata[i], siidata[i]); return; } i++; } break; case DATAUL: /* unsigned long */ uldata = (unsigned long *)data; ulidata = (unsigned long *)idata; while (i < nelem) { if (uldata[i] != ulidata[i]) { fprintf(stderr, "UL element %d did not match (%ld != %ld)\n", i, uldata[i], ulidata[i]); return; } i++; } break; case DATASL: /* signed long */ sldata = (signed long *)data; slidata = (signed long *)idata; while (i < nelem) { if (sldata[i] != slidata[i]) { fprintf(stderr, "SL element %d did not match (%ld != %ld)\n", i, sldata[i], slidata[i]); return; } i++; } break; #ifdef CBF_USE_LONG_LONG case DATAULL: /* unsigned long long */ ulldata = (unsigned long long *)data; ullidata = (unsigned long long *)idata; while (i < nelem) { if (ulldata[i] != ullidata[i]) { fprintf(stderr, "ULL element %d did not match (%lld != %lld)\n", i, ulldata[i], ullidata[i]); return; } i++; } break; case DATASLL: /* signed long long */ slldata = (signed long long *)data; sllidata = (signed long long *)idata; while (i < nelem) { if (slldata[i] != sllidata[i]) { fprintf(stderr, "SLL element %d did not match (%lld != %lld)\n", i, slldata[i], sllidata[i]); return; } i++; } break; #else case DATAULL: /* unsigned long long */ ulldata = (CBF_ull_type *)data; ullidata = (CBF_ull_type *)idata; while (i < nelem) { #if CBF_ULL_INTS == 2 if (ulldata[i].el0 != ullidata[i].el0 || ulldata[i].el1 != ullidata[i].el1) { fprintf(stderr, "ULL element %d did not match (%x %x != %x %x)\n", i, ulldata[i].el1,ulldata[i].el0, ullidata[i].el1,ullidata[i].el0); return; } #else if (ulldata[i].el0 != ullidata[i].el0 || ulldata[i].el1 != ullidata[i].el1 || ulldata[i].el2 != ullidata[i].el2 || ulldata[i].el3 != ullidata[i].el3) { fprintf(stderr, "ULL element %d did not match (%x %x %x %x != %x %x %x %x)\n", i, ulldata[i].el3,ulldata[i].el2,ulldata[i].el1,ulldata[i].el0, ullidata[i].el3,ullidata[i].el2,ullidata[i].el1,ullidata[i].el0); return; } #endif i++; } break; case DATASLL: /* signed long long */ slldata = (CBF_sll_type *)data; sllidata = (CBF_sll_type *)idata; while (i < nelem) { #if CBF_SLL_INTS == 2 if (slldata[i].el0 != sllidata[i].el0 || slldata[i].el1 != sllidata[i].el1) { fprintf(stderr, "SLL element %d did not match (%x %x != %x %x)\n", i, slldata[i].el1,slldata[i].el0, sllidata[i].el1,sllidata[i].el0); return; } #else if (slldata[i].el0 != sllidata[i].el0 || slldata[i].el1 != sllidata[i].el1 || slldata[i].el2 != sllidata[i].el2 || slldata[i].el3 != sllidata[i].el3) { fprintf(stderr, "ULL element %d did not match (%x %x %x %x != %x %x %x %x)\n", i, ulldata[i].el3,ulldata[i].el2,ulldata[i].el1,ulldata[i].el0, ullidata[i].el3,ullidata[i].el2,ullidata[i].el1,ullidata[i].el0); return; } #endif i++; } break; #endif case DATAF: /* float */ fdata = (float *)data; fidata = (float *)idata; while (i < nelem) { if (fabs(fdata[i] - fidata[i]) > FLT_MIN) { fprintf(stderr, "F element %d did not match (%g != %g)\n", i, fdata[i], fidata[i]); return; } i++; } break; case DATAD: /* double */ ddata = (double *)data; didata = (double *)idata; while (i < nelem) { if (fabs(ddata[i] - didata[i]) > DBL_MIN) { fprintf(stderr, "D element %d did not match (%g != %g)\n", i, ddata[i], didata[i]); return; } i++; } break; } } void testinteger(const char *fn, int rows, int cols, int type, int comp) { void *data, *idata; size_t elsize; size_t nelem = rows*cols; size_t isize; int isign; elsize = createtestimage(&data, type, nelem); if (elsize == 0) { fprintf(stderr, "Could not create test image\n"); return; } if (createtestfile(fn, 0, rows, cols, comp, data, elsize, type & 1) != 0) { fprintf(stderr, "Could not create test file\n"); return; } if (readtestimage(fn, &idata, &isize, &isign) != nelem) { fprintf(stderr, "Did not read %ld elements\n", (long) nelem); } if (isize != elsize) fprintf(stderr, "Size of elements does not match (%ld != %ld)\n", (long)elsize, (long)isize); if (isign != (type & 1)) fprintf(stderr, "Sign of elements does not match (%d != %d)\n", type & 1, isign); checkdata(type, nelem, data, idata); free(data); free(idata); } void testreal(const char *fn, int rows, int cols, int type, int comp) { void *data, *idata; size_t elsize; size_t nelem = rows*cols; size_t isize; int isign; elsize = createtestimage(&data, type, nelem); if (elsize == 0) { fprintf(stderr, "Could not create test image\n"); return; } if (createtestfile(fn, 1, rows, cols, comp, data, elsize, 1) != 0) { fprintf(stderr, "Could not create test file\n"); return; } if (readtestimage(fn, &idata, &isize, &isign) != nelem) { fprintf(stderr, "Did not read %ld elements\n", (long) nelem); } if (isize != elsize) fprintf(stderr, "Size of elements does not match (%ld != %ld)\n", (long)elsize, (long)isize); checkdata(type, nelem, data, idata); free(data); free(idata); } void testall(const char *fn) { int rows = 512; int cols = 10; int c, t; int comp[] = { CBF_NONE, /* CBF_PREDICTOR, not implemented! */ CBF_BYTE_OFFSET, CBF_PACKED_V2, CBF_CANONICAL }; char * compstr[] = { "CBF_NONE", /* "CBF_PREDICTOR", */ "CBF_BYTE_OFFSET", "CBF_PACKED_V2", "CBF_CANONICAL" }; char * datastr[] = { "unsigned char", "signed char", "unsigned short", "signed short", "unsigned int", "signed int", "unsigned long", "signed long", #ifdef CBF_USE_LONG_LONG "unsigned long long", "signed long long", #else "CBF_ull_type", "CBF_sll_type", #endif "float", "double" }; for (c = 0; c < 4; c++) { printf("Testing compression scheme %d, %d %s\n", c, comp[c], compstr[c]); for (t = 0; t < DATAF; t++) { printf(" with data type %d, %s\n", t, datastr[t]); testinteger(fn, rows, cols, t, comp[c]); } printf(" with data type %d, %s\n", DATAF, datastr[DATAF]); testreal(fn, rows, cols, DATAF, comp[c]); printf(" with data type %d, %s\n", DATAD, datastr[DATAD]); testreal(fn, rows, cols, DATAD, comp[c]); } } int main(int argc, char **argv) { char *fn; if (argc < 2) fn = "CTC.cbf"; else fn = argv[1]; printf("Saving to %s\n", fn); testall(fn); return 0; } ./CBFlib-0.9.2.2/examples/template_mar345_2300x2300.cbf0000644000076500007650000001266211603702122020144 0ustar yayayaya###CBF: VERSION 1.1 data_image_1 # category DIFFRN loop_ _diffrn.id _diffrn.crystal_id DIFFRN_ID DIFFRN_CRYSTAL_ID # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.current _diffrn_source.type DIFFRN_ID synchrotron 100.0 'SSRL beamline 9-1' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.probe _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source _diffrn_radiation.collimation DIFFRN_ID WAVELENGTH1 x-ray 'Si 111' 0.8 0.0 0.08 0.01 0.00 '0.20 mm x 0.20 mm' # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.details _diffrn_detector.number_of_axes DIFFRN_ID MAR345-SN26 'MAR 345' 'slow mode' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id MAR345-SN26 DETECTOR_X MAR345-SN26 DETECTOR_Y MAR345-SN26 DETECTOR_Z MAR345-SN26 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 MAR345-SN26 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method _diffrn_measurement.details DIFFRN_ID GONIOMETER 3 rotation 'i0=1.000 i1=1.000 i2=1.000 ib=1.000 beamstop=20 mm 0% attenuation' # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 0.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 0.0 0.0 FRAME1 GONIOMETER_KAPPA 0.0 0.0 FRAME1 GONIOMETER_PHI 0.0 0.0 FRAME1 DETECTOR_Z 0.0 0.0 FRAME1 DETECTOR_Y 0.0 0.0 FRAME1 DETECTOR_X 0.0 0.0 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 -1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 -172.5 172.5 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 2300 1 increasing ELEMENT_X ARRAY1 2 2300 2 increasing ELEMENT_Y # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.075 0.150 ELEMENT_Y ELEMENT_Y -0.075 -0.150 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 1.15 0.2 240000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ? ./CBFlib-0.9.2.2/examples/img2cif.c0000644000076500007650000011515411603702122015105 0ustar yayayaya/********************************************************************** * img2cif -- convert an image file to a cif file * * * * Version 0.9.1 14 February 2010 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006 -- 2010 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * WHILE YOU MAY ALTERNATIVE DISTRIBUTE THE API UNDER THE LGPL * * YOU MAY ***NOT*** DISTRBUTE THIS PROGRAM UNDER THE LGPL * * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /********************************************************************** * SYNOPSIS * * * * img2cif [-i input_image] [-o output_cif] \ * * [-c {p[acked]|c[annonical]|[n[one]}] \ * * [-m {h[eaders]|n[oheaders]}] [-d {d[igest]|n[odigest]}] \ * * [-e {b[ase64]|q[uoted-printable]| \ * * d[ecimal]|h[exadecimal]|o[ctal]|n[one]}] \ * * [-b {f[orward]|b[ackwards]}] \ * * [input_image] [output_cif] * * * * the options are: * * * * -i input_image (default: stdin) * * the input_image file in MAR300, MAR345 or ADSC CCD detector * * format is given. If no input_image file is specified or is * * given as "-", an image is copied from stdin to a temporary file.* * * * -o output_cif (default: stdout) * * the output cif (if base64 or quoted-printable encoding is used) * * or cbf (if no encoding is used). if no output_cif is specified * * or is given as "-", the output is written to stdout * * * * -c compression_scheme (packed, canonical or none, * * default packed) * * * * -m [no]headers (default headers for cifs, noheaders for cbfs) * * selects MIME (N. Freed, N. Borenstein, RFC 2045, November 1996) * * headers within binary data value text fields. * * * * -d [no]digest (default md5 digest [R. Rivest, RFC 1321, April * * 1992 using"RSA Data Security, Inc. MD5 Message-Digest * * Algorithm"] when MIME headers are selected) * * * * -e encoding (base64, quoted-printable, decimal, hexadecimal, * * octal or none, default: base64) specifies one of the standard * * MIME encodings (base64 or quoted-printable) or a non-standard * * decimal, hexamdecimal or octal encoding for an ascii cif * * or "none" for a binary cbf * * * * -b direction (forward or backwards, default: natural direction) * * specifies the direction of mapping of bytes into words * * for decimal, hexadecimal or octal output, marked by '>' for * * forward or '<' for backwards as the second character of each * * line of output, and in '#' comment lines. * * * * * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term 'this software', as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #include "cbf.h" #include "img.h" #include #include #include #include #include #include #include #include "cbf_getopt.h" #define I2CBUFSIZ 8192 #ifdef __MINGW32__ #define NOMKSTEMP #define NOTMPDIR #endif #undef cbf_failnez #define cbf_failnez(x) \ {int err; \ err = (x); \ if (err) { \ fprintf(stderr,"\nCBFlib fatal error %d \n",err); \ exit(-1); \ } \ } int main (int argc, char *argv []) { FILE *out, *file; clock_t a,b; img_handle img; cbf_handle cbf; double pixel_size, gain, wavelength, distance; int overload, dimension [2], precedence [2]; const char *detector; char *detector_char; char detector_id [64]; const char *direction [2]; int c; int errflg = 0; const char *imgin, *imgout; char *imgtmp=NULL; #ifndef NOMKSTEMP int imgtmpfd; #endif int imgtmpused; int nbytes; char buf[I2CBUFSIZ]; int mime, digest, encoding, compression, bytedir, term, cbforcif; cbf_getopt_handle opts; const char * optarg; /* Extract options */ /********************************************************************** * img2cif [-i input_image] [-o output_cif] \ * * [-c {p[acked]|c[annonical]|{b[yte_offset]}|\ * * {v[2packed]}|{f[latpacked]}[n[one]}] \ * * [-m {h[eaders]|n[oheaders]}] [-d {d[igest]|n[odigest]}] \ * * [-e {b[ase64]|q[uoted-printable]|\ * * d[ecimal]|h[exadecimal]|o[ctal]|n[one]}] \ * * [-w {2|3|4|6|8}] [-b {f[orward]|b[ackwards]}\ * * [input_image] [output_cif] * * * **********************************************************************/ mime = 0; digest = 0; encoding = 0; compression = 0; bytedir = 0; imgin = NULL; imgout = NULL; imgtmpused = 0; cbf_failnez(cbf_make_getopt_handle(&opts)) cbf_failnez(cbf_getopt_parse(opts, argc, argv, "i:o:c:m:d:e:b:")) if (!cbf_rewind_getopt_option(opts)) for(;!cbf_get_getopt_data(opts,&c,NULL,NULL,&optarg);cbf_next_getopt_option(opts)) { if (!c) break; switch (c) { case 'i': if (imgin) errflg++; else imgin = optarg; break; case 'o': if (imgout) errflg++; else imgout = optarg; break; case 'c': if (compression) errflg++; if (optarg[0] == 'p' || optarg[0] == 'P') { compression = CBF_PACKED; } else { if (optarg[0] == 'c' || optarg[0] == 'C') { compression = CBF_CANONICAL; } else { if (optarg[0] == 'b' || optarg[0] == 'B') { compression = CBF_BYTE_OFFSET; } else { if (optarg[0] == 'n' || optarg[0] == 'N') { compression = CBF_NONE; } else { if (optarg[0] == 'v' || optarg[0] == 'V') { compression = CBF_PACKED_V2; } else { if (optarg[0] == 'f' || optarg[0] == 'F') { compression = CBF_PACKED|CBF_FLAT_IMAGE; } else { errflg++; } } } } } } break; case 'm': if (mime) errflg++; if (optarg[0] == 'h' || optarg[0] == 'H' ) { mime = MIME_HEADERS; } else { if (optarg[0] == 'n' || optarg[0] == 'N' ) { mime = PLAIN_HEADERS; } else { errflg++; } } break; case 'd': if (digest) errflg++; if (optarg[0] == 'd' || optarg[0] == 'H' ) { digest = MSG_DIGEST; } else { if (optarg[0] == 'n' || optarg[0] == 'N' ) { digest = MSG_NODIGEST; } else { errflg++; } } break; case 'b': if (bytedir) errflg++; if (optarg[0] == 'f' || optarg[0] == 'F') { bytedir = ENC_FORWARD; } else { if (optarg[0] == 'b' || optarg[0] == 'B' ) { bytedir = ENC_BACKWARD; } else { errflg++; } } break; case 'e': if (encoding) errflg++; if (optarg[0] == 'b' || optarg[0] == 'B' ) { encoding = ENC_BASE64; } else { if (optarg[0] == 'q' || optarg[0] == 'Q' ) { encoding = ENC_QP; } else { if (optarg[0] == 'd' || optarg[0] == 'D' ) { encoding = ENC_BASE10; } else { if (optarg[0] == 'h' || optarg[0] == 'H' ) { encoding = ENC_BASE16; } else { if (optarg[0] == 'o' || optarg[0] == 'O' ) { encoding = ENC_BASE8; } else { if (optarg[0] == 'n' || optarg[0] == 'N' ) { encoding = ENC_NONE; } else { errflg++; } } } } } } break; default: errflg++; break; } } for(;!cbf_get_getopt_data(opts,&c,NULL,NULL,&optarg);cbf_next_getopt_option(opts)) { if (!imgin) { imgin = optarg; } else { if (!imgout) { imgout = optarg; } else { errflg++; } } } if (errflg) { fprintf(stderr,"img2cif: Usage: \n"); fprintf(stderr," img2cif [-i input_image] [-o output_cif] \\\n"); fprintf(stderr," [-c {p[acked]|c[annonical]|{b[yte_offset]}|\\\n"); fprintf(stderr," {v[2packed}|{f[latpacked}[n[one]}] \\\n"); fprintf(stderr," [-m {h[eaders]|n[oheaders]}] [-d {d[igest]|n[odigest]}] \\\n"); fprintf(stderr," [-e {b[ase64]|q[uoted-printable]|\\\n"); fprintf(stderr," d[ecimal]|h[examdecimal|o[ctal]|n[one]}] \\\n"); fprintf(stderr," [-w {2|3|4|6|8}] [-b {f[orward]|b[ackwards]}\\\n"); fprintf(stderr," [input_image] [output_cif] \n\n"); exit(2); } /* Set up for CIF of CBF output */ if (!encoding) encoding = ENC_BASE64; cbforcif = CBF; term = ENC_CRTERM | ENC_LFTERM; if (encoding == ENC_BASE64 || \ encoding == ENC_QP || \ encoding == ENC_BASE10 || \ encoding == ENC_BASE16 || \ encoding == ENC_BASE8) { cbforcif = CIF; term = ENC_LFTERM; } /* Set up for headers */ if (!mime) mime = MIME_HEADERS; if (!digest) { if (mime == MIME_HEADERS) { digest = MSG_DIGEST; } else { digest = MSG_NODIGEST; } } /* Set up for Compression */ if (!compression) compression = CBF_PACKED; /* Read the image */ if (!imgin || strcmp(imgin?imgin:"","-") == 0) { imgtmp=(char *)malloc(strlen("/tmp/img2cifXXXXXX")+1); #ifdef NOTMPDIR strcpy(imgtmp, "img2cifXXXXXX"); #else strcpy(imgtmp, "/tmp/img2cifXXXXXX"); #endif #ifdef NOMKSTEMP if ((imgtmp = mktemp(imgtmp)) == NULL ) { fprintf(stderr,"\n img2cif: Can't create temporary file name %s.\n", imgtmp); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } if ( (file = fopen(imgtmp,"wb+")) == NULL) { fprintf(stderr,"Can't open temporary file %s.\n", imgtmp); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } #else if ((imgtmpfd = mkstemp(imgtmp)) == -1 ) { fprintf(stderr,"Can't create temporary file %s.\n", imgtmp); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } if ( (file = fdopen(imgtmpfd, "w+")) == NULL) { fprintf(stderr,"img2cif: Can't open temporary file %s.\n", imgtmp); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } #endif while ((nbytes = fread(buf, 1, 8192, stdin))) { if(nbytes != fwrite(buf, 1, nbytes, file)) { fprintf(stderr,"img2cif: Failed to write %s.\n", imgtmp); exit(1); } } fclose(file); imgin = imgtmp; imgtmpused = 1; } img = img_make_handle (); a = clock (); cbf_failnez (img_read (img, imgin)) if ( imgtmpused ) { if (unlink(imgtmp) != 0 ) { fprintf(stderr,"img2cif: Can't unlink temporary file %s.\n", imgtmp); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } } b = clock (); fprintf (stderr, "img2cif: Time to read the image: %.3fs\n", ((b - a) * 1.0) / CLOCKS_PER_SEC); /* Get some detector parameters */ /* Detector identifier */ detector = img_get_field (img, "DETECTOR"); if (!detector) detector = "unknown"; strncpy (detector_id, detector, 63); detector_id [63] = 0; detector_char = detector_id; while (*detector_char) if (isspace (*detector_char)) memmove (detector_char, detector_char + 1, strlen (detector_char)); else { *detector_char = tolower (*detector_char); detector_char++; } /* Pixel size */ pixel_size = img_get_number (img, "PIXEL SIZE") * 0.001; /* Wavelength */ wavelength = img_get_number (img, "WAVELENGTH"); /* Distance */ distance = img_get_number (img, "DISTANCE") * 0.001; /* Image size and orientation & gain and overload */ if (strcmp (detector_id, "mar180") == 0 || strcmp (detector_id, "mar300") == 0) { gain = 1.08; overload = 120000; dimension [0] = img_rows (img); dimension [1] = img_columns (img); precedence [0] = 1; precedence [1] = 2; direction [0] = "decreasing"; direction [1] = "increasing"; } else if (strcmp (detector_id, "mar345") == 0) { gain = 1.55; overload = 240000; dimension [0] = img_columns (img); dimension [1] = img_rows (img); precedence [0] = 2; precedence [1] = 1; direction [0] = "increasing"; direction [1] = "increasing"; } else if (strncmp (detector_id, "adscquantum", 11) == 0) { gain = 0.20; overload = 65000; dimension [0] = img_columns (img); dimension [1] = img_rows (img); precedence [0] = 2; precedence [1] = 1; direction [0] = "increasing"; direction [1] = "increasing"; } else { gain = 0.0; overload = 0; dimension [0] = img_rows (img); dimension [1] = img_columns (img); precedence [0] = 1; precedence [1] = 2; direction [0] = NULL; direction [1] = NULL; } /* Make a cbf version of the image */ a = clock (); /* Create the cbf */ cbf_failnez (cbf_make_handle (&cbf)) /* Make a new data block */ cbf_failnez (cbf_new_datablock (cbf, "image_1")) /* Make the _diffrn category */ cbf_failnez (cbf_new_category (cbf, "diffrn")) cbf_failnez (cbf_new_column (cbf, "id")) cbf_failnez (cbf_set_value (cbf, "DS1")) /* Make the _diffrn_source category */ cbf_failnez (cbf_new_category (cbf, "diffrn_source")) cbf_failnez (cbf_new_column (cbf, "diffrn_id")) cbf_failnez (cbf_set_value (cbf, "DS1")) cbf_failnez (cbf_new_column (cbf, "source")) cbf_failnez (cbf_set_value (cbf, "synchrotron")) cbf_failnez (cbf_new_column (cbf, "type")) cbf_failnez (cbf_set_value (cbf, "ssrl crystallography")) /* Make the _diffrn_radiation category */ cbf_failnez (cbf_new_category (cbf, "diffrn_radiation")) cbf_failnez (cbf_new_column (cbf, "diffrn_id")) cbf_failnez (cbf_set_value (cbf, "DS1")) cbf_failnez (cbf_new_column (cbf, "wavelength_id")) cbf_failnez (cbf_set_value (cbf, "L1")) /* Make the _diffrn_radiation_wavelength category */ cbf_failnez (cbf_new_category (cbf, "diffrn_radiation_wavelength")) cbf_failnez (cbf_new_column (cbf, "id")) cbf_failnez (cbf_set_value (cbf, "L1")) cbf_failnez (cbf_new_column (cbf, "wavelength")) if (wavelength) cbf_failnez (cbf_set_doublevalue (cbf, "%.4f", wavelength)) cbf_failnez (cbf_new_column (cbf, "wt")) cbf_failnez (cbf_set_value (cbf, "1.0")) /* Make the _diffrn_measurement category */ cbf_failnez (cbf_new_category (cbf, "diffrn_measurement")) cbf_failnez (cbf_new_column (cbf, "diffrn_id")) cbf_failnez (cbf_set_value (cbf, "DS1")) cbf_failnez (cbf_new_column (cbf, "method")) cbf_failnez (cbf_set_value (cbf, "oscillation")) cbf_failnez (cbf_new_column (cbf, "sample_detector_distance")) if (distance) cbf_failnez (cbf_set_doublevalue (cbf, "%.4f", distance)) /* Make the _diffrn_detector category */ cbf_failnez (cbf_new_category (cbf, "diffrn_detector")) cbf_failnez (cbf_new_column (cbf, "id")) cbf_failnez (cbf_set_value (cbf, detector_id)) cbf_failnez (cbf_new_column (cbf, "diffrn_id")) cbf_failnez (cbf_set_value (cbf, "DS1")) cbf_failnez (cbf_new_column (cbf, "type")) cbf_failnez (cbf_set_value (cbf, detector)) /* Make the _diffrn_detector_element category */ cbf_failnez (cbf_new_category (cbf, "diffrn_detector_element")) cbf_failnez (cbf_new_column (cbf, "id")) cbf_failnez (cbf_set_integervalue (cbf, 1)) cbf_failnez (cbf_new_column (cbf, "detector_id")) cbf_failnez (cbf_set_value (cbf, detector_id)) /* Make the _diffrn_frame_data category */ cbf_failnez (cbf_new_category (cbf, "diffrn_frame_data")) cbf_failnez (cbf_new_column (cbf, "id")) cbf_failnez (cbf_set_value (cbf, "frame_1")) cbf_failnez (cbf_new_column (cbf, "detector_element_id")) cbf_failnez (cbf_set_integervalue (cbf, 1)) cbf_failnez (cbf_new_column (cbf, "detector_id")) cbf_failnez (cbf_set_value (cbf, detector_id)) cbf_failnez (cbf_new_column (cbf, "array_id")) cbf_failnez (cbf_set_value (cbf, "image_1")) cbf_failnez (cbf_new_column (cbf, "binary_id")) cbf_failnez (cbf_set_integervalue (cbf, 1)) /* Make the _array_structure_list category */ cbf_failnez (cbf_new_category (cbf, "array_structure_list")) cbf_failnez (cbf_new_column (cbf, "array_id")) cbf_failnez (cbf_set_value (cbf, "image_1")) cbf_failnez (cbf_new_row (cbf)) cbf_failnez (cbf_set_value (cbf, "image_1")) cbf_failnez (cbf_new_column (cbf, "index")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_integervalue (cbf, 1)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_integervalue (cbf, 2)) cbf_failnez (cbf_new_column (cbf, "dimension")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_integervalue (cbf, dimension [0])) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_integervalue (cbf, dimension [1])) cbf_failnez (cbf_new_column (cbf, "precedence")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_integervalue (cbf, precedence [0])) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_integervalue (cbf, precedence [1])) cbf_failnez (cbf_new_column (cbf, "direction")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_value (cbf, direction [0])) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, direction [1])) /* Make the _array_element_size category */ cbf_failnez (cbf_new_category (cbf, "array_element_size")) cbf_failnez (cbf_new_column (cbf, "array_id")) cbf_failnez (cbf_set_value (cbf, "image_1")) cbf_failnez (cbf_new_row (cbf)) cbf_failnez (cbf_set_value (cbf, "image_1")) cbf_failnez (cbf_new_column (cbf, "index")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_integervalue (cbf, 1)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_integervalue (cbf, 2)) cbf_failnez (cbf_new_column (cbf, "size")) if (pixel_size > 0) { cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.1fe-6", pixel_size * 1e6)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.1fe-6", pixel_size * 1e6)) } /* Make the _array_intensities category */ cbf_failnez (cbf_new_category (cbf, "array_intensities")) cbf_failnez (cbf_new_column (cbf, "array_id")) cbf_failnez (cbf_set_value (cbf, "image_1")) cbf_failnez (cbf_new_column (cbf, "binary_id")) cbf_failnez (cbf_set_integervalue (cbf, 1)) cbf_failnez (cbf_new_column (cbf, "linearity")) cbf_failnez (cbf_set_value (cbf, "linear")) cbf_failnez (cbf_new_column (cbf, "gain")) if (gain) cbf_failnez (cbf_set_doublevalue (cbf, "%.3g", gain)) cbf_failnez (cbf_new_column (cbf, "overload")) if (overload) cbf_failnez (cbf_set_integervalue (cbf, overload)) cbf_failnez (cbf_new_column (cbf, "undefined")) cbf_failnez (cbf_set_integervalue (cbf, 0)) /* Make the _array_data category */ cbf_failnez (cbf_new_category (cbf, "array_data")) cbf_failnez (cbf_new_column (cbf, "array_id")) cbf_failnez (cbf_set_value (cbf, "image_1")) cbf_failnez (cbf_new_column (cbf, "binary_id")) cbf_failnez (cbf_set_integervalue (cbf, 1)) cbf_failnez (cbf_new_column (cbf, "data")) /* Save the binary data */ if (precedence[0] == 1) { cbf_failnez (cbf_set_integerarray_wdims_fs (cbf, compression, 1, img_pixelptr (img, 0, 0), sizeof (int), 1, img_rows (img) * img_columns (img), "little_endian",dimension[0],dimension[1],0,0 )) } else { cbf_failnez (cbf_set_integerarray_wdims_fs (cbf, compression, 1, img_pixelptr (img, 0, 0), sizeof (int), 1, img_rows (img) * img_columns (img), "little_endian",dimension[1],dimension[0],0,0 )) } /* Write the new file */ if (!imgout || strcmp(imgout?imgout:"","-") == 0) { out = stdout; } else { out = fopen (imgout, "w+b"); } if (!out) { if (encoding == ENC_NONE) { fprintf (stderr, "img2cif: Couldn't open the CBF file %s\n", imgout); } else { fprintf (stderr, "img2cif: Couldn't open the CIF file %s\n", imgout); } exit (1); } cbf_failnez (cbf_write_file (cbf, out, 1, cbforcif, mime | digest, encoding | bytedir | term)) /* Free the cbf */ cbf_failnez (cbf_free_handle (cbf)) b = clock (); if (encoding == ENC_NONE) { fprintf (stderr, "img2cif: Time to write the CBF image: %.3fs\n", ((b - a) * 1.0) / CLOCKS_PER_SEC); } else { fprintf (stderr, "img2cif: Time to write the CIF image: %.3fs\n", ((b - a) * 1.0) / CLOCKS_PER_SEC); } cbf_failnez (cbf_free_getopt_handle(opts)) /* Success */ return 0; } ./CBFlib-0.9.2.2/examples/cbf2adscimg_sub.c0000755000076500007650000005516111603702122016606 0ustar yayayaya/* $Id */ /********************************************************************** * cbf2adscimg_sub -- jiffy to read a CBF file and make an adsc (SMV) * * image file. * * * * Version 0.1 * * * * Chris Nielsen (cn@adsc-xray.com) * * * * Code starting point taken from cbfwrap.c * * * * cbfwrap.c: * * Harry Powell (harry@mrc-lmb.cam.ac.uk) * * developed from makecbf by * * Paul Ellis (ellis@ssrl.slac.stanford.edu) * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * The IUCr Policy * * on * * the Use of the Crystallographic Information File (CIF) * * * * The Crystallographic Information File (Hall, Allen & Brown, * * 1991) is, as of January 1992, the recommended method for * * submitting publications to Acta Crystallographica Section C. The * * International Union of Crystallography holds the Copyright on * * the CIF, and has applied for Patents on the STAR File syntax * * which is the basis for the CIF format. * * * * It is a principal objective of the IUCr to promote the use of * * CIF for the exchange and storage of scientific data. The IUCr's * * sponsorship of the CIF development was motivated by its * * responsibility to its scientific journals, which set the * * standards in crystallographic publishing. The IUCr intends that * * CIFs will be used increasingly for electronic submission of * * manuscripts to these journals in future. The IUCr recognises * * that, if the CIF and the STAR File are to be adopted as a means * * for universal data exchange, the syntax of these files must be * * strictly and uniformly adhered to. Even small deviations from * * the syntax would ultimately cause the demise of the universal * * file concept. Through its Copyrights and Patents the IUCr has * * taken the steps needed to ensure strict conformance with this * * syntax. * * * * The IUCr policy on the use of the CIF and STAR File processes is * * as follows: * * _________________________________________________________________ * * * * * 1 CIFs and STAR Files may be generated, stored or transmitted, * * without permission or charge, provided their purpose is not * * specifically for profit or commercial gain, and provided that * * the published syntax is strictly adhered to. * * * 2 Computer software may be developed for use with CIFs or STAR * * files, without permission or charge, provided it is distributed * * in the public domain. This condition also applies to software * * for which a charge is made, provided that its primary function * * is for use with files that satisfy condition 1 and that it is * * distributed as a minor component of a larger package of * * software. * * * 3 Permission will be granted for the use of CIFs and STAR Files * * for specific commercial purposes (such as databases or network * * exchange processes), and for the distribution of commercial * * CIF/STAR software, on written application to the IUCr Executive * * Secretary, 2 Abbey Square, Chester CH1 2HU, England. The * * nature, terms and duration of the licences granted will be * * determined by the IUCr Executive and Finance Committees. * * * * _________________________________________________________________ * * * * In summary, the IUCr wishes to promote the use of the STAR File * * concepts as a standard universal data file. It will insist on * * strict compliance with the published syntax for all * * applications. To assist with this compliance, the IUCr provides * * public domain software for checking the logical integrity of a * * CIF, and for validating the data name definitions contained * * within a CIF. Detailed information on this software, and the * * associated dictionaries, may be obtained from the IUCr Office at * * 5 Abbey Square, Chester CH1 2HU, England. * **********************************************************************/ #include "cbf.h" #include "cbf_simple.h" #include #include #include #include #include #undef cbf_failnez #define cbf_failnez(x) \ {int err; \ err = (x); \ if (err) { \ fprintf(stderr,"\nCBFlib fatal error %x \n",err); \ fprintf(stderr,"caused by call " #x "\n"); \ } \ } static char * array_id; void puthd (char* field, char* value, char* header) { char temp[6]; int i, diff; char *hp, *vp, *tp, *fp; /* * find the } marking the end of the information in the header */ for ( hp=header; *hp != '}'; hp++); /* * Write the field name starting at the position of the } */ for ( fp=field; *fp!=0; hp++, fp++) *hp = *fp; /* * The field and the values are seperated by an = sign */ *hp++ = '='; /* * Write the field name starting at the position of the } */ for ( vp=value; *vp!=0; hp++, vp++) *hp = *vp; /* * End this field with a ; and new line * and mark the end of the header with a } */ *hp++ = ';'; *hp++ = 10; *hp++ = '}'; /* * Make the header a multiple of 4 by padding with spaces */ i = (int) (hp-header); diff = 4 - i%4; if ( diff < 4 ) for (i=0; i= 1 && index <= 2) precedence[i-1] = index; cbf_failnez (cbf_find_column (cbf, "dimension")) cbf_failnez (cbf_get_integervalue (cbf, &dimension[i-1])) cbf_failnez (cbf_find_column (cbf, "direction")) cbf_failnez (cbf_get_value (cbf, &direction[i-1])) cbf_failnez (cbf_find_column (cbf, "array_id")) } if (dimension [0] == 0 || dimension [1] == 0) return (1); /* * If we locate the diffrn_frame_data.details column then * the header from the original image is stored there. * * This becomes the header of the output image without * modification. This could change, with CBF header items * duplicating original header items superceeding the * original SMV header values. */ make_smv_header_from_cbf = 0; if(NULL != header) { make_smv_header_from_cbf = 1; if(0 == cbf_find_category (cbf, "diffrn_frame_data") || 0 == cbf_find_category(cbf, "diffrn_data_frame")) { if(0 == cbf_find_column (cbf, "details")) { cbf_failnez(cbf_get_value (cbf, &smv_header)) if(0) fprintf(stdout,"Embedded SMV header in CBF header is:\n%s\n", smv_header); /* * Construct the SMV header directly from this item. */ if(NULL == (hp = strstr(smv_header, "HEADER_BYTES"))) { fprintf(stderr,"cbf2adscimg_sub: HEADER_BYTES not found in item diffrn_data_frame.details\n"); fprintf(stderr,"\tIt is assumed this item contains the original SMV image header.\n"); fprintf(stderr,"\tTry to reconstruct an SMV header from the CBF header items.\n"); } else { if (NULL == (hpequal = strstr(hp, "="))) { fprintf(stderr,"cbf2adscimg_sub: HEADER_BYTES value not found in item diffrn_data_frame.details\n"); fprintf(stderr,"\tIt is assumed this item contains the original SMV image header.\n"); fprintf(stderr,"\tTry to reconstruct an SMV header from the CBF header items.\n"); } else { sscanf(hpequal + 1, "%d", &header_length); if(0) fprintf(stdout,"header length decoded as: %d\n", header_length); if(NULL == (char_header = (char *) malloc(header_length))) { fprintf(stderr,"cbf2adscimg_sub: Error allocating %d bytes for header\n", header_length); return(1); } clrhd(char_header); hpe = ((char *) smv_header) + strlen(smv_header); while (hp && hp <= hpe && *hp && *hp != ';' && *hp != '\n' && *hp != '\r') hp++; while (hp && hp <= hpe && *hp && *hp != '\n' && *hp != '\r') hp++; if (hp && *hp == '\n') hp++; while(hp && hp <= hpe && *hp ) { int tokencnt, tokenstate; fps = hp; while (fps <= hpe && (isspace(*fps)||*fps=='#')) fps++; fpe = strstr(hp, "="); fpe--; vps = fpe + 2; vpe = strstr(hp, ";"); vpe--; for(i = tokencnt = tokenstate = 0, cp = fps; cp <= fpe; ) { if (isspace(*cp)) { tokenstate = 1; } else { if (tokenstate) tokencnt++; tokenstate = 0; } field[i++] = *cp++; } if (tokencnt > 0) break; field[i] = '\0'; for(i = 0, cp = vps; cp <= vpe; ) value[i++] = *cp++; value[i] = '\0'; puthd(field, value, char_header); padhd(char_header, 512); hp = vpe + 3; } if(0) fprintf(stdout,"Reconstructed header:\n%s\n", char_header); make_smv_header_from_cbf = 0; *header = char_header; } } } } } if(make_smv_header_from_cbf) { /* Detector */ if (cbf_find_category (cbf, "diffrn_detector") == 0) { cbf_failnez (cbf_find_column (cbf, "id")) cbf_failnez(cbf_get_value (cbf, &detector)) } /* Crystal to detector distance - obsolete, use diffrn_scan_axis detector_z if ((cbf_find_category (cbf, "diffrn_measurement") == 0) && (cbf_find_column (cbf, "sample_detector_distance") == 0) && (cbf_get_doublevalue (cbf, &distance) == 0) && (cbf_get_doublevalue (cbf, &distance) == 0) ) { cbf_double[1] = distance; } else { cbf_double[1] = -999.0; } */ /* hrp 18.01.2007 - new simple way to read header info, using CBFlib 0.7.6.1 + img.c/img.h*/ cbf_get_wavelength (cbf, &wavelength); /* if (cbf_find_category (cbf, "diffrn_radiation_wavelength") == 0) { cbf_failnez (cbf_find_column (cbf, "wavelength")) cbf_failnez(cbf_get_doublevalue (cbf, &wavelength)) } */ i = cbf_construct_detector (cbf, &this_detector, 0); fprintf(stdout, "return from cbf_construct_detector: %x (hex)\n", i); /* b_c[0],[1] slow and fast changing direction in pixels, [2],[3] in mm. */ cbf_get_beam_center (this_detector, &beam_centre [0], &beam_centre [1], &beam_centre [2], &beam_centre [3]); printf("beam centre values = %f %f %f %f\n", beam_centre [0], beam_centre [1], beam_centre [2], beam_centre [3]); cbf_get_detector_distance (this_detector, &distance); /* printf("distance from header is %f metres\n",cbf_double[1]); if ((cbf_find_category (cbf, "diffrn_scan_axis") == 0) && (cbf_find_column (cbf, "displacement_start") == 0) && (cbf_find_column (cbf, "SCAN1") == 0) && (cbf_get_doublevalue (cbf, &distance) == 0) && (cbf_get_doublevalue (cbf, &distance) == 0) ) { cbf_double[1] = distance; } else { cbf_double[1] = -999.0; } */ /* scan angle and size - assume PHI for the moment cbf_get_axis_setting (cbf, 0, "GONIOMETER_OMEGA", &phi_start, &phi_range); cbf_double[5] = phi_start; cbf_double[7] = phi_range; cbf_double[6] = phi_range + phi_start; printf("omega range is %f %f %f \n",cbf_double[5],cbf_double[6],cbf_double[7]); cbf_get_axis_setting (cbf, 0, "GONIOMETER_KAPPA", &phi_start, &phi_range); cbf_double[5] = phi_start; cbf_double[7] = phi_range; cbf_double[6] = phi_range + phi_start; printf("kappa range is %f %f %f \n",cbf_double[5],cbf_double[6],cbf_double[7]); */ cbf_get_axis_setting (cbf, 0, "GONIOMETER_PHI", &phi_start, &phi_range); /* printf("phi range is %f %f %f \n",cbf_double[5],cbf_double[6],cbf_double[7]); */ /* Pixel size(s) */ if (cbf_find_category (cbf, "array_element_size") == 0 ){ cbf_failnez (cbf_find_column (cbf, "index")) cbf_failnez (cbf_get_integervalue (cbf, &index)) cbf_failnez (cbf_find_column (cbf, "size")) cbf_failnez (cbf_get_doublevalue (cbf, &pixel_size)) cbf_failnez(cbf_next_row (cbf)) cbf_failnez (cbf_find_column (cbf, "index")) cbf_failnez (cbf_get_integervalue (cbf, &index)) cbf_failnez (cbf_find_column (cbf, "size")) cbf_failnez (cbf_get_doublevalue (cbf, &pixel_size)) } else { } /* other pixel information */ if (cbf_find_category (cbf, "array_intensities") == 0) { cbf_failnez (cbf_find_column (cbf, "gain")) cbf_failnez (cbf_get_doublevalue (cbf, &gain)) cbf_failnez (cbf_find_column (cbf, "overload")) cbf_failnez (cbf_get_integervalue (cbf, &overload)) } else { } /* Polarization of the incident radiation - daft definition at the moment so this code is serving only as a place-holder if (cbf_find_category (cbf, "diffrn_radiation_polarizn_ratio") == 0) { cbf_failnez (cbf_get_doublevalue (cbf, &polarrat)) cbf_double[8] = polarrat; cbf_failnez (cbf_find_column (cbf, "polarization_collimation")) cbf_failnez (cbf_get_value (cbf, &polarcoll)) strcpy(&cbf_char[6][0],polarcoll); } else { cbf_double[8] = -999.0; strcpy(cbf_char[6][0],"unspecified collimation"); } */ } /* * If the user has supplied NULL for data (return only header info) return. */ if(NULL == data) return(0); /* * Extract the data block. * * This routine allocates the memory needed to output the data. * The caller is responsible for freeing this memory after use. */ if(NULL == (uint_data = (unsigned int *) malloc(dimension[0] * dimension[1] * sizeof (unsigned int)))) { fprintf(stderr, "cbfhandle2img: Error allocating %lu bytes of memory for integer data image\n", (unsigned long)dimension[0] * dimension[1] * sizeof (unsigned int)); return(1); } if(NULL == (ushort_data = (unsigned short *) malloc(dimension[0] * dimension[1] * sizeof (unsigned short)))) { fprintf(stderr, "cbfhandle2img: Error allocating %lu bytes of memory for unsigned short data image\n", (unsigned long)dimension[0] * dimension[1] * sizeof (unsigned short)); return(1); } /* Find the binary data */ cbf_failnez (cbf_find_category (cbf, "array_data")) cbf_failnez (cbf_find_column (cbf, "array_id")) /* fprintf(stderr,"array id: %s\n",array_id); */ cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_find_row (cbf, array_id)) cbf_failnez (cbf_find_column (cbf, "data")) cbf_failnez (cbf_get_integerarray (cbf, &id, uint_data, sizeof(int), 1, dimension[0] * dimension[1], &nelem_read)) /* * first we need to decide which way round the image should be read into the * array. This depends on things like the precedence and direction */ if(strcmp (direction[0],"increasing") == 0){ dirsta[0] = dimension[0] - 1; dirend[0] = -1; dirinc[0] = -1; } else { dirsta[0] = 0; dirend[0] = dimension[0]; dirinc[0] = 1; } if(strcmp (direction[1],"increasing") == 0){ dirsta[1] = 0; dirend[1] = dimension[1]; dirinc[1] = 1; } else{ dirsta[1] = dimension[1]; dirend[1] = -1; dirinc[1] = -1; } if (precedence[0]==1){ first = 1; second = 0; } else{ first = 0; second = 1; } colrow = 0; up = ushort_data; ip = uint_data; k = dimension[0] * dimension[1]; for(i = 0; i < k; i++) *up++ = (unsigned short) (0x0000ffff & *ip++); *data = ushort_data; free(uint_data); /* Success */ return(0); } int cbf2adscimg_sub(char *filename, char **header, unsigned short **data) { FILE *in; cbf_handle cbf; int err; /* Create the cbf handle for the image file*/ cbf_failnez (cbf_make_handle (&cbf)) /* Read the file */ if (NULL == ( in = fopen (filename, "rb"))) { fprintf (stderr, " Couldn't open the CBF file %s\n", filename); return (1); } /* check for CBF format file */ if(1 == (err = (cbf_read_file (cbf, in, MSG_DIGESTNOW)))) return(1); err = cbfhandle2img_sub(cbf, header, data); cbf_failnez (cbf_free_handle (cbf)) return(err); } ./CBFlib-0.9.2.2/examples/cif2cbf.c0000644000076500007650000027015611603702122015067 0ustar yayayaya/********************************************************************** * cif2cbf -- convert a cif to a cbf file * * * * Version 0.9 04 August 2009 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * WHILE YOU MAY ALTERNATIVE DISTRIBUTE THE API UNDER THE LGPL * * YOU MAY ***NOT*** DISTRBUTE THIS PROGRAM UNDER THE LGPL * * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /********************************************************************** * SYNOPSIS * * * * cif2cbf [-i input_cif] [-o output_cbf] \ * * [-u update_cif ] \ * * [-b {f[orward]|b[ackwards]}] \ * * [-B {read|liberal|noread}] [-B {write|nowrite}] \ * * [-c {p[acked]|c[annonical]|{b[yte_offset]}|\ * * {v[2packed]}|{f[latpacked]}[n[one]}] \ * * [-C highclipvalue ] \ * * [-D ] \ * * [-d {d[igest]|n[odigest]|w[warndigest]} \ * * [-e {b[ase64]|k|q[uoted-printable]| \ * * d[ecimal]|h[exadecimal]|o[ctal]|n[one]}] \ * * [-I {0|2|4|8}] \ * * [-L lowclipvalue ] \ * * [-m {h[eaders]|n[oheaders]}] \ * * [-m {dim[ensions]|nod[imensions}] \ * * [-p {0|1|2|4}] \ * * [-R {0|4|8} \ * * [-S {read|noread}] [-S {write|nowrite}] \ * * [-T {read|noread}] [-T {write|nowrite}] \ * * [-v dictionary]* [-w] [-D]\ * * [input_cif] [output_cbf] * * * * the options are: * * * * -i input_cif (default: stdin) * * the input file in CIF or CBF format. If input_cif is not * * specified or is given as "-", it is copied from stdin to a * * temporary file. * * * * -o output_cbf (default: stdout) * * the output cif (if base64 or quoted-printable encoding is used) * * or cbf (if no encoding is used). if no output_cif is specified * * or is given as "-", the output is written to stdout * * if the output_cbf is /dev/null, no output is written. * * * * -u update_cif (no default) * * and optional second input file in CIF or CBF format containing * * data blocks to be merged with data blocks from the primary * * input CIF or CBF * * * * The remaining options specify the characteristics of the * * output cbf. Most of the characteristics of the input cif are * * derived from context, except when modified by the -B, -S, -T, -v * * and -w flags. * * * * -b byte_order (forward or backwards, default forward (1234) on * * little-endian machines, backwards (4321) on big-endian machines * * * * -B [no]read or liberal (default noread) * * read to enable reading of DDLm style brackets * * liberal to accept whitespace for commas * * * * -B [no]write (default write) * * write to enable writing of DDLm style brackets * * * * -c compression_scheme (packed, canonical, byte_offset, * * v2packed, flatpacked or none, * * default packed) * * * * -C highclipvalue * * specifies a double precision value to which to clip the data * * * * -d [no]digest or warndigest (default md5 digest [R. Rivest, * * RFC 1321, April 1992 using"RSA Data Security, Inc. MD5 * * Message-Digest Algorithm"] when MIME headers are selected) * * * * -D test cbf_construct_detector * * * * -e encoding (base64, k, quoted-printable or none, default base64) * * specifies one of the standard MIME encodings for an ascii cif * * or "none" for a binary cbf * * * * -I 0 or integer element size * * specifies integer conversion of the data, 0 to use the input * * number of bytes, 2, 4 or 8 for short, long or long long * * output integers * * * * -L lowclipvalue * * specifies a double precision value to cut off the data from * * below * * * * -m [no]headers (default headers) * * selects MIME (N. Freed, N. Borenstein, RFC 2045, November 1996) * * headers within binary data value text fields. * * * * -m [nod]imensions (default dimensions) * * selects detailed recovery of dimensions from the input CIF * * for use in the MIME header of the output CIF * * * * -p K_of_padding (0, 1, 2, 4) for no padding after binary data * * 1023, 2047 or 4095 bytes of padding after binary data * * * * -R 0 or integer element size * * specifies real conversion of the data, 0 to use the input * * number of bytes, 4 or 8 for float or double output reals * * * * * -S [no]read or (default noread) * * read to enable reading of whitespace and comments * * * * -S [no]write (default write) * * write to enable writing of whitespace and comments * * * * -T [no]read or (default noread) * * read to enable reading of DDLm style triple quotes * * * * -T [no]write (default write) * * write to enable writing of DDLm style triple quotes * * * * -v dictionary specifies a dictionary to be used to validate * * the input cif and to apply aliases to the output cif. * * This option may be specified multiple times, with dictionaries * * layered in the order given. * * * * -w process wide (2048 character) lines * * * * -W write wide (2048 character) lines * * * * * **********************************************************************/ /********************************************************************** * CREDITS * * * * This program is a Crystallographic Information File (CIF) * * application. Please see the IUCR Policy below. See the IUCR * * web page (http://www.iucr.org) or its mirrors for background * * and references on CIF. * * * * This program is a Crystallographic Binary File (CBF) application. * * Please see the ImgCIF/CBF web page at * * * * http://ndbserver.rutgers.edu/mmcif/cbf * * * * for background and references. The CBF definition is available * * on the web page created by Andy Hammersley at * * * * http://www.ersf.fr/computing/Forum/imgCIF/cbf_definition.html * * * * This program is a CBFlib application. See "CBFLIB, An ANSI-C * * API for Crystallographic Binary Files", Version 0.1, April 1998 * * by Paul J. Ellis, Stanford Synchrotron Radiation Laboratory, * * ellis@ssrl.slac.stanford.edu * * * * This program uses routines derived from mpack/munpack version * * 1.5, ftp://ftp.andrew.cmu.edu/pub/mpack by John G. Myers, * * jgm+@cmu.edu. "Mpack and munpack are utilties for encoding and * * decoding ... binary files in MIME ... format." Please see the * * copyright notices and disclaimers in the mpack/munpack routines * * * * This program uses routines derived from the "RSA Data Security, * * Inc. MD5 Message-Digest Algorithm." Please see the copyright * * notice and disclaimer in md5c.c * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term 'this software', as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #include "cbf.h" #include "cbf_simple.h" #include "img.h" #include "cbf_string.h" #include "cbf_copy.h" #include #include #include #include #include #include #include "cbf_getopt.h" #include #define C2CBUFSIZ 8192 #define NUMDICTS 50 #ifdef __MINGW32__ #define NOMKSTEMP #define NOTMPDIR #endif #define HDR_FINDDIMS 0x0040 /* On read, find header dims */ #define HDR_NOFINDDIMS 0x0080 /* On read, don't find header dims */ int local_exit (int status); int outerror(int err); int outerror(int err) { if ((err&CBF_FORMAT)==CBF_FORMAT) fprintf(stderr, " cif2cbf: The file format is invalid.\n"); if ((err&CBF_ALLOC)==CBF_ALLOC) fprintf(stderr, " cif2cbf Memory allocation failed.\n"); if ((err&CBF_ARGUMENT)==CBF_ARGUMENT) fprintf(stderr, " cif2cbf: Invalid function argument.\n"); if ((err&CBF_ASCII)==CBF_ASCII) fprintf(stderr, " cif2cbf: The value is ASCII (not binary).\n"); if ((err&CBF_BINARY)==CBF_BINARY) fprintf(stderr, " cif2cbf: The value is binary (not ASCII).\n"); if ((err&CBF_BITCOUNT)==CBF_BITCOUNT) fprintf(stderr, " cif2cbf: The expected number of bits does" " not match the actual number written.\n"); if ((err&CBF_ENDOFDATA)==CBF_ENDOFDATA) fprintf(stderr, " cif2cbf: The end of the data was reached" " before the end of the array.\n"); if ((err&CBF_FILECLOSE)==CBF_FILECLOSE) fprintf(stderr, " cif2cbf: File close error.\n"); if ((err&CBF_FILEOPEN)==CBF_FILEOPEN) fprintf(stderr, " cif2cbf: File open error.\n"); if ((err&CBF_FILEREAD)==CBF_FILEREAD) fprintf(stderr, " cif2cbf: File read error.\n"); if ((err&CBF_FILESEEK)==CBF_FILESEEK) fprintf(stderr, " cif2cbf: File seek error.\n"); if ((err&CBF_FILETELL)==CBF_FILETELL) fprintf(stderr, " cif2cbf: File tell error.\n"); if ((err&CBF_FILEWRITE)==CBF_FILEWRITE) fprintf(stderr, " cif2cbf: File write error.\n"); if ((err&CBF_IDENTICAL)==CBF_IDENTICAL) fprintf(stderr, " cif2cbf: A data block with the new name already exists.\n"); if ((err&CBF_NOTFOUND)==CBF_NOTFOUND) fprintf(stderr, " cif2cbf: The data block, category, column or" " row does not exist.\n"); if ((err&CBF_OVERFLOW)==CBF_OVERFLOW) fprintf(stderr, " cif2cbf: The number read cannot fit into the " "destination argument.\n The destination has been set to the nearest value.\n"); if ((err& CBF_UNDEFINED)==CBF_UNDEFINED) fprintf(stderr, " cif2cbf: The requested number is not defined (e.g. 0/0).\n"); if ((err&CBF_NOTIMPLEMENTED)==CBF_NOTIMPLEMENTED) fprintf(stderr, " cif2cbf: The requested functionality is not yet implemented.\n"); return 0; } #undef cbf_failnez #define cbf_failnez(x) \ {int err; \ err = (x); \ if (err) { \ fprintf(stderr,"CBFlib fatal error %d\n",err); \ outerror(err); \ local_exit (-1); \ } \ } void set_MP_terms(int crterm, int nlterm); int main (int argc, char *argv []) { FILE *in, *out=NULL, *update=NULL, *file, *dict; clock_t a,b; cbf_handle cif; cbf_handle ucif; cbf_handle cbf; cbf_handle dic; cbf_handle odic; cbf_getopt_handle opts; int devnull = 0; int c; int errflg = 0; const char *cifin, *cbfout, *updatecif; const char *dictionary[NUMDICTS]; int dqrflags[NUMDICTS]; char *ciftmp=NULL; #ifndef NOMKSTEMP int ciftmpfd; #endif int ciftmpused; int padflag; int dimflag; int nbytes; int ndict = 0; int kd; int wide = 0; int Wide = 0; int IorR = 0; int nelsize; int testconstruct; char buf[C2CBUFSIZ]; unsigned int blocks, categories, blocknum, catnum, blockitems, itemnum; CBF_NODETYPE itemtype; const char *datablock_name; const char *saveframe_name; const char *category_name; const char *column_name; const char *value; unsigned int colnum, rownum; unsigned int columns; unsigned int rows; double cliphigh, cliplow; int mime, digest, encoding, compression, bytedir, cbforcif, term; int qrflags, qwflags; const char * optarg; /* Extract options */ /********************************************************************** * cif2cbf [-i input_cif] [-o output_cbf] \ * * [-u update_cif] \ * * [-b {b[ackwards]|f[orwards]}] \ * * [-B {read|liberal|noread}] [-B {write|nowrite}] \ * * [-c {p[acked]|c[annonical]|{b[yte_offset]}|\ * * {v[2packed]}|{f[latpacked]}[n[one]}] \ * * [-C highclipvalue] \ * * [-d {d[igest]|n[odigest]|w[arndigest]} \ * * [-D ] \ * * [-e {b[ase64]|k|q[uoted-printable]| \ * * d[ecimal]|h[exadecimal]|o[ctal]|n[one]}] \ * * [-I {0|2|4|8}] \ * * [-L lowclipvalue ] \ * * [-m {h[eaders]|noh[eaders]}] \ * * [-m {d[imensions]|nod[imensions}] \ * * [-R {0|4|8}] \ * * [-S {read|noread}] [-S {write|nowrite}] \ * * [-T {read|noread}] [-T {write|nowrite}] \ * * [-p {0|1|2|4}] \ * * [-v dictionary]* [-w] [-W] \ * * [input_cif] [output_cbf] * * * **********************************************************************/ mime = 0; digest = 0; encoding = 0; compression = 0; bytedir = 0; ndict = 0; padflag = 0; qrflags = qwflags = 0; dimflag = 0; nelsize = 0; cifin = NULL; cbfout = NULL; updatecif = NULL; ciftmpused = 0; testconstruct = 0; cliphigh = cliplow = 0.; cbf_failnez(cbf_make_getopt_handle(&opts)) cbf_failnez(cbf_getopt_parse(opts, argc, argv, "-i(input):" \ "o(output):" \ "u(update):" \ "b(byte-direction):" \ "B(parse-brackets):" \ "c(compression):" \ "C(cliphigh):" \ "D(test-construct-detector)" \ "d(digest):" \ "e(encoding):" \ "I(integer):" \ "L(cliplow):" \ "m(mime-header):" \ "p(pad):" \ "P(parse-level):" \ "R(real):" \ "S(white-space):" \ "T(treble-quotes):" \ "v(validation-dictionary):" \ "w(read-wide)" \ "W(write-wide)" \ )) if (!cbf_rewind_getopt_option(opts)) for(;!cbf_get_getopt_data(opts,&c,NULL,NULL,&optarg);cbf_next_getopt_option(opts)) { if (!c) break; switch (c) { case 'i': /* input file */ if (cifin) errflg++; else cifin = optarg; break; case 'o': /* output file */ if (cbfout) errflg++; else cbfout = optarg; break; case 'u': /* update file */ if (updatecif) errflg++; else updatecif = optarg; break; case 'b': /* byte order */ if (bytedir) errflg++; if (optarg[0] == 'f' || optarg[0] == 'F') { bytedir = ENC_FORWARD; } else { if (optarg[0] == 'b' || optarg[0] == 'B' ) { bytedir = ENC_BACKWARD; } else { errflg++; } } break; case 'B': if (!strcmp(optarg,"cif20read")) { qrflags &= ~CBF_PARSE_BRACKETS; qrflags |= CBF_PARSE_BRC; } else if (!strcmp(optarg,"nocif20read")) { qrflags &= ~CBF_PARSE_BRACKETS; } else if (!strcmp(optarg,"cif20write")) { qwflags &= ~CBF_PARSE_BRACKETS; qwflags |= CBF_PARSE_BRC; } else if (!strcmp(optarg,"nocif20write")) { qwflags &= ~CBF_PARSE_BRACKETS; } else if (!strcmp(optarg,"read")) { qrflags |= CBF_PARSE_BRACKETS; } else if (!strcmp(optarg,"noread")) { qrflags &= ~CBF_PARSE_BRACKETS; } else if (!strcmp(optarg,"write")) { qwflags |= CBF_PARSE_BRACKETS; } else if (!strcmp(optarg,"nowrite")) { qwflags &= ~CBF_PARSE_BRACKETS; } else errflg++; break; case 'c': if (compression) errflg++; if (optarg[0] == 'p' || optarg[0] == 'P') { compression = CBF_PACKED; } else { if (optarg[0] == 'c' || optarg[0] == 'C') { compression = CBF_CANONICAL; } else { if (optarg[0] == 'b' || optarg[0] == 'B') { compression = CBF_BYTE_OFFSET; } else { if (optarg[0] == 'n' || optarg[0] == 'N') { compression = CBF_NONE; } else { if (optarg[0] == 'v' || optarg[0] == 'V') { compression = CBF_PACKED_V2; } else { if (optarg[0] == 'f' || optarg[0] == 'F') { compression = CBF_PACKED|CBF_FLAT_IMAGE; } else { errflg++; } } } } } } break; case 'C': cliphigh = atof(optarg); break; case 'd': if (digest) errflg++; if (optarg[0] == 'd' || optarg[0] == 'H' ) { digest = MSG_DIGEST; } else { if (optarg[0] == 'n' || optarg[0] == 'N' ) { digest = MSG_NODIGEST; } else { if (optarg[0] == 'w' || optarg[0] == 'W' ) { digest = MSG_DIGESTWARN; } else { errflg++; } } } break; case 'D': /* test construct_detector */ if (testconstruct) errflg++; else testconstruct = 1; break; case 'e': if (encoding) errflg++; if (optarg[0] == 'b' || optarg[0] == 'B' ) { encoding = ENC_BASE64; } else { if (optarg[0] == 'k' || optarg[0] == 'K' ) { encoding = ENC_BASE32K; } else { if (optarg[0] == 'q' || optarg[0] == 'Q' ) { encoding = ENC_QP; } else { if (optarg[0] == 'd' || optarg[0] == 'D' ) { encoding = ENC_BASE10; } else { if (optarg[0] == 'h' || optarg[0] == 'H' ) { encoding = ENC_BASE16; } else { if (optarg[0] == 'o' || optarg[0] == 'O' ) { encoding = ENC_BASE8; } else { if (optarg[0] == 'n' || optarg[0] == 'N' ) { encoding = ENC_NONE; } else { errflg++; } } } } } } } break; case 'I': if (IorR) errflg++; IorR = CBF_CPY_SETINTEGER; nelsize = atoi(optarg); if (nelsize != 0 && nelsize != 1 && nelsize !=2 && nelsize !=4 && nelsize != 8) errflg++; break; case 'L': cliplow = atof(optarg); break; case 'm': if (optarg[0] == 'h' || optarg[0] == 'H' ) { if (mime) errflg++; mime = MIME_HEADERS; } else if (optarg[0] == 'd' || optarg[0] == 'D' ) { if (dimflag) errflg++; dimflag = HDR_FINDDIMS; } else if (optarg[0] == 'n' || optarg[0] == 'N' ) { if (!strncasecmp(optarg,"noh",3) ){ if (mime) errflg++; mime = PLAIN_HEADERS; } else if (!strncasecmp(optarg,"nod",3)) { if (dimflag) errflg++; dimflag = HDR_NOFINDDIMS; } else { errflg++; } } else { errflg++; } break; case 'p': if (padflag) errflg++; if (optarg[0] == '1') { padflag = PAD_1K; } else if (optarg[0] == '2'){ padflag = PAD_2K; } else if (optarg[0] == '4'){ padflag = PAD_4K; } else errflg++; break; case 'P': /* Parse level */ if (!strcmp(optarg,"cif20read")) { qrflags &= ~(CBF_PARSE_BRACKETS|CBF_PARSE_TQ|CBF_PARSE_CIF2_DELIMS|CBF_PARSE_WIDE|CBF_PARSE_UTF8); qrflags |= CBF_PARSE_BRC|CBF_PARSE_TQ|CBF_PARSE_CIF2_DELIMS|CBF_PARSE_WIDE|CBF_PARSE_UTF8; } else if (!strcmp(optarg,"cif20write")) { qwflags &= ~(CBF_PARSE_BRACKETS|CBF_PARSE_TQ|CBF_PARSE_CIF2_DELIMS|CBF_PARSE_WIDE|CBF_PARSE_UTF8); qwflags |= CBF_PARSE_BRC|CBF_PARSE_TQ|CBF_PARSE_CIF2_DELIMS|CBF_PARSE_WIDE|CBF_PARSE_UTF8; } else if (!strcmp(optarg,"oldddlmread")) { qrflags &= ~(CBF_PARSE_BRACKETS|CBF_PARSE_TQ|CBF_PARSE_CIF2_DELIMS|CBF_PARSE_WIDE|CBF_PARSE_UTF8); qrflags |= CBF_PARSE_BRACKETS|CBF_PARSE_WIDE; } else if (!strcmp(optarg,"oldddlmwrite")) { qwflags &= ~(CBF_PARSE_BRACKETS|CBF_PARSE_TQ|CBF_PARSE_CIF2_DELIMS|CBF_PARSE_WIDE|CBF_PARSE_UTF8); qwflags |= CBF_PARSE_BRACKETS|CBF_PARSE_WIDE; } if (!strcmp(optarg,"cif11read")) { qrflags &= ~(CBF_PARSE_BRACKETS|CBF_PARSE_TQ|CBF_PARSE_CIF2_DELIMS|CBF_PARSE_WIDE|CBF_PARSE_UTF8); qrflags |= CBF_PARSE_WIDE; } else if (!strcmp(optarg,"cif11write")) { qwflags &= ~(CBF_PARSE_BRACKETS|CBF_PARSE_TQ|CBF_PARSE_CIF2_DELIMS|CBF_PARSE_WIDE|CBF_PARSE_UTF8); qwflags |= CBF_PARSE_WIDE; } else if (!strcmp(optarg,"cif10read")) { qrflags &= ~(CBF_PARSE_BRACKETS|CBF_PARSE_TQ|CBF_PARSE_CIF2_DELIMS|CBF_PARSE_WIDE|CBF_PARSE_UTF8); } else if (!strcmp(optarg,"cif10write")) { qwflags &= ~(CBF_PARSE_BRACKETS|CBF_PARSE_TQ|CBF_PARSE_CIF2_DELIMS|CBF_PARSE_WIDE|CBF_PARSE_UTF8); } else errflg++; break; case 'R': if (IorR) errflg++; IorR = CBF_CPY_SETREAL; nelsize = atoi(optarg); if (nelsize != 0 && nelsize !=4 && nelsize != 8) errflg++; break; case 'S': /* Parse whitespace */ if (!strcmp(optarg,"read")) { qrflags |= CBF_PARSE_WS; } else if (!strcmp(optarg,"noread")) { qrflags &= CBF_PARSE_WS; } else if (!strcmp(optarg,"write")) { qwflags |= CBF_PARSE_WS; } else if (!strcmp(optarg,"nowrite")) { qwflags &= CBF_PARSE_WS; } else errflg++; break; case 'T': /* Parse treble quotes */ if (!strcmp(optarg,"read")) { qrflags |= CBF_PARSE_TQ; } else if (!strcmp(optarg,"noread")) { qrflags &= ~CBF_PARSE_TQ; } else if (!strcmp(optarg,"write")) { qwflags |= CBF_PARSE_TQ; } else if (!strcmp(optarg,"nowrite")) { qwflags &= ~CBF_PARSE_TQ; } else errflg++; break; case 'v': /* validate against dictionary */ if (ndict < NUMDICTS) { dqrflags[ndict] = qrflags; dictionary[ndict++] = optarg; } else if (ndict == NUMDICTS) { errflg++; ndict++; fprintf(stderr, " Too many dictionaries, increase NUMDICTS"); } break; case 'w': /* read wide files */ if (wide) errflg++; else wide = 1; break; case 'W': /* write wide files */ if (Wide) errflg++; else Wide = 1; break; default: errflg++; break; } } for(;!cbf_get_getopt_data(opts,&c,NULL,NULL,&optarg);cbf_next_getopt_option(opts)) { if (!cifin) { cifin = optarg; } else { if (!cbfout) { cbfout = optarg; } else { errflg++; } } } if (errflg) { fprintf(stderr,"cif2cbf: Usage: \n"); fprintf(stderr, " cif2cbf [-i input_cif] [-o output_cbf] \\\n"); fprintf(stderr, " [-u update_cif] \\\n"); fprintf(stderr, " [-c {p[acked]|c[annonical]|{b[yte_offset]}|\\\n"); fprintf(stderr, " {v[2packed}|{f[latpacked}[n[one]}] \\\n"); fprintf(stderr, " [-C highclipvalue] \\\n"); fprintf(stderr, " [-D ] \\\n"); fprintf(stderr, " [-I {0|2|4|8}] \\\n"); fprintf(stderr, " [-R {0|4|8}] \\\n"); fprintf(stderr, " [-L {0|4|8}] \\\n"); fprintf(stderr, " [-m {h[eaders]|noh[eaders]}] \\\n"); fprintf(stderr, " [-m {d[imensions]|nod[imensions}] \\\n"); fprintf(stderr, " [-d {d[igest]|n[odigest]|w[arndigest]}] \\\n"); fprintf(stderr, " [-B {read|liberal|noread}] [-B {write|nowrite}] \\\n"); fprintf(stderr, " [-S {read|noread}] [-S {write|nowrite}] \\\n"); fprintf(stderr, " [-T {read|noread}] [-T {write|nowrite}] \\\n"); fprintf(stderr, " [-e {b[ase64]|q[uoted-printable]|\\\n"); fprintf(stderr, " d[ecimal]|h[examdecimal|o[ctal]|n[one]}] \\\n"); fprintf(stderr, " [-b {f[orward]|b[ackwards]}\\\n"); fprintf(stderr, " [-p {1|2|4}\\\n"); fprintf(stderr, " [-v dictionary]* [-w] [-W]\\\n"); fprintf(stderr, " [input_cif] [output_cbf] \n\n"); exit(2); } /* Set up for CIF of CBF output */ if (!encoding) { encoding = ENC_BASE64; } cbforcif = CBF; term = ENC_CRTERM | ENC_LFTERM; if (encoding == ENC_BASE64 || \ encoding == ENC_BASE32K || \ encoding == ENC_QP || \ encoding == ENC_BASE10 || \ encoding == ENC_BASE16 || \ encoding == ENC_BASE8) { cbforcif = CIF; term = ENC_LFTERM; } /* Set up for headers */ if (!mime) { mime = MIME_HEADERS; } if (!digest) { if (mime == MIME_HEADERS) { digest = MSG_DIGEST; } else { digest = MSG_NODIGEST; } } if (!dimflag) dimflag = HDR_FINDDIMS; /* Set up for decimal, hexadecimal or octal output */ if (!bytedir) bytedir = ENC_BACKWARD; /* Set up for Compression */ if (!compression) compression = CBF_PACKED; /* Read the cif */ if (!cifin || strcmp(cifin?cifin:"","-") == 0) { ciftmp = (char *)malloc(strlen("/tmp/cif2cbfXXXXXX")+1); #ifdef NOTMPDIR strcpy(ciftmp, "cif2cbfXXXXXX"); #else strcpy(ciftmp, "/tmp/cif2cbfXXXXXX"); #endif #ifdef NOMKSTEMP if ((ciftmp = mktemp(ciftmp)) == NULL ) { fprintf(stderr,"\n cif2cbf: Can't create temporary file name %s.\n", ciftmp); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } if ( (file = fopen(ciftmp,"wb+")) == NULL) { fprintf(stderr,"Can't open temporary file %s.\n", ciftmp); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } #else if ((ciftmpfd = mkstemp(ciftmp)) == -1 ) { fprintf(stderr,"\n cif2cbf: Can't create temporary file %s.\n", ciftmp); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } if ( (file = fdopen(ciftmpfd, "w+")) == NULL) { fprintf(stderr,"Can't open temporary file %s.\n", ciftmp); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } #endif while ((nbytes = fread(buf, 1, C2CBUFSIZ, stdin))) { if(nbytes != fwrite(buf, 1, nbytes, file)) { fprintf(stderr,"Failed to write %s.\n", ciftmp); exit(1); } } fclose(file); cifin = ciftmp; ciftmpused = 1; } if ( cbf_make_handle (&cif) ) { fprintf(stderr,"Failed to create handle for input_cif\n"); exit(1); } if ( cbf_make_handle (&dic) ) { fprintf(stderr,"Failed to create handle for dictionary\n"); exit(1); } if ( cbf_make_handle (&cbf) ) { fprintf(stderr,"Failed to create handle for output_cbf\n"); exit(1); } if ( cbf_make_handle (&ucif) ) { fprintf(stderr,"Failed to create handle for update_cif\n"); exit(1); } for (kd=0; kd< ndict; kd++) { if (!(dict = fopen (dictionary[kd], "rb"))) { fprintf (stderr,"Couldn't open the dictionary %s\n", dictionary[kd]); exit (1); } cbf_failnez(cbf_read_widefile(dic, dict, MSG_DIGEST|dqrflags[kd])) cbf_failnez(cbf_convert_dictionary(cif,dic)) cbf_failnez(cbf_get_dictionary(cif,&odic)) cbf_failnez(cbf_set_dictionary(cbf,odic)) } a = clock (); /* Read the file */ if (!(in = fopen (cifin, "rb"))) { fprintf (stderr,"Couldn't open the input CIF file %s\n", cifin); exit (1); } if (ciftmpused) { if (unlink(ciftmp) != 0 ) { fprintf(stderr,"cif2cif: Can't unlink temporary file %s.\n", ciftmp); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } } if (!wide) { cbf_failnez (cbf_read_file (cif, in, MSG_DIGEST|qrflags|(digest&MSG_DIGESTWARN))) } else { cbf_failnez (cbf_read_widefile (cif, in, MSG_DIGEST|qrflags|(digest&MSG_DIGESTWARN))) } cbf_failnez (cbf_rewind_datablock(cif)) cbf_failnez (cbf_count_datablocks(cif, &blocks)) for (blocknum = 0; blocknum < blocks; blocknum++ ) { /* start of copy loop */ cbf_failnez (cbf_select_datablock(cif, blocknum)) cbf_failnez (cbf_datablock_name(cif, &datablock_name)) cbf_failnez (cbf_force_new_datablock(cbf, datablock_name)) if ( !cbf_rewind_blockitem(cif, &itemtype) ) { cbf_failnez (cbf_count_blockitems(cif, &blockitems)) for (itemnum = 0; itemnum < blockitems; itemnum++) { cbf_select_blockitem(cif, itemnum, &itemtype); if (itemtype == CBF_CATEGORY) { cbf_category_name(cif,&category_name); cbf_force_new_category(cbf, category_name); cbf_count_rows(cif,&rows); cbf_count_columns(cif,&columns); /* Transfer the columns names from cif to cbf */ if ( ! cbf_rewind_column(cif) ) { do { cbf_failnez(cbf_column_name(cif, &column_name)) cbf_failnez(cbf_new_column(cbf, column_name)) } while ( ! cbf_next_column(cif) ); cbf_rewind_column(cif); cbf_rewind_row(cif); } /* Transfer the rows from cif to cbf */ for (rownum = 0; rownum < rows; rownum++ ) { cbf_failnez (cbf_select_row(cif, rownum)) cbf_failnez (cbf_new_row(cbf)) cbf_rewind_column(cif); for (colnum = 0; colnum < columns; colnum++ ) { const char *typeofvalue; cbf_failnez (cbf_select_column(cif, colnum)) cbf_failnez (cbf_column_name(cif, &column_name)) if ( ! cbf_get_value(cif, &value) ) { if (compression && value && column_name && !cbf_cistrcmp("compression_type",column_name)) { cbf_failnez (cbf_select_column(cbf, colnum)) switch (compression&CBF_COMPRESSION_MASK) { case (CBF_NONE): cbf_failnez (cbf_set_value (cbf,"none")) cbf_failnez (cbf_set_typeofvalue(cbf,"word")) break; case (CBF_CANONICAL): cbf_failnez (cbf_set_value (cbf,"canonical")) cbf_failnez (cbf_set_typeofvalue(cbf,"word")) break; case (CBF_PACKED): cbf_failnez (cbf_set_value (cbf,"packed")) cbf_failnez (cbf_set_typeofvalue(cbf,"word")) break; case (CBF_PACKED_V2): cbf_failnez (cbf_set_value (cbf,"packed_v2")) cbf_failnez (cbf_set_typeofvalue(cbf,"word")) break; case (CBF_BYTE_OFFSET): cbf_failnez (cbf_set_value (cbf,"byte_offsets")) cbf_failnez (cbf_set_typeofvalue(cbf,"word")) break; case (CBF_PREDICTOR): cbf_failnez (cbf_set_value (cbf,"predictor")) cbf_failnez (cbf_set_typeofvalue(cbf,"word")) break; default: cbf_failnez (cbf_set_value (cbf,".")) cbf_failnez (cbf_set_typeofvalue(cbf,"null")) break; } if (compression&CBF_FLAG_MASK) { if (compression&CBF_UNCORRELATED_SECTIONS) { cbf_failnez (cbf_require_column (cbf, "compression_type_flag")) cbf_failnez (cbf_set_value (cbf, "uncorrelated_sections")) cbf_failnez (cbf_set_typeofvalue (cbf, "word")) } else if (compression&CBF_FLAT_IMAGE) { cbf_failnez (cbf_require_column (cbf, "compression_type_flag")) cbf_failnez (cbf_set_value (cbf, "flat")) cbf_failnez (cbf_set_typeofvalue (cbf, "word")) } } else { if (!cbf_find_column(cbf, "compression_type_flag")) { cbf_failnez (cbf_set_value (cbf,".")) cbf_failnez (cbf_set_typeofvalue(cbf,"null")) } } } else if (compression && value && column_name && !cbf_cistrcmp("compression_type_flag",column_name)) { if (compression&CBF_FLAG_MASK) { if (compression&CBF_UNCORRELATED_SECTIONS) { cbf_failnez (cbf_require_column (cbf, "compression_type_flag")) cbf_failnez (cbf_set_value (cbf, "uncorrelated_sections")) cbf_failnez (cbf_set_typeofvalue (cbf, "word")) } else if (compression&CBF_FLAT_IMAGE) { cbf_failnez (cbf_require_column (cbf, "compression_type_flag")) cbf_failnez (cbf_set_value (cbf, "flat")) cbf_failnez (cbf_set_typeofvalue (cbf, "word")) } } else { if (!cbf_find_column(cbf, "compression_type_flag")) { cbf_failnez (cbf_set_value (cbf,".")) cbf_failnez (cbf_set_typeofvalue(cbf,"null")) } } } else { cbf_failnez (cbf_get_typeofvalue(cif, &typeofvalue)) cbf_failnez (cbf_select_column(cbf, colnum)) cbf_failnez (cbf_set_value(cbf, value)) cbf_failnez (cbf_set_typeofvalue(cbf, typeofvalue)) } } else { void * array; int binary_id, elsigned, elunsigned; size_t elements,elements_read, elsize; int minelement, maxelement; unsigned int cifcompression; int realarray; const char *byteorder; size_t dim1, dim2, dim3, padding; cbf_failnez(cbf_get_arrayparameters_wdims_fs( cif, &cifcompression, &binary_id, &elsize, &elsigned, &elunsigned, &elements, &minelement, &maxelement, &realarray, &byteorder, &dim1, &dim2, &dim3, &padding)) if ((array=malloc(elsize*elements))) { cbf_failnez (cbf_select_column(cbf,colnum)) if (!realarray) { cbf_failnez (cbf_get_integerarray( cif, &binary_id, array, elsize, elsigned, elements, &elements_read)) if (dimflag == HDR_FINDDIMS && dim1==0) { cbf_get_arraydimensions(cif,NULL,&dim1,&dim2,&dim3); } if (IorR == 0 || (IorR == CBF_CPY_SETINTEGER && (nelsize==elsize||nelsize==0))) { cbf_failnez(cbf_set_integerarray_wdims_fs( cbf, compression, binary_id, array, elsize, elsigned, elements, "little_endian", dim1, dim2, dim3, 0)) } else { cbf_failnez(cbf_copy_value(cbf,cif,category_name,column_name,rownum,compression,dimflag,IorR, nelsize?nelsize:elsize,0,cliplow,cliphigh)) } } else { cbf_failnez (cbf_get_realarray( cif, &binary_id, array, elsize, elements, &elements_read)) if (dimflag == HDR_FINDDIMS && dim1==0) { cbf_get_arraydimensions(cif,NULL,&dim1,&dim2,&dim3); } if (IorR == 0 || (IorR == CBF_CPY_SETREAL && (nelsize==elsize||nelsize==0))) { cbf_failnez(cbf_set_realarray_wdims_fs( cbf, compression, binary_id, array, elsize, elements, "little_endian", dim1, dim2, dim3, 0)) } else { cbf_failnez(cbf_copy_value(cbf,cif,category_name,column_name,rownum,compression,dimflag,IorR, nelsize?nelsize:elsize,CBF_CPY_SETSIGNED,cliplow,cliphigh)) } } free(array); } else { fprintf(stderr, "\nFailed to allocate memory %ld bytes", (long) elsize*elements); exit(1); } } } } } else { cbf_saveframe_name(cif,&saveframe_name); cbf_force_new_saveframe(cbf, saveframe_name); if ( !cbf_rewind_category(cif) ) { cbf_failnez (cbf_count_categories(cif, &categories)) for (catnum = 0; catnum < categories; catnum++) { cbf_select_category(cif, catnum); cbf_category_name(cif,&category_name); cbf_force_new_category(cbf, category_name); cbf_count_rows(cif,&rows); cbf_count_columns(cif,&columns); /* Transfer the columns names from cif to cbf */ if ( ! cbf_rewind_column(cif) ) { do { cbf_failnez(cbf_column_name(cif, &column_name)) cbf_failnez(cbf_new_column(cbf, column_name)) } while ( ! cbf_next_column(cif) ); cbf_rewind_column(cif); cbf_rewind_row(cif); } /* Transfer the rows from cif to cbf */ for (rownum = 0; rownum < rows; rownum++ ) { cbf_failnez (cbf_select_row(cif, rownum)) cbf_failnez (cbf_new_row(cbf)) cbf_rewind_column(cif); for (colnum = 0; colnum < columns; colnum++ ) { const char *typeofvalue; cbf_failnez (cbf_select_column(cif, colnum)) if ( ! cbf_get_value(cif, &value) ) { cbf_failnez (cbf_get_typeofvalue(cif, &typeofvalue)) cbf_failnez (cbf_select_column(cbf, colnum)) cbf_failnez (cbf_set_value(cbf, value)) cbf_failnez (cbf_set_typeofvalue(cbf, typeofvalue)) } else { void * array; int binary_id, elsigned, elunsigned; size_t elements,elements_read, elsize; int minelement, maxelement; unsigned int cifcompression; int realarray; const char * byteorder; size_t dim1, dim2, dim3, padding; cbf_failnez(cbf_get_arrayparameters_wdims_fs( cif, &cifcompression, &binary_id, &elsize, &elsigned, &elunsigned, &elements, &minelement, &maxelement, &realarray, &byteorder, &dim1, &dim2, &dim3, &padding)) if ((array=malloc(elsize*elements))) { cbf_failnez (cbf_select_column(cbf,colnum)) if (!realarray) { cbf_failnez (cbf_get_integerarray( cif, &binary_id, array, elsize, elsigned, elements, &elements_read)) cbf_failnez(cbf_set_integerarray_wdims_fs( cbf, compression, binary_id, array, elsize, elsigned, elements, byteorder, dim1, dim2, dim3, padding)) } else { cbf_failnez (cbf_get_realarray( cif, &binary_id, array, elsize, elements, &elements_read)) if (dimflag == HDR_FINDDIMS && dim1==0) { cbf_get_arraydimensions(cif,NULL,&dim1,&dim2,&dim3); } cbf_failnez(cbf_set_realarray_wdims_fs( cbf, compression, binary_id, array, elsize, elements, byteorder, dim1, dim2, dim3, padding)) } free(array); } else { fprintf(stderr, "\nFailed to allocate memory %ld bytes", (long) elsize*elements); exit(1); } } } } } } } } } } b = clock (); fprintf (stderr, " Time to read input_cif: %.3fs\n", ((b - a) * 1.0) / CLOCKS_PER_SEC); /* Read the update file, if any */ if (updatecif) { if (!(update = fopen (updatecif, "rb"))) { fprintf (stderr,"Couldn't open the update CIF file %s\n", updatecif); exit (1); } cbf_failnez (cbf_read_widefile (ucif, update, MSG_DIGEST|qrflags|(digest&MSG_DIGESTWARN))) cbf_failnez (cbf_rewind_datablock(ucif)) cbf_failnez (cbf_count_datablocks(ucif, &blocks)) for (blocknum = 0; blocknum < blocks; blocknum++ ) { /* start of merge loop */ cbf_failnez (cbf_select_datablock(ucif, blocknum)) cbf_failnez (cbf_datablock_name(ucif, &datablock_name)) /* either this is a new datablock, in which case we copy it or it has the same name as an existing datablock, in which case we merge it */ cbf_failnez (cbf_require_datablock(cbf, datablock_name)) if ( !cbf_rewind_blockitem(ucif, &itemtype) ) { cbf_failnez (cbf_count_blockitems(ucif, &blockitems)) for (itemnum = 0; itemnum < blockitems; itemnum++) { cbf_select_blockitem(ucif, itemnum, &itemtype); if (itemtype == CBF_CATEGORY) { cbf_category_name(ucif,&category_name); cbf_require_category(cbf, category_name); cbf_count_rows(ucif,&rows); cbf_count_columns(ucif,&columns); /* Transfer the columns names from ucif to cbf */ if ( ! cbf_rewind_column(ucif) ) { do { cbf_failnez(cbf_column_name(ucif, &column_name)) cbf_failnez(cbf_require_column(cbf, column_name)) } while ( ! cbf_next_column(ucif) ); cbf_rewind_column(ucif); cbf_rewind_row(ucif); } /* Transfer the rows from ucif to cbf */ for (rownum = 0; rownum < rows; rownum++ ) { cbf_failnez (cbf_select_row(ucif, rownum)) if (cbf_select_row(cbf,rownum)){ cbf_failnez (cbf_new_row(cbf)) } cbf_rewind_column(ucif); for (colnum = 0; colnum < columns; colnum++ ) { const char *typeofvalue; cbf_failnez (cbf_select_column(ucif, colnum)) cbf_failnez (cbf_column_name(ucif, &column_name)) if ( ! cbf_get_value(ucif, &value) ) { if (compression && value && column_name && !cbf_cistrcmp("compression_type",column_name)) { cbf_failnez (cbf_find_column(cbf, column_name)) switch (compression&CBF_COMPRESSION_MASK) { case (CBF_NONE): cbf_failnez (cbf_set_value (cbf,"none")) cbf_failnez (cbf_set_typeofvalue(cbf,"word")) break; case (CBF_CANONICAL): cbf_failnez (cbf_set_value (cbf,"canonical")) cbf_failnez (cbf_set_typeofvalue(cbf,"word")) break; case (CBF_PACKED): cbf_failnez (cbf_set_value (cbf,"packed")) cbf_failnez (cbf_set_typeofvalue(cbf,"word")) break; case (CBF_PACKED_V2): cbf_failnez (cbf_set_value (cbf,"packed_v2")) cbf_failnez (cbf_set_typeofvalue(cbf,"word")) break; case (CBF_BYTE_OFFSET): cbf_failnez (cbf_set_value (cbf,"byte_offsets")) cbf_failnez (cbf_set_typeofvalue(cbf,"word")) break; case (CBF_PREDICTOR): cbf_failnez (cbf_set_value (cbf,"predictor")) cbf_failnez (cbf_set_typeofvalue(cbf,"word")) break; default: cbf_failnez (cbf_set_value (cbf,".")) cbf_failnez (cbf_set_typeofvalue(cbf,"null")) break; } if (compression&CBF_FLAG_MASK) { if (compression&CBF_UNCORRELATED_SECTIONS) { cbf_failnez (cbf_require_column (cbf, "compression_type_flag")) cbf_failnez (cbf_set_value (cbf, "uncorrelated_sections")) cbf_failnez (cbf_set_typeofvalue (cbf, "word")) } else if (compression&CBF_FLAT_IMAGE) { cbf_failnez (cbf_require_column (cbf, "compression_type_flag")) cbf_failnez (cbf_set_value (cbf, "flat")) cbf_failnez (cbf_set_typeofvalue (cbf, "word")) } } else { if (!cbf_find_column(cbf, "compression_type_flag")) { cbf_failnez (cbf_set_value (cbf,".")) cbf_failnez (cbf_set_typeofvalue(cbf,"null")) } } } else if (compression && value && column_name && !cbf_cistrcmp("compression_type_flag",column_name)) { if (compression&CBF_FLAG_MASK) { if (compression&CBF_UNCORRELATED_SECTIONS) { cbf_failnez (cbf_require_column (cbf, "compression_type_flag")) cbf_failnez (cbf_set_value (cbf, "uncorrelated_sections")) cbf_failnez (cbf_set_typeofvalue (cbf, "word")) } else if (compression&CBF_FLAT_IMAGE) { cbf_failnez (cbf_require_column (cbf, "compression_type_flag")) cbf_failnez (cbf_set_value (cbf, "flat")) cbf_failnez (cbf_set_typeofvalue (cbf, "word")) } } else { if (!cbf_find_column(cbf, "compression_type_flag")) { cbf_failnez (cbf_set_value (cbf,".")) cbf_failnez (cbf_set_typeofvalue(cbf,"null")) } } } else { cbf_failnez (cbf_get_typeofvalue(ucif, &typeofvalue)) cbf_failnez (cbf_find_column(cbf, column_name)) cbf_failnez (cbf_set_value(cbf, value)) cbf_failnez (cbf_set_typeofvalue(cbf, typeofvalue)) } } else { void * array; int binary_id, elsigned, elunsigned; size_t elements,elements_read, elsize; int minelement, maxelement; unsigned int cifcompression; int realarray; const char *byteorder; size_t dim1, dim2, dim3, padding; cbf_failnez(cbf_get_arrayparameters_wdims_fs( ucif, &cifcompression, &binary_id, &elsize, &elsigned, &elunsigned, &elements, &minelement, &maxelement, &realarray, &byteorder, &dim1, &dim2, &dim3, &padding)) if ((array=malloc(elsize*elements))) { cbf_failnez (cbf_find_column(cbf,column_name)) if (!realarray) { cbf_failnez (cbf_get_integerarray( ucif, &binary_id, array, elsize, elsigned, elements, &elements_read)) if (dimflag == HDR_FINDDIMS && dim1==0) { cbf_get_arraydimensions(ucif,NULL,&dim1,&dim2,&dim3); } cbf_failnez(cbf_set_integerarray_wdims_fs( cbf, compression, binary_id, array, elsize, elsigned, elements, "little_endian", dim1, dim2, dim3, 0)) } else { cbf_failnez (cbf_get_realarray( ucif, &binary_id, array, elsize, elements, &elements_read)) if (dimflag == HDR_FINDDIMS && dim1==0) { cbf_get_arraydimensions(ucif,NULL,&dim1,&dim2,&dim3); } cbf_failnez(cbf_set_realarray_wdims_fs( cbf, compression, binary_id, array, elsize, elements, "little_endian", dim1, dim2, dim3, 0)) } free(array); } else { fprintf(stderr, "\nFailed to allocate memory %ld bytes", (long) elsize*elements); exit(1); } } } } } else { cbf_saveframe_name(ucif,&saveframe_name); if (!cbf_find_saveframe(cbf,saveframe_name) ) { cbf_failnez(cbf_force_new_saveframe(cbf, saveframe_name)) } if ( !cbf_rewind_category(ucif) ) { cbf_failnez (cbf_count_categories(ucif, &categories)) for (catnum = 0; catnum < categories; catnum++) { cbf_select_category(ucif, catnum); cbf_category_name(ucif,&category_name); cbf_require_category(cbf, category_name); cbf_count_rows(ucif,&rows); cbf_count_columns(ucif,&columns); /* Transfer the columns names from ucif to cbf */ if ( ! cbf_rewind_column(ucif) ) { do { cbf_failnez(cbf_column_name(ucif, &column_name)) cbf_failnez(cbf_require_column(cbf, column_name)) } while ( ! cbf_next_column(ucif) ); cbf_rewind_column(ucif); cbf_rewind_row(ucif); } /* Transfer the rows from ucif to cbf */ for (rownum = 0; rownum < rows; rownum++ ) { cbf_failnez (cbf_select_row(ucif, rownum)) if (cbf_select_row(cbf, rownum)) { cbf_failnez (cbf_new_row(cbf)) } cbf_rewind_column(ucif); for (colnum = 0; colnum < columns; colnum++ ) { const char *typeofvalue; cbf_failnez (cbf_select_column(ucif, colnum)) cbf_failnez (cbf_column_name(ucif, &column_name)) if ( ! cbf_get_value(ucif, &value) ) { cbf_failnez (cbf_get_typeofvalue(ucif, &typeofvalue)) cbf_failnez (cbf_find_column(cbf, column_name)) cbf_failnez (cbf_set_value(cbf, value)) cbf_failnez (cbf_set_typeofvalue(cbf, typeofvalue)) } else { void * array; int binary_id, elsigned, elunsigned; size_t elements,elements_read, elsize; int minelement, maxelement; unsigned int cifcompression; int realarray; const char * byteorder; size_t dim1, dim2, dim3, padding; cbf_failnez(cbf_get_arrayparameters_wdims_fs( ucif, &cifcompression, &binary_id, &elsize, &elsigned, &elunsigned, &elements, &minelement, &maxelement, &realarray, &byteorder, &dim1, &dim2, &dim3, &padding)) if ((array=malloc(elsize*elements))) { cbf_failnez (cbf_find_column(cbf,column_name)) if (!realarray) { cbf_failnez (cbf_get_integerarray( ucif, &binary_id, array, elsize, elsigned, elements, &elements_read)) cbf_failnez(cbf_set_integerarray_wdims_fs( cbf, compression, binary_id, array, elsize, elsigned, elements, byteorder, dim1, dim2, dim3, padding)) } else { cbf_failnez (cbf_get_realarray( ucif, &binary_id, array, elsize, elements, &elements_read)) if (dimflag == HDR_FINDDIMS && dim1==0) { cbf_get_arraydimensions(ucif,NULL,&dim1,&dim2,&dim3); } cbf_failnez(cbf_set_realarray_wdims_fs( cbf, compression, binary_id, array, elsize, elements, byteorder, dim1, dim2, dim3, padding)) } free(array); } else { fprintf(stderr, "\nFailed to allocate memory %ld bytes", (long) elsize*elements); exit(1); } } } } } } } } } } } a = clock (); out = NULL; if ( ! cbfout || strcmp(cbfout?cbfout:"","-") == 0 ) { out = stdout; } else if ( strcmp(cbfout?cbfout:"","/dev/null") ==0 ){ devnull=1; } else { out = fopen (cbfout, "w+b"); } if ( ( devnull == 0 ) && ! out ) { if (encoding == ENC_NONE) { printf (" Couldn't open the CBF file %s\n", cbfout); } else { printf (" Couldn't open the CIF file %s\n", cbfout); } exit (1); } if (testconstruct) { cbf_detector detector; cbf_failnez(cbf_construct_detector (cbf, &detector, 0)) cbf_free_detector (detector); } if ( ! devnull ){ if (Wide) { cbf_failnez (cbf_write_widefile (cbf, out, 1, cbforcif, mime | (digest&(MSG_DIGEST|MSG_DIGESTNOW)) | padflag | qwflags, encoding | bytedir | term )) } else { cbf_failnez (cbf_write_file (cbf, out, 1, cbforcif, mime | (digest&(MSG_DIGEST|MSG_DIGESTNOW)) | padflag | qwflags, encoding | bytedir | term )) } } cbf_failnez (cbf_free_handle (cbf)) b = clock (); if (encoding == ENC_NONE) { fprintf (stderr, " Time to write the CBF image: %.3fs\n", ((b - a) * 1.0) / CLOCKS_PER_SEC); } else { if ( ! devnull ) fprintf (stderr, " Time to write the CIF image: %.3fs\n", ((b - a) * 1.0) / CLOCKS_PER_SEC); } cbf_failnez (cbf_free_getopt_handle(opts)) exit(0); } int local_exit (int status) { exit(status); return 1; /* avoid warnings */ } ./CBFlib-0.9.2.2/examples/template_adscquantum4_2304x2304.cbf0000644000076500007650000001264211603702122021550 0ustar yayayaya###CBF: VERSION 1.1 data_image_1 # category DIFFRN loop_ _diffrn.id _diffrn.crystal_id DIFFRN_ID DIFFRN_CRYSTAL_ID # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.current _diffrn_source.type DIFFRN_ID synchrotron 100.0 'SSRL beamline 1-5' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.probe _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source _diffrn_radiation.collimation DIFFRN_ID WAVELENGTH1 x-ray 'Si 111' 0.8 0.0 0.08 0.01 0.00 '0.20 mm x 0.20 mm' # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.98 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.details _diffrn_detector.number_of_axes DIFFRN_ID ADSCQ4 'ADSC QUANTUM4' 'slow mode' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id ADSCQ4 DETECTOR_X ADSCQ4 DETECTOR_Y ADSCQ4 DETECTOR_Z ADSCQ4 DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 ADSCQ4 # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method _diffrn_measurement.details DIFFRN_ID GONIOMETER 3 rotation 'i0=1.000 i1=1.000 i2=1.000 ib=1.000 beamstop=20 mm 0% attenuation' # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 0.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 0.0 0.0 FRAME1 GONIOMETER_KAPPA 0.0 0.0 FRAME1 GONIOMETER_PHI 0.0 0.0 FRAME1 DETECTOR_Z 0.0 0.0 FRAME1 DETECTOR_Y 0.0 0.0 FRAME1 DETECTOR_X 0.0 0.0 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 -1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 -94.0032 94.0032 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 2304 1 increasing ELEMENT_X ARRAY1 2 2304 2 increasing ELEMENT_Y # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.0408 0.0816 ELEMENT_Y ELEMENT_Y -0.0408 -0.0816 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 0.23 0.03 65000 0 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ? ./CBFlib-0.9.2.2/examples/tiff2cbf.c0000644000076500007650000005016311603702122015250 0ustar yayayaya/********************************************************************** * tiffcbf -- convert a tiff file to a cbf file * * * * Version 0.7.6 28 June 2006 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * WHILE YOU MAY ALTERNATIVE DISTRIBUTE THE API UNDER THE LGPL * * YOU MAY ***NOT*** DISTRBUTE THIS PROGRAM UNDER THE LGPL * * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #include "cbf.h" #include #include #include #include #include #include int local_exit(int status) { exit(status); return status; /* to avoid warning messages */ } #undef cbf_failnez #define cbf_failnez(x) \ {int err; \ err = (x); \ if (err) { \ fprintf(stderr,"\nCBFlib fatal error %x \n",err); \ local_exit(-1); \ } \ } int main (int argc, char *argv []) { FILE *out; TIFF *tif; cbf_handle cbf; clock_t a,b; uint32 width; uint32 height; uint32 npixels; unsigned char * raster; int imageno; /* Usage */ if (argc < 3) { fprintf (stderr, "\n Usage: %s tifffile cbffile\n", argv [0]); exit (2); } /* Read the tiff image */ a = clock (); if (!(tif=TIFFOpen(argv[1], "r"))) { fprintf(stderr," %s unable to open tiff image %s, abort\n", argv[0], argv[1]); local_exit(-1); } b = clock (); fprintf (stderr, " Time to read the image: %.3fs\n", ((b - a) * 1.0) / CLOCKS_PER_SEC); /* Make a cbf version of the image */ a = clock (); /* Create the cbf */ cbf_failnez (cbf_make_handle (&cbf)) /* Make a new data block */ cbf_failnez (cbf_new_datablock (cbf, "image_1")) imageno = 0; cbf_failnez (cbf_require_category (cbf, "array_data")) do { char buffer[40]; char * headstring; size_t headsize, nheadsize; unsigned int rows; tstrip_t nstrips, strip; tsize_t stripsize; size_t totread; int elsize, elsign, real, plex, treturn; uint16 sampleformat, samplesperpixel, bitspersample, planarconfig; size_t dimslow, dimmid, dimfast; plex = 1; real = 0; elsign = 0; imageno++; /* bump the image number, starting with 1 versus the tiff directory number that starts with zero */ /* Make or add to the _array_data category */ cbf_failnez (cbf_require_column (cbf, "header_convention")) cbf_failnez (cbf_count_rows (cbf, &rows)) while (rows < imageno) { cbf_failnez (cbf_new_row (cbf)) rows++; } cbf_failnez (cbf_select_row (cbf,imageno-1)) cbf_failnez (cbf_set_value (cbf, "TIFF")) cbf_failnez (cbf_require_column (cbf, "array_id")) sprintf(buffer,"image_%d",imageno); cbf_failnez (cbf_set_value (cbf, buffer)) cbf_failnez (cbf_require_column (cbf, "binary_id")) cbf_failnez (cbf_set_integervalue (cbf, imageno)) cbf_failnez (cbf_require_column (cbf, "header_contents")) headsize = 1+TIFFSNPrintDirectory(tif,buffer,0,TIFFPRINT_COLORMAP|TIFFPRINT_CURVES); headstring = (char *) _TIFFmalloc(headsize); if (!headstring) { cbf_failnez(CBF_ALLOC); } nheadsize = TIFFSNPrintDirectory(tif,headstring,headsize-1,TIFFPRINT_COLORMAP|TIFFPRINT_CURVES); if (nheadsize > headsize-1) { _TIFFfree(headstring); cbf_failnez(CBF_ALLOC); } cbf_onfailnez(cbf_set_value (cbf,headstring),_TIFFfree(headstring)); _TIFFfree(headstring); cbf_failnez (cbf_require_column (cbf, "data")) treturn = TIFFGetField(tif, TIFFTAG_IMAGEWIDTH, &width); if (treturn != 1) cbf_failnez(CBF_ARGUMENT); dimfast = width; treturn = TIFFGetField(tif, TIFFTAG_IMAGELENGTH, &height); if (treturn != 1) cbf_failnez(CBF_ARGUMENT); dimmid = height; dimslow = 1; treturn = TIFFGetField(tif, TIFFTAG_SAMPLEFORMAT, &sampleformat); if (treturn != 1) cbf_failnez(CBF_ARGUMENT); treturn = TIFFGetField(tif, TIFFTAG_SAMPLESPERPIXEL, &samplesperpixel); if (treturn != 1) cbf_failnez(CBF_ARGUMENT); treturn = TIFFGetField(tif, TIFFTAG_BITSPERSAMPLE, &bitspersample); if (treturn != 1) cbf_failnez(CBF_ARGUMENT); treturn = TIFFGetField(tif, TIFFTAG_PLANARCONFIG, &planarconfig); if (treturn != 1) cbf_failnez(CBF_ARGUMENT); switch ( bitspersample ) { case 8: elsize = 1; break; case 16: elsize = 2; break; case 32: elsize = 4; break; case 64: elsize = 8; break; default: cbf_failnez(CBF_FORMAT); } switch ( sampleformat ) { case SAMPLEFORMAT_UINT: elsign = 0; real = 0; plex = 1; break; /* !unsigned integer data */ case SAMPLEFORMAT_INT: elsign = 1; real = 0; plex = 1; break; /* !signed integer data */ case SAMPLEFORMAT_IEEEFP: elsign = 1; real = 1; plex = 1; break; /* !IEEE floating point data */ case SAMPLEFORMAT_VOID: cbf_failnez(CBF_FORMAT); /* !untyped data */ case SAMPLEFORMAT_COMPLEXINT: elsign = 1; real = 0; plex = 2; elsize /=2; break; /* !complex signed int */ case SAMPLEFORMAT_COMPLEXIEEEFP:elsign = 1; real = 1; plex = 2; elsize /=2; break; /* !complex ieee floating */ default: cbf_failnez(CBF_FORMAT); } switch ( planarconfig ) { case PLANARCONFIG_CONTIG: plex *= samplesperpixel; samplesperpixel = 1; if (plex > 1) { dimslow = dimmid; dimmid = dimfast; dimfast = plex; } break; case PLANARCONFIG_SEPARATE: if (plex > 1 && samplesperpixel > 1) { dimfast = dimfast*plex; dimslow = samplesperpixel; } else if (plex == 1 && samplesperpixel > 1 ) { dimslow = samplesperpixel; } else if (plex > 1 && samplesperpixel == 1) { dimslow = dimmid; dimmid = dimfast; dimfast = plex; } } npixels = dimslow*dimmid*dimfast; nstrips = TIFFNumberOfStrips(tif); stripsize = TIFFStripSize(tif); raster = (unsigned char *) _TIFFmalloc(stripsize*nstrips+stripsize-1); elsize = stripsize*nstrips/npixels; totread = 0; for (strip = 0; strip < nstrips; strip++) { totread +=TIFFReadEncodedStrip(tif, strip, raster+strip*stripsize, stripsize); } if(real){ cbf_failnez (cbf_set_realarray_wdims_fs (cbf, CBF_NONE, imageno, (void *)raster, elsize, npixels, "little_endian",dimfast,dimmid,dimslow,0 )) } else { cbf_failnez (cbf_set_integerarray_wdims_fs (cbf, CBF_NONE, imageno, (void *)raster, elsize, elsign, npixels, "little_endian",dimfast,dimmid,dimslow,0 )) } _TIFFfree(raster); } while (TIFFReadDirectory(tif)); /* Write the new file */ out = fopen (argv [2], "w+b"); if (!out) { fprintf (stderr, " Couldn't open the CBF file %s\n", argv [2]); exit (1); } cbf_failnez (cbf_write_file (cbf, out, 1, CBF, MSG_DIGEST | MIME_HEADERS , 0)) /* Free the cbf */ cbf_failnez (cbf_free_handle (cbf)) b = clock (); fprintf (stderr, " Time to write the CBF image: %.3fs\n", ((b - a) * 1.0) / CLOCKS_PER_SEC); /* Free the tiff images */ TIFFClose(tif); /* Success */ return 0; } ./CBFlib-0.9.2.2/examples/sequence_match.c0000644000076500007650000013517311603702122016554 0ustar yayayaya/* * sequence_match.c * * match 2 mmCIF files on sequence and export the matching portions * of their atoms lists * * * Created by Herbert J. Bernstein on 2/24/10. * Copyright 2010 Herbert J. Bernstein. All rights reserved. * */ /********************************************************************** * SYNOPSIS * * * * seqmatch [-l leftinput] [-r rightinput] \ * * [-m leftoutput] [-s rightoutput] \ * * [-a|-c] * * [leftinput] [rightinput] \ * * [leftoutput] [rightoutput] * * * * * **********************************************************************/ #include "cbf.h" #include "cbf_simple.h" #include "cbf_string.h" #include "cbf_copy.h" #include #include #include #include #include #include #include "cbf_getopt.h" #include #include #include #define C2CBUFSIZ 8192 #ifdef __MINGW32__ #define NOMKSTEMP #define NOTMPDIR #endif int local_exit (int status); int outerror(int err); int outerror(int err) { if ((err&CBF_FORMAT)==CBF_FORMAT) fprintf(stderr, " cif2cbf: The file format is invalid.\n"); if ((err&CBF_ALLOC)==CBF_ALLOC) fprintf(stderr, " cif2cbf Memory allocation failed.\n"); if ((err&CBF_ARGUMENT)==CBF_ARGUMENT) fprintf(stderr, " cif2cbf: Invalid function argument.\n"); if ((err&CBF_ASCII)==CBF_ASCII) fprintf(stderr, " cif2cbf: The value is ASCII (not binary).\n"); if ((err&CBF_BINARY)==CBF_BINARY) fprintf(stderr, " cif2cbf: The value is binary (not ASCII).\n"); if ((err&CBF_BITCOUNT)==CBF_BITCOUNT) fprintf(stderr, " cif2cbf: The expected number of bits does" " not match the actual number written.\n"); if ((err&CBF_ENDOFDATA)==CBF_ENDOFDATA) fprintf(stderr, " cif2cbf: The end of the data was reached" " before the end of the array.\n"); if ((err&CBF_FILECLOSE)==CBF_FILECLOSE) fprintf(stderr, " cif2cbf: File close error.\n"); if ((err&CBF_FILEOPEN)==CBF_FILEOPEN) fprintf(stderr, " cif2cbf: File open error.\n"); if ((err&CBF_FILEREAD)==CBF_FILEREAD) fprintf(stderr, " cif2cbf: File read error.\n"); if ((err&CBF_FILESEEK)==CBF_FILESEEK) fprintf(stderr, " cif2cbf: File seek error.\n"); if ((err&CBF_FILETELL)==CBF_FILETELL) fprintf(stderr, " cif2cbf: File tell error.\n"); if ((err&CBF_FILEWRITE)==CBF_FILEWRITE) fprintf(stderr, " cif2cbf: File write error.\n"); if ((err&CBF_IDENTICAL)==CBF_IDENTICAL) fprintf(stderr, " cif2cbf: A data block with the new name already exists.\n"); if ((err&CBF_NOTFOUND)==CBF_NOTFOUND) fprintf(stderr, " cif2cbf: The data block, category, column or" " row does not exist.\n"); if ((err&CBF_OVERFLOW)==CBF_OVERFLOW) fprintf(stderr, " cif2cbf: The number read cannot fit into the " "destination argument.\n The destination has been set to the nearest value.\n"); if ((err& CBF_UNDEFINED)==CBF_UNDEFINED) fprintf(stderr, " cif2cbf: The requested number is not defined (e.g. 0/0).\n"); if ((err&CBF_NOTIMPLEMENTED)==CBF_NOTIMPLEMENTED) fprintf(stderr, " cif2cbf: The requested functionality is not yet implemented.\n"); return 0; } #undef cbf_failnez #define cbf_failnez(x) \ {int err; \ err = (x); \ if (err) { \ fprintf(stderr,"CBFlib fatal error %d\n",err); \ outerror(err); \ local_exit (-1); \ } \ } typedef struct { int hashchain; /* next index by residue name */ int resnumhashchain; /* next index by residue number */ const char * resname; /* residue name */ int resnum; /* residue number */ int seqmatch; /* index in another chain of a match */ } residue_entry; typedef struct { int hash_table[256]; /* indices by residue name hash code */ int hash_end[256]; /* indices of the ends of the name hash chains */ int hash_resnum[256]; /* indices by residue number hash code */ int hash_resnum_end[256]; /* indices of the ends of the number hash chains */ size_t size; size_t capacity; int minresnum; int maxresnum; residue_entry * residues; const char* entity; } residue_chain; typedef residue_chain * chainhandle; int residue_hash(const char * resname) { int hashcode; int c; int j; size_t len; hashcode = 0; if (!resname) return -1; len = strlen(resname); for (j=0; jhash_table[i] = -1; (*handle)->hash_end[i] = -1; (*handle)->hash_resnum[i] = -1; (*handle)->hash_resnum_end[i] = -1; } (*handle)->size = 0; (*handle)->capacity = (!capacity)?10:capacity; (*handle)->entity = entity; (*handle)->residues = (residue_entry*)malloc(((*handle)->capacity)*sizeof(residue_entry)); (*handle)->maxresnum = -999999; (*handle)->minresnum = 999999; if (!(*handle)->residues) { free (*handle); *handle = NULL; return -1; } return 0; } int add_residue(chainhandle handle, const char * residue, int resnum) { residue_entry * re; int hashcode; int he; if (!handle) return -1; if (handle->size >= handle->capacity) { if((re=(residue_entry *)malloc(handle->capacity*2*sizeof(residue_entry)))){ memmove(re,handle->residues,(handle->size)*sizeof(residue_entry)); free(handle->residues); handle->capacity *=2; handle->residues = re; } else { return -1; } } re=handle->residues; hashcode = residue_hash(residue); re[handle->size].hashchain=-1; re[handle->size].resname = residue; re[handle->size].resnum = resnum; if (resnum < handle->minresnum) handle->minresnum = resnum; if (resnum > handle->maxresnum) handle->maxresnum = resnum; re[handle->size].seqmatch = -1; if ((he=(handle->hash_end)[hashcode]) != -1) { re[he].hashchain = handle->size; } (handle->hash_end)[hashcode] = handle->size; if ((handle->hash_table)[hashcode] == -1) { (handle->hash_table)[hashcode] = handle->size; } hashcode=resnum&0xFF; re[handle->size].resnumhashchain=-1; (handle->hash_resnum_end)[hashcode] = handle->size; if ((handle->hash_resnum)[hashcode] == -1) { (handle->hash_resnum)[hashcode] = handle->size; } (handle->size)++; return 0; } int get_by_residue(chainhandle chain, int oldindex, const char* residue) { int hashcode; hashcode = residue_hash(residue); if (oldindex < 0 ) { oldindex = chain->hash_table[hashcode]; } else { oldindex = (chain->residues)[oldindex].hashchain; } if (oldindex < 0) return -1; while(cbf_cistrcmp((chain->residues)[oldindex].resname,residue) ) { oldindex = (chain->residues)[oldindex].hashchain; if (oldindex < 0) return -1; } return oldindex; } int get_by_resnum(chainhandle chain, int oldindex, int resnum) { if (oldindex < 0) { oldindex = chain->hash_resnum[resnum&0xFF]; } else { oldindex = (chain->residues)[oldindex].resnumhashchain; } if (oldindex < 0) return -1; while((chain->residues)[oldindex].resnum != resnum ) { oldindex = (chain->residues)[oldindex].resnumhashchain; if (oldindex < 0) return -1; } return oldindex; } /* find the next match to a given residue, returning the index, not the residue number*/ int find_residue(chainhandle chain, const char * residue, int startnum, int minnum) { int hashcode; int index; if (startnum < chain->minresnum) { hashcode = residue_hash(residue); index = chain->hash_table[hashcode]; } else { index = get_by_resnum(chain,-1,startnum); index = (chain->residues)[index].hashchain; } while(index >= 0 ){ if ( !cbf_cistrcmp((chain->residues)[index].resname,residue) && (chain->residues)[index].resnum >= minnum) { return index; } else { index = (chain->residues)[index].hashchain; } } return index; } /* compare part of two sequences by residue number returns 0 for a match or the relative index of the first difference, starting at 1*/ int seq_comp_partial(chainhandle leftseq, chainhandle rightseq, int leftstart, int rightstart, int lentomatch) { int ii; int left, right; int imatch; left = -1; right = -1; for (ii=0; iiresidues)[left].seqmatch = -1; if (right < 0) return ii+1; if (!cbf_cistrcmp((leftseq->residues)[left].resname,(rightseq->residues)[right].resname)) { (leftseq->residues)[left].seqmatch = right; left = right = -1; continue; } while ( (left = get_by_resnum(leftseq, left, leftstart+ii)) >= 0) { right = -1; imatch = 0; while ( (right = get_by_resnum(rightseq, right, rightstart+ii)) >= 0) { if (!cbf_cistrcmp((leftseq->residues)[left].resname,(rightseq->residues)[right].resname)){ imatch = 1; break; } if (imatch == 1) { left = right = -1; continue; } } } return ii+1; } left = -1; right = -1; } return 0; } int seq_comp(chainhandle leftseq, chainhandle rightseq ) { int index; int seqlim; int isl; int isr; int iii; int leftlow; int lefthigh; int rightlow; int righthigh; int imatch; int lentomatch; int kmatched; leftlow = leftseq->minresnum; lefthigh = leftseq->maxresnum; rightlow = rightseq->minresnum; righthigh = rightseq->maxresnum; seqlim = (lefthigh-leftlow+1)/2; if (seqlim > 6) seqlim = 6; for (iii=0;iii <=leftseq->size; iii++) { (leftseq->residues)[iii].seqmatch=-1; } kmatched = 0; /* we will try to match a sequence of length lm from the left sequence to some portion of the right sequence, accepting any match of at least 4 residues */ isl = leftlow; while (isl <= lefthigh) { index = get_by_resnum(leftseq,-1,isl); if (index < 0) { isl++; continue; } iii = find_residue(rightseq,(leftseq->residues)[index].resname,-1,rightlow); if (iii < 0) { while((index=get_by_resnum(leftseq,index,isl)>=0)){ iii = find_residue(rightseq,(leftseq->residues)[index].resname,-1,rightlow); if (iii < 0) { continue; } isr = (rightseq->residues)[iii].resnum; lentomatch = lefthigh-isl+1; if (lentomatch > righthigh-isr+1) { lentomatch = righthigh-isr+1; } imatch = seq_comp_partial(leftseq, rightseq, isl, isr, lentomatch); if (imatch > 0 && imatch < 4) { (leftseq->residues)[index].seqmatch=-1; while((index=get_by_resnum(leftseq,index,isl)>=0)){ (leftseq->residues)[index].seqmatch=-1; } continue; } if (imatch == 0 ) imatch = lentomatch; isl += imatch-1; rightlow = isr+imatch; kmatched +=imatch; break; } } else { isr = (rightseq->residues)[iii].resnum; lentomatch = lefthigh-isl+1; if (lentomatch > righthigh-isr+1) { lentomatch = righthigh-isr+1; } imatch = seq_comp_partial(leftseq, rightseq, isl, isr, lentomatch); if (imatch > 0 && imatch < 4) { (leftseq->residues)[index].seqmatch=-1; while((index=get_by_resnum(leftseq,index,isl)>=0)){ (leftseq->residues)[index].seqmatch=-1; } isl++; continue; } if (imatch == 0 ) imatch = lentomatch; isl += imatch; rightlow = isr+imatch; kmatched +=imatch; break; } isl++; } return kmatched; } int main (int argc, char *argv []) { FILE *leftin, *rightin, *leftout=NULL, *rightout=NULL; const char * leftinstr, * rightinstr, * leftoutstr, * rightoutstr; char * leftintmpstr, *rightintmpstr; cbf_handle leftincbf, rightincbf, leftoutcbf, rightoutcbf; cbf_getopt_handle opts; int doall,doca; int nbytes; int c; int leftdevnull, rightdevnull; char buf[C2CBUFSIZ]; chainhandle leftch[256]; chainhandle rightch[256]; const char * leftchname[256]; const char * rightchname[256]; int left_to_right[256]; int right_to_left[256]; int numleftch, numrightch; int iii, jjj; int errflg = 0; #ifndef NOMKSTEMP int leftintmpfd, rightintmpfd; #endif int leftintmpused, rightintmpused; const char * optarg; /* Extract options */ leftinstr = NULL; rightinstr = NULL; leftoutstr = NULL; rightoutstr = NULL; leftintmpstr = NULL; rightintmpstr = NULL; leftdevnull = rightdevnull = 0; leftintmpused = rightintmpused = 0; errflg = 0; numleftch = numrightch = 0; doall = doca = 0; cbf_failnez(cbf_make_getopt_handle(&opts)) cbf_failnez(cbf_getopt_parse(opts, argc, argv, "-l(leftinput):" \ "-r(rightinput):" \ "-m(leftoutput):" \ "-s(rightoutput):" \ "-a(allatoms)" \ "-c(calpha)" \ )) if (!cbf_rewind_getopt_option(opts)) for(;!cbf_get_getopt_data(opts,&c,NULL,NULL,&optarg);cbf_next_getopt_option(opts)) { if (!c) break; switch(c) { case 'l': /* left input file */ if (leftinstr) errflg++; else leftinstr = optarg; break; case 'r': /* right input file */ if (rightinstr) errflg++; else rightinstr = optarg; break; case 'm': /* left output file */ if (leftoutstr) errflg++; else leftoutstr = optarg; break; case 's': /* right output file */ if (rightoutstr) errflg++; else rightoutstr = optarg; break; case 'a': /* do all atoms */ if (doall|doca) errflg++; else doall=1; break; case 'c': /* do only carbon alpha */ if (doall|doca) errflg++; else doca=1; break; default: errflg++; break; } } for(;!cbf_get_getopt_data(opts,&c,NULL,NULL,&optarg);cbf_next_getopt_option(opts)) { if (!leftinstr) { leftinstr = optarg; } else { if (!rightinstr) { rightinstr = optarg; } else { if (!leftoutstr) { leftoutstr = optarg; } else { if (!rightoutstr) { rightoutstr = optarg; } else { errflg++; } } } } } if (errflg) { fprintf(stderr,"seqmatch: Usage: \n"); fprintf(stderr, " seqmatch [-l leftin] [-r rightin] \\\n"); fprintf(stderr, " [-m leftout] [-s rightout]\\\n"); fprintf(stderr, " [-a|-c] \\\n"); fprintf(stderr, " [leftin] [rightin] [leftout] [rightout]\n"); exit(2); } if ( cbf_make_handle (&leftincbf) ) { fprintf(stderr,"Failed to create handle for left input cif\n"); exit(1); } if ( cbf_make_handle (&rightincbf) ) { fprintf(stderr,"Failed to create handle for right input cif\n"); exit(1); } if ( cbf_make_handle (&leftoutcbf) ) { fprintf(stderr,"Failed to create handle for left output cif\n"); exit(1); } if ( cbf_make_handle (&rightoutcbf) ) { fprintf(stderr,"Failed to create handle for right output cif\n"); exit(1); } /* Read the leftin cif */ if (!leftinstr || strcmp(leftinstr?leftinstr:"","-") == 0) { leftintmpstr = (char *)malloc(strlen("/tmp/seqmatchlXXXXXX")+1); #ifdef NOTMPDIR strcpy(leftintmpstr, "seqmatchlXXXXXX"); #else strcpy(leftintmpstr, "/tmp/seqmatchlXXXXXX"); #endif #ifdef NOMKSTEMP if ((leftintmpstr = mktemp(leftintmpstr)) == NULL ) { fprintf(stderr,"\n seqmatch: Can't create temporary file name %s.\n", leftintmpstr); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } if ( (leftin = fopen(leftintmpstr,"wb+")) == NULL) { fprintf(stderr,"Can't open temporary file %s.\n", leftintmpstr); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } #else if ((leftintmpfd = mkstemp(leftintmpstr)) == -1 ) { fprintf(stderr,"\n seqmatch: Can't create temporary file %s.\n", leftintmpstr); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } if ( (leftin = fdopen(leftintmpfd, "w+")) == NULL) { fprintf(stderr,"Can't open temporary file %s.\n", leftintmpstr); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } #endif while ((nbytes = fread(buf, 1, C2CBUFSIZ, stdin))) { if(nbytes != fwrite(buf, 1, nbytes, leftin)) { fprintf(stderr,"Failed to write %s.\n", leftintmpstr); exit(1); } } fclose(leftin); leftinstr = leftintmpstr; leftintmpused = 1; } /* Read the left input file */ if (!(leftin = fopen (leftinstr, "rb"))) { fprintf (stderr,"Couldn't open the left input CIF file %s\n", leftinstr); exit (1); } if (leftintmpused) { if (unlink(leftintmpstr) != 0 ) { fprintf(stderr,"seqmatch: Can't unlink temporary file %s.\n", leftintmpstr); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } } cbf_failnez (cbf_read_widefile (leftincbf, leftin, MSG_DIGEST)) /* Read the rightin cif */ if (!rightinstr || strcmp(rightinstr?rightinstr:"","-") == 0) { rightintmpstr = (char *)malloc(strlen("/tmp/seqmatchrXXXXXX")+1); #ifdef NOTMPDIR strcpy(rightintmpstr, "seqmatchrXXXXXX"); #else strcpy(rightintmpstr, "/tmp/seqmatchrXXXXXX"); #endif #ifdef NOMKSTEMP if ((rightintmpstr = mktemp(rightintmpstr)) == NULL ) { fprintf(stderr,"\n seqmatch: Can't create temporary file name %s.\n", rightintmpstr); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } if ( (rightin = fopen(rightintmpstr,"wb+")) == NULL) { fprintf(stderr,"Can't open temporary file %s.\n", rightintmpstr); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } #else if ((rightintmpfd = mkstemp(rightintmpstr)) == -1 ) { fprintf(stderr,"\n seqmatch: Can't create temporary file %s.\n", rightintmpstr); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } if ( (rightin = fdopen(rightintmpfd, "w+")) == NULL) { fprintf(stderr,"Can't open temporary file %s.\n", rightintmpstr); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } #endif while ((nbytes = fread(buf, 1, C2CBUFSIZ, stdin))) { if(nbytes != fwrite(buf, 1, nbytes, rightin)) { fprintf(stderr,"Failed to write %s.\n", rightintmpstr); exit(1); } } fclose(rightin); rightinstr = rightintmpstr; rightintmpused = 1; } /* Read the right input file */ if (!(rightin = fopen (rightinstr, "rb"))) { fprintf (stderr,"Couldn't open the right input CIF file %s\n", rightinstr); exit (1); } if (rightintmpused) { if (unlink(rightintmpstr) != 0 ) { fprintf(stderr,"seqmatch: Can't unlink temporary file %s.\n", rightintmpstr); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } } cbf_failnez (cbf_read_widefile (rightincbf, rightin, MSG_DIGEST)) leftout = rightout = NULL; if (!cbf_find_tag(leftincbf,"_entity_poly_seq.entity_id")) { if (!cbf_find_tag(rightincbf,"_entity_poly_seq.entity_id")) { } else { fprintf(stderr,"seqmatch: Unable to find _entity_poly_seq.entity_id in right input %s\n",rightinstr); exit(1); } } else { fprintf(stderr,"seqmatch: Unable to find _entity_poly_seq.entity_id in left input %s\n",leftinstr); if (cbf_find_tag(rightincbf,"_entity_poly_seq.entity_id")) { fprintf(stderr,"seqmatch: Unable to find _entity_poly_seq.entity_id in right input %s\n",rightinstr); exit(1); } } cbf_failnez(cbf_rewind_row(leftincbf)); cbf_failnez(cbf_rewind_row(rightincbf)); { const char * lastleftent = NULL; const char * lastrightent = NULL; const char * entity, * residue; unsigned int leftrows, rightrows; int row; int seqnum; cbf_failnez (cbf_count_rows(leftincbf,&leftrows)) for (row=0;rowminresnum; maxresnum = chain->maxresnum; for (resnum=minresnum; resnum<=maxresnum; resnum++) { index = -1; while((index = get_by_resnum(chain, index, resnum))!=-1) { fprintf(stderr," left chain %d residue %d %s\n",iii,resnum,(chain->residues)[index].resname); } } } for (iii=0; iiiminresnum; maxresnum = chain->maxresnum; for (resnum=minresnum; resnum<=maxresnum; resnum++) { index = -1; while((index = get_by_resnum(chain, index, resnum))!=-1) { fprintf(stderr," right chain %d residue %d %s\n",iii,resnum,(chain->residues)[index].resname); } } } fprintf(stderr,"%d chains in %s, %d chains in %s\n", numleftch, leftinstr, numrightch, rightinstr); for (iii=0; iii<256; iii++) left_to_right[iii]=-1; for (iii=0; iii<256; iii++) right_to_left[iii]=-1; for (iii=0; iiimaxresnum-leftch[iii]->minresnum+1; countr = rightch[iii]->maxresnum-rightch[iii]->minresnum+1; if ((lr=seq_comp(leftch[iii],rightch[jjj])) > 1+countl/3 && (rl=seq_comp(rightch[jjj],leftch[iii]))> 1+countr/3 ) {left_to_right[iii]=jjj; right_to_left[jjj]=iii; fprintf(stderr,"matched %d to %d, matching %d on the left and %d on the right \n",iii,jjj, lr, rl); } } } } cbf_failnez(cbf_copy_cbf(leftoutcbf,leftincbf,CBF_BYTE_OFFSET,CBF_HDR_FINDDIMS)) cbf_failnez(cbf_copy_cbf(rightoutcbf,rightincbf,CBF_BYTE_OFFSET,CBF_HDR_FINDDIMS)) if (!cbf_find_tag(leftoutcbf,"_atom_site.label_seq_id")) { if (cbf_find_tag(rightoutcbf,"_atom_site.label_seq_id")) { fprintf(stderr,"seqmatch: Unable to find _atom_site.label_seq_id in right input %s\n",rightinstr); exit(1); } } else { fprintf(stderr,"seqmatch: Unable to find _atom_site.label_seq_id in left input %s\n",leftinstr); if (cbf_find_tag(rightoutcbf,"_atom_site.label_seq_id")) { fprintf(stderr,"seqmatch: Unable to find _atom_site.label_seq_id in right input %s\n",rightinstr); exit(1); } } { int row; unsigned int leftrows; int seqnum; const char * resname; const char * entity; const char * atomtype; const char * atomname; int iii; int foundent; cbf_failnez (cbf_count_rows(leftoutcbf,&leftrows)) for (row=0;row=0 && !cbf_cistrcmp((leftch[iii]->residues[left]).resname,resname)) { if (doca) { cbf_failnez(cbf_find_column(leftoutcbf,"type_symbol")) cbf_failnez(cbf_get_value(leftoutcbf,&atomtype)) cbf_failnez(cbf_find_column(leftoutcbf,"label_atom_id")) cbf_failnez(cbf_get_value(leftoutcbf,&atomname)) if (!atomtype || !atomname || cbf_cistrcmp(atomtype,"C") || cbf_cistrcmp(atomname,"CA")) { cbf_failnez(cbf_remove_row(leftoutcbf)) row--; leftrows--; break; } } break; } while (left >=0 && (left=(leftch[iii]->residues[left]).resnumhashchain)>=0) { if (!cbf_cistrcmp((leftch[iii]->residues[left]).resname,resname)) { if (doca) { cbf_failnez(cbf_find_column(leftoutcbf,"type_symbol")) cbf_failnez(cbf_get_value(leftoutcbf,&atomtype)) cbf_failnez(cbf_find_column(leftoutcbf,"label_atom_id")) cbf_failnez(cbf_get_value(leftoutcbf,&atomname)) if (!atomtype || !atomname || cbf_cistrcmp(atomtype,"C") || cbf_cistrcmp(atomname,"CA")) { cbf_failnez(cbf_remove_row(leftoutcbf)) row--; leftrows--; break; } } break; } } /* if there is no matching residue on the right, we will just drop this atom, but even if there is a matching residue, we may be required to drop to atom if we are only accepting carbon alphas */ if (left < 0) { cbf_failnez(cbf_remove_row(leftoutcbf)) row--; leftrows--; break; } else if (doca) { cbf_failnez(cbf_find_column(leftoutcbf,"type_symbol")) cbf_failnez(cbf_get_value(leftoutcbf,&atomtype)) cbf_failnez(cbf_find_column(leftoutcbf,"label_atom_id")) cbf_failnez(cbf_get_value(leftoutcbf,&atomname)) if (!atomtype || !atomname || cbf_cistrcmp(atomtype,"C") || cbf_cistrcmp(atomname,"CA")) { cbf_failnez(cbf_remove_row(leftoutcbf)) row--; leftrows--; break; } } } } } } if (!foundent) { cbf_failnez(cbf_remove_row(leftoutcbf)) row--; leftrows--; } } } } { int row; unsigned int rightrows; int seqnum; const char * resname; const char * entity; const char * atomtype; const char * atomname; int iii; int foundent; cbf_failnez (cbf_count_rows(rightoutcbf,&rightrows)) for (row=0;row=0 && !cbf_cistrcmp((rightch[iii]->residues[right]).resname,resname)) { if (doca) { cbf_failnez(cbf_find_column(rightoutcbf,"type_symbol")) cbf_failnez(cbf_get_value(rightoutcbf,&atomtype)) cbf_failnez(cbf_find_column(rightoutcbf,"label_atom_id")) cbf_failnez(cbf_get_value(rightoutcbf,&atomname)) if (!atomtype || !atomname || cbf_cistrcmp(atomtype,"C") || cbf_cistrcmp(atomname,"CA")) { cbf_failnez(cbf_remove_row(rightoutcbf)) row--; rightrows--; break; } } break; } while (right >=0 && (right=(rightch[iii]->residues[right]).resnumhashchain)>=0) { if (!cbf_cistrcmp((rightch[iii]->residues[right]).resname,resname)) { if (doca) { cbf_failnez(cbf_find_column(rightoutcbf,"type_symbol")) cbf_failnez(cbf_get_value(rightoutcbf,&atomtype)) cbf_failnez(cbf_find_column(rightoutcbf,"label_atom_id")) cbf_failnez(cbf_get_value(rightoutcbf,&atomname)) if (!atomtype || !atomname || cbf_cistrcmp(atomtype,"C") || cbf_cistrcmp(atomname,"CA")) { cbf_failnez(cbf_remove_row(rightoutcbf)) row--; rightrows--; break; } } break; } } /* if there is no matching residue on the right, we will just drop this atom, but even if there is a matching residue, we may be required to drop to atom if we are only accepting carbon alphas */ if (right < 0) { cbf_failnez(cbf_remove_row(rightoutcbf)) row--; rightrows--; break; } else if (doca) { cbf_failnez(cbf_find_column(rightoutcbf,"type_symbol")) cbf_failnez(cbf_get_value(rightoutcbf,&atomtype)) cbf_failnez(cbf_find_column(rightoutcbf,"label_atom_id")) cbf_failnez(cbf_get_value(rightoutcbf,&atomname)) if (!atomtype || !atomname || cbf_cistrcmp(atomtype,"C") || cbf_cistrcmp(atomname,"CA")) { cbf_failnez(cbf_remove_row(rightoutcbf)) row--; rightrows--; break; } } } } } } if (!foundent) { cbf_failnez(cbf_remove_row(rightoutcbf)) row--; rightrows--; } } } } /* Having pruned just to matching residues and possibly just matching CA, now prune to match all atoms by residue name, atom name and atom type */ { int leftrow, rightrow; unsigned int leftrows, rightrows; int leftresses, rightresses; int leftdels, rightdels; int leftainr, rightainr; int lastleft, lastright; const char * leftresname, * rightresname; const char * leftatomtype, * rightatomtype; const char * leftatomname, * rightatomname; int rightresnum, leftresnum; cbf_failnez (cbf_count_rows(leftoutcbf,&leftrows)) cbf_failnez (cbf_count_rows(rightoutcbf,&rightrows)) leftrow=rightrow=0; leftdels=rightdels=0; lastleft = lastright = -999999; leftainr = rightainr = 0; leftresses = rightresses = 0; while (leftrow < leftrows && rightrow < rightrows) { cbf_failnez(cbf_select_row(leftoutcbf, leftrow)) cbf_failnez(cbf_select_row(rightoutcbf, rightrow)) /* try to get the residue sequence numbers and the residue names */ cbf_failnez(cbf_find_column(leftoutcbf,"label_seq_id")) cbf_failnez(cbf_find_column(rightoutcbf,"label_seq_id")) if (!cbf_get_integervalue(leftoutcbf,&leftresnum) &&!cbf_find_column(leftoutcbf,"label_comp_id") &&!cbf_get_value(leftoutcbf,&leftresname) &&!cbf_get_integervalue(rightoutcbf,&rightresnum) &&!cbf_find_column(rightoutcbf,"label_comp_id") &&!cbf_get_value(rightoutcbf,&rightresname)) { if (leftresnum != lastleft) { if (leftainr!=0) leftresses++; lastleft = leftresnum; leftainr = 0; } if (rightresnum != lastright) { if (rightainr!=0) rightresses++; lastright = rightresnum; rightainr = 0; } cbf_failnez(cbf_find_column(leftoutcbf,"type_symbol")) cbf_failnez(cbf_get_value(leftoutcbf,&leftatomtype)) cbf_failnez(cbf_find_column(leftoutcbf,"label_atom_id")) cbf_failnez(cbf_get_value(leftoutcbf,&leftatomname)) cbf_failnez(cbf_find_column(rightoutcbf,"type_symbol")) cbf_failnez(cbf_get_value(rightoutcbf,&rightatomtype)) cbf_failnez(cbf_find_column(rightoutcbf,"label_atom_id")) cbf_failnez(cbf_get_value(rightoutcbf,&rightatomname)) leftainr++; rightainr++; if (!cbf_cistrcmp(leftatomtype,rightatomtype) &&!cbf_cistrcmp(leftatomname,rightatomname) &&!cbf_cistrcmp(leftresname,rightresname) &&leftainr==rightainr) { leftrow++; rightrow++; continue; } if (!cbf_cistrcmp(leftresname,rightresname)) { if (leftainr > rightainr) { cbf_failnez(cbf_remove_row(leftoutcbf)) leftrows--; leftainr--; rightainr--; leftdels++; continue; } if (leftainr < rightainr) { cbf_failnez(cbf_remove_row(rightoutcbf)) rightrows--; rightainr--; leftainr--; rightdels++; continue; } cbf_failnez(cbf_remove_row(leftoutcbf)) cbf_failnez(cbf_remove_row(rightoutcbf)) leftrows--; leftainr--; leftdels++; rightrows--; rightainr--; rightdels++; continue; } if (rightresnum > leftresnum ) { cbf_failnez(cbf_remove_row(leftoutcbf)) leftrows--; leftainr--; rightainr--; leftdels++; continue; } if (leftresnum > rightresnum ) { cbf_failnez(cbf_remove_row(rightoutcbf)) rightrows--; rightainr--; leftainr--; rightdels++; continue; } cbf_failnez(cbf_remove_row(leftoutcbf)) cbf_failnez(cbf_remove_row(rightoutcbf)) leftrows--; leftainr--; leftdels++; rightrows--; rightainr--; rightdels++; } } while (leftrow < leftrows ) { cbf_failnez(cbf_select_row(leftoutcbf, leftrow)) cbf_failnez(cbf_remove_row(leftoutcbf)) leftrows--; } while (rightrow < rightrows ) { cbf_failnez(cbf_select_row(rightoutcbf, rightrow)) cbf_failnez(cbf_remove_row(rightoutcbf)) rightrows--; } } if ( ! leftoutstr || strcmp(leftoutstr?leftoutstr:"","-") == 0 ) { leftout = stdout; } else if ( strcmp(leftoutstr?leftoutstr:"","/dev/null") ==0 ){ leftdevnull=1; } else { leftout = fopen (leftoutstr, "w+b"); } if ( ! rightoutstr || strcmp(rightoutstr?rightoutstr:"","-") == 0 ) { rightout = stdout; } else if ( strcmp(rightoutstr?rightoutstr:"","/dev/null") ==0 ){ rightdevnull=1; } else { rightout = fopen (rightoutstr, "w+b"); } cbf_failnez (cbf_write_widefile (leftoutcbf, leftout, 1, CIF, MIME_HEADERS|MSG_DIGEST, 0)) cbf_failnez (cbf_write_widefile (rightoutcbf, rightout, 1, CIF, MIME_HEADERS|MSG_DIGEST, 0)) exit(0); } int local_exit (int status) { exit(status); return 1; /* avoid warnings */ } ./CBFlib-0.9.2.2/examples/testcbf.c0000644000076500007650000000065511603702122015216 0ustar yayayaya#include "cbf.h" int main() { FILE *f; cbf_handle ch; int status; unsigned int m; f = fopen("examples/template_pilatus6m_2463x2527.cbf", "rb"); cbf_make_handle(&ch); status = cbf_read_widefile(ch, f, MSG_DIGEST); printf("read_widefile (%d)\n", status); status = cbf_count_datablocks(ch, &m); printf("count_dbs (%d) = %d\n", status, m); /* fclose(f);*/ /* let cbflib handle the closing of a file */ return 0; } ./CBFlib-0.9.2.2/examples/adscimg2cbf_sub.c0000644000076500007650000015615711603702122016612 0ustar yayayaya/********************************************************************** * adscimg2cbf -- convert an ADSC SMV image file to a cbf file * * * * Chris Nielsen, 5 December 2007 * * ADSC * * * * based on img2cbf from * * CBFlib Version 0.7.6 28 June 2006 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2008 Herbert J. Bernstein * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * WHILE YOU MAY ALTERNATIVE DISTRIBUTE THE API UNDER THE LGPL * * YOU MAY ***NOT*** DISTRBUTE THIS PROGRAM UNDER THE LGPL * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #include "cbf.h" #include "cbf_simple.h" #include #include #include #include #include int local_exit(int status) { exit(status); return status; /* to avoid warning messages */ } #undef cbf_failnez #define cbf_failnez(x) \ {int err; \ err = (x); \ if (err) { \ fprintf(stderr,"\nCBFlib fatal error %x \n",err); \ local_exit(-1); \ } \ } /****************************************************************/ /* * GETBO - Return the byte-order of the computer. * * 0 if little-endian * 1 if big-endian * 2 if unknown-endian * * 14-Sep-1994 Marty Stanton Brandeis University * */ /* Commented out 19 June 2008 because of optimization bug in gcc -- HJB int getbo() { long i4; long *pi4; short *i2; i4=1; pi4 = &i4; i2 = (short *) pi4; if ( *i2 == 1 && *(i2+1) == 0 ) return (0); else if ( *i2 == 0 && *(i2+1) == 1 ) return (1); else return(2); } */ void short_swap(p,n) unsigned short *p; int n; { register int i,j; register unsigned short *q; for(i = 0, q = p; i < n;i++,q++) { j = *q; *q = ((j << 8 ) | (j >> 8)) & 0x0000ffff; } } void gethd ( char* field, char* value, char* header ) { char *hp, *lhp, *fp, *vp; int l, j; char *newfield; /* * Find the last occurance of "field" in "header" */ l = strlen (field); newfield = (char*) malloc ( l + 3 ); *newfield = 10; strncpy (newfield+1, field, l); *(newfield+l+1) = '='; *(newfield+l+2) = (char) 0; l += 2; lhp = 0; for (hp=header; *hp != '}'; hp++) { for (fp=newfield, j=0; j X * * Define the origin to be the upper left hand corner, since * this is the "storage origin" of the data array. * * The incoming beam center value is nominally defined as the * adxv mm coordinate system: origin in mm in the lower left hand * corner. * * Other conventions are recognized either through additional header * keywords or "BEAM_CENTER" variants (future) found in the ADSC * header, or forced through the beam_center_convention parameter * to adscimg2cbf_sub() function. */ s[0] = '\0'; gethd("BEAM_CENTER_X", s, header); if('\0' == s[0]) header_beam_x = detector_center_x; else header_beam_x = atof(s); det_beam_center_to_origin_dist_x = - header_beam_x; s[0] = '\0'; gethd("BEAM_CENTER_Y", s, header); if('\0' == s[0]) header_beam_y = detector_center_y; else header_beam_y = atof(s); switch(beam_center_convention) { case BEAM_CENTER_FROM_HEADER: case BEAM_CENTER_LLHC: default: det_beam_center_to_origin_dist_x = - header_beam_x; det_beam_center_to_origin_dist_y = (smv_size1 - 1.5) * pixel_size - header_beam_y; break; case BEAM_CENTER_ULHC: det_beam_center_to_origin_dist_x = - header_beam_x; det_beam_center_to_origin_dist_y = header_beam_y; break; case BEAM_CENTER_MOSFLM: det_beam_center_to_origin_dist_x = - header_beam_y; det_beam_center_to_origin_dist_y = header_beam_x; break; } /* Date */ s[0] = '\0'; gethd("DATE", s, header); if('\0' == s[0]) { smv_date[0] = '\0'; cbf_date[0] = '\0'; } else { strcpy(smv_date, s); smv_date_to_cbf_date(smv_date, cbf_date); } /* Wavelength */ s[0] = '\0'; gethd("WAVELENGTH", s, header); if('\0' == s[0]) wavelength = -1; else { wavelength = atof(s); gain = gain / wavelength; } /* Oscillation start */ s[0] = '\0'; gethd("OSC_START", s, header); if('\0' == s[0]) oscillation_start = 0.0; else oscillation_start = atof(s); /* Oscillation range */ s[0] = '\0'; gethd("OSC_RANGE", s, header); if('\0' == s[0]) oscillation_range = 0.0; else oscillation_range = atof(s); /* Distance */ s[0] = '\0'; gethd("DISTANCE", s, header); if('\0' == s[0]) distance = -1; else distance = atof(s); /* Time */ s[0] = '\0'; gethd("TIME", s, header); if('\0' == s[0]) smv_time = -1; else smv_time = atof(s); overload = 65535; /* Image size and orientation & gain and overload */ dimension [0] = smv_size1; dimension [1] = smv_size2; precedence [0] = 1; precedence [1] = 2; direction [0] = "increasing"; direction [1] = "increasing"; /* Make sure to swap bytes if there is a change in byte order * between the machine which made the SMV file and this machine */ /* this_bo = getbo();*/ cbf_get_local_integer_byte_order(&local_bo); this_bo = (local_bo[0]=='l'||local_bo[0]=='L')?0:1; smv_bo = this_bo; s[0] = '\0'; gethd("BYTE_ORDER", s, header); if('\0' != s[0]) { if(0 == strcmp(s, "little_endian")) smv_bo = 0; else if(0 == strcmp(s, "big_endian")) smv_bo = 1; } if(this_bo != smv_bo) short_swap(data, smv_size1 * smv_size1); /* Make a cbf version of the image */ a = clock (); /* Create the cbf */ cbf_failnez (cbf_make_handle (&cbf)) /* Make a new data block */ cbf_failnez (cbf_new_datablock (cbf, "image_1")) /* Make the _diffrn category */ cbf_failnez (cbf_new_category (cbf, "diffrn")) cbf_failnez (cbf_new_column (cbf, "id")) cbf_failnez (cbf_set_value (cbf, "DS1")) /* Make the _diffrn_source category */ cbf_failnez (cbf_new_category (cbf, "diffrn_source")) cbf_failnez (cbf_new_column (cbf, "diffrn_id")) cbf_failnez (cbf_set_value (cbf, "DS1")) cbf_failnez (cbf_new_column (cbf, "source")) cbf_failnez (cbf_set_value (cbf, "synchrotron")) cbf_failnez (cbf_new_column (cbf, "type")) cbf_failnez (cbf_set_value (cbf, facility)) /* Make the _diffrn_radiation category */ cbf_failnez (cbf_new_category (cbf, "diffrn_radiation")) cbf_failnez (cbf_new_column (cbf, "diffrn_id")) cbf_failnez (cbf_set_value (cbf, "DS1")) cbf_failnez (cbf_new_column (cbf, "wavelength_id")) cbf_failnez (cbf_set_value (cbf, "L1")) /* Make the _diffrn_radiation_wavelength category */ cbf_failnez (cbf_new_category (cbf, "diffrn_radiation_wavelength")) cbf_failnez (cbf_new_column (cbf, "id")) cbf_failnez (cbf_set_value (cbf, "L1")) cbf_failnez (cbf_new_column (cbf, "wavelength")) if (wavelength > 0.0) cbf_failnez (cbf_set_doublevalue (cbf, "%.6f", wavelength)) cbf_failnez (cbf_new_column (cbf, "wt")) cbf_failnez (cbf_set_value (cbf, "1.0")) /* Make the _diffrn_measurement category */ cbf_failnez (cbf_new_category (cbf, "diffrn_measurement")) cbf_failnez (cbf_new_column (cbf, "diffrn_id")) cbf_failnez (cbf_set_value (cbf, "DS1")) cbf_failnez (cbf_new_column (cbf, "id")) cbf_failnez (cbf_set_value (cbf, "GONIOMETER")) cbf_failnez (cbf_new_column (cbf, "method")) cbf_failnez (cbf_set_value (cbf, "oscillation")) cbf_failnez (cbf_new_column (cbf, "number_of_axes")) cbf_failnez (cbf_set_integervalue (cbf, 1)) cbf_failnez (cbf_new_column (cbf, "sample_detector_distance")) if (distance > 0.0) cbf_failnez (cbf_set_doublevalue (cbf, "%.4f", distance)) else cbf_failnez (cbf_set_value (cbf, "unknown")) /* Make the _diffrn_measurement_axis category */ cbf_failnez (cbf_new_category (cbf, "diffrn_measurement_axis")) cbf_failnez (cbf_new_column (cbf, "measurement_id")) cbf_failnez (cbf_set_value (cbf, "GONIOMETER")) cbf_failnez (cbf_new_column (cbf, "axis_id")) cbf_failnez (cbf_set_value (cbf, "GONIOMETER_PHI")) /* Make the _diffrn_scan category */ cbf_failnez (cbf_new_category (cbf, "diffrn_scan")) cbf_failnez (cbf_new_column (cbf, "id")) cbf_failnez (cbf_set_value (cbf, "SCAN1")) cbf_failnez (cbf_new_column (cbf, "frame_id_start")) cbf_failnez (cbf_set_value (cbf, "FRAME1")) cbf_failnez (cbf_new_column (cbf, "frame_id_end")) cbf_failnez (cbf_set_value (cbf, "FRAME1")) cbf_failnez (cbf_new_column (cbf, "frames")) cbf_failnez (cbf_set_integervalue (cbf, 1)) /* Make the _diffrn_scan_axis category */ cbf_failnez (cbf_new_category (cbf, "diffrn_scan_axis")) cbf_failnez (cbf_new_column (cbf, "scan_id")) cbf_failnez (cbf_set_value (cbf, "SCAN1")) cbf_failnez (cbf_new_row (cbf)) cbf_failnez (cbf_set_value (cbf, "SCAN1")) cbf_failnez (cbf_new_row (cbf)) cbf_failnez (cbf_set_value (cbf, "SCAN1")) cbf_failnez (cbf_new_row (cbf)) cbf_failnez (cbf_set_value (cbf, "SCAN1")) cbf_failnez (cbf_new_row (cbf)) cbf_failnez (cbf_set_value (cbf, "SCAN1")) cbf_failnez (cbf_new_column (cbf, "axis_id")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_value (cbf, "GONIOMETER_PHI")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "DETECTOR_Z")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "DETECTOR_Y")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "DETECTOR_X")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "DETECTOR_PITCH")) cbf_failnez (cbf_new_column (cbf, "angle_start")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", oscillation_start)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_new_column (cbf, "angle_range")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", oscillation_range)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_new_column (cbf, "angle_increment")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", oscillation_range)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_new_column (cbf, "displacement_start")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", distance)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_new_column (cbf, "displacement_range")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_new_column (cbf, "displacement_increment")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) /* Make the _diffrn_scan_frame category */ cbf_failnez (cbf_new_category (cbf, "diffrn_scan_frame")) cbf_failnez (cbf_new_column (cbf, "frame_id")) cbf_failnez (cbf_set_value (cbf, "FRAME1")) cbf_failnez (cbf_new_column (cbf, "frame_number")) cbf_failnez (cbf_set_value (cbf, "1")) if(-1 != smv_time) { cbf_failnez (cbf_new_column (cbf, "integration_time")) cbf_failnez (cbf_set_doublevalue (cbf, "%.4f", smv_time)) } if('\0' != cbf_date[0]) { cbf_failnez (cbf_new_column (cbf, "date")) cbf_failnez (cbf_set_value (cbf, cbf_date)) } /* Make the _diffrn_scan_frame_axis category */ cbf_failnez (cbf_new_category (cbf, "diffrn_scan_frame_axis")) cbf_failnez (cbf_new_column (cbf, "frame_id")) cbf_failnez (cbf_set_value (cbf, "FRAME1")) cbf_failnez (cbf_new_row (cbf)) cbf_failnez (cbf_set_value (cbf, "FRAME1")) cbf_failnez (cbf_new_row (cbf)) cbf_failnez (cbf_set_value (cbf, "FRAME1")) cbf_failnez (cbf_new_row (cbf)) cbf_failnez (cbf_set_value (cbf, "FRAME1")) cbf_failnez (cbf_new_row (cbf)) cbf_failnez (cbf_set_value (cbf, "FRAME1")) cbf_failnez (cbf_new_column (cbf, "axis_id")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_value (cbf, "GONIOMETER_PHI")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "DETECTOR_Z")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "DETECTOR_Y")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "DETECTOR_X")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "DETECTOR_PITCH")) cbf_failnez (cbf_new_column (cbf, "angle")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", oscillation_start)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_new_column (cbf, "displacement")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.00)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", distance)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.2f", 0.0)) /* Make the _axis category */ cbf_failnez (cbf_new_category (cbf, "axis")) cbf_failnez (cbf_new_column (cbf, "id")) cbf_failnez (cbf_set_value (cbf, "GONIOMETER_PHI")) cbf_failnez (cbf_new_row (cbf)) cbf_failnez (cbf_set_value (cbf, "SOURCE")) cbf_failnez (cbf_new_row (cbf)) cbf_failnez (cbf_set_value (cbf, "GRAVITY")) cbf_failnez (cbf_new_row (cbf)) cbf_failnez (cbf_set_value (cbf, "DETECTOR_Z")) cbf_failnez (cbf_new_row (cbf)) cbf_failnez (cbf_set_value (cbf, "DETECTOR_Y")) cbf_failnez (cbf_new_row (cbf)) cbf_failnez (cbf_set_value (cbf, "DETECTOR_X")) cbf_failnez (cbf_new_row (cbf)) cbf_failnez (cbf_set_value (cbf, "DETECTOR_PITCH")) cbf_failnez (cbf_new_row (cbf)) cbf_failnez (cbf_set_value (cbf, "ELEMENT_X")) cbf_failnez (cbf_new_row (cbf)) cbf_failnez (cbf_set_value (cbf, "ELEMENT_Y")) cbf_failnez (cbf_new_column (cbf, "type")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_value (cbf, "rotation")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "general")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "general")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "translation")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "translation")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "translation")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "rotation")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "translation")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "translation")) cbf_failnez (cbf_new_column (cbf, "equipment")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_value (cbf, "goniometer")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "source")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "gravity")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "detector")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "detector")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "detector")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "detector")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "detector")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "detector")) cbf_failnez (cbf_new_column (cbf, "depends_on")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_value (cbf, ".")) cbf_failnez (cbf_set_typeofvalue (cbf, "null")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, ".")) cbf_failnez (cbf_set_typeofvalue (cbf, "null")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, ".")) cbf_failnez (cbf_set_typeofvalue (cbf, "null")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, ".")) cbf_failnez (cbf_set_typeofvalue (cbf, "null")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "DETECTOR_Z")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "DETECTOR_Y")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "DETECTOR_X")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "DETECTOR_PITCH")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "ELEMENT_X")) cbf_failnez (cbf_new_column (cbf, "vector[1]")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_value (cbf, "1")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "1")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "1")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_new_column (cbf, "vector[2]")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "-1")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "1")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "1")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "1")) cbf_failnez (cbf_new_column (cbf, "vector[3]")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "1")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "-1")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_new_column (cbf, "offset[1]")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_value (cbf, ".")) cbf_failnez (cbf_set_typeofvalue (cbf, "null")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, ".")) cbf_failnez (cbf_set_typeofvalue (cbf, "null")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, ".")) cbf_failnez (cbf_set_typeofvalue (cbf, "null")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.3f", det_beam_center_to_origin_dist_x)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_new_column (cbf, "offset[2]")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_value (cbf, ".")) cbf_failnez (cbf_set_typeofvalue (cbf, "null")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, ".")) cbf_failnez (cbf_set_typeofvalue (cbf, "null")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, ".")) cbf_failnez (cbf_set_typeofvalue (cbf, "null")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.3f", det_beam_center_to_origin_dist_y)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_new_column (cbf, "offset[3]")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_value (cbf, ".")) cbf_failnez (cbf_set_typeofvalue (cbf, "null")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, ".")) cbf_failnez (cbf_set_typeofvalue (cbf, "null")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, ".")) cbf_failnez (cbf_set_typeofvalue (cbf, "null")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "0")) /* Make the _diffrn_detector category */ cbf_failnez (cbf_new_category (cbf, "diffrn_detector")) cbf_failnez (cbf_new_column (cbf, "id")) cbf_failnez (cbf_set_value (cbf, detector_id)) cbf_failnez (cbf_new_column (cbf, "diffrn_id")) cbf_failnez (cbf_set_value (cbf, "DS1")) cbf_failnez (cbf_new_column (cbf, "type")) cbf_failnez (cbf_set_value (cbf, detector_type)) cbf_failnez (cbf_new_column (cbf, "details")) cbf_failnez (cbf_set_value (cbf, detector_mode)) cbf_failnez (cbf_new_column (cbf, "number_of_axes")) cbf_failnez (cbf_set_integervalue (cbf, 4)) /* Make the _diffrn_detector_axis category */ cbf_failnez (cbf_new_category (cbf, "diffrn_detector_axis")) cbf_failnez (cbf_new_column (cbf, "detector_id")) cbf_failnez (cbf_set_value (cbf, detector_id)) cbf_failnez (cbf_new_row (cbf)) cbf_failnez (cbf_set_value (cbf, detector_id)) cbf_failnez (cbf_new_row (cbf)) cbf_failnez (cbf_set_value (cbf, detector_id)) cbf_failnez (cbf_new_row (cbf)) cbf_failnez (cbf_set_value (cbf, detector_id)) cbf_failnez (cbf_new_column (cbf, "axis_id")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_value (cbf, "DETECTOR_X")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "DETECTOR_Y")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "DETECTOR_Z")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "DETECTOR_PITCH")) cbf_failnez (cbf_next_row (cbf)) /* Make the _diffrn_detector_element category */ cbf_failnez (cbf_new_category (cbf, "diffrn_detector_element")) cbf_failnez (cbf_new_column (cbf, "id")) cbf_failnez (cbf_set_value (cbf, "ELEMENT1")) cbf_failnez (cbf_new_column (cbf, "detector_id")) cbf_failnez (cbf_set_value (cbf, detector_id)) /* Make the _diffrn_frame_data category */ cbf_failnez (cbf_new_category (cbf, "diffrn_data_frame")) cbf_failnez (cbf_new_column (cbf, "id")) cbf_failnez (cbf_set_value (cbf, "frame_1")) cbf_failnez (cbf_new_column (cbf, "detector_element_id")) cbf_failnez (cbf_set_value (cbf, "ELEMENT1")) cbf_failnez (cbf_new_column (cbf, "detector_id")) cbf_failnez (cbf_set_value (cbf, detector_id)) cbf_failnez (cbf_new_column (cbf, "array_id")) cbf_failnez (cbf_set_value (cbf, "image_1")) cbf_failnez (cbf_new_column (cbf, "binary_id")) cbf_failnez (cbf_set_integervalue (cbf, 1)) cbf_failnez (cbf_new_column (cbf, "details")) cbf_failnez (cbf_set_value (cbf, header_as_details)) cbf_failnez (cbf_set_typeofvalue (cbf,"text")) free(header_as_details); /* Make the _array_structure_list category */ cbf_failnez (cbf_new_category (cbf, "array_structure_list")) cbf_failnez (cbf_new_column (cbf, "array_id")) cbf_failnez (cbf_set_value (cbf, "image_1")) cbf_failnez (cbf_new_row (cbf)) cbf_failnez (cbf_set_value (cbf, "image_1")) cbf_failnez (cbf_new_column (cbf, "index")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_integervalue (cbf, 1)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_integervalue (cbf, 2)) cbf_failnez (cbf_new_column (cbf, "dimension")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_integervalue (cbf, dimension [0])) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_integervalue (cbf, dimension [1])) cbf_failnez (cbf_new_column (cbf, "precedence")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_integervalue (cbf, precedence [0])) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_integervalue (cbf, precedence [1])) cbf_failnez (cbf_new_column (cbf, "direction")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_value (cbf, direction [0])) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, direction [1])) cbf_failnez (cbf_new_column (cbf, "axis_set_id")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_value (cbf, "ELEMENT_X")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "ELEMENT_Y")) /* Make the _array_element_size category */ cbf_failnez (cbf_new_category (cbf, "array_element_size")) cbf_failnez (cbf_new_column (cbf, "array_id")) cbf_failnez (cbf_set_value (cbf, "image_1")) cbf_failnez (cbf_new_row (cbf)) cbf_failnez (cbf_set_value (cbf, "image_1")) cbf_failnez (cbf_new_column (cbf, "index")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_integervalue (cbf, 1)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_integervalue (cbf, 2)) cbf_failnez (cbf_new_column (cbf, "size")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.3fe-6", pixel_size * 1000.)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.3fe-6", pixel_size * 1000.)) /* Make the _array_structure_list_axis category */ cbf_failnez (cbf_new_category (cbf, "array_structure_list_axis")) cbf_failnez (cbf_new_column (cbf, "axis_set_id")) cbf_failnez (cbf_set_value (cbf, "ELEMENT_X")) cbf_failnez (cbf_new_row (cbf)) cbf_failnez (cbf_set_value (cbf, "ELEMENT_Y")) cbf_failnez (cbf_new_column (cbf, "axis_id")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_value (cbf, "ELEMENT_X")) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_value (cbf, "ELEMENT_Y")) cbf_failnez (cbf_new_column (cbf, "displacement")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.6f", 0.0)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.6f", 0.0)) cbf_failnez (cbf_new_column (cbf, "displacement_increment")) cbf_failnez (cbf_rewind_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.6f", pixel_size)) cbf_failnez (cbf_next_row (cbf)) cbf_failnez (cbf_set_doublevalue (cbf, "%.6f", -pixel_size)) /* Make the _array_intensities category */ cbf_failnez (cbf_new_category (cbf, "array_intensities")) cbf_failnez (cbf_new_column (cbf, "array_id")) cbf_failnez (cbf_set_value (cbf, "image_1")) cbf_failnez (cbf_new_column (cbf, "binary_id")) cbf_failnez (cbf_set_integervalue (cbf, 1)) cbf_failnez (cbf_new_column (cbf, "linearity")) cbf_failnez (cbf_set_value (cbf, "linear")) cbf_failnez (cbf_new_column (cbf, "gain")) if (gain > 0.0) cbf_failnez (cbf_set_doublevalue (cbf, "%.3g", gain)) cbf_failnez (cbf_new_column (cbf, "overload")) if (overload > 0.0) cbf_failnez (cbf_set_integervalue (cbf, overload)) cbf_failnez (cbf_new_column (cbf, "undefined_value")) cbf_failnez (cbf_set_integervalue (cbf, 0)) cbf_failnez (cbf_new_column (cbf, "pixel_slow_bin_size")) cbf_failnez (cbf_set_integervalue (cbf, smv_bin)) cbf_failnez (cbf_new_column (cbf, "pixel_fast_bin_size")) cbf_failnez (cbf_set_integervalue (cbf, smv_bin)) /* Make the _array_data category */ cbf_failnez (cbf_new_category (cbf, "array_data")) cbf_failnez (cbf_new_column (cbf, "array_id")) cbf_failnez (cbf_set_value (cbf, "image_1")) cbf_failnez (cbf_new_column (cbf, "binary_id")) cbf_failnez (cbf_set_integervalue (cbf, 1)) cbf_failnez (cbf_new_column (cbf, "data")) /* Save the binary data */ if(NULL == (data_as_int = (int *) malloc(smv_size1 * smv_size2 * sizeof (int)))) { fprintf(stderr, "Error mallocing %d bytes of temporary memory for image conversion\n", (int) (smv_size1 * smv_size2 * sizeof (int))); return(1); } ip = data_as_int; up = data; for(i = 0; i < smv_size2; i++) for(j = 0; j < smv_size1; j++) *ip++ = 0x0000ffff & *up++; /* int cbf_set_integerarray_wdims_fs (cbf_handle handle, unsigned int compression, int id, void *value, size_t elsize, int elsign, size_t nelem, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding) */ cbf_failnez( cbf_set_integerarray_wdims_fs ((cbf_handle) cbf, (unsigned int) pack_flags, (int) 1, data_as_int, (size_t) sizeof (int), (int) 1, (size_t) smv_size1 * smv_size2, "little_endian", (size_t) smv_size1, (size_t) smv_size2, (size_t) 0, (size_t) 0)) /* Write the new file */ out = fopen (cbf_filename, "w+b"); if (!out) { fprintf (stderr, " Couldn't open the CBF file %s\n", cbf_filename); exit (1); } cbf_failnez (cbf_write_file (cbf, out, 1, CBF, MSG_DIGEST | MIME_HEADERS | pad_flag, 0)) /* Free the cbf */ cbf_failnez (cbf_free_handle (cbf)) free(data_as_int); b = clock (); fprintf (stderr, " Time to write the CBF image: %.3fs\n", ((b - a) * 1.0) / CLOCKS_PER_SEC); return 0; } ./CBFlib-0.9.2.2/examples/cif2c.c0000644000076500007650000007307611603702122014561 0ustar yayayaya/********************************************************************** * cif2c -- convert a cif to a CBFlib function * * * * Version 0.9.1 6 January 2010 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * WHILE YOU MAY ALTERNATIVE DISTRIBUTE THE API UNDER THE LGPL * * YOU MAY ***NOT*** DISTRBUTE THIS PROGRAM UNDER THE LGPL * * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /********************************************************************** * SYNOPSIS * * * * cif2c [-i input_cif] [-o output_C_function] \ * * [-n name_of_function] \ * * [input_cif] [output_C_function] * * * * the options are: * * * * -i input_cif (default: stdin) * * the input file in CIF or CBF format. If input_cif is not * * specified or is given as "-", it is copied from stdin to a * * temporary file. * * * * -o output_C_function (default: stdout) * * the file that will receive the code of a C function that will * * regenerate the given cif, replacing binary text fields with * * "." If no output_C_code is specified or is given as "-", * * the output is written to stdout * * * * -n name_of_function (default: cbf_create_template) * * the name of the function that will be written * * * * * The function that is created has a cbf handle as it argument * * and returns an int value, which will be 0 for normal completion. * * * * Binary sections are not recreated by the C function * * * * * **********************************************************************/ /********************************************************************** * CREDITS * * * * This program is a Crystallographic Information File (CIF) * * application. Please see the IUCR Policy below. See the IUCR * * web page (http://www.iucr.org) or its mirrors for background * * and references on CIF. * * * * This program is a Crystallographic Binary File (CBF) application. * * Please see the ImgCIF/CBF web page at * * * * http://ndbserver.rutgers.edu/mmcif/cbf * * * * for background and references. The CBF definition is available * * on the web page created by Andy Hammersley at * * * * http://www.ersf.fr/computing/Forum/imgCIF/cbf_definition.html * * * * This program is a CBFlib application. See "CBFLIB, An ANSI-C * * API for Crystallographic Binary Files", Version 0.1, April 1998 * * by Paul J. Ellis, Stanford Synchrotron Radiation Laboratory, * * ellis@ssrl.slac.stanford.edu * * * * This program uses routines derived from mpack/munpack version * * 1.5, ftp://ftp.andrew.cmu.edu/pub/mpack by John G. Myers, * * jgm+@cmu.edu. "Mpack and munpack are utilties for encoding and * * decoding ... binary files in MIME ... format." Please see the * * copyright notices and disclaimers in the mpack/munpack routines * * * * This program uses routines derived from the "RSA Data Security, * * Inc. MD5 Message-Digest Algorithm." Please see the copyright * * notice and disclaimer in md5c.c * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #include "cbf.h" #include "img.h" #include #include #include #include #include #include #include "cbf_getopt.h" #include #define C2CBUFSIZ 8192 #ifdef __MINGW32__ #define NOMKSTEMP #define NOTMPDIR #endif int local_exit (int status); #undef cbf_failnez #define cbf_failnez(x) \ {int err; \ err = (x); \ if (err) { \ fprintf(stderr,"CBFlib fatal error %d\n",err); \ local_exit (-1); \ } \ } void set_MP_terms(int crterm, int nlterm); int main (int argc, char *argv []) { FILE *in, *out, *file; clock_t a,b; cbf_handle cif; cbf_handle cbf; cbf_getopt_handle opts; int c; int errflg = 0; const char *cifin, *codeout, *function_name; char ciftmp[19]; #ifdef NOMKSTEMP char *xciftmp; #endif #ifndef NOMKSTEMP int ciftmpfd; #endif int ciftmpused; unsigned int nbytes; char buf[C2CBUFSIZ]; char ovalue[C2CBUFSIZ*8]; unsigned int blocks, categories, blocknum, catnum; const char *datablock_name; const char *category_name; const char *column_name; const char *value; unsigned int colnum, rownum; unsigned int columns; unsigned int rows; const char * optarg; /* Extract options */ /********************************************************************** * cif2c [-i input_cif] [-o output_C_function] \ * * [-n {name_of_function] \ * * [input_cif] [output_cbf] * * * **********************************************************************/ cifin = NULL; codeout = NULL; function_name = NULL; ciftmpused = 0; cbf_failnez(cbf_make_getopt_handle(&opts)) cbf_failnez(cbf_getopt_parse(opts, argc, argv, "-i(input):" \ "-o(output):" \ "-n(name_of_function):" \ )) if (!cbf_rewind_getopt_option(opts)) for(;!cbf_get_getopt_data(opts,&c,NULL,NULL,&optarg);cbf_next_getopt_option(opts)) { if (!c) break; switch (c) { case 'i': if (cifin) errflg++; else cifin = optarg; break; case 'o': if (codeout) errflg++; else codeout = optarg; break; case 'n': if (function_name) errflg++; else function_name = optarg; break; default: errflg++; break; } } for(;!cbf_get_getopt_data(opts,&c,NULL,NULL,&optarg);cbf_next_getopt_option(opts)) { if (!cifin) { cifin = optarg; } else { if (!codeout) { codeout = optarg; } else { errflg++; } } } if (errflg) { fprintf(stderr,"cif2c: Usage: \n"); fprintf(stderr, " cif2c [-i input_cif] [-o output_C_function] \\\n"); fprintf(stderr, " [-n name_of_function] \\\n"); fprintf(stderr, " [input_cif] [output_C_function] \n\n"); exit(2); } /* Read the cif */ if (!cifin || strcmp(cifin?cifin:"","-") == 0) { #ifdef NOTMPDIR strcpy(ciftmp, "cif2cXXXXXX"); #else strcpy(ciftmp, "/tmp/cif2cXXXXXX"); #endif #ifdef NOMKSTEMP if ((xciftmp=mktemp(ciftmp)) == NULL ) { fprintf(stderr,"\n cif2c: Can't create temporary file name %s.\n", ciftmp); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } if ( (file = fopen(ciftmp,"wb+")) == NULL) { fprintf(stderr,"Can't open temporary file %s.\n", ciftmp); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } #else if ((ciftmpfd = mkstemp(ciftmp)) == -1 ) { fprintf(stderr,"Can't create temporary file %s.\n", ciftmp); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } if ( (file = fdopen(ciftmpfd, "w+")) == NULL) { fprintf(stderr,"Can't open temporary file %s.\n", ciftmp); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } #endif while ((nbytes = fread(buf, 1, C2CBUFSIZ, stdin))) { if(nbytes != fwrite(buf, 1, nbytes, file)) { fprintf(stderr,"Failed to write %s.\n", ciftmp); exit(1); } } fclose(file); cifin = ciftmp; ciftmpused = 1; } if ( cbf_make_handle (&cif) ) { fprintf(stderr,"Failed to create handle for input_cif\n"); exit(1); } if ( cbf_make_handle (&cbf) ) { fprintf(stderr,"Failed to create handle for output_cbf\n"); exit(1); } a = clock (); /* Read the file */ if (!(in = fopen (cifin, "rb"))) { fprintf (stderr,"Couldn't open the input CIF file %s\n", cifin); exit (1); } if (ciftmpused) { if (unlink(ciftmp) != 0 ) { fprintf(stderr,"cif2cif: Can't unlink temporary file %s.\n", ciftmp); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } } cbf_failnez (cbf_read_file (cif, in, MSG_DIGEST)) /* Prepare the output file */ if ( ! codeout || strcmp(codeout?codeout:"","-") == 0 ) { out = stdout; } else { out = fopen (codeout, "w+b"); } if ( ! out ) { printf (" Couldn't open the output code file %s\n", codeout); exit (1); } /* Start the code output */ fprintf(out,"/* Code generated by cif2c */\n"); fprintf(out,"#ifdef __cplusplus\n"); fprintf(out,"extern \"C\" {\n\n"); fprintf(out,"#endif\n\n"); fprintf(out,"#include \"cbf.h\"\n"); fprintf(out,"#include \"cbf_simple.h\"\n"); if (!function_name) function_name = "cbf_create_template"; fprintf(out,"int %s(cbf_handle handle) {\n\n",function_name); cbf_failnez (cbf_rewind_datablock(cif)) cbf_failnez (cbf_count_datablocks(cif, &blocks)) for (blocknum = 0; blocknum < blocks; blocknum++ ) { /* start of copy loop */ cbf_failnez (cbf_select_datablock(cif, blocknum)) cbf_failnez (cbf_datablock_name(cif, &datablock_name)) fprintf(out," cbf_failnez (cbf_force_new_datablock(handle, \"%s\"))\n", datablock_name); if ( !cbf_rewind_category(cif) ) { cbf_failnez (cbf_count_categories(cif, &categories)) for (catnum = 0; catnum < categories; catnum++) { cbf_select_category(cif, catnum); cbf_category_name(cif,&category_name); fprintf(out,"\n cbf_failnez (cbf_force_new_category(handle,\"%s\"))\n", category_name); cbf_count_rows(cif,&rows); cbf_count_columns(cif,&columns); /* Transfer the columns names from cif to cbf */ if ( ! cbf_rewind_column(cif) ) { do { cbf_failnez(cbf_column_name(cif, &column_name)) fprintf(out," cbf_failnez (cbf_require_column(handle,\"%s\"))\n", column_name); } while ( ! cbf_next_column(cif) ); cbf_rewind_column(cif); cbf_rewind_row(cif); } /* Transfer the rows from cif to cbf */ for (rownum = 0; rownum < rows; rownum++ ) { cbf_failnez (cbf_select_row(cif, rownum)) fprintf(out," cbf_failnez (cbf_new_row(handle))\n"); cbf_rewind_column(cif); for (colnum = 0; colnum < columns; colnum++ ) { const char *typeofvalue; cbf_failnez (cbf_select_column(cif, colnum)) cbf_failnez (cbf_column_name(cif, &column_name)) if ( ! cbf_get_value(cif, &value) ) { int ipos, opos, skip; cbf_failnez (cbf_get_typeofvalue(cif, &typeofvalue)) ipos = 0; opos = 0; while(value[ipos]) { skip = 0; switch (value[ipos]) { case '"': case '\\': ovalue[opos++] = '\\'; break; case '\t': ovalue[opos++] = '\\'; ovalue[opos++] = 't'; skip = 1; break; case '\n': ovalue[opos++] = '\\'; ovalue[opos++] = 'n'; skip = 1; break; } if ( !skip && ((unsigned char)(value[ipos]) < 32 || (unsigned char)(value[ipos]) >= 127)) { sprintf(ovalue+opos,"\\0x%03o",(unsigned char)value[ipos]); opos+= 6; skip = 1; } if ( !skip ) ovalue[opos++] = value[ipos++]; else ipos++; } ovalue[opos] = '\0'; fprintf(out," cbf_failnez (cbf_find_column(handle, \"%s\"))\n", column_name); fprintf(out," cbf_failnez (cbf_set_value(handle, \"%s\"))\n", ovalue); fprintf(out," cbf_failnez (cbf_set_typeofvalue(handle, \"%s\"))\n", typeofvalue); } else { fprintf(out," cbf_failnez (cbf_find_column(handle, \"%s\"))\n", column_name); fprintf(out," cbf_failnez (cbf_set_value(handle, \".\"))\n"); fprintf(out," cbf_failnez (cbf_set_typeofvalue(handle, \"%s\"))\n", "null"); } } } } } } fprintf(out," return 0;\n\n}\n"); fprintf(out,"#ifdef __cplusplus\n\n"); fprintf(out,"}\n"); fprintf(out,"#endif\n"); b = clock (); fprintf (stderr, " Time to read input_cif: %.3fs\n", ((b - a) * 1.0) / CLOCKS_PER_SEC); a = clock (); cbf_failnez (cbf_free_handle (cbf)) b = clock (); fprintf (stderr, " Time to write the code: %.3fs\n", ((b - a) * 1.0) / CLOCKS_PER_SEC); exit(0); } int local_exit (int status) { exit(status); return 1; /* avoid warnings */ } ./CBFlib-0.9.2.2/examples/template_adscquantum315_3072x3072.cbf0000644000076500007650000001325511603702122021724 0ustar yayayaya###CBF: VERSION 1.1 data_image_1 # category DIFFRN loop_ _diffrn.id _diffrn.crystal_id DIFFRN_ID DIFFRN_CRYSTAL_ID # category DIFFRN_SOURCE loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.current _diffrn_source.type DIFFRN_ID synchrotron 100.0 'SSRL beamline 1-5' # category DIFFRN_RADIATION loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.probe _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source _diffrn_radiation.collimation DIFFRN_ID WAVELENGTH1 x-ray 'Si 111' 0.8 0.0 0.08 0.01 0.00 '0.20 mm x 0.20 mm' # category DIFFRN_RADIATION_WAVELENGTH loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.979381 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.details _diffrn_detector.number_of_axes DIFFRN_ID ADSCQ315-SNXXX 'ADSC QUANTUM315' 'slow mode' 4 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id ADSCQ315-SNXXX DETECTOR_X ADSCQ315-SNXXX DETECTOR_Y ADSCQ315-SNXXX DETECTOR_Z ADSCQ315-SNXXX DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 ADSCQ315-SNXXX # category DIFFRN_DATA_FRAME loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method _diffrn_measurement.details DIFFRN_ID GONIOMETER 3 rotation 'i0=1.000 i1=1.000 i2=1.000 ib=1.000 beamstop=20 mm 0% attenuation' # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 0.0 SCAN1 1997-12-04T10:23:48 # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 0.0 0.0 FRAME1 GONIOMETER_KAPPA 0.0 0.0 FRAME1 GONIOMETER_PHI 0.0 0.0 FRAME1 DETECTOR_Z 0.0 0.0 FRAME1 DETECTOR_Y 0.0 0.0 FRAME1 DETECTOR_X 0.0 0.0 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0 0.76604 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 -1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_X 0 1 0 0 0 0 ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 -157.500 157.500 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 3072 1 increasing ELEMENT_X ARRAY1 2 3072 2 increasing ELEMENT_Y # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.051294 0.102588 ELEMENT_Y ELEMENT_Y -0.051294 -0.102588 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.overload _array_intensities.undefined_value _array_intensities.pixel_slow_bin_size _array_intensities.pixel_fast_bin_size ARRAY1 1 linear 2.45 65535 0 2 2 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" packed little_endian # category ARRAY_DATA loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 0.000102588 ARRAY1 2 0.000102588 # category ARRAY_DATA loop_ _array_data.array_id _array_data.binary_id _array_data.data ARRAY1 1 ? ./CBFlib-0.9.2.2/examples/template_pilatus6m_2463x2527.cbf0000644000076500007650000002303411603702122021075 0ustar yayayaya###CBF: VERSION 1.5 data_image_1 # category DIFFRN loop_ _diffrn.id _diffrn.crystal_id DIFFRN_ID DIFFRN_CRYSTAL_ID # category DIFFRN_SOURCE _diffrn_source.diffrn_id DIFFRN_ID _diffrn_source.source synchrotron _diffrn_source.type '?' # category DIFFRN_RADIATION _diffrn_radiation.diffrn_id DIFFRN_ID _diffrn_radiation.wavelength_id L1 # category DIFFRN_RADIATION_WAVELENGTH _diffrn_radiation_wavelength.id L1 _diffrn_radiation_wavelength.wavelength 1.5418 _diffrn_radiation_wavelength.wt 1.0 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.details _diffrn_detector.number_of_axes DIFFRN_ID Pilatus6M 'SLS Pilatus 6M' . 3 # category DIFFRN_DETECTOR_AXIS loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id Pilatus6M DETECTOR_Y Pilatus6M DETECTOR_Z Pilatus6M DETECTOR_PITCH # category DIFFRN_DETECTOR_ELEMENT loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id 1 Pilatus6M # category DIFFRN_DATA_FRAME _diffrn_data_frame.id frame_1 _diffrn_data_frame.detector_element_id 1 _diffrn_data_frame.detector_id Pilatus6M _diffrn_data_frame.array_id image_1 _diffrn_data_frame.binary_id 1 # category DIFFRN_MEASUREMENT loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method _diffrn_measurement.details DIFFRN_ID GONIOMETER 3 oscillation '.' # category DIFFRN_MEASUREMENT_AXIS loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_PHI GONIOMETER GONIOMETER_KAPPA GONIOMETER GONIOMETER_OMEGA # category DIFFRN_SCAN loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # category DIFFRN_SCAN_AXIS loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_KAPPA 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 GONIOMETER_PHI 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.0 0.0 0.0 SCAN1 DETECTOR_PITCH 0.0 0.0 0.0 0.0 0.0 0.0 # category DIFFRN_SCAN_FRAME loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 0.0 SCAN1 "1997-12-04T10:23:48" # category DIFFRN_SCAN_FRAME_AXIS loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 0.0 0.0 FRAME1 GONIOMETER_KAPPA 0.0 0.0 FRAME1 GONIOMETER_PHI 0.0 0.0 FRAME1 DETECTOR_Z 0.0 0.0 FRAME1 DETECTOR_Y 0.0 0.0 FRAME1 DETECTOR_PITCH 0.0 0.0 # category AXIS ################################################################################ # # # This is a fairly general set of axis definitions based on the setup # # at SLS X06SA as of 22 June 2007 when using the PILATUS 6M SN 1 # # # # The actual setup does not have a full goniometer but to show an examples of # # complete setup, a kappa geometry goniometer has been defined. In the actual# # beamline there is only one axis, rotating clockwise around x, which we are # # calling GONIOMETER_PHI, marked as dependent on GONIOMETER_KAPPA, which is # # dependent on GONIOMETER_OMEGA. As long as GONIOMETER_KAPPA and # # GONIOMETER_OMEGA are left at their 0 reference position, there should be # # no harm in leaving them in this template. # # # # # ################################################################################ loop_ _axis.id #___ _axis.type #___\___________ _axis.equipment #___|___________\____________ _axis.depends_on #___|___________|____________\______________ _axis.vector[1] #___|___________|____________|______________\__ _axis.vector[2] #___|___________|____________|______________|__\__ _axis.vector[3] #___|___________|____________|______________|__|__\ _axis.offset[1] #___|___________|____________|______________|__|__|___ _axis.offset[2] #___|___________|____________|______________|__|__|___\__ _axis.offset[3] #___|___________|____________|______________|__|__|___|__\__ # | | | | | | | | \ # | | | | | | | | | ######################|###########|############|##############|##|##|###|##|##| # The SLS Beamline axis convention is similar to the imgCIF convention, but | # Y and Z run the other way | | | | | | | | ######################|###########|############|##############|##|##|###|##|##| # | | | | | | | | | SLS_X general general . 1 0 0 0 0 0 SLS_Y general general . 0 -1 0 0 0 0 SLS_Z general general . 0 0 -1 0 0 0 # | | | | | | | | | ######################|###########|############|##############|##|##|###|##|##| # We define a kappa geometry with a left-handed omega and phi and a right- | | # handed kappa. The kappa axis arm is at the top when omega is zero | | | ######################|###########|############|##############|##|##|###|##|##| # | | | | | | | | | GONIOMETER_OMEGA rotation goniometer . -1 0 0 . . . GONIOMETER_KAPPA rotation goniometer GONIOMETER_OMEGA 0.64279 0.76604 0 . . . GONIOMETER_PHI rotation goniometer GONIOMETER_KAPPA -1 0 0 . . . ######################|###########|############|##############|##|##|###|##|##| SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . ######################|###########|############|##############|##|##|###|##|##| # | | | | | | | | | ######################|###########|############|##############|##|##|###|##|##| # The detector is assumed to be mounted on an arm parallel to the beam | | # with a DETECTOR_Y vertical translation and a pitch axis | | ######################|###########|############|##############|##|##|###|##|##| # | | | | | | | | | DETECTOR_Z translation detector . 0 0 -1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 -1 0 0 0 0 DETECTOR_PITCH rotation detector DETECTOR_Y 1 0 0 0 0 0 ######################|###########|############|##############|##|##|###|##|##| # This detector is assumed to have the 0,0 corner at +X and -Y | | | | | # we assume a 2463 x 2527 detector on a 0.172 mm pixel pitch | | | | | ######################|###########|############|##############|##|##|###|##|##| # | | | | | | | | | ELEMENT_X translation detector DETECTOR_PITCH 1 0 0 211.818 -217.322 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 # category ARRAY_STRUCTURE_LIST loop_ _array_structure_list.array_id _array_structure_list.axis_set_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction image_1 ELEMENT_X 1 2463 1 increasing image_1 ELEMENT_Y 2 2527 2 increasing # category ARRAY_STRUCTURE_LIST_AXIS loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X -0.086 -0.172 ELEMENT_Y ELEMENT_Y 0.086 0.172 # category ARRAY_INTENSITIES loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value image_1 1 linear 1 . 67000000 -3 # category ARRAY_STRUCTURE loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order image_1 "signed 32-bit integer" byte_offset little_endian # category ARRAY_ELEMENT_SIZE loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size image_1 1 0.172e-3 image_1 2 0.172e-3 # category ARRAY_INTENSITIES _array_intensities.array_id image_1 _array_intensities.binary_id 1 _array_intensities.linearity linear # category ARRAY_DATA _array_data.header_convention SLS_1.0 _array_data.header_contents . _array_data.array_id image_1 _array_data.binary_id 1 _array_data.data . ./CBFlib-0.9.2.2/examples/dectris_cbf_template_test/0000755000076500007650000000000011603703070020616 5ustar yayayaya./CBFlib-0.9.2.2/examples/dectris_cbf_template_test/mx_cbf_t_extras.h0000644000076500007650000000061111603702122024131 0ustar yayayaya/* mx_cbf_t_extras.h - some extra includes for the test/demo program */ #ifndef MX_CBFT_EXTRAS_H #define MX_CBFT_EXTRAS_H #define IMAGE_NCOL 2463 /* width of 6M */ #define IMAGE_NROW 2527 /* height of 6M */ #define LENFN 180 char image_timestamp[] = "2010-06-20T17:54.329"; int count_cutoff = 1048575; int camera_wide = 2463; int camera_high = 2527; double exposure_time=0.095; #endif ./CBFlib-0.9.2.2/examples/dectris_cbf_template_test/mx_parms.h0000644000076500007650000000462111603702122022615 0ustar yayayaya/* mx_parms.h - declarations for parsing MX paramters */ #ifndef MX_PARAMS_H #define MX_PARAMS_H /* prototypes of functions */ int parse_mx_param_string(char *); int format_mx_params(char *, int); int format_non_mx_params(char *, int); int format_mx_single(char *, char *); void increment_mx_settings(int); int setup_cbf_template(char *); int print_cbf_header(char *, int, char *); /* start of MX_PARAMS enum - please do not change this comment - lines below will change */ typedef enum { Wavelength = 1, Energy_range, Detector_distance, Detector_Voffset, Beam_xy, Beam_x, Beam_y, Flux, Filter_transmission, Start_angle, Angle_increment, Detector_2theta, Polarization, Alpha, Kappa, Phi, Phi_increment, Chi, Chi_increment, Oscillation_axis, N_oscillations, Start_position, Position_increment, Shutter_time, CBF_template_file, Timestamp, Exposure_period, Exposure_time, Count_cutoff, Compression_type, X_dimension, Y_dimension, } MX_PARAMS_CMND ; typedef struct { MX_PARAMS_CMND cmnd; char *name; } MX_PARAMS_LIST ; #ifdef MX_PARAMS_MAIN static MX_PARAMS_LIST mx_params_list[] = { { Wavelength, "Wavelength" }, { Energy_range, "Energy_range" }, { Detector_distance, "Detector_distance" }, { Detector_Voffset, "Detector_Voffset" }, { Beam_xy, "Beam_xy" }, { Beam_x, "Beam_x" }, { Beam_y, "Beam_y" }, { Flux, "Flux" }, { Filter_transmission, "Filter_transmission" }, { Start_angle, "Start_angle" }, { Angle_increment, "Angle_increment" }, { Detector_2theta, "Detector_2theta" }, { Polarization, "Polarization" }, { Alpha, "Alpha" }, { Kappa, "Kappa" }, { Phi, "Phi" }, { Phi_increment, "Phi_increment" }, { Chi, "Chi" }, { Chi_increment, "Chi_increment" }, { Oscillation_axis, "Oscillation_axis" }, { N_oscillations, "N_oscillations" }, { Start_position, "Start_position" }, { Position_increment, "Position_increment" }, { Shutter_time, "Shutter_time" }, { CBF_template_file, "CBF_template_file" }, { Timestamp, "Timestamp" }, { Exposure_period, "Exposure_period" }, { Exposure_time, "Exposure_time" }, { Count_cutoff, "Count_cutoff" }, { Compression_type, "Compression_type" }, { X_dimension, "X_dimension" }, { Y_dimension, "Y_dimension" }, } ; static int mx_params_count = sizeof(mx_params_list)/sizeof(MX_PARAMS_LIST); /* end of variable data - please do not change this comment */ #endif #endif ./CBFlib-0.9.2.2/examples/dectris_cbf_template_test/cbf_template_t.c0000644000076500007650000005440511603702122023737 0ustar yayayaya/* test program to output a CBF header from a template */ /* gcc -g -Wall -o cbf_template_t cbf_template_t.c */ /* ** ** GPL license declared below. ** ** Copyright (C) 2010 E. F. Eikenberry, DECTRIS, AG ** All rights reserved. ** ** This program is free software; you can redistribute it and/or modify ** it under the terms of the GNU General Public License as published by ** the Free Software Foundation; either version 2 of the License, or ** (at your option) any later version. ** ** This program is distributed in the hope that it will be useful, ** but WITHOUT ANY WARRANTY; without even the implied warranty of ** MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the ** GNU General Public License for more details. ** ** You should have received a copy of the GNU General Public License ** along with this program; if not, write to the Free Software ** Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307, USA. ** ** EF Eikenberry, Jun, 2010 ** DECTRIS, Ltd. Neuenhoferstrasse 107, CH-5400 Baden, Switzerland. */ #define MX_PARAMS_MAIN /* turn on space allocations in mx_parms.h */ #include #include #include #include #include #include #include #include "mx_parms.h" #include "mx_cbf_t_extras.h" /* ** dummy functions */ int set_current_energy(double a, int b, int c, char *d) { return 0; } double dcb_get_exposure_period(void) { return 0.100; } /*****************************************************************************\ ** ** ** Global variables ** ** ** \*****************************************************************************/ #define TEXT_SIZE 30 static float mx_beam_x=(float)IMAGE_NCOL/2.0; static int mx_beam_x_defined=0; static float mx_beam_y=(float)IMAGE_NROW/2.0; static int mx_beam_y_defined=0; static int mx_n_oscilations=1; static int mx_n_oscilations_defined=0; static float mx_wavelength=1.54; static int mx_wavelength_defined=0; static float mx_det_distance=1.0; static int mx_det_distance_defined=0; static float mx_det_voffset=0.0; static int mx_det_voffset_defined=0; static float mx_start_angle=0.0; static int mx_start_angle_defined=0; static float mx_angle_increment=0.1; static int mx_angle_increment_defined=0; static float mx_det_2theta=0.0; static int mx_det_2theta_defined=0; static float mx_polarization=0.99; static int mx_polarization_defined=0; static float mx_alpha=0.0; static int mx_alpha_defined=0; static float mx_kappa=0.0; static int mx_kappa_defined=0; static float mx_phi=0.0; static int mx_phi_defined=0; static float mx_phi_increment=0.0; static int mx_phi_increment_defined=0; static float mx_chi=0.0; static int mx_chi_defined=0; static float mx_chi_increment=0.0; static int mx_chi_increment_defined=0; static float mx_flux=0.0; static int mx_flux_defined=0; static float mx_filter_tx=1.0; static int mx_filter_tx_defined=0; static float mx_e_range_low=0.0; static int mx_e_range_low_defined=0; static float mx_e_range_hi=0.0; static int mx_e_range_hi_defined=0; static char mx_oscillation_axis[TEXT_SIZE]="X, CW"; static int mx_oscillation_axis_defined=0; static float mx_start_position=0.0; static int mx_start_position_defined=0; static float mx_position_increment=0.0; static int mx_position_increment_defined=0; static float mx_shutter_time=0.0; static int mx_shutter_time_defined=0; static char cbf_template_file[LENFN]="\0"; static int cbf_template_file_defined=0; static char msg[80]; /*****************************************************************************\ ** ** ** End of global variables ** ** ** \*****************************************************************************/ /* ----- Functions defined in this module ---- */ static MX_PARAMS_CMND find_mx_param_command(char **); static MX_PARAMS_CMND find_mx_param_command(char **pP) { int i, j, n, idx=0; char *p=*pP; msg[0]='\0'; while(*p && (isspace(*p) || *p==';' || *p==',')) /* space to next command */ p++; if (*p == '\0') /* end of line? */ return 0; for (n=0; *(p+n); n++) /* count characters in command */ if (!isalnum(*(p+n)) && *(p+n)!='_') /* allows '_' */ break; j = 0; /* count matching names */ for (i = 0; i < mx_params_count; i++) if ( strncasecmp(p, mx_params_list[i].name, n) == 0 ) { idx = i; /* permit unambiguous abbreviations */ j++; if ( n == strlen(mx_params_list[i].name) ) { j = 1; /* to skip next block */ break; /* exact match is exempt from ambiguity check */ } } if (j != 1) { for (i=0; *(p+i) && !isspace(*(p+i)); i++) ; *(p+i) = '\0'; /* isolate command */ if (j == 0) sprintf(msg, "Command not found: %s", p); else sprintf(msg, "Command '%s' is ambiguous", p); return 0; } *pP += n; /* skip over command name */ return mx_params_list[idx].cmnd; } /*****************************************************************************\ ** ** ** CBF header from template ** ** ** \*****************************************************************************/ /* Note that CBF_TXT_HEADER_SIZE must fit within CBF_HEADER_SIZE in cbftvx.c */ #define CBF_TXT_HEADER_SIZE 8000 #define MAX_NODES 30 static char cbf_template[CBF_TXT_HEADER_SIZE]; static int cbf_header_initialized=0; struct CBF_NODE { MX_PARAMS_CMND cmnd; char *subP; char *strP; struct CBF_NODE *next; struct CBF_NODE *prev; } ; static struct CBF_NODE nodes[MAX_NODES]; int setup_cbf_template(char *msg) { int i, len, m, nidx=0, count; FILE *ifp; char line[120], *p, *q, *sub=NULL, substr[30], *txt=NULL, *ptxt=NULL; MX_PARAMS_CMND cmnd; struct CBF_NODE *tnode, *rnode; cbf_header_initialized=0; if (!cbf_template_file[0]) /* no template given - no error */ return 0; if ( !(ifp=fopen(cbf_template_file, "r")) ) { sprintf(msg, "Could not open template file for reading:\n %s", cbf_template_file); printf("%s\n", msg); return -1; } /* read and edit the template ensure that lines end in CRLF (a CBF standard) */ cbf_template[0]='\0'; m=0; while( (fgets(line, sizeof(line), ifp)) ) { /* if we find a mini-header, discard it */ if(strstr(line, "--CIF-BINARY-FORMAT-SECTION--")) break; len = strlen(line); if (len > -4+sizeof(line)) { fclose(ifp); strcpy(msg, "Line too long in CBF template"); printf("%s\n", msg); return -1; } p = line+strlen(line); while (p>=line && (*p=='\n' || *p=='\r' || *p=='\0')) /* cut off ending */ p--; strcpy(p+1, "\r\n"); /* CRLF is the correct line ending for CBF */ p = line; while(!ptxt && (*p==' ' || *p=='\t')) /* in case of leading space */ p++; q = cbf_template+m; /* memorize position */ m+=sprintf(cbf_template+m, "%s", p); /* put line in buffer */ if (txt) /* start of text has been found */ continue; if (ptxt && line[0]=='_') txt = q; /* confirmed start of text */ if (!sub && *q=='@') sub = q; /* position of first substitution */ if (*q=='@' || *q=='#') continue; if (strstr(q, "--- End of preamble")) txt = cbf_template+m; /* start of next line */ if (!txt) ptxt = q; /* possible start of text - probably CRLF */ } fclose(ifp); if (!txt) { sprintf(msg, "*** Error in template file format - text not found\n"); printf("%s\n", msg); return -1; } /* the ending is critical for CBF library parsing "\r\n;\r\n;\r\n" is required; we add an extra blank line */ while(isspace(*(cbf_template+m)) || *(cbf_template+m)=='\0') m--; m++; m+=sprintf(cbf_template+m, "\r\n;\r\n;\r\n\r\n"); /* ** (1) Identify each defined program parameter in turn (e.g., 'Timestamp') ** (2) Pick up the associated substitution key (e.g., '_timestamp_') ** (3) Search through the text for 1 or more instances of the key ** (4) Make up a 'node' for each instance giving the key type and the ** position of the instance in the text ** (5) Insert the node in the doubly-linked list such that traversing the ** linked-list enumerates the nodes in the order they occur in the text. ** The nodes are in arbitrary order in the array of nodes; only the ** link pointers keep track of the order. ** (6) After all instances are found, terminate each text segment ('\0') ** ** The final arrangement is an initial text segment, followed by the ** array of nodes (instances). Each instance contains a variable value ** to be printed, followed by a text segment. */ memset(nodes, 0, sizeof(nodes)); /* doubly linked list */ nodes[0].subP=nodes[0].strP=txt; /* start of text */ /* parse the substitutions */ while (sub && *sub=='@') { q=sub+1; while(isspace(*q)) q++; cmnd = find_mx_param_command(&q); if (!cmnd) { sprintf(msg, "*** Error - unrecognized variable name (%s)", q); printf("%s\n", msg); return -1; } while(isspace(*q)) q++; p = substr; while(!isspace(*q) && *q!='\r' && *q!='\n' && *q!='\0') *p++ = *q++; *p = '\0'; /* substr == string to search for */ while(isspace(*q) && *q!='\r') q++; if(isalnum(*q) || *q=='-') { switch (cmnd) /* store initial value(s) */ { case Energy_range: mx_e_range_low = atof(q); while(*q && (isdigit(*q) || *q=='-' || *q=='.')) /* skip number */ q++; while(*q && (isspace(*q) || *q==',')) /* skip to next number */ q++; if (*q == '\0') /* end of line? */ return 0; mx_e_range_hi = atof(q); mx_e_range_low_defined=1; mx_e_range_hi_defined=1; break; case Detector_distance: mx_det_distance = atof(q); mx_det_distance_defined=1; break; case Detector_Voffset: mx_det_voffset = atof(q); mx_det_voffset_defined=1; break; case Beam_xy: mx_beam_x = atof(q); while(*q && (isdigit(*q) || *q=='-' || *q=='.')) /* skip number */ q++; while(*q && (isspace(*q) || *q==',')) /* skip to next number */ q++; if (*q == '\0') /* end of line? */ break; mx_beam_y = atof(q); mx_beam_x_defined=1; mx_beam_y_defined=1; break; case Beam_x: mx_beam_x = atof(q); mx_beam_x_defined=1; break; case Beam_y: mx_beam_y = atof(q); mx_beam_y_defined=1; break; case Flux: mx_flux = atof(q); mx_flux_defined=1; break; case Filter_transmission: mx_filter_tx = atof(q); mx_filter_tx_defined=1; break; case Start_angle: mx_start_angle = atof(q); mx_start_angle_defined=1; break; case Angle_increment: mx_angle_increment = atof(q); mx_angle_increment_defined=1; mx_start_angle_defined=1; /* defaults to 0 */ break; case Detector_2theta: mx_det_2theta = atof(q); mx_det_2theta_defined=1; break; case Polarization: mx_polarization = atof(q); mx_polarization_defined=1; break; case Alpha: mx_alpha = atof(p); mx_alpha_defined=1; break; case Kappa: mx_kappa = atof(q); mx_kappa_defined=1; break; case Phi: mx_phi = atof(q); mx_phi_defined=1; break; case Phi_increment: mx_phi_increment = atof(q); mx_phi_increment_defined=1; mx_phi_defined=1; /* defaults to 0 */ break; case Chi: mx_chi = atof(q); mx_chi_defined=1; break; case Chi_increment: mx_chi_increment = atof(q); mx_chi_increment_defined=1; mx_chi_defined=1; /* defaults to 0 */ break; case Oscillation_axis: memset(mx_oscillation_axis, 0, TEXT_SIZE); strncat(mx_oscillation_axis, q, TEXT_SIZE-2); for (i=0; mx_oscillation_axis[i] && isubPnext; } if (nidx >= -1+MAX_NODES) { strcpy(msg, "Too many substitution nodes in CBF template"); printf("%s\n", line); return -1; } nidx++; /* allocate a new node */ nodes[nidx].cmnd = cmnd; /* name of variable */ nodes[nidx].subP = p; /* pointer to substitution string */ nodes[nidx].strP = p+strlen(substr); /* start of next string */ nodes[nidx].next = rnode->next; /* insert new node in chain */ nodes[nidx].prev = rnode; if (rnode->next) rnode->next->prev = &nodes[nidx]; rnode->next = &nodes[nidx]; q = p+strlen(substr); } if ( !count ) { sprintf(msg, "*** Error: key string ( %s ) not found", substr); printf("%s\n", msg); return -1; } #if 0 /* print the doubly linked list */ {char t1[20], t2[20]; for(i=0; i<=nidx; i++) { strcpy(t1, " "); if (nodes[i].subP) strncpy(t1, nodes[i].subP, 20); t1[19]='\0'; while((q=strchr(t1,'\n')))*q='.'; while((q=strchr(t1,'\r')))*q='.'; strcpy(t2, " "); if (nodes[i].strP) strncpy(t2, nodes[i].strP, 20); t2[19]='\0'; while((q=strchr(t2,'\n')))*q='.'; while((q=strchr(t2,'\r')))*q='.'; printf("%2d %p %2d %20s %20s %p %p\n", i, &nodes[i], (int)nodes[i].cmnd, t1, t2, nodes[i].next, nodes[i].prev); } strncpy(t1, p, 20); t1[19]='\0'; while((q=strchr(t1,'\n')))*q='.'; while((q=strchr(t1,'\r')))*q='.'; printf(" p = %p, text = %s\n", p, t1); printf("\n"); } #endif sub = 1+strchr(sub, '\n'); /* next line */ } /* terminate the internal strings */ tnode = nodes[0].next; while(tnode) { *(tnode->subP) = '\0'; tnode = tnode->next; } cbf_header_initialized=1; return 0; } /* print the CBF header from the template into the buffer provided returns size */ int print_cbf_header(char *dest, int size, char *conv) { struct CBF_NODE *tnode=&nodes[0]; int m=0; if (!cbf_header_initialized) return 0; m += sprintf(dest+m, "%s", tnode->strP); tnode = tnode->next; while(tnode && mcmnd) { case Wavelength: if(mx_wavelength_defined) m += sprintf(dest+m, "%.2f", mx_wavelength); else m += sprintf(dest+m, ""); break; case Energy_range: if(mx_e_range_low_defined && mx_e_range_hi_defined) m += sprintf(dest+m, "%.0f %.0f", mx_e_range_low, mx_e_range_hi); else m += sprintf(dest+m, ""); break; case Detector_distance: if(mx_det_distance_defined) m += sprintf(dest+m, "%.3f", mx_det_distance); else m += sprintf(dest+m, ""); break; case Detector_Voffset: if(mx_det_voffset_defined) m += sprintf(dest+m, "%.3f", mx_det_voffset); else m += sprintf(dest+m, ""); break; case Beam_xy: if(mx_beam_x_defined && mx_beam_y_defined) m += sprintf(dest+m, "%.2f %.2f", mx_beam_x, mx_beam_y); else m += sprintf(dest+m, ""); break; case Beam_x: if(mx_beam_x_defined) m += sprintf(dest+m, "%.2f", mx_beam_x); else m += sprintf(dest+m, ""); break; case Beam_y: if(mx_beam_y_defined) m += sprintf(dest+m, "%.2f", mx_beam_y); else m += sprintf(dest+m, ""); break; case Flux: if(mx_flux_defined) m += sprintf(dest+m, "%g", mx_flux); else m += sprintf(dest+m, ""); break; case Filter_transmission: if(mx_filter_tx_defined) m += sprintf(dest+m, "%.4f", mx_filter_tx); else m += sprintf(dest+m, ""); break; case Start_angle: if(mx_start_angle_defined) m += sprintf(dest+m, "%.4f", mx_start_angle); else m += sprintf(dest+m, ""); break; case Angle_increment: if(mx_angle_increment_defined) m += sprintf(dest+m, "%.4f", mx_angle_increment); else m += sprintf(dest+m, ""); break; case Detector_2theta: if(mx_det_2theta_defined) m += sprintf(dest+m, "%.4f", mx_det_2theta); else m += sprintf(dest+m, ""); break; case Polarization: if(mx_polarization_defined) m += sprintf(dest+m, "%.3f", mx_polarization); else m += sprintf(dest+m, ""); break; case Alpha: if(mx_alpha_defined) m += sprintf(dest+m, "%.4f", mx_alpha); else m += sprintf(dest+m, ""); break; case Kappa: if(mx_kappa_defined) m += sprintf(dest+m, "%.4f", mx_kappa); else m += sprintf(dest+m, ""); break; case Phi: if(mx_phi_defined) m += sprintf(dest+m, "%.4f", mx_phi); else m += sprintf(dest+m, ""); break; case Phi_increment: if(mx_phi_increment_defined) m += sprintf(dest+m, "%.4f", mx_phi_increment); else m += sprintf(dest+m, ""); break; case Chi: if(mx_chi_defined) m += sprintf(dest+m, "%.4f", mx_chi); else m += sprintf(dest+m, ""); break; case Chi_increment: if(mx_chi_increment_defined) m += sprintf(dest+m, "%.4f", mx_chi_increment); else m += sprintf(dest+m, ""); break; case Oscillation_axis: if(mx_oscillation_axis_defined) m += sprintf(dest+m, "%s", mx_oscillation_axis); else m += sprintf(dest+m, ""); break; case N_oscillations: if(mx_n_oscilations_defined) m += sprintf(dest+m, "%d", mx_n_oscilations); else m += sprintf(dest+m, ""); break; case Start_position: if(mx_start_position_defined) m += sprintf(dest+m, "%.4f", mx_start_position); else m += sprintf(dest+m, ""); break; case Position_increment: if(mx_position_increment_defined) m += sprintf(dest+m, "%.4f", mx_position_increment); else m += sprintf(dest+m, ""); break; case Shutter_time: if(mx_shutter_time_defined) m += sprintf(dest+m, "%.7f", mx_shutter_time); else m += sprintf(dest+m, ""); break; case Timestamp: m += sprintf(dest+m, "%s", image_timestamp); break; case Exposure_period: m += sprintf(dest+m, "%.6f", dcb_get_exposure_period()); break; case Exposure_time: m += sprintf(dest+m, "%.6f", exposure_time); break; case Count_cutoff: m += sprintf(dest+m, "%u", count_cutoff); break; case Compression_type: if (strstr(conv, "x-")) conv+=2; m += sprintf(dest+m, "%s", conv); break; case X_dimension: m += sprintf(dest+m, "%d", camera_wide); break; case Y_dimension: m += sprintf(dest+m, "%d", camera_high); break; case CBF_template_file: default: break; } m += sprintf(dest+m, "%s", tnode->strP); tnode = tnode->next; } if (m >= -1+size-TEXT_SIZE) printf("Size exceeded - CBF header not completed\n"); return m; } /*************************************************\ ** ** ** main program for cbf test -or- demo ** ** ** \*************************************************/ int main (int argc, char *argv[]) { FILE *ofp; char msg[500]="\0"; char bufr[10000]; char line[80]; strcpy(cbf_template_file, "cbf_6M_template.cbf"); cbf_template_file_defined=1; setup_cbf_template(msg); if (msg[0]) { printf("%s\n", msg); return 0; } print_cbf_header(bufr, sizeof(bufr), "CBF_BYTE_OFFSET"); strcpy(line, "cbf_template_t.out"); if (!(ofp = fopen(line, "w+b"))) { printf("Could not open %s for writing\n", line); return 0; } /* The first part of a DECTRIS CBF header in an image file is a comment header containing detector settings and mx_settings (these are crystallography parameters supplied by the user that are also reproduced in the CBF syntax below) */ fprintf(ofp, "###CBF: VERSION 1.5, CBFlib v0.7.8 - SLS/DECTRIS PILATUS detectors\r\n" "\r\n" "data_test65\r\n" "\r\n" "_array_data.header_convention \"SLS/DECTRIS_1.1\"\r\n" "_array_data.header_contents\r\n" ";\r\n"); fprintf(ofp, "# Detector: PILATUS 100K, In-house (m141) Test System\r\n" "# 2010-Jun-16T19:09:48.271\r\n" "# Pixel_size 172e-6 m x 172e-6 m\r\n" "# Silicon sensor, thickness 0.000320 m\r\n" "# Exposure_time 1.0000000 s\r\n" "# Exposure_period 1.0000000 s\r\n" "# Tau = 0 s\r\n" "# Count_cutoff 1048574 counts\r\n" "# Threshold_setting 0 eV\r\n" "# Gain_setting not set (vrf = -0.200)\r\n" "# N_excluded_pixels = 0\r\n" "# Excluded_pixels: (nil)\r\n" "# Flat_field: (nil)\r\n" "# Trim_file: (nil)\r\n" "# Image_path: /home/det/p2_det/images/\r\n" ";\r\n" ); /* now the part made up from the template */ fprintf(ofp, "%s", bufr); /* now the mini-header and the data */ fprintf(ofp, "_array_data.data\r\n" ";\r\n" "--CIF-BINARY-FORMAT-SECTION--\r\n" "Content-Type: application/octet-stream;\r\n" " conversions=\"x-CBF_BYTE_OFFSET\"\r\n" "Content-Transfer-Encoding: BINARY\r\n" ); fprintf(ofp, "X-Binary-Size: 94981\r\n" "X-Binary-ID: 1\r\n" "X-Binary-Element-Type: \"signed 32-bit integer\"\r\n" "X-Binary-Element-Byte-Order: LITTLE_ENDIAN\r\n" "Content-MD5: VwGHOeEVHfClJWkB5v5Geg==\r\n" "X-Binary-Number-of-Elements: 94965\r\n" "X-Binary-Size-Fastest-Dimension: 487\r\n" "X-Binary-Size-Second-Dimension: 195\r\n" "X-Binary-Size-Padding: 4095\r\n" "\r\n" "--- data comes here ---\r\n" "--CIF-BINARY-FORMAT-SECTION----\r\n" ";\r\n" ); fclose(ofp); printf ("%s was written\n", line); return 0; } ./CBFlib-0.9.2.2/examples/dectris_cbf_template_test/cbf_6M_template.cbf0000644000076500007650000001246311603702122024264 0ustar yayayaya###CBF: VERSION 1.1 # Template for Diamond MX beamlines phase 1 - replacing what we currently # have in ADSC, Rayonix and DECTRIS image headers with a standard syntax # and description. # # DECTRIS translation table follows... # @ Exposure_time _expt_ @ Exposure_period _expp_ @ Start_angle _omega_ 3.987 @ Angle_increment _d_omega_ 0.123 @ Timestamp _timestamp_ @ Count_cutoff _cutoff_ @ Compression_type _compress_ @ X_dimension _wide_ @ Y_dimension _high_ # # These items will be pre-populated in the template so need not be included: # # Wavelength # Detector_distance # Beam_xy # Alpha # Kappa # Phi # Chi # Oscillation_axis # Pixel_size # Detector --- End of preamble # This and all subsequent lines will appear in the header _diffrn.id DLS_I03 _diffrn.crystal_id XTAL0001 # the following items will be fixed for the beamline loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type DLS_I03 synchrotron 'Diamond Light Source Beamline I03' loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source DLS_I03 WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes DLS_I03 ADSC_I03 'ADSC Quantum 315' 3 loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id ADSC_I03 DETECTOR_X ADSC_I03 DETECTOR_Y ADSC_I03 DETECTOR_Z loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 ADSC_I03 loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # at the moment we have only a single axis system in place - this will change # to a kappa at some point for I04 -> number_of_axes = 3 # GONIOMETER GONIOMETER_PHI # GONIOMETER GONIOMETER_KAPPA loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method DLS_I03 GONIOMETER 1 rotation loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_OMEGA # these items will be written by GDA on a scan-by-scan basis loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.97930 1.0 # these values should probably be updated from the results of postrefinement loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA _omega_ 1.0 _d_omega_ 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.exposure_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 _expt_ _expp_ SCAN1 _timestamp_ loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 # this could also contain postrefined results loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 ELEMENT_X translation detector DETECTOR_X 1 0 0 157.2 157.2 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 _wide_ 1 increasing ELEMENT_X ARRAY1 2 _high_ 2 increasing ELEMENT_Y loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.0512 0.1024 ELEMENT_Y ELEMENT_Y 0.0512 0.1024 loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 102.4e-6 ARRAY1 2 102.4e-6 loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 0.5 0.2 _cutoff_ 0 loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" _compress_ little_endian ./CBFlib-0.9.2.2/examples/dectris_cbf_template_test/cbf_test_orig.out0000644000076500007650000001357011603702122024163 0ustar yayayaya###CBF: VERSION 1.5, CBFlib v0.7.8 - SLS/DECTRIS PILATUS detectors data_test65 _array_data.header_convention "SLS/DECTRIS_1.1" _array_data.header_contents ; # Detector: PILATUS 100K, In-house (m141) Test System # 2010-Jun-16T19:09:48.271 # Pixel_size 172e-6 m x 172e-6 m # Silicon sensor, thickness 0.000320 m # Exposure_time 1.0000000 s # Exposure_period 1.0000000 s # Tau = 0 s # Count_cutoff 1048574 counts # Threshold_setting 0 eV # Gain_setting not set (vrf = -0.200) # N_excluded_pixels = 0 # Excluded_pixels: (nil) # Flat_field: (nil) # Trim_file: (nil) # Image_path: /home/det/p2_det/images/ ; # This and all subsequent lines will appear in the header _diffrn.id DLS_I03 _diffrn.crystal_id XTAL0001 # the following items will be fixed for the beamline loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type DLS_I03 synchrotron 'Diamond Light Source Beamline I03' loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source DLS_I03 WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes DLS_I03 ADSC_I03 'ADSC Quantum 315' 3 loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id ADSC_I03 DETECTOR_X ADSC_I03 DETECTOR_Y ADSC_I03 DETECTOR_Z loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 ADSC_I03 loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # at the moment we have only a single axis system in place - this will change # to a kappa at some point for I04 -> number_of_axes = 3 # GONIOMETER GONIOMETER_PHI # GONIOMETER GONIOMETER_KAPPA loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method DLS_I03 GONIOMETER 1 rotation loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_OMEGA # these items will be written by GDA on a scan-by-scan basis loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.97930 1.0 # these values should probably be updated from the results of postrefinement loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA 3.9870 1.0 0.1230 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.exposure_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 0.095000 0.100000 SCAN1 2010-06-20T17:54.329 loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 # this could also contain postrefined results loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 ELEMENT_X translation detector DETECTOR_X 1 0 0 157.2 157.2 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 2463 1 increasing ELEMENT_X ARRAY1 2 2527 2 increasing ELEMENT_Y loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.0512 0.1024 ELEMENT_Y ELEMENT_Y 0.0512 0.1024 loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 102.4e-6 ARRAY1 2 102.4e-6 loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 0.5 0.2 1048575 0 loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" CBF_BYTE_OFFSET little_endian ; ; _array_data.data ; --CIF-BINARY-FORMAT-SECTION-- Content-Type: application/octet-stream; conversions="x-CBF_BYTE_OFFSET" Content-Transfer-Encoding: BINARY X-Binary-Size: 94981 X-Binary-ID: 1 X-Binary-Element-Type: "signed 32-bit integer" X-Binary-Element-Byte-Order: LITTLE_ENDIAN Content-MD5: VwGHOeEVHfClJWkB5v5Geg== X-Binary-Number-of-Elements: 94965 X-Binary-Size-Fastest-Dimension: 487 X-Binary-Size-Second-Dimension: 195 X-Binary-Size-Padding: 4095 --- data comes here --- --CIF-BINARY-FORMAT-SECTION---- ; ./CBFlib-0.9.2.2/examples/dectris_cbf_template_test/cbf_template_HOWTO.txt0000644000076500007650000002407711603702122024773 0ustar yayayaya cbf_template_HOWTO.txt How to Use a Template to Write Full CBF Headers Under camserver. This system was developed in collaboration with Diamond Light Source. Below, starting with the line "###CBF: VERSION 1.1" is an example of a CBF header template. It has been tested for validity against CBFlib_0.7.7. The template consists of a "preamble" containing descriptive information and "substitution" commands. The preamble is ended by the "--- End of preamble" statement. The preamble is followed by the body of the CBF header which is reproduced verbatim in the image file, except for the requested variable substitutions. The "--- End of preamble" statement is optional, but is required if any immediately following comments are to be reproduced. The substitution commands each reference an internal program variable in the DECTRIS control software and define a corresponding "key" which is to be found in the body of the header and substituted by the running value of the variable while data-taking proceeds. Substitution commands take the form: @ (1) The character in column 0 must be '@' (2) The DECTRIS internal variables are listed below. Variables to be substituted must exist (be spelled correctly), are not case-sensitive and may be listed in any order. (3) The keys may be any unique text. We find forms like "_expt_" to be easy to find visually in the text. Keys should be preceeded and followed by blank spaces, unless they are at the beginning or end of a line, where the respective leading or trailing blank can be omitted. (4) Many of the variables can have an initial value specified in the line of the substitution command. These are listed below. Alternatively, variables may be initialized using the MXsettings command to camserver. (5) Each key must be found one or more times in the text. The spelling and orthography of the key in the substitution command must match the key in the body of the text. (6) The location of the template file must be declared to camserver using, e.g.: "MXsettings CBF_template_file /full/path/to/file/phase_1.2.cbf" where the full path to the template is given. The absence of this declaration indicates that the template facility is not being used. The location (path) of the template is arbitrary. (7) The template can be updated dynamically between exposure series. The template is reprocessed at the start of each expsoure series so that initial values can be set. (8) The content of the template is completely arbitrary and therefore not specific for CBF. (9) Currently the CBF template, including the preamble, must be less than 8 kB in size; there can be up to 30 substitution points. For more information on CBF, see: http://arcib.dowling.edu/software/CBFlib/ DECTRIS internal variables that can be given initial values in the substitution command line: @ Energy_range @ Detector_distance @ Detector_Voffset @ Beam_xy @ Beam_x @ Beam_y @ Flux @ Filter_transmission @ Start_angle @ Angle_increment @ Detector_2theta @ Polarization @ Alpha @ Kappa @ Phi @ Phi_increment @ Chi @ Chi_increment @ Oscillation_axis @ N_oscillations @ Start_position @ Position_increment @ Shutter_time DECTRIS internal variables that do not take initial values in the substitution command line: @ Wavelength @ Timestamp @ Exposure_period @ Exposure_time @ Count_cutoff @ Compression_type @ X_dimension @ Y_dimension Note that the compression type can be CBF_BYTE_OFFSET or CBF_NONE depending on the image data. For crystallography, the latter case almost never happens, but SAXS data sometimes do not compress. The X_dimension and Y_dimension variables were added for convenience in writing more portable templates. The "Shutter_time" variable can be used in cases where the shutter open time differs from the requested Exposure_time. All text up to and including the "--- End of preamble" statement is elided in the final header text. If the "--- End of preamble" statement is not used, then all text up to the first recognized CBF declaration is elided. All variables that have been defined will also appear as comments near the top of the CBF header, where they will show up on the first page of "more". The header text defined by the template will be positioned below these comments. Below that will be the "mini-header" needed by XDS, followed by the image data. Disclaimer: Although every effort has been made to make the CBF header template system reliable, robust and easy to use, it will easily create image files that cannot be opened by any application. Please do **not** contact us if this happens to you. Eric.Eikenberry@dectris.com Graeme.Winter@diamond.ac.uk 6 May 2010 ============================================================================ ###CBF: VERSION 1.1 # Template for Diamond MX beamlines phase 1 - replacing what we currently # have in ADSC, Rayonix and DECTRIS image headers with a standard syntax # and description. # # DECTRIS translation table follows... # @ Exposure_time _expt_ @ Exposure_period _expp_ @ Start_angle _omega_ 3.987 @ Angle_increment _d_omega_ 0.123 @ Timestamp _timestamp_ @ Count_cutoff _cutoff_ @ Compression_type _compress_ @ X_dimension _wide_ @ Y_dimension _high_ # # These items will be pre-populated in the template so need not be included: # # Wavelength # Detector_distance # Beam_xy # Alpha # Kappa # Phi # Chi # Oscillation_axis # Pixel_size # Detector --- End of preamble # This and all subsequent lines will appear in the header _diffrn.id DLS_I03 _diffrn.crystal_id XTAL0001 # the following items will be fixed for the beamline loop_ _diffrn_source.diffrn_id _diffrn_source.source _diffrn_source.type DLS_I03 synchrotron 'Diamond Light Source Beamline I03' loop_ _diffrn_radiation.diffrn_id _diffrn_radiation.wavelength_id _diffrn_radiation.monochromator _diffrn_radiation.polarizn_source_ratio _diffrn_radiation.polarizn_source_norm _diffrn_radiation.div_x_source _diffrn_radiation.div_y_source _diffrn_radiation.div_x_y_source DLS_I03 WAVELENGTH1 'Si 111' 0.8 0.0 0.08 0.01 0.00 # category DIFFRN_DETECTOR loop_ _diffrn_detector.diffrn_id _diffrn_detector.id _diffrn_detector.type _diffrn_detector.number_of_axes DLS_I03 ADSC_I03 'ADSC Quantum 315' 3 loop_ _diffrn_detector_axis.detector_id _diffrn_detector_axis.axis_id ADSC_I03 DETECTOR_X ADSC_I03 DETECTOR_Y ADSC_I03 DETECTOR_Z loop_ _diffrn_detector_element.id _diffrn_detector_element.detector_id ELEMENT1 ADSC_I03 loop_ _diffrn_data_frame.id _diffrn_data_frame.detector_element_id _diffrn_data_frame.array_id _diffrn_data_frame.binary_id FRAME1 ELEMENT1 ARRAY1 1 loop_ _diffrn_scan.id _diffrn_scan.frame_id_start _diffrn_scan.frame_id_end _diffrn_scan.frames SCAN1 FRAME1 FRAME1 1 # at the moment we have only a single axis system in place - this will change # to a kappa at some point for I04 -> number_of_axes = 3 # GONIOMETER GONIOMETER_PHI # GONIOMETER GONIOMETER_KAPPA loop_ _diffrn_measurement.diffrn_id _diffrn_measurement.id _diffrn_measurement.number_of_axes _diffrn_measurement.method DLS_I03 GONIOMETER 1 rotation loop_ _diffrn_measurement_axis.measurement_id _diffrn_measurement_axis.axis_id GONIOMETER GONIOMETER_OMEGA # these items will be written by GDA on a scan-by-scan basis loop_ _diffrn_radiation_wavelength.id _diffrn_radiation_wavelength.wavelength _diffrn_radiation_wavelength.wt WAVELENGTH1 0.97930 1.0 # these values should probably be updated from the results of postrefinement loop_ _diffrn_scan_axis.scan_id _diffrn_scan_axis.axis_id _diffrn_scan_axis.angle_start _diffrn_scan_axis.angle_range _diffrn_scan_axis.angle_increment _diffrn_scan_axis.displacement_start _diffrn_scan_axis.displacement_range _diffrn_scan_axis.displacement_increment SCAN1 GONIOMETER_OMEGA _omega_ 1.0 _d_omega_ 0.0 0.0 0.0 SCAN1 DETECTOR_Z 0.0 0.0 0.0 -240.0 0.0 0.0 SCAN1 DETECTOR_Y 0.0 0.0 0.0 0.6 0.0 0.0 SCAN1 DETECTOR_X 0.0 0.0 0.0 -0.5 0.0 0.0 loop_ _diffrn_scan_frame.frame_id _diffrn_scan_frame.frame_number _diffrn_scan_frame.integration_time _diffrn_scan_frame.exposure_time _diffrn_scan_frame.scan_id _diffrn_scan_frame.date FRAME1 1 _expt_ _expp_ SCAN1 _timestamp_ loop_ _diffrn_scan_frame_axis.frame_id _diffrn_scan_frame_axis.axis_id _diffrn_scan_frame_axis.angle _diffrn_scan_frame_axis.displacement FRAME1 GONIOMETER_OMEGA 12.0 0.0 FRAME1 DETECTOR_Z 0.0 -240.0 FRAME1 DETECTOR_Y 0.0 0.6 FRAME1 DETECTOR_X 0.0 -0.5 # this could also contain postrefined results loop_ _axis.id _axis.type _axis.equipment _axis.depends_on _axis.vector[1] _axis.vector[2] _axis.vector[3] _axis.offset[1] _axis.offset[2] _axis.offset[3] GONIOMETER_OMEGA rotation goniometer . 1 0 0 . . . SOURCE general source . 0 0 1 . . . GRAVITY general gravity . 0 -1 0 . . . DETECTOR_Z translation detector . 0 0 1 0 0 0 DETECTOR_Y translation detector DETECTOR_Z 0 1 0 0 0 0 DETECTOR_X translation detector DETECTOR_Y 1 0 0 0 0 0 ELEMENT_X translation detector DETECTOR_X 1 0 0 157.2 157.2 0 ELEMENT_Y translation detector ELEMENT_X 0 1 0 0 0 0 loop_ _array_structure_list.array_id _array_structure_list.index _array_structure_list.dimension _array_structure_list.precedence _array_structure_list.direction _array_structure_list.axis_set_id ARRAY1 1 _wide_ 1 increasing ELEMENT_X ARRAY1 2 _high_ 2 increasing ELEMENT_Y loop_ _array_structure_list_axis.axis_set_id _array_structure_list_axis.axis_id _array_structure_list_axis.displacement _array_structure_list_axis.displacement_increment ELEMENT_X ELEMENT_X 0.0512 0.1024 ELEMENT_Y ELEMENT_Y 0.0512 0.1024 loop_ _array_element_size.array_id _array_element_size.index _array_element_size.size ARRAY1 1 102.4e-6 ARRAY1 2 102.4e-6 loop_ _array_intensities.array_id _array_intensities.binary_id _array_intensities.linearity _array_intensities.gain _array_intensities.gain_esd _array_intensities.overload _array_intensities.undefined_value ARRAY1 1 linear 0.5 0.2 _cutoff_ 0 loop_ _array_structure.id _array_structure.encoding_type _array_structure.compression_type _array_structure.byte_order ARRAY1 "signed 32-bit integer" _compress_ little_endian ./CBFlib-0.9.2.2/examples/convert_image.c0000644000076500007650000015635611603702122016420 0ustar yayayaya/********************************************************************** * convert_image -- convert an image file to a cbf file * * * * Version 0.7.9 30 December 2007 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * WHILE YOU MAY ALTERNATIVELY DISTRIBUTE THE API UNDER THE LGPL * * YOU MAY ***NOT*** DISTRIBUTE THIS PROGRAM UNDER THE LGPL * * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term 'this software', as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ /********************************************************************** * SYNOPSIS * * * * convert_image [-i input_img] [-o output_cbf] [-p template_cbf]\ * * [-d detector name] -m [x|y|x=y] [-z distance] \ * * [-c category_alias=category_root]* \ * * [-t tag_alias=tag_root]* [-F] [-R] [-S ] \ * * [input_img] [output_cbf] * * * * the options are: * * * * -i input_img (default: stdin) * * the input file as an image in smv, mar300, or mar345 format. * * If input_img is not specified or is given as "-", it is copied * * from stdin to a temporary file. * * * * -p template_cbf * * the template for the final cbf to be produced. If template_cbf * * is not specified the name is constructed from the first token * * of the detector name and the image size as * * template__x.cbf * * * * -o output_cbf (default: stdout ) * * the output cbf combining the image and the template. If the * * output_cbf is not specified or is given as "-", it is written * * to stdout. * * * * -d detectorname * * a detector name to be used if none is provided in the image * * header. * * * * -F * * when writing packed compression, treat the entire image as * * one line with no averaging * * * * -m [x|y|x=y] (default x=y, square arrays only) * * mirror the array in the x-axis (y -> -y) * * in the y-axis (x -> -x) * * or in x=y ( x -> y, y-> x) * * * * -r n * * rotate the array n times 90 degrees counter clockwise * * x -> y, y -> -x for each rotation, n = 1, 2 or 3 * * * * -R * * if setting a beam center, set reference values of * * axis settings as well as standard settings * * * * -S * * when generating a copy of the img header in the .details field, * * insert a space in front and before and after the equals sign * * for compatability with older versions of convert_image * * * * -z distance * * detector distance along Z-axis * * * * -c category_alias=category_root * * -t tag_alias=tagroot * * map the given alias to the given root, so that instead * * of outputting the alias, the root will be presented in the * * output cbf instead. These options may be repeated as many * * times as needed. * * * **********************************************************************/ #include "cbf.h" #include "cbf_simple.h" #include "cbf_string.h" #include "img.h" #include #include #include #include #include #include #include "cbf_getopt.h" #include double rint(double); int local_exit (int status); int outerror(int err); int outerror(int err) { if ((err&CBF_FORMAT)==CBF_FORMAT) fprintf(stderr, " convert_image: The file format is invalid.\n"); if ((err&CBF_ALLOC)==CBF_ALLOC) fprintf(stderr, " convert_image Memory allocation failed.\n"); if ((err&CBF_ARGUMENT)==CBF_ARGUMENT) fprintf(stderr, " convert_image: Invalid function argument.\n"); if ((err&CBF_ASCII)==CBF_ASCII) fprintf(stderr, " convert_image: The value is ASCII (not binary).\n"); if ((err&CBF_BINARY)==CBF_BINARY) fprintf(stderr, " convert_image: The value is binary (not ASCII).\n"); if ((err&CBF_BITCOUNT)==CBF_BITCOUNT) fprintf(stderr, " convert_image: The expected number of bits does" " not match the actual number written.\n"); if ((err&CBF_ENDOFDATA)==CBF_ENDOFDATA) fprintf(stderr, " convert_image: The end of the data was reached" " before the end of the array.\n"); if ((err&CBF_FILECLOSE)==CBF_FILECLOSE) fprintf(stderr, " convert_image: File close error.\n"); if ((err&CBF_FILEOPEN)==CBF_FILEOPEN) fprintf(stderr, " convert_image: File open error.\n"); if ((err&CBF_FILEREAD)==CBF_FILEREAD) fprintf(stderr, " convert_image: File read error.\n"); if ((err&CBF_FILESEEK)==CBF_FILESEEK) fprintf(stderr, " convert_image: File seek error.\n"); if ((err&CBF_FILETELL)==CBF_FILETELL) fprintf(stderr, " convert_image: File tell error.\n"); if ((err&CBF_FILEWRITE)==CBF_FILEWRITE) fprintf(stderr, " convert_image: File write error.\n"); if ((err&CBF_IDENTICAL)==CBF_IDENTICAL) fprintf(stderr, " convert_image: A data block with the new name already exists.\n"); if ((err&CBF_NOTFOUND)==CBF_NOTFOUND) fprintf(stderr, " convert_image: The data block, category, column or" " row does not exist.\n"); if ((err&CBF_OVERFLOW)==CBF_OVERFLOW) fprintf(stderr, " convert_image: The number read cannot fit into the" "destination argument.\n The destination has been set to the nearest value.\n"); if ((err& CBF_UNDEFINED)==CBF_UNDEFINED) fprintf(stderr, " convert_image: The requested number is not defined (e.g. 0/0).\n"); if ((err&CBF_NOTIMPLEMENTED)==CBF_NOTIMPLEMENTED) fprintf(stderr, " convert_image: The requested functionality is not yet implemented.\n"); return 0; } #undef cbf_failnez #define cbf_failnez(x) \ {int err; \ err = (x); \ if (err) { \ fprintf(stderr," convert_image: CBFlib fatal error %d\n",err); \ outerror(err); \ outusage(); \ local_exit (-1); \ } \ } typedef enum { posx=1, posy=2, negx=-1, negy=-2 } axes; typedef struct { axes posxtarg, posytarg; } axisxform; int outusage ( void ) { fprintf(stderr," \n Usage:\n"); fprintf(stderr," convert_image [-i input_img] [-o output_cbf] [-p template_cbf]\\\n"); fprintf(stderr," [-d detector name] -m [x|y|x=y] [-z distance] \\\n"); fprintf(stderr," [-c category_alias=category_root]* \\\n"); fprintf(stderr," [-t tag_alias=tag_root]* [-F] [-R] [-S]\\\n"); fprintf(stderr," [input_img] [output_cbf]\n"); fprintf(stderr," the options are:\n"); fprintf(stderr," -i input_img (default: stdin)\n"); fprintf(stderr," the input file as an image in smv, mar300, or mar345 format.\n"); fprintf(stderr," If input_img is not specified or is given as \"-\", it is copied\n"); fprintf(stderr," from stdin to a temporary file.\n"); fprintf(stderr," -p template_cbf\n"); fprintf(stderr," the template for the final cbf to be produced. If template_cbf\n"); fprintf(stderr," is not specified the name is constructed from the first token\n"); fprintf(stderr," of the detector name and the image size as\n"); fprintf(stderr," template__x.cbf\n"); fprintf(stderr," -o output_cbf (default: stdout )\n"); fprintf(stderr," the output cbf combining the image and the template. If the\n"); fprintf(stderr," output_cbf is not specified or is given as \"-\", it is written\n"); fprintf(stderr," to stdout.\n"); fprintf(stderr," -d detectorname\n"); fprintf(stderr," a detector name to be used if none is provided in the image\n"); fprintf(stderr," header.\n"); fprintf(stderr," -F\n"); fprintf(stderr," when writing packed compression, treat the entire image as\n"); fprintf(stderr," one line with no averaging \n"); fprintf(stderr," -m [x|y|x=y] (default x=y, square arrays only)\n"); fprintf(stderr," mirror the array in the x-axis (y -> -y)\n"); fprintf(stderr," in the y-axis (x -> -x)\n"); fprintf(stderr," or in x=y ( x -> y, y-> x)\n"); fprintf(stderr," -r n\n"); fprintf(stderr," rotate the array n times 90 degrees counter clockwise\n"); fprintf(stderr," x -> y, y -> -x for each rotation, n = 1, 2 or 3\n"); fprintf(stderr," -R\n"); fprintf(stderr," if setting a beam center, set reference values of\n"); fprintf(stderr," axis settings as well as standard settings\n"); fprintf(stderr," -S\n"); fprintf(stderr," when generating a copy of the img header in the .details field,\n"); fprintf(stderr," insert a space in front and before and after the equals sign\n"); fprintf(stderr," for compatability with older versions of convert_image\n"); fprintf(stderr," -z distance\n"); fprintf(stderr," detector distance along Z-axis.\n"); fprintf(stderr," -c category_alias=category_root\n"); fprintf(stderr," -t tag_alias=tagroot\n"); fprintf(stderr," map the given alias to the given root, so that instead\n"); fprintf(stderr," of outputting the alias, the root will be presented in the\n"); fprintf(stderr," output cbf instead. These options may be repeated as many\n"); fprintf(stderr," times as needed.\n"); return -1; } void applyxform(axisxform * current, axisxform * xform) { switch (current->posxtarg) { case (posx): current->posxtarg = xform->posxtarg; break; case (posy): current->posxtarg = xform->posytarg; break; case (negx): current->posxtarg = xform->posxtarg==posx?negx: (xform->posxtarg==negx?posx: (xform->posxtarg==posy?negy: (xform->posxtarg==negy?posy:0))); break; case (negy): current->posxtarg = xform->posytarg==posx?negx: (xform->posytarg==negx?posx: (xform->posytarg==posy?negy: (xform->posytarg==negy?posy:0))); break; } switch (current->posytarg) { case (posx): current->posytarg = xform->posxtarg; break; case (posy): current->posytarg = xform->posytarg; break; case (negx): current->posytarg = xform->posxtarg==posx?negx: (xform->posxtarg==negx?posx: (xform->posxtarg==posy?negy: (xform->posxtarg==negy?posy:0))); break; case (negy): current->posytarg = xform->posytarg==posx?negx: (xform->posytarg==negx?posx: (xform->posytarg==posy?negy: (xform->posytarg==negy?posy:0))); break; } return; } int main (int argc, char *argv []) { FILE *in, *out; img_handle img; cbf_handle cbf; char detector_type [64], template_name [256], oscaxis [20], *c; const char *detector_name, *detector_opt, *beam_center, *pixel_size, *axis, *array_id, *binning; char *header_info; double wavelength, distance, osc_start, osc_range, time, bcx, bcy, psx, psy, binx, biny; size_t header_info_size; int dorefs; const char *date; static const char *monthname [] = { "Jan", "Feb", "Mar", "Apr", "May", "Jun", "Jul", "Aug", "Sep", "Oct", "Nov", "Dec" }; axisxform overall = { posx, posy }; axisxform mirrorx = { posx, negy }; axisxform mirrory = { negx, posy }; axisxform mirrorxy = { posy, posx }; axisxform rotate1 = { posy, negx }; axisxform rotate2 = { negx, negy }; axisxform rotate3 = { negy, posx }; axisxform * currentxform; int copt; int errflg = 0; char * imgtmp=NULL; int imgtmpused = 0; const char *imgin, *cbfout, *template, *distancestr, *alias; cbf_detector detector; char *tag, *data, *root; char xalias[81]; int index; int transpose; int fastlen, slowlen; int flat; int sequal; const char * optarg; cbf_getopt_handle opts; /* Usage */ imgin = NULL; cbfout = NULL; template = NULL; detector_opt = NULL; transpose = 0; distancestr = NULL; dorefs = 0; flat = 0; sequal = 0; cbf_failnez (cbf_make_handle (&cbf)) cbf_failnez(cbf_make_getopt_handle(&opts)) cbf_failnez(cbf_getopt_parse(opts, argc, argv, "FRSi:o:p:d:m:r:z:c:t:")) if (!cbf_rewind_getopt_option(opts)) for(;!cbf_get_getopt_data(opts,&copt,NULL,NULL,&optarg);cbf_next_getopt_option(opts)) { if (!copt) break; switch(copt) { case 'i': if (imgin) errflg++; else imgin = optarg; break; case 'o': if (cbfout) errflg++; else cbfout = optarg; break; case 'p': if (template) errflg++; else template = optarg; break; case 'F': flat = 1; break; case 'm': currentxform = (axisxform *)NULL; if (!strcmp(optarg,"x")) currentxform = &mirrorx; if (!strcmp(optarg,"y")) currentxform = &mirrory; if (!strcmp(optarg,"x=y")) currentxform = &mirrorxy; if (!currentxform) errflg++; else applyxform(&overall,currentxform); break; case 'r': currentxform = (axisxform *)NULL; if (!strcmp(optarg,"1")) currentxform = &rotate1; if (!strcmp(optarg,"2")) currentxform = &rotate2; if (!strcmp(optarg,"3")) currentxform = &rotate3; if (!currentxform) errflg++; else applyxform(&overall,currentxform); break; case 'R': dorefs = 1; break; case 'S': if (sequal) errflg++; sequal = 1; break; case 'd': if (detector_opt) errflg++; else detector_opt = optarg; break; case 'z': if (distancestr) errflg++; else distancestr = optarg; break; case 'c': case 't': alias = optarg; if (alias == NULL || *alias == '\0') { errflg++; break; } root = strchr(alias,'='); if (root == NULL || root-alias > 80 || root-alias < 2 || *(root+1) =='\0') { errflg++; break; } strncpy(xalias,optarg,root-alias); xalias[root-alias] = '\0'; root++; if(copt == 'c') { cbf_failnez (cbf_set_category_root(cbf, (const char *)xalias, (const char *) root)) } else { cbf_failnez (cbf_set_tag_root(cbf, (const char *)xalias, (const char *) root)) } break; default: errflg++; break; } } for(;!cbf_get_getopt_data(opts,&copt,NULL,NULL,&optarg);cbf_next_getopt_option(opts)) { if (!imgin) { imgin = optarg; } else { if (!cbfout) { cbfout = optarg; } else { errflg++; } } } if (errflg) { outusage(); exit(-1); } if (!imgin || strcmp(imgin?imgin:"","-") == 0) { imgtmp = (char *)malloc(strlen("/tmp/cvt_imgXXXXXX")+1); strcpy(imgtmp, "/tmp/cvt_imgXXXXXX"); if ((imgin = mktemp(imgtmp)) == NULL ) { fprintf(stderr,"\n convert_image: Can't create temporary file name %s.\n", imgtmp); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } imgtmpused = 1; } /* Read the image */ img = img_make_handle (); cbf_failnez (img_read (img, imgin)) if (imgtmpused) { if (unlink(imgtmp) != 0 ) { fprintf(stderr," convert_image: Can't unlink temporary file %s.\n", imgtmp); fprintf(stderr,"%s\n",strerror(errno)); exit(1); } } /* Identify the detector */ detector_name = img_get_field (img, "DETECTOR"); if (!detector_name || !strcmp(detector_name,"(null)")) { if (detector_opt == NULL) { fprintf (stderr, "\n convert_inage: No detector name provided in image or on the command line!"); outusage(); exit (3); } detector_name = detector_opt; } for (c = detector_type; *detector_name; detector_name++) if (!isspace (*detector_name)) *c++ = tolower (*detector_name); *c = '\0'; /* Construct the template name */ if (template) { in = fopen (template, "rb"); } else { sprintf (template_name, "template_%s_%dx%d.cbf", detector_type, img_columns (img), img_rows (img)); fprintf(stderr," convert_image: template_name: %s\n", template_name); /* Read and modify the template */ in = fopen (template_name, "rb"); } if (!in) { fprintf (stderr," convert_image: unable to open template_name: %s\n", template?template:template_name); exit (4); } cbf_failnez (cbf_read_template (cbf, in)) /* report the header */ header_info_size = 0; for (index = 0; !img_get_next_field(img,(const char **) &tag, (const char **) &data, &index);) { if (tag && data) { header_info_size += (strlen(tag) + strlen(data)+4+sequal*3); } else { if (tag && !data) { header_info_size += (strlen(tag) +2+sequal); } } } header_info_size+=2; cbf_failnez((header_info = malloc(sizeof(char)*header_info_size))==NULL?CBF_ALLOC:0) *header_info = '\0' ; header_info_size = 0; for (index = 0; !img_get_next_field(img,(const char **) &tag, (const char **) &data, &index);) { if (tag && data) { if (sequal) { sprintf (header_info+header_info_size, "\n %s = %s;", tag, data); header_info_size += (strlen(tag) + strlen(data)+6); } else { sprintf (header_info+header_info_size, "\n%s=%s;", tag, data); header_info_size += (strlen(tag) + strlen(data)+3); } } else { if (tag && !data) { if (sequal) { sprintf (header_info+header_info_size, " %s;\n", tag); header_info_size += (strlen(tag) +3); } else { sprintf (header_info+header_info_size, "%s;\n", tag); header_info_size += (strlen(tag) +2); } } } } cbf_failnez(cbf_get_array_id(cbf, 0, &array_id)) cbf_failnez(cbf_require_column(cbf, "details")) cbf_failnez(cbf_set_value(cbf, header_info)) cbf_failnez(cbf_set_typeofvalue(cbf,"text")) /* Wavelength */ wavelength = img_get_number (img, "WAVELENGTH"); if (wavelength) cbf_failnez (cbf_set_wavelength (cbf, wavelength)) /* Distance */ distance = img_get_number (img, "DISTANCE"); if (distance == 0.) { distance = atof (distancestr); } cbf_failnez (cbf_set_axis_setting (cbf, 0, "DETECTOR_Z", distance, 0)) cbf_failnez(cbf_require_category(cbf,"diffrn_measurement")) cbf_failnez(cbf_require_column(cbf,"sample_detector_distance")) cbf_failnez(cbf_set_doublevalue(cbf,"%g", distance)) /* Oscillation start and range */ axis = img_get_field (img, "OSCILLATION AXIS"); if (!axis) axis = "PHI"; if (img_get_field(img, "OSC_START")) osc_start = img_get_number (img, "OSC_START"); else osc_start = img_get_number (img, axis); if (img_get_field(img, "OSC_RANGE")) osc_range = img_get_number (img, "OSC_RANGE"); else osc_range = img_get_number (img, "OSCILLATION RANGE"); sprintf (oscaxis, "GONIOMETER_%s", axis); cbf_failnez (cbf_set_axis_setting (cbf, 0, oscaxis, osc_start, osc_range)) /* Exposure time */ time = img_get_number (img, "EXPOSURE TIME"); if (time) cbf_failnez (cbf_set_integration_time (cbf, 0, time)) /* Date stamp */ date = img_get_field (img, "DATE"); if (date) { char monthstring [16]; int month, day, hour, minute, year; double second; year = 0; sscanf (date, "%*s %s %d %d:%d:%lf %d", monthstring, &day, &hour, &minute, &second, &year); if (year != 0) { for (month = 0; month < 12; month++) if (strcmp (monthname [month], monthstring) == 0) break; month++; if (month <= 12) cbf_failnez (cbf_set_datestamp (cbf, 0, year, month, day, hour, minute, second, CBF_NOTIMEZONE, 0)) } } /* diffrn.id */ cbf_failnez (cbf_set_diffrn_id (cbf, "DS1")) /* Image */ if (img->rowmajor) { fastlen = img_columns(img); slowlen = img_rows(img); } else { fastlen = img_rows(img); slowlen = img_columns(img); } if (overall.posxtarg != posx || overall.posytarg != posy || img->rowmajor) { int fastorig, faststep, sloworig, slowstep, curpos, i, j; int * tempimg; if (overall.posxtarg==0 || overall.posytarg==0) { fprintf (stderr,"\n convert_image: invalid image transform.\n"); exit(1); } if (img_rows(img) != img_columns(img) ) { fprintf(stderr,"\n convert_img: Unable to transpose image\n"); exit(-1); } /* if in row major order, the fast index is the x axis, counting the columns, and the slow index is the y axis, counting the rows */ if (img->rowmajor) { fastorig = sloworig = 0; faststep = 1; slowstep = img_columns(img); switch (overall.posxtarg) { case (posx): break; case (negx): fastorig = img_columns(img)-1; faststep = -1; break; case (posy): faststep = img_columns(img); fastlen = img_rows(img); slowlen = img_columns(img); break; case (negy): fastorig = (img_columns(img))*(img_rows(img)-1); faststep = -img_columns(img); fastlen = img_rows(img); slowlen = img_columns(img); break; } switch (overall.posytarg) { case (posx): slowstep = 1; fastlen = img_rows(img); slowlen = img_columns(img); break; case (negx): sloworig = img_columns(img)-1; slowstep= -1; fastlen = img_rows(img); slowlen = img_columns(img); break; case (posy): break; case (negy): sloworig = img_columns(img)*(img_rows(img)-1); slowstep = -img_columns(img); break; } } else { fastorig = sloworig = 0; faststep = 1; slowstep = img_rows(img); switch (overall.posxtarg) { case (posx): break; case (negx): sloworig = img_rows(img)*(img_columns(img)-1); slowstep = -img_rows(img); break; case (posy): slowstep = 1; fastlen = img_columns(img); slowlen = img_rows(img); break; case (negy): sloworig = img_rows(img)-1; slowstep = -1; fastlen = img_columns(img); slowlen = img_rows(img); break; break; } switch (overall.posytarg) { case (posx): faststep = img_rows(img); fastlen = img_columns(img); slowlen = img_rows(img); break; case (negx): fastorig = (img_rows(img))*(img_columns(img)-1); faststep = -img_rows(img); fastlen = img_columns(img); slowlen = img_rows(img); break; case (posy): break; case (negy): fastorig = img_rows(img)-1; faststep = -1; break; } } curpos = fastorig+sloworig; tempimg = malloc(img_columns(img)*img_rows(img)*sizeof(int)); if (!tempimg) { fprintf(stderr,"\n unable to allocate temporary image array\n"); } for (i=0;iimage)+i+j*fastlen); /* *((int *)tempimg+curpos) = img_pixel(img, j, i); */ curpos = curpos+slowstep; } } for (i=0;iimage)+i+j*fastlen) = *((int *)tempimg+i+j*fastlen); } } } if (flat) { cbf_failnez (cbf_set_image (cbf, 0, 0, CBF_PACKED|CBF_FLAT_IMAGE, img->image, sizeof (int), 1, slowlen, fastlen)) } else { cbf_failnez (cbf_set_image (cbf, 0, 0, CBF_PACKED, img->image, sizeof (int), 1, slowlen, fastlen)) } /* fix up the array_structure_list.direction and .precedence */ if (overall.posxtarg != posx || overall.posytarg != posy) { unsigned int arow[2], precedence[2], temp; char * direction[2], * dtemp; arow[0] = arow[1] = 0; precedence[0] = 1; precedence[1] = 2; direction[0] = direction[1] = NULL; cbf_failnez (cbf_find_category (cbf, "array_structure_list")) cbf_failnez (cbf_find_column (cbf, "array_id")) while (!cbf_find_nextrow (cbf, array_id)) { cbf_failnez (cbf_find_column (cbf, "precedence")) cbf_failnez (cbf_get_integervalue (cbf, (int *)&temp)) if (temp == 1 || temp == 2) { cbf_failnez(cbf_row_number(cbf,&(arow[temp-1]))) arow[temp-1]++; cbf_failnez(cbf_find_column(cbf,"direction")) cbf_failnez(cbf_get_value(cbf,(const char**)&(direction[temp-1]))) cbf_failnez(cbf_find_column (cbf, "array_id")) } } switch (overall.posxtarg) { case (posx): break; case (negx): if (!cbf_cistrcmp(direction[0],"increasing")) { direction[0] = "decreasing"; } else { direction[0] = "increasing"; } break; case (posy): precedence[0] = 2; precedence[1] = 1; dtemp = direction[0]; direction[0]=direction[1]; direction[1]=dtemp; break; case (negy): precedence[0] = 2; precedence[1] = 1; dtemp = direction[0]; direction[0]=direction[1]; direction[1]=dtemp; if (!cbf_cistrcmp(direction[0],"increasing")) { direction[0] = "decreasing"; } else { direction[0] = "increasing"; } break; } switch (overall.posytarg) { case (posx): break; case (negx): if (!cbf_cistrcmp(direction[1],"increasing")) { direction[1] = "decreasing"; } else { direction[1] = "increasing"; } break; case (posy): break; case (negy): if (!cbf_cistrcmp(direction[1],"increasing")) { direction[1] = "decreasing"; } else { direction[1] = "increasing"; } break; } if (arow[0]) { cbf_failnez (cbf_select_row (cbf, arow[0]-1)) cbf_failnez (cbf_find_column (cbf, "precedence")) cbf_failnez (cbf_set_integervalue (cbf, precedence[0])) cbf_failnez (cbf_find_column (cbf, "direction")) cbf_failnez (cbf_set_value (cbf, direction[0])) } if (arow[1]) { cbf_failnez (cbf_select_row (cbf, arow[1]-1)) cbf_failnez (cbf_find_column (cbf, "precedence")) cbf_failnez (cbf_set_integervalue (cbf, precedence[1])) cbf_failnez (cbf_find_column (cbf, "direction")) cbf_failnez (cbf_set_value (cbf, direction[1])) } } /* binning */ binx = biny = 0.0; if ((binning = img_get_field(img,"BIN"))) { char *endptr; biny = binx = strtod (binning, &endptr); if (*endptr && *(endptr+1)) biny = strtod (endptr+1, &endptr); if (binx <= 0.0 || biny <= 0.0) { fprintf(stderr," Bad bin values %g x %g ignored\n", binx, biny); } else { cbf_failnez(cbf_set_bin_sizes(cbf, 0, binx, biny)) } } /* beam center and pixel size */ bcx = bcy = psx = psy = 0.0; if ((pixel_size = img_get_field(img,"PIXEL SIZE")) || (pixel_size = img_get_field(img,"PIXEL_SIZE")) ) { char *endptr; psy = psx = strtod (pixel_size, &endptr); if (*endptr) psy = strtod (endptr, &endptr); } if ((beam_center = img_get_field(img,"BEAM CENTRE")) ) { char *endptr; bcx = strtod (beam_center, &endptr); if (*endptr) bcy = strtod (endptr, &endptr); if (psx) bcx /= psx; if (psy) bcy /= psy; bcx = .5*rint(2.*bcx); bcy = .5*rint(2.*bcy); } if ((beam_center = img_get_field(img,"CENTER")) ) { char *endptr; endptr = strstr(beam_center,"X "); bcx = strtod (endptr+2, &endptr); if (*endptr) { endptr = strstr(endptr,"Y "); bcy = strtod (endptr+2, &endptr); } } if (overall.posxtarg != posx || overall.posytarg != posy) { double obcx = bcx, obcy = bcy, opsx = psx, opsy = psy; switch (overall.posxtarg) { case (posx): break; case (negx): bcx = img_columns(img)-1-obcx; break; case (posy): bcx = obcy; psx = opsy; break; case (negy): bcx = img_rows(img)-1-obcy; psx = opsy; break; } switch (overall.posytarg) { case (posx): bcy = obcx; psy = opsx; break; case (negx): bcy = img_columns(img)-1-obcx; psy = opsx; break; case (posy): bcy = obcy; break; case (negy): bcy = img_rows(img)-1-obcy; break; } } cbf_failnez (cbf_set_pixel_size (cbf, 0, 1, psx)) cbf_failnez (cbf_set_pixel_size (cbf, 0, 2, psy)) /* fprintf(stderr, "header pixel center indices: %g %g\n",bcx, bcy); */ cbf_failnez(cbf_construct_detector (cbf, &detector, 0)) cbf_failnez(cbf_set_beam_center(detector,&bcx,&bcy,NULL,NULL)) cbf_failnez(cbf_free_detector(detector)) if (dorefs) { cbf_failnez(cbf_require_reference_detector (cbf, &detector, 0)) cbf_failnez(cbf_set_reference_beam_center(detector,&bcx,&bcy,NULL,NULL)) cbf_failnez(cbf_free_detector(detector)) } /*****************************************************************************/ { const char *id; /* double d [4]; */ /* int i [4]; */ /* unsigned int u [4]; */ /* size_t s [4]; */ /* double cell[6], cell_esd[6], rcell[6], rcell_esd[6]; */ cbf_goniometer goniometer; /* Change the diffrn.id entry in all the categories */ /* cbf_set_diffrn_id (cbf, "TEST"); */ /* Get the diffrn.id entry */ /* cbf_get_diffrn_id (cbf, &id); */ /* Change the diffrn.crystal_id entry */ /* cbf_set_crystal_id (cbf, "CTEST"); */ /* Get the diffrn.crystal_id entry */ cbf_get_crystal_id (cbf, &id); /* Test the cell functions */ /* cell[0] = cell[1] = cell[2] = cell[3] = cell[4] = cell[5] = 0.; cell_esd[0] = cell_esd[1] = cell_esd[2] = cell_esd[3] = cell_esd[4] = cell_esd[5] = 0.; rcell[0] = rcell[1] = rcell[2] = rcell[3] = rcell[4] = rcell[5] = 0.; rcell_esd[0] = rcell_esd[1] = rcell_esd[2] = rcell_esd[3] = rcell_esd[4] = rcell_esd[5] = 0.; if (cbf_get_unit_cell(cbf, cell, cell_esd) || cbf_get_reciprocal_cell(cbf, rcell, rcell_esd)) { fprintf(stdout," No cell in the template, putting in rcell, no cell\n"); rcell[0]=rcell[1]=rcell[2]=1.; rcell[3]=rcell[4]=rcell[5]=90.; rcell_esd[0]=rcell_esd[1]=rcell_esd[2]=0.; rcell_esd[3]=rcell_esd[4]=rcell_esd[5]=0.; cbf_failnez(cbf_set_reciprocal_cell(cbf,rcell,rcell_esd)) } cbf_failnez(cbf_get_unit_cell(cbf,cell,cell_esd)) cbf_failnez(cbf_get_reciprocal_cell(cbf,rcell,rcell_esd)) fprintf(stdout," Starting cell, rcell:\n {%g,%g,%g,%g,%g,%g} {%g,%g,%g,%g,%g,%g}\n", cell[0], cell[1], cell[2], cell[3], cell[4], cell[5], rcell[0], rcell[1], rcell[2], rcell[3], rcell[4], rcell[5]); cell[0] = 85.; cell[1] = 90.; cell[2] = 95.; cell_esd[0] = .05; cell_esd[1] = .035; cell_esd[2] = .15; cell[3] = 78.13; cell[4] = 103.12; cell[5] = 101.48; cell_esd[3] = .055; cell_esd[4] = .065; cell_esd[5] = .11; cbf_failnez(cbf_compute_reciprocal_cell(cell,rcell)) cbf_failnez(cbf_set_unit_cell(cbf,cell,cell_esd)) cbf_failnez(cbf_set_reciprocal_cell(cbf,rcell,rcell_esd)) cell[0] = cell[1] = cell[2] = cell[3] = cell[4] = cell[5] = 0.; cell_esd[0] = cell_esd[1] = cell_esd[2] = cell_esd[3] = cell_esd[4] = cell_esd[5] = 0.; rcell[0] = rcell[1] = rcell[2] = rcell[3] = rcell[4] = rcell[5] = 0.; rcell_esd[0] = rcell_esd[1] = rcell_esd[2] = rcell_esd[3] = rcell_esd[4] = rcell_esd[5] = 0.; cbf_failnez(cbf_get_unit_cell (cbf,cell,cell_esd)) cbf_failnez(cbf_get_reciprocal_cell (cbf,rcell,rcell_esd)) fprintf(stdout," Final cell, rcell:\n {%g,%g,%g,%g,%g,%g} {%g,%g,%g,%g,%g,%g}\n", cell[0], cell[1], cell[2], cell[3], cell[4], cell[5], rcell[0], rcell[1], rcell[2], rcell[3], rcell[4], rcell[5]); */ /* Set the wavelength */ /* cbf_set_wavelength (cbf, 2.14); */ /* Get the wavelength */ /* cbf_get_wavelength (cbf, &wavelength); */ /* Set the polarization */ /* cbf_set_polarization (cbf, 0.5, 0.75); */ /* Get the polarization */ /* cbf_get_polarization (cbf, &d [0], &d [1]); */ /* Set the divergence */ /* cbf_set_divergence (cbf, 0.3, 0.4, 0.5); */ /* Get the divergence */ /* cbf_get_divergence (cbf, &d [0], &d [1], &d [2]); */ /* Get the number of elements */ /* cbf_count_elements (cbf, &u [0]); */ /* Get the element id */ cbf_get_element_id (cbf, 0, &id); /* fprintf(stdout," Element ID: %s\n", id); */ /* Set the gain of a detector element */ /* cbf_set_gain (cbf, 0, 0.24, 0.04); */ /* Get the gain of a detector element */ /* cbf_get_gain (cbf, 0, &d [0], &d [1]); */ /* Set the overload value of a detector element */ /* cbf_set_overload (cbf, 0, 100000); */ /* Get the overload value of a detector element */ /* cbf_get_overload (cbf, 0, &d [0]); */ /* Set the integration time */ /* cbf_set_integration_time (cbf, 0, 10.1); */ /* Get the integration time */ /* cbf_get_integration_time (cbf, 0, &d [0]); */ /* Set the collection date and time (1) as seconds since January 1 1970 */ /* cbf_set_timestamp (cbf, 0, 1000.0, CBF_NOTIMEZONE, 0.1); */ /* Get the collection date and time (1) as seconds since January 1 1970 */ /* cbf_get_timestamp (cbf, 0, &d [0], &i [0]); */ /* Get the image size */ /* cbf_get_image_size (cbf, 0, 0, &s [0], &s [1]); */ /* Change the setting of an axis */ /* cbf_set_axis_setting (cbf, 0, "GONIOMETER_PHI", 27.0, 0.5); */ /* Get the setting of an axis */ /* cbf_get_axis_setting (cbf, 0, "GONIOMETER_PHI", &d [0], &d [1]); */ /* Construct a goniometer */ cbf_failnez(cbf_construct_goniometer (cbf, &goniometer)) /* Get the rotation axis */ /* cbf_get_rotation_axis (goniometer, 0, &d [0], &d [1], &d [2]); */ /* Get the rotation range */ /* cbf_get_rotation_range (goniometer, 0, &d [0], &d [1]); */ /* Reorient a vector */ /* cbf_rotate_vector (goniometer, 0, 0.5, 0.3, 0, 1, &d [0], &d [1], &d [2]); */ /* Convert a vector to reciprocal space */ /* cbf_get_reciprocal (goniometer, 0, 0.3, 0.98, 1, 2, -3, &d [0], &d [1], &d [2]); */ /* Construct a detector positioner */ /* cbf_failnez(cbf_construct_detector (cbf, &detector, 0)); */ /* Get the beam center */ /* cbf_get_beam_center (detector, &d [0], &d [1], &d [2], &d [3]); fprintf(stderr," convert_image: beam center: %g %g %g %g\n", d[0], d[1], d[2], d[3]); */ /* Get the detector distance */ /* cbf_get_detector_distance (detector, &d [0]); */ /* fprintf(stdout, " detector distance: %-15g\n",d[0]); */ /* Get the detector normal */ /* cbf_get_detector_normal (detector, &d [0], &d [1], &d [2]); */ /* Calcluate the coordinates of a pixel */ /* cbf_get_pixel_coordinates (detector, 1, 3, &d [0], &d [1], &d [2]); */ /* Calcluate the area of a pixel */ /* cbf_get_pixel_area (detector, 1, 3, &d [0], &d [1]); fprintf(stdout, " Pixel area, projected area at pixel(3,1): %-15g, %-15g\n",d[0], d[1]); cbf_get_pixel_area_fs(detector, 12, 25, &d [0], &d [1]); fprintf(stdout, " Pixel area, projected area at pixel(12,25): %-15g, %-15g\n",d[0], d[1]); */ /* Calculate the dimensions of a pixel */ /* cbf_failnez (cbf_get_inferred_pixel_size (detector, 1, &d [0])) cbf_failnez (cbf_get_inferred_pixel_size (detector, 2, &d [1])) fprintf(stdout, " Template detector size: %-15g x %-15g \n", d[0], d[1]); cbf_failnez (cbf_get_inferred_pixel_size_sf(detector, 1, &d [0])) cbf_failnez (cbf_get_inferred_pixel_size_sf(detector, 2, &d [1])) fprintf(stdout, " Inferred detector size (sf) : %-15g x %-15g \n", d[0], d[1]); cbf_failnez (cbf_set_pixel_size (cbf, 0, 1, d [0])) cbf_failnez (cbf_set_pixel_size (cbf, 0, 2, d [1])) cbf_failnez (cbf_get_pixel_size_fs(cbf, 0, 1, &d [2])) cbf_failnez (cbf_get_pixel_size_fs(cbf, 0, 2, &d [3])) fprintf(stdout, " Array element size (fs): %-15g x %-15g \n", d[2], d[3]); cbf_failnez (cbf_set_pixel_size_sf(cbf, 0, 1, d [1])) cbf_failnez (cbf_set_pixel_size_sf(cbf, 0, 2, d [0])) cbf_failnez (cbf_get_pixel_size_sf(cbf, 0, 1, &d [2])) cbf_failnez (cbf_get_pixel_size_sf(cbf, 0, 2, &d [3])) fprintf(stdout, " Array element size (sf): %-15g x %-15g \n", d[2], d[3]); */ /* Get the bin sizes */ /*if(cbf_get_bin_sizes(cbf,0,&d[0],&d[1])) { fprintf (stdout," Pixel bin sizes not specified \n"); } else { fprintf(stdout, " Pixel bin sizes %-.15g x %-.15g \n", d[0], d[1]); } */ /* Free a detector */ /* cbf_free_detector (detector); */ /* Free a goniometer */ /* cbf_free_goniometer (goniometer);*/ } /*****************************************************************************/ /* Write the new file */ out = stdout; if (cbfout && strcmp(cbfout,"-"))out = fopen (cbfout, "w+b"); if (!out) { fprintf (stderr, " convert_image: Couldn't open the CBF file %s\n", cbfout); exit (1); } cbf_failnez (cbf_write_file (cbf, out, (cbfout && strcmp(cbfout,"-"))?1:0, CBF, MSG_DIGEST | MIME_HEADERS, 0)) /* Free the cbf */ cbf_failnez (cbf_free_handle (cbf)) /* Free the image */ img_free_handle (img); /* Free the getopt_handle */ cbf_failnez (cbf_free_getopt_handle(opts)) /* Success */ return 0; } int local_exit (int status) { exit(status); return 1; /* avoid warnings */ } ./CBFlib-0.9.2.2/dREL-ply-0.5/0000755000076500007650000000000011603703065013473 5ustar yayayaya./CBFlib-0.9.2.2/dREL-ply-0.5/test_data.cif0000755000076500007650000000117011603702115016123 0ustar yayayaya### A cif for testing dREL constructs # Based on example in dREL documentation 2008 data_testdata loop_ _position.number _position.object_id _position.vector_xyz 1 origin [0.0, 0.0, 0.0] 2 body-diagonal [5.0, 5.0, 5.0] 32 diagonal-terminal [10.0, 10.0, 10.0] loop_ _geom.type _geom.vertex1_id _geom.vertex2_id _geom.vertex3_id point origin . . line origin body-diagonal . line body-diagonal diagonal-terminal . triangle origin body-diagonal diagonal-terminal ./CBFlib-0.9.2.2/dREL-ply-0.5/parser.out0000755000076500007650000256712311603702115015536 0ustar yayayayaCreated by PLY version 3.2 (http://www.dabeaz.com/ply) Unused terminals: COMMENT Grammar Rule 0 S' -> final_input Rule 1 final_input -> input Rule 2 input -> statement Rule 3 input -> input statement Rule 4 statement -> stmt_list Rule 5 statement -> compound_stmt Rule 6 stmt_list -> simple_stmt Rule 7 stmt_list -> stmt_list ; simple_stmt Rule 8 stmt_list -> stmt_list ; simple_stmt ; Rule 9 simple_stmt -> assignment_stmt Rule 10 simple_stmt -> augmented_assignment_stmt Rule 11 simple_stmt -> fancy_drel_assignment_stmt Rule 12 simple_stmt -> print_stmt Rule 13 simple_stmt -> BREAK Rule 14 simple_stmt -> NEXT Rule 15 print_stmt -> PRINT expression Rule 16 expression_list -> expression Rule 17 expression_list -> expression_list , expression Rule 18 expression -> or_test Rule 19 target -> primary Rule 20 target -> ( target_list ) Rule 21 target -> [ target_list ] Rule 22 or_test -> and_test Rule 23 or_test -> or_test OR and_test Rule 24 and_test -> not_test Rule 25 and_test -> and_test AND not_test Rule 26 not_test -> comparison Rule 27 not_test -> NOT not_test Rule 28 comparison -> a_expr Rule 29 comparison -> a_expr comp_operator a_expr Rule 30 comp_operator -> < Rule 31 comp_operator -> > Rule 32 comp_operator -> GTE Rule 33 comp_operator -> LTE Rule 34 comp_operator -> NEQ Rule 35 comp_operator -> ISEQUAL Rule 36 comp_operator -> IN Rule 37 comp_operator -> NOT IN Rule 38 a_expr -> m_expr Rule 39 a_expr -> a_expr + m_expr Rule 40 a_expr -> a_expr - m_expr Rule 41 m_expr -> u_expr Rule 42 m_expr -> m_expr * u_expr Rule 43 m_expr -> m_expr / u_expr Rule 44 m_expr -> m_expr ^ u_expr Rule 45 u_expr -> power Rule 46 u_expr -> - u_expr Rule 47 u_expr -> + u_expr Rule 48 power -> primary Rule 49 power -> primary POWER u_expr Rule 50 primary -> atom Rule 51 primary -> primary_att Rule 52 primary -> subscription Rule 53 primary -> slicing Rule 54 primary -> call Rule 55 primary_att -> attributeref Rule 56 atom -> ID Rule 57 atom -> item_tag Rule 58 atom -> literal Rule 59 atom -> enclosure Rule 60 item_tag -> ITEM_TAG Rule 61 literal -> stringliteral Rule 62 literal -> INTEGER Rule 63 literal -> HEXINT Rule 64 literal -> OCTINT Rule 65 literal -> BININT Rule 66 literal -> REAL Rule 67 literal -> IMAGINARY Rule 68 stringliteral -> STRPREFIX SHORTSTRING Rule 69 stringliteral -> STRPREFIX LONGSTRING Rule 70 stringliteral -> SHORTSTRING Rule 71 stringliteral -> LONGSTRING Rule 72 enclosure -> parenth_form Rule 73 enclosure -> string_conversion Rule 74 enclosure -> list_display Rule 75 parenth_form -> ( expression_list ) Rule 76 parenth_form -> ( ) Rule 77 string_conversion -> ` expression_list ` Rule 78 list_display -> [ listmaker ] Rule 79 list_display -> [ ] Rule 80 listmaker -> expression listmaker2 Rule 81 listmaker -> expression list_for Rule 82 listmaker2 -> , expression Rule 83 listmaker2 -> listmaker2 , expression Rule 84 listmaker2 -> Rule 85 list_for -> FOR expression_list IN testlist Rule 86 list_for -> FOR expression_list IN testlist list_iter Rule 87 testlist -> or_test Rule 88 testlist -> testlist , or_test Rule 89 testlist -> testlist , or_test , Rule 90 list_iter -> list_for Rule 91 list_iter -> list_if Rule 92 list_if -> IF or_test Rule 93 list_if -> IF or_test list_iter Rule 94 attributeref -> primary attribute_tag Rule 95 attribute_tag -> . ID Rule 96 attribute_tag -> REAL Rule 97 subscription -> primary [ expression_list ] Rule 98 slicing -> simple_slicing Rule 99 slicing -> extended_slicing Rule 100 simple_slicing -> primary [ short_slice ] Rule 101 short_slice -> : Rule 102 short_slice -> expression : expression Rule 103 short_slice -> : expression Rule 104 short_slice -> expression : Rule 105 extended_slicing -> primary [ slice_list ] Rule 106 slice_list -> slice_item Rule 107 slice_list -> slice_list , slice_item Rule 108 slice_item -> expression Rule 109 slice_item -> proper_slice Rule 110 slice_item -> ELLIPSIS Rule 111 proper_slice -> short_slice Rule 112 proper_slice -> long_slice Rule 113 long_slice -> short_slice : Rule 114 long_slice -> short_slice : expression Rule 115 call -> primary ( ) Rule 116 call -> primary ( argument_list ) Rule 117 argument_list -> func_arg Rule 118 argument_list -> argument_list , func_arg Rule 119 func_arg -> expression Rule 120 augmented_assignment_stmt -> target AUGOP expression_list Rule 121 fancy_drel_assignment_stmt -> primary ( dotlist ) Rule 122 dotlist -> . ID = expression Rule 123 dotlist -> dotlist , . ID = expression Rule 124 assignment_stmt -> target_list = expression_list Rule 125 target_list -> target Rule 126 target_list -> target_list , target Rule 127 compound_stmt -> if_stmt Rule 128 compound_stmt -> for_stmt Rule 129 compound_stmt -> do_stmt Rule 130 compound_stmt -> loop_stmt Rule 131 compound_stmt -> with_stmt Rule 132 compound_stmt -> where_stmt Rule 133 compound_stmt -> switch_stmt Rule 134 compound_stmt -> funcdef Rule 135 if_stmt -> IF expression suite Rule 136 if_stmt -> if_stmt ELSE suite Rule 137 suite -> simple_stmt Rule 138 suite -> compound_stmt Rule 139 suite -> open_brace statement_block close_brace Rule 140 open_brace -> { Rule 141 close_brace -> } Rule 142 statement_block -> statement Rule 143 statement_block -> statement_block statement Rule 144 for_stmt -> FOR target_list IN expression_list suite Rule 145 loop_stmt -> loop_head suite Rule 146 loop_head -> LOOP ID AS ID Rule 147 loop_head -> LOOP ID AS ID : ID Rule 148 loop_head -> LOOP ID AS ID : ID comp_operator ID Rule 149 do_stmt -> do_stmt_head suite Rule 150 do_stmt_head -> DO ID = expression , expression Rule 151 do_stmt_head -> DO ID = expression , expression , expression Rule 152 with_stmt -> with_head suite Rule 153 with_head -> WITH ID AS ID Rule 154 where_stmt -> WHERE expression suite ELSE suite Rule 155 switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace Rule 156 caselist -> CASE target_list suite Rule 157 caselist -> caselist CASE target_list suite Rule 158 funcdef -> FUNCTION ID ( arglist ) suite Rule 159 arglist -> ID : list_display Rule 160 arglist -> arglist , ID : list_display Terminals, with rules where they appear ( : 20 75 76 115 116 121 158 ) : 20 75 76 115 116 121 158 * : 42 + : 39 47 , : 17 82 83 88 89 89 107 118 123 126 150 151 151 160 - : 40 46 . : 95 122 123 / : 43 : : 101 102 103 104 113 114 147 148 159 160 ; : 7 8 8 < : 30 = : 122 123 124 150 151 > : 31 AND : 25 AS : 146 147 148 153 AUGOP : 120 BININT : 65 BREAK : 13 CASE : 156 157 COMMENT : DEFAULT : 155 DO : 150 151 ELLIPSIS : 110 ELSE : 136 154 FOR : 85 86 144 FUNCTION : 158 GTE : 32 HEXINT : 63 ID : 56 95 122 123 146 146 147 147 147 148 148 148 148 150 151 153 153 155 158 159 160 IF : 92 93 135 IMAGINARY : 67 IN : 36 37 85 86 144 INTEGER : 62 ISEQUAL : 35 ITEM_TAG : 60 LONGSTRING : 69 71 LOOP : 146 147 148 LTE : 33 NEQ : 34 NEXT : 14 NOT : 27 37 OCTINT : 64 OR : 23 POWER : 49 PRINT : 15 REAL : 66 96 SHORTSTRING : 68 70 STRPREFIX : 68 69 SWITCH : 155 WHERE : 154 WITH : 153 [ : 21 78 79 97 100 105 ] : 21 78 79 97 100 105 ^ : 44 ` : 77 77 error : { : 140 } : 141 Nonterminals, with rules where they appear a_expr : 28 29 29 39 40 and_test : 22 23 25 arglist : 158 160 argument_list : 116 118 assignment_stmt : 9 atom : 50 attribute_tag : 94 attributeref : 55 augmented_assignment_stmt : 10 call : 54 caselist : 155 157 close_brace : 139 155 comp_operator : 29 148 comparison : 26 compound_stmt : 5 138 do_stmt : 129 do_stmt_head : 149 dotlist : 121 123 enclosure : 59 expression : 15 16 17 80 81 82 83 102 102 103 104 108 114 119 122 123 135 150 150 151 151 151 154 expression_list : 17 75 77 85 86 97 120 124 144 extended_slicing : 99 fancy_drel_assignment_stmt : 11 final_input : 0 for_stmt : 128 func_arg : 117 118 funcdef : 134 if_stmt : 127 136 input : 1 3 item_tag : 57 list_display : 74 159 160 list_for : 81 90 list_if : 91 list_iter : 86 93 listmaker : 78 listmaker2 : 80 83 literal : 58 long_slice : 112 loop_head : 145 loop_stmt : 130 m_expr : 38 39 40 42 43 44 not_test : 24 25 27 open_brace : 139 155 or_test : 18 23 87 88 89 92 93 parenth_form : 72 power : 45 primary : 19 48 49 94 97 100 105 115 116 121 primary_att : 51 print_stmt : 12 proper_slice : 109 short_slice : 100 111 113 114 simple_slicing : 98 simple_stmt : 6 7 8 137 slice_item : 106 107 slice_list : 105 107 slicing : 53 statement : 2 3 142 143 statement_block : 139 143 stmt_list : 4 7 8 string_conversion : 73 stringliteral : 61 subscription : 52 suite : 135 136 144 145 149 152 154 154 155 156 157 158 switch_stmt : 133 target : 120 125 126 target_list : 20 21 124 126 144 156 157 testlist : 85 86 88 89 u_expr : 41 42 43 44 46 47 49 where_stmt : 132 with_head : 152 with_stmt : 131 Parsing method: LALR state 0 (0) S' -> . final_input (1) final_input -> . input (2) input -> . statement (3) input -> . input statement (4) statement -> . stmt_list (5) statement -> . compound_stmt (6) stmt_list -> . simple_stmt (7) stmt_list -> . stmt_list ; simple_stmt (8) stmt_list -> . stmt_list ; simple_stmt ; (127) compound_stmt -> . if_stmt (128) compound_stmt -> . for_stmt (129) compound_stmt -> . do_stmt (130) compound_stmt -> . loop_stmt (131) compound_stmt -> . with_stmt (132) compound_stmt -> . where_stmt (133) compound_stmt -> . switch_stmt (134) compound_stmt -> . funcdef (9) simple_stmt -> . assignment_stmt (10) simple_stmt -> . augmented_assignment_stmt (11) simple_stmt -> . fancy_drel_assignment_stmt (12) simple_stmt -> . print_stmt (13) simple_stmt -> . BREAK (14) simple_stmt -> . NEXT (135) if_stmt -> . IF expression suite (136) if_stmt -> . if_stmt ELSE suite (144) for_stmt -> . FOR target_list IN expression_list suite (149) do_stmt -> . do_stmt_head suite (145) loop_stmt -> . loop_head suite (152) with_stmt -> . with_head suite (154) where_stmt -> . WHERE expression suite ELSE suite (155) switch_stmt -> . SWITCH ID open_brace caselist DEFAULT suite close_brace (158) funcdef -> . FUNCTION ID ( arglist ) suite (124) assignment_stmt -> . target_list = expression_list (120) augmented_assignment_stmt -> . target AUGOP expression_list (121) fancy_drel_assignment_stmt -> . primary ( dotlist ) (15) print_stmt -> . PRINT expression (150) do_stmt_head -> . DO ID = expression , expression (151) do_stmt_head -> . DO ID = expression , expression , expression (146) loop_head -> . LOOP ID AS ID (147) loop_head -> . LOOP ID AS ID : ID (148) loop_head -> . LOOP ID AS ID : ID comp_operator ID (153) with_head -> . WITH ID AS ID (125) target_list -> . target (126) target_list -> . target_list , target (19) target -> . primary (20) target -> . ( target_list ) (21) target -> . [ target_list ] (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] BREAK shift and go to state 56 NEXT shift and go to state 7 IF shift and go to state 61 FOR shift and go to state 30 WHERE shift and go to state 19 SWITCH shift and go to state 46 FUNCTION shift and go to state 36 PRINT shift and go to state 28 DO shift and go to state 58 LOOP shift and go to state 25 WITH shift and go to state 5 ( shift and go to state 6 [ shift and go to state 38 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ` shift and go to state 20 final_input shift and go to state 1 fancy_drel_assignment_stmt shift and go to state 26 primary_att shift and go to state 41 primary shift and go to state 42 augmented_assignment_stmt shift and go to state 27 stringliteral shift and go to state 23 item_tag shift and go to state 52 switch_stmt shift and go to state 43 do_stmt_head shift and go to state 4 enclosure shift and go to state 29 subscription shift and go to state 53 parenth_form shift and go to state 8 print_stmt shift and go to state 50 literal shift and go to state 45 assignment_stmt shift and go to state 32 call shift and go to state 47 statement shift and go to state 48 string_conversion shift and go to state 49 with_head shift and go to state 51 loop_head shift and go to state 12 do_stmt shift and go to state 13 compound_stmt shift and go to state 35 attributeref shift and go to state 9 simple_slicing shift and go to state 37 simple_stmt shift and go to state 14 loop_stmt shift and go to state 15 slicing shift and go to state 17 target_list shift and go to state 63 for_stmt shift and go to state 18 input shift and go to state 11 funcdef shift and go to state 3 target shift and go to state 54 stmt_list shift and go to state 62 if_stmt shift and go to state 21 extended_slicing shift and go to state 34 list_display shift and go to state 22 where_stmt shift and go to state 39 with_stmt shift and go to state 24 atom shift and go to state 2 state 1 (0) S' -> final_input . state 2 (50) primary -> atom . ( reduce using rule 50 (primary -> atom .) [ reduce using rule 50 (primary -> atom .) . reduce using rule 50 (primary -> atom .) REAL reduce using rule 50 (primary -> atom .) AUGOP reduce using rule 50 (primary -> atom .) = reduce using rule 50 (primary -> atom .) , reduce using rule 50 (primary -> atom .) POWER reduce using rule 50 (primary -> atom .) * reduce using rule 50 (primary -> atom .) / reduce using rule 50 (primary -> atom .) ^ reduce using rule 50 (primary -> atom .) + reduce using rule 50 (primary -> atom .) - reduce using rule 50 (primary -> atom .) < reduce using rule 50 (primary -> atom .) > reduce using rule 50 (primary -> atom .) GTE reduce using rule 50 (primary -> atom .) LTE reduce using rule 50 (primary -> atom .) NEQ reduce using rule 50 (primary -> atom .) ISEQUAL reduce using rule 50 (primary -> atom .) IN reduce using rule 50 (primary -> atom .) NOT reduce using rule 50 (primary -> atom .) AND reduce using rule 50 (primary -> atom .) OR reduce using rule 50 (primary -> atom .) ; reduce using rule 50 (primary -> atom .) BREAK reduce using rule 50 (primary -> atom .) NEXT reduce using rule 50 (primary -> atom .) IF reduce using rule 50 (primary -> atom .) FOR reduce using rule 50 (primary -> atom .) WHERE reduce using rule 50 (primary -> atom .) SWITCH reduce using rule 50 (primary -> atom .) FUNCTION reduce using rule 50 (primary -> atom .) PRINT reduce using rule 50 (primary -> atom .) DO reduce using rule 50 (primary -> atom .) LOOP reduce using rule 50 (primary -> atom .) WITH reduce using rule 50 (primary -> atom .) ID reduce using rule 50 (primary -> atom .) ITEM_TAG reduce using rule 50 (primary -> atom .) INTEGER reduce using rule 50 (primary -> atom .) HEXINT reduce using rule 50 (primary -> atom .) OCTINT reduce using rule 50 (primary -> atom .) BININT reduce using rule 50 (primary -> atom .) IMAGINARY reduce using rule 50 (primary -> atom .) STRPREFIX reduce using rule 50 (primary -> atom .) SHORTSTRING reduce using rule 50 (primary -> atom .) LONGSTRING reduce using rule 50 (primary -> atom .) ` reduce using rule 50 (primary -> atom .) $end reduce using rule 50 (primary -> atom .) } reduce using rule 50 (primary -> atom .) ELSE reduce using rule 50 (primary -> atom .) DEFAULT reduce using rule 50 (primary -> atom .) CASE reduce using rule 50 (primary -> atom .) ) reduce using rule 50 (primary -> atom .) : reduce using rule 50 (primary -> atom .) ] reduce using rule 50 (primary -> atom .) { reduce using rule 50 (primary -> atom .) state 3 (134) compound_stmt -> funcdef . BREAK reduce using rule 134 (compound_stmt -> funcdef .) NEXT reduce using rule 134 (compound_stmt -> funcdef .) IF reduce using rule 134 (compound_stmt -> funcdef .) FOR reduce using rule 134 (compound_stmt -> funcdef .) WHERE reduce using rule 134 (compound_stmt -> funcdef .) SWITCH reduce using rule 134 (compound_stmt -> funcdef .) FUNCTION reduce using rule 134 (compound_stmt -> funcdef .) PRINT reduce using rule 134 (compound_stmt -> funcdef .) DO reduce using rule 134 (compound_stmt -> funcdef .) LOOP reduce using rule 134 (compound_stmt -> funcdef .) WITH reduce using rule 134 (compound_stmt -> funcdef .) ( reduce using rule 134 (compound_stmt -> funcdef .) [ reduce using rule 134 (compound_stmt -> funcdef .) ID reduce using rule 134 (compound_stmt -> funcdef .) ITEM_TAG reduce using rule 134 (compound_stmt -> funcdef .) INTEGER reduce using rule 134 (compound_stmt -> funcdef .) HEXINT reduce using rule 134 (compound_stmt -> funcdef .) OCTINT reduce using rule 134 (compound_stmt -> funcdef .) BININT reduce using rule 134 (compound_stmt -> funcdef .) REAL reduce using rule 134 (compound_stmt -> funcdef .) IMAGINARY reduce using rule 134 (compound_stmt -> funcdef .) STRPREFIX reduce using rule 134 (compound_stmt -> funcdef .) SHORTSTRING reduce using rule 134 (compound_stmt -> funcdef .) LONGSTRING reduce using rule 134 (compound_stmt -> funcdef .) ` reduce using rule 134 (compound_stmt -> funcdef .) $end reduce using rule 134 (compound_stmt -> funcdef .) } reduce using rule 134 (compound_stmt -> funcdef .) ELSE reduce using rule 134 (compound_stmt -> funcdef .) DEFAULT reduce using rule 134 (compound_stmt -> funcdef .) CASE reduce using rule 134 (compound_stmt -> funcdef .) state 4 (149) do_stmt -> do_stmt_head . suite (137) suite -> . simple_stmt (138) suite -> . compound_stmt (139) suite -> . open_brace statement_block close_brace (9) simple_stmt -> . assignment_stmt (10) simple_stmt -> . augmented_assignment_stmt (11) simple_stmt -> . fancy_drel_assignment_stmt (12) simple_stmt -> . print_stmt (13) simple_stmt -> . BREAK (14) simple_stmt -> . NEXT (127) compound_stmt -> . if_stmt (128) compound_stmt -> . for_stmt (129) compound_stmt -> . do_stmt (130) compound_stmt -> . loop_stmt (131) compound_stmt -> . with_stmt (132) compound_stmt -> . where_stmt (133) compound_stmt -> . switch_stmt (134) compound_stmt -> . funcdef (140) open_brace -> . { (124) assignment_stmt -> . target_list = expression_list (120) augmented_assignment_stmt -> . target AUGOP expression_list (121) fancy_drel_assignment_stmt -> . primary ( dotlist ) (15) print_stmt -> . PRINT expression (135) if_stmt -> . IF expression suite (136) if_stmt -> . if_stmt ELSE suite (144) for_stmt -> . FOR target_list IN expression_list suite (149) do_stmt -> . do_stmt_head suite (145) loop_stmt -> . loop_head suite (152) with_stmt -> . with_head suite (154) where_stmt -> . WHERE expression suite ELSE suite (155) switch_stmt -> . SWITCH ID open_brace caselist DEFAULT suite close_brace (158) funcdef -> . FUNCTION ID ( arglist ) suite (125) target_list -> . target (126) target_list -> . target_list , target (19) target -> . primary (20) target -> . ( target_list ) (21) target -> . [ target_list ] (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (150) do_stmt_head -> . DO ID = expression , expression (151) do_stmt_head -> . DO ID = expression , expression , expression (146) loop_head -> . LOOP ID AS ID (147) loop_head -> . LOOP ID AS ID : ID (148) loop_head -> . LOOP ID AS ID : ID comp_operator ID (153) with_head -> . WITH ID AS ID (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] BREAK shift and go to state 56 NEXT shift and go to state 7 { shift and go to state 69 PRINT shift and go to state 28 IF shift and go to state 61 FOR shift and go to state 30 WHERE shift and go to state 19 SWITCH shift and go to state 46 FUNCTION shift and go to state 36 ( shift and go to state 6 [ shift and go to state 38 DO shift and go to state 58 LOOP shift and go to state 25 WITH shift and go to state 5 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ` shift and go to state 20 fancy_drel_assignment_stmt shift and go to state 26 primary_att shift and go to state 41 atom shift and go to state 2 primary shift and go to state 42 stringliteral shift and go to state 23 item_tag shift and go to state 52 switch_stmt shift and go to state 43 do_stmt_head shift and go to state 4 enclosure shift and go to state 29 parenth_form shift and go to state 8 simple_stmt shift and go to state 66 literal shift and go to state 45 assignment_stmt shift and go to state 32 call shift and go to state 47 string_conversion shift and go to state 49 with_head shift and go to state 51 suite shift and go to state 65 loop_head shift and go to state 12 do_stmt shift and go to state 13 compound_stmt shift and go to state 67 attributeref shift and go to state 9 simple_slicing shift and go to state 37 print_stmt shift and go to state 50 loop_stmt shift and go to state 15 slicing shift and go to state 17 target_list shift and go to state 63 for_stmt shift and go to state 18 augmented_assignment_stmt shift and go to state 27 funcdef shift and go to state 3 target shift and go to state 54 if_stmt shift and go to state 21 extended_slicing shift and go to state 34 list_display shift and go to state 22 where_stmt shift and go to state 39 open_brace shift and go to state 68 with_stmt shift and go to state 24 subscription shift and go to state 53 state 5 (153) with_head -> WITH . ID AS ID ID shift and go to state 70 state 6 (20) target -> ( . target_list ) (75) parenth_form -> ( . expression_list ) (76) parenth_form -> ( . ) (125) target_list -> . target (126) target_list -> . target_list , target (16) expression_list -> . expression (17) expression_list -> . expression_list , expression (19) target -> . primary (20) target -> . ( target_list ) (21) target -> . [ target_list ] (18) expression -> . or_test (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (26) not_test -> . comparison (27) not_test -> . NOT not_test (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr ) shift and go to state 76 ( shift and go to state 6 [ shift and go to state 38 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 NOT shift and go to state 72 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ` shift and go to state 20 - shift and go to state 79 + shift and go to state 77 primary_att shift and go to state 41 primary shift and go to state 73 stringliteral shift and go to state 23 not_test shift and go to state 74 enclosure shift and go to state 29 power shift and go to state 75 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 simple_slicing shift and go to state 37 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 target_list shift and go to state 81 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 target shift and go to state 84 expression_list shift and go to state 85 list_display shift and go to state 22 or_test shift and go to state 86 expression shift and go to state 87 state 7 (14) simple_stmt -> NEXT . ; reduce using rule 14 (simple_stmt -> NEXT .) BREAK reduce using rule 14 (simple_stmt -> NEXT .) NEXT reduce using rule 14 (simple_stmt -> NEXT .) IF reduce using rule 14 (simple_stmt -> NEXT .) FOR reduce using rule 14 (simple_stmt -> NEXT .) WHERE reduce using rule 14 (simple_stmt -> NEXT .) SWITCH reduce using rule 14 (simple_stmt -> NEXT .) FUNCTION reduce using rule 14 (simple_stmt -> NEXT .) PRINT reduce using rule 14 (simple_stmt -> NEXT .) DO reduce using rule 14 (simple_stmt -> NEXT .) LOOP reduce using rule 14 (simple_stmt -> NEXT .) WITH reduce using rule 14 (simple_stmt -> NEXT .) ( reduce using rule 14 (simple_stmt -> NEXT .) [ reduce using rule 14 (simple_stmt -> NEXT .) ID reduce using rule 14 (simple_stmt -> NEXT .) ITEM_TAG reduce using rule 14 (simple_stmt -> NEXT .) INTEGER reduce using rule 14 (simple_stmt -> NEXT .) HEXINT reduce using rule 14 (simple_stmt -> NEXT .) OCTINT reduce using rule 14 (simple_stmt -> NEXT .) BININT reduce using rule 14 (simple_stmt -> NEXT .) REAL reduce using rule 14 (simple_stmt -> NEXT .) IMAGINARY reduce using rule 14 (simple_stmt -> NEXT .) STRPREFIX reduce using rule 14 (simple_stmt -> NEXT .) SHORTSTRING reduce using rule 14 (simple_stmt -> NEXT .) LONGSTRING reduce using rule 14 (simple_stmt -> NEXT .) ` reduce using rule 14 (simple_stmt -> NEXT .) $end reduce using rule 14 (simple_stmt -> NEXT .) } reduce using rule 14 (simple_stmt -> NEXT .) ELSE reduce using rule 14 (simple_stmt -> NEXT .) DEFAULT reduce using rule 14 (simple_stmt -> NEXT .) CASE reduce using rule 14 (simple_stmt -> NEXT .) state 8 (72) enclosure -> parenth_form . POWER reduce using rule 72 (enclosure -> parenth_form .) [ reduce using rule 72 (enclosure -> parenth_form .) ( reduce using rule 72 (enclosure -> parenth_form .) . reduce using rule 72 (enclosure -> parenth_form .) REAL reduce using rule 72 (enclosure -> parenth_form .) * reduce using rule 72 (enclosure -> parenth_form .) / reduce using rule 72 (enclosure -> parenth_form .) ^ reduce using rule 72 (enclosure -> parenth_form .) + reduce using rule 72 (enclosure -> parenth_form .) - reduce using rule 72 (enclosure -> parenth_form .) < reduce using rule 72 (enclosure -> parenth_form .) > reduce using rule 72 (enclosure -> parenth_form .) GTE reduce using rule 72 (enclosure -> parenth_form .) LTE reduce using rule 72 (enclosure -> parenth_form .) NEQ reduce using rule 72 (enclosure -> parenth_form .) ISEQUAL reduce using rule 72 (enclosure -> parenth_form .) IN reduce using rule 72 (enclosure -> parenth_form .) NOT reduce using rule 72 (enclosure -> parenth_form .) AND reduce using rule 72 (enclosure -> parenth_form .) OR reduce using rule 72 (enclosure -> parenth_form .) ) reduce using rule 72 (enclosure -> parenth_form .) , reduce using rule 72 (enclosure -> parenth_form .) BREAK reduce using rule 72 (enclosure -> parenth_form .) NEXT reduce using rule 72 (enclosure -> parenth_form .) { reduce using rule 72 (enclosure -> parenth_form .) PRINT reduce using rule 72 (enclosure -> parenth_form .) IF reduce using rule 72 (enclosure -> parenth_form .) FOR reduce using rule 72 (enclosure -> parenth_form .) WHERE reduce using rule 72 (enclosure -> parenth_form .) SWITCH reduce using rule 72 (enclosure -> parenth_form .) FUNCTION reduce using rule 72 (enclosure -> parenth_form .) DO reduce using rule 72 (enclosure -> parenth_form .) LOOP reduce using rule 72 (enclosure -> parenth_form .) WITH reduce using rule 72 (enclosure -> parenth_form .) ID reduce using rule 72 (enclosure -> parenth_form .) ITEM_TAG reduce using rule 72 (enclosure -> parenth_form .) INTEGER reduce using rule 72 (enclosure -> parenth_form .) HEXINT reduce using rule 72 (enclosure -> parenth_form .) OCTINT reduce using rule 72 (enclosure -> parenth_form .) BININT reduce using rule 72 (enclosure -> parenth_form .) IMAGINARY reduce using rule 72 (enclosure -> parenth_form .) STRPREFIX reduce using rule 72 (enclosure -> parenth_form .) SHORTSTRING reduce using rule 72 (enclosure -> parenth_form .) LONGSTRING reduce using rule 72 (enclosure -> parenth_form .) ` reduce using rule 72 (enclosure -> parenth_form .) ; reduce using rule 72 (enclosure -> parenth_form .) $end reduce using rule 72 (enclosure -> parenth_form .) } reduce using rule 72 (enclosure -> parenth_form .) ELSE reduce using rule 72 (enclosure -> parenth_form .) DEFAULT reduce using rule 72 (enclosure -> parenth_form .) CASE reduce using rule 72 (enclosure -> parenth_form .) ] reduce using rule 72 (enclosure -> parenth_form .) : reduce using rule 72 (enclosure -> parenth_form .) AUGOP reduce using rule 72 (enclosure -> parenth_form .) = reduce using rule 72 (enclosure -> parenth_form .) state 9 (55) primary_att -> attributeref . POWER reduce using rule 55 (primary_att -> attributeref .) [ reduce using rule 55 (primary_att -> attributeref .) ( reduce using rule 55 (primary_att -> attributeref .) . reduce using rule 55 (primary_att -> attributeref .) REAL reduce using rule 55 (primary_att -> attributeref .) * reduce using rule 55 (primary_att -> attributeref .) / reduce using rule 55 (primary_att -> attributeref .) ^ reduce using rule 55 (primary_att -> attributeref .) + reduce using rule 55 (primary_att -> attributeref .) - reduce using rule 55 (primary_att -> attributeref .) < reduce using rule 55 (primary_att -> attributeref .) > reduce using rule 55 (primary_att -> attributeref .) GTE reduce using rule 55 (primary_att -> attributeref .) LTE reduce using rule 55 (primary_att -> attributeref .) NEQ reduce using rule 55 (primary_att -> attributeref .) ISEQUAL reduce using rule 55 (primary_att -> attributeref .) IN reduce using rule 55 (primary_att -> attributeref .) NOT reduce using rule 55 (primary_att -> attributeref .) AND reduce using rule 55 (primary_att -> attributeref .) OR reduce using rule 55 (primary_att -> attributeref .) , reduce using rule 55 (primary_att -> attributeref .) BREAK reduce using rule 55 (primary_att -> attributeref .) NEXT reduce using rule 55 (primary_att -> attributeref .) { reduce using rule 55 (primary_att -> attributeref .) PRINT reduce using rule 55 (primary_att -> attributeref .) IF reduce using rule 55 (primary_att -> attributeref .) FOR reduce using rule 55 (primary_att -> attributeref .) WHERE reduce using rule 55 (primary_att -> attributeref .) SWITCH reduce using rule 55 (primary_att -> attributeref .) FUNCTION reduce using rule 55 (primary_att -> attributeref .) DO reduce using rule 55 (primary_att -> attributeref .) LOOP reduce using rule 55 (primary_att -> attributeref .) WITH reduce using rule 55 (primary_att -> attributeref .) ID reduce using rule 55 (primary_att -> attributeref .) ITEM_TAG reduce using rule 55 (primary_att -> attributeref .) INTEGER reduce using rule 55 (primary_att -> attributeref .) HEXINT reduce using rule 55 (primary_att -> attributeref .) OCTINT reduce using rule 55 (primary_att -> attributeref .) BININT reduce using rule 55 (primary_att -> attributeref .) IMAGINARY reduce using rule 55 (primary_att -> attributeref .) STRPREFIX reduce using rule 55 (primary_att -> attributeref .) SHORTSTRING reduce using rule 55 (primary_att -> attributeref .) LONGSTRING reduce using rule 55 (primary_att -> attributeref .) ` reduce using rule 55 (primary_att -> attributeref .) AUGOP reduce using rule 55 (primary_att -> attributeref .) = reduce using rule 55 (primary_att -> attributeref .) ; reduce using rule 55 (primary_att -> attributeref .) $end reduce using rule 55 (primary_att -> attributeref .) } reduce using rule 55 (primary_att -> attributeref .) ELSE reduce using rule 55 (primary_att -> attributeref .) DEFAULT reduce using rule 55 (primary_att -> attributeref .) CASE reduce using rule 55 (primary_att -> attributeref .) ] reduce using rule 55 (primary_att -> attributeref .) ) reduce using rule 55 (primary_att -> attributeref .) : reduce using rule 55 (primary_att -> attributeref .) state 10 (68) stringliteral -> STRPREFIX . SHORTSTRING (69) stringliteral -> STRPREFIX . LONGSTRING SHORTSTRING shift and go to state 88 LONGSTRING shift and go to state 89 state 11 (1) final_input -> input . (3) input -> input . statement (4) statement -> . stmt_list (5) statement -> . compound_stmt (6) stmt_list -> . simple_stmt (7) stmt_list -> . stmt_list ; simple_stmt (8) stmt_list -> . stmt_list ; simple_stmt ; (127) compound_stmt -> . if_stmt (128) compound_stmt -> . for_stmt (129) compound_stmt -> . do_stmt (130) compound_stmt -> . loop_stmt (131) compound_stmt -> . with_stmt (132) compound_stmt -> . where_stmt (133) compound_stmt -> . switch_stmt (134) compound_stmt -> . funcdef (9) simple_stmt -> . assignment_stmt (10) simple_stmt -> . augmented_assignment_stmt (11) simple_stmt -> . fancy_drel_assignment_stmt (12) simple_stmt -> . print_stmt (13) simple_stmt -> . BREAK (14) simple_stmt -> . NEXT (135) if_stmt -> . IF expression suite (136) if_stmt -> . if_stmt ELSE suite (144) for_stmt -> . FOR target_list IN expression_list suite (149) do_stmt -> . do_stmt_head suite (145) loop_stmt -> . loop_head suite (152) with_stmt -> . with_head suite (154) where_stmt -> . WHERE expression suite ELSE suite (155) switch_stmt -> . SWITCH ID open_brace caselist DEFAULT suite close_brace (158) funcdef -> . FUNCTION ID ( arglist ) suite (124) assignment_stmt -> . target_list = expression_list (120) augmented_assignment_stmt -> . target AUGOP expression_list (121) fancy_drel_assignment_stmt -> . primary ( dotlist ) (15) print_stmt -> . PRINT expression (150) do_stmt_head -> . DO ID = expression , expression (151) do_stmt_head -> . DO ID = expression , expression , expression (146) loop_head -> . LOOP ID AS ID (147) loop_head -> . LOOP ID AS ID : ID (148) loop_head -> . LOOP ID AS ID : ID comp_operator ID (153) with_head -> . WITH ID AS ID (125) target_list -> . target (126) target_list -> . target_list , target (19) target -> . primary (20) target -> . ( target_list ) (21) target -> . [ target_list ] (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] $end reduce using rule 1 (final_input -> input .) BREAK shift and go to state 56 NEXT shift and go to state 7 IF shift and go to state 61 FOR shift and go to state 30 WHERE shift and go to state 19 SWITCH shift and go to state 46 FUNCTION shift and go to state 36 PRINT shift and go to state 28 DO shift and go to state 58 LOOP shift and go to state 25 WITH shift and go to state 5 ( shift and go to state 6 [ shift and go to state 38 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ` shift and go to state 20 fancy_drel_assignment_stmt shift and go to state 26 primary_att shift and go to state 41 primary shift and go to state 42 augmented_assignment_stmt shift and go to state 27 stringliteral shift and go to state 23 item_tag shift and go to state 52 switch_stmt shift and go to state 43 do_stmt_head shift and go to state 4 enclosure shift and go to state 29 subscription shift and go to state 53 parenth_form shift and go to state 8 print_stmt shift and go to state 50 literal shift and go to state 45 assignment_stmt shift and go to state 32 call shift and go to state 47 statement shift and go to state 90 string_conversion shift and go to state 49 with_head shift and go to state 51 loop_head shift and go to state 12 do_stmt shift and go to state 13 compound_stmt shift and go to state 35 attributeref shift and go to state 9 simple_slicing shift and go to state 37 simple_stmt shift and go to state 14 loop_stmt shift and go to state 15 slicing shift and go to state 17 target_list shift and go to state 63 for_stmt shift and go to state 18 funcdef shift and go to state 3 target shift and go to state 54 stmt_list shift and go to state 62 if_stmt shift and go to state 21 extended_slicing shift and go to state 34 list_display shift and go to state 22 where_stmt shift and go to state 39 with_stmt shift and go to state 24 atom shift and go to state 2 state 12 (145) loop_stmt -> loop_head . suite (137) suite -> . simple_stmt (138) suite -> . compound_stmt (139) suite -> . open_brace statement_block close_brace (9) simple_stmt -> . assignment_stmt (10) simple_stmt -> . augmented_assignment_stmt (11) simple_stmt -> . fancy_drel_assignment_stmt (12) simple_stmt -> . print_stmt (13) simple_stmt -> . BREAK (14) simple_stmt -> . NEXT (127) compound_stmt -> . if_stmt (128) compound_stmt -> . for_stmt (129) compound_stmt -> . do_stmt (130) compound_stmt -> . loop_stmt (131) compound_stmt -> . with_stmt (132) compound_stmt -> . where_stmt (133) compound_stmt -> . switch_stmt (134) compound_stmt -> . funcdef (140) open_brace -> . { (124) assignment_stmt -> . target_list = expression_list (120) augmented_assignment_stmt -> . target AUGOP expression_list (121) fancy_drel_assignment_stmt -> . primary ( dotlist ) (15) print_stmt -> . PRINT expression (135) if_stmt -> . IF expression suite (136) if_stmt -> . if_stmt ELSE suite (144) for_stmt -> . FOR target_list IN expression_list suite (149) do_stmt -> . do_stmt_head suite (145) loop_stmt -> . loop_head suite (152) with_stmt -> . with_head suite (154) where_stmt -> . WHERE expression suite ELSE suite (155) switch_stmt -> . SWITCH ID open_brace caselist DEFAULT suite close_brace (158) funcdef -> . FUNCTION ID ( arglist ) suite (125) target_list -> . target (126) target_list -> . target_list , target (19) target -> . primary (20) target -> . ( target_list ) (21) target -> . [ target_list ] (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (150) do_stmt_head -> . DO ID = expression , expression (151) do_stmt_head -> . DO ID = expression , expression , expression (146) loop_head -> . LOOP ID AS ID (147) loop_head -> . LOOP ID AS ID : ID (148) loop_head -> . LOOP ID AS ID : ID comp_operator ID (153) with_head -> . WITH ID AS ID (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] BREAK shift and go to state 56 NEXT shift and go to state 7 { shift and go to state 69 PRINT shift and go to state 28 IF shift and go to state 61 FOR shift and go to state 30 WHERE shift and go to state 19 SWITCH shift and go to state 46 FUNCTION shift and go to state 36 ( shift and go to state 6 [ shift and go to state 38 DO shift and go to state 58 LOOP shift and go to state 25 WITH shift and go to state 5 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ` shift and go to state 20 fancy_drel_assignment_stmt shift and go to state 26 primary_att shift and go to state 41 atom shift and go to state 2 primary shift and go to state 42 stringliteral shift and go to state 23 item_tag shift and go to state 52 switch_stmt shift and go to state 43 do_stmt_head shift and go to state 4 enclosure shift and go to state 29 parenth_form shift and go to state 8 simple_stmt shift and go to state 66 literal shift and go to state 45 assignment_stmt shift and go to state 32 call shift and go to state 47 string_conversion shift and go to state 49 with_head shift and go to state 51 suite shift and go to state 91 loop_head shift and go to state 12 do_stmt shift and go to state 13 compound_stmt shift and go to state 67 attributeref shift and go to state 9 simple_slicing shift and go to state 37 print_stmt shift and go to state 50 loop_stmt shift and go to state 15 slicing shift and go to state 17 target_list shift and go to state 63 for_stmt shift and go to state 18 augmented_assignment_stmt shift and go to state 27 funcdef shift and go to state 3 target shift and go to state 54 if_stmt shift and go to state 21 extended_slicing shift and go to state 34 list_display shift and go to state 22 where_stmt shift and go to state 39 open_brace shift and go to state 68 with_stmt shift and go to state 24 subscription shift and go to state 53 state 13 (129) compound_stmt -> do_stmt . BREAK reduce using rule 129 (compound_stmt -> do_stmt .) NEXT reduce using rule 129 (compound_stmt -> do_stmt .) IF reduce using rule 129 (compound_stmt -> do_stmt .) FOR reduce using rule 129 (compound_stmt -> do_stmt .) WHERE reduce using rule 129 (compound_stmt -> do_stmt .) SWITCH reduce using rule 129 (compound_stmt -> do_stmt .) FUNCTION reduce using rule 129 (compound_stmt -> do_stmt .) PRINT reduce using rule 129 (compound_stmt -> do_stmt .) DO reduce using rule 129 (compound_stmt -> do_stmt .) LOOP reduce using rule 129 (compound_stmt -> do_stmt .) WITH reduce using rule 129 (compound_stmt -> do_stmt .) ( reduce using rule 129 (compound_stmt -> do_stmt .) [ reduce using rule 129 (compound_stmt -> do_stmt .) ID reduce using rule 129 (compound_stmt -> do_stmt .) ITEM_TAG reduce using rule 129 (compound_stmt -> do_stmt .) INTEGER reduce using rule 129 (compound_stmt -> do_stmt .) HEXINT reduce using rule 129 (compound_stmt -> do_stmt .) OCTINT reduce using rule 129 (compound_stmt -> do_stmt .) BININT reduce using rule 129 (compound_stmt -> do_stmt .) REAL reduce using rule 129 (compound_stmt -> do_stmt .) IMAGINARY reduce using rule 129 (compound_stmt -> do_stmt .) STRPREFIX reduce using rule 129 (compound_stmt -> do_stmt .) SHORTSTRING reduce using rule 129 (compound_stmt -> do_stmt .) LONGSTRING reduce using rule 129 (compound_stmt -> do_stmt .) ` reduce using rule 129 (compound_stmt -> do_stmt .) $end reduce using rule 129 (compound_stmt -> do_stmt .) } reduce using rule 129 (compound_stmt -> do_stmt .) ELSE reduce using rule 129 (compound_stmt -> do_stmt .) DEFAULT reduce using rule 129 (compound_stmt -> do_stmt .) CASE reduce using rule 129 (compound_stmt -> do_stmt .) state 14 (6) stmt_list -> simple_stmt . ; reduce using rule 6 (stmt_list -> simple_stmt .) } reduce using rule 6 (stmt_list -> simple_stmt .) BREAK reduce using rule 6 (stmt_list -> simple_stmt .) NEXT reduce using rule 6 (stmt_list -> simple_stmt .) IF reduce using rule 6 (stmt_list -> simple_stmt .) FOR reduce using rule 6 (stmt_list -> simple_stmt .) WHERE reduce using rule 6 (stmt_list -> simple_stmt .) SWITCH reduce using rule 6 (stmt_list -> simple_stmt .) FUNCTION reduce using rule 6 (stmt_list -> simple_stmt .) PRINT reduce using rule 6 (stmt_list -> simple_stmt .) DO reduce using rule 6 (stmt_list -> simple_stmt .) LOOP reduce using rule 6 (stmt_list -> simple_stmt .) WITH reduce using rule 6 (stmt_list -> simple_stmt .) ( reduce using rule 6 (stmt_list -> simple_stmt .) [ reduce using rule 6 (stmt_list -> simple_stmt .) ID reduce using rule 6 (stmt_list -> simple_stmt .) ITEM_TAG reduce using rule 6 (stmt_list -> simple_stmt .) INTEGER reduce using rule 6 (stmt_list -> simple_stmt .) HEXINT reduce using rule 6 (stmt_list -> simple_stmt .) OCTINT reduce using rule 6 (stmt_list -> simple_stmt .) BININT reduce using rule 6 (stmt_list -> simple_stmt .) REAL reduce using rule 6 (stmt_list -> simple_stmt .) IMAGINARY reduce using rule 6 (stmt_list -> simple_stmt .) STRPREFIX reduce using rule 6 (stmt_list -> simple_stmt .) SHORTSTRING reduce using rule 6 (stmt_list -> simple_stmt .) LONGSTRING reduce using rule 6 (stmt_list -> simple_stmt .) ` reduce using rule 6 (stmt_list -> simple_stmt .) $end reduce using rule 6 (stmt_list -> simple_stmt .) state 15 (130) compound_stmt -> loop_stmt . BREAK reduce using rule 130 (compound_stmt -> loop_stmt .) NEXT reduce using rule 130 (compound_stmt -> loop_stmt .) IF reduce using rule 130 (compound_stmt -> loop_stmt .) FOR reduce using rule 130 (compound_stmt -> loop_stmt .) WHERE reduce using rule 130 (compound_stmt -> loop_stmt .) SWITCH reduce using rule 130 (compound_stmt -> loop_stmt .) FUNCTION reduce using rule 130 (compound_stmt -> loop_stmt .) PRINT reduce using rule 130 (compound_stmt -> loop_stmt .) DO reduce using rule 130 (compound_stmt -> loop_stmt .) LOOP reduce using rule 130 (compound_stmt -> loop_stmt .) WITH reduce using rule 130 (compound_stmt -> loop_stmt .) ( reduce using rule 130 (compound_stmt -> loop_stmt .) [ reduce using rule 130 (compound_stmt -> loop_stmt .) ID reduce using rule 130 (compound_stmt -> loop_stmt .) ITEM_TAG reduce using rule 130 (compound_stmt -> loop_stmt .) INTEGER reduce using rule 130 (compound_stmt -> loop_stmt .) HEXINT reduce using rule 130 (compound_stmt -> loop_stmt .) OCTINT reduce using rule 130 (compound_stmt -> loop_stmt .) BININT reduce using rule 130 (compound_stmt -> loop_stmt .) REAL reduce using rule 130 (compound_stmt -> loop_stmt .) IMAGINARY reduce using rule 130 (compound_stmt -> loop_stmt .) STRPREFIX reduce using rule 130 (compound_stmt -> loop_stmt .) SHORTSTRING reduce using rule 130 (compound_stmt -> loop_stmt .) LONGSTRING reduce using rule 130 (compound_stmt -> loop_stmt .) ` reduce using rule 130 (compound_stmt -> loop_stmt .) $end reduce using rule 130 (compound_stmt -> loop_stmt .) } reduce using rule 130 (compound_stmt -> loop_stmt .) ELSE reduce using rule 130 (compound_stmt -> loop_stmt .) DEFAULT reduce using rule 130 (compound_stmt -> loop_stmt .) CASE reduce using rule 130 (compound_stmt -> loop_stmt .) state 16 (71) stringliteral -> LONGSTRING . POWER reduce using rule 71 (stringliteral -> LONGSTRING .) [ reduce using rule 71 (stringliteral -> LONGSTRING .) ( reduce using rule 71 (stringliteral -> LONGSTRING .) . reduce using rule 71 (stringliteral -> LONGSTRING .) REAL reduce using rule 71 (stringliteral -> LONGSTRING .) * reduce using rule 71 (stringliteral -> LONGSTRING .) / reduce using rule 71 (stringliteral -> LONGSTRING .) ^ reduce using rule 71 (stringliteral -> LONGSTRING .) + reduce using rule 71 (stringliteral -> LONGSTRING .) - reduce using rule 71 (stringliteral -> LONGSTRING .) < reduce using rule 71 (stringliteral -> LONGSTRING .) > reduce using rule 71 (stringliteral -> LONGSTRING .) GTE reduce using rule 71 (stringliteral -> LONGSTRING .) LTE reduce using rule 71 (stringliteral -> LONGSTRING .) NEQ reduce using rule 71 (stringliteral -> LONGSTRING .) ISEQUAL reduce using rule 71 (stringliteral -> LONGSTRING .) IN reduce using rule 71 (stringliteral -> LONGSTRING .) NOT reduce using rule 71 (stringliteral -> LONGSTRING .) AND reduce using rule 71 (stringliteral -> LONGSTRING .) OR reduce using rule 71 (stringliteral -> LONGSTRING .) ) reduce using rule 71 (stringliteral -> LONGSTRING .) , reduce using rule 71 (stringliteral -> LONGSTRING .) BREAK reduce using rule 71 (stringliteral -> LONGSTRING .) NEXT reduce using rule 71 (stringliteral -> LONGSTRING .) { reduce using rule 71 (stringliteral -> LONGSTRING .) PRINT reduce using rule 71 (stringliteral -> LONGSTRING .) IF reduce using rule 71 (stringliteral -> LONGSTRING .) FOR reduce using rule 71 (stringliteral -> LONGSTRING .) WHERE reduce using rule 71 (stringliteral -> LONGSTRING .) SWITCH reduce using rule 71 (stringliteral -> LONGSTRING .) FUNCTION reduce using rule 71 (stringliteral -> LONGSTRING .) DO reduce using rule 71 (stringliteral -> LONGSTRING .) LOOP reduce using rule 71 (stringliteral -> LONGSTRING .) WITH reduce using rule 71 (stringliteral -> LONGSTRING .) ID reduce using rule 71 (stringliteral -> LONGSTRING .) ITEM_TAG reduce using rule 71 (stringliteral -> LONGSTRING .) INTEGER reduce using rule 71 (stringliteral -> LONGSTRING .) HEXINT reduce using rule 71 (stringliteral -> LONGSTRING .) OCTINT reduce using rule 71 (stringliteral -> LONGSTRING .) BININT reduce using rule 71 (stringliteral -> LONGSTRING .) IMAGINARY reduce using rule 71 (stringliteral -> LONGSTRING .) STRPREFIX reduce using rule 71 (stringliteral -> LONGSTRING .) SHORTSTRING reduce using rule 71 (stringliteral -> LONGSTRING .) LONGSTRING reduce using rule 71 (stringliteral -> LONGSTRING .) ` reduce using rule 71 (stringliteral -> LONGSTRING .) ; reduce using rule 71 (stringliteral -> LONGSTRING .) $end reduce using rule 71 (stringliteral -> LONGSTRING .) } reduce using rule 71 (stringliteral -> LONGSTRING .) ELSE reduce using rule 71 (stringliteral -> LONGSTRING .) DEFAULT reduce using rule 71 (stringliteral -> LONGSTRING .) CASE reduce using rule 71 (stringliteral -> LONGSTRING .) ] reduce using rule 71 (stringliteral -> LONGSTRING .) : reduce using rule 71 (stringliteral -> LONGSTRING .) AUGOP reduce using rule 71 (stringliteral -> LONGSTRING .) = reduce using rule 71 (stringliteral -> LONGSTRING .) state 17 (53) primary -> slicing . ( reduce using rule 53 (primary -> slicing .) [ reduce using rule 53 (primary -> slicing .) . reduce using rule 53 (primary -> slicing .) REAL reduce using rule 53 (primary -> slicing .) AUGOP reduce using rule 53 (primary -> slicing .) = reduce using rule 53 (primary -> slicing .) , reduce using rule 53 (primary -> slicing .) POWER reduce using rule 53 (primary -> slicing .) * reduce using rule 53 (primary -> slicing .) / reduce using rule 53 (primary -> slicing .) ^ reduce using rule 53 (primary -> slicing .) + reduce using rule 53 (primary -> slicing .) - reduce using rule 53 (primary -> slicing .) < reduce using rule 53 (primary -> slicing .) > reduce using rule 53 (primary -> slicing .) GTE reduce using rule 53 (primary -> slicing .) LTE reduce using rule 53 (primary -> slicing .) NEQ reduce using rule 53 (primary -> slicing .) ISEQUAL reduce using rule 53 (primary -> slicing .) IN reduce using rule 53 (primary -> slicing .) NOT reduce using rule 53 (primary -> slicing .) AND reduce using rule 53 (primary -> slicing .) OR reduce using rule 53 (primary -> slicing .) ; reduce using rule 53 (primary -> slicing .) BREAK reduce using rule 53 (primary -> slicing .) NEXT reduce using rule 53 (primary -> slicing .) IF reduce using rule 53 (primary -> slicing .) FOR reduce using rule 53 (primary -> slicing .) WHERE reduce using rule 53 (primary -> slicing .) SWITCH reduce using rule 53 (primary -> slicing .) FUNCTION reduce using rule 53 (primary -> slicing .) PRINT reduce using rule 53 (primary -> slicing .) DO reduce using rule 53 (primary -> slicing .) LOOP reduce using rule 53 (primary -> slicing .) WITH reduce using rule 53 (primary -> slicing .) ID reduce using rule 53 (primary -> slicing .) ITEM_TAG reduce using rule 53 (primary -> slicing .) INTEGER reduce using rule 53 (primary -> slicing .) HEXINT reduce using rule 53 (primary -> slicing .) OCTINT reduce using rule 53 (primary -> slicing .) BININT reduce using rule 53 (primary -> slicing .) IMAGINARY reduce using rule 53 (primary -> slicing .) STRPREFIX reduce using rule 53 (primary -> slicing .) SHORTSTRING reduce using rule 53 (primary -> slicing .) LONGSTRING reduce using rule 53 (primary -> slicing .) ` reduce using rule 53 (primary -> slicing .) $end reduce using rule 53 (primary -> slicing .) } reduce using rule 53 (primary -> slicing .) ELSE reduce using rule 53 (primary -> slicing .) DEFAULT reduce using rule 53 (primary -> slicing .) CASE reduce using rule 53 (primary -> slicing .) ) reduce using rule 53 (primary -> slicing .) : reduce using rule 53 (primary -> slicing .) ] reduce using rule 53 (primary -> slicing .) { reduce using rule 53 (primary -> slicing .) state 18 (128) compound_stmt -> for_stmt . BREAK reduce using rule 128 (compound_stmt -> for_stmt .) NEXT reduce using rule 128 (compound_stmt -> for_stmt .) IF reduce using rule 128 (compound_stmt -> for_stmt .) FOR reduce using rule 128 (compound_stmt -> for_stmt .) WHERE reduce using rule 128 (compound_stmt -> for_stmt .) SWITCH reduce using rule 128 (compound_stmt -> for_stmt .) FUNCTION reduce using rule 128 (compound_stmt -> for_stmt .) PRINT reduce using rule 128 (compound_stmt -> for_stmt .) DO reduce using rule 128 (compound_stmt -> for_stmt .) LOOP reduce using rule 128 (compound_stmt -> for_stmt .) WITH reduce using rule 128 (compound_stmt -> for_stmt .) ( reduce using rule 128 (compound_stmt -> for_stmt .) [ reduce using rule 128 (compound_stmt -> for_stmt .) ID reduce using rule 128 (compound_stmt -> for_stmt .) ITEM_TAG reduce using rule 128 (compound_stmt -> for_stmt .) INTEGER reduce using rule 128 (compound_stmt -> for_stmt .) HEXINT reduce using rule 128 (compound_stmt -> for_stmt .) OCTINT reduce using rule 128 (compound_stmt -> for_stmt .) BININT reduce using rule 128 (compound_stmt -> for_stmt .) REAL reduce using rule 128 (compound_stmt -> for_stmt .) IMAGINARY reduce using rule 128 (compound_stmt -> for_stmt .) STRPREFIX reduce using rule 128 (compound_stmt -> for_stmt .) SHORTSTRING reduce using rule 128 (compound_stmt -> for_stmt .) LONGSTRING reduce using rule 128 (compound_stmt -> for_stmt .) ` reduce using rule 128 (compound_stmt -> for_stmt .) $end reduce using rule 128 (compound_stmt -> for_stmt .) } reduce using rule 128 (compound_stmt -> for_stmt .) ELSE reduce using rule 128 (compound_stmt -> for_stmt .) DEFAULT reduce using rule 128 (compound_stmt -> for_stmt .) CASE reduce using rule 128 (compound_stmt -> for_stmt .) state 19 (154) where_stmt -> WHERE . expression suite ELSE suite (18) expression -> . or_test (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 extended_slicing shift and go to state 34 list_display shift and go to state 22 or_test shift and go to state 86 expression shift and go to state 95 state 20 (77) string_conversion -> ` . expression_list ` (16) expression_list -> . expression (17) expression_list -> . expression_list , expression (18) expression -> . or_test (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 expression_list shift and go to state 96 list_display shift and go to state 22 or_test shift and go to state 86 expression shift and go to state 87 state 21 (127) compound_stmt -> if_stmt . (136) if_stmt -> if_stmt . ELSE suite ! shift/reduce conflict for ELSE resolved as shift BREAK reduce using rule 127 (compound_stmt -> if_stmt .) NEXT reduce using rule 127 (compound_stmt -> if_stmt .) IF reduce using rule 127 (compound_stmt -> if_stmt .) FOR reduce using rule 127 (compound_stmt -> if_stmt .) WHERE reduce using rule 127 (compound_stmt -> if_stmt .) SWITCH reduce using rule 127 (compound_stmt -> if_stmt .) FUNCTION reduce using rule 127 (compound_stmt -> if_stmt .) PRINT reduce using rule 127 (compound_stmt -> if_stmt .) DO reduce using rule 127 (compound_stmt -> if_stmt .) LOOP reduce using rule 127 (compound_stmt -> if_stmt .) WITH reduce using rule 127 (compound_stmt -> if_stmt .) ( reduce using rule 127 (compound_stmt -> if_stmt .) [ reduce using rule 127 (compound_stmt -> if_stmt .) ID reduce using rule 127 (compound_stmt -> if_stmt .) ITEM_TAG reduce using rule 127 (compound_stmt -> if_stmt .) INTEGER reduce using rule 127 (compound_stmt -> if_stmt .) HEXINT reduce using rule 127 (compound_stmt -> if_stmt .) OCTINT reduce using rule 127 (compound_stmt -> if_stmt .) BININT reduce using rule 127 (compound_stmt -> if_stmt .) REAL reduce using rule 127 (compound_stmt -> if_stmt .) IMAGINARY reduce using rule 127 (compound_stmt -> if_stmt .) STRPREFIX reduce using rule 127 (compound_stmt -> if_stmt .) SHORTSTRING reduce using rule 127 (compound_stmt -> if_stmt .) LONGSTRING reduce using rule 127 (compound_stmt -> if_stmt .) ` reduce using rule 127 (compound_stmt -> if_stmt .) $end reduce using rule 127 (compound_stmt -> if_stmt .) } reduce using rule 127 (compound_stmt -> if_stmt .) DEFAULT reduce using rule 127 (compound_stmt -> if_stmt .) CASE reduce using rule 127 (compound_stmt -> if_stmt .) ELSE shift and go to state 97 ! ELSE [ reduce using rule 127 (compound_stmt -> if_stmt .) ] state 22 (74) enclosure -> list_display . POWER reduce using rule 74 (enclosure -> list_display .) [ reduce using rule 74 (enclosure -> list_display .) ( reduce using rule 74 (enclosure -> list_display .) . reduce using rule 74 (enclosure -> list_display .) REAL reduce using rule 74 (enclosure -> list_display .) * reduce using rule 74 (enclosure -> list_display .) / reduce using rule 74 (enclosure -> list_display .) ^ reduce using rule 74 (enclosure -> list_display .) + reduce using rule 74 (enclosure -> list_display .) - reduce using rule 74 (enclosure -> list_display .) < reduce using rule 74 (enclosure -> list_display .) > reduce using rule 74 (enclosure -> list_display .) GTE reduce using rule 74 (enclosure -> list_display .) LTE reduce using rule 74 (enclosure -> list_display .) NEQ reduce using rule 74 (enclosure -> list_display .) ISEQUAL reduce using rule 74 (enclosure -> list_display .) IN reduce using rule 74 (enclosure -> list_display .) NOT reduce using rule 74 (enclosure -> list_display .) AND reduce using rule 74 (enclosure -> list_display .) OR reduce using rule 74 (enclosure -> list_display .) ) reduce using rule 74 (enclosure -> list_display .) , reduce using rule 74 (enclosure -> list_display .) BREAK reduce using rule 74 (enclosure -> list_display .) NEXT reduce using rule 74 (enclosure -> list_display .) { reduce using rule 74 (enclosure -> list_display .) PRINT reduce using rule 74 (enclosure -> list_display .) IF reduce using rule 74 (enclosure -> list_display .) FOR reduce using rule 74 (enclosure -> list_display .) WHERE reduce using rule 74 (enclosure -> list_display .) SWITCH reduce using rule 74 (enclosure -> list_display .) FUNCTION reduce using rule 74 (enclosure -> list_display .) DO reduce using rule 74 (enclosure -> list_display .) LOOP reduce using rule 74 (enclosure -> list_display .) WITH reduce using rule 74 (enclosure -> list_display .) ID reduce using rule 74 (enclosure -> list_display .) ITEM_TAG reduce using rule 74 (enclosure -> list_display .) INTEGER reduce using rule 74 (enclosure -> list_display .) HEXINT reduce using rule 74 (enclosure -> list_display .) OCTINT reduce using rule 74 (enclosure -> list_display .) BININT reduce using rule 74 (enclosure -> list_display .) IMAGINARY reduce using rule 74 (enclosure -> list_display .) STRPREFIX reduce using rule 74 (enclosure -> list_display .) SHORTSTRING reduce using rule 74 (enclosure -> list_display .) LONGSTRING reduce using rule 74 (enclosure -> list_display .) ` reduce using rule 74 (enclosure -> list_display .) ; reduce using rule 74 (enclosure -> list_display .) $end reduce using rule 74 (enclosure -> list_display .) } reduce using rule 74 (enclosure -> list_display .) ELSE reduce using rule 74 (enclosure -> list_display .) DEFAULT reduce using rule 74 (enclosure -> list_display .) CASE reduce using rule 74 (enclosure -> list_display .) ] reduce using rule 74 (enclosure -> list_display .) : reduce using rule 74 (enclosure -> list_display .) AUGOP reduce using rule 74 (enclosure -> list_display .) = reduce using rule 74 (enclosure -> list_display .) state 23 (61) literal -> stringliteral . POWER reduce using rule 61 (literal -> stringliteral .) [ reduce using rule 61 (literal -> stringliteral .) ( reduce using rule 61 (literal -> stringliteral .) . reduce using rule 61 (literal -> stringliteral .) REAL reduce using rule 61 (literal -> stringliteral .) * reduce using rule 61 (literal -> stringliteral .) / reduce using rule 61 (literal -> stringliteral .) ^ reduce using rule 61 (literal -> stringliteral .) + reduce using rule 61 (literal -> stringliteral .) - reduce using rule 61 (literal -> stringliteral .) < reduce using rule 61 (literal -> stringliteral .) > reduce using rule 61 (literal -> stringliteral .) GTE reduce using rule 61 (literal -> stringliteral .) LTE reduce using rule 61 (literal -> stringliteral .) NEQ reduce using rule 61 (literal -> stringliteral .) ISEQUAL reduce using rule 61 (literal -> stringliteral .) IN reduce using rule 61 (literal -> stringliteral .) NOT reduce using rule 61 (literal -> stringliteral .) AND reduce using rule 61 (literal -> stringliteral .) OR reduce using rule 61 (literal -> stringliteral .) ] reduce using rule 61 (literal -> stringliteral .) : reduce using rule 61 (literal -> stringliteral .) , reduce using rule 61 (literal -> stringliteral .) AUGOP reduce using rule 61 (literal -> stringliteral .) = reduce using rule 61 (literal -> stringliteral .) ) reduce using rule 61 (literal -> stringliteral .) BREAK reduce using rule 61 (literal -> stringliteral .) NEXT reduce using rule 61 (literal -> stringliteral .) { reduce using rule 61 (literal -> stringliteral .) PRINT reduce using rule 61 (literal -> stringliteral .) IF reduce using rule 61 (literal -> stringliteral .) FOR reduce using rule 61 (literal -> stringliteral .) WHERE reduce using rule 61 (literal -> stringliteral .) SWITCH reduce using rule 61 (literal -> stringliteral .) FUNCTION reduce using rule 61 (literal -> stringliteral .) DO reduce using rule 61 (literal -> stringliteral .) LOOP reduce using rule 61 (literal -> stringliteral .) WITH reduce using rule 61 (literal -> stringliteral .) ID reduce using rule 61 (literal -> stringliteral .) ITEM_TAG reduce using rule 61 (literal -> stringliteral .) INTEGER reduce using rule 61 (literal -> stringliteral .) HEXINT reduce using rule 61 (literal -> stringliteral .) OCTINT reduce using rule 61 (literal -> stringliteral .) BININT reduce using rule 61 (literal -> stringliteral .) IMAGINARY reduce using rule 61 (literal -> stringliteral .) STRPREFIX reduce using rule 61 (literal -> stringliteral .) SHORTSTRING reduce using rule 61 (literal -> stringliteral .) LONGSTRING reduce using rule 61 (literal -> stringliteral .) ` reduce using rule 61 (literal -> stringliteral .) ; reduce using rule 61 (literal -> stringliteral .) $end reduce using rule 61 (literal -> stringliteral .) } reduce using rule 61 (literal -> stringliteral .) ELSE reduce using rule 61 (literal -> stringliteral .) DEFAULT reduce using rule 61 (literal -> stringliteral .) CASE reduce using rule 61 (literal -> stringliteral .) state 24 (131) compound_stmt -> with_stmt . BREAK reduce using rule 131 (compound_stmt -> with_stmt .) NEXT reduce using rule 131 (compound_stmt -> with_stmt .) IF reduce using rule 131 (compound_stmt -> with_stmt .) FOR reduce using rule 131 (compound_stmt -> with_stmt .) WHERE reduce using rule 131 (compound_stmt -> with_stmt .) SWITCH reduce using rule 131 (compound_stmt -> with_stmt .) FUNCTION reduce using rule 131 (compound_stmt -> with_stmt .) PRINT reduce using rule 131 (compound_stmt -> with_stmt .) DO reduce using rule 131 (compound_stmt -> with_stmt .) LOOP reduce using rule 131 (compound_stmt -> with_stmt .) WITH reduce using rule 131 (compound_stmt -> with_stmt .) ( reduce using rule 131 (compound_stmt -> with_stmt .) [ reduce using rule 131 (compound_stmt -> with_stmt .) ID reduce using rule 131 (compound_stmt -> with_stmt .) ITEM_TAG reduce using rule 131 (compound_stmt -> with_stmt .) INTEGER reduce using rule 131 (compound_stmt -> with_stmt .) HEXINT reduce using rule 131 (compound_stmt -> with_stmt .) OCTINT reduce using rule 131 (compound_stmt -> with_stmt .) BININT reduce using rule 131 (compound_stmt -> with_stmt .) REAL reduce using rule 131 (compound_stmt -> with_stmt .) IMAGINARY reduce using rule 131 (compound_stmt -> with_stmt .) STRPREFIX reduce using rule 131 (compound_stmt -> with_stmt .) SHORTSTRING reduce using rule 131 (compound_stmt -> with_stmt .) LONGSTRING reduce using rule 131 (compound_stmt -> with_stmt .) ` reduce using rule 131 (compound_stmt -> with_stmt .) $end reduce using rule 131 (compound_stmt -> with_stmt .) } reduce using rule 131 (compound_stmt -> with_stmt .) ELSE reduce using rule 131 (compound_stmt -> with_stmt .) DEFAULT reduce using rule 131 (compound_stmt -> with_stmt .) CASE reduce using rule 131 (compound_stmt -> with_stmt .) state 25 (146) loop_head -> LOOP . ID AS ID (147) loop_head -> LOOP . ID AS ID : ID (148) loop_head -> LOOP . ID AS ID : ID comp_operator ID ID shift and go to state 98 state 26 (11) simple_stmt -> fancy_drel_assignment_stmt . ; reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) BREAK reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) NEXT reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) IF reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) FOR reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) WHERE reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) SWITCH reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) FUNCTION reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) PRINT reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) DO reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) LOOP reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) WITH reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) ( reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) [ reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) ID reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) ITEM_TAG reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) INTEGER reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) HEXINT reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) OCTINT reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) BININT reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) REAL reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) IMAGINARY reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) STRPREFIX reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) SHORTSTRING reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) LONGSTRING reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) ` reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) $end reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) } reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) ELSE reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) DEFAULT reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) CASE reduce using rule 11 (simple_stmt -> fancy_drel_assignment_stmt .) state 27 (10) simple_stmt -> augmented_assignment_stmt . ; reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) BREAK reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) NEXT reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) IF reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) FOR reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) WHERE reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) SWITCH reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) FUNCTION reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) PRINT reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) DO reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) LOOP reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) WITH reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) ( reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) [ reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) ID reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) ITEM_TAG reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) INTEGER reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) HEXINT reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) OCTINT reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) BININT reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) REAL reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) IMAGINARY reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) STRPREFIX reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) SHORTSTRING reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) LONGSTRING reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) ` reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) $end reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) } reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) ELSE reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) DEFAULT reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) CASE reduce using rule 10 (simple_stmt -> augmented_assignment_stmt .) state 28 (15) print_stmt -> PRINT . expression (18) expression -> . or_test (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 list_display shift and go to state 22 or_test shift and go to state 86 expression shift and go to state 99 state 29 (59) atom -> enclosure . [ reduce using rule 59 (atom -> enclosure .) ( reduce using rule 59 (atom -> enclosure .) POWER reduce using rule 59 (atom -> enclosure .) . reduce using rule 59 (atom -> enclosure .) REAL reduce using rule 59 (atom -> enclosure .) ) reduce using rule 59 (atom -> enclosure .) , reduce using rule 59 (atom -> enclosure .) * reduce using rule 59 (atom -> enclosure .) / reduce using rule 59 (atom -> enclosure .) ^ reduce using rule 59 (atom -> enclosure .) + reduce using rule 59 (atom -> enclosure .) - reduce using rule 59 (atom -> enclosure .) < reduce using rule 59 (atom -> enclosure .) > reduce using rule 59 (atom -> enclosure .) GTE reduce using rule 59 (atom -> enclosure .) LTE reduce using rule 59 (atom -> enclosure .) NEQ reduce using rule 59 (atom -> enclosure .) ISEQUAL reduce using rule 59 (atom -> enclosure .) IN reduce using rule 59 (atom -> enclosure .) NOT reduce using rule 59 (atom -> enclosure .) AND reduce using rule 59 (atom -> enclosure .) OR reduce using rule 59 (atom -> enclosure .) BREAK reduce using rule 59 (atom -> enclosure .) NEXT reduce using rule 59 (atom -> enclosure .) { reduce using rule 59 (atom -> enclosure .) PRINT reduce using rule 59 (atom -> enclosure .) IF reduce using rule 59 (atom -> enclosure .) FOR reduce using rule 59 (atom -> enclosure .) WHERE reduce using rule 59 (atom -> enclosure .) SWITCH reduce using rule 59 (atom -> enclosure .) FUNCTION reduce using rule 59 (atom -> enclosure .) DO reduce using rule 59 (atom -> enclosure .) LOOP reduce using rule 59 (atom -> enclosure .) WITH reduce using rule 59 (atom -> enclosure .) ID reduce using rule 59 (atom -> enclosure .) ITEM_TAG reduce using rule 59 (atom -> enclosure .) INTEGER reduce using rule 59 (atom -> enclosure .) HEXINT reduce using rule 59 (atom -> enclosure .) OCTINT reduce using rule 59 (atom -> enclosure .) BININT reduce using rule 59 (atom -> enclosure .) IMAGINARY reduce using rule 59 (atom -> enclosure .) STRPREFIX reduce using rule 59 (atom -> enclosure .) SHORTSTRING reduce using rule 59 (atom -> enclosure .) LONGSTRING reduce using rule 59 (atom -> enclosure .) ` reduce using rule 59 (atom -> enclosure .) ] reduce using rule 59 (atom -> enclosure .) ; reduce using rule 59 (atom -> enclosure .) $end reduce using rule 59 (atom -> enclosure .) } reduce using rule 59 (atom -> enclosure .) ELSE reduce using rule 59 (atom -> enclosure .) DEFAULT reduce using rule 59 (atom -> enclosure .) CASE reduce using rule 59 (atom -> enclosure .) AUGOP reduce using rule 59 (atom -> enclosure .) = reduce using rule 59 (atom -> enclosure .) : reduce using rule 59 (atom -> enclosure .) state 30 (144) for_stmt -> FOR . target_list IN expression_list suite (125) target_list -> . target (126) target_list -> . target_list , target (19) target -> . primary (20) target -> . ( target_list ) (21) target -> . [ target_list ] (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] ( shift and go to state 6 [ shift and go to state 38 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ` shift and go to state 20 primary_att shift and go to state 41 primary shift and go to state 100 enclosure shift and go to state 29 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 simple_slicing shift and go to state 37 slicing shift and go to state 17 target_list shift and go to state 101 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 target shift and go to state 84 list_display shift and go to state 22 stringliteral shift and go to state 23 state 31 (70) stringliteral -> SHORTSTRING . POWER reduce using rule 70 (stringliteral -> SHORTSTRING .) [ reduce using rule 70 (stringliteral -> SHORTSTRING .) ( reduce using rule 70 (stringliteral -> SHORTSTRING .) . reduce using rule 70 (stringliteral -> SHORTSTRING .) REAL reduce using rule 70 (stringliteral -> SHORTSTRING .) * reduce using rule 70 (stringliteral -> SHORTSTRING .) / reduce using rule 70 (stringliteral -> SHORTSTRING .) ^ reduce using rule 70 (stringliteral -> SHORTSTRING .) + reduce using rule 70 (stringliteral -> SHORTSTRING .) - reduce using rule 70 (stringliteral -> SHORTSTRING .) < reduce using rule 70 (stringliteral -> SHORTSTRING .) > reduce using rule 70 (stringliteral -> SHORTSTRING .) GTE reduce using rule 70 (stringliteral -> SHORTSTRING .) LTE reduce using rule 70 (stringliteral -> SHORTSTRING .) NEQ reduce using rule 70 (stringliteral -> SHORTSTRING .) ISEQUAL reduce using rule 70 (stringliteral -> SHORTSTRING .) IN reduce using rule 70 (stringliteral -> SHORTSTRING .) NOT reduce using rule 70 (stringliteral -> SHORTSTRING .) AND reduce using rule 70 (stringliteral -> SHORTSTRING .) OR reduce using rule 70 (stringliteral -> SHORTSTRING .) ) reduce using rule 70 (stringliteral -> SHORTSTRING .) , reduce using rule 70 (stringliteral -> SHORTSTRING .) BREAK reduce using rule 70 (stringliteral -> SHORTSTRING .) NEXT reduce using rule 70 (stringliteral -> SHORTSTRING .) { reduce using rule 70 (stringliteral -> SHORTSTRING .) PRINT reduce using rule 70 (stringliteral -> SHORTSTRING .) IF reduce using rule 70 (stringliteral -> SHORTSTRING .) FOR reduce using rule 70 (stringliteral -> SHORTSTRING .) WHERE reduce using rule 70 (stringliteral -> SHORTSTRING .) SWITCH reduce using rule 70 (stringliteral -> SHORTSTRING .) FUNCTION reduce using rule 70 (stringliteral -> SHORTSTRING .) DO reduce using rule 70 (stringliteral -> SHORTSTRING .) LOOP reduce using rule 70 (stringliteral -> SHORTSTRING .) WITH reduce using rule 70 (stringliteral -> SHORTSTRING .) ID reduce using rule 70 (stringliteral -> SHORTSTRING .) ITEM_TAG reduce using rule 70 (stringliteral -> SHORTSTRING .) INTEGER reduce using rule 70 (stringliteral -> SHORTSTRING .) HEXINT reduce using rule 70 (stringliteral -> SHORTSTRING .) OCTINT reduce using rule 70 (stringliteral -> SHORTSTRING .) BININT reduce using rule 70 (stringliteral -> SHORTSTRING .) IMAGINARY reduce using rule 70 (stringliteral -> SHORTSTRING .) STRPREFIX reduce using rule 70 (stringliteral -> SHORTSTRING .) SHORTSTRING reduce using rule 70 (stringliteral -> SHORTSTRING .) LONGSTRING reduce using rule 70 (stringliteral -> SHORTSTRING .) ` reduce using rule 70 (stringliteral -> SHORTSTRING .) ; reduce using rule 70 (stringliteral -> SHORTSTRING .) $end reduce using rule 70 (stringliteral -> SHORTSTRING .) } reduce using rule 70 (stringliteral -> SHORTSTRING .) ELSE reduce using rule 70 (stringliteral -> SHORTSTRING .) DEFAULT reduce using rule 70 (stringliteral -> SHORTSTRING .) CASE reduce using rule 70 (stringliteral -> SHORTSTRING .) ] reduce using rule 70 (stringliteral -> SHORTSTRING .) : reduce using rule 70 (stringliteral -> SHORTSTRING .) AUGOP reduce using rule 70 (stringliteral -> SHORTSTRING .) = reduce using rule 70 (stringliteral -> SHORTSTRING .) state 32 (9) simple_stmt -> assignment_stmt . ; reduce using rule 9 (simple_stmt -> assignment_stmt .) BREAK reduce using rule 9 (simple_stmt -> assignment_stmt .) NEXT reduce using rule 9 (simple_stmt -> assignment_stmt .) IF reduce using rule 9 (simple_stmt -> assignment_stmt .) FOR reduce using rule 9 (simple_stmt -> assignment_stmt .) WHERE reduce using rule 9 (simple_stmt -> assignment_stmt .) SWITCH reduce using rule 9 (simple_stmt -> assignment_stmt .) FUNCTION reduce using rule 9 (simple_stmt -> assignment_stmt .) PRINT reduce using rule 9 (simple_stmt -> assignment_stmt .) DO reduce using rule 9 (simple_stmt -> assignment_stmt .) LOOP reduce using rule 9 (simple_stmt -> assignment_stmt .) WITH reduce using rule 9 (simple_stmt -> assignment_stmt .) ( reduce using rule 9 (simple_stmt -> assignment_stmt .) [ reduce using rule 9 (simple_stmt -> assignment_stmt .) ID reduce using rule 9 (simple_stmt -> assignment_stmt .) ITEM_TAG reduce using rule 9 (simple_stmt -> assignment_stmt .) INTEGER reduce using rule 9 (simple_stmt -> assignment_stmt .) HEXINT reduce using rule 9 (simple_stmt -> assignment_stmt .) OCTINT reduce using rule 9 (simple_stmt -> assignment_stmt .) BININT reduce using rule 9 (simple_stmt -> assignment_stmt .) REAL reduce using rule 9 (simple_stmt -> assignment_stmt .) IMAGINARY reduce using rule 9 (simple_stmt -> assignment_stmt .) STRPREFIX reduce using rule 9 (simple_stmt -> assignment_stmt .) SHORTSTRING reduce using rule 9 (simple_stmt -> assignment_stmt .) LONGSTRING reduce using rule 9 (simple_stmt -> assignment_stmt .) ` reduce using rule 9 (simple_stmt -> assignment_stmt .) $end reduce using rule 9 (simple_stmt -> assignment_stmt .) } reduce using rule 9 (simple_stmt -> assignment_stmt .) ELSE reduce using rule 9 (simple_stmt -> assignment_stmt .) DEFAULT reduce using rule 9 (simple_stmt -> assignment_stmt .) CASE reduce using rule 9 (simple_stmt -> assignment_stmt .) state 33 (64) literal -> OCTINT . POWER reduce using rule 64 (literal -> OCTINT .) [ reduce using rule 64 (literal -> OCTINT .) ( reduce using rule 64 (literal -> OCTINT .) . reduce using rule 64 (literal -> OCTINT .) REAL reduce using rule 64 (literal -> OCTINT .) * reduce using rule 64 (literal -> OCTINT .) / reduce using rule 64 (literal -> OCTINT .) ^ reduce using rule 64 (literal -> OCTINT .) + reduce using rule 64 (literal -> OCTINT .) - reduce using rule 64 (literal -> OCTINT .) < reduce using rule 64 (literal -> OCTINT .) > reduce using rule 64 (literal -> OCTINT .) GTE reduce using rule 64 (literal -> OCTINT .) LTE reduce using rule 64 (literal -> OCTINT .) NEQ reduce using rule 64 (literal -> OCTINT .) ISEQUAL reduce using rule 64 (literal -> OCTINT .) IN reduce using rule 64 (literal -> OCTINT .) NOT reduce using rule 64 (literal -> OCTINT .) AND reduce using rule 64 (literal -> OCTINT .) OR reduce using rule 64 (literal -> OCTINT .) ] reduce using rule 64 (literal -> OCTINT .) : reduce using rule 64 (literal -> OCTINT .) , reduce using rule 64 (literal -> OCTINT .) AUGOP reduce using rule 64 (literal -> OCTINT .) = reduce using rule 64 (literal -> OCTINT .) ) reduce using rule 64 (literal -> OCTINT .) BREAK reduce using rule 64 (literal -> OCTINT .) NEXT reduce using rule 64 (literal -> OCTINT .) { reduce using rule 64 (literal -> OCTINT .) PRINT reduce using rule 64 (literal -> OCTINT .) IF reduce using rule 64 (literal -> OCTINT .) FOR reduce using rule 64 (literal -> OCTINT .) WHERE reduce using rule 64 (literal -> OCTINT .) SWITCH reduce using rule 64 (literal -> OCTINT .) FUNCTION reduce using rule 64 (literal -> OCTINT .) DO reduce using rule 64 (literal -> OCTINT .) LOOP reduce using rule 64 (literal -> OCTINT .) WITH reduce using rule 64 (literal -> OCTINT .) ID reduce using rule 64 (literal -> OCTINT .) ITEM_TAG reduce using rule 64 (literal -> OCTINT .) INTEGER reduce using rule 64 (literal -> OCTINT .) HEXINT reduce using rule 64 (literal -> OCTINT .) OCTINT reduce using rule 64 (literal -> OCTINT .) BININT reduce using rule 64 (literal -> OCTINT .) IMAGINARY reduce using rule 64 (literal -> OCTINT .) STRPREFIX reduce using rule 64 (literal -> OCTINT .) SHORTSTRING reduce using rule 64 (literal -> OCTINT .) LONGSTRING reduce using rule 64 (literal -> OCTINT .) ` reduce using rule 64 (literal -> OCTINT .) ; reduce using rule 64 (literal -> OCTINT .) $end reduce using rule 64 (literal -> OCTINT .) } reduce using rule 64 (literal -> OCTINT .) ELSE reduce using rule 64 (literal -> OCTINT .) DEFAULT reduce using rule 64 (literal -> OCTINT .) CASE reduce using rule 64 (literal -> OCTINT .) state 34 (99) slicing -> extended_slicing . POWER reduce using rule 99 (slicing -> extended_slicing .) [ reduce using rule 99 (slicing -> extended_slicing .) ( reduce using rule 99 (slicing -> extended_slicing .) . reduce using rule 99 (slicing -> extended_slicing .) REAL reduce using rule 99 (slicing -> extended_slicing .) * reduce using rule 99 (slicing -> extended_slicing .) / reduce using rule 99 (slicing -> extended_slicing .) ^ reduce using rule 99 (slicing -> extended_slicing .) + reduce using rule 99 (slicing -> extended_slicing .) - reduce using rule 99 (slicing -> extended_slicing .) < reduce using rule 99 (slicing -> extended_slicing .) > reduce using rule 99 (slicing -> extended_slicing .) GTE reduce using rule 99 (slicing -> extended_slicing .) LTE reduce using rule 99 (slicing -> extended_slicing .) NEQ reduce using rule 99 (slicing -> extended_slicing .) ISEQUAL reduce using rule 99 (slicing -> extended_slicing .) IN reduce using rule 99 (slicing -> extended_slicing .) NOT reduce using rule 99 (slicing -> extended_slicing .) AND reduce using rule 99 (slicing -> extended_slicing .) OR reduce using rule 99 (slicing -> extended_slicing .) , reduce using rule 99 (slicing -> extended_slicing .) FOR reduce using rule 99 (slicing -> extended_slicing .) IF reduce using rule 99 (slicing -> extended_slicing .) ] reduce using rule 99 (slicing -> extended_slicing .) AUGOP reduce using rule 99 (slicing -> extended_slicing .) = reduce using rule 99 (slicing -> extended_slicing .) BREAK reduce using rule 99 (slicing -> extended_slicing .) NEXT reduce using rule 99 (slicing -> extended_slicing .) { reduce using rule 99 (slicing -> extended_slicing .) PRINT reduce using rule 99 (slicing -> extended_slicing .) WHERE reduce using rule 99 (slicing -> extended_slicing .) SWITCH reduce using rule 99 (slicing -> extended_slicing .) FUNCTION reduce using rule 99 (slicing -> extended_slicing .) DO reduce using rule 99 (slicing -> extended_slicing .) LOOP reduce using rule 99 (slicing -> extended_slicing .) WITH reduce using rule 99 (slicing -> extended_slicing .) ID reduce using rule 99 (slicing -> extended_slicing .) ITEM_TAG reduce using rule 99 (slicing -> extended_slicing .) INTEGER reduce using rule 99 (slicing -> extended_slicing .) HEXINT reduce using rule 99 (slicing -> extended_slicing .) OCTINT reduce using rule 99 (slicing -> extended_slicing .) BININT reduce using rule 99 (slicing -> extended_slicing .) IMAGINARY reduce using rule 99 (slicing -> extended_slicing .) STRPREFIX reduce using rule 99 (slicing -> extended_slicing .) SHORTSTRING reduce using rule 99 (slicing -> extended_slicing .) LONGSTRING reduce using rule 99 (slicing -> extended_slicing .) ` reduce using rule 99 (slicing -> extended_slicing .) ) reduce using rule 99 (slicing -> extended_slicing .) ; reduce using rule 99 (slicing -> extended_slicing .) $end reduce using rule 99 (slicing -> extended_slicing .) } reduce using rule 99 (slicing -> extended_slicing .) ELSE reduce using rule 99 (slicing -> extended_slicing .) DEFAULT reduce using rule 99 (slicing -> extended_slicing .) CASE reduce using rule 99 (slicing -> extended_slicing .) : reduce using rule 99 (slicing -> extended_slicing .) state 35 (5) statement -> compound_stmt . } reduce using rule 5 (statement -> compound_stmt .) BREAK reduce using rule 5 (statement -> compound_stmt .) NEXT reduce using rule 5 (statement -> compound_stmt .) IF reduce using rule 5 (statement -> compound_stmt .) FOR reduce using rule 5 (statement -> compound_stmt .) WHERE reduce using rule 5 (statement -> compound_stmt .) SWITCH reduce using rule 5 (statement -> compound_stmt .) FUNCTION reduce using rule 5 (statement -> compound_stmt .) PRINT reduce using rule 5 (statement -> compound_stmt .) DO reduce using rule 5 (statement -> compound_stmt .) LOOP reduce using rule 5 (statement -> compound_stmt .) WITH reduce using rule 5 (statement -> compound_stmt .) ( reduce using rule 5 (statement -> compound_stmt .) [ reduce using rule 5 (statement -> compound_stmt .) ID reduce using rule 5 (statement -> compound_stmt .) ITEM_TAG reduce using rule 5 (statement -> compound_stmt .) INTEGER reduce using rule 5 (statement -> compound_stmt .) HEXINT reduce using rule 5 (statement -> compound_stmt .) OCTINT reduce using rule 5 (statement -> compound_stmt .) BININT reduce using rule 5 (statement -> compound_stmt .) REAL reduce using rule 5 (statement -> compound_stmt .) IMAGINARY reduce using rule 5 (statement -> compound_stmt .) STRPREFIX reduce using rule 5 (statement -> compound_stmt .) SHORTSTRING reduce using rule 5 (statement -> compound_stmt .) LONGSTRING reduce using rule 5 (statement -> compound_stmt .) ` reduce using rule 5 (statement -> compound_stmt .) $end reduce using rule 5 (statement -> compound_stmt .) state 36 (158) funcdef -> FUNCTION . ID ( arglist ) suite ID shift and go to state 102 state 37 (98) slicing -> simple_slicing . POWER reduce using rule 98 (slicing -> simple_slicing .) [ reduce using rule 98 (slicing -> simple_slicing .) ( reduce using rule 98 (slicing -> simple_slicing .) . reduce using rule 98 (slicing -> simple_slicing .) REAL reduce using rule 98 (slicing -> simple_slicing .) * reduce using rule 98 (slicing -> simple_slicing .) / reduce using rule 98 (slicing -> simple_slicing .) ^ reduce using rule 98 (slicing -> simple_slicing .) + reduce using rule 98 (slicing -> simple_slicing .) - reduce using rule 98 (slicing -> simple_slicing .) < reduce using rule 98 (slicing -> simple_slicing .) > reduce using rule 98 (slicing -> simple_slicing .) GTE reduce using rule 98 (slicing -> simple_slicing .) LTE reduce using rule 98 (slicing -> simple_slicing .) NEQ reduce using rule 98 (slicing -> simple_slicing .) ISEQUAL reduce using rule 98 (slicing -> simple_slicing .) IN reduce using rule 98 (slicing -> simple_slicing .) NOT reduce using rule 98 (slicing -> simple_slicing .) AND reduce using rule 98 (slicing -> simple_slicing .) OR reduce using rule 98 (slicing -> simple_slicing .) , reduce using rule 98 (slicing -> simple_slicing .) FOR reduce using rule 98 (slicing -> simple_slicing .) IF reduce using rule 98 (slicing -> simple_slicing .) ] reduce using rule 98 (slicing -> simple_slicing .) AUGOP reduce using rule 98 (slicing -> simple_slicing .) = reduce using rule 98 (slicing -> simple_slicing .) BREAK reduce using rule 98 (slicing -> simple_slicing .) NEXT reduce using rule 98 (slicing -> simple_slicing .) { reduce using rule 98 (slicing -> simple_slicing .) PRINT reduce using rule 98 (slicing -> simple_slicing .) WHERE reduce using rule 98 (slicing -> simple_slicing .) SWITCH reduce using rule 98 (slicing -> simple_slicing .) FUNCTION reduce using rule 98 (slicing -> simple_slicing .) DO reduce using rule 98 (slicing -> simple_slicing .) LOOP reduce using rule 98 (slicing -> simple_slicing .) WITH reduce using rule 98 (slicing -> simple_slicing .) ID reduce using rule 98 (slicing -> simple_slicing .) ITEM_TAG reduce using rule 98 (slicing -> simple_slicing .) INTEGER reduce using rule 98 (slicing -> simple_slicing .) HEXINT reduce using rule 98 (slicing -> simple_slicing .) OCTINT reduce using rule 98 (slicing -> simple_slicing .) BININT reduce using rule 98 (slicing -> simple_slicing .) IMAGINARY reduce using rule 98 (slicing -> simple_slicing .) STRPREFIX reduce using rule 98 (slicing -> simple_slicing .) SHORTSTRING reduce using rule 98 (slicing -> simple_slicing .) LONGSTRING reduce using rule 98 (slicing -> simple_slicing .) ` reduce using rule 98 (slicing -> simple_slicing .) ) reduce using rule 98 (slicing -> simple_slicing .) ; reduce using rule 98 (slicing -> simple_slicing .) $end reduce using rule 98 (slicing -> simple_slicing .) } reduce using rule 98 (slicing -> simple_slicing .) ELSE reduce using rule 98 (slicing -> simple_slicing .) DEFAULT reduce using rule 98 (slicing -> simple_slicing .) CASE reduce using rule 98 (slicing -> simple_slicing .) : reduce using rule 98 (slicing -> simple_slicing .) state 38 (21) target -> [ . target_list ] (78) list_display -> [ . listmaker ] (79) list_display -> [ . ] (125) target_list -> . target (126) target_list -> . target_list , target (80) listmaker -> . expression listmaker2 (81) listmaker -> . expression list_for (19) target -> . primary (20) target -> . ( target_list ) (21) target -> . [ target_list ] (18) expression -> . or_test (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (26) not_test -> . comparison (27) not_test -> . NOT not_test (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr ] shift and go to state 105 ( shift and go to state 6 [ shift and go to state 38 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 NOT shift and go to state 72 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ` shift and go to state 20 - shift and go to state 79 + shift and go to state 77 primary_att shift and go to state 41 primary shift and go to state 73 stringliteral shift and go to state 23 not_test shift and go to state 74 listmaker shift and go to state 103 enclosure shift and go to state 29 power shift and go to state 75 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 simple_slicing shift and go to state 37 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 target_list shift and go to state 104 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 target shift and go to state 84 list_display shift and go to state 22 or_test shift and go to state 86 expression shift and go to state 106 state 39 (132) compound_stmt -> where_stmt . BREAK reduce using rule 132 (compound_stmt -> where_stmt .) NEXT reduce using rule 132 (compound_stmt -> where_stmt .) IF reduce using rule 132 (compound_stmt -> where_stmt .) FOR reduce using rule 132 (compound_stmt -> where_stmt .) WHERE reduce using rule 132 (compound_stmt -> where_stmt .) SWITCH reduce using rule 132 (compound_stmt -> where_stmt .) FUNCTION reduce using rule 132 (compound_stmt -> where_stmt .) PRINT reduce using rule 132 (compound_stmt -> where_stmt .) DO reduce using rule 132 (compound_stmt -> where_stmt .) LOOP reduce using rule 132 (compound_stmt -> where_stmt .) WITH reduce using rule 132 (compound_stmt -> where_stmt .) ( reduce using rule 132 (compound_stmt -> where_stmt .) [ reduce using rule 132 (compound_stmt -> where_stmt .) ID reduce using rule 132 (compound_stmt -> where_stmt .) ITEM_TAG reduce using rule 132 (compound_stmt -> where_stmt .) INTEGER reduce using rule 132 (compound_stmt -> where_stmt .) HEXINT reduce using rule 132 (compound_stmt -> where_stmt .) OCTINT reduce using rule 132 (compound_stmt -> where_stmt .) BININT reduce using rule 132 (compound_stmt -> where_stmt .) REAL reduce using rule 132 (compound_stmt -> where_stmt .) IMAGINARY reduce using rule 132 (compound_stmt -> where_stmt .) STRPREFIX reduce using rule 132 (compound_stmt -> where_stmt .) SHORTSTRING reduce using rule 132 (compound_stmt -> where_stmt .) LONGSTRING reduce using rule 132 (compound_stmt -> where_stmt .) ` reduce using rule 132 (compound_stmt -> where_stmt .) $end reduce using rule 132 (compound_stmt -> where_stmt .) } reduce using rule 132 (compound_stmt -> where_stmt .) ELSE reduce using rule 132 (compound_stmt -> where_stmt .) DEFAULT reduce using rule 132 (compound_stmt -> where_stmt .) CASE reduce using rule 132 (compound_stmt -> where_stmt .) state 40 (66) literal -> REAL . POWER reduce using rule 66 (literal -> REAL .) [ reduce using rule 66 (literal -> REAL .) ( reduce using rule 66 (literal -> REAL .) . reduce using rule 66 (literal -> REAL .) REAL reduce using rule 66 (literal -> REAL .) * reduce using rule 66 (literal -> REAL .) / reduce using rule 66 (literal -> REAL .) ^ reduce using rule 66 (literal -> REAL .) + reduce using rule 66 (literal -> REAL .) - reduce using rule 66 (literal -> REAL .) < reduce using rule 66 (literal -> REAL .) > reduce using rule 66 (literal -> REAL .) GTE reduce using rule 66 (literal -> REAL .) LTE reduce using rule 66 (literal -> REAL .) NEQ reduce using rule 66 (literal -> REAL .) ISEQUAL reduce using rule 66 (literal -> REAL .) IN reduce using rule 66 (literal -> REAL .) NOT reduce using rule 66 (literal -> REAL .) AND reduce using rule 66 (literal -> REAL .) OR reduce using rule 66 (literal -> REAL .) ] reduce using rule 66 (literal -> REAL .) : reduce using rule 66 (literal -> REAL .) , reduce using rule 66 (literal -> REAL .) AUGOP reduce using rule 66 (literal -> REAL .) = reduce using rule 66 (literal -> REAL .) ) reduce using rule 66 (literal -> REAL .) BREAK reduce using rule 66 (literal -> REAL .) NEXT reduce using rule 66 (literal -> REAL .) { reduce using rule 66 (literal -> REAL .) PRINT reduce using rule 66 (literal -> REAL .) IF reduce using rule 66 (literal -> REAL .) FOR reduce using rule 66 (literal -> REAL .) WHERE reduce using rule 66 (literal -> REAL .) SWITCH reduce using rule 66 (literal -> REAL .) FUNCTION reduce using rule 66 (literal -> REAL .) DO reduce using rule 66 (literal -> REAL .) LOOP reduce using rule 66 (literal -> REAL .) WITH reduce using rule 66 (literal -> REAL .) ID reduce using rule 66 (literal -> REAL .) ITEM_TAG reduce using rule 66 (literal -> REAL .) INTEGER reduce using rule 66 (literal -> REAL .) HEXINT reduce using rule 66 (literal -> REAL .) OCTINT reduce using rule 66 (literal -> REAL .) BININT reduce using rule 66 (literal -> REAL .) IMAGINARY reduce using rule 66 (literal -> REAL .) STRPREFIX reduce using rule 66 (literal -> REAL .) SHORTSTRING reduce using rule 66 (literal -> REAL .) LONGSTRING reduce using rule 66 (literal -> REAL .) ` reduce using rule 66 (literal -> REAL .) ; reduce using rule 66 (literal -> REAL .) $end reduce using rule 66 (literal -> REAL .) } reduce using rule 66 (literal -> REAL .) ELSE reduce using rule 66 (literal -> REAL .) DEFAULT reduce using rule 66 (literal -> REAL .) CASE reduce using rule 66 (literal -> REAL .) state 41 (51) primary -> primary_att . ( reduce using rule 51 (primary -> primary_att .) [ reduce using rule 51 (primary -> primary_att .) . reduce using rule 51 (primary -> primary_att .) REAL reduce using rule 51 (primary -> primary_att .) AUGOP reduce using rule 51 (primary -> primary_att .) = reduce using rule 51 (primary -> primary_att .) , reduce using rule 51 (primary -> primary_att .) POWER reduce using rule 51 (primary -> primary_att .) * reduce using rule 51 (primary -> primary_att .) / reduce using rule 51 (primary -> primary_att .) ^ reduce using rule 51 (primary -> primary_att .) + reduce using rule 51 (primary -> primary_att .) - reduce using rule 51 (primary -> primary_att .) < reduce using rule 51 (primary -> primary_att .) > reduce using rule 51 (primary -> primary_att .) GTE reduce using rule 51 (primary -> primary_att .) LTE reduce using rule 51 (primary -> primary_att .) NEQ reduce using rule 51 (primary -> primary_att .) ISEQUAL reduce using rule 51 (primary -> primary_att .) IN reduce using rule 51 (primary -> primary_att .) NOT reduce using rule 51 (primary -> primary_att .) AND reduce using rule 51 (primary -> primary_att .) OR reduce using rule 51 (primary -> primary_att .) ; reduce using rule 51 (primary -> primary_att .) BREAK reduce using rule 51 (primary -> primary_att .) NEXT reduce using rule 51 (primary -> primary_att .) IF reduce using rule 51 (primary -> primary_att .) FOR reduce using rule 51 (primary -> primary_att .) WHERE reduce using rule 51 (primary -> primary_att .) SWITCH reduce using rule 51 (primary -> primary_att .) FUNCTION reduce using rule 51 (primary -> primary_att .) PRINT reduce using rule 51 (primary -> primary_att .) DO reduce using rule 51 (primary -> primary_att .) LOOP reduce using rule 51 (primary -> primary_att .) WITH reduce using rule 51 (primary -> primary_att .) ID reduce using rule 51 (primary -> primary_att .) ITEM_TAG reduce using rule 51 (primary -> primary_att .) INTEGER reduce using rule 51 (primary -> primary_att .) HEXINT reduce using rule 51 (primary -> primary_att .) OCTINT reduce using rule 51 (primary -> primary_att .) BININT reduce using rule 51 (primary -> primary_att .) IMAGINARY reduce using rule 51 (primary -> primary_att .) STRPREFIX reduce using rule 51 (primary -> primary_att .) SHORTSTRING reduce using rule 51 (primary -> primary_att .) LONGSTRING reduce using rule 51 (primary -> primary_att .) ` reduce using rule 51 (primary -> primary_att .) $end reduce using rule 51 (primary -> primary_att .) } reduce using rule 51 (primary -> primary_att .) ELSE reduce using rule 51 (primary -> primary_att .) DEFAULT reduce using rule 51 (primary -> primary_att .) CASE reduce using rule 51 (primary -> primary_att .) ) reduce using rule 51 (primary -> primary_att .) : reduce using rule 51 (primary -> primary_att .) ] reduce using rule 51 (primary -> primary_att .) { reduce using rule 51 (primary -> primary_att .) state 42 (121) fancy_drel_assignment_stmt -> primary . ( dotlist ) (19) target -> primary . (97) subscription -> primary . [ expression_list ] (115) call -> primary . ( ) (116) call -> primary . ( argument_list ) (94) attributeref -> primary . attribute_tag (100) simple_slicing -> primary . [ short_slice ] (105) extended_slicing -> primary . [ slice_list ] (95) attribute_tag -> . . ID (96) attribute_tag -> . REAL ( shift and go to state 109 AUGOP reduce using rule 19 (target -> primary .) = reduce using rule 19 (target -> primary .) , reduce using rule 19 (target -> primary .) [ shift and go to state 111 . shift and go to state 110 REAL shift and go to state 107 attribute_tag shift and go to state 108 state 43 (133) compound_stmt -> switch_stmt . BREAK reduce using rule 133 (compound_stmt -> switch_stmt .) NEXT reduce using rule 133 (compound_stmt -> switch_stmt .) IF reduce using rule 133 (compound_stmt -> switch_stmt .) FOR reduce using rule 133 (compound_stmt -> switch_stmt .) WHERE reduce using rule 133 (compound_stmt -> switch_stmt .) SWITCH reduce using rule 133 (compound_stmt -> switch_stmt .) FUNCTION reduce using rule 133 (compound_stmt -> switch_stmt .) PRINT reduce using rule 133 (compound_stmt -> switch_stmt .) DO reduce using rule 133 (compound_stmt -> switch_stmt .) LOOP reduce using rule 133 (compound_stmt -> switch_stmt .) WITH reduce using rule 133 (compound_stmt -> switch_stmt .) ( reduce using rule 133 (compound_stmt -> switch_stmt .) [ reduce using rule 133 (compound_stmt -> switch_stmt .) ID reduce using rule 133 (compound_stmt -> switch_stmt .) ITEM_TAG reduce using rule 133 (compound_stmt -> switch_stmt .) INTEGER reduce using rule 133 (compound_stmt -> switch_stmt .) HEXINT reduce using rule 133 (compound_stmt -> switch_stmt .) OCTINT reduce using rule 133 (compound_stmt -> switch_stmt .) BININT reduce using rule 133 (compound_stmt -> switch_stmt .) REAL reduce using rule 133 (compound_stmt -> switch_stmt .) IMAGINARY reduce using rule 133 (compound_stmt -> switch_stmt .) STRPREFIX reduce using rule 133 (compound_stmt -> switch_stmt .) SHORTSTRING reduce using rule 133 (compound_stmt -> switch_stmt .) LONGSTRING reduce using rule 133 (compound_stmt -> switch_stmt .) ` reduce using rule 133 (compound_stmt -> switch_stmt .) $end reduce using rule 133 (compound_stmt -> switch_stmt .) } reduce using rule 133 (compound_stmt -> switch_stmt .) ELSE reduce using rule 133 (compound_stmt -> switch_stmt .) DEFAULT reduce using rule 133 (compound_stmt -> switch_stmt .) CASE reduce using rule 133 (compound_stmt -> switch_stmt .) state 44 (65) literal -> BININT . POWER reduce using rule 65 (literal -> BININT .) [ reduce using rule 65 (literal -> BININT .) ( reduce using rule 65 (literal -> BININT .) . reduce using rule 65 (literal -> BININT .) REAL reduce using rule 65 (literal -> BININT .) * reduce using rule 65 (literal -> BININT .) / reduce using rule 65 (literal -> BININT .) ^ reduce using rule 65 (literal -> BININT .) + reduce using rule 65 (literal -> BININT .) - reduce using rule 65 (literal -> BININT .) < reduce using rule 65 (literal -> BININT .) > reduce using rule 65 (literal -> BININT .) GTE reduce using rule 65 (literal -> BININT .) LTE reduce using rule 65 (literal -> BININT .) NEQ reduce using rule 65 (literal -> BININT .) ISEQUAL reduce using rule 65 (literal -> BININT .) IN reduce using rule 65 (literal -> BININT .) NOT reduce using rule 65 (literal -> BININT .) AND reduce using rule 65 (literal -> BININT .) OR reduce using rule 65 (literal -> BININT .) ] reduce using rule 65 (literal -> BININT .) : reduce using rule 65 (literal -> BININT .) , reduce using rule 65 (literal -> BININT .) AUGOP reduce using rule 65 (literal -> BININT .) = reduce using rule 65 (literal -> BININT .) ) reduce using rule 65 (literal -> BININT .) BREAK reduce using rule 65 (literal -> BININT .) NEXT reduce using rule 65 (literal -> BININT .) { reduce using rule 65 (literal -> BININT .) PRINT reduce using rule 65 (literal -> BININT .) IF reduce using rule 65 (literal -> BININT .) FOR reduce using rule 65 (literal -> BININT .) WHERE reduce using rule 65 (literal -> BININT .) SWITCH reduce using rule 65 (literal -> BININT .) FUNCTION reduce using rule 65 (literal -> BININT .) DO reduce using rule 65 (literal -> BININT .) LOOP reduce using rule 65 (literal -> BININT .) WITH reduce using rule 65 (literal -> BININT .) ID reduce using rule 65 (literal -> BININT .) ITEM_TAG reduce using rule 65 (literal -> BININT .) INTEGER reduce using rule 65 (literal -> BININT .) HEXINT reduce using rule 65 (literal -> BININT .) OCTINT reduce using rule 65 (literal -> BININT .) BININT reduce using rule 65 (literal -> BININT .) IMAGINARY reduce using rule 65 (literal -> BININT .) STRPREFIX reduce using rule 65 (literal -> BININT .) SHORTSTRING reduce using rule 65 (literal -> BININT .) LONGSTRING reduce using rule 65 (literal -> BININT .) ` reduce using rule 65 (literal -> BININT .) ; reduce using rule 65 (literal -> BININT .) $end reduce using rule 65 (literal -> BININT .) } reduce using rule 65 (literal -> BININT .) ELSE reduce using rule 65 (literal -> BININT .) DEFAULT reduce using rule 65 (literal -> BININT .) CASE reduce using rule 65 (literal -> BININT .) state 45 (58) atom -> literal . [ reduce using rule 58 (atom -> literal .) ( reduce using rule 58 (atom -> literal .) POWER reduce using rule 58 (atom -> literal .) . reduce using rule 58 (atom -> literal .) REAL reduce using rule 58 (atom -> literal .) ) reduce using rule 58 (atom -> literal .) , reduce using rule 58 (atom -> literal .) * reduce using rule 58 (atom -> literal .) / reduce using rule 58 (atom -> literal .) ^ reduce using rule 58 (atom -> literal .) + reduce using rule 58 (atom -> literal .) - reduce using rule 58 (atom -> literal .) < reduce using rule 58 (atom -> literal .) > reduce using rule 58 (atom -> literal .) GTE reduce using rule 58 (atom -> literal .) LTE reduce using rule 58 (atom -> literal .) NEQ reduce using rule 58 (atom -> literal .) ISEQUAL reduce using rule 58 (atom -> literal .) IN reduce using rule 58 (atom -> literal .) NOT reduce using rule 58 (atom -> literal .) AND reduce using rule 58 (atom -> literal .) OR reduce using rule 58 (atom -> literal .) BREAK reduce using rule 58 (atom -> literal .) NEXT reduce using rule 58 (atom -> literal .) { reduce using rule 58 (atom -> literal .) PRINT reduce using rule 58 (atom -> literal .) IF reduce using rule 58 (atom -> literal .) FOR reduce using rule 58 (atom -> literal .) WHERE reduce using rule 58 (atom -> literal .) SWITCH reduce using rule 58 (atom -> literal .) FUNCTION reduce using rule 58 (atom -> literal .) DO reduce using rule 58 (atom -> literal .) LOOP reduce using rule 58 (atom -> literal .) WITH reduce using rule 58 (atom -> literal .) ID reduce using rule 58 (atom -> literal .) ITEM_TAG reduce using rule 58 (atom -> literal .) INTEGER reduce using rule 58 (atom -> literal .) HEXINT reduce using rule 58 (atom -> literal .) OCTINT reduce using rule 58 (atom -> literal .) BININT reduce using rule 58 (atom -> literal .) IMAGINARY reduce using rule 58 (atom -> literal .) STRPREFIX reduce using rule 58 (atom -> literal .) SHORTSTRING reduce using rule 58 (atom -> literal .) LONGSTRING reduce using rule 58 (atom -> literal .) ` reduce using rule 58 (atom -> literal .) ] reduce using rule 58 (atom -> literal .) ; reduce using rule 58 (atom -> literal .) $end reduce using rule 58 (atom -> literal .) } reduce using rule 58 (atom -> literal .) ELSE reduce using rule 58 (atom -> literal .) DEFAULT reduce using rule 58 (atom -> literal .) CASE reduce using rule 58 (atom -> literal .) AUGOP reduce using rule 58 (atom -> literal .) = reduce using rule 58 (atom -> literal .) : reduce using rule 58 (atom -> literal .) state 46 (155) switch_stmt -> SWITCH . ID open_brace caselist DEFAULT suite close_brace ID shift and go to state 112 state 47 (54) primary -> call . ( reduce using rule 54 (primary -> call .) [ reduce using rule 54 (primary -> call .) . reduce using rule 54 (primary -> call .) REAL reduce using rule 54 (primary -> call .) AUGOP reduce using rule 54 (primary -> call .) = reduce using rule 54 (primary -> call .) , reduce using rule 54 (primary -> call .) POWER reduce using rule 54 (primary -> call .) * reduce using rule 54 (primary -> call .) / reduce using rule 54 (primary -> call .) ^ reduce using rule 54 (primary -> call .) + reduce using rule 54 (primary -> call .) - reduce using rule 54 (primary -> call .) < reduce using rule 54 (primary -> call .) > reduce using rule 54 (primary -> call .) GTE reduce using rule 54 (primary -> call .) LTE reduce using rule 54 (primary -> call .) NEQ reduce using rule 54 (primary -> call .) ISEQUAL reduce using rule 54 (primary -> call .) IN reduce using rule 54 (primary -> call .) NOT reduce using rule 54 (primary -> call .) AND reduce using rule 54 (primary -> call .) OR reduce using rule 54 (primary -> call .) ; reduce using rule 54 (primary -> call .) BREAK reduce using rule 54 (primary -> call .) NEXT reduce using rule 54 (primary -> call .) IF reduce using rule 54 (primary -> call .) FOR reduce using rule 54 (primary -> call .) WHERE reduce using rule 54 (primary -> call .) SWITCH reduce using rule 54 (primary -> call .) FUNCTION reduce using rule 54 (primary -> call .) PRINT reduce using rule 54 (primary -> call .) DO reduce using rule 54 (primary -> call .) LOOP reduce using rule 54 (primary -> call .) WITH reduce using rule 54 (primary -> call .) ID reduce using rule 54 (primary -> call .) ITEM_TAG reduce using rule 54 (primary -> call .) INTEGER reduce using rule 54 (primary -> call .) HEXINT reduce using rule 54 (primary -> call .) OCTINT reduce using rule 54 (primary -> call .) BININT reduce using rule 54 (primary -> call .) IMAGINARY reduce using rule 54 (primary -> call .) STRPREFIX reduce using rule 54 (primary -> call .) SHORTSTRING reduce using rule 54 (primary -> call .) LONGSTRING reduce using rule 54 (primary -> call .) ` reduce using rule 54 (primary -> call .) $end reduce using rule 54 (primary -> call .) } reduce using rule 54 (primary -> call .) ELSE reduce using rule 54 (primary -> call .) DEFAULT reduce using rule 54 (primary -> call .) CASE reduce using rule 54 (primary -> call .) ) reduce using rule 54 (primary -> call .) : reduce using rule 54 (primary -> call .) ] reduce using rule 54 (primary -> call .) { reduce using rule 54 (primary -> call .) state 48 (2) input -> statement . BREAK reduce using rule 2 (input -> statement .) NEXT reduce using rule 2 (input -> statement .) IF reduce using rule 2 (input -> statement .) FOR reduce using rule 2 (input -> statement .) WHERE reduce using rule 2 (input -> statement .) SWITCH reduce using rule 2 (input -> statement .) FUNCTION reduce using rule 2 (input -> statement .) PRINT reduce using rule 2 (input -> statement .) DO reduce using rule 2 (input -> statement .) LOOP reduce using rule 2 (input -> statement .) WITH reduce using rule 2 (input -> statement .) ( reduce using rule 2 (input -> statement .) [ reduce using rule 2 (input -> statement .) ID reduce using rule 2 (input -> statement .) ITEM_TAG reduce using rule 2 (input -> statement .) INTEGER reduce using rule 2 (input -> statement .) HEXINT reduce using rule 2 (input -> statement .) OCTINT reduce using rule 2 (input -> statement .) BININT reduce using rule 2 (input -> statement .) REAL reduce using rule 2 (input -> statement .) IMAGINARY reduce using rule 2 (input -> statement .) STRPREFIX reduce using rule 2 (input -> statement .) SHORTSTRING reduce using rule 2 (input -> statement .) LONGSTRING reduce using rule 2 (input -> statement .) ` reduce using rule 2 (input -> statement .) $end reduce using rule 2 (input -> statement .) state 49 (73) enclosure -> string_conversion . POWER reduce using rule 73 (enclosure -> string_conversion .) [ reduce using rule 73 (enclosure -> string_conversion .) ( reduce using rule 73 (enclosure -> string_conversion .) . reduce using rule 73 (enclosure -> string_conversion .) REAL reduce using rule 73 (enclosure -> string_conversion .) * reduce using rule 73 (enclosure -> string_conversion .) / reduce using rule 73 (enclosure -> string_conversion .) ^ reduce using rule 73 (enclosure -> string_conversion .) + reduce using rule 73 (enclosure -> string_conversion .) - reduce using rule 73 (enclosure -> string_conversion .) < reduce using rule 73 (enclosure -> string_conversion .) > reduce using rule 73 (enclosure -> string_conversion .) GTE reduce using rule 73 (enclosure -> string_conversion .) LTE reduce using rule 73 (enclosure -> string_conversion .) NEQ reduce using rule 73 (enclosure -> string_conversion .) ISEQUAL reduce using rule 73 (enclosure -> string_conversion .) IN reduce using rule 73 (enclosure -> string_conversion .) NOT reduce using rule 73 (enclosure -> string_conversion .) AND reduce using rule 73 (enclosure -> string_conversion .) OR reduce using rule 73 (enclosure -> string_conversion .) ) reduce using rule 73 (enclosure -> string_conversion .) , reduce using rule 73 (enclosure -> string_conversion .) BREAK reduce using rule 73 (enclosure -> string_conversion .) NEXT reduce using rule 73 (enclosure -> string_conversion .) { reduce using rule 73 (enclosure -> string_conversion .) PRINT reduce using rule 73 (enclosure -> string_conversion .) IF reduce using rule 73 (enclosure -> string_conversion .) FOR reduce using rule 73 (enclosure -> string_conversion .) WHERE reduce using rule 73 (enclosure -> string_conversion .) SWITCH reduce using rule 73 (enclosure -> string_conversion .) FUNCTION reduce using rule 73 (enclosure -> string_conversion .) DO reduce using rule 73 (enclosure -> string_conversion .) LOOP reduce using rule 73 (enclosure -> string_conversion .) WITH reduce using rule 73 (enclosure -> string_conversion .) ID reduce using rule 73 (enclosure -> string_conversion .) ITEM_TAG reduce using rule 73 (enclosure -> string_conversion .) INTEGER reduce using rule 73 (enclosure -> string_conversion .) HEXINT reduce using rule 73 (enclosure -> string_conversion .) OCTINT reduce using rule 73 (enclosure -> string_conversion .) BININT reduce using rule 73 (enclosure -> string_conversion .) IMAGINARY reduce using rule 73 (enclosure -> string_conversion .) STRPREFIX reduce using rule 73 (enclosure -> string_conversion .) SHORTSTRING reduce using rule 73 (enclosure -> string_conversion .) LONGSTRING reduce using rule 73 (enclosure -> string_conversion .) ` reduce using rule 73 (enclosure -> string_conversion .) ; reduce using rule 73 (enclosure -> string_conversion .) $end reduce using rule 73 (enclosure -> string_conversion .) } reduce using rule 73 (enclosure -> string_conversion .) ELSE reduce using rule 73 (enclosure -> string_conversion .) DEFAULT reduce using rule 73 (enclosure -> string_conversion .) CASE reduce using rule 73 (enclosure -> string_conversion .) ] reduce using rule 73 (enclosure -> string_conversion .) : reduce using rule 73 (enclosure -> string_conversion .) AUGOP reduce using rule 73 (enclosure -> string_conversion .) = reduce using rule 73 (enclosure -> string_conversion .) state 50 (12) simple_stmt -> print_stmt . ; reduce using rule 12 (simple_stmt -> print_stmt .) BREAK reduce using rule 12 (simple_stmt -> print_stmt .) NEXT reduce using rule 12 (simple_stmt -> print_stmt .) IF reduce using rule 12 (simple_stmt -> print_stmt .) FOR reduce using rule 12 (simple_stmt -> print_stmt .) WHERE reduce using rule 12 (simple_stmt -> print_stmt .) SWITCH reduce using rule 12 (simple_stmt -> print_stmt .) FUNCTION reduce using rule 12 (simple_stmt -> print_stmt .) PRINT reduce using rule 12 (simple_stmt -> print_stmt .) DO reduce using rule 12 (simple_stmt -> print_stmt .) LOOP reduce using rule 12 (simple_stmt -> print_stmt .) WITH reduce using rule 12 (simple_stmt -> print_stmt .) ( reduce using rule 12 (simple_stmt -> print_stmt .) [ reduce using rule 12 (simple_stmt -> print_stmt .) ID reduce using rule 12 (simple_stmt -> print_stmt .) ITEM_TAG reduce using rule 12 (simple_stmt -> print_stmt .) INTEGER reduce using rule 12 (simple_stmt -> print_stmt .) HEXINT reduce using rule 12 (simple_stmt -> print_stmt .) OCTINT reduce using rule 12 (simple_stmt -> print_stmt .) BININT reduce using rule 12 (simple_stmt -> print_stmt .) REAL reduce using rule 12 (simple_stmt -> print_stmt .) IMAGINARY reduce using rule 12 (simple_stmt -> print_stmt .) STRPREFIX reduce using rule 12 (simple_stmt -> print_stmt .) SHORTSTRING reduce using rule 12 (simple_stmt -> print_stmt .) LONGSTRING reduce using rule 12 (simple_stmt -> print_stmt .) ` reduce using rule 12 (simple_stmt -> print_stmt .) $end reduce using rule 12 (simple_stmt -> print_stmt .) } reduce using rule 12 (simple_stmt -> print_stmt .) ELSE reduce using rule 12 (simple_stmt -> print_stmt .) DEFAULT reduce using rule 12 (simple_stmt -> print_stmt .) CASE reduce using rule 12 (simple_stmt -> print_stmt .) state 51 (152) with_stmt -> with_head . suite (137) suite -> . simple_stmt (138) suite -> . compound_stmt (139) suite -> . open_brace statement_block close_brace (9) simple_stmt -> . assignment_stmt (10) simple_stmt -> . augmented_assignment_stmt (11) simple_stmt -> . fancy_drel_assignment_stmt (12) simple_stmt -> . print_stmt (13) simple_stmt -> . BREAK (14) simple_stmt -> . NEXT (127) compound_stmt -> . if_stmt (128) compound_stmt -> . for_stmt (129) compound_stmt -> . do_stmt (130) compound_stmt -> . loop_stmt (131) compound_stmt -> . with_stmt (132) compound_stmt -> . where_stmt (133) compound_stmt -> . switch_stmt (134) compound_stmt -> . funcdef (140) open_brace -> . { (124) assignment_stmt -> . target_list = expression_list (120) augmented_assignment_stmt -> . target AUGOP expression_list (121) fancy_drel_assignment_stmt -> . primary ( dotlist ) (15) print_stmt -> . PRINT expression (135) if_stmt -> . IF expression suite (136) if_stmt -> . if_stmt ELSE suite (144) for_stmt -> . FOR target_list IN expression_list suite (149) do_stmt -> . do_stmt_head suite (145) loop_stmt -> . loop_head suite (152) with_stmt -> . with_head suite (154) where_stmt -> . WHERE expression suite ELSE suite (155) switch_stmt -> . SWITCH ID open_brace caselist DEFAULT suite close_brace (158) funcdef -> . FUNCTION ID ( arglist ) suite (125) target_list -> . target (126) target_list -> . target_list , target (19) target -> . primary (20) target -> . ( target_list ) (21) target -> . [ target_list ] (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (150) do_stmt_head -> . DO ID = expression , expression (151) do_stmt_head -> . DO ID = expression , expression , expression (146) loop_head -> . LOOP ID AS ID (147) loop_head -> . LOOP ID AS ID : ID (148) loop_head -> . LOOP ID AS ID : ID comp_operator ID (153) with_head -> . WITH ID AS ID (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] BREAK shift and go to state 56 NEXT shift and go to state 7 { shift and go to state 69 PRINT shift and go to state 28 IF shift and go to state 61 FOR shift and go to state 30 WHERE shift and go to state 19 SWITCH shift and go to state 46 FUNCTION shift and go to state 36 ( shift and go to state 6 [ shift and go to state 38 DO shift and go to state 58 LOOP shift and go to state 25 WITH shift and go to state 5 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ` shift and go to state 20 fancy_drel_assignment_stmt shift and go to state 26 primary_att shift and go to state 41 atom shift and go to state 2 primary shift and go to state 42 stringliteral shift and go to state 23 item_tag shift and go to state 52 switch_stmt shift and go to state 43 do_stmt_head shift and go to state 4 enclosure shift and go to state 29 parenth_form shift and go to state 8 simple_stmt shift and go to state 66 literal shift and go to state 45 assignment_stmt shift and go to state 32 call shift and go to state 47 string_conversion shift and go to state 49 with_head shift and go to state 51 suite shift and go to state 113 loop_head shift and go to state 12 do_stmt shift and go to state 13 compound_stmt shift and go to state 67 attributeref shift and go to state 9 simple_slicing shift and go to state 37 print_stmt shift and go to state 50 loop_stmt shift and go to state 15 slicing shift and go to state 17 target_list shift and go to state 63 for_stmt shift and go to state 18 augmented_assignment_stmt shift and go to state 27 funcdef shift and go to state 3 target shift and go to state 54 if_stmt shift and go to state 21 extended_slicing shift and go to state 34 list_display shift and go to state 22 where_stmt shift and go to state 39 open_brace shift and go to state 68 with_stmt shift and go to state 24 subscription shift and go to state 53 state 52 (57) atom -> item_tag . [ reduce using rule 57 (atom -> item_tag .) ( reduce using rule 57 (atom -> item_tag .) POWER reduce using rule 57 (atom -> item_tag .) . reduce using rule 57 (atom -> item_tag .) REAL reduce using rule 57 (atom -> item_tag .) ) reduce using rule 57 (atom -> item_tag .) , reduce using rule 57 (atom -> item_tag .) * reduce using rule 57 (atom -> item_tag .) / reduce using rule 57 (atom -> item_tag .) ^ reduce using rule 57 (atom -> item_tag .) + reduce using rule 57 (atom -> item_tag .) - reduce using rule 57 (atom -> item_tag .) < reduce using rule 57 (atom -> item_tag .) > reduce using rule 57 (atom -> item_tag .) GTE reduce using rule 57 (atom -> item_tag .) LTE reduce using rule 57 (atom -> item_tag .) NEQ reduce using rule 57 (atom -> item_tag .) ISEQUAL reduce using rule 57 (atom -> item_tag .) IN reduce using rule 57 (atom -> item_tag .) NOT reduce using rule 57 (atom -> item_tag .) AND reduce using rule 57 (atom -> item_tag .) OR reduce using rule 57 (atom -> item_tag .) BREAK reduce using rule 57 (atom -> item_tag .) NEXT reduce using rule 57 (atom -> item_tag .) { reduce using rule 57 (atom -> item_tag .) PRINT reduce using rule 57 (atom -> item_tag .) IF reduce using rule 57 (atom -> item_tag .) FOR reduce using rule 57 (atom -> item_tag .) WHERE reduce using rule 57 (atom -> item_tag .) SWITCH reduce using rule 57 (atom -> item_tag .) FUNCTION reduce using rule 57 (atom -> item_tag .) DO reduce using rule 57 (atom -> item_tag .) LOOP reduce using rule 57 (atom -> item_tag .) WITH reduce using rule 57 (atom -> item_tag .) ID reduce using rule 57 (atom -> item_tag .) ITEM_TAG reduce using rule 57 (atom -> item_tag .) INTEGER reduce using rule 57 (atom -> item_tag .) HEXINT reduce using rule 57 (atom -> item_tag .) OCTINT reduce using rule 57 (atom -> item_tag .) BININT reduce using rule 57 (atom -> item_tag .) IMAGINARY reduce using rule 57 (atom -> item_tag .) STRPREFIX reduce using rule 57 (atom -> item_tag .) SHORTSTRING reduce using rule 57 (atom -> item_tag .) LONGSTRING reduce using rule 57 (atom -> item_tag .) ` reduce using rule 57 (atom -> item_tag .) ] reduce using rule 57 (atom -> item_tag .) ; reduce using rule 57 (atom -> item_tag .) $end reduce using rule 57 (atom -> item_tag .) } reduce using rule 57 (atom -> item_tag .) ELSE reduce using rule 57 (atom -> item_tag .) DEFAULT reduce using rule 57 (atom -> item_tag .) CASE reduce using rule 57 (atom -> item_tag .) AUGOP reduce using rule 57 (atom -> item_tag .) = reduce using rule 57 (atom -> item_tag .) : reduce using rule 57 (atom -> item_tag .) state 53 (52) primary -> subscription . ( reduce using rule 52 (primary -> subscription .) [ reduce using rule 52 (primary -> subscription .) . reduce using rule 52 (primary -> subscription .) REAL reduce using rule 52 (primary -> subscription .) AUGOP reduce using rule 52 (primary -> subscription .) = reduce using rule 52 (primary -> subscription .) , reduce using rule 52 (primary -> subscription .) POWER reduce using rule 52 (primary -> subscription .) * reduce using rule 52 (primary -> subscription .) / reduce using rule 52 (primary -> subscription .) ^ reduce using rule 52 (primary -> subscription .) + reduce using rule 52 (primary -> subscription .) - reduce using rule 52 (primary -> subscription .) < reduce using rule 52 (primary -> subscription .) > reduce using rule 52 (primary -> subscription .) GTE reduce using rule 52 (primary -> subscription .) LTE reduce using rule 52 (primary -> subscription .) NEQ reduce using rule 52 (primary -> subscription .) ISEQUAL reduce using rule 52 (primary -> subscription .) IN reduce using rule 52 (primary -> subscription .) NOT reduce using rule 52 (primary -> subscription .) AND reduce using rule 52 (primary -> subscription .) OR reduce using rule 52 (primary -> subscription .) ; reduce using rule 52 (primary -> subscription .) BREAK reduce using rule 52 (primary -> subscription .) NEXT reduce using rule 52 (primary -> subscription .) IF reduce using rule 52 (primary -> subscription .) FOR reduce using rule 52 (primary -> subscription .) WHERE reduce using rule 52 (primary -> subscription .) SWITCH reduce using rule 52 (primary -> subscription .) FUNCTION reduce using rule 52 (primary -> subscription .) PRINT reduce using rule 52 (primary -> subscription .) DO reduce using rule 52 (primary -> subscription .) LOOP reduce using rule 52 (primary -> subscription .) WITH reduce using rule 52 (primary -> subscription .) ID reduce using rule 52 (primary -> subscription .) ITEM_TAG reduce using rule 52 (primary -> subscription .) INTEGER reduce using rule 52 (primary -> subscription .) HEXINT reduce using rule 52 (primary -> subscription .) OCTINT reduce using rule 52 (primary -> subscription .) BININT reduce using rule 52 (primary -> subscription .) IMAGINARY reduce using rule 52 (primary -> subscription .) STRPREFIX reduce using rule 52 (primary -> subscription .) SHORTSTRING reduce using rule 52 (primary -> subscription .) LONGSTRING reduce using rule 52 (primary -> subscription .) ` reduce using rule 52 (primary -> subscription .) $end reduce using rule 52 (primary -> subscription .) } reduce using rule 52 (primary -> subscription .) ELSE reduce using rule 52 (primary -> subscription .) DEFAULT reduce using rule 52 (primary -> subscription .) CASE reduce using rule 52 (primary -> subscription .) ) reduce using rule 52 (primary -> subscription .) : reduce using rule 52 (primary -> subscription .) ] reduce using rule 52 (primary -> subscription .) { reduce using rule 52 (primary -> subscription .) state 54 (120) augmented_assignment_stmt -> target . AUGOP expression_list (125) target_list -> target . AUGOP shift and go to state 114 = reduce using rule 125 (target_list -> target .) , reduce using rule 125 (target_list -> target .) state 55 (62) literal -> INTEGER . POWER reduce using rule 62 (literal -> INTEGER .) [ reduce using rule 62 (literal -> INTEGER .) ( reduce using rule 62 (literal -> INTEGER .) . reduce using rule 62 (literal -> INTEGER .) REAL reduce using rule 62 (literal -> INTEGER .) * reduce using rule 62 (literal -> INTEGER .) / reduce using rule 62 (literal -> INTEGER .) ^ reduce using rule 62 (literal -> INTEGER .) + reduce using rule 62 (literal -> INTEGER .) - reduce using rule 62 (literal -> INTEGER .) < reduce using rule 62 (literal -> INTEGER .) > reduce using rule 62 (literal -> INTEGER .) GTE reduce using rule 62 (literal -> INTEGER .) LTE reduce using rule 62 (literal -> INTEGER .) NEQ reduce using rule 62 (literal -> INTEGER .) ISEQUAL reduce using rule 62 (literal -> INTEGER .) IN reduce using rule 62 (literal -> INTEGER .) NOT reduce using rule 62 (literal -> INTEGER .) AND reduce using rule 62 (literal -> INTEGER .) OR reduce using rule 62 (literal -> INTEGER .) ] reduce using rule 62 (literal -> INTEGER .) : reduce using rule 62 (literal -> INTEGER .) , reduce using rule 62 (literal -> INTEGER .) AUGOP reduce using rule 62 (literal -> INTEGER .) = reduce using rule 62 (literal -> INTEGER .) ) reduce using rule 62 (literal -> INTEGER .) BREAK reduce using rule 62 (literal -> INTEGER .) NEXT reduce using rule 62 (literal -> INTEGER .) { reduce using rule 62 (literal -> INTEGER .) PRINT reduce using rule 62 (literal -> INTEGER .) IF reduce using rule 62 (literal -> INTEGER .) FOR reduce using rule 62 (literal -> INTEGER .) WHERE reduce using rule 62 (literal -> INTEGER .) SWITCH reduce using rule 62 (literal -> INTEGER .) FUNCTION reduce using rule 62 (literal -> INTEGER .) DO reduce using rule 62 (literal -> INTEGER .) LOOP reduce using rule 62 (literal -> INTEGER .) WITH reduce using rule 62 (literal -> INTEGER .) ID reduce using rule 62 (literal -> INTEGER .) ITEM_TAG reduce using rule 62 (literal -> INTEGER .) INTEGER reduce using rule 62 (literal -> INTEGER .) HEXINT reduce using rule 62 (literal -> INTEGER .) OCTINT reduce using rule 62 (literal -> INTEGER .) BININT reduce using rule 62 (literal -> INTEGER .) IMAGINARY reduce using rule 62 (literal -> INTEGER .) STRPREFIX reduce using rule 62 (literal -> INTEGER .) SHORTSTRING reduce using rule 62 (literal -> INTEGER .) LONGSTRING reduce using rule 62 (literal -> INTEGER .) ` reduce using rule 62 (literal -> INTEGER .) ; reduce using rule 62 (literal -> INTEGER .) $end reduce using rule 62 (literal -> INTEGER .) } reduce using rule 62 (literal -> INTEGER .) ELSE reduce using rule 62 (literal -> INTEGER .) DEFAULT reduce using rule 62 (literal -> INTEGER .) CASE reduce using rule 62 (literal -> INTEGER .) state 56 (13) simple_stmt -> BREAK . ; reduce using rule 13 (simple_stmt -> BREAK .) BREAK reduce using rule 13 (simple_stmt -> BREAK .) NEXT reduce using rule 13 (simple_stmt -> BREAK .) IF reduce using rule 13 (simple_stmt -> BREAK .) FOR reduce using rule 13 (simple_stmt -> BREAK .) WHERE reduce using rule 13 (simple_stmt -> BREAK .) SWITCH reduce using rule 13 (simple_stmt -> BREAK .) FUNCTION reduce using rule 13 (simple_stmt -> BREAK .) PRINT reduce using rule 13 (simple_stmt -> BREAK .) DO reduce using rule 13 (simple_stmt -> BREAK .) LOOP reduce using rule 13 (simple_stmt -> BREAK .) WITH reduce using rule 13 (simple_stmt -> BREAK .) ( reduce using rule 13 (simple_stmt -> BREAK .) [ reduce using rule 13 (simple_stmt -> BREAK .) ID reduce using rule 13 (simple_stmt -> BREAK .) ITEM_TAG reduce using rule 13 (simple_stmt -> BREAK .) INTEGER reduce using rule 13 (simple_stmt -> BREAK .) HEXINT reduce using rule 13 (simple_stmt -> BREAK .) OCTINT reduce using rule 13 (simple_stmt -> BREAK .) BININT reduce using rule 13 (simple_stmt -> BREAK .) REAL reduce using rule 13 (simple_stmt -> BREAK .) IMAGINARY reduce using rule 13 (simple_stmt -> BREAK .) STRPREFIX reduce using rule 13 (simple_stmt -> BREAK .) SHORTSTRING reduce using rule 13 (simple_stmt -> BREAK .) LONGSTRING reduce using rule 13 (simple_stmt -> BREAK .) ` reduce using rule 13 (simple_stmt -> BREAK .) $end reduce using rule 13 (simple_stmt -> BREAK .) } reduce using rule 13 (simple_stmt -> BREAK .) ELSE reduce using rule 13 (simple_stmt -> BREAK .) DEFAULT reduce using rule 13 (simple_stmt -> BREAK .) CASE reduce using rule 13 (simple_stmt -> BREAK .) state 57 (63) literal -> HEXINT . POWER reduce using rule 63 (literal -> HEXINT .) [ reduce using rule 63 (literal -> HEXINT .) ( reduce using rule 63 (literal -> HEXINT .) . reduce using rule 63 (literal -> HEXINT .) REAL reduce using rule 63 (literal -> HEXINT .) * reduce using rule 63 (literal -> HEXINT .) / reduce using rule 63 (literal -> HEXINT .) ^ reduce using rule 63 (literal -> HEXINT .) + reduce using rule 63 (literal -> HEXINT .) - reduce using rule 63 (literal -> HEXINT .) < reduce using rule 63 (literal -> HEXINT .) > reduce using rule 63 (literal -> HEXINT .) GTE reduce using rule 63 (literal -> HEXINT .) LTE reduce using rule 63 (literal -> HEXINT .) NEQ reduce using rule 63 (literal -> HEXINT .) ISEQUAL reduce using rule 63 (literal -> HEXINT .) IN reduce using rule 63 (literal -> HEXINT .) NOT reduce using rule 63 (literal -> HEXINT .) AND reduce using rule 63 (literal -> HEXINT .) OR reduce using rule 63 (literal -> HEXINT .) ] reduce using rule 63 (literal -> HEXINT .) : reduce using rule 63 (literal -> HEXINT .) , reduce using rule 63 (literal -> HEXINT .) AUGOP reduce using rule 63 (literal -> HEXINT .) = reduce using rule 63 (literal -> HEXINT .) ) reduce using rule 63 (literal -> HEXINT .) BREAK reduce using rule 63 (literal -> HEXINT .) NEXT reduce using rule 63 (literal -> HEXINT .) { reduce using rule 63 (literal -> HEXINT .) PRINT reduce using rule 63 (literal -> HEXINT .) IF reduce using rule 63 (literal -> HEXINT .) FOR reduce using rule 63 (literal -> HEXINT .) WHERE reduce using rule 63 (literal -> HEXINT .) SWITCH reduce using rule 63 (literal -> HEXINT .) FUNCTION reduce using rule 63 (literal -> HEXINT .) DO reduce using rule 63 (literal -> HEXINT .) LOOP reduce using rule 63 (literal -> HEXINT .) WITH reduce using rule 63 (literal -> HEXINT .) ID reduce using rule 63 (literal -> HEXINT .) ITEM_TAG reduce using rule 63 (literal -> HEXINT .) INTEGER reduce using rule 63 (literal -> HEXINT .) HEXINT reduce using rule 63 (literal -> HEXINT .) OCTINT reduce using rule 63 (literal -> HEXINT .) BININT reduce using rule 63 (literal -> HEXINT .) IMAGINARY reduce using rule 63 (literal -> HEXINT .) STRPREFIX reduce using rule 63 (literal -> HEXINT .) SHORTSTRING reduce using rule 63 (literal -> HEXINT .) LONGSTRING reduce using rule 63 (literal -> HEXINT .) ` reduce using rule 63 (literal -> HEXINT .) ; reduce using rule 63 (literal -> HEXINT .) $end reduce using rule 63 (literal -> HEXINT .) } reduce using rule 63 (literal -> HEXINT .) ELSE reduce using rule 63 (literal -> HEXINT .) DEFAULT reduce using rule 63 (literal -> HEXINT .) CASE reduce using rule 63 (literal -> HEXINT .) state 58 (150) do_stmt_head -> DO . ID = expression , expression (151) do_stmt_head -> DO . ID = expression , expression , expression ID shift and go to state 115 state 59 (67) literal -> IMAGINARY . POWER reduce using rule 67 (literal -> IMAGINARY .) [ reduce using rule 67 (literal -> IMAGINARY .) ( reduce using rule 67 (literal -> IMAGINARY .) . reduce using rule 67 (literal -> IMAGINARY .) REAL reduce using rule 67 (literal -> IMAGINARY .) * reduce using rule 67 (literal -> IMAGINARY .) / reduce using rule 67 (literal -> IMAGINARY .) ^ reduce using rule 67 (literal -> IMAGINARY .) + reduce using rule 67 (literal -> IMAGINARY .) - reduce using rule 67 (literal -> IMAGINARY .) < reduce using rule 67 (literal -> IMAGINARY .) > reduce using rule 67 (literal -> IMAGINARY .) GTE reduce using rule 67 (literal -> IMAGINARY .) LTE reduce using rule 67 (literal -> IMAGINARY .) NEQ reduce using rule 67 (literal -> IMAGINARY .) ISEQUAL reduce using rule 67 (literal -> IMAGINARY .) IN reduce using rule 67 (literal -> IMAGINARY .) NOT reduce using rule 67 (literal -> IMAGINARY .) AND reduce using rule 67 (literal -> IMAGINARY .) OR reduce using rule 67 (literal -> IMAGINARY .) ] reduce using rule 67 (literal -> IMAGINARY .) : reduce using rule 67 (literal -> IMAGINARY .) , reduce using rule 67 (literal -> IMAGINARY .) AUGOP reduce using rule 67 (literal -> IMAGINARY .) = reduce using rule 67 (literal -> IMAGINARY .) ) reduce using rule 67 (literal -> IMAGINARY .) BREAK reduce using rule 67 (literal -> IMAGINARY .) NEXT reduce using rule 67 (literal -> IMAGINARY .) { reduce using rule 67 (literal -> IMAGINARY .) PRINT reduce using rule 67 (literal -> IMAGINARY .) IF reduce using rule 67 (literal -> IMAGINARY .) FOR reduce using rule 67 (literal -> IMAGINARY .) WHERE reduce using rule 67 (literal -> IMAGINARY .) SWITCH reduce using rule 67 (literal -> IMAGINARY .) FUNCTION reduce using rule 67 (literal -> IMAGINARY .) DO reduce using rule 67 (literal -> IMAGINARY .) LOOP reduce using rule 67 (literal -> IMAGINARY .) WITH reduce using rule 67 (literal -> IMAGINARY .) ID reduce using rule 67 (literal -> IMAGINARY .) ITEM_TAG reduce using rule 67 (literal -> IMAGINARY .) INTEGER reduce using rule 67 (literal -> IMAGINARY .) HEXINT reduce using rule 67 (literal -> IMAGINARY .) OCTINT reduce using rule 67 (literal -> IMAGINARY .) BININT reduce using rule 67 (literal -> IMAGINARY .) IMAGINARY reduce using rule 67 (literal -> IMAGINARY .) STRPREFIX reduce using rule 67 (literal -> IMAGINARY .) SHORTSTRING reduce using rule 67 (literal -> IMAGINARY .) LONGSTRING reduce using rule 67 (literal -> IMAGINARY .) ` reduce using rule 67 (literal -> IMAGINARY .) ; reduce using rule 67 (literal -> IMAGINARY .) $end reduce using rule 67 (literal -> IMAGINARY .) } reduce using rule 67 (literal -> IMAGINARY .) ELSE reduce using rule 67 (literal -> IMAGINARY .) DEFAULT reduce using rule 67 (literal -> IMAGINARY .) CASE reduce using rule 67 (literal -> IMAGINARY .) state 60 (56) atom -> ID . [ reduce using rule 56 (atom -> ID .) ( reduce using rule 56 (atom -> ID .) POWER reduce using rule 56 (atom -> ID .) . reduce using rule 56 (atom -> ID .) REAL reduce using rule 56 (atom -> ID .) ) reduce using rule 56 (atom -> ID .) , reduce using rule 56 (atom -> ID .) * reduce using rule 56 (atom -> ID .) / reduce using rule 56 (atom -> ID .) ^ reduce using rule 56 (atom -> ID .) + reduce using rule 56 (atom -> ID .) - reduce using rule 56 (atom -> ID .) < reduce using rule 56 (atom -> ID .) > reduce using rule 56 (atom -> ID .) GTE reduce using rule 56 (atom -> ID .) LTE reduce using rule 56 (atom -> ID .) NEQ reduce using rule 56 (atom -> ID .) ISEQUAL reduce using rule 56 (atom -> ID .) IN reduce using rule 56 (atom -> ID .) NOT reduce using rule 56 (atom -> ID .) AND reduce using rule 56 (atom -> ID .) OR reduce using rule 56 (atom -> ID .) BREAK reduce using rule 56 (atom -> ID .) NEXT reduce using rule 56 (atom -> ID .) { reduce using rule 56 (atom -> ID .) PRINT reduce using rule 56 (atom -> ID .) IF reduce using rule 56 (atom -> ID .) FOR reduce using rule 56 (atom -> ID .) WHERE reduce using rule 56 (atom -> ID .) SWITCH reduce using rule 56 (atom -> ID .) FUNCTION reduce using rule 56 (atom -> ID .) DO reduce using rule 56 (atom -> ID .) LOOP reduce using rule 56 (atom -> ID .) WITH reduce using rule 56 (atom -> ID .) ID reduce using rule 56 (atom -> ID .) ITEM_TAG reduce using rule 56 (atom -> ID .) INTEGER reduce using rule 56 (atom -> ID .) HEXINT reduce using rule 56 (atom -> ID .) OCTINT reduce using rule 56 (atom -> ID .) BININT reduce using rule 56 (atom -> ID .) IMAGINARY reduce using rule 56 (atom -> ID .) STRPREFIX reduce using rule 56 (atom -> ID .) SHORTSTRING reduce using rule 56 (atom -> ID .) LONGSTRING reduce using rule 56 (atom -> ID .) ` reduce using rule 56 (atom -> ID .) ] reduce using rule 56 (atom -> ID .) ; reduce using rule 56 (atom -> ID .) $end reduce using rule 56 (atom -> ID .) } reduce using rule 56 (atom -> ID .) ELSE reduce using rule 56 (atom -> ID .) DEFAULT reduce using rule 56 (atom -> ID .) CASE reduce using rule 56 (atom -> ID .) AUGOP reduce using rule 56 (atom -> ID .) = reduce using rule 56 (atom -> ID .) : reduce using rule 56 (atom -> ID .) state 61 (135) if_stmt -> IF . expression suite (18) expression -> . or_test (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 extended_slicing shift and go to state 34 list_display shift and go to state 22 or_test shift and go to state 86 expression shift and go to state 116 state 62 (4) statement -> stmt_list . (7) stmt_list -> stmt_list . ; simple_stmt (8) stmt_list -> stmt_list . ; simple_stmt ; } reduce using rule 4 (statement -> stmt_list .) BREAK reduce using rule 4 (statement -> stmt_list .) NEXT reduce using rule 4 (statement -> stmt_list .) IF reduce using rule 4 (statement -> stmt_list .) FOR reduce using rule 4 (statement -> stmt_list .) WHERE reduce using rule 4 (statement -> stmt_list .) SWITCH reduce using rule 4 (statement -> stmt_list .) FUNCTION reduce using rule 4 (statement -> stmt_list .) PRINT reduce using rule 4 (statement -> stmt_list .) DO reduce using rule 4 (statement -> stmt_list .) LOOP reduce using rule 4 (statement -> stmt_list .) WITH reduce using rule 4 (statement -> stmt_list .) ( reduce using rule 4 (statement -> stmt_list .) [ reduce using rule 4 (statement -> stmt_list .) ID reduce using rule 4 (statement -> stmt_list .) ITEM_TAG reduce using rule 4 (statement -> stmt_list .) INTEGER reduce using rule 4 (statement -> stmt_list .) HEXINT reduce using rule 4 (statement -> stmt_list .) OCTINT reduce using rule 4 (statement -> stmt_list .) BININT reduce using rule 4 (statement -> stmt_list .) REAL reduce using rule 4 (statement -> stmt_list .) IMAGINARY reduce using rule 4 (statement -> stmt_list .) STRPREFIX reduce using rule 4 (statement -> stmt_list .) SHORTSTRING reduce using rule 4 (statement -> stmt_list .) LONGSTRING reduce using rule 4 (statement -> stmt_list .) ` reduce using rule 4 (statement -> stmt_list .) $end reduce using rule 4 (statement -> stmt_list .) ; shift and go to state 117 state 63 (124) assignment_stmt -> target_list . = expression_list (126) target_list -> target_list . , target = shift and go to state 118 , shift and go to state 119 state 64 (60) item_tag -> ITEM_TAG . POWER reduce using rule 60 (item_tag -> ITEM_TAG .) [ reduce using rule 60 (item_tag -> ITEM_TAG .) ( reduce using rule 60 (item_tag -> ITEM_TAG .) . reduce using rule 60 (item_tag -> ITEM_TAG .) REAL reduce using rule 60 (item_tag -> ITEM_TAG .) * reduce using rule 60 (item_tag -> ITEM_TAG .) / reduce using rule 60 (item_tag -> ITEM_TAG .) ^ reduce using rule 60 (item_tag -> ITEM_TAG .) + reduce using rule 60 (item_tag -> ITEM_TAG .) - reduce using rule 60 (item_tag -> ITEM_TAG .) < reduce using rule 60 (item_tag -> ITEM_TAG .) > reduce using rule 60 (item_tag -> ITEM_TAG .) GTE reduce using rule 60 (item_tag -> ITEM_TAG .) LTE reduce using rule 60 (item_tag -> ITEM_TAG .) NEQ reduce using rule 60 (item_tag -> ITEM_TAG .) ISEQUAL reduce using rule 60 (item_tag -> ITEM_TAG .) IN reduce using rule 60 (item_tag -> ITEM_TAG .) NOT reduce using rule 60 (item_tag -> ITEM_TAG .) AND reduce using rule 60 (item_tag -> ITEM_TAG .) OR reduce using rule 60 (item_tag -> ITEM_TAG .) BREAK reduce using rule 60 (item_tag -> ITEM_TAG .) NEXT reduce using rule 60 (item_tag -> ITEM_TAG .) { reduce using rule 60 (item_tag -> ITEM_TAG .) PRINT reduce using rule 60 (item_tag -> ITEM_TAG .) IF reduce using rule 60 (item_tag -> ITEM_TAG .) FOR reduce using rule 60 (item_tag -> ITEM_TAG .) WHERE reduce using rule 60 (item_tag -> ITEM_TAG .) SWITCH reduce using rule 60 (item_tag -> ITEM_TAG .) FUNCTION reduce using rule 60 (item_tag -> ITEM_TAG .) DO reduce using rule 60 (item_tag -> ITEM_TAG .) LOOP reduce using rule 60 (item_tag -> ITEM_TAG .) WITH reduce using rule 60 (item_tag -> ITEM_TAG .) ID reduce using rule 60 (item_tag -> ITEM_TAG .) ITEM_TAG reduce using rule 60 (item_tag -> ITEM_TAG .) INTEGER reduce using rule 60 (item_tag -> ITEM_TAG .) HEXINT reduce using rule 60 (item_tag -> ITEM_TAG .) OCTINT reduce using rule 60 (item_tag -> ITEM_TAG .) BININT reduce using rule 60 (item_tag -> ITEM_TAG .) IMAGINARY reduce using rule 60 (item_tag -> ITEM_TAG .) STRPREFIX reduce using rule 60 (item_tag -> ITEM_TAG .) SHORTSTRING reduce using rule 60 (item_tag -> ITEM_TAG .) LONGSTRING reduce using rule 60 (item_tag -> ITEM_TAG .) ` reduce using rule 60 (item_tag -> ITEM_TAG .) , reduce using rule 60 (item_tag -> ITEM_TAG .) AUGOP reduce using rule 60 (item_tag -> ITEM_TAG .) = reduce using rule 60 (item_tag -> ITEM_TAG .) ] reduce using rule 60 (item_tag -> ITEM_TAG .) : reduce using rule 60 (item_tag -> ITEM_TAG .) ) reduce using rule 60 (item_tag -> ITEM_TAG .) ; reduce using rule 60 (item_tag -> ITEM_TAG .) $end reduce using rule 60 (item_tag -> ITEM_TAG .) } reduce using rule 60 (item_tag -> ITEM_TAG .) ELSE reduce using rule 60 (item_tag -> ITEM_TAG .) DEFAULT reduce using rule 60 (item_tag -> ITEM_TAG .) CASE reduce using rule 60 (item_tag -> ITEM_TAG .) state 65 (149) do_stmt -> do_stmt_head suite . BREAK reduce using rule 149 (do_stmt -> do_stmt_head suite .) NEXT reduce using rule 149 (do_stmt -> do_stmt_head suite .) IF reduce using rule 149 (do_stmt -> do_stmt_head suite .) FOR reduce using rule 149 (do_stmt -> do_stmt_head suite .) WHERE reduce using rule 149 (do_stmt -> do_stmt_head suite .) SWITCH reduce using rule 149 (do_stmt -> do_stmt_head suite .) FUNCTION reduce using rule 149 (do_stmt -> do_stmt_head suite .) PRINT reduce using rule 149 (do_stmt -> do_stmt_head suite .) DO reduce using rule 149 (do_stmt -> do_stmt_head suite .) LOOP reduce using rule 149 (do_stmt -> do_stmt_head suite .) WITH reduce using rule 149 (do_stmt -> do_stmt_head suite .) ( reduce using rule 149 (do_stmt -> do_stmt_head suite .) [ reduce using rule 149 (do_stmt -> do_stmt_head suite .) ID reduce using rule 149 (do_stmt -> do_stmt_head suite .) ITEM_TAG reduce using rule 149 (do_stmt -> do_stmt_head suite .) INTEGER reduce using rule 149 (do_stmt -> do_stmt_head suite .) HEXINT reduce using rule 149 (do_stmt -> do_stmt_head suite .) OCTINT reduce using rule 149 (do_stmt -> do_stmt_head suite .) BININT reduce using rule 149 (do_stmt -> do_stmt_head suite .) REAL reduce using rule 149 (do_stmt -> do_stmt_head suite .) IMAGINARY reduce using rule 149 (do_stmt -> do_stmt_head suite .) STRPREFIX reduce using rule 149 (do_stmt -> do_stmt_head suite .) SHORTSTRING reduce using rule 149 (do_stmt -> do_stmt_head suite .) LONGSTRING reduce using rule 149 (do_stmt -> do_stmt_head suite .) ` reduce using rule 149 (do_stmt -> do_stmt_head suite .) $end reduce using rule 149 (do_stmt -> do_stmt_head suite .) } reduce using rule 149 (do_stmt -> do_stmt_head suite .) ELSE reduce using rule 149 (do_stmt -> do_stmt_head suite .) DEFAULT reduce using rule 149 (do_stmt -> do_stmt_head suite .) CASE reduce using rule 149 (do_stmt -> do_stmt_head suite .) state 66 (137) suite -> simple_stmt . BREAK reduce using rule 137 (suite -> simple_stmt .) NEXT reduce using rule 137 (suite -> simple_stmt .) IF reduce using rule 137 (suite -> simple_stmt .) FOR reduce using rule 137 (suite -> simple_stmt .) WHERE reduce using rule 137 (suite -> simple_stmt .) SWITCH reduce using rule 137 (suite -> simple_stmt .) FUNCTION reduce using rule 137 (suite -> simple_stmt .) PRINT reduce using rule 137 (suite -> simple_stmt .) DO reduce using rule 137 (suite -> simple_stmt .) LOOP reduce using rule 137 (suite -> simple_stmt .) WITH reduce using rule 137 (suite -> simple_stmt .) ( reduce using rule 137 (suite -> simple_stmt .) [ reduce using rule 137 (suite -> simple_stmt .) ID reduce using rule 137 (suite -> simple_stmt .) ITEM_TAG reduce using rule 137 (suite -> simple_stmt .) INTEGER reduce using rule 137 (suite -> simple_stmt .) HEXINT reduce using rule 137 (suite -> simple_stmt .) OCTINT reduce using rule 137 (suite -> simple_stmt .) BININT reduce using rule 137 (suite -> simple_stmt .) REAL reduce using rule 137 (suite -> simple_stmt .) IMAGINARY reduce using rule 137 (suite -> simple_stmt .) STRPREFIX reduce using rule 137 (suite -> simple_stmt .) SHORTSTRING reduce using rule 137 (suite -> simple_stmt .) LONGSTRING reduce using rule 137 (suite -> simple_stmt .) ` reduce using rule 137 (suite -> simple_stmt .) $end reduce using rule 137 (suite -> simple_stmt .) } reduce using rule 137 (suite -> simple_stmt .) ELSE reduce using rule 137 (suite -> simple_stmt .) DEFAULT reduce using rule 137 (suite -> simple_stmt .) CASE reduce using rule 137 (suite -> simple_stmt .) state 67 (138) suite -> compound_stmt . BREAK reduce using rule 138 (suite -> compound_stmt .) NEXT reduce using rule 138 (suite -> compound_stmt .) IF reduce using rule 138 (suite -> compound_stmt .) FOR reduce using rule 138 (suite -> compound_stmt .) WHERE reduce using rule 138 (suite -> compound_stmt .) SWITCH reduce using rule 138 (suite -> compound_stmt .) FUNCTION reduce using rule 138 (suite -> compound_stmt .) PRINT reduce using rule 138 (suite -> compound_stmt .) DO reduce using rule 138 (suite -> compound_stmt .) LOOP reduce using rule 138 (suite -> compound_stmt .) WITH reduce using rule 138 (suite -> compound_stmt .) ( reduce using rule 138 (suite -> compound_stmt .) [ reduce using rule 138 (suite -> compound_stmt .) ID reduce using rule 138 (suite -> compound_stmt .) ITEM_TAG reduce using rule 138 (suite -> compound_stmt .) INTEGER reduce using rule 138 (suite -> compound_stmt .) HEXINT reduce using rule 138 (suite -> compound_stmt .) OCTINT reduce using rule 138 (suite -> compound_stmt .) BININT reduce using rule 138 (suite -> compound_stmt .) REAL reduce using rule 138 (suite -> compound_stmt .) IMAGINARY reduce using rule 138 (suite -> compound_stmt .) STRPREFIX reduce using rule 138 (suite -> compound_stmt .) SHORTSTRING reduce using rule 138 (suite -> compound_stmt .) LONGSTRING reduce using rule 138 (suite -> compound_stmt .) ` reduce using rule 138 (suite -> compound_stmt .) $end reduce using rule 138 (suite -> compound_stmt .) } reduce using rule 138 (suite -> compound_stmt .) ELSE reduce using rule 138 (suite -> compound_stmt .) DEFAULT reduce using rule 138 (suite -> compound_stmt .) CASE reduce using rule 138 (suite -> compound_stmt .) state 68 (139) suite -> open_brace . statement_block close_brace (142) statement_block -> . statement (143) statement_block -> . statement_block statement (4) statement -> . stmt_list (5) statement -> . compound_stmt (6) stmt_list -> . simple_stmt (7) stmt_list -> . stmt_list ; simple_stmt (8) stmt_list -> . stmt_list ; simple_stmt ; (127) compound_stmt -> . if_stmt (128) compound_stmt -> . for_stmt (129) compound_stmt -> . do_stmt (130) compound_stmt -> . loop_stmt (131) compound_stmt -> . with_stmt (132) compound_stmt -> . where_stmt (133) compound_stmt -> . switch_stmt (134) compound_stmt -> . funcdef (9) simple_stmt -> . assignment_stmt (10) simple_stmt -> . augmented_assignment_stmt (11) simple_stmt -> . fancy_drel_assignment_stmt (12) simple_stmt -> . print_stmt (13) simple_stmt -> . BREAK (14) simple_stmt -> . NEXT (135) if_stmt -> . IF expression suite (136) if_stmt -> . if_stmt ELSE suite (144) for_stmt -> . FOR target_list IN expression_list suite (149) do_stmt -> . do_stmt_head suite (145) loop_stmt -> . loop_head suite (152) with_stmt -> . with_head suite (154) where_stmt -> . WHERE expression suite ELSE suite (155) switch_stmt -> . SWITCH ID open_brace caselist DEFAULT suite close_brace (158) funcdef -> . FUNCTION ID ( arglist ) suite (124) assignment_stmt -> . target_list = expression_list (120) augmented_assignment_stmt -> . target AUGOP expression_list (121) fancy_drel_assignment_stmt -> . primary ( dotlist ) (15) print_stmt -> . PRINT expression (150) do_stmt_head -> . DO ID = expression , expression (151) do_stmt_head -> . DO ID = expression , expression , expression (146) loop_head -> . LOOP ID AS ID (147) loop_head -> . LOOP ID AS ID : ID (148) loop_head -> . LOOP ID AS ID : ID comp_operator ID (153) with_head -> . WITH ID AS ID (125) target_list -> . target (126) target_list -> . target_list , target (19) target -> . primary (20) target -> . ( target_list ) (21) target -> . [ target_list ] (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] BREAK shift and go to state 56 NEXT shift and go to state 7 IF shift and go to state 61 FOR shift and go to state 30 WHERE shift and go to state 19 SWITCH shift and go to state 46 FUNCTION shift and go to state 36 PRINT shift and go to state 28 DO shift and go to state 58 LOOP shift and go to state 25 WITH shift and go to state 5 ( shift and go to state 6 [ shift and go to state 38 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ` shift and go to state 20 fancy_drel_assignment_stmt shift and go to state 26 primary_att shift and go to state 41 atom shift and go to state 2 primary shift and go to state 42 statement_block shift and go to state 120 stringliteral shift and go to state 23 item_tag shift and go to state 52 switch_stmt shift and go to state 43 do_stmt_head shift and go to state 4 enclosure shift and go to state 29 parenth_form shift and go to state 8 simple_stmt shift and go to state 14 literal shift and go to state 45 assignment_stmt shift and go to state 32 call shift and go to state 47 statement shift and go to state 121 string_conversion shift and go to state 49 with_head shift and go to state 51 loop_head shift and go to state 12 do_stmt shift and go to state 13 compound_stmt shift and go to state 35 attributeref shift and go to state 9 simple_slicing shift and go to state 37 print_stmt shift and go to state 50 loop_stmt shift and go to state 15 slicing shift and go to state 17 target_list shift and go to state 63 for_stmt shift and go to state 18 augmented_assignment_stmt shift and go to state 27 funcdef shift and go to state 3 target shift and go to state 54 stmt_list shift and go to state 62 if_stmt shift and go to state 21 extended_slicing shift and go to state 34 list_display shift and go to state 22 where_stmt shift and go to state 39 with_stmt shift and go to state 24 subscription shift and go to state 53 state 69 (140) open_brace -> { . BREAK reduce using rule 140 (open_brace -> { .) NEXT reduce using rule 140 (open_brace -> { .) IF reduce using rule 140 (open_brace -> { .) FOR reduce using rule 140 (open_brace -> { .) WHERE reduce using rule 140 (open_brace -> { .) SWITCH reduce using rule 140 (open_brace -> { .) FUNCTION reduce using rule 140 (open_brace -> { .) PRINT reduce using rule 140 (open_brace -> { .) DO reduce using rule 140 (open_brace -> { .) LOOP reduce using rule 140 (open_brace -> { .) WITH reduce using rule 140 (open_brace -> { .) ( reduce using rule 140 (open_brace -> { .) [ reduce using rule 140 (open_brace -> { .) ID reduce using rule 140 (open_brace -> { .) ITEM_TAG reduce using rule 140 (open_brace -> { .) INTEGER reduce using rule 140 (open_brace -> { .) HEXINT reduce using rule 140 (open_brace -> { .) OCTINT reduce using rule 140 (open_brace -> { .) BININT reduce using rule 140 (open_brace -> { .) REAL reduce using rule 140 (open_brace -> { .) IMAGINARY reduce using rule 140 (open_brace -> { .) STRPREFIX reduce using rule 140 (open_brace -> { .) SHORTSTRING reduce using rule 140 (open_brace -> { .) LONGSTRING reduce using rule 140 (open_brace -> { .) ` reduce using rule 140 (open_brace -> { .) CASE reduce using rule 140 (open_brace -> { .) state 70 (153) with_head -> WITH ID . AS ID AS shift and go to state 122 state 71 (41) m_expr -> u_expr . * reduce using rule 41 (m_expr -> u_expr .) / reduce using rule 41 (m_expr -> u_expr .) ^ reduce using rule 41 (m_expr -> u_expr .) + reduce using rule 41 (m_expr -> u_expr .) - reduce using rule 41 (m_expr -> u_expr .) < reduce using rule 41 (m_expr -> u_expr .) > reduce using rule 41 (m_expr -> u_expr .) GTE reduce using rule 41 (m_expr -> u_expr .) LTE reduce using rule 41 (m_expr -> u_expr .) NEQ reduce using rule 41 (m_expr -> u_expr .) ISEQUAL reduce using rule 41 (m_expr -> u_expr .) IN reduce using rule 41 (m_expr -> u_expr .) NOT reduce using rule 41 (m_expr -> u_expr .) AND reduce using rule 41 (m_expr -> u_expr .) OR reduce using rule 41 (m_expr -> u_expr .) ; reduce using rule 41 (m_expr -> u_expr .) BREAK reduce using rule 41 (m_expr -> u_expr .) NEXT reduce using rule 41 (m_expr -> u_expr .) IF reduce using rule 41 (m_expr -> u_expr .) FOR reduce using rule 41 (m_expr -> u_expr .) WHERE reduce using rule 41 (m_expr -> u_expr .) SWITCH reduce using rule 41 (m_expr -> u_expr .) FUNCTION reduce using rule 41 (m_expr -> u_expr .) PRINT reduce using rule 41 (m_expr -> u_expr .) DO reduce using rule 41 (m_expr -> u_expr .) LOOP reduce using rule 41 (m_expr -> u_expr .) WITH reduce using rule 41 (m_expr -> u_expr .) ( reduce using rule 41 (m_expr -> u_expr .) [ reduce using rule 41 (m_expr -> u_expr .) ID reduce using rule 41 (m_expr -> u_expr .) ITEM_TAG reduce using rule 41 (m_expr -> u_expr .) INTEGER reduce using rule 41 (m_expr -> u_expr .) HEXINT reduce using rule 41 (m_expr -> u_expr .) OCTINT reduce using rule 41 (m_expr -> u_expr .) BININT reduce using rule 41 (m_expr -> u_expr .) REAL reduce using rule 41 (m_expr -> u_expr .) IMAGINARY reduce using rule 41 (m_expr -> u_expr .) STRPREFIX reduce using rule 41 (m_expr -> u_expr .) SHORTSTRING reduce using rule 41 (m_expr -> u_expr .) LONGSTRING reduce using rule 41 (m_expr -> u_expr .) ` reduce using rule 41 (m_expr -> u_expr .) $end reduce using rule 41 (m_expr -> u_expr .) } reduce using rule 41 (m_expr -> u_expr .) ELSE reduce using rule 41 (m_expr -> u_expr .) DEFAULT reduce using rule 41 (m_expr -> u_expr .) CASE reduce using rule 41 (m_expr -> u_expr .) ) reduce using rule 41 (m_expr -> u_expr .) , reduce using rule 41 (m_expr -> u_expr .) { reduce using rule 41 (m_expr -> u_expr .) ] reduce using rule 41 (m_expr -> u_expr .) : reduce using rule 41 (m_expr -> u_expr .) state 72 (27) not_test -> NOT . not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 not_test shift and go to state 123 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 power shift and go to state 75 a_expr shift and go to state 78 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 list_display shift and go to state 22 stringliteral shift and go to state 23 state 73 (19) target -> primary . (97) subscription -> primary . [ expression_list ] (115) call -> primary . ( ) (116) call -> primary . ( argument_list ) (94) attributeref -> primary . attribute_tag (100) simple_slicing -> primary . [ short_slice ] (105) extended_slicing -> primary . [ slice_list ] (48) power -> primary . (49) power -> primary . POWER u_expr (95) attribute_tag -> . . ID (96) attribute_tag -> . REAL ! reduce/reduce conflict for ) resolved using rule 19 (target -> primary .) ! reduce/reduce conflict for , resolved using rule 19 (target -> primary .) ! reduce/reduce conflict for ] resolved using rule 19 (target -> primary .) ) reduce using rule 19 (target -> primary .) , reduce using rule 19 (target -> primary .) ] reduce using rule 19 (target -> primary .) [ shift and go to state 111 ( shift and go to state 125 * reduce using rule 48 (power -> primary .) / reduce using rule 48 (power -> primary .) ^ reduce using rule 48 (power -> primary .) + reduce using rule 48 (power -> primary .) - reduce using rule 48 (power -> primary .) < reduce using rule 48 (power -> primary .) > reduce using rule 48 (power -> primary .) GTE reduce using rule 48 (power -> primary .) LTE reduce using rule 48 (power -> primary .) NEQ reduce using rule 48 (power -> primary .) ISEQUAL reduce using rule 48 (power -> primary .) IN reduce using rule 48 (power -> primary .) NOT reduce using rule 48 (power -> primary .) AND reduce using rule 48 (power -> primary .) OR reduce using rule 48 (power -> primary .) FOR reduce using rule 48 (power -> primary .) POWER shift and go to state 124 . shift and go to state 110 REAL shift and go to state 107 ! ) [ reduce using rule 48 (power -> primary .) ] ! , [ reduce using rule 48 (power -> primary .) ] ! ] [ reduce using rule 48 (power -> primary .) ] attribute_tag shift and go to state 108 state 74 (24) and_test -> not_test . AND reduce using rule 24 (and_test -> not_test .) OR reduce using rule 24 (and_test -> not_test .) ) reduce using rule 24 (and_test -> not_test .) , reduce using rule 24 (and_test -> not_test .) BREAK reduce using rule 24 (and_test -> not_test .) NEXT reduce using rule 24 (and_test -> not_test .) { reduce using rule 24 (and_test -> not_test .) PRINT reduce using rule 24 (and_test -> not_test .) IF reduce using rule 24 (and_test -> not_test .) FOR reduce using rule 24 (and_test -> not_test .) WHERE reduce using rule 24 (and_test -> not_test .) SWITCH reduce using rule 24 (and_test -> not_test .) FUNCTION reduce using rule 24 (and_test -> not_test .) ( reduce using rule 24 (and_test -> not_test .) [ reduce using rule 24 (and_test -> not_test .) DO reduce using rule 24 (and_test -> not_test .) LOOP reduce using rule 24 (and_test -> not_test .) WITH reduce using rule 24 (and_test -> not_test .) ID reduce using rule 24 (and_test -> not_test .) ITEM_TAG reduce using rule 24 (and_test -> not_test .) INTEGER reduce using rule 24 (and_test -> not_test .) HEXINT reduce using rule 24 (and_test -> not_test .) OCTINT reduce using rule 24 (and_test -> not_test .) BININT reduce using rule 24 (and_test -> not_test .) REAL reduce using rule 24 (and_test -> not_test .) IMAGINARY reduce using rule 24 (and_test -> not_test .) STRPREFIX reduce using rule 24 (and_test -> not_test .) SHORTSTRING reduce using rule 24 (and_test -> not_test .) LONGSTRING reduce using rule 24 (and_test -> not_test .) ` reduce using rule 24 (and_test -> not_test .) ; reduce using rule 24 (and_test -> not_test .) $end reduce using rule 24 (and_test -> not_test .) } reduce using rule 24 (and_test -> not_test .) ELSE reduce using rule 24 (and_test -> not_test .) DEFAULT reduce using rule 24 (and_test -> not_test .) CASE reduce using rule 24 (and_test -> not_test .) ] reduce using rule 24 (and_test -> not_test .) : reduce using rule 24 (and_test -> not_test .) IN reduce using rule 24 (and_test -> not_test .) state 75 (45) u_expr -> power . * reduce using rule 45 (u_expr -> power .) / reduce using rule 45 (u_expr -> power .) ^ reduce using rule 45 (u_expr -> power .) + reduce using rule 45 (u_expr -> power .) - reduce using rule 45 (u_expr -> power .) < reduce using rule 45 (u_expr -> power .) > reduce using rule 45 (u_expr -> power .) GTE reduce using rule 45 (u_expr -> power .) LTE reduce using rule 45 (u_expr -> power .) NEQ reduce using rule 45 (u_expr -> power .) ISEQUAL reduce using rule 45 (u_expr -> power .) IN reduce using rule 45 (u_expr -> power .) NOT reduce using rule 45 (u_expr -> power .) AND reduce using rule 45 (u_expr -> power .) OR reduce using rule 45 (u_expr -> power .) , reduce using rule 45 (u_expr -> power .) FOR reduce using rule 45 (u_expr -> power .) ] reduce using rule 45 (u_expr -> power .) ) reduce using rule 45 (u_expr -> power .) ` reduce using rule 45 (u_expr -> power .) ; reduce using rule 45 (u_expr -> power .) BREAK reduce using rule 45 (u_expr -> power .) NEXT reduce using rule 45 (u_expr -> power .) IF reduce using rule 45 (u_expr -> power .) WHERE reduce using rule 45 (u_expr -> power .) SWITCH reduce using rule 45 (u_expr -> power .) FUNCTION reduce using rule 45 (u_expr -> power .) PRINT reduce using rule 45 (u_expr -> power .) DO reduce using rule 45 (u_expr -> power .) LOOP reduce using rule 45 (u_expr -> power .) WITH reduce using rule 45 (u_expr -> power .) ( reduce using rule 45 (u_expr -> power .) [ reduce using rule 45 (u_expr -> power .) ID reduce using rule 45 (u_expr -> power .) ITEM_TAG reduce using rule 45 (u_expr -> power .) INTEGER reduce using rule 45 (u_expr -> power .) HEXINT reduce using rule 45 (u_expr -> power .) OCTINT reduce using rule 45 (u_expr -> power .) BININT reduce using rule 45 (u_expr -> power .) REAL reduce using rule 45 (u_expr -> power .) IMAGINARY reduce using rule 45 (u_expr -> power .) STRPREFIX reduce using rule 45 (u_expr -> power .) SHORTSTRING reduce using rule 45 (u_expr -> power .) LONGSTRING reduce using rule 45 (u_expr -> power .) $end reduce using rule 45 (u_expr -> power .) } reduce using rule 45 (u_expr -> power .) ELSE reduce using rule 45 (u_expr -> power .) DEFAULT reduce using rule 45 (u_expr -> power .) CASE reduce using rule 45 (u_expr -> power .) { reduce using rule 45 (u_expr -> power .) : reduce using rule 45 (u_expr -> power .) state 76 (76) parenth_form -> ( ) . POWER reduce using rule 76 (parenth_form -> ( ) .) [ reduce using rule 76 (parenth_form -> ( ) .) ( reduce using rule 76 (parenth_form -> ( ) .) . reduce using rule 76 (parenth_form -> ( ) .) REAL reduce using rule 76 (parenth_form -> ( ) .) * reduce using rule 76 (parenth_form -> ( ) .) / reduce using rule 76 (parenth_form -> ( ) .) ^ reduce using rule 76 (parenth_form -> ( ) .) + reduce using rule 76 (parenth_form -> ( ) .) - reduce using rule 76 (parenth_form -> ( ) .) < reduce using rule 76 (parenth_form -> ( ) .) > reduce using rule 76 (parenth_form -> ( ) .) GTE reduce using rule 76 (parenth_form -> ( ) .) LTE reduce using rule 76 (parenth_form -> ( ) .) NEQ reduce using rule 76 (parenth_form -> ( ) .) ISEQUAL reduce using rule 76 (parenth_form -> ( ) .) IN reduce using rule 76 (parenth_form -> ( ) .) NOT reduce using rule 76 (parenth_form -> ( ) .) AND reduce using rule 76 (parenth_form -> ( ) .) OR reduce using rule 76 (parenth_form -> ( ) .) ] reduce using rule 76 (parenth_form -> ( ) .) : reduce using rule 76 (parenth_form -> ( ) .) , reduce using rule 76 (parenth_form -> ( ) .) ) reduce using rule 76 (parenth_form -> ( ) .) BREAK reduce using rule 76 (parenth_form -> ( ) .) NEXT reduce using rule 76 (parenth_form -> ( ) .) { reduce using rule 76 (parenth_form -> ( ) .) PRINT reduce using rule 76 (parenth_form -> ( ) .) IF reduce using rule 76 (parenth_form -> ( ) .) FOR reduce using rule 76 (parenth_form -> ( ) .) WHERE reduce using rule 76 (parenth_form -> ( ) .) SWITCH reduce using rule 76 (parenth_form -> ( ) .) FUNCTION reduce using rule 76 (parenth_form -> ( ) .) DO reduce using rule 76 (parenth_form -> ( ) .) LOOP reduce using rule 76 (parenth_form -> ( ) .) WITH reduce using rule 76 (parenth_form -> ( ) .) ID reduce using rule 76 (parenth_form -> ( ) .) ITEM_TAG reduce using rule 76 (parenth_form -> ( ) .) INTEGER reduce using rule 76 (parenth_form -> ( ) .) HEXINT reduce using rule 76 (parenth_form -> ( ) .) OCTINT reduce using rule 76 (parenth_form -> ( ) .) BININT reduce using rule 76 (parenth_form -> ( ) .) IMAGINARY reduce using rule 76 (parenth_form -> ( ) .) STRPREFIX reduce using rule 76 (parenth_form -> ( ) .) SHORTSTRING reduce using rule 76 (parenth_form -> ( ) .) LONGSTRING reduce using rule 76 (parenth_form -> ( ) .) ` reduce using rule 76 (parenth_form -> ( ) .) ; reduce using rule 76 (parenth_form -> ( ) .) $end reduce using rule 76 (parenth_form -> ( ) .) } reduce using rule 76 (parenth_form -> ( ) .) ELSE reduce using rule 76 (parenth_form -> ( ) .) DEFAULT reduce using rule 76 (parenth_form -> ( ) .) CASE reduce using rule 76 (parenth_form -> ( ) .) AUGOP reduce using rule 76 (parenth_form -> ( ) .) = reduce using rule 76 (parenth_form -> ( ) .) state 77 (47) u_expr -> + . u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 enclosure shift and go to state 29 power shift and go to state 75 u_expr shift and go to state 126 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 simple_slicing shift and go to state 37 slicing shift and go to state 17 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 list_display shift and go to state 22 stringliteral shift and go to state 23 state 78 (28) comparison -> a_expr . (29) comparison -> a_expr . comp_operator a_expr (39) a_expr -> a_expr . + m_expr (40) a_expr -> a_expr . - m_expr (30) comp_operator -> . < (31) comp_operator -> . > (32) comp_operator -> . GTE (33) comp_operator -> . LTE (34) comp_operator -> . NEQ (35) comp_operator -> . ISEQUAL (36) comp_operator -> . IN (37) comp_operator -> . NOT IN ! shift/reduce conflict for IN resolved as shift AND reduce using rule 28 (comparison -> a_expr .) OR reduce using rule 28 (comparison -> a_expr .) ) reduce using rule 28 (comparison -> a_expr .) , reduce using rule 28 (comparison -> a_expr .) ] reduce using rule 28 (comparison -> a_expr .) FOR reduce using rule 28 (comparison -> a_expr .) IF reduce using rule 28 (comparison -> a_expr .) ; reduce using rule 28 (comparison -> a_expr .) BREAK reduce using rule 28 (comparison -> a_expr .) NEXT reduce using rule 28 (comparison -> a_expr .) WHERE reduce using rule 28 (comparison -> a_expr .) SWITCH reduce using rule 28 (comparison -> a_expr .) FUNCTION reduce using rule 28 (comparison -> a_expr .) PRINT reduce using rule 28 (comparison -> a_expr .) DO reduce using rule 28 (comparison -> a_expr .) LOOP reduce using rule 28 (comparison -> a_expr .) WITH reduce using rule 28 (comparison -> a_expr .) ( reduce using rule 28 (comparison -> a_expr .) [ reduce using rule 28 (comparison -> a_expr .) ID reduce using rule 28 (comparison -> a_expr .) ITEM_TAG reduce using rule 28 (comparison -> a_expr .) INTEGER reduce using rule 28 (comparison -> a_expr .) HEXINT reduce using rule 28 (comparison -> a_expr .) OCTINT reduce using rule 28 (comparison -> a_expr .) BININT reduce using rule 28 (comparison -> a_expr .) REAL reduce using rule 28 (comparison -> a_expr .) IMAGINARY reduce using rule 28 (comparison -> a_expr .) STRPREFIX reduce using rule 28 (comparison -> a_expr .) SHORTSTRING reduce using rule 28 (comparison -> a_expr .) LONGSTRING reduce using rule 28 (comparison -> a_expr .) ` reduce using rule 28 (comparison -> a_expr .) $end reduce using rule 28 (comparison -> a_expr .) } reduce using rule 28 (comparison -> a_expr .) ELSE reduce using rule 28 (comparison -> a_expr .) DEFAULT reduce using rule 28 (comparison -> a_expr .) CASE reduce using rule 28 (comparison -> a_expr .) { reduce using rule 28 (comparison -> a_expr .) : reduce using rule 28 (comparison -> a_expr .) + shift and go to state 129 - shift and go to state 131 < shift and go to state 136 > shift and go to state 137 GTE shift and go to state 132 LTE shift and go to state 127 NEQ shift and go to state 135 ISEQUAL shift and go to state 133 IN shift and go to state 130 NOT shift and go to state 134 ! IN [ reduce using rule 28 (comparison -> a_expr .) ] comp_operator shift and go to state 128 state 79 (46) u_expr -> - . u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 enclosure shift and go to state 29 power shift and go to state 75 u_expr shift and go to state 138 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 simple_slicing shift and go to state 37 slicing shift and go to state 17 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 list_display shift and go to state 22 stringliteral shift and go to state 23 state 80 (22) or_test -> and_test . (25) and_test -> and_test . AND not_test , reduce using rule 22 (or_test -> and_test .) OR reduce using rule 22 (or_test -> and_test .) FOR reduce using rule 22 (or_test -> and_test .) IF reduce using rule 22 (or_test -> and_test .) ] reduce using rule 22 (or_test -> and_test .) : reduce using rule 22 (or_test -> and_test .) IN reduce using rule 22 (or_test -> and_test .) ; reduce using rule 22 (or_test -> and_test .) BREAK reduce using rule 22 (or_test -> and_test .) NEXT reduce using rule 22 (or_test -> and_test .) WHERE reduce using rule 22 (or_test -> and_test .) SWITCH reduce using rule 22 (or_test -> and_test .) FUNCTION reduce using rule 22 (or_test -> and_test .) PRINT reduce using rule 22 (or_test -> and_test .) DO reduce using rule 22 (or_test -> and_test .) LOOP reduce using rule 22 (or_test -> and_test .) WITH reduce using rule 22 (or_test -> and_test .) ( reduce using rule 22 (or_test -> and_test .) [ reduce using rule 22 (or_test -> and_test .) ID reduce using rule 22 (or_test -> and_test .) ITEM_TAG reduce using rule 22 (or_test -> and_test .) INTEGER reduce using rule 22 (or_test -> and_test .) HEXINT reduce using rule 22 (or_test -> and_test .) OCTINT reduce using rule 22 (or_test -> and_test .) BININT reduce using rule 22 (or_test -> and_test .) REAL reduce using rule 22 (or_test -> and_test .) IMAGINARY reduce using rule 22 (or_test -> and_test .) STRPREFIX reduce using rule 22 (or_test -> and_test .) SHORTSTRING reduce using rule 22 (or_test -> and_test .) LONGSTRING reduce using rule 22 (or_test -> and_test .) ` reduce using rule 22 (or_test -> and_test .) $end reduce using rule 22 (or_test -> and_test .) } reduce using rule 22 (or_test -> and_test .) ELSE reduce using rule 22 (or_test -> and_test .) DEFAULT reduce using rule 22 (or_test -> and_test .) CASE reduce using rule 22 (or_test -> and_test .) ) reduce using rule 22 (or_test -> and_test .) { reduce using rule 22 (or_test -> and_test .) AND shift and go to state 139 state 81 (20) target -> ( target_list . ) (126) target_list -> target_list . , target ) shift and go to state 140 , shift and go to state 119 state 82 (38) a_expr -> m_expr . (42) m_expr -> m_expr . * u_expr (43) m_expr -> m_expr . / u_expr (44) m_expr -> m_expr . ^ u_expr + reduce using rule 38 (a_expr -> m_expr .) - reduce using rule 38 (a_expr -> m_expr .) < reduce using rule 38 (a_expr -> m_expr .) > reduce using rule 38 (a_expr -> m_expr .) GTE reduce using rule 38 (a_expr -> m_expr .) LTE reduce using rule 38 (a_expr -> m_expr .) NEQ reduce using rule 38 (a_expr -> m_expr .) ISEQUAL reduce using rule 38 (a_expr -> m_expr .) IN reduce using rule 38 (a_expr -> m_expr .) NOT reduce using rule 38 (a_expr -> m_expr .) AND reduce using rule 38 (a_expr -> m_expr .) OR reduce using rule 38 (a_expr -> m_expr .) ) reduce using rule 38 (a_expr -> m_expr .) , reduce using rule 38 (a_expr -> m_expr .) BREAK reduce using rule 38 (a_expr -> m_expr .) NEXT reduce using rule 38 (a_expr -> m_expr .) { reduce using rule 38 (a_expr -> m_expr .) PRINT reduce using rule 38 (a_expr -> m_expr .) IF reduce using rule 38 (a_expr -> m_expr .) FOR reduce using rule 38 (a_expr -> m_expr .) WHERE reduce using rule 38 (a_expr -> m_expr .) SWITCH reduce using rule 38 (a_expr -> m_expr .) FUNCTION reduce using rule 38 (a_expr -> m_expr .) ( reduce using rule 38 (a_expr -> m_expr .) [ reduce using rule 38 (a_expr -> m_expr .) DO reduce using rule 38 (a_expr -> m_expr .) LOOP reduce using rule 38 (a_expr -> m_expr .) WITH reduce using rule 38 (a_expr -> m_expr .) ID reduce using rule 38 (a_expr -> m_expr .) ITEM_TAG reduce using rule 38 (a_expr -> m_expr .) INTEGER reduce using rule 38 (a_expr -> m_expr .) HEXINT reduce using rule 38 (a_expr -> m_expr .) OCTINT reduce using rule 38 (a_expr -> m_expr .) BININT reduce using rule 38 (a_expr -> m_expr .) REAL reduce using rule 38 (a_expr -> m_expr .) IMAGINARY reduce using rule 38 (a_expr -> m_expr .) STRPREFIX reduce using rule 38 (a_expr -> m_expr .) SHORTSTRING reduce using rule 38 (a_expr -> m_expr .) LONGSTRING reduce using rule 38 (a_expr -> m_expr .) ` reduce using rule 38 (a_expr -> m_expr .) ; reduce using rule 38 (a_expr -> m_expr .) $end reduce using rule 38 (a_expr -> m_expr .) } reduce using rule 38 (a_expr -> m_expr .) ELSE reduce using rule 38 (a_expr -> m_expr .) DEFAULT reduce using rule 38 (a_expr -> m_expr .) CASE reduce using rule 38 (a_expr -> m_expr .) ] reduce using rule 38 (a_expr -> m_expr .) : reduce using rule 38 (a_expr -> m_expr .) * shift and go to state 141 / shift and go to state 142 ^ shift and go to state 143 state 83 (26) not_test -> comparison . AND reduce using rule 26 (not_test -> comparison .) OR reduce using rule 26 (not_test -> comparison .) ) reduce using rule 26 (not_test -> comparison .) , reduce using rule 26 (not_test -> comparison .) : reduce using rule 26 (not_test -> comparison .) ] reduce using rule 26 (not_test -> comparison .) FOR reduce using rule 26 (not_test -> comparison .) IF reduce using rule 26 (not_test -> comparison .) BREAK reduce using rule 26 (not_test -> comparison .) NEXT reduce using rule 26 (not_test -> comparison .) { reduce using rule 26 (not_test -> comparison .) PRINT reduce using rule 26 (not_test -> comparison .) WHERE reduce using rule 26 (not_test -> comparison .) SWITCH reduce using rule 26 (not_test -> comparison .) FUNCTION reduce using rule 26 (not_test -> comparison .) ( reduce using rule 26 (not_test -> comparison .) [ reduce using rule 26 (not_test -> comparison .) DO reduce using rule 26 (not_test -> comparison .) LOOP reduce using rule 26 (not_test -> comparison .) WITH reduce using rule 26 (not_test -> comparison .) ID reduce using rule 26 (not_test -> comparison .) ITEM_TAG reduce using rule 26 (not_test -> comparison .) INTEGER reduce using rule 26 (not_test -> comparison .) HEXINT reduce using rule 26 (not_test -> comparison .) OCTINT reduce using rule 26 (not_test -> comparison .) BININT reduce using rule 26 (not_test -> comparison .) REAL reduce using rule 26 (not_test -> comparison .) IMAGINARY reduce using rule 26 (not_test -> comparison .) STRPREFIX reduce using rule 26 (not_test -> comparison .) SHORTSTRING reduce using rule 26 (not_test -> comparison .) LONGSTRING reduce using rule 26 (not_test -> comparison .) ` reduce using rule 26 (not_test -> comparison .) ; reduce using rule 26 (not_test -> comparison .) $end reduce using rule 26 (not_test -> comparison .) } reduce using rule 26 (not_test -> comparison .) ELSE reduce using rule 26 (not_test -> comparison .) DEFAULT reduce using rule 26 (not_test -> comparison .) CASE reduce using rule 26 (not_test -> comparison .) IN reduce using rule 26 (not_test -> comparison .) state 84 (125) target_list -> target . ) reduce using rule 125 (target_list -> target .) , reduce using rule 125 (target_list -> target .) BREAK reduce using rule 125 (target_list -> target .) NEXT reduce using rule 125 (target_list -> target .) { reduce using rule 125 (target_list -> target .) PRINT reduce using rule 125 (target_list -> target .) IF reduce using rule 125 (target_list -> target .) FOR reduce using rule 125 (target_list -> target .) WHERE reduce using rule 125 (target_list -> target .) SWITCH reduce using rule 125 (target_list -> target .) FUNCTION reduce using rule 125 (target_list -> target .) ( reduce using rule 125 (target_list -> target .) [ reduce using rule 125 (target_list -> target .) DO reduce using rule 125 (target_list -> target .) LOOP reduce using rule 125 (target_list -> target .) WITH reduce using rule 125 (target_list -> target .) ID reduce using rule 125 (target_list -> target .) ITEM_TAG reduce using rule 125 (target_list -> target .) INTEGER reduce using rule 125 (target_list -> target .) HEXINT reduce using rule 125 (target_list -> target .) OCTINT reduce using rule 125 (target_list -> target .) BININT reduce using rule 125 (target_list -> target .) REAL reduce using rule 125 (target_list -> target .) IMAGINARY reduce using rule 125 (target_list -> target .) STRPREFIX reduce using rule 125 (target_list -> target .) SHORTSTRING reduce using rule 125 (target_list -> target .) LONGSTRING reduce using rule 125 (target_list -> target .) ` reduce using rule 125 (target_list -> target .) ] reduce using rule 125 (target_list -> target .) IN reduce using rule 125 (target_list -> target .) state 85 (75) parenth_form -> ( expression_list . ) (17) expression_list -> expression_list . , expression ) shift and go to state 144 , shift and go to state 145 state 86 (18) expression -> or_test . (23) or_test -> or_test . OR and_test ) reduce using rule 18 (expression -> or_test .) , reduce using rule 18 (expression -> or_test .) ; reduce using rule 18 (expression -> or_test .) BREAK reduce using rule 18 (expression -> or_test .) NEXT reduce using rule 18 (expression -> or_test .) IF reduce using rule 18 (expression -> or_test .) FOR reduce using rule 18 (expression -> or_test .) WHERE reduce using rule 18 (expression -> or_test .) SWITCH reduce using rule 18 (expression -> or_test .) FUNCTION reduce using rule 18 (expression -> or_test .) PRINT reduce using rule 18 (expression -> or_test .) DO reduce using rule 18 (expression -> or_test .) LOOP reduce using rule 18 (expression -> or_test .) WITH reduce using rule 18 (expression -> or_test .) ( reduce using rule 18 (expression -> or_test .) [ reduce using rule 18 (expression -> or_test .) ID reduce using rule 18 (expression -> or_test .) ITEM_TAG reduce using rule 18 (expression -> or_test .) INTEGER reduce using rule 18 (expression -> or_test .) HEXINT reduce using rule 18 (expression -> or_test .) OCTINT reduce using rule 18 (expression -> or_test .) BININT reduce using rule 18 (expression -> or_test .) REAL reduce using rule 18 (expression -> or_test .) IMAGINARY reduce using rule 18 (expression -> or_test .) STRPREFIX reduce using rule 18 (expression -> or_test .) SHORTSTRING reduce using rule 18 (expression -> or_test .) LONGSTRING reduce using rule 18 (expression -> or_test .) ` reduce using rule 18 (expression -> or_test .) $end reduce using rule 18 (expression -> or_test .) } reduce using rule 18 (expression -> or_test .) ELSE reduce using rule 18 (expression -> or_test .) DEFAULT reduce using rule 18 (expression -> or_test .) CASE reduce using rule 18 (expression -> or_test .) { reduce using rule 18 (expression -> or_test .) ] reduce using rule 18 (expression -> or_test .) : reduce using rule 18 (expression -> or_test .) IN reduce using rule 18 (expression -> or_test .) OR shift and go to state 146 state 87 (16) expression_list -> expression . ) reduce using rule 16 (expression_list -> expression .) , reduce using rule 16 (expression_list -> expression .) ` reduce using rule 16 (expression_list -> expression .) IN reduce using rule 16 (expression_list -> expression .) ; reduce using rule 16 (expression_list -> expression .) BREAK reduce using rule 16 (expression_list -> expression .) NEXT reduce using rule 16 (expression_list -> expression .) IF reduce using rule 16 (expression_list -> expression .) FOR reduce using rule 16 (expression_list -> expression .) WHERE reduce using rule 16 (expression_list -> expression .) SWITCH reduce using rule 16 (expression_list -> expression .) FUNCTION reduce using rule 16 (expression_list -> expression .) PRINT reduce using rule 16 (expression_list -> expression .) DO reduce using rule 16 (expression_list -> expression .) LOOP reduce using rule 16 (expression_list -> expression .) WITH reduce using rule 16 (expression_list -> expression .) ( reduce using rule 16 (expression_list -> expression .) [ reduce using rule 16 (expression_list -> expression .) ID reduce using rule 16 (expression_list -> expression .) ITEM_TAG reduce using rule 16 (expression_list -> expression .) INTEGER reduce using rule 16 (expression_list -> expression .) HEXINT reduce using rule 16 (expression_list -> expression .) OCTINT reduce using rule 16 (expression_list -> expression .) BININT reduce using rule 16 (expression_list -> expression .) REAL reduce using rule 16 (expression_list -> expression .) IMAGINARY reduce using rule 16 (expression_list -> expression .) STRPREFIX reduce using rule 16 (expression_list -> expression .) SHORTSTRING reduce using rule 16 (expression_list -> expression .) LONGSTRING reduce using rule 16 (expression_list -> expression .) $end reduce using rule 16 (expression_list -> expression .) } reduce using rule 16 (expression_list -> expression .) ELSE reduce using rule 16 (expression_list -> expression .) DEFAULT reduce using rule 16 (expression_list -> expression .) CASE reduce using rule 16 (expression_list -> expression .) { reduce using rule 16 (expression_list -> expression .) state 88 (68) stringliteral -> STRPREFIX SHORTSTRING . POWER reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) [ reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) ( reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) . reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) REAL reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) * reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) / reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) ^ reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) + reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) - reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) < reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) > reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) GTE reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) LTE reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) NEQ reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) ISEQUAL reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) IN reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) NOT reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) AND reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) OR reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) ) reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) , reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) BREAK reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) NEXT reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) { reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) PRINT reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) IF reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) FOR reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) WHERE reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) SWITCH reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) FUNCTION reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) DO reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) LOOP reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) WITH reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) ID reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) ITEM_TAG reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) INTEGER reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) HEXINT reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) OCTINT reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) BININT reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) IMAGINARY reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) STRPREFIX reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) SHORTSTRING reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) LONGSTRING reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) ` reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) ; reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) $end reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) } reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) ELSE reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) DEFAULT reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) CASE reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) ] reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) : reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) AUGOP reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) = reduce using rule 68 (stringliteral -> STRPREFIX SHORTSTRING .) state 89 (69) stringliteral -> STRPREFIX LONGSTRING . POWER reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) [ reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) ( reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) . reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) REAL reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) * reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) / reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) ^ reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) + reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) - reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) < reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) > reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) GTE reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) LTE reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) NEQ reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) ISEQUAL reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) IN reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) NOT reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) AND reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) OR reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) ) reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) , reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) BREAK reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) NEXT reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) { reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) PRINT reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) IF reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) FOR reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) WHERE reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) SWITCH reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) FUNCTION reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) DO reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) LOOP reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) WITH reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) ID reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) ITEM_TAG reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) INTEGER reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) HEXINT reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) OCTINT reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) BININT reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) IMAGINARY reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) STRPREFIX reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) SHORTSTRING reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) LONGSTRING reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) ` reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) ; reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) $end reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) } reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) ELSE reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) DEFAULT reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) CASE reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) ] reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) : reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) AUGOP reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) = reduce using rule 69 (stringliteral -> STRPREFIX LONGSTRING .) state 90 (3) input -> input statement . BREAK reduce using rule 3 (input -> input statement .) NEXT reduce using rule 3 (input -> input statement .) IF reduce using rule 3 (input -> input statement .) FOR reduce using rule 3 (input -> input statement .) WHERE reduce using rule 3 (input -> input statement .) SWITCH reduce using rule 3 (input -> input statement .) FUNCTION reduce using rule 3 (input -> input statement .) PRINT reduce using rule 3 (input -> input statement .) DO reduce using rule 3 (input -> input statement .) LOOP reduce using rule 3 (input -> input statement .) WITH reduce using rule 3 (input -> input statement .) ( reduce using rule 3 (input -> input statement .) [ reduce using rule 3 (input -> input statement .) ID reduce using rule 3 (input -> input statement .) ITEM_TAG reduce using rule 3 (input -> input statement .) INTEGER reduce using rule 3 (input -> input statement .) HEXINT reduce using rule 3 (input -> input statement .) OCTINT reduce using rule 3 (input -> input statement .) BININT reduce using rule 3 (input -> input statement .) REAL reduce using rule 3 (input -> input statement .) IMAGINARY reduce using rule 3 (input -> input statement .) STRPREFIX reduce using rule 3 (input -> input statement .) SHORTSTRING reduce using rule 3 (input -> input statement .) LONGSTRING reduce using rule 3 (input -> input statement .) ` reduce using rule 3 (input -> input statement .) $end reduce using rule 3 (input -> input statement .) state 91 (145) loop_stmt -> loop_head suite . BREAK reduce using rule 145 (loop_stmt -> loop_head suite .) NEXT reduce using rule 145 (loop_stmt -> loop_head suite .) IF reduce using rule 145 (loop_stmt -> loop_head suite .) FOR reduce using rule 145 (loop_stmt -> loop_head suite .) WHERE reduce using rule 145 (loop_stmt -> loop_head suite .) SWITCH reduce using rule 145 (loop_stmt -> loop_head suite .) FUNCTION reduce using rule 145 (loop_stmt -> loop_head suite .) PRINT reduce using rule 145 (loop_stmt -> loop_head suite .) DO reduce using rule 145 (loop_stmt -> loop_head suite .) LOOP reduce using rule 145 (loop_stmt -> loop_head suite .) WITH reduce using rule 145 (loop_stmt -> loop_head suite .) ( reduce using rule 145 (loop_stmt -> loop_head suite .) [ reduce using rule 145 (loop_stmt -> loop_head suite .) ID reduce using rule 145 (loop_stmt -> loop_head suite .) ITEM_TAG reduce using rule 145 (loop_stmt -> loop_head suite .) INTEGER reduce using rule 145 (loop_stmt -> loop_head suite .) HEXINT reduce using rule 145 (loop_stmt -> loop_head suite .) OCTINT reduce using rule 145 (loop_stmt -> loop_head suite .) BININT reduce using rule 145 (loop_stmt -> loop_head suite .) REAL reduce using rule 145 (loop_stmt -> loop_head suite .) IMAGINARY reduce using rule 145 (loop_stmt -> loop_head suite .) STRPREFIX reduce using rule 145 (loop_stmt -> loop_head suite .) SHORTSTRING reduce using rule 145 (loop_stmt -> loop_head suite .) LONGSTRING reduce using rule 145 (loop_stmt -> loop_head suite .) ` reduce using rule 145 (loop_stmt -> loop_head suite .) $end reduce using rule 145 (loop_stmt -> loop_head suite .) } reduce using rule 145 (loop_stmt -> loop_head suite .) ELSE reduce using rule 145 (loop_stmt -> loop_head suite .) DEFAULT reduce using rule 145 (loop_stmt -> loop_head suite .) CASE reduce using rule 145 (loop_stmt -> loop_head suite .) state 92 (48) power -> primary . (49) power -> primary . POWER u_expr (97) subscription -> primary . [ expression_list ] (115) call -> primary . ( ) (116) call -> primary . ( argument_list ) (94) attributeref -> primary . attribute_tag (100) simple_slicing -> primary . [ short_slice ] (105) extended_slicing -> primary . [ slice_list ] (95) attribute_tag -> . . ID (96) attribute_tag -> . REAL ! shift/reduce conflict for [ resolved as shift ! shift/reduce conflict for ( resolved as shift ! shift/reduce conflict for REAL resolved as shift * reduce using rule 48 (power -> primary .) / reduce using rule 48 (power -> primary .) ^ reduce using rule 48 (power -> primary .) + reduce using rule 48 (power -> primary .) - reduce using rule 48 (power -> primary .) < reduce using rule 48 (power -> primary .) > reduce using rule 48 (power -> primary .) GTE reduce using rule 48 (power -> primary .) LTE reduce using rule 48 (power -> primary .) NEQ reduce using rule 48 (power -> primary .) ISEQUAL reduce using rule 48 (power -> primary .) IN reduce using rule 48 (power -> primary .) NOT reduce using rule 48 (power -> primary .) AND reduce using rule 48 (power -> primary .) OR reduce using rule 48 (power -> primary .) ) reduce using rule 48 (power -> primary .) , reduce using rule 48 (power -> primary .) BREAK reduce using rule 48 (power -> primary .) NEXT reduce using rule 48 (power -> primary .) { reduce using rule 48 (power -> primary .) PRINT reduce using rule 48 (power -> primary .) IF reduce using rule 48 (power -> primary .) FOR reduce using rule 48 (power -> primary .) WHERE reduce using rule 48 (power -> primary .) SWITCH reduce using rule 48 (power -> primary .) FUNCTION reduce using rule 48 (power -> primary .) DO reduce using rule 48 (power -> primary .) LOOP reduce using rule 48 (power -> primary .) WITH reduce using rule 48 (power -> primary .) ID reduce using rule 48 (power -> primary .) ITEM_TAG reduce using rule 48 (power -> primary .) INTEGER reduce using rule 48 (power -> primary .) HEXINT reduce using rule 48 (power -> primary .) OCTINT reduce using rule 48 (power -> primary .) BININT reduce using rule 48 (power -> primary .) IMAGINARY reduce using rule 48 (power -> primary .) STRPREFIX reduce using rule 48 (power -> primary .) SHORTSTRING reduce using rule 48 (power -> primary .) LONGSTRING reduce using rule 48 (power -> primary .) ` reduce using rule 48 (power -> primary .) ; reduce using rule 48 (power -> primary .) $end reduce using rule 48 (power -> primary .) } reduce using rule 48 (power -> primary .) ELSE reduce using rule 48 (power -> primary .) DEFAULT reduce using rule 48 (power -> primary .) CASE reduce using rule 48 (power -> primary .) ] reduce using rule 48 (power -> primary .) : reduce using rule 48 (power -> primary .) POWER shift and go to state 124 [ shift and go to state 111 ( shift and go to state 125 . shift and go to state 110 REAL shift and go to state 107 ! ( [ reduce using rule 48 (power -> primary .) ] ! [ [ reduce using rule 48 (power -> primary .) ] ! REAL [ reduce using rule 48 (power -> primary .) ] attribute_tag shift and go to state 108 state 93 (78) list_display -> [ . listmaker ] (79) list_display -> [ . ] (80) listmaker -> . expression listmaker2 (81) listmaker -> . expression list_for (18) expression -> . or_test (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] ] shift and go to state 105 NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 listmaker shift and go to state 103 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 list_display shift and go to state 22 or_test shift and go to state 86 expression shift and go to state 106 state 94 (75) parenth_form -> ( . expression_list ) (76) parenth_form -> ( . ) (16) expression_list -> . expression (17) expression_list -> . expression_list , expression (18) expression -> . or_test (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] ) shift and go to state 76 NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 expression_list shift and go to state 85 list_display shift and go to state 22 or_test shift and go to state 86 expression shift and go to state 87 state 95 (154) where_stmt -> WHERE expression . suite ELSE suite (137) suite -> . simple_stmt (138) suite -> . compound_stmt (139) suite -> . open_brace statement_block close_brace (9) simple_stmt -> . assignment_stmt (10) simple_stmt -> . augmented_assignment_stmt (11) simple_stmt -> . fancy_drel_assignment_stmt (12) simple_stmt -> . print_stmt (13) simple_stmt -> . BREAK (14) simple_stmt -> . NEXT (127) compound_stmt -> . if_stmt (128) compound_stmt -> . for_stmt (129) compound_stmt -> . do_stmt (130) compound_stmt -> . loop_stmt (131) compound_stmt -> . with_stmt (132) compound_stmt -> . where_stmt (133) compound_stmt -> . switch_stmt (134) compound_stmt -> . funcdef (140) open_brace -> . { (124) assignment_stmt -> . target_list = expression_list (120) augmented_assignment_stmt -> . target AUGOP expression_list (121) fancy_drel_assignment_stmt -> . primary ( dotlist ) (15) print_stmt -> . PRINT expression (135) if_stmt -> . IF expression suite (136) if_stmt -> . if_stmt ELSE suite (144) for_stmt -> . FOR target_list IN expression_list suite (149) do_stmt -> . do_stmt_head suite (145) loop_stmt -> . loop_head suite (152) with_stmt -> . with_head suite (154) where_stmt -> . WHERE expression suite ELSE suite (155) switch_stmt -> . SWITCH ID open_brace caselist DEFAULT suite close_brace (158) funcdef -> . FUNCTION ID ( arglist ) suite (125) target_list -> . target (126) target_list -> . target_list , target (19) target -> . primary (20) target -> . ( target_list ) (21) target -> . [ target_list ] (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (150) do_stmt_head -> . DO ID = expression , expression (151) do_stmt_head -> . DO ID = expression , expression , expression (146) loop_head -> . LOOP ID AS ID (147) loop_head -> . LOOP ID AS ID : ID (148) loop_head -> . LOOP ID AS ID : ID comp_operator ID (153) with_head -> . WITH ID AS ID (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] BREAK shift and go to state 56 NEXT shift and go to state 7 { shift and go to state 69 PRINT shift and go to state 28 IF shift and go to state 61 FOR shift and go to state 30 WHERE shift and go to state 19 SWITCH shift and go to state 46 FUNCTION shift and go to state 36 ( shift and go to state 6 [ shift and go to state 38 DO shift and go to state 58 LOOP shift and go to state 25 WITH shift and go to state 5 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ` shift and go to state 20 fancy_drel_assignment_stmt shift and go to state 26 primary_att shift and go to state 41 atom shift and go to state 2 primary shift and go to state 42 stringliteral shift and go to state 23 item_tag shift and go to state 52 switch_stmt shift and go to state 43 do_stmt_head shift and go to state 4 enclosure shift and go to state 29 parenth_form shift and go to state 8 simple_stmt shift and go to state 66 literal shift and go to state 45 assignment_stmt shift and go to state 32 call shift and go to state 47 string_conversion shift and go to state 49 with_head shift and go to state 51 suite shift and go to state 147 loop_head shift and go to state 12 do_stmt shift and go to state 13 compound_stmt shift and go to state 67 attributeref shift and go to state 9 simple_slicing shift and go to state 37 print_stmt shift and go to state 50 loop_stmt shift and go to state 15 slicing shift and go to state 17 target_list shift and go to state 63 for_stmt shift and go to state 18 augmented_assignment_stmt shift and go to state 27 funcdef shift and go to state 3 target shift and go to state 54 if_stmt shift and go to state 21 extended_slicing shift and go to state 34 list_display shift and go to state 22 where_stmt shift and go to state 39 open_brace shift and go to state 68 with_stmt shift and go to state 24 subscription shift and go to state 53 state 96 (77) string_conversion -> ` expression_list . ` (17) expression_list -> expression_list . , expression ` shift and go to state 148 , shift and go to state 145 state 97 (136) if_stmt -> if_stmt ELSE . suite (137) suite -> . simple_stmt (138) suite -> . compound_stmt (139) suite -> . open_brace statement_block close_brace (9) simple_stmt -> . assignment_stmt (10) simple_stmt -> . augmented_assignment_stmt (11) simple_stmt -> . fancy_drel_assignment_stmt (12) simple_stmt -> . print_stmt (13) simple_stmt -> . BREAK (14) simple_stmt -> . NEXT (127) compound_stmt -> . if_stmt (128) compound_stmt -> . for_stmt (129) compound_stmt -> . do_stmt (130) compound_stmt -> . loop_stmt (131) compound_stmt -> . with_stmt (132) compound_stmt -> . where_stmt (133) compound_stmt -> . switch_stmt (134) compound_stmt -> . funcdef (140) open_brace -> . { (124) assignment_stmt -> . target_list = expression_list (120) augmented_assignment_stmt -> . target AUGOP expression_list (121) fancy_drel_assignment_stmt -> . primary ( dotlist ) (15) print_stmt -> . PRINT expression (135) if_stmt -> . IF expression suite (136) if_stmt -> . if_stmt ELSE suite (144) for_stmt -> . FOR target_list IN expression_list suite (149) do_stmt -> . do_stmt_head suite (145) loop_stmt -> . loop_head suite (152) with_stmt -> . with_head suite (154) where_stmt -> . WHERE expression suite ELSE suite (155) switch_stmt -> . SWITCH ID open_brace caselist DEFAULT suite close_brace (158) funcdef -> . FUNCTION ID ( arglist ) suite (125) target_list -> . target (126) target_list -> . target_list , target (19) target -> . primary (20) target -> . ( target_list ) (21) target -> . [ target_list ] (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (150) do_stmt_head -> . DO ID = expression , expression (151) do_stmt_head -> . DO ID = expression , expression , expression (146) loop_head -> . LOOP ID AS ID (147) loop_head -> . LOOP ID AS ID : ID (148) loop_head -> . LOOP ID AS ID : ID comp_operator ID (153) with_head -> . WITH ID AS ID (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] BREAK shift and go to state 56 NEXT shift and go to state 7 { shift and go to state 69 PRINT shift and go to state 28 IF shift and go to state 61 FOR shift and go to state 30 WHERE shift and go to state 19 SWITCH shift and go to state 46 FUNCTION shift and go to state 36 ( shift and go to state 6 [ shift and go to state 38 DO shift and go to state 58 LOOP shift and go to state 25 WITH shift and go to state 5 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ` shift and go to state 20 fancy_drel_assignment_stmt shift and go to state 26 primary_att shift and go to state 41 atom shift and go to state 2 primary shift and go to state 42 stringliteral shift and go to state 23 item_tag shift and go to state 52 switch_stmt shift and go to state 43 do_stmt_head shift and go to state 4 enclosure shift and go to state 29 parenth_form shift and go to state 8 simple_stmt shift and go to state 66 literal shift and go to state 45 assignment_stmt shift and go to state 32 call shift and go to state 47 string_conversion shift and go to state 49 with_head shift and go to state 51 suite shift and go to state 149 loop_head shift and go to state 12 do_stmt shift and go to state 13 compound_stmt shift and go to state 67 attributeref shift and go to state 9 simple_slicing shift and go to state 37 print_stmt shift and go to state 50 loop_stmt shift and go to state 15 slicing shift and go to state 17 target_list shift and go to state 63 for_stmt shift and go to state 18 augmented_assignment_stmt shift and go to state 27 funcdef shift and go to state 3 target shift and go to state 54 if_stmt shift and go to state 21 extended_slicing shift and go to state 34 list_display shift and go to state 22 where_stmt shift and go to state 39 open_brace shift and go to state 68 with_stmt shift and go to state 24 subscription shift and go to state 53 state 98 (146) loop_head -> LOOP ID . AS ID (147) loop_head -> LOOP ID . AS ID : ID (148) loop_head -> LOOP ID . AS ID : ID comp_operator ID AS shift and go to state 150 state 99 (15) print_stmt -> PRINT expression . ; reduce using rule 15 (print_stmt -> PRINT expression .) } reduce using rule 15 (print_stmt -> PRINT expression .) BREAK reduce using rule 15 (print_stmt -> PRINT expression .) NEXT reduce using rule 15 (print_stmt -> PRINT expression .) IF reduce using rule 15 (print_stmt -> PRINT expression .) FOR reduce using rule 15 (print_stmt -> PRINT expression .) WHERE reduce using rule 15 (print_stmt -> PRINT expression .) SWITCH reduce using rule 15 (print_stmt -> PRINT expression .) FUNCTION reduce using rule 15 (print_stmt -> PRINT expression .) PRINT reduce using rule 15 (print_stmt -> PRINT expression .) DO reduce using rule 15 (print_stmt -> PRINT expression .) LOOP reduce using rule 15 (print_stmt -> PRINT expression .) WITH reduce using rule 15 (print_stmt -> PRINT expression .) ( reduce using rule 15 (print_stmt -> PRINT expression .) [ reduce using rule 15 (print_stmt -> PRINT expression .) ID reduce using rule 15 (print_stmt -> PRINT expression .) ITEM_TAG reduce using rule 15 (print_stmt -> PRINT expression .) INTEGER reduce using rule 15 (print_stmt -> PRINT expression .) HEXINT reduce using rule 15 (print_stmt -> PRINT expression .) OCTINT reduce using rule 15 (print_stmt -> PRINT expression .) BININT reduce using rule 15 (print_stmt -> PRINT expression .) REAL reduce using rule 15 (print_stmt -> PRINT expression .) IMAGINARY reduce using rule 15 (print_stmt -> PRINT expression .) STRPREFIX reduce using rule 15 (print_stmt -> PRINT expression .) SHORTSTRING reduce using rule 15 (print_stmt -> PRINT expression .) LONGSTRING reduce using rule 15 (print_stmt -> PRINT expression .) ` reduce using rule 15 (print_stmt -> PRINT expression .) $end reduce using rule 15 (print_stmt -> PRINT expression .) ELSE reduce using rule 15 (print_stmt -> PRINT expression .) DEFAULT reduce using rule 15 (print_stmt -> PRINT expression .) CASE reduce using rule 15 (print_stmt -> PRINT expression .) state 100 (19) target -> primary . (97) subscription -> primary . [ expression_list ] (115) call -> primary . ( ) (116) call -> primary . ( argument_list ) (94) attributeref -> primary . attribute_tag (100) simple_slicing -> primary . [ short_slice ] (105) extended_slicing -> primary . [ slice_list ] (95) attribute_tag -> . . ID (96) attribute_tag -> . REAL ! shift/reduce conflict for [ resolved as shift ! shift/reduce conflict for ( resolved as shift ! shift/reduce conflict for REAL resolved as shift , reduce using rule 19 (target -> primary .) BREAK reduce using rule 19 (target -> primary .) NEXT reduce using rule 19 (target -> primary .) { reduce using rule 19 (target -> primary .) PRINT reduce using rule 19 (target -> primary .) IF reduce using rule 19 (target -> primary .) FOR reduce using rule 19 (target -> primary .) WHERE reduce using rule 19 (target -> primary .) SWITCH reduce using rule 19 (target -> primary .) FUNCTION reduce using rule 19 (target -> primary .) DO reduce using rule 19 (target -> primary .) LOOP reduce using rule 19 (target -> primary .) WITH reduce using rule 19 (target -> primary .) ID reduce using rule 19 (target -> primary .) ITEM_TAG reduce using rule 19 (target -> primary .) INTEGER reduce using rule 19 (target -> primary .) HEXINT reduce using rule 19 (target -> primary .) OCTINT reduce using rule 19 (target -> primary .) BININT reduce using rule 19 (target -> primary .) IMAGINARY reduce using rule 19 (target -> primary .) STRPREFIX reduce using rule 19 (target -> primary .) SHORTSTRING reduce using rule 19 (target -> primary .) LONGSTRING reduce using rule 19 (target -> primary .) ` reduce using rule 19 (target -> primary .) = reduce using rule 19 (target -> primary .) ) reduce using rule 19 (target -> primary .) IN reduce using rule 19 (target -> primary .) ] reduce using rule 19 (target -> primary .) [ shift and go to state 111 ( shift and go to state 125 . shift and go to state 110 REAL shift and go to state 107 ! ( [ reduce using rule 19 (target -> primary .) ] ! [ [ reduce using rule 19 (target -> primary .) ] ! REAL [ reduce using rule 19 (target -> primary .) ] attribute_tag shift and go to state 108 state 101 (144) for_stmt -> FOR target_list . IN expression_list suite (126) target_list -> target_list . , target IN shift and go to state 151 , shift and go to state 119 state 102 (158) funcdef -> FUNCTION ID . ( arglist ) suite ( shift and go to state 152 state 103 (78) list_display -> [ listmaker . ] ] shift and go to state 153 state 104 (21) target -> [ target_list . ] (126) target_list -> target_list . , target ] shift and go to state 154 , shift and go to state 119 state 105 (79) list_display -> [ ] . ( reduce using rule 79 (list_display -> [ ] .) [ reduce using rule 79 (list_display -> [ ] .) . reduce using rule 79 (list_display -> [ ] .) REAL reduce using rule 79 (list_display -> [ ] .) AUGOP reduce using rule 79 (list_display -> [ ] .) = reduce using rule 79 (list_display -> [ ] .) , reduce using rule 79 (list_display -> [ ] .) BREAK reduce using rule 79 (list_display -> [ ] .) NEXT reduce using rule 79 (list_display -> [ ] .) { reduce using rule 79 (list_display -> [ ] .) PRINT reduce using rule 79 (list_display -> [ ] .) IF reduce using rule 79 (list_display -> [ ] .) FOR reduce using rule 79 (list_display -> [ ] .) WHERE reduce using rule 79 (list_display -> [ ] .) SWITCH reduce using rule 79 (list_display -> [ ] .) FUNCTION reduce using rule 79 (list_display -> [ ] .) DO reduce using rule 79 (list_display -> [ ] .) LOOP reduce using rule 79 (list_display -> [ ] .) WITH reduce using rule 79 (list_display -> [ ] .) ID reduce using rule 79 (list_display -> [ ] .) ITEM_TAG reduce using rule 79 (list_display -> [ ] .) INTEGER reduce using rule 79 (list_display -> [ ] .) HEXINT reduce using rule 79 (list_display -> [ ] .) OCTINT reduce using rule 79 (list_display -> [ ] .) BININT reduce using rule 79 (list_display -> [ ] .) IMAGINARY reduce using rule 79 (list_display -> [ ] .) STRPREFIX reduce using rule 79 (list_display -> [ ] .) SHORTSTRING reduce using rule 79 (list_display -> [ ] .) LONGSTRING reduce using rule 79 (list_display -> [ ] .) ` reduce using rule 79 (list_display -> [ ] .) POWER reduce using rule 79 (list_display -> [ ] .) * reduce using rule 79 (list_display -> [ ] .) / reduce using rule 79 (list_display -> [ ] .) ^ reduce using rule 79 (list_display -> [ ] .) + reduce using rule 79 (list_display -> [ ] .) - reduce using rule 79 (list_display -> [ ] .) < reduce using rule 79 (list_display -> [ ] .) > reduce using rule 79 (list_display -> [ ] .) GTE reduce using rule 79 (list_display -> [ ] .) LTE reduce using rule 79 (list_display -> [ ] .) NEQ reduce using rule 79 (list_display -> [ ] .) ISEQUAL reduce using rule 79 (list_display -> [ ] .) IN reduce using rule 79 (list_display -> [ ] .) NOT reduce using rule 79 (list_display -> [ ] .) AND reduce using rule 79 (list_display -> [ ] .) OR reduce using rule 79 (list_display -> [ ] .) ) reduce using rule 79 (list_display -> [ ] .) ; reduce using rule 79 (list_display -> [ ] .) $end reduce using rule 79 (list_display -> [ ] .) } reduce using rule 79 (list_display -> [ ] .) ELSE reduce using rule 79 (list_display -> [ ] .) DEFAULT reduce using rule 79 (list_display -> [ ] .) CASE reduce using rule 79 (list_display -> [ ] .) ] reduce using rule 79 (list_display -> [ ] .) : reduce using rule 79 (list_display -> [ ] .) state 106 (80) listmaker -> expression . listmaker2 (81) listmaker -> expression . list_for (82) listmaker2 -> . , expression (83) listmaker2 -> . listmaker2 , expression (84) listmaker2 -> . (85) list_for -> . FOR expression_list IN testlist (86) list_for -> . FOR expression_list IN testlist list_iter ! shift/reduce conflict for , resolved as shift , shift and go to state 157 ] reduce using rule 84 (listmaker2 -> .) FOR shift and go to state 155 ! , [ reduce using rule 84 (listmaker2 -> .) ] listmaker2 shift and go to state 156 list_for shift and go to state 158 state 107 (96) attribute_tag -> REAL . POWER reduce using rule 96 (attribute_tag -> REAL .) [ reduce using rule 96 (attribute_tag -> REAL .) ( reduce using rule 96 (attribute_tag -> REAL .) . reduce using rule 96 (attribute_tag -> REAL .) REAL reduce using rule 96 (attribute_tag -> REAL .) * reduce using rule 96 (attribute_tag -> REAL .) / reduce using rule 96 (attribute_tag -> REAL .) ^ reduce using rule 96 (attribute_tag -> REAL .) + reduce using rule 96 (attribute_tag -> REAL .) - reduce using rule 96 (attribute_tag -> REAL .) < reduce using rule 96 (attribute_tag -> REAL .) > reduce using rule 96 (attribute_tag -> REAL .) GTE reduce using rule 96 (attribute_tag -> REAL .) LTE reduce using rule 96 (attribute_tag -> REAL .) NEQ reduce using rule 96 (attribute_tag -> REAL .) ISEQUAL reduce using rule 96 (attribute_tag -> REAL .) IN reduce using rule 96 (attribute_tag -> REAL .) NOT reduce using rule 96 (attribute_tag -> REAL .) AND reduce using rule 96 (attribute_tag -> REAL .) OR reduce using rule 96 (attribute_tag -> REAL .) BREAK reduce using rule 96 (attribute_tag -> REAL .) NEXT reduce using rule 96 (attribute_tag -> REAL .) { reduce using rule 96 (attribute_tag -> REAL .) PRINT reduce using rule 96 (attribute_tag -> REAL .) IF reduce using rule 96 (attribute_tag -> REAL .) FOR reduce using rule 96 (attribute_tag -> REAL .) WHERE reduce using rule 96 (attribute_tag -> REAL .) SWITCH reduce using rule 96 (attribute_tag -> REAL .) FUNCTION reduce using rule 96 (attribute_tag -> REAL .) DO reduce using rule 96 (attribute_tag -> REAL .) LOOP reduce using rule 96 (attribute_tag -> REAL .) WITH reduce using rule 96 (attribute_tag -> REAL .) ID reduce using rule 96 (attribute_tag -> REAL .) ITEM_TAG reduce using rule 96 (attribute_tag -> REAL .) INTEGER reduce using rule 96 (attribute_tag -> REAL .) HEXINT reduce using rule 96 (attribute_tag -> REAL .) OCTINT reduce using rule 96 (attribute_tag -> REAL .) BININT reduce using rule 96 (attribute_tag -> REAL .) IMAGINARY reduce using rule 96 (attribute_tag -> REAL .) STRPREFIX reduce using rule 96 (attribute_tag -> REAL .) SHORTSTRING reduce using rule 96 (attribute_tag -> REAL .) LONGSTRING reduce using rule 96 (attribute_tag -> REAL .) ` reduce using rule 96 (attribute_tag -> REAL .) , reduce using rule 96 (attribute_tag -> REAL .) ; reduce using rule 96 (attribute_tag -> REAL .) $end reduce using rule 96 (attribute_tag -> REAL .) } reduce using rule 96 (attribute_tag -> REAL .) ELSE reduce using rule 96 (attribute_tag -> REAL .) DEFAULT reduce using rule 96 (attribute_tag -> REAL .) CASE reduce using rule 96 (attribute_tag -> REAL .) ) reduce using rule 96 (attribute_tag -> REAL .) ] reduce using rule 96 (attribute_tag -> REAL .) : reduce using rule 96 (attribute_tag -> REAL .) AUGOP reduce using rule 96 (attribute_tag -> REAL .) = reduce using rule 96 (attribute_tag -> REAL .) state 108 (94) attributeref -> primary attribute_tag . [ reduce using rule 94 (attributeref -> primary attribute_tag .) ( reduce using rule 94 (attributeref -> primary attribute_tag .) . reduce using rule 94 (attributeref -> primary attribute_tag .) REAL reduce using rule 94 (attributeref -> primary attribute_tag .) IN reduce using rule 94 (attributeref -> primary attribute_tag .) , reduce using rule 94 (attributeref -> primary attribute_tag .) POWER reduce using rule 94 (attributeref -> primary attribute_tag .) * reduce using rule 94 (attributeref -> primary attribute_tag .) / reduce using rule 94 (attributeref -> primary attribute_tag .) ^ reduce using rule 94 (attributeref -> primary attribute_tag .) + reduce using rule 94 (attributeref -> primary attribute_tag .) - reduce using rule 94 (attributeref -> primary attribute_tag .) < reduce using rule 94 (attributeref -> primary attribute_tag .) > reduce using rule 94 (attributeref -> primary attribute_tag .) GTE reduce using rule 94 (attributeref -> primary attribute_tag .) LTE reduce using rule 94 (attributeref -> primary attribute_tag .) NEQ reduce using rule 94 (attributeref -> primary attribute_tag .) ISEQUAL reduce using rule 94 (attributeref -> primary attribute_tag .) NOT reduce using rule 94 (attributeref -> primary attribute_tag .) AND reduce using rule 94 (attributeref -> primary attribute_tag .) OR reduce using rule 94 (attributeref -> primary attribute_tag .) FOR reduce using rule 94 (attributeref -> primary attribute_tag .) IF reduce using rule 94 (attributeref -> primary attribute_tag .) ] reduce using rule 94 (attributeref -> primary attribute_tag .) ) reduce using rule 94 (attributeref -> primary attribute_tag .) AUGOP reduce using rule 94 (attributeref -> primary attribute_tag .) = reduce using rule 94 (attributeref -> primary attribute_tag .) BREAK reduce using rule 94 (attributeref -> primary attribute_tag .) NEXT reduce using rule 94 (attributeref -> primary attribute_tag .) { reduce using rule 94 (attributeref -> primary attribute_tag .) PRINT reduce using rule 94 (attributeref -> primary attribute_tag .) WHERE reduce using rule 94 (attributeref -> primary attribute_tag .) SWITCH reduce using rule 94 (attributeref -> primary attribute_tag .) FUNCTION reduce using rule 94 (attributeref -> primary attribute_tag .) DO reduce using rule 94 (attributeref -> primary attribute_tag .) LOOP reduce using rule 94 (attributeref -> primary attribute_tag .) WITH reduce using rule 94 (attributeref -> primary attribute_tag .) ID reduce using rule 94 (attributeref -> primary attribute_tag .) ITEM_TAG reduce using rule 94 (attributeref -> primary attribute_tag .) INTEGER reduce using rule 94 (attributeref -> primary attribute_tag .) HEXINT reduce using rule 94 (attributeref -> primary attribute_tag .) OCTINT reduce using rule 94 (attributeref -> primary attribute_tag .) BININT reduce using rule 94 (attributeref -> primary attribute_tag .) IMAGINARY reduce using rule 94 (attributeref -> primary attribute_tag .) STRPREFIX reduce using rule 94 (attributeref -> primary attribute_tag .) SHORTSTRING reduce using rule 94 (attributeref -> primary attribute_tag .) LONGSTRING reduce using rule 94 (attributeref -> primary attribute_tag .) ` reduce using rule 94 (attributeref -> primary attribute_tag .) ; reduce using rule 94 (attributeref -> primary attribute_tag .) $end reduce using rule 94 (attributeref -> primary attribute_tag .) } reduce using rule 94 (attributeref -> primary attribute_tag .) ELSE reduce using rule 94 (attributeref -> primary attribute_tag .) DEFAULT reduce using rule 94 (attributeref -> primary attribute_tag .) CASE reduce using rule 94 (attributeref -> primary attribute_tag .) : reduce using rule 94 (attributeref -> primary attribute_tag .) state 109 (121) fancy_drel_assignment_stmt -> primary ( . dotlist ) (115) call -> primary ( . ) (116) call -> primary ( . argument_list ) (122) dotlist -> . . ID = expression (123) dotlist -> . dotlist , . ID = expression (117) argument_list -> . func_arg (118) argument_list -> . argument_list , func_arg (119) func_arg -> . expression (18) expression -> . or_test (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] ) shift and go to state 161 . shift and go to state 162 NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 func_arg shift and go to state 159 enclosure shift and go to state 29 dotlist shift and go to state 160 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 argument_list shift and go to state 163 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 list_display shift and go to state 22 or_test shift and go to state 86 expression shift and go to state 164 state 110 (95) attribute_tag -> . . ID ID shift and go to state 165 state 111 (97) subscription -> primary [ . expression_list ] (100) simple_slicing -> primary [ . short_slice ] (105) extended_slicing -> primary [ . slice_list ] (16) expression_list -> . expression (17) expression_list -> . expression_list , expression (101) short_slice -> . : (102) short_slice -> . expression : expression (103) short_slice -> . : expression (104) short_slice -> . expression : (106) slice_list -> . slice_item (107) slice_list -> . slice_list , slice_item (18) expression -> . or_test (108) slice_item -> . expression (109) slice_item -> . proper_slice (110) slice_item -> . ELLIPSIS (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (111) proper_slice -> . short_slice (112) proper_slice -> . long_slice (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (113) long_slice -> . short_slice : (114) long_slice -> . short_slice : expression (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] : shift and go to state 169 ELLIPSIS shift and go to state 168 NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 enclosure shift and go to state 29 slice_list shift and go to state 166 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 short_slice shift and go to state 167 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 long_slice shift and go to state 170 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 proper_slice shift and go to state 171 expression_list shift and go to state 172 list_display shift and go to state 22 or_test shift and go to state 86 m_expr shift and go to state 82 slice_item shift and go to state 173 expression shift and go to state 174 state 112 (155) switch_stmt -> SWITCH ID . open_brace caselist DEFAULT suite close_brace (140) open_brace -> . { { shift and go to state 69 open_brace shift and go to state 175 state 113 (152) with_stmt -> with_head suite . } reduce using rule 152 (with_stmt -> with_head suite .) BREAK reduce using rule 152 (with_stmt -> with_head suite .) NEXT reduce using rule 152 (with_stmt -> with_head suite .) IF reduce using rule 152 (with_stmt -> with_head suite .) FOR reduce using rule 152 (with_stmt -> with_head suite .) WHERE reduce using rule 152 (with_stmt -> with_head suite .) SWITCH reduce using rule 152 (with_stmt -> with_head suite .) FUNCTION reduce using rule 152 (with_stmt -> with_head suite .) PRINT reduce using rule 152 (with_stmt -> with_head suite .) DO reduce using rule 152 (with_stmt -> with_head suite .) LOOP reduce using rule 152 (with_stmt -> with_head suite .) WITH reduce using rule 152 (with_stmt -> with_head suite .) ( reduce using rule 152 (with_stmt -> with_head suite .) [ reduce using rule 152 (with_stmt -> with_head suite .) ID reduce using rule 152 (with_stmt -> with_head suite .) ITEM_TAG reduce using rule 152 (with_stmt -> with_head suite .) INTEGER reduce using rule 152 (with_stmt -> with_head suite .) HEXINT reduce using rule 152 (with_stmt -> with_head suite .) OCTINT reduce using rule 152 (with_stmt -> with_head suite .) BININT reduce using rule 152 (with_stmt -> with_head suite .) REAL reduce using rule 152 (with_stmt -> with_head suite .) IMAGINARY reduce using rule 152 (with_stmt -> with_head suite .) STRPREFIX reduce using rule 152 (with_stmt -> with_head suite .) SHORTSTRING reduce using rule 152 (with_stmt -> with_head suite .) LONGSTRING reduce using rule 152 (with_stmt -> with_head suite .) ` reduce using rule 152 (with_stmt -> with_head suite .) $end reduce using rule 152 (with_stmt -> with_head suite .) ELSE reduce using rule 152 (with_stmt -> with_head suite .) DEFAULT reduce using rule 152 (with_stmt -> with_head suite .) CASE reduce using rule 152 (with_stmt -> with_head suite .) state 114 (120) augmented_assignment_stmt -> target AUGOP . expression_list (16) expression_list -> . expression (17) expression_list -> . expression_list , expression (18) expression -> . or_test (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 expression_list shift and go to state 176 list_display shift and go to state 22 or_test shift and go to state 86 expression shift and go to state 87 state 115 (150) do_stmt_head -> DO ID . = expression , expression (151) do_stmt_head -> DO ID . = expression , expression , expression = shift and go to state 177 state 116 (135) if_stmt -> IF expression . suite (137) suite -> . simple_stmt (138) suite -> . compound_stmt (139) suite -> . open_brace statement_block close_brace (9) simple_stmt -> . assignment_stmt (10) simple_stmt -> . augmented_assignment_stmt (11) simple_stmt -> . fancy_drel_assignment_stmt (12) simple_stmt -> . print_stmt (13) simple_stmt -> . BREAK (14) simple_stmt -> . NEXT (127) compound_stmt -> . if_stmt (128) compound_stmt -> . for_stmt (129) compound_stmt -> . do_stmt (130) compound_stmt -> . loop_stmt (131) compound_stmt -> . with_stmt (132) compound_stmt -> . where_stmt (133) compound_stmt -> . switch_stmt (134) compound_stmt -> . funcdef (140) open_brace -> . { (124) assignment_stmt -> . target_list = expression_list (120) augmented_assignment_stmt -> . target AUGOP expression_list (121) fancy_drel_assignment_stmt -> . primary ( dotlist ) (15) print_stmt -> . PRINT expression (135) if_stmt -> . IF expression suite (136) if_stmt -> . if_stmt ELSE suite (144) for_stmt -> . FOR target_list IN expression_list suite (149) do_stmt -> . do_stmt_head suite (145) loop_stmt -> . loop_head suite (152) with_stmt -> . with_head suite (154) where_stmt -> . WHERE expression suite ELSE suite (155) switch_stmt -> . SWITCH ID open_brace caselist DEFAULT suite close_brace (158) funcdef -> . FUNCTION ID ( arglist ) suite (125) target_list -> . target (126) target_list -> . target_list , target (19) target -> . primary (20) target -> . ( target_list ) (21) target -> . [ target_list ] (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (150) do_stmt_head -> . DO ID = expression , expression (151) do_stmt_head -> . DO ID = expression , expression , expression (146) loop_head -> . LOOP ID AS ID (147) loop_head -> . LOOP ID AS ID : ID (148) loop_head -> . LOOP ID AS ID : ID comp_operator ID (153) with_head -> . WITH ID AS ID (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] BREAK shift and go to state 56 NEXT shift and go to state 7 { shift and go to state 69 PRINT shift and go to state 28 IF shift and go to state 61 FOR shift and go to state 30 WHERE shift and go to state 19 SWITCH shift and go to state 46 FUNCTION shift and go to state 36 ( shift and go to state 6 [ shift and go to state 38 DO shift and go to state 58 LOOP shift and go to state 25 WITH shift and go to state 5 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ` shift and go to state 20 fancy_drel_assignment_stmt shift and go to state 26 primary_att shift and go to state 41 atom shift and go to state 2 primary shift and go to state 42 stringliteral shift and go to state 23 item_tag shift and go to state 52 switch_stmt shift and go to state 43 do_stmt_head shift and go to state 4 enclosure shift and go to state 29 parenth_form shift and go to state 8 simple_stmt shift and go to state 66 literal shift and go to state 45 assignment_stmt shift and go to state 32 call shift and go to state 47 string_conversion shift and go to state 49 with_head shift and go to state 51 suite shift and go to state 178 loop_head shift and go to state 12 do_stmt shift and go to state 13 compound_stmt shift and go to state 67 attributeref shift and go to state 9 simple_slicing shift and go to state 37 print_stmt shift and go to state 50 loop_stmt shift and go to state 15 slicing shift and go to state 17 target_list shift and go to state 63 for_stmt shift and go to state 18 augmented_assignment_stmt shift and go to state 27 funcdef shift and go to state 3 target shift and go to state 54 if_stmt shift and go to state 21 extended_slicing shift and go to state 34 list_display shift and go to state 22 where_stmt shift and go to state 39 open_brace shift and go to state 68 with_stmt shift and go to state 24 subscription shift and go to state 53 state 117 (7) stmt_list -> stmt_list ; . simple_stmt (8) stmt_list -> stmt_list ; . simple_stmt ; (9) simple_stmt -> . assignment_stmt (10) simple_stmt -> . augmented_assignment_stmt (11) simple_stmt -> . fancy_drel_assignment_stmt (12) simple_stmt -> . print_stmt (13) simple_stmt -> . BREAK (14) simple_stmt -> . NEXT (124) assignment_stmt -> . target_list = expression_list (120) augmented_assignment_stmt -> . target AUGOP expression_list (121) fancy_drel_assignment_stmt -> . primary ( dotlist ) (15) print_stmt -> . PRINT expression (125) target_list -> . target (126) target_list -> . target_list , target (19) target -> . primary (20) target -> . ( target_list ) (21) target -> . [ target_list ] (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] BREAK shift and go to state 56 NEXT shift and go to state 7 PRINT shift and go to state 28 ( shift and go to state 6 [ shift and go to state 38 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ` shift and go to state 20 fancy_drel_assignment_stmt shift and go to state 26 primary_att shift and go to state 41 primary shift and go to state 42 augmented_assignment_stmt shift and go to state 27 enclosure shift and go to state 29 parenth_form shift and go to state 8 print_stmt shift and go to state 50 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 assignment_stmt shift and go to state 32 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 simple_slicing shift and go to state 37 simple_stmt shift and go to state 179 slicing shift and go to state 17 target_list shift and go to state 63 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 target shift and go to state 54 list_display shift and go to state 22 stringliteral shift and go to state 23 state 118 (124) assignment_stmt -> target_list = . expression_list (16) expression_list -> . expression (17) expression_list -> . expression_list , expression (18) expression -> . or_test (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 expression_list shift and go to state 180 list_display shift and go to state 22 or_test shift and go to state 86 expression shift and go to state 87 state 119 (126) target_list -> target_list , . target (19) target -> . primary (20) target -> . ( target_list ) (21) target -> . [ target_list ] (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] ( shift and go to state 6 [ shift and go to state 38 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ` shift and go to state 20 primary_att shift and go to state 41 primary shift and go to state 100 enclosure shift and go to state 29 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 simple_slicing shift and go to state 37 slicing shift and go to state 17 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 target shift and go to state 181 list_display shift and go to state 22 stringliteral shift and go to state 23 state 120 (139) suite -> open_brace statement_block . close_brace (143) statement_block -> statement_block . statement (141) close_brace -> . } (4) statement -> . stmt_list (5) statement -> . compound_stmt (6) stmt_list -> . simple_stmt (7) stmt_list -> . stmt_list ; simple_stmt (8) stmt_list -> . stmt_list ; simple_stmt ; (127) compound_stmt -> . if_stmt (128) compound_stmt -> . for_stmt (129) compound_stmt -> . do_stmt (130) compound_stmt -> . loop_stmt (131) compound_stmt -> . with_stmt (132) compound_stmt -> . where_stmt (133) compound_stmt -> . switch_stmt (134) compound_stmt -> . funcdef (9) simple_stmt -> . assignment_stmt (10) simple_stmt -> . augmented_assignment_stmt (11) simple_stmt -> . fancy_drel_assignment_stmt (12) simple_stmt -> . print_stmt (13) simple_stmt -> . BREAK (14) simple_stmt -> . NEXT (135) if_stmt -> . IF expression suite (136) if_stmt -> . if_stmt ELSE suite (144) for_stmt -> . FOR target_list IN expression_list suite (149) do_stmt -> . do_stmt_head suite (145) loop_stmt -> . loop_head suite (152) with_stmt -> . with_head suite (154) where_stmt -> . WHERE expression suite ELSE suite (155) switch_stmt -> . SWITCH ID open_brace caselist DEFAULT suite close_brace (158) funcdef -> . FUNCTION ID ( arglist ) suite (124) assignment_stmt -> . target_list = expression_list (120) augmented_assignment_stmt -> . target AUGOP expression_list (121) fancy_drel_assignment_stmt -> . primary ( dotlist ) (15) print_stmt -> . PRINT expression (150) do_stmt_head -> . DO ID = expression , expression (151) do_stmt_head -> . DO ID = expression , expression , expression (146) loop_head -> . LOOP ID AS ID (147) loop_head -> . LOOP ID AS ID : ID (148) loop_head -> . LOOP ID AS ID : ID comp_operator ID (153) with_head -> . WITH ID AS ID (125) target_list -> . target (126) target_list -> . target_list , target (19) target -> . primary (20) target -> . ( target_list ) (21) target -> . [ target_list ] (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] } shift and go to state 184 BREAK shift and go to state 56 NEXT shift and go to state 7 IF shift and go to state 61 FOR shift and go to state 30 WHERE shift and go to state 19 SWITCH shift and go to state 46 FUNCTION shift and go to state 36 PRINT shift and go to state 28 DO shift and go to state 58 LOOP shift and go to state 25 WITH shift and go to state 5 ( shift and go to state 6 [ shift and go to state 38 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ` shift and go to state 20 fancy_drel_assignment_stmt shift and go to state 26 primary_att shift and go to state 41 atom shift and go to state 2 primary shift and go to state 42 stringliteral shift and go to state 23 item_tag shift and go to state 52 switch_stmt shift and go to state 43 do_stmt_head shift and go to state 4 enclosure shift and go to state 29 parenth_form shift and go to state 8 simple_stmt shift and go to state 14 literal shift and go to state 45 assignment_stmt shift and go to state 32 call shift and go to state 47 statement shift and go to state 183 string_conversion shift and go to state 49 with_head shift and go to state 51 loop_head shift and go to state 12 do_stmt shift and go to state 13 compound_stmt shift and go to state 35 attributeref shift and go to state 9 simple_slicing shift and go to state 37 print_stmt shift and go to state 50 loop_stmt shift and go to state 15 slicing shift and go to state 17 target_list shift and go to state 63 for_stmt shift and go to state 18 augmented_assignment_stmt shift and go to state 27 close_brace shift and go to state 182 funcdef shift and go to state 3 target shift and go to state 54 stmt_list shift and go to state 62 if_stmt shift and go to state 21 extended_slicing shift and go to state 34 list_display shift and go to state 22 where_stmt shift and go to state 39 with_stmt shift and go to state 24 subscription shift and go to state 53 state 121 (142) statement_block -> statement . } reduce using rule 142 (statement_block -> statement .) BREAK reduce using rule 142 (statement_block -> statement .) NEXT reduce using rule 142 (statement_block -> statement .) IF reduce using rule 142 (statement_block -> statement .) FOR reduce using rule 142 (statement_block -> statement .) WHERE reduce using rule 142 (statement_block -> statement .) SWITCH reduce using rule 142 (statement_block -> statement .) FUNCTION reduce using rule 142 (statement_block -> statement .) PRINT reduce using rule 142 (statement_block -> statement .) DO reduce using rule 142 (statement_block -> statement .) LOOP reduce using rule 142 (statement_block -> statement .) WITH reduce using rule 142 (statement_block -> statement .) ( reduce using rule 142 (statement_block -> statement .) [ reduce using rule 142 (statement_block -> statement .) ID reduce using rule 142 (statement_block -> statement .) ITEM_TAG reduce using rule 142 (statement_block -> statement .) INTEGER reduce using rule 142 (statement_block -> statement .) HEXINT reduce using rule 142 (statement_block -> statement .) OCTINT reduce using rule 142 (statement_block -> statement .) BININT reduce using rule 142 (statement_block -> statement .) REAL reduce using rule 142 (statement_block -> statement .) IMAGINARY reduce using rule 142 (statement_block -> statement .) STRPREFIX reduce using rule 142 (statement_block -> statement .) SHORTSTRING reduce using rule 142 (statement_block -> statement .) LONGSTRING reduce using rule 142 (statement_block -> statement .) ` reduce using rule 142 (statement_block -> statement .) state 122 (153) with_head -> WITH ID AS . ID ID shift and go to state 185 state 123 (27) not_test -> NOT not_test . AND reduce using rule 27 (not_test -> NOT not_test .) OR reduce using rule 27 (not_test -> NOT not_test .) ) reduce using rule 27 (not_test -> NOT not_test .) , reduce using rule 27 (not_test -> NOT not_test .) : reduce using rule 27 (not_test -> NOT not_test .) ] reduce using rule 27 (not_test -> NOT not_test .) FOR reduce using rule 27 (not_test -> NOT not_test .) IF reduce using rule 27 (not_test -> NOT not_test .) BREAK reduce using rule 27 (not_test -> NOT not_test .) NEXT reduce using rule 27 (not_test -> NOT not_test .) { reduce using rule 27 (not_test -> NOT not_test .) PRINT reduce using rule 27 (not_test -> NOT not_test .) WHERE reduce using rule 27 (not_test -> NOT not_test .) SWITCH reduce using rule 27 (not_test -> NOT not_test .) FUNCTION reduce using rule 27 (not_test -> NOT not_test .) ( reduce using rule 27 (not_test -> NOT not_test .) [ reduce using rule 27 (not_test -> NOT not_test .) DO reduce using rule 27 (not_test -> NOT not_test .) LOOP reduce using rule 27 (not_test -> NOT not_test .) WITH reduce using rule 27 (not_test -> NOT not_test .) ID reduce using rule 27 (not_test -> NOT not_test .) ITEM_TAG reduce using rule 27 (not_test -> NOT not_test .) INTEGER reduce using rule 27 (not_test -> NOT not_test .) HEXINT reduce using rule 27 (not_test -> NOT not_test .) OCTINT reduce using rule 27 (not_test -> NOT not_test .) BININT reduce using rule 27 (not_test -> NOT not_test .) REAL reduce using rule 27 (not_test -> NOT not_test .) IMAGINARY reduce using rule 27 (not_test -> NOT not_test .) STRPREFIX reduce using rule 27 (not_test -> NOT not_test .) SHORTSTRING reduce using rule 27 (not_test -> NOT not_test .) LONGSTRING reduce using rule 27 (not_test -> NOT not_test .) ` reduce using rule 27 (not_test -> NOT not_test .) ; reduce using rule 27 (not_test -> NOT not_test .) $end reduce using rule 27 (not_test -> NOT not_test .) } reduce using rule 27 (not_test -> NOT not_test .) ELSE reduce using rule 27 (not_test -> NOT not_test .) DEFAULT reduce using rule 27 (not_test -> NOT not_test .) CASE reduce using rule 27 (not_test -> NOT not_test .) IN reduce using rule 27 (not_test -> NOT not_test .) state 124 (49) power -> primary POWER . u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 enclosure shift and go to state 29 power shift and go to state 75 u_expr shift and go to state 186 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 simple_slicing shift and go to state 37 slicing shift and go to state 17 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 list_display shift and go to state 22 stringliteral shift and go to state 23 state 125 (115) call -> primary ( . ) (116) call -> primary ( . argument_list ) (117) argument_list -> . func_arg (118) argument_list -> . argument_list , func_arg (119) func_arg -> . expression (18) expression -> . or_test (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] ) shift and go to state 161 NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 func_arg shift and go to state 159 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 argument_list shift and go to state 163 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 list_display shift and go to state 22 or_test shift and go to state 86 expression shift and go to state 164 state 126 (47) u_expr -> + u_expr . * reduce using rule 47 (u_expr -> + u_expr .) / reduce using rule 47 (u_expr -> + u_expr .) ^ reduce using rule 47 (u_expr -> + u_expr .) + reduce using rule 47 (u_expr -> + u_expr .) - reduce using rule 47 (u_expr -> + u_expr .) < reduce using rule 47 (u_expr -> + u_expr .) > reduce using rule 47 (u_expr -> + u_expr .) GTE reduce using rule 47 (u_expr -> + u_expr .) LTE reduce using rule 47 (u_expr -> + u_expr .) NEQ reduce using rule 47 (u_expr -> + u_expr .) ISEQUAL reduce using rule 47 (u_expr -> + u_expr .) IN reduce using rule 47 (u_expr -> + u_expr .) NOT reduce using rule 47 (u_expr -> + u_expr .) AND reduce using rule 47 (u_expr -> + u_expr .) OR reduce using rule 47 (u_expr -> + u_expr .) , reduce using rule 47 (u_expr -> + u_expr .) FOR reduce using rule 47 (u_expr -> + u_expr .) ] reduce using rule 47 (u_expr -> + u_expr .) ) reduce using rule 47 (u_expr -> + u_expr .) ` reduce using rule 47 (u_expr -> + u_expr .) ; reduce using rule 47 (u_expr -> + u_expr .) BREAK reduce using rule 47 (u_expr -> + u_expr .) NEXT reduce using rule 47 (u_expr -> + u_expr .) IF reduce using rule 47 (u_expr -> + u_expr .) WHERE reduce using rule 47 (u_expr -> + u_expr .) SWITCH reduce using rule 47 (u_expr -> + u_expr .) FUNCTION reduce using rule 47 (u_expr -> + u_expr .) PRINT reduce using rule 47 (u_expr -> + u_expr .) DO reduce using rule 47 (u_expr -> + u_expr .) LOOP reduce using rule 47 (u_expr -> + u_expr .) WITH reduce using rule 47 (u_expr -> + u_expr .) ( reduce using rule 47 (u_expr -> + u_expr .) [ reduce using rule 47 (u_expr -> + u_expr .) ID reduce using rule 47 (u_expr -> + u_expr .) ITEM_TAG reduce using rule 47 (u_expr -> + u_expr .) INTEGER reduce using rule 47 (u_expr -> + u_expr .) HEXINT reduce using rule 47 (u_expr -> + u_expr .) OCTINT reduce using rule 47 (u_expr -> + u_expr .) BININT reduce using rule 47 (u_expr -> + u_expr .) REAL reduce using rule 47 (u_expr -> + u_expr .) IMAGINARY reduce using rule 47 (u_expr -> + u_expr .) STRPREFIX reduce using rule 47 (u_expr -> + u_expr .) SHORTSTRING reduce using rule 47 (u_expr -> + u_expr .) LONGSTRING reduce using rule 47 (u_expr -> + u_expr .) $end reduce using rule 47 (u_expr -> + u_expr .) } reduce using rule 47 (u_expr -> + u_expr .) ELSE reduce using rule 47 (u_expr -> + u_expr .) DEFAULT reduce using rule 47 (u_expr -> + u_expr .) CASE reduce using rule 47 (u_expr -> + u_expr .) { reduce using rule 47 (u_expr -> + u_expr .) : reduce using rule 47 (u_expr -> + u_expr .) state 127 (33) comp_operator -> LTE . - reduce using rule 33 (comp_operator -> LTE .) + reduce using rule 33 (comp_operator -> LTE .) ID reduce using rule 33 (comp_operator -> LTE .) ITEM_TAG reduce using rule 33 (comp_operator -> LTE .) INTEGER reduce using rule 33 (comp_operator -> LTE .) HEXINT reduce using rule 33 (comp_operator -> LTE .) OCTINT reduce using rule 33 (comp_operator -> LTE .) BININT reduce using rule 33 (comp_operator -> LTE .) REAL reduce using rule 33 (comp_operator -> LTE .) IMAGINARY reduce using rule 33 (comp_operator -> LTE .) STRPREFIX reduce using rule 33 (comp_operator -> LTE .) SHORTSTRING reduce using rule 33 (comp_operator -> LTE .) LONGSTRING reduce using rule 33 (comp_operator -> LTE .) ( reduce using rule 33 (comp_operator -> LTE .) ` reduce using rule 33 (comp_operator -> LTE .) [ reduce using rule 33 (comp_operator -> LTE .) state 128 (29) comparison -> a_expr comp_operator . a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 power shift and go to state 75 a_expr shift and go to state 187 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 list_display shift and go to state 22 stringliteral shift and go to state 23 state 129 (39) a_expr -> a_expr + . m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 enclosure shift and go to state 29 power shift and go to state 75 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 simple_slicing shift and go to state 37 slicing shift and go to state 17 m_expr shift and go to state 188 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 list_display shift and go to state 22 stringliteral shift and go to state 23 state 130 (36) comp_operator -> IN . - reduce using rule 36 (comp_operator -> IN .) + reduce using rule 36 (comp_operator -> IN .) ID reduce using rule 36 (comp_operator -> IN .) ITEM_TAG reduce using rule 36 (comp_operator -> IN .) INTEGER reduce using rule 36 (comp_operator -> IN .) HEXINT reduce using rule 36 (comp_operator -> IN .) OCTINT reduce using rule 36 (comp_operator -> IN .) BININT reduce using rule 36 (comp_operator -> IN .) REAL reduce using rule 36 (comp_operator -> IN .) IMAGINARY reduce using rule 36 (comp_operator -> IN .) STRPREFIX reduce using rule 36 (comp_operator -> IN .) SHORTSTRING reduce using rule 36 (comp_operator -> IN .) LONGSTRING reduce using rule 36 (comp_operator -> IN .) ( reduce using rule 36 (comp_operator -> IN .) ` reduce using rule 36 (comp_operator -> IN .) [ reduce using rule 36 (comp_operator -> IN .) state 131 (40) a_expr -> a_expr - . m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 enclosure shift and go to state 29 power shift and go to state 75 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 simple_slicing shift and go to state 37 slicing shift and go to state 17 m_expr shift and go to state 189 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 list_display shift and go to state 22 stringliteral shift and go to state 23 state 132 (32) comp_operator -> GTE . - reduce using rule 32 (comp_operator -> GTE .) + reduce using rule 32 (comp_operator -> GTE .) ID reduce using rule 32 (comp_operator -> GTE .) ITEM_TAG reduce using rule 32 (comp_operator -> GTE .) INTEGER reduce using rule 32 (comp_operator -> GTE .) HEXINT reduce using rule 32 (comp_operator -> GTE .) OCTINT reduce using rule 32 (comp_operator -> GTE .) BININT reduce using rule 32 (comp_operator -> GTE .) REAL reduce using rule 32 (comp_operator -> GTE .) IMAGINARY reduce using rule 32 (comp_operator -> GTE .) STRPREFIX reduce using rule 32 (comp_operator -> GTE .) SHORTSTRING reduce using rule 32 (comp_operator -> GTE .) LONGSTRING reduce using rule 32 (comp_operator -> GTE .) ( reduce using rule 32 (comp_operator -> GTE .) ` reduce using rule 32 (comp_operator -> GTE .) [ reduce using rule 32 (comp_operator -> GTE .) state 133 (35) comp_operator -> ISEQUAL . - reduce using rule 35 (comp_operator -> ISEQUAL .) + reduce using rule 35 (comp_operator -> ISEQUAL .) ID reduce using rule 35 (comp_operator -> ISEQUAL .) ITEM_TAG reduce using rule 35 (comp_operator -> ISEQUAL .) INTEGER reduce using rule 35 (comp_operator -> ISEQUAL .) HEXINT reduce using rule 35 (comp_operator -> ISEQUAL .) OCTINT reduce using rule 35 (comp_operator -> ISEQUAL .) BININT reduce using rule 35 (comp_operator -> ISEQUAL .) REAL reduce using rule 35 (comp_operator -> ISEQUAL .) IMAGINARY reduce using rule 35 (comp_operator -> ISEQUAL .) STRPREFIX reduce using rule 35 (comp_operator -> ISEQUAL .) SHORTSTRING reduce using rule 35 (comp_operator -> ISEQUAL .) LONGSTRING reduce using rule 35 (comp_operator -> ISEQUAL .) ( reduce using rule 35 (comp_operator -> ISEQUAL .) ` reduce using rule 35 (comp_operator -> ISEQUAL .) [ reduce using rule 35 (comp_operator -> ISEQUAL .) state 134 (37) comp_operator -> NOT . IN IN shift and go to state 190 state 135 (34) comp_operator -> NEQ . - reduce using rule 34 (comp_operator -> NEQ .) + reduce using rule 34 (comp_operator -> NEQ .) ID reduce using rule 34 (comp_operator -> NEQ .) ITEM_TAG reduce using rule 34 (comp_operator -> NEQ .) INTEGER reduce using rule 34 (comp_operator -> NEQ .) HEXINT reduce using rule 34 (comp_operator -> NEQ .) OCTINT reduce using rule 34 (comp_operator -> NEQ .) BININT reduce using rule 34 (comp_operator -> NEQ .) REAL reduce using rule 34 (comp_operator -> NEQ .) IMAGINARY reduce using rule 34 (comp_operator -> NEQ .) STRPREFIX reduce using rule 34 (comp_operator -> NEQ .) SHORTSTRING reduce using rule 34 (comp_operator -> NEQ .) LONGSTRING reduce using rule 34 (comp_operator -> NEQ .) ( reduce using rule 34 (comp_operator -> NEQ .) ` reduce using rule 34 (comp_operator -> NEQ .) [ reduce using rule 34 (comp_operator -> NEQ .) state 136 (30) comp_operator -> < . - reduce using rule 30 (comp_operator -> < .) + reduce using rule 30 (comp_operator -> < .) ID reduce using rule 30 (comp_operator -> < .) ITEM_TAG reduce using rule 30 (comp_operator -> < .) INTEGER reduce using rule 30 (comp_operator -> < .) HEXINT reduce using rule 30 (comp_operator -> < .) OCTINT reduce using rule 30 (comp_operator -> < .) BININT reduce using rule 30 (comp_operator -> < .) REAL reduce using rule 30 (comp_operator -> < .) IMAGINARY reduce using rule 30 (comp_operator -> < .) STRPREFIX reduce using rule 30 (comp_operator -> < .) SHORTSTRING reduce using rule 30 (comp_operator -> < .) LONGSTRING reduce using rule 30 (comp_operator -> < .) ( reduce using rule 30 (comp_operator -> < .) ` reduce using rule 30 (comp_operator -> < .) [ reduce using rule 30 (comp_operator -> < .) state 137 (31) comp_operator -> > . - reduce using rule 31 (comp_operator -> > .) + reduce using rule 31 (comp_operator -> > .) ID reduce using rule 31 (comp_operator -> > .) ITEM_TAG reduce using rule 31 (comp_operator -> > .) INTEGER reduce using rule 31 (comp_operator -> > .) HEXINT reduce using rule 31 (comp_operator -> > .) OCTINT reduce using rule 31 (comp_operator -> > .) BININT reduce using rule 31 (comp_operator -> > .) REAL reduce using rule 31 (comp_operator -> > .) IMAGINARY reduce using rule 31 (comp_operator -> > .) STRPREFIX reduce using rule 31 (comp_operator -> > .) SHORTSTRING reduce using rule 31 (comp_operator -> > .) LONGSTRING reduce using rule 31 (comp_operator -> > .) ( reduce using rule 31 (comp_operator -> > .) ` reduce using rule 31 (comp_operator -> > .) [ reduce using rule 31 (comp_operator -> > .) state 138 (46) u_expr -> - u_expr . * reduce using rule 46 (u_expr -> - u_expr .) / reduce using rule 46 (u_expr -> - u_expr .) ^ reduce using rule 46 (u_expr -> - u_expr .) + reduce using rule 46 (u_expr -> - u_expr .) - reduce using rule 46 (u_expr -> - u_expr .) < reduce using rule 46 (u_expr -> - u_expr .) > reduce using rule 46 (u_expr -> - u_expr .) GTE reduce using rule 46 (u_expr -> - u_expr .) LTE reduce using rule 46 (u_expr -> - u_expr .) NEQ reduce using rule 46 (u_expr -> - u_expr .) ISEQUAL reduce using rule 46 (u_expr -> - u_expr .) IN reduce using rule 46 (u_expr -> - u_expr .) NOT reduce using rule 46 (u_expr -> - u_expr .) AND reduce using rule 46 (u_expr -> - u_expr .) OR reduce using rule 46 (u_expr -> - u_expr .) , reduce using rule 46 (u_expr -> - u_expr .) FOR reduce using rule 46 (u_expr -> - u_expr .) ] reduce using rule 46 (u_expr -> - u_expr .) ) reduce using rule 46 (u_expr -> - u_expr .) ` reduce using rule 46 (u_expr -> - u_expr .) ; reduce using rule 46 (u_expr -> - u_expr .) BREAK reduce using rule 46 (u_expr -> - u_expr .) NEXT reduce using rule 46 (u_expr -> - u_expr .) IF reduce using rule 46 (u_expr -> - u_expr .) WHERE reduce using rule 46 (u_expr -> - u_expr .) SWITCH reduce using rule 46 (u_expr -> - u_expr .) FUNCTION reduce using rule 46 (u_expr -> - u_expr .) PRINT reduce using rule 46 (u_expr -> - u_expr .) DO reduce using rule 46 (u_expr -> - u_expr .) LOOP reduce using rule 46 (u_expr -> - u_expr .) WITH reduce using rule 46 (u_expr -> - u_expr .) ( reduce using rule 46 (u_expr -> - u_expr .) [ reduce using rule 46 (u_expr -> - u_expr .) ID reduce using rule 46 (u_expr -> - u_expr .) ITEM_TAG reduce using rule 46 (u_expr -> - u_expr .) INTEGER reduce using rule 46 (u_expr -> - u_expr .) HEXINT reduce using rule 46 (u_expr -> - u_expr .) OCTINT reduce using rule 46 (u_expr -> - u_expr .) BININT reduce using rule 46 (u_expr -> - u_expr .) REAL reduce using rule 46 (u_expr -> - u_expr .) IMAGINARY reduce using rule 46 (u_expr -> - u_expr .) STRPREFIX reduce using rule 46 (u_expr -> - u_expr .) SHORTSTRING reduce using rule 46 (u_expr -> - u_expr .) LONGSTRING reduce using rule 46 (u_expr -> - u_expr .) $end reduce using rule 46 (u_expr -> - u_expr .) } reduce using rule 46 (u_expr -> - u_expr .) ELSE reduce using rule 46 (u_expr -> - u_expr .) DEFAULT reduce using rule 46 (u_expr -> - u_expr .) CASE reduce using rule 46 (u_expr -> - u_expr .) { reduce using rule 46 (u_expr -> - u_expr .) : reduce using rule 46 (u_expr -> - u_expr .) state 139 (25) and_test -> and_test AND . not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 not_test shift and go to state 191 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 power shift and go to state 75 a_expr shift and go to state 78 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 list_display shift and go to state 22 stringliteral shift and go to state 23 state 140 (20) target -> ( target_list ) . AUGOP reduce using rule 20 (target -> ( target_list ) .) = reduce using rule 20 (target -> ( target_list ) .) , reduce using rule 20 (target -> ( target_list ) .) ) reduce using rule 20 (target -> ( target_list ) .) BREAK reduce using rule 20 (target -> ( target_list ) .) NEXT reduce using rule 20 (target -> ( target_list ) .) { reduce using rule 20 (target -> ( target_list ) .) PRINT reduce using rule 20 (target -> ( target_list ) .) IF reduce using rule 20 (target -> ( target_list ) .) FOR reduce using rule 20 (target -> ( target_list ) .) WHERE reduce using rule 20 (target -> ( target_list ) .) SWITCH reduce using rule 20 (target -> ( target_list ) .) FUNCTION reduce using rule 20 (target -> ( target_list ) .) ( reduce using rule 20 (target -> ( target_list ) .) [ reduce using rule 20 (target -> ( target_list ) .) DO reduce using rule 20 (target -> ( target_list ) .) LOOP reduce using rule 20 (target -> ( target_list ) .) WITH reduce using rule 20 (target -> ( target_list ) .) ID reduce using rule 20 (target -> ( target_list ) .) ITEM_TAG reduce using rule 20 (target -> ( target_list ) .) INTEGER reduce using rule 20 (target -> ( target_list ) .) HEXINT reduce using rule 20 (target -> ( target_list ) .) OCTINT reduce using rule 20 (target -> ( target_list ) .) BININT reduce using rule 20 (target -> ( target_list ) .) REAL reduce using rule 20 (target -> ( target_list ) .) IMAGINARY reduce using rule 20 (target -> ( target_list ) .) STRPREFIX reduce using rule 20 (target -> ( target_list ) .) SHORTSTRING reduce using rule 20 (target -> ( target_list ) .) LONGSTRING reduce using rule 20 (target -> ( target_list ) .) ` reduce using rule 20 (target -> ( target_list ) .) ] reduce using rule 20 (target -> ( target_list ) .) IN reduce using rule 20 (target -> ( target_list ) .) state 141 (42) m_expr -> m_expr * . u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 enclosure shift and go to state 29 power shift and go to state 75 u_expr shift and go to state 192 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 simple_slicing shift and go to state 37 slicing shift and go to state 17 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 list_display shift and go to state 22 stringliteral shift and go to state 23 state 142 (43) m_expr -> m_expr / . u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 enclosure shift and go to state 29 power shift and go to state 75 u_expr shift and go to state 193 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 simple_slicing shift and go to state 37 slicing shift and go to state 17 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 list_display shift and go to state 22 stringliteral shift and go to state 23 state 143 (44) m_expr -> m_expr ^ . u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 enclosure shift and go to state 29 power shift and go to state 75 u_expr shift and go to state 194 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 simple_slicing shift and go to state 37 slicing shift and go to state 17 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 list_display shift and go to state 22 stringliteral shift and go to state 23 state 144 (75) parenth_form -> ( expression_list ) . POWER reduce using rule 75 (parenth_form -> ( expression_list ) .) [ reduce using rule 75 (parenth_form -> ( expression_list ) .) ( reduce using rule 75 (parenth_form -> ( expression_list ) .) . reduce using rule 75 (parenth_form -> ( expression_list ) .) REAL reduce using rule 75 (parenth_form -> ( expression_list ) .) * reduce using rule 75 (parenth_form -> ( expression_list ) .) / reduce using rule 75 (parenth_form -> ( expression_list ) .) ^ reduce using rule 75 (parenth_form -> ( expression_list ) .) + reduce using rule 75 (parenth_form -> ( expression_list ) .) - reduce using rule 75 (parenth_form -> ( expression_list ) .) < reduce using rule 75 (parenth_form -> ( expression_list ) .) > reduce using rule 75 (parenth_form -> ( expression_list ) .) GTE reduce using rule 75 (parenth_form -> ( expression_list ) .) LTE reduce using rule 75 (parenth_form -> ( expression_list ) .) NEQ reduce using rule 75 (parenth_form -> ( expression_list ) .) ISEQUAL reduce using rule 75 (parenth_form -> ( expression_list ) .) IN reduce using rule 75 (parenth_form -> ( expression_list ) .) NOT reduce using rule 75 (parenth_form -> ( expression_list ) .) AND reduce using rule 75 (parenth_form -> ( expression_list ) .) OR reduce using rule 75 (parenth_form -> ( expression_list ) .) ] reduce using rule 75 (parenth_form -> ( expression_list ) .) : reduce using rule 75 (parenth_form -> ( expression_list ) .) , reduce using rule 75 (parenth_form -> ( expression_list ) .) ) reduce using rule 75 (parenth_form -> ( expression_list ) .) BREAK reduce using rule 75 (parenth_form -> ( expression_list ) .) NEXT reduce using rule 75 (parenth_form -> ( expression_list ) .) { reduce using rule 75 (parenth_form -> ( expression_list ) .) PRINT reduce using rule 75 (parenth_form -> ( expression_list ) .) IF reduce using rule 75 (parenth_form -> ( expression_list ) .) FOR reduce using rule 75 (parenth_form -> ( expression_list ) .) WHERE reduce using rule 75 (parenth_form -> ( expression_list ) .) SWITCH reduce using rule 75 (parenth_form -> ( expression_list ) .) FUNCTION reduce using rule 75 (parenth_form -> ( expression_list ) .) DO reduce using rule 75 (parenth_form -> ( expression_list ) .) LOOP reduce using rule 75 (parenth_form -> ( expression_list ) .) WITH reduce using rule 75 (parenth_form -> ( expression_list ) .) ID reduce using rule 75 (parenth_form -> ( expression_list ) .) ITEM_TAG reduce using rule 75 (parenth_form -> ( expression_list ) .) INTEGER reduce using rule 75 (parenth_form -> ( expression_list ) .) HEXINT reduce using rule 75 (parenth_form -> ( expression_list ) .) OCTINT reduce using rule 75 (parenth_form -> ( expression_list ) .) BININT reduce using rule 75 (parenth_form -> ( expression_list ) .) IMAGINARY reduce using rule 75 (parenth_form -> ( expression_list ) .) STRPREFIX reduce using rule 75 (parenth_form -> ( expression_list ) .) SHORTSTRING reduce using rule 75 (parenth_form -> ( expression_list ) .) LONGSTRING reduce using rule 75 (parenth_form -> ( expression_list ) .) ` reduce using rule 75 (parenth_form -> ( expression_list ) .) ; reduce using rule 75 (parenth_form -> ( expression_list ) .) $end reduce using rule 75 (parenth_form -> ( expression_list ) .) } reduce using rule 75 (parenth_form -> ( expression_list ) .) ELSE reduce using rule 75 (parenth_form -> ( expression_list ) .) DEFAULT reduce using rule 75 (parenth_form -> ( expression_list ) .) CASE reduce using rule 75 (parenth_form -> ( expression_list ) .) AUGOP reduce using rule 75 (parenth_form -> ( expression_list ) .) = reduce using rule 75 (parenth_form -> ( expression_list ) .) state 145 (17) expression_list -> expression_list , . expression (18) expression -> . or_test (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 list_display shift and go to state 22 or_test shift and go to state 86 expression shift and go to state 195 state 146 (23) or_test -> or_test OR . and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 196 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 list_display shift and go to state 22 state 147 (154) where_stmt -> WHERE expression suite . ELSE suite ELSE shift and go to state 197 state 148 (77) string_conversion -> ` expression_list ` . POWER reduce using rule 77 (string_conversion -> ` expression_list ` .) [ reduce using rule 77 (string_conversion -> ` expression_list ` .) ( reduce using rule 77 (string_conversion -> ` expression_list ` .) . reduce using rule 77 (string_conversion -> ` expression_list ` .) REAL reduce using rule 77 (string_conversion -> ` expression_list ` .) * reduce using rule 77 (string_conversion -> ` expression_list ` .) / reduce using rule 77 (string_conversion -> ` expression_list ` .) ^ reduce using rule 77 (string_conversion -> ` expression_list ` .) + reduce using rule 77 (string_conversion -> ` expression_list ` .) - reduce using rule 77 (string_conversion -> ` expression_list ` .) < reduce using rule 77 (string_conversion -> ` expression_list ` .) > reduce using rule 77 (string_conversion -> ` expression_list ` .) GTE reduce using rule 77 (string_conversion -> ` expression_list ` .) LTE reduce using rule 77 (string_conversion -> ` expression_list ` .) NEQ reduce using rule 77 (string_conversion -> ` expression_list ` .) ISEQUAL reduce using rule 77 (string_conversion -> ` expression_list ` .) IN reduce using rule 77 (string_conversion -> ` expression_list ` .) NOT reduce using rule 77 (string_conversion -> ` expression_list ` .) AND reduce using rule 77 (string_conversion -> ` expression_list ` .) OR reduce using rule 77 (string_conversion -> ` expression_list ` .) , reduce using rule 77 (string_conversion -> ` expression_list ` .) BREAK reduce using rule 77 (string_conversion -> ` expression_list ` .) NEXT reduce using rule 77 (string_conversion -> ` expression_list ` .) { reduce using rule 77 (string_conversion -> ` expression_list ` .) PRINT reduce using rule 77 (string_conversion -> ` expression_list ` .) IF reduce using rule 77 (string_conversion -> ` expression_list ` .) FOR reduce using rule 77 (string_conversion -> ` expression_list ` .) WHERE reduce using rule 77 (string_conversion -> ` expression_list ` .) SWITCH reduce using rule 77 (string_conversion -> ` expression_list ` .) FUNCTION reduce using rule 77 (string_conversion -> ` expression_list ` .) DO reduce using rule 77 (string_conversion -> ` expression_list ` .) LOOP reduce using rule 77 (string_conversion -> ` expression_list ` .) WITH reduce using rule 77 (string_conversion -> ` expression_list ` .) ID reduce using rule 77 (string_conversion -> ` expression_list ` .) ITEM_TAG reduce using rule 77 (string_conversion -> ` expression_list ` .) INTEGER reduce using rule 77 (string_conversion -> ` expression_list ` .) HEXINT reduce using rule 77 (string_conversion -> ` expression_list ` .) OCTINT reduce using rule 77 (string_conversion -> ` expression_list ` .) BININT reduce using rule 77 (string_conversion -> ` expression_list ` .) IMAGINARY reduce using rule 77 (string_conversion -> ` expression_list ` .) STRPREFIX reduce using rule 77 (string_conversion -> ` expression_list ` .) SHORTSTRING reduce using rule 77 (string_conversion -> ` expression_list ` .) LONGSTRING reduce using rule 77 (string_conversion -> ` expression_list ` .) ` reduce using rule 77 (string_conversion -> ` expression_list ` .) ) reduce using rule 77 (string_conversion -> ` expression_list ` .) ; reduce using rule 77 (string_conversion -> ` expression_list ` .) $end reduce using rule 77 (string_conversion -> ` expression_list ` .) } reduce using rule 77 (string_conversion -> ` expression_list ` .) ELSE reduce using rule 77 (string_conversion -> ` expression_list ` .) DEFAULT reduce using rule 77 (string_conversion -> ` expression_list ` .) CASE reduce using rule 77 (string_conversion -> ` expression_list ` .) ] reduce using rule 77 (string_conversion -> ` expression_list ` .) : reduce using rule 77 (string_conversion -> ` expression_list ` .) AUGOP reduce using rule 77 (string_conversion -> ` expression_list ` .) = reduce using rule 77 (string_conversion -> ` expression_list ` .) state 149 (136) if_stmt -> if_stmt ELSE suite . BREAK reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) NEXT reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) IF reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) FOR reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) WHERE reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) SWITCH reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) FUNCTION reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) PRINT reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) DO reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) LOOP reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) WITH reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) ( reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) [ reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) ID reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) ITEM_TAG reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) INTEGER reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) HEXINT reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) OCTINT reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) BININT reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) REAL reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) IMAGINARY reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) STRPREFIX reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) SHORTSTRING reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) LONGSTRING reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) ` reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) $end reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) } reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) ELSE reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) DEFAULT reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) CASE reduce using rule 136 (if_stmt -> if_stmt ELSE suite .) state 150 (146) loop_head -> LOOP ID AS . ID (147) loop_head -> LOOP ID AS . ID : ID (148) loop_head -> LOOP ID AS . ID : ID comp_operator ID ID shift and go to state 198 state 151 (144) for_stmt -> FOR target_list IN . expression_list suite (16) expression_list -> . expression (17) expression_list -> . expression_list , expression (18) expression -> . or_test (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 extended_slicing shift and go to state 34 expression_list shift and go to state 199 list_display shift and go to state 22 or_test shift and go to state 86 expression shift and go to state 87 state 152 (158) funcdef -> FUNCTION ID ( . arglist ) suite (159) arglist -> . ID : list_display (160) arglist -> . arglist , ID : list_display ID shift and go to state 201 arglist shift and go to state 200 state 153 (78) list_display -> [ listmaker ] . ( reduce using rule 78 (list_display -> [ listmaker ] .) [ reduce using rule 78 (list_display -> [ listmaker ] .) . reduce using rule 78 (list_display -> [ listmaker ] .) REAL reduce using rule 78 (list_display -> [ listmaker ] .) AUGOP reduce using rule 78 (list_display -> [ listmaker ] .) = reduce using rule 78 (list_display -> [ listmaker ] .) , reduce using rule 78 (list_display -> [ listmaker ] .) BREAK reduce using rule 78 (list_display -> [ listmaker ] .) NEXT reduce using rule 78 (list_display -> [ listmaker ] .) { reduce using rule 78 (list_display -> [ listmaker ] .) PRINT reduce using rule 78 (list_display -> [ listmaker ] .) IF reduce using rule 78 (list_display -> [ listmaker ] .) FOR reduce using rule 78 (list_display -> [ listmaker ] .) WHERE reduce using rule 78 (list_display -> [ listmaker ] .) SWITCH reduce using rule 78 (list_display -> [ listmaker ] .) FUNCTION reduce using rule 78 (list_display -> [ listmaker ] .) DO reduce using rule 78 (list_display -> [ listmaker ] .) LOOP reduce using rule 78 (list_display -> [ listmaker ] .) WITH reduce using rule 78 (list_display -> [ listmaker ] .) ID reduce using rule 78 (list_display -> [ listmaker ] .) ITEM_TAG reduce using rule 78 (list_display -> [ listmaker ] .) INTEGER reduce using rule 78 (list_display -> [ listmaker ] .) HEXINT reduce using rule 78 (list_display -> [ listmaker ] .) OCTINT reduce using rule 78 (list_display -> [ listmaker ] .) BININT reduce using rule 78 (list_display -> [ listmaker ] .) IMAGINARY reduce using rule 78 (list_display -> [ listmaker ] .) STRPREFIX reduce using rule 78 (list_display -> [ listmaker ] .) SHORTSTRING reduce using rule 78 (list_display -> [ listmaker ] .) LONGSTRING reduce using rule 78 (list_display -> [ listmaker ] .) ` reduce using rule 78 (list_display -> [ listmaker ] .) POWER reduce using rule 78 (list_display -> [ listmaker ] .) * reduce using rule 78 (list_display -> [ listmaker ] .) / reduce using rule 78 (list_display -> [ listmaker ] .) ^ reduce using rule 78 (list_display -> [ listmaker ] .) + reduce using rule 78 (list_display -> [ listmaker ] .) - reduce using rule 78 (list_display -> [ listmaker ] .) < reduce using rule 78 (list_display -> [ listmaker ] .) > reduce using rule 78 (list_display -> [ listmaker ] .) GTE reduce using rule 78 (list_display -> [ listmaker ] .) LTE reduce using rule 78 (list_display -> [ listmaker ] .) NEQ reduce using rule 78 (list_display -> [ listmaker ] .) ISEQUAL reduce using rule 78 (list_display -> [ listmaker ] .) IN reduce using rule 78 (list_display -> [ listmaker ] .) NOT reduce using rule 78 (list_display -> [ listmaker ] .) AND reduce using rule 78 (list_display -> [ listmaker ] .) OR reduce using rule 78 (list_display -> [ listmaker ] .) ) reduce using rule 78 (list_display -> [ listmaker ] .) ; reduce using rule 78 (list_display -> [ listmaker ] .) $end reduce using rule 78 (list_display -> [ listmaker ] .) } reduce using rule 78 (list_display -> [ listmaker ] .) ELSE reduce using rule 78 (list_display -> [ listmaker ] .) DEFAULT reduce using rule 78 (list_display -> [ listmaker ] .) CASE reduce using rule 78 (list_display -> [ listmaker ] .) ] reduce using rule 78 (list_display -> [ listmaker ] .) : reduce using rule 78 (list_display -> [ listmaker ] .) state 154 (21) target -> [ target_list ] . AUGOP reduce using rule 21 (target -> [ target_list ] .) = reduce using rule 21 (target -> [ target_list ] .) , reduce using rule 21 (target -> [ target_list ] .) ) reduce using rule 21 (target -> [ target_list ] .) BREAK reduce using rule 21 (target -> [ target_list ] .) NEXT reduce using rule 21 (target -> [ target_list ] .) { reduce using rule 21 (target -> [ target_list ] .) PRINT reduce using rule 21 (target -> [ target_list ] .) IF reduce using rule 21 (target -> [ target_list ] .) FOR reduce using rule 21 (target -> [ target_list ] .) WHERE reduce using rule 21 (target -> [ target_list ] .) SWITCH reduce using rule 21 (target -> [ target_list ] .) FUNCTION reduce using rule 21 (target -> [ target_list ] .) ( reduce using rule 21 (target -> [ target_list ] .) [ reduce using rule 21 (target -> [ target_list ] .) DO reduce using rule 21 (target -> [ target_list ] .) LOOP reduce using rule 21 (target -> [ target_list ] .) WITH reduce using rule 21 (target -> [ target_list ] .) ID reduce using rule 21 (target -> [ target_list ] .) ITEM_TAG reduce using rule 21 (target -> [ target_list ] .) INTEGER reduce using rule 21 (target -> [ target_list ] .) HEXINT reduce using rule 21 (target -> [ target_list ] .) OCTINT reduce using rule 21 (target -> [ target_list ] .) BININT reduce using rule 21 (target -> [ target_list ] .) REAL reduce using rule 21 (target -> [ target_list ] .) IMAGINARY reduce using rule 21 (target -> [ target_list ] .) STRPREFIX reduce using rule 21 (target -> [ target_list ] .) SHORTSTRING reduce using rule 21 (target -> [ target_list ] .) LONGSTRING reduce using rule 21 (target -> [ target_list ] .) ` reduce using rule 21 (target -> [ target_list ] .) ] reduce using rule 21 (target -> [ target_list ] .) IN reduce using rule 21 (target -> [ target_list ] .) state 155 (85) list_for -> FOR . expression_list IN testlist (86) list_for -> FOR . expression_list IN testlist list_iter (16) expression_list -> . expression (17) expression_list -> . expression_list , expression (18) expression -> . or_test (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 string_conversion shift and go to state 49 call shift and go to state 47 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 extended_slicing shift and go to state 34 expression_list shift and go to state 202 list_display shift and go to state 22 or_test shift and go to state 86 expression shift and go to state 87 state 156 (80) listmaker -> expression listmaker2 . (83) listmaker2 -> listmaker2 . , expression ] reduce using rule 80 (listmaker -> expression listmaker2 .) , shift and go to state 203 state 157 (82) listmaker2 -> , . expression (18) expression -> . or_test (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 list_display shift and go to state 22 or_test shift and go to state 86 expression shift and go to state 204 state 158 (81) listmaker -> expression list_for . ] reduce using rule 81 (listmaker -> expression list_for .) state 159 (117) argument_list -> func_arg . ) reduce using rule 117 (argument_list -> func_arg .) , reduce using rule 117 (argument_list -> func_arg .) state 160 (121) fancy_drel_assignment_stmt -> primary ( dotlist . ) (123) dotlist -> dotlist . , . ID = expression ) shift and go to state 205 , shift and go to state 206 state 161 (115) call -> primary ( ) . [ reduce using rule 115 (call -> primary ( ) .) ( reduce using rule 115 (call -> primary ( ) .) POWER reduce using rule 115 (call -> primary ( ) .) . reduce using rule 115 (call -> primary ( ) .) REAL reduce using rule 115 (call -> primary ( ) .) ] reduce using rule 115 (call -> primary ( ) .) , reduce using rule 115 (call -> primary ( ) .) * reduce using rule 115 (call -> primary ( ) .) / reduce using rule 115 (call -> primary ( ) .) ^ reduce using rule 115 (call -> primary ( ) .) + reduce using rule 115 (call -> primary ( ) .) - reduce using rule 115 (call -> primary ( ) .) < reduce using rule 115 (call -> primary ( ) .) > reduce using rule 115 (call -> primary ( ) .) GTE reduce using rule 115 (call -> primary ( ) .) LTE reduce using rule 115 (call -> primary ( ) .) NEQ reduce using rule 115 (call -> primary ( ) .) ISEQUAL reduce using rule 115 (call -> primary ( ) .) IN reduce using rule 115 (call -> primary ( ) .) NOT reduce using rule 115 (call -> primary ( ) .) AND reduce using rule 115 (call -> primary ( ) .) OR reduce using rule 115 (call -> primary ( ) .) FOR reduce using rule 115 (call -> primary ( ) .) ) reduce using rule 115 (call -> primary ( ) .) BREAK reduce using rule 115 (call -> primary ( ) .) NEXT reduce using rule 115 (call -> primary ( ) .) { reduce using rule 115 (call -> primary ( ) .) PRINT reduce using rule 115 (call -> primary ( ) .) IF reduce using rule 115 (call -> primary ( ) .) WHERE reduce using rule 115 (call -> primary ( ) .) SWITCH reduce using rule 115 (call -> primary ( ) .) FUNCTION reduce using rule 115 (call -> primary ( ) .) DO reduce using rule 115 (call -> primary ( ) .) LOOP reduce using rule 115 (call -> primary ( ) .) WITH reduce using rule 115 (call -> primary ( ) .) ID reduce using rule 115 (call -> primary ( ) .) ITEM_TAG reduce using rule 115 (call -> primary ( ) .) INTEGER reduce using rule 115 (call -> primary ( ) .) HEXINT reduce using rule 115 (call -> primary ( ) .) OCTINT reduce using rule 115 (call -> primary ( ) .) BININT reduce using rule 115 (call -> primary ( ) .) IMAGINARY reduce using rule 115 (call -> primary ( ) .) STRPREFIX reduce using rule 115 (call -> primary ( ) .) SHORTSTRING reduce using rule 115 (call -> primary ( ) .) LONGSTRING reduce using rule 115 (call -> primary ( ) .) ` reduce using rule 115 (call -> primary ( ) .) ; reduce using rule 115 (call -> primary ( ) .) $end reduce using rule 115 (call -> primary ( ) .) } reduce using rule 115 (call -> primary ( ) .) ELSE reduce using rule 115 (call -> primary ( ) .) DEFAULT reduce using rule 115 (call -> primary ( ) .) CASE reduce using rule 115 (call -> primary ( ) .) : reduce using rule 115 (call -> primary ( ) .) AUGOP reduce using rule 115 (call -> primary ( ) .) = reduce using rule 115 (call -> primary ( ) .) state 162 (122) dotlist -> . . ID = expression ID shift and go to state 207 state 163 (116) call -> primary ( argument_list . ) (118) argument_list -> argument_list . , func_arg ) shift and go to state 208 , shift and go to state 209 state 164 (119) func_arg -> expression . ) reduce using rule 119 (func_arg -> expression .) , reduce using rule 119 (func_arg -> expression .) state 165 (95) attribute_tag -> . ID . POWER reduce using rule 95 (attribute_tag -> . ID .) [ reduce using rule 95 (attribute_tag -> . ID .) ( reduce using rule 95 (attribute_tag -> . ID .) . reduce using rule 95 (attribute_tag -> . ID .) REAL reduce using rule 95 (attribute_tag -> . ID .) * reduce using rule 95 (attribute_tag -> . ID .) / reduce using rule 95 (attribute_tag -> . ID .) ^ reduce using rule 95 (attribute_tag -> . ID .) + reduce using rule 95 (attribute_tag -> . ID .) - reduce using rule 95 (attribute_tag -> . ID .) < reduce using rule 95 (attribute_tag -> . ID .) > reduce using rule 95 (attribute_tag -> . ID .) GTE reduce using rule 95 (attribute_tag -> . ID .) LTE reduce using rule 95 (attribute_tag -> . ID .) NEQ reduce using rule 95 (attribute_tag -> . ID .) ISEQUAL reduce using rule 95 (attribute_tag -> . ID .) IN reduce using rule 95 (attribute_tag -> . ID .) NOT reduce using rule 95 (attribute_tag -> . ID .) AND reduce using rule 95 (attribute_tag -> . ID .) OR reduce using rule 95 (attribute_tag -> . ID .) BREAK reduce using rule 95 (attribute_tag -> . ID .) NEXT reduce using rule 95 (attribute_tag -> . ID .) { reduce using rule 95 (attribute_tag -> . ID .) PRINT reduce using rule 95 (attribute_tag -> . ID .) IF reduce using rule 95 (attribute_tag -> . ID .) FOR reduce using rule 95 (attribute_tag -> . ID .) WHERE reduce using rule 95 (attribute_tag -> . ID .) SWITCH reduce using rule 95 (attribute_tag -> . ID .) FUNCTION reduce using rule 95 (attribute_tag -> . ID .) DO reduce using rule 95 (attribute_tag -> . ID .) LOOP reduce using rule 95 (attribute_tag -> . ID .) WITH reduce using rule 95 (attribute_tag -> . ID .) ID reduce using rule 95 (attribute_tag -> . ID .) ITEM_TAG reduce using rule 95 (attribute_tag -> . ID .) INTEGER reduce using rule 95 (attribute_tag -> . ID .) HEXINT reduce using rule 95 (attribute_tag -> . ID .) OCTINT reduce using rule 95 (attribute_tag -> . ID .) BININT reduce using rule 95 (attribute_tag -> . ID .) IMAGINARY reduce using rule 95 (attribute_tag -> . ID .) STRPREFIX reduce using rule 95 (attribute_tag -> . ID .) SHORTSTRING reduce using rule 95 (attribute_tag -> . ID .) LONGSTRING reduce using rule 95 (attribute_tag -> . ID .) ` reduce using rule 95 (attribute_tag -> . ID .) , reduce using rule 95 (attribute_tag -> . ID .) ; reduce using rule 95 (attribute_tag -> . ID .) $end reduce using rule 95 (attribute_tag -> . ID .) } reduce using rule 95 (attribute_tag -> . ID .) ELSE reduce using rule 95 (attribute_tag -> . ID .) DEFAULT reduce using rule 95 (attribute_tag -> . ID .) CASE reduce using rule 95 (attribute_tag -> . ID .) ) reduce using rule 95 (attribute_tag -> . ID .) ] reduce using rule 95 (attribute_tag -> . ID .) : reduce using rule 95 (attribute_tag -> . ID .) AUGOP reduce using rule 95 (attribute_tag -> . ID .) = reduce using rule 95 (attribute_tag -> . ID .) state 166 (105) extended_slicing -> primary [ slice_list . ] (107) slice_list -> slice_list . , slice_item ] shift and go to state 211 , shift and go to state 210 state 167 (100) simple_slicing -> primary [ short_slice . ] (111) proper_slice -> short_slice . (113) long_slice -> short_slice . : (114) long_slice -> short_slice . : expression ! shift/reduce conflict for ] resolved as shift ] shift and go to state 212 , reduce using rule 111 (proper_slice -> short_slice .) : shift and go to state 213 ! ] [ reduce using rule 111 (proper_slice -> short_slice .) ] state 168 (110) slice_item -> ELLIPSIS . ] reduce using rule 110 (slice_item -> ELLIPSIS .) , reduce using rule 110 (slice_item -> ELLIPSIS .) state 169 (101) short_slice -> : . (103) short_slice -> : . expression (18) expression -> . or_test (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] : reduce using rule 101 (short_slice -> : .) ] reduce using rule 101 (short_slice -> : .) , reduce using rule 101 (short_slice -> : .) NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 list_display shift and go to state 22 or_test shift and go to state 86 expression shift and go to state 214 state 170 (112) proper_slice -> long_slice . ] reduce using rule 112 (proper_slice -> long_slice .) , reduce using rule 112 (proper_slice -> long_slice .) state 171 (109) slice_item -> proper_slice . ] reduce using rule 109 (slice_item -> proper_slice .) , reduce using rule 109 (slice_item -> proper_slice .) state 172 (97) subscription -> primary [ expression_list . ] (17) expression_list -> expression_list . , expression ] shift and go to state 215 , shift and go to state 145 state 173 (106) slice_list -> slice_item . ] reduce using rule 106 (slice_list -> slice_item .) , reduce using rule 106 (slice_list -> slice_item .) state 174 (16) expression_list -> expression . (102) short_slice -> expression . : expression (104) short_slice -> expression . : (108) slice_item -> expression . ! reduce/reduce conflict for ] resolved using rule 16 (expression_list -> expression .) ! reduce/reduce conflict for , resolved using rule 16 (expression_list -> expression .) ] reduce using rule 16 (expression_list -> expression .) , reduce using rule 16 (expression_list -> expression .) : shift and go to state 216 ! ] [ reduce using rule 108 (slice_item -> expression .) ] ! , [ reduce using rule 108 (slice_item -> expression .) ] state 175 (155) switch_stmt -> SWITCH ID open_brace . caselist DEFAULT suite close_brace (156) caselist -> . CASE target_list suite (157) caselist -> . caselist CASE target_list suite CASE shift and go to state 217 caselist shift and go to state 218 state 176 (120) augmented_assignment_stmt -> target AUGOP expression_list . (17) expression_list -> expression_list . , expression BREAK reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) NEXT reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) IF reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) FOR reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) WHERE reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) SWITCH reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) FUNCTION reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) PRINT reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) DO reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) LOOP reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) WITH reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) ( reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) [ reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) ID reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) ITEM_TAG reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) INTEGER reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) HEXINT reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) OCTINT reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) BININT reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) REAL reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) IMAGINARY reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) STRPREFIX reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) SHORTSTRING reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) LONGSTRING reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) ` reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) $end reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) } reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) ELSE reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) DEFAULT reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) CASE reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) ; reduce using rule 120 (augmented_assignment_stmt -> target AUGOP expression_list .) , shift and go to state 145 state 177 (150) do_stmt_head -> DO ID = . expression , expression (151) do_stmt_head -> DO ID = . expression , expression , expression (18) expression -> . or_test (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 list_display shift and go to state 22 or_test shift and go to state 86 expression shift and go to state 219 state 178 (135) if_stmt -> IF expression suite . BREAK reduce using rule 135 (if_stmt -> IF expression suite .) NEXT reduce using rule 135 (if_stmt -> IF expression suite .) IF reduce using rule 135 (if_stmt -> IF expression suite .) FOR reduce using rule 135 (if_stmt -> IF expression suite .) WHERE reduce using rule 135 (if_stmt -> IF expression suite .) SWITCH reduce using rule 135 (if_stmt -> IF expression suite .) FUNCTION reduce using rule 135 (if_stmt -> IF expression suite .) PRINT reduce using rule 135 (if_stmt -> IF expression suite .) DO reduce using rule 135 (if_stmt -> IF expression suite .) LOOP reduce using rule 135 (if_stmt -> IF expression suite .) WITH reduce using rule 135 (if_stmt -> IF expression suite .) ( reduce using rule 135 (if_stmt -> IF expression suite .) [ reduce using rule 135 (if_stmt -> IF expression suite .) ID reduce using rule 135 (if_stmt -> IF expression suite .) ITEM_TAG reduce using rule 135 (if_stmt -> IF expression suite .) INTEGER reduce using rule 135 (if_stmt -> IF expression suite .) HEXINT reduce using rule 135 (if_stmt -> IF expression suite .) OCTINT reduce using rule 135 (if_stmt -> IF expression suite .) BININT reduce using rule 135 (if_stmt -> IF expression suite .) REAL reduce using rule 135 (if_stmt -> IF expression suite .) IMAGINARY reduce using rule 135 (if_stmt -> IF expression suite .) STRPREFIX reduce using rule 135 (if_stmt -> IF expression suite .) SHORTSTRING reduce using rule 135 (if_stmt -> IF expression suite .) LONGSTRING reduce using rule 135 (if_stmt -> IF expression suite .) ` reduce using rule 135 (if_stmt -> IF expression suite .) $end reduce using rule 135 (if_stmt -> IF expression suite .) } reduce using rule 135 (if_stmt -> IF expression suite .) ELSE reduce using rule 135 (if_stmt -> IF expression suite .) DEFAULT reduce using rule 135 (if_stmt -> IF expression suite .) CASE reduce using rule 135 (if_stmt -> IF expression suite .) state 179 (7) stmt_list -> stmt_list ; simple_stmt . (8) stmt_list -> stmt_list ; simple_stmt . ; ! shift/reduce conflict for ; resolved as shift } reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) BREAK reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) NEXT reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) IF reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) FOR reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) WHERE reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) SWITCH reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) FUNCTION reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) PRINT reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) DO reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) LOOP reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) WITH reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) ( reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) [ reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) ID reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) ITEM_TAG reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) INTEGER reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) HEXINT reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) OCTINT reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) BININT reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) REAL reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) IMAGINARY reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) STRPREFIX reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) SHORTSTRING reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) LONGSTRING reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) ` reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) $end reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) ; shift and go to state 220 ! ; [ reduce using rule 7 (stmt_list -> stmt_list ; simple_stmt .) ] state 180 (124) assignment_stmt -> target_list = expression_list . (17) expression_list -> expression_list . , expression BREAK reduce using rule 124 (assignment_stmt -> target_list = expression_list .) NEXT reduce using rule 124 (assignment_stmt -> target_list = expression_list .) IF reduce using rule 124 (assignment_stmt -> target_list = expression_list .) FOR reduce using rule 124 (assignment_stmt -> target_list = expression_list .) WHERE reduce using rule 124 (assignment_stmt -> target_list = expression_list .) SWITCH reduce using rule 124 (assignment_stmt -> target_list = expression_list .) FUNCTION reduce using rule 124 (assignment_stmt -> target_list = expression_list .) PRINT reduce using rule 124 (assignment_stmt -> target_list = expression_list .) DO reduce using rule 124 (assignment_stmt -> target_list = expression_list .) LOOP reduce using rule 124 (assignment_stmt -> target_list = expression_list .) WITH reduce using rule 124 (assignment_stmt -> target_list = expression_list .) ( reduce using rule 124 (assignment_stmt -> target_list = expression_list .) [ reduce using rule 124 (assignment_stmt -> target_list = expression_list .) ID reduce using rule 124 (assignment_stmt -> target_list = expression_list .) ITEM_TAG reduce using rule 124 (assignment_stmt -> target_list = expression_list .) INTEGER reduce using rule 124 (assignment_stmt -> target_list = expression_list .) HEXINT reduce using rule 124 (assignment_stmt -> target_list = expression_list .) OCTINT reduce using rule 124 (assignment_stmt -> target_list = expression_list .) BININT reduce using rule 124 (assignment_stmt -> target_list = expression_list .) REAL reduce using rule 124 (assignment_stmt -> target_list = expression_list .) IMAGINARY reduce using rule 124 (assignment_stmt -> target_list = expression_list .) STRPREFIX reduce using rule 124 (assignment_stmt -> target_list = expression_list .) SHORTSTRING reduce using rule 124 (assignment_stmt -> target_list = expression_list .) LONGSTRING reduce using rule 124 (assignment_stmt -> target_list = expression_list .) ` reduce using rule 124 (assignment_stmt -> target_list = expression_list .) $end reduce using rule 124 (assignment_stmt -> target_list = expression_list .) } reduce using rule 124 (assignment_stmt -> target_list = expression_list .) ELSE reduce using rule 124 (assignment_stmt -> target_list = expression_list .) DEFAULT reduce using rule 124 (assignment_stmt -> target_list = expression_list .) CASE reduce using rule 124 (assignment_stmt -> target_list = expression_list .) ; reduce using rule 124 (assignment_stmt -> target_list = expression_list .) , shift and go to state 145 state 181 (126) target_list -> target_list , target . = reduce using rule 126 (target_list -> target_list , target .) , reduce using rule 126 (target_list -> target_list , target .) ) reduce using rule 126 (target_list -> target_list , target .) BREAK reduce using rule 126 (target_list -> target_list , target .) NEXT reduce using rule 126 (target_list -> target_list , target .) { reduce using rule 126 (target_list -> target_list , target .) PRINT reduce using rule 126 (target_list -> target_list , target .) IF reduce using rule 126 (target_list -> target_list , target .) FOR reduce using rule 126 (target_list -> target_list , target .) WHERE reduce using rule 126 (target_list -> target_list , target .) SWITCH reduce using rule 126 (target_list -> target_list , target .) FUNCTION reduce using rule 126 (target_list -> target_list , target .) ( reduce using rule 126 (target_list -> target_list , target .) [ reduce using rule 126 (target_list -> target_list , target .) DO reduce using rule 126 (target_list -> target_list , target .) LOOP reduce using rule 126 (target_list -> target_list , target .) WITH reduce using rule 126 (target_list -> target_list , target .) ID reduce using rule 126 (target_list -> target_list , target .) ITEM_TAG reduce using rule 126 (target_list -> target_list , target .) INTEGER reduce using rule 126 (target_list -> target_list , target .) HEXINT reduce using rule 126 (target_list -> target_list , target .) OCTINT reduce using rule 126 (target_list -> target_list , target .) BININT reduce using rule 126 (target_list -> target_list , target .) REAL reduce using rule 126 (target_list -> target_list , target .) IMAGINARY reduce using rule 126 (target_list -> target_list , target .) STRPREFIX reduce using rule 126 (target_list -> target_list , target .) SHORTSTRING reduce using rule 126 (target_list -> target_list , target .) LONGSTRING reduce using rule 126 (target_list -> target_list , target .) ` reduce using rule 126 (target_list -> target_list , target .) ] reduce using rule 126 (target_list -> target_list , target .) IN reduce using rule 126 (target_list -> target_list , target .) state 182 (139) suite -> open_brace statement_block close_brace . BREAK reduce using rule 139 (suite -> open_brace statement_block close_brace .) NEXT reduce using rule 139 (suite -> open_brace statement_block close_brace .) IF reduce using rule 139 (suite -> open_brace statement_block close_brace .) FOR reduce using rule 139 (suite -> open_brace statement_block close_brace .) WHERE reduce using rule 139 (suite -> open_brace statement_block close_brace .) SWITCH reduce using rule 139 (suite -> open_brace statement_block close_brace .) FUNCTION reduce using rule 139 (suite -> open_brace statement_block close_brace .) PRINT reduce using rule 139 (suite -> open_brace statement_block close_brace .) DO reduce using rule 139 (suite -> open_brace statement_block close_brace .) LOOP reduce using rule 139 (suite -> open_brace statement_block close_brace .) WITH reduce using rule 139 (suite -> open_brace statement_block close_brace .) ( reduce using rule 139 (suite -> open_brace statement_block close_brace .) [ reduce using rule 139 (suite -> open_brace statement_block close_brace .) ID reduce using rule 139 (suite -> open_brace statement_block close_brace .) ITEM_TAG reduce using rule 139 (suite -> open_brace statement_block close_brace .) INTEGER reduce using rule 139 (suite -> open_brace statement_block close_brace .) HEXINT reduce using rule 139 (suite -> open_brace statement_block close_brace .) OCTINT reduce using rule 139 (suite -> open_brace statement_block close_brace .) BININT reduce using rule 139 (suite -> open_brace statement_block close_brace .) REAL reduce using rule 139 (suite -> open_brace statement_block close_brace .) IMAGINARY reduce using rule 139 (suite -> open_brace statement_block close_brace .) STRPREFIX reduce using rule 139 (suite -> open_brace statement_block close_brace .) SHORTSTRING reduce using rule 139 (suite -> open_brace statement_block close_brace .) LONGSTRING reduce using rule 139 (suite -> open_brace statement_block close_brace .) ` reduce using rule 139 (suite -> open_brace statement_block close_brace .) $end reduce using rule 139 (suite -> open_brace statement_block close_brace .) } reduce using rule 139 (suite -> open_brace statement_block close_brace .) ELSE reduce using rule 139 (suite -> open_brace statement_block close_brace .) DEFAULT reduce using rule 139 (suite -> open_brace statement_block close_brace .) CASE reduce using rule 139 (suite -> open_brace statement_block close_brace .) state 183 (143) statement_block -> statement_block statement . } reduce using rule 143 (statement_block -> statement_block statement .) BREAK reduce using rule 143 (statement_block -> statement_block statement .) NEXT reduce using rule 143 (statement_block -> statement_block statement .) IF reduce using rule 143 (statement_block -> statement_block statement .) FOR reduce using rule 143 (statement_block -> statement_block statement .) WHERE reduce using rule 143 (statement_block -> statement_block statement .) SWITCH reduce using rule 143 (statement_block -> statement_block statement .) FUNCTION reduce using rule 143 (statement_block -> statement_block statement .) PRINT reduce using rule 143 (statement_block -> statement_block statement .) DO reduce using rule 143 (statement_block -> statement_block statement .) LOOP reduce using rule 143 (statement_block -> statement_block statement .) WITH reduce using rule 143 (statement_block -> statement_block statement .) ( reduce using rule 143 (statement_block -> statement_block statement .) [ reduce using rule 143 (statement_block -> statement_block statement .) ID reduce using rule 143 (statement_block -> statement_block statement .) ITEM_TAG reduce using rule 143 (statement_block -> statement_block statement .) INTEGER reduce using rule 143 (statement_block -> statement_block statement .) HEXINT reduce using rule 143 (statement_block -> statement_block statement .) OCTINT reduce using rule 143 (statement_block -> statement_block statement .) BININT reduce using rule 143 (statement_block -> statement_block statement .) REAL reduce using rule 143 (statement_block -> statement_block statement .) IMAGINARY reduce using rule 143 (statement_block -> statement_block statement .) STRPREFIX reduce using rule 143 (statement_block -> statement_block statement .) SHORTSTRING reduce using rule 143 (statement_block -> statement_block statement .) LONGSTRING reduce using rule 143 (statement_block -> statement_block statement .) ` reduce using rule 143 (statement_block -> statement_block statement .) state 184 (141) close_brace -> } . BREAK reduce using rule 141 (close_brace -> } .) NEXT reduce using rule 141 (close_brace -> } .) IF reduce using rule 141 (close_brace -> } .) FOR reduce using rule 141 (close_brace -> } .) WHERE reduce using rule 141 (close_brace -> } .) SWITCH reduce using rule 141 (close_brace -> } .) FUNCTION reduce using rule 141 (close_brace -> } .) PRINT reduce using rule 141 (close_brace -> } .) DO reduce using rule 141 (close_brace -> } .) LOOP reduce using rule 141 (close_brace -> } .) WITH reduce using rule 141 (close_brace -> } .) ( reduce using rule 141 (close_brace -> } .) [ reduce using rule 141 (close_brace -> } .) ID reduce using rule 141 (close_brace -> } .) ITEM_TAG reduce using rule 141 (close_brace -> } .) INTEGER reduce using rule 141 (close_brace -> } .) HEXINT reduce using rule 141 (close_brace -> } .) OCTINT reduce using rule 141 (close_brace -> } .) BININT reduce using rule 141 (close_brace -> } .) REAL reduce using rule 141 (close_brace -> } .) IMAGINARY reduce using rule 141 (close_brace -> } .) STRPREFIX reduce using rule 141 (close_brace -> } .) SHORTSTRING reduce using rule 141 (close_brace -> } .) LONGSTRING reduce using rule 141 (close_brace -> } .) ` reduce using rule 141 (close_brace -> } .) $end reduce using rule 141 (close_brace -> } .) } reduce using rule 141 (close_brace -> } .) ELSE reduce using rule 141 (close_brace -> } .) DEFAULT reduce using rule 141 (close_brace -> } .) CASE reduce using rule 141 (close_brace -> } .) state 185 (153) with_head -> WITH ID AS ID . BREAK reduce using rule 153 (with_head -> WITH ID AS ID .) NEXT reduce using rule 153 (with_head -> WITH ID AS ID .) { reduce using rule 153 (with_head -> WITH ID AS ID .) PRINT reduce using rule 153 (with_head -> WITH ID AS ID .) IF reduce using rule 153 (with_head -> WITH ID AS ID .) FOR reduce using rule 153 (with_head -> WITH ID AS ID .) WHERE reduce using rule 153 (with_head -> WITH ID AS ID .) SWITCH reduce using rule 153 (with_head -> WITH ID AS ID .) FUNCTION reduce using rule 153 (with_head -> WITH ID AS ID .) ( reduce using rule 153 (with_head -> WITH ID AS ID .) [ reduce using rule 153 (with_head -> WITH ID AS ID .) DO reduce using rule 153 (with_head -> WITH ID AS ID .) LOOP reduce using rule 153 (with_head -> WITH ID AS ID .) WITH reduce using rule 153 (with_head -> WITH ID AS ID .) ID reduce using rule 153 (with_head -> WITH ID AS ID .) ITEM_TAG reduce using rule 153 (with_head -> WITH ID AS ID .) INTEGER reduce using rule 153 (with_head -> WITH ID AS ID .) HEXINT reduce using rule 153 (with_head -> WITH ID AS ID .) OCTINT reduce using rule 153 (with_head -> WITH ID AS ID .) BININT reduce using rule 153 (with_head -> WITH ID AS ID .) REAL reduce using rule 153 (with_head -> WITH ID AS ID .) IMAGINARY reduce using rule 153 (with_head -> WITH ID AS ID .) STRPREFIX reduce using rule 153 (with_head -> WITH ID AS ID .) SHORTSTRING reduce using rule 153 (with_head -> WITH ID AS ID .) LONGSTRING reduce using rule 153 (with_head -> WITH ID AS ID .) ` reduce using rule 153 (with_head -> WITH ID AS ID .) state 186 (49) power -> primary POWER u_expr . * reduce using rule 49 (power -> primary POWER u_expr .) / reduce using rule 49 (power -> primary POWER u_expr .) ^ reduce using rule 49 (power -> primary POWER u_expr .) + reduce using rule 49 (power -> primary POWER u_expr .) - reduce using rule 49 (power -> primary POWER u_expr .) < reduce using rule 49 (power -> primary POWER u_expr .) > reduce using rule 49 (power -> primary POWER u_expr .) GTE reduce using rule 49 (power -> primary POWER u_expr .) LTE reduce using rule 49 (power -> primary POWER u_expr .) NEQ reduce using rule 49 (power -> primary POWER u_expr .) ISEQUAL reduce using rule 49 (power -> primary POWER u_expr .) IN reduce using rule 49 (power -> primary POWER u_expr .) NOT reduce using rule 49 (power -> primary POWER u_expr .) AND reduce using rule 49 (power -> primary POWER u_expr .) OR reduce using rule 49 (power -> primary POWER u_expr .) ) reduce using rule 49 (power -> primary POWER u_expr .) , reduce using rule 49 (power -> primary POWER u_expr .) BREAK reduce using rule 49 (power -> primary POWER u_expr .) NEXT reduce using rule 49 (power -> primary POWER u_expr .) { reduce using rule 49 (power -> primary POWER u_expr .) PRINT reduce using rule 49 (power -> primary POWER u_expr .) IF reduce using rule 49 (power -> primary POWER u_expr .) FOR reduce using rule 49 (power -> primary POWER u_expr .) WHERE reduce using rule 49 (power -> primary POWER u_expr .) SWITCH reduce using rule 49 (power -> primary POWER u_expr .) FUNCTION reduce using rule 49 (power -> primary POWER u_expr .) ( reduce using rule 49 (power -> primary POWER u_expr .) [ reduce using rule 49 (power -> primary POWER u_expr .) DO reduce using rule 49 (power -> primary POWER u_expr .) LOOP reduce using rule 49 (power -> primary POWER u_expr .) WITH reduce using rule 49 (power -> primary POWER u_expr .) ID reduce using rule 49 (power -> primary POWER u_expr .) ITEM_TAG reduce using rule 49 (power -> primary POWER u_expr .) INTEGER reduce using rule 49 (power -> primary POWER u_expr .) HEXINT reduce using rule 49 (power -> primary POWER u_expr .) OCTINT reduce using rule 49 (power -> primary POWER u_expr .) BININT reduce using rule 49 (power -> primary POWER u_expr .) REAL reduce using rule 49 (power -> primary POWER u_expr .) IMAGINARY reduce using rule 49 (power -> primary POWER u_expr .) STRPREFIX reduce using rule 49 (power -> primary POWER u_expr .) SHORTSTRING reduce using rule 49 (power -> primary POWER u_expr .) LONGSTRING reduce using rule 49 (power -> primary POWER u_expr .) ` reduce using rule 49 (power -> primary POWER u_expr .) ; reduce using rule 49 (power -> primary POWER u_expr .) $end reduce using rule 49 (power -> primary POWER u_expr .) } reduce using rule 49 (power -> primary POWER u_expr .) ELSE reduce using rule 49 (power -> primary POWER u_expr .) DEFAULT reduce using rule 49 (power -> primary POWER u_expr .) CASE reduce using rule 49 (power -> primary POWER u_expr .) ] reduce using rule 49 (power -> primary POWER u_expr .) : reduce using rule 49 (power -> primary POWER u_expr .) state 187 (29) comparison -> a_expr comp_operator a_expr . (39) a_expr -> a_expr . + m_expr (40) a_expr -> a_expr . - m_expr AND reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) OR reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) ) reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) , reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) ] reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) FOR reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) IF reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) ; reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) BREAK reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) NEXT reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) WHERE reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) SWITCH reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) FUNCTION reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) PRINT reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) DO reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) LOOP reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) WITH reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) ( reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) [ reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) ID reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) ITEM_TAG reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) INTEGER reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) HEXINT reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) OCTINT reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) BININT reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) REAL reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) IMAGINARY reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) STRPREFIX reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) SHORTSTRING reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) LONGSTRING reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) ` reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) $end reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) } reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) ELSE reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) DEFAULT reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) CASE reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) { reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) : reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) IN reduce using rule 29 (comparison -> a_expr comp_operator a_expr .) + shift and go to state 129 - shift and go to state 131 state 188 (39) a_expr -> a_expr + m_expr . (42) m_expr -> m_expr . * u_expr (43) m_expr -> m_expr . / u_expr (44) m_expr -> m_expr . ^ u_expr + reduce using rule 39 (a_expr -> a_expr + m_expr .) - reduce using rule 39 (a_expr -> a_expr + m_expr .) < reduce using rule 39 (a_expr -> a_expr + m_expr .) > reduce using rule 39 (a_expr -> a_expr + m_expr .) GTE reduce using rule 39 (a_expr -> a_expr + m_expr .) LTE reduce using rule 39 (a_expr -> a_expr + m_expr .) NEQ reduce using rule 39 (a_expr -> a_expr + m_expr .) ISEQUAL reduce using rule 39 (a_expr -> a_expr + m_expr .) IN reduce using rule 39 (a_expr -> a_expr + m_expr .) NOT reduce using rule 39 (a_expr -> a_expr + m_expr .) AND reduce using rule 39 (a_expr -> a_expr + m_expr .) OR reduce using rule 39 (a_expr -> a_expr + m_expr .) ) reduce using rule 39 (a_expr -> a_expr + m_expr .) , reduce using rule 39 (a_expr -> a_expr + m_expr .) BREAK reduce using rule 39 (a_expr -> a_expr + m_expr .) NEXT reduce using rule 39 (a_expr -> a_expr + m_expr .) { reduce using rule 39 (a_expr -> a_expr + m_expr .) PRINT reduce using rule 39 (a_expr -> a_expr + m_expr .) IF reduce using rule 39 (a_expr -> a_expr + m_expr .) FOR reduce using rule 39 (a_expr -> a_expr + m_expr .) WHERE reduce using rule 39 (a_expr -> a_expr + m_expr .) SWITCH reduce using rule 39 (a_expr -> a_expr + m_expr .) FUNCTION reduce using rule 39 (a_expr -> a_expr + m_expr .) ( reduce using rule 39 (a_expr -> a_expr + m_expr .) [ reduce using rule 39 (a_expr -> a_expr + m_expr .) DO reduce using rule 39 (a_expr -> a_expr + m_expr .) LOOP reduce using rule 39 (a_expr -> a_expr + m_expr .) WITH reduce using rule 39 (a_expr -> a_expr + m_expr .) ID reduce using rule 39 (a_expr -> a_expr + m_expr .) ITEM_TAG reduce using rule 39 (a_expr -> a_expr + m_expr .) INTEGER reduce using rule 39 (a_expr -> a_expr + m_expr .) HEXINT reduce using rule 39 (a_expr -> a_expr + m_expr .) OCTINT reduce using rule 39 (a_expr -> a_expr + m_expr .) BININT reduce using rule 39 (a_expr -> a_expr + m_expr .) REAL reduce using rule 39 (a_expr -> a_expr + m_expr .) IMAGINARY reduce using rule 39 (a_expr -> a_expr + m_expr .) STRPREFIX reduce using rule 39 (a_expr -> a_expr + m_expr .) SHORTSTRING reduce using rule 39 (a_expr -> a_expr + m_expr .) LONGSTRING reduce using rule 39 (a_expr -> a_expr + m_expr .) ` reduce using rule 39 (a_expr -> a_expr + m_expr .) ; reduce using rule 39 (a_expr -> a_expr + m_expr .) $end reduce using rule 39 (a_expr -> a_expr + m_expr .) } reduce using rule 39 (a_expr -> a_expr + m_expr .) ELSE reduce using rule 39 (a_expr -> a_expr + m_expr .) DEFAULT reduce using rule 39 (a_expr -> a_expr + m_expr .) CASE reduce using rule 39 (a_expr -> a_expr + m_expr .) ] reduce using rule 39 (a_expr -> a_expr + m_expr .) : reduce using rule 39 (a_expr -> a_expr + m_expr .) * shift and go to state 141 / shift and go to state 142 ^ shift and go to state 143 state 189 (40) a_expr -> a_expr - m_expr . (42) m_expr -> m_expr . * u_expr (43) m_expr -> m_expr . / u_expr (44) m_expr -> m_expr . ^ u_expr + reduce using rule 40 (a_expr -> a_expr - m_expr .) - reduce using rule 40 (a_expr -> a_expr - m_expr .) < reduce using rule 40 (a_expr -> a_expr - m_expr .) > reduce using rule 40 (a_expr -> a_expr - m_expr .) GTE reduce using rule 40 (a_expr -> a_expr - m_expr .) LTE reduce using rule 40 (a_expr -> a_expr - m_expr .) NEQ reduce using rule 40 (a_expr -> a_expr - m_expr .) ISEQUAL reduce using rule 40 (a_expr -> a_expr - m_expr .) IN reduce using rule 40 (a_expr -> a_expr - m_expr .) NOT reduce using rule 40 (a_expr -> a_expr - m_expr .) AND reduce using rule 40 (a_expr -> a_expr - m_expr .) OR reduce using rule 40 (a_expr -> a_expr - m_expr .) ) reduce using rule 40 (a_expr -> a_expr - m_expr .) , reduce using rule 40 (a_expr -> a_expr - m_expr .) BREAK reduce using rule 40 (a_expr -> a_expr - m_expr .) NEXT reduce using rule 40 (a_expr -> a_expr - m_expr .) { reduce using rule 40 (a_expr -> a_expr - m_expr .) PRINT reduce using rule 40 (a_expr -> a_expr - m_expr .) IF reduce using rule 40 (a_expr -> a_expr - m_expr .) FOR reduce using rule 40 (a_expr -> a_expr - m_expr .) WHERE reduce using rule 40 (a_expr -> a_expr - m_expr .) SWITCH reduce using rule 40 (a_expr -> a_expr - m_expr .) FUNCTION reduce using rule 40 (a_expr -> a_expr - m_expr .) ( reduce using rule 40 (a_expr -> a_expr - m_expr .) [ reduce using rule 40 (a_expr -> a_expr - m_expr .) DO reduce using rule 40 (a_expr -> a_expr - m_expr .) LOOP reduce using rule 40 (a_expr -> a_expr - m_expr .) WITH reduce using rule 40 (a_expr -> a_expr - m_expr .) ID reduce using rule 40 (a_expr -> a_expr - m_expr .) ITEM_TAG reduce using rule 40 (a_expr -> a_expr - m_expr .) INTEGER reduce using rule 40 (a_expr -> a_expr - m_expr .) HEXINT reduce using rule 40 (a_expr -> a_expr - m_expr .) OCTINT reduce using rule 40 (a_expr -> a_expr - m_expr .) BININT reduce using rule 40 (a_expr -> a_expr - m_expr .) REAL reduce using rule 40 (a_expr -> a_expr - m_expr .) IMAGINARY reduce using rule 40 (a_expr -> a_expr - m_expr .) STRPREFIX reduce using rule 40 (a_expr -> a_expr - m_expr .) SHORTSTRING reduce using rule 40 (a_expr -> a_expr - m_expr .) LONGSTRING reduce using rule 40 (a_expr -> a_expr - m_expr .) ` reduce using rule 40 (a_expr -> a_expr - m_expr .) ; reduce using rule 40 (a_expr -> a_expr - m_expr .) $end reduce using rule 40 (a_expr -> a_expr - m_expr .) } reduce using rule 40 (a_expr -> a_expr - m_expr .) ELSE reduce using rule 40 (a_expr -> a_expr - m_expr .) DEFAULT reduce using rule 40 (a_expr -> a_expr - m_expr .) CASE reduce using rule 40 (a_expr -> a_expr - m_expr .) ] reduce using rule 40 (a_expr -> a_expr - m_expr .) : reduce using rule 40 (a_expr -> a_expr - m_expr .) * shift and go to state 141 / shift and go to state 142 ^ shift and go to state 143 state 190 (37) comp_operator -> NOT IN . - reduce using rule 37 (comp_operator -> NOT IN .) + reduce using rule 37 (comp_operator -> NOT IN .) ID reduce using rule 37 (comp_operator -> NOT IN .) ITEM_TAG reduce using rule 37 (comp_operator -> NOT IN .) INTEGER reduce using rule 37 (comp_operator -> NOT IN .) HEXINT reduce using rule 37 (comp_operator -> NOT IN .) OCTINT reduce using rule 37 (comp_operator -> NOT IN .) BININT reduce using rule 37 (comp_operator -> NOT IN .) REAL reduce using rule 37 (comp_operator -> NOT IN .) IMAGINARY reduce using rule 37 (comp_operator -> NOT IN .) STRPREFIX reduce using rule 37 (comp_operator -> NOT IN .) SHORTSTRING reduce using rule 37 (comp_operator -> NOT IN .) LONGSTRING reduce using rule 37 (comp_operator -> NOT IN .) ( reduce using rule 37 (comp_operator -> NOT IN .) ` reduce using rule 37 (comp_operator -> NOT IN .) [ reduce using rule 37 (comp_operator -> NOT IN .) state 191 (25) and_test -> and_test AND not_test . AND reduce using rule 25 (and_test -> and_test AND not_test .) OR reduce using rule 25 (and_test -> and_test AND not_test .) ) reduce using rule 25 (and_test -> and_test AND not_test .) , reduce using rule 25 (and_test -> and_test AND not_test .) BREAK reduce using rule 25 (and_test -> and_test AND not_test .) NEXT reduce using rule 25 (and_test -> and_test AND not_test .) { reduce using rule 25 (and_test -> and_test AND not_test .) PRINT reduce using rule 25 (and_test -> and_test AND not_test .) IF reduce using rule 25 (and_test -> and_test AND not_test .) FOR reduce using rule 25 (and_test -> and_test AND not_test .) WHERE reduce using rule 25 (and_test -> and_test AND not_test .) SWITCH reduce using rule 25 (and_test -> and_test AND not_test .) FUNCTION reduce using rule 25 (and_test -> and_test AND not_test .) ( reduce using rule 25 (and_test -> and_test AND not_test .) [ reduce using rule 25 (and_test -> and_test AND not_test .) DO reduce using rule 25 (and_test -> and_test AND not_test .) LOOP reduce using rule 25 (and_test -> and_test AND not_test .) WITH reduce using rule 25 (and_test -> and_test AND not_test .) ID reduce using rule 25 (and_test -> and_test AND not_test .) ITEM_TAG reduce using rule 25 (and_test -> and_test AND not_test .) INTEGER reduce using rule 25 (and_test -> and_test AND not_test .) HEXINT reduce using rule 25 (and_test -> and_test AND not_test .) OCTINT reduce using rule 25 (and_test -> and_test AND not_test .) BININT reduce using rule 25 (and_test -> and_test AND not_test .) REAL reduce using rule 25 (and_test -> and_test AND not_test .) IMAGINARY reduce using rule 25 (and_test -> and_test AND not_test .) STRPREFIX reduce using rule 25 (and_test -> and_test AND not_test .) SHORTSTRING reduce using rule 25 (and_test -> and_test AND not_test .) LONGSTRING reduce using rule 25 (and_test -> and_test AND not_test .) ` reduce using rule 25 (and_test -> and_test AND not_test .) ; reduce using rule 25 (and_test -> and_test AND not_test .) $end reduce using rule 25 (and_test -> and_test AND not_test .) } reduce using rule 25 (and_test -> and_test AND not_test .) ELSE reduce using rule 25 (and_test -> and_test AND not_test .) DEFAULT reduce using rule 25 (and_test -> and_test AND not_test .) CASE reduce using rule 25 (and_test -> and_test AND not_test .) ] reduce using rule 25 (and_test -> and_test AND not_test .) : reduce using rule 25 (and_test -> and_test AND not_test .) IN reduce using rule 25 (and_test -> and_test AND not_test .) state 192 (42) m_expr -> m_expr * u_expr . * reduce using rule 42 (m_expr -> m_expr * u_expr .) / reduce using rule 42 (m_expr -> m_expr * u_expr .) ^ reduce using rule 42 (m_expr -> m_expr * u_expr .) + reduce using rule 42 (m_expr -> m_expr * u_expr .) - reduce using rule 42 (m_expr -> m_expr * u_expr .) < reduce using rule 42 (m_expr -> m_expr * u_expr .) > reduce using rule 42 (m_expr -> m_expr * u_expr .) GTE reduce using rule 42 (m_expr -> m_expr * u_expr .) LTE reduce using rule 42 (m_expr -> m_expr * u_expr .) NEQ reduce using rule 42 (m_expr -> m_expr * u_expr .) ISEQUAL reduce using rule 42 (m_expr -> m_expr * u_expr .) IN reduce using rule 42 (m_expr -> m_expr * u_expr .) NOT reduce using rule 42 (m_expr -> m_expr * u_expr .) AND reduce using rule 42 (m_expr -> m_expr * u_expr .) OR reduce using rule 42 (m_expr -> m_expr * u_expr .) ; reduce using rule 42 (m_expr -> m_expr * u_expr .) BREAK reduce using rule 42 (m_expr -> m_expr * u_expr .) NEXT reduce using rule 42 (m_expr -> m_expr * u_expr .) IF reduce using rule 42 (m_expr -> m_expr * u_expr .) FOR reduce using rule 42 (m_expr -> m_expr * u_expr .) WHERE reduce using rule 42 (m_expr -> m_expr * u_expr .) SWITCH reduce using rule 42 (m_expr -> m_expr * u_expr .) FUNCTION reduce using rule 42 (m_expr -> m_expr * u_expr .) PRINT reduce using rule 42 (m_expr -> m_expr * u_expr .) DO reduce using rule 42 (m_expr -> m_expr * u_expr .) LOOP reduce using rule 42 (m_expr -> m_expr * u_expr .) WITH reduce using rule 42 (m_expr -> m_expr * u_expr .) ( reduce using rule 42 (m_expr -> m_expr * u_expr .) [ reduce using rule 42 (m_expr -> m_expr * u_expr .) ID reduce using rule 42 (m_expr -> m_expr * u_expr .) ITEM_TAG reduce using rule 42 (m_expr -> m_expr * u_expr .) INTEGER reduce using rule 42 (m_expr -> m_expr * u_expr .) HEXINT reduce using rule 42 (m_expr -> m_expr * u_expr .) OCTINT reduce using rule 42 (m_expr -> m_expr * u_expr .) BININT reduce using rule 42 (m_expr -> m_expr * u_expr .) REAL reduce using rule 42 (m_expr -> m_expr * u_expr .) IMAGINARY reduce using rule 42 (m_expr -> m_expr * u_expr .) STRPREFIX reduce using rule 42 (m_expr -> m_expr * u_expr .) SHORTSTRING reduce using rule 42 (m_expr -> m_expr * u_expr .) LONGSTRING reduce using rule 42 (m_expr -> m_expr * u_expr .) ` reduce using rule 42 (m_expr -> m_expr * u_expr .) $end reduce using rule 42 (m_expr -> m_expr * u_expr .) } reduce using rule 42 (m_expr -> m_expr * u_expr .) ELSE reduce using rule 42 (m_expr -> m_expr * u_expr .) DEFAULT reduce using rule 42 (m_expr -> m_expr * u_expr .) CASE reduce using rule 42 (m_expr -> m_expr * u_expr .) ) reduce using rule 42 (m_expr -> m_expr * u_expr .) , reduce using rule 42 (m_expr -> m_expr * u_expr .) { reduce using rule 42 (m_expr -> m_expr * u_expr .) ] reduce using rule 42 (m_expr -> m_expr * u_expr .) : reduce using rule 42 (m_expr -> m_expr * u_expr .) state 193 (43) m_expr -> m_expr / u_expr . * reduce using rule 43 (m_expr -> m_expr / u_expr .) / reduce using rule 43 (m_expr -> m_expr / u_expr .) ^ reduce using rule 43 (m_expr -> m_expr / u_expr .) + reduce using rule 43 (m_expr -> m_expr / u_expr .) - reduce using rule 43 (m_expr -> m_expr / u_expr .) < reduce using rule 43 (m_expr -> m_expr / u_expr .) > reduce using rule 43 (m_expr -> m_expr / u_expr .) GTE reduce using rule 43 (m_expr -> m_expr / u_expr .) LTE reduce using rule 43 (m_expr -> m_expr / u_expr .) NEQ reduce using rule 43 (m_expr -> m_expr / u_expr .) ISEQUAL reduce using rule 43 (m_expr -> m_expr / u_expr .) IN reduce using rule 43 (m_expr -> m_expr / u_expr .) NOT reduce using rule 43 (m_expr -> m_expr / u_expr .) AND reduce using rule 43 (m_expr -> m_expr / u_expr .) OR reduce using rule 43 (m_expr -> m_expr / u_expr .) ; reduce using rule 43 (m_expr -> m_expr / u_expr .) BREAK reduce using rule 43 (m_expr -> m_expr / u_expr .) NEXT reduce using rule 43 (m_expr -> m_expr / u_expr .) IF reduce using rule 43 (m_expr -> m_expr / u_expr .) FOR reduce using rule 43 (m_expr -> m_expr / u_expr .) WHERE reduce using rule 43 (m_expr -> m_expr / u_expr .) SWITCH reduce using rule 43 (m_expr -> m_expr / u_expr .) FUNCTION reduce using rule 43 (m_expr -> m_expr / u_expr .) PRINT reduce using rule 43 (m_expr -> m_expr / u_expr .) DO reduce using rule 43 (m_expr -> m_expr / u_expr .) LOOP reduce using rule 43 (m_expr -> m_expr / u_expr .) WITH reduce using rule 43 (m_expr -> m_expr / u_expr .) ( reduce using rule 43 (m_expr -> m_expr / u_expr .) [ reduce using rule 43 (m_expr -> m_expr / u_expr .) ID reduce using rule 43 (m_expr -> m_expr / u_expr .) ITEM_TAG reduce using rule 43 (m_expr -> m_expr / u_expr .) INTEGER reduce using rule 43 (m_expr -> m_expr / u_expr .) HEXINT reduce using rule 43 (m_expr -> m_expr / u_expr .) OCTINT reduce using rule 43 (m_expr -> m_expr / u_expr .) BININT reduce using rule 43 (m_expr -> m_expr / u_expr .) REAL reduce using rule 43 (m_expr -> m_expr / u_expr .) IMAGINARY reduce using rule 43 (m_expr -> m_expr / u_expr .) STRPREFIX reduce using rule 43 (m_expr -> m_expr / u_expr .) SHORTSTRING reduce using rule 43 (m_expr -> m_expr / u_expr .) LONGSTRING reduce using rule 43 (m_expr -> m_expr / u_expr .) ` reduce using rule 43 (m_expr -> m_expr / u_expr .) $end reduce using rule 43 (m_expr -> m_expr / u_expr .) } reduce using rule 43 (m_expr -> m_expr / u_expr .) ELSE reduce using rule 43 (m_expr -> m_expr / u_expr .) DEFAULT reduce using rule 43 (m_expr -> m_expr / u_expr .) CASE reduce using rule 43 (m_expr -> m_expr / u_expr .) ) reduce using rule 43 (m_expr -> m_expr / u_expr .) , reduce using rule 43 (m_expr -> m_expr / u_expr .) { reduce using rule 43 (m_expr -> m_expr / u_expr .) ] reduce using rule 43 (m_expr -> m_expr / u_expr .) : reduce using rule 43 (m_expr -> m_expr / u_expr .) state 194 (44) m_expr -> m_expr ^ u_expr . * reduce using rule 44 (m_expr -> m_expr ^ u_expr .) / reduce using rule 44 (m_expr -> m_expr ^ u_expr .) ^ reduce using rule 44 (m_expr -> m_expr ^ u_expr .) + reduce using rule 44 (m_expr -> m_expr ^ u_expr .) - reduce using rule 44 (m_expr -> m_expr ^ u_expr .) < reduce using rule 44 (m_expr -> m_expr ^ u_expr .) > reduce using rule 44 (m_expr -> m_expr ^ u_expr .) GTE reduce using rule 44 (m_expr -> m_expr ^ u_expr .) LTE reduce using rule 44 (m_expr -> m_expr ^ u_expr .) NEQ reduce using rule 44 (m_expr -> m_expr ^ u_expr .) ISEQUAL reduce using rule 44 (m_expr -> m_expr ^ u_expr .) IN reduce using rule 44 (m_expr -> m_expr ^ u_expr .) NOT reduce using rule 44 (m_expr -> m_expr ^ u_expr .) AND reduce using rule 44 (m_expr -> m_expr ^ u_expr .) OR reduce using rule 44 (m_expr -> m_expr ^ u_expr .) ; reduce using rule 44 (m_expr -> m_expr ^ u_expr .) BREAK reduce using rule 44 (m_expr -> m_expr ^ u_expr .) NEXT reduce using rule 44 (m_expr -> m_expr ^ u_expr .) IF reduce using rule 44 (m_expr -> m_expr ^ u_expr .) FOR reduce using rule 44 (m_expr -> m_expr ^ u_expr .) WHERE reduce using rule 44 (m_expr -> m_expr ^ u_expr .) SWITCH reduce using rule 44 (m_expr -> m_expr ^ u_expr .) FUNCTION reduce using rule 44 (m_expr -> m_expr ^ u_expr .) PRINT reduce using rule 44 (m_expr -> m_expr ^ u_expr .) DO reduce using rule 44 (m_expr -> m_expr ^ u_expr .) LOOP reduce using rule 44 (m_expr -> m_expr ^ u_expr .) WITH reduce using rule 44 (m_expr -> m_expr ^ u_expr .) ( reduce using rule 44 (m_expr -> m_expr ^ u_expr .) [ reduce using rule 44 (m_expr -> m_expr ^ u_expr .) ID reduce using rule 44 (m_expr -> m_expr ^ u_expr .) ITEM_TAG reduce using rule 44 (m_expr -> m_expr ^ u_expr .) INTEGER reduce using rule 44 (m_expr -> m_expr ^ u_expr .) HEXINT reduce using rule 44 (m_expr -> m_expr ^ u_expr .) OCTINT reduce using rule 44 (m_expr -> m_expr ^ u_expr .) BININT reduce using rule 44 (m_expr -> m_expr ^ u_expr .) REAL reduce using rule 44 (m_expr -> m_expr ^ u_expr .) IMAGINARY reduce using rule 44 (m_expr -> m_expr ^ u_expr .) STRPREFIX reduce using rule 44 (m_expr -> m_expr ^ u_expr .) SHORTSTRING reduce using rule 44 (m_expr -> m_expr ^ u_expr .) LONGSTRING reduce using rule 44 (m_expr -> m_expr ^ u_expr .) ` reduce using rule 44 (m_expr -> m_expr ^ u_expr .) $end reduce using rule 44 (m_expr -> m_expr ^ u_expr .) } reduce using rule 44 (m_expr -> m_expr ^ u_expr .) ELSE reduce using rule 44 (m_expr -> m_expr ^ u_expr .) DEFAULT reduce using rule 44 (m_expr -> m_expr ^ u_expr .) CASE reduce using rule 44 (m_expr -> m_expr ^ u_expr .) ) reduce using rule 44 (m_expr -> m_expr ^ u_expr .) , reduce using rule 44 (m_expr -> m_expr ^ u_expr .) { reduce using rule 44 (m_expr -> m_expr ^ u_expr .) ] reduce using rule 44 (m_expr -> m_expr ^ u_expr .) : reduce using rule 44 (m_expr -> m_expr ^ u_expr .) state 195 (17) expression_list -> expression_list , expression . ) reduce using rule 17 (expression_list -> expression_list , expression .) , reduce using rule 17 (expression_list -> expression_list , expression .) ` reduce using rule 17 (expression_list -> expression_list , expression .) IN reduce using rule 17 (expression_list -> expression_list , expression .) ; reduce using rule 17 (expression_list -> expression_list , expression .) BREAK reduce using rule 17 (expression_list -> expression_list , expression .) NEXT reduce using rule 17 (expression_list -> expression_list , expression .) IF reduce using rule 17 (expression_list -> expression_list , expression .) FOR reduce using rule 17 (expression_list -> expression_list , expression .) WHERE reduce using rule 17 (expression_list -> expression_list , expression .) SWITCH reduce using rule 17 (expression_list -> expression_list , expression .) FUNCTION reduce using rule 17 (expression_list -> expression_list , expression .) PRINT reduce using rule 17 (expression_list -> expression_list , expression .) DO reduce using rule 17 (expression_list -> expression_list , expression .) LOOP reduce using rule 17 (expression_list -> expression_list , expression .) WITH reduce using rule 17 (expression_list -> expression_list , expression .) ( reduce using rule 17 (expression_list -> expression_list , expression .) [ reduce using rule 17 (expression_list -> expression_list , expression .) ID reduce using rule 17 (expression_list -> expression_list , expression .) ITEM_TAG reduce using rule 17 (expression_list -> expression_list , expression .) INTEGER reduce using rule 17 (expression_list -> expression_list , expression .) HEXINT reduce using rule 17 (expression_list -> expression_list , expression .) OCTINT reduce using rule 17 (expression_list -> expression_list , expression .) BININT reduce using rule 17 (expression_list -> expression_list , expression .) REAL reduce using rule 17 (expression_list -> expression_list , expression .) IMAGINARY reduce using rule 17 (expression_list -> expression_list , expression .) STRPREFIX reduce using rule 17 (expression_list -> expression_list , expression .) SHORTSTRING reduce using rule 17 (expression_list -> expression_list , expression .) LONGSTRING reduce using rule 17 (expression_list -> expression_list , expression .) $end reduce using rule 17 (expression_list -> expression_list , expression .) } reduce using rule 17 (expression_list -> expression_list , expression .) ELSE reduce using rule 17 (expression_list -> expression_list , expression .) DEFAULT reduce using rule 17 (expression_list -> expression_list , expression .) CASE reduce using rule 17 (expression_list -> expression_list , expression .) ] reduce using rule 17 (expression_list -> expression_list , expression .) { reduce using rule 17 (expression_list -> expression_list , expression .) state 196 (23) or_test -> or_test OR and_test . (25) and_test -> and_test . AND not_test , reduce using rule 23 (or_test -> or_test OR and_test .) OR reduce using rule 23 (or_test -> or_test OR and_test .) FOR reduce using rule 23 (or_test -> or_test OR and_test .) IF reduce using rule 23 (or_test -> or_test OR and_test .) ] reduce using rule 23 (or_test -> or_test OR and_test .) : reduce using rule 23 (or_test -> or_test OR and_test .) IN reduce using rule 23 (or_test -> or_test OR and_test .) ; reduce using rule 23 (or_test -> or_test OR and_test .) BREAK reduce using rule 23 (or_test -> or_test OR and_test .) NEXT reduce using rule 23 (or_test -> or_test OR and_test .) WHERE reduce using rule 23 (or_test -> or_test OR and_test .) SWITCH reduce using rule 23 (or_test -> or_test OR and_test .) FUNCTION reduce using rule 23 (or_test -> or_test OR and_test .) PRINT reduce using rule 23 (or_test -> or_test OR and_test .) DO reduce using rule 23 (or_test -> or_test OR and_test .) LOOP reduce using rule 23 (or_test -> or_test OR and_test .) WITH reduce using rule 23 (or_test -> or_test OR and_test .) ( reduce using rule 23 (or_test -> or_test OR and_test .) [ reduce using rule 23 (or_test -> or_test OR and_test .) ID reduce using rule 23 (or_test -> or_test OR and_test .) ITEM_TAG reduce using rule 23 (or_test -> or_test OR and_test .) INTEGER reduce using rule 23 (or_test -> or_test OR and_test .) HEXINT reduce using rule 23 (or_test -> or_test OR and_test .) OCTINT reduce using rule 23 (or_test -> or_test OR and_test .) BININT reduce using rule 23 (or_test -> or_test OR and_test .) REAL reduce using rule 23 (or_test -> or_test OR and_test .) IMAGINARY reduce using rule 23 (or_test -> or_test OR and_test .) STRPREFIX reduce using rule 23 (or_test -> or_test OR and_test .) SHORTSTRING reduce using rule 23 (or_test -> or_test OR and_test .) LONGSTRING reduce using rule 23 (or_test -> or_test OR and_test .) ` reduce using rule 23 (or_test -> or_test OR and_test .) $end reduce using rule 23 (or_test -> or_test OR and_test .) } reduce using rule 23 (or_test -> or_test OR and_test .) ELSE reduce using rule 23 (or_test -> or_test OR and_test .) DEFAULT reduce using rule 23 (or_test -> or_test OR and_test .) CASE reduce using rule 23 (or_test -> or_test OR and_test .) ) reduce using rule 23 (or_test -> or_test OR and_test .) { reduce using rule 23 (or_test -> or_test OR and_test .) AND shift and go to state 139 state 197 (154) where_stmt -> WHERE expression suite ELSE . suite (137) suite -> . simple_stmt (138) suite -> . compound_stmt (139) suite -> . open_brace statement_block close_brace (9) simple_stmt -> . assignment_stmt (10) simple_stmt -> . augmented_assignment_stmt (11) simple_stmt -> . fancy_drel_assignment_stmt (12) simple_stmt -> . print_stmt (13) simple_stmt -> . BREAK (14) simple_stmt -> . NEXT (127) compound_stmt -> . if_stmt (128) compound_stmt -> . for_stmt (129) compound_stmt -> . do_stmt (130) compound_stmt -> . loop_stmt (131) compound_stmt -> . with_stmt (132) compound_stmt -> . where_stmt (133) compound_stmt -> . switch_stmt (134) compound_stmt -> . funcdef (140) open_brace -> . { (124) assignment_stmt -> . target_list = expression_list (120) augmented_assignment_stmt -> . target AUGOP expression_list (121) fancy_drel_assignment_stmt -> . primary ( dotlist ) (15) print_stmt -> . PRINT expression (135) if_stmt -> . IF expression suite (136) if_stmt -> . if_stmt ELSE suite (144) for_stmt -> . FOR target_list IN expression_list suite (149) do_stmt -> . do_stmt_head suite (145) loop_stmt -> . loop_head suite (152) with_stmt -> . with_head suite (154) where_stmt -> . WHERE expression suite ELSE suite (155) switch_stmt -> . SWITCH ID open_brace caselist DEFAULT suite close_brace (158) funcdef -> . FUNCTION ID ( arglist ) suite (125) target_list -> . target (126) target_list -> . target_list , target (19) target -> . primary (20) target -> . ( target_list ) (21) target -> . [ target_list ] (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (150) do_stmt_head -> . DO ID = expression , expression (151) do_stmt_head -> . DO ID = expression , expression , expression (146) loop_head -> . LOOP ID AS ID (147) loop_head -> . LOOP ID AS ID : ID (148) loop_head -> . LOOP ID AS ID : ID comp_operator ID (153) with_head -> . WITH ID AS ID (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] BREAK shift and go to state 56 NEXT shift and go to state 7 { shift and go to state 69 PRINT shift and go to state 28 IF shift and go to state 61 FOR shift and go to state 30 WHERE shift and go to state 19 SWITCH shift and go to state 46 FUNCTION shift and go to state 36 ( shift and go to state 6 [ shift and go to state 38 DO shift and go to state 58 LOOP shift and go to state 25 WITH shift and go to state 5 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ` shift and go to state 20 fancy_drel_assignment_stmt shift and go to state 26 primary_att shift and go to state 41 atom shift and go to state 2 primary shift and go to state 42 stringliteral shift and go to state 23 item_tag shift and go to state 52 switch_stmt shift and go to state 43 do_stmt_head shift and go to state 4 enclosure shift and go to state 29 parenth_form shift and go to state 8 simple_stmt shift and go to state 66 literal shift and go to state 45 assignment_stmt shift and go to state 32 call shift and go to state 47 string_conversion shift and go to state 49 with_head shift and go to state 51 suite shift and go to state 221 loop_head shift and go to state 12 do_stmt shift and go to state 13 compound_stmt shift and go to state 67 attributeref shift and go to state 9 simple_slicing shift and go to state 37 print_stmt shift and go to state 50 loop_stmt shift and go to state 15 slicing shift and go to state 17 target_list shift and go to state 63 for_stmt shift and go to state 18 augmented_assignment_stmt shift and go to state 27 funcdef shift and go to state 3 target shift and go to state 54 if_stmt shift and go to state 21 extended_slicing shift and go to state 34 list_display shift and go to state 22 where_stmt shift and go to state 39 open_brace shift and go to state 68 with_stmt shift and go to state 24 subscription shift and go to state 53 state 198 (146) loop_head -> LOOP ID AS ID . (147) loop_head -> LOOP ID AS ID . : ID (148) loop_head -> LOOP ID AS ID . : ID comp_operator ID BREAK reduce using rule 146 (loop_head -> LOOP ID AS ID .) NEXT reduce using rule 146 (loop_head -> LOOP ID AS ID .) { reduce using rule 146 (loop_head -> LOOP ID AS ID .) PRINT reduce using rule 146 (loop_head -> LOOP ID AS ID .) IF reduce using rule 146 (loop_head -> LOOP ID AS ID .) FOR reduce using rule 146 (loop_head -> LOOP ID AS ID .) WHERE reduce using rule 146 (loop_head -> LOOP ID AS ID .) SWITCH reduce using rule 146 (loop_head -> LOOP ID AS ID .) FUNCTION reduce using rule 146 (loop_head -> LOOP ID AS ID .) ( reduce using rule 146 (loop_head -> LOOP ID AS ID .) [ reduce using rule 146 (loop_head -> LOOP ID AS ID .) DO reduce using rule 146 (loop_head -> LOOP ID AS ID .) LOOP reduce using rule 146 (loop_head -> LOOP ID AS ID .) WITH reduce using rule 146 (loop_head -> LOOP ID AS ID .) ID reduce using rule 146 (loop_head -> LOOP ID AS ID .) ITEM_TAG reduce using rule 146 (loop_head -> LOOP ID AS ID .) INTEGER reduce using rule 146 (loop_head -> LOOP ID AS ID .) HEXINT reduce using rule 146 (loop_head -> LOOP ID AS ID .) OCTINT reduce using rule 146 (loop_head -> LOOP ID AS ID .) BININT reduce using rule 146 (loop_head -> LOOP ID AS ID .) REAL reduce using rule 146 (loop_head -> LOOP ID AS ID .) IMAGINARY reduce using rule 146 (loop_head -> LOOP ID AS ID .) STRPREFIX reduce using rule 146 (loop_head -> LOOP ID AS ID .) SHORTSTRING reduce using rule 146 (loop_head -> LOOP ID AS ID .) LONGSTRING reduce using rule 146 (loop_head -> LOOP ID AS ID .) ` reduce using rule 146 (loop_head -> LOOP ID AS ID .) : shift and go to state 222 state 199 (144) for_stmt -> FOR target_list IN expression_list . suite (17) expression_list -> expression_list . , expression (137) suite -> . simple_stmt (138) suite -> . compound_stmt (139) suite -> . open_brace statement_block close_brace (9) simple_stmt -> . assignment_stmt (10) simple_stmt -> . augmented_assignment_stmt (11) simple_stmt -> . fancy_drel_assignment_stmt (12) simple_stmt -> . print_stmt (13) simple_stmt -> . BREAK (14) simple_stmt -> . NEXT (127) compound_stmt -> . if_stmt (128) compound_stmt -> . for_stmt (129) compound_stmt -> . do_stmt (130) compound_stmt -> . loop_stmt (131) compound_stmt -> . with_stmt (132) compound_stmt -> . where_stmt (133) compound_stmt -> . switch_stmt (134) compound_stmt -> . funcdef (140) open_brace -> . { (124) assignment_stmt -> . target_list = expression_list (120) augmented_assignment_stmt -> . target AUGOP expression_list (121) fancy_drel_assignment_stmt -> . primary ( dotlist ) (15) print_stmt -> . PRINT expression (135) if_stmt -> . IF expression suite (136) if_stmt -> . if_stmt ELSE suite (144) for_stmt -> . FOR target_list IN expression_list suite (149) do_stmt -> . do_stmt_head suite (145) loop_stmt -> . loop_head suite (152) with_stmt -> . with_head suite (154) where_stmt -> . WHERE expression suite ELSE suite (155) switch_stmt -> . SWITCH ID open_brace caselist DEFAULT suite close_brace (158) funcdef -> . FUNCTION ID ( arglist ) suite (125) target_list -> . target (126) target_list -> . target_list , target (19) target -> . primary (20) target -> . ( target_list ) (21) target -> . [ target_list ] (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (150) do_stmt_head -> . DO ID = expression , expression (151) do_stmt_head -> . DO ID = expression , expression , expression (146) loop_head -> . LOOP ID AS ID (147) loop_head -> . LOOP ID AS ID : ID (148) loop_head -> . LOOP ID AS ID : ID comp_operator ID (153) with_head -> . WITH ID AS ID (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] , shift and go to state 145 BREAK shift and go to state 56 NEXT shift and go to state 7 { shift and go to state 69 PRINT shift and go to state 28 IF shift and go to state 61 FOR shift and go to state 30 WHERE shift and go to state 19 SWITCH shift and go to state 46 FUNCTION shift and go to state 36 ( shift and go to state 6 [ shift and go to state 38 DO shift and go to state 58 LOOP shift and go to state 25 WITH shift and go to state 5 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ` shift and go to state 20 fancy_drel_assignment_stmt shift and go to state 26 primary_att shift and go to state 41 atom shift and go to state 2 primary shift and go to state 42 stringliteral shift and go to state 23 item_tag shift and go to state 52 switch_stmt shift and go to state 43 do_stmt_head shift and go to state 4 enclosure shift and go to state 29 parenth_form shift and go to state 8 simple_stmt shift and go to state 66 literal shift and go to state 45 assignment_stmt shift and go to state 32 call shift and go to state 47 string_conversion shift and go to state 49 with_head shift and go to state 51 suite shift and go to state 223 loop_head shift and go to state 12 do_stmt shift and go to state 13 compound_stmt shift and go to state 67 attributeref shift and go to state 9 simple_slicing shift and go to state 37 print_stmt shift and go to state 50 loop_stmt shift and go to state 15 slicing shift and go to state 17 target_list shift and go to state 63 for_stmt shift and go to state 18 augmented_assignment_stmt shift and go to state 27 funcdef shift and go to state 3 target shift and go to state 54 if_stmt shift and go to state 21 extended_slicing shift and go to state 34 list_display shift and go to state 22 where_stmt shift and go to state 39 open_brace shift and go to state 68 with_stmt shift and go to state 24 subscription shift and go to state 53 state 200 (158) funcdef -> FUNCTION ID ( arglist . ) suite (160) arglist -> arglist . , ID : list_display ) shift and go to state 224 , shift and go to state 225 state 201 (159) arglist -> ID . : list_display : shift and go to state 226 state 202 (85) list_for -> FOR expression_list . IN testlist (86) list_for -> FOR expression_list . IN testlist list_iter (17) expression_list -> expression_list . , expression IN shift and go to state 227 , shift and go to state 145 state 203 (83) listmaker2 -> listmaker2 , . expression (18) expression -> . or_test (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 list_display shift and go to state 22 or_test shift and go to state 86 expression shift and go to state 228 state 204 (82) listmaker2 -> , expression . , reduce using rule 82 (listmaker2 -> , expression .) ] reduce using rule 82 (listmaker2 -> , expression .) state 205 (121) fancy_drel_assignment_stmt -> primary ( dotlist ) . ; reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) } reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) BREAK reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) NEXT reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) IF reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) FOR reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) WHERE reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) SWITCH reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) FUNCTION reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) PRINT reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) DO reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) LOOP reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) WITH reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) ( reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) [ reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) ID reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) ITEM_TAG reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) INTEGER reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) HEXINT reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) OCTINT reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) BININT reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) REAL reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) IMAGINARY reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) STRPREFIX reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) SHORTSTRING reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) LONGSTRING reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) ` reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) $end reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) ELSE reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) DEFAULT reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) CASE reduce using rule 121 (fancy_drel_assignment_stmt -> primary ( dotlist ) .) state 206 (123) dotlist -> dotlist , . . ID = expression . shift and go to state 229 state 207 (122) dotlist -> . ID . = expression = shift and go to state 230 state 208 (116) call -> primary ( argument_list ) . [ reduce using rule 116 (call -> primary ( argument_list ) .) ( reduce using rule 116 (call -> primary ( argument_list ) .) POWER reduce using rule 116 (call -> primary ( argument_list ) .) . reduce using rule 116 (call -> primary ( argument_list ) .) REAL reduce using rule 116 (call -> primary ( argument_list ) .) ] reduce using rule 116 (call -> primary ( argument_list ) .) , reduce using rule 116 (call -> primary ( argument_list ) .) * reduce using rule 116 (call -> primary ( argument_list ) .) / reduce using rule 116 (call -> primary ( argument_list ) .) ^ reduce using rule 116 (call -> primary ( argument_list ) .) + reduce using rule 116 (call -> primary ( argument_list ) .) - reduce using rule 116 (call -> primary ( argument_list ) .) < reduce using rule 116 (call -> primary ( argument_list ) .) > reduce using rule 116 (call -> primary ( argument_list ) .) GTE reduce using rule 116 (call -> primary ( argument_list ) .) LTE reduce using rule 116 (call -> primary ( argument_list ) .) NEQ reduce using rule 116 (call -> primary ( argument_list ) .) ISEQUAL reduce using rule 116 (call -> primary ( argument_list ) .) IN reduce using rule 116 (call -> primary ( argument_list ) .) NOT reduce using rule 116 (call -> primary ( argument_list ) .) AND reduce using rule 116 (call -> primary ( argument_list ) .) OR reduce using rule 116 (call -> primary ( argument_list ) .) FOR reduce using rule 116 (call -> primary ( argument_list ) .) ) reduce using rule 116 (call -> primary ( argument_list ) .) BREAK reduce using rule 116 (call -> primary ( argument_list ) .) NEXT reduce using rule 116 (call -> primary ( argument_list ) .) { reduce using rule 116 (call -> primary ( argument_list ) .) PRINT reduce using rule 116 (call -> primary ( argument_list ) .) IF reduce using rule 116 (call -> primary ( argument_list ) .) WHERE reduce using rule 116 (call -> primary ( argument_list ) .) SWITCH reduce using rule 116 (call -> primary ( argument_list ) .) FUNCTION reduce using rule 116 (call -> primary ( argument_list ) .) DO reduce using rule 116 (call -> primary ( argument_list ) .) LOOP reduce using rule 116 (call -> primary ( argument_list ) .) WITH reduce using rule 116 (call -> primary ( argument_list ) .) ID reduce using rule 116 (call -> primary ( argument_list ) .) ITEM_TAG reduce using rule 116 (call -> primary ( argument_list ) .) INTEGER reduce using rule 116 (call -> primary ( argument_list ) .) HEXINT reduce using rule 116 (call -> primary ( argument_list ) .) OCTINT reduce using rule 116 (call -> primary ( argument_list ) .) BININT reduce using rule 116 (call -> primary ( argument_list ) .) IMAGINARY reduce using rule 116 (call -> primary ( argument_list ) .) STRPREFIX reduce using rule 116 (call -> primary ( argument_list ) .) SHORTSTRING reduce using rule 116 (call -> primary ( argument_list ) .) LONGSTRING reduce using rule 116 (call -> primary ( argument_list ) .) ` reduce using rule 116 (call -> primary ( argument_list ) .) ; reduce using rule 116 (call -> primary ( argument_list ) .) $end reduce using rule 116 (call -> primary ( argument_list ) .) } reduce using rule 116 (call -> primary ( argument_list ) .) ELSE reduce using rule 116 (call -> primary ( argument_list ) .) DEFAULT reduce using rule 116 (call -> primary ( argument_list ) .) CASE reduce using rule 116 (call -> primary ( argument_list ) .) : reduce using rule 116 (call -> primary ( argument_list ) .) AUGOP reduce using rule 116 (call -> primary ( argument_list ) .) = reduce using rule 116 (call -> primary ( argument_list ) .) state 209 (118) argument_list -> argument_list , . func_arg (119) func_arg -> . expression (18) expression -> . or_test (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 func_arg shift and go to state 231 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 list_display shift and go to state 22 or_test shift and go to state 86 expression shift and go to state 164 state 210 (107) slice_list -> slice_list , . slice_item (108) slice_item -> . expression (109) slice_item -> . proper_slice (110) slice_item -> . ELLIPSIS (18) expression -> . or_test (111) proper_slice -> . short_slice (112) proper_slice -> . long_slice (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (101) short_slice -> . : (102) short_slice -> . expression : expression (103) short_slice -> . : expression (104) short_slice -> . expression : (113) long_slice -> . short_slice : (114) long_slice -> . short_slice : expression (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] ELLIPSIS shift and go to state 168 : shift and go to state 169 NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 short_slice shift and go to state 232 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 long_slice shift and go to state 170 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 proper_slice shift and go to state 171 list_display shift and go to state 22 or_test shift and go to state 86 m_expr shift and go to state 82 slice_item shift and go to state 233 expression shift and go to state 234 state 211 (105) extended_slicing -> primary [ slice_list ] . ( reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) [ reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) . reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) REAL reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) AUGOP reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) = reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) , reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) POWER reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) * reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) / reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) ^ reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) + reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) - reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) < reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) > reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) GTE reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) LTE reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) NEQ reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) ISEQUAL reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) IN reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) NOT reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) AND reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) OR reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) ) reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) BREAK reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) NEXT reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) { reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) PRINT reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) IF reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) FOR reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) WHERE reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) SWITCH reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) FUNCTION reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) DO reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) LOOP reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) WITH reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) ID reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) ITEM_TAG reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) INTEGER reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) HEXINT reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) OCTINT reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) BININT reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) IMAGINARY reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) STRPREFIX reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) SHORTSTRING reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) LONGSTRING reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) ` reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) ; reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) $end reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) } reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) ELSE reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) DEFAULT reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) CASE reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) ] reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) : reduce using rule 105 (extended_slicing -> primary [ slice_list ] .) state 212 (100) simple_slicing -> primary [ short_slice ] . ( reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) [ reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) . reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) REAL reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) AUGOP reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) = reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) , reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) POWER reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) * reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) / reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) ^ reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) + reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) - reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) < reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) > reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) GTE reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) LTE reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) NEQ reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) ISEQUAL reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) IN reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) NOT reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) AND reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) OR reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) FOR reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) IF reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) ] reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) ) reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) BREAK reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) NEXT reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) { reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) PRINT reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) WHERE reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) SWITCH reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) FUNCTION reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) DO reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) LOOP reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) WITH reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) ID reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) ITEM_TAG reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) INTEGER reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) HEXINT reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) OCTINT reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) BININT reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) IMAGINARY reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) STRPREFIX reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) SHORTSTRING reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) LONGSTRING reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) ` reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) ; reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) $end reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) } reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) ELSE reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) DEFAULT reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) CASE reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) : reduce using rule 100 (simple_slicing -> primary [ short_slice ] .) state 213 (113) long_slice -> short_slice : . (114) long_slice -> short_slice : . expression (18) expression -> . or_test (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] ] reduce using rule 113 (long_slice -> short_slice : .) , reduce using rule 113 (long_slice -> short_slice : .) NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 list_display shift and go to state 22 or_test shift and go to state 86 expression shift and go to state 235 state 214 (103) short_slice -> : expression . : reduce using rule 103 (short_slice -> : expression .) ] reduce using rule 103 (short_slice -> : expression .) , reduce using rule 103 (short_slice -> : expression .) state 215 (97) subscription -> primary [ expression_list ] . POWER reduce using rule 97 (subscription -> primary [ expression_list ] .) [ reduce using rule 97 (subscription -> primary [ expression_list ] .) ( reduce using rule 97 (subscription -> primary [ expression_list ] .) . reduce using rule 97 (subscription -> primary [ expression_list ] .) REAL reduce using rule 97 (subscription -> primary [ expression_list ] .) * reduce using rule 97 (subscription -> primary [ expression_list ] .) / reduce using rule 97 (subscription -> primary [ expression_list ] .) ^ reduce using rule 97 (subscription -> primary [ expression_list ] .) + reduce using rule 97 (subscription -> primary [ expression_list ] .) - reduce using rule 97 (subscription -> primary [ expression_list ] .) < reduce using rule 97 (subscription -> primary [ expression_list ] .) > reduce using rule 97 (subscription -> primary [ expression_list ] .) GTE reduce using rule 97 (subscription -> primary [ expression_list ] .) LTE reduce using rule 97 (subscription -> primary [ expression_list ] .) NEQ reduce using rule 97 (subscription -> primary [ expression_list ] .) ISEQUAL reduce using rule 97 (subscription -> primary [ expression_list ] .) IN reduce using rule 97 (subscription -> primary [ expression_list ] .) NOT reduce using rule 97 (subscription -> primary [ expression_list ] .) AND reduce using rule 97 (subscription -> primary [ expression_list ] .) OR reduce using rule 97 (subscription -> primary [ expression_list ] .) ) reduce using rule 97 (subscription -> primary [ expression_list ] .) , reduce using rule 97 (subscription -> primary [ expression_list ] .) BREAK reduce using rule 97 (subscription -> primary [ expression_list ] .) NEXT reduce using rule 97 (subscription -> primary [ expression_list ] .) { reduce using rule 97 (subscription -> primary [ expression_list ] .) PRINT reduce using rule 97 (subscription -> primary [ expression_list ] .) IF reduce using rule 97 (subscription -> primary [ expression_list ] .) FOR reduce using rule 97 (subscription -> primary [ expression_list ] .) WHERE reduce using rule 97 (subscription -> primary [ expression_list ] .) SWITCH reduce using rule 97 (subscription -> primary [ expression_list ] .) FUNCTION reduce using rule 97 (subscription -> primary [ expression_list ] .) DO reduce using rule 97 (subscription -> primary [ expression_list ] .) LOOP reduce using rule 97 (subscription -> primary [ expression_list ] .) WITH reduce using rule 97 (subscription -> primary [ expression_list ] .) ID reduce using rule 97 (subscription -> primary [ expression_list ] .) ITEM_TAG reduce using rule 97 (subscription -> primary [ expression_list ] .) INTEGER reduce using rule 97 (subscription -> primary [ expression_list ] .) HEXINT reduce using rule 97 (subscription -> primary [ expression_list ] .) OCTINT reduce using rule 97 (subscription -> primary [ expression_list ] .) BININT reduce using rule 97 (subscription -> primary [ expression_list ] .) IMAGINARY reduce using rule 97 (subscription -> primary [ expression_list ] .) STRPREFIX reduce using rule 97 (subscription -> primary [ expression_list ] .) SHORTSTRING reduce using rule 97 (subscription -> primary [ expression_list ] .) LONGSTRING reduce using rule 97 (subscription -> primary [ expression_list ] .) ` reduce using rule 97 (subscription -> primary [ expression_list ] .) ; reduce using rule 97 (subscription -> primary [ expression_list ] .) $end reduce using rule 97 (subscription -> primary [ expression_list ] .) } reduce using rule 97 (subscription -> primary [ expression_list ] .) ELSE reduce using rule 97 (subscription -> primary [ expression_list ] .) DEFAULT reduce using rule 97 (subscription -> primary [ expression_list ] .) CASE reduce using rule 97 (subscription -> primary [ expression_list ] .) ] reduce using rule 97 (subscription -> primary [ expression_list ] .) : reduce using rule 97 (subscription -> primary [ expression_list ] .) AUGOP reduce using rule 97 (subscription -> primary [ expression_list ] .) = reduce using rule 97 (subscription -> primary [ expression_list ] .) state 216 (102) short_slice -> expression : . expression (104) short_slice -> expression : . (18) expression -> . or_test (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] : reduce using rule 104 (short_slice -> expression : .) ] reduce using rule 104 (short_slice -> expression : .) , reduce using rule 104 (short_slice -> expression : .) NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 list_display shift and go to state 22 or_test shift and go to state 86 expression shift and go to state 236 state 217 (156) caselist -> CASE . target_list suite (125) target_list -> . target (126) target_list -> . target_list , target (19) target -> . primary (20) target -> . ( target_list ) (21) target -> . [ target_list ] (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] ( shift and go to state 6 [ shift and go to state 38 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ` shift and go to state 20 primary_att shift and go to state 41 primary shift and go to state 100 enclosure shift and go to state 29 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 simple_slicing shift and go to state 37 slicing shift and go to state 17 target_list shift and go to state 237 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 target shift and go to state 84 list_display shift and go to state 22 stringliteral shift and go to state 23 state 218 (155) switch_stmt -> SWITCH ID open_brace caselist . DEFAULT suite close_brace (157) caselist -> caselist . CASE target_list suite DEFAULT shift and go to state 239 CASE shift and go to state 238 state 219 (150) do_stmt_head -> DO ID = expression . , expression (151) do_stmt_head -> DO ID = expression . , expression , expression , shift and go to state 240 state 220 (8) stmt_list -> stmt_list ; simple_stmt ; . ; reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) } reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) BREAK reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) NEXT reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) IF reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) FOR reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) WHERE reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) SWITCH reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) FUNCTION reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) PRINT reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) DO reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) LOOP reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) WITH reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) ( reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) [ reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) ID reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) ITEM_TAG reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) INTEGER reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) HEXINT reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) OCTINT reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) BININT reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) REAL reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) IMAGINARY reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) STRPREFIX reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) SHORTSTRING reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) LONGSTRING reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) ` reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) $end reduce using rule 8 (stmt_list -> stmt_list ; simple_stmt ; .) state 221 (154) where_stmt -> WHERE expression suite ELSE suite . BREAK reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) NEXT reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) IF reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) FOR reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) WHERE reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) SWITCH reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) FUNCTION reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) PRINT reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) DO reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) LOOP reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) WITH reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) ( reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) [ reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) ID reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) ITEM_TAG reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) INTEGER reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) HEXINT reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) OCTINT reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) BININT reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) REAL reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) IMAGINARY reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) STRPREFIX reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) SHORTSTRING reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) LONGSTRING reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) ` reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) $end reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) } reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) ELSE reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) DEFAULT reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) CASE reduce using rule 154 (where_stmt -> WHERE expression suite ELSE suite .) state 222 (147) loop_head -> LOOP ID AS ID : . ID (148) loop_head -> LOOP ID AS ID : . ID comp_operator ID ID shift and go to state 241 state 223 (144) for_stmt -> FOR target_list IN expression_list suite . BREAK reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) NEXT reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) IF reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) FOR reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) WHERE reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) SWITCH reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) FUNCTION reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) PRINT reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) DO reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) LOOP reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) WITH reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) ( reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) [ reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) ID reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) ITEM_TAG reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) INTEGER reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) HEXINT reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) OCTINT reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) BININT reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) REAL reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) IMAGINARY reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) STRPREFIX reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) SHORTSTRING reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) LONGSTRING reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) ` reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) $end reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) ELSE reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) } reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) DEFAULT reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) CASE reduce using rule 144 (for_stmt -> FOR target_list IN expression_list suite .) state 224 (158) funcdef -> FUNCTION ID ( arglist ) . suite (137) suite -> . simple_stmt (138) suite -> . compound_stmt (139) suite -> . open_brace statement_block close_brace (9) simple_stmt -> . assignment_stmt (10) simple_stmt -> . augmented_assignment_stmt (11) simple_stmt -> . fancy_drel_assignment_stmt (12) simple_stmt -> . print_stmt (13) simple_stmt -> . BREAK (14) simple_stmt -> . NEXT (127) compound_stmt -> . if_stmt (128) compound_stmt -> . for_stmt (129) compound_stmt -> . do_stmt (130) compound_stmt -> . loop_stmt (131) compound_stmt -> . with_stmt (132) compound_stmt -> . where_stmt (133) compound_stmt -> . switch_stmt (134) compound_stmt -> . funcdef (140) open_brace -> . { (124) assignment_stmt -> . target_list = expression_list (120) augmented_assignment_stmt -> . target AUGOP expression_list (121) fancy_drel_assignment_stmt -> . primary ( dotlist ) (15) print_stmt -> . PRINT expression (135) if_stmt -> . IF expression suite (136) if_stmt -> . if_stmt ELSE suite (144) for_stmt -> . FOR target_list IN expression_list suite (149) do_stmt -> . do_stmt_head suite (145) loop_stmt -> . loop_head suite (152) with_stmt -> . with_head suite (154) where_stmt -> . WHERE expression suite ELSE suite (155) switch_stmt -> . SWITCH ID open_brace caselist DEFAULT suite close_brace (158) funcdef -> . FUNCTION ID ( arglist ) suite (125) target_list -> . target (126) target_list -> . target_list , target (19) target -> . primary (20) target -> . ( target_list ) (21) target -> . [ target_list ] (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (150) do_stmt_head -> . DO ID = expression , expression (151) do_stmt_head -> . DO ID = expression , expression , expression (146) loop_head -> . LOOP ID AS ID (147) loop_head -> . LOOP ID AS ID : ID (148) loop_head -> . LOOP ID AS ID : ID comp_operator ID (153) with_head -> . WITH ID AS ID (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] BREAK shift and go to state 56 NEXT shift and go to state 7 { shift and go to state 69 PRINT shift and go to state 28 IF shift and go to state 61 FOR shift and go to state 30 WHERE shift and go to state 19 SWITCH shift and go to state 46 FUNCTION shift and go to state 36 ( shift and go to state 6 [ shift and go to state 38 DO shift and go to state 58 LOOP shift and go to state 25 WITH shift and go to state 5 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ` shift and go to state 20 fancy_drel_assignment_stmt shift and go to state 26 primary_att shift and go to state 41 atom shift and go to state 2 primary shift and go to state 42 stringliteral shift and go to state 23 item_tag shift and go to state 52 switch_stmt shift and go to state 43 do_stmt_head shift and go to state 4 enclosure shift and go to state 29 parenth_form shift and go to state 8 simple_stmt shift and go to state 66 literal shift and go to state 45 assignment_stmt shift and go to state 32 call shift and go to state 47 string_conversion shift and go to state 49 with_head shift and go to state 51 suite shift and go to state 242 loop_head shift and go to state 12 do_stmt shift and go to state 13 compound_stmt shift and go to state 67 attributeref shift and go to state 9 simple_slicing shift and go to state 37 print_stmt shift and go to state 50 loop_stmt shift and go to state 15 slicing shift and go to state 17 target_list shift and go to state 63 for_stmt shift and go to state 18 augmented_assignment_stmt shift and go to state 27 funcdef shift and go to state 3 target shift and go to state 54 if_stmt shift and go to state 21 extended_slicing shift and go to state 34 list_display shift and go to state 22 where_stmt shift and go to state 39 open_brace shift and go to state 68 with_stmt shift and go to state 24 subscription shift and go to state 53 state 225 (160) arglist -> arglist , . ID : list_display ID shift and go to state 243 state 226 (159) arglist -> ID : . list_display (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] [ shift and go to state 93 list_display shift and go to state 244 state 227 (85) list_for -> FOR expression_list IN . testlist (86) list_for -> FOR expression_list IN . testlist list_iter (87) testlist -> . or_test (88) testlist -> . testlist , or_test (89) testlist -> . testlist , or_test , (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 string_conversion shift and go to state 49 call shift and go to state 47 power shift and go to state 75 a_expr shift and go to state 78 testlist shift and go to state 245 and_test shift and go to state 80 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 extended_slicing shift and go to state 34 list_display shift and go to state 22 or_test shift and go to state 246 state 228 (83) listmaker2 -> listmaker2 , expression . , reduce using rule 83 (listmaker2 -> listmaker2 , expression .) ] reduce using rule 83 (listmaker2 -> listmaker2 , expression .) state 229 (123) dotlist -> dotlist , . . ID = expression ID shift and go to state 247 state 230 (122) dotlist -> . ID = . expression (18) expression -> . or_test (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 list_display shift and go to state 22 or_test shift and go to state 86 expression shift and go to state 248 state 231 (118) argument_list -> argument_list , func_arg . ) reduce using rule 118 (argument_list -> argument_list , func_arg .) , reduce using rule 118 (argument_list -> argument_list , func_arg .) state 232 (111) proper_slice -> short_slice . (113) long_slice -> short_slice . : (114) long_slice -> short_slice . : expression ] reduce using rule 111 (proper_slice -> short_slice .) , reduce using rule 111 (proper_slice -> short_slice .) : shift and go to state 213 state 233 (107) slice_list -> slice_list , slice_item . ] reduce using rule 107 (slice_list -> slice_list , slice_item .) , reduce using rule 107 (slice_list -> slice_list , slice_item .) state 234 (108) slice_item -> expression . (102) short_slice -> expression . : expression (104) short_slice -> expression . : ] reduce using rule 108 (slice_item -> expression .) , reduce using rule 108 (slice_item -> expression .) : shift and go to state 216 state 235 (114) long_slice -> short_slice : expression . ] reduce using rule 114 (long_slice -> short_slice : expression .) , reduce using rule 114 (long_slice -> short_slice : expression .) state 236 (102) short_slice -> expression : expression . : reduce using rule 102 (short_slice -> expression : expression .) ] reduce using rule 102 (short_slice -> expression : expression .) , reduce using rule 102 (short_slice -> expression : expression .) state 237 (156) caselist -> CASE target_list . suite (126) target_list -> target_list . , target (137) suite -> . simple_stmt (138) suite -> . compound_stmt (139) suite -> . open_brace statement_block close_brace (9) simple_stmt -> . assignment_stmt (10) simple_stmt -> . augmented_assignment_stmt (11) simple_stmt -> . fancy_drel_assignment_stmt (12) simple_stmt -> . print_stmt (13) simple_stmt -> . BREAK (14) simple_stmt -> . NEXT (127) compound_stmt -> . if_stmt (128) compound_stmt -> . for_stmt (129) compound_stmt -> . do_stmt (130) compound_stmt -> . loop_stmt (131) compound_stmt -> . with_stmt (132) compound_stmt -> . where_stmt (133) compound_stmt -> . switch_stmt (134) compound_stmt -> . funcdef (140) open_brace -> . { (124) assignment_stmt -> . target_list = expression_list (120) augmented_assignment_stmt -> . target AUGOP expression_list (121) fancy_drel_assignment_stmt -> . primary ( dotlist ) (15) print_stmt -> . PRINT expression (135) if_stmt -> . IF expression suite (136) if_stmt -> . if_stmt ELSE suite (144) for_stmt -> . FOR target_list IN expression_list suite (149) do_stmt -> . do_stmt_head suite (145) loop_stmt -> . loop_head suite (152) with_stmt -> . with_head suite (154) where_stmt -> . WHERE expression suite ELSE suite (155) switch_stmt -> . SWITCH ID open_brace caselist DEFAULT suite close_brace (158) funcdef -> . FUNCTION ID ( arglist ) suite (125) target_list -> . target (126) target_list -> . target_list , target (19) target -> . primary (20) target -> . ( target_list ) (21) target -> . [ target_list ] (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (150) do_stmt_head -> . DO ID = expression , expression (151) do_stmt_head -> . DO ID = expression , expression , expression (146) loop_head -> . LOOP ID AS ID (147) loop_head -> . LOOP ID AS ID : ID (148) loop_head -> . LOOP ID AS ID : ID comp_operator ID (153) with_head -> . WITH ID AS ID (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] , shift and go to state 119 BREAK shift and go to state 56 NEXT shift and go to state 7 { shift and go to state 69 PRINT shift and go to state 28 IF shift and go to state 61 FOR shift and go to state 30 WHERE shift and go to state 19 SWITCH shift and go to state 46 FUNCTION shift and go to state 36 ( shift and go to state 6 [ shift and go to state 38 DO shift and go to state 58 LOOP shift and go to state 25 WITH shift and go to state 5 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ` shift and go to state 20 fancy_drel_assignment_stmt shift and go to state 26 primary_att shift and go to state 41 atom shift and go to state 2 primary shift and go to state 42 stringliteral shift and go to state 23 item_tag shift and go to state 52 switch_stmt shift and go to state 43 do_stmt_head shift and go to state 4 enclosure shift and go to state 29 parenth_form shift and go to state 8 simple_stmt shift and go to state 66 literal shift and go to state 45 assignment_stmt shift and go to state 32 call shift and go to state 47 string_conversion shift and go to state 49 with_head shift and go to state 51 suite shift and go to state 249 loop_head shift and go to state 12 do_stmt shift and go to state 13 compound_stmt shift and go to state 67 attributeref shift and go to state 9 simple_slicing shift and go to state 37 print_stmt shift and go to state 50 loop_stmt shift and go to state 15 slicing shift and go to state 17 target_list shift and go to state 63 for_stmt shift and go to state 18 augmented_assignment_stmt shift and go to state 27 funcdef shift and go to state 3 if_stmt shift and go to state 21 target shift and go to state 54 extended_slicing shift and go to state 34 list_display shift and go to state 22 where_stmt shift and go to state 39 open_brace shift and go to state 68 with_stmt shift and go to state 24 subscription shift and go to state 53 state 238 (157) caselist -> caselist CASE . target_list suite (125) target_list -> . target (126) target_list -> . target_list , target (19) target -> . primary (20) target -> . ( target_list ) (21) target -> . [ target_list ] (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] ( shift and go to state 6 [ shift and go to state 38 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ` shift and go to state 20 primary_att shift and go to state 41 primary shift and go to state 100 enclosure shift and go to state 29 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 simple_slicing shift and go to state 37 slicing shift and go to state 17 target_list shift and go to state 250 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 target shift and go to state 84 list_display shift and go to state 22 stringliteral shift and go to state 23 state 239 (155) switch_stmt -> SWITCH ID open_brace caselist DEFAULT . suite close_brace (137) suite -> . simple_stmt (138) suite -> . compound_stmt (139) suite -> . open_brace statement_block close_brace (9) simple_stmt -> . assignment_stmt (10) simple_stmt -> . augmented_assignment_stmt (11) simple_stmt -> . fancy_drel_assignment_stmt (12) simple_stmt -> . print_stmt (13) simple_stmt -> . BREAK (14) simple_stmt -> . NEXT (127) compound_stmt -> . if_stmt (128) compound_stmt -> . for_stmt (129) compound_stmt -> . do_stmt (130) compound_stmt -> . loop_stmt (131) compound_stmt -> . with_stmt (132) compound_stmt -> . where_stmt (133) compound_stmt -> . switch_stmt (134) compound_stmt -> . funcdef (140) open_brace -> . { (124) assignment_stmt -> . target_list = expression_list (120) augmented_assignment_stmt -> . target AUGOP expression_list (121) fancy_drel_assignment_stmt -> . primary ( dotlist ) (15) print_stmt -> . PRINT expression (135) if_stmt -> . IF expression suite (136) if_stmt -> . if_stmt ELSE suite (144) for_stmt -> . FOR target_list IN expression_list suite (149) do_stmt -> . do_stmt_head suite (145) loop_stmt -> . loop_head suite (152) with_stmt -> . with_head suite (154) where_stmt -> . WHERE expression suite ELSE suite (155) switch_stmt -> . SWITCH ID open_brace caselist DEFAULT suite close_brace (158) funcdef -> . FUNCTION ID ( arglist ) suite (125) target_list -> . target (126) target_list -> . target_list , target (19) target -> . primary (20) target -> . ( target_list ) (21) target -> . [ target_list ] (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (150) do_stmt_head -> . DO ID = expression , expression (151) do_stmt_head -> . DO ID = expression , expression , expression (146) loop_head -> . LOOP ID AS ID (147) loop_head -> . LOOP ID AS ID : ID (148) loop_head -> . LOOP ID AS ID : ID comp_operator ID (153) with_head -> . WITH ID AS ID (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] BREAK shift and go to state 56 NEXT shift and go to state 7 { shift and go to state 69 PRINT shift and go to state 28 IF shift and go to state 61 FOR shift and go to state 30 WHERE shift and go to state 19 SWITCH shift and go to state 46 FUNCTION shift and go to state 36 ( shift and go to state 6 [ shift and go to state 38 DO shift and go to state 58 LOOP shift and go to state 25 WITH shift and go to state 5 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ` shift and go to state 20 fancy_drel_assignment_stmt shift and go to state 26 primary_att shift and go to state 41 atom shift and go to state 2 primary shift and go to state 42 stringliteral shift and go to state 23 item_tag shift and go to state 52 switch_stmt shift and go to state 43 do_stmt_head shift and go to state 4 enclosure shift and go to state 29 parenth_form shift and go to state 8 simple_stmt shift and go to state 66 literal shift and go to state 45 assignment_stmt shift and go to state 32 call shift and go to state 47 string_conversion shift and go to state 49 with_head shift and go to state 51 suite shift and go to state 251 loop_head shift and go to state 12 do_stmt shift and go to state 13 compound_stmt shift and go to state 67 attributeref shift and go to state 9 simple_slicing shift and go to state 37 print_stmt shift and go to state 50 loop_stmt shift and go to state 15 slicing shift and go to state 17 target_list shift and go to state 63 for_stmt shift and go to state 18 augmented_assignment_stmt shift and go to state 27 funcdef shift and go to state 3 target shift and go to state 54 if_stmt shift and go to state 21 extended_slicing shift and go to state 34 list_display shift and go to state 22 where_stmt shift and go to state 39 open_brace shift and go to state 68 with_stmt shift and go to state 24 subscription shift and go to state 53 state 240 (150) do_stmt_head -> DO ID = expression , . expression (151) do_stmt_head -> DO ID = expression , . expression , expression (18) expression -> . or_test (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 list_display shift and go to state 22 or_test shift and go to state 86 expression shift and go to state 252 state 241 (147) loop_head -> LOOP ID AS ID : ID . (148) loop_head -> LOOP ID AS ID : ID . comp_operator ID (30) comp_operator -> . < (31) comp_operator -> . > (32) comp_operator -> . GTE (33) comp_operator -> . LTE (34) comp_operator -> . NEQ (35) comp_operator -> . ISEQUAL (36) comp_operator -> . IN (37) comp_operator -> . NOT IN BREAK reduce using rule 147 (loop_head -> LOOP ID AS ID : ID .) NEXT reduce using rule 147 (loop_head -> LOOP ID AS ID : ID .) { reduce using rule 147 (loop_head -> LOOP ID AS ID : ID .) PRINT reduce using rule 147 (loop_head -> LOOP ID AS ID : ID .) IF reduce using rule 147 (loop_head -> LOOP ID AS ID : ID .) FOR reduce using rule 147 (loop_head -> LOOP ID AS ID : ID .) WHERE reduce using rule 147 (loop_head -> LOOP ID AS ID : ID .) SWITCH reduce using rule 147 (loop_head -> LOOP ID AS ID : ID .) FUNCTION reduce using rule 147 (loop_head -> LOOP ID AS ID : ID .) ( reduce using rule 147 (loop_head -> LOOP ID AS ID : ID .) [ reduce using rule 147 (loop_head -> LOOP ID AS ID : ID .) DO reduce using rule 147 (loop_head -> LOOP ID AS ID : ID .) LOOP reduce using rule 147 (loop_head -> LOOP ID AS ID : ID .) WITH reduce using rule 147 (loop_head -> LOOP ID AS ID : ID .) ID reduce using rule 147 (loop_head -> LOOP ID AS ID : ID .) ITEM_TAG reduce using rule 147 (loop_head -> LOOP ID AS ID : ID .) INTEGER reduce using rule 147 (loop_head -> LOOP ID AS ID : ID .) HEXINT reduce using rule 147 (loop_head -> LOOP ID AS ID : ID .) OCTINT reduce using rule 147 (loop_head -> LOOP ID AS ID : ID .) BININT reduce using rule 147 (loop_head -> LOOP ID AS ID : ID .) REAL reduce using rule 147 (loop_head -> LOOP ID AS ID : ID .) IMAGINARY reduce using rule 147 (loop_head -> LOOP ID AS ID : ID .) STRPREFIX reduce using rule 147 (loop_head -> LOOP ID AS ID : ID .) SHORTSTRING reduce using rule 147 (loop_head -> LOOP ID AS ID : ID .) LONGSTRING reduce using rule 147 (loop_head -> LOOP ID AS ID : ID .) ` reduce using rule 147 (loop_head -> LOOP ID AS ID : ID .) < shift and go to state 136 > shift and go to state 137 GTE shift and go to state 132 LTE shift and go to state 127 NEQ shift and go to state 135 ISEQUAL shift and go to state 133 IN shift and go to state 130 NOT shift and go to state 134 comp_operator shift and go to state 253 state 242 (158) funcdef -> FUNCTION ID ( arglist ) suite . BREAK reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) NEXT reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) IF reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) FOR reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) WHERE reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) SWITCH reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) FUNCTION reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) PRINT reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) DO reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) LOOP reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) WITH reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) ( reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) [ reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) ID reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) ITEM_TAG reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) INTEGER reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) HEXINT reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) OCTINT reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) BININT reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) REAL reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) IMAGINARY reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) STRPREFIX reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) SHORTSTRING reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) LONGSTRING reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) ` reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) $end reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) } reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) ELSE reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) DEFAULT reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) CASE reduce using rule 158 (funcdef -> FUNCTION ID ( arglist ) suite .) state 243 (160) arglist -> arglist , ID . : list_display : shift and go to state 254 state 244 (159) arglist -> ID : list_display . ) reduce using rule 159 (arglist -> ID : list_display .) , reduce using rule 159 (arglist -> ID : list_display .) state 245 (85) list_for -> FOR expression_list IN testlist . (86) list_for -> FOR expression_list IN testlist . list_iter (88) testlist -> testlist . , or_test (89) testlist -> testlist . , or_test , (90) list_iter -> . list_for (91) list_iter -> . list_if (85) list_for -> . FOR expression_list IN testlist (86) list_for -> . FOR expression_list IN testlist list_iter (92) list_if -> . IF or_test (93) list_if -> . IF or_test list_iter ] reduce using rule 85 (list_for -> FOR expression_list IN testlist .) , shift and go to state 255 FOR shift and go to state 155 IF shift and go to state 259 list_iter shift and go to state 256 list_if shift and go to state 257 list_for shift and go to state 258 state 246 (87) testlist -> or_test . (23) or_test -> or_test . OR and_test , reduce using rule 87 (testlist -> or_test .) FOR reduce using rule 87 (testlist -> or_test .) IF reduce using rule 87 (testlist -> or_test .) ] reduce using rule 87 (testlist -> or_test .) OR shift and go to state 146 state 247 (123) dotlist -> dotlist , . ID . = expression = shift and go to state 260 state 248 (122) dotlist -> . ID = expression . ) reduce using rule 122 (dotlist -> . ID = expression .) , reduce using rule 122 (dotlist -> . ID = expression .) state 249 (156) caselist -> CASE target_list suite . DEFAULT reduce using rule 156 (caselist -> CASE target_list suite .) CASE reduce using rule 156 (caselist -> CASE target_list suite .) state 250 (157) caselist -> caselist CASE target_list . suite (126) target_list -> target_list . , target (137) suite -> . simple_stmt (138) suite -> . compound_stmt (139) suite -> . open_brace statement_block close_brace (9) simple_stmt -> . assignment_stmt (10) simple_stmt -> . augmented_assignment_stmt (11) simple_stmt -> . fancy_drel_assignment_stmt (12) simple_stmt -> . print_stmt (13) simple_stmt -> . BREAK (14) simple_stmt -> . NEXT (127) compound_stmt -> . if_stmt (128) compound_stmt -> . for_stmt (129) compound_stmt -> . do_stmt (130) compound_stmt -> . loop_stmt (131) compound_stmt -> . with_stmt (132) compound_stmt -> . where_stmt (133) compound_stmt -> . switch_stmt (134) compound_stmt -> . funcdef (140) open_brace -> . { (124) assignment_stmt -> . target_list = expression_list (120) augmented_assignment_stmt -> . target AUGOP expression_list (121) fancy_drel_assignment_stmt -> . primary ( dotlist ) (15) print_stmt -> . PRINT expression (135) if_stmt -> . IF expression suite (136) if_stmt -> . if_stmt ELSE suite (144) for_stmt -> . FOR target_list IN expression_list suite (149) do_stmt -> . do_stmt_head suite (145) loop_stmt -> . loop_head suite (152) with_stmt -> . with_head suite (154) where_stmt -> . WHERE expression suite ELSE suite (155) switch_stmt -> . SWITCH ID open_brace caselist DEFAULT suite close_brace (158) funcdef -> . FUNCTION ID ( arglist ) suite (125) target_list -> . target (126) target_list -> . target_list , target (19) target -> . primary (20) target -> . ( target_list ) (21) target -> . [ target_list ] (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (150) do_stmt_head -> . DO ID = expression , expression (151) do_stmt_head -> . DO ID = expression , expression , expression (146) loop_head -> . LOOP ID AS ID (147) loop_head -> . LOOP ID AS ID : ID (148) loop_head -> . LOOP ID AS ID : ID comp_operator ID (153) with_head -> . WITH ID AS ID (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] , shift and go to state 119 BREAK shift and go to state 56 NEXT shift and go to state 7 { shift and go to state 69 PRINT shift and go to state 28 IF shift and go to state 61 FOR shift and go to state 30 WHERE shift and go to state 19 SWITCH shift and go to state 46 FUNCTION shift and go to state 36 ( shift and go to state 6 [ shift and go to state 38 DO shift and go to state 58 LOOP shift and go to state 25 WITH shift and go to state 5 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ` shift and go to state 20 fancy_drel_assignment_stmt shift and go to state 26 primary_att shift and go to state 41 atom shift and go to state 2 primary shift and go to state 42 stringliteral shift and go to state 23 item_tag shift and go to state 52 switch_stmt shift and go to state 43 do_stmt_head shift and go to state 4 enclosure shift and go to state 29 parenth_form shift and go to state 8 simple_stmt shift and go to state 66 literal shift and go to state 45 assignment_stmt shift and go to state 32 call shift and go to state 47 string_conversion shift and go to state 49 with_head shift and go to state 51 suite shift and go to state 261 loop_head shift and go to state 12 do_stmt shift and go to state 13 compound_stmt shift and go to state 67 attributeref shift and go to state 9 simple_slicing shift and go to state 37 print_stmt shift and go to state 50 loop_stmt shift and go to state 15 slicing shift and go to state 17 target_list shift and go to state 63 for_stmt shift and go to state 18 augmented_assignment_stmt shift and go to state 27 funcdef shift and go to state 3 if_stmt shift and go to state 21 target shift and go to state 54 extended_slicing shift and go to state 34 list_display shift and go to state 22 where_stmt shift and go to state 39 open_brace shift and go to state 68 with_stmt shift and go to state 24 subscription shift and go to state 53 state 251 (155) switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite . close_brace (141) close_brace -> . } } shift and go to state 184 close_brace shift and go to state 262 state 252 (150) do_stmt_head -> DO ID = expression , expression . (151) do_stmt_head -> DO ID = expression , expression . , expression BREAK reduce using rule 150 (do_stmt_head -> DO ID = expression , expression .) NEXT reduce using rule 150 (do_stmt_head -> DO ID = expression , expression .) { reduce using rule 150 (do_stmt_head -> DO ID = expression , expression .) PRINT reduce using rule 150 (do_stmt_head -> DO ID = expression , expression .) IF reduce using rule 150 (do_stmt_head -> DO ID = expression , expression .) FOR reduce using rule 150 (do_stmt_head -> DO ID = expression , expression .) WHERE reduce using rule 150 (do_stmt_head -> DO ID = expression , expression .) SWITCH reduce using rule 150 (do_stmt_head -> DO ID = expression , expression .) FUNCTION reduce using rule 150 (do_stmt_head -> DO ID = expression , expression .) ( reduce using rule 150 (do_stmt_head -> DO ID = expression , expression .) [ reduce using rule 150 (do_stmt_head -> DO ID = expression , expression .) DO reduce using rule 150 (do_stmt_head -> DO ID = expression , expression .) LOOP reduce using rule 150 (do_stmt_head -> DO ID = expression , expression .) WITH reduce using rule 150 (do_stmt_head -> DO ID = expression , expression .) ID reduce using rule 150 (do_stmt_head -> DO ID = expression , expression .) ITEM_TAG reduce using rule 150 (do_stmt_head -> DO ID = expression , expression .) INTEGER reduce using rule 150 (do_stmt_head -> DO ID = expression , expression .) HEXINT reduce using rule 150 (do_stmt_head -> DO ID = expression , expression .) OCTINT reduce using rule 150 (do_stmt_head -> DO ID = expression , expression .) BININT reduce using rule 150 (do_stmt_head -> DO ID = expression , expression .) REAL reduce using rule 150 (do_stmt_head -> DO ID = expression , expression .) IMAGINARY reduce using rule 150 (do_stmt_head -> DO ID = expression , expression .) STRPREFIX reduce using rule 150 (do_stmt_head -> DO ID = expression , expression .) SHORTSTRING reduce using rule 150 (do_stmt_head -> DO ID = expression , expression .) LONGSTRING reduce using rule 150 (do_stmt_head -> DO ID = expression , expression .) ` reduce using rule 150 (do_stmt_head -> DO ID = expression , expression .) , shift and go to state 263 state 253 (148) loop_head -> LOOP ID AS ID : ID comp_operator . ID ID shift and go to state 264 state 254 (160) arglist -> arglist , ID : . list_display (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] [ shift and go to state 93 list_display shift and go to state 265 state 255 (88) testlist -> testlist , . or_test (89) testlist -> testlist , . or_test , (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 list_display shift and go to state 22 or_test shift and go to state 266 state 256 (86) list_for -> FOR expression_list IN testlist list_iter . ] reduce using rule 86 (list_for -> FOR expression_list IN testlist list_iter .) state 257 (91) list_iter -> list_if . ] reduce using rule 91 (list_iter -> list_if .) state 258 (90) list_iter -> list_for . ] reduce using rule 90 (list_iter -> list_for .) state 259 (92) list_if -> IF . or_test (93) list_if -> IF . or_test list_iter (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 string_conversion shift and go to state 49 call shift and go to state 47 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 extended_slicing shift and go to state 34 list_display shift and go to state 22 or_test shift and go to state 267 state 260 (123) dotlist -> dotlist , . ID = . expression (18) expression -> . or_test (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 list_display shift and go to state 22 or_test shift and go to state 86 expression shift and go to state 268 state 261 (157) caselist -> caselist CASE target_list suite . DEFAULT reduce using rule 157 (caselist -> caselist CASE target_list suite .) CASE reduce using rule 157 (caselist -> caselist CASE target_list suite .) state 262 (155) switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace . DEFAULT reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) CASE reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) } reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) BREAK reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) NEXT reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) IF reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) FOR reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) WHERE reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) SWITCH reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) FUNCTION reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) PRINT reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) DO reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) LOOP reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) WITH reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) ( reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) [ reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) ID reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) ITEM_TAG reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) INTEGER reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) HEXINT reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) OCTINT reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) BININT reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) REAL reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) IMAGINARY reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) STRPREFIX reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) SHORTSTRING reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) LONGSTRING reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) ` reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) $end reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) ELSE reduce using rule 155 (switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace .) state 263 (151) do_stmt_head -> DO ID = expression , expression , . expression (18) expression -> . or_test (22) or_test -> . and_test (23) or_test -> . or_test OR and_test (24) and_test -> . not_test (25) and_test -> . and_test AND not_test (26) not_test -> . comparison (27) not_test -> . NOT not_test (28) comparison -> . a_expr (29) comparison -> . a_expr comp_operator a_expr (38) a_expr -> . m_expr (39) a_expr -> . a_expr + m_expr (40) a_expr -> . a_expr - m_expr (41) m_expr -> . u_expr (42) m_expr -> . m_expr * u_expr (43) m_expr -> . m_expr / u_expr (44) m_expr -> . m_expr ^ u_expr (45) u_expr -> . power (46) u_expr -> . - u_expr (47) u_expr -> . + u_expr (48) power -> . primary (49) power -> . primary POWER u_expr (50) primary -> . atom (51) primary -> . primary_att (52) primary -> . subscription (53) primary -> . slicing (54) primary -> . call (56) atom -> . ID (57) atom -> . item_tag (58) atom -> . literal (59) atom -> . enclosure (55) primary_att -> . attributeref (97) subscription -> . primary [ expression_list ] (98) slicing -> . simple_slicing (99) slicing -> . extended_slicing (115) call -> . primary ( ) (116) call -> . primary ( argument_list ) (60) item_tag -> . ITEM_TAG (61) literal -> . stringliteral (62) literal -> . INTEGER (63) literal -> . HEXINT (64) literal -> . OCTINT (65) literal -> . BININT (66) literal -> . REAL (67) literal -> . IMAGINARY (72) enclosure -> . parenth_form (73) enclosure -> . string_conversion (74) enclosure -> . list_display (94) attributeref -> . primary attribute_tag (100) simple_slicing -> . primary [ short_slice ] (105) extended_slicing -> . primary [ slice_list ] (68) stringliteral -> . STRPREFIX SHORTSTRING (69) stringliteral -> . STRPREFIX LONGSTRING (70) stringliteral -> . SHORTSTRING (71) stringliteral -> . LONGSTRING (75) parenth_form -> . ( expression_list ) (76) parenth_form -> . ( ) (77) string_conversion -> . ` expression_list ` (78) list_display -> . [ listmaker ] (79) list_display -> . [ ] NOT shift and go to state 72 - shift and go to state 79 + shift and go to state 77 ID shift and go to state 60 ITEM_TAG shift and go to state 64 INTEGER shift and go to state 55 HEXINT shift and go to state 57 OCTINT shift and go to state 33 BININT shift and go to state 44 REAL shift and go to state 40 IMAGINARY shift and go to state 59 STRPREFIX shift and go to state 10 SHORTSTRING shift and go to state 31 LONGSTRING shift and go to state 16 ( shift and go to state 94 ` shift and go to state 20 [ shift and go to state 93 primary_att shift and go to state 41 primary shift and go to state 92 stringliteral shift and go to state 23 not_test shift and go to state 74 enclosure shift and go to state 29 simple_slicing shift and go to state 37 u_expr shift and go to state 71 parenth_form shift and go to state 8 literal shift and go to state 45 attributeref shift and go to state 9 call shift and go to state 47 string_conversion shift and go to state 49 extended_slicing shift and go to state 34 power shift and go to state 75 a_expr shift and go to state 78 and_test shift and go to state 80 slicing shift and go to state 17 m_expr shift and go to state 82 atom shift and go to state 2 item_tag shift and go to state 52 subscription shift and go to state 53 comparison shift and go to state 83 list_display shift and go to state 22 or_test shift and go to state 86 expression shift and go to state 269 state 264 (148) loop_head -> LOOP ID AS ID : ID comp_operator ID . BREAK reduce using rule 148 (loop_head -> LOOP ID AS ID : ID comp_operator ID .) NEXT reduce using rule 148 (loop_head -> LOOP ID AS ID : ID comp_operator ID .) { reduce using rule 148 (loop_head -> LOOP ID AS ID : ID comp_operator ID .) PRINT reduce using rule 148 (loop_head -> LOOP ID AS ID : ID comp_operator ID .) IF reduce using rule 148 (loop_head -> LOOP ID AS ID : ID comp_operator ID .) FOR reduce using rule 148 (loop_head -> LOOP ID AS ID : ID comp_operator ID .) WHERE reduce using rule 148 (loop_head -> LOOP ID AS ID : ID comp_operator ID .) SWITCH reduce using rule 148 (loop_head -> LOOP ID AS ID : ID comp_operator ID .) FUNCTION reduce using rule 148 (loop_head -> LOOP ID AS ID : ID comp_operator ID .) ( reduce using rule 148 (loop_head -> LOOP ID AS ID : ID comp_operator ID .) [ reduce using rule 148 (loop_head -> LOOP ID AS ID : ID comp_operator ID .) DO reduce using rule 148 (loop_head -> LOOP ID AS ID : ID comp_operator ID .) LOOP reduce using rule 148 (loop_head -> LOOP ID AS ID : ID comp_operator ID .) WITH reduce using rule 148 (loop_head -> LOOP ID AS ID : ID comp_operator ID .) ID reduce using rule 148 (loop_head -> LOOP ID AS ID : ID comp_operator ID .) ITEM_TAG reduce using rule 148 (loop_head -> LOOP ID AS ID : ID comp_operator ID .) INTEGER reduce using rule 148 (loop_head -> LOOP ID AS ID : ID comp_operator ID .) HEXINT reduce using rule 148 (loop_head -> LOOP ID AS ID : ID comp_operator ID .) OCTINT reduce using rule 148 (loop_head -> LOOP ID AS ID : ID comp_operator ID .) BININT reduce using rule 148 (loop_head -> LOOP ID AS ID : ID comp_operator ID .) REAL reduce using rule 148 (loop_head -> LOOP ID AS ID : ID comp_operator ID .) IMAGINARY reduce using rule 148 (loop_head -> LOOP ID AS ID : ID comp_operator ID .) STRPREFIX reduce using rule 148 (loop_head -> LOOP ID AS ID : ID comp_operator ID .) SHORTSTRING reduce using rule 148 (loop_head -> LOOP ID AS ID : ID comp_operator ID .) LONGSTRING reduce using rule 148 (loop_head -> LOOP ID AS ID : ID comp_operator ID .) ` reduce using rule 148 (loop_head -> LOOP ID AS ID : ID comp_operator ID .) state 265 (160) arglist -> arglist , ID : list_display . ) reduce using rule 160 (arglist -> arglist , ID : list_display .) , reduce using rule 160 (arglist -> arglist , ID : list_display .) state 266 (88) testlist -> testlist , or_test . (89) testlist -> testlist , or_test . , (23) or_test -> or_test . OR and_test ! shift/reduce conflict for , resolved as shift FOR reduce using rule 88 (testlist -> testlist , or_test .) IF reduce using rule 88 (testlist -> testlist , or_test .) ] reduce using rule 88 (testlist -> testlist , or_test .) , shift and go to state 270 OR shift and go to state 146 ! , [ reduce using rule 88 (testlist -> testlist , or_test .) ] state 267 (92) list_if -> IF or_test . (93) list_if -> IF or_test . list_iter (23) or_test -> or_test . OR and_test (90) list_iter -> . list_for (91) list_iter -> . list_if (85) list_for -> . FOR expression_list IN testlist (86) list_for -> . FOR expression_list IN testlist list_iter (92) list_if -> . IF or_test (93) list_if -> . IF or_test list_iter ] reduce using rule 92 (list_if -> IF or_test .) OR shift and go to state 146 FOR shift and go to state 155 IF shift and go to state 259 list_iter shift and go to state 271 list_if shift and go to state 257 list_for shift and go to state 258 state 268 (123) dotlist -> dotlist , . ID = expression . ) reduce using rule 123 (dotlist -> dotlist , . ID = expression .) , reduce using rule 123 (dotlist -> dotlist , . ID = expression .) state 269 (151) do_stmt_head -> DO ID = expression , expression , expression . BREAK reduce using rule 151 (do_stmt_head -> DO ID = expression , expression , expression .) NEXT reduce using rule 151 (do_stmt_head -> DO ID = expression , expression , expression .) { reduce using rule 151 (do_stmt_head -> DO ID = expression , expression , expression .) PRINT reduce using rule 151 (do_stmt_head -> DO ID = expression , expression , expression .) IF reduce using rule 151 (do_stmt_head -> DO ID = expression , expression , expression .) FOR reduce using rule 151 (do_stmt_head -> DO ID = expression , expression , expression .) WHERE reduce using rule 151 (do_stmt_head -> DO ID = expression , expression , expression .) SWITCH reduce using rule 151 (do_stmt_head -> DO ID = expression , expression , expression .) FUNCTION reduce using rule 151 (do_stmt_head -> DO ID = expression , expression , expression .) ( reduce using rule 151 (do_stmt_head -> DO ID = expression , expression , expression .) [ reduce using rule 151 (do_stmt_head -> DO ID = expression , expression , expression .) DO reduce using rule 151 (do_stmt_head -> DO ID = expression , expression , expression .) LOOP reduce using rule 151 (do_stmt_head -> DO ID = expression , expression , expression .) WITH reduce using rule 151 (do_stmt_head -> DO ID = expression , expression , expression .) ID reduce using rule 151 (do_stmt_head -> DO ID = expression , expression , expression .) ITEM_TAG reduce using rule 151 (do_stmt_head -> DO ID = expression , expression , expression .) INTEGER reduce using rule 151 (do_stmt_head -> DO ID = expression , expression , expression .) HEXINT reduce using rule 151 (do_stmt_head -> DO ID = expression , expression , expression .) OCTINT reduce using rule 151 (do_stmt_head -> DO ID = expression , expression , expression .) BININT reduce using rule 151 (do_stmt_head -> DO ID = expression , expression , expression .) REAL reduce using rule 151 (do_stmt_head -> DO ID = expression , expression , expression .) IMAGINARY reduce using rule 151 (do_stmt_head -> DO ID = expression , expression , expression .) STRPREFIX reduce using rule 151 (do_stmt_head -> DO ID = expression , expression , expression .) SHORTSTRING reduce using rule 151 (do_stmt_head -> DO ID = expression , expression , expression .) LONGSTRING reduce using rule 151 (do_stmt_head -> DO ID = expression , expression , expression .) ` reduce using rule 151 (do_stmt_head -> DO ID = expression , expression , expression .) state 270 (89) testlist -> testlist , or_test , . , reduce using rule 89 (testlist -> testlist , or_test , .) FOR reduce using rule 89 (testlist -> testlist , or_test , .) IF reduce using rule 89 (testlist -> testlist , or_test , .) ] reduce using rule 89 (testlist -> testlist , or_test , .) state 271 (93) list_if -> IF or_test list_iter . ] reduce using rule 93 (list_if -> IF or_test list_iter .) WARNING: WARNING: Conflicts: WARNING: WARNING: shift/reduce conflict for ELSE in state 21 resolved as shift WARNING: shift/reduce conflict for IN in state 78 resolved as shift WARNING: shift/reduce conflict for [ in state 92 resolved as shift WARNING: shift/reduce conflict for ( in state 92 resolved as shift WARNING: shift/reduce conflict for REAL in state 92 resolved as shift WARNING: shift/reduce conflict for [ in state 100 resolved as shift WARNING: shift/reduce conflict for ( in state 100 resolved as shift WARNING: shift/reduce conflict for REAL in state 100 resolved as shift WARNING: shift/reduce conflict for , in state 106 resolved as shift WARNING: shift/reduce conflict for ] in state 167 resolved as shift WARNING: shift/reduce conflict for ; in state 179 resolved as shift WARNING: shift/reduce conflict for , in state 266 resolved as shift WARNING: reduce/reduce conflict in state 73 resolved using rule (target -> primary) WARNING: rejected rule (power -> primary) in state 73 WARNING: reduce/reduce conflict in state 174 resolved using rule (expression_list -> expression) WARNING: rejected rule (slice_item -> expression) in state 174 ./CBFlib-0.9.2.2/dREL-ply-0.5/dREL_ply.egg-info/0000755000076500007650000000000011603703070016633 5ustar yayayaya./CBFlib-0.9.2.2/dREL-ply-0.5/dREL_ply.egg-info/PKG-INFO0000755000076500007650000000036411603702115017735 0ustar yayayayaMetadata-Version: 1.0 Name: dREL-ply Version: 0.5 Summary: Conversion from dREL to python Home-page: http://pycifrw.berlios.de Author: James Hester Author-email: jamesrhester at gmail.com License: UNKNOWN Description: UNKNOWN Platform: UNKNOWN ./CBFlib-0.9.2.2/dREL-ply-0.5/dREL_ply.egg-info/dependency_links.txt0000755000076500007650000000000111603702115022703 0ustar yayayaya ./CBFlib-0.9.2.2/dREL-ply-0.5/dREL_ply.egg-info/SOURCES.txt0000755000076500007650000000032211603702115020516 0ustar yayayayaREADME drel_lex.py drel_yacc.py setup.cfg setup.py dREL_ply.egg-info/PKG-INFO dREL_ply.egg-info/SOURCES.txt dREL_ply.egg-info/dependency_links.txt dREL_ply.egg-info/requires.txt dREL_ply.egg-info/top_level.txt ./CBFlib-0.9.2.2/dREL-ply-0.5/dREL_ply.egg-info/top_level.txt0000755000076500007650000000002311603702115021362 0ustar yayayayadrel_yacc drel_lex ./CBFlib-0.9.2.2/dREL-ply-0.5/dREL_ply.egg-info/requires.txt0000755000076500007650000000001011603702115021224 0ustar yayayayaply>=2.5./CBFlib-0.9.2.2/dREL-ply-0.5/README0000755000076500007650000000117611603702115014356 0ustar yayayaya ReadMe - dREL-ply-0.5 -------------------- This is a snapshot of James Hester's dREL-ply-0.5 as of 7 December 2009 for support of CBFlib releases, with changes by E. Zlateva. This is a pre-release of software that will become part of PyCifRW. You should check http://pycifrw.berlios.de for later releases. This is a Python package for parsing and transforming dREL functions. dREL is a draft language for specification of relationships among items in a CIF (Crystallographic Information Framework) data file. You should have PLY (Python Lex/Yacc) installed as a prerequisite. ./CBFlib-0.9.2.2/dREL-ply-0.5/PKG-INFO0000755000076500007650000000036411603702115014571 0ustar yayayayaMetadata-Version: 1.0 Name: dREL-ply Version: 0.5 Summary: Conversion from dREL to python Home-page: http://pycifrw.berlios.de Author: James Hester Author-email: jamesrhester at gmail.com License: UNKNOWN Description: UNKNOWN Platform: UNKNOWN ./CBFlib-0.9.2.2/dREL-ply-0.5/drel_lex.py0000755000076500007650000000705711603702115015652 0ustar yayayaya#Attempt to implement dREL using PLY (Python Lex Yacc) import ply.lex as lex import re #for multiline flag tokens = ( 'SHORTSTRING', 'LONGSTRING', 'INTEGER', 'BININT', 'HEXINT', 'OCTINT', 'REAL', 'POWER', 'ISEQUAL', 'NEQ', 'GTE', 'LTE', 'IMAGINARY', 'ID', #variable name 'ITEM_TAG', #cif item as variable 'COMMENT', 'STRPREFIX', 'ELLIPSIS', 'AND', 'OR', 'IN', 'NOT', 'DO', 'FOR', 'LOOP', 'AS', 'WITH', 'WHERE', 'ELSE', 'BREAK', 'NEXT', 'IF', 'SWITCH', 'CASE', 'DEFAULT', 'AUGOP', 'PRINT', 'FUNCTION' ) literals = '+*-/;()[],:^<>{}=.`' t_ignore = ' \t\n' def t_error(t): print 'Illegal character %s' % repr(t.value[0]) t_POWER = r'\*\*' t_ISEQUAL = r'==' t_NEQ = r'!=' t_GTE = r'>=' t_LTE = r'<=' t_ELLIPSIS = r'\.\.\.' def t_AUGOP(t): r'(\+\+=)|(\+=)|(-=)|(\*=)|(/=)' return t # Do the reals before the integers, otherwise the integer will # match the first part of the real # def t_IMAGINARY(t): r'(((([0-9]+[.][0-9]*)|([.][0-9]+))([Ee][+-]?[0-9]+)?)|([0-9]+))[jJ]' return t def t_REAL(t): r'(([0-9]+[.][0-9]*)|([.][0-9]+))([Ee][+-]?[0-9]+)?' try: value = float(t.value) except ValueError: print 'Error converting %s to real' % t.value return t # Do the binary,octal etc before decimal integer otherwise the 0 at # the front will match the decimal integer 0 # def t_BININT(t): r'0[bB][0-1]+' try: t.value = `int(t.value[2:],base=2)` except ValueError: print 'Unable to convert binary value %s' % t.value return t def t_OCTINT(t): r'0[oO][0-7]+' try: t.value = `int(t.value[2:],base=8)` except ValueError: print 'Unable to convert octal value %s' % t.value return t def t_HEXINT(t): r'0[xX][0-9a-fA-F]+' try: t.value = `int(t.value,base=16)` except ValueError: print 'Unable to convert hex value %s' % t.value return t def t_INTEGER(t): r'[0-9]+' try: value = int(t.value) except ValueError: print 'Incorrect integer value %s' % t.value return t def t_STRPREFIX(t): r'r(?=["\'])|u(?=["\'])|R(?=["\'])|U(?=["\'])|ur(?=["\'])|UR(?=["\'])|Ur(?=["\'])|uR(?=["\'])' return t # try longstring first as otherwise the '' will match a shortstring def t_LONGSTRING(t): r"('''([^\\]|(\\.))*''')|(\"\"\"([^\\]|(\\.))*\"\"\")" return t def t_SHORTSTRING(t): r"('([^'\n]|(\\.))*')|(\"([^\"\n]|(\\.))*\")" return t reserved = { 'and': 'AND', 'or': 'OR', 'in': 'IN', 'not': 'NOT', 'do': 'DO', 'Do': 'DO', 'for': 'FOR', 'For': 'FOR', 'loop': 'LOOP', 'Loop': 'LOOP', 'as': 'AS', 'with': 'WITH', 'With': 'WITH', 'where': 'WHERE', 'Where': 'WHERE', 'else': 'ELSE', 'Else': 'ELSE', 'Next': 'NEXT', 'next' : 'NEXT', 'break': 'BREAK', 'if': 'IF', 'If': 'IF', 'switch': 'SWITCH', 'case' : 'CASE', 'Function' : 'FUNCTION', 'function' : 'FUNCTION', 'Print' : 'PRINT', 'print' : 'PRINT', 'default' : 'DEFAULT' } def t_ID(t): r'[a-zA-Z][a-zA-Z0-9_$]*' t.type = reserved.get(t.value,'ID') if t.type == 'NEXT': t.value = 'continue' return t # Item tags can have periods and underscores inside, and must have # at least one of them at the front def t_ITEM_TAG(t): r'_[a-zA-Z_.]+' return t def t_COMMENT(t): r'\#.*' pass lexer = lex.lex(reflags=re.MULTILINE) if __name__ == "__main__": lex.runmain(lexer) ./CBFlib-0.9.2.2/dREL-ply-0.5/testdic20000755000076500007650000000560711603702115015145 0ustar yayayaya############################################################################## # # # PROTOTYPE DDL DICTIONARY # # # ############################################################################## data_TEST_DIC _dictionary.title TEST_DIC _dictionary.class Attribute _dictionary.version 3.7.06 _dictionary.date 2007-03-18 _dictionary.uri www.iucr.org/cif/dic/ddl.dic _dictionary.ddl_conformance 3.7.06 _dictionary.namespace DdlDic _description.text ; This dictionary contains the definitions of attributes that make up the DDLm dictionary definition language. It provides the meta meta data for all CIF dictionaries. ; save_TEST_ATTR _definition.id test_attr _definition.scope Category _definition.class Head _definition.update 2006-12-05 _description.text ; This category is parent of all other categories in the DDLm dictionary. ; save_ #------------------------------------------------------------------------------- save_POSITION _definition.id position _category.id position _category_key.generic '_position.object_id' _definition.scope Category save_ save_position.number _definition.id '_position.number' _name.category_id position _name.object_id number _type.container Single _type.contents Integer _type.purpose Index save_ save_position.object_id _definition.id '_position.object_id' _name.category_id position _name.object_id object_id _type.container Single _type.contents Uchar save_ save_position.vector_xyz _definition.id '_position.vector_xyz' _name.category_id position _name.object_id vector_xyz _type.container Array _type.contents Real _type.dimension [3] save_ save_GEOM _definition.id geom _category.id geom _definition.scope Category save_ save_geom.vertex1_id _definition.id '_geom.vertex1_id' _name.category_id geom _name.object_id vertex1_id _name.linked_item_id '_position.object_id' _type.container Single _type.contents Uchar save_ save_geom.vertex2_id _definition.id '_geom.vertex2_id' _name.category_id geom _name.object_id vertex2_id _name.linked_item_id '_position.object_id' _type.container Single _type.contents Uchar save_ save_geom.vertex3_id _definition.id '_geom.vertex3_id' _name.category_id geom _name.object_id vertex3_id _name.linked_item_id '_position.object_id' _type.container Single _type.contents Uchar save_ ./CBFlib-0.9.2.2/dREL-ply-0.5/TestDrel.py0000755000076500007650000003325711603702115015603 0ustar yayayaya# Test suite for the dRel parser # import unittest import drel_lex import drel_yacc import CifFile import StarFile # Test simple statements class SimpleStatementTestCase(unittest.TestCase): def setUp(self): #create our lexer and parser self.lexer = drel_lex.lexer self.parser = drel_yacc.parser # as we disallow simple expressions on a separate line to avoid a # reduce/reduce conflict for identifiers, we need at least an # assignment statement def testrealnum(self): """test parsing of real numbers""" res = self.parser.parse('a=5.45\n',debug=True,lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc","a",have_sn=False) exec realfunc self.failUnless(myfunc(self,self)==5.45) res = self.parser.parse('a=.45e-24\n',debug=True,lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc","a",have_sn=False) exec realfunc self.failUnless(myfunc(self,self) ==.45e-24) def testinteger(self): """test parsing an integer""" resm = [0,0,0,0] checkm = [1230,77,5,473] resm[0] = self.parser.parse('a = 1230\n',lexer=self.lexer) resm[1] = self.parser.parse('a = 0x4D\n',lexer=self.lexer) resm[2] = self.parser.parse('a = 0B0101\n',lexer=self.lexer) resm[3] = self.parser.parse('a = 0o731\n',lexer=self.lexer) for res,check in zip(resm,checkm): realfunc = drel_yacc.make_func(res,"myfunc","a",have_sn=False) exec realfunc self.failUnless(myfunc(self,self) == check) def testcomplex(self): """test parsing a complex number""" resc = self.parser.parse('a = 13.45j\n',lexer=self.lexer) realfunc = drel_yacc.make_func(resc,"myfunc","a",have_sn=False) exec realfunc self.failUnless(myfunc(self,self) == 13.45j) def testshortstring(self): """test parsing a one-line string""" jk = "a = \"my pink pony's mane\"" jl = "a = 'my pink pony\"s mane'" ress = self.parser.parse(jk+"\n",lexer=self.lexer) resr = self.parser.parse(jl+"\n",lexer=self.lexer) realfunc = drel_yacc.make_func(ress,"myfunc","a",have_sn=False) exec realfunc self.failUnless(myfunc(self,self) == jk[5:-1]) realfunc = drel_yacc.make_func(resr,"myfunc","a",have_sn=False) exec realfunc self.failUnless(myfunc(self,self) == jl[5:-1]) # # This fails due to extra indentation introduced when constructing the # enclosing function # def testlongstring(self): """test parsing multi-line strings""" jk = '''a = """ a long string la la la '"' some more end"""''' jl = """a = ''' a long string la la la '"' some more end'''""" ress = self.parser.parse(jk+"\n",lexer=self.lexer) resr = self.parser.parse(jl+"\n",lexer=self.lexer) realfunc = drel_yacc.make_func(ress,"myfunc","a",have_sn=False) exec realfunc self.failUnless(myfunc(self,self) == jk[7:-3]) realfunc = drel_yacc.make_func(resr,"myfunc","a",have_sn=False) exec realfunc self.failUnless(myfunc(self,self) == jl[7:-3]) def testmathexpr(self): """test simple maths expressions """ testexpr = (("a = 5.45 + 23.6e05",5.45+23.6e05), ("a = 11 - 45",11-45), ("a = 45.6 / 22.2",45.6/22.2)) for test,check in testexpr: res = self.parser.parse(test+"\n",lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc","a",have_sn=False) exec realfunc self.failUnless(myfunc(self,self) == check) def testexprlist(self): """test comma-separated expressions""" test = "a = 5,6,7+8.5e2" res = self.parser.parse(test+"\n",lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc","a",have_sn=False) exec realfunc self.failUnless(myfunc(self,self) ==(5,6,7+8.5e2)) def testparen(self): """test parentheses""" test = "a = ('once', 'upon', 6,7j +.5e2)" res = self.parser.parse(test+"\n",lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc","a",have_sn=False) exec realfunc self.failUnless(myfunc(self,self) ==('once' , 'upon' , 6 , 7j + .5e2 )) def testlists(self): """test list parsing""" test = "a = ['once', 'upon', 6,7j +.5e2]" res = self.parser.parse(test+"\n",lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc","a",have_sn=False) exec realfunc self.failUnless(myfunc(self,self) ==['once' , 'upon' , 6 , 7j + .5e2 ]) class MoreComplexTestCase(unittest.TestCase): def setUp(self): #create our lexer and parser self.lexer = drel_lex.lexer self.parser = drel_yacc.parser self.parser.withtable = {} self.parser.special_id = [] self.parser.target_id = None self.parser.indent = "" def testassignment(self): """Test that an assignment works""" teststrg = "n = 11" res = self.parser.parse(teststrg,lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc","n",have_sn=False) exec realfunc self.failUnless(myfunc(self,self)==11) def test_do_stmt(self): """Test how a do statement comes out""" teststrg = """ total = 0 do jkl = 0,20,2 { total = total + jkl } do emm = 1,5 { total = total + emm } """ res = self.parser.parse(teststrg + "\n",lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc","total",have_sn=False) exec realfunc realres = myfunc(self,self) # Do statements are inclusive print "Do statement returns %d" % realres self.failUnless(realres==125) print res def test_do_stmt_2(self): """Test how another do statement comes out""" teststrg = """ pp = 0 geom_hbond = [(1,2),(2,3),(3,4)] do i= 0,1 { l,s = geom_hbond [i] pp += s } """ self.parser.special_id = [{'axy':1}] res = self.parser.parse(teststrg + "\n",debug=True,lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc","pp",have_sn=False) exec realfunc realres = myfunc(self,self) # Do statements are inclusive print "Do statement returns %d" % realres self.failUnless(realres==5) print res def test_nested_stmt(self): """Test how a nested do statement prints""" teststrg = """ total = 0 othertotal = 0 do jkl = 0,20,2 { total = total + jkl do emm = 1,5 { othertotal = othertotal + 1 } } end_of_loop = -25.6 """ res = self.parser.parse(teststrg + "\n",lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc","othertotal,total",have_sn=False) print "Nested do:\n" + realfunc exec realfunc othertotal,total = myfunc(self,self) print "nested do returns %d, %d" % (othertotal,total) self.failUnless(othertotal==55) self.failUnless(total==110) def test_if_stmt(self): """test parsing of if statement""" teststrg = """ dmin = 5.0 d1 = 4.0 rad1 = 2.2 radius_bond = 2.0 If (d1(rad1+radius_bond)) b = 5 """ res = self.parser.parse(teststrg + "\n",lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc","b",have_sn=False) exec realfunc b = myfunc(self,self) print "if returns %d" % b self.failUnless(b==5) # We don't test the return value until we have a way to actually access it! def test_fancy_assign(self): """Test fancy assignment""" teststrg = """ a = [2,3,4] b = 3 c= 4 do jkl = 1,5,1 { geom_angle( .id = Tuple(a,b,c), .distances = Tuple(b,c), .value = jkl) } """ self.parser.target_id = "geom_angle" res = self.parser.parse(teststrg + "\n",debug=True,lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc",None,cat_meth = True,have_sn=False) print "Fancy assign: %s" % res[0] exec realfunc b = myfunc(self,self) print "Geom_angle.angle = %s" % b['geom_angle.value'] self.failUnless(b['geom_angle.value']==[1,2,3,4]) def test_tables(self): """Test that tables are parsed correctly""" teststrg = """ jk = Table() jk['bx'] = 25 """ print "Table test:" res = self.parser.parse(teststrg+"\n",debug=True,lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc","jk",have_sn=False) print "Table: %s" % `res[0]` exec realfunc b = myfunc(self,self) self.failUnless(b['bx']==25) class WithDictTestCase(unittest.TestCase): """Now test flow control which requires a dictionary present""" def setUp(self): #create our lexer and parser self.lexer = drel_lex.lexer self.parser = drel_yacc.parser #use a simple dictionary self.testdic = CifFile.CifDic("testdic") self.testblock = CifFile.CifFile("testdic")["DDL_DIC"] #create the global namespace self.namespace = self.testblock.keys() self.namespace = dict(map(None,self.namespace,self.namespace)) self.parser.special_id = [self.namespace] self.parser.withtable = {} self.parser.target_id = None self.parser.indent = "" def test_with_stmt(self): """Test what comes out of a simple flow statement, including multiple with statements""" teststrg = """ with p as description with q as dictionary { x = 22 j = 25 jj = q.date px = p.text _dictionary.date = "2007-04-01" }""" self.parser.loopable_cats = [] #category dictionary is not looped self.parser.target_id = '_dictionary.date' res = self.parser.parse(teststrg+"\n",lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc",None) print "With statement -> \n" + realfunc exec realfunc newdate = myfunc(self.testdic,self.testblock) print 'date now %s' % newdate self.failUnless(newdate == "2007-04-01") def test_loop_statement(self): """Test proper processing of loop statements""" teststrg = """ n = 0 loop p as dictionary_audit n += 1 _symmetry.ops = n """ self.parser.loopable_cats = ['dictionary_audit'] #category dictionary is not looped self.parser.target_id = '_symmetry.ops' res = self.parser.parse(teststrg+"\n",lexer=self.lexer,debug=1) realfunc = drel_yacc.make_func(res,"myfunc",None) print "Loop statement -> \n" + realfunc exec realfunc symops = myfunc(self.testdic,self.testblock) print 'symops now %d' % symops self.failUnless(symops == 81) def test_functions(self): """Test that functions are converted correctly""" struct_testdic = CifFile.CifFile("cif_core.dic", grammar="DDLm") struct_testblock = struct_testdic["CIF_CORE"] self.parser.loopable_cats = ["import"] #category import is looped self.parser.target_id = "_import_list.id" self.parser.withtable = {} teststrg = """ with i as import _import_list.id = List([i.scope, i.block, i.file, i.if_dupl, i.if_miss]) """ res = self.parser.parse(teststrg+"\n",lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc",None) print "With statement -> \n" + realfunc exec realfunc retval = myfunc(self.testdic,struct_testblock,3) self.failUnless(retval == StarFile.StarList(["dic","CORE_MODEL","core_model.dic","exit","exit"])) def test_attributes(self): """Test that attributes of complex expressions come out OK""" # We need to do a scary funky attribute of a key lookup ourdic = CifFile.CifDic("testdic2") testblock = CifFile.CifFile("test_data.cif")["testdata"] self.parser.loopable_cats = ['geom','position'] # teststrg = """ LineList = [] PointList = [] With p as position Loop g as geom { If (g.type == "point") { PointList += Tuple(g.vertex1_id,p[g.vertex1_id].vector_xyz) } #Else if (g.type == "line") { # LineList ++= Tuple(Tuple(g.vertex1_id, g.vertex2_id), # Tuple(p[g.vertex1_id].vector_xyz, # p[g.vertex2_id].vector_xyz)) #} } """ self.parser.target_id = 'PointList' res = self.parser.parse(teststrg+"\n",lexer=self.lexer) realfunc = drel_yacc.make_func(res,"myfunc","PointList") print "Function -> \n" + realfunc exec realfunc retval = myfunc(ourdic,testblock,"LineList") print "testdic2 return value" + `retval` print "Value for comparison with docs: %s" % `retval[0]` def test_funcdef(self): """Test function conversion""" teststrg = """ function Closest( v :[Array, Real], # coord vector to be cell translated w :[Array, Real]) { # target vector d = v - w t = Int( Mod( 99.5 + d, 1.0 ) - d ) Closest = Tuple ( v+t, t ) } """ self.parser.target_id = 'Closest' res,ww = self.parser.parse(teststrg+"\n",lexer=self.lexer) print "Function -> \n" + res exec res retval = Closest(0.2,0.8) print 'Closest 0.2,0.8 returns ' + ",".join([`retval[0]`,`retval[1]`]) self.failUnless(retval == StarFile.StarTuple(1.2,1)) if __name__=='__main__': unittest.main() ./CBFlib-0.9.2.2/dREL-ply-0.5/testdic0000755000076500007650000017542211603702115015066 0ustar yayayaya############################################################################## # # # PROTOTYPE DDL DICTIONARY # # # ############################################################################## data_DDL_DIC _dictionary.title DDL_DIC _dictionary.class Attribute _dictionary.version 3.7.06 _dictionary.date 2007-03-18 _dictionary.uri www.iucr.org/cif/dic/ddl.dic _dictionary.ddl_conformance 3.7.06 _dictionary.namespace DdlDic _description.text ; This dictionary contains the definitions of attributes that make up the DDLm dictionary definition language. It provides the meta meta data for all CIF dictionaries. ; save_DDL_ATTR _definition.id ddl_attr _definition.scope Category _definition.class Head _definition.update 2006-12-05 _description.text ; This category is parent of all other categories in the DDLm dictionary. ; save_ #------------------------------------------------------------------------------- save_ALIAS _definition.id alias _definition.scope Category _definition.class List _definition.update 2007-02-06 _description.text ; The attributes used to specify the aliased names of definitions. ; _category.parent_id ddl_attr _category_key.generic '_alias.definition_id' save_ save_alias.definition_id _definition.id '_alias.definition_id' _definition.class Attribute _definition.update 2006-11-16 _description.text ; Identifier tag of an aliased definition. ; _name.category_id alias _name.object_id definition_id _type.purpose Key _type.container Single _type.contents Tag save_ save_alias.dictionary_uri _definition.id '_alias.dictionary_uri' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Dictionary URI in which the aliased definition belongs. ; _name.category_id alias _name.object_id dictionary_uri _type.purpose Identify _type.container Single _type.contents Uri save_ #---------------------------------------------------------------------------- save_CATEGORY _definition.id category _definition.scope Category _definition.class Set _definition.update 2006-11-16 _description.text ; The attributes used to specify the properties of a "category" of data items. ; _category.parent_id ddl_attr save_ save_category.parent_id _definition.id '_category.parent_id' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The definition id of the category which is a higher member of the organisational hierarchy than the current category definition. ; _name.category_id category _name.object_id parent_id _type.purpose Identify _type.container Single _type.contents Tag save_ save_category.parent_join _definition.id '_category.parent_join' _definition.update 2006-12-21 _definition.class Attribute _description.text ; Yes or No flag indication if a category-list may be merged at instantiation with its parent category. Note that category-sets may always be merged with the parent category. ; _name.category_id category _name.object_id parent_join _type.purpose Identify _type.container Single _type.contents YesorNo _enumeration.default No save_ #---------------------------------------------------------------------------- save_CATEGORY_KEY _definition.id category_key _definition.scope Category _definition.class Set _definition.update 2006-11-16 _description.text ; Attributes used to specify the access keys of List categories. ; _category.parent_id category save_ save_category_key.generic _definition.id '_category_key.generic' _definition.update 2007-02-08 _definition.class Attribute _description.text ; Tag of a data item in a List category which is the generic key to access other items in the category. The value of this item must be unique in order to provide unambiguous access to a packet (row) in the table of values. ; _name.category_id category_key _name.object_id generic _type.purpose Identify _type.container Single _type.contents Tag save_ save_category_key.primitive _definition.id '_category_key.primitive' _definition.update 2007-02-08 _definition.class Attribute _description.text ; Tuple of the data item (or data items) in a List category which form the primitive composite key to access other items in the category. The value of this tuple must be unique to provide unambiguous access to a packet (row) in the table of values. ; _name.category_id category_key _name.object_id primitive _type.purpose Identify _type.container Tuple _type.contents Tag _type.dimension [1:] save_ #----------------------------------------------------------------------------- save_CATEGORY_MANDATORY _definition.id category_mandatory _definition.scope Category _definition.class List _definition.update 2007-02-06 _description.text ; The attributes used to specify the properties of a "category_mandatory" of data items. ; _category.parent_id category _category_key.generic '_category_mandatory.item_id' save_ save_category_mandatory.item_id _definition.id '_category_mandatory.item_id' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The data name of an item in this category which must exist within a data file if any item within this category appears. ; _name.category_id category_mandatory _name.object_id item_id _type.purpose Key _type.container Single _type.contents Tag save_ #---------------------------------------------------------------------------- save_DEFINITION _definition.id definition _definition.scope Category _definition.class Set _definition.update 2006-11-16 _description.text ; The attributes for classifying dictionary definitions. ; _category.parent_id ddl_attr save_ save_definition.class _definition.id '_definition.class' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The nature and the function of a definition or definitions. ; _name.category_id definition _name.object_id class _type.purpose State _type.container Single _type.contents Code loop_ _enumeration_set.state _enumeration_set.detail Audit ; Item used to IDENTIFY and AUDIT dictionary properties only. ; Attribute ; Item used as an attribute in the definition of other data items. Applied in dictionaries only. ; Head ; Category of items that is the parent of all other categories in the dictionary. ; List ; Category of items that in a data file must reside in a looped list with a key item defined. ; Set ; Category of items that form a set (but not a loopable list). These items may be referenced as a class of items in a dREL methods expression. ; Datum ; Item in a domain-specific dictionary. These items appear in data files. ; Transient ; Definition saveframes specifying the attributes, enumeration values and functions used in dictionary definitions. These tags are ONLY used in dictionary definitions. ; _enumeration.default Datum save_ save_definition.id _definition.id '_definition.id' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Identifier name of the definition contained within a save frame. ; _name.category_id definition _name.object_id id _type.purpose Identify _type.container Single _type.contents Tag save_ save_definition.scope _definition.id '_definition.scope' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The extent to which a definition affects other definitions. ; _name.category_id definition _name.object_id scope _type.purpose State _type.container Single _type.contents Code loop_ _enumeration_set.state _enumeration_set.detail Dictionary "applies to all defined items in the dictionary" Category "applies to all defined items in the category" Item "applies to a single item definition" _enumeration.default Item save_ save_definition.update _definition.id '_definition.update' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The date that a definition was last changed. ; _name.category_id definition _name.object_id update _type.purpose Audit _type.container Single _type.contents Date save_ save_definition.xref_code _definition.id '_definition.xref_code' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Code identifying the equivalent definition in the dictionary referenced by the DICTIONARY_XREF attributes. ; _name.category_id definition _name.object_id xref_code _type.purpose Identify _type.container Single _type.contents Code save_ #---------------------------------------------------------------------------- save_DESCRIPTION _definition.id description _definition.scope Category _definition.class Set _definition.update 2006-11-16 _description.text ; The attributes of descriptive (non-machine parseable) parts of definitions. ; _category.parent_id ddl_attr save_ save_description.key_words _definition.id '_description.key_words' _definition.update 2006-11-16 _definition.class Attribute _description.text ; List of key-words categorising the item. ; _description.common 'key words' _name.category_id description _name.object_id key_words _type.purpose Describe _type.container List _type.contents Code save_ save_description.common _definition.id '_description.common' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Commonly-used identifying name for the item. ; _description.common 'common name' _name.category_id description _name.object_id common _type.purpose Describe _type.container Single _type.contents Text save_ save_description.text _definition.id '_description.text' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The text description of the defined item. ; _description.common 'description' _name.category_id description _name.object_id text _type.purpose Describe _type.container Single _type.contents Text save_ #---------------------------------------------------------------------------- save_DESCRIPTION_EXAMPLE _definition.id description_example _definition.scope Category _definition.class List _definition.update 2007-02-06 _description.text ; The attributes of descriptive (non-machine parseable) examples of values of the defined items. ; _category.parent_id description _category_key.generic '_description_example.case' save_ save_description_example.case _definition.id '_description_example.case' _definition.update 2006-11-16 _definition.class Attribute _description.text ; An example case of the defined item. ; _name.category_id description_example _name.object_id case _type.purpose Key _type.container Single _type.contents Text save_ save_description_example.detail _definition.id '_description_example.detail' _definition.update 2006-11-16 _definition.class Attribute _description.text ; A description of an example case for the defined item. ; _name.category_id description_example _name.object_id detail _type.purpose Describe _type.container Single _type.contents Text save_ #---------------------------------------------------------------------------- save_DICTIONARY _definition.id dictionary _definition.scope Category _definition.class Set _definition.update 2006-11-16 _description.text ; Attributes for identifying and registering the dictionary. The items in this category are NOT used as attributes of INDIVIDUAL data items. ; _category.parent_id ddl_attr save_ save_dictionary.class _definition.id '_dictionary.class' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The nature, or field of interest, of data items defined in the dictionary. ; _name.category_id dictionary _name.object_id class _type.purpose State _type.container Single _type.contents Code loop_ _enumeration_set.state _enumeration_set.detail Attribute 'dictionary containing DDL attribute definitions' Instance 'dictionary containing data definitions' Import 'dictionary containing definitions for importation' Function 'dictionary containing method function definitions' _enumeration.default Instance save_ save_dictionary.date _definition.id '_dictionary.date' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The date that the last dictionary revision took place. ; _name.category_id dictionary _name.object_id date _type.purpose Audit _type.container Single _type.contents Date save_ save_dictionary.ddl_conformance _definition.id '_dictionary.ddl_conformance' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The version number of the DDL dictionary that this dictionary conforms to. ; _name.category_id dictionary _name.object_id ddl_conformance _type.purpose Audit _type.container Single _type.contents Version save_ save_dictionary.namespace _definition.id '_dictionary.namespace' _definition.update 2006-12-05 _definition.class Attribute _description.text ; The namespace code that may be prefixed (with a trailing colon ":") to an item tag defined in the defining dictionary when used in particular applications. Because tags must be unique, namespace codes are unlikely to be used data files. ; _name.category_id dictionary _name.object_id namespace _type.purpose Identify _type.container Single _type.contents Code save_ save_dictionary.title _definition.id '_dictionary.title' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The common title of the dictionary. Will usually match the name attached to the data_ statement of the dictionary file. ; _name.category_id dictionary _name.object_id title _type.purpose Identify _type.container Single _type.contents Code save_ save_dictionary.uri _definition.id '_dictionary.uri' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The universal resource indicator of this dictionary. ; _name.category_id dictionary _name.object_id uri _type.purpose Identify _type.container Single _type.contents Uri save_ save_dictionary.version _definition.id '_dictionary.version' _definition.update 2006-11-16 _definition.class Attribute _description.text ; A unique version identifier for the dictionary. ; _name.category_id dictionary _name.object_id version _type.purpose Audit _type.container Single _type.contents Version save_ #---------------------------------------------------------------------------- save_DICTIONARY_AUDIT _definition.id dictionary_audit _definition.scope Category _definition.class List _definition.update 2007-02-06 _description.text ; Attributes for identifying and registering the dictionary. The items in this category are NOT used as attributes of individual data items. ; _category.parent_id dictionary _category_key.generic '_dictionary_audit.version' save_ save_dictionary_audit.date _definition.id '_dictionary_audit.date' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The date of each dictionary revision. ; _name.category_id dictionary_audit _name.object_id date _type.purpose Audit _type.container Single _type.contents Date save_ save_dictionary_audit.revision _definition.id '_dictionary_audit.revision' _definition.update 2006-11-16 _definition.class Attribute _description.text ; A description of the revision applied for the _dictionary_audit.version. ; _name.category_id dictionary_audit _name.object_id revision _type.purpose Describe _type.container Single _type.contents Text save_ save_dictionary_audit.version _definition.id '_dictionary_audit.version' _definition.update 2006-11-16 _definition.class Attribute _description.text ; A unique version identifier for each revision of the dictionary. ; _name.category_id dictionary_audit _name.object_id version _type.purpose Key _type.container Single _type.contents Version save_ #----------------------------------------------------------------------------- save_DICTIONARY_VALID _definition.id dictionary_valid _definition.scope Category _definition.class List _definition.update 2007-02-06 _description.text ; Data items which are used to specify the contents of definitions in the dictionary in terms of the _definition.scope and the required and prohibited attributes. ; _category.parent_id dictionary _category_key.generic '_dictionary_valid.scope' save_ save_dictionary_valid.attributes _definition.id '_dictionary_valid.attributes' _definition.update 2006-11-16 _definition.class Attribute _description.text ; A list of the attribute names and the attribute categories that are either MANDATORY or PROHIBITED for the _definition.scope value specified in the corresponding _dictionary_valid.scope. All unlisted attributes are considered optional. MANDATORY attributes are preceded by a "+" character. PROHIBITED attributes are preceded by a "!" character. RECOMMENDED attributes are preceded by a "." character. ; _name.category_id dictionary_valid _name.object_id attributes _type.purpose Audit _type.container Single _type.contents Text save_ save_dictionary_valid.scope _definition.id '_dictionary_valid.scope' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The _definition.scope code corresponding to the attribute list given in _dictionary_valid.attributes. ; _name.category_id dictionary_valid _name.object_id scope _name.linked_item_id '_definition.scope' _type.purpose Key _type.container Single _type.contents Code loop_ _enumeration_set.state _enumeration_set.detail Dictionary "applies to all defined items in the dictionary" Category "applies to all defined items in the category" Item "applies to a single definition" save_ #----------------------------------------------------------------------------- save_DICTIONARY_XREF _definition.id dictionary_xref _definition.scope Category _definition.class List _definition.update 2007-02-06 _description.text ; Data items which are used to cross reference other dictionaries that have defined the same data items. Data items in this category are NOT used as attributes of individual data items. ; _category.parent_id dictionary _category_key.generic '_dictionary_xref.code' save_ save_dictionary_xref.code _definition.id '_dictionary_xref.code' _definition.update 2006-11-16 _definition.class Attribute _description.text ; A code identifying the cross-referenced dictionary. ; _name.category_id dictionary_xref _name.object_id code _type.purpose Key _type.container Single _type.contents Code save_ save_dictionary_xref.date _definition.id '_dictionary_xref.date' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Date of the cross-referenced dictionary. ; _name.category_id dictionary_xref _name.object_id date _type.purpose Audit _type.container Single _type.contents Date save_ save_dictionary_xref.format _definition.id '_dictionary_xref.format' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Format of the cross referenced dictionary. ; _name.category_id dictionary_xref _name.object_id format _type.purpose Audit _type.container Single _type.contents Text save_ save_dictionary_xref.name _definition.id '_dictionary_xref.name' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The name and description of the cross-referenced dictionary. ; _name.category_id dictionary_xref _name.object_id name _type.purpose Audit _type.container Single _type.contents Text save_ save_dictionary_xref.uri _definition.id '_dictionary_xref.uri' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The source URI of the cross referenced dictionary data. ; _name.category_id dictionary_xref _name.object_id uri _type.purpose Audit _type.container Single _type.contents Uri save_ #---------------------------------------------------------------------------- save_ENUMERATION _definition.id enumeration _definition.scope Category _definition.class Set _definition.update 2006-11-16 _description.text ; The attributes for restricting the values of defined data items. ; _category.parent_id ddl_attr save_ save_enumeration.default _definition.id '_enumeration.default' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The default value for the defined item if it is not specified explicitly. ; _name.category_id enumeration _name.object_id default _type.purpose Limit _type.container Single _type.contents Implied save_ save_enumeration.def_index_id _definition.id '_enumeration.def_index_id' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The data name of the value that is used as an index in the DEFAULTS enumeration list to select the default enumeration value. The value must match one of the _enumeration_default.index values. ; _name.category_id enumeration _name.object_id def_index_id _type.purpose Identify _type.container Single _type.contents Tag save_ save_enumeration.range _definition.id '_enumeration.range' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The inclusive range of values "from:to" allowed for the defined item. ; _name.category_id enumeration _name.object_id range _type.purpose Limit _type.container Single _type.contents Range save_ save_enumeration.mandatory _definition.id '_enumeration.mandatory' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Yes or No flag on whether the enumerate states specified for an item in the current definition (in which item appears) MUST be used on instantiation. ; _name.category_id enumeration _name.object_id mandatory _type.purpose Limit _type.container Single _type.contents YesorNo _enumeration.default Yes save_ #----------------------------------------------------------------------------- save_ENUMERATION_DEFAULT _definition.id enumeration_default _definition.scope Category _definition.class List _definition.update 2007-02-06 _description.text ; List of pre-determined default enumeration values indexed to a data item by the item _enumeration.def_index_id. ; _category.parent_id enumeration _category_key.generic '_enumeration_default.index' save_ save_enumeration_default.index _definition.id '_enumeration_default.index' _definition.update 2006-11-16 _definition.class Attribute _description.text ; A list of possible values for the item _enumeration.def_index_id used to index (select) the enumeration default value from the _enumeration_default.value list. ; _name.category_id enumeration_default _name.object_id index _type.purpose Key _type.container Single _type.contents Code save_ save_enumeration_default.value _definition.id '_enumeration_default.value' _definition.update 2006-11-16 _definition.class Attribute _description.text ; A list of possible default enumeration values for the defined item. This is selected by the _enumeration_default.index value which matches value of the item specified by _enumeration.def_index_id. ; _name.category_id enumeration_default _name.object_id value _type.purpose Limit _type.container Single _type.contents Implied save_ #----------------------------------------------------------------------------- save_ENUMERATION_SET _definition.id enumeration_set _definition.scope Category _definition.class List _definition.update 2007-02-06 _description.text ; Attributes of data items which are used to define a set of unique pre-determined values. ; _category.parent_id enumeration _category_key.generic '_enumeration_set.state' save_ save_enumeration_set.state _definition.id '_enumeration_set.state' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Permitted value state for the defined item. ; _name.category_id enumeration_set _name.object_id state _type.purpose Key _type.container Single _type.contents Code save_ save_enumeration_set.construct _definition.id '_enumeration_set.construct' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The construction rules of the value that the code describes. The code conforms to regular expression (REGEX) specifications. ; _name.category_id enumeration_set _name.object_id construct _type.purpose Limit _type.container Single _type.contents Regex save_ save_enumeration_set.detail _definition.id '_enumeration_set.detail' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The meaning of the code (identified by _enumeration_set.state) in terms of the value of the quantity it describes. ; _name.category_id enumeration_set _name.object_id detail _type.purpose Describe _type.container Single _type.contents Text save_ save_enumeration_set.xref_code _definition.id '_enumeration_set.xref_code' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Identity of the equivalent item in the dictionary referenced by the DICTIONARY_XREF attributes. ; _name.category_id enumeration_set _name.object_id xref_code _type.purpose Identify _type.container Single _type.contents Code save_ save_enumeration_set.xref_dictionary _definition.id '_enumeration_set.xref_dictionary' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Code identifying the dictionary in the DICTIONARY_XREF list. ; _name.category_id enumeration_set _name.object_id xref_dictionary _type.purpose Link _type.container Single _type.contents Code save_ #---------------------------------------------------------------------------- save_IMPORT _definition.id import _definition.scope Category _definition.class List _definition.update 2007-02-06 _description.text ; Used to import the values of specific attributes from other dictionary definitions within and without the current dictionary. ; _category.parent_id ddl_attr _category_key.generic '_import.block' save_ save_import.block _definition.id '_import.block' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Tag of the definition block to be imported with the file specified by _import.file ; _name.category_id import _name.object_id block _type.purpose Key _type.container Single _type.contents Tag loop_ _description_example.case '_atom_site.xyz' 'refln' save_ save_import.file _definition.id '_import.file' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The URI or filename of the file from which the definition block, designated by _import.block, is to be sourced. ; _name.category_id import _name.object_id file _type.purpose Identify _type.container Single _type.contents Uri save_ save_import.if_dupl _definition.id '_import.if_dupl' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Action taken if the definition block requested already exists in the importing dictionary. ; _name.category_id import _name.object_id if_dupl _type.purpose State _type.container Single _type.contents Code loop_ _enumeration_set.state _enumeration_set.detail Ignore 'ignore imported definitions if id conflict' Replace 'replace existing with imported definitions' Exit 'issue error exception and exit' _enumeration.default Exit save_ save_import.if_miss _definition.id '_import.if_miss' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Action taken if the definition block requested is missing from the source dictionary. ; _name.category_id import _name.object_id if_miss _type.purpose State _type.container Single _type.contents Code loop_ _enumeration_set.state _enumeration_set.detail Ignore 'ignore import' Exit 'issue error exception and exit' _enumeration.default Exit save_ save_import.scope _definition.id '_import.scope' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Code signaling the scope of the definition block to be imported. ; _name.category_id import _name.object_id scope _type.purpose State _type.container Single _type.contents Code loop_ _enumeration_set.state _enumeration_set.detail Dic 'all saveframes in the source file' Cat 'all saveframes in the specific category' Grp 'all saveframes in the category with children' Itm 'one saveframe containing an item definition' Att 'import attributes within a saveframe' Sta 'import enumeration state list only' Val 'import enumeration default value list only' save_ #---------------------------------------------------------------------------- save_IMPORT_LIST _definition.id import_list _definition.scope Category _definition.class Set _definition.update 2006-11-16 _description.text ; Used to import the values of specific attributes from other dictionary definitions within and without the current dictionary, as a LIST of attributes. ; _category.parent_id ddl_attr save_ save_import_list.id _definition.id '_import_list.id' _definition.update 2006-11-16 _definition.class AttributeSet _description.text ; A list of the attributes, defined individually in the category IMPORT, used to import definitions from other dictionaries. ; _name.category_id import_list _name.object_id id _type.purpose Import _type.container List _type.contents [Code,Tag,Uri,Code,Code] _type.dimension [5 []*] loop_ _method.purpose _method.expression Definition ; With i as import _import_list.id = List([i.scope, i.block, i.file, i.if_dupl, i.if_miss]) ; save_ #---------------------------------------------------------------------------- save_LOOP _definition.id loop _definition.scope Category _definition.class Set _definition.update 2006-11-16 _description.text ; Attributes for looped lists. ; _category.parent_id ddl_attr save_ save_loop.level _definition.id '_loop.level' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Specifies the level of the loop structure in which a defined item must reside if it used in a looped list. ; _name.category_id loop _name.object_id level _type.purpose Limit _type.container Single _type.contents Index _enumeration.range 1: _enumeration.default 1 save_ #---------------------------------------------------------------------------- save_METHOD _definition.id method _definition.scope Category _definition.class List _definition.update 2007-02-06 _description.text ; Methods used for evaluating, validating and defining items. ; _category.parent_id ddl_attr _category_key.generic '_method.purpose' save_ save_method.purpose _definition.id '_method.purpose' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The purpose and scope of the method expression. ; _name.category_id method _name.object_id purpose _type.purpose State _type.container Single _type.contents Code loop_ _enumeration_set.state _enumeration_set.detail Evaluation "method evaluates an item from related item values" Definition "method generates attribute value(s) in the definition" Validation "method compares an evaluation with existing item value" _enumeration.default Evaluation save_ save_method.expression _definition.id '_method.expression' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The method expression for the defined item. ; _name.category_id method _name.object_id expression _type.purpose Method _type.container Single _type.contents Text save_ #---------------------------------------------------------------------------- save_NAME _definition.id name _definition.scope Category _definition.class Set _definition.update 2006-11-16 _description.text ; Attributes for identifying items and item categories. ; _category.parent_id ddl_attr save_ save_name.object_id _definition.id '_name.object_id' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The object name part of a data tag that is unique within the category or mergable family of categories. ; _name.category_id name _name.object_id object_id _type.purpose Identify _type.container Single _type.contents Otag save_ save_name.category_id _definition.id '_name.category_id' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Name of the category of the defined data item. ; _name.category_id name _name.object_id category_id _type.purpose Identify _type.container Single _type.contents Ctag save_ save_name.linked_item_id _definition.id '_name.linked_item_id' _definition.update 2007-03-18 _definition.class Attribute _description.text ; Name of an equivalent item in another category which has a common set of values. ; _name.category_id name _name.object_id linked_item_id _type.purpose Identify _type.container Single _type.contents Tag save_ #---------------------------------------------------------------------------- save_TYPE _definition.id type _definition.scope Category _definition.class Set _definition.update 2006-11-16 _description.text ; Attributes which specify the 'typing' of data items. ; _category.parent_id ddl_attr save_ save_type.container _definition.id '_type.container' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The CONTAINER type of the defined data item value. ; _name.category_id type _name.object_id container _type.purpose State _type.container Single _type.contents Code loop_ _enumeration_set.state _enumeration_set.detail Single 'a single value' Multiple 'values related by boolean ',|&!*' or range ":" ops' List 'list of values bounded by []; separated by commas' Array 'List of fixed length and dimension' Tuple 'immutable List bounded by (); nested tuples allowed' Table 'key:value elements bounded by {}; separated by commas' Implied 'implied by type.container of associated value' _enumeration.default Single save_ save_type.contents _definition.id '_type.contents' _definition.update 2006-11-16 _definition.class Attribute _description.text ; Used to specify the syntax construction of value elements of the defined object. The syntax is specified in terms of fixed regex constructs that have been enumerated as states. Values with more than one element may be specified as a list of multiple states. Note that this list may contain states related by boolean or range operators. The typing of elements is determined by the replication of the minimum set of states declared. ; _name.category_id type _name.object_id contents _type.purpose State _type.container Multiple _type.contents Code _import_list.id ['sta','type_contents','com_val.dic','exit','exit'] loop_ _description_example.case _description_example.detail 'Integer' 'all elements are integer' 'Real,Code' 'elements are in muliples of real number and codes' 'Real|Code' 'elements are either a real number or a code' save_ save_type.purpose _definition.id '_type.purpose' _definition.update 2006-11-16 _definition.class Attribute _description.text ; The primary purpose or origin of the defined data item. ; _name.category_id type _name.object_id purpose _type.purpose State _type.container Single _type.contents Code loop_ _enumeration_set.state _enumeration_set.detail _enumeration_set.construct Import ; >>> For dictionaries only <<< Used within dictionaries to import definition lines from other dictionaries. In the expanded dictionary the import item is replaced by the imported items. ; Method ; >>> For dictionaries only <<< A text method expression in a dictionary definition relating the defined item to other defined items. ; Audit ; An item used to contain audit information about the creation or conformance of a file. ; Identify An item used to identify another item or file. ; Describe ; A descriptive item intended only for human interpretation. ; Limit ; An item used to limit the values of other items. ; State ; An item with one or more codified values that must exist within a discrete and countable list of enumerated states. ; Key ; An item with a codified value that is the key to identifying specific packets of items in the same category. ; Link ; An item with a value that is a foreign key linking packets in this category list to packets in another category. ; Assigned An item whose value is assigned in the process of modelling measured and observed data items. ; Observed ; An item whose value is determined by observation or deduction. Numerical observed values do NOT have a standard uncertainty. ; Measured ; A numerical item whose value is measured or derived from a measurement. It is expected to have a standard uncertainty value which is either 1) appended as integers in parentheses at the precision of the trailing digits, or 2) as a separate item with the same name as defined item but with a trailing '_su'. ; save_ save_type.dimension _definition.id '_type.dimension' _definition.update 2006-12-05 _definition.class Attribute _description.text ; The dimensions of the list array bounded by square brackets. Each dimension may be expressed simply as an integer giving the maximum index permitted (the minimum is assumed to be 1). * is used to signal unknown number of array elements. Alternately, each dimension may be entered in the form: :. ; _name.category_id type _name.object_id dimension _type.purpose Limit _type.container List _type.contents Index _type_array.dimension [1: []*] loop_ _description_example.case _description_example.detail "[3,3]" 'in Array definition: 3x3 elements' "[6]" 'in List definition: 6 values' "[4[2]]" 'in Tuple defn: 4 Tuples of 2 values' save_ #---------------------------------------------------------------------------- save_UNITS _definition.id units _definition.scope Category _definition.class Set _definition.update 2006-11-16 _description.text ; The attributes for specifying units of measure. ; _category.parent_id ddl_attr save_ save_units.code _definition.id '_units.code' _definition.update 2006-11-16 _definition.class Attribute _description.text ; A code which identifies the units of measurement. ; _name.category_id units _name.object_id code _type.purpose State _type.container Single _type.contents Code _import_list.id ['sta','units_code','com_val.dic','exit','exit'] save_ #============================================================================= # The dictionary's attribute validation criteria and the creation history. #============================================================================ loop_ _dictionary_valid.scope _dictionary_valid.attributes Dictionary ; + _dictionary.title + _dictionary.class + _dictionary.version + _dictionary.date + _dictionary.uri + _dictionary.ddl_conformance + _dictionary.namespace + _dictionary_audit.version + _dictionary_audit.date + _dictionary_audit.revision . _description.text ! ALIAS ! CATEGORY ! DEFINITION ! ENUMERATION ! LOOP ! METHOD ! NAME ! TYPE ! UNITS ; Category ; + _definition.id + _definition.scope + _definition.class + _category.parent_id . _category_key.generic . _category_key.primitive . _category_mandatory.item_id . _description.text ! ALIAS ! DICTIONARY ! ENUMERATION ! IMPORT ! LOOP ! NAME ! TYPE ! UNITS ; Item ; + _definition.id + _definition.scope + _definition.class + _definition.update + _name.object_id + _name.category_id + _type.purpose + _type.container + _type.contents . _description.text . _description.common ! CATEGORY ! DICTIONARY ; loop_ _dictionary_audit.version _dictionary_audit.date _dictionary_audit.revision 3.0 1999-04-06 ; Initial draft of DDL3 based on attributes from DDL1.4 and DDL2.1.1. ; 3.0.1 1999-05-06 ; Added new method attributes and enumeration LIST values ; 3.0.2 1999-05-11 ; Repacked and redefined some definition and dictionary attributes ; 3.0.3 1999-05-12 ; Introduced category.level etc. attributes and rearranged categories ; 3.0.4 1999-05-18 ; Removed category.level, linked.parent, linked.child, category.child_id Changed related.function to include "Parent_Key", "Linked_Key", "Linked_Values" and "Linked_Array" codes. ; 3.0.5 1999-05-22 ; Access keys in category families are inherited. Remove "Linked_Values" for related.function. ; 3.0.6 1999-05-24 ; Add "Su_Implicit" code to related.function. ; 3.0.7 1999-05-25 ; Further simplifications to the syntax. ; 3.0.8 1999-05-27 ; Change _definition.class code DATA_ITEM to ITEM_DEFINITION ; 3.0.9 1999-06-10 ; Add "List" to _type_array.class enumerations. ; 3.0.10 1999-06-11 ; Add various codes to the enumeration lists. ; 3.0.11 1999-06-22 ; Convert all enumeration list data names. ; 3.0.12 1999-06-28 ; Recaste the TYPE attributes and enumerations. ; 3.0.13 1999-07-05 ; Change "pattern" to "function" for TYPE attributes. ; 3.0.14 1999-07-09 ; Change "string" to "container" for TYPE attributes. Change codes for definition.scope and definition.class ; 3.0.15 1999-11-26 ; Add the _definition.update attribute. ; 3.0.16 2000-02-15 ; Change the names of the files to reflect prototype specifications. ; 3.0.17 2000-04-17 ; Add the attributes description.compact and description.abbreviated. ; 3.0.18 2000-05-19 ; Add the definition class TRANSIENT for FUNCTION definitions. ; 3.0.19 2000-06-06 ; Change the definition scope GROUP to Category. Change the definition scope ITEM to SINGLE. Add the definition scope COSET for common definitions. Change type.function to type.purpose. ; 3.0.20 2000-06-07 ; Add the definition for category.coset_id Add the definition for item.coset_id Added the Equivalent code to related.function ; 3.1.00 2000-06-12 ; Reorganised families into category groupings ATTRIBUTES and ENUMERATION ; 3.1.01 2000-06-20 ; Inserted possible method validation scripts ; 3.1.02 2000-06-24 ; MAJOR modifications and additions following discussions with JW. ; 3.1.03 2000-06-26 ; Changes to MODEL attributes and many other changes. ; 3.1.04 2000-06-28 ; Version agreed upon up to JW's return to Rutgers. ; 3.1.05 2000-06-29 ; In method.class change ENUMERATION to EVALUATION. ; 3.1.06 2000-07-03 ; Corrections from running dREL 1.0.3. ; 3.1.07 2000-07-11 ; Add the attribute enumeration.dot. ; 3.1.08 2000-09-13 ; Remove the attribute enumeration.dot. ; 3.1.09 2000-10-09 ; Add the XREF definitions. In type_purpose change 'From:To' to 'Range'; 'Code' to 'State'. In type_container add the enumeration 'Multiple' ; 3.2.00 2000-11-02 ; MAJOR revision and simplification of ALL definitions. Blame PMR! ; 3.2.01 2000-11-03 ; Move the enumeration lists back into their respective definitions. ; 3.2.02 2000-11-06 ; Change "State" back to "Code". ; 3.2.03 2000-11-07 ; Add category_key.relational which gives the relational key used in DDL2 ; 3.2.04 2000-11-10 ; MAJOR changes to a number of attributes and categories. ; 3.2.05 2000-11-13 ; Introduced definition.import_id. ; 3.2.06 2000-11-24 ; Change the _method.class enumeration state "Units" to "Definition". ; 3.2.07 2001-08-30 ; Change "category.parent_id" to "category.family_id". ; 3.2.08 2001-09-03 ; Change "alias.dictionary_class" to "alias.dictionary_uri". Change the "dictionary.class" states to "Attribute" and "Instance" ; 3.2.09 2001-09-26 ; Change "category.family_id" to "category.parent_id". ; 3.2.10 2001-10-01 ; Remove the definition of "alias.dictionary_version". ; 3.2.11 2001-10-02 ; Converted reference to "codes.unit_code" to "codes.units_code". ; 3.2.12 2001-11-13 ; Corrected loop miscount in "type.purpose". ; 3.2.13 2001-11-14 ; Corrected name.category_id in category.parent_id. ; 3.2.14 2002-02-02 ; Remove key from category DEFINITION. ; 3.2.15 2002-07-30 ; Several small typos corrected. Add "Tuple" to the list of type.container enumerations ; 3.2.16 2004-10-12 ; Corrected mismatch in version numbering between v2.13a and v2.13b and merged these changes into this version. ; 3.2.17 2004-10-12 ; In dictionary.class changed enumeration.default to "Instance" In type.container append a ' to the enumeration detail of "Tuple" ; 3.3.00 2004-11-09 ; Change definition.import_id to definition_import.id in many defs. Insert category DEFINITION_IMPORT and the items .id, .conflict, .protocol and .source. ; 3.3.01 2004-11-10 ; Make further changes to the DEFINITION_IMPORT definitions and introduce the DEFINITION_TEMPLATE category. ; 3.3.02 2004-11-11 ; Introduce an IMPORT category containing IMPORT_DICTIONARY, IMPORT_DEFINITION, IMPORT_CATEGORY, IMPORT_ATTRIBUTE. Change DEFINITION_TEMPLATE to IMPORT_TEMPLATE. ; 3.3.03 2004-11-12 ; Major changes to all the new attributes. Introduce categories DEFINITION_CONTEXT. ; 3.3.04 2004-11-13 ; Cleaned up the IMPORT changes and cases of enumerates. ; 3.3.05 2004-11-16 ; Further changes to IMPORT definitions. ; 3.3.06 2004-11-18 ; Some minor correction of typos ; 3.3.07 2005-11-22 ; Changed _dictionary.name to _dictionary.filename Changed _dictionary_xref.name to _dictionary_xref.filename Added _dictionary.title to describe the common name of the dictionary ; 3.3.08 2005-12-12 ; Changed ddl to ddl_attr Added Template and Function to _dictionary.class ; 3.3.09 2006-02-02 ; Add the definition of _dictionary_xref.source. ; 3.3.10 2006-02-07 ; Add import attribute definitions ; 3.4.01 2006-02-12 ; Remove save frames from dictionary attributes. Change the attribute _dictionary.parent_name to _dictionary.parent_id ; 3.4.02 2006-02-16 ; In the _import_*.conflict definitions change the enumeration state Unique to Ignore, and change the default state to Error. In the _import_*.missing definitions change default enumeration state to Error. ; 3.5.01 2006-03-07 ; Structural changes to the file to conform with the import model 3. Move the template file for *.relational_id to com_att.dic Change all references to *.relational_id into the tuple format. Move the _codes_ddl.units_code to enum_set.dic and insert the _import_enum_set.id tuples. ; 3.5.02 2006-03-22 ; Rename _enumeration.default_index_id to _enumeration.def_index_id. Correct the attributes _enumeration_default.index and *.value. ; 3.5.03 2006-05-09 ; Reword many of the import attributes. Correct the tuple description for _import_dictionary. Insert all of the definitions for _import_defaults attributes. Update _dictionary.class definition - change "Template" to "Import". Remove _enumeration.scope "open" from _definition_context.domain. ; 3.6.01 2006-06-16 ; Major revamp of TYPE attributes... changed: _type.value to _type.contents and expand enumeration list. _type.purpose has new role and different enumeration states. _name.object_id changed to _name.object_id. _enumeration_set.code becomes _enumeration_set.state. Changed the _type.value (now .contents) states to match expanded list. Added _dictionary.ddl_conformance attribute. Changed _category.join_set_id to _category.join_cat_id. Remove _enumeration.scope definition. ; 3.6.02 2006-06-17 ; Change the states of _type.purpose. ; 3.6.03 2006-06-18 ; Correct _type.contents value in _import_dictionary.id. ; 3.6.04 2006-06-20 ; Change state 'Point' to 'Link' in _type.contents definition. Add Formula to _type.contents ; 3.6.05 2006-06-27 ; Change all IMPORT attributes and apply. Add _dictionary.namespace attribute and apply. Add states to _definition.class and apply. Add _enumeration_set.scope. Add .context to ENUMERATE_SET, ENUMERATE_DEFAULT, DESCRIPTION_EXAMPLE ; 3.6.06 2006-07-18 ; Change the descriptions of the _type.container states. The _enueration_set.scope removed (enumeration.mandatory used). In _type_array.dimension change _type.contents to List. ; 3.6.07 2006-08-30 ; Change 'att' to 'sta' in the imports of _type.contents and _units.code. Replace states 'vector' and 'matrix' in _type.container with 'array'. In _type.purpose change 'model' to 'assigned'; 'observe' to 'observed'; and 'measure' to 'measured'. ; 3.6.08 2006-08-31 ; Remove the category TYPE_ARRAY and insert _type.dimension Replace _description.compact with _description.common Replace _description.abbreviated with _description.key_words ; 3.6.09 2006-10-31 ; Remove all attributes and categories referring to 'context'. ; 3.6.10 2006-11-09 ; Replace _method.id with method.purpose. Redefine the DICTIONARY_VALID values. ; 3.7.01 2006-11-16 ; Apply _definition.scope changes. Add _category.parent_join. Add _dictionary.xref_code. Add _enumeration_set.xref_dictionary. Remove all relational keys. ; 3.7.02 2006-12-05 ; Rewording of description.text in DDL_ATTR and definition.namespace Rewording of category_mandatory.item_id Reworded descriptions of definition.class descriptions. Removed dictionary.filename. Corrected examples in type.dimension. Remove dictionary.parent_id and dictionary.parent_uri. ; 3.7.03 2006-12-21 ; Default for _category.parent_join is now "No" ; 3.7.04 2007-02-06 ; Change _category_key.item_id to _category_key.generic Add _category_key.primitive ; 3.7.05 2007-02-08 ; Change the _type.purpose of _category_key.generic and .primitive to Identify ; 3.7.06 2007-03-18 ; Change the description for _name.linked_item_id ; ./CBFlib-0.9.2.2/dREL-ply-0.5/drelc.py0000644000076500007650000000203511603702115015131 0ustar yayayaya#!/usr/bin/python import drel_lex import drel_yacc import sys import CifFile import StarFile class Process: def execute_method(self): valuename = sys.argv[1] #print "Valuename: %s" % valuename datablock_name = sys.argv[2] #print "Datablock: %s" % datablock_name #dictionary = sys.argv[3] #cbf_handle = sys.argv[3] #print "CBF handle: %s" % cbf_handle #create our lexer and parser self.lexer = drel_lex.lexer self.parser = drel_yacc.parser #use a simple dictionary testdic = CifFile.CifDic("cif_expanded.dic", grammar='DDLm') self.testblock = CifFile.CifFile("cbf_data_debug") [datablock_name] self.testblock.assign_dictionary(testdic) realres = self.testblock[valuename] #create the global namespace print "Generated value: %s" % realres fout = open("method_output", 'w') print>>fout, realres #method returns realres as the value that would be missing #for validation #failUnless(realres == value) p = Process() p.execute_method() ./CBFlib-0.9.2.2/dREL-ply-0.5/parsetab.py0000755000076500007650000025074511603702115015661 0ustar yayayaya # parsetab.py # This file is automatically generated. Do not edit. _tabversion = '3.2' _lr_method = 'LALR' _lr_signature = '\x9a\xba\xc8\x80\x9a\xe3#2\x8f\xfe\xca8\xdc\xab\xbb\x8f' _lr_action_items = {'REAL':([0,2,3,4,6,7,8,9,11,12,13,14,15,16,17,18,19,20,21,22,23,24,26,27,28,29,30,31,32,33,34,35,37,38,39,40,41,42,43,44,45,47,48,49,50,51,52,53,55,56,57,59,60,61,62,64,65,66,67,68,69,71,72,73,74,75,76,77,78,79,80,82,83,84,86,87,88,89,90,91,92,93,94,95,97,99,100,105,107,108,109,111,113,114,116,117,118,119,120,121,123,124,125,126,127,128,129,130,131,132,133,135,136,137,138,139,140,141,142,143,144,145,146,148,149,151,153,154,155,157,161,165,169,176,177,178,179,180,181,182,183,184,185,186,187,188,189,190,191,192,193,194,195,196,197,198,199,203,205,208,209,210,211,212,213,215,216,217,220,221,223,224,227,230,237,238,239,240,241,242,250,252,255,259,260,262,263,264,269,],[40,-50,-134,40,40,-14,-72,-55,40,40,-129,-6,-130,-71,-53,-128,40,40,-127,-74,-61,-131,-11,-10,40,-59,40,-70,-9,-64,-99,-5,-98,40,-132,-66,-51,107,-133,-65,-58,-54,-2,-73,-12,40,-57,-52,-62,-13,-63,-67,-56,40,-4,-60,-149,-137,-138,40,-140,-41,40,107,-24,-45,-76,40,-28,40,-22,-38,-26,-125,-18,-16,-68,-69,-3,-145,107,40,40,40,40,-15,107,-79,-96,-94,40,40,-152,40,40,40,40,40,40,-142,-27,40,40,-47,-33,40,40,-36,40,-32,-35,-34,-30,-31,-46,40,-20,40,40,40,-75,40,40,-77,-136,40,-78,-21,40,40,-115,-95,40,-120,40,-135,-7,-124,-126,-139,-143,-141,-153,-49,-29,-39,-40,-37,-25,-42,-43,-44,-17,-23,40,-146,40,40,-121,-116,40,40,-105,-100,40,-97,40,40,-8,-154,-144,40,40,40,40,40,40,40,-147,-158,40,-150,40,40,40,-155,40,-148,-151,]),'DO':([0,2,3,4,7,8,9,11,12,13,14,15,16,17,18,21,22,23,24,26,27,29,31,32,33,34,35,37,39,40,41,43,44,45,47,48,49,50,51,52,53,55,56,57,59,60,62,64,65,66,67,68,69,71,74,75,76,78,80,82,83,84,86,87,88,89,90,91,92,95,97,99,100,105,107,108,113,116,120,121,123,126,138,140,144,148,149,153,154,161,165,176,178,179,180,181,182,183,184,185,186,187,188,189,191,192,193,194,195,196,197,198,199,205,208,211,212,215,220,221,223,224,237,239,241,242,250,252,262,264,269,],[58,-50,-134,58,-14,-72,-55,58,58,-129,-6,-130,-71,-53,-128,-127,-74,-61,-131,-11,-10,-59,-70,-9,-64,-99,-5,-98,-132,-66,-51,-133,-65,-58,-54,-2,-73,-12,58,-57,-52,-62,-13,-63,-67,-56,-4,-60,-149,-137,-138,58,-140,-41,-24,-45,-76,-28,-22,-38,-26,-125,-18,-16,-68,-69,-3,-145,-48,58,58,-15,-19,-79,-96,-94,-152,58,58,-142,-27,-47,-46,-20,-75,-77,-136,-78,-21,-115,-95,-120,-135,-7,-124,-126,-139,-143,-141,-153,-49,-29,-39,-40,-25,-42,-43,-44,-17,-23,58,-146,58,-121,-116,-105,-100,-97,-8,-154,-144,58,58,58,-147,-158,58,-150,-155,-148,-151,]),'DEFAULT':([2,3,7,8,9,13,15,16,17,18,21,22,23,24,26,27,29,31,32,33,34,37,39,40,41,43,44,45,47,49,50,52,53,55,56,57,59,60,64,65,66,67,71,74,75,76,78,80,82,83,86,87,88,89,91,92,99,105,107,108,113,123,126,138,144,148,149,153,161,165,176,178,180,182,184,186,187,188,189,191,192,193,194,195,196,205,208,211,212,215,218,221,223,242,249,261,262,],[-50,-134,-14,-72,-55,-129,-130,-71,-53,-128,-127,-74,-61,-131,-11,-10,-59,-70,-9,-64,-99,-98,-132,-66,-51,-133,-65,-58,-54,-73,-12,-57,-52,-62,-13,-63,-67,-56,-60,-149,-137,-138,-41,-24,-45,-76,-28,-22,-38,-26,-18,-16,-68,-69,-145,-48,-15,-79,-96,-94,-152,-27,-47,-46,-75,-77,-136,-78,-115,-95,-120,-135,-124,-139,-141,-49,-29,-39,-40,-25,-42,-43,-44,-17,-23,-121,-116,-105,-100,-97,239,-154,-144,-158,-156,-157,-155,]),'-':([2,6,8,9,16,17,19,20,22,23,28,29,31,33,34,37,38,40,41,44,45,47,49,52,53,55,57,59,60,61,64,71,72,73,75,76,77,78,79,82,88,89,92,93,94,105,107,108,109,111,114,118,124,125,126,127,128,129,130,131,132,133,135,136,137,138,139,141,142,143,144,145,146,148,151,153,155,157,161,165,169,177,186,187,188,189,190,192,193,194,203,208,209,210,211,212,213,215,216,227,230,240,255,259,260,263,],[-50,79,-72,-55,-71,-53,79,79,-74,-61,79,-59,-70,-64,-99,-98,79,-66,-51,-65,-58,-54,-73,-57,-52,-62,-63,-67,-56,79,-60,-41,79,-48,-45,-76,79,131,79,-38,-68,-69,-48,79,79,-79,-96,-94,79,79,79,79,79,79,-47,-33,79,79,-36,79,-32,-35,-34,-30,-31,-46,79,79,79,79,-75,79,79,-77,79,-78,79,79,-115,-95,79,79,-49,131,-39,-40,-37,-42,-43,-44,79,-116,79,79,-105,-100,79,-97,79,79,79,79,79,79,79,79,]),',':([2,8,9,16,17,22,23,29,31,33,34,37,40,41,42,44,45,47,49,52,53,54,55,57,59,60,63,64,71,73,74,75,76,78,80,81,82,83,84,85,86,87,88,89,92,96,100,101,104,105,106,107,108,123,126,138,140,144,148,153,154,156,159,160,161,163,164,165,166,167,168,169,170,171,172,173,174,176,180,181,186,187,188,189,191,192,193,194,195,196,199,200,202,204,208,211,212,213,214,215,216,219,228,231,232,233,234,235,236,237,244,245,246,248,250,252,265,266,268,270,],[-50,-72,-55,-71,-53,-74,-61,-59,-70,-64,-99,-98,-66,-51,-19,-65,-58,-54,-73,-57,-52,-125,-62,-63,-67,-56,119,-60,-41,-19,-24,-45,-76,-28,-22,119,-38,-26,-125,145,-18,-16,-68,-69,-48,145,-19,119,119,-79,157,-96,-94,-27,-47,-46,-20,-75,-77,-78,-21,203,-117,206,-115,209,-119,-95,210,-111,-110,-101,-112,-109,145,-106,-16,145,145,-126,-49,-29,-39,-40,-25,-42,-43,-44,-17,-23,145,225,145,-82,-116,-105,-100,-113,-103,-97,-104,240,-83,-118,-111,-107,-108,-114,-102,119,-159,255,-87,-122,119,263,-160,270,-123,-89,]),'PRINT':([0,2,3,4,7,8,9,11,12,13,14,15,16,17,18,21,22,23,24,26,27,29,31,32,33,34,35,37,39,40,41,43,44,45,47,48,49,50,51,52,53,55,56,57,59,60,62,64,65,66,67,68,69,71,74,75,76,78,80,82,83,84,86,87,88,89,90,91,92,95,97,99,100,105,107,108,113,116,117,120,121,123,126,138,140,144,148,149,153,154,161,165,176,178,179,180,181,182,183,184,185,186,187,188,189,191,192,193,194,195,196,197,198,199,205,208,211,212,215,220,221,223,224,237,239,241,242,250,252,262,264,269,],[28,-50,-134,28,-14,-72,-55,28,28,-129,-6,-130,-71,-53,-128,-127,-74,-61,-131,-11,-10,-59,-70,-9,-64,-99,-5,-98,-132,-66,-51,-133,-65,-58,-54,-2,-73,-12,28,-57,-52,-62,-13,-63,-67,-56,-4,-60,-149,-137,-138,28,-140,-41,-24,-45,-76,-28,-22,-38,-26,-125,-18,-16,-68,-69,-3,-145,-48,28,28,-15,-19,-79,-96,-94,-152,28,28,28,-142,-27,-47,-46,-20,-75,-77,-136,-78,-21,-115,-95,-120,-135,-7,-124,-126,-139,-143,-141,-153,-49,-29,-39,-40,-25,-42,-43,-44,-17,-23,28,-146,28,-121,-116,-105,-100,-97,-8,-154,-144,28,28,28,-147,-158,28,-150,-155,-148,-151,]),'AUGOP':([2,8,9,16,17,22,23,29,31,33,34,37,40,41,42,44,45,47,49,52,53,54,55,57,59,60,64,76,88,89,105,107,108,140,144,148,153,154,161,165,208,211,212,215,],[-50,-72,-55,-71,-53,-74,-61,-59,-70,-64,-99,-98,-66,-51,-19,-65,-58,-54,-73,-57,-52,114,-62,-63,-67,-56,-60,-76,-68,-69,-79,-96,-94,-20,-75,-77,-78,-21,-115,-95,-116,-105,-100,-97,]),';':([2,7,8,9,14,16,17,22,23,26,27,29,31,32,33,34,37,40,41,44,45,47,49,50,52,53,55,56,57,59,60,62,64,71,74,75,76,78,80,82,83,86,87,88,89,92,99,105,107,108,123,126,138,144,148,153,161,165,176,179,180,186,187,188,189,191,192,193,194,195,196,205,208,211,212,215,220,],[-50,-14,-72,-55,-6,-71,-53,-74,-61,-11,-10,-59,-70,-9,-64,-99,-98,-66,-51,-65,-58,-54,-73,-12,-57,-52,-62,-13,-63,-67,-56,117,-60,-41,-24,-45,-76,-28,-22,-38,-26,-18,-16,-68,-69,-48,-15,-79,-96,-94,-27,-47,-46,-75,-77,-78,-115,-95,-120,220,-124,-49,-29,-39,-40,-25,-42,-43,-44,-17,-23,-121,-116,-105,-100,-97,-8,]),'BININT':([0,2,3,4,6,7,8,9,11,12,13,14,15,16,17,18,19,20,21,22,23,24,26,27,28,29,30,31,32,33,34,35,37,38,39,40,41,43,44,45,47,48,49,50,51,52,53,55,56,57,59,60,61,62,64,65,66,67,68,69,71,72,74,75,76,77,78,79,80,82,83,84,86,87,88,89,90,91,92,93,94,95,97,99,100,105,107,108,109,111,113,114,116,117,118,119,120,121,123,124,125,126,127,128,129,130,131,132,133,135,136,137,138,139,140,141,142,143,144,145,146,148,149,151,153,154,155,157,161,165,169,176,177,178,179,180,181,182,183,184,185,186,187,188,189,190,191,192,193,194,195,196,197,198,199,203,205,208,209,210,211,212,213,215,216,217,220,221,223,224,227,230,237,238,239,240,241,242,250,252,255,259,260,262,263,264,269,],[44,-50,-134,44,44,-14,-72,-55,44,44,-129,-6,-130,-71,-53,-128,44,44,-127,-74,-61,-131,-11,-10,44,-59,44,-70,-9,-64,-99,-5,-98,44,-132,-66,-51,-133,-65,-58,-54,-2,-73,-12,44,-57,-52,-62,-13,-63,-67,-56,44,-4,-60,-149,-137,-138,44,-140,-41,44,-24,-45,-76,44,-28,44,-22,-38,-26,-125,-18,-16,-68,-69,-3,-145,-48,44,44,44,44,-15,-19,-79,-96,-94,44,44,-152,44,44,44,44,44,44,-142,-27,44,44,-47,-33,44,44,-36,44,-32,-35,-34,-30,-31,-46,44,-20,44,44,44,-75,44,44,-77,-136,44,-78,-21,44,44,-115,-95,44,-120,44,-135,-7,-124,-126,-139,-143,-141,-153,-49,-29,-39,-40,-37,-25,-42,-43,-44,-17,-23,44,-146,44,44,-121,-116,44,44,-105,-100,44,-97,44,44,-8,-154,-144,44,44,44,44,44,44,44,-147,-158,44,-150,44,44,44,-155,44,-148,-151,]),'.':([2,8,9,16,17,22,23,29,31,33,34,37,40,41,42,44,45,47,49,52,53,55,57,59,60,64,73,76,88,89,92,100,105,107,108,109,144,148,153,161,165,206,208,211,212,215,],[-50,-72,-55,-71,-53,-74,-61,-59,-70,-64,-99,-98,-66,-51,110,-65,-58,-54,-73,-57,-52,-62,-63,-67,-56,-60,110,-76,-68,-69,110,110,-79,-96,-94,162,-75,-77,-78,-115,-95,229,-116,-105,-100,-97,]),'WITH':([0,2,3,4,7,8,9,11,12,13,14,15,16,17,18,21,22,23,24,26,27,29,31,32,33,34,35,37,39,40,41,43,44,45,47,48,49,50,51,52,53,55,56,57,59,60,62,64,65,66,67,68,69,71,74,75,76,78,80,82,83,84,86,87,88,89,90,91,92,95,97,99,100,105,107,108,113,116,120,121,123,126,138,140,144,148,149,153,154,161,165,176,178,179,180,181,182,183,184,185,186,187,188,189,191,192,193,194,195,196,197,198,199,205,208,211,212,215,220,221,223,224,237,239,241,242,250,252,262,264,269,],[5,-50,-134,5,-14,-72,-55,5,5,-129,-6,-130,-71,-53,-128,-127,-74,-61,-131,-11,-10,-59,-70,-9,-64,-99,-5,-98,-132,-66,-51,-133,-65,-58,-54,-2,-73,-12,5,-57,-52,-62,-13,-63,-67,-56,-4,-60,-149,-137,-138,5,-140,-41,-24,-45,-76,-28,-22,-38,-26,-125,-18,-16,-68,-69,-3,-145,-48,5,5,-15,-19,-79,-96,-94,-152,5,5,-142,-27,-47,-46,-20,-75,-77,-136,-78,-21,-115,-95,-120,-135,-7,-124,-126,-139,-143,-141,-153,-49,-29,-39,-40,-25,-42,-43,-44,-17,-23,5,-146,5,-121,-116,-105,-100,-97,-8,-154,-144,5,5,5,-147,-158,5,-150,-155,-148,-151,]),'NEQ':([2,8,9,16,17,22,23,29,31,33,34,37,40,41,44,45,47,49,52,53,55,57,59,60,64,71,73,75,76,78,82,88,89,92,105,107,108,126,138,144,148,153,161,165,186,188,189,192,193,194,208,211,212,215,241,],[-50,-72,-55,-71,-53,-74,-61,-59,-70,-64,-99,-98,-66,-51,-65,-58,-54,-73,-57,-52,-62,-63,-67,-56,-60,-41,-48,-45,-76,135,-38,-68,-69,-48,-79,-96,-94,-47,-46,-75,-77,-78,-115,-95,-49,-39,-40,-42,-43,-44,-116,-105,-100,-97,135,]),'CASE':([2,3,7,8,9,13,15,16,17,18,21,22,23,24,26,27,29,31,32,33,34,37,39,40,41,43,44,45,47,49,50,52,53,55,56,57,59,60,64,65,66,67,69,71,74,75,76,78,80,82,83,86,87,88,89,91,92,99,105,107,108,113,123,126,138,144,148,149,153,161,165,175,176,178,180,182,184,186,187,188,189,191,192,193,194,195,196,205,208,211,212,215,218,221,223,242,249,261,262,],[-50,-134,-14,-72,-55,-129,-130,-71,-53,-128,-127,-74,-61,-131,-11,-10,-59,-70,-9,-64,-99,-98,-132,-66,-51,-133,-65,-58,-54,-73,-12,-57,-52,-62,-13,-63,-67,-56,-60,-149,-137,-138,-140,-41,-24,-45,-76,-28,-22,-38,-26,-18,-16,-68,-69,-145,-48,-15,-79,-96,-94,-152,-27,-47,-46,-75,-77,-136,-78,-115,-95,217,-120,-135,-124,-139,-141,-49,-29,-39,-40,-25,-42,-43,-44,-17,-23,-121,-116,-105,-100,-97,238,-154,-144,-158,-156,-157,-155,]),'POWER':([2,8,9,16,17,22,23,29,31,33,34,37,40,41,44,45,47,49,52,53,55,57,59,60,64,73,76,88,89,92,105,107,108,144,148,153,161,165,208,211,212,215,],[-50,-72,-55,-71,-53,-74,-61,-59,-70,-64,-99,-98,-66,-51,-65,-58,-54,-73,-57,-52,-62,-63,-67,-56,-60,124,-76,-68,-69,124,-79,-96,-94,-75,-77,-78,-115,-95,-116,-105,-100,-97,]),')':([2,6,8,9,16,17,22,23,29,31,33,34,37,40,41,44,45,47,49,52,53,55,57,59,60,64,71,73,74,75,76,78,80,81,82,83,84,85,86,87,88,89,92,94,100,105,107,108,109,123,125,126,138,140,144,148,153,154,159,160,161,163,164,165,181,186,187,188,189,191,192,193,194,195,196,200,208,211,212,215,231,244,248,265,268,],[-50,76,-72,-55,-71,-53,-74,-61,-59,-70,-64,-99,-98,-66,-51,-65,-58,-54,-73,-57,-52,-62,-63,-67,-56,-60,-41,-19,-24,-45,-76,-28,-22,140,-38,-26,-125,144,-18,-16,-68,-69,-48,76,-19,-79,-96,-94,161,-27,161,-47,-46,-20,-75,-77,-78,-21,-117,205,-115,208,-119,-95,-126,-49,-29,-39,-40,-25,-42,-43,-44,-17,-23,224,-116,-105,-100,-97,-118,-159,-122,-160,-123,]),'(':([0,2,3,4,6,7,8,9,11,12,13,14,15,16,17,18,19,20,21,22,23,24,26,27,28,29,30,31,32,33,34,35,37,38,39,40,41,42,43,44,45,47,48,49,50,51,52,53,55,56,57,59,60,61,62,64,65,66,67,68,69,71,72,73,74,75,76,77,78,79,80,82,83,84,86,87,88,89,90,91,92,93,94,95,97,99,100,102,105,107,108,109,111,113,114,116,117,118,119,120,121,123,124,125,126,127,128,129,130,131,132,133,135,136,137,138,139,140,141,142,143,144,145,146,148,149,151,153,154,155,157,161,165,169,176,177,178,179,180,181,182,183,184,185,186,187,188,189,190,191,192,193,194,195,196,197,198,199,203,205,208,209,210,211,212,213,215,216,217,220,221,223,224,227,230,237,238,239,240,241,242,250,252,255,259,260,262,263,264,269,],[6,-50,-134,6,6,-14,-72,-55,6,6,-129,-6,-130,-71,-53,-128,94,94,-127,-74,-61,-131,-11,-10,94,-59,6,-70,-9,-64,-99,-5,-98,6,-132,-66,-51,109,-133,-65,-58,-54,-2,-73,-12,6,-57,-52,-62,-13,-63,-67,-56,94,-4,-60,-149,-137,-138,6,-140,-41,94,125,-24,-45,-76,94,-28,94,-22,-38,-26,-125,-18,-16,-68,-69,-3,-145,125,94,94,6,6,-15,125,152,-79,-96,-94,94,94,-152,94,6,6,94,6,6,-142,-27,94,94,-47,-33,94,94,-36,94,-32,-35,-34,-30,-31,-46,94,-20,94,94,94,-75,94,94,-77,-136,94,-78,-21,94,94,-115,-95,94,-120,94,-135,-7,-124,-126,-139,-143,-141,-153,-49,-29,-39,-40,-37,-25,-42,-43,-44,-17,-23,6,-146,6,94,-121,-116,94,94,-105,-100,94,-97,94,6,-8,-154,-144,6,94,94,6,6,6,94,-147,-158,6,-150,94,94,94,-155,94,-148,-151,]),'+':([2,6,8,9,16,17,19,20,22,23,28,29,31,33,34,37,38,40,41,44,45,47,49,52,53,55,57,59,60,61,64,71,72,73,75,76,77,78,79,82,88,89,92,93,94,105,107,108,109,111,114,118,124,125,126,127,128,129,130,131,132,133,135,136,137,138,139,141,142,143,144,145,146,148,151,153,155,157,161,165,169,177,186,187,188,189,190,192,193,194,203,208,209,210,211,212,213,215,216,227,230,240,255,259,260,263,],[-50,77,-72,-55,-71,-53,77,77,-74,-61,77,-59,-70,-64,-99,-98,77,-66,-51,-65,-58,-54,-73,-57,-52,-62,-63,-67,-56,77,-60,-41,77,-48,-45,-76,77,129,77,-38,-68,-69,-48,77,77,-79,-96,-94,77,77,77,77,77,77,-47,-33,77,77,-36,77,-32,-35,-34,-30,-31,-46,77,77,77,77,-75,77,77,-77,77,-78,77,77,-115,-95,77,77,-49,129,-39,-40,-37,-42,-43,-44,77,-116,77,77,-105,-100,77,-97,77,77,77,77,77,77,77,77,]),'*':([2,8,9,16,17,22,23,29,31,33,34,37,40,41,44,45,47,49,52,53,55,57,59,60,64,71,73,75,76,82,88,89,92,105,107,108,126,138,144,148,153,161,165,186,188,189,192,193,194,208,211,212,215,],[-50,-72,-55,-71,-53,-74,-61,-59,-70,-64,-99,-98,-66,-51,-65,-58,-54,-73,-57,-52,-62,-63,-67,-56,-60,-41,-48,-45,-76,141,-68,-69,-48,-79,-96,-94,-47,-46,-75,-77,-78,-115,-95,-49,141,141,-42,-43,-44,-116,-105,-100,-97,]),']':([2,8,9,16,17,22,23,29,31,33,34,37,38,40,41,44,45,47,49,52,53,55,57,59,60,64,71,73,74,75,76,78,80,82,83,84,86,88,89,92,93,100,103,104,105,106,107,108,123,126,138,140,144,148,153,154,156,158,161,165,166,167,168,169,170,171,172,173,174,181,186,187,188,189,191,192,193,194,195,196,204,208,211,212,213,214,215,216,228,232,233,234,235,236,245,246,256,257,258,266,267,270,271,],[-50,-72,-55,-71,-53,-74,-61,-59,-70,-64,-99,-98,105,-66,-51,-65,-58,-54,-73,-57,-52,-62,-63,-67,-56,-60,-41,-19,-24,-45,-76,-28,-22,-38,-26,-125,-18,-68,-69,-48,105,-19,153,154,-79,-84,-96,-94,-27,-47,-46,-20,-75,-77,-78,-21,-80,-81,-115,-95,211,212,-110,-101,-112,-109,215,-106,-16,-126,-49,-29,-39,-40,-25,-42,-43,-44,-17,-23,-82,-116,-105,-100,-113,-103,-97,-104,-83,-111,-107,-108,-114,-102,-85,-87,-86,-91,-90,-88,-92,-89,-93,]),'SHORTSTRING':([0,2,3,4,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,26,27,28,29,30,31,32,33,34,35,37,38,39,40,41,43,44,45,47,48,49,50,51,52,53,55,56,57,59,60,61,62,64,65,66,67,68,69,71,72,74,75,76,77,78,79,80,82,83,84,86,87,88,89,90,91,92,93,94,95,97,99,100,105,107,108,109,111,113,114,116,117,118,119,120,121,123,124,125,126,127,128,129,130,131,132,133,135,136,137,138,139,140,141,142,143,144,145,146,148,149,151,153,154,155,157,161,165,169,176,177,178,179,180,181,182,183,184,185,186,187,188,189,190,191,192,193,194,195,196,197,198,199,203,205,208,209,210,211,212,213,215,216,217,220,221,223,224,227,230,237,238,239,240,241,242,250,252,255,259,260,262,263,264,269,],[31,-50,-134,31,31,-14,-72,-55,88,31,31,-129,-6,-130,-71,-53,-128,31,31,-127,-74,-61,-131,-11,-10,31,-59,31,-70,-9,-64,-99,-5,-98,31,-132,-66,-51,-133,-65,-58,-54,-2,-73,-12,31,-57,-52,-62,-13,-63,-67,-56,31,-4,-60,-149,-137,-138,31,-140,-41,31,-24,-45,-76,31,-28,31,-22,-38,-26,-125,-18,-16,-68,-69,-3,-145,-48,31,31,31,31,-15,-19,-79,-96,-94,31,31,-152,31,31,31,31,31,31,-142,-27,31,31,-47,-33,31,31,-36,31,-32,-35,-34,-30,-31,-46,31,-20,31,31,31,-75,31,31,-77,-136,31,-78,-21,31,31,-115,-95,31,-120,31,-135,-7,-124,-126,-139,-143,-141,-153,-49,-29,-39,-40,-37,-25,-42,-43,-44,-17,-23,31,-146,31,31,-121,-116,31,31,-105,-100,31,-97,31,31,-8,-154,-144,31,31,31,31,31,31,31,-147,-158,31,-150,31,31,31,-155,31,-148,-151,]),'/':([2,8,9,16,17,22,23,29,31,33,34,37,40,41,44,45,47,49,52,53,55,57,59,60,64,71,73,75,76,82,88,89,92,105,107,108,126,138,144,148,153,161,165,186,188,189,192,193,194,208,211,212,215,],[-50,-72,-55,-71,-53,-74,-61,-59,-70,-64,-99,-98,-66,-51,-65,-58,-54,-73,-57,-52,-62,-63,-67,-56,-60,-41,-48,-45,-76,142,-68,-69,-48,-79,-96,-94,-47,-46,-75,-77,-78,-115,-95,-49,142,142,-42,-43,-44,-116,-105,-100,-97,]),'NEXT':([0,2,3,4,7,8,9,11,12,13,14,15,16,17,18,21,22,23,24,26,27,29,31,32,33,34,35,37,39,40,41,43,44,45,47,48,49,50,51,52,53,55,56,57,59,60,62,64,65,66,67,68,69,71,74,75,76,78,80,82,83,84,86,87,88,89,90,91,92,95,97,99,100,105,107,108,113,116,117,120,121,123,126,138,140,144,148,149,153,154,161,165,176,178,179,180,181,182,183,184,185,186,187,188,189,191,192,193,194,195,196,197,198,199,205,208,211,212,215,220,221,223,224,237,239,241,242,250,252,262,264,269,],[7,-50,-134,7,-14,-72,-55,7,7,-129,-6,-130,-71,-53,-128,-127,-74,-61,-131,-11,-10,-59,-70,-9,-64,-99,-5,-98,-132,-66,-51,-133,-65,-58,-54,-2,-73,-12,7,-57,-52,-62,-13,-63,-67,-56,-4,-60,-149,-137,-138,7,-140,-41,-24,-45,-76,-28,-22,-38,-26,-125,-18,-16,-68,-69,-3,-145,-48,7,7,-15,-19,-79,-96,-94,-152,7,7,7,-142,-27,-47,-46,-20,-75,-77,-136,-78,-21,-115,-95,-120,-135,-7,-124,-126,-139,-143,-141,-153,-49,-29,-39,-40,-25,-42,-43,-44,-17,-23,7,-146,7,-121,-116,-105,-100,-97,-8,-154,-144,7,7,7,-147,-158,7,-150,-155,-148,-151,]),'SWITCH':([0,2,3,4,7,8,9,11,12,13,14,15,16,17,18,21,22,23,24,26,27,29,31,32,33,34,35,37,39,40,41,43,44,45,47,48,49,50,51,52,53,55,56,57,59,60,62,64,65,66,67,68,69,71,74,75,76,78,80,82,83,84,86,87,88,89,90,91,92,95,97,99,100,105,107,108,113,116,120,121,123,126,138,140,144,148,149,153,154,161,165,176,178,179,180,181,182,183,184,185,186,187,188,189,191,192,193,194,195,196,197,198,199,205,208,211,212,215,220,221,223,224,237,239,241,242,250,252,262,264,269,],[46,-50,-134,46,-14,-72,-55,46,46,-129,-6,-130,-71,-53,-128,-127,-74,-61,-131,-11,-10,-59,-70,-9,-64,-99,-5,-98,-132,-66,-51,-133,-65,-58,-54,-2,-73,-12,46,-57,-52,-62,-13,-63,-67,-56,-4,-60,-149,-137,-138,46,-140,-41,-24,-45,-76,-28,-22,-38,-26,-125,-18,-16,-68,-69,-3,-145,-48,46,46,-15,-19,-79,-96,-94,-152,46,46,-142,-27,-47,-46,-20,-75,-77,-136,-78,-21,-115,-95,-120,-135,-7,-124,-126,-139,-143,-141,-153,-49,-29,-39,-40,-25,-42,-43,-44,-17,-23,46,-146,46,-121,-116,-105,-100,-97,-8,-154,-144,46,46,46,-147,-158,46,-150,-155,-148,-151,]),'OCTINT':([0,2,3,4,6,7,8,9,11,12,13,14,15,16,17,18,19,20,21,22,23,24,26,27,28,29,30,31,32,33,34,35,37,38,39,40,41,43,44,45,47,48,49,50,51,52,53,55,56,57,59,60,61,62,64,65,66,67,68,69,71,72,74,75,76,77,78,79,80,82,83,84,86,87,88,89,90,91,92,93,94,95,97,99,100,105,107,108,109,111,113,114,116,117,118,119,120,121,123,124,125,126,127,128,129,130,131,132,133,135,136,137,138,139,140,141,142,143,144,145,146,148,149,151,153,154,155,157,161,165,169,176,177,178,179,180,181,182,183,184,185,186,187,188,189,190,191,192,193,194,195,196,197,198,199,203,205,208,209,210,211,212,213,215,216,217,220,221,223,224,227,230,237,238,239,240,241,242,250,252,255,259,260,262,263,264,269,],[33,-50,-134,33,33,-14,-72,-55,33,33,-129,-6,-130,-71,-53,-128,33,33,-127,-74,-61,-131,-11,-10,33,-59,33,-70,-9,-64,-99,-5,-98,33,-132,-66,-51,-133,-65,-58,-54,-2,-73,-12,33,-57,-52,-62,-13,-63,-67,-56,33,-4,-60,-149,-137,-138,33,-140,-41,33,-24,-45,-76,33,-28,33,-22,-38,-26,-125,-18,-16,-68,-69,-3,-145,-48,33,33,33,33,-15,-19,-79,-96,-94,33,33,-152,33,33,33,33,33,33,-142,-27,33,33,-47,-33,33,33,-36,33,-32,-35,-34,-30,-31,-46,33,-20,33,33,33,-75,33,33,-77,-136,33,-78,-21,33,33,-115,-95,33,-120,33,-135,-7,-124,-126,-139,-143,-141,-153,-49,-29,-39,-40,-37,-25,-42,-43,-44,-17,-23,33,-146,33,33,-121,-116,33,33,-105,-100,33,-97,33,33,-8,-154,-144,33,33,33,33,33,33,33,-147,-158,33,-150,33,33,33,-155,33,-148,-151,]),'STRPREFIX':([0,2,3,4,6,7,8,9,11,12,13,14,15,16,17,18,19,20,21,22,23,24,26,27,28,29,30,31,32,33,34,35,37,38,39,40,41,43,44,45,47,48,49,50,51,52,53,55,56,57,59,60,61,62,64,65,66,67,68,69,71,72,74,75,76,77,78,79,80,82,83,84,86,87,88,89,90,91,92,93,94,95,97,99,100,105,107,108,109,111,113,114,116,117,118,119,120,121,123,124,125,126,127,128,129,130,131,132,133,135,136,137,138,139,140,141,142,143,144,145,146,148,149,151,153,154,155,157,161,165,169,176,177,178,179,180,181,182,183,184,185,186,187,188,189,190,191,192,193,194,195,196,197,198,199,203,205,208,209,210,211,212,213,215,216,217,220,221,223,224,227,230,237,238,239,240,241,242,250,252,255,259,260,262,263,264,269,],[10,-50,-134,10,10,-14,-72,-55,10,10,-129,-6,-130,-71,-53,-128,10,10,-127,-74,-61,-131,-11,-10,10,-59,10,-70,-9,-64,-99,-5,-98,10,-132,-66,-51,-133,-65,-58,-54,-2,-73,-12,10,-57,-52,-62,-13,-63,-67,-56,10,-4,-60,-149,-137,-138,10,-140,-41,10,-24,-45,-76,10,-28,10,-22,-38,-26,-125,-18,-16,-68,-69,-3,-145,-48,10,10,10,10,-15,-19,-79,-96,-94,10,10,-152,10,10,10,10,10,10,-142,-27,10,10,-47,-33,10,10,-36,10,-32,-35,-34,-30,-31,-46,10,-20,10,10,10,-75,10,10,-77,-136,10,-78,-21,10,10,-115,-95,10,-120,10,-135,-7,-124,-126,-139,-143,-141,-153,-49,-29,-39,-40,-37,-25,-42,-43,-44,-17,-23,10,-146,10,10,-121,-116,10,10,-105,-100,10,-97,10,10,-8,-154,-144,10,10,10,10,10,10,10,-147,-158,10,-150,10,10,10,-155,10,-148,-151,]),'INTEGER':([0,2,3,4,6,7,8,9,11,12,13,14,15,16,17,18,19,20,21,22,23,24,26,27,28,29,30,31,32,33,34,35,37,38,39,40,41,43,44,45,47,48,49,50,51,52,53,55,56,57,59,60,61,62,64,65,66,67,68,69,71,72,74,75,76,77,78,79,80,82,83,84,86,87,88,89,90,91,92,93,94,95,97,99,100,105,107,108,109,111,113,114,116,117,118,119,120,121,123,124,125,126,127,128,129,130,131,132,133,135,136,137,138,139,140,141,142,143,144,145,146,148,149,151,153,154,155,157,161,165,169,176,177,178,179,180,181,182,183,184,185,186,187,188,189,190,191,192,193,194,195,196,197,198,199,203,205,208,209,210,211,212,213,215,216,217,220,221,223,224,227,230,237,238,239,240,241,242,250,252,255,259,260,262,263,264,269,],[55,-50,-134,55,55,-14,-72,-55,55,55,-129,-6,-130,-71,-53,-128,55,55,-127,-74,-61,-131,-11,-10,55,-59,55,-70,-9,-64,-99,-5,-98,55,-132,-66,-51,-133,-65,-58,-54,-2,-73,-12,55,-57,-52,-62,-13,-63,-67,-56,55,-4,-60,-149,-137,-138,55,-140,-41,55,-24,-45,-76,55,-28,55,-22,-38,-26,-125,-18,-16,-68,-69,-3,-145,-48,55,55,55,55,-15,-19,-79,-96,-94,55,55,-152,55,55,55,55,55,55,-142,-27,55,55,-47,-33,55,55,-36,55,-32,-35,-34,-30,-31,-46,55,-20,55,55,55,-75,55,55,-77,-136,55,-78,-21,55,55,-115,-95,55,-120,55,-135,-7,-124,-126,-139,-143,-141,-153,-49,-29,-39,-40,-37,-25,-42,-43,-44,-17,-23,55,-146,55,55,-121,-116,55,55,-105,-100,55,-97,55,55,-8,-154,-144,55,55,55,55,55,55,55,-147,-158,55,-150,55,55,55,-155,55,-148,-151,]),'IMAGINARY':([0,2,3,4,6,7,8,9,11,12,13,14,15,16,17,18,19,20,21,22,23,24,26,27,28,29,30,31,32,33,34,35,37,38,39,40,41,43,44,45,47,48,49,50,51,52,53,55,56,57,59,60,61,62,64,65,66,67,68,69,71,72,74,75,76,77,78,79,80,82,83,84,86,87,88,89,90,91,92,93,94,95,97,99,100,105,107,108,109,111,113,114,116,117,118,119,120,121,123,124,125,126,127,128,129,130,131,132,133,135,136,137,138,139,140,141,142,143,144,145,146,148,149,151,153,154,155,157,161,165,169,176,177,178,179,180,181,182,183,184,185,186,187,188,189,190,191,192,193,194,195,196,197,198,199,203,205,208,209,210,211,212,213,215,216,217,220,221,223,224,227,230,237,238,239,240,241,242,250,252,255,259,260,262,263,264,269,],[59,-50,-134,59,59,-14,-72,-55,59,59,-129,-6,-130,-71,-53,-128,59,59,-127,-74,-61,-131,-11,-10,59,-59,59,-70,-9,-64,-99,-5,-98,59,-132,-66,-51,-133,-65,-58,-54,-2,-73,-12,59,-57,-52,-62,-13,-63,-67,-56,59,-4,-60,-149,-137,-138,59,-140,-41,59,-24,-45,-76,59,-28,59,-22,-38,-26,-125,-18,-16,-68,-69,-3,-145,-48,59,59,59,59,-15,-19,-79,-96,-94,59,59,-152,59,59,59,59,59,59,-142,-27,59,59,-47,-33,59,59,-36,59,-32,-35,-34,-30,-31,-46,59,-20,59,59,59,-75,59,59,-77,-136,59,-78,-21,59,59,-115,-95,59,-120,59,-135,-7,-124,-126,-139,-143,-141,-153,-49,-29,-39,-40,-37,-25,-42,-43,-44,-17,-23,59,-146,59,59,-121,-116,59,59,-105,-100,59,-97,59,59,-8,-154,-144,59,59,59,59,59,59,59,-147,-158,59,-150,59,59,59,-155,59,-148,-151,]),'^':([2,8,9,16,17,22,23,29,31,33,34,37,40,41,44,45,47,49,52,53,55,57,59,60,64,71,73,75,76,82,88,89,92,105,107,108,126,138,144,148,153,161,165,186,188,189,192,193,194,208,211,212,215,],[-50,-72,-55,-71,-53,-74,-61,-59,-70,-64,-99,-98,-66,-51,-65,-58,-54,-73,-57,-52,-62,-63,-67,-56,-60,-41,-48,-45,-76,143,-68,-69,-48,-79,-96,-94,-47,-46,-75,-77,-78,-115,-95,-49,143,143,-42,-43,-44,-116,-105,-100,-97,]),'=':([2,8,9,16,17,22,23,29,31,33,34,37,40,41,42,44,45,47,49,52,53,54,55,57,59,60,63,64,76,88,89,100,105,107,108,115,140,144,148,153,154,161,165,181,207,208,211,212,215,247,],[-50,-72,-55,-71,-53,-74,-61,-59,-70,-64,-99,-98,-66,-51,-19,-65,-58,-54,-73,-57,-52,-125,-62,-63,-67,-56,118,-60,-76,-68,-69,-19,-79,-96,-94,177,-20,-75,-77,-78,-21,-115,-95,-126,230,-116,-105,-100,-97,260,]),'<':([2,8,9,16,17,22,23,29,31,33,34,37,40,41,44,45,47,49,52,53,55,57,59,60,64,71,73,75,76,78,82,88,89,92,105,107,108,126,138,144,148,153,161,165,186,188,189,192,193,194,208,211,212,215,241,],[-50,-72,-55,-71,-53,-74,-61,-59,-70,-64,-99,-98,-66,-51,-65,-58,-54,-73,-57,-52,-62,-63,-67,-56,-60,-41,-48,-45,-76,136,-38,-68,-69,-48,-79,-96,-94,-47,-46,-75,-77,-78,-115,-95,-49,-39,-40,-42,-43,-44,-116,-105,-100,-97,136,]),'$end':([1,2,3,7,8,9,11,13,14,15,16,17,18,21,22,23,24,26,27,29,31,32,33,34,35,37,39,40,41,43,44,45,47,48,49,50,52,53,55,56,57,59,60,62,64,65,66,67,71,74,75,76,78,80,82,83,86,87,88,89,90,91,92,99,105,107,108,113,123,126,138,144,148,149,153,161,165,176,178,179,180,182,184,186,187,188,189,191,192,193,194,195,196,205,208,211,212,215,220,221,223,242,262,],[0,-50,-134,-14,-72,-55,-1,-129,-6,-130,-71,-53,-128,-127,-74,-61,-131,-11,-10,-59,-70,-9,-64,-99,-5,-98,-132,-66,-51,-133,-65,-58,-54,-2,-73,-12,-57,-52,-62,-13,-63,-67,-56,-4,-60,-149,-137,-138,-41,-24,-45,-76,-28,-22,-38,-26,-18,-16,-68,-69,-3,-145,-48,-15,-79,-96,-94,-152,-27,-47,-46,-75,-77,-136,-78,-115,-95,-120,-135,-7,-124,-139,-141,-49,-29,-39,-40,-25,-42,-43,-44,-17,-23,-121,-116,-105,-100,-97,-8,-154,-144,-158,-155,]),'FUNCTION':([0,2,3,4,7,8,9,11,12,13,14,15,16,17,18,21,22,23,24,26,27,29,31,32,33,34,35,37,39,40,41,43,44,45,47,48,49,50,51,52,53,55,56,57,59,60,62,64,65,66,67,68,69,71,74,75,76,78,80,82,83,84,86,87,88,89,90,91,92,95,97,99,100,105,107,108,113,116,120,121,123,126,138,140,144,148,149,153,154,161,165,176,178,179,180,181,182,183,184,185,186,187,188,189,191,192,193,194,195,196,197,198,199,205,208,211,212,215,220,221,223,224,237,239,241,242,250,252,262,264,269,],[36,-50,-134,36,-14,-72,-55,36,36,-129,-6,-130,-71,-53,-128,-127,-74,-61,-131,-11,-10,-59,-70,-9,-64,-99,-5,-98,-132,-66,-51,-133,-65,-58,-54,-2,-73,-12,36,-57,-52,-62,-13,-63,-67,-56,-4,-60,-149,-137,-138,36,-140,-41,-24,-45,-76,-28,-22,-38,-26,-125,-18,-16,-68,-69,-3,-145,-48,36,36,-15,-19,-79,-96,-94,-152,36,36,-142,-27,-47,-46,-20,-75,-77,-136,-78,-21,-115,-95,-120,-135,-7,-124,-126,-139,-143,-141,-153,-49,-29,-39,-40,-25,-42,-43,-44,-17,-23,36,-146,36,-121,-116,-105,-100,-97,-8,-154,-144,36,36,36,-147,-158,36,-150,-155,-148,-151,]),'GTE':([2,8,9,16,17,22,23,29,31,33,34,37,40,41,44,45,47,49,52,53,55,57,59,60,64,71,73,75,76,78,82,88,89,92,105,107,108,126,138,144,148,153,161,165,186,188,189,192,193,194,208,211,212,215,241,],[-50,-72,-55,-71,-53,-74,-61,-59,-70,-64,-99,-98,-66,-51,-65,-58,-54,-73,-57,-52,-62,-63,-67,-56,-60,-41,-48,-45,-76,132,-38,-68,-69,-48,-79,-96,-94,-47,-46,-75,-77,-78,-115,-95,-49,-39,-40,-42,-43,-44,-116,-105,-100,-97,132,]),'FOR':([0,2,3,4,7,8,9,11,12,13,14,15,16,17,18,21,22,23,24,26,27,29,31,32,33,34,35,37,39,40,41,43,44,45,47,48,49,50,51,52,53,55,56,57,59,60,62,64,65,66,67,68,69,71,73,74,75,76,78,80,82,83,84,86,87,88,89,90,91,92,95,97,99,100,105,106,107,108,113,116,120,121,123,126,138,140,144,148,149,153,154,161,165,176,178,179,180,181,182,183,184,185,186,187,188,189,191,192,193,194,195,196,197,198,199,205,208,211,212,215,220,221,223,224,237,239,241,242,245,246,250,252,262,264,266,267,269,270,],[30,-50,-134,30,-14,-72,-55,30,30,-129,-6,-130,-71,-53,-128,-127,-74,-61,-131,-11,-10,-59,-70,-9,-64,-99,-5,-98,-132,-66,-51,-133,-65,-58,-54,-2,-73,-12,30,-57,-52,-62,-13,-63,-67,-56,-4,-60,-149,-137,-138,30,-140,-41,-48,-24,-45,-76,-28,-22,-38,-26,-125,-18,-16,-68,-69,-3,-145,-48,30,30,-15,-19,-79,155,-96,-94,-152,30,30,-142,-27,-47,-46,-20,-75,-77,-136,-78,-21,-115,-95,-120,-135,-7,-124,-126,-139,-143,-141,-153,-49,-29,-39,-40,-25,-42,-43,-44,-17,-23,30,-146,30,-121,-116,-105,-100,-97,-8,-154,-144,30,30,30,-147,-158,155,-87,30,-150,-155,-148,-88,155,-151,-89,]),'LONGSTRING':([0,2,3,4,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,26,27,28,29,30,31,32,33,34,35,37,38,39,40,41,43,44,45,47,48,49,50,51,52,53,55,56,57,59,60,61,62,64,65,66,67,68,69,71,72,74,75,76,77,78,79,80,82,83,84,86,87,88,89,90,91,92,93,94,95,97,99,100,105,107,108,109,111,113,114,116,117,118,119,120,121,123,124,125,126,127,128,129,130,131,132,133,135,136,137,138,139,140,141,142,143,144,145,146,148,149,151,153,154,155,157,161,165,169,176,177,178,179,180,181,182,183,184,185,186,187,188,189,190,191,192,193,194,195,196,197,198,199,203,205,208,209,210,211,212,213,215,216,217,220,221,223,224,227,230,237,238,239,240,241,242,250,252,255,259,260,262,263,264,269,],[16,-50,-134,16,16,-14,-72,-55,89,16,16,-129,-6,-130,-71,-53,-128,16,16,-127,-74,-61,-131,-11,-10,16,-59,16,-70,-9,-64,-99,-5,-98,16,-132,-66,-51,-133,-65,-58,-54,-2,-73,-12,16,-57,-52,-62,-13,-63,-67,-56,16,-4,-60,-149,-137,-138,16,-140,-41,16,-24,-45,-76,16,-28,16,-22,-38,-26,-125,-18,-16,-68,-69,-3,-145,-48,16,16,16,16,-15,-19,-79,-96,-94,16,16,-152,16,16,16,16,16,16,-142,-27,16,16,-47,-33,16,16,-36,16,-32,-35,-34,-30,-31,-46,16,-20,16,16,16,-75,16,16,-77,-136,16,-78,-21,16,16,-115,-95,16,-120,16,-135,-7,-124,-126,-139,-143,-141,-153,-49,-29,-39,-40,-37,-25,-42,-43,-44,-17,-23,16,-146,16,16,-121,-116,16,16,-105,-100,16,-97,16,16,-8,-154,-144,16,16,16,16,16,16,16,-147,-158,16,-150,16,16,16,-155,16,-148,-151,]),'NOT':([2,6,8,9,16,17,19,20,22,23,28,29,31,33,34,37,38,40,41,44,45,47,49,52,53,55,57,59,60,61,64,71,72,73,75,76,78,82,88,89,92,93,94,105,107,108,109,111,114,118,125,126,138,139,144,145,146,148,151,153,155,157,161,165,169,177,186,188,189,192,193,194,203,208,209,210,211,212,213,215,216,227,230,240,241,255,259,260,263,],[-50,72,-72,-55,-71,-53,72,72,-74,-61,72,-59,-70,-64,-99,-98,72,-66,-51,-65,-58,-54,-73,-57,-52,-62,-63,-67,-56,72,-60,-41,72,-48,-45,-76,134,-38,-68,-69,-48,72,72,-79,-96,-94,72,72,72,72,72,-47,-46,72,-75,72,72,-77,72,-78,72,72,-115,-95,72,72,-49,-39,-40,-42,-43,-44,72,-116,72,72,-105,-100,72,-97,72,72,72,72,134,72,72,72,72,]),'AS':([70,98,],[122,150,]),'LTE':([2,8,9,16,17,22,23,29,31,33,34,37,40,41,44,45,47,49,52,53,55,57,59,60,64,71,73,75,76,78,82,88,89,92,105,107,108,126,138,144,148,153,161,165,186,188,189,192,193,194,208,211,212,215,241,],[-50,-72,-55,-71,-53,-74,-61,-59,-70,-64,-99,-98,-66,-51,-65,-58,-54,-73,-57,-52,-62,-63,-67,-56,-60,-41,-48,-45,-76,127,-38,-68,-69,-48,-79,-96,-94,-47,-46,-75,-77,-78,-115,-95,-49,-39,-40,-42,-43,-44,-116,-105,-100,-97,127,]),'IN':([2,8,9,16,17,22,23,29,31,33,34,37,40,41,44,45,47,49,52,53,55,57,59,60,64,71,73,74,75,76,78,80,82,83,84,86,87,88,89,92,100,101,105,107,108,123,126,134,138,140,144,148,153,154,161,165,181,186,187,188,189,191,192,193,194,195,196,202,208,211,212,215,241,],[-50,-72,-55,-71,-53,-74,-61,-59,-70,-64,-99,-98,-66,-51,-65,-58,-54,-73,-57,-52,-62,-63,-67,-56,-60,-41,-48,-24,-45,-76,130,-22,-38,-26,-125,-18,-16,-68,-69,-48,-19,151,-79,-96,-94,-27,-47,190,-46,-20,-75,-77,-78,-21,-115,-95,-126,-49,-29,-39,-40,-25,-42,-43,-44,-17,-23,227,-116,-105,-100,-97,130,]),'[':([0,2,3,4,6,7,8,9,11,12,13,14,15,16,17,18,19,20,21,22,23,24,26,27,28,29,30,31,32,33,34,35,37,38,39,40,41,42,43,44,45,47,48,49,50,51,52,53,55,56,57,59,60,61,62,64,65,66,67,68,69,71,72,73,74,75,76,77,78,79,80,82,83,84,86,87,88,89,90,91,92,93,94,95,97,99,100,105,107,108,109,111,113,114,116,117,118,119,120,121,123,124,125,126,127,128,129,130,131,132,133,135,136,137,138,139,140,141,142,143,144,145,146,148,149,151,153,154,155,157,161,165,169,176,177,178,179,180,181,182,183,184,185,186,187,188,189,190,191,192,193,194,195,196,197,198,199,203,205,208,209,210,211,212,213,215,216,217,220,221,223,224,226,227,230,237,238,239,240,241,242,250,252,254,255,259,260,262,263,264,269,],[38,-50,-134,38,38,-14,-72,-55,38,38,-129,-6,-130,-71,-53,-128,93,93,-127,-74,-61,-131,-11,-10,93,-59,38,-70,-9,-64,-99,-5,-98,38,-132,-66,-51,111,-133,-65,-58,-54,-2,-73,-12,38,-57,-52,-62,-13,-63,-67,-56,93,-4,-60,-149,-137,-138,38,-140,-41,93,111,-24,-45,-76,93,-28,93,-22,-38,-26,-125,-18,-16,-68,-69,-3,-145,111,93,93,38,38,-15,111,-79,-96,-94,93,93,-152,93,38,38,93,38,38,-142,-27,93,93,-47,-33,93,93,-36,93,-32,-35,-34,-30,-31,-46,93,-20,93,93,93,-75,93,93,-77,-136,93,-78,-21,93,93,-115,-95,93,-120,93,-135,-7,-124,-126,-139,-143,-141,-153,-49,-29,-39,-40,-37,-25,-42,-43,-44,-17,-23,38,-146,38,93,-121,-116,93,93,-105,-100,93,-97,93,38,-8,-154,-144,38,93,93,93,38,38,38,93,-147,-158,38,-150,93,93,93,93,-155,93,-148,-151,]),'ELSE':([2,3,7,8,9,13,15,16,17,18,21,22,23,24,26,27,29,31,32,33,34,37,39,40,41,43,44,45,47,49,50,52,53,55,56,57,59,60,64,65,66,67,71,74,75,76,78,80,82,83,86,87,88,89,91,92,99,105,107,108,113,123,126,138,144,147,148,149,153,161,165,176,178,180,182,184,186,187,188,189,191,192,193,194,195,196,205,208,211,212,215,221,223,242,262,],[-50,-134,-14,-72,-55,-129,-130,-71,-53,-128,97,-74,-61,-131,-11,-10,-59,-70,-9,-64,-99,-98,-132,-66,-51,-133,-65,-58,-54,-73,-12,-57,-52,-62,-13,-63,-67,-56,-60,-149,-137,-138,-41,-24,-45,-76,-28,-22,-38,-26,-18,-16,-68,-69,-145,-48,-15,-79,-96,-94,-152,-27,-47,-46,-75,197,-77,-136,-78,-115,-95,-120,-135,-124,-139,-141,-49,-29,-39,-40,-25,-42,-43,-44,-17,-23,-121,-116,-105,-100,-97,-154,-144,-158,-155,]),'WHERE':([0,2,3,4,7,8,9,11,12,13,14,15,16,17,18,21,22,23,24,26,27,29,31,32,33,34,35,37,39,40,41,43,44,45,47,48,49,50,51,52,53,55,56,57,59,60,62,64,65,66,67,68,69,71,74,75,76,78,80,82,83,84,86,87,88,89,90,91,92,95,97,99,100,105,107,108,113,116,120,121,123,126,138,140,144,148,149,153,154,161,165,176,178,179,180,181,182,183,184,185,186,187,188,189,191,192,193,194,195,196,197,198,199,205,208,211,212,215,220,221,223,224,237,239,241,242,250,252,262,264,269,],[19,-50,-134,19,-14,-72,-55,19,19,-129,-6,-130,-71,-53,-128,-127,-74,-61,-131,-11,-10,-59,-70,-9,-64,-99,-5,-98,-132,-66,-51,-133,-65,-58,-54,-2,-73,-12,19,-57,-52,-62,-13,-63,-67,-56,-4,-60,-149,-137,-138,19,-140,-41,-24,-45,-76,-28,-22,-38,-26,-125,-18,-16,-68,-69,-3,-145,-48,19,19,-15,-19,-79,-96,-94,-152,19,19,-142,-27,-47,-46,-20,-75,-77,-136,-78,-21,-115,-95,-120,-135,-7,-124,-126,-139,-143,-141,-153,-49,-29,-39,-40,-25,-42,-43,-44,-17,-23,19,-146,19,-121,-116,-105,-100,-97,-8,-154,-144,19,19,19,-147,-158,19,-150,-155,-148,-151,]),'ID':([0,2,3,4,5,6,7,8,9,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,43,44,45,46,47,48,49,50,51,52,53,55,56,57,58,59,60,61,62,64,65,66,67,68,69,71,72,74,75,76,77,78,79,80,82,83,84,86,87,88,89,90,91,92,93,94,95,97,99,100,105,107,108,109,110,111,113,114,116,117,118,119,120,121,122,123,124,125,126,127,128,129,130,131,132,133,135,136,137,138,139,140,141,142,143,144,145,146,148,149,150,151,152,153,154,155,157,161,162,165,169,176,177,178,179,180,181,182,183,184,185,186,187,188,189,190,191,192,193,194,195,196,197,198,199,203,205,208,209,210,211,212,213,215,216,217,220,221,222,223,224,225,227,229,230,237,238,239,240,241,242,250,252,253,255,259,260,262,263,264,269,],[60,-50,-134,60,70,60,-14,-72,-55,60,60,-129,-6,-130,-71,-53,-128,60,60,-127,-74,-61,-131,98,-11,-10,60,-59,60,-70,-9,-64,-99,-5,102,-98,60,-132,-66,-51,-133,-65,-58,112,-54,-2,-73,-12,60,-57,-52,-62,-13,-63,115,-67,-56,60,-4,-60,-149,-137,-138,60,-140,-41,60,-24,-45,-76,60,-28,60,-22,-38,-26,-125,-18,-16,-68,-69,-3,-145,-48,60,60,60,60,-15,-19,-79,-96,-94,60,165,60,-152,60,60,60,60,60,60,-142,185,-27,60,60,-47,-33,60,60,-36,60,-32,-35,-34,-30,-31,-46,60,-20,60,60,60,-75,60,60,-77,-136,198,60,201,-78,-21,60,60,-115,207,-95,60,-120,60,-135,-7,-124,-126,-139,-143,-141,-153,-49,-29,-39,-40,-37,-25,-42,-43,-44,-17,-23,60,-146,60,60,-121,-116,60,60,-105,-100,60,-97,60,60,-8,-154,241,-144,60,243,60,247,60,60,60,60,60,-147,-158,60,-150,264,60,60,60,-155,60,-148,-151,]),'IF':([0,2,3,4,7,8,9,11,12,13,14,15,16,17,18,21,22,23,24,26,27,29,31,32,33,34,35,37,39,40,41,43,44,45,47,48,49,50,51,52,53,55,56,57,59,60,62,64,65,66,67,68,69,71,74,75,76,78,80,82,83,84,86,87,88,89,90,91,92,95,97,99,100,105,107,108,113,116,120,121,123,126,138,140,144,148,149,153,154,161,165,176,178,179,180,181,182,183,184,185,186,187,188,189,191,192,193,194,195,196,197,198,199,205,208,211,212,215,220,221,223,224,237,239,241,242,245,246,250,252,262,264,266,267,269,270,],[61,-50,-134,61,-14,-72,-55,61,61,-129,-6,-130,-71,-53,-128,-127,-74,-61,-131,-11,-10,-59,-70,-9,-64,-99,-5,-98,-132,-66,-51,-133,-65,-58,-54,-2,-73,-12,61,-57,-52,-62,-13,-63,-67,-56,-4,-60,-149,-137,-138,61,-140,-41,-24,-45,-76,-28,-22,-38,-26,-125,-18,-16,-68,-69,-3,-145,-48,61,61,-15,-19,-79,-96,-94,-152,61,61,-142,-27,-47,-46,-20,-75,-77,-136,-78,-21,-115,-95,-120,-135,-7,-124,-126,-139,-143,-141,-153,-49,-29,-39,-40,-25,-42,-43,-44,-17,-23,61,-146,61,-121,-116,-105,-100,-97,-8,-154,-144,61,61,61,-147,-158,259,-87,61,-150,-155,-148,-88,259,-151,-89,]),'AND':([2,8,9,16,17,22,23,29,31,33,34,37,40,41,44,45,47,49,52,53,55,57,59,60,64,71,73,74,75,76,78,80,82,83,88,89,92,105,107,108,123,126,138,144,148,153,161,165,186,187,188,189,191,192,193,194,196,208,211,212,215,],[-50,-72,-55,-71,-53,-74,-61,-59,-70,-64,-99,-98,-66,-51,-65,-58,-54,-73,-57,-52,-62,-63,-67,-56,-60,-41,-48,-24,-45,-76,-28,139,-38,-26,-68,-69,-48,-79,-96,-94,-27,-47,-46,-75,-77,-78,-115,-95,-49,-29,-39,-40,-25,-42,-43,-44,139,-116,-105,-100,-97,]),'`':([0,2,3,4,6,7,8,9,11,12,13,14,15,16,17,18,19,20,21,22,23,24,26,27,28,29,30,31,32,33,34,35,37,38,39,40,41,43,44,45,47,48,49,50,51,52,53,55,56,57,59,60,61,62,64,65,66,67,68,69,71,72,74,75,76,77,78,79,80,82,83,84,86,87,88,89,90,91,92,93,94,95,96,97,99,100,105,107,108,109,111,113,114,116,117,118,119,120,121,123,124,125,126,127,128,129,130,131,132,133,135,136,137,138,139,140,141,142,143,144,145,146,148,149,151,153,154,155,157,161,165,169,176,177,178,179,180,181,182,183,184,185,186,187,188,189,190,191,192,193,194,195,196,197,198,199,203,205,208,209,210,211,212,213,215,216,217,220,221,223,224,227,230,237,238,239,240,241,242,250,252,255,259,260,262,263,264,269,],[20,-50,-134,20,20,-14,-72,-55,20,20,-129,-6,-130,-71,-53,-128,20,20,-127,-74,-61,-131,-11,-10,20,-59,20,-70,-9,-64,-99,-5,-98,20,-132,-66,-51,-133,-65,-58,-54,-2,-73,-12,20,-57,-52,-62,-13,-63,-67,-56,20,-4,-60,-149,-137,-138,20,-140,-41,20,-24,-45,-76,20,-28,20,-22,-38,-26,-125,-18,-16,-68,-69,-3,-145,-48,20,20,20,148,20,-15,-19,-79,-96,-94,20,20,-152,20,20,20,20,20,20,-142,-27,20,20,-47,-33,20,20,-36,20,-32,-35,-34,-30,-31,-46,20,-20,20,20,20,-75,20,20,-77,-136,20,-78,-21,20,20,-115,-95,20,-120,20,-135,-7,-124,-126,-139,-143,-141,-153,-49,-29,-39,-40,-37,-25,-42,-43,-44,-17,-23,20,-146,20,20,-121,-116,20,20,-105,-100,20,-97,20,20,-8,-154,-144,20,20,20,20,20,20,20,-147,-158,20,-150,20,20,20,-155,20,-148,-151,]),':':([2,8,9,16,17,22,23,29,31,33,34,37,40,41,44,45,47,49,52,53,55,57,59,60,64,71,74,75,76,78,80,82,83,86,88,89,92,105,107,108,111,123,126,138,144,148,153,161,165,167,169,174,186,187,188,189,191,192,193,194,196,198,201,208,210,211,212,214,215,216,232,234,236,243,],[-50,-72,-55,-71,-53,-74,-61,-59,-70,-64,-99,-98,-66,-51,-65,-58,-54,-73,-57,-52,-62,-63,-67,-56,-60,-41,-24,-45,-76,-28,-22,-38,-26,-18,-68,-69,-48,-79,-96,-94,169,-27,-47,-46,-75,-77,-78,-115,-95,213,-101,216,-49,-29,-39,-40,-25,-42,-43,-44,-23,222,226,-116,169,-105,-100,-103,-97,-104,213,216,-102,254,]),'ELLIPSIS':([111,210,],[168,168,]),'BREAK':([0,2,3,4,7,8,9,11,12,13,14,15,16,17,18,21,22,23,24,26,27,29,31,32,33,34,35,37,39,40,41,43,44,45,47,48,49,50,51,52,53,55,56,57,59,60,62,64,65,66,67,68,69,71,74,75,76,78,80,82,83,84,86,87,88,89,90,91,92,95,97,99,100,105,107,108,113,116,117,120,121,123,126,138,140,144,148,149,153,154,161,165,176,178,179,180,181,182,183,184,185,186,187,188,189,191,192,193,194,195,196,197,198,199,205,208,211,212,215,220,221,223,224,237,239,241,242,250,252,262,264,269,],[56,-50,-134,56,-14,-72,-55,56,56,-129,-6,-130,-71,-53,-128,-127,-74,-61,-131,-11,-10,-59,-70,-9,-64,-99,-5,-98,-132,-66,-51,-133,-65,-58,-54,-2,-73,-12,56,-57,-52,-62,-13,-63,-67,-56,-4,-60,-149,-137,-138,56,-140,-41,-24,-45,-76,-28,-22,-38,-26,-125,-18,-16,-68,-69,-3,-145,-48,56,56,-15,-19,-79,-96,-94,-152,56,56,56,-142,-27,-47,-46,-20,-75,-77,-136,-78,-21,-115,-95,-120,-135,-7,-124,-126,-139,-143,-141,-153,-49,-29,-39,-40,-25,-42,-43,-44,-17,-23,56,-146,56,-121,-116,-105,-100,-97,-8,-154,-144,56,56,56,-147,-158,56,-150,-155,-148,-151,]),'HEXINT':([0,2,3,4,6,7,8,9,11,12,13,14,15,16,17,18,19,20,21,22,23,24,26,27,28,29,30,31,32,33,34,35,37,38,39,40,41,43,44,45,47,48,49,50,51,52,53,55,56,57,59,60,61,62,64,65,66,67,68,69,71,72,74,75,76,77,78,79,80,82,83,84,86,87,88,89,90,91,92,93,94,95,97,99,100,105,107,108,109,111,113,114,116,117,118,119,120,121,123,124,125,126,127,128,129,130,131,132,133,135,136,137,138,139,140,141,142,143,144,145,146,148,149,151,153,154,155,157,161,165,169,176,177,178,179,180,181,182,183,184,185,186,187,188,189,190,191,192,193,194,195,196,197,198,199,203,205,208,209,210,211,212,213,215,216,217,220,221,223,224,227,230,237,238,239,240,241,242,250,252,255,259,260,262,263,264,269,],[57,-50,-134,57,57,-14,-72,-55,57,57,-129,-6,-130,-71,-53,-128,57,57,-127,-74,-61,-131,-11,-10,57,-59,57,-70,-9,-64,-99,-5,-98,57,-132,-66,-51,-133,-65,-58,-54,-2,-73,-12,57,-57,-52,-62,-13,-63,-67,-56,57,-4,-60,-149,-137,-138,57,-140,-41,57,-24,-45,-76,57,-28,57,-22,-38,-26,-125,-18,-16,-68,-69,-3,-145,-48,57,57,57,57,-15,-19,-79,-96,-94,57,57,-152,57,57,57,57,57,57,-142,-27,57,57,-47,-33,57,57,-36,57,-32,-35,-34,-30,-31,-46,57,-20,57,57,57,-75,57,57,-77,-136,57,-78,-21,57,57,-115,-95,57,-120,57,-135,-7,-124,-126,-139,-143,-141,-153,-49,-29,-39,-40,-37,-25,-42,-43,-44,-17,-23,57,-146,57,57,-121,-116,57,57,-105,-100,57,-97,57,57,-8,-154,-144,57,57,57,57,57,57,57,-147,-158,57,-150,57,57,57,-155,57,-148,-151,]),'ISEQUAL':([2,8,9,16,17,22,23,29,31,33,34,37,40,41,44,45,47,49,52,53,55,57,59,60,64,71,73,75,76,78,82,88,89,92,105,107,108,126,138,144,148,153,161,165,186,188,189,192,193,194,208,211,212,215,241,],[-50,-72,-55,-71,-53,-74,-61,-59,-70,-64,-99,-98,-66,-51,-65,-58,-54,-73,-57,-52,-62,-63,-67,-56,-60,-41,-48,-45,-76,133,-38,-68,-69,-48,-79,-96,-94,-47,-46,-75,-77,-78,-115,-95,-49,-39,-40,-42,-43,-44,-116,-105,-100,-97,133,]),'ITEM_TAG':([0,2,3,4,6,7,8,9,11,12,13,14,15,16,17,18,19,20,21,22,23,24,26,27,28,29,30,31,32,33,34,35,37,38,39,40,41,43,44,45,47,48,49,50,51,52,53,55,56,57,59,60,61,62,64,65,66,67,68,69,71,72,74,75,76,77,78,79,80,82,83,84,86,87,88,89,90,91,92,93,94,95,97,99,100,105,107,108,109,111,113,114,116,117,118,119,120,121,123,124,125,126,127,128,129,130,131,132,133,135,136,137,138,139,140,141,142,143,144,145,146,148,149,151,153,154,155,157,161,165,169,176,177,178,179,180,181,182,183,184,185,186,187,188,189,190,191,192,193,194,195,196,197,198,199,203,205,208,209,210,211,212,213,215,216,217,220,221,223,224,227,230,237,238,239,240,241,242,250,252,255,259,260,262,263,264,269,],[64,-50,-134,64,64,-14,-72,-55,64,64,-129,-6,-130,-71,-53,-128,64,64,-127,-74,-61,-131,-11,-10,64,-59,64,-70,-9,-64,-99,-5,-98,64,-132,-66,-51,-133,-65,-58,-54,-2,-73,-12,64,-57,-52,-62,-13,-63,-67,-56,64,-4,-60,-149,-137,-138,64,-140,-41,64,-24,-45,-76,64,-28,64,-22,-38,-26,-125,-18,-16,-68,-69,-3,-145,-48,64,64,64,64,-15,-19,-79,-96,-94,64,64,-152,64,64,64,64,64,64,-142,-27,64,64,-47,-33,64,64,-36,64,-32,-35,-34,-30,-31,-46,64,-20,64,64,64,-75,64,64,-77,-136,64,-78,-21,64,64,-115,-95,64,-120,64,-135,-7,-124,-126,-139,-143,-141,-153,-49,-29,-39,-40,-37,-25,-42,-43,-44,-17,-23,64,-146,64,64,-121,-116,64,64,-105,-100,64,-97,64,64,-8,-154,-144,64,64,64,64,64,64,64,-147,-158,64,-150,64,64,64,-155,64,-148,-151,]),'{':([2,4,8,9,12,16,17,22,23,29,31,33,34,37,40,41,44,45,47,49,51,52,53,55,57,59,60,64,71,74,75,76,78,80,82,83,84,86,87,88,89,92,95,97,100,105,107,108,112,116,123,126,138,140,144,148,153,154,161,165,181,185,186,187,188,189,191,192,193,194,195,196,197,198,199,208,211,212,215,224,237,239,241,250,252,264,269,],[-50,69,-72,-55,69,-71,-53,-74,-61,-59,-70,-64,-99,-98,-66,-51,-65,-58,-54,-73,69,-57,-52,-62,-63,-67,-56,-60,-41,-24,-45,-76,-28,-22,-38,-26,-125,-18,-16,-68,-69,-48,69,69,-19,-79,-96,-94,69,69,-27,-47,-46,-20,-75,-77,-78,-21,-115,-95,-126,-153,-49,-29,-39,-40,-25,-42,-43,-44,-17,-23,69,-146,69,-116,-105,-100,-97,69,69,69,-147,69,-150,-148,-151,]),'>':([2,8,9,16,17,22,23,29,31,33,34,37,40,41,44,45,47,49,52,53,55,57,59,60,64,71,73,75,76,78,82,88,89,92,105,107,108,126,138,144,148,153,161,165,186,188,189,192,193,194,208,211,212,215,241,],[-50,-72,-55,-71,-53,-74,-61,-59,-70,-64,-99,-98,-66,-51,-65,-58,-54,-73,-57,-52,-62,-63,-67,-56,-60,-41,-48,-45,-76,137,-38,-68,-69,-48,-79,-96,-94,-47,-46,-75,-77,-78,-115,-95,-49,-39,-40,-42,-43,-44,-116,-105,-100,-97,137,]),'}':([2,3,7,8,9,13,14,15,16,17,18,21,22,23,24,26,27,29,31,32,33,34,35,37,39,40,41,43,44,45,47,49,50,52,53,55,56,57,59,60,62,64,65,66,67,71,74,75,76,78,80,82,83,86,87,88,89,91,92,99,105,107,108,113,120,121,123,126,138,144,148,149,153,161,165,176,178,179,180,182,183,184,186,187,188,189,191,192,193,194,195,196,205,208,211,212,215,220,221,223,242,251,262,],[-50,-134,-14,-72,-55,-129,-6,-130,-71,-53,-128,-127,-74,-61,-131,-11,-10,-59,-70,-9,-64,-99,-5,-98,-132,-66,-51,-133,-65,-58,-54,-73,-12,-57,-52,-62,-13,-63,-67,-56,-4,-60,-149,-137,-138,-41,-24,-45,-76,-28,-22,-38,-26,-18,-16,-68,-69,-145,-48,-15,-79,-96,-94,-152,184,-142,-27,-47,-46,-75,-77,-136,-78,-115,-95,-120,-135,-7,-124,-139,-143,-141,-49,-29,-39,-40,-25,-42,-43,-44,-17,-23,-121,-116,-105,-100,-97,-8,-154,-144,-158,184,-155,]),'OR':([2,8,9,16,17,22,23,29,31,33,34,37,40,41,44,45,47,49,52,53,55,57,59,60,64,71,73,74,75,76,78,80,82,83,86,88,89,92,105,107,108,123,126,138,144,148,153,161,165,186,187,188,189,191,192,193,194,196,208,211,212,215,246,266,267,],[-50,-72,-55,-71,-53,-74,-61,-59,-70,-64,-99,-98,-66,-51,-65,-58,-54,-73,-57,-52,-62,-63,-67,-56,-60,-41,-48,-24,-45,-76,-28,-22,-38,-26,146,-68,-69,-48,-79,-96,-94,-27,-47,-46,-75,-77,-78,-115,-95,-49,-29,-39,-40,-25,-42,-43,-44,-23,-116,-105,-100,-97,146,146,146,]),'LOOP':([0,2,3,4,7,8,9,11,12,13,14,15,16,17,18,21,22,23,24,26,27,29,31,32,33,34,35,37,39,40,41,43,44,45,47,48,49,50,51,52,53,55,56,57,59,60,62,64,65,66,67,68,69,71,74,75,76,78,80,82,83,84,86,87,88,89,90,91,92,95,97,99,100,105,107,108,113,116,120,121,123,126,138,140,144,148,149,153,154,161,165,176,178,179,180,181,182,183,184,185,186,187,188,189,191,192,193,194,195,196,197,198,199,205,208,211,212,215,220,221,223,224,237,239,241,242,250,252,262,264,269,],[25,-50,-134,25,-14,-72,-55,25,25,-129,-6,-130,-71,-53,-128,-127,-74,-61,-131,-11,-10,-59,-70,-9,-64,-99,-5,-98,-132,-66,-51,-133,-65,-58,-54,-2,-73,-12,25,-57,-52,-62,-13,-63,-67,-56,-4,-60,-149,-137,-138,25,-140,-41,-24,-45,-76,-28,-22,-38,-26,-125,-18,-16,-68,-69,-3,-145,-48,25,25,-15,-19,-79,-96,-94,-152,25,25,-142,-27,-47,-46,-20,-75,-77,-136,-78,-21,-115,-95,-120,-135,-7,-124,-126,-139,-143,-141,-153,-49,-29,-39,-40,-25,-42,-43,-44,-17,-23,25,-146,25,-121,-116,-105,-100,-97,-8,-154,-144,25,25,25,-147,-158,25,-150,-155,-148,-151,]),} _lr_action = { } for _k, _v in _lr_action_items.items(): for _x,_y in zip(_v[0],_v[1]): if not _x in _lr_action: _lr_action[_x] = { } _lr_action[_x][_k] = _y del _lr_action_items _lr_goto_items = {'final_input':([0,],[1,]),'not_test':([6,19,20,28,38,61,72,93,94,109,111,114,118,125,139,145,146,151,155,157,169,177,203,209,210,213,216,227,230,240,255,259,260,263,],[74,74,74,74,74,74,123,74,74,74,74,74,74,74,191,74,74,74,74,74,74,74,74,74,74,74,74,74,74,74,74,74,74,74,]),'fancy_drel_assignment_stmt':([0,4,11,12,51,68,95,97,116,117,120,197,199,224,237,239,250,],[26,26,26,26,26,26,26,26,26,26,26,26,26,26,26,26,26,]),'primary_att':([0,4,6,11,12,19,20,28,30,38,51,61,68,72,77,79,93,94,95,97,109,111,114,116,117,118,119,120,124,125,128,129,131,139,141,142,143,145,146,151,155,157,169,177,197,199,203,209,210,213,216,217,224,227,230,237,238,239,240,250,255,259,260,263,],[41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,41,]),'close_brace':([120,251,],[182,262,]),'primary':([0,4,6,11,12,19,20,28,30,38,51,61,68,72,77,79,93,94,95,97,109,111,114,116,117,118,119,120,124,125,128,129,131,139,141,142,143,145,146,151,155,157,169,177,197,199,203,209,210,213,216,217,224,227,230,237,238,239,240,250,255,259,260,263,],[42,42,73,42,42,92,92,92,100,73,42,92,42,92,92,92,92,92,42,42,92,92,92,42,42,92,100,42,92,92,92,92,92,92,92,92,92,92,92,92,92,92,92,92,42,42,92,92,92,92,92,100,42,92,92,42,100,42,92,42,92,92,92,92,]),'augmented_assignment_stmt':([0,4,11,12,51,68,95,97,116,117,120,197,199,224,237,239,250,],[27,27,27,27,27,27,27,27,27,27,27,27,27,27,27,27,27,]),'or_test':([6,19,20,28,38,61,93,94,109,111,114,118,125,145,151,155,157,169,177,203,209,210,213,216,227,230,240,255,259,260,263,],[86,86,86,86,86,86,86,86,86,86,86,86,86,86,86,86,86,86,86,86,86,86,86,86,246,86,86,266,267,86,86,]),'item_tag':([0,4,6,11,12,19,20,28,30,38,51,61,68,72,77,79,93,94,95,97,109,111,114,116,117,118,119,120,124,125,128,129,131,139,141,142,143,145,146,151,155,157,169,177,197,199,203,209,210,213,216,217,224,227,230,237,238,239,240,250,255,259,260,263,],[52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,52,]),'arglist':([152,],[200,]),'switch_stmt':([0,4,11,12,51,68,95,97,116,120,197,199,224,237,239,250,],[43,43,43,43,43,43,43,43,43,43,43,43,43,43,43,43,]),'listmaker':([38,93,],[103,103,]),'do_stmt_head':([0,4,11,12,51,68,95,97,116,120,197,199,224,237,239,250,],[4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,4,]),'open_brace':([4,12,51,95,97,112,116,197,199,224,237,239,250,],[68,68,68,68,68,175,68,68,68,68,68,68,68,]),'proper_slice':([111,210,],[171,171,]),'enclosure':([0,4,6,11,12,19,20,28,30,38,51,61,68,72,77,79,93,94,95,97,109,111,114,116,117,118,119,120,124,125,128,129,131,139,141,142,143,145,146,151,155,157,169,177,197,199,203,209,210,213,216,217,224,227,230,237,238,239,240,250,255,259,260,263,],[29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,29,]),'comp_operator':([78,241,],[128,253,]),'statement_block':([68,],[120,]),'dotlist':([109,],[160,]),'func_arg':([109,125,209,],[159,159,231,]),'caselist':([175,],[218,]),'power':([6,19,20,28,38,61,72,77,79,93,94,109,111,114,118,124,125,128,129,131,139,141,142,143,145,146,151,155,157,169,177,203,209,210,213,216,227,230,240,255,259,260,263,],[75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,75,]),'list_iter':([245,267,],[256,271,]),'u_expr':([6,19,20,28,38,61,72,77,79,93,94,109,111,114,118,124,125,128,129,131,139,141,142,143,145,146,151,155,157,169,177,203,209,210,213,216,227,230,240,255,259,260,263,],[71,71,71,71,71,71,71,126,138,71,71,71,71,71,71,186,71,71,71,71,71,192,193,194,71,71,71,71,71,71,71,71,71,71,71,71,71,71,71,71,71,71,71,]),'parenth_form':([0,4,6,11,12,19,20,28,30,38,51,61,68,72,77,79,93,94,95,97,109,111,114,116,117,118,119,120,124,125,128,129,131,139,141,142,143,145,146,151,155,157,169,177,197,199,203,209,210,213,216,217,224,227,230,237,238,239,240,250,255,259,260,263,],[8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,8,]),'literal':([0,4,6,11,12,19,20,28,30,38,51,61,68,72,77,79,93,94,95,97,109,111,114,116,117,118,119,120,124,125,128,129,131,139,141,142,143,145,146,151,155,157,169,177,197,199,203,209,210,213,216,217,224,227,230,237,238,239,240,250,255,259,260,263,],[45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,45,]),'assignment_stmt':([0,4,11,12,51,68,95,97,116,117,120,197,199,224,237,239,250,],[32,32,32,32,32,32,32,32,32,32,32,32,32,32,32,32,32,]),'call':([0,4,6,11,12,19,20,28,30,38,51,61,68,72,77,79,93,94,95,97,109,111,114,116,117,118,119,120,124,125,128,129,131,139,141,142,143,145,146,151,155,157,169,177,197,199,203,209,210,213,216,217,224,227,230,237,238,239,240,250,255,259,260,263,],[47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,47,]),'argument_list':([109,125,],[163,163,]),'statement':([0,11,68,120,],[48,90,121,183,]),'string_conversion':([0,4,6,11,12,19,20,28,30,38,51,61,68,72,77,79,93,94,95,97,109,111,114,116,117,118,119,120,124,125,128,129,131,139,141,142,143,145,146,151,155,157,169,177,197,199,203,209,210,213,216,217,224,227,230,237,238,239,240,250,255,259,260,263,],[49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,49,]),'with_head':([0,4,11,12,51,68,95,97,116,120,197,199,224,237,239,250,],[51,51,51,51,51,51,51,51,51,51,51,51,51,51,51,51,]),'input':([0,],[11,]),'loop_head':([0,4,11,12,51,68,95,97,116,120,197,199,224,237,239,250,],[12,12,12,12,12,12,12,12,12,12,12,12,12,12,12,12,]),'do_stmt':([0,4,11,12,51,68,95,97,116,120,197,199,224,237,239,250,],[13,13,13,13,13,13,13,13,13,13,13,13,13,13,13,13,]),'compound_stmt':([0,4,11,12,51,68,95,97,116,120,197,199,224,237,239,250,],[35,67,35,67,67,35,67,67,67,35,67,67,67,67,67,67,]),'list_if':([245,267,],[257,257,]),'attributeref':([0,4,6,11,12,19,20,28,30,38,51,61,68,72,77,79,93,94,95,97,109,111,114,116,117,118,119,120,124,125,128,129,131,139,141,142,143,145,146,151,155,157,169,177,197,199,203,209,210,213,216,217,224,227,230,237,238,239,240,250,255,259,260,263,],[9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,9,]),'listmaker2':([106,],[156,]),'short_slice':([111,210,],[167,232,]),'simple_slicing':([0,4,6,11,12,19,20,28,30,38,51,61,68,72,77,79,93,94,95,97,109,111,114,116,117,118,119,120,124,125,128,129,131,139,141,142,143,145,146,151,155,157,169,177,197,199,203,209,210,213,216,217,224,227,230,237,238,239,240,250,255,259,260,263,],[37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,37,]),'a_expr':([6,19,20,28,38,61,72,93,94,109,111,114,118,125,128,139,145,146,151,155,157,169,177,203,209,210,213,216,227,230,240,255,259,260,263,],[78,78,78,78,78,78,78,78,78,78,78,78,78,78,187,78,78,78,78,78,78,78,78,78,78,78,78,78,78,78,78,78,78,78,78,]),'print_stmt':([0,4,11,12,51,68,95,97,116,117,120,197,199,224,237,239,250,],[50,50,50,50,50,50,50,50,50,50,50,50,50,50,50,50,50,]),'list_for':([106,245,267,],[158,258,258,]),'testlist':([227,],[245,]),'loop_stmt':([0,4,11,12,51,68,95,97,116,120,197,199,224,237,239,250,],[15,15,15,15,15,15,15,15,15,15,15,15,15,15,15,15,]),'slicing':([0,4,6,11,12,19,20,28,30,38,51,61,68,72,77,79,93,94,95,97,109,111,114,116,117,118,119,120,124,125,128,129,131,139,141,142,143,145,146,151,155,157,169,177,197,199,203,209,210,213,216,217,224,227,230,237,238,239,240,250,255,259,260,263,],[17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,17,]),'target_list':([0,4,6,11,12,30,38,51,68,95,97,116,117,120,197,199,217,224,237,238,239,250,],[63,63,81,63,63,101,104,63,63,63,63,63,63,63,63,63,237,63,63,250,63,63,]),'for_stmt':([0,4,11,12,51,68,95,97,116,120,197,199,224,237,239,250,],[18,18,18,18,18,18,18,18,18,18,18,18,18,18,18,18,]),'m_expr':([6,19,20,28,38,61,72,93,94,109,111,114,118,125,128,129,131,139,145,146,151,155,157,169,177,203,209,210,213,216,227,230,240,255,259,260,263,],[82,82,82,82,82,82,82,82,82,82,82,82,82,82,82,188,189,82,82,82,82,82,82,82,82,82,82,82,82,82,82,82,82,82,82,82,82,]),'and_test':([6,19,20,28,38,61,93,94,109,111,114,118,125,145,146,151,155,157,169,177,203,209,210,213,216,227,230,240,255,259,260,263,],[80,80,80,80,80,80,80,80,80,80,80,80,80,80,196,80,80,80,80,80,80,80,80,80,80,80,80,80,80,80,80,80,]),'atom':([0,4,6,11,12,19,20,28,30,38,51,61,68,72,77,79,93,94,95,97,109,111,114,116,117,118,119,120,124,125,128,129,131,139,141,142,143,145,146,151,155,157,169,177,197,199,203,209,210,213,216,217,224,227,230,237,238,239,240,250,255,259,260,263,],[2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,2,]),'funcdef':([0,4,11,12,51,68,95,97,116,120,197,199,224,237,239,250,],[3,3,3,3,3,3,3,3,3,3,3,3,3,3,3,3,]),'slice_list':([111,],[166,]),'subscription':([0,4,6,11,12,19,20,28,30,38,51,61,68,72,77,79,93,94,95,97,109,111,114,116,117,118,119,120,124,125,128,129,131,139,141,142,143,145,146,151,155,157,169,177,197,199,203,209,210,213,216,217,224,227,230,237,238,239,240,250,255,259,260,263,],[53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,53,]),'stmt_list':([0,11,68,120,],[62,62,62,62,]),'comparison':([6,19,20,28,38,61,72,93,94,109,111,114,118,125,139,145,146,151,155,157,169,177,203,209,210,213,216,227,230,240,255,259,260,263,],[83,83,83,83,83,83,83,83,83,83,83,83,83,83,83,83,83,83,83,83,83,83,83,83,83,83,83,83,83,83,83,83,83,83,]),'attribute_tag':([42,73,92,100,],[108,108,108,108,]),'if_stmt':([0,4,11,12,51,68,95,97,116,120,197,199,224,237,239,250,],[21,21,21,21,21,21,21,21,21,21,21,21,21,21,21,21,]),'extended_slicing':([0,4,6,11,12,19,20,28,30,38,51,61,68,72,77,79,93,94,95,97,109,111,114,116,117,118,119,120,124,125,128,129,131,139,141,142,143,145,146,151,155,157,169,177,197,199,203,209,210,213,216,217,224,227,230,237,238,239,240,250,255,259,260,263,],[34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,34,]),'expression_list':([6,20,94,111,114,118,151,155,],[85,96,85,172,176,180,199,202,]),'list_display':([0,4,6,11,12,19,20,28,30,38,51,61,68,72,77,79,93,94,95,97,109,111,114,116,117,118,119,120,124,125,128,129,131,139,141,142,143,145,146,151,155,157,169,177,197,199,203,209,210,213,216,217,224,226,227,230,237,238,239,240,250,254,255,259,260,263,],[22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,22,244,22,22,22,22,22,22,22,265,22,22,22,22,]),'where_stmt':([0,4,11,12,51,68,95,97,116,120,197,199,224,237,239,250,],[39,39,39,39,39,39,39,39,39,39,39,39,39,39,39,39,]),'stringliteral':([0,4,6,11,12,19,20,28,30,38,51,61,68,72,77,79,93,94,95,97,109,111,114,116,117,118,119,120,124,125,128,129,131,139,141,142,143,145,146,151,155,157,169,177,197,199,203,209,210,213,216,217,224,227,230,237,238,239,240,250,255,259,260,263,],[23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,23,]),'with_stmt':([0,4,11,12,51,68,95,97,116,120,197,199,224,237,239,250,],[24,24,24,24,24,24,24,24,24,24,24,24,24,24,24,24,]),'long_slice':([111,210,],[170,170,]),'suite':([4,12,51,95,97,116,197,199,224,237,239,250,],[65,91,113,147,149,178,221,223,242,249,251,261,]),'target':([0,4,6,11,12,30,38,51,68,95,97,116,117,119,120,197,199,217,224,237,238,239,250,],[54,54,84,54,54,84,84,54,54,54,54,54,54,181,54,54,54,84,54,54,84,54,54,]),'simple_stmt':([0,4,11,12,51,68,95,97,116,117,120,197,199,224,237,239,250,],[14,66,14,66,66,14,66,66,66,179,14,66,66,66,66,66,66,]),'slice_item':([111,210,],[173,233,]),'expression':([6,19,20,28,38,61,93,94,109,111,114,118,125,145,151,155,157,169,177,203,209,210,213,216,230,240,260,263,],[87,95,87,99,106,116,106,87,164,174,87,87,164,195,87,87,204,214,219,228,164,234,235,236,248,252,268,269,]),} _lr_goto = { } for _k, _v in _lr_goto_items.items(): for _x,_y in zip(_v[0],_v[1]): if not _x in _lr_goto: _lr_goto[_x] = { } _lr_goto[_x][_k] = _y del _lr_goto_items _lr_productions = [ ("S' -> final_input","S'",1,None,None,None), ('final_input -> input','final_input',1,'p_final_input','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',20), ('input -> statement','input',1,'p_input','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',24), ('input -> input statement','input',2,'p_input','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',25), ('statement -> stmt_list','statement',1,'p_statement','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',29), ('statement -> compound_stmt','statement',1,'p_statement','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',30), ('stmt_list -> simple_stmt','stmt_list',1,'p_stmt_list','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',34), ('stmt_list -> stmt_list ; simple_stmt','stmt_list',3,'p_stmt_list','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',35), ('stmt_list -> stmt_list ; simple_stmt ;','stmt_list',4,'p_stmt_list','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',36), ('simple_stmt -> assignment_stmt','simple_stmt',1,'p_simple_stmt','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',46), ('simple_stmt -> augmented_assignment_stmt','simple_stmt',1,'p_simple_stmt','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',47), ('simple_stmt -> fancy_drel_assignment_stmt','simple_stmt',1,'p_simple_stmt','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',48), ('simple_stmt -> print_stmt','simple_stmt',1,'p_simple_stmt','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',49), ('simple_stmt -> BREAK','simple_stmt',1,'p_simple_stmt','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',50), ('simple_stmt -> NEXT','simple_stmt',1,'p_simple_stmt','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',51), ('print_stmt -> PRINT expression','print_stmt',2,'p_print_stmt','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',56), ('expression_list -> expression','expression_list',1,'p_expression_list','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',62), ('expression_list -> expression_list , expression','expression_list',3,'p_expression_list','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',63), ('expression -> or_test','expression',1,'p_expression','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',75), ('target -> primary','target',1,'p_target','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',84), ('target -> ( target_list )','target',3,'p_target','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',85), ('target -> [ target_list ]','target',3,'p_target','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',86), ('or_test -> and_test','or_test',1,'p_or_test','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',99), ('or_test -> or_test OR and_test','or_test',3,'p_or_test','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',100), ('and_test -> not_test','and_test',1,'p_and_test','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',105), ('and_test -> and_test AND not_test','and_test',3,'p_and_test','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',106), ('not_test -> comparison','not_test',1,'p_not_test','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',111), ('not_test -> NOT not_test','not_test',2,'p_not_test','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',112), ('comparison -> a_expr','comparison',1,'p_comparison','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',117), ('comparison -> a_expr comp_operator a_expr','comparison',3,'p_comparison','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',118), ('comp_operator -> <','comp_operator',1,'p_comp_operator','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',124), ('comp_operator -> >','comp_operator',1,'p_comp_operator','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',125), ('comp_operator -> GTE','comp_operator',1,'p_comp_operator','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',126), ('comp_operator -> LTE','comp_operator',1,'p_comp_operator','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',127), ('comp_operator -> NEQ','comp_operator',1,'p_comp_operator','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',128), ('comp_operator -> ISEQUAL','comp_operator',1,'p_comp_operator','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',129), ('comp_operator -> IN','comp_operator',1,'p_comp_operator','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',130), ('comp_operator -> NOT IN','comp_operator',2,'p_comp_operator','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',131), ('a_expr -> m_expr','a_expr',1,'p_a_expr','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',137), ('a_expr -> a_expr + m_expr','a_expr',3,'p_a_expr','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',138), ('a_expr -> a_expr - m_expr','a_expr',3,'p_a_expr','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',139), ('m_expr -> u_expr','m_expr',1,'p_m_expr','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',146), ('m_expr -> m_expr * u_expr','m_expr',3,'p_m_expr','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',147), ('m_expr -> m_expr / u_expr','m_expr',3,'p_m_expr','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',148), ('m_expr -> m_expr ^ u_expr','m_expr',3,'p_m_expr','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',149), ('u_expr -> power','u_expr',1,'p_u_expr','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',161), ('u_expr -> - u_expr','u_expr',2,'p_u_expr','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',162), ('u_expr -> + u_expr','u_expr',2,'p_u_expr','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',163), ('power -> primary','power',1,'p_power','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',170), ('power -> primary POWER u_expr','power',3,'p_power','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',171), ('primary -> atom','primary',1,'p_primary','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',179), ('primary -> primary_att','primary',1,'p_primary','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',180), ('primary -> subscription','primary',1,'p_primary','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',181), ('primary -> slicing','primary',1,'p_primary','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',182), ('primary -> call','primary',1,'p_primary','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',183), ('primary_att -> attributeref','primary_att',1,'p_primary_att','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',189), ('atom -> ID','atom',1,'p_atom','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',195), ('atom -> item_tag','atom',1,'p_atom','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',196), ('atom -> literal','atom',1,'p_atom','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',197), ('atom -> enclosure','atom',1,'p_atom','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',198), ('item_tag -> ITEM_TAG','item_tag',1,'p_item_tag','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',203), ('literal -> stringliteral','literal',1,'p_literal','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',211), ('literal -> INTEGER','literal',1,'p_literal','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',212), ('literal -> HEXINT','literal',1,'p_literal','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',213), ('literal -> OCTINT','literal',1,'p_literal','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',214), ('literal -> BININT','literal',1,'p_literal','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',215), ('literal -> REAL','literal',1,'p_literal','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',216), ('literal -> IMAGINARY','literal',1,'p_literal','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',217), ('stringliteral -> STRPREFIX SHORTSTRING','stringliteral',2,'p_stringliteral','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',222), ('stringliteral -> STRPREFIX LONGSTRING','stringliteral',2,'p_stringliteral','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',223), ('stringliteral -> SHORTSTRING','stringliteral',1,'p_stringliteral','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',224), ('stringliteral -> LONGSTRING','stringliteral',1,'p_stringliteral','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',225), ('enclosure -> parenth_form','enclosure',1,'p_enclosure','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',230), ('enclosure -> string_conversion','enclosure',1,'p_enclosure','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',231), ('enclosure -> list_display','enclosure',1,'p_enclosure','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',232), ('parenth_form -> ( expression_list )','parenth_form',3,'p_parenth_form','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',236), ('parenth_form -> ( )','parenth_form',2,'p_parenth_form','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',237), ('string_conversion -> ` expression_list `','string_conversion',3,'p_string_conversion','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',244), ('list_display -> [ listmaker ]','list_display',3,'p_list_display','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',248), ('list_display -> [ ]','list_display',2,'p_list_display','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',249), ('listmaker -> expression listmaker2','listmaker',2,'p_listmaker','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',257), ('listmaker -> expression list_for','listmaker',2,'p_listmaker','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',258), ('listmaker2 -> , expression','listmaker2',2,'p_listmaker2','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',264), ('listmaker2 -> listmaker2 , expression','listmaker2',3,'p_listmaker2','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',265), ('listmaker2 -> ','listmaker2',0,'p_listmaker2','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',266), ('list_for -> FOR expression_list IN testlist','list_for',4,'p_list_for','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',270), ('list_for -> FOR expression_list IN testlist list_iter','list_for',5,'p_list_for','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',271), ('testlist -> or_test','testlist',1,'p_testlist','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',275), ('testlist -> testlist , or_test','testlist',3,'p_testlist','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',276), ('testlist -> testlist , or_test ,','testlist',4,'p_testlist','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',277), ('list_iter -> list_for','list_iter',1,'p_list_iter','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',281), ('list_iter -> list_if','list_iter',1,'p_list_iter','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',282), ('list_if -> IF or_test','list_if',2,'p_list_if','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',286), ('list_if -> IF or_test list_iter','list_if',3,'p_list_if','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',287), ('attributeref -> primary attribute_tag','attributeref',2,'p_attributeref','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',305), ('attribute_tag -> . ID','attribute_tag',2,'p_attribute_tag','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',327), ('attribute_tag -> REAL','attribute_tag',1,'p_attribute_tag','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',328), ('subscription -> primary [ expression_list ]','subscription',4,'p_subscription','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',337), ('slicing -> simple_slicing','slicing',1,'p_slicing','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',355), ('slicing -> extended_slicing','slicing',1,'p_slicing','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',356), ('simple_slicing -> primary [ short_slice ]','simple_slicing',4,'p_simple_slicing','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',360), ('short_slice -> :','short_slice',1,'p_short_slice','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',364), ('short_slice -> expression : expression','short_slice',3,'p_short_slice','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',365), ('short_slice -> : expression','short_slice',2,'p_short_slice','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',366), ('short_slice -> expression :','short_slice',2,'p_short_slice','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',367), ('extended_slicing -> primary [ slice_list ]','extended_slicing',4,'p_extended_slicing','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',371), ('slice_list -> slice_item','slice_list',1,'p_slice_list','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',375), ('slice_list -> slice_list , slice_item','slice_list',3,'p_slice_list','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',376), ('slice_item -> expression','slice_item',1,'p_slice_item','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',380), ('slice_item -> proper_slice','slice_item',1,'p_slice_item','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',381), ('slice_item -> ELLIPSIS','slice_item',1,'p_slice_item','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',382), ('proper_slice -> short_slice','proper_slice',1,'p_proper_slice','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',386), ('proper_slice -> long_slice','proper_slice',1,'p_proper_slice','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',387), ('long_slice -> short_slice :','long_slice',2,'p_long_slice','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',391), ('long_slice -> short_slice : expression','long_slice',3,'p_long_slice','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',392), ('call -> primary ( )','call',3,'p_call','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',402), ('call -> primary ( argument_list )','call',4,'p_call','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',403), ('argument_list -> func_arg','argument_list',1,'p_argument_list','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',428), ('argument_list -> argument_list , func_arg','argument_list',3,'p_argument_list','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',429), ('func_arg -> expression','func_arg',1,'p_func_arg','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',433), ('augmented_assignment_stmt -> target AUGOP expression_list','augmented_assignment_stmt',3,'p_augmented_assignment_stmt','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',437), ('fancy_drel_assignment_stmt -> primary ( dotlist )','fancy_drel_assignment_stmt',4,'p_fancy_drel_assignment_stmt','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',449), ('dotlist -> . ID = expression','dotlist',4,'p_dotlist','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',458), ('dotlist -> dotlist , . ID = expression','dotlist',6,'p_dotlist','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',459), ('assignment_stmt -> target_list = expression_list','assignment_stmt',3,'p_assignment_stmt','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',476), ('target_list -> target','target_list',1,'p_target_list','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',480), ('target_list -> target_list , target','target_list',3,'p_target_list','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',481), ('compound_stmt -> if_stmt','compound_stmt',1,'p_compound_stmt','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',487), ('compound_stmt -> for_stmt','compound_stmt',1,'p_compound_stmt','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',488), ('compound_stmt -> do_stmt','compound_stmt',1,'p_compound_stmt','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',489), ('compound_stmt -> loop_stmt','compound_stmt',1,'p_compound_stmt','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',490), ('compound_stmt -> with_stmt','compound_stmt',1,'p_compound_stmt','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',491), ('compound_stmt -> where_stmt','compound_stmt',1,'p_compound_stmt','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',492), ('compound_stmt -> switch_stmt','compound_stmt',1,'p_compound_stmt','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',493), ('compound_stmt -> funcdef','compound_stmt',1,'p_compound_stmt','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',494), ('if_stmt -> IF expression suite','if_stmt',3,'p_if_stmt','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',499), ('if_stmt -> if_stmt ELSE suite','if_stmt',3,'p_if_stmt','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',500), ('suite -> simple_stmt','suite',1,'p_suite','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',515), ('suite -> compound_stmt','suite',1,'p_suite','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',516), ('suite -> open_brace statement_block close_brace','suite',3,'p_suite','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',517), ('open_brace -> {','open_brace',1,'p_open_brace','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',524), ('close_brace -> }','close_brace',1,'p_close_brace','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',529), ('statement_block -> statement','statement_block',1,'p_statement_block','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',534), ('statement_block -> statement_block statement','statement_block',2,'p_statement_block','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',535), ('for_stmt -> FOR target_list IN expression_list suite','for_stmt',5,'p_for_stmt','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',540), ('loop_stmt -> loop_head suite','loop_stmt',2,'p_loop_stmt','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',549), ('loop_head -> LOOP ID AS ID','loop_head',4,'p_loop_head','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',555), ('loop_head -> LOOP ID AS ID : ID','loop_head',6,'p_loop_head','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',556), ('loop_head -> LOOP ID AS ID : ID comp_operator ID','loop_head',8,'p_loop_head','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',557), ('do_stmt -> do_stmt_head suite','do_stmt',2,'p_do_stmt','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',579), ('do_stmt_head -> DO ID = expression , expression','do_stmt_head',6,'p_do_stmt_head','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',586), ('do_stmt_head -> DO ID = expression , expression , expression','do_stmt_head',8,'p_do_stmt_head','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',587), ('with_stmt -> with_head suite','with_stmt',2,'p_with_stmt','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',600), ('with_head -> WITH ID AS ID','with_head',4,'p_with_head','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',617), ('where_stmt -> WHERE expression suite ELSE suite','where_stmt',5,'p_where_stmt','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',629), ('switch_stmt -> SWITCH ID open_brace caselist DEFAULT suite close_brace','switch_stmt',7,'p_switch_stmt','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',633), ('caselist -> CASE target_list suite','caselist',3,'p_caselist','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',637), ('caselist -> caselist CASE target_list suite','caselist',4,'p_caselist','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',638), ('funcdef -> FUNCTION ID ( arglist ) suite','funcdef',6,'p_funcdef','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',642), ('arglist -> ID : list_display','arglist',3,'p_arglist','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',650), ('arglist -> arglist , ID : list_display','arglist',5,'p_arglist','/Users/gupi/sourceforge/cbflib/bleeding/cbflib_bleeding_edge/dREL-ply-0.5/drel_yacc.py',651), ] ./CBFlib-0.9.2.2/dREL-ply-0.5/setup.cfg0000755000076500007650000000007311603702115015312 0ustar yayayaya[egg_info] tag_build = tag_date = 0 tag_svn_revision = 0 ./CBFlib-0.9.2.2/dREL-ply-0.5/setup.py0000755000076500007650000000065311603702115015207 0ustar yayayaya# Setup file for automatic installation of the dREL parser # distribution from setuptools import setup, Extension setup(name="dREL-ply", version = "0.5", description = "Conversion from dREL to python", author = "James Hester", author_email = "jamesrhester at gmail.com", url="http://pycifrw.berlios.de", py_modules = ['drel_yacc','drel_lex'], install_requires = ['ply>=2.5'] ) ./CBFlib-0.9.2.2/dREL-ply-0.5/drel_prep.py0000644000076500007650000000076211603702115016021 0ustar yayayaya#!/usr/bin/python import sys class Process: def execute_method(self): valuename = sys.argv[1] editname = valuename + '_local' print valuename print editname f = open("cbf_data_debug", "r") data = f.readline() str_list = [] while data: data = f.readline() print data str = data.replace(valuename, editname) print str str_list.append(str) str = "".join(str_list) fout = open("cbf_data_debug_changed", "w") print>>fout, str p = Process() p.execute_method() ./CBFlib-0.9.2.2/dREL-ply-0.5/drel_yacc.py0000755000076500007650000005636211603702115016004 0ustar yayayaya# A dREL grammar written for python-ply # # The output string should be a series of executable python statements, # which define a function which is called with a PyCIFRW CifBlock # object as single argument "cfdata" # # The object so defined will be a method of the dictionary object, taking # arguments self,cfdata. Therefore dictionary information is accessed # through "self", and data through "cfdata". import drel_lex import ply.yacc as yacc tokens = drel_lex.tokens # Overall translation unit # We return the text of the function, as well as a table of 'with' packets # and corresponding index names # def p_final_input(p): '''final_input : input''' p[0] = [p[1],p.parser.withtable] def p_input(p): '''input : statement | input statement''' p[0] = "\n".join(p[1:]) def p_statement(p): '''statement : stmt_list | compound_stmt''' p[0] = p[1] def p_stmt_list(p): '''stmt_list : simple_stmt | stmt_list ";" simple_stmt | stmt_list ";" simple_stmt ";" ''' if len(p) == 2: p[0] = p[1] else: p[0] = ";".join((p[1],p[3])) # differs from Python in that an expression list is not # allowed. Thus no procedure calls, for example. # This is done to avoid a reduce/reduce conflict for # identifiers (start of expression? start of target?) def p_simple_stmt(p): '''simple_stmt : assignment_stmt | augmented_assignment_stmt | fancy_drel_assignment_stmt | print_stmt | BREAK | NEXT''' p[0] = p[1] print "Simple statement: " + p[0] def p_print_stmt(p): '''print_stmt : PRINT expression ''' p[0] = 'print ' + p[2] # note do not accept trailing commas def p_expression_list(p): '''expression_list : expression | expression_list "," expression ''' if len(p) == 2: p[0] = p[1] else: p[0] = " ".join((p[1],",",p[3])) print "constructing expr list: %s" % `p[0]` # Simplified from the python 2.5 version due to apparent conflict with # the other type of IF expression... # def p_expression(p): '''expression : or_test ''' if len(p) == 2: p[0] = p[1] # else: p[0] = " ".join((p[1],"if",p[3],"else", p[5])) # This is too generous, as it allows a function call on the # LHS to be assigned to. This will cause a syntax error on # execution we hope. def p_target(p): '''target : primary | "(" target_list ")" | "[" target_list "]" ''' # search our enclosing blocks for special ids newid = 0 # print 'Special ids: %s' % `p.parser.special_id` for idtable in p.parser.special_id: newid = idtable.get(p[1],0) if newid: break if newid: p[0] = newid else: p[0] = " ".join(p[1:]) def p_or_test(p): ''' or_test : and_test | or_test OR and_test''' if len(p) == 2: p[0] = p[1] else: p[0] = " ".join((p[1],"or",p[3])) def p_and_test(p): '''and_test : not_test | and_test AND not_test''' if len(p) == 2: p[0] = p[1] else: p[0] = " ".join((p[1],"and",p[3])) def p_not_test(p): '''not_test : comparison | NOT not_test''' if len(p) == 2: p[0] = p[1] else: p[0] = " ".join(("not",p[2])) def p_comparison(p): '''comparison : a_expr | a_expr comp_operator a_expr''' if len(p) == 2: p[0] = p[1] else: p[0] = " ".join((p[1],p[2],p[3])) def p_comp_operator(p): '''comp_operator : "<" | ">" | GTE | LTE | NEQ | ISEQUAL | IN | NOT IN ''' if len(p)==3: p[0] = " not in " else: p[0] = p[1] def p_a_expr(p): '''a_expr : m_expr | a_expr "+" m_expr | a_expr "-" m_expr''' if len(p) == 2: p[0] = p[1] else: p[0] = " ".join((p[1] , p[2] , p[3])) def p_m_expr(p): '''m_expr : u_expr | m_expr "*" u_expr | m_expr "/" u_expr | m_expr "^" u_expr ''' if len(p) == 2: p[0] = p[1] else: if p[2] == "^": p[0] = "numpy.cross(" + p[1] + " , " + p[3] + ")" elif p[2] == "*": #need to invoke numpy version p[0] = "numpy.dot("+p[1]+","+p[3]+")" else: p[0] = " ".join((p[1] , p[2] , p[3])) def p_u_expr(p): '''u_expr : power | "-" u_expr | "+" u_expr''' if len(p) == 2: p[0] = p[1] else: p[0] = " ".join(p[1:]) def p_power(p): '''power : primary | primary POWER u_expr''' if len(p) == 2: p[0] = p[1] else: p[0] = " ".join((p[1] , "**" , p[3])) print 'At power: p[0] is %s' % `p[0]` def p_primary(p): '''primary : atom | primary_att | subscription | slicing | call''' # print 'Primary -> %s' % repr(p[1]) p[0] = p[1] # Separated out so that we can re-initialise subscription category def p_primary_att(p): '''primary_att : attributeref''' print "Reinitialising sub_subject from %s to null" % p.parser.sub_subject p.parser.sub_subject = "" p[0] = p[1] def p_atom(p): '''atom : ID | item_tag | literal | enclosure''' # print 'Atom -> %s' % repr(p[1]) p[0] = p[1] def p_item_tag(p): '''item_tag : ITEM_TAG''' # print "Target %s, treating %s" % (p.parser.target_name,"".join(p[1:])) if p.parser.target_id == "".join(p[1:]): p[0] = "__dreltarget" else: p[0] = "ciffile['%s']" % p[1] def p_literal(p): '''literal : stringliteral | INTEGER | HEXINT | OCTINT | BININT | REAL | IMAGINARY''' # print 'literal-> %s' % repr(p[1]) p[0] = p[1] def p_stringliteral(p): '''stringliteral : STRPREFIX SHORTSTRING | STRPREFIX LONGSTRING | SHORTSTRING | LONGSTRING''' if len(p)==3: p[0] = p[1]+p[2] else: p[0] = p[1] def p_enclosure(p): '''enclosure : parenth_form | string_conversion | list_display ''' p[0]=p[1] def p_parenth_form(p): '''parenth_form : "(" expression_list ")" | "(" ")" ''' if len(p) == 3: p[0] = "( )" else: p[0] = " ".join(p[1:]) # print 'Parens: %s' % `p[0]` def p_string_conversion(p): '''string_conversion : "`" expression_list "`" ''' p[0] = "".join(p[1:]) def p_list_display(p): ''' list_display : "[" listmaker "]" | "[" "]" ''' if len(p) == 3: p[0] = "StarFile.StarList([])" else: p[0] = "StarFile.StarList("+"".join(p[1:])+")" # scrap the trailing comma def p_listmaker(p): '''listmaker : expression listmaker2 | expression list_for ''' p[0] = " ".join(p[1:]) #no need to rewrite for dREL->python # print 'listmaker: %s' % `p[0]` def p_listmaker2(p): '''listmaker2 : "," expression | listmaker2 "," expression | ''' p[0] = " ".join(p[1:]) def p_list_for(p): '''list_for : FOR expression_list IN testlist | FOR expression_list IN testlist list_iter''' pass def p_testlist(p): '''testlist : or_test | testlist "," or_test | testlist "," or_test "," ''' pass def p_list_iter(p): '''list_iter : list_for | list_if''' pass def p_list_if(p): '''list_if : IF or_test | IF or_test list_iter''' pass # We have to intercept attribute references which relate to # aliased category variables, as well as to catch literal # item names containing a period. # # Note that we need to catch tags of the form 't.12', which # our lexer will interpret as ID REAL. We therefore also # accept t.12(3), which is not allowed, but we don't bother # trying to catch this error here. # # Note that there is no other meaning for '.' in drel beyond # category-item specifications, so we adopt a default stance # of converting all otherwise unresolvable attribute references # to simple table references to fit in with the PyCIFRW practice. def p_attributeref(p): '''attributeref : primary attribute_tag ''' # intercept special loop variables # print `p.parser.special_id` newid = None for idtable in p.parser.special_id: newid = idtable.get(p[1],0) if newid: break if newid: p[0] = "ciffile["+'"_'+newid[0]+p[2]+'"]' print "In ID processing: %s\n" % `newid` # a with statement may require an index if newid[1]: p[0] = p[0] + "[" + newid[1] + "]" elif p.parser.special_id[0].has_key("".join(p[1:])): # a global variable from the dictionary print "Using global dictionary variable "+p[1:] p[0] = 'ciffile['+"".join(p[1:])+']' else: #could be a keyed index operation, add back category val p[0] = p[1]+'["'+ p.parser.sub_subject+p[2] + '"]' p.parser.sub_subject = "" def p_attribute_tag(p): '''attribute_tag : "." ID | REAL ''' p[0] = "".join(p[1:]) # A subscription becomes a key lookup if the primary is a # pre-defined 'category variable'. We use the GetKeyedPacket # method we have specially added to PyCIFRW to simplify the # code here # def p_subscription(p): '''subscription : primary "[" expression_list "]" ''' # intercept special loop variables # print `p.parser.special_id` newid = None for idtable in p.parser.special_id: newid = idtable.get(p[1],0) if newid: break if newid: # We first get the PyCIFRW Loop block... key_item = 'self["'+newid[0]+'"]["_category_key.generic"]' get_loop = "ciffile.GetLoop(%s).GetKeyedPacket(%s,%s)" % (key_item,key_item,p[3]) p[0] = get_loop p.parser.sub_subject = "_"+newid[0]#in case of attribute reference following print "Set sub_subject to %s" % p.parser.sub_subject else: p[0] = " ".join(p[1:]) def p_slicing(p): '''slicing : simple_slicing | extended_slicing ''' p[0] = p[1] def p_simple_slicing(p): '''simple_slicing : primary "[" short_slice "]" ''' p[0] = " ".join(p[1:]) def p_short_slice(p): '''short_slice : ":" | expression ":" expression | ":" expression | expression ":" ''' p[0] = " ".join(p[1:]) def p_extended_slicing(p): '''extended_slicing : primary "[" slice_list "]" ''' p[0] = " ".join(p[1:]) def p_slice_list(p): '''slice_list : slice_item | slice_list "," slice_item ''' p[0] = " ".join(p[1:]) def p_slice_item(p): '''slice_item : expression | proper_slice | ELLIPSIS ''' p[0] = p[1] def p_proper_slice(p): '''proper_slice : short_slice | long_slice ''' p[0] = p[1] def p_long_slice(p): '''long_slice : short_slice ":" | short_slice ":" expression ''' p[0] = " ".join(p[1:]) # Last of the primary non-terminals... # We can catch quite a few of the functions simply by # rewriting the function name. By default, the function # name is passed through unchanged; this makes sure that # the built-in functions are found OK # def p_call(p): '''call : primary "(" ")" | primary "(" argument_list ")" ''' # simple built-in functions only at this stage builtins = {"list":"StarFile.StarList", "tuple":"StarFile.StarTuple", "table":"dict", "int":"int", "len":"len"} funcname = builtins.get(p[1].lower(),p[1]) # try to catch a few straightforward trickier ones if funcname.lower() == "mod": p[0] = "divmod" + "".join(p[2:]) + "[1]" elif funcname.lower() in ['sind','cosd','tand']: p[0] = "math."+funcname[:3].lower()+"("+ "math.radians" + "".join(p[2:])+")" elif funcname.lower() in ['array']: p[0] = "numpy.array(" + "".join(p[2:]) + ")" else: p[0] = funcname + "".join(p[2:]) #print "Function call: %s" % p[0] # It seems that in dREL the arguments are expressed differently # in the form arg [: specifier], arg ... # # We assume a simplified form # def p_argument_list(p): '''argument_list : func_arg | argument_list "," func_arg ''' p[0] = " ".join(p[1:]) def p_func_arg(p): '''func_arg : expression ''' p[0] = p[1] #ignore list structure for now def p_augmented_assignment_stmt(p): '''augmented_assignment_stmt : target AUGOP expression_list''' augsym = "%s" % p[2] if augsym == "++=": #append to list p[0] = p[1] + "+= [" + p[3] + "]" else: p[0] = " ".join(p[1:]) # We simultaneously create multiple results for a single category. In # this case __dreltarget is a dictionary with keys for each category # entry. def p_fancy_drel_assignment_stmt(p): '''fancy_drel_assignment_stmt : primary "(" dotlist ")" ''' del p.parser.fancy_drel_id p[0] = p[3] print "Fancy assignment -> " + p[0] # Something made up specially for drel. We accumulate results for a series of # items in a dictionary which is returned def p_dotlist(p): '''dotlist : "." ID "=" expression | dotlist "," "." ID "=" expression''' if len(p) == 5: #first element of dotlist, element -2 is category id p.parser.fancy_drel_id = p[-2] if p[-2] == p.parser.target_id: #we will return the results realid = p[-2]+"."+p[2] p[0] = "__dreltarget.update({'%s':__dreltarget.get('%s',[])+[%s]})\n" % (realid,realid,p[4]) else: p[0] = p[-2] + "".join(p[1:]) + "\n" print 'Fancy id is ' + `p[-2]` else: if p.parser.fancy_drel_id == p.parser.target_id: realid = p.parser.fancy_drel_id + "." + p[4] p[0] = p[1] + "__dreltarget.update({'%s':__dreltarget.get('%s',[])+[%s]})\n" % (realid,realid,p[6]) else: p[0] = p[1] + p.parser.fancy_drel_id + "".join(p[3:]) + "\n" def p_assignment_stmt(p): '''assignment_stmt : target_list "=" expression_list''' p[0] = " ".join(p[1:]) def p_target_list(p): '''target_list : target | target_list "," target ''' p[0] = " ".join(p[1:]) # now for the compound statements def p_compound_stmt(p): '''compound_stmt : if_stmt | for_stmt | do_stmt | loop_stmt | with_stmt | where_stmt | switch_stmt | funcdef ''' p[0] = p[1] print "Compound statement: \n" + p[0] def p_if_stmt(p): '''if_stmt : IF expression suite | if_stmt ELSE suite ''' if p[1].lower() == "if": #first form of expression p[0] = "if " p[0] += p[2] + ":" p[0] += add_indent(p[3]) else: #else statement p[0] = p[1] + "\n" p[0] += p[2].lower() + ":" + add_indent(p[3]) print "If statement: \n" + p[0] # Note the dREL divergence from Python here: we allow compound # statements to follow without a separate block (like C etc.) # For simplicity we indent consistently (further up) def p_suite(p): '''suite : simple_stmt | compound_stmt | open_brace statement_block close_brace ''' if len(p) == 2: p[0] = "\n" + p[1] else: p[0] = p[2] + "\n" # separate so we can do the indent/dedent thing def p_open_brace(p): '''open_brace : "{"''' p.parser.indent += 4*" " print 'Parser indent now "%s"' % p.parser.indent def p_close_brace(p): '''close_brace : "}"''' p.parser.indent = p.parser.indent[:-4] print 'Parser indent now "%s"' % p.parser.indent def p_statement_block(p): '''statement_block : statement | statement_block statement''' if len(p) == 2: p[0] = "\n" + p[1] else: p[0] = p[1] + "\n" + p[2] def p_for_stmt(p): '''for_stmt : FOR target_list IN expression_list suite''' p[0] = "for " + p[2] + "in" + p[4] + ":\n" + add_indent(p[5]) # We split the loop statement into parts so that we can capture the # ID before the suite is processed. Note that we should record that # we have an extra indent due to the loop test and remove it at the # end, but we haven't done this yet. def p_loop_stmt(p): '''loop_stmt : loop_head suite''' p[0] = p[1] + add_indent(p[2]) # We capture a list of all the actually present items in the current # datafile def p_loop_head(p): '''loop_head : LOOP ID AS ID | LOOP ID AS ID ":" ID | LOOP ID AS ID ":" ID comp_operator ID''' p[0] = "__pycitems = self.names_in_cat('%s')" % p[4] p[0] += "\nprint 'names in cat = %s' % `__pycitems`" p[0] += "\n" + "__pycitems = filter(lambda a:ciffile.has_key(a),__pycitems)" p[0] += "\nprint 'names in cat -> %s' % `__pycitems`\n" p.parser.special_id[-1].update({p[2]: [p[4],"",False]}) print "%s means %s" % (p[2],p.parser.special_id[-1][p[2]][0]) if p[4] in p.parser.loopable_cats: #loop over another index if len(p)>5: #are provided with index loop_index = p[6] else: loop_index = "__pi%d" % len(p.parser.special_id[-1]) p.parser.special_id[-1][p[2]][1] = loop_index p.parser.special_id[-1][p[2]][2] = True p[0] += "\n"+ "for %s in range(len(ciffile[__pycitems[0]])):" % loop_index else: #have to emit a block which runs once... p[0] += "\n" + "for __noloop in [0]:" if len(p)==9: # do an "if" test before proceeding iftest = "if " + "".join(p[6:9]) + ":" p[0] += "\n " + iftest def p_do_stmt(p): '''do_stmt : do_stmt_head suite''' p[0] = p[1] + add_indent(p[2]) # To translate the dREL do to a for statement, we need to make the # end of the range included in the range def p_do_stmt_head(p): '''do_stmt_head : DO ID "=" expression "," expression | DO ID "=" expression "," expression "," expression ''' print "Do stmt: " + `p[1:]` incr = "1" if len(p)==9: incr = p[8] rangeend = p[6]+"+%s/2" % incr # avoid float expressions else: rangeend = p[6]+"+%s" % incr # because 1/2 = 0 p[0] = "for " + p[2] + " in range(" + p[4] + "," + rangeend + "," + incr + "):" # Statement blocks after with statements do not require indenting so we # undo our indentation def p_with_stmt(p): '''with_stmt : with_head suite''' p[0] = p[2] #outgoing = p.parser.special_id.pop() #outindents = filter(lambda a:a[2],outgoing.values()) #p.parser.indent = p.parser.indent[:len(p.parser.indent)-4*len(outindents)] # Done here to capture the id before processing the suite # A with statement doesn't need any indenting... # We assume a variable 'loopable_cats' is available to us # We have a somewhat complex structure to allow for multiple simultaneous # with statements, although that is not in the standard. We could # probably assume a single packet variable per with statement and # simplify the special_id structure a bit # Note that we allow multiple with statements grouped together (as long # as nothing else separates them) def p_with_head(p): '''with_head : WITH ID AS ID''' # p[0] = "__pycitems = self.names_in_cat('%s')" % p[4] p.parser.special_id.append({p[2]: [p[4],"",False]}) if p[4] in p.parser.loopable_cats: tb_length = len(p.parser.withtable) #generate unique id p.parser.withtable.update({p[4]:"__pi%d" % tb_length}) p.parser.special_id[-1][p[2]][1] = p.parser.withtable[p[4]] print "%s means %s" % (p[2],p.parser.special_id[-1][p[2]][0]) if p.parser.special_id[-1][p[2]][1]: print "%s looped using %s" % (p[2],p.parser.special_id[-1][p[2]][1]) def p_where_stmt(p): '''where_stmt : WHERE expression suite ELSE suite''' pass def p_switch_stmt(p): '''switch_stmt : SWITCH ID open_brace caselist DEFAULT suite close_brace ''' pass def p_caselist(p): '''caselist : CASE target_list suite | caselist CASE target_list suite''' pass def p_funcdef(p): ''' funcdef : FUNCTION ID "(" arglist ")" suite ''' p[0] = "def " + "".join(p[2:6]) + ":" # add some import statements p[0] += "\n" + add_indent("import StarFile,math,numpy") # add a return statement as the last statement of the suite p[0] += "\n" + add_indent(p[6] + 'return ' + p[2] + '\n') def p_arglist(p): ''' arglist : ID ":" list_display | arglist "," ID ":" list_display ''' if len(p) == 4: p[0] = p[1] else: p[0] = p[1] + "," + p[3] def p_error(p): print 'Syntax error at token %s, value %s' % (p.type,p.value) ### Now some helper functions # do indentation: we substitute any "\n" characters in the # input with "\n+4 spaces" def add_indent(instring): import re indented = re.sub("(?m)^"," ",instring) indented = indented.rstrip(" ") #remove extras at end print "Indenting: \n%s\n->\n%s" % (instring,indented) return indented # The following function creates a function. The function # modifies the 'ciffile' argument in place. The pi argument is a # packet index for when we are accessing looped data using a # 'with' statement. Returnname is the variable name for returned # data, and for looped data this should always be "__dreltarget". # See the test file for ways of using this # # The parser data is a two-element list with the first element the text of # the function, and the second element a table of looped values # # Normally this function is called in a context where 'self' is a CifDic # object; for the purposes of testing, we want to be able to remove any # references to dictionary methods and so include the have_sn flag. def make_func(parser_data,funcname,returnname,cat_meth = False,have_sn=True): import re if not returnname: returnname = "__dreltarget" func_text = parser_data[0] # now indent the string noindent = func_text.splitlines() # get the minimum indent and remove empty lines noindent = filter(lambda a:a,noindent) no_spaces = map(lambda a:re.match(r' *',a),noindent) no_spaces = map(lambda a:a.end(),no_spaces) min_spaces = min(no_spaces)+4 # because we add 4 ourselves to everything with_indices = parser_data[1].values() w_i_list = ",".join(with_indices) preamble = "def %s(self,ciffile,%s):\n" % (funcname,w_i_list) preamble += min_spaces*" " + "import StarFile\n" preamble += min_spaces*" " + "import math\n" preamble += min_spaces*" " + "import numpy\n" if have_sn: preamble += min_spaces*" " + "self.switch_numpy(True)\n" if cat_meth: preamble += min_spaces*" " + "%s = {}\n" % returnname indented = map(lambda a:" " + a+"\n",noindent) postamble = "" if have_sn: postamble = " "*min_spaces + "self.switch_numpy(False)\n" postamble += " "*min_spaces + "return %s" % returnname final = preamble + "".join(indented) + postamble return final parser = yacc.yacc() parser.indent = "" parser.special_id=[{}] parser.looped_value = False #Determines with statement construction parser.target_id = None parser.withtable = {} #Table of 'with' packet access info parser.sub_subject="" ./CBFlib-0.9.2.2/Makefile_LINUX_gcc42_DMALLOC0000644000076500007650000020033011603702122016326 0ustar yayayaya ###################################################################### # Makefile - command file for make to create CBFlib # # # # Version 0.9.2 12 Feb 2011 # # # # Paul Ellis and # # Herbert J. Bernstein (yaya@bernstein-plus-sons.com) # # # # (C) Copyright 2006 - 2011 Herbert J. Bernstein # # # ###################################################################### ###################################################################### # # # YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL # # # # ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS # # OF THE LGPL # # # ###################################################################### ########################### GPL NOTICES ############################## # # # This program is free software; you can redistribute it and/or # # modify it under the terms of the GNU General Public License as # # published by the Free Software Foundation; either version 2 of # # (the License, or (at your option) any later version. # # # # This program is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # # GNU General Public License for more details. # # # # You should have received a copy of the GNU General Public License # # along with this program; if not, write to the Free Software # # Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA # # 02111-1307 USA # # # ###################################################################### ######################### LGPL NOTICES ############################### # # # This library is free software; you can redistribute it and/or # # modify it under the terms of the GNU Lesser General Public # # License as published by the Free Software Foundation; either # # version 2.1 of the License, or (at your option) any later version. # # # # This library is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # # Lesser General Public License for more details. # # # # You should have received a copy of the GNU Lesser General Public # # License along with this library; if not, write to the Free # # Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, # # MA 02110-1301 USA # # # ###################################################################### ###################################################################### # # # Stanford University Notices # # for the CBFlib software package that incorporates SLAC software # # on which copyright is disclaimed # # # # This software # # ------------- # # The term "this software", as used in these Notices, refers to # # those portions of the software package CBFlib that were created by # # employees of the Stanford Linear Accelerator Center, Stanford # # University. # # # # Stanford disclaimer of copyright # # -------------------------------- # # Stanford University, owner of the copyright, hereby disclaims its # # copyright and all other rights in this software. Hence, anyone # # may freely use it for any purpose without restriction. # # # # Acknowledgement of sponsorship # # ------------------------------ # # This software was produced by the Stanford Linear Accelerator # # Center, Stanford University, under Contract DE-AC03-76SFO0515 with # # the Department of Energy. # # # # Government disclaimer of liability # # ---------------------------------- # # Neither the United States nor the United States Department of # # Energy, nor any of their employees, makes any warranty, express or # # implied, or assumes any legal liability or responsibility for the # # accuracy, completeness, or usefulness of any data, apparatus, # # product, or process disclosed, or represents that its use would # # not infringe privately owned rights. # # # # Stanford disclaimer of liability # # -------------------------------- # # Stanford University makes no representations or warranties, # # express or implied, nor assumes any liability for the use of this # # software. # # # # Maintenance of notices # # ---------------------- # # In the interest of clarity regarding the origin and status of this # # software, this and all the preceding Stanford University notices # # are to remain affixed to any copy or derivative of this software # # made or distributed by the recipient and are to be affixed to any # # copy of software made or distributed by the recipient that # # contains a copy or derivative of this software. # # # # Based on SLAC Software Notices, Set 4 # # OTT.002a, 2004 FEB 03 # ###################################################################### ###################################################################### # NOTICE # # Creative endeavors depend on the lively exchange of ideas. There # # are laws and customs which establish rights and responsibilities # # for authors and the users of what authors create. This notice # # is not intended to prevent you from using the software and # # documents in this package, but to ensure that there are no # # misunderstandings about terms and conditions of such use. # # # # Please read the following notice carefully. If you do not # # understand any portion of this notice, please seek appropriate # # professional legal advice before making use of the software and # # documents included in this software package. In addition to # # whatever other steps you may be obliged to take to respect the # # intellectual property rights of the various parties involved, if # # you do make use of the software and documents in this package, # # please give credit where credit is due by citing this package, # # its authors and the URL or other source from which you obtained # # it, or equivalent primary references in the literature with the # # same authors. # # # # Some of the software and documents included within this software # # package are the intellectual property of various parties, and # # placement in this package does not in any way imply that any # # such rights have in any way been waived or diminished. # # # # With respect to any software or documents for which a copyright # # exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. # # # # Even though the authors of the various documents and software # # found here have made a good faith effort to ensure that the # # documents are correct and that the software performs according # # to its documentation, and we would greatly appreciate hearing of # # any problems you may encounter, the programs and documents any # # files created by the programs are provided **AS IS** without any * # warranty as to correctness, merchantability or fitness for any # # particular or general use. # # # # THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF # # PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE # # PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS # # OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE # # PROGRAMS OR DOCUMENTS. # ###################################################################### ###################################################################### # # # The IUCr Policy # # for the Protection and the Promotion of the STAR File and # # CIF Standards for Exchanging and Archiving Electronic Data # # # # Overview # # # # The Crystallographic Information File (CIF)[1] is a standard for # # information interchange promulgated by the International Union of # # Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the # # recommended method for submitting publications to Acta # # Crystallographica Section C and reports of crystal structure # # determinations to other sections of Acta Crystallographica # # and many other journals. The syntax of a CIF is a subset of the # # more general STAR File[2] format. The CIF and STAR File approaches # # are used increasingly in the structural sciences for data exchange # # and archiving, and are having a significant influence on these # # activities in other fields. # # # # Statement of intent # # # # The IUCr's interest in the STAR File is as a general data # # interchange standard for science, and its interest in the CIF, # # a conformant derivative of the STAR File, is as a concise data # # exchange and archival standard for crystallography and structural # # science. # # # # Protection of the standards # # # # To protect the STAR File and the CIF as standards for # # interchanging and archiving electronic data, the IUCr, on behalf # # of the scientific community, # # # # # holds the copyrights on the standards themselves, * # # # # owns the associated trademarks and service marks, and * # # # # holds a patent on the STAR File. * # # # These intellectual property rights relate solely to the # # interchange formats, not to the data contained therein, nor to # # the software used in the generation, access or manipulation of # # the data. # # # # Promotion of the standards # # # # The sole requirement that the IUCr, in its protective role, # # imposes on software purporting to process STAR File or CIF data # # is that the following conditions be met prior to sale or # # distribution. # # # # # Software claiming to read files written to either the STAR * # File or the CIF standard must be able to extract the pertinent # # data from a file conformant to the STAR File syntax, or the CIF # # syntax, respectively. # # # # # Software claiming to write files in either the STAR File, or * # the CIF, standard must produce files that are conformant to the # # STAR File syntax, or the CIF syntax, respectively. # # # # # Software claiming to read definitions from a specific data * # dictionary approved by the IUCr must be able to extract any # # pertinent definition which is conformant to the dictionary # # definition language (DDL)[3] associated with that dictionary. # # # # The IUCr, through its Committee on CIF Standards, will assist # # any developer to verify that software meets these conformance # # conditions. # # # # Glossary of terms # # # # [1] CIF: is a data file conformant to the file syntax defined # # at http://www.iucr.org/iucr-top/cif/spec/index.html # # # # [2] STAR File: is a data file conformant to the file syntax # # defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html # # # # [3] DDL: is a language used in a data dictionary to define data # # items in terms of "attributes". Dictionaries currently approved # # by the IUCr, and the DDL versions used to construct these # # dictionaries, are listed at # # http://www.iucr.org/iucr-top/cif/spec/ddl/index.html # # # # Last modified: 30 September 2000 # # # # IUCr Policy Copyright (C) 2000 International Union of # # Crystallography # ###################################################################### # Version string VERSION = 0.9.2 # # Comment out the next line if scratch test files sould be retain # CLEANTESTS = yes # # Definition to get a version of tifflib to support tiff2cbf # TIFF = tiff-3.9.4-rev-6Feb11 TIFFPREFIX = $(PWD) # # Definitions to get a stable version of regex # REGEX = regex-20090805 REGEXDIR = /usr/lib REGEXDEP = # Program to use to retrieve a URL DOWNLOAD = wget # Flag to control symlinks versus copying SLFLAGS = --use_ln # # Program to use to pack shars # SHAR = /usr/bin/shar #SHAR = /usr/local/bin/gshar # # Program to use to create archives # AR = /usr/bin/ar # # Program to use to add an index to an archive # RANLIB = /usr/bin/ranlib # # Program to use to decompress a data file # DECOMPRESS = /usr/bin/bunzip2 # # Program to use to compress a data file # COMPRESS = /usr/bin/bzip2 # # Program to use to generate a signature # SIGNATURE = /usr/bin/openssl dgst -md5 # # Extension for compressed data file (with period) # CEXT = .bz2 # # Extension for signatures of files # SEXT = .md5 # call to time a command #TIME = #TIME = time # # Program to display differences between files # DIFF = diff -u -b # # Program to generate wrapper classes for Python # PYSWIG = swig -python # # Program to generate wrapper classes for Java # JSWIG = swig -java # # Program to generate LaTex and HTML program documentation # NUWEB = nuweb # # Compiler for Java # JAVAC = javac # # Java archiver for compiled classes # JAR = jar # # Java SDK root directory # ifeq ($(JDKDIR),) JDKDIR = /usr/lib/java endif ifneq ($(CBF_DONT_USE_LONG_LONG),) NOLLFLAG = -DCBF_DONT_USE_LONG_LONG else NOLLFLAG = endif # # PYCBF definitions # PYCBFEXT = so PYCBFBOPT = SETUP_PY = setup.py # # Set the compiler and flags # ######################################################### # # Appropriate compiler definitions for Linux # with gcc version 4.2 and DMALLOC # ######################################################### CC = gcc C++ = g++ CFLAGS = -g -O2 -Wall -D_USE_XOPEN_EXTENDED -fno-strict-aliasing -DDMALLOC -DDMALLOC_FUNC_CHECK -I$(HOME)/include F90C = gfortran F90FLAGS = -g -fno-range-check F90LDFLAGS = SOCFLAGS = -fPIC SOLDFLAGS = -shared -Wl,-rpath,$(INSTALLDIR)/lib JAVAINCLUDES = -I$(JDKDIR)/include -I$(JDKDIR)/include/linux LDPREFIX = LD_LIBRARY_PATH=$(SOLIB) EXTRALIBS = -lm -L$(HOME)/lib -ldmalloc M4FLAGS = -Dfcb_bytes_in_rec=131072 TIME = time ifneq ($(NOFORTRAN),) F90C = endif # # Directories # ROOT = . LIB = $(ROOT)/lib SOLIB = $(ROOT)/solib JCBF = $(ROOT)/jcbf JAVADIR = $(ROOT)/java BIN = $(ROOT)/bin SRC = $(ROOT)/src INCLUDE = $(ROOT)/include M4 = $(ROOT)/m4 PYCBF = $(ROOT)/pycbf EXAMPLES = $(ROOT)/examples DECTRIS_EXAMPLES = $(EXAMPLES)/dectris_cbf_template_test DOC = $(ROOT)/doc GRAPHICS = $(ROOT)/html_graphics DATADIRI = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Input DATADIRO = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Output DATADIRS = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only INSTALLDIR = $(HOME) # # URLs from which to retrieve the data directories # DATAURLBASE = http://downloads.sf.net/cbflib/ DATAURLI = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Input.tar.gz DATAURLO = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Output.tar.gz DATAURLS = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz # # URLs from which to retrieve needed external package snapshots # REGEXURL = http://downloads.sf.net/cbflib/$(REGEX).tar.gz TIFFURL = http://downloads.sf.net/cbflib/$(TIFF).tar.gz # # Include directories # INCLUDES = -I$(INCLUDE) -I$(SRC) ###################################################################### # You should not need to make modifications below this line # ###################################################################### # # Suffixes of files to be used or built # .SUFFIXES: .c .o .f90 .m4 .m4.f90: m4 -P $(M4FLAGS) $< > $@ ifneq ($(F90C),) .f90.o: $(F90C) $(F90FLAGS) -c $< -o $@ endif # # Common dependencies # COMMONDEP = Makefile # # Source files # SOURCE = $(SRC)/cbf.c \ $(SRC)/cbf_alloc.c \ $(SRC)/cbf_ascii.c \ $(SRC)/cbf_binary.c \ $(SRC)/cbf_byte_offset.c \ $(SRC)/cbf_canonical.c \ $(SRC)/cbf_codes.c \ $(SRC)/cbf_compress.c \ $(SRC)/cbf_context.c \ $(SRC)/cbf_copy.c \ $(SRC)/cbf_file.c \ $(SRC)/cbf_getopt.c \ $(SRC)/cbf_lex.c \ $(SRC)/cbf_packed.c \ $(SRC)/cbf_predictor.c \ $(SRC)/cbf_read_binary.c \ $(SRC)/cbf_read_mime.c \ $(SRC)/cbf_simple.c \ $(SRC)/cbf_string.c \ $(SRC)/cbf_stx.c \ $(SRC)/cbf_tree.c \ $(SRC)/cbf_uncompressed.c \ $(SRC)/cbf_write.c \ $(SRC)/cbf_write_binary.c \ $(SRC)/cbf_ws.c \ $(SRC)/md5c.c F90SOURCE = $(SRC)/fcb_atol_wcnt.f90 \ $(SRC)/fcb_ci_strncmparr.f90 \ $(SRC)/fcb_exit_binary.f90 \ $(SRC)/fcb_nblen_array.f90 \ $(SRC)/fcb_next_binary.f90 \ $(SRC)/fcb_open_cifin.f90 \ $(SRC)/fcb_packed.f90 \ $(SRC)/fcb_read_bits.f90 \ $(SRC)/fcb_read_byte.f90 \ $(SRC)/fcb_read_image.f90 \ $(SRC)/fcb_read_line.f90 \ $(SRC)/fcb_read_xds_i2.f90 \ $(SRC)/fcb_skip_whitespace.f90 \ $(EXAMPLES)/test_fcb_read_image.f90 \ $(EXAMPLES)/test_xds_binary.f90 # # Header files # HEADERS = $(INCLUDE)/cbf.h \ $(INCLUDE)/cbf_alloc.h \ $(INCLUDE)/cbf_ascii.h \ $(INCLUDE)/cbf_binary.h \ $(INCLUDE)/cbf_byte_offset.h \ $(INCLUDE)/cbf_canonical.h \ $(INCLUDE)/cbf_codes.h \ $(INCLUDE)/cbf_compress.h \ $(INCLUDE)/cbf_context.h \ $(INCLUDE)/cbf_copy.h \ $(INCLUDE)/cbf_file.h \ $(INCLUDE)/cbf_getopt.h \ $(INCLUDE)/cbf_lex.h \ $(INCLUDE)/cbf_packed.h \ $(INCLUDE)/cbf_predictor.h \ $(INCLUDE)/cbf_read_binary.h \ $(INCLUDE)/cbf_read_mime.h \ $(INCLUDE)/cbf_simple.h \ $(INCLUDE)/cbf_string.h \ $(INCLUDE)/cbf_stx.h \ $(INCLUDE)/cbf_tree.h \ $(INCLUDE)/cbf_uncompressed.h \ $(INCLUDE)/cbf_write.h \ $(INCLUDE)/cbf_write_binary.h \ $(INCLUDE)/cbf_ws.h \ $(INCLUDE)/global.h \ $(INCLUDE)/cbff.h \ $(INCLUDE)/md5.h # # m4 macro files # M4FILES = $(M4)/fcblib_defines.m4 \ $(M4)/fcb_exit_binary.m4 \ $(M4)/fcb_next_binary.m4 \ $(M4)/fcb_open_cifin.m4 \ $(M4)/fcb_packed.m4 \ $(M4)/fcb_read_bits.m4 \ $(M4)/fcb_read_image.m4 \ $(M4)/fcb_read_xds_i2.m4 \ $(M4)/test_fcb_read_image.m4 \ $(M4)/test_xds_binary.m4 # # Documentation files # DOCUMENTS = $(DOC)/CBFlib.html \ $(DOC)/CBFlib.txt \ $(DOC)/CBFlib_NOTICES.html \ $(DOC)/CBFlib_NOTICES.txt \ $(DOC)/ChangeLog \ $(DOC)/ChangeLog.html \ $(DOC)/MANIFEST \ $(DOC)/gpl.txt $(DOC)/lgpl.txt # # HTML Graphics files # JPEGS = $(GRAPHICS)/CBFbackground.jpg \ $(GRAPHICS)/CBFbig.jpg \ $(GRAPHICS)/CBFbutton.jpg \ $(GRAPHICS)/cbflibbackground.jpg \ $(GRAPHICS)/cbflibbig.jpg \ $(GRAPHICS)/cbflibbutton.jpg \ $(GRAPHICS)/cifhome.jpg \ $(GRAPHICS)/iucrhome.jpg \ $(GRAPHICS)/noticeButton.jpg # # Default: instructions # default: @echo ' ' @echo '***************************************************************' @echo ' ' @echo ' PLEASE READ README and doc/CBFlib_NOTICES.txt' @echo ' ' @echo ' Before making the CBF library and example programs, check' @echo ' that the C compiler name and flags are correct:' @echo ' ' @echo ' The current values are:' @echo ' ' @echo ' $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG)' @echo ' ' @echo ' Before installing the CBF library and example programs, check' @echo ' that the install directory is correct:' @echo ' ' @echo ' The current value :' @echo ' ' @echo ' $(INSTALLDIR) ' @echo ' ' @echo ' To compile the CBF library and example programs type:' @echo ' ' @echo ' make clean' @echo ' make all' @echo ' ' @echo ' To compile the CBF library as a shared object library, type:' @echo ' ' @echo ' make shared' @echo ' ' @echo ' To compile the Java wrapper classes for CBF library, type:' @echo ' ' @echo ' make javawrapper' @echo ' ' @echo ' To run a set of tests type:' @echo ' ' @echo ' make tests' @echo ' ' @echo ' To run some java tests type:' @echo ' ' @echo ' make javatests' @echo ' ' @echo ' The tests assume that several data files are in the directories' @echo ' $(DATADIRI) and $(DATADIRO)' @echo ' ' @echo ' Alternatively tests can be run comparing MD5 signatures only by' @echo ' ' @echo ' make tests_sigs_only' @echo ' ' @echo ' These signature only tests save space and download time by' @echo ' assuming that input data files and the output signatures' @echo ' are in the directories' @echo ' $(DATADIRI) and $(DATADIRS)' @echo ' ' @echo ' These directory can be obtained from' @echo ' ' @echo ' $(DATAURLI) ' @echo ' $(DATAURLO) ' @echo ' $(DATAURLS) ' @echo ' ' @echo ' To clean up the directories type:' @echo ' ' @echo ' make clean' @echo ' ' @echo ' To install the library and binaries type:' @echo ' ' @echo ' make install' @echo ' ' @echo '***************************************************************' @echo ' ' # # Compile the library and examples # all:: $(BIN) $(SOURCE) $(F90SOURCE) $(HEADERS) \ symlinksdone $(REGEXDEP) \ $(LIB)/libcbf.a \ $(LIB)/libfcb.a \ $(LIB)/libimg.a \ $(BIN)/adscimg2cbf \ $(BIN)/cbf2adscimg \ $(BIN)/convert_image \ $(BIN)/convert_minicbf \ $(BIN)/sequence_match \ $(BIN)/arvai_test \ $(BIN)/makecbf \ $(BIN)/img2cif \ $(BIN)/adscimg2cbf \ $(BIN)/cif2cbf \ $(BIN)/testcell \ $(BIN)/cif2c \ $(BIN)/testreals \ $(BIN)/testflat \ $(BIN)/testflatpacked ifneq ($(F90C),) all:: $(BIN)/test_xds_binary \ $(BIN)/test_fcb_read_image endif shared: $(SOLIB)/libcbf.so $(SOLIB)/libfcb.so $(SOLIB)/libimg.so javawrapper: shared $(JCBF) $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf_wrap.so ifneq ($(CBFLIB_USE_PYCIFRW),) PYCIFRWDEF = -Dcbf_use_pycifrw=yes else PYCIFRWDEF = endif Makefiles: Makefile \ Makefile_LINUX \ Makefile_LINUX_64 \ Makefile_LINUX_gcc42 \ Makefile_LINUX_DMALLOC \ Makefile_LINUX_gcc42_DMALLOC \ Makefile_OSX \ Makefile_OSX_gcc42 \ Makefile_OSX_gcc42_DMALLOC \ Makefile_AIX \ Makefile_MINGW \ Makefile_IRIX_gcc Makefile_LINUX: $(M4)/Makefile.m4 -cp Makefile_LINUX Makefile_LINUX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX $(M4)/Makefile.m4 > Makefile_LINUX Makefile_LINUX_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_LINUX Makefile_LINUX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_DMALLOC $(M4)/Makefile.m4 > Makefile_LINUX_DMALLOC Makefile_LINUX_64: $(M4)/Makefile.m4 -cp Makefile_LINUX_64 Makefile_LINUX_64_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_64 $(M4)/Makefile.m4 > Makefile_LINUX_64 Makefile_LINUX_gcc42: $(M4)/Makefile.m4 -cp Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_gcc42 $(M4)/Makefile.m4 > Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_gcc42_DMALLOC $(M4)/Makefile.m4 > Makefile_LINUX_gcc42_DMALLOC Makefile_OSX: $(M4)/Makefile.m4 -cp Makefile_OSX Makefile_OSX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX $(M4)/Makefile.m4 > Makefile_OSX Makefile_OSX_gcc42: $(M4)/Makefile.m4 -cp Makefile_OSX_gcc42 Makefile_OSX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX_gcc42 $(M4)/Makefile.m4 > Makefile_OSX_gcc42 Makefile_OSX_gcc42_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_OSX_gcc42 Makefile_OSX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX_gcc42_DMALLOC $(M4)/Makefile.m4 > Makefile_OSX_gcc42_DMALLOC Makefile_AIX: $(M4)/Makefile.m4 -cp Makefile_AIX Makefile_AIX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=AIX $(M4)/Makefile.m4 > Makefile_AIX Makefile_MINGW: $(M4)/Makefile.m4 -cp Makefile_MINGW Makefile_MINGW_old m4 -P $(PYCIFRWDEF) -Dcbf_system=MINGW $(M4)/Makefile.m4 > Makefile_MINGW Makefile_IRIX_gcc: $(M4)/Makefile.m4 -cp Makefile_IRIX_gcc Makefile_IRIX_gcc_old m4 -P $(PYCIFREDEF) -Dcbf_system=IRIX_gcc $(M4)/Makefile.m4 > Makefile_IRIX_gcc Makefile: $(M4)/Makefile.m4 -cp Makefile Makefile_old m4 -P $(PYCIFRWDEF) -Dcbf_system=default $(M4)/Makefile.m4 > Makefile symlinksdone: chmod a+x .symlinks chmod a+x .undosymlinks chmod a+x doc/.symlinks chmod a+x doc/.undosymlinks chmod a+x libtool/.symlinks chmod a+x libtool/.undosymlinks ./.symlinks $(SLFLAGS) touch symlinksdone install: all $(INSTALLDIR) $(INSTALLDIR)/lib $(INSTALLDIR)/bin \ $(INSTALLDIR)/include $(INSTALLDIR)/include/cbflib \ $(PYSOURCE) -chmod -R 755 $(INSTALLDIR)/include/cbflib -chmod 755 $(INSTALLDIR)/lib/libcbf.a -cp $(INSTALLDIR)/lib/libcbf.a $(INSTALLDIR)/lib/libcbf_old.a cp $(LIB)/libcbf.a $(INSTALLDIR)/lib/libcbf.a -cp $(INSTALLDIR)/lib/libimg.a $(INSTALLDIR)/lib/libimg_old.a cp $(LIB)/libimg.a $(INSTALLDIR)/lib/libimg.a -cp $(INSTALLDIR)/bin/adscimg2cbf $(INSTALLDIR)/bin/adscimg2cbf_old cp $(BIN)/adscimg2cbf $(INSTALLDIR)/bin/adscimg2cbf -cp $(INSTALLDIR)/bin/cbf2adscimg $(INSTALLDIR)/bin/cbf2adscimg_old cp $(BIN)/cbf2adscimg $(INSTALLDIR)/bin/cbf2adscimg -cp $(INSTALLDIR)/bin/convert_image $(INSTALLDIR)/bin/convert_image_old cp $(BIN)/convert_image $(INSTALLDIR)/bin/convert_image -cp $(INSTALLDIR)/bin/convert_minicbf $(INSTALLDIR)/bin/convert_minicbf_old cp $(BIN)/convert_minicbf $(INSTALLDIR)/bin/convert_minicbf -cp $(INSTALLDIR)/bin/makecbf $(INSTALLDIR)/bin/makecbf_old cp $(BIN)/makecbf $(INSTALLDIR)/bin/makecbf -cp $(INSTALLDIR)/bin/img2cif $(INSTALLDIR)/bin/img2cif_old cp $(BIN)/img2cif $(INSTALLDIR)/bin/img2cif -cp $(INSTALLDIR)/bin/cif2cbf $(INSTALLDIR)/bin/cif2cbf_old cp $(BIN)/cif2cbf $(INSTALLDIR)/bin/cif2cbf -cp $(INSTALLDIR)/bin/sequence_match $(INSTALLDIR)/bin/sequence_match_old cp $(BIN)/sequence_match $(INSTALLDIR)/bin/sequence_match -cp $(INSTALLDIR)/bin/arvai_test $(INSTALLDIR)/bin/arvai_test_old cp $(BIN)/arvai_test $(INSTALLDIR)/bin/arvai_test -cp $(INSTALLDIR)/bin/cif2c $(INSTALLDIR)/bin/cif2c_old cp $(BIN)/cif2c $(INSTALLDIR)/bin/cif2c -cp $(INSTALLDIR)/bin/testreals $(INSTALLDIR)/bin/testreals_old cp $(BIN)/testreals $(INSTALLDIR)/bin/testreals -cp $(INSTALLDIR)/bin/testflat $(INSTALLDIR)/bin/testflat_old cp $(BIN)/testflat $(INSTALLDIR)/bin/testflat -cp $(INSTALLDIR)/bin/testflatpacked $(INSTALLDIR)/bin/testflatpacked_old cp $(BIN)/testflatpacked $(INSTALLDIR)/bin/testflatpacked chmod -R 755 $(INSTALLDIR)/include/cbflib -rm -rf $(INSTALLDIR)/include/cbflib_old -cp -r $(INSTALLDIR)/include/cbflib $(INSTALLDIR)/include/cbflib_old -rm -rf $(INSTALLDIR)/include/cbflib cp -r $(INCLUDE) $(INSTALLDIR)/include/cbflib chmod 644 $(INSTALLDIR)/lib/libcbf.a chmod 755 $(INSTALLDIR)/bin/convert_image chmod 755 $(INSTALLDIR)/bin/convert_minicbf chmod 755 $(INSTALLDIR)/bin/makecbf chmod 755 $(INSTALLDIR)/bin/img2cif chmod 755 $(INSTALLDIR)/bin/cif2cbf chmod 755 $(INSTALLDIR)/bin/sequence_match chmod 755 $(INSTALLDIR)/bin/arvai_test chmod 755 $(INSTALLDIR)/bin/cif2c chmod 755 $(INSTALLDIR)/bin/testreals chmod 755 $(INSTALLDIR)/bin/testflat chmod 755 $(INSTALLDIR)/bin/testflatpacked chmod 644 $(INSTALLDIR)/include/cbflib/*.h # # REGEX # ifneq ($(REGEXDEP),) $(REGEXDEP): $(REGEX) (cd $(REGEX); ./configure; make install) endif $(REGEX): $(DOWNLOAD) $(REGEXURL) tar -xvf $(REGEX).tar.gz -rm $(REGEX).tar.gz # # TIFF # $(TIFF): $(DOWNLOAD) $(TIFFURL) tar -xvf $(TIFF).tar.gz -rm $(TIFF).tar.gz (cd $(TIFF); ./configure --prefix=$(TIFFPREFIX); make install) # # Directories # $(INSTALLDIR): mkdir -p $(INSTALLDIR) $(INSTALLDIR)/lib: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/lib $(INSTALLDIR)/bin: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/bin $(INSTALLDIR)/include: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/include $(INSTALLDIR)/include/cbflib: $(INSTALLDIR)/include mkdir -p $(INSTALLDIR)/include/cbflib $(LIB): mkdir $@ $(BIN): mkdir $@ $(SOLIB): mkdir $@ $(JCBF): mkdir $@ # # Parser # $(SRC)/cbf_stx.c: $(SRC)/cbf.stx.y bison $(SRC)/cbf.stx.y -o $(SRC)/cbf.stx.tab.c -d mv $(SRC)/cbf.stx.tab.c $(SRC)/cbf_stx.c mv $(SRC)/cbf.stx.tab.h $(INCLUDE)/cbf_stx.h # # CBF library # $(LIB)/libcbf.a: $(SOURCE) $(HEADERS) $(COMMONDEP) $(LIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG) $(INCLUDES) $(WARNINGS) -c $(SOURCE) $(AR) cr $@ *.o mv *.o $(LIB) ifneq ($(RANLIB),) $(RANLIB) $@ endif $(SOLIB)/libcbf.so: $(SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(SOURCE) $(CC) -o $@ *.o $(SOLDFLAGS) $(EXTRALIBS) rm *.o # # IMG library # $(LIB)/libimg.a: $(EXAMPLES)/img.c $(HEADERS) $(COMMONDEP) $(LIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) -c $(EXAMPLES)/img.c $(AR) cr $@ img.o ifneq ($(RANLIB),) $(RANLIB) $@ endif rm img.o $(SOLIB)/libimg.so: $(SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(EXAMPLES)/img.c $(CC) -o $@ img.o $(SOLDFLAGS) rm img.o # # CBF and IMG libraries # CBF_IMG_LIBS: $(LIB)/libcbf.a $(LIB)/libimg.a # # FCB library # $(LIB)/libfcb.a: $(F90SOURCE) $(COMMONDEP) $(LIB) ifneq ($(F90C),) $(F90C) $(F90FLAGS) -c $(F90SOURCE) $(AR) cr $@ *.o ifneq ($(RANLIB),) $(RANLIB) $@ endif rm *.o else echo "Define F90C to build $(LIB)/libfcb.a" endif $(SOLIB)/libfcb.so: $(F90SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) ifneq ($(F90C),) $(F90C) $(F90FLAGS) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(F90SOURCE) $(F90C) $(F90FLAGS) -o $@ *.o $(SOLDFLAGS) rm *.o else echo "Define F90C to build $(SOLIB)/libfcb.so" endif # # Python bindings # $(PYCBF)/_pycbf.$(PYCBFEXT): $(PYCBF) $(LIB)/libcbf.a \ $(PYCBF)/$(SETUP_PY) \ $(LIB)/libfcb.a \ $(LIB)/libimg.a \ $(PYCBF)/pycbf.i \ $(PYCBF)/cbfhandlewrappers.i \ $(PYCBF)/cbfdetectorwrappers.i \ $(PYCBF)/cbfgenericwrappers.i \ $(PYCBF)/cbfgoniometerwrappers.i (cd $(PYCBF); python $(SETUP_PY) build $(PYCBFBOPT); cp build/lib.*/_pycbf.$(PYCBFEXT) .) $(PYCBF)/setup.py: $(M4)/setup_py.m4 (m4 -P -Dregexlib=NOREGEXLIB -Dregexlibdir=NOREGEXLIBDIR $(M4)/setup_py.m4 > $@) $(PYCBF)/setup_MINGW.py: m4/setup_py.m4 (m4 -P -Dregexlib=regex -Dregexlibdir=$(REGEXDIR) $(M4)/setup_py.m4 > $@) $(LIB)/_pycbf.$(PYCBFEXT): $(PYCBF)/_pycbf.$(PYCBFEXT) cp $(PYCBF)/_pycbf.$(PYCBFEXT) $(LIB)/_pycbf.$(PYCBFEXT) $(PYCBF)/pycbf.pdf: $(PYCBF)/pycbf.w (cd $(PYCBF); \ $(NUWEB) pycbf; \ latex pycbf; \ $(NUWEB) pycbf; \ latex pycbf; \ dvipdfm pycbf ) $(PYCBF)/CBFlib.txt: $(DOC)/CBFlib.html links -dump $(DOC)/CBFlib.html > $(PYCBF)/CBFlib.txt $(PYCBF)/cbfhandlewrappers.i \ $(PYCBF)/cbfdetectorwrappers.i \ $(PYCBF)/cbfgenericwrappers.i \ $(PYCBF)/cbfgoniometerwrappers.i: $(PYCBF)/CBFlib.txt $(PYCBF)/make_pycbf.py (cd $(PYCBF); python make_pycbf.py; $(PYSWIG) pycbf.i; python setup.py build) # # Java bindings # $(JCBF)/cbflib-$(VERSION).jar: $(JCBF) $(JCBF)/jcbf.i $(JSWIG) -I$(INCLUDE) -package org.iucr.cbflib -outdir $(JCBF) $(JCBF)/jcbf.i $(JAVAC) -d . $(JCBF)/*.java $(JAR) cf $@ org $(SOLIB)/libcbf_wrap.so: $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf.so $(CC) $(CFLAGS) $(NOLLFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) $(JAVAINCLUDES) -c $(JCBF)/jcbf_wrap.c $(CC) -o $@ jcbf_wrap.o $(SOLDFLAGS) -L$(SOLIB) -lcbf rm jcbf_wrap.o # # F90SOURCE # $(SRC)/fcb_exit_binary.f90: $(M4)/fcb_exit_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_exit_binary.m4) > $(SRC)/fcb_exit_binary.f90 $(SRC)/fcb_next_binary.f90: $(M4)/fcb_next_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_next_binary.m4) > $(SRC)/fcb_next_binary.f90 $(SRC)/fcb_open_cifin.f90: $(M4)/fcb_open_cifin.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_open_cifin.m4) > $(SRC)/fcb_open_cifin.f90 $(SRC)/fcb_packed.f90: $(M4)/fcb_packed.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_packed.m4) > $(SRC)/fcb_packed.f90 $(SRC)/fcb_read_bits.f90: $(M4)/fcb_read_bits.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_bits.m4) > $(SRC)/fcb_read_bits.f90 $(SRC)/fcb_read_image.f90: $(M4)/fcb_read_image.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_image.m4) > $(SRC)/fcb_read_image.f90 $(SRC)/fcb_read_xds_i2.f90: $(M4)/fcb_read_xds_i2.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_xds_i2.m4) > $(SRC)/fcb_read_xds_i2.f90 $(EXAMPLES)/test_fcb_read_image.f90: $(M4)/test_fcb_read_image.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) test_fcb_read_image.m4) > $(EXAMPLES)/test_fcb_read_image.f90 $(EXAMPLES)/test_xds_binary.f90: $(M4)/test_xds_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) test_xds_binary.m4) > $(EXAMPLES)/test_xds_binary.f90 # # convert_image example program # $(BIN)/convert_image: $(LIB)/libcbf.a $(EXAMPLES)/convert_image.c $(EXAMPLES)/img.c \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/convert_image.c $(EXAMPLES)/img.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # convert_minicbf example program # $(BIN)/convert_minicbf: $(LIB)/libcbf.a $(EXAMPLES)/convert_minicbf.c \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/convert_minicbf.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # makecbf example program # $(BIN)/makecbf: $(LIB)/libcbf.a $(EXAMPLES)/makecbf.c $(LIB)/libimg.a $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/makecbf.c -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # adscimg2cbf example program # $(BIN)/adscimg2cbf: $(LIB)/libcbf.a $(EXAMPLES)/adscimg2cbf.c $(EXAMPLES)/adscimg2cbf_sub.c $(CC) $(CFLAGS) $(NOLLFLAG) -D_SVID_SOURCE $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/adscimg2cbf.c $(EXAMPLES)/adscimg2cbf_sub.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # cbf2adscimg example program # $(BIN)/cbf2adscimg: $(LIB)/libcbf.a $(EXAMPLES)/cbf2adscimg.c $(EXAMPLES)/cbf2adscimg_sub.c $(CC) $(CFLAGS) $(NOLLFLAG) -D_SVID_SOURCE $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cbf2adscimg.c $(EXAMPLES)/cbf2adscimg_sub.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # changtestcompression example program # $(BIN)/changtestcompression: $(LIB)/libcbf.a $(EXAMPLES)/changtestcompression.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/changtestcompression.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # img2cif example program # $(BIN)/img2cif: $(LIB)/libcbf.a $(EXAMPLES)/img2cif.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOTPINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/img2cif.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # cif2cbf example program # $(BIN)/cif2cbf: $(LIB)/libcbf.a $(EXAMPLES)/cif2cbf.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cif2cbf.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # dectris cbf_template_t program # $(BIN)/cbf_template_t: $(DECTRIS_EXAMPLES)/cbf_template_t.c \ $(DECTRIS_EXAMPLES)/mx_cbf_t_extras.h \ $(DECTRIS_EXAMPLES)/mx_parms.h $(CC) $(CFLAGS) $(NOLLFLAG) -I $(DECTRIS_EXAMPLES) $(WARNINGS) \ $(DECTRIS_EXAMPLES)/cbf_template_t.c -o $@ # # testcell example program # $(BIN)/testcell: $(LIB)/libcbf.a $(EXAMPLES)/testcell.C $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testcell.C -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # cif2c example program # $(BIN)/cif2c: $(LIB)/libcbf.a $(EXAMPLES)/cif2c.c $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cif2c.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # sauter_test example program # $(BIN)/sauter_test: $(LIB)/libcbf.a $(EXAMPLES)/sauter_test.C $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/sauter_test.C -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # sequence_match example program # $(BIN)/sequence_match: $(LIB)/libcbf.a $(EXAMPLES)/sequence_match.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/sequence_match.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # tiff2cbf example program # $(BIN)/tiff2cbf: $(LIB)/libcbf.a $(EXAMPLES)/tiff2cbf.c \ $(GOPTLIB) $(GOPTINC) $(TIFF) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ -I$(TIFFPREFIX)/include $(EXAMPLES)/tiff2cbf.c $(GOPTLIB) -L$(LIB) \ -lcbf -L$(TIFFPREFIX)/lib -ltiff $(EXTRALIBS) -limg -o $@ # # Andy Arvai's buffered read test program # $(BIN)/arvai_test: $(LIB)/libcbf.a $(EXAMPLES)/arvai_test.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/arvai_test.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # testreals example program # $(BIN)/testreals: $(LIB)/libcbf.a $(EXAMPLES)/testreals.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testreals.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testflat example program # $(BIN)/testflat: $(LIB)/libcbf.a $(EXAMPLES)/testflat.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testflat.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testflatpacked example program # $(BIN)/testflatpacked: $(LIB)/libcbf.a $(EXAMPLES)/testflatpacked.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testflatpacked.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ ifneq ($(F90C),) # # test_xds_binary example program # $(BIN)/test_xds_binary: $(LIB)/libfcb.a $(EXAMPLES)/test_xds_binary.f90 $(F90C) $(F90FLAGS) $(F90LDFLAGS) $(EXAMPLES)/test_xds_binary.f90 \ -L$(LIB) -lfcb -o $@ # # test_fcb_read_image example program # $(BIN)/test_fcb_read_image: $(LIB)/libfcb.a $(EXAMPLES)/test_fcb_read_image.f90 $(F90C) $(F90FLAGS) $(F90LDFLAGS) $(EXAMPLES)/test_fcb_read_image.f90 \ -L$(LIB) -lfcb -o $@ endif # # testcbf (C) # $(BIN)/ctestcbf: $(EXAMPLES)/testcbf.c $(LIB)/libcbf.a $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testcbf.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testcbf (Java) # $(BIN)/testcbf.class: $(EXAMPLES)/testcbf.java $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf_wrap.so $(JAVAC) -cp $(JCBF)/cbflib-$(VERSION).jar -d $(BIN) $(EXAMPLES)/testcbf.java # # Data files for tests # $(DATADIRI): (cd ..; $(DOWNLOAD) $(DATAURLI)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Input.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Input.tar.gz) $(DATADIRO): (cd ..; $(DOWNLOAD) $(DATAURLO)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Output.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Output.tar.gz) $(DATADIRS): (cd ..; $(DOWNLOAD) $(DATAURLS)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz) # Input Data Files TESTINPUT_BASIC = example.mar2300 DATADIRI_INPUT_BASIC = $(DATADIRI)/example.mar2300$(CEXT) TESTINPUT_EXTRA = 9ins.cif mb_LP_1_001.img insulin_pilatus6m.cbf testrealin.cbf \ testflatin.cbf testflatpackedin.cbf XRD1621.tif DATADIRI_INPUT_EXTRA = $(DATADIRI)/9ins.cif$(CEXT) $(DATADIRI)/mb_LP_1_001.img$(CEXT) \ $(DATADIRI)/insulin_pilatus6m.cbf$(CEXT) $(DATADIRI)/testrealin.cbf$(CEXT) \ $(DATADIRI)/testflatin.cbf$(CEXT) $(DATADIRI)/testflatpackedin.cbf$(CEXT) \ $(DATADIRI)/XRD1621.tif$(CEXT) # Output Data Files TESTOUTPUT = adscconverted_flat_orig.cbf \ adscconverted_orig.cbf converted_flat_orig.cbf converted_orig.cbf \ insulin_pilatus6mconverted_orig.cbf \ mb_LP_1_001_orig.cbf testcell_orig.prt \ test_xds_bin_testflatout_orig.out \ test_xds_bin_testflatpackedout_orig.out test_fcb_read_testflatout_orig.out \ test_fcb_read_testflatpackedout_orig.out \ XRD1621_orig.cbf XRD1621_I4encbC100_orig.cbf NEWTESTOUTPUT = adscconverted_flat.cbf \ adscconverted.cbf converted_flat.cbf converted.cbf \ insulin_pilatus6mconverted.cbf \ mb_LP_1_001.cbf testcell.prt \ test_xds_bin_testflatout.out \ test_xds_bin_testflatpackedout.out test_fcb_read_testflatout.out \ test_fcb_read_testflatpackedout.out \ XRD1621.cbf XRD1621_I4encbC100.cbf DATADIRO_OUTPUT = $(DATADIRO)/adscconverted_flat_orig.cbf$(CEXT) \ $(DATADIRO)/adscconverted_orig.cbf$(CEXT) \ $(DATADIRO)/converted_flat_orig.cbf$(CEXT) \ $(DATADIRO)/converted_orig.cbf$(CEXT) \ $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(CEXT) \ $(DATADIRO)/mb_LP_1_001_orig.cbf$(CEXT) \ $(DATADIRO)/testcell_orig.prt$(CEXT) \ $(DATADIRO)/test_xds_bin_testflatout_orig.out$(CEXT) \ $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(CEXT) \ $(DATADIRO)/test_fcb_read_testflatout_orig.out$(CEXT) \ $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(CEXT) \ $(DATADIRO)/XRD1621_orig.cbf$(CEXT) \ $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(CEXT) DATADIRO_OUTPUT_SIGNATURES = $(DATADIRO)/adscconverted_flat_orig.cbf$(SEXT) \ $(DATADIRO)/adscconverted_orig.cbf$(SEXT) \ $(DATADIRO)/converted_flat_orig.cbf$(SEXT) \ $(DATADIRO)/converted_orig.cbf$(SEXT) \ $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(SEXT) \ $(DATADIRO)/mb_LP_1_001_orig.cbf$(SEXT) \ $(DATADIRO)/testcell_orig.prt$(SEXT) \ $(DATADIRO)/test_xds_bin_testflatout_orig.out$(SEXT) \ $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(SEXT) \ $(DATADIRO)/test_fcb_read_testflatout_orig.out$(SEXT) \ $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(SEXT) \ $(DATADIRO)/XRD1621_orig.cbf$(SEXT) \ $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(SEXT) # Output Data File Signatures TESTOUTPUTSIGS = adscconverted_flat_orig.cbf$(SEXT) \ adscconverted_orig.cbf$(SEXT) converted_flat_orig.cbf$(SEXT) converted_orig.cbf$(SEXT) \ insulin_pilatus6mconverted_orig.cbf$(SEXT) \ mb_LP_1_001_orig.cbf$(SEXT) testcell_orig.prt$(SEXT) \ test_xds_bin_testflatout_orig.out$(SEXT) \ test_xds_bin_testflatpackedout_orig.out$(SEXT) test_fcb_read_testflatout_orig.out$(SEXT) \ test_fcb_read_testflatpackedout_orig.out$(SEXT) \ XRD1621_orig.cbf$(SEXT) DATADIRS_OUTPUT_SIGNATURES = $(DATADIRS)/adscconverted_flat_orig.cbf$(SEXT) \ $(DATADIRS)/adscconverted_orig.cbf$(SEXT) \ $(DATADIRS)/converted_flat_orig.cbf$(SEXT) \ $(DATADIRS)/converted_orig.cbf$(SEXT) \ $(DATADIRS)/insulin_pilatus6mconverted_orig.cbf$(SEXT) \ $(DATADIRS)/mb_LP_1_001_orig.cbf$(SEXT) \ $(DATADIRS)/testcell_orig.prt$(SEXT) \ $(DATADIRS)/test_xds_bin_testflatout_orig.out$(SEXT) \ $(DATADIRS)/test_xds_bin_testflatpackedout_orig.out$(SEXT) \ $(DATADIRS)/test_fcb_read_testflatout_orig.out$(SEXT) \ $(DATADIRS)/test_fcb_read_testflatpackedout_orig.out$(SEXT) \ $(DATADIRS)/XRD1621_orig.cbf$(SEXT) \ $(DATADIRS)/XRD1621_I4encbC100_orig.cbf$(SEXT) # Fetch Input Data Files $(TESTINPUT_BASIC): $(DATADIRI) $(DATADIRI_INPUT_BASIC) $(DECOMPRESS) < $(DATADIRI)/$@$(CEXT) > $@ cp $(DATADIRI)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) $(TESTINPUT_EXTRA): $(DATADIRI) $(DATADIRI_INPUT_EXTRA) $(DECOMPRESS) < $(DATADIRI)/$@$(CEXT) > $@ cp $(DATADIRI)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) # Fetch Output Data Files and Signatures $(TESTOUTPUT): $(DATADIRO) $(DATADIRO_OUTPUT) $(DATADIRO_OUTPUT_SIGNATURES) $(DECOMPRESS) < $(DATADIRO)/$@$(CEXT) > $@ cp $(DATADIRO)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) # Fetch Output Data File Signatures $(TESTOUTPUTSIGS): $(DATADIRS) $(DATADIRS_OUTPUT_SIGNATURES) cp $(DATADIRS)/$@ $@ # # Tests # tests: $(LIB) $(BIN) symlinksdone basic extra dectristests pycbftests tests_sigs_only: $(LIB) $(BIN) symlinksdone basic extra_sigs_only restore_output: $(NEWTESTOUTPUT) $(DATADIRO) $(SIGNATURE) < adscconverted_flat.cbf > $(DATADIRO)/adscconverted_flat_orig.cbf$(SEXT) $(SIGNATURE) < adscconverted.cbf > $(DATADIRO)/adscconverted_orig.cbf$(SEXT) $(SIGNATURE) < converted_flat.cbf > $(DATADIRO)/converted_flat_orig.cbf$(SEXT) $(SIGNATURE) < converted.cbf > $(DATADIRO)/converted_orig.cbf$(SEXT) $(SIGNATURE) < insulin_pilatus6mconverted.cbf > $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(SEXT) $(SIGNATURE) < mb_LP_1_001.cbf$ > $(DATADIRO)/mb_LP_1_001_orig.cbf$(SEXT) $(SIGNATURE) < testcell.prt > $(DATADIRO)/testcell_orig.prt$(SEXT) $(SIGNATURE) < test_xds_bin_testflatout.out > $(DATADIRO)/test_xds_bin_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_xds_bin_testflatpackedout.out > $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatout.out > $(DATADIRO)/test_fcb_read_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatpackedout.out > $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < XRD1621.cbf > $(DATADIRO)/XRD1621_orig.cbf$(SEXT) $(SIGNATURE) < XRD1621_I4encbC100.cbf > $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(SEXT) $(COMPRESS) < adscconverted_flat.cbf > $(DATADIRO)/adscconverted_flat_orig.cbf$(CEXT) $(COMPRESS) < adscconverted.cbf > $(DATADIRO)/adscconverted_orig.cbf$(CEXT) $(COMPRESS) < converted_flat.cbf > $(DATADIRO)/converted_flat_orig.cbf$(CEXT) $(COMPRESS) < converted.cbf > $(DATADIRO)/converted_orig.cbf$(CEXT) $(COMPRESS) < insulin_pilatus6mconverted.cbf > $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(CEXT) $(COMPRESS) < mb_LP_1_001.cbf$ > $(DATADIRO)/mb_LP_1_001_orig.cbf$(CEXT) $(COMPRESS) < testcell.prt > $(DATADIRO)/testcell_orig.prt$(CEXT) $(COMPRESS) < test_xds_bin_testflatout.out > $(DATADIRO)/test_xds_bin_testflatout_orig.out$(CEXT) $(COMPRESS) < test_xds_bin_testflatpackedout.out > $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(CEXT) $(COMPRESS) < test_fcb_read_testflatout.out > $(DATADIRO)/test_fcb_read_testflatout_orig.out$(CEXT) $(COMPRESS) < test_fcb_read_testflatpackedout.out > $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(CEXT) $(COMPRESS) < XRD1621.cbf > $(DATADIRO)/XRD1621_orig.cbf$(CEXT) $(COMPRESS) < XRD1621_I4encbC100.cbf > $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(CEXT) restore_sigs_only: $(NEWTESTOUTPUT) $(DATADIRS) $(SIGNATURE) < adscconverted_flat.cbf > $(DATADIRS)/adscconverted_flat_orig.cbf$(SEXT) $(SIGNATURE) < adscconverted.cbf > $(DATADIRS)/adscconverted_orig.cbf$(SEXT) $(SIGNATURE) < converted_flat.cbf > $(DATADIRS)/converted_flat_orig.cbf$(SEXT) $(SIGNATURE) < converted.cbf > $(DATADIRS)/converted_orig.cbf$(SEXT) $(SIGNATURE) < insulin_pilatus6mconverted.cbf > $(DATADIRS)/insulin_pilatus6mconverted_orig.cbf$(SEXT) $(SIGNATURE) < mb_LP_1_001.cbf$ > $(DATADIRS)/mb_LP_1_001_orig.cbf$(SEXT) $(SIGNATURE) < testcell.prt > $(DATADIRS)/testcell_orig.prt$(SEXT) $(SIGNATURE) < test_xds_bin_testflatout.out > $(DATADIRS)/test_xds_bin_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_xds_bin_testflatpackedout.out > $(DATADIRS)/test_xds_bin_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatout.out > $(DATADIRS)/test_fcb_read_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatpackedout.out > $(DATADIRS)/test_fcb_read_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < XRD1621.cbf > $(DATADIRS)/XRD1621_orig.cbf$(SEXT) $(SIGNATURE) < XRD1621_I4encbC100.cbf > $(DATADIRS)/XRD1621_I4encbC100_orig.cbf$(SEXT) restore_signatures: restore_output restore_sigs_only # # Basic Tests # basic: $(BIN)/makecbf $(BIN)/img2cif $(BIN)/cif2cbf $(TESTINPUT_BASIC) $(BIN)/makecbf example.mar2300 makecbf.cbf $(BIN)/img2cif -c flatpacked -m headers -d digest \ -e base64 example.mar2300 img2cif_packed.cif $(BIN)/img2cif -c canonical -m headers -d digest \ -e base64 example.mar2300 img2cif_canonical.cif $(BIN)/img2cif -c flatpacked -m headers -d digest \ -e none example.mar2300 img2cif_packed.cbf $(BIN)/img2cif -c canonical -m headers -d digest \ -e none example.mar2300 img2cif_canonical.cbf $(BIN)/cif2cbf -e none -c flatpacked \ img2cif_canonical.cif cif2cbf_packed.cbf $(BIN)/cif2cbf -e none -c canonical \ img2cif_packed.cif cif2cbf_canonical.cbf -cmp cif2cbf_packed.cbf makecbf.cbf -cmp cif2cbf_packed.cbf img2cif_packed.cbf -cmp cif2cbf_canonical.cbf img2cif_canonical.cbf # # Extra Tests # ifneq ($(F90C),) extra: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/test_xds_binary $(BIN)/test_fcb_read_image $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg \ $(BIN)/changtestcompression $(BIN)/tiff2cbf \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUT) else extra: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUT) endif $(TIME) $(BIN)/cif2cbf -e hex -c none \ makecbf.cbf cif2cbf_ehcn.cif $(TIME) $(BIN)/cif2cbf -e none -c flatpacked \ cif2cbf_ehcn.cif cif2cbf_encp.cbf; rm cif2cbf_ehcn.cif -cmp makecbf.cbf cif2cbf_encp.cbf $(TIME) $(BIN)/cif2cbf -i 9ins.cif -o 9ins.cbf -cmp 9ins.cif 9ins.cbf $(TIME) $(BIN)/convert_image -F example.mar2300 converted_flat.cbf -cmp converted_flat.cbf converted_flat_orig.cbf $(TIME) $(BIN)/convert_image example.mar2300 converted.cbf -cmp converted.cbf converted_orig.cbf -$(TIME) $(BIN)/testcell < testcell.dat > testcell.prt -cmp testcell.prt testcell_orig.prt $(TIME) $(BIN)/convert_image -F -d adscquantum315 mb_LP_1_001.img adscconverted_flat.cbf -cmp adscconverted_flat.cbf adscconverted_flat_orig.cbf $(TIME) $(BIN)/convert_image -d adscquantum315 mb_LP_1_001.img adscconverted.cbf -cmp adscconverted.cbf adscconverted_orig.cbf $(TIME) $(BIN)/adscimg2cbf --no_pad --cbf_packed,flat mb_LP_1_001.img -cmp mb_LP_1_001.cbf mb_LP_1_001_orig.cbf ifneq ($(CLEANTESTS),) mv mb_LP_1_001.cbf nmb_LP_1_001.cbf else cp mb_LP_1_001.cbf nmb_LP_1_001.cbf endif $(TIME) $(BIN)/cbf2adscimg nmb_LP_1_001.cbf -cmp nmb_LP_1_001.img mb_LP_1_001.img rm nmb_LP_1_001.cbf ifneq ($(CLEANTESTS),) rm nmb_LP_1_001.img endif $(TIME) $(BIN)/convert_minicbf -d pilatus6m insulin_pilatus6m.cbf insulin_pilatus6mconverted.cbf -cmp insulin_pilatus6mconverted.cbf insulin_pilatus6mconverted_orig.cbf $(TIME) $(BIN)/testreals -cmp testrealin.cbf testrealout.cbf $(TIME) $(BIN)/testflat -cmp testflatin.cbf testflatout.cbf $(TIME) $(BIN)/testflatpacked -cmp testflatpackedin.cbf testflatpackedout.cbf ifneq ($(F90C),) echo testflatout.cbf | $(TIME) $(BIN)/test_xds_binary > test_xds_bin_testflatout.out -$(DIFF) test_xds_bin_testflatout.out test_xds_bin_testflatout_orig.out echo testflatpackedout.cbf | $(TIME) $(BIN)/test_xds_binary > test_xds_bin_testflatpackedout.out -$(DIFF) test_xds_bin_testflatpackedout.out test_xds_bin_testflatpackedout_orig.out echo testflatout.cbf | $(TIME) $(BIN)/test_fcb_read_image > test_fcb_read_testflatout.out -$(DIFF) test_fcb_read_testflatout.out test_fcb_read_testflatout_orig.out echo testflatpackedout.cbf | $(TIME) $(BIN)/test_fcb_read_image > test_fcb_read_testflatpackedout.out -$(DIFF) test_fcb_read_testflatpackedout.out test_fcb_read_testflatpackedout_orig.out endif $(TIME) $(BIN)/sauter_test $(TIME) $(BIN)/changtestcompression $(TIME) (export LD_LIBRARY_PATH=$(LIB);$(BIN)/tiff2cbf XRD1621.tif XRD1621.cbf) -$(DIFF) XRD1621.cbf XRD1621_orig.cbf $(TIME) $(BIN)/cif2cbf -I 4 -C 100. -L 0. -e n -c b -i XRD1621.cbf -o XRD1621_I4encbC100.cbf -$(DIFF) XRD1621_I4encbC100.cbf XRD1621_I4encbC100_orig.cbf ifneq ($(F90C),) extra_sigs_only: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/test_xds_binary $(BIN)/test_fcb_read_image $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg $(BIN)/tiff2cbf \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) else extra_sigs_only: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf\ basic $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) endif $(TIME) $(BIN)/cif2cbf -e hex -c none \ makecbf.cbf cif2cbf_ehcn.cif $(TIME) $(BIN)/cif2cbf -e none -c packed \ cif2cbf_ehcn.cif cif2cbf_encp.cbf; rm cif2cbf_ehcn.cif -cmp makecbf.cbf cif2cbf_encp.cbf $(TIME) $(BIN)/cif2cbf -i 9ins.cif -o 9ins.cbf -cmp 9ins.cif 9ins.cbf $(TIME) $(BIN)/convert_image -F example.mar2300 converted_flat.cbf -$(SIGNATURE) < converted_flat.cbf | $(DIFF) - converted_flat_orig.cbf$(SEXT); rm converted_flat.cbf $(TIME) $(BIN)/convert_image example.mar2300 converted.cbf -$(SIGNATURE) < converted.cbf | $(DIFF) - converted_orig.cbf$(SEXT); rm converted.cbf -$(TIME) $(BIN)/testcell < testcell.dat | \ $(SIGNATURE) | $(DIFF) - testcell_orig.prt$(SEXT) $(TIME) $(BIN)/convert_image -F -d adscquantum315 mb_LP_1_001.img adscconverted_flat.cbf -$(SIGNATURE) < adscconverted_flat.cbf | $(DIFF) - adscconverted_flat_orig.cbf$(SEXT) $(TIME) $(BIN)/convert_image -d adscquantum315 mb_LP_1_001.img adscconverted.cbf -$(SIGNATURE) < adscconverted.cbf | $(DIFF) - adscconverted_orig.cbf$(SEXT); rm adscconverted.cbf $(TIME) $(BIN)/adscimg2cbf --cbf_packed,flat mb_LP_1_001.img -$(SIGNATURE) < mb_LP_1_001.cbf | $(DIFF) - mb_LP_1_001_orig.cbf$(SEXT) mv mb_LP_1_001.cbf nmb_LP_1_001.cbf $(TIME) $(BIN)/cbf2adscimg nmb_LP_1_001.cbf -cmp nmb_LP_1_001.img mb_LP_1_001.img rm nmb_LP_1_001.cbf rm nmb_LP_1_001.img $(TIME) $(BIN)/convert_minicbf -d pilatus6m insulin_pilatus6m.cbf insulin_pilatus6mconverted.cbf -$(SIGNATURE) < insulin_pilatus6mconverted.cbf | $(DIFF) - insulin_pilatus6mconverted_orig.cbf$(SEXT); rm insulin_pilatus6mconverted.cbf $(TIME) $(BIN)/testreals -cmp testrealin.cbf testrealout.cbf $(TIME) $(BIN)/testflat -cmp testflatin.cbf testflatout.cbf $(TIME) $(BIN)/testflatpacked -cmp testflatpackedin.cbf testflatpackedout.cbf ifneq ($(F90C),) echo testflatout.cbf | $(TIME) $(BIN)/test_xds_binary | \ $(SIGNATURE) | $(DIFF) - test_xds_bin_testflatout_orig.out$(SEXT) echo testflatpackedout.cbf | $(TIME) $(BIN)/test_xds_binary | \ $(SIGNATURE) | $(DIFF) - test_xds_bin_testflatpackedout_orig.out$(SEXT) echo testflatout.cbf | $(TIME) $(BIN)/test_fcb_read_image | \ $(SIGNATURE) | $(DIFF) - test_fcb_read_testflatout_orig.out$(SEXT) echo testflatpackedout.cbf | $(TIME) $(BIN)/test_fcb_read_image | \ $(SIGNATURE) | $(DIFF) - test_fcb_read_testflatpackedout_orig.out$(SEXT) endif $(TIME) $(BIN)/sauter_test $(TIME) $(BIN)/tiff2cbf XRD1621.tif XRD1621.cbf $(TIME) $(BIN)/cif2cbf -I 4 -C 100. -L 0. -e n -c b -i XRD1621.cbf -o XRD1621_I4encbC100.cbf -$(SIGNATURE) < XRD1621.cbf | $(DIFF) - XRD1621_orig.cbf$(SEXT); rm XRD1621.cbf -$(SIGNATURE) < XRD1621_I4encbC100.cbf | $(DIFF) - XRD1621_I4encbC100_orig.cbf$(SEXT); rm XRD1621_I4encbC100.cbf @-rm -f adscconverted_flat.cbf @-rm -f $(TESTINPUT_BASIC) $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) @-rm -f cif2cbf_packed.cbf makecbf.cbf \ cif2cbf_packed.cbf img2cif_packed.cbf \ cif2cbf_canonical.cbf img2cif_canonical.cbf @-rm -f testrealout.cbf testflatout.cbf testflatpackedout.cbf \ cif2cbf_encp.cbf img2cif_canonical.cif img2cif_packed.cif 9ins.cbf pycbftests: $(PYCBF)/_pycbf.$(PYCBFEXT) (cd $(PYCBF); python pycbf_test1.py) (cd $(PYCBF); python pycbf_test2.py) (cd $(PYCBF); python pycbf_test3.py) javatests: $(BIN)/ctestcbf $(BIN)/testcbf.class $(SOLIB)/libcbf_wrap.so $(BIN)/ctestcbf > testcbfc.txt $(LDPREFIX) java -cp $(JCBF)/cbflib-$(VERSION).jar:$(BIN) testcbf > testcbfj.txt $(DIFF) testcbfc.txt testcbfj.txt dectristests: $(BIN)/cbf_template_t $(DECTRIS_EXAMPLES)/cbf_test_orig.out (cd $(DECTRIS_EXAMPLES); ../../bin/cbf_template_t; diff -a -u cbf_test_orig.out cbf_template_t.out) # # Remove all non-source files # empty: @-rm -f $(LIB)/*.o @-rm -f $(LIB)/libcbf.a @-rm -f $(LIB)/libfcb.a @-rm -f $(LIB)/libimg.a @-rm -f $(LIB)/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/build/*/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/build/src/cbf_simple.o @-rm -f $(PYCBF)/build/*/pycbf_wrap.o @-rm -rf $(BIN)/adscimg2cbf* @-rm -rf $(BIN)/cbf2adscimg* @-rm -rf $(BIN)/makecbf* @-rm -rf $(BIN)/img2cif* @-rm -rf $(BIN)/cif2cbf* @-rm -rf $(BIN)/convert_image* @-rm -rf $(BIN)/convert_minicbf* @-rm -rf $(BIN)/test_fcb_read_image* @-rm -rf $(BIN)/test_xds_binary* @-rm -rf $(BIN)/testcell* @-rm -rf $(BIN)/cif2c* @-rm -rf $(BIN)/testreals* @-rm -rf $(BIN)/testflat* @-rm -rf $(BIN)/testflatpacked* @-rm -rf $(BIN)/cbf_template_t* @-rm -rf $(BIN)/sauter_test* @-rm -rf $(BIN)/arvai_test* @-rm -rf $(BIN)/changtestcompression* @-rm -rf $(BIN)/tiff2cbf* @-rm -f makecbf.cbf @-rm -f img2cif_packed.cif @-rm -f img2cif_canonical.cif @-rm -f img2cif_packed.cbf @-rm -f img2cif_canonical.cbf @-rm -f img2cif_raw.cbf @-rm -f cif2cbf_packed.cbf @-rm -f cif2cbf_canonical.cbf @-rm -f converted.cbf @-rm -f adscconverted.cbf @-rm -f converted_flat.cbf @-rm -f adscconverted_flat.cbf @-rm -f adscconverted_flat_rev.cbf @-rm -f mb_LP_1_001.cbf @-rm -f cif2cbf_ehcn.cif @-rm -f cif2cbf_encp.cbf @-rm -f 9ins.cbf @-rm -f 9ins.cif @-rm -f testcell.prt @-rm -f example.mar2300 @-rm -f converted_orig.cbf @-rm -f adscconverted_orig.cbf @-rm -f converted_flat_orig.cbf @-rm -f adscconverted_flat_orig.cbf @-rm -f adscconverted_flat_rev_orig.cbf @-rm -f mb_LP_1_001_orig.cbf @-rm -f insulin_pilatus6mconverted_orig.cbf @-rm -f insulin_pilatus6mconverted.cbf @-rm -f insulin_pilatus6m.cbf @-rm -f testrealin.cbf @-rm -f testrealout.cbf @-rm -f testflatin.cbf @-rm -f testflatout.cbf @-rm -f testflatpackedin.cbf @-rm -f testflatpackedout.cbf @-rm -f CTC.cbf @-rm -f test_fcb_read_testflatout.out @-rm -f test_fcb_read_testflatpackedout.out @-rm -f test_xds_bin_testflatpackedout.out @-rm -f test_xds_bin_testflatout.out @-rm -f test_fcb_read_testflatout_orig.out @-rm -f test_fcb_read_testflatpackedout_orig.out @-rm -f test_xds_bin_testflatpackedout_orig.out @-rm -f test_xds_bin_testflatout_orig.out @-rm -f mb_LP_1_001.img @-rm -f 9ins.cif @-rm -f testcell_orig.prt @-rm -f $(DECTRIS_EXAMPLES)/cbf_template_t.out @-rm -f XRD1621.cbf @-rm -f XRD1621_orig.cbf @-rm -f XRD1621_orig.cbf @-rm -f XRD1621_I4encbC100.cbf @-rm -f $(SRC)/fcb_exit_binary.f90 @-rm -f $(SRC)/fcb_next_binary.f90 @-rm -f $(SRC)/fcb_open_cifin.f90 @-rm -f $(SRC)/fcb_packed.f90 @-rm -f $(SRC)/fcb_read_bits.f90 @-rm -f $(SRC)/fcb_read_image.f90 @-rm -f $(SRC)/fcb_read_xds_i2.f90 @-rm -f $(EXAMPLES)/test_fcb_read_image.f90 @-rm -f $(EXAMPLES)/test_xds_binary.f90 @-rm -f symlinksdone @-rm -f $(TESTOUTPUT) *$(SEXT) @-rm -f $(SOLIB)/*.o @-rm -f $(SOLIB)/libcbf_wrap.so @-rm -f $(SOLIB)/libjcbf.so @-rm -f $(SOLIB)/libimg.so @-rm -f $(SOLIB)/libfcb.so @-rm -rf $(JCBF)/org @-rm -f $(JCBF)/*.java @-rm -f $(JCBF)/jcbf_wrap.c @-rm -f $(SRC)/cbf_wrap.c @-rm -f $(BIN)/ctestcbf $(BIN)/testcbf.class testcbfc.txt testcbfj.txt @-rm -rf $(REGEX) @-rm -rf $(TIFF) ./.undosymlinks # # Remove temporary files # clean: @-rm -f core @-rm -f *.o @-rm -f *.u # # Restore to distribution state # distclean: clean empty # # Create a Tape Archive for distribution # tar: $(DOCUMENTS) $(SOURCE) $(SRC)/cbf.stx $(HEADERS) $(M4FILES)\ $(EXAMPLES) \ README.html README Makefile \ $(JPEGS) -/bin/rm -f CBFlib.tar* tar cvBf CBFlib.tar \ $(DOCUMENTS) $(SOURCE) $(SRC)/cbf.stx $(HEADERS) $(M4FILES)\ $(EXAMPLES) \ README.html README Makefile \ $(JPEGS) gzip --best CBFlib.tar ./CBFlib-0.9.2.2/include/0000755000076500007650000000000011603703065013226 5ustar yayayaya./CBFlib-0.9.2.2/include/cbf_compress.h0000644000076500007650000005070011603702115016041 0ustar yayayaya/********************************************************************** * cbf_compress.h * * * * Version 0.8.0 20 July 2008 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifndef CBF_COMPRESS_H #define CBF_COMPRESS_H #ifdef __cplusplus extern "C" { #endif #include #include "cbf_file.h" /* Compress an array */ int cbf_compress (void *source, size_t elsize, int elsign, size_t nelem, unsigned int compression, cbf_file *file, size_t *compressedsize, int *bits, char *digest, int realarray, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); #define cbf_compress_fs(source,elsize,elsign,nelem,compression,file,compressedsize,bits,digest,realarray,byteorder,dimfast,dimmid,dimslow,padding) \ cbf_compress((source),(elsize),(elsign),(nelem),(compression),(file),(compressedsize),(bits),(digest),(realarray),(byteorder),(dimfast),(dimmid),(dimslow),(padding)) #define cbf_compress_sf(source,elsize,elsign,nelem,compression,file,compressedsize,bits,digest,realarray,byteorder,dimslow,dimmid,dimfast,padding) \ cbf_compress((source),(elsize),(elsign),(nelem),(compression),(file),(compressedsize),(bits),(digest),(realarray),(byteorder),(dimfast),(dimmid),(dimslow),(padding)) /* Get the parameters of an array (read up to the start of the table) */ int cbf_decompress_parameters (int *eltype, size_t *elsize, int *elsigned, int *elunsigned, size_t *nelem, int *minelem, int *maxelem, unsigned int compression, cbf_file *file); /* Decompress an array (from the start of the table) */ int cbf_decompress (void *destination, size_t elsize, int elsign, size_t nelem, size_t *nelem_read, size_t compressedsize, unsigned int compression, int bits, int sign, cbf_file *file, int realarray, const char *byteorder, size_t dimover, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); #define cbf_decompress_fs(destination,elsize,elsign,nelem,nelem_read,compressedsize,compression,bits,sign,file,realarray,byteorder,dimover,dimfast,dimmid,dimslow,padding) \ cbf_decompress((destination),(elsize),(elsign),(nelem),(nelem_read),(compressedsize),(compression),(bits),(sign),(file),(realarray),(byteorder),(dimover),(dimfast),(dimmid),(dimslow),(padding)) #define cbf_decompress_sf(destination,elsize,elsign,nelem,nelem_read,compressedsize,compression,bits,sign,file,realarray,byteorder,dimover,dimslow,dimmid,dimfast,padding) \ cbf_decompress((destination),(elsize),(elsign),(nelem),(nelem_read),(compressedsize),(compression),(bits),(sign),(file),(realarray),(byteorder),(dimover),(dimfast),(dimmid),(dimslow),(padding)) #ifdef __cplusplus } #endif #endif /* CBF_COMPRESS_H */ ./CBFlib-0.9.2.2/include/cbf.h0000644000076500007650000016317011603702115014134 0ustar yayayaya/********************************************************************** * cbf.h -- cbflib basic API functions * * * * Version 0.8.0 20 July 2008 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifndef CBF_H #define CBF_H #ifdef __cplusplus extern "C" { #endif #include "cbf_tree.h" #include #include #include /* Currently the cbf library assumes a 32-bit or larger integer */ #ifndef SWIG /* Something wrong with the SWIG preprocessor makes it barf on this when used on a 64-bit OS! */ #if UINT_MAX / 65535U < 65535U #error cbflib assumes int is at least 32 bits #endif #else #define CBF_USE_LONG_LONG typedef long long CBF_sll_type; typedef unsigned long long CBF_ull_type; #endif #if defined(CBF_DONT_USE_LONG_LONG) || defined(__cplusplus) || defined(__MINGW32__) #undef ULLONG_MAX #undef CBF_USE_LONG_LONG #endif #ifndef SWIG #if defined(ULLONG_MAX) && defined(LLONG_MAX) #if ULLONG_MAX >= 18446744073709551615U #define CBF_USE_LONG_LONG typedef long long CBF_sll_type; typedef unsigned long long CBF_ull_type; #else #if UINT_MAX >= 4294967295U typedef struct { unsigned int el0:32;unsigned int el1:32;} CBF_sll_type; typedef struct { unsigned int el0:32;unsigned int el1:32;} CBF_ull_type; #define CBF_SLL_INTS 2 #define CBF_ULL_INTS 2 #else typedef struct { unsigned int el0:32;unsigned int el1:32;unsigned int el2:32;unsigned int el3:32;} CBF_sll_type; typedef struct { unsigned int el0:32;unsigned int el1:32;unsigned int el2:32;unsigned int el3:32;} CBF_ull_type; #define CBF_SLL_INTS 4 #define CBF_ULL_INTS 4 #endif #endif #else #if UINT_MAX >= 4294967295U typedef struct { unsigned int el0:32;unsigned int el1:32;} CBF_sll_type; typedef struct { unsigned int el0:32;unsigned int el1:32;} CBF_ull_type; #define CBF_SLL_INTS 2 #define CBF_ULL_INTS 2 #else typedef struct { unsigned int el0:32;unsigned int el1:32;unsigned int el2:32;unsigned int el3:32;} CBF_sll_type; typedef struct { unsigned int el0:32;unsigned int el1:32;unsigned int el2:32;unsigned int el3:32;} CBF_ull_type; #define CBF_SLL_INTS 4 #define CBF_ULL_INTS 4 #endif #endif #endif /* API version and assumed dictionary version */ #define CBF_API_VERSION "CBFlib v0.9.0" #define CBF_DIC_VERSION "CBF: VERSION 1.6" /* Maximum line length */ #define CBF_LINELENGTH_10 80 #define CBF_LINELENGTH_11 2048 #define CBF_LINELENGTH_20 8192 /* Initial io buffer sizes */ #define CBF_INIT_READ_BUFFER 4096 #define CBF_INIT_WRITE_BUFFER 4096 #define CBF_TRANSFER_BUFFER 4096 /* Error codes */ #define CBF_FORMAT 0x00000001 /* 1 */ #define CBF_ALLOC 0x00000002 /* 2 */ #define CBF_ARGUMENT 0x00000004 /* 4 */ #define CBF_ASCII 0x00000008 /* 8 */ #define CBF_BINARY 0x00000010 /* 16 */ #define CBF_BITCOUNT 0x00000020 /* 32 */ #define CBF_ENDOFDATA 0x00000040 /* 64 */ #define CBF_FILECLOSE 0x00000080 /* 128 */ #define CBF_FILEOPEN 0x00000100 /* 256 */ #define CBF_FILEREAD 0x00000200 /* 512 */ #define CBF_FILESEEK 0x00000400 /* 1024 */ #define CBF_FILETELL 0x00000800 /* 2048 */ #define CBF_FILEWRITE 0x00001000 /* 4096 */ #define CBF_IDENTICAL 0x00002000 /* 8192 */ #define CBF_NOTFOUND 0x00004000 /* 16384 */ #define CBF_OVERFLOW 0x00008000 /* 32768 */ #define CBF_UNDEFINED 0x00010000 /* 65536 */ #define CBF_NOTIMPLEMENTED 0x00020000 /* 131072 */ #define CBF_NOCOMPRESSION 0x00040000 /* 262144 */ /* Token Type Strings */ #define CBF_TOKEN_NULL '\377' #define CBF_TOKEN_WORD '\300' /* Simple word */ #define CBF_TOKEN_SQSTRING '\301' /* Single-quoted string */ #define CBF_TOKEN_DQSTRING '\302' /* Double-quoted string */ #define CBF_TOKEN_SCSTRING '\303' /* Semicolon-delimited string */ #define CBF_TOKEN_BIN '\304' /* Binary section */ #define CBF_TOKEN_MIME_BIN '\305' /* Mime-encoded binary section */ #define CBF_TOKEN_TMP_BIN '\306' /* Temporary binary section */ #define CBF_TOKEN_BKTSTRING '\311' /* Composite string [] */ #define CBF_TOKEN_BRCSTRING '\312' /* Composite string {} */ #define CBF_TOKEN_PRNSTRING '\313' /* Composite string () */ #define CBF_TOKEN_TDQSTRING '\314' /* Triple Double-Quoted String */ #define CBF_TOKEN_TSQSTRING '\315' /* Triple Single-Quoted String */ #define CBF_TOKEN_BKTITEM '\316' /* Bracketed item */ #define CBF_TOKEN_FUNCTION '\317' /* Function definition */ #define cbf_token_term(tokentype) \ (((tokentype)==CBF_TOKEN_WORD)?' ': \ (((tokentype)==CBF_TOKEN_SQSTRING)?'\'': \ (((tokentype)==CBF_TOKEN_DQSTRING)?'"': \ (((tokentype)==CBF_TOKEN_SCSTRING)?';': \ (((tokentype)==CBF_TOKEN_BKTSTRING)?']': \ (((tokentype)==CBF_TOKEN_BRCSTRING)?'}': \ (((tokentype)==CBF_TOKEN_PRNSTRING)?')': \ (((tokentype)==CBF_TOKEN_TDQSTRING)?'"': \ (((tokentype)==CBF_TOKEN_TDQSTRING)?'\'': '\0' )))))))) ) /* Constants for case sensitivity */ #define CBF_CASE_INSENSITIVE 1 #define CBF_CASE_SENSITIVE 0 /* Constants used for compression */ #define CBF_INTEGER 0x0010 /* Uncompressed integer */ #define CBF_FLOAT 0x0020 /* Uncompressed IEEE floating-point */ #define CBF_CANONICAL 0x0050 /* Canonical compression */ #define CBF_PACKED 0x0060 /* CCP4 Packed (JPA) compression */ #define CBF_PACKED_V2 0x0090 /* CCP4 Packed (JPA) compression V2 */ #define CBF_BYTE_OFFSET 0x0070 /* Byte Offset Compression */ #define CBF_PREDICTOR 0x0080 /* Predictor_Huffman Compression */ #define CBF_NONE 0x0040 /* No compression flag */ #define CBF_COMPRESSION_MASK \ 0x00FF /* Mask to separate compression type from flags */ #define CBF_FLAG_MASK 0x0F00 /* Mask to separate flags from compression type */ #define CBF_UNCORRELATED_SECTIONS \ 0x0100 /* Flag for uncorrelated sections */ #define CBF_FLAT_IMAGE 0x0200 /* Flag for flat (linear) images */ #define CBF_NO_EXPAND 0x0400 /* Flag to try not to expand */ /* Flags used for logging */ #define CBF_LOGERROR 0x0001 /* Log a fatal error */ #define CBF_LOGWARNING 0x0002 /* Log a warning */ #define CBF_LOGWOLINE 0x0004 /* Log without the line and column */ #define CBF_LOGWOCOLUMN 0x0008 /* Log without the column */ #define CBF_LOGSTARTLOC 0x0010 /* Log using the start location */ #define CBF_LOGCURRENTLOC 0x0020 /* Log using the current location */ /* Constants used for headers */ #define PLAIN_HEADERS 0x0001 /* Use plain ASCII headers */ #define MIME_HEADERS 0x0002 /* Use MIME headers */ #define MSG_NODIGEST 0x0004 /* Do not check message digests */ #define MSG_DIGEST 0x0008 /* Check message digests */ #define MSG_DIGESTNOW 0x0010 /* Check message digests immediately */ #define MSG_DIGESTWARN 0x0020 /* Warn on message digests immediately*/ #define PAD_1K 0x0020 /* Pad binaries with 1023 0's */ #define PAD_2K 0x0040 /* Pad binaries with 2047 0's */ #define PAD_4K 0x0080 /* Pad binaries with 4095 0's */ /* Constants used to control CIF parsing */ #define CBF_PARSE_BRC 0x0100 /* PARSE DDLm/CIF2 brace {,...} */ #define CBF_PARSE_PRN 0x0200 /* PARSE DDLm parens (,...) */ #define CBF_PARSE_BKT 0x0400 /* PARSE DDLm brackets [,...] */ #define CBF_PARSE_BRACKETS \ 0x0700 /* PARSE ALL brackets */ #define CBF_PARSE_TQ 0x0800 /* PARSE treble quotes """...""" and '''...''' */ #define CBF_PARSE_CIF2_DELIMS \ 0x1000 /* Do not scan past an unescaped close quote do not accept {} , : " ' in non-delimited strings'{ */ #define CBF_PARSE_DDLm 0x0700 /* For DDLm parse (), [], {} */ #define CBF_PARSE_CIF2 0x1F00 /* For CIF2 parse {}, treble quotes, stop on unescaped close quotes */ #define CBF_PARSE_DEFINES \ 0x2000 /* Recognize DEFINE_name */ #define CBF_PARSE_WIDE 0x4000 /* PARSE wide files */ #define CBF_PARSE_WS 0x8000 /* PARSE whitespace */ #define CBF_PARSE_UTF8 0x10000 /* PARSE UTF-8 */ #define HDR_DEFAULT (MIME_HEADERS | MSG_NODIGEST) #define MIME_NOHEADERS PLAIN_HEADERS /* CBF vs CIF */ #define CBF 0x0000 /* Use simple binary sections */ #define CIF 0x0001 /* Use MIME-encoded binary sections */ /* Constants used for encoding */ #define ENC_NONE 0x0001 /* Use BINARY encoding */ #define ENC_BASE64 0x0002 /* Use BASE64 encoding */ #define ENC_BASE32K 0x0004 /* Use X-BASE32K encoding */ #define ENC_QP 0x0008 /* Use QUOTED-PRINTABLE encoding */ #define ENC_BASE10 0x0010 /* Use BASE10 encoding */ #define ENC_BASE16 0x0020 /* Use BASE16 encoding */ #define ENC_BASE8 0x0040 /* Use BASE8 encoding */ #define ENC_FORWARD 0x0080 /* Map bytes to words forward (1234) */ #define ENC_BACKWARD 0x0100 /* Map bytes to words backward (4321) */ #define ENC_CRTERM 0x0200 /* Terminate lines with CR */ #define ENC_LFTERM 0x0400 /* Terminate lines with LF */ #define ENC_DEFAULT (ENC_BASE64 | ENC_LFTERM | ENC_FORWARD) /* Convenience definitions for functions returning error codes */ /* First we need to bring everything into the preprocessor */ #ifdef __STDC_VERSION__ #if __STDC_VERSION__ < 199901L # if __GNUC__ >= 2 # define __func__ __FUNCTION__ # endif #endif #endif #ifdef CBFDEBUG #ifndef __FILE__ #define cbf_failnez(x) {int err; err = (x); if (err) { fprintf (stderr, \ "\nCBFlib error %d \n", err); return err; }} #define cbf_onfailnez(x,c) {int err; err = (x); if (err) { fprintf (stderr, \ "\nCBFlib error %d \n", err); \ { c; } return err; }} #else #ifndef __func__ #define cbf_failnez(x) {int err; err = (x); if (err) { fprintf (stderr, \ "\nCBFlib error %d at %s:%d\n", err,__FILE__,__LINE__); return err; }} #define cbf_onfailnez(x,c) {int err; err = (x); if (err) { fprintf (stderr, \ "\nCBFlib error %d at %s:%d\n", err,__FILE__,__LINE__); \ { c; } return err; }} #else #define cbf_failnez(x) {int err; err = (x); if (err) { fprintf (stderr, \ "\nCBFlib error %d at %s:%d(%s)\n", err,__FILE__,__LINE__,__func__); return err; }} #define cbf_onfailnez(x,c) {int err; err = (x); if (err) { fprintf (stderr, \ "\nCBFlib error %d at %s:%d(%s)\n", err,__FILE__,__LINE__,__func__); \ { c; } return err; }} #endif #endif #else #define cbf_failnez(f) { int err; err = (f); if (err) return err; } #define cbf_onfailnez(f,c) { int err; err = (f); if (err) {{ c; } return err; }} #endif /* cbf handle */ typedef struct _cbf_handle_struct { cbf_node *node; struct _cbf_handle_struct *dictionary; cbf_file * file; /* NULL or an active cbf_file for input */ cbf_file * commentfile; /* NULL or file for whitespace and comments */ int startcolumn, startline; /* starting location of last token */ FILE * logfile; /* NULL or an active stream for error logging */ int warnings, errors; int refcount, row, search_row; } cbf_handle_struct; typedef cbf_handle_struct *cbf_handle; /* Prototypes */ /* Create a handle */ int cbf_make_handle (cbf_handle *handle); /* Free a handle */ int cbf_free_handle (cbf_handle handle); /* Read a file */ int cbf_read_file (cbf_handle handle, FILE *stream, int flags); /* Read a wide file */ int cbf_read_widefile (cbf_handle handle, FILE *stream, int flags); /* Read a pre-read buffered file */ int cbf_read_buffered_file (cbf_handle handle, FILE *stream, int flags, const char * buffer, size_t buffer_len); /* Write a file */ int cbf_write_file (cbf_handle handle, FILE *stream, int isbuffer, int ciforcbf, int headers, int encoding); /* Write a file, starting at the local node */ int cbf_write_local_file (cbf_handle handle, FILE *stream, int isbuffer, int ciforcbf, int headers, int encoding); /* Write a wide file */ int cbf_write_widefile (cbf_handle handle, FILE *stream, int isbuffer, int ciforcbf, int headers, int encoding); /* Add a data block */ int cbf_new_datablock (cbf_handle handle, const char *datablockname); /* Add a save frame block */ int cbf_new_saveframe (cbf_handle handle, const char *saveframename); /* Add a data block, allowing for duplicates */ int cbf_force_new_datablock (cbf_handle handle, const char *datablockname); /* Add a save frame, allowing for duplicates */ int cbf_force_new_saveframe (cbf_handle handle, const char *saveframename); /* Add a category to the current data block */ int cbf_new_category (cbf_handle handle, const char *categoryname); /* Add a category to the current data block, allowing for duplicates */ int cbf_force_new_category (cbf_handle handle, const char *categoryname); /* Add a column to the current category */ int cbf_new_column (cbf_handle handle, const char *columnname); /* Add a row to the current category */ int cbf_new_row (cbf_handle handle); /* Insert a row in the current category */ int cbf_insert_row (cbf_handle handle, const int rownumber); /* Delete a row from the current category */ int cbf_delete_row (cbf_handle handle, const int rownumber); /* Change the name of the current data block */ int cbf_set_datablockname (cbf_handle handle, const char *datablockname); /* Change the name of the current save frame */ int cbf_set_saveframename (cbf_handle handle, const char *saveframename); /* Delete all categories from all the data blocks */ int cbf_reset_datablocks (cbf_handle handle); /* Delete all categories from the current data block */ int cbf_reset_datablock (cbf_handle handle); /* Delete all categories from the current save frame */ int cbf_reset_saveframe (cbf_handle handle); /* Delete all columns and rows from the current category */ int cbf_reset_category (cbf_handle handle); /* Delete the current data block */ int cbf_remove_datablock (cbf_handle handle); /* Delete the current save frame */ int cbf_remove_saveframe (cbf_handle handle); /* Delete the current category */ int cbf_remove_category (cbf_handle handle); /* Delete the current column */ int cbf_remove_column (cbf_handle handle); /* Delete the current row */ int cbf_remove_row (cbf_handle handle); /* Make the first data block the current data block */ int cbf_rewind_datablock (cbf_handle handle); /* Make the first category in the current data block the current category */ int cbf_rewind_category (cbf_handle handle); /* Make the first save frame in the current data block the current category */ int cbf_rewind_saveframe (cbf_handle handle); /* Make the first category or save frame in the current data block the current category */ int cbf_rewind_blockitem (cbf_handle handle, CBF_NODETYPE *type); /* Make the first column in the current category the current column */ int cbf_rewind_column (cbf_handle handle); /* Make the first row in the current category the current row */ int cbf_rewind_row (cbf_handle handle); /* Make the next data block the current data block */ int cbf_next_datablock (cbf_handle handle); /* Make the next save frame in the current data block the current save frame */ int cbf_next_saveframe (cbf_handle handle); /* Make the next category in the current data block the current category */ int cbf_next_category (cbf_handle handle); /* Make the next save frame or category the current data block or category */ int cbf_next_blockitem (cbf_handle handle, CBF_NODETYPE * type); /* Make the next column in the current category the current column */ int cbf_next_column (cbf_handle handle); /* Make the next row in the current category the current row */ int cbf_next_row (cbf_handle handle); /* Make the named data block the current data block */ int cbf_find_datablock (cbf_handle handle, const char *datablockname); /* Make the named save frame in the current data block the current save frame */ int cbf_find_saveframe (cbf_handle handle, const char *saveframe); /* Make the named category in the current data block or save frame the current category */ int cbf_find_category (cbf_handle handle, const char *categoryname); /* Make the named column in the current category the current column */ int cbf_find_column (cbf_handle handle, const char *columnname); /* Make the first row with matching value the current row */ int cbf_find_row (cbf_handle handle, const char *value); /* Make the first row with matching value the current row creating it if necessary */ int cbf_require_row (cbf_handle handle, const char *value); /* Make the next row with matching value the current row */ int cbf_find_nextrow (cbf_handle handle, const char *value); /* Make the next row with matching value the current row, creating the row if necessary */ int cbf_require_nextrow (cbf_handle handle, const char *value); /* Count the data blocks */ int cbf_count_datablocks (cbf_handle handle, unsigned int *datablocks); /* Count the save frames in the current data block */ int cbf_count_saveframes (cbf_handle handle, unsigned int *saveframes); /* Count the categories in the current data block */ int cbf_count_categories (cbf_handle handle, unsigned int *categories); /* Count the items in the current data block */ int cbf_count_blockitems (cbf_handle handle, unsigned int *blockitems); /* Count the columns in the current category */ int cbf_count_columns (cbf_handle handle, unsigned int *columns); /* Count the rows in the current category */ int cbf_count_rows (cbf_handle handle, unsigned int *rows); /* Make the specified data block the current data block */ int cbf_select_datablock (cbf_handle handle, unsigned int datablock); /* Make the specified save frame the current save frame */ int cbf_select_saveframe (cbf_handle handle, unsigned int saveframe); /* Make the specified category the current category */ int cbf_select_category (cbf_handle handle, unsigned int category); /* Make the specified category or save frame the current block item */ int cbf_select_blockitem (cbf_handle handle, unsigned int item, CBF_NODETYPE * type); /* Make the specified column the current column */ int cbf_select_column (cbf_handle handle, unsigned int column); /* Make the specified row the current row */ int cbf_select_row (cbf_handle handle, unsigned int row); /* Get the name of the current data block */ int cbf_datablock_name (cbf_handle handle, const char **datablockname); /* Get the name of the current save frame */ int cbf_saveframe_name (cbf_handle handle, const char **saveframename); /* Get the name of the current category */ int cbf_category_name (cbf_handle handle, const char **categoryname); /* Get the name of the current column */ int cbf_column_name (cbf_handle handle, const char **columnname); /* Set the name of the current column */ int cbf_set_column_name (cbf_handle handle, const char *columnname); /* Get the number of the current row */ int cbf_row_number (cbf_handle handle, unsigned int *row); /* Get the number of the current column */ int cbf_column_number (cbf_handle handle, unsigned int *column); /* Get the number of the current block item */ int cbf_blockitem_number (cbf_handle handle, unsigned int *blockitem); /* Get the ascii value of the current (row, column) entry */ int cbf_get_value (cbf_handle handle, const char **value); /* Set the ascii value of the current (row, column) entry */ int cbf_set_value (cbf_handle handle, const char *value); /* Get the ascii value of the current (row, column) entry, setting it to a default value if necessary */ int cbf_require_value (cbf_handle handle, const char **value, const char *defaultvalue); /* Get the ascii type of value of the current (row, column) entry */ int cbf_get_typeofvalue (cbf_handle handle, const char **typeofvalue); /* Set the ascii type of value of the current (row, column) entry */ int cbf_set_typeofvalue (cbf_handle handle, const char *typeofvalue); /* Get the (int) numeric value of the current (row, column) entry */ int cbf_get_integervalue (cbf_handle handle, int *number); /* Get the (double) numeric value of the current (row, column) entry */ int cbf_get_doublevalue (cbf_handle handle, double *number); /* Set the ascii value of the current (row, column) entry from an int */ int cbf_set_integervalue (cbf_handle handle, int number); /* Set the ascii value of the current (row, column) entry from a double */ int cbf_set_doublevalue (cbf_handle handle, const char *format, double number); /* Get the name of the current save frame */ int cbf_saveframe_name (cbf_handle handle, const char **saveframename); /* Get the ascii value of the current (row, column) entry, setting it to a default value if necessary */ int cbf_require_value (cbf_handle handle, const char **value, const char *defaultvalue); /* Get the (integer) numeric value of the current (row, column) entry, setting it if necessary */ int cbf_require_integervalue (cbf_handle handle, int *number, int defaultvalue); /* Get the (double) numeric value of the current (row, column) entry, setting it if necessary */ int cbf_require_doublevalue (cbf_handle handle, double *number, double defaultvalue); /* Get the parameters of the current (row, column) array entry */ int cbf_get_arrayparameters (cbf_handle handle, unsigned int *compression, int *id, size_t *elsize, int *elsigned, int *elunsigned, size_t *nelem, int *minelem, int *maxelem, int *realarray); /* Get the parameters of the current (row, column) array entry */ int cbf_get_arrayparameters_wdims (cbf_handle handle, unsigned int *compression, int *id, size_t *elsize, int *elsigned, int *elunsigned, size_t *nelem, int *minelem, int *maxelem, int *realarray, const char **byteorder, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding); #define cbf_get_arrayparameters_wdims_fs(handle, compression, id, elsize, elsigned, elunsigned, nelem, minelem, maxelem, realarray, byteorder, dimfast, dimmid, dimslow, padding) \ cbf_get_arrayparameters_wdims((handle),(compression),(id),(elsize),(elsigned),(elunsigned),(nelem),(minelem),(maxelem),(realarray),(byteorder),(dimfast),(dimmid),(dimslow), (padding)) #define cbf_get_arrayparameters_wdims_sf(handle, compression, id, elsize, elsigned, elunsigned, nelem, minelem, maxelem, realarray, byteorder, dimslow, dimmid, dimfast, padding) \ cbf_get_arrayparameters_wdims((handle),(compression),(id),(elsize),(elsigned),(elunsigned),(nelem),(minelem),(maxelem),(realarray),(byteorder),(dimfast),(dimmid),(dimslow), (padding)) /* Get the dimensions of the current (row, column) array entry from the CBF tags */ int cbf_get_arraydimensions(cbf_handle handle, size_t * dimover, size_t * dimfast, size_t * dimmid, size_t * dimslow); /* Get the parameters of the current (row, column) integer array entry */ int cbf_get_integerarrayparameters (cbf_handle handle, unsigned int *compression, int *id, size_t *elsize, int *elsigned, int *elunsigned, size_t *nelem, int *minelem, int *maxelem); /* Get the parameters of the current (row, column) integer array entry */ int cbf_get_integerarrayparameters_wdims (cbf_handle handle, unsigned int *compression, int *id, size_t *elsize, int *elsigned, int *elunsigned, size_t *nelem, int *minelem, int *maxelem, const char **byteorder, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding); #define cbf_get_integerarrayparameters_wdims_fs(handle, compression, id, elsize, elsigned, elunsigned, nelem, minelem, maxelem, byteorder, dimfast, dimmid, dimslow, padding) \ cbf_get_integerarrayparameters_wdims((handle),(compression),(id),(elsize),(elsigned),(elunsigned),(nelem),(minelem),(maxelem),(byteorder),(dimfast),(dimmid),(dimslow), (padding)) #define cbf_get_integerarrayparameters_wdims_sf(handle, compression, id, elsize, elsigned, elunsigned, nelem, minelem, maxelem, byteorder, dimslow, dimmid, dimfast, padding) \ cbf_get_integerarrayparameters_wdims((handle),(compression),(id),(elsize),(elsigned),(elunsigned),(nelem),(minelem),(maxelem),(byteorder),(dimfast),(dimmid),(dimslow), (padding)) /* Get the integer value of the current (row, column) array entry */ int cbf_get_integerarray (cbf_handle handle, int *id, void *value, size_t elsize, int elsign, size_t nelem, size_t *nelem_read); /* Get the real value of the current (row, column) array entry */ int cbf_get_realarray (cbf_handle handle, int *id, void *value, size_t elsize, size_t nelem, size_t *nelem_read); /* Get the parameters of the current (row, column) array entry */ int cbf_get_realarrayparameters (cbf_handle handle, unsigned int *compression, int *id, size_t *elsize, size_t *nelem); /* Get the parameters of the current (row, column) array entry */ int cbf_get_realarrayparameters_wdims (cbf_handle handle, unsigned int *compression, int *id, size_t *elsize, size_t *nelem, const char **byteorder, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding); #define cbf_get_realarrayparameters_wdims_fs(handle,compression,id,elsize,nelem,byteorder,dimfast,dimmid,dimslow,padding) \ cbf_get_realarrayparameters_wdims((handle),(compression),(id),(elsize),(nelem),(byteorder),(dimfast),(dimmid),(dimslow),(padding)) #define cbf_get_realarrayparameters_wdims_sf(handle,compression,id,elsize,nelem,byteorder,dimslow,dimmid,dimfast,padding) \ cbf_get_realarrayparameters_wdims((handle),(compression),(id),(elsize),(nelem),(byteorder),(dimfast),(dimmid),(dimslow),(padding)) /* Set the integer value of the current (row, column) array entry */ int cbf_set_integerarray (cbf_handle handle, unsigned int compression, int id, void *value, size_t elsize, int elsign, size_t nelem); /* Set the integer value of the current (row, column) array entry */ int cbf_set_integerarray_wdims (cbf_handle handle, unsigned int compression, int id, void *value, size_t elsize, int elsign, size_t nelem, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); #define cbf_set_integerarray_wdims_fs(handle, compression, id, value, elsize, elsign, nelem, byteorder, dimfast, dimmid, dimslow, padding) \ cbf_set_integerarray_wdims((handle),(compression),(id),(value),(elsize),(elsign),(nelem),(byteorder),(dimfast),(dimmid),(dimslow),(padding)) #define cbf_set_integerarray_wdims_sf(handle, compression, id, value, elsize, elsign, nelem, byteorder, dimslow, dimmid, dimfast, padding) \ cbf_set_integerarray_wdims((handle),(compression),(id),(value),(elsize),(elsign),(nelem),(byteorder),(dimfast),(dimmid),(dimslow),(padding)) /* Set the real value of the current (row, column) array entry */ int cbf_set_realarray (cbf_handle handle, unsigned int compression, int id, void *value, size_t elsize, size_t nelem); /* Set the real value of the current (row, column) array entry with dimensions */ int cbf_set_realarray_wdims (cbf_handle handle, unsigned int compression, int id, void *value, size_t elsize, size_t nelem, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); #define cbf_set_realarray_wdims_fs(handle, compression, id, value, elsize, nelem, byteorder, dimfast, dimmid, dimslow, padding) \ cbf_set_realarray_wdims((handle),(compression),(id),(value),(elsize),(nelem),(byteorder),(dimfast),(dimmid),(dimslow),(padding)) #define cbf_set_realarray_wdims_sf(handle, compression, id, value, elsize, nelem, byteorder, dimslow, dimmid, dimfast, padding) \ cbf_set_realarray_wdims((handle),(compression),(id),(value),(elsize),(nelem),(byteorder),(dimfast),(dimmid),(dimslow),(padding)) /* Issue a warning message */ void cbf_warning (const char *message); /* Issue an error message */ void cbf_error (const char *message); /* issue a log message for a cbf */ void cbf_log (cbf_handle handle, const char *message, int logflags); /* issue a log message for a cbf_file */ void cbf_flog (cbf_file * file, const char *message, int logflags); /* Find a datablock, creating it if necessary */ int cbf_require_datablock (cbf_handle handle, const char *datablockname); /* Find a category, creating it if necessary */ int cbf_require_category (cbf_handle handle, const char *categoryname); /* Find a column, creating it if necessary */ int cbf_require_column (cbf_handle handle, const char *columnname); /* Find a column value, return a default if necessary */ int cbf_require_column_value (cbf_handle handle, const char *columnname, const char **value, const char *defaultvalue); /* Find a column integer value, return a default if necessary */ int cbf_require_column_integervalue (cbf_handle handle, const char *columnname, int *number, const int defaultvalue); /* Find a column double value, return a default if necessary */ int cbf_require_column_doublevalue (cbf_handle handle, const char *columnname, double *number, const double defaultvalue); /* Get the local byte order of the default integer type */ int cbf_get_local_integer_byte_order (char ** byte_order); /* Get the local byte order of the default real type */ int cbf_get_local_real_byte_order (char ** byte_order); /* Get the local real format */ int cbf_get_local_real_format (char ** real_format ); /* Get the dictionary for a cbf */ int cbf_get_dictionary (cbf_handle handle, cbf_handle * dictionary); /* Set the dictionary for a cbf */ int cbf_set_dictionary (cbf_handle handle, cbf_handle dictionary); /* Get the dictionary for a cbf, or create one */ int cbf_require_dictionary (cbf_handle handle, cbf_handle * dictionary); /* Put the value into the named column, updating the hash table links */ int cbf_set_hashedvalue(cbf_handle handle, const char * value, const char * columnname, int valuerow); /* Find value in the named column, using the hash table links */ int cbf_find_hashedvalue(cbf_handle handle, const char * value, const char * columnname, int caseinsensitive); /* Take a defintion from a dictionary and insert it into the has tables of a cbf dictionary */ int cbf_convert_dictionary_definition(cbf_handle cbfdictionary, cbf_handle dictionary, const char * name); /* Increment a column */ int cbf_increment_column( cbf_handle handle, const char* columnname, int * count ); /* Reset a column */ int cbf_reset_column( cbf_handle handle, const char* columnname); /* Reset reference counts for a dictionary */ int cbf_reset_refcounts( cbf_handle dictionary ); /* Convert a DDL1 or DDL2 dictionary and add it to a CBF dictionary */ int cbf_convert_dictionary (cbf_handle handle, cbf_handle dictionary ); /* Find the requested tag anywhere in the cbf, make it the current column */ int cbf_find_tag (cbf_handle handle, const char *tag); /* Find the requested tag in the cbf within the current save frame or data block, make it the current column */ int cbf_find_local_tag (cbf_handle handle, const char *tag); /* Find the requested category and column anywhere in the cbf, make it the current column */ int cbf_srch_tag (cbf_handle handle, cbf_node *node, const char *categoryname, const char *columnname); /* Find the root alias of a given category */ int cbf_find_category_root (cbf_handle handle, const char* categoryname, const char** categoryroot); /* Find the root alias of a given category, defaulting to the current one */ int cbf_require_category_root (cbf_handle handle, const char* categoryname, const char** categoryroot); /* Set the root alias of a given category */ int cbf_set_category_root (cbf_handle handle, const char* categoryname, const char* categoryroot); /* Find the root alias of a given tag */ int cbf_find_tag_root (cbf_handle handle, const char* tagname, const char** tagroot); /* Find the root alias of a given tag, defaulting to the current one */ int cbf_require_tag_root (cbf_handle handle, const char* tagname, const char** tagroot); /* Set the root alias of a given tag */ int cbf_set_tag_root (cbf_handle handle, const char* tagname, const char* tagroot); /* Find the category of a given tag */ int cbf_find_tag_category (cbf_handle handle, const char* tagname, const char** categoryname); /* Set category of a given tag */ int cbf_set_tag_category (cbf_handle handle, const char* tagname, const char* categoryname); /* Validate portion of CBF */ int cbf_validate (cbf_handle handle, cbf_node * node, CBF_NODETYPE type, cbf_node * catnode); /* Load accumulator */ int cbf_mpint_load_acc(unsigned int * acc, size_t acsize, void * source, size_t elsize, int elsign, const char * border); /* Store accumulator */ int cbf_mpint_store_acc(unsigned int * acc, size_t acsize, void * dest, size_t elsize, int elsign, const char *border); /* Clear accumulator */ int cbf_mpint_clear_acc(unsigned int * acc, size_t acsize); /* Increment accumulator */ int cbf_mpint_increment_acc(unsigned int * acc, size_t acsize); /* Decrement accumulator */ int cbf_mpint_decrement_acc(unsigned int * acc, size_t acsize); /* Negate accumulator */ int cbf_mpint_negate_acc(unsigned int * acc, size_t acsize); /* Add to accumulator */ int cbf_mpint_add_acc(unsigned int * acc, size_t acsize, unsigned int * add, size_t addsize); /* Shift accumulator right */ int cbf_mpint_rightshift_acc(unsigned int * acc, size_t acsize, int shift); /* Shift accumulator left */ int cbf_mpint_leftshift_acc(unsigned int * acc, size_t acsize, int shift); /* get accumulator bit length */ int cbf_mpint_get_acc_bitlength(unsigned int * acc, size_t acsize, size_t * bitlength); /* Check value of type validity */ int cbf_check_type_contents(const char *type, const char *value); /* Regex Match function */ int cbf_match(const char *string, char *pattern); /* Interpreter for dREL method expression */ int cbf_drel(cbf_handle handle, cbf_handle dict, const char *mainitemname, const char *datablock, const char *expression); /* Construct Functions dictionary */ int cbf_construct_functions_dictionary(cbf_handle dict, const char *datablockname, const char *functionname); #ifdef __cplusplus } #endif #endif /* CBF_H */ ./CBFlib-0.9.2.2/include/md5.h0000644000076500007650000000250611603702115014062 0ustar yayayaya/* MD5.H - header file for MD5C.C */ /* Copyright (C) 1991-2, RSA Data Security, Inc. Created 1991. All rights reserved. License to copy and use this software is granted provided that it is identified as the "RSA Data Security, Inc. MD5 Message-Digest Algorithm" in all material mentioning or referencing this software or this function. License is also granted to make and use derivative works provided that such works are identified as "derived from the RSA Data Security, Inc. MD5 Message-Digest Algorithm" in all material mentioning or referencing the derived work. RSA Data Security, Inc. makes no representations concerning either the merchantability of this software or the suitability of this software for any particular purpose. It is provided "as is" without express or implied warranty of any kind. These notices must be retained in any copies of any part of this documentation and/or software. */ /* MD5 context. */ typedef struct { UINT4 state[4]; /* state (ABCD) */ UINT4 count[2]; /* number of bits, modulo 2^64 (lsb first) */ unsigned char buffer[64]; /* input buffer */ } MD5_CTX; void MD5Init PROTO_LIST ((MD5_CTX *)); void MD5Update PROTO_LIST ((MD5_CTX *, unsigned char *, unsigned int)); void MD5Final PROTO_LIST ((unsigned char [16], MD5_CTX *)); ./CBFlib-0.9.2.2/include/cbf_getopt.h0000644000076500007650000002135611603702115015515 0ustar yayayaya/********************************************************************** * cbf_getopt.h * * * * * * Created by Herbert J. Bernstein on 6/8/09. * * (C) Copyright 2009 Herbert J. Bernstein * * * * * * This is a functional replacement for gnu getopt * * for use with CBFlib to minimize porting problems and * * to ensure appropriateness of use under the LGPL * * * * The interface is _not_ a drop-in replacment for the * * gnu getopt interface. * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ #ifndef CBF_GETOPT_H #define CBF_GETOPT_H #ifdef __cplusplus extern "C" { #endif typedef struct { int optopt; /* character of the option if a "-x" option, this is 'x', whether given in options or not if a "--xxx" option, this is the option letter preceding the (xxx) in the options string if there is no option letter, 0 */ int optord; /* ordinal of the option in options, or -1 */ const char * optstr; /* the null-terminated character string of the option if a "-x" option is given, this is "x" if a "--xxx" option, this is "xxx" optstr is given whether the option is in options or not. A NULL is used for a value with no option */ const char * optval; /* the null-terminated character string of the option value, or null if none is given if the option is specified in options, the value may begin with '-', but if the option is not specified in options, a value that begins with '-' is treated as a new option */ } cbf_getopt_optstruct; typedef struct { cbf_getopt_optstruct * optstructs; /* array of optstructs */ size_t optstructs_size; /* count of valid optstructs in optstructs */ size_t optstructs_capacity; /* capacity of optstructs */ int optind; /* next option in optstructs to process */ const char * options; /* string of options: if x is a valid option that has a required argument, "x:" should appear in the string; if x is a valid option that has an optional argument, "x::" should appear in the string. If what follows "x" is the end of the string or is a character other than a ":", then x does not accept an option. If '(' appears, then all characters prior to the next matching ')' are the name of a long option If the options string begins with '-', all options are left in their original location, any options not specified in the options string are reported with optord -1 and if the next argv value is not an option, it is returned as the value. If the options string begins with '+', the first non-option cases all remaining argv elements to be return as values just as if as "--" had been encountered at that point Normally, non-options are sorted to the end of the list. */ } cbf_getopt_struct; typedef cbf_getopt_struct * cbf_getopt_handle; /* create a cbf_getopt handle */ int cbf_make_getopt_handle(cbf_getopt_handle * handle); /* free a cbf_getopt handle */ int cbf_free_getopt_handle(cbf_getopt_handle handle); /* Populate a cbf_getopt data structure and set to search from the first argument */ int cbf_getopt_parse ( cbf_getopt_handle handle, int argc, char ** argv, const char * options); /* Get first option from a cbf_getopt handle */ int cbf_rewind_getopt_option ( cbf_getopt_handle handle ); /* Get next option from a cbf_getopt handle */ int cbf_next_getopt_option ( cbf_getopt_handle handle ); /* Get option by number (0 ... ) from a cbf_getopt handle */ int cbf_select_getopt_option ( cbf_getopt_handle handle, unsigned int option ); /* Count the options in a cbf_getopt handle */ int cbf_count_getopt_options ( cbf_getopt_handle handle, unsigned int * options ); /* Get the data for an option */ int cbf_get_getopt_data ( cbf_getopt_handle handle, int * optopt, int * optord, const char * * optstr, const char ** optval); #ifdef __cplusplus } #endif #endif ./CBFlib-0.9.2.2/include/cbf_copy.h0000644000076500007650000004643611603702115015173 0ustar yayayaya/********************************************************************** * cbf_copy.h -- cbflib copy functions * * * * Version 0.9.1 23 February 2010 * * * * (C) Copyright 2010 Herbert J. Bernstein * * * * Part of the CBFlib API * * by * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term ‘this software’, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifndef CBF_COPY_H #define CBF_COPY_H #ifdef __cplusplus extern "C" { #endif #define CBF_HDR_FINDDIMS 0x0040 /* On read, find header dims */ #define CBF_HDR_NOFINDDIMS 0x0080 /* On read, don't find header dims */ #define CBF_CPY_SETINTEGER 0x0001 /* On write, force integer */ #define CBF_CPY_SETREAL 0x0002 /* On write, force real */ #define CBF_CPY_SETSIGNED 0x0004 /* On write, force signed */ #define CBF_CPY_SETUNSIGNED 0x0008 /* On write, force unsigned */ /* cbf_copy_cbf -- copy cbfin to cbfout */ int cbf_copy_cbf(cbf_handle cbfout, cbf_handle cbfin, const int compression, const int dimflag); /* cbf_copy_category -- copy the current category from cifin to the specified category in cifout */ int cbf_copy_category (cbf_handle cbfout, cbf_handle cbfin, const char * category_name, const int compression, const int dimflag); /* cbf_copy_datablock -- copy the current datablock from cifin to the next datablock in cifout */ int cbf_copy_datablock (cbf_handle cbfout, cbf_handle cbfin, const char * datablock_name, const int compression, const int dimflag); /* cbf_copy_value -- copy the current value from cbfin to cbfout, specifying the target category, column, rownum, compression, dimension details, element type, size and sign */ int cbf_copy_value(cbf_handle cbfout, cbf_handle cbfin, const char * category_name, const char * column_name, const unsigned int rownum, const int compression, const int dimflag, const int eltype, const int elsize, const int elsign, const double cliplow, const double cliphigh); #ifdef __cplusplus } #endif #endif /* CBF_COPY_H */ ./CBFlib-0.9.2.2/include/cbf_read_binary.h0000644000076500007650000004257111603702115016474 0ustar yayayaya/********************************************************************** * cbf_read_binary.h * * * * Version 0.7.6 14 July 2006 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifndef CBF_READ_BINARY_H #define CBF_READ_BINARY_H #ifdef __cplusplus extern "C" { #endif #include "cbf_file.h" /* Parse a binary header looking for the size and id */ int cbf_parse_binaryheader (cbf_file *file, size_t *size, long *id, unsigned int *compression, int mime); #ifdef __cplusplus } #endif #endif /* CBF_READ_MIME_H */ ./CBFlib-0.9.2.2/include/cbf_predictor.h0000644000076500007650000005050311603702115016202 0ustar yayayaya/********************************************************************** * cbf_predictor.h * * * * Version 0.8.0 20 July 2008 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifndef CBF_PREDICTOR_H #define CBF_PREDICTOR_H #ifdef __cplusplus extern "C" { #endif #include #include "cbf_file.h" /* Compress an array with the Predictor-Huffman algorithm */ int cbf_compress_predictor (void *source, size_t elsize, int elsign, size_t nelem, unsigned int compression, cbf_file *file, size_t *compressedsize, int *storedbits, int realarray, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); #define cbf_compress_predictor_fs(source,elsize,elsign,nelem,compression,file,compressedsize,storedbits,realarray,byteorder,dimfast,dimmid,dimslow,padding) \ cbf_compress_predictor((source),(elsize),(elsign),(nelem),(compression),(file),(compressedsize),(storedbits),(realarray),(byteorder),(dimfast),(dimmid),(dimslow),(padding)) #define cbf_compress_predictor_sf(source,elsize,elsign,nelem,compression,file,compressedsize,storedbits,realarray,byteorder,dimslow,dimmid,dimfast,padding) \ cbf_compress_predictor((source),(elsize),(elsign),(nelem),(compression),(file),(compressedsize),(storedbits),(realarray),(byteorder),(dimfast),(dimmid),(dimslow),(padding)) /* Decompress an array with the Predictor-Huffman algorithm */ int cbf_decompress_predictor (void *destination, size_t elsize, int elsign, size_t nelem, size_t *nelem_read, size_t compressedsize, unsigned int compression, int data_bits, int data_sign, cbf_file *file, int realarray, const char *byteorder, size_t dimover, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); #define cbf_decompress_predictor_fs(destination,elsize,elsign,nelem,nelem_read,compressedsize,compression,data_bits,data_sign,file,realarray,byteorder,dimover,dimfast,dimmid,dimslow,padding) \ cbf_decompress_predictor((destination),(elsize),(elsign),(nelem),(nelem_read),(compressedsize),(compression),(data_bits),(data_sign),(file),(realarray),(byteorder),(dimover),(dimfast),(dimmid),(dimslow),(padding)) #define cbf_decompress_predictor_sf(destination,elsize,elsign,nelem,nelem_read,compressedsize,compression,data_bits,data_sign,file,realarray,byteorder,dimover,dimslow,dimmid,dimfast,padding) \ cbf_decompress_predictor((destination),(elsize),(elsign),(nelem),(nelem_read),(compressedsize),(compression),(data_bits),(data_sign),(file),(realarray),(byteorder),(dimover),(dimfast),(dimmid),(dimslow),(padding)) #ifdef __cplusplus } #endif #endif /* CBF_PREDICTOR_H */ ./CBFlib-0.9.2.2/include/cbf_file.h0000644000076500007650000005551211603702115015133 0ustar yayayaya/********************************************************************** * cbf_file.h * * * * Version 0.7.6 14 July 2006 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifndef CBF_FILE_H #define CBF_FILE_H #ifdef __cplusplus extern "C" { #endif #include #include "global.h" #include "md5.h" /* File structure */ typedef struct { FILE *stream; /* File pointer */ FILE *logfile; /* NULL or an active stream for error logging */ int errors; /* logged error messages */ int warnings; /* logged warnings */ unsigned int connections; /* Number of pointers to this structure */ int temporary; /* Flag for temporary file (memres) */ int bits [2]; /* Buffer for bitwise reads and writes */ char *characters; /* Buffer for character writes */ char *characters_base; /* Buffer for character memres file */ size_t characters_size; /* Size of the buffer for character writes*/ size_t characters_used; /* Characters in the character buffer */ int last_read; /* The last character read */ unsigned int line; /* Current line */ unsigned int column; /* Current column */ unsigned int columnlimit; /* Ascii line column limit (80 or 2048) */ char *buffer; /* Buffer */ size_t buffer_size; /* Size of the buffer */ size_t buffer_used; /* Number in use */ int read_headers; /* message digest control (read) */ int write_headers; /* message digest and header type (write) */ int write_encoding; /* encoding and line terminations (write) */ MD5_CTX *digest; /* message digest context */ } cbf_file; /* Create and initialise a file */ int cbf_make_file (cbf_file **file, FILE *stream); /* Create and initialise a wide file */ int cbf_make_widefile (cbf_file **file, FILE *stream); /* Free a file */ int cbf_free_file (cbf_file **file); /* Add a file connection */ int cbf_add_fileconnection (cbf_file **file, FILE *stream); /* Remove a connection */ int cbf_delete_fileconnection (cbf_file **file); /* Count the connections */ int cbf_file_connections (cbf_file *file); /* Set the size of an input/output buffer */ int cbf_set_io_buffersize (cbf_file *file, size_t size); /* Set the size of an output buffer */ int cbf_set_buffersize (cbf_file *file, size_t size); /* Empty the buffer */ int cbf_reset_buffer (cbf_file *file); /* Add a character to the buffer */ int cbf_save_character (cbf_file *file, int c); /* Add a character to the buffer, trimming trailing spaces */ int cbf_save_character_trim (cbf_file *file, int c); /* Add a character to the buffer at a given position */ int cbf_save_character_at (cbf_file *file, int c, size_t position); /* Retrieve the buffer */ int cbf_get_buffer (cbf_file *file, const char **buffer, size_t *buffer_size); /* Get the file coordinates */ int cbf_get_filecoordinates (cbf_file *file, unsigned int *line, unsigned int *column); /* Set the file coordinates */ int cbf_set_filecoordinates (cbf_file *file, unsigned int line, unsigned int column); /* Read the next bit */ int cbf_get_bit (cbf_file *file); /* Read the next bits (signed) */ int cbf_get_bits (cbf_file *file, int *bitslist, int bitcount); /* Write bits */ int cbf_put_bits (cbf_file *file, int *bitslist, int bitcount); /* Read an integer as a series of bits */ int cbf_get_integer (cbf_file *file, int *val, int valsign, int bitcount); /* Write an integer as a series of bits */ int cbf_put_integer (cbf_file *file, int val, int valsign, int bitcount); /* Initialize a message digest */ int cbf_start_digest (cbf_file *file); /* Get the message digest */ int cbf_end_digest (cbf_file *file, char *digest); /* Discard any bits in the buffers */ int cbf_reset_bits (cbf_file *file); /* Discard any bits in the input buffers */ int cbf_reset_in_bits (cbf_file *file); /* Discard any characters in the character buffers */ int cbf_reset_characters (cbf_file *file); /* Flush any remaining bits (write) */ int cbf_flush_bits (cbf_file *file); /* Flush the character buffer (write) */ int cbf_flush_characters (cbf_file *file); /* Set output buffer size */ int cbf_set_output_buffersize (cbf_file *file, size_t size); /* Get the next character */ int cbf_get_character (cbf_file *file); /* Read the next character (convert end-of-line and update line and column) */ int cbf_read_character (cbf_file *file); /* Put the next character */ int cbf_put_character (cbf_file *file, int c); /* Write the next character (convert end-of-line and update line and column) */ int cbf_write_character (cbf_file *file, int c); /* Put a string */ int cbf_put_string (cbf_file *file, const char *string); /* Write a string (convert end-of-line and update line and column) */ int cbf_write_string (cbf_file *file, const char *string); /* Read a (CR/LF)-terminated line into the buffer */ int cbf_read_line (cbf_file *file, const char **line); /* Read nelem characters into the buffer */ int cbf_get_block (cbf_file *file, size_t nelem); /* Write nelem characters from the buffer */ int cbf_put_block (cbf_file *file, size_t nelem); /* Copy characters between files */ int cbf_copy_file (cbf_file *destination, cbf_file *source, size_t nelem); /* Get the file position */ int cbf_get_fileposition (cbf_file *file, long int *position); /* Set the file position */ int cbf_set_fileposition (cbf_file *file, long int position, int whence); #ifdef __cplusplus } #endif #endif /* CBF_FILE_H */ ./CBFlib-0.9.2.2/include/cbf_lex.h0000644000076500007650000004230411603702115014777 0ustar yayayaya/********************************************************************** * cbf_lex.h * * * * Version 0.7.6 14 July 2006 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifndef CBF_LEX_H #define CBF_LEX_H #ifdef __cplusplus extern "C" { #endif #include "cbf_tree.h" #include "cbf_file.h" #include "cbf_stx.h" #include /* Get the next token */ int cbf_lex (cbf_handle handle, YYSTYPE *val); #ifdef __cplusplus } #endif #endif /* CBF_LEX_H */ ./CBFlib-0.9.2.2/include/cbf_stx.h0000644000076500007650000000516611603702115015032 0ustar yayayaya/* A Bison parser, made by GNU Bison 2.3. */ /* Skeleton interface for Bison's Yacc-like parsers in C Copyright (C) 1984, 1989, 1990, 2000, 2001, 2002, 2003, 2004, 2005, 2006 Free Software Foundation, Inc. This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* As a special exception, you may create a larger work that contains part or all of the Bison parser skeleton and distribute that work under terms of your choice, so long as that work isn't itself a parser generator using the skeleton or a modified version thereof as a parser skeleton. Alternatively, if you modify or redistribute the parser skeleton itself, you may (at your option) remove this special exception, which will cause the skeleton and the resulting Bison output files to be licensed under the GNU General Public License without this special exception. This special exception was added by the Free Software Foundation in version 2.2 of Bison. */ /* Tokens. */ #ifndef YYTOKENTYPE # define YYTOKENTYPE /* Put the tokens into the symbol table, so that GDB and other debuggers know about them. */ enum yytokentype { DATA = 258, DEFINE = 259, SAVE = 260, SAVEEND = 261, LOOP = 262, ITEM = 263, CATEGORY = 264, COLUMN = 265, STRING = 266, CBFWORD = 267, BINARY = 268, UNKNOWN = 269, COMMENT = 270, ERROR = 271 }; #endif /* Tokens. */ #define DATA 258 #define DEFINE 259 #define SAVE 260 #define SAVEEND 261 #define LOOP 262 #define ITEM 263 #define CATEGORY 264 #define COLUMN 265 #define STRING 266 #define CBFWORD 267 #define BINARY 268 #define UNKNOWN 269 #define COMMENT 270 #define ERROR 271 #if ! defined YYSTYPE && ! defined YYSTYPE_IS_DECLARED typedef union YYSTYPE { int errorcode; const char *text; cbf_node *node; } /* Line 1529 of yacc.c. */ YYSTYPE; # define yystype YYSTYPE /* obsolescent; will be withdrawn */ # define YYSTYPE_IS_DECLARED 1 # define YYSTYPE_IS_TRIVIAL 1 #endif ./CBFlib-0.9.2.2/include/cbf_write_binary.h0000644000076500007650000004244011603702115016706 0ustar yayayaya/********************************************************************** * cbf_write_binary.h * * * * Version 0.7.6 14 July 2006 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifndef CBF_WRITE_BINARY_H #define CBF_WRITE_BINARY_H #ifdef __cplusplus extern "C" { #endif #include "cbf_tree.h" /* Write a binary value */ int cbf_write_binary (cbf_node *column, unsigned int row, cbf_file *file, int isbuffer); #ifdef __cplusplus } #endif #endif /* CBF_WRITE_BINARY_H */ ./CBFlib-0.9.2.2/include/cbf_byte_offset.h0000644000076500007650000005053211603702115016522 0ustar yayayaya/********************************************************************** * cbf_byte_offset.h * * * * Version 0.8.0 20 July 2008 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifndef CBF_BYTE_OFFSET_H #define CBF_BYTE_OFFSET_H #ifdef __cplusplus extern "C" { #endif #include #include "cbf_file.h" /* Compress an array with the byte-offset algorithm */ int cbf_compress_byte_offset (void *source, size_t elsize, int elsign, size_t nelem, unsigned int compression, cbf_file *file, size_t *compressedsize, int *storedbits, int realarray, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); #define cbf_compress_byte_offset_fs(source,elsize,elsign,nelem,compression,file,compressedsize,storedbits,realarray,byteorder,dimfast,dimmid,dimslow,padding) \ cbf_compress_byte_offset((source),(elsize),(elsign),(nelem),(compression),(file),(compressedsize),(storedbits),(realarray),(byteorder),(dimfast),(dimmid),(dimslow),(padding)) #define cbf_compress_byte_offset_sf(source,elsize,elsign,nelem,compression,file,compressedsize,storedbits,realarray,byteorder,dimslow,dimmid,dimfast,padding) \ cbf_compress_byte_offset((source),(elsize),(elsign),(nelem),(compression),(file),(compressedsize),(storedbits),(realarray),(byteorder),(dimfast),(dimmid),(dimslow),(padding)) /* Decompress an array with the byte-offset algorithm */ int cbf_decompress_byte_offset (void *destination, size_t elsize, int elsign, size_t nelem, size_t *nelem_read, size_t compressedsize, unsigned int compression, int bits, int sign, cbf_file *file, int realarray, const char *byteorder, size_t dimover, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); #define cbf_decompress_byte_offset_fs(destination,elsize,elsign,nelem,nelem_read,compressedsize,compression,bits,sign,file,realarray,byteorder,dimover,dimfast,dimmid,dimslow,padding) \ cbf_decompress_byte_offset((destination),(elsize),(elsign),(nelem),(nelem_read),(compressedsize),(compression),(bits),(sign),(file),(realarray),(byteorder),(dimover),(dimfast),(dimmid),(dimslow),(padding)) #define cbf_decompress_byte_offset_sf(destination,elsize,elsign,nelem,nelem_read,compressedsize,compression,bits,sign,file,realarray,byteorder,dimover,dimslow,dimmid,dimfast,padding) \ cbf_decompress_byte_offset((destination),(elsize),(elsign),(nelem),(nelem_read),(compressedsize),(compression),(bits),(sign),(file),(realarray),(byteorder),(dimover),(dimfast),(dimmid),(dimslow),(padding)) #ifdef __cplusplus } #endif #endif /* CBF_BYTE_OFFSET_H */ ./CBFlib-0.9.2.2/include/cbf_tree.h0000644000076500007650000005370111603702115015151 0ustar yayayaya/********************************************************************** * cbf_tree.h * * * * Version 0.7.6 14 July 2006 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifndef CBF_TREE_H #define CBF_TREE_H #ifdef __cplusplus extern "C" { #endif #include "cbf_context.h" /* Node types */ typedef enum { CBF_UNDEFNODE, /* Undefined */ CBF_LINK, /* Link */ CBF_ROOT, /* Root */ CBF_DATABLOCK, /* Datablock */ CBF_SAVEFRAME, /* Saveframe */ CBF_CATEGORY, /* Category */ CBF_COLUMN, /* Column */ CBF_VALUE, /* Value */ /* Not a visible node type */ CBF_FUNCTION, /* Function */ CBF_BKT, /* Bracket */ CBF_BRC, /* Brace */ CBF_PRN /* Paren */ } CBF_NODETYPE; /* Node structure */ typedef struct cbf_node_struct { CBF_NODETYPE type; cbf_context *context; const char *name; struct cbf_node_struct *parent; struct cbf_node_struct *link; unsigned int children; size_t child_size; struct cbf_node_struct **child; } cbf_node; /* Prototypes */ /* Undo links and promote to the first non-link freeing the memory for the links */ int cbf_undo_links (cbf_node **node); /* These function will not trace a link */ /* Free a node */ int cbf_free_node (cbf_node *node); /* Set the number of children */ int cbf_set_children (cbf_node *node, unsigned int children); /* Change a link */ int cbf_set_link (cbf_node *link, cbf_node *node); /* Add a child link */ int cbf_add_link (cbf_node *link, cbf_node *child); /* Set a link successively to each child link */ int cbf_shift_link (cbf_node *link); /* These function will trace a link */ /* Trace a link */ cbf_node *cbf_get_link (const cbf_node *node); /* Find a child node */ int cbf_find_child (cbf_node **child, const cbf_node *node, const char *name); /* Find a child node by name and type */ int cbf_find_typed_child (cbf_node **child, const cbf_node *node, const char *name, CBF_NODETYPE type); /* Find a child node, accepting the last match */ int cbf_find_last_child (cbf_node **child, const cbf_node *node, const char *name); /* Find a child node, accepting the last match */ int cbf_find_last_typed_child (cbf_node **child, const cbf_node *node, const char *name, CBF_NODETYPE type); /* Find a parent node */ int cbf_find_parent (cbf_node **parent, const cbf_node *node, CBF_NODETYPE type); /* Count the number of children */ int cbf_count_children (unsigned int *children, const cbf_node *node); /* Count the number of children of a given type */ int cbf_count_typed_children (unsigned int *children, const cbf_node *node, CBF_NODETYPE type); /* Get the index of a child */ int cbf_child_index (unsigned int *index, const cbf_node *node); /* Get the specified child */ int cbf_get_child (cbf_node **child, const cbf_node *node, unsigned int index); /* Add a child to a node */ int cbf_add_child (cbf_node *node, cbf_node *child); /* Add a child to a node with duplicates allowed */ int cbf_add_new_child (cbf_node *node, cbf_node *child); /* Get the name of a node */ int cbf_get_name (const char **name, cbf_node *node); /* All of the following functions assume that the string arguments have been created using cbf_copy_string and that no pointers to the strings are retained by the calling functions */ /* Name a node */ int cbf_name_node (cbf_node *node, const char *name); /* Name a node allowing for duplicates */ int cbf_name_new_node (cbf_node *node, const char *name); /* Make a new node */ int cbf_make_node (cbf_node **node, CBF_NODETYPE type, cbf_context *context, const char *name); /* Make a new node allowing for duplicates */ int cbf_make_new_node (cbf_node **node, CBF_NODETYPE type, cbf_context *context, const char *name); /* Make a new child node */ int cbf_make_child (cbf_node **child, cbf_node *node, CBF_NODETYPE type, const char *name); /* Make a new child node, with duplicates allowed */ int cbf_make_new_child (cbf_node **child, cbf_node *node, CBF_NODETYPE type, const char *name); /* Get the value of a row */ int cbf_get_columnrow (const char **value, const cbf_node *column, unsigned int row); /* Set the value of a row */ int cbf_set_columnrow (cbf_node *column, unsigned int row, const char *value, int free); /* Insert a value in a column */ int cbf_insert_columnrow (cbf_node *column, unsigned int row, const char *value); /* Delete a value from a column */ int cbf_delete_columnrow (cbf_node *column, unsigned int row); /* Add a value to a column */ int cbf_add_columnrow (cbf_node *column, const char *value); /* compute a hash code for a string */ int cbf_compute_hashcode(const char *string, unsigned int *hashcode); #ifdef __cplusplus } #endif #endif /* CBF_TREE_H */ ./CBFlib-0.9.2.2/include/global.h0000644000076500007650000000316511603702115014637 0ustar yayayaya/* GLOBAL.H - RSAREF types and constants */ /* Copyright (C) 1991-2, RSA Data Security, Inc. Created 1991. All rights reserved. License to copy and use this software is granted provided that it is identified as the "RSA Data Security, Inc. MD5 Message-Digest Algorithm" in all material mentioning or referencing this software or this function. License is also granted to make and use derivative works provided that such works are identified as "derived from the RSA Data Security, Inc. MD5 Message-Digest Algorithm" in all material mentioning or referencing the derived work. RSA Data Security, Inc. makes no representations concerning either the merchantability of this software or the suitability of this software for any particular purpose. It is provided "as is" without express or implied warranty of any kind. These notices must be retained in any copies of any part of this documentation and/or software. */ /* PROTOTYPES should be set to one if and only if the compiler supports function argument prototyping. The following makes PROTOTYPES default to 0 if it has not already been defined with C compiler flags. */ #ifndef PROTOTYPES #define PROTOTYPES 0 #endif /* POINTER defines a generic pointer type */ typedef unsigned char *POINTER; /* UINT2 defines a two byte word */ typedef unsigned short int UINT2; /* UINT4 defines a four byte word */ typedef unsigned int UINT4; /* PROTO_LIST is defined depending on how PROTOTYPES is defined above. If using PROTOTYPES, then PROTO_LIST returns the list, otherwise it returns an empty list. */ #if PROTOTYPES #define PROTO_LIST(list) list #else #define PROTO_LIST(list) () #endif ./CBFlib-0.9.2.2/include/cbff.h0000644000076500007650000036512011603702115014301 0ustar yayayaya/********************************************************************** * cbff -- cbflib C rouitnes for fortran access * * * * Version 0.8.1 1 March 2009 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2009 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term ‘this software’, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifdef CBFF_H #define CBFF_H #ifdef __cplusplus extern "C" { #endif #include #include "cbf.h" #include "cbf_simple.h" /* Return the bit pattern of a FILE * pointer as a size_t opaque handle */ size_t cbff_file(FILE * file); /* Return the FILE * pointer for a size_t opaque handle */ FILE * cbff_file_handle(const size_t cbffFile); /* Return the bit pattern of a cbf_handle as a size_t opaque handle */ size_t cbff_handle(cbf_handle cbfHandle)); /* Return the cbf_handle for a size_t opaque handle */ cbf_handle cbff_cbf_handle(size_t CBFFhandle); /* Return the bit pattern of a goniometer as a size_t opaque handle */ size_t cbff_goniometer(cbf_goniometer cbfGoniometer); /* Return the goniometer handle for a size_t opaque handle */ cbf_goniometer cbff_cbf_goniometer(size_t CBFFgoniometer); /* Return the bit pattern of a detector as a size_t opaque handle */ size_t cbff_detector(cbf_detector cbfDetector); /* Return the detector handle for a size_t opaque handle */ cbf_detector cbff_cbf_detector(size_t CBFFdetector); /* Return the bit pattern of a node handle as a size_t opaque handle */ size_t cbff_node_handle(cbf_node * cbfNode); /* Return the node handle for a size_t opaque handle */ cbf_node * cbff_cbf_node_handle(size_t cbffNode); CBF_NODETYPE cbff_cbf_nodetype(char * str) ; int cbff_nodetype(CBF_NODETYPE nodetype, char * nodetypestring, int start_nodetypestring, int end_nodetypestring, int * status_nodetypestring); /* Return a size_t opaque handle from an fopen */ size_t cbff_fopen(const char * filename, const char * mode); int cbff_fclose(const size_t cbffFile); /* Create a handle */ int cbff_make_handle(size_t * CBFFhandle); /* Free a handle */ int cbff_free_handle( size_t CBFFhandle); /* Read a file */ int cbff_read_file( size_t CBFFhandle, size_t CBFFstream, int flags); /* Read a wide file */ int cbff_read_widefile( size_t CBFFhandle, size_t CBFFstream, int flags); /* Read a pre-read buffered file */ int cbff_read_buffered_file( size_t CBFFhandle, size_t CBFFstream, int flags, const char * buffer, size_t buffer_len); /* Write a file */ int cbff_write_file( size_t CBFFhandle, size_t CBFFstream, int isbuffer, int ciforcbf, int headers, int encoding); /* Write a file, starting at the local node */ int cbff_write_local_file( size_t CBFFhandle, size_t CBFFstream, int isbuffer, int ciforcbf, int headers, int encoding); /* Write a wide file */ int cbff_write_widefile( size_t CBFFhandle, size_t CBFFstream, int isbuffer, int ciforcbf, int headers, int encoding); /* Add a data block */ int cbff_new_datablock( size_t CBFFhandle, const char * datablockname); /* Add a save frame block */ int cbff_new_saveframe( size_t CBFFhandle, const char * saveframename); /* Add a data block, allowing for duplicates */ int cbff_force_new_datablock( size_t CBFFhandle, const char * datablockname); /* Add a save frame, allowing for duplicates */ int cbff_force_new_saveframe( size_t CBFFhandle, const char * saveframename); /* Add a category to the current data block */ int cbff_new_category( size_t CBFFhandle, const char * categoryname); /* Add a category to the current data block, allowing for duplicates */ int cbff_force_new_category( size_t CBFFhandle, const char * categoryname); /* Add a column to the current category */ int cbff_new_column( size_t CBFFhandle, const char * columnname); /* Add a row to the current category */ int cbff_new_row( size_t CBFFhandle); /* Insert a row in the current category */ int cbff_insert_row( size_t CBFFhandle, const int rownumber); /* Delete a row from the current category */ int cbff_delete_row( size_t CBFFhandle, const int rownumber); /* Change the name of the current data block */ int cbff_set_datablockname( size_t CBFFhandle, const char * datablockname); /* Change the name of the current save frame */ int cbff_set_saveframename( size_t CBFFhandle, const char * saveframename); /* Delete all categories from all the data blocks */ int cbff_reset_datablocks( size_t CBFFhandle); /* Delete all categories from the current data block */ int cbff_reset_datablock( size_t CBFFhandle); /* Delete all categories from the current save frame */ int cbff_reset_saveframe( size_t CBFFhandle); /* Delete all columns and rows from the current category */ int cbff_reset_category( size_t CBFFhandle); /* Delete the current data block */ int cbff_remove_datablock( size_t CBFFhandle); /* Delete the current save frame */ int cbff_remove_saveframe( size_t CBFFhandle); /* Delete the current category */ int cbff_remove_category( size_t CBFFhandle); /* Delete the current column */ int cbff_remove_column( size_t CBFFhandle); /* Delete the current row */ int cbff_remove_row( size_t CBFFhandle); /* Make the first data block the current data block */ int cbff_rewind_datablock( size_t CBFFhandle); /* Make the first category in the current data block the current category */ int cbff_rewind_category( size_t CBFFhandle); /* Make the first save frame in the current data block the current category */ int cbff_rewind_saveframe( size_t CBFFhandle); /* Make the first category or save frame in the current data block the current category */ int cbff_rewind_blockitem( size_t CBFFhandle, char * copy_type, size_t start_type, size_t end_type, int * status_type); /* Make the first column in the current category the current column */ int cbff_rewind_column( size_t CBFFhandle); /* Make the first row in the current category the current row */ int cbff_rewind_row( size_t CBFFhandle); /* Make the next data block the current data block */ int cbff_next_datablock( size_t CBFFhandle); /* Make the next save frame in the current data block the current save frame */ int cbff_next_saveframe( size_t CBFFhandle); /* Make the next category in the current data block the current category */ int cbff_next_category( size_t CBFFhandle); /* Make the next save frame or category the current data block or category */ int cbff_next_blockitem( size_t CBFFhandle, char * copy_type, size_t start_type, size_t end_type, int * status_type); /* Make the next column in the current category the current column */ int cbff_next_column( size_t CBFFhandle); /* Make the next row in the current category the current row */ int cbff_next_row( size_t CBFFhandle); /* Make the named data block the current data block */ int cbff_find_datablock( size_t CBFFhandle, const char * datablockname); /* Make the named save frame in the current data block the current save frame */ int cbff_find_saveframe( size_t CBFFhandle, const char * saveframe); /* Make the named category in the current data block or save frame the current category */ int cbff_find_category( size_t CBFFhandle, const char * categoryname); /* Make the named column in the current category the current column */ int cbff_find_column( size_t CBFFhandle, const char * columnname); /* Make the first row with matching value the current row */ int cbff_find_row( size_t CBFFhandle, const char * value); /* Make the first row with matching value the current row creating it if necessary */ int cbff_require_row( size_t CBFFhandle, const char * value); /* Make the next row with matching value the current row */ int cbff_find_nextrow( size_t CBFFhandle, const char * value); /* Make the next row with matching value the current row, creating the row if necessary */ int cbff_require_nextrow( size_t CBFFhandle, const char * value); /* Count the data blocks */ int cbff_count_datablocks( size_t CBFFhandle, unsigned int * datablocks); /* Count the save frames in the current data block */ int cbff_count_saveframes( size_t CBFFhandle, unsigned int * saveframes); /* Count the categories in the current data block */ int cbff_count_categories( size_t CBFFhandle, unsigned int * categories); /* Count the items in the current data block */ int cbff_count_blockitems( size_t CBFFhandle, unsigned int * blockitems); /* Count the columns in the current category */ int cbff_count_columns( size_t CBFFhandle, unsigned int * columns); /* Count the rows in the current category */ int cbff_count_rows( size_t CBFFhandle, unsigned int * rows); /* Make the specified data block the current data block */ int cbff_select_datablock( size_t CBFFhandle, unsigned int datablock); /* Make the specified save frame the current save frame */ int cbff_select_saveframe( size_t CBFFhandle, unsigned int saveframe); /* Make the specified category the current category */ int cbff_select_category( size_t CBFFhandle, unsigned int category); /* Make the specified category or save frame the current block item */ int cbff_select_blockitem( size_t CBFFhandle, unsigned int item, char * copy_type, size_t start_type, size_t end_type, int * status_type); /* Make the specified column the current column */ int cbff_select_column( size_t CBFFhandle, unsigned int column); /* Make the specified row the current row */ int cbff_select_row( size_t CBFFhandle, unsigned int row); /* Get the name of the current data block */ int cbff_datablock_name( size_t CBFFhandle, char * copy_datablockname, size_t start_datablockname, size_t end_datablockname, int * status_datablockname); /* Get the name of the current save frame */ int cbff_saveframe_name( size_t CBFFhandle, char * copy_saveframename, size_t start_saveframename, size_t end_saveframename, int * status_saveframename); /* Get the name of the current category */ int cbff_category_name( size_t CBFFhandle, char * copy_categoryname, size_t start_categoryname, size_t end_categoryname, int * status_categoryname); /* Get the name of the current column */ int cbff_column_name( size_t CBFFhandle, char * copy_columnname, size_t start_columnname, size_t end_columnname, int * status_columnname); /* Get the number of the current row */ int cbff_row_number( size_t CBFFhandle, unsigned int * row); /* Get the number of the current column */ int cbff_column_number( size_t CBFFhandle, unsigned int * column); /* Get the number of the current block item */ int cbff_blockitem_number( size_t CBFFhandle, unsigned int * blockitem); /* Get the ascii value of the current (row, column) entry */ int cbff_get_value( size_t CBFFhandle, char * copy_value, size_t start_value, size_t end_value, int * status_value); /* Set the ascii value of the current (row, column) entry */ int cbff_set_value( size_t CBFFhandle, const char * value); /* Get the ascii value of the current (row, column) entry, setting it to a default value if necessary */ int cbff_require_value( size_t CBFFhandle, char * copy_value, size_t start_value, size_t end_value, int * status_value, const char * defaultvalue); /* Get the ascii type of value of the current (row, column) entry */ int cbff_get_typeofvalue( size_t CBFFhandle, char * copy_typeofvalue, size_t start_typeofvalue, size_t end_typeofvalue, int * status_typeofvalue); /* Set the ascii type of value of the current (row, column) entry */ int cbff_set_typeofvalue( size_t CBFFhandle, const char * typeofvalue); /* Get the (int) numeric value of the current (row, column) entry */ int cbff_get_integervalue( size_t CBFFhandle, int * number); /* Get the (double) numeric value of the current (row, column) entry */ int cbff_get_doublevalue( size_t CBFFhandle, double * number); /* Set the ascii value of the current (row, column) entry from an int */ int cbff_set_integervalue( size_t CBFFhandle, int number); /* Set the ascii value of the current (row, column) entry from a double */ int cbff_set_doublevalue( size_t CBFFhandle, const char * format, double number); /* Get the (integer) numeric value of the current (row, column) entry, setting it if necessary */ int cbff_require_integervalue( size_t CBFFhandle, int * number, int defaultvalue); /* Get the (double) numeric value of the current (row, column) entry, setting it if necessary */ int cbff_require_doublevalue( size_t CBFFhandle, double * number, double defaultvalue); /* Get the parameters of the current (row, column) array entry */ int cbff_get_arrayparameters( size_t CBFFhandle, unsigned int * compression, int * id, size_t * elsize, int * elsigned, int * elunsigned, size_t * nelem, int * minelem, int * maxelem, int * realarray); /* Get the parameters of the current (row, column) array entry */ int cbff_get_arrayparameters_wdims( size_t CBFFhandle, unsigned int * compression, int * id, size_t * elsize, int * elsigned, int * elunsigned, size_t * nelem, int * minelem, int * maxelem, int * realarray, char * copy_byteorder, size_t start_byteorder, size_t end_byteorder, int * status_byteorder, size_t * dimfast, size_t * dimmid, size_t * dimslow, size_t * padding); int cbff_get_arrayparameters_wdims_fs( size_t CBFFhandle, unsigned int * compression, int * id, size_t * elsize, int * elsigned, int * elunsigned, size_t * nelem, int * minelem, int * maxelem, int * realarray, char * copy_byteorder, size_t start_byteorder, size_t end_byteorder, int * status_byteorder, size_t * dimfast, size_t * dimmid, size_t * dimslow, size_t * padding); int cbff_get_arrayparameters_wdims_sf( size_t CBFFhandle, unsigned int * compression, int * id, size_t * elsize, int * elsigned, int * elunsigned, size_t * nelem, int * minelem, int * maxelem, int * realarray, char * copy_byteorder, size_t start_byteorder, size_t end_byteorder, int * status_byteorder, size_t * dimslow, size_t * dimmid, size_t * dimfast, size_t * padding); /* Get the parameters of the current (row, column) integer array entry */ int cbff_get_integerarrayparameters( size_t CBFFhandle, unsigned int * compression, int * id, size_t * elsize, int * elsigned, int * elunsigned, size_t * nelem, int * minelem, int * maxelem); /* Get the parameters of the current (row, column) integer array entry */ int cbff_get_integerarrayparameters_wdims( size_t CBFFhandle, unsigned int * compression, int * id, size_t * elsize, int * elsigned, int * elunsigned, size_t * nelem, int * minelem, int * maxelem, char * copy_byteorder, size_t start_byteorder, size_t end_byteorder, int * status_byteorder, size_t * dimfast, size_t * dimmid, size_t * dimslow, size_t * padding); int cbff_get_integerarrayparameters_wdims_fs( size_t CBFFhandle, unsigned int * compression, int * id, size_t * elsize, int * elsigned, int * elunsigned, size_t * nelem, int * minelem, int * maxelem, char * copy_byteorder, size_t start_byteorder, size_t end_byteorder, int * status_byteorder, size_t * dimfast, size_t * dimmid, size_t * dimslow, size_t * padding); int cbff_get_integerarrayparameters_wdims_sf( size_t CBFFhandle, unsigned int * compression, int * id, size_t * elsize, int * elsigned, int * elunsigned, size_t * nelem, int * minelem, int * maxelem, char * copy_byteorder, size_t start_byteorder, size_t end_byteorder, int * status_byteorder, size_t * dimslow, size_t * dimmid, size_t * dimfast, size_t * padding); /* Get the integer value of the current (row, column) array entry */ int cbff_get_integerarray( size_t CBFFhandle, int * id, void * value, size_t elsize, int elsign, size_t nelem, size_t * nelem_read); /* Get the real value of the current (row, column) array entry */ int cbff_get_realarray( size_t CBFFhandle, int * id, void * value, size_t elsize, size_t nelem, size_t * nelem_read); /* Get the parameters of the current (row, column) array entry */ int cbff_get_realarrayparameters( size_t CBFFhandle, unsigned int * compression, int * id, size_t * elsize, size_t * nelem); /* Get the parameters of the current (row, column) array entry */ int cbff_get_realarrayparameters_wdims( size_t CBFFhandle, unsigned int * compression, int * id, size_t * elsize, size_t * nelem, char * copy_byteorder, size_t start_byteorder, size_t end_byteorder, int * status_byteorder, size_t * dimfast, size_t * dimmid, size_t * dimslow, size_t * padding); int cbff_get_realarrayparameters_wdims_fs( size_t CBFFhandle, unsigned int * compression, int * id, size_t * elsize, size_t * nelem, char * copy_byteorder, size_t start_byteorder, size_t end_byteorder, int * status_byteorder, size_t * dimfast, size_t * dimmid, size_t * dimslow, size_t * padding); int cbff_get_realarrayparameters_wdims_sf( size_t CBFFhandle, unsigned int * compression, int * id, size_t * elsize, size_t * nelem, char * copy_byteorder, size_t start_byteorder, size_t end_byteorder, int * status_byteorder, size_t * dimslow, size_t * dimmid, size_t * dimfast, size_t * padding); /* Set the integer value of the current (row, column) array entry */ int cbff_set_integerarray( size_t CBFFhandle, unsigned int compression, int id, void * value, size_t elsize, int elsign, size_t nelem); /* Set the integer value of the current (row, column) array entry */ int cbff_set_integerarray_wdims( size_t CBFFhandle, unsigned int compression, int id, void * value, size_t elsize, int elsign, size_t nelem, const char * byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); int cbff_set_integerarray_wdims_fs( size_t CBFFhandle, unsigned int compression, int id, void * value, size_t elsize, int elsign, size_t nelem, const char * byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); int cbff_set_integerarray_wdims_sf( size_t CBFFhandle, unsigned int compression, int id, void * value, size_t elsize, int elsign, size_t nelem, const char * byteorder, size_t dimslow, size_t dimmid, size_t dimfast, size_t padding); /* Set the real value of the current (row, column) array entry */ int cbff_set_realarray( size_t CBFFhandle, unsigned int compression, int id, void * value, size_t elsize, size_t nelem); /* Set the real value of the current (row, column) array entry with dimensions */ int cbff_set_realarray_wdims( size_t CBFFhandle, unsigned int compression, int id, void * value, size_t elsize, size_t nelem, const char * byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); int cbff_set_realarray_wdims_fs( size_t CBFFhandle, unsigned int compression, int id, void * value, size_t elsize, size_t nelem, const char * byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); int cbff_set_realarray_wdims_sf( size_t CBFFhandle, unsigned int compression, int id, void * value, size_t elsize, size_t nelem, const char * byteorder, size_t dimslow, size_t dimmid, size_t dimfast, size_t padding); /* Issue a warning message */ void cbf_warning (const char *message); /* Issue an error message */ void cbf_error (const char *message); /* issue a log message for a cbf */ void cbf_log (cbf_handle handle, const char *message, int logflags); /* issue a log message for a cbf_file */ void cbf_flog (cbf_file * file, const char *message, int logflags); /* Find a datablock, creating it if necessary */ int cbff_require_datablock( size_t CBFFhandle, const char * datablockname); /* Find a category, creating it if necessary */ int cbff_require_category( size_t CBFFhandle, const char * categoryname); /* Find a column, creating it if necessary */ int cbff_require_column( size_t CBFFhandle, const char * columnname); /* Find a column value, return a default if necessary */ int cbff_require_column_value( size_t CBFFhandle, const char * columnname, char * copy_value, size_t start_value, size_t end_value, int * status_value, const char * defaultvalue); /* Find a column integer value, return a default if necessary */ int cbff_require_column_integervalue( size_t CBFFhandle, const char * columnname, int * number, const int defaultvalue); /* Find a column double value, return a default if necessary */ int cbff_require_column_doublevalue( size_t CBFFhandle, const char * columnname, double * number, const double defaultvalue); /* Get the local byte order of the default integer type */ int cbff_get_local_integer_byte_order( char * copy_byte_order, size_t start_byte_order, size_t end_byte_order, int * status_byte_order); /* Get the local byte order of the default real type */ int cbff_get_local_real_byte_order( char * copy_byte_order, size_t start_byte_order, size_t end_byte_order, int * status_byte_order); /* Get the local real format */ int cbff_get_local_real_format( char * copy_real_format, size_t start_real_format, size_t end_real_format, int * status_real_format); /* Get the dictionary for a cbf */ int cbff_get_dictionary( size_t CBFFhandle, cbf_handle * dictionary); /* Set the dictionary for a cbf */ int cbff_set_dictionary( size_t CBFFhandle, size_t CBFFdictionary); /* Get the dictionary for a cbf, or create one */ int cbff_require_dictionary( size_t CBFFhandle, size_t * CBFFdictionary); /* Put the value into the named column, updating the hash table links */ int cbff_set_hashedvalue( size_t CBFFhandle, const char * value, const char * columnname, int valuerow); /* Find value in the named column, using the hash table links */ int cbff_find_hashedvalue( size_t CBFFhandle, const char * value, const char * columnname, int caseinsensitive); /* Take a defintion from a dictionary and insert it into the has tables of a cbf dictionary */ int cbff_convert_dictionary_definition( size_t CBFFhandle, size_t CBFFhandle, const char * name); /* Increment a column */ int cbff_increment_column( size_t CBFFhandle, const char* columnname, int * count); /* Reset a column */ int cbff_reset_column( size_t CBFFhandle, const char* columnname); /* Reset reference counts for a dictionary */ int cbff_reset_refcounts( size_t CBFFhandle); /* Convert a DDL1 or DDL2 dictionary and add it to a CBF dictionary */ int cbff_convert_dictionary( size_t CBFFhandle, size_t CBFFhandle); /* Find the requested tag anywhere in the cbf, make it the current column */ int cbff_find_tag( size_t CBFFhandle, const char * tag); /* Find the requested tag in the cbf within the current save frame or data block, make it the current column */ int cbff_find_local_tag( size_t CBFFhandle, const char * tag); /* Find the requested category and column anywhere in the cbf, make it the current column */ int cbff_srch_tag( size_t CBFFhandle, cbf_node * node, const char * categoryname, const char * columnname); /* Find the root alias of a given category */ int cbff_find_category_root( size_t CBFFhandle, const char* categoryname, char * copy_categoryroot, size_t start_categoryroot, size_t end_categoryroot, int * status_categoryroot); /* Find the root alias of a given category, defaulting to the current one */ int cbff_require_category_root( size_t CBFFhandle, const char* categoryname, char * copy_categoryroot, size_t start_categoryroot, size_t end_categoryroot, int * status_categoryroot); /* Set the root alias of a given category */ int cbff_set_category_root( size_t CBFFhandle, const char* categoryname, const char* categoryroot); /* Find the root alias of a given tag */ int cbff_find_tag_root( size_t CBFFhandle, const char* tagname, char * copy_tagroot, size_t start_tagroot, size_t end_tagroot, int * status_tagroot); /* Find the root alias of a given tag, defaulting to the current one */ int cbff_require_tag_root( size_t CBFFhandle, const char* tagname, char * copy_tagroot, size_t start_tagroot, size_t end_tagroot, int * status_tagroot); /* Set the root alias of a given tag */ int cbff_set_tag_root( size_t CBFFhandle, const char* tagname, const char* tagroot); /* Find the category of a given tag */ int cbff_find_tag_category( size_t CBFFhandle, const char* tagname, char * copy_categoryname, size_t start_categoryname, size_t end_categoryname, int * status_categoryname); /* Set category of a given tag */ int cbff_set_tag_category( size_t CBFFhandle, const char* tagname, const char* categoryname); /* Validate portion of CBF */ int cbff_validate( size_t CBFFhandle, size_t CBFFnode, char * CBFFtype, size_t CBFFcatnode); /* Load accumulator */ int cbff_mpint_load_acc( unsigned int * acc, size_t acsize, void * source, size_t elsize, int elsign, const char * border); /* Store accumulator */ int cbff_mpint_store_acc( unsigned int * acc, size_t acsize, void * dest, size_t elsize, int elsign, const char * border); /* Clear accumulator */ int cbff_mpint_clear_acc( unsigned int * acc, size_t acsize); /* Increment accumulator */ int cbff_mpint_increment_acc( unsigned int * acc, size_t acsize); /* Decrement accumulator */ int cbff_mpint_decrement_acc( unsigned int * acc, size_t acsize); /* Negate accumulator */ int cbff_mpint_negate_acc( unsigned int * acc, size_t acsize); /* Add to accumulator */ int cbff_mpint_add_acc( unsigned int * acc, size_t acsize, unsigned int * add, size_t addsize); /* Shift accumulator right */ int cbff_mpint_rightshift_acc( unsigned int * acc, size_t acsize, int shift); /* Shift accumulator left */ int cbff_mpint_leftshift_acc( unsigned int * acc, size_t acsize, int shift); /* Check value of type validity */ int cbff_check_type_contents( const char * type, const char * value); /* Regex Match function */ int cbff_match( const char * string, char * pattern); /* Read a template file */ int cbff_read_template( size_t CBFFhandle, size_t CBFFstream); /* Get the diffrn.id entry */ int cbff_get_diffrn_id( size_t CBFFhandle, char * copy_diffrn_id, size_t start_diffrn_id, size_t end_diffrn_id, int * status_diffrn_id); /* Change the diffrn.id entry in all the categories */ int cbff_set_diffrn_id( size_t CBFFhandle, const char * diffrn_id); /* Change the diffrn.id entry, creating it if necessary */ int cbff_require_diffrn_id( size_t CBFFhandle, char * copy_diffrn_id, size_t start_diffrn_id, size_t end_diffrn_id, int * status_diffrn_id, const char * default_id); /* Get the diffrn.crystal_id entry */ int cbff_get_crystal_id( size_t CBFFhandle, char * copy_crystal_id, size_t start_crystal_id, size_t end_crystal_id, int * status_crystal_id); /* Change the diffrn.crystal_id entry */ int cbff_set_crystal_id( size_t CBFFhandle, const char * crystal_id); /* Get the wavelength */ int cbff_get_wavelength( size_t CBFFhandle, double * wavelength); /* Set the wavelength */ int cbff_set_wavelength( size_t CBFFhandle, double wavelength); /* Get the polarization */ int cbff_get_polarization( size_t CBFFhandle, double * polarizn_source_ratio, double * polarizn_source_norm); /* Set the polarization */ int cbff_set_polarization( size_t CBFFhandle, double polarizn_source_ratio, double polarizn_source_norm); /* Get the divergence */ int cbff_get_divergence( size_t CBFFhandle, double * div_x_source, double * div_y_source, double * div_x_y_source); /* Set the divergence */ int cbff_set_divergence( size_t CBFFhandle, double div_x_source, double div_y_source, double div_x_y_source); /* Get the number of elements */ int cbff_count_elements( size_t CBFFhandle, unsigned int * elements); /* Get the element id */ int cbff_get_element_id( size_t CBFFhandle, unsigned int element_number, char * copy_element_id, size_t start_element_id, size_t end_element_id, int * status_element_id); /* Get the detector id */ int cbff_get_detector_id( size_t CBFFhandle, unsigned int element_number, char * copy_detector_id, size_t start_detector_id, size_t end_detector_id, int * status_detector_id); /* Get the array id for a given detector element */ int cbff_get_array_id( size_t CBFFhandle, unsigned int element_number, char * copy_array_id, size_t start_array_id, size_t end_array_id, int * status_array_id); /* Get the pixel size of a detector element in a given direction */ int cbff_get_pixel_size( size_t CBFFhandle, unsigned int element_number, int axis_number, double * psize); int cbff_get_pixel_size_fs( size_t CBFFhandle, unsigned int element_number, int axis_number, double * psize); int cbff_get_pixel_size_sf( size_t CBFFhandle, unsigned int element_number, int axis_number, double * psize); /* Set the pixel size of a detector element in a given direction */ int cbff_set_pixel_size( size_t CBFFhandle, unsigned int element_number, int axis_number, double psize){ return cbf_set_pixel_size; int cbff_set_pixel_size_fs( size_t CBFFhandle, unsigned int element_number, int axis_number, double psize); int cbff_set_pixel_size_sf( size_t CBFFhandle, unsigned int element_number, int axis_number, double psize); /* Get the gain of a detector element */ int cbff_get_gain( size_t CBFFhandle, unsigned int element_number, double * gain, double * gain_esd); /* Set the gain of a detector element */ int cbff_set_gain( size_t CBFFhandle, unsigned int element_number, double gain, double gain_esd); /* Get the bin sizes of a detector element */ int cbff_get_bin_sizes( size_t CBFFhandle, unsigned int element_number, double * slowbinsize, double * fastbinsize); /* Set the bin sizes of a detector element */ int cbff_set_bin_sizes( size_t CBFFhandle, unsigned int element_number, double slowbinsize, double fastbinsize); /* Get the overload value of a detector element */ int cbff_get_overload( size_t CBFFhandle, unsigned int element_number, double * overload); /* Set the overload value of a detector element */ int cbff_set_overload( size_t CBFFhandle, unsigned int element_number, double overload); /* Get the integration time */ int cbff_get_integration_time( size_t CBFFhandle, unsigned int reserved, double * time); /* Set the integration time */ int cbff_set_integration_time( size_t CBFFhandle, unsigned int reserved, double time); /* Convert gregorian to julian date (in days) */ double cbff_gregorian_julian (int year, int month, int day, int hour, int minute, double second); /* Get the collection date and time (1) as seconds since January 1 1970 */ int cbff_get_timestamp( size_t CBFFhandle, unsigned int reserved, double * time, int * timezone); /* Get the collection date and time (2) as individual fields */ int cbff_get_datestamp( size_t CBFFhandle, unsigned int reserved, int * year, int * month, int * day, int * hour, int * minute, double * second, int * timezone); /* Set the collection date and time (1) as seconds since January 1 1970 */ int cbff_set_timestamp( size_t CBFFhandle, unsigned int reserved, double time, int timezone, double precision); /* Set the collection date and time (2) as individual fields */ int cbff_set_datestamp( size_t CBFFhandle, unsigned int reserved, int year, int month, int day, int hour, int minute, double second, int timezone, double precision); /* Set the collection date and time (3) as current time to the second */ int cbff_set_current_timestamp( size_t CBFFhandle, unsigned int reserved, int timezone); /* Get the image size */ int cbff_get_image_size( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, size_t * ndimslow, size_t * ndimfast); int cbff_get_image_size_fs( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, size_t * ndimfast, size_t * ndimslow); int cbff_get_image_size_sf( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, size_t * ndimslow, size_t * ndimfast); /* Read a binary section into an image. ndimslow is the slow dimension, ndimfast is fast dimension.*/ int cbff_get_image( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast); int cbff_get_image_fs( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, void * array, size_t elsize, int elsign, size_t ndimfast, size_t ndimslow); int cbff_get_image_sf( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast); /* Read a binary section into a real image. ndimslow is the slow dimension, ndimfast is fast dimension.*/ int cbff_get_real_image( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, void * array, size_t elsize, size_t ndimslow, size_t ndimfast); int cbff_get_real_image_fs( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, void * array, size_t elsize, size_t ndimfast, size_t ndimslow); int cbff_get_real_image_sf( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, void * array, size_t elsize, size_t ndimslow, size_t ndimfast); /* Get the 3D image size. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_get_3d_image_size( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, size_t * ndimslow, size_t * ndimmid, size_t * ndimfast); int cbff_get_3d_image_size_fs( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, size_t * ndimfast, size_t * ndimmid, size_t * ndimlow); int cbff_get_3d_image_size_sf( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, size_t * ndimslow, size_t * ndimmid, size_t * ndimfast); /* Read a 3D binary section into an image. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_get_3d_image( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); int cbff_get_3d_image_fs( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, void * array, size_t elsize, int elsign, size_t ndimfast, size_t ndimmid, size_t ndimslow); int cbff_get_3d_image_sf( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); /* Read a 3D binary section into a real image. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_get_real_3d_image( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, void * array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); int cbff_get_real_3d_image_fs( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, void * array, size_t elsize, size_t ndimfast, size_t ndimmid, size_t ndimslow); int cbff_get_real_3d_image_sf( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, void * array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); /* Save an image. ndimslow is the slow dimension, ndimfast is fast. */ int cbff_set_image( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, unsigned int compression, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast); int cbff_set_image_fs( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, unsigned int compression, void * array, size_t elsize, int elsign, size_t ndimfast, size_t ndimslow); int cbff_set_image_sf( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, unsigned int compression, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast); /* Save a real image. ndimslow is the slow dimension, ndimfast is fast. */ int cbff_set_real_image( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, unsigned int compression, void * array, size_t elsize, size_t ndimslow, size_t ndimfast); int cbff_set_real_image_fs( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, unsigned int compression, void * array, size_t elsize, size_t ndimfast, size_t ndimslow); int cbff_set_real_image_sf( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, unsigned int compression, void * array, size_t elsize, size_t ndimslow, size_t ndimfast); /* Save a 3D image. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension. */ int cbff_set_3d_image( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, unsigned int compression, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); int cbff_set_3d_image_fs( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, unsigned int compression, void * array, size_t elsize, int elsign, size_t ndimfast, size_t ndimmid, size_t ndimslow); int cbff_set_3d_image_sf( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, unsigned int compression, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); /* Save a real 3D image. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_set_real_3d_image( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, unsigned int compression, void * array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); int cbff_set_real_3d_image_fs( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, unsigned int compression, void * array, size_t elsize, size_t ndimfast, size_t ndimmid, size_t ndimslow); int cbff_set_real_3d_image_sf( size_t CBFFhandle, unsigned int reserved, unsigned int element_number, unsigned int compression, void * array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); /* Get the array_id for a map segment or map segment mask. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension. */ int cbff_get_map_array_id( size_t CBFFhandle, unsigned int reserved, const char * segment_id, char * copy_array_id, size_t start_array_id, size_t end_array_id, int * status_array_id, int ismask, int require, size_t ndimslow, size_t ndimmid, size_t ndimfast); int cbff_get_map_array_id_fs( size_t CBFFhandle, unsigned int reserved, const char * segment_id, char * copy_array_id, size_t start_array_id, size_t end_array_id, int * status_array_id, int ismask, int require, size_t ndimfast, size_t ndimmid, size_t ndimslow); int cbff_get_map_array_id_sf( size_t CBFFhandle, unsigned int reserved, const char * segment_id, char * copy_array_id, size_t start_array_id, size_t end_array_id, int * status_array_id, int ismask, int require, size_t ndimslow, size_t ndimmid, size_t ndimfast); /* Get the map segment size. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_get_map_segment_size( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, size_t * ndimslow, size_t * ndimmid, size_t * ndimfast); int cbff_get_map_segment_size_fs( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, size_t * ndimfast, size_t * ndimmid, size_t * ndimslow); int cbff_get_map_segment_size_sf( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, size_t * ndimslow, size_t * ndimmid, size_t * ndimfast); /* Read a map segment. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_get_map_segment( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); int cbff_get_map_segment_fs( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, void * array, size_t elsize, int elsign, size_t ndimfast, size_t ndimmid, size_t ndimslow); int cbff_get_map_segment_sf( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); /* Read a map segment mask. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_get_map_segment_mask( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); int cbff_get_map_segment_mask_fs( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, void * array, size_t elsize, int elsign, size_t ndimfast, size_t ndimmid, size_t ndimslow); int cbff_get_map_segment_mask_sf( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); /* Read a real map segment. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_get_real_map_segment( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, void * array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); int cbff_get_real_map_segment_fs( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, void * array, size_t elsize, size_t ndimfast, size_t ndimmid, size_t ndimslow); int cbff_get_real_map_segment_sf( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, void * array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); /* Read a real map segment mask. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_get_real_map_segment_mask( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, void * array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); int cbff_get_real_map_segment_mask_fs( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, void * array, size_t elsize, size_t ndimfast, size_t ndimmid, size_t ndimslow); int cbff_get_real_map_segment_mask_sf( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, void * array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); /* Save a map segment. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_set_map_segment( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, unsigned int compression, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); int cbff_set_map_segment_fs( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, unsigned int compression, void * array, size_t elsize, int elsign, size_t ndimfast, size_t ndimmid, size_t ndimslow); int cbff_set_map_segment_sf( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, unsigned int compression, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); /* Save a map segment mask. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_set_map_segment_mask( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, unsigned int compression, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); int cbff_set_map_segment_mask_fs( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, unsigned int compression, void * array, size_t elsize, int elsign, size_t ndimfast, size_t ndimmid, size_t ndimslow); int cbff_set_map_segment_mask_sf( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, unsigned int compression, void * array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); /* Save a real map segment. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_set_real_map_segment( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, unsigned int compression, void * array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); int cbff_set_real_map_segment_fs( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, unsigned int compression, void * array, size_t elsize, size_t ndimfast, size_t ndimmid, size_t ndimslow); int cbff_set_real_map_segment_sf( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, unsigned int compression, void * array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); /* Save a real map segment mask. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_set_real_map_segment_mask( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, unsigned int compression, void * array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast){ return cbf_set_real_map_segment_mask( cbff_cbf_handle(CBFFhandle), reserved, segment_id, binary_id, compression, array, elsize, ndimslow, ndimmid, ndimfast); } int cbff_set_real_map_segment_mask_fs( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, unsigned int compression, void * array, size_t elsize, size_t ndimfast, size_t ndimmid, size_t ndimslow); int cbff_set_real_map_segment_mask_sf( size_t CBFFhandle, unsigned int reserved, const char * segment_id, int * binary_id, unsigned int compression, void * array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); /* Get the 3D array size. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_get_3d_array_size( size_t CBFFhandle, unsigned int reserved, const char * array_id, size_t * ndimslow, size_t * ndimmid, size_t * ndimfast){ return cbf_get_3d_array_size( cbff_cbf_handle(CBFFhandle), reserved, array_id, ndimslow, ndimmid, ndimfast); } int cbff_get_3d_array_size_fs( size_t CBFFhandle, unsigned int reserved, const char * array_id, size_t * ndimfast, size_t * ndimmid, size_t * ndimslow){ return cbf_get_3d_array_size( cbff_cbf_handle(CBFFhandle), reserved, array_id, ndimslow, ndimmid, ndimfast); } int cbff_get_3d_array_size_sf( size_t CBFFhandle, unsigned int reserved, const char * array_id, size_t * ndimslow, size_t * ndimmid, size_t * ndimfast); /* Read a 3D array. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_get_3d_array( size_t CBFFhandle, unsigned int reserved, const char * array_id, int * binary_id, void * array, int eltype, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); int cbff_get_3d_array_fs( size_t CBFFhandle, unsigned int reserved, const char * array_id, int * binary_id, void * array, int eltype, size_t elsize, int elsign, size_t ndimfast, size_t ndimmid, size_t ndimslow); int cbff_get_3d_array_sf( size_t CBFFhandle, unsigned int reserved, const char * array_id, int * binary_id, void * array, int eltype, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); /* Save a 3D array. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbff_set_3d_array( size_t CBFFhandle, unsigned int reserved, const char * array_id, int * binary_id, unsigned int compression, void * array, int eltype, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); int cbff_set_3d_array_fs( size_t CBFFhandle, unsigned int reserved, const char * array_id, int * binary_id, unsigned int compression, void * array, int eltype, size_t elsize, int elsign, size_t ndimfast, size_t ndimmid, size_t ndimslow); int cbff_set_3d_array_sf( size_t CBFFhandle, unsigned int reserved, const char * array_id, int * binary_id, unsigned int compression, void * array, int eltype, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); /* Get the setting of an axis */ int cbff_get_axis_setting( size_t CBFFhandle, unsigned int reserved, const char * axis_id, double * start, double * increment); /* Get the reference setting of an axis */ int cbff_get_axis_reference_setting( size_t CBFFhandle, unsigned int reserved, const char * axis_id, double * refsetting); /* Change the setting of an axis */ int cbff_set_axis_setting( size_t CBFFhandle, unsigned int reserved, const char * axis_id, double start, double increment); /* Change the reference setting of an axis */ int cbff_set_axis_reference_setting( size_t CBFFhandle, unsigned int reserved, const char * axis_id, double refsetting); /* Construct a goniometer */ int cbff_construct_goniometer( size_t CBFFhandle, size_t * CBFFgoniometer); /* Free a goniometer */ int cbff_free_goniometer( size_t CBFFgoniometer); /* Get the rotation axis */ int cbff_get_rotation_axis( size_t CBFFgoniometer, unsigned int reserved, double * vector1, double * vector2, double * vector3); /* Get the rotation range */ int cbff_get_rotation_range( size_t CBFFgoniometer, unsigned int reserved, double * start, double * increment); /* Reorient a vector */ int cbff_rotate_vector( size_t CBFFgoniometer, unsigned int reserved, double ratio, double initial1, double initial2, double initial3, double * final1, double * final2, double * final3); /* Convert a vector to reciprocal space */ int cbff_get_reciprocal( size_t CBFFgoniometer, unsigned int reserved, double ratio, double wavelength, double real1, double real2, double real3, double * reciprocal1, double * reciprocal2, double * reciprocal3); /* Construct a detector positioner */ int cbff_construct_detector( size_t CBFFhandle, size_t * CBFFdetector, unsigned int element_number); /* Construct a reference detector positioner */ int cbff_construct_reference_detector( size_t CBFFhandle, size_t * CBFFdetector, unsigned int element_number); /* Construct a detector positioner, creating the necessary categories, and columns */ int cbff_require_detector( size_t CBFFhandle, size_t * CBFFdetector, unsigned int element_number); /* Construct a reference detector positioner, creating the necessary categories, and columns */ int cbff_require_reference_detector( size_t CBFFhandle, size_t * CBFFdetector, unsigned int element_number); /* Free a detector */ int cbff_free_detector( size_t CBFFdetector); /* Get the beam center */ int cbff_get_beam_center( size_t CBFFdetector, double * indexslow, double * indexfast, double * centerslow, double * centerfast); int cbff_get_beam_center_fs( size_t CBFFdetector, double * indexfast, double * indexslow, double * centerfast, double * centerslow); int cbff_get_beam_center_sf( size_t CBFFdetector, double * indexslow, double * indexfast, double * centerslow, double * centerfast); /* Set the beam center */ int cbff_set_beam_center( size_t CBFFdetector, double * indexslow, double * indexfast, double * centerslow, double * centerfast); int cbff_set_beam_center_fs( size_t CBFFdetector, double * indexfast, double * indexslow, double * centerfast, double * centerslow); int cbff_set_beam_center_sf( size_t CBFFdetector, double * indexslow, double * indexfast, double * centerslow, double * centerfast); /* Set the reference beam center */ int cbff_set_reference_beam_center( size_t CBFFdetector, double * indexslow, double * indexfast, double * centerslow, double * centerfast); int cbff_set_reference_beam_center_fs( size_t CBFFdetector, double * indexfast, double * indexslow, double * centerfast, double * centerslow); int cbff_set_reference_beam_center_sf( size_t CBFFdetector, double * indexslow, double * indexfast, double * centerslow, double * centerfast); /* Get the detector distance */ int cbff_get_detector_distance( size_t CBFFdetector, double * distance); /* Get the detector normal */ int cbff_get_detector_normal( size_t CBFFdetector, double * normal1, double * normal2, double * normal3); /* Calcluate the coordinates of a pixel */ int cbff_get_pixel_coordinates( size_t CBFFdetector, double indexslow, double indexfast, double * coordinate1, double * coordinate2, double * coordinate3); int cbff_get_pixel_coordinates_fs( size_t CBFFdetector, double indexfast, double indexslow, double * coordinate1, double * coordinate2, double * coordinate3); int cbff_get_pixel_coordinates_sf( size_t CBFFdetector, double indexslow, double indexfast, double * coordinate1, double * coordinate2, double * coordinate3); /* Get the pixel normal */ int cbff_get_pixel_normal( size_t CBFFdetector, double indexslow, double indexfast, double * normal1, double * normal2, double * normal3); int cbff_get_pixel_normal_fs( size_t CBFFdetector, double indexfast, double indexslow, double * normal1, double * normal2, double * normal3); int cbff_get_pixel_normal_sf( size_t CBFFdetector, double indexslow, double indexfast, double * normal1, double * normal2, double * normal3); /* Calcluate the area of a pixel */ int cbff_get_pixel_area( size_t CBFFdetector, double indexslow, double indexfast, double * area, double * projected_area){ return cbf_get_pixel_area( cbff_cbf_detector(CBFFdetector), indexslow, indexfast, area, projected_area); } int cbff_get_pixel_area_fs( size_t CBFFdetector, double indexfast, double indexslow, double * area, double * projected_area){ return cbf_get_pixel_area( cbff_cbf_detector(CBFFdetector), indexslow, indexfast, area, projected_area); } int cbff_get_pixel_area_sf( size_t CBFFdetector, double indexslow, double indexfast, double * area, double * projected_area); /* Calcluate the size of a pixel from the detector element axis displacements */ int cbff_get_inferred_pixel_size( size_t CBFFdetector, int axis_number, double * psize); int cbff_get_inferred_pixel_size_fs( size_t CBFFdetector, int axis_number, double * psize); int cbff_get_inferred_pixel_size_sf( size_t CBFFdetector, int axis_number, double * psize); /* Get the unit cell parameters */ int cbff_get_unit_cell( size_t CBFFhandle, double cell[6], double cell_esd[6]); /* Set the unit cell parameters */ int cbff_set_unit_cell( size_t CBFFhandle, double cell[6], double cell_esd[6]); /* Get the reciprocal cell parameters */ int cbff_get_reciprocal_cell( size_t CBFFhandle, double cell[6], double cell_esd[6]); /* Set the reciprocal cell parameters */ int cbff_set_reciprocal_cell( size_t CBFFhandle, double cell[6], double cell_esd[6]); /* Compute a cell volume */ int cbff_compute_cell_volume( double cell[6], double * volume); /* Compute a reciprocal cell */ int cbff_compute_reciprocal_cell( double cell[6], double rcell[6]); /* Get the orientation matrix entry */ int cbff_get_orientation_matrix( size_t CBFFhandle, double ub_matrix[9]); /* Set the orientation matrix entry */ int cbff_set_orientation_matrix( size_t CBFFhandle, double ub_matrix[9]); #ifdef __cplusplus } #endif #endif ./CBFlib-0.9.2.2/include/cbf_ws.h0000644000076500007650000005203711603702115014644 0ustar yayayaya/********************************************************************** * cbf_ws.h * * * * Version 0.9.0 26 April 2009 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term ‘this software’, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ /* 1. The prefix ws is reserved for special whitespace categories and tag. 2. For any given tag, , in a category, , whitespace and comments for the tag and its value(s) will be given by .ws_ (for DDL2 style tag naming) or ws_tag (for DDLm and DDL1 style undotted naming). In all cases this tag will be part of the same category as 3. For any given category, , whitespace and comments for the category as a whole will be given by _ws__.ws_ (note the double underscore). This category ws__ is distinct from . 4. For any given data block or save frame, whitespace and comments for the data block or save frame as whole will be given by _ws_.ws_ 5. Whitespace and comments may be given as a prologue (intended to be presented before the element), zero or more emlogues (intended to be presented between the initial sub-element, e.g. "loop_" or the tag name and the rest of the element) or an epilogue (intended to be presented after the element as a whole). We use the term "-logues" for prologues, emlogues and epilogue The –logues for an element may be given as a single string, in which case only an epilogue is intended or as a bracketed construct (using parentheses) with multiple –logues. If only one –logue is given, ir is the epilogue. If two –logues are given, the first is the prologue and the second id the epilogue. If more emlogues are given than there are breaks in the element, the extra emolgues are prepended to the epilogue. The emlogues for a bracketed construct may also be bracketed constructs to provide whitespace and comments within bracketed constructs. 6. A prologue, emlogue or epilogue is a string of one or more lines starting with a optional colon-terminated column position for that line, followed by optional whitespace, followed by an optional comment. If no column position is given the whitespace begins at the next syntactically valid location. If a column position is given, then, on writing, a new line will be started if necessary to align to that column. A column position with no whitespace and no comment simply provides alignment for the next sub-element. If the end of a –logue line is a comment, whatever follows will be forced to a new line */ #ifndef CBF_WS_H #define CBF_WS_H #ifdef __cplusplus extern "C" { #endif #include "cbf.h" #include "cbf_ascii.h" #include "cbf_binary.h" #include "cbf_compress.h" #include "cbf_file.h" #include "cbf_tree.h" #include "cbf_write.h" #include "cbf_write_binary.h" #include "cbf_read_mime.h" #include "cbf_string.h" #include #include #include #include typedef enum {pro, em, epi} logue; /* insert a column number into the buffer for the commentfile */ int cbf_set_ws_column (cbf_file * commentfile, size_t columnumber); /* Apply pending whitespace to new node */ int cbf_apply_ws(cbf_handle handle); /* scan a string for a bracketed substring at level targetdepth and index targetindex */ int cbf_find_bracketstring(const char * string, const char * stringlimit, const char * stringtype, char * * bracketstring, char * * bracketstringlimit, int * more, size_t targetdepth, size_t targetindex ); /* Write an ascii whitespace value */ int cbf_write_ws_ascii (const char *string, cbf_file *file); /* Write a ws and comment value to a file */ int cbf_write_ws_value (cbf_node *column, unsigned int row, cbf_file *file, int isbuffer, logue whichlogue); int cbf_write_ws_prologue(const cbf_node *node, cbf_file *file, int isbuffer); int cbf_write_ws_emlogue(const cbf_node *node, cbf_file *file, int isbuffer); int cbf_write_ws_epilogue(const cbf_node *node, cbf_file *file, int isbuffer); #ifdef __cplusplus } #endif #endif /* CBF_WS_H */ ./CBFlib-0.9.2.2/include/cbf_alloc.h0000644000076500007650000004302311603702115015300 0ustar yayayaya/********************************************************************** * cbf_alloc.h * * * * Version 0.7.6 14 July 2006 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifndef CBF_ALLOC_H #define CBF_ALLOC_H #ifdef __cplusplus extern "C" { #endif #include /* Allocate a block of memory */ int cbf_alloc (void **new_block, size_t *new_nelem, size_t elsize, size_t nelem); /* Reallocate a block of memory (never lose the old block on failure) */ int cbf_realloc (void **old_block, size_t *old_nelem, size_t elsize, size_t nelem); /* Free a block of memory as text*/ int cbf_free_text (const char **old_block, size_t *old_nelem); /* Free a block of memory */ int cbf_free (void **old_block, size_t *old_nelem); #ifdef __cplusplus } #endif #endif /* CBF_ALLOC_H */ ./CBFlib-0.9.2.2/include/cbf_string.h0000644000076500007650000004261711603702115015524 0ustar yayayaya/********************************************************************** * cbf_string.h * * * * Version 0.8.0 20 July 2008 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifndef CBF_STRING_H #define CBF_STRING_H #ifdef __cplusplus extern "C" { #endif #include /* Case-insensitive strcmp */ int cbf_cistrcmp (const char *s1, const char *s2); /* Case-insensitive strncmp */ int cbf_cistrncmp (const char *s1, const char *s2, size_t n); /* swap bytes in an array (local copy of swab to deal with systems that lack swab */ int cbf_swab(const void * src, void * dst, size_t len); #ifdef __cplusplus } #endif #endif /* CBF_FILE_H */ ./CBFlib-0.9.2.2/include/cbf_ascii.h0000644000076500007650000004326611603702115015307 0ustar yayayaya/********************************************************************** * cbf_ascii.h * * * * Version 0.7.6 14 July 2006 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifndef CBF_ASCII_H #define CBF_ASCII_H #ifdef __cplusplus extern "C" { #endif #include "cbf_file.h" /* Format the next, possibly folded text line in fline, updating the pointer in string to be ready for the next pass. fline_size is the valid line length. fline must be one longer to allow for termination.*/ int cbf_foldtextline(const char** string, char* fline, int fline_size, int unfoldme, int foldme, char termc ); /* Write an ascii value */ int cbf_write_ascii (cbf_handle handle, const char *string, cbf_file *file); #ifdef __cplusplus } #endif #endif /* CBF_ASCII_H */ ./CBFlib-0.9.2.2/include/cbf_context.h0000644000076500007650000004447711603702115015710 0ustar yayayaya/********************************************************************** * cbf_context.h * * * * Version 0.7.6 14 July 2006 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifndef CBF_CONTEXT_H #define CBF_CONTEXT_H #ifdef __cplusplus extern "C" { #endif #include "cbf_file.h" #include /* Context structure */ typedef struct { cbf_file *temporary; /* Temporary file */ unsigned int connections; /* Number of pointers to this structure */ } cbf_context; /* Create and initialise a context */ int cbf_make_context (cbf_context **context); /* Free a context */ int cbf_free_context (cbf_context **context); /* Add a context connection */ int cbf_add_contextconnection (cbf_context **context); /* Remove a context connection */ int cbf_delete_contextconnection (cbf_context **context); /* Open a temporary file connection */ int cbf_open_temporary (cbf_context *context, cbf_file **temporary); /* Close a temporary file connection */ int cbf_close_temporary (cbf_context *context, cbf_file **temporary); /* Copy a string */ const char *cbf_copy_string (cbf_context *context, const char *string, char type); /* Copy a two strings */ const char *cbf_copy_strings (cbf_context *context, const char *string1, const char *string2, char type); /* Free a string */ void cbf_free_string (cbf_context *context, const char *string); #ifdef __cplusplus } #endif #endif /* CBF_CONTEXT_H */ ./CBFlib-0.9.2.2/include/cbf_binary.h0000644000076500007650000005060411603702115015475 0ustar yayayaya/********************************************************************** * cbf_binary.h * * * * Version 0.8.0 20 July 2008 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006,2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifndef CBF_BINARY_H #define CBF_BINARY_H #ifdef __cplusplus extern "C" { #endif #include "cbf_tree.h" /* Parse a binary text value */ int cbf_get_bintext (cbf_node *column, unsigned int row, int *type, int *id, cbf_file **file, long *start, size_t *size, int *checked_digest, char *digest, int *elsize, int *elsign, int *reallarray, const char **byteorder, size_t *dimover, size_t *dim1, size_t *dim2, size_t *dim3, size_t *padding, unsigned int *compression); /* Set a binary text value */ int cbf_set_bintext (cbf_node *column, unsigned int row, int type, int id, cbf_file *file, long start, long size, int checked_digest, const char *digest, int elsize, int elsign, int realarray, const char *byteorder, size_t dimover, size_t dim1, size_t dim2, size_t dim3, size_t padding, unsigned int compression); /* Check for a binary value */ int cbf_is_binary (cbf_node *column, unsigned int row); /* Is this an encoded binary value? */ int cbf_is_mimebinary (cbf_node *column, unsigned int row); /* Free a value */ int cbf_free_value (cbf_context *context, cbf_node *column, unsigned int row); /* Set a binary value */ int cbf_set_binary (cbf_node *column, unsigned int row, unsigned int compression, int binary_id, void *value, size_t elsize, int elsign, size_t nelem, int realarray, const char *byteorder, size_t dimover, size_t dim1, size_t dim2, size_t dim3, size_t padding); /* Check the message digest */ int cbf_check_digest (cbf_node *column, unsigned int row); /* Get the parameters of a binary value */ int cbf_binary_parameters (cbf_node *column, unsigned int row, unsigned int *compression, int *binary_id, int *eltype, size_t *elsize, int *elsigned, int *elunsigned, size_t *nelem, int *minelem, int *maxelem, int *realarray, const char **byteorder, size_t *dim1, size_t *dim2, size_t *dim3, size_t *padding); /* Get a binary value */ int cbf_get_binary (cbf_node *column, unsigned int row, int *binary_id, void *value, size_t elsize, int elsign, size_t nelem, size_t *nelem_read, int *realarray, const char **byteorder, size_t *dimover, size_t *dim1, size_t *dim2, size_t *dim3, size_t *padding); #ifdef __cplusplus } #endif #endif /* CBF_BINARY_H */ ./CBFlib-0.9.2.2/include/cbf_read_mime.h0000644000076500007650000004703511603702115016137 0ustar yayayaya/********************************************************************** * cbf_read_mime.h * * * * Version 0.8.0 20 July 2008 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifndef CBF_READ_MIME_H #define CBF_READ_MIME_H #ifdef __cplusplus extern "C" { #endif #include "cbf_file.h" /* Convert a MIME-encoded binary section to a temporary binary section */ int cbf_mime_temp (cbf_node *column, unsigned int row); /* Find non-blank length of a line */ int cbf_nblen (const char *line, size_t *nblen); /* Convert a MIME-encoded binary section to a normal binary section */ int cbf_read_mime (cbf_file *infile, cbf_file *outfile, size_t *size, long *id, char *old_digest, char *new_digest); /* Parse the MIME header looking for values of type: Content-Type: Content-Transfer-Encoding: Content-MD5: X-Binary-Size: X-Binary-ID: X-Binary-Element-Type: X-Binary-Element-Byte-Order: X-Binary-Size-Number-of-Elements; X-Binary-Size-Fastest-Dimension: X-Binary-Size-Second-Dimension: X-Binary-Size-Third-Dimension: X-Binary-Size-Padding: */ int cbf_parse_mimeheader (cbf_file *file, int *encoding, size_t *size, long *id, char *digest, unsigned int *compression, int *bits, int *sign, int *real, const char **byteorder, size_t *dimover, size_t *dimfast, size_t *dimmid, size_t *dimslow, size_t *padding); #define cbf_parse_mimeheader_fs(file, encoding, size, id, digest, compression, bits, sign, real, byteorder, dimover, dimfast, dimmid, dimslow, padding) \ cbf_parse_mimeheader((file),(encoding),(size),(id),(digest),(compression),(bits),(sign),(real),(byteorder),(dimover),(dimfast),(dimmid),(dimslow),(padding) ) #define cbf_parse_mimeheader_sf(file, encoding, size, id, digest, compression, bits, sign, real, byteorder, dimover, dimslow, dimmid, dimfast, padding) \ cbf_parse_mimeheader((file),(encoding),(size),(id),(digest),(compression),(bits),(sign),(real),(byteorder),(dimover),(dimfast),(dimmid),(dimslow),(padding) ) #ifdef __cplusplus } #endif #endif /* CBF_READ_MIME_H */ ./CBFlib-0.9.2.2/include/cbf_uncompressed.h0000644000076500007650000005007111603702115016716 0ustar yayayaya/********************************************************************** * cbf_uncompressed.h * * * * Version 0.8.0 20 July 2008 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifndef CBF_UNCOMPRESSED_H #define CBF_UNCOMPRESSED_H #ifdef __cplusplus extern "C" { #endif #include #include "cbf_file.h" /* Copy an array without compression */ int cbf_compress_none (void *source, size_t elsize, int elsign, size_t nelem, unsigned int compression, cbf_file *file, size_t *compressedsize, int *storedbits, int realarray, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); #define cbf_compress_none_fs(source,elsize,elsign,nelem,compression,file,compressedsize,storedbits,realarray,byteorder,dimfast,dimmid,dimslow,padding) \ cbf_compress_none((source),(elsize),(elsign),(nelem),(compression),(file),(compressedsize),(storedbits),(realarray),(byteorder),(dimfast),(dimmid),(dimslow),(padding)) #define cbf_compress_none_sf(source,elsize,elsign,nelem,compression,file,compressedsize,storedbits,realarray,byteorder,dimslow,dimmid,dimfast,padding) \ cbf_compress_none((source),(elsize),(elsign),(nelem),(compression),(file),(compressedsize),(storedbits),(realarray),(byteorder),(dimfast),(dimmid),(dimslow),(padding)) /* Recover an array without decompression */ int cbf_decompress_none (void *destination, size_t elsize, int elsign, size_t nelem, size_t *nelem_read, size_t compressedsize, unsigned int compression, int data_bits, int data_sign, cbf_file *file, int realarray, const char *byteorder, size_t dimover, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); #define cbf_decompress_none_fs(destination,elsize,elsign,nelem,nelem_read,compressedsize,compression,bits,sign,file,realarray,byteorder,dimover,dimfast,dimmid,dimslow,padding) \ cbf_decompress_none((destination),(elsize),(elsign),(nelem),(nelem_read),(compressedsize),(compression),(bits),(sign),(file),(realarray),(byteorder),(dimover),(dimfast),(dimmid),(dimslow),(padding)) #define cbf_decompress_none_sf(destination,elsize,elsign,nelem,nelem_read,compressedsize,compression,bits,sign,file,realarray,byteorder,dimover,dimslow,dimmid,dimfast,padding) \ cbf_decompress_none((destination),(elsize),(elsign),(nelem),(nelem_read),(compressedsize),(compression),(bits),(sign),(file),(realarray),(byteorder),(dimover),(dimfast),(dimmid),(dimslow),(padding)) #ifdef __cplusplus } #endif #endif /* CBF_UNCOMPRESSED_H */ ./CBFlib-0.9.2.2/include/cbf_write.h0000644000076500007650000004334111603702115015343 0ustar yayayaya/********************************************************************** * cbf_write.h * * * * Version 0.7.6 14 July 2006 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifndef CBF_WRITE_H #define CBF_WRITE_H #ifdef __cplusplus extern "C" { #endif #include "cbf_tree.h" /* Get the value type of an ascii string */ int cbf_get_value_type(const char *value, const char **value_type); /* Set the value type of an ascii string */ int cbf_set_value_type(cbf_handle handle, char *value, const char *value_type); /* Check the value type */ int cbf_value_type (char *value); /* Write a node to a stream */ int cbf_write_node (cbf_handle handle, const cbf_node *node, cbf_file *file, int isbuffer); /* Compose an item name from a category and column */ int cbf_compose_itemname (cbf_handle handle, const cbf_node *column, char * itemname, size_t limit); #ifdef __cplusplus } #endif #endif /* CBF_WRITE_H */ ./CBFlib-0.9.2.2/include/cbf_codes.h0000644000076500007650000004675411603702115015321 0ustar yayayaya/********************************************************************** * cbf_codes.h * * * * Version 0.7.7 19 February 2007 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifndef CBF_CODES_H #define CBF_CODES_H #ifdef __cplusplus extern "C" { #endif #include "cbf.h" #include "cbf_file.h" /* Check a 24-character base-64 MD5 digest */ int cbf_is_base64digest (const char *encoded_digest); /* Encode a 16-character MD5 digest in base-64 (25 characters) */ int cbf_md5digest_to64 (char *encoded_digest, const unsigned char *digest); /* Calculate the MD5 digest (25 characters) of a block of data */ int cbf_md5digest (cbf_file *file, size_t size, char *digest); /* Convert binary data to quoted-printable text */ int cbf_toqp (cbf_file *infile, cbf_file *outfile, size_t size); /* Convert binary data to base-64 text */ int cbf_tobase64 (cbf_file *infile, cbf_file *outfile, size_t size); /*Convert binary data to base-32k text */ int cbf_tobase32k(cbf_file *infile, cbf_file *outfile, size_t size); /* Bit shuffles for base-32K */ char * cbf_encode32k_bit_op(unsigned char *txt, size_t size, size_t *size2); /* Test for big endian */ int cbf_isBigEndian(); /* Fix endianess */ void cbf_endianFix(char *str, size_t size, int fromEndian, int toEndian); /* Convert binary data to base-8/base-10/base-16 text */ int cbf_tobasex (cbf_file *infile, cbf_file *outfile, size_t size, size_t elsize, unsigned int base); /* Convert quoted-printable text to binary data */ int cbf_fromqp (cbf_file *infile, cbf_file *outfile, size_t size, size_t *readsize, char *digest); /* Convert base-64 text to binary data */ int cbf_frombase64 (cbf_file *infile, cbf_file *outfile, size_t size, size_t *readsize, char *digest); /* Convert base-32k text to binary data */ int cbf_frombase32k (cbf_file *infile, cbf_file *outfile, size_t size, size_t *readsize, char *digest); /* bit shuffles for base-32k */ int cbf_decode32k_bit_op(char *encoded, char *decoded, size_t size); /* Convert base-8/base-10/base-16 text to binary data */ int cbf_frombasex (cbf_file *infile, cbf_file *outfile, size_t size, size_t *readsize, char *digest); #ifdef __cplusplus } #endif #endif /* CBF_CODES_H */ ./CBFlib-0.9.2.2/include/cbf_packed.h0000644000076500007650000005016611603702115015443 0ustar yayayaya/********************************************************************** * cbf_packed.h * * * * Version 0.8.0 20 July 2008 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifndef CBF_PACKED_H #define CBF_PACKED_H #ifdef __cplusplus extern "C" { #endif #include #include "cbf_file.h" /* Compress an array */ int cbf_compress_packed (void *source, size_t elsize, int elsign, size_t nelem, unsigned int compression, cbf_file *file, size_t *compressedsize, int *storedbits, int realarray, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); #define cbf_compress_packed_fs(source,elsize,elsign,nelem,compression,file,compressedsize,storedbits,realarray,byteorder,dimfast,dimmid,dimslow,padding) \ cbf_compress_packed((source),(elsize),(elsign),(nelem),(compression),(file),(compressedsize),(storedbits),(realarray),(byteorder),(dimfast),(dimmid),(dimslow),(padding)) #define cbf_compress_packed_sf(source,elsize,elsign,nelem,compression,file,compressedsize,storedbits,realarray,byteorder,dimslow,dimmid,dimfast,padding) \ cbf_compress_packed((source),(elsize),(elsign),(nelem),(compression),(file),(compressedsize),(storedbits),(realarray),(byteorder),(dimfast),(dimmid),(dimslow),(padding)) /* Decompress an array */ int cbf_decompress_packed (void *destination, size_t elsize, int elsign, size_t nelem, size_t *nelem_read, size_t compressedsize, unsigned int compression, int data_bits, int data_sign, cbf_file *file, int realarray, const char *byteorder, size_t dimover, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); #define cbf_decompress_packed_fs(destination,elsize,elsign,nelem,nelem_read,compressedsize,compression,data_bits,data_sign,file,realarray,byteorder,dimover,dimfast,dimmid,dimslow,padding) \ cbf_decompress_packed((destination),(elsize),(elsign),(nelem),(nelem_read),(compressedsize),(compression),(data_bits),(data_sign),(file),(realarray),(byteorder),(dimover),(dimfast),(dimmid),(dimslow),(padding)) #define cbf_decompress_packed_sf(destination,elsize,elsign,nelem,nelem_read,compressedsize,compression,data_bits,data_sign,file,realarray,byteorder,dimover,dimslow,dimmid,dimfast,padding) \ cbf_decompress_packed((destination),(elsize),(elsign),(nelem),(nelem_read),(compressedsize),(compression),(data_bits),(data_sign),(file),(realarray),(byteorder),(dimover),(dimfast),(dimmid),(dimslow),(padding)) #ifdef __cplusplus } #endif #endif /* CBF_PACKED_H */ ./CBFlib-0.9.2.2/include/cbf_canonical.h0000644000076500007650000005731211603702115016143 0ustar yayayaya/********************************************************************** * cbf_canonical.h * * * * Version 0.8.0 20 July 2008 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifndef CBF_CANONICAL_H #define CBF_CANONICAL_H #ifdef __cplusplus extern "C" { #endif #include #include "cbf_file.h" /* Compression tree node */ typedef struct cbf_compress_nodestruct { size_t count; /* Number in the file */ unsigned int code; /* Code */ unsigned int bitcount; /* Bits in the minimum-redundancy code */ unsigned int bitcode [4]; /* Minimum-redundancy code */ struct cbf_compress_nodestruct *next, *child [2]; } cbf_compress_node; /* Compression data */ typedef struct { cbf_file *file; /* File */ unsigned int bits; /* Coded bits */ unsigned int maxbits; /* Maximum saved bits */ unsigned int endcode; /* End-of-data code endcode = 1 << bits == 2^bits */ size_t nodes; /* Number of nodes */ size_t nextnode; /* Number of nodes used */ cbf_compress_node *node; /* Nodes */ } cbf_compress_data; /* Create compression data */ int cbf_make_compressdata (cbf_compress_data **data, cbf_file *file); /* Free data */ void cbf_free_compressdata (cbf_compress_data *data); /* Initialise compression data arrays */ int cbf_initialise_compressdata (cbf_compress_data *data, unsigned int bits, unsigned int maxbits); /* Write a compression table */ int cbf_put_table (cbf_compress_data *data, unsigned int *bitcount); /* Read a compression table */ int cbf_get_table (cbf_compress_data *data); /* End the bitstream */ int cbf_put_stopcode (cbf_compress_data *data, unsigned int *bitcount); /* Insert a node into a tree */ cbf_compress_node *cbf_insert_node (cbf_compress_node *tree, cbf_compress_node *node); /* Append a node to a list */ cbf_compress_node *cbf_append_node (cbf_compress_node *list, cbf_compress_node *node); /* Convert an ordered tree into an ordered list */ cbf_compress_node *cbf_order_node (cbf_compress_node *tree); /* Create an ordered list */ cbf_compress_node *cbf_create_list (cbf_compress_data *data); /* Combine the two nodes with minimum count */ cbf_compress_node *cbf_reduce_list (cbf_compress_data *data, cbf_compress_node *list); /* Generate the minimum-redundancy code lengths */ int cbf_generate_codelengths (cbf_compress_node *tree, int bitcount); /* Reverse the order of the bits in the bit-codes */ int cbf_reverse_bitcodes (cbf_compress_data *data); /* Generate the canonical bit-codes */ int cbf_generate_canonicalcodes (cbf_compress_data *data); /* Compare the bitcodes of two nodes */ int cbf_compare_bitcodes (const void *void1, const void *void2); /* Construct a tree from an ordered set of nodes */ int cbf_construct_tree (cbf_compress_data *data, cbf_compress_node **node, int bits, cbf_compress_node **root); /* Sort the nodes and set up the decoding arrays */ int cbf_setup_decode (cbf_compress_data *data, cbf_compress_node **start); /* Calculate the expected bit count */ unsigned long cbf_count_bits (cbf_compress_data *data); /* Read a code */ int cbf_get_code (cbf_compress_data *data, cbf_compress_node *root, unsigned int *code, unsigned int *bitcount); /* Write a coded integer */ int cbf_put_code (cbf_compress_data *data, int code, unsigned int overflow, unsigned int *bitcount); /* Count the values */ int cbf_count_values (cbf_compress_data *data, void *source, size_t elsize, int elsign, size_t nelem, int *minelem, int *maxelem, char *border); /* Compress an array */ int cbf_compress_canonical (void *source, size_t elsize, int elsign, size_t nelem, unsigned int compression, cbf_file *file, size_t *compressedsize, int *storedbits, int realarray, const char *byteorder, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); /* Decompress an array (from the start of the table) */ int cbf_decompress_canonical (void *destination, size_t elsize, int elsign, size_t nelem, size_t *nelem_read, size_t compressedsize, unsigned int compression, int bits, int sign, cbf_file *file, int realarray, const char *byteorder, size_t dimover, size_t dimfast, size_t dimmid, size_t dimslow, size_t padding); #define cbf_decompress_canonical_fs(destination,elsize,elsign,nelem,nelem_read,compressedsize,compression,bits,sign,file,realarray,byteorder,dimover,dimfast,dimmid,dimslow,padding) \ cbf_decompress_canonical((destination),(elsize),(elsign),(nelem),(nelem_read),(compressedsize),(compression),(bits),(sign),(file),(realarray),(byteorder),(dimover),(dimfast),(dimmid),(dimslow),(padding)) #define cbf_decompress_canonical_sf(destination,elsize,elsign,nelem,nelem_read,compressedsize,compression,bits,sign,file,realarray,byteorder,dimover,dimslow,dimmid,dimfast,padding) \ cbf_decompress_canonical((destination),(elsize),(elsign),(nelem),(nelem_read),(compressedsize),(compression),(bits),(sign),(file),(realarray),(byteorder),(dimover),(dimfast),(dimmid),(dimslow),(padding)) #ifdef __cplusplus } #endif #endif /* CBF_CANONICAL_H */ ./CBFlib-0.9.2.2/include/cbf_simple.h0000644000076500007650000017360011603702115015504 0ustar yayayaya/********************************************************************** * cbf_simple -- cbflib simplified API functions * * * * Version 0.8.0 20 July 2008 * * * * Paul Ellis and * * Herbert J. Bernstein (yaya@bernstein-plus-sons.com) * * * * (C) Copyright 2006, 2007 Herbert J. Bernstein * * * **********************************************************************/ /********************************************************************** * * * YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL * * * * ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS * * OF THE LGPL * * * **********************************************************************/ /*************************** GPL NOTICES ****************************** * * * This program is free software; you can redistribute it and/or * * modify it under the terms of the GNU General Public License as * * published by the Free Software Foundation; either version 2 of * * (the License, or (at your option) any later version. * * * * This program is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * * GNU General Public License for more details. * * * * You should have received a copy of the GNU General Public License * * along with this program; if not, write to the Free Software * * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA * * 02111-1307 USA * * * **********************************************************************/ /************************* LGPL NOTICES ******************************* * * * This library is free software; you can redistribute it and/or * * modify it under the terms of the GNU Lesser General Public * * License as published by the Free Software Foundation; either * * version 2.1 of the License, or (at your option) any later version. * * * * This library is distributed in the hope that it will be useful, * * but WITHOUT ANY WARRANTY; without even the implied warranty of * * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * * Lesser General Public License for more details. * * * * You should have received a copy of the GNU Lesser General Public * * License along with this library; if not, write to the Free * * Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, * * MA 02110-1301 USA * * * **********************************************************************/ /********************************************************************** * * * Stanford University Notices * * for the CBFlib software package that incorporates SLAC software * * on which copyright is disclaimed * * * * This software * * ------------- * * The term Ôthis softwareÕ, as used in these Notices, refers to * * those portions of the software package CBFlib that were created by * * employees of the Stanford Linear Accelerator Center, Stanford * * University. * * * * Stanford disclaimer of copyright * * -------------------------------- * * Stanford University, owner of the copyright, hereby disclaims its * * copyright and all other rights in this software. Hence, anyone * * may freely use it for any purpose without restriction. * * * * Acknowledgement of sponsorship * * ------------------------------ * * This software was produced by the Stanford Linear Accelerator * * Center, Stanford University, under Contract DE-AC03-76SFO0515 with * * the Department of Energy. * * * * Government disclaimer of liability * * ---------------------------------- * * Neither the United States nor the United States Department of * * Energy, nor any of their employees, makes any warranty, express or * * implied, or assumes any legal liability or responsibility for the * * accuracy, completeness, or usefulness of any data, apparatus, * * product, or process disclosed, or represents that its use would * * not infringe privately owned rights. * * * * Stanford disclaimer of liability * * -------------------------------- * * Stanford University makes no representations or warranties, * * express or implied, nor assumes any liability for the use of this * * software. * * * * Maintenance of notices * * ---------------------- * * In the interest of clarity regarding the origin and status of this * * software, this and all the preceding Stanford University notices * * are to remain affixed to any copy or derivative of this software * * made or distributed by the recipient and are to be affixed to any * * copy of software made or distributed by the recipient that * * contains a copy or derivative of this software. * * * * Based on SLAC Software Notices, Set 4 * * OTT.002a, 2004 FEB 03 * **********************************************************************/ /********************************************************************** * NOTICE * * Creative endeavors depend on the lively exchange of ideas. There * * are laws and customs which establish rights and responsibilities * * for authors and the users of what authors create. This notice * * is not intended to prevent you from using the software and * * documents in this package, but to ensure that there are no * * misunderstandings about terms and conditions of such use. * * * * Please read the following notice carefully. If you do not * * understand any portion of this notice, please seek appropriate * * professional legal advice before making use of the software and * * documents included in this software package. In addition to * * whatever other steps you may be obliged to take to respect the * * intellectual property rights of the various parties involved, if * * you do make use of the software and documents in this package, * * please give credit where credit is due by citing this package, * * its authors and the URL or other source from which you obtained * * it, or equivalent primary references in the literature with the * * same authors. * * * * Some of the software and documents included within this software * * package are the intellectual property of various parties, and * * placement in this package does not in any way imply that any * * such rights have in any way been waived or diminished. * * * * With respect to any software or documents for which a copyright * * exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. * * * * Even though the authors of the various documents and software * * found here have made a good faith effort to ensure that the * * documents are correct and that the software performs according * * to its documentation, and we would greatly appreciate hearing of * * any problems you may encounter, the programs and documents any * * files created by the programs are provided **AS IS** without any * * warranty as to correctness, merchantability or fitness for any * * particular or general use. * * * * THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF * * PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE * * PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS * * OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE * * PROGRAMS OR DOCUMENTS. * **********************************************************************/ /********************************************************************** * * * The IUCr Policy * * for the Protection and the Promotion of the STAR File and * * CIF Standards for Exchanging and Archiving Electronic Data * * * * Overview * * * * The Crystallographic Information File (CIF)[1] is a standard for * * information interchange promulgated by the International Union of * * Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the * * recommended method for submitting publications to Acta * * Crystallographica Section C and reports of crystal structure * * determinations to other sections of Acta Crystallographica * * and many other journals. The syntax of a CIF is a subset of the * * more general STAR File[2] format. The CIF and STAR File approaches * * are used increasingly in the structural sciences for data exchange * * and archiving, and are having a significant influence on these * * activities in other fields. * * * * Statement of intent * * * * The IUCr's interest in the STAR File is as a general data * * interchange standard for science, and its interest in the CIF, * * a conformant derivative of the STAR File, is as a concise data * * exchange and archival standard for crystallography and structural * * science. * * * * Protection of the standards * * * * To protect the STAR File and the CIF as standards for * * interchanging and archiving electronic data, the IUCr, on behalf * * of the scientific community, * * * * * holds the copyrights on the standards themselves, * * * * * owns the associated trademarks and service marks, and * * * * * holds a patent on the STAR File. * * * * These intellectual property rights relate solely to the * * interchange formats, not to the data contained therein, nor to * * the software used in the generation, access or manipulation of * * the data. * * * * Promotion of the standards * * * * The sole requirement that the IUCr, in its protective role, * * imposes on software purporting to process STAR File or CIF data * * is that the following conditions be met prior to sale or * * distribution. * * * * * Software claiming to read files written to either the STAR * * File or the CIF standard must be able to extract the pertinent * * data from a file conformant to the STAR File syntax, or the CIF * * syntax, respectively. * * * * * Software claiming to write files in either the STAR File, or * * the CIF, standard must produce files that are conformant to the * * STAR File syntax, or the CIF syntax, respectively. * * * * * Software claiming to read definitions from a specific data * * dictionary approved by the IUCr must be able to extract any * * pertinent definition which is conformant to the dictionary * * definition language (DDL)[3] associated with that dictionary. * * * * The IUCr, through its Committee on CIF Standards, will assist * * any developer to verify that software meets these conformance * * conditions. * * * * Glossary of terms * * * * [1] CIF: is a data file conformant to the file syntax defined * * at http://www.iucr.org/iucr-top/cif/spec/index.html * * * * [2] STAR File: is a data file conformant to the file syntax * * defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html * * * * [3] DDL: is a language used in a data dictionary to define data * * items in terms of "attributes". Dictionaries currently approved * * by the IUCr, and the DDL versions used to construct these * * dictionaries, are listed at * * http://www.iucr.org/iucr-top/cif/spec/ddl/index.html * * * * Last modified: 30 September 2000 * * * * IUCr Policy Copyright (C) 2000 International Union of * * Crystallography * **********************************************************************/ #ifndef CBF_SIMPLE_H #define CBF_SIMPLE_H #ifdef __cplusplus extern "C" { #endif #include "cbf.h" #define CBF_NOTIMEZONE 1440 /* Geometry structures */ typedef enum { CBF_ROTATION_AXIS, CBF_TRANSLATION_AXIS, CBF_GENERAL_AXIS } cbf_axis_type; typedef struct { char *name, *depends_on; double vector [3], offset [3], start, increment, setting; cbf_axis_type type; } cbf_axis_struct; typedef struct { double matrix [3][4]; cbf_axis_struct *axis; size_t axes; int matrix_is_valid, axes_are_connected; } cbf_positioner_struct; typedef cbf_positioner_struct *cbf_positioner; typedef cbf_positioner_struct *cbf_goniometer; typedef struct { cbf_positioner positioner; double displacement [2], increment [2]; size_t axes, index [2]; cbf_handle handle; int element; } cbf_detector_struct; typedef cbf_detector_struct *cbf_detector; /* Read a template file */ int cbf_read_template (cbf_handle handle, FILE *stream); /* Get the diffrn.id entry */ int cbf_get_diffrn_id (cbf_handle handle, const char **diffrn_id); /* Change the diffrn.id entry in all the categories */ int cbf_set_diffrn_id (cbf_handle handle, const char *diffrn_id); /* Change the diffrn.id entry, creating it if necessary */ int cbf_require_diffrn_id (cbf_handle handle, const char **diffrn_id, const char *default_id); /* Get the diffrn.crystal_id entry */ int cbf_get_crystal_id (cbf_handle handle, const char **crystal_id); /* Change the diffrn.crystal_id entry */ int cbf_set_crystal_id (cbf_handle handle, const char *crystal_id); /* Get the wavelength */ int cbf_get_wavelength (cbf_handle handle, double *wavelength); /* Set the wavelength */ int cbf_set_wavelength (cbf_handle handle, double wavelength); /* Get the polarization */ int cbf_get_polarization (cbf_handle handle, double *polarizn_source_ratio, double *polarizn_source_norm); /* Set the polarization */ int cbf_set_polarization (cbf_handle handle, double polarizn_source_ratio, double polarizn_source_norm); /* Get the divergence */ int cbf_get_divergence (cbf_handle handle, double *div_x_source, double *div_y_source, double *div_x_y_source); /* Set the divergence */ int cbf_set_divergence (cbf_handle handle, double div_x_source, double div_y_source, double div_x_y_source); /* Get the number of elements */ int cbf_count_elements (cbf_handle handle, unsigned int *elements); /* Get the element id */ int cbf_get_element_id (cbf_handle handle, unsigned int element_number, const char **element_id); /* Get the detector id */ int cbf_get_detector_id (cbf_handle handle, unsigned int element_number, const char **detector_id); /* Get the array id for a given detector element */ int cbf_get_array_id (cbf_handle handle, unsigned int element_number, const char **array_id); /* Get the pixel size of a detector element in a given direction */ int cbf_get_pixel_size(cbf_handle handle, unsigned int element_number, int axis_number, double * psize); #define cbf_get_pixel_size_fs(handle, element_number, axis_number, psize) \ cbf_get_pixel_size((handle),(element_number),-(axis_number),(psize)) #define cbf_get_pixel_size_sf(handle, element_number, axis_number, psize) \ cbf_get_pixel_size((handle),(element_number),(axis_number),(psize)) /* Set the pixel size of a detector element in a given direction */ int cbf_set_pixel_size(cbf_handle handle, unsigned int element_number, int axis_number, double psize); #define cbf_set_pixel_size_fs(handle, element_number, axis_number, psize) \ cbf_set_pixel_size((handle),(element_number),-(axis_number),(psize)) #define cbf_set_pixel_size_sf(handle, element_number, axis_number, psize) \ cbf_set_pixel_size((handle),(element_number),(axis_number),(psize)) /* Get the gain of a detector element */ int cbf_get_gain (cbf_handle handle, unsigned int element_number, double *gain, double *gain_esd); /* Set the gain of a detector element */ int cbf_set_gain (cbf_handle handle, unsigned int element_number, double gain, double gain_esd); /* Get the bin sizes of a detector element */ int cbf_get_bin_sizes(cbf_handle handle, unsigned int element_number, double * slowbinsize, double * fastbinsize); /* Set the bin sizes of a detector element */ int cbf_set_bin_sizes(cbf_handle handle, unsigned int element_number, double slowbinsize, double fastbinsize); /* Get the overload value of a detector element */ int cbf_get_overload (cbf_handle handle, unsigned int element_number, double *overload); /* Set the overload value of a detector element */ int cbf_set_overload (cbf_handle handle, unsigned int element_number, double overload); /* Get the integration time */ int cbf_get_integration_time (cbf_handle handle, unsigned int reserved, double *time); /* Set the integration time */ int cbf_set_integration_time (cbf_handle handle, unsigned int reserved, double time); /* Convert gregorian to julian date (in days) */ double cbf_gregorian_julian (int year, int month, int day, int hour, int minute, double second); /* Get the collection date and time (1) as seconds since January 1 1970 */ int cbf_get_timestamp (cbf_handle handle, unsigned int reserved, double *time, int *timezone); /* Get the collection date and time (2) as individual fields */ int cbf_get_datestamp (cbf_handle handle, unsigned int reserved, int *year, int *month, int *day, int *hour, int *minute, double *second, int *timezone); /* Set the collection date and time (1) as seconds since January 1 1970 */ int cbf_set_timestamp (cbf_handle handle, unsigned int reserved, double time, int timezone, double precision); /* Set the collection date and time (2) as individual fields */ int cbf_set_datestamp (cbf_handle handle, unsigned int reserved, int year, int month, int day, int hour, int minute, double second, int timezone, double precision); /* Set the collection date and time (3) as current time to the second */ int cbf_set_current_timestamp (cbf_handle handle, unsigned int reserved, int timezone); /* Get the image size */ int cbf_get_image_size (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimslow, size_t *ndimfast); #define cbf_get_image_size_fs(handle, reserved, element_number, ndimfast, ndimslow) \ cbf_get_image_size((handle),(reserved),(element_number),(ndimslow),(ndimfast)) #define cbf_get_image_size_sf(handle, reserved, element_number, ndimslow, ndimfast) \ cbf_get_image_size((handle),(reserved),(element_number),(ndimslow),(ndimfast)) /* Read a binary section into an image. ndimslow is the slow dimension, ndimfast is fast dimension.*/ int cbf_get_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast); #define cbf_get_image_fs(handle, reserved, element_number, array, elsize, elsign, ndimfast, ndimslow) \ cbf_get_image ((handle),(reserved),(element_number),(array),(elsize),(elsign),(ndimslow),(ndimfast)) #define cbf_get_image_sf(handle, reserved, element_number, array, elsize, elsign, ndimslow, ndimfast) \ cbf_get_image ((handle),(reserved),(element_number),(array),(elsize),(elsign),(ndimslow),(ndimfast)) /* Read a binary section into a real image. ndimslow is the slow dimension, ndimfast is fast dimension.*/ int cbf_get_real_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimslow, size_t ndimfast); #define cbf_get_real_image_fs(handle, reserved, element_number, array, elsize, ndimfast, ndimslow)\ cbf_get_real_image ((handle),(reserved),(element_number),(array),(elsize),(ndimslow),(ndimfast)) #define cbf_get_real_image_sf(handle, reserved, element_number, array, elsize, ndimslow, ndimfast)\ cbf_get_real_image ((handle),(reserved),(element_number),(array),(elsize),(ndimslow),(ndimfast)) /* Get the 3D image size. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_get_3d_image_size (cbf_handle handle, unsigned int reserved, unsigned int element_number, size_t *ndimslow, size_t *ndimmid, size_t *ndimfast); #define cbf_get_3d_image_size_fs(handle, reserved, element_number, ndimfast, ndimmid, ndimslow) \ cbf_get_3d_image_size((handle),(reserved),(element_number),(ndimslow),(ndimmid),(ndimfast)) #define cbf_get_3d_image_size_sf(handle, reserved, element_number, ndimslow, ndimmid, ndimfast) \ cbf_get_3d_image_size((handle),(reserved),(element_number),(ndimslow),(ndimmid),(ndimfast)) /* Read a 3D binary section into an image. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_get_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); #define cbf_get_3d_image_fs(handle, reserved, element_number, array, elsize, elsign, ndimfast, ndimmid, ndimslow) \ cbf_get_3d_image((handle),(reserved),(element_number),(array),(elsize),(elsign),(ndimslow),(ndimmid),(ndimfast)) #define cbf_get_3d_image_sf(handle, reserved, element_number, array, elsize, elsign, ndimslow, ndimmid, ndimfast) \ cbf_get_3d_image((handle),(reserved),(element_number),(array),(elsize),(elsign),(ndimslow),(ndimmid),(ndimfast)) /* Read a 3D binary section into a real image. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_get_real_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, void *array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); #define cbf_get_real_3d_image_fs(handle, reserved, element_number, array, elsize, ndimfast, ndimmid, ndimslow) \ cbf_get_real_3d_image((handle),(reserved),(element_number),(array),(elsize),(ndimslow),(ndimmid),(ndimfast)) #define cbf_get_real_3d_image_sf(handle, reserved, element_number, array, elsize, ndimslow, ndimmid, ndimfast) \ cbf_get_real_3d_image((handle),(reserved),(element_number),(array),(elsize),(ndimslow),(ndimmid),(ndimfast)) /* Save an image. ndimslow is the slow dimension, ndimfast is fast. */ int cbf_set_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimfast); #define cbf_set_image_fs(handle, reserved, element_number, compression, array, elsize, elsign, ndimfast, ndimslow) \ cbf_set_image ((handle),(reserved),(element_number),(compression),(array),(elsize),(elsign),(ndimslow),(ndimfast) ) #define cbf_set_image_sf(handle, reserved, element_number, compression, array, elsize, elsign, ndimslow, ndimfast) \ cbf_set_image ((handle),(reserved),(element_number),(compression),(array),(elsize),(elsign),(ndimslow),(ndimfast) ) /* Save a real image. ndimslow is the slow dimension, ndimfast is fast. */ int cbf_set_real_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, size_t ndimslow, size_t ndimfast); #define cbf_set_real_image_fs(handle, reserved, element_number, compression, array, elsize, ndimfast, ndimslow) \ cbf_set_real_image ((handle),(reserved),(element_number),(compression),(array),(elsize),(ndimslow),(ndimfast) ) #define cbf_set_real_image_sf(handle, reserved, element_number, compression, array, elsize, ndimslow, ndimfast) \ cbf_set_real_image ((handle),(reserved),(element_number),(compression),(array),(elsize),(ndimslow),(ndimfast) ) /* Save a 3D image. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension. */ int cbf_set_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); #define cbf_set_3d_image_fs(handle, reserved, element_number, compression, array, elsize, elsign, ndimfast, ndimmid, ndimslow) \ cbf_set_3d_image ((handle),(reserved),(element_number),(compression),(array),(elsize),(elsign),(ndimslow),(ndimmid),(ndimfast) ) #define cbf_set_3d_image_sf(handle, reserved, element_number, compression, array, elsize, elsign, ndimslow, ndimmid, ndimfast) \ cbf_set_3d_image ((handle),(reserved),(element_number),(compression),(array),(elsize),(elsign),(ndimslow),(ndimmid),(ndimfast) ) /* Save a real 3D image. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_set_real_3d_image (cbf_handle handle, unsigned int reserved, unsigned int element_number, unsigned int compression, void *array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); #define cbf_set_real_3d_image_fs(handle, reserved, element_number, compression, array, elsize, ndimfast, ndimmid, ndimslow) \ cbf_set_real_3d_image ((handle),(reserved),(element_number),(compression),(array),(elsize),(ndimslow),(ndimmid),(ndimfast) ) #define cbf_set_real_3d_image_sf(handle, reserved, element_number, compression, array, elsize, ndimslow, ndimmid, ndimfast) \ cbf_set_real_3d_image ((handle),(reserved),(element_number),(compression),(array),(elsize),(ndimslow),(ndimmid),(ndimfast) ) /* Get the array_id for a map segment or map segment mask. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension. */ int cbf_get_map_array_id (cbf_handle handle, unsigned int reserved, const char *segment_id, const char **array_id, int ismask, int require, size_t ndimslow, size_t ndimmid, size_t ndimfast); #define cbf_get_map_array_id_fs(handle, reserved, segment_id, array_id, ismask, require, ndimfast, ndimmid, ndimslow) \ cbf_get_map_array_id ((handle),(reserved),(segment_id),(array_id),(ismask),(require),(ndimslow),(ndimmid),(ndimfast) ) #define cbf_get_map_array_id_sf(handle, reserved, segment_id, array_id, ismask, require, ndimslow, ndimmid, ndimfast) \ cbf_get_map_array_id ((handle),(reserved),(segment_id),(array_id),(ismask),(require),(ndimslow),(ndimmid),(ndimfast) ) /* Get the map segment size. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_get_map_segment_size (cbf_handle handle, unsigned int reserved, const char *segment_id, int *binary_id, size_t *ndimslow, size_t *ndimmid, size_t *ndimfast); #define cbf_get_map_segment_size_fs(handle, reserved, segment_id, binary_id, ndimfast, ndimmid, ndimslow) \ cbf_get_map_segment_size ((handle),(reserved),(segment_id),(binary_id),(ndimslow),(ndimmid),(ndimfast) ) #define cbf_get_map_segment_size_sf(handle, reserved, segment_id, binary_id, ndimslow, ndimmid, ndimfast) \ cbf_get_map_segment_size ((handle),(reserved),(segment_id),(binary_id),(ndimslow),(ndimmid),(ndimfast) ) /* Read a map segment. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_get_map_segment (cbf_handle handle, unsigned int reserved, const char *segment_id, int *binary_id, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); #define cbf_get_map_segment_fs(handle, reserved, segment_id, binary_id, array, elsize, elsign, ndimfast, ndimmid, ndimslow) \ cbf_get_map_segment ((handle),(reserved),(segment_id),(binary_id),(array),(elsize),(elsign),(ndimslow),(ndimmid),(ndimfast) ) #define cbf_get_map_segment_sf(handle, reserved, segment_id, binary_id, array, elsize, elsign, ndimslow, ndimmid, ndimfast) \ cbf_get_map_segment ((handle),(reserved),(segment_id),(binary_id),(array),(elsize),(elsign),(ndimslow),(ndimmid),(ndimfast) ) /* Read a map segment mask. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_get_map_segment_mask (cbf_handle handle, unsigned int reserved, const char *segment_id, int *binary_id, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); #define cbf_get_map_segment_mask_fs(handle, reserved, segment_id, binary_id, array, elsize, elsign, ndimfast, ndimmid, ndimslow) \ cbf_get_map_segment_mask ((handle),(reserved),(segment_id),(binary_id),(array),(elsize),(elsign),(ndimslow),(ndimmid),(ndimfast) ) #define cbf_get_map_segment_mask_sf(handle, reserved, segment_id, binary_id, array, elsize, elsign, ndimslow, ndimmid, ndimfast) \ cbf_get_map_segment_mask ((handle),(reserved),(segment_id),(binary_id),(array),(elsize),(elsign),(ndimslow),(ndimmid),(ndimfast) ) /* Read a real map segment. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_get_real_map_segment (cbf_handle handle, unsigned int reserved, const char *segment_id, int *binary_id, void *array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); #define cbf_get_real_map_segment_fs(handle, reserved, segment_id, binary_id, array, elsize, ndimfast, ndimmid, ndimslow) \ cbf_get_real_map_segment ((handle),(reserved),(segment_id),(binary_id),(array),(elsize),(ndimslow),(ndimmid),(ndimfast) ) #define cbf_get_real_map_segment_sf(handle, reserved, segment_id, binary_id, array, elsize, ndimslow, ndimmid, ndimfast) \ cbf_get_real_map_segment ((handle),(reserved),(segment_id),(binary_id),(array),(elsize),(ndimslow),(ndimmid),(ndimfast) ) /* Read a real map segment mask. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_get_real_map_segment_mask (cbf_handle handle, unsigned int reserved, const char *segment_id, int *binary_id, void *array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); #define cbf_get_real_map_segment_mask_fs(handle, reserved, segment_id, binary_id, array, elsize, ndimfast, ndimmid, ndimslow) \ cbf_get_real_map_segment_mask ((handle),(reserved),(segment_id),(binary_id),(array),(elsize),(ndimslow),(ndimmid),(ndimfast) ) #define cbf_get_real_map_segment_mask_sf(handle, reserved, segment_id, binary_id, array, elsize, ndimslow, ndimmid, ndimfast) \ cbf_get_real_map_segment_mask ((handle),(reserved),(segment_id),(binary_id),(array),(elsize),(ndimslow),(ndimmid),(ndimfast) ) /* Save a map segment. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_set_map_segment (cbf_handle handle, unsigned int reserved, const char *segment_id, int *binary_id, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); #define cbf_set_map_segment_fs(handle, reserved, segment_id, binary_id, compression, array, elsize, elsign, ndimfast, ndimmid, ndimslow) \ cbf_set_map_segment ((handle),(reserved),(segment_id),(binary_id),(compression),(array),(elsize),(elsign),(ndimslow),(ndimmid),(ndimfast) ) #define cbf_set_map_segment_sf(handle, reserved, segment_id, binary_id, compression, array, elsize, elsign, ndimslow, ndimmid, ndimfast) \ cbf_set_map_segment ((handle),(reserved),(segment_id),(binary_id),(compression),(array),(elsize),(elsign),(ndimslow),(ndimmid),(ndimfast) ) /* Save a map segment mask. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_set_map_segment_mask (cbf_handle handle, unsigned int reserved, const char *segment_id, int *binary_id, unsigned int compression, void *array, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); #define cbf_set_map_segment_mask_fs(handle, reserved, segment_id, binary_id, compression, array, elsize, elsign, ndimfast, ndimmid, ndimslow) \ cbf_set_map_segment_mask ((handle),(reserved),(segment_id),(binary_id),(compression),(array),(elsize),(elsign),(ndimslow),(ndimmid),(ndimfast) ) #define cbf_set_map_segment_mask_sf(handle, reserved, segment_id, binary_id, compression, array, elsize, elsign, ndimslow, ndimmid, ndimfast) \ cbf_set_map_segment_mask ((handle),(reserved),(segment_id),(binary_id),(compression),(array),(elsize),(elsign),(ndimslow),(ndimmid),(ndimfast) ) /* Save a real map segment. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_set_real_map_segment (cbf_handle handle, unsigned int reserved, const char *segment_id, int *binary_id, unsigned int compression, void *array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); #define cbf_set_real_map_segment_fs(handle, reserved, segment_id, binary_id, compression, array, elsize, ndimfast, ndimmid, ndimslow) \ cbf_set_real_map_segment ((handle),(reserved),(segment_id),(binary_id),(compression),(array),(elsize),(ndimslow),(ndimmid),(ndimfast) ) #define cbf_set_real_map_segment_sf(handle, reserved, segment_id, binary_id, compression, array, elsize, ndimslow, ndimmid, ndimfast) \ cbf_set_real_map_segment ((handle),(reserved),(segment_id),(binary_id),(compression),(array),(elsize),(ndimslow),(ndimmid),(ndimfast) ) /* Save a real map segment mask. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_set_real_map_segment_mask (cbf_handle handle, unsigned int reserved, const char *segment_id, int *binary_id, unsigned int compression, void *array, size_t elsize, size_t ndimslow, size_t ndimmid, size_t ndimfast); #define cbf_set_real_map_segment_mask_fs(handle, reserved, segment_id, binary_id, compression, array, elsize, ndimfast, ndimmid, ndimslow) \ cbf_set_real_map_segment_mask ((handle),(reserved),(segment_id),(binary_id),(compression),(array),(elsize),(ndimslow),(ndimmid),(ndimfast) ) #define cbf_set_real_map_segment_mask_sf(handle, reserved, segment_id, binary_id, compression, array, elsize, ndimslow, ndimmid, ndimfast) \ cbf_set_real_map_segment_mask ((handle),(reserved),(segment_id),(binary_id),(compression),(array),(elsize),(ndimslow),(ndimmid),(ndimfast) ) /* Get the 3D array size. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_get_3d_array_size (cbf_handle handle, unsigned int reserved, const char *array_id, size_t *ndimslow, size_t *ndimmid, size_t *ndimfast); #define cbf_get_3d_array_size_fs(handle, reserved, array_id, ndimfast, ndimmid, ndimslow) \ cbf_get_3d_array_size ((handle),(reserved),(array_id),(ndimslow),(ndimmid),(ndimfast) ) #define cbf_get_3d_array_size_sf(handle, reserved, array_id, ndimslow, ndimmid, ndimfast) \ cbf_get_3d_array_size ((handle),(reserved),(array_id),(ndimslow),(ndimmid),(ndimfast) ) /* Read a 3D array. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_get_3d_array (cbf_handle handle, unsigned int reserved, const char *array_id, int *binary_id, void *array, int eltype, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); #define cbf_get_3d_array_fs(handle, reserved, array_id, binary_id, array, eltype, elsize, elsign, ndimfast, ndimmid, ndimslow) \ cbf_get_3d_array ((handle),(reserved),(array_id),(binary_id),(array),(eltype),(elsize),(elsign),(ndimslow),(ndimmid),(ndimfast) ) #define cbf_get_3d_array_sf(handle, reserved, array_id, binary_id, array, eltype, elsize, elsign, ndimslow, ndimmid, ndimfast) \ cbf_get_3d_array ((handle),(reserved),(array_id),(binary_id),(array),(eltype),(elsize),(elsign),(ndimslow),(ndimmid),(ndimfast) ) /* Save a 3D array. ndimslow is the slowest dimension, ndimmid is the next faster dimension, ndimfast is the fastest dimension */ int cbf_set_3d_array (cbf_handle handle, unsigned int reserved, const char *array_id, int *binary_id, unsigned int compression, void *array, int eltype, size_t elsize, int elsign, size_t ndimslow, size_t ndimmid, size_t ndimfast); #define cbf_set_3d_array_fs(handle, reserved, array_id, binary_id, compression, array, eltype, elsize, elsign, ndimfast, ndimmid, ndimslow) \ cbf_set_3d_array ((handle),(reserved),(array_id),(binary_id),(compression),(array),(eltype),(elsize),(elsign),(ndimslow),(ndimmid),(ndimfast) ) #define cbf_set_3d_array_sf(handle, reserved, array_id, binary_id, compression, array, eltype, elsize, elsign, ndimslow, ndimmid, ndimfast) \ cbf_set_3d_array ((handle),(reserved),(array_id),(binary_id),(compression),(array),(eltype),(elsize),(elsign),(ndimslow),(ndimmid),(ndimfast) ) /* Get the setting of an axis */ int cbf_get_axis_setting (cbf_handle handle, unsigned int reserved, const char *axis_id, double *start, double *increment); /* Get the reference setting of an axis */ int cbf_get_axis_reference_setting (cbf_handle handle, unsigned int reserved, const char *axis_id, double *refsetting); /* Change the setting of an axis */ int cbf_set_axis_setting (cbf_handle handle, unsigned int reserved, const char *axis_id, double start, double increment); /* Change the reference setting of an axis */ int cbf_set_axis_reference_setting (cbf_handle handle, unsigned int reserved, const char *axis_id, double refsetting); /* Construct a goniometer */ int cbf_construct_goniometer (cbf_handle handle, cbf_goniometer *goniometer); /* Free a goniometer */ int cbf_free_goniometer (cbf_goniometer goniometer); /* Get the rotation axis */ int cbf_get_rotation_axis (cbf_goniometer goniometer, unsigned int reserved, double *vector1, double *vector2, double *vector3); /* Get the rotation range */ int cbf_get_rotation_range (cbf_goniometer goniometer, unsigned int reserved, double *start, double *increment); /* Reorient a vector */ int cbf_rotate_vector (cbf_goniometer goniometer, unsigned int reserved, double ratio, double initial1, double initial2, double initial3, double *final1, double *final2, double *final3); /* Convert a vector to reciprocal space */ int cbf_get_reciprocal (cbf_goniometer goniometer, unsigned int reserved, double ratio, double wavelength, double real1, double real2, double real3, double *reciprocal1, double *reciprocal2, double *reciprocal3); /* Construct a detector positioner */ int cbf_construct_detector (cbf_handle handle, cbf_detector *detector, unsigned int element_number); /* Construct a reference detector positioner */ int cbf_construct_reference_detector (cbf_handle handle, cbf_detector *detector, unsigned int element_number); /* Construct a detector positioner, creating the necessary categories, and columns */ int cbf_require_detector (cbf_handle handle, cbf_detector *detector, unsigned int element_number); /* Construct a reference detector positioner, creating the necessary categories, and columns */ int cbf_require_reference_detector (cbf_handle handle, cbf_detector *detector, unsigned int element_number); /* Free a detector */ int cbf_free_detector (cbf_detector detector); /* Get the beam center */ int cbf_get_beam_center (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast); #define cbf_get_beam_center_sf(detector, indexslow, indexfast, \ centerslow, centerfast) \ cbf_get_beam_center((detector),(indexslow),(indexfast), \ (centerslow),(centerfast) ) #define cbf_get_beam_center_fs(detector, indexfast, indexslow, \ centerfast, centerslow) \ cbf_get_beam_center((detector),(indexslow),(indexfast), \ (centerslow),(centerfast) ) /* Set the beam center */ int cbf_set_beam_center (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast); #define cbf_set_beam_center_sf(detector, indexslow, indexfast, \ centerslow, centerfast) \ cbf_set_beam_center((detector),(indexslow),(indexfast), \ (centerslow),(centerfast) ) #define cbf_set_beam_center_fs(detector, indexfast, indexslow, \ centerfast, centerslow) \ cbf_set_beam_center((detector),(indexslow),(indexfast), \ (centerslow),(centerfast) ) /* Set the reference beam center */ int cbf_set_reference_beam_center (cbf_detector detector, double *indexslow, double *indexfast, double *centerslow, double *centerfast); #define cbf_set_reference_beam_center_sf(detector, indexslow, indexfast, \ centerslow, centerfast) \ cbf_set_reference_beam_center((detector),(indexslow),(indexfast), \ (centerslow),(centerfast) ) #define cbf_set_reference_beam_center_fs(detector, indexfast, indexslow, \ centerfast, centerslow) \ cbf_set_reference_beam_center((detector),(indexfast),(indexslow), \ (centerslow),(centerfast) ) /* Get the detector distance */ int cbf_get_detector_distance (cbf_detector detector, double *distance); /* Get the detector normal */ int cbf_get_detector_normal (cbf_detector detector, double *normal1, double *normal2, double *normal3); /* Calcluate the coordinates of a pixel */ int cbf_get_pixel_coordinates (cbf_detector detector, double indexslow, double indexfast, double *coordinate1, double *coordinate2, double *coordinate3); #define cbf_get_pixel_coordinates_sf(detector, indexslow, indexfast, \ coordinate1, coordinate2, coordinate3) \ cbf_get_pixel_coordinates ((detector),(indexslow),(indexfast), \ (coordinate1), (coordinate2), (coordinate3)) #define cbf_get_pixel_coordinates_fs(detector, indexfast, indexslow, \ coordinate1, coordinate2, coordinate3) \ cbf_get_pixel_coordinates ((detector),(indexslow),(indexfast), \ (coordinate1), (coordinate2), (coordinate3)) /* Get the pixel normal */ int cbf_get_pixel_normal (cbf_detector detector, double indexslow, double indexfast, double *normal1, double *normal2, double *normal3); #define cbf_get_pixel_normal_sf(detector, indexslow, indexfast, \ normal1, normal2, normal3) \ cbf_get_pixel_normal ((detector),(indexslow),(indexfast), \ (normal1), (normal2), (normal3) ) #define cbf_get_pixel_normal_fs(detector, indexfast, indexslow, \ normal1, normal2, normal3) \ cbf_get_pixel_normal ((detector),(indexslow),(indexfast), \ (normal1), (normal2), (normal3) ) /* Calcluate the slow axis of a detector */ int cbf_get_detector_axis_slow (cbf_detector detector, double *slowaxis1, double *slowaxis2, double *slowaxis3); /* Calcluate the fast axis of a detector */ int cbf_get_detector_axis_fast (cbf_detector detector, double *fastaxis1, double *fastaxis2, double *fastaxis3); /* Calcluate the axes of a detector */ int cbf_get_detector_axes (cbf_detector detector, double *slowaxis1, double *slowaxis2, double *slowaxis3, double *fastaxis1, double *fastaxis2, double *fastaxis3); #define cbf_get_detector_axes_sf(detector, slowaxis1, slowaxis2, slowaxis3, fastaxis1, fastaxis2, fastaxis3) \ cbf_get_detector_axes ((detector), (slowaxis1), (slowaxis2), (slowaxis3), (fastaxis1), (fastaxis2), (fastaxis3)) #define cbf_get_detector_axes_fs(detector, fastaxis1, fastaxis2, fastaxis3, slowaxis1, slowaxis2, slowaxis3) \ cbf_get_detector_axes ((detector), (slowaxis1), (slowaxis2), (slowaxis3), (fastaxis1), (fastaxis2), (fastaxis3)) /* Calcluate the area of a pixel */ int cbf_get_pixel_area (cbf_detector detector, double indexslow, double indexfast, double *area, double *projected_area); #define cbf_get_pixel_area_sf(detector, indexslow, indexfast, area, projected_area) \ cbf_get_pixel_area ((detector), (indexslow), (indexfast), (area), (projected_area)) #define cbf_get_pixel_area_fs(detector, indexfast, indexslow, area, projected_area) \ cbf_get_pixel_area ((detector), (indexslow), (indexfast), (area), (projected_area)) /* Calcluate the size of a pixel from the detector element axis displacements */ int cbf_get_inferred_pixel_size (cbf_detector detector, int axis_number, double *psize); #define cbf_get_inferred_pixel_size_fs(detector, axis_number, psize) \ cbf_get_inferred_pixel_size((detector), -(axis_number), (psize)) #define cbf_get_inferred_pixel_size_sf(detector, axis_number, psize) \ cbf_get_inferred_pixel_size((detector), (axis_number), (psize)) /* Get the unit cell parameters */ int cbf_get_unit_cell (cbf_handle handle, double cell[6], double cell_esd[6] ); /* Set the unit cell parameters */ int cbf_set_unit_cell (cbf_handle handle, double cell[6], double cell_esd[6] ); /* Get the reciprocal cell parameters */ int cbf_get_reciprocal_cell (cbf_handle handle, double cell[6], double cell_esd[6] ); /* Set the reciprocal cell parameters */ int cbf_set_reciprocal_cell (cbf_handle handle, double cell[6], double cell_esd[6] ); /* Compute a cell volume */ int cbf_compute_cell_volume (double cell[6], double *volume); /* Compute a reciprocal cell */ int cbf_compute_reciprocal_cell (double cell[6], double rcell[6]); /* Get the orientation matrix entry */ int cbf_get_orientation_matrix (cbf_handle handle, double ub_matrix[9]); /* Set the orientation matrix entry */ int cbf_set_orientation_matrix (cbf_handle handle, double ub_matrix[9]); #ifdef __cplusplus } #endif #endif /* CBF_SIMPLE_H */ ./CBFlib-0.9.2.2/ply-3.2/0000755000076500007650000000000011603703065012707 5ustar yayayaya./CBFlib-0.9.2.2/ply-3.2/doc/0000755000076500007650000000000011603703070013450 5ustar yayayaya./CBFlib-0.9.2.2/ply-3.2/doc/internal.html0000644000076500007650000007077011603702121016161 0ustar yayayaya PLY Internals

    PLY Internals

    David M. Beazley
    dave@dabeaz.com

    PLY Version: 3.0

    1. Introduction

    This document describes classes and functions that make up the internal operation of PLY. Using this programming interface, it is possible to manually build an parser using a different interface specification than what PLY normally uses. For example, you could build a gramar from information parsed in a completely different input format. Some of these objects may be useful for building more advanced parsing engines such as GLR.

    It should be stressed that using PLY at this level is not for the faint of heart. Generally, it's assumed that you know a bit of the underlying compiler theory and how an LR parser is put together.

    2. Grammar Class

    The file ply.yacc defines a class Grammar that is used to hold and manipulate information about a grammar specification. It encapsulates the same basic information about a grammar that is put into a YACC file including the list of tokens, precedence rules, and grammar rules. Various operations are provided to perform different validations on the grammar. In addition, there are operations to compute the first and follow sets that are needed by the various table generation algorithms.

    Grammar(terminals)

    Creates a new grammar object. terminals is a list of strings specifying the terminals for the grammar. An instance g of Grammar has the following methods:

    g.set_precedence(term,assoc,level)

    Sets the precedence level and associativity for a given terminal term. assoc is one of 'right', 'left', or 'nonassoc' and level is a positive integer. The higher the value of level, the higher the precedence. Here is an example of typical precedence settings:
    g.set_precedence('PLUS',  'left',1)
    g.set_precedence('MINUS', 'left',1)
    g.set_precedence('TIMES', 'left',2)
    g.set_precedence('DIVIDE','left',2)
    g.set_precedence('UMINUS','left',3)
    
    This method must be called prior to adding any productions to the grammar with g.add_production(). The precedence of individual grammar rules is determined by the precedence of the right-most terminal.

    g.add_production(name,syms,func=None,file='',line=0)

    Adds a new grammar rule. name is the name of the rule, syms is a list of symbols making up the right hand side of the rule, func is the function to call when reducing the rule. file and line specify the filename and line number of the rule and are used for generating error messages.

    The list of symbols in syms may include character literals and %prec specifiers. Here are some examples:

    g.add_production('expr',['expr','PLUS','term'],func,file,line)
    g.add_production('expr',['expr','"+"','term'],func,file,line)
    g.add_production('expr',['MINUS','expr','%prec','UMINUS'],func,file,line)
    

    If any kind of error is detected, a GrammarError exception is raised with a message indicating the reason for the failure.

    g.set_start(start=None)

    Sets the starting rule for the grammar. start is a string specifying the name of the start rule. If start is omitted, the first grammar rule added with add_production() is taken to be the starting rule. This method must always be called after all productions have been added.

    g.find_unreachable()

    Diagnostic function. Returns a list of all unreachable non-terminals defined in the grammar. This is used to identify inactive parts of the grammar specification.

    g.infinite_cycle()

    Diagnostic function. Returns a list of all non-terminals in the grammar that result in an infinite cycle. This condition occurs if there is no way for a grammar rule to expand to a string containing only terminal symbols.

    g.undefined_symbols()

    Diagnostic function. Returns a list of tuples (name, prod) corresponding to undefined symbols in the grammar. name is the name of the undefined symbol and prod is an instance of Production which has information about the production rule where the undefined symbol was used.

    g.unused_terminals()

    Diagnostic function. Returns a list of terminals that were defined, but never used in the grammar.

    g.unused_rules()

    Diagnostic function. Returns a list of Production instances corresponding to production rules that were defined in the grammar, but never used anywhere. This is slightly different than find_unreachable().

    g.unused_precedence()

    Diagnostic function. Returns a list of tuples (term, assoc) corresponding to precedence rules that were set, but never used the grammar. term is the terminal name and assoc is the precedence associativity (e.g., 'left', 'right', or 'nonassoc'.

    g.compute_first()

    Compute all of the first sets for all symbols in the grammar. Returns a dictionary mapping symbol names to a list of all first symbols.

    g.compute_follow()

    Compute all of the follow sets for all non-terminals in the grammar. The follow set is the set of all possible symbols that might follow a given non-terminal. Returns a dictionary mapping non-terminal names to a list of symbols.

    g.build_lritems()

    Calculates all of the LR items for all productions in the grammar. This step is required before using the grammar for any kind of table generation. See the section on LR items below.

    The following attributes are set by the above methods and may be useful in code that works with the grammar. All of these attributes should be assumed to be read-only. Changing their values directly will likely break the grammar.

    g.Productions

    A list of all productions added. The first entry is reserved for a production representing the starting rule. The objects in this list are instances of the Production class, described shortly.

    g.Prodnames

    A dictionary mapping the names of nonterminals to a list of all productions of that nonterminal.

    g.Terminals

    A dictionary mapping the names of terminals to a list of the production numbers where they are used.

    g.Nonterminals

    A dictionary mapping the names of nonterminals to a list of the production numbers where they are used.

    g.First

    A dictionary representing the first sets for all grammar symbols. This is computed and returned by the compute_first() method.

    g.Follow

    A dictionary representing the follow sets for all grammar rules. This is computed and returned by the compute_follow() method.

    g.Start

    Starting symbol for the grammar. Set by the set_start() method.
    For the purposes of debugging, a Grammar object supports the __len__() and __getitem__() special methods. Accessing g[n] returns the nth production from the grammar.

    3. Productions

    Grammar objects store grammar rules as instances of a Production class. This class has no public constructor--you should only create productions by calling Grammar.add_production(). The following attributes are available on a Production instance p.

    p.name

    The name of the production. For a grammar rule such as A : B C D, this is 'A'.

    p.prod

    A tuple of symbols making up the right-hand side of the production. For a grammar rule such as A : B C D, this is ('B','C','D').

    p.number

    Production number. An integer containing the index of the production in the grammar's Productions list.

    p.func

    The name of the reduction function associated with the production. This is the function that will execute when reducing the entire grammar rule during parsing.

    p.callable

    The callable object associated with the name in p.func. This is None unless the production has been bound using bind().

    p.file

    Filename associated with the production. Typically this is the file where the production was defined. Used for error messages.

    p.lineno

    Line number associated with the production. Typically this is the line number in p.file where the production was defined. Used for error messages.

    p.prec

    Precedence and associativity associated with the production. This is a tuple (assoc,level) where assoc is one of 'left','right', or 'nonassoc' and level is an integer. This value is determined by the precedence of the right-most terminal symbol in the production or by use of the %prec specifier when adding the production.

    p.usyms

    A list of all unique symbols found in the production.

    p.lr_items

    A list of all LR items for this production. This attribute only has a meaningful value if the Grammar.build_lritems() method has been called. The items in this list are instances of LRItem described below.

    p.lr_next

    The head of a linked-list representation of the LR items in p.lr_items. This attribute only has a meaningful value if the Grammar.build_lritems() method has been called. Each LRItem instance has a lr_next attribute to move to the next item. The list is terminated by None.

    p.bind(dict)

    Binds the production function name in p.func to a callable object in dict. This operation is typically carried out in the last step prior to running the parsing engine and is needed since parsing tables are typically read from files which only include the function names, not the functions themselves.

    Production objects support the __len__(), __getitem__(), and __str__() special methods. len(p) returns the number of symbols in p.prod and p[n] is the same as p.prod[n].

    4. LRItems

    The construction of parsing tables in an LR-based parser generator is primarily done over a set of "LR Items". An LR item represents a stage of parsing one of the grammar rules. To compute the LR items, it is first necessary to call Grammar.build_lritems(). Once this step, all of the productions in the grammar will have their LR items attached to them.

    Here is an interactive example that shows what LR items look like if you interactively experiment. In this example, g is a Grammar object.

    >>> g.build_lritems()
    >>> p = g[1]
    >>> p
    Production(statement -> ID = expr)
    >>>
    
    In the above code, p represents the first grammar rule. In this case, a rule 'statement -> ID = expr'.

    Now, let's look at the LR items for p.

    >>> p.lr_items
    [LRItem(statement -> . ID = expr), 
     LRItem(statement -> ID . = expr), 
     LRItem(statement -> ID = . expr), 
     LRItem(statement -> ID = expr .)]
    >>>
    
    In each LR item, the dot (.) represents a specific stage of parsing. In each LR item, the dot is advanced by one symbol. It is only when the dot reaches the very end that a production is successfully parsed.

    An instance lr of LRItem has the following attributes that hold information related to that specific stage of parsing.

    lr.name

    The name of the grammar rule. For example, 'statement' in the above example.

    lr.prod

    A tuple of symbols representing the right-hand side of the production, including the special '.' character. For example, ('ID','.','=','expr').

    lr.number

    An integer representing the production number in the grammar.

    lr.usyms

    A set of unique symbols in the production. Inherited from the original Production instance.

    lr.lr_index

    An integer representing the position of the dot (.). You should never use lr.prod.index() to search for it--the result will be wrong if the grammar happens to also use (.) as a character literal.

    lr.lr_after

    A list of all productions that can legally appear immediately to the right of the dot (.). This list contains Production instances. This attribute represents all of the possible branches a parse can take from the current position. For example, suppose that lr represents a stage immediately before an expression like this:
    >>> lr
    LRItem(statement -> ID = . expr)
    >>>
    
    Then, the value of lr.lr_after might look like this, showing all productions that can legally appear next:
    >>> lr.lr_after
    [Production(expr -> expr PLUS expr), 
     Production(expr -> expr MINUS expr), 
     Production(expr -> expr TIMES expr), 
     Production(expr -> expr DIVIDE expr), 
     Production(expr -> MINUS expr), 
     Production(expr -> LPAREN expr RPAREN), 
     Production(expr -> NUMBER), 
     Production(expr -> ID)]
    >>>
    

    lr.lr_before

    The grammar symbol that appears immediately before the dot (.) or None if at the beginning of the parse.

    lr.lr_next

    A link to the next LR item, representing the next stage of the parse. None if lr is the last LR item.
    LRItem instances also support the __len__() and __getitem__() special methods. len(lr) returns the number of items in lr.prod including the dot (.). lr[n] returns lr.prod[n].

    It goes without saying that all of the attributes associated with LR items should be assumed to be read-only. Modifications will very likely create a small black-hole that will consume you and your code.

    5. LRTable

    The LRTable class is used to represent LR parsing table data. This minimally includes the production list, action table, and goto table.

    LRTable()

    Create an empty LRTable object. This object contains only the information needed to run an LR parser.
    An instance lrtab of LRTable has the following methods:

    lrtab.read_table(module)

    Populates the LR table with information from the module specified in module. module is either a module object already loaded with import or the name of a Python module. If it's a string containing a module name, it is loaded and parsing data is extracted. Returns the signature value that was used when initially writing the tables. Raises a VersionError exception if the module was created using an incompatible version of PLY.

    lrtab.bind_callables(dict)

    This binds all of the function names used in productions to callable objects found in the dictionary dict. During table generation and when reading LR tables from files, PLY only uses the names of action functions such as 'p_expr', 'p_statement', etc. In order to actually run the parser, these names have to be bound to callable objects. This method is always called prior to running a parser.
    After lrtab has been populated, the following attributes are defined.

    lrtab.lr_method

    The LR parsing method used (e.g., 'LALR')

    lrtab.lr_productions

    The production list. If the parsing tables have been newly constructed, this will be a list of Production instances. If the parsing tables have been read from a file, it's a list of MiniProduction instances. This, together with lr_action and lr_goto contain all of the information needed by the LR parsing engine.

    lrtab.lr_action

    The LR action dictionary that implements the underlying state machine. The keys of this dictionary are the LR states.

    lrtab.lr_goto

    The LR goto table that contains information about grammar rule reductions.

    6. LRGeneratedTable

    The LRGeneratedTable class represents constructed LR parsing tables on a grammar. It is a subclass of LRTable.

    LRGeneratedTable(grammar, method='LALR',log=None)

    Create the LR parsing tables on a grammar. grammar is an instance of Grammar, method is a string with the parsing method ('SLR' or 'LALR'), and log is a logger object used to write debugging information. The debugging information written to log is the same as what appears in the parser.out file created by yacc. By supplying a custom logger with a different message format, it is possible to get more information (e.g., the line number in yacc.py used for issuing each line of output in the log). The result is an instance of LRGeneratedTable.

    An instance lr of LRGeneratedTable has the following attributes.

    lr.grammar

    A link to the Grammar object used to construct the parsing tables.

    lr.lr_method

    The LR parsing method used (e.g., 'LALR')

    lr.lr_productions

    A reference to grammar.Productions. This, together with lr_action and lr_goto contain all of the information needed by the LR parsing engine.

    lr.lr_action

    The LR action dictionary that implements the underlying state machine. The keys of this dictionary are the LR states.

    lr.lr_goto

    The LR goto table that contains information about grammar rule reductions.

    lr.sr_conflicts

    A list of tuples (state,token,resolution) identifying all shift/reduce conflicts. state is the LR state number where the conflict occurred, token is the token causing the conflict, and resolution is a string describing the resolution taken. resolution is either 'shift' or 'reduce'.

    lr.rr_conflicts

    A list of tuples (state,rule,rejected) identifying all reduce/reduce conflicts. state is the LR state number where the conflict occurred, rule is the production rule that was selected and rejected is the production rule that was rejected. Both rule and rejected are instances of Production. They can be inspected to provide the user with more information.

    There are two public methods of LRGeneratedTable.

    lr.write_table(modulename,outputdir="",signature="")

    Writes the LR parsing table information to a Python module. modulename is a string specifying the name of a module such as "parsetab". outputdir is the name of a directory where the module should be created. signature is a string representing a grammar signature that's written into the output file. This can be used to detect when the data stored in a module file is out-of-sync with the the grammar specification (and that the tables need to be regenerated). If modulename is a string "parsetab", this function creates a file called parsetab.py. If the module name represents a package such as "foo.bar.parsetab", then only the last component, "parsetab" is used.

    7. LRParser

    The LRParser class implements the low-level LR parsing engine.

    LRParser(lrtab, error_func)

    Create an LRParser. lrtab is an instance of LRTable containing the LR production and state tables. error_func is the error function to invoke in the event of a parsing error.
    An instance p of LRParser has the following methods:

    p.parse(input=None,lexer=None,debug=0,tracking=0,tokenfunc=None)

    Run the parser. input is a string, which if supplied is fed into the lexer using its input() method. lexer is an instance of the Lexer class to use for tokenizing. If not supplied, the last lexer created with the lex module is used. debug is a boolean flag that enables debugging. tracking is a boolean flag that tells the parser to perform additional line number tracking. tokenfunc is a callable function that returns the next token. If supplied, the parser will use it to get all tokens.

    p.restart()

    Resets the parser state for a parse already in progress.

    8. ParserReflect

    The ParserReflect class is used to collect parser specification data from a Python module or object. This class is what collects all of the p_rule() functions in a PLY file, performs basic error checking, and collects all of the needed information to build a grammar. Most of the high-level PLY interface as used by the yacc() function is actually implemented by this class.

    ParserReflect(pdict, log=None)

    Creates a ParserReflect instance. pdict is a dictionary containing parser specification data. This dictionary typically corresponds to the module or class dictionary of code that implements a PLY parser. log is a logger instance that will be used to report error messages.
    An instance p of ParserReflect has the following methods:

    p.get_all()

    Collect and store all required parsing information.

    p.validate_all()

    Validate all of the collected parsing information. This is a seprate step from p.get_all() as a performance optimization. In order to increase parser start-up time, a parser can elect to only validate the parsing data when regenerating the parsing tables. The validation step tries to collect as much information as possible rather than raising an exception at the first sign of trouble. The attribute p.error is set if there are any validation errors. The value of this attribute is also returned.

    p.signature()

    Compute a signature representing the contents of the collected parsing data. The signature value should change if anything in the parser specification has changed in a way that would justify parser table regeneration. This method can be called after p.get_all(), but before p.validate_all().
    The following attributes are set in the process of collecting data:

    p.start

    The grammar start symbol, if any. Taken from pdict['start'].

    p.error_func

    The error handling function or None. Taken from pdict['p_error'].

    p.tokens

    The token list. Taken from pdict['tokens'].

    p.prec

    The precedence specifier. Taken from pdict['precedence'].

    p.preclist

    A parsed version of the precedence specified. A list of tuples of the form (token,assoc,level) where token is the terminal symbol, assoc is the associativity (e.g., 'left') and level is a numeric precedence level.

    p.grammar

    A list of tuples (name, rules) representing the grammar rules. name is the name of a Python function or method in pdict that starts with "p_". rules is a list of tuples (filename,line,prodname,syms) representing the grammar rules found in the documentation string of that function. filename and line contain location information that can be used for debugging. prodname is the name of the production. syms is the right-hand side of the production. If you have a function like this
    def p_expr(p):
        '''expr : expr PLUS expr
                | expr MINUS expr
                | expr TIMES expr
                | expr DIVIDE expr'''
    
    then the corresponding entry in p.grammar might look like this:
    ('p_expr', [ ('calc.py',10,'expr', ['expr','PLUS','expr']),
                 ('calc.py',11,'expr', ['expr','MINUS','expr']),
                 ('calc.py',12,'expr', ['expr','TIMES','expr']),
                 ('calc.py',13,'expr', ['expr','DIVIDE','expr'])
               ])
    

    p.pfuncs

    A sorted list of tuples (line, file, name, doc) representing all of the p_ functions found. line and file give location information. name is the name of the function. doc is the documentation string. This list is sorted in ascending order by line number.

    p.files

    A dictionary holding all of the source filenames that were encountered while collecting parser information. Only the keys of this dictionary have any meaning.

    p.error

    An attribute that indicates whether or not any critical errors occurred in validation. If this is set, it means that that some kind of problem was detected and that no further processing should be performed.

    9. High-level operation

    Using all of the above classes requires some attention to detail. The yacc() function carries out a very specific sequence of operations to create a grammar. This same sequence should be emulated if you build an alternative PLY interface.
    1. A ParserReflect object is created and raw grammar specification data is collected.
    2. A Grammar object is created and populated with information from the specification data.
    3. A LRGenerator object is created to run the LALR algorithm over the Grammar object.
    4. Productions in the LRGenerator and bound to callables using the bind_callables() method.
    5. A LRParser object is created from from the information in the LRGenerator object.
    ./CBFlib-0.9.2.2/ply-3.2/doc/makedoc.py0000644000076500007650000001334611603702121015430 0ustar yayayaya#!/usr/local/bin/python ############################################################################### # Takes a chapter as input and adds internal links and numbering to all # of the H1, H2, H3, H4 and H5 sections. # # Every heading HTML tag (H1, H2 etc) is given an autogenerated name to link # to. However, if the name is not an autogenerated name from a previous run, # it will be kept. If it is autogenerated, it might change on subsequent runs # of this program. Thus if you want to create links to one of the headings, # then change the heading link name to something that does not look like an # autogenerated link name. ############################################################################### import sys import re import string ############################################################################### # Functions ############################################################################### # Regexs for alink = re.compile(r"", re.IGNORECASE) heading = re.compile(r"(_nn\d)", re.IGNORECASE) def getheadingname(m): autogeneratedheading = True; if m.group(1) != None: amatch = alink.match(m.group(1)) if amatch: # A non-autogenerated heading - keep it headingname = amatch.group(1) autogeneratedheading = heading.match(headingname) if autogeneratedheading: # The heading name was either non-existent or autogenerated, # We can create a new heading / change the existing heading headingname = "%s_nn%d" % (filenamebase, nameindex) return headingname ############################################################################### # Main program ############################################################################### if len(sys.argv) != 2: print "usage: makedoc.py filename" sys.exit(1) filename = sys.argv[1] filenamebase = string.split(filename,".")[0] section = 0 subsection = 0 subsubsection = 0 subsubsubsection = 0 nameindex = 0 name = "" # Regexs for

    ,...

    sections h1 = re.compile(r".*?

    ()*[\d\.\s]*(.*?)

    ", re.IGNORECASE) h2 = re.compile(r".*?

    ()*[\d\.\s]*(.*?)

    ", re.IGNORECASE) h3 = re.compile(r".*?

    ()*[\d\.\s]*(.*?)

    ", re.IGNORECASE) h4 = re.compile(r".*?

    ()*[\d\.\s]*(.*?)

    ", re.IGNORECASE) h5 = re.compile(r".*?
    ()*[\d\.\s]*(.*?)
    ", re.IGNORECASE) data = open(filename).read() # Read data open(filename+".bak","w").write(data) # Make backup lines = data.splitlines() result = [ ] # This is the result of postprocessing the file index = "\n
    \n" # index contains the index for adding at the top of the file. Also printed to stdout. skip = 0 skipspace = 0 for s in lines: if s == "": if not skip: result.append("@INDEX@") skip = 1 else: skip = 0 continue; if skip: continue if not s and skipspace: continue if skipspace: result.append("") result.append("") skipspace = 0 m = h2.match(s) if m: prevheadingtext = m.group(2) nameindex += 1 section += 1 headingname = getheadingname(m) result.append("""

    %d. %s

    """ % (headingname,section, prevheadingtext)) if subsubsubsection: index += "\n" if subsubsection: index += "\n" if subsection: index += "\n" if section == 1: index += "
      \n" index += """
    • %s\n""" % (headingname,prevheadingtext) subsection = 0 subsubsection = 0 subsubsubsection = 0 skipspace = 1 continue m = h3.match(s) if m: prevheadingtext = m.group(2) nameindex += 1 subsection += 1 headingname = getheadingname(m) result.append("""

      %d.%d %s

      """ % (headingname,section, subsection, prevheadingtext)) if subsubsubsection: index += "
    \n" if subsubsection: index += "\n" if subsection == 1: index += "
      \n" index += """
    • %s\n""" % (headingname,prevheadingtext) subsubsection = 0 skipspace = 1 continue m = h4.match(s) if m: prevheadingtext = m.group(2) nameindex += 1 subsubsection += 1 subsubsubsection = 0 headingname = getheadingname(m) result.append("""

      %d.%d.%d %s

      """ % (headingname,section, subsection, subsubsection, prevheadingtext)) if subsubsubsection: index += "
    \n" if subsubsection == 1: index += "
      \n" index += """
    • %s\n""" % (headingname,prevheadingtext) skipspace = 1 continue m = h5.match(s) if m: prevheadingtext = m.group(2) nameindex += 1 subsubsubsection += 1 headingname = getheadingname(m) result.append("""
      %d.%d.%d.%d %s
      """ % (headingname,section, subsection, subsubsection, subsubsubsection, prevheadingtext)) if subsubsubsection == 1: index += "
        \n" index += """
      • %s\n""" % (headingname,prevheadingtext) skipspace = 1 continue result.append(s) if subsubsubsection: index += "
      \n" if subsubsection: index += "
    \n" if subsection: index += "\n" if section: index += "\n" index += "
    \n\n" data = "\n".join(result) data = data.replace("@INDEX@",index) + "\n"; # Write the file back out open(filename,"w").write(data) ./CBFlib-0.9.2.2/ply-3.2/doc/ply.html0000644000076500007650000032177711603702121015157 0ustar yayayaya PLY (Python Lex-Yacc)

    PLY (Python Lex-Yacc)

    David M. Beazley
    dave@dabeaz.com

    PLY Version: 3.0

    1. Preface and Requirements

    This document provides an overview of lexing and parsing with PLY. Given the intrinsic complexity of parsing, I would strongly advise that you read (or at least skim) this entire document before jumping into a big development project with PLY.

    PLY-3.0 is compatible with both Python 2 and Python 3. Be aware that Python 3 support is new and has not been extensively tested (although all of the examples and unit tests pass under Python 3.0). If you are using Python 2, you should try to use Python 2.4 or newer. Although PLY works with versions as far back as Python 2.2, some of its optional features require more modern library modules.

    2. Introduction

    PLY is a pure-Python implementation of the popular compiler construction tools lex and yacc. The main goal of PLY is to stay fairly faithful to the way in which traditional lex/yacc tools work. This includes supporting LALR(1) parsing as well as providing extensive input validation, error reporting, and diagnostics. Thus, if you've used yacc in another programming language, it should be relatively straightforward to use PLY.

    Early versions of PLY were developed to support an Introduction to Compilers Course I taught in 2001 at the University of Chicago. In this course, students built a fully functional compiler for a simple Pascal-like language. Their compiler, implemented entirely in Python, had to include lexical analysis, parsing, type checking, type inference, nested scoping, and code generation for the SPARC processor. Approximately 30 different compiler implementations were completed in this course. Most of PLY's interface and operation has been influenced by common usability problems encountered by students. Since 2001, PLY has continued to be improved as feedback has been received from users. PLY-3.0 represents a major refactoring of the original implementation with an eye towards future enhancements.

    Since PLY was primarily developed as an instructional tool, you will find it to be fairly picky about token and grammar rule specification. In part, this added formality is meant to catch common programming mistakes made by novice users. However, advanced users will also find such features to be useful when building complicated grammars for real programming languages. It should also be noted that PLY does not provide much in the way of bells and whistles (e.g., automatic construction of abstract syntax trees, tree traversal, etc.). Nor would I consider it to be a parsing framework. Instead, you will find a bare-bones, yet fully capable lex/yacc implementation written entirely in Python.

    The rest of this document assumes that you are somewhat familar with parsing theory, syntax directed translation, and the use of compiler construction tools such as lex and yacc in other programming languages. If you are unfamilar with these topics, you will probably want to consult an introductory text such as "Compilers: Principles, Techniques, and Tools", by Aho, Sethi, and Ullman. O'Reilly's "Lex and Yacc" by John Levine may also be handy. In fact, the O'Reilly book can be used as a reference for PLY as the concepts are virtually identical.

    3. PLY Overview

    PLY consists of two separate modules; lex.py and yacc.py, both of which are found in a Python package called ply. The lex.py module is used to break input text into a collection of tokens specified by a collection of regular expression rules. yacc.py is used to recognize language syntax that has been specified in the form of a context free grammar. yacc.py uses LR parsing and generates its parsing tables using either the LALR(1) (the default) or SLR table generation algorithms.

    The two tools are meant to work together. Specifically, lex.py provides an external interface in the form of a token() function that returns the next valid token on the input stream. yacc.py calls this repeatedly to retrieve tokens and invoke grammar rules. The output of yacc.py is often an Abstract Syntax Tree (AST). However, this is entirely up to the user. If desired, yacc.py can also be used to implement simple one-pass compilers.

    Like its Unix counterpart, yacc.py provides most of the features you expect including extensive error checking, grammar validation, support for empty productions, error tokens, and ambiguity resolution via precedence rules. In fact, everything that is possible in traditional yacc should be supported in PLY.

    The primary difference between yacc.py and Unix yacc is that yacc.py doesn't involve a separate code-generation process. Instead, PLY relies on reflection (introspection) to build its lexers and parsers. Unlike traditional lex/yacc which require a special input file that is converted into a separate source file, the specifications given to PLY are valid Python programs. This means that there are no extra source files nor is there a special compiler construction step (e.g., running yacc to generate Python code for the compiler). Since the generation of the parsing tables is relatively expensive, PLY caches the results and saves them to a file. If no changes are detected in the input source, the tables are read from the cache. Otherwise, they are regenerated.

    4. Lex

    lex.py is used to tokenize an input string. For example, suppose you're writing a programming language and a user supplied the following input string:
    x = 3 + 42 * (s - t)
    
    A tokenizer splits the string into individual tokens
    'x','=', '3', '+', '42', '*', '(', 's', '-', 't', ')'
    
    Tokens are usually given names to indicate what they are. For example:
    'ID','EQUALS','NUMBER','PLUS','NUMBER','TIMES',
    'LPAREN','ID','MINUS','ID','RPAREN'
    
    More specifically, the input is broken into pairs of token types and values. For example:
    ('ID','x'), ('EQUALS','='), ('NUMBER','3'), 
    ('PLUS','+'), ('NUMBER','42), ('TIMES','*'),
    ('LPAREN','('), ('ID','s'), ('MINUS','-'),
    ('ID','t'), ('RPAREN',')'
    
    The identification of tokens is typically done by writing a series of regular expression rules. The next section shows how this is done using lex.py.

    4.1 Lex Example

    The following example shows how lex.py is used to write a simple tokenizer.
    # ------------------------------------------------------------
    # calclex.py
    #
    # tokenizer for a simple expression evaluator for
    # numbers and +,-,*,/
    # ------------------------------------------------------------
    import ply.lex as lex
    
    # List of token names.   This is always required
    tokens = (
       'NUMBER',
       'PLUS',
       'MINUS',
       'TIMES',
       'DIVIDE',
       'LPAREN',
       'RPAREN',
    )
    
    # Regular expression rules for simple tokens
    t_PLUS    = r'\+'
    t_MINUS   = r'-'
    t_TIMES   = r'\*'
    t_DIVIDE  = r'/'
    t_LPAREN  = r'\('
    t_RPAREN  = r'\)'
    
    # A regular expression rule with some action code
    def t_NUMBER(t):
        r'\d+'
        t.value = int(t.value)    
        return t
    
    # Define a rule so we can track line numbers
    def t_newline(t):
        r'\n+'
        t.lexer.lineno += len(t.value)
    
    # A string containing ignored characters (spaces and tabs)
    t_ignore  = ' \t'
    
    # Error handling rule
    def t_error(t):
        print "Illegal character '%s'" % t.value[0]
        t.lexer.skip(1)
    
    # Build the lexer
    lexer = lex.lex()
    
    
    To use the lexer, you first need to feed it some input text using its input() method. After that, repeated calls to token() produce tokens. The following code shows how this works:
    
    # Test it out
    data = '''
    3 + 4 * 10
      + -20 *2
    '''
    
    # Give the lexer some input
    lexer.input(data)
    
    # Tokenize
    while True:
        tok = lexer.token()
        if not tok: break      # No more input
        print tok
    
    When executed, the example will produce the following output:
    $ python example.py
    LexToken(NUMBER,3,2,1)
    LexToken(PLUS,'+',2,3)
    LexToken(NUMBER,4,2,5)
    LexToken(TIMES,'*',2,7)
    LexToken(NUMBER,10,2,10)
    LexToken(PLUS,'+',3,14)
    LexToken(MINUS,'-',3,16)
    LexToken(NUMBER,20,3,18)
    LexToken(TIMES,'*',3,20)
    LexToken(NUMBER,2,3,21)
    
    Lexers also support the iteration protocol. So, you can write the above loop as follows:
    for tok in lexer:
        print tok
    
    The tokens returned by lexer.token() are instances of LexToken. This object has attributes tok.type, tok.value, tok.lineno, and tok.lexpos. The following code shows an example of accessing these attributes:
    # Tokenize
    while True:
        tok = lexer.token()
        if not tok: break      # No more input
        print tok.type, tok.value, tok.line, tok.lexpos
    
    The tok.type and tok.value attributes contain the type and value of the token itself. tok.line and tok.lexpos contain information about the location of the token. tok.lexpos is the index of the token relative to the start of the input text.

    4.2 The tokens list

    All lexers must provide a list tokens that defines all of the possible token names that can be produced by the lexer. This list is always required and is used to perform a variety of validation checks. The tokens list is also used by the yacc.py module to identify terminals.

    In the example, the following code specified the token names:

    tokens = (
       'NUMBER',
       'PLUS',
       'MINUS',
       'TIMES',
       'DIVIDE',
       'LPAREN',
       'RPAREN',
    )
    

    4.3 Specification of tokens

    Each token is specified by writing a regular expression rule. Each of these rules are are defined by making declarations with a special prefix t_ to indicate that it defines a token. For simple tokens, the regular expression can be specified as strings such as this (note: Python raw strings are used since they are the most convenient way to write regular expression strings):
    t_PLUS = r'\+'
    
    In this case, the name following the t_ must exactly match one of the names supplied in tokens. If some kind of action needs to be performed, a token rule can be specified as a function. For example, this rule matches numbers and converts the string into a Python integer.
    def t_NUMBER(t):
        r'\d+'
        t.value = int(t.value)
        return t
    
    When a function is used, the regular expression rule is specified in the function documentation string. The function always takes a single argument which is an instance of LexToken. This object has attributes of t.type which is the token type (as a string), t.value which is the lexeme (the actual text matched), t.lineno which is the current line number, and t.lexpos which is the position of the token relative to the beginning of the input text. By default, t.type is set to the name following the t_ prefix. The action function can modify the contents of the LexToken object as appropriate. However, when it is done, the resulting token should be returned. If no value is returned by the action function, the token is simply discarded and the next token read.

    Internally, lex.py uses the re module to do its patten matching. When building the master regular expression, rules are added in the following order:

    1. All tokens defined by functions are added in the same order as they appear in the lexer file.
    2. Tokens defined by strings are added next by sorting them in order of decreasing regular expression length (longer expressions are added first).

    Without this ordering, it can be difficult to correctly match certain types of tokens. For example, if you wanted to have separate tokens for "=" and "==", you need to make sure that "==" is checked first. By sorting regular expressions in order of decreasing length, this problem is solved for rules defined as strings. For functions, the order can be explicitly controlled since rules appearing first are checked first.

    To handle reserved words, you should write a single rule to match an identifier and do a special name lookup in a function like this:

    reserved = {
       'if' : 'IF',
       'then' : 'THEN',
       'else' : 'ELSE',
       'while' : 'WHILE',
       ...
    }
    
    tokens = ['LPAREN','RPAREN',...,'ID'] + list(reserved.values())
    
    def t_ID(t):
        r'[a-zA-Z_][a-zA-Z_0-9]*'
        t.type = reserved.get(t.value,'ID')    # Check for reserved words
        return t
    
    This approach greatly reduces the number of regular expression rules and is likely to make things a little faster.

    Note: You should avoid writing individual rules for reserved words. For example, if you write rules like this,

    t_FOR   = r'for'
    t_PRINT = r'print'
    
    those rules will be triggered for identifiers that include those words as a prefix such as "forget" or "printed". This is probably not what you want.

    4.4 Token values

    When tokens are returned by lex, they have a value that is stored in the value attribute. Normally, the value is the text that was matched. However, the value can be assigned to any Python object. For instance, when lexing identifiers, you may want to return both the identifier name and information from some sort of symbol table. To do this, you might write a rule like this:
    def t_ID(t):
        ...
        # Look up symbol table information and return a tuple
        t.value = (t.value, symbol_lookup(t.value))
        ...
        return t
    
    It is important to note that storing data in other attribute names is not recommended. The yacc.py module only exposes the contents of the value attribute. Thus, accessing other attributes may be unnecessarily awkward. If you need to store multiple values on a token, assign a tuple, dictionary, or instance to value.

    4.5 Discarded tokens

    To discard a token, such as a comment, simply define a token rule that returns no value. For example:
    def t_COMMENT(t):
        r'\#.*'
        pass
        # No return value. Token discarded
    
    Alternatively, you can include the prefix "ignore_" in the token declaration to force a token to be ignored. For example:
    t_ignore_COMMENT = r'\#.*'
    
    Be advised that if you are ignoring many different kinds of text, you may still want to use functions since these provide more precise control over the order in which regular expressions are matched (i.e., functions are matched in order of specification whereas strings are sorted by regular expression length).

    4.6 Line numbers and positional information

    By default, lex.py knows nothing about line numbers. This is because lex.py doesn't know anything about what constitutes a "line" of input (e.g., the newline character or even if the input is textual data). To update this information, you need to write a special rule. In the example, the t_newline() rule shows how to do this.

    # Define a rule so we can track line numbers
    def t_newline(t):
        r'\n+'
        t.lexer.lineno += len(t.value)
    
    Within the rule, the lineno attribute of the underlying lexer t.lexer is updated. After the line number is updated, the token is simply discarded since nothing is returned.

    lex.py does not perform and kind of automatic column tracking. However, it does record positional information related to each token in the lexpos attribute. Using this, it is usually possible to compute column information as a separate step. For instance, just count backwards until you reach a newline.

    # Compute column. 
    #     input is the input text string
    #     token is a token instance
    def find_column(input,token):
        last_cr = input.rfind('\n',0,token.lexpos)
        if last_cr < 0:
    	last_cr = 0
        column = (token.lexpos - last_cr) + 1
        return column
    
    Since column information is often only useful in the context of error handling, calculating the column position can be performed when needed as opposed to doing it for each token.

    4.7 Ignored characters

    The special t_ignore rule is reserved by lex.py for characters that should be completely ignored in the input stream. Usually this is used to skip over whitespace and other non-essential characters. Although it is possible to define a regular expression rule for whitespace in a manner similar to t_newline(), the use of t_ignore provides substantially better lexing performance because it is handled as a special case and is checked in a much more efficient manner than the normal regular expression rules.

    4.8 Literal characters

    Literal characters can be specified by defining a variable literals in your lexing module. For example:

    literals = [ '+','-','*','/' ]
    
    or alternatively
    literals = "+-*/"
    
    A literal character is simply a single character that is returned "as is" when encountered by the lexer. Literals are checked after all of the defined regular expression rules. Thus, if a rule starts with one of the literal characters, it will always take precedence.

    When a literal token is returned, both its type and value attributes are set to the character itself. For example, '+'.

    4.9 Error handling

    Finally, the t_error() function is used to handle lexing errors that occur when illegal characters are detected. In this case, the t.value attribute contains the rest of the input string that has not been tokenized. In the example, the error function was defined as follows:

    # Error handling rule
    def t_error(t):
        print "Illegal character '%s'" % t.value[0]
        t.lexer.skip(1)
    
    In this case, we simply print the offending character and skip ahead one character by calling t.lexer.skip(1).

    4.10 Building and using the lexer

    To build the lexer, the function lex.lex() is used. This function uses Python reflection (or introspection) to read the the regular expression rules out of the calling context and build the lexer. Once the lexer has been built, two methods can be used to control the lexer.

    • lexer.input(data). Reset the lexer and store a new input string.
    • lexer.token(). Return the next token. Returns a special LexToken instance on success or None if the end of the input text has been reached.
    The preferred way to use PLY is to invoke the above methods directly on the lexer object returned by the lex() function. The legacy interface to PLY involves module-level functions lex.input() and lex.token(). For example:
    lex.lex()
    lex.input(sometext)
    while 1:
        tok = lex.token()
        if not tok: break
        print tok
    

    In this example, the module-level functions lex.input() and lex.token() are bound to the input() and token() methods of the last lexer created by the lex module. This interface may go away at some point so it's probably best not to use it.

    4.11 The @TOKEN decorator

    In some applications, you may want to define build tokens from as a series of more complex regular expression rules. For example:
    digit            = r'([0-9])'
    nondigit         = r'([_A-Za-z])'
    identifier       = r'(' + nondigit + r'(' + digit + r'|' + nondigit + r')*)'        
    
    def t_ID(t):
        # want docstring to be identifier above. ?????
        ...
    
    In this case, we want the regular expression rule for ID to be one of the variables above. However, there is no way to directly specify this using a normal documentation string. To solve this problem, you can use the @TOKEN decorator. For example:
    from ply.lex import TOKEN
    
    @TOKEN(identifier)
    def t_ID(t):
        ...
    
    This will attach identifier to the docstring for t_ID() allowing lex.py to work normally. An alternative approach this problem is to set the docstring directly like this:
    def t_ID(t):
        ...
    
    t_ID.__doc__ = identifier
    
    NOTE: Use of @TOKEN requires Python-2.4 or newer. If you're concerned about backwards compatibility with older versions of Python, use the alternative approach of setting the docstring directly.

    4.12 Optimized mode

    For improved performance, it may be desirable to use Python's optimized mode (e.g., running Python with the -O option). However, doing so causes Python to ignore documentation strings. This presents special problems for lex.py. To handle this case, you can create your lexer using the optimize option as follows:
    lexer = lex.lex(optimize=1)
    
    Next, run Python in its normal operating mode. When you do this, lex.py will write a file called lextab.py to the current directory. This file contains all of the regular expression rules and tables used during lexing. On subsequent executions, lextab.py will simply be imported to build the lexer. This approach substantially improves the startup time of the lexer and it works in Python's optimized mode.

    To change the name of the lexer-generated file, use the lextab keyword argument. For example:

    lexer = lex.lex(optimize=1,lextab="footab")
    
    When running in optimized mode, it is important to note that lex disables most error checking. Thus, this is really only recommended if you're sure everything is working correctly and you're ready to start releasing production code.

    4.13 Debugging

    For the purpose of debugging, you can run lex() in a debugging mode as follows:
    lexer = lex.lex(debug=1)
    

    This will produce various sorts of debugging information including all of the added rules, the master regular expressions used by the lexer, and tokens generating during lexing.

    In addition, lex.py comes with a simple main function which will either tokenize input read from standard input or from a file specified on the command line. To use it, simply put this in your lexer:

    if __name__ == '__main__':
         lex.runmain()
    
    Please refer to the "Debugging" section near the end for some more advanced details of debugging.

    4.14 Alternative specification of lexers

    As shown in the example, lexers are specified all within one Python module. If you want to put token rules in a different module from the one in which you invoke lex(), use the module keyword argument.

    For example, you might have a dedicated module that just contains the token rules:

    # module: tokrules.py
    # This module just contains the lexing rules
    
    # List of token names.   This is always required
    tokens = (
       'NUMBER',
       'PLUS',
       'MINUS',
       'TIMES',
       'DIVIDE',
       'LPAREN',
       'RPAREN',
    )
    
    # Regular expression rules for simple tokens
    t_PLUS    = r'\+'
    t_MINUS   = r'-'
    t_TIMES   = r'\*'
    t_DIVIDE  = r'/'
    t_LPAREN  = r'\('
    t_RPAREN  = r'\)'
    
    # A regular expression rule with some action code
    def t_NUMBER(t):
        r'\d+'
        t.value = int(t.value)    
        return t
    
    # Define a rule so we can track line numbers
    def t_newline(t):
        r'\n+'
        t.lexer.lineno += len(t.value)
    
    # A string containing ignored characters (spaces and tabs)
    t_ignore  = ' \t'
    
    # Error handling rule
    def t_error(t):
        print "Illegal character '%s'" % t.value[0]
        t.lexer.skip(1)
    
    Now, if you wanted to build a tokenizer from these rules from within a different module, you would do the following (shown for Python interactive mode):
    >>> import tokrules
    >>> lexer = lex.lex(module=tokrules)
    >>> lexer.input("3 + 4")
    >>> lexer.token()
    LexToken(NUMBER,3,1,1,0)
    >>> lexer.token()
    LexToken(PLUS,'+',1,2)
    >>> lexer.token()
    LexToken(NUMBER,4,1,4)
    >>> lexer.token()
    None
    >>>
    
    The module option can also be used to define lexers from instances of a class. For example:
    import ply.lex as lex
    
    class MyLexer:
        # List of token names.   This is always required
        tokens = (
           'NUMBER',
           'PLUS',
           'MINUS',
           'TIMES',
           'DIVIDE',
           'LPAREN',
           'RPAREN',
        )
    
        # Regular expression rules for simple tokens
        t_PLUS    = r'\+'
        t_MINUS   = r'-'
        t_TIMES   = r'\*'
        t_DIVIDE  = r'/'
        t_LPAREN  = r'\('
        t_RPAREN  = r'\)'
    
        # A regular expression rule with some action code
        # Note addition of self parameter since we're in a class
        def t_NUMBER(self,t):
            r'\d+'
            t.value = int(t.value)    
            return t
    
        # Define a rule so we can track line numbers
        def t_newline(self,t):
            r'\n+'
            t.lexer.lineno += len(t.value)
    
        # A string containing ignored characters (spaces and tabs)
        t_ignore  = ' \t'
    
        # Error handling rule
        def t_error(self,t):
            print "Illegal character '%s'" % t.value[0]
            t.lexer.skip(1)
    
        # Build the lexer
        def build(self,**kwargs):
            self.lexer = lex.lex(module=self, **kwargs)
        
        # Test it output
        def test(self,data):
            self.lexer.input(data)
            while True:
                 tok = lexer.token()
                 if not tok: break
                 print tok
    
    # Build the lexer and try it out
    m = MyLexer()
    m.build()           # Build the lexer
    m.test("3 + 4")     # Test it
    
    When building a lexer from class, you should construct the lexer from an instance of the class, not the class object itself. This is because PLY only works properly if the lexer actions are defined by bound-methods.

    When using the module option to lex(), PLY collects symbols from the underlying object using the dir() function. There is no direct access to the __dict__ attribute of the object supplied as a module value.

    Finally, if you want to keep things nicely encapsulated, but don't want to use a full-fledged class definition, lexers can be defined using closures. For example:

    import ply.lex as lex
    
    # List of token names.   This is always required
    tokens = (
      'NUMBER',
      'PLUS',
      'MINUS',
      'TIMES',
      'DIVIDE',
      'LPAREN',
      'RPAREN',
    )
    
    def MyLexer():
        # Regular expression rules for simple tokens
        t_PLUS    = r'\+'
        t_MINUS   = r'-'
        t_TIMES   = r'\*'
        t_DIVIDE  = r'/'
        t_LPAREN  = r'\('
        t_RPAREN  = r'\)'
    
        # A regular expression rule with some action code
        def t_NUMBER(t):
            r'\d+'
            t.value = int(t.value)    
            return t
    
        # Define a rule so we can track line numbers
        def t_newline(t):
            r'\n+'
            t.lexer.lineno += len(t.value)
    
        # A string containing ignored characters (spaces and tabs)
        t_ignore  = ' \t'
    
        # Error handling rule
        def t_error(t):
            print "Illegal character '%s'" % t.value[0]
            t.lexer.skip(1)
    
        # Build the lexer from my environment and return it    
        return lex.lex()
    

    4.15 Maintaining state

    In your lexer, you may want to maintain a variety of state information. This might include mode settings, symbol tables, and other details. As an example, suppose that you wanted to keep track of how many NUMBER tokens had been encountered.

    One way to do this is to keep a set of global variables in the module where you created the lexer. For example:

    num_count = 0
    def t_NUMBER(t):
        r'\d+'
        global num_count
        num_count += 1
        t.value = int(t.value)    
        return t
    
    If you don't like the use of a global variable, another place to store information is inside the Lexer object created by lex(). To this, you can use the lexer attribute of tokens passed to the various rules. For example:
    def t_NUMBER(t):
        r'\d+'
        t.lexer.num_count += 1     # Note use of lexer attribute
        t.value = int(t.value)    
        return t
    
    lexer = lex.lex()
    lexer.num_count = 0            # Set the initial count
    
    This latter approach has the advantage of being simple and working correctly in applications where multiple instantiations of a given lexer exist in the same application. However, this might also feel like a gross violation of encapsulation to OO purists. Just to put your mind at some ease, all internal attributes of the lexer (with the exception of lineno) have names that are prefixed by lex (e.g., lexdata,lexpos, etc.). Thus, it is perfectly safe to store attributes in the lexer that don't have names starting with that prefix or a name that conlicts with one of the predefined methods (e.g., input(), token(), etc.).

    If you don't like assigning values on the lexer object, you can define your lexer as a class as shown in the previous section:

    class MyLexer:
        ...
        def t_NUMBER(self,t):
            r'\d+'
            self.num_count += 1
            t.value = int(t.value)    
            return t
    
        def build(self, **kwargs):
            self.lexer = lex.lex(object=self,**kwargs)
    
        def __init__(self):
            self.num_count = 0
    
    The class approach may be the easiest to manage if your application is going to be creating multiple instances of the same lexer and you need to manage a lot of state.

    State can also be managed through closures. For example, in Python 3:

    def MyLexer():
        num_count = 0
        ...
        def t_NUMBER(t):
            r'\d+'
            nonlocal num_count
            num_count += 1
            t.value = int(t.value)    
            return t
        ...
    

    4.16 Lexer cloning

    If necessary, a lexer object can be duplicated by invoking its clone() method. For example:

    lexer = lex.lex()
    ...
    newlexer = lexer.clone()
    
    When a lexer is cloned, the copy is exactly identical to the original lexer including any input text and internal state. However, the clone allows a different set of input text to be supplied which may be processed separately. This may be useful in situations when you are writing a parser/compiler that involves recursive or reentrant processing. For instance, if you needed to scan ahead in the input for some reason, you could create a clone and use it to look ahead. Or, if you were implementing some kind of preprocessor, cloned lexers could be used to handle different input files.

    Creating a clone is different than calling lex.lex() in that PLY doesn't regenerate any of the internal tables or regular expressions. So,

    Special considerations need to be made when cloning lexers that also maintain their own internal state using classes or closures. Namely, you need to be aware that the newly created lexers will share all of this state with the original lexer. For example, if you defined a lexer as a class and did this:

    m = MyLexer()
    a = lex.lex(object=m)      # Create a lexer
    
    b = a.clone()              # Clone the lexer
    
    Then both a and b are going to be bound to the same object m and any changes to m will be reflected in both lexers. It's important to emphasize that clone() is only meant to create a new lexer that reuses the regular expressions and environment of another lexer. If you need to make a totally new copy of a lexer, then call lex() again.

    4.17 Internal lexer state

    A Lexer object lexer has a number of internal attributes that may be useful in certain situations.

    lexer.lexpos

    This attribute is an integer that contains the current position within the input text. If you modify the value, it will change the result of the next call to token(). Within token rule functions, this points to the first character after the matched text. If the value is modified within a rule, the next returned token will be matched at the new position.

    lexer.lineno

    The current value of the line number attribute stored in the lexer. PLY only specifies that the attribute exists---it never sets, updates, or performs any processing with it. If you want to track line numbers, you will need to add code yourself (see the section on line numbers and positional information).

    lexer.lexdata

    The current input text stored in the lexer. This is the string passed with the input() method. It would probably be a bad idea to modify this unless you really know what you're doing.

    lexer.lexmatch

    This is the raw Match object returned by the Python re.match() function (used internally by PLY) for the current token. If you have written a regular expression that contains named groups, you can use this to retrieve those values. Note: This attribute is only updated when tokens are defined and processed by functions.

    4.18 Conditional lexing and start conditions

    In advanced parsing applications, it may be useful to have different lexing states. For instance, you may want the occurrence of a certain token or syntactic construct to trigger a different kind of lexing. PLY supports a feature that allows the underlying lexer to be put into a series of different states. Each state can have its own tokens, lexing rules, and so forth. The implementation is based largely on the "start condition" feature of GNU flex. Details of this can be found at http://www.gnu.org/software/flex/manual/html_chapter/flex_11.html..

    To define a new lexing state, it must first be declared. This is done by including a "states" declaration in your lex file. For example:

    states = (
       ('foo','exclusive'),
       ('bar','inclusive'),
    )
    
    This declaration declares two states, 'foo' and 'bar'. States may be of two types; 'exclusive' and 'inclusive'. An exclusive state completely overrides the default behavior of the lexer. That is, lex will only return tokens and apply rules defined specifically for that state. An inclusive state adds additional tokens and rules to the default set of rules. Thus, lex will return both the tokens defined by default in addition to those defined for the inclusive state.

    Once a state has been declared, tokens and rules are declared by including the state name in token/rule declaration. For example:

    t_foo_NUMBER = r'\d+'                      # Token 'NUMBER' in state 'foo'        
    t_bar_ID     = r'[a-zA-Z_][a-zA-Z0-9_]*'   # Token 'ID' in state 'bar'
    
    def t_foo_newline(t):
        r'\n'
        t.lexer.lineno += 1
    
    A token can be declared in multiple states by including multiple state names in the declaration. For example:
    t_foo_bar_NUMBER = r'\d+'         # Defines token 'NUMBER' in both state 'foo' and 'bar'
    
    Alternative, a token can be declared in all states using the 'ANY' in the name.
    t_ANY_NUMBER = r'\d+'         # Defines a token 'NUMBER' in all states
    
    If no state name is supplied, as is normally the case, the token is associated with a special state 'INITIAL'. For example, these two declarations are identical:
    t_NUMBER = r'\d+'
    t_INITIAL_NUMBER = r'\d+'
    

    States are also associated with the special t_ignore and t_error() declarations. For example, if a state treats these differently, you can declare:

    t_foo_ignore = " \t\n"       # Ignored characters for state 'foo'
    
    def t_bar_error(t):          # Special error handler for state 'bar'
        pass 
    
    By default, lexing operates in the 'INITIAL' state. This state includes all of the normally defined tokens. For users who aren't using different states, this fact is completely transparent. If, during lexing or parsing, you want to change the lexing state, use the begin() method. For example:
    def t_begin_foo(t):
        r'start_foo'
        t.lexer.begin('foo')             # Starts 'foo' state
    
    To get out of a state, you use begin() to switch back to the initial state. For example:
    def t_foo_end(t):
        r'end_foo'
        t.lexer.begin('INITIAL')        # Back to the initial state
    
    The management of states can also be done with a stack. For example:
    def t_begin_foo(t):
        r'start_foo'
        t.lexer.push_state('foo')             # Starts 'foo' state
    
    def t_foo_end(t):
        r'end_foo'
        t.lexer.pop_state()                   # Back to the previous state
    

    The use of a stack would be useful in situations where there are many ways of entering a new lexing state and you merely want to go back to the previous state afterwards.

    An example might help clarify. Suppose you were writing a parser and you wanted to grab sections of arbitrary C code enclosed by curly braces. That is, whenever you encounter a starting brace '{', you want to read all of the enclosed code up to the ending brace '}' and return it as a string. Doing this with a normal regular expression rule is nearly (if not actually) impossible. This is because braces can be nested and can be included in comments and strings. Thus, simply matching up to the first matching '}' character isn't good enough. Here is how you might use lexer states to do this:

    # Declare the state
    states = (
      ('ccode','exclusive'),
    )
    
    # Match the first {. Enter ccode state.
    def t_ccode(t):
        r'\{'
        t.lexer.code_start = t.lexer.lexpos        # Record the starting position
        t.lexer.level = 1                          # Initial brace level
        t.lexer.begin('ccode')                     # Enter 'ccode' state
    
    # Rules for the ccode state
    def t_ccode_lbrace(t):     
        r'\{'
        t.lexer.level +=1                
    
    def t_ccode_rbrace(t):
        r'\}'
        t.lexer.level -=1
    
        # If closing brace, return the code fragment
        if t.lexer.level == 0:
             t.value = t.lexer.lexdata[t.lexer.code_start:t.lexer.lexpos+1]
             t.type = "CCODE"
             t.lexer.lineno += t.value.count('\n')
             t.lexer.begin('INITIAL')           
             return t
    
    # C or C++ comment (ignore)    
    def t_ccode_comment(t):
        r'(/\*(.|\n)*?*/)|(//.*)'
        pass
    
    # C string
    def t_ccode_string(t):
       r'\"([^\\\n]|(\\.))*?\"'
    
    # C character literal
    def t_ccode_char(t):
       r'\'([^\\\n]|(\\.))*?\''
    
    # Any sequence of non-whitespace characters (not braces, strings)
    def t_ccode_nonspace(t):
       r'[^\s\{\}\'\"]+'
    
    # Ignored characters (whitespace)
    t_ccode_ignore = " \t\n"
    
    # For bad characters, we just skip over it
    def t_ccode_error(t):
        t.lexer.skip(1)
    
    In this example, the occurrence of the first '{' causes the lexer to record the starting position and enter a new state 'ccode'. A collection of rules then match various parts of the input that follow (comments, strings, etc.). All of these rules merely discard the token (by not returning a value). However, if the closing right brace is encountered, the rule t_ccode_rbrace collects all of the code (using the earlier recorded starting position), stores it, and returns a token 'CCODE' containing all of that text. When returning the token, the lexing state is restored back to its initial state.

    4.19 Miscellaneous Issues

  • The lexer requires input to be supplied as a single input string. Since most machines have more than enough memory, this rarely presents a performance concern. However, it means that the lexer currently can't be used with streaming data such as open files or sockets. This limitation is primarily a side-effect of using the re module.

  • The lexer should work properly with both Unicode strings given as token and pattern matching rules as well as for input text.

  • If you need to supply optional flags to the re.compile() function, use the reflags option to lex. For example:
    lex.lex(reflags=re.UNICODE)
    

  • Since the lexer is written entirely in Python, its performance is largely determined by that of the Python re module. Although the lexer has been written to be as efficient as possible, it's not blazingly fast when used on very large input files. If performance is concern, you might consider upgrading to the most recent version of Python, creating a hand-written lexer, or offloading the lexer into a C extension module.

    If you are going to create a hand-written lexer and you plan to use it with yacc.py, it only needs to conform to the following requirements:

    • It must provide a token() method that returns the next token or None if no more tokens are available.
    • The token() method must return an object tok that has type and value attributes.

    5. Parsing basics

    yacc.py is used to parse language syntax. Before showing an example, there are a few important bits of background that must be mentioned. First, syntax is usually specified in terms of a BNF grammar. For example, if you wanted to parse simple arithmetic expressions, you might first write an unambiguous grammar specification like this:
     
    expression : expression + term
               | expression - term
               | term
    
    term       : term * factor
               | term / factor
               | factor
    
    factor     : NUMBER
               | ( expression )
    
    In the grammar, symbols such as NUMBER, +, -, *, and / are known as terminals and correspond to raw input tokens. Identifiers such as term and factor refer to grammar rules comprised of a collection of terminals and other rules. These identifiers are known as non-terminals.

    The semantic behavior of a language is often specified using a technique known as syntax directed translation. In syntax directed translation, attributes are attached to each symbol in a given grammar rule along with an action. Whenever a particular grammar rule is recognized, the action describes what to do. For example, given the expression grammar above, you might write the specification for a simple calculator like this:

     
    Grammar                             Action
    --------------------------------    -------------------------------------------- 
    expression0 : expression1 + term    expression0.val = expression1.val + term.val
                | expression1 - term    expression0.val = expression1.val - term.val
                | term                  expression0.val = term.val
    
    term0       : term1 * factor        term0.val = term1.val * factor.val
                | term1 / factor        term0.val = term1.val / factor.val
                | factor                term0.val = factor.val
    
    factor      : NUMBER                factor.val = int(NUMBER.lexval)
                | ( expression )        factor.val = expression.val
    
    A good way to think about syntax directed translation is to view each symbol in the grammar as a kind of object. Associated with each symbol is a value representing its "state" (for example, the val attribute above). Semantic actions are then expressed as a collection of functions or methods that operate on the symbols and associated values.

    Yacc uses a parsing technique known as LR-parsing or shift-reduce parsing. LR parsing is a bottom up technique that tries to recognize the right-hand-side of various grammar rules. Whenever a valid right-hand-side is found in the input, the appropriate action code is triggered and the grammar symbols are replaced by the grammar symbol on the left-hand-side.

    LR parsing is commonly implemented by shifting grammar symbols onto a stack and looking at the stack and the next input token for patterns that match one of the grammar rules. The details of the algorithm can be found in a compiler textbook, but the following example illustrates the steps that are performed if you wanted to parse the expression 3 + 5 * (10 - 20) using the grammar defined above. In the example, the special symbol $ represents the end of input.

    Step Symbol Stack           Input Tokens            Action
    ---- ---------------------  ---------------------   -------------------------------
    1                           3 + 5 * ( 10 - 20 )$    Shift 3
    2    3                        + 5 * ( 10 - 20 )$    Reduce factor : NUMBER
    3    factor                   + 5 * ( 10 - 20 )$    Reduce term   : factor
    4    term                     + 5 * ( 10 - 20 )$    Reduce expr : term
    5    expr                     + 5 * ( 10 - 20 )$    Shift +
    6    expr +                     5 * ( 10 - 20 )$    Shift 5
    7    expr + 5                     * ( 10 - 20 )$    Reduce factor : NUMBER
    8    expr + factor                * ( 10 - 20 )$    Reduce term   : factor
    9    expr + term                  * ( 10 - 20 )$    Shift *
    10   expr + term *                  ( 10 - 20 )$    Shift (
    11   expr + term * (                  10 - 20 )$    Shift 10
    12   expr + term * ( 10                  - 20 )$    Reduce factor : NUMBER
    13   expr + term * ( factor              - 20 )$    Reduce term : factor
    14   expr + term * ( term                - 20 )$    Reduce expr : term
    15   expr + term * ( expr                - 20 )$    Shift -
    16   expr + term * ( expr -                20 )$    Shift 20
    17   expr + term * ( expr - 20                )$    Reduce factor : NUMBER
    18   expr + term * ( expr - factor            )$    Reduce term : factor
    19   expr + term * ( expr - term              )$    Reduce expr : expr - term
    20   expr + term * ( expr                     )$    Shift )
    21   expr + term * ( expr )                    $    Reduce factor : (expr)
    22   expr + term * factor                      $    Reduce term : term * factor
    23   expr + term                               $    Reduce expr : expr + term
    24   expr                                      $    Reduce expr
    25                                             $    Success!
    
    When parsing the expression, an underlying state machine and the current input token determine what happens next. If the next token looks like part of a valid grammar rule (based on other items on the stack), it is generally shifted onto the stack. If the top of the stack contains a valid right-hand-side of a grammar rule, it is usually "reduced" and the symbols replaced with the symbol on the left-hand-side. When this reduction occurs, the appropriate action is triggered (if defined). If the input token can't be shifted and the top of stack doesn't match any grammar rules, a syntax error has occurred and the parser must take some kind of recovery step (or bail out). A parse is only successful if the parser reaches a state where the symbol stack is empty and there are no more input tokens.

    It is important to note that the underlying implementation is built around a large finite-state machine that is encoded in a collection of tables. The construction of these tables is non-trivial and beyond the scope of this discussion. However, subtle details of this process explain why, in the example above, the parser chooses to shift a token onto the stack in step 9 rather than reducing the rule expr : expr + term.

    6. Yacc

    The ply.yacc module implements the parsing component of PLY. The name "yacc" stands for "Yet Another Compiler Compiler" and is borrowed from the Unix tool of the same name.

    6.1 An example

    Suppose you wanted to make a grammar for simple arithmetic expressions as previously described. Here is how you would do it with yacc.py:
    # Yacc example
    
    import ply.yacc as yacc
    
    # Get the token map from the lexer.  This is required.
    from calclex import tokens
    
    def p_expression_plus(p):
        'expression : expression PLUS term'
        p[0] = p[1] + p[3]
    
    def p_expression_minus(p):
        'expression : expression MINUS term'
        p[0] = p[1] - p[3]
    
    def p_expression_term(p):
        'expression : term'
        p[0] = p[1]
    
    def p_term_times(p):
        'term : term TIMES factor'
        p[0] = p[1] * p[3]
    
    def p_term_div(p):
        'term : term DIVIDE factor'
        p[0] = p[1] / p[3]
    
    def p_term_factor(p):
        'term : factor'
        p[0] = p[1]
    
    def p_factor_num(p):
        'factor : NUMBER'
        p[0] = p[1]
    
    def p_factor_expr(p):
        'factor : LPAREN expression RPAREN'
        p[0] = p[2]
    
    # Error rule for syntax errors
    def p_error(p):
        print "Syntax error in input!"
    
    # Build the parser
    parser = yacc.yacc()
    
    while True:
       try:
           s = raw_input('calc > ')
       except EOFError:
           break
       if not s: continue
       result = parser.parse(s)
       print result
    
    In this example, each grammar rule is defined by a Python function where the docstring to that function contains the appropriate context-free grammar specification. The statements that make up the function body implement the semantic actions of the rule. Each function accepts a single argument p that is a sequence containing the values of each grammar symbol in the corresponding rule. The values of p[i] are mapped to grammar symbols as shown here:
    def p_expression_plus(p):
        'expression : expression PLUS term'
        #   ^            ^        ^    ^
        #  p[0]         p[1]     p[2] p[3]
    
        p[0] = p[1] + p[3]
    

    For tokens, the "value" of the corresponding p[i] is the same as the p.value attribute assigned in the lexer module. For non-terminals, the value is determined by whatever is placed in p[0] when rules are reduced. This value can be anything at all. However, it probably most common for the value to be a simple Python type, a tuple, or an instance. In this example, we are relying on the fact that the NUMBER token stores an integer value in its value field. All of the other rules simply perform various types of integer operations and propagate the result.

    Note: The use of negative indices have a special meaning in yacc---specially p[-1] does not have the same value as p[3] in this example. Please see the section on "Embedded Actions" for further details.

    The first rule defined in the yacc specification determines the starting grammar symbol (in this case, a rule for expression appears first). Whenever the starting rule is reduced by the parser and no more input is available, parsing stops and the final value is returned (this value will be whatever the top-most rule placed in p[0]). Note: an alternative starting symbol can be specified using the start keyword argument to yacc().

    The p_error(p) rule is defined to catch syntax errors. See the error handling section below for more detail.

    To build the parser, call the yacc.yacc() function. This function looks at the module and attempts to construct all of the LR parsing tables for the grammar you have specified. The first time yacc.yacc() is invoked, you will get a message such as this:

    $ python calcparse.py
    Generating LALR tables
    calc > 
    
    Since table construction is relatively expensive (especially for large grammars), the resulting parsing table is written to the current directory in a file called parsetab.py. In addition, a debugging file called parser.out is created. On subsequent executions, yacc will reload the table from parsetab.py unless it has detected a change in the underlying grammar (in which case the tables and parsetab.py file are regenerated). Note: The names of parser output files can be changed if necessary. See the PLY Reference for details.

    If any errors are detected in your grammar specification, yacc.py will produce diagnostic messages and possibly raise an exception. Some of the errors that can be detected include:

    • Duplicated function names (if more than one rule function have the same name in the grammar file).
    • Shift/reduce and reduce/reduce conflicts generated by ambiguous grammars.
    • Badly specified grammar rules.
    • Infinite recursion (rules that can never terminate).
    • Unused rules and tokens
    • Undefined rules and tokens
    The next few sections discuss grammar specification in more detail.

    The final part of the example shows how to actually run the parser created by yacc(). To run the parser, you simply have to call the parse() with a string of input text. This will run all of the grammar rules and return the result of the entire parse. This result return is the value assigned to p[0] in the starting grammar rule.

    6.2 Combining Grammar Rule Functions

    When grammar rules are similar, they can be combined into a single function. For example, consider the two rules in our earlier example:
    def p_expression_plus(p):
        'expression : expression PLUS term'
        p[0] = p[1] + p[3]
    
    def p_expression_minus(t):
        'expression : expression MINUS term'
        p[0] = p[1] - p[3]
    
    Instead of writing two functions, you might write a single function like this:
    def p_expression(p):
        '''expression : expression PLUS term
                      | expression MINUS term'''
        if p[2] == '+':
            p[0] = p[1] + p[3]
        elif p[2] == '-':
            p[0] = p[1] - p[3]
    
    In general, the doc string for any given function can contain multiple grammar rules. So, it would have also been legal (although possibly confusing) to write this:
    def p_binary_operators(p):
        '''expression : expression PLUS term
                      | expression MINUS term
           term       : term TIMES factor
                      | term DIVIDE factor'''
        if p[2] == '+':
            p[0] = p[1] + p[3]
        elif p[2] == '-':
            p[0] = p[1] - p[3]
        elif p[2] == '*':
            p[0] = p[1] * p[3]
        elif p[2] == '/':
            p[0] = p[1] / p[3]
    
    When combining grammar rules into a single function, it is usually a good idea for all of the rules to have a similar structure (e.g., the same number of terms). Otherwise, the corresponding action code may be more complicated than necessary. However, it is possible to handle simple cases using len(). For example:
    def p_expressions(p):
        '''expression : expression MINUS expression
                      | MINUS expression'''
        if (len(p) == 4):
            p[0] = p[1] - p[3]
        elif (len(p) == 3):
            p[0] = -p[2]
    
    If parsing performance is a concern, you should resist the urge to put too much conditional processing into a single grammar rule as shown in these examples. When you add checks to see which grammar rule is being handled, you are actually duplicating the work that the parser has already performed (i.e., the parser already knows exactly what rule it matched). You can eliminate this overhead by using a separate p_rule() function for each grammar rule.

    6.3 Character Literals

    If desired, a grammar may contain tokens defined as single character literals. For example:
    def p_binary_operators(p):
        '''expression : expression '+' term
                      | expression '-' term
           term       : term '*' factor
                      | term '/' factor'''
        if p[2] == '+':
            p[0] = p[1] + p[3]
        elif p[2] == '-':
            p[0] = p[1] - p[3]
        elif p[2] == '*':
            p[0] = p[1] * p[3]
        elif p[2] == '/':
            p[0] = p[1] / p[3]
    
    A character literal must be enclosed in quotes such as '+'. In addition, if literals are used, they must be declared in the corresponding lex file through the use of a special literals declaration.
    # Literals.  Should be placed in module given to lex()
    literals = ['+','-','*','/' ]
    
    Character literals are limited to a single character. Thus, it is not legal to specify literals such as '<=' or '=='. For this, use the normal lexing rules (e.g., define a rule such as t_EQ = r'==').

    6.4 Empty Productions

    yacc.py can handle empty productions by defining a rule like this:
    def p_empty(p):
        'empty :'
        pass
    
    Now to use the empty production, simply use 'empty' as a symbol. For example:
    def p_optitem(p):
        'optitem : item'
        '        | empty'
        ...
    
    Note: You can write empty rules anywhere by simply specifying an empty right hand side. However, I personally find that writing an "empty" rule and using "empty" to denote an empty production is easier to read and more clearly states your intentions.

    6.5 Changing the starting symbol

    Normally, the first rule found in a yacc specification defines the starting grammar rule (top level rule). To change this, simply supply a start specifier in your file. For example:
    start = 'foo'
    
    def p_bar(p):
        'bar : A B'
    
    # This is the starting rule due to the start specifier above
    def p_foo(p):
        'foo : bar X'
    ...
    
    The use of a start specifier may be useful during debugging since you can use it to have yacc build a subset of a larger grammar. For this purpose, it is also possible to specify a starting symbol as an argument to yacc(). For example:
    yacc.yacc(start='foo')
    

    6.6 Dealing With Ambiguous Grammars

    The expression grammar given in the earlier example has been written in a special format to eliminate ambiguity. However, in many situations, it is extremely difficult or awkward to write grammars in this format. A much more natural way to express the grammar is in a more compact form like this:
    expression : expression PLUS expression
               | expression MINUS expression
               | expression TIMES expression
               | expression DIVIDE expression
               | LPAREN expression RPAREN
               | NUMBER
    
    Unfortunately, this grammar specification is ambiguous. For example, if you are parsing the string "3 * 4 + 5", there is no way to tell how the operators are supposed to be grouped. For example, does the expression mean "(3 * 4) + 5" or is it "3 * (4+5)"?

    When an ambiguous grammar is given to yacc.py it will print messages about "shift/reduce conflicts" or "reduce/reduce conflicts". A shift/reduce conflict is caused when the parser generator can't decide whether or not to reduce a rule or shift a symbol on the parsing stack. For example, consider the string "3 * 4 + 5" and the internal parsing stack:

    Step Symbol Stack           Input Tokens            Action
    ---- ---------------------  ---------------------   -------------------------------
    1    $                                3 * 4 + 5$    Shift 3
    2    $ 3                                * 4 + 5$    Reduce : expression : NUMBER
    3    $ expr                             * 4 + 5$    Shift *
    4    $ expr *                             4 + 5$    Shift 4
    5    $ expr * 4                             + 5$    Reduce: expression : NUMBER
    6    $ expr * expr                          + 5$    SHIFT/REDUCE CONFLICT ????
    
    In this case, when the parser reaches step 6, it has two options. One is to reduce the rule expr : expr * expr on the stack. The other option is to shift the token + on the stack. Both options are perfectly legal from the rules of the context-free-grammar.

    By default, all shift/reduce conflicts are resolved in favor of shifting. Therefore, in the above example, the parser will always shift the + instead of reducing. Although this strategy works in many cases (for example, the case of "if-then" versus "if-then-else"), it is not enough for arithmetic expressions. In fact, in the above example, the decision to shift + is completely wrong---we should have reduced expr * expr since multiplication has higher mathematical precedence than addition.

    To resolve ambiguity, especially in expression grammars, yacc.py allows individual tokens to be assigned a precedence level and associativity. This is done by adding a variable precedence to the grammar file like this:

    precedence = (
        ('left', 'PLUS', 'MINUS'),
        ('left', 'TIMES', 'DIVIDE'),
    )
    
    This declaration specifies that PLUS/MINUS have the same precedence level and are left-associative and that TIMES/DIVIDE have the same precedence and are left-associative. Within the precedence declaration, tokens are ordered from lowest to highest precedence. Thus, this declaration specifies that TIMES/DIVIDE have higher precedence than PLUS/MINUS (since they appear later in the precedence specification).

    The precedence specification works by associating a numerical precedence level value and associativity direction to the listed tokens. For example, in the above example you get:

    PLUS      : level = 1,  assoc = 'left'
    MINUS     : level = 1,  assoc = 'left'
    TIMES     : level = 2,  assoc = 'left'
    DIVIDE    : level = 2,  assoc = 'left'
    
    These values are then used to attach a numerical precedence value and associativity direction to each grammar rule. This is always determined by looking at the precedence of the right-most terminal symbol. For example:
    expression : expression PLUS expression                 # level = 1, left
               | expression MINUS expression                # level = 1, left
               | expression TIMES expression                # level = 2, left
               | expression DIVIDE expression               # level = 2, left
               | LPAREN expression RPAREN                   # level = None (not specified)
               | NUMBER                                     # level = None (not specified)
    
    When shift/reduce conflicts are encountered, the parser generator resolves the conflict by looking at the precedence rules and associativity specifiers.

    1. If the current token has higher precedence than the rule on the stack, it is shifted.
    2. If the grammar rule on the stack has higher precedence, the rule is reduced.
    3. If the current token and the grammar rule have the same precedence, the rule is reduced for left associativity, whereas the token is shifted for right associativity.
    4. If nothing is known about the precedence, shift/reduce conflicts are resolved in favor of shifting (the default).
    For example, if "expression PLUS expression" has been parsed and the next token is "TIMES", the action is going to be a shift because "TIMES" has a higher precedence level than "PLUS". On the other hand, if "expression TIMES expression" has been parsed and the next token is "PLUS", the action is going to be reduce because "PLUS" has a lower precedence than "TIMES."

    When shift/reduce conflicts are resolved using the first three techniques (with the help of precedence rules), yacc.py will report no errors or conflicts in the grammar (although it will print some information in the parser.out debugging file).

    One problem with the precedence specifier technique is that it is sometimes necessary to change the precedence of an operator in certain contexts. For example, consider a unary-minus operator in "3 + 4 * -5". Mathematically, the unary minus is normally given a very high precedence--being evaluated before the multiply. However, in our precedence specifier, MINUS has a lower precedence than TIMES. To deal with this, precedence rules can be given for so-called "fictitious tokens" like this:

    precedence = (
        ('left', 'PLUS', 'MINUS'),
        ('left', 'TIMES', 'DIVIDE'),
        ('right', 'UMINUS'),            # Unary minus operator
    )
    
    Now, in the grammar file, we can write our unary minus rule like this:
    def p_expr_uminus(p):
        'expression : MINUS expression %prec UMINUS'
        p[0] = -p[2]
    
    In this case, %prec UMINUS overrides the default rule precedence--setting it to that of UMINUS in the precedence specifier.

    At first, the use of UMINUS in this example may appear very confusing. UMINUS is not an input token or a grammer rule. Instead, you should think of it as the name of a special marker in the precedence table. When you use the %prec qualifier, you're simply telling yacc that you want the precedence of the expression to be the same as for this special marker instead of the usual precedence.

    It is also possible to specify non-associativity in the precedence table. This would be used when you don't want operations to chain together. For example, suppose you wanted to support comparison operators like < and > but you didn't want to allow combinations like a < b < c. To do this, simply specify a rule like this:

    precedence = (
        ('nonassoc', 'LESSTHAN', 'GREATERTHAN'),  # Nonassociative operators
        ('left', 'PLUS', 'MINUS'),
        ('left', 'TIMES', 'DIVIDE'),
        ('right', 'UMINUS'),            # Unary minus operator
    )
    

    If you do this, the occurrence of input text such as a < b < c will result in a syntax error. However, simple expressions such as a < b will still be fine.

    Reduce/reduce conflicts are caused when there are multiple grammar rules that can be applied to a given set of symbols. This kind of conflict is almost always bad and is always resolved by picking the rule that appears first in the grammar file. Reduce/reduce conflicts are almost always caused when different sets of grammar rules somehow generate the same set of symbols. For example:

    assignment :  ID EQUALS NUMBER
               |  ID EQUALS expression
               
    expression : expression PLUS expression
               | expression MINUS expression
               | expression TIMES expression
               | expression DIVIDE expression
               | LPAREN expression RPAREN
               | NUMBER
    
    In this case, a reduce/reduce conflict exists between these two rules:
    assignment  : ID EQUALS NUMBER
    expression  : NUMBER
    
    For example, if you wrote "a = 5", the parser can't figure out if this is supposed to be reduced as assignment : ID EQUALS NUMBER or whether it's supposed to reduce the 5 as an expression and then reduce the rule assignment : ID EQUALS expression.

    It should be noted that reduce/reduce conflicts are notoriously difficult to spot simply looking at the input grammer. When a reduce/reduce conflict occurs, yacc() will try to help by printing a warning message such as this:

    WARNING: 1 reduce/reduce conflict
    WARNING: reduce/reduce conflict in state 15 resolved using rule (assignment -> ID EQUALS NUMBER)
    WARNING: rejected rule (expression -> NUMBER)
    
    This message identifies the two rules that are in conflict. However, it may not tell you how the parser arrived at such a state. To try and figure it out, you'll probably have to look at your grammar and the contents of the parser.out debugging file with an appropriately high level of caffeination.

    6.7 The parser.out file

    Tracking down shift/reduce and reduce/reduce conflicts is one of the finer pleasures of using an LR parsing algorithm. To assist in debugging, yacc.py creates a debugging file called 'parser.out' when it generates the parsing table. The contents of this file look like the following:
    Unused terminals:
    
    
    Grammar
    
    Rule 1     expression -> expression PLUS expression
    Rule 2     expression -> expression MINUS expression
    Rule 3     expression -> expression TIMES expression
    Rule 4     expression -> expression DIVIDE expression
    Rule 5     expression -> NUMBER
    Rule 6     expression -> LPAREN expression RPAREN
    
    Terminals, with rules where they appear
    
    TIMES                : 3
    error                : 
    MINUS                : 2
    RPAREN               : 6
    LPAREN               : 6
    DIVIDE               : 4
    PLUS                 : 1
    NUMBER               : 5
    
    Nonterminals, with rules where they appear
    
    expression           : 1 1 2 2 3 3 4 4 6 0
    
    
    Parsing method: LALR
    
    
    state 0
    
        S' -> . expression
        expression -> . expression PLUS expression
        expression -> . expression MINUS expression
        expression -> . expression TIMES expression
        expression -> . expression DIVIDE expression
        expression -> . NUMBER
        expression -> . LPAREN expression RPAREN
    
        NUMBER          shift and go to state 3
        LPAREN          shift and go to state 2
    
    
    state 1
    
        S' -> expression .
        expression -> expression . PLUS expression
        expression -> expression . MINUS expression
        expression -> expression . TIMES expression
        expression -> expression . DIVIDE expression
    
        PLUS            shift and go to state 6
        MINUS           shift and go to state 5
        TIMES           shift and go to state 4
        DIVIDE          shift and go to state 7
    
    
    state 2
    
        expression -> LPAREN . expression RPAREN
        expression -> . expression PLUS expression
        expression -> . expression MINUS expression
        expression -> . expression TIMES expression
        expression -> . expression DIVIDE expression
        expression -> . NUMBER
        expression -> . LPAREN expression RPAREN
    
        NUMBER          shift and go to state 3
        LPAREN          shift and go to state 2
    
    
    state 3
    
        expression -> NUMBER .
    
        $               reduce using rule 5
        PLUS            reduce using rule 5
        MINUS           reduce using rule 5
        TIMES           reduce using rule 5
        DIVIDE          reduce using rule 5
        RPAREN          reduce using rule 5
    
    
    state 4
    
        expression -> expression TIMES . expression
        expression -> . expression PLUS expression
        expression -> . expression MINUS expression
        expression -> . expression TIMES expression
        expression -> . expression DIVIDE expression
        expression -> . NUMBER
        expression -> . LPAREN expression RPAREN
    
        NUMBER          shift and go to state 3
        LPAREN          shift and go to state 2
    
    
    state 5
    
        expression -> expression MINUS . expression
        expression -> . expression PLUS expression
        expression -> . expression MINUS expression
        expression -> . expression TIMES expression
        expression -> . expression DIVIDE expression
        expression -> . NUMBER
        expression -> . LPAREN expression RPAREN
    
        NUMBER          shift and go to state 3
        LPAREN          shift and go to state 2
    
    
    state 6
    
        expression -> expression PLUS . expression
        expression -> . expression PLUS expression
        expression -> . expression MINUS expression
        expression -> . expression TIMES expression
        expression -> . expression DIVIDE expression
        expression -> . NUMBER
        expression -> . LPAREN expression RPAREN
    
        NUMBER          shift and go to state 3
        LPAREN          shift and go to state 2
    
    
    state 7
    
        expression -> expression DIVIDE . expression
        expression -> . expression PLUS expression
        expression -> . expression MINUS expression
        expression -> . expression TIMES expression
        expression -> . expression DIVIDE expression
        expression -> . NUMBER
        expression -> . LPAREN expression RPAREN
    
        NUMBER          shift and go to state 3
        LPAREN          shift and go to state 2
    
    
    state 8
    
        expression -> LPAREN expression . RPAREN
        expression -> expression . PLUS expression
        expression -> expression . MINUS expression
        expression -> expression . TIMES expression
        expression -> expression . DIVIDE expression
    
        RPAREN          shift and go to state 13
        PLUS            shift and go to state 6
        MINUS           shift and go to state 5
        TIMES           shift and go to state 4
        DIVIDE          shift and go to state 7
    
    
    state 9
    
        expression -> expression TIMES expression .
        expression -> expression . PLUS expression
        expression -> expression . MINUS expression
        expression -> expression . TIMES expression
        expression -> expression . DIVIDE expression
    
        $               reduce using rule 3
        PLUS            reduce using rule 3
        MINUS           reduce using rule 3
        TIMES           reduce using rule 3
        DIVIDE          reduce using rule 3
        RPAREN          reduce using rule 3
    
      ! PLUS            [ shift and go to state 6 ]
      ! MINUS           [ shift and go to state 5 ]
      ! TIMES           [ shift and go to state 4 ]
      ! DIVIDE          [ shift and go to state 7 ]
    
    state 10
    
        expression -> expression MINUS expression .
        expression -> expression . PLUS expression
        expression -> expression . MINUS expression
        expression -> expression . TIMES expression
        expression -> expression . DIVIDE expression
    
        $               reduce using rule 2
        PLUS            reduce using rule 2
        MINUS           reduce using rule 2
        RPAREN          reduce using rule 2
        TIMES           shift and go to state 4
        DIVIDE          shift and go to state 7
    
      ! TIMES           [ reduce using rule 2 ]
      ! DIVIDE          [ reduce using rule 2 ]
      ! PLUS            [ shift and go to state 6 ]
      ! MINUS           [ shift and go to state 5 ]
    
    state 11
    
        expression -> expression PLUS expression .
        expression -> expression . PLUS expression
        expression -> expression . MINUS expression
        expression -> expression . TIMES expression
        expression -> expression . DIVIDE expression
    
        $               reduce using rule 1
        PLUS            reduce using rule 1
        MINUS           reduce using rule 1
        RPAREN          reduce using rule 1
        TIMES           shift and go to state 4
        DIVIDE          shift and go to state 7
    
      ! TIMES           [ reduce using rule 1 ]
      ! DIVIDE          [ reduce using rule 1 ]
      ! PLUS            [ shift and go to state 6 ]
      ! MINUS           [ shift and go to state 5 ]
    
    state 12
    
        expression -> expression DIVIDE expression .
        expression -> expression . PLUS expression
        expression -> expression . MINUS expression
        expression -> expression . TIMES expression
        expression -> expression . DIVIDE expression
    
        $               reduce using rule 4
        PLUS            reduce using rule 4
        MINUS           reduce using rule 4
        TIMES           reduce using rule 4
        DIVIDE          reduce using rule 4
        RPAREN          reduce using rule 4
    
      ! PLUS            [ shift and go to state 6 ]
      ! MINUS           [ shift and go to state 5 ]
      ! TIMES           [ shift and go to state 4 ]
      ! DIVIDE          [ shift and go to state 7 ]
    
    state 13
    
        expression -> LPAREN expression RPAREN .
    
        $               reduce using rule 6
        PLUS            reduce using rule 6
        MINUS           reduce using rule 6
        TIMES           reduce using rule 6
        DIVIDE          reduce using rule 6
        RPAREN          reduce using rule 6
    
    The different states that appear in this file are a representation of every possible sequence of valid input tokens allowed by the grammar. When receiving input tokens, the parser is building up a stack and looking for matching rules. Each state keeps track of the grammar rules that might be in the process of being matched at that point. Within each rule, the "." character indicates the current location of the parse within that rule. In addition, the actions for each valid input token are listed. When a shift/reduce or reduce/reduce conflict arises, rules not selected are prefixed with an !. For example:
      ! TIMES           [ reduce using rule 2 ]
      ! DIVIDE          [ reduce using rule 2 ]
      ! PLUS            [ shift and go to state 6 ]
      ! MINUS           [ shift and go to state 5 ]
    
    By looking at these rules (and with a little practice), you can usually track down the source of most parsing conflicts. It should also be stressed that not all shift-reduce conflicts are bad. However, the only way to be sure that they are resolved correctly is to look at parser.out.

    6.8 Syntax Error Handling

    If you are creating a parser for production use, the handling of syntax errors is important. As a general rule, you don't want a parser to simply throw up its hands and stop at the first sign of trouble. Instead, you want it to report the error, recover if possible, and continue parsing so that all of the errors in the input get reported to the user at once. This is the standard behavior found in compilers for languages such as C, C++, and Java. In PLY, when a syntax error occurs during parsing, the error is immediately detected (i.e., the parser does not read any more tokens beyond the source of the error). However, at this point, the parser enters a recovery mode that can be used to try and continue further parsing. As a general rule, error recovery in LR parsers is a delicate topic that involves ancient rituals and black-magic. The recovery mechanism provided by yacc.py is comparable to Unix yacc so you may want consult a book like O'Reilly's "Lex and Yacc" for some of the finer details.

    When a syntax error occurs, yacc.py performs the following steps:

    1. On the first occurrence of an error, the user-defined p_error() function is called with the offending token as an argument. However, if the syntax error is due to reaching the end-of-file, p_error() is called with an argument of None. Afterwards, the parser enters an "error-recovery" mode in which it will not make future calls to p_error() until it has successfully shifted at least 3 tokens onto the parsing stack.

    2. If no recovery action is taken in p_error(), the offending lookahead token is replaced with a special error token.

    3. If the offending lookahead token is already set to error, the top item of the parsing stack is deleted.

    4. If the entire parsing stack is unwound, the parser enters a restart state and attempts to start parsing from its initial state.

    5. If a grammar rule accepts error as a token, it will be shifted onto the parsing stack.

    6. If the top item of the parsing stack is error, lookahead tokens will be discarded until the parser can successfully shift a new symbol or reduce a rule involving error.

    6.8.1 Recovery and resynchronization with error rules

    The most well-behaved approach for handling syntax errors is to write grammar rules that include the error token. For example, suppose your language had a grammar rule for a print statement like this:
    def p_statement_print(p):
         'statement : PRINT expr SEMI'
         ...
    
    To account for the possibility of a bad expression, you might write an additional grammar rule like this:
    def p_statement_print_error(p):
         'statement : PRINT error SEMI'
         print "Syntax error in print statement. Bad expression"
    
    
    In this case, the error token will match any sequence of tokens that might appear up to the first semicolon that is encountered. Once the semicolon is reached, the rule will be invoked and the error token will go away.

    This type of recovery is sometimes known as parser resynchronization. The error token acts as a wildcard for any bad input text and the token immediately following error acts as a synchronization token.

    It is important to note that the error token usually does not appear as the last token on the right in an error rule. For example:

    def p_statement_print_error(p):
        'statement : PRINT error'
        print "Syntax error in print statement. Bad expression"
    
    This is because the first bad token encountered will cause the rule to be reduced--which may make it difficult to recover if more bad tokens immediately follow.

    6.8.2 Panic mode recovery

    An alternative error recovery scheme is to enter a panic mode recovery in which tokens are discarded to a point where the parser might be able to recover in some sensible manner.

    Panic mode recovery is implemented entirely in the p_error() function. For example, this function starts discarding tokens until it reaches a closing '}'. Then, it restarts the parser in its initial state.

    def p_error(p):
        print "Whoa. You are seriously hosed."
        # Read ahead looking for a closing '}'
        while 1:
            tok = yacc.token()             # Get the next token
            if not tok or tok.type == 'RBRACE': break
        yacc.restart()
    

    This function simply discards the bad token and tells the parser that the error was ok.

    def p_error(p):
        print "Syntax error at token", p.type
        # Just discard the token and tell the parser it's okay.
        yacc.errok()
    

    Within the p_error() function, three functions are available to control the behavior of the parser:

    • yacc.errok(). This resets the parser state so it doesn't think it's in error-recovery mode. This will prevent an error token from being generated and will reset the internal error counters so that the next syntax error will call p_error() again.

    • yacc.token(). This returns the next token on the input stream.

    • yacc.restart(). This discards the entire parsing stack and resets the parser to its initial state.
    Note: these functions are only available when invoking p_error() and are not available at any other time.

    To supply the next lookahead token to the parser, p_error() can return a token. This might be useful if trying to synchronize on special characters. For example:

    def p_error(p):
        # Read ahead looking for a terminating ";"
        while 1:
            tok = yacc.token()             # Get the next token
            if not tok or tok.type == 'SEMI': break
        yacc.errok()
    
        # Return SEMI to the parser as the next lookahead token
        return tok  
    

    6.8.3 Signaling an error from a production

    If necessary, a production rule can manually force the parser to enter error recovery. This is done by raising the SyntaxError exception like this:
    def p_production(p):
        'production : some production ...'
        raise SyntaxError
    
    The effect of raising SyntaxError is the same as if the last symbol shifted onto the parsing stack was actually a syntax error. Thus, when you do this, the last symbol shifted is popped off of the parsing stack and the current lookahead token is set to an error token. The parser then enters error-recovery mode where it tries to reduce rules that can accept error tokens. The steps that follow from this point are exactly the same as if a syntax error were detected and p_error() were called.

    One important aspect of manually setting an error is that the p_error() function will NOT be called in this case. If you need to issue an error message, make sure you do it in the production that raises SyntaxError.

    Note: This feature of PLY is meant to mimic the behavior of the YYERROR macro in yacc.

    6.8.4 General comments on error handling

    For normal types of languages, error recovery with error rules and resynchronization characters is probably the most reliable technique. This is because you can instrument the grammar to catch errors at selected places where it is relatively easy to recover and continue parsing. Panic mode recovery is really only useful in certain specialized applications where you might want to discard huge portions of the input text to find a valid restart point.

    6.9 Line Number and Position Tracking

    Position tracking is often a tricky problem when writing compilers. By default, PLY tracks the line number and position of all tokens. This information is available using the following functions:
    • p.lineno(num). Return the line number for symbol num
    • p.lexpos(num). Return the lexing position for symbol num
    For example:
    def p_expression(p):
        'expression : expression PLUS expression'
        line   = p.lineno(2)        # line number of the PLUS token
        index  = p.lexpos(2)        # Position of the PLUS token
    
    As an optional feature, yacc.py can automatically track line numbers and positions for all of the grammar symbols as well. However, this extra tracking requires extra processing and can significantly slow down parsing. Therefore, it must be enabled by passing the tracking=True option to yacc.parse(). For example:
    yacc.parse(data,tracking=True)
    
    Once enabled, the lineno() and lexpos() methods work for all grammar symbols. In addition, two additional methods can be used:
    • p.linespan(num). Return a tuple (startline,endline) with the starting and ending line number for symbol num.
    • p.lexspan(num). Return a tuple (start,end) with the starting and ending positions for symbol num.
    For example:
    def p_expression(p):
        'expression : expression PLUS expression'
        p.lineno(1)        # Line number of the left expression
        p.lineno(2)        # line number of the PLUS operator
        p.lineno(3)        # line number of the right expression
        ...
        start,end = p.linespan(3)    # Start,end lines of the right expression
        starti,endi = p.lexspan(3)   # Start,end positions of right expression
    
    
    Note: The lexspan() function only returns the range of values up to the start of the last grammar symbol.

    Although it may be convenient for PLY to track position information on all grammar symbols, this is often unnecessary. For example, if you are merely using line number information in an error message, you can often just key off of a specific token in the grammar rule. For example:

    def p_bad_func(p):
        'funccall : fname LPAREN error RPAREN'
        # Line number reported from LPAREN token
        print "Bad function call at line", p.lineno(2)
    

    Similarly, you may get better parsing performance if you only selectively propagate line number information where it's needed using the p.set_lineno() method. For example:

    def p_fname(p):
        'fname : ID'
        p[0] = p[1]
        p.set_lineno(0,p.lineno(1))
    
    PLY doesn't retain line number information from rules that have already been parsed. If you are building an abstract syntax tree and need to have line numbers, you should make sure that the line numbers appear in the tree itself.

    6.10 AST Construction

    yacc.py provides no special functions for constructing an abstract syntax tree. However, such construction is easy enough to do on your own.

    A minimal way to construct a tree is to simply create and propagate a tuple or list in each grammar rule function. There are many possible ways to do this, but one example would be something like this:

    def p_expression_binop(p):
        '''expression : expression PLUS expression
                      | expression MINUS expression
                      | expression TIMES expression
                      | expression DIVIDE expression'''
    
        p[0] = ('binary-expression',p[2],p[1],p[3])
    
    def p_expression_group(p):
        'expression : LPAREN expression RPAREN'
        p[0] = ('group-expression',p[2])
    
    def p_expression_number(p):
        'expression : NUMBER'
        p[0] = ('number-expression',p[1])
    

    Another approach is to create a set of data structure for different kinds of abstract syntax tree nodes and assign nodes to p[0] in each rule. For example:

    class Expr: pass
    
    class BinOp(Expr):
        def __init__(self,left,op,right):
            self.type = "binop"
            self.left = left
            self.right = right
            self.op = op
    
    class Number(Expr):
        def __init__(self,value):
            self.type = "number"
            self.value = value
    
    def p_expression_binop(p):
        '''expression : expression PLUS expression
                      | expression MINUS expression
                      | expression TIMES expression
                      | expression DIVIDE expression'''
    
        p[0] = BinOp(p[1],p[2],p[3])
    
    def p_expression_group(p):
        'expression : LPAREN expression RPAREN'
        p[0] = p[2]
    
    def p_expression_number(p):
        'expression : NUMBER'
        p[0] = Number(p[1])
    
    The advantage to this approach is that it may make it easier to attach more complicated semantics, type checking, code generation, and other features to the node classes.

    To simplify tree traversal, it may make sense to pick a very generic tree structure for your parse tree nodes. For example:

    class Node:
        def __init__(self,type,children=None,leaf=None):
             self.type = type
             if children:
                  self.children = children
             else:
                  self.children = [ ]
             self.leaf = leaf
    	 
    def p_expression_binop(p):
        '''expression : expression PLUS expression
                      | expression MINUS expression
                      | expression TIMES expression
                      | expression DIVIDE expression'''
    
        p[0] = Node("binop", [p[1],p[3]], p[2])
    

    6.11 Embedded Actions

    The parsing technique used by yacc only allows actions to be executed at the end of a rule. For example, suppose you have a rule like this:
    def p_foo(p):
        "foo : A B C D"
        print "Parsed a foo", p[1],p[2],p[3],p[4]
    

    In this case, the supplied action code only executes after all of the symbols A, B, C, and D have been parsed. Sometimes, however, it is useful to execute small code fragments during intermediate stages of parsing. For example, suppose you wanted to perform some action immediately after A has been parsed. To do this, write an empty rule like this:

    def p_foo(p):
        "foo : A seen_A B C D"
        print "Parsed a foo", p[1],p[3],p[4],p[5]
        print "seen_A returned", p[2]
    
    def p_seen_A(p):
        "seen_A :"
        print "Saw an A = ", p[-1]   # Access grammar symbol to left
        p[0] = some_value            # Assign value to seen_A
    
    

    In this example, the empty seen_A rule executes immediately after A is shifted onto the parsing stack. Within this rule, p[-1] refers to the symbol on the stack that appears immediately to the left of the seen_A symbol. In this case, it would be the value of A in the foo rule immediately above. Like other rules, a value can be returned from an embedded action by simply assigning it to p[0]

    The use of embedded actions can sometimes introduce extra shift/reduce conflicts. For example, this grammar has no conflicts:

    def p_foo(p):
        """foo : abcd
               | abcx"""
    
    def p_abcd(p):
        "abcd : A B C D"
    
    def p_abcx(p):
        "abcx : A B C X"
    
    However, if you insert an embedded action into one of the rules like this,
    def p_foo(p):
        """foo : abcd
               | abcx"""
    
    def p_abcd(p):
        "abcd : A B C D"
    
    def p_abcx(p):
        "abcx : A B seen_AB C X"
    
    def p_seen_AB(p):
        "seen_AB :"
    
    an extra shift-reduce conflict will be introduced. This conflict is caused by the fact that the same symbol C appears next in both the abcd and abcx rules. The parser can either shift the symbol (abcd rule) or reduce the empty rule seen_AB (abcx rule).

    A common use of embedded rules is to control other aspects of parsing such as scoping of local variables. For example, if you were parsing C code, you might write code like this:

    def p_statements_block(p):
        "statements: LBRACE new_scope statements RBRACE"""
        # Action code
        ...
        pop_scope()        # Return to previous scope
    
    def p_new_scope(p):
        "new_scope :"
        # Create a new scope for local variables
        s = new_scope()
        push_scope(s)
        ...
    
    In this case, the embedded action new_scope executes immediately after a LBRACE ({) symbol is parsed. This might adjust internal symbol tables and other aspects of the parser. Upon completion of the rule statements_block, code might undo the operations performed in the embedded action (e.g., pop_scope()).

    6.12 Miscellaneous Yacc Notes

    • The default parsing method is LALR. To use SLR instead, run yacc() as follows:
      yacc.yacc(method="SLR")
      
      Note: LALR table generation takes approximately twice as long as SLR table generation. There is no difference in actual parsing performance---the same code is used in both cases. LALR is preferred when working with more complicated grammars since it is more powerful.

    • By default, yacc.py relies on lex.py for tokenizing. However, an alternative tokenizer can be supplied as follows:
      yacc.parse(lexer=x)
      
      in this case, x must be a Lexer object that minimally has a x.token() method for retrieving the next token. If an input string is given to yacc.parse(), the lexer must also have an x.input() method.

    • By default, the yacc generates tables in debugging mode (which produces the parser.out file and other output). To disable this, use
      yacc.yacc(debug=0)
      

    • To change the name of the parsetab.py file, use:
      yacc.yacc(tabmodule="foo")
      

    • To change the directory in which the parsetab.py file (and other output files) are written, use:
      yacc.yacc(tabmodule="foo",outputdir="somedirectory")
      

    • To prevent yacc from generating any kind of parser table file, use:
      yacc.yacc(write_tables=0)
      
      Note: If you disable table generation, yacc() will regenerate the parsing tables each time it runs (which may take awhile depending on how large your grammar is).

    • To print copious amounts of debugging during parsing, use:
      yacc.parse(debug=1)     
      

    • The yacc.yacc() function really returns a parser object. If you want to support multiple parsers in the same application, do this:
      p = yacc.yacc()
      ...
      p.parse()
      
      Note: The function yacc.parse() is bound to the last parser that was generated.

    • Since the generation of the LALR tables is relatively expensive, previously generated tables are cached and reused if possible. The decision to regenerate the tables is determined by taking an MD5 checksum of all grammar rules and precedence rules. Only in the event of a mismatch are the tables regenerated.

      It should be noted that table generation is reasonably efficient, even for grammars that involve around a 100 rules and several hundred states. For more complex languages such as C, table generation may take 30-60 seconds on a slow machine. Please be patient.

    • Since LR parsing is driven by tables, the performance of the parser is largely independent of the size of the grammar. The biggest bottlenecks will be the lexer and the complexity of the code in your grammar rules.

    7. Multiple Parsers and Lexers

    In advanced parsing applications, you may want to have multiple parsers and lexers.

    As a general rules this isn't a problem. However, to make it work, you need to carefully make sure everything gets hooked up correctly. First, make sure you save the objects returned by lex() and yacc(). For example:

    lexer  = lex.lex()       # Return lexer object
    parser = yacc.yacc()     # Return parser object
    
    Next, when parsing, make sure you give the parse() function a reference to the lexer it should be using. For example:
    parser.parse(text,lexer=lexer)
    
    If you forget to do this, the parser will use the last lexer created--which is not always what you want.

    Within lexer and parser rule functions, these objects are also available. In the lexer, the "lexer" attribute of a token refers to the lexer object that triggered the rule. For example:

    def t_NUMBER(t):
       r'\d+'
       ...
       print t.lexer           # Show lexer object
    
    In the parser, the "lexer" and "parser" attributes refer to the lexer and parser objects respectively.
    def p_expr_plus(p):
       'expr : expr PLUS expr'
       ...
       print p.parser          # Show parser object
       print p.lexer           # Show lexer object
    
    If necessary, arbitrary attributes can be attached to the lexer or parser object. For example, if you wanted to have different parsing modes, you could attach a mode attribute to the parser object and look at it later.

    8. Using Python's Optimized Mode

    Because PLY uses information from doc-strings, parsing and lexing information must be gathered while running the Python interpreter in normal mode (i.e., not with the -O or -OO options). However, if you specify optimized mode like this:
    lex.lex(optimize=1)
    yacc.yacc(optimize=1)
    
    then PLY can later be used when Python runs in optimized mode. To make this work, make sure you first run Python in normal mode. Once the lexing and parsing tables have been generated the first time, run Python in optimized mode. PLY will use the tables without the need for doc strings.

    Beware: running PLY in optimized mode disables a lot of error checking. You should only do this when your project has stabilized and you don't need to do any debugging. One of the purposes of optimized mode is to substantially decrease the startup time of your compiler (by assuming that everything is already properly specified and works).

    9. Advanced Debugging

    Debugging a compiler is typically not an easy task. PLY provides some advanced diagonistic capabilities through the use of Python's logging module. The next two sections describe this:

    9.1 Debugging the lex() and yacc() commands

    Both the lex() and yacc() commands have a debugging mode that can be enabled using the debug flag. For example:

    lex.lex(debug=True)
    yacc.yacc(debug=True)
    
    Normally, the output produced by debugging is routed to either standard error or, in the case of yacc(), to a file parser.out. This output can be more carefully controlled by supplying a logging object. Here is an example that adds information about where different debugging messages are coming from:
    # Set up a logging object
    import logging
    logging.basicConfig(
        level = logging.DEBUG,
        filename = "parselog.txt",
        filemode = "w",
        format = "%(filename)10s:%(lineno)4d:%(message)s"
    )
    log = logging.getLogger()
    
    lex.lex(debug=True,debuglog=log)
    yacc.yacc(debug=True,debuglog=log)
    
    If you supply a custom logger, the amount of debugging information produced can be controlled by setting the logging level. Typically, debugging messages are either issued at the DEBUG, INFO, or WARNING levels.

    PLY's error messages and warnings are also produced using the logging interface. This can be controlled by passing a logging object using the errorlog parameter.

    lex.lex(errorlog=log)
    yacc.yacc(errorlog=log)
    
    If you want to completely silence warnings, you can either pass in a logging object with an appropriate filter level or use the NullLogger object defined in either lex or yacc. For example:
    yacc.yacc(errorlog=yacc.NullLogger())
    

    9.2 Run-time Debugging

    To enable run-time debugging of a parser, use the debug option to parse. This option can either be an integer (which simply turns debugging on or off) or an instance of a logger object. For example:

    log = logging.getLogger()
    parser.parse(input,debug=log)
    
    If a logging object is passed, you can use its filtering level to control how much output gets generated. The INFO level is used to produce information about rule reductions. The DEBUG level will show information about the parsing stack, token shifts, and other details. The ERROR level shows information related to parsing errors.

    For very complicated problems, you should pass in a logging object that redirects to a file where you can more easily inspect the output after execution.

    10. Where to go from here?

    The examples directory of the PLY distribution contains several simple examples. Please consult a compilers textbook for the theory and underlying implementation details or LR parsing. ./CBFlib-0.9.2.2/ply-3.2/ply/0000755000076500007650000000000011603703070013507 5ustar yayayaya./CBFlib-0.9.2.2/ply-3.2/ply/yacc.py0000644000076500007650000037274711603702121015020 0ustar yayayaya# ----------------------------------------------------------------------------- # ply: yacc.py # # Copyright (C) 2001-2009, # David M. Beazley (Dabeaz LLC) # All rights reserved. # # Redistribution and use in source and binary forms, with or without # modification, are permitted provided that the following conditions are # met: # # * Redistributions of source code must retain the above copyright notice, # this list of conditions and the following disclaimer. # * Redistributions in binary form must reproduce the above copyright notice, # this list of conditions and the following disclaimer in the documentation # and/or other materials provided with the distribution. # * Neither the name of the David Beazley or Dabeaz LLC may be used to # endorse or promote products derived from this software without # specific prior written permission. # # THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS # "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT # LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR # A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT # OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, # SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT # LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, # DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY # THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT # (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE # OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. # ----------------------------------------------------------------------------- # # This implements an LR parser that is constructed from grammar rules defined # as Python functions. The grammer is specified by supplying the BNF inside # Python documentation strings. The inspiration for this technique was borrowed # from John Aycock's Spark parsing system. PLY might be viewed as cross between # Spark and the GNU bison utility. # # The current implementation is only somewhat object-oriented. The # LR parser itself is defined in terms of an object (which allows multiple # parsers to co-exist). However, most of the variables used during table # construction are defined in terms of global variables. Users shouldn't # notice unless they are trying to define multiple parsers at the same # time using threads (in which case they should have their head examined). # # This implementation supports both SLR and LALR(1) parsing. LALR(1) # support was originally implemented by Elias Ioup (ezioup@alumni.uchicago.edu), # using the algorithm found in Aho, Sethi, and Ullman "Compilers: Principles, # Techniques, and Tools" (The Dragon Book). LALR(1) has since been replaced # by the more efficient DeRemer and Pennello algorithm. # # :::::::: WARNING ::::::: # # Construction of LR parsing tables is fairly complicated and expensive. # To make this module run fast, a *LOT* of work has been put into # optimization---often at the expensive of readability and what might # consider to be good Python "coding style." Modify the code at your # own risk! # ---------------------------------------------------------------------------- __version__ = "3.2" __tabversion__ = "3.2" # Table version #----------------------------------------------------------------------------- # === User configurable parameters === # # Change these to modify the default behavior of yacc (if you wish) #----------------------------------------------------------------------------- yaccdebug = 1 # Debugging mode. If set, yacc generates a # a 'parser.out' file in the current directory debug_file = 'parser.out' # Default name of the debugging file tab_module = 'parsetab' # Default name of the table module default_lr = 'LALR' # Default LR table generation method error_count = 3 # Number of symbols that must be shifted to leave recovery mode yaccdevel = 0 # Set to True if developing yacc. This turns off optimized # implementations of certain functions. resultlimit = 40 # Size limit of results when running in debug mode. pickle_protocol = 0 # Protocol to use when writing pickle files import re, types, sys, os.path # Compatibility function for python 2.6/3.0 if sys.version_info[0] < 3: def func_code(f): return f.func_code else: def func_code(f): return f.__code__ # Compatibility try: MAXINT = sys.maxint except AttributeError: MAXINT = sys.maxsize # Python 2.x/3.0 compatibility. def load_ply_lex(): if sys.version_info[0] < 3: import lex else: import ply.lex as lex return lex # This object is a stand-in for a logging object created by the # logging module. PLY will use this by default to create things # such as the parser.out file. If a user wants more detailed # information, they can create their own logging object and pass # it into PLY. class PlyLogger(object): def __init__(self,f): self.f = f def debug(self,msg,*args,**kwargs): self.f.write((msg % args) + "\n") info = debug def warning(self,msg,*args,**kwargs): self.f.write("WARNING: "+ (msg % args) + "\n") def error(self,msg,*args,**kwargs): self.f.write("ERROR: " + (msg % args) + "\n") critical = debug # Null logger is used when no output is generated. Does nothing. class NullLogger(object): def __getattribute__(self,name): return self def __call__(self,*args,**kwargs): return self # Exception raised for yacc-related errors class YaccError(Exception): pass # Format the result message that the parser produces when running in debug mode. def format_result(r): repr_str = repr(r) if '\n' in repr_str: repr_str = repr(repr_str) if len(repr_str) > resultlimit: repr_str = repr_str[:resultlimit]+" ..." result = "<%s @ 0x%x> (%s)" % (type(r).__name__,id(r),repr_str) return result # Format stack entries when the parser is running in debug mode def format_stack_entry(r): repr_str = repr(r) if '\n' in repr_str: repr_str = repr(repr_str) if len(repr_str) < 16: return repr_str else: return "<%s @ 0x%x>" % (type(r).__name__,id(r)) #----------------------------------------------------------------------------- # === LR Parsing Engine === # # The following classes are used for the LR parser itself. These are not # used during table construction and are independent of the actual LR # table generation algorithm #----------------------------------------------------------------------------- # This class is used to hold non-terminal grammar symbols during parsing. # It normally has the following attributes set: # .type = Grammar symbol type # .value = Symbol value # .lineno = Starting line number # .endlineno = Ending line number (optional, set automatically) # .lexpos = Starting lex position # .endlexpos = Ending lex position (optional, set automatically) class YaccSymbol: def __str__(self): return self.type def __repr__(self): return str(self) # This class is a wrapper around the objects actually passed to each # grammar rule. Index lookup and assignment actually assign the # .value attribute of the underlying YaccSymbol object. # The lineno() method returns the line number of a given # item (or 0 if not defined). The linespan() method returns # a tuple of (startline,endline) representing the range of lines # for a symbol. The lexspan() method returns a tuple (lexpos,endlexpos) # representing the range of positional information for a symbol. class YaccProduction: def __init__(self,s,stack=None): self.slice = s self.stack = stack self.lexer = None self.parser= None def __getitem__(self,n): if n >= 0: return self.slice[n].value else: return self.stack[n].value def __setitem__(self,n,v): self.slice[n].value = v def __getslice__(self,i,j): return [s.value for s in self.slice[i:j]] def __len__(self): return len(self.slice) def lineno(self,n): return getattr(self.slice[n],"lineno",0) def set_lineno(self,n,lineno): self.slice[n].lineno = n def linespan(self,n): startline = getattr(self.slice[n],"lineno",0) endline = getattr(self.slice[n],"endlineno",startline) return startline,endline def lexpos(self,n): return getattr(self.slice[n],"lexpos",0) def lexspan(self,n): startpos = getattr(self.slice[n],"lexpos",0) endpos = getattr(self.slice[n],"endlexpos",startpos) return startpos,endpos def error(self): raise SyntaxError # ----------------------------------------------------------------------------- # == LRParser == # # The LR Parsing engine. # ----------------------------------------------------------------------------- class LRParser: def __init__(self,lrtab,errorf): self.productions = lrtab.lr_productions self.action = lrtab.lr_action self.goto = lrtab.lr_goto self.errorfunc = errorf def errok(self): self.errorok = 1 def restart(self): del self.statestack[:] del self.symstack[:] sym = YaccSymbol() sym.type = '$end' self.symstack.append(sym) self.statestack.append(0) def parse(self,input=None,lexer=None,debug=0,tracking=0,tokenfunc=None): if debug or yaccdevel: if isinstance(debug,int): debug = PlyLogger(sys.stderr) return self.parsedebug(input,lexer,debug,tracking,tokenfunc) elif tracking: return self.parseopt(input,lexer,debug,tracking,tokenfunc) else: return self.parseopt_notrack(input,lexer,debug,tracking,tokenfunc) # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! # parsedebug(). # # This is the debugging enabled version of parse(). All changes made to the # parsing engine should be made here. For the non-debugging version, # copy this code to a method parseopt() and delete all of the sections # enclosed in: # # #--! DEBUG # statements # #--! DEBUG # # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! def parsedebug(self,input=None,lexer=None,debug=None,tracking=0,tokenfunc=None): lookahead = None # Current lookahead symbol lookaheadstack = [ ] # Stack of lookahead symbols actions = self.action # Local reference to action table (to avoid lookup on self.) goto = self.goto # Local reference to goto table (to avoid lookup on self.) prod = self.productions # Local reference to production list (to avoid lookup on self.) pslice = YaccProduction(None) # Production object passed to grammar rules errorcount = 0 # Used during error recovery # --! DEBUG debug.info("PLY: PARSE DEBUG START") # --! DEBUG # If no lexer was given, we will try to use the lex module if not lexer: lex = load_ply_lex() lexer = lex.lexer # Set up the lexer and parser objects on pslice pslice.lexer = lexer pslice.parser = self # If input was supplied, pass to lexer if input is not None: lexer.input(input) if tokenfunc is None: # Tokenize function get_token = lexer.token else: get_token = tokenfunc # Set up the state and symbol stacks statestack = [ ] # Stack of parsing states self.statestack = statestack symstack = [ ] # Stack of grammar symbols self.symstack = symstack pslice.stack = symstack # Put in the production errtoken = None # Err token # The start state is assumed to be (0,$end) statestack.append(0) sym = YaccSymbol() sym.type = "$end" symstack.append(sym) state = 0 while 1: # Get the next symbol on the input. If a lookahead symbol # is already set, we just use that. Otherwise, we'll pull # the next token off of the lookaheadstack or from the lexer # --! DEBUG debug.debug('') debug.debug('State : %s', state) # --! DEBUG if not lookahead: if not lookaheadstack: lookahead = get_token() # Get the next token else: lookahead = lookaheadstack.pop() if not lookahead: lookahead = YaccSymbol() lookahead.type = "$end" # --! DEBUG debug.debug('Stack : %s', ("%s . %s" % (" ".join([xx.type for xx in symstack][1:]), str(lookahead))).lstrip()) # --! DEBUG # Check the action table ltype = lookahead.type t = actions[state].get(ltype) if t is not None: if t > 0: # shift a symbol on the stack statestack.append(t) state = t # --! DEBUG debug.debug("Action : Shift and goto state %s", t) # --! DEBUG symstack.append(lookahead) lookahead = None # Decrease error count on successful shift if errorcount: errorcount -=1 continue if t < 0: # reduce a symbol on the stack, emit a production p = prod[-t] pname = p.name plen = p.len # Get production function sym = YaccSymbol() sym.type = pname # Production name sym.value = None # --! DEBUG if plen: debug.info("Action : Reduce rule [%s] with %s and goto state %d", p.str, "["+",".join([format_stack_entry(_v.value) for _v in symstack[-plen:]])+"]",-t) else: debug.info("Action : Reduce rule [%s] with %s and goto state %d", p.str, [],-t) # --! DEBUG if plen: targ = symstack[-plen-1:] targ[0] = sym # --! TRACKING if tracking: t1 = targ[1] sym.lineno = t1.lineno sym.lexpos = t1.lexpos t1 = targ[-1] sym.endlineno = getattr(t1,"endlineno",t1.lineno) sym.endlexpos = getattr(t1,"endlexpos",t1.lexpos) # --! TRACKING # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! # The code enclosed in this section is duplicated # below as a performance optimization. Make sure # changes get made in both locations. pslice.slice = targ try: # Call the grammar rule with our special slice object del symstack[-plen:] del statestack[-plen:] p.callable(pslice) # --! DEBUG debug.info("Result : %s", format_result(pslice[0])) # --! DEBUG symstack.append(sym) state = goto[statestack[-1]][pname] statestack.append(state) except SyntaxError: # If an error was set. Enter error recovery state lookaheadstack.append(lookahead) symstack.pop() statestack.pop() state = statestack[-1] sym.type = 'error' lookahead = sym errorcount = error_count self.errorok = 0 continue # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! else: # --! TRACKING if tracking: sym.lineno = lexer.lineno sym.lexpos = lexer.lexpos # --! TRACKING targ = [ sym ] # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! # The code enclosed in this section is duplicated # above as a performance optimization. Make sure # changes get made in both locations. pslice.slice = targ try: # Call the grammar rule with our special slice object p.callable(pslice) # --! DEBUG debug.info("Result : %s", format_result(pslice[0])) # --! DEBUG symstack.append(sym) state = goto[statestack[-1]][pname] statestack.append(state) except SyntaxError: # If an error was set. Enter error recovery state lookaheadstack.append(lookahead) symstack.pop() statestack.pop() state = statestack[-1] sym.type = 'error' lookahead = sym errorcount = error_count self.errorok = 0 continue # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! if t == 0: n = symstack[-1] result = getattr(n,"value",None) # --! DEBUG debug.info("Done : Returning %s", format_result(result)) debug.info("PLY: PARSE DEBUG END") # --! DEBUG return result if t == None: # --! DEBUG debug.error('Error : %s', ("%s . %s" % (" ".join([xx.type for xx in symstack][1:]), str(lookahead))).lstrip()) # --! DEBUG # We have some kind of parsing error here. To handle # this, we are going to push the current token onto # the tokenstack and replace it with an 'error' token. # If there are any synchronization rules, they may # catch it. # # In addition to pushing the error token, we call call # the user defined p_error() function if this is the # first syntax error. This function is only called if # errorcount == 0. if errorcount == 0 or self.errorok: errorcount = error_count self.errorok = 0 errtoken = lookahead if errtoken.type == "$end": errtoken = None # End of file! if self.errorfunc: global errok,token,restart errok = self.errok # Set some special functions available in error recovery token = get_token restart = self.restart if errtoken and not hasattr(errtoken,'lexer'): errtoken.lexer = lexer tok = self.errorfunc(errtoken) del errok, token, restart # Delete special functions if self.errorok: # User must have done some kind of panic # mode recovery on their own. The # returned token is the next lookahead lookahead = tok errtoken = None continue else: if errtoken: if hasattr(errtoken,"lineno"): lineno = lookahead.lineno else: lineno = 0 if lineno: sys.stderr.write("yacc: Syntax error at line %d, token=%s\n" % (lineno, errtoken.type)) else: sys.stderr.write("yacc: Syntax error, token=%s" % errtoken.type) else: sys.stderr.write("yacc: Parse error in input. EOF\n") return else: errorcount = error_count # case 1: the statestack only has 1 entry on it. If we're in this state, the # entire parse has been rolled back and we're completely hosed. The token is # discarded and we just keep going. if len(statestack) <= 1 and lookahead.type != "$end": lookahead = None errtoken = None state = 0 # Nuke the pushback stack del lookaheadstack[:] continue # case 2: the statestack has a couple of entries on it, but we're # at the end of the file. nuke the top entry and generate an error token # Start nuking entries on the stack if lookahead.type == "$end": # Whoa. We're really hosed here. Bail out return if lookahead.type != 'error': sym = symstack[-1] if sym.type == 'error': # Hmmm. Error is on top of stack, we'll just nuke input # symbol and continue lookahead = None continue t = YaccSymbol() t.type = 'error' if hasattr(lookahead,"lineno"): t.lineno = lookahead.lineno t.value = lookahead lookaheadstack.append(lookahead) lookahead = t else: symstack.pop() statestack.pop() state = statestack[-1] # Potential bug fix continue # Call an error function here raise RuntimeError("yacc: internal parser error!!!\n") # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! # parseopt(). # # Optimized version of parse() method. DO NOT EDIT THIS CODE DIRECTLY. # Edit the debug version above, then copy any modifications to the method # below while removing #--! DEBUG sections. # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! def parseopt(self,input=None,lexer=None,debug=0,tracking=0,tokenfunc=None): lookahead = None # Current lookahead symbol lookaheadstack = [ ] # Stack of lookahead symbols actions = self.action # Local reference to action table (to avoid lookup on self.) goto = self.goto # Local reference to goto table (to avoid lookup on self.) prod = self.productions # Local reference to production list (to avoid lookup on self.) pslice = YaccProduction(None) # Production object passed to grammar rules errorcount = 0 # Used during error recovery # If no lexer was given, we will try to use the lex module if not lexer: lex = load_ply_lex() lexer = lex.lexer # Set up the lexer and parser objects on pslice pslice.lexer = lexer pslice.parser = self # If input was supplied, pass to lexer if input is not None: lexer.input(input) if tokenfunc is None: # Tokenize function get_token = lexer.token else: get_token = tokenfunc # Set up the state and symbol stacks statestack = [ ] # Stack of parsing states self.statestack = statestack symstack = [ ] # Stack of grammar symbols self.symstack = symstack pslice.stack = symstack # Put in the production errtoken = None # Err token # The start state is assumed to be (0,$end) statestack.append(0) sym = YaccSymbol() sym.type = '$end' symstack.append(sym) state = 0 while 1: # Get the next symbol on the input. If a lookahead symbol # is already set, we just use that. Otherwise, we'll pull # the next token off of the lookaheadstack or from the lexer if not lookahead: if not lookaheadstack: lookahead = get_token() # Get the next token else: lookahead = lookaheadstack.pop() if not lookahead: lookahead = YaccSymbol() lookahead.type = '$end' # Check the action table ltype = lookahead.type t = actions[state].get(ltype) if t is not None: if t > 0: # shift a symbol on the stack statestack.append(t) state = t symstack.append(lookahead) lookahead = None # Decrease error count on successful shift if errorcount: errorcount -=1 continue if t < 0: # reduce a symbol on the stack, emit a production p = prod[-t] pname = p.name plen = p.len # Get production function sym = YaccSymbol() sym.type = pname # Production name sym.value = None if plen: targ = symstack[-plen-1:] targ[0] = sym # --! TRACKING if tracking: t1 = targ[1] sym.lineno = t1.lineno sym.lexpos = t1.lexpos t1 = targ[-1] sym.endlineno = getattr(t1,"endlineno",t1.lineno) sym.endlexpos = getattr(t1,"endlexpos",t1.lexpos) # --! TRACKING # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! # The code enclosed in this section is duplicated # below as a performance optimization. Make sure # changes get made in both locations. pslice.slice = targ try: # Call the grammar rule with our special slice object del symstack[-plen:] del statestack[-plen:] p.callable(pslice) symstack.append(sym) state = goto[statestack[-1]][pname] statestack.append(state) except SyntaxError: # If an error was set. Enter error recovery state lookaheadstack.append(lookahead) symstack.pop() statestack.pop() state = statestack[-1] sym.type = 'error' lookahead = sym errorcount = error_count self.errorok = 0 continue # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! else: # --! TRACKING if tracking: sym.lineno = lexer.lineno sym.lexpos = lexer.lexpos # --! TRACKING targ = [ sym ] # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! # The code enclosed in this section is duplicated # above as a performance optimization. Make sure # changes get made in both locations. pslice.slice = targ try: # Call the grammar rule with our special slice object p.callable(pslice) symstack.append(sym) state = goto[statestack[-1]][pname] statestack.append(state) except SyntaxError: # If an error was set. Enter error recovery state lookaheadstack.append(lookahead) symstack.pop() statestack.pop() state = statestack[-1] sym.type = 'error' lookahead = sym errorcount = error_count self.errorok = 0 continue # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! if t == 0: n = symstack[-1] return getattr(n,"value",None) if t == None: # We have some kind of parsing error here. To handle # this, we are going to push the current token onto # the tokenstack and replace it with an 'error' token. # If there are any synchronization rules, they may # catch it. # # In addition to pushing the error token, we call call # the user defined p_error() function if this is the # first syntax error. This function is only called if # errorcount == 0. if errorcount == 0 or self.errorok: errorcount = error_count self.errorok = 0 errtoken = lookahead if errtoken.type == '$end': errtoken = None # End of file! if self.errorfunc: global errok,token,restart errok = self.errok # Set some special functions available in error recovery token = get_token restart = self.restart if errtoken and not hasattr(errtoken,'lexer'): errtoken.lexer = lexer tok = self.errorfunc(errtoken) del errok, token, restart # Delete special functions if self.errorok: # User must have done some kind of panic # mode recovery on their own. The # returned token is the next lookahead lookahead = tok errtoken = None continue else: if errtoken: if hasattr(errtoken,"lineno"): lineno = lookahead.lineno else: lineno = 0 if lineno: sys.stderr.write("yacc: Syntax error at line %d, token=%s\n" % (lineno, errtoken.type)) else: sys.stderr.write("yacc: Syntax error, token=%s" % errtoken.type) else: sys.stderr.write("yacc: Parse error in input. EOF\n") return else: errorcount = error_count # case 1: the statestack only has 1 entry on it. If we're in this state, the # entire parse has been rolled back and we're completely hosed. The token is # discarded and we just keep going. if len(statestack) <= 1 and lookahead.type != '$end': lookahead = None errtoken = None state = 0 # Nuke the pushback stack del lookaheadstack[:] continue # case 2: the statestack has a couple of entries on it, but we're # at the end of the file. nuke the top entry and generate an error token # Start nuking entries on the stack if lookahead.type == '$end': # Whoa. We're really hosed here. Bail out return if lookahead.type != 'error': sym = symstack[-1] if sym.type == 'error': # Hmmm. Error is on top of stack, we'll just nuke input # symbol and continue lookahead = None continue t = YaccSymbol() t.type = 'error' if hasattr(lookahead,"lineno"): t.lineno = lookahead.lineno t.value = lookahead lookaheadstack.append(lookahead) lookahead = t else: symstack.pop() statestack.pop() state = statestack[-1] # Potential bug fix continue # Call an error function here raise RuntimeError("yacc: internal parser error!!!\n") # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! # parseopt_notrack(). # # Optimized version of parseopt() with line number tracking removed. # DO NOT EDIT THIS CODE DIRECTLY. Copy the optimized version and remove # code in the #--! TRACKING sections # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! def parseopt_notrack(self,input=None,lexer=None,debug=0,tracking=0,tokenfunc=None): lookahead = None # Current lookahead symbol lookaheadstack = [ ] # Stack of lookahead symbols actions = self.action # Local reference to action table (to avoid lookup on self.) goto = self.goto # Local reference to goto table (to avoid lookup on self.) prod = self.productions # Local reference to production list (to avoid lookup on self.) pslice = YaccProduction(None) # Production object passed to grammar rules errorcount = 0 # Used during error recovery # If no lexer was given, we will try to use the lex module if not lexer: lex = load_ply_lex() lexer = lex.lexer # Set up the lexer and parser objects on pslice pslice.lexer = lexer pslice.parser = self # If input was supplied, pass to lexer if input is not None: lexer.input(input) if tokenfunc is None: # Tokenize function get_token = lexer.token else: get_token = tokenfunc # Set up the state and symbol stacks statestack = [ ] # Stack of parsing states self.statestack = statestack symstack = [ ] # Stack of grammar symbols self.symstack = symstack pslice.stack = symstack # Put in the production errtoken = None # Err token # The start state is assumed to be (0,$end) statestack.append(0) sym = YaccSymbol() sym.type = '$end' symstack.append(sym) state = 0 while 1: # Get the next symbol on the input. If a lookahead symbol # is already set, we just use that. Otherwise, we'll pull # the next token off of the lookaheadstack or from the lexer if not lookahead: if not lookaheadstack: lookahead = get_token() # Get the next token else: lookahead = lookaheadstack.pop() if not lookahead: lookahead = YaccSymbol() lookahead.type = '$end' # Check the action table ltype = lookahead.type t = actions[state].get(ltype) if t is not None: if t > 0: # shift a symbol on the stack statestack.append(t) state = t symstack.append(lookahead) lookahead = None # Decrease error count on successful shift if errorcount: errorcount -=1 continue if t < 0: # reduce a symbol on the stack, emit a production p = prod[-t] pname = p.name plen = p.len # Get production function sym = YaccSymbol() sym.type = pname # Production name sym.value = None if plen: targ = symstack[-plen-1:] targ[0] = sym # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! # The code enclosed in this section is duplicated # below as a performance optimization. Make sure # changes get made in both locations. pslice.slice = targ try: # Call the grammar rule with our special slice object del symstack[-plen:] del statestack[-plen:] p.callable(pslice) symstack.append(sym) state = goto[statestack[-1]][pname] statestack.append(state) except SyntaxError: # If an error was set. Enter error recovery state lookaheadstack.append(lookahead) symstack.pop() statestack.pop() state = statestack[-1] sym.type = 'error' lookahead = sym errorcount = error_count self.errorok = 0 continue # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! else: targ = [ sym ] # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! # The code enclosed in this section is duplicated # above as a performance optimization. Make sure # changes get made in both locations. pslice.slice = targ try: # Call the grammar rule with our special slice object p.callable(pslice) symstack.append(sym) state = goto[statestack[-1]][pname] statestack.append(state) except SyntaxError: # If an error was set. Enter error recovery state lookaheadstack.append(lookahead) symstack.pop() statestack.pop() state = statestack[-1] sym.type = 'error' lookahead = sym errorcount = error_count self.errorok = 0 continue # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! if t == 0: n = symstack[-1] return getattr(n,"value",None) if t == None: # We have some kind of parsing error here. To handle # this, we are going to push the current token onto # the tokenstack and replace it with an 'error' token. # If there are any synchronization rules, they may # catch it. # # In addition to pushing the error token, we call call # the user defined p_error() function if this is the # first syntax error. This function is only called if # errorcount == 0. if errorcount == 0 or self.errorok: errorcount = error_count self.errorok = 0 errtoken = lookahead if errtoken.type == '$end': errtoken = None # End of file! if self.errorfunc: global errok,token,restart errok = self.errok # Set some special functions available in error recovery token = get_token restart = self.restart if errtoken and not hasattr(errtoken,'lexer'): errtoken.lexer = lexer tok = self.errorfunc(errtoken) del errok, token, restart # Delete special functions if self.errorok: # User must have done some kind of panic # mode recovery on their own. The # returned token is the next lookahead lookahead = tok errtoken = None continue else: if errtoken: if hasattr(errtoken,"lineno"): lineno = lookahead.lineno else: lineno = 0 if lineno: sys.stderr.write("yacc: Syntax error at line %d, token=%s\n" % (lineno, errtoken.type)) else: sys.stderr.write("yacc: Syntax error, token=%s" % errtoken.type) else: sys.stderr.write("yacc: Parse error in input. EOF\n") return else: errorcount = error_count # case 1: the statestack only has 1 entry on it. If we're in this state, the # entire parse has been rolled back and we're completely hosed. The token is # discarded and we just keep going. if len(statestack) <= 1 and lookahead.type != '$end': lookahead = None errtoken = None state = 0 # Nuke the pushback stack del lookaheadstack[:] continue # case 2: the statestack has a couple of entries on it, but we're # at the end of the file. nuke the top entry and generate an error token # Start nuking entries on the stack if lookahead.type == '$end': # Whoa. We're really hosed here. Bail out return if lookahead.type != 'error': sym = symstack[-1] if sym.type == 'error': # Hmmm. Error is on top of stack, we'll just nuke input # symbol and continue lookahead = None continue t = YaccSymbol() t.type = 'error' if hasattr(lookahead,"lineno"): t.lineno = lookahead.lineno t.value = lookahead lookaheadstack.append(lookahead) lookahead = t else: symstack.pop() statestack.pop() state = statestack[-1] # Potential bug fix continue # Call an error function here raise RuntimeError("yacc: internal parser error!!!\n") # ----------------------------------------------------------------------------- # === Grammar Representation === # # The following functions, classes, and variables are used to represent and # manipulate the rules that make up a grammar. # ----------------------------------------------------------------------------- import re # regex matching identifiers _is_identifier = re.compile(r'^[a-zA-Z0-9_-]+$') # ----------------------------------------------------------------------------- # class Production: # # This class stores the raw information about a single production or grammar rule. # A grammar rule refers to a specification such as this: # # expr : expr PLUS term # # Here are the basic attributes defined on all productions # # name - Name of the production. For example 'expr' # prod - A list of symbols on the right side ['expr','PLUS','term'] # prec - Production precedence level # number - Production number. # func - Function that executes on reduce # file - File where production function is defined # lineno - Line number where production function is defined # # The following attributes are defined or optional. # # len - Length of the production (number of symbols on right hand side) # usyms - Set of unique symbols found in the production # ----------------------------------------------------------------------------- class Production(object): reduced = 0 def __init__(self,number,name,prod,precedence=('right',0),func=None,file='',line=0): self.name = name self.prod = tuple(prod) self.number = number self.func = func self.callable = None self.file = file self.line = line self.prec = precedence # Internal settings used during table construction self.len = len(self.prod) # Length of the production # Create a list of unique production symbols used in the production self.usyms = [ ] for s in self.prod: if s not in self.usyms: self.usyms.append(s) # List of all LR items for the production self.lr_items = [] self.lr_next = None # Create a string representation if self.prod: self.str = "%s -> %s" % (self.name," ".join(self.prod)) else: self.str = "%s -> " % self.name def __str__(self): return self.str def __repr__(self): return "Production("+str(self)+")" def __len__(self): return len(self.prod) def __nonzero__(self): return 1 def __getitem__(self,index): return self.prod[index] # Return the nth lr_item from the production (or None if at the end) def lr_item(self,n): if n > len(self.prod): return None p = LRItem(self,n) # Precompute the list of productions immediately following. Hack. Remove later try: p.lr_after = Prodnames[p.prod[n+1]] except (IndexError,KeyError): p.lr_after = [] try: p.lr_before = p.prod[n-1] except IndexError: p.lr_before = None return p # Bind the production function name to a callable def bind(self,pdict): if self.func: self.callable = pdict[self.func] # This class serves as a minimal standin for Production objects when # reading table data from files. It only contains information # actually used by the LR parsing engine, plus some additional # debugging information. class MiniProduction(object): def __init__(self,str,name,len,func,file,line): self.name = name self.len = len self.func = func self.callable = None self.file = file self.line = line self.str = str def __str__(self): return self.str def __repr__(self): return "MiniProduction(%s)" % self.str # Bind the production function name to a callable def bind(self,pdict): if self.func: self.callable = pdict[self.func] # ----------------------------------------------------------------------------- # class LRItem # # This class represents a specific stage of parsing a production rule. For # example: # # expr : expr . PLUS term # # In the above, the "." represents the current location of the parse. Here # basic attributes: # # name - Name of the production. For example 'expr' # prod - A list of symbols on the right side ['expr','.', 'PLUS','term'] # number - Production number. # # lr_next Next LR item. Example, if we are ' expr -> expr . PLUS term' # then lr_next refers to 'expr -> expr PLUS . term' # lr_index - LR item index (location of the ".") in the prod list. # lookaheads - LALR lookahead symbols for this item # len - Length of the production (number of symbols on right hand side) # lr_after - List of all productions that immediately follow # lr_before - Grammar symbol immediately before # ----------------------------------------------------------------------------- class LRItem(object): def __init__(self,p,n): self.name = p.name self.prod = list(p.prod) self.number = p.number self.lr_index = n self.lookaheads = { } self.prod.insert(n,".") self.prod = tuple(self.prod) self.len = len(self.prod) self.usyms = p.usyms def __str__(self): if self.prod: s = "%s -> %s" % (self.name," ".join(self.prod)) else: s = "%s -> " % self.name return s def __repr__(self): return "LRItem("+str(self)+")" # ----------------------------------------------------------------------------- # rightmost_terminal() # # Return the rightmost terminal from a list of symbols. Used in add_production() # ----------------------------------------------------------------------------- def rightmost_terminal(symbols, terminals): i = len(symbols) - 1 while i >= 0: if symbols[i] in terminals: return symbols[i] i -= 1 return None # ----------------------------------------------------------------------------- # === GRAMMAR CLASS === # # The following class represents the contents of the specified grammar along # with various computed properties such as first sets, follow sets, LR items, etc. # This data is used for critical parts of the table generation process later. # ----------------------------------------------------------------------------- class GrammarError(YaccError): pass class Grammar(object): def __init__(self,terminals): self.Productions = [None] # A list of all of the productions. The first # entry is always reserved for the purpose of # building an augmented grammar self.Prodnames = { } # A dictionary mapping the names of nonterminals to a list of all # productions of that nonterminal. self.Prodmap = { } # A dictionary that is only used to detect duplicate # productions. self.Terminals = { } # A dictionary mapping the names of terminal symbols to a # list of the rules where they are used. for term in terminals: self.Terminals[term] = [] self.Terminals['error'] = [] self.Nonterminals = { } # A dictionary mapping names of nonterminals to a list # of rule numbers where they are used. self.First = { } # A dictionary of precomputed FIRST(x) symbols self.Follow = { } # A dictionary of precomputed FOLLOW(x) symbols self.Precedence = { } # Precedence rules for each terminal. Contains tuples of the # form ('right',level) or ('nonassoc', level) or ('left',level) self.UsedPrecedence = { } # Precedence rules that were actually used by the grammer. # This is only used to provide error checking and to generate # a warning about unused precedence rules. self.Start = None # Starting symbol for the grammar def __len__(self): return len(self.Productions) def __getitem__(self,index): return self.Productions[index] # ----------------------------------------------------------------------------- # set_precedence() # # Sets the precedence for a given terminal. assoc is the associativity such as # 'left','right', or 'nonassoc'. level is a numeric level. # # ----------------------------------------------------------------------------- def set_precedence(self,term,assoc,level): assert self.Productions == [None],"Must call set_precedence() before add_production()" if term in self.Precedence: raise GrammarError("Precedence already specified for terminal '%s'" % term) if assoc not in ['left','right','nonassoc']: raise GrammarError("Associativity must be one of 'left','right', or 'nonassoc'") self.Precedence[term] = (assoc,level) # ----------------------------------------------------------------------------- # add_production() # # Given an action function, this function assembles a production rule and # computes its precedence level. # # The production rule is supplied as a list of symbols. For example, # a rule such as 'expr : expr PLUS term' has a production name of 'expr' and # symbols ['expr','PLUS','term']. # # Precedence is determined by the precedence of the right-most non-terminal # or the precedence of a terminal specified by %prec. # # A variety of error checks are performed to make sure production symbols # are valid and that %prec is used correctly. # ----------------------------------------------------------------------------- def add_production(self,prodname,syms,func=None,file='',line=0): if prodname in self.Terminals: raise GrammarError("%s:%d: Illegal rule name '%s'. Already defined as a token" % (file,line,prodname)) if prodname == 'error': raise GrammarError("%s:%d: Illegal rule name '%s'. error is a reserved word" % (file,line,prodname)) if not _is_identifier.match(prodname): raise GrammarError("%s:%d: Illegal rule name '%s'" % (file,line,prodname)) # Look for literal tokens for n,s in enumerate(syms): if s[0] in "'\"": try: c = eval(s) if (len(c) > 1): raise GrammarError("%s:%d: Literal token %s in rule '%s' may only be a single character" % (file,line,s, prodname)) if not c in self.Terminals: self.Terminals[c] = [] syms[n] = c continue except SyntaxError: pass if not _is_identifier.match(s) and s != '%prec': raise GrammarError("%s:%d: Illegal name '%s' in rule '%s'" % (file,line,s, prodname)) # Determine the precedence level if '%prec' in syms: if syms[-1] == '%prec': raise GrammarError("%s:%d: Syntax error. Nothing follows %%prec" % (file,line)) if syms[-2] != '%prec': raise GrammarError("%s:%d: Syntax error. %%prec can only appear at the end of a grammar rule" % (file,line)) precname = syms[-1] prodprec = self.Precedence.get(precname,None) if not prodprec: raise GrammarError("%s:%d: Nothing known about the precedence of '%s'" % (file,line,precname)) else: self.UsedPrecedence[precname] = 1 del syms[-2:] # Drop %prec from the rule else: # If no %prec, precedence is determined by the rightmost terminal symbol precname = rightmost_terminal(syms,self.Terminals) prodprec = self.Precedence.get(precname,('right',0)) # See if the rule is already in the rulemap map = "%s -> %s" % (prodname,syms) if map in self.Prodmap: m = self.Prodmap[map] raise GrammarError("%s:%d: Duplicate rule %s. " % (file,line, m) + "Previous definition at %s:%d" % (m.file, m.line)) # From this point on, everything is valid. Create a new Production instance pnumber = len(self.Productions) if not prodname in self.Nonterminals: self.Nonterminals[prodname] = [ ] # Add the production number to Terminals and Nonterminals for t in syms: if t in self.Terminals: self.Terminals[t].append(pnumber) else: if not t in self.Nonterminals: self.Nonterminals[t] = [ ] self.Nonterminals[t].append(pnumber) # Create a production and add it to the list of productions p = Production(pnumber,prodname,syms,prodprec,func,file,line) self.Productions.append(p) self.Prodmap[map] = p # Add to the global productions list try: self.Prodnames[prodname].append(p) except KeyError: self.Prodnames[prodname] = [ p ] return 0 # ----------------------------------------------------------------------------- # set_start() # # Sets the starting symbol and creates the augmented grammar. Production # rule 0 is S' -> start where start is the start symbol. # ----------------------------------------------------------------------------- def set_start(self,start=None): if not start: start = self.Productions[1].name if start not in self.Nonterminals: raise GrammarError("start symbol %s undefined" % start) self.Productions[0] = Production(0,"S'",[start]) self.Nonterminals[start].append(0) self.Start = start # ----------------------------------------------------------------------------- # find_unreachable() # # Find all of the nonterminal symbols that can't be reached from the starting # symbol. Returns a list of nonterminals that can't be reached. # ----------------------------------------------------------------------------- def find_unreachable(self): # Mark all symbols that are reachable from a symbol s def mark_reachable_from(s): if reachable[s]: # We've already reached symbol s. return reachable[s] = 1 for p in self.Prodnames.get(s,[]): for r in p.prod: mark_reachable_from(r) reachable = { } for s in list(self.Terminals) + list(self.Nonterminals): reachable[s] = 0 mark_reachable_from( self.Productions[0].prod[0] ) return [s for s in list(self.Nonterminals) if not reachable[s]] # ----------------------------------------------------------------------------- # infinite_cycles() # # This function looks at the various parsing rules and tries to detect # infinite recursion cycles (grammar rules where there is no possible way # to derive a string of only terminals). # ----------------------------------------------------------------------------- def infinite_cycles(self): terminates = {} # Terminals: for t in self.Terminals: terminates[t] = 1 terminates['$end'] = 1 # Nonterminals: # Initialize to false: for n in self.Nonterminals: terminates[n] = 0 # Then propagate termination until no change: while 1: some_change = 0 for (n,pl) in self.Prodnames.items(): # Nonterminal n terminates iff any of its productions terminates. for p in pl: # Production p terminates iff all of its rhs symbols terminate. for s in p.prod: if not terminates[s]: # The symbol s does not terminate, # so production p does not terminate. p_terminates = 0 break else: # didn't break from the loop, # so every symbol s terminates # so production p terminates. p_terminates = 1 if p_terminates: # symbol n terminates! if not terminates[n]: terminates[n] = 1 some_change = 1 # Don't need to consider any more productions for this n. break if not some_change: break infinite = [] for (s,term) in terminates.items(): if not term: if not s in self.Prodnames and not s in self.Terminals and s != 'error': # s is used-but-not-defined, and we've already warned of that, # so it would be overkill to say that it's also non-terminating. pass else: infinite.append(s) return infinite # ----------------------------------------------------------------------------- # undefined_symbols() # # Find all symbols that were used the grammar, but not defined as tokens or # grammar rules. Returns a list of tuples (sym, prod) where sym in the symbol # and prod is the production where the symbol was used. # ----------------------------------------------------------------------------- def undefined_symbols(self): result = [] for p in self.Productions: if not p: continue for s in p.prod: if not s in self.Prodnames and not s in self.Terminals and s != 'error': result.append((s,p)) return result # ----------------------------------------------------------------------------- # unused_terminals() # # Find all terminals that were defined, but not used by the grammar. Returns # a list of all symbols. # ----------------------------------------------------------------------------- def unused_terminals(self): unused_tok = [] for s,v in self.Terminals.items(): if s != 'error' and not v: unused_tok.append(s) return unused_tok # ------------------------------------------------------------------------------ # unused_rules() # # Find all grammar rules that were defined, but not used (maybe not reachable) # Returns a list of productions. # ------------------------------------------------------------------------------ def unused_rules(self): unused_prod = [] for s,v in self.Nonterminals.items(): if not v: p = self.Prodnames[s][0] unused_prod.append(p) return unused_prod # ----------------------------------------------------------------------------- # unused_precedence() # # Returns a list of tuples (term,precedence) corresponding to precedence # rules that were never used by the grammar. term is the name of the terminal # on which precedence was applied and precedence is a string such as 'left' or # 'right' corresponding to the type of precedence. # ----------------------------------------------------------------------------- def unused_precedence(self): unused = [] for termname in self.Precedence: if not (termname in self.Terminals or termname in self.UsedPrecedence): unused.append((termname,self.Precedence[termname][0])) return unused # ------------------------------------------------------------------------- # _first() # # Compute the value of FIRST1(beta) where beta is a tuple of symbols. # # During execution of compute_first1, the result may be incomplete. # Afterward (e.g., when called from compute_follow()), it will be complete. # ------------------------------------------------------------------------- def _first(self,beta): # We are computing First(x1,x2,x3,...,xn) result = [ ] for x in beta: x_produces_empty = 0 # Add all the non- symbols of First[x] to the result. for f in self.First[x]: if f == '': x_produces_empty = 1 else: if f not in result: result.append(f) if x_produces_empty: # We have to consider the next x in beta, # i.e. stay in the loop. pass else: # We don't have to consider any further symbols in beta. break else: # There was no 'break' from the loop, # so x_produces_empty was true for all x in beta, # so beta produces empty as well. result.append('') return result # ------------------------------------------------------------------------- # compute_first() # # Compute the value of FIRST1(X) for all symbols # ------------------------------------------------------------------------- def compute_first(self): if self.First: return self.First # Terminals: for t in self.Terminals: self.First[t] = [t] self.First['$end'] = ['$end'] # Nonterminals: # Initialize to the empty set: for n in self.Nonterminals: self.First[n] = [] # Then propagate symbols until no change: while 1: some_change = 0 for n in self.Nonterminals: for p in self.Prodnames[n]: for f in self._first(p.prod): if f not in self.First[n]: self.First[n].append( f ) some_change = 1 if not some_change: break return self.First # --------------------------------------------------------------------- # compute_follow() # # Computes all of the follow sets for every non-terminal symbol. The # follow set is the set of all symbols that might follow a given # non-terminal. See the Dragon book, 2nd Ed. p. 189. # --------------------------------------------------------------------- def compute_follow(self,start=None): # If already computed, return the result if self.Follow: return self.Follow # If first sets not computed yet, do that first. if not self.First: self.compute_first() # Add '$end' to the follow list of the start symbol for k in self.Nonterminals: self.Follow[k] = [ ] if not start: start = self.Productions[1].name self.Follow[start] = [ '$end' ] while 1: didadd = 0 for p in self.Productions[1:]: # Here is the production set for i in range(len(p.prod)): B = p.prod[i] if B in self.Nonterminals: # Okay. We got a non-terminal in a production fst = self._first(p.prod[i+1:]) hasempty = 0 for f in fst: if f != '' and f not in self.Follow[B]: self.Follow[B].append(f) didadd = 1 if f == '': hasempty = 1 if hasempty or i == (len(p.prod)-1): # Add elements of follow(a) to follow(b) for f in self.Follow[p.name]: if f not in self.Follow[B]: self.Follow[B].append(f) didadd = 1 if not didadd: break return self.Follow # ----------------------------------------------------------------------------- # build_lritems() # # This function walks the list of productions and builds a complete set of the # LR items. The LR items are stored in two ways: First, they are uniquely # numbered and placed in the list _lritems. Second, a linked list of LR items # is built for each production. For example: # # E -> E PLUS E # # Creates the list # # [E -> . E PLUS E, E -> E . PLUS E, E -> E PLUS . E, E -> E PLUS E . ] # ----------------------------------------------------------------------------- def build_lritems(self): for p in self.Productions: lastlri = p i = 0 lr_items = [] while 1: if i > len(p): lri = None else: lri = LRItem(p,i) # Precompute the list of productions immediately following try: lri.lr_after = self.Prodnames[lri.prod[i+1]] except (IndexError,KeyError): lri.lr_after = [] try: lri.lr_before = lri.prod[i-1] except IndexError: lri.lr_before = None lastlri.lr_next = lri if not lri: break lr_items.append(lri) lastlri = lri i += 1 p.lr_items = lr_items # ----------------------------------------------------------------------------- # == Class LRTable == # # This basic class represents a basic table of LR parsing information. # Methods for generating the tables are not defined here. They are defined # in the derived class LRGeneratedTable. # ----------------------------------------------------------------------------- class VersionError(YaccError): pass class LRTable(object): def __init__(self): self.lr_action = None self.lr_goto = None self.lr_productions = None self.lr_method = None def read_table(self,module): if isinstance(module,types.ModuleType): parsetab = module else: if sys.version_info[0] < 3: exec("import %s as parsetab" % module) else: env = { } exec("import %s as parsetab" % module, env, env) parsetab = env['parsetab'] if parsetab._tabversion != __tabversion__: raise VersionError("yacc table file version is out of date") self.lr_action = parsetab._lr_action self.lr_goto = parsetab._lr_goto self.lr_productions = [] for p in parsetab._lr_productions: self.lr_productions.append(MiniProduction(*p)) self.lr_method = parsetab._lr_method return parsetab._lr_signature def read_pickle(self,filename): try: import cPickle as pickle except ImportError: import pickle in_f = open(filename,"rb") tabversion = pickle.load(in_f) if tabversion != __tabversion__: raise VersionError("yacc table file version is out of date") self.lr_method = pickle.load(in_f) signature = pickle.load(in_f) self.lr_action = pickle.load(in_f) self.lr_goto = pickle.load(in_f) productions = pickle.load(in_f) self.lr_productions = [] for p in productions: self.lr_productions.append(MiniProduction(*p)) in_f.close() return signature # Bind all production function names to callable objects in pdict def bind_callables(self,pdict): for p in self.lr_productions: p.bind(pdict) # ----------------------------------------------------------------------------- # === LR Generator === # # The following classes and functions are used to generate LR parsing tables on # a grammar. # ----------------------------------------------------------------------------- # ----------------------------------------------------------------------------- # digraph() # traverse() # # The following two functions are used to compute set valued functions # of the form: # # F(x) = F'(x) U U{F(y) | x R y} # # This is used to compute the values of Read() sets as well as FOLLOW sets # in LALR(1) generation. # # Inputs: X - An input set # R - A relation # FP - Set-valued function # ------------------------------------------------------------------------------ def digraph(X,R,FP): N = { } for x in X: N[x] = 0 stack = [] F = { } for x in X: if N[x] == 0: traverse(x,N,stack,F,X,R,FP) return F def traverse(x,N,stack,F,X,R,FP): stack.append(x) d = len(stack) N[x] = d F[x] = FP(x) # F(X) <- F'(x) rel = R(x) # Get y's related to x for y in rel: if N[y] == 0: traverse(y,N,stack,F,X,R,FP) N[x] = min(N[x],N[y]) for a in F.get(y,[]): if a not in F[x]: F[x].append(a) if N[x] == d: N[stack[-1]] = MAXINT F[stack[-1]] = F[x] element = stack.pop() while element != x: N[stack[-1]] = MAXINT F[stack[-1]] = F[x] element = stack.pop() class LALRError(YaccError): pass # ----------------------------------------------------------------------------- # == LRGeneratedTable == # # This class implements the LR table generation algorithm. There are no # public methods except for write() # ----------------------------------------------------------------------------- class LRGeneratedTable(LRTable): def __init__(self,grammar,method='LALR',log=None): if method not in ['SLR','LALR']: raise LALRError("Unsupported method %s" % method) self.grammar = grammar self.lr_method = method # Set up the logger if not log: log = NullLogger() self.log = log # Internal attributes self.lr_action = {} # Action table self.lr_goto = {} # Goto table self.lr_productions = grammar.Productions # Copy of grammar Production array self.lr_goto_cache = {} # Cache of computed gotos self.lr0_cidhash = {} # Cache of closures self._add_count = 0 # Internal counter used to detect cycles # Diagonistic information filled in by the table generator self.sr_conflict = 0 self.rr_conflict = 0 self.conflicts = [] # List of conflicts self.sr_conflicts = [] self.rr_conflicts = [] # Build the tables self.grammar.build_lritems() self.grammar.compute_first() self.grammar.compute_follow() self.lr_parse_table() # Compute the LR(0) closure operation on I, where I is a set of LR(0) items. def lr0_closure(self,I): self._add_count += 1 # Add everything in I to J J = I[:] didadd = 1 while didadd: didadd = 0 for j in J: for x in j.lr_after: if getattr(x,"lr0_added",0) == self._add_count: continue # Add B --> .G to J J.append(x.lr_next) x.lr0_added = self._add_count didadd = 1 return J # Compute the LR(0) goto function goto(I,X) where I is a set # of LR(0) items and X is a grammar symbol. This function is written # in a way that guarantees uniqueness of the generated goto sets # (i.e. the same goto set will never be returned as two different Python # objects). With uniqueness, we can later do fast set comparisons using # id(obj) instead of element-wise comparison. def lr0_goto(self,I,x): # First we look for a previously cached entry g = self.lr_goto_cache.get((id(I),x),None) if g: return g # Now we generate the goto set in a way that guarantees uniqueness # of the result s = self.lr_goto_cache.get(x,None) if not s: s = { } self.lr_goto_cache[x] = s gs = [ ] for p in I: n = p.lr_next if n and n.lr_before == x: s1 = s.get(id(n),None) if not s1: s1 = { } s[id(n)] = s1 gs.append(n) s = s1 g = s.get('$end',None) if not g: if gs: g = self.lr0_closure(gs) s['$end'] = g else: s['$end'] = gs self.lr_goto_cache[(id(I),x)] = g return g # Compute the LR(0) sets of item function def lr0_items(self): C = [ self.lr0_closure([self.grammar.Productions[0].lr_next]) ] i = 0 for I in C: self.lr0_cidhash[id(I)] = i i += 1 # Loop over the items in C and each grammar symbols i = 0 while i < len(C): I = C[i] i += 1 # Collect all of the symbols that could possibly be in the goto(I,X) sets asyms = { } for ii in I: for s in ii.usyms: asyms[s] = None for x in asyms: g = self.lr0_goto(I,x) if not g: continue if id(g) in self.lr0_cidhash: continue self.lr0_cidhash[id(g)] = len(C) C.append(g) return C # ----------------------------------------------------------------------------- # ==== LALR(1) Parsing ==== # # LALR(1) parsing is almost exactly the same as SLR except that instead of # relying upon Follow() sets when performing reductions, a more selective # lookahead set that incorporates the state of the LR(0) machine is utilized. # Thus, we mainly just have to focus on calculating the lookahead sets. # # The method used here is due to DeRemer and Pennelo (1982). # # DeRemer, F. L., and T. J. Pennelo: "Efficient Computation of LALR(1) # Lookahead Sets", ACM Transactions on Programming Languages and Systems, # Vol. 4, No. 4, Oct. 1982, pp. 615-649 # # Further details can also be found in: # # J. Tremblay and P. Sorenson, "The Theory and Practice of Compiler Writing", # McGraw-Hill Book Company, (1985). # # ----------------------------------------------------------------------------- # ----------------------------------------------------------------------------- # compute_nullable_nonterminals() # # Creates a dictionary containing all of the non-terminals that might produce # an empty production. # ----------------------------------------------------------------------------- def compute_nullable_nonterminals(self): nullable = {} num_nullable = 0 while 1: for p in self.grammar.Productions[1:]: if p.len == 0: nullable[p.name] = 1 continue for t in p.prod: if not t in nullable: break else: nullable[p.name] = 1 if len(nullable) == num_nullable: break num_nullable = len(nullable) return nullable # ----------------------------------------------------------------------------- # find_nonterminal_trans(C) # # Given a set of LR(0) items, this functions finds all of the non-terminal # transitions. These are transitions in which a dot appears immediately before # a non-terminal. Returns a list of tuples of the form (state,N) where state # is the state number and N is the nonterminal symbol. # # The input C is the set of LR(0) items. # ----------------------------------------------------------------------------- def find_nonterminal_transitions(self,C): trans = [] for state in range(len(C)): for p in C[state]: if p.lr_index < p.len - 1: t = (state,p.prod[p.lr_index+1]) if t[1] in self.grammar.Nonterminals: if t not in trans: trans.append(t) state = state + 1 return trans # ----------------------------------------------------------------------------- # dr_relation() # # Computes the DR(p,A) relationships for non-terminal transitions. The input # is a tuple (state,N) where state is a number and N is a nonterminal symbol. # # Returns a list of terminals. # ----------------------------------------------------------------------------- def dr_relation(self,C,trans,nullable): dr_set = { } state,N = trans terms = [] g = self.lr0_goto(C[state],N) for p in g: if p.lr_index < p.len - 1: a = p.prod[p.lr_index+1] if a in self.grammar.Terminals: if a not in terms: terms.append(a) # This extra bit is to handle the start state if state == 0 and N == self.grammar.Productions[0].prod[0]: terms.append('$end') return terms # ----------------------------------------------------------------------------- # reads_relation() # # Computes the READS() relation (p,A) READS (t,C). # ----------------------------------------------------------------------------- def reads_relation(self,C, trans, empty): # Look for empty transitions rel = [] state, N = trans g = self.lr0_goto(C[state],N) j = self.lr0_cidhash.get(id(g),-1) for p in g: if p.lr_index < p.len - 1: a = p.prod[p.lr_index + 1] if a in empty: rel.append((j,a)) return rel # ----------------------------------------------------------------------------- # compute_lookback_includes() # # Determines the lookback and includes relations # # LOOKBACK: # # This relation is determined by running the LR(0) state machine forward. # For example, starting with a production "N : . A B C", we run it forward # to obtain "N : A B C ." We then build a relationship between this final # state and the starting state. These relationships are stored in a dictionary # lookdict. # # INCLUDES: # # Computes the INCLUDE() relation (p,A) INCLUDES (p',B). # # This relation is used to determine non-terminal transitions that occur # inside of other non-terminal transition states. (p,A) INCLUDES (p', B) # if the following holds: # # B -> LAT, where T -> epsilon and p' -L-> p # # L is essentially a prefix (which may be empty), T is a suffix that must be # able to derive an empty string. State p' must lead to state p with the string L. # # ----------------------------------------------------------------------------- def compute_lookback_includes(self,C,trans,nullable): lookdict = {} # Dictionary of lookback relations includedict = {} # Dictionary of include relations # Make a dictionary of non-terminal transitions dtrans = {} for t in trans: dtrans[t] = 1 # Loop over all transitions and compute lookbacks and includes for state,N in trans: lookb = [] includes = [] for p in C[state]: if p.name != N: continue # Okay, we have a name match. We now follow the production all the way # through the state machine until we get the . on the right hand side lr_index = p.lr_index j = state while lr_index < p.len - 1: lr_index = lr_index + 1 t = p.prod[lr_index] # Check to see if this symbol and state are a non-terminal transition if (j,t) in dtrans: # Yes. Okay, there is some chance that this is an includes relation # the only way to know for certain is whether the rest of the # production derives empty li = lr_index + 1 while li < p.len: if p.prod[li] in self.grammar.Terminals: break # No forget it if not p.prod[li] in nullable: break li = li + 1 else: # Appears to be a relation between (j,t) and (state,N) includes.append((j,t)) g = self.lr0_goto(C[j],t) # Go to next set j = self.lr0_cidhash.get(id(g),-1) # Go to next state # When we get here, j is the final state, now we have to locate the production for r in C[j]: if r.name != p.name: continue if r.len != p.len: continue i = 0 # This look is comparing a production ". A B C" with "A B C ." while i < r.lr_index: if r.prod[i] != p.prod[i+1]: break i = i + 1 else: lookb.append((j,r)) for i in includes: if not i in includedict: includedict[i] = [] includedict[i].append((state,N)) lookdict[(state,N)] = lookb return lookdict,includedict # ----------------------------------------------------------------------------- # compute_read_sets() # # Given a set of LR(0) items, this function computes the read sets. # # Inputs: C = Set of LR(0) items # ntrans = Set of nonterminal transitions # nullable = Set of empty transitions # # Returns a set containing the read sets # ----------------------------------------------------------------------------- def compute_read_sets(self,C, ntrans, nullable): FP = lambda x: self.dr_relation(C,x,nullable) R = lambda x: self.reads_relation(C,x,nullable) F = digraph(ntrans,R,FP) return F # ----------------------------------------------------------------------------- # compute_follow_sets() # # Given a set of LR(0) items, a set of non-terminal transitions, a readset, # and an include set, this function computes the follow sets # # Follow(p,A) = Read(p,A) U U {Follow(p',B) | (p,A) INCLUDES (p',B)} # # Inputs: # ntrans = Set of nonterminal transitions # readsets = Readset (previously computed) # inclsets = Include sets (previously computed) # # Returns a set containing the follow sets # ----------------------------------------------------------------------------- def compute_follow_sets(self,ntrans,readsets,inclsets): FP = lambda x: readsets[x] R = lambda x: inclsets.get(x,[]) F = digraph(ntrans,R,FP) return F # ----------------------------------------------------------------------------- # add_lookaheads() # # Attaches the lookahead symbols to grammar rules. # # Inputs: lookbacks - Set of lookback relations # followset - Computed follow set # # This function directly attaches the lookaheads to productions contained # in the lookbacks set # ----------------------------------------------------------------------------- def add_lookaheads(self,lookbacks,followset): for trans,lb in lookbacks.items(): # Loop over productions in lookback for state,p in lb: if not state in p.lookaheads: p.lookaheads[state] = [] f = followset.get(trans,[]) for a in f: if a not in p.lookaheads[state]: p.lookaheads[state].append(a) # ----------------------------------------------------------------------------- # add_lalr_lookaheads() # # This function does all of the work of adding lookahead information for use # with LALR parsing # ----------------------------------------------------------------------------- def add_lalr_lookaheads(self,C): # Determine all of the nullable nonterminals nullable = self.compute_nullable_nonterminals() # Find all non-terminal transitions trans = self.find_nonterminal_transitions(C) # Compute read sets readsets = self.compute_read_sets(C,trans,nullable) # Compute lookback/includes relations lookd, included = self.compute_lookback_includes(C,trans,nullable) # Compute LALR FOLLOW sets followsets = self.compute_follow_sets(trans,readsets,included) # Add all of the lookaheads self.add_lookaheads(lookd,followsets) # ----------------------------------------------------------------------------- # lr_parse_table() # # This function constructs the parse tables for SLR or LALR # ----------------------------------------------------------------------------- def lr_parse_table(self): Productions = self.grammar.Productions Precedence = self.grammar.Precedence goto = self.lr_goto # Goto array action = self.lr_action # Action array log = self.log # Logger for output actionp = { } # Action production array (temporary) log.info("Parsing method: %s", self.lr_method) # Step 1: Construct C = { I0, I1, ... IN}, collection of LR(0) items # This determines the number of states C = self.lr0_items() if self.lr_method == 'LALR': self.add_lalr_lookaheads(C) # Build the parser table, state by state st = 0 for I in C: # Loop over each production in I actlist = [ ] # List of actions st_action = { } st_actionp = { } st_goto = { } log.info("") log.info("state %d", st) log.info("") for p in I: log.info(" (%d) %s", p.number, str(p)) log.info("") for p in I: if p.len == p.lr_index + 1: if p.name == "S'": # Start symbol. Accept! st_action["$end"] = 0 st_actionp["$end"] = p else: # We are at the end of a production. Reduce! if self.lr_method == 'LALR': laheads = p.lookaheads[st] else: laheads = self.grammar.Follow[p.name] for a in laheads: actlist.append((a,p,"reduce using rule %d (%s)" % (p.number,p))) r = st_action.get(a,None) if r is not None: # Whoa. Have a shift/reduce or reduce/reduce conflict if r > 0: # Need to decide on shift or reduce here # By default we favor shifting. Need to add # some precedence rules here. sprec,slevel = Productions[st_actionp[a].number].prec rprec,rlevel = Precedence.get(a,('right',0)) if (slevel < rlevel) or ((slevel == rlevel) and (rprec == 'left')): # We really need to reduce here. st_action[a] = -p.number st_actionp[a] = p if not slevel and not rlevel: log.info(" ! shift/reduce conflict for %s resolved as reduce",a) self.sr_conflicts.append((st,a,'reduce')) Productions[p.number].reduced += 1 elif (slevel == rlevel) and (rprec == 'nonassoc'): st_action[a] = None else: # Hmmm. Guess we'll keep the shift if not rlevel: log.info(" ! shift/reduce conflict for %s resolved as shift",a) self.sr_conflicts.append((st,a,'shift')) elif r < 0: # Reduce/reduce conflict. In this case, we favor the rule # that was defined first in the grammar file oldp = Productions[-r] pp = Productions[p.number] if oldp.line > pp.line: st_action[a] = -p.number st_actionp[a] = p chosenp,rejectp = pp,oldp Productions[p.number].reduced += 1 Productions[oldp.number].reduced -= 1 else: chosenp,rejectp = oldp,pp self.rr_conflicts.append((st,chosenp,rejectp)) log.info(" ! reduce/reduce conflict for %s resolved using rule %d (%s)", a,st_actionp[a].number, st_actionp[a]) else: raise LALRError("Unknown conflict in state %d" % st) else: st_action[a] = -p.number st_actionp[a] = p Productions[p.number].reduced += 1 else: i = p.lr_index a = p.prod[i+1] # Get symbol right after the "." if a in self.grammar.Terminals: g = self.lr0_goto(I,a) j = self.lr0_cidhash.get(id(g),-1) if j >= 0: # We are in a shift state actlist.append((a,p,"shift and go to state %d" % j)) r = st_action.get(a,None) if r is not None: # Whoa have a shift/reduce or shift/shift conflict if r > 0: if r != j: raise LALRError("Shift/shift conflict in state %d" % st) elif r < 0: # Do a precedence check. # - if precedence of reduce rule is higher, we reduce. # - if precedence of reduce is same and left assoc, we reduce. # - otherwise we shift rprec,rlevel = Productions[st_actionp[a].number].prec sprec,slevel = Precedence.get(a,('right',0)) if (slevel > rlevel) or ((slevel == rlevel) and (rprec == 'right')): # We decide to shift here... highest precedence to shift Productions[st_actionp[a].number].reduced -= 1 st_action[a] = j st_actionp[a] = p if not rlevel: log.info(" ! shift/reduce conflict for %s resolved as shift",a) self.sr_conflicts.append((st,a,'shift')) elif (slevel == rlevel) and (rprec == 'nonassoc'): st_action[a] = None else: # Hmmm. Guess we'll keep the reduce if not slevel and not rlevel: log.info(" ! shift/reduce conflict for %s resolved as reduce",a) self.sr_conflicts.append((st,a,'reduce')) else: raise LALRError("Unknown conflict in state %d" % st) else: st_action[a] = j st_actionp[a] = p # Print the actions associated with each terminal _actprint = { } for a,p,m in actlist: if a in st_action: if p is st_actionp[a]: log.info(" %-15s %s",a,m) _actprint[(a,m)] = 1 log.info("") # Print the actions that were not used. (debugging) not_used = 0 for a,p,m in actlist: if a in st_action: if p is not st_actionp[a]: if not (a,m) in _actprint: log.debug(" ! %-15s [ %s ]",a,m) not_used = 1 _actprint[(a,m)] = 1 if not_used: log.debug("") # Construct the goto table for this state nkeys = { } for ii in I: for s in ii.usyms: if s in self.grammar.Nonterminals: nkeys[s] = None for n in nkeys: g = self.lr0_goto(I,n) j = self.lr0_cidhash.get(id(g),-1) if j >= 0: st_goto[n] = j log.info(" %-30s shift and go to state %d",n,j) action[st] = st_action actionp[st] = st_actionp goto[st] = st_goto st += 1 # ----------------------------------------------------------------------------- # write() # # This function writes the LR parsing tables to a file # ----------------------------------------------------------------------------- def write_table(self,modulename,outputdir='',signature=""): basemodulename = modulename.split(".")[-1] filename = os.path.join(outputdir,basemodulename) + ".py" try: f = open(filename,"w") f.write(""" # %s # This file is automatically generated. Do not edit. _tabversion = %r _lr_method = %r _lr_signature = %r """ % (filename, __tabversion__, self.lr_method, signature)) # Change smaller to 0 to go back to original tables smaller = 1 # Factor out names to try and make smaller if smaller: items = { } for s,nd in self.lr_action.items(): for name,v in nd.items(): i = items.get(name) if not i: i = ([],[]) items[name] = i i[0].append(s) i[1].append(v) f.write("\n_lr_action_items = {") for k,v in items.items(): f.write("%r:([" % k) for i in v[0]: f.write("%r," % i) f.write("],[") for i in v[1]: f.write("%r," % i) f.write("]),") f.write("}\n") f.write(""" _lr_action = { } for _k, _v in _lr_action_items.items(): for _x,_y in zip(_v[0],_v[1]): if not _x in _lr_action: _lr_action[_x] = { } _lr_action[_x][_k] = _y del _lr_action_items """) else: f.write("\n_lr_action = { "); for k,v in self.lr_action.items(): f.write("(%r,%r):%r," % (k[0],k[1],v)) f.write("}\n"); if smaller: # Factor out names to try and make smaller items = { } for s,nd in self.lr_goto.items(): for name,v in nd.items(): i = items.get(name) if not i: i = ([],[]) items[name] = i i[0].append(s) i[1].append(v) f.write("\n_lr_goto_items = {") for k,v in items.items(): f.write("%r:([" % k) for i in v[0]: f.write("%r," % i) f.write("],[") for i in v[1]: f.write("%r," % i) f.write("]),") f.write("}\n") f.write(""" _lr_goto = { } for _k, _v in _lr_goto_items.items(): for _x,_y in zip(_v[0],_v[1]): if not _x in _lr_goto: _lr_goto[_x] = { } _lr_goto[_x][_k] = _y del _lr_goto_items """) else: f.write("\n_lr_goto = { "); for k,v in self.lr_goto.items(): f.write("(%r,%r):%r," % (k[0],k[1],v)) f.write("}\n"); # Write production table f.write("_lr_productions = [\n") for p in self.lr_productions: if p.func: f.write(" (%r,%r,%d,%r,%r,%d),\n" % (p.str,p.name, p.len, p.func,p.file,p.line)) else: f.write(" (%r,%r,%d,None,None,None),\n" % (str(p),p.name, p.len)) f.write("]\n") f.close() except IOError: e = sys.exc_info()[1] sys.stderr.write("Unable to create '%s'\n" % filename) sys.stderr.write(str(e)+"\n") return # ----------------------------------------------------------------------------- # pickle_table() # # This function pickles the LR parsing tables to a supplied file object # ----------------------------------------------------------------------------- def pickle_table(self,filename,signature=""): try: import cPickle as pickle except ImportError: import pickle outf = open(filename,"wb") pickle.dump(__tabversion__,outf,pickle_protocol) pickle.dump(self.lr_method,outf,pickle_protocol) pickle.dump(signature,outf,pickle_protocol) pickle.dump(self.lr_action,outf,pickle_protocol) pickle.dump(self.lr_goto,outf,pickle_protocol) outp = [] for p in self.lr_productions: if p.func: outp.append((p.str,p.name, p.len, p.func,p.file,p.line)) else: outp.append((str(p),p.name,p.len,None,None,None)) pickle.dump(outp,outf,pickle_protocol) outf.close() # ----------------------------------------------------------------------------- # === INTROSPECTION === # # The following functions and classes are used to implement the PLY # introspection features followed by the yacc() function itself. # ----------------------------------------------------------------------------- # ----------------------------------------------------------------------------- # get_caller_module_dict() # # This function returns a dictionary containing all of the symbols defined within # a caller further down the call stack. This is used to get the environment # associated with the yacc() call if none was provided. # ----------------------------------------------------------------------------- def get_caller_module_dict(levels): try: raise RuntimeError except RuntimeError: e,b,t = sys.exc_info() f = t.tb_frame while levels > 0: f = f.f_back levels -= 1 ldict = f.f_globals.copy() if f.f_globals != f.f_locals: ldict.update(f.f_locals) return ldict # ----------------------------------------------------------------------------- # parse_grammar() # # This takes a raw grammar rule string and parses it into production data # ----------------------------------------------------------------------------- def parse_grammar(doc,file,line): grammar = [] # Split the doc string into lines pstrings = doc.splitlines() lastp = None dline = line for ps in pstrings: dline += 1 p = ps.split() if not p: continue try: if p[0] == '|': # This is a continuation of a previous rule if not lastp: raise SyntaxError("%s:%d: Misplaced '|'" % (file,dline)) prodname = lastp syms = p[1:] else: prodname = p[0] lastp = prodname syms = p[2:] assign = p[1] if assign != ':' and assign != '::=': raise SyntaxError("%s:%d: Syntax error. Expected ':'" % (file,dline)) grammar.append((file,dline,prodname,syms)) except SyntaxError: raise except Exception: raise SyntaxError("%s:%d: Syntax error in rule '%s'" % (file,dline,ps.strip())) return grammar # ----------------------------------------------------------------------------- # ParserReflect() # # This class represents information extracted for building a parser including # start symbol, error function, tokens, precedence list, action functions, # etc. # ----------------------------------------------------------------------------- class ParserReflect(object): def __init__(self,pdict,log=None): self.pdict = pdict self.start = None self.error_func = None self.tokens = None self.files = {} self.grammar = [] self.error = 0 if log is None: self.log = PlyLogger(sys.stderr) else: self.log = log # Get all of the basic information def get_all(self): self.get_start() self.get_error_func() self.get_tokens() self.get_precedence() self.get_pfunctions() # Validate all of the information def validate_all(self): self.validate_start() self.validate_error_func() self.validate_tokens() self.validate_precedence() self.validate_pfunctions() self.validate_files() return self.error # Compute a signature over the grammar def signature(self): try: from hashlib import md5 except ImportError: from md5 import md5 try: sig = md5() if self.start: sig.update(self.start.encode('latin-1')) if self.prec: sig.update("".join(["".join(p) for p in self.prec]).encode('latin-1')) if self.tokens: sig.update(" ".join(self.tokens).encode('latin-1')) for f in self.pfuncs: if f[3]: sig.update(f[3].encode('latin-1')) except (TypeError,ValueError): pass return sig.digest() # ----------------------------------------------------------------------------- # validate_file() # # This method checks to see if there are duplicated p_rulename() functions # in the parser module file. Without this function, it is really easy for # users to make mistakes by cutting and pasting code fragments (and it's a real # bugger to try and figure out why the resulting parser doesn't work). Therefore, # we just do a little regular expression pattern matching of def statements # to try and detect duplicates. # ----------------------------------------------------------------------------- def validate_files(self): # Match def p_funcname( fre = re.compile(r'\s*def\s+(p_[a-zA-Z_0-9]*)\(') for filename in self.files.keys(): base,ext = os.path.splitext(filename) if ext != '.py': return 1 # No idea. Assume it's okay. try: f = open(filename) lines = f.readlines() f.close() except IOError: continue counthash = { } for linen,l in enumerate(lines): linen += 1 m = fre.match(l) if m: name = m.group(1) prev = counthash.get(name) if not prev: counthash[name] = linen else: self.log.warning("%s:%d: Function %s redefined. Previously defined on line %d", filename,linen,name,prev) # Get the start symbol def get_start(self): self.start = self.pdict.get('start') # Validate the start symbol def validate_start(self): if self.start is not None: if not isinstance(self.start,str): self.log.error("'start' must be a string") # Look for error handler def get_error_func(self): self.error_func = self.pdict.get('p_error') # Validate the error function def validate_error_func(self): if self.error_func: if isinstance(self.error_func,types.FunctionType): ismethod = 0 elif isinstance(self.error_func, types.MethodType): ismethod = 1 else: self.log.error("'p_error' defined, but is not a function or method") self.error = 1 return eline = func_code(self.error_func).co_firstlineno efile = func_code(self.error_func).co_filename self.files[efile] = 1 if (func_code(self.error_func).co_argcount != 1+ismethod): self.log.error("%s:%d: p_error() requires 1 argument",efile,eline) self.error = 1 # Get the tokens map def get_tokens(self): tokens = self.pdict.get("tokens",None) if not tokens: self.log.error("No token list is defined") self.error = 1 return if not isinstance(tokens,(list, tuple)): self.log.error("tokens must be a list or tuple") self.error = 1 return if not tokens: self.log.error("tokens is empty") self.error = 1 return self.tokens = tokens # Validate the tokens def validate_tokens(self): # Validate the tokens. if 'error' in self.tokens: self.log.error("Illegal token name 'error'. Is a reserved word") self.error = 1 return terminals = {} for n in self.tokens: if n in terminals: self.log.warning("Token '%s' multiply defined", n) terminals[n] = 1 # Get the precedence map (if any) def get_precedence(self): self.prec = self.pdict.get("precedence",None) # Validate and parse the precedence map def validate_precedence(self): preclist = [] if self.prec: if not isinstance(self.prec,(list,tuple)): self.log.error("precedence must be a list or tuple") self.error = 1 return for level,p in enumerate(self.prec): if not isinstance(p,(list,tuple)): self.log.error("Bad precedence table") self.error = 1 return if len(p) < 2: self.log.error("Malformed precedence entry %s. Must be (assoc, term, ..., term)",p) self.error = 1 return assoc = p[0] if not isinstance(assoc,str): self.log.error("precedence associativity must be a string") self.error = 1 return for term in p[1:]: if not isinstance(term,str): self.log.error("precedence items must be strings") self.error = 1 return preclist.append((term,assoc,level+1)) self.preclist = preclist # Get all p_functions from the grammar def get_pfunctions(self): p_functions = [] for name, item in self.pdict.items(): if name[:2] != 'p_': continue if name == 'p_error': continue if isinstance(item,(types.FunctionType,types.MethodType)): line = func_code(item).co_firstlineno file = func_code(item).co_filename p_functions.append((line,file,name,item.__doc__)) # Sort all of the actions by line number p_functions.sort() self.pfuncs = p_functions # Validate all of the p_functions def validate_pfunctions(self): grammar = [] # Check for non-empty symbols if len(self.pfuncs) == 0: self.log.error("no rules of the form p_rulename are defined") self.error = 1 return for line, file, name, doc in self.pfuncs: func = self.pdict[name] if isinstance(func, types.MethodType): reqargs = 2 else: reqargs = 1 if func_code(func).co_argcount > reqargs: self.log.error("%s:%d: Rule '%s' has too many arguments",file,line,func.__name__) self.error = 1 elif func_code(func).co_argcount < reqargs: self.log.error("%s:%d: Rule '%s' requires an argument",file,line,func.__name__) self.error = 1 elif not func.__doc__: self.log.warning("%s:%d: No documentation string specified in function '%s' (ignored)",file,line,func.__name__) else: try: parsed_g = parse_grammar(doc,file,line) for g in parsed_g: grammar.append((name, g)) except SyntaxError: e = sys.exc_info()[1] self.log.error(str(e)) self.error = 1 # Looks like a valid grammar rule # Mark the file in which defined. self.files[file] = 1 # Secondary validation step that looks for p_ definitions that are not functions # or functions that look like they might be grammar rules. for n,v in self.pdict.items(): if n[0:2] == 'p_' and isinstance(v, (types.FunctionType, types.MethodType)): continue if n[0:2] == 't_': continue if n[0:2] == 'p_' and n != 'p_error': self.log.warning("'%s' not defined as a function", n) if ((isinstance(v,types.FunctionType) and func_code(v).co_argcount == 1) or (isinstance(v,types.MethodType) and func_code(v).co_argcount == 2)): try: doc = v.__doc__.split(" ") if doc[1] == ':': self.log.warning("%s:%d: Possible grammar rule '%s' defined without p_ prefix", func_code(v).co_filename, func_code(v).co_firstlineno,n) except Exception: pass self.grammar = grammar # ----------------------------------------------------------------------------- # yacc(module) # # Build a parser # ----------------------------------------------------------------------------- def yacc(method='LALR', debug=yaccdebug, module=None, tabmodule=tab_module, start=None, check_recursion=1, optimize=0, write_tables=1, debugfile=debug_file,outputdir='', debuglog=None, errorlog = None, picklefile=None): global parse # Reference to the parsing method of the last built parser # If pickling is enabled, table files are not created if picklefile: write_tables = 0 if errorlog is None: errorlog = PlyLogger(sys.stderr) # Get the module dictionary used for the parser if module: _items = [(k,getattr(module,k)) for k in dir(module)] pdict = dict(_items) else: pdict = get_caller_module_dict(2) # Collect parser information from the dictionary pinfo = ParserReflect(pdict,log=errorlog) pinfo.get_all() if pinfo.error: raise YaccError("Unable to build parser") # Check signature against table files (if any) signature = pinfo.signature() # Read the tables try: lr = LRTable() if picklefile: read_signature = lr.read_pickle(picklefile) else: read_signature = lr.read_table(tabmodule) if optimize or (read_signature == signature): try: lr.bind_callables(pinfo.pdict) parser = LRParser(lr,pinfo.error_func) parse = parser.parse return parser except Exception: e = sys.exc_info()[1] errorlog.warning("There was a problem loading the table file: %s", repr(e)) except VersionError: e = sys.exc_info() errorlog.warning(str(e)) except Exception: pass if debuglog is None: if debug: debuglog = PlyLogger(open(debugfile,"w")) else: debuglog = NullLogger() debuglog.info("Created by PLY version %s (http://www.dabeaz.com/ply)", __version__) errors = 0 # Validate the parser information if pinfo.validate_all(): raise YaccError("Unable to build parser") if not pinfo.error_func: errorlog.warning("no p_error() function is defined") # Create a grammar object grammar = Grammar(pinfo.tokens) # Set precedence level for terminals for term, assoc, level in pinfo.preclist: try: grammar.set_precedence(term,assoc,level) except GrammarError: e = sys.exc_info()[1] errorlog.warning("%s",str(e)) # Add productions to the grammar for funcname, gram in pinfo.grammar: file, line, prodname, syms = gram try: grammar.add_production(prodname,syms,funcname,file,line) except GrammarError: e = sys.exc_info()[1] errorlog.error("%s",str(e)) errors = 1 # Set the grammar start symbols try: if start is None: grammar.set_start(pinfo.start) else: grammar.set_start(start) except GrammarError: e = sys.exc_info()[1] errorlog.error(str(e)) errors = 1 if errors: raise YaccError("Unable to build parser") # Verify the grammar structure undefined_symbols = grammar.undefined_symbols() for sym, prod in undefined_symbols: errorlog.error("%s:%d: Symbol '%s' used, but not defined as a token or a rule",prod.file,prod.line,sym) errors = 1 unused_terminals = grammar.unused_terminals() if unused_terminals: debuglog.info("") debuglog.info("Unused terminals:") debuglog.info("") for term in unused_terminals: errorlog.warning("Token '%s' defined, but not used", term) debuglog.info(" %s", term) # Print out all productions to the debug log if debug: debuglog.info("") debuglog.info("Grammar") debuglog.info("") for n,p in enumerate(grammar.Productions): debuglog.info("Rule %-5d %s", n, p) # Find unused non-terminals unused_rules = grammar.unused_rules() for prod in unused_rules: errorlog.warning("%s:%d: Rule '%s' defined, but not used", prod.file, prod.line, prod.name) if len(unused_terminals) == 1: errorlog.warning("There is 1 unused token") if len(unused_terminals) > 1: errorlog.warning("There are %d unused tokens", len(unused_terminals)) if len(unused_rules) == 1: errorlog.warning("There is 1 unused rule") if len(unused_rules) > 1: errorlog.warning("There are %d unused rules", len(unused_rules)) if debug: debuglog.info("") debuglog.info("Terminals, with rules where they appear") debuglog.info("") terms = list(grammar.Terminals) terms.sort() for term in terms: debuglog.info("%-20s : %s", term, " ".join([str(s) for s in grammar.Terminals[term]])) debuglog.info("") debuglog.info("Nonterminals, with rules where they appear") debuglog.info("") nonterms = list(grammar.Nonterminals) nonterms.sort() for nonterm in nonterms: debuglog.info("%-20s : %s", nonterm, " ".join([str(s) for s in grammar.Nonterminals[nonterm]])) debuglog.info("") if check_recursion: unreachable = grammar.find_unreachable() for u in unreachable: errorlog.warning("Symbol '%s' is unreachable",u) infinite = grammar.infinite_cycles() for inf in infinite: errorlog.error("Infinite recursion detected for symbol '%s'", inf) errors = 1 unused_prec = grammar.unused_precedence() for term, assoc in unused_prec: errorlog.error("Precedence rule '%s' defined for unknown symbol '%s'", assoc, term) errors = 1 if errors: raise YaccError("Unable to build parser") # Run the LRGeneratedTable on the grammar if debug: errorlog.debug("Generating %s tables", method) lr = LRGeneratedTable(grammar,method,debuglog) if debug: num_sr = len(lr.sr_conflicts) # Report shift/reduce and reduce/reduce conflicts if num_sr == 1: errorlog.warning("1 shift/reduce conflict") elif num_sr > 1: errorlog.warning("%d shift/reduce conflicts", num_sr) num_rr = len(lr.rr_conflicts) if num_rr == 1: errorlog.warning("1 reduce/reduce conflict") elif num_rr > 1: errorlog.warning("%d reduce/reduce conflicts", num_rr) # Write out conflicts to the output file if debug and (lr.sr_conflicts or lr.rr_conflicts): debuglog.warning("") debuglog.warning("Conflicts:") debuglog.warning("") for state, tok, resolution in lr.sr_conflicts: debuglog.warning("shift/reduce conflict for %s in state %d resolved as %s", tok, state, resolution) already_reported = {} for state, rule, rejected in lr.rr_conflicts: if (state,id(rule),id(rejected)) in already_reported: continue debuglog.warning("reduce/reduce conflict in state %d resolved using rule (%s)", state, rule) debuglog.warning("rejected rule (%s) in state %d", rejected,state) errorlog.warning("reduce/reduce conflict in state %d resolved using rule (%s)", state, rule) errorlog.warning("rejected rule (%s) in state %d", rejected, state) already_reported[state,id(rule),id(rejected)] = 1 warned_never = [] for state, rule, rejected in lr.rr_conflicts: if not rejected.reduced and (rejected not in warned_never): debuglog.warning("Rule (%s) is never reduced", rejected) errorlog.warning("Rule (%s) is never reduced", rejected) warned_never.append(rejected) # Write the table file if requested if write_tables: lr.write_table(tabmodule,outputdir,signature) # Write a pickled version of the tables if picklefile: lr.pickle_table(picklefile,signature) # Build the parser lr.bind_callables(pinfo.pdict) parser = LRParser(lr,pinfo.error_func) parse = parser.parse return parser ./CBFlib-0.9.2.2/ply-3.2/ply/cpp.py0000644000076500007650000010042211603702121014636 0ustar yayayaya# ----------------------------------------------------------------------------- # cpp.py # # Author: David Beazley (http://www.dabeaz.com) # Copyright (C) 2007 # All rights reserved # # This module implements an ANSI-C style lexical preprocessor for PLY. # ----------------------------------------------------------------------------- from __future__ import generators # ----------------------------------------------------------------------------- # Default preprocessor lexer definitions. These tokens are enough to get # a basic preprocessor working. Other modules may import these if they want # ----------------------------------------------------------------------------- tokens = ( 'CPP_ID','CPP_INTEGER', 'CPP_FLOAT', 'CPP_STRING', 'CPP_CHAR', 'CPP_WS', 'CPP_COMMENT', 'CPP_POUND','CPP_DPOUND' ) literals = "+-*/%|&~^<>=!?()[]{}.,;:\\\'\"" # Whitespace def t_CPP_WS(t): r'\s+' t.lexer.lineno += t.value.count("\n") return t t_CPP_POUND = r'\#' t_CPP_DPOUND = r'\#\#' # Identifier t_CPP_ID = r'[A-Za-z_][\w_]*' # Integer literal def CPP_INTEGER(t): r'(((((0x)|(0X))[0-9a-fA-F]+)|(\d+))([uU]|[lL]|[uU][lL]|[lL][uU])?)' return t t_CPP_INTEGER = CPP_INTEGER # Floating literal t_CPP_FLOAT = r'((\d+)(\.\d+)(e(\+|-)?(\d+))? | (\d+)e(\+|-)?(\d+))([lL]|[fF])?' # String literal def t_CPP_STRING(t): r'\"([^\\\n]|(\\(.|\n)))*?\"' t.lexer.lineno += t.value.count("\n") return t # Character constant 'c' or L'c' def t_CPP_CHAR(t): r'(L)?\'([^\\\n]|(\\(.|\n)))*?\'' t.lexer.lineno += t.value.count("\n") return t # Comment def t_CPP_COMMENT(t): r'(/\*(.|\n)*?\*/)|(//.*?\n)' t.lexer.lineno += t.value.count("\n") return t def t_error(t): t.type = t.value[0] t.value = t.value[0] t.lexer.skip(1) return t import re import copy import time import os.path # ----------------------------------------------------------------------------- # trigraph() # # Given an input string, this function replaces all trigraph sequences. # The following mapping is used: # # ??= # # ??/ \ # ??' ^ # ??( [ # ??) ] # ??! | # ??< { # ??> } # ??- ~ # ----------------------------------------------------------------------------- _trigraph_pat = re.compile(r'''\?\?[=/\'\(\)\!<>\-]''') _trigraph_rep = { '=':'#', '/':'\\', "'":'^', '(':'[', ')':']', '!':'|', '<':'{', '>':'}', '-':'~' } def trigraph(input): return _trigraph_pat.sub(lambda g: _trigraph_rep[g.group()[-1]],input) # ------------------------------------------------------------------ # Macro object # # This object holds information about preprocessor macros # # .name - Macro name (string) # .value - Macro value (a list of tokens) # .arglist - List of argument names # .variadic - Boolean indicating whether or not variadic macro # .vararg - Name of the variadic parameter # # When a macro is created, the macro replacement token sequence is # pre-scanned and used to create patch lists that are later used # during macro expansion # ------------------------------------------------------------------ class Macro(object): def __init__(self,name,value,arglist=None,variadic=False): self.name = name self.value = value self.arglist = arglist self.variadic = variadic if variadic: self.vararg = arglist[-1] self.source = None # ------------------------------------------------------------------ # Preprocessor object # # Object representing a preprocessor. Contains macro definitions, # include directories, and other information # ------------------------------------------------------------------ class Preprocessor(object): def __init__(self,lexer=None): if lexer is None: lexer = lex.lexer self.lexer = lexer self.macros = { } self.path = [] self.temp_path = [] # Probe the lexer for selected tokens self.lexprobe() tm = time.localtime() self.define("__DATE__ \"%s\"" % time.strftime("%b %d %Y",tm)) self.define("__TIME__ \"%s\"" % time.strftime("%H:%M:%S",tm)) self.parser = None # ----------------------------------------------------------------------------- # tokenize() # # Utility function. Given a string of text, tokenize into a list of tokens # ----------------------------------------------------------------------------- def tokenize(self,text): tokens = [] self.lexer.input(text) while True: tok = self.lexer.token() if not tok: break tokens.append(tok) return tokens # --------------------------------------------------------------------- # error() # # Report a preprocessor error/warning of some kind # ---------------------------------------------------------------------- def error(self,file,line,msg): print >>sys.stderr,"%s:%d %s" % (file,line,msg) # ---------------------------------------------------------------------- # lexprobe() # # This method probes the preprocessor lexer object to discover # the token types of symbols that are important to the preprocessor. # If this works right, the preprocessor will simply "work" # with any suitable lexer regardless of how tokens have been named. # ---------------------------------------------------------------------- def lexprobe(self): # Determine the token type for identifiers self.lexer.input("identifier") tok = self.lexer.token() if not tok or tok.value != "identifier": print "Couldn't determine identifier type" else: self.t_ID = tok.type # Determine the token type for integers self.lexer.input("12345") tok = self.lexer.token() if not tok or int(tok.value) != 12345: print "Couldn't determine integer type" else: self.t_INTEGER = tok.type self.t_INTEGER_TYPE = type(tok.value) # Determine the token type for strings enclosed in double quotes self.lexer.input("\"filename\"") tok = self.lexer.token() if not tok or tok.value != "\"filename\"": print "Couldn't determine string type" else: self.t_STRING = tok.type # Determine the token type for whitespace--if any self.lexer.input(" ") tok = self.lexer.token() if not tok or tok.value != " ": self.t_SPACE = None else: self.t_SPACE = tok.type # Determine the token type for newlines self.lexer.input("\n") tok = self.lexer.token() if not tok or tok.value != "\n": self.t_NEWLINE = None print "Couldn't determine token for newlines" else: self.t_NEWLINE = tok.type self.t_WS = (self.t_SPACE, self.t_NEWLINE) # Check for other characters used by the preprocessor chars = [ '<','>','#','##','\\','(',')',',','.'] for c in chars: self.lexer.input(c) tok = self.lexer.token() if not tok or tok.value != c: print "Unable to lex '%s' required for preprocessor" % c # ---------------------------------------------------------------------- # add_path() # # Adds a search path to the preprocessor. # ---------------------------------------------------------------------- def add_path(self,path): self.path.append(path) # ---------------------------------------------------------------------- # group_lines() # # Given an input string, this function splits it into lines. Trailing whitespace # is removed. Any line ending with \ is grouped with the next line. This # function forms the lowest level of the preprocessor---grouping into text into # a line-by-line format. # ---------------------------------------------------------------------- def group_lines(self,input): lex = self.lexer.clone() lines = [x.rstrip() for x in input.splitlines()] for i in xrange(len(lines)): j = i+1 while lines[i].endswith('\\') and (j < len(lines)): lines[i] = lines[i][:-1]+lines[j] lines[j] = "" j += 1 input = "\n".join(lines) lex.input(input) lex.lineno = 1 current_line = [] while True: tok = lex.token() if not tok: break current_line.append(tok) if tok.type in self.t_WS and '\n' in tok.value: yield current_line current_line = [] if current_line: yield current_line # ---------------------------------------------------------------------- # tokenstrip() # # Remove leading/trailing whitespace tokens from a token list # ---------------------------------------------------------------------- def tokenstrip(self,tokens): i = 0 while i < len(tokens) and tokens[i].type in self.t_WS: i += 1 del tokens[:i] i = len(tokens)-1 while i >= 0 and tokens[i].type in self.t_WS: i -= 1 del tokens[i+1:] return tokens # ---------------------------------------------------------------------- # collect_args() # # Collects comma separated arguments from a list of tokens. The arguments # must be enclosed in parenthesis. Returns a tuple (tokencount,args,positions) # where tokencount is the number of tokens consumed, args is a list of arguments, # and positions is a list of integers containing the starting index of each # argument. Each argument is represented by a list of tokens. # # When collecting arguments, leading and trailing whitespace is removed # from each argument. # # This function properly handles nested parenthesis and commas---these do not # define new arguments. # ---------------------------------------------------------------------- def collect_args(self,tokenlist): args = [] positions = [] current_arg = [] nesting = 1 tokenlen = len(tokenlist) # Search for the opening '('. i = 0 while (i < tokenlen) and (tokenlist[i].type in self.t_WS): i += 1 if (i < tokenlen) and (tokenlist[i].value == '('): positions.append(i+1) else: self.error(self.source,tokenlist[0].lineno,"Missing '(' in macro arguments") return 0, [], [] i += 1 while i < tokenlen: t = tokenlist[i] if t.value == '(': current_arg.append(t) nesting += 1 elif t.value == ')': nesting -= 1 if nesting == 0: if current_arg: args.append(self.tokenstrip(current_arg)) positions.append(i) return i+1,args,positions current_arg.append(t) elif t.value == ',' and nesting == 1: args.append(self.tokenstrip(current_arg)) positions.append(i+1) current_arg = [] else: current_arg.append(t) i += 1 # Missing end argument self.error(self.source,tokenlist[-1].lineno,"Missing ')' in macro arguments") return 0, [],[] # ---------------------------------------------------------------------- # macro_prescan() # # Examine the macro value (token sequence) and identify patch points # This is used to speed up macro expansion later on---we'll know # right away where to apply patches to the value to form the expansion # ---------------------------------------------------------------------- def macro_prescan(self,macro): macro.patch = [] # Standard macro arguments macro.str_patch = [] # String conversion expansion macro.var_comma_patch = [] # Variadic macro comma patch i = 0 while i < len(macro.value): if macro.value[i].type == self.t_ID and macro.value[i].value in macro.arglist: argnum = macro.arglist.index(macro.value[i].value) # Conversion of argument to a string if i > 0 and macro.value[i-1].value == '#': macro.value[i] = copy.copy(macro.value[i]) macro.value[i].type = self.t_STRING del macro.value[i-1] macro.str_patch.append((argnum,i-1)) continue # Concatenation elif (i > 0 and macro.value[i-1].value == '##'): macro.patch.append(('c',argnum,i-1)) del macro.value[i-1] continue elif ((i+1) < len(macro.value) and macro.value[i+1].value == '##'): macro.patch.append(('c',argnum,i)) i += 1 continue # Standard expansion else: macro.patch.append(('e',argnum,i)) elif macro.value[i].value == '##': if macro.variadic and (i > 0) and (macro.value[i-1].value == ',') and \ ((i+1) < len(macro.value)) and (macro.value[i+1].type == self.t_ID) and \ (macro.value[i+1].value == macro.vararg): macro.var_comma_patch.append(i-1) i += 1 macro.patch.sort(key=lambda x: x[2],reverse=True) # ---------------------------------------------------------------------- # macro_expand_args() # # Given a Macro and list of arguments (each a token list), this method # returns an expanded version of a macro. The return value is a token sequence # representing the replacement macro tokens # ---------------------------------------------------------------------- def macro_expand_args(self,macro,args): # Make a copy of the macro token sequence rep = [copy.copy(_x) for _x in macro.value] # Make string expansion patches. These do not alter the length of the replacement sequence str_expansion = {} for argnum, i in macro.str_patch: if argnum not in str_expansion: str_expansion[argnum] = ('"%s"' % "".join([x.value for x in args[argnum]])).replace("\\","\\\\") rep[i] = copy.copy(rep[i]) rep[i].value = str_expansion[argnum] # Make the variadic macro comma patch. If the variadic macro argument is empty, we get rid comma_patch = False if macro.variadic and not args[-1]: for i in macro.var_comma_patch: rep[i] = None comma_patch = True # Make all other patches. The order of these matters. It is assumed that the patch list # has been sorted in reverse order of patch location since replacements will cause the # size of the replacement sequence to expand from the patch point. expanded = { } for ptype, argnum, i in macro.patch: # Concatenation. Argument is left unexpanded if ptype == 'c': rep[i:i+1] = args[argnum] # Normal expansion. Argument is macro expanded first elif ptype == 'e': if argnum not in expanded: expanded[argnum] = self.expand_macros(args[argnum]) rep[i:i+1] = expanded[argnum] # Get rid of removed comma if necessary if comma_patch: rep = [_i for _i in rep if _i] return rep # ---------------------------------------------------------------------- # expand_macros() # # Given a list of tokens, this function performs macro expansion. # The expanded argument is a dictionary that contains macros already # expanded. This is used to prevent infinite recursion. # ---------------------------------------------------------------------- def expand_macros(self,tokens,expanded=None): if expanded is None: expanded = {} i = 0 while i < len(tokens): t = tokens[i] if t.type == self.t_ID: if t.value in self.macros and t.value not in expanded: # Yes, we found a macro match expanded[t.value] = True m = self.macros[t.value] if not m.arglist: # A simple macro ex = self.expand_macros([copy.copy(_x) for _x in m.value],expanded) for e in ex: e.lineno = t.lineno tokens[i:i+1] = ex i += len(ex) else: # A macro with arguments j = i + 1 while j < len(tokens) and tokens[j].type in self.t_WS: j += 1 if tokens[j].value == '(': tokcount,args,positions = self.collect_args(tokens[j:]) if not m.variadic and len(args) != len(m.arglist): self.error(self.source,t.lineno,"Macro %s requires %d arguments" % (t.value,len(m.arglist))) i = j + tokcount elif m.variadic and len(args) < len(m.arglist)-1: if len(m.arglist) > 2: self.error(self.source,t.lineno,"Macro %s must have at least %d arguments" % (t.value, len(m.arglist)-1)) else: self.error(self.source,t.lineno,"Macro %s must have at least %d argument" % (t.value, len(m.arglist)-1)) i = j + tokcount else: if m.variadic: if len(args) == len(m.arglist)-1: args.append([]) else: args[len(m.arglist)-1] = tokens[j+positions[len(m.arglist)-1]:j+tokcount-1] del args[len(m.arglist):] # Get macro replacement text rep = self.macro_expand_args(m,args) rep = self.expand_macros(rep,expanded) for r in rep: r.lineno = t.lineno tokens[i:j+tokcount] = rep i += len(rep) del expanded[t.value] continue elif t.value == '__LINE__': t.type = self.t_INTEGER t.value = self.t_INTEGER_TYPE(t.lineno) i += 1 return tokens # ---------------------------------------------------------------------- # evalexpr() # # Evaluate an expression token sequence for the purposes of evaluating # integral expressions. # ---------------------------------------------------------------------- def evalexpr(self,tokens): # tokens = tokenize(line) # Search for defined macros i = 0 while i < len(tokens): if tokens[i].type == self.t_ID and tokens[i].value == 'defined': j = i + 1 needparen = False result = "0L" while j < len(tokens): if tokens[j].type in self.t_WS: j += 1 continue elif tokens[j].type == self.t_ID: if tokens[j].value in self.macros: result = "1L" else: result = "0L" if not needparen: break elif tokens[j].value == '(': needparen = True elif tokens[j].value == ')': break else: self.error(self.source,tokens[i].lineno,"Malformed defined()") j += 1 tokens[i].type = self.t_INTEGER tokens[i].value = self.t_INTEGER_TYPE(result) del tokens[i+1:j+1] i += 1 tokens = self.expand_macros(tokens) for i,t in enumerate(tokens): if t.type == self.t_ID: tokens[i] = copy.copy(t) tokens[i].type = self.t_INTEGER tokens[i].value = self.t_INTEGER_TYPE("0L") elif t.type == self.t_INTEGER: tokens[i] = copy.copy(t) # Strip off any trailing suffixes tokens[i].value = str(tokens[i].value) while tokens[i].value[-1] not in "0123456789abcdefABCDEF": tokens[i].value = tokens[i].value[:-1] expr = "".join([str(x.value) for x in tokens]) expr = expr.replace("&&"," and ") expr = expr.replace("||"," or ") expr = expr.replace("!"," not ") try: result = eval(expr) except StandardError: self.error(self.source,tokens[0].lineno,"Couldn't evaluate expression") result = 0 return result # ---------------------------------------------------------------------- # parsegen() # # Parse an input string/ # ---------------------------------------------------------------------- def parsegen(self,input,source=None): # Replace trigraph sequences t = trigraph(input) lines = self.group_lines(t) if not source: source = "" self.define("__FILE__ \"%s\"" % source) self.source = source chunk = [] enable = True iftrigger = False ifstack = [] for x in lines: for i,tok in enumerate(x): if tok.type not in self.t_WS: break if tok.value == '#': # Preprocessor directive for tok in x: if tok in self.t_WS and '\n' in tok.value: chunk.append(tok) dirtokens = self.tokenstrip(x[i+1:]) if dirtokens: name = dirtokens[0].value args = self.tokenstrip(dirtokens[1:]) else: name = "" args = [] if name == 'define': if enable: for tok in self.expand_macros(chunk): yield tok chunk = [] self.define(args) elif name == 'include': if enable: for tok in self.expand_macros(chunk): yield tok chunk = [] oldfile = self.macros['__FILE__'] for tok in self.include(args): yield tok self.macros['__FILE__'] = oldfile self.source = source elif name == 'undef': if enable: for tok in self.expand_macros(chunk): yield tok chunk = [] self.undef(args) elif name == 'ifdef': ifstack.append((enable,iftrigger)) if enable: if not args[0].value in self.macros: enable = False iftrigger = False else: iftrigger = True elif name == 'ifndef': ifstack.append((enable,iftrigger)) if enable: if args[0].value in self.macros: enable = False iftrigger = False else: iftrigger = True elif name == 'if': ifstack.append((enable,iftrigger)) if enable: result = self.evalexpr(args) if not result: enable = False iftrigger = False else: iftrigger = True elif name == 'elif': if ifstack: if ifstack[-1][0]: # We only pay attention if outer "if" allows this if enable: # If already true, we flip enable False enable = False elif not iftrigger: # If False, but not triggered yet, we'll check expression result = self.evalexpr(args) if result: enable = True iftrigger = True else: self.error(self.source,dirtokens[0].lineno,"Misplaced #elif") elif name == 'else': if ifstack: if ifstack[-1][0]: if enable: enable = False elif not iftrigger: enable = True iftrigger = True else: self.error(self.source,dirtokens[0].lineno,"Misplaced #else") elif name == 'endif': if ifstack: enable,iftrigger = ifstack.pop() else: self.error(self.source,dirtokens[0].lineno,"Misplaced #endif") else: # Unknown preprocessor directive pass else: # Normal text if enable: chunk.extend(x) for tok in self.expand_macros(chunk): yield tok chunk = [] # ---------------------------------------------------------------------- # include() # # Implementation of file-inclusion # ---------------------------------------------------------------------- def include(self,tokens): # Try to extract the filename and then process an include file if not tokens: return if tokens: if tokens[0].value != '<' and tokens[0].type != self.t_STRING: tokens = self.expand_macros(tokens) if tokens[0].value == '<': # Include <...> i = 1 while i < len(tokens): if tokens[i].value == '>': break i += 1 else: print "Malformed #include <...>" return filename = "".join([x.value for x in tokens[1:i]]) path = self.path + [""] + self.temp_path elif tokens[0].type == self.t_STRING: filename = tokens[0].value[1:-1] path = self.temp_path + [""] + self.path else: print "Malformed #include statement" return for p in path: iname = os.path.join(p,filename) try: data = open(iname,"r").read() dname = os.path.dirname(iname) if dname: self.temp_path.insert(0,dname) for tok in self.parsegen(data,filename): yield tok if dname: del self.temp_path[0] break except IOError,e: pass else: print "Couldn't find '%s'" % filename # ---------------------------------------------------------------------- # define() # # Define a new macro # ---------------------------------------------------------------------- def define(self,tokens): if isinstance(tokens,(str,unicode)): tokens = self.tokenize(tokens) linetok = tokens try: name = linetok[0] if len(linetok) > 1: mtype = linetok[1] else: mtype = None if not mtype: m = Macro(name.value,[]) self.macros[name.value] = m elif mtype.type in self.t_WS: # A normal macro m = Macro(name.value,self.tokenstrip(linetok[2:])) self.macros[name.value] = m elif mtype.value == '(': # A macro with arguments tokcount, args, positions = self.collect_args(linetok[1:]) variadic = False for a in args: if variadic: print "No more arguments may follow a variadic argument" break astr = "".join([str(_i.value) for _i in a]) if astr == "...": variadic = True a[0].type = self.t_ID a[0].value = '__VA_ARGS__' variadic = True del a[1:] continue elif astr[-3:] == "..." and a[0].type == self.t_ID: variadic = True del a[1:] # If, for some reason, "." is part of the identifier, strip off the name for the purposes # of macro expansion if a[0].value[-3:] == '...': a[0].value = a[0].value[:-3] continue if len(a) > 1 or a[0].type != self.t_ID: print "Invalid macro argument" break else: mvalue = self.tokenstrip(linetok[1+tokcount:]) i = 0 while i < len(mvalue): if i+1 < len(mvalue): if mvalue[i].type in self.t_WS and mvalue[i+1].value == '##': del mvalue[i] continue elif mvalue[i].value == '##' and mvalue[i+1].type in self.t_WS: del mvalue[i+1] i += 1 m = Macro(name.value,mvalue,[x[0].value for x in args],variadic) self.macro_prescan(m) self.macros[name.value] = m else: print "Bad macro definition" except LookupError: print "Bad macro definition" # ---------------------------------------------------------------------- # undef() # # Undefine a macro # ---------------------------------------------------------------------- def undef(self,tokens): id = tokens[0].value try: del self.macros[id] except LookupError: pass # ---------------------------------------------------------------------- # parse() # # Parse input text. # ---------------------------------------------------------------------- def parse(self,input,source=None,ignore={}): self.ignore = ignore self.parser = self.parsegen(input,source) # ---------------------------------------------------------------------- # token() # # Method to return individual tokens # ---------------------------------------------------------------------- def token(self): try: while True: tok = self.parser.next() if tok.type not in self.ignore: return tok except StopIteration: self.parser = None return None if __name__ == '__main__': import ply.lex as lex lexer = lex.lex() # Run a preprocessor import sys f = open(sys.argv[1]) input = f.read() p = Preprocessor(lexer) p.parse(input,sys.argv[1]) while True: tok = p.token() if not tok: break print p.source, tok ./CBFlib-0.9.2.2/ply-3.2/ply/lex.py0000644000076500007650000011736611603702121014663 0ustar yayayaya# ----------------------------------------------------------------------------- # ply: lex.py # # Copyright (C) 2001-2009, # David M. Beazley (Dabeaz LLC) # All rights reserved. # # Redistribution and use in source and binary forms, with or without # modification, are permitted provided that the following conditions are # met: # # * Redistributions of source code must retain the above copyright notice, # this list of conditions and the following disclaimer. # * Redistributions in binary form must reproduce the above copyright notice, # this list of conditions and the following disclaimer in the documentation # and/or other materials provided with the distribution. # * Neither the name of the David Beazley or Dabeaz LLC may be used to # endorse or promote products derived from this software without # specific prior written permission. # # THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS # "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT # LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR # A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT # OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, # SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT # LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, # DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY # THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT # (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE # OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. # ----------------------------------------------------------------------------- __version__ = "3.2" __tabversion__ = "3.2" # Version of table file used import re, sys, types, copy, os # This tuple contains known string types try: # Python 2.6 StringTypes = (types.StringType, types.UnicodeType) except AttributeError: # Python 3.0 StringTypes = (str, bytes) # Extract the code attribute of a function. Different implementations # are for Python 2/3 compatibility. if sys.version_info[0] < 3: def func_code(f): return f.func_code else: def func_code(f): return f.__code__ # This regular expression is used to match valid token names _is_identifier = re.compile(r'^[a-zA-Z0-9_]+$') # Exception thrown when invalid token encountered and no default error # handler is defined. class LexError(Exception): def __init__(self,message,s): self.args = (message,) self.text = s # Token class. This class is used to represent the tokens produced. class LexToken(object): def __str__(self): return "LexToken(%s,%r,%d,%d)" % (self.type,self.value,self.lineno,self.lexpos) def __repr__(self): return str(self) # This object is a stand-in for a logging object created by the # logging module. class PlyLogger(object): def __init__(self,f): self.f = f def critical(self,msg,*args,**kwargs): self.f.write((msg % args) + "\n") def warning(self,msg,*args,**kwargs): self.f.write("WARNING: "+ (msg % args) + "\n") def error(self,msg,*args,**kwargs): self.f.write("ERROR: " + (msg % args) + "\n") info = critical debug = critical # Null logger is used when no output is generated. Does nothing. class NullLogger(object): def __getattribute__(self,name): return self def __call__(self,*args,**kwargs): return self # ----------------------------------------------------------------------------- # === Lexing Engine === # # The following Lexer class implements the lexer runtime. There are only # a few public methods and attributes: # # input() - Store a new string in the lexer # token() - Get the next token # clone() - Clone the lexer # # lineno - Current line number # lexpos - Current position in the input string # ----------------------------------------------------------------------------- class Lexer: def __init__(self): self.lexre = None # Master regular expression. This is a list of # tuples (re,findex) where re is a compiled # regular expression and findex is a list # mapping regex group numbers to rules self.lexretext = None # Current regular expression strings self.lexstatere = {} # Dictionary mapping lexer states to master regexs self.lexstateretext = {} # Dictionary mapping lexer states to regex strings self.lexstaterenames = {} # Dictionary mapping lexer states to symbol names self.lexstate = "INITIAL" # Current lexer state self.lexstatestack = [] # Stack of lexer states self.lexstateinfo = None # State information self.lexstateignore = {} # Dictionary of ignored characters for each state self.lexstateerrorf = {} # Dictionary of error functions for each state self.lexreflags = 0 # Optional re compile flags self.lexdata = None # Actual input data (as a string) self.lexpos = 0 # Current position in input text self.lexlen = 0 # Length of the input text self.lexerrorf = None # Error rule (if any) self.lextokens = None # List of valid tokens self.lexignore = "" # Ignored characters self.lexliterals = "" # Literal characters that can be passed through self.lexmodule = None # Module self.lineno = 1 # Current line number self.lexoptimize = 0 # Optimized mode def clone(self,object=None): c = copy.copy(self) # If the object parameter has been supplied, it means we are attaching the # lexer to a new object. In this case, we have to rebind all methods in # the lexstatere and lexstateerrorf tables. if object: newtab = { } for key, ritem in self.lexstatere.items(): newre = [] for cre, findex in ritem: newfindex = [] for f in findex: if not f or not f[0]: newfindex.append(f) continue newfindex.append((getattr(object,f[0].__name__),f[1])) newre.append((cre,newfindex)) newtab[key] = newre c.lexstatere = newtab c.lexstateerrorf = { } for key, ef in self.lexstateerrorf.items(): c.lexstateerrorf[key] = getattr(object,ef.__name__) c.lexmodule = object return c # ------------------------------------------------------------ # writetab() - Write lexer information to a table file # ------------------------------------------------------------ def writetab(self,tabfile,outputdir=""): if isinstance(tabfile,types.ModuleType): return basetabfilename = tabfile.split(".")[-1] filename = os.path.join(outputdir,basetabfilename)+".py" tf = open(filename,"w") tf.write("# %s.py. This file automatically created by PLY (version %s). Don't edit!\n" % (tabfile,__version__)) tf.write("_tabversion = %s\n" % repr(__version__)) tf.write("_lextokens = %s\n" % repr(self.lextokens)) tf.write("_lexreflags = %s\n" % repr(self.lexreflags)) tf.write("_lexliterals = %s\n" % repr(self.lexliterals)) tf.write("_lexstateinfo = %s\n" % repr(self.lexstateinfo)) tabre = { } # Collect all functions in the initial state initial = self.lexstatere["INITIAL"] initialfuncs = [] for part in initial: for f in part[1]: if f and f[0]: initialfuncs.append(f) for key, lre in self.lexstatere.items(): titem = [] for i in range(len(lre)): titem.append((self.lexstateretext[key][i],_funcs_to_names(lre[i][1],self.lexstaterenames[key][i]))) tabre[key] = titem tf.write("_lexstatere = %s\n" % repr(tabre)) tf.write("_lexstateignore = %s\n" % repr(self.lexstateignore)) taberr = { } for key, ef in self.lexstateerrorf.items(): if ef: taberr[key] = ef.__name__ else: taberr[key] = None tf.write("_lexstateerrorf = %s\n" % repr(taberr)) tf.close() # ------------------------------------------------------------ # readtab() - Read lexer information from a tab file # ------------------------------------------------------------ def readtab(self,tabfile,fdict): if isinstance(tabfile,types.ModuleType): lextab = tabfile else: if sys.version_info[0] < 3: exec("import %s as lextab" % tabfile) else: env = { } exec("import %s as lextab" % tabfile, env,env) lextab = env['lextab'] if getattr(lextab,"_tabversion","0.0") != __version__: raise ImportError("Inconsistent PLY version") self.lextokens = lextab._lextokens self.lexreflags = lextab._lexreflags self.lexliterals = lextab._lexliterals self.lexstateinfo = lextab._lexstateinfo self.lexstateignore = lextab._lexstateignore self.lexstatere = { } self.lexstateretext = { } for key,lre in lextab._lexstatere.items(): titem = [] txtitem = [] for i in range(len(lre)): titem.append((re.compile(lre[i][0],lextab._lexreflags),_names_to_funcs(lre[i][1],fdict))) txtitem.append(lre[i][0]) self.lexstatere[key] = titem self.lexstateretext[key] = txtitem self.lexstateerrorf = { } for key,ef in lextab._lexstateerrorf.items(): self.lexstateerrorf[key] = fdict[ef] self.begin('INITIAL') # ------------------------------------------------------------ # input() - Push a new string into the lexer # ------------------------------------------------------------ def input(self,s): # Pull off the first character to see if s looks like a string c = s[:1] if not isinstance(c,StringTypes): raise ValueError("Expected a string") self.lexdata = s self.lexpos = 0 self.lexlen = len(s) # ------------------------------------------------------------ # begin() - Changes the lexing state # ------------------------------------------------------------ def begin(self,state): if not state in self.lexstatere: raise ValueError("Undefined state") self.lexre = self.lexstatere[state] self.lexretext = self.lexstateretext[state] self.lexignore = self.lexstateignore.get(state,"") self.lexerrorf = self.lexstateerrorf.get(state,None) self.lexstate = state # ------------------------------------------------------------ # push_state() - Changes the lexing state and saves old on stack # ------------------------------------------------------------ def push_state(self,state): self.lexstatestack.append(self.lexstate) self.begin(state) # ------------------------------------------------------------ # pop_state() - Restores the previous state # ------------------------------------------------------------ def pop_state(self): self.begin(self.lexstatestack.pop()) # ------------------------------------------------------------ # current_state() - Returns the current lexing state # ------------------------------------------------------------ def current_state(self): return self.lexstate # ------------------------------------------------------------ # skip() - Skip ahead n characters # ------------------------------------------------------------ def skip(self,n): self.lexpos += n # ------------------------------------------------------------ # opttoken() - Return the next token from the Lexer # # Note: This function has been carefully implemented to be as fast # as possible. Don't make changes unless you really know what # you are doing # ------------------------------------------------------------ def token(self): # Make local copies of frequently referenced attributes lexpos = self.lexpos lexlen = self.lexlen lexignore = self.lexignore lexdata = self.lexdata while lexpos < lexlen: # This code provides some short-circuit code for whitespace, tabs, and other ignored characters if lexdata[lexpos] in lexignore: lexpos += 1 continue # Look for a regular expression match for lexre,lexindexfunc in self.lexre: m = lexre.match(lexdata,lexpos) if not m: continue # Create a token for return tok = LexToken() tok.value = m.group() tok.lineno = self.lineno tok.lexpos = lexpos i = m.lastindex func,tok.type = lexindexfunc[i] if not func: # If no token type was set, it's an ignored token if tok.type: self.lexpos = m.end() return tok else: lexpos = m.end() break lexpos = m.end() # If token is processed by a function, call it tok.lexer = self # Set additional attributes useful in token rules self.lexmatch = m self.lexpos = lexpos newtok = func(tok) # Every function must return a token, if nothing, we just move to next token if not newtok: lexpos = self.lexpos # This is here in case user has updated lexpos. lexignore = self.lexignore # This is here in case there was a state change break # Verify type of the token. If not in the token map, raise an error if not self.lexoptimize: if not newtok.type in self.lextokens: raise LexError("%s:%d: Rule '%s' returned an unknown token type '%s'" % ( func_code(func).co_filename, func_code(func).co_firstlineno, func.__name__, newtok.type),lexdata[lexpos:]) return newtok else: # No match, see if in literals if lexdata[lexpos] in self.lexliterals: tok = LexToken() tok.value = lexdata[lexpos] tok.lineno = self.lineno tok.type = tok.value tok.lexpos = lexpos self.lexpos = lexpos + 1 return tok # No match. Call t_error() if defined. if self.lexerrorf: tok = LexToken() tok.value = self.lexdata[lexpos:] tok.lineno = self.lineno tok.type = "error" tok.lexer = self tok.lexpos = lexpos self.lexpos = lexpos newtok = self.lexerrorf(tok) if lexpos == self.lexpos: # Error method didn't change text position at all. This is an error. raise LexError("Scanning error. Illegal character '%s'" % (lexdata[lexpos]), lexdata[lexpos:]) lexpos = self.lexpos if not newtok: continue return newtok self.lexpos = lexpos raise LexError("Illegal character '%s' at index %d" % (lexdata[lexpos],lexpos), lexdata[lexpos:]) self.lexpos = lexpos + 1 if self.lexdata is None: raise RuntimeError("No input string given with input()") return None # Iterator interface def __iter__(self): return self def next(self): t = self.token() if t is None: raise StopIteration return t __next__ = next # ----------------------------------------------------------------------------- # ==== Lex Builder === # # The functions and classes below are used to collect lexing information # and build a Lexer object from it. # ----------------------------------------------------------------------------- # ----------------------------------------------------------------------------- # get_caller_module_dict() # # This function returns a dictionary containing all of the symbols defined within # a caller further down the call stack. This is used to get the environment # associated with the yacc() call if none was provided. # ----------------------------------------------------------------------------- def get_caller_module_dict(levels): try: raise RuntimeError except RuntimeError: e,b,t = sys.exc_info() f = t.tb_frame while levels > 0: f = f.f_back levels -= 1 ldict = f.f_globals.copy() if f.f_globals != f.f_locals: ldict.update(f.f_locals) return ldict # ----------------------------------------------------------------------------- # _funcs_to_names() # # Given a list of regular expression functions, this converts it to a list # suitable for output to a table file # ----------------------------------------------------------------------------- def _funcs_to_names(funclist,namelist): result = [] for f,name in zip(funclist,namelist): if f and f[0]: result.append((name, f[1])) else: result.append(f) return result # ----------------------------------------------------------------------------- # _names_to_funcs() # # Given a list of regular expression function names, this converts it back to # functions. # ----------------------------------------------------------------------------- def _names_to_funcs(namelist,fdict): result = [] for n in namelist: if n and n[0]: result.append((fdict[n[0]],n[1])) else: result.append(n) return result # ----------------------------------------------------------------------------- # _form_master_re() # # This function takes a list of all of the regex components and attempts to # form the master regular expression. Given limitations in the Python re # module, it may be necessary to break the master regex into separate expressions. # ----------------------------------------------------------------------------- def _form_master_re(relist,reflags,ldict,toknames): if not relist: return [] regex = "|".join(relist) try: lexre = re.compile(regex,re.VERBOSE | reflags) # Build the index to function map for the matching engine lexindexfunc = [ None ] * (max(lexre.groupindex.values())+1) lexindexnames = lexindexfunc[:] for f,i in lexre.groupindex.items(): handle = ldict.get(f,None) if type(handle) in (types.FunctionType, types.MethodType): lexindexfunc[i] = (handle,toknames[f]) lexindexnames[i] = f elif handle is not None: lexindexnames[i] = f if f.find("ignore_") > 0: lexindexfunc[i] = (None,None) else: lexindexfunc[i] = (None, toknames[f]) return [(lexre,lexindexfunc)],[regex],[lexindexnames] except Exception: m = int(len(relist)/2) if m == 0: m = 1 llist, lre, lnames = _form_master_re(relist[:m],reflags,ldict,toknames) rlist, rre, rnames = _form_master_re(relist[m:],reflags,ldict,toknames) return llist+rlist, lre+rre, lnames+rnames # ----------------------------------------------------------------------------- # def _statetoken(s,names) # # Given a declaration name s of the form "t_" and a dictionary whose keys are # state names, this function returns a tuple (states,tokenname) where states # is a tuple of state names and tokenname is the name of the token. For example, # calling this with s = "t_foo_bar_SPAM" might return (('foo','bar'),'SPAM') # ----------------------------------------------------------------------------- def _statetoken(s,names): nonstate = 1 parts = s.split("_") for i in range(1,len(parts)): if not parts[i] in names and parts[i] != 'ANY': break if i > 1: states = tuple(parts[1:i]) else: states = ('INITIAL',) if 'ANY' in states: states = tuple(names) tokenname = "_".join(parts[i:]) return (states,tokenname) # ----------------------------------------------------------------------------- # LexerReflect() # # This class represents information needed to build a lexer as extracted from a # user's input file. # ----------------------------------------------------------------------------- class LexerReflect(object): def __init__(self,ldict,log=None,reflags=0): self.ldict = ldict self.error_func = None self.tokens = [] self.reflags = reflags self.stateinfo = { 'INITIAL' : 'inclusive'} self.files = {} self.error = 0 if log is None: self.log = PlyLogger(sys.stderr) else: self.log = log # Get all of the basic information def get_all(self): self.get_tokens() self.get_literals() self.get_states() self.get_rules() # Validate all of the information def validate_all(self): self.validate_tokens() self.validate_literals() self.validate_rules() return self.error # Get the tokens map def get_tokens(self): tokens = self.ldict.get("tokens",None) if not tokens: self.log.error("No token list is defined") self.error = 1 return if not isinstance(tokens,(list, tuple)): self.log.error("tokens must be a list or tuple") self.error = 1 return if not tokens: self.log.error("tokens is empty") self.error = 1 return self.tokens = tokens # Validate the tokens def validate_tokens(self): terminals = {} for n in self.tokens: if not _is_identifier.match(n): self.log.error("Bad token name '%s'",n) self.error = 1 if n in terminals: self.log.warning("Token '%s' multiply defined", n) terminals[n] = 1 # Get the literals specifier def get_literals(self): self.literals = self.ldict.get("literals","") # Validate literals def validate_literals(self): try: for c in self.literals: if not isinstance(c,StringTypes) or len(c) > 1: self.log.error("Invalid literal %s. Must be a single character", repr(c)) self.error = 1 continue except TypeError: self.log.error("Invalid literals specification. literals must be a sequence of characters") self.error = 1 def get_states(self): self.states = self.ldict.get("states",None) # Build statemap if self.states: if not isinstance(self.states,(tuple,list)): self.log.error("states must be defined as a tuple or list") self.error = 1 else: for s in self.states: if not isinstance(s,tuple) or len(s) != 2: self.log.error("Invalid state specifier %s. Must be a tuple (statename,'exclusive|inclusive')",repr(s)) self.error = 1 continue name, statetype = s if not isinstance(name,StringTypes): self.log.error("State name %s must be a string", repr(name)) self.error = 1 continue if not (statetype == 'inclusive' or statetype == 'exclusive'): self.log.error("State type for state %s must be 'inclusive' or 'exclusive'",name) self.error = 1 continue if name in self.stateinfo: self.log.error("State '%s' already defined",name) self.error = 1 continue self.stateinfo[name] = statetype # Get all of the symbols with a t_ prefix and sort them into various # categories (functions, strings, error functions, and ignore characters) def get_rules(self): tsymbols = [f for f in self.ldict if f[:2] == 't_' ] # Now build up a list of functions and a list of strings self.toknames = { } # Mapping of symbols to token names self.funcsym = { } # Symbols defined as functions self.strsym = { } # Symbols defined as strings self.ignore = { } # Ignore strings by state self.errorf = { } # Error functions by state for s in self.stateinfo: self.funcsym[s] = [] self.strsym[s] = [] if len(tsymbols) == 0: self.log.error("No rules of the form t_rulename are defined") self.error = 1 return for f in tsymbols: t = self.ldict[f] states, tokname = _statetoken(f,self.stateinfo) self.toknames[f] = tokname if hasattr(t,"__call__"): if tokname == 'error': for s in states: self.errorf[s] = t elif tokname == 'ignore': line = func_code(t).co_firstlineno file = func_code(t).co_filename self.log.error("%s:%d: Rule '%s' must be defined as a string",file,line,t.__name__) self.error = 1 else: for s in states: self.funcsym[s].append((f,t)) elif isinstance(t, StringTypes): if tokname == 'ignore': for s in states: self.ignore[s] = t if "\\" in t: self.log.warning("%s contains a literal backslash '\\'",f) elif tokname == 'error': self.log.error("Rule '%s' must be defined as a function", f) self.error = 1 else: for s in states: self.strsym[s].append((f,t)) else: self.log.error("%s not defined as a function or string", f) self.error = 1 # Sort the functions by line number for f in self.funcsym.values(): if sys.version_info[0] < 3: f.sort(lambda x,y: cmp(func_code(x[1]).co_firstlineno,func_code(y[1]).co_firstlineno)) else: # Python 3.0 f.sort(key=lambda x: func_code(x[1]).co_firstlineno) # Sort the strings by regular expression length for s in self.strsym.values(): if sys.version_info[0] < 3: s.sort(lambda x,y: (len(x[1]) < len(y[1])) - (len(x[1]) > len(y[1]))) else: # Python 3.0 s.sort(key=lambda x: len(x[1]),reverse=True) # Validate all of the t_rules collected def validate_rules(self): for state in self.stateinfo: # Validate all rules defined by functions for fname, f in self.funcsym[state]: line = func_code(f).co_firstlineno file = func_code(f).co_filename self.files[file] = 1 tokname = self.toknames[fname] if isinstance(f, types.MethodType): reqargs = 2 else: reqargs = 1 nargs = func_code(f).co_argcount if nargs > reqargs: self.log.error("%s:%d: Rule '%s' has too many arguments",file,line,f.__name__) self.error = 1 continue if nargs < reqargs: self.log.error("%s:%d: Rule '%s' requires an argument", file,line,f.__name__) self.error = 1 continue if not f.__doc__: self.log.error("%s:%d: No regular expression defined for rule '%s'",file,line,f.__name__) self.error = 1 continue try: c = re.compile("(?P<%s>%s)" % (fname,f.__doc__), re.VERBOSE | self.reflags) if c.match(""): self.log.error("%s:%d: Regular expression for rule '%s' matches empty string", file,line,f.__name__) self.error = 1 except re.error: _etype, e, _etrace = sys.exc_info() self.log.error("%s:%d: Invalid regular expression for rule '%s'. %s", file,line,f.__name__,e) if '#' in f.__doc__: self.log.error("%s:%d. Make sure '#' in rule '%s' is escaped with '\\#'",file,line, f.__name__) self.error = 1 # Validate all rules defined by strings for name,r in self.strsym[state]: tokname = self.toknames[name] if tokname == 'error': self.log.error("Rule '%s' must be defined as a function", name) self.error = 1 continue if not tokname in self.tokens and tokname.find("ignore_") < 0: self.log.error("Rule '%s' defined for an unspecified token %s",name,tokname) self.error = 1 continue try: c = re.compile("(?P<%s>%s)" % (name,r),re.VERBOSE | self.reflags) if (c.match("")): self.log.error("Regular expression for rule '%s' matches empty string",name) self.error = 1 except re.error: _etype, e, _etrace = sys.exc_info() self.log.error("Invalid regular expression for rule '%s'. %s",name,e) if '#' in r: self.log.error("Make sure '#' in rule '%s' is escaped with '\\#'",name) self.error = 1 if not self.funcsym[state] and not self.strsym[state]: self.log.error("No rules defined for state '%s'",state) self.error = 1 # Validate the error function efunc = self.errorf.get(state,None) if efunc: f = efunc line = func_code(f).co_firstlineno file = func_code(f).co_filename self.files[file] = 1 if isinstance(f, types.MethodType): reqargs = 2 else: reqargs = 1 nargs = func_code(f).co_argcount if nargs > reqargs: self.log.error("%s:%d: Rule '%s' has too many arguments",file,line,f.__name__) self.error = 1 if nargs < reqargs: self.log.error("%s:%d: Rule '%s' requires an argument", file,line,f.__name__) self.error = 1 for f in self.files: self.validate_file(f) # ----------------------------------------------------------------------------- # validate_file() # # This checks to see if there are duplicated t_rulename() functions or strings # in the parser input file. This is done using a simple regular expression # match on each line in the given file. # ----------------------------------------------------------------------------- def validate_file(self,filename): import os.path base,ext = os.path.splitext(filename) if ext != '.py': return # No idea what the file is. Return OK try: f = open(filename) lines = f.readlines() f.close() except IOError: return # Couldn't find the file. Don't worry about it fre = re.compile(r'\s*def\s+(t_[a-zA-Z_0-9]*)\(') sre = re.compile(r'\s*(t_[a-zA-Z_0-9]*)\s*=') counthash = { } linen = 1 for l in lines: m = fre.match(l) if not m: m = sre.match(l) if m: name = m.group(1) prev = counthash.get(name) if not prev: counthash[name] = linen else: self.log.error("%s:%d: Rule %s redefined. Previously defined on line %d",filename,linen,name,prev) self.error = 1 linen += 1 # ----------------------------------------------------------------------------- # lex(module) # # Build all of the regular expression rules from definitions in the supplied module # ----------------------------------------------------------------------------- def lex(module=None,object=None,debug=0,optimize=0,lextab="lextab",reflags=0,nowarn=0,outputdir="", debuglog=None, errorlog=None): global lexer ldict = None stateinfo = { 'INITIAL' : 'inclusive'} lexobj = Lexer() lexobj.lexoptimize = optimize global token,input if errorlog is None: errorlog = PlyLogger(sys.stderr) if debug: if debuglog is None: debuglog = PlyLogger(sys.stderr) # Get the module dictionary used for the lexer if object: module = object if module: _items = [(k,getattr(module,k)) for k in dir(module)] ldict = dict(_items) else: ldict = get_caller_module_dict(2) # Collect parser information from the dictionary linfo = LexerReflect(ldict,log=errorlog,reflags=reflags) linfo.get_all() if not optimize: if linfo.validate_all(): raise SyntaxError("Can't build lexer") if optimize and lextab: try: lexobj.readtab(lextab,ldict) token = lexobj.token input = lexobj.input lexer = lexobj return lexobj except ImportError: pass # Dump some basic debugging information if debug: debuglog.info("lex: tokens = %r", linfo.tokens) debuglog.info("lex: literals = %r", linfo.literals) debuglog.info("lex: states = %r", linfo.stateinfo) # Build a dictionary of valid token names lexobj.lextokens = { } for n in linfo.tokens: lexobj.lextokens[n] = 1 # Get literals specification if isinstance(linfo.literals,(list,tuple)): lexobj.lexliterals = type(linfo.literals[0])().join(linfo.literals) else: lexobj.lexliterals = linfo.literals # Get the stateinfo dictionary stateinfo = linfo.stateinfo regexs = { } # Build the master regular expressions for state in stateinfo: regex_list = [] # Add rules defined by functions first for fname, f in linfo.funcsym[state]: line = func_code(f).co_firstlineno file = func_code(f).co_filename regex_list.append("(?P<%s>%s)" % (fname,f.__doc__)) if debug: debuglog.info("lex: Adding rule %s -> '%s' (state '%s')",fname,f.__doc__, state) # Now add all of the simple rules for name,r in linfo.strsym[state]: regex_list.append("(?P<%s>%s)" % (name,r)) if debug: debuglog.info("lex: Adding rule %s -> '%s' (state '%s')",name,r, state) regexs[state] = regex_list # Build the master regular expressions if debug: debuglog.info("lex: ==== MASTER REGEXS FOLLOW ====") for state in regexs: lexre, re_text, re_names = _form_master_re(regexs[state],reflags,ldict,linfo.toknames) lexobj.lexstatere[state] = lexre lexobj.lexstateretext[state] = re_text lexobj.lexstaterenames[state] = re_names if debug: for i in range(len(re_text)): debuglog.info("lex: state '%s' : regex[%d] = '%s'",state, i, re_text[i]) # For inclusive states, we need to add the regular expressions from the INITIAL state for state,stype in stateinfo.items(): if state != "INITIAL" and stype == 'inclusive': lexobj.lexstatere[state].extend(lexobj.lexstatere['INITIAL']) lexobj.lexstateretext[state].extend(lexobj.lexstateretext['INITIAL']) lexobj.lexstaterenames[state].extend(lexobj.lexstaterenames['INITIAL']) lexobj.lexstateinfo = stateinfo lexobj.lexre = lexobj.lexstatere["INITIAL"] lexobj.lexretext = lexobj.lexstateretext["INITIAL"] # Set up ignore variables lexobj.lexstateignore = linfo.ignore lexobj.lexignore = lexobj.lexstateignore.get("INITIAL","") # Set up error functions lexobj.lexstateerrorf = linfo.errorf lexobj.lexerrorf = linfo.errorf.get("INITIAL",None) if not lexobj.lexerrorf: errorlog.warning("No t_error rule is defined") # Check state information for ignore and error rules for s,stype in stateinfo.items(): if stype == 'exclusive': if not s in linfo.errorf: errorlog.warning("No error rule is defined for exclusive state '%s'", s) if not s in linfo.ignore and lexobj.lexignore: errorlog.warning("No ignore rule is defined for exclusive state '%s'", s) elif stype == 'inclusive': if not s in linfo.errorf: linfo.errorf[s] = linfo.errorf.get("INITIAL",None) if not s in linfo.ignore: linfo.ignore[s] = linfo.ignore.get("INITIAL","") # Create global versions of the token() and input() functions token = lexobj.token input = lexobj.input lexer = lexobj # If in optimize mode, we write the lextab if lextab and optimize: lexobj.writetab(lextab,outputdir) return lexobj # ----------------------------------------------------------------------------- # runmain() # # This runs the lexer as a main program # ----------------------------------------------------------------------------- def runmain(lexer=None,data=None): if not data: try: filename = sys.argv[1] f = open(filename) data = f.read() f.close() except IndexError: sys.stdout.write("Reading from standard input (type EOF to end):\n") data = sys.stdin.read() if lexer: _input = lexer.input else: _input = input _input(data) if lexer: _token = lexer.token else: _token = token while 1: tok = _token() if not tok: break sys.stdout.write("(%s,%r,%d,%d)\n" % (tok.type, tok.value, tok.lineno,tok.lexpos)) # ----------------------------------------------------------------------------- # @TOKEN(regex) # # This decorator function can be used to set the regex expression on a function # when its docstring might need to be set in an alternative way # ----------------------------------------------------------------------------- def TOKEN(r): def set_doc(f): if hasattr(r,"__call__"): f.__doc__ = r.__doc__ else: f.__doc__ = r return f return set_doc # Alternative spelling of the TOKEN decorator Token = TOKEN ./CBFlib-0.9.2.2/ply-3.2/ply/ctokens.py0000644000076500007650000000614211603702121015526 0ustar yayayaya# ---------------------------------------------------------------------- # ctokens.py # # Token specifications for symbols in ANSI C and C++. This file is # meant to be used as a library in other tokenizers. # ---------------------------------------------------------------------- # Reserved words tokens = [ # Literals (identifier, integer constant, float constant, string constant, char const) 'ID', 'TYPEID', 'ICONST', 'FCONST', 'SCONST', 'CCONST', # Operators (+,-,*,/,%,|,&,~,^,<<,>>, ||, &&, !, <, <=, >, >=, ==, !=) 'PLUS', 'MINUS', 'TIMES', 'DIVIDE', 'MOD', 'OR', 'AND', 'NOT', 'XOR', 'LSHIFT', 'RSHIFT', 'LOR', 'LAND', 'LNOT', 'LT', 'LE', 'GT', 'GE', 'EQ', 'NE', # Assignment (=, *=, /=, %=, +=, -=, <<=, >>=, &=, ^=, |=) 'EQUALS', 'TIMESEQUAL', 'DIVEQUAL', 'MODEQUAL', 'PLUSEQUAL', 'MINUSEQUAL', 'LSHIFTEQUAL','RSHIFTEQUAL', 'ANDEQUAL', 'XOREQUAL', 'OREQUAL', # Increment/decrement (++,--) 'PLUSPLUS', 'MINUSMINUS', # Structure dereference (->) 'ARROW', # Ternary operator (?) 'TERNARY', # Delimeters ( ) [ ] { } , . ; : 'LPAREN', 'RPAREN', 'LBRACKET', 'RBRACKET', 'LBRACE', 'RBRACE', 'COMMA', 'PERIOD', 'SEMI', 'COLON', # Ellipsis (...) 'ELLIPSIS', ] # Operators t_PLUS = r'\+' t_MINUS = r'-' t_TIMES = r'\*' t_DIVIDE = r'/' t_MODULO = r'%' t_OR = r'\|' t_AND = r'&' t_NOT = r'~' t_XOR = r'\^' t_LSHIFT = r'<<' t_RSHIFT = r'>>' t_LOR = r'\|\|' t_LAND = r'&&' t_LNOT = r'!' t_LT = r'<' t_GT = r'>' t_LE = r'<=' t_GE = r'>=' t_EQ = r'==' t_NE = r'!=' # Assignment operators t_EQUALS = r'=' t_TIMESEQUAL = r'\*=' t_DIVEQUAL = r'/=' t_MODEQUAL = r'%=' t_PLUSEQUAL = r'\+=' t_MINUSEQUAL = r'-=' t_LSHIFTEQUAL = r'<<=' t_RSHIFTEQUAL = r'>>=' t_ANDEQUAL = r'&=' t_OREQUAL = r'\|=' t_XOREQUAL = r'^=' # Increment/decrement t_INCREMENT = r'\+\+' t_DECREMENT = r'--' # -> t_ARROW = r'->' # ? t_TERNARY = r'\?' # Delimeters t_LPAREN = r'\(' t_RPAREN = r'\)' t_LBRACKET = r'\[' t_RBRACKET = r'\]' t_LBRACE = r'\{' t_RBRACE = r'\}' t_COMMA = r',' t_PERIOD = r'\.' t_SEMI = r';' t_COLON = r':' t_ELLIPSIS = r'\.\.\.' # Identifiers t_ID = r'[A-Za-z_][A-Za-z0-9_]*' # Integer literal t_INTEGER = r'\d+([uU]|[lL]|[uU][lL]|[lL][uU])?' # Floating literal t_FLOAT = r'((\d+)(\.\d+)(e(\+|-)?(\d+))? | (\d+)e(\+|-)?(\d+))([lL]|[fF])?' # String literal t_STRING = r'\"([^\\\n]|(\\.))*?\"' # Character constant 'c' or L'c' t_CHARACTER = r'(L)?\'([^\\\n]|(\\.))*?\'' # Comment (C-Style) def t_COMMENT(t): r'/\*(.|\n)*?\*/' t.lexer.lineno += t.value.count('\n') return t # Comment (C++-Style) def t_CPPCOMMENT(t): r'//.*\n' t.lexer.lineno += 1 return t ./CBFlib-0.9.2.2/ply-3.2/ply/__init__.py0000644000076500007650000000012211603702121015607 0ustar yayayaya# PLY package # Author: David Beazley (dave@dabeaz.com) __all__ = ['lex','yacc'] ./CBFlib-0.9.2.2/ply-3.2/TODO0000644000076500007650000000066211603702121013373 0ustar yayayayaThe PLY to-do list: 1. Finish writing the C Preprocessor module. Started in the file ply/cpp.py 2. Create and document libraries of useful tokens. 3. Expand the examples/yply tool that parses bison/yacc files. 4. Think of various diabolical things to do with the new yacc internals. For example, it is now possible to specify grammrs using completely different schemes than the reflection approach used by PLY. ./CBFlib-0.9.2.2/ply-3.2/dist/0000755000076500007650000000000011603703070013646 5ustar yayayaya./CBFlib-0.9.2.2/ply-3.2/dist/ply-3.2-py2.6.egg0000644000076500007650000025254011603702121016316 0ustar yayayayaPKU0^;“×2EGG-INFO/dependency_links.txtãPKU0^;?_¿C£çEGG-INFO/PKG-INFO…’MoÔ0†ïùsB u ·œhµ$²b¨ÇY{’XØqd75¿žqXÒöÔ¢dâyÞå+1jdÜý¤ŸZ¸­ßWtÔÂlsµ?ÖªSrCná˜yôtôoà•ª>{G»Y™ç¶i–e©5ž ÿÔÊ»F`Mu—d/´°Ç‹Ñp/ß,åëtGmAã…>=-VQ4EáÞŸöÕž¢ fæÕR×ëØ=€‰‰'Ï#0n¶ähb,gÁ÷`Å,N²Ø…Þ‡kˆNbd Ï–6dOÈ)P3)›4P¡GÅò€ †ã“i» d³ÿ_NÑ2¼SXw×}{ûf”V§–Ѩ±X§¾7Êe][ÈZˆÉrqj1 ’iXúõ}ÑÀ¼´**ÎG.‰‹åÈÄ Küæ_ô—ÉŠ˜æÙ^µÈÍœ7®0uR¥Âx#/¤HÓ¤B²$ AVdì/òÍjþ9 Ý٠ɧøš÷RÁ#©S:$ŒØ—ÊV⬈”sò?˜ ]ÕÕHê·¤xF>Zd‘w-ü8|9|ûu¨þPKU0^;k\nÞÝEGG-INFO/SOURCES.txteŽA Â0E÷½K“3ˆFÑ––®IÇ&¥¹}Q’Bq3ü÷ß,~g§»©"Ê›§Š}ÒŽœ¶¼)+aFŠ=.%¦§µ9+œ¦ÚÑ+èöv©¯s³oûf莦W²È^ŒÈH#’MàÍñÿCƒÇúŸŒ¢¿'ïØ8YPKU0^;efžEGG-INFO/top_level.txt+È©äPKU0^;“×2EGG-INFO/zip-safeãPK7Qu5K•RRply/__init__.pySVð‰T(HLÎNLOåRVp,-ÉÈ/²RpI,ËLQpJM¬ÊI­TÐHI,KuHILòõ’ós5¹¸âãsrâãl¢ÕsR+ÔuÔ+““Õc¹PKU0^;ô’µply/__init__.pyc»ø‰—k—X²k20± ‰ bdHgbˆ2˜‚5˜‚% "'µ¢„HW&&'ûi0‚„ÙD||bNN|¼È$Ql $’J3sRô“R2‹Kôr“ó‹+t ôÌtKó2ËR‹ŠsôSÓÓõ r*õãã3ó2Kâãõ *K8€:mróSJsRí@öƒÌPKƒFF:ÒJ.ˆ ply/cpp.pyÝ=ýwÛ6’¿û¯`äçUK²Ý½»½ÕÅÉsóÑõ{Iš—¤ÛëIª-R‰Ô’TlmÓýÛo>AJq¥»·ËÖ‘HƒÁÌ`f0@Ç^oŸ×ѱ7]­ú«ÍÑ1|½Zó4xÞóàszßEÁßÑÆóçE±œÝÝÝõÃàžö§é²ž¥«MßÎ ÏÖñ¾=?ÿBY,BÇ£Ì £YœÄEœ&yßó€h@B¯H?E *‹¼(I×·sx(*ðn‚<žš îÒìSœÜ"€Š9@e²ùƒìaAã~ÙxwARì½£GïKÏ?TÚÏÞ¾\?owùË›/¾ñ®Ýåç/_ýpõAÞ¼ÿðîúÍ÷òîÙ_®T±ŸÞ«§?¼~ýâªòö‡ßHÐÏùæ¨st´ˆ àãqhö¾9;ùò‡üòøÉ壧~g8þõ·~÷¿£Ñ¨=jµÑ?Í¡|¾ ¦Ñ0Â+&ܦ_tØ/kòÓ6}-úİþ"N€'Þé%<ù,Ö ŽuRø­QÒêp¥d+ñ  ÇD¡ °ã¶xö\ˆ™ëH<‹£LºæëÞÿ½¿OÆÃÑÝdü —MŠè-úKØkTÖ:àãu~ßùâŸÿw§3<ïý9èÍ®z/ǧðhžv:þpýãøËpñ þoüþÁ›ÎÓNÛÙ)Ñ ¨Ý!f/iP€0*Ô¸<ñ›ºãS«þ¨O‘?:ýÒëö§ÙKÀ‡ºÿ¾Èô&JÞ±$éükùÃ_€ãÉz;òû_FI§Óùæé¨õp¶‚"œY0…ƽ) Ü“מ¶=НàSÃeYgÆ«ÎÓQ»£öïÂ(]¢~՛棷~6ú†ÛƒÖ¾9þŸõákÒypËx#ÚŒ²,ÍTkE¿Ø¬"OžÅsºu½àÆóOñÊ¿°;(”XÉoS0Eò{/Õó4﯂b~-2w›«¹¦þÿ>þ%hÏâdµ.Àœ¡LvA¿‚Ý›­“)*uÀxµõÊ̤„àåÑßÖQÉÂÒ‹·X¤w(ÔË`µÂO€²Î£p@Ư§O/ñ£¼=ѺmãÇ/êÖÇ¡ºíàÇXÝ>Â/êö1~üªnŸàÇo궇ÿØ¿½˜H‚L€g¨PÒ–«xùY»Ý==^ž¶öGÑ£ÇOF½1<îhõ€¼PïW’–öe{Ð>nwùæ n@Ñó]«Ý´‘¯|x5”7¸Ë›GpóEÞ<†›_å͸ùMÞôàæí£ßŽXô¥\ÈÑÆ¢kô°Ÿ¯oüE°¼ ïvà½Þöo³t½3Õ»» k?b @^Ó,õқѴ(½3¾÷æé"ÌAŠÁëZ$µÁMº¶Ü•%BÈ¥0ö“`‘tx=œžø< :¢u½?ñÐÝ9ŒÖ™ðud… »¥Xá•(ÏÖ¨Û¨…\AÎâ G ~—¦‹ˆÆ!<`ãs7ÈÄ“´ðTiêE @3roù”œ£²ð ,#ÐòÔëŸæ8ÚÎiEv©?ƒ¥~©´—Oƒ$‰BÐ!otí´WLçD˜€Âˆ@p ™Á’ \g¬"°µè~$9°k?Br4]yÎlòY2„,£O&è¦N&~-f]äD—XÙ»|“&øˆIwù|°HTÇ k±Ì\ÍÒ$ЧùJ Ä¥'¾Ù5¯.ÛTðuå³½&r_ÁÅagÂÎÓu6E´°k{‰oõA¥ Èx,â[pÔ’âÀ‚àÞ?K“"ˆ“\H€6yèˆ8™.Öaä…q Ò,Žò.ÉYJcAà{•½GÛ‡l<ÉŠ&À(ž Á¨ÂW&·øÕ%~²‹`rI{m¿b•…öl™ñ]x>´8^DËÕ¤|§^"×Ò›ˆF:·‡T¨]¥Œ*¬‚Ö ë€³ ^Kt{ÀYé/R˜òâ7¿cV#ŽF~k2y~õáÌOG­“&+Þ Wõ:£z­“ï$ôN~nu‹e§ʇë×ÍPþ28y=8yï‚ê/'Ò²ü3!~¿ØèÄ0‰~ñß%1ŽÅã‹üò¥úÒã®éëè¾è* â MmÛrÌ•|+äI¾M²Õ„Ø–4öuÉÈûTG½¾›ƒûã}ÈÖÖ0PG«L°5ù# ͼx7`T>Ù ›>ø—QúpWV–ž6lŸ°xv`2ø]D.»©å¸äÙ]%‚Çy fã÷½2²ä £Fì›í»8ýé.ó[+·Â{ò$ßä0xB¨Ñ…5À˜ã¨òÍŠû,˜¦Qt"r˜ ¼4ôè}NjÊjÞŒ0Χég¡.©<»+8gˉæ›åMºÐÜž^äØTè @×3žý`<*ç `·ŠÍ] S¡C‚¯…E[¢ú] š7H6^¾Ž‹àf!•mÝY¸€ÚˆÚ<½“ãj|޼›GŸ"ìH@åQF@*4»ðÝÃ%ðÝ""ˆXtªÆAþVYªÕÑGóh/G:ú¸ð!œ¨G—žÑÔ!,Æ­géz&í:'±/«ú-U-?Îá=œÂv±üî$á¸U=.¾ýã¿ýûÃI-øŠ¤Ü™"°¶+TL‘¢¾ÔäÃÏo_`Q(¦á¸3ñØìåL()NâÄ Ó5”¿­Ó"j¢ê¨…* ‡ ø{’3æ®¶{Gúr<ï!’v§B»½tÔJuì eKUJ‰"?½Çõ®]«¶1ŸÍ£é'Bƒ'MSéåhœw³©4UË’³‡±£nû üãþƒ¡¨¶øÃÿúíÒ%Äæ¦8š ‚£§:§¦Ë÷•~a…‹ÖÜXcÒ Ù`°÷ØkŸäm°Ä[Ãä2$Œu 4=ˆÛ„!MÉ,·ç* sœ DA6{4gs9&žw Ÿ@¡E~#~³£øLúÚôþ ä¡ á„Æ‹E¡ÂÓù ¦X¹êtÌAý Ç§Æ3žgRña<îs䕚ªCQ#ÿ£÷Ø«…©0‡Ú~_‡ƒÞÅø”ï>Žkj|Ä­VåíG\sº(Õ1K.[šþÇ4–¨è´ZQÄËõbË€8]gxºÄ/sZÞ<ïFx[&Ü•ÞT'àzëÎi¸)ò¶4cÈ“ö(iãS¥Â«ÍnâhMUŠT© Û{ý­ Þú:gw<Ä#1@ÕÜPÝœU5%§†”ç¯BÅ÷?ü5\9ÄËZp|nIY,–(Lœåï8+œ7™ó ‘·!(IQwfµ&zž^_Ûr¯¦eP.ƒ²m+˜t™¦ ¾N‚ìÖ¶{ÏøUe–KôpôrI ‡&é7e1o¹†R7‘1ëPbå1V{GýEw¤X¯€¶LtZ3Ç呼»JsŽÒKq¾×Rˆ*C‹IFr½¼ÁHÄ‰Ò ›°‹håX¬D[!Ú•v˜©š2ËÊy7Äš‚Íq6dÒ씌‚é\ @_ÀÓr!Žœ±NÁ>q…˜KhéL°ŒÖ5ær(³ :†séoH‡yéè('Oˆ)¿܆U”-6ÞšÀœ(0 ˆ´ÆBjœ¤% ãD©0EÅ. r<'&%ê‡ò' É.U ’WÓ*$ †ý*o<–ʚ׺´H¤µ>¢¹%à•¦;¨a*¡Í’Þ³ÛJP˜$ &8ýFÅç£æ“­/CµâÔ@§òÓÍÕV˜buñѳÀ)¢Ik Ь´Æ5ÓÎ2^,–K ÏÇÂíè¶^Çy.ˆ‚=â;%>-Óè •yÞuMƒlõ¸´ ²Ï–¿Â“aÕýŠoaУê>h£\”N¥””Ã1ͬ6:Ž6díž][à¨d$¨Z[Òu—Á ljìËTi¯5jåUwYÁA Kç?€Â"vÛ$×].ª}~x_›‡oS•0ÊöXÙ­«š7£é9v ‚2æìºi ¤: ;[F¡1åܳ×B­OÐpNƒÄr[^Ü*¨·ÔSeÌDVp"\¿)#+˜)…ÌŸHØH¾ŠàËzegˆÌ’4üî¢öbá}JÒ;„³¼ƒ»`£|¸-â"S*’eI¸ÁY6=)ÓRöNAe$MB’•¤Gšz§û>Ó/”XC61‹hd¡-ž†Ð„9P<üªÏà_!]M”`>Ù„¼Œ*°cï¯F†’ð]©ÜN3 Ù®'Xsæi/•½¼ÔrP¤¬BÌW9bdŽSé€Ó ˜åúäNú.˜U½‚.»"žžïEkù·rY ˜ÂˆŒÑŽþRs;ÌÎF ðÇ„Ò>þcaíÖöN’š‹Îz8g²±mh@IžÔž>Ó» õjl:øq²®Nú‰ÌSó §ÙïÉèø»õØv¤L´M”ÛÓvw+Ú;¦¶Œ?™.Ç ¨vétO]ªéP\õ¶vASIU%RöÓeik1j1%‚9‡½ Hµ­‚PWän“Ð×»Alº"°8ªu¶jÙçŽ ¬è²­-ÔË€ê:IÍZÃPäÊiê]Ôú66{ò4+üOÑæR¤ß¼ûá·ãn¡"Œ.1y˜6$^¡+|"s¬8]‰Y‰7x>Ï¿µèZG,,p"Št"d\DØÄü]Ï ŠpØEø_Âîä ºt|L-?² zeÎ-ÛÎd}•Óó*ùJïƒMr0íúS=A³"W24;áÅéìÃÒMîy-`r_Úb"‘‘H͈…õÒ¿žZ_î*ã†,ÐíãTÆä¶˜KÄtBV+o°He—Þ¯ef%â)T /KX6¬â—ß‘Â)¿¹:üŒ×C®ŠvÛo·NòVÛ;ñZb`x/Æ´ZDA¾È*ãN§/ºê·F£Vþ{:¾²½~ä*¦Ò—(Vød¤˜W¼=àÖõÌUF¾EËU±ézwn _=,Ã=†IYØz¬Ä¡¼I$> «Mª«å%§Ö«rH­²ê_Å õ[…2¸E†WÝKÑ%Ýf¡ˆŠ’ /ƒä‘TDŽ §)'«Ñj¡J¤×š˜9犡îå0®Ð¶%|Q1ò6˜9N‘sòÚ4XçÄH |Žù§ C ½YVÂ,ñ¤Ù[¿:Ô”Î4˜iéí^×5Ú¼±?Z·Õ„iÍ oÈÖìAº’&|žžÐŽr&½fop vQ*§¾‰ƒ65ÅÏâLcÑba ¹}S¡HpnS.ßjª„ ¬Ú9wÜ×»TõóŒÞÛuñþž‡)ʇˆf‹1OÁ.\Ö²>Pkš°“˜ÍBÌb¼Â:“XkS˜Sxu˜“LnÂ\°SVQÆkþV\BÖ?ÈXB¨­Ý°gº AÍxÌOm¸×.‹‚pc J vld…¡&´‘GîtéXì‰hÊ0é¦-v%šŽÝŠ Î ºž(ÕÄëŽ5ãÜ5®xÚÎX”} ­îˆW;Îcïgܼr‡F|A@!%K#"â¢ÂP´3–VÆUØíÜKÀH+@uhìȲ>2Rv劳…ïW[°Ì1…¤Þ*Ñ©bc¥ˆÉ^)!Q¦Mâkmy)-¥¬-JS!½èÞdý¬/¤! çˆK´®‹2^¼Óš 8^<">Ö¯Äܺ^m´vÊW<Ó@7/ÂèÔq-%KY1Ö %üAMØJC…¥×p‘4…Á¼@ž‚Kñ®™ëW]X¾ ÅOr™E˜ã¦2Û(Äëšm7¬Î¨9€üŠXÍ2Nº¾?¶zÞs,µ8èiVòžxßn¯öud£DÚò`v\wµ¬ôa6ÁCàü»QþJ¶ïÒ?C4v#‡à>‹ÏååäG^úÞpË–×îl“- mÇ¥éÿxª4LµØà㩤t]xÖual×Ñî`w[ ²‹íØ…Ý7 ^ìS—¦ßï,9ªó5@Ló /v0ÐòBC §~7®f_a±å¥,wÉÐ1¿°ÚaÈ K…ëCùoì±|}|2ÁLýɤÆVÖ Œ<Æ]VÅkª»s|IÂjךB»‡Û>ÙSMÃDÇ­hvVä ì ÀV°¬œ³N É:«uCœ·ùE\S.°sžXÆ3uç`™Nª;îÄI™*uî±EÞt´Zçh…òœŠ’Q_9 *½´Ú¥Òò}) ¢y‡|Ö»¢I…”†V Õ•r•ã¹a—^ëüU5]ÚéÂÖæË<È­ÝâÒÖ`¼x›­6O غ&”Íš±¤Ú…ƒj%zÛìf3õ5dÑ—VÌtí¼.Û|À$@“Úm-dWþ•¼šm"NS‹Ò\`Œ†¥~§å65‚fÅm ¾24Jž[EÄÊhþxj99–ÖWúÉaõå±6²,Ó»ùHÀùÅ”äz´Ë`Q]5–)½: qL8³ÖlÔ¹ÒïÀŸslV`¯hg™&œ¯g³ø>ªF=(2ßzZmˆõ©U ×Ed̪uN{‰ÿãOÿùçàf "}õݳç/^¶jœ’ 6èîEëqÿŒöLjå,Äý^¦1¨5-†¥ÍD5ü(¸þð‡V·EF«µ¥ä—/X o+øË!Aôm¤ÙÆS Õ‰FÞG:Ôi´*TªÃ Ô#»§ÙæzŽ­ÚGI¨ô[*Kz£ÒP1r|s(9¡rÙ¹~oñ±½5ïlÿ —¥P(7§u™ž2ЬùSï˜ÉŽƒêJV£›'ž©wr'1MßWtŒ”m”ÆÁâ»êÝÁr=T·Å9hÿôýN!°a-Kµ¥Þk××´; (â[ Jü@S Ü\³NËËäå:ÆÿÓs’Ú¦®ì&À³¦N“ÅQ žL®2Qué¨Ûi% 3EjÏ2ïVÆÓÌ0Ûª³¨ [§é:,çüØ&n£Hºÿú”ý?§ªòêytˈbsÈ^:×ýW <ÞÕëHAýFÑep² : ÇÇÞO‘—&´çgãaÎ]B‰;P<]ci+žµ0i/½Ë)·gK—$3Õ#:0NäêÀœ×1ács}A÷íT'bìÎ$¦úҒ‰Uîz70!£#øuz›¨@Äp‡Ô”N*ç˜[Q{|j$ÛEF-24E «-l‘3‚ûX áFk›ñh~zÇȈšP ^[>opï ð;ŠîEqwð;qøÿ“»yÔêT§”“ðwé-ÛŒàB‹°4«t廥ë0ýÅž8Ĺ¾±cïÇ÷[&æÙ˜åtÜUiä¹ITw*ßÖ¹ü½EœyFÑTßw̨Æ×ùÒUßYó•o“ó3Üv-}ˆ³ºÓ™‡³”ÞÿFUy“ÈÔ-o~ÀôUL|-ð„9Z›•ç)ò2#žš!Dƒƒ…|¼·1Å* ª68¼©—t•*—”gúè°Ó—:ÏÅÚÁ#kc]T¿yMd[û—Ô¾K¬¯ ÷ûý'UÁö\KH;¬ùVq1ÖvŸÎÒŒ#®ÙšxÊ_Ò¯ê0«P×?ÐúS×%hmUñŠðØG™ÎbŒ|Ÿäm\ˆ=ˆ•¡PÓÈ=ç3Š:¥¨L4ß¿Y­×œvf/é'±¦r}»‹? Ó]'ñ4 #ûAG$}*¦®‚ŽâÓ¶w{̈ *ØÂ r5Å[ÌÓu¤g.ÅB¹„q±ËY'²Re÷›L¶Æ÷ŽjP…s¹°®ÜO=ìZŰ벪‚©±]}0³>agѽ;Á‰Ÿ½ì! õí`ìˆå<óæÌ˜·¨Üyнu½æìyÅn×ÒöK3î¹m•»Mký‹í™ÅB¯¼I½ešiÇÑÑ9òÏ„A;eòºÌ¥~€‹÷ìLƒI¬§ð³ &cš`€‹R“—F½Æ©kPz eîKsi™\ÑžLþz5¹z÷ýûɤý»¡œåáECŽòöÜ7¤Í°÷ÇÁXˆ|êÀá5eÃíeŒsuù(yüM ‹Ô¯†Ãeœöz)ÜŠûr ‡#ŒÕ/·¹eDÛ!ÝZn+¹ÍÖ7Lƾ äˆ)áLû5öÜ_¥é§õÊ‘=Öäþ8/ìZ?^•„Ò!?¤3ÎM×øâau>]ï6«y”`^Žw§¸ŠK"Ι<Ç™sßÜóöIYnÚ4×oÁgŽ.ýÍ>ôŸ_` š¾˜/Õª™³c|9¨AÎB;Á\’ó5ÿtT‘ª,“0þ‡ë`¡OµöN_Æ)¡ÿ^š-•u§²Sáò—/˜²}üGL¤.Žy4ÐvïØÿ¾HW×øÓEåL“£•IŸ€É?‡‡3LPN&b7Ó2ˆµ›Iütñj±Á_·›§7ÖoúêH¨wëÄúÝ4R¾a¦ÍdÜ· ôüg˜É2yäÉú3G¢§¸ƒÍø5GjŸk¬¸³RZm€.F1ƒV ¿)cg1²ê^ÉebÉ‘8À∯ÿPKU0^;ÇÏ&ÍUäJ ply/cpp.pyc½\[lÙy>g†‘âE7K–/kú¢e¯$ßÖÞõÊöz-ÙVbË.í]íÊÔ24g$MÍÊKo(§[o›¦M‚¦ARI‹4i>å!M›HÛ‡¢/) 4@Š Ð"@ѧ"E‹¢E‹ô¿œ3Êòf±Ìá™3çüçöÿß9gø½ÿH'?ùê§ç+Býë…Ï«ðñÿK aÁ)î Q•bI iÂ2…VTX1aÅ…Õ#¬„°’b%!–ài¯X‚)ñ¾KP,-– dF,Aá¬X‚ò}ô¨GØ=b *ö‹¥¤°(³WXƒ”H kˆiaí D†º2,N÷‰¥>:ý:= –…ΰFÄcèúqÚÚ)¬QqÊÚ%¬ÝðµGX{áë9a탯œ°öÃ×a„¯Cƒ¯ç…5_yaMˆSKÃÂ:LÖaï+RX/`Îc!ÞZ֤Πrw {·°¦Å=Cx¿È=Ü#œ½bi¯°÷b .=§;¿O,ívNØû„³_XGÅ(à€°ç =$l ú lLØcÂy^؇ ![Ç„=.¼ !±@ž*N{B¤¼¨7\É‹ËwùJýϤ\ÄLèÂÍü1Xç'ð/< šI¸¬Ú®Ý(7½†ßŒÁíÅ7Jó³Í^\¸5wy®ÐL¨ûKW¯_¸Eõðîæ­ÂüÂåfº½xåB! ²x3 rñúµks ·"7®¿¾0™¥[7Ü™<<=Ö~þÑÛ3çÎî?ŸŸ¸½üñ©^9S?PÁã'‚ÕÀ¥ Ã,GRÊމl ówÚ(QÞͼeM¸ý#>Hæ‘D3 —ªÝ²ÔãªãÚ®G™ÊÕu›RoÝmòLÑ%bDÿ(\î¬;UkúŽåøÍ©µrÅó[“ÇŽNš\wvÃ/W§íÕÕéZõát¥V›ª=¤yj–xrv"ìˆ0ž“>v²xî‹!‘…Äí “KåÉwKË·‹ï”– õDxnRý Ø7üw´5ÑÎ}sbâöÑÉ—Ë“+&/-¬¢udb"{ýõåöíêU¸@ŠpÁ›‰óbGòÅ)ú²óÅ#íɉóÜ»ó¹vŽRÝÙyîæÊ%èâöø`Nðüí·‹Å¢» sRÌOµ‹îÄÄÄáóÅ!ö( w )¼¤Ÿå¼4S#°M…™a{#|{vuâ|qü)£ÿ¹2Œáä³#®b~ºx˜Gc:< ü===Iwâç6¾tg| pg¶¢¡‡x2"ŒjR<¨Ð½ ÜÀK4¢×‚ƒt$ÈC#"${X³i tçßwjÏnˆq¢Ýhx ”]LÈ>ú[ð‡PšÎÏß>;]/æ‹Åý3犓˄–éz–V£Héiº¾M×qºÞ¦kž®\k‚®mºî§ëÇé:C× ºž£ë#ºNÓlêiÄ>ÓTÁ´¾OS z“Yg¡«øM,>ÀÅÛTã1YF££Œ©¬)±­u©ÙpVåÚÝRî‘‚Xmx뵎‚X} b¦Z^»c•ÏázûDo‹ÔÊÍ&ŽÀ_¿ÃÍco·¶þlt”jæ®ÐÐ-©kåJà ìIlÿ5,1[  n›8ƒïh$xÒ+X7–„y\cb~dyC(Y0)·J˜˜ðúAÌ@B"‚lZ¯R ›R Ëk×bà–×lÌ*7V«04¸å†S¶œ ©}¸gTcÁsmÊó½õFÅÎG‰²«+…£†  U8þ d ;S*9®Ó,•ÚH%C3PqÙ/¸\‡T*ª–Jkžµ^…[‚UZœKåªoNwulª{EO¯L’ʺ| `û¾×x’ þ´ÃÄ’<©=ƒQô30Coqô9ØuÏ ô?0‘D/D9 í@  S‚ÄÓè”(b€\I>Dš2ûÐ;ÁD?:(˜ÀbÀÓè©èI€‚ùCȨˆC'ªõK̨0š{=ÂKƒHÄç Il¨XØ@¢Ì°«œˆèD”p%†¸"LmÃ; œÌLâÜ€J +ÌLJ¦~ ?T¬ßˬ]ð J³nÍ•J¹cþÂé±;¹1+7ö–z|kþZ÷ã+gÆ®»™'®&6¡ƒIÌÊEa Þ')ĹK|Ó^«•讇‹KܱY9k6•©z•r•îŠe¯€uMÅýfc%ȯ•¾Ý íV8%”¶nÚ­m—}Q>ƒµ‡I¨Òð§ËL)¹þhµ#aXú¸¬ëC ¡Mö‡lÄŽy/ðâTи&bVM»]°JNs°F}TÈŶ¡¬sd6G&5°Üj(?£éÝ·]š’r­f»+øSº\Ón5é)•ói™ ùL):ïÚ_J ÕnЏÌʸˆÊY‰¨iŠéiB“lÄ¢B7ÅŠ)†ùt ™ÙÌ?ƒ\è³#õ=M¿ia±i¬+N•y 2*¾æo[­â“ ó (´Š¶>zXG ÑYw¶;õj´Ú4ÖT­ŸmÓ{¦ð=¹|ÅMóƒHHò™–ùTZà 1Áä  ˆº¦EŠûÂã8CAQÌé µûýÔãOô7¢Õó!hõ­tºéõ†è%>½Ñè¥å7w2ED™tJ¬°á@jÐp°ðU XM 8· È£³Ë!‘ dûéëô ÊèqáÍðå+õ”>‹Äè;ÑI';Ȱ³â¢/sÑ[¯Zîx3gÙM»±Üœë”È¡ÍNlyìø‰“/:/[ûûžRËmÚ«ªŠ @AcàIâUew•k ·çrìùc[—'È­xœk¿ƒ‚çptÝ ÃZfd[¾°³ ðþºNù/Àõu·|§Šôr rãcþx®a×׆mùZÈ€Ègº±pEh k0>ŒD!À°î âQ™ð]éÖ[7æTt…jÖgì½Ü¼qá✪¾0·xu~aNQ_¼ÙAŸÂU¡ ©Ê]ÐK4¨ÊvµÐ«Péϱö%¤aö¨î” #E©ç0%6åî”é •À\c‡¹ aóHkéáza›õ•%Ńå çð‚V7ßžÒyÏB‡”-‹ìÿ+~áÒâ  ¥èÛ2ÔI¶@ÓFP¥’½ÙåA±AúÌ~V°õœxdЍh½‡,ëÓŽâáÿìòšØìŒ!lÄEk Âý(\ì>{s ÇñNµ{BxÇ!‹‹.ç0£#œ5ƒ¶åÌÀ螺õ; Éë×Å"`²W”6Hë=§'œîEÑ~è­ W½ÛlôÒˆa!c¡!¬­ 1!œ4ÍOFÜ‹ o)ÌÍÒ}–Ê¿!™xýÇ`^üÍ‹BszäêUGÕº@qWrŒšBß'ó}Zî˜Û«è÷à­_«:M’~RÏ D‘%[²»j+óÐ¥E+ÅÇ#èžç¸,Äj¹ˆó¼çBIKw>0 Õ˜ÑÂ^º}ŒC-ÍRGÈ §ë=ò@*ëô „OIb·ËÀØaò≤ƒ¦üãÄÃY9)Aì’` Ë]ð=hdÑŒ4bd¥ÀC‹ÂýA¸f¸ œ‡ ñ»‚";¨^Fîh Å-Ȇcì>À­:Ü…+!Žî= Õê \d*u2¨ Ïv"ɘ&Hô§{ ‰b3r’OF–ȿ۵j!ûü£xqŸÁ¬÷±1 <6.;§ö0šžd„‚T/O,Âw+Ümh;}•Œp¼Fhª£IÞ @\8 Òšöø3ÕøIœ© ÊD§Š‰¶nøì  Z%Tk…Ø=¶„öùÚ´V£€*M²W©ã`)ßì4×:$; KÝ:bDÐän ¡&•yeQá~ŸáÄDG‹ÞÕO_Ú äƒ†1ûU¢àžŠ ‹(@팈F#õ”ŒæýÍî¸Å Ý5pN·‹7Ç~j3zâxùÜÌæväopA6Mmœ§¶çÉ©Í'$Ö&ƒ…l¥kŽï£e4ž»*Gîm®ÜX]_Pñɦ)¼!T௻ÆÄV5¨¥MòÂ6 !Æ /¸Ø@¡Ihib‹…€BSÈÜ@×§ìšç;MÇñè FªP¡"0BŸ:€2‰å3Û›¨xÕª]¡ý‹(W”tò_ÊŒ±tûåc/X,IÃi€È>Ä \“ð—òÈ~ðµ1•4Ò2k†üî Êò=–gXÕR:ah ýŒÊCDÃèC»(jš?ÿ>/ÃOØsŠ“°?ä'q¥¾;E5L « )ïŠ „],£¤±Ž[Ã4eçfû‘ =D0Lê,ÞIòeL·Â!ÿú!Qÿª!;ݸ¶U7"Ôãüˆœ"´:´”oÓÕfˆ2h€ÍS9×]|$ÔÌá­šÑMtÔ•"”Œu—t¿#º—DQÿ}ÎN ï‹"4ìOm5ì8ÕpÅÓqë‰A„yâÔCÄŒ4=ÝÉOÉ`SmÒzÀ˜ÜÍ%UêÁÆ%Þè°6³`êlˆõvëÖ°#U( å=Ù„7dZÝ·víÑîÊx›7%Ôž„È8Q­n_ä ‡¡ÒoKµÝ@Ó°±¤M¶"™c`àW8þ*»Äw¸Iý Ü(U¼µµ2ç1^\áM¡"æjƒÂ²[„tš-@‰Wá„Ðw¯Ñ$#2Âê¾t+k¬ºëÛ Ò¾ .sêWÊn 'b†ðŽ#†ˆuÃò¤ÜcäÉßvÉ8¥3€q/ÊQ@»8àÚˆ<._¯nX-\Pœ¼”ƸIöxÐÝVîN“ €ä@=£<˜I0aZ_PÒìò¯‰"Ù3h°½Þ<¹mùEã@9Î.÷‰$:í$¶7PwÅ#r7†ÆÐ*1º;ÈàªQTÀ„f”šá£*º~V,‚lôR×PO²pDÅhÊË ÙS`KCìAæU¤€ VýßHÁ¦Dë³T: ¥‹" =­™ÖvÅ(ÑïtþŒ©ï$OS, J] “¡¢yÙͶX¯ž N*)'· ŸÅv¯ðŽ’UÙÈ`Ïg—wЬhg…× u3˜¨J[>ÊàZ¹l)˃¶€1Î^ ×—¼0>áÁÎI?c»ȼ©@fÞÃË#¼ÜëHb­Z®Ø…3œ|B¨x=;ZBíÚ­ZÙµJ³g/¬öÇxA°p_¨øz©EˆƒÛ˜i%ÒTÛ›£ð¾PV¾rËŽ/Ȱ)Òuv©MÛbŒ ¨W:±Ì 9Û•Ïþ@>ÕøÐ&ùšTÛ阌€‹&R`õîËdîÑmËÄðI¬ŽQãÿ»å^3.l‘ßÿ4iRíò$™3 Þi$“ õ·&ËiÇûŽI†º †z„¼iÀÖÁçLmÊ’ÑŠFÇ\eƒ¾hRä—6;!wF™·t3Êf;HPíãÌÇ=,Ü1ÊŽ°`(#$ÎØñuñ(¦6‹0± y{vy€b2H¢”õ;àþ·é¬ÁÈ5@²½OØÝdžTÏFЃMvÏ€r¥’ Ê —Õ®T’5%´t@²Ó™!ã)oHŽàò“}@¿áÄǘ)ï-‚$UxÞ”jFsÐý,ÏK†ΪÑY5áÒ+¸qfR§@²G`dõß2%·á}ý)M îÇ1~–ŸÙQ²LNoÙxl‹Æ•YGpOnY-þSªmÙï_ü ~¼ižN² Ù0ÇLµX€—›+ŒŽ¨6ðf?ÔÛ\`fSÞ W…Íû ØSÄoíèe4fˆ3Ìz¼€ÈEs 2rëš3²ÑÅÓs¶žõi!R?ÆÝÀ2%fÂAÕÎcÒ¨¥UrÙí$¦„y̱ù¦ÅމÖqÉÏóuøÚÇ­ÔÀí#Ìχ˭­ûÍÜÝò;WnæªvîÂ5üñ_Xm÷cœºTÊhßq3ß ÆÙ@ б„OJ„NrGŠ£ãŽ’Ñõ9¼,áå6BtGaP˜ç3Z SI¶ê)¯j-b·H<¡Î(€3JG&YÛ¬ãåSºrc»F*Žíï÷-²ÍÐÛDËlsò ‘6Àë4^V‘ò~9d&U,i,²q9 ÖÚaÐ §2c$eNö¯@©ðPƒ:hÉA*%÷ÙN;ÐsfÐû¬ÜÐ{W>ƒ}½“mê@ÌIö’IR sƒ\!Œrÿ+Ùƒa²?ZÏ(²¬NÔ©“úcÂýÚærÜÔéN¶©¡é8À2´\⢶AZ(8]?+¥ûz¸š²Â’t„#5]D•KFqíç´¶â# zàI¦éê2‡tzu)u.¥ì:×T)œ-®>ò¢öÆÌP”TP]ªØ|ë_D3£ng—@–³¡¶ ºæôø1ˆÆ±N«3[wÌŠtw¬þG°Ž½^¢çlI¯Ù':LÐEõj‡=bœH4öÙ•Ÿ 5[0ä"¶ ŸE«Q˜Œƒ8RR&7nzô©ø!Y_1tó.„3 6L¦ƒÚ<íÊ¡TÎyØ'šƒj¿¸eÑ=%"Í!q/IÑø·iáñÀ–C/P|Ž*¹†o’</¹|BÄ"&h9z•¾Ž]íl6Ò¹¾kåêŠ×X³­œª’Ÿàý t®Òfê©Ó/½\¾Sç^»8;w‰p¤öüó>š©9°"s”Ñn“©žó¹BKÑc×kæ|l6Ø)µñHx¹içð°‹í£•L¿[Bò™y;à¼)€.yÕ6¸²x ß&øæs͹…_Ѷ8öƒ ö›MC¹aÍᡆЎJ gLF®m[µrC/Þ¯W›é æÕ€6 íYìb‘ÖL°¿‚´L†é#Øœ! Áo#ð› è’Qc/vÀô0|g%X ¿]P{§ ?ždÀïe‡}­xOT„6LuÀ“÷ü7È ¯%™1ÙÒgLà“XÃ*°êÂ…âú½q½É÷(ÒF[üzÝ­ã•`ù˜]>Dˆ“$¹—v I:P² c[`’µºš|Ò ¡c0"[ç‘ÂìòiUQÕÀÞO0Íå5þGÉžêeï[ôÑJN? üÚÖ`Uƒæ"›ÐÂýÑ™Ù\4…å¨X†ŽpàŒ¤i„rÁãs£ZkONÏ.÷ªÎ¾!ë–\äÉâÉdSNÖÿ""ë?Œ„\õLíþSûF˜ZšÐÌHU#£¨wÕøgPÙNñ™` Ã]Hþ?ô¢êBv«1ì_ç¤ §¨H.6pŒ"jÖ¹gÈ}t¤6`¨ú· ‰ ïêiêg {’ö ¹my.<•öQ–ˆ>5æ Hô‰ÚfÒîV¤3Dú="NX² Ù ŸÞ%¦žÔtê?41jS;¼Us4;näïM‰êÿcÒ(„ÜnÍÚ¤µPåèÞôSoV¹7ç»{óÂæÞ\Po6· ÙõZäƒÚèjs0؃6‡yŽñ@‘Œ5_O!5ªÛÜ?%ìCú¸æÃgñƒ8÷ß"Šs;Ç”XòiÐKóWõiPLÓـОÙE­›·R]·lå•p= ÷¬» c9®»‚©¥(Ó $땪³ÂÛi.¾æøβrñ*áÛO>ôù|”íZΊ߷é)f²Æ7g uÝaÖ±—5ü¥@?oÚ™khåËJ?þ/_ Ôu¯ÖÃ5OAØ­&žÍì´ídÐ"éÓ5 Zwïs:EzÛpVWíOêŠß,Wî“úe…}U+lËiðÖ8Ÿ9oêuðªü*|E<›c;túvÕvñ%-ÿû¤¨St!iô ½×g oDj”tŸ‰w9¹Ãõ–#–À¾>ÈÇ:;dø.­Rið­6—$ ­e¶¼Ã3úžï’Aî°±ßçÆä€Ê'f$‡r[äÃ!Ç÷j³ gM€®JZÙä)‹Ufê-/Ê üÈdœ2;®†:ª ¢ÿe n’£8K'?"!n¼cÚ ½:B¬½¼:ŠÝlǯ³`ѾÚ~ŠñG¦0Æÿ]Ü=`½=¨¹Š{ø­ĸ[òÉ‘A¦»†A~Ý~E%¦ ¨€2çÞaÏ[…:dvù›ˆnÀ`õ¸Íç¥(ùð=dð6í–AÆhèT”*Ü«b¸gNÅOtœ/Š\á˯ÔÒ>¥ëÐÊ!â]À÷=°’†ä®Kq«ÝX¬ß–ð Ñe—Q‚Y$!K¾ —E° €Ö0'´uG!98D/2âk›'ä ÇÜÌÔÔÔ9ÂWƺ=[¡oÚã)|Q¨דîŒEG&óÙ«ºŠV‘»A.çÃ7²jÕ}¯”#då—-ö«œehv}ŸÂ75žÌ_gï!½…÷Ðq )ôySj•‚95µ‡´±A« Ã,‹Ê!–ñÖÆöpŠpùûˆOHQxà*ŽÄ 1d°#1D‡¯¢2"OÊÝ€ Cr7ÜõPDg¸;0ºùƒ„qp¢à2$ œ~œkŠíüŽ©Ý!Ìê Å0Ÿ.ï ¢¯›¼[=Êaœ¶¡¦#Î^áþEYè” FYžçCß&rç*½œÆñ~åASþŒûcƒblØ%ɰ;ªìn¨¢õþ*ÈTâh~3½Sçtè=¦öÜÀ»D_¦a´q÷î¸ä D.º|…0 ±(ÃXÔ‹rI!‡J‡¤µqZ>"ß]À8Mñ‘ Uy)0¥zú&.TÚF8QÏJ·.È®Jˆ}ŠN‰wd`úöQö•€<×Õeâáº{:uã[ †¶$¶'Él'; ZÙ¢E“§ªßPU; C›«#ʵB· œ—ocIg´:ÀÓY>ËÎþ„Þiíbçu6_ˆk$£óÏÖm£ž1ƒÊA‰ÃÝ5ÃD³áGg±61y–æY$åb‡óÔâ÷ b’!±ÑÆz»_Oé@ý¤ù¨ŒÕˆVDýÊF•Oph &0¸èî‘æÁsŠ"J”M1#å´è ÖSž#öˆ- ^nÍkØ{n­ü0·âU«Þ;¹rN¿õÐêÔ*½PãÝ'«’SЋßÇB_Ж&íkœ/³&ø ¡‚De¿É?—°F?’ÀÊâ×µ²Ø.Ú#GM<ˆŒ4ä0à< <Å÷3&,‚¼}pí3öÈ¡<ꄨ<VbŒNŸaN\æñÛÜ)÷@ú0<ÛYÔ¿O¨egÉÚîä¡÷òQœ¼$M^&.ƒÃÒoo§’éE{S¿{«_à-»6½Ízy€^5#ëaÕé"ë¡0'ÂGsBnÐw·Ïê°¸&‹¦~™íx}(*X·áòð î¾õÔÑ[ÙõÚñˆè°nùÉ:àÍ⢻/J‹×ÏX#ÔKÈ会‚x nsZ \pY>qÄ*"ëÕæ›ÁÅ#(Ï¡7-žÁAu:Oÿ13xKÏTïè \å„\`wø%¼¼@ ¾É0C.í«x¹#´ÇÜÁÄÞ$;“œ`ZjrŒÉ³&ïø¯ñr¥k4ÛÒ+PéÓX-ë˜L '²‰Tb>û{/&Ž$ާ^K¼’ú¥Ä±Ä¥D*›P1ˆµ²ãFÓõ#Bm©´²Þ\oà+Ñ"-zCÕÁe©ú4õ(ù7øGh:¿ÄÁ?Cú–ùÙBðæ½ÊQ/uˆÐÏáhë”â„»;´T78š_ÀŸfaÞŸÂ7e ¬3*ÞZ zF÷ˆ) AçݹgWš¬^ÑkK•` §ð5]<¤Æ/P-àåO4{‚–z@ð½RøV  ß Ö¯ózÆU-¹Ïb9ùÇ ø½ôsI-¢}=û͘™ˆÆd ¿#tÁ_4KIúÌ7Ç7ý%ÍÄàpÿðOÄOÄ?¥ÏS&8¿}Ñ#¢òÿPK±Ud9H_í*´b ply/ctokens.py­VmwšHþiN*ÝÛŠVIÊYƒf·]19DÇ”S9€ÝMkûÛ÷ÎÙo¥x™gî3÷m.súOyZç°,³Ï,-Œ—×Ö9¾Îø/l¯ãeTÆYZÀ:Ë¡x}~Ì’â,oêÀ¢tÃnט}ŠqQœ0ˆ äxfQZB™Á#ƒMÁVA?æQþÊ ²òË6Ž¿²¼0Pé'9„L+Xþ·ý'ËWE«%æ-Àçܸdy„¾¨ñŠ¥%:Êr í*ÙšµDKt@ƒu’EåÁ{Qæqút0±üÉõm¢Vœ‘¢2û8±…ä }o:ãÒu%M+i(¥–´ËA³Ê,Gúš®u´+íBÛj—Úí^ëõ´~_ƒíVƒËK Î4èáSœìã‰ãÌ”vLÜ»)ßaìxB˜9c›„‘ó§3² óÑD±Üø„å‘ÍžOÆ}“îô½sM”„Š+a©ä’–„h¹K›Ü|C²}Kô¶\'¶Š"~JŸ1 ¢ W8.ptqè8zä&wòÇ=ŽíÎQûöÎr÷Ò«t³’ÑÑJæÙ<:òMšN>Ê)éqµ]­dŒN%Wâ.NºÌ÷èjŤ„Å”êé9J‘ÌÓŽ`Zæ›e¹É¬XÎÖ8Ò%UïK}+ü¿öËg,OùÉÊdý€: gvàYÁÇãˆX?3<XgІ9,à| xoe &V`{”v)Éùßkø‡- ¢’0»BvyV†þxlQðíÀñ©\¦öØ¡໾·wÄN’ø¥À^¢†±Ë°ë:“©Ã£³^”VùÀ㇠¹v„(ªuHçˉR‡Câ€Ô +¢óGw®_C.8âpüÝ–CX4§Ð%GðÄœ"?8ò¡ÎGt÷Zƒz=MP¿OZ„[a¡[7‘,$ݺ:#¤f»°ƒ#7Mˆ°ÂnÒ1I© êdß6@&A^“ÖB­£¶’UÕBt¼aÔ骚 ø0HSÅ!"‹Â”Uq ]T5›C(ìšUmÖwÓÍ}Ž0‘csŸäÖ‘Úõ§#K.MQ Çˆ,SVÛ©Ú½ˆbC'C ÇöØöfGl]qèFv¨ëD§÷¹™¼yÕ³¦÷iÁ€çAô¬š­Â÷­‹Ç‰:S(T)LP›¢+»Ö14'­FhQiÕ»Bø­Ò:¾sˆ:_ÝUJƒZa]ÉàïPWz'è°[Ö‘·tHd“¬Ññ"Õ=‡Î>·ô¿#ýëÃB ¿è¿=,:2ïâ.”ˆ›å|fߨ ^uÕùæn±'.þAIø‡¿´E®®ùí‰ß—ö$×®o͈BU‘¤­¢ü‡©aw«·4ÙÀH:žVÅ&ëëÝSqÛÓOgãÝߨóû0 ÓÅV C£Ýî Â7¤5Ä;[´,.z ,À¯¦‹¿<Êï-LèLúªºíA¨œ’)‚,{_÷¡>-_Ön­ØDâñ¨e[|O±Y„ÕØ†)×íàç„Ï–FÂþe¹‘Ä)K3¼îàÌ—(Ù0c™mÒRUÂT_Áœám …òxÏn·¶ëdÒ°ñ•ÑAžÿÙð×½øÂâóPKU0^;_¤Vk ply/ctokens.pyc¥VmwE~Ò”ô…"XŤUÊ&! È›@Ú’mYÙ&a“ò2ݶ–ÞP£!å°)4úEÿÏ¿áGwæÎ&á Ç4dî}îÌܹϳÙ;üù÷±Ù3½ÞìßþÞæoôW þ—M€’ IÐP 4šÍ€fAGAs c ÷@ÇA'@ïƒæA€>}útô èSÐg ÏAg@_€Î‚@‹ /A_Ζ@çA( Ê€²   (*€.‚.¾]Æþ(.G®ð*y Šë¼Å¥~ÅÕÞ€â‚oBqÍ· ¸ì"W¾ Åů@qý%(¦pŠY”¡˜È(æRb:U(fäB1©U(æµÅÔîB1;Š ~ ÅïA1MŠ™®C1Ùó­C1å³¾ÅÄ(æÞ„bú-(V`ŠExÅ:<„b)A±¡XÅšlB±,!+³ÅâlC±>;P,ÑwP¬Ò. õŠµÚƒb¹ŠkC±hO¡.ƒöñ; ®€¾7ÎUPMç~æý ¼j?Ŧõ¸áZ׫ÔkÍ–qWGnsäVÄd·áo4ûGØY÷jÖkyënÓ¬«z¼ªÛOêézÕœV ,תÆÖê-cq\ïð›w½U9$WÏú<«óõ6ãè}:okÌš 5Aî}cj®IçÞß(ûÍþl\ Áýi©r¸N3–œ Ù˜¡À£ÃRG8ÃÓBq˜Ÿ€)£ÁhBa4ž0²õ‡fGË jåà±HÔ(nM$WçñïåÊ=·e@ƒT<#âêÜ•úúzÙnàÕEÖ¦»îÙY¿.y]ß÷M¯i)ÃlŸ›r2ÌxNB–Ìø«„¶)YY‰&ͺp`ð’,]0cÑŒ+²~YÖ‹Y³°lV,GIs¼ bÎÙhV`N`±(vÅ&Z²«·—¥œl˜•]Â,'5„%1Ž˜´˜M1[b~ó‹)ì‚€¼·Ìx3J™þD§ØÝ,çÔnî§-ë\ÌÝØÙÊD zeÍíÁf×ç=qxÐ ]ŠJ¼Êqx]Úá„Ú´0;È¥K&˜.œ5Þ›aGò<]Õ9Nê“Íí0 {[' óét¦.F§uv?] Ï¿={~O³Ñ_-XEß‹< €‡: ãM “Ô÷Ço \ŸØ1±¦£%‰ÞÓ*Ì8ùAØÓé2…Hçšut6ó‹ë¶_µ_˜ßc·Ók÷Lðån÷°m¼½ƒÃ^ßÑ{Œ¬}G_]fˆôöä°Ó¥ÂêDýü³Ý½ƒèUîÒÅüµÜa¯ó²ý"ÚíÚûû…çÝ×…½þÁí^”þÚ¼áýý"¸µÖKJWƒ‰3‰!ÙdLöÔdé-‚ºðB!Ÿ {½ÏƒÛz(k¨cA5.ùëž“º [ú`Tú|¢æ\ÓÓºÙ!îŽé1SÆ•#¾ôêiãÛn-€ûà†_7]¡¿Ãí÷ˆqtÿO7`ñtë–=¶y °í[Öø¶½³§SXWçüØYFÜ8;ÜÎÅ©Å5Ú–>7b2jÖ†Î86ö£C=ÏD‘À±12ã‘ñ?Ë1º,´Lã“Ö/zµJàêÇeqÕ±< iö’(n÷VÖQ—ç"Èæ/0¿ìl¬•mýSÃß|ÙNØö/Ä\ñ}Hâø°€ÿ›0c9µÜ57°;Výz9>»Ù ¼Úš¥Z¹[æÃ™Tàê÷`õ÷à_}\ñÙvÛ+úIFð0Ÿ<ž˜OÌ$æ“ó‰ãÉTRÿ¥ú3—œ™ï?ÿ¾.i¾ÉTò?f‡Ÿ™Ô?PK@x:Ë+ðE&öž ply/lex.pyí=ks㸑ßý+ù\–v8Ê̦êªâ[ïÇÖ̪â±ç$Ïnö<>-A63©”måñ߯€ doì½\Õ©’YYF£»ÑènîŠ×ÏùÙÙËt} RùÐ_®wváïã|¹.’›ÛJt{âÛ7oÞ¾†~Á£“ø.™‰}ñNÆIåZtOâkø*NO{ðü(Mu-E!KYÜÉYŸ`Žä,)«"¹^UIž‰8›‰U)E’‰2_SI¿\'Y\¬ÅÉnÄ4Ïf v*±’Õüþ÷‡Y)ò¹FišÏ¤X¬Ê æRÅ€*B¯ó;|¤I”åU2•HÏ“R¤ ؃f3#ršÆÉB}F†³È¡Ñ€YÎV€ÚLÄ/FE¨)Îòéj!³ŠèLР×oa%rxZˆE\É"‰Ó²¦9-uµæ gv&ê‡Ï³x!#üμ¤ À׬c¬ÅµDtsÂAf³¼–†0î"¯¤`j¯Í!`51‡<õ2ŸW÷È!5÷ˆr)§È?Ð/A¾*s2桲$Œ‰W/~ŽÅøüýÅOG£€ïŸFç?O'âÝÏðp ŽÏ?ý<~øáBüp~z2ÅÑÙ üzv1¾û|q>”ÎÑúvèÑÑÙÏbðÇO£Áx,ÎGbøñÓéÀüÑÑÙÅp0ŽÄðìøôóÉðìC$„8;¿§Ãà hxqÑÀÍŽâü½ø8ÿ½ž/~¦ß/Îp´÷ç#Ü–âÓÑèbxüùôh$>}}:Nîd8>>=~œôU ~œ]ˆñG§§î\ÌùOgƒNÀžªx7<Þp0šêÉp48¾À9Õߎ€€â)î”ñ§Áñ¾M0££ÑÏ‘‚:üçghÅÉÑÇ£0ÁîVÊÀò >"â@Žñçwã‹áÅç‹øp~~BF?ã§çc"Úçñ€ÚÑÅ @€fо¿û<õ†gƒÑèó§‹áùYû' àyOˆÌçg8aâ™ÁùègŒ´ uˆÄO? à÷R–(v„¤åŽ/ìf0"gUÏUœ >œ? ÎŽøüáü4z°lÃ16ÒÐÀ 0êgš8.`† õÞe∖U ß‹£“‡ˆ¼jŒ0*¶!Òÿ bû™ÍÎdr' Üg“ ìgq(:¿ëÛŸ«øº~¢~üÙ?ò’ñu ¢+IY2ìì$‹e^ \ŒD¹•Q­—þƒ21y¹ƒ ƒÒ Z-S•ŠñR|Íò{P< ©@þQŸªXìð€ŸÖ 12ñmÿ_é‡15»ÀV€[—š÷ëÕ ýÏY‚úêíȇ©\Vâ¨ba(E‘üßõß„àV‘¸^W²ì!úƒ‡ªˆ§¬ÐHÅ&$óU6ea{’Ìç²±-€*©4¼((A˜©ýöwl±„ç×IšTë>rŽ$ìëuH²y~ùæJ|'~ÇxÏ䜛 ÝyÅ(ÇU‘‰yß<Þ‘i)ÝmBÏ&³Z…¼Y¥q!äÃŒZ|øUéT?Ó[q§ þù8*•rg’”PFY"´Í!€éã$[ºÅþ_Ưÿrôú¿Þ¼þýäêÕ¿ì+ââ2!üê¶@–¸¿pIf—Ù4_e ñ`tTžYŽsŠWi%$®*€¹…ßSTŸ¨ˆæI†6ÏèÔ²§òÖ¾k†êÕt™•“j2é–2G0‡2¾‘QiÑHà“~\Ükè=ïy%*xÎìNHÓà ‰œŒ‰EA4#À8˘«hš¥Ò¥ˆºÁœ`uóë?Éiå  <ª°n®gÇtÜ+£½"Ú›Áÿz±'ºŒ,îúT^©¯)-ËÕwXö¼ìYÃ!¾­ã.üİ#ŒŽá)¬Ík°kûc‘æ77¸çU“i!c´¯×D  €¥¹J%Z0ŠŸÒõ)<“Eˆö2Ú(Ò|æ°4sÓx FX°©Zóò&ú—7ú曯÷ø¥Ñ»fŠìv¡)КˆW¢ó%ëÀŒ5TèšÚOÚÝpºä@t^‰Í#¯?>(Ïó@›À£¨iʨ!¯W7ö°6g+8\¤´†›iÖ o¹¢5¿‘™,pUA"æ RÁ*¾Òh¶F í yv¾–¯zAQºØYÅTwh¥ÝõÙµë®hùâfF®dÀÜa;×9@ ¬Zƒ”´1RzT€„cl ì µJž¥kT0b.ïÅru‚y §«Û|Æg CÎò€Æ¤õ†¥êöj _£Ì ÈŠÒËê0BcsG’T^Ç’¥X†2pÛišgÒk{Œ¿Ù@¹) á6]¤Jñ™ÈV‹kK§pcx@§,:MTMçù­)#¦eÑ"‹üm ¸‘Å’ÁþìŠqYá74oŸe* SuœÜúì²ÕUŠ.˜g gò¡‡ûP€ÿ@¥žg†° Ézä£á-âåy àBÿ›"_-Õj—¤(A”*…ëÐq×°AIæ&(POhY¬¿þÝÆë$!£OÿEÞƒÔ¡d3H¯€i¬ÕÀ˜i±c2¹jÈ\®×yª¬µ \´ý‡gC<þu<¢ZÀÂ}áŸéWpye¨8¦ŸÀL¶1 ÷V:¨^Qê]IRNÅ‚=!áž7YC œÌÄô6FKY ƒ»a>¤pçàRcÿoZÈy“ùÆÙçd•Æ)nJµµl@˜ÅUÜ”»âhZ­ ?K;jÔÙöBê5à üt±p—Ú£ Ù¸&Ís*³tÎ-`(ìíc2Øiï‹.œŠâlÝœƒ2š}O•ÇÍ:A4 iX¦ÓÂêÒï^sÖ–‡âmëÚJÓ*v[$‘îÒ1âï34½emw²'»ŠíµCÄÑÒlS´á¼ßÇôIÀ¢)³2ø—@°N@Ü‹^K`¡rµ\¦‰œE"©Àr‰aUïÙ´Ó¶¹n¥’¥ 46W4XEÃŒ]Ó¸”¹ï$KÔëM!0_µi”d@e‘he€Í“äø(ûõÄ€/yÜG×>Ð…†ø»ó…ÃW¹ŽÚå r»»½¿—ÝÞACwLbÖË«Æ#„:Eç‹VÀÃoÑTà 4rŽ€¸e $E°í¡1ô /—o®64w胊’Ù¬;ïm$[ÉöV ]u†PÇ‹ÑêO&¨õ&“üùöª×•ˆl@ M àpkXæKXÐ+ %õuÚL]Û‚›·´¨õLËÈyƒ_¸S;Ïøà5ªm伦L=#•¸µŒšî(Ú?dF3:®àÀðZü„¨]n©Þñµ ò¹F§ó»Ÿ|Á">ÔÎ’â°Ó±ˆ ŒŸ”I†®©ìêÆì…d‰MNHwU˜hæ§kQª']É õW¿iXu;ýNïòõÛz“Z-󲿌«ÛþŸò$ë#dïU§¿\w € y,þîêQç¾Ó³žk§Á®ØƒÖêäAÞÞxUå¸ xÌ^Ûn›O§?‹®òYB·ú³ýJÈYRýæKFn'M!ËýÜ k¹¡z§÷J€î§îÖεQÐììZ ­ýµ‰ÖÚ_5h`¬ƒ6ºA+ÛB0 z–š± l‰¼FNSTº¨÷j3ÕœÁƃÅ5Võ¯‡¾zº4ç‚+¿1‚.]‚¢ T}Å$µ:hÈ6’jØ $rS‚Á&›óÙ²U­Øã[ ÅÁ‚hZÈÇkÜŠtSA"´„4lœÝÈ.l¡.À턯‚a´IàLHòø2¹Š&„ý¤ÊI —~ŠD¡ŸîÖóu1€ò4úÎ&+ÐÈôŒ@láKm7oàLjâñ&è 9±n¶ó ÉiMK±¹më‹‘MÝÑÄÝD£³} —„`>—²Û{FU ²w¦5å¾%Ý“ª|vE©Gwôä|–?®Z¤§+HÏd:«öæasɶ]•9 þ §ÝŽº§Üƒcq©FÂeSC¹›)Ì"2» Øh!Âþü¿iKšyÃÓË}þkÿÊ9ih«F¶¢ìD7ý7žøÍ¡°T¤g{ÄI)Å0äÛ°Î0Óº„Ã2žQ‰kxÖÎõÎÚô9Tøök}Ûêéh´WÚÕ~ý`ƒÏÈëalq5ºÐƒVÿ cf¯~‹£/ ã”öñG|²ªž_5YW´J󼹊š+Ö‹X=¡ž"…eé)ÞüC’ÁXfFðÚú¦†£Æ6µ4š[?¸í[|yõaä/ÏF-®ñ r\Êù•‹Éµ¼c}_QûÏ©ôuÎkñiUÞúw8phª/\žiÌ‘ G%5`_±í`næsvûÌ“¢¬j§y¡¥$.Ò<ÿŠ!r_¥ñU:N¥òòÀ:ÿ(oƒ¥W¦‘¹áŸ¶HâýˆÜJà –` c «Ót**kSÜ(i‹ ÷[ùœ+ÊÌ‚+z|‹;Ú\â’Öû3­$Æ+‰°]EŽD/•'ÞßÛhþ9Sá !@q’Åþþ§ÿ^Úê8‹€hécä}@ ôA­véï¨@ÍÈŒqZw%ohXê`_Z¬çãŒ%ìð ÝÈtp*ã;x”§3A`ñôësr…IušwCZ 8Oz!1©ž<#Ùò¥EµàëÏd[ò.ÉWåóï«zÐÐ]p½ë<*A·nï9'?å[‡è‹âùOëû½‘.îè-!D6žqæå×dIÃßâi)óowžiž4Ç«v*W‡"{ÆÉåËJÇcèõ1t4¶ä î§zŸå•媯d¦1Ø}+ôô™8\»–xº™Çê†ÿ‚©•É5Åj±ëoƒFŸ*É´ÊRY–b¯ðèˆ 1öSÜ߯>ÂÛžY® €gZ¦ŽÇqiè¥ù/ëòe")á`^È?¯`š€LÝ-SiÇΘþuøÉ¡½¸ös4 œçðƒý¼¡“¼³‡6DløC}0»¿EŸ¬Bå;5¦«ŒU(E¬ª,ŒÉ_HQÞÂ)ðõ4)¦«¤âh L˜ç2Æ0„ˈt'4oÐýã¸Bñ’qºR5÷kžBê ñ¶ñÌÜøxÓ9kQâ;(&µáa$£!"É6“Èç¶ÂlÁGC0bWÍ+J­˜Hoêh -ZðfÜÉ_ŽÞ–x»í^è4‡uègs@hÀq›Ðlѧ€™–VæžØº57Ôö­båæ$i¬v=ѱñ !$ôð0Cp8ðª›CxôìÒ­1àÎä"¨÷ iJYá%ñ>¶žä³„$áÔv+éš÷‹>Z'm’JUÈPƒ6·"~9À50É×&­½ü5T°`³O%\¯­ðôHàÕ P¯Ù_ñ…l#E4Ô±¬D<ã¼%–µ0ÄÈOPt“@úaZúc‚(^&ÐÚb3ûáí)m œK¾i0¸“˜ª¥u™ÎÃ5Sû.R|‡ð'l³È9FÀŠ_ô+ve<«ܢ,ütÅß%) !9bµœÑwë·Ñ¢:6ŽQÑ_÷*"åëæà-LHI É|Í{QEö±0ìB̳úW A‹Ôö*Çé·ÕLi¹ë±×€%ÊÙÙ|À˜œê\€Î^y°7;#¼ÞÞß+÷§P†˜,œžbIlCW™­#àÇJ³€o½þ4Ÿ˜«Öðâ¬TäýVÀæ>#²‰Ð‹\Í{pØjp·G¸ºÑ:dio êsßk-M@ýû¾ÝðâlÕwª‘ÑyÞH­í¥ýtc¥·Ì8íP=YjjâUÀÒÁ¥U6,C_£ð®&œÐC’›D¿úÖÆ3QÞ6E ·=+ý;„ogõ’zö% 64ªÇ¥(+¡PÞ ×Qí¢I‡;r`š˜%3 „ÈÑâ6ˆkÒQýˆ—0Æ#ÎúPXƒH°³ÄMrJŠÒ¿Õ=€åÊTd£Ûlu²¢4®ð¾SêæpÜ3çåÉEu{žeÍèÆh.ù o¶òD šâá9òÇU¾dÄì(o-yPP0$¥§â—_1GP ÉJñn•¤3Bv ­Á3e…Ht¤¤ù=96tÖßT…ã(O›ؾËÕ8Xiä­Ñ³äÃIªÈ~~ÞÈŠ±€‹8vp‚—aÀ»:5ÐØç…rAÆbVÕ«ü`¤NL—HdQrÚ‚Ií$fOˆf‚¨ù)fd¶¡S»³;Uq©×áFe,Éì.)ò ½[¬,óiBF¸)¦°Ž§Sж|rBq•±!­Ë.¼À¢àÞj!c*ïÀ^SûͤK‡=RIÐöïu]G´a×eR…µeñâ£êWד9l7ÊpŸ“y¢L'›¦vêK/lÓJ8Á”+úCº бŸÀyrU‚@Ü÷bõ‘Ä&‰á¯à«¾q’/€aß%"Ç*Iuq*t§”Õ ó€jWKCm[]á_í›ÅR:ÖAà:.“i£þ…vAÃ`\!>còv{Í'ú6.ôŒwVè Ýïw=ûaC}“¶ÔH‡Ð½SíZq6 ˆ›ÇmØ›>¢v|!_B[¤¶j¯=îWááû·u͉z ÝÛáÏjSÒ9t7­×Ÿ‘"¯>ß6Óy°.c×é5»1«ú¡S*žÈÜNÃ"<¢.[.$„ý -MŒ“ÀÐ?u\-¸÷“‘sØç‰R¨ið¼þ儱åÏ¡.â3tÍM&ná ¬a›qa¿º9&™¹MTÑÀ-ž¨¢Ï²À)È'̻خÂÈ÷wQÖ<;l 9aÐ9 ç°aT]è®ÃuéÊl±J«d™® ×FÂCÀ@¾Ì®hxoš0U!X«êíhö}HxXYü}©u(Àß_d' ÁYâ¶ñÏ€^^+¦°5Ôa[òŠ `Ŭ;í9FÙÆ…ª*™jTÌÙÍN…‘nRY_nšPŽê4˜¨µ‘=ô§á¨8ïvá›Åærâýú÷ZÞ”•;¥#A|ºyó;œ£tZˆoŒ=ês ?ð¥¹vèÐS­/ÔÚZðšéÊÞÂ[m£.ÉшÎÈÁd=Ÿ„ gM }#[‡¬‚„t'´Ê›Ö¸Íµ€^Îqót#Ö4šÃKÊTývK˜væá”×Û§RºØesðoµaØëDœ¸Þ²I²ægkµ¾¥à"Ǽ„c#ðÓ¤%õnÏykCß¢âØœ¿1QÙÚgœ§d«~mÒ¨év-âÚÖ<2ûÌ,íþ/%škÀ6I¼­±:\ô:êÖÌ=ý™s¨KŠÙü–Úþߘ™;KDáJ'Îáú´ŽtP9€`ãO0‘kžÓÇj±|yÀð?…¥~¼<~ïf `õU®5fb3N½ ]-S!q•RùâVý_<‰Ë&‰éÆœfA9½“³»­'ß[OþaŠ–!Šš±àŒS‘‡ÅJ6Ýg–1®ì_á [¡éS ZÈõÙk‹åËÃé}w½¶lN§›ûm(èïU@$ôá«äùV•ÜPÇóÍ긾žºÄ¯\ ?µåGtd i.KÑÍaƒŸBþY½îæÛ'ˆàºWSpgê‰Oø™Þìô–RŸï5ÜÇi † ƒ™•UŽITÙ_|B/Õ+m륭þ­3ÄSÝ¢y|÷΋$Ýë›i Vùõ¦ÙÚ0Æ,Ÿúµå¶Lâ,ÉX½sçºÎ;_[üJj¸ñM7ЯÓý÷Oßí•ßï•üú$–†=t—YA€öåukvØT]ítBg”-´ƒmr(¡TWd–õñh²>‚´Êç3—M—¿þLÈu ø|-â©lÏ4xÄĵó7m /öÊ–ùF-Ž- XÙ¥p•-üÝŠ^Ÿ+Š”+8p+PõŠà}e9—:«lï]‡ÑÅ9ýIZÑ÷£à‡n$‘ ϨiÕ€mЧUï¼ü ¢ÝQù’Nãï^Ûê€5|Ôðü®-À³}޶ ¤¬s}©¡ïs‘—i¥Ô ÿD’¨=]þu-¸Émß Û/“}[<ÚÿL²îiBŽV`«LkA98þӥأ™Ò?%™²®ñ­^ïX=J*µúCí}UšËŽNä•›{ ª^Dˆ{3à¾T¨›ål­¨ˆ Ãåo0‡ŽýóžDþÿhñG‹ÿ;§‡6÷²MàÎÂx°ÕçWž„çue˜î`<]òŽxoåôkiÕ¡­Ì›g«eŠÁ(¨€Í=J·g¹áŒKOß%ªŒªe\”T‚Ý„òÖYÇ3ÌÚY•”Ó,Jª§ñ —J‰Oï£ ¯†à<ûEØtÙ q #óN«4,×;Wï"1?ãKH".Óª_SB±íX.À@©Ì12š"ÔûËõ¾IÓÒ*’ÌdLUEaJÓéë’‡ç°^5ЈÏÞ+O\G“øèãE8ýå)뺀¿þEÙÃó@Ä“‡½óÁ×q¬R*îÆ£™‹)›xŸˆ’ë_£j•éš7òÏö¿”ßÀB})_u«‰z­òäÍëß_}ÓûÒÝ·bcƒ=›}Êo÷-O)IÎ[¼)pëe“ŽqÄ0ÕØãÚ@™¿÷ñ¦w^×Ñk¨?.›×7Ø­ÜÐ-ÐENt5¼·M!†5^Åa=1RÍaëE§T@ËX1¡ D—'(´M{“ tiñIÕ¦­C+Q6XØ›uÌ®$)ž±Iˆˆ?ù À+Û(Çøy©|èrÎ)'UpL›ýê[¿lÖQÞQ!q²YõëãT*ë³ãŒ±ÆšÓ"¬áEô¢äÃ7‘.__S*%Øáÿvê,Š(Ëñ–[[o–ŠøeË&é‚íLý§¹\ðÀ*ã®k%˜äЧ$E`¹µë?‰CÎ QÒôÞ¨¿ÚHp5=Òv&ëGãÜL•0OÚÒ$4¢‚¥`æ†.áü ót#à:ÈX½ÎÌJ}£Š :·&mýn?á¿M?çßk|&”#‹Qݯ‘~]‡J®þÚëñ»eaÉõ¨}'z-©Ìƒ ¤]™f-õA¾53Ö/~2v‰÷jœnM†%èSN²P ¤Ñð²sΧÎ}•ÒÓDBAڬꇱ.ÔÞI Öﯳ*ÖõšŽcÔ’EkÕ©YÇ0¬zu#l» QÛŠÑõ«l¸=§>yaëä‡9ÔšÕ!Ùâ3 xKxCQÉ2n2Ô“†}Q¿¬ÅEß$ª×ùdµXrQ_΢qãR4ò¶—Þ=}rQ ¬:Ð .ôj(ŒçuR/MÛØÓ Â·zš·mì«‚š½Q­À 5[¥+ì ì¾èÕŠ[«e™IõЦŒIɰgç$ü;= ávMgëhìRA¥Þ42oê-*RÒ¼Û_œÒíqrdˆ¾ž°Au»ù²Ö žp°_Jç­Ãà—`[D¶Ë´©(ÍzÔwÀÍë_‚=¡ G7hnWÍf®‚ùå#îiÕºýå‰lºþ}¢Ãå)ΖzR:eÛeSÃööó¦t¢—¬+ óõ÷ìèÖî±X“î€*L݉ À€ÔxæØkúDëTvï4Ç´ºó¶Cù›_œ þ8ïÏOOÏ¢'Zõ9{‡‘ôJ—àåOßô¥½ ‚5?¯‚“^=„ZÀ¸ïmª‚z{Cë…-DˉóvðFs¾m²Û»ñÉa>¼KºwhÕKÌ%LÜ˽b`ù“#‘ ã{5;¼§ ‹Êè6‘°÷’rÄ©F×lÖrÞ)kM™ðV@³Yp^×@Ö"³Y§%Ñ~s(Ìû;9B>aáQ¥m}û0Uz›Wã¹9røUX6q@+8jóx6—´ÂäF6Ð0¥éjç¶Ñïófï½ Õn¯Þ[ž¢ÕO1^_-uÎf/ÐÛǃ¨š÷Ù1Ôo’¨Úï¼köåœ7ƒ(©Ððò!BX˜W%1ü§×0ØÆ¼¾'Q§¿{óTY‡½b5Hf!ïdQëƒzÄ´NE¹~É펊e¢<~Ç5”|£ïÀjõ¸¡TspªÁ‰¢fTçöK4®d›8Xð¹çñˆ) ¿ 3 @~„lzípý(ÜNª £ÙáÝö/íÛM½$DùXTiéÃéö8I½ðÏÝ“­‡ÕÖCªw8Ux É:6'êX²¤¹è¸ÚS¢_gÏõ®ñý¥ô¶˜Æa_i^¯®ÎÚÆýÕÓçç,üü~Çb•-b|§^]Ê~*kLJ˜`¬îzSÄ‹—©¤¡A•1®bÛÕ§¸ Þ”z^¿}^qqswùÖ ÇÙrû¡ÞvÈ—¾÷À:`¡doö»ÁÂê—%㻉Ñâ&kij¸P¼Ë%àÄàü=šB ©{_²N;7É4–ÛI ‡‰Åå²°˜Ü=›fuþ©‹ãõÚ€[{ €×[Ë®›qú æZ)ý\O~(‘­Bì2MaÊv÷Êh¯ˆöf𿿺«ËèGuÍþÈ*ÄÕ¥ññÝrÏ¿Áþãâüƒ3>HX›l&§9×7yÓ8ÃÐ.]¹TÎ.Éh¹ý±à}l±‹…Å2‘Tx£:UÅϹƗ6©(K2ºèNÁÀÊ@»ßaÉæõËlf5g«š €Ççîܵ tŽZÑž£fÞxÄÑß-Åèß&9í­ƒ* Ò¹-UN¸êGUÊ¥äBjJÃÐdêÛ¹PÌL¿ïìüPKU0^;ü¼uXB(Wi ply/lex.pyc½}{p×yßÙÝûÀ½¸oI‘KQ AI¤(ÉÖƒ¦äH!%Ó‘(yI 2-øúw,y±{qw!](n¨­Ó¦i›º¶“qê6í4“Lãñ8ÿµ3öÄi<±ÓÆUÓ6ãÉŒÇí¤iÝNëüÓfê~ßï;gw/ÅT€)Až=ï×÷þÎá·ÿg½úâ7¿q}Yé?“ôûcôÉRª¥Ôm -Õ¢¿¶ºk«Û¶‰;ê¶câu»`âEu»hâ%u»¤¶¦•_PAáZ¡F*j!<¥ ~UÝ©ªhRYôÇV~M熶²ÞðÔUËQ³­‚º£TTWV«¨Þ¥¨°J%ýáÛ*U­²Ú±Ôí1ÕRþ¸Z¡!T¸ÀŽRŸ¼=¡ZUåO"u8MR­šI­§©GTkĤަ©Óª5¦VhAÆÓ¤ÕšÀŽªÖ$"³ª5…È1Õ:‚ÈqÕšFä„j͘V¦Mܧü“ü—¦ÉgMä˜I?®Þ­ªÛ§Ìç õ.­«Z÷¡ÑÓÊ?­nßÏ‹}sþ$ïœCÁã ~Hn¼©'-Ó†*óûã\°LAŸrÕäÄ“ +›árc9jù’ÄÁÊ<7… ¾DÁÒfÐn=²Ô âäâzs9Š{½tñ‰ ›að–ß›íGüÕÕG:í­GÚ~ïbgËãšsm›cÖ=gˆ‚Óh ųÌ@8š'²ÑÄ£~úSÍ ï’ë}~.~x®ûð\‹þžŸ/˜­H¶:~Âm¿ÕloúI‰bí ôÃH¢~¯ÅrTK_ìy£'ÝFã…}à'=d¼= fGXp„x©þá IŽE×ïИ>– +äñ8¼aD¼ÉÃ:&5ªtÍÑ’U±ª^mo½­®úû@èSÊI!|É‘ãZŽQ¢U–ùq'˶^ßtëÈÅ­AL%xÉ6k|(hŠgøJnÓù™cÒO(ƒ4ùH[ŒY¦i’3t,ŒO5¥*cÉàÃûv7H|Ù²’9%ëñª‡Î)wßfTtge™º –›íOì3•‚™Š›ŸJ+Í mU6ÓáeYxλqýÆ‹—ÝÝ“ó‚³yyÓàsæ ‘Ö% ÂÕ[‡4nòšç½âýÿž ŸŸ©ÛB†‡a˜—Ú;Ê1±/p`®Dh å/m® €OñjpíšðŠÃ?Dx876Ûí÷ƒô{¡ ŽS~£ ;d@X @/æÈtï k<¦U¹n&I7XÚLˆt6Ô wô°^y¿a9é8´½×lU³Ýn4šê}Qø)\uH(ü>ªôi•Gá|‚ˆÚæ6Õ6›ú³ûlêöÕâ¶»-H()-”• †X(àH……ŽTµPp{˜ŽÔ´@p»Î€" ÜUþ( t†˜AÜKs¿¦@RfŽ#¶Z“ˆc")j&¤QR«’R6µ†L™Š‰TyŠ6ej&¥n"#&kÔDÆxU82n"&k’׉#S¦ú¡a¼ 7€Ù®ß¸~ëús/AlH8@Ŧ D܈Bá|hC»>°ÄˆU”ÒWLGݧ¤‘ÁO.1:Äàã š´¤žû `ùnRË¥çä› VÃhWOÀg+f,]¥Ý$vº,Ÿ­fÒô" £ÖöC3 ]Q%ÌþÅæK÷3¬+Ýì6Ûi®pÄOΉ:I°¼ãË<óÓJ¡bÝËЯá9²OYØÚÀpŠÛ6Ó¦è¤eѹÛvTïŸi™¸c’P¯.þšzÓVÛµ]äC»]R½wT¿H]d”Õö2*ª·¨úC”ñšÚ®ª~UÕ:5eÑ¿tègkÑÅ+ÌmS SÀO«Ð2itº˜BJÙ ¨vl|ØjvÅ6¥6®©…~ M”ÕÓY”Ô§¤‚º²ñ0p˜Ð8®AÎ"Pë=•ÒÍ™ ›~‡•îÓærhêÿRS Ù£§mvÆŒåˆöèœÒ¬õg¬Ùéøa çOÓA®9`t¾–’¢¥;þrÙn ¡ÿvÒ\sv×’Í|Û:b”IÇâ}Wä• lÑé­H¦| ËÇÁ?¨^—Û„þŠiBY£¥²U²ÆT²KÖ”U·ÊÖ#Ö¤5‚“Èù÷QšwFi™Åƒª9–[¤‹Õ ¼Q¶ŠŠÂ&Y”@Õ´­Òì6Î íï•Í›¿b0C{JKMÛGˆŽ’èÄÒA †˜,pÃ81Ó82’\R„((™’òÉeNæ#3¼;gÈäÔvçTLN}wNÕ䌤9k€#Neâ3K@Ä4¤z/ðѾºø,ÀéÃ|ȉ&Í^]<¯A*:!UW³Ñ8E‡T0–Ô1‹6*ÖBï]Ý|0.g>Æ™VÛ5tUW½[*™Pɤêc.ô÷êâ©íÕ¯£Mª=Å€1ÛQ³É.Æ1çM§y´ÐFÊZ Ú ÃAŸ¢/Y‚,Ai÷ÊŒš•™X™QÕû(’¦£¿hFOS˜ù˜ fUTºšµù¤d_¦ã1ô0:ÐñqnRøïq>‹Ð—AyÆÇœ“ÞŽ?Náw.¦”‹î­µ vW‚¶ï67“h½ ¦½åäÙi¹K[î«/}Òg¸ ¢ª¿è^Âs‰ë·‚ät5fI¸AÀlJ¸î3TJ§§4ÇÝ“®‰ØžtC‡v§§´RÒ½û ºâ,ÖõÓf TÅÛ/Gè¤ä̳ø ZÄ‘Ëf¸,ìkHbd¼ âxËhLâ¸(%W§™¬!r' BD"˜{@L ½\rYéà±Ñ{„ƒsð0Œ|½ËÀ²ÑfÒÙLZAM/5c_çrÛ`nÒhøVd}šK„°¹-V½Í6øÇðôât‘Y?&3éêÀ®ñS‹´3Þµƒ³4”Ôæ¯r+šŸ´Šô;kZ3ôsL~ì’]ט~'¬Y[Á$}=kØ3\È¿lÛ#T¸Ÿ·–§Nÿ;8}BÑ~Šû«ŠÑ>aúðãÊbKì ³„þÙ0Fìp…i‚ãÂkáYÁPçp*‘ú»â(d A`²á™Z9 Ô¿CŸ%uÇAk~Y›~Æjï0þ~œãU͉s¼¦ypŽhî›ãcšïÖüû„‰LªÞ—P`JGŸýðY‘©cãýßQþ´òg4®N~I†þ¬ ޽Vh%h5dd´\þñ4yˆ’±„†;⪹JÀÔG 7—d'˜F^éc²Á$>6þ›ZÐc?¡z1öûÒ±ßgÆ^ñ­ =8!5…Ú¥¯“LS5G5㚃‚õNÔM‰¸ÍØeäGLŽfÊ9:<ˆ+˜/]¼³&âz¸L)tœ‰yÎÕ…€ã€íæ!¶^ç€Ï®÷zâ­fp cIï#\äá\ÇÀ ôwŠ™vddVB›y” ¼if!S D´‚~€Âæóh ”æÝäà–As@'‰,GëFHhH±ðpÚ`—ZÒa,²ä¯áü°ÁnÞ‚A{+­`9ñ|³n~øP÷š)"ì yKœz¨§Œ95[´óÿ†yVcžª=e9B±YŠÕ,ócXË’Æ9! U·Æuê€x ŒOÁi²–¥œK²O))AL‡-kËÎ#KËòZš.ðúô›"Èã„C6Æùƒ]èZ¯C\<1M7NºA¸ŠÃ?_6§û{9·RJù:pî<^;È©²Ýª4tÏÂjCT ‰|ý¥µnÊ®Zcô“ŠŽfõ°rÛÊh¿i>wÊ@œ‰¥s³^"ZZÀ c`1ßÐ?hƼüŽ­Õ œ>dÒ•I¯mû°Ê)Lù4¿F’ ‰7´Æ8Ó*D–½ÃÁœ'ï¬Ò$§™˜ïCÊÐ{&õÞc°hS‚_áÆ*»³&¥L‡#ÁqÓ?Gég¯‰‡“iôa¤ÚÑëêèƒgå,Ð×=d¦€þr†ˆíC8*|@;›ñZ 2i¥–ÂÉ},QÇÒ)ä5 »bôØ—NÔ9<UE”³>°áYNá ‡iÁòf·K4K†ä憴Ò&eH¥'í}¬Mcƒ‡•Óƒvæ»Açì®åP =ä˜åÚ¶ôoÛú¤n;à‰ë½g‹…¶ß²­~AЀ£î”D„êx’ZÙ8ÜÑûE›kˆÉX´R‰e¶¢’Ú;P8çÒ)óÔ"¶aÜ3IeŽ3Ó~¦‚xXd–÷2sLÌQ CĽT‘7̬Lça˜†ÔUeúÊXí‡XaÒhدáåúÒw] oÕÉŒ…}ôÂú¶aR;3Un[ÙÚ½j0è¨ê¼N±a Ý~”&;ÎX“w‘ù‰aËâS!.Mª±M[í­açjYhXÝ\0›Iž÷ãz~!uæÞeW,«•.)¶q&¿Fé£oÒ ¯S{[eÊ*M¦Ë—k[·‹&³L©‰ §dY f܃ÓΈÒ6}89rÞx%¬´ n£˜ÎÝ‚®hpÏ)kap¶˜Aæ!!†³,Rb˜eô¢y&:sñå¹Öe×#©Ø=7Ÿs‰‡Ûì2!k†îfx7ŒÞ]0œ.KÑ(³[ÌDìær3dÛ£ &î¢{½ÝöW›mwy­ÙmËÑEù˜™àý³ÜfâB+èεPìFä‚ÐœŠ»J¸!tß’5IŸ??Ìàp"B:/ 2¹ÞL–×`¡Ççj7ÚìxLíD+Ey3NDYW)WÙ2Æ¿k ÒÔ“\b>è£"0MËÄÖyzÄ|wãDü/DvÿpJÐ!Ń)Ø “`]¸«LãúþsÒVŒ—Ùh ×u š¶ü.%òŒš6º{ ¶þ#àŸã†l­É·U·Ç­ªUvªÄØNÈ]v*$Œ×ØPjMÚebÝF­"±Æô+Ö»æ”Q»èT‰P—ˆß˜³‹Î¥Ô5ó\G1Ëš•æŸQb°OѿԵU±Î’ˆÏüÊ^ʹŸ­òLX j4þú.‚4À1Ké·ÆÂ–É*øùŒ“à=~!=!| o&Qç: o É…»èjrt5$1òónùW-ͯ+Ë¡ó8BsÅ"T40JHcÊwZÌo)ŸJVXÙª· ]΄7»ºø”CØ;ÚÄè,4i¬uŠŽÃ„Æ2 ²ò¦½é4Ë1 ûšÛ AåÄw‚䘮e• ·iAðÁä¼Ä]?Þlk5êÉC€…רÒ×2iN”›ÖqÂΩPºT‹ÙR½Êëtuñcú€G³µ9# üޤÍîZ£zZÄ1 û¯扵hø9Øäàqð3‡°Œ¾_€24¿gx¸Ï ú­˜øž…óÑ)*k•my4·Ìô\P[g5 S‘XšG|^lwtÌV-¨[ÚÂÛ‹ pfŠƒ’:IÒ@ï7M!QP~gp\¾­ÙLQ)l‹-ì2±Ä·sXgVyàûa[ëƒå…ºQØ›¯l„b}#VQÑ t³Æ#ÌÊò ÀW#ðP×l¸LT»ç&é— V”B髀ˮ8Ä­‡—°æ(°æÏ ÖcvUV‘˜Ö#©\Á]‹ö¼ƒ¤ @è°rEãT¾­±!p{D¥%Ní.1Ê&·íqXÿF‰í­³ým¦O‚͸šá±iü &¬c(¶ è6r8mÀ7n̳xë±Îëp°a*¼~Í{þ•›×„*Ã±Ùƒê ¥˜¶¤áw‹V´ÏSp¨zÁ¹½À\‘qX`„ò“µ¨…OpmÔ°õµÞ²ßá’è,èÛ´‘(ê®7Ö‰i%„Ùõç' Æî fM¥¨€¿hñnâÔë“¿JÌ.tPl,7¾-˜…žªK¦áµfØjûÞϧ˜ŸûÂU(E®eŒ€‡ÜÕfÿ.2 Ø_¦J ¯Su‘H€cÍ:®U¶˲¦ˆH0ë2mØ'l—¾¦­ºªZ÷Óð¯LÉ€ÿWÈ·V(­[e7“«JT‡‰­QèÇM9Xc©wx’º˜š*yuã!›‡þŒ;H=)õ4wSTawF›8Œ&ÌǤ$Ti\ݦßSœ µƒäMPk‘àpÂXúçn|Rl ìrÎS IÞK*¯±Î~³CûËÇ^4ÁC&#s„ £P¡8™­qv>´STEiá0¼ag¹ÉŠr%ÚúiÂë÷+f`ç³'-<ö<:ýþr’:îñ¢ÀœÇà¬÷jŒ+ÙeÏÞßéú°÷¼›ó ^À4ËÆ7Õ¦½¥½¶E3½j¼ôúF³¿fî9=!ÎzÚV2ºÿ2ãF-ZЩ¤£ÝªÆ0ŒKIýœÓž6 `ÏâO6cÚ±Çcã ‰2öŒÇ¨ r}#•+µåé+JKÑ™¬4$ ÇPÀyVxU9+-jH ÆÑjÎý ¾¢Î ðˆNó™™Â™1$ìt^¦í½"#[ÀRaÍõ¡‰ÙiÌÉ|425·Pbcµs^M¦þx&?)üÙ%f÷ïcp³ÄK_²Sy®ŠŸ½ó»ÇùL” Ѹ€e3Ûñ|Z:å‘|*&Šãpx³­å; )?¹ï” ß‹)ÿ½tÊâú®y/æ“fÂAA+µ¬ÁÙKÌktŠi¡W` ¬SاΞ†‹ûG[+àtïwx¼lS¾i“V7ˆ]m]½ÝÉÝõMÊ_òݦ”Œº.Ð:lRºÕö×;É–‘€¸¾q=@, ¼h ó_å$NÎpó;‡¢ÿ’*=kkÉ]‘xWxíiý¯ùN=ÑÓ}äA¯A£Ò‹ô†^]l1-×,;¶¯ãæì#홥=Œ Æw’‰yIdx),Y k,Ìç•1µ!OØBžo¶ôþ0Õƒ"Svæ8¸ª%ÊÍu’ôš½Ù¾ùt) n-?L‚•€Ø»ƒÂ23«Z¿»„,Άàô¯¹mÞ‹ ìEɪ#!»Î$6C)á:±’Rƒ©³‡ŠæÔxœIg‘¼ï&Jð~*-Ú{r©…èoS°å«Þ§ÓSs“OQ `µÎdŽ Ó,Üy9PÞ°•£¤³qž,íAO‚/ Ã,ÿ.„“\T†\äB.ʪ‹”œÖÂ…âݦz6ÿ^Ý\½~ìí羜Âx„«m?S¡Ç×÷V‰Ý¸ã/Ó‰Z†îðb–žáШߨôÃeßVrÉ]›ïdàm)cñÏ¥gŽ"K/¢¿ÎÄ!8x¿O•š wp(°fYdµï€RcÇÚÁkf Ð-’ŒZЄѓ’Áå÷É—áž9€ÿ‡ÔÆŸ³¬ÞA\]Âl3Ô”÷Åç“:û2lö¬òë}ý«‹“P=µ‡†:o-l|ÑFqyô¢b¸ö2¨³’1ûÂ1F…Õ{¬,²9§›·Ù+[ýtµÒ¥še'R›ë½ïhß‚›“ Ìà×UnH/Ð ŽïAAfð_¬Æ,Å<ó5Än$:k|³ñÓ¶ef)‹âæ·£–â¥áL ßÙø‹6†Ÿ5WßÛÜ·ÔBÏÓkL‰÷9°™GØ;€ŒÀ‹dJ”à3æYîá7l“6–>ÍaqòBï =2Óè‹<Ø}- ‰´ÑªcÒÆôË­)•¥flÎöô8 Ø$ˆ¢3fw&' Œ1½OÖ€ÏÖ]‘D›]@ÂÀK¹\ËF§•÷¸ ì‹Þ±âöð›ñTs—£0ia QE˜6SÅíf¼æž{óì¦?¢Ý­I…ïµFÉþ\ l¸:â:’1Ð2ÏÀZ0t–@Ö‡†Ý[ó„Ù÷Ž­%a1fÀàŽ×;pðþ²2v .ÐC¸u¦æ+íæúR«ùìoÙrÑN|îxrLd\™g̨­!ƒ;ˆŠÝýÞ!ðiÿ*}ÃŒmïú^Ù=,¹L¥?îü©™u4?Ë@™ Þû÷‡4ƒßMg°gaGvÏ`ÿ1ê‚þžŽÖçsI7ÝÁ.ü†É‚/õÖºV®u)ê}×@«øSƒGØÍ½ÿsS­ãò_z0¼¿¤ŒáŽ›™€ÞMiuž·¦Ì0Q7AäVwÓ‡O}vS½ñ©GÅf ¥2 o)"Y| ìÉ_7Ñ& ­xA¤}`æå_Q¥Ÿãåd󠲞Î.¨‚}©[ãö¤Q9àû(16c|IP±_wöæ”Æß÷[&gœþ=n×YH–j¥îŒá‚á”3“ÆpžØŸ‡™b0?? ™õ¾U0ŒÏט êÍÚš+°øV]ÕÎÄc†ǃì_õÛ1E¹+¡ôÅÃÙmh©¨`â¶“YÞÊby°8–µU…+l†,ï>,„†H1OˆmœïRᵦ6NŠ ծЅ]U:µŠ?²ÖÖ +"‰¢·Ì-Kj„âÜ*ìãîLµ`u˜§€k…‘ȤŸ¡÷ï‡;Y ÎØ´ÉIñ‰X7ÍE¶@Võ­Å¬ÉÊ@“}’àø¢hU7?‚á=#­ÁÙZoP°Ð‹PiZŸÏÀæQ½ául8±=Ä1›t&ßKósŠ jø²êÛÉp^d[Ö|GùJä^ãí<›ohLÉÊgo[[·s[Rçû˜÷²«1¾gœ² —íÜ64îe&0„ah•“ã1¥È¤élpÅ/Û´â—í… kÑ#*·úµÁ1Oi÷’Á1s¾\ˆJUÌ£l¤ŽÞ£¼ÑÓãó÷ƃ0|þ^aø›b9™'¥#zR¼¾èN¤!PÈ󥙌Ϭ×6’’›D‘»Þ ·ˆ]Ý\÷Ã$†¹bÕÍ€øQöPM‹>–•dn×_Ýl7»®ßëPA\o5|"Ëò]Ó^©šÿè«WæâgçâóÐV‚w1îmg ¾ ÷P_kØ ßûxÖ€Qfì3 †.ºsâvu&~ÂÔ¾è¾Ü¼ë»ñ&qççΜsƒ0×1kõãåf‡fçØsožÑ~¹€öþ±Ò¶¿øÂ@­übÁبaŒÞ{.Žá×úgZ$>ÈÂÄ|©í®EÌwîR¹'?Ÿ8UÌÌó0Â(ý‘ʳÉ }˰\¹«{ÿDež¿tö–£Í0É1XUÃ×4­h¹ÑÈJ¼_QÚÊ)z~0S¬™öþ£Ò6ï×9øO*¯‚›Fjðc4fX-ܤÃ+óPâ¿ñß9ø|?ã#7ðˆŸØö)E-xÅEÞ/¥Ãö“nsÙe·×•W™øÀ”#ãtï1GöpdÄ…GT |VUÕf+¸®ŠU¶Í¿Uý¯c'.ìq`ãÄŸ¢¸kM8Ü›+ r²ÏZÓºìY¨¡¤ì4ÌöIæÚ69•t¯ù>ëèñ¸CÈ3£yîíc–Òªå»J«¬ä&‘hw3/C˜µ[tE[gUÞ½ƒõ/ø…š«$lt]§ˆï(Ú Ú¡î‰(cQçË'TRÛx¢‡ˆk w_{¿,_„çU~fx/‚‰dM±ªº?4 ü_SÑ›ø‡¨ˆ˜)‰Ç`r= Ziß fmD|Ñ*œzeã 1mÔð jI?•"˜Ñ¥Ô¥ 4ü$ qã—µ!M® ä_8€iéÍøA‚Ó7ã‡æ“†~û²qéÂÓ‹žsVQ*°7+~ð1Ÿ<¹‹VÌÅ„\4à_t_%i*ˆ6ãÌçFl^ ©`k~Ä@_ä'¼FxÁ ~/ñ^UZ¿Êº\®{¯›Z×_‘‹’´Æÿ| Ê)†ÀÃM½·9xÙˆL¸ª[½$çnËý yE¿¬ëwŽ€yˆj®¥åBl[À¸³Oó>(äþ€*=Cƒ4±¯8ÉJªHPÆNû#ôS² žì’ö½%›¤ßQÄFl‚-ë–8çY¥7,Òïqðo9`ã°X%Ù¦S”Ðæ€?0”Cq!ÿmªä26bgdóh¥L?S•áJ¡R«œª¼X¹ƒûÆò> ›Î' >x¢½êÌK‡ßï7ƒœÃPÇN+ÆEG,ŒòR VÅX`¢›ïSlHmt´¸•¾C  ËÉúV¨Ôë°O*¹¤B?œBð˜@ñÌ€‰+øG}¶Î¬)ny‰„æÖaÈÒxÆx¥2XÑ¢ÙŽeËc'ü‚ ×9-Ïžà¶¼ØêÙu£ôí.„Ÿ€F3ú8 —xUø•‚Ü^mA=£ª9ŠŒ1ÕãHž76úV!™V,+R‚õ†Y¶g¥A°àLIƒ’4„¤#ù¤ ’¦S €­´G3ŠùXÔ;ãW ¼Æ Ù½g-$GukɬJŽiÛ!³ÌÉqÁÏæì`ó™–ž-4VW’ä[FA§…ñ÷„ê}ŸqòÕÅ?RÛ“pΞR½·Qˆ†5ɲßè˵=­’Sª? ®ßUÛ3¹ÏÓj›I"ÒýБáôàLöÂ÷¾t%êYêùû5›z7Ñóºç«èyVm˵=«úÇ>–o¹¦ÕïÙü»@uûœxeã†Í~âæ± I-yZrß’K]]üŸu>ÍÚø‡h |–.æåïGr-ñ÷%,Û£(ûòSÁãx«p 6rJÿÊ|ñ't\—Q¦Ì“¨û¤êð¶sð îé¶}?¿.ßź¸X—S,•óRðåQW·Íz‡©´Zp7H]æQ”9) ñ¡|é)SzãEkcª˜[íÖ®.\¹]s‘™ºêÊžîtùG×GVÊ›éwá}Q!¹ã‚ò¦dðOÑ•³ ÖŒ< £³¸^Ú)ƒÀÒú?Þäwš@Ó\ÜF„‹Å.»é«Lϸs¹äÔÉc0YÛà¥tîÑ¥A±žÚ(ÿ\«Å—.»šºð¬Xó™Ìtö~†þ¸/?wóÖ5Ïõ®½xí›î ¯¼ôÒ+ ÈÁmÎlÒÐen蟚k-Òp—"7³FìóÖ€òZúϼ޼?ä2J™}K@°K ð¹¡à;¥ò€Ô½V›¿œò(LöåþgêÓêý®Òv VÐÅ{-`µðFÉßçüßàkäy­0iÊãírƒwäpîsð¾xì>&¢ ¼p ™âÖ)Pø|•8à„ðý„WLà)#_²/½È²é«.òÐTöŠ Þ©* ê‡-yÆ ÷ð\Åw9€–-n¨BVÅ«¸ß S߯š?mÚÒQ²JÅc<µyŽR¬¯˜²aÄ/{o˜bxÊ·­Êu7^9úCÈ7M~ÜréŽ÷_•–WïŠX+/jÎx%‚»œ¾.AÇ/ɹj¾pyücnx— Íl´÷¿ÍBhiºÇC‡$.W'à/t°<Íy5:2»&óÝŒ”ÍVŠŠUqê|½–eZ§¬ª{‚_ qŽòe\J²G,G¿™R²†è«â0?>Iå+ð¦wf­óT£b—`Ã(9F?F-œÆ× ÅNÚ#~%‹ËÌAÊæ'ùU›³NʳŽÓÏ›=¬Ç’ ø—F1Ž\¾¤;EeŽ"æÒ#19#æ/gz3ëOŒ€6±‰ãIP0Ö³lx7Îé]L}³ÖѲ´µ°“ü\§xV´ÅJ_ÒÒ^]‰˜üMU*¯Iù<úx€xV°&-Êë÷MreªæG‚Xï*˜c‘æK¸V†G²ÞNgiºŸ©l%Ø. ÂAm|eÏ£=xKŽÄLÆÅ+Ýh1SØjv[únü<¼’®½ò‘—`õüå*ì•ÿA@UdÍUƒžšÝÕ·DŠ-(‘bE€e0¸Î·€ä‘)í¯m&òêœjŠ «_HñOzŸ^Þþ(T&¸Ÿ¶½m J%]¢ bÞ_=0Hn†ëÍ ücy¶L POÅÓ1ë( @„޽ƒûäÅÁÛÛ¯Ù½÷/*ü¯(–ú æ·~¸~ÀJÌ%¡6¥Íþ´C,ô9¥ßÊiX¸‚ñ9ã¹ÔO_À—7¬Aùÿ³AÔ¹Wû-ƒv¸0±Ÿ°r¦:ɤ¼Ê¢Ûr³ÌF¤=ÿÙ_ ¸õÊO\»1]PæIžÑÒ<ÓxyÒ nϹ—ÔŒŠdV¾¨,j>˜Ù«T ¢¯…ÿ×+ü ë4Ú{ÎËœt/„«í+Žcóe·ñâ”Uw*…Ñâtiº2=6=5ùCu¹2]«ŒWÎUf¦¨ž?÷ùÑÓ•êÿPKÄ1y:ä„ÂVÆaçõ ply/yacc.pyí½ûWãH’(ü;E¶ëÖÁžž¢gg϶és)Šªf–¢ø€šî¾ Ÿ°¨‘%¯$óèÙùßo<ò­”lh¨µv§ËH™‘™‘‘ñÊÈÈWbã9ŸµWb–=l‰‡x<ÎÖ^Á‹ÝböP¦W×µèïÄ·oßnnÀþÁ§÷ñm:Ÿ†â]ÿš%¢ÿ>¾€Ÿâà`wßw²LPÕJ”I•”·ÉdH0“IZÕez1¯Ó"q>ó*i.ªb^Žzs‘æqù .‹rZEâ.­¯EQҿż Ób’^¦ãAD".1KÊiZ×ÉDÌʺ?ê븆ÿ$&ËŠ»4¿ã"Ÿ¤X©ÂJ(©·àøÿßy=«Dq©º4.&‰˜Î«ÆRÇÐU„_·øI¡(/êtœ n|O+‘4b7šO¼A“ã,N§I9án@s:T7`”“9t­£'âÉ]rˆ“b<Ÿ&yMx&hPë÷0|-Å4®“2³Êàœ¦ŠªZcP#;LRª‡ßóxš`ð7Ó’"$oH Úx ’t· >$ù¤(d  ´;-êD06€Ö&Ð! 5q xèUqYß!…êÕ,#ý@½éªDÊÉ™†ªŠzL´zúÃþ‰8ùüáôÇã=¿Ž?ÿeÿýÞ{ñîgø¸'v?ý|¼ÿñ‡SñÃçƒ÷{Ç'bçð=¼=<=Þ÷åôóñ @éíœ@Ý}Ú9üYìýtt¼wr">‹ýOGûàïžîïDbÿp÷àËûýÑâðó)À8Øÿ´ O?GÔp³¢øüA|Ú;ÞýþÜy·°ú3µøaÿô[ûðù—¥8Ú9>Ýßýr°s,޾}>Ù8¸÷û'»;ûŸöÞ¡ЪØûËÞá©8ùaçàÀ+€ùüãáÞ1Àªx·ýÜyw°‡ÑPßïïížâ˜Ì¯]@ tñWÊÉÑÞî>üœìÁˆvŽŽ$Ô“½ÿï ƒâýΧ0ÀþBÌÀôì~9Þû„tœ|ywrºúåtO|üüù=aüdïø/û»{'ÿ&>ŸÒ¾œìCÛ9Ý¡Æà Àïw_Nö {û‡§{ÇÇ_ŽN÷?`²ì@?w ò{BóçC0ÑÌÞçãŸ0â‚æ!?þ°ï³„±DÅ `n÷Ô.-"qTf¬âpïãÁþǽÃÝ=üþáü¸²7€iÛ?ÁûÔ4´ú…ŽÓ=ÉúàqDÓ*ö?ˆ÷ÙÇÎËâ@'û’lu»?HÄÛ~nIƒhµ™NgY‚ Ù‘88³vÉœ¾». [­è«2žNãR”ó,ÁÅ~™æÉ Å•8z€å‹Ëy>&7„&®€ ­R‹@]<ˆj>i‡\лÃÀò*à`KrxŸ@f–_P‚ egiÉ_€)3£©“ñužþÇ8 tç¢(ËâŽ:G=ÿsq‹‡q1¾Y¯Ä ô†F‹]¨ª:™죃ŸÅ”X8°¼Û4ú8´qYT1©ï’Ù0×V üãát˜m–ÖC‰` ó²„!d0ß.¯½,…ïûÅ|&úɯ)üûâl>ÍÓá| ¯Ša2™9ªá®‘]Äúz „?Ï ë;×0³AD=û’eS ‰Þn1¥ lKÁއB;U+¥â §E‘U=ÑG’}_B»¹xW73&@ÌÀH`€¤ý'‹Ç´º` دiS—\‚PGï“ã×=‚?Jò<Š4}g\oÉ…è!2Rù·T}-2Š’kASb…‹á2NKÀëš¡6ŠË5Ç9%ÀMnd§è07 óÐ[sû¾W5 _üîàóéï°…»5Ž“F8›Ã²ÍIã)f@bé¯D À>AŸï’uS‰/¾ @ý µMüD®`p%6p—«¢˜(V×ý–øPý%èXŸP¿fÄ’î p@ÆÎÜöÓêæ›g– kk£pT¾F#èØ½? ¿íÁkÀ·ù"_ ~½8B~_[{õœ}Ú u³ùloo;Aœ^¦Wó’úä ¡F˜ˆ®ãüŠ–;r‚ÍF+ð–ø LpTBaþÐôÞq‰¸uµº<÷xÖ°‰Ir1¿" oú#5?^!5@gXû`%@©Ô¹«$O@îõÇkAÔØ b±Îsj÷º¸^  %˜&i b£(ÖÖ¨W#*=sjªž1ÆlËa¢{‹×€RFr‰iðnÝ]-g¹2×ä´Œ²’ ûYw¥ ?àŠ%È&`ö¯‹ÉÚZ¢¿?ÖäMÌΧ Myõ0½æÇ™v°6«ëô²&{Gd Ê @Xx`✨I¼M2šÄ·MøÀŒ±òi Ê•-fˆ&²î‹™z^’•{©8 ðÓ…“êÊ&¶ã¤$£Ø¨^kk`ó–2€Š(ø¿ÐEhNðwâ\X¼Ž…Ì}žçØWɤJ”¸¶6KÇ7Y2[¯.ÆEæ47õÆŽ>‚†ÆBãÚD'ÕÚ d Vrý0CAJX$Šj8‹ëë5Sø™JvªÆFêÞŒÙæ·Ãýý†o×RœÆj¨xTš_goÏÅwâ[„O )ª?BVÚ¿li,— θêÏkIV%KWѷѨÑß5Pb¸ü§ŸÀv\a§ñ=È”µä~œÌj±S³…žì!½†‹W0MkF)þvxC&‰§âªYOF S²ä¾/;»3T†gjÑ+3~ë#€BÔ…U9‰üS©MR…_1ˆ2€)ÏW c.!‹ŒARJ%9P˜ À !]ü.Í2¢$ÞPZqmTc ~»€t.T|I†y½1R :š;¤®LЙ”‘ƒ¨)§ÒŸEúâT(ݪ‹(y½q ŸÅ6Ÿ²º€Ý†¥2Îà­8Ê BRö¹üÀÖ&#­G£>êõ‘M\øbx p© Ó*ä’Óê*ú]\^UÑï~ws‡?U‡¸â’~ŠŠ×‚Šˆ7¢÷×¼7`¢€¡Rñm¼¦Ûx¸ðÛROêo[¢÷F›Õ-g~4|°ü?tÑ~Œ|fgfXÈç~2š$K2gˆ)å…â ¯ÒBì®÷ˆV°K¨†rHû4^ ©u¬¦¥[“]à'«"t5SZñàWÅƵG Ùa§8(\e(Z6Ê$£•Eˆ®ä~†/Äcúºâ` é¸Dú´rX€$­ª˜4'ù^Ú¡ÒëÙ-(ˆqȃë—rHè6Zs„?á½bSëÍ׎*±Õ,+ÿÖU²$7/Å÷Ây6(øólË*yþ¦'†ÃaOv*îw¯+ñÄÛû×÷ß‹þëjК룠‚.×Ç ¢tFnÇäŒ1¨5 »ÀÇ77ùb ƒØ´‘IFáák`ô;±ù¯ JTŸ²B–°q×¶ÁW²› ¨/Iûq/¿B·‚2NÝ \1 mO0¿`ÿRÒpư+ d––AVºç.ñœ% -°pšO°'¨€K8×s`]è"n¨µÚl~vkD næŠA‚».² Œ)ß@‡:/´ãOéËr”Êùöqßè×R´jY¡5³e&kˆä¡&J|tš!ÕÐ*zgóD=á"ôÎ*“ÁÔæJ¾ÔqIÊ'¾9iýVY˜U|¨bâ•ý‚xeœEØiÏëUäÜ»Íä~VT6Aa‚ש޻1Êò¦Q«è‚V-–ΰ…К)ÄßmñAx¶ŠÒB¶Êª¢5‹çA“8bPåãÙ :%¹žp†Y"V’€aêQ¦0%ñø€Ø.cÔëöðïA(7ó/‰ªJ¯r4i ~‡-9Ԣ>$%;‘ :d†raóüöÒ6”Ãdê´§½¨â*½%ÿ.(S˜†ìàŠ°¶•=bl5‹ó`ô…ƒa‡ÞJÙ¯°p$im@ØF^+^I> (M@Ñ_M*3/éð 6§ë3MEšº>Û›RÄ+ÛÒ|Ý–mR;âý=(Ó¦ÂV‰§íÃ"O|E®ÊÐÏ 6÷š$â6KF÷Œ!A9…ÐÜ/̃­/Z ÃYÓ˜ÕœBñ=«[Îz NåçL]º4É4· vÏ´—›×ht¹® º]s;M€4ú¥©ûU²2NíF[Ó­_ÎÏm Âõªö!¡x7u-­\.’æd=©âöE=®Õ‹ÞZ##ZĵâEòßm‘»Ý!jotH/'¨°¸WzJyéµ×Ñr é>KÙê0­¸Gãj¹øSë<bMÍÒð,ý/!ýïù·U%¿T­·qʬ /"ô5ìþ™æ³8mTr˜•#ëµ[>fÍ’nÊók·èUQG¦(¾v rÏæù˜ ò_î´ßø ÆÔ+nd›¦ È $"¿Ò$É4ƒ­æ²[çÏÓÆGxm©ßØŸX§Üëÿ ˆvÝã<ÚU™|Ò‡¿^ ÝUÆ^¡$$»Îgóš^DòŠ’í¶ý6ªK€ä†?‹›$GŒúÒ1•¾!Íwr›Ï²H T‹þ´qÒ§ÒÐp=pKqïÒ¶åuBß_Uƒ’TœÒ¶t£ñ°ƒ‰ÆÃCáQè1˜XÌ%ƒ®©[ÝðA£}4tÛ´l:Ý <8Ïæ+ñÍs>¦…ÏÁßÉ/¼µ\yû&IŽæÞDí ‘rF$†º&ñi«ÓxB{X¨›¦ ?SÜ ½NJÒ·?HûÍ9Ó¬l.’ 0v¬´ÝÍÄJÓÔ8 m–eRã6t¦Ôð*±8Ó+èÍ8+*ŠØrÆOX°ßˆ÷{ï¾|´ßÒ’£8”®²/2kî¶<­]«›~.³ÀÑ̉)΀5VÍÂpvåVœ)Êúw†Ò—ÏĹㄾ  á1â"ÖR¥!8”ƒݧer ”ƒ;ýH\Œ]}|q[¤e½r9𕥄ÌvSæt´BÅ–n…¡Õ†-2;Ú0Å8s™†Øn‘‚Ƙ@}šd!w¼T¹%`ì_'VÊ06”’jk²±uH@¿Xn$*nö×ÖL1wuàCÄ9Dƒ®ß;:øy c Oö¸89Ý9>í ‚¬—ûhð ¶¿0|…lâHÜ%¼SC'äî^Ív©Ú¹U ¤ÅL\Ž…·½}*¿Y}ð/[€vÇpO¦I¶*CK¤GNy!`xÒ¼9Z“Òÿ(0=y¸ .@ˆ ˆµ4™D4ż7lKUá”vh¹7ÆŸ”C*Äk°f×ÖL!4jc |Ç][µj DÔ ‡ôW»<µ+è–[ðMì™ð-ýrĉ*SÚ¨Lö$¥cî¨J›æÅ^ù‡­ÚñW±°Ï_Öi›•®ùDá°9¢Ð öÞëõo/pÆ«óüW,#F¹îSÆsYKl£Ã­ªæSæ% Ôûo#Tg!¬[Šª…«%4ä‚ì5VŽ©_À´ô›»kŒÙt©ü•ø˜ðžQžÜ׊b Æ‘½ÚŽm•x 1aHÕÀ ú4˜÷Äæ3F³ßɉ×;Íæ™Ew„'…¢-Xoñä*°Y´.Ìš©ÉoñažËzÃúú ýÛ ¡Ol‰×ÕzÄÈ´¶à›ÄQU›ª¿_‚FÔ,†­‘hЄ¦Îå êijæ!ÐnW†³bæñúåæƒ Òs°°GáŸKf%r¾‚máÓï½®ÄÊÐVWOô†¿iÞ?»¿ç Óîþž¼vrmŸmn"ò´ëÞƒa†1΀¦%©£Ûè¡Ü>Òjš+r$\´8EP‘ÊáQåùè¢O5 BìoºÄ÷âmx&_qd•v1+®àryûi²¸:<ïŠ9ÕÁ¯-½ Szljèí0†·Ä d!i­Ü.L$ZzÖ:ºëÓ5D±p9¼¥Õ÷ F¯¯d’UNŠf“ªºœg<Áê饥¨nÙJëÆöf°Æ¸Àm†y ;DßµÓD™ÐAª QD"Áµ8$hígÈÀ"gõy¸EB¡!þÉPhc‘ÌÍng‘AZ¦DHÓO‡öŠ)fŽTmYÆEk§±²Ú[袆nR‡)ÂчgÛ²ÐKá˜'íqöº:çÃg¯«Æê˜Àê˜FUF¢wÖ{Ó‹— 6Œny<b£[›užmP/ÏÏozç½h£eŵK¨gÊÙykðy3X8 "^Yj)£dcs+LöªFýQ¥p«¦kx4êß÷Ãd";vúù­n"7Ʀ7Û»&˜€õ&P½)/¬Á;è\ƒ~/×—Å1AfߤÞt6‰t7Ûgߦºê“;/zƒ¥ç¦£Üý–a`§êøåÓ“‡:ÙçG’æúìE¨‹$+î0<3ÆSž´îÑ1c­³àÔ¨æe˜×1$åt²£ÏçâÁœ¬àóÈþÜV]wrCiâq ÛÛÞÉ]ôÖêü›tÉsÔó’ÂÅ €©ì½è„H›!\\Áì«,Se6ÄT!û3¹CÜ=Èn™bzbøí1Øm±ÂäÆr›À¨ÏÓn§-¬ UHd÷g6î6ÏÏÏH2w㯩«Œ<û‘aàÖvé"²Ú§³~¬Ð‘O*+x/¯“ÒwRÓÐ< m9åSU!7lص eÉÂŽógËvöû ëË [Ê¯Ö:TÒÝ{/Ôö–øÖ˜Û <™›whE_Kü;b’”ì²R·p_V0J­éŒtòóÿŽ”sLüC Ð$A¹b+!¶böóßQˆ…}HÛÛmN¤Ü±ˆ[p­Ow(C,zäjèE´¡ûœ„ÌÞófz0Tw¹,‚ÿiá;¸{‡ï{Oë¥w(Åþ¤0ËþÜFí.ÈÜYŽ\§¥¿Ð]ŽÏ‹»Ìý~>þ˜p"ÌÀ!@™™Ø[“Ì…düÌi%ÑZ@AINûRxªãªY+fóêÚ9d-wžòº©üðþà](ô7Éä x¤!pKɸä0fŸö´JîJœï|ÈÇ×e‘KÝ€£äÑÆiüÂ| À‡ÌE<á\VjÐ*ÊœñG]%ì D¦ÿ´ ŸŽeª,"³ÔÀùE5±S —iYáN#Š n]±60dÊìªa—06§VÓăã§2¸khóÊ0{z ^ŠõêMfkk§Ã‘ÏdÃFm‰µ‹i xxÿš— ž¬ +¿xìØ‰$moK&Š¡¨R£Šd¸hW÷3º ½7ÏA ´¦•â¨ÏÄ‹ø6NI1DÎâ*í ¬DƒÞ(m-);­ºµh ִВǵë¸"±¤>Dëd­B==tðô†c\C²qGÓ£›l×kП礶1ï5QP`éí¦C"mëF=¯8Û¥g ¶=A²ôxwžŽÁó”F¹äm&>×ͧlTg!Jñ8m2’“vÊ»× zl­ `,5«þ˜ÐÓ©ƒuo†XtØ=P°AŸê¬Å`KS_o4/6÷åY]·]Ë”=à’ÝÅÇÄ=«ä\½%¹øãš€½žH’Þ~]ý5'„Û‰\ιÀ¢ëÆóczfºƒqûÐÎ6ßÖ4V8Î(#tö>Ð Ú^Í5ÞÞ—VATG*Œ-&MÆéäò€é&¦¦…œÊ˜¢»d½LŒ+E-:žŠ+åñk“õ©,H=¸Pª¤üRÀà°aôâ¨S€ŠÀc.ϸœÈ„T*té&If¬(\,ò¶ê@|‡)‚€ÖòM·o„´ÌÅBÓ ùrGy8¿á8PTÿií¡(A\sý¬eC¢=”@RÅ·[>Q\“c hI¼TÇì‰6"q1œ8•ˆ*‘Ë:µL)Cr5¶º˜IJ£Í`™,Âø0¼P>™N#Ò×=jyI/LÝ3 –ÌuÁžA:->}MžF¶_ÞÒƒ©.:ÌÂ0%6Nš á~p¨ÃBœòÑLõÈ:Aòð~˜N§CÁÆeÊØƒéÀÄMÂq´¸hˆ}uÀ“1&8“ ]K-#|:!ÕËÄ€ÔËx,¬»f áv•oø8ñ\눒n½æIÎ7G z„èXÂY·”“.윓_‰£¢FÉJ,¦ºL#Ìž¤+[smyâ:tJò!Éc{é”S?)Qœ¢Ïdˈt‚ôÍ7ߘ$7/xf‰Žø¸'–>«´dÓIòxˆÂ÷Ÿ1°Ø{¿ʹnw?¿ß“™‡1ÃÚ›¤µ9ú¤Ò¶Éèœ!¡ïÂÎ.^É3O*¹CãpŽ?.“iq‹,ÖœÒg’†/‚5ïÐbΠ­Î ½Ôy¡¬“=ê‹ÕÁÕ ŸÕ ŸÕ Ÿg>áãŸ_ði;á³:fóŽÙH2óUâÕ · =ÝöÍêÈêÈËœY-X-h>«³ÒêlÁ?ÆÙ‚UØã*ì1ðü³‡=bÅ ÄUìþ*v_¬b÷Ýg%$VB"ðü³ ‰°eý›cãLµ~d|ÓÇÒ1¾ ®n‚XWÿ ®fGè*¸z\½ ®^W¯‚«WÁÕ«àêÿvÁÕ]B|\ýÏ\Ý5Ó«àêUpõ*¸ZYW?Å·l‚«õ]KYó¥ 䥰¯*S>||F)!-Ä»|ÉCb®›6aØäApy¾eÜ+ÛOï_÷ð¼(# v`µÆÚ*Àz`½ °^X¯¬WÖ«ëU€õ*Àz`(¸ °^Xÿ °~¢}¶ Î >«à\|VqW«¸«ÀóÏw…ƒç®ÂW ¤UøªyVltÅFÏ?; Û-«ðÕUøjpø«ðUûY…¯®ÂWWá«Î³ _í,» _õžUøê#š^…¯®ÂWWá««ðÕÎn¬ÂWWá«g¾j=/¾Š¹žñx­Ï6,ÎÒczœÌ@Õ¤°>­½Zcßó%HËâ¹›Öø#1Î0~à»Ëm®Šüs¤W*X`MAyŸÍ3œä䪠Øøkz>Þ.¸CñìxXK§³5LÓjùW´‡¾X:Ar¸L“²Z¥ÕÈü 4 Uýrýÿ?‹7~ÝÙø¿o7þ4Ú8ó¿Ö_dÊ»Övö–œ àü©ª‹2aÓ¤Œï^3†7“É<ÌsŠÊ€evPz1lù@î¸.s ë¤p¾˜Í<•»ƒ ®qãU.î\Ê÷³Rlñ?G_NÐöTP”£ {yWéX WKALCו'{ŒÁJ&ÔÔ‚®w÷7Ä!þ”¢Ûí +¹Qw¾ ýX×ÕU8+TßáÐÔâRÁ)]¦W×5 ŒÆ3®­ã@àÊú¹-KhV ¾M& ›%·IfúÎ1Þ^q~;Ô¥(Ä‘~P¼„Ö˜÷cBzõ(àÃÔÁ@3YÞ‘K0dACŒg]Y ¬|`…¢/£Á¬ ř֓ZÒžR\nhM'ŋȞ$ùîÏø3*ú²GîTñ4]SØ%ÌÕ@Ü£È0Ñ/Õæyú ØTíK°=&Ågç0þªíóV“”Ù<‰­gclüh”æi=qL<8£+™VÔxWï³rÄaçOäYóC±, â½tBÆÖOtAå`lYÆP£Ç[*7¾W×Tê¥é +Í ›ÐÔQ›¿K¦³úá{«¡®Y‹ ˵m-M¹Ã¥ Ùåq­zcé½Á 4©Ü›Þ gÊmáR³]+/ò_“²h­¹i¾JjœPŶÒ|’Ü· B ©€k*®ñ,óõªìaÅØ¦zl‹ 2Ú§€)7Æü@wKÖ•œÔê†ôŠï½±o©^:¼ ƒ"Ž÷-06I¡Sy †§<õ!ׂ}H&N“I“I IÐQ~@kF‹Ç²jÀ†“6Âf¸*âËštOœs¤ªêlƸÌßlžTÊ}ýþ>b˜ŒŒèß“ú1è€j-Ãpó ,jŽþäVmS_6jÚìà®k‰ôÙšEïзïM¶V>H„‘:ªä‰žð‹ÙNÓl’j)+g\˧À¶$Õ<Ó…Ï×<-;)oQ³A¯Ó$õ4¦ˆ¼|l¹^ãˆR…zTNöE<1òf×15J» ‹ûµÜ©33N‘tŒ õãq='/‰‡ >ìWo^çW #1Ëæo‘¨mÚ5P:GwE–;” Ê'I›’ÒTJ€Ñ°F ˆ4R:Hãx”¾¡u?ªÿõŠ2rù¹°üRLÛïæÙ®_W-,4ïÿG[/fÏ2kõMY-Ù+ËèÄev•ØávD;›¯dú,iüm‰³tè¦û,qÌ…E ôì~Øa*žM+|è´A–ŽŸW »v+d½þfûõÑìp=-f¬VêÛ,Sc®I팞Cü%u¾¡ØãGHh22f± j‘u3 ç¡›¢TÆó°î€! C Êz”>4Ù'Áoúþ|ÁÔlýš°hìoãÝDP;¬qÎW*¸šBä«jjcö­Y-¤ª¥nÛj9šº† E `„òÑ9ýçÔãR/e KUj€™9Úš+HDóŠk¼2o¯êþlØe¿J8Ö"%ZÞ7CÛâoâïÍ> Ar'eajÃÞ £lb[º·Û!%ßä ‚z@ôçBƒ£ÃFzFãhU¤Ê)Aº¼Ù#©¨aò<¿”¢U9-ªz„ì&Uª? vh™)ºŒPeX±‹}î œý‹4íA5™å‹0Ÿ¹ëˆÆ@çeO"ÝÕJ¢7UdÆÀ$øŒŸaMÅ÷Ngªu–ž/Uð\Ps«Ëbc[6aÛ]_s³ƒw;Žw>}Ú9»;''-› ­„´PÓéÉᥞó«üçqVäWŒb9qC¤Í\Ú‹äÞ3`¸5¬<é2œ1©a‚¸uù‡r¬D"©ÇC¥,‘ ‘JJ¤q úþ˜·‘LÇØàÛ×ìŸ.ðô"[×bõRÆð>îƒJ”Òx… ŸZ5÷;²D Z±HCç¨?Õ%eCWøÅoÝ?µŸW2€N]ßÅHd NŒ·k^Ί Uº%!^ÌÓŒlÂ8Âüj -òYkŽ”Ì~"\”=ÈŽ@uͼ|g3Ë¥ <¾œk²Ù`áfɮںaÔ î0Ð[è ¿ií-+-2@WíN’3{èÓ+ï ß™S=øG£Nst¥©!ú–ì‘B²ÙÙäŠÄV»¢V_‰ŒÐ"ig§îpΰÔ9;oZF|&à ‚¥mºXˆ—ä´$R >m+²âµ%ÔÍÄåÓÚMr»%š»~Ø?>9íßt‚ &s×GÂü|pðùÇv GfßÏj}`BÀ©Nb`úzýˆ]åõ!½P1ï%±Š¡÷ƒhÓq€;nýu˜,à³ÅŒ?ûu–\ê‚Þ(PE±:¬Æ-ß;ÚÒ ù¦ˆ¡€Yn §2Òßa°ªoÑŠ•çï1!óKÎù#C²–l!wq™S}ÚŸçÔÌÌ—O'2¾Û ‰—a^”«…Í(%4¬Þ’fƒ'z×-ÊÉ.=JÏ+ä&h'#ƒ>x£rŸ$RS²Œ(Š9w’EûD¡*®šþc4½Më¥I’n¡#-  &qÑÈ`’2ó+7)ÛóbBÏ“‡ ­¸DÔ=¹ØÌ¬a° f³ñÕ˜m¥ÆD½OÝF‡h|DK3½aGôl ] 9y:%9ÊZÏZé:ÃŒÖn•˜"±¸þºZG«_ ì¶yJåþâ™7ofÎÎwfÇ¡: p:VN®³N‚ðÍo3,-9ûöܬ‰\* ‹Ï¦È´ P t=½;™´ãifÊQU¾ï“"ªšX蜪Á(îR8u]S(5¹¼xŸ£iÆÚÊH k+[f=´.v­6sée?¥5 ¥r…cpÜqXKÁ)L FYXPRÌ™í@0Š¢%<½mW‹-uP/hà5sû³Cö^R“a /މ‘­YÄMÕÑê@(€B-|¼³”cÊIìR›Úø%üYg×eq³³N&zžºQlö *iötÚâ?0„×ÕÖëÉ–ØÏ²ä ó’:‰° ÅŽäX*ðˆèBµÉ¥·ªtǃ`ÏÚ”ŸÐ¥DE1ÇÆh¼+ÊÉRBê )H±¯‹ÿÆþµ÷ÂÚé>(Šbýh"%À࣫n¼IQÄIB²ô2ô&U^÷Ðs„9o \oý¯½^ è·ýxÿOÜ¢«å€ @ï£:5ˆïÅfçº<Øc¯iP„3D¢e%õ"11•ãë¸æ”6«H¦Õï3ÎñxÑZpÏΟ»›ønY˜†³K´œ”kc_:Myuà ’n5àl‰t¼€XYà,À„¬iØ™¡¥¦À¢í÷J\ø<Ÿ£7­ɾÒL5¢¥Ø'ZQTùöÓÆuâœd>,j EfW`%^DwtQé>|{þTܺ}à6A Í™æ1,.½³3±2ÜÙA„&Óˆ)dyß‹ µ¸íël”µNU—gÿô¦iÍbx“¡Š\þäÁr“lE¸Ü6Öê=INhõU-r_Oã™®ƒŽI—ËÑbù‹¥ÓÜqkºžšaÐ×3øŸKÔ”÷^¹9¹ó¯A»öHLLâÍ"šl·´¿@jgg@5[!€S ŒhC¹*-~`ZÌÍŠ”2F f“òW¼'탙'wv¤@ŠY,r;¯°ÚhÝnqoXVËÖQmçdÀ j>S•Ï9 ÖÚΤF£2­Â8†QÙ ]§l+¿¯—‘Ù¾Óö\ÒJ-Ã:$–ê%ÐÓŽ¦Zág™¢NZHÕT`a1ææ.ÁôâáhHC2Q²Ï–PlÂ1kÝÒ}Q wÉ–))ì­dzÝÐKÝC†~H=J…b.‡¦kfM˜ôô½}iŸ%xhsçUžÛ“ŽTEHž¿“|Ãb±»·È[NÖ‘sN Þàߩ՜lë…Í[3tç?ý;äJ¤oÞ,Úy@l?ìæ¹ð^ʲvø}û‚I)h ÌsiîRˆ~l_%œqÔZ}o£ÞÉz/:£zç^E‡-p‰P6mÛQÎP^Da¤“ÑàqŒ—l$UÁžöóh– ,‹¢¾ú†åàEäö¬¥——”‹7€¬(a]ªÉe5לem)Gì3ÎYÞb‹åue$Œ*Ð<§‹ï⣠3]!Ùâv—® ‘RELФrAD ªWÎ5F³„îІÙÈYJÝI®.€{†Óçt'x„CÒ7€uCGQÌÚHƒK8W«BélwµY˜ÚqááÁZÜöƒ[/VÁ®Ë.ÛDßž,¹I8ùÂñYBø®õ¸K»½ì+ñ¾ÀyÊÞöÃÇé„®izÓÂÙþ³Îr~ª‡I&äµúÔªWMË7gû€˜REá +­ncI–[U“¿éˆUS„X;]Ù‚^‰Jmƒn\Ìë €¶!m¡Heò²´MŒJ&*„1¼BˆÌ1k1Ï&l+å†nù*D«¸Åz=PÔÚ?®)ÃWhcŸöµ­¦%tèZªlªÈÚKšZÚ°IŽÞfk9&…q —‰‡âl\8ÛÖÖ¬ÜF,J ÏÑ©‚—ŒC/3oì ”×àaª<¾–Ëú߃†'/ÒÊwjMñÌkM1ˆ/§»¢ ÖÄj#2¬šgusMºfäÁ¥8ÛjÉW´Pä¾èrå)ª3³¶N$as™—¥jœd½cÑJÔžeOd­™‹¢æFÌ#y¼$á*tÂÑU Í Ó˜7FÄÔwJ ë‘YÝ6g¸•óÛ³®Iä¶9ÿ¦Å®f ½x@l¦mö]û.@. ô§ñÃEâšÂr€9ñê/2PŸx¬a* þØI¶ Õ©&~f{EÙÇ]Ÿ½mnDX½ øÐ] ÁB_G´†·¶K& ú4õžUÍŠ|¢2Å›<5 Ì'±•óÎÂa•>¨ Ïùx!l(ÞÒñµ½å‹â-V¡}ùÄÛ Ö. ÃGÑ•F8ËíØæx¨yÌc(#æåfîËQŸ®½˜Ûq7é1ål6¶ÇJ’î7*±çîñ¬w‚ @ S¥ X,ð¡ðÊxöE!áè°”· v­ô'œ<H€_lö/’:VÊþf«UªVW JxïåE¼”êLžÙ–ñ¬Üþ&Ï— Æb] âU¦^ÅKwðÈ4(ûÀ–“áÕ0¢,ê²’5TŠ®éß»ŒÿÂdþ}vÞ¬©W¢“všSŽsëG>AÏDŒÐ)˜þýftÿmtÿ‡h8F÷¹Í•Â(\Z¿§kx¾K…÷2Ž3©Ft6×u}IN¤Ä{(ò¯9µ~ɽ:»?WL@ªw …óR¯ U#¨w^Rà”l§Eƒ ô¼iuwVØŠÜxãÞnyJéeóN¿Í𮧨·m{'^ÏBÓâ|%Ò!°ÊªŽuÀ :ošVd ’z2!_C£?èk¸œ—è¤Ö³(;ÖlÏuI…"‹Nii£PÉ ±Nå×»\PdX7æë×å\zkAÕ&>¢õï’,sGàΩ¦©¦ÂùBÖ†„çð®GðΟn,øóv‘ÛÅ–L´lÃg»õççØ*°x‡«Ôþ©Eþh6 ÔÏ'ìP#‘P•ÔnG—Ù;°º“û,›:¹ß³n,ÓMU6°%Úê uy¶$ ™P£ÓIé5(ät;\¢jŤ·uu8^—÷ƒª¿|®àSõ3-<Ÿ+HÝ#Ä*;„ÁÊÀ‡GÉwo\11 êB“WV-L“øN™n™²ÏÈòò€žb7Ð1Ü!½/ã«/øÃ›a¾[bo2³¡ØüßzV©É¦gí:|Sô÷ªÃ»‘šX£¥4yAî`rœRÇmÈälà(~uXø¯dŸŒ^*4´$òla¬œËV«¨—1ÓSLLNœ}âÜŽr8ÛÍÒœ€žÝ4¢*CÔZ¨Ž*¢V䰬Ƃlq’N0Ö0ăҳͭ`$Êr³Þs Ãl9hJJ#²:d"ùa C|gr%¦­—"¼{D@'wùóMü€×>àM‘‡k³L,³è–oK¥'Éaígé@T;Û½Ž+c,´W¢ãÒ§ëÀø/Éu¨”3òIx„IäÝ‚[ÞÒæUÔÔÔ½Ó·¤}b?ÂÚaóí\Žˆ Ú°ék£û“âI–LU>É#ÁúÆÈþ㢞•ÆhäD[Kà¾)ù—Ÿ7|ž²òpPrêL…-qx¶râ•:A5õRŒô°6qëlÞ$= Õ ÆŒ©M.Œ¶ˆ[¶„ØÃpá=>S¼çjNV²ŽÜÖϨâPW¤¡ÿBfô^`Áó—õhºdâ™bKîÿeqUŠsw–Cƒk‡³pãºrM¥2sò¬…+qÛÁksÚ½2\Iæu›Eixá?=ár\ç5ÒÐ#;?²g7áW%1ÏÃÒ}ùDÌͶœè\¦ç:ß²ékÛíL Ò7ww“9ëRLƒV2wø+DLÈ á“ÏMkL¡úŠ¡2@†àƒˆ7¾`˜ÙùçÕϯ›yeü®ÌˆyÊiw·M\Î È…Ë8¡³TÆj'uxUΧ¤¾.&l-ªÜo2»Um.æ±£1Ô½ÇJ˜kB$«çÈÕ‰NÝûQ¦ß™Ð^,‘Ü_ »íN$'Ѹ ‘œŸ>W‹ÝP&iøŠ×±·}³™NK‘)M‚³L(1#˜¦£ZëGS”y‡LÒJ©ëóç7تá'úãï„tW)e! ÐWèpÝÒ1ájx˘!ñ`XøwâÍ•[1ýž¼*é5¥>WMáaÙw§Z˜Ï'ù­ÿ¨&"@ÿi²kìðýl]ý½îZ­êõ‘/ÈÈú{4 ¾qh.í’«²+P˜½jNiË¢çgÖ²©ÍtE¿m#>§(¾k‚uI13䙵éxŠõziË7†§éÝiŽßúª·S¤J¯ò^û‹d–ŽoÔ*AT{ù.rPÒÐøˆê!Ñ/³¤¨£rY'ÈZ†xòØ~¢TôU?¢^yaϱESÛÀ0+âI+;^¿õµÏNkçô<ðŸE$½°(t7T›’[Š>…úŸ›à±'ÃqVTI¿ŸâѲÌåï&ìvsùÓ©€_ÝýÆd„Æ:À“^ªXÎòï ]k}6¤»}ùê¹wA‘:ôº#õ®Œ<´®t·îÔ÷²ZÚÔpð´é+ë Áç×Pžc“z;»¦”ÐuãâNdÎi3h½‡1¢,$t о¢…ºµWfKcµUjÿ˜Ör[|XÇ¿ˆ/ûЈÿ÷âX<üݨ¦*ã”Ռ޾$×Ó1°íþ€ârcÿåÜ™ôšJL¬ßßXy‰‡ò&Š.‰Ÿ°[bGÞLMNY‹ ŽågXu™º"E?Ž„¼ümÃCÀsÏÐ.M5k?EÇч#¹-uG‡bü¤Wá!ÆM(›œo3ÖÜëCwU"\³r:¹#¾÷C$»²fq¦ÜÙ®â[¦7ŠÞË•T*º¡zÍ‹öüLJ#¤ ûyÄõÓ@|·ÁÔµ&{”Aác¿,–þdû°^ñÄ2©ÝkDIO/Ÿ´öï¼e×*êŽÓÝÎ6´ÛÞ¶2Â`M·™i_Õº$\\ûÔ±°¹¿)º§:£;F®ô8»*Ê´¾ž²e,¯/Í 4›_d`O¥¡-5K$˜;tà½@Rÿµ°åÝ—Æokútuƒ»º½Žó´eÅU ¹TuæÎ,Ê5‚É:Íœ÷¾ä˜7ÔgX´ g×á?|ÍM…Wo넹Îg[a•„.@Ù(ðz`Ž3ºº²îðP^¥âÊó‹WhˆÏ³ì€*ô}ý”¾ÃƒWGšë|Ú`";ñ·¿›Ê;òîV}A“]KêÂÍZñC¸Ž£k´¹Ið9‚`FÇ?†­s›qYÊÃÈ~g@³_'^gvé‰Áœà¶cÑÀÁÛÑ8\ÇÕuc4(Ë û9³G˜Rr\Ìóš1ñV˜ºùô]ÅC›ñ|~Ùž®÷)%¤UŽ ÁNÊxËBFS;ë¼ð(¯*¡Gù%,îšûä~.»?«o•œÛ³sÓ?u{.³ÖÚ2ßgpÞÚ´únþîX¾àr†¶¢…Bakí…ì(‡^ÑÄ—Ž®²†ì¨7Pßi u-¹.üÿ~$#‡÷ehz"w‘°;…¯€(¡0ÇÛ÷=}½ñ˜Óæ©•í ÚF"û³.ògÀôþÙ–™‹À†#‹]¹×èðŽX…_°±?‡£µHãûEï´³‚V‚¼ t¹bšJ&½p´½í|«#Ï£ÆÄ;Yß‹áGöóg­*ÿ~x·æ~¨;$} Ö°ðêÕn'â¤ÚžÆ¿úûÑOƒùH.‘aù—QìRGRy[³ð%{­C£(ÞâN½šÇe |*©äöiŽ—¬HkKY©Ì@Ùb } ÿ¥s$:Ÿ¡\2ˆyf,¿Izy™ÐmtG@·…ê‘ô  ó?â­3¦#^ʆiéÖŒLºŒ9p‰x{\¦Êye²Þ¤t§(¹^~†©ŒY_Ú¸CÑoêyK‘æ€×atïDfñ]w|#•ë™L]‡W_r*ºiE׺RÔã*RÇûÐÅý´áåƒÄu¡ïsuúaq‡Ík§ÍBùóiR‰¤­øa|ªöîÞ7»ITžO*à%od«Å WU úŸ\Aû.|òÕ©¥ë›2œÈ-·÷ø|‚;´‰­Ó¨`rü¶’5”ÐŽ}<#È4ÌfôÌ•vÔåÍf+·Î•î+Ç—…§áªa×]"±,j42ç*ÇNhâî?·dµË7µLkæ5Õ» ]rqJrÊP’¼QYyD°´Z¹Nà†¼K”Õõ™£ x©†$},ŠtC>÷‘>wƒ>Y­SžÑpq¬îînÚäE1£Ãú4fæïŸhšbL\_µôLÝyö9ȳa``Ç)0)Ô)ÅÉîÌs4¡½p<îi‰—’€ÚDŠ Œ¼Â$Â=D5ü¯(åGÌ‘Ÿr6mD°ÙRüˆ·æW=»ëâÓøcßmü€Jð;Ô±xœ?D4ô¦ây—è ®{e2çsÞÅÙé#ýs 2š1¶¯$“—ÃÓ%VN†Ë /WŸè'å$D˜M3¶B-_ƒö¡ðx½UˆóΙ·Ó‘õÅ—Ò®fén†T“ÐI ¡w{^ßTHtkDw›pҧߺ2ÙižU‹-±qí±”‹º  8TÅÈS`#9Р7Nu_nª/žÖ"¥Q|RIxïV¥€ëÈ»W©"€UÛŠ’à¨TÝJÛoX_pæ8í,[<¡A÷%T¡+¶jì°jO,amÜŠ> Ñèp`R&× dj‹Y™íœœë¬„¸MÉ›®»ÞÁ1Çýöó«9GxŠÉì[pôrúêÌ’ÒKHpŽíì6Nìh®±{FåC‡˜G¨«Á¿“ c#$-{½‘³$Oטúo6[OÙ`xÐÙæyƒ‡-w>HAPû7„–-þG麾»ŽQ´-ÿ}c3 uf«¿äzž”#µßv’Î÷gÑÎ@oùW×éŒ#\cPîBÕÄlV‡JB\Dúú@gÙÄ M`Ùê|9/»Tlìñʈ‘æÑ†` ,.eïòzF¼å™Ö$ ¨¼m†¦•§ à±é{r*Ë/¢Øœžs–M@tǵÒ}’½aO#Üâ¬-{˧@.àä#.R>G[€ù‘O²Ä>g©Ù¯lA.*ÜÐbRîøw‰ÌÌìtØé;‡šf*zɵ‰q˜ÕRËóxoçýIß,OÁ«•^‹~ û…‚×U¹˜¨#V}o´¾ÔŒµb‹oXXμ}8Z+Â,–G®Œ_ÿ!û)”õjml.\DEÁu„L>pD­¥–'!:oÑ/Q<%ÔȾ† …þE<¾!³ù¤‘ÆMßêUi‡§å¨ªIâzX>þ÷w;»ÿîšºÄ 4m7nO*çy®¼ÒÝJ<@¹6`61‘Zö šæJ;Ü´qîUéŠ-1;âØí‘ÂLEžRN Q\ eȨ¸öàÛħr>[F7á‰éT—ÔaKÙå¾óu“ö•øšwÆPùu±{ºÐ6[-ç¾tçþáîÁ—÷{'[íœEiòUþ\Þ |5Ö›0;~€/|kÓ؆.Æã¹Ê}–R ÊÖN.’–šŒ!2=ï”Ç'µó: f¯‹lRùGñy‡GvNÕ~ø)þ̪4“·îÌÖÅÆ¼›¹4ŒN*<9”ÒÕÜ´Ñv™Þ‹>Û'2usÅÀò>éü˰ ïÚU† Ú~VþzåKàœqxò“HzCõ2ôd᾿eÊfZ¢ __åNævfѦ(in¦ˆÕ há û‚xÍW\VBü”Ûòød1 €%¢>áí°±w)}Õ-O™C–E; Ø&pØ;—o$ç·wT(˜µ@èֹäpP9ÌÕiY©˜áö @ó¸£fÓ/KXl$%)-ß7Ûâ°-.“*o%¿rÌiéªÊ!1м¸S96¼T*?ÚUeàÖ×e1¿º¶Ìq% 8 íDó½CtïêøHÃÈq‡+•ß¶Ô€F©_”E×øÂ~³G˜²Vƒ¶.\…C>oŽAâgïD&.¡.ñK+ûZ))…ÊÄÏta(1 ïý%ªii ¸FO~&žÍt ïðÀüA”§iœ0G¬e|œ7Uˆnø8³tÍ…tÓ$Qñ8)Il§´ÝB¢EF8gú[[´ÈœYfEkÁ9?YºÔ\ò#é%U”²T6EiÓ“a¬3yiÉ!n甸Òpx×e¹všYà2mACºÝ70¨ç•Ø‘¾¾ºà«µê¡´,&I$líyX ÓD*”Zt‘*Hæ$âQé,‹ Ž­c±,Z&$ä-2.½Œ¶:Ã’"ù°–<7V1T¶ì?pháÌ n!“„^®E·;Jÿ;Óß)Ñ0yUÙÈjákØÀtF7¸ûOÜùP*)t‚ûåúHÖ®ö¶ |´cµÀ“³Š¥eaÛ…ê«­vE³Ó$+†ý3MÏ+G3êRgL_ÇÐ03¢¼O¹t?œ±Ž¢âéÅ$÷[Ìkmgînt5÷ÙŽý^-Ï󮈇ÊÔA5Ù+÷(”9&öò¤Ëêôc‰W¿m3"’»€Œ¤Vñt3­f sX©nÉÐ2ê·ù˜#ýþÿ÷7õâ?ÃΉ¿‡•OûÖ²yüÂjè¼êŽù¼ÜÚDØÊsƒf]D®»o°UuXf 60úҋЦ-Z†’Úv"5T{#Ð[Œª¬sþíX8eÜ{foê-\l_eµa¼½…òÚN]c<©ñÊ€)¡Xx·ñ„…‚°ÌõlhùÐâq§ Ǫ¿«êi:÷ô ž¤eB¡oqpL_º`ŽII M”ûÔ$Þ–#1çžwZ4­z3Cdª›4J¼£ýLHÙ]Ó©J‡¯ã°7N~,S³¡~Éíj*sÑ®~éMuPŠõÚT?»ŒtÖ´¨g˜aCœÖ÷,´Y®æ^¶5lïó:±zéï¾àªŒA_o]šun6໢¼¡4¾º€Ã,]çÌ[Aæ$@2&0èP…~êöFØÚ°öhœÐ¥þÙ±bº’¥:yrÛ"ê¬ÖôÅ> ý§Ê}J-tF¢ì:-¨{WéÄG f¯ÛF_lø¢C€ÕÊý}Ë>dŒDÚØñ[lºÂ—j™hÇÎâ`¢\±±Ùb8 €±s¼ÆÒÑe¼Ç9y¸¦/ºr‡Û-^ºP—ó±<\NÕTb\›˜ ÿ ^_¬Ã|¬Ãé²syääÎi‹P°Šë ƒšÅ;ðÑù~‡žÙoº'’u6¡Àéj¢‘Ð1f<ºmµÃYíðoÂz1¯1ÈkoÆ1Ât{3ï5^ „™¢âòÁÈ&»?CdÅýž âçpó-<yÇÛ%pR'3±¹«N½ù›Ø‰ýÍH ‡C0+þuÑÉMîYá=NÜmp×TÈk¯i×öö©ÃÁú«Ê‘nÊßœ pz'Äþ]NiÎ*q–¼2"©Z\Tê¬÷%Ã>±2ßaãÙ—öûñÑsvÖÃ(«Þ¹Xt]³™e«Ê¬µÊâ}㓼¦`ù¹Y‘ñNÒ=˜¥Wjèɤ¹´í+ÇáıËÏî7×x'­ôgÝ6‡yä"×¾Þ8šE=:Ç”ðYg²maIõWLVÒ×Ät¿x†’+j £%n9 ë?è‹Ç4Q°Ær™Òq'¥ˆ‡âÞ©®®ÓËú÷r@¸ B¿Ô •,b)ÈÔŸïÛ@„ûr˜¨ˆš1EÇäÜ!ÓÚëyÀw¨´Äx—Ù]".ã[´J$بæ@¾<&mãZWòe‹”îvi(Öª,¹¥€@;zÓâñ¹¤ èLÆKC/ zi ë+™ úòæÅèí©Ü—þN0ìNL_½¾ ^Óž$õ‚¸ÝûØv±EÛC, 4| 6R·œ[D°<®ñ1,9FÖº¡åÓ€ÌJ;ƒ=ÊÙÁÈR÷Ú2Ƈ|lQû»lu6do¯Ñ¤«Šì–s=p‘^/?ïêid”±6¼¢8ZgÐë (|lÊŸijgX“f®í®'É,m'F0½ãª*Æë¤G„‚éÛ»¶Œ@³ŸWâ‡ét:ç˜õã.YCö&I8EM÷Sˆï+S|b#ÈËÒF \ëQ²è8(ú0s_¸Žã*‰Œ\¡íA;Qöâ6ø†Þ¸ÒIÓùú'uj_ºË1-ïÒ@‹l2ó$ÊFÙ­ÙÏ̯¬åcvb˜¡#î{<Œ¿~Óbû¯à×ãë¢JòYT&˜Ñ2›E8°ÿ*þæƒ#$û7Ç1Ë–šHÁ^D³å‘ÒHâØOKoß·žN·íI 3lŽ…ý'h+3TÉ® ÏÏôüË?¬}¬¹}ó˜ÿæ1½°qL5¾Ù¿<Ža7˜ÊI ËOa,ø„á餪í©Vež¬™…1ÿ$ O2ÿòõÿ3íF|þç8x^V.­ KëŸ^Ý_Ž©4™‰·_zT¦9ï8©,c´,RJUKAC´ê¤ÂQ‚žQýp6BÔ§¤†²b<£ÇJ¸êfû¶!Iq{4íXsw5_olþ±¢mÍ8š¶OˆÌYË5<µn°†È~¢DÞ°‡çއ¢?I.æWW`Áºõ¡ÄˆN&‡RD?;9~o)4o½¤›ô8*k’–Ûë둾?m–¦¡ ¼#]Wê–KücXͲ´î÷†½Á™}Ç­º©½žÕp××Ã_Š4ïëæ"è@¼½áìÁx n¼kDÁ yFz½ÞÚ+à{êÒº­OÏëƒtÇ´Uª3ÃÑÐF†›LÒz¸6rî|]®­¬ýÂÜØGï°}hãt½ý´ÈÜXç+NxBó¦‰j }E¯Z!ÞÒÁ€BPT?¦iÝK'ˆúeµ@jä°˜8Ï\WË4¡SLz ëú,]¾ÈAy¡/òß0Ÿ(9Yž·ª o‰KN: yB’’ã!û#’j+)2vˆRÖ?;‡¿;£>Sy›×ËR˜bJªÊTåªÐ¦.tР5Yÿ57—–ê{”ÿÖkÂEôÝ0î+èÓð_—[ý3$á›pWõAÑ[?cV¼¡µ\*®‹¦cðÜ|\ƒ ZD!¬©Ïÿkî³ç;°3’ò±«£Xò„užœ  ¢÷ш®Tû5õGˆÏh„ƒÔS$éttï‚ÛÖg#º‹À(>î§³Ñ ~=¬MÀèô»´Ök(`a›(H~Ôloðo]¤÷ˆõnéþ.[r*û7ˆšÀLtpF¸SöokK3­'òAûX~‡ºÉŠÛ™BâvtýŠ×u5ø5x¼;ÌéÌ=žÏ5BÛÒ¿<ÎùÒdq¦/ÌàìA-ÅßôH—än W÷‹ð¶W”½ÝɈä^]ç@ðîÇÈ{švhË]`,gm6D3gÁ1¸½žDêÇ ‚Æ9à¬ýˆã#P$Xx‹jtÄ!1ì´ûï‚m£ nþ£{ÀQönüìz!5Q¦o¢Ö¯Õ5çŸWœÓѹ‡jeFdAμløµª'IYªF¿ä*ýÛ˜²Ò‹õ×Õ:w^_ËÞ ‡˜ Þô½çcÐ/j óâKœÙ₆2^q™¥ù¥ïê~YÃÙé=YÎÚ²k1•V«¼Õ~|D Ð //¸÷é…ÊhFðjÒ²‡/¬–×·OæSà»®е#98Xäu1.²pEÏ^}DE…Ÿ'4Æêâ*"'n©fcn&ÂwÕ/ä{<Áê-‘§²µ0Ks@»üŠA{¬-Œ#„²¥øÕ0´¯zm0^¿³xzüùäho÷tÿóaË¥ôÖµë˜Q]Qo]Á®o&Vrtð3]z^—E5“§ö."ÌJ‚å²Xø!ûëÖÁš(â¿ÃÝõ`ŒÆd­ŒØ©6ÂDHúöz›Ó–:aÈÂËMT> r‹»R)^ä n  Êkkp7«à{yAµhÜ[¯2.&ùmZ9Î󶽬© h¤æ ÿÑÞ¦¼¢èÙ'~ i—V¥,qX<ïLcNÉiBÜ›>I¦n¿7u’è"ªš€aG˜ßzX_Œ.KXâúµÌH=i†CQ‡áåˆ\ƒÍÇ)+a8±™L•Š0®²âSç‹ÙƒÕ/˜ë+ÆW៘%Îß!`ÃùlsÚ7…šùª3ÎÖõüË]Ëí{Ô`×#é—ñ“bE寥¬¾X¹ÂDÏÀ7 'Íc\ÇÏÞ[R4œþNŠ1)‰Æ­¹²[J®Wâ]ï´Z ‚uë±;xƯQá‡Bì­§¯rb’8ÔT Eß&ô‚¤#m)XÖ•TØ >¥àïJn 4.zœòþ5U&ÀØE,òŸ““¯4_‰4}¹—¹Ó4|¾@]QŽÃ¼¢O€ÞËhƒ×ÕÖëÉ–ø”¨b K‚ni?4i±Onä5×( oœáÅHK¨]š>!i…Ë—ghÙ±º€…ºZ”óÞ?}˜±Á óOÏW?‹«ªA¿ÐÒ$½Jªºÿ¢¹­œur“ÊØ:þQ9Yû1ÐÝ“9hÜc2¢g£RFÕXÎ •üQž—•›\r¨âu `}ãn¨“¢5|÷–L/ÄÕN¢–=§]§ Ó)ˆs2°.Äx^ׯ¢ªè7άµøjJjFŸî¬¨×+Ϋ.ÀÁPMxQ»±—é1 èÛÝõƒÊÒ?Ϩ fêË×kÊÐ7àËçJºíQ%£½KøãIAÅÕu†P®æYŒ×¡îC?³¸®˜{ºƒá'f„mÔo Ïêfz=@ÏÁK_;çñ];âÕ%Ðwö`“p Z0ŠX*ʇW®ÿµú”þkõ¦?Å¿îlüßÑÛ?ÿnð×¾}ó­^Ú¥1ubˆqŒþþÆxE˜›ÞD‘a¯úáÍ  i,Åpö°¾¥Vâ¦)Bפ“$ŠªšcG„Š›øaèš ÎMCðÝæMË dr†`Ö<Û\viW©ý¶kûŸð](ãbž×(¿Z¢X±y”Ña9 £ÖúÔ±ÀŽ# â¨`扸ûYsP€ÿi˜ëªÐ?Ð,‹ù¬ßrj­o(¥Ç³ >A¹ Vû†·¦Ãh„ÁòÝAýJÞÅ%ú:µÝöA9GéÀ„twñ—J¾¬\ P†œ” Lï¼ðü°Kê l׺ª #G¯eõ.¤r•mËÎ \®ÓûuÝ‚Ö8[›ñTI¯-Gii?ó©ÂH*¼Äoe±t˜,Ùjd'l"Ëž«»­P$ROÅ\ Hö _õX:ø²ÞÒƒÊÇÜŒk·àεV›ØkoY¡Ð”hàÎÇ›)Õ šTCE€¨¨p™V:úÔ=¨@g®:  ÿ‰j/¾é-¦Æ¼*¼ª5פ›@/7ˆF±ÌÒßR;ÕÞÐÉS‰ðG¤zƒ€€Q–ZžntxB›È‹kóoš³$ôΊwu¡ôRô»!Çåñ5u›oÔ,±Œ$Ç’H§{ùþcžâvÖ&(‚WsTQzu,"-D¶Ç«¤×aÏœ•'íHßãÂÅÖã=ïÀ¹ºe=`\øã<,¸ßé›êM(x:Ç'š&“©>»¡èfbÿÀ¬ß-…ÍÄøÊá’k?ºsêϧ`Hv%•×N=1¶³i[6ä‘ò~qxc˜6‚•‡öH×%ãPšä2£Þϲä cÞ‰8H+‘`†bŸ- 0ðÀ#X¿ZôѸË/ïì0Πºà¸å„PS9¥Ñ §H ìš™Q9@ÏðNþhÈ|J§±‚-+¬bÑGß}.³åªålù}B‚”Oë6Vµ©¥VvÃñ¥6Ð=iN{/ð‹Ê{nÓL‹;¤EA¡Cù¼¾ƒË;Dav§—Zæ (Ë¢.ûéõ¸ËYÿ^¯;’ÕaÎ /4ÄwñÄ9ÅN-Q© f .ÔYŸè‰úN|»\Ç>ÅzK§{ ÑÀÐ~] Å'9}™GW¥f柃^4û­£ð_SKm{nÍéàŽ…5âЀ­aª8ˆô6­BjòóŒNTÒhk÷ [@úR‘Þ>£äHn5:¹¥Ü2¸%Ø1H|+ÑÛ…4ž(Z€o6ƒ&û“ÜGýô·-س±Hä>y°½ýŸÇY i;†Ø2ÞRbÄÁHcœ%¨p¶õ-].:ùzË{²$í®+ͽ½¨5íØnÔoš+QÃÄhñI8Ú6BëTÐ ¾ŽnÕ (æNõ|ÓŽ+)Ä„T2&Åx4¸9àÑ÷omݨ3å</Ë—ÝVU4·iØ»4d ®5%¦iÏ.§H(´ ãÑQ#6„[à+^‰–Š|C^Í]¶@Emuw€”ñ¶[Ë ™É·Pwi1ngvH?M]7š°³h ‰"¹20æ¥k¡á8k&¹v |iƒ,.°´pb¿]Â^6¥‡ä a7íÂïUÅ¥MÂcl€;a £S>ÐF!c:¨(Âö` J`Åå¼&7£íŽ»ë”÷UÈ=&v üB ^³ ·•L鈒 Å5ݺÃÔÌFÜHj¥4‰eFWB0`ËqYX á >ϳ(ãE¬ƒ#t´ãR¦t—ã“ÍraÓ˜>Ä}Ö¿‰À2Žkç’&n®tƒæOÑ¶Ñ fò„È`P¼h]µIk9ÉñíÀD¢Ñ5^&ŒÕº¿Q™ófœTi†…UN©‰UؘÒC¼8°¦ß'®~Ä!Å?Ã2ÒîÔ±O ¹•Ý4{¥lÜ™ ºø*F¹áãøµ³ÕpLx†Š÷³³Þd”q„G†|íàøÔ:ÏÙA‘42ºfÑj<+)¬bÄú¦^Wi+>›©ùŒÓ%Å>(cªaÛʽã¶”–ÐÞÞF‰4E¸é3iöÁÿLUˆ+¦–~VFÖÌóF`¸šRèË!ýÓâK¶›ÆÛB™µœî­ÙÚŸ @³;RŒfe˜‚ŽOÔEÓ†ìäM{M®•uÙ¯¿ðTÿ8TûQ¨F?l  }°F(£Â"y“ù©.–ty›%RÀ–8”xª‹Z-‡ó,“@*€‹?Êj»ÌÙÑÇttð³Py§^Ãò½®ëÙÖïww7œÄIü+Flý~–=`îýÑHŸçH§¡ËbýÞ\“Ó¹,É J<…7ai“âz<‚o Cayaíi›#˜ö¾¯b}|>Ö*¤uÜ(_¥5Ì}Ñ© ^‘mC ¤¬Ê!nn½Uo"•·š ¢ÝÌ‹_ú†;"“•ù\¹{n¾ º²*»ÿ¤$Mäâ’TkG¢¯|µ3BHÆö`_J»RšüðÅ ]–3]cßûéô!uÆ K/ÆÞ]iºÔwŽòDº#ׯsâL»¦ Æå*{×õDêFŠôì ¬€M/…޵jÆYÙäÂñZRVãï.–Ó¬hUéÄO7n<¼ø(ñÑ¡´Íê7¨6 &Ò˧˜t.ï³›ç’'ŒÔemk ߤ8¡´LS¦M$ãFÁsrÝ”'|ÕÙª¨örœSÃoÀ t]"Ú¶=:’&ýã/Z"Ðf;ç9‚Ùfxî'9:@»ÿÅ:¥é ˶÷¾|Éù ¶Ñ^Ôúbï#¶wÂÁk(ìÁ S©{{r_7(]í$¤•.)‰ˆ£6ëšŒŽ Ðy$‰@OXkrU-«ÜßïÜú<ë ùË_oüqÂãÆÜzÜtÓ:OƒsÙzeSoÞ4¨Š^[ëÅ,ó¹K„7ÜùmsjV„0K‚r¬°šÜ›òiŠ6¨6»úÁÊjŠq´&{ƒn°ß/ ò×.ÎAbp„ŧŒ˜IhâºO5ÝÞ3°ÁÚo]ú>Ÿˆ“:0ÉÝQ'È%û K®ÄhEaßU­W‹nÀ+çïÄÚì‰ t.­×ß¾­Ä–a(‘ÐÇœÎPøU“9ºÑ•3¬q~nÉÇÇ#ÎÎ-ý ¸Ë\}v3ÍÒ!$Êo” P[•²Æ2Ø´{v&ë98mV«çB4Ý›ç%&Ó'½Ã°½K4è­OÞ€çÌûôçEÂÌÖ0鉩ًæö…î9míØ=Q¯Fㇱ{’’’ætbNj释TÐ5äñ$é§«L/a^f«~ëаd2.ÐC¤žád 7rÏï¼¹5'°/@s"/~pGaEƒ½jªñ𠓺È,eUþhr‡áÑß‚j2P=b™_Â@?ÊëJºÝ`D2Ü™úC:àܦժŽdš.µBZÙ8è£ !!çÏJçb'"æ8¡ó°Î #¸¾5Љ+QmlûWÌ7WÎfø ‹ñö=Cü~1@qAˆÄŠŠ5J|QZÈ(dx#*—QC¡!•Ë©érL–»ž3C¢ò« )µ—wHLÒyE|KG hÅø èº!‰¤?î*A³Â†á0?:wIÉ#"¾ËfÎŽ¡\xmFpç-9Öý1Î9$¼¸qÙÓ‡€”3t3?€ÂeCWix±ã m„ñÝ;âá¹±çÞçšé¤uôCVÐ!~Ûg»Õr#hEÖµ òNPk€-f›Õ¾®ïÜãcðÑ»€ úý5´l¿E ãþñ+OÌûߨüÞ)¿ÖO‡ÆTŒyA¯©æ…ÐTBóBÂTæ…¤©$Í )SI™Ò¦’6/dL%c^èâ}ÖTä&k®åÌ 9wßm^èv÷=æ…wŸ7/ôšj©õ¡ì„Ôø²1¼ *9óQùx¿©çä¡Û>lä™yÀ¼0hfëM²:d^ΙF¿ ä?¼Æ«zh‚ç+=,4b*RhÔ,H?z‘rØ÷¿0f*}.µß§Ž›Ê€©N0uЧNšÊ«:`*ü9h*#fA†gÔg:d*cL÷I‡Me‚I“>éHÇØTs¦V0•æ† ðQS9èZtÈ8f*‡]êŸzÜT .õ¨O=a*ÇØ¼)S9nª“|}¿¾ÍT¦\¡Û|êIS9éòNûÔiS9åòÞîSO™ÊüÀí¦rš7w˜ÊWú¬ÏwÚTî4ÕSL=çSϘÊy:k*wñæNS¹Û}åŸï «šêySMâ*à'°!ת€ß½Lçÿ•w˜ üÜ…½<} 7!—»ÏÞU ð“ËJ¹Ùª6Ï6ÖÚí.÷Ø._i'åá©Gž*ÖP¢è¯MãòeùïÒ<Š»ßc¨*#—Mf¼<ÄK¼¶³rYX«Ï—敪&á²€ª /­ór¹²V[ªÜy¥RkµÏ.—ç­õ3çÏ}Ç™µzízµÙ*/ÝY]\¼seiãÎòüüÙ•¢,@ó"ŠãÆoºAèc‰­)•˜RL¸–Üjs>kޱM ]s0ømiqÅ„` ¬bY”‚-…\ Í–1õè9ajLÚDó1—t n ˜ØÆck£Õî‘ѲZ£^ªÕ|±T]oc¤gå^{›Ù‡ÞòsKr¥$‰%©ú*ªêbŸ‡ƒþ°/à¼?³´ñTcq±Úôø-xyï—KU1§! ‡Ü$ÃÀŸ!S@§¸I3=cŠ:ó¡\?ÀyÌw€++Çg]çY Ö­êÒ¾L»…¦Z½Ö.•®Ç¦ÿàKøÈ{‘~ÐC£@ššQéñ˜àµ€E‰K-46Ç{¶¯’Ë+ÍZ»ÊN»Ýœ/·Ù“rs±ÕNË͵Wp{ËýÁ÷*Õ+k‹ë»t&é:Sˆw¦âû3&su(Áf)^zâÒ»/¶w¯ˆ9‹zVìÅ¥—þý˜€º K½V_Üܧî Êw‹ï-þ¥w3Sm6ͯº2 ð³0X// Fkçø°Ü¨¬-Éc µ8àà˜¡8ˆ¤!Wp^€«6_^ŠÚw+X__Cq|7dÃl˜³‰l‚íº´¶´´B˜¼ B(êêðKÞ£ø¤±RWºq‹\× ÞbTnyèû9¦‹²+¶ÛÍÚ•µ¶ŒìÇLçÖ“°ízï^íJxÀØ?˜°{Yyi©Tz=Âa\FpÁØt|ðV&y\J}½ë&&™Èþýòö]€ÏsÛåçVf2š$ßÀýi0ì'Ü ¤Ÿ•”ƒ–¶á,#‹zË­ô—Ó܆ÛÜ<ôE]Ö|;°ÏmÙ©“¦1h‚M>€l&Ùšk…µ$°µÞKÎ…„Ý Gìö­è‚cV8{öl 03Õ*¼³pn}jýáÂôTëÔtÚÁm³ºÒ´{x½ÝÍ„ÖÚR{©¶\k3C{c¥Êl£»µ ዤU“` J­v“›ƒ¾ep‚[h4—Ëí’ÖøIÔÕ˹î ò¦? ƒcº –åÐ_y[Co‰¤‡þ2G;t£À8éý‚àêËÓ9Ð5Œo«»s§ ÅC¸Æ¥àÁð¨‡Êc¸ßÕ9 W«]ž¿V’©ln|·±è1³THôˆtycùJcéí¡Ç7I³×z×½ÝÌ ¨•Jµ˜x[3Ú‰¬ZÅ3û1úèÔ/σdù·“E8«½”ñ}9e}‚W¸:$i¢ ƒÇÐ?Fd9Y/mùi×ëë奵ª¶>ìèRý–á·ÛXzCèþåRé¿FMiv,oú?y ×-µÎ™íŒN›¨Ðµ»x—é DîvM¾¾OMn¹&ÁDÔ‘Ûƒý>Œ¦,Êæ°•ˆš,Í?zq®ßl R—ä$(ñÁÕóZb¯n¤:½ÆëË„½Ò‹ççŠç÷‘ô¸‰ ˆ—J¿ëÖ ‡ÝQ1\-ˆ#9¶û°kü¾#^!J¥ÿ6Ö0ñ~ó‹7 àQáÖz#á¸.Ï¥Z½Zo(¤“QFõ–æÕ–{0'àÜòš‘R¿± Nv‚uð&Àzf'XkÚ­Ž06-é’ŽÍomdÇC²±3{²P/€v¼à€û‚'ÙlÎiêj½¢ŸÖÎ>ä(ÙÑYæÜÛl#7'Ζܗ­µVÊõe<š¿· hÕõ•F+´X·öÂШÿá/aÒÛ1iìâLZ—›4ÉÊ‘‚(µhA€ûÝm3¶ƒB´TÙG‚í3"ôËõvyLÝþ¡-Šþm4+—¦)(‰3lÒ*·¸—wàr—ݺ.>Œ (}ñÝÆJ4ö‡”»CJý#‡¶'ô¤²Iˆ0ì_ ?NÞSÅgHÒx²#M²î†Ù›Z·4]ÒTSø¿B}n„²£²HÓõU•$¤gväO3½kGz†éYÐzðì õ0*Ó5c©<܇–ÐÛ$#‹û”#ÓqØp‘²]j–VÒÓ5VÚ”Nº‡R½ÑnÊ Q­¡Z}e­]¼Ó8Y0ÅÆÈW«/²UíÆµj‹o?À—­ /ê 嘔y› 9]'ä×ç¦ëÕ.®¯­4˜‚­ŒÛ­.£ÜØV–7²óæ0i!uÌ·z0Þ2 eüWFevÓ\ y³™Ç”ÉV^×—›Ý¦ÄúqÓÚ^ΚÆ_ײn¥0Šo»¨jÇÛœÙê5õ ßÈÛg6ûˆ!ºùØo6ûùØÃùHž=@¶Z/šŒÚÛ}lß öæ )±˜¼–{.KéØY/gзì ì›>V›i³òˆü“1+h_/«L›zžiµAûŒl£þ“i~2O®¾h7µÞ4öJ—© )k6Œ6‘!1›ò0bjýÂ}gðÚ0Ä G FUVþVÁlÃ$ëÖ¨ÙìB['jr7Ê93›cnÄ?ŸðP¶Z”R Ib_Ç0¶e9¦¢b¤´Ã]è]iôÊ›´é~‡Õ‘ _]+Aõ‚Œ|‹µtOl›ÍqS“ú'x3n¶&ŸÍ ;wȱuØl6µlõÞäýAæïcŽö!¼¨ôÛ¬7ø|ú€-fÓè¢9D0.˜E×Ë»òüWÚ|¯x¦`Ò>†$¨¸%96m Û›Y,4hB{³¬?Ä׳2wÉöqÚ«EÈx^.«L£ÔEí‡,Œ†Œ4‹²‡L4³æ?Ïǃì~Y)+8©?‹`UÁ°‡OGØ«‚q=ÒÔQmSAö…²Ã‚!oÇ]eßî±(_d¿ˆª‘gà±cæÊ´¹’3WNÛ.!)6½òó2Áj% ö_û ¼"Éfë8÷ üãfó¸i•œw˜ÚiS;“(IÒžad0ô¨5ÊpÀ¾ÕW•ø«ƒžÀÃtÌÚã=¨U²æåÀ4Î8\qK˜Æ!‡Uµº 4Þå`(ä”Öî‡XÃF[ƒ€IûF»¬uÛº,Ê#„1Bi7Býn„ð_ÇÄé\c¶Ò7X)î³ga8&…á•$Òg‡ð’ß{æ©÷_(<óHñò» ßõèsï.\~ö‘Ⳟ@n3#™cÐÆ…Â…ÂTË=Ï_³Ï \§Z…³rO¹dA­­@1?B6H²]¾Z[hÊõJ,P¤6ÊÞÏT¬ GU-4×–ª…§Zs…Wjí«’kG¹ ¿ó"¯§y£•Pñ«@ô]t.RmÇF’a¦(µ¶ûb£.½á'Ûk4™@c†w‘w]ºÈÊ(Ð+m Þœò ƒÒCŠ d‘ åvr$iéé©Í‡¦Z9ZÅìÌåàiòÚ¶²Z½@’ölá]ï}<×:â3 ]mÖËKU6hö£Gæ¦Ù@ŠžÆjúâWãn¿ˆ™/‚ÖŽœÃ¥ì¨g6¦øÒÞ‡ dþÅY\<¤d5Hø¡Â,/7jõâ)GÆ/µÚÍÚ 3,VÛÅ ãDÂÿâmnðTœA‰‘Ÿ7Õ8“//-•¯,U‹SH~±Rö±4ßXæá²±’â3¸<‹ËûåU¯–[æRr>g¬Å …ÜE)\[®ª¨ç„ã8ÛP„·8ï8™¥FãZùjµ\Qy€{RvßSŽ¿Å±æ˜@@ ª Uå\ëµñW³ QiÛ sÀ 1ùy75„þâƪÁ××Udå8A›×åJ` ¢í€R]5wͱ`éº*ÕËÍE>·Ï«ù„kzéÅ»ç8}Ò€}‘-a,8 é=¤ƒ´U[õéD> 7ŸçD>óò—N"j‚t2ϼyyN¤óA\q>ì!o< åÞ“ÌCa^Ò$O¢?kÆô©©eüš”{>œ”¯õ9¹ÏQ’ ƃƒÙl˜»‚.©aRê ‚^ù7Ç¿,Û+µ¥3’¿?‘Í ÷Ms&2ŽJ}Ù={O~,Ðõ#gȾɗóÒ–l˜K¢\w˜ ú z™ ކÂþ +‘Ngé0)ßïS!Ê÷'Ò^.ÐϑɅlA˜IçÄr„‘çüåô­ðœ–ÍLÅØÌô663íØÌÌN6³ë¦lfö&lf®“ÍìvlfOŒÍÌ{6³×±™!ÉÄ>²™ùmlæ?H½'Ù¿“tïQkµ®>xú Ï€s´Œß8G Üè>;ÿ½Š#Žñ{Twë<Þs;!Í¡Í܃ÑK(£×%Œ^—~wÄ1z—C2z#`ôÈu ®s䨰~~D„lбŒÞ0HûÆŒò[ãÂo%Ào‘¢=ÎoM Â4 $´* ð~”÷£ÌŸdŽö^€cgVËW»ô´-fÓ'z&8Ÿ“fãicÛB~‹ÿŽ’"êöŒA~‘1æyŒ|Äct qp‘óýžròwìÅÈy <ÊcБ߇9 ÏËeu:çªüÀ„ÑÀĸª õó!ó×¹_1ø²ô€Ò·¨à§ñ}È;]öy•%z6ÜÉÁV¦óSÓGƒ§Ý8˜#žƒ)˜rŒb¨£¦|Ôs0ÇÈcd·s0éX5–ƒ9h®Ì•¬¹rÔØvƒ9ã`dJ4¬þlÊs0Z{.ÎÁŒ€Av Yer0ÇMíØ"È5ÙžyFj2ôØ·úêgã¯ò Ǭ=ä8˜DœƒÑq»)ÓÃPvãLÀ!ÆÁ$=£o:8­Ëâ’Ò #”v#ÔïFïF<3B\Ó¥#¶Ò7€W÷ÙÛà¢c9˜.å` IµŒ—ãÓ&¢“ˆþ¿þÔúÉ›Rë»êÅ—q¹9~ X\m§¿oJzŽÚ.®àry'u]\5Vf‘ÕÅ&èÃÃoHJaœVl“÷]…'Añ\`†O¸¸ÑÙÁWq\ü.[¸¼† ÌËÆåëpù(.°ÖU‚ö㮿·L¿–¤ÔsB+·Þ…~} Ôkj;åê©Öpš5¼)µ¼IZuï|¤TGÂ|Ï_*}z(NŸ>üÿÓ§–>½ë/™>ýš¯ }ú…à–èÓß27¡O• Ù‹p}ûÖØÛ$°RÖxŒê™ˆÇÏ$vP…#Ž*üëÚè=©ÂI*~HÜ¿yªpB©ÂÎO½ªð€§ šòÁUxÈ”yªð0é¶ÌÞTáG0W’*!¥þÅá’$=LˈvOŒÙÌÈo€¾hx±|æÕGμpîÌ¥3swœ t~ß@:ÅÞÈŽÝ4Œñ•¤‚a=XR΃%íÅoÆå[pÙÇ®¾HZP½Á_¨Ï"1þ%áä Â8‘Y.¸-|ÓîuìÜþ™K£ì&wúx7 ¬iï\G·ugØÙݱˆ§©;õi'\é>·K;ß‚ÌõýmìÅx—u¸W‚NË^³¯m°~QõFýÕj³Q*ýX¬9;¼Óº=<Áã ¦82‘­ÚtVªë·X£ö+Õ…F³ºÝáèk÷\,¦ÚüiÌÊ8geÔ¤‚¾D"8 í’ú¤WhštÌw ·›L¨™Ý™|Ç–qkc'p­Tjó·î/ŽõuEàôóI»ØŒCú%ØhsW¿D‡Ôˆ0²Fß0{©Ä\A¼·®z|.tù~\~À쥄( NzJ)ŒöžÉìMž®Õk»FÞW,ÄzXÞ”gƒ~gⳉ‹'g6ÎY#i)šŠsɵMÊ2iGìdâŽä¯ó ·,”׉¶Wî Ú§v)æ3ïË6ü+Io'Û‚ßt<§¯Ävû7ÛÆðO¨º¸=ƒ;à‚ñ¾RíoÞlÙ4PüÌ~´ ó_u¬þtÇjß¾¸÷o!VJ}!i½|„åé4YüN¬´ öø›Y°E%©vº©ÂÙ+r§RÎ#ˆ1 d>j Ç„vÙ^5ṅْó ? Û×v¦“ïAPw¤PF_ËZ>¥âÝ“HàUf“D¾’ë­¶n„ ´=mŽ]Žû]Ìv ÓS«·d#,~£_õßj:ük)dØMÌþpØ®XƒòÃêG‘Á]âˆ<öqÏ/Ñg³æüß-¿„X"½žY ˜€("oSb¯»‘$ç[û‡ lò¾h¹àx˜«$>ð¢Ò5ÓÅo÷¨æ+€tºRé¨÷ý^ËxV0ÖêŸ'­«¬àîlÆ“§×A$臣¡ëïàR äaš¬¸$ÛÍp—+åî‘Ó5´=d~; Ö¨8D·ëJ`ý¡mH¼Nçjs&öÊ)`§ "I+6sr¯Ìëf%P7€qÿóRMê¥û²L¢ußd‚UìËP÷ÝùŠê´IÓ(臺܇h(³ìèB—ëo†Æ3‹~w™—f(3¯|ÊÌ®>$÷B†•¡ K‚çc=dSz¨ÀÎÐK+ᛑۣ«Ÿ2üf¡UÙ³ŸÑ•×-]Írx'µ†[ƒÕ¹Çi^³&|ÖÞ=³J­Öö¨‹Ü÷ ˆþ¤}9?9}®±Ùøä€ÏX%‰¼™ÑOß] ­ÝůºáÍ›ü'†í'à£J/{øÝ°A¾<ûý°ê\òH€Y”Û†ô°!p6ë¡÷X³>‹Å'P±´šR`Ø6¹l'wýšrqnfP›½1Ð7.°X¯™¨ ‹* ?›o—Z{-ȸ§Î‚³°rÈ» ¹Xœ í¯Øp”èSû>ãc2Uÿb6óyfëÇM²=BxSC™>KÎhÞŸ´<¢i²B*¥µºïø¯û6'F²éà´¶7'0»íàƒ’rÕ¸ãlÚóQ÷gVûe¶Tÿ+O6_ ùãl“–=ÌõÏ"a+iÖ¿Á‰Ñ°¼8·NÂ_Þ¥Ìz tÒŹ2õ3 dž ¨Ï)£€ŠšºÌ3«¯ Ô¼Î6¨YOã„¢‘„dV¡³¶9’ÄJÏXèž]­šY¡ËVRH{¯¤½—ñY³>oµlÝsl]Ƒ͒àpßQÿìY 0IÒèI©õùVÐ5ǽ«‰¿ÙÍl'’󆟘 ¥;¡ç»¾¢¥ŽJ»ÒT„DÀgŒ@ešÛÕ–îV `ˆ·­Ærµ$pP_¬ÒqzeI·D0‡+¥¨,7ÄZ´A•Üì-#ȾX¥ùy!xþðø8×P:‘#4æRüW¶&Ù®LO(ÛVˆ”îD:ȦÒa&즙^>Ì]a:Àö˜ Î$’áˆÚý` ½äV•‹ ůx(^2íQÇ„É Ã2R¶3·¼úùÛ}¨~ÖÑßñCÑiß ­'ó½/ ħÀñh¥8aY`¨J—±ýq;L¡YUÕUn Ü´ÖŸtc »ÚʱOn¦âž&ÜVWOÒÍk3ôÛÚf¥tÀNò‡ »R›^^žC«“½¡R£øùUÔVZ«Rb$›Új¸ÖCÕvYƒp ï:Õºeoª­ëÙŸƒœðÝÒ4 Œ/ØJsn%zå cî¼ 3‰d"•Êë²E©œqD<´Êé.Çá\Öz fÔ¨z1Ôzfõ i Ÿ-Ðúao\×%žÂç[1¾2ëë>ç2çºâ$ê!&ö9NöSNãäb^^œ»ßÎx´0Ç½à „~ÚMt…aWDæøGdûùù½*Óœ°tÎË’þ²7ÍQýzå¡ñÝI~׸m«"R£ø/ÚٟɆh¾±¼‚“|8çŸÂœŸåšÊ]¤†Ã~R ¤H?Èooäo4¥ÀU‡ù÷bðÿuWPXéuØN<¤ÛÙÚužï!.rÜrR¹å”ã–eþ;àh}ÑÎÓú{£üG.ν3ܨé%@€RnBA!0I¦zbËÃ[ÅÎ_è—³Qt"f›Ð®J.Þ2RÓKÚf‘z—ºéiãÒÛKj9äv~ž6«·ˆä÷êŸ lý©ŒC—Y™$.Š÷ú~dÿÉKîk„ñ B8[ô±úõBF}0»úù÷Ç ~³«ßƒô IÛð¾¡ÇqJGÿŒýßó ï% ê× :f±ú»~9äürø‚Ã׈­*µJ¹RÑUqŸ{õ(åL -=Ëñj¹µ(²7¾j(¶ü9,ßLÈe#$6—ŒÑ²|B,Y4á(Ñg¿°„ŠPÊÊIJop4° ê°¼é v"ÕAIYïÜ>oE¡Ê2Êœa‹øþüºƒƒ ¿±î’)Sÿ&Š’”iƒ"!e6Ž8Œ˜"EÉ,•S©¥rÀ–ÊÌà-•c¥ÇY8k-•3Û,•ùJ-•¹–rH#Pò“TŠ(¶…_uhk½P9EQ7êÕœ‰[©DÈ5ïAÊ›ªÐ€F1,A ¿ÇXAgñûpù6fÅOu¢^@•Z#—[í¥fÆLz*U³¶/H˜¥JKMrŸ h:§H˜¶·øKC²ñö ,é°~Î ¼¤èI–.ÑDc»9 …i#ü÷ýü2.¿‚Ë?Çå7qÁ±Å‰Ëoãò%¿ü¸Vÿ7\þ]Çò¹!ÏOH©c`P †FM'²‰lwvbðrOöPö‘l¶/; ×cÙ©žI#¿OOõü+5íù)5œé4íyªø,¤?ûeþ¼ÃJí­¸õg\Sy£‰tžŸÂå.O®®YZ®¶¯6*ûhØù˘]ŽBS¼±Óÿ¬#"K¸ª†¡ºÅ)«?i‚jÂíïçÂBô-ÝK>W¿Í›9ù×è&Ù¿Cò¹Í„ú“ŒTMs–JªTzwèpk]ÖzHcZoºèÕ›Œ[½~’éy•ÑÖ¼F•i•JÝO¥üF©| ó0À"ƒ2 é+Q ¬-¯4šmƬlÜáÂE:œ¯0”…6 ©÷²‚=Äú?¨§ …J¹]ÕŽã~Õkmc¥Ú"ëþ4º|‡áqöy€n¤N[—ê•b ¥!ZÏÊô§hôì0{@A ‚úlrìŒÅ›ŸW¤VüC¤åmZ«¶X/·×šÕkVê¢Ôjýúþ0Öh ”°%Žê¡Œµ7D¤87-lu.ì—»ž 'TO·I¹'àvÙ×à—1Aý<]Z¨2“³õ#²¿Ü߆t ÜÆ¡nqºÙVç*¹QIÖ ²ž›<'ÑÂg;m51øLÆ73¥Sf{†®)ÙÎ"iÛ9³~TŸü@¿ìº°=ÈxÀþuR{ÿô³OyÞÊ\ 8›WÞ Øòˆ-矩Í_[ª4ŸàŠP—"FÃÔWøPcÅF¦ÄáÊÅ?ÀR QÛZ üXóKVU½<¼ö-ƒ¢øŸŒ?¶´ ÝhuPÇä€T=ë÷»jÿîÍçn™úe]½vEƒAí½û¸«s‘'š—ŠAón&ã&ï+ÆÉsÄQÌœ#E¯‚H ò™}ë"¦N%šµu)c܉;XV»º;üßDTÒÈb&دúÿR£n'¢‡÷xvbÞi½ñt#Y§Qˆ=r­Xƒ’ÈoI6_e\‹õ¯Òl÷E'³Mظ'=¹S“÷‘*qn@~³’Þ!N t¶›et¦ªgÊ ùy^‹\g?ÇKÅÿIg\–ÇoyÎðµJm±Y^¹ú2l”“¥ŒI/INÚš]²0cÞ²5¯9ƒs,B9—˜©¶yF‡âF`%þ3›î\X0ÌßÒŹï {€hH–µó(ÄɨÀÀò1†Öì(zù¶Ï¬¿“ÁÛ“HvÊÑÓVäí <âôèENÎOð7»ú8%¬^£Þ­2Œ”¶Zß[VõšBßD=é6ëZ›, ÷so­ìê‘ ˜õÎI1þ†‡Ýg<Æ#ÓØ]s¹V§—ˆôéGžâÒ³Œí¡^…„žÀP1»,.9\º TVÕ¬.ñiƒ×²ï³T]Œ|ËË“íÍxSža˰ÿÖ‚Bp€’¥sá*è Ü??õÈSÅ¿R`T¾÷1‚اŠï®ÖiŽSédf7+˜× îaâŸtñ!R.>DÚŇÈ8ûþ.gߟuöý9gßßíìû{œ}ÞÙ÷÷:û~ÚúÃÄ?¤‰­üƒ˜•‘F<ÎÚï<`ÿ²)o™Bƒ“Íp›=«ò*ÖË Zˆ6•¾NÆ•Øîþå ý¡p(¼‰ÿUo⟴¤º½éq7yGàôº›>wÓo%ϵ%gôa0þ0ä†yÇÅG2žkâòSEŽ )ùçê­µ.ÕJA)]¡êcN2ãAš dôI5GS"Í*Bh,Æ(Š.Hiƒn¶ô·l«óW•fZjž+Í×*WË­«JmÃ̉aÃU èõ…¥Ú¼>7cÏX?îA=b¹5!–½Ef?âýýagà\”¤Ž©S'GÍ+å?ìWùíËIY ‡©;o#áÐG.tQq4Úþ¼ÈÇå#“›T½Â}a‰;ôa/=[ß”6Ú'ãyQmZKª½ÏÄzqî«A`sÒƒæÂÈð »vûÇ<ýNj fO-RYk €ne¬É>s·üŽ˜`6¦òW–Y?‡®V”€:8ùÕC~ èj*èP¡’'x}²¦»x¿Ûö…š% -tò/d¬ Ç}23iA×K:€î;h2Â`õCἋ¦àÃԼ׫j¤Qn’Q¦!ª"µD‘ Ð. D,S3X ,ûèûµrËÀìÎX¹§5P7¨Õ»*õ)Bœ5³}Ä@U8'l'…W6耆Ö]G“ h¾ÏÈÑXšÛ -¡E5bAÕ‹­Èé• ­ó· P] €è~ÐQ¥ B®™‚Õ%äè QÙ`,gÊp Dbgõ½a¯;Õ3kbdêýÂ,–Uw” É$uzN †w(Œw'›R.ÞNYþyFIµûà"y§EI™ßBÎvÚIÛ…oý¼n€BÔm9òe<×O£6Úê¥hù•´“÷ a&À7-“þ9A Ÿ6³ë«H¹8Ws|z–‘‰$0Î?VƒÐ”uÛІCm{éšõªK{PöeC3ýcùn è(ØE²Þí…È^7*‚ÑÁÀ–w’V ;8Ý-Ôc*D”Y/œ§pªÕÔº‚ôê©}ØC<¥`ýÏ^ï x³Hj(èMi Áî)!®AØFÀÊo" Tü¶‚A¸jb@ôÝf½!5™ü#çæì’Vè–æ6£Š˜Lø j'uÎr.çÆ6 HjQéö¬ÌгzÛJÎÆ ÝøŒu¦ÑtÀlŸÙuRS¦c>9>ULPG‡°5åíI)Ô×–K.AqÂkû±»ÀµÁ©Ö\õˆä-‡Îty1žjEhy<€iË›l8 ,DJ°‚§üŽódk ò#°Öõz2*?ÍÿÃvt'.εí$À¬È!ðq,òYEÃIk_¤;ûk>0ÈD*X¬Äc»˜x«‚Õï‘ßgäw;³jþ6aÂÌnèCðßøÉú[n²t½9L…uÆ­³v³\oi¤Äý›1ø;Ð66K%~‰~­÷`ÂÆí„·ë–ßX0)¿¼py½êuÙmb†Mÿ“]Ut_{‰ƒÚZ¥+)ã´E…ëM&¼luÝ5 t^8cOS«ŽéÊÚ‰›°"í󔆬M1OV:ð½òûùÝËßld't§†/Õš2j®Fâxë뱦øÜÅ3; ¾mÛ6±çßòͱ7gTŸØîމ.ÞƒËyGŽWš¥Vµ­sÞãá@¦©Eôªp0¼ˆ¶[¿Ö¬.•1ï/uy—ä4"b†£D­c²saâwÈ®î§Þký„]¡S¿Û¤g¢=½í\5j࡬Öïwð@iJx˜QxHÛ—Ôz{ aL Á )½œ·<ýœüžä4çÌèêŒfî`'Õµm"g÷˜9=õ˜¦ PøG§Óu¿Ù×9KÉtËO½J…äê‘I;à§-Ñ 21AêGB·V¯Æ¥¥ãÊ>õÓ@& L4#»•à³õ÷„|õÎð%NÕ¥t[1½Û¬ÿé§.àß ˆ{ç^ý2AÑÌ*ƒÕÃ@ðydÝê5ëD¯ÀžøšÿÉ•WTª¯È3ÈéEs葊ÉþP”³Ï¬×ÅU¡šÇõc ¤vbuoµ½Nøíº®Þ‡¶ÒÕ_YÕMˆs÷¸À¸•{)o÷GŽŸˆ½I_L«Hê5«“ÊÖȹ8÷Ý.F¶±ÃåÆêÃúnaÚ£Ž7°]$;ÈòJÃÞ¥ExÏ„íÜ âÌ—±ÞišT°úOé]ÎõnÀ/—³2_³Év«±ãFoª©×XSIr>Y£2œfm5Ó!j9ä’Õ(Ì9çv R.Fã××Ä.«oÝe½ªl7¬Jv¥Ñ¸Vq"–Z}~iM8t<åê6K›½N¼‹bW¬í?ËXnŠ­ÃÒ& ¼TÓµ"g¨LĈ*¶¡<­äšðXñWíŠO[ ¸7‘1=$°°[÷›L*KÖžæJ‰¡TNîûƒI!³†’oL0E!ÑM»À é9Žàm¨8$oz› +ÉX²ŒÚñwÊåã¡õÔònZ‚R:C&¦±‚Xv',G÷¥r†õô¥ÂEÝ¥Ô}êuŠl¬€˜Z0‰zGùH¤;ãæüV¹Û™¥òò•JùáÿCºÞN3/|%›Y|TÊÿ;×<ýLo`âðÎ8’¢®ð}ÞiT‡÷ûQ¢£Q,| Vßn©@R¦õû]ÞÌdDþƒð€&ˆA’ác†‚7‚¡ÐMN—Nt6—cZ„h2¼*›©4òV§"ŒNHI¸Æô{HÙtÎq0©ïÑ2,÷ýhY½<†.ï”?îò½MÈ2Û-0 _Ž`£ªôBÇ•Ëúgmœ:z’|ÚyÈ%ÍúGUà²#=©v¬ñ8ikû?ã$½Tqè\u±~A‰Ï»œ Ðå§Þq\>Ðì¬Vö²Àß,zèžcú{JÙéòCn†·KU(å°˜]#qYwz¡ýIVrc¹ãý¸J÷ˆ„" ž7õêä<ÌzèY=Èm`ØxóOõ#ð¿Òø7È+eo…ÎYLÙòM"Fk•èHì`œ’ÜBÂq )9¡cLVùn€ä½¸\Äå\ÞËWŽ®ïD·J¼+¾¹Wâ›{…ú?­[è!7Ðå¥fl´eLØ“èKŒ$Èxþ"ýnŒ«]1iû–3˜¯…n¼n¤“ntS=¯¢mfPÇOéÓž)Ï8fxÀËg<‰kmäÿu† ã_f<Ñ•D?®=¼æÝ§’θFMèf—~4þrývƒçŽ1!ZËÁôm“ÇÃÉä«¿Ef=Vò)–|_J#– :}/Odʘ1ô!L @I­šV<«b7®3›Œ›‚»Õj:ØÑ÷^†¬FÈþº÷ð‡‰ kDòúï$…5¸8÷!ýð=ÂÛ°ýrET–ë¼ßÍ&ýN}@b¿¢ç4 A¬ãÈ—¤iLäžzVýµa.‹AõºZ&Q Ò‡yæÓN^Ÿžú }Ù”‡a¨‘ñÐÐŽåL÷&³²ƒÀ»!ÓÓ¸—GµhÈé<¹ (#ìb?ÞkbrÀvx"YÅðß–FÍêŸ%b 9  éãC/W®mó˜•è«ý{}uÀ}eVoKºAvçWµö4*ß"{"ÕN¡’+Æ÷¹› s‡[ã<Ài×n!u4žz?RH’¥¼+,MwMÇaP ´œÃhŽíÝ xžI¿„ÚGxŸ.é“ÁÞmÞ}ô?)\[Ÿ–Êñ*7zœSbw¬ úá\hO_‚ÍÇKÝÕâpòÏ2°¿ˆG!aìS¦ñk< ,‚ÿ¼{3`ÿ¡ öSdX¥$ØS˜%ÈŒÆÇà]é`u.›ó½Š.¿P¸…¢ HA2¹m¡´>»ù°`¶UŸjœ÷´cÞ*üž—¾HÞÔúÐ|ooyºAÛPåt°[G€ 6ò›*?dÖ?ävqîyóR" A¶[‡íQx›®&;V8Yï¤oÞ³&úF°¬Cö™¬ÿåC×ùëDëØeŽ˜õ-ýêÚ_}ÇW”.šÀW.‘fÇ鈩Œw6DêßÑœ¹L°Z–ߤñ›Ý<¢û€–OzT‡1)е[σfë¨Y¿ËlÅY¶çNš­cfó˜[WGÙT;™¼˜YýùÆ÷dfW¿13‹P åpÜDKïø[Yz®pR³ã´ÌÃ8NàAR¹kþ‹ ~Z©äec–Ö»<É+ÜÑ,é>¸¨}ÌR­új px…8Kjr!†½´›1ôH¬óìúÂT…Ñ òßôTå,jhp£Ág¼lœñj4,~a•kè¥JqÆ®©øs(w7+;Zh]­-´ï´%œq  NµW«±t]Ãsi²¸zË… Áø–êaF }ƒ»ÖC¶-ú†5ììÅèÏÕ5X•/W«ÜÀi„­q÷ÅB¹^),6 í†ÏA ËìfÙ­‘ÿ©3çïm!ÔU¿mº&¼ˆvÎQù¦¹î>g{»Ëw sµ[Å\‘’þå´„¢M숊ŒŽE£©sx„݈•ƒØÎ15Ø„ç‘~ÆñH±8XŸÄå(Êþ îµê«œ\"ÁHHÁ= ¢Nº5=„Œ@Ô\žVö´k.M½Ô“bE¥&ìv[õÝö%"‘«ÁyÛz][ðO+Z¹­î1'4’üdÜ( T8c\-n‹a0Õ‘Ò'65‘fõK• O¢˜¿ÚhUíÇšÕ—¥ÀŠêæ½¶D£Všµz»øÏŒÚ.ÑÏߪ_«n´Šw’3"/en¯,—ê.€·é§ ¤ÇFDφép(ÕƒH[*¬ ‡\^õÀ UmÑÂSò†C|s\¸Ð|˜ONãÁɰƧˆLÊ_o"#÷Gƒ|¢›±½zé›9L†ù`"˜ ‡™ÿp˜^qÙHM“ZŸäò)­u’'¬i]“üºÜ%†¥%£l1lýQÃA) ÐòL0ŒÌ†Õ›ñkRë=GM#RòøvLÞ?Oºüz¶,TÂ͵h“šlÙ dƒÿç{’m Ñ+LµÖQ<¤ .ÆiËÙÁÅJ#mC´ñl`m¡Ö?)+(QùI¦,ø»õ%ò7öÅø¢›góv‘ÍévA&ó$ª)Ò‚I Iº­˜…ÌÙ„†Ì¼aÒšÐãÔ賫_G;{ô@Å*ëŸâ—ì÷oðû½ü¾æÊ‚êdÇÖ“«Ë@Ÿ2ÆïkŽ¢'p>¸ÊõøM[$}“"k¾ˆmä¤OЖö¡WÉ„9Ÿ ¡)Õë 6´gwô@éfi6þIS_cc«_Úþ±]¦­ç¯zÚ¾&œ]½?t Øÿiûá[ž¶Ó‰mÓöëá®Ó6¸}Ú†âÓÖó6§íÓ‰]?6¬u¿Êºá˜Ø°'N×zMãŸm„Iú¢Ÿ×› WF=­ ™…´ýØï'\ÁQx÷iLÔxY߬ß÷ÍóÍRcéÙzÑGP}œ¾pm2Îò}"Ïã,KoqVèÓÚ}NÃ9aÆnXχày“ˆ¶y©ø7Uìµ ·„0 {Â+ŒÏ;.t‰\ž½Zk©B¦®µËåv þH…Egž¶p±Q­«P­ÔÚgs1WÈÂC…©f.9/ƼS˜¦ø‰YmÀÆ;yOª¥™äüKm^˜~‘­žjžæ¿s§õyîÔi·[¹Ö?í¬… [9P†¥k§ ¥ë Ò¶á,¯Ó§. =̺~º´œ¯ÖV¦K×_<7wZ®çç4Ú¼À®—Ö;«»Pˆ=¼XZŸ³Ÿ×B¯^,]ÃëÒF®R]ÚѤ Æí!Y?-½Ÿjžº€Ar™hÚ ×/ÄÓ÷ƒ¨Ð[C€Ú.ø»½ïx³³óQ[rŒØÔÙz†þÚæ++/^̵ÆHB똜žªœv7§NçÜ7þîR£^.È ™ËQÀþ\ž—òÁùf„7bÖæZÎÜ´©ÑZYªµIö5ZzZe¹}U „c«žÔû'žÈ&áýEO<ÏzŠœ>„Ÿð„wtV6p4îïÕðí)G0V×çKµúBƒ‡ëá›>3T,ÈÍÆZ{e­]©IéÀ:\AŸ«V…¡dò²¬òjSÛìm•ëm!#u‘¨…]™ÒÒ [J…ö¿‚ êñÇY«_‚‡ñDúÂt×d‡§CòB4½>!ðzàôL€ldøYèÍG„¼ã¿áÈÂLw"Ïà_·” ßFùЗÇ¿ 'ƒÂÛa6-d,B¦NÞ-ÒGí¹lósNÜÔÏ9±‹ŸsÒÚ°¶©\mSýX‡<%&·§†»fìÚ55Kµ¶ý².ÌçVÛm(ñJQ°Ÿ¶Ç‰cäaæš×~^°r‡ûW¨í —«û”}Ö¶¬£¯IçMsàónÓ¯\™¦GÚÿ‹Ë_àòŸÜ:äÒ¬¬-¯p-ÒÓ^=†@ÚùÆÒ®îÏŸð‹tÏUyÖ-͘ª–Kë+rŠ–u·ànVö/¸í׈@‘ià±ÎÏÑ`rð ÓRï ï””áLbÇ ŽS§H RÞÁšƒ¶ªÁ»Ø¡ÆSÑËâ ™þýç­0«cRÓ§+L:è›ÊNdeÈÈgdzwdŸÌŽf³rÿó}>¸·xý¬\6r0KøH +î[eÅ®¸*5Ø`YhQØÃšj­§°*íÇÚ-:%ž,Êû·ŒYù ׬ŸiʈR#G+7ðwÙ$¯¡IyZl»ñ8õψ©­!'jÎ<ª}¥´Ð2GJPJ«Nº´¸Ô¸‚Óté¤aÍcJKy¤2zà ã0|.”]´ŠÀbí+jX•p{ÛÒ¾Љ½t±Ú¦ûzU(@î4%Tý-ØI °9ÆóÎÒ%5Kƒ!4%, õ±š^ ÔŠ5Ój3@‹n€ä}- î ÀMSµzß$u¢cîS´wÜøûH?ñm踯¶‹.õl;©"Eû×.F@¶®þ~:&Q*@»Ø-jV…ÛÇ[Í7¡çIT4tÊIja**F‚'ìö-Å„j뙥ͬʾg¥I)pΜ?bË)H"üEŽ~Æd뜭¨‚itj _]¡¸Oc£7…RèдҘ!í ·œV­¾¨gP! Õ ï*<|œÂç6Ýïܦà þÆ|é#4áÀPëõln¡É»:/:WçJ,º ›]¦1*‹¬ ÀR˹H.ݦž36ˆ+ŸMg nˆŸñûã8TK8¾žðÀó>ˆÀ%·TèÎ6çq8ˆsuÞÝ&dßzà£A‘ãÇÜf…^Ýålyxky$jµÝ]èïþ.Q^jÜ“rKoÑ@†O±ÊÙ$;H.ÇJçánLb~ðrûx:zÆV.ÛÏï`|rŸœýÛ9*½­QQ£w—öCD†þ]//Õ°ýÚqŠ'Å«/žnG¬#olØ:ÓýØu~Ná‘Aª÷oL{â_ý7ØÞŽõƒ‹õÑë÷90AÃd‚B0AK´—²Ç…±c‚lŽÀåÐpˆNÃ5ÙUÑÁ7tLÂøC9âiÓxÒe«ã¡JA¤5f.Y+}©Q­W?e^cU»ÖÙŽÕÖ™²A4bèŽü0Z$%4‰óbK› Æ -CÁm¼àêÿÃßìl}B††VW6P¤žë厤ŽêVdÆ8^H S¸¤roKU[íZýÌy*6x-#§1ž#—",Õ®?8Æ ˆ®¸éÌ’Ú•ªjù(Úø¤{C¨S«HÄGÓxSXaï+/­U£ðS•ÚbµÕŽ9ÎáSl£l¤¾x—hüEc9¡ÅfcmEEvÔšºå£r6ôi¡©¢3 )^nU5àž|'â§ð *d­Þfœ—^' ½D%pt¨¶ ûë·¼¾Ojîîvq¾°_<È›T˜ ê·Wþ܉9JÁúxíhOM˜˜©kÅù½+IæNDòP‡äMÝ!”} Šù)©êd·ñ§‹ºvúp:_åÛiÚîP§m ïÀ½QÐëZÊv%X}ÐÕúÞÐöã$7í“þpÎrAùEhD–¤é߇|ØQa‘;p%tÌŽ vÎØ£»@Ct¤dú4´Oœ½ÓñºÛž6Œ~<þ©dd&}põK1@Ò ÞE{°{:i'à¤Ãk§ WÖÚЯA‹R.8r'¾ªÖŒ²=‹-Ýì\¹ºVkV[…ó…rsq‘ÄzÜL*@þ‘±çä8‹­Z#›²bF6õ[$G¯q¸5p=ñSƒ"y&YE‘¬M”O§Å=¡¹~K›®®·dªy‡:n¶¾K¾o·w…Σú ûe£O†ƒ49$)ónx¨ûÁm‹ÄÁÒ/bå°£ðÕyÙZ?nú@À6âœÆº_ d¾³Lr—2;*Níži“¡¹¢Y$µˆƒ.5ì±’°oœ¸säRJ+»CR̉ãˆ×V„ 苲Hi:B«˜1Zýg;P—BÏçpùFc©¾Ø1џܶõÓRÉÑ$ŽÐ¶'¤ÂQû¯{žwèÝOâ«Æ8· =õ°c×jᶉSìh8kAîw¢KàÓµ‚„%y`Åk,ÜÑaÇé=pÃæêÔ9Òã:uŸ-<±ãœQ´ry–ùõ|е¥vm%¢tt1a˜csBÒ# @'¶?6aß-Ÿ˜ëv„îå¸«Ú Œí²ÉÜuyÉŒ£>–%w´OîïþøíRÕµm› Q—kïZàNõ±[ÎóAÇ–ÒNl[ÏqÒÀ¢ö”‚Òúaw–¯QJ<øC“ÚtœÚ»¾Ä.õµ36N§0jAì ¤ì©ÛÊ€cM;#4(ɺv~+³[Û_°‘ÿ\œ»D—MzÌíV¼k—â›Ü,U/§Q˜ÆœY{¯ú¤ÇBæ€g.Ѽ5vìˆJ× ðÑr%~n,µ\8“¼{º¼´Ðh.W;òÈö×Üài±OÛÚ§yùižÉ~ºpöìY½=¥&§:›TÞõ,vGîQfË­ö.—Í£®ñŸÜF‹˜Ü‰$gÝ~‰º11FùQè¿2ŽA†!ǾœjWü©¸Õr«Òä ]óTn;ü ÛI¤©5'îè¶nïo‹V™ÜôOŒ?;ësz ÃümÛÏZ+T¢° £þð„ø7êgÇ‚RÝ7…<º¬p7V¡Ši2ຣÇ.òØÕkkˆ (R¼ò$vl™PwÝ.ì¥?dHõÔ”Š7plÙýÿg3õs¥ Š?»ÿ2pÓ‹á)•*ùRIúm4ÛÅÏ¡»ù/È‹ø@šj.¾y?¦þ;ä³ßÒí•ozڀɘ ’û;‘ÈEB/¾»/ᦶíâ¾Ý\ä­Ã&tn¿ ‹w¾În¯ç®/%- Ȥm¥œ_i’µé,S©þ¤ñV°žQOž›¢2u†„zöTüû)K”ü gàÀåÛ²z‘j€Žâf[ñôÍ‹«™ÃJÁ¡™äö"ȹq©˜m—Áq]©4aã3C“Œåx2˜­?j’í>ÊÞ¡Z¼~dUšÂ€:®µíAF©cÈõ`uréi¦ÍìzÍa÷a]’Ï‘j77ñ¤9j]3kè»Nň»ô°:¿¨âШXÖ/ܯ´Æš–ó'Púá£fÔ‘[ñ¯âcª¸Q«V™1E+§âR>¶-£õ´"óð>ié6pë‰$pËJÞGšòÍé5Q=c±ûq63©Íœ]½-‘lOĤ²’:¶2aëšÖ K˜¹j…¯ûÞIãYÀ¢?Wþj¹%dg£°\®ox&°?E>ÊëÙÅr=Êú˜‰ß^Åd-²»Z¡µRÇiéèg=oÊ*§k‹õF³Z9Uü‡Å•mÅ•äJ˜<­“ß•[1ö–âèâG‚Naà3V«ë»ø)óú5WË+5a,…a^)aû_¨­Oð›êg;IæÏtâéEÿîhóœT¯ø ‡±U»ì­/t§Ï«xŸØ¾êq<±ýGq™â²AÕzÔ­&DCÚ'Ü® S"3¡×R\)-ª“,3ôlºý8-´ø½RÝg€ö? hßóX93H¯ŒœPû£ð°×\P6¶À¦m£Aor …íâœlÃò;*œÁ)ùC¾ '8)ùòá¥iænæEú~\h!é$ÅyoQ`DΞœ!™Òõ$W¸q±ûcYôÍRÓ¯ä,œ¦ƒž¾lW6—=’=˜MfÓò–¿^ù÷H¶_B0­ð9»Ãmˆ¿cX('¥Ê‡õTáÈús:’9ø†ÊV×>¬ìšdc ×^ƒ?dVÔ#{ æNmØ.°èQ~mܬ/óñ˜ÀÉ«MÀ|ë€Ùƒ+{í8¼Ù7'锚ÀÞ´&Û'Þx8s±AÁp®†²ƒ­†³ë¯ó{Sò½-’íáw¼yÈ€r; oÝ­m7ñó·Ñ—ö(ý°›Í#TÍ®þžoÄÝ{6"·£òRN KS~/œÝ¸‹Ú4Híå{'Ùºi­^Ÿfí¢ê3Æ}÷ÜM¾ÛúQ±Ý'K¾qŠó}̬¿žÃÎýä¸Ù:áú"”Ì S»×;è8œô=ú‹Ä,*9ÍJ¦Ìæ”i¼äáFýaìC>þ oàҌ鸑 töz1ëô5ל}îyu%éøðÆvÿDÿ.Ÿ¸Ç´Ïp>Ï*J:ÂîÉO›QŠÌõIõcþ’ýˆ¸“}š6ëR~ZJN¹!cX…øÈõœRÈ£©Ùöyô lDÊÇùÐRCÑRˆçIÒZÎæ6þ'Ï£»U8ÒQáô®ŽÿÎUˆ!|0ØuÇvaû.ŽßÝ\¶§Ìæ)S»‡x½ˆžÓ>á“!(*¦v¯Ú$ÜnËJê’Ѻ`z‡%¼?ýÚílFÿÎôìnšÜ³Qï`£N›ÍÓñFÖF‰5êL¼QgmYIõ:oÔ¦_;ëõO·5ÊK6* &÷Lîä)KwªíÅ9&‚aÏ)ð>”á:¹Ÿ™Ï›õi³y^7È»Ü2¹Ç²ëHÑ ¦ÂÓ¡<¬=È0"zÊM‚»¦dþA0Ùÿf8à÷˜Í{vBãÄŽÇÁá°[@™8HKm±¶{Íæ½;k;ªœãßë ìÛŽÚŽ¡ GV2¸>}GhWrº§?d_§p>)y8°¨âœí!ÇWúþ³uŸÙºßØ\²øï3›5÷ëR² ]ñ€Yÿ)Û™‹sŸs/˜­‘¹ý°Ù¼€êqó n„šyÀ‡\¿­Gí˜bõÔ3@“nC)IeR÷Î\Ý;rARðÀžŸž‘/ò¬ª[a›ý|g³4µ¯2=F¡ÚF¹8ï›t’µ…þãÑ󌩽Ó~*Xýã,~³6€1ycùÚ#”dAX¡±6"*'VÞ>ÊPƒ¢zk×ô´gIÉ]’eÚæûD¢ZTlª`”ü³W«Âž¾BNn¥Ù¼Ëœ&NÌlthSTP/X˜ÇèIU)\Ù(<óÔûývS­ÂôÕv{åÂw¾òÊ+g+å+Õò«gçË ÖOQê*ìr¤óôüg¤£ÌªÅˆÞªxùJcI¹F¸Ó«‚u'ª ›F*–ÈØ”*øðèؘ¾¦Cq‹z‘ŸÊyÆphñ VF~ ÿ=uæ^fC«¤|ùîuù±®AÁ»f[D%Þ¤QÁT¥ó-§qgQŠ&ö(É—1<ëú|š|¶•T¼Â22¿…òÊJU`:ä©3wk8Ïàå[·¨bQåß  t#>SÒÚµº€ÉüUžuN뉺ŒM­]-4«ók 1•j[-Éá›ØŠŠ3>å3‘„~§ÜÖlÀxA°ªö¨)@±€$¸Å98¿{ˆޤŒßî/©µ=¿Glö[Šîñ–#û˜{ºÐ‚ÝM£¤ÄbtDLx{и¨+; ïZ*%…!RÀ“;¢›L:×7­B½*kÛv®2ý˜—tZC«e~­ÉwÔEKZUü0¸|ðæ*+  ç qœB¨'òŒCo¨ž'p¡ÕCÅ8aLÍËuàû©ç\RCçLL# èi®¥èèVÊ'°|UýJ% Oxþq/ÓùeÜñ˜gÚÿü–ñPØÃ³ž©æa,“ßö² ¨¨bD”_BU´©äñщÑ_Â…®œðÒà* ©ri?hœ”*r¶â±E'Wìÿ2Ö¼MàØžKóuÈ!ç¯V篕ür¢è©±Ò®-×^Õ#(b®—j±V©^Y[B/^s†tLZj,ª *P30Ãê•ÆÜ4í„s(Í@Õ¡—ÓECz­¦œØp©éæGŽáEœÖ­NJi÷!k`=˜jÄ  S‡'Ùèì h‚ô06'¿„Ëçýd=Ëu?Y”³}­Ÿ¬ûðà۞ÂТÔÎ>?æÀ'†µhË·VüïˆK/màÙ’ƒƒ>ZMÛljÑëeÀ%¹F—xG”—022oz@ûˆiããêÕù+7Ù•¸ oÙÚŸÁý— ;¬£o]™ 惡D&xŽL Ês.èOô$`e› †Â¾`˜nˆƒòÜEÙáq¹öcrM…8Sd"̇ý‰4œq¥ì@¢/‘3}RfŒ¹ÈS”N‡¬ä±OêÆ9e| ºa’€gLOpP¾/wžQ–¡†r<áž!¯<Ѓ‡CŒ3éÿu¹úYFr¼'ÜöL¯-=lSìzCý2¤¦hGFÞ Ê]_gÐN=“—vÐ/„èß$-*ú‚c%ûwܦS¯:!u¡¾„Œ^˜ ¦ ™¿ xü·¦1\„ÞÑ0Ë»kÝììÛ…òÚR»´Ô,® ¦p9‚ œÙ‹?ŒË9¼LØn´ÎÒ†³TO†n/—׫qƒ¸Vi·›5¡Y¬­wF³´³®Lã Sqÿ¸GÍÄèÐQAAvïðxüGåàîu\>‹Ëwâòc =£sK@¸dž©A§ˆ5¹“|Âo'Ü‚þí~‰5þ¸ôãš— ÄÈé.„z—¿Pþ¸žK ùD6™àÉZ½‰l~´43šÈæ²Cù¡sC_6ø{¥'Ñ79úÄèéÑÙþÑpôËæOåú¬äÍŽ"Ç_d‡³Ór7íÿPKU0^;“×2¤EGG-INFO/dependency_links.txtPKU0^;?_¿C£ç¤>EGG-INFO/PKG-INFOPKU0^;k\nÞݤEGG-INFO/SOURCES.txtPKU0^;efž¤ÁEGG-INFO/top_level.txtPKU0^;“×2¤ûEGG-INFO/zip-safePK7Qu5K•RR¤-ply/__init__.pyPKU0^;ô’µ¤¬ply/__init__.pycPKƒFF:ÒJ.ˆ ¤lply/cpp.pyPKU0^;ÇÏ&ÍUäJ ¤!ply/cpp.pycPK±Ud9H_í*´b ¤š?ply/ctokens.pyPKU0^;_¤Vk ¤zDply/ctokens.pycPK@x:Ë+ðE&öž ¤ýIply/lex.pyPKU0^;ü¼uXB(Wi ¤µpply/lex.pycPKÄ1y:ä„ÂVÆaçõ ¤ ™ply/yacc.pyPKU0^;}tzyV9ø ¤ûply/yacc.pycPK˜²Q./CBFlib-0.9.2.2/ply-3.2/test/0000755000076500007650000000000011603703070013662 5ustar yayayaya./CBFlib-0.9.2.2/ply-3.2/test/yacc_badtok.py0000644000076500007650000000277711603702121016510 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_badtok.py # # A grammar, but tokens is a bad datatype # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc tokens = "Hello" # Parsing rules precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(t): 'statement : NAME EQUALS expression' names[t[1]] = t[3] def p_statement_expr(t): 'statement : expression' print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_error(t): print("Syntax error at '%s'" % t.value) yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/lex_module_import.py0000644000076500007650000000156111603702121017762 0ustar yayayaya# ----------------------------------------------------------------------------- # lex_module_import.py # # A lexer defined in a module, but built in lex_module.py # ----------------------------------------------------------------------------- tokens = ( 'NAME','NUMBER', 'PLUS','MINUS','TIMES','DIVIDE','EQUALS', 'LPAREN','RPAREN', ) # Tokens t_PLUS = r'\+' t_MINUS = r'-' t_TIMES = r'\*' t_DIVIDE = r'/' t_EQUALS = r'=' t_LPAREN = r'\(' t_RPAREN = r'\)' t_NAME = r'[a-zA-Z_][a-zA-Z0-9_]*' def t_NUMBER(t): r'\d+' try: t.value = int(t.value) except ValueError: print("Integer value too large %s" % t.value) t.value = 0 return t t_ignore = " \t" def t_newline(t): r'\n+' t.lineno += t.value.count("\n") def t_error(t): print("Illegal character '%s'" % t.value[0]) t.lexer.skip(1) ./CBFlib-0.9.2.2/ply-3.2/test/yacc_misplaced.py0000644000076500007650000000300311603702121017164 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_misplaced.py # # A misplaced | in grammar rules # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(t): 'statement : NAME EQUALS expression' names[t[1]] = t[3] def p_statement_expr(t): 'statement : expression' print(t[1]) def p_expression_binop(t): ''' | expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_error(t): print("Syntax error at '%s'" % t.value) yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/yacc_unused.py0000644000076500007650000000320511603702121016532 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_unused.py # # A grammar with an unused rule # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(t): 'statement : NAME EQUALS expression' names[t[1]] = t[3] def p_statement_expr(t): 'statement : expression' print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_expr_list(t): 'exprlist : exprlist COMMA expression' pass def p_expr_list_2(t): 'exprlist : expression' pass def p_error(t): print("Syntax error at '%s'" % t.value) yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/lex_token_dup.py0000644000076500007650000000047711603702121017100 0ustar yayayaya# lex_token_dup.py # # Duplicate token name in tokens import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "NUMBER", "MINUS" ] t_PLUS = r'\+' t_MINUS = r'-' def t_NUMBER(t): r'\d+' return t def t_error(t): pass lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/lex_re1.py0000644000076500007650000000043411603702121015570 0ustar yayayaya# lex_re1.py # # Bad regular expression in a string import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "NUMBER", ] t_PLUS = r'\+' t_MINUS = r'-' t_NUMBER = r'(\d+' def t_error(t): pass lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/lex_re2.py0000644000076500007650000000045011603702121015567 0ustar yayayaya# lex_re2.py # # Regular expression rule matches empty string import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "NUMBER", ] t_PLUS = r'\+?' t_MINUS = r'-' t_NUMBER = r'(\d+)' def t_error(t): pass lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/lex_re3.py0000644000076500007650000000050311603702121015567 0ustar yayayaya# lex_re3.py # # Regular expression rule matches empty string import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "NUMBER", "POUND", ] t_PLUS = r'\+' t_MINUS = r'-' t_NUMBER = r'(\d+)' t_POUND = r'#' def t_error(t): pass lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/yacc_term1.py0000644000076500007650000000300111603702121016251 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_term1.py # # Terminal used on the left-hand-side # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(t): 'NUMBER : NAME EQUALS expression' names[t[1]] = t[3] def p_statement_expr(t): 'statement : expression' print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_error(t): print("Syntax error at '%s'" % t.value) yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/README0000644000076500007650000000044511603702121014541 0ustar yayayayaThis directory mostly contains tests for various types of error conditions. To run: $ python testlex.py . $ python testyacc.py . The tests can also be run using the Python unittest module. $ python rununit.py The script 'cleanup.sh' cleans up this directory to its original state. ./CBFlib-0.9.2.2/ply-3.2/test/testyacc.py0000644000076500007650000003362611603702121016061 0ustar yayayaya# testyacc.py import unittest try: import StringIO except ImportError: import io as StringIO import sys import os sys.path.insert(0,"..") sys.tracebacklimit = 0 import ply.yacc def check_expected(result,expected): resultlines = [] for line in result.splitlines(): if line.startswith("WARNING: "): line = line[9:] elif line.startswith("ERROR: "): line = line[7:] resultlines.append(line) expectedlines = expected.splitlines() if len(resultlines) != len(expectedlines): return False for rline,eline in zip(resultlines,expectedlines): if not rline.endswith(eline): return False return True def run_import(module): code = "import "+module exec(code) del sys.modules[module] # Tests related to errors and warnings when building parsers class YaccErrorWarningTests(unittest.TestCase): def setUp(self): sys.stderr = StringIO.StringIO() sys.stdout = StringIO.StringIO() try: os.remove("parsetab.py") os.remove("parsetab.pyc") except OSError: pass def tearDown(self): sys.stderr = sys.__stderr__ sys.stdout = sys.__stdout__ def test_yacc_badargs(self): self.assertRaises(ply.yacc.YaccError,run_import,"yacc_badargs") result = sys.stderr.getvalue() self.assert_(check_expected(result, "yacc_badargs.py:23: Rule 'p_statement_assign' has too many arguments\n" "yacc_badargs.py:27: Rule 'p_statement_expr' requires an argument\n" )) def test_yacc_badid(self): self.assertRaises(ply.yacc.YaccError,run_import,"yacc_badid") result = sys.stderr.getvalue() self.assert_(check_expected(result, "yacc_badid.py:32: Illegal name 'bad&rule' in rule 'statement'\n" "yacc_badid.py:36: Illegal rule name 'bad&rule'\n" )) def test_yacc_badprec(self): try: run_import("yacc_badprec") except ply.yacc.YaccError: result = sys.stderr.getvalue() self.assert_(check_expected(result, "precedence must be a list or tuple\n" )) def test_yacc_badprec2(self): self.assertRaises(ply.yacc.YaccError,run_import,"yacc_badprec2") result = sys.stderr.getvalue() self.assert_(check_expected(result, "Bad precedence table\n" )) def test_yacc_badprec3(self): run_import("yacc_badprec3") result = sys.stderr.getvalue() self.assert_(check_expected(result, "Precedence already specified for terminal 'MINUS'\n" "Generating LALR tables\n" )) def test_yacc_badrule(self): self.assertRaises(ply.yacc.YaccError,run_import,"yacc_badrule") result = sys.stderr.getvalue() self.assert_(check_expected(result, "yacc_badrule.py:24: Syntax error. Expected ':'\n" "yacc_badrule.py:28: Syntax error in rule 'statement'\n" "yacc_badrule.py:33: Syntax error. Expected ':'\n" "yacc_badrule.py:42: Syntax error. Expected ':'\n" )) def test_yacc_badtok(self): try: run_import("yacc_badtok") except ply.yacc.YaccError: result = sys.stderr.getvalue() self.assert_(check_expected(result, "tokens must be a list or tuple\n")) def test_yacc_dup(self): run_import("yacc_dup") result = sys.stderr.getvalue() self.assert_(check_expected(result, "yacc_dup.py:27: Function p_statement redefined. Previously defined on line 23\n" "Token 'EQUALS' defined, but not used\n" "There is 1 unused token\n" "Generating LALR tables\n" )) def test_yacc_error1(self): try: run_import("yacc_error1") except ply.yacc.YaccError: result = sys.stderr.getvalue() self.assert_(check_expected(result, "yacc_error1.py:61: p_error() requires 1 argument\n")) def test_yacc_error2(self): try: run_import("yacc_error2") except ply.yacc.YaccError: result = sys.stderr.getvalue() self.assert_(check_expected(result, "yacc_error2.py:61: p_error() requires 1 argument\n")) def test_yacc_error3(self): try: run_import("yacc_error3") except ply.yacc.YaccError: e = sys.exc_info()[1] result = sys.stderr.getvalue() self.assert_(check_expected(result, "'p_error' defined, but is not a function or method\n")) def test_yacc_error4(self): self.assertRaises(ply.yacc.YaccError,run_import,"yacc_error4") result = sys.stderr.getvalue() self.assert_(check_expected(result, "yacc_error4.py:62: Illegal rule name 'error'. Already defined as a token\n" )) def test_yacc_inf(self): self.assertRaises(ply.yacc.YaccError,run_import,"yacc_inf") result = sys.stderr.getvalue() self.assert_(check_expected(result, "Token 'NUMBER' defined, but not used\n" "There is 1 unused token\n" "Infinite recursion detected for symbol 'statement'\n" "Infinite recursion detected for symbol 'expression'\n" )) def test_yacc_literal(self): self.assertRaises(ply.yacc.YaccError,run_import,"yacc_literal") result = sys.stderr.getvalue() self.assert_(check_expected(result, "yacc_literal.py:36: Literal token '**' in rule 'expression' may only be a single character\n" )) def test_yacc_misplaced(self): self.assertRaises(ply.yacc.YaccError,run_import,"yacc_misplaced") result = sys.stderr.getvalue() self.assert_(check_expected(result, "yacc_misplaced.py:32: Misplaced '|'\n" )) def test_yacc_missing1(self): self.assertRaises(ply.yacc.YaccError,run_import,"yacc_missing1") result = sys.stderr.getvalue() self.assert_(check_expected(result, "yacc_missing1.py:24: Symbol 'location' used, but not defined as a token or a rule\n" )) def test_yacc_nested(self): run_import("yacc_nested") result = sys.stdout.getvalue() self.assert_(check_expected(result, "A\n" "A\n" "A\n", )) def test_yacc_nodoc(self): run_import("yacc_nodoc") result = sys.stderr.getvalue() self.assert_(check_expected(result, "yacc_nodoc.py:27: No documentation string specified in function 'p_statement_expr' (ignored)\n" "Generating LALR tables\n" )) def test_yacc_noerror(self): run_import("yacc_noerror") result = sys.stderr.getvalue() self.assert_(check_expected(result, "no p_error() function is defined\n" "Generating LALR tables\n" )) def test_yacc_nop(self): run_import("yacc_nop") result = sys.stderr.getvalue() self.assert_(check_expected(result, "yacc_nop.py:27: Possible grammar rule 'statement_expr' defined without p_ prefix\n" "Generating LALR tables\n" )) def test_yacc_notfunc(self): run_import("yacc_notfunc") result = sys.stderr.getvalue() self.assert_(check_expected(result, "'p_statement_assign' not defined as a function\n" "Token 'EQUALS' defined, but not used\n" "There is 1 unused token\n" "Generating LALR tables\n" )) def test_yacc_notok(self): try: run_import("yacc_notok") except ply.yacc.YaccError: result = sys.stderr.getvalue() self.assert_(check_expected(result, "No token list is defined\n")) def test_yacc_rr(self): run_import("yacc_rr") result = sys.stderr.getvalue() self.assert_(check_expected(result, "Generating LALR tables\n" "1 reduce/reduce conflict\n" "reduce/reduce conflict in state 15 resolved using rule (statement -> NAME EQUALS NUMBER)\n" "rejected rule (expression -> NUMBER) in state 15\n" )) def test_yacc_rr_unused(self): run_import("yacc_rr_unused") result = sys.stderr.getvalue() self.assert_(check_expected(result, "no p_error() function is defined\n" "Generating LALR tables\n" "3 reduce/reduce conflicts\n" "reduce/reduce conflict in state 1 resolved using rule (rule3 -> A)\n" "rejected rule (rule4 -> A) in state 1\n" "reduce/reduce conflict in state 1 resolved using rule (rule3 -> A)\n" "rejected rule (rule5 -> A) in state 1\n" "reduce/reduce conflict in state 1 resolved using rule (rule4 -> A)\n" "rejected rule (rule5 -> A) in state 1\n" "Rule (rule5 -> A) is never reduced\n" )) def test_yacc_simple(self): run_import("yacc_simple") result = sys.stderr.getvalue() self.assert_(check_expected(result, "Generating LALR tables\n" )) def test_yacc_sr(self): run_import("yacc_sr") result = sys.stderr.getvalue() self.assert_(check_expected(result, "Generating LALR tables\n" "20 shift/reduce conflicts\n" )) def test_yacc_term1(self): self.assertRaises(ply.yacc.YaccError,run_import,"yacc_term1") result = sys.stderr.getvalue() self.assert_(check_expected(result, "yacc_term1.py:24: Illegal rule name 'NUMBER'. Already defined as a token\n" )) def test_yacc_unused(self): self.assertRaises(ply.yacc.YaccError,run_import,"yacc_unused") result = sys.stderr.getvalue() self.assert_(check_expected(result, "yacc_unused.py:62: Symbol 'COMMA' used, but not defined as a token or a rule\n" "Symbol 'COMMA' is unreachable\n" "Symbol 'exprlist' is unreachable\n" )) def test_yacc_unused_rule(self): run_import("yacc_unused_rule") result = sys.stderr.getvalue() self.assert_(check_expected(result, "yacc_unused_rule.py:62: Rule 'integer' defined, but not used\n" "There is 1 unused rule\n" "Symbol 'integer' is unreachable\n" "Generating LALR tables\n" )) def test_yacc_uprec(self): self.assertRaises(ply.yacc.YaccError,run_import,"yacc_uprec") result = sys.stderr.getvalue() print repr(result) self.assert_(check_expected(result, "yacc_uprec.py:37: Nothing known about the precedence of 'UMINUS'\n" )) def test_yacc_uprec2(self): self.assertRaises(ply.yacc.YaccError,run_import,"yacc_uprec2") result = sys.stderr.getvalue() self.assert_(check_expected(result, "yacc_uprec2.py:37: Syntax error. Nothing follows %prec\n" )) def test_yacc_prec1(self): self.assertRaises(ply.yacc.YaccError,run_import,"yacc_prec1") result = sys.stderr.getvalue() self.assert_(check_expected(result, "Precedence rule 'left' defined for unknown symbol '+'\n" "Precedence rule 'left' defined for unknown symbol '*'\n" "Precedence rule 'left' defined for unknown symbol '-'\n" "Precedence rule 'left' defined for unknown symbol '/'\n" )) unittest.main() ./CBFlib-0.9.2.2/ply-3.2/test/testlex.py0000755000076500007650000005361111603702121015731 0ustar yayayaya# testlex.py import unittest try: import StringIO except ImportError: import io as StringIO import sys sys.path.insert(0,"..") sys.tracebacklimit = 0 import ply.lex def check_expected(result,expected): if sys.version_info[0] >= 3: if isinstance(result,str): result = result.encode('ascii') if isinstance(expected,str): expected = expected.encode('ascii') resultlines = result.splitlines() expectedlines = expected.splitlines() if len(resultlines) != len(expectedlines): return False for rline,eline in zip(resultlines,expectedlines): if not rline.endswith(eline): return False return True def run_import(module): code = "import "+module exec(code) del sys.modules[module] # Tests related to errors and warnings when building lexers class LexErrorWarningTests(unittest.TestCase): def setUp(self): sys.stderr = StringIO.StringIO() sys.stdout = StringIO.StringIO() def tearDown(self): sys.stderr = sys.__stderr__ sys.stdout = sys.__stdout__ def test_lex_doc1(self): self.assertRaises(SyntaxError,run_import,"lex_doc1") result = sys.stderr.getvalue() self.assert_(check_expected(result, "lex_doc1.py:18: No regular expression defined for rule 't_NUMBER'\n")) def test_lex_dup1(self): self.assertRaises(SyntaxError,run_import,"lex_dup1") result = sys.stderr.getvalue() self.assert_(check_expected(result, "lex_dup1.py:20: Rule t_NUMBER redefined. Previously defined on line 18\n" )) def test_lex_dup2(self): self.assertRaises(SyntaxError,run_import,"lex_dup2") result = sys.stderr.getvalue() self.assert_(check_expected(result, "lex_dup2.py:22: Rule t_NUMBER redefined. Previously defined on line 18\n" )) def test_lex_dup3(self): self.assertRaises(SyntaxError,run_import,"lex_dup3") result = sys.stderr.getvalue() self.assert_(check_expected(result, "lex_dup3.py:20: Rule t_NUMBER redefined. Previously defined on line 18\n" )) def test_lex_empty(self): self.assertRaises(SyntaxError,run_import,"lex_empty") result = sys.stderr.getvalue() self.assert_(check_expected(result, "No rules of the form t_rulename are defined\n" "No rules defined for state 'INITIAL'\n")) def test_lex_error1(self): run_import("lex_error1") result = sys.stderr.getvalue() self.assert_(check_expected(result, "No t_error rule is defined\n")) def test_lex_error2(self): self.assertRaises(SyntaxError,run_import,"lex_error2") result = sys.stderr.getvalue() self.assert_(check_expected(result, "Rule 't_error' must be defined as a function\n") ) def test_lex_error3(self): self.assertRaises(SyntaxError,run_import,"lex_error3") result = sys.stderr.getvalue() self.assert_(check_expected(result, "lex_error3.py:20: Rule 't_error' requires an argument\n")) def test_lex_error4(self): self.assertRaises(SyntaxError,run_import,"lex_error4") result = sys.stderr.getvalue() self.assert_(check_expected(result, "lex_error4.py:20: Rule 't_error' has too many arguments\n")) def test_lex_ignore(self): self.assertRaises(SyntaxError,run_import,"lex_ignore") result = sys.stderr.getvalue() self.assert_(check_expected(result, "lex_ignore.py:20: Rule 't_ignore' must be defined as a string\n")) def test_lex_ignore2(self): run_import("lex_ignore2") result = sys.stderr.getvalue() self.assert_(check_expected(result, "t_ignore contains a literal backslash '\\'\n")) def test_lex_re1(self): self.assertRaises(SyntaxError,run_import,"lex_re1") result = sys.stderr.getvalue() self.assert_(check_expected(result, "Invalid regular expression for rule 't_NUMBER'. unbalanced parenthesis\n")) def test_lex_re2(self): self.assertRaises(SyntaxError,run_import,"lex_re2") result = sys.stderr.getvalue() self.assert_(check_expected(result, "Regular expression for rule 't_PLUS' matches empty string\n")) def test_lex_re3(self): self.assertRaises(SyntaxError,run_import,"lex_re3") result = sys.stderr.getvalue() self.assert_(check_expected(result, "Invalid regular expression for rule 't_POUND'. unbalanced parenthesis\n" "Make sure '#' in rule 't_POUND' is escaped with '\\#'\n")) def test_lex_rule1(self): self.assertRaises(SyntaxError,run_import,"lex_rule1") result = sys.stderr.getvalue() self.assert_(check_expected(result, "t_NUMBER not defined as a function or string\n")) def test_lex_rule2(self): self.assertRaises(SyntaxError,run_import,"lex_rule2") result = sys.stderr.getvalue() self.assert_(check_expected(result, "lex_rule2.py:18: Rule 't_NUMBER' requires an argument\n")) def test_lex_rule3(self): self.assertRaises(SyntaxError,run_import,"lex_rule3") result = sys.stderr.getvalue() self.assert_(check_expected(result, "lex_rule3.py:18: Rule 't_NUMBER' has too many arguments\n")) def test_lex_state1(self): self.assertRaises(SyntaxError,run_import,"lex_state1") result = sys.stderr.getvalue() self.assert_(check_expected(result, "states must be defined as a tuple or list\n")) def test_lex_state2(self): self.assertRaises(SyntaxError,run_import,"lex_state2") result = sys.stderr.getvalue() self.assert_(check_expected(result, "Invalid state specifier 'comment'. Must be a tuple (statename,'exclusive|inclusive')\n" "Invalid state specifier 'example'. Must be a tuple (statename,'exclusive|inclusive')\n")) def test_lex_state3(self): self.assertRaises(SyntaxError,run_import,"lex_state3") result = sys.stderr.getvalue() self.assert_(check_expected(result, "State name 1 must be a string\n" "No rules defined for state 'example'\n")) def test_lex_state4(self): self.assertRaises(SyntaxError,run_import,"lex_state4") result = sys.stderr.getvalue() self.assert_(check_expected(result, "State type for state comment must be 'inclusive' or 'exclusive'\n")) def test_lex_state5(self): self.assertRaises(SyntaxError,run_import,"lex_state5") result = sys.stderr.getvalue() self.assert_(check_expected(result, "State 'comment' already defined\n")) def test_lex_state_noerror(self): run_import("lex_state_noerror") result = sys.stderr.getvalue() self.assert_(check_expected(result, "No error rule is defined for exclusive state 'comment'\n")) def test_lex_state_norule(self): self.assertRaises(SyntaxError,run_import,"lex_state_norule") result = sys.stderr.getvalue() self.assert_(check_expected(result, "No rules defined for state 'example'\n")) def test_lex_token1(self): self.assertRaises(SyntaxError,run_import,"lex_token1") result = sys.stderr.getvalue() self.assert_(check_expected(result, "No token list is defined\n" "Rule 't_NUMBER' defined for an unspecified token NUMBER\n" "Rule 't_PLUS' defined for an unspecified token PLUS\n" "Rule 't_MINUS' defined for an unspecified token MINUS\n" )) def test_lex_token2(self): self.assertRaises(SyntaxError,run_import,"lex_token2") result = sys.stderr.getvalue() self.assert_(check_expected(result, "tokens must be a list or tuple\n" "Rule 't_NUMBER' defined for an unspecified token NUMBER\n" "Rule 't_PLUS' defined for an unspecified token PLUS\n" "Rule 't_MINUS' defined for an unspecified token MINUS\n" )) def test_lex_token3(self): self.assertRaises(SyntaxError,run_import,"lex_token3") result = sys.stderr.getvalue() self.assert_(check_expected(result, "Rule 't_MINUS' defined for an unspecified token MINUS\n")) def test_lex_token4(self): self.assertRaises(SyntaxError,run_import,"lex_token4") result = sys.stderr.getvalue() self.assert_(check_expected(result, "Bad token name '-'\n")) def test_lex_token5(self): try: run_import("lex_token5") except ply.lex.LexError: e = sys.exc_info()[1] self.assert_(check_expected(str(e),"lex_token5.py:19: Rule 't_NUMBER' returned an unknown token type 'NUM'")) def test_lex_token_dup(self): run_import("lex_token_dup") result = sys.stderr.getvalue() self.assert_(check_expected(result, "Token 'MINUS' multiply defined\n")) def test_lex_literal1(self): self.assertRaises(SyntaxError,run_import,"lex_literal1") result = sys.stderr.getvalue() self.assert_(check_expected(result, "Invalid literal '**'. Must be a single character\n")) def test_lex_literal2(self): self.assertRaises(SyntaxError,run_import,"lex_literal2") result = sys.stderr.getvalue() self.assert_(check_expected(result, "Invalid literals specification. literals must be a sequence of characters\n")) import os import subprocess import shutil # Tests related to various build options associated with lexers class LexBuildOptionTests(unittest.TestCase): def setUp(self): sys.stderr = StringIO.StringIO() sys.stdout = StringIO.StringIO() def tearDown(self): sys.stderr = sys.__stderr__ sys.stdout = sys.__stdout__ try: shutil.rmtree("lexdir") except OSError: pass def test_lex_module(self): run_import("lex_module") result = sys.stdout.getvalue() self.assert_(check_expected(result, "(NUMBER,3,1,0)\n" "(PLUS,'+',1,1)\n" "(NUMBER,4,1,2)\n")) def test_lex_object(self): run_import("lex_object") result = sys.stdout.getvalue() self.assert_(check_expected(result, "(NUMBER,3,1,0)\n" "(PLUS,'+',1,1)\n" "(NUMBER,4,1,2)\n")) def test_lex_closure(self): run_import("lex_closure") result = sys.stdout.getvalue() self.assert_(check_expected(result, "(NUMBER,3,1,0)\n" "(PLUS,'+',1,1)\n" "(NUMBER,4,1,2)\n")) def test_lex_optimize(self): try: os.remove("lextab.py") except OSError: pass try: os.remove("lextab.pyc") except OSError: pass try: os.remove("lextab.pyo") except OSError: pass run_import("lex_optimize") result = sys.stdout.getvalue() self.assert_(check_expected(result, "(NUMBER,3,1,0)\n" "(PLUS,'+',1,1)\n" "(NUMBER,4,1,2)\n")) self.assert_(os.path.exists("lextab.py")) p = subprocess.Popen([sys.executable,'-O','lex_optimize.py'], stdout=subprocess.PIPE) result = p.stdout.read() self.assert_(check_expected(result, "(NUMBER,3,1,0)\n" "(PLUS,'+',1,1)\n" "(NUMBER,4,1,2)\n")) self.assert_(os.path.exists("lextab.pyo")) os.remove("lextab.pyo") p = subprocess.Popen([sys.executable,'-OO','lex_optimize.py'], stdout=subprocess.PIPE) result = p.stdout.read() self.assert_(check_expected(result, "(NUMBER,3,1,0)\n" "(PLUS,'+',1,1)\n" "(NUMBER,4,1,2)\n")) self.assert_(os.path.exists("lextab.pyo")) try: os.remove("lextab.py") except OSError: pass try: os.remove("lextab.pyc") except OSError: pass try: os.remove("lextab.pyo") except OSError: pass def test_lex_optimize2(self): try: os.remove("opt2tab.py") except OSError: pass try: os.remove("opt2tab.pyc") except OSError: pass try: os.remove("opt2tab.pyo") except OSError: pass run_import("lex_optimize2") result = sys.stdout.getvalue() self.assert_(check_expected(result, "(NUMBER,3,1,0)\n" "(PLUS,'+',1,1)\n" "(NUMBER,4,1,2)\n")) self.assert_(os.path.exists("opt2tab.py")) p = subprocess.Popen([sys.executable,'-O','lex_optimize2.py'], stdout=subprocess.PIPE) result = p.stdout.read() self.assert_(check_expected(result, "(NUMBER,3,1,0)\n" "(PLUS,'+',1,1)\n" "(NUMBER,4,1,2)\n")) self.assert_(os.path.exists("opt2tab.pyo")) os.remove("opt2tab.pyo") p = subprocess.Popen([sys.executable,'-OO','lex_optimize2.py'], stdout=subprocess.PIPE) result = p.stdout.read() self.assert_(check_expected(result, "(NUMBER,3,1,0)\n" "(PLUS,'+',1,1)\n" "(NUMBER,4,1,2)\n")) self.assert_(os.path.exists("opt2tab.pyo")) try: os.remove("opt2tab.py") except OSError: pass try: os.remove("opt2tab.pyc") except OSError: pass try: os.remove("opt2tab.pyo") except OSError: pass def test_lex_optimize3(self): try: shutil.rmtree("lexdir") except OSError: pass os.mkdir("lexdir") os.mkdir("lexdir/sub") open("lexdir/__init__.py","w").write("") open("lexdir/sub/__init__.py","w").write("") run_import("lex_optimize3") result = sys.stdout.getvalue() self.assert_(check_expected(result, "(NUMBER,3,1,0)\n" "(PLUS,'+',1,1)\n" "(NUMBER,4,1,2)\n")) self.assert_(os.path.exists("lexdir/sub/calctab.py")) p = subprocess.Popen([sys.executable,'-O','lex_optimize3.py'], stdout=subprocess.PIPE) result = p.stdout.read() self.assert_(check_expected(result, "(NUMBER,3,1,0)\n" "(PLUS,'+',1,1)\n" "(NUMBER,4,1,2)\n")) self.assert_(os.path.exists("lexdir/sub/calctab.pyo")) os.remove("lexdir/sub/calctab.pyo") p = subprocess.Popen([sys.executable,'-OO','lex_optimize3.py'], stdout=subprocess.PIPE) result = p.stdout.read() self.assert_(check_expected(result, "(NUMBER,3,1,0)\n" "(PLUS,'+',1,1)\n" "(NUMBER,4,1,2)\n")) self.assert_(os.path.exists("lexdir/sub/calctab.pyo")) try: shutil.rmtree("lexdir") except OSError: pass def test_lex_opt_alias(self): try: os.remove("aliastab.py") except OSError: pass try: os.remove("aliastab.pyc") except OSError: pass try: os.remove("aliastab.pyo") except OSError: pass run_import("lex_opt_alias") result = sys.stdout.getvalue() self.assert_(check_expected(result, "(NUMBER,3,1,0)\n" "(+,'+',1,1)\n" "(NUMBER,4,1,2)\n")) self.assert_(os.path.exists("aliastab.py")) p = subprocess.Popen([sys.executable,'-O','lex_opt_alias.py'], stdout=subprocess.PIPE) result = p.stdout.read() self.assert_(check_expected(result, "(NUMBER,3,1,0)\n" "(+,'+',1,1)\n" "(NUMBER,4,1,2)\n")) self.assert_(os.path.exists("aliastab.pyo")) os.remove("aliastab.pyo") p = subprocess.Popen([sys.executable,'-OO','lex_opt_alias.py'], stdout=subprocess.PIPE) result = p.stdout.read() self.assert_(check_expected(result, "(NUMBER,3,1,0)\n" "(+,'+',1,1)\n" "(NUMBER,4,1,2)\n")) self.assert_(os.path.exists("aliastab.pyo")) try: os.remove("aliastab.py") except OSError: pass try: os.remove("aliastab.pyc") except OSError: pass try: os.remove("aliastab.pyo") except OSError: pass def test_lex_many_tokens(self): try: os.remove("manytab.py") except OSError: pass try: os.remove("manytab.pyc") except OSError: pass try: os.remove("manytab.pyo") except OSError: pass run_import("lex_many_tokens") result = sys.stdout.getvalue() self.assert_(check_expected(result, "(TOK34,'TOK34:',1,0)\n" "(TOK143,'TOK143:',1,7)\n" "(TOK269,'TOK269:',1,15)\n" "(TOK372,'TOK372:',1,23)\n" "(TOK452,'TOK452:',1,31)\n" "(TOK561,'TOK561:',1,39)\n" "(TOK999,'TOK999:',1,47)\n" )) self.assert_(os.path.exists("manytab.py")) p = subprocess.Popen([sys.executable,'-O','lex_many_tokens.py'], stdout=subprocess.PIPE) result = p.stdout.read() self.assert_(check_expected(result, "(TOK34,'TOK34:',1,0)\n" "(TOK143,'TOK143:',1,7)\n" "(TOK269,'TOK269:',1,15)\n" "(TOK372,'TOK372:',1,23)\n" "(TOK452,'TOK452:',1,31)\n" "(TOK561,'TOK561:',1,39)\n" "(TOK999,'TOK999:',1,47)\n" )) self.assert_(os.path.exists("manytab.pyo")) os.remove("manytab.pyo") try: os.remove("manytab.py") except OSError: pass try: os.remove("manytab.pyc") except OSError: pass try: os.remove("manytab.pyo") except OSError: pass # Tests related to run-time behavior of lexers class LexRunTests(unittest.TestCase): def setUp(self): sys.stderr = StringIO.StringIO() sys.stdout = StringIO.StringIO() def tearDown(self): sys.stderr = sys.__stderr__ sys.stdout = sys.__stdout__ def test_lex_hedit(self): run_import("lex_hedit") result = sys.stdout.getvalue() self.assert_(check_expected(result, "(H_EDIT_DESCRIPTOR,'abc',1,0)\n" "(H_EDIT_DESCRIPTOR,'abcdefghij',1,6)\n" "(H_EDIT_DESCRIPTOR,'xy',1,20)\n")) def test_lex_state_try(self): run_import("lex_state_try") result = sys.stdout.getvalue() self.assert_(check_expected(result, "(NUMBER,'3',1,0)\n" "(PLUS,'+',1,2)\n" "(NUMBER,'4',1,4)\n" "Entering comment state\n" "comment body LexToken(body_part,'This is a comment */',1,9)\n" "(PLUS,'+',1,30)\n" "(NUMBER,'10',1,32)\n" )) unittest.main() ./CBFlib-0.9.2.2/ply-3.2/test/lex_many_tokens.py0000644000076500007650000000107211603702121017427 0ustar yayayaya# lex_many_tokens.py # # Test lex's ability to handle a large number of tokens (beyond the # 100-group limit of the re module) import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = ["TOK%d" % i for i in range(1000)] for tok in tokens: if sys.version_info[0] < 3: exec("t_%s = '%s:'" % (tok,tok)) else: exec("t_%s = '%s:'" % (tok,tok), globals()) t_ignore = " \t" def t_error(t): pass lex.lex(optimize=1,lextab="manytab") lex.runmain(data="TOK34: TOK143: TOK269: TOK372: TOK452: TOK561: TOK999:") ./CBFlib-0.9.2.2/ply-3.2/test/yacc_badargs.py0000644000076500007650000000277011603702121016640 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_badargs.py # # Rules with wrong # args # ----------------------------------------------------------------------------- import sys sys.tracebacklimit = 0 sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(t,s): 'statement : NAME EQUALS expression' names[t[1]] = t[3] def p_statement_expr(): 'statement : expression' print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_error(t): print("Syntax error at '%s'" % t.value) yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/lex_ignore2.py0000644000076500007650000000046211603702121016447 0ustar yayayaya# lex_ignore2.py # # ignore declaration as a raw string import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "NUMBER", ] t_PLUS = r'\+' t_MINUS = r'-' t_NUMBER = r'\d+' t_ignore = r' \t' def t_error(t): pass lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/yacc_badprec2.py0000644000076500007650000000273511603702121016720 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_badprec2.py # # Bad precedence # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules precedence = ( 42, ('left','TIMES','DIVIDE'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(t): 'statement : NAME EQUALS expression' names[t[1]] = t[3] def p_statement_expr(t): 'statement : expression' print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_error(t): print("Syntax error at '%s'" % t.value) yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/yacc_badprec3.py0000644000076500007650000000277211603702121016722 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_badprec3.py # # Bad precedence # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE','MINUS'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(t): 'statement : NAME EQUALS expression' names[t[1]] = t[3] def p_statement_expr(t): 'statement : expression' print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[3] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_error(t): print("Syntax error at '%s'" % t.value) yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/yacc_noerror.py0000644000076500007650000000270111603702121016715 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_noerror.py # # No p_error() rule defined. # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(t): 'statement : NAME EQUALS expression' names[t[1]] = t[3] def p_statement_expr(t): 'statement : expression' print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/lex_hedit.py0000644000076500007650000000216511603702121016201 0ustar yayayaya# ----------------------------------------------------------------------------- # hedit.py # # Paring of Fortran H Edit descriptions (Contributed by Pearu Peterson) # # These tokens can't be easily tokenized because they are of the following # form: # # nHc1...cn # # where n is a positive integer and c1 ... cn are characters. # # This example shows how to modify the state of the lexer to parse # such tokens # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = ( 'H_EDIT_DESCRIPTOR', ) # Tokens t_ignore = " \t\n" def t_H_EDIT_DESCRIPTOR(t): r"\d+H.*" # This grabs all of the remaining text i = t.value.index('H') n = eval(t.value[:i]) # Adjust the tokenizing position t.lexer.lexpos -= len(t.value) - (i+1+n) t.value = t.value[i+1:i+1+n] return t def t_error(t): print("Illegal character '%s'" % t.value[0]) t.lexer.skip(1) # Build the lexer lex.lex() lex.runmain(data="3Habc 10Habcdefghij 2Hxy") ./CBFlib-0.9.2.2/ply-3.2/test/yacc_uprec.py0000644000076500007650000000263411603702121016352 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_uprec.py # # A grammar with a bad %prec specifier # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules # dictionary of names names = { } def p_statement_assign(t): 'statement : NAME EQUALS expression' names[t[1]] = t[3] def p_statement_expr(t): 'statement : expression' print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_error(t): print("Syntax error at '%s'" % t.value) yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/yacc_nested.py0000644000076500007650000000102111603702121016503 0ustar yayayayaimport sys if ".." not in sys.path: sys.path.insert(0,"..") from ply import lex, yacc t_A = 'A' t_B = 'B' t_C = 'C' tokens = ('A', 'B', 'C') the_lexer = lex.lex() def t_error(t): pass def p_error(p): pass def p_start(t): '''start : A nest C''' pass def p_nest(t): '''nest : B''' print(t[-1]) the_parser = yacc.yacc(debug = False, write_tables = False) the_parser.parse('ABC', the_lexer) the_parser.parse('ABC', the_lexer, tracking=True) the_parser.parse('ABC', the_lexer, tracking=True, debug=1) ./CBFlib-0.9.2.2/ply-3.2/test/lex_optimize.py0000644000076500007650000000170411603702121016742 0ustar yayayaya# ----------------------------------------------------------------------------- # lex_optimize.py # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = ( 'NAME','NUMBER', 'PLUS','MINUS','TIMES','DIVIDE','EQUALS', 'LPAREN','RPAREN', ) # Tokens t_PLUS = r'\+' t_MINUS = r'-' t_TIMES = r'\*' t_DIVIDE = r'/' t_EQUALS = r'=' t_LPAREN = r'\(' t_RPAREN = r'\)' t_NAME = r'[a-zA-Z_][a-zA-Z0-9_]*' def t_NUMBER(t): r'\d+' try: t.value = int(t.value) except ValueError: print("Integer value too large %s" % t.value) t.value = 0 return t t_ignore = " \t" def t_newline(t): r'\n+' t.lineno += t.value.count("\n") def t_error(t): print("Illegal character '%s'" % t.value[0]) t.lexer.skip(1) # Build the lexer lex.lex(optimize=1) lex.runmain(data="3+4") ./CBFlib-0.9.2.2/ply-3.2/test/lex_optimize2.py0000644000076500007650000000172611603702121017030 0ustar yayayaya# ----------------------------------------------------------------------------- # lex_optimize2.py # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = ( 'NAME','NUMBER', 'PLUS','MINUS','TIMES','DIVIDE','EQUALS', 'LPAREN','RPAREN', ) # Tokens t_PLUS = r'\+' t_MINUS = r'-' t_TIMES = r'\*' t_DIVIDE = r'/' t_EQUALS = r'=' t_LPAREN = r'\(' t_RPAREN = r'\)' t_NAME = r'[a-zA-Z_][a-zA-Z0-9_]*' def t_NUMBER(t): r'\d+' try: t.value = int(t.value) except ValueError: print("Integer value too large %s" % t.value) t.value = 0 return t t_ignore = " \t" def t_newline(t): r'\n+' t.lineno += t.value.count("\n") def t_error(t): print("Illegal character '%s'" % t.value[0]) t.lexer.skip(1) # Build the lexer lex.lex(optimize=1,lextab="opt2tab") lex.runmain(data="3+4") ./CBFlib-0.9.2.2/ply-3.2/test/lex_optimize3.py0000644000076500007650000000204611603702121017025 0ustar yayayaya# ----------------------------------------------------------------------------- # lex_optimize3.py # # Writes table in a subdirectory structure. # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = ( 'NAME','NUMBER', 'PLUS','MINUS','TIMES','DIVIDE','EQUALS', 'LPAREN','RPAREN', ) # Tokens t_PLUS = r'\+' t_MINUS = r'-' t_TIMES = r'\*' t_DIVIDE = r'/' t_EQUALS = r'=' t_LPAREN = r'\(' t_RPAREN = r'\)' t_NAME = r'[a-zA-Z_][a-zA-Z0-9_]*' def t_NUMBER(t): r'\d+' try: t.value = int(t.value) except ValueError: print("Integer value too large %s" % t.value) t.value = 0 return t t_ignore = " \t" def t_newline(t): r'\n+' t.lineno += t.value.count("\n") def t_error(t): print("Illegal character '%s'" % t.value[0]) t.lexer.skip(1) # Build the lexer lex.lex(optimize=1,lextab="lexdir.sub.calctab",outputdir="lexdir/sub") lex.runmain(data="3+4") ./CBFlib-0.9.2.2/ply-3.2/test/yacc_prec1.py0000644000076500007650000000302411603702121016240 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_prec1.py # # Tests case where precedence specifier doesn't match up to terminals # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules precedence = ( ('left','+','-'), ('left','*','/'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(t): 'statement : NAME EQUALS expression' names[t[1]] = t[3] def p_statement_expr(t): 'statement : expression' print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_error(t): print("Syntax error at '%s'" % t.value) yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/yacc_badprec.py0000644000076500007650000000264611603702121016637 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_badprec.py # # Bad precedence specifier # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules precedence = "blah" # dictionary of names names = { } def p_statement_assign(t): 'statement : NAME EQUALS expression' names[t[1]] = t[3] def p_statement_expr(t): 'statement : expression' print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_error(t): print("Syntax error at '%s'" % t.value) yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/lex_token1.py0000644000076500007650000000034511603702121016303 0ustar yayayaya# lex_token1.py # # Tests for absence of tokens variable import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex t_PLUS = r'\+' t_MINUS = r'-' t_NUMBER = r'\d+' def t_error(t): pass lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/lex_token2.py0000644000076500007650000000037611603702121016310 0ustar yayayaya# lex_token2.py # # Tests for tokens of wrong type import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = "PLUS MINUS NUMBER" t_PLUS = r'\+' t_MINUS = r'-' t_NUMBER = r'\d+' def t_error(t): pass lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/lex_token3.py0000644000076500007650000000044611603702121016307 0ustar yayayaya# lex_token3.py # # tokens is right type, but is missing a token for one rule import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "NUMBER", ] t_PLUS = r'\+' t_MINUS = r'-' t_NUMBER = r'\d+' def t_error(t): pass lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/lex_token4.py0000644000076500007650000000042111603702121016301 0ustar yayayaya# lex_token4.py # # Bad token name import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "-", "NUMBER", ] t_PLUS = r'\+' t_MINUS = r'-' t_NUMBER = r'\d+' def t_error(t): pass lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/lex_token5.py0000644000076500007650000000053611603702121016311 0ustar yayayaya# lex_token5.py # # Return a bad token name import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "NUMBER", ] t_PLUS = r'\+' t_MINUS = r'-' def t_NUMBER(t): r'\d+' t.type = "NUM" return t def t_error(t): pass lex.lex() lex.input("1234") t = lex.token() ./CBFlib-0.9.2.2/ply-3.2/test/lex_state_try.py0000644000076500007650000000127411603702121017122 0ustar yayayaya# lex_state_try.py # # Declaration of a state for which no rules are defined import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "NUMBER", ] states = (('comment', 'exclusive'),) t_PLUS = r'\+' t_MINUS = r'-' t_NUMBER = r'\d+' t_ignore = " \t" # Comments def t_comment(t): r'/\*' t.lexer.begin('comment') print("Entering comment state") def t_comment_body_part(t): r'(.|\n)*\*/' print("comment body %s" % t) t.lexer.begin('INITIAL') def t_error(t): pass t_comment_error = t_error t_comment_ignore = t_ignore lex.lex() data = "3 + 4 /* This is a comment */ + 10" lex.runmain(data=data) ./CBFlib-0.9.2.2/ply-3.2/test/yacc_badid.py0000644000076500007650000000315111603702121016272 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_badid.py # # Attempt to define a rule with a bad-identifier name # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(t): 'statement : NAME EQUALS expression' names[t[1]] = t[3] def p_statement_expr(t): 'statement : expression' print(t[1]) def p_statement_expr2(t): 'statement : bad&rule' pass def p_badrule(t): 'bad&rule : expression' pass def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_error(t): pass yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/yacc_literal.py0000644000076500007650000000303611603702121016665 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_literal.py # # Grammar with bad literal characters # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules precedence = ( ('left','+','-'), ('left','*','/'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(t): 'statement : NAME EQUALS expression' names[t[1]] = t[3] def p_statement_expr(t): 'statement : expression' print(t[1]) def p_expression_binop(t): '''expression : expression '+' expression | expression '-' expression | expression '*' expression | expression '/' expression | expression '**' expression ''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_error(t): print("Syntax error at '%s'" % t.value) yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/lex_literal1.py0000644000076500007650000000042011603702121016611 0ustar yayayaya# lex_literal1.py # # Bad literal specification import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "NUMBER", ] literals = ["+","-","**"] def t_NUMBER(t): r'\d+' return t def t_error(t): pass lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/lex_literal2.py0000644000076500007650000000040411603702121016614 0ustar yayayaya# lex_literal2.py # # Bad literal specification import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "NUMBER", ] literals = 23 def t_NUMBER(t): r'\d+' return t def t_error(t): pass lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/lex_module.py0000644000076500007650000000027111603702121016365 0ustar yayayaya# lex_module.py # import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex import lex_module_import lex.lex(module=lex_module_import) lex.runmain(data="3+4") ./CBFlib-0.9.2.2/ply-3.2/test/yacc_missing1.py0000644000076500007650000000300311603702121016755 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_missing1.py # # Grammar with a missing rule # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(t): 'statement : location EQUALS expression' names[t[1]] = t[3] def p_statement_expr(t): 'statement : expression' print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_error(t): print("Syntax error at '%s'" % t.value) yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/lex_object.py0000644000076500007650000000216511603702121016352 0ustar yayayaya# ----------------------------------------------------------------------------- # lex_object.py # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex class CalcLexer: tokens = ( 'NAME','NUMBER', 'PLUS','MINUS','TIMES','DIVIDE','EQUALS', 'LPAREN','RPAREN', ) # Tokens t_PLUS = r'\+' t_MINUS = r'-' t_TIMES = r'\*' t_DIVIDE = r'/' t_EQUALS = r'=' t_LPAREN = r'\(' t_RPAREN = r'\)' t_NAME = r'[a-zA-Z_][a-zA-Z0-9_]*' def t_NUMBER(self,t): r'\d+' try: t.value = int(t.value) except ValueError: print("Integer value too large %s" % t.value) t.value = 0 return t t_ignore = " \t" def t_newline(self,t): r'\n+' t.lineno += t.value.count("\n") def t_error(self,t): print("Illegal character '%s'" % t.value[0]) t.lexer.skip(1) calc = CalcLexer() # Build the lexer lex.lex(object=calc) lex.runmain(data="3+4") ./CBFlib-0.9.2.2/ply-3.2/test/yacc_rr_unused.py0000644000076500007650000000105011603702121017231 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_rr_unused.py # # A grammar with reduce/reduce conflicts and a rule that never # gets reduced. # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc tokens = ('A', 'B', 'C') def p_grammar(p): ''' rule1 : rule2 B | rule2 C rule2 : rule3 B | rule4 | rule5 rule3 : A rule4 : A rule5 : A ''' yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/lex_doc1.py0000644000076500007650000000043411603702121015727 0ustar yayayaya# lex_doc1.py # # Missing documentation string import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "NUMBER", ] t_PLUS = r'\+' t_MINUS = r'-' def t_NUMBER(t): pass def t_error(t): pass lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/yacc_notfunc.py0000644000076500007650000000270411603702121016706 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_notfunc.py # # p_rule not defined as a function # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE'), ('right','UMINUS'), ) # dictionary of names names = { } p_statement_assign = "Blah" def p_statement_expr(t): 'statement : expression' print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_error(t): print("Syntax error at '%s'" % t.value) yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/yacc_unused_rule.py0000644000076500007650000000307411603702121017565 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_unused_rule.py # # Grammar with an unused rule # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(t): 'statement : NAME EQUALS expression' names[t[1]] = t[3] def p_statement_expr(t): 'statement : expression' print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_integer(t): 'integer : NUMBER' t[0] = t[1] def p_error(t): print("Syntax error at '%s'" % t.value) yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/lex_opt_alias.py0000644000076500007650000000211311603702121017050 0ustar yayayaya# ----------------------------------------------------------------------------- # lex_opt_alias.py # # Tests ability to match up functions with states, aliases, and # lexing tables. # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") tokens = ( 'NAME','NUMBER', ) states = (('instdef','inclusive'),('spam','exclusive')) literals = ['=','+','-','*','/', '(',')'] # Tokens def t_instdef_spam_BITS(t): r'[01-]+' return t t_NAME = r'[a-zA-Z_][a-zA-Z0-9_]*' def NUMBER(t): r'\d+' try: t.value = int(t.value) except ValueError: print("Integer value too large %s" % t.value) t.value = 0 return t t_ANY_NUMBER = NUMBER t_ignore = " \t" t_spam_ignore = t_ignore def t_newline(t): r'\n+' t.lexer.lineno += t.value.count("\n") def t_error(t): print("Illegal character '%s'" % t.value[0]) t.lexer.skip(1) t_spam_error = t_error # Build the lexer import ply.lex as lex lex.lex(optimize=1,lextab="aliastab") lex.runmain(data="3+4") ./CBFlib-0.9.2.2/ply-3.2/test/cleanup.sh0000755000076500007650000000005611603702121015645 0ustar yayayaya#!/bin/sh rm -f *~ *.pyc *.pyo *.dif *.out ./CBFlib-0.9.2.2/ply-3.2/test/lex_state_norule.py0000644000076500007650000000112711603702121017605 0ustar yayayaya# lex_state_norule.py # # Declaration of a state for which no rules are defined import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "NUMBER", ] states = (('comment', 'exclusive'), ('example', 'exclusive')) t_PLUS = r'\+' t_MINUS = r'-' t_NUMBER = r'\d+' # Comments def t_comment(t): r'/\*' t.lexer.begin('comment') print("Entering comment state") def t_comment_body_part(t): r'(.|\n)*\*/' print("comment body %s" % t) t.lexer.begin('INITIAL') def t_error(t): pass lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/yacc_dup.py0000644000076500007650000000274711603702121016031 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_dup.py # # Duplicated rule name # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement(t): 'statement : NAME EQUALS expression' names[t[1]] = t[3] def p_statement(t): 'statement : expression' print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_error(t): print("Syntax error at '%s'" % t.value) yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/lex_state1.py0000644000076500007650000000077511603702121016312 0ustar yayayaya# lex_state1.py # # Bad state declaration import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "NUMBER", ] states = 'comment' t_PLUS = r'\+' t_MINUS = r'-' t_NUMBER = r'\d+' # Comments def t_comment(t): r'/\*' t.lexer.begin('comment') print("Entering comment state") def t_comment_body_part(t): r'(.|\n)*\*/' print("comment body %s" % t) t.lexer.begin('INITIAL') def t_error(t): pass lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/lex_state2.py0000644000076500007650000000101111603702121016273 0ustar yayayaya# lex_state2.py # # Bad state declaration import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "NUMBER", ] states = ('comment','example') t_PLUS = r'\+' t_MINUS = r'-' t_NUMBER = r'\d+' # Comments def t_comment(t): r'/\*' t.lexer.begin('comment') print("Entering comment state") def t_comment_body_part(t): r'(.|\n)*\*/' print("comment body %s" % t) t.lexer.begin('INITIAL') def t_error(t): pass lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/yacc_nodoc.py0000644000076500007650000000274211603702121016336 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_nodoc.py # # Rule with a missing doc-string # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(t): 'statement : NAME EQUALS expression' names[t[1]] = t[3] def p_statement_expr(t): print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_error(t): print("Syntax error at '%s'" % t.value) yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/lex_state3.py0000644000076500007650000000107411603702121016305 0ustar yayayaya# lex_state3.py # # Bad state declaration import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "NUMBER", ] comment = 1 states = ((comment, 'inclusive'), ('example', 'exclusive')) t_PLUS = r'\+' t_MINUS = r'-' t_NUMBER = r'\d+' # Comments def t_comment(t): r'/\*' t.lexer.begin('comment') print("Entering comment state") def t_comment_body_part(t): r'(.|\n)*\*/' print("comment body %s" % t) t.lexer.begin('INITIAL') def t_error(t): pass lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/lex_state4.py0000644000076500007650000000101711603702121016303 0ustar yayayaya# lex_state4.py # # Bad state declaration import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "NUMBER", ] states = (('comment', 'exclsive'),) t_PLUS = r'\+' t_MINUS = r'-' t_NUMBER = r'\d+' # Comments def t_comment(t): r'/\*' t.lexer.begin('comment') print("Entering comment state") def t_comment_body_part(t): r'(.|\n)*\*/' print("comment body %s" % t) t.lexer.begin('INITIAL') def t_error(t): pass lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/lex_state5.py0000644000076500007650000000106111603702121016303 0ustar yayayaya# lex_state5.py # # Bad state declaration import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "NUMBER", ] states = (('comment', 'exclusive'), ('comment', 'exclusive')) t_PLUS = r'\+' t_MINUS = r'-' t_NUMBER = r'\d+' # Comments def t_comment(t): r'/\*' t.lexer.begin('comment') print("Entering comment state") def t_comment_body_part(t): r'(.|\n)*\*/' print("comment body %s" % t) t.lexer.begin('INITIAL') def t_error(t): pass lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/lex_state_noerror.py0000644000076500007650000000106511603702121017770 0ustar yayayaya# lex_state_noerror.py # # Declaration of a state for which no rules are defined import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "NUMBER", ] states = (('comment', 'exclusive'),) t_PLUS = r'\+' t_MINUS = r'-' t_NUMBER = r'\d+' # Comments def t_comment(t): r'/\*' t.lexer.begin('comment') print("Entering comment state") def t_comment_body_part(t): r'(.|\n)*\*/' print("comment body %s" % t) t.lexer.begin('INITIAL') def t_error(t): pass lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/lex_dup1.py0000644000076500007650000000044711603702121015756 0ustar yayayaya# lex_dup1.py # # Duplicated rule specifiers import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "NUMBER", ] t_PLUS = r'\+' t_MINUS = r'-' t_NUMBER = r'\d+' t_NUMBER = r'\d+' def t_error(t): pass lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/lex_dup2.py0000644000076500007650000000051511603702121015753 0ustar yayayaya# lex_dup2.py # # Duplicated rule specifiers import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "NUMBER", ] t_PLUS = r'\+' t_MINUS = r'-' def t_NUMBER(t): r'\d+' pass def t_NUMBER(t): r'\d+' pass def t_error(t): pass lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/lex_dup3.py0000644000076500007650000000047211603702121015756 0ustar yayayaya# lex_dup3.py # # Duplicated rule specifiers import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "NUMBER", ] t_PLUS = r'\+' t_MINUS = r'-' t_NUMBER = r'\d+' def t_NUMBER(t): r'\d+' pass def t_error(t): pass lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/yacc_uprec2.py0000644000076500007650000000262611603702121016435 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_uprec2.py # # A grammar with a bad %prec specifier # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules # dictionary of names names = { } def p_statement_assign(t): 'statement : NAME EQUALS expression' names[t[1]] = t[3] def p_statement_expr(t): 'statement : expression' print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_error(t): print("Syntax error at '%s'" % t.value) yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/yacc_inf.py0000644000076500007650000000237611603702121016013 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_inf.py # # Infinite recursion # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(t): 'statement : NAME EQUALS expression' names[t[1]] = t[3] def p_statement_expr(t): 'statement : expression' print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_error(t): print("Syntax error at '%s'" % t.value) yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/yacc_simple.py0000644000076500007650000000300611603702121016517 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_simple.py # # A simple, properly specifier grammar # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(t): 'statement : NAME EQUALS expression' names[t[1]] = t[3] def p_statement_expr(t): 'statement : expression' print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_error(t): print("Syntax error at '%s'" % t.value) yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/yacc_badrule.py0000644000076500007650000000276511603702121016657 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_badrule.py # # Syntax problems in the rule strings # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(t): 'statement NAME EQUALS expression' names[t[1]] = t[3] def p_statement_expr(t): 'statement' print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression: MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_error(t): print("Syntax error at '%s'" % t.value) yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/lex_rule1.py0000644000076500007650000000044611603702121016134 0ustar yayayaya# lex_rule1.py # # Rule function with incorrect number of arguments import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "NUMBER", ] t_PLUS = r'\+' t_MINUS = r'-' t_NUMBER = 1 def t_error(t): pass lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/lex_rule2.py0000644000076500007650000000050111603702121016125 0ustar yayayaya# lex_rule2.py # # Rule function with incorrect number of arguments import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "NUMBER", ] t_PLUS = r'\+' t_MINUS = r'-' def t_NUMBER(): r'\d+' return t def t_error(t): pass lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/lex_rule3.py0000644000076500007650000000050211603702121016127 0ustar yayayaya# lex_rule3.py # # Rule function with incorrect number of arguments import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "NUMBER", ] t_PLUS = r'\+' t_MINUS = r'-' def t_NUMBER(t,s): r'\d+' return t def t_error(t): pass lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/yacc_nop.py0000644000076500007650000000301411603702121016021 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_nop.py # # Possible grammar rule defined without p_ prefix # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(t): 'statement : NAME EQUALS expression' names[t[1]] = t[3] def statement_expr(t): 'statement : expression' print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_error(t): print("Syntax error at '%s'" % t.value) yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/lex_empty.py0000644000076500007650000000030011603702121016227 0ustar yayayaya# lex_empty.py # # No rules defined import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "NUMBER", ] lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/calclex.py0000644000076500007650000000163511603702121015650 0ustar yayayaya# ----------------------------------------------------------------------------- # calclex.py # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = ( 'NAME','NUMBER', 'PLUS','MINUS','TIMES','DIVIDE','EQUALS', 'LPAREN','RPAREN', ) # Tokens t_PLUS = r'\+' t_MINUS = r'-' t_TIMES = r'\*' t_DIVIDE = r'/' t_EQUALS = r'=' t_LPAREN = r'\(' t_RPAREN = r'\)' t_NAME = r'[a-zA-Z_][a-zA-Z0-9_]*' def t_NUMBER(t): r'\d+' try: t.value = int(t.value) except ValueError: print("Integer value too large %s" % t.value) t.value = 0 return t t_ignore = " \t" def t_newline(t): r'\n+' t.lineno += t.value.count("\n") def t_error(t): print("Illegal character '%s'" % t.value[0]) t.lexer.skip(1) # Build the lexer lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/lex_closure.py0000644000076500007650000000213711603702121016557 0ustar yayayaya# ----------------------------------------------------------------------------- # lex_closure.py # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = ( 'NAME','NUMBER', 'PLUS','MINUS','TIMES','DIVIDE','EQUALS', 'LPAREN','RPAREN', ) def make_calc(): # Tokens t_PLUS = r'\+' t_MINUS = r'-' t_TIMES = r'\*' t_DIVIDE = r'/' t_EQUALS = r'=' t_LPAREN = r'\(' t_RPAREN = r'\)' t_NAME = r'[a-zA-Z_][a-zA-Z0-9_]*' def t_NUMBER(t): r'\d+' try: t.value = int(t.value) except ValueError: print("Integer value too large %s" % t.value) t.value = 0 return t t_ignore = " \t" def t_newline(t): r'\n+' t.lineno += t.value.count("\n") def t_error(t): print("Illegal character '%s'" % t.value[0]) t.lexer.skip(1) # Build the lexer return lex.lex() make_calc() lex.runmain(data="3+4") ./CBFlib-0.9.2.2/ply-3.2/test/yacc_rr.py0000644000076500007650000000313711603702121015656 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_rr.py # # A grammar with a reduce/reduce conflict # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(t): 'statement : NAME EQUALS expression' names[t[1]] = t[3] def p_statement_assign_2(t): 'statement : NAME EQUALS NUMBER' names[t[1]] = t[3] def p_statement_expr(t): 'statement : expression' print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_error(t): print("Syntax error at '%s'" % t.value) yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/yacc_sr.py0000644000076500007650000000261511603702121015657 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_sr.py # # A grammar with shift-reduce conflicts # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules # dictionary of names names = { } def p_statement_assign(t): 'statement : NAME EQUALS expression' names[t[1]] = t[3] def p_statement_expr(t): 'statement : expression' print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_error(t): print("Syntax error at '%s'" % t.value) yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/lex_error1.py0000644000076500007650000000037011603702121016312 0ustar yayayaya# lex_error1.py # # Missing t_error() rule import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "NUMBER", ] t_PLUS = r'\+' t_MINUS = r'-' t_NUMBER = r'\d+' lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/lex_error2.py0000644000076500007650000000042411603702121016313 0ustar yayayaya# lex_error2.py # # t_error defined, but not function import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "NUMBER", ] t_PLUS = r'\+' t_MINUS = r'-' t_NUMBER = r'\d+' t_error = "foo" lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/lex_error3.py0000644000076500007650000000045511603702121016320 0ustar yayayaya# lex_error3.py # # t_error defined as function, but with wrong # args import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "NUMBER", ] t_PLUS = r'\+' t_MINUS = r'-' t_NUMBER = r'\d+' def t_error(): pass lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/lex_error4.py0000644000076500007650000000045411603702121016320 0ustar yayayaya# lex_error4.py # # t_error defined as function, but too many args import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "NUMBER", ] t_PLUS = r'\+' t_MINUS = r'-' t_NUMBER = r'\d+' def t_error(t,s): pass lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/yacc_error1.py0000644000076500007650000000277211603702121016451 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_error1.py # # Bad p_error() function # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(t): 'statement : NAME EQUALS expression' names[t[1]] = t[3] def p_statement_expr(t): 'statement : expression' print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_error(t,s): print("Syntax error at '%s'" % t.value) yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/yacc_error2.py0000644000076500007650000000276711603702121016456 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_error2.py # # Bad p_error() function # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(t): 'statement : NAME EQUALS expression' names[t[1]] = t[3] def p_statement_expr(t): 'statement : expression' print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_error(): print("Syntax error at '%s'" % t.value) yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/yacc_error3.py0000644000076500007650000000271511603702121016450 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_error3.py # # Bad p_error() function # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(t): 'statement : NAME EQUALS expression' names[t[1]] = t[3] def p_statement_expr(t): 'statement : expression' print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 p_error = "blah" yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/yacc_error4.py0000644000076500007650000000303211603702121016442 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_error4.py # # Attempt to define a rule named 'error' # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc from calclex import tokens # Parsing rules precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(t): 'statement : NAME EQUALS expression' names[t[1]] = t[3] def p_statement_expr(t): 'statement : expression' print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_error_handler(t): 'error : NAME' pass def p_error(t): pass yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/test/lex_ignore.py0000644000076500007650000000052111603702121016361 0ustar yayayaya# lex_ignore.py # # Improperly specific ignore declaration import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.lex as lex tokens = [ "PLUS", "MINUS", "NUMBER", ] t_PLUS = r'\+' t_MINUS = r'-' t_NUMBER = r'\d+' def t_ignore(t): ' \t' pass def t_error(t): pass import sys lex.lex() ./CBFlib-0.9.2.2/ply-3.2/test/yacc_notok.py0000644000076500007650000000277011603702121016367 0ustar yayayaya# ----------------------------------------------------------------------------- # yacc_notok.py # # A grammar, but we forgot to import the tokens list # ----------------------------------------------------------------------------- import sys if ".." not in sys.path: sys.path.insert(0,"..") import ply.yacc as yacc # Parsing rules precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(t): 'statement : NAME EQUALS expression' names[t[1]] = t[3] def p_statement_expr(t): 'statement : expression' print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_error(t): print("Syntax error at '%s'" % t.value) yacc.yacc() ./CBFlib-0.9.2.2/ply-3.2/build/0000755000076500007650000000000011603703070014002 5ustar yayayaya./CBFlib-0.9.2.2/ply-3.2/build/lib/0000755000076500007650000000000011603703074014554 5ustar yayayaya./CBFlib-0.9.2.2/ply-3.2/build/lib/ply/0000755000076500007650000000000011603703101015347 5ustar yayayaya./CBFlib-0.9.2.2/ply-3.2/build/lib/ply/yacc.py0000644000076500007650000037274711603702120016664 0ustar yayayaya# ----------------------------------------------------------------------------- # ply: yacc.py # # Copyright (C) 2001-2009, # David M. Beazley (Dabeaz LLC) # All rights reserved. # # Redistribution and use in source and binary forms, with or without # modification, are permitted provided that the following conditions are # met: # # * Redistributions of source code must retain the above copyright notice, # this list of conditions and the following disclaimer. # * Redistributions in binary form must reproduce the above copyright notice, # this list of conditions and the following disclaimer in the documentation # and/or other materials provided with the distribution. # * Neither the name of the David Beazley or Dabeaz LLC may be used to # endorse or promote products derived from this software without # specific prior written permission. # # THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS # "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT # LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR # A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT # OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, # SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT # LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, # DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY # THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT # (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE # OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. # ----------------------------------------------------------------------------- # # This implements an LR parser that is constructed from grammar rules defined # as Python functions. The grammer is specified by supplying the BNF inside # Python documentation strings. The inspiration for this technique was borrowed # from John Aycock's Spark parsing system. PLY might be viewed as cross between # Spark and the GNU bison utility. # # The current implementation is only somewhat object-oriented. The # LR parser itself is defined in terms of an object (which allows multiple # parsers to co-exist). However, most of the variables used during table # construction are defined in terms of global variables. Users shouldn't # notice unless they are trying to define multiple parsers at the same # time using threads (in which case they should have their head examined). # # This implementation supports both SLR and LALR(1) parsing. LALR(1) # support was originally implemented by Elias Ioup (ezioup@alumni.uchicago.edu), # using the algorithm found in Aho, Sethi, and Ullman "Compilers: Principles, # Techniques, and Tools" (The Dragon Book). LALR(1) has since been replaced # by the more efficient DeRemer and Pennello algorithm. # # :::::::: WARNING ::::::: # # Construction of LR parsing tables is fairly complicated and expensive. # To make this module run fast, a *LOT* of work has been put into # optimization---often at the expensive of readability and what might # consider to be good Python "coding style." Modify the code at your # own risk! # ---------------------------------------------------------------------------- __version__ = "3.2" __tabversion__ = "3.2" # Table version #----------------------------------------------------------------------------- # === User configurable parameters === # # Change these to modify the default behavior of yacc (if you wish) #----------------------------------------------------------------------------- yaccdebug = 1 # Debugging mode. If set, yacc generates a # a 'parser.out' file in the current directory debug_file = 'parser.out' # Default name of the debugging file tab_module = 'parsetab' # Default name of the table module default_lr = 'LALR' # Default LR table generation method error_count = 3 # Number of symbols that must be shifted to leave recovery mode yaccdevel = 0 # Set to True if developing yacc. This turns off optimized # implementations of certain functions. resultlimit = 40 # Size limit of results when running in debug mode. pickle_protocol = 0 # Protocol to use when writing pickle files import re, types, sys, os.path # Compatibility function for python 2.6/3.0 if sys.version_info[0] < 3: def func_code(f): return f.func_code else: def func_code(f): return f.__code__ # Compatibility try: MAXINT = sys.maxint except AttributeError: MAXINT = sys.maxsize # Python 2.x/3.0 compatibility. def load_ply_lex(): if sys.version_info[0] < 3: import lex else: import ply.lex as lex return lex # This object is a stand-in for a logging object created by the # logging module. PLY will use this by default to create things # such as the parser.out file. If a user wants more detailed # information, they can create their own logging object and pass # it into PLY. class PlyLogger(object): def __init__(self,f): self.f = f def debug(self,msg,*args,**kwargs): self.f.write((msg % args) + "\n") info = debug def warning(self,msg,*args,**kwargs): self.f.write("WARNING: "+ (msg % args) + "\n") def error(self,msg,*args,**kwargs): self.f.write("ERROR: " + (msg % args) + "\n") critical = debug # Null logger is used when no output is generated. Does nothing. class NullLogger(object): def __getattribute__(self,name): return self def __call__(self,*args,**kwargs): return self # Exception raised for yacc-related errors class YaccError(Exception): pass # Format the result message that the parser produces when running in debug mode. def format_result(r): repr_str = repr(r) if '\n' in repr_str: repr_str = repr(repr_str) if len(repr_str) > resultlimit: repr_str = repr_str[:resultlimit]+" ..." result = "<%s @ 0x%x> (%s)" % (type(r).__name__,id(r),repr_str) return result # Format stack entries when the parser is running in debug mode def format_stack_entry(r): repr_str = repr(r) if '\n' in repr_str: repr_str = repr(repr_str) if len(repr_str) < 16: return repr_str else: return "<%s @ 0x%x>" % (type(r).__name__,id(r)) #----------------------------------------------------------------------------- # === LR Parsing Engine === # # The following classes are used for the LR parser itself. These are not # used during table construction and are independent of the actual LR # table generation algorithm #----------------------------------------------------------------------------- # This class is used to hold non-terminal grammar symbols during parsing. # It normally has the following attributes set: # .type = Grammar symbol type # .value = Symbol value # .lineno = Starting line number # .endlineno = Ending line number (optional, set automatically) # .lexpos = Starting lex position # .endlexpos = Ending lex position (optional, set automatically) class YaccSymbol: def __str__(self): return self.type def __repr__(self): return str(self) # This class is a wrapper around the objects actually passed to each # grammar rule. Index lookup and assignment actually assign the # .value attribute of the underlying YaccSymbol object. # The lineno() method returns the line number of a given # item (or 0 if not defined). The linespan() method returns # a tuple of (startline,endline) representing the range of lines # for a symbol. The lexspan() method returns a tuple (lexpos,endlexpos) # representing the range of positional information for a symbol. class YaccProduction: def __init__(self,s,stack=None): self.slice = s self.stack = stack self.lexer = None self.parser= None def __getitem__(self,n): if n >= 0: return self.slice[n].value else: return self.stack[n].value def __setitem__(self,n,v): self.slice[n].value = v def __getslice__(self,i,j): return [s.value for s in self.slice[i:j]] def __len__(self): return len(self.slice) def lineno(self,n): return getattr(self.slice[n],"lineno",0) def set_lineno(self,n,lineno): self.slice[n].lineno = n def linespan(self,n): startline = getattr(self.slice[n],"lineno",0) endline = getattr(self.slice[n],"endlineno",startline) return startline,endline def lexpos(self,n): return getattr(self.slice[n],"lexpos",0) def lexspan(self,n): startpos = getattr(self.slice[n],"lexpos",0) endpos = getattr(self.slice[n],"endlexpos",startpos) return startpos,endpos def error(self): raise SyntaxError # ----------------------------------------------------------------------------- # == LRParser == # # The LR Parsing engine. # ----------------------------------------------------------------------------- class LRParser: def __init__(self,lrtab,errorf): self.productions = lrtab.lr_productions self.action = lrtab.lr_action self.goto = lrtab.lr_goto self.errorfunc = errorf def errok(self): self.errorok = 1 def restart(self): del self.statestack[:] del self.symstack[:] sym = YaccSymbol() sym.type = '$end' self.symstack.append(sym) self.statestack.append(0) def parse(self,input=None,lexer=None,debug=0,tracking=0,tokenfunc=None): if debug or yaccdevel: if isinstance(debug,int): debug = PlyLogger(sys.stderr) return self.parsedebug(input,lexer,debug,tracking,tokenfunc) elif tracking: return self.parseopt(input,lexer,debug,tracking,tokenfunc) else: return self.parseopt_notrack(input,lexer,debug,tracking,tokenfunc) # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! # parsedebug(). # # This is the debugging enabled version of parse(). All changes made to the # parsing engine should be made here. For the non-debugging version, # copy this code to a method parseopt() and delete all of the sections # enclosed in: # # #--! DEBUG # statements # #--! DEBUG # # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! def parsedebug(self,input=None,lexer=None,debug=None,tracking=0,tokenfunc=None): lookahead = None # Current lookahead symbol lookaheadstack = [ ] # Stack of lookahead symbols actions = self.action # Local reference to action table (to avoid lookup on self.) goto = self.goto # Local reference to goto table (to avoid lookup on self.) prod = self.productions # Local reference to production list (to avoid lookup on self.) pslice = YaccProduction(None) # Production object passed to grammar rules errorcount = 0 # Used during error recovery # --! DEBUG debug.info("PLY: PARSE DEBUG START") # --! DEBUG # If no lexer was given, we will try to use the lex module if not lexer: lex = load_ply_lex() lexer = lex.lexer # Set up the lexer and parser objects on pslice pslice.lexer = lexer pslice.parser = self # If input was supplied, pass to lexer if input is not None: lexer.input(input) if tokenfunc is None: # Tokenize function get_token = lexer.token else: get_token = tokenfunc # Set up the state and symbol stacks statestack = [ ] # Stack of parsing states self.statestack = statestack symstack = [ ] # Stack of grammar symbols self.symstack = symstack pslice.stack = symstack # Put in the production errtoken = None # Err token # The start state is assumed to be (0,$end) statestack.append(0) sym = YaccSymbol() sym.type = "$end" symstack.append(sym) state = 0 while 1: # Get the next symbol on the input. If a lookahead symbol # is already set, we just use that. Otherwise, we'll pull # the next token off of the lookaheadstack or from the lexer # --! DEBUG debug.debug('') debug.debug('State : %s', state) # --! DEBUG if not lookahead: if not lookaheadstack: lookahead = get_token() # Get the next token else: lookahead = lookaheadstack.pop() if not lookahead: lookahead = YaccSymbol() lookahead.type = "$end" # --! DEBUG debug.debug('Stack : %s', ("%s . %s" % (" ".join([xx.type for xx in symstack][1:]), str(lookahead))).lstrip()) # --! DEBUG # Check the action table ltype = lookahead.type t = actions[state].get(ltype) if t is not None: if t > 0: # shift a symbol on the stack statestack.append(t) state = t # --! DEBUG debug.debug("Action : Shift and goto state %s", t) # --! DEBUG symstack.append(lookahead) lookahead = None # Decrease error count on successful shift if errorcount: errorcount -=1 continue if t < 0: # reduce a symbol on the stack, emit a production p = prod[-t] pname = p.name plen = p.len # Get production function sym = YaccSymbol() sym.type = pname # Production name sym.value = None # --! DEBUG if plen: debug.info("Action : Reduce rule [%s] with %s and goto state %d", p.str, "["+",".join([format_stack_entry(_v.value) for _v in symstack[-plen:]])+"]",-t) else: debug.info("Action : Reduce rule [%s] with %s and goto state %d", p.str, [],-t) # --! DEBUG if plen: targ = symstack[-plen-1:] targ[0] = sym # --! TRACKING if tracking: t1 = targ[1] sym.lineno = t1.lineno sym.lexpos = t1.lexpos t1 = targ[-1] sym.endlineno = getattr(t1,"endlineno",t1.lineno) sym.endlexpos = getattr(t1,"endlexpos",t1.lexpos) # --! TRACKING # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! # The code enclosed in this section is duplicated # below as a performance optimization. Make sure # changes get made in both locations. pslice.slice = targ try: # Call the grammar rule with our special slice object del symstack[-plen:] del statestack[-plen:] p.callable(pslice) # --! DEBUG debug.info("Result : %s", format_result(pslice[0])) # --! DEBUG symstack.append(sym) state = goto[statestack[-1]][pname] statestack.append(state) except SyntaxError: # If an error was set. Enter error recovery state lookaheadstack.append(lookahead) symstack.pop() statestack.pop() state = statestack[-1] sym.type = 'error' lookahead = sym errorcount = error_count self.errorok = 0 continue # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! else: # --! TRACKING if tracking: sym.lineno = lexer.lineno sym.lexpos = lexer.lexpos # --! TRACKING targ = [ sym ] # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! # The code enclosed in this section is duplicated # above as a performance optimization. Make sure # changes get made in both locations. pslice.slice = targ try: # Call the grammar rule with our special slice object p.callable(pslice) # --! DEBUG debug.info("Result : %s", format_result(pslice[0])) # --! DEBUG symstack.append(sym) state = goto[statestack[-1]][pname] statestack.append(state) except SyntaxError: # If an error was set. Enter error recovery state lookaheadstack.append(lookahead) symstack.pop() statestack.pop() state = statestack[-1] sym.type = 'error' lookahead = sym errorcount = error_count self.errorok = 0 continue # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! if t == 0: n = symstack[-1] result = getattr(n,"value",None) # --! DEBUG debug.info("Done : Returning %s", format_result(result)) debug.info("PLY: PARSE DEBUG END") # --! DEBUG return result if t == None: # --! DEBUG debug.error('Error : %s', ("%s . %s" % (" ".join([xx.type for xx in symstack][1:]), str(lookahead))).lstrip()) # --! DEBUG # We have some kind of parsing error here. To handle # this, we are going to push the current token onto # the tokenstack and replace it with an 'error' token. # If there are any synchronization rules, they may # catch it. # # In addition to pushing the error token, we call call # the user defined p_error() function if this is the # first syntax error. This function is only called if # errorcount == 0. if errorcount == 0 or self.errorok: errorcount = error_count self.errorok = 0 errtoken = lookahead if errtoken.type == "$end": errtoken = None # End of file! if self.errorfunc: global errok,token,restart errok = self.errok # Set some special functions available in error recovery token = get_token restart = self.restart if errtoken and not hasattr(errtoken,'lexer'): errtoken.lexer = lexer tok = self.errorfunc(errtoken) del errok, token, restart # Delete special functions if self.errorok: # User must have done some kind of panic # mode recovery on their own. The # returned token is the next lookahead lookahead = tok errtoken = None continue else: if errtoken: if hasattr(errtoken,"lineno"): lineno = lookahead.lineno else: lineno = 0 if lineno: sys.stderr.write("yacc: Syntax error at line %d, token=%s\n" % (lineno, errtoken.type)) else: sys.stderr.write("yacc: Syntax error, token=%s" % errtoken.type) else: sys.stderr.write("yacc: Parse error in input. EOF\n") return else: errorcount = error_count # case 1: the statestack only has 1 entry on it. If we're in this state, the # entire parse has been rolled back and we're completely hosed. The token is # discarded and we just keep going. if len(statestack) <= 1 and lookahead.type != "$end": lookahead = None errtoken = None state = 0 # Nuke the pushback stack del lookaheadstack[:] continue # case 2: the statestack has a couple of entries on it, but we're # at the end of the file. nuke the top entry and generate an error token # Start nuking entries on the stack if lookahead.type == "$end": # Whoa. We're really hosed here. Bail out return if lookahead.type != 'error': sym = symstack[-1] if sym.type == 'error': # Hmmm. Error is on top of stack, we'll just nuke input # symbol and continue lookahead = None continue t = YaccSymbol() t.type = 'error' if hasattr(lookahead,"lineno"): t.lineno = lookahead.lineno t.value = lookahead lookaheadstack.append(lookahead) lookahead = t else: symstack.pop() statestack.pop() state = statestack[-1] # Potential bug fix continue # Call an error function here raise RuntimeError("yacc: internal parser error!!!\n") # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! # parseopt(). # # Optimized version of parse() method. DO NOT EDIT THIS CODE DIRECTLY. # Edit the debug version above, then copy any modifications to the method # below while removing #--! DEBUG sections. # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! def parseopt(self,input=None,lexer=None,debug=0,tracking=0,tokenfunc=None): lookahead = None # Current lookahead symbol lookaheadstack = [ ] # Stack of lookahead symbols actions = self.action # Local reference to action table (to avoid lookup on self.) goto = self.goto # Local reference to goto table (to avoid lookup on self.) prod = self.productions # Local reference to production list (to avoid lookup on self.) pslice = YaccProduction(None) # Production object passed to grammar rules errorcount = 0 # Used during error recovery # If no lexer was given, we will try to use the lex module if not lexer: lex = load_ply_lex() lexer = lex.lexer # Set up the lexer and parser objects on pslice pslice.lexer = lexer pslice.parser = self # If input was supplied, pass to lexer if input is not None: lexer.input(input) if tokenfunc is None: # Tokenize function get_token = lexer.token else: get_token = tokenfunc # Set up the state and symbol stacks statestack = [ ] # Stack of parsing states self.statestack = statestack symstack = [ ] # Stack of grammar symbols self.symstack = symstack pslice.stack = symstack # Put in the production errtoken = None # Err token # The start state is assumed to be (0,$end) statestack.append(0) sym = YaccSymbol() sym.type = '$end' symstack.append(sym) state = 0 while 1: # Get the next symbol on the input. If a lookahead symbol # is already set, we just use that. Otherwise, we'll pull # the next token off of the lookaheadstack or from the lexer if not lookahead: if not lookaheadstack: lookahead = get_token() # Get the next token else: lookahead = lookaheadstack.pop() if not lookahead: lookahead = YaccSymbol() lookahead.type = '$end' # Check the action table ltype = lookahead.type t = actions[state].get(ltype) if t is not None: if t > 0: # shift a symbol on the stack statestack.append(t) state = t symstack.append(lookahead) lookahead = None # Decrease error count on successful shift if errorcount: errorcount -=1 continue if t < 0: # reduce a symbol on the stack, emit a production p = prod[-t] pname = p.name plen = p.len # Get production function sym = YaccSymbol() sym.type = pname # Production name sym.value = None if plen: targ = symstack[-plen-1:] targ[0] = sym # --! TRACKING if tracking: t1 = targ[1] sym.lineno = t1.lineno sym.lexpos = t1.lexpos t1 = targ[-1] sym.endlineno = getattr(t1,"endlineno",t1.lineno) sym.endlexpos = getattr(t1,"endlexpos",t1.lexpos) # --! TRACKING # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! # The code enclosed in this section is duplicated # below as a performance optimization. Make sure # changes get made in both locations. pslice.slice = targ try: # Call the grammar rule with our special slice object del symstack[-plen:] del statestack[-plen:] p.callable(pslice) symstack.append(sym) state = goto[statestack[-1]][pname] statestack.append(state) except SyntaxError: # If an error was set. Enter error recovery state lookaheadstack.append(lookahead) symstack.pop() statestack.pop() state = statestack[-1] sym.type = 'error' lookahead = sym errorcount = error_count self.errorok = 0 continue # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! else: # --! TRACKING if tracking: sym.lineno = lexer.lineno sym.lexpos = lexer.lexpos # --! TRACKING targ = [ sym ] # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! # The code enclosed in this section is duplicated # above as a performance optimization. Make sure # changes get made in both locations. pslice.slice = targ try: # Call the grammar rule with our special slice object p.callable(pslice) symstack.append(sym) state = goto[statestack[-1]][pname] statestack.append(state) except SyntaxError: # If an error was set. Enter error recovery state lookaheadstack.append(lookahead) symstack.pop() statestack.pop() state = statestack[-1] sym.type = 'error' lookahead = sym errorcount = error_count self.errorok = 0 continue # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! if t == 0: n = symstack[-1] return getattr(n,"value",None) if t == None: # We have some kind of parsing error here. To handle # this, we are going to push the current token onto # the tokenstack and replace it with an 'error' token. # If there are any synchronization rules, they may # catch it. # # In addition to pushing the error token, we call call # the user defined p_error() function if this is the # first syntax error. This function is only called if # errorcount == 0. if errorcount == 0 or self.errorok: errorcount = error_count self.errorok = 0 errtoken = lookahead if errtoken.type == '$end': errtoken = None # End of file! if self.errorfunc: global errok,token,restart errok = self.errok # Set some special functions available in error recovery token = get_token restart = self.restart if errtoken and not hasattr(errtoken,'lexer'): errtoken.lexer = lexer tok = self.errorfunc(errtoken) del errok, token, restart # Delete special functions if self.errorok: # User must have done some kind of panic # mode recovery on their own. The # returned token is the next lookahead lookahead = tok errtoken = None continue else: if errtoken: if hasattr(errtoken,"lineno"): lineno = lookahead.lineno else: lineno = 0 if lineno: sys.stderr.write("yacc: Syntax error at line %d, token=%s\n" % (lineno, errtoken.type)) else: sys.stderr.write("yacc: Syntax error, token=%s" % errtoken.type) else: sys.stderr.write("yacc: Parse error in input. EOF\n") return else: errorcount = error_count # case 1: the statestack only has 1 entry on it. If we're in this state, the # entire parse has been rolled back and we're completely hosed. The token is # discarded and we just keep going. if len(statestack) <= 1 and lookahead.type != '$end': lookahead = None errtoken = None state = 0 # Nuke the pushback stack del lookaheadstack[:] continue # case 2: the statestack has a couple of entries on it, but we're # at the end of the file. nuke the top entry and generate an error token # Start nuking entries on the stack if lookahead.type == '$end': # Whoa. We're really hosed here. Bail out return if lookahead.type != 'error': sym = symstack[-1] if sym.type == 'error': # Hmmm. Error is on top of stack, we'll just nuke input # symbol and continue lookahead = None continue t = YaccSymbol() t.type = 'error' if hasattr(lookahead,"lineno"): t.lineno = lookahead.lineno t.value = lookahead lookaheadstack.append(lookahead) lookahead = t else: symstack.pop() statestack.pop() state = statestack[-1] # Potential bug fix continue # Call an error function here raise RuntimeError("yacc: internal parser error!!!\n") # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! # parseopt_notrack(). # # Optimized version of parseopt() with line number tracking removed. # DO NOT EDIT THIS CODE DIRECTLY. Copy the optimized version and remove # code in the #--! TRACKING sections # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! def parseopt_notrack(self,input=None,lexer=None,debug=0,tracking=0,tokenfunc=None): lookahead = None # Current lookahead symbol lookaheadstack = [ ] # Stack of lookahead symbols actions = self.action # Local reference to action table (to avoid lookup on self.) goto = self.goto # Local reference to goto table (to avoid lookup on self.) prod = self.productions # Local reference to production list (to avoid lookup on self.) pslice = YaccProduction(None) # Production object passed to grammar rules errorcount = 0 # Used during error recovery # If no lexer was given, we will try to use the lex module if not lexer: lex = load_ply_lex() lexer = lex.lexer # Set up the lexer and parser objects on pslice pslice.lexer = lexer pslice.parser = self # If input was supplied, pass to lexer if input is not None: lexer.input(input) if tokenfunc is None: # Tokenize function get_token = lexer.token else: get_token = tokenfunc # Set up the state and symbol stacks statestack = [ ] # Stack of parsing states self.statestack = statestack symstack = [ ] # Stack of grammar symbols self.symstack = symstack pslice.stack = symstack # Put in the production errtoken = None # Err token # The start state is assumed to be (0,$end) statestack.append(0) sym = YaccSymbol() sym.type = '$end' symstack.append(sym) state = 0 while 1: # Get the next symbol on the input. If a lookahead symbol # is already set, we just use that. Otherwise, we'll pull # the next token off of the lookaheadstack or from the lexer if not lookahead: if not lookaheadstack: lookahead = get_token() # Get the next token else: lookahead = lookaheadstack.pop() if not lookahead: lookahead = YaccSymbol() lookahead.type = '$end' # Check the action table ltype = lookahead.type t = actions[state].get(ltype) if t is not None: if t > 0: # shift a symbol on the stack statestack.append(t) state = t symstack.append(lookahead) lookahead = None # Decrease error count on successful shift if errorcount: errorcount -=1 continue if t < 0: # reduce a symbol on the stack, emit a production p = prod[-t] pname = p.name plen = p.len # Get production function sym = YaccSymbol() sym.type = pname # Production name sym.value = None if plen: targ = symstack[-plen-1:] targ[0] = sym # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! # The code enclosed in this section is duplicated # below as a performance optimization. Make sure # changes get made in both locations. pslice.slice = targ try: # Call the grammar rule with our special slice object del symstack[-plen:] del statestack[-plen:] p.callable(pslice) symstack.append(sym) state = goto[statestack[-1]][pname] statestack.append(state) except SyntaxError: # If an error was set. Enter error recovery state lookaheadstack.append(lookahead) symstack.pop() statestack.pop() state = statestack[-1] sym.type = 'error' lookahead = sym errorcount = error_count self.errorok = 0 continue # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! else: targ = [ sym ] # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! # The code enclosed in this section is duplicated # above as a performance optimization. Make sure # changes get made in both locations. pslice.slice = targ try: # Call the grammar rule with our special slice object p.callable(pslice) symstack.append(sym) state = goto[statestack[-1]][pname] statestack.append(state) except SyntaxError: # If an error was set. Enter error recovery state lookaheadstack.append(lookahead) symstack.pop() statestack.pop() state = statestack[-1] sym.type = 'error' lookahead = sym errorcount = error_count self.errorok = 0 continue # !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! if t == 0: n = symstack[-1] return getattr(n,"value",None) if t == None: # We have some kind of parsing error here. To handle # this, we are going to push the current token onto # the tokenstack and replace it with an 'error' token. # If there are any synchronization rules, they may # catch it. # # In addition to pushing the error token, we call call # the user defined p_error() function if this is the # first syntax error. This function is only called if # errorcount == 0. if errorcount == 0 or self.errorok: errorcount = error_count self.errorok = 0 errtoken = lookahead if errtoken.type == '$end': errtoken = None # End of file! if self.errorfunc: global errok,token,restart errok = self.errok # Set some special functions available in error recovery token = get_token restart = self.restart if errtoken and not hasattr(errtoken,'lexer'): errtoken.lexer = lexer tok = self.errorfunc(errtoken) del errok, token, restart # Delete special functions if self.errorok: # User must have done some kind of panic # mode recovery on their own. The # returned token is the next lookahead lookahead = tok errtoken = None continue else: if errtoken: if hasattr(errtoken,"lineno"): lineno = lookahead.lineno else: lineno = 0 if lineno: sys.stderr.write("yacc: Syntax error at line %d, token=%s\n" % (lineno, errtoken.type)) else: sys.stderr.write("yacc: Syntax error, token=%s" % errtoken.type) else: sys.stderr.write("yacc: Parse error in input. EOF\n") return else: errorcount = error_count # case 1: the statestack only has 1 entry on it. If we're in this state, the # entire parse has been rolled back and we're completely hosed. The token is # discarded and we just keep going. if len(statestack) <= 1 and lookahead.type != '$end': lookahead = None errtoken = None state = 0 # Nuke the pushback stack del lookaheadstack[:] continue # case 2: the statestack has a couple of entries on it, but we're # at the end of the file. nuke the top entry and generate an error token # Start nuking entries on the stack if lookahead.type == '$end': # Whoa. We're really hosed here. Bail out return if lookahead.type != 'error': sym = symstack[-1] if sym.type == 'error': # Hmmm. Error is on top of stack, we'll just nuke input # symbol and continue lookahead = None continue t = YaccSymbol() t.type = 'error' if hasattr(lookahead,"lineno"): t.lineno = lookahead.lineno t.value = lookahead lookaheadstack.append(lookahead) lookahead = t else: symstack.pop() statestack.pop() state = statestack[-1] # Potential bug fix continue # Call an error function here raise RuntimeError("yacc: internal parser error!!!\n") # ----------------------------------------------------------------------------- # === Grammar Representation === # # The following functions, classes, and variables are used to represent and # manipulate the rules that make up a grammar. # ----------------------------------------------------------------------------- import re # regex matching identifiers _is_identifier = re.compile(r'^[a-zA-Z0-9_-]+$') # ----------------------------------------------------------------------------- # class Production: # # This class stores the raw information about a single production or grammar rule. # A grammar rule refers to a specification such as this: # # expr : expr PLUS term # # Here are the basic attributes defined on all productions # # name - Name of the production. For example 'expr' # prod - A list of symbols on the right side ['expr','PLUS','term'] # prec - Production precedence level # number - Production number. # func - Function that executes on reduce # file - File where production function is defined # lineno - Line number where production function is defined # # The following attributes are defined or optional. # # len - Length of the production (number of symbols on right hand side) # usyms - Set of unique symbols found in the production # ----------------------------------------------------------------------------- class Production(object): reduced = 0 def __init__(self,number,name,prod,precedence=('right',0),func=None,file='',line=0): self.name = name self.prod = tuple(prod) self.number = number self.func = func self.callable = None self.file = file self.line = line self.prec = precedence # Internal settings used during table construction self.len = len(self.prod) # Length of the production # Create a list of unique production symbols used in the production self.usyms = [ ] for s in self.prod: if s not in self.usyms: self.usyms.append(s) # List of all LR items for the production self.lr_items = [] self.lr_next = None # Create a string representation if self.prod: self.str = "%s -> %s" % (self.name," ".join(self.prod)) else: self.str = "%s -> " % self.name def __str__(self): return self.str def __repr__(self): return "Production("+str(self)+")" def __len__(self): return len(self.prod) def __nonzero__(self): return 1 def __getitem__(self,index): return self.prod[index] # Return the nth lr_item from the production (or None if at the end) def lr_item(self,n): if n > len(self.prod): return None p = LRItem(self,n) # Precompute the list of productions immediately following. Hack. Remove later try: p.lr_after = Prodnames[p.prod[n+1]] except (IndexError,KeyError): p.lr_after = [] try: p.lr_before = p.prod[n-1] except IndexError: p.lr_before = None return p # Bind the production function name to a callable def bind(self,pdict): if self.func: self.callable = pdict[self.func] # This class serves as a minimal standin for Production objects when # reading table data from files. It only contains information # actually used by the LR parsing engine, plus some additional # debugging information. class MiniProduction(object): def __init__(self,str,name,len,func,file,line): self.name = name self.len = len self.func = func self.callable = None self.file = file self.line = line self.str = str def __str__(self): return self.str def __repr__(self): return "MiniProduction(%s)" % self.str # Bind the production function name to a callable def bind(self,pdict): if self.func: self.callable = pdict[self.func] # ----------------------------------------------------------------------------- # class LRItem # # This class represents a specific stage of parsing a production rule. For # example: # # expr : expr . PLUS term # # In the above, the "." represents the current location of the parse. Here # basic attributes: # # name - Name of the production. For example 'expr' # prod - A list of symbols on the right side ['expr','.', 'PLUS','term'] # number - Production number. # # lr_next Next LR item. Example, if we are ' expr -> expr . PLUS term' # then lr_next refers to 'expr -> expr PLUS . term' # lr_index - LR item index (location of the ".") in the prod list. # lookaheads - LALR lookahead symbols for this item # len - Length of the production (number of symbols on right hand side) # lr_after - List of all productions that immediately follow # lr_before - Grammar symbol immediately before # ----------------------------------------------------------------------------- class LRItem(object): def __init__(self,p,n): self.name = p.name self.prod = list(p.prod) self.number = p.number self.lr_index = n self.lookaheads = { } self.prod.insert(n,".") self.prod = tuple(self.prod) self.len = len(self.prod) self.usyms = p.usyms def __str__(self): if self.prod: s = "%s -> %s" % (self.name," ".join(self.prod)) else: s = "%s -> " % self.name return s def __repr__(self): return "LRItem("+str(self)+")" # ----------------------------------------------------------------------------- # rightmost_terminal() # # Return the rightmost terminal from a list of symbols. Used in add_production() # ----------------------------------------------------------------------------- def rightmost_terminal(symbols, terminals): i = len(symbols) - 1 while i >= 0: if symbols[i] in terminals: return symbols[i] i -= 1 return None # ----------------------------------------------------------------------------- # === GRAMMAR CLASS === # # The following class represents the contents of the specified grammar along # with various computed properties such as first sets, follow sets, LR items, etc. # This data is used for critical parts of the table generation process later. # ----------------------------------------------------------------------------- class GrammarError(YaccError): pass class Grammar(object): def __init__(self,terminals): self.Productions = [None] # A list of all of the productions. The first # entry is always reserved for the purpose of # building an augmented grammar self.Prodnames = { } # A dictionary mapping the names of nonterminals to a list of all # productions of that nonterminal. self.Prodmap = { } # A dictionary that is only used to detect duplicate # productions. self.Terminals = { } # A dictionary mapping the names of terminal symbols to a # list of the rules where they are used. for term in terminals: self.Terminals[term] = [] self.Terminals['error'] = [] self.Nonterminals = { } # A dictionary mapping names of nonterminals to a list # of rule numbers where they are used. self.First = { } # A dictionary of precomputed FIRST(x) symbols self.Follow = { } # A dictionary of precomputed FOLLOW(x) symbols self.Precedence = { } # Precedence rules for each terminal. Contains tuples of the # form ('right',level) or ('nonassoc', level) or ('left',level) self.UsedPrecedence = { } # Precedence rules that were actually used by the grammer. # This is only used to provide error checking and to generate # a warning about unused precedence rules. self.Start = None # Starting symbol for the grammar def __len__(self): return len(self.Productions) def __getitem__(self,index): return self.Productions[index] # ----------------------------------------------------------------------------- # set_precedence() # # Sets the precedence for a given terminal. assoc is the associativity such as # 'left','right', or 'nonassoc'. level is a numeric level. # # ----------------------------------------------------------------------------- def set_precedence(self,term,assoc,level): assert self.Productions == [None],"Must call set_precedence() before add_production()" if term in self.Precedence: raise GrammarError("Precedence already specified for terminal '%s'" % term) if assoc not in ['left','right','nonassoc']: raise GrammarError("Associativity must be one of 'left','right', or 'nonassoc'") self.Precedence[term] = (assoc,level) # ----------------------------------------------------------------------------- # add_production() # # Given an action function, this function assembles a production rule and # computes its precedence level. # # The production rule is supplied as a list of symbols. For example, # a rule such as 'expr : expr PLUS term' has a production name of 'expr' and # symbols ['expr','PLUS','term']. # # Precedence is determined by the precedence of the right-most non-terminal # or the precedence of a terminal specified by %prec. # # A variety of error checks are performed to make sure production symbols # are valid and that %prec is used correctly. # ----------------------------------------------------------------------------- def add_production(self,prodname,syms,func=None,file='',line=0): if prodname in self.Terminals: raise GrammarError("%s:%d: Illegal rule name '%s'. Already defined as a token" % (file,line,prodname)) if prodname == 'error': raise GrammarError("%s:%d: Illegal rule name '%s'. error is a reserved word" % (file,line,prodname)) if not _is_identifier.match(prodname): raise GrammarError("%s:%d: Illegal rule name '%s'" % (file,line,prodname)) # Look for literal tokens for n,s in enumerate(syms): if s[0] in "'\"": try: c = eval(s) if (len(c) > 1): raise GrammarError("%s:%d: Literal token %s in rule '%s' may only be a single character" % (file,line,s, prodname)) if not c in self.Terminals: self.Terminals[c] = [] syms[n] = c continue except SyntaxError: pass if not _is_identifier.match(s) and s != '%prec': raise GrammarError("%s:%d: Illegal name '%s' in rule '%s'" % (file,line,s, prodname)) # Determine the precedence level if '%prec' in syms: if syms[-1] == '%prec': raise GrammarError("%s:%d: Syntax error. Nothing follows %%prec" % (file,line)) if syms[-2] != '%prec': raise GrammarError("%s:%d: Syntax error. %%prec can only appear at the end of a grammar rule" % (file,line)) precname = syms[-1] prodprec = self.Precedence.get(precname,None) if not prodprec: raise GrammarError("%s:%d: Nothing known about the precedence of '%s'" % (file,line,precname)) else: self.UsedPrecedence[precname] = 1 del syms[-2:] # Drop %prec from the rule else: # If no %prec, precedence is determined by the rightmost terminal symbol precname = rightmost_terminal(syms,self.Terminals) prodprec = self.Precedence.get(precname,('right',0)) # See if the rule is already in the rulemap map = "%s -> %s" % (prodname,syms) if map in self.Prodmap: m = self.Prodmap[map] raise GrammarError("%s:%d: Duplicate rule %s. " % (file,line, m) + "Previous definition at %s:%d" % (m.file, m.line)) # From this point on, everything is valid. Create a new Production instance pnumber = len(self.Productions) if not prodname in self.Nonterminals: self.Nonterminals[prodname] = [ ] # Add the production number to Terminals and Nonterminals for t in syms: if t in self.Terminals: self.Terminals[t].append(pnumber) else: if not t in self.Nonterminals: self.Nonterminals[t] = [ ] self.Nonterminals[t].append(pnumber) # Create a production and add it to the list of productions p = Production(pnumber,prodname,syms,prodprec,func,file,line) self.Productions.append(p) self.Prodmap[map] = p # Add to the global productions list try: self.Prodnames[prodname].append(p) except KeyError: self.Prodnames[prodname] = [ p ] return 0 # ----------------------------------------------------------------------------- # set_start() # # Sets the starting symbol and creates the augmented grammar. Production # rule 0 is S' -> start where start is the start symbol. # ----------------------------------------------------------------------------- def set_start(self,start=None): if not start: start = self.Productions[1].name if start not in self.Nonterminals: raise GrammarError("start symbol %s undefined" % start) self.Productions[0] = Production(0,"S'",[start]) self.Nonterminals[start].append(0) self.Start = start # ----------------------------------------------------------------------------- # find_unreachable() # # Find all of the nonterminal symbols that can't be reached from the starting # symbol. Returns a list of nonterminals that can't be reached. # ----------------------------------------------------------------------------- def find_unreachable(self): # Mark all symbols that are reachable from a symbol s def mark_reachable_from(s): if reachable[s]: # We've already reached symbol s. return reachable[s] = 1 for p in self.Prodnames.get(s,[]): for r in p.prod: mark_reachable_from(r) reachable = { } for s in list(self.Terminals) + list(self.Nonterminals): reachable[s] = 0 mark_reachable_from( self.Productions[0].prod[0] ) return [s for s in list(self.Nonterminals) if not reachable[s]] # ----------------------------------------------------------------------------- # infinite_cycles() # # This function looks at the various parsing rules and tries to detect # infinite recursion cycles (grammar rules where there is no possible way # to derive a string of only terminals). # ----------------------------------------------------------------------------- def infinite_cycles(self): terminates = {} # Terminals: for t in self.Terminals: terminates[t] = 1 terminates['$end'] = 1 # Nonterminals: # Initialize to false: for n in self.Nonterminals: terminates[n] = 0 # Then propagate termination until no change: while 1: some_change = 0 for (n,pl) in self.Prodnames.items(): # Nonterminal n terminates iff any of its productions terminates. for p in pl: # Production p terminates iff all of its rhs symbols terminate. for s in p.prod: if not terminates[s]: # The symbol s does not terminate, # so production p does not terminate. p_terminates = 0 break else: # didn't break from the loop, # so every symbol s terminates # so production p terminates. p_terminates = 1 if p_terminates: # symbol n terminates! if not terminates[n]: terminates[n] = 1 some_change = 1 # Don't need to consider any more productions for this n. break if not some_change: break infinite = [] for (s,term) in terminates.items(): if not term: if not s in self.Prodnames and not s in self.Terminals and s != 'error': # s is used-but-not-defined, and we've already warned of that, # so it would be overkill to say that it's also non-terminating. pass else: infinite.append(s) return infinite # ----------------------------------------------------------------------------- # undefined_symbols() # # Find all symbols that were used the grammar, but not defined as tokens or # grammar rules. Returns a list of tuples (sym, prod) where sym in the symbol # and prod is the production where the symbol was used. # ----------------------------------------------------------------------------- def undefined_symbols(self): result = [] for p in self.Productions: if not p: continue for s in p.prod: if not s in self.Prodnames and not s in self.Terminals and s != 'error': result.append((s,p)) return result # ----------------------------------------------------------------------------- # unused_terminals() # # Find all terminals that were defined, but not used by the grammar. Returns # a list of all symbols. # ----------------------------------------------------------------------------- def unused_terminals(self): unused_tok = [] for s,v in self.Terminals.items(): if s != 'error' and not v: unused_tok.append(s) return unused_tok # ------------------------------------------------------------------------------ # unused_rules() # # Find all grammar rules that were defined, but not used (maybe not reachable) # Returns a list of productions. # ------------------------------------------------------------------------------ def unused_rules(self): unused_prod = [] for s,v in self.Nonterminals.items(): if not v: p = self.Prodnames[s][0] unused_prod.append(p) return unused_prod # ----------------------------------------------------------------------------- # unused_precedence() # # Returns a list of tuples (term,precedence) corresponding to precedence # rules that were never used by the grammar. term is the name of the terminal # on which precedence was applied and precedence is a string such as 'left' or # 'right' corresponding to the type of precedence. # ----------------------------------------------------------------------------- def unused_precedence(self): unused = [] for termname in self.Precedence: if not (termname in self.Terminals or termname in self.UsedPrecedence): unused.append((termname,self.Precedence[termname][0])) return unused # ------------------------------------------------------------------------- # _first() # # Compute the value of FIRST1(beta) where beta is a tuple of symbols. # # During execution of compute_first1, the result may be incomplete. # Afterward (e.g., when called from compute_follow()), it will be complete. # ------------------------------------------------------------------------- def _first(self,beta): # We are computing First(x1,x2,x3,...,xn) result = [ ] for x in beta: x_produces_empty = 0 # Add all the non- symbols of First[x] to the result. for f in self.First[x]: if f == '': x_produces_empty = 1 else: if f not in result: result.append(f) if x_produces_empty: # We have to consider the next x in beta, # i.e. stay in the loop. pass else: # We don't have to consider any further symbols in beta. break else: # There was no 'break' from the loop, # so x_produces_empty was true for all x in beta, # so beta produces empty as well. result.append('') return result # ------------------------------------------------------------------------- # compute_first() # # Compute the value of FIRST1(X) for all symbols # ------------------------------------------------------------------------- def compute_first(self): if self.First: return self.First # Terminals: for t in self.Terminals: self.First[t] = [t] self.First['$end'] = ['$end'] # Nonterminals: # Initialize to the empty set: for n in self.Nonterminals: self.First[n] = [] # Then propagate symbols until no change: while 1: some_change = 0 for n in self.Nonterminals: for p in self.Prodnames[n]: for f in self._first(p.prod): if f not in self.First[n]: self.First[n].append( f ) some_change = 1 if not some_change: break return self.First # --------------------------------------------------------------------- # compute_follow() # # Computes all of the follow sets for every non-terminal symbol. The # follow set is the set of all symbols that might follow a given # non-terminal. See the Dragon book, 2nd Ed. p. 189. # --------------------------------------------------------------------- def compute_follow(self,start=None): # If already computed, return the result if self.Follow: return self.Follow # If first sets not computed yet, do that first. if not self.First: self.compute_first() # Add '$end' to the follow list of the start symbol for k in self.Nonterminals: self.Follow[k] = [ ] if not start: start = self.Productions[1].name self.Follow[start] = [ '$end' ] while 1: didadd = 0 for p in self.Productions[1:]: # Here is the production set for i in range(len(p.prod)): B = p.prod[i] if B in self.Nonterminals: # Okay. We got a non-terminal in a production fst = self._first(p.prod[i+1:]) hasempty = 0 for f in fst: if f != '' and f not in self.Follow[B]: self.Follow[B].append(f) didadd = 1 if f == '': hasempty = 1 if hasempty or i == (len(p.prod)-1): # Add elements of follow(a) to follow(b) for f in self.Follow[p.name]: if f not in self.Follow[B]: self.Follow[B].append(f) didadd = 1 if not didadd: break return self.Follow # ----------------------------------------------------------------------------- # build_lritems() # # This function walks the list of productions and builds a complete set of the # LR items. The LR items are stored in two ways: First, they are uniquely # numbered and placed in the list _lritems. Second, a linked list of LR items # is built for each production. For example: # # E -> E PLUS E # # Creates the list # # [E -> . E PLUS E, E -> E . PLUS E, E -> E PLUS . E, E -> E PLUS E . ] # ----------------------------------------------------------------------------- def build_lritems(self): for p in self.Productions: lastlri = p i = 0 lr_items = [] while 1: if i > len(p): lri = None else: lri = LRItem(p,i) # Precompute the list of productions immediately following try: lri.lr_after = self.Prodnames[lri.prod[i+1]] except (IndexError,KeyError): lri.lr_after = [] try: lri.lr_before = lri.prod[i-1] except IndexError: lri.lr_before = None lastlri.lr_next = lri if not lri: break lr_items.append(lri) lastlri = lri i += 1 p.lr_items = lr_items # ----------------------------------------------------------------------------- # == Class LRTable == # # This basic class represents a basic table of LR parsing information. # Methods for generating the tables are not defined here. They are defined # in the derived class LRGeneratedTable. # ----------------------------------------------------------------------------- class VersionError(YaccError): pass class LRTable(object): def __init__(self): self.lr_action = None self.lr_goto = None self.lr_productions = None self.lr_method = None def read_table(self,module): if isinstance(module,types.ModuleType): parsetab = module else: if sys.version_info[0] < 3: exec("import %s as parsetab" % module) else: env = { } exec("import %s as parsetab" % module, env, env) parsetab = env['parsetab'] if parsetab._tabversion != __tabversion__: raise VersionError("yacc table file version is out of date") self.lr_action = parsetab._lr_action self.lr_goto = parsetab._lr_goto self.lr_productions = [] for p in parsetab._lr_productions: self.lr_productions.append(MiniProduction(*p)) self.lr_method = parsetab._lr_method return parsetab._lr_signature def read_pickle(self,filename): try: import cPickle as pickle except ImportError: import pickle in_f = open(filename,"rb") tabversion = pickle.load(in_f) if tabversion != __tabversion__: raise VersionError("yacc table file version is out of date") self.lr_method = pickle.load(in_f) signature = pickle.load(in_f) self.lr_action = pickle.load(in_f) self.lr_goto = pickle.load(in_f) productions = pickle.load(in_f) self.lr_productions = [] for p in productions: self.lr_productions.append(MiniProduction(*p)) in_f.close() return signature # Bind all production function names to callable objects in pdict def bind_callables(self,pdict): for p in self.lr_productions: p.bind(pdict) # ----------------------------------------------------------------------------- # === LR Generator === # # The following classes and functions are used to generate LR parsing tables on # a grammar. # ----------------------------------------------------------------------------- # ----------------------------------------------------------------------------- # digraph() # traverse() # # The following two functions are used to compute set valued functions # of the form: # # F(x) = F'(x) U U{F(y) | x R y} # # This is used to compute the values of Read() sets as well as FOLLOW sets # in LALR(1) generation. # # Inputs: X - An input set # R - A relation # FP - Set-valued function # ------------------------------------------------------------------------------ def digraph(X,R,FP): N = { } for x in X: N[x] = 0 stack = [] F = { } for x in X: if N[x] == 0: traverse(x,N,stack,F,X,R,FP) return F def traverse(x,N,stack,F,X,R,FP): stack.append(x) d = len(stack) N[x] = d F[x] = FP(x) # F(X) <- F'(x) rel = R(x) # Get y's related to x for y in rel: if N[y] == 0: traverse(y,N,stack,F,X,R,FP) N[x] = min(N[x],N[y]) for a in F.get(y,[]): if a not in F[x]: F[x].append(a) if N[x] == d: N[stack[-1]] = MAXINT F[stack[-1]] = F[x] element = stack.pop() while element != x: N[stack[-1]] = MAXINT F[stack[-1]] = F[x] element = stack.pop() class LALRError(YaccError): pass # ----------------------------------------------------------------------------- # == LRGeneratedTable == # # This class implements the LR table generation algorithm. There are no # public methods except for write() # ----------------------------------------------------------------------------- class LRGeneratedTable(LRTable): def __init__(self,grammar,method='LALR',log=None): if method not in ['SLR','LALR']: raise LALRError("Unsupported method %s" % method) self.grammar = grammar self.lr_method = method # Set up the logger if not log: log = NullLogger() self.log = log # Internal attributes self.lr_action = {} # Action table self.lr_goto = {} # Goto table self.lr_productions = grammar.Productions # Copy of grammar Production array self.lr_goto_cache = {} # Cache of computed gotos self.lr0_cidhash = {} # Cache of closures self._add_count = 0 # Internal counter used to detect cycles # Diagonistic information filled in by the table generator self.sr_conflict = 0 self.rr_conflict = 0 self.conflicts = [] # List of conflicts self.sr_conflicts = [] self.rr_conflicts = [] # Build the tables self.grammar.build_lritems() self.grammar.compute_first() self.grammar.compute_follow() self.lr_parse_table() # Compute the LR(0) closure operation on I, where I is a set of LR(0) items. def lr0_closure(self,I): self._add_count += 1 # Add everything in I to J J = I[:] didadd = 1 while didadd: didadd = 0 for j in J: for x in j.lr_after: if getattr(x,"lr0_added",0) == self._add_count: continue # Add B --> .G to J J.append(x.lr_next) x.lr0_added = self._add_count didadd = 1 return J # Compute the LR(0) goto function goto(I,X) where I is a set # of LR(0) items and X is a grammar symbol. This function is written # in a way that guarantees uniqueness of the generated goto sets # (i.e. the same goto set will never be returned as two different Python # objects). With uniqueness, we can later do fast set comparisons using # id(obj) instead of element-wise comparison. def lr0_goto(self,I,x): # First we look for a previously cached entry g = self.lr_goto_cache.get((id(I),x),None) if g: return g # Now we generate the goto set in a way that guarantees uniqueness # of the result s = self.lr_goto_cache.get(x,None) if not s: s = { } self.lr_goto_cache[x] = s gs = [ ] for p in I: n = p.lr_next if n and n.lr_before == x: s1 = s.get(id(n),None) if not s1: s1 = { } s[id(n)] = s1 gs.append(n) s = s1 g = s.get('$end',None) if not g: if gs: g = self.lr0_closure(gs) s['$end'] = g else: s['$end'] = gs self.lr_goto_cache[(id(I),x)] = g return g # Compute the LR(0) sets of item function def lr0_items(self): C = [ self.lr0_closure([self.grammar.Productions[0].lr_next]) ] i = 0 for I in C: self.lr0_cidhash[id(I)] = i i += 1 # Loop over the items in C and each grammar symbols i = 0 while i < len(C): I = C[i] i += 1 # Collect all of the symbols that could possibly be in the goto(I,X) sets asyms = { } for ii in I: for s in ii.usyms: asyms[s] = None for x in asyms: g = self.lr0_goto(I,x) if not g: continue if id(g) in self.lr0_cidhash: continue self.lr0_cidhash[id(g)] = len(C) C.append(g) return C # ----------------------------------------------------------------------------- # ==== LALR(1) Parsing ==== # # LALR(1) parsing is almost exactly the same as SLR except that instead of # relying upon Follow() sets when performing reductions, a more selective # lookahead set that incorporates the state of the LR(0) machine is utilized. # Thus, we mainly just have to focus on calculating the lookahead sets. # # The method used here is due to DeRemer and Pennelo (1982). # # DeRemer, F. L., and T. J. Pennelo: "Efficient Computation of LALR(1) # Lookahead Sets", ACM Transactions on Programming Languages and Systems, # Vol. 4, No. 4, Oct. 1982, pp. 615-649 # # Further details can also be found in: # # J. Tremblay and P. Sorenson, "The Theory and Practice of Compiler Writing", # McGraw-Hill Book Company, (1985). # # ----------------------------------------------------------------------------- # ----------------------------------------------------------------------------- # compute_nullable_nonterminals() # # Creates a dictionary containing all of the non-terminals that might produce # an empty production. # ----------------------------------------------------------------------------- def compute_nullable_nonterminals(self): nullable = {} num_nullable = 0 while 1: for p in self.grammar.Productions[1:]: if p.len == 0: nullable[p.name] = 1 continue for t in p.prod: if not t in nullable: break else: nullable[p.name] = 1 if len(nullable) == num_nullable: break num_nullable = len(nullable) return nullable # ----------------------------------------------------------------------------- # find_nonterminal_trans(C) # # Given a set of LR(0) items, this functions finds all of the non-terminal # transitions. These are transitions in which a dot appears immediately before # a non-terminal. Returns a list of tuples of the form (state,N) where state # is the state number and N is the nonterminal symbol. # # The input C is the set of LR(0) items. # ----------------------------------------------------------------------------- def find_nonterminal_transitions(self,C): trans = [] for state in range(len(C)): for p in C[state]: if p.lr_index < p.len - 1: t = (state,p.prod[p.lr_index+1]) if t[1] in self.grammar.Nonterminals: if t not in trans: trans.append(t) state = state + 1 return trans # ----------------------------------------------------------------------------- # dr_relation() # # Computes the DR(p,A) relationships for non-terminal transitions. The input # is a tuple (state,N) where state is a number and N is a nonterminal symbol. # # Returns a list of terminals. # ----------------------------------------------------------------------------- def dr_relation(self,C,trans,nullable): dr_set = { } state,N = trans terms = [] g = self.lr0_goto(C[state],N) for p in g: if p.lr_index < p.len - 1: a = p.prod[p.lr_index+1] if a in self.grammar.Terminals: if a not in terms: terms.append(a) # This extra bit is to handle the start state if state == 0 and N == self.grammar.Productions[0].prod[0]: terms.append('$end') return terms # ----------------------------------------------------------------------------- # reads_relation() # # Computes the READS() relation (p,A) READS (t,C). # ----------------------------------------------------------------------------- def reads_relation(self,C, trans, empty): # Look for empty transitions rel = [] state, N = trans g = self.lr0_goto(C[state],N) j = self.lr0_cidhash.get(id(g),-1) for p in g: if p.lr_index < p.len - 1: a = p.prod[p.lr_index + 1] if a in empty: rel.append((j,a)) return rel # ----------------------------------------------------------------------------- # compute_lookback_includes() # # Determines the lookback and includes relations # # LOOKBACK: # # This relation is determined by running the LR(0) state machine forward. # For example, starting with a production "N : . A B C", we run it forward # to obtain "N : A B C ." We then build a relationship between this final # state and the starting state. These relationships are stored in a dictionary # lookdict. # # INCLUDES: # # Computes the INCLUDE() relation (p,A) INCLUDES (p',B). # # This relation is used to determine non-terminal transitions that occur # inside of other non-terminal transition states. (p,A) INCLUDES (p', B) # if the following holds: # # B -> LAT, where T -> epsilon and p' -L-> p # # L is essentially a prefix (which may be empty), T is a suffix that must be # able to derive an empty string. State p' must lead to state p with the string L. # # ----------------------------------------------------------------------------- def compute_lookback_includes(self,C,trans,nullable): lookdict = {} # Dictionary of lookback relations includedict = {} # Dictionary of include relations # Make a dictionary of non-terminal transitions dtrans = {} for t in trans: dtrans[t] = 1 # Loop over all transitions and compute lookbacks and includes for state,N in trans: lookb = [] includes = [] for p in C[state]: if p.name != N: continue # Okay, we have a name match. We now follow the production all the way # through the state machine until we get the . on the right hand side lr_index = p.lr_index j = state while lr_index < p.len - 1: lr_index = lr_index + 1 t = p.prod[lr_index] # Check to see if this symbol and state are a non-terminal transition if (j,t) in dtrans: # Yes. Okay, there is some chance that this is an includes relation # the only way to know for certain is whether the rest of the # production derives empty li = lr_index + 1 while li < p.len: if p.prod[li] in self.grammar.Terminals: break # No forget it if not p.prod[li] in nullable: break li = li + 1 else: # Appears to be a relation between (j,t) and (state,N) includes.append((j,t)) g = self.lr0_goto(C[j],t) # Go to next set j = self.lr0_cidhash.get(id(g),-1) # Go to next state # When we get here, j is the final state, now we have to locate the production for r in C[j]: if r.name != p.name: continue if r.len != p.len: continue i = 0 # This look is comparing a production ". A B C" with "A B C ." while i < r.lr_index: if r.prod[i] != p.prod[i+1]: break i = i + 1 else: lookb.append((j,r)) for i in includes: if not i in includedict: includedict[i] = [] includedict[i].append((state,N)) lookdict[(state,N)] = lookb return lookdict,includedict # ----------------------------------------------------------------------------- # compute_read_sets() # # Given a set of LR(0) items, this function computes the read sets. # # Inputs: C = Set of LR(0) items # ntrans = Set of nonterminal transitions # nullable = Set of empty transitions # # Returns a set containing the read sets # ----------------------------------------------------------------------------- def compute_read_sets(self,C, ntrans, nullable): FP = lambda x: self.dr_relation(C,x,nullable) R = lambda x: self.reads_relation(C,x,nullable) F = digraph(ntrans,R,FP) return F # ----------------------------------------------------------------------------- # compute_follow_sets() # # Given a set of LR(0) items, a set of non-terminal transitions, a readset, # and an include set, this function computes the follow sets # # Follow(p,A) = Read(p,A) U U {Follow(p',B) | (p,A) INCLUDES (p',B)} # # Inputs: # ntrans = Set of nonterminal transitions # readsets = Readset (previously computed) # inclsets = Include sets (previously computed) # # Returns a set containing the follow sets # ----------------------------------------------------------------------------- def compute_follow_sets(self,ntrans,readsets,inclsets): FP = lambda x: readsets[x] R = lambda x: inclsets.get(x,[]) F = digraph(ntrans,R,FP) return F # ----------------------------------------------------------------------------- # add_lookaheads() # # Attaches the lookahead symbols to grammar rules. # # Inputs: lookbacks - Set of lookback relations # followset - Computed follow set # # This function directly attaches the lookaheads to productions contained # in the lookbacks set # ----------------------------------------------------------------------------- def add_lookaheads(self,lookbacks,followset): for trans,lb in lookbacks.items(): # Loop over productions in lookback for state,p in lb: if not state in p.lookaheads: p.lookaheads[state] = [] f = followset.get(trans,[]) for a in f: if a not in p.lookaheads[state]: p.lookaheads[state].append(a) # ----------------------------------------------------------------------------- # add_lalr_lookaheads() # # This function does all of the work of adding lookahead information for use # with LALR parsing # ----------------------------------------------------------------------------- def add_lalr_lookaheads(self,C): # Determine all of the nullable nonterminals nullable = self.compute_nullable_nonterminals() # Find all non-terminal transitions trans = self.find_nonterminal_transitions(C) # Compute read sets readsets = self.compute_read_sets(C,trans,nullable) # Compute lookback/includes relations lookd, included = self.compute_lookback_includes(C,trans,nullable) # Compute LALR FOLLOW sets followsets = self.compute_follow_sets(trans,readsets,included) # Add all of the lookaheads self.add_lookaheads(lookd,followsets) # ----------------------------------------------------------------------------- # lr_parse_table() # # This function constructs the parse tables for SLR or LALR # ----------------------------------------------------------------------------- def lr_parse_table(self): Productions = self.grammar.Productions Precedence = self.grammar.Precedence goto = self.lr_goto # Goto array action = self.lr_action # Action array log = self.log # Logger for output actionp = { } # Action production array (temporary) log.info("Parsing method: %s", self.lr_method) # Step 1: Construct C = { I0, I1, ... IN}, collection of LR(0) items # This determines the number of states C = self.lr0_items() if self.lr_method == 'LALR': self.add_lalr_lookaheads(C) # Build the parser table, state by state st = 0 for I in C: # Loop over each production in I actlist = [ ] # List of actions st_action = { } st_actionp = { } st_goto = { } log.info("") log.info("state %d", st) log.info("") for p in I: log.info(" (%d) %s", p.number, str(p)) log.info("") for p in I: if p.len == p.lr_index + 1: if p.name == "S'": # Start symbol. Accept! st_action["$end"] = 0 st_actionp["$end"] = p else: # We are at the end of a production. Reduce! if self.lr_method == 'LALR': laheads = p.lookaheads[st] else: laheads = self.grammar.Follow[p.name] for a in laheads: actlist.append((a,p,"reduce using rule %d (%s)" % (p.number,p))) r = st_action.get(a,None) if r is not None: # Whoa. Have a shift/reduce or reduce/reduce conflict if r > 0: # Need to decide on shift or reduce here # By default we favor shifting. Need to add # some precedence rules here. sprec,slevel = Productions[st_actionp[a].number].prec rprec,rlevel = Precedence.get(a,('right',0)) if (slevel < rlevel) or ((slevel == rlevel) and (rprec == 'left')): # We really need to reduce here. st_action[a] = -p.number st_actionp[a] = p if not slevel and not rlevel: log.info(" ! shift/reduce conflict for %s resolved as reduce",a) self.sr_conflicts.append((st,a,'reduce')) Productions[p.number].reduced += 1 elif (slevel == rlevel) and (rprec == 'nonassoc'): st_action[a] = None else: # Hmmm. Guess we'll keep the shift if not rlevel: log.info(" ! shift/reduce conflict for %s resolved as shift",a) self.sr_conflicts.append((st,a,'shift')) elif r < 0: # Reduce/reduce conflict. In this case, we favor the rule # that was defined first in the grammar file oldp = Productions[-r] pp = Productions[p.number] if oldp.line > pp.line: st_action[a] = -p.number st_actionp[a] = p chosenp,rejectp = pp,oldp Productions[p.number].reduced += 1 Productions[oldp.number].reduced -= 1 else: chosenp,rejectp = oldp,pp self.rr_conflicts.append((st,chosenp,rejectp)) log.info(" ! reduce/reduce conflict for %s resolved using rule %d (%s)", a,st_actionp[a].number, st_actionp[a]) else: raise LALRError("Unknown conflict in state %d" % st) else: st_action[a] = -p.number st_actionp[a] = p Productions[p.number].reduced += 1 else: i = p.lr_index a = p.prod[i+1] # Get symbol right after the "." if a in self.grammar.Terminals: g = self.lr0_goto(I,a) j = self.lr0_cidhash.get(id(g),-1) if j >= 0: # We are in a shift state actlist.append((a,p,"shift and go to state %d" % j)) r = st_action.get(a,None) if r is not None: # Whoa have a shift/reduce or shift/shift conflict if r > 0: if r != j: raise LALRError("Shift/shift conflict in state %d" % st) elif r < 0: # Do a precedence check. # - if precedence of reduce rule is higher, we reduce. # - if precedence of reduce is same and left assoc, we reduce. # - otherwise we shift rprec,rlevel = Productions[st_actionp[a].number].prec sprec,slevel = Precedence.get(a,('right',0)) if (slevel > rlevel) or ((slevel == rlevel) and (rprec == 'right')): # We decide to shift here... highest precedence to shift Productions[st_actionp[a].number].reduced -= 1 st_action[a] = j st_actionp[a] = p if not rlevel: log.info(" ! shift/reduce conflict for %s resolved as shift",a) self.sr_conflicts.append((st,a,'shift')) elif (slevel == rlevel) and (rprec == 'nonassoc'): st_action[a] = None else: # Hmmm. Guess we'll keep the reduce if not slevel and not rlevel: log.info(" ! shift/reduce conflict for %s resolved as reduce",a) self.sr_conflicts.append((st,a,'reduce')) else: raise LALRError("Unknown conflict in state %d" % st) else: st_action[a] = j st_actionp[a] = p # Print the actions associated with each terminal _actprint = { } for a,p,m in actlist: if a in st_action: if p is st_actionp[a]: log.info(" %-15s %s",a,m) _actprint[(a,m)] = 1 log.info("") # Print the actions that were not used. (debugging) not_used = 0 for a,p,m in actlist: if a in st_action: if p is not st_actionp[a]: if not (a,m) in _actprint: log.debug(" ! %-15s [ %s ]",a,m) not_used = 1 _actprint[(a,m)] = 1 if not_used: log.debug("") # Construct the goto table for this state nkeys = { } for ii in I: for s in ii.usyms: if s in self.grammar.Nonterminals: nkeys[s] = None for n in nkeys: g = self.lr0_goto(I,n) j = self.lr0_cidhash.get(id(g),-1) if j >= 0: st_goto[n] = j log.info(" %-30s shift and go to state %d",n,j) action[st] = st_action actionp[st] = st_actionp goto[st] = st_goto st += 1 # ----------------------------------------------------------------------------- # write() # # This function writes the LR parsing tables to a file # ----------------------------------------------------------------------------- def write_table(self,modulename,outputdir='',signature=""): basemodulename = modulename.split(".")[-1] filename = os.path.join(outputdir,basemodulename) + ".py" try: f = open(filename,"w") f.write(""" # %s # This file is automatically generated. Do not edit. _tabversion = %r _lr_method = %r _lr_signature = %r """ % (filename, __tabversion__, self.lr_method, signature)) # Change smaller to 0 to go back to original tables smaller = 1 # Factor out names to try and make smaller if smaller: items = { } for s,nd in self.lr_action.items(): for name,v in nd.items(): i = items.get(name) if not i: i = ([],[]) items[name] = i i[0].append(s) i[1].append(v) f.write("\n_lr_action_items = {") for k,v in items.items(): f.write("%r:([" % k) for i in v[0]: f.write("%r," % i) f.write("],[") for i in v[1]: f.write("%r," % i) f.write("]),") f.write("}\n") f.write(""" _lr_action = { } for _k, _v in _lr_action_items.items(): for _x,_y in zip(_v[0],_v[1]): if not _x in _lr_action: _lr_action[_x] = { } _lr_action[_x][_k] = _y del _lr_action_items """) else: f.write("\n_lr_action = { "); for k,v in self.lr_action.items(): f.write("(%r,%r):%r," % (k[0],k[1],v)) f.write("}\n"); if smaller: # Factor out names to try and make smaller items = { } for s,nd in self.lr_goto.items(): for name,v in nd.items(): i = items.get(name) if not i: i = ([],[]) items[name] = i i[0].append(s) i[1].append(v) f.write("\n_lr_goto_items = {") for k,v in items.items(): f.write("%r:([" % k) for i in v[0]: f.write("%r," % i) f.write("],[") for i in v[1]: f.write("%r," % i) f.write("]),") f.write("}\n") f.write(""" _lr_goto = { } for _k, _v in _lr_goto_items.items(): for _x,_y in zip(_v[0],_v[1]): if not _x in _lr_goto: _lr_goto[_x] = { } _lr_goto[_x][_k] = _y del _lr_goto_items """) else: f.write("\n_lr_goto = { "); for k,v in self.lr_goto.items(): f.write("(%r,%r):%r," % (k[0],k[1],v)) f.write("}\n"); # Write production table f.write("_lr_productions = [\n") for p in self.lr_productions: if p.func: f.write(" (%r,%r,%d,%r,%r,%d),\n" % (p.str,p.name, p.len, p.func,p.file,p.line)) else: f.write(" (%r,%r,%d,None,None,None),\n" % (str(p),p.name, p.len)) f.write("]\n") f.close() except IOError: e = sys.exc_info()[1] sys.stderr.write("Unable to create '%s'\n" % filename) sys.stderr.write(str(e)+"\n") return # ----------------------------------------------------------------------------- # pickle_table() # # This function pickles the LR parsing tables to a supplied file object # ----------------------------------------------------------------------------- def pickle_table(self,filename,signature=""): try: import cPickle as pickle except ImportError: import pickle outf = open(filename,"wb") pickle.dump(__tabversion__,outf,pickle_protocol) pickle.dump(self.lr_method,outf,pickle_protocol) pickle.dump(signature,outf,pickle_protocol) pickle.dump(self.lr_action,outf,pickle_protocol) pickle.dump(self.lr_goto,outf,pickle_protocol) outp = [] for p in self.lr_productions: if p.func: outp.append((p.str,p.name, p.len, p.func,p.file,p.line)) else: outp.append((str(p),p.name,p.len,None,None,None)) pickle.dump(outp,outf,pickle_protocol) outf.close() # ----------------------------------------------------------------------------- # === INTROSPECTION === # # The following functions and classes are used to implement the PLY # introspection features followed by the yacc() function itself. # ----------------------------------------------------------------------------- # ----------------------------------------------------------------------------- # get_caller_module_dict() # # This function returns a dictionary containing all of the symbols defined within # a caller further down the call stack. This is used to get the environment # associated with the yacc() call if none was provided. # ----------------------------------------------------------------------------- def get_caller_module_dict(levels): try: raise RuntimeError except RuntimeError: e,b,t = sys.exc_info() f = t.tb_frame while levels > 0: f = f.f_back levels -= 1 ldict = f.f_globals.copy() if f.f_globals != f.f_locals: ldict.update(f.f_locals) return ldict # ----------------------------------------------------------------------------- # parse_grammar() # # This takes a raw grammar rule string and parses it into production data # ----------------------------------------------------------------------------- def parse_grammar(doc,file,line): grammar = [] # Split the doc string into lines pstrings = doc.splitlines() lastp = None dline = line for ps in pstrings: dline += 1 p = ps.split() if not p: continue try: if p[0] == '|': # This is a continuation of a previous rule if not lastp: raise SyntaxError("%s:%d: Misplaced '|'" % (file,dline)) prodname = lastp syms = p[1:] else: prodname = p[0] lastp = prodname syms = p[2:] assign = p[1] if assign != ':' and assign != '::=': raise SyntaxError("%s:%d: Syntax error. Expected ':'" % (file,dline)) grammar.append((file,dline,prodname,syms)) except SyntaxError: raise except Exception: raise SyntaxError("%s:%d: Syntax error in rule '%s'" % (file,dline,ps.strip())) return grammar # ----------------------------------------------------------------------------- # ParserReflect() # # This class represents information extracted for building a parser including # start symbol, error function, tokens, precedence list, action functions, # etc. # ----------------------------------------------------------------------------- class ParserReflect(object): def __init__(self,pdict,log=None): self.pdict = pdict self.start = None self.error_func = None self.tokens = None self.files = {} self.grammar = [] self.error = 0 if log is None: self.log = PlyLogger(sys.stderr) else: self.log = log # Get all of the basic information def get_all(self): self.get_start() self.get_error_func() self.get_tokens() self.get_precedence() self.get_pfunctions() # Validate all of the information def validate_all(self): self.validate_start() self.validate_error_func() self.validate_tokens() self.validate_precedence() self.validate_pfunctions() self.validate_files() return self.error # Compute a signature over the grammar def signature(self): try: from hashlib import md5 except ImportError: from md5 import md5 try: sig = md5() if self.start: sig.update(self.start.encode('latin-1')) if self.prec: sig.update("".join(["".join(p) for p in self.prec]).encode('latin-1')) if self.tokens: sig.update(" ".join(self.tokens).encode('latin-1')) for f in self.pfuncs: if f[3]: sig.update(f[3].encode('latin-1')) except (TypeError,ValueError): pass return sig.digest() # ----------------------------------------------------------------------------- # validate_file() # # This method checks to see if there are duplicated p_rulename() functions # in the parser module file. Without this function, it is really easy for # users to make mistakes by cutting and pasting code fragments (and it's a real # bugger to try and figure out why the resulting parser doesn't work). Therefore, # we just do a little regular expression pattern matching of def statements # to try and detect duplicates. # ----------------------------------------------------------------------------- def validate_files(self): # Match def p_funcname( fre = re.compile(r'\s*def\s+(p_[a-zA-Z_0-9]*)\(') for filename in self.files.keys(): base,ext = os.path.splitext(filename) if ext != '.py': return 1 # No idea. Assume it's okay. try: f = open(filename) lines = f.readlines() f.close() except IOError: continue counthash = { } for linen,l in enumerate(lines): linen += 1 m = fre.match(l) if m: name = m.group(1) prev = counthash.get(name) if not prev: counthash[name] = linen else: self.log.warning("%s:%d: Function %s redefined. Previously defined on line %d", filename,linen,name,prev) # Get the start symbol def get_start(self): self.start = self.pdict.get('start') # Validate the start symbol def validate_start(self): if self.start is not None: if not isinstance(self.start,str): self.log.error("'start' must be a string") # Look for error handler def get_error_func(self): self.error_func = self.pdict.get('p_error') # Validate the error function def validate_error_func(self): if self.error_func: if isinstance(self.error_func,types.FunctionType): ismethod = 0 elif isinstance(self.error_func, types.MethodType): ismethod = 1 else: self.log.error("'p_error' defined, but is not a function or method") self.error = 1 return eline = func_code(self.error_func).co_firstlineno efile = func_code(self.error_func).co_filename self.files[efile] = 1 if (func_code(self.error_func).co_argcount != 1+ismethod): self.log.error("%s:%d: p_error() requires 1 argument",efile,eline) self.error = 1 # Get the tokens map def get_tokens(self): tokens = self.pdict.get("tokens",None) if not tokens: self.log.error("No token list is defined") self.error = 1 return if not isinstance(tokens,(list, tuple)): self.log.error("tokens must be a list or tuple") self.error = 1 return if not tokens: self.log.error("tokens is empty") self.error = 1 return self.tokens = tokens # Validate the tokens def validate_tokens(self): # Validate the tokens. if 'error' in self.tokens: self.log.error("Illegal token name 'error'. Is a reserved word") self.error = 1 return terminals = {} for n in self.tokens: if n in terminals: self.log.warning("Token '%s' multiply defined", n) terminals[n] = 1 # Get the precedence map (if any) def get_precedence(self): self.prec = self.pdict.get("precedence",None) # Validate and parse the precedence map def validate_precedence(self): preclist = [] if self.prec: if not isinstance(self.prec,(list,tuple)): self.log.error("precedence must be a list or tuple") self.error = 1 return for level,p in enumerate(self.prec): if not isinstance(p,(list,tuple)): self.log.error("Bad precedence table") self.error = 1 return if len(p) < 2: self.log.error("Malformed precedence entry %s. Must be (assoc, term, ..., term)",p) self.error = 1 return assoc = p[0] if not isinstance(assoc,str): self.log.error("precedence associativity must be a string") self.error = 1 return for term in p[1:]: if not isinstance(term,str): self.log.error("precedence items must be strings") self.error = 1 return preclist.append((term,assoc,level+1)) self.preclist = preclist # Get all p_functions from the grammar def get_pfunctions(self): p_functions = [] for name, item in self.pdict.items(): if name[:2] != 'p_': continue if name == 'p_error': continue if isinstance(item,(types.FunctionType,types.MethodType)): line = func_code(item).co_firstlineno file = func_code(item).co_filename p_functions.append((line,file,name,item.__doc__)) # Sort all of the actions by line number p_functions.sort() self.pfuncs = p_functions # Validate all of the p_functions def validate_pfunctions(self): grammar = [] # Check for non-empty symbols if len(self.pfuncs) == 0: self.log.error("no rules of the form p_rulename are defined") self.error = 1 return for line, file, name, doc in self.pfuncs: func = self.pdict[name] if isinstance(func, types.MethodType): reqargs = 2 else: reqargs = 1 if func_code(func).co_argcount > reqargs: self.log.error("%s:%d: Rule '%s' has too many arguments",file,line,func.__name__) self.error = 1 elif func_code(func).co_argcount < reqargs: self.log.error("%s:%d: Rule '%s' requires an argument",file,line,func.__name__) self.error = 1 elif not func.__doc__: self.log.warning("%s:%d: No documentation string specified in function '%s' (ignored)",file,line,func.__name__) else: try: parsed_g = parse_grammar(doc,file,line) for g in parsed_g: grammar.append((name, g)) except SyntaxError: e = sys.exc_info()[1] self.log.error(str(e)) self.error = 1 # Looks like a valid grammar rule # Mark the file in which defined. self.files[file] = 1 # Secondary validation step that looks for p_ definitions that are not functions # or functions that look like they might be grammar rules. for n,v in self.pdict.items(): if n[0:2] == 'p_' and isinstance(v, (types.FunctionType, types.MethodType)): continue if n[0:2] == 't_': continue if n[0:2] == 'p_' and n != 'p_error': self.log.warning("'%s' not defined as a function", n) if ((isinstance(v,types.FunctionType) and func_code(v).co_argcount == 1) or (isinstance(v,types.MethodType) and func_code(v).co_argcount == 2)): try: doc = v.__doc__.split(" ") if doc[1] == ':': self.log.warning("%s:%d: Possible grammar rule '%s' defined without p_ prefix", func_code(v).co_filename, func_code(v).co_firstlineno,n) except Exception: pass self.grammar = grammar # ----------------------------------------------------------------------------- # yacc(module) # # Build a parser # ----------------------------------------------------------------------------- def yacc(method='LALR', debug=yaccdebug, module=None, tabmodule=tab_module, start=None, check_recursion=1, optimize=0, write_tables=1, debugfile=debug_file,outputdir='', debuglog=None, errorlog = None, picklefile=None): global parse # Reference to the parsing method of the last built parser # If pickling is enabled, table files are not created if picklefile: write_tables = 0 if errorlog is None: errorlog = PlyLogger(sys.stderr) # Get the module dictionary used for the parser if module: _items = [(k,getattr(module,k)) for k in dir(module)] pdict = dict(_items) else: pdict = get_caller_module_dict(2) # Collect parser information from the dictionary pinfo = ParserReflect(pdict,log=errorlog) pinfo.get_all() if pinfo.error: raise YaccError("Unable to build parser") # Check signature against table files (if any) signature = pinfo.signature() # Read the tables try: lr = LRTable() if picklefile: read_signature = lr.read_pickle(picklefile) else: read_signature = lr.read_table(tabmodule) if optimize or (read_signature == signature): try: lr.bind_callables(pinfo.pdict) parser = LRParser(lr,pinfo.error_func) parse = parser.parse return parser except Exception: e = sys.exc_info()[1] errorlog.warning("There was a problem loading the table file: %s", repr(e)) except VersionError: e = sys.exc_info() errorlog.warning(str(e)) except Exception: pass if debuglog is None: if debug: debuglog = PlyLogger(open(debugfile,"w")) else: debuglog = NullLogger() debuglog.info("Created by PLY version %s (http://www.dabeaz.com/ply)", __version__) errors = 0 # Validate the parser information if pinfo.validate_all(): raise YaccError("Unable to build parser") if not pinfo.error_func: errorlog.warning("no p_error() function is defined") # Create a grammar object grammar = Grammar(pinfo.tokens) # Set precedence level for terminals for term, assoc, level in pinfo.preclist: try: grammar.set_precedence(term,assoc,level) except GrammarError: e = sys.exc_info()[1] errorlog.warning("%s",str(e)) # Add productions to the grammar for funcname, gram in pinfo.grammar: file, line, prodname, syms = gram try: grammar.add_production(prodname,syms,funcname,file,line) except GrammarError: e = sys.exc_info()[1] errorlog.error("%s",str(e)) errors = 1 # Set the grammar start symbols try: if start is None: grammar.set_start(pinfo.start) else: grammar.set_start(start) except GrammarError: e = sys.exc_info()[1] errorlog.error(str(e)) errors = 1 if errors: raise YaccError("Unable to build parser") # Verify the grammar structure undefined_symbols = grammar.undefined_symbols() for sym, prod in undefined_symbols: errorlog.error("%s:%d: Symbol '%s' used, but not defined as a token or a rule",prod.file,prod.line,sym) errors = 1 unused_terminals = grammar.unused_terminals() if unused_terminals: debuglog.info("") debuglog.info("Unused terminals:") debuglog.info("") for term in unused_terminals: errorlog.warning("Token '%s' defined, but not used", term) debuglog.info(" %s", term) # Print out all productions to the debug log if debug: debuglog.info("") debuglog.info("Grammar") debuglog.info("") for n,p in enumerate(grammar.Productions): debuglog.info("Rule %-5d %s", n, p) # Find unused non-terminals unused_rules = grammar.unused_rules() for prod in unused_rules: errorlog.warning("%s:%d: Rule '%s' defined, but not used", prod.file, prod.line, prod.name) if len(unused_terminals) == 1: errorlog.warning("There is 1 unused token") if len(unused_terminals) > 1: errorlog.warning("There are %d unused tokens", len(unused_terminals)) if len(unused_rules) == 1: errorlog.warning("There is 1 unused rule") if len(unused_rules) > 1: errorlog.warning("There are %d unused rules", len(unused_rules)) if debug: debuglog.info("") debuglog.info("Terminals, with rules where they appear") debuglog.info("") terms = list(grammar.Terminals) terms.sort() for term in terms: debuglog.info("%-20s : %s", term, " ".join([str(s) for s in grammar.Terminals[term]])) debuglog.info("") debuglog.info("Nonterminals, with rules where they appear") debuglog.info("") nonterms = list(grammar.Nonterminals) nonterms.sort() for nonterm in nonterms: debuglog.info("%-20s : %s", nonterm, " ".join([str(s) for s in grammar.Nonterminals[nonterm]])) debuglog.info("") if check_recursion: unreachable = grammar.find_unreachable() for u in unreachable: errorlog.warning("Symbol '%s' is unreachable",u) infinite = grammar.infinite_cycles() for inf in infinite: errorlog.error("Infinite recursion detected for symbol '%s'", inf) errors = 1 unused_prec = grammar.unused_precedence() for term, assoc in unused_prec: errorlog.error("Precedence rule '%s' defined for unknown symbol '%s'", assoc, term) errors = 1 if errors: raise YaccError("Unable to build parser") # Run the LRGeneratedTable on the grammar if debug: errorlog.debug("Generating %s tables", method) lr = LRGeneratedTable(grammar,method,debuglog) if debug: num_sr = len(lr.sr_conflicts) # Report shift/reduce and reduce/reduce conflicts if num_sr == 1: errorlog.warning("1 shift/reduce conflict") elif num_sr > 1: errorlog.warning("%d shift/reduce conflicts", num_sr) num_rr = len(lr.rr_conflicts) if num_rr == 1: errorlog.warning("1 reduce/reduce conflict") elif num_rr > 1: errorlog.warning("%d reduce/reduce conflicts", num_rr) # Write out conflicts to the output file if debug and (lr.sr_conflicts or lr.rr_conflicts): debuglog.warning("") debuglog.warning("Conflicts:") debuglog.warning("") for state, tok, resolution in lr.sr_conflicts: debuglog.warning("shift/reduce conflict for %s in state %d resolved as %s", tok, state, resolution) already_reported = {} for state, rule, rejected in lr.rr_conflicts: if (state,id(rule),id(rejected)) in already_reported: continue debuglog.warning("reduce/reduce conflict in state %d resolved using rule (%s)", state, rule) debuglog.warning("rejected rule (%s) in state %d", rejected,state) errorlog.warning("reduce/reduce conflict in state %d resolved using rule (%s)", state, rule) errorlog.warning("rejected rule (%s) in state %d", rejected, state) already_reported[state,id(rule),id(rejected)] = 1 warned_never = [] for state, rule, rejected in lr.rr_conflicts: if not rejected.reduced and (rejected not in warned_never): debuglog.warning("Rule (%s) is never reduced", rejected) errorlog.warning("Rule (%s) is never reduced", rejected) warned_never.append(rejected) # Write the table file if requested if write_tables: lr.write_table(tabmodule,outputdir,signature) # Write a pickled version of the tables if picklefile: lr.pickle_table(picklefile,signature) # Build the parser lr.bind_callables(pinfo.pdict) parser = LRParser(lr,pinfo.error_func) parse = parser.parse return parser ./CBFlib-0.9.2.2/ply-3.2/build/lib/ply/cpp.py0000644000076500007650000010042211603702120016502 0ustar yayayaya# ----------------------------------------------------------------------------- # cpp.py # # Author: David Beazley (http://www.dabeaz.com) # Copyright (C) 2007 # All rights reserved # # This module implements an ANSI-C style lexical preprocessor for PLY. # ----------------------------------------------------------------------------- from __future__ import generators # ----------------------------------------------------------------------------- # Default preprocessor lexer definitions. These tokens are enough to get # a basic preprocessor working. Other modules may import these if they want # ----------------------------------------------------------------------------- tokens = ( 'CPP_ID','CPP_INTEGER', 'CPP_FLOAT', 'CPP_STRING', 'CPP_CHAR', 'CPP_WS', 'CPP_COMMENT', 'CPP_POUND','CPP_DPOUND' ) literals = "+-*/%|&~^<>=!?()[]{}.,;:\\\'\"" # Whitespace def t_CPP_WS(t): r'\s+' t.lexer.lineno += t.value.count("\n") return t t_CPP_POUND = r'\#' t_CPP_DPOUND = r'\#\#' # Identifier t_CPP_ID = r'[A-Za-z_][\w_]*' # Integer literal def CPP_INTEGER(t): r'(((((0x)|(0X))[0-9a-fA-F]+)|(\d+))([uU]|[lL]|[uU][lL]|[lL][uU])?)' return t t_CPP_INTEGER = CPP_INTEGER # Floating literal t_CPP_FLOAT = r'((\d+)(\.\d+)(e(\+|-)?(\d+))? | (\d+)e(\+|-)?(\d+))([lL]|[fF])?' # String literal def t_CPP_STRING(t): r'\"([^\\\n]|(\\(.|\n)))*?\"' t.lexer.lineno += t.value.count("\n") return t # Character constant 'c' or L'c' def t_CPP_CHAR(t): r'(L)?\'([^\\\n]|(\\(.|\n)))*?\'' t.lexer.lineno += t.value.count("\n") return t # Comment def t_CPP_COMMENT(t): r'(/\*(.|\n)*?\*/)|(//.*?\n)' t.lexer.lineno += t.value.count("\n") return t def t_error(t): t.type = t.value[0] t.value = t.value[0] t.lexer.skip(1) return t import re import copy import time import os.path # ----------------------------------------------------------------------------- # trigraph() # # Given an input string, this function replaces all trigraph sequences. # The following mapping is used: # # ??= # # ??/ \ # ??' ^ # ??( [ # ??) ] # ??! | # ??< { # ??> } # ??- ~ # ----------------------------------------------------------------------------- _trigraph_pat = re.compile(r'''\?\?[=/\'\(\)\!<>\-]''') _trigraph_rep = { '=':'#', '/':'\\', "'":'^', '(':'[', ')':']', '!':'|', '<':'{', '>':'}', '-':'~' } def trigraph(input): return _trigraph_pat.sub(lambda g: _trigraph_rep[g.group()[-1]],input) # ------------------------------------------------------------------ # Macro object # # This object holds information about preprocessor macros # # .name - Macro name (string) # .value - Macro value (a list of tokens) # .arglist - List of argument names # .variadic - Boolean indicating whether or not variadic macro # .vararg - Name of the variadic parameter # # When a macro is created, the macro replacement token sequence is # pre-scanned and used to create patch lists that are later used # during macro expansion # ------------------------------------------------------------------ class Macro(object): def __init__(self,name,value,arglist=None,variadic=False): self.name = name self.value = value self.arglist = arglist self.variadic = variadic if variadic: self.vararg = arglist[-1] self.source = None # ------------------------------------------------------------------ # Preprocessor object # # Object representing a preprocessor. Contains macro definitions, # include directories, and other information # ------------------------------------------------------------------ class Preprocessor(object): def __init__(self,lexer=None): if lexer is None: lexer = lex.lexer self.lexer = lexer self.macros = { } self.path = [] self.temp_path = [] # Probe the lexer for selected tokens self.lexprobe() tm = time.localtime() self.define("__DATE__ \"%s\"" % time.strftime("%b %d %Y",tm)) self.define("__TIME__ \"%s\"" % time.strftime("%H:%M:%S",tm)) self.parser = None # ----------------------------------------------------------------------------- # tokenize() # # Utility function. Given a string of text, tokenize into a list of tokens # ----------------------------------------------------------------------------- def tokenize(self,text): tokens = [] self.lexer.input(text) while True: tok = self.lexer.token() if not tok: break tokens.append(tok) return tokens # --------------------------------------------------------------------- # error() # # Report a preprocessor error/warning of some kind # ---------------------------------------------------------------------- def error(self,file,line,msg): print >>sys.stderr,"%s:%d %s" % (file,line,msg) # ---------------------------------------------------------------------- # lexprobe() # # This method probes the preprocessor lexer object to discover # the token types of symbols that are important to the preprocessor. # If this works right, the preprocessor will simply "work" # with any suitable lexer regardless of how tokens have been named. # ---------------------------------------------------------------------- def lexprobe(self): # Determine the token type for identifiers self.lexer.input("identifier") tok = self.lexer.token() if not tok or tok.value != "identifier": print "Couldn't determine identifier type" else: self.t_ID = tok.type # Determine the token type for integers self.lexer.input("12345") tok = self.lexer.token() if not tok or int(tok.value) != 12345: print "Couldn't determine integer type" else: self.t_INTEGER = tok.type self.t_INTEGER_TYPE = type(tok.value) # Determine the token type for strings enclosed in double quotes self.lexer.input("\"filename\"") tok = self.lexer.token() if not tok or tok.value != "\"filename\"": print "Couldn't determine string type" else: self.t_STRING = tok.type # Determine the token type for whitespace--if any self.lexer.input(" ") tok = self.lexer.token() if not tok or tok.value != " ": self.t_SPACE = None else: self.t_SPACE = tok.type # Determine the token type for newlines self.lexer.input("\n") tok = self.lexer.token() if not tok or tok.value != "\n": self.t_NEWLINE = None print "Couldn't determine token for newlines" else: self.t_NEWLINE = tok.type self.t_WS = (self.t_SPACE, self.t_NEWLINE) # Check for other characters used by the preprocessor chars = [ '<','>','#','##','\\','(',')',',','.'] for c in chars: self.lexer.input(c) tok = self.lexer.token() if not tok or tok.value != c: print "Unable to lex '%s' required for preprocessor" % c # ---------------------------------------------------------------------- # add_path() # # Adds a search path to the preprocessor. # ---------------------------------------------------------------------- def add_path(self,path): self.path.append(path) # ---------------------------------------------------------------------- # group_lines() # # Given an input string, this function splits it into lines. Trailing whitespace # is removed. Any line ending with \ is grouped with the next line. This # function forms the lowest level of the preprocessor---grouping into text into # a line-by-line format. # ---------------------------------------------------------------------- def group_lines(self,input): lex = self.lexer.clone() lines = [x.rstrip() for x in input.splitlines()] for i in xrange(len(lines)): j = i+1 while lines[i].endswith('\\') and (j < len(lines)): lines[i] = lines[i][:-1]+lines[j] lines[j] = "" j += 1 input = "\n".join(lines) lex.input(input) lex.lineno = 1 current_line = [] while True: tok = lex.token() if not tok: break current_line.append(tok) if tok.type in self.t_WS and '\n' in tok.value: yield current_line current_line = [] if current_line: yield current_line # ---------------------------------------------------------------------- # tokenstrip() # # Remove leading/trailing whitespace tokens from a token list # ---------------------------------------------------------------------- def tokenstrip(self,tokens): i = 0 while i < len(tokens) and tokens[i].type in self.t_WS: i += 1 del tokens[:i] i = len(tokens)-1 while i >= 0 and tokens[i].type in self.t_WS: i -= 1 del tokens[i+1:] return tokens # ---------------------------------------------------------------------- # collect_args() # # Collects comma separated arguments from a list of tokens. The arguments # must be enclosed in parenthesis. Returns a tuple (tokencount,args,positions) # where tokencount is the number of tokens consumed, args is a list of arguments, # and positions is a list of integers containing the starting index of each # argument. Each argument is represented by a list of tokens. # # When collecting arguments, leading and trailing whitespace is removed # from each argument. # # This function properly handles nested parenthesis and commas---these do not # define new arguments. # ---------------------------------------------------------------------- def collect_args(self,tokenlist): args = [] positions = [] current_arg = [] nesting = 1 tokenlen = len(tokenlist) # Search for the opening '('. i = 0 while (i < tokenlen) and (tokenlist[i].type in self.t_WS): i += 1 if (i < tokenlen) and (tokenlist[i].value == '('): positions.append(i+1) else: self.error(self.source,tokenlist[0].lineno,"Missing '(' in macro arguments") return 0, [], [] i += 1 while i < tokenlen: t = tokenlist[i] if t.value == '(': current_arg.append(t) nesting += 1 elif t.value == ')': nesting -= 1 if nesting == 0: if current_arg: args.append(self.tokenstrip(current_arg)) positions.append(i) return i+1,args,positions current_arg.append(t) elif t.value == ',' and nesting == 1: args.append(self.tokenstrip(current_arg)) positions.append(i+1) current_arg = [] else: current_arg.append(t) i += 1 # Missing end argument self.error(self.source,tokenlist[-1].lineno,"Missing ')' in macro arguments") return 0, [],[] # ---------------------------------------------------------------------- # macro_prescan() # # Examine the macro value (token sequence) and identify patch points # This is used to speed up macro expansion later on---we'll know # right away where to apply patches to the value to form the expansion # ---------------------------------------------------------------------- def macro_prescan(self,macro): macro.patch = [] # Standard macro arguments macro.str_patch = [] # String conversion expansion macro.var_comma_patch = [] # Variadic macro comma patch i = 0 while i < len(macro.value): if macro.value[i].type == self.t_ID and macro.value[i].value in macro.arglist: argnum = macro.arglist.index(macro.value[i].value) # Conversion of argument to a string if i > 0 and macro.value[i-1].value == '#': macro.value[i] = copy.copy(macro.value[i]) macro.value[i].type = self.t_STRING del macro.value[i-1] macro.str_patch.append((argnum,i-1)) continue # Concatenation elif (i > 0 and macro.value[i-1].value == '##'): macro.patch.append(('c',argnum,i-1)) del macro.value[i-1] continue elif ((i+1) < len(macro.value) and macro.value[i+1].value == '##'): macro.patch.append(('c',argnum,i)) i += 1 continue # Standard expansion else: macro.patch.append(('e',argnum,i)) elif macro.value[i].value == '##': if macro.variadic and (i > 0) and (macro.value[i-1].value == ',') and \ ((i+1) < len(macro.value)) and (macro.value[i+1].type == self.t_ID) and \ (macro.value[i+1].value == macro.vararg): macro.var_comma_patch.append(i-1) i += 1 macro.patch.sort(key=lambda x: x[2],reverse=True) # ---------------------------------------------------------------------- # macro_expand_args() # # Given a Macro and list of arguments (each a token list), this method # returns an expanded version of a macro. The return value is a token sequence # representing the replacement macro tokens # ---------------------------------------------------------------------- def macro_expand_args(self,macro,args): # Make a copy of the macro token sequence rep = [copy.copy(_x) for _x in macro.value] # Make string expansion patches. These do not alter the length of the replacement sequence str_expansion = {} for argnum, i in macro.str_patch: if argnum not in str_expansion: str_expansion[argnum] = ('"%s"' % "".join([x.value for x in args[argnum]])).replace("\\","\\\\") rep[i] = copy.copy(rep[i]) rep[i].value = str_expansion[argnum] # Make the variadic macro comma patch. If the variadic macro argument is empty, we get rid comma_patch = False if macro.variadic and not args[-1]: for i in macro.var_comma_patch: rep[i] = None comma_patch = True # Make all other patches. The order of these matters. It is assumed that the patch list # has been sorted in reverse order of patch location since replacements will cause the # size of the replacement sequence to expand from the patch point. expanded = { } for ptype, argnum, i in macro.patch: # Concatenation. Argument is left unexpanded if ptype == 'c': rep[i:i+1] = args[argnum] # Normal expansion. Argument is macro expanded first elif ptype == 'e': if argnum not in expanded: expanded[argnum] = self.expand_macros(args[argnum]) rep[i:i+1] = expanded[argnum] # Get rid of removed comma if necessary if comma_patch: rep = [_i for _i in rep if _i] return rep # ---------------------------------------------------------------------- # expand_macros() # # Given a list of tokens, this function performs macro expansion. # The expanded argument is a dictionary that contains macros already # expanded. This is used to prevent infinite recursion. # ---------------------------------------------------------------------- def expand_macros(self,tokens,expanded=None): if expanded is None: expanded = {} i = 0 while i < len(tokens): t = tokens[i] if t.type == self.t_ID: if t.value in self.macros and t.value not in expanded: # Yes, we found a macro match expanded[t.value] = True m = self.macros[t.value] if not m.arglist: # A simple macro ex = self.expand_macros([copy.copy(_x) for _x in m.value],expanded) for e in ex: e.lineno = t.lineno tokens[i:i+1] = ex i += len(ex) else: # A macro with arguments j = i + 1 while j < len(tokens) and tokens[j].type in self.t_WS: j += 1 if tokens[j].value == '(': tokcount,args,positions = self.collect_args(tokens[j:]) if not m.variadic and len(args) != len(m.arglist): self.error(self.source,t.lineno,"Macro %s requires %d arguments" % (t.value,len(m.arglist))) i = j + tokcount elif m.variadic and len(args) < len(m.arglist)-1: if len(m.arglist) > 2: self.error(self.source,t.lineno,"Macro %s must have at least %d arguments" % (t.value, len(m.arglist)-1)) else: self.error(self.source,t.lineno,"Macro %s must have at least %d argument" % (t.value, len(m.arglist)-1)) i = j + tokcount else: if m.variadic: if len(args) == len(m.arglist)-1: args.append([]) else: args[len(m.arglist)-1] = tokens[j+positions[len(m.arglist)-1]:j+tokcount-1] del args[len(m.arglist):] # Get macro replacement text rep = self.macro_expand_args(m,args) rep = self.expand_macros(rep,expanded) for r in rep: r.lineno = t.lineno tokens[i:j+tokcount] = rep i += len(rep) del expanded[t.value] continue elif t.value == '__LINE__': t.type = self.t_INTEGER t.value = self.t_INTEGER_TYPE(t.lineno) i += 1 return tokens # ---------------------------------------------------------------------- # evalexpr() # # Evaluate an expression token sequence for the purposes of evaluating # integral expressions. # ---------------------------------------------------------------------- def evalexpr(self,tokens): # tokens = tokenize(line) # Search for defined macros i = 0 while i < len(tokens): if tokens[i].type == self.t_ID and tokens[i].value == 'defined': j = i + 1 needparen = False result = "0L" while j < len(tokens): if tokens[j].type in self.t_WS: j += 1 continue elif tokens[j].type == self.t_ID: if tokens[j].value in self.macros: result = "1L" else: result = "0L" if not needparen: break elif tokens[j].value == '(': needparen = True elif tokens[j].value == ')': break else: self.error(self.source,tokens[i].lineno,"Malformed defined()") j += 1 tokens[i].type = self.t_INTEGER tokens[i].value = self.t_INTEGER_TYPE(result) del tokens[i+1:j+1] i += 1 tokens = self.expand_macros(tokens) for i,t in enumerate(tokens): if t.type == self.t_ID: tokens[i] = copy.copy(t) tokens[i].type = self.t_INTEGER tokens[i].value = self.t_INTEGER_TYPE("0L") elif t.type == self.t_INTEGER: tokens[i] = copy.copy(t) # Strip off any trailing suffixes tokens[i].value = str(tokens[i].value) while tokens[i].value[-1] not in "0123456789abcdefABCDEF": tokens[i].value = tokens[i].value[:-1] expr = "".join([str(x.value) for x in tokens]) expr = expr.replace("&&"," and ") expr = expr.replace("||"," or ") expr = expr.replace("!"," not ") try: result = eval(expr) except StandardError: self.error(self.source,tokens[0].lineno,"Couldn't evaluate expression") result = 0 return result # ---------------------------------------------------------------------- # parsegen() # # Parse an input string/ # ---------------------------------------------------------------------- def parsegen(self,input,source=None): # Replace trigraph sequences t = trigraph(input) lines = self.group_lines(t) if not source: source = "" self.define("__FILE__ \"%s\"" % source) self.source = source chunk = [] enable = True iftrigger = False ifstack = [] for x in lines: for i,tok in enumerate(x): if tok.type not in self.t_WS: break if tok.value == '#': # Preprocessor directive for tok in x: if tok in self.t_WS and '\n' in tok.value: chunk.append(tok) dirtokens = self.tokenstrip(x[i+1:]) if dirtokens: name = dirtokens[0].value args = self.tokenstrip(dirtokens[1:]) else: name = "" args = [] if name == 'define': if enable: for tok in self.expand_macros(chunk): yield tok chunk = [] self.define(args) elif name == 'include': if enable: for tok in self.expand_macros(chunk): yield tok chunk = [] oldfile = self.macros['__FILE__'] for tok in self.include(args): yield tok self.macros['__FILE__'] = oldfile self.source = source elif name == 'undef': if enable: for tok in self.expand_macros(chunk): yield tok chunk = [] self.undef(args) elif name == 'ifdef': ifstack.append((enable,iftrigger)) if enable: if not args[0].value in self.macros: enable = False iftrigger = False else: iftrigger = True elif name == 'ifndef': ifstack.append((enable,iftrigger)) if enable: if args[0].value in self.macros: enable = False iftrigger = False else: iftrigger = True elif name == 'if': ifstack.append((enable,iftrigger)) if enable: result = self.evalexpr(args) if not result: enable = False iftrigger = False else: iftrigger = True elif name == 'elif': if ifstack: if ifstack[-1][0]: # We only pay attention if outer "if" allows this if enable: # If already true, we flip enable False enable = False elif not iftrigger: # If False, but not triggered yet, we'll check expression result = self.evalexpr(args) if result: enable = True iftrigger = True else: self.error(self.source,dirtokens[0].lineno,"Misplaced #elif") elif name == 'else': if ifstack: if ifstack[-1][0]: if enable: enable = False elif not iftrigger: enable = True iftrigger = True else: self.error(self.source,dirtokens[0].lineno,"Misplaced #else") elif name == 'endif': if ifstack: enable,iftrigger = ifstack.pop() else: self.error(self.source,dirtokens[0].lineno,"Misplaced #endif") else: # Unknown preprocessor directive pass else: # Normal text if enable: chunk.extend(x) for tok in self.expand_macros(chunk): yield tok chunk = [] # ---------------------------------------------------------------------- # include() # # Implementation of file-inclusion # ---------------------------------------------------------------------- def include(self,tokens): # Try to extract the filename and then process an include file if not tokens: return if tokens: if tokens[0].value != '<' and tokens[0].type != self.t_STRING: tokens = self.expand_macros(tokens) if tokens[0].value == '<': # Include <...> i = 1 while i < len(tokens): if tokens[i].value == '>': break i += 1 else: print "Malformed #include <...>" return filename = "".join([x.value for x in tokens[1:i]]) path = self.path + [""] + self.temp_path elif tokens[0].type == self.t_STRING: filename = tokens[0].value[1:-1] path = self.temp_path + [""] + self.path else: print "Malformed #include statement" return for p in path: iname = os.path.join(p,filename) try: data = open(iname,"r").read() dname = os.path.dirname(iname) if dname: self.temp_path.insert(0,dname) for tok in self.parsegen(data,filename): yield tok if dname: del self.temp_path[0] break except IOError,e: pass else: print "Couldn't find '%s'" % filename # ---------------------------------------------------------------------- # define() # # Define a new macro # ---------------------------------------------------------------------- def define(self,tokens): if isinstance(tokens,(str,unicode)): tokens = self.tokenize(tokens) linetok = tokens try: name = linetok[0] if len(linetok) > 1: mtype = linetok[1] else: mtype = None if not mtype: m = Macro(name.value,[]) self.macros[name.value] = m elif mtype.type in self.t_WS: # A normal macro m = Macro(name.value,self.tokenstrip(linetok[2:])) self.macros[name.value] = m elif mtype.value == '(': # A macro with arguments tokcount, args, positions = self.collect_args(linetok[1:]) variadic = False for a in args: if variadic: print "No more arguments may follow a variadic argument" break astr = "".join([str(_i.value) for _i in a]) if astr == "...": variadic = True a[0].type = self.t_ID a[0].value = '__VA_ARGS__' variadic = True del a[1:] continue elif astr[-3:] == "..." and a[0].type == self.t_ID: variadic = True del a[1:] # If, for some reason, "." is part of the identifier, strip off the name for the purposes # of macro expansion if a[0].value[-3:] == '...': a[0].value = a[0].value[:-3] continue if len(a) > 1 or a[0].type != self.t_ID: print "Invalid macro argument" break else: mvalue = self.tokenstrip(linetok[1+tokcount:]) i = 0 while i < len(mvalue): if i+1 < len(mvalue): if mvalue[i].type in self.t_WS and mvalue[i+1].value == '##': del mvalue[i] continue elif mvalue[i].value == '##' and mvalue[i+1].type in self.t_WS: del mvalue[i+1] i += 1 m = Macro(name.value,mvalue,[x[0].value for x in args],variadic) self.macro_prescan(m) self.macros[name.value] = m else: print "Bad macro definition" except LookupError: print "Bad macro definition" # ---------------------------------------------------------------------- # undef() # # Undefine a macro # ---------------------------------------------------------------------- def undef(self,tokens): id = tokens[0].value try: del self.macros[id] except LookupError: pass # ---------------------------------------------------------------------- # parse() # # Parse input text. # ---------------------------------------------------------------------- def parse(self,input,source=None,ignore={}): self.ignore = ignore self.parser = self.parsegen(input,source) # ---------------------------------------------------------------------- # token() # # Method to return individual tokens # ---------------------------------------------------------------------- def token(self): try: while True: tok = self.parser.next() if tok.type not in self.ignore: return tok except StopIteration: self.parser = None return None if __name__ == '__main__': import ply.lex as lex lexer = lex.lex() # Run a preprocessor import sys f = open(sys.argv[1]) input = f.read() p = Preprocessor(lexer) p.parse(input,sys.argv[1]) while True: tok = p.token() if not tok: break print p.source, tok ./CBFlib-0.9.2.2/ply-3.2/build/lib/ply/lex.py0000644000076500007650000011736611603702120016527 0ustar yayayaya# ----------------------------------------------------------------------------- # ply: lex.py # # Copyright (C) 2001-2009, # David M. Beazley (Dabeaz LLC) # All rights reserved. # # Redistribution and use in source and binary forms, with or without # modification, are permitted provided that the following conditions are # met: # # * Redistributions of source code must retain the above copyright notice, # this list of conditions and the following disclaimer. # * Redistributions in binary form must reproduce the above copyright notice, # this list of conditions and the following disclaimer in the documentation # and/or other materials provided with the distribution. # * Neither the name of the David Beazley or Dabeaz LLC may be used to # endorse or promote products derived from this software without # specific prior written permission. # # THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS # "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT # LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR # A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT # OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, # SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT # LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, # DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY # THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT # (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE # OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. # ----------------------------------------------------------------------------- __version__ = "3.2" __tabversion__ = "3.2" # Version of table file used import re, sys, types, copy, os # This tuple contains known string types try: # Python 2.6 StringTypes = (types.StringType, types.UnicodeType) except AttributeError: # Python 3.0 StringTypes = (str, bytes) # Extract the code attribute of a function. Different implementations # are for Python 2/3 compatibility. if sys.version_info[0] < 3: def func_code(f): return f.func_code else: def func_code(f): return f.__code__ # This regular expression is used to match valid token names _is_identifier = re.compile(r'^[a-zA-Z0-9_]+$') # Exception thrown when invalid token encountered and no default error # handler is defined. class LexError(Exception): def __init__(self,message,s): self.args = (message,) self.text = s # Token class. This class is used to represent the tokens produced. class LexToken(object): def __str__(self): return "LexToken(%s,%r,%d,%d)" % (self.type,self.value,self.lineno,self.lexpos) def __repr__(self): return str(self) # This object is a stand-in for a logging object created by the # logging module. class PlyLogger(object): def __init__(self,f): self.f = f def critical(self,msg,*args,**kwargs): self.f.write((msg % args) + "\n") def warning(self,msg,*args,**kwargs): self.f.write("WARNING: "+ (msg % args) + "\n") def error(self,msg,*args,**kwargs): self.f.write("ERROR: " + (msg % args) + "\n") info = critical debug = critical # Null logger is used when no output is generated. Does nothing. class NullLogger(object): def __getattribute__(self,name): return self def __call__(self,*args,**kwargs): return self # ----------------------------------------------------------------------------- # === Lexing Engine === # # The following Lexer class implements the lexer runtime. There are only # a few public methods and attributes: # # input() - Store a new string in the lexer # token() - Get the next token # clone() - Clone the lexer # # lineno - Current line number # lexpos - Current position in the input string # ----------------------------------------------------------------------------- class Lexer: def __init__(self): self.lexre = None # Master regular expression. This is a list of # tuples (re,findex) where re is a compiled # regular expression and findex is a list # mapping regex group numbers to rules self.lexretext = None # Current regular expression strings self.lexstatere = {} # Dictionary mapping lexer states to master regexs self.lexstateretext = {} # Dictionary mapping lexer states to regex strings self.lexstaterenames = {} # Dictionary mapping lexer states to symbol names self.lexstate = "INITIAL" # Current lexer state self.lexstatestack = [] # Stack of lexer states self.lexstateinfo = None # State information self.lexstateignore = {} # Dictionary of ignored characters for each state self.lexstateerrorf = {} # Dictionary of error functions for each state self.lexreflags = 0 # Optional re compile flags self.lexdata = None # Actual input data (as a string) self.lexpos = 0 # Current position in input text self.lexlen = 0 # Length of the input text self.lexerrorf = None # Error rule (if any) self.lextokens = None # List of valid tokens self.lexignore = "" # Ignored characters self.lexliterals = "" # Literal characters that can be passed through self.lexmodule = None # Module self.lineno = 1 # Current line number self.lexoptimize = 0 # Optimized mode def clone(self,object=None): c = copy.copy(self) # If the object parameter has been supplied, it means we are attaching the # lexer to a new object. In this case, we have to rebind all methods in # the lexstatere and lexstateerrorf tables. if object: newtab = { } for key, ritem in self.lexstatere.items(): newre = [] for cre, findex in ritem: newfindex = [] for f in findex: if not f or not f[0]: newfindex.append(f) continue newfindex.append((getattr(object,f[0].__name__),f[1])) newre.append((cre,newfindex)) newtab[key] = newre c.lexstatere = newtab c.lexstateerrorf = { } for key, ef in self.lexstateerrorf.items(): c.lexstateerrorf[key] = getattr(object,ef.__name__) c.lexmodule = object return c # ------------------------------------------------------------ # writetab() - Write lexer information to a table file # ------------------------------------------------------------ def writetab(self,tabfile,outputdir=""): if isinstance(tabfile,types.ModuleType): return basetabfilename = tabfile.split(".")[-1] filename = os.path.join(outputdir,basetabfilename)+".py" tf = open(filename,"w") tf.write("# %s.py. This file automatically created by PLY (version %s). Don't edit!\n" % (tabfile,__version__)) tf.write("_tabversion = %s\n" % repr(__version__)) tf.write("_lextokens = %s\n" % repr(self.lextokens)) tf.write("_lexreflags = %s\n" % repr(self.lexreflags)) tf.write("_lexliterals = %s\n" % repr(self.lexliterals)) tf.write("_lexstateinfo = %s\n" % repr(self.lexstateinfo)) tabre = { } # Collect all functions in the initial state initial = self.lexstatere["INITIAL"] initialfuncs = [] for part in initial: for f in part[1]: if f and f[0]: initialfuncs.append(f) for key, lre in self.lexstatere.items(): titem = [] for i in range(len(lre)): titem.append((self.lexstateretext[key][i],_funcs_to_names(lre[i][1],self.lexstaterenames[key][i]))) tabre[key] = titem tf.write("_lexstatere = %s\n" % repr(tabre)) tf.write("_lexstateignore = %s\n" % repr(self.lexstateignore)) taberr = { } for key, ef in self.lexstateerrorf.items(): if ef: taberr[key] = ef.__name__ else: taberr[key] = None tf.write("_lexstateerrorf = %s\n" % repr(taberr)) tf.close() # ------------------------------------------------------------ # readtab() - Read lexer information from a tab file # ------------------------------------------------------------ def readtab(self,tabfile,fdict): if isinstance(tabfile,types.ModuleType): lextab = tabfile else: if sys.version_info[0] < 3: exec("import %s as lextab" % tabfile) else: env = { } exec("import %s as lextab" % tabfile, env,env) lextab = env['lextab'] if getattr(lextab,"_tabversion","0.0") != __version__: raise ImportError("Inconsistent PLY version") self.lextokens = lextab._lextokens self.lexreflags = lextab._lexreflags self.lexliterals = lextab._lexliterals self.lexstateinfo = lextab._lexstateinfo self.lexstateignore = lextab._lexstateignore self.lexstatere = { } self.lexstateretext = { } for key,lre in lextab._lexstatere.items(): titem = [] txtitem = [] for i in range(len(lre)): titem.append((re.compile(lre[i][0],lextab._lexreflags),_names_to_funcs(lre[i][1],fdict))) txtitem.append(lre[i][0]) self.lexstatere[key] = titem self.lexstateretext[key] = txtitem self.lexstateerrorf = { } for key,ef in lextab._lexstateerrorf.items(): self.lexstateerrorf[key] = fdict[ef] self.begin('INITIAL') # ------------------------------------------------------------ # input() - Push a new string into the lexer # ------------------------------------------------------------ def input(self,s): # Pull off the first character to see if s looks like a string c = s[:1] if not isinstance(c,StringTypes): raise ValueError("Expected a string") self.lexdata = s self.lexpos = 0 self.lexlen = len(s) # ------------------------------------------------------------ # begin() - Changes the lexing state # ------------------------------------------------------------ def begin(self,state): if not state in self.lexstatere: raise ValueError("Undefined state") self.lexre = self.lexstatere[state] self.lexretext = self.lexstateretext[state] self.lexignore = self.lexstateignore.get(state,"") self.lexerrorf = self.lexstateerrorf.get(state,None) self.lexstate = state # ------------------------------------------------------------ # push_state() - Changes the lexing state and saves old on stack # ------------------------------------------------------------ def push_state(self,state): self.lexstatestack.append(self.lexstate) self.begin(state) # ------------------------------------------------------------ # pop_state() - Restores the previous state # ------------------------------------------------------------ def pop_state(self): self.begin(self.lexstatestack.pop()) # ------------------------------------------------------------ # current_state() - Returns the current lexing state # ------------------------------------------------------------ def current_state(self): return self.lexstate # ------------------------------------------------------------ # skip() - Skip ahead n characters # ------------------------------------------------------------ def skip(self,n): self.lexpos += n # ------------------------------------------------------------ # opttoken() - Return the next token from the Lexer # # Note: This function has been carefully implemented to be as fast # as possible. Don't make changes unless you really know what # you are doing # ------------------------------------------------------------ def token(self): # Make local copies of frequently referenced attributes lexpos = self.lexpos lexlen = self.lexlen lexignore = self.lexignore lexdata = self.lexdata while lexpos < lexlen: # This code provides some short-circuit code for whitespace, tabs, and other ignored characters if lexdata[lexpos] in lexignore: lexpos += 1 continue # Look for a regular expression match for lexre,lexindexfunc in self.lexre: m = lexre.match(lexdata,lexpos) if not m: continue # Create a token for return tok = LexToken() tok.value = m.group() tok.lineno = self.lineno tok.lexpos = lexpos i = m.lastindex func,tok.type = lexindexfunc[i] if not func: # If no token type was set, it's an ignored token if tok.type: self.lexpos = m.end() return tok else: lexpos = m.end() break lexpos = m.end() # If token is processed by a function, call it tok.lexer = self # Set additional attributes useful in token rules self.lexmatch = m self.lexpos = lexpos newtok = func(tok) # Every function must return a token, if nothing, we just move to next token if not newtok: lexpos = self.lexpos # This is here in case user has updated lexpos. lexignore = self.lexignore # This is here in case there was a state change break # Verify type of the token. If not in the token map, raise an error if not self.lexoptimize: if not newtok.type in self.lextokens: raise LexError("%s:%d: Rule '%s' returned an unknown token type '%s'" % ( func_code(func).co_filename, func_code(func).co_firstlineno, func.__name__, newtok.type),lexdata[lexpos:]) return newtok else: # No match, see if in literals if lexdata[lexpos] in self.lexliterals: tok = LexToken() tok.value = lexdata[lexpos] tok.lineno = self.lineno tok.type = tok.value tok.lexpos = lexpos self.lexpos = lexpos + 1 return tok # No match. Call t_error() if defined. if self.lexerrorf: tok = LexToken() tok.value = self.lexdata[lexpos:] tok.lineno = self.lineno tok.type = "error" tok.lexer = self tok.lexpos = lexpos self.lexpos = lexpos newtok = self.lexerrorf(tok) if lexpos == self.lexpos: # Error method didn't change text position at all. This is an error. raise LexError("Scanning error. Illegal character '%s'" % (lexdata[lexpos]), lexdata[lexpos:]) lexpos = self.lexpos if not newtok: continue return newtok self.lexpos = lexpos raise LexError("Illegal character '%s' at index %d" % (lexdata[lexpos],lexpos), lexdata[lexpos:]) self.lexpos = lexpos + 1 if self.lexdata is None: raise RuntimeError("No input string given with input()") return None # Iterator interface def __iter__(self): return self def next(self): t = self.token() if t is None: raise StopIteration return t __next__ = next # ----------------------------------------------------------------------------- # ==== Lex Builder === # # The functions and classes below are used to collect lexing information # and build a Lexer object from it. # ----------------------------------------------------------------------------- # ----------------------------------------------------------------------------- # get_caller_module_dict() # # This function returns a dictionary containing all of the symbols defined within # a caller further down the call stack. This is used to get the environment # associated with the yacc() call if none was provided. # ----------------------------------------------------------------------------- def get_caller_module_dict(levels): try: raise RuntimeError except RuntimeError: e,b,t = sys.exc_info() f = t.tb_frame while levels > 0: f = f.f_back levels -= 1 ldict = f.f_globals.copy() if f.f_globals != f.f_locals: ldict.update(f.f_locals) return ldict # ----------------------------------------------------------------------------- # _funcs_to_names() # # Given a list of regular expression functions, this converts it to a list # suitable for output to a table file # ----------------------------------------------------------------------------- def _funcs_to_names(funclist,namelist): result = [] for f,name in zip(funclist,namelist): if f and f[0]: result.append((name, f[1])) else: result.append(f) return result # ----------------------------------------------------------------------------- # _names_to_funcs() # # Given a list of regular expression function names, this converts it back to # functions. # ----------------------------------------------------------------------------- def _names_to_funcs(namelist,fdict): result = [] for n in namelist: if n and n[0]: result.append((fdict[n[0]],n[1])) else: result.append(n) return result # ----------------------------------------------------------------------------- # _form_master_re() # # This function takes a list of all of the regex components and attempts to # form the master regular expression. Given limitations in the Python re # module, it may be necessary to break the master regex into separate expressions. # ----------------------------------------------------------------------------- def _form_master_re(relist,reflags,ldict,toknames): if not relist: return [] regex = "|".join(relist) try: lexre = re.compile(regex,re.VERBOSE | reflags) # Build the index to function map for the matching engine lexindexfunc = [ None ] * (max(lexre.groupindex.values())+1) lexindexnames = lexindexfunc[:] for f,i in lexre.groupindex.items(): handle = ldict.get(f,None) if type(handle) in (types.FunctionType, types.MethodType): lexindexfunc[i] = (handle,toknames[f]) lexindexnames[i] = f elif handle is not None: lexindexnames[i] = f if f.find("ignore_") > 0: lexindexfunc[i] = (None,None) else: lexindexfunc[i] = (None, toknames[f]) return [(lexre,lexindexfunc)],[regex],[lexindexnames] except Exception: m = int(len(relist)/2) if m == 0: m = 1 llist, lre, lnames = _form_master_re(relist[:m],reflags,ldict,toknames) rlist, rre, rnames = _form_master_re(relist[m:],reflags,ldict,toknames) return llist+rlist, lre+rre, lnames+rnames # ----------------------------------------------------------------------------- # def _statetoken(s,names) # # Given a declaration name s of the form "t_" and a dictionary whose keys are # state names, this function returns a tuple (states,tokenname) where states # is a tuple of state names and tokenname is the name of the token. For example, # calling this with s = "t_foo_bar_SPAM" might return (('foo','bar'),'SPAM') # ----------------------------------------------------------------------------- def _statetoken(s,names): nonstate = 1 parts = s.split("_") for i in range(1,len(parts)): if not parts[i] in names and parts[i] != 'ANY': break if i > 1: states = tuple(parts[1:i]) else: states = ('INITIAL',) if 'ANY' in states: states = tuple(names) tokenname = "_".join(parts[i:]) return (states,tokenname) # ----------------------------------------------------------------------------- # LexerReflect() # # This class represents information needed to build a lexer as extracted from a # user's input file. # ----------------------------------------------------------------------------- class LexerReflect(object): def __init__(self,ldict,log=None,reflags=0): self.ldict = ldict self.error_func = None self.tokens = [] self.reflags = reflags self.stateinfo = { 'INITIAL' : 'inclusive'} self.files = {} self.error = 0 if log is None: self.log = PlyLogger(sys.stderr) else: self.log = log # Get all of the basic information def get_all(self): self.get_tokens() self.get_literals() self.get_states() self.get_rules() # Validate all of the information def validate_all(self): self.validate_tokens() self.validate_literals() self.validate_rules() return self.error # Get the tokens map def get_tokens(self): tokens = self.ldict.get("tokens",None) if not tokens: self.log.error("No token list is defined") self.error = 1 return if not isinstance(tokens,(list, tuple)): self.log.error("tokens must be a list or tuple") self.error = 1 return if not tokens: self.log.error("tokens is empty") self.error = 1 return self.tokens = tokens # Validate the tokens def validate_tokens(self): terminals = {} for n in self.tokens: if not _is_identifier.match(n): self.log.error("Bad token name '%s'",n) self.error = 1 if n in terminals: self.log.warning("Token '%s' multiply defined", n) terminals[n] = 1 # Get the literals specifier def get_literals(self): self.literals = self.ldict.get("literals","") # Validate literals def validate_literals(self): try: for c in self.literals: if not isinstance(c,StringTypes) or len(c) > 1: self.log.error("Invalid literal %s. Must be a single character", repr(c)) self.error = 1 continue except TypeError: self.log.error("Invalid literals specification. literals must be a sequence of characters") self.error = 1 def get_states(self): self.states = self.ldict.get("states",None) # Build statemap if self.states: if not isinstance(self.states,(tuple,list)): self.log.error("states must be defined as a tuple or list") self.error = 1 else: for s in self.states: if not isinstance(s,tuple) or len(s) != 2: self.log.error("Invalid state specifier %s. Must be a tuple (statename,'exclusive|inclusive')",repr(s)) self.error = 1 continue name, statetype = s if not isinstance(name,StringTypes): self.log.error("State name %s must be a string", repr(name)) self.error = 1 continue if not (statetype == 'inclusive' or statetype == 'exclusive'): self.log.error("State type for state %s must be 'inclusive' or 'exclusive'",name) self.error = 1 continue if name in self.stateinfo: self.log.error("State '%s' already defined",name) self.error = 1 continue self.stateinfo[name] = statetype # Get all of the symbols with a t_ prefix and sort them into various # categories (functions, strings, error functions, and ignore characters) def get_rules(self): tsymbols = [f for f in self.ldict if f[:2] == 't_' ] # Now build up a list of functions and a list of strings self.toknames = { } # Mapping of symbols to token names self.funcsym = { } # Symbols defined as functions self.strsym = { } # Symbols defined as strings self.ignore = { } # Ignore strings by state self.errorf = { } # Error functions by state for s in self.stateinfo: self.funcsym[s] = [] self.strsym[s] = [] if len(tsymbols) == 0: self.log.error("No rules of the form t_rulename are defined") self.error = 1 return for f in tsymbols: t = self.ldict[f] states, tokname = _statetoken(f,self.stateinfo) self.toknames[f] = tokname if hasattr(t,"__call__"): if tokname == 'error': for s in states: self.errorf[s] = t elif tokname == 'ignore': line = func_code(t).co_firstlineno file = func_code(t).co_filename self.log.error("%s:%d: Rule '%s' must be defined as a string",file,line,t.__name__) self.error = 1 else: for s in states: self.funcsym[s].append((f,t)) elif isinstance(t, StringTypes): if tokname == 'ignore': for s in states: self.ignore[s] = t if "\\" in t: self.log.warning("%s contains a literal backslash '\\'",f) elif tokname == 'error': self.log.error("Rule '%s' must be defined as a function", f) self.error = 1 else: for s in states: self.strsym[s].append((f,t)) else: self.log.error("%s not defined as a function or string", f) self.error = 1 # Sort the functions by line number for f in self.funcsym.values(): if sys.version_info[0] < 3: f.sort(lambda x,y: cmp(func_code(x[1]).co_firstlineno,func_code(y[1]).co_firstlineno)) else: # Python 3.0 f.sort(key=lambda x: func_code(x[1]).co_firstlineno) # Sort the strings by regular expression length for s in self.strsym.values(): if sys.version_info[0] < 3: s.sort(lambda x,y: (len(x[1]) < len(y[1])) - (len(x[1]) > len(y[1]))) else: # Python 3.0 s.sort(key=lambda x: len(x[1]),reverse=True) # Validate all of the t_rules collected def validate_rules(self): for state in self.stateinfo: # Validate all rules defined by functions for fname, f in self.funcsym[state]: line = func_code(f).co_firstlineno file = func_code(f).co_filename self.files[file] = 1 tokname = self.toknames[fname] if isinstance(f, types.MethodType): reqargs = 2 else: reqargs = 1 nargs = func_code(f).co_argcount if nargs > reqargs: self.log.error("%s:%d: Rule '%s' has too many arguments",file,line,f.__name__) self.error = 1 continue if nargs < reqargs: self.log.error("%s:%d: Rule '%s' requires an argument", file,line,f.__name__) self.error = 1 continue if not f.__doc__: self.log.error("%s:%d: No regular expression defined for rule '%s'",file,line,f.__name__) self.error = 1 continue try: c = re.compile("(?P<%s>%s)" % (fname,f.__doc__), re.VERBOSE | self.reflags) if c.match(""): self.log.error("%s:%d: Regular expression for rule '%s' matches empty string", file,line,f.__name__) self.error = 1 except re.error: _etype, e, _etrace = sys.exc_info() self.log.error("%s:%d: Invalid regular expression for rule '%s'. %s", file,line,f.__name__,e) if '#' in f.__doc__: self.log.error("%s:%d. Make sure '#' in rule '%s' is escaped with '\\#'",file,line, f.__name__) self.error = 1 # Validate all rules defined by strings for name,r in self.strsym[state]: tokname = self.toknames[name] if tokname == 'error': self.log.error("Rule '%s' must be defined as a function", name) self.error = 1 continue if not tokname in self.tokens and tokname.find("ignore_") < 0: self.log.error("Rule '%s' defined for an unspecified token %s",name,tokname) self.error = 1 continue try: c = re.compile("(?P<%s>%s)" % (name,r),re.VERBOSE | self.reflags) if (c.match("")): self.log.error("Regular expression for rule '%s' matches empty string",name) self.error = 1 except re.error: _etype, e, _etrace = sys.exc_info() self.log.error("Invalid regular expression for rule '%s'. %s",name,e) if '#' in r: self.log.error("Make sure '#' in rule '%s' is escaped with '\\#'",name) self.error = 1 if not self.funcsym[state] and not self.strsym[state]: self.log.error("No rules defined for state '%s'",state) self.error = 1 # Validate the error function efunc = self.errorf.get(state,None) if efunc: f = efunc line = func_code(f).co_firstlineno file = func_code(f).co_filename self.files[file] = 1 if isinstance(f, types.MethodType): reqargs = 2 else: reqargs = 1 nargs = func_code(f).co_argcount if nargs > reqargs: self.log.error("%s:%d: Rule '%s' has too many arguments",file,line,f.__name__) self.error = 1 if nargs < reqargs: self.log.error("%s:%d: Rule '%s' requires an argument", file,line,f.__name__) self.error = 1 for f in self.files: self.validate_file(f) # ----------------------------------------------------------------------------- # validate_file() # # This checks to see if there are duplicated t_rulename() functions or strings # in the parser input file. This is done using a simple regular expression # match on each line in the given file. # ----------------------------------------------------------------------------- def validate_file(self,filename): import os.path base,ext = os.path.splitext(filename) if ext != '.py': return # No idea what the file is. Return OK try: f = open(filename) lines = f.readlines() f.close() except IOError: return # Couldn't find the file. Don't worry about it fre = re.compile(r'\s*def\s+(t_[a-zA-Z_0-9]*)\(') sre = re.compile(r'\s*(t_[a-zA-Z_0-9]*)\s*=') counthash = { } linen = 1 for l in lines: m = fre.match(l) if not m: m = sre.match(l) if m: name = m.group(1) prev = counthash.get(name) if not prev: counthash[name] = linen else: self.log.error("%s:%d: Rule %s redefined. Previously defined on line %d",filename,linen,name,prev) self.error = 1 linen += 1 # ----------------------------------------------------------------------------- # lex(module) # # Build all of the regular expression rules from definitions in the supplied module # ----------------------------------------------------------------------------- def lex(module=None,object=None,debug=0,optimize=0,lextab="lextab",reflags=0,nowarn=0,outputdir="", debuglog=None, errorlog=None): global lexer ldict = None stateinfo = { 'INITIAL' : 'inclusive'} lexobj = Lexer() lexobj.lexoptimize = optimize global token,input if errorlog is None: errorlog = PlyLogger(sys.stderr) if debug: if debuglog is None: debuglog = PlyLogger(sys.stderr) # Get the module dictionary used for the lexer if object: module = object if module: _items = [(k,getattr(module,k)) for k in dir(module)] ldict = dict(_items) else: ldict = get_caller_module_dict(2) # Collect parser information from the dictionary linfo = LexerReflect(ldict,log=errorlog,reflags=reflags) linfo.get_all() if not optimize: if linfo.validate_all(): raise SyntaxError("Can't build lexer") if optimize and lextab: try: lexobj.readtab(lextab,ldict) token = lexobj.token input = lexobj.input lexer = lexobj return lexobj except ImportError: pass # Dump some basic debugging information if debug: debuglog.info("lex: tokens = %r", linfo.tokens) debuglog.info("lex: literals = %r", linfo.literals) debuglog.info("lex: states = %r", linfo.stateinfo) # Build a dictionary of valid token names lexobj.lextokens = { } for n in linfo.tokens: lexobj.lextokens[n] = 1 # Get literals specification if isinstance(linfo.literals,(list,tuple)): lexobj.lexliterals = type(linfo.literals[0])().join(linfo.literals) else: lexobj.lexliterals = linfo.literals # Get the stateinfo dictionary stateinfo = linfo.stateinfo regexs = { } # Build the master regular expressions for state in stateinfo: regex_list = [] # Add rules defined by functions first for fname, f in linfo.funcsym[state]: line = func_code(f).co_firstlineno file = func_code(f).co_filename regex_list.append("(?P<%s>%s)" % (fname,f.__doc__)) if debug: debuglog.info("lex: Adding rule %s -> '%s' (state '%s')",fname,f.__doc__, state) # Now add all of the simple rules for name,r in linfo.strsym[state]: regex_list.append("(?P<%s>%s)" % (name,r)) if debug: debuglog.info("lex: Adding rule %s -> '%s' (state '%s')",name,r, state) regexs[state] = regex_list # Build the master regular expressions if debug: debuglog.info("lex: ==== MASTER REGEXS FOLLOW ====") for state in regexs: lexre, re_text, re_names = _form_master_re(regexs[state],reflags,ldict,linfo.toknames) lexobj.lexstatere[state] = lexre lexobj.lexstateretext[state] = re_text lexobj.lexstaterenames[state] = re_names if debug: for i in range(len(re_text)): debuglog.info("lex: state '%s' : regex[%d] = '%s'",state, i, re_text[i]) # For inclusive states, we need to add the regular expressions from the INITIAL state for state,stype in stateinfo.items(): if state != "INITIAL" and stype == 'inclusive': lexobj.lexstatere[state].extend(lexobj.lexstatere['INITIAL']) lexobj.lexstateretext[state].extend(lexobj.lexstateretext['INITIAL']) lexobj.lexstaterenames[state].extend(lexobj.lexstaterenames['INITIAL']) lexobj.lexstateinfo = stateinfo lexobj.lexre = lexobj.lexstatere["INITIAL"] lexobj.lexretext = lexobj.lexstateretext["INITIAL"] # Set up ignore variables lexobj.lexstateignore = linfo.ignore lexobj.lexignore = lexobj.lexstateignore.get("INITIAL","") # Set up error functions lexobj.lexstateerrorf = linfo.errorf lexobj.lexerrorf = linfo.errorf.get("INITIAL",None) if not lexobj.lexerrorf: errorlog.warning("No t_error rule is defined") # Check state information for ignore and error rules for s,stype in stateinfo.items(): if stype == 'exclusive': if not s in linfo.errorf: errorlog.warning("No error rule is defined for exclusive state '%s'", s) if not s in linfo.ignore and lexobj.lexignore: errorlog.warning("No ignore rule is defined for exclusive state '%s'", s) elif stype == 'inclusive': if not s in linfo.errorf: linfo.errorf[s] = linfo.errorf.get("INITIAL",None) if not s in linfo.ignore: linfo.ignore[s] = linfo.ignore.get("INITIAL","") # Create global versions of the token() and input() functions token = lexobj.token input = lexobj.input lexer = lexobj # If in optimize mode, we write the lextab if lextab and optimize: lexobj.writetab(lextab,outputdir) return lexobj # ----------------------------------------------------------------------------- # runmain() # # This runs the lexer as a main program # ----------------------------------------------------------------------------- def runmain(lexer=None,data=None): if not data: try: filename = sys.argv[1] f = open(filename) data = f.read() f.close() except IndexError: sys.stdout.write("Reading from standard input (type EOF to end):\n") data = sys.stdin.read() if lexer: _input = lexer.input else: _input = input _input(data) if lexer: _token = lexer.token else: _token = token while 1: tok = _token() if not tok: break sys.stdout.write("(%s,%r,%d,%d)\n" % (tok.type, tok.value, tok.lineno,tok.lexpos)) # ----------------------------------------------------------------------------- # @TOKEN(regex) # # This decorator function can be used to set the regex expression on a function # when its docstring might need to be set in an alternative way # ----------------------------------------------------------------------------- def TOKEN(r): def set_doc(f): if hasattr(r,"__call__"): f.__doc__ = r.__doc__ else: f.__doc__ = r return f return set_doc # Alternative spelling of the TOKEN decorator Token = TOKEN ./CBFlib-0.9.2.2/ply-3.2/build/lib/ply/ctokens.py0000644000076500007650000000614211603702120017372 0ustar yayayaya# ---------------------------------------------------------------------- # ctokens.py # # Token specifications for symbols in ANSI C and C++. This file is # meant to be used as a library in other tokenizers. # ---------------------------------------------------------------------- # Reserved words tokens = [ # Literals (identifier, integer constant, float constant, string constant, char const) 'ID', 'TYPEID', 'ICONST', 'FCONST', 'SCONST', 'CCONST', # Operators (+,-,*,/,%,|,&,~,^,<<,>>, ||, &&, !, <, <=, >, >=, ==, !=) 'PLUS', 'MINUS', 'TIMES', 'DIVIDE', 'MOD', 'OR', 'AND', 'NOT', 'XOR', 'LSHIFT', 'RSHIFT', 'LOR', 'LAND', 'LNOT', 'LT', 'LE', 'GT', 'GE', 'EQ', 'NE', # Assignment (=, *=, /=, %=, +=, -=, <<=, >>=, &=, ^=, |=) 'EQUALS', 'TIMESEQUAL', 'DIVEQUAL', 'MODEQUAL', 'PLUSEQUAL', 'MINUSEQUAL', 'LSHIFTEQUAL','RSHIFTEQUAL', 'ANDEQUAL', 'XOREQUAL', 'OREQUAL', # Increment/decrement (++,--) 'PLUSPLUS', 'MINUSMINUS', # Structure dereference (->) 'ARROW', # Ternary operator (?) 'TERNARY', # Delimeters ( ) [ ] { } , . ; : 'LPAREN', 'RPAREN', 'LBRACKET', 'RBRACKET', 'LBRACE', 'RBRACE', 'COMMA', 'PERIOD', 'SEMI', 'COLON', # Ellipsis (...) 'ELLIPSIS', ] # Operators t_PLUS = r'\+' t_MINUS = r'-' t_TIMES = r'\*' t_DIVIDE = r'/' t_MODULO = r'%' t_OR = r'\|' t_AND = r'&' t_NOT = r'~' t_XOR = r'\^' t_LSHIFT = r'<<' t_RSHIFT = r'>>' t_LOR = r'\|\|' t_LAND = r'&&' t_LNOT = r'!' t_LT = r'<' t_GT = r'>' t_LE = r'<=' t_GE = r'>=' t_EQ = r'==' t_NE = r'!=' # Assignment operators t_EQUALS = r'=' t_TIMESEQUAL = r'\*=' t_DIVEQUAL = r'/=' t_MODEQUAL = r'%=' t_PLUSEQUAL = r'\+=' t_MINUSEQUAL = r'-=' t_LSHIFTEQUAL = r'<<=' t_RSHIFTEQUAL = r'>>=' t_ANDEQUAL = r'&=' t_OREQUAL = r'\|=' t_XOREQUAL = r'^=' # Increment/decrement t_INCREMENT = r'\+\+' t_DECREMENT = r'--' # -> t_ARROW = r'->' # ? t_TERNARY = r'\?' # Delimeters t_LPAREN = r'\(' t_RPAREN = r'\)' t_LBRACKET = r'\[' t_RBRACKET = r'\]' t_LBRACE = r'\{' t_RBRACE = r'\}' t_COMMA = r',' t_PERIOD = r'\.' t_SEMI = r';' t_COLON = r':' t_ELLIPSIS = r'\.\.\.' # Identifiers t_ID = r'[A-Za-z_][A-Za-z0-9_]*' # Integer literal t_INTEGER = r'\d+([uU]|[lL]|[uU][lL]|[lL][uU])?' # Floating literal t_FLOAT = r'((\d+)(\.\d+)(e(\+|-)?(\d+))? | (\d+)e(\+|-)?(\d+))([lL]|[fF])?' # String literal t_STRING = r'\"([^\\\n]|(\\.))*?\"' # Character constant 'c' or L'c' t_CHARACTER = r'(L)?\'([^\\\n]|(\\.))*?\'' # Comment (C-Style) def t_COMMENT(t): r'/\*(.|\n)*?\*/' t.lexer.lineno += t.value.count('\n') return t # Comment (C++-Style) def t_CPPCOMMENT(t): r'//.*\n' t.lexer.lineno += 1 return t ./CBFlib-0.9.2.2/ply-3.2/build/lib/ply/__init__.py0000644000076500007650000000012211603702120017453 0ustar yayayaya# PLY package # Author: David Beazley (dave@dabeaz.com) __all__ = ['lex','yacc'] ./CBFlib-0.9.2.2/ply-3.2/build/bdist.macosx-10.6-universal/0000755000076500007650000000000011603703074020774 5ustar yayayaya./CBFlib-0.9.2.2/ply-3.2/README0000644000076500007650000002054311603702121013563 0ustar yayayayaPLY (Python Lex-Yacc) Version 3.2 Copyright (C) 2001-2009, David M. Beazley (Dabeaz LLC) All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: * Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. * Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. * Neither the name of the David Beazley or Dabeaz LLC may be used to endorse or promote products derived from this software without specific prior written permission. THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. Introduction ============ PLY is a 100% Python implementation of the common parsing tools lex and yacc. Here are a few highlights: - PLY is very closely modeled after traditional lex/yacc. If you know how to use these tools in C, you will find PLY to be similar. - PLY provides *very* extensive error reporting and diagnostic information to assist in parser construction. The original implementation was developed for instructional purposes. As a result, the system tries to identify the most common types of errors made by novice users. - PLY provides full support for empty productions, error recovery, precedence specifiers, and moderately ambiguous grammars. - Parsing is based on LR-parsing which is fast, memory efficient, better suited to large grammars, and which has a number of nice properties when dealing with syntax errors and other parsing problems. Currently, PLY builds its parsing tables using the LALR(1) algorithm used in yacc. - PLY uses Python introspection features to build lexers and parsers. This greatly simplifies the task of parser construction since it reduces the number of files and eliminates the need to run a separate lex/yacc tool before running your program. - PLY can be used to build parsers for "real" programming languages. Although it is not ultra-fast due to its Python implementation, PLY can be used to parse grammars consisting of several hundred rules (as might be found for a language like C). The lexer and LR parser are also reasonably efficient when parsing typically sized programs. People have used PLY to build parsers for C, C++, ADA, and other real programming languages. How to Use ========== PLY consists of two files : lex.py and yacc.py. These are contained within the 'ply' directory which may also be used as a Python package. To use PLY, simply copy the 'ply' directory to your project and import lex and yacc from the associated 'ply' package. For example: import ply.lex as lex import ply.yacc as yacc Alternatively, you can copy just the files lex.py and yacc.py individually and use them as modules. For example: import lex import yacc The file setup.py can be used to install ply using distutils. The file doc/ply.html contains complete documentation on how to use the system. The example directory contains several different examples including a PLY specification for ANSI C as given in K&R 2nd Ed. A simple example is found at the end of this document Requirements ============ PLY requires the use of Python 2.2 or greater. However, you should use the latest Python release if possible. It should work on just about any platform. PLY has been tested with both CPython and Jython. It also seems to work with IronPython. Resources ========= More information about PLY can be obtained on the PLY webpage at: http://www.dabeaz.com/ply For a detailed overview of parsing theory, consult the excellent book "Compilers : Principles, Techniques, and Tools" by Aho, Sethi, and Ullman. The topics found in "Lex & Yacc" by Levine, Mason, and Brown may also be useful. A Google group for PLY can be found at http://groups.google.com/group/ply-hack Acknowledgments =============== A special thanks is in order for all of the students in CS326 who suffered through about 25 different versions of these tools :-). The CHANGES file acknowledges those who have contributed patches. Elias Ioup did the first implementation of LALR(1) parsing in PLY-1.x. Andrew Waters and Markus Schoepflin were instrumental in reporting bugs and testing a revised LALR(1) implementation for PLY-2.0. Special Note for PLY-3.0 ======================== PLY-3.0 the first PLY release to support Python 3. However, backwards compatibility with Python 2.2 is still preserved. PLY provides dual Python 2/3 compatibility by restricting its implementation to a common subset of basic language features. You should not convert PLY using 2to3--it is not necessary and may in fact break the implementation. Example ======= Here is a simple example showing a PLY implementation of a calculator with variables. # ----------------------------------------------------------------------------- # calc.py # # A simple calculator with variables. # ----------------------------------------------------------------------------- tokens = ( 'NAME','NUMBER', 'PLUS','MINUS','TIMES','DIVIDE','EQUALS', 'LPAREN','RPAREN', ) # Tokens t_PLUS = r'\+' t_MINUS = r'-' t_TIMES = r'\*' t_DIVIDE = r'/' t_EQUALS = r'=' t_LPAREN = r'\(' t_RPAREN = r'\)' t_NAME = r'[a-zA-Z_][a-zA-Z0-9_]*' def t_NUMBER(t): r'\d+' t.value = int(t.value) return t # Ignored characters t_ignore = " \t" def t_newline(t): r'\n+' t.lexer.lineno += t.value.count("\n") def t_error(t): print "Illegal character '%s'" % t.value[0] t.lexer.skip(1) # Build the lexer import ply.lex as lex lex.lex() # Precedence rules for the arithmetic operators precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE'), ('right','UMINUS'), ) # dictionary of names (for storing variables) names = { } def p_statement_assign(p): 'statement : NAME EQUALS expression' names[p[1]] = p[3] def p_statement_expr(p): 'statement : expression' print p[1] def p_expression_binop(p): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if p[2] == '+' : p[0] = p[1] + p[3] elif p[2] == '-': p[0] = p[1] - p[3] elif p[2] == '*': p[0] = p[1] * p[3] elif p[2] == '/': p[0] = p[1] / p[3] def p_expression_uminus(p): 'expression : MINUS expression %prec UMINUS' p[0] = -p[2] def p_expression_group(p): 'expression : LPAREN expression RPAREN' p[0] = p[2] def p_expression_number(p): 'expression : NUMBER' p[0] = p[1] def p_expression_name(p): 'expression : NAME' try: p[0] = names[p[1]] except LookupError: print "Undefined name '%s'" % p[1] p[0] = 0 def p_error(p): print "Syntax error at '%s'" % p.value import ply.yacc as yacc yacc.yacc() while 1: try: s = raw_input('calc > ') except EOFError: break yacc.parse(s) Bug Reports and Patches ======================= My goal with PLY is to simply have a decent lex/yacc implementation for Python. As a general rule, I don't spend huge amounts of time working on it unless I receive very specific bug reports and/or patches to fix problems. I also try to incorporate submitted feature requests and enhancements into each new version. To contact me about bugs and/or new features, please send email to dave@dabeaz.com. In addition there is a Google group for discussing PLY related issues at http://groups.google.com/group/ply-hack -- Dave ./CBFlib-0.9.2.2/ply-3.2/example/0000755000076500007650000000000011603703070014336 5ustar yayayaya./CBFlib-0.9.2.2/ply-3.2/example/calc/0000755000076500007650000000000011603703074015244 5ustar yayayaya./CBFlib-0.9.2.2/ply-3.2/example/calc/calc.py0000644000076500007650000000417511603702121016517 0ustar yayayaya# ----------------------------------------------------------------------------- # calc.py # # A simple calculator with variables. This is from O'Reilly's # "Lex and Yacc", p. 63. # ----------------------------------------------------------------------------- import sys sys.path.insert(0,"../..") if sys.version_info[0] >= 3: raw_input = input tokens = ( 'NAME','NUMBER', ) literals = ['=','+','-','*','/', '(',')'] # Tokens t_NAME = r'[a-zA-Z_][a-zA-Z0-9_]*' def t_NUMBER(t): r'\d+' t.value = int(t.value) return t t_ignore = " \t" def t_newline(t): r'\n+' t.lexer.lineno += t.value.count("\n") def t_error(t): print("Illegal character '%s'" % t.value[0]) t.lexer.skip(1) # Build the lexer import ply.lex as lex lex.lex() # Parsing rules precedence = ( ('left','+','-'), ('left','*','/'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(p): 'statement : NAME "=" expression' names[p[1]] = p[3] def p_statement_expr(p): 'statement : expression' print(p[1]) def p_expression_binop(p): '''expression : expression '+' expression | expression '-' expression | expression '*' expression | expression '/' expression''' if p[2] == '+' : p[0] = p[1] + p[3] elif p[2] == '-': p[0] = p[1] - p[3] elif p[2] == '*': p[0] = p[1] * p[3] elif p[2] == '/': p[0] = p[1] / p[3] def p_expression_uminus(p): "expression : '-' expression %prec UMINUS" p[0] = -p[2] def p_expression_group(p): "expression : '(' expression ')'" p[0] = p[2] def p_expression_number(p): "expression : NUMBER" p[0] = p[1] def p_expression_name(p): "expression : NAME" try: p[0] = names[p[1]] except LookupError: print("Undefined name '%s'" % p[1]) p[0] = 0 def p_error(p): if p: print("Syntax error at '%s'" % p.value) else: print("Syntax error at EOF") import ply.yacc as yacc yacc.yacc() while 1: try: s = raw_input('calc > ') except EOFError: break if not s: continue yacc.parse(s) ./CBFlib-0.9.2.2/ply-3.2/example/yply/0000755000076500007650000000000011603703074015337 5ustar yayayaya./CBFlib-0.9.2.2/ply-3.2/example/yply/README0000644000076500007650000000300311603702121016203 0ustar yayayayayply.py This example implements a program yply.py that converts a UNIX-yacc specification file into a PLY-compatible program. To use, simply run it like this: % python yply.py [-nocode] inputfile.y >myparser.py The output of this program is Python code. In the output, any C code in the original file is included, but is commented out. If you use the -nocode option, then all of the C code in the original file is just discarded. To use the resulting grammer with PLY, you'll need to edit the myparser.py file. Within this file, some stub code is included that can be used to test the construction of the parsing tables. However, you'll need to do more editing to make a workable parser. Disclaimer: This just an example I threw together in an afternoon. It might have some bugs. However, it worked when I tried it on a yacc-specified C++ parser containing 442 rules and 855 parsing states. Comments: 1. This example does not parse specification files meant for lex/flex. You'll need to specify the tokenizer on your own. 2. This example shows a number of interesting PLY features including - Parsing of literal text delimited by nested parentheses - Some interaction between the parser and the lexer. - Use of literals in the grammar specification - One pass compilation. The program just emits the result, there is no intermediate parse tree. 3. This program could probably be cleaned up and enhanced a lot. It would be great if someone wanted to work on this (hint). -Dave ./CBFlib-0.9.2.2/ply-3.2/example/yply/ylex.py0000644000076500007650000000422611603702121016666 0ustar yayayaya# lexer for yacc-grammars # # Author: David Beazley (dave@dabeaz.com) # Date : October 2, 2006 import sys sys.path.append("../..") from ply import * tokens = ( 'LITERAL','SECTION','TOKEN','LEFT','RIGHT','PREC','START','TYPE','NONASSOC','UNION','CODE', 'ID','QLITERAL','NUMBER', ) states = (('code','exclusive'),) literals = [ ';', ',', '<', '>', '|',':' ] t_ignore = ' \t' t_TOKEN = r'%token' t_LEFT = r'%left' t_RIGHT = r'%right' t_NONASSOC = r'%nonassoc' t_PREC = r'%prec' t_START = r'%start' t_TYPE = r'%type' t_UNION = r'%union' t_ID = r'[a-zA-Z_][a-zA-Z_0-9]*' t_QLITERAL = r'''(?P['"]).*?(?P=quote)''' t_NUMBER = r'\d+' def t_SECTION(t): r'%%' if getattr(t.lexer,"lastsection",0): t.value = t.lexer.lexdata[t.lexpos+2:] t.lexer.lexpos = len(t.lexer.lexdata) else: t.lexer.lastsection = 0 return t # Comments def t_ccomment(t): r'/\*(.|\n)*?\*/' t.lexer.lineno += t.value.count('\n') t_ignore_cppcomment = r'//.*' def t_LITERAL(t): r'%\{(.|\n)*?%\}' t.lexer.lineno += t.value.count("\n") return t def t_NEWLINE(t): r'\n' t.lexer.lineno += 1 def t_code(t): r'\{' t.lexer.codestart = t.lexpos t.lexer.level = 1 t.lexer.begin('code') def t_code_ignore_string(t): r'\"([^\\\n]|(\\.))*?\"' def t_code_ignore_char(t): r'\'([^\\\n]|(\\.))*?\'' def t_code_ignore_comment(t): r'/\*(.|\n)*?\*/' def t_code_ignore_cppcom(t): r'//.*' def t_code_lbrace(t): r'\{' t.lexer.level += 1 def t_code_rbrace(t): r'\}' t.lexer.level -= 1 if t.lexer.level == 0: t.type = 'CODE' t.value = t.lexer.lexdata[t.lexer.codestart:t.lexpos+1] t.lexer.begin('INITIAL') t.lexer.lineno += t.value.count('\n') return t t_code_ignore_nonspace = r'[^\s\}\'\"\{]+' t_code_ignore_whitespace = r'\s+' t_code_ignore = "" def t_code_error(t): raise RuntimeError def t_error(t): print "%d: Illegal character '%s'" % (t.lexer.lineno, t.value[0]) print t.value t.lexer.skip(1) lex.lex() if __name__ == '__main__': lex.runmain() ./CBFlib-0.9.2.2/ply-3.2/example/yply/yply.py0000755000076500007650000000232511603702121016703 0ustar yayayaya#!/usr/local/bin/python # yply.py # # Author: David Beazley (dave@dabeaz.com) # Date : October 2, 2006 # # Converts a UNIX-yacc specification file into a PLY-compatible # specification. To use, simply do this: # # % python yply.py [-nocode] inputfile.y >myparser.py # # The output of this program is Python code. In the output, # any C code in the original file is included, but is commented. # If you use the -nocode option, then all of the C code in the # original file is discarded. # # Disclaimer: This just an example I threw together in an afternoon. # It might have some bugs. However, it worked when I tried it on # a yacc-specified C++ parser containing 442 rules and 855 parsing # states. # import sys sys.path.insert(0,"../..") import ylex import yparse from ply import * if len(sys.argv) == 1: print "usage : yply.py [-nocode] inputfile" raise SystemExit if len(sys.argv) == 3: if sys.argv[1] == '-nocode': yparse.emit_code = 0 else: print "Unknown option '%s'" % sys.argv[1] raise SystemExit filename = sys.argv[2] else: filename = sys.argv[1] yacc.parse(open(filename).read()) print """ if __name__ == '__main__': from ply import * yacc.yacc() """ ./CBFlib-0.9.2.2/ply-3.2/example/yply/yparse.py0000644000076500007650000001140211603702121017202 0ustar yayayaya# parser for Unix yacc-based grammars # # Author: David Beazley (dave@dabeaz.com) # Date : October 2, 2006 import ylex tokens = ylex.tokens from ply import * tokenlist = [] preclist = [] emit_code = 1 def p_yacc(p): '''yacc : defsection rulesection''' def p_defsection(p): '''defsection : definitions SECTION | SECTION''' p.lexer.lastsection = 1 print "tokens = ", repr(tokenlist) print print "precedence = ", repr(preclist) print print "# -------------- RULES ----------------" print def p_rulesection(p): '''rulesection : rules SECTION''' print "# -------------- RULES END ----------------" print_code(p[2],0) def p_definitions(p): '''definitions : definitions definition | definition''' def p_definition_literal(p): '''definition : LITERAL''' print_code(p[1],0) def p_definition_start(p): '''definition : START ID''' print "start = '%s'" % p[2] def p_definition_token(p): '''definition : toktype opttype idlist optsemi ''' for i in p[3]: if i[0] not in "'\"": tokenlist.append(i) if p[1] == '%left': preclist.append(('left',) + tuple(p[3])) elif p[1] == '%right': preclist.append(('right',) + tuple(p[3])) elif p[1] == '%nonassoc': preclist.append(('nonassoc',)+ tuple(p[3])) def p_toktype(p): '''toktype : TOKEN | LEFT | RIGHT | NONASSOC''' p[0] = p[1] def p_opttype(p): '''opttype : '<' ID '>' | empty''' def p_idlist(p): '''idlist : idlist optcomma tokenid | tokenid''' if len(p) == 2: p[0] = [p[1]] else: p[0] = p[1] p[1].append(p[3]) def p_tokenid(p): '''tokenid : ID | ID NUMBER | QLITERAL | QLITERAL NUMBER''' p[0] = p[1] def p_optsemi(p): '''optsemi : ';' | empty''' def p_optcomma(p): '''optcomma : ',' | empty''' def p_definition_type(p): '''definition : TYPE '<' ID '>' namelist optsemi''' # type declarations are ignored def p_namelist(p): '''namelist : namelist optcomma ID | ID''' def p_definition_union(p): '''definition : UNION CODE optsemi''' # Union declarations are ignored def p_rules(p): '''rules : rules rule | rule''' if len(p) == 2: rule = p[1] else: rule = p[2] # Print out a Python equivalent of this rule embedded = [ ] # Embedded actions (a mess) embed_count = 0 rulename = rule[0] rulecount = 1 for r in rule[1]: # r contains one of the rule possibilities print "def p_%s_%d(p):" % (rulename,rulecount) prod = [] prodcode = "" for i in range(len(r)): item = r[i] if item[0] == '{': # A code block if i == len(r) - 1: prodcode = item break else: # an embedded action embed_name = "_embed%d_%s" % (embed_count,rulename) prod.append(embed_name) embedded.append((embed_name,item)) embed_count += 1 else: prod.append(item) print " '''%s : %s'''" % (rulename, " ".join(prod)) # Emit code print_code(prodcode,4) print rulecount += 1 for e,code in embedded: print "def p_%s(p):" % e print " '''%s : '''" % e print_code(code,4) print def p_rule(p): '''rule : ID ':' rulelist ';' ''' p[0] = (p[1],[p[3]]) def p_rule2(p): '''rule : ID ':' rulelist morerules ';' ''' p[4].insert(0,p[3]) p[0] = (p[1],p[4]) def p_rule_empty(p): '''rule : ID ':' ';' ''' p[0] = (p[1],[[]]) def p_rule_empty2(p): '''rule : ID ':' morerules ';' ''' p[3].insert(0,[]) p[0] = (p[1],p[3]) def p_morerules(p): '''morerules : morerules '|' rulelist | '|' rulelist | '|' ''' if len(p) == 2: p[0] = [[]] elif len(p) == 3: p[0] = [p[2]] else: p[0] = p[1] p[0].append(p[3]) # print "morerules", len(p), p[0] def p_rulelist(p): '''rulelist : rulelist ruleitem | ruleitem''' if len(p) == 2: p[0] = [p[1]] else: p[0] = p[1] p[1].append(p[2]) def p_ruleitem(p): '''ruleitem : ID | QLITERAL | CODE | PREC''' p[0] = p[1] def p_empty(p): '''empty : ''' def p_error(p): pass yacc.yacc(debug=0) def print_code(code,indent): if not emit_code: return codelines = code.splitlines() for c in codelines: print "%s# %s" % (" "*indent,c) ./CBFlib-0.9.2.2/ply-3.2/example/BASIC/0000755000076500007650000000000011603703074015163 5ustar yayayaya./CBFlib-0.9.2.2/ply-3.2/example/BASIC/linear.bas0000644000076500007650000000064411603702121017120 0ustar yayayaya1 REM ::: SOLVE A SYSTEM OF LINEAR EQUATIONS 2 REM ::: A1*X1 + A2*X2 = B1 3 REM ::: A3*X1 + A4*X2 = B2 4 REM -------------------------------------- 10 READ A1, A2, A3, A4 15 LET D = A1 * A4 - A3 * A2 20 IF D = 0 THEN 65 30 READ B1, B2 37 LET X1 = (B1*A4 - B2*A2) / D 42 LET X2 = (A1*B2 - A3*B1) / D 55 PRINT X1, X2 60 GOTO 30 65 PRINT "NO UNIQUE SOLUTION" 70 DATA 1, 2, 4 80 DATA 2, -7, 5 85 DATA 1, 3, 4, -7 90 END ./CBFlib-0.9.2.2/ply-3.2/example/BASIC/dim.bas0000644000076500007650000000034011603702121016410 0ustar yayayaya5 DIM A(50,15) 10 FOR I = 1 TO 50 20 FOR J = 1 TO 15 30 LET A(I,J) = I + J 35 REM PRINT I,J, A(I,J) 40 NEXT J 50 NEXT I 100 FOR I = 1 TO 50 110 FOR J = 1 TO 15 120 PRINT A(I,J), 130 NEXT J 140 PRINT 150 NEXT I 999 END ./CBFlib-0.9.2.2/ply-3.2/example/BASIC/func.bas0000644000076500007650000000011111603702121016566 0ustar yayayaya10 DEF FDX(X) = 2*X 20 FOR I = 0 TO 100 30 PRINT FDX(I) 40 NEXT I 50 END ./CBFlib-0.9.2.2/ply-3.2/example/BASIC/README0000644000076500007650000000471711603702121016044 0ustar yayayayaInspired by a September 14, 2006 Salon article "Why Johnny Can't Code" by David Brin (http://www.salon.com/tech/feature/2006/09/14/basic/index.html), I thought that a fully working BASIC interpreter might be an interesting, if not questionable, PLY example. Uh, okay, so maybe it's just a bad idea, but in any case, here it is. In this example, you'll find a rough implementation of 1964 Dartmouth BASIC as described in the manual at: http://www.bitsavers.org/pdf/dartmouth/BASIC_Oct64.pdf See also: http://en.wikipedia.org/wiki/Dartmouth_BASIC This dialect is downright primitive---there are no string variables and no facilities for interactive input. Moreover, subroutines and functions are brain-dead even more than they usually are for BASIC. Of course, the GOTO statement is provided. Nevertheless, there are a few interesting aspects of this example: - It illustrates a fully working interpreter including lexing, parsing, and interpretation of instructions. - The parser shows how to catch and report various kinds of parsing errors in a more graceful way. - The example both parses files (supplied on command line) and interactive input entered line by line. - It shows how you might represent parsed information. In this case, each BASIC statement is encoded into a Python tuple containing the statement type and parameters. These tuples are then stored in a dictionary indexed by program line numbers. - Even though it's just BASIC, the parser contains more than 80 rules and 150 parsing states. Thus, it's a little more meaty than the calculator example. To use the example, run it as follows: % python basic.py hello.bas HELLO WORLD % or use it interactively: % python basic.py [BASIC] 10 PRINT "HELLO WORLD" [BASIC] 20 END [BASIC] RUN HELLO WORLD [BASIC] The following files are defined: basic.py - High level script that controls everything basiclex.py - BASIC tokenizer basparse.py - BASIC parser basinterp.py - BASIC interpreter that runs parsed programs. In addition, a number of sample BASIC programs (.bas suffix) are provided. These were taken out of the Dartmouth manual. Disclaimer: I haven't spent a ton of time testing this and it's likely that I've skimped here and there on a few finer details (e.g., strictly enforcing variable naming rules). However, the interpreter seems to be able to run the examples in the BASIC manual. Have fun! -Dave ./CBFlib-0.9.2.2/ply-3.2/example/BASIC/powers.bas0000644000076500007650000000041411603702121017160 0ustar yayayaya5 PRINT "THIS PROGRAM COMPUTES AND PRINTS THE NTH POWERS" 6 PRINT "OF THE NUMBERS LESS THAN OR EQUAL TO N FOR VARIOUS" 7 PRINT "N FROM 1 THROUGH 7" 8 PRINT 10 FOR N = 1 TO 7 15 PRINT "N = "N 20 FOR I = 1 TO N 30 PRINT I^N, 40 NEXT I 50 PRINT 60 PRINT 70 NEXT N 80 END ./CBFlib-0.9.2.2/ply-3.2/example/BASIC/basiclex.py0000644000076500007650000000223111603702121017315 0ustar yayayaya# An implementation of Dartmouth BASIC (1964) from ply import * keywords = ( 'LET','READ','DATA','PRINT','GOTO','IF','THEN','FOR','NEXT','TO','STEP', 'END','STOP','DEF','GOSUB','DIM','REM','RETURN','RUN','LIST','NEW', ) tokens = keywords + ( 'EQUALS','PLUS','MINUS','TIMES','DIVIDE','POWER', 'LPAREN','RPAREN','LT','LE','GT','GE','NE', 'COMMA','SEMI', 'INTEGER','FLOAT', 'STRING', 'ID','NEWLINE' ) t_ignore = ' \t' def t_REM(t): r'REM .*' return t def t_ID(t): r'[A-Z][A-Z0-9]*' if t.value in keywords: t.type = t.value return t t_EQUALS = r'=' t_PLUS = r'\+' t_MINUS = r'-' t_TIMES = r'\*' t_POWER = r'\^' t_DIVIDE = r'/' t_LPAREN = r'\(' t_RPAREN = r'\)' t_LT = r'<' t_LE = r'<=' t_GT = r'>' t_GE = r'>=' t_NE = r'<>' t_COMMA = r'\,' t_SEMI = r';' t_INTEGER = r'\d+' t_FLOAT = r'((\d*\.\d+)(E[\+-]?\d+)?|([1-9]\d*E[\+-]?\d+))' t_STRING = r'\".*?\"' def t_NEWLINE(t): r'\n' t.lexer.lineno += 1 return t def t_error(t): print("Illegal character %s" % t.value[0]) t.lexer.skip(1) lex.lex(debug=0) ./CBFlib-0.9.2.2/ply-3.2/example/BASIC/basiclog.py0000644000076500007650000000323611603702121017314 0ustar yayayaya# An implementation of Dartmouth BASIC (1964) # import sys sys.path.insert(0,"../..") if sys.version_info[0] >= 3: raw_input = input import logging logging.basicConfig( level = logging.INFO, filename = "parselog.txt", filemode = "w" ) log = logging.getLogger() import basiclex import basparse import basinterp # If a filename has been specified, we try to run it. # If a runtime error occurs, we bail out and enter # interactive mode below if len(sys.argv) == 2: data = open(sys.argv[1]).read() prog = basparse.parse(data,debug=log) if not prog: raise SystemExit b = basinterp.BasicInterpreter(prog) try: b.run() raise SystemExit except RuntimeError: pass else: b = basinterp.BasicInterpreter({}) # Interactive mode. This incrementally adds/deletes statements # from the program stored in the BasicInterpreter object. In # addition, special commands 'NEW','LIST',and 'RUN' are added. # Specifying a line number with no code deletes that line from # the program. while 1: try: line = raw_input("[BASIC] ") except EOFError: raise SystemExit if not line: continue line += "\n" prog = basparse.parse(line,debug=log) if not prog: continue keys = list(prog) if keys[0] > 0: b.add_statements(prog) else: stat = prog[keys[0]] if stat[0] == 'RUN': try: b.run() except RuntimeError: pass elif stat[0] == 'LIST': b.list() elif stat[0] == 'BLANK': b.del_line(stat[1]) elif stat[0] == 'NEW': b.new() ./CBFlib-0.9.2.2/ply-3.2/example/BASIC/sqrt1.bas0000644000076500007650000000011611603702121016712 0ustar yayayaya10 LET X = 0 20 LET X = X + 1 30 PRINT X, SQR(X) 40 IF X < 100 THEN 20 50 END ./CBFlib-0.9.2.2/ply-3.2/example/BASIC/sqrt2.bas0000644000076500007650000000007011603702121016712 0ustar yayayaya10 FOR X = 1 TO 100 20 PRINT X, SQR(X) 30 NEXT X 40 END ./CBFlib-0.9.2.2/ply-3.2/example/BASIC/gosub.bas0000644000076500007650000000033011603702121016755 0ustar yayayaya100 LET X = 3 110 GOSUB 400 120 PRINT U, V, W 200 LET X = 5 210 GOSUB 400 220 LET Z = U + 2*V + 3*W 230 PRINT Z 240 GOTO 999 400 LET U = X*X 410 LET V = X*X*X 420 LET W = X*X*X*X + X*X*X + X*X + X 430 RETURN 999 END ./CBFlib-0.9.2.2/ply-3.2/example/BASIC/basparse.py0000644000076500007650000002130311603702121017324 0ustar yayayaya# An implementation of Dartmouth BASIC (1964) # from ply import * import basiclex tokens = basiclex.tokens precedence = ( ('left', 'PLUS','MINUS'), ('left', 'TIMES','DIVIDE'), ('left', 'POWER'), ('right','UMINUS') ) #### A BASIC program is a series of statements. We represent the program as a #### dictionary of tuples indexed by line number. def p_program(p): '''program : program statement | statement''' if len(p) == 2 and p[1]: p[0] = { } line,stat = p[1] p[0][line] = stat elif len(p) ==3: p[0] = p[1] if not p[0]: p[0] = { } if p[2]: line,stat = p[2] p[0][line] = stat #### This catch-all rule is used for any catastrophic errors. In this case, #### we simply return nothing def p_program_error(p): '''program : error''' p[0] = None p.parser.error = 1 #### Format of all BASIC statements. def p_statement(p): '''statement : INTEGER command NEWLINE''' if isinstance(p[2],str): print("%s %s %s" % (p[2],"AT LINE", p[1])) p[0] = None p.parser.error = 1 else: lineno = int(p[1]) p[0] = (lineno,p[2]) #### Interactive statements. def p_statement_interactive(p): '''statement : RUN NEWLINE | LIST NEWLINE | NEW NEWLINE''' p[0] = (0, (p[1],0)) #### Blank line number def p_statement_blank(p): '''statement : INTEGER NEWLINE''' p[0] = (0,('BLANK',int(p[1]))) #### Error handling for malformed statements def p_statement_bad(p): '''statement : INTEGER error NEWLINE''' print("MALFORMED STATEMENT AT LINE %s" % p[1]) p[0] = None p.parser.error = 1 #### Blank line def p_statement_newline(p): '''statement : NEWLINE''' p[0] = None #### LET statement def p_command_let(p): '''command : LET variable EQUALS expr''' p[0] = ('LET',p[2],p[4]) def p_command_let_bad(p): '''command : LET variable EQUALS error''' p[0] = "BAD EXPRESSION IN LET" #### READ statement def p_command_read(p): '''command : READ varlist''' p[0] = ('READ',p[2]) def p_command_read_bad(p): '''command : READ error''' p[0] = "MALFORMED VARIABLE LIST IN READ" #### DATA statement def p_command_data(p): '''command : DATA numlist''' p[0] = ('DATA',p[2]) def p_command_data_bad(p): '''command : DATA error''' p[0] = "MALFORMED NUMBER LIST IN DATA" #### PRINT statement def p_command_print(p): '''command : PRINT plist optend''' p[0] = ('PRINT',p[2],p[3]) def p_command_print_bad(p): '''command : PRINT error''' p[0] = "MALFORMED PRINT STATEMENT" #### Optional ending on PRINT. Either a comma (,) or semicolon (;) def p_optend(p): '''optend : COMMA | SEMI |''' if len(p) == 2: p[0] = p[1] else: p[0] = None #### PRINT statement with no arguments def p_command_print_empty(p): '''command : PRINT''' p[0] = ('PRINT',[],None) #### GOTO statement def p_command_goto(p): '''command : GOTO INTEGER''' p[0] = ('GOTO',int(p[2])) def p_command_goto_bad(p): '''command : GOTO error''' p[0] = "INVALID LINE NUMBER IN GOTO" #### IF-THEN statement def p_command_if(p): '''command : IF relexpr THEN INTEGER''' p[0] = ('IF',p[2],int(p[4])) def p_command_if_bad(p): '''command : IF error THEN INTEGER''' p[0] = "BAD RELATIONAL EXPRESSION" def p_command_if_bad2(p): '''command : IF relexpr THEN error''' p[0] = "INVALID LINE NUMBER IN THEN" #### FOR statement def p_command_for(p): '''command : FOR ID EQUALS expr TO expr optstep''' p[0] = ('FOR',p[2],p[4],p[6],p[7]) def p_command_for_bad_initial(p): '''command : FOR ID EQUALS error TO expr optstep''' p[0] = "BAD INITIAL VALUE IN FOR STATEMENT" def p_command_for_bad_final(p): '''command : FOR ID EQUALS expr TO error optstep''' p[0] = "BAD FINAL VALUE IN FOR STATEMENT" def p_command_for_bad_step(p): '''command : FOR ID EQUALS expr TO expr STEP error''' p[0] = "MALFORMED STEP IN FOR STATEMENT" #### Optional STEP qualifier on FOR statement def p_optstep(p): '''optstep : STEP expr | empty''' if len(p) == 3: p[0] = p[2] else: p[0] = None #### NEXT statement def p_command_next(p): '''command : NEXT ID''' p[0] = ('NEXT',p[2]) def p_command_next_bad(p): '''command : NEXT error''' p[0] = "MALFORMED NEXT" #### END statement def p_command_end(p): '''command : END''' p[0] = ('END',) #### REM statement def p_command_rem(p): '''command : REM''' p[0] = ('REM',p[1]) #### STOP statement def p_command_stop(p): '''command : STOP''' p[0] = ('STOP',) #### DEF statement def p_command_def(p): '''command : DEF ID LPAREN ID RPAREN EQUALS expr''' p[0] = ('FUNC',p[2],p[4],p[7]) def p_command_def_bad_rhs(p): '''command : DEF ID LPAREN ID RPAREN EQUALS error''' p[0] = "BAD EXPRESSION IN DEF STATEMENT" def p_command_def_bad_arg(p): '''command : DEF ID LPAREN error RPAREN EQUALS expr''' p[0] = "BAD ARGUMENT IN DEF STATEMENT" #### GOSUB statement def p_command_gosub(p): '''command : GOSUB INTEGER''' p[0] = ('GOSUB',int(p[2])) def p_command_gosub_bad(p): '''command : GOSUB error''' p[0] = "INVALID LINE NUMBER IN GOSUB" #### RETURN statement def p_command_return(p): '''command : RETURN''' p[0] = ('RETURN',) #### DIM statement def p_command_dim(p): '''command : DIM dimlist''' p[0] = ('DIM',p[2]) def p_command_dim_bad(p): '''command : DIM error''' p[0] = "MALFORMED VARIABLE LIST IN DIM" #### List of variables supplied to DIM statement def p_dimlist(p): '''dimlist : dimlist COMMA dimitem | dimitem''' if len(p) == 4: p[0] = p[1] p[0].append(p[3]) else: p[0] = [p[1]] #### DIM items def p_dimitem_single(p): '''dimitem : ID LPAREN INTEGER RPAREN''' p[0] = (p[1],eval(p[3]),0) def p_dimitem_double(p): '''dimitem : ID LPAREN INTEGER COMMA INTEGER RPAREN''' p[0] = (p[1],eval(p[3]),eval(p[5])) #### Arithmetic expressions def p_expr_binary(p): '''expr : expr PLUS expr | expr MINUS expr | expr TIMES expr | expr DIVIDE expr | expr POWER expr''' p[0] = ('BINOP',p[2],p[1],p[3]) def p_expr_number(p): '''expr : INTEGER | FLOAT''' p[0] = ('NUM',eval(p[1])) def p_expr_variable(p): '''expr : variable''' p[0] = ('VAR',p[1]) def p_expr_group(p): '''expr : LPAREN expr RPAREN''' p[0] = ('GROUP',p[2]) def p_expr_unary(p): '''expr : MINUS expr %prec UMINUS''' p[0] = ('UNARY','-',p[2]) #### Relational expressions def p_relexpr(p): '''relexpr : expr LT expr | expr LE expr | expr GT expr | expr GE expr | expr EQUALS expr | expr NE expr''' p[0] = ('RELOP',p[2],p[1],p[3]) #### Variables def p_variable(p): '''variable : ID | ID LPAREN expr RPAREN | ID LPAREN expr COMMA expr RPAREN''' if len(p) == 2: p[0] = (p[1],None,None) elif len(p) == 5: p[0] = (p[1],p[3],None) else: p[0] = (p[1],p[3],p[5]) #### Builds a list of variable targets as a Python list def p_varlist(p): '''varlist : varlist COMMA variable | variable''' if len(p) > 2: p[0] = p[1] p[0].append(p[3]) else: p[0] = [p[1]] #### Builds a list of numbers as a Python list def p_numlist(p): '''numlist : numlist COMMA number | number''' if len(p) > 2: p[0] = p[1] p[0].append(p[3]) else: p[0] = [p[1]] #### A number. May be an integer or a float def p_number(p): '''number : INTEGER | FLOAT''' p[0] = eval(p[1]) #### A signed number. def p_number_signed(p): '''number : MINUS INTEGER | MINUS FLOAT''' p[0] = eval("-"+p[2]) #### List of targets for a print statement #### Returns a list of tuples (label,expr) def p_plist(p): '''plist : plist COMMA pitem | pitem''' if len(p) > 3: p[0] = p[1] p[0].append(p[3]) else: p[0] = [p[1]] def p_item_string(p): '''pitem : STRING''' p[0] = (p[1][1:-1],None) def p_item_string_expr(p): '''pitem : STRING expr''' p[0] = (p[1][1:-1],p[2]) def p_item_expr(p): '''pitem : expr''' p[0] = ("",p[1]) #### Empty def p_empty(p): '''empty : ''' #### Catastrophic error handler def p_error(p): if not p: print("SYNTAX ERROR AT EOF") bparser = yacc.yacc() def parse(data,debug=0): bparser.error = 0 p = bparser.parse(data,debug=debug) if bparser.error: return None return p ./CBFlib-0.9.2.2/ply-3.2/example/BASIC/gcd.bas0000644000076500007650000000054711603702121016405 0ustar yayayaya10 PRINT "A","B","C","GCD" 20 READ A,B,C 30 LET X = A 40 LET Y = B 50 GOSUB 200 60 LET X = G 70 LET Y = C 80 GOSUB 200 90 PRINT A, B, C, G 100 GOTO 20 110 DATA 60, 90, 120 120 DATA 38456, 64872, 98765 130 DATA 32, 384, 72 200 LET Q = INT(X/Y) 210 LET R = X - Q*Y 220 IF R = 0 THEN 300 230 LET X = Y 240 LET Y = R 250 GOTO 200 300 LET G = Y 310 RETURN 999 END ./CBFlib-0.9.2.2/ply-3.2/example/BASIC/rand.bas0000644000076500007650000000007411603702121016567 0ustar yayayaya10 FOR I = 1 TO 20 20 PRINT INT(10*RND(0)) 30 NEXT I 40 END ./CBFlib-0.9.2.2/ply-3.2/example/BASIC/basinterp.py0000644000076500007650000004160411603702121017521 0ustar yayayaya# This file provides the runtime support for running a basic program # Assumes the program has been parsed using basparse.py import sys import math import random class BasicInterpreter: # Initialize the interpreter. prog is a dictionary # containing (line,statement) mappings def __init__(self,prog): self.prog = prog self.functions = { # Built-in function table 'SIN' : lambda z: math.sin(self.eval(z)), 'COS' : lambda z: math.cos(self.eval(z)), 'TAN' : lambda z: math.tan(self.eval(z)), 'ATN' : lambda z: math.atan(self.eval(z)), 'EXP' : lambda z: math.exp(self.eval(z)), 'ABS' : lambda z: abs(self.eval(z)), 'LOG' : lambda z: math.log(self.eval(z)), 'SQR' : lambda z: math.sqrt(self.eval(z)), 'INT' : lambda z: int(self.eval(z)), 'RND' : lambda z: random.random() } # Collect all data statements def collect_data(self): self.data = [] for lineno in self.stat: if self.prog[lineno][0] == 'DATA': self.data = self.data + self.prog[lineno][1] self.dc = 0 # Initialize the data counter # Check for end statements def check_end(self): has_end = 0 for lineno in self.stat: if self.prog[lineno][0] == 'END' and not has_end: has_end = lineno if not has_end: print("NO END INSTRUCTION") self.error = 1 return if has_end != lineno: print("END IS NOT LAST") self.error = 1 # Check loops def check_loops(self): for pc in range(len(self.stat)): lineno = self.stat[pc] if self.prog[lineno][0] == 'FOR': forinst = self.prog[lineno] loopvar = forinst[1] for i in range(pc+1,len(self.stat)): if self.prog[self.stat[i]][0] == 'NEXT': nextvar = self.prog[self.stat[i]][1] if nextvar != loopvar: continue self.loopend[pc] = i break else: print("FOR WITHOUT NEXT AT LINE %s" % self.stat[pc]) self.error = 1 # Evaluate an expression def eval(self,expr): etype = expr[0] if etype == 'NUM': return expr[1] elif etype == 'GROUP': return self.eval(expr[1]) elif etype == 'UNARY': if expr[1] == '-': return -self.eval(expr[2]) elif etype == 'BINOP': if expr[1] == '+': return self.eval(expr[2])+self.eval(expr[3]) elif expr[1] == '-': return self.eval(expr[2])-self.eval(expr[3]) elif expr[1] == '*': return self.eval(expr[2])*self.eval(expr[3]) elif expr[1] == '/': return float(self.eval(expr[2]))/self.eval(expr[3]) elif expr[1] == '^': return abs(self.eval(expr[2]))**self.eval(expr[3]) elif etype == 'VAR': var,dim1,dim2 = expr[1] if not dim1 and not dim2: if var in self.vars: return self.vars[var] else: print("UNDEFINED VARIABLE %s AT LINE %s" % (var, self.stat[self.pc])) raise RuntimeError # May be a list lookup or a function evaluation if dim1 and not dim2: if var in self.functions: # A function return self.functions[var](dim1) else: # A list evaluation if var in self.lists: dim1val = self.eval(dim1) if dim1val < 1 or dim1val > len(self.lists[var]): print("LIST INDEX OUT OF BOUNDS AT LINE %s" % self.stat[self.pc]) raise RuntimeError return self.lists[var][dim1val-1] if dim1 and dim2: if var in self.tables: dim1val = self.eval(dim1) dim2val = self.eval(dim2) if dim1val < 1 or dim1val > len(self.tables[var]) or dim2val < 1 or dim2val > len(self.tables[var][0]): print("TABLE INDEX OUT OUT BOUNDS AT LINE %s" % self.stat[self.pc]) raise RuntimeError return self.tables[var][dim1val-1][dim2val-1] print("UNDEFINED VARIABLE %s AT LINE %s" % (var, self.stat[self.pc])) raise RuntimeError # Evaluate a relational expression def releval(self,expr): etype = expr[1] lhs = self.eval(expr[2]) rhs = self.eval(expr[3]) if etype == '<': if lhs < rhs: return 1 else: return 0 elif etype == '<=': if lhs <= rhs: return 1 else: return 0 elif etype == '>': if lhs > rhs: return 1 else: return 0 elif etype == '>=': if lhs >= rhs: return 1 else: return 0 elif etype == '=': if lhs == rhs: return 1 else: return 0 elif etype == '<>': if lhs != rhs: return 1 else: return 0 # Assignment def assign(self,target,value): var, dim1, dim2 = target if not dim1 and not dim2: self.vars[var] = self.eval(value) elif dim1 and not dim2: # List assignment dim1val = self.eval(dim1) if not var in self.lists: self.lists[var] = [0]*10 if dim1val > len(self.lists[var]): print ("DIMENSION TOO LARGE AT LINE %s" % self.stat[self.pc]) raise RuntimeError self.lists[var][dim1val-1] = self.eval(value) elif dim1 and dim2: dim1val = self.eval(dim1) dim2val = self.eval(dim2) if not var in self.tables: temp = [0]*10 v = [] for i in range(10): v.append(temp[:]) self.tables[var] = v # Variable already exists if dim1val > len(self.tables[var]) or dim2val > len(self.tables[var][0]): print("DIMENSION TOO LARGE AT LINE %s" % self.stat[self.pc]) raise RuntimeError self.tables[var][dim1val-1][dim2val-1] = self.eval(value) # Change the current line number def goto(self,linenum): if not linenum in self.prog: print("UNDEFINED LINE NUMBER %d AT LINE %d" % (linenum, self.stat[self.pc])) raise RuntimeError self.pc = self.stat.index(linenum) # Run it def run(self): self.vars = { } # All variables self.lists = { } # List variables self.tables = { } # Tables self.loops = [ ] # Currently active loops self.loopend= { } # Mapping saying where loops end self.gosub = None # Gosub return point (if any) self.error = 0 # Indicates program error self.stat = list(self.prog) # Ordered list of all line numbers self.stat.sort() self.pc = 0 # Current program counter # Processing prior to running self.collect_data() # Collect all of the data statements self.check_end() self.check_loops() if self.error: raise RuntimeError while 1: line = self.stat[self.pc] instr = self.prog[line] op = instr[0] # END and STOP statements if op == 'END' or op == 'STOP': break # We're done # GOTO statement elif op == 'GOTO': newline = instr[1] self.goto(newline) continue # PRINT statement elif op == 'PRINT': plist = instr[1] out = "" for label,val in plist: if out: out += ' '*(15 - (len(out) % 15)) out += label if val: if label: out += " " eval = self.eval(val) out += str(eval) sys.stdout.write(out) end = instr[2] if not (end == ',' or end == ';'): sys.stdout.write("\n") if end == ',': sys.stdout.write(" "*(15-(len(out) % 15))) if end == ';': sys.stdout.write(" "*(3-(len(out) % 3))) # LET statement elif op == 'LET': target = instr[1] value = instr[2] self.assign(target,value) # READ statement elif op == 'READ': for target in instr[1]: if self.dc < len(self.data): value = ('NUM',self.data[self.dc]) self.assign(target,value) self.dc += 1 else: # No more data. Program ends return elif op == 'IF': relop = instr[1] newline = instr[2] if (self.releval(relop)): self.goto(newline) continue elif op == 'FOR': loopvar = instr[1] initval = instr[2] finval = instr[3] stepval = instr[4] # Check to see if this is a new loop if not self.loops or self.loops[-1][0] != self.pc: # Looks like a new loop. Make the initial assignment newvalue = initval self.assign((loopvar,None,None),initval) if not stepval: stepval = ('NUM',1) stepval = self.eval(stepval) # Evaluate step here self.loops.append((self.pc,stepval)) else: # It's a repeat of the previous loop # Update the value of the loop variable according to the step stepval = ('NUM',self.loops[-1][1]) newvalue = ('BINOP','+',('VAR',(loopvar,None,None)),stepval) if self.loops[-1][1] < 0: relop = '>=' else: relop = '<=' if not self.releval(('RELOP',relop,newvalue,finval)): # Loop is done. Jump to the NEXT self.pc = self.loopend[self.pc] self.loops.pop() else: self.assign((loopvar,None,None),newvalue) elif op == 'NEXT': if not self.loops: print("NEXT WITHOUT FOR AT LINE %s" % line) return nextvar = instr[1] self.pc = self.loops[-1][0] loopinst = self.prog[self.stat[self.pc]] forvar = loopinst[1] if nextvar != forvar: print("NEXT DOESN'T MATCH FOR AT LINE %s" % line) return continue elif op == 'GOSUB': newline = instr[1] if self.gosub: print("ALREADY IN A SUBROUTINE AT LINE %s" % line) return self.gosub = self.stat[self.pc] self.goto(newline) continue elif op == 'RETURN': if not self.gosub: print("RETURN WITHOUT A GOSUB AT LINE %s" % line) return self.goto(self.gosub) self.gosub = None elif op == 'FUNC': fname = instr[1] pname = instr[2] expr = instr[3] def eval_func(pvalue,name=pname,self=self,expr=expr): self.assign((pname,None,None),pvalue) return self.eval(expr) self.functions[fname] = eval_func elif op == 'DIM': for vname,x,y in instr[1]: if y == 0: # Single dimension variable self.lists[vname] = [0]*x else: # Double dimension variable temp = [0]*y v = [] for i in range(x): v.append(temp[:]) self.tables[vname] = v self.pc += 1 # Utility functions for program listing def expr_str(self,expr): etype = expr[0] if etype == 'NUM': return str(expr[1]) elif etype == 'GROUP': return "(%s)" % self.expr_str(expr[1]) elif etype == 'UNARY': if expr[1] == '-': return "-"+str(expr[2]) elif etype == 'BINOP': return "%s %s %s" % (self.expr_str(expr[2]),expr[1],self.expr_str(expr[3])) elif etype == 'VAR': return self.var_str(expr[1]) def relexpr_str(self,expr): return "%s %s %s" % (self.expr_str(expr[2]),expr[1],self.expr_str(expr[3])) def var_str(self,var): varname,dim1,dim2 = var if not dim1 and not dim2: return varname if dim1 and not dim2: return "%s(%s)" % (varname, self.expr_str(dim1)) return "%s(%s,%s)" % (varname, self.expr_str(dim1),self.expr_str(dim2)) # Create a program listing def list(self): stat = list(self.prog) # Ordered list of all line numbers stat.sort() for line in stat: instr = self.prog[line] op = instr[0] if op in ['END','STOP','RETURN']: print("%s %s" % (line, op)) continue elif op == 'REM': print("%s %s" % (line, instr[1])) elif op == 'PRINT': _out = "%s %s " % (line, op) first = 1 for p in instr[1]: if not first: _out += ", " if p[0] and p[1]: _out += '"%s"%s' % (p[0],self.expr_str(p[1])) elif p[1]: _out += self.expr_str(p[1]) else: _out += '"%s"' % (p[0],) first = 0 if instr[2]: _out += instr[2] print(_out) elif op == 'LET': print("%s LET %s = %s" % (line,self.var_str(instr[1]),self.expr_str(instr[2]))) elif op == 'READ': _out = "%s READ " % line first = 1 for r in instr[1]: if not first: _out += "," _out += self.var_str(r) first = 0 print(_out) elif op == 'IF': print("%s IF %s THEN %d" % (line,self.relexpr_str(instr[1]),instr[2])) elif op == 'GOTO' or op == 'GOSUB': print("%s %s %s" % (line, op, instr[1])) elif op == 'FOR': _out = "%s FOR %s = %s TO %s" % (line,instr[1],self.expr_str(instr[2]),self.expr_str(instr[3])) if instr[4]: _out += " STEP %s" % (self.expr_str(instr[4])) print(_out) elif op == 'NEXT': print("%s NEXT %s" % (line, instr[1])) elif op == 'FUNC': print("%s DEF %s(%s) = %s" % (line,instr[1],instr[2],self.expr_str(instr[3]))) elif op == 'DIM': _out = "%s DIM " % line first = 1 for vname,x,y in instr[1]: if not first: _out += "," first = 0 if y == 0: _out += "%s(%d)" % (vname,x) else: _out += "%s(%d,%d)" % (vname,x,y) print(_out) elif op == 'DATA': _out = "%s DATA " % line first = 1 for v in instr[1]: if not first: _out += "," first = 0 _out += v print(_out) # Erase the current program def new(self): self.prog = {} # Insert statements def add_statements(self,prog): for line,stat in prog.items(): self.prog[line] = stat # Delete a statement def del_line(self,lineno): try: del self.prog[lineno] except KeyError: pass ./CBFlib-0.9.2.2/ply-3.2/example/BASIC/sears.bas0000644000076500007650000000074111603702121016761 0ustar yayayaya1 REM :: THIS PROGRAM COMPUTES HOW MANY TIMES YOU HAVE TO FOLD 2 REM :: A PIECE OF PAPER SO THAT IT IS TALLER THAN THE 3 REM :: SEARS TOWER. 4 REM :: S = HEIGHT OF TOWER (METERS) 5 REM :: T = THICKNESS OF PAPER (MILLIMETERS) 10 LET S = 442 20 LET T = 0.1 30 REM CONVERT T TO METERS 40 LET T = T * .001 50 LET F = 1 60 LET H = T 100 IF H > S THEN 200 120 LET H = 2 * H 125 LET F = F + 1 130 GOTO 100 200 PRINT "NUMBER OF FOLDS ="F 220 PRINT "FINAL HEIGHT ="H 999 END ./CBFlib-0.9.2.2/ply-3.2/example/BASIC/sales.bas0000644000076500007650000000056711603702121016761 0ustar yayayaya10 FOR I = 1 TO 3 20 READ P(I) 30 NEXT I 40 FOR I = 1 TO 3 50 FOR J = 1 TO 5 60 READ S(I,J) 70 NEXT J 80 NEXT I 90 FOR J = 1 TO 5 100 LET S = 0 110 FOR I = 1 TO 3 120 LET S = S + P(I) * S(I,J) 130 NEXT I 140 PRINT "TOTAL SALES FOR SALESMAN"J, "$"S 150 NEXT J 200 DATA 1.25, 4.30, 2.50 210 DATA 40, 20, 37, 29, 42 220 DATA 10, 16, 3, 21, 8 230 DATA 35, 47, 29, 16, 33 300 END ./CBFlib-0.9.2.2/ply-3.2/example/BASIC/hello.bas0000644000076500007650000000007111603702121016743 0ustar yayayaya5 REM HELLO WORLD PROGAM 10 PRINT "HELLO WORLD" 99 END ./CBFlib-0.9.2.2/ply-3.2/example/BASIC/basic.py0000644000076500007650000000277511603702121016621 0ustar yayayaya# An implementation of Dartmouth BASIC (1964) # import sys sys.path.insert(0,"../..") if sys.version_info[0] >= 3: raw_input = input import basiclex import basparse import basinterp # If a filename has been specified, we try to run it. # If a runtime error occurs, we bail out and enter # interactive mode below if len(sys.argv) == 2: data = open(sys.argv[1]).read() prog = basparse.parse(data) if not prog: raise SystemExit b = basinterp.BasicInterpreter(prog) try: b.run() raise SystemExit except RuntimeError: pass else: b = basinterp.BasicInterpreter({}) # Interactive mode. This incrementally adds/deletes statements # from the program stored in the BasicInterpreter object. In # addition, special commands 'NEW','LIST',and 'RUN' are added. # Specifying a line number with no code deletes that line from # the program. while 1: try: line = raw_input("[BASIC] ") except EOFError: raise SystemExit if not line: continue line += "\n" prog = basparse.parse(line) if not prog: continue keys = list(prog) if keys[0] > 0: b.add_statements(prog) else: stat = prog[keys[0]] if stat[0] == 'RUN': try: b.run() except RuntimeError: pass elif stat[0] == 'LIST': b.list() elif stat[0] == 'BLANK': b.del_line(stat[1]) elif stat[0] == 'NEW': b.new() ./CBFlib-0.9.2.2/ply-3.2/example/BASIC/maxsin.bas0000644000076500007650000000033111603702121017136 0ustar yayayaya5 PRINT "X VALUE", "SINE", "RESOLUTION" 10 READ D 20 LET M = -1 30 FOR X = 0 TO 3 STEP D 40 IF SIN(X) <= M THEN 80 50 LET X0 = X 60 LET M = SIN(X) 80 NEXT X 85 PRINT X0, M, D 90 GOTO 10 100 DATA .1, .01, .001 110 END ./CBFlib-0.9.2.2/ply-3.2/example/ansic/0000755000076500007650000000000011603703074015437 5ustar yayayaya./CBFlib-0.9.2.2/ply-3.2/example/ansic/README0000644000076500007650000000013011603702121016301 0ustar yayayayaThis example is incomplete. Was going to specify an ANSI C parser. This is part of it. ./CBFlib-0.9.2.2/ply-3.2/example/ansic/cparse.py0000644000076500007650000004727111603702121017271 0ustar yayayaya# ----------------------------------------------------------------------------- # cparse.py # # Simple parser for ANSI C. Based on the grammar in K&R, 2nd Ed. # ----------------------------------------------------------------------------- import sys import clex import ply.yacc as yacc # Get the token map tokens = clex.tokens # translation-unit: def p_translation_unit_1(t): 'translation_unit : external_declaration' pass def p_translation_unit_2(t): 'translation_unit : translation_unit external_declaration' pass # external-declaration: def p_external_declaration_1(t): 'external_declaration : function_definition' pass def p_external_declaration_2(t): 'external_declaration : declaration' pass # function-definition: def p_function_definition_1(t): 'function_definition : declaration_specifiers declarator declaration_list compound_statement' pass def p_function_definition_2(t): 'function_definition : declarator declaration_list compound_statement' pass def p_function_definition_3(t): 'function_definition : declarator compound_statement' pass def p_function_definition_4(t): 'function_definition : declaration_specifiers declarator compound_statement' pass # declaration: def p_declaration_1(t): 'declaration : declaration_specifiers init_declarator_list SEMI' pass def p_declaration_2(t): 'declaration : declaration_specifiers SEMI' pass # declaration-list: def p_declaration_list_1(t): 'declaration_list : declaration' pass def p_declaration_list_2(t): 'declaration_list : declaration_list declaration ' pass # declaration-specifiers def p_declaration_specifiers_1(t): 'declaration_specifiers : storage_class_specifier declaration_specifiers' pass def p_declaration_specifiers_2(t): 'declaration_specifiers : type_specifier declaration_specifiers' pass def p_declaration_specifiers_3(t): 'declaration_specifiers : type_qualifier declaration_specifiers' pass def p_declaration_specifiers_4(t): 'declaration_specifiers : storage_class_specifier' pass def p_declaration_specifiers_5(t): 'declaration_specifiers : type_specifier' pass def p_declaration_specifiers_6(t): 'declaration_specifiers : type_qualifier' pass # storage-class-specifier def p_storage_class_specifier(t): '''storage_class_specifier : AUTO | REGISTER | STATIC | EXTERN | TYPEDEF ''' pass # type-specifier: def p_type_specifier(t): '''type_specifier : VOID | CHAR | SHORT | INT | LONG | FLOAT | DOUBLE | SIGNED | UNSIGNED | struct_or_union_specifier | enum_specifier | TYPEID ''' pass # type-qualifier: def p_type_qualifier(t): '''type_qualifier : CONST | VOLATILE''' pass # struct-or-union-specifier def p_struct_or_union_specifier_1(t): 'struct_or_union_specifier : struct_or_union ID LBRACE struct_declaration_list RBRACE' pass def p_struct_or_union_specifier_2(t): 'struct_or_union_specifier : struct_or_union LBRACE struct_declaration_list RBRACE' pass def p_struct_or_union_specifier_3(t): 'struct_or_union_specifier : struct_or_union ID' pass # struct-or-union: def p_struct_or_union(t): '''struct_or_union : STRUCT | UNION ''' pass # struct-declaration-list: def p_struct_declaration_list_1(t): 'struct_declaration_list : struct_declaration' pass def p_struct_declaration_list_2(t): 'struct_declaration_list : struct_declaration_list struct_declaration' pass # init-declarator-list: def p_init_declarator_list_1(t): 'init_declarator_list : init_declarator' pass def p_init_declarator_list_2(t): 'init_declarator_list : init_declarator_list COMMA init_declarator' pass # init-declarator def p_init_declarator_1(t): 'init_declarator : declarator' pass def p_init_declarator_2(t): 'init_declarator : declarator EQUALS initializer' pass # struct-declaration: def p_struct_declaration(t): 'struct_declaration : specifier_qualifier_list struct_declarator_list SEMI' pass # specifier-qualifier-list: def p_specifier_qualifier_list_1(t): 'specifier_qualifier_list : type_specifier specifier_qualifier_list' pass def p_specifier_qualifier_list_2(t): 'specifier_qualifier_list : type_specifier' pass def p_specifier_qualifier_list_3(t): 'specifier_qualifier_list : type_qualifier specifier_qualifier_list' pass def p_specifier_qualifier_list_4(t): 'specifier_qualifier_list : type_qualifier' pass # struct-declarator-list: def p_struct_declarator_list_1(t): 'struct_declarator_list : struct_declarator' pass def p_struct_declarator_list_2(t): 'struct_declarator_list : struct_declarator_list COMMA struct_declarator' pass # struct-declarator: def p_struct_declarator_1(t): 'struct_declarator : declarator' pass def p_struct_declarator_2(t): 'struct_declarator : declarator COLON constant_expression' pass def p_struct_declarator_3(t): 'struct_declarator : COLON constant_expression' pass # enum-specifier: def p_enum_specifier_1(t): 'enum_specifier : ENUM ID LBRACE enumerator_list RBRACE' pass def p_enum_specifier_2(t): 'enum_specifier : ENUM LBRACE enumerator_list RBRACE' pass def p_enum_specifier_3(t): 'enum_specifier : ENUM ID' pass # enumerator_list: def p_enumerator_list_1(t): 'enumerator_list : enumerator' pass def p_enumerator_list_2(t): 'enumerator_list : enumerator_list COMMA enumerator' pass # enumerator: def p_enumerator_1(t): 'enumerator : ID' pass def p_enumerator_2(t): 'enumerator : ID EQUALS constant_expression' pass # declarator: def p_declarator_1(t): 'declarator : pointer direct_declarator' pass def p_declarator_2(t): 'declarator : direct_declarator' pass # direct-declarator: def p_direct_declarator_1(t): 'direct_declarator : ID' pass def p_direct_declarator_2(t): 'direct_declarator : LPAREN declarator RPAREN' pass def p_direct_declarator_3(t): 'direct_declarator : direct_declarator LBRACKET constant_expression_opt RBRACKET' pass def p_direct_declarator_4(t): 'direct_declarator : direct_declarator LPAREN parameter_type_list RPAREN ' pass def p_direct_declarator_5(t): 'direct_declarator : direct_declarator LPAREN identifier_list RPAREN ' pass def p_direct_declarator_6(t): 'direct_declarator : direct_declarator LPAREN RPAREN ' pass # pointer: def p_pointer_1(t): 'pointer : TIMES type_qualifier_list' pass def p_pointer_2(t): 'pointer : TIMES' pass def p_pointer_3(t): 'pointer : TIMES type_qualifier_list pointer' pass def p_pointer_4(t): 'pointer : TIMES pointer' pass # type-qualifier-list: def p_type_qualifier_list_1(t): 'type_qualifier_list : type_qualifier' pass def p_type_qualifier_list_2(t): 'type_qualifier_list : type_qualifier_list type_qualifier' pass # parameter-type-list: def p_parameter_type_list_1(t): 'parameter_type_list : parameter_list' pass def p_parameter_type_list_2(t): 'parameter_type_list : parameter_list COMMA ELLIPSIS' pass # parameter-list: def p_parameter_list_1(t): 'parameter_list : parameter_declaration' pass def p_parameter_list_2(t): 'parameter_list : parameter_list COMMA parameter_declaration' pass # parameter-declaration: def p_parameter_declaration_1(t): 'parameter_declaration : declaration_specifiers declarator' pass def p_parameter_declaration_2(t): 'parameter_declaration : declaration_specifiers abstract_declarator_opt' pass # identifier-list: def p_identifier_list_1(t): 'identifier_list : ID' pass def p_identifier_list_2(t): 'identifier_list : identifier_list COMMA ID' pass # initializer: def p_initializer_1(t): 'initializer : assignment_expression' pass def p_initializer_2(t): '''initializer : LBRACE initializer_list RBRACE | LBRACE initializer_list COMMA RBRACE''' pass # initializer-list: def p_initializer_list_1(t): 'initializer_list : initializer' pass def p_initializer_list_2(t): 'initializer_list : initializer_list COMMA initializer' pass # type-name: def p_type_name(t): 'type_name : specifier_qualifier_list abstract_declarator_opt' pass def p_abstract_declarator_opt_1(t): 'abstract_declarator_opt : empty' pass def p_abstract_declarator_opt_2(t): 'abstract_declarator_opt : abstract_declarator' pass # abstract-declarator: def p_abstract_declarator_1(t): 'abstract_declarator : pointer ' pass def p_abstract_declarator_2(t): 'abstract_declarator : pointer direct_abstract_declarator' pass def p_abstract_declarator_3(t): 'abstract_declarator : direct_abstract_declarator' pass # direct-abstract-declarator: def p_direct_abstract_declarator_1(t): 'direct_abstract_declarator : LPAREN abstract_declarator RPAREN' pass def p_direct_abstract_declarator_2(t): 'direct_abstract_declarator : direct_abstract_declarator LBRACKET constant_expression_opt RBRACKET' pass def p_direct_abstract_declarator_3(t): 'direct_abstract_declarator : LBRACKET constant_expression_opt RBRACKET' pass def p_direct_abstract_declarator_4(t): 'direct_abstract_declarator : direct_abstract_declarator LPAREN parameter_type_list_opt RPAREN' pass def p_direct_abstract_declarator_5(t): 'direct_abstract_declarator : LPAREN parameter_type_list_opt RPAREN' pass # Optional fields in abstract declarators def p_constant_expression_opt_1(t): 'constant_expression_opt : empty' pass def p_constant_expression_opt_2(t): 'constant_expression_opt : constant_expression' pass def p_parameter_type_list_opt_1(t): 'parameter_type_list_opt : empty' pass def p_parameter_type_list_opt_2(t): 'parameter_type_list_opt : parameter_type_list' pass # statement: def p_statement(t): ''' statement : labeled_statement | expression_statement | compound_statement | selection_statement | iteration_statement | jump_statement ''' pass # labeled-statement: def p_labeled_statement_1(t): 'labeled_statement : ID COLON statement' pass def p_labeled_statement_2(t): 'labeled_statement : CASE constant_expression COLON statement' pass def p_labeled_statement_3(t): 'labeled_statement : DEFAULT COLON statement' pass # expression-statement: def p_expression_statement(t): 'expression_statement : expression_opt SEMI' pass # compound-statement: def p_compound_statement_1(t): 'compound_statement : LBRACE declaration_list statement_list RBRACE' pass def p_compound_statement_2(t): 'compound_statement : LBRACE statement_list RBRACE' pass def p_compound_statement_3(t): 'compound_statement : LBRACE declaration_list RBRACE' pass def p_compound_statement_4(t): 'compound_statement : LBRACE RBRACE' pass # statement-list: def p_statement_list_1(t): 'statement_list : statement' pass def p_statement_list_2(t): 'statement_list : statement_list statement' pass # selection-statement def p_selection_statement_1(t): 'selection_statement : IF LPAREN expression RPAREN statement' pass def p_selection_statement_2(t): 'selection_statement : IF LPAREN expression RPAREN statement ELSE statement ' pass def p_selection_statement_3(t): 'selection_statement : SWITCH LPAREN expression RPAREN statement ' pass # iteration_statement: def p_iteration_statement_1(t): 'iteration_statement : WHILE LPAREN expression RPAREN statement' pass def p_iteration_statement_2(t): 'iteration_statement : FOR LPAREN expression_opt SEMI expression_opt SEMI expression_opt RPAREN statement ' pass def p_iteration_statement_3(t): 'iteration_statement : DO statement WHILE LPAREN expression RPAREN SEMI' pass # jump_statement: def p_jump_statement_1(t): 'jump_statement : GOTO ID SEMI' pass def p_jump_statement_2(t): 'jump_statement : CONTINUE SEMI' pass def p_jump_statement_3(t): 'jump_statement : BREAK SEMI' pass def p_jump_statement_4(t): 'jump_statement : RETURN expression_opt SEMI' pass def p_expression_opt_1(t): 'expression_opt : empty' pass def p_expression_opt_2(t): 'expression_opt : expression' pass # expression: def p_expression_1(t): 'expression : assignment_expression' pass def p_expression_2(t): 'expression : expression COMMA assignment_expression' pass # assigment_expression: def p_assignment_expression_1(t): 'assignment_expression : conditional_expression' pass def p_assignment_expression_2(t): 'assignment_expression : unary_expression assignment_operator assignment_expression' pass # assignment_operator: def p_assignment_operator(t): ''' assignment_operator : EQUALS | TIMESEQUAL | DIVEQUAL | MODEQUAL | PLUSEQUAL | MINUSEQUAL | LSHIFTEQUAL | RSHIFTEQUAL | ANDEQUAL | OREQUAL | XOREQUAL ''' pass # conditional-expression def p_conditional_expression_1(t): 'conditional_expression : logical_or_expression' pass def p_conditional_expression_2(t): 'conditional_expression : logical_or_expression CONDOP expression COLON conditional_expression ' pass # constant-expression def p_constant_expression(t): 'constant_expression : conditional_expression' pass # logical-or-expression def p_logical_or_expression_1(t): 'logical_or_expression : logical_and_expression' pass def p_logical_or_expression_2(t): 'logical_or_expression : logical_or_expression LOR logical_and_expression' pass # logical-and-expression def p_logical_and_expression_1(t): 'logical_and_expression : inclusive_or_expression' pass def p_logical_and_expression_2(t): 'logical_and_expression : logical_and_expression LAND inclusive_or_expression' pass # inclusive-or-expression: def p_inclusive_or_expression_1(t): 'inclusive_or_expression : exclusive_or_expression' pass def p_inclusive_or_expression_2(t): 'inclusive_or_expression : inclusive_or_expression OR exclusive_or_expression' pass # exclusive-or-expression: def p_exclusive_or_expression_1(t): 'exclusive_or_expression : and_expression' pass def p_exclusive_or_expression_2(t): 'exclusive_or_expression : exclusive_or_expression XOR and_expression' pass # AND-expression def p_and_expression_1(t): 'and_expression : equality_expression' pass def p_and_expression_2(t): 'and_expression : and_expression AND equality_expression' pass # equality-expression: def p_equality_expression_1(t): 'equality_expression : relational_expression' pass def p_equality_expression_2(t): 'equality_expression : equality_expression EQ relational_expression' pass def p_equality_expression_3(t): 'equality_expression : equality_expression NE relational_expression' pass # relational-expression: def p_relational_expression_1(t): 'relational_expression : shift_expression' pass def p_relational_expression_2(t): 'relational_expression : relational_expression LT shift_expression' pass def p_relational_expression_3(t): 'relational_expression : relational_expression GT shift_expression' pass def p_relational_expression_4(t): 'relational_expression : relational_expression LE shift_expression' pass def p_relational_expression_5(t): 'relational_expression : relational_expression GE shift_expression' pass # shift-expression def p_shift_expression_1(t): 'shift_expression : additive_expression' pass def p_shift_expression_2(t): 'shift_expression : shift_expression LSHIFT additive_expression' pass def p_shift_expression_3(t): 'shift_expression : shift_expression RSHIFT additive_expression' pass # additive-expression def p_additive_expression_1(t): 'additive_expression : multiplicative_expression' pass def p_additive_expression_2(t): 'additive_expression : additive_expression PLUS multiplicative_expression' pass def p_additive_expression_3(t): 'additive_expression : additive_expression MINUS multiplicative_expression' pass # multiplicative-expression def p_multiplicative_expression_1(t): 'multiplicative_expression : cast_expression' pass def p_multiplicative_expression_2(t): 'multiplicative_expression : multiplicative_expression TIMES cast_expression' pass def p_multiplicative_expression_3(t): 'multiplicative_expression : multiplicative_expression DIVIDE cast_expression' pass def p_multiplicative_expression_4(t): 'multiplicative_expression : multiplicative_expression MOD cast_expression' pass # cast-expression: def p_cast_expression_1(t): 'cast_expression : unary_expression' pass def p_cast_expression_2(t): 'cast_expression : LPAREN type_name RPAREN cast_expression' pass # unary-expression: def p_unary_expression_1(t): 'unary_expression : postfix_expression' pass def p_unary_expression_2(t): 'unary_expression : PLUSPLUS unary_expression' pass def p_unary_expression_3(t): 'unary_expression : MINUSMINUS unary_expression' pass def p_unary_expression_4(t): 'unary_expression : unary_operator cast_expression' pass def p_unary_expression_5(t): 'unary_expression : SIZEOF unary_expression' pass def p_unary_expression_6(t): 'unary_expression : SIZEOF LPAREN type_name RPAREN' pass #unary-operator def p_unary_operator(t): '''unary_operator : AND | TIMES | PLUS | MINUS | NOT | LNOT ''' pass # postfix-expression: def p_postfix_expression_1(t): 'postfix_expression : primary_expression' pass def p_postfix_expression_2(t): 'postfix_expression : postfix_expression LBRACKET expression RBRACKET' pass def p_postfix_expression_3(t): 'postfix_expression : postfix_expression LPAREN argument_expression_list RPAREN' pass def p_postfix_expression_4(t): 'postfix_expression : postfix_expression LPAREN RPAREN' pass def p_postfix_expression_5(t): 'postfix_expression : postfix_expression PERIOD ID' pass def p_postfix_expression_6(t): 'postfix_expression : postfix_expression ARROW ID' pass def p_postfix_expression_7(t): 'postfix_expression : postfix_expression PLUSPLUS' pass def p_postfix_expression_8(t): 'postfix_expression : postfix_expression MINUSMINUS' pass # primary-expression: def p_primary_expression(t): '''primary_expression : ID | constant | SCONST | LPAREN expression RPAREN''' pass # argument-expression-list: def p_argument_expression_list(t): '''argument_expression_list : assignment_expression | argument_expression_list COMMA assignment_expression''' pass # constant: def p_constant(t): '''constant : ICONST | FCONST | CCONST''' pass def p_empty(t): 'empty : ' pass def p_error(t): print("Whoa. We're hosed") import profile # Build the grammar yacc.yacc(method='LALR') #profile.run("yacc.yacc(method='LALR')") ./CBFlib-0.9.2.2/ply-3.2/example/ansic/clex.py0000644000076500007650000000753311603702121016744 0ustar yayayaya# ---------------------------------------------------------------------- # clex.py # # A lexer for ANSI C. # ---------------------------------------------------------------------- import sys sys.path.insert(0,"../..") import ply.lex as lex # Reserved words reserved = ( 'AUTO', 'BREAK', 'CASE', 'CHAR', 'CONST', 'CONTINUE', 'DEFAULT', 'DO', 'DOUBLE', 'ELSE', 'ENUM', 'EXTERN', 'FLOAT', 'FOR', 'GOTO', 'IF', 'INT', 'LONG', 'REGISTER', 'RETURN', 'SHORT', 'SIGNED', 'SIZEOF', 'STATIC', 'STRUCT', 'SWITCH', 'TYPEDEF', 'UNION', 'UNSIGNED', 'VOID', 'VOLATILE', 'WHILE', ) tokens = reserved + ( # Literals (identifier, integer constant, float constant, string constant, char const) 'ID', 'TYPEID', 'ICONST', 'FCONST', 'SCONST', 'CCONST', # Operators (+,-,*,/,%,|,&,~,^,<<,>>, ||, &&, !, <, <=, >, >=, ==, !=) 'PLUS', 'MINUS', 'TIMES', 'DIVIDE', 'MOD', 'OR', 'AND', 'NOT', 'XOR', 'LSHIFT', 'RSHIFT', 'LOR', 'LAND', 'LNOT', 'LT', 'LE', 'GT', 'GE', 'EQ', 'NE', # Assignment (=, *=, /=, %=, +=, -=, <<=, >>=, &=, ^=, |=) 'EQUALS', 'TIMESEQUAL', 'DIVEQUAL', 'MODEQUAL', 'PLUSEQUAL', 'MINUSEQUAL', 'LSHIFTEQUAL','RSHIFTEQUAL', 'ANDEQUAL', 'XOREQUAL', 'OREQUAL', # Increment/decrement (++,--) 'PLUSPLUS', 'MINUSMINUS', # Structure dereference (->) 'ARROW', # Conditional operator (?) 'CONDOP', # Delimeters ( ) [ ] { } , . ; : 'LPAREN', 'RPAREN', 'LBRACKET', 'RBRACKET', 'LBRACE', 'RBRACE', 'COMMA', 'PERIOD', 'SEMI', 'COLON', # Ellipsis (...) 'ELLIPSIS', ) # Completely ignored characters t_ignore = ' \t\x0c' # Newlines def t_NEWLINE(t): r'\n+' t.lexer.lineno += t.value.count("\n") # Operators t_PLUS = r'\+' t_MINUS = r'-' t_TIMES = r'\*' t_DIVIDE = r'/' t_MOD = r'%' t_OR = r'\|' t_AND = r'&' t_NOT = r'~' t_XOR = r'\^' t_LSHIFT = r'<<' t_RSHIFT = r'>>' t_LOR = r'\|\|' t_LAND = r'&&' t_LNOT = r'!' t_LT = r'<' t_GT = r'>' t_LE = r'<=' t_GE = r'>=' t_EQ = r'==' t_NE = r'!=' # Assignment operators t_EQUALS = r'=' t_TIMESEQUAL = r'\*=' t_DIVEQUAL = r'/=' t_MODEQUAL = r'%=' t_PLUSEQUAL = r'\+=' t_MINUSEQUAL = r'-=' t_LSHIFTEQUAL = r'<<=' t_RSHIFTEQUAL = r'>>=' t_ANDEQUAL = r'&=' t_OREQUAL = r'\|=' t_XOREQUAL = r'^=' # Increment/decrement t_PLUSPLUS = r'\+\+' t_MINUSMINUS = r'--' # -> t_ARROW = r'->' # ? t_CONDOP = r'\?' # Delimeters t_LPAREN = r'\(' t_RPAREN = r'\)' t_LBRACKET = r'\[' t_RBRACKET = r'\]' t_LBRACE = r'\{' t_RBRACE = r'\}' t_COMMA = r',' t_PERIOD = r'\.' t_SEMI = r';' t_COLON = r':' t_ELLIPSIS = r'\.\.\.' # Identifiers and reserved words reserved_map = { } for r in reserved: reserved_map[r.lower()] = r def t_ID(t): r'[A-Za-z_][\w_]*' t.type = reserved_map.get(t.value,"ID") return t # Integer literal t_ICONST = r'\d+([uU]|[lL]|[uU][lL]|[lL][uU])?' # Floating literal t_FCONST = r'((\d+)(\.\d+)(e(\+|-)?(\d+))? | (\d+)e(\+|-)?(\d+))([lL]|[fF])?' # String literal t_SCONST = r'\"([^\\\n]|(\\.))*?\"' # Character constant 'c' or L'c' t_CCONST = r'(L)?\'([^\\\n]|(\\.))*?\'' # Comments def t_comment(t): r'/\*(.|\n)*?\*/' t.lexer.lineno += t.value.count('\n') # Preprocessor directive (ignored) def t_preprocessor(t): r'\#(.)*?\n' t.lexer.lineno += 1 def t_error(t): print("Illegal character %s" % repr(t.value[0])) t.lexer.skip(1) lexer = lex.lex(optimize=1) if __name__ == "__main__": lex.runmain(lexer) ./CBFlib-0.9.2.2/ply-3.2/example/hedit/0000755000076500007650000000000011603703074015437 5ustar yayayaya./CBFlib-0.9.2.2/ply-3.2/example/hedit/hedit.py0000644000076500007650000000210511603702121017074 0ustar yayayaya# ----------------------------------------------------------------------------- # hedit.py # # Paring of Fortran H Edit descriptions (Contributed by Pearu Peterson) # # These tokens can't be easily tokenized because they are of the following # form: # # nHc1...cn # # where n is a positive integer and c1 ... cn are characters. # # This example shows how to modify the state of the lexer to parse # such tokens # ----------------------------------------------------------------------------- import sys sys.path.insert(0,"../..") tokens = ( 'H_EDIT_DESCRIPTOR', ) # Tokens t_ignore = " \t\n" def t_H_EDIT_DESCRIPTOR(t): r"\d+H.*" # This grabs all of the remaining text i = t.value.index('H') n = eval(t.value[:i]) # Adjust the tokenizing position t.lexer.lexpos -= len(t.value) - (i+1+n) t.value = t.value[i+1:i+1+n] return t def t_error(t): print("Illegal character '%s'" % t.value[0]) t.lexer.skip(1) # Build the lexer import ply.lex as lex lex.lex() lex.runmain() ./CBFlib-0.9.2.2/ply-3.2/example/README0000644000076500007650000000047311603702121015216 0ustar yayayayaSimple examples: calc - Simple calculator classcalc - Simple calculate defined as a class Complex examples ansic - ANSI C grammar from K&R BASIC - A small BASIC interpreter GardenSnake - A simple python-like language yply - Converts Unix yacc files to PLY programs. ./CBFlib-0.9.2.2/ply-3.2/example/closurecalc/0000755000076500007650000000000011603703074016641 5ustar yayayaya./CBFlib-0.9.2.2/ply-3.2/example/closurecalc/calc.py0000644000076500007650000000572411603702121020115 0ustar yayayaya# ----------------------------------------------------------------------------- # calc.py # # A calculator parser that makes use of closures. The function make_calculator() # returns a function that accepts an input string and returns a result. All # lexing rules, parsing rules, and internal state are held inside the function. # ----------------------------------------------------------------------------- import sys sys.path.insert(0,"../..") if sys.version_info[0] >= 3: raw_input = input # Make a calculator function def make_calculator(): import ply.lex as lex import ply.yacc as yacc # ------- Internal calculator state variables = { } # Dictionary of stored variables # ------- Calculator tokenizing rules tokens = ( 'NAME','NUMBER', ) literals = ['=','+','-','*','/', '(',')'] t_ignore = " \t" t_NAME = r'[a-zA-Z_][a-zA-Z0-9_]*' def t_NUMBER(t): r'\d+' t.value = int(t.value) return t def t_newline(t): r'\n+' t.lexer.lineno += t.value.count("\n") def t_error(t): print("Illegal character '%s'" % t.value[0]) t.lexer.skip(1) # Build the lexer lexer = lex.lex() # ------- Calculator parsing rules precedence = ( ('left','+','-'), ('left','*','/'), ('right','UMINUS'), ) def p_statement_assign(p): 'statement : NAME "=" expression' variables[p[1]] = p[3] p[0] = None def p_statement_expr(p): 'statement : expression' p[0] = p[1] def p_expression_binop(p): '''expression : expression '+' expression | expression '-' expression | expression '*' expression | expression '/' expression''' if p[2] == '+' : p[0] = p[1] + p[3] elif p[2] == '-': p[0] = p[1] - p[3] elif p[2] == '*': p[0] = p[1] * p[3] elif p[2] == '/': p[0] = p[1] / p[3] def p_expression_uminus(p): "expression : '-' expression %prec UMINUS" p[0] = -p[2] def p_expression_group(p): "expression : '(' expression ')'" p[0] = p[2] def p_expression_number(p): "expression : NUMBER" p[0] = p[1] def p_expression_name(p): "expression : NAME" try: p[0] = variables[p[1]] except LookupError: print("Undefined name '%s'" % p[1]) p[0] = 0 def p_error(p): if p: print("Syntax error at '%s'" % p.value) else: print("Syntax error at EOF") # Build the parser parser = yacc.yacc() # ------- Input function def input(text): result = parser.parse(text,lexer=lexer) return result return input # Make a calculator object and use it calc = make_calculator() while True: try: s = raw_input("calc > ") except EOFError: break r = calc(s) if r: print(r) ./CBFlib-0.9.2.2/ply-3.2/example/GardenSnake/0000755000076500007650000000000011603703074016524 5ustar yayayaya./CBFlib-0.9.2.2/ply-3.2/example/GardenSnake/README0000644000076500007650000000036511603702121017400 0ustar yayayayaThis example is Andrew Dalke's GardenSnake language. It shows how to process an indentation-like language like Python. Further details can be found here: http://dalkescientific.com/writings/diary/archive/2006/08/30/gardensnake_language.html ./CBFlib-0.9.2.2/ply-3.2/example/GardenSnake/GardenSnake.py0000644000076500007650000004541511603702121021261 0ustar yayayaya# GardenSnake - a parser generator demonstration program # # This implements a modified version of a subset of Python: # - only 'def', 'return' and 'if' statements # - 'if' only has 'then' clause (no elif nor else) # - single-quoted strings only, content in raw format # - numbers are decimal.Decimal instances (not integers or floats) # - no print statment; use the built-in 'print' function # - only < > == + - / * implemented (and unary + -) # - assignment and tuple assignment work # - no generators of any sort # - no ... well, no quite a lot # Why? I'm thinking about a new indentation-based configuration # language for a project and wanted to figure out how to do it. Once # I got that working I needed a way to test it out. My original AST # was dumb so I decided to target Python's AST and compile it into # Python code. Plus, it's pretty cool that it only took a day or so # from sitting down with Ply to having working code. # This uses David Beazley's Ply from http://www.dabeaz.com/ply/ # This work is hereby released into the Public Domain. To view a copy of # the public domain dedication, visit # http://creativecommons.org/licenses/publicdomain/ or send a letter to # Creative Commons, 543 Howard Street, 5th Floor, San Francisco, # California, 94105, USA. # # Portions of this work are derived from Python's Grammar definition # and may be covered under the Python copyright and license # # Andrew Dalke / Dalke Scientific Software, LLC # 30 August 2006 / Cape Town, South Africa # Changelog: # 30 August - added link to CC license; removed the "swapcase" encoding # Modifications for inclusion in PLY distribution import sys sys.path.insert(0,"../..") from ply import * ##### Lexer ###### #import lex import decimal tokens = ( 'DEF', 'IF', 'NAME', 'NUMBER', # Python decimals 'STRING', # single quoted strings only; syntax of raw strings 'LPAR', 'RPAR', 'COLON', 'EQ', 'ASSIGN', 'LT', 'GT', 'PLUS', 'MINUS', 'MULT', 'DIV', 'RETURN', 'WS', 'NEWLINE', 'COMMA', 'SEMICOLON', 'INDENT', 'DEDENT', 'ENDMARKER', ) #t_NUMBER = r'\d+' # taken from decmial.py but without the leading sign def t_NUMBER(t): r"""(\d+(\.\d*)?|\.\d+)([eE][-+]? \d+)?""" t.value = decimal.Decimal(t.value) return t def t_STRING(t): r"'([^\\']+|\\'|\\\\)*'" # I think this is right ... t.value=t.value[1:-1].decode("string-escape") # .swapcase() # for fun return t t_COLON = r':' t_EQ = r'==' t_ASSIGN = r'=' t_LT = r'<' t_GT = r'>' t_PLUS = r'\+' t_MINUS = r'-' t_MULT = r'\*' t_DIV = r'/' t_COMMA = r',' t_SEMICOLON = r';' # Ply nicely documented how to do this. RESERVED = { "def": "DEF", "if": "IF", "return": "RETURN", } def t_NAME(t): r'[a-zA-Z_][a-zA-Z0-9_]*' t.type = RESERVED.get(t.value, "NAME") return t # Putting this before t_WS let it consume lines with only comments in # them so the latter code never sees the WS part. Not consuming the # newline. Needed for "if 1: #comment" def t_comment(t): r"[ ]*\043[^\n]*" # \043 is '#' pass # Whitespace def t_WS(t): r' [ ]+ ' if t.lexer.at_line_start and t.lexer.paren_count == 0: return t # Don't generate newline tokens when inside of parenthesis, eg # a = (1, # 2, 3) def t_newline(t): r'\n+' t.lexer.lineno += len(t.value) t.type = "NEWLINE" if t.lexer.paren_count == 0: return t def t_LPAR(t): r'\(' t.lexer.paren_count += 1 return t def t_RPAR(t): r'\)' # check for underflow? should be the job of the parser t.lexer.paren_count -= 1 return t def t_error(t): raise SyntaxError("Unknown symbol %r" % (t.value[0],)) print "Skipping", repr(t.value[0]) t.lexer.skip(1) ## I implemented INDENT / DEDENT generation as a post-processing filter # The original lex token stream contains WS and NEWLINE characters. # WS will only occur before any other tokens on a line. # I have three filters. One tags tokens by adding two attributes. # "must_indent" is True if the token must be indented from the # previous code. The other is "at_line_start" which is True for WS # and the first non-WS/non-NEWLINE on a line. It flags the check so # see if the new line has changed indication level. # Python's syntax has three INDENT states # 0) no colon hence no need to indent # 1) "if 1: go()" - simple statements have a COLON but no need for an indent # 2) "if 1:\n go()" - complex statements have a COLON NEWLINE and must indent NO_INDENT = 0 MAY_INDENT = 1 MUST_INDENT = 2 # only care about whitespace at the start of a line def track_tokens_filter(lexer, tokens): lexer.at_line_start = at_line_start = True indent = NO_INDENT saw_colon = False for token in tokens: token.at_line_start = at_line_start if token.type == "COLON": at_line_start = False indent = MAY_INDENT token.must_indent = False elif token.type == "NEWLINE": at_line_start = True if indent == MAY_INDENT: indent = MUST_INDENT token.must_indent = False elif token.type == "WS": assert token.at_line_start == True at_line_start = True token.must_indent = False else: # A real token; only indent after COLON NEWLINE if indent == MUST_INDENT: token.must_indent = True else: token.must_indent = False at_line_start = False indent = NO_INDENT yield token lexer.at_line_start = at_line_start def _new_token(type, lineno): tok = lex.LexToken() tok.type = type tok.value = None tok.lineno = lineno return tok # Synthesize a DEDENT tag def DEDENT(lineno): return _new_token("DEDENT", lineno) # Synthesize an INDENT tag def INDENT(lineno): return _new_token("INDENT", lineno) # Track the indentation level and emit the right INDENT / DEDENT events. def indentation_filter(tokens): # A stack of indentation levels; will never pop item 0 levels = [0] token = None depth = 0 prev_was_ws = False for token in tokens: ## if 1: ## print "Process", token, ## if token.at_line_start: ## print "at_line_start", ## if token.must_indent: ## print "must_indent", ## print # WS only occurs at the start of the line # There may be WS followed by NEWLINE so # only track the depth here. Don't indent/dedent # until there's something real. if token.type == "WS": assert depth == 0 depth = len(token.value) prev_was_ws = True # WS tokens are never passed to the parser continue if token.type == "NEWLINE": depth = 0 if prev_was_ws or token.at_line_start: # ignore blank lines continue # pass the other cases on through yield token continue # then it must be a real token (not WS, not NEWLINE) # which can affect the indentation level prev_was_ws = False if token.must_indent: # The current depth must be larger than the previous level if not (depth > levels[-1]): raise IndentationError("expected an indented block") levels.append(depth) yield INDENT(token.lineno) elif token.at_line_start: # Must be on the same level or one of the previous levels if depth == levels[-1]: # At the same level pass elif depth > levels[-1]: raise IndentationError("indentation increase but not in new block") else: # Back up; but only if it matches a previous level try: i = levels.index(depth) except ValueError: raise IndentationError("inconsistent indentation") for _ in range(i+1, len(levels)): yield DEDENT(token.lineno) levels.pop() yield token ### Finished processing ### # Must dedent any remaining levels if len(levels) > 1: assert token is not None for _ in range(1, len(levels)): yield DEDENT(token.lineno) # The top-level filter adds an ENDMARKER, if requested. # Python's grammar uses it. def filter(lexer, add_endmarker = True): token = None tokens = iter(lexer.token, None) tokens = track_tokens_filter(lexer, tokens) for token in indentation_filter(tokens): yield token if add_endmarker: lineno = 1 if token is not None: lineno = token.lineno yield _new_token("ENDMARKER", lineno) # Combine Ply and my filters into a new lexer class IndentLexer(object): def __init__(self, debug=0, optimize=0, lextab='lextab', reflags=0): self.lexer = lex.lex(debug=debug, optimize=optimize, lextab=lextab, reflags=reflags) self.token_stream = None def input(self, s, add_endmarker=True): self.lexer.paren_count = 0 self.lexer.input(s) self.token_stream = filter(self.lexer, add_endmarker) def token(self): try: return self.token_stream.next() except StopIteration: return None ########## Parser (tokens -> AST) ###### # also part of Ply #import yacc # I use the Python AST from compiler import ast # Helper function def Assign(left, right): names = [] if isinstance(left, ast.Name): # Single assignment on left return ast.Assign([ast.AssName(left.name, 'OP_ASSIGN')], right) elif isinstance(left, ast.Tuple): # List of things - make sure they are Name nodes names = [] for child in left.getChildren(): if not isinstance(child, ast.Name): raise SyntaxError("that assignment not supported") names.append(child.name) ass_list = [ast.AssName(name, 'OP_ASSIGN') for name in names] return ast.Assign([ast.AssTuple(ass_list)], right) else: raise SyntaxError("Can't do that yet") # The grammar comments come from Python's Grammar/Grammar file ## NB: compound_stmt in single_input is followed by extra NEWLINE! # file_input: (NEWLINE | stmt)* ENDMARKER def p_file_input_end(p): """file_input_end : file_input ENDMARKER""" p[0] = ast.Stmt(p[1]) def p_file_input(p): """file_input : file_input NEWLINE | file_input stmt | NEWLINE | stmt""" if isinstance(p[len(p)-1], basestring): if len(p) == 3: p[0] = p[1] else: p[0] = [] # p == 2 --> only a blank line else: if len(p) == 3: p[0] = p[1] + p[2] else: p[0] = p[1] # funcdef: [decorators] 'def' NAME parameters ':' suite # ignoring decorators def p_funcdef(p): "funcdef : DEF NAME parameters COLON suite" p[0] = ast.Function(None, p[2], tuple(p[3]), (), 0, None, p[5]) # parameters: '(' [varargslist] ')' def p_parameters(p): """parameters : LPAR RPAR | LPAR varargslist RPAR""" if len(p) == 3: p[0] = [] else: p[0] = p[2] # varargslist: (fpdef ['=' test] ',')* ('*' NAME [',' '**' NAME] | '**' NAME) | # highly simplified def p_varargslist(p): """varargslist : varargslist COMMA NAME | NAME""" if len(p) == 4: p[0] = p[1] + p[3] else: p[0] = [p[1]] # stmt: simple_stmt | compound_stmt def p_stmt_simple(p): """stmt : simple_stmt""" # simple_stmt is a list p[0] = p[1] def p_stmt_compound(p): """stmt : compound_stmt""" p[0] = [p[1]] # simple_stmt: small_stmt (';' small_stmt)* [';'] NEWLINE def p_simple_stmt(p): """simple_stmt : small_stmts NEWLINE | small_stmts SEMICOLON NEWLINE""" p[0] = p[1] def p_small_stmts(p): """small_stmts : small_stmts SEMICOLON small_stmt | small_stmt""" if len(p) == 4: p[0] = p[1] + [p[3]] else: p[0] = [p[1]] # small_stmt: expr_stmt | print_stmt | del_stmt | pass_stmt | flow_stmt | # import_stmt | global_stmt | exec_stmt | assert_stmt def p_small_stmt(p): """small_stmt : flow_stmt | expr_stmt""" p[0] = p[1] # expr_stmt: testlist (augassign (yield_expr|testlist) | # ('=' (yield_expr|testlist))*) # augassign: ('+=' | '-=' | '*=' | '/=' | '%=' | '&=' | '|=' | '^=' | # '<<=' | '>>=' | '**=' | '//=') def p_expr_stmt(p): """expr_stmt : testlist ASSIGN testlist | testlist """ if len(p) == 2: # a list of expressions p[0] = ast.Discard(p[1]) else: p[0] = Assign(p[1], p[3]) def p_flow_stmt(p): "flow_stmt : return_stmt" p[0] = p[1] # return_stmt: 'return' [testlist] def p_return_stmt(p): "return_stmt : RETURN testlist" p[0] = ast.Return(p[2]) def p_compound_stmt(p): """compound_stmt : if_stmt | funcdef""" p[0] = p[1] def p_if_stmt(p): 'if_stmt : IF test COLON suite' p[0] = ast.If([(p[2], p[4])], None) def p_suite(p): """suite : simple_stmt | NEWLINE INDENT stmts DEDENT""" if len(p) == 2: p[0] = ast.Stmt(p[1]) else: p[0] = ast.Stmt(p[3]) def p_stmts(p): """stmts : stmts stmt | stmt""" if len(p) == 3: p[0] = p[1] + p[2] else: p[0] = p[1] ## No using Python's approach because Ply supports precedence # comparison: expr (comp_op expr)* # arith_expr: term (('+'|'-') term)* # term: factor (('*'|'/'|'%'|'//') factor)* # factor: ('+'|'-'|'~') factor | power # comp_op: '<'|'>'|'=='|'>='|'<='|'<>'|'!='|'in'|'not' 'in'|'is'|'is' 'not' def make_lt_compare((left, right)): return ast.Compare(left, [('<', right),]) def make_gt_compare((left, right)): return ast.Compare(left, [('>', right),]) def make_eq_compare((left, right)): return ast.Compare(left, [('==', right),]) binary_ops = { "+": ast.Add, "-": ast.Sub, "*": ast.Mul, "/": ast.Div, "<": make_lt_compare, ">": make_gt_compare, "==": make_eq_compare, } unary_ops = { "+": ast.UnaryAdd, "-": ast.UnarySub, } precedence = ( ("left", "EQ", "GT", "LT"), ("left", "PLUS", "MINUS"), ("left", "MULT", "DIV"), ) def p_comparison(p): """comparison : comparison PLUS comparison | comparison MINUS comparison | comparison MULT comparison | comparison DIV comparison | comparison LT comparison | comparison EQ comparison | comparison GT comparison | PLUS comparison | MINUS comparison | power""" if len(p) == 4: p[0] = binary_ops[p[2]]((p[1], p[3])) elif len(p) == 3: p[0] = unary_ops[p[1]](p[2]) else: p[0] = p[1] # power: atom trailer* ['**' factor] # trailers enables function calls. I only allow one level of calls # so this is 'trailer' def p_power(p): """power : atom | atom trailer""" if len(p) == 2: p[0] = p[1] else: if p[2][0] == "CALL": p[0] = ast.CallFunc(p[1], p[2][1], None, None) else: raise AssertionError("not implemented") def p_atom_name(p): """atom : NAME""" p[0] = ast.Name(p[1]) def p_atom_number(p): """atom : NUMBER | STRING""" p[0] = ast.Const(p[1]) def p_atom_tuple(p): """atom : LPAR testlist RPAR""" p[0] = p[2] # trailer: '(' [arglist] ')' | '[' subscriptlist ']' | '.' NAME def p_trailer(p): "trailer : LPAR arglist RPAR" p[0] = ("CALL", p[2]) # testlist: test (',' test)* [','] # Contains shift/reduce error def p_testlist(p): """testlist : testlist_multi COMMA | testlist_multi """ if len(p) == 2: p[0] = p[1] else: # May need to promote singleton to tuple if isinstance(p[1], list): p[0] = p[1] else: p[0] = [p[1]] # Convert into a tuple? if isinstance(p[0], list): p[0] = ast.Tuple(p[0]) def p_testlist_multi(p): """testlist_multi : testlist_multi COMMA test | test""" if len(p) == 2: # singleton p[0] = p[1] else: if isinstance(p[1], list): p[0] = p[1] + [p[3]] else: # singleton -> tuple p[0] = [p[1], p[3]] # test: or_test ['if' or_test 'else' test] | lambdef # as I don't support 'and', 'or', and 'not' this works down to 'comparison' def p_test(p): "test : comparison" p[0] = p[1] # arglist: (argument ',')* (argument [',']| '*' test [',' '**' test] | '**' test) # XXX INCOMPLETE: this doesn't allow the trailing comma def p_arglist(p): """arglist : arglist COMMA argument | argument""" if len(p) == 4: p[0] = p[1] + [p[3]] else: p[0] = [p[1]] # argument: test [gen_for] | test '=' test # Really [keyword '='] test def p_argument(p): "argument : test" p[0] = p[1] def p_error(p): #print "Error!", repr(p) raise SyntaxError(p) class GardenSnakeParser(object): def __init__(self, lexer = None): if lexer is None: lexer = IndentLexer() self.lexer = lexer self.parser = yacc.yacc(start="file_input_end") def parse(self, code): self.lexer.input(code) result = self.parser.parse(lexer = self.lexer) return ast.Module(None, result) ###### Code generation ###### from compiler import misc, syntax, pycodegen class GardenSnakeCompiler(object): def __init__(self): self.parser = GardenSnakeParser() def compile(self, code, filename=""): tree = self.parser.parse(code) #print tree misc.set_filename(filename, tree) syntax.check(tree) gen = pycodegen.ModuleCodeGenerator(tree) code = gen.getCode() return code ####### Test code ####### compile = GardenSnakeCompiler().compile code = r""" print('LET\'S TRY THIS \\OUT') #Comment here def x(a): print('called with',a) if a == 1: return 2 if a*2 > 10: return 999 / 4 # Another comment here return a+2*3 ints = (1, 2, 3, 4, 5) print('mutiline-expression', ints) t = 4+1/3*2+6*(9-5+1) print('predence test; should be 34+2/3:', t, t==(34+2/3)) print('numbers', 1,2,3,4,5) if 1: 8 a=9 print(x(a)) print(x(1)) print(x(2)) print(x(8),'3') print('this is decimal', 1/5) print('BIG DECIMAL', 1.234567891234567e12345) """ # Set up the GardenSnake run-time environment def print_(*args): print "-->", " ".join(map(str,args)) globals()["print"] = print_ compiled_code = compile(code) exec compiled_code in globals() print "Done" ./CBFlib-0.9.2.2/ply-3.2/example/calcdebug/0000755000076500007650000000000011603703074016253 5ustar yayayaya./CBFlib-0.9.2.2/ply-3.2/example/calcdebug/calc.py0000644000076500007650000000440211603702121017517 0ustar yayayaya# ----------------------------------------------------------------------------- # calc.py # # This example shows how to run the parser in a debugging mode # with output routed to a logging object. # ----------------------------------------------------------------------------- import sys sys.path.insert(0,"../..") if sys.version_info[0] >= 3: raw_input = input tokens = ( 'NAME','NUMBER', ) literals = ['=','+','-','*','/', '(',')'] # Tokens t_NAME = r'[a-zA-Z_][a-zA-Z0-9_]*' def t_NUMBER(t): r'\d+' t.value = int(t.value) return t t_ignore = " \t" def t_newline(t): r'\n+' t.lexer.lineno += t.value.count("\n") def t_error(t): print("Illegal character '%s'" % t.value[0]) t.lexer.skip(1) # Build the lexer import ply.lex as lex lex.lex() # Parsing rules precedence = ( ('left','+','-'), ('left','*','/'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(p): 'statement : NAME "=" expression' names[p[1]] = p[3] def p_statement_expr(p): 'statement : expression' print(p[1]) def p_expression_binop(p): '''expression : expression '+' expression | expression '-' expression | expression '*' expression | expression '/' expression''' if p[2] == '+' : p[0] = p[1] + p[3] elif p[2] == '-': p[0] = p[1] - p[3] elif p[2] == '*': p[0] = p[1] * p[3] elif p[2] == '/': p[0] = p[1] / p[3] def p_expression_uminus(p): "expression : '-' expression %prec UMINUS" p[0] = -p[2] def p_expression_group(p): "expression : '(' expression ')'" p[0] = p[2] def p_expression_number(p): "expression : NUMBER" p[0] = p[1] def p_expression_name(p): "expression : NAME" try: p[0] = names[p[1]] except LookupError: print("Undefined name '%s'" % p[1]) p[0] = 0 def p_error(p): if p: print("Syntax error at '%s'" % p.value) else: print("Syntax error at EOF") import ply.yacc as yacc yacc.yacc() import logging logging.basicConfig( level=logging.INFO, filename="parselog.txt" ) while 1: try: s = raw_input('calc > ') except EOFError: break if not s: continue yacc.parse(s,debug=logging.getLogger()) ./CBFlib-0.9.2.2/ply-3.2/example/unicalc/0000755000076500007650000000000011603703074015760 5ustar yayayaya./CBFlib-0.9.2.2/ply-3.2/example/unicalc/calc.py0000644000076500007650000000470611603702121017233 0ustar yayayaya# ----------------------------------------------------------------------------- # calc.py # # A simple calculator with variables. This is from O'Reilly's # "Lex and Yacc", p. 63. # # This example uses unicode strings for tokens, docstrings, and input. # ----------------------------------------------------------------------------- import sys sys.path.insert(0,"../..") tokens = ( 'NAME','NUMBER', 'PLUS','MINUS','TIMES','DIVIDE','EQUALS', 'LPAREN','RPAREN', ) # Tokens t_PLUS = ur'\+' t_MINUS = ur'-' t_TIMES = ur'\*' t_DIVIDE = ur'/' t_EQUALS = ur'=' t_LPAREN = ur'\(' t_RPAREN = ur'\)' t_NAME = ur'[a-zA-Z_][a-zA-Z0-9_]*' def t_NUMBER(t): ur'\d+' try: t.value = int(t.value) except ValueError: print "Integer value too large", t.value t.value = 0 return t t_ignore = u" \t" def t_newline(t): ur'\n+' t.lexer.lineno += t.value.count("\n") def t_error(t): print "Illegal character '%s'" % t.value[0] t.lexer.skip(1) # Build the lexer import ply.lex as lex lex.lex() # Parsing rules precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(p): 'statement : NAME EQUALS expression' names[p[1]] = p[3] def p_statement_expr(p): 'statement : expression' print p[1] def p_expression_binop(p): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if p[2] == u'+' : p[0] = p[1] + p[3] elif p[2] == u'-': p[0] = p[1] - p[3] elif p[2] == u'*': p[0] = p[1] * p[3] elif p[2] == u'/': p[0] = p[1] / p[3] def p_expression_uminus(p): 'expression : MINUS expression %prec UMINUS' p[0] = -p[2] def p_expression_group(p): 'expression : LPAREN expression RPAREN' p[0] = p[2] def p_expression_number(p): 'expression : NUMBER' p[0] = p[1] def p_expression_name(p): 'expression : NAME' try: p[0] = names[p[1]] except LookupError: print "Undefined name '%s'" % p[1] p[0] = 0 def p_error(p): if p: print "Syntax error at '%s'" % p.value else: print "Syntax error at EOF" import ply.yacc as yacc yacc.yacc() while 1: try: s = raw_input('calc > ') except EOFError: break if not s: continue yacc.parse(unicode(s)) ./CBFlib-0.9.2.2/ply-3.2/example/newclasscalc/0000755000076500007650000000000011603703074017004 5ustar yayayaya./CBFlib-0.9.2.2/ply-3.2/example/newclasscalc/calc.py0000755000076500007650000001003511603702121020252 0ustar yayayaya#!/usr/bin/env python # ----------------------------------------------------------------------------- # calc.py # # A simple calculator with variables. This is from O'Reilly's # "Lex and Yacc", p. 63. # # Class-based example contributed to PLY by David McNab. # # Modified to use new-style classes. Test case. # ----------------------------------------------------------------------------- import sys sys.path.insert(0,"../..") if sys.version_info[0] >= 3: raw_input = input import ply.lex as lex import ply.yacc as yacc import os class Parser(object): """ Base class for a lexer/parser that has the rules defined as methods """ tokens = () precedence = () def __init__(self, **kw): self.debug = kw.get('debug', 0) self.names = { } try: modname = os.path.split(os.path.splitext(__file__)[0])[1] + "_" + self.__class__.__name__ except: modname = "parser"+"_"+self.__class__.__name__ self.debugfile = modname + ".dbg" self.tabmodule = modname + "_" + "parsetab" #print self.debugfile, self.tabmodule # Build the lexer and parser lex.lex(module=self, debug=self.debug) yacc.yacc(module=self, debug=self.debug, debugfile=self.debugfile, tabmodule=self.tabmodule) def run(self): while 1: try: s = raw_input('calc > ') except EOFError: break if not s: continue yacc.parse(s) class Calc(Parser): tokens = ( 'NAME','NUMBER', 'PLUS','MINUS','EXP', 'TIMES','DIVIDE','EQUALS', 'LPAREN','RPAREN', ) # Tokens t_PLUS = r'\+' t_MINUS = r'-' t_EXP = r'\*\*' t_TIMES = r'\*' t_DIVIDE = r'/' t_EQUALS = r'=' t_LPAREN = r'\(' t_RPAREN = r'\)' t_NAME = r'[a-zA-Z_][a-zA-Z0-9_]*' def t_NUMBER(self, t): r'\d+' try: t.value = int(t.value) except ValueError: print("Integer value too large %s" % t.value) t.value = 0 #print "parsed number %s" % repr(t.value) return t t_ignore = " \t" def t_newline(self, t): r'\n+' t.lexer.lineno += t.value.count("\n") def t_error(self, t): print("Illegal character '%s'" % t.value[0]) t.lexer.skip(1) # Parsing rules precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE'), ('left', 'EXP'), ('right','UMINUS'), ) def p_statement_assign(self, p): 'statement : NAME EQUALS expression' self.names[p[1]] = p[3] def p_statement_expr(self, p): 'statement : expression' print(p[1]) def p_expression_binop(self, p): """ expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression | expression EXP expression """ #print [repr(p[i]) for i in range(0,4)] if p[2] == '+' : p[0] = p[1] + p[3] elif p[2] == '-': p[0] = p[1] - p[3] elif p[2] == '*': p[0] = p[1] * p[3] elif p[2] == '/': p[0] = p[1] / p[3] elif p[2] == '**': p[0] = p[1] ** p[3] def p_expression_uminus(self, p): 'expression : MINUS expression %prec UMINUS' p[0] = -p[2] def p_expression_group(self, p): 'expression : LPAREN expression RPAREN' p[0] = p[2] def p_expression_number(self, p): 'expression : NUMBER' p[0] = p[1] def p_expression_name(self, p): 'expression : NAME' try: p[0] = self.names[p[1]] except LookupError: print("Undefined name '%s'" % p[1]) p[0] = 0 def p_error(self, p): if p: print("Syntax error at '%s'" % p.value) else: print("Syntax error at EOF") if __name__ == '__main__': calc = Calc() calc.run() ./CBFlib-0.9.2.2/ply-3.2/example/cleanup.sh0000755000076500007650000000010211603702121016311 0ustar yayayaya#!/bin/sh rm -f */*.pyc */parsetab.py */parser.out */*~ */*.class ./CBFlib-0.9.2.2/ply-3.2/example/classcalc/0000755000076500007650000000000011603703074016272 5ustar yayayaya./CBFlib-0.9.2.2/ply-3.2/example/classcalc/calc.py0000755000076500007650000000773211603702121017552 0ustar yayayaya#!/usr/bin/env python # ----------------------------------------------------------------------------- # calc.py # # A simple calculator with variables. This is from O'Reilly's # "Lex and Yacc", p. 63. # # Class-based example contributed to PLY by David McNab # ----------------------------------------------------------------------------- import sys sys.path.insert(0,"../..") if sys.version_info[0] >= 3: raw_input = input import ply.lex as lex import ply.yacc as yacc import os class Parser: """ Base class for a lexer/parser that has the rules defined as methods """ tokens = () precedence = () def __init__(self, **kw): self.debug = kw.get('debug', 0) self.names = { } try: modname = os.path.split(os.path.splitext(__file__)[0])[1] + "_" + self.__class__.__name__ except: modname = "parser"+"_"+self.__class__.__name__ self.debugfile = modname + ".dbg" self.tabmodule = modname + "_" + "parsetab" #print self.debugfile, self.tabmodule # Build the lexer and parser lex.lex(module=self, debug=self.debug) yacc.yacc(module=self, debug=self.debug, debugfile=self.debugfile, tabmodule=self.tabmodule) def run(self): while 1: try: s = raw_input('calc > ') except EOFError: break if not s: continue yacc.parse(s) class Calc(Parser): tokens = ( 'NAME','NUMBER', 'PLUS','MINUS','EXP', 'TIMES','DIVIDE','EQUALS', 'LPAREN','RPAREN', ) # Tokens t_PLUS = r'\+' t_MINUS = r'-' t_EXP = r'\*\*' t_TIMES = r'\*' t_DIVIDE = r'/' t_EQUALS = r'=' t_LPAREN = r'\(' t_RPAREN = r'\)' t_NAME = r'[a-zA-Z_][a-zA-Z0-9_]*' def t_NUMBER(self, t): r'\d+' try: t.value = int(t.value) except ValueError: print("Integer value too large %s" % t.value) t.value = 0 #print "parsed number %s" % repr(t.value) return t t_ignore = " \t" def t_newline(self, t): r'\n+' t.lexer.lineno += t.value.count("\n") def t_error(self, t): print("Illegal character '%s'" % t.value[0]) t.lexer.skip(1) # Parsing rules precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE'), ('left', 'EXP'), ('right','UMINUS'), ) def p_statement_assign(self, p): 'statement : NAME EQUALS expression' self.names[p[1]] = p[3] def p_statement_expr(self, p): 'statement : expression' print(p[1]) def p_expression_binop(self, p): """ expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression | expression EXP expression """ #print [repr(p[i]) for i in range(0,4)] if p[2] == '+' : p[0] = p[1] + p[3] elif p[2] == '-': p[0] = p[1] - p[3] elif p[2] == '*': p[0] = p[1] * p[3] elif p[2] == '/': p[0] = p[1] / p[3] elif p[2] == '**': p[0] = p[1] ** p[3] def p_expression_uminus(self, p): 'expression : MINUS expression %prec UMINUS' p[0] = -p[2] def p_expression_group(self, p): 'expression : LPAREN expression RPAREN' p[0] = p[2] def p_expression_number(self, p): 'expression : NUMBER' p[0] = p[1] def p_expression_name(self, p): 'expression : NAME' try: p[0] = self.names[p[1]] except LookupError: print("Undefined name '%s'" % p[1]) p[0] = 0 def p_error(self, p): if p: print("Syntax error at '%s'" % p.value) else: print("Syntax error at EOF") if __name__ == '__main__': calc = Calc() calc.run() ./CBFlib-0.9.2.2/ply-3.2/example/optcalc/0000755000076500007650000000000011603703074015767 5ustar yayayaya./CBFlib-0.9.2.2/ply-3.2/example/optcalc/README0000644000076500007650000000030311603702121016633 0ustar yayayayaAn example showing how to use Python optimized mode. To run: - First run 'python calc.py' - Then run 'python -OO calc.py' If working correctly, the second version should run the same way. ./CBFlib-0.9.2.2/ply-3.2/example/optcalc/calc.py0000644000076500007650000000471211603702121017237 0ustar yayayaya# ----------------------------------------------------------------------------- # calc.py # # A simple calculator with variables. This is from O'Reilly's # "Lex and Yacc", p. 63. # ----------------------------------------------------------------------------- import sys sys.path.insert(0,"../..") if sys.version_info[0] >= 3: raw_input = input tokens = ( 'NAME','NUMBER', 'PLUS','MINUS','TIMES','DIVIDE','EQUALS', 'LPAREN','RPAREN', ) # Tokens t_PLUS = r'\+' t_MINUS = r'-' t_TIMES = r'\*' t_DIVIDE = r'/' t_EQUALS = r'=' t_LPAREN = r'\(' t_RPAREN = r'\)' t_NAME = r'[a-zA-Z_][a-zA-Z0-9_]*' def t_NUMBER(t): r'\d+' try: t.value = int(t.value) except ValueError: print("Integer value too large %s" % t.value) t.value = 0 return t t_ignore = " \t" def t_newline(t): r'\n+' t.lexer.lineno += t.value.count("\n") def t_error(t): print("Illegal character '%s'" % t.value[0]) t.lexer.skip(1) # Build the lexer import ply.lex as lex lex.lex(optimize=1) # Parsing rules precedence = ( ('left','PLUS','MINUS'), ('left','TIMES','DIVIDE'), ('right','UMINUS'), ) # dictionary of names names = { } def p_statement_assign(t): 'statement : NAME EQUALS expression' names[t[1]] = t[3] def p_statement_expr(t): 'statement : expression' print(t[1]) def p_expression_binop(t): '''expression : expression PLUS expression | expression MINUS expression | expression TIMES expression | expression DIVIDE expression''' if t[2] == '+' : t[0] = t[1] + t[3] elif t[2] == '-': t[0] = t[1] - t[3] elif t[2] == '*': t[0] = t[1] * t[3] elif t[2] == '/': t[0] = t[1] / t[3] elif t[2] == '<': t[0] = t[1] < t[3] def p_expression_uminus(t): 'expression : MINUS expression %prec UMINUS' t[0] = -t[2] def p_expression_group(t): 'expression : LPAREN expression RPAREN' t[0] = t[2] def p_expression_number(t): 'expression : NUMBER' t[0] = t[1] def p_expression_name(t): 'expression : NAME' try: t[0] = names[t[1]] except LookupError: print("Undefined name '%s'" % t[1]) t[0] = 0 def p_error(t): if t: print("Syntax error at '%s'" % t.value) else: print("Syntax error at EOF") import ply.yacc as yacc yacc.yacc(optimize=1) while 1: try: s = raw_input('calc > ') except EOFError: break yacc.parse(s) ./CBFlib-0.9.2.2/ply-3.2/ANNOUNCE0000644000076500007650000000274711603702121014042 0ustar yayayayaMarch 24, 2009 Announcing : PLY-3.2 (Python Lex-Yacc) http://www.dabeaz.com/ply I'm pleased to announce a significant new update to PLY---a 100% Python implementation of the common parsing tools lex and yacc. PLY-3.2 adds compatibility for Python 2.6 and 3.0, provides some new customization options, and cleans up a lot of internal implementation details. If you are new to PLY, here are a few highlights: - PLY is closely modeled after traditional lex/yacc. If you know how to use these or similar tools in other languages, you will find PLY to be comparable. - PLY provides very extensive error reporting and diagnostic information to assist in parser construction. The original implementation was developed for instructional purposes. As a result, the system tries to identify the most common types of errors made by novice users. - PLY provides full support for empty productions, error recovery, precedence rules, and ambiguous grammars. - Parsing is based on LR-parsing which is fast, memory efficient, better suited to large grammars, and which has a number of nice properties when dealing with syntax errors and other parsing problems. Currently, PLY can build its parsing tables using either SLR or LALR(1) algorithms. More information about PLY can be obtained on the PLY webpage at: http://www.dabeaz.com/ply PLY is freely available. Cheers, David Beazley (http://www.dabeaz.com)./CBFlib-0.9.2.2/ply-3.2/setup.py0000644000076500007650000000174511603702121014420 0ustar yayayayatry: from setuptools import setup except ImportError: from distutils.core import setup setup(name = "ply", description="Python Lex & Yacc", long_description = """ PLY is yet another implementation of lex and yacc for Python. Some notable features include the fact that its implemented entirely in Python and it uses LALR(1) parsing which is efficient and well suited for larger grammars. PLY provides most of the standard lex/yacc features including support for empty productions, precedence rules, error recovery, and support for ambiguous grammars. PLY is extremely easy to use and provides very extensive error checking. """, license="""BSD""", version = "3.2", author = "David Beazley", author_email = "dave@dabeaz.com", maintainer = "David Beazley", maintainer_email = "dave@dabeaz.com", url = "http://www.dabeaz.com/ply/", packages = ['ply'], ) ./CBFlib-0.9.2.2/ply-3.2/CHANGES0000644000076500007650000012467711603702121013713 0ustar yayayaya Version 3.2 ----------------------------- 03/24/09: beazley Added an extra check to not print duplicated warning messages about reduce/reduce conflicts. 03/24/09: beazley Switched PLY over to a BSD-license. 03/23/09: beazley Performance optimization. Discovered a few places to make speedups in LR table generation. 03/23/09: beazley New warning message. PLY now warns about rules never reduced due to reduce/reduce conflicts. Suggested by Bruce Frederiksen. 03/23/09: beazley Some clean-up of warning messages related to reduce/reduce errors. 03/23/09: beazley Added a new picklefile option to yacc() to write the parsing tables to a filename using the pickle module. Here is how it works: yacc(picklefile="parsetab.p") This option can be used if the normal parsetab.py file is extremely large. For example, on jython, it is impossible to read parsing tables if the parsetab.py exceeds a certain threshold. The filename supplied to the picklefile option is opened relative to the current working directory of the Python interpreter. If you need to refer to the file elsewhere, you will need to supply an absolute or relative path. For maximum portability, the pickle file is written using protocol 0. 03/13/09: beazley Fixed a bug in parser.out generation where the rule numbers where off by one. 03/13/09: beazley Fixed a string formatting bug with one of the error messages. Reported by Richard Reitmeyer Version 3.1 ----------------------------- 02/28/09: beazley Fixed broken start argument to yacc(). PLY-3.0 broke this feature by accident. 02/28/09: beazley Fixed debugging output. yacc() no longer reports shift/reduce or reduce/reduce conflicts if debugging is turned off. This restores similar behavior in PLY-2.5. Reported by Andrew Waters. Version 3.0 ----------------------------- 02/03/09: beazley Fixed missing lexer attribute on certain tokens when invoking the parser p_error() function. Reported by Bart Whiteley. 02/02/09: beazley The lex() command now does all error-reporting and diagonistics using the logging module interface. Pass in a Logger object using the errorlog parameter to specify a different logger. 02/02/09: beazley Refactored ply.lex to use a more object-oriented and organized approach to collecting lexer information. 02/01/09: beazley Removed the nowarn option from lex(). All output is controlled by passing in a logger object. Just pass in a logger with a high level setting to suppress output. This argument was never documented to begin with so hopefully no one was relying upon it. 02/01/09: beazley Discovered and removed a dead if-statement in the lexer. This resulted in a 6-7% speedup in lexing when I tested it. 01/13/09: beazley Minor change to the procedure for signalling a syntax error in a production rule. A normal SyntaxError exception should be raised instead of yacc.SyntaxError. 01/13/09: beazley Added a new method p.set_lineno(n,lineno) that can be used to set the line number of symbol n in grammar rules. This simplifies manual tracking of line numbers. 01/11/09: beazley Vastly improved debugging support for yacc.parse(). Instead of passing debug as an integer, you can supply a Logging object (see the logging module). Messages will be generated at the ERROR, INFO, and DEBUG logging levels, each level providing progressively more information. The debugging trace also shows states, grammar rule, values passed into grammar rules, and the result of each reduction. 01/09/09: beazley The yacc() command now does all error-reporting and diagnostics using the interface of the logging module. Use the errorlog parameter to specify a logging object for error messages. Use the debuglog parameter to specify a logging object for the 'parser.out' output. 01/09/09: beazley *HUGE* refactoring of the the ply.yacc() implementation. The high-level user interface is backwards compatible, but the internals are completely reorganized into classes. No more global variables. The internals are also more extensible. For example, you can use the classes to construct a LALR(1) parser in an entirely different manner than what is currently the case. Documentation is forthcoming. 01/07/09: beazley Various cleanup and refactoring of yacc internals. 01/06/09: beazley Fixed a bug with precedence assignment. yacc was assigning the precedence each rule based on the left-most token, when in fact, it should have been using the right-most token. Reported by Bruce Frederiksen. 11/27/08: beazley Numerous changes to support Python 3.0 including removal of deprecated statements (e.g., has_key) and the additional of compatibility code to emulate features from Python 2 that have been removed, but which are needed. Fixed the unit testing suite to work with Python 3.0. The code should be backwards compatible with Python 2. 11/26/08: beazley Loosened the rules on what kind of objects can be passed in as the "module" parameter to lex() and yacc(). Previously, you could only use a module or an instance. Now, PLY just uses dir() to get a list of symbols on whatever the object is without regard for its type. 11/26/08: beazley Changed all except: statements to be compatible with Python2.x/3.x syntax. 11/26/08: beazley Changed all raise Exception, value statements to raise Exception(value) for forward compatibility. 11/26/08: beazley Removed all print statements from lex and yacc, using sys.stdout and sys.stderr directly. Preparation for Python 3.0 support. 11/04/08: beazley Fixed a bug with referring to symbols on the the parsing stack using negative indices. 05/29/08: beazley Completely revamped the testing system to use the unittest module for everything. Added additional tests to cover new errors/warnings. Version 2.5 ----------------------------- 05/28/08: beazley Fixed a bug with writing lex-tables in optimized mode and start states. Reported by Kevin Henry. Version 2.4 ----------------------------- 05/04/08: beazley A version number is now embedded in the table file signature so that yacc can more gracefully accomodate changes to the output format in the future. 05/04/08: beazley Removed undocumented .pushback() method on grammar productions. I'm not sure this ever worked and can't recall ever using it. Might have been an abandoned idea that never really got fleshed out. This feature was never described or tested so removing it is hopefully harmless. 05/04/08: beazley Added extra error checking to yacc() to detect precedence rules defined for undefined terminal symbols. This allows yacc() to detect a potential problem that can be really tricky to debug if no warning message or error message is generated about it. 05/04/08: beazley lex() now has an outputdir that can specify the output directory for tables when running in optimize mode. For example: lexer = lex.lex(optimize=True, lextab="ltab", outputdir="foo/bar") The behavior of specifying a table module and output directory are more aligned with the behavior of yacc(). 05/04/08: beazley [Issue 9] Fixed filename bug in when specifying the modulename in lex() and yacc(). If you specified options such as the following: parser = yacc.yacc(tabmodule="foo.bar.parsetab",outputdir="foo/bar") yacc would create a file "foo.bar.parsetab.py" in the given directory. Now, it simply generates a file "parsetab.py" in that directory. Bug reported by cptbinho. 05/04/08: beazley Slight modification to lex() and yacc() to allow their table files to be loaded from a previously loaded module. This might make it easier to load the parsing tables from a complicated package structure. For example: import foo.bar.spam.parsetab as parsetab parser = yacc.yacc(tabmodule=parsetab) Note: lex and yacc will never regenerate the table file if used in the form---you will get a warning message instead. This idea suggested by Brian Clapper. 04/28/08: beazley Fixed a big with p_error() functions being picked up correctly when running in yacc(optimize=1) mode. Patch contributed by Bart Whiteley. 02/28/08: beazley Fixed a bug with 'nonassoc' precedence rules. Basically the non-precedence was being ignored and not producing the correct run-time behavior in the parser. 02/16/08: beazley Slight relaxation of what the input() method to a lexer will accept as a string. Instead of testing the input to see if the input is a string or unicode string, it checks to see if the input object looks like it contains string data. This change makes it possible to pass string-like objects in as input. For example, the object returned by mmap. import mmap, os data = mmap.mmap(os.open(filename,os.O_RDONLY), os.path.getsize(filename), access=mmap.ACCESS_READ) lexer.input(data) 11/29/07: beazley Modification of ply.lex to allow token functions to aliased. This is subtle, but it makes it easier to create libraries and to reuse token specifications. For example, suppose you defined a function like this: def number(t): r'\d+' t.value = int(t.value) return t This change would allow you to define a token rule as follows: t_NUMBER = number In this case, the token type will be set to 'NUMBER' and use the associated number() function to process tokens. 11/28/07: beazley Slight modification to lex and yacc to grab symbols from both the local and global dictionaries of the caller. This modification allows lexers and parsers to be defined using inner functions and closures. 11/28/07: beazley Performance optimization: The lexer.lexmatch and t.lexer attributes are no longer set for lexer tokens that are not defined by functions. The only normal use of these attributes would be in lexer rules that need to perform some kind of special processing. Thus, it doesn't make any sense to set them on every token. *** POTENTIAL INCOMPATIBILITY *** This might break code that is mucking around with internal lexer state in some sort of magical way. 11/27/07: beazley Added the ability to put the parser into error-handling mode from within a normal production. To do this, simply raise a yacc.SyntaxError exception like this: def p_some_production(p): 'some_production : prod1 prod2' ... raise yacc.SyntaxError # Signal an error A number of things happen after this occurs: - The last symbol shifted onto the symbol stack is discarded and parser state backed up to what it was before the the rule reduction. - The current lookahead symbol is saved and replaced by the 'error' symbol. - The parser enters error recovery mode where it tries to either reduce the 'error' rule or it starts discarding items off of the stack until the parser resets. When an error is manually set, the parser does *not* call the p_error() function (if any is defined). *** NEW FEATURE *** Suggested on the mailing list 11/27/07: beazley Fixed structure bug in examples/ansic. Reported by Dion Blazakis. 11/27/07: beazley Fixed a bug in the lexer related to start conditions and ignored token rules. If a rule was defined that changed state, but returned no token, the lexer could be left in an inconsistent state. Reported by 11/27/07: beazley Modified setup.py to support Python Eggs. Patch contributed by Simon Cross. 11/09/07: beazely Fixed a bug in error handling in yacc. If a syntax error occurred and the parser rolled the entire parse stack back, the parser would be left in in inconsistent state that would cause it to trigger incorrect actions on subsequent input. Reported by Ton Biegstraaten, Justin King, and others. 11/09/07: beazley Fixed a bug when passing empty input strings to yacc.parse(). This would result in an error message about "No input given". Reported by Andrew Dalke. Version 2.3 ----------------------------- 02/20/07: beazley Fixed a bug with character literals if the literal '.' appeared as the last symbol of a grammar rule. Reported by Ales Smrcka. 02/19/07: beazley Warning messages are now redirected to stderr instead of being printed to standard output. 02/19/07: beazley Added a warning message to lex.py if it detects a literal backslash character inside the t_ignore declaration. This is to help problems that might occur if someone accidentally defines t_ignore as a Python raw string. For example: t_ignore = r' \t' The idea for this is from an email I received from David Cimimi who reported bizarre behavior in lexing as a result of defining t_ignore as a raw string by accident. 02/18/07: beazley Performance improvements. Made some changes to the internal table organization and LR parser to improve parsing performance. 02/18/07: beazley Automatic tracking of line number and position information must now be enabled by a special flag to parse(). For example: yacc.parse(data,tracking=True) In many applications, it's just not that important to have the parser automatically track all line numbers. By making this an optional feature, it allows the parser to run significantly faster (more than a 20% speed increase in many cases). Note: positional information is always available for raw tokens---this change only applies to positional information associated with nonterminal grammar symbols. *** POTENTIAL INCOMPATIBILITY *** 02/18/07: beazley Yacc no longer supports extended slices of grammar productions. However, it does support regular slices. For example: def p_foo(p): '''foo: a b c d e''' p[0] = p[1:3] This change is a performance improvement to the parser--it streamlines normal access to the grammar values since slices are now handled in a __getslice__() method as opposed to __getitem__(). 02/12/07: beazley Fixed a bug in the handling of token names when combined with start conditions. Bug reported by Todd O'Bryan. Version 2.2 ------------------------------ 11/01/06: beazley Added lexpos() and lexspan() methods to grammar symbols. These mirror the same functionality of lineno() and linespan(). For example: def p_expr(p): 'expr : expr PLUS expr' p.lexpos(1) # Lexing position of left-hand-expression p.lexpos(1) # Lexing position of PLUS start,end = p.lexspan(3) # Lexing range of right hand expression 11/01/06: beazley Minor change to error handling. The recommended way to skip characters in the input is to use t.lexer.skip() as shown here: def t_error(t): print "Illegal character '%s'" % t.value[0] t.lexer.skip(1) The old approach of just using t.skip(1) will still work, but won't be documented. 10/31/06: beazley Discarded tokens can now be specified as simple strings instead of functions. To do this, simply include the text "ignore_" in the token declaration. For example: t_ignore_cppcomment = r'//.*' Previously, this had to be done with a function. For example: def t_ignore_cppcomment(t): r'//.*' pass If start conditions/states are being used, state names should appear before the "ignore_" text. 10/19/06: beazley The Lex module now provides support for flex-style start conditions as described at http://www.gnu.org/software/flex/manual/html_chapter/flex_11.html. Please refer to this document to understand this change note. Refer to the PLY documentation for PLY-specific explanation of how this works. To use start conditions, you first need to declare a set of states in your lexer file: states = ( ('foo','exclusive'), ('bar','inclusive') ) This serves the same role as the %s and %x specifiers in flex. One a state has been declared, tokens for that state can be declared by defining rules of the form t_state_TOK. For example: t_PLUS = '\+' # Rule defined in INITIAL state t_foo_NUM = '\d+' # Rule defined in foo state t_bar_NUM = '\d+' # Rule defined in bar state t_foo_bar_NUM = '\d+' # Rule defined in both foo and bar t_ANY_NUM = '\d+' # Rule defined in all states In addition to defining tokens for each state, the t_ignore and t_error specifications can be customized for specific states. For example: t_foo_ignore = " " # Ignored characters for foo state def t_bar_error(t): # Handle errors in bar state With token rules, the following methods can be used to change states def t_TOKNAME(t): t.lexer.begin('foo') # Begin state 'foo' t.lexer.push_state('foo') # Begin state 'foo', push old state # onto a stack t.lexer.pop_state() # Restore previous state t.lexer.current_state() # Returns name of current state These methods mirror the BEGIN(), yy_push_state(), yy_pop_state(), and yy_top_state() functions in flex. The use of start states can be used as one way to write sub-lexers. For example, the lexer or parser might instruct the lexer to start generating a different set of tokens depending on the context. example/yply/ylex.py shows the use of start states to grab C/C++ code fragments out of traditional yacc specification files. *** NEW FEATURE *** Suggested by Daniel Larraz with whom I also discussed various aspects of the design. 10/19/06: beazley Minor change to the way in which yacc.py was reporting shift/reduce conflicts. Although the underlying LALR(1) algorithm was correct, PLY was under-reporting the number of conflicts compared to yacc/bison when precedence rules were in effect. This change should make PLY report the same number of conflicts as yacc. 10/19/06: beazley Modified yacc so that grammar rules could also include the '-' character. For example: def p_expr_list(p): 'expression-list : expression-list expression' Suggested by Oldrich Jedlicka. 10/18/06: beazley Attribute lexer.lexmatch added so that token rules can access the re match object that was generated. For example: def t_FOO(t): r'some regex' m = t.lexer.lexmatch # Do something with m This may be useful if you want to access named groups specified within the regex for a specific token. Suggested by Oldrich Jedlicka. 10/16/06: beazley Changed the error message that results if an illegal character is encountered and no default error function is defined in lex. The exception is now more informative about the actual cause of the error. Version 2.1 ------------------------------ 10/02/06: beazley The last Lexer object built by lex() can be found in lex.lexer. The last Parser object built by yacc() can be found in yacc.parser. 10/02/06: beazley New example added: examples/yply This example uses PLY to convert Unix-yacc specification files to PLY programs with the same grammar. This may be useful if you want to convert a grammar from bison/yacc to use with PLY. 10/02/06: beazley Added support for a start symbol to be specified in the yacc input file itself. Just do this: start = 'name' where 'name' matches some grammar rule. For example: def p_name(p): 'name : A B C' ... This mirrors the functionality of the yacc %start specifier. 09/30/06: beazley Some new examples added.: examples/GardenSnake : A simple indentation based language similar to Python. Shows how you might handle whitespace. Contributed by Andrew Dalke. examples/BASIC : An implementation of 1964 Dartmouth BASIC. Contributed by Dave against his better judgement. 09/28/06: beazley Minor patch to allow named groups to be used in lex regular expression rules. For example: t_QSTRING = r'''(?P['"]).*?(?P=quote)''' Patch submitted by Adam Ring. 09/28/06: beazley LALR(1) is now the default parsing method. To use SLR, use yacc.yacc(method="SLR"). Note: there is no performance impact on parsing when using LALR(1) instead of SLR. However, constructing the parsing tables will take a little longer. 09/26/06: beazley Change to line number tracking. To modify line numbers, modify the line number of the lexer itself. For example: def t_NEWLINE(t): r'\n' t.lexer.lineno += 1 This modification is both cleanup and a performance optimization. In past versions, lex was monitoring every token for changes in the line number. This extra processing is unnecessary for a vast majority of tokens. Thus, this new approach cleans it up a bit. *** POTENTIAL INCOMPATIBILITY *** You will need to change code in your lexer that updates the line number. For example, "t.lineno += 1" becomes "t.lexer.lineno += 1" 09/26/06: beazley Added the lexing position to tokens as an attribute lexpos. This is the raw index into the input text at which a token appears. This information can be used to compute column numbers and other details (e.g., scan backwards from lexpos to the first newline to get a column position). 09/25/06: beazley Changed the name of the __copy__() method on the Lexer class to clone(). This is used to clone a Lexer object (e.g., if you're running different lexers at the same time). 09/21/06: beazley Limitations related to the use of the re module have been eliminated. Several users reported problems with regular expressions exceeding more than 100 named groups. To solve this, lex.py is now capable of automatically splitting its master regular regular expression into smaller expressions as needed. This should, in theory, make it possible to specify an arbitrarily large number of tokens. 09/21/06: beazley Improved error checking in lex.py. Rules that match the empty string are now rejected (otherwise they cause the lexer to enter an infinite loop). An extra check for rules containing '#' has also been added. Since lex compiles regular expressions in verbose mode, '#' is interpreted as a regex comment, it is critical to use '\#' instead. 09/18/06: beazley Added a @TOKEN decorator function to lex.py that can be used to define token rules where the documentation string might be computed in some way. digit = r'([0-9])' nondigit = r'([_A-Za-z])' identifier = r'(' + nondigit + r'(' + digit + r'|' + nondigit + r')*)' from ply.lex import TOKEN @TOKEN(identifier) def t_ID(t): # Do whatever The @TOKEN decorator merely sets the documentation string of the associated token function as needed for lex to work. Note: An alternative solution is the following: def t_ID(t): # Do whatever t_ID.__doc__ = identifier Note: Decorators require the use of Python 2.4 or later. If compatibility with old versions is needed, use the latter solution. The need for this feature was suggested by Cem Karan. 09/14/06: beazley Support for single-character literal tokens has been added to yacc. These literals must be enclosed in quotes. For example: def p_expr(p): "expr : expr '+' expr" ... def p_expr(p): 'expr : expr "-" expr' ... In addition to this, it is necessary to tell the lexer module about literal characters. This is done by defining the variable 'literals' as a list of characters. This should be defined in the module that invokes the lex.lex() function. For example: literals = ['+','-','*','/','(',')','='] or simply literals = '+=*/()=' It is important to note that literals can only be a single character. When the lexer fails to match a token using its normal regular expression rules, it will check the current character against the literal list. If found, it will be returned with a token type set to match the literal character. Otherwise, an illegal character will be signalled. 09/14/06: beazley Modified PLY to install itself as a proper Python package called 'ply'. This will make it a little more friendly to other modules. This changes the usage of PLY only slightly. Just do this to import the modules import ply.lex as lex import ply.yacc as yacc Alternatively, you can do this: from ply import * Which imports both the lex and yacc modules. Change suggested by Lee June. 09/13/06: beazley Changed the handling of negative indices when used in production rules. A negative production index now accesses already parsed symbols on the parsing stack. For example, def p_foo(p): "foo: A B C D" print p[1] # Value of 'A' symbol print p[2] # Value of 'B' symbol print p[-1] # Value of whatever symbol appears before A # on the parsing stack. p[0] = some_val # Sets the value of the 'foo' grammer symbol This behavior makes it easier to work with embedded actions within the parsing rules. For example, in C-yacc, it is possible to write code like this: bar: A { printf("seen an A = %d\n", $1); } B { do_stuff; } In this example, the printf() code executes immediately after A has been parsed. Within the embedded action code, $1 refers to the A symbol on the stack. To perform this equivalent action in PLY, you need to write a pair of rules like this: def p_bar(p): "bar : A seen_A B" do_stuff def p_seen_A(p): "seen_A :" print "seen an A =", p[-1] The second rule "seen_A" is merely a empty production which should be reduced as soon as A is parsed in the "bar" rule above. The use of the negative index p[-1] is used to access whatever symbol appeared before the seen_A symbol. This feature also makes it possible to support inherited attributes. For example: def p_decl(p): "decl : scope name" def p_scope(p): """scope : GLOBAL | LOCAL""" p[0] = p[1] def p_name(p): "name : ID" if p[-1] == "GLOBAL": # ... else if p[-1] == "LOCAL": #... In this case, the name rule is inheriting an attribute from the scope declaration that precedes it. *** POTENTIAL INCOMPATIBILITY *** If you are currently using negative indices within existing grammar rules, your code will break. This should be extremely rare if non-existent in most cases. The argument to various grammar rules is not usually not processed in the same way as a list of items. Version 2.0 ------------------------------ 09/07/06: beazley Major cleanup and refactoring of the LR table generation code. Both SLR and LALR(1) table generation is now performed by the same code base with only minor extensions for extra LALR(1) processing. 09/07/06: beazley Completely reimplemented the entire LALR(1) parsing engine to use the DeRemer and Pennello algorithm for calculating lookahead sets. This significantly improves the performance of generating LALR(1) tables and has the added feature of actually working correctly! If you experienced weird behavior with LALR(1) in prior releases, this should hopefully resolve all of those problems. Many thanks to Andrew Waters and Markus Schoepflin for submitting bug reports and helping me test out the revised LALR(1) support. Version 1.8 ------------------------------ 08/02/06: beazley Fixed a problem related to the handling of default actions in LALR(1) parsing. If you experienced subtle and/or bizarre behavior when trying to use the LALR(1) engine, this may correct those problems. Patch contributed by Russ Cox. Note: This patch has been superceded by revisions for LALR(1) parsing in Ply-2.0. 08/02/06: beazley Added support for slicing of productions in yacc. Patch contributed by Patrick Mezard. Version 1.7 ------------------------------ 03/02/06: beazley Fixed infinite recursion problem ReduceToTerminals() function that would sometimes come up in LALR(1) table generation. Reported by Markus Schoepflin. 03/01/06: beazley Added "reflags" argument to lex(). For example: lex.lex(reflags=re.UNICODE) This can be used to specify optional flags to the re.compile() function used inside the lexer. This may be necessary for special situations such as processing Unicode (e.g., if you want escapes like \w and \b to consult the Unicode character property database). The need for this suggested by Andreas Jung. 03/01/06: beazley Fixed a bug with an uninitialized variable on repeated instantiations of parser objects when the write_tables=0 argument was used. Reported by Michael Brown. 03/01/06: beazley Modified lex.py to accept Unicode strings both as the regular expressions for tokens and as input. Hopefully this is the only change needed for Unicode support. Patch contributed by Johan Dahl. 03/01/06: beazley Modified the class-based interface to work with new-style or old-style classes. Patch contributed by Michael Brown (although I tweaked it slightly so it would work with older versions of Python). Version 1.6 ------------------------------ 05/27/05: beazley Incorporated patch contributed by Christopher Stawarz to fix an extremely devious bug in LALR(1) parser generation. This patch should fix problems numerous people reported with LALR parsing. 05/27/05: beazley Fixed problem with lex.py copy constructor. Reported by Dave Aitel, Aaron Lav, and Thad Austin. 05/27/05: beazley Added outputdir option to yacc() to control output directory. Contributed by Christopher Stawarz. 05/27/05: beazley Added rununit.py test script to run tests using the Python unittest module. Contributed by Miki Tebeka. Version 1.5 ------------------------------ 05/26/04: beazley Major enhancement. LALR(1) parsing support is now working. This feature was implemented by Elias Ioup (ezioup@alumni.uchicago.edu) and optimized by David Beazley. To use LALR(1) parsing do the following: yacc.yacc(method="LALR") Computing LALR(1) parsing tables takes about twice as long as the default SLR method. However, LALR(1) allows you to handle more complex grammars. For example, the ANSI C grammar (in example/ansic) has 13 shift-reduce conflicts with SLR, but only has 1 shift-reduce conflict with LALR(1). 05/20/04: beazley Added a __len__ method to parser production lists. Can be used in parser rules like this: def p_somerule(p): """a : B C D | E F" if (len(p) == 3): # Must have been first rule elif (len(p) == 2): # Must be second rule Suggested by Joshua Gerth and others. Version 1.4 ------------------------------ 04/23/04: beazley Incorporated a variety of patches contributed by Eric Raymond. These include: 0. Cleans up some comments so they don't wrap on an 80-column display. 1. Directs compiler errors to stderr where they belong. 2. Implements and documents automatic line counting when \n is ignored. 3. Changes the way progress messages are dumped when debugging is on. The new format is both less verbose and conveys more information than the old, including shift and reduce actions. 04/23/04: beazley Added a Python setup.py file to simply installation. Contributed by Adam Kerrison. 04/23/04: beazley Added patches contributed by Adam Kerrison. - Some output is now only shown when debugging is enabled. This means that PLY will be completely silent when not in debugging mode. - An optional parameter "write_tables" can be passed to yacc() to control whether or not parsing tables are written. By default, it is true, but it can be turned off if you don't want the yacc table file. Note: disabling this will cause yacc() to regenerate the parsing table each time. 04/23/04: beazley Added patches contributed by David McNab. This patch addes two features: - The parser can be supplied as a class instead of a module. For an example of this, see the example/classcalc directory. - Debugging output can be directed to a filename of the user's choice. Use yacc(debugfile="somefile.out") Version 1.3 ------------------------------ 12/10/02: jmdyck Various minor adjustments to the code that Dave checked in today. Updated test/yacc_{inf,unused}.exp to reflect today's changes. 12/10/02: beazley Incorporated a variety of minor bug fixes to empty production handling and infinite recursion checking. Contributed by Michael Dyck. 12/10/02: beazley Removed bogus recover() method call in yacc.restart() Version 1.2 ------------------------------ 11/27/02: beazley Lexer and parser objects are now available as an attribute of tokens and slices respectively. For example: def t_NUMBER(t): r'\d+' print t.lexer def p_expr_plus(t): 'expr: expr PLUS expr' print t.lexer print t.parser This can be used for state management (if needed). 10/31/02: beazley Modified yacc.py to work with Python optimize mode. To make this work, you need to use yacc.yacc(optimize=1) Furthermore, you need to first run Python in normal mode to generate the necessary parsetab.py files. After that, you can use python -O or python -OO. Note: optimized mode turns off a lot of error checking. Only use when you are sure that your grammar is working. Make sure parsetab.py is up to date! 10/30/02: beazley Added cloning of Lexer objects. For example: import copy l = lex.lex() lc = copy.copy(l) l.input("Some text") lc.input("Some other text") ... This might be useful if the same "lexer" is meant to be used in different contexts---or if multiple lexers are running concurrently. 10/30/02: beazley Fixed subtle bug with first set computation and empty productions. Patch submitted by Michael Dyck. 10/30/02: beazley Fixed error messages to use "filename:line: message" instead of "filename:line. message". This makes error reporting more friendly to emacs. Patch submitted by François Pinard. 10/30/02: beazley Improvements to parser.out file. Terminals and nonterminals are sorted instead of being printed in random order. Patch submitted by François Pinard. 10/30/02: beazley Improvements to parser.out file output. Rules are now printed in a way that's easier to understand. Contributed by Russ Cox. 10/30/02: beazley Added 'nonassoc' associativity support. This can be used to disable the chaining of operators like a < b < c. To use, simply specify 'nonassoc' in the precedence table precedence = ( ('nonassoc', 'LESSTHAN', 'GREATERTHAN'), # Nonassociative operators ('left', 'PLUS', 'MINUS'), ('left', 'TIMES', 'DIVIDE'), ('right', 'UMINUS'), # Unary minus operator ) Patch contributed by Russ Cox. 10/30/02: beazley Modified the lexer to provide optional support for Python -O and -OO modes. To make this work, Python *first* needs to be run in unoptimized mode. This reads the lexing information and creates a file "lextab.py". Then, run lex like this: # module foo.py ... ... lex.lex(optimize=1) Once the lextab file has been created, subsequent calls to lex.lex() will read data from the lextab file instead of using introspection. In optimized mode (-O, -OO) everything should work normally despite the loss of doc strings. To change the name of the file 'lextab.py' use the following: lex.lex(lextab="footab") (this creates a file footab.py) Version 1.1 October 25, 2001 ------------------------------ 10/25/01: beazley Modified the table generator to produce much more compact data. This should greatly reduce the size of the parsetab.py[c] file. Caveat: the tables still need to be constructed so a little more work is done in parsetab on import. 10/25/01: beazley There may be a possible bug in the cycle detector that reports errors about infinite recursion. I'm having a little trouble tracking it down, but if you get this problem, you can disable the cycle detector as follows: yacc.yacc(check_recursion = 0) 10/25/01: beazley Fixed a bug in lex.py that sometimes caused illegal characters to be reported incorrectly. Reported by Sverre Jørgensen. 7/8/01 : beazley Added a reference to the underlying lexer object when tokens are handled by functions. The lexer is available as the 'lexer' attribute. This was added to provide better lexing support for languages such as Fortran where certain types of tokens can't be conveniently expressed as regular expressions (and where the tokenizing function may want to perform a little backtracking). Suggested by Pearu Peterson. 6/20/01 : beazley Modified yacc() function so that an optional starting symbol can be specified. For example: yacc.yacc(start="statement") Normally yacc always treats the first production rule as the starting symbol. However, if you are debugging your grammar it may be useful to specify an alternative starting symbol. Idea suggested by Rich Salz. Version 1.0 June 18, 2001 -------------------------- Initial public offering ./CBFlib-0.9.2.2/ply-3.2/ply.egg-info/0000755000076500007650000000000011603703070015201 5ustar yayayaya./CBFlib-0.9.2.2/ply-3.2/ply.egg-info/PKG-INFO0000644000076500007650000000134711603702121016277 0ustar yayayayaMetadata-Version: 1.0 Name: ply Version: 3.2 Summary: Python Lex & Yacc Home-page: http://www.dabeaz.com/ply/ Author: David Beazley Author-email: dave@dabeaz.com License: BSD Description: PLY is yet another implementation of lex and yacc for Python. Some notable features include the fact that its implemented entirely in Python and it uses LALR(1) parsing which is efficient and well suited for larger grammars. PLY provides most of the standard lex/yacc features including support for empty productions, precedence rules, error recovery, and support for ambiguous grammars. PLY is extremely easy to use and provides very extensive error checking. Platform: UNKNOWN ./CBFlib-0.9.2.2/ply-3.2/ply.egg-info/dependency_links.txt0000644000076500007650000000000111603702121021243 0ustar yayayaya ./CBFlib-0.9.2.2/ply-3.2/ply.egg-info/SOURCES.txt0000644000076500007650000000033511603702121017062 0ustar yayayayaREADME setup.py ply/__init__.py ply/cpp.py ply/ctokens.py ply/lex.py ply/yacc.py ply.egg-info/PKG-INFO ply.egg-info/SOURCES.txt ply.egg-info/dependency_links.txt ply.egg-info/top_level.txt test/testlex.py test/testyacc.py./CBFlib-0.9.2.2/ply-3.2/ply.egg-info/top_level.txt0000644000076500007650000000000411603702121017721 0ustar yayayayaply ./CBFlib-0.9.2.2/.symlinks0000755000076500007650000001222411603751052013460 0ustar yayayaya#!/bin/sh ###################################################################### # # # .symlinks for CBFlib directory # # # # originally a csh script by H. J. Bernstein # # converted to sh by J. Wright, 12 Jun 2007 # # # # Version 0.8.0 20 Jul 2008 # # # # Paul Ellis and # # Herbert J. Bernstein (yaya@bernstein-plus-sons.com) # # # # (C) Copyright 2006 - 2008 Herbert J. Bernstein # # # ###################################################################### ###################################################################### # # # YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL # # # # ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS # # OF THE LGPL # # # ###################################################################### ########################### GPL NOTICES ############################## # # # This program is free software; you can redistribute it and/or # # modify it under the terms of the GNU General Public License as # # published by the Free Software Foundation; either version 2 of # # (the License, or (at your option) any later version. # # # # This program is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # # GNU General Public License for more details. # # # # You should have received a copy of the GNU General Public License # # along with this program; if not, write to the Free Software # # Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA # # 02111-1307 USA # # # ###################################################################### ######################### LGPL NOTICES ############################### # # # This library is free software; you can redistribute it and/or # # modify it under the terms of the GNU Lesser General Public # # License as published by the Free Software Foundation; either # # version 2.1 of the License, or (at your option) any later version. # # # # This library is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # # Lesser General Public License for more details. # # # # You should have received a copy of the GNU Lesser General Public # # License along with this library; if not, write to the Free # # Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, # # MA 02110-1301 USA # # # ###################################################################### # Usage ./.symlinks [--use_cp] if [ ${1:-NOARG} = "--use_cp" ] ; then LN="cp -p" else LN="ln -s" fi if [ ! -e index.html ] ; then $LN README.html index.html fi if [ ! -e gpl.txt ] ; then $LN doc/gpl.txt gpl.txt fi if [ ! -e lgpl.txt ] ; then $LN doc/lgpl.txt lgpl.txt fi if [ ! -e CBFlib.tar.gz ] ; then $LN ../CBFlib-0.9.2.2.tar.gz CBFlib.tar.gz fi if [ ! -e template_adscquantum315_3072x3072.cbf ] ; then $LN examples/template_adscquantum315_3072x3072.cbf template_adscquantum315_3072x3072.cbf fi if [ ! -e template_adscquantum4_2304x2304.cbf ] ; then $LN examples/template_adscquantum4_2304x2304.cbf template_adscquantum4_2304x2304.cbf fi if [ ! -e template_mar345_2300x2300.cbf ] ; then $LN examples/template_mar345_2300x2300.cbf template_mar345_2300x2300.cbf fi if [ ! -e template_pilatus6m_2463x2527.cbf ] ; then $LN examples/template_pilatus6m_2463x2527.cbf template_pilatus6m_2463x2527.cbf fi for file in * do if [ -d "$file" ] ; then if [ -e "$file/.symlinks" ] ; then (cd "$file"; sh -c "./.symlinks $1") fi fi done ./CBFlib-0.9.2.2/Makefile_OSX_gcc420000644000076500007650000020025511603702122014753 0ustar yayayaya ###################################################################### # Makefile - command file for make to create CBFlib # # # # Version 0.9.2 12 Feb 2011 # # # # Paul Ellis and # # Herbert J. Bernstein (yaya@bernstein-plus-sons.com) # # # # (C) Copyright 2006 - 2011 Herbert J. Bernstein # # # ###################################################################### ###################################################################### # # # YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL # # # # ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS # # OF THE LGPL # # # ###################################################################### ########################### GPL NOTICES ############################## # # # This program is free software; you can redistribute it and/or # # modify it under the terms of the GNU General Public License as # # published by the Free Software Foundation; either version 2 of # # (the License, or (at your option) any later version. # # # # This program is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # # GNU General Public License for more details. # # # # You should have received a copy of the GNU General Public License # # along with this program; if not, write to the Free Software # # Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA # # 02111-1307 USA # # # ###################################################################### ######################### LGPL NOTICES ############################### # # # This library is free software; you can redistribute it and/or # # modify it under the terms of the GNU Lesser General Public # # License as published by the Free Software Foundation; either # # version 2.1 of the License, or (at your option) any later version. # # # # This library is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # # Lesser General Public License for more details. # # # # You should have received a copy of the GNU Lesser General Public # # License along with this library; if not, write to the Free # # Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, # # MA 02110-1301 USA # # # ###################################################################### ###################################################################### # # # Stanford University Notices # # for the CBFlib software package that incorporates SLAC software # # on which copyright is disclaimed # # # # This software # # ------------- # # The term "this software", as used in these Notices, refers to # # those portions of the software package CBFlib that were created by # # employees of the Stanford Linear Accelerator Center, Stanford # # University. # # # # Stanford disclaimer of copyright # # -------------------------------- # # Stanford University, owner of the copyright, hereby disclaims its # # copyright and all other rights in this software. Hence, anyone # # may freely use it for any purpose without restriction. # # # # Acknowledgement of sponsorship # # ------------------------------ # # This software was produced by the Stanford Linear Accelerator # # Center, Stanford University, under Contract DE-AC03-76SFO0515 with # # the Department of Energy. # # # # Government disclaimer of liability # # ---------------------------------- # # Neither the United States nor the United States Department of # # Energy, nor any of their employees, makes any warranty, express or # # implied, or assumes any legal liability or responsibility for the # # accuracy, completeness, or usefulness of any data, apparatus, # # product, or process disclosed, or represents that its use would # # not infringe privately owned rights. # # # # Stanford disclaimer of liability # # -------------------------------- # # Stanford University makes no representations or warranties, # # express or implied, nor assumes any liability for the use of this # # software. # # # # Maintenance of notices # # ---------------------- # # In the interest of clarity regarding the origin and status of this # # software, this and all the preceding Stanford University notices # # are to remain affixed to any copy or derivative of this software # # made or distributed by the recipient and are to be affixed to any # # copy of software made or distributed by the recipient that # # contains a copy or derivative of this software. # # # # Based on SLAC Software Notices, Set 4 # # OTT.002a, 2004 FEB 03 # ###################################################################### ###################################################################### # NOTICE # # Creative endeavors depend on the lively exchange of ideas. There # # are laws and customs which establish rights and responsibilities # # for authors and the users of what authors create. This notice # # is not intended to prevent you from using the software and # # documents in this package, but to ensure that there are no # # misunderstandings about terms and conditions of such use. # # # # Please read the following notice carefully. If you do not # # understand any portion of this notice, please seek appropriate # # professional legal advice before making use of the software and # # documents included in this software package. In addition to # # whatever other steps you may be obliged to take to respect the # # intellectual property rights of the various parties involved, if # # you do make use of the software and documents in this package, # # please give credit where credit is due by citing this package, # # its authors and the URL or other source from which you obtained # # it, or equivalent primary references in the literature with the # # same authors. # # # # Some of the software and documents included within this software # # package are the intellectual property of various parties, and # # placement in this package does not in any way imply that any # # such rights have in any way been waived or diminished. # # # # With respect to any software or documents for which a copyright # # exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. # # # # Even though the authors of the various documents and software # # found here have made a good faith effort to ensure that the # # documents are correct and that the software performs according # # to its documentation, and we would greatly appreciate hearing of # # any problems you may encounter, the programs and documents any # # files created by the programs are provided **AS IS** without any * # warranty as to correctness, merchantability or fitness for any # # particular or general use. # # # # THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF # # PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE # # PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS # # OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE # # PROGRAMS OR DOCUMENTS. # ###################################################################### ###################################################################### # # # The IUCr Policy # # for the Protection and the Promotion of the STAR File and # # CIF Standards for Exchanging and Archiving Electronic Data # # # # Overview # # # # The Crystallographic Information File (CIF)[1] is a standard for # # information interchange promulgated by the International Union of # # Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the # # recommended method for submitting publications to Acta # # Crystallographica Section C and reports of crystal structure # # determinations to other sections of Acta Crystallographica # # and many other journals. The syntax of a CIF is a subset of the # # more general STAR File[2] format. The CIF and STAR File approaches # # are used increasingly in the structural sciences for data exchange # # and archiving, and are having a significant influence on these # # activities in other fields. # # # # Statement of intent # # # # The IUCr's interest in the STAR File is as a general data # # interchange standard for science, and its interest in the CIF, # # a conformant derivative of the STAR File, is as a concise data # # exchange and archival standard for crystallography and structural # # science. # # # # Protection of the standards # # # # To protect the STAR File and the CIF as standards for # # interchanging and archiving electronic data, the IUCr, on behalf # # of the scientific community, # # # # # holds the copyrights on the standards themselves, * # # # # owns the associated trademarks and service marks, and * # # # # holds a patent on the STAR File. * # # # These intellectual property rights relate solely to the # # interchange formats, not to the data contained therein, nor to # # the software used in the generation, access or manipulation of # # the data. # # # # Promotion of the standards # # # # The sole requirement that the IUCr, in its protective role, # # imposes on software purporting to process STAR File or CIF data # # is that the following conditions be met prior to sale or # # distribution. # # # # # Software claiming to read files written to either the STAR * # File or the CIF standard must be able to extract the pertinent # # data from a file conformant to the STAR File syntax, or the CIF # # syntax, respectively. # # # # # Software claiming to write files in either the STAR File, or * # the CIF, standard must produce files that are conformant to the # # STAR File syntax, or the CIF syntax, respectively. # # # # # Software claiming to read definitions from a specific data * # dictionary approved by the IUCr must be able to extract any # # pertinent definition which is conformant to the dictionary # # definition language (DDL)[3] associated with that dictionary. # # # # The IUCr, through its Committee on CIF Standards, will assist # # any developer to verify that software meets these conformance # # conditions. # # # # Glossary of terms # # # # [1] CIF: is a data file conformant to the file syntax defined # # at http://www.iucr.org/iucr-top/cif/spec/index.html # # # # [2] STAR File: is a data file conformant to the file syntax # # defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html # # # # [3] DDL: is a language used in a data dictionary to define data # # items in terms of "attributes". Dictionaries currently approved # # by the IUCr, and the DDL versions used to construct these # # dictionaries, are listed at # # http://www.iucr.org/iucr-top/cif/spec/ddl/index.html # # # # Last modified: 30 September 2000 # # # # IUCr Policy Copyright (C) 2000 International Union of # # Crystallography # ###################################################################### # Version string VERSION = 0.9.2 # # Comment out the next line if scratch test files sould be retain # CLEANTESTS = yes # # Definition to get a version of tifflib to support tiff2cbf # TIFF = tiff-3.9.4-rev-6Feb11 TIFFPREFIX = $(PWD) # # Definitions to get a stable version of regex # REGEX = regex-20090805 REGEXDIR = /usr/lib REGEXDEP = # Program to use to retrieve a URL DOWNLOAD = wget # Flag to control symlinks versus copying SLFLAGS = --use_ln # # Program to use to pack shars # SHAR = /usr/bin/shar #SHAR = /usr/local/bin/gshar # # Program to use to create archives # AR = /usr/bin/ar # # Program to use to add an index to an archive # RANLIB = /usr/bin/ranlib # # Program to use to decompress a data file # DECOMPRESS = /usr/bin/bunzip2 # # Program to use to compress a data file # COMPRESS = /usr/bin/bzip2 # # Program to use to generate a signature # SIGNATURE = /usr/bin/openssl dgst -md5 # # Extension for compressed data file (with period) # CEXT = .bz2 # # Extension for signatures of files # SEXT = .md5 # call to time a command #TIME = #TIME = time # # Program to display differences between files # DIFF = diff -u -b # # Program to generate wrapper classes for Python # PYSWIG = swig -python # # Program to generate wrapper classes for Java # JSWIG = swig -java # # Program to generate LaTex and HTML program documentation # NUWEB = nuweb # # Compiler for Java # JAVAC = javac # # Java archiver for compiled classes # JAR = jar # # Java SDK root directory # ifeq ($(JDKDIR),) JDKDIR = /usr/lib/java endif ifneq ($(CBF_DONT_USE_LONG_LONG),) NOLLFLAG = -DCBF_DONT_USE_LONG_LONG else NOLLFLAG = endif # # PYCBF definitions # PYCBFEXT = so PYCBFBOPT = SETUP_PY = setup.py # # Set the compiler and flags # ######################################################### # # Appropriate compiler definitions for MAC OS X # with gcc 4.2 # Also change defintion of DOWNLOAD # ######################################################### CC = gcc C++ = g++ CFLAGS = -g -O2 -Wall -ansi -pedantic F90C = gfortran F90FLAGS = -g -fno-range-check F90LDFLAGS = -bind_at_load SOCFLAGS = -fPIC SOLDFLAGS = -shared -Wl,-rpath,$(INSTALLDIR)/lib JAVAINCLUDES = -I$(JDKDIR)/include -I$(JDKDIR)/include/linux LDPREFIX = LD_LIBRARY_PATH=$(SOLIB) EXTRALIBS = -lm M4FLAGS = -Dfcb_bytes_in_rec=131072 TIME = time DOWNLOAD = /sw/bin/wget ifneq ($(NOFORTRAN),) F90C = endif # # Directories # ROOT = . LIB = $(ROOT)/lib SOLIB = $(ROOT)/solib JCBF = $(ROOT)/jcbf JAVADIR = $(ROOT)/java BIN = $(ROOT)/bin SRC = $(ROOT)/src INCLUDE = $(ROOT)/include M4 = $(ROOT)/m4 PYCBF = $(ROOT)/pycbf EXAMPLES = $(ROOT)/examples DECTRIS_EXAMPLES = $(EXAMPLES)/dectris_cbf_template_test DOC = $(ROOT)/doc GRAPHICS = $(ROOT)/html_graphics DATADIRI = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Input DATADIRO = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Output DATADIRS = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only INSTALLDIR = $(HOME) # # URLs from which to retrieve the data directories # DATAURLBASE = http://downloads.sf.net/cbflib/ DATAURLI = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Input.tar.gz DATAURLO = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Output.tar.gz DATAURLS = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz # # URLs from which to retrieve needed external package snapshots # REGEXURL = http://downloads.sf.net/cbflib/$(REGEX).tar.gz TIFFURL = http://downloads.sf.net/cbflib/$(TIFF).tar.gz # # Include directories # INCLUDES = -I$(INCLUDE) -I$(SRC) ###################################################################### # You should not need to make modifications below this line # ###################################################################### # # Suffixes of files to be used or built # .SUFFIXES: .c .o .f90 .m4 .m4.f90: m4 -P $(M4FLAGS) $< > $@ ifneq ($(F90C),) .f90.o: $(F90C) $(F90FLAGS) -c $< -o $@ endif # # Common dependencies # COMMONDEP = Makefile # # Source files # SOURCE = $(SRC)/cbf.c \ $(SRC)/cbf_alloc.c \ $(SRC)/cbf_ascii.c \ $(SRC)/cbf_binary.c \ $(SRC)/cbf_byte_offset.c \ $(SRC)/cbf_canonical.c \ $(SRC)/cbf_codes.c \ $(SRC)/cbf_compress.c \ $(SRC)/cbf_context.c \ $(SRC)/cbf_copy.c \ $(SRC)/cbf_file.c \ $(SRC)/cbf_getopt.c \ $(SRC)/cbf_lex.c \ $(SRC)/cbf_packed.c \ $(SRC)/cbf_predictor.c \ $(SRC)/cbf_read_binary.c \ $(SRC)/cbf_read_mime.c \ $(SRC)/cbf_simple.c \ $(SRC)/cbf_string.c \ $(SRC)/cbf_stx.c \ $(SRC)/cbf_tree.c \ $(SRC)/cbf_uncompressed.c \ $(SRC)/cbf_write.c \ $(SRC)/cbf_write_binary.c \ $(SRC)/cbf_ws.c \ $(SRC)/md5c.c F90SOURCE = $(SRC)/fcb_atol_wcnt.f90 \ $(SRC)/fcb_ci_strncmparr.f90 \ $(SRC)/fcb_exit_binary.f90 \ $(SRC)/fcb_nblen_array.f90 \ $(SRC)/fcb_next_binary.f90 \ $(SRC)/fcb_open_cifin.f90 \ $(SRC)/fcb_packed.f90 \ $(SRC)/fcb_read_bits.f90 \ $(SRC)/fcb_read_byte.f90 \ $(SRC)/fcb_read_image.f90 \ $(SRC)/fcb_read_line.f90 \ $(SRC)/fcb_read_xds_i2.f90 \ $(SRC)/fcb_skip_whitespace.f90 \ $(EXAMPLES)/test_fcb_read_image.f90 \ $(EXAMPLES)/test_xds_binary.f90 # # Header files # HEADERS = $(INCLUDE)/cbf.h \ $(INCLUDE)/cbf_alloc.h \ $(INCLUDE)/cbf_ascii.h \ $(INCLUDE)/cbf_binary.h \ $(INCLUDE)/cbf_byte_offset.h \ $(INCLUDE)/cbf_canonical.h \ $(INCLUDE)/cbf_codes.h \ $(INCLUDE)/cbf_compress.h \ $(INCLUDE)/cbf_context.h \ $(INCLUDE)/cbf_copy.h \ $(INCLUDE)/cbf_file.h \ $(INCLUDE)/cbf_getopt.h \ $(INCLUDE)/cbf_lex.h \ $(INCLUDE)/cbf_packed.h \ $(INCLUDE)/cbf_predictor.h \ $(INCLUDE)/cbf_read_binary.h \ $(INCLUDE)/cbf_read_mime.h \ $(INCLUDE)/cbf_simple.h \ $(INCLUDE)/cbf_string.h \ $(INCLUDE)/cbf_stx.h \ $(INCLUDE)/cbf_tree.h \ $(INCLUDE)/cbf_uncompressed.h \ $(INCLUDE)/cbf_write.h \ $(INCLUDE)/cbf_write_binary.h \ $(INCLUDE)/cbf_ws.h \ $(INCLUDE)/global.h \ $(INCLUDE)/cbff.h \ $(INCLUDE)/md5.h # # m4 macro files # M4FILES = $(M4)/fcblib_defines.m4 \ $(M4)/fcb_exit_binary.m4 \ $(M4)/fcb_next_binary.m4 \ $(M4)/fcb_open_cifin.m4 \ $(M4)/fcb_packed.m4 \ $(M4)/fcb_read_bits.m4 \ $(M4)/fcb_read_image.m4 \ $(M4)/fcb_read_xds_i2.m4 \ $(M4)/test_fcb_read_image.m4 \ $(M4)/test_xds_binary.m4 # # Documentation files # DOCUMENTS = $(DOC)/CBFlib.html \ $(DOC)/CBFlib.txt \ $(DOC)/CBFlib_NOTICES.html \ $(DOC)/CBFlib_NOTICES.txt \ $(DOC)/ChangeLog \ $(DOC)/ChangeLog.html \ $(DOC)/MANIFEST \ $(DOC)/gpl.txt $(DOC)/lgpl.txt # # HTML Graphics files # JPEGS = $(GRAPHICS)/CBFbackground.jpg \ $(GRAPHICS)/CBFbig.jpg \ $(GRAPHICS)/CBFbutton.jpg \ $(GRAPHICS)/cbflibbackground.jpg \ $(GRAPHICS)/cbflibbig.jpg \ $(GRAPHICS)/cbflibbutton.jpg \ $(GRAPHICS)/cifhome.jpg \ $(GRAPHICS)/iucrhome.jpg \ $(GRAPHICS)/noticeButton.jpg # # Default: instructions # default: @echo ' ' @echo '***************************************************************' @echo ' ' @echo ' PLEASE READ README and doc/CBFlib_NOTICES.txt' @echo ' ' @echo ' Before making the CBF library and example programs, check' @echo ' that the C compiler name and flags are correct:' @echo ' ' @echo ' The current values are:' @echo ' ' @echo ' $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG)' @echo ' ' @echo ' Before installing the CBF library and example programs, check' @echo ' that the install directory is correct:' @echo ' ' @echo ' The current value :' @echo ' ' @echo ' $(INSTALLDIR) ' @echo ' ' @echo ' To compile the CBF library and example programs type:' @echo ' ' @echo ' make clean' @echo ' make all' @echo ' ' @echo ' To compile the CBF library as a shared object library, type:' @echo ' ' @echo ' make shared' @echo ' ' @echo ' To compile the Java wrapper classes for CBF library, type:' @echo ' ' @echo ' make javawrapper' @echo ' ' @echo ' To run a set of tests type:' @echo ' ' @echo ' make tests' @echo ' ' @echo ' To run some java tests type:' @echo ' ' @echo ' make javatests' @echo ' ' @echo ' The tests assume that several data files are in the directories' @echo ' $(DATADIRI) and $(DATADIRO)' @echo ' ' @echo ' Alternatively tests can be run comparing MD5 signatures only by' @echo ' ' @echo ' make tests_sigs_only' @echo ' ' @echo ' These signature only tests save space and download time by' @echo ' assuming that input data files and the output signatures' @echo ' are in the directories' @echo ' $(DATADIRI) and $(DATADIRS)' @echo ' ' @echo ' These directory can be obtained from' @echo ' ' @echo ' $(DATAURLI) ' @echo ' $(DATAURLO) ' @echo ' $(DATAURLS) ' @echo ' ' @echo ' To clean up the directories type:' @echo ' ' @echo ' make clean' @echo ' ' @echo ' To install the library and binaries type:' @echo ' ' @echo ' make install' @echo ' ' @echo '***************************************************************' @echo ' ' # # Compile the library and examples # all:: $(BIN) $(SOURCE) $(F90SOURCE) $(HEADERS) \ symlinksdone $(REGEXDEP) \ $(LIB)/libcbf.a \ $(LIB)/libfcb.a \ $(LIB)/libimg.a \ $(BIN)/adscimg2cbf \ $(BIN)/cbf2adscimg \ $(BIN)/convert_image \ $(BIN)/convert_minicbf \ $(BIN)/sequence_match \ $(BIN)/arvai_test \ $(BIN)/makecbf \ $(BIN)/img2cif \ $(BIN)/adscimg2cbf \ $(BIN)/cif2cbf \ $(BIN)/testcell \ $(BIN)/cif2c \ $(BIN)/testreals \ $(BIN)/testflat \ $(BIN)/testflatpacked ifneq ($(F90C),) all:: $(BIN)/test_xds_binary \ $(BIN)/test_fcb_read_image endif shared: $(SOLIB)/libcbf.so $(SOLIB)/libfcb.so $(SOLIB)/libimg.so javawrapper: shared $(JCBF) $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf_wrap.so ifneq ($(CBFLIB_USE_PYCIFRW),) PYCIFRWDEF = -Dcbf_use_pycifrw=yes else PYCIFRWDEF = endif Makefiles: Makefile \ Makefile_LINUX \ Makefile_LINUX_64 \ Makefile_LINUX_gcc42 \ Makefile_LINUX_DMALLOC \ Makefile_LINUX_gcc42_DMALLOC \ Makefile_OSX \ Makefile_OSX_gcc42 \ Makefile_OSX_gcc42_DMALLOC \ Makefile_AIX \ Makefile_MINGW \ Makefile_IRIX_gcc Makefile_LINUX: $(M4)/Makefile.m4 -cp Makefile_LINUX Makefile_LINUX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX $(M4)/Makefile.m4 > Makefile_LINUX Makefile_LINUX_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_LINUX Makefile_LINUX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_DMALLOC $(M4)/Makefile.m4 > Makefile_LINUX_DMALLOC Makefile_LINUX_64: $(M4)/Makefile.m4 -cp Makefile_LINUX_64 Makefile_LINUX_64_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_64 $(M4)/Makefile.m4 > Makefile_LINUX_64 Makefile_LINUX_gcc42: $(M4)/Makefile.m4 -cp Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_gcc42 $(M4)/Makefile.m4 > Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_gcc42_DMALLOC $(M4)/Makefile.m4 > Makefile_LINUX_gcc42_DMALLOC Makefile_OSX: $(M4)/Makefile.m4 -cp Makefile_OSX Makefile_OSX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX $(M4)/Makefile.m4 > Makefile_OSX Makefile_OSX_gcc42: $(M4)/Makefile.m4 -cp Makefile_OSX_gcc42 Makefile_OSX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX_gcc42 $(M4)/Makefile.m4 > Makefile_OSX_gcc42 Makefile_OSX_gcc42_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_OSX_gcc42 Makefile_OSX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX_gcc42_DMALLOC $(M4)/Makefile.m4 > Makefile_OSX_gcc42_DMALLOC Makefile_AIX: $(M4)/Makefile.m4 -cp Makefile_AIX Makefile_AIX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=AIX $(M4)/Makefile.m4 > Makefile_AIX Makefile_MINGW: $(M4)/Makefile.m4 -cp Makefile_MINGW Makefile_MINGW_old m4 -P $(PYCIFRWDEF) -Dcbf_system=MINGW $(M4)/Makefile.m4 > Makefile_MINGW Makefile_IRIX_gcc: $(M4)/Makefile.m4 -cp Makefile_IRIX_gcc Makefile_IRIX_gcc_old m4 -P $(PYCIFREDEF) -Dcbf_system=IRIX_gcc $(M4)/Makefile.m4 > Makefile_IRIX_gcc Makefile: $(M4)/Makefile.m4 -cp Makefile Makefile_old m4 -P $(PYCIFRWDEF) -Dcbf_system=default $(M4)/Makefile.m4 > Makefile symlinksdone: chmod a+x .symlinks chmod a+x .undosymlinks chmod a+x doc/.symlinks chmod a+x doc/.undosymlinks chmod a+x libtool/.symlinks chmod a+x libtool/.undosymlinks ./.symlinks $(SLFLAGS) touch symlinksdone install: all $(INSTALLDIR) $(INSTALLDIR)/lib $(INSTALLDIR)/bin \ $(INSTALLDIR)/include $(INSTALLDIR)/include/cbflib \ $(PYSOURCE) -chmod -R 755 $(INSTALLDIR)/include/cbflib -chmod 755 $(INSTALLDIR)/lib/libcbf.a -cp $(INSTALLDIR)/lib/libcbf.a $(INSTALLDIR)/lib/libcbf_old.a cp $(LIB)/libcbf.a $(INSTALLDIR)/lib/libcbf.a -cp $(INSTALLDIR)/lib/libimg.a $(INSTALLDIR)/lib/libimg_old.a cp $(LIB)/libimg.a $(INSTALLDIR)/lib/libimg.a -cp $(INSTALLDIR)/bin/adscimg2cbf $(INSTALLDIR)/bin/adscimg2cbf_old cp $(BIN)/adscimg2cbf $(INSTALLDIR)/bin/adscimg2cbf -cp $(INSTALLDIR)/bin/cbf2adscimg $(INSTALLDIR)/bin/cbf2adscimg_old cp $(BIN)/cbf2adscimg $(INSTALLDIR)/bin/cbf2adscimg -cp $(INSTALLDIR)/bin/convert_image $(INSTALLDIR)/bin/convert_image_old cp $(BIN)/convert_image $(INSTALLDIR)/bin/convert_image -cp $(INSTALLDIR)/bin/convert_minicbf $(INSTALLDIR)/bin/convert_minicbf_old cp $(BIN)/convert_minicbf $(INSTALLDIR)/bin/convert_minicbf -cp $(INSTALLDIR)/bin/makecbf $(INSTALLDIR)/bin/makecbf_old cp $(BIN)/makecbf $(INSTALLDIR)/bin/makecbf -cp $(INSTALLDIR)/bin/img2cif $(INSTALLDIR)/bin/img2cif_old cp $(BIN)/img2cif $(INSTALLDIR)/bin/img2cif -cp $(INSTALLDIR)/bin/cif2cbf $(INSTALLDIR)/bin/cif2cbf_old cp $(BIN)/cif2cbf $(INSTALLDIR)/bin/cif2cbf -cp $(INSTALLDIR)/bin/sequence_match $(INSTALLDIR)/bin/sequence_match_old cp $(BIN)/sequence_match $(INSTALLDIR)/bin/sequence_match -cp $(INSTALLDIR)/bin/arvai_test $(INSTALLDIR)/bin/arvai_test_old cp $(BIN)/arvai_test $(INSTALLDIR)/bin/arvai_test -cp $(INSTALLDIR)/bin/cif2c $(INSTALLDIR)/bin/cif2c_old cp $(BIN)/cif2c $(INSTALLDIR)/bin/cif2c -cp $(INSTALLDIR)/bin/testreals $(INSTALLDIR)/bin/testreals_old cp $(BIN)/testreals $(INSTALLDIR)/bin/testreals -cp $(INSTALLDIR)/bin/testflat $(INSTALLDIR)/bin/testflat_old cp $(BIN)/testflat $(INSTALLDIR)/bin/testflat -cp $(INSTALLDIR)/bin/testflatpacked $(INSTALLDIR)/bin/testflatpacked_old cp $(BIN)/testflatpacked $(INSTALLDIR)/bin/testflatpacked chmod -R 755 $(INSTALLDIR)/include/cbflib -rm -rf $(INSTALLDIR)/include/cbflib_old -cp -r $(INSTALLDIR)/include/cbflib $(INSTALLDIR)/include/cbflib_old -rm -rf $(INSTALLDIR)/include/cbflib cp -r $(INCLUDE) $(INSTALLDIR)/include/cbflib chmod 644 $(INSTALLDIR)/lib/libcbf.a chmod 755 $(INSTALLDIR)/bin/convert_image chmod 755 $(INSTALLDIR)/bin/convert_minicbf chmod 755 $(INSTALLDIR)/bin/makecbf chmod 755 $(INSTALLDIR)/bin/img2cif chmod 755 $(INSTALLDIR)/bin/cif2cbf chmod 755 $(INSTALLDIR)/bin/sequence_match chmod 755 $(INSTALLDIR)/bin/arvai_test chmod 755 $(INSTALLDIR)/bin/cif2c chmod 755 $(INSTALLDIR)/bin/testreals chmod 755 $(INSTALLDIR)/bin/testflat chmod 755 $(INSTALLDIR)/bin/testflatpacked chmod 644 $(INSTALLDIR)/include/cbflib/*.h # # REGEX # ifneq ($(REGEXDEP),) $(REGEXDEP): $(REGEX) (cd $(REGEX); ./configure; make install) endif $(REGEX): $(DOWNLOAD) $(REGEXURL) tar -xvf $(REGEX).tar.gz -rm $(REGEX).tar.gz # # TIFF # $(TIFF): $(DOWNLOAD) $(TIFFURL) tar -xvf $(TIFF).tar.gz -rm $(TIFF).tar.gz (cd $(TIFF); ./configure --prefix=$(TIFFPREFIX); make install) # # Directories # $(INSTALLDIR): mkdir -p $(INSTALLDIR) $(INSTALLDIR)/lib: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/lib $(INSTALLDIR)/bin: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/bin $(INSTALLDIR)/include: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/include $(INSTALLDIR)/include/cbflib: $(INSTALLDIR)/include mkdir -p $(INSTALLDIR)/include/cbflib $(LIB): mkdir $@ $(BIN): mkdir $@ $(SOLIB): mkdir $@ $(JCBF): mkdir $@ # # Parser # $(SRC)/cbf_stx.c: $(SRC)/cbf.stx.y bison $(SRC)/cbf.stx.y -o $(SRC)/cbf.stx.tab.c -d mv $(SRC)/cbf.stx.tab.c $(SRC)/cbf_stx.c mv $(SRC)/cbf.stx.tab.h $(INCLUDE)/cbf_stx.h # # CBF library # $(LIB)/libcbf.a: $(SOURCE) $(HEADERS) $(COMMONDEP) $(LIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG) $(INCLUDES) $(WARNINGS) -c $(SOURCE) $(AR) cr $@ *.o mv *.o $(LIB) ifneq ($(RANLIB),) $(RANLIB) $@ endif $(SOLIB)/libcbf.so: $(SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(SOURCE) $(CC) -o $@ *.o $(SOLDFLAGS) $(EXTRALIBS) rm *.o # # IMG library # $(LIB)/libimg.a: $(EXAMPLES)/img.c $(HEADERS) $(COMMONDEP) $(LIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) -c $(EXAMPLES)/img.c $(AR) cr $@ img.o ifneq ($(RANLIB),) $(RANLIB) $@ endif rm img.o $(SOLIB)/libimg.so: $(SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(EXAMPLES)/img.c $(CC) -o $@ img.o $(SOLDFLAGS) rm img.o # # CBF and IMG libraries # CBF_IMG_LIBS: $(LIB)/libcbf.a $(LIB)/libimg.a # # FCB library # $(LIB)/libfcb.a: $(F90SOURCE) $(COMMONDEP) $(LIB) ifneq ($(F90C),) $(F90C) $(F90FLAGS) -c $(F90SOURCE) $(AR) cr $@ *.o ifneq ($(RANLIB),) $(RANLIB) $@ endif rm *.o else echo "Define F90C to build $(LIB)/libfcb.a" endif $(SOLIB)/libfcb.so: $(F90SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) ifneq ($(F90C),) $(F90C) $(F90FLAGS) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(F90SOURCE) $(F90C) $(F90FLAGS) -o $@ *.o $(SOLDFLAGS) rm *.o else echo "Define F90C to build $(SOLIB)/libfcb.so" endif # # Python bindings # $(PYCBF)/_pycbf.$(PYCBFEXT): $(PYCBF) $(LIB)/libcbf.a \ $(PYCBF)/$(SETUP_PY) \ $(LIB)/libfcb.a \ $(LIB)/libimg.a \ $(PYCBF)/pycbf.i \ $(PYCBF)/cbfhandlewrappers.i \ $(PYCBF)/cbfdetectorwrappers.i \ $(PYCBF)/cbfgenericwrappers.i \ $(PYCBF)/cbfgoniometerwrappers.i (cd $(PYCBF); python $(SETUP_PY) build $(PYCBFBOPT); cp build/lib.*/_pycbf.$(PYCBFEXT) .) $(PYCBF)/setup.py: $(M4)/setup_py.m4 (m4 -P -Dregexlib=NOREGEXLIB -Dregexlibdir=NOREGEXLIBDIR $(M4)/setup_py.m4 > $@) $(PYCBF)/setup_MINGW.py: m4/setup_py.m4 (m4 -P -Dregexlib=regex -Dregexlibdir=$(REGEXDIR) $(M4)/setup_py.m4 > $@) $(LIB)/_pycbf.$(PYCBFEXT): $(PYCBF)/_pycbf.$(PYCBFEXT) cp $(PYCBF)/_pycbf.$(PYCBFEXT) $(LIB)/_pycbf.$(PYCBFEXT) $(PYCBF)/pycbf.pdf: $(PYCBF)/pycbf.w (cd $(PYCBF); \ $(NUWEB) pycbf; \ latex pycbf; \ $(NUWEB) pycbf; \ latex pycbf; \ dvipdfm pycbf ) $(PYCBF)/CBFlib.txt: $(DOC)/CBFlib.html links -dump $(DOC)/CBFlib.html > $(PYCBF)/CBFlib.txt $(PYCBF)/cbfhandlewrappers.i \ $(PYCBF)/cbfdetectorwrappers.i \ $(PYCBF)/cbfgenericwrappers.i \ $(PYCBF)/cbfgoniometerwrappers.i: $(PYCBF)/CBFlib.txt $(PYCBF)/make_pycbf.py (cd $(PYCBF); python make_pycbf.py; $(PYSWIG) pycbf.i; python setup.py build) # # Java bindings # $(JCBF)/cbflib-$(VERSION).jar: $(JCBF) $(JCBF)/jcbf.i $(JSWIG) -I$(INCLUDE) -package org.iucr.cbflib -outdir $(JCBF) $(JCBF)/jcbf.i $(JAVAC) -d . $(JCBF)/*.java $(JAR) cf $@ org $(SOLIB)/libcbf_wrap.so: $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf.so $(CC) $(CFLAGS) $(NOLLFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) $(JAVAINCLUDES) -c $(JCBF)/jcbf_wrap.c $(CC) -o $@ jcbf_wrap.o $(SOLDFLAGS) -L$(SOLIB) -lcbf rm jcbf_wrap.o # # F90SOURCE # $(SRC)/fcb_exit_binary.f90: $(M4)/fcb_exit_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_exit_binary.m4) > $(SRC)/fcb_exit_binary.f90 $(SRC)/fcb_next_binary.f90: $(M4)/fcb_next_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_next_binary.m4) > $(SRC)/fcb_next_binary.f90 $(SRC)/fcb_open_cifin.f90: $(M4)/fcb_open_cifin.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_open_cifin.m4) > $(SRC)/fcb_open_cifin.f90 $(SRC)/fcb_packed.f90: $(M4)/fcb_packed.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_packed.m4) > $(SRC)/fcb_packed.f90 $(SRC)/fcb_read_bits.f90: $(M4)/fcb_read_bits.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_bits.m4) > $(SRC)/fcb_read_bits.f90 $(SRC)/fcb_read_image.f90: $(M4)/fcb_read_image.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_image.m4) > $(SRC)/fcb_read_image.f90 $(SRC)/fcb_read_xds_i2.f90: $(M4)/fcb_read_xds_i2.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_xds_i2.m4) > $(SRC)/fcb_read_xds_i2.f90 $(EXAMPLES)/test_fcb_read_image.f90: $(M4)/test_fcb_read_image.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) test_fcb_read_image.m4) > $(EXAMPLES)/test_fcb_read_image.f90 $(EXAMPLES)/test_xds_binary.f90: $(M4)/test_xds_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) test_xds_binary.m4) > $(EXAMPLES)/test_xds_binary.f90 # # convert_image example program # $(BIN)/convert_image: $(LIB)/libcbf.a $(EXAMPLES)/convert_image.c $(EXAMPLES)/img.c \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/convert_image.c $(EXAMPLES)/img.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # convert_minicbf example program # $(BIN)/convert_minicbf: $(LIB)/libcbf.a $(EXAMPLES)/convert_minicbf.c \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/convert_minicbf.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # makecbf example program # $(BIN)/makecbf: $(LIB)/libcbf.a $(EXAMPLES)/makecbf.c $(LIB)/libimg.a $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/makecbf.c -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # adscimg2cbf example program # $(BIN)/adscimg2cbf: $(LIB)/libcbf.a $(EXAMPLES)/adscimg2cbf.c $(EXAMPLES)/adscimg2cbf_sub.c $(CC) $(CFLAGS) $(NOLLFLAG) -D_SVID_SOURCE $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/adscimg2cbf.c $(EXAMPLES)/adscimg2cbf_sub.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # cbf2adscimg example program # $(BIN)/cbf2adscimg: $(LIB)/libcbf.a $(EXAMPLES)/cbf2adscimg.c $(EXAMPLES)/cbf2adscimg_sub.c $(CC) $(CFLAGS) $(NOLLFLAG) -D_SVID_SOURCE $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cbf2adscimg.c $(EXAMPLES)/cbf2adscimg_sub.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # changtestcompression example program # $(BIN)/changtestcompression: $(LIB)/libcbf.a $(EXAMPLES)/changtestcompression.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/changtestcompression.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # img2cif example program # $(BIN)/img2cif: $(LIB)/libcbf.a $(EXAMPLES)/img2cif.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOTPINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/img2cif.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # cif2cbf example program # $(BIN)/cif2cbf: $(LIB)/libcbf.a $(EXAMPLES)/cif2cbf.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cif2cbf.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # dectris cbf_template_t program # $(BIN)/cbf_template_t: $(DECTRIS_EXAMPLES)/cbf_template_t.c \ $(DECTRIS_EXAMPLES)/mx_cbf_t_extras.h \ $(DECTRIS_EXAMPLES)/mx_parms.h $(CC) $(CFLAGS) $(NOLLFLAG) -I $(DECTRIS_EXAMPLES) $(WARNINGS) \ $(DECTRIS_EXAMPLES)/cbf_template_t.c -o $@ # # testcell example program # $(BIN)/testcell: $(LIB)/libcbf.a $(EXAMPLES)/testcell.C $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testcell.C -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # cif2c example program # $(BIN)/cif2c: $(LIB)/libcbf.a $(EXAMPLES)/cif2c.c $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cif2c.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # sauter_test example program # $(BIN)/sauter_test: $(LIB)/libcbf.a $(EXAMPLES)/sauter_test.C $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/sauter_test.C -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # sequence_match example program # $(BIN)/sequence_match: $(LIB)/libcbf.a $(EXAMPLES)/sequence_match.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/sequence_match.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # tiff2cbf example program # $(BIN)/tiff2cbf: $(LIB)/libcbf.a $(EXAMPLES)/tiff2cbf.c \ $(GOPTLIB) $(GOPTINC) $(TIFF) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ -I$(TIFFPREFIX)/include $(EXAMPLES)/tiff2cbf.c $(GOPTLIB) -L$(LIB) \ -lcbf -L$(TIFFPREFIX)/lib -ltiff $(EXTRALIBS) -limg -o $@ # # Andy Arvai's buffered read test program # $(BIN)/arvai_test: $(LIB)/libcbf.a $(EXAMPLES)/arvai_test.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/arvai_test.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # testreals example program # $(BIN)/testreals: $(LIB)/libcbf.a $(EXAMPLES)/testreals.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testreals.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testflat example program # $(BIN)/testflat: $(LIB)/libcbf.a $(EXAMPLES)/testflat.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testflat.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testflatpacked example program # $(BIN)/testflatpacked: $(LIB)/libcbf.a $(EXAMPLES)/testflatpacked.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testflatpacked.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ ifneq ($(F90C),) # # test_xds_binary example program # $(BIN)/test_xds_binary: $(LIB)/libfcb.a $(EXAMPLES)/test_xds_binary.f90 $(F90C) $(F90FLAGS) $(F90LDFLAGS) $(EXAMPLES)/test_xds_binary.f90 \ -L$(LIB) -lfcb -o $@ # # test_fcb_read_image example program # $(BIN)/test_fcb_read_image: $(LIB)/libfcb.a $(EXAMPLES)/test_fcb_read_image.f90 $(F90C) $(F90FLAGS) $(F90LDFLAGS) $(EXAMPLES)/test_fcb_read_image.f90 \ -L$(LIB) -lfcb -o $@ endif # # testcbf (C) # $(BIN)/ctestcbf: $(EXAMPLES)/testcbf.c $(LIB)/libcbf.a $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testcbf.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testcbf (Java) # $(BIN)/testcbf.class: $(EXAMPLES)/testcbf.java $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf_wrap.so $(JAVAC) -cp $(JCBF)/cbflib-$(VERSION).jar -d $(BIN) $(EXAMPLES)/testcbf.java # # Data files for tests # $(DATADIRI): (cd ..; $(DOWNLOAD) $(DATAURLI)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Input.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Input.tar.gz) $(DATADIRO): (cd ..; $(DOWNLOAD) $(DATAURLO)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Output.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Output.tar.gz) $(DATADIRS): (cd ..; $(DOWNLOAD) $(DATAURLS)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz) # Input Data Files TESTINPUT_BASIC = example.mar2300 DATADIRI_INPUT_BASIC = $(DATADIRI)/example.mar2300$(CEXT) TESTINPUT_EXTRA = 9ins.cif mb_LP_1_001.img insulin_pilatus6m.cbf testrealin.cbf \ testflatin.cbf testflatpackedin.cbf XRD1621.tif DATADIRI_INPUT_EXTRA = $(DATADIRI)/9ins.cif$(CEXT) $(DATADIRI)/mb_LP_1_001.img$(CEXT) \ $(DATADIRI)/insulin_pilatus6m.cbf$(CEXT) $(DATADIRI)/testrealin.cbf$(CEXT) \ $(DATADIRI)/testflatin.cbf$(CEXT) $(DATADIRI)/testflatpackedin.cbf$(CEXT) \ $(DATADIRI)/XRD1621.tif$(CEXT) # Output Data Files TESTOUTPUT = adscconverted_flat_orig.cbf \ adscconverted_orig.cbf converted_flat_orig.cbf converted_orig.cbf \ insulin_pilatus6mconverted_orig.cbf \ mb_LP_1_001_orig.cbf testcell_orig.prt \ test_xds_bin_testflatout_orig.out \ test_xds_bin_testflatpackedout_orig.out test_fcb_read_testflatout_orig.out \ test_fcb_read_testflatpackedout_orig.out \ XRD1621_orig.cbf XRD1621_I4encbC100_orig.cbf NEWTESTOUTPUT = adscconverted_flat.cbf \ adscconverted.cbf converted_flat.cbf converted.cbf \ insulin_pilatus6mconverted.cbf \ mb_LP_1_001.cbf testcell.prt \ test_xds_bin_testflatout.out \ test_xds_bin_testflatpackedout.out test_fcb_read_testflatout.out \ test_fcb_read_testflatpackedout.out \ XRD1621.cbf XRD1621_I4encbC100.cbf DATADIRO_OUTPUT = $(DATADIRO)/adscconverted_flat_orig.cbf$(CEXT) \ $(DATADIRO)/adscconverted_orig.cbf$(CEXT) \ $(DATADIRO)/converted_flat_orig.cbf$(CEXT) \ $(DATADIRO)/converted_orig.cbf$(CEXT) \ $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(CEXT) \ $(DATADIRO)/mb_LP_1_001_orig.cbf$(CEXT) \ $(DATADIRO)/testcell_orig.prt$(CEXT) \ $(DATADIRO)/test_xds_bin_testflatout_orig.out$(CEXT) \ $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(CEXT) \ $(DATADIRO)/test_fcb_read_testflatout_orig.out$(CEXT) \ $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(CEXT) \ $(DATADIRO)/XRD1621_orig.cbf$(CEXT) \ $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(CEXT) DATADIRO_OUTPUT_SIGNATURES = $(DATADIRO)/adscconverted_flat_orig.cbf$(SEXT) \ $(DATADIRO)/adscconverted_orig.cbf$(SEXT) \ $(DATADIRO)/converted_flat_orig.cbf$(SEXT) \ $(DATADIRO)/converted_orig.cbf$(SEXT) \ $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(SEXT) \ $(DATADIRO)/mb_LP_1_001_orig.cbf$(SEXT) \ $(DATADIRO)/testcell_orig.prt$(SEXT) \ $(DATADIRO)/test_xds_bin_testflatout_orig.out$(SEXT) \ $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(SEXT) \ $(DATADIRO)/test_fcb_read_testflatout_orig.out$(SEXT) \ $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(SEXT) \ $(DATADIRO)/XRD1621_orig.cbf$(SEXT) \ $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(SEXT) # Output Data File Signatures TESTOUTPUTSIGS = adscconverted_flat_orig.cbf$(SEXT) \ adscconverted_orig.cbf$(SEXT) converted_flat_orig.cbf$(SEXT) converted_orig.cbf$(SEXT) \ insulin_pilatus6mconverted_orig.cbf$(SEXT) \ mb_LP_1_001_orig.cbf$(SEXT) testcell_orig.prt$(SEXT) \ test_xds_bin_testflatout_orig.out$(SEXT) \ test_xds_bin_testflatpackedout_orig.out$(SEXT) test_fcb_read_testflatout_orig.out$(SEXT) \ test_fcb_read_testflatpackedout_orig.out$(SEXT) \ XRD1621_orig.cbf$(SEXT) DATADIRS_OUTPUT_SIGNATURES = $(DATADIRS)/adscconverted_flat_orig.cbf$(SEXT) \ $(DATADIRS)/adscconverted_orig.cbf$(SEXT) \ $(DATADIRS)/converted_flat_orig.cbf$(SEXT) \ $(DATADIRS)/converted_orig.cbf$(SEXT) \ $(DATADIRS)/insulin_pilatus6mconverted_orig.cbf$(SEXT) \ $(DATADIRS)/mb_LP_1_001_orig.cbf$(SEXT) \ $(DATADIRS)/testcell_orig.prt$(SEXT) \ $(DATADIRS)/test_xds_bin_testflatout_orig.out$(SEXT) \ $(DATADIRS)/test_xds_bin_testflatpackedout_orig.out$(SEXT) \ $(DATADIRS)/test_fcb_read_testflatout_orig.out$(SEXT) \ $(DATADIRS)/test_fcb_read_testflatpackedout_orig.out$(SEXT) \ $(DATADIRS)/XRD1621_orig.cbf$(SEXT) \ $(DATADIRS)/XRD1621_I4encbC100_orig.cbf$(SEXT) # Fetch Input Data Files $(TESTINPUT_BASIC): $(DATADIRI) $(DATADIRI_INPUT_BASIC) $(DECOMPRESS) < $(DATADIRI)/$@$(CEXT) > $@ cp $(DATADIRI)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) $(TESTINPUT_EXTRA): $(DATADIRI) $(DATADIRI_INPUT_EXTRA) $(DECOMPRESS) < $(DATADIRI)/$@$(CEXT) > $@ cp $(DATADIRI)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) # Fetch Output Data Files and Signatures $(TESTOUTPUT): $(DATADIRO) $(DATADIRO_OUTPUT) $(DATADIRO_OUTPUT_SIGNATURES) $(DECOMPRESS) < $(DATADIRO)/$@$(CEXT) > $@ cp $(DATADIRO)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) # Fetch Output Data File Signatures $(TESTOUTPUTSIGS): $(DATADIRS) $(DATADIRS_OUTPUT_SIGNATURES) cp $(DATADIRS)/$@ $@ # # Tests # tests: $(LIB) $(BIN) symlinksdone basic extra dectristests pycbftests tests_sigs_only: $(LIB) $(BIN) symlinksdone basic extra_sigs_only restore_output: $(NEWTESTOUTPUT) $(DATADIRO) $(SIGNATURE) < adscconverted_flat.cbf > $(DATADIRO)/adscconverted_flat_orig.cbf$(SEXT) $(SIGNATURE) < adscconverted.cbf > $(DATADIRO)/adscconverted_orig.cbf$(SEXT) $(SIGNATURE) < converted_flat.cbf > $(DATADIRO)/converted_flat_orig.cbf$(SEXT) $(SIGNATURE) < converted.cbf > $(DATADIRO)/converted_orig.cbf$(SEXT) $(SIGNATURE) < insulin_pilatus6mconverted.cbf > $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(SEXT) $(SIGNATURE) < mb_LP_1_001.cbf$ > $(DATADIRO)/mb_LP_1_001_orig.cbf$(SEXT) $(SIGNATURE) < testcell.prt > $(DATADIRO)/testcell_orig.prt$(SEXT) $(SIGNATURE) < test_xds_bin_testflatout.out > $(DATADIRO)/test_xds_bin_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_xds_bin_testflatpackedout.out > $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatout.out > $(DATADIRO)/test_fcb_read_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatpackedout.out > $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < XRD1621.cbf > $(DATADIRO)/XRD1621_orig.cbf$(SEXT) $(SIGNATURE) < XRD1621_I4encbC100.cbf > $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(SEXT) $(COMPRESS) < adscconverted_flat.cbf > $(DATADIRO)/adscconverted_flat_orig.cbf$(CEXT) $(COMPRESS) < adscconverted.cbf > $(DATADIRO)/adscconverted_orig.cbf$(CEXT) $(COMPRESS) < converted_flat.cbf > $(DATADIRO)/converted_flat_orig.cbf$(CEXT) $(COMPRESS) < converted.cbf > $(DATADIRO)/converted_orig.cbf$(CEXT) $(COMPRESS) < insulin_pilatus6mconverted.cbf > $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(CEXT) $(COMPRESS) < mb_LP_1_001.cbf$ > $(DATADIRO)/mb_LP_1_001_orig.cbf$(CEXT) $(COMPRESS) < testcell.prt > $(DATADIRO)/testcell_orig.prt$(CEXT) $(COMPRESS) < test_xds_bin_testflatout.out > $(DATADIRO)/test_xds_bin_testflatout_orig.out$(CEXT) $(COMPRESS) < test_xds_bin_testflatpackedout.out > $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(CEXT) $(COMPRESS) < test_fcb_read_testflatout.out > $(DATADIRO)/test_fcb_read_testflatout_orig.out$(CEXT) $(COMPRESS) < test_fcb_read_testflatpackedout.out > $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(CEXT) $(COMPRESS) < XRD1621.cbf > $(DATADIRO)/XRD1621_orig.cbf$(CEXT) $(COMPRESS) < XRD1621_I4encbC100.cbf > $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(CEXT) restore_sigs_only: $(NEWTESTOUTPUT) $(DATADIRS) $(SIGNATURE) < adscconverted_flat.cbf > $(DATADIRS)/adscconverted_flat_orig.cbf$(SEXT) $(SIGNATURE) < adscconverted.cbf > $(DATADIRS)/adscconverted_orig.cbf$(SEXT) $(SIGNATURE) < converted_flat.cbf > $(DATADIRS)/converted_flat_orig.cbf$(SEXT) $(SIGNATURE) < converted.cbf > $(DATADIRS)/converted_orig.cbf$(SEXT) $(SIGNATURE) < insulin_pilatus6mconverted.cbf > $(DATADIRS)/insulin_pilatus6mconverted_orig.cbf$(SEXT) $(SIGNATURE) < mb_LP_1_001.cbf$ > $(DATADIRS)/mb_LP_1_001_orig.cbf$(SEXT) $(SIGNATURE) < testcell.prt > $(DATADIRS)/testcell_orig.prt$(SEXT) $(SIGNATURE) < test_xds_bin_testflatout.out > $(DATADIRS)/test_xds_bin_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_xds_bin_testflatpackedout.out > $(DATADIRS)/test_xds_bin_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatout.out > $(DATADIRS)/test_fcb_read_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatpackedout.out > $(DATADIRS)/test_fcb_read_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < XRD1621.cbf > $(DATADIRS)/XRD1621_orig.cbf$(SEXT) $(SIGNATURE) < XRD1621_I4encbC100.cbf > $(DATADIRS)/XRD1621_I4encbC100_orig.cbf$(SEXT) restore_signatures: restore_output restore_sigs_only # # Basic Tests # basic: $(BIN)/makecbf $(BIN)/img2cif $(BIN)/cif2cbf $(TESTINPUT_BASIC) $(BIN)/makecbf example.mar2300 makecbf.cbf $(BIN)/img2cif -c flatpacked -m headers -d digest \ -e base64 example.mar2300 img2cif_packed.cif $(BIN)/img2cif -c canonical -m headers -d digest \ -e base64 example.mar2300 img2cif_canonical.cif $(BIN)/img2cif -c flatpacked -m headers -d digest \ -e none example.mar2300 img2cif_packed.cbf $(BIN)/img2cif -c canonical -m headers -d digest \ -e none example.mar2300 img2cif_canonical.cbf $(BIN)/cif2cbf -e none -c flatpacked \ img2cif_canonical.cif cif2cbf_packed.cbf $(BIN)/cif2cbf -e none -c canonical \ img2cif_packed.cif cif2cbf_canonical.cbf -cmp cif2cbf_packed.cbf makecbf.cbf -cmp cif2cbf_packed.cbf img2cif_packed.cbf -cmp cif2cbf_canonical.cbf img2cif_canonical.cbf # # Extra Tests # ifneq ($(F90C),) extra: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/test_xds_binary $(BIN)/test_fcb_read_image $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg \ $(BIN)/changtestcompression $(BIN)/tiff2cbf \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUT) else extra: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUT) endif $(TIME) $(BIN)/cif2cbf -e hex -c none \ makecbf.cbf cif2cbf_ehcn.cif $(TIME) $(BIN)/cif2cbf -e none -c flatpacked \ cif2cbf_ehcn.cif cif2cbf_encp.cbf; rm cif2cbf_ehcn.cif -cmp makecbf.cbf cif2cbf_encp.cbf $(TIME) $(BIN)/cif2cbf -i 9ins.cif -o 9ins.cbf -cmp 9ins.cif 9ins.cbf $(TIME) $(BIN)/convert_image -F example.mar2300 converted_flat.cbf -cmp converted_flat.cbf converted_flat_orig.cbf $(TIME) $(BIN)/convert_image example.mar2300 converted.cbf -cmp converted.cbf converted_orig.cbf -$(TIME) $(BIN)/testcell < testcell.dat > testcell.prt -cmp testcell.prt testcell_orig.prt $(TIME) $(BIN)/convert_image -F -d adscquantum315 mb_LP_1_001.img adscconverted_flat.cbf -cmp adscconverted_flat.cbf adscconverted_flat_orig.cbf $(TIME) $(BIN)/convert_image -d adscquantum315 mb_LP_1_001.img adscconverted.cbf -cmp adscconverted.cbf adscconverted_orig.cbf $(TIME) $(BIN)/adscimg2cbf --no_pad --cbf_packed,flat mb_LP_1_001.img -cmp mb_LP_1_001.cbf mb_LP_1_001_orig.cbf ifneq ($(CLEANTESTS),) mv mb_LP_1_001.cbf nmb_LP_1_001.cbf else cp mb_LP_1_001.cbf nmb_LP_1_001.cbf endif $(TIME) $(BIN)/cbf2adscimg nmb_LP_1_001.cbf -cmp nmb_LP_1_001.img mb_LP_1_001.img rm nmb_LP_1_001.cbf ifneq ($(CLEANTESTS),) rm nmb_LP_1_001.img endif $(TIME) $(BIN)/convert_minicbf -d pilatus6m insulin_pilatus6m.cbf insulin_pilatus6mconverted.cbf -cmp insulin_pilatus6mconverted.cbf insulin_pilatus6mconverted_orig.cbf $(TIME) $(BIN)/testreals -cmp testrealin.cbf testrealout.cbf $(TIME) $(BIN)/testflat -cmp testflatin.cbf testflatout.cbf $(TIME) $(BIN)/testflatpacked -cmp testflatpackedin.cbf testflatpackedout.cbf ifneq ($(F90C),) echo testflatout.cbf | $(TIME) $(BIN)/test_xds_binary > test_xds_bin_testflatout.out -$(DIFF) test_xds_bin_testflatout.out test_xds_bin_testflatout_orig.out echo testflatpackedout.cbf | $(TIME) $(BIN)/test_xds_binary > test_xds_bin_testflatpackedout.out -$(DIFF) test_xds_bin_testflatpackedout.out test_xds_bin_testflatpackedout_orig.out echo testflatout.cbf | $(TIME) $(BIN)/test_fcb_read_image > test_fcb_read_testflatout.out -$(DIFF) test_fcb_read_testflatout.out test_fcb_read_testflatout_orig.out echo testflatpackedout.cbf | $(TIME) $(BIN)/test_fcb_read_image > test_fcb_read_testflatpackedout.out -$(DIFF) test_fcb_read_testflatpackedout.out test_fcb_read_testflatpackedout_orig.out endif $(TIME) $(BIN)/sauter_test $(TIME) $(BIN)/changtestcompression $(TIME) (export LD_LIBRARY_PATH=$(LIB);$(BIN)/tiff2cbf XRD1621.tif XRD1621.cbf) -$(DIFF) XRD1621.cbf XRD1621_orig.cbf $(TIME) $(BIN)/cif2cbf -I 4 -C 100. -L 0. -e n -c b -i XRD1621.cbf -o XRD1621_I4encbC100.cbf -$(DIFF) XRD1621_I4encbC100.cbf XRD1621_I4encbC100_orig.cbf ifneq ($(F90C),) extra_sigs_only: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/test_xds_binary $(BIN)/test_fcb_read_image $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg $(BIN)/tiff2cbf \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) else extra_sigs_only: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf\ basic $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) endif $(TIME) $(BIN)/cif2cbf -e hex -c none \ makecbf.cbf cif2cbf_ehcn.cif $(TIME) $(BIN)/cif2cbf -e none -c packed \ cif2cbf_ehcn.cif cif2cbf_encp.cbf; rm cif2cbf_ehcn.cif -cmp makecbf.cbf cif2cbf_encp.cbf $(TIME) $(BIN)/cif2cbf -i 9ins.cif -o 9ins.cbf -cmp 9ins.cif 9ins.cbf $(TIME) $(BIN)/convert_image -F example.mar2300 converted_flat.cbf -$(SIGNATURE) < converted_flat.cbf | $(DIFF) - converted_flat_orig.cbf$(SEXT); rm converted_flat.cbf $(TIME) $(BIN)/convert_image example.mar2300 converted.cbf -$(SIGNATURE) < converted.cbf | $(DIFF) - converted_orig.cbf$(SEXT); rm converted.cbf -$(TIME) $(BIN)/testcell < testcell.dat | \ $(SIGNATURE) | $(DIFF) - testcell_orig.prt$(SEXT) $(TIME) $(BIN)/convert_image -F -d adscquantum315 mb_LP_1_001.img adscconverted_flat.cbf -$(SIGNATURE) < adscconverted_flat.cbf | $(DIFF) - adscconverted_flat_orig.cbf$(SEXT) $(TIME) $(BIN)/convert_image -d adscquantum315 mb_LP_1_001.img adscconverted.cbf -$(SIGNATURE) < adscconverted.cbf | $(DIFF) - adscconverted_orig.cbf$(SEXT); rm adscconverted.cbf $(TIME) $(BIN)/adscimg2cbf --cbf_packed,flat mb_LP_1_001.img -$(SIGNATURE) < mb_LP_1_001.cbf | $(DIFF) - mb_LP_1_001_orig.cbf$(SEXT) mv mb_LP_1_001.cbf nmb_LP_1_001.cbf $(TIME) $(BIN)/cbf2adscimg nmb_LP_1_001.cbf -cmp nmb_LP_1_001.img mb_LP_1_001.img rm nmb_LP_1_001.cbf rm nmb_LP_1_001.img $(TIME) $(BIN)/convert_minicbf -d pilatus6m insulin_pilatus6m.cbf insulin_pilatus6mconverted.cbf -$(SIGNATURE) < insulin_pilatus6mconverted.cbf | $(DIFF) - insulin_pilatus6mconverted_orig.cbf$(SEXT); rm insulin_pilatus6mconverted.cbf $(TIME) $(BIN)/testreals -cmp testrealin.cbf testrealout.cbf $(TIME) $(BIN)/testflat -cmp testflatin.cbf testflatout.cbf $(TIME) $(BIN)/testflatpacked -cmp testflatpackedin.cbf testflatpackedout.cbf ifneq ($(F90C),) echo testflatout.cbf | $(TIME) $(BIN)/test_xds_binary | \ $(SIGNATURE) | $(DIFF) - test_xds_bin_testflatout_orig.out$(SEXT) echo testflatpackedout.cbf | $(TIME) $(BIN)/test_xds_binary | \ $(SIGNATURE) | $(DIFF) - test_xds_bin_testflatpackedout_orig.out$(SEXT) echo testflatout.cbf | $(TIME) $(BIN)/test_fcb_read_image | \ $(SIGNATURE) | $(DIFF) - test_fcb_read_testflatout_orig.out$(SEXT) echo testflatpackedout.cbf | $(TIME) $(BIN)/test_fcb_read_image | \ $(SIGNATURE) | $(DIFF) - test_fcb_read_testflatpackedout_orig.out$(SEXT) endif $(TIME) $(BIN)/sauter_test $(TIME) $(BIN)/tiff2cbf XRD1621.tif XRD1621.cbf $(TIME) $(BIN)/cif2cbf -I 4 -C 100. -L 0. -e n -c b -i XRD1621.cbf -o XRD1621_I4encbC100.cbf -$(SIGNATURE) < XRD1621.cbf | $(DIFF) - XRD1621_orig.cbf$(SEXT); rm XRD1621.cbf -$(SIGNATURE) < XRD1621_I4encbC100.cbf | $(DIFF) - XRD1621_I4encbC100_orig.cbf$(SEXT); rm XRD1621_I4encbC100.cbf @-rm -f adscconverted_flat.cbf @-rm -f $(TESTINPUT_BASIC) $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) @-rm -f cif2cbf_packed.cbf makecbf.cbf \ cif2cbf_packed.cbf img2cif_packed.cbf \ cif2cbf_canonical.cbf img2cif_canonical.cbf @-rm -f testrealout.cbf testflatout.cbf testflatpackedout.cbf \ cif2cbf_encp.cbf img2cif_canonical.cif img2cif_packed.cif 9ins.cbf pycbftests: $(PYCBF)/_pycbf.$(PYCBFEXT) (cd $(PYCBF); python pycbf_test1.py) (cd $(PYCBF); python pycbf_test2.py) (cd $(PYCBF); python pycbf_test3.py) javatests: $(BIN)/ctestcbf $(BIN)/testcbf.class $(SOLIB)/libcbf_wrap.so $(BIN)/ctestcbf > testcbfc.txt $(LDPREFIX) java -cp $(JCBF)/cbflib-$(VERSION).jar:$(BIN) testcbf > testcbfj.txt $(DIFF) testcbfc.txt testcbfj.txt dectristests: $(BIN)/cbf_template_t $(DECTRIS_EXAMPLES)/cbf_test_orig.out (cd $(DECTRIS_EXAMPLES); ../../bin/cbf_template_t; diff -a -u cbf_test_orig.out cbf_template_t.out) # # Remove all non-source files # empty: @-rm -f $(LIB)/*.o @-rm -f $(LIB)/libcbf.a @-rm -f $(LIB)/libfcb.a @-rm -f $(LIB)/libimg.a @-rm -f $(LIB)/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/build/*/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/build/src/cbf_simple.o @-rm -f $(PYCBF)/build/*/pycbf_wrap.o @-rm -rf $(BIN)/adscimg2cbf* @-rm -rf $(BIN)/cbf2adscimg* @-rm -rf $(BIN)/makecbf* @-rm -rf $(BIN)/img2cif* @-rm -rf $(BIN)/cif2cbf* @-rm -rf $(BIN)/convert_image* @-rm -rf $(BIN)/convert_minicbf* @-rm -rf $(BIN)/test_fcb_read_image* @-rm -rf $(BIN)/test_xds_binary* @-rm -rf $(BIN)/testcell* @-rm -rf $(BIN)/cif2c* @-rm -rf $(BIN)/testreals* @-rm -rf $(BIN)/testflat* @-rm -rf $(BIN)/testflatpacked* @-rm -rf $(BIN)/cbf_template_t* @-rm -rf $(BIN)/sauter_test* @-rm -rf $(BIN)/arvai_test* @-rm -rf $(BIN)/changtestcompression* @-rm -rf $(BIN)/tiff2cbf* @-rm -f makecbf.cbf @-rm -f img2cif_packed.cif @-rm -f img2cif_canonical.cif @-rm -f img2cif_packed.cbf @-rm -f img2cif_canonical.cbf @-rm -f img2cif_raw.cbf @-rm -f cif2cbf_packed.cbf @-rm -f cif2cbf_canonical.cbf @-rm -f converted.cbf @-rm -f adscconverted.cbf @-rm -f converted_flat.cbf @-rm -f adscconverted_flat.cbf @-rm -f adscconverted_flat_rev.cbf @-rm -f mb_LP_1_001.cbf @-rm -f cif2cbf_ehcn.cif @-rm -f cif2cbf_encp.cbf @-rm -f 9ins.cbf @-rm -f 9ins.cif @-rm -f testcell.prt @-rm -f example.mar2300 @-rm -f converted_orig.cbf @-rm -f adscconverted_orig.cbf @-rm -f converted_flat_orig.cbf @-rm -f adscconverted_flat_orig.cbf @-rm -f adscconverted_flat_rev_orig.cbf @-rm -f mb_LP_1_001_orig.cbf @-rm -f insulin_pilatus6mconverted_orig.cbf @-rm -f insulin_pilatus6mconverted.cbf @-rm -f insulin_pilatus6m.cbf @-rm -f testrealin.cbf @-rm -f testrealout.cbf @-rm -f testflatin.cbf @-rm -f testflatout.cbf @-rm -f testflatpackedin.cbf @-rm -f testflatpackedout.cbf @-rm -f CTC.cbf @-rm -f test_fcb_read_testflatout.out @-rm -f test_fcb_read_testflatpackedout.out @-rm -f test_xds_bin_testflatpackedout.out @-rm -f test_xds_bin_testflatout.out @-rm -f test_fcb_read_testflatout_orig.out @-rm -f test_fcb_read_testflatpackedout_orig.out @-rm -f test_xds_bin_testflatpackedout_orig.out @-rm -f test_xds_bin_testflatout_orig.out @-rm -f mb_LP_1_001.img @-rm -f 9ins.cif @-rm -f testcell_orig.prt @-rm -f $(DECTRIS_EXAMPLES)/cbf_template_t.out @-rm -f XRD1621.cbf @-rm -f XRD1621_orig.cbf @-rm -f XRD1621_orig.cbf @-rm -f XRD1621_I4encbC100.cbf @-rm -f $(SRC)/fcb_exit_binary.f90 @-rm -f $(SRC)/fcb_next_binary.f90 @-rm -f $(SRC)/fcb_open_cifin.f90 @-rm -f $(SRC)/fcb_packed.f90 @-rm -f $(SRC)/fcb_read_bits.f90 @-rm -f $(SRC)/fcb_read_image.f90 @-rm -f $(SRC)/fcb_read_xds_i2.f90 @-rm -f $(EXAMPLES)/test_fcb_read_image.f90 @-rm -f $(EXAMPLES)/test_xds_binary.f90 @-rm -f symlinksdone @-rm -f $(TESTOUTPUT) *$(SEXT) @-rm -f $(SOLIB)/*.o @-rm -f $(SOLIB)/libcbf_wrap.so @-rm -f $(SOLIB)/libjcbf.so @-rm -f $(SOLIB)/libimg.so @-rm -f $(SOLIB)/libfcb.so @-rm -rf $(JCBF)/org @-rm -f $(JCBF)/*.java @-rm -f $(JCBF)/jcbf_wrap.c @-rm -f $(SRC)/cbf_wrap.c @-rm -f $(BIN)/ctestcbf $(BIN)/testcbf.class testcbfc.txt testcbfj.txt @-rm -rf $(REGEX) @-rm -rf $(TIFF) ./.undosymlinks # # Remove temporary files # clean: @-rm -f core @-rm -f *.o @-rm -f *.u # # Restore to distribution state # distclean: clean empty # # Create a Tape Archive for distribution # tar: $(DOCUMENTS) $(SOURCE) $(SRC)/cbf.stx $(HEADERS) $(M4FILES)\ $(EXAMPLES) \ README.html README Makefile \ $(JPEGS) -/bin/rm -f CBFlib.tar* tar cvBf CBFlib.tar \ $(DOCUMENTS) $(SOURCE) $(SRC)/cbf.stx $(HEADERS) $(M4FILES)\ $(EXAMPLES) \ README.html README Makefile \ $(JPEGS) gzip --best CBFlib.tar ./CBFlib-0.9.2.2/Makefile_OSX_gcc42_DMALLOC0000644000076500007650000020040211603702122016100 0ustar yayayaya ###################################################################### # Makefile - command file for make to create CBFlib # # # # Version 0.9.2 12 Feb 2011 # # # # Paul Ellis and # # Herbert J. Bernstein (yaya@bernstein-plus-sons.com) # # # # (C) Copyright 2006 - 2011 Herbert J. Bernstein # # # ###################################################################### ###################################################################### # # # YOU MAY REDISTRIBUTE THE CBFLIB PACKAGE UNDER THE TERMS OF THE GPL # # # # ALTERNATIVELY YOU MAY REDISTRIBUTE THE CBFLIB API UNDER THE TERMS # # OF THE LGPL # # # ###################################################################### ########################### GPL NOTICES ############################## # # # This program is free software; you can redistribute it and/or # # modify it under the terms of the GNU General Public License as # # published by the Free Software Foundation; either version 2 of # # (the License, or (at your option) any later version. # # # # This program is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # # GNU General Public License for more details. # # # # You should have received a copy of the GNU General Public License # # along with this program; if not, write to the Free Software # # Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA # # 02111-1307 USA # # # ###################################################################### ######################### LGPL NOTICES ############################### # # # This library is free software; you can redistribute it and/or # # modify it under the terms of the GNU Lesser General Public # # License as published by the Free Software Foundation; either # # version 2.1 of the License, or (at your option) any later version. # # # # This library is distributed in the hope that it will be useful, # # but WITHOUT ANY WARRANTY; without even the implied warranty of # # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # # Lesser General Public License for more details. # # # # You should have received a copy of the GNU Lesser General Public # # License along with this library; if not, write to the Free # # Software Foundation, Inc., 51 Franklin St, Fifth Floor, Boston, # # MA 02110-1301 USA # # # ###################################################################### ###################################################################### # # # Stanford University Notices # # for the CBFlib software package that incorporates SLAC software # # on which copyright is disclaimed # # # # This software # # ------------- # # The term "this software", as used in these Notices, refers to # # those portions of the software package CBFlib that were created by # # employees of the Stanford Linear Accelerator Center, Stanford # # University. # # # # Stanford disclaimer of copyright # # -------------------------------- # # Stanford University, owner of the copyright, hereby disclaims its # # copyright and all other rights in this software. Hence, anyone # # may freely use it for any purpose without restriction. # # # # Acknowledgement of sponsorship # # ------------------------------ # # This software was produced by the Stanford Linear Accelerator # # Center, Stanford University, under Contract DE-AC03-76SFO0515 with # # the Department of Energy. # # # # Government disclaimer of liability # # ---------------------------------- # # Neither the United States nor the United States Department of # # Energy, nor any of their employees, makes any warranty, express or # # implied, or assumes any legal liability or responsibility for the # # accuracy, completeness, or usefulness of any data, apparatus, # # product, or process disclosed, or represents that its use would # # not infringe privately owned rights. # # # # Stanford disclaimer of liability # # -------------------------------- # # Stanford University makes no representations or warranties, # # express or implied, nor assumes any liability for the use of this # # software. # # # # Maintenance of notices # # ---------------------- # # In the interest of clarity regarding the origin and status of this # # software, this and all the preceding Stanford University notices # # are to remain affixed to any copy or derivative of this software # # made or distributed by the recipient and are to be affixed to any # # copy of software made or distributed by the recipient that # # contains a copy or derivative of this software. # # # # Based on SLAC Software Notices, Set 4 # # OTT.002a, 2004 FEB 03 # ###################################################################### ###################################################################### # NOTICE # # Creative endeavors depend on the lively exchange of ideas. There # # are laws and customs which establish rights and responsibilities # # for authors and the users of what authors create. This notice # # is not intended to prevent you from using the software and # # documents in this package, but to ensure that there are no # # misunderstandings about terms and conditions of such use. # # # # Please read the following notice carefully. If you do not # # understand any portion of this notice, please seek appropriate # # professional legal advice before making use of the software and # # documents included in this software package. In addition to # # whatever other steps you may be obliged to take to respect the # # intellectual property rights of the various parties involved, if # # you do make use of the software and documents in this package, # # please give credit where credit is due by citing this package, # # its authors and the URL or other source from which you obtained # # it, or equivalent primary references in the literature with the # # same authors. # # # # Some of the software and documents included within this software # # package are the intellectual property of various parties, and # # placement in this package does not in any way imply that any # # such rights have in any way been waived or diminished. # # # # With respect to any software or documents for which a copyright # # exists, ALL RIGHTS ARE RESERVED TO THE OWNERS OF SUCH COPYRIGHT. # # # # Even though the authors of the various documents and software # # found here have made a good faith effort to ensure that the # # documents are correct and that the software performs according # # to its documentation, and we would greatly appreciate hearing of # # any problems you may encounter, the programs and documents any # # files created by the programs are provided **AS IS** without any * # warranty as to correctness, merchantability or fitness for any # # particular or general use. # # # # THE RESPONSIBILITY FOR ANY ADVERSE CONSEQUENCES FROM THE USE OF # # PROGRAMS OR DOCUMENTS OR ANY FILE OR FILES CREATED BY USE OF THE # # PROGRAMS OR DOCUMENTS LIES SOLELY WITH THE USERS OF THE PROGRAMS # # OR DOCUMENTS OR FILE OR FILES AND NOT WITH AUTHORS OF THE # # PROGRAMS OR DOCUMENTS. # ###################################################################### ###################################################################### # # # The IUCr Policy # # for the Protection and the Promotion of the STAR File and # # CIF Standards for Exchanging and Archiving Electronic Data # # # # Overview # # # # The Crystallographic Information File (CIF)[1] is a standard for # # information interchange promulgated by the International Union of # # Crystallography (IUCr). CIF (Hall, Allen & Brown, 1991) is the # # recommended method for submitting publications to Acta # # Crystallographica Section C and reports of crystal structure # # determinations to other sections of Acta Crystallographica # # and many other journals. The syntax of a CIF is a subset of the # # more general STAR File[2] format. The CIF and STAR File approaches # # are used increasingly in the structural sciences for data exchange # # and archiving, and are having a significant influence on these # # activities in other fields. # # # # Statement of intent # # # # The IUCr's interest in the STAR File is as a general data # # interchange standard for science, and its interest in the CIF, # # a conformant derivative of the STAR File, is as a concise data # # exchange and archival standard for crystallography and structural # # science. # # # # Protection of the standards # # # # To protect the STAR File and the CIF as standards for # # interchanging and archiving electronic data, the IUCr, on behalf # # of the scientific community, # # # # # holds the copyrights on the standards themselves, * # # # # owns the associated trademarks and service marks, and * # # # # holds a patent on the STAR File. * # # # These intellectual property rights relate solely to the # # interchange formats, not to the data contained therein, nor to # # the software used in the generation, access or manipulation of # # the data. # # # # Promotion of the standards # # # # The sole requirement that the IUCr, in its protective role, # # imposes on software purporting to process STAR File or CIF data # # is that the following conditions be met prior to sale or # # distribution. # # # # # Software claiming to read files written to either the STAR * # File or the CIF standard must be able to extract the pertinent # # data from a file conformant to the STAR File syntax, or the CIF # # syntax, respectively. # # # # # Software claiming to write files in either the STAR File, or * # the CIF, standard must produce files that are conformant to the # # STAR File syntax, or the CIF syntax, respectively. # # # # # Software claiming to read definitions from a specific data * # dictionary approved by the IUCr must be able to extract any # # pertinent definition which is conformant to the dictionary # # definition language (DDL)[3] associated with that dictionary. # # # # The IUCr, through its Committee on CIF Standards, will assist # # any developer to verify that software meets these conformance # # conditions. # # # # Glossary of terms # # # # [1] CIF: is a data file conformant to the file syntax defined # # at http://www.iucr.org/iucr-top/cif/spec/index.html # # # # [2] STAR File: is a data file conformant to the file syntax # # defined at http://www.iucr.org/iucr-top/cif/spec/star/index.html # # # # [3] DDL: is a language used in a data dictionary to define data # # items in terms of "attributes". Dictionaries currently approved # # by the IUCr, and the DDL versions used to construct these # # dictionaries, are listed at # # http://www.iucr.org/iucr-top/cif/spec/ddl/index.html # # # # Last modified: 30 September 2000 # # # # IUCr Policy Copyright (C) 2000 International Union of # # Crystallography # ###################################################################### # Version string VERSION = 0.9.2 # # Comment out the next line if scratch test files sould be retain # CLEANTESTS = yes # # Definition to get a version of tifflib to support tiff2cbf # TIFF = tiff-3.9.4-rev-6Feb11 TIFFPREFIX = $(PWD) # # Definitions to get a stable version of regex # REGEX = regex-20090805 REGEXDIR = /usr/lib REGEXDEP = # Program to use to retrieve a URL DOWNLOAD = wget # Flag to control symlinks versus copying SLFLAGS = --use_ln # # Program to use to pack shars # SHAR = /usr/bin/shar #SHAR = /usr/local/bin/gshar # # Program to use to create archives # AR = /usr/bin/ar # # Program to use to add an index to an archive # RANLIB = /usr/bin/ranlib # # Program to use to decompress a data file # DECOMPRESS = /usr/bin/bunzip2 # # Program to use to compress a data file # COMPRESS = /usr/bin/bzip2 # # Program to use to generate a signature # SIGNATURE = /usr/bin/openssl dgst -md5 # # Extension for compressed data file (with period) # CEXT = .bz2 # # Extension for signatures of files # SEXT = .md5 # call to time a command #TIME = #TIME = time # # Program to display differences between files # DIFF = diff -u -b # # Program to generate wrapper classes for Python # PYSWIG = swig -python # # Program to generate wrapper classes for Java # JSWIG = swig -java # # Program to generate LaTex and HTML program documentation # NUWEB = nuweb # # Compiler for Java # JAVAC = javac # # Java archiver for compiled classes # JAR = jar # # Java SDK root directory # ifeq ($(JDKDIR),) JDKDIR = /usr/lib/java endif ifneq ($(CBF_DONT_USE_LONG_LONG),) NOLLFLAG = -DCBF_DONT_USE_LONG_LONG else NOLLFLAG = endif # # PYCBF definitions # PYCBFEXT = so PYCBFBOPT = SETUP_PY = setup.py # # Set the compiler and flags # ######################################################### # # Appropriate compiler definitions for MAC OS X # with gcc 4.2 and DMALLOC # Also change defintion of DOWNLOAD # ######################################################### CC = gcc C++ = g++ CFLAGS = -g -O2 -Wall -ansi -pedantic -DDMALLOC -DDMALLOC_FUNC_CHECK -I$(HOME)/include F90C = gfortran F90FLAGS = -g -fno-range-check F90LDFLAGS = -bind_at_load SOCFLAGS = -fPIC SOLDFLAGS = -shared -Wl,-rpath,$(INSTALLDIR)/lib JAVAINCLUDES = -I$(JDKDIR)/include -I$(JDKDIR)/include/linux LDPREFIX = LD_LIBRARY_PATH=$(SOLIB) EXTRALIBS = -lm -L$(HOME)/lib -ldmalloc M4FLAGS = -Dfcb_bytes_in_rec=131072 TIME = time DOWNLOAD = /sw/bin/wget ifneq ($(NOFORTRAN),) F90C = endif # # Directories # ROOT = . LIB = $(ROOT)/lib SOLIB = $(ROOT)/solib JCBF = $(ROOT)/jcbf JAVADIR = $(ROOT)/java BIN = $(ROOT)/bin SRC = $(ROOT)/src INCLUDE = $(ROOT)/include M4 = $(ROOT)/m4 PYCBF = $(ROOT)/pycbf EXAMPLES = $(ROOT)/examples DECTRIS_EXAMPLES = $(EXAMPLES)/dectris_cbf_template_test DOC = $(ROOT)/doc GRAPHICS = $(ROOT)/html_graphics DATADIRI = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Input DATADIRO = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Output DATADIRS = $(ROOT)/../CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only INSTALLDIR = $(HOME) # # URLs from which to retrieve the data directories # DATAURLBASE = http://downloads.sf.net/cbflib/ DATAURLI = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Input.tar.gz DATAURLO = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Output.tar.gz DATAURLS = $(DATAURLBASE)/CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz # # URLs from which to retrieve needed external package snapshots # REGEXURL = http://downloads.sf.net/cbflib/$(REGEX).tar.gz TIFFURL = http://downloads.sf.net/cbflib/$(TIFF).tar.gz # # Include directories # INCLUDES = -I$(INCLUDE) -I$(SRC) ###################################################################### # You should not need to make modifications below this line # ###################################################################### # # Suffixes of files to be used or built # .SUFFIXES: .c .o .f90 .m4 .m4.f90: m4 -P $(M4FLAGS) $< > $@ ifneq ($(F90C),) .f90.o: $(F90C) $(F90FLAGS) -c $< -o $@ endif # # Common dependencies # COMMONDEP = Makefile # # Source files # SOURCE = $(SRC)/cbf.c \ $(SRC)/cbf_alloc.c \ $(SRC)/cbf_ascii.c \ $(SRC)/cbf_binary.c \ $(SRC)/cbf_byte_offset.c \ $(SRC)/cbf_canonical.c \ $(SRC)/cbf_codes.c \ $(SRC)/cbf_compress.c \ $(SRC)/cbf_context.c \ $(SRC)/cbf_copy.c \ $(SRC)/cbf_file.c \ $(SRC)/cbf_getopt.c \ $(SRC)/cbf_lex.c \ $(SRC)/cbf_packed.c \ $(SRC)/cbf_predictor.c \ $(SRC)/cbf_read_binary.c \ $(SRC)/cbf_read_mime.c \ $(SRC)/cbf_simple.c \ $(SRC)/cbf_string.c \ $(SRC)/cbf_stx.c \ $(SRC)/cbf_tree.c \ $(SRC)/cbf_uncompressed.c \ $(SRC)/cbf_write.c \ $(SRC)/cbf_write_binary.c \ $(SRC)/cbf_ws.c \ $(SRC)/md5c.c F90SOURCE = $(SRC)/fcb_atol_wcnt.f90 \ $(SRC)/fcb_ci_strncmparr.f90 \ $(SRC)/fcb_exit_binary.f90 \ $(SRC)/fcb_nblen_array.f90 \ $(SRC)/fcb_next_binary.f90 \ $(SRC)/fcb_open_cifin.f90 \ $(SRC)/fcb_packed.f90 \ $(SRC)/fcb_read_bits.f90 \ $(SRC)/fcb_read_byte.f90 \ $(SRC)/fcb_read_image.f90 \ $(SRC)/fcb_read_line.f90 \ $(SRC)/fcb_read_xds_i2.f90 \ $(SRC)/fcb_skip_whitespace.f90 \ $(EXAMPLES)/test_fcb_read_image.f90 \ $(EXAMPLES)/test_xds_binary.f90 # # Header files # HEADERS = $(INCLUDE)/cbf.h \ $(INCLUDE)/cbf_alloc.h \ $(INCLUDE)/cbf_ascii.h \ $(INCLUDE)/cbf_binary.h \ $(INCLUDE)/cbf_byte_offset.h \ $(INCLUDE)/cbf_canonical.h \ $(INCLUDE)/cbf_codes.h \ $(INCLUDE)/cbf_compress.h \ $(INCLUDE)/cbf_context.h \ $(INCLUDE)/cbf_copy.h \ $(INCLUDE)/cbf_file.h \ $(INCLUDE)/cbf_getopt.h \ $(INCLUDE)/cbf_lex.h \ $(INCLUDE)/cbf_packed.h \ $(INCLUDE)/cbf_predictor.h \ $(INCLUDE)/cbf_read_binary.h \ $(INCLUDE)/cbf_read_mime.h \ $(INCLUDE)/cbf_simple.h \ $(INCLUDE)/cbf_string.h \ $(INCLUDE)/cbf_stx.h \ $(INCLUDE)/cbf_tree.h \ $(INCLUDE)/cbf_uncompressed.h \ $(INCLUDE)/cbf_write.h \ $(INCLUDE)/cbf_write_binary.h \ $(INCLUDE)/cbf_ws.h \ $(INCLUDE)/global.h \ $(INCLUDE)/cbff.h \ $(INCLUDE)/md5.h # # m4 macro files # M4FILES = $(M4)/fcblib_defines.m4 \ $(M4)/fcb_exit_binary.m4 \ $(M4)/fcb_next_binary.m4 \ $(M4)/fcb_open_cifin.m4 \ $(M4)/fcb_packed.m4 \ $(M4)/fcb_read_bits.m4 \ $(M4)/fcb_read_image.m4 \ $(M4)/fcb_read_xds_i2.m4 \ $(M4)/test_fcb_read_image.m4 \ $(M4)/test_xds_binary.m4 # # Documentation files # DOCUMENTS = $(DOC)/CBFlib.html \ $(DOC)/CBFlib.txt \ $(DOC)/CBFlib_NOTICES.html \ $(DOC)/CBFlib_NOTICES.txt \ $(DOC)/ChangeLog \ $(DOC)/ChangeLog.html \ $(DOC)/MANIFEST \ $(DOC)/gpl.txt $(DOC)/lgpl.txt # # HTML Graphics files # JPEGS = $(GRAPHICS)/CBFbackground.jpg \ $(GRAPHICS)/CBFbig.jpg \ $(GRAPHICS)/CBFbutton.jpg \ $(GRAPHICS)/cbflibbackground.jpg \ $(GRAPHICS)/cbflibbig.jpg \ $(GRAPHICS)/cbflibbutton.jpg \ $(GRAPHICS)/cifhome.jpg \ $(GRAPHICS)/iucrhome.jpg \ $(GRAPHICS)/noticeButton.jpg # # Default: instructions # default: @echo ' ' @echo '***************************************************************' @echo ' ' @echo ' PLEASE READ README and doc/CBFlib_NOTICES.txt' @echo ' ' @echo ' Before making the CBF library and example programs, check' @echo ' that the C compiler name and flags are correct:' @echo ' ' @echo ' The current values are:' @echo ' ' @echo ' $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG)' @echo ' ' @echo ' Before installing the CBF library and example programs, check' @echo ' that the install directory is correct:' @echo ' ' @echo ' The current value :' @echo ' ' @echo ' $(INSTALLDIR) ' @echo ' ' @echo ' To compile the CBF library and example programs type:' @echo ' ' @echo ' make clean' @echo ' make all' @echo ' ' @echo ' To compile the CBF library as a shared object library, type:' @echo ' ' @echo ' make shared' @echo ' ' @echo ' To compile the Java wrapper classes for CBF library, type:' @echo ' ' @echo ' make javawrapper' @echo ' ' @echo ' To run a set of tests type:' @echo ' ' @echo ' make tests' @echo ' ' @echo ' To run some java tests type:' @echo ' ' @echo ' make javatests' @echo ' ' @echo ' The tests assume that several data files are in the directories' @echo ' $(DATADIRI) and $(DATADIRO)' @echo ' ' @echo ' Alternatively tests can be run comparing MD5 signatures only by' @echo ' ' @echo ' make tests_sigs_only' @echo ' ' @echo ' These signature only tests save space and download time by' @echo ' assuming that input data files and the output signatures' @echo ' are in the directories' @echo ' $(DATADIRI) and $(DATADIRS)' @echo ' ' @echo ' These directory can be obtained from' @echo ' ' @echo ' $(DATAURLI) ' @echo ' $(DATAURLO) ' @echo ' $(DATAURLS) ' @echo ' ' @echo ' To clean up the directories type:' @echo ' ' @echo ' make clean' @echo ' ' @echo ' To install the library and binaries type:' @echo ' ' @echo ' make install' @echo ' ' @echo '***************************************************************' @echo ' ' # # Compile the library and examples # all:: $(BIN) $(SOURCE) $(F90SOURCE) $(HEADERS) \ symlinksdone $(REGEXDEP) \ $(LIB)/libcbf.a \ $(LIB)/libfcb.a \ $(LIB)/libimg.a \ $(BIN)/adscimg2cbf \ $(BIN)/cbf2adscimg \ $(BIN)/convert_image \ $(BIN)/convert_minicbf \ $(BIN)/sequence_match \ $(BIN)/arvai_test \ $(BIN)/makecbf \ $(BIN)/img2cif \ $(BIN)/adscimg2cbf \ $(BIN)/cif2cbf \ $(BIN)/testcell \ $(BIN)/cif2c \ $(BIN)/testreals \ $(BIN)/testflat \ $(BIN)/testflatpacked ifneq ($(F90C),) all:: $(BIN)/test_xds_binary \ $(BIN)/test_fcb_read_image endif shared: $(SOLIB)/libcbf.so $(SOLIB)/libfcb.so $(SOLIB)/libimg.so javawrapper: shared $(JCBF) $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf_wrap.so ifneq ($(CBFLIB_USE_PYCIFRW),) PYCIFRWDEF = -Dcbf_use_pycifrw=yes else PYCIFRWDEF = endif Makefiles: Makefile \ Makefile_LINUX \ Makefile_LINUX_64 \ Makefile_LINUX_gcc42 \ Makefile_LINUX_DMALLOC \ Makefile_LINUX_gcc42_DMALLOC \ Makefile_OSX \ Makefile_OSX_gcc42 \ Makefile_OSX_gcc42_DMALLOC \ Makefile_AIX \ Makefile_MINGW \ Makefile_IRIX_gcc Makefile_LINUX: $(M4)/Makefile.m4 -cp Makefile_LINUX Makefile_LINUX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX $(M4)/Makefile.m4 > Makefile_LINUX Makefile_LINUX_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_LINUX Makefile_LINUX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_DMALLOC $(M4)/Makefile.m4 > Makefile_LINUX_DMALLOC Makefile_LINUX_64: $(M4)/Makefile.m4 -cp Makefile_LINUX_64 Makefile_LINUX_64_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_64 $(M4)/Makefile.m4 > Makefile_LINUX_64 Makefile_LINUX_gcc42: $(M4)/Makefile.m4 -cp Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_gcc42 $(M4)/Makefile.m4 > Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_LINUX_gcc42 Makefile_LINUX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=LINUX_gcc42_DMALLOC $(M4)/Makefile.m4 > Makefile_LINUX_gcc42_DMALLOC Makefile_OSX: $(M4)/Makefile.m4 -cp Makefile_OSX Makefile_OSX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX $(M4)/Makefile.m4 > Makefile_OSX Makefile_OSX_gcc42: $(M4)/Makefile.m4 -cp Makefile_OSX_gcc42 Makefile_OSX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX_gcc42 $(M4)/Makefile.m4 > Makefile_OSX_gcc42 Makefile_OSX_gcc42_DMALLOC: $(M4)/Makefile.m4 -cp Makefile_OSX_gcc42 Makefile_OSX_gcc42_old m4 -P $(PYCIFRWDEF) -Dcbf_system=OSX_gcc42_DMALLOC $(M4)/Makefile.m4 > Makefile_OSX_gcc42_DMALLOC Makefile_AIX: $(M4)/Makefile.m4 -cp Makefile_AIX Makefile_AIX_old m4 -P $(PYCIFRWDEF) -Dcbf_system=AIX $(M4)/Makefile.m4 > Makefile_AIX Makefile_MINGW: $(M4)/Makefile.m4 -cp Makefile_MINGW Makefile_MINGW_old m4 -P $(PYCIFRWDEF) -Dcbf_system=MINGW $(M4)/Makefile.m4 > Makefile_MINGW Makefile_IRIX_gcc: $(M4)/Makefile.m4 -cp Makefile_IRIX_gcc Makefile_IRIX_gcc_old m4 -P $(PYCIFREDEF) -Dcbf_system=IRIX_gcc $(M4)/Makefile.m4 > Makefile_IRIX_gcc Makefile: $(M4)/Makefile.m4 -cp Makefile Makefile_old m4 -P $(PYCIFRWDEF) -Dcbf_system=default $(M4)/Makefile.m4 > Makefile symlinksdone: chmod a+x .symlinks chmod a+x .undosymlinks chmod a+x doc/.symlinks chmod a+x doc/.undosymlinks chmod a+x libtool/.symlinks chmod a+x libtool/.undosymlinks ./.symlinks $(SLFLAGS) touch symlinksdone install: all $(INSTALLDIR) $(INSTALLDIR)/lib $(INSTALLDIR)/bin \ $(INSTALLDIR)/include $(INSTALLDIR)/include/cbflib \ $(PYSOURCE) -chmod -R 755 $(INSTALLDIR)/include/cbflib -chmod 755 $(INSTALLDIR)/lib/libcbf.a -cp $(INSTALLDIR)/lib/libcbf.a $(INSTALLDIR)/lib/libcbf_old.a cp $(LIB)/libcbf.a $(INSTALLDIR)/lib/libcbf.a -cp $(INSTALLDIR)/lib/libimg.a $(INSTALLDIR)/lib/libimg_old.a cp $(LIB)/libimg.a $(INSTALLDIR)/lib/libimg.a -cp $(INSTALLDIR)/bin/adscimg2cbf $(INSTALLDIR)/bin/adscimg2cbf_old cp $(BIN)/adscimg2cbf $(INSTALLDIR)/bin/adscimg2cbf -cp $(INSTALLDIR)/bin/cbf2adscimg $(INSTALLDIR)/bin/cbf2adscimg_old cp $(BIN)/cbf2adscimg $(INSTALLDIR)/bin/cbf2adscimg -cp $(INSTALLDIR)/bin/convert_image $(INSTALLDIR)/bin/convert_image_old cp $(BIN)/convert_image $(INSTALLDIR)/bin/convert_image -cp $(INSTALLDIR)/bin/convert_minicbf $(INSTALLDIR)/bin/convert_minicbf_old cp $(BIN)/convert_minicbf $(INSTALLDIR)/bin/convert_minicbf -cp $(INSTALLDIR)/bin/makecbf $(INSTALLDIR)/bin/makecbf_old cp $(BIN)/makecbf $(INSTALLDIR)/bin/makecbf -cp $(INSTALLDIR)/bin/img2cif $(INSTALLDIR)/bin/img2cif_old cp $(BIN)/img2cif $(INSTALLDIR)/bin/img2cif -cp $(INSTALLDIR)/bin/cif2cbf $(INSTALLDIR)/bin/cif2cbf_old cp $(BIN)/cif2cbf $(INSTALLDIR)/bin/cif2cbf -cp $(INSTALLDIR)/bin/sequence_match $(INSTALLDIR)/bin/sequence_match_old cp $(BIN)/sequence_match $(INSTALLDIR)/bin/sequence_match -cp $(INSTALLDIR)/bin/arvai_test $(INSTALLDIR)/bin/arvai_test_old cp $(BIN)/arvai_test $(INSTALLDIR)/bin/arvai_test -cp $(INSTALLDIR)/bin/cif2c $(INSTALLDIR)/bin/cif2c_old cp $(BIN)/cif2c $(INSTALLDIR)/bin/cif2c -cp $(INSTALLDIR)/bin/testreals $(INSTALLDIR)/bin/testreals_old cp $(BIN)/testreals $(INSTALLDIR)/bin/testreals -cp $(INSTALLDIR)/bin/testflat $(INSTALLDIR)/bin/testflat_old cp $(BIN)/testflat $(INSTALLDIR)/bin/testflat -cp $(INSTALLDIR)/bin/testflatpacked $(INSTALLDIR)/bin/testflatpacked_old cp $(BIN)/testflatpacked $(INSTALLDIR)/bin/testflatpacked chmod -R 755 $(INSTALLDIR)/include/cbflib -rm -rf $(INSTALLDIR)/include/cbflib_old -cp -r $(INSTALLDIR)/include/cbflib $(INSTALLDIR)/include/cbflib_old -rm -rf $(INSTALLDIR)/include/cbflib cp -r $(INCLUDE) $(INSTALLDIR)/include/cbflib chmod 644 $(INSTALLDIR)/lib/libcbf.a chmod 755 $(INSTALLDIR)/bin/convert_image chmod 755 $(INSTALLDIR)/bin/convert_minicbf chmod 755 $(INSTALLDIR)/bin/makecbf chmod 755 $(INSTALLDIR)/bin/img2cif chmod 755 $(INSTALLDIR)/bin/cif2cbf chmod 755 $(INSTALLDIR)/bin/sequence_match chmod 755 $(INSTALLDIR)/bin/arvai_test chmod 755 $(INSTALLDIR)/bin/cif2c chmod 755 $(INSTALLDIR)/bin/testreals chmod 755 $(INSTALLDIR)/bin/testflat chmod 755 $(INSTALLDIR)/bin/testflatpacked chmod 644 $(INSTALLDIR)/include/cbflib/*.h # # REGEX # ifneq ($(REGEXDEP),) $(REGEXDEP): $(REGEX) (cd $(REGEX); ./configure; make install) endif $(REGEX): $(DOWNLOAD) $(REGEXURL) tar -xvf $(REGEX).tar.gz -rm $(REGEX).tar.gz # # TIFF # $(TIFF): $(DOWNLOAD) $(TIFFURL) tar -xvf $(TIFF).tar.gz -rm $(TIFF).tar.gz (cd $(TIFF); ./configure --prefix=$(TIFFPREFIX); make install) # # Directories # $(INSTALLDIR): mkdir -p $(INSTALLDIR) $(INSTALLDIR)/lib: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/lib $(INSTALLDIR)/bin: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/bin $(INSTALLDIR)/include: $(INSTALLDIR) mkdir -p $(INSTALLDIR)/include $(INSTALLDIR)/include/cbflib: $(INSTALLDIR)/include mkdir -p $(INSTALLDIR)/include/cbflib $(LIB): mkdir $@ $(BIN): mkdir $@ $(SOLIB): mkdir $@ $(JCBF): mkdir $@ # # Parser # $(SRC)/cbf_stx.c: $(SRC)/cbf.stx.y bison $(SRC)/cbf.stx.y -o $(SRC)/cbf.stx.tab.c -d mv $(SRC)/cbf.stx.tab.c $(SRC)/cbf_stx.c mv $(SRC)/cbf.stx.tab.h $(INCLUDE)/cbf_stx.h # # CBF library # $(LIB)/libcbf.a: $(SOURCE) $(HEADERS) $(COMMONDEP) $(LIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG) $(INCLUDES) $(WARNINGS) -c $(SOURCE) $(AR) cr $@ *.o mv *.o $(LIB) ifneq ($(RANLIB),) $(RANLIB) $@ endif $(SOLIB)/libcbf.so: $(SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(PYCIFRWFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(SOURCE) $(CC) -o $@ *.o $(SOLDFLAGS) $(EXTRALIBS) rm *.o # # IMG library # $(LIB)/libimg.a: $(EXAMPLES)/img.c $(HEADERS) $(COMMONDEP) $(LIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) -c $(EXAMPLES)/img.c $(AR) cr $@ img.o ifneq ($(RANLIB),) $(RANLIB) $@ endif rm img.o $(SOLIB)/libimg.so: $(SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) $(CC) $(CFLAGS) $(NOLLFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(EXAMPLES)/img.c $(CC) -o $@ img.o $(SOLDFLAGS) rm img.o # # CBF and IMG libraries # CBF_IMG_LIBS: $(LIB)/libcbf.a $(LIB)/libimg.a # # FCB library # $(LIB)/libfcb.a: $(F90SOURCE) $(COMMONDEP) $(LIB) ifneq ($(F90C),) $(F90C) $(F90FLAGS) -c $(F90SOURCE) $(AR) cr $@ *.o ifneq ($(RANLIB),) $(RANLIB) $@ endif rm *.o else echo "Define F90C to build $(LIB)/libfcb.a" endif $(SOLIB)/libfcb.so: $(F90SOURCE) $(HEADERS) $(COMMONDEP) $(SOLIB) ifneq ($(F90C),) $(F90C) $(F90FLAGS) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) -c $(F90SOURCE) $(F90C) $(F90FLAGS) -o $@ *.o $(SOLDFLAGS) rm *.o else echo "Define F90C to build $(SOLIB)/libfcb.so" endif # # Python bindings # $(PYCBF)/_pycbf.$(PYCBFEXT): $(PYCBF) $(LIB)/libcbf.a \ $(PYCBF)/$(SETUP_PY) \ $(LIB)/libfcb.a \ $(LIB)/libimg.a \ $(PYCBF)/pycbf.i \ $(PYCBF)/cbfhandlewrappers.i \ $(PYCBF)/cbfdetectorwrappers.i \ $(PYCBF)/cbfgenericwrappers.i \ $(PYCBF)/cbfgoniometerwrappers.i (cd $(PYCBF); python $(SETUP_PY) build $(PYCBFBOPT); cp build/lib.*/_pycbf.$(PYCBFEXT) .) $(PYCBF)/setup.py: $(M4)/setup_py.m4 (m4 -P -Dregexlib=NOREGEXLIB -Dregexlibdir=NOREGEXLIBDIR $(M4)/setup_py.m4 > $@) $(PYCBF)/setup_MINGW.py: m4/setup_py.m4 (m4 -P -Dregexlib=regex -Dregexlibdir=$(REGEXDIR) $(M4)/setup_py.m4 > $@) $(LIB)/_pycbf.$(PYCBFEXT): $(PYCBF)/_pycbf.$(PYCBFEXT) cp $(PYCBF)/_pycbf.$(PYCBFEXT) $(LIB)/_pycbf.$(PYCBFEXT) $(PYCBF)/pycbf.pdf: $(PYCBF)/pycbf.w (cd $(PYCBF); \ $(NUWEB) pycbf; \ latex pycbf; \ $(NUWEB) pycbf; \ latex pycbf; \ dvipdfm pycbf ) $(PYCBF)/CBFlib.txt: $(DOC)/CBFlib.html links -dump $(DOC)/CBFlib.html > $(PYCBF)/CBFlib.txt $(PYCBF)/cbfhandlewrappers.i \ $(PYCBF)/cbfdetectorwrappers.i \ $(PYCBF)/cbfgenericwrappers.i \ $(PYCBF)/cbfgoniometerwrappers.i: $(PYCBF)/CBFlib.txt $(PYCBF)/make_pycbf.py (cd $(PYCBF); python make_pycbf.py; $(PYSWIG) pycbf.i; python setup.py build) # # Java bindings # $(JCBF)/cbflib-$(VERSION).jar: $(JCBF) $(JCBF)/jcbf.i $(JSWIG) -I$(INCLUDE) -package org.iucr.cbflib -outdir $(JCBF) $(JCBF)/jcbf.i $(JAVAC) -d . $(JCBF)/*.java $(JAR) cf $@ org $(SOLIB)/libcbf_wrap.so: $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf.so $(CC) $(CFLAGS) $(NOLLFLAG) $(SOCFLAGS) $(INCLUDES) $(WARNINGS) $(JAVAINCLUDES) -c $(JCBF)/jcbf_wrap.c $(CC) -o $@ jcbf_wrap.o $(SOLDFLAGS) -L$(SOLIB) -lcbf rm jcbf_wrap.o # # F90SOURCE # $(SRC)/fcb_exit_binary.f90: $(M4)/fcb_exit_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_exit_binary.m4) > $(SRC)/fcb_exit_binary.f90 $(SRC)/fcb_next_binary.f90: $(M4)/fcb_next_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_next_binary.m4) > $(SRC)/fcb_next_binary.f90 $(SRC)/fcb_open_cifin.f90: $(M4)/fcb_open_cifin.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_open_cifin.m4) > $(SRC)/fcb_open_cifin.f90 $(SRC)/fcb_packed.f90: $(M4)/fcb_packed.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_packed.m4) > $(SRC)/fcb_packed.f90 $(SRC)/fcb_read_bits.f90: $(M4)/fcb_read_bits.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_bits.m4) > $(SRC)/fcb_read_bits.f90 $(SRC)/fcb_read_image.f90: $(M4)/fcb_read_image.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_image.m4) > $(SRC)/fcb_read_image.f90 $(SRC)/fcb_read_xds_i2.f90: $(M4)/fcb_read_xds_i2.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) fcb_read_xds_i2.m4) > $(SRC)/fcb_read_xds_i2.f90 $(EXAMPLES)/test_fcb_read_image.f90: $(M4)/test_fcb_read_image.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) test_fcb_read_image.m4) > $(EXAMPLES)/test_fcb_read_image.f90 $(EXAMPLES)/test_xds_binary.f90: $(M4)/test_xds_binary.m4 $(M4)/fcblib_defines.m4 (cd $(M4); m4 -P $(M4FLAGS) test_xds_binary.m4) > $(EXAMPLES)/test_xds_binary.f90 # # convert_image example program # $(BIN)/convert_image: $(LIB)/libcbf.a $(EXAMPLES)/convert_image.c $(EXAMPLES)/img.c \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/convert_image.c $(EXAMPLES)/img.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # convert_minicbf example program # $(BIN)/convert_minicbf: $(LIB)/libcbf.a $(EXAMPLES)/convert_minicbf.c \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/convert_minicbf.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # makecbf example program # $(BIN)/makecbf: $(LIB)/libcbf.a $(EXAMPLES)/makecbf.c $(LIB)/libimg.a $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/makecbf.c -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # adscimg2cbf example program # $(BIN)/adscimg2cbf: $(LIB)/libcbf.a $(EXAMPLES)/adscimg2cbf.c $(EXAMPLES)/adscimg2cbf_sub.c $(CC) $(CFLAGS) $(NOLLFLAG) -D_SVID_SOURCE $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/adscimg2cbf.c $(EXAMPLES)/adscimg2cbf_sub.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # cbf2adscimg example program # $(BIN)/cbf2adscimg: $(LIB)/libcbf.a $(EXAMPLES)/cbf2adscimg.c $(EXAMPLES)/cbf2adscimg_sub.c $(CC) $(CFLAGS) $(NOLLFLAG) -D_SVID_SOURCE $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cbf2adscimg.c $(EXAMPLES)/cbf2adscimg_sub.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # changtestcompression example program # $(BIN)/changtestcompression: $(LIB)/libcbf.a $(EXAMPLES)/changtestcompression.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/changtestcompression.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # img2cif example program # $(BIN)/img2cif: $(LIB)/libcbf.a $(EXAMPLES)/img2cif.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOTPINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/img2cif.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # cif2cbf example program # $(BIN)/cif2cbf: $(LIB)/libcbf.a $(EXAMPLES)/cif2cbf.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cif2cbf.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # dectris cbf_template_t program # $(BIN)/cbf_template_t: $(DECTRIS_EXAMPLES)/cbf_template_t.c \ $(DECTRIS_EXAMPLES)/mx_cbf_t_extras.h \ $(DECTRIS_EXAMPLES)/mx_parms.h $(CC) $(CFLAGS) $(NOLLFLAG) -I $(DECTRIS_EXAMPLES) $(WARNINGS) \ $(DECTRIS_EXAMPLES)/cbf_template_t.c -o $@ # # testcell example program # $(BIN)/testcell: $(LIB)/libcbf.a $(EXAMPLES)/testcell.C $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testcell.C -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # cif2c example program # $(BIN)/cif2c: $(LIB)/libcbf.a $(EXAMPLES)/cif2c.c $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/cif2c.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # sauter_test example program # $(BIN)/sauter_test: $(LIB)/libcbf.a $(EXAMPLES)/sauter_test.C $(C++) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/sauter_test.C -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # sequence_match example program # $(BIN)/sequence_match: $(LIB)/libcbf.a $(EXAMPLES)/sequence_match.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/sequence_match.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # tiff2cbf example program # $(BIN)/tiff2cbf: $(LIB)/libcbf.a $(EXAMPLES)/tiff2cbf.c \ $(GOPTLIB) $(GOPTINC) $(TIFF) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ -I$(TIFFPREFIX)/include $(EXAMPLES)/tiff2cbf.c $(GOPTLIB) -L$(LIB) \ -lcbf -L$(TIFFPREFIX)/lib -ltiff $(EXTRALIBS) -limg -o $@ # # Andy Arvai's buffered read test program # $(BIN)/arvai_test: $(LIB)/libcbf.a $(EXAMPLES)/arvai_test.c $(LIB)/libimg.a \ $(GOPTLIB) $(GOPTINC) $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/arvai_test.c $(GOPTLIB) -L$(LIB) \ -lcbf $(EXTRALIBS) -limg -o $@ # # testreals example program # $(BIN)/testreals: $(LIB)/libcbf.a $(EXAMPLES)/testreals.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testreals.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testflat example program # $(BIN)/testflat: $(LIB)/libcbf.a $(EXAMPLES)/testflat.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testflat.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testflatpacked example program # $(BIN)/testflatpacked: $(LIB)/libcbf.a $(EXAMPLES)/testflatpacked.c $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testflatpacked.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ ifneq ($(F90C),) # # test_xds_binary example program # $(BIN)/test_xds_binary: $(LIB)/libfcb.a $(EXAMPLES)/test_xds_binary.f90 $(F90C) $(F90FLAGS) $(F90LDFLAGS) $(EXAMPLES)/test_xds_binary.f90 \ -L$(LIB) -lfcb -o $@ # # test_fcb_read_image example program # $(BIN)/test_fcb_read_image: $(LIB)/libfcb.a $(EXAMPLES)/test_fcb_read_image.f90 $(F90C) $(F90FLAGS) $(F90LDFLAGS) $(EXAMPLES)/test_fcb_read_image.f90 \ -L$(LIB) -lfcb -o $@ endif # # testcbf (C) # $(BIN)/ctestcbf: $(EXAMPLES)/testcbf.c $(LIB)/libcbf.a $(CC) $(CFLAGS) $(NOLLFLAG) $(INCLUDES) $(WARNINGS) \ $(EXAMPLES)/testcbf.c -L$(LIB) \ -lcbf $(EXTRALIBS) -o $@ # # testcbf (Java) # $(BIN)/testcbf.class: $(EXAMPLES)/testcbf.java $(JCBF)/cbflib-$(VERSION).jar $(SOLIB)/libcbf_wrap.so $(JAVAC) -cp $(JCBF)/cbflib-$(VERSION).jar -d $(BIN) $(EXAMPLES)/testcbf.java # # Data files for tests # $(DATADIRI): (cd ..; $(DOWNLOAD) $(DATAURLI)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Input.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Input.tar.gz) $(DATADIRO): (cd ..; $(DOWNLOAD) $(DATAURLO)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Output.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Output.tar.gz) $(DATADIRS): (cd ..; $(DOWNLOAD) $(DATAURLS)) (cd ..; tar -zxvf CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz) -(cd ..; rm CBFlib_$(VERSION)_Data_Files_Output_Sigs_Only.tar.gz) # Input Data Files TESTINPUT_BASIC = example.mar2300 DATADIRI_INPUT_BASIC = $(DATADIRI)/example.mar2300$(CEXT) TESTINPUT_EXTRA = 9ins.cif mb_LP_1_001.img insulin_pilatus6m.cbf testrealin.cbf \ testflatin.cbf testflatpackedin.cbf XRD1621.tif DATADIRI_INPUT_EXTRA = $(DATADIRI)/9ins.cif$(CEXT) $(DATADIRI)/mb_LP_1_001.img$(CEXT) \ $(DATADIRI)/insulin_pilatus6m.cbf$(CEXT) $(DATADIRI)/testrealin.cbf$(CEXT) \ $(DATADIRI)/testflatin.cbf$(CEXT) $(DATADIRI)/testflatpackedin.cbf$(CEXT) \ $(DATADIRI)/XRD1621.tif$(CEXT) # Output Data Files TESTOUTPUT = adscconverted_flat_orig.cbf \ adscconverted_orig.cbf converted_flat_orig.cbf converted_orig.cbf \ insulin_pilatus6mconverted_orig.cbf \ mb_LP_1_001_orig.cbf testcell_orig.prt \ test_xds_bin_testflatout_orig.out \ test_xds_bin_testflatpackedout_orig.out test_fcb_read_testflatout_orig.out \ test_fcb_read_testflatpackedout_orig.out \ XRD1621_orig.cbf XRD1621_I4encbC100_orig.cbf NEWTESTOUTPUT = adscconverted_flat.cbf \ adscconverted.cbf converted_flat.cbf converted.cbf \ insulin_pilatus6mconverted.cbf \ mb_LP_1_001.cbf testcell.prt \ test_xds_bin_testflatout.out \ test_xds_bin_testflatpackedout.out test_fcb_read_testflatout.out \ test_fcb_read_testflatpackedout.out \ XRD1621.cbf XRD1621_I4encbC100.cbf DATADIRO_OUTPUT = $(DATADIRO)/adscconverted_flat_orig.cbf$(CEXT) \ $(DATADIRO)/adscconverted_orig.cbf$(CEXT) \ $(DATADIRO)/converted_flat_orig.cbf$(CEXT) \ $(DATADIRO)/converted_orig.cbf$(CEXT) \ $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(CEXT) \ $(DATADIRO)/mb_LP_1_001_orig.cbf$(CEXT) \ $(DATADIRO)/testcell_orig.prt$(CEXT) \ $(DATADIRO)/test_xds_bin_testflatout_orig.out$(CEXT) \ $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(CEXT) \ $(DATADIRO)/test_fcb_read_testflatout_orig.out$(CEXT) \ $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(CEXT) \ $(DATADIRO)/XRD1621_orig.cbf$(CEXT) \ $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(CEXT) DATADIRO_OUTPUT_SIGNATURES = $(DATADIRO)/adscconverted_flat_orig.cbf$(SEXT) \ $(DATADIRO)/adscconverted_orig.cbf$(SEXT) \ $(DATADIRO)/converted_flat_orig.cbf$(SEXT) \ $(DATADIRO)/converted_orig.cbf$(SEXT) \ $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(SEXT) \ $(DATADIRO)/mb_LP_1_001_orig.cbf$(SEXT) \ $(DATADIRO)/testcell_orig.prt$(SEXT) \ $(DATADIRO)/test_xds_bin_testflatout_orig.out$(SEXT) \ $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(SEXT) \ $(DATADIRO)/test_fcb_read_testflatout_orig.out$(SEXT) \ $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(SEXT) \ $(DATADIRO)/XRD1621_orig.cbf$(SEXT) \ $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(SEXT) # Output Data File Signatures TESTOUTPUTSIGS = adscconverted_flat_orig.cbf$(SEXT) \ adscconverted_orig.cbf$(SEXT) converted_flat_orig.cbf$(SEXT) converted_orig.cbf$(SEXT) \ insulin_pilatus6mconverted_orig.cbf$(SEXT) \ mb_LP_1_001_orig.cbf$(SEXT) testcell_orig.prt$(SEXT) \ test_xds_bin_testflatout_orig.out$(SEXT) \ test_xds_bin_testflatpackedout_orig.out$(SEXT) test_fcb_read_testflatout_orig.out$(SEXT) \ test_fcb_read_testflatpackedout_orig.out$(SEXT) \ XRD1621_orig.cbf$(SEXT) DATADIRS_OUTPUT_SIGNATURES = $(DATADIRS)/adscconverted_flat_orig.cbf$(SEXT) \ $(DATADIRS)/adscconverted_orig.cbf$(SEXT) \ $(DATADIRS)/converted_flat_orig.cbf$(SEXT) \ $(DATADIRS)/converted_orig.cbf$(SEXT) \ $(DATADIRS)/insulin_pilatus6mconverted_orig.cbf$(SEXT) \ $(DATADIRS)/mb_LP_1_001_orig.cbf$(SEXT) \ $(DATADIRS)/testcell_orig.prt$(SEXT) \ $(DATADIRS)/test_xds_bin_testflatout_orig.out$(SEXT) \ $(DATADIRS)/test_xds_bin_testflatpackedout_orig.out$(SEXT) \ $(DATADIRS)/test_fcb_read_testflatout_orig.out$(SEXT) \ $(DATADIRS)/test_fcb_read_testflatpackedout_orig.out$(SEXT) \ $(DATADIRS)/XRD1621_orig.cbf$(SEXT) \ $(DATADIRS)/XRD1621_I4encbC100_orig.cbf$(SEXT) # Fetch Input Data Files $(TESTINPUT_BASIC): $(DATADIRI) $(DATADIRI_INPUT_BASIC) $(DECOMPRESS) < $(DATADIRI)/$@$(CEXT) > $@ cp $(DATADIRI)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) $(TESTINPUT_EXTRA): $(DATADIRI) $(DATADIRI_INPUT_EXTRA) $(DECOMPRESS) < $(DATADIRI)/$@$(CEXT) > $@ cp $(DATADIRI)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) # Fetch Output Data Files and Signatures $(TESTOUTPUT): $(DATADIRO) $(DATADIRO_OUTPUT) $(DATADIRO_OUTPUT_SIGNATURES) $(DECOMPRESS) < $(DATADIRO)/$@$(CEXT) > $@ cp $(DATADIRO)/$@$(SEXT) $@$(SEXT) -$(SIGNATURE) < $@ | $(DIFF) - $@$(SEXT) # Fetch Output Data File Signatures $(TESTOUTPUTSIGS): $(DATADIRS) $(DATADIRS_OUTPUT_SIGNATURES) cp $(DATADIRS)/$@ $@ # # Tests # tests: $(LIB) $(BIN) symlinksdone basic extra dectristests pycbftests tests_sigs_only: $(LIB) $(BIN) symlinksdone basic extra_sigs_only restore_output: $(NEWTESTOUTPUT) $(DATADIRO) $(SIGNATURE) < adscconverted_flat.cbf > $(DATADIRO)/adscconverted_flat_orig.cbf$(SEXT) $(SIGNATURE) < adscconverted.cbf > $(DATADIRO)/adscconverted_orig.cbf$(SEXT) $(SIGNATURE) < converted_flat.cbf > $(DATADIRO)/converted_flat_orig.cbf$(SEXT) $(SIGNATURE) < converted.cbf > $(DATADIRO)/converted_orig.cbf$(SEXT) $(SIGNATURE) < insulin_pilatus6mconverted.cbf > $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(SEXT) $(SIGNATURE) < mb_LP_1_001.cbf$ > $(DATADIRO)/mb_LP_1_001_orig.cbf$(SEXT) $(SIGNATURE) < testcell.prt > $(DATADIRO)/testcell_orig.prt$(SEXT) $(SIGNATURE) < test_xds_bin_testflatout.out > $(DATADIRO)/test_xds_bin_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_xds_bin_testflatpackedout.out > $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatout.out > $(DATADIRO)/test_fcb_read_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatpackedout.out > $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < XRD1621.cbf > $(DATADIRO)/XRD1621_orig.cbf$(SEXT) $(SIGNATURE) < XRD1621_I4encbC100.cbf > $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(SEXT) $(COMPRESS) < adscconverted_flat.cbf > $(DATADIRO)/adscconverted_flat_orig.cbf$(CEXT) $(COMPRESS) < adscconverted.cbf > $(DATADIRO)/adscconverted_orig.cbf$(CEXT) $(COMPRESS) < converted_flat.cbf > $(DATADIRO)/converted_flat_orig.cbf$(CEXT) $(COMPRESS) < converted.cbf > $(DATADIRO)/converted_orig.cbf$(CEXT) $(COMPRESS) < insulin_pilatus6mconverted.cbf > $(DATADIRO)/insulin_pilatus6mconverted_orig.cbf$(CEXT) $(COMPRESS) < mb_LP_1_001.cbf$ > $(DATADIRO)/mb_LP_1_001_orig.cbf$(CEXT) $(COMPRESS) < testcell.prt > $(DATADIRO)/testcell_orig.prt$(CEXT) $(COMPRESS) < test_xds_bin_testflatout.out > $(DATADIRO)/test_xds_bin_testflatout_orig.out$(CEXT) $(COMPRESS) < test_xds_bin_testflatpackedout.out > $(DATADIRO)/test_xds_bin_testflatpackedout_orig.out$(CEXT) $(COMPRESS) < test_fcb_read_testflatout.out > $(DATADIRO)/test_fcb_read_testflatout_orig.out$(CEXT) $(COMPRESS) < test_fcb_read_testflatpackedout.out > $(DATADIRO)/test_fcb_read_testflatpackedout_orig.out$(CEXT) $(COMPRESS) < XRD1621.cbf > $(DATADIRO)/XRD1621_orig.cbf$(CEXT) $(COMPRESS) < XRD1621_I4encbC100.cbf > $(DATADIRO)/XRD1621_I4encbC100_orig.cbf$(CEXT) restore_sigs_only: $(NEWTESTOUTPUT) $(DATADIRS) $(SIGNATURE) < adscconverted_flat.cbf > $(DATADIRS)/adscconverted_flat_orig.cbf$(SEXT) $(SIGNATURE) < adscconverted.cbf > $(DATADIRS)/adscconverted_orig.cbf$(SEXT) $(SIGNATURE) < converted_flat.cbf > $(DATADIRS)/converted_flat_orig.cbf$(SEXT) $(SIGNATURE) < converted.cbf > $(DATADIRS)/converted_orig.cbf$(SEXT) $(SIGNATURE) < insulin_pilatus6mconverted.cbf > $(DATADIRS)/insulin_pilatus6mconverted_orig.cbf$(SEXT) $(SIGNATURE) < mb_LP_1_001.cbf$ > $(DATADIRS)/mb_LP_1_001_orig.cbf$(SEXT) $(SIGNATURE) < testcell.prt > $(DATADIRS)/testcell_orig.prt$(SEXT) $(SIGNATURE) < test_xds_bin_testflatout.out > $(DATADIRS)/test_xds_bin_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_xds_bin_testflatpackedout.out > $(DATADIRS)/test_xds_bin_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatout.out > $(DATADIRS)/test_fcb_read_testflatout_orig.out$(SEXT) $(SIGNATURE) < test_fcb_read_testflatpackedout.out > $(DATADIRS)/test_fcb_read_testflatpackedout_orig.out$(SEXT) $(SIGNATURE) < XRD1621.cbf > $(DATADIRS)/XRD1621_orig.cbf$(SEXT) $(SIGNATURE) < XRD1621_I4encbC100.cbf > $(DATADIRS)/XRD1621_I4encbC100_orig.cbf$(SEXT) restore_signatures: restore_output restore_sigs_only # # Basic Tests # basic: $(BIN)/makecbf $(BIN)/img2cif $(BIN)/cif2cbf $(TESTINPUT_BASIC) $(BIN)/makecbf example.mar2300 makecbf.cbf $(BIN)/img2cif -c flatpacked -m headers -d digest \ -e base64 example.mar2300 img2cif_packed.cif $(BIN)/img2cif -c canonical -m headers -d digest \ -e base64 example.mar2300 img2cif_canonical.cif $(BIN)/img2cif -c flatpacked -m headers -d digest \ -e none example.mar2300 img2cif_packed.cbf $(BIN)/img2cif -c canonical -m headers -d digest \ -e none example.mar2300 img2cif_canonical.cbf $(BIN)/cif2cbf -e none -c flatpacked \ img2cif_canonical.cif cif2cbf_packed.cbf $(BIN)/cif2cbf -e none -c canonical \ img2cif_packed.cif cif2cbf_canonical.cbf -cmp cif2cbf_packed.cbf makecbf.cbf -cmp cif2cbf_packed.cbf img2cif_packed.cbf -cmp cif2cbf_canonical.cbf img2cif_canonical.cbf # # Extra Tests # ifneq ($(F90C),) extra: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/test_xds_binary $(BIN)/test_fcb_read_image $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg \ $(BIN)/changtestcompression $(BIN)/tiff2cbf \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUT) else extra: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUT) endif $(TIME) $(BIN)/cif2cbf -e hex -c none \ makecbf.cbf cif2cbf_ehcn.cif $(TIME) $(BIN)/cif2cbf -e none -c flatpacked \ cif2cbf_ehcn.cif cif2cbf_encp.cbf; rm cif2cbf_ehcn.cif -cmp makecbf.cbf cif2cbf_encp.cbf $(TIME) $(BIN)/cif2cbf -i 9ins.cif -o 9ins.cbf -cmp 9ins.cif 9ins.cbf $(TIME) $(BIN)/convert_image -F example.mar2300 converted_flat.cbf -cmp converted_flat.cbf converted_flat_orig.cbf $(TIME) $(BIN)/convert_image example.mar2300 converted.cbf -cmp converted.cbf converted_orig.cbf -$(TIME) $(BIN)/testcell < testcell.dat > testcell.prt -cmp testcell.prt testcell_orig.prt $(TIME) $(BIN)/convert_image -F -d adscquantum315 mb_LP_1_001.img adscconverted_flat.cbf -cmp adscconverted_flat.cbf adscconverted_flat_orig.cbf $(TIME) $(BIN)/convert_image -d adscquantum315 mb_LP_1_001.img adscconverted.cbf -cmp adscconverted.cbf adscconverted_orig.cbf $(TIME) $(BIN)/adscimg2cbf --no_pad --cbf_packed,flat mb_LP_1_001.img -cmp mb_LP_1_001.cbf mb_LP_1_001_orig.cbf ifneq ($(CLEANTESTS),) mv mb_LP_1_001.cbf nmb_LP_1_001.cbf else cp mb_LP_1_001.cbf nmb_LP_1_001.cbf endif $(TIME) $(BIN)/cbf2adscimg nmb_LP_1_001.cbf -cmp nmb_LP_1_001.img mb_LP_1_001.img rm nmb_LP_1_001.cbf ifneq ($(CLEANTESTS),) rm nmb_LP_1_001.img endif $(TIME) $(BIN)/convert_minicbf -d pilatus6m insulin_pilatus6m.cbf insulin_pilatus6mconverted.cbf -cmp insulin_pilatus6mconverted.cbf insulin_pilatus6mconverted_orig.cbf $(TIME) $(BIN)/testreals -cmp testrealin.cbf testrealout.cbf $(TIME) $(BIN)/testflat -cmp testflatin.cbf testflatout.cbf $(TIME) $(BIN)/testflatpacked -cmp testflatpackedin.cbf testflatpackedout.cbf ifneq ($(F90C),) echo testflatout.cbf | $(TIME) $(BIN)/test_xds_binary > test_xds_bin_testflatout.out -$(DIFF) test_xds_bin_testflatout.out test_xds_bin_testflatout_orig.out echo testflatpackedout.cbf | $(TIME) $(BIN)/test_xds_binary > test_xds_bin_testflatpackedout.out -$(DIFF) test_xds_bin_testflatpackedout.out test_xds_bin_testflatpackedout_orig.out echo testflatout.cbf | $(TIME) $(BIN)/test_fcb_read_image > test_fcb_read_testflatout.out -$(DIFF) test_fcb_read_testflatout.out test_fcb_read_testflatout_orig.out echo testflatpackedout.cbf | $(TIME) $(BIN)/test_fcb_read_image > test_fcb_read_testflatpackedout.out -$(DIFF) test_fcb_read_testflatpackedout.out test_fcb_read_testflatpackedout_orig.out endif $(TIME) $(BIN)/sauter_test $(TIME) $(BIN)/changtestcompression $(TIME) (export LD_LIBRARY_PATH=$(LIB);$(BIN)/tiff2cbf XRD1621.tif XRD1621.cbf) -$(DIFF) XRD1621.cbf XRD1621_orig.cbf $(TIME) $(BIN)/cif2cbf -I 4 -C 100. -L 0. -e n -c b -i XRD1621.cbf -o XRD1621_I4encbC100.cbf -$(DIFF) XRD1621_I4encbC100.cbf XRD1621_I4encbC100_orig.cbf ifneq ($(F90C),) extra_sigs_only: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/test_xds_binary $(BIN)/test_fcb_read_image $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf $(BIN)/cbf2adscimg $(BIN)/tiff2cbf \ basic $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) else extra_sigs_only: $(BIN)/convert_image $(BIN)/convert_minicbf $(BIN)/cif2cbf $(BIN)/testcell \ $(BIN)/testreals $(BIN)/testflat $(BIN)/testflatpacked \ $(BIN)/convert_minicbf \ $(BIN)/sauter_test $(BIN)/adscimg2cbf\ basic $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) endif $(TIME) $(BIN)/cif2cbf -e hex -c none \ makecbf.cbf cif2cbf_ehcn.cif $(TIME) $(BIN)/cif2cbf -e none -c packed \ cif2cbf_ehcn.cif cif2cbf_encp.cbf; rm cif2cbf_ehcn.cif -cmp makecbf.cbf cif2cbf_encp.cbf $(TIME) $(BIN)/cif2cbf -i 9ins.cif -o 9ins.cbf -cmp 9ins.cif 9ins.cbf $(TIME) $(BIN)/convert_image -F example.mar2300 converted_flat.cbf -$(SIGNATURE) < converted_flat.cbf | $(DIFF) - converted_flat_orig.cbf$(SEXT); rm converted_flat.cbf $(TIME) $(BIN)/convert_image example.mar2300 converted.cbf -$(SIGNATURE) < converted.cbf | $(DIFF) - converted_orig.cbf$(SEXT); rm converted.cbf -$(TIME) $(BIN)/testcell < testcell.dat | \ $(SIGNATURE) | $(DIFF) - testcell_orig.prt$(SEXT) $(TIME) $(BIN)/convert_image -F -d adscquantum315 mb_LP_1_001.img adscconverted_flat.cbf -$(SIGNATURE) < adscconverted_flat.cbf | $(DIFF) - adscconverted_flat_orig.cbf$(SEXT) $(TIME) $(BIN)/convert_image -d adscquantum315 mb_LP_1_001.img adscconverted.cbf -$(SIGNATURE) < adscconverted.cbf | $(DIFF) - adscconverted_orig.cbf$(SEXT); rm adscconverted.cbf $(TIME) $(BIN)/adscimg2cbf --cbf_packed,flat mb_LP_1_001.img -$(SIGNATURE) < mb_LP_1_001.cbf | $(DIFF) - mb_LP_1_001_orig.cbf$(SEXT) mv mb_LP_1_001.cbf nmb_LP_1_001.cbf $(TIME) $(BIN)/cbf2adscimg nmb_LP_1_001.cbf -cmp nmb_LP_1_001.img mb_LP_1_001.img rm nmb_LP_1_001.cbf rm nmb_LP_1_001.img $(TIME) $(BIN)/convert_minicbf -d pilatus6m insulin_pilatus6m.cbf insulin_pilatus6mconverted.cbf -$(SIGNATURE) < insulin_pilatus6mconverted.cbf | $(DIFF) - insulin_pilatus6mconverted_orig.cbf$(SEXT); rm insulin_pilatus6mconverted.cbf $(TIME) $(BIN)/testreals -cmp testrealin.cbf testrealout.cbf $(TIME) $(BIN)/testflat -cmp testflatin.cbf testflatout.cbf $(TIME) $(BIN)/testflatpacked -cmp testflatpackedin.cbf testflatpackedout.cbf ifneq ($(F90C),) echo testflatout.cbf | $(TIME) $(BIN)/test_xds_binary | \ $(SIGNATURE) | $(DIFF) - test_xds_bin_testflatout_orig.out$(SEXT) echo testflatpackedout.cbf | $(TIME) $(BIN)/test_xds_binary | \ $(SIGNATURE) | $(DIFF) - test_xds_bin_testflatpackedout_orig.out$(SEXT) echo testflatout.cbf | $(TIME) $(BIN)/test_fcb_read_image | \ $(SIGNATURE) | $(DIFF) - test_fcb_read_testflatout_orig.out$(SEXT) echo testflatpackedout.cbf | $(TIME) $(BIN)/test_fcb_read_image | \ $(SIGNATURE) | $(DIFF) - test_fcb_read_testflatpackedout_orig.out$(SEXT) endif $(TIME) $(BIN)/sauter_test $(TIME) $(BIN)/tiff2cbf XRD1621.tif XRD1621.cbf $(TIME) $(BIN)/cif2cbf -I 4 -C 100. -L 0. -e n -c b -i XRD1621.cbf -o XRD1621_I4encbC100.cbf -$(SIGNATURE) < XRD1621.cbf | $(DIFF) - XRD1621_orig.cbf$(SEXT); rm XRD1621.cbf -$(SIGNATURE) < XRD1621_I4encbC100.cbf | $(DIFF) - XRD1621_I4encbC100_orig.cbf$(SEXT); rm XRD1621_I4encbC100.cbf @-rm -f adscconverted_flat.cbf @-rm -f $(TESTINPUT_BASIC) $(TESTINPUT_EXTRA) $(TESTOUTPUTSIGS) @-rm -f cif2cbf_packed.cbf makecbf.cbf \ cif2cbf_packed.cbf img2cif_packed.cbf \ cif2cbf_canonical.cbf img2cif_canonical.cbf @-rm -f testrealout.cbf testflatout.cbf testflatpackedout.cbf \ cif2cbf_encp.cbf img2cif_canonical.cif img2cif_packed.cif 9ins.cbf pycbftests: $(PYCBF)/_pycbf.$(PYCBFEXT) (cd $(PYCBF); python pycbf_test1.py) (cd $(PYCBF); python pycbf_test2.py) (cd $(PYCBF); python pycbf_test3.py) javatests: $(BIN)/ctestcbf $(BIN)/testcbf.class $(SOLIB)/libcbf_wrap.so $(BIN)/ctestcbf > testcbfc.txt $(LDPREFIX) java -cp $(JCBF)/cbflib-$(VERSION).jar:$(BIN) testcbf > testcbfj.txt $(DIFF) testcbfc.txt testcbfj.txt dectristests: $(BIN)/cbf_template_t $(DECTRIS_EXAMPLES)/cbf_test_orig.out (cd $(DECTRIS_EXAMPLES); ../../bin/cbf_template_t; diff -a -u cbf_test_orig.out cbf_template_t.out) # # Remove all non-source files # empty: @-rm -f $(LIB)/*.o @-rm -f $(LIB)/libcbf.a @-rm -f $(LIB)/libfcb.a @-rm -f $(LIB)/libimg.a @-rm -f $(LIB)/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/build/*/_pycbf.$(PYCBFEXT) @-rm -f $(PYCBF)/build/src/cbf_simple.o @-rm -f $(PYCBF)/build/*/pycbf_wrap.o @-rm -rf $(BIN)/adscimg2cbf* @-rm -rf $(BIN)/cbf2adscimg* @-rm -rf $(BIN)/makecbf* @-rm -rf $(BIN)/img2cif* @-rm -rf $(BIN)/cif2cbf* @-rm -rf $(BIN)/convert_image* @-rm -rf $(BIN)/convert_minicbf* @-rm -rf $(BIN)/test_fcb_read_image* @-rm -rf $(BIN)/test_xds_binary* @-rm -rf $(BIN)/testcell* @-rm -rf $(BIN)/cif2c* @-rm -rf $(BIN)/testreals* @-rm -rf $(BIN)/testflat* @-rm -rf $(BIN)/testflatpacked* @-rm -rf $(BIN)/cbf_template_t* @-rm -rf $(BIN)/sauter_test* @-rm -rf $(BIN)/arvai_test* @-rm -rf $(BIN)/changtestcompression* @-rm -rf $(BIN)/tiff2cbf* @-rm -f makecbf.cbf @-rm -f img2cif_packed.cif @-rm -f img2cif_canonical.cif @-rm -f img2cif_packed.cbf @-rm -f img2cif_canonical.cbf @-rm -f img2cif_raw.cbf @-rm -f cif2cbf_packed.cbf @-rm -f cif2cbf_canonical.cbf @-rm -f converted.cbf @-rm -f adscconverted.cbf @-rm -f converted_flat.cbf @-rm -f adscconverted_flat.cbf @-rm -f adscconverted_flat_rev.cbf @-rm -f mb_LP_1_001.cbf @-rm -f cif2cbf_ehcn.cif @-rm -f cif2cbf_encp.cbf @-rm -f 9ins.cbf @-rm -f 9ins.cif @-rm -f testcell.prt @-rm -f example.mar2300 @-rm -f converted_orig.cbf @-rm -f adscconverted_orig.cbf @-rm -f converted_flat_orig.cbf @-rm -f adscconverted_flat_orig.cbf @-rm -f adscconverted_flat_rev_orig.cbf @-rm -f mb_LP_1_001_orig.cbf @-rm -f insulin_pilatus6mconverted_orig.cbf @-rm -f insulin_pilatus6mconverted.cbf @-rm -f insulin_pilatus6m.cbf @-rm -f testrealin.cbf @-rm -f testrealout.cbf @-rm -f testflatin.cbf @-rm -f testflatout.cbf @-rm -f testflatpackedin.cbf @-rm -f testflatpackedout.cbf @-rm -f CTC.cbf @-rm -f test_fcb_read_testflatout.out @-rm -f test_fcb_read_testflatpackedout.out @-rm -f test_xds_bin_testflatpackedout.out @-rm -f test_xds_bin_testflatout.out @-rm -f test_fcb_read_testflatout_orig.out @-rm -f test_fcb_read_testflatpackedout_orig.out @-rm -f test_xds_bin_testflatpackedout_orig.out @-rm -f test_xds_bin_testflatout_orig.out @-rm -f mb_LP_1_001.img @-rm -f 9ins.cif @-rm -f testcell_orig.prt @-rm -f $(DECTRIS_EXAMPLES)/cbf_template_t.out @-rm -f XRD1621.cbf @-rm -f XRD1621_orig.cbf @-rm -f XRD1621_orig.cbf @-rm -f XRD1621_I4encbC100.cbf @-rm -f $(SRC)/fcb_exit_binary.f90 @-rm -f $(SRC)/fcb_next_binary.f90 @-rm -f $(SRC)/fcb_open_cifin.f90 @-rm -f $(SRC)/fcb_packed.f90 @-rm -f $(SRC)/fcb_read_bits.f90 @-rm -f $(SRC)/fcb_read_image.f90 @-rm -f $(SRC)/fcb_read_xds_i2.f90 @-rm -f $(EXAMPLES)/test_fcb_read_image.f90 @-rm -f $(EXAMPLES)/test_xds_binary.f90 @-rm -f symlinksdone @-rm -f $(TESTOUTPUT) *$(SEXT) @-rm -f $(SOLIB)/*.o @-rm -f $(SOLIB)/libcbf_wrap.so @-rm -f $(SOLIB)/libjcbf.so @-rm -f $(SOLIB)/libimg.so @-rm -f $(SOLIB)/libfcb.so @-rm -rf $(JCBF)/org @-rm -f $(JCBF)/*.java @-rm -f $(JCBF)/jcbf_wrap.c @-rm -f $(SRC)/cbf_wrap.c @-rm -f $(BIN)/ctestcbf $(BIN)/testcbf.class testcbfc.txt testcbfj.txt @-rm -rf $(REGEX) @-rm -rf $(TIFF) ./.undosymlinks # # Remove temporary files # clean: @-rm -f core @-rm -f *.o @-rm -f *.u # # Restore to distribution state # distclean: clean empty # # Create a Tape Archive for distribution # tar: $(DOCUMENTS) $(SOURCE) $(SRC)/cbf.stx $(HEADERS) $(M4FILES)\ $(EXAMPLES) \ README.html README Makefile \ $(JPEGS) -/bin/rm -f CBFlib.tar* tar cvBf CBFlib.tar \ $(DOCUMENTS) $(SOURCE) $(SRC)/cbf.stx $(HEADERS) $(M4FILES)\ $(EXAMPLES) \ README.html README Makefile \ $(JPEGS) gzip --best CBFlib.tar ./CBFlib-0.9.2.2/template_adscquantum315_3072x3072.cbf0000777000076500007650000000000011603751102030221 2examples/template_adscquantum315_3072x3072.cbfustar yayayaya./CBFlib-0.9.2.2/template_pilatus6m_2463x2527.cbf0000777000076500007650000000000011603751102026553 2examples/template_pilatus6m_2463x2527.cbfustar yayayaya